From 5d963845bbc325471fd91c94b04ab40c5e589878 Mon Sep 17 00:00:00 2001 From: Fraser Dunlop Date: Mon, 10 Sep 2018 11:05:27 +0100 Subject: [PATCH 001/229] Abandoning SetOfSequences rep --- conjure-cp.cabal | 3 + fastbuild.sh | 1 + src/Conjure/Compute/DomainOf.hs | 3 +- src/Conjure/Language/AbstractLiteral.hs | 10 +++ src/Conjure/Language/Domain.hs | 32 ++++++++- src/Conjure/Language/Domain/AddAttributes.hs | 1 + src/Conjure/Language/Instantiate.hs | 14 ++++ src/Conjure/Language/Lexer.hs | 5 ++ src/Conjure/Language/Parser.hs | 35 ++++++++++ src/Conjure/Language/Type.hs | 5 ++ src/Conjure/Representations/Combined.hs | 7 ++ .../Permutation/AsSequences.hs | 67 +++++++++++++++++++ .../Rules/Vertical/Permutation/AsSequences.hs | 26 +++++++ src/Conjure/UI/Model.hs | 4 ++ .../parsing/01/permutation_given.essence | 11 +++ .../parsing/01/permutation_given.param | 1 + .../parsing/01/permutation_given.solution | 2 + tests/custom/permutations/parsing/01/run.sh | 3 + .../parsing/02/permutation_given.essence | 7 ++ .../parsing/02/permutation_given.param | 1 + tests/custom/permutations/parsing/02/run.sh | 3 + tests/custom/permutations/parsing/runthese.sh | 1 + 22 files changed, 239 insertions(+), 3 deletions(-) create mode 100644 fastbuild.sh create mode 100644 src/Conjure/Representations/Permutation/AsSequences.hs create mode 100644 src/Conjure/Rules/Vertical/Permutation/AsSequences.hs create mode 100644 tests/custom/permutations/parsing/01/permutation_given.essence create mode 100644 tests/custom/permutations/parsing/01/permutation_given.param create mode 100644 tests/custom/permutations/parsing/01/permutation_given.solution create mode 100755 tests/custom/permutations/parsing/01/run.sh create mode 100644 tests/custom/permutations/parsing/02/permutation_given.essence create mode 100644 tests/custom/permutations/parsing/02/permutation_given.param create mode 100755 tests/custom/permutations/parsing/02/run.sh create mode 100644 tests/custom/permutations/parsing/runthese.sh diff --git a/conjure-cp.cabal b/conjure-cp.cabal index 46c2b93e96..65f6c3a506 100644 --- a/conjure-cp.cabal +++ b/conjure-cp.cabal @@ -171,6 +171,7 @@ Library , Conjure.Representations.Relation.RelationAsSet , Conjure.Representations.Partition.Occurrence , Conjure.Representations.Partition.PartitionAsSet + , Conjure.Representations.Permutation.AsSequences -- definitions of rules , Conjure.Rules.Definition @@ -210,6 +211,8 @@ Library , Conjure.Rules.Vertical.Partition.PartitionAsSet , Conjure.Rules.Vertical.Partition.Occurrence + , Conjure.Rules.Vertical.Permutation.AsSequences + , Conjure.Rules.BubbleUp , Conjure.Rules.DontCare , Conjure.Rules.TildeOrdering diff --git a/fastbuild.sh b/fastbuild.sh new file mode 100644 index 0000000000..ad7bf59198 --- /dev/null +++ b/fastbuild.sh @@ -0,0 +1 @@ +stack build --fast diff --git a/src/Conjure/Compute/DomainOf.hs b/src/Conjure/Compute/DomainOf.hs index 76a2d9a710..f1280cb4df 100644 --- a/src/Conjure/Compute/DomainOf.hs +++ b/src/Conjure/Compute/DomainOf.hs @@ -291,12 +291,13 @@ instance DomainOf (AbstractLiteral Expression) where where attr = PartitionAttr (SizeAttr_MaxSize (fromInt $ genericLength xss)) (SizeAttr_MaxSize (fromInt $ maximum [genericLength xs | xs <- xss])) False - + domainOf (AbsLitPermutation xss) = DomainPermutation def def <$> (domainUnions =<< mapM domainOf (concat xss)) indexDomainsOf (AbsLitMatrix ind inn) = (ind :) <$> (mapM domainUnions =<< mapM indexDomainsOf inn) indexDomainsOf _ = return [] + -- all the `Op`s instance DomainOf (OpActive x) where diff --git a/src/Conjure/Language/AbstractLiteral.hs b/src/Conjure/Language/AbstractLiteral.hs index 930f1d8c63..019375c842 100644 --- a/src/Conjure/Language/AbstractLiteral.hs +++ b/src/Conjure/Language/AbstractLiteral.hs @@ -30,6 +30,7 @@ data AbstractLiteral x | AbsLitSequence [x] | AbsLitRelation [[x]] | AbsLitPartition [[x]] + | AbsLitPermutation [[x]] deriving (Eq, Ord, Show, Data, Functor, Traversable, Foldable, Typeable, Generic) instance Serialize x => Serialize (AbstractLiteral x) @@ -50,6 +51,7 @@ instance Pretty a => Pretty (AbstractLiteral a) where pretty (AbsLitSequence xs ) = "sequence" <> prettyList prParens "," xs pretty (AbsLitRelation xss) = "relation" <> prettyListDoc prParens "," [ pretty (AbsLitTuple xs) | xs <- xss ] pretty (AbsLitPartition xss) = "partition" <> prettyListDoc prParens "," [ prettyList prBraces "," xs | xs <- xss ] + pretty (AbsLitPermutation xss) = "permutation" <> prettyListDoc prParens "," [ prettyList prParens "," xs | xs <- xss ] instance (VarSymBreakingDescription x, ExpressionLike x) => VarSymBreakingDescription (AbstractLiteral x) where varSymBreakingDescription (AbsLitTuple xs) = JSON.Object $ M.fromList @@ -98,6 +100,11 @@ instance (VarSymBreakingDescription x, ExpressionLike x) => VarSymBreakingDescri , ("children", JSON.Array $ V.fromList $ map (varSymBreakingDescription . AbsLitSet) xs) , ("symmetricChildren", JSON.Bool True) ] + varSymBreakingDescription (AbsLitPermutation xs) = JSON.Object $ M.fromList + [ ("type", JSON.String "AbsLitPermutation") + , ("children", JSON.Array $ V.fromList $ map (varSymBreakingDescription . AbsLitSequence) xs) + , ("symmetricChildren", JSON.Bool True) + ] instance (TypeOf a, Pretty a) => TypeOf (AbstractLiteral a) where @@ -137,6 +144,7 @@ instance (TypeOf a, Pretty a) => TypeOf (AbstractLiteral a) where typeOf (AbsLitPartition [] ) = return (TypePartition TypeAny) typeOf p@(AbsLitPartition xss) = TypePartition <$> (homoType (pretty p) =<< mapM typeOf (concat xss)) + typeOf p@(AbsLitPermutation xss) = TypePermutation <$> (homoType (pretty p) =<< mapM typeOf (concat xss)) normaliseAbsLit :: (Ord c, ExpressionLike c) => (c -> c) -> AbstractLiteral c -> AbstractLiteral c @@ -150,6 +158,7 @@ normaliseAbsLit norm (AbsLitFunction xs ) = AbsLitFunction $ sortN normaliseAbsLit norm (AbsLitSequence xs ) = AbsLitSequence $ map norm xs normaliseAbsLit norm (AbsLitRelation xss) = AbsLitRelation $ sortNub $ map (map norm) xss normaliseAbsLit norm (AbsLitPartition xss) = AbsLitPartition $ sortNub $ map (sortNub . map norm) xss +normaliseAbsLit norm (AbsLitPermutation xss) = AbsLitPermutation $ map (map norm) xss emptyCollectionAbsLit :: AbstractLiteral c -> Bool emptyCollectionAbsLit AbsLitTuple{} = False @@ -162,3 +171,4 @@ emptyCollectionAbsLit (AbsLitFunction xs) = null xs emptyCollectionAbsLit (AbsLitSequence xs) = null xs emptyCollectionAbsLit (AbsLitRelation xs) = null xs emptyCollectionAbsLit (AbsLitPartition xs) = null xs +emptyCollectionAbsLit (AbsLitPermutation xs) = null xs diff --git a/src/Conjure/Language/Domain.hs b/src/Conjure/Language/Domain.hs index 961ee01954..e8ac4c4192 100644 --- a/src/Conjure/Language/Domain.hs +++ b/src/Conjure/Language/Domain.hs @@ -13,6 +13,7 @@ module Conjure.Language.Domain , SequenceAttr(..) , RelationAttr(..), BinaryRelationAttrs(..), BinaryRelationAttr(..) , PartitionAttr(..) + , PermutationAttr(..) , AttrName(..) , DomainAttributes(..), DomainAttribute(..) -- only for parsing , textToRepresentation, representationToShortText, representationToFullText @@ -71,6 +72,7 @@ data Domain r x | DomainSequence r (SequenceAttr x) (Domain r x) | DomainRelation r (RelationAttr x) [Domain r x] | DomainPartition r (PartitionAttr x) (Domain r x) + | DomainPermutation r (PermutationAttr x) (Domain r x) | DomainOp Name [Domain r x] | DomainReference Name (Maybe (Domain r x)) | DomainMetaVar String @@ -153,6 +155,7 @@ typeOfDomain (DomainFunction _ _ x y) = TypeFunction <$> typeOf x <*> typeOf typeOfDomain (DomainSequence _ _ x ) = TypeSequence <$> typeOf x typeOfDomain (DomainRelation _ _ xs ) = TypeRelation <$> mapM typeOf xs typeOfDomain (DomainPartition _ _ x ) = TypePartition <$> typeOf x +typeOfDomain (DomainPermutation _ _ x ) = TypePermutation <$> typeOf x typeOfDomain p@(DomainOp _ ds) = do ts <- mapM typeOfDomain ds if typesUnify ts @@ -191,8 +194,8 @@ changeRepr rep = go DomainSequence rep attr (go d) go (DomainRelation _ attr ds) = DomainRelation rep attr (map go ds) - go (DomainPartition _ attr d) = - DomainPartition rep attr (go d) + go (DomainPartition _ attr d) = DomainPartition rep attr (go d) + go (DomainPermutation _ attr d) = DomainPermutation rep attr (go d) go (DomainOp op ds) = DomainOp op (map go ds) go (DomainReference x r) = DomainReference x (fmap go r) go (DomainMetaVar x) = DomainMetaVar x @@ -243,6 +246,7 @@ reprTree (DomainFunction r _ a b) = Tree (Just r) [reprTree a, reprTree b] reprTree (DomainSequence r _ a ) = Tree (Just r) [reprTree a] reprTree (DomainRelation r _ as ) = Tree (Just r) (map reprTree as) reprTree (DomainPartition r _ a ) = Tree (Just r) [reprTree a] +reprTree (DomainPermutation r _ a) = Tree (Just r) [reprTree a] reprTree DomainOp{} = Tree Nothing [] reprTree DomainReference{} = Tree Nothing [] reprTree DomainMetaVar{} = Tree Nothing [] @@ -268,6 +272,7 @@ applyReprTree (DomainFunction _ attr a b) (Tree (Just r) [aRepr, bRepr]) = Doma applyReprTree (DomainSequence _ attr a ) (Tree (Just r) [aRepr]) = DomainSequence r attr <$> applyReprTree a aRepr applyReprTree (DomainRelation _ attr as ) (Tree (Just r) asRepr) = DomainRelation r attr <$> zipWithM applyReprTree as asRepr applyReprTree (DomainPartition _ attr a ) (Tree (Just r) [aRepr]) = DomainPartition r attr <$> applyReprTree a aRepr +applyReprTree (DomainPermutation _ attr a ) (Tree (Just r) [aRepr]) = DomainPermutation r attr <$> applyReprTree a aRepr applyReprTree dom@DomainOp{} (Tree Nothing []) = return (defRepr dom) applyReprTree dom@DomainReference{} (Tree Nothing []) = return (defRepr dom) applyReprTree dom@DomainMetaVar{} (Tree Nothing []) = return (defRepr dom) @@ -680,6 +685,25 @@ instance Pretty a => Pretty (PartitionAttr a) where else prettyList prParens "," inside + +data PermutationAttr x + = PermutationAttr (SizeAttr x) + deriving (Eq, Ord, Show, Data, Functor, Traversable, Foldable, Typeable, Generic) +instance Serialize a => Serialize (PermutationAttr a) +instance Hashable a => Hashable (PermutationAttr a) +instance ToJSON a => ToJSON (PermutationAttr a) where toJSON = genericToJSON jsonOptions +instance FromJSON a => FromJSON (PermutationAttr a) where parseJSON = genericParseJSON jsonOptions +instance Default (PermutationAttr a) where def = PermutationAttr def +instance Pretty a => Pretty (PermutationAttr a) where + pretty (PermutationAttr a ) = + let inside = filter (/=prEmpty) [pretty a] + in if null inside + then prEmpty + else prettyList prParens "," inside + + + + data DomainAttributes a = DomainAttributes [DomainAttribute a] deriving (Eq, Ord, Show, Data, Functor, Traversable, Foldable, Typeable, Generic) @@ -771,6 +795,7 @@ data HasRepresentation | Partition_AsSet HasRepresentation HasRepresentation -- carries: representations for the inner sets | Partition_Occurrence + | Permutation_AsSequences deriving (Eq, Ord, Show, Data, Typeable, Generic) @@ -841,6 +866,7 @@ instance (Pretty r, Pretty a) => Pretty (Domain r a) where pretty (DomainPartition r attrs inner) = hang ("partition" <+> prettyAttrs r attrs <+> "from") 4 (pretty inner) + pretty (DomainPermutation r attrs inner) = hang ("permutation" <+> prettyAttrs r attrs <+> "from") 4 (pretty inner) pretty d@DomainOp{} = pretty (show d) @@ -895,6 +921,7 @@ textToRepresentation t [] | t == "RelationAsMatrix" = retu textToRepresentation t [repr] | t == "RelationAsSet" = return (Relation_AsSet repr) textToRepresentation t [repr1, repr2] | t == "PartitionAsSet" = return (Partition_AsSet repr1 repr2) textToRepresentation t [] | t == "PartitionOccurrence" = return Partition_Occurrence +textToRepresentation t [] | t == "PermutationAsSequences" = return Permutation_AsSequences textToRepresentation t _ = bug ("textToRepresentation:" <+> pretty t) representationToShortText :: HasRepresentation -> Text @@ -915,6 +942,7 @@ representationToShortText Relation_AsMatrix = "RelationAsMatrix" representationToShortText Relation_AsSet{} = "RelationAsSet" representationToShortText Partition_AsSet{} = "PartitionAsSet" representationToShortText Partition_Occurrence = "PartitionOccurrence" +representationToShortText Permutation_AsSequences = "PermutationAsSequences" representationToShortText r = bug ("representationToShortText:" <+> pretty (show r)) representationToFullText :: HasRepresentation -> Text diff --git a/src/Conjure/Language/Domain/AddAttributes.hs b/src/Conjure/Language/Domain/AddAttributes.hs index 652805acd4..e6e173c23b 100644 --- a/src/Conjure/Language/Domain/AddAttributes.hs +++ b/src/Conjure/Language/Domain/AddAttributes.hs @@ -84,6 +84,7 @@ addAttributeToDomain d@DomainMatrix{} = const $ const $ return d addAttributeToDomain d@DomainOp{} = const $ const $ return d addAttributeToDomain d@DomainReference{} = const $ const $ return d addAttributeToDomain d@DomainMetaVar{} = const $ const $ return d +addAttributeToDomain d@DomainPermutation{} = const $ const $ return d addAttributeToDomain domain@(DomainSet r (SetAttr sizeAttr) inner) = updater where updater attr (Just val) = case attr of diff --git a/src/Conjure/Language/Instantiate.hs b/src/Conjure/Language/Instantiate.hs index 2ba1bc3ef3..6ea90f3f5a 100644 --- a/src/Conjure/Language/Instantiate.hs +++ b/src/Conjure/Language/Instantiate.hs @@ -262,6 +262,7 @@ instantiateD (DomainFunction r attrs innerFr innerTo) = DomainFunction r <$> in instantiateD (DomainSequence r attrs inner) = DomainSequence r <$> instantiateSequenceAttr attrs <*> instantiateD inner instantiateD (DomainRelation r attrs inners) = DomainRelation r <$> instantiateRelationAttr attrs <*> mapM instantiateD inners instantiateD (DomainPartition r attrs inner) = DomainPartition r <$> instantiatePartitionAttr attrs <*> instantiateD inner +instantiateD (DomainPermutation r attrs inner) = DomainPermutation r <$> instantiatePermutationAttr attrs <*> instantiateD inner instantiateD (DomainOp nm ds) = DomainOp nm <$> mapM instantiateD ds instantiateD (DomainReference _ (Just d)) = instantiateD d instantiateD (DomainReference name Nothing) = do @@ -373,6 +374,19 @@ instantiatePartitionAttr (PartitionAttr a b r) = <*> pure r +instantiatePermutationAttr + :: ( MonadFail m + , MonadUserError m + , MonadState [(Name, Expression)] m + , EnumerateDomain m + ) + => PermutationAttr Expression + -> m (PermutationAttr Constant) +instantiatePermutationAttr (PermutationAttr s) = + PermutationAttr <$> instantiateSizeAttr s + + + instantiateR :: ( MonadFail m , MonadUserError m diff --git a/src/Conjure/Language/Lexer.hs b/src/Conjure/Language/Lexer.hs index 474a8e06f6..a6d6ef7254 100644 --- a/src/Conjure/Language/Lexer.hs +++ b/src/Conjure/Language/Lexer.hs @@ -116,6 +116,9 @@ data Lexeme | L_minNumParts | L_maxNumParts + -- type: permutation + | L_permutation + -- operators, page 21 of the holy paper | L_union | L_intersect @@ -354,6 +357,8 @@ lexemes = sortBy (flip (comparing (T.length . fst))) $ map swap , ( L_sequence, "sequence" ) , ( L_relation, "relation" ) , ( L_partition, "partition" ) + + , ( L_permutation, "permutation" ) -- , ( L_regular, "regular" ) -- , ( L_partSize, "partSize" ) -- , ( L_minPartSize, "minPartSize" ) diff --git a/src/Conjure/Language/Parser.hs b/src/Conjure/Language/Parser.hs index 3dce603fbb..9a2fb0cc6b 100644 --- a/src/Conjure/Language/Parser.hs +++ b/src/Conjure/Language/Parser.hs @@ -252,6 +252,7 @@ parseDomainWithRepr = pDomainAtom , pSequence , pRelation , pPartition + , pPermutation , DomainMetaVar <$> parseMetaVariable, parens parseDomainWithRepr ] @@ -390,6 +391,13 @@ parseDomainWithRepr = pDomainAtom lexeme L_from y <- parseDomainWithRepr return $ DomainPartition r x y + pPermutation = do + lexeme L_permutation + r <- parseRepr + x <- parsePermutationAttr + lexeme L_of -- $ trace (textToString $ representationToShortText r) L_of + y <- parseDomainWithRepr + return $ DomainPermutation r x y parseAttributes :: Parser (DomainAttributes Expression) parseAttributes = do @@ -573,6 +581,26 @@ parsePartitionAttr = do return PartitionAttr {..} +parsePermutationAttr :: Parser (PermutationAttr Expression) +parsePermutationAttr = do + pos <- getPosition + DomainAttributes attrs <- parseAttributes + checkExtraAttributes pos "permutation" attrs + [ "size", "minSize", "maxSize" + ] + size <- case filterSizey attrs of + [DANameValue "size" a] -> return (SizeAttr_Size a) + [DANameValue "minSize" a] -> return (SizeAttr_MinSize a) + [DANameValue "maxSize" a] -> return (SizeAttr_MaxSize a) + [DANameValue "maxSize" b, DANameValue "minSize" a] -> return (SizeAttr_MinMaxSize a b) + [] -> return SizeAttr_None + as -> do + setPosition pos + fail ("incompatible attributes:" <+> stringToDoc (show as)) + return (PermutationAttr size) + + + checkExtraAttributes :: SourcePos -> Doc -> [DomainAttribute a] -> [Name] -> Parser () checkExtraAttributes pos ty attrs supported = do let extras = mapMaybe f attrs @@ -885,6 +913,7 @@ parseLiteral = label "value" $ msum , mkAbstractLiteral <$> pSequence , mkAbstractLiteral <$> pRelation , mkAbstractLiteral <$> pPartition + , mkAbstractLiteral <$> pPermutation ] where @@ -977,6 +1006,12 @@ parseLiteral = label "value" $ msum return (AbsLitPartition xs) where inner = braces (commaSeparated0 parseExpr) + pPermutation = do + lexeme L_permutation + xs <- parens (commaSeparated0 inner) + return (AbsLitPermutation xs) + where + inner = parens (commaSeparated0 parseExpr) diff --git a/src/Conjure/Language/Type.hs b/src/Conjure/Language/Type.hs index 80c52be432..895a8eb730 100644 --- a/src/Conjure/Language/Type.hs +++ b/src/Conjure/Language/Type.hs @@ -35,6 +35,7 @@ data Type | TypeSequence Type | TypeRelation [Type] | TypePartition Type + | TypePermutation Type deriving (Eq, Ord, Show, Data, Typeable, Generic) instance Serialize Type @@ -68,6 +69,7 @@ instance Pretty Type where pretty (TypeSequence x) = "sequence of" <+> pretty x pretty (TypePartition x) = "partition from" <+> pretty x pretty (TypeRelation xs) = "relation of" <+> prettyList prParens " *" xs + pretty (TypePermutation x) = "permutation of" <+> pretty x -- | Check whether two types unify or not. typeUnify :: Type -> Type -> Bool @@ -110,6 +112,7 @@ typeUnify (TypeRelation [TypeAny]) TypeRelation{} = True -- also typeUnify TypeRelation{} (TypeRelation [TypeAny]) = True typeUnify (TypeRelation as) (TypeRelation bs) = (length as == length bs) && and (zipWith typeUnify as bs) typeUnify (TypePartition a) (TypePartition b) = typeUnify a b +typeUnify (TypePermutation a) (TypePermutation b) = typeUnify a b typeUnify _ _ = False -- | Check whether a given list of types unify with each other or not. @@ -162,6 +165,7 @@ mostDefined = foldr f TypeAny f x (TypeRelation [TypeAny]) = x f (TypeRelation as) (TypeRelation bs) | length as == length bs = TypeRelation (zipWith f as bs) f (TypePartition a) (TypePartition b) = TypePartition (f a b) + f (TypePermutation a) (TypePermutation b) = TypePermutation (f a b) f _ _ = TypeAny matrixNumDims :: Type -> Int @@ -187,6 +191,7 @@ innerTypeOf (TypeFunction a b) = return (TypeTuple [a,b]) innerTypeOf (TypeSequence t) = return (TypeTuple [TypeInt,t]) innerTypeOf (TypeRelation ts) = return (TypeTuple ts) innerTypeOf (TypePartition t) = return (TypeSet t) +innerTypeOf (TypePermutation t) = return (TypePermutation t) innerTypeOf t = fail ("innerTypeOf:" <+> pretty (show t)) isPrimitiveType :: Type -> Bool diff --git a/src/Conjure/Representations/Combined.hs b/src/Conjure/Representations/Combined.hs index f262a2c8d8..c517a5b270 100644 --- a/src/Conjure/Representations/Combined.hs +++ b/src/Conjure/Representations/Combined.hs @@ -36,6 +36,7 @@ import Conjure.Representations.Relation.RelationAsMatrix import Conjure.Representations.Relation.RelationAsSet import Conjure.Representations.Partition.Occurrence import Conjure.Representations.Partition.PartitionAsSet +import Conjure.Representations.Permutation.AsSequences -- | Refine (down) a domain, outputting refinement expressions (X) one level (1). @@ -181,6 +182,9 @@ dispatch domain = do (bug "reprOptions inside dispatch") (bug "useLevels inside dispatch") _ -> nope + DomainPermutation r _ _ -> case r of + Permutation_AsSequences -> permutationAsSequences + _ -> nope _ -> nope @@ -201,6 +205,7 @@ reprsStandardOrderNoLevels = return $ concat , relationAsMatrix , partitionAsSet dispatch (reprOptions reprsStandardOrderNoLevels) False , partitionOccurrence + , permutationAsSequences ] , [ functionAsRelation dispatch (reprOptions reprsStandardOrderNoLevels) , relationAsSet dispatch (reprOptions reprsStandardOrderNoLevels) False @@ -224,6 +229,7 @@ reprsStandardOrder = , relationAsMatrix , partitionAsSet dispatch (reprOptions reprsStandardOrder) True , partitionOccurrence + , permutationAsSequences ] , [ functionAsRelation dispatch (reprOptions reprsStandardOrder) , relationAsSet dispatch (reprOptions reprsStandardOrder) True @@ -254,6 +260,7 @@ reprsSparseOrder = map return , partitionAsSet dispatch (reprOptions reprsSparseOrder) False , partitionOccurrence -- redundant + , permutationAsSequences ] diff --git a/src/Conjure/Representations/Permutation/AsSequences.hs b/src/Conjure/Representations/Permutation/AsSequences.hs new file mode 100644 index 0000000000..8ee5d474fc --- /dev/null +++ b/src/Conjure/Representations/Permutation/AsSequences.hs @@ -0,0 +1,67 @@ +{-# LANGUAGE RecordWildCards #-} +{-# LANGUAGE QuasiQuotes #-} +{-# LANGUAGE ViewPatterns #-} + +module Conjure.Representations.Permutation.AsSequences ( permutationAsSequences ) where + +-- conjure +import Conjure.Prelude +import Conjure.Bug +import Conjure.Language +import Conjure.Language.DomainSizeOf +import Conjure.Language.Expression.DomainSizeOf () +import Conjure.Language.ZeroVal ( zeroVal, EnumerateDomain ) +import Conjure.Representations.Internal +import Conjure.Representations.Common +import Conjure.Representations.Function.Function1D ( domainValues ) + +permutationAsSequences :: forall m . (MonadFail m, NameGen m, EnumerateDomain m) => Representation m +permutationAsSequences = Representation chck downD structuralCons downC up + where + chck :: TypeOf_ReprCheck m + chck f (DomainPermutation _ s innerDomain) + | domainCanIndexMatrix innerDomain + = map (DomainPermutation Permutation_AsSequences s) <$> f innerDomain + chck _ _ = return [] + + downD :: TypeOf_DownD m + downD (name, domain@(DomainPermutation Permutation_AsSequences _ innerDomain)) + | domainCanIndexMatrix innerDomain = do + --TODO do calc on m and permutation size attribute + m <- domainSizeOf innerDomain + return $ Just + [ ( mkOutName (Just "SetOfSequences") domain name + , DomainSet Set_ExplicitVarSizeWithFlags (SetAttr (SizeAttr_MaxSize m)) + (DomainSequence Sequence_ExplicitBounded + (SequenceAttr (SizeAttr_MaxSize m) JectivityAttr_None) innerDomain) + ) + ] + downD (_, domain@(DomainPermutation r _ _)) = trace (textToString (representationToShortText r)) $ na "{downD} AsSequences" + + downD _ = na "{downD} AsSequences" + + structuralCons :: TypeOf_Structural m + structuralCons f downX1 indom@(DomainPermutation _ _ inner) + = return $ \p -> do + refs <- downX1 p + case refsof + [set] -> do + outDomSet <- outDomainSet inDom + innerStructuralConsGenSet <- f outDomSet + --define quantifieds + concat <$> sequence + [ innerStructuralConsGenSet set + , return [[essence| + forAll (&seqAPat, &seqBPat) in set . + forAll &i : inner . + &i in &seqAPat <-> !(&i in &seqBPat) + |] + ] + ] + + downC :: TypeOf_DownC m + downC = error "partitionAsSequence downC not defined" + + up :: TypeOf_Up m + up = error "partitionAsSequence up not defined" + diff --git a/src/Conjure/Rules/Vertical/Permutation/AsSequences.hs b/src/Conjure/Rules/Vertical/Permutation/AsSequences.hs new file mode 100644 index 0000000000..5ee2a0a31c --- /dev/null +++ b/src/Conjure/Rules/Vertical/Permutation/AsSequences.hs @@ -0,0 +1,26 @@ +{-# LANGUAGE QuasiQuotes #-} + +module Conjure.Rules.Vertical.Permutation.AsSequences where + +import Conjure.Rules.Import + + +rule_Comprehension :: Rule +rule_Comprehension = "permutation-comprehension{AsSequences}" `namedRule` theRule where + theRule (Comprehension body gensOrConds) = do + (gocBefore, (pat, perm), gocAfter) <- matchFirst gensOrConds $ \ goc -> case goc of + Generator (GenInExpr pat@Single{} expr) -> return (pat, matchDefs [opToSet, opToMSet] expr) + _ -> na "rule_Comprehension" + TypePermutation{} <- typeOf perm + Permutation_AsSequences <- representationOf perm + [setOfSequences] <- downX1 perm + return + ( "Vertical rule for permutation-comprehension, AsSequences representation" + , do + return $ Comprehension body + $ gocBefore + ++ [ Generator (GenInExpr pat setOfSequences) + ] + ++ gocAfter + ) + theRule _ = na "rule_Comprehension" diff --git a/src/Conjure/UI/Model.hs b/src/Conjure/UI/Model.hs index 7a88e22896..7326712115 100644 --- a/src/Conjure/UI/Model.hs +++ b/src/Conjure/UI/Model.hs @@ -86,6 +86,8 @@ import qualified Conjure.Rules.Horizontal.Partition as Horizontal.Partition import qualified Conjure.Rules.Vertical.Partition.PartitionAsSet as Vertical.Partition.PartitionAsSet import qualified Conjure.Rules.Vertical.Partition.Occurrence as Vertical.Partition.Occurrence +import qualified Conjure.Rules.Vertical.Permutation.AsSequences as Vertical.Permutation.AsSequences + import qualified Conjure.Rules.BubbleUp as BubbleUp import qualified Conjure.Rules.DontCare as DontCare import qualified Conjure.Rules.TildeOrdering as TildeOrdering @@ -1134,6 +1136,8 @@ verticalRules = , Vertical.Partition.PartitionAsSet.rule_Comprehension , Vertical.Partition.Occurrence.rule_Comprehension + , Vertical.Permutation.AsSequences.rule_Comprehension + ] horizontalRules :: [Rule] diff --git a/tests/custom/permutations/parsing/01/permutation_given.essence b/tests/custom/permutations/parsing/01/permutation_given.essence new file mode 100644 index 0000000000..6223624be1 --- /dev/null +++ b/tests/custom/permutations/parsing/01/permutation_given.essence @@ -0,0 +1,11 @@ + +$ given n : int +letting n be 4 + +$given p : permutation of int(1..n) + +$letting p be permutation((1,3),(2,4)) + +find p : permutation of int(1..n) + + diff --git a/tests/custom/permutations/parsing/01/permutation_given.param b/tests/custom/permutations/parsing/01/permutation_given.param new file mode 100644 index 0000000000..8c41c9b747 --- /dev/null +++ b/tests/custom/permutations/parsing/01/permutation_given.param @@ -0,0 +1 @@ +letting p be permutation((1,3),(2,1)) diff --git a/tests/custom/permutations/parsing/01/permutation_given.solution b/tests/custom/permutations/parsing/01/permutation_given.solution new file mode 100644 index 0000000000..fa3c1c5e86 --- /dev/null +++ b/tests/custom/permutations/parsing/01/permutation_given.solution @@ -0,0 +1,2 @@ +language Essence 1.3 + diff --git a/tests/custom/permutations/parsing/01/run.sh b/tests/custom/permutations/parsing/01/run.sh new file mode 100755 index 0000000000..3ff6233922 --- /dev/null +++ b/tests/custom/permutations/parsing/01/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence *.param +cat conjure-output/*.solution +#rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/parsing/02/permutation_given.essence b/tests/custom/permutations/parsing/02/permutation_given.essence new file mode 100644 index 0000000000..c64c004178 --- /dev/null +++ b/tests/custom/permutations/parsing/02/permutation_given.essence @@ -0,0 +1,7 @@ + +$ given n : int +letting n be 3 + +given p : permutation of int(1..n) + +such that true diff --git a/tests/custom/permutations/parsing/02/permutation_given.param b/tests/custom/permutations/parsing/02/permutation_given.param new file mode 100644 index 0000000000..2099896d75 --- /dev/null +++ b/tests/custom/permutations/parsing/02/permutation_given.param @@ -0,0 +1 @@ +letting p be permutation((1,3,2)) diff --git a/tests/custom/permutations/parsing/02/run.sh b/tests/custom/permutations/parsing/02/run.sh new file mode 100755 index 0000000000..e4c2a2c644 --- /dev/null +++ b/tests/custom/permutations/parsing/02/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence *.essence +cat conjure-output/*.solution +#rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/parsing/runthese.sh b/tests/custom/permutations/parsing/runthese.sh new file mode 100644 index 0000000000..fa4c1234c8 --- /dev/null +++ b/tests/custom/permutations/parsing/runthese.sh @@ -0,0 +1 @@ +stack test --fast --test-arguments "-p custom.permutations.parsing" From 432b4cbff217d0294215b6e9c4dc006b39f244e5 Mon Sep 17 00:00:00 2001 From: Fraser Dunlop Date: Mon, 10 Sep 2018 11:43:20 +0100 Subject: [PATCH 002/229] Some sketching of Function repr --- conjure-cp.cabal | 5 +- src/Conjure/Language/Domain.hs | 6 +- src/Conjure/Representations/Combined.hs | 10 +-- .../Representations/Permutation/AsFunction.hs | 53 +++++++++++++++ .../Permutation/AsSequences.hs | 67 ------------------- src/Conjure/Rules/Horizontal/Permutation.hs | 27 ++++++++ .../Rules/Vertical/Permutation/AsFunction.hs | 35 ++++++++++ .../Rules/Vertical/Permutation/AsSequences.hs | 26 ------- src/Conjure/UI/Model.hs | 4 +- 9 files changed, 128 insertions(+), 105 deletions(-) create mode 100644 src/Conjure/Representations/Permutation/AsFunction.hs delete mode 100644 src/Conjure/Representations/Permutation/AsSequences.hs create mode 100644 src/Conjure/Rules/Horizontal/Permutation.hs create mode 100644 src/Conjure/Rules/Vertical/Permutation/AsFunction.hs delete mode 100644 src/Conjure/Rules/Vertical/Permutation/AsSequences.hs diff --git a/conjure-cp.cabal b/conjure-cp.cabal index 65f6c3a506..be4f20480a 100644 --- a/conjure-cp.cabal +++ b/conjure-cp.cabal @@ -171,7 +171,7 @@ Library , Conjure.Representations.Relation.RelationAsSet , Conjure.Representations.Partition.Occurrence , Conjure.Representations.Partition.PartitionAsSet - , Conjure.Representations.Permutation.AsSequences + , Conjure.Representations.Permutation.AsFunction -- definitions of rules , Conjure.Rules.Definition @@ -211,7 +211,8 @@ Library , Conjure.Rules.Vertical.Partition.PartitionAsSet , Conjure.Rules.Vertical.Partition.Occurrence - , Conjure.Rules.Vertical.Permutation.AsSequences + , Conjure.Rules.Horizontal.Permutation + , Conjure.Rules.Vertical.Permutation.AsFunction , Conjure.Rules.BubbleUp , Conjure.Rules.DontCare diff --git a/src/Conjure/Language/Domain.hs b/src/Conjure/Language/Domain.hs index e8ac4c4192..40cdce06e6 100644 --- a/src/Conjure/Language/Domain.hs +++ b/src/Conjure/Language/Domain.hs @@ -795,7 +795,7 @@ data HasRepresentation | Partition_AsSet HasRepresentation HasRepresentation -- carries: representations for the inner sets | Partition_Occurrence - | Permutation_AsSequences + | Permutation_AsFunction deriving (Eq, Ord, Show, Data, Typeable, Generic) @@ -921,7 +921,7 @@ textToRepresentation t [] | t == "RelationAsMatrix" = retu textToRepresentation t [repr] | t == "RelationAsSet" = return (Relation_AsSet repr) textToRepresentation t [repr1, repr2] | t == "PartitionAsSet" = return (Partition_AsSet repr1 repr2) textToRepresentation t [] | t == "PartitionOccurrence" = return Partition_Occurrence -textToRepresentation t [] | t == "PermutationAsSequences" = return Permutation_AsSequences +textToRepresentation t [] | t == "PermutationAsFunction" = return Permutation_AsFunction textToRepresentation t _ = bug ("textToRepresentation:" <+> pretty t) representationToShortText :: HasRepresentation -> Text @@ -942,7 +942,7 @@ representationToShortText Relation_AsMatrix = "RelationAsMatrix" representationToShortText Relation_AsSet{} = "RelationAsSet" representationToShortText Partition_AsSet{} = "PartitionAsSet" representationToShortText Partition_Occurrence = "PartitionOccurrence" -representationToShortText Permutation_AsSequences = "PermutationAsSequences" +representationToShortText Permutation_AsFunction = "PermutationAsFunction" representationToShortText r = bug ("representationToShortText:" <+> pretty (show r)) representationToFullText :: HasRepresentation -> Text diff --git a/src/Conjure/Representations/Combined.hs b/src/Conjure/Representations/Combined.hs index c517a5b270..b60986ab05 100644 --- a/src/Conjure/Representations/Combined.hs +++ b/src/Conjure/Representations/Combined.hs @@ -36,7 +36,7 @@ import Conjure.Representations.Relation.RelationAsMatrix import Conjure.Representations.Relation.RelationAsSet import Conjure.Representations.Partition.Occurrence import Conjure.Representations.Partition.PartitionAsSet -import Conjure.Representations.Permutation.AsSequences +import Conjure.Representations.Permutation.AsFunction -- | Refine (down) a domain, outputting refinement expressions (X) one level (1). @@ -183,7 +183,7 @@ dispatch domain = do (bug "useLevels inside dispatch") _ -> nope DomainPermutation r _ _ -> case r of - Permutation_AsSequences -> permutationAsSequences + Permutation_AsFunction -> permutationAsFunction _ -> nope _ -> nope @@ -205,7 +205,7 @@ reprsStandardOrderNoLevels = return $ concat , relationAsMatrix , partitionAsSet dispatch (reprOptions reprsStandardOrderNoLevels) False , partitionOccurrence - , permutationAsSequences + , permutationAsFunction ] , [ functionAsRelation dispatch (reprOptions reprsStandardOrderNoLevels) , relationAsSet dispatch (reprOptions reprsStandardOrderNoLevels) False @@ -229,7 +229,7 @@ reprsStandardOrder = , relationAsMatrix , partitionAsSet dispatch (reprOptions reprsStandardOrder) True , partitionOccurrence - , permutationAsSequences + , permutationAsFunction ] , [ functionAsRelation dispatch (reprOptions reprsStandardOrder) , relationAsSet dispatch (reprOptions reprsStandardOrder) True @@ -260,7 +260,7 @@ reprsSparseOrder = map return , partitionAsSet dispatch (reprOptions reprsSparseOrder) False , partitionOccurrence -- redundant - , permutationAsSequences + , permutationAsFunction ] diff --git a/src/Conjure/Representations/Permutation/AsFunction.hs b/src/Conjure/Representations/Permutation/AsFunction.hs new file mode 100644 index 0000000000..4d9ddf6567 --- /dev/null +++ b/src/Conjure/Representations/Permutation/AsFunction.hs @@ -0,0 +1,53 @@ +{-# LANGUAGE RecordWildCards #-} +{-# LANGUAGE QuasiQuotes #-} +{-# LANGUAGE ViewPatterns #-} + +module Conjure.Representations.Permutation.AsFunction ( permutationAsFunction ) where + +-- conjure +import Conjure.Prelude +import Conjure.Bug +import Conjure.Language +import Conjure.Language.DomainSizeOf +import Conjure.Language.Expression.DomainSizeOf () +import Conjure.Language.ZeroVal ( zeroVal, EnumerateDomain ) +import Conjure.Representations.Internal +import Conjure.Representations.Common +import Conjure.Representations.Function.Function1D ( domainValues ) + +permutationAsFunction :: forall m . (MonadFail m, NameGen m, EnumerateDomain m) => Representation m +permutationAsFunction = Representation chck downD structuralCons downC up + where + chck :: TypeOf_ReprCheck m + chck f (DomainPermutation _ s innerDomain) + | domainCanIndexMatrix innerDomain + = map (DomainPermutation Permutation_AsFunction s) <$> f innerDomain + chck _ _ = return [] + + downD :: TypeOf_DownD m + downD (name, domain@(DomainPermutation Permutation_AsFunction _ innerDomain)) + | domainCanIndexMatrix innerDomain = do + --TODO do calc on m and permutation size attribute + m <- domainSizeOf innerDomain + return $ Just + [ ( mkOutName (Just "PermutationFunction") domain name + , DomainFunction (Function_AsRelation Relation_AsMatrix) (FunctionAttr (SizeAttr_MaxSize m) PartialityAttr_Total JectivityAttr_Bijective) innerDomain innerDomain + ) + ] + downD (_, domain@(DomainPermutation r _ _)) = trace (textToString (representationToShortText r)) $ na "{downD} AsFunction" + + downD _ = na "{downD} AsFunction" + + structuralCons :: TypeOf_Structural m + structuralCons f downX1 indom@(DomainPermutation _ _ inner) + = return $ \p -> do + refs <- downX1 p + case refs of + [f] -> error "partitionAsFunction structuralCons not defined" + + downC :: TypeOf_DownC m + downC = error "partitionAsFunction downC not defined" + + up :: TypeOf_Up m + up = error "partitionAsFunction up not defined" + diff --git a/src/Conjure/Representations/Permutation/AsSequences.hs b/src/Conjure/Representations/Permutation/AsSequences.hs deleted file mode 100644 index 8ee5d474fc..0000000000 --- a/src/Conjure/Representations/Permutation/AsSequences.hs +++ /dev/null @@ -1,67 +0,0 @@ -{-# LANGUAGE RecordWildCards #-} -{-# LANGUAGE QuasiQuotes #-} -{-# LANGUAGE ViewPatterns #-} - -module Conjure.Representations.Permutation.AsSequences ( permutationAsSequences ) where - --- conjure -import Conjure.Prelude -import Conjure.Bug -import Conjure.Language -import Conjure.Language.DomainSizeOf -import Conjure.Language.Expression.DomainSizeOf () -import Conjure.Language.ZeroVal ( zeroVal, EnumerateDomain ) -import Conjure.Representations.Internal -import Conjure.Representations.Common -import Conjure.Representations.Function.Function1D ( domainValues ) - -permutationAsSequences :: forall m . (MonadFail m, NameGen m, EnumerateDomain m) => Representation m -permutationAsSequences = Representation chck downD structuralCons downC up - where - chck :: TypeOf_ReprCheck m - chck f (DomainPermutation _ s innerDomain) - | domainCanIndexMatrix innerDomain - = map (DomainPermutation Permutation_AsSequences s) <$> f innerDomain - chck _ _ = return [] - - downD :: TypeOf_DownD m - downD (name, domain@(DomainPermutation Permutation_AsSequences _ innerDomain)) - | domainCanIndexMatrix innerDomain = do - --TODO do calc on m and permutation size attribute - m <- domainSizeOf innerDomain - return $ Just - [ ( mkOutName (Just "SetOfSequences") domain name - , DomainSet Set_ExplicitVarSizeWithFlags (SetAttr (SizeAttr_MaxSize m)) - (DomainSequence Sequence_ExplicitBounded - (SequenceAttr (SizeAttr_MaxSize m) JectivityAttr_None) innerDomain) - ) - ] - downD (_, domain@(DomainPermutation r _ _)) = trace (textToString (representationToShortText r)) $ na "{downD} AsSequences" - - downD _ = na "{downD} AsSequences" - - structuralCons :: TypeOf_Structural m - structuralCons f downX1 indom@(DomainPermutation _ _ inner) - = return $ \p -> do - refs <- downX1 p - case refsof - [set] -> do - outDomSet <- outDomainSet inDom - innerStructuralConsGenSet <- f outDomSet - --define quantifieds - concat <$> sequence - [ innerStructuralConsGenSet set - , return [[essence| - forAll (&seqAPat, &seqBPat) in set . - forAll &i : inner . - &i in &seqAPat <-> !(&i in &seqBPat) - |] - ] - ] - - downC :: TypeOf_DownC m - downC = error "partitionAsSequence downC not defined" - - up :: TypeOf_Up m - up = error "partitionAsSequence up not defined" - diff --git a/src/Conjure/Rules/Horizontal/Permutation.hs b/src/Conjure/Rules/Horizontal/Permutation.hs new file mode 100644 index 0000000000..9c7b3f7103 --- /dev/null +++ b/src/Conjure/Rules/Horizontal/Permutation.hs @@ -0,0 +1,27 @@ +{-# LANGUAGE QuasiQuotes #-} + +module Conjure.Rules.Horizontal.Permutation where + +import Conjure.Rules.Import +import Conjure.Rules.Definition + +-- uniplate +import Data.Generics.Uniplate.Zipper as Zipper ( up, hole ) + + +-- | want this to be +-- [_ | (i, j) <- compose(f, g) +-- , ...] +-- becomes +-- [_ | i : int(1..10) +-- , g(i) in defined(f) +-- , letting j be f(g(i)) +-- ] +rule_Composition_Comprehension :: Rule +rule_Composition_Comprehension = + error "permutation: rule_Composition_Comprehension not defined yet" + + + + + diff --git a/src/Conjure/Rules/Vertical/Permutation/AsFunction.hs b/src/Conjure/Rules/Vertical/Permutation/AsFunction.hs new file mode 100644 index 0000000000..fd86dd9a75 --- /dev/null +++ b/src/Conjure/Rules/Vertical/Permutation/AsFunction.hs @@ -0,0 +1,35 @@ +{-# LANGUAGE QuasiQuotes #-} + +module Conjure.Rules.Vertical.Permutation.AsFunction where + +import Conjure.Rules.Import + +-- | This just unwraps the function in a comprehension +-- Just like having the bare bijective total function in the comprehension +-- +-- unclear if this should stay but it is here for now +rule_Comprehension :: Rule +rule_Comprehension = "permutation-comprehension{AsFunction}" `namedRule` theRule where + theRule (Comprehension body gensOrConds) = do + (gocBefore, (pat, perm), gocAfter) <- matchFirst gensOrConds $ \ goc -> case goc of + Generator (GenInExpr pat@Single{} expr) -> return (pat, matchDefs [opToSet, opToMSet] expr) + _ -> na "rule_Comprehension" + TypePermutation{} <- typeOf perm + Permutation_AsFunction <- representationOf perm + [func] <- downX1 perm + return + ( "Vertical rule for permutation-comprehension, AsFunction representation" + , do + return $ Comprehension body + $ gocBefore + ++ [ Generator (GenInExpr pat func) + ] + ++ gocAfter + ) + theRule _ = na "rule_Comprehension" + + +-- | Want this to be +-- p(i) becomes [i, f(i)][toInt(i in defined(f))] +rule_Application :: Rule +rule_Application = error "permutation: rule_Application not defined yet." diff --git a/src/Conjure/Rules/Vertical/Permutation/AsSequences.hs b/src/Conjure/Rules/Vertical/Permutation/AsSequences.hs deleted file mode 100644 index 5ee2a0a31c..0000000000 --- a/src/Conjure/Rules/Vertical/Permutation/AsSequences.hs +++ /dev/null @@ -1,26 +0,0 @@ -{-# LANGUAGE QuasiQuotes #-} - -module Conjure.Rules.Vertical.Permutation.AsSequences where - -import Conjure.Rules.Import - - -rule_Comprehension :: Rule -rule_Comprehension = "permutation-comprehension{AsSequences}" `namedRule` theRule where - theRule (Comprehension body gensOrConds) = do - (gocBefore, (pat, perm), gocAfter) <- matchFirst gensOrConds $ \ goc -> case goc of - Generator (GenInExpr pat@Single{} expr) -> return (pat, matchDefs [opToSet, opToMSet] expr) - _ -> na "rule_Comprehension" - TypePermutation{} <- typeOf perm - Permutation_AsSequences <- representationOf perm - [setOfSequences] <- downX1 perm - return - ( "Vertical rule for permutation-comprehension, AsSequences representation" - , do - return $ Comprehension body - $ gocBefore - ++ [ Generator (GenInExpr pat setOfSequences) - ] - ++ gocAfter - ) - theRule _ = na "rule_Comprehension" diff --git a/src/Conjure/UI/Model.hs b/src/Conjure/UI/Model.hs index 7326712115..d769c63fa0 100644 --- a/src/Conjure/UI/Model.hs +++ b/src/Conjure/UI/Model.hs @@ -86,7 +86,7 @@ import qualified Conjure.Rules.Horizontal.Partition as Horizontal.Partition import qualified Conjure.Rules.Vertical.Partition.PartitionAsSet as Vertical.Partition.PartitionAsSet import qualified Conjure.Rules.Vertical.Partition.Occurrence as Vertical.Partition.Occurrence -import qualified Conjure.Rules.Vertical.Permutation.AsSequences as Vertical.Permutation.AsSequences +import qualified Conjure.Rules.Vertical.Permutation.AsFunction as Vertical.Permutation.AsFunction import qualified Conjure.Rules.BubbleUp as BubbleUp import qualified Conjure.Rules.DontCare as DontCare @@ -1136,7 +1136,7 @@ verticalRules = , Vertical.Partition.PartitionAsSet.rule_Comprehension , Vertical.Partition.Occurrence.rule_Comprehension - , Vertical.Permutation.AsSequences.rule_Comprehension + , Vertical.Permutation.AsFunction.rule_Comprehension ] From cfdfcd7f2f33bf42632546b0770a709b446c43f0 Mon Sep 17 00:00:00 2001 From: Fraser Dunlop Date: Thu, 4 Oct 2018 10:10:39 +0100 Subject: [PATCH 003/229] Pulled in permutation-safe - basic tests now passing --- conjure-cp.cabal | 4 + etc/hs-deps/stack-8.4.yaml | 2 + etc/hs-deps/stack-head.yaml | 2 + fastbuild.sh | 2 +- src/Conjure/Compute/DomainOf.hs | 17 + src/Conjure/Language/Constant.hs | 10 +- src/Conjure/Language/Domain.hs | 2 +- .../Language/Expression/DomainSizeOf.hs | 2 + src/Conjure/Language/Expression/Op.hs | 6 + src/Conjure/Language/Expression/Op/Apply.hs | 63 ++ .../Language/Expression/Op/Internal/Common.hs | 3 + .../Expression/Op/PermutationTuples.hs | 47 + src/Conjure/Language/Expression/Op/Permute.hs | 62 + src/Conjure/Language/Expression/Op/ToSet.hs | 1 + src/Conjure/Language/Lenses.hs | 46 + src/Conjure/Language/Lexer.hs | 6 + src/Conjure/Language/Type.hs | 2 +- src/Conjure/Process/Enums.hs | 4 + src/Conjure/Representations/Combined.hs | 9 +- .../Representations/Permutation/AsFunction.hs | 118 +- .../Rules/Horizontal/.Permutation.hs.swo | Bin 0 -> 12288 bytes src/Conjure/Rules/Horizontal/Permutation.hs | 60 +- .../Rules/Vertical/Permutation/AsFunction.hs | 74 +- src/Conjure/UI/Model.hs | 11 +- .../permutations/basic/01/permutation.essence | 9 + .../permutations/basic/01/permutation.param | 1 + .../permutations/{parsing => basic}/01/run.sh | 2 +- .../permutations/basic/01/stdout.expected | 7 + .../02/permutation.essence} | 0 .../02/permutation.param} | 0 tests/custom/permutations/basic/02/run.sh | 3 + .../permutations/basic/02/stdout.expected | 7 + .../permutations/basic/03/permutation.essence | 7 + .../permutations/basic/03/permutation.param | 1 + tests/custom/permutations/basic/03/run.sh | 3 + .../permutations/basic/03/stderr.expected | 10 + .../permutations/basic/03/stdout.expected | 4 + .../permutations/basic/04/permutation.essence | 7 + .../permutations/basic/04/permutation.param | 1 + tests/custom/permutations/basic/04/run.sh | 3 + .../permutations/basic/04/stdout.expected | 7 + .../permutations/basic/05/permutation.essence | 11 + .../permutations/basic/05/permutation.param | 1 + tests/custom/permutations/basic/05/run.sh | 3 + .../permutations/basic/05/stdout.expected | 8 + .../permutations/basic/06/permutation.essence | 11 + .../permutations/basic/06/permutation.param | 1 + tests/custom/permutations/basic/06/run.sh | 3 + .../permutations/basic/06/stdout.expected | 8 + .../permutations/basic/07/permutation.essence | 11 + .../permutations/basic/07/permutation.param | 1 + tests/custom/permutations/basic/07/run.sh | 3 + .../permutations/basic/07/stdout.expected | 8 + .../permutations/basic/08/permutation.essence | 14 + .../permutations/basic/08/permutation.param | 2 + tests/custom/permutations/basic/08/run.sh | 3 + .../permutations/basic/08/stdout.expected | 8 + .../permutations/basic/09/permutation.essence | 14 + .../permutations/basic/09/permutation.param | 3 + tests/custom/permutations/basic/09/run.sh | 3 + .../permutations/basic/09/stdout.expected | 8 + .../permutations/basic/10/permutation.essence | 14 + .../permutations/basic/10/permutation.param | 3 + tests/custom/permutations/basic/10/run.sh | 3 + .../permutations/basic/10/stdout.expected | 8 + .../permutations/basic/11/permutation.essence | 8 + tests/custom/permutations/basic/11/run.sh | 3 + .../permutations/basic/11/stdout.expected | 9 + .../permutations/basic/12/permutation.essence | 8 + tests/custom/permutations/basic/12/run.sh | 3 + .../permutations/basic/12/stdout.expected | 9 + .../permutations/basic/13/permutation.essence | 10 + tests/custom/permutations/basic/13/run.sh | 3 + .../permutations/basic/13/stdout.expected | 8 + .../permutations/basic/14/permutation.essence | 7 + tests/custom/permutations/basic/14/run.sh | 3 + .../permutations/basic/14/stdout.expected | 44 + .../permutations/basic/15/permutation.essence | 10 + tests/custom/permutations/basic/15/run.sh | 3 + .../permutations/basic/15/stdout.expected | 8 + .../permutations/basic/16/permutation.essence | 9 + tests/custom/permutations/basic/16/run.sh | 3 + .../permutations/basic/16/stdout.expected | 12 + .../permutations/basic/17/permutation.essence | 8 + tests/custom/permutations/basic/17/run.sh | 3 + .../permutations/basic/17/stdout.expected | 34 + .../permutations/basic/18/permutation.essence | 6 + tests/custom/permutations/basic/18/run.sh | 3 + .../permutations/basic/18/stdout.expected | 28 + .../permutations/basic/19/permutation.essence | 7 + tests/custom/permutations/basic/19/run.sh | 3 + .../permutations/basic/19/stdout.expected | 268 +++++ .../permutations/basic/20/permutation.essence | 6 + tests/custom/permutations/basic/20/run.sh | 3 + .../permutations/basic/20/stdout.expected | 1004 +++++++++++++++++ tests/custom/permutations/basic/runthese.sh | 1 + .../parsing/01/permutation_given.essence | 11 - .../parsing/01/permutation_given.param | 1 - .../parsing/01/permutation_given.solution | 2 - tests/custom/permutations/parsing/02/run.sh | 3 - tests/custom/permutations/parsing/runthese.sh | 1 - 101 files changed, 2268 insertions(+), 61 deletions(-) create mode 100644 src/Conjure/Language/Expression/Op/Apply.hs create mode 100644 src/Conjure/Language/Expression/Op/PermutationTuples.hs create mode 100644 src/Conjure/Language/Expression/Op/Permute.hs create mode 100644 src/Conjure/Rules/Horizontal/.Permutation.hs.swo create mode 100644 tests/custom/permutations/basic/01/permutation.essence create mode 100644 tests/custom/permutations/basic/01/permutation.param rename tests/custom/permutations/{parsing => basic}/01/run.sh (64%) create mode 100644 tests/custom/permutations/basic/01/stdout.expected rename tests/custom/permutations/{parsing/02/permutation_given.essence => basic/02/permutation.essence} (100%) rename tests/custom/permutations/{parsing/02/permutation_given.param => basic/02/permutation.param} (100%) create mode 100755 tests/custom/permutations/basic/02/run.sh create mode 100644 tests/custom/permutations/basic/02/stdout.expected create mode 100644 tests/custom/permutations/basic/03/permutation.essence create mode 100644 tests/custom/permutations/basic/03/permutation.param create mode 100755 tests/custom/permutations/basic/03/run.sh create mode 100644 tests/custom/permutations/basic/03/stderr.expected create mode 100644 tests/custom/permutations/basic/03/stdout.expected create mode 100644 tests/custom/permutations/basic/04/permutation.essence create mode 100644 tests/custom/permutations/basic/04/permutation.param create mode 100755 tests/custom/permutations/basic/04/run.sh create mode 100644 tests/custom/permutations/basic/04/stdout.expected create mode 100644 tests/custom/permutations/basic/05/permutation.essence create mode 100644 tests/custom/permutations/basic/05/permutation.param create mode 100755 tests/custom/permutations/basic/05/run.sh create mode 100644 tests/custom/permutations/basic/05/stdout.expected create mode 100644 tests/custom/permutations/basic/06/permutation.essence create mode 100644 tests/custom/permutations/basic/06/permutation.param create mode 100755 tests/custom/permutations/basic/06/run.sh create mode 100644 tests/custom/permutations/basic/06/stdout.expected create mode 100644 tests/custom/permutations/basic/07/permutation.essence create mode 100644 tests/custom/permutations/basic/07/permutation.param create mode 100755 tests/custom/permutations/basic/07/run.sh create mode 100644 tests/custom/permutations/basic/07/stdout.expected create mode 100644 tests/custom/permutations/basic/08/permutation.essence create mode 100644 tests/custom/permutations/basic/08/permutation.param create mode 100755 tests/custom/permutations/basic/08/run.sh create mode 100644 tests/custom/permutations/basic/08/stdout.expected create mode 100644 tests/custom/permutations/basic/09/permutation.essence create mode 100644 tests/custom/permutations/basic/09/permutation.param create mode 100755 tests/custom/permutations/basic/09/run.sh create mode 100644 tests/custom/permutations/basic/09/stdout.expected create mode 100644 tests/custom/permutations/basic/10/permutation.essence create mode 100644 tests/custom/permutations/basic/10/permutation.param create mode 100755 tests/custom/permutations/basic/10/run.sh create mode 100644 tests/custom/permutations/basic/10/stdout.expected create mode 100644 tests/custom/permutations/basic/11/permutation.essence create mode 100755 tests/custom/permutations/basic/11/run.sh create mode 100644 tests/custom/permutations/basic/11/stdout.expected create mode 100644 tests/custom/permutations/basic/12/permutation.essence create mode 100755 tests/custom/permutations/basic/12/run.sh create mode 100644 tests/custom/permutations/basic/12/stdout.expected create mode 100644 tests/custom/permutations/basic/13/permutation.essence create mode 100755 tests/custom/permutations/basic/13/run.sh create mode 100644 tests/custom/permutations/basic/13/stdout.expected create mode 100644 tests/custom/permutations/basic/14/permutation.essence create mode 100755 tests/custom/permutations/basic/14/run.sh create mode 100644 tests/custom/permutations/basic/14/stdout.expected create mode 100644 tests/custom/permutations/basic/15/permutation.essence create mode 100755 tests/custom/permutations/basic/15/run.sh create mode 100644 tests/custom/permutations/basic/15/stdout.expected create mode 100644 tests/custom/permutations/basic/16/permutation.essence create mode 100755 tests/custom/permutations/basic/16/run.sh create mode 100644 tests/custom/permutations/basic/16/stdout.expected create mode 100644 tests/custom/permutations/basic/17/permutation.essence create mode 100755 tests/custom/permutations/basic/17/run.sh create mode 100644 tests/custom/permutations/basic/17/stdout.expected create mode 100644 tests/custom/permutations/basic/18/permutation.essence create mode 100755 tests/custom/permutations/basic/18/run.sh create mode 100644 tests/custom/permutations/basic/18/stdout.expected create mode 100644 tests/custom/permutations/basic/19/permutation.essence create mode 100755 tests/custom/permutations/basic/19/run.sh create mode 100644 tests/custom/permutations/basic/19/stdout.expected create mode 100644 tests/custom/permutations/basic/20/permutation.essence create mode 100755 tests/custom/permutations/basic/20/run.sh create mode 100644 tests/custom/permutations/basic/20/stdout.expected create mode 100644 tests/custom/permutations/basic/runthese.sh delete mode 100644 tests/custom/permutations/parsing/01/permutation_given.essence delete mode 100644 tests/custom/permutations/parsing/01/permutation_given.param delete mode 100644 tests/custom/permutations/parsing/01/permutation_given.solution delete mode 100755 tests/custom/permutations/parsing/02/run.sh delete mode 100644 tests/custom/permutations/parsing/runthese.sh diff --git a/conjure-cp.cabal b/conjure-cp.cabal index be4f20480a..c3773d25f3 100644 --- a/conjure-cp.cabal +++ b/conjure-cp.cabal @@ -50,6 +50,7 @@ Library , Conjure.Language.Expression.Op.AllDiffExcept , Conjure.Language.Expression.Op.And , Conjure.Language.Expression.Op.Apart + , Conjure.Language.Expression.Op.Apply , Conjure.Language.Expression.Op.AttributeAsConstraint , Conjure.Language.Expression.Op.CatchUndef , Conjure.Language.Expression.Op.Defined @@ -87,6 +88,8 @@ Library , Conjure.Language.Expression.Op.Participants , Conjure.Language.Expression.Op.Parts , Conjure.Language.Expression.Op.Party + , Conjure.Language.Expression.Op.Permute + , Conjure.Language.Expression.Op.PermutationTuples , Conjure.Language.Expression.Op.Pow , Conjure.Language.Expression.Op.PowerSet , Conjure.Language.Expression.Op.Pred @@ -252,6 +255,7 @@ Library , megaparsec >= 4.1.1 && < 5 , mtl , parallel-io + , permutation-safe , pipes , pretty > 1.1.1.1 -- >= 2.9 because of the TH fix: https://github.com/nick8325/quickcheck/issues/101 diff --git a/etc/hs-deps/stack-8.4.yaml b/etc/hs-deps/stack-8.4.yaml index c249596735..dc4d2c2cf5 100644 --- a/etc/hs-deps/stack-8.4.yaml +++ b/etc/hs-deps/stack-8.4.yaml @@ -7,3 +7,5 @@ extra-deps: - megaparsec-4.4.0 - tasty-1.1.0.1 - tasty-ant-xml-1.1.4 +- git: https://github.com/fraser-dunlop/permutation-safe + commit: 008c6227c6ed390b6bd71e88a76e002a66b9f64a diff --git a/etc/hs-deps/stack-head.yaml b/etc/hs-deps/stack-head.yaml index ba4a1187cf..c5082981f6 100644 --- a/etc/hs-deps/stack-head.yaml +++ b/etc/hs-deps/stack-head.yaml @@ -7,3 +7,5 @@ extra-deps: - megaparsec-4.4.0 - tasty-1.1.0.1 - tasty-ant-xml-1.1.4 +- git: https://github.com/fraser-dunlop/permutation-safe + commit: 008c6227c6ed390b6bd71e88a76e002a66b9f64a diff --git a/fastbuild.sh b/fastbuild.sh index ad7bf59198..4feed6a0e0 100644 --- a/fastbuild.sh +++ b/fastbuild.sh @@ -1 +1 @@ -stack build --fast +stack install --fast diff --git a/src/Conjure/Compute/DomainOf.hs b/src/Conjure/Compute/DomainOf.hs index f1280cb4df..772acd33b1 100644 --- a/src/Conjure/Compute/DomainOf.hs +++ b/src/Conjure/Compute/DomainOf.hs @@ -81,6 +81,7 @@ instance (DomainOf x, TypeOf x, Pretty x, ExpressionLike x, Domain () x :< x, Do domainOf (MkOpAllDiffExcept x) = domainOf x domainOf (MkOpAnd x) = domainOf x domainOf (MkOpApart x) = domainOf x + domainOf (MkOpApply x) = domainOf x domainOf (MkOpAttributeAsConstraint x) = domainOf x domainOf (MkOpCatchUndef x) = domainOf x domainOf (MkOpDefined x) = domainOf x @@ -118,6 +119,8 @@ instance (DomainOf x, TypeOf x, Pretty x, ExpressionLike x, Domain () x :< x, Do domainOf (MkOpParticipants x) = domainOf x domainOf (MkOpParts x) = domainOf x domainOf (MkOpParty x) = domainOf x + domainOf (MkOpPermute x) = domainOf x + domainOf (MkOpPermutationTuples x) = domainOf x domainOf (MkOpPow x) = domainOf x domainOf (MkOpPowerSet x) = domainOf x domainOf (MkOpPred x) = domainOf x @@ -152,6 +155,7 @@ instance (DomainOf x, TypeOf x, Pretty x, ExpressionLike x, Domain () x :< x, Do indexDomainsOf (MkOpAllDiffExcept x) = indexDomainsOf x indexDomainsOf (MkOpAnd x) = indexDomainsOf x indexDomainsOf (MkOpApart x) = indexDomainsOf x + indexDomainsOf (MkOpApply x) = indexDomainsOf x indexDomainsOf (MkOpAttributeAsConstraint x) = indexDomainsOf x indexDomainsOf (MkOpCatchUndef x) = indexDomainsOf x indexDomainsOf (MkOpDefined x) = indexDomainsOf x @@ -189,6 +193,8 @@ instance (DomainOf x, TypeOf x, Pretty x, ExpressionLike x, Domain () x :< x, Do indexDomainsOf (MkOpParticipants x) = indexDomainsOf x indexDomainsOf (MkOpParts x) = indexDomainsOf x indexDomainsOf (MkOpParty x) = indexDomainsOf x + indexDomainsOf (MkOpPermute x) = indexDomainsOf x + indexDomainsOf (MkOpPermutationTuples x) = indexDomainsOf x indexDomainsOf (MkOpPow x) = indexDomainsOf x indexDomainsOf (MkOpPowerSet x) = indexDomainsOf x indexDomainsOf (MkOpPred x) = indexDomainsOf x @@ -501,6 +507,17 @@ instance DomainOf x => DomainOf (OpParts x) where instance (Pretty x, TypeOf x) => DomainOf (OpParty x) where domainOf op = mkDomainAny ("OpParty:" <++> pretty op) <$> typeOf op +instance (Pretty x, TypeOf x) => DomainOf (OpPermute x) where + domainOf op = mkDomainAny ("OpPermute:" <++> pretty op) <$> typeOf op + +instance (Pretty x, TypeOf x) => DomainOf (OpPermutationTuples x) where + domainOf op = mkDomainAny ("OpPermutationTuples:" <++> pretty op) <$> typeOf op + + + +instance (Pretty x, TypeOf x) => DomainOf (OpApply x) where + domainOf op = mkDomainAny ("OpApply:" <++> pretty op) <$> typeOf op + instance (Pretty x, TypeOf x) => DomainOf (OpPow x) where domainOf op = mkDomainAny ("OpPow:" <++> pretty op) <$> typeOf op diff --git a/src/Conjure/Language/Constant.hs b/src/Conjure/Language/Constant.hs index 8322b6833d..30b10624e7 100644 --- a/src/Conjure/Language/Constant.hs +++ b/src/Conjure/Language/Constant.hs @@ -20,6 +20,7 @@ module Conjure.Language.Constant , viewConstantSequence , viewConstantRelation , viewConstantPartition + , viewConstantPermutation ) where -- conjure @@ -415,7 +416,10 @@ validateConstantForDomain name c@(ConstantAbstract (AbsLitPartition valss)) d@(DomainPartition _ _ dInner) = nested c d $ mapM_ (\ val -> validateConstantForDomain name val dInner ) (concat valss) - +validateConstantForDomain name + c@(ConstantAbstract (AbsLitPermutation valss)) + d@(DomainPermutation _ _ dInner) = nested c d $ + mapM_ (\ val -> validateConstantForDomain name val dInner ) (concat valss) validateConstantForDomain name c@(TypedConstant c' _) d = nested c d $ validateConstantForDomain name c' d validateConstantForDomain name c d = constantNotInDomain name c d @@ -511,3 +515,7 @@ viewConstantPartition (ConstantAbstract (AbsLitPartition xs)) = return xs viewConstantPartition (TypedConstant c _) = viewConstantPartition c viewConstantPartition constant = fail ("Expecting a partition, but got:" <++> pretty constant) +viewConstantPermutation :: MonadFail m => Constant -> m [[Constant]] +viewConstantPermutation (ConstantAbstract (AbsLitPermutation xs)) = return xs +viewConstantPermutation (TypedConstant c _) = viewConstantPermutation c +viewConstantPermutation constant = fail ("Expecting a permutation, but got:" <++> pretty constant) diff --git a/src/Conjure/Language/Domain.hs b/src/Conjure/Language/Domain.hs index 40cdce06e6..ceee0f174f 100644 --- a/src/Conjure/Language/Domain.hs +++ b/src/Conjure/Language/Domain.hs @@ -866,7 +866,7 @@ instance (Pretty r, Pretty a) => Pretty (Domain r a) where pretty (DomainPartition r attrs inner) = hang ("partition" <+> prettyAttrs r attrs <+> "from") 4 (pretty inner) - pretty (DomainPermutation r attrs inner) = hang ("permutation" <+> prettyAttrs r attrs <+> "from") 4 (pretty inner) + pretty (DomainPermutation r attrs inner) = hang ("permutation" <+> prettyAttrs r attrs <+> "of") 4 (pretty inner) pretty d@DomainOp{} = pretty (show d) diff --git a/src/Conjure/Language/Expression/DomainSizeOf.hs b/src/Conjure/Language/Expression/DomainSizeOf.hs index 1ee7a0a019..15007fab5d 100644 --- a/src/Conjure/Language/Expression/DomainSizeOf.hs +++ b/src/Conjure/Language/Expression/DomainSizeOf.hs @@ -71,6 +71,8 @@ instance DomainSizeOf Expression Expression where domainSizeOf (DomainPartition _ a inner) = domainSizeOf $ DomainSet def (SetAttr (partsNum a)) $ DomainSet def (SetAttr (partsSize a)) inner + domainSizeOf (DomainPermutation _ (PermutationAttr sizeAttr) inner) = + domainSizeOf $ DomainSet def (SetAttr sizeAttr) inner domainSizeOf d = bug ("not implemented: domainSizeOf:" <+> vcat [pretty d, pretty (show d)]) diff --git a/src/Conjure/Language/Expression/Op.hs b/src/Conjure/Language/Expression/Op.hs index 521e4db770..99b7fd17af 100644 --- a/src/Conjure/Language/Expression/Op.hs +++ b/src/Conjure/Language/Expression/Op.hs @@ -117,6 +117,12 @@ mkOp op xs = L_party -> inject $ MkOpParty $ OpParty (arg xs 0 "party") (arg xs 1 "party") L_participants -> inject $ MkOpParticipants $ OpParticipants (arg xs 0 "participants") + L_permute -> inject $ MkOpPermute $ OpPermute (arg xs 0 "permute") + (arg xs 1 "permute") + L_permutationTuples -> inject $ MkOpPermutationTuples $ OpPermutationTuples (arg xs 0 "permutationTuples") + L_apply -> inject $ MkOpApply $ OpApply (arg xs 0 "apply") + (arg xs 1 "apply") + L_active -> inject $ MkOpActive $ OpActive (arg xs 0 "active") (arg xs 1 "active" |> nameOut |> fromMaybe (bug "active")) L_pred -> inject $ MkOpPred $ OpPred (arg xs 0 "pred") diff --git a/src/Conjure/Language/Expression/Op/Apply.hs b/src/Conjure/Language/Expression/Op/Apply.hs new file mode 100644 index 0000000000..7a842889c8 --- /dev/null +++ b/src/Conjure/Language/Expression/Op/Apply.hs @@ -0,0 +1,63 @@ +{-# LANGUAGE DeriveGeneric, DeriveDataTypeable, DeriveFunctor, DeriveTraversable, DeriveFoldable, ViewPatterns #-} + +module Conjure.Language.Expression.Op.Apply where + +import Conjure.Prelude +import Conjure.Language.Expression.Op.Internal.Common +import Conjure.Bug + +import qualified Data.Aeson as JSON -- aeson +import qualified Data.HashMap.Strict as M -- unordered-containers +import qualified Data.Vector as V -- vector + +import Data.List (cycle) + +data OpApply x = OpApply x x + deriving (Eq, Ord, Show, Data, Functor, Traversable, Foldable, Typeable, Generic) + +instance Serialize x => Serialize (OpApply x) +instance Hashable x => Hashable (OpApply x) +instance ToJSON x => ToJSON (OpApply x) where toJSON = genericToJSON jsonOptions +instance FromJSON x => FromJSON (OpApply x) where parseJSON = genericParseJSON jsonOptions + +instance (TypeOf x, Pretty x) => TypeOf (OpApply x) where + typeOf inp@(OpApply p q) = do + pTy <- typeOf p + qTy <- typeOf q + case (pTy, qTy) of + (TypePermutation pTyInner, TypePermutation qTyInner) -> + if typesUnify [pTyInner, qTyInner] + then return pTy + else raiseTypeError inp + _ -> raiseTypeError inp + +instance EvaluateOp OpApply where + evaluateOp op@(OpApply g@(viewConstantPermutation -> Just gss) + h@(viewConstantPermutation -> Just hss)) = do + gt <- typeOf g + ht <- typeOf h + case (gt, ht) of + (TypePermutation TypeInt, TypePermutation TypeInt) -> + let appI xss i = case filter (i `elem`) xss of + [] -> return i + [k] -> return $ head $ drop 1 $ dropWhile (/= i) $ cycle k + _ -> bug "evaluateOp{OpApply} element should only be in one cycle of permutation" + in ConstantAbstract . AbsLitPermutation <$> (mapM (mapM (appI gss)) hss) + _ -> na $ "evaluateOp{OpApply} only defined for Ints right now:" <++> pretty (show op) + evaluateOp op = na $ "evaluateOp{OpApply}:" <++> pretty (show op) + +instance SimplifyOp OpApply x where + simplifyOp _ = na "simplifyOp{OpApply}" + +instance Pretty x => Pretty (OpApply x) where + prettyPrec _ (OpApply a i) = "apply" <> prettyList prParens "," [a,i] + + +instance VarSymBreakingDescription x => VarSymBreakingDescription (OpApply x) where + varSymBreakingDescription (OpApply a i) = JSON.Object $ M.fromList + [ ("type", JSON.String "OpApply") + , ("children", JSON.Array $ V.fromList + [ varSymBreakingDescription a + , varSymBreakingDescription i + ]) + ] diff --git a/src/Conjure/Language/Expression/Op/Internal/Common.hs b/src/Conjure/Language/Expression/Op/Internal/Common.hs index ef5ae32bce..452add227c 100644 --- a/src/Conjure/Language/Expression/Op/Internal/Common.hs +++ b/src/Conjure/Language/Expression/Op/Internal/Common.hs @@ -228,6 +228,7 @@ functionals = , L_max , L_allDiff , L_alldifferent_except + , L_apply , L_catchUndef , L_dontCare , L_hist @@ -248,6 +249,8 @@ functionals = , L_party , L_participants , L_parts + , L_permute + , L_permutationTuples , L_freq , L_toInt , L_flatten diff --git a/src/Conjure/Language/Expression/Op/PermutationTuples.hs b/src/Conjure/Language/Expression/Op/PermutationTuples.hs new file mode 100644 index 0000000000..e5054663ed --- /dev/null +++ b/src/Conjure/Language/Expression/Op/PermutationTuples.hs @@ -0,0 +1,47 @@ +{-# LANGUAGE DeriveGeneric, DeriveDataTypeable, DeriveFunctor, DeriveTraversable, DeriveFoldable, ViewPatterns #-} + +module Conjure.Language.Expression.Op.PermutationTuples where + +import Conjure.Prelude +import Conjure.Language.Expression.Op.Internal.Common +import Conjure.Bug + +import qualified Data.Aeson as JSON -- aeson +import qualified Data.HashMap.Strict as M -- unordered-containers +import qualified Data.Vector as V -- vector + +import Data.List (cycle) + +data OpPermutationTuples x = OpPermutationTuples x + deriving (Eq, Ord, Show, Data, Functor, Traversable, Foldable, Typeable, Generic) + +instance Serialize x => Serialize (OpPermutationTuples x) +instance Hashable x => Hashable (OpPermutationTuples x) +instance ToJSON x => ToJSON (OpPermutationTuples x) where toJSON = genericToJSON jsonOptions +instance FromJSON x => FromJSON (OpPermutationTuples x) where parseJSON = genericParseJSON jsonOptions + +instance (TypeOf x, Pretty x) => TypeOf (OpPermutationTuples x) where + typeOf inp@(OpPermutationTuples p) = do + pTy <- typeOf p + case (pTy) of + (TypePermutation pTyInner) -> + return $ TypeSet $ TypeTuple [pTyInner, pTyInner] + _ -> raiseTypeError inp + +instance EvaluateOp OpPermutationTuples where + evaluateOp op = na $ "evaluateOp{OpPermutationTuples}:" <++> pretty (show op) + +instance SimplifyOp OpPermutationTuples x where + simplifyOp _ = na "simplifyOp{OpPermutationTuples}" + +instance Pretty x => Pretty (OpPermutationTuples x) where + prettyPrec _ (OpPermutationTuples a) = "permutationTuples" <> prettyList prParens "," [a] + + +instance VarSymBreakingDescription x => VarSymBreakingDescription (OpPermutationTuples x) where + varSymBreakingDescription (OpPermutationTuples a) = JSON.Object $ M.fromList + [ ("type", JSON.String "OpPermutationTuples") + , ("children", JSON.Array $ V.fromList + [ varSymBreakingDescription a + ]) + ] diff --git a/src/Conjure/Language/Expression/Op/Permute.hs b/src/Conjure/Language/Expression/Op/Permute.hs new file mode 100644 index 0000000000..01633a0e06 --- /dev/null +++ b/src/Conjure/Language/Expression/Op/Permute.hs @@ -0,0 +1,62 @@ +{-# LANGUAGE DeriveGeneric, DeriveDataTypeable, DeriveFunctor, DeriveTraversable, DeriveFoldable, ViewPatterns #-} + +module Conjure.Language.Expression.Op.Permute where + +import Conjure.Prelude +import Conjure.Language.Expression.Op.Internal.Common +import Conjure.Bug + +import qualified Data.Aeson as JSON -- aeson +import qualified Data.HashMap.Strict as M -- unordered-containers +import qualified Data.Vector as V -- vector + +import Data.List (cycle) + +data OpPermute x = OpPermute x x + deriving (Eq, Ord, Show, Data, Functor, Traversable, Foldable, Typeable, Generic) + +instance Serialize x => Serialize (OpPermute x) +instance Hashable x => Hashable (OpPermute x) +instance ToJSON x => ToJSON (OpPermute x) where toJSON = genericToJSON jsonOptions +instance FromJSON x => FromJSON (OpPermute x) where parseJSON = genericParseJSON jsonOptions + +instance (TypeOf x, Pretty x) => TypeOf (OpPermute x) where + typeOf inp@(OpPermute p i) = do + pTy <- typeOf p + iTy <- typeOf i + case (pTy,iTy) of + (TypePermutation pTyInner, TypeMatrix indx mTyInner) -> + if typesUnify [pTyInner, mTyInner] + then return $ TypeMatrix indx mTyInner + else raiseTypeError inp + (TypePermutation pTyInner, iTyIs) -> + if typesUnify [iTyIs, pTyInner] + then return pTyInner + else raiseTypeError inp + _ -> raiseTypeError inp + +instance EvaluateOp OpPermute where + evaluateOp op@(OpPermute (viewConstantPermutation -> Just xss) i) = do + ti <- typeOf i + case ti of + TypeInt -> case filter (i `elem`) xss of + [] -> return i + [h] -> return $ head $ drop 1 $ dropWhile (/= i) $ cycle h + _ -> bug "evaluateOp{OpPermute} element should only be in one cycle of permutation" + _ -> na $ "evaluateOp{OpPermute} only defined for Ints right now:" <++> pretty (show op) + evaluateOp op = na $ "evaluateOp{OpPermute}:" <++> pretty (show op) + +instance SimplifyOp OpPermute x where + simplifyOp _ = na "simplifyOp{OpPermute}" + +instance Pretty x => Pretty (OpPermute x) where + prettyPrec _ (OpPermute a i) = "permute" <> prettyList prParens "," [a,i] + +instance VarSymBreakingDescription x => VarSymBreakingDescription (OpPermute x) where + varSymBreakingDescription (OpPermute a i) = JSON.Object $ M.fromList + [ ("type", JSON.String "OpPermute") + , ("children", JSON.Array $ V.fromList + [ varSymBreakingDescription a + , varSymBreakingDescription i + ]) + ] diff --git a/src/Conjure/Language/Expression/Op/ToSet.hs b/src/Conjure/Language/Expression/Op/ToSet.hs index 606c79c702..b5b8af5b26 100644 --- a/src/Conjure/Language/Expression/Op/ToSet.hs +++ b/src/Conjure/Language/Expression/Op/ToSet.hs @@ -25,6 +25,7 @@ instance (TypeOf x, Pretty x) => TypeOf (OpToSet x) where tx <- typeOf x case tx of TypeRelation is -> return (TypeSet (TypeTuple is)) + TypePermutation is -> return (TypeSet (TypeTuple [is, is])) TypeMSet i -> return (TypeSet i) TypeFunction i j -> return (TypeSet (TypeTuple [i,j])) TypeMatrix _ i -> return (TypeSet i) diff --git a/src/Conjure/Language/Lenses.hs b/src/Conjure/Language/Lenses.hs index 778098fbbe..0cbc530d71 100644 --- a/src/Conjure/Language/Lenses.hs +++ b/src/Conjure/Language/Lenses.hs @@ -280,6 +280,26 @@ opToSet _ = ) +opPermutationTuples + :: ( Op x :< x + , Pretty x + , MonadFail m + ) + => Proxy (m :: * -> *) + -> ( x -> x + , x -> m x + ) +opPermutationTuples _ = + ( inject . MkOpPermutationTuples . OpPermutationTuples + , \ p -> do + op <- project p + case op of + MkOpPermutationTuples (OpPermutationTuples x) -> return x + _ -> na ("Lenses.opPermutationTuples:" <++> pretty p) + ) + + + opToSetWithFlag :: ( Op x :< x , Pretty x @@ -1279,6 +1299,32 @@ functionLiteral _ = extract p = na ("Lenses.functionLiteral:" <+> pretty p) +permutationLiteral + :: MonadFail m + => Proxy (m :: * -> *) + -> ( Type -> [[Expression]] -> Expression + , Expression -> m (Type, [[Expression]]) + ) +permutationLiteral _ = + ( \ ty elems -> + if null elems + then Typed (AbstractLiteral (AbsLitPermutation elems)) ty + else AbstractLiteral (AbsLitPermutation elems) + , \ p -> do + ty <- typeOf p + xs <- followAliases extract p + return (ty, xs) + ) + where + extract (Constant (ConstantAbstract (AbsLitPermutation xs))) = return [ [Constant z | z <- x] | x <- xs ] + extract (AbstractLiteral (AbsLitPermutation xs)) = return xs + extract (Typed x _) = extract x + extract (Constant (TypedConstant x _)) = extract (Constant x) + extract p = na ("Lenses.permutationLiteral:" <+> pretty p) + + + + sequenceLiteral :: MonadFail m => Proxy (m :: * -> *) diff --git a/src/Conjure/Language/Lexer.hs b/src/Conjure/Language/Lexer.hs index a6d6ef7254..df2b6cac0a 100644 --- a/src/Conjure/Language/Lexer.hs +++ b/src/Conjure/Language/Lexer.hs @@ -118,6 +118,9 @@ data Lexeme -- type: permutation | L_permutation + | L_permute + | L_permutationTuples + | L_apply -- operators, page 21 of the holy paper | L_union @@ -359,6 +362,9 @@ lexemes = sortBy (flip (comparing (T.length . fst))) $ map swap , ( L_partition, "partition" ) , ( L_permutation, "permutation" ) + , ( L_permutationTuples, "permutationTuples" ) + , ( L_permute, "permute") + , ( L_apply, "apply") -- , ( L_regular, "regular" ) -- , ( L_partSize, "partSize" ) -- , ( L_minPartSize, "minPartSize" ) diff --git a/src/Conjure/Language/Type.hs b/src/Conjure/Language/Type.hs index 895a8eb730..ce419ad33d 100644 --- a/src/Conjure/Language/Type.hs +++ b/src/Conjure/Language/Type.hs @@ -191,7 +191,7 @@ innerTypeOf (TypeFunction a b) = return (TypeTuple [a,b]) innerTypeOf (TypeSequence t) = return (TypeTuple [TypeInt,t]) innerTypeOf (TypeRelation ts) = return (TypeTuple ts) innerTypeOf (TypePartition t) = return (TypeSet t) -innerTypeOf (TypePermutation t) = return (TypePermutation t) +innerTypeOf (TypePermutation t) = return (TypeTuple [t,t]) innerTypeOf t = fail ("innerTypeOf:" <+> pretty (show t)) isPrimitiveType :: Type -> Bool diff --git a/src/Conjure/Process/Enums.hs b/src/Conjure/Process/Enums.hs index 4fe13c6dff..be1d960c82 100644 --- a/src/Conjure/Process/Enums.hs +++ b/src/Conjure/Process/Enums.hs @@ -241,6 +241,10 @@ addEnumsAndUnnamedsBack unnameds ctxt = helper [ [ helper inner c | c <- line ] | line <- vals ] + (DomainPermutation _ _ inner, ConstantAbstract (AbsLitPermutation vals)) -> + ConstantAbstract $ AbsLitPermutation + [ [helper inner c | c <- line ] + | line <- vals] _ -> bug ("addEnumsAndUnnamedsBack 3:" <++> vcat [ "domain :" <+> pretty domain , "constant:" <+> pretty constant ]) diff --git a/src/Conjure/Representations/Combined.hs b/src/Conjure/Representations/Combined.hs index b60986ab05..2fb8373520 100644 --- a/src/Conjure/Representations/Combined.hs +++ b/src/Conjure/Representations/Combined.hs @@ -183,7 +183,8 @@ dispatch domain = do (bug "useLevels inside dispatch") _ -> nope DomainPermutation r _ _ -> case r of - Permutation_AsFunction -> permutationAsFunction + Permutation_AsFunction -> permutationAsFunction dispatch + _ -> nope _ -> nope @@ -205,7 +206,7 @@ reprsStandardOrderNoLevels = return $ concat , relationAsMatrix , partitionAsSet dispatch (reprOptions reprsStandardOrderNoLevels) False , partitionOccurrence - , permutationAsFunction + , permutationAsFunction dispatch ] , [ functionAsRelation dispatch (reprOptions reprsStandardOrderNoLevels) , relationAsSet dispatch (reprOptions reprsStandardOrderNoLevels) False @@ -229,7 +230,7 @@ reprsStandardOrder = , relationAsMatrix , partitionAsSet dispatch (reprOptions reprsStandardOrder) True , partitionOccurrence - , permutationAsFunction + , permutationAsFunction dispatch ] , [ functionAsRelation dispatch (reprOptions reprsStandardOrder) , relationAsSet dispatch (reprOptions reprsStandardOrder) True @@ -260,7 +261,7 @@ reprsSparseOrder = map return , partitionAsSet dispatch (reprOptions reprsSparseOrder) False , partitionOccurrence -- redundant - , permutationAsFunction + , permutationAsFunction dispatch ] diff --git a/src/Conjure/Representations/Permutation/AsFunction.hs b/src/Conjure/Representations/Permutation/AsFunction.hs index 4d9ddf6567..c1967880a4 100644 --- a/src/Conjure/Representations/Permutation/AsFunction.hs +++ b/src/Conjure/Representations/Permutation/AsFunction.hs @@ -1,22 +1,26 @@ {-# LANGUAGE RecordWildCards #-} -{-# LANGUAGE QuasiQuotes #-} -{-# LANGUAGE ViewPatterns #-} +{-# LANGUAGE QuasiQuotes #-} +{-# LANGUAGE ViewPatterns #-} +{-# LANGUAGE Rank2Types #-} module Conjure.Representations.Permutation.AsFunction ( permutationAsFunction ) where -- conjure import Conjure.Prelude -import Conjure.Bug import Conjure.Language import Conjure.Language.DomainSizeOf import Conjure.Language.Expression.DomainSizeOf () -import Conjure.Language.ZeroVal ( zeroVal, EnumerateDomain ) import Conjure.Representations.Internal import Conjure.Representations.Common -import Conjure.Representations.Function.Function1D ( domainValues ) +import Conjure.Process.Enumerate +import Data.Permutation -permutationAsFunction :: forall m . (MonadFail m, NameGen m, EnumerateDomain m) => Representation m -permutationAsFunction = Representation chck downD structuralCons downC up + +permutationAsFunction + :: forall m . (MonadFail m, NameGen m, EnumerateDomain m) + => (forall x . DispatchFunction m x) + -> Representation m +permutationAsFunction dispatch = Representation chck downD structuralCons downC up where chck :: TypeOf_ReprCheck m chck f (DomainPermutation _ s innerDomain) @@ -24,30 +28,106 @@ permutationAsFunction = Representation chck downD structuralCons downC up = map (DomainPermutation Permutation_AsFunction s) <$> f innerDomain chck _ _ = return [] + outName :: Domain HasRepresentation x -> Name -> Name + outName name domain = mkOutName (Just "PermutationFunction") name domain + + + + outDomain :: (DomainSizeOf x x, Pretty x) => Domain HasRepresentation x -> m (Domain HasRepresentation x) + outDomain (DomainPermutation Permutation_AsFunction _ innerDomain) = do + s <- domainSizeOf innerDomain + return (DomainFunction (Function_1D) + (FunctionAttr (SizeAttr_Size s) PartialityAttr_Total JectivityAttr_Bijective) innerDomain innerDomain) + outDomain domain = na $ vcat [ "{outDomain} PermutationAsFunction" + , "domain:" <+> pretty domain + ] + + downD :: TypeOf_DownD m downD (name, domain@(DomainPermutation Permutation_AsFunction _ innerDomain)) | domainCanIndexMatrix innerDomain = do - --TODO do calc on m and permutation size attribute m <- domainSizeOf innerDomain return $ Just - [ ( mkOutName (Just "PermutationFunction") domain name - , DomainFunction (Function_AsRelation Relation_AsMatrix) (FunctionAttr (SizeAttr_MaxSize m) PartialityAttr_Total JectivityAttr_Bijective) innerDomain innerDomain + [ ( outName domain name + , DomainFunction (Function_1D) + (FunctionAttr (SizeAttr_Size m) PartialityAttr_Total JectivityAttr_Bijective) innerDomain innerDomain ) ] - downD (_, domain@(DomainPermutation r _ _)) = trace (textToString (representationToShortText r)) $ na "{downD} AsFunction" - downD _ = na "{downD} AsFunction" + structuralCons :: TypeOf_Structural m - structuralCons f downX1 indom@(DomainPermutation _ _ inner) - = return $ \p -> do - refs <- downX1 p - case refs of - [f] -> error "partitionAsFunction structuralCons not defined" + structuralCons f downX1 inDom@(DomainPermutation _ (PermutationAttr s) innerDom) + = return $ \inpFun -> do + refs <- downX1 inpFun + case refs of + [fun] -> do + outDom <- outDomain inDom + innerStructuralConsGen <- f outDom + (iPat, i) <- quantifiedVarOverDomain (forgetRepr innerDom) + concat <$> sequence [ innerStructuralConsGen fun + , return $ mkSizeCons s [essence| + sum([ toInt(&i != image(&fun, &i)) | &iPat : &innerDom ]) + |] + ] + _ -> na $ vcat [ "{structuralCons} PermutationAsFunction" + , pretty inDom + ] + structuralCons _ _ inDom = + na $ vcat [ "{structuralCons} PermutationAsFunction" + , pretty inDom + ] downC :: TypeOf_DownC m - downC = error "partitionAsFunction downC not defined" + downC ( name + , inDom@(DomainPermutation Permutation_AsFunction _ innerDom) + , ConstantAbstract (AbsLitPermutation vals) + ) = do + outDom <- outDomain inDom + enumDo <- enumerateDomain $ forgetRepr innerDom + case fromCycles vals of + Right perm -> + rDownC + (dispatch outDom) + ( outName inDom name + , outDom + , ConstantAbstract $ AbsLitFunction $ zip enumDo (toFunction perm <$> enumDo) + ) + Left (PermutationError err) -> fail $ vcat $ + [ "PermutationError: " <+> stringToDoc err] + downC (name, domain, constant) = na $ vcat [ "{downC} PermutationAsFunction" + , "name:" <+> pretty name + , "domain:" <+> pretty domain + , "constant:" <+> pretty constant + ] + + up :: TypeOf_Up m - up = error "partitionAsFunction up not defined" + up ctxt ( name + , domain@(DomainPermutation Permutation_AsFunction{} _ _)) = do + case ( lookup (outName domain name) ctxt) of + (Just (ConstantAbstract (AbsLitFunction f))) -> do + case toCyclesCanonical <$> fromRelation f of + Right cycles -> + return (name, ConstantAbstract (AbsLitPermutation cycles)) + Left (PermutationError err) -> fail $ vcat $ + [ "PermutationError: " <+> stringToDoc err + , "No value for:" <+> pretty (outName domain name) + , "When working on:" <+> pretty name + , "With domain:" <+> pretty domain + ] ++ + ("Bindings in context:" : prettyContext ctxt) + _ -> fail $ vcat $ + [ "No value for:" <+> pretty (outName domain name) + , "When working on:" <+> pretty name + , "With domain:" <+> pretty domain + ] ++ + ("Bindings in context:" : prettyContext ctxt) + up _ (name, domain) = na $ vcat [ "{up} PermutationAsFunction" + , "name:" <+> pretty name + , "domain:" <+> pretty domain + ] + + diff --git a/src/Conjure/Rules/Horizontal/.Permutation.hs.swo b/src/Conjure/Rules/Horizontal/.Permutation.hs.swo new file mode 100644 index 0000000000000000000000000000000000000000..bc034e3e0859792b31933e26ac50799b8cd17399 GIT binary patch literal 12288 zcmeI2OKjXk7{{kP%cB%g@etzhHHjiyc)d+|2t`e+v}x0bq)kg7f^C#KyR*Aay|x*T z+oVlFf^w^bkl@0Br+Pp_0x2L4Js>VTDse!F8(iRkpj_a<1rYpa?0t5#8*xI&mVRsR z%s1bR|NiEi*~AOmj!n(bWA-+N<4(pN3|9-Q8+Wo7Rv9ac#nN_F-sjjSoQR7kH?w=z z_8fmr>u0pX`~;6q$so)Z1Aj3VJRgZ-eouORIQDpy-yaC~Y~V}B%g=IAi=`voz_+W> zny#~oOo2>+UJAsroO^5&duaQJp6Y`GTWQN(M|-u%>M{i~1u_LP1u_LP1u_LP1u_LP z1^#CW$Z!LD7WZ^rdS8dq^M;P|-|2BUEx*5`KK+`VG6gaPG6gaPG6gaPG6gaPG6gaP zG6gaPG6gaP{(}lQCB{C)kN>-Gz~J!z|N8I$A2u`gJ$N6y3!gCv2Vb~;1%#37zHM{dK+Wkflt8O z;4SbbxByJ>*R70Q2A9AEPy;i7fiG`i>@_e8e%;8}yI=_%2YbPln;H8ETm&b~$c(X7CQ4#|5weCV&C%1Ha*qGFQMC;B)X9XdXne%GLW5G*4sXJ2W8hWj=X< zg3nL8k_*QhV3Zu(i+F#l)Yz=IO242E=_vK}MKpCDta!I#`fMq~_E zW*uqKFvrOx*QenimZ=J4({KeU4OdOtk=u#0`r`J!mF7(w}1+&vnG|F-Jr_gS|N=Fjc!`1Hol1 zd>W$TuB_^??&8l-slXy`5@sYl9Xq~s%PudWcXrL#lI&4gm#v!q79q>5!*7x?%ImV# zv(h4+q{wLzt7Etpm4c2Ug9eUqAze&xQtJRAWl`9CnU1_9xJy@w1>_`UWP~`d* z*q?U1n3It-;ig67(Z1L(YCFM0!I7ep_wpJ`iqbH75FLY26>Ue~biP7{V=buUtOtE0 z4!bLE1sP5V8zWy{NVSWGPY4ucQS%SSGh#k9~@d;`(THv0Eky8KR@UTVAF@ zqJu7)N`ghzPAPxtqT$U@+9g|@B!tt3`tEf2K%rvtjMCRg>sx?OC7k+}shMBWfH#Ii z>>XSa$p%_rdUe}Op=Kbl*PZ9mwz+g}ooh~+^8<9!#}Zpo8?=*+ZqHP?;N4x1j*_xn zdo3Qv#9eO8z4q-~dz}`#EtpV}X3Q=(Ua`_d!Hwan1r3x4`XOmY__!wDAlo$G+3lWh zia{+5B3I>)d`r%0+<*>>mh90jASSJ3i?ScdR)s^a$mkjv`&$C2qHn3I*<^>=+EJqJ zWEopc#7fmvTD8ZEeh!^cqT8I)@uchf$426&5fMaO2&D7Y*c;WV&+loftgi*fT#Hn0 z_X9~KUUq%tvSls@C<(i@8;tccsE;R?Q*klJlCwp~BNA%}Ez$y(9iw6(f*O_To7#-0 zLov#_sxVJ0aA}=sA+xPq`r`FgX#WR|dsM0@VQdPJ4}0 zOU7CqP2=ZAniiE+T9v-gZqJIKi0!<+*N elems + let outLiteral = make matrixLiteral + (TypeMatrix TypeInt (TypeTuple [inner,inner])) + (DomainInt [RangeBounded 1 (fromInt (genericLength permTups))]) + [ AbstractLiteral (AbsLitTuple [a,b]) + | (a,b) <- permTups + ] + return + ( "Vertical rule for permutation literal application to a single value (permute), AsFunction representation" + , do + (hName, h) <- auxiliaryVar + (fPat, f) <- quantifiedVar + (tPat, t) <- quantifiedVar + (gPat, g) <- quantifiedVar + (ePat, e) <- quantifiedVar + return $ WithLocals + [essence| &h |] + (AuxiliaryVars + [ Declaration (FindOrGiven LocalFind hName innerD) + , SuchThat + [ [essence| + (forAll (&fPat, &tPat) in &outLiteral . &f = &i <-> &h = &t) + /\ (!(exists (&gPat, &ePat) in &outLiteral . &g = &h) <-> &h = &i) + |] + ] + ] + ) + ) + else na "rule_Permute_Literal" + theRule _ = na "rule_Permute_Literal" diff --git a/src/Conjure/Rules/Vertical/Permutation/AsFunction.hs b/src/Conjure/Rules/Vertical/Permutation/AsFunction.hs index fd86dd9a75..1c26a6184b 100644 --- a/src/Conjure/Rules/Vertical/Permutation/AsFunction.hs +++ b/src/Conjure/Rules/Vertical/Permutation/AsFunction.hs @@ -8,28 +8,80 @@ import Conjure.Rules.Import -- Just like having the bare bijective total function in the comprehension -- -- unclear if this should stay but it is here for now -rule_Comprehension :: Rule -rule_Comprehension = "permutation-comprehension{AsFunction}" `namedRule` theRule where - theRule (Comprehension body gensOrConds) = do +--rule_Permute_Comprehension :: Rule +--rule_Permute_Comprehension = "permutation-comprehension{AsFunction}" `namedRule` theRule where +-- theRule (Comprehension body gensOrConds) = do +-- (gocBefore, (pat, perm, over), gocAfter) <- matchFirst gensOrConds $ \ goc -> case goc of +-- Generator (GenInExpr pat [essence| permute(&perm,&over) |]) -> return (pat, perm, over) +-- _ -> na "rule_Comprehension" +-- TypePermutation{} <- typeOf perm +-- Permutation_AsFunction <- representationOf perm +---- [f] <- downX1 perm +---- horizontal? +-- return +-- ( "Vertical rule for permutation-comprehension, AsFunction representation" +-- , do +-- (iPat, i) <- quantifiedVar +-- return $ Comprehension body +-- $ gocBefore +-- ++ [ Generator (GenInExpr pat [essence| +-- [permute(&perm, &i) | &iPat <- &over] +-- |] +-- ) +-- ] +-- ++ gocAfter +-- ) +-- theRule _ = na "rule_Comprehension" + + +rule_Permute_Comprehension_Tuples :: Rule +rule_Permute_Comprehension_Tuples = "permutation-comprehension-tuples{AsFunction}" `namedRule` theRule where + theRule (Comprehension body gensOrConds) = do (gocBefore, (pat, perm), gocAfter) <- matchFirst gensOrConds $ \ goc -> case goc of - Generator (GenInExpr pat@Single{} expr) -> return (pat, matchDefs [opToSet, opToMSet] expr) + Generator (GenInExpr pat [essence| &perm |] ) -> return (pat, perm) _ -> na "rule_Comprehension" TypePermutation{} <- typeOf perm Permutation_AsFunction <- representationOf perm - [func] <- downX1 perm + [f] <- downX1 perm return - ( "Vertical rule for permutation-comprehension, AsFunction representation" + ( "Vertical rule for permutation-comprehension-tuples, AsFunction representation" , do return $ Comprehension body $ gocBefore - ++ [ Generator (GenInExpr pat func) + ++ [ Generator (GenInExpr pat [essence| &f|]) ] ++ gocAfter ) theRule _ = na "rule_Comprehension" --- | Want this to be --- p(i) becomes [i, f(i)][toInt(i in defined(f))] -rule_Application :: Rule -rule_Application = error "permutation: rule_Application not defined yet." + +rule_Permute :: Rule +rule_Permute = "permutation-permute{AsFunction}" `namedRule` theRule where + theRule [essence| permute(&p, &i) |] = do + case p of WithLocals{} -> na "bubble-delay" ; _ -> return () + TypePermutation inner <- typeOf p + typeI <- typeOf i + [f] <- downX1 p + if typesUnify [inner, typeI] + then return + ( "Vertical rule for permutation application to a single value (permute), AsFunction representation" + , do + return [essence| [&i, catchUndef(image(&f,&i),0)][toInt(&i in defined(&f))+1] |] + ) + else na "rule_Permute" + theRule _ = na "rule_Permute" + +--rule_Compose :: Rule +--rule_Compose = "permutation-compose{AsFunction}" `namedRule` theRule where +-- theRule [essence| compose(&p, &q) |] = do +-- TypePermutation innerP <- typeOf p +-- TypePermutation innerQ <- typeOf q +-- if typesUnify [innerP, innerQ] +-- then return +-- ( "Vertical rule for permutation composition, AsFunction representation" +-- , do +-- +-- ) +-- else na "rule_Compose" +-- theRule _ = na "rule_Compose" diff --git a/src/Conjure/UI/Model.hs b/src/Conjure/UI/Model.hs index d769c63fa0..5e572d67ba 100644 --- a/src/Conjure/UI/Model.hs +++ b/src/Conjure/UI/Model.hs @@ -87,6 +87,7 @@ import qualified Conjure.Rules.Vertical.Partition.PartitionAsSet as Vertical.Par import qualified Conjure.Rules.Vertical.Partition.Occurrence as Vertical.Partition.Occurrence import qualified Conjure.Rules.Vertical.Permutation.AsFunction as Vertical.Permutation.AsFunction +import qualified Conjure.Rules.Horizontal.Permutation as Horizontal.Permutation import qualified Conjure.Rules.BubbleUp as BubbleUp import qualified Conjure.Rules.DontCare as DontCare @@ -1136,7 +1137,9 @@ verticalRules = , Vertical.Partition.PartitionAsSet.rule_Comprehension , Vertical.Partition.Occurrence.rule_Comprehension - , Vertical.Permutation.AsFunction.rule_Comprehension + + , Vertical.Permutation.AsFunction.rule_Permute_Comprehension_Tuples + ] @@ -1263,6 +1266,10 @@ horizontalRules = , Horizontal.Partition.rule_Card , Horizontal.Partition.rule_In + , Horizontal.Permutation.rule_Permute_Literal + , Horizontal.Permutation.rule_Apply + + ] @@ -1338,6 +1345,8 @@ delayedRules = , Vertical.Matrix.rule_Comprehension_SingletonDomain , Vertical.Matrix.rule_Concatenate_Singleton , Vertical.Matrix.rule_MatrixIndexing + + , Vertical.Permutation.AsFunction.rule_Permute ] , [ rule_ReducerToComprehension ] diff --git a/tests/custom/permutations/basic/01/permutation.essence b/tests/custom/permutations/basic/01/permutation.essence new file mode 100644 index 0000000000..ec84d3ae7d --- /dev/null +++ b/tests/custom/permutations/basic/01/permutation.essence @@ -0,0 +1,9 @@ +letting n be 4 + +given p : permutation of int(1..n) + +such that true + + + + diff --git a/tests/custom/permutations/basic/01/permutation.param b/tests/custom/permutations/basic/01/permutation.param new file mode 100644 index 0000000000..8a8c516801 --- /dev/null +++ b/tests/custom/permutations/basic/01/permutation.param @@ -0,0 +1 @@ +letting p be permutation((1,3,4)) diff --git a/tests/custom/permutations/parsing/01/run.sh b/tests/custom/permutations/basic/01/run.sh similarity index 64% rename from tests/custom/permutations/parsing/01/run.sh rename to tests/custom/permutations/basic/01/run.sh index 3ff6233922..9dc67e67f5 100755 --- a/tests/custom/permutations/parsing/01/run.sh +++ b/tests/custom/permutations/basic/01/run.sh @@ -1,3 +1,3 @@ conjure solve *.essence *.param cat conjure-output/*.solution -#rm -rf conjure-output *.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/basic/01/stdout.expected b/tests/custom/permutations/basic/01/stdout.expected new file mode 100644 index 0000000000..1d9c5a0937 --- /dev/null +++ b/tests/custom/permutations/basic/01/stdout.expected @@ -0,0 +1,7 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime permutation.param +Copying solution to: permutation-permutation.solution +language Essence 1.3 + diff --git a/tests/custom/permutations/parsing/02/permutation_given.essence b/tests/custom/permutations/basic/02/permutation.essence similarity index 100% rename from tests/custom/permutations/parsing/02/permutation_given.essence rename to tests/custom/permutations/basic/02/permutation.essence diff --git a/tests/custom/permutations/parsing/02/permutation_given.param b/tests/custom/permutations/basic/02/permutation.param similarity index 100% rename from tests/custom/permutations/parsing/02/permutation_given.param rename to tests/custom/permutations/basic/02/permutation.param diff --git a/tests/custom/permutations/basic/02/run.sh b/tests/custom/permutations/basic/02/run.sh new file mode 100755 index 0000000000..9dc67e67f5 --- /dev/null +++ b/tests/custom/permutations/basic/02/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence *.param +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/basic/02/stdout.expected b/tests/custom/permutations/basic/02/stdout.expected new file mode 100644 index 0000000000..1d9c5a0937 --- /dev/null +++ b/tests/custom/permutations/basic/02/stdout.expected @@ -0,0 +1,7 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime permutation.param +Copying solution to: permutation-permutation.solution +language Essence 1.3 + diff --git a/tests/custom/permutations/basic/03/permutation.essence b/tests/custom/permutations/basic/03/permutation.essence new file mode 100644 index 0000000000..c64c004178 --- /dev/null +++ b/tests/custom/permutations/basic/03/permutation.essence @@ -0,0 +1,7 @@ + +$ given n : int +letting n be 3 + +given p : permutation of int(1..n) + +such that true diff --git a/tests/custom/permutations/basic/03/permutation.param b/tests/custom/permutations/basic/03/permutation.param new file mode 100644 index 0000000000..a862179e25 --- /dev/null +++ b/tests/custom/permutations/basic/03/permutation.param @@ -0,0 +1 @@ +letting p be permutation((1,3),(2,4)) diff --git a/tests/custom/permutations/basic/03/run.sh b/tests/custom/permutations/basic/03/run.sh new file mode 100755 index 0000000000..9dc67e67f5 --- /dev/null +++ b/tests/custom/permutations/basic/03/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence *.param +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/basic/03/stderr.expected b/tests/custom/permutations/basic/03/stderr.expected new file mode 100644 index 0000000000..fa292aad7b --- /dev/null +++ b/tests/custom/permutations/basic/03/stderr.expected @@ -0,0 +1,10 @@ +Error: + The value is not a member of the domain. + Value : permutation((1, 3), (2, 4)) + Domain: permutation {PermutationAsFunction} of int(1..3) + Reason: + The value is not a member of the domain. + Name : p + Value : 4 + Domain: int(1..3) +cat: conjure-output/*.solution: No such file or directory diff --git a/tests/custom/permutations/basic/03/stdout.expected b/tests/custom/permutations/basic/03/stdout.expected new file mode 100644 index 0000000000..a1634e8c4c --- /dev/null +++ b/tests/custom/permutations/basic/03/stdout.expected @@ -0,0 +1,4 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime permutation.param diff --git a/tests/custom/permutations/basic/04/permutation.essence b/tests/custom/permutations/basic/04/permutation.essence new file mode 100644 index 0000000000..8f5c54c2d9 --- /dev/null +++ b/tests/custom/permutations/basic/04/permutation.essence @@ -0,0 +1,7 @@ + +$ given n : int +letting n be 4 + +given p : permutation of int(1..n) + +such that true diff --git a/tests/custom/permutations/basic/04/permutation.param b/tests/custom/permutations/basic/04/permutation.param new file mode 100644 index 0000000000..a862179e25 --- /dev/null +++ b/tests/custom/permutations/basic/04/permutation.param @@ -0,0 +1 @@ +letting p be permutation((1,3),(2,4)) diff --git a/tests/custom/permutations/basic/04/run.sh b/tests/custom/permutations/basic/04/run.sh new file mode 100755 index 0000000000..9dc67e67f5 --- /dev/null +++ b/tests/custom/permutations/basic/04/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence *.param +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/basic/04/stdout.expected b/tests/custom/permutations/basic/04/stdout.expected new file mode 100644 index 0000000000..1d9c5a0937 --- /dev/null +++ b/tests/custom/permutations/basic/04/stdout.expected @@ -0,0 +1,7 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime permutation.param +Copying solution to: permutation-permutation.solution +language Essence 1.3 + diff --git a/tests/custom/permutations/basic/05/permutation.essence b/tests/custom/permutations/basic/05/permutation.essence new file mode 100644 index 0000000000..7ec01e48e4 --- /dev/null +++ b/tests/custom/permutations/basic/05/permutation.essence @@ -0,0 +1,11 @@ + +$ given n : int +letting n be 4 + +given p : permutation of int(1..n) + +letting j be 0 + +find i : int(0..5) + +such that permute(p,i) = j diff --git a/tests/custom/permutations/basic/05/permutation.param b/tests/custom/permutations/basic/05/permutation.param new file mode 100644 index 0000000000..836e4e008c --- /dev/null +++ b/tests/custom/permutations/basic/05/permutation.param @@ -0,0 +1 @@ +letting p be permutation((1,3),(4,2)) diff --git a/tests/custom/permutations/basic/05/run.sh b/tests/custom/permutations/basic/05/run.sh new file mode 100755 index 0000000000..9dc67e67f5 --- /dev/null +++ b/tests/custom/permutations/basic/05/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence *.param +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/basic/05/stdout.expected b/tests/custom/permutations/basic/05/stdout.expected new file mode 100644 index 0000000000..826dd27a43 --- /dev/null +++ b/tests/custom/permutations/basic/05/stdout.expected @@ -0,0 +1,8 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime permutation.param +Copying solution to: permutation-permutation.solution +language Essence 1.3 + +letting i be 0 diff --git a/tests/custom/permutations/basic/06/permutation.essence b/tests/custom/permutations/basic/06/permutation.essence new file mode 100644 index 0000000000..34ccb38417 --- /dev/null +++ b/tests/custom/permutations/basic/06/permutation.essence @@ -0,0 +1,11 @@ + +$ given n : int +letting n be 4 + +given p : permutation of int(1..n) + +letting j be 1 + +find i : int(0..5) + +such that permute(p,i) = j diff --git a/tests/custom/permutations/basic/06/permutation.param b/tests/custom/permutations/basic/06/permutation.param new file mode 100644 index 0000000000..836e4e008c --- /dev/null +++ b/tests/custom/permutations/basic/06/permutation.param @@ -0,0 +1 @@ +letting p be permutation((1,3),(4,2)) diff --git a/tests/custom/permutations/basic/06/run.sh b/tests/custom/permutations/basic/06/run.sh new file mode 100755 index 0000000000..9dc67e67f5 --- /dev/null +++ b/tests/custom/permutations/basic/06/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence *.param +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/basic/06/stdout.expected b/tests/custom/permutations/basic/06/stdout.expected new file mode 100644 index 0000000000..d20985577b --- /dev/null +++ b/tests/custom/permutations/basic/06/stdout.expected @@ -0,0 +1,8 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime permutation.param +Copying solution to: permutation-permutation.solution +language Essence 1.3 + +letting i be 3 diff --git a/tests/custom/permutations/basic/07/permutation.essence b/tests/custom/permutations/basic/07/permutation.essence new file mode 100644 index 0000000000..2ba9ab44a9 --- /dev/null +++ b/tests/custom/permutations/basic/07/permutation.essence @@ -0,0 +1,11 @@ + +$ given n : int +letting n be 4 + +given p : permutation of int(1..n) + +letting j be 2 + +find i : int(0..5) + +such that permute(p,i) = j diff --git a/tests/custom/permutations/basic/07/permutation.param b/tests/custom/permutations/basic/07/permutation.param new file mode 100644 index 0000000000..836e4e008c --- /dev/null +++ b/tests/custom/permutations/basic/07/permutation.param @@ -0,0 +1 @@ +letting p be permutation((1,3),(4,2)) diff --git a/tests/custom/permutations/basic/07/run.sh b/tests/custom/permutations/basic/07/run.sh new file mode 100755 index 0000000000..9dc67e67f5 --- /dev/null +++ b/tests/custom/permutations/basic/07/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence *.param +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/basic/07/stdout.expected b/tests/custom/permutations/basic/07/stdout.expected new file mode 100644 index 0000000000..0165072a84 --- /dev/null +++ b/tests/custom/permutations/basic/07/stdout.expected @@ -0,0 +1,8 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime permutation.param +Copying solution to: permutation-permutation.solution +language Essence 1.3 + +letting i be 4 diff --git a/tests/custom/permutations/basic/08/permutation.essence b/tests/custom/permutations/basic/08/permutation.essence new file mode 100644 index 0000000000..29e49ca1f8 --- /dev/null +++ b/tests/custom/permutations/basic/08/permutation.essence @@ -0,0 +1,14 @@ + +$ given n : int +letting n be 4 +letting m be 8 + +given p : permutation of int(1..n) + +given q : permutation of int(n..m) + +letting j be 7 + +find i : int(1..8) + +such that permute(apply(q,p),i) = j diff --git a/tests/custom/permutations/basic/08/permutation.param b/tests/custom/permutations/basic/08/permutation.param new file mode 100644 index 0000000000..6888afc4ca --- /dev/null +++ b/tests/custom/permutations/basic/08/permutation.param @@ -0,0 +1,2 @@ +letting p be permutation((1,3),(4,2)) +letting q be permutation((4,7),(5,8)) diff --git a/tests/custom/permutations/basic/08/run.sh b/tests/custom/permutations/basic/08/run.sh new file mode 100755 index 0000000000..9dc67e67f5 --- /dev/null +++ b/tests/custom/permutations/basic/08/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence *.param +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/basic/08/stdout.expected b/tests/custom/permutations/basic/08/stdout.expected new file mode 100644 index 0000000000..83d7661729 --- /dev/null +++ b/tests/custom/permutations/basic/08/stdout.expected @@ -0,0 +1,8 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime permutation.param +Copying solution to: permutation-permutation.solution +language Essence 1.3 + +letting i be 2 diff --git a/tests/custom/permutations/basic/09/permutation.essence b/tests/custom/permutations/basic/09/permutation.essence new file mode 100644 index 0000000000..98e482e940 --- /dev/null +++ b/tests/custom/permutations/basic/09/permutation.essence @@ -0,0 +1,14 @@ +letting n be 4 +letting m be 8 + +given p : permutation of int(1..n) + +given q : permutation of int(n..m) + +given w : permutation of int(7..15) + +letting j be 12 + +find i : int(1..8) + +such that permute(apply(w,apply(w,apply(q,p))),i) = j diff --git a/tests/custom/permutations/basic/09/permutation.param b/tests/custom/permutations/basic/09/permutation.param new file mode 100644 index 0000000000..57228ed8e2 --- /dev/null +++ b/tests/custom/permutations/basic/09/permutation.param @@ -0,0 +1,3 @@ +letting p be permutation((1,3),(4,2)) +letting q be permutation((4,7),(5,8)) +letting w be permutation((7,9,12),(14,15)) diff --git a/tests/custom/permutations/basic/09/run.sh b/tests/custom/permutations/basic/09/run.sh new file mode 100755 index 0000000000..9dc67e67f5 --- /dev/null +++ b/tests/custom/permutations/basic/09/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence *.param +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/basic/09/stdout.expected b/tests/custom/permutations/basic/09/stdout.expected new file mode 100644 index 0000000000..83d7661729 --- /dev/null +++ b/tests/custom/permutations/basic/09/stdout.expected @@ -0,0 +1,8 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime permutation.param +Copying solution to: permutation-permutation.solution +language Essence 1.3 + +letting i be 2 diff --git a/tests/custom/permutations/basic/10/permutation.essence b/tests/custom/permutations/basic/10/permutation.essence new file mode 100644 index 0000000000..9475d5e8bd --- /dev/null +++ b/tests/custom/permutations/basic/10/permutation.essence @@ -0,0 +1,14 @@ +letting n be 4 +letting m be 8 + +given p : permutation of int(1..n) + +given q : permutation of int(n..m) + +given w : permutation of int(7..15) + +letting j be 20 + +find i : int(1..30) + +such that permute(apply(w,apply(w,apply(q,p))),i) = j diff --git a/tests/custom/permutations/basic/10/permutation.param b/tests/custom/permutations/basic/10/permutation.param new file mode 100644 index 0000000000..57228ed8e2 --- /dev/null +++ b/tests/custom/permutations/basic/10/permutation.param @@ -0,0 +1,3 @@ +letting p be permutation((1,3),(4,2)) +letting q be permutation((4,7),(5,8)) +letting w be permutation((7,9,12),(14,15)) diff --git a/tests/custom/permutations/basic/10/run.sh b/tests/custom/permutations/basic/10/run.sh new file mode 100755 index 0000000000..9dc67e67f5 --- /dev/null +++ b/tests/custom/permutations/basic/10/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence *.param +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/basic/10/stdout.expected b/tests/custom/permutations/basic/10/stdout.expected new file mode 100644 index 0000000000..497335e5d7 --- /dev/null +++ b/tests/custom/permutations/basic/10/stdout.expected @@ -0,0 +1,8 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime permutation.param +Copying solution to: permutation-permutation.solution +language Essence 1.3 + +letting i be 20 diff --git a/tests/custom/permutations/basic/11/permutation.essence b/tests/custom/permutations/basic/11/permutation.essence new file mode 100644 index 0000000000..d1708afb60 --- /dev/null +++ b/tests/custom/permutations/basic/11/permutation.essence @@ -0,0 +1,8 @@ + +find p : permutation (size 7) of int(1..25) + +letting j be 20 + +find i : int(1..30) + +such that permute(p,i) = j diff --git a/tests/custom/permutations/basic/11/run.sh b/tests/custom/permutations/basic/11/run.sh new file mode 100755 index 0000000000..b4899d6266 --- /dev/null +++ b/tests/custom/permutations/basic/11/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/basic/11/stdout.expected b/tests/custom/permutations/basic/11/stdout.expected new file mode 100644 index 0000000000..af3f7d5758 --- /dev/null +++ b/tests/custom/permutations/basic/11/stdout.expected @@ -0,0 +1,9 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Copying solution to: permutation.solution +language Essence 1.3 + +letting i be 19 +letting p be permutation((19, 20), (21, 22), (23, 24, 25)) diff --git a/tests/custom/permutations/basic/12/permutation.essence b/tests/custom/permutations/basic/12/permutation.essence new file mode 100644 index 0000000000..f17eee3982 --- /dev/null +++ b/tests/custom/permutations/basic/12/permutation.essence @@ -0,0 +1,8 @@ + +find p : permutation of int(1..25) + +letting j be 20 + +find i : int(1..30) + +such that permute(p,i) = j diff --git a/tests/custom/permutations/basic/12/run.sh b/tests/custom/permutations/basic/12/run.sh new file mode 100755 index 0000000000..b4899d6266 --- /dev/null +++ b/tests/custom/permutations/basic/12/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/basic/12/stdout.expected b/tests/custom/permutations/basic/12/stdout.expected new file mode 100644 index 0000000000..40db6adacd --- /dev/null +++ b/tests/custom/permutations/basic/12/stdout.expected @@ -0,0 +1,9 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Copying solution to: permutation.solution +language Essence 1.3 + +letting i be 20 +letting p be permutation() diff --git a/tests/custom/permutations/basic/13/permutation.essence b/tests/custom/permutations/basic/13/permutation.essence new file mode 100644 index 0000000000..c613663867 --- /dev/null +++ b/tests/custom/permutations/basic/13/permutation.essence @@ -0,0 +1,10 @@ + +find p : permutation of int(1..30) + +letting j be [20,3,4,7] + +letting k be [24,5,4,6] + +such that + forAll i : int(1..4) . + j[i] = permute(p,k[i]) diff --git a/tests/custom/permutations/basic/13/run.sh b/tests/custom/permutations/basic/13/run.sh new file mode 100755 index 0000000000..b4899d6266 --- /dev/null +++ b/tests/custom/permutations/basic/13/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/basic/13/stdout.expected b/tests/custom/permutations/basic/13/stdout.expected new file mode 100644 index 0000000000..eae25cd50d --- /dev/null +++ b/tests/custom/permutations/basic/13/stdout.expected @@ -0,0 +1,8 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Copying solution to: permutation.solution +language Essence 1.3 + +letting p be permutation((3, 5), (6, 7), (20, 21, 22, 23, 24)) diff --git a/tests/custom/permutations/basic/14/permutation.essence b/tests/custom/permutations/basic/14/permutation.essence new file mode 100644 index 0000000000..a729fb7bca --- /dev/null +++ b/tests/custom/permutations/basic/14/permutation.essence @@ -0,0 +1,7 @@ + + +find m : matrix indexed by [int(1..9)] of int(0..1) + +such that + forAll i, j : int(1..9) . + i != j -> m <=lex [m[permute(permutation((i,j)),k)] | k : int(1..9)] diff --git a/tests/custom/permutations/basic/14/run.sh b/tests/custom/permutations/basic/14/run.sh new file mode 100755 index 0000000000..bb7cfec8d9 --- /dev/null +++ b/tests/custom/permutations/basic/14/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence --number-of-solutions=25 +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/basic/14/stdout.expected b/tests/custom/permutations/basic/14/stdout.expected new file mode 100644 index 0000000000..f0d0665e21 --- /dev/null +++ b/tests/custom/permutations/basic/14/stdout.expected @@ -0,0 +1,44 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Copying solution to: permutation-000001.solution +Copying solution to: permutation-000002.solution +Copying solution to: permutation-000003.solution +Copying solution to: permutation-000004.solution +Copying solution to: permutation-000005.solution +Copying solution to: permutation-000006.solution +Copying solution to: permutation-000007.solution +Copying solution to: permutation-000008.solution +Copying solution to: permutation-000009.solution +Copying solution to: permutation-000010.solution +language Essence 1.3 + +letting m be [0, 0, 0, 0, 0, 0, 0, 0, 0; int(1..9)] +language Essence 1.3 + +letting m be [0, 0, 0, 0, 0, 0, 0, 0, 1; int(1..9)] +language Essence 1.3 + +letting m be [0, 0, 0, 0, 0, 0, 0, 1, 1; int(1..9)] +language Essence 1.3 + +letting m be [0, 0, 0, 0, 0, 0, 1, 1, 1; int(1..9)] +language Essence 1.3 + +letting m be [0, 0, 0, 0, 0, 1, 1, 1, 1; int(1..9)] +language Essence 1.3 + +letting m be [0, 0, 0, 0, 1, 1, 1, 1, 1; int(1..9)] +language Essence 1.3 + +letting m be [0, 0, 0, 1, 1, 1, 1, 1, 1; int(1..9)] +language Essence 1.3 + +letting m be [0, 0, 1, 1, 1, 1, 1, 1, 1; int(1..9)] +language Essence 1.3 + +letting m be [0, 1, 1, 1, 1, 1, 1, 1, 1; int(1..9)] +language Essence 1.3 + +letting m be [1, 1, 1, 1, 1, 1, 1, 1, 1; int(1..9)] diff --git a/tests/custom/permutations/basic/15/permutation.essence b/tests/custom/permutations/basic/15/permutation.essence new file mode 100644 index 0000000000..5adbfc504a --- /dev/null +++ b/tests/custom/permutations/basic/15/permutation.essence @@ -0,0 +1,10 @@ + +letting p be permutation((1,5,4),(7,12,20)) + +letting j be [20,3,4,7] + +find k : set of int(1..30) + +such that + forAll i in j . + permute(p, i) in k diff --git a/tests/custom/permutations/basic/15/run.sh b/tests/custom/permutations/basic/15/run.sh new file mode 100755 index 0000000000..b4899d6266 --- /dev/null +++ b/tests/custom/permutations/basic/15/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/basic/15/stdout.expected b/tests/custom/permutations/basic/15/stdout.expected new file mode 100644 index 0000000000..899694ba25 --- /dev/null +++ b/tests/custom/permutations/basic/15/stdout.expected @@ -0,0 +1,8 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Copying solution to: permutation.solution +language Essence 1.3 + +letting k be {1, 3, 7, 12} diff --git a/tests/custom/permutations/basic/16/permutation.essence b/tests/custom/permutations/basic/16/permutation.essence new file mode 100644 index 0000000000..c6973b00b4 --- /dev/null +++ b/tests/custom/permutations/basic/16/permutation.essence @@ -0,0 +1,9 @@ + +find p : permutation of int(3..7) + +letting j be [20,3,4,7,2,15,12,5] + +such that + forAll i : int(1..4) . + permute(p,j[i]) = j[i] + diff --git a/tests/custom/permutations/basic/16/run.sh b/tests/custom/permutations/basic/16/run.sh new file mode 100755 index 0000000000..de361d4354 --- /dev/null +++ b/tests/custom/permutations/basic/16/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence --number-of-solutions=40 +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/basic/16/stdout.expected b/tests/custom/permutations/basic/16/stdout.expected new file mode 100644 index 0000000000..19bfe22fc9 --- /dev/null +++ b/tests/custom/permutations/basic/16/stdout.expected @@ -0,0 +1,12 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Copying solution to: permutation-000001.solution +Copying solution to: permutation-000002.solution +language Essence 1.3 + +letting p be permutation() +language Essence 1.3 + +letting p be permutation((5, 6)) diff --git a/tests/custom/permutations/basic/17/permutation.essence b/tests/custom/permutations/basic/17/permutation.essence new file mode 100644 index 0000000000..fab8a15f3a --- /dev/null +++ b/tests/custom/permutations/basic/17/permutation.essence @@ -0,0 +1,8 @@ + +find p : permutation of int(1..5) +find q : permutation of int(3..7) + +such that + forAll i : int(1..7) . + permute(p,i) = permute(q,i) + diff --git a/tests/custom/permutations/basic/17/run.sh b/tests/custom/permutations/basic/17/run.sh new file mode 100755 index 0000000000..de361d4354 --- /dev/null +++ b/tests/custom/permutations/basic/17/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence --number-of-solutions=40 +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/basic/17/stdout.expected b/tests/custom/permutations/basic/17/stdout.expected new file mode 100644 index 0000000000..2bc692b21d --- /dev/null +++ b/tests/custom/permutations/basic/17/stdout.expected @@ -0,0 +1,34 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Copying solution to: permutation-000001.solution +Copying solution to: permutation-000002.solution +Copying solution to: permutation-000003.solution +Copying solution to: permutation-000004.solution +Copying solution to: permutation-000005.solution +Copying solution to: permutation-000006.solution +language Essence 1.3 + +letting p be permutation() +letting q be permutation() +language Essence 1.3 + +letting p be permutation((4, 5)) +letting q be permutation((4, 5)) +language Essence 1.3 + +letting p be permutation((3, 4)) +letting q be permutation((3, 4)) +language Essence 1.3 + +letting p be permutation((3, 4, 5)) +letting q be permutation((3, 4, 5)) +language Essence 1.3 + +letting p be permutation((3, 5, 4)) +letting q be permutation((3, 5, 4)) +language Essence 1.3 + +letting p be permutation((3, 5)) +letting q be permutation((3, 5)) diff --git a/tests/custom/permutations/basic/18/permutation.essence b/tests/custom/permutations/basic/18/permutation.essence new file mode 100644 index 0000000000..300a4d28f1 --- /dev/null +++ b/tests/custom/permutations/basic/18/permutation.essence @@ -0,0 +1,6 @@ + +find m : matrix indexed by [int(1..5)] of int(0..1) + +such that + forAll i, j : int(1..5) . + i != j -> m <=lex [m[permute(permutation((i,j)),k)] | k : int(1..5)] diff --git a/tests/custom/permutations/basic/18/run.sh b/tests/custom/permutations/basic/18/run.sh new file mode 100755 index 0000000000..a440de2e64 --- /dev/null +++ b/tests/custom/permutations/basic/18/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence --number-of-solutions=20 +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/basic/18/stdout.expected b/tests/custom/permutations/basic/18/stdout.expected new file mode 100644 index 0000000000..cd7357680f --- /dev/null +++ b/tests/custom/permutations/basic/18/stdout.expected @@ -0,0 +1,28 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Copying solution to: permutation-000001.solution +Copying solution to: permutation-000002.solution +Copying solution to: permutation-000003.solution +Copying solution to: permutation-000004.solution +Copying solution to: permutation-000005.solution +Copying solution to: permutation-000006.solution +language Essence 1.3 + +letting m be [0, 0, 0, 0, 0; int(1..5)] +language Essence 1.3 + +letting m be [0, 0, 0, 0, 1; int(1..5)] +language Essence 1.3 + +letting m be [0, 0, 0, 1, 1; int(1..5)] +language Essence 1.3 + +letting m be [0, 0, 1, 1, 1; int(1..5)] +language Essence 1.3 + +letting m be [0, 1, 1, 1, 1; int(1..5)] +language Essence 1.3 + +letting m be [1, 1, 1, 1, 1; int(1..5)] diff --git a/tests/custom/permutations/basic/19/permutation.essence b/tests/custom/permutations/basic/19/permutation.essence new file mode 100644 index 0000000000..49e7888ea6 --- /dev/null +++ b/tests/custom/permutations/basic/19/permutation.essence @@ -0,0 +1,7 @@ + +find p : permutation of int(1..4) +find s : set of (int(1..4), int(1..4)) + +such that + and([ x in s | x <- p]) + /\ and([ permute(p, a) = b | (a,b) <- s]) diff --git a/tests/custom/permutations/basic/19/run.sh b/tests/custom/permutations/basic/19/run.sh new file mode 100755 index 0000000000..0ab098f9b5 --- /dev/null +++ b/tests/custom/permutations/basic/19/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence --number-of-solutions=200 +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/basic/19/stdout.expected b/tests/custom/permutations/basic/19/stdout.expected new file mode 100644 index 0000000000..cf39893719 --- /dev/null +++ b/tests/custom/permutations/basic/19/stdout.expected @@ -0,0 +1,268 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Copying solution to: permutation-000001.solution +Copying solution to: permutation-000002.solution +Copying solution to: permutation-000003.solution +Copying solution to: permutation-000004.solution +Copying solution to: permutation-000005.solution +Copying solution to: permutation-000006.solution +Copying solution to: permutation-000007.solution +Copying solution to: permutation-000008.solution +Copying solution to: permutation-000009.solution +Copying solution to: permutation-000010.solution +Copying solution to: permutation-000011.solution +Copying solution to: permutation-000012.solution +Copying solution to: permutation-000013.solution +Copying solution to: permutation-000014.solution +Copying solution to: permutation-000015.solution +Copying solution to: permutation-000016.solution +Copying solution to: permutation-000017.solution +Copying solution to: permutation-000018.solution +Copying solution to: permutation-000019.solution +Copying solution to: permutation-000020.solution +Copying solution to: permutation-000021.solution +Copying solution to: permutation-000022.solution +Copying solution to: permutation-000023.solution +Copying solution to: permutation-000024.solution +language Essence 1.3 + +letting p be permutation() +letting s be {(1, 1), (2, 2), (3, 3), (4, 4)} +$ Visualisation for s +$ 1 1 +$ 2 2 +$ 3 3 +$ 4 4 + +language Essence 1.3 + +letting p be permutation((3, 4)) +letting s be {(1, 1), (2, 2), (3, 4), (4, 3)} +$ Visualisation for s +$ 1 1 +$ 2 2 +$ 3 4 +$ 4 3 + +language Essence 1.3 + +letting p be permutation((2, 3)) +letting s be {(1, 1), (2, 3), (3, 2), (4, 4)} +$ Visualisation for s +$ 1 1 +$ 2 3 +$ 3 2 +$ 4 4 + +language Essence 1.3 + +letting p be permutation((2, 3, 4)) +letting s be {(1, 1), (2, 3), (3, 4), (4, 2)} +$ Visualisation for s +$ 1 1 +$ 2 3 +$ 3 4 +$ 4 2 + +language Essence 1.3 + +letting p be permutation((2, 4, 3)) +letting s be {(1, 1), (2, 4), (3, 2), (4, 3)} +$ Visualisation for s +$ 1 1 +$ 2 4 +$ 3 2 +$ 4 3 + +language Essence 1.3 + +letting p be permutation((2, 4)) +letting s be {(1, 1), (2, 4), (3, 3), (4, 2)} +$ Visualisation for s +$ 1 1 +$ 2 4 +$ 3 3 +$ 4 2 + +language Essence 1.3 + +letting p be permutation((1, 2)) +letting s be {(1, 2), (2, 1), (3, 3), (4, 4)} +$ Visualisation for s +$ 1 2 +$ 2 1 +$ 3 3 +$ 4 4 + +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4)) +letting s be {(1, 2), (2, 1), (3, 4), (4, 3)} +$ Visualisation for s +$ 1 2 +$ 2 1 +$ 3 4 +$ 4 3 + +language Essence 1.3 + +letting p be permutation((1, 2, 3)) +letting s be {(1, 2), (2, 3), (3, 1), (4, 4)} +$ Visualisation for s +$ 1 2 +$ 2 3 +$ 3 1 +$ 4 4 + +language Essence 1.3 + +letting p be permutation((1, 2, 3, 4)) +letting s be {(1, 2), (2, 3), (3, 4), (4, 1)} +$ Visualisation for s +$ 1 2 +$ 2 3 +$ 3 4 +$ 4 1 + +language Essence 1.3 + +letting p be permutation((1, 2, 4, 3)) +letting s be {(1, 2), (2, 4), (3, 1), (4, 3)} +$ Visualisation for s +$ 1 2 +$ 2 4 +$ 3 1 +$ 4 3 + +language Essence 1.3 + +letting p be permutation((1, 2, 4)) +letting s be {(1, 2), (2, 4), (3, 3), (4, 1)} +$ Visualisation for s +$ 1 2 +$ 2 4 +$ 3 3 +$ 4 1 + +language Essence 1.3 + +letting p be permutation((1, 3, 2)) +letting s be {(1, 3), (2, 1), (3, 2), (4, 4)} +$ Visualisation for s +$ 1 3 +$ 2 1 +$ 3 2 +$ 4 4 + +language Essence 1.3 + +letting p be permutation((1, 3, 4, 2)) +letting s be {(1, 3), (2, 1), (3, 4), (4, 2)} +$ Visualisation for s +$ 1 3 +$ 2 1 +$ 3 4 +$ 4 2 + +language Essence 1.3 + +letting p be permutation((1, 3)) +letting s be {(1, 3), (2, 2), (3, 1), (4, 4)} +$ Visualisation for s +$ 1 3 +$ 2 2 +$ 3 1 +$ 4 4 + +language Essence 1.3 + +letting p be permutation((1, 3, 4)) +letting s be {(1, 3), (2, 2), (3, 4), (4, 1)} +$ Visualisation for s +$ 1 3 +$ 2 2 +$ 3 4 +$ 4 1 + +language Essence 1.3 + +letting p be permutation((1, 3), (2, 4)) +letting s be {(1, 3), (2, 4), (3, 1), (4, 2)} +$ Visualisation for s +$ 1 3 +$ 2 4 +$ 3 1 +$ 4 2 + +language Essence 1.3 + +letting p be permutation((1, 3, 2, 4)) +letting s be {(1, 3), (2, 4), (3, 2), (4, 1)} +$ Visualisation for s +$ 1 3 +$ 2 4 +$ 3 2 +$ 4 1 + +language Essence 1.3 + +letting p be permutation((1, 4, 3, 2)) +letting s be {(1, 4), (2, 1), (3, 2), (4, 3)} +$ Visualisation for s +$ 1 4 +$ 2 1 +$ 3 2 +$ 4 3 + +language Essence 1.3 + +letting p be permutation((1, 4, 2)) +letting s be {(1, 4), (2, 1), (3, 3), (4, 2)} +$ Visualisation for s +$ 1 4 +$ 2 1 +$ 3 3 +$ 4 2 + +language Essence 1.3 + +letting p be permutation((1, 4, 3)) +letting s be {(1, 4), (2, 2), (3, 1), (4, 3)} +$ Visualisation for s +$ 1 4 +$ 2 2 +$ 3 1 +$ 4 3 + +language Essence 1.3 + +letting p be permutation((1, 4)) +letting s be {(1, 4), (2, 2), (3, 3), (4, 1)} +$ Visualisation for s +$ 1 4 +$ 2 2 +$ 3 3 +$ 4 1 + +language Essence 1.3 + +letting p be permutation((1, 4, 2, 3)) +letting s be {(1, 4), (2, 3), (3, 1), (4, 2)} +$ Visualisation for s +$ 1 4 +$ 2 3 +$ 3 1 +$ 4 2 + +language Essence 1.3 + +letting p be permutation((1, 4), (2, 3)) +letting s be {(1, 4), (2, 3), (3, 2), (4, 1)} +$ Visualisation for s +$ 1 4 +$ 2 3 +$ 3 2 +$ 4 1 + diff --git a/tests/custom/permutations/basic/20/permutation.essence b/tests/custom/permutations/basic/20/permutation.essence new file mode 100644 index 0000000000..876cbaab24 --- /dev/null +++ b/tests/custom/permutations/basic/20/permutation.essence @@ -0,0 +1,6 @@ + +find p : permutation (size 10) of int(1..10) +find q : permutation (size 10) of int(1..10) + +such that + and([ permute(p, b) = a | (a,b) <- q]) diff --git a/tests/custom/permutations/basic/20/run.sh b/tests/custom/permutations/basic/20/run.sh new file mode 100755 index 0000000000..0ab098f9b5 --- /dev/null +++ b/tests/custom/permutations/basic/20/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence --number-of-solutions=200 +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/basic/20/stdout.expected b/tests/custom/permutations/basic/20/stdout.expected new file mode 100644 index 0000000000..eb4493e3a5 --- /dev/null +++ b/tests/custom/permutations/basic/20/stdout.expected @@ -0,0 +1,1004 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Copying solution to: permutation-000001.solution +Copying solution to: permutation-000002.solution +Copying solution to: permutation-000003.solution +Copying solution to: permutation-000004.solution +Copying solution to: permutation-000005.solution +Copying solution to: permutation-000006.solution +Copying solution to: permutation-000007.solution +Copying solution to: permutation-000008.solution +Copying solution to: permutation-000009.solution +Copying solution to: permutation-000010.solution +Copying solution to: permutation-000011.solution +Copying solution to: permutation-000012.solution +Copying solution to: permutation-000013.solution +Copying solution to: permutation-000014.solution +Copying solution to: permutation-000015.solution +Copying solution to: permutation-000016.solution +Copying solution to: permutation-000017.solution +Copying solution to: permutation-000018.solution +Copying solution to: permutation-000019.solution +Copying solution to: permutation-000020.solution +Copying solution to: permutation-000021.solution +Copying solution to: permutation-000022.solution +Copying solution to: permutation-000023.solution +Copying solution to: permutation-000024.solution +Copying solution to: permutation-000025.solution +Copying solution to: permutation-000026.solution +Copying solution to: permutation-000027.solution +Copying solution to: permutation-000028.solution +Copying solution to: permutation-000029.solution +Copying solution to: permutation-000030.solution +Copying solution to: permutation-000031.solution +Copying solution to: permutation-000032.solution +Copying solution to: permutation-000033.solution +Copying solution to: permutation-000034.solution +Copying solution to: permutation-000035.solution +Copying solution to: permutation-000036.solution +Copying solution to: permutation-000037.solution +Copying solution to: permutation-000038.solution +Copying solution to: permutation-000039.solution +Copying solution to: permutation-000040.solution +Copying solution to: permutation-000041.solution +Copying solution to: permutation-000042.solution +Copying solution to: permutation-000043.solution +Copying solution to: permutation-000044.solution +Copying solution to: permutation-000045.solution +Copying solution to: permutation-000046.solution +Copying solution to: permutation-000047.solution +Copying solution to: permutation-000048.solution +Copying solution to: permutation-000049.solution +Copying solution to: permutation-000050.solution +Copying solution to: permutation-000051.solution +Copying solution to: permutation-000052.solution +Copying solution to: permutation-000053.solution +Copying solution to: permutation-000054.solution +Copying solution to: permutation-000055.solution +Copying solution to: permutation-000056.solution +Copying solution to: permutation-000057.solution +Copying solution to: permutation-000058.solution +Copying solution to: permutation-000059.solution +Copying solution to: permutation-000060.solution +Copying solution to: permutation-000061.solution +Copying solution to: permutation-000062.solution +Copying solution to: permutation-000063.solution +Copying solution to: permutation-000064.solution +Copying solution to: permutation-000065.solution +Copying solution to: permutation-000066.solution +Copying solution to: permutation-000067.solution +Copying solution to: permutation-000068.solution +Copying solution to: permutation-000069.solution +Copying solution to: permutation-000070.solution +Copying solution to: permutation-000071.solution +Copying solution to: permutation-000072.solution +Copying solution to: permutation-000073.solution +Copying solution to: permutation-000074.solution +Copying solution to: permutation-000075.solution +Copying solution to: permutation-000076.solution +Copying solution to: permutation-000077.solution +Copying solution to: permutation-000078.solution +Copying solution to: permutation-000079.solution +Copying solution to: permutation-000080.solution +Copying solution to: permutation-000081.solution +Copying solution to: permutation-000082.solution +Copying solution to: permutation-000083.solution +Copying solution to: permutation-000084.solution +Copying solution to: permutation-000085.solution +Copying solution to: permutation-000086.solution +Copying solution to: permutation-000087.solution +Copying solution to: permutation-000088.solution +Copying solution to: permutation-000089.solution +Copying solution to: permutation-000090.solution +Copying solution to: permutation-000091.solution +Copying solution to: permutation-000092.solution +Copying solution to: permutation-000093.solution +Copying solution to: permutation-000094.solution +Copying solution to: permutation-000095.solution +Copying solution to: permutation-000096.solution +Copying solution to: permutation-000097.solution +Copying solution to: permutation-000098.solution +Copying solution to: permutation-000099.solution +Copying solution to: permutation-000100.solution +Copying solution to: permutation-000101.solution +Copying solution to: permutation-000102.solution +Copying solution to: permutation-000103.solution +Copying solution to: permutation-000104.solution +Copying solution to: permutation-000105.solution +Copying solution to: permutation-000106.solution +Copying solution to: permutation-000107.solution +Copying solution to: permutation-000108.solution +Copying solution to: permutation-000109.solution +Copying solution to: permutation-000110.solution +Copying solution to: permutation-000111.solution +Copying solution to: permutation-000112.solution +Copying solution to: permutation-000113.solution +Copying solution to: permutation-000114.solution +Copying solution to: permutation-000115.solution +Copying solution to: permutation-000116.solution +Copying solution to: permutation-000117.solution +Copying solution to: permutation-000118.solution +Copying solution to: permutation-000119.solution +Copying solution to: permutation-000120.solution +Copying solution to: permutation-000121.solution +Copying solution to: permutation-000122.solution +Copying solution to: permutation-000123.solution +Copying solution to: permutation-000124.solution +Copying solution to: permutation-000125.solution +Copying solution to: permutation-000126.solution +Copying solution to: permutation-000127.solution +Copying solution to: permutation-000128.solution +Copying solution to: permutation-000129.solution +Copying solution to: permutation-000130.solution +Copying solution to: permutation-000131.solution +Copying solution to: permutation-000132.solution +Copying solution to: permutation-000133.solution +Copying solution to: permutation-000134.solution +Copying solution to: permutation-000135.solution +Copying solution to: permutation-000136.solution +Copying solution to: permutation-000137.solution +Copying solution to: permutation-000138.solution +Copying solution to: permutation-000139.solution +Copying solution to: permutation-000140.solution +Copying solution to: permutation-000141.solution +Copying solution to: permutation-000142.solution +Copying solution to: permutation-000143.solution +Copying solution to: permutation-000144.solution +Copying solution to: permutation-000145.solution +Copying solution to: permutation-000146.solution +Copying solution to: permutation-000147.solution +Copying solution to: permutation-000148.solution +Copying solution to: permutation-000149.solution +Copying solution to: permutation-000150.solution +Copying solution to: permutation-000151.solution +Copying solution to: permutation-000152.solution +Copying solution to: permutation-000153.solution +Copying solution to: permutation-000154.solution +Copying solution to: permutation-000155.solution +Copying solution to: permutation-000156.solution +Copying solution to: permutation-000157.solution +Copying solution to: permutation-000158.solution +Copying solution to: permutation-000159.solution +Copying solution to: permutation-000160.solution +Copying solution to: permutation-000161.solution +Copying solution to: permutation-000162.solution +Copying solution to: permutation-000163.solution +Copying solution to: permutation-000164.solution +Copying solution to: permutation-000165.solution +Copying solution to: permutation-000166.solution +Copying solution to: permutation-000167.solution +Copying solution to: permutation-000168.solution +Copying solution to: permutation-000169.solution +Copying solution to: permutation-000170.solution +Copying solution to: permutation-000171.solution +Copying solution to: permutation-000172.solution +Copying solution to: permutation-000173.solution +Copying solution to: permutation-000174.solution +Copying solution to: permutation-000175.solution +Copying solution to: permutation-000176.solution +Copying solution to: permutation-000177.solution +Copying solution to: permutation-000178.solution +Copying solution to: permutation-000179.solution +Copying solution to: permutation-000180.solution +Copying solution to: permutation-000181.solution +Copying solution to: permutation-000182.solution +Copying solution to: permutation-000183.solution +Copying solution to: permutation-000184.solution +Copying solution to: permutation-000185.solution +Copying solution to: permutation-000186.solution +Copying solution to: permutation-000187.solution +Copying solution to: permutation-000188.solution +Copying solution to: permutation-000189.solution +Copying solution to: permutation-000190.solution +Copying solution to: permutation-000191.solution +Copying solution to: permutation-000192.solution +Copying solution to: permutation-000193.solution +Copying solution to: permutation-000194.solution +Copying solution to: permutation-000195.solution +Copying solution to: permutation-000196.solution +Copying solution to: permutation-000197.solution +Copying solution to: permutation-000198.solution +Copying solution to: permutation-000199.solution +Copying solution to: permutation-000200.solution +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 6), (7, 8), (9, 10)) +letting q be permutation((1, 2), (3, 4), (5, 6), (7, 8), (9, 10)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 6), (7, 8, 9, 10)) +letting q be permutation((1, 2), (3, 4), (5, 6), (7, 10, 9, 8)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 6), (7, 8, 10, 9)) +letting q be permutation((1, 2), (3, 4), (5, 6), (7, 9, 10, 8)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 6), (7, 9, 10, 8)) +letting q be permutation((1, 2), (3, 4), (5, 6), (7, 8, 10, 9)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 6), (7, 9), (8, 10)) +letting q be permutation((1, 2), (3, 4), (5, 6), (7, 9), (8, 10)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 6), (7, 9, 8, 10)) +letting q be permutation((1, 2), (3, 4), (5, 6), (7, 10, 8, 9)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 6), (7, 10, 9, 8)) +letting q be permutation((1, 2), (3, 4), (5, 6), (7, 8, 9, 10)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 6), (7, 10, 8, 9)) +letting q be permutation((1, 2), (3, 4), (5, 6), (7, 9, 8, 10)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 6), (7, 10), (8, 9)) +letting q be permutation((1, 2), (3, 4), (5, 6), (7, 10), (8, 9)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 6, 7), (8, 9, 10)) +letting q be permutation((1, 2), (3, 4), (5, 7, 6), (8, 10, 9)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 6, 7), (8, 10, 9)) +letting q be permutation((1, 2), (3, 4), (5, 7, 6), (8, 9, 10)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 6, 7, 8), (9, 10)) +letting q be permutation((1, 2), (3, 4), (5, 8, 7, 6), (9, 10)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 6, 7, 8, 9, 10)) +letting q be permutation((1, 2), (3, 4), (5, 10, 9, 8, 7, 6)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 6, 7, 8, 10, 9)) +letting q be permutation((1, 2), (3, 4), (5, 9, 10, 8, 7, 6)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 6, 7, 9, 10, 8)) +letting q be permutation((1, 2), (3, 4), (5, 8, 10, 9, 7, 6)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 6, 7, 9), (8, 10)) +letting q be permutation((1, 2), (3, 4), (5, 9, 7, 6), (8, 10)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 6, 7, 9, 8, 10)) +letting q be permutation((1, 2), (3, 4), (5, 10, 8, 9, 7, 6)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 6, 7, 10, 9, 8)) +letting q be permutation((1, 2), (3, 4), (5, 8, 9, 10, 7, 6)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 6, 7, 10, 8, 9)) +letting q be permutation((1, 2), (3, 4), (5, 9, 8, 10, 7, 6)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 6, 7, 10), (8, 9)) +letting q be permutation((1, 2), (3, 4), (5, 10, 7, 6), (8, 9)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 6, 8, 7), (9, 10)) +letting q be permutation((1, 2), (3, 4), (5, 7, 8, 6), (9, 10)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 6, 8, 9, 10, 7)) +letting q be permutation((1, 2), (3, 4), (5, 7, 10, 9, 8, 6)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 6, 8, 10, 9, 7)) +letting q be permutation((1, 2), (3, 4), (5, 7, 9, 10, 8, 6)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 6, 8), (7, 9, 10)) +letting q be permutation((1, 2), (3, 4), (5, 8, 6), (7, 10, 9)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 6, 8, 7, 9, 10)) +letting q be permutation((1, 2), (3, 4), (5, 10, 9, 7, 8, 6)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 6, 8, 10, 7, 9)) +letting q be permutation((1, 2), (3, 4), (5, 9, 7, 10, 8, 6)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 6, 8, 10), (7, 9)) +letting q be permutation((1, 2), (3, 4), (5, 10, 8, 6), (7, 9)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 6, 8), (7, 10, 9)) +letting q be permutation((1, 2), (3, 4), (5, 8, 6), (7, 9, 10)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 6, 8, 7, 10, 9)) +letting q be permutation((1, 2), (3, 4), (5, 9, 10, 7, 8, 6)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 6, 8, 9), (7, 10)) +letting q be permutation((1, 2), (3, 4), (5, 9, 8, 6), (7, 10)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 6, 8, 9, 7, 10)) +letting q be permutation((1, 2), (3, 4), (5, 10, 7, 9, 8, 6)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 6, 9, 10, 8, 7)) +letting q be permutation((1, 2), (3, 4), (5, 7, 8, 10, 9, 6)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 6, 9, 7), (8, 10)) +letting q be permutation((1, 2), (3, 4), (5, 7, 9, 6), (8, 10)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 6, 9, 8, 10, 7)) +letting q be permutation((1, 2), (3, 4), (5, 7, 10, 8, 9, 6)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 6, 9, 10, 7, 8)) +letting q be permutation((1, 2), (3, 4), (5, 8, 7, 10, 9, 6)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 6, 9, 10), (7, 8)) +letting q be permutation((1, 2), (3, 4), (5, 10, 9, 6), (7, 8)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 6, 9), (7, 8, 10)) +letting q be permutation((1, 2), (3, 4), (5, 9, 6), (7, 10, 8)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 6, 9, 7, 8, 10)) +letting q be permutation((1, 2), (3, 4), (5, 10, 8, 7, 9, 6)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 6, 9, 7, 10, 8)) +letting q be permutation((1, 2), (3, 4), (5, 8, 10, 7, 9, 6)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 6, 9, 8), (7, 10)) +letting q be permutation((1, 2), (3, 4), (5, 8, 9, 6), (7, 10)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 6, 9), (7, 10, 8)) +letting q be permutation((1, 2), (3, 4), (5, 9, 6), (7, 8, 10)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 6, 9, 8, 7, 10)) +letting q be permutation((1, 2), (3, 4), (5, 10, 7, 8, 9, 6)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 6, 10, 9, 8, 7)) +letting q be permutation((1, 2), (3, 4), (5, 7, 8, 9, 10, 6)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 6, 10, 8, 9, 7)) +letting q be permutation((1, 2), (3, 4), (5, 7, 9, 8, 10, 6)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 6, 10, 7), (8, 9)) +letting q be permutation((1, 2), (3, 4), (5, 7, 10, 6), (8, 9)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 6, 10, 9, 7, 8)) +letting q be permutation((1, 2), (3, 4), (5, 8, 7, 9, 10, 6)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 6, 10, 9), (7, 8)) +letting q be permutation((1, 2), (3, 4), (5, 9, 10, 6), (7, 8)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 6, 10, 7, 8, 9)) +letting q be permutation((1, 2), (3, 4), (5, 9, 8, 7, 10, 6)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 6, 10), (7, 8, 9)) +letting q be permutation((1, 2), (3, 4), (5, 10, 6), (7, 9, 8)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 6, 10, 8), (7, 9)) +letting q be permutation((1, 2), (3, 4), (5, 8, 10, 6), (7, 9)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 6, 10, 7, 9, 8)) +letting q be permutation((1, 2), (3, 4), (5, 8, 9, 7, 10, 6)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 6, 10, 8, 7, 9)) +letting q be permutation((1, 2), (3, 4), (5, 9, 7, 8, 10, 6)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 6, 10), (7, 9, 8)) +letting q be permutation((1, 2), (3, 4), (5, 10, 6), (7, 8, 9)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 7, 6), (8, 9, 10)) +letting q be permutation((1, 2), (3, 4), (5, 6, 7), (8, 10, 9)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 7, 6), (8, 10, 9)) +letting q be permutation((1, 2), (3, 4), (5, 6, 7), (8, 9, 10)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 7, 8, 6), (9, 10)) +letting q be permutation((1, 2), (3, 4), (5, 6, 8, 7), (9, 10)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 7, 8, 9, 10, 6)) +letting q be permutation((1, 2), (3, 4), (5, 6, 10, 9, 8, 7)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 7, 8, 10, 9, 6)) +letting q be permutation((1, 2), (3, 4), (5, 6, 9, 10, 8, 7)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 7, 9, 10, 8, 6)) +letting q be permutation((1, 2), (3, 4), (5, 6, 8, 10, 9, 7)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 7, 9, 6), (8, 10)) +letting q be permutation((1, 2), (3, 4), (5, 6, 9, 7), (8, 10)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 7, 9, 8, 10, 6)) +letting q be permutation((1, 2), (3, 4), (5, 6, 10, 8, 9, 7)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 7, 10, 9, 8, 6)) +letting q be permutation((1, 2), (3, 4), (5, 6, 8, 9, 10, 7)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 7, 10, 8, 9, 6)) +letting q be permutation((1, 2), (3, 4), (5, 6, 9, 8, 10, 7)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 7, 10, 6), (8, 9)) +letting q be permutation((1, 2), (3, 4), (5, 6, 10, 7), (8, 9)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 7), (6, 8), (9, 10)) +letting q be permutation((1, 2), (3, 4), (5, 7), (6, 8), (9, 10)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 7), (6, 8, 9, 10)) +letting q be permutation((1, 2), (3, 4), (5, 7), (6, 10, 9, 8)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 7), (6, 8, 10, 9)) +letting q be permutation((1, 2), (3, 4), (5, 7), (6, 9, 10, 8)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 7, 6, 8), (9, 10)) +letting q be permutation((1, 2), (3, 4), (5, 8, 6, 7), (9, 10)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 7, 6, 8, 9, 10)) +letting q be permutation((1, 2), (3, 4), (5, 10, 9, 8, 6, 7)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 7, 6, 8, 10, 9)) +letting q be permutation((1, 2), (3, 4), (5, 9, 10, 8, 6, 7)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 7, 9, 10, 6, 8)) +letting q be permutation((1, 2), (3, 4), (5, 8, 6, 10, 9, 7)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 7, 9, 10), (6, 8)) +letting q be permutation((1, 2), (3, 4), (5, 10, 9, 7), (6, 8)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 7, 9), (6, 8, 10)) +letting q be permutation((1, 2), (3, 4), (5, 9, 7), (6, 10, 8)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 7, 9, 6, 8, 10)) +letting q be permutation((1, 2), (3, 4), (5, 10, 8, 6, 9, 7)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 7, 10, 9, 6, 8)) +letting q be permutation((1, 2), (3, 4), (5, 8, 6, 9, 10, 7)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 7, 10, 9), (6, 8)) +letting q be permutation((1, 2), (3, 4), (5, 9, 10, 7), (6, 8)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 7, 10, 6, 8, 9)) +letting q be permutation((1, 2), (3, 4), (5, 9, 8, 6, 10, 7)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 7, 10), (6, 8, 9)) +letting q be permutation((1, 2), (3, 4), (5, 10, 7), (6, 9, 8)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 7), (6, 9, 10, 8)) +letting q be permutation((1, 2), (3, 4), (5, 7), (6, 8, 10, 9)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 7), (6, 9), (8, 10)) +letting q be permutation((1, 2), (3, 4), (5, 7), (6, 9), (8, 10)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 7), (6, 9, 8, 10)) +letting q be permutation((1, 2), (3, 4), (5, 7), (6, 10, 8, 9)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 7, 6, 9, 10, 8)) +letting q be permutation((1, 2), (3, 4), (5, 8, 10, 9, 6, 7)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 7, 6, 9), (8, 10)) +letting q be permutation((1, 2), (3, 4), (5, 9, 6, 7), (8, 10)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 7, 6, 9, 8, 10)) +letting q be permutation((1, 2), (3, 4), (5, 10, 8, 9, 6, 7)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 7, 8), (6, 9, 10)) +letting q be permutation((1, 2), (3, 4), (5, 8, 7), (6, 10, 9)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 7, 8, 6, 9, 10)) +letting q be permutation((1, 2), (3, 4), (5, 10, 9, 6, 8, 7)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 7, 8, 10, 6, 9)) +letting q be permutation((1, 2), (3, 4), (5, 9, 6, 10, 8, 7)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 7, 8, 10), (6, 9)) +letting q be permutation((1, 2), (3, 4), (5, 10, 8, 7), (6, 9)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 7, 10, 8), (6, 9)) +letting q be permutation((1, 2), (3, 4), (5, 8, 10, 7), (6, 9)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 7, 10, 6, 9, 8)) +letting q be permutation((1, 2), (3, 4), (5, 8, 9, 6, 10, 7)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 7, 10, 8, 6, 9)) +letting q be permutation((1, 2), (3, 4), (5, 9, 6, 8, 10, 7)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 7, 10), (6, 9, 8)) +letting q be permutation((1, 2), (3, 4), (5, 10, 7), (6, 8, 9)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 7), (6, 10, 9, 8)) +letting q be permutation((1, 2), (3, 4), (5, 7), (6, 8, 9, 10)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 7), (6, 10, 8, 9)) +letting q be permutation((1, 2), (3, 4), (5, 7), (6, 9, 8, 10)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 7), (6, 10), (8, 9)) +letting q be permutation((1, 2), (3, 4), (5, 7), (6, 10), (8, 9)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 7, 6, 10, 9, 8)) +letting q be permutation((1, 2), (3, 4), (5, 8, 9, 10, 6, 7)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 7, 6, 10, 8, 9)) +letting q be permutation((1, 2), (3, 4), (5, 9, 8, 10, 6, 7)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 7, 6, 10), (8, 9)) +letting q be permutation((1, 2), (3, 4), (5, 10, 6, 7), (8, 9)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 7, 8), (6, 10, 9)) +letting q be permutation((1, 2), (3, 4), (5, 8, 7), (6, 9, 10)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 7, 8, 6, 10, 9)) +letting q be permutation((1, 2), (3, 4), (5, 9, 10, 6, 8, 7)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 7, 8, 9), (6, 10)) +letting q be permutation((1, 2), (3, 4), (5, 9, 8, 7), (6, 10)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 7, 8, 9, 6, 10)) +letting q be permutation((1, 2), (3, 4), (5, 10, 6, 9, 8, 7)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 7, 9, 6, 10, 8)) +letting q be permutation((1, 2), (3, 4), (5, 8, 10, 6, 9, 7)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 7, 9, 8), (6, 10)) +letting q be permutation((1, 2), (3, 4), (5, 8, 9, 7), (6, 10)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 7, 9), (6, 10, 8)) +letting q be permutation((1, 2), (3, 4), (5, 9, 7), (6, 8, 10)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 7, 9, 8, 6, 10)) +letting q be permutation((1, 2), (3, 4), (5, 10, 6, 8, 9, 7)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 8, 7, 6), (9, 10)) +letting q be permutation((1, 2), (3, 4), (5, 6, 7, 8), (9, 10)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 8, 9, 10, 7, 6)) +letting q be permutation((1, 2), (3, 4), (5, 6, 7, 10, 9, 8)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 8, 10, 9, 7, 6)) +letting q be permutation((1, 2), (3, 4), (5, 6, 7, 9, 10, 8)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 8, 6), (7, 9, 10)) +letting q be permutation((1, 2), (3, 4), (5, 6, 8), (7, 10, 9)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 8, 7, 9, 10, 6)) +letting q be permutation((1, 2), (3, 4), (5, 6, 10, 9, 7, 8)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 8, 10, 7, 9, 6)) +letting q be permutation((1, 2), (3, 4), (5, 6, 9, 7, 10, 8)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 8, 10, 6), (7, 9)) +letting q be permutation((1, 2), (3, 4), (5, 6, 10, 8), (7, 9)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 8, 6), (7, 10, 9)) +letting q be permutation((1, 2), (3, 4), (5, 6, 8), (7, 9, 10)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 8, 7, 10, 9, 6)) +letting q be permutation((1, 2), (3, 4), (5, 6, 9, 10, 7, 8)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 8, 9, 6), (7, 10)) +letting q be permutation((1, 2), (3, 4), (5, 6, 9, 8), (7, 10)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 8, 9, 7, 10, 6)) +letting q be permutation((1, 2), (3, 4), (5, 6, 10, 7, 9, 8)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 8, 6, 7), (9, 10)) +letting q be permutation((1, 2), (3, 4), (5, 7, 6, 8), (9, 10)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 8, 9, 10, 6, 7)) +letting q be permutation((1, 2), (3, 4), (5, 7, 6, 10, 9, 8)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 8, 10, 9, 6, 7)) +letting q be permutation((1, 2), (3, 4), (5, 7, 6, 9, 10, 8)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 8), (6, 7), (9, 10)) +letting q be permutation((1, 2), (3, 4), (5, 8), (6, 7), (9, 10)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 8, 9, 10), (6, 7)) +letting q be permutation((1, 2), (3, 4), (5, 10, 9, 8), (6, 7)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 8, 10, 9), (6, 7)) +letting q be permutation((1, 2), (3, 4), (5, 9, 10, 8), (6, 7)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 8), (6, 7, 9, 10)) +letting q be permutation((1, 2), (3, 4), (5, 8), (6, 10, 9, 7)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 8, 6, 7, 9, 10)) +letting q be permutation((1, 2), (3, 4), (5, 10, 9, 7, 6, 8)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 8, 10, 6, 7, 9)) +letting q be permutation((1, 2), (3, 4), (5, 9, 7, 6, 10, 8)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 8, 10), (6, 7, 9)) +letting q be permutation((1, 2), (3, 4), (5, 10, 8), (6, 9, 7)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 8), (6, 7, 10, 9)) +letting q be permutation((1, 2), (3, 4), (5, 8), (6, 9, 10, 7)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 8, 6, 7, 10, 9)) +letting q be permutation((1, 2), (3, 4), (5, 9, 10, 7, 6, 8)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 8, 9), (6, 7, 10)) +letting q be permutation((1, 2), (3, 4), (5, 9, 8), (6, 10, 7)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 8, 9, 6, 7, 10)) +letting q be permutation((1, 2), (3, 4), (5, 10, 7, 6, 9, 8)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 8, 6, 9, 10, 7)) +letting q be permutation((1, 2), (3, 4), (5, 7, 10, 9, 6, 8)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 8, 7), (6, 9, 10)) +letting q be permutation((1, 2), (3, 4), (5, 7, 8), (6, 10, 9)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 8, 10, 7), (6, 9)) +letting q be permutation((1, 2), (3, 4), (5, 7, 10, 8), (6, 9)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 8, 10, 6, 9, 7)) +letting q be permutation((1, 2), (3, 4), (5, 7, 9, 6, 10, 8)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 8), (6, 9, 10, 7)) +letting q be permutation((1, 2), (3, 4), (5, 8), (6, 7, 10, 9)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 8, 7, 6, 9, 10)) +letting q be permutation((1, 2), (3, 4), (5, 10, 9, 6, 7, 8)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 8, 10, 7, 6, 9)) +letting q be permutation((1, 2), (3, 4), (5, 9, 6, 7, 10, 8)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 8, 10), (6, 9, 7)) +letting q be permutation((1, 2), (3, 4), (5, 10, 8), (6, 7, 9)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 8), (6, 9), (7, 10)) +letting q be permutation((1, 2), (3, 4), (5, 8), (6, 9), (7, 10)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 8), (6, 9, 7, 10)) +letting q be permutation((1, 2), (3, 4), (5, 8), (6, 10, 7, 9)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 8, 6, 9), (7, 10)) +letting q be permutation((1, 2), (3, 4), (5, 9, 6, 8), (7, 10)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 8, 6, 9, 7, 10)) +letting q be permutation((1, 2), (3, 4), (5, 10, 7, 9, 6, 8)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 8, 7, 10, 6, 9)) +letting q be permutation((1, 2), (3, 4), (5, 9, 6, 10, 7, 8)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 8, 7, 10), (6, 9)) +letting q be permutation((1, 2), (3, 4), (5, 10, 7, 8), (6, 9)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 8, 6, 10, 9, 7)) +letting q be permutation((1, 2), (3, 4), (5, 7, 9, 10, 6, 8)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 8, 7), (6, 10, 9)) +letting q be permutation((1, 2), (3, 4), (5, 7, 8), (6, 9, 10)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 8, 9, 6, 10, 7)) +letting q be permutation((1, 2), (3, 4), (5, 7, 10, 6, 9, 8)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 8, 9, 7), (6, 10)) +letting q be permutation((1, 2), (3, 4), (5, 7, 9, 8), (6, 10)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 8), (6, 10, 9, 7)) +letting q be permutation((1, 2), (3, 4), (5, 8), (6, 7, 9, 10)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 8, 7, 6, 10, 9)) +letting q be permutation((1, 2), (3, 4), (5, 9, 10, 6, 7, 8)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 8, 9), (6, 10, 7)) +letting q be permutation((1, 2), (3, 4), (5, 9, 8), (6, 7, 10)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 8, 9, 7, 6, 10)) +letting q be permutation((1, 2), (3, 4), (5, 10, 6, 7, 9, 8)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 8), (6, 10, 7, 9)) +letting q be permutation((1, 2), (3, 4), (5, 8), (6, 9, 7, 10)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 8), (6, 10), (7, 9)) +letting q be permutation((1, 2), (3, 4), (5, 8), (6, 10), (7, 9)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 8, 6, 10, 7, 9)) +letting q be permutation((1, 2), (3, 4), (5, 9, 7, 10, 6, 8)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 8, 6, 10), (7, 9)) +letting q be permutation((1, 2), (3, 4), (5, 10, 6, 8), (7, 9)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 8, 7, 9), (6, 10)) +letting q be permutation((1, 2), (3, 4), (5, 9, 7, 8), (6, 10)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 8, 7, 9, 6, 10)) +letting q be permutation((1, 2), (3, 4), (5, 10, 6, 9, 7, 8)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 9, 10, 8, 7, 6)) +letting q be permutation((1, 2), (3, 4), (5, 6, 7, 8, 10, 9)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 9, 7, 6), (8, 10)) +letting q be permutation((1, 2), (3, 4), (5, 6, 7, 9), (8, 10)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 9, 8, 10, 7, 6)) +letting q be permutation((1, 2), (3, 4), (5, 6, 7, 10, 8, 9)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 9, 10, 7, 8, 6)) +letting q be permutation((1, 2), (3, 4), (5, 6, 8, 7, 10, 9)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 9, 10, 6), (7, 8)) +letting q be permutation((1, 2), (3, 4), (5, 6, 10, 9), (7, 8)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 9, 6), (7, 8, 10)) +letting q be permutation((1, 2), (3, 4), (5, 6, 9), (7, 10, 8)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 9, 7, 8, 10, 6)) +letting q be permutation((1, 2), (3, 4), (5, 6, 10, 8, 7, 9)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 9, 7, 10, 8, 6)) +letting q be permutation((1, 2), (3, 4), (5, 6, 8, 10, 7, 9)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 9, 8, 6), (7, 10)) +letting q be permutation((1, 2), (3, 4), (5, 6, 8, 9), (7, 10)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 9, 6), (7, 10, 8)) +letting q be permutation((1, 2), (3, 4), (5, 6, 9), (7, 8, 10)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 9, 8, 7, 10, 6)) +letting q be permutation((1, 2), (3, 4), (5, 6, 10, 7, 8, 9)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 9, 10, 8, 6, 7)) +letting q be permutation((1, 2), (3, 4), (5, 7, 6, 8, 10, 9)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 9, 6, 7), (8, 10)) +letting q be permutation((1, 2), (3, 4), (5, 7, 6, 9), (8, 10)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 9, 8, 10, 6, 7)) +letting q be permutation((1, 2), (3, 4), (5, 7, 6, 10, 8, 9)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 9, 10, 8), (6, 7)) +letting q be permutation((1, 2), (3, 4), (5, 8, 10, 9), (6, 7)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 9), (6, 7), (8, 10)) +letting q be permutation((1, 2), (3, 4), (5, 9), (6, 7), (8, 10)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 9, 8, 10), (6, 7)) +letting q be permutation((1, 2), (3, 4), (5, 10, 8, 9), (6, 7)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 9, 10, 6, 7, 8)) +letting q be permutation((1, 2), (3, 4), (5, 8, 7, 6, 10, 9)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 9, 10), (6, 7, 8)) +letting q be permutation((1, 2), (3, 4), (5, 10, 9), (6, 8, 7)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 9), (6, 7, 8, 10)) +letting q be permutation((1, 2), (3, 4), (5, 9), (6, 10, 8, 7)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 9, 6, 7, 8, 10)) +letting q be permutation((1, 2), (3, 4), (5, 10, 8, 7, 6, 9)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 9, 6, 7, 10, 8)) +letting q be permutation((1, 2), (3, 4), (5, 8, 10, 7, 6, 9)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 9, 8), (6, 7, 10)) +letting q be permutation((1, 2), (3, 4), (5, 8, 9), (6, 10, 7)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 9), (6, 7, 10, 8)) +letting q be permutation((1, 2), (3, 4), (5, 9), (6, 8, 10, 7)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 9, 8, 6, 7, 10)) +letting q be permutation((1, 2), (3, 4), (5, 10, 7, 6, 8, 9)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 9, 10, 7), (6, 8)) +letting q be permutation((1, 2), (3, 4), (5, 7, 10, 9), (6, 8)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 9, 10, 6, 8, 7)) +letting q be permutation((1, 2), (3, 4), (5, 7, 8, 6, 10, 9)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 9, 6, 8, 10, 7)) +letting q be permutation((1, 2), (3, 4), (5, 7, 10, 8, 6, 9)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 9, 7), (6, 8, 10)) +letting q be permutation((1, 2), (3, 4), (5, 7, 9), (6, 10, 8)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 9, 10, 7, 6, 8)) +letting q be permutation((1, 2), (3, 4), (5, 8, 6, 7, 10, 9)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 9, 10), (6, 8, 7)) +letting q be permutation((1, 2), (3, 4), (5, 10, 9), (6, 7, 8)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 9), (6, 8, 10, 7)) +letting q be permutation((1, 2), (3, 4), (5, 9), (6, 7, 10, 8)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 9, 7, 6, 8, 10)) +letting q be permutation((1, 2), (3, 4), (5, 10, 8, 6, 7, 9)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 9, 6, 8), (7, 10)) +letting q be permutation((1, 2), (3, 4), (5, 8, 6, 9), (7, 10)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 9, 7, 10, 6, 8)) +letting q be permutation((1, 2), (3, 4), (5, 8, 6, 10, 7, 9)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 9), (6, 8), (7, 10)) +letting q be permutation((1, 2), (3, 4), (5, 9), (6, 8), (7, 10)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 9, 7, 10), (6, 8)) +letting q be permutation((1, 2), (3, 4), (5, 10, 7, 9), (6, 8)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 9), (6, 8, 7, 10)) +letting q be permutation((1, 2), (3, 4), (5, 9), (6, 10, 7, 8)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 9, 6, 8, 7, 10)) +letting q be permutation((1, 2), (3, 4), (5, 10, 7, 8, 6, 9)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 9, 7), (6, 10, 8)) +letting q be permutation((1, 2), (3, 4), (5, 7, 9), (6, 8, 10)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4), (5, 9, 8, 6, 10, 7)) +letting q be permutation((1, 2), (3, 4), (5, 7, 10, 6, 8, 9)) diff --git a/tests/custom/permutations/basic/runthese.sh b/tests/custom/permutations/basic/runthese.sh new file mode 100644 index 0000000000..999a81cb2f --- /dev/null +++ b/tests/custom/permutations/basic/runthese.sh @@ -0,0 +1 @@ +stack test --fast --test-arguments "-p custom.permutations.basic" diff --git a/tests/custom/permutations/parsing/01/permutation_given.essence b/tests/custom/permutations/parsing/01/permutation_given.essence deleted file mode 100644 index 6223624be1..0000000000 --- a/tests/custom/permutations/parsing/01/permutation_given.essence +++ /dev/null @@ -1,11 +0,0 @@ - -$ given n : int -letting n be 4 - -$given p : permutation of int(1..n) - -$letting p be permutation((1,3),(2,4)) - -find p : permutation of int(1..n) - - diff --git a/tests/custom/permutations/parsing/01/permutation_given.param b/tests/custom/permutations/parsing/01/permutation_given.param deleted file mode 100644 index 8c41c9b747..0000000000 --- a/tests/custom/permutations/parsing/01/permutation_given.param +++ /dev/null @@ -1 +0,0 @@ -letting p be permutation((1,3),(2,1)) diff --git a/tests/custom/permutations/parsing/01/permutation_given.solution b/tests/custom/permutations/parsing/01/permutation_given.solution deleted file mode 100644 index fa3c1c5e86..0000000000 --- a/tests/custom/permutations/parsing/01/permutation_given.solution +++ /dev/null @@ -1,2 +0,0 @@ -language Essence 1.3 - diff --git a/tests/custom/permutations/parsing/02/run.sh b/tests/custom/permutations/parsing/02/run.sh deleted file mode 100755 index e4c2a2c644..0000000000 --- a/tests/custom/permutations/parsing/02/run.sh +++ /dev/null @@ -1,3 +0,0 @@ -conjure solve *.essence *.essence -cat conjure-output/*.solution -#rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/parsing/runthese.sh b/tests/custom/permutations/parsing/runthese.sh deleted file mode 100644 index fa4c1234c8..0000000000 --- a/tests/custom/permutations/parsing/runthese.sh +++ /dev/null @@ -1 +0,0 @@ -stack test --fast --test-arguments "-p custom.permutations.parsing" From 75d7d10fb12a665d11aaa50648fd304bd31fb4ae Mon Sep 17 00:00:00 2001 From: Fraser Dunlop Date: Thu, 4 Oct 2018 10:18:27 +0100 Subject: [PATCH 004/229] housekeeping --- .../Rules/Horizontal/.Permutation.hs.swo | Bin 12288 -> 0 bytes src/Conjure/Rules/Horizontal/Permutation.hs | 23 ++-------- .../Rules/Vertical/Permutation/AsFunction.hs | 43 ------------------ 3 files changed, 3 insertions(+), 63 deletions(-) delete mode 100644 src/Conjure/Rules/Horizontal/.Permutation.hs.swo diff --git a/src/Conjure/Rules/Horizontal/.Permutation.hs.swo b/src/Conjure/Rules/Horizontal/.Permutation.hs.swo deleted file mode 100644 index bc034e3e0859792b31933e26ac50799b8cd17399..0000000000000000000000000000000000000000 GIT binary patch literal 0 HcmV?d00001 literal 12288 zcmeI2OKjXk7{{kP%cB%g@etzhHHjiyc)d+|2t`e+v}x0bq)kg7f^C#KyR*Aay|x*T z+oVlFf^w^bkl@0Br+Pp_0x2L4Js>VTDse!F8(iRkpj_a<1rYpa?0t5#8*xI&mVRsR z%s1bR|NiEi*~AOmj!n(bWA-+N<4(pN3|9-Q8+Wo7Rv9ac#nN_F-sjjSoQR7kH?w=z z_8fmr>u0pX`~;6q$so)Z1Aj3VJRgZ-eouORIQDpy-yaC~Y~V}B%g=IAi=`voz_+W> zny#~oOo2>+UJAsroO^5&duaQJp6Y`GTWQN(M|-u%>M{i~1u_LP1u_LP1u_LP1u_LP z1^#CW$Z!LD7WZ^rdS8dq^M;P|-|2BUEx*5`KK+`VG6gaPG6gaPG6gaPG6gaPG6gaP zG6gaPG6gaP{(}lQCB{C)kN>-Gz~J!z|N8I$A2u`gJ$N6y3!gCv2Vb~;1%#37zHM{dK+Wkflt8O z;4SbbxByJ>*R70Q2A9AEPy;i7fiG`i>@_e8e%;8}yI=_%2YbPln;H8ETm&b~$c(X7CQ4#|5weCV&C%1Ha*qGFQMC;B)X9XdXne%GLW5G*4sXJ2W8hWj=X< zg3nL8k_*QhV3Zu(i+F#l)Yz=IO242E=_vK}MKpCDta!I#`fMq~_E zW*uqKFvrOx*QenimZ=J4({KeU4OdOtk=u#0`r`J!mF7(w}1+&vnG|F-Jr_gS|N=Fjc!`1Hol1 zd>W$TuB_^??&8l-slXy`5@sYl9Xq~s%PudWcXrL#lI&4gm#v!q79q>5!*7x?%ImV# zv(h4+q{wLzt7Etpm4c2Ug9eUqAze&xQtJRAWl`9CnU1_9xJy@w1>_`UWP~`d* z*q?U1n3It-;ig67(Z1L(YCFM0!I7ep_wpJ`iqbH75FLY26>Ue~biP7{V=buUtOtE0 z4!bLE1sP5V8zWy{NVSWGPY4ucQS%SSGh#k9~@d;`(THv0Eky8KR@UTVAF@ zqJu7)N`ghzPAPxtqT$U@+9g|@B!tt3`tEf2K%rvtjMCRg>sx?OC7k+}shMBWfH#Ii z>>XSa$p%_rdUe}Op=Kbl*PZ9mwz+g}ooh~+^8<9!#}Zpo8?=*+ZqHP?;N4x1j*_xn zdo3Qv#9eO8z4q-~dz}`#EtpV}X3Q=(Ua`_d!Hwan1r3x4`XOmY__!wDAlo$G+3lWh zia{+5B3I>)d`r%0+<*>>mh90jASSJ3i?ScdR)s^a$mkjv`&$C2qHn3I*<^>=+EJqJ zWEopc#7fmvTD8ZEeh!^cqT8I)@uchf$426&5fMaO2&D7Y*c;WV&+loftgi*fT#Hn0 z_X9~KUUq%tvSls@C<(i@8;tccsE;R?Q*klJlCwp~BNA%}Ez$y(9iw6(f*O_To7#-0 zLov#_sxVJ0aA}=sA+xPq`r`FgX#WR|dsM0@VQdPJ4}0 zOU7CqP2=ZAniiE+T9v-gZqJIKi0!<+*N elems + let prmTup pt = take (length pt) $ zip (cycle pt) (drop 1 $ cycle pt) + permTups = join $ prmTup <$> elems let outLiteral = make matrixLiteral (TypeMatrix TypeInt (TypeTuple [inner,inner])) (DomainInt [RangeBounded 1 (fromInt (genericLength permTups))]) @@ -61,7 +44,7 @@ rule_Permute_Literal = "permutation-permute-literal{AsFunction}" `namedRule` the (fPat, f) <- quantifiedVar (tPat, t) <- quantifiedVar (gPat, g) <- quantifiedVar - (ePat, e) <- quantifiedVar + (ePat, _) <- quantifiedVar return $ WithLocals [essence| &h |] (AuxiliaryVars diff --git a/src/Conjure/Rules/Vertical/Permutation/AsFunction.hs b/src/Conjure/Rules/Vertical/Permutation/AsFunction.hs index 1c26a6184b..fb68412371 100644 --- a/src/Conjure/Rules/Vertical/Permutation/AsFunction.hs +++ b/src/Conjure/Rules/Vertical/Permutation/AsFunction.hs @@ -4,36 +4,6 @@ module Conjure.Rules.Vertical.Permutation.AsFunction where import Conjure.Rules.Import --- | This just unwraps the function in a comprehension --- Just like having the bare bijective total function in the comprehension --- --- unclear if this should stay but it is here for now ---rule_Permute_Comprehension :: Rule ---rule_Permute_Comprehension = "permutation-comprehension{AsFunction}" `namedRule` theRule where --- theRule (Comprehension body gensOrConds) = do --- (gocBefore, (pat, perm, over), gocAfter) <- matchFirst gensOrConds $ \ goc -> case goc of --- Generator (GenInExpr pat [essence| permute(&perm,&over) |]) -> return (pat, perm, over) --- _ -> na "rule_Comprehension" --- TypePermutation{} <- typeOf perm --- Permutation_AsFunction <- representationOf perm ----- [f] <- downX1 perm ----- horizontal? --- return --- ( "Vertical rule for permutation-comprehension, AsFunction representation" --- , do --- (iPat, i) <- quantifiedVar --- return $ Comprehension body --- $ gocBefore --- ++ [ Generator (GenInExpr pat [essence| --- [permute(&perm, &i) | &iPat <- &over] --- |] --- ) --- ] --- ++ gocAfter --- ) --- theRule _ = na "rule_Comprehension" - - rule_Permute_Comprehension_Tuples :: Rule rule_Permute_Comprehension_Tuples = "permutation-comprehension-tuples{AsFunction}" `namedRule` theRule where theRule (Comprehension body gensOrConds) = do @@ -72,16 +42,3 @@ rule_Permute = "permutation-permute{AsFunction}" `namedRule` theRule where else na "rule_Permute" theRule _ = na "rule_Permute" ---rule_Compose :: Rule ---rule_Compose = "permutation-compose{AsFunction}" `namedRule` theRule where --- theRule [essence| compose(&p, &q) |] = do --- TypePermutation innerP <- typeOf p --- TypePermutation innerQ <- typeOf q --- if typesUnify [innerP, innerQ] --- then return --- ( "Vertical rule for permutation composition, AsFunction representation" --- , do --- --- ) --- else na "rule_Compose" --- theRule _ = na "rule_Compose" From 4a42268bc5a187ced0f113ad3b0610a48fa7664f Mon Sep 17 00:00:00 2001 From: Fraser Dunlop Date: Tue, 9 Oct 2018 11:15:12 +0100 Subject: [PATCH 005/229] matrix <=lex permute(p,matrix) rule added for sym --- .../Expression/Op/PermutationTuples.hs | 2 - src/Conjure/Rules/Horizontal/Permutation.hs | 5 +- src/Conjure/Rules/Vertical/Matrix.hs | 100 +++++++++++++++++- .../Rules/Vertical/Permutation/AsFunction.hs | 15 ++- src/Conjure/Rules/Vertical/Tuple.hs | 29 +++++ src/Conjure/UI/Model.hs | 2 + .../permutations/basic/21/permutation.essence | 13 +++ .../permutations/basic/21/permutation.param | 2 + tests/custom/permutations/basic/21/run.sh | 3 + .../permutations/basic/21/stdout.expected | 8 ++ .../permutations/basic/22/permutation.essence | 11 ++ .../permutations/basic/22/permutation.param | 1 + tests/custom/permutations/basic/22/run.sh | 3 + .../permutations/basic/22/stdout.expected | 9 ++ 14 files changed, 196 insertions(+), 7 deletions(-) create mode 100644 tests/custom/permutations/basic/21/permutation.essence create mode 100644 tests/custom/permutations/basic/21/permutation.param create mode 100755 tests/custom/permutations/basic/21/run.sh create mode 100644 tests/custom/permutations/basic/21/stdout.expected create mode 100644 tests/custom/permutations/basic/22/permutation.essence create mode 100644 tests/custom/permutations/basic/22/permutation.param create mode 100755 tests/custom/permutations/basic/22/run.sh create mode 100644 tests/custom/permutations/basic/22/stdout.expected diff --git a/src/Conjure/Language/Expression/Op/PermutationTuples.hs b/src/Conjure/Language/Expression/Op/PermutationTuples.hs index e5054663ed..d698f60bf9 100644 --- a/src/Conjure/Language/Expression/Op/PermutationTuples.hs +++ b/src/Conjure/Language/Expression/Op/PermutationTuples.hs @@ -4,13 +4,11 @@ module Conjure.Language.Expression.Op.PermutationTuples where import Conjure.Prelude import Conjure.Language.Expression.Op.Internal.Common -import Conjure.Bug import qualified Data.Aeson as JSON -- aeson import qualified Data.HashMap.Strict as M -- unordered-containers import qualified Data.Vector as V -- vector -import Data.List (cycle) data OpPermutationTuples x = OpPermutationTuples x deriving (Eq, Ord, Show, Data, Functor, Traversable, Foldable, Typeable, Generic) diff --git a/src/Conjure/Rules/Horizontal/Permutation.hs b/src/Conjure/Rules/Horizontal/Permutation.hs index dce44b34d5..f7994eb83d 100644 --- a/src/Conjure/Rules/Horizontal/Permutation.hs +++ b/src/Conjure/Rules/Horizontal/Permutation.hs @@ -1,10 +1,8 @@ {-# LANGUAGE QuasiQuotes #-} - module Conjure.Rules.Horizontal.Permutation where import Conjure.Rules.Import import Data.List (cycle) - rule_Apply :: Rule rule_Apply = "permutation-apply{rule_Apply}" `namedRule` theRule where theRule [essence| permute(apply(&g, &h),&i) |] = do @@ -21,6 +19,7 @@ rule_Apply = "permutation-apply{rule_Apply}" `namedRule` theRule where theRule _ = na "rule_Apply" + rule_Permute_Literal :: Rule rule_Permute_Literal = "permutation-permute-literal{AsFunction}" `namedRule` theRule where theRule [essence| permute(&p, &i) |] = do @@ -30,7 +29,7 @@ rule_Permute_Literal = "permutation-permute-literal{AsFunction}" `namedRule` the then do innerD <- domainOf i let prmTup pt = take (length pt) $ zip (cycle pt) (drop 1 $ cycle pt) - permTups = join $ prmTup <$> elems + permTups = join $ prmTup <$> elems let outLiteral = make matrixLiteral (TypeMatrix TypeInt (TypeTuple [inner,inner])) (DomainInt [RangeBounded 1 (fromInt (genericLength permTups))]) diff --git a/src/Conjure/Rules/Vertical/Matrix.hs b/src/Conjure/Rules/Vertical/Matrix.hs index ad0ecc09bc..947d9577f0 100644 --- a/src/Conjure/Rules/Vertical/Matrix.hs +++ b/src/Conjure/Rules/Vertical/Matrix.hs @@ -4,7 +4,7 @@ module Conjure.Rules.Vertical.Matrix where import Conjure.Rules.Import -import Conjure.Rules.Vertical.Tuple ( decomposeLexLt, decomposeLexLeq, decomposeLexDotLt, decomposeLexDotLeq ) +import Conjure.Rules.Vertical.Tuple ( decomposeLexLt, decomposeLexLeq, decomposeLexDotLt, decomposeLexDotLeq, decomposeLexDotLeqSym ) rule_Comprehension_Literal :: Rule @@ -379,6 +379,37 @@ rule_Matrix_Lt_Primitive = "matrix-Lt-primitive" `namedRule` theRule where rule_Matrix_Leq_Primitive :: Rule rule_Matrix_Leq_Primitive = "matrix-Leq-primitive" `namedRule` theRule where + theRule [essence| &x .<= permute(&perm, &y) |] = do + tx@TypeMatrix{} <- typeOf x -- TODO: check if x and y have the same arity + ty@(TypeMatrix _ yinner) <- typeOf y + (TypePermutation pinner) <- typeOf perm + if typesUnify [yinner, pinner] + then do + unless (isPrimitiveType tx) $ fail ("not a primitive type:" <+> pretty tx) + unless (isPrimitiveType ty) $ fail ("not a primitive type:" <+> pretty ty) + x' <- flattenIfNeeded x + y' <- flattenIfNeeded y + dy'@(DomainMatrix dyindex _) <- domainOf y' + return + ( "Horizontal rule for matrix <=" + , do + (dPat, d) <- quantifiedVar + (pyName, py) <- auxiliaryVar + return $ WithLocals + [essence| &x' <=lex &py |] + (AuxiliaryVars + --TODO need union of permutation and dy domains + [ Declaration (FindOrGiven LocalFind pyName dy') + , SuchThat + [ [essence| + forAll &dPat : &dyindex . + &py[&d] = permute(&perm,&y'[&d]) + |] + ] + ] + ) + ) + else na "rule_Matrix_Leq_Symbreak_Primitive" theRule p = do (x,y) <- case (match opLeq p, match opDotLeq p) of (Just a, _) -> return a @@ -446,6 +477,17 @@ rule_Matrix_DotLt_Decompose = "matrix-DotLt-tuple" `namedRule` theRule where rule_Matrix_DotLeq_Decompose :: Rule rule_Matrix_DotLeq_Decompose = "matrix-DotLeq-tuple" `namedRule` theRule where + theRule p@[essence| &x .<= permute(&perm, &y) |] = do + tx@TypeMatrix{} <- typeOf x -- TODO: check matrix index & tuple arity + ty@TypeMatrix{} <- typeOf y + when (isPrimitiveType tx) $ fail ("this is a primitive type:" <+> pretty tx) + when (isPrimitiveType ty) $ fail ("this is a primitive type:" <+> pretty ty) + xs <- downX1 x + ys <- downX1 y + return + ( "Horizontal rule for matrix .<=, decomposing" + , return $ decomposeLexDotLeqSym p perm xs ys + ) theRule p = do (x,y) <- match opDotLeq p tx@TypeMatrix{} <- typeOf x -- TODO: check matrix index & tuple arity @@ -459,6 +501,62 @@ rule_Matrix_DotLeq_Decompose = "matrix-DotLeq-tuple" `namedRule` theRule where , return $ decomposeLexDotLeq p xs ys ) +-- HACK +-- Moved inside rule_Matrix_DotLeq_Decompose since we need to do this refinement first +-- otherwise compact will choose the other as it will also match and we fail +rule_Matrix_DotLeq_Symbreak_Decompose :: Rule +rule_Matrix_DotLeq_Symbreak_Decompose = "matrix-DotLeq-tuple" `namedRule` theRule where + theRule p@[essence| &x .<= permute(&perm, &y) |] = do + tx@TypeMatrix{} <- typeOf x -- TODO: check matrix index & tuple arity + ty@TypeMatrix{} <- typeOf y + when (isPrimitiveType tx) $ fail ("this is a primitive type:" <+> pretty tx) + when (isPrimitiveType ty) $ fail ("this is a primitive type:" <+> pretty ty) + xs <- downX1 x + ys <- downX1 y + return + ( "Horizontal rule for matrix .<=, decomposing" + , return $ decomposeLexDotLeqSym p perm xs ys + ) + theRule _ = na "rule_Matrix_DotLeq_Symbreak_Decompose" + +-- HACK +-- Moved inside rule_Matrix_Leq_Primitive since we need to do this refinement first +-- otherwise compact will choose the other as it will also match and we fail +rule_Matrix_Leq_Symbreak_Primitive :: Rule +rule_Matrix_Leq_Symbreak_Primitive = "matrix-Leq-symbreak-primitive" `namedRule` theRule where + theRule [essence| &x .<= permute(&perm, &y) |] = do + tx@TypeMatrix{} <- typeOf x -- TODO: check if x and y have the same arity + ty@(TypeMatrix _ yinner) <- typeOf y + (TypePermutation pinner) <- typeOf perm + if typesUnify [yinner, pinner] + then do + unless (isPrimitiveType tx) $ fail ("not a primitive type:" <+> pretty tx) + unless (isPrimitiveType ty) $ fail ("not a primitive type:" <+> pretty ty) + x' <- flattenIfNeeded x + y' <- flattenIfNeeded y + dy'@(DomainMatrix dyindex _) <- domainOf y' + return + ( "Horizontal rule for matrix <=" + , do + (dPat, d) <- quantifiedVar + (pyName, py) <- auxiliaryVar + return $ WithLocals + [essence| &x' <=lex &py |] + (AuxiliaryVars + --TODO need union of permutation and dy domains + [ Declaration (FindOrGiven LocalFind pyName dy') + , SuchThat + [ [essence| + forAll &dPat : &dyindex . + &py[&d] = permute(&perm,&y'[&d]) + |] + ] + ] + ) + ) + else na "rule_Matrix_Leq_Symbreak_Primitive" + theRule _ = na "rule_Matrix_Leq_Symbreak_Primitive" + rule_Comprehension_SingletonDomain :: Rule rule_Comprehension_SingletonDomain = "matrix-comprehension-singleton-domain" `namedRule` theRule where diff --git a/src/Conjure/Rules/Vertical/Permutation/AsFunction.hs b/src/Conjure/Rules/Vertical/Permutation/AsFunction.hs index fb68412371..d411d1fc29 100644 --- a/src/Conjure/Rules/Vertical/Permutation/AsFunction.hs +++ b/src/Conjure/Rules/Vertical/Permutation/AsFunction.hs @@ -29,7 +29,8 @@ rule_Permute_Comprehension_Tuples = "permutation-comprehension-tuples{AsFunction rule_Permute :: Rule rule_Permute = "permutation-permute{AsFunction}" `namedRule` theRule where theRule [essence| permute(&p, &i) |] = do - case p of WithLocals{} -> na "bubble-delay" ; _ -> return () + --TODO is bubble-delay necessary here? +-- case p of WithLocals{} -> na "bubble-delay" ; _ -> return () TypePermutation inner <- typeOf p typeI <- typeOf i [f] <- downX1 p @@ -42,3 +43,15 @@ rule_Permute = "permutation-permute{AsFunction}" `namedRule` theRule where else na "rule_Permute" theRule _ = na "rule_Permute" + +--rule_Permute_Set :: Rule +--rule_Permute_Set = "permutation-permute-set{AsFunction}" `namedRule` theRule where +-- theRule [essence| permute(&p,&i) |] = do +-- TypePermutation (TypeUnnamed nameperm) <- typeOf p +-- TypeSet (TypeUnnamed nameset) <- i +-- if nameperm == nameset +-- then applyPermutationOverSet +-- else na "rule_Permute_Set" +-- theRule _ = na "rule_Permute_Set" +-- +--applyPermutationOverSet = error "applyPermutationOverSet" diff --git a/src/Conjure/Rules/Vertical/Tuple.hs b/src/Conjure/Rules/Vertical/Tuple.hs index 8fa84bcff7..dde1a28763 100644 --- a/src/Conjure/Rules/Vertical/Tuple.hs +++ b/src/Conjure/Rules/Vertical/Tuple.hs @@ -11,6 +11,7 @@ rule_Tuple_Eq = "tuple-eq" `namedRule` theRule where (x,y) <- match opEq p TypeTuple{} <- typeOf x -- TODO: check if x and y have the same arity TypeTuple{} <- typeOf y +-- failExceptForTuplesOfSameArity x y xs <- downX1 x ys <- downX1 y return @@ -25,6 +26,7 @@ rule_Tuple_Neq = "tuple-neq" `namedRule` theRule where (x,y) <- match opNeq p TypeTuple{} <- typeOf x -- TODO: check if x and y have the same arity TypeTuple{} <- typeOf y +-- failExceptForTuplesOfSameArity x y xs <- downX1 x ys <- downX1 y return @@ -39,6 +41,7 @@ rule_Tuple_Lt = "tuple-Lt" `namedRule` theRule where (x,y) <- match opLt p TypeTuple{} <- typeOf x -- TODO: check if x and y have the same arity TypeTuple{} <- typeOf y +-- failExceptForTuplesOfSameArity x y xs <- downX1 x ys <- downX1 y return @@ -53,6 +56,7 @@ rule_Tuple_Leq = "tuple-Leq" `namedRule` theRule where (x,y) <- match opLeq p TypeTuple{} <- typeOf x -- TODO: check if x and y have the same arity TypeTuple{} <- typeOf y +-- failExceptForTuplesOfSameArity x y xs <- downX1 x ys <- downX1 y return @@ -67,6 +71,7 @@ rule_Tuple_DotLt = "tuple-DotLt" `namedRule` theRule where (x,y) <- match opDotLt p TypeTuple{} <- typeOf x -- TODO: check if x and y have the same arity TypeTuple{} <- typeOf y +-- failExceptForTuplesOfSameArity x y xs <- downX1 x ys <- downX1 y return @@ -81,6 +86,7 @@ rule_Tuple_DotLeq = "tuple-DotLeq" `namedRule` theRule where (x,y) <- match opDotLeq p TypeTuple{} <- typeOf x -- TODO: check if x and y have the same arity TypeTuple{} <- typeOf y +-- failExceptForTuplesOfSameArity x y xs <- downX1 x ys <- downX1 y return @@ -95,6 +101,7 @@ rule_Tuple_TildeLt = "tuple-TildeLt" `namedRule` theRule where (x,y) <- match opTildeLt p TypeTuple{} <- typeOf x -- TODO: check if x and y have the same arity TypeTuple{} <- typeOf y +-- failExceptForTuplesOfSameArity x y xs <- downX1 x ys <- downX1 y return @@ -109,6 +116,7 @@ rule_Tuple_TildeLeq = "tuple-TildeLeq" `namedRule` theRule where (x,y) <- match opTildeLeq p TypeTuple{} <- typeOf x -- TODO: check if x and y have the same arity TypeTuple{} <- typeOf y +-- failExceptForTuplesOfSameArity x y xs <- downX1 x ys <- downX1 y return @@ -116,6 +124,17 @@ rule_Tuple_TildeLeq = "tuple-TildeLeq" `namedRule` theRule where , return $ decomposeLexTildeLeq p xs ys ) +failExceptForTuplesOfSameArity :: MonadFail m => Expression -> Expression -> m () +failExceptForTuplesOfSameArity (AbstractLiteral (AbsLitTuple a)) (AbstractLiteral (AbsLitTuple b)) = + if length a == length b + then return () + else fail "failExceptForTuplesOfSameArity: These tuples are not of the same arity." +failExceptForTuplesOfSameArity (Domain (DomainTuple a)) (Domain (DomainTuple b)) = + if length a == length b + then return () + else fail "failExceptForTuplesOfSameArity: These tuples are not of the same arity." +failExceptForTuplesOfSameArity _ _ = fail "failExceptForTuplesOfSameArity: These things are not tuples." + decomposeLexLt :: Expression -> [Expression] -> [Expression] -> Expression decomposeLexLt p = unroll @@ -150,6 +169,16 @@ decomposeLexDotLeq p = unroll in [essence| (&a .< &b) \/ ((&a = &b) /\ &rest) |] unroll _ _ = bug ("arity mismatch in:" <+> pretty p) +decomposeLexDotLeqSym :: Expression -> Expression + -> [Expression] -> [Expression] -> Expression +decomposeLexDotLeqSym p perm = unroll + where + unroll [a] [b] = [essence| &a .<= permute(&perm, &b) |] + unroll (a:as) (b:bs) = let rest = unroll as bs + in [essence| (&a .< apply(&perm,&b)) \/ ((&a = apply(&perm,&b)) /\ &rest) |] + unroll _ _ = bug ("arity mismatch in:" <+> pretty p) + + decomposeLexTildeLt :: Expression -> [Expression] -> [Expression] -> Expression decomposeLexTildeLt p = unroll diff --git a/src/Conjure/UI/Model.hs b/src/Conjure/UI/Model.hs index 5e572d67ba..7c326f5cc1 100644 --- a/src/Conjure/UI/Model.hs +++ b/src/Conjure/UI/Model.hs @@ -1073,11 +1073,13 @@ verticalRules = , Vertical.Matrix.rule_Comprehension_ToSet_List_DuplicateFree , Vertical.Matrix.rule_Matrix_Eq , Vertical.Matrix.rule_Matrix_Neq +-- , Vertical.Matrix.rule_Matrix_Leq_Symbreak_Primitive , Vertical.Matrix.rule_Matrix_Leq_Primitive , Vertical.Matrix.rule_Matrix_Leq_Decompose , Vertical.Matrix.rule_Matrix_Lt_Primitive , Vertical.Matrix.rule_Matrix_Lt_Decompose , Vertical.Matrix.rule_Matrix_DotLeq_Decompose +-- , Vertical.Matrix.rule_Matrix_DotLeq_Symbreak_Decompose , Vertical.Matrix.rule_Matrix_DotLt_Decompose , Vertical.Matrix.rule_IndexingIdentical diff --git a/tests/custom/permutations/basic/21/permutation.essence b/tests/custom/permutations/basic/21/permutation.essence new file mode 100644 index 0000000000..8877f6fb99 --- /dev/null +++ b/tests/custom/permutations/basic/21/permutation.essence @@ -0,0 +1,13 @@ + +letting n be 4 +letting m be 8 + +given p : permutation of int(1..n) + +given q : permutation of int(n..m) + +letting j be 20 + +find i : int(1..30) + +such that permute(apply(q,p),i) = j diff --git a/tests/custom/permutations/basic/21/permutation.param b/tests/custom/permutations/basic/21/permutation.param new file mode 100644 index 0000000000..6888afc4ca --- /dev/null +++ b/tests/custom/permutations/basic/21/permutation.param @@ -0,0 +1,2 @@ +letting p be permutation((1,3),(4,2)) +letting q be permutation((4,7),(5,8)) diff --git a/tests/custom/permutations/basic/21/run.sh b/tests/custom/permutations/basic/21/run.sh new file mode 100755 index 0000000000..9dc67e67f5 --- /dev/null +++ b/tests/custom/permutations/basic/21/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence *.param +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/basic/21/stdout.expected b/tests/custom/permutations/basic/21/stdout.expected new file mode 100644 index 0000000000..497335e5d7 --- /dev/null +++ b/tests/custom/permutations/basic/21/stdout.expected @@ -0,0 +1,8 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime permutation.param +Copying solution to: permutation-permutation.solution +language Essence 1.3 + +letting i be 20 diff --git a/tests/custom/permutations/basic/22/permutation.essence b/tests/custom/permutations/basic/22/permutation.essence new file mode 100644 index 0000000000..6b2af0501e --- /dev/null +++ b/tests/custom/permutations/basic/22/permutation.essence @@ -0,0 +1,11 @@ + +given n : int + +find x : matrix indexed by [int(1..n)] of int(0..3) + +find y : matrix indexed by [int(1..n)] of int(0..3) + + +such that + forAll i, j : int(1..n) . + i != j -> y .<= permute(permutation((i,j)), x) diff --git a/tests/custom/permutations/basic/22/permutation.param b/tests/custom/permutations/basic/22/permutation.param new file mode 100644 index 0000000000..f1b89d4a65 --- /dev/null +++ b/tests/custom/permutations/basic/22/permutation.param @@ -0,0 +1 @@ +letting n be 4 diff --git a/tests/custom/permutations/basic/22/run.sh b/tests/custom/permutations/basic/22/run.sh new file mode 100755 index 0000000000..81aa56049c --- /dev/null +++ b/tests/custom/permutations/basic/22/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence *.param --number-of-solutions=4 +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/basic/22/stdout.expected b/tests/custom/permutations/basic/22/stdout.expected new file mode 100644 index 0000000000..5994701792 --- /dev/null +++ b/tests/custom/permutations/basic/22/stdout.expected @@ -0,0 +1,9 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime permutation.param +Copying solution to: permutation-permutation.solution +language Essence 1.3 + +letting x be [0, 0, 0, 0; int(1..4)] +letting y be [0, 0, 0, 0; int(1..4)] From 78cfc0e83a48eea5cf2b29f1dcbd575d87f21f17 Mon Sep 17 00:00:00 2001 From: Fraser Dunlop Date: Wed, 10 Oct 2018 10:10:02 +0100 Subject: [PATCH 006/229] tuple <=lex permute(permutation,tuple) rule --- src/Conjure/Language/Expression/Op/Permute.hs | 4 + src/Conjure/Rules/Vertical/Matrix.hs | 1 + src/Conjure/Rules/Vertical/Tuple.hs | 13 ++- .../permutations/basic/22/permutation.essence | 4 +- .../permutations/basic/22/permutation.param | 2 +- tests/custom/permutations/basic/22/run.sh | 2 +- .../permutations/basic/22/stdout.expected | 101 +++++++++++++++++- .../permutations/basic/23/permutation.essence | 12 +++ .../permutations/basic/23/permutation.param | 1 + tests/custom/permutations/basic/23/run.sh | 3 + .../permutations/basic/23/stdout.expected | 24 +++++ 11 files changed, 159 insertions(+), 8 deletions(-) create mode 100644 tests/custom/permutations/basic/23/permutation.essence create mode 100644 tests/custom/permutations/basic/23/permutation.param create mode 100755 tests/custom/permutations/basic/23/run.sh create mode 100644 tests/custom/permutations/basic/23/stdout.expected diff --git a/src/Conjure/Language/Expression/Op/Permute.hs b/src/Conjure/Language/Expression/Op/Permute.hs index 01633a0e06..103ca9b1aa 100644 --- a/src/Conjure/Language/Expression/Op/Permute.hs +++ b/src/Conjure/Language/Expression/Op/Permute.hs @@ -25,6 +25,10 @@ instance (TypeOf x, Pretty x) => TypeOf (OpPermute x) where pTy <- typeOf p iTy <- typeOf i case (pTy,iTy) of + (TypePermutation pTyInner, TypeTuple mTyInner) -> + if typesUnify $ [pTyInner] ++ mTyInner + then return $ TypeTuple mTyInner + else raiseTypeError inp (TypePermutation pTyInner, TypeMatrix indx mTyInner) -> if typesUnify [pTyInner, mTyInner] then return $ TypeMatrix indx mTyInner diff --git a/src/Conjure/Rules/Vertical/Matrix.hs b/src/Conjure/Rules/Vertical/Matrix.hs index 947d9577f0..db4a730120 100644 --- a/src/Conjure/Rules/Vertical/Matrix.hs +++ b/src/Conjure/Rules/Vertical/Matrix.hs @@ -480,6 +480,7 @@ rule_Matrix_DotLeq_Decompose = "matrix-DotLeq-tuple" `namedRule` theRule where theRule p@[essence| &x .<= permute(&perm, &y) |] = do tx@TypeMatrix{} <- typeOf x -- TODO: check matrix index & tuple arity ty@TypeMatrix{} <- typeOf y + TypePermutation{} <- typeOf perm when (isPrimitiveType tx) $ fail ("this is a primitive type:" <+> pretty tx) when (isPrimitiveType ty) $ fail ("this is a primitive type:" <+> pretty ty) xs <- downX1 x diff --git a/src/Conjure/Rules/Vertical/Tuple.hs b/src/Conjure/Rules/Vertical/Tuple.hs index dde1a28763..c38a1ba873 100644 --- a/src/Conjure/Rules/Vertical/Tuple.hs +++ b/src/Conjure/Rules/Vertical/Tuple.hs @@ -82,6 +82,17 @@ rule_Tuple_DotLt = "tuple-DotLt" `namedRule` theRule where rule_Tuple_DotLeq :: Rule rule_Tuple_DotLeq = "tuple-DotLeq" `namedRule` theRule where + theRule p@[essence| &x .<= permute(&perm, &y) |] = do + tx@TypeTuple{} <- typeOf x -- TODO: check matrix index & tuple arity + ty@TypeTuple{} <- typeOf y + TypePermutation{} <- typeOf perm + xs <- downX1 x + ys <- downX1 y + return + ( "Horizontal rule for matrix .<=, decomposing" + , return $ decomposeLexDotLeqSym p perm xs ys + ) + theRule p = do (x,y) <- match opDotLeq p TypeTuple{} <- typeOf x -- TODO: check if x and y have the same arity @@ -175,7 +186,7 @@ decomposeLexDotLeqSym p perm = unroll where unroll [a] [b] = [essence| &a .<= permute(&perm, &b) |] unroll (a:as) (b:bs) = let rest = unroll as bs - in [essence| (&a .< apply(&perm,&b)) \/ ((&a = apply(&perm,&b)) /\ &rest) |] + in [essence| (&a .< permute(&perm,&b)) \/ ((&a = permute(&perm,&b)) /\ &rest) |] unroll _ _ = bug ("arity mismatch in:" <+> pretty p) diff --git a/tests/custom/permutations/basic/22/permutation.essence b/tests/custom/permutations/basic/22/permutation.essence index 6b2af0501e..4eac7b2e81 100644 --- a/tests/custom/permutations/basic/22/permutation.essence +++ b/tests/custom/permutations/basic/22/permutation.essence @@ -1,9 +1,9 @@ given n : int -find x : matrix indexed by [int(1..n)] of int(0..3) +find x : matrix indexed by [int(1..n)] of int(1..n) -find y : matrix indexed by [int(1..n)] of int(0..3) +find y : matrix indexed by [int(1..n)] of int(1..n) such that diff --git a/tests/custom/permutations/basic/22/permutation.param b/tests/custom/permutations/basic/22/permutation.param index f1b89d4a65..36d2429361 100644 --- a/tests/custom/permutations/basic/22/permutation.param +++ b/tests/custom/permutations/basic/22/permutation.param @@ -1 +1 @@ -letting n be 4 +letting n be 5 diff --git a/tests/custom/permutations/basic/22/run.sh b/tests/custom/permutations/basic/22/run.sh index 81aa56049c..98ec8c2243 100755 --- a/tests/custom/permutations/basic/22/run.sh +++ b/tests/custom/permutations/basic/22/run.sh @@ -1,3 +1,3 @@ -conjure solve *.essence *.param --number-of-solutions=4 +conjure solve *.essence *.param --number-of-solutions=20 cat conjure-output/*.solution rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/basic/22/stdout.expected b/tests/custom/permutations/basic/22/stdout.expected index 5994701792..0b96e4d933 100644 --- a/tests/custom/permutations/basic/22/stdout.expected +++ b/tests/custom/permutations/basic/22/stdout.expected @@ -2,8 +2,103 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output Savile Row: model000001.eprime permutation.param -Copying solution to: permutation-permutation.solution +Copying solution to: permutation-permutation-000001.solution +Copying solution to: permutation-permutation-000002.solution +Copying solution to: permutation-permutation-000003.solution +Copying solution to: permutation-permutation-000004.solution +Copying solution to: permutation-permutation-000005.solution +Copying solution to: permutation-permutation-000006.solution +Copying solution to: permutation-permutation-000007.solution +Copying solution to: permutation-permutation-000008.solution +Copying solution to: permutation-permutation-000009.solution +Copying solution to: permutation-permutation-000010.solution +Copying solution to: permutation-permutation-000011.solution +Copying solution to: permutation-permutation-000012.solution +Copying solution to: permutation-permutation-000013.solution +Copying solution to: permutation-permutation-000014.solution +Copying solution to: permutation-permutation-000015.solution +Copying solution to: permutation-permutation-000016.solution +Copying solution to: permutation-permutation-000017.solution +Copying solution to: permutation-permutation-000018.solution +Copying solution to: permutation-permutation-000019.solution +Copying solution to: permutation-permutation-000020.solution language Essence 1.3 -letting x be [0, 0, 0, 0; int(1..4)] -letting y be [0, 0, 0, 0; int(1..4)] +letting x be [1, 1, 1, 1, 1; int(1..5)] +letting y be [1, 1, 1, 1, 1; int(1..5)] +language Essence 1.3 + +letting x be [1, 1, 1, 1, 2; int(1..5)] +letting y be [1, 1, 1, 1, 1; int(1..5)] +language Essence 1.3 + +letting x be [1, 1, 1, 1, 2; int(1..5)] +letting y be [1, 1, 1, 1, 2; int(1..5)] +language Essence 1.3 + +letting x be [1, 1, 1, 1, 3; int(1..5)] +letting y be [1, 1, 1, 1, 1; int(1..5)] +language Essence 1.3 + +letting x be [1, 1, 1, 1, 3; int(1..5)] +letting y be [1, 1, 1, 1, 2; int(1..5)] +language Essence 1.3 + +letting x be [1, 1, 1, 1, 4; int(1..5)] +letting y be [1, 1, 1, 1, 1; int(1..5)] +language Essence 1.3 + +letting x be [1, 1, 1, 1, 4; int(1..5)] +letting y be [1, 1, 1, 1, 2; int(1..5)] +language Essence 1.3 + +letting x be [1, 1, 1, 1, 5; int(1..5)] +letting y be [1, 1, 1, 1, 1; int(1..5)] +language Essence 1.3 + +letting x be [1, 1, 1, 1, 5; int(1..5)] +letting y be [1, 1, 1, 1, 2; int(1..5)] +language Essence 1.3 + +letting x be [1, 1, 1, 2, 1; int(1..5)] +letting y be [1, 1, 1, 1, 1; int(1..5)] +language Essence 1.3 + +letting x be [1, 1, 1, 2, 1; int(1..5)] +letting y be [1, 1, 1, 1, 2; int(1..5)] +language Essence 1.3 + +letting x be [1, 1, 1, 2, 1; int(1..5)] +letting y be [1, 1, 1, 1, 3; int(1..5)] +language Essence 1.3 + +letting x be [1, 1, 1, 2, 1; int(1..5)] +letting y be [1, 1, 1, 1, 4; int(1..5)] +language Essence 1.3 + +letting x be [1, 1, 1, 2, 1; int(1..5)] +letting y be [1, 1, 1, 1, 5; int(1..5)] +language Essence 1.3 + +letting x be [1, 1, 1, 2, 1; int(1..5)] +letting y be [1, 1, 1, 2, 1; int(1..5)] +language Essence 1.3 + +letting x be [1, 1, 1, 2, 2; int(1..5)] +letting y be [1, 1, 1, 1, 1; int(1..5)] +language Essence 1.3 + +letting x be [1, 1, 1, 2, 2; int(1..5)] +letting y be [1, 1, 1, 1, 2; int(1..5)] +language Essence 1.3 + +letting x be [1, 1, 1, 2, 2; int(1..5)] +letting y be [1, 1, 1, 1, 3; int(1..5)] +language Essence 1.3 + +letting x be [1, 1, 1, 2, 2; int(1..5)] +letting y be [1, 1, 1, 1, 4; int(1..5)] +language Essence 1.3 + +letting x be [1, 1, 1, 2, 2; int(1..5)] +letting y be [1, 1, 1, 1, 5; int(1..5)] diff --git a/tests/custom/permutations/basic/23/permutation.essence b/tests/custom/permutations/basic/23/permutation.essence new file mode 100644 index 0000000000..7b6299176f --- /dev/null +++ b/tests/custom/permutations/basic/23/permutation.essence @@ -0,0 +1,12 @@ + +given n : int + +find x : (int(1..n), int(1..n), int(1..n)) + +find y : (int(1..n), int(1..n), int(1..n)) + + + +such that + forAll i, j : int(1..n) . + i != j -> y .<= permute(permutation((i,j)), x) diff --git a/tests/custom/permutations/basic/23/permutation.param b/tests/custom/permutations/basic/23/permutation.param new file mode 100644 index 0000000000..f1b89d4a65 --- /dev/null +++ b/tests/custom/permutations/basic/23/permutation.param @@ -0,0 +1 @@ +letting n be 4 diff --git a/tests/custom/permutations/basic/23/run.sh b/tests/custom/permutations/basic/23/run.sh new file mode 100755 index 0000000000..81aa56049c --- /dev/null +++ b/tests/custom/permutations/basic/23/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence *.param --number-of-solutions=4 +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/basic/23/stdout.expected b/tests/custom/permutations/basic/23/stdout.expected new file mode 100644 index 0000000000..58bb53cf5f --- /dev/null +++ b/tests/custom/permutations/basic/23/stdout.expected @@ -0,0 +1,24 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime permutation.param +Copying solution to: permutation-permutation-000001.solution +Copying solution to: permutation-permutation-000002.solution +Copying solution to: permutation-permutation-000003.solution +Copying solution to: permutation-permutation-000004.solution +language Essence 1.3 + +letting x be (1, 1, 1) +letting y be (1, 1, 1) +language Essence 1.3 + +letting x be (1, 1, 2) +letting y be (1, 1, 1) +language Essence 1.3 + +letting x be (1, 1, 2) +letting y be (1, 1, 2) +language Essence 1.3 + +letting x be (1, 1, 3) +letting y be (1, 1, 1) From d1c7ddb71aba13575b08abee6573c5184b9c2e02 Mon Sep 17 00:00:00 2001 From: Fraser Dunlop Date: Mon, 15 Oct 2018 10:46:45 +0100 Subject: [PATCH 007/229] Dotleq approach to be abandoned in favor of sledgehammer --- src/Conjure/Language/Expression/Op/Permute.hs | 4 ++++ src/Conjure/Representations/Set/Explicit.hs | 10 +++++++- src/Conjure/Representations/Set/Occurrence.hs | 8 ++++++- src/Conjure/Rules/Horizontal/Set.hs | 14 +++++++++++ src/Conjure/Rules/Vertical/Tuple.hs | 4 ++-- .../permutations/basic/24/permutation.essence | 12 ++++++++++ .../permutations/basic/24/permutation.param | 1 + tests/custom/permutations/basic/24/run.sh | 3 +++ .../permutations/basic/24/stdout.expected | 24 +++++++++++++++++++ 9 files changed, 76 insertions(+), 4 deletions(-) create mode 100644 tests/custom/permutations/basic/24/permutation.essence create mode 100644 tests/custom/permutations/basic/24/permutation.param create mode 100755 tests/custom/permutations/basic/24/run.sh create mode 100644 tests/custom/permutations/basic/24/stdout.expected diff --git a/src/Conjure/Language/Expression/Op/Permute.hs b/src/Conjure/Language/Expression/Op/Permute.hs index 103ca9b1aa..9ed251505b 100644 --- a/src/Conjure/Language/Expression/Op/Permute.hs +++ b/src/Conjure/Language/Expression/Op/Permute.hs @@ -25,6 +25,10 @@ instance (TypeOf x, Pretty x) => TypeOf (OpPermute x) where pTy <- typeOf p iTy <- typeOf i case (pTy,iTy) of + (TypePermutation pTyInner, TypeSet mTyInner) -> + if typesUnify $ [pTyInner, mTyInner] + then return $ TypeSet mTyInner + else raiseTypeError inp (TypePermutation pTyInner, TypeTuple mTyInner) -> if typesUnify $ [pTyInner] ++ mTyInner then return $ TypeTuple mTyInner diff --git a/src/Conjure/Representations/Set/Explicit.hs b/src/Conjure/Representations/Set/Explicit.hs index 923036532e..6881886334 100644 --- a/src/Conjure/Representations/Set/Explicit.hs +++ b/src/Conjure/Representations/Set/Explicit.hs @@ -12,7 +12,8 @@ setExplicit :: forall m . (MonadFail m, NameGen m) => Representation m setExplicit = Representation chck downD structuralCons downC up where - + + -- | We can represent any inner domain but set must be fixed size chck :: TypeOf_ReprCheck m chck f (DomainSet _ attrs@(SetAttr SizeAttr_Size{}) innerDomain) = map (DomainSet Set_Explicit attrs) <$> f innerDomain @@ -21,6 +22,7 @@ setExplicit = Representation chck downD structuralCons downC up outName :: Domain HasRepresentation x -> Name -> Name outName = mkOutName Nothing + -- | A 1D matrix of size of set containing innerDomain objects downD :: TypeOf_DownD m downD (name, domain@(DomainSet Set_Explicit (SetAttr (SizeAttr_Size size)) innerDomain)) = return $ Just [ ( outName domain name @@ -30,9 +32,13 @@ setExplicit = Representation chck downD structuralCons downC up ) ] downD _ = na "{downD} Explicit" + -- | Enforce lex ordering of matrix (symmetry breaking) and inner structural constraints of + -- 'active' elements of inner domain structuralCons :: TypeOf_Structural m structuralCons f downX1 (DomainSet Set_Explicit (SetAttr (SizeAttr_Size size)) innerDomain) = do let + -- | Makes sure i'th value is lex less than (i+1)'th value + -- a symmetry breaking structural constraint ordering m = do (iPat, i) <- quantifiedVar return $ return -- for list @@ -41,6 +47,8 @@ setExplicit = Representation chck downD structuralCons downC up &m[&i] .< &m[&i+1] |] + -- | Enforces structural constraints for the elements of the inner domain + -- that are in the set. innerStructuralCons m = do (iPat, i) <- quantifiedVarOverDomain [essenceDomain| int(1..&size) |] let activeZone b = [essence| forAll &iPat : int(1..&size) . &b |] diff --git a/src/Conjure/Representations/Set/Occurrence.hs b/src/Conjure/Representations/Set/Occurrence.hs index a5e751c1da..1c1bcbb85a 100644 --- a/src/Conjure/Representations/Set/Occurrence.hs +++ b/src/Conjure/Representations/Set/Occurrence.hs @@ -14,13 +14,16 @@ setOccurrence = Representation chck downD structuralCons downC up where + -- | We can only represent Set of Int as occurrence chck :: TypeOf_ReprCheck m - chck f (DomainSet _ attrs innerDomain@DomainInt{}) = map (DomainSet Set_Occurrence attrs) <$> f innerDomain + chck f (DomainSet _ attrs innerDomain@DomainInt{}) = + map (DomainSet Set_Occurrence attrs) <$> f innerDomain chck _ _ = return [] outName :: Domain HasRepresentation x -> Name -> Name outName = mkOutName Nothing + -- | Matrix of Bool indexed by inner domain of set (which must be an int domain) downD :: TypeOf_DownD m downD (name, domain@(DomainSet Set_Occurrence _attrs innerDomain@DomainInt{})) = return $ Just [ ( outName domain name @@ -29,6 +32,7 @@ setOccurrence = Representation chck downD structuralCons downC up ] downD _ = na "{downD} Occurrence" + -- | Constrain number of trues in matrix to be congruent with cardinality constraint structuralCons :: TypeOf_Structural m structuralCons _ downX1 (DomainSet Set_Occurrence (SetAttr attrs) innerDomain@DomainInt{}) = return $ \ set -> do @@ -41,6 +45,7 @@ setOccurrence = Representation chck downD structuralCons downC up _ -> na "{structuralCons} Occurrence" structuralCons _ _ _ = na "{structuralCons} Occurrence" + -- | If value is in the set then that value's index maps to a bool downC :: TypeOf_DownC m downC ( name , domain@(DomainSet Set_Occurrence _attrs innerDomain@(DomainInt intRanges)) @@ -59,6 +64,7 @@ setOccurrence = Representation chck downD structuralCons downC up ] downC _ = na "{downC} Occurrence" + -- | Reversal of downC - if innerDom value zips with matrix true then it's in up :: TypeOf_Up m up ctxt (name, domain@(DomainSet _ _ (DomainInt intRanges)))= case lookup (outName domain name) ctxt of diff --git a/src/Conjure/Rules/Horizontal/Set.hs b/src/Conjure/Rules/Horizontal/Set.hs index 552e96d863..10b6a212f6 100644 --- a/src/Conjure/Rules/Horizontal/Set.hs +++ b/src/Conjure/Rules/Horizontal/Set.hs @@ -129,6 +129,20 @@ rule_DotLt = "set-DotLt" `namedRule` theRule where rule_DotLeq :: Rule rule_DotLeq = "set-DotLeq" `namedRule` theRule where + --This works but not for occurrence rep + theRule [essence| &a .<= permute(&perm, &b) |] = do + TypeSet{} <- typeOf a + TypeSet{} <- typeOf b + TypePermutation{} <- typeOf perm + sameRepresentation a b + ma <- tupleLitIfNeeded <$> downX1 a + mb <- tupleLitIfNeeded <$> downX1 b + return + ( "Horizontal rule for set .<=" + <+> pretty ([essence| &ma .<= permute(&perm, &mb) |]) + + , return $ [essence| &ma .<= permute(&perm, &mb) |] + ) theRule p = do (a,b) <- match opDotLeq p TypeSet{} <- typeOf a diff --git a/src/Conjure/Rules/Vertical/Tuple.hs b/src/Conjure/Rules/Vertical/Tuple.hs index c38a1ba873..0e737b7fc5 100644 --- a/src/Conjure/Rules/Vertical/Tuple.hs +++ b/src/Conjure/Rules/Vertical/Tuple.hs @@ -83,8 +83,8 @@ rule_Tuple_DotLt = "tuple-DotLt" `namedRule` theRule where rule_Tuple_DotLeq :: Rule rule_Tuple_DotLeq = "tuple-DotLeq" `namedRule` theRule where theRule p@[essence| &x .<= permute(&perm, &y) |] = do - tx@TypeTuple{} <- typeOf x -- TODO: check matrix index & tuple arity - ty@TypeTuple{} <- typeOf y + TypeTuple{} <- typeOf x -- TODO: check matrix index & tuple arity + TypeTuple{} <- typeOf y TypePermutation{} <- typeOf perm xs <- downX1 x ys <- downX1 y diff --git a/tests/custom/permutations/basic/24/permutation.essence b/tests/custom/permutations/basic/24/permutation.essence new file mode 100644 index 0000000000..a220ea12cb --- /dev/null +++ b/tests/custom/permutations/basic/24/permutation.essence @@ -0,0 +1,12 @@ + +given n : int + +find x : set (size n) of int(1..n) + +find y : set (size n) of int(1..n) + + + +such that + forAll i, j : int(1..n) . + i != j -> y .<= permute(permutation((i,j)), x) diff --git a/tests/custom/permutations/basic/24/permutation.param b/tests/custom/permutations/basic/24/permutation.param new file mode 100644 index 0000000000..f1b89d4a65 --- /dev/null +++ b/tests/custom/permutations/basic/24/permutation.param @@ -0,0 +1 @@ +letting n be 4 diff --git a/tests/custom/permutations/basic/24/run.sh b/tests/custom/permutations/basic/24/run.sh new file mode 100755 index 0000000000..98ec8c2243 --- /dev/null +++ b/tests/custom/permutations/basic/24/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence *.param --number-of-solutions=20 +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/basic/24/stdout.expected b/tests/custom/permutations/basic/24/stdout.expected new file mode 100644 index 0000000000..58bb53cf5f --- /dev/null +++ b/tests/custom/permutations/basic/24/stdout.expected @@ -0,0 +1,24 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime permutation.param +Copying solution to: permutation-permutation-000001.solution +Copying solution to: permutation-permutation-000002.solution +Copying solution to: permutation-permutation-000003.solution +Copying solution to: permutation-permutation-000004.solution +language Essence 1.3 + +letting x be (1, 1, 1) +letting y be (1, 1, 1) +language Essence 1.3 + +letting x be (1, 1, 2) +letting y be (1, 1, 1) +language Essence 1.3 + +letting x be (1, 1, 2) +letting y be (1, 1, 2) +language Essence 1.3 + +letting x be (1, 1, 3) +letting y be (1, 1, 1) From 8257b45a3e3e12e96c16658d11a02f5496adf159 Mon Sep 17 00:00:00 2001 From: Fraser Dunlop Date: Wed, 17 Oct 2018 14:54:34 +0100 Subject: [PATCH 008/229] Integer Tags --- src/Conjure/Compute/DomainOf.hs | 22 +- src/Conjure/Compute/DomainUnion.hs | 3 +- src/Conjure/Language/Arbitrary.hs | 6 +- src/Conjure/Language/Constant.hs | 18 +- src/Conjure/Language/Domain.hs | 58 +++--- src/Conjure/Language/Expression.hs | 2 +- .../Language/Expression/DomainSizeOf.hs | 8 +- .../Language/Expression/Op/AllDiffExcept.hs | 2 +- src/Conjure/Language/Expression/Op/Apply.hs | 2 +- src/Conjure/Language/Expression/Op/Defined.hs | 2 +- src/Conjure/Language/Expression/Op/Div.hs | 4 +- .../Language/Expression/Op/Factorial.hs | 4 +- src/Conjure/Language/Expression/Op/Flatten.hs | 4 +- src/Conjure/Language/Expression/Op/Freq.hs | 2 +- src/Conjure/Language/Expression/Op/Geq.hs | 2 +- src/Conjure/Language/Expression/Op/Gt.hs | 2 +- src/Conjure/Language/Expression/Op/Hist.hs | 10 +- src/Conjure/Language/Expression/Op/Image.hs | 2 +- .../Language/Expression/Op/ImageSet.hs | 2 +- .../Language/Expression/Op/Indexing.hs | 6 +- .../Language/Expression/Op/Internal/Common.hs | 12 +- src/Conjure/Language/Expression/Op/Leq.hs | 2 +- src/Conjure/Language/Expression/Op/Lt.hs | 2 +- src/Conjure/Language/Expression/Op/Max.hs | 14 +- src/Conjure/Language/Expression/Op/Min.hs | 14 +- src/Conjure/Language/Expression/Op/Minus.hs | 2 +- src/Conjure/Language/Expression/Op/Mod.hs | 4 +- src/Conjure/Language/Expression/Op/Negate.hs | 4 +- src/Conjure/Language/Expression/Op/Permute.hs | 19 +- src/Conjure/Language/Expression/Op/Pow.hs | 4 +- .../Language/Expression/Op/PreImage.hs | 2 +- src/Conjure/Language/Expression/Op/Pred.hs | 2 +- src/Conjure/Language/Expression/Op/Product.hs | 16 +- src/Conjure/Language/Expression/Op/Slicing.hs | 4 +- src/Conjure/Language/Expression/Op/Succ.hs | 2 +- src/Conjure/Language/Expression/Op/Sum.hs | 16 +- src/Conjure/Language/Expression/Op/ToInt.hs | 2 +- src/Conjure/Language/Expression/Op/TwoBars.hs | 4 +- src/Conjure/Language/Instantiate.hs | 8 +- src/Conjure/Language/Lenses.hs | 12 +- src/Conjure/Language/Parser.hs | 6 +- src/Conjure/Language/ParserC.hs | 6 +- src/Conjure/Language/Type.hs | 25 ++- src/Conjure/Language/ZeroVal.hs | 6 +- src/Conjure/Process/Enumerate.hs | 8 +- src/Conjure/Process/Enums.hs | 14 +- src/Conjure/Process/FiniteGivens.hs | 14 +- src/Conjure/Process/ModelStrengthening.hs | 2 +- src/Conjure/Process/Sanity.hs | 2 +- src/Conjure/Process/Unnameds.hs | 2 +- .../Representations/Function/Function1D.hs | 2 +- .../MSet/ExplicitWithRepetition.hs | 4 +- .../Representations/Partition/Occurrence.hs | 14 +- .../Partition/PartitionAsSet.hs | 2 +- src/Conjure/Representations/Primitive.hs | 4 +- .../Sequence/ExplicitBounded.hs | 16 +- src/Conjure/Representations/Set/Explicit.hs | 2 +- .../Set/ExplicitVarSizeWithDummy.hs | 14 +- src/Conjure/Representations/Set/Occurrence.hs | 4 +- src/Conjure/Rules/BubbleUp.hs | 2 +- src/Conjure/Rules/DontCare.hs | 16 +- src/Conjure/Rules/Horizontal/Function.hs | 12 +- src/Conjure/Rules/Horizontal/MSet.hs | 10 +- src/Conjure/Rules/Horizontal/Partition.hs | 4 +- src/Conjure/Rules/Horizontal/Permutation.hs | 4 +- src/Conjure/Rules/Horizontal/Relation.hs | 4 +- src/Conjure/Rules/Horizontal/Sequence.hs | 8 +- src/Conjure/Rules/Horizontal/Set.hs | 24 +-- src/Conjure/Rules/TildeOrdering.hs | 8 +- src/Conjure/Rules/Vertical/Matrix.hs | 188 +++++++++++------- src/Conjure/Rules/Vertical/Set/Explicit.hs | 4 +- src/Conjure/Rules/Vertical/Tuple.hs | 40 ++-- src/Conjure/UI/Model.hs | 12 +- src/Conjure/UI/TranslateParameter.hs | 2 +- src/Conjure/UI/TypeCheck.hs | 4 +- src/test/Conjure/Language/DomainSizeTest.hs | 10 +- .../permutations/basic/25/permutation.essence | 15 ++ .../permutations/basic/25/permutation.param | 2 + tests/custom/permutations/basic/25/run.sh | 3 + .../permutations/basic/25/stdout.expected | 124 ++++++++++++ .../permutations/basic/26/permutation.essence | 16 ++ .../permutations/basic/26/permutation.param | 1 + tests/custom/permutations/basic/26/run.sh | 3 + .../permutations/basic/26/stdout.expected | 124 ++++++++++++ 84 files changed, 716 insertions(+), 377 deletions(-) create mode 100644 tests/custom/permutations/basic/25/permutation.essence create mode 100644 tests/custom/permutations/basic/25/permutation.param create mode 100755 tests/custom/permutations/basic/25/run.sh create mode 100644 tests/custom/permutations/basic/25/stdout.expected create mode 100644 tests/custom/permutations/basic/26/permutation.essence create mode 100644 tests/custom/permutations/basic/26/permutation.param create mode 100755 tests/custom/permutations/basic/26/run.sh create mode 100644 tests/custom/permutations/basic/26/stdout.expected diff --git a/src/Conjure/Compute/DomainOf.hs b/src/Conjure/Compute/DomainOf.hs index 772acd33b1..39a448210f 100644 --- a/src/Conjure/Compute/DomainOf.hs +++ b/src/Conjure/Compute/DomainOf.hs @@ -62,7 +62,7 @@ instance DomainOf Expression where -- if an empty matrix literal has a type annotation indexDomainsOf (Typed lit ty) | emptyCollectionX lit = let - tyToDom (TypeMatrix TypeInt t) = DomainInt [RangeBounded 1 0] : tyToDom t + tyToDom (TypeMatrix (TypeInt name) t) = DomainInt name [RangeBounded 1 0] : tyToDom t tyToDom _ = [] in return (tyToDom ty) @@ -226,7 +226,7 @@ instance (DomainOf x, TypeOf x, Pretty x, ExpressionLike x, Domain () x :< x, Do instance DomainOf Constant where domainOf ConstantBool{} = return DomainBool - domainOf i@ConstantInt{} = return $ DomainInt [RangeSingle (Constant i)] + domainOf i@ConstantInt{} = return $ DomainInt Nothing [RangeSingle (Constant i)] domainOf (ConstantEnum defn _ _ ) = return (DomainEnum defn Nothing Nothing) domainOf ConstantField{} = fail "DomainOf-Constant-ConstantField" domainOf (ConstantAbstract x) = domainOf (fmap Constant x) @@ -346,7 +346,7 @@ instance DomainOf x => DomainOf (OpDiv x) where ] |] let low = [essence| min(&vals) |] let upp = [essence| max(&vals) |] - return (DomainInt [RangeBounded low upp] :: Dom) + return (DomainInt Nothing [RangeBounded low upp] :: Dom) instance DomainOf (OpDontCare x) where domainOf _ = return DomainBool @@ -446,7 +446,7 @@ instance (Pretty x, TypeOf x, ExpressionLike x, DomainOf x, Domain () x :< x) => let low = [essence| max(&lows) |] let upps = fromList [ [essence| max(`&d`) |] | d <- doms ] let upp = [essence| max(&upps) |] - return (DomainInt [RangeBounded low upp] :: Dom) + return (DomainInt Nothing [RangeBounded low upp] :: Dom) domainOf op = mkDomainAny ("OpMax:" <++> pretty op) <$> typeOf op instance (Pretty x, TypeOf x, ExpressionLike x, DomainOf x, Domain () x :< x) => DomainOf (OpMin x) where @@ -458,7 +458,7 @@ instance (Pretty x, TypeOf x, ExpressionLike x, DomainOf x, Domain () x :< x) => let low = [essence| min(&lows) |] let upps = fromList [ [essence| max(`&d`) |] | d <- doms ] let upp = [essence| min(&upps) |] - return (DomainInt [RangeBounded low upp] :: Dom) + return (DomainInt Nothing [RangeBounded low upp] :: Dom) domainOf op = mkDomainAny ("OpMin:" <++> pretty op) <$> typeOf op instance DomainOf x => DomainOf (OpMinus x) where @@ -474,7 +474,7 @@ instance DomainOf x => DomainOf (OpMinus x) where let low = [essence| &xDom_Min - &yDom_Max |] let upp = [essence| &xDom_Max - &yDom_Min |] - return (DomainInt [RangeBounded low upp] :: Dom) + return (DomainInt Nothing [RangeBounded low upp] :: Dom) instance (Pretty x, TypeOf x) => DomainOf (OpMod x) where domainOf op = mkDomainAny ("OpMod:" <++> pretty op) <$> typeOf op @@ -543,8 +543,8 @@ instance (ExpressionLike x, DomainOf x) => DomainOf (OpProduct x) where let upp = [essence| product(&upps) |] -- a (too lax) lower bound is -upp let low = [essence| -1 * &upp |] - return $ DomainInt [RangeBounded low upp] - domainOf _ = return $ DomainInt [RangeBounded 1 1] + return $ DomainInt Nothing [RangeBounded low upp] + domainOf _ = return $ DomainInt Nothing [RangeBounded 1 1] instance DomainOf x => DomainOf (OpRange x) where domainOf (OpRange f) = do @@ -592,8 +592,8 @@ instance (ExpressionLike x, DomainOf x) => DomainOf (OpSum x) where let low = [essence| sum(&lows) |] let upps = fromList [ [essence| max(`&d`) |] | d <- doms ] let upp = [essence| sum(&upps) |] - return (DomainInt [RangeBounded low upp] :: Dom) - domainOf _ = return $ DomainInt [RangeBounded 0 0] + return (DomainInt Nothing [RangeBounded low upp] :: Dom) + domainOf _ = return $ DomainInt Nothing [RangeBounded 0 0] instance DomainOf (OpSupset x) where domainOf _ = return DomainBool @@ -608,7 +608,7 @@ instance DomainOf (OpTildeLt x) where domainOf _ = return DomainBool instance DomainOf (OpToInt x) where - domainOf _ = return $ DomainInt [RangeBounded 0 1] + domainOf _ = return $ DomainInt Nothing [RangeBounded 0 1] instance (Pretty x, TypeOf x) => DomainOf (OpToMSet x) where domainOf op = mkDomainAny ("OpToMSet:" <++> pretty op) <$> typeOf op diff --git a/src/Conjure/Compute/DomainUnion.hs b/src/Conjure/Compute/DomainUnion.hs index 1c9e8f8d29..224332c785 100644 --- a/src/Conjure/Compute/DomainUnion.hs +++ b/src/Conjure/Compute/DomainUnion.hs @@ -44,7 +44,8 @@ instance domainUnion DomainAny{} d = return d domainUnion d DomainAny{} = return d domainUnion DomainBool DomainBool = return DomainBool - domainUnion (DomainInt r1) (DomainInt r2) = return $ DomainInt (r1 `L.union` r2) + domainUnion (DomainInt Nothing r1) (DomainInt Nothing r2) = + return $ DomainInt Nothing (r1 `L.union` r2) domainUnion (DomainTuple []) d@DomainTuple{} = return d domainUnion d@DomainTuple{} (DomainTuple []) = return d domainUnion (DomainTuple xs) (DomainTuple ys) diff --git a/src/Conjure/Language/Arbitrary.hs b/src/Conjure/Language/Arbitrary.hs index fe2d9e010f..ecbfc1b617 100644 --- a/src/Conjure/Language/Arbitrary.hs +++ b/src/Conjure/Language/Arbitrary.hs @@ -106,7 +106,7 @@ arbitraryDomainAndConstant = sized dispatch intBounded = do l <- choose (0 :: Integer, 100) u <- choose (l, 200) - return ( DomainInt [RangeBounded (ConstantInt l) (ConstantInt u)] + return ( DomainInt Nothing [RangeBounded (ConstantInt l) (ConstantInt u)] , ConstantInt <$> choose (l,u) ) @@ -114,7 +114,7 @@ arbitraryDomainAndConstant = sized dispatch intSingles = do count <- choose (1 :: Integer, 20) vals <- vectorOf (fromInteger count) (choose (0 :: Integer, 100)) - return ( DomainInt (map (RangeSingle . ConstantInt) vals) + return ( DomainInt Nothing (map (RangeSingle . ConstantInt) vals) , ConstantInt <$> pickFromList vals ) @@ -153,7 +153,7 @@ arbitraryDomainAndConstant = sized dispatch if null allVals then bug "allVals null" - else return ( DomainInt rs + else return ( DomainInt Nothing rs , ConstantInt <$> pickFromList allVals ) diff --git a/src/Conjure/Language/Constant.hs b/src/Conjure/Language/Constant.hs index 30b10624e7..db00b429d4 100644 --- a/src/Conjure/Language/Constant.hs +++ b/src/Conjure/Language/Constant.hs @@ -94,7 +94,7 @@ instance Arbitrary Constant where instance TypeOf Constant where typeOf ConstantBool{} = return TypeBool - typeOf ConstantInt{} = return TypeInt + typeOf ConstantInt{} = return $ TypeInt Nothing typeOf (ConstantEnum defn _ _ ) = return (TypeEnum defn) typeOf (ConstantField _ ty) = return ty typeOf (ConstantAbstract x ) = typeOf x @@ -104,8 +104,8 @@ instance TypeOf Constant where instance DomainSizeOf Constant Integer where domainSizeOf DomainBool{} = return 2 - domainSizeOf (DomainIntE x) = bug ("not implemented, domainSizeOf DomainIntE" <+> pretty (show x)) - domainSizeOf (DomainInt rs) = domainSizeOfRanges rs + domainSizeOf (DomainIntE _ x) = bug ("not implemented, domainSizeOf DomainIntE" <+> pretty (show x)) + domainSizeOf (DomainInt _ rs) = domainSizeOfRanges rs domainSizeOf DomainEnum{} = fail "domainSizeOf: Unknown for given enum." domainSizeOf (DomainTuple ds) = product <$> mapM domainSizeOf ds domainSizeOf (DomainMatrix index inner) = intPow <$> domainSizeOf inner <*> domainSizeOf index @@ -168,7 +168,7 @@ instance Pretty Constant where (indices,inner) = first (index:) $ collect innerNested collect (TypeMatrix i j) = first (i:) $ collect j collect x = ([],x) - pretty' TypeInt = "int()" + pretty' (TypeInt _) = "int()" pretty' t = pretty t in prParens $ "[] : `" <> pretty' ty <> "`" @@ -271,9 +271,9 @@ validateConstantForDomain :: forall m r . (MonadFail m, Pretty r) => Name -> Con validateConstantForDomain _ ConstantBool{} DomainBool{} = return () -validateConstantForDomain _ _ (DomainInt []) = return () -- no restrictions +validateConstantForDomain _ _ (DomainInt _ []) = return () -- no restrictions -validateConstantForDomain name c@(ConstantInt i) d@(DomainInt rs) = +validateConstantForDomain name c@(ConstantInt i) d@(DomainInt _ rs) = let intInRange RangeOpen = True intInRange (RangeSingle (ConstantInt a)) = i == a @@ -308,7 +308,7 @@ validateConstantForDomain name lu2 = mapM lu rs <- mapM lu2 ranges - validateConstantForDomain name c (DomainInt rs :: Domain r Constant) + validateConstantForDomain name c (DomainInt Nothing rs :: Domain r Constant) validateConstantForDomain name c@(ConstantAbstract (AbsLitTuple cs)) @@ -335,7 +335,7 @@ validateConstantForDomain name d@(DomainMatrix dIndex dInner) = do nested c d $ mapM_ (\ val -> validateConstantForDomain name val dInner ) vals - unless (cIndex == dIndex || cIndex == DomainInt []) $ fail $ vcat + unless (cIndex == dIndex || cIndex == DomainInt Nothing []) $ fail $ vcat [ "The indices do not match between the value and the domain." , "Value :" <+> pretty c , "Domain:" <+> pretty d @@ -490,7 +490,7 @@ viewConstantFunction (TypedConstant c _) = viewConstantFunction c viewConstantFunction constant = do let suggestion = case constant of - ConstantAbstract (AbsLitMatrix (DomainInt rs) vals) -> do + ConstantAbstract (AbsLitMatrix (DomainInt Nothing rs) vals) -> do froms <- valuesInIntDomain rs return $ Just $ pretty $ AbsLitFunction (zip (map ConstantInt froms) vals) _ -> return Nothing diff --git a/src/Conjure/Language/Domain.hs b/src/Conjure/Language/Domain.hs index ceee0f174f..af2a8b801f 100644 --- a/src/Conjure/Language/Domain.hs +++ b/src/Conjure/Language/Domain.hs @@ -21,7 +21,7 @@ module Conjure.Language.Domain , Tree(..), reprTree, reprAtTopLevel, applyReprTree , reprTreeEncoded , forgetRepr, changeRepr, defRepr - , mkDomainBool, mkDomainInt, mkDomainIntB, mkDomainAny + , mkDomainBool, mkDomainInt, mkDomainIntB, mkDomainIntBNamed, mkDomainAny , typeOfDomain , readBinRel , normaliseDomain, normaliseRange @@ -54,8 +54,8 @@ import Data.Data ( toConstr, constrIndex ) data Domain r x = DomainAny Text Type | DomainBool - | DomainIntE x - | DomainInt [Range x] + | DomainIntE (Maybe Name) x + | DomainInt (Maybe Name) [Range x] | DomainEnum Name (Maybe [Range x]) -- subset of values for this domain @@ -85,10 +85,14 @@ mkDomainBool :: Domain () x mkDomainBool = DomainBool mkDomainInt :: [Range x] -> Domain () x -mkDomainInt = DomainInt +mkDomainInt = DomainInt Nothing mkDomainIntB :: x -> x -> Domain () x -mkDomainIntB l u = DomainInt [RangeBounded l u] +mkDomainIntB l u = DomainInt Nothing [RangeBounded l u] + +mkDomainIntBNamed :: Name -> x -> x -> Domain () x +mkDomainIntBNamed name l u = DomainInt (Just name) [RangeBounded l u] + mkDomainAny :: Doc -> Type -> Domain r x mkDomainAny reason = DomainAny (stringToText $ show reason) @@ -102,16 +106,16 @@ instance Arbitrary x => Arbitrary (Domain r x) where arbitrary = sized f where f 0 = oneof [ return DomainBool - , DomainInt <$> arbitrary + , DomainInt Nothing <$> arbitrary -- , DomainEnum <$> arbitrary <*> arbitrary ] f s = do arity <- choose (2 :: Int, 10) DomainTuple <$> vectorOf arity (f (div s 10)) shrink DomainBool = [] - shrink (DomainInt []) = [DomainBool] - shrink (DomainInt [r]) = DomainBool : DomainInt [] : [DomainInt [r'] | r' <- shrink r] - shrink (DomainInt rs) = [DomainInt (init rs)] + shrink (DomainInt Nothing []) = [DomainBool] + shrink (DomainInt Nothing [r]) = DomainBool : DomainInt Nothing [] : [DomainInt Nothing [r'] | r' <- shrink r] + shrink (DomainInt Nothing rs) = [DomainInt Nothing (init rs)] shrink _ = [] instance (Pretty r, TypeOf x, Pretty x) => TypeOf (Domain r x) where @@ -120,27 +124,27 @@ instance (Pretty r, TypeOf x, Pretty x) => TypeOf (Domain r x) where typeOfDomain :: (MonadFail m, Pretty r, TypeOf x, Pretty x) => Domain r x -> m Type typeOfDomain (DomainAny _ ty) = return ty typeOfDomain DomainBool = return TypeBool -typeOfDomain d@(DomainIntE x) = do +typeOfDomain d@(DomainIntE name x) = do ty <- typeOf x case ty of - TypeInt -> return () -- pre recoverDomainInt - TypeList TypeInt -> return () - TypeMatrix _ TypeInt -> return () - TypeSet TypeInt -> return () + TypeInt _ -> return () -- pre recoverDomainInt + TypeList (TypeInt _) -> return () + TypeMatrix _ (TypeInt _) -> return () + TypeSet (TypeInt _) -> return () _ -> fail $ vcat [ "Expected an integer, but got:" <++> pretty ty , "In domain:" <+> pretty d ] - return TypeInt -typeOfDomain d@(DomainInt rs) = do + return $ TypeInt name +typeOfDomain d@(DomainInt name rs) = do forM_ rs $ \ r -> forM_ r $ \ x -> do ty <- typeOf x case ty of - TypeInt -> return () + TypeInt _ -> return () _ -> fail $ vcat [ "Expected an integer, but got:" <++> pretty ty , "For:" <+> pretty x , "In domain:" <+> pretty d ] - return TypeInt + return $ TypeInt name typeOfDomain (DomainEnum defn _ _ ) = return (TypeEnum defn) typeOfDomain (DomainUnnamed defn _ ) = return (TypeUnnamed defn) typeOfDomain (DomainTuple xs ) = TypeTuple <$> mapM typeOf xs @@ -176,8 +180,8 @@ changeRepr rep = go where go (DomainAny t ty) = DomainAny t ty go DomainBool = DomainBool - go (DomainIntE x) = DomainIntE x - go (DomainInt rs) = DomainInt rs + go (DomainIntE name x) = DomainIntE name x + go (DomainInt name rs) = DomainInt name rs go (DomainEnum defn rs mp) = DomainEnum defn rs mp go (DomainUnnamed defn s) = DomainUnnamed defn s go (DomainTuple ds) = DomainTuple (map go ds) @@ -819,10 +823,12 @@ instance (Pretty r, Pretty a) => Pretty (Domain r a) where pretty DomainBool = "bool" - pretty (DomainIntE x) = "int" <> prParens (pretty x) + pretty (DomainIntE _ x) = "int" <> prParens (pretty x) + + pretty (DomainInt _ []) = "int" + + pretty (DomainInt _ ranges) = "int" <> prettyList prParens "," ranges - pretty (DomainInt []) = "int" - pretty (DomainInt ranges) = "int" <> prettyList prParens "," ranges pretty (DomainEnum name (Just ranges) _) = pretty name <> prettyList prParens "," ranges pretty (DomainEnum name _ _) = pretty name @@ -968,7 +974,7 @@ representationToFullText r = representationToShortText r normaliseDomain :: (Ord c, ExpressionLike c) => (c -> c) -> Domain r c -> Domain r c normaliseDomain _norm DomainBool = DomainBool -normaliseDomain norm (DomainInt rs ) = DomainInt $ sort $ map (normaliseRange norm) (expandRanges rs) +normaliseDomain norm (DomainInt name rs ) = DomainInt name $ sort $ map (normaliseRange norm) (expandRanges rs) normaliseDomain _norm (DomainEnum n Nothing mp) = DomainEnum n Nothing mp normaliseDomain _norm (DomainEnum n (Just rs) mp) = DomainEnum n (Just $ sort rs) mp normaliseDomain norm (DomainUnnamed n x ) = DomainUnnamed n (norm x) @@ -1011,8 +1017,8 @@ innerDomainOf (DomainPartition _ _ t) = return (DomainSet () def t) innerDomainOf t = fail ("innerDomainOf:" <+> pretty (show t)) singletonDomainInt :: (Eq x, CanBeAnAlias x) => Domain r x -> Maybe x -singletonDomainInt (DomainInt [RangeSingle a]) = Just a -singletonDomainInt (DomainInt [RangeBounded a b]) = +singletonDomainInt (DomainInt _ [RangeSingle a]) = Just a +singletonDomainInt (DomainInt _ [RangeBounded a b]) = let followAlias (isAlias -> Just x) = followAlias x followAlias x = x diff --git a/src/Conjure/Language/Expression.hs b/src/Conjure/Language/Expression.hs index af66eb3db2..657fd28636 100644 --- a/src/Conjure/Language/Expression.hs +++ b/src/Conjure/Language/Expression.hs @@ -759,7 +759,7 @@ instance VarSymBreakingDescription AbstractPattern where patternToExpr :: AbstractPattern -> Expression patternToExpr (Single nm) = Reference nm Nothing patternToExpr (AbsPatTuple ts) = AbstractLiteral $ AbsLitTuple $ map patternToExpr ts -patternToExpr (AbsPatMatrix ts) = AbstractLiteral $ AbsLitMatrix (DomainInt [RangeBounded 1 (fromInt (genericLength ts))]) +patternToExpr (AbsPatMatrix ts) = AbstractLiteral $ AbsLitMatrix (DomainInt Nothing [RangeBounded 1 (fromInt (genericLength ts))]) $ map patternToExpr ts patternToExpr (AbsPatSet ts) = AbstractLiteral $ AbsLitSet $ map patternToExpr ts patternToExpr AbstractPatternMetaVar{} = bug "patternToExpr" diff --git a/src/Conjure/Language/Expression/DomainSizeOf.hs b/src/Conjure/Language/Expression/DomainSizeOf.hs index 15007fab5d..6cc6185baa 100644 --- a/src/Conjure/Language/Expression/DomainSizeOf.hs +++ b/src/Conjure/Language/Expression/DomainSizeOf.hs @@ -22,12 +22,12 @@ import Conjure.Language.Pretty instance DomainSizeOf Expression Expression where domainSizeOf DomainBool = return 2 - domainSizeOf (DomainInt [] ) = fail "domainSizeOf infinite integer domain" - domainSizeOf (DomainInt [r]) = domainSizeOfRange r - domainSizeOf (DomainInt rs ) = make opSum . fromList <$> mapM domainSizeOfRange rs + domainSizeOf (DomainInt _ [] ) = fail "domainSizeOf infinite integer domain" + domainSizeOf (DomainInt _ [r]) = domainSizeOfRange r + domainSizeOf (DomainInt _ rs ) = make opSum . fromList <$> mapM domainSizeOfRange rs domainSizeOf (DomainEnum n Nothing _) = return $ let n' = n `mappend` "_EnumSize" - in Reference n' (Just (DeclHasRepr Given n' (DomainInt []))) + in Reference n' (Just (DeclHasRepr Given n' (DomainInt (Just n) []))) domainSizeOf (DomainUnnamed _ x) = return x domainSizeOf (DomainTuple []) = return 1 domainSizeOf (DomainTuple xs) = make opProduct . fromList <$> mapM domainSizeOf xs diff --git a/src/Conjure/Language/Expression/Op/AllDiffExcept.hs b/src/Conjure/Language/Expression/Op/AllDiffExcept.hs index f6052614e5..f918304cb1 100644 --- a/src/Conjure/Language/Expression/Op/AllDiffExcept.hs +++ b/src/Conjure/Language/Expression/Op/AllDiffExcept.hs @@ -23,7 +23,7 @@ instance (TypeOf x, Pretty x) => TypeOf (OpAllDiffExcept x) where tyX <- typeOf x tyN <- typeOf n case tyN of - TypeInt -> return () + TypeInt _ -> return () _ -> raiseTypeError p case tyX of TypeList{} -> return TypeBool diff --git a/src/Conjure/Language/Expression/Op/Apply.hs b/src/Conjure/Language/Expression/Op/Apply.hs index 7a842889c8..2a9f2581dc 100644 --- a/src/Conjure/Language/Expression/Op/Apply.hs +++ b/src/Conjure/Language/Expression/Op/Apply.hs @@ -37,7 +37,7 @@ instance EvaluateOp OpApply where gt <- typeOf g ht <- typeOf h case (gt, ht) of - (TypePermutation TypeInt, TypePermutation TypeInt) -> + (TypePermutation (TypeInt _), TypePermutation (TypeInt _)) -> let appI xss i = case filter (i `elem`) xss of [] -> return i [k] -> return $ head $ drop 1 $ dropWhile (/= i) $ cycle k diff --git a/src/Conjure/Language/Expression/Op/Defined.hs b/src/Conjure/Language/Expression/Op/Defined.hs index c89ec2b099..611b088e9d 100644 --- a/src/Conjure/Language/Expression/Op/Defined.hs +++ b/src/Conjure/Language/Expression/Op/Defined.hs @@ -23,7 +23,7 @@ instance (Pretty x, TypeOf x) => TypeOf (OpDefined x) where ty <- typeOf x case ty of TypeFunction a _ -> return (TypeSet a) - TypeSequence _ -> return (TypeSet TypeInt) + TypeSequence _ -> return (TypeSet $ TypeInt Nothing) _ -> raiseTypeError p instance EvaluateOp OpDefined where diff --git a/src/Conjure/Language/Expression/Op/Div.hs b/src/Conjure/Language/Expression/Op/Div.hs index 75b8b8bc18..4bea5d3d05 100644 --- a/src/Conjure/Language/Expression/Op/Div.hs +++ b/src/Conjure/Language/Expression/Op/Div.hs @@ -25,10 +25,10 @@ instance (TypeOf x, Pretty x) => TypeOf (OpDiv x) where typeOf p@(OpDiv a b) = intToIntToInt p a b instance EvaluateOp OpDiv where - evaluateOp p | any isUndef (childrenBi p) = return $ mkUndef TypeInt $ "Has undefined children:" <+> pretty p + evaluateOp p | any isUndef (childrenBi p) = return $ mkUndef (TypeInt Nothing) $ "Has undefined children:" <+> pretty p evaluateOp p@(OpDiv x y) | y /= 0 = ConstantInt <$> (div <$> intOut "div x" x <*> intOut "div y" y) - | otherwise = return $ mkUndef TypeInt $ "division by zero:" <+> pretty p + | otherwise = return $ mkUndef (TypeInt Nothing) $ "division by zero:" <+> pretty p instance SimplifyOp OpDiv x where simplifyOp _ = na "simplifyOp{OpDiv}" diff --git a/src/Conjure/Language/Expression/Op/Factorial.hs b/src/Conjure/Language/Expression/Op/Factorial.hs index 553d23da84..107e600171 100644 --- a/src/Conjure/Language/Expression/Op/Factorial.hs +++ b/src/Conjure/Language/Expression/Op/Factorial.hs @@ -19,10 +19,10 @@ instance ToJSON x => ToJSON (OpFactorial x) where toJSON = genericToJSON j instance FromJSON x => FromJSON (OpFactorial x) where parseJSON = genericParseJSON jsonOptions instance TypeOf x => TypeOf (OpFactorial x) where - typeOf (OpFactorial a) = do TypeInt <- typeOf a ; return TypeInt + typeOf (OpFactorial a) = do TypeInt Nothing <- typeOf a ; return $ TypeInt Nothing instance EvaluateOp OpFactorial where - evaluateOp p | any isUndef (childrenBi p) = return $ mkUndef TypeInt $ "Has undefined children:" <+> pretty p + evaluateOp p | any isUndef (childrenBi p) = return $ mkUndef (TypeInt Nothing) $ "Has undefined children:" <+> pretty p evaluateOp (OpFactorial x) = ConstantInt . product . enumFromTo 1 <$> intOut "factorial" x instance SimplifyOp OpFactorial x where diff --git a/src/Conjure/Language/Expression/Op/Flatten.hs b/src/Conjure/Language/Expression/Op/Flatten.hs index 692ff1ad10..923c50a549 100644 --- a/src/Conjure/Language/Expression/Op/Flatten.hs +++ b/src/Conjure/Language/Expression/Op/Flatten.hs @@ -42,7 +42,7 @@ instance EvaluateOp OpFlatten where flat c = [c] let flattened = flat m return (ConstantAbstract $ AbsLitMatrix - (DomainInt [RangeBounded 1 (fromInt (genericLength flattened))]) + (DomainInt Nothing [RangeBounded 1 (fromInt (genericLength flattened))]) flattened) evaluateOp (OpFlatten (Just n) m) = do let flat lvl c | lvl < 0 = return [c] @@ -50,7 +50,7 @@ instance EvaluateOp OpFlatten where flat _ _ = fail $ "Cannot flatten" <+> pretty n <+> "levels." flattened <- flat n m return (ConstantAbstract $ AbsLitMatrix - (DomainInt [RangeBounded 1 (fromInt (genericLength flattened))]) + (DomainInt Nothing [RangeBounded 1 (fromInt (genericLength flattened))]) flattened) instance SimplifyOp OpFlatten x where diff --git a/src/Conjure/Language/Expression/Op/Freq.hs b/src/Conjure/Language/Expression/Op/Freq.hs index 622ce7fbad..7db0bcb1ac 100644 --- a/src/Conjure/Language/Expression/Op/Freq.hs +++ b/src/Conjure/Language/Expression/Op/Freq.hs @@ -24,7 +24,7 @@ instance (TypeOf x, Pretty x) => TypeOf (OpFreq x) where tyE <- typeOf e case tyM of TypeMSet tyE' - | tyE `typeUnify` tyE' -> return TypeInt + | tyE `typeUnify` tyE' -> return $ TypeInt Nothing | otherwise -> raiseTypeError $ vcat [ "The first argument of freq is expected to be a multi-set." , pretty p diff --git a/src/Conjure/Language/Expression/Op/Geq.hs b/src/Conjure/Language/Expression/Op/Geq.hs index e14b59f53b..4ad066ad03 100644 --- a/src/Conjure/Language/Expression/Op/Geq.hs +++ b/src/Conjure/Language/Expression/Op/Geq.hs @@ -23,7 +23,7 @@ instance BinaryOperator (OpGeq x) where instance (TypeOf x, Pretty x) => TypeOf (OpGeq x) where typeOf p@(OpGeq a b) = sameToSameToBool p a b - [TypeBool, TypeInt, TypeEnum "?"] + [TypeBool, TypeInt Nothing, TypeEnum "?"] instance EvaluateOp OpGeq where evaluateOp (OpGeq x y) = return $ ConstantBool $ x >= y diff --git a/src/Conjure/Language/Expression/Op/Gt.hs b/src/Conjure/Language/Expression/Op/Gt.hs index 430c10db40..cb3bf47001 100644 --- a/src/Conjure/Language/Expression/Op/Gt.hs +++ b/src/Conjure/Language/Expression/Op/Gt.hs @@ -23,7 +23,7 @@ instance BinaryOperator (OpGt x) where instance (TypeOf x, Pretty x) => TypeOf (OpGt x) where typeOf p@(OpGt a b) = sameToSameToBool p a b - [TypeBool, TypeInt, TypeEnum "?"] + [TypeBool, TypeInt Nothing, TypeEnum "?"] instance EvaluateOp OpGt where evaluateOp (OpGt x y) = return $ ConstantBool $ x > y diff --git a/src/Conjure/Language/Expression/Op/Hist.hs b/src/Conjure/Language/Expression/Op/Hist.hs index 30827135ad..22dcedac1a 100644 --- a/src/Conjure/Language/Expression/Op/Hist.hs +++ b/src/Conjure/Language/Expression/Op/Hist.hs @@ -22,17 +22,17 @@ instance (TypeOf x, Pretty x) => TypeOf (OpHist x) where typeOf p@(OpHist a) = do tyA <- typeOf a case tyA of - TypeMSet aInner -> return $ TypeMatrix TypeInt $ TypeTuple [aInner, TypeInt] - TypeMatrix _ aInner -> return $ TypeMatrix TypeInt $ TypeTuple [aInner, TypeInt] - TypeList aInner -> return $ TypeMatrix TypeInt $ TypeTuple [aInner, TypeInt] + TypeMSet aInner -> return $ TypeMatrix (TypeInt Nothing) $ TypeTuple [aInner, TypeInt Nothing] + TypeMatrix _ aInner -> return $ TypeMatrix (TypeInt Nothing) $ TypeTuple [aInner, TypeInt Nothing] + TypeList aInner -> return $ TypeMatrix (TypeInt Nothing) $ TypeTuple [aInner, TypeInt Nothing] _ -> raiseTypeError p instance EvaluateOp OpHist where evaluateOp (OpHist (viewConstantMSet -> Just cs)) = return $ ConstantAbstract $ AbsLitMatrix - (DomainInt [RangeBounded 1 (fromInt $ genericLength $ histogram cs)]) + (DomainInt Nothing [RangeBounded 1 (fromInt $ genericLength $ histogram cs)]) [ ConstantAbstract $ AbsLitTuple [e, ConstantInt n] | (e, n) <- histogram cs ] evaluateOp (OpHist (viewConstantMatrix -> Just (_, cs))) = return $ ConstantAbstract $ AbsLitMatrix - (DomainInt [RangeBounded 1 (fromInt $ genericLength $ histogram cs)]) + (DomainInt Nothing [RangeBounded 1 (fromInt $ genericLength $ histogram cs)]) [ ConstantAbstract $ AbsLitTuple [e, ConstantInt n] | (e, n) <- histogram cs ] evaluateOp op = na $ "evaluateOp{OpHist}:" <++> pretty (show op) diff --git a/src/Conjure/Language/Expression/Op/Image.hs b/src/Conjure/Language/Expression/Op/Image.hs index f41fe9d54e..5dc93907e8 100644 --- a/src/Conjure/Language/Expression/Op/Image.hs +++ b/src/Conjure/Language/Expression/Op/Image.hs @@ -23,7 +23,7 @@ instance (TypeOf x, Pretty x) => TypeOf (OpImage x) where tyF <- typeOf f (from, to) <- case tyF of TypeFunction from to -> return (from, to) - TypeSequence to -> return (TypeInt, to) + TypeSequence to -> return (TypeInt Nothing, to) _ -> raiseTypeError $ "(function application)" <+> pretty p xTy <- typeOf x if typesUnify [xTy, from] diff --git a/src/Conjure/Language/Expression/Op/ImageSet.hs b/src/Conjure/Language/Expression/Op/ImageSet.hs index 759c696a4c..1217ad9d69 100644 --- a/src/Conjure/Language/Expression/Op/ImageSet.hs +++ b/src/Conjure/Language/Expression/Op/ImageSet.hs @@ -23,7 +23,7 @@ instance (TypeOf x, Pretty x) => TypeOf (OpImageSet x) where tyF <- typeOf f (from, to) <- case tyF of TypeFunction from to -> return (from, to) - TypeSequence to -> return (TypeInt, to) + TypeSequence to -> return (TypeInt Nothing, to) _ -> raiseTypeError $ "(function application)" <+> pretty p xTy <- typeOf x if typesUnify [xTy, from] diff --git a/src/Conjure/Language/Expression/Op/Indexing.hs b/src/Conjure/Language/Expression/Op/Indexing.hs index 201558f0e5..824f1dfaf1 100644 --- a/src/Conjure/Language/Expression/Op/Indexing.hs +++ b/src/Conjure/Language/Expression/Op/Indexing.hs @@ -36,11 +36,11 @@ instance (TypeOf x, Pretty x, ExpressionLike x, ReferenceContainer x) => TypeOf , "Actual type of index :" <+> pretty tyI ] TypeList inn - | typesUnify [TypeInt, tyI] -> return inn + | typesUnify [TypeInt Nothing, tyI] -> return inn | otherwise -> fail $ "Indexing with inappropriate type:" <++> vcat [ "The expression:" <+> pretty p , "Indexing:" <+> pretty m - , "Expected type of index:" <+> pretty TypeInt + , "Expected type of index:" <+> pretty (TypeInt Nothing) , "Actual type of index :" <+> pretty tyI ] TypeTuple inns -> do @@ -80,7 +80,7 @@ instance EvaluateOp OpIndexing where TypeList tyTo -> return tyTo _ -> fail "evaluateOp{OpIndexing}" return $ mkUndef tyTo $ "Has undefined children (index):" <+> pretty p - evaluateOp (OpIndexing m@(viewConstantMatrix -> Just (DomainInt index, vals)) (ConstantInt x)) = do + evaluateOp (OpIndexing m@(viewConstantMatrix -> Just (DomainInt _ index, vals)) (ConstantInt x)) = do ty <- typeOf m tyTo <- case ty of TypeMatrix _ tyTo -> return tyTo TypeList tyTo -> return tyTo diff --git a/src/Conjure/Language/Expression/Op/Internal/Common.hs b/src/Conjure/Language/Expression/Op/Internal/Common.hs index 452add227c..2c9bc9b8b0 100644 --- a/src/Conjure/Language/Expression/Op/Internal/Common.hs +++ b/src/Conjure/Language/Expression/Op/Internal/Common.hs @@ -85,7 +85,7 @@ intToInt :: (MonadFail m, TypeOf a, Pretty p) => p -> a -> m Type intToInt p a = do tya <- typeOf a case tya of - TypeInt -> return TypeInt + TypeInt name -> return $ TypeInt name _ -> fail $ vcat [ "When type checking:" <+> pretty p , "Argument expected to be an int, but it is:" <++> pretty tya @@ -97,8 +97,14 @@ intToIntToInt p a b = do tya <- typeOf a tyb <- typeOf b case (tya, tyb) of - (TypeInt, TypeInt) -> return TypeInt - (_, TypeInt) -> fail $ vcat + (TypeInt namea, TypeInt nameb) -> + if namea == nameb + then return $ TypeInt namea + else fail$ vcat + [ "When type checking:" <+> pretty p + , "TypeInt names are not equal:" <+> pretty namea <+> pretty nameb + ] + (_, TypeInt _) -> fail $ vcat [ "When type checking:" <+> pretty p , "First argument expected to be an int, but it is:" <++> pretty tya ] diff --git a/src/Conjure/Language/Expression/Op/Leq.hs b/src/Conjure/Language/Expression/Op/Leq.hs index 12fc0576b0..1422e9314d 100644 --- a/src/Conjure/Language/Expression/Op/Leq.hs +++ b/src/Conjure/Language/Expression/Op/Leq.hs @@ -23,7 +23,7 @@ instance BinaryOperator (OpLeq x) where instance (TypeOf x, Pretty x) => TypeOf (OpLeq x) where typeOf p@(OpLeq a b) = sameToSameToBool p a b - [TypeBool, TypeInt, TypeEnum "?"] + [TypeBool, TypeInt Nothing, TypeEnum "?"] instance EvaluateOp OpLeq where evaluateOp (OpLeq x y) = return $ ConstantBool $ x <= y diff --git a/src/Conjure/Language/Expression/Op/Lt.hs b/src/Conjure/Language/Expression/Op/Lt.hs index a010f81268..dd0b571199 100644 --- a/src/Conjure/Language/Expression/Op/Lt.hs +++ b/src/Conjure/Language/Expression/Op/Lt.hs @@ -23,7 +23,7 @@ instance BinaryOperator (OpLt x) where instance (TypeOf x, Pretty x) => TypeOf (OpLt x) where typeOf p@(OpLt a b) = sameToSameToBool p a b - [TypeBool, TypeInt, TypeEnum "?"] + [TypeBool, TypeInt Nothing, TypeEnum "?"] instance EvaluateOp OpLt where evaluateOp (OpLt x y) = return $ ConstantBool $ x < y diff --git a/src/Conjure/Language/Expression/Op/Max.hs b/src/Conjure/Language/Expression/Op/Max.hs index dbecc86a5a..6b296e2d61 100644 --- a/src/Conjure/Language/Expression/Op/Max.hs +++ b/src/Conjure/Language/Expression/Op/Max.hs @@ -39,19 +39,19 @@ instance ( TypeOf x, Pretty x , "Unexpected type inside max:" <+> pretty ty ] case tyInner of - TypeInt -> return () + TypeInt Nothing -> return () _ -> raiseTypeError $ vcat [ pretty p , "Unexpected type inside max:" <+> pretty ty ] return tyInner instance EvaluateOp OpMax where - evaluateOp p | any isUndef (childrenBi p) = return $ mkUndef TypeInt $ "Has undefined children:" <+> pretty p + evaluateOp p | any isUndef (childrenBi p) = return $ mkUndef (TypeInt Nothing) $ "Has undefined children:" <+> pretty p evaluateOp (OpMax (DomainInConstant DomainBool)) = return (ConstantBool True) - evaluateOp (OpMax (DomainInConstant (DomainInt rs))) = do + evaluateOp (OpMax (DomainInConstant (DomainInt Nothing rs))) = do is <- rangesInts rs return $ if null is - then mkUndef TypeInt "Empty collection in max" + then mkUndef (TypeInt Nothing) "Empty collection in max" else ConstantInt (maximum is) evaluateOp (OpMax coll@(viewConstantMatrix -> Just (_, xs))) = case xs of @@ -61,7 +61,7 @@ instance EvaluateOp OpMax where (x:_) -> do tyInner <- typeOf x case tyInner of - TypeInt -> do + TypeInt Nothing -> do is <- concatMapM (intsOut "OpMax 1") xs return $ ConstantInt (maximum is) _ -> na "evaluateOp{OpMax}" @@ -73,7 +73,7 @@ instance EvaluateOp OpMax where (x:_) -> do tyInner <- typeOf x case tyInner of - TypeInt -> do + TypeInt Nothing -> do is <- concatMapM (intsOut "OpMax 1") xs return $ ConstantInt (maximum is) _ -> na "evaluateOp{OpMax}" @@ -85,7 +85,7 @@ instance EvaluateOp OpMax where (x:_) -> do tyInner <- typeOf x case tyInner of - TypeInt -> do + TypeInt Nothing -> do is <- concatMapM (intsOut "OpMax 1") xs return $ ConstantInt (maximum is) _ -> na "evaluateOp{OpMax}" diff --git a/src/Conjure/Language/Expression/Op/Min.hs b/src/Conjure/Language/Expression/Op/Min.hs index 0192e6f66a..7d618aaa40 100644 --- a/src/Conjure/Language/Expression/Op/Min.hs +++ b/src/Conjure/Language/Expression/Op/Min.hs @@ -39,19 +39,19 @@ instance ( TypeOf x, Pretty x , "Unexpected type inside min:" <+> pretty ty ] case tyInner of - TypeInt -> return () + TypeInt Nothing -> return () _ -> raiseTypeError $ vcat [ pretty p , "Unexpected type inside min:" <+> pretty ty ] return tyInner instance EvaluateOp OpMin where - evaluateOp p | any isUndef (childrenBi p) = return $ mkUndef TypeInt $ "Has undefined children:" <+> pretty p + evaluateOp p | any isUndef (childrenBi p) = return $ mkUndef (TypeInt Nothing) $ "Has undefined children:" <+> pretty p evaluateOp (OpMin (DomainInConstant DomainBool)) = return (ConstantBool False) - evaluateOp (OpMin (DomainInConstant (DomainInt rs))) = do + evaluateOp (OpMin (DomainInConstant (DomainInt Nothing rs))) = do is <- rangesInts rs return $ if null is - then mkUndef TypeInt "Empty collection in min" + then mkUndef (TypeInt Nothing) "Empty collection in min" else ConstantInt (minimum is) evaluateOp (OpMin coll@(viewConstantMatrix -> Just (_, xs))) = do case xs of @@ -61,7 +61,7 @@ instance EvaluateOp OpMin where (x:_) -> do tyInner <- typeOf x case tyInner of - TypeInt -> do + TypeInt _ -> do is <- concatMapM (intsOut "OpMin 1") xs return $ ConstantInt (minimum is) _ -> na "evaluateOp{OpMin}" @@ -73,7 +73,7 @@ instance EvaluateOp OpMin where (x:_) -> do tyInner <- typeOf x case tyInner of - TypeInt -> do + TypeInt Nothing -> do is <- concatMapM (intsOut "OpMin 1") xs return $ ConstantInt (minimum is) _ -> na "evaluateOp{OpMin}" @@ -85,7 +85,7 @@ instance EvaluateOp OpMin where (x:_) -> do tyInner <- typeOf x case tyInner of - TypeInt -> do + TypeInt Nothing -> do is <- concatMapM (intsOut "OpMin 1") xs return $ ConstantInt (minimum is) _ -> na "evaluateOp{OpMin}" diff --git a/src/Conjure/Language/Expression/Op/Minus.hs b/src/Conjure/Language/Expression/Op/Minus.hs index 155c255c19..658a4c204f 100644 --- a/src/Conjure/Language/Expression/Op/Minus.hs +++ b/src/Conjure/Language/Expression/Op/Minus.hs @@ -23,7 +23,7 @@ instance BinaryOperator (OpMinus x) where instance (TypeOf x, Pretty x) => TypeOf (OpMinus x) where typeOf p@(OpMinus a b) = sameToSameToSame p a b - [ TypeInt + [ TypeInt Nothing , TypeSet TypeAny , TypeMSet TypeAny , TypeFunction TypeAny TypeAny diff --git a/src/Conjure/Language/Expression/Op/Mod.hs b/src/Conjure/Language/Expression/Op/Mod.hs index 7d18a045ab..bb4c37c20d 100644 --- a/src/Conjure/Language/Expression/Op/Mod.hs +++ b/src/Conjure/Language/Expression/Op/Mod.hs @@ -25,10 +25,10 @@ instance (TypeOf x, Pretty x) => TypeOf (OpMod x) where typeOf p@(OpMod a b) = intToIntToInt p a b instance EvaluateOp OpMod where - evaluateOp p | any isUndef (childrenBi p) = return $ mkUndef TypeInt $ "Has undefined children:" <+> pretty p + evaluateOp p | any isUndef (childrenBi p) = return $ mkUndef (TypeInt Nothing) $ "Has undefined children:" <+> pretty p evaluateOp p@(OpMod x y) | y /= 0 = ConstantInt <$> (mod <$> intOut "mod x" x <*> intOut "mod y" y) - | otherwise = return $ mkUndef TypeInt $ "modulo zero:" <+> pretty p + | otherwise = return $ mkUndef (TypeInt Nothing) $ "modulo zero:" <+> pretty p instance SimplifyOp OpMod x where simplifyOp _ = na "simplifyOp{OpMod}" diff --git a/src/Conjure/Language/Expression/Op/Negate.hs b/src/Conjure/Language/Expression/Op/Negate.hs index 74c35615d1..4c8df2ed32 100644 --- a/src/Conjure/Language/Expression/Op/Negate.hs +++ b/src/Conjure/Language/Expression/Op/Negate.hs @@ -19,10 +19,10 @@ instance ToJSON x => ToJSON (OpNegate x) where toJSON = genericToJSON json instance FromJSON x => FromJSON (OpNegate x) where parseJSON = genericParseJSON jsonOptions instance TypeOf x => TypeOf (OpNegate x) where - typeOf (OpNegate a) = do TypeInt <- typeOf a ; return TypeInt + typeOf (OpNegate a) = do TypeInt Nothing <- typeOf a ; return (TypeInt Nothing) instance EvaluateOp OpNegate where - evaluateOp p | any isUndef (childrenBi p) = return $ mkUndef TypeInt $ "Has undefined children:" <+> pretty p + evaluateOp p | any isUndef (childrenBi p) = return $ mkUndef (TypeInt Nothing) $ "Has undefined children:" <+> pretty p evaluateOp (OpNegate x) = ConstantInt . negate <$> intOut "OpNegate" x instance SimplifyOp OpNegate x where diff --git a/src/Conjure/Language/Expression/Op/Permute.hs b/src/Conjure/Language/Expression/Op/Permute.hs index 9ed251505b..5f359a829d 100644 --- a/src/Conjure/Language/Expression/Op/Permute.hs +++ b/src/Conjure/Language/Expression/Op/Permute.hs @@ -25,29 +25,14 @@ instance (TypeOf x, Pretty x) => TypeOf (OpPermute x) where pTy <- typeOf p iTy <- typeOf i case (pTy,iTy) of - (TypePermutation pTyInner, TypeSet mTyInner) -> - if typesUnify $ [pTyInner, mTyInner] - then return $ TypeSet mTyInner - else raiseTypeError inp - (TypePermutation pTyInner, TypeTuple mTyInner) -> - if typesUnify $ [pTyInner] ++ mTyInner - then return $ TypeTuple mTyInner - else raiseTypeError inp - (TypePermutation pTyInner, TypeMatrix indx mTyInner) -> - if typesUnify [pTyInner, mTyInner] - then return $ TypeMatrix indx mTyInner - else raiseTypeError inp - (TypePermutation pTyInner, iTyIs) -> - if typesUnify [iTyIs, pTyInner] - then return pTyInner - else raiseTypeError inp + (TypePermutation _, thing) -> return thing _ -> raiseTypeError inp instance EvaluateOp OpPermute where evaluateOp op@(OpPermute (viewConstantPermutation -> Just xss) i) = do ti <- typeOf i case ti of - TypeInt -> case filter (i `elem`) xss of + TypeInt _-> case filter (i `elem`) xss of [] -> return i [h] -> return $ head $ drop 1 $ dropWhile (/= i) $ cycle h _ -> bug "evaluateOp{OpPermute} element should only be in one cycle of permutation" diff --git a/src/Conjure/Language/Expression/Op/Pow.hs b/src/Conjure/Language/Expression/Op/Pow.hs index 7fbc96f9a2..cf19e7bb51 100644 --- a/src/Conjure/Language/Expression/Op/Pow.hs +++ b/src/Conjure/Language/Expression/Op/Pow.hs @@ -25,10 +25,10 @@ instance (TypeOf x, Pretty x) => TypeOf (OpPow x) where typeOf p@(OpPow a b) = intToIntToInt p a b instance EvaluateOp OpPow where - evaluateOp p | any isUndef (childrenBi p) = return $ mkUndef TypeInt $ "Has undefined children:" <+> pretty p + evaluateOp p | any isUndef (childrenBi p) = return $ mkUndef (TypeInt Nothing) $ "Has undefined children:" <+> pretty p evaluateOp p@(OpPow x y) | y >= 0 = ConstantInt <$> ((^) <$> intOut "pow x" x <*> intOut "pow y" y) - | otherwise = return $ mkUndef TypeInt $ "negative exponent:" <+> pretty p + | otherwise = return $ mkUndef (TypeInt Nothing) $ "negative exponent:" <+> pretty p instance SimplifyOp OpPow x where simplifyOp _ = na "simplifyOp{OpPow}" diff --git a/src/Conjure/Language/Expression/Op/PreImage.hs b/src/Conjure/Language/Expression/Op/PreImage.hs index e49afb7c42..f9d96258af 100644 --- a/src/Conjure/Language/Expression/Op/PreImage.hs +++ b/src/Conjure/Language/Expression/Op/PreImage.hs @@ -29,7 +29,7 @@ instance (TypeOf x, Pretty x) => TypeOf (OpPreImage x) where else raiseTypeError p TypeSequence to -> do if typesUnify [xTy, to] - then return (TypeSet TypeInt) + then return (TypeSet (TypeInt Nothing)) else raiseTypeError p _ -> raiseTypeError p diff --git a/src/Conjure/Language/Expression/Op/Pred.hs b/src/Conjure/Language/Expression/Op/Pred.hs index bc8948e1bb..ddf20468e8 100644 --- a/src/Conjure/Language/Expression/Op/Pred.hs +++ b/src/Conjure/Language/Expression/Op/Pred.hs @@ -28,7 +28,7 @@ instance (TypeOf x, Pretty x) => TypeOf (OpPred x) where _ -> raiseTypeError p instance EvaluateOp OpPred where - evaluateOp p | any isUndef (childrenBi p) = return $ mkUndef TypeInt $ "Has undefined children:" <+> pretty p + evaluateOp p | any isUndef (childrenBi p) = return $ mkUndef (TypeInt Nothing) $ "Has undefined children:" <+> pretty p evaluateOp (OpPred (ConstantBool _)) = return (ConstantBool False) -- True --> False -- False --> undef, hence False evaluateOp (OpPred (ConstantInt x)) = return (ConstantInt (pred x)) diff --git a/src/Conjure/Language/Expression/Op/Product.hs b/src/Conjure/Language/Expression/Op/Product.hs index 94ba9380ab..b4171ee935 100644 --- a/src/Conjure/Language/Expression/Op/Product.hs +++ b/src/Conjure/Language/Expression/Op/Product.hs @@ -23,12 +23,12 @@ instance (TypeOf x, Pretty x, ExpressionLike x) => TypeOf (OpProduct x) where typeOf p@(OpProduct x) = do ty <- typeOf x case ty of - TypeList TypeAny -> return TypeInt - TypeList TypeInt -> return TypeInt - TypeMatrix _ TypeAny -> return TypeInt - TypeMatrix _ TypeInt -> return TypeInt - TypeSet TypeInt -> return TypeInt - TypeMSet TypeInt -> return TypeInt + TypeList TypeAny -> return $ TypeInt Nothing + TypeList (TypeInt Nothing) -> return (TypeInt Nothing) + TypeMatrix _ TypeAny -> return $ TypeInt Nothing + TypeMatrix _ (TypeInt Nothing) -> return (TypeInt Nothing) + TypeSet (TypeInt Nothing) -> return (TypeInt Nothing) + TypeMSet (TypeInt Nothing) -> return (TypeInt Nothing) _ -> raiseTypeError $ vcat [ pretty p , "The argument has type:" <+> pretty ty ] @@ -37,10 +37,10 @@ instance BinaryOperator (OpProduct x) where opLexeme _ = L_Times instance EvaluateOp OpProduct where - evaluateOp p | any isUndef (childrenBi p) = return $ mkUndef TypeInt $ "Has undefined children:" <+> pretty p + evaluateOp p | any isUndef (childrenBi p) = return $ mkUndef (TypeInt Nothing) $ "Has undefined children:" <+> pretty p evaluateOp p@(OpProduct x) | Just xs <- listOut x - , any isUndef xs = return $ mkUndef TypeInt $ "Has undefined children:" <+> pretty p + , any isUndef xs = return $ mkUndef (TypeInt Nothing) $ "Has undefined children:" <+> pretty p evaluateOp (OpProduct x) = ConstantInt . product <$> intsOut "OpProduct" x instance (OpProduct x :< x) => SimplifyOp OpProduct x where diff --git a/src/Conjure/Language/Expression/Op/Slicing.hs b/src/Conjure/Language/Expression/Op/Slicing.hs index 0f920b43d9..2121dc26db 100644 --- a/src/Conjure/Language/Expression/Op/Slicing.hs +++ b/src/Conjure/Language/Expression/Op/Slicing.hs @@ -28,7 +28,7 @@ instance (TypeOf x, Pretty x) => TypeOf (OpSlicing x) where return ty instance EvaluateOp OpSlicing where - evaluateOp (OpSlicing (viewConstantMatrix -> Just (DomainInt index, vals)) lb ub) = do + evaluateOp (OpSlicing (viewConstantMatrix -> Just (DomainInt _ index, vals)) lb ub) = do indexVals <- valuesInIntDomain index outVals <- fmap catMaybes $ forM (zip indexVals vals) $ \ (thisIndex, thisVal) -> case lb of @@ -36,7 +36,7 @@ instance EvaluateOp OpSlicing where _ -> case ub of Just (ConstantInt upper) | upper < thisIndex -> return Nothing _ -> return $ Just (thisIndex, thisVal) - let outDomain = DomainInt $ map (RangeSingle . ConstantInt . fst) outVals + let outDomain = DomainInt Nothing $ map (RangeSingle . ConstantInt . fst) outVals return $ ConstantAbstract $ AbsLitMatrix outDomain (map snd outVals) evaluateOp op = na $ "evaluateOp{OpSlicing}:" <++> pretty (show op) diff --git a/src/Conjure/Language/Expression/Op/Succ.hs b/src/Conjure/Language/Expression/Op/Succ.hs index 923bd39554..be01ebdeae 100644 --- a/src/Conjure/Language/Expression/Op/Succ.hs +++ b/src/Conjure/Language/Expression/Op/Succ.hs @@ -28,7 +28,7 @@ instance (TypeOf x, Pretty x) => TypeOf (OpSucc x) where _ -> raiseTypeError p instance EvaluateOp OpSucc where - evaluateOp p | any isUndef (childrenBi p) = return $ mkUndef TypeInt $ "Has undefined children:" <+> pretty p + evaluateOp p | any isUndef (childrenBi p) = return $ mkUndef (TypeInt Nothing) $ "Has undefined children:" <+> pretty p evaluateOp (OpSucc (ConstantBool False)) = return (ConstantBool True) evaluateOp (OpSucc (ConstantBool True )) = return (ConstantBool False) -- undef evaluateOp (OpSucc (ConstantInt x)) = return (ConstantInt (succ x)) diff --git a/src/Conjure/Language/Expression/Op/Sum.hs b/src/Conjure/Language/Expression/Op/Sum.hs index 96f4e4bbbd..77eb0fc290 100644 --- a/src/Conjure/Language/Expression/Op/Sum.hs +++ b/src/Conjure/Language/Expression/Op/Sum.hs @@ -23,12 +23,12 @@ instance (TypeOf x, Pretty x, ExpressionLike x) => TypeOf (OpSum x) where typeOf p@(OpSum x) = do ty <- typeOf x case ty of - TypeList TypeAny -> return TypeInt - TypeList TypeInt -> return TypeInt - TypeMatrix _ TypeAny -> return TypeInt - TypeMatrix _ TypeInt -> return TypeInt - TypeSet TypeInt -> return TypeInt - TypeMSet TypeInt -> return TypeInt + TypeList TypeAny -> return $ TypeInt Nothing + TypeList (TypeInt Nothing) -> return $ TypeInt Nothing + TypeMatrix _ TypeAny -> return $ TypeInt Nothing + TypeMatrix _ (TypeInt Nothing) -> return $ TypeInt Nothing + TypeSet (TypeInt Nothing) -> return $ TypeInt Nothing + TypeMSet (TypeInt Nothing) -> return $ TypeInt Nothing _ -> raiseTypeError $ vcat [ pretty p , "The argument has type:" <+> pretty ty ] @@ -37,10 +37,10 @@ instance BinaryOperator (OpSum x) where opLexeme _ = L_Plus instance EvaluateOp OpSum where - evaluateOp p | any isUndef (childrenBi p) = return $ mkUndef TypeInt $ "Has undefined children:" <+> pretty p + evaluateOp p | any isUndef (childrenBi p) = return $ mkUndef (TypeInt Nothing) $ "Has undefined children:" <+> pretty p evaluateOp p@(OpSum x) | Just xs <- listOut x - , any isUndef xs = return $ mkUndef TypeInt $ "Has undefined children:" <+> pretty p + , any isUndef xs = return $ mkUndef (TypeInt Nothing) $ "Has undefined children:" <+> pretty p evaluateOp (OpSum x) = ConstantInt . sum <$> intsOut "OpSum" x instance (OpSum x :< x) => SimplifyOp OpSum x where diff --git a/src/Conjure/Language/Expression/Op/ToInt.hs b/src/Conjure/Language/Expression/Op/ToInt.hs index bb52bffdf6..6e3d02c649 100644 --- a/src/Conjure/Language/Expression/Op/ToInt.hs +++ b/src/Conjure/Language/Expression/Op/ToInt.hs @@ -22,7 +22,7 @@ instance (TypeOf x, Pretty x) => TypeOf (OpToInt x) where typeOf p@(OpToInt x) = do ty <- typeOf x case ty of - TypeBool -> return TypeInt + TypeBool -> return $ TypeInt Nothing _ -> raiseTypeError $ vcat [ pretty p , "Expected type bool." diff --git a/src/Conjure/Language/Expression/Op/TwoBars.hs b/src/Conjure/Language/Expression/Op/TwoBars.hs index 8540639b8c..0c28e4fd70 100644 --- a/src/Conjure/Language/Expression/Op/TwoBars.hs +++ b/src/Conjure/Language/Expression/Op/TwoBars.hs @@ -36,7 +36,7 @@ instance (TypeOf x, Pretty x) => TypeOf (OpTwoBars x) where , "Expected an integer or a collection." , "But got:" <+> pretty ty ] - return TypeInt + return $ TypeInt Nothing instance EvaluateOp OpTwoBars where evaluateOp (OpTwoBars x) = @@ -54,7 +54,7 @@ instance EvaluateOp OpTwoBars where (viewConstantPartition -> Just xs) -> return $ ConstantInt $ genericLength $ sortNub $ concat xs -- cardinality of a domain - DomainInConstant (DomainInt rs) -> ConstantInt . genericLength <$> rangesInts rs + DomainInConstant (DomainInt _ rs) -> ConstantInt . genericLength <$> rangesInts rs DomainInConstant dom -> runNameGen () $ domainSizeOf dom _ -> na $ "evaluateOp OpTwoBars" <+> pretty (show x) diff --git a/src/Conjure/Language/Instantiate.hs b/src/Conjure/Language/Instantiate.hs index 6ea90f3f5a..768b23a4c8 100644 --- a/src/Conjure/Language/Instantiate.hs +++ b/src/Conjure/Language/Instantiate.hs @@ -128,7 +128,7 @@ instantiateE (Comprehension body gensOrConds) = do ty else return $ ConstantAbstract $ AbsLitMatrix - (DomainInt [RangeBounded 1 (fromInt (genericLength constants))]) + (DomainInt Nothing [RangeBounded 1 (fromInt (genericLength constants))]) constants instantiateE (Reference name (Just (RecordField _ ty))) = return $ ConstantField name ty @@ -223,15 +223,15 @@ instantiateD -> m (Domain r Constant) instantiateD (DomainAny t ty) = return (DomainAny t ty) instantiateD DomainBool = return DomainBool -instantiateD (DomainIntE x) = do +instantiateD (DomainIntE name x) = do x' <- instantiateE x let vals = case (x', viewConstantMatrix x', viewConstantSet x') of (ConstantInt{}, _, _) -> [x'] (_, Just (_, xs), _) -> xs (_, _, Just xs) -> xs _ -> [] - return (DomainInt (map RangeSingle vals)) -instantiateD (DomainInt ranges) = DomainInt <$> mapM instantiateR ranges + return (DomainInt name (map RangeSingle vals)) +instantiateD (DomainInt name ranges) = DomainInt name <$> mapM instantiateR ranges instantiateD (DomainEnum nm Nothing _) = do st <- gets id case lookup nm st of diff --git a/src/Conjure/Language/Lenses.hs b/src/Conjure/Language/Lenses.hs index 0cbc530d71..2b7515b870 100644 --- a/src/Conjure/Language/Lenses.hs +++ b/src/Conjure/Language/Lenses.hs @@ -1506,9 +1506,9 @@ fixRelationProj = transformBi f maxOfDomain :: (MonadFail m, Pretty r) => Domain r Expression -> m Expression -maxOfDomain (DomainInt [] ) = fail "rule_DomainMinMax.maxOfDomain []" -maxOfDomain (DomainInt [r]) = maxOfRange r -maxOfDomain (DomainInt rs ) = do +maxOfDomain (DomainInt _ [] ) = fail "rule_DomainMinMax.maxOfDomain []" +maxOfDomain (DomainInt _ [r]) = maxOfRange r +maxOfDomain (DomainInt _ rs ) = do xs <- mapM maxOfRange rs return (make opMax (fromList xs)) maxOfDomain d = fail ("rule_DomainMinMax.maxOfDomain" <+> pretty d) @@ -1519,9 +1519,9 @@ maxOfRange (RangeBounded _ x) = return x maxOfRange r = fail ("rule_DomainMinMax.maxOfRange" <+> pretty r) minOfDomain :: (MonadFail m, Pretty r) => Domain r Expression -> m Expression -minOfDomain (DomainInt [] ) = fail "rule_DomainMinMax.minOfDomain []" -minOfDomain (DomainInt [r]) = minOfRange r -minOfDomain (DomainInt rs ) = do +minOfDomain (DomainInt _ [] ) = fail "rule_DomainMinMax.minOfDomain []" +minOfDomain (DomainInt _ [r]) = minOfRange r +minOfDomain (DomainInt _ rs ) = do xs <- mapM minOfRange rs return (make opMin (fromList xs)) minOfDomain d = fail ("rule_DomainMinMax.minOfDomain" <+> pretty d) diff --git a/src/Conjure/Language/Parser.hs b/src/Conjure/Language/Parser.hs index 9a2fb0cc6b..77ea60ea58 100644 --- a/src/Conjure/Language/Parser.hs +++ b/src/Conjure/Language/Parser.hs @@ -280,14 +280,14 @@ parseDomainWithRepr = pDomainAtom lexeme L_int x <- parens parseExpr case typeOf x of - Just TypeInt -> return $ DomainInt [RangeSingle x] - _ -> return $ DomainIntE x + Just (TypeInt Nothing)-> return $ DomainInt Nothing [RangeSingle x] + _ -> return $ DomainIntE Nothing x pInt = do lexeme L_int mxs <- optional $ parens $ commaSeparated0 $ parseRange parseExpr let xs = fromMaybe [] mxs - return $ DomainInt xs + return $ DomainInt Nothing xs pReference = do r <- identifierText diff --git a/src/Conjure/Language/ParserC.hs b/src/Conjure/Language/ParserC.hs index 17db29da2b..876d684cb7 100644 --- a/src/Conjure/Language/ParserC.hs +++ b/src/Conjure/Language/ParserC.hs @@ -131,14 +131,14 @@ parseDomainWithRepr = pDomainAtom lexeme L_int x <- parens parseExpr case typeOf x of - Just TypeInt -> return $ DomainInt [RangeSingle x] - _ -> return $ DomainIntE x + Just (TypeInt Nothing) -> return $ DomainInt Nothing [RangeSingle x] + _ -> return $ DomainIntE Nothing x pInt = do lexeme L_int mxs <- optional $ parens $ commaSeparated0 $ parseRange parseExpr let xs = fromMaybe [] mxs - return $ DomainInt xs + return $ DomainInt Nothing xs pReference = do r <- identifierText diff --git a/src/Conjure/Language/Type.hs b/src/Conjure/Language/Type.hs index ce419ad33d..20662fcc10 100644 --- a/src/Conjure/Language/Type.hs +++ b/src/Conjure/Language/Type.hs @@ -9,6 +9,7 @@ module Conjure.Language.Type , matrixNumDims , innerTypeOf , isPrimitiveType + , containsType ) where -- conjure @@ -21,7 +22,7 @@ import Conjure.Language.Pretty data Type = TypeAny | TypeBool - | TypeInt + | TypeInt (Maybe Name) | TypeEnum Name | TypeUnnamed Name | TypeTuple [Type] @@ -46,7 +47,8 @@ instance FromJSON Type where parseJSON = genericParseJSON jsonOptions instance Pretty Type where pretty TypeAny = "?" pretty TypeBool = "bool" - pretty TypeInt = "int" + pretty (TypeInt Nothing) = "int" + pretty (TypeInt (Just name)) = "int:" <> pretty name pretty (TypeEnum nm ) = pretty nm pretty (TypeUnnamed nm) = pretty nm pretty (TypeTuple xs) = (if length xs <= 1 then "tuple" else prEmpty) @@ -76,9 +78,11 @@ typeUnify :: Type -> Type -> Bool typeUnify TypeAny _ = True typeUnify _ TypeAny = True typeUnify TypeBool TypeBool = True -typeUnify TypeInt TypeInt = True -typeUnify TypeInt TypeEnum{} = True -typeUnify TypeEnum{} TypeInt = True +typeUnify (TypeInt a) (TypeInt b) = a == b +typeUnify (TypeInt (Nothing)) (TypeEnum _) = False +typeUnify (TypeInt (Just a)) (TypeEnum b) = a == b +typeUnify (TypeEnum _) (TypeInt (Nothing)) = False +typeUnify (TypeEnum b) (TypeInt (Just a)) = a == b typeUnify (TypeEnum a) (TypeEnum b) = a == b || a == "?" || b == "?" -- the "?" is a hack so sameToSameToBool works typeUnify (TypeUnnamed a) (TypeUnnamed b) = a == b typeUnify (TypeTuple [TypeAny]) TypeTuple{} = True @@ -188,7 +192,7 @@ innerTypeOf (TypeMatrix _ t) = return t innerTypeOf (TypeSet t) = return t innerTypeOf (TypeMSet t) = return t innerTypeOf (TypeFunction a b) = return (TypeTuple [a,b]) -innerTypeOf (TypeSequence t) = return (TypeTuple [TypeInt,t]) +innerTypeOf (TypeSequence t) = return (TypeTuple [TypeInt Nothing,t]) innerTypeOf (TypeRelation ts) = return (TypeTuple ts) innerTypeOf (TypePartition t) = return (TypeSet t) innerTypeOf (TypePermutation t) = return (TypeTuple [t,t]) @@ -199,3 +203,12 @@ isPrimitiveType TypeBool{} = True isPrimitiveType TypeInt{} = True isPrimitiveType (TypeMatrix index inner) = and [isPrimitiveType index, isPrimitiveType inner] isPrimitiveType _ = False + +containsType :: Type -> Type -> Bool +containsType container containee = + if typesUnify [container, containee] + then True + else case innerTypeOf container of + Nothing -> False + Just so -> containsType so containee + diff --git a/src/Conjure/Language/ZeroVal.hs b/src/Conjure/Language/ZeroVal.hs index f752e99cda..97fdfba7c6 100644 --- a/src/Conjure/Language/ZeroVal.hs +++ b/src/Conjure/Language/ZeroVal.hs @@ -11,8 +11,8 @@ import Conjure.Process.Enumerate ( EnumerateDomain, enumerateDomain ) zeroVal :: (MonadFail m, EnumerateDomain m, Pretty r) => Domain r Constant -> m Constant zeroVal DomainBool = return $ ConstantBool False -zeroVal (DomainInt []) = return $ ConstantInt 0 -zeroVal (DomainInt (r:_)) = zeroValR r +zeroVal (DomainInt _ []) = return $ ConstantInt 0 +zeroVal (DomainInt _ (r:_)) = zeroValR r zeroVal (DomainTuple ds) = ConstantAbstract . AbsLitTuple <$> mapM zeroVal ds zeroVal (DomainRecord xs) = do values <- forM xs $ \ (nm, dom) -> do @@ -25,7 +25,7 @@ zeroVal (DomainVariant xs@((nm, dom):_)) = do zeroVal (DomainMatrix index inner) = do z <- zeroVal inner is <- case index of - DomainInt rs -> rangesInts rs + DomainInt _ rs -> rangesInts rs _ -> fail $ "Matrix indexed by a domain that isn't int:" <+> pretty index return $ ConstantAbstract $ AbsLitMatrix index $ replicate (length is) z zeroVal d@(DomainSet _ (SetAttr sizeAttr) inner) = do diff --git a/src/Conjure/Process/Enumerate.hs b/src/Conjure/Process/Enumerate.hs index 5ec3067c1d..ace8af8169 100644 --- a/src/Conjure/Process/Enumerate.hs +++ b/src/Conjure/Process/Enumerate.hs @@ -90,18 +90,18 @@ enumerateDomain d | not (null [ () | ConstantUndefined{} <- universeBi d ]) = ] enumerateDomain DomainBool = return [ConstantBool False, ConstantBool True] -enumerateDomain (DomainInt []) = fail "enumerateDomain: infinite domain" -enumerateDomain (DomainInt rs) = concatMapM enumerateRange rs +enumerateDomain (DomainInt _ []) = fail "enumerateDomain: infinite domain" +enumerateDomain (DomainInt Nothing rs) = concatMapM enumerateRange rs enumerateDomain (DomainUnnamed _ (ConstantInt n)) = return (map ConstantInt [1..n]) enumerateDomain (DomainEnum _dName (Just rs) _mp) = concatMapM enumerateRange rs enumerateDomain (DomainTuple ds) = do inners <- mapM enumerateDomain ds return $ map (ConstantAbstract . AbsLitTuple) (sequence inners) -enumerateDomain (DomainMatrix (DomainInt indexDom) innerDom) = do +enumerateDomain (DomainMatrix (DomainInt name indexDom) innerDom) = do inners <- enumerateDomain innerDom indexInts <- rangesInts indexDom return - [ ConstantAbstract (AbsLitMatrix (DomainInt indexDom) vals) + [ ConstantAbstract (AbsLitMatrix (DomainInt name indexDom) vals) | vals <- replicateM (length indexInts) inners ] diff --git a/src/Conjure/Process/Enums.hs b/src/Conjure/Process/Enums.hs index be1d960c82..9f995972d3 100644 --- a/src/Conjure/Process/Enums.hs +++ b/src/Conjure/Process/Enums.hs @@ -33,7 +33,7 @@ removeEnumsFromModel = case st of Declaration (LettingDomainDefnEnum ename names) -> do namesBefore <- gets (map fst . snd) - let outDomain = mkDomainIntB 1 (fromInt (genericLength names)) + let outDomain = mkDomainIntBNamed ename 1 (fromInt (genericLength names)) case names `intersect` namesBefore of [] -> modify ( ( [(ename, outDomain)] , zip names allNats @@ -57,7 +57,7 @@ removeEnumsFromModel = onD :: MonadFail m => Domain () Expression -> m (Domain () Expression) onD (DomainEnum nm (Just ranges) _) | Just _ <- lookup nm enumDomainNames - = DomainInt <$> mapM (mapM (nameToX nameToIntMapping)) ranges + = DomainInt (Just nm) <$> mapM (mapM (nameToX nameToIntMapping)) ranges onD (DomainEnum nm Nothing _) | Just d <- lookup nm enumDomainNames = return (DomainReference nm (Just d)) @@ -75,8 +75,8 @@ removeEnumsFromModel = case st of Declaration (GivenDomainDefnEnum name) -> do let nameS = name `mappend` "_EnumSize" - let outDomainS = DomainInt [] - let outDomain = mkDomainIntB 1 + let outDomainS = DomainInt (Just name) [] + let outDomain = mkDomainIntBNamed name 1 (Reference nameS (Just (Alias (Domain outDomainS)))) modify ([(name, outDomain)] `mappend`) return [ Declaration (FindOrGiven Given nameS outDomainS) @@ -88,7 +88,7 @@ removeEnumsFromModel = onD :: Domain () Expression -> Domain () Expression onD (DomainEnum nm (Just ranges) _) | Just _ <- lookup nm enumDomainNames - = DomainInt ranges + = DomainInt (Just nm) ranges onD (DomainEnum nm Nothing _) | Just d <- lookup nm enumDomainNames = DomainReference nm (Just d) @@ -127,7 +127,7 @@ removeEnumsFromParam model param = do case st of Declaration (LettingDomainDefnEnum ename names) -> do namesBefore <- gets (map fst . snd) - let outDomain = mkDomainIntB 1 (fromInt (genericLength names)) + let outDomain = mkDomainIntBNamed ename 1 (fromInt (genericLength names)) case names `intersect` namesBefore of [] -> modify ( ( [(ename, outDomain)] , zip names allNats @@ -151,7 +151,7 @@ removeEnumsFromParam model param = do onD :: MonadFail m => Domain () Expression -> m (Domain () Expression) onD (DomainEnum nm (Just ranges) _) | Just _ <- lookup nm enumDomainNames - = DomainInt <$> mapM (mapM (nameToX nameToIntMapping)) ranges + = DomainInt (Just nm) <$> mapM (mapM (nameToX nameToIntMapping)) ranges onD (DomainEnum nm Nothing _) | Just d <- lookup nm enumDomainNames = return (DomainReference nm (Just d)) diff --git a/src/Conjure/Process/FiniteGivens.hs b/src/Conjure/Process/FiniteGivens.hs index 7e1db81c5d..45cab08ec6 100644 --- a/src/Conjure/Process/FiniteGivens.hs +++ b/src/Conjure/Process/FiniteGivens.hs @@ -32,7 +32,7 @@ finiteGivens m = flip evalStateT 1 $ do case st of Declaration (FindOrGiven Given name domain) -> do (domain', extras, _) <- mkFinite domain - return $ [ Declaration $ FindOrGiven Given e (DomainInt []) | e <- extras ] + return $ [ Declaration $ FindOrGiven Given e (DomainInt Nothing []) | e <- extras ] ++ [ Declaration $ FindOrGiven Given name domain' ] _ -> return [st] namegenst <- exportNameGenState @@ -365,11 +365,11 @@ mkFiniteInner , [Name] , [Constant] -> m [(Name, Constant)] ) -mkFiniteInner (DomainInt []) = do +mkFiniteInner (DomainInt name []) = do fr <- nextName "fin" to <- nextName "fin" return - ( DomainInt [RangeBounded (fromName fr) (fromName to)] + ( DomainInt name [RangeBounded (fromName fr) (fromName to)] , [fr, to] , \ constants -> do logDebug $ "mkFiniteInner DomainInt" <+> vcat (map pretty constants) @@ -378,20 +378,20 @@ mkFiniteInner (DomainInt []) = do , (to, ConstantInt (maximum0 ints)) ] ) -mkFiniteInner (DomainInt [RangeLowerBounded low]) = do +mkFiniteInner (DomainInt name [RangeLowerBounded low]) = do new <- nextName "fin" return - ( DomainInt [RangeBounded low (fromName new)] + ( DomainInt name [RangeBounded low (fromName new)] , [new] , \ constants -> do logDebug $ "mkFiniteInner DomainInt" <+> vcat (map pretty constants) ints <- failToUserError $ mapM viewConstantInt constants return [ (new, ConstantInt (maximum0 ints)) ] ) -mkFiniteInner (DomainInt [RangeUpperBounded upp]) = do +mkFiniteInner (DomainInt name [RangeUpperBounded upp]) = do new <- nextName "fin" return - ( DomainInt [RangeBounded (fromName new) upp] + ( DomainInt name [RangeBounded (fromName new) upp] , [new] , \ constants -> do logDebug $ "mkFiniteInner DomainInt" <+> vcat (map pretty constants) diff --git a/src/Conjure/Process/ModelStrengthening.hs b/src/Conjure/Process/ModelStrengthening.hs index 8db8944b58..e2bd0ebe88 100644 --- a/src/Conjure/Process/ModelStrengthening.hs +++ b/src/Conjure/Process/ModelStrengthening.hs @@ -781,7 +781,7 @@ forAllIneqToIneqSum _ (_, cs) = do partsAreNumeric (_, _, e1, e2) = (&&) <$> domainIsNumeric e1 <*> domainIsNumeric e2 domainIsNumeric e = case domainOf e of Right DomainInt{} -> return True - Right (DomainAny _ TypeInt) -> return True + Right (DomainAny _ (TypeInt _)) -> return True _ -> return False -- Replace the forAll with the (in)equality between sums mkConstraint :: (Generator, Maybe ExpressionZ, Expression, Expression) -> Maybe ExpressionZ diff --git a/src/Conjure/Process/Sanity.hs b/src/Conjure/Process/Sanity.hs index ed1b8b5369..bfa704811c 100644 --- a/src/Conjure/Process/Sanity.hs +++ b/src/Conjure/Process/Sanity.hs @@ -37,7 +37,7 @@ sanityChecks model = do -- check for binary relation attrobutes checkDomain :: MonadWriter [Doc] m => Bool -> Maybe Statement -> Domain () Expression -> m () checkDomain checkForInfinity mstmt domain = case domain of - DomainInt rs | checkForInfinity && isInfinite rs -> recordErr + DomainInt _ rs | checkForInfinity && isInfinite rs -> recordErr [ "Infinite integer domain." , "Context:" <++> maybe (pretty domain) pretty mstmt ] diff --git a/src/Conjure/Process/Unnameds.hs b/src/Conjure/Process/Unnameds.hs index f97970eebc..92e113155c 100644 --- a/src/Conjure/Process/Unnameds.hs +++ b/src/Conjure/Process/Unnameds.hs @@ -17,7 +17,7 @@ removeUnnamedsFromModel model = do statements' <- forM (mStatements model) $ \ st -> case st of Declaration (LettingDomainDefnUnnamed name size) -> do - let outDomain = mkDomainIntB 1 size + let outDomain = mkDomainIntBNamed name 1 size return $ Declaration $ Letting name $ Domain outDomain _ -> return st return model { mStatements = statements' } diff --git a/src/Conjure/Representations/Function/Function1D.hs b/src/Conjure/Representations/Function/Function1D.hs index 444023b012..5fe758b50c 100644 --- a/src/Conjure/Representations/Function/Function1D.hs +++ b/src/Conjure/Representations/Function/Function1D.hs @@ -178,5 +178,5 @@ domainValues :: (MonadFail m, Pretty r) => Domain r Constant -> m [Constant] domainValues dom = case dom of DomainBool -> return [ConstantBool False, ConstantBool True] - DomainInt rs -> map ConstantInt <$> valuesInIntDomain rs + DomainInt Nothing rs -> map ConstantInt <$> valuesInIntDomain rs _ -> fail ("domainValues, not supported:" <+> pretty dom) diff --git a/src/Conjure/Representations/MSet/ExplicitWithRepetition.hs b/src/Conjure/Representations/MSet/ExplicitWithRepetition.hs index f45d669785..826137e68b 100644 --- a/src/Conjure/Representations/MSet/ExplicitWithRepetition.hs +++ b/src/Conjure/Representations/MSet/ExplicitWithRepetition.hs @@ -49,7 +49,7 @@ msetExplicitWithRepetition = Representation chck downD structuralCons downC up case attrs of MSetAttr (SizeAttr_Size size) _ -> do let indexDomain = mkDomainIntB 1 size - let flagDomain = defRepr $ DomainInt [RangeSingle size] + let flagDomain = defRepr $ DomainInt Nothing [RangeSingle size] return (indexDomain, flagDomain) _ -> do maxSize <- getMaxSize attrs innerDomain @@ -139,7 +139,7 @@ msetExplicitWithRepetition = Representation chck downD structuralCons downC up ) = case attrs of MSetAttr (SizeAttr_Size size) _ -> do let indexDomain = mkDomainIntB 1 size - let flagDomain = DomainInt [RangeSingle size] + let flagDomain = DomainInt Nothing [RangeSingle size] return $ Just [ ( nameFlag domain name diff --git a/src/Conjure/Representations/Partition/Occurrence.hs b/src/Conjure/Representations/Partition/Occurrence.hs index bd0db5e54e..611d68b91e 100644 --- a/src/Conjure/Representations/Partition/Occurrence.hs +++ b/src/Conjure/Representations/Partition/Occurrence.hs @@ -63,24 +63,24 @@ partitionOccurrence = Representation chck downD structuralCons downC up [ -- number of active parts ( nameNumParts domain name - , DomainInt [RangeBounded 1 maxNumParts] + , DomainInt Nothing [RangeBounded 1 maxNumParts] ) -- for each element, the part it belongs to , ( nameWhichPart domain name , DomainMatrix (forgetRepr innerDomain) - (DomainInt [RangeBounded 1 maxNumParts]) + (DomainInt Nothing [RangeBounded 1 maxNumParts]) ) -- for each part, number of elements in the part , ( namePartSizes domain name , DomainMatrix - (DomainInt [RangeBounded 1 maxNumParts]) - (DomainInt [RangeBounded 0 maxPartSizes]) + (DomainInt Nothing [RangeBounded 1 maxNumParts]) + (DomainInt Nothing [RangeBounded 0 maxPartSizes]) ) -- wtf was this? , ( nameFirstIndex domain name , DomainMatrix - (DomainInt [RangeBounded 1 maxNumParts]) + (DomainInt Nothing [RangeBounded 1 maxNumParts]) innerDomain -- dontCare if not used ) ] @@ -246,12 +246,12 @@ partitionOccurrence = Representation chck downD structuralCons downC up (forgetRepr innerDomain) (map (ConstantInt . fst) whichPartValInside)) partSizesVal = ConstantAbstract (AbsLitMatrix - (DomainInt [RangeBounded 1 maxNumParts']) + (DomainInt Nothing [RangeBounded 1 maxNumParts']) (map (ConstantInt . genericLength) vals ++ replicate (fromInteger (maxNumParts - genericLength vals)) (ConstantInt 0))) firstIndexVal = ConstantAbstract (AbsLitMatrix - (DomainInt [RangeBounded 1 maxNumParts']) + (DomainInt Nothing [RangeBounded 1 maxNumParts']) ([ case lookup p whichPartValInside of Nothing -> bug $ vcat [ "Not found:" <+> pretty p , "Inside:" <+> prettyList id "," whichPartValInside diff --git a/src/Conjure/Representations/Partition/PartitionAsSet.hs b/src/Conjure/Representations/Partition/PartitionAsSet.hs index 2415b7a442..c20fc7302d 100644 --- a/src/Conjure/Representations/Partition/PartitionAsSet.hs +++ b/src/Conjure/Representations/Partition/PartitionAsSet.hs @@ -79,7 +79,7 @@ partitionAsSet dispatch reprOptions useLevels = Representation chck downD struct exactlyOnce rel = do innerType <- typeOf innerDomain - if innerType `typeUnify` TypeInt + if innerType `typeUnify` TypeInt Nothing then do (iPat, i) <- quantifiedVar (jPat, j) <- quantifiedVar diff --git a/src/Conjure/Representations/Primitive.hs b/src/Conjure/Representations/Primitive.hs index 8e99cdee0f..5d1d2a8f22 100644 --- a/src/Conjure/Representations/Primitive.hs +++ b/src/Conjure/Representations/Primitive.hs @@ -14,8 +14,8 @@ primitive = Representation { rCheck = \ _ domain -> return $ case domain of DomainBool -> [DomainBool] - DomainIntE x -> [DomainIntE x] - DomainInt rs -> [DomainInt rs] + DomainIntE name x -> [DomainIntE name x] + DomainInt name rs -> [DomainInt name rs] _ -> [] , rDownD = const $ return Nothing , rStructural = \ _ _ _ -> return (\ _ -> return [] ) diff --git a/src/Conjure/Representations/Sequence/ExplicitBounded.hs b/src/Conjure/Representations/Sequence/ExplicitBounded.hs index 12d0838e0c..f10462bd47 100644 --- a/src/Conjure/Representations/Sequence/ExplicitBounded.hs +++ b/src/Conjure/Representations/Sequence/ExplicitBounded.hs @@ -40,11 +40,11 @@ sequenceExplicitBounded = Representation chck downD structuralCons downC up innerDomain)) = return $ Just [ ( nameMarker domain name - , DomainInt [RangeBounded size size] + , DomainInt Nothing [RangeBounded size size] ) , ( nameValues domain name , DomainMatrix - (DomainInt [RangeBounded 1 size]) + (DomainInt Nothing [RangeBounded 1 size]) innerDomain ) ] downD (name, domain@(DomainSequence @@ -54,11 +54,11 @@ sequenceExplicitBounded = Representation chck downD structuralCons downC up maxSize <- getMaxSize sizeAttr return $ Just [ ( nameMarker domain name - , DomainInt [RangeBounded 0 maxSize] + , DomainInt Nothing [RangeBounded 0 maxSize] ) , ( nameValues domain name , DomainMatrix - (DomainInt [RangeBounded 1 maxSize]) + (DomainInt Nothing [RangeBounded 1 maxSize]) innerDomain ) ] downD _ = na "{downD} ExplicitBounded" @@ -67,7 +67,7 @@ sequenceExplicitBounded = Representation chck downD structuralCons downC up structuralCons f downX1 (DomainSequence Sequence_ExplicitBounded (SequenceAttr (SizeAttr_Size size) jectivityAttr) innerDomain) = do let injectiveCons values = do innerType <- typeOf innerDomain - if typeUnify innerType TypeInt + if typeUnify innerType (TypeInt Nothing) then do return $ return $ -- list [essence| allDiff(&values) |] @@ -193,12 +193,12 @@ sequenceExplicitBounded = Representation chck downD structuralCons downC up ) = return $ Just [ ( nameMarker domain name - , DomainInt [RangeBounded size size] + , DomainInt Nothing [RangeBounded size size] , ConstantInt (genericLength constants) ) , ( nameValues domain name - , DomainMatrix (DomainInt [RangeBounded 1 size]) innerDomain - , ConstantAbstract $ AbsLitMatrix (DomainInt [RangeBounded 1 size]) constants + , DomainMatrix (DomainInt Nothing [RangeBounded 1 size]) innerDomain + , ConstantAbstract $ AbsLitMatrix (DomainInt Nothing [RangeBounded 1 size]) constants ) ] downC ( name diff --git a/src/Conjure/Representations/Set/Explicit.hs b/src/Conjure/Representations/Set/Explicit.hs index 6881886334..66c2996244 100644 --- a/src/Conjure/Representations/Set/Explicit.hs +++ b/src/Conjure/Representations/Set/Explicit.hs @@ -27,7 +27,7 @@ setExplicit = Representation chck downD structuralCons downC up downD (name, domain@(DomainSet Set_Explicit (SetAttr (SizeAttr_Size size)) innerDomain)) = return $ Just [ ( outName domain name , DomainMatrix - (DomainInt [RangeBounded 1 size]) + (DomainInt Nothing [RangeBounded 1 size]) innerDomain ) ] downD _ = na "{downD} Explicit" diff --git a/src/Conjure/Representations/Set/ExplicitVarSizeWithDummy.hs b/src/Conjure/Representations/Set/ExplicitVarSizeWithDummy.hs index 22e28a9235..87a20cdff2 100644 --- a/src/Conjure/Representations/Set/ExplicitVarSizeWithDummy.hs +++ b/src/Conjure/Representations/Set/ExplicitVarSizeWithDummy.hs @@ -32,11 +32,11 @@ setExplicitVarSizeWithDummy = Representation chck downD structuralCons downC up _ -> domainSizeOf innerDomain calcDummyDomain :: Pretty r => Domain r Expression -> Domain r Expression - calcDummyDomain (DomainInt [RangeBounded lb ub]) = - DomainInt [RangeBounded lb [essence| &ub + 1 |]] - calcDummyDomain dom@(DomainInt ranges) = + calcDummyDomain (DomainInt name [RangeBounded lb ub]) = + DomainInt name [RangeBounded lb [essence| &ub + 1 |]] + calcDummyDomain dom@(DomainInt name ranges) = let dummyElem = calcDummyElem dom - in DomainInt (ranges ++ [RangeSingle dummyElem]) + in DomainInt name (ranges ++ [RangeSingle dummyElem]) calcDummyDomain dom = bug ("ExplicitVarSizeWithDummy.calcDummyDomain" <+> pretty dom) calcDummyElem :: Pretty r => Domain r Expression -> Expression @@ -45,8 +45,8 @@ setExplicitVarSizeWithDummy = Representation chck downD structuralCons downC up in [essence| &theMax + 1 |] calcDummyElemC :: Pretty r => Domain r Constant -> Constant - calcDummyElemC (DomainInt []) = bug "ExplicitVarSizeWithDummy.calcDummyElemC []" - calcDummyElemC (DomainInt rs) = ConstantInt $ + calcDummyElemC (DomainInt _ []) = bug "ExplicitVarSizeWithDummy.calcDummyElemC []" + calcDummyElemC (DomainInt _ rs) = ConstantInt $ 1 + maximum [ i | r <- rs , i <- case r of @@ -63,7 +63,7 @@ setExplicitVarSizeWithDummy = Representation chck downD structuralCons downC up return $ Just [ ( outName domain name , DomainMatrix - (DomainInt [RangeBounded 1 maxSize]) + (DomainInt Nothing [RangeBounded 1 maxSize]) domainWithDummy ) ] downD _ = na "{downD} ExplicitVarSizeWithDummy" diff --git a/src/Conjure/Representations/Set/Occurrence.hs b/src/Conjure/Representations/Set/Occurrence.hs index 1c1bcbb85a..523106c8fe 100644 --- a/src/Conjure/Representations/Set/Occurrence.hs +++ b/src/Conjure/Representations/Set/Occurrence.hs @@ -48,7 +48,7 @@ setOccurrence = Representation chck downD structuralCons downC up -- | If value is in the set then that value's index maps to a bool downC :: TypeOf_DownC m downC ( name - , domain@(DomainSet Set_Occurrence _attrs innerDomain@(DomainInt intRanges)) + , domain@(DomainSet Set_Occurrence _attrs innerDomain@(DomainInt _ intRanges)) , ConstantAbstract (AbsLitSet constants) ) = do innerDomainVals <- valuesInIntDomain intRanges @@ -66,7 +66,7 @@ setOccurrence = Representation chck downD structuralCons downC up -- | Reversal of downC - if innerDom value zips with matrix true then it's in up :: TypeOf_Up m - up ctxt (name, domain@(DomainSet _ _ (DomainInt intRanges)))= + up ctxt (name, domain@(DomainSet _ _ (DomainInt _ intRanges)))= case lookup (outName domain name) ctxt of Just constantMatrix -> case viewConstantMatrix constantMatrix of diff --git a/src/Conjure/Rules/BubbleUp.hs b/src/Conjure/Rules/BubbleUp.hs index ecd78e20d8..d8f30a3816 100644 --- a/src/Conjure/Rules/BubbleUp.hs +++ b/src/Conjure/Rules/BubbleUp.hs @@ -51,7 +51,7 @@ rule_ToMultiply_HeadOfIntComprehension :: Rule rule_ToMultiply_HeadOfIntComprehension = "bubble-to-multiply-HeadOfIntComprehension" `namedRule` theRule where theRule p = do (_, mk, Comprehension (WithLocals x (DefinednessConstraints cons)) gocs) <- match opReducer p - TypeInt <- typeOf x + TypeInt _ <- typeOf x let conjunct = make opAnd (fromList cons) let x' = [essence| &x * toInt(&conjunct) |] let out = mk $ Comprehension x' gocs diff --git a/src/Conjure/Rules/DontCare.hs b/src/Conjure/Rules/DontCare.hs index a8da5d9233..e8ab12ffdf 100644 --- a/src/Conjure/Rules/DontCare.hs +++ b/src/Conjure/Rules/DontCare.hs @@ -21,18 +21,18 @@ rule_Int :: Rule rule_Int = "dontCare-int" `namedRule` theRule where theRule p = do x <- match opDontCare p - TypeInt <- typeOf x + TypeInt _ <- typeOf x xDomain <- domainOf x let raiseBug = bug ("dontCare on domain:" <+> pretty xDomain) let val = case xDomain of - DomainInt [] -> raiseBug - DomainInt (r:_) -> case r of + DomainInt _ [] -> raiseBug + DomainInt _ (r:_) -> case r of RangeOpen -> raiseBug RangeSingle v -> v RangeLowerBounded v -> v RangeUpperBounded v -> v RangeBounded v _ -> v - DomainIntE v -> [essence| min(&v) |] + DomainIntE _ v -> [essence| min(&v) |] _ -> raiseBug return ( "dontCare value for this integer is" <+> pretty val @@ -122,18 +122,18 @@ handleDontCares p = typX <- typeOf x case typX of TypeBool -> return (make opEq x (fromBool False)) - TypeInt -> do + TypeInt _ -> do domX <- domainOf x let raiseBug = bug ("dontCare on domain:" <+> pretty domX) let val = case domX of - DomainInt [] -> raiseBug - DomainInt (r:_) -> case r of + DomainInt _ [] -> raiseBug + DomainInt _ (r:_) -> case r of RangeOpen -> raiseBug RangeSingle v -> v RangeLowerBounded v -> v RangeUpperBounded v -> v RangeBounded v _ -> v - DomainIntE v -> [essence| min(&v) |] + DomainIntE _ v -> [essence| min(&v) |] _ -> raiseBug return $ make opEq x val TypeTuple{} -> do diff --git a/src/Conjure/Rules/Horizontal/Function.hs b/src/Conjure/Rules/Horizontal/Function.hs index 4247975078..166f9355b4 100644 --- a/src/Conjure/Rules/Horizontal/Function.hs +++ b/src/Conjure/Rules/Horizontal/Function.hs @@ -17,8 +17,8 @@ rule_Comprehension_Literal = "function-comprehension-literal" `namedRule` theRul _ -> na "rule_Comprehension_Literal" (TypeFunction fr to, elems) <- match functionLiteral expr let outLiteral = make matrixLiteral - (TypeMatrix TypeInt (TypeTuple [fr,to])) - (DomainInt [RangeBounded 1 (fromInt (genericLength elems))]) + (TypeMatrix (TypeInt Nothing) (TypeTuple [fr,to])) + (DomainInt Nothing [RangeBounded 1 (fromInt (genericLength elems))]) [ AbstractLiteral (AbsLitTuple [a,b]) | (a,b) <- elems ] @@ -592,7 +592,7 @@ rule_Image_Int = "function-image-int" `namedRule` theRule where case match opRestrict func of Nothing -> return () Just{} -> na "rule_Image_Int" -- do not use this rule for restricted functions - TypeFunction _ TypeInt <- typeOf func + TypeFunction _ (TypeInt Nothing) <- typeOf func return ( "Function image, int." , do @@ -612,7 +612,7 @@ rule_Image_IntMatrixIndexed = "function-image-IntMatrixIndexed" `namedRule` theR theRule p = do (matrix, indices) <- match opMatrixIndexing p (func, arg) <- match opImage matrix - TypeFunction _ (TypeMatrix _ TypeInt) <- typeOf func + TypeFunction _ (TypeMatrix _ (TypeInt Nothing)) <- typeOf func return ( "Function image, matrix of int." , do @@ -636,7 +636,7 @@ rule_Image_IntTupleIndexed = "function-image-IntTupleIndexed" `namedRule` theRul TypeFunction _ (TypeTuple ts) <- typeOf func iInt <- match constantInt index case atMay ts (fromInteger (iInt-1)) of - Just TypeInt -> return () + Just (TypeInt Nothing) -> return () _ -> na "rule_Image_IntTupleIndexed" return ( "Function image, tuple of int." @@ -796,7 +796,7 @@ rule_DefinedOrRange_Union = "function-DefinedOrRange-union" `namedRule` theRule return ( "Horizontal rule for function union" , return $ make opFlatten $ AbstractLiteral $ AbsLitMatrix - (DomainInt [RangeBounded 1 2]) + (DomainInt Nothing [RangeBounded 1 2]) [ Comprehension body $ gocBefore ++ [ Generator (GenInExpr pat mkx) ] diff --git a/src/Conjure/Rules/Horizontal/MSet.hs b/src/Conjure/Rules/Horizontal/MSet.hs index f54397693e..5965092d09 100644 --- a/src/Conjure/Rules/Horizontal/MSet.hs +++ b/src/Conjure/Rules/Horizontal/MSet.hs @@ -13,8 +13,8 @@ rule_Comprehension_Literal = "mset-comprehension-literal" `namedRule` theRule wh _ -> na "rule_Comprehension_Literal" (TypeMSet tau, elems) <- match msetLiteral expr let outLiteral = make matrixLiteral - (TypeMatrix TypeInt tau) - (DomainInt [RangeBounded 1 (fromInt (genericLength elems))]) + (TypeMatrix (TypeInt Nothing) tau) + (DomainInt Nothing [RangeBounded 1 (fromInt (genericLength elems))]) elems let upd val old = lambdaToFunction pat old val return @@ -38,7 +38,7 @@ rule_Comprehension_ToSet_Literal = "mset-comprehension-toSet-literal" `namedRule mset <- match opToSet expr (TypeMSet tau, elems) <- match msetLiteral mset let outLiteralDomain = mkDomainIntB 1 (fromInt $ genericLength elems) - let outLiteral = make matrixLiteral (TypeMatrix TypeInt tau) outLiteralDomain elems + let outLiteral = make matrixLiteral (TypeMatrix (TypeInt Nothing) tau) outLiteralDomain elems let upd val old = lambdaToFunction pat old val return ( "Comprehension on toSet of mset literals" @@ -185,7 +185,7 @@ rule_DotLeq = "mset-DotLeq" `namedRule` theRule where rule_MaxMin :: Rule rule_MaxMin = "mset-max-min" `namedRule` theRule where theRule [essence| max(&s) |] = do - TypeMSet TypeInt <- typeOf s + TypeMSet (TypeInt Nothing) <- typeOf s return ( "Horizontal rule for mset max" , do @@ -193,7 +193,7 @@ rule_MaxMin = "mset-max-min" `namedRule` theRule where return [essence| max([&i | &iPat <- &s]) |] ) theRule [essence| min(&s) |] = do - TypeMSet TypeInt <- typeOf s + TypeMSet (TypeInt Nothing) <- typeOf s return ( "Horizontal rule for mset min" , do diff --git a/src/Conjure/Rules/Horizontal/Partition.hs b/src/Conjure/Rules/Horizontal/Partition.hs index 63b17ac1a3..b1a23425d9 100644 --- a/src/Conjure/Rules/Horizontal/Partition.hs +++ b/src/Conjure/Rules/Horizontal/Partition.hs @@ -13,8 +13,8 @@ rule_Comprehension_Literal = "partition-comprehension-literal" `namedRule` theRu _ -> na "rule_Comprehension_Literal" (TypePartition tau, elems) <- match partitionLiteral p let outLiteral = make matrixLiteral - (TypeMatrix TypeInt (TypeSet tau)) - (DomainInt [RangeBounded 1 (fromInt (genericLength elems))]) + (TypeMatrix (TypeInt Nothing) (TypeSet tau)) + (DomainInt Nothing [RangeBounded 1 (fromInt (genericLength elems))]) [ AbstractLiteral (AbsLitSet e) | e <- elems ] diff --git a/src/Conjure/Rules/Horizontal/Permutation.hs b/src/Conjure/Rules/Horizontal/Permutation.hs index f7994eb83d..3fedf9b3f5 100644 --- a/src/Conjure/Rules/Horizontal/Permutation.hs +++ b/src/Conjure/Rules/Horizontal/Permutation.hs @@ -31,8 +31,8 @@ rule_Permute_Literal = "permutation-permute-literal{AsFunction}" `namedRule` the let prmTup pt = take (length pt) $ zip (cycle pt) (drop 1 $ cycle pt) permTups = join $ prmTup <$> elems let outLiteral = make matrixLiteral - (TypeMatrix TypeInt (TypeTuple [inner,inner])) - (DomainInt [RangeBounded 1 (fromInt (genericLength permTups))]) + (TypeMatrix (TypeInt Nothing) (TypeTuple [inner,inner])) + (DomainInt Nothing [RangeBounded 1 (fromInt (genericLength permTups))]) [ AbstractLiteral (AbsLitTuple [a,b]) | (a,b) <- permTups ] diff --git a/src/Conjure/Rules/Horizontal/Relation.hs b/src/Conjure/Rules/Horizontal/Relation.hs index 06d17f8a55..5b747900a9 100644 --- a/src/Conjure/Rules/Horizontal/Relation.hs +++ b/src/Conjure/Rules/Horizontal/Relation.hs @@ -13,8 +13,8 @@ rule_Comprehension_Literal = "relation-comprehension-literal" `namedRule` theRul _ -> na "rule_Comprehension_Literal" (TypeRelation taus, elems) <- match relationLiteral expr let outLiteral = make matrixLiteral - (TypeMatrix TypeInt (TypeTuple taus)) - (DomainInt [RangeBounded 1 (fromInt (genericLength elems))]) + (TypeMatrix (TypeInt Nothing) (TypeTuple taus)) + (DomainInt Nothing [RangeBounded 1 (fromInt (genericLength elems))]) [ AbstractLiteral (AbsLitTuple row) | row <- elems ] diff --git a/src/Conjure/Rules/Horizontal/Sequence.hs b/src/Conjure/Rules/Horizontal/Sequence.hs index f3c268594f..2f4ec70ac4 100644 --- a/src/Conjure/Rules/Horizontal/Sequence.hs +++ b/src/Conjure/Rules/Horizontal/Sequence.hs @@ -13,8 +13,8 @@ rule_Comprehension_Literal = "sequence-comprehension-literal" `namedRule` theRul _ -> na "rule_Comprehension_Literal" (TypeSequence t, elems) <- match sequenceLiteral expr let outLiteral = make matrixLiteral - (TypeMatrix TypeInt t) - (DomainInt [RangeBounded 1 (fromInt (genericLength elems))]) + (TypeMatrix (TypeInt Nothing) t) + (DomainInt Nothing [RangeBounded 1 (fromInt (genericLength elems))]) elems let upd val old = lambdaToFunction pat old val return @@ -60,7 +60,7 @@ rule_Image_Literal_Int :: Rule rule_Image_Literal_Int = "sequence-image-literal-int" `namedRule` theRule where theRule p = do (func, arg) <- match opImage p - (TypeSequence TypeInt, elems) <- match sequenceLiteral func + (TypeSequence (TypeInt Nothing), elems) <- match sequenceLiteral func return ( "Image of sequence literal" , return $ @@ -464,7 +464,7 @@ rule_Image_Int = "sequence-image-int" `namedRule` theRule where case match opRestrict func of Nothing -> return () Just{} -> na "rule_Image_Int" -- do not use this rule for restricted sequences - TypeSequence TypeInt <- typeOf func + TypeSequence (TypeInt Nothing) <- typeOf func return (func, arg) case try of Nothing -> return (const ch) -- do not fail if a child is not of proper form diff --git a/src/Conjure/Rules/Horizontal/Set.hs b/src/Conjure/Rules/Horizontal/Set.hs index 10b6a212f6..c4fdfb50e7 100644 --- a/src/Conjure/Rules/Horizontal/Set.hs +++ b/src/Conjure/Rules/Horizontal/Set.hs @@ -13,8 +13,8 @@ rule_Comprehension_Literal = "set-comprehension-literal" `namedRule` theRule whe _ -> na "rule_Comprehension_Literal" (TypeSet tau, elems) <- match setLiteral expr let outLiteral = make matrixLiteral - (TypeMatrix TypeInt tau) - (DomainInt [RangeBounded 1 (fromInt (genericLength elems))]) + (TypeMatrix (TypeInt Nothing) tau) + (DomainInt Nothing [RangeBounded 1 (fromInt (genericLength elems))]) elems let upd val old = lambdaToFunction pat old val return @@ -205,7 +205,7 @@ rule_Union = "set-union" `namedRule` theRule where return ( "Horizontal rule for set union" , return $ make opFlatten $ AbstractLiteral $ AbsLitMatrix - (DomainInt [RangeBounded 1 2]) + (DomainInt Nothing [RangeBounded 1 2]) [ Comprehension body $ gocBefore ++ [ Generator (GenInExpr pat (mkModifier x)) ] @@ -313,7 +313,7 @@ rule_PowerSet_Comprehension = "set-powerSet-comprehension" `namedRule` theRule w rule_MaxMin :: Rule rule_MaxMin = "set-max-min" `namedRule` theRule where theRule [essence| max(&s) |] = do - TypeSet TypeInt <- typeOf s + TypeSet (TypeInt Nothing) <- typeOf s return ( "Horizontal rule for set max" , do @@ -321,7 +321,7 @@ rule_MaxMin = "set-max-min" `namedRule` theRule where return [essence| max([&i | &iPat <- &s]) |] ) theRule [essence| min(&s) |] = do - TypeSet TypeInt <- typeOf s + TypeSet (TypeInt Nothing) <- typeOf s return ( "Horizontal rule for set min" , do @@ -386,16 +386,16 @@ rule_CardViaFreq = "set-card-via-freq" `namedRule` theRule where rule_Param_MinOfSet :: Rule rule_Param_MinOfSet = "param-min-of-set" `namedRule` theRule where theRule [essence| min(&s) |] = do - TypeSet TypeInt <- typeOf s + TypeSet (TypeInt Nothing) <- typeOf s unless (categoryOf s == CatParameter) $ na "rule_Param_MinOfSet" DomainSet _ _ inner <- domainOf s case inner of - DomainInt rs | isInfinite rs -> na "rule_Param_MaxOfSet" + DomainInt Nothing rs | isInfinite rs -> na "rule_Param_MaxOfSet" _ -> return () return ( "min of a parameter set" , case inner of - DomainInt [RangeBounded l _] -> return l + DomainInt Nothing [RangeBounded l _] -> return l _ -> do (iPat, i) <- quantifiedVar return [essence| min([ &i | &iPat : &inner ]) |] @@ -406,16 +406,16 @@ rule_Param_MinOfSet = "param-min-of-set" `namedRule` theRule where rule_Param_MaxOfSet :: Rule rule_Param_MaxOfSet = "param-max-of-set" `namedRule` theRule where theRule [essence| max(&s) |] = do - TypeSet TypeInt <- typeOf s + TypeSet (TypeInt Nothing) <- typeOf s unless (categoryOf s == CatParameter) $ na "rule_Param_MaxOfSet" DomainSet _ _ inner <- domainOf s case inner of - DomainInt rs | isInfinite rs -> na "rule_Param_MaxOfSet" + DomainInt Nothing rs | isInfinite rs -> na "rule_Param_MaxOfSet" _ -> return () return ( "max of a parameter set" , case inner of - DomainInt [RangeBounded _ u] -> return u + DomainInt Nothing [RangeBounded _ u] -> return u _ -> do (iPat, i) <- quantifiedVar return [essence| max([ &i | &iPat : &inner ]) |] @@ -426,7 +426,7 @@ rule_Param_MaxOfSet = "param-max-of-set" `namedRule` theRule where rule_Param_Card :: Rule rule_Param_Card = "param-card-of-set" `namedRule` theRule where theRule [essence| |&s| |] = do - TypeSet TypeInt <- typeOf s + TypeSet (TypeInt Nothing) <- typeOf s unless (categoryOf s == CatParameter) $ na "rule_Param_Card" DomainSet _ (SetAttr (SizeAttr_Size n)) _ <- domainOf s return diff --git a/src/Conjure/Rules/TildeOrdering.hs b/src/Conjure/Rules/TildeOrdering.hs index 6fa609a8a0..9b3ab97bf5 100644 --- a/src/Conjure/Rules/TildeOrdering.hs +++ b/src/Conjure/Rules/TildeOrdering.hs @@ -11,8 +11,8 @@ rule_BoolInt = "tildeOrd-bool-int" `namedRule` theRule where tyx <- typeOf x tyy <- typeOf y case mostDefined [tyx, tyy] of - TypeBool -> return () - TypeInt -> return () + TypeBool -> return () + TypeInt _ -> return () _ -> na "rule_BoolInt" return ( "~< to <" @@ -22,8 +22,8 @@ rule_BoolInt = "tildeOrd-bool-int" `namedRule` theRule where tyx <- typeOf x tyy <- typeOf y case mostDefined [tyx, tyy] of - TypeBool -> return () - TypeInt -> return () + TypeBool -> return () + TypeInt _ -> return () _ -> na "rule_BoolInt" return ( "~<= to <=" diff --git a/src/Conjure/Rules/Vertical/Matrix.hs b/src/Conjure/Rules/Vertical/Matrix.hs index db4a730120..02e311d773 100644 --- a/src/Conjure/Rules/Vertical/Matrix.hs +++ b/src/Conjure/Rules/Vertical/Matrix.hs @@ -4,7 +4,7 @@ module Conjure.Rules.Vertical.Matrix where import Conjure.Rules.Import -import Conjure.Rules.Vertical.Tuple ( decomposeLexLt, decomposeLexLeq, decomposeLexDotLt, decomposeLexDotLeq, decomposeLexDotLeqSym ) +import Conjure.Rules.Vertical.Tuple ( decomposeLexLt, decomposeLexLeq, decomposeLexDotLt, decomposeLexDotLeq) rule_Comprehension_Literal :: Rule @@ -15,7 +15,7 @@ rule_Comprehension_Literal = "matrix-comprehension-literal" `namedRule` theRule _ -> na "rule_Comprehension_Literal" (_, _index, elems) <- match matrixLiteral expr tyInner <- typeOf body - let ty = TypeMatrix TypeInt tyInner + let ty = TypeMatrix (TypeInt Nothing) tyInner return ( "Vertical rule for matrix-comprehension on matrix literal" , return $ if null elems @@ -377,29 +377,30 @@ rule_Matrix_Lt_Primitive = "matrix-Lt-primitive" `namedRule` theRule where ) -rule_Matrix_Leq_Primitive :: Rule -rule_Matrix_Leq_Primitive = "matrix-Leq-primitive" `namedRule` theRule where - theRule [essence| &x .<= permute(&perm, &y) |] = do - tx@TypeMatrix{} <- typeOf x -- TODO: check if x and y have the same arity +-- TODO need to permute on the indices too +rule_Matrix_Permute :: Rule +rule_Matrix_Permute = "matrix-permute" `namedRule` theRule where + theRule [essence| permute(&perm, &y) |] = do ty@(TypeMatrix _ yinner) <- typeOf y (TypePermutation pinner) <- typeOf perm if typesUnify [yinner, pinner] then do - unless (isPrimitiveType tx) $ fail ("not a primitive type:" <+> pretty tx) unless (isPrimitiveType ty) $ fail ("not a primitive type:" <+> pretty ty) - x' <- flattenIfNeeded x y' <- flattenIfNeeded y - dy'@(DomainMatrix dyindex _) <- domainOf y' + DomainMatrix dyindex dyinner <- domainOf y' + DomainPermutation _ _ dpinner <- domainOf perm + dun <- domainUnion dpinner dyinner return - ( "Horizontal rule for matrix <=" + ( "Horizontal rule for permute matrix" , do (dPat, d) <- quantifiedVar (pyName, py) <- auxiliaryVar return $ WithLocals - [essence| &x' <=lex &py |] + [essence| &py |] (AuxiliaryVars --TODO need union of permutation and dy domains - [ Declaration (FindOrGiven LocalFind pyName dy') + [ Declaration (FindOrGiven LocalFind pyName + (DomainMatrix dyindex dun)) , SuchThat [ [essence| forAll &dPat : &dyindex . @@ -409,7 +410,46 @@ rule_Matrix_Leq_Primitive = "matrix-Leq-primitive" `namedRule` theRule where ] ) ) - else na "rule_Matrix_Leq_Symbreak_Primitive" + else if yinner `containsType` pinner + then error "rule_Matrix_Permute recursion not defined yet" + else return ( "horixontal rule for permute matrix no type match" + , return [essence| &y |] + ) + theRule _ = na "rule_Matrix_Permute" + +rule_Matrix_Leq_Primitive :: Rule +rule_Matrix_Leq_Primitive = "matrix-Leq-primitive" `namedRule` theRule where +-- theRule [essence| &x .<= permute(&perm, &y) |] = do +-- tx@TypeMatrix{} <- typeOf x -- TODO: check if x and y have the same arity +-- ty@(TypeMatrix _ yinner) <- typeOf y +-- (TypePermutation pinner) <- typeOf perm +-- if typesUnify [yinner, pinner] +-- then do +-- unless (isPrimitiveType tx) $ fail ("not a primitive type:" <+> pretty tx) +-- unless (isPrimitiveType ty) $ fail ("not a primitive type:" <+> pretty ty) +-- x' <- flattenIfNeeded x +-- y' <- flattenIfNeeded y +-- dy'@(DomainMatrix dyindex _) <- domainOf y' +-- return +-- ( "Horizontal rule for matrix <=" +-- , do +-- (dPat, d) <- quantifiedVar +-- (pyName, py) <- auxiliaryVar +-- return $ WithLocals +-- [essence| &x' <=lex &py |] +-- (AuxiliaryVars +-- --TODO need union of permutation and dy domains +-- [ Declaration (FindOrGiven LocalFind pyName dy') +-- , SuchThat +-- [ [essence| +-- forAll &dPat : &dyindex . +-- &py[&d] = permute(&perm,&y'[&d]) +-- |] +-- ] +-- ] +-- ) +-- ) +-- else na "rule_Matrix_Leq_Symbreak_Primitive" theRule p = do (x,y) <- case (match opLeq p, match opDotLeq p) of (Just a, _) -> return a @@ -477,18 +517,18 @@ rule_Matrix_DotLt_Decompose = "matrix-DotLt-tuple" `namedRule` theRule where rule_Matrix_DotLeq_Decompose :: Rule rule_Matrix_DotLeq_Decompose = "matrix-DotLeq-tuple" `namedRule` theRule where - theRule p@[essence| &x .<= permute(&perm, &y) |] = do - tx@TypeMatrix{} <- typeOf x -- TODO: check matrix index & tuple arity - ty@TypeMatrix{} <- typeOf y - TypePermutation{} <- typeOf perm - when (isPrimitiveType tx) $ fail ("this is a primitive type:" <+> pretty tx) - when (isPrimitiveType ty) $ fail ("this is a primitive type:" <+> pretty ty) - xs <- downX1 x - ys <- downX1 y - return - ( "Horizontal rule for matrix .<=, decomposing" - , return $ decomposeLexDotLeqSym p perm xs ys - ) +-- theRule p@[essence| &x .<= permute(&perm, &y) |] = do +-- tx@TypeMatrix{} <- typeOf x -- TODO: check matrix index & tuple arity +-- ty@TypeMatrix{} <- typeOf y +-- TypePermutation{} <- typeOf perm +-- when (isPrimitiveType tx) $ fail ("this is a primitive type:" <+> pretty tx) +-- when (isPrimitiveType ty) $ fail ("this is a primitive type:" <+> pretty ty) +-- xs <- downX1 x +-- ys <- downX1 y +-- return +-- ( "Horizontal rule for matrix .<=, decomposing" +-- , return $ decomposeLexDotLeqSym p perm xs ys +-- ) theRule p = do (x,y) <- match opDotLeq p tx@TypeMatrix{} <- typeOf x -- TODO: check matrix index & tuple arity @@ -505,58 +545,58 @@ rule_Matrix_DotLeq_Decompose = "matrix-DotLeq-tuple" `namedRule` theRule where -- HACK -- Moved inside rule_Matrix_DotLeq_Decompose since we need to do this refinement first -- otherwise compact will choose the other as it will also match and we fail -rule_Matrix_DotLeq_Symbreak_Decompose :: Rule -rule_Matrix_DotLeq_Symbreak_Decompose = "matrix-DotLeq-tuple" `namedRule` theRule where - theRule p@[essence| &x .<= permute(&perm, &y) |] = do - tx@TypeMatrix{} <- typeOf x -- TODO: check matrix index & tuple arity - ty@TypeMatrix{} <- typeOf y - when (isPrimitiveType tx) $ fail ("this is a primitive type:" <+> pretty tx) - when (isPrimitiveType ty) $ fail ("this is a primitive type:" <+> pretty ty) - xs <- downX1 x - ys <- downX1 y - return - ( "Horizontal rule for matrix .<=, decomposing" - , return $ decomposeLexDotLeqSym p perm xs ys - ) - theRule _ = na "rule_Matrix_DotLeq_Symbreak_Decompose" +--rule_Matrix_DotLeq_Symbreak_Decompose :: Rule +--rule_Matrix_DotLeq_Symbreak_Decompose = "matrix-DotLeq-tuple" `namedRule` theRule where +-- theRule p@[essence| &x .<= permute(&perm, &y) |] = do +-- tx@TypeMatrix{} <- typeOf x -- TODO: check matrix index & tuple arity +-- ty@TypeMatrix{} <- typeOf y +-- when (isPrimitiveType tx) $ fail ("this is a primitive type:" <+> pretty tx) +-- when (isPrimitiveType ty) $ fail ("this is a primitive type:" <+> pretty ty) +-- xs <- downX1 x +-- ys <- downX1 y +-- return +-- ( "Horizontal rule for matrix .<=, decomposing" +-- , return $ decomposeLexDotLeqSym p perm xs ys +-- ) +-- theRule _ = na "rule_Matrix_DotLeq_Symbreak_Decompose" -- HACK -- Moved inside rule_Matrix_Leq_Primitive since we need to do this refinement first -- otherwise compact will choose the other as it will also match and we fail -rule_Matrix_Leq_Symbreak_Primitive :: Rule -rule_Matrix_Leq_Symbreak_Primitive = "matrix-Leq-symbreak-primitive" `namedRule` theRule where - theRule [essence| &x .<= permute(&perm, &y) |] = do - tx@TypeMatrix{} <- typeOf x -- TODO: check if x and y have the same arity - ty@(TypeMatrix _ yinner) <- typeOf y - (TypePermutation pinner) <- typeOf perm - if typesUnify [yinner, pinner] - then do - unless (isPrimitiveType tx) $ fail ("not a primitive type:" <+> pretty tx) - unless (isPrimitiveType ty) $ fail ("not a primitive type:" <+> pretty ty) - x' <- flattenIfNeeded x - y' <- flattenIfNeeded y - dy'@(DomainMatrix dyindex _) <- domainOf y' - return - ( "Horizontal rule for matrix <=" - , do - (dPat, d) <- quantifiedVar - (pyName, py) <- auxiliaryVar - return $ WithLocals - [essence| &x' <=lex &py |] - (AuxiliaryVars - --TODO need union of permutation and dy domains - [ Declaration (FindOrGiven LocalFind pyName dy') - , SuchThat - [ [essence| - forAll &dPat : &dyindex . - &py[&d] = permute(&perm,&y'[&d]) - |] - ] - ] - ) - ) - else na "rule_Matrix_Leq_Symbreak_Primitive" - theRule _ = na "rule_Matrix_Leq_Symbreak_Primitive" +--rule_Matrix_Leq_Symbreak_Primitive :: Rule +--rule_Matrix_Leq_Symbreak_Primitive = "matrix-Leq-symbreak-primitive" `namedRule` theRule where +-- theRule [essence| &x .<= permute(&perm, &y) |] = do +-- tx@TypeMatrix{} <- typeOf x -- TODO: check if x and y have the same arity +-- ty@(TypeMatrix _ yinner) <- typeOf y +-- (TypePermutation pinner) <- typeOf perm +-- if typesUnify [yinner, pinner] +-- then do +-- unless (isPrimitiveType tx) $ fail ("not a primitive type:" <+> pretty tx) +-- unless (isPrimitiveType ty) $ fail ("not a primitive type:" <+> pretty ty) +-- x' <- flattenIfNeeded x +-- y' <- flattenIfNeeded y +-- dy'@(DomainMatrix dyindex _) <- domainOf y' +-- return +-- ( "Horizontal rule for matrix <=" +-- , do +-- (dPat, d) <- quantifiedVar +-- (pyName, py) <- auxiliaryVar +-- return $ WithLocals +-- [essence| &x' <=lex &py |] +-- (AuxiliaryVars +-- --TODO need union of permutation and dy domains +-- [ Declaration (FindOrGiven LocalFind pyName dy') +-- , SuchThat +-- [ [essence| +-- forAll &dPat : &dyindex . +-- &py[&d] = permute(&perm,&y'[&d]) +-- |] +-- ] +-- ] +-- ) +-- ) +-- else na "rule_Matrix_Leq_Symbreak_Primitive" +-- theRule _ = na "rule_Matrix_Leq_Symbreak_Primitive" rule_Comprehension_SingletonDomain :: Rule @@ -602,7 +642,7 @@ rule_MatrixIndexing :: Rule rule_MatrixIndexing = "matrix-indexing" `namedRule` theRule where theRule p = do (matrix, indexer) <- match opIndexing p - (_, DomainInt ranges, elems) <- match matrixLiteral matrix + (_, DomainInt _ ranges, elems) <- match matrixLiteral matrix indexInts <- rangesInts ranges indexerInt <- intOut "rule_MatrixIndexing" indexer if length indexInts == length elems diff --git a/src/Conjure/Rules/Vertical/Set/Explicit.hs b/src/Conjure/Rules/Vertical/Set/Explicit.hs index 89fe006e53..8940a51c8a 100644 --- a/src/Conjure/Rules/Vertical/Set/Explicit.hs +++ b/src/Conjure/Rules/Vertical/Set/Explicit.hs @@ -88,7 +88,7 @@ rule_Min = "set-min{Explicit}" `namedRule` theRule where DomainMatrix index _ <- domainOf m minInIndex <- case index of - DomainInt [RangeBounded lb _] -> return lb + DomainInt _ [RangeBounded lb _] -> return lb _ -> do (jPat, j) <- quantifiedVar return [essence| min([&j | &jPat : &index]) |] @@ -109,7 +109,7 @@ rule_Max = "set-max{Explicit}" `namedRule` theRule where DomainMatrix index _ <- domainOf m maxInIndex <- case index of - DomainInt [RangeBounded _ ub] -> return ub + DomainInt _ [RangeBounded _ ub] -> return ub _ -> do (jPat, j) <- quantifiedVar return [essence| max([&j | &jPat : &index]) |] diff --git a/src/Conjure/Rules/Vertical/Tuple.hs b/src/Conjure/Rules/Vertical/Tuple.hs index 0e737b7fc5..3c48511ba2 100644 --- a/src/Conjure/Rules/Vertical/Tuple.hs +++ b/src/Conjure/Rules/Vertical/Tuple.hs @@ -82,17 +82,17 @@ rule_Tuple_DotLt = "tuple-DotLt" `namedRule` theRule where rule_Tuple_DotLeq :: Rule rule_Tuple_DotLeq = "tuple-DotLeq" `namedRule` theRule where - theRule p@[essence| &x .<= permute(&perm, &y) |] = do - TypeTuple{} <- typeOf x -- TODO: check matrix index & tuple arity - TypeTuple{} <- typeOf y - TypePermutation{} <- typeOf perm - xs <- downX1 x - ys <- downX1 y - return - ( "Horizontal rule for matrix .<=, decomposing" - , return $ decomposeLexDotLeqSym p perm xs ys - ) - +-- theRule p@[essence| &x .<= permute(&perm, &y) |] = do +-- TypeTuple{} <- typeOf x -- TODO: check matrix index & tuple arity +-- TypeTuple{} <- typeOf y +-- TypePermutation{} <- typeOf perm +-- xs <- downX1 x +-- ys <- downX1 y +-- return +-- ( "Horizontal rule for matrix .<=, decomposing" +-- , return $ decomposeLexDotLeqSym p perm xs ys +-- ) +-- theRule p = do (x,y) <- match opDotLeq p TypeTuple{} <- typeOf x -- TODO: check if x and y have the same arity @@ -180,15 +180,15 @@ decomposeLexDotLeq p = unroll in [essence| (&a .< &b) \/ ((&a = &b) /\ &rest) |] unroll _ _ = bug ("arity mismatch in:" <+> pretty p) -decomposeLexDotLeqSym :: Expression -> Expression - -> [Expression] -> [Expression] -> Expression -decomposeLexDotLeqSym p perm = unroll - where - unroll [a] [b] = [essence| &a .<= permute(&perm, &b) |] - unroll (a:as) (b:bs) = let rest = unroll as bs - in [essence| (&a .< permute(&perm,&b)) \/ ((&a = permute(&perm,&b)) /\ &rest) |] - unroll _ _ = bug ("arity mismatch in:" <+> pretty p) - +--decomposeLexDotLeqSym :: Expression -> Expression +-- -> [Expression] -> [Expression] -> Expression +--decomposeLexDotLeqSym p perm = unroll +-- where +-- unroll [a] [b] = [essence| &a .<= permute(&perm, &b) |] +-- unroll (a:as) (b:bs) = let rest = unroll as bs +-- in [essence| (&a .< permute(&perm,&b)) \/ ((&a = permute(&perm,&b)) /\ &rest) |] +-- unroll _ _ = bug ("arity mismatch in:" <+> pretty p) +-- decomposeLexTildeLt :: Expression -> [Expression] -> [Expression] -> Expression diff --git a/src/Conjure/UI/Model.hs b/src/Conjure/UI/Model.hs index 7c326f5cc1..6a409415ae 100644 --- a/src/Conjure/UI/Model.hs +++ b/src/Conjure/UI/Model.hs @@ -613,7 +613,7 @@ oneSuchThat m = m { mStatements = onStatements (mStatements m) } emptyMatrixLiterals :: Model -> Model emptyMatrixLiterals model = let - f (TypeList ty) = TypeMatrix TypeInt ty + f (TypeList ty) = TypeMatrix (TypeInt Nothing) ty f x = x in model { mStatements = mStatements model |> transformBi f } @@ -668,7 +668,7 @@ updateDeclarations model = do domains = [ d | (n, d) <- representations, n == nm ] nub <$> concatMapM (onEachDomain forg nm) domains Declaration (GivenDomainDefnEnum name) -> return - [ Declaration (FindOrGiven Given (name `mappend` "_EnumSize") (DomainInt [])) ] + [ Declaration (FindOrGiven Given (name `mappend` "_EnumSize") (DomainInt Nothing [])) ] Declaration (Letting nm x) -> do let usedAfter = nbUses nm afters > 0 let isRefined = (0 :: Int) == sum @@ -1073,7 +1073,7 @@ verticalRules = , Vertical.Matrix.rule_Comprehension_ToSet_List_DuplicateFree , Vertical.Matrix.rule_Matrix_Eq , Vertical.Matrix.rule_Matrix_Neq --- , Vertical.Matrix.rule_Matrix_Leq_Symbreak_Primitive + , Vertical.Matrix.rule_Matrix_Permute , Vertical.Matrix.rule_Matrix_Leq_Primitive , Vertical.Matrix.rule_Matrix_Leq_Decompose , Vertical.Matrix.rule_Matrix_Lt_Primitive @@ -1731,7 +1731,7 @@ rule_Decompose_AllDiff = "decompose-allDiff" `namedRule` theRule where ty <- typeOf m case ty of TypeMatrix _ TypeBool -> na "allDiff can stay" - TypeMatrix _ TypeInt -> na "allDiff can stay" + TypeMatrix _ (TypeInt _) -> na "allDiff can stay" TypeMatrix _ _ -> return () _ -> na "allDiff on something other than a matrix." index:_ <- indexDomainsOf m @@ -1763,7 +1763,7 @@ rule_DomainCardinality = "domain-cardinality" `namedRule` theRule where return ( "Cardinality of a domain" , case d of - DomainInt [RangeBounded 1 u] -> return u + DomainInt Nothing [RangeBounded 1 u] -> return u _ -> do (iPat, _) <- quantifiedVar return [essence| sum([ 1 | &iPat : &d ]) |] @@ -1934,7 +1934,7 @@ rule_InlineConditions_AllDiff = "inline-conditions-allDiff" `namedRule` theRule collectLowerBounds (RangeBounded x _) = return x collectLowerBounds _ = userErr1 ("Unexpected infinite domain:" <+> pretty domBody) - collectLowerBoundsD (DomainInt rs) = mapM collectLowerBounds rs + collectLowerBoundsD (DomainInt _ rs) = mapM collectLowerBounds rs collectLowerBoundsD _ = userErr1 ("Expected an integer domain, but got:" <+> pretty domBody) bounds <- collectLowerBoundsD domBody diff --git a/src/Conjure/UI/TranslateParameter.hs b/src/Conjure/UI/TranslateParameter.hs index 3e27b4d8e4..7895466be6 100644 --- a/src/Conjure/UI/TranslateParameter.hs +++ b/src/Conjure/UI/TranslateParameter.hs @@ -116,7 +116,7 @@ translateParameter eprimeModel0 essenceParam0 = do ] else return $ Just (n, d, TypedConstant c cTy) else return $ Just (n, d, v) - | (n, d) <- essenceGivens' ++ [ (n, DomainInt []) | n <- generatedLettingNames ] + | (n, d) <- essenceGivens' ++ [ (n, DomainInt Nothing []) | n <- generatedLettingNames ] ] logDebug $ "[essenceGivensAndLettings ]" <+> vcat [ vcat [ "name :" <+> pretty n , "domain :" <+> pretty d diff --git a/src/Conjure/UI/TypeCheck.hs b/src/Conjure/UI/TypeCheck.hs index ded588becd..4b5e9a2903 100644 --- a/src/Conjure/UI/TypeCheck.hs +++ b/src/Conjure/UI/TypeCheck.hs @@ -162,10 +162,10 @@ typeCheckModel model1 = do -- DomainInt [RangeSingle x] from DomainIntE x, if x has type int let domainIntERecover :: forall m . MonadFail m => Domain () Expression -> m (Domain () Expression) - domainIntERecover d@(DomainIntE x) = do + domainIntERecover d@(DomainIntE name x) = do ty <- typeOf x return $ case ty of - TypeInt -> DomainInt [RangeSingle x] + TypeInt _ -> DomainInt name [RangeSingle x] _ -> d domainIntERecover d = return d statements4 <- transformBiM domainIntERecover statements3 diff --git a/src/test/Conjure/Language/DomainSizeTest.hs b/src/test/Conjure/Language/DomainSizeTest.hs index 571891c5d6..37c5f66705 100644 --- a/src/test/Conjure/Language/DomainSizeTest.hs +++ b/src/test/Conjure/Language/DomainSizeTest.hs @@ -19,17 +19,17 @@ tests = testGroup "domainSize" [ testCase "domain size of bool is 2" $ domainSizeConstant DomainBool @?= Right 2 , testCase "domain size of int(1..100)" $ - domainSizeConstant (DomainInt [RangeBounded (ConstantInt 1) (ConstantInt 100)]) @?= Right 100 + domainSizeConstant (DomainInt Nothing [RangeBounded (ConstantInt 1) (ConstantInt 100)]) @?= Right 100 , testCase "domain size of int(1,...,100)" $ - domainSizeConstant (DomainInt (map (RangeSingle . ConstantInt) [1 .. 100])) @?= Right 100 + domainSizeConstant (DomainInt Nothing (map (RangeSingle . ConstantInt) [1 .. 100])) @?= Right 100 , testCase "domain size of int(13)" $ - domainSizeConstant (DomainInt [RangeSingle (ConstantInt 13)]) @?= Right 1 + domainSizeConstant (DomainInt Nothing [RangeSingle (ConstantInt 13)]) @?= Right 1 , testCase "domain size of int(13,1..100)" $ - domainSizeConstant (DomainInt [ RangeSingle (ConstantInt 13) + domainSizeConstant (DomainInt Nothing [ RangeSingle (ConstantInt 13) , RangeBounded (ConstantInt 1) (ConstantInt 100) ]) @?= Right 100 , testCase "domain size of int(113,1..100)" $ - domainSizeConstant (DomainInt [ RangeSingle (ConstantInt 113) + domainSizeConstant (DomainInt Nothing [ RangeSingle (ConstantInt 113) , RangeBounded (ConstantInt 1) (ConstantInt 100) ]) @?= Right 101 , testCase "domain size of set of bool #1" $ diff --git a/tests/custom/permutations/basic/25/permutation.essence b/tests/custom/permutations/basic/25/permutation.essence new file mode 100644 index 0000000000..fad89799a5 --- /dev/null +++ b/tests/custom/permutations/basic/25/permutation.essence @@ -0,0 +1,15 @@ + +given n : int +given m : int + +find p : permutation of int(1..m) + +find x : matrix indexed by [int(1..n)] of int(1..n) + +find y : matrix indexed by [int(1..n)] of int(n..m) + + +such that + y = permute(p,x) + /\ allDiff(y) + /\ allDiff(x) diff --git a/tests/custom/permutations/basic/25/permutation.param b/tests/custom/permutations/basic/25/permutation.param new file mode 100644 index 0000000000..4c5bdd272d --- /dev/null +++ b/tests/custom/permutations/basic/25/permutation.param @@ -0,0 +1,2 @@ +letting n be 5 +letting m be 10 diff --git a/tests/custom/permutations/basic/25/run.sh b/tests/custom/permutations/basic/25/run.sh new file mode 100755 index 0000000000..98ec8c2243 --- /dev/null +++ b/tests/custom/permutations/basic/25/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence *.param --number-of-solutions=20 +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/basic/25/stdout.expected b/tests/custom/permutations/basic/25/stdout.expected new file mode 100644 index 0000000000..9d98db50a0 --- /dev/null +++ b/tests/custom/permutations/basic/25/stdout.expected @@ -0,0 +1,124 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime permutation.param +Copying solution to: permutation-permutation-000001.solution +Copying solution to: permutation-permutation-000002.solution +Copying solution to: permutation-permutation-000003.solution +Copying solution to: permutation-permutation-000004.solution +Copying solution to: permutation-permutation-000005.solution +Copying solution to: permutation-permutation-000006.solution +Copying solution to: permutation-permutation-000007.solution +Copying solution to: permutation-permutation-000008.solution +Copying solution to: permutation-permutation-000009.solution +Copying solution to: permutation-permutation-000010.solution +Copying solution to: permutation-permutation-000011.solution +Copying solution to: permutation-permutation-000012.solution +Copying solution to: permutation-permutation-000013.solution +Copying solution to: permutation-permutation-000014.solution +Copying solution to: permutation-permutation-000015.solution +Copying solution to: permutation-permutation-000016.solution +Copying solution to: permutation-permutation-000017.solution +Copying solution to: permutation-permutation-000018.solution +Copying solution to: permutation-permutation-000019.solution +Copying solution to: permutation-permutation-000020.solution +language Essence 1.3 + +letting p be permutation((1, 5, 9, 4, 8, 3, 7, 2, 6)) +letting x be [1, 2, 3, 4, 5; int(1..5)] +letting y be [5, 6, 7, 8, 9; int(1..5)] +language Essence 1.3 + +letting p be permutation((1, 5, 9, 4, 8, 3, 7, 2, 6)) +letting x be [1, 2, 3, 5, 4; int(1..5)] +letting y be [5, 6, 7, 9, 8; int(1..5)] +language Essence 1.3 + +letting p be permutation((1, 5, 9, 4, 8, 3, 7, 2, 6)) +letting x be [1, 2, 4, 3, 5; int(1..5)] +letting y be [5, 6, 8, 7, 9; int(1..5)] +language Essence 1.3 + +letting p be permutation((1, 5, 9, 4, 8, 3, 7, 2, 6)) +letting x be [1, 2, 4, 5, 3; int(1..5)] +letting y be [5, 6, 8, 9, 7; int(1..5)] +language Essence 1.3 + +letting p be permutation((1, 5, 9, 4, 8, 3, 7, 2, 6)) +letting x be [1, 2, 5, 3, 4; int(1..5)] +letting y be [5, 6, 9, 7, 8; int(1..5)] +language Essence 1.3 + +letting p be permutation((1, 5, 9, 4, 8, 3, 7, 2, 6)) +letting x be [1, 2, 5, 4, 3; int(1..5)] +letting y be [5, 6, 9, 8, 7; int(1..5)] +language Essence 1.3 + +letting p be permutation((1, 5, 9, 4, 8, 3, 7, 2, 6)) +letting x be [1, 3, 2, 4, 5; int(1..5)] +letting y be [5, 7, 6, 8, 9; int(1..5)] +language Essence 1.3 + +letting p be permutation((1, 5, 9, 4, 8, 3, 7, 2, 6)) +letting x be [1, 3, 2, 5, 4; int(1..5)] +letting y be [5, 7, 6, 9, 8; int(1..5)] +language Essence 1.3 + +letting p be permutation((1, 5, 9, 4, 8, 3, 7, 2, 6)) +letting x be [1, 3, 4, 2, 5; int(1..5)] +letting y be [5, 7, 8, 6, 9; int(1..5)] +language Essence 1.3 + +letting p be permutation((1, 5, 9, 4, 8, 3, 7, 2, 6)) +letting x be [1, 3, 4, 5, 2; int(1..5)] +letting y be [5, 7, 8, 9, 6; int(1..5)] +language Essence 1.3 + +letting p be permutation((1, 5, 9, 4, 8, 3, 7, 2, 6)) +letting x be [1, 3, 5, 2, 4; int(1..5)] +letting y be [5, 7, 9, 6, 8; int(1..5)] +language Essence 1.3 + +letting p be permutation((1, 5, 9, 4, 8, 3, 7, 2, 6)) +letting x be [1, 3, 5, 4, 2; int(1..5)] +letting y be [5, 7, 9, 8, 6; int(1..5)] +language Essence 1.3 + +letting p be permutation((1, 5, 9, 4, 8, 3, 7, 2, 6)) +letting x be [1, 4, 2, 3, 5; int(1..5)] +letting y be [5, 8, 6, 7, 9; int(1..5)] +language Essence 1.3 + +letting p be permutation((1, 5, 9, 4, 8, 3, 7, 2, 6)) +letting x be [1, 4, 2, 5, 3; int(1..5)] +letting y be [5, 8, 6, 9, 7; int(1..5)] +language Essence 1.3 + +letting p be permutation((1, 5, 9, 4, 8, 3, 7, 2, 6)) +letting x be [1, 4, 3, 2, 5; int(1..5)] +letting y be [5, 8, 7, 6, 9; int(1..5)] +language Essence 1.3 + +letting p be permutation((1, 5, 9, 4, 8, 3, 7, 2, 6)) +letting x be [1, 4, 3, 5, 2; int(1..5)] +letting y be [5, 8, 7, 9, 6; int(1..5)] +language Essence 1.3 + +letting p be permutation((1, 5, 9, 4, 8, 3, 7, 2, 6)) +letting x be [1, 4, 5, 2, 3; int(1..5)] +letting y be [5, 8, 9, 6, 7; int(1..5)] +language Essence 1.3 + +letting p be permutation((1, 5, 9, 4, 8, 3, 7, 2, 6)) +letting x be [1, 4, 5, 3, 2; int(1..5)] +letting y be [5, 8, 9, 7, 6; int(1..5)] +language Essence 1.3 + +letting p be permutation((1, 5, 9, 4, 8, 3, 7, 2, 6)) +letting x be [1, 5, 2, 3, 4; int(1..5)] +letting y be [5, 9, 6, 7, 8; int(1..5)] +language Essence 1.3 + +letting p be permutation((1, 5, 9, 4, 8, 3, 7, 2, 6)) +letting x be [1, 5, 2, 4, 3; int(1..5)] +letting y be [5, 9, 6, 8, 7; int(1..5)] diff --git a/tests/custom/permutations/basic/26/permutation.essence b/tests/custom/permutations/basic/26/permutation.essence new file mode 100644 index 0000000000..03db6ad78f --- /dev/null +++ b/tests/custom/permutations/basic/26/permutation.essence @@ -0,0 +1,16 @@ + +given n : int + +letting MYTYPE be new type enum {THING1, THING2, THING3, THING4, THING5} + +letting p be permutation ((3,4)) + +find x : matrix indexed by [int(1..n)] of MYTYPE + +find y : matrix indexed by [int(1..n)] of MYTYPE + + +such that + y = permute(p,x) + /\ allDiff(y) + /\ allDiff(x) diff --git a/tests/custom/permutations/basic/26/permutation.param b/tests/custom/permutations/basic/26/permutation.param new file mode 100644 index 0000000000..36d2429361 --- /dev/null +++ b/tests/custom/permutations/basic/26/permutation.param @@ -0,0 +1 @@ +letting n be 5 diff --git a/tests/custom/permutations/basic/26/run.sh b/tests/custom/permutations/basic/26/run.sh new file mode 100755 index 0000000000..98ec8c2243 --- /dev/null +++ b/tests/custom/permutations/basic/26/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence *.param --number-of-solutions=20 +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/basic/26/stdout.expected b/tests/custom/permutations/basic/26/stdout.expected new file mode 100644 index 0000000000..9d98db50a0 --- /dev/null +++ b/tests/custom/permutations/basic/26/stdout.expected @@ -0,0 +1,124 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime permutation.param +Copying solution to: permutation-permutation-000001.solution +Copying solution to: permutation-permutation-000002.solution +Copying solution to: permutation-permutation-000003.solution +Copying solution to: permutation-permutation-000004.solution +Copying solution to: permutation-permutation-000005.solution +Copying solution to: permutation-permutation-000006.solution +Copying solution to: permutation-permutation-000007.solution +Copying solution to: permutation-permutation-000008.solution +Copying solution to: permutation-permutation-000009.solution +Copying solution to: permutation-permutation-000010.solution +Copying solution to: permutation-permutation-000011.solution +Copying solution to: permutation-permutation-000012.solution +Copying solution to: permutation-permutation-000013.solution +Copying solution to: permutation-permutation-000014.solution +Copying solution to: permutation-permutation-000015.solution +Copying solution to: permutation-permutation-000016.solution +Copying solution to: permutation-permutation-000017.solution +Copying solution to: permutation-permutation-000018.solution +Copying solution to: permutation-permutation-000019.solution +Copying solution to: permutation-permutation-000020.solution +language Essence 1.3 + +letting p be permutation((1, 5, 9, 4, 8, 3, 7, 2, 6)) +letting x be [1, 2, 3, 4, 5; int(1..5)] +letting y be [5, 6, 7, 8, 9; int(1..5)] +language Essence 1.3 + +letting p be permutation((1, 5, 9, 4, 8, 3, 7, 2, 6)) +letting x be [1, 2, 3, 5, 4; int(1..5)] +letting y be [5, 6, 7, 9, 8; int(1..5)] +language Essence 1.3 + +letting p be permutation((1, 5, 9, 4, 8, 3, 7, 2, 6)) +letting x be [1, 2, 4, 3, 5; int(1..5)] +letting y be [5, 6, 8, 7, 9; int(1..5)] +language Essence 1.3 + +letting p be permutation((1, 5, 9, 4, 8, 3, 7, 2, 6)) +letting x be [1, 2, 4, 5, 3; int(1..5)] +letting y be [5, 6, 8, 9, 7; int(1..5)] +language Essence 1.3 + +letting p be permutation((1, 5, 9, 4, 8, 3, 7, 2, 6)) +letting x be [1, 2, 5, 3, 4; int(1..5)] +letting y be [5, 6, 9, 7, 8; int(1..5)] +language Essence 1.3 + +letting p be permutation((1, 5, 9, 4, 8, 3, 7, 2, 6)) +letting x be [1, 2, 5, 4, 3; int(1..5)] +letting y be [5, 6, 9, 8, 7; int(1..5)] +language Essence 1.3 + +letting p be permutation((1, 5, 9, 4, 8, 3, 7, 2, 6)) +letting x be [1, 3, 2, 4, 5; int(1..5)] +letting y be [5, 7, 6, 8, 9; int(1..5)] +language Essence 1.3 + +letting p be permutation((1, 5, 9, 4, 8, 3, 7, 2, 6)) +letting x be [1, 3, 2, 5, 4; int(1..5)] +letting y be [5, 7, 6, 9, 8; int(1..5)] +language Essence 1.3 + +letting p be permutation((1, 5, 9, 4, 8, 3, 7, 2, 6)) +letting x be [1, 3, 4, 2, 5; int(1..5)] +letting y be [5, 7, 8, 6, 9; int(1..5)] +language Essence 1.3 + +letting p be permutation((1, 5, 9, 4, 8, 3, 7, 2, 6)) +letting x be [1, 3, 4, 5, 2; int(1..5)] +letting y be [5, 7, 8, 9, 6; int(1..5)] +language Essence 1.3 + +letting p be permutation((1, 5, 9, 4, 8, 3, 7, 2, 6)) +letting x be [1, 3, 5, 2, 4; int(1..5)] +letting y be [5, 7, 9, 6, 8; int(1..5)] +language Essence 1.3 + +letting p be permutation((1, 5, 9, 4, 8, 3, 7, 2, 6)) +letting x be [1, 3, 5, 4, 2; int(1..5)] +letting y be [5, 7, 9, 8, 6; int(1..5)] +language Essence 1.3 + +letting p be permutation((1, 5, 9, 4, 8, 3, 7, 2, 6)) +letting x be [1, 4, 2, 3, 5; int(1..5)] +letting y be [5, 8, 6, 7, 9; int(1..5)] +language Essence 1.3 + +letting p be permutation((1, 5, 9, 4, 8, 3, 7, 2, 6)) +letting x be [1, 4, 2, 5, 3; int(1..5)] +letting y be [5, 8, 6, 9, 7; int(1..5)] +language Essence 1.3 + +letting p be permutation((1, 5, 9, 4, 8, 3, 7, 2, 6)) +letting x be [1, 4, 3, 2, 5; int(1..5)] +letting y be [5, 8, 7, 6, 9; int(1..5)] +language Essence 1.3 + +letting p be permutation((1, 5, 9, 4, 8, 3, 7, 2, 6)) +letting x be [1, 4, 3, 5, 2; int(1..5)] +letting y be [5, 8, 7, 9, 6; int(1..5)] +language Essence 1.3 + +letting p be permutation((1, 5, 9, 4, 8, 3, 7, 2, 6)) +letting x be [1, 4, 5, 2, 3; int(1..5)] +letting y be [5, 8, 9, 6, 7; int(1..5)] +language Essence 1.3 + +letting p be permutation((1, 5, 9, 4, 8, 3, 7, 2, 6)) +letting x be [1, 4, 5, 3, 2; int(1..5)] +letting y be [5, 8, 9, 7, 6; int(1..5)] +language Essence 1.3 + +letting p be permutation((1, 5, 9, 4, 8, 3, 7, 2, 6)) +letting x be [1, 5, 2, 3, 4; int(1..5)] +letting y be [5, 9, 6, 7, 8; int(1..5)] +language Essence 1.3 + +letting p be permutation((1, 5, 9, 4, 8, 3, 7, 2, 6)) +letting x be [1, 5, 2, 4, 3; int(1..5)] +letting y be [5, 9, 6, 8, 7; int(1..5)] From 2429d52b5c0769938bf2975c068ace4d8a958a72 Mon Sep 17 00:00:00 2001 From: Fraser Dunlop Date: Thu, 18 Oct 2018 14:58:16 +0100 Subject: [PATCH 009/229] Adding tag to ConstantInt --- src/Conjure/Language/Arbitrary.hs | 26 +- src/Conjure/Language/Constant.hs | 86 +-- src/Conjure/Language/Expression.hs | 4 +- .../Language/Expression/Op/AllDiffExcept.hs | 4 +- src/Conjure/Language/Expression/Op/Div.hs | 2 +- .../Language/Expression/Op/Factorial.hs | 2 +- src/Conjure/Language/Expression/Op/Freq.hs | 2 +- src/Conjure/Language/Expression/Op/Hist.hs | 4 +- .../Language/Expression/Op/Indexing.hs | 4 +- src/Conjure/Language/Expression/Op/Max.hs | 8 +- src/Conjure/Language/Expression/Op/Min.hs | 8 +- src/Conjure/Language/Expression/Op/Minus.hs | 2 +- src/Conjure/Language/Expression/Op/Mod.hs | 2 +- src/Conjure/Language/Expression/Op/Negate.hs | 2 +- src/Conjure/Language/Expression/Op/Pow.hs | 2 +- .../Language/Expression/Op/PreImage.hs | 2 +- src/Conjure/Language/Expression/Op/Pred.hs | 2 +- src/Conjure/Language/Expression/Op/Product.hs | 2 +- src/Conjure/Language/Expression/Op/Slicing.hs | 6 +- src/Conjure/Language/Expression/Op/Succ.hs | 2 +- src/Conjure/Language/Expression/Op/Sum.hs | 2 +- src/Conjure/Language/Expression/Op/TildeLt.hs | 2 +- src/Conjure/Language/Expression/Op/ToInt.hs | 6 +- src/Conjure/Language/Expression/Op/TwoBars.hs | 18 +- src/Conjure/Language/Instantiate.hs | 2 +- src/Conjure/Language/Lenses.hs | 4 +- src/Conjure/Language/NameResolution.hs | 2 +- src/Conjure/Language/Parser.hs | 2 +- src/Conjure/Language/ParserC.hs | 2 +- src/Conjure/Language/ZeroVal.hs | 6 +- src/Conjure/Process/Enumerate.hs | 4 +- src/Conjure/Process/Enums.hs | 11 +- src/Conjure/Process/FiniteGivens.hs | 36 +- src/Conjure/Process/InferAttributes.hs | 2 +- .../Representations/Function/Function1D.hs | 2 +- .../Representations/MSet/ExplicitWithFlags.hs | 8 +- .../MSet/ExplicitWithRepetition.hs | 6 +- .../Representations/Partition/Occurrence.hs | 10 +- .../Sequence/ExplicitBounded.hs | 8 +- .../Set/ExplicitVarSizeWithDummy.hs | 8 +- .../Set/ExplicitVarSizeWithFlags.hs | 2 +- .../Set/ExplicitVarSizeWithMarker.hs | 6 +- src/Conjure/Representations/Set/Occurrence.hs | 4 +- src/Conjure/Representations/Variant.hs | 2 +- src/Conjure/UI/TranslateSolution.hs | 2 +- src/Conjure/UI/ValidateSolution.hs | 6 +- src/test/Conjure/Language/DomainSizeTest.hs | 16 +- src/test/Conjure/RepresentationsTest.hs | 560 +++++++++--------- .../permutations/basic/26/stdout.expected | 100 ++-- 49 files changed, 496 insertions(+), 515 deletions(-) diff --git a/src/Conjure/Language/Arbitrary.hs b/src/Conjure/Language/Arbitrary.hs index ecbfc1b617..606d7be7a5 100644 --- a/src/Conjure/Language/Arbitrary.hs +++ b/src/Conjure/Language/Arbitrary.hs @@ -106,24 +106,24 @@ arbitraryDomainAndConstant = sized dispatch intBounded = do l <- choose (0 :: Integer, 100) u <- choose (l, 200) - return ( DomainInt Nothing [RangeBounded (ConstantInt l) (ConstantInt u)] - , ConstantInt <$> choose (l,u) + return ( DomainInt Nothing [RangeBounded (ConstantInt Nothing l) (ConstantInt Nothing u)] + , ConstantInt Nothing <$> choose (l,u) ) intSingles :: Gen (Domain r Constant, Gen Constant) intSingles = do count <- choose (1 :: Integer, 20) vals <- vectorOf (fromInteger count) (choose (0 :: Integer, 100)) - return ( DomainInt Nothing (map (RangeSingle . ConstantInt) vals) - , ConstantInt <$> pickFromList vals + return ( DomainInt Nothing (map (RangeSingle . ConstantInt Nothing) vals) + , ConstantInt Nothing <$> pickFromList vals ) intMixed :: Gen (Domain r Constant, Gen Constant) intMixed = do - let single = RangeSingle . ConstantInt <$> choose (0 :: Integer, 100) + let single = RangeSingle . ConstantInt Nothing <$> choose (0 :: Integer, 100) let pair = do l <- choose (0 :: Integer, 100) u <- choose (l, 200) - return $ RangeBounded (ConstantInt l) (ConstantInt u) + return $ RangeBounded (ConstantInt Nothing l) (ConstantInt Nothing u) numSingles <- choose (1 :: Int, 10) numPairs <- choose (1 :: Int, 10) @@ -146,15 +146,15 @@ arbitraryDomainAndConstant = sized dispatch [ vals | r <- rs , let vals = case r of - RangeSingle (ConstantInt i) -> [i] - RangeBounded (ConstantInt l) (ConstantInt u) -> [l..u] + RangeSingle (ConstantInt Nothing i) -> [i] + RangeBounded (ConstantInt Nothing l) (ConstantInt Nothing u) -> [l..u] _ -> [] ] if null allVals then bug "allVals null" else return ( DomainInt Nothing rs - , ConstantInt <$> pickFromList allVals + , ConstantInt Nothing <$> pickFromList allVals ) -- enum :: Gen (Domain HasRepresentation Constant, Gen Constant) @@ -194,7 +194,7 @@ arbitraryDomainAndConstant = sized dispatch let domainOut = DomainSet repr - (SetAttr (SizeAttr_Size (ConstantInt size))) + (SetAttr (SizeAttr_Size (ConstantInt Nothing size))) dom return ( domainOut , let try n = @@ -223,7 +223,7 @@ arbitraryDomainAndConstant = sized dispatch maxSize <- choose (0 :: Integer, sizeUpTo) repr <- pickFromList [Set_ExplicitVarSizeWithFlags, Set_ExplicitVarSizeWithMarker] return ( DomainSet repr - (SetAttr (SizeAttr_MaxSize (ConstantInt maxSize))) + (SetAttr (SizeAttr_MaxSize (ConstantInt Nothing maxSize))) dom , do numElems <- choose (0, maxSize) elems <- vectorOf (fromInteger numElems) constantGen @@ -244,8 +244,8 @@ arbitraryDomainAndConstant = sized dispatch DomainSet repr (SetAttr (SizeAttr_MinMaxSize - (ConstantInt minSize) - (ConstantInt maxSize))) + (ConstantInt Nothing minSize) + (ConstantInt Nothing maxSize))) dom return ( domainOut , let try n = diff --git a/src/Conjure/Language/Constant.hs b/src/Conjure/Language/Constant.hs index db00b429d4..f37636a906 100644 --- a/src/Conjure/Language/Constant.hs +++ b/src/Conjure/Language/Constant.hs @@ -45,7 +45,7 @@ import Test.QuickCheck ( Arbitrary(..), oneof ) data Constant = ConstantBool Bool - | ConstantInt Integer + | ConstantInt (Maybe Name) Integer | ConstantEnum Name {- name for the enum domain -} [Name] {- values in the enum domain -} Name {- the literal -} @@ -70,7 +70,7 @@ instance Ord Constant where -- the "usual" comparisons compare (ConstantBool a) (ConstantBool b) = compare a b - compare (ConstantInt a) (ConstantInt b) = compare a b + compare (ConstantInt _ a) (ConstantInt _ b) = compare a b compare (ConstantEnum _ aVals aVal) (ConstantEnum _ bVals bVal) = compare (elemIndex aVal aVals, aVal) (elemIndex bVal bVals, bVal) compare (ConstantField a1 a2) (ConstantField b1 b2) = compare (a1,a2) (b1,b2) @@ -89,12 +89,12 @@ instance FromJSON Constant where parseJSON = genericParseJSON jsonOptions instance Arbitrary Constant where arbitrary = oneof [ ConstantBool <$> arbitrary - , ConstantInt <$> arbitrary + , ConstantInt Nothing <$> arbitrary ] instance TypeOf Constant where typeOf ConstantBool{} = return TypeBool - typeOf ConstantInt{} = return $ TypeInt Nothing + typeOf (ConstantInt name _) = return $ TypeInt name typeOf (ConstantEnum defn _ _ ) = return (TypeEnum defn) typeOf (ConstantField _ ty) = return ty typeOf (ConstantAbstract x ) = typeOf x @@ -114,17 +114,17 @@ instance DomainSizeOf Constant Integer where SizeAttr_None -> do innerSize <- domainSizeOf inner return (2 `intPow` innerSize) - SizeAttr_Size (ConstantInt size) -> do + SizeAttr_Size (ConstantInt Nothing size) -> do innerSize <- domainSizeOf inner return (nchoosek (product . enumFromTo 1) innerSize size) SizeAttr_MinSize{} -> do -- TODO: we can do better here innerSize <- domainSizeOf inner return (2 `intPow` innerSize) - SizeAttr_MaxSize (ConstantInt maxSize) -> do + SizeAttr_MaxSize (ConstantInt Nothing maxSize) -> do innerSize <- domainSizeOf inner return $ sum [ nchoosek (product . enumFromTo 1) innerSize k | k <- [0 .. maxSize] ] - SizeAttr_MinMaxSize (ConstantInt minSize) (ConstantInt maxSize) -> do + SizeAttr_MinMaxSize (ConstantInt Nothing minSize) (ConstantInt Nothing maxSize) -> do innerSize <- domainSizeOf inner return $ sum [ nchoosek (product . enumFromTo 1) innerSize k | k <- [minSize .. maxSize] ] _ -> fail ("domainSizeOf{Constant}" <+> pretty d) @@ -151,7 +151,7 @@ domainSizeOfRanges :: MonadFail m => [Range Constant] -> m Integer domainSizeOfRanges = fmap genericLength . valuesInIntDomain instance DomainSizeOf Constant Constant where - domainSizeOf = fmap ConstantInt . domainSizeOf + domainSizeOf = fmap (ConstantInt Nothing) . domainSizeOf instance Pretty Constant where @@ -175,7 +175,7 @@ instance Pretty Constant where pretty (ConstantBool False) = "false" pretty (ConstantBool True ) = "true" - pretty (ConstantInt x ) = pretty x + pretty (ConstantInt _ x ) = pretty x pretty (ConstantEnum _ _ x) = pretty x pretty (ConstantField n _) = pretty n pretty (ConstantAbstract x) = pretty x @@ -184,8 +184,8 @@ instance Pretty Constant where pretty (ConstantUndefined reason ty) = "undefined" <> prParens (pretty reason <+> ":" <+> "`" <> pretty ty <> "`") instance ExpressionLike Constant where - fromInt = ConstantInt - intOut _ (ConstantInt x) = return x + fromInt = ConstantInt Nothing + intOut _ (ConstantInt Nothing x) = return x intOut doc c = fail $ vcat [ "Expecting an integer, but found:" <+> pretty c , "Called from:" <+> doc ] @@ -228,17 +228,17 @@ normaliseConstant (TypedConstant c ty) = TypedConstant (normaliseConstant c) ty normaliseConstant x@ConstantUndefined{} = x instance Num Constant where - ConstantInt x + ConstantInt y = ConstantInt (x+y) + ConstantInt Nothing x + ConstantInt Nothing y = ConstantInt Nothing (x+y) x + y = bug $ vcat [ "Num Constant (+)", "x:" <+> pretty x, "y:" <+> pretty y ] - ConstantInt x - ConstantInt y = ConstantInt (x-y) + ConstantInt Nothing x - ConstantInt Nothing y = ConstantInt Nothing (x-y) x - y = bug $ vcat [ "Num Constant (-)", "x:" <+> pretty x, "y:" <+> pretty y ] - ConstantInt x * ConstantInt y = ConstantInt (x*y) + ConstantInt Nothing x * ConstantInt Nothing y = ConstantInt Nothing (x*y) x * y = bug $ vcat [ "Num Constant (*)", "x:" <+> pretty x, "y:" <+> pretty y ] - abs (ConstantInt x) = ConstantInt (abs x) + abs (ConstantInt Nothing x) = ConstantInt Nothing (abs x) abs x = bug $ vcat [ "Num Constant abs", "x:" <+> pretty x ] - signum (ConstantInt x) = ConstantInt (signum x) + signum (ConstantInt Nothing x) = ConstantInt Nothing (signum x) signum x = bug $ vcat [ "Num Constant signum", "x:" <+> pretty x ] - fromInteger = ConstantInt . fromInteger + fromInteger = ConstantInt Nothing . fromInteger valuesInIntDomain :: MonadFail m => [Range Constant] -> m [Integer] @@ -254,8 +254,8 @@ valuesInIntDomain ranges = [ vals | r <- ranges , let vals = case r of - RangeSingle (ConstantInt x) -> return [x] - RangeBounded (ConstantInt l) (ConstantInt u) -> return [l..u] + RangeSingle (ConstantInt Nothing x) -> return [x] + RangeBounded (ConstantInt Nothing l) (ConstantInt Nothing u) -> return [l..u] _ -> Nothing ] @@ -273,17 +273,17 @@ validateConstantForDomain _ ConstantBool{} DomainBool{} = return () validateConstantForDomain _ _ (DomainInt _ []) = return () -- no restrictions -validateConstantForDomain name c@(ConstantInt i) d@(DomainInt _ rs) = +validateConstantForDomain name c@(ConstantInt Nothing i) d@(DomainInt Nothing rs) = let intInRange RangeOpen = True - intInRange (RangeSingle (ConstantInt a)) = i == a - intInRange (RangeLowerBounded (ConstantInt a)) = i >= a - intInRange (RangeUpperBounded (ConstantInt a)) = i <= a - intInRange (RangeBounded (ConstantInt a) (ConstantInt b)) = i >= a && i <= b + intInRange (RangeSingle (ConstantInt Nothing a)) = i == a + intInRange (RangeLowerBounded (ConstantInt Nothing a)) = i >= a + intInRange (RangeUpperBounded (ConstantInt Nothing a)) = i <= a + intInRange (RangeBounded (ConstantInt Nothing a) (ConstantInt Nothing b)) = i >= a && i <= b intInRange _ = False in unless (any intInRange rs) (constantNotInDomain name c d) -validateConstantForDomain _ (ConstantInt i) (DomainUnnamed _ (ConstantInt a)) | i >= 1 && i <= a = return () +validateConstantForDomain _ (ConstantInt (Just cname) i) (DomainUnnamed uname (ConstantInt Nothing a)) | cname == uname && i >= 1 && i <= a = return () validateConstantForDomain _ _ (DomainEnum _ Nothing _) = return () -- no restrictions validateConstantForDomain name c d@(DomainEnum _ _ Nothing) = @@ -294,14 +294,14 @@ validateConstantForDomain name c d@(DomainEnum _ _ Nothing) = ] validateConstantForDomain name c@ConstantInt{} - d@(DomainEnum _ (Just ranges) (Just mp)) = nested c d $ do + d@(DomainEnum name'' (Just ranges) (Just mp)) = nested c d $ do let -- lu :: MonadFail m => Name -> m Constant lu (ConstantEnum _ _ nm) = case lookup nm mp of Nothing -> fail $ "No value for:" <+> pretty nm - Just v -> return (ConstantInt v) - lu (ConstantInt v) = return (ConstantInt v) + Just v -> return (ConstantInt (Just name'') v) + lu (ConstantInt name' v) = return (ConstantInt name' v) lu x = fail $ "validateConstantForDomain.lu" <+> pretty x -- lu2 :: MonadFail m => Range Name -> m (Range Constant) @@ -346,10 +346,10 @@ validateConstantForDomain name d@(DomainSet _ (SetAttr sizeAttr) dInner) = do let cardinalityOK = case sizeAttr of SizeAttr_None -> True - SizeAttr_Size (ConstantInt s) -> s == genericLength vals - SizeAttr_MinSize (ConstantInt s) -> s <= genericLength vals - SizeAttr_MaxSize (ConstantInt s) -> genericLength vals <= s - SizeAttr_MinMaxSize (ConstantInt smin) (ConstantInt smax) -> + SizeAttr_Size (ConstantInt Nothing s) -> s == genericLength vals + SizeAttr_MinSize (ConstantInt Nothing s) -> s <= genericLength vals + SizeAttr_MaxSize (ConstantInt Nothing s) -> genericLength vals <= s + SizeAttr_MinMaxSize (ConstantInt Nothing smin) (ConstantInt Nothing smax) -> smin <= genericLength vals && genericLength vals <= smax _ -> False unless cardinalityOK $ fail $ vcat @@ -366,10 +366,10 @@ validateConstantForDomain name d@(DomainMSet _ (MSetAttr sizeAttr occurAttr) dInner) = do let cardinalityOK = case sizeAttr of SizeAttr_None -> True - SizeAttr_Size (ConstantInt s) -> s == genericLength vals - SizeAttr_MinSize (ConstantInt s) -> s <= genericLength vals - SizeAttr_MaxSize (ConstantInt s) -> genericLength vals <= s - SizeAttr_MinMaxSize (ConstantInt smin) (ConstantInt smax) -> + SizeAttr_Size (ConstantInt Nothing s) -> s == genericLength vals + SizeAttr_MinSize (ConstantInt Nothing s) -> s <= genericLength vals + SizeAttr_MaxSize (ConstantInt Nothing s) -> genericLength vals <= s + SizeAttr_MinMaxSize (ConstantInt Nothing smin) (ConstantInt Nothing smax) -> smin <= genericLength vals && genericLength vals <= smax _ -> False unless cardinalityOK $ fail $ vcat @@ -381,9 +381,9 @@ validateConstantForDomain name ] let occurOK = case occurAttr of OccurAttr_None -> True - OccurAttr_MinOccur (ConstantInt s) -> and [ s <= occ | (_, occ) <- histogram vals ] - OccurAttr_MaxOccur (ConstantInt s) -> and [ occ <= s | (_, occ) <- histogram vals ] - OccurAttr_MinMaxOccur (ConstantInt smin) (ConstantInt smax) -> + OccurAttr_MinOccur (ConstantInt Nothing s) -> and [ s <= occ | (_, occ) <- histogram vals ] + OccurAttr_MaxOccur (ConstantInt Nothing s) -> and [ occ <= s | (_, occ) <- histogram vals ] + OccurAttr_MinMaxOccur (ConstantInt Nothing smin) (ConstantInt Nothing smax) -> and [ smin <= occ && occ <= smax | (_, occ) <- histogram vals ] _ -> False unless occurOK $ fail $ vcat @@ -446,12 +446,12 @@ constantNotInDomain n c d = fail $ vcat viewConstantBool :: MonadFail m => Constant -> m Bool viewConstantBool (ConstantBool i) = return i -viewConstantBool (ConstantInt 0) = return False -viewConstantBool (ConstantInt 1) = return True +viewConstantBool (ConstantInt Nothing 0) = return False +viewConstantBool (ConstantInt Nothing 1) = return True viewConstantBool constant = fail ("Expecting a boolean integer, but got:" <++> pretty constant) viewConstantInt :: MonadFail m => Constant -> m Integer -viewConstantInt (ConstantInt i) = return i +viewConstantInt (ConstantInt _ i) = return i viewConstantInt constant = fail ("Expecting an integer, but got:" <++> pretty constant) viewConstantTuple :: MonadFail m => Constant -> m [Constant] @@ -492,7 +492,7 @@ viewConstantFunction constant = do suggestion = case constant of ConstantAbstract (AbsLitMatrix (DomainInt Nothing rs) vals) -> do froms <- valuesInIntDomain rs - return $ Just $ pretty $ AbsLitFunction (zip (map ConstantInt froms) vals) + return $ Just $ pretty $ AbsLitFunction (zip (map (ConstantInt Nothing) froms) vals) _ -> return Nothing suggestion >>= \case Nothing -> fail ("Expecting a function, but got:" <++> pretty constant) diff --git a/src/Conjure/Language/Expression.hs b/src/Conjure/Language/Expression.hs index 657fd28636..bf1a180868 100644 --- a/src/Conjure/Language/Expression.hs +++ b/src/Conjure/Language/Expression.hs @@ -163,7 +163,7 @@ instance Pretty Declaration where isPrim :: Constant -> Maybe Prim isPrim (ConstantBool val) = Just (Left val) - isPrim (ConstantInt val) = Just (Right (Left val)) + isPrim (ConstantInt Nothing val) = Just (Right (Left val)) isPrim val@ConstantEnum{} = Just (Right (Right val)) isPrim _ = Nothing @@ -576,7 +576,7 @@ instance FromJSON InBubble where parseJSON = genericParseJSON jsonOptions e2c :: MonadFail m => Expression -> m Constant e2c (Constant c) = return c e2c (AbstractLiteral c) = ConstantAbstract <$> mapM e2c c -e2c (Op (MkOpNegate (OpNegate (Constant (ConstantInt x))))) = return $ ConstantInt $ negate x +e2c (Op (MkOpNegate (OpNegate (Constant (ConstantInt Nothing x))))) = return $ ConstantInt Nothing $ negate x e2c x = fail ("e2c, not a constant:" <+> pretty x) -- | generate a fresh name for a quantified variable. diff --git a/src/Conjure/Language/Expression/Op/AllDiffExcept.hs b/src/Conjure/Language/Expression/Op/AllDiffExcept.hs index f918304cb1..30eb128944 100644 --- a/src/Conjure/Language/Expression/Op/AllDiffExcept.hs +++ b/src/Conjure/Language/Expression/Op/AllDiffExcept.hs @@ -31,8 +31,8 @@ instance (TypeOf x, Pretty x) => TypeOf (OpAllDiffExcept x) where _ -> raiseTypeError p instance EvaluateOp OpAllDiffExcept where - evaluateOp (OpAllDiffExcept (viewConstantMatrix -> Just (_, vals)) (viewConstantInt -> Just n)) = do - let vals' = filter (ConstantInt n/=) vals + evaluateOp (OpAllDiffExcept (viewConstantMatrix -> Just (_, vals)) someint) = do + let vals' = filter (someint/=) vals return $ ConstantBool $ length vals' == length (sortNub vals') evaluateOp op = na $ "evaluateOp{OpAllDiffExcept}:" <++> pretty (show op) diff --git a/src/Conjure/Language/Expression/Op/Div.hs b/src/Conjure/Language/Expression/Op/Div.hs index 4bea5d3d05..d1cd7f3b90 100644 --- a/src/Conjure/Language/Expression/Op/Div.hs +++ b/src/Conjure/Language/Expression/Op/Div.hs @@ -27,7 +27,7 @@ instance (TypeOf x, Pretty x) => TypeOf (OpDiv x) where instance EvaluateOp OpDiv where evaluateOp p | any isUndef (childrenBi p) = return $ mkUndef (TypeInt Nothing) $ "Has undefined children:" <+> pretty p evaluateOp p@(OpDiv x y) - | y /= 0 = ConstantInt <$> (div <$> intOut "div x" x <*> intOut "div y" y) + | y /= 0 = ConstantInt Nothing <$> (div <$> intOut "div x" x <*> intOut "div y" y) | otherwise = return $ mkUndef (TypeInt Nothing) $ "division by zero:" <+> pretty p instance SimplifyOp OpDiv x where diff --git a/src/Conjure/Language/Expression/Op/Factorial.hs b/src/Conjure/Language/Expression/Op/Factorial.hs index 107e600171..aab44189d5 100644 --- a/src/Conjure/Language/Expression/Op/Factorial.hs +++ b/src/Conjure/Language/Expression/Op/Factorial.hs @@ -23,7 +23,7 @@ instance TypeOf x => TypeOf (OpFactorial x) where instance EvaluateOp OpFactorial where evaluateOp p | any isUndef (childrenBi p) = return $ mkUndef (TypeInt Nothing) $ "Has undefined children:" <+> pretty p - evaluateOp (OpFactorial x) = ConstantInt . product . enumFromTo 1 <$> intOut "factorial" x + evaluateOp (OpFactorial x) = ConstantInt Nothing . product . enumFromTo 1 <$> intOut "factorial" x instance SimplifyOp OpFactorial x where simplifyOp _ = na "simplifyOp{OpFactorial}" diff --git a/src/Conjure/Language/Expression/Op/Freq.hs b/src/Conjure/Language/Expression/Op/Freq.hs index 7db0bcb1ac..f65ac19318 100644 --- a/src/Conjure/Language/Expression/Op/Freq.hs +++ b/src/Conjure/Language/Expression/Op/Freq.hs @@ -32,7 +32,7 @@ instance (TypeOf x, Pretty x) => TypeOf (OpFreq x) where _ -> raiseTypeError p instance EvaluateOp OpFreq where - evaluateOp (OpFreq (viewConstantMSet -> Just cs) c) = return $ ConstantInt $ sum [ 1 | i <- cs, c == i ] + evaluateOp (OpFreq (viewConstantMSet -> Just cs) c) = return $ ConstantInt Nothing $ sum [ 1 | i <- cs, c == i ] evaluateOp op = na $ "evaluateOp{OpFreq}:" <++> pretty (show op) instance SimplifyOp OpFreq x where diff --git a/src/Conjure/Language/Expression/Op/Hist.hs b/src/Conjure/Language/Expression/Op/Hist.hs index 22dcedac1a..324ec1404a 100644 --- a/src/Conjure/Language/Expression/Op/Hist.hs +++ b/src/Conjure/Language/Expression/Op/Hist.hs @@ -30,10 +30,10 @@ instance (TypeOf x, Pretty x) => TypeOf (OpHist x) where instance EvaluateOp OpHist where evaluateOp (OpHist (viewConstantMSet -> Just cs)) = return $ ConstantAbstract $ AbsLitMatrix (DomainInt Nothing [RangeBounded 1 (fromInt $ genericLength $ histogram cs)]) - [ ConstantAbstract $ AbsLitTuple [e, ConstantInt n] | (e, n) <- histogram cs ] + [ ConstantAbstract $ AbsLitTuple [e, ConstantInt Nothing n] | (e, n) <- histogram cs ] evaluateOp (OpHist (viewConstantMatrix -> Just (_, cs))) = return $ ConstantAbstract $ AbsLitMatrix (DomainInt Nothing [RangeBounded 1 (fromInt $ genericLength $ histogram cs)]) - [ ConstantAbstract $ AbsLitTuple [e, ConstantInt n] | (e, n) <- histogram cs ] + [ ConstantAbstract $ AbsLitTuple [e, ConstantInt Nothing n] | (e, n) <- histogram cs ] evaluateOp op = na $ "evaluateOp{OpHist}:" <++> pretty (show op) instance SimplifyOp OpHist x where diff --git a/src/Conjure/Language/Expression/Op/Indexing.hs b/src/Conjure/Language/Expression/Op/Indexing.hs index 824f1dfaf1..b3c5b0a8bd 100644 --- a/src/Conjure/Language/Expression/Op/Indexing.hs +++ b/src/Conjure/Language/Expression/Op/Indexing.hs @@ -80,7 +80,7 @@ instance EvaluateOp OpIndexing where TypeList tyTo -> return tyTo _ -> fail "evaluateOp{OpIndexing}" return $ mkUndef tyTo $ "Has undefined children (index):" <+> pretty p - evaluateOp (OpIndexing m@(viewConstantMatrix -> Just (DomainInt _ index, vals)) (ConstantInt x)) = do + evaluateOp (OpIndexing m@(viewConstantMatrix -> Just (DomainInt _ index, vals)) (ConstantInt _ x)) = do ty <- typeOf m tyTo <- case ty of TypeMatrix _ tyTo -> return tyTo TypeList tyTo -> return tyTo @@ -96,7 +96,7 @@ instance EvaluateOp OpIndexing where [ "Matrix is multiply defined at this point:" <+> pretty x , "Matrix value:" <+> pretty m ] - evaluateOp (OpIndexing (viewConstantTuple -> Just vals) (ConstantInt x)) = return (at vals (fromInteger (x-1))) + evaluateOp (OpIndexing (viewConstantTuple -> Just vals) (ConstantInt _ x)) = return (at vals (fromInteger (x-1))) evaluateOp rec@(OpIndexing (viewConstantRecord -> Just vals) (ConstantField name _)) = case lookup name vals of Nothing -> bug $ vcat diff --git a/src/Conjure/Language/Expression/Op/Max.hs b/src/Conjure/Language/Expression/Op/Max.hs index 6b296e2d61..ea25ee1332 100644 --- a/src/Conjure/Language/Expression/Op/Max.hs +++ b/src/Conjure/Language/Expression/Op/Max.hs @@ -52,7 +52,7 @@ instance EvaluateOp OpMax where is <- rangesInts rs return $ if null is then mkUndef (TypeInt Nothing) "Empty collection in max" - else ConstantInt (maximum is) + else ConstantInt Nothing (maximum is) evaluateOp (OpMax coll@(viewConstantMatrix -> Just (_, xs))) = case xs of [] -> do @@ -63,7 +63,7 @@ instance EvaluateOp OpMax where case tyInner of TypeInt Nothing -> do is <- concatMapM (intsOut "OpMax 1") xs - return $ ConstantInt (maximum is) + return $ ConstantInt Nothing (maximum is) _ -> na "evaluateOp{OpMax}" evaluateOp (OpMax coll@(viewConstantSet -> Just xs)) = do case xs of @@ -75,7 +75,7 @@ instance EvaluateOp OpMax where case tyInner of TypeInt Nothing -> do is <- concatMapM (intsOut "OpMax 1") xs - return $ ConstantInt (maximum is) + return $ ConstantInt Nothing (maximum is) _ -> na "evaluateOp{OpMax}" evaluateOp (OpMax coll@(viewConstantMSet -> Just xs)) = do case xs of @@ -87,7 +87,7 @@ instance EvaluateOp OpMax where case tyInner of TypeInt Nothing -> do is <- concatMapM (intsOut "OpMax 1") xs - return $ ConstantInt (maximum is) + return $ ConstantInt Nothing (maximum is) _ -> na "evaluateOp{OpMax}" evaluateOp _ = na "evaluateOp{OpMax}" diff --git a/src/Conjure/Language/Expression/Op/Min.hs b/src/Conjure/Language/Expression/Op/Min.hs index 7d618aaa40..9a2628187d 100644 --- a/src/Conjure/Language/Expression/Op/Min.hs +++ b/src/Conjure/Language/Expression/Op/Min.hs @@ -52,7 +52,7 @@ instance EvaluateOp OpMin where is <- rangesInts rs return $ if null is then mkUndef (TypeInt Nothing) "Empty collection in min" - else ConstantInt (minimum is) + else ConstantInt Nothing (minimum is) evaluateOp (OpMin coll@(viewConstantMatrix -> Just (_, xs))) = do case xs of [] -> do @@ -63,7 +63,7 @@ instance EvaluateOp OpMin where case tyInner of TypeInt _ -> do is <- concatMapM (intsOut "OpMin 1") xs - return $ ConstantInt (minimum is) + return $ ConstantInt Nothing (minimum is) _ -> na "evaluateOp{OpMin}" evaluateOp (OpMin coll@(viewConstantSet -> Just xs)) = do case xs of @@ -75,7 +75,7 @@ instance EvaluateOp OpMin where case tyInner of TypeInt Nothing -> do is <- concatMapM (intsOut "OpMin 1") xs - return $ ConstantInt (minimum is) + return $ ConstantInt Nothing (minimum is) _ -> na "evaluateOp{OpMin}" evaluateOp (OpMin coll@(viewConstantMSet -> Just xs)) = do case xs of @@ -87,7 +87,7 @@ instance EvaluateOp OpMin where case tyInner of TypeInt Nothing -> do is <- concatMapM (intsOut "OpMin 1") xs - return $ ConstantInt (minimum is) + return $ ConstantInt Nothing (minimum is) _ -> na "evaluateOp{OpMin}" evaluateOp op = na $ "evaluateOp{OpMin}" <+> pretty (show op) diff --git a/src/Conjure/Language/Expression/Op/Minus.hs b/src/Conjure/Language/Expression/Op/Minus.hs index 658a4c204f..899d6e67e7 100644 --- a/src/Conjure/Language/Expression/Op/Minus.hs +++ b/src/Conjure/Language/Expression/Op/Minus.hs @@ -34,7 +34,7 @@ instance EvaluateOp OpMinus where evaluateOp p | any isUndef (childrenBi p) = do ty <- typeOf p return $ mkUndef ty $ "Has undefined children:" <+> pretty p - evaluateOp (OpMinus (ConstantInt a) (ConstantInt b)) = return $ ConstantInt (a - b) + evaluateOp (OpMinus (ConstantInt Nothing a) (ConstantInt Nothing b)) = return $ ConstantInt Nothing (a - b) evaluateOp (OpMinus (viewConstantSet -> Just as) (viewConstantSet -> Just bs)) = do let outs = [ a diff --git a/src/Conjure/Language/Expression/Op/Mod.hs b/src/Conjure/Language/Expression/Op/Mod.hs index bb4c37c20d..6aabc26808 100644 --- a/src/Conjure/Language/Expression/Op/Mod.hs +++ b/src/Conjure/Language/Expression/Op/Mod.hs @@ -27,7 +27,7 @@ instance (TypeOf x, Pretty x) => TypeOf (OpMod x) where instance EvaluateOp OpMod where evaluateOp p | any isUndef (childrenBi p) = return $ mkUndef (TypeInt Nothing) $ "Has undefined children:" <+> pretty p evaluateOp p@(OpMod x y) - | y /= 0 = ConstantInt <$> (mod <$> intOut "mod x" x <*> intOut "mod y" y) + | y /= 0 = ConstantInt Nothing <$> (mod <$> intOut "mod x" x <*> intOut "mod y" y) | otherwise = return $ mkUndef (TypeInt Nothing) $ "modulo zero:" <+> pretty p instance SimplifyOp OpMod x where diff --git a/src/Conjure/Language/Expression/Op/Negate.hs b/src/Conjure/Language/Expression/Op/Negate.hs index 4c8df2ed32..70a49a921b 100644 --- a/src/Conjure/Language/Expression/Op/Negate.hs +++ b/src/Conjure/Language/Expression/Op/Negate.hs @@ -23,7 +23,7 @@ instance TypeOf x => TypeOf (OpNegate x) where instance EvaluateOp OpNegate where evaluateOp p | any isUndef (childrenBi p) = return $ mkUndef (TypeInt Nothing) $ "Has undefined children:" <+> pretty p - evaluateOp (OpNegate x) = ConstantInt . negate <$> intOut "OpNegate" x + evaluateOp (OpNegate x) = ConstantInt Nothing . negate <$> intOut "OpNegate" x instance SimplifyOp OpNegate x where simplifyOp _ = na "simplifyOp{OpNegate}" diff --git a/src/Conjure/Language/Expression/Op/Pow.hs b/src/Conjure/Language/Expression/Op/Pow.hs index cf19e7bb51..038e0e191d 100644 --- a/src/Conjure/Language/Expression/Op/Pow.hs +++ b/src/Conjure/Language/Expression/Op/Pow.hs @@ -27,7 +27,7 @@ instance (TypeOf x, Pretty x) => TypeOf (OpPow x) where instance EvaluateOp OpPow where evaluateOp p | any isUndef (childrenBi p) = return $ mkUndef (TypeInt Nothing) $ "Has undefined children:" <+> pretty p evaluateOp p@(OpPow x y) - | y >= 0 = ConstantInt <$> ((^) <$> intOut "pow x" x <*> intOut "pow y" y) + | y >= 0 = ConstantInt Nothing <$> ((^) <$> intOut "pow x" x <*> intOut "pow y" y) | otherwise = return $ mkUndef (TypeInt Nothing) $ "negative exponent:" <+> pretty p instance SimplifyOp OpPow x where diff --git a/src/Conjure/Language/Expression/Op/PreImage.hs b/src/Conjure/Language/Expression/Op/PreImage.hs index f9d96258af..ba0d9de7f8 100644 --- a/src/Conjure/Language/Expression/Op/PreImage.hs +++ b/src/Conjure/Language/Expression/Op/PreImage.hs @@ -38,7 +38,7 @@ instance EvaluateOp OpPreImage where return $ ConstantAbstract $ AbsLitSet [ x | (x,y) <- xs, a == y ] evaluateOp (OpPreImage (viewConstantSequence -> Just xs) a) = return $ ConstantAbstract $ AbsLitSet [ x | (n,y) <- zip allNats xs - , let x = ConstantInt n + , let x = ConstantInt Nothing n , a == y ] evaluateOp op = na $ "evaluateOp{OpPreImage}:" <++> pretty (show op) diff --git a/src/Conjure/Language/Expression/Op/Pred.hs b/src/Conjure/Language/Expression/Op/Pred.hs index ddf20468e8..dc9fbd7eb0 100644 --- a/src/Conjure/Language/Expression/Op/Pred.hs +++ b/src/Conjure/Language/Expression/Op/Pred.hs @@ -31,7 +31,7 @@ instance EvaluateOp OpPred where evaluateOp p | any isUndef (childrenBi p) = return $ mkUndef (TypeInt Nothing) $ "Has undefined children:" <+> pretty p evaluateOp (OpPred (ConstantBool _)) = return (ConstantBool False) -- True --> False -- False --> undef, hence False - evaluateOp (OpPred (ConstantInt x)) = return (ConstantInt (pred x)) + evaluateOp (OpPred (ConstantInt name x)) = return (ConstantInt name (pred x)) evaluateOp op = na $ "evaluateOp{OpPred}" <+> pretty (show op) instance SimplifyOp OpPred x where diff --git a/src/Conjure/Language/Expression/Op/Product.hs b/src/Conjure/Language/Expression/Op/Product.hs index b4171ee935..f7c947c359 100644 --- a/src/Conjure/Language/Expression/Op/Product.hs +++ b/src/Conjure/Language/Expression/Op/Product.hs @@ -41,7 +41,7 @@ instance EvaluateOp OpProduct where evaluateOp p@(OpProduct x) | Just xs <- listOut x , any isUndef xs = return $ mkUndef (TypeInt Nothing) $ "Has undefined children:" <+> pretty p - evaluateOp (OpProduct x) = ConstantInt . product <$> intsOut "OpProduct" x + evaluateOp (OpProduct x) = ConstantInt Nothing . product <$> intsOut "OpProduct" x instance (OpProduct x :< x) => SimplifyOp OpProduct x where simplifyOp (OpProduct x) diff --git a/src/Conjure/Language/Expression/Op/Slicing.hs b/src/Conjure/Language/Expression/Op/Slicing.hs index 2121dc26db..e2cb61b9b4 100644 --- a/src/Conjure/Language/Expression/Op/Slicing.hs +++ b/src/Conjure/Language/Expression/Op/Slicing.hs @@ -32,11 +32,11 @@ instance EvaluateOp OpSlicing where indexVals <- valuesInIntDomain index outVals <- fmap catMaybes $ forM (zip indexVals vals) $ \ (thisIndex, thisVal) -> case lb of - Just (ConstantInt lower) | lower > thisIndex -> return Nothing + Just (ConstantInt Nothing lower) | lower > thisIndex -> return Nothing _ -> case ub of - Just (ConstantInt upper) | upper < thisIndex -> return Nothing + Just (ConstantInt Nothing upper) | upper < thisIndex -> return Nothing _ -> return $ Just (thisIndex, thisVal) - let outDomain = DomainInt Nothing $ map (RangeSingle . ConstantInt . fst) outVals + let outDomain = DomainInt Nothing $ map (RangeSingle . ConstantInt Nothing . fst) outVals return $ ConstantAbstract $ AbsLitMatrix outDomain (map snd outVals) evaluateOp op = na $ "evaluateOp{OpSlicing}:" <++> pretty (show op) diff --git a/src/Conjure/Language/Expression/Op/Succ.hs b/src/Conjure/Language/Expression/Op/Succ.hs index be01ebdeae..cc5e6a0175 100644 --- a/src/Conjure/Language/Expression/Op/Succ.hs +++ b/src/Conjure/Language/Expression/Op/Succ.hs @@ -31,7 +31,7 @@ instance EvaluateOp OpSucc where evaluateOp p | any isUndef (childrenBi p) = return $ mkUndef (TypeInt Nothing) $ "Has undefined children:" <+> pretty p evaluateOp (OpSucc (ConstantBool False)) = return (ConstantBool True) evaluateOp (OpSucc (ConstantBool True )) = return (ConstantBool False) -- undef - evaluateOp (OpSucc (ConstantInt x)) = return (ConstantInt (succ x)) + evaluateOp (OpSucc (ConstantInt name x)) = return (ConstantInt name (succ x)) evaluateOp op = na $ "evaluateOp{OpSucc}" <+> pretty (show op) instance SimplifyOp OpSucc x where diff --git a/src/Conjure/Language/Expression/Op/Sum.hs b/src/Conjure/Language/Expression/Op/Sum.hs index 77eb0fc290..865245e644 100644 --- a/src/Conjure/Language/Expression/Op/Sum.hs +++ b/src/Conjure/Language/Expression/Op/Sum.hs @@ -41,7 +41,7 @@ instance EvaluateOp OpSum where evaluateOp p@(OpSum x) | Just xs <- listOut x , any isUndef xs = return $ mkUndef (TypeInt Nothing) $ "Has undefined children:" <+> pretty p - evaluateOp (OpSum x) = ConstantInt . sum <$> intsOut "OpSum" x + evaluateOp (OpSum x) = ConstantInt Nothing . sum <$> intsOut "OpSum" x instance (OpSum x :< x) => SimplifyOp OpSum x where simplifyOp (OpSum x) diff --git a/src/Conjure/Language/Expression/Op/TildeLt.hs b/src/Conjure/Language/Expression/Op/TildeLt.hs index a738238e10..7f43995d7b 100644 --- a/src/Conjure/Language/Expression/Op/TildeLt.hs +++ b/src/Conjure/Language/Expression/Op/TildeLt.hs @@ -33,7 +33,7 @@ instance EvaluateOp OpTildeLt where tupleE (i,j) = ConstantAbstract $ AbsLitTuple [i,j] tilLt (ConstantBool a) (ConstantBool b) = a < b - tilLt (ConstantInt a) (ConstantInt b) = a < b + tilLt (ConstantInt Nothing a) (ConstantInt Nothing b) = a < b tilLt (viewConstantTuple -> Just []) (viewConstantTuple -> Just []) = False tilLt (viewConstantTuple -> Just (a:as)) diff --git a/src/Conjure/Language/Expression/Op/ToInt.hs b/src/Conjure/Language/Expression/Op/ToInt.hs index 6e3d02c649..ef90e8a001 100644 --- a/src/Conjure/Language/Expression/Op/ToInt.hs +++ b/src/Conjure/Language/Expression/Op/ToInt.hs @@ -30,9 +30,9 @@ instance (TypeOf x, Pretty x) => TypeOf (OpToInt x) where ] instance EvaluateOp OpToInt where - evaluateOp (OpToInt (ConstantBool False)) = return (ConstantInt 0) - evaluateOp (OpToInt (ConstantBool True )) = return (ConstantInt 1) - evaluateOp (OpToInt ConstantUndefined{}) = return (ConstantInt 0) + evaluateOp (OpToInt (ConstantBool False)) = return (ConstantInt Nothing 0) + evaluateOp (OpToInt (ConstantBool True )) = return (ConstantInt Nothing 1) + evaluateOp (OpToInt ConstantUndefined{}) = return (ConstantInt Nothing 0) evaluateOp op = na $ "evaluateOp{OpToInt}:" <++> pretty (show op) instance SimplifyOp OpToInt x where diff --git a/src/Conjure/Language/Expression/Op/TwoBars.hs b/src/Conjure/Language/Expression/Op/TwoBars.hs index 0c28e4fd70..dce2376579 100644 --- a/src/Conjure/Language/Expression/Op/TwoBars.hs +++ b/src/Conjure/Language/Expression/Op/TwoBars.hs @@ -42,19 +42,19 @@ instance EvaluateOp OpTwoBars where evaluateOp (OpTwoBars x) = case x of -- absolute value - ConstantInt y -> return $ ConstantInt $ abs y + ConstantInt Nothing y -> return $ ConstantInt Nothing $ abs y -- cardinality of a constant - (viewConstantMatrix -> Just (_, xs)) -> return $ ConstantInt $ genericLength xs - (viewConstantSet -> Just xs) -> return $ ConstantInt $ genericLength $ sortNub xs - (viewConstantMSet -> Just xs) -> return $ ConstantInt $ genericLength xs - (viewConstantFunction -> Just xs) -> return $ ConstantInt $ genericLength $ sortNub xs - (viewConstantSequence -> Just xs) -> return $ ConstantInt $ genericLength xs - (viewConstantRelation -> Just xs) -> return $ ConstantInt $ genericLength $ sortNub xs - (viewConstantPartition -> Just xs) -> return $ ConstantInt $ genericLength $ sortNub $ concat xs + (viewConstantMatrix -> Just (_, xs)) -> return $ ConstantInt Nothing $ genericLength xs + (viewConstantSet -> Just xs) -> return $ ConstantInt Nothing $ genericLength $ sortNub xs + (viewConstantMSet -> Just xs) -> return $ ConstantInt Nothing $ genericLength xs + (viewConstantFunction -> Just xs) -> return $ ConstantInt Nothing $ genericLength $ sortNub xs + (viewConstantSequence -> Just xs) -> return $ ConstantInt Nothing $ genericLength xs + (viewConstantRelation -> Just xs) -> return $ ConstantInt Nothing $ genericLength $ sortNub xs + (viewConstantPartition -> Just xs) -> return $ ConstantInt Nothing $ genericLength $ sortNub $ concat xs -- cardinality of a domain - DomainInConstant (DomainInt _ rs) -> ConstantInt . genericLength <$> rangesInts rs + DomainInConstant (DomainInt _ rs) -> ConstantInt Nothing . genericLength <$> rangesInts rs DomainInConstant dom -> runNameGen () $ domainSizeOf dom _ -> na $ "evaluateOp OpTwoBars" <+> pretty (show x) diff --git a/src/Conjure/Language/Instantiate.hs b/src/Conjure/Language/Instantiate.hs index 768b23a4c8..9ade3e4cbe 100644 --- a/src/Conjure/Language/Instantiate.hs +++ b/src/Conjure/Language/Instantiate.hs @@ -245,7 +245,7 @@ instantiateD (DomainEnum nm rs0 _) = do |> fmap4 e2c' st <- gets id mp <- forM (universeBi rs :: [Name]) $ \ n -> case lookup n st of - Just (Constant (ConstantInt i)) -> return (n, i) + Just (Constant (ConstantInt _ i)) -> return (n, i) Nothing -> fail $ "No value for member of enum domain:" <+> pretty n Just _ -> fail $ "Incompatible value for member of enum domain:" <+> pretty n return (DomainEnum nm (rs :: Maybe [Range Constant]) (Just mp)) diff --git a/src/Conjure/Language/Lenses.hs b/src/Conjure/Language/Lenses.hs index 2b7515b870..0331b92876 100644 --- a/src/Conjure/Language/Lenses.hs +++ b/src/Conjure/Language/Lenses.hs @@ -1166,9 +1166,9 @@ constantInt , Expression -> m Integer ) constantInt _ = - ( Constant . ConstantInt + ( Constant . ConstantInt Nothing , \ p -> case p of - (Constant (ConstantInt i)) -> return i + (Constant (ConstantInt Nothing i)) -> return i _ -> na ("Lenses.constantInt:" <++> pretty p) ) diff --git a/src/Conjure/Language/NameResolution.hs b/src/Conjure/Language/NameResolution.hs index 9ca4d46a81..5a51bc05a8 100644 --- a/src/Conjure/Language/NameResolution.hs +++ b/src/Conjure/Language/NameResolution.hs @@ -101,7 +101,7 @@ resolveStatement st = modify ((nm, Alias (Domain (DomainUnnamed nm x'))) :) return (Declaration (LettingDomainDefnUnnamed nm x')) LettingDomainDefnEnum _ nms -> do - modify ( [ (nm, Alias (Constant (ConstantInt i))) + modify ( [ (nm, Alias (Constant (ConstantInt (Just nm) i))) | (nm, i) <- zip nms [1..] ] ++) return st diff --git a/src/Conjure/Language/Parser.hs b/src/Conjure/Language/Parser.hs index 77ea60ea58..8ce3e9f7be 100644 --- a/src/Conjure/Language/Parser.hs +++ b/src/Conjure/Language/Parser.hs @@ -930,7 +930,7 @@ parseLiteral = label "value" $ msum True <$ lexeme L_true return (ConstantBool x) - pInt = ConstantInt . fromInteger <$> integer + pInt = ConstantInt Nothing . fromInteger <$> integer pMatrix = do lexeme L_OpenBracket diff --git a/src/Conjure/Language/ParserC.hs b/src/Conjure/Language/ParserC.hs index 876d684cb7..0442c0d9c6 100644 --- a/src/Conjure/Language/ParserC.hs +++ b/src/Conjure/Language/ParserC.hs @@ -515,7 +515,7 @@ parseLiteral = label "value" (do p <- pCore ; p) pCore = satisfyL $ \case L_false -> Just $ return $ Constant $ ConstantBool False L_true -> Just $ return $ Constant $ ConstantBool True - LIntLiteral i -> Just $ return $ Constant $ ConstantInt (fromInteger i) + LIntLiteral i -> Just $ return $ Constant $ ConstantInt Nothing (fromInteger i) L_OpenBracket -> Just pMatrix L_tuple -> Just pTupleWith L_OpenParen -> Just pTupleWithout diff --git a/src/Conjure/Language/ZeroVal.hs b/src/Conjure/Language/ZeroVal.hs index 97fdfba7c6..d255b36334 100644 --- a/src/Conjure/Language/ZeroVal.hs +++ b/src/Conjure/Language/ZeroVal.hs @@ -11,8 +11,8 @@ import Conjure.Process.Enumerate ( EnumerateDomain, enumerateDomain ) zeroVal :: (MonadFail m, EnumerateDomain m, Pretty r) => Domain r Constant -> m Constant zeroVal DomainBool = return $ ConstantBool False -zeroVal (DomainInt _ []) = return $ ConstantInt 0 -zeroVal (DomainInt _ (r:_)) = zeroValR r +zeroVal (DomainInt Nothing []) = return $ ConstantInt Nothing 0 +zeroVal (DomainInt Nothing (r:_)) = zeroValR r zeroVal (DomainTuple ds) = ConstantAbstract . AbsLitTuple <$> mapM zeroVal ds zeroVal (DomainRecord xs) = do values <- forM xs $ \ (nm, dom) -> do @@ -81,5 +81,5 @@ getMin d (SizeAttr_MinMaxSize x _) = returnInt d x returnInt :: (MonadFail m, Pretty r, Pretty x) => Domain r x -> Constant -> m Integer -returnInt _ (ConstantInt x) = return x +returnInt _ (ConstantInt _ x) = return x returnInt d _ = fail $ "Attribute expected to be an int in:" <+> pretty d diff --git a/src/Conjure/Process/Enumerate.hs b/src/Conjure/Process/Enumerate.hs index ace8af8169..595e6585a9 100644 --- a/src/Conjure/Process/Enumerate.hs +++ b/src/Conjure/Process/Enumerate.hs @@ -92,7 +92,7 @@ enumerateDomain d | not (null [ () | ConstantUndefined{} <- universeBi d ]) = enumerateDomain DomainBool = return [ConstantBool False, ConstantBool True] enumerateDomain (DomainInt _ []) = fail "enumerateDomain: infinite domain" enumerateDomain (DomainInt Nothing rs) = concatMapM enumerateRange rs -enumerateDomain (DomainUnnamed _ (ConstantInt n)) = return (map ConstantInt [1..n]) +enumerateDomain (DomainUnnamed nm (ConstantInt _ n)) = return (map (ConstantInt (Just nm)) [1..n]) enumerateDomain (DomainEnum _dName (Just rs) _mp) = concatMapM enumerateRange rs enumerateDomain (DomainTuple ds) = do inners <- mapM enumerateDomain ds @@ -193,7 +193,7 @@ enumerateDomain d = liftIO' $ withSystemTempDirectory ("conjure-enumerateDomain- enumerateRange :: MonadFail m => Range Constant -> m [Constant] enumerateRange (RangeSingle x) = return [x] -enumerateRange (RangeBounded (ConstantInt x) (ConstantInt y)) = return $ map ConstantInt [x..y] +enumerateRange (RangeBounded (ConstantInt Nothing x) (ConstantInt Nothing y)) = return $ map (ConstantInt Nothing) [x..y] enumerateRange RangeBounded{} = fail "enumerateRange RangeBounded" enumerateRange RangeOpen{} = fail "enumerateRange RangeOpen" enumerateRange RangeLowerBounded{} = fail "enumerateRange RangeLowerBounded" diff --git a/src/Conjure/Process/Enums.hs b/src/Conjure/Process/Enums.hs index 9f995972d3..01ff427981 100644 --- a/src/Conjure/Process/Enums.hs +++ b/src/Conjure/Process/Enums.hs @@ -188,14 +188,15 @@ addEnumsAndUnnamedsBack unnameds ctxt = helper (DomainIntE{}, c) -> c (DomainInt{} , c) -> c - (DomainEnum ename _ _, ConstantInt i) -> - fromMaybe (bug $ "addEnumsAndUnnamedsBack 1:" <+> pretty (i, ename)) - (lookup (i, ename) ctxt) + (DomainEnum ename _ _, ConstantInt nname i) -> + if (Just ename) == nname + then fromMaybe (bug $ "addEnumsAndUnnamedsBack 1:" <+> pretty (i, ename)) (lookup (i, ename) ctxt) + else bug $ "addEnumsAndUnnamedsBack 1: ConstantInt tag didn't match" <+> pretty (i, ename) - (DomainReference ename _ , ConstantInt i) -> + (DomainReference ename _ , ConstantInt nname i) -> if ename `elem` unnameds then ConstantEnum ename [] (mconcat [ename, "_", Name (T.pack (show i))]) - else ConstantInt i -- assume this was an int if if is not in the unnameds list + else ConstantInt nname i -- assume this was an int if if is not in the unnameds list (DomainTuple ds, ConstantAbstract (AbsLitTuple cs)) -> ConstantAbstract $ AbsLitTuple diff --git a/src/Conjure/Process/FiniteGivens.hs b/src/Conjure/Process/FiniteGivens.hs index 45cab08ec6..c52c1ba18c 100644 --- a/src/Conjure/Process/FiniteGivens.hs +++ b/src/Conjure/Process/FiniteGivens.hs @@ -211,7 +211,7 @@ mkFiniteOutermost (DomainSet () _ inner) = do set <- failToUserError $ viewConstantSet constant let setSize = genericLength set innerValues <- innerF set - return $ innerValues ++ [(s, ConstantInt setSize)] + return $ innerValues ++ [(s, ConstantInt Nothing setSize)] ) mkFiniteOutermost (DomainMSet () attr@(MSetAttr SizeAttr_Size{} _) inner) = do (inner', innerExtras, innerF) <- mkFiniteInner inner @@ -235,7 +235,7 @@ mkFiniteOutermost (DomainMSet () (MSetAttr _ occurAttr) inner) = do set <- failToUserError $ viewConstantMSet constant let setSize = genericLength set innerValues <- innerF set - return $ innerValues ++ [(s, ConstantInt setSize)] + return $ innerValues ++ [(s, ConstantInt Nothing setSize)] ) mkFiniteOutermost (DomainSequence () attr@(SequenceAttr SizeAttr_Size{} _) inner) = do (inner', innerExtras, innerF) <- mkFiniteInner inner @@ -259,7 +259,7 @@ mkFiniteOutermost (DomainSequence () (SequenceAttr _ jectivityAttr) inner) = do set <- failToUserError $ viewConstantSequence constant let setSize = genericLength set innerValues <- innerF set - return $ innerValues ++ [(s, ConstantInt setSize)] + return $ innerValues ++ [(s, ConstantInt Nothing setSize)] ) mkFiniteOutermost (DomainFunction () attr@(FunctionAttr SizeAttr_Size{} _ _) innerFr innerTo) = do (innerFr', innerFrExtras, innerFrF) <- mkFiniteInner innerFr @@ -289,7 +289,7 @@ mkFiniteOutermost (DomainFunction () (FunctionAttr _ partialityAttr jectivityAtt let functionSize = genericLength function innerFrValues <- innerFrF (map fst function) innerToValues <- innerToF (map snd function) - return $ innerFrValues ++ innerToValues ++ [(s, ConstantInt functionSize)] + return $ innerFrValues ++ innerToValues ++ [(s, ConstantInt Nothing functionSize)] ) mkFiniteOutermost (DomainRelation () attr@(RelationAttr SizeAttr_Size{} _) inners) = do (inners', innersExtras, innersF) <- unzip3 <$> mapM mkFiniteInner inners @@ -315,7 +315,7 @@ mkFiniteOutermost (DomainRelation () (RelationAttr _ binRelAttr) inners) = do relation <- failToUserError $ viewConstantRelation constant let relationSize = genericLength relation innersValues <- zipWithM ($) innersF (transpose relation) - return $ concat innersValues ++ [(s, ConstantInt relationSize)] + return $ concat innersValues ++ [(s, ConstantInt Nothing relationSize)] ) mkFiniteOutermost (DomainPartition () attr@(PartitionAttr SizeAttr_Size{} SizeAttr_Size{} _) inner) = do (inner', innerExtras, innerF) <- mkFiniteInner inner @@ -345,8 +345,8 @@ mkFiniteOutermost (DomainPartition () (PartitionAttr _ _ isRegularAttr) inner) = let numPartsVal = genericLength parts let partsSizeVal = maximum0 $ map genericLength parts innerValues <- mapM innerF parts - return $ concat innerValues ++ [ (numPartsFin, ConstantInt numPartsVal) - , (partsSizeFin, ConstantInt partsSizeVal) + return $ concat innerValues ++ [ (numPartsFin, ConstantInt Nothing numPartsVal) + , (partsSizeFin, ConstantInt Nothing partsSizeVal) ] ) mkFiniteOutermost d = return (d, [], const (return [])) @@ -374,8 +374,8 @@ mkFiniteInner (DomainInt name []) = do , \ constants -> do logDebug $ "mkFiniteInner DomainInt" <+> vcat (map pretty constants) ints <- failToUserError $ mapM viewConstantInt constants - return [ (fr, ConstantInt (minimum ints)) - , (to, ConstantInt (maximum0 ints)) + return [ (fr, ConstantInt Nothing (minimum ints)) + , (to, ConstantInt Nothing (maximum0 ints)) ] ) mkFiniteInner (DomainInt name [RangeLowerBounded low]) = do @@ -386,7 +386,7 @@ mkFiniteInner (DomainInt name [RangeLowerBounded low]) = do , \ constants -> do logDebug $ "mkFiniteInner DomainInt" <+> vcat (map pretty constants) ints <- failToUserError $ mapM viewConstantInt constants - return [ (new, ConstantInt (maximum0 ints)) ] + return [ (new, ConstantInt Nothing (maximum0 ints)) ] ) mkFiniteInner (DomainInt name [RangeUpperBounded upp]) = do new <- nextName "fin" @@ -396,7 +396,7 @@ mkFiniteInner (DomainInt name [RangeUpperBounded upp]) = do , \ constants -> do logDebug $ "mkFiniteInner DomainInt" <+> vcat (map pretty constants) ints <- failToUserError $ mapM viewConstantInt constants - return [ (new, ConstantInt (minimum ints)) ] + return [ (new, ConstantInt Nothing (minimum ints)) ] ) mkFiniteInner (DomainTuple inners) = do mids <- mapM mkFiniteInner inners @@ -476,7 +476,7 @@ mkFiniteInner (DomainSet () _ inner) = do sets <- failToUserError $ mapM viewConstantSet constants let setMaxSize = maximum0 $ map genericLength sets innerValues <- innerF (concat sets) - return $ innerValues ++ [(s, ConstantInt setMaxSize)] + return $ innerValues ++ [(s, ConstantInt Nothing setMaxSize)] ) mkFiniteInner (DomainMSet () attr@(MSetAttr SizeAttr_Size{} _) inner) = do (inner', innerExtras, innerF) <- mkFiniteInner inner @@ -499,7 +499,7 @@ mkFiniteInner (DomainMSet () (MSetAttr _ occurAttr) inner) = do sets <- failToUserError $ mapM viewConstantMSet constants let setMaxSize = maximum0 $ map genericLength sets innerValues <- innerF (concat sets) - return $ innerValues ++ [(s, ConstantInt setMaxSize)] + return $ innerValues ++ [(s, ConstantInt Nothing setMaxSize)] ) mkFiniteInner (DomainSequence () attr@(SequenceAttr SizeAttr_Size{} _) inner) = do (inner', innerExtras, innerF) <- mkFiniteInner inner @@ -522,7 +522,7 @@ mkFiniteInner (DomainSequence () (SequenceAttr _ jectivityAttr) inner) = do seqs <- failToUserError $ mapM viewConstantSequence constants let seqMaxSize = maximum0 $ map genericLength seqs innerValues <- innerF (concat seqs) - return $ innerValues ++ [(s, ConstantInt seqMaxSize)] + return $ innerValues ++ [(s, ConstantInt Nothing seqMaxSize)] ) mkFiniteInner (DomainFunction () attr@(FunctionAttr SizeAttr_Size{} _ _) innerFr innerTo) = do (innerFr', innerFrExtras, innerFrF) <- mkFiniteInner innerFr @@ -552,7 +552,7 @@ mkFiniteInner (DomainFunction () (FunctionAttr _ partialityAttr jectivityAttr) i let functionMaxSize = maximum0 $ map genericLength functions innerFrValues <- innerFrF (map fst (concat functions)) innerToValues <- innerToF (map snd (concat functions)) - return $ innerFrValues ++ innerToValues ++ [(s, ConstantInt functionMaxSize)] + return $ innerFrValues ++ innerToValues ++ [(s, ConstantInt Nothing functionMaxSize)] ) mkFiniteInner (DomainRelation () attr@(RelationAttr SizeAttr_Size{} _) inners) = do (inners', innersExtras, innersF) <- unzip3 <$> mapM mkFiniteInner inners @@ -578,7 +578,7 @@ mkFiniteInner (DomainRelation () (RelationAttr _ binRelAttr) inners) = do relations <- failToUserError $ mapM viewConstantRelation constants let relationMaxSize = maximum0 $ map genericLength relations innersValues <- zipWithM ($) innersF (transpose $ concat relations) - return $ concat innersValues ++ [(s, ConstantInt relationMaxSize)] + return $ concat innersValues ++ [(s, ConstantInt Nothing relationMaxSize)] ) mkFiniteInner (DomainPartition () attr@(PartitionAttr SizeAttr_Size{} SizeAttr_Size{} _) inner) = do (inner', innerExtras, innerF) <- mkFiniteInner inner @@ -608,8 +608,8 @@ mkFiniteInner (DomainPartition () (PartitionAttr _ _ isRegularAttr) inner) = do let numPartsVal = maximum0 $ map genericLength parts let partsSizeVal = maximum0 $ map genericLength parts innerValues <- mapM innerF (concat parts) - return $ concat innerValues ++ [ (numPartsFin, ConstantInt numPartsVal) - , (partsSizeFin, ConstantInt partsSizeVal) + return $ concat innerValues ++ [ (numPartsFin, ConstantInt Nothing numPartsVal) + , (partsSizeFin, ConstantInt Nothing partsSizeVal) ] ) mkFiniteInner d = return (d, [], const (return [])) diff --git a/src/Conjure/Process/InferAttributes.hs b/src/Conjure/Process/InferAttributes.hs index c030c98b92..fa8e3f4a3a 100644 --- a/src/Conjure/Process/InferAttributes.hs +++ b/src/Conjure/Process/InferAttributes.hs @@ -33,7 +33,7 @@ inferAttributes = flip evalStateT [] . go where x' <- resolveX x modify ((nm, Alias (Domain (DomainUnnamed nm x'))) :) LettingDomainDefnEnum _ nms -> do - modify ( [ (nm, Alias (Constant (ConstantInt i))) + modify ( [ (nm, Alias (Constant (ConstantInt (Just nm) i))) | (nm, i) <- zip nms [1..] ] ++) GivenDomainDefnEnum{} -> return () -- ignoring diff --git a/src/Conjure/Representations/Function/Function1D.hs b/src/Conjure/Representations/Function/Function1D.hs index 5fe758b50c..a67c55ad02 100644 --- a/src/Conjure/Representations/Function/Function1D.hs +++ b/src/Conjure/Representations/Function/Function1D.hs @@ -178,5 +178,5 @@ domainValues :: (MonadFail m, Pretty r) => Domain r Constant -> m [Constant] domainValues dom = case dom of DomainBool -> return [ConstantBool False, ConstantBool True] - DomainInt Nothing rs -> map ConstantInt <$> valuesInIntDomain rs + DomainInt name rs -> map (ConstantInt name) <$> valuesInIntDomain rs _ -> fail ("domainValues, not supported:" <+> pretty dom) diff --git a/src/Conjure/Representations/MSet/ExplicitWithFlags.hs b/src/Conjure/Representations/MSet/ExplicitWithFlags.hs index 65c93c95a3..f26926ed51 100644 --- a/src/Conjure/Representations/MSet/ExplicitWithFlags.hs +++ b/src/Conjure/Representations/MSet/ExplicitWithFlags.hs @@ -138,7 +138,7 @@ msetExplicitWithFlags = Representation chck downD structuralCons downC up maxSizeInt <- case maxSize of - ConstantInt x -> return x + ConstantInt Nothing x -> return x _ -> fail $ vcat [ "Expecting an integer for the maxSize attribute." , "But got:" <+> pretty maxSize @@ -148,8 +148,8 @@ msetExplicitWithFlags = Representation chck downD structuralCons downC up z <- zeroVal innerDomain let zeroes = replicate (fromInteger (maxSizeInt - genericLength constants)) z - let counts = map (ConstantInt . snd) constants - let falses = replicate (fromInteger (maxSizeInt - genericLength constants)) (ConstantInt 0) + let counts = map (ConstantInt Nothing . snd) constants + let falses = replicate (fromInteger (maxSizeInt - genericLength constants)) (ConstantInt Nothing 0) return $ Just [ ( nameFlag domain name @@ -174,7 +174,7 @@ msetExplicitWithFlags = Representation chck downD structuralCons downC up Just (_, vals) -> return (name, ConstantAbstract $ AbsLitMSet $ concat [ replicate (fromInteger i) v - | (ConstantInt i,v) <- zip flags vals + | (ConstantInt Nothing i,v) <- zip flags vals ] ) _ -> fail $ vcat [ "Expecting a matrix literal for:" <+> pretty (nameValues domain name) diff --git a/src/Conjure/Representations/MSet/ExplicitWithRepetition.hs b/src/Conjure/Representations/MSet/ExplicitWithRepetition.hs index 826137e68b..269b5062a1 100644 --- a/src/Conjure/Representations/MSet/ExplicitWithRepetition.hs +++ b/src/Conjure/Representations/MSet/ExplicitWithRepetition.hs @@ -144,7 +144,7 @@ msetExplicitWithRepetition = Representation chck downD structuralCons downC up return $ Just [ ( nameFlag domain name , defRepr flagDomain - , ConstantInt (genericLength constants) + , ConstantInt Nothing (genericLength constants) ) , ( nameValues domain name , DomainMatrix indexDomain innerDomain @@ -156,7 +156,7 @@ msetExplicitWithRepetition = Representation chck downD structuralCons downC up maxSize <- getMaxSize attrs innerDomain maxSizeInt <- case maxSize of - ConstantInt x -> return x + ConstantInt Nothing x -> return x _ -> fail $ vcat [ "Expecting an integer for the maxSize attribute." , "But got:" <+> pretty maxSize @@ -172,7 +172,7 @@ msetExplicitWithRepetition = Representation chck downD structuralCons downC up return $ Just [ ( nameFlag domain name , defRepr flagDomain - , ConstantInt (genericLength constants) + , ConstantInt Nothing (genericLength constants) ) , ( nameValues domain name , DomainMatrix indexDomain innerDomain diff --git a/src/Conjure/Representations/Partition/Occurrence.hs b/src/Conjure/Representations/Partition/Occurrence.hs index 611d68b91e..a45d503c4c 100644 --- a/src/Conjure/Representations/Partition/Occurrence.hs +++ b/src/Conjure/Representations/Partition/Occurrence.hs @@ -241,15 +241,15 @@ partitionOccurrence = Representation chck downD structuralCons downC up , mem `elem` pVals ] ] - numPartsVal = ConstantInt (genericLength vals) + numPartsVal = ConstantInt Nothing (genericLength vals) whichPartVal = ConstantAbstract (AbsLitMatrix (forgetRepr innerDomain) - (map (ConstantInt . fst) whichPartValInside)) + (map (ConstantInt Nothing . fst) whichPartValInside)) partSizesVal = ConstantAbstract (AbsLitMatrix (DomainInt Nothing [RangeBounded 1 maxNumParts']) - (map (ConstantInt . genericLength) vals + (map (ConstantInt Nothing . genericLength) vals ++ replicate (fromInteger (maxNumParts - genericLength vals)) - (ConstantInt 0))) + (ConstantInt Nothing 0))) firstIndexVal = ConstantAbstract (AbsLitMatrix (DomainInt Nothing [RangeBounded 1 maxNumParts']) ([ case lookup p whichPartValInside of @@ -281,7 +281,7 @@ partitionOccurrence = Representation chck downD structuralCons downC up return ( name , normaliseConstant $ ConstantAbstract $ AbsLitPartition - [ [ member | (member, b) <- zip members whichPartValues, b == ConstantInt bucket ] + [ [ member | (member, b) <- zip members whichPartValues, b == ConstantInt Nothing bucket ] | bucket <- [1..numPartsValue] ] ) diff --git a/src/Conjure/Representations/Sequence/ExplicitBounded.hs b/src/Conjure/Representations/Sequence/ExplicitBounded.hs index f10462bd47..162ef8f45c 100644 --- a/src/Conjure/Representations/Sequence/ExplicitBounded.hs +++ b/src/Conjure/Representations/Sequence/ExplicitBounded.hs @@ -194,7 +194,7 @@ sequenceExplicitBounded = Representation chck downD structuralCons downC up return $ Just [ ( nameMarker domain name , DomainInt Nothing [RangeBounded size size] - , ConstantInt (genericLength constants) + , ConstantInt Nothing (genericLength constants) ) , ( nameValues domain name , DomainMatrix (DomainInt Nothing [RangeBounded 1 size]) innerDomain @@ -209,7 +209,7 @@ sequenceExplicitBounded = Representation chck downD structuralCons downC up let indexDomain i = mkDomainIntB (fromInt i) maxSize maxSizeInt <- case maxSize of - ConstantInt x -> return x + ConstantInt Nothing x -> return x _ -> fail $ vcat [ "Expecting an integer for the maxSize attribute." , "But got:" <+> pretty maxSize @@ -221,7 +221,7 @@ sequenceExplicitBounded = Representation chck downD structuralCons downC up return $ Just [ ( nameMarker domain name , defRepr (indexDomain 0) - , ConstantInt (genericLength constants) + , ConstantInt Nothing (genericLength constants) ) , ( nameValues domain name , DomainMatrix (indexDomain 1) innerDomain @@ -239,7 +239,7 @@ sequenceExplicitBounded = Representation chck downD structuralCons downC up case (lookup (nameMarker domain name) ctxt, lookup (nameValues domain name) ctxt) of (Just marker, Just constantMatrix) -> case marker of - ConstantInt card -> + ConstantInt Nothing card -> case viewConstantMatrix constantMatrix of Just (_, vals) -> return (name, ConstantAbstract (AbsLitSequence (genericTake card vals))) diff --git a/src/Conjure/Representations/Set/ExplicitVarSizeWithDummy.hs b/src/Conjure/Representations/Set/ExplicitVarSizeWithDummy.hs index 87a20cdff2..29e7d94d4d 100644 --- a/src/Conjure/Representations/Set/ExplicitVarSizeWithDummy.hs +++ b/src/Conjure/Representations/Set/ExplicitVarSizeWithDummy.hs @@ -46,12 +46,12 @@ setExplicitVarSizeWithDummy = Representation chck downD structuralCons downC up calcDummyElemC :: Pretty r => Domain r Constant -> Constant calcDummyElemC (DomainInt _ []) = bug "ExplicitVarSizeWithDummy.calcDummyElemC []" - calcDummyElemC (DomainInt _ rs) = ConstantInt $ + calcDummyElemC (DomainInt _ rs) = ConstantInt Nothing $ 1 + maximum [ i | r <- rs , i <- case r of - RangeSingle (ConstantInt x) -> [x] - RangeBounded (ConstantInt x) (ConstantInt y) -> [x..y] + RangeSingle (ConstantInt Nothing x) -> [x] + RangeBounded (ConstantInt Nothing x) (ConstantInt Nothing y) -> [x..y] _ -> bug ("ExplicitVarSizeWithDummy.calcDummyElemC" <+> pretty r) ] calcDummyElemC d = bug ("ExplicitVarSizeWithDummy.calcDummyElemC" <+> pretty d) @@ -127,7 +127,7 @@ setExplicitVarSizeWithDummy = Representation chck downD structuralCons downC up let indexDomain i = mkDomainIntB (fromInt i) maxSize maxSizeInt <- case maxSize of - ConstantInt x -> return x + ConstantInt Nothing x -> return x _ -> fail $ vcat [ "Expecting an integer for the maxSize attribute." , "But got:" <+> pretty maxSize diff --git a/src/Conjure/Representations/Set/ExplicitVarSizeWithFlags.hs b/src/Conjure/Representations/Set/ExplicitVarSizeWithFlags.hs index 8e91a409cb..d2002a6dbd 100644 --- a/src/Conjure/Representations/Set/ExplicitVarSizeWithFlags.hs +++ b/src/Conjure/Representations/Set/ExplicitVarSizeWithFlags.hs @@ -111,7 +111,7 @@ setExplicitVarSizeWithFlags = Representation chck downD structuralCons downC up maxSizeInt <- case maxSize of - ConstantInt x -> return x + ConstantInt Nothing x -> return x _ -> fail $ vcat [ "Expecting an integer for the maxSize attribute." , "But got:" <+> pretty maxSize diff --git a/src/Conjure/Representations/Set/ExplicitVarSizeWithMarker.hs b/src/Conjure/Representations/Set/ExplicitVarSizeWithMarker.hs index f291dc1f30..522201a4d5 100644 --- a/src/Conjure/Representations/Set/ExplicitVarSizeWithMarker.hs +++ b/src/Conjure/Representations/Set/ExplicitVarSizeWithMarker.hs @@ -99,7 +99,7 @@ setExplicitVarSizeWithMarker = Representation chck downD structuralCons downC up let indexDomain i = mkDomainIntB (fromInt i) maxSize maxSizeInt <- case maxSize of - ConstantInt x -> return x + ConstantInt Nothing x -> return x _ -> fail $ vcat [ "Expecting an integer for the maxSize attribute." , "But got:" <+> pretty maxSize @@ -111,7 +111,7 @@ setExplicitVarSizeWithMarker = Representation chck downD structuralCons downC up return $ Just [ ( nameMarker domain name , defRepr (indexDomain 0) - , ConstantInt (genericLength constants) + , ConstantInt Nothing (genericLength constants) ) , ( nameValues domain name , DomainMatrix (indexDomain 1) innerDomain @@ -125,7 +125,7 @@ setExplicitVarSizeWithMarker = Representation chck downD structuralCons downC up case (lookup (nameMarker domain name) ctxt, lookup (nameValues domain name) ctxt) of (Just marker, Just constantMatrix) -> case marker of - ConstantInt card -> + ConstantInt Nothing card -> case (viewConstantMatrix constantMatrix, constantMatrix) of (Just (_, vals), _) -> return (name, ConstantAbstract (AbsLitSet (genericTake card vals))) diff --git a/src/Conjure/Representations/Set/Occurrence.hs b/src/Conjure/Representations/Set/Occurrence.hs index 523106c8fe..48b02767c1 100644 --- a/src/Conjure/Representations/Set/Occurrence.hs +++ b/src/Conjure/Representations/Set/Occurrence.hs @@ -58,7 +58,7 @@ setOccurrence = Representation chck downD structuralCons downC up , ConstantAbstract $ AbsLitMatrix (forgetRepr innerDomain) [ ConstantBool isIn | v <- innerDomainVals - , let isIn = ConstantInt v `elem` constants + , let isIn = ConstantInt Nothing v `elem` constants ] ) ] @@ -73,7 +73,7 @@ setOccurrence = Representation chck downD structuralCons downC up Just (_, vals) -> do innerDomainVals <- valuesInIntDomain intRanges return (name, ConstantAbstract $ AbsLitSet - [ ConstantInt v + [ ConstantInt Nothing v | (v,b) <- zip innerDomainVals vals , viewConstantBool b == Just True ] ) diff --git a/src/Conjure/Representations/Variant.hs b/src/Conjure/Representations/Variant.hs index 48145aa51f..217e5231e6 100644 --- a/src/Conjure/Representations/Variant.hs +++ b/src/Conjure/Representations/Variant.hs @@ -90,7 +90,7 @@ variant = Representation chck downD structuralCons downC up up ctxt (name, DomainVariant ds) = do let dsForgotten = [ (n, defRepr d) | (n,d) <- ds ] case lookup (mkName name "_tag") ctxt of - Just (ConstantInt i) -> + Just (ConstantInt _ i) -> let iTag = at ds (fromInteger (i-1)) |> fst iName = mkName name iTag in case lookup iName ctxt of diff --git a/src/Conjure/UI/TranslateSolution.hs b/src/Conjure/UI/TranslateSolution.hs index 3e9d19119c..5c36cf6ebb 100644 --- a/src/Conjure/UI/TranslateSolution.hs +++ b/src/Conjure/UI/TranslateSolution.hs @@ -90,7 +90,7 @@ translateSolution eprimeModel essenceParam' eprimeSolution = do unnamedsAsEnumDomains <- forM unnameds $ \ (n, s') -> do s <- instantiateExpression eprimeLettings s' case s of - ConstantInt size -> return $ + ConstantInt _ size -> return $ let nms = [ mconcat [n, "_", Name (T.pack (show i))] | i <- [1 .. size] ] diff --git a/src/Conjure/UI/ValidateSolution.hs b/src/Conjure/UI/ValidateSolution.hs index ad6bcaca05..1be93d3151 100644 --- a/src/Conjure/UI/ValidateSolution.hs +++ b/src/Conjure/UI/ValidateSolution.hs @@ -86,7 +86,7 @@ validateSolution essenceModel essenceParam essenceSolution = flip evalStateT [] case [ val | Declaration (LettingDomainDefnEnum nm2 val) <- mStatements essenceParam, nm == nm2 ] of [val] -> do let domain = mkDomainIntB 1 (fromInt (genericLength val)) - let values = [ (n, Constant (ConstantInt i)) + let values = [ (n, Constant (ConstantInt (Just n) i)) | (n, i) <- zip val allNats ] modify (((nm, Domain domain) : values) ++) @@ -97,7 +97,7 @@ validateSolution essenceModel essenceParam essenceSolution = flip evalStateT [] ] Declaration (LettingDomainDefnEnum nm val) -> do let domain = mkDomainIntB 1 (fromInt (genericLength val)) - let values = [ (n, Constant (ConstantInt i)) + let values = [ (n, Constant (ConstantInt (Just n) i)) | (n, i) <- zip val allNats ] modify (((nm, Domain domain) : values) ++) @@ -105,7 +105,7 @@ validateSolution essenceModel essenceParam essenceSolution = flip evalStateT [] case [ nms | Declaration (LettingDomainDefnEnum nm2 nms) <- mStatements essenceSolution , nm == nm2 ] of [nms] -> do let domain = mkDomainIntB 1 (fromInt (genericLength nms)) - let values = [ (n, Constant (ConstantInt i)) + let values = [ (n, Constant (ConstantInt (Just n) i)) | (i,n) <- zip allNats nms ] modify (((nm, Domain domain) : values) ++) diff --git a/src/test/Conjure/Language/DomainSizeTest.hs b/src/test/Conjure/Language/DomainSizeTest.hs index 37c5f66705..969c694ce4 100644 --- a/src/test/Conjure/Language/DomainSizeTest.hs +++ b/src/test/Conjure/Language/DomainSizeTest.hs @@ -19,23 +19,23 @@ tests = testGroup "domainSize" [ testCase "domain size of bool is 2" $ domainSizeConstant DomainBool @?= Right 2 , testCase "domain size of int(1..100)" $ - domainSizeConstant (DomainInt Nothing [RangeBounded (ConstantInt 1) (ConstantInt 100)]) @?= Right 100 + domainSizeConstant (DomainInt Nothing [RangeBounded (ConstantInt Nothing 1) (ConstantInt Nothing 100)]) @?= Right 100 , testCase "domain size of int(1,...,100)" $ - domainSizeConstant (DomainInt Nothing (map (RangeSingle . ConstantInt) [1 .. 100])) @?= Right 100 + domainSizeConstant (DomainInt Nothing (map (RangeSingle . ConstantInt Nothing) [1 .. 100])) @?= Right 100 , testCase "domain size of int(13)" $ - domainSizeConstant (DomainInt Nothing [RangeSingle (ConstantInt 13)]) @?= Right 1 + domainSizeConstant (DomainInt Nothing [RangeSingle (ConstantInt Nothing 13)]) @?= Right 1 , testCase "domain size of int(13,1..100)" $ - domainSizeConstant (DomainInt Nothing [ RangeSingle (ConstantInt 13) - , RangeBounded (ConstantInt 1) (ConstantInt 100) + domainSizeConstant (DomainInt Nothing [ RangeSingle (ConstantInt Nothing 13) + , RangeBounded (ConstantInt Nothing 1) (ConstantInt Nothing 100) ]) @?= Right 100 , testCase "domain size of int(113,1..100)" $ - domainSizeConstant (DomainInt Nothing [ RangeSingle (ConstantInt 113) - , RangeBounded (ConstantInt 1) (ConstantInt 100) + domainSizeConstant (DomainInt Nothing [ RangeSingle (ConstantInt Nothing 113) + , RangeBounded (ConstantInt Nothing 1) (ConstantInt Nothing 100) ]) @?= Right 101 , testCase "domain size of set of bool #1" $ domainSizeConstant (DomainSet () (SetAttr SizeAttr_None) DomainBool) @?= Right 4 , testCase "domain size of set of bool #2" $ let setOfSize n = DomainSet () (SetAttr (SizeAttr_Size n)) - in domainSizeConstant (setOfSize (ConstantInt 2) DomainBool) @?= Right 1 + in domainSizeConstant (setOfSize (ConstantInt Nothing 2) DomainBool) @?= Right 1 ] diff --git a/src/test/Conjure/RepresentationsTest.hs b/src/test/Conjure/RepresentationsTest.hs index 1c5fadd6c5..816d2fd120 100644 --- a/src/test/Conjure/RepresentationsTest.hs +++ b/src/test/Conjure/RepresentationsTest.hs @@ -38,7 +38,7 @@ tests = testGroup "representations" , testCase "int #1" $ let highDomain = intDomain 1 4 - highConstant = ConstantInt 3 + highConstant = ConstantInt Nothing 3 low = [("x", highDomain, highConstant)] in testCases "x" highDomain highConstant (const Nothing) low low @@ -52,7 +52,7 @@ tests = testGroup "representations" , testCase "matrix of int" $ let highDomain = DomainMatrix (intDomain 1 3) (intDomain 1 5) - highConstant = ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantInt 2, ConstantInt 3, ConstantInt 5] + highConstant = ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantInt Nothing 2, ConstantInt Nothing 3, ConstantInt Nothing 5] low = [("x", highDomain, highConstant)] in testCases "x" highDomain highConstant (const Nothing) low low @@ -75,9 +75,9 @@ tests = testGroup "representations" DomainMatrix (intDomain 1 3) (DomainMatrix (intDomain 1 2) (intDomain 0 9)) highConstant = ConstantAbstract $ AbsLitMatrix (intDomain 1 3) - [ ConstantAbstract $ AbsLitMatrix (intDomain 1 2) [ConstantInt 3, ConstantInt 7] - , ConstantAbstract $ AbsLitMatrix (intDomain 1 2) [ConstantInt 2, ConstantInt 8] - , ConstantAbstract $ AbsLitMatrix (intDomain 1 2) [ConstantInt 0, ConstantInt 1] + [ ConstantAbstract $ AbsLitMatrix (intDomain 1 2) [ConstantInt Nothing 3, ConstantInt Nothing 7] + , ConstantAbstract $ AbsLitMatrix (intDomain 1 2) [ConstantInt Nothing 2, ConstantInt Nothing 8] + , ConstantAbstract $ AbsLitMatrix (intDomain 1 2) [ConstantInt Nothing 0, ConstantInt Nothing 1] ] low = [("x", highDomain, highConstant)] in testCases "x" highDomain highConstant (const Nothing) low low @@ -85,18 +85,18 @@ tests = testGroup "representations" , testCase "(bool, int)" $ let highDomain = DomainTuple [DomainBool, intDomain 1 3] - highConstant = ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantInt 2] + highConstant = ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantInt Nothing 2] low = [ ( "x_1", DomainBool , ConstantBool False ) - , ( "x_2", intDomain 1 3, ConstantInt 2 ) + , ( "x_2", intDomain 1 3, ConstantInt Nothing 2 ) ] in testCases "x" highDomain highConstant Just low low , testCase "(bool, int, bool)" $ let highDomain = DomainTuple [DomainBool, intDomain 1 3, DomainBool] - highConstant = ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantInt 2, ConstantBool True] + highConstant = ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantInt Nothing 2, ConstantBool True] low = [ ( "x_1", DomainBool , ConstantBool False ) - , ( "x_2", intDomain 1 3, ConstantInt 2 ) + , ( "x_2", intDomain 1 3, ConstantInt Nothing 2 ) , ( "x_3", DomainBool , ConstantBool True ) ] in testCases "x" highDomain highConstant Just low low @@ -104,12 +104,12 @@ tests = testGroup "representations" , testCase "((bool, int), bool)" $ let highDomain = DomainTuple [DomainTuple [DomainBool, intDomain 1 3], DomainBool] - highConstant = ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantInt 2], ConstantBool True] - mid = [ ( "x_1", DomainTuple [DomainBool, intDomain 1 3], ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantInt 2] ) + highConstant = ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantInt Nothing 2], ConstantBool True] + mid = [ ( "x_1", DomainTuple [DomainBool, intDomain 1 3], ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantInt Nothing 2] ) , ( "x_2", DomainBool, ConstantBool True ) ] low = [ ( "x_1_1", DomainBool , ConstantBool False ) - , ( "x_1_2", intDomain 1 3, ConstantInt 2 ) + , ( "x_1_2", intDomain 1 3, ConstantInt Nothing 2 ) , ( "x_2" , DomainBool , ConstantBool True ) ] in testCases "x" highDomain highConstant Just mid low @@ -117,12 +117,12 @@ tests = testGroup "representations" , testCase "(bool, (int, bool))" $ let highDomain = DomainTuple [DomainBool, DomainTuple [intDomain 1 3, DomainBool]] - highConstant = ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantAbstract $ AbsLitTuple [ConstantInt 2, ConstantBool True]] + highConstant = ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantAbstract $ AbsLitTuple [ConstantInt Nothing 2, ConstantBool True]] mid = [ ( "x_1", DomainBool, ConstantBool False ) - , ( "x_2", DomainTuple [intDomain 1 3, DomainBool], ConstantAbstract $ AbsLitTuple [ConstantInt 2, ConstantBool True] ) + , ( "x_2", DomainTuple [intDomain 1 3, DomainBool], ConstantAbstract $ AbsLitTuple [ConstantInt Nothing 2, ConstantBool True] ) ] low = [ ( "x_1" , DomainBool , ConstantBool False ) - , ( "x_2_1", intDomain 1 3, ConstantInt 2 ) + , ( "x_2_1", intDomain 1 3, ConstantInt Nothing 2 ) , ( "x_2_2", DomainBool , ConstantBool True ) ] in testCases "x" highDomain highConstant Just mid low @@ -130,70 +130,70 @@ tests = testGroup "representations" , testCase "(bool, int, bool, int)" $ let highDomain = DomainTuple [DomainBool, intDomain 1 3, DomainBool, intDomain 2 5] - highConstant = ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantInt 2, ConstantBool True, ConstantInt 4] + highConstant = ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantInt Nothing 2, ConstantBool True, ConstantInt Nothing 4] low = [ ( "x_1", DomainBool , ConstantBool False ) - , ( "x_2", intDomain 1 3, ConstantInt 2 ) + , ( "x_2", intDomain 1 3, ConstantInt Nothing 2 ) , ( "x_3", DomainBool , ConstantBool True ) - , ( "x_4", intDomain 2 5, ConstantInt 4 ) + , ( "x_4", intDomain 2 5, ConstantInt Nothing 4 ) ] in testCases "x" highDomain highConstant Just low low , testCase "((bool, int), (bool, int))" $ let highDomain = DomainTuple [DomainTuple [DomainBool, intDomain 1 3], DomainTuple [DomainBool, intDomain 2 5]] - highConstant = ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantInt 2], ConstantAbstract $ AbsLitTuple [ConstantBool True, ConstantInt 4]] - mid = [ ( "x_1", DomainTuple [DomainBool, intDomain 1 3], ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantInt 2] ) - , ( "x_2", DomainTuple [DomainBool, intDomain 2 5], ConstantAbstract $ AbsLitTuple [ConstantBool True , ConstantInt 4] ) + highConstant = ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantInt Nothing 2], ConstantAbstract $ AbsLitTuple [ConstantBool True, ConstantInt Nothing 4]] + mid = [ ( "x_1", DomainTuple [DomainBool, intDomain 1 3], ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantInt Nothing 2] ) + , ( "x_2", DomainTuple [DomainBool, intDomain 2 5], ConstantAbstract $ AbsLitTuple [ConstantBool True , ConstantInt Nothing 4] ) ] low = [ ( "x_1_1", DomainBool , ConstantBool False ) - , ( "x_1_2", intDomain 1 3, ConstantInt 2 ) + , ( "x_1_2", intDomain 1 3, ConstantInt Nothing 2 ) , ( "x_2_1", DomainBool , ConstantBool True ) - , ( "x_2_2", intDomain 2 5, ConstantInt 4 ) + , ( "x_2_2", intDomain 2 5, ConstantInt Nothing 4 ) ] in testCases "x" highDomain highConstant Just mid low , testCase "(bool, (int, (bool, int)))" $ let highDomain = DomainTuple [DomainBool, DomainTuple [intDomain 1 3, DomainTuple [DomainBool, intDomain 2 5]]] - highConstant = ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantAbstract $ AbsLitTuple [ConstantInt 2, ConstantAbstract $ AbsLitTuple [ConstantBool True, ConstantInt 4]]] + highConstant = ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantAbstract $ AbsLitTuple [ConstantInt Nothing 2, ConstantAbstract $ AbsLitTuple [ConstantBool True, ConstantInt Nothing 4]]] mid = [ ( "x_1", DomainBool , ConstantBool False ) , ( "x_2", DomainTuple [intDomain 1 3, DomainTuple [DomainBool, intDomain 2 5]] - , ConstantAbstract $ AbsLitTuple [ConstantInt 2, ConstantAbstract $ AbsLitTuple [ConstantBool True, ConstantInt 4]] ) + , ConstantAbstract $ AbsLitTuple [ConstantInt Nothing 2, ConstantAbstract $ AbsLitTuple [ConstantBool True, ConstantInt Nothing 4]] ) ] low = [ ( "x_1" , DomainBool , ConstantBool False ) - , ( "x_2_1" , intDomain 1 3, ConstantInt 2 ) + , ( "x_2_1" , intDomain 1 3, ConstantInt Nothing 2 ) , ( "x_2_2_1", DomainBool , ConstantBool True ) - , ( "x_2_2_2", intDomain 2 5, ConstantInt 4 ) + , ( "x_2_2_2", intDomain 2 5, ConstantInt Nothing 4 ) ] in testCases "x" highDomain highConstant Just mid low , testCase "(bool, (int, bool), int)" $ let highDomain = DomainTuple [DomainBool, DomainTuple [intDomain 1 3, DomainBool], intDomain 2 5] - highConstant = ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantAbstract $ AbsLitTuple [ConstantInt 2, ConstantBool True], ConstantInt 4] + highConstant = ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantAbstract $ AbsLitTuple [ConstantInt Nothing 2, ConstantBool True], ConstantInt Nothing 4] mid = [ ( "x_1", DomainBool , ConstantBool False ) - , ( "x_2", DomainTuple [intDomain 1 3, DomainBool], ConstantAbstract $ AbsLitTuple [ConstantInt 2, ConstantBool True] ) - , ( "x_3", intDomain 2 5, ConstantInt 4 ) + , ( "x_2", DomainTuple [intDomain 1 3, DomainBool], ConstantAbstract $ AbsLitTuple [ConstantInt Nothing 2, ConstantBool True] ) + , ( "x_3", intDomain 2 5, ConstantInt Nothing 4 ) ] low = [ ( "x_1" , DomainBool , ConstantBool False ) - , ( "x_2_1", intDomain 1 3, ConstantInt 2 ) + , ( "x_2_1", intDomain 1 3, ConstantInt Nothing 2 ) , ( "x_2_2", DomainBool , ConstantBool True ) - , ( "x_3" , intDomain 2 5, ConstantInt 4 ) + , ( "x_3" , intDomain 2 5, ConstantInt Nothing 4 ) ] in testCases "x" highDomain highConstant Just mid low , testCase "(((bool, int), bool), int)" $ let highDomain = DomainTuple [DomainTuple [ DomainTuple [DomainBool, intDomain 1 3], DomainBool], intDomain 2 5] - highConstant = ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantInt 2], ConstantBool True], ConstantInt 4] + highConstant = ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantInt Nothing 2], ConstantBool True], ConstantInt Nothing 4] mid = [ ( "x_1", DomainTuple [ DomainTuple [DomainBool, intDomain 1 3], DomainBool] - , ConstantAbstract $ AbsLitTuple [ ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantInt 2], ConstantBool True] ) - , ( "x_2", intDomain 2 5, ConstantInt 4 ) + , ConstantAbstract $ AbsLitTuple [ ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantInt Nothing 2], ConstantBool True] ) + , ( "x_2", intDomain 2 5, ConstantInt Nothing 4 ) ] low = [ ( "x_1_1_1", DomainBool , ConstantBool False ) - , ( "x_1_1_2", intDomain 1 3, ConstantInt 2 ) + , ( "x_1_1_2", intDomain 1 3, ConstantInt Nothing 2 ) , ( "x_1_2" , DomainBool , ConstantBool True ) - , ( "x_2" , intDomain 2 5, ConstantInt 4 ) + , ( "x_2" , intDomain 2 5, ConstantInt Nothing 4 ) ] in testCases "x" highDomain highConstant Just mid low @@ -203,14 +203,14 @@ tests = testGroup "representations" DomainMatrix (intDomain 1 3) (DomainTuple [DomainBool, intDomain 0 9]) highConstant = ConstantAbstract $ AbsLitMatrix (intDomain 1 3) - [ ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantInt 0] - , ConstantAbstract $ AbsLitTuple [ConstantBool True , ConstantInt 3] - , ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantInt 4] + [ ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantInt Nothing 0] + , ConstantAbstract $ AbsLitTuple [ConstantBool True , ConstantInt Nothing 3] + , ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantInt Nothing 4] ] low = [ ( "x_1", DomainMatrix (intDomain 1 3) DomainBool , ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantBool False, ConstantBool True, ConstantBool False] ) , ( "x_2", DomainMatrix (intDomain 1 3) (intDomain 0 9) - , ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantInt 0, ConstantInt 3, ConstantInt 4] ) + , ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantInt Nothing 0, ConstantInt Nothing 3, ConstantInt Nothing 4] ) ] in testCases "x" highDomain highConstant Just low low @@ -219,12 +219,12 @@ tests = testGroup "representations" highDomain = DomainMatrix (intDomain 1 3) (DomainTuple [DomainBool, intDomain 1 3, DomainBool]) highConstant = ConstantAbstract $ AbsLitMatrix (intDomain 1 3) - [ ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantInt 2, ConstantBool True] - , ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantInt 3, ConstantBool False] - , ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantInt 4, ConstantBool False] + [ ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantInt Nothing 2, ConstantBool True] + , ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantInt Nothing 3, ConstantBool False] + , ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantInt Nothing 4, ConstantBool False] ] low = [ ( "x_1", DomainMatrix (intDomain 1 3) DomainBool , ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantBool False, ConstantBool False, ConstantBool False] ) - , ( "x_2", DomainMatrix (intDomain 1 3) (intDomain 1 3), ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantInt 2 , ConstantInt 3 , ConstantInt 4 ] ) + , ( "x_2", DomainMatrix (intDomain 1 3) (intDomain 1 3), ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantInt Nothing 2 , ConstantInt Nothing 3 , ConstantInt Nothing 4 ] ) , ( "x_3", DomainMatrix (intDomain 1 3) DomainBool , ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantBool True , ConstantBool False, ConstantBool False] ) ] in testCases "x" highDomain highConstant Just low low @@ -234,21 +234,21 @@ tests = testGroup "representations" highDomain = DomainMatrix (intDomain 1 3) (DomainTuple [DomainTuple [DomainBool, intDomain 1 3], DomainBool]) highConstant = ConstantAbstract $ AbsLitMatrix (intDomain 1 3) - [ ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantInt 2], ConstantBool True] - , ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantInt 3], ConstantBool False] - , ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ConstantBool True , ConstantInt 4], ConstantBool False] + [ ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantInt Nothing 2], ConstantBool True] + , ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantInt Nothing 3], ConstantBool False] + , ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ConstantBool True , ConstantInt Nothing 4], ConstantBool False] ] mid = [ ( "x_1", DomainMatrix (intDomain 1 3) (DomainTuple [DomainBool, intDomain 1 3]) , ConstantAbstract $ AbsLitMatrix (intDomain 1 3) - [ ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantInt 2] - , ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantInt 3] - , ConstantAbstract $ AbsLitTuple [ConstantBool True , ConstantInt 4] + [ ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantInt Nothing 2] + , ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantInt Nothing 3] + , ConstantAbstract $ AbsLitTuple [ConstantBool True , ConstantInt Nothing 4] ] ) , ( "x_2", DomainMatrix (intDomain 1 3) DomainBool , ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantBool True , ConstantBool False, ConstantBool False] ) ] low = [ ( "x_1_1", DomainMatrix (intDomain 1 3) DomainBool , ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantBool False, ConstantBool False, ConstantBool True ] ) - , ( "x_1_2", DomainMatrix (intDomain 1 3) (intDomain 1 3), ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantInt 2 , ConstantInt 3 , ConstantInt 4 ] ) + , ( "x_1_2", DomainMatrix (intDomain 1 3) (intDomain 1 3), ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantInt Nothing 2 , ConstantInt Nothing 3 , ConstantInt Nothing 4 ] ) , ( "x_2" , DomainMatrix (intDomain 1 3) DomainBool , ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantBool True , ConstantBool False, ConstantBool False] ) ] in testCases "x" highDomain highConstant Just mid low @@ -258,23 +258,23 @@ tests = testGroup "representations" highDomain = DomainMatrix (intDomain 1 3) (DomainTuple [DomainBool, DomainTuple [intDomain 0 9, DomainBool]]) highConstant = ConstantAbstract $ AbsLitMatrix (intDomain 1 3) - [ ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantAbstract $ AbsLitTuple [ConstantInt 0, ConstantBool True]] - , ConstantAbstract $ AbsLitTuple [ConstantBool True , ConstantAbstract $ AbsLitTuple [ConstantInt 3, ConstantBool False]] - , ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantAbstract $ AbsLitTuple [ConstantInt 4, ConstantBool True]] + [ ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantAbstract $ AbsLitTuple [ConstantInt Nothing 0, ConstantBool True]] + , ConstantAbstract $ AbsLitTuple [ConstantBool True , ConstantAbstract $ AbsLitTuple [ConstantInt Nothing 3, ConstantBool False]] + , ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantAbstract $ AbsLitTuple [ConstantInt Nothing 4, ConstantBool True]] ] mid = [ ( "x_1", DomainMatrix (intDomain 1 3) DomainBool , ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantBool False, ConstantBool True, ConstantBool False] ) , ( "x_2", DomainMatrix (intDomain 1 3) (DomainTuple [intDomain 0 9, DomainBool]) , ConstantAbstract $ AbsLitMatrix (intDomain 1 3) - [ ConstantAbstract $ AbsLitTuple [ConstantInt 0, ConstantBool True] - , ConstantAbstract $ AbsLitTuple [ConstantInt 3, ConstantBool False] - , ConstantAbstract $ AbsLitTuple [ConstantInt 4, ConstantBool True] + [ ConstantAbstract $ AbsLitTuple [ConstantInt Nothing 0, ConstantBool True] + , ConstantAbstract $ AbsLitTuple [ConstantInt Nothing 3, ConstantBool False] + , ConstantAbstract $ AbsLitTuple [ConstantInt Nothing 4, ConstantBool True] ] ) ] low = [ ( "x_1" , DomainMatrix (intDomain 1 3) DomainBool , ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantBool False, ConstantBool True, ConstantBool False] ) , ( "x_2_1", DomainMatrix (intDomain 1 3) (intDomain 0 9) - , ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantInt 0, ConstantInt 3, ConstantInt 4] ) + , ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantInt Nothing 0, ConstantInt Nothing 3, ConstantInt Nothing 4] ) , ( "x_2_2", DomainMatrix (intDomain 1 3) DomainBool , ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantBool True, ConstantBool False, ConstantBool True] ) ] @@ -285,14 +285,14 @@ tests = testGroup "representations" highDomain = DomainMatrix (intDomain 1 3) (DomainTuple [DomainBool, intDomain 1 3, DomainBool, intDomain 2 5]) highConstant = ConstantAbstract $ AbsLitMatrix (intDomain 1 3) - [ ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantInt 2, ConstantBool True , ConstantInt 4] - , ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantInt 3, ConstantBool False, ConstantInt 6] - , ConstantAbstract $ AbsLitTuple [ConstantBool True , ConstantInt 4, ConstantBool False, ConstantInt 8] + [ ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantInt Nothing 2, ConstantBool True , ConstantInt Nothing 4] + , ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantInt Nothing 3, ConstantBool False, ConstantInt Nothing 6] + , ConstantAbstract $ AbsLitTuple [ConstantBool True , ConstantInt Nothing 4, ConstantBool False, ConstantInt Nothing 8] ] low = [ ( "x_1", DomainMatrix (intDomain 1 3) DomainBool , ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantBool False, ConstantBool False, ConstantBool True ] ) - , ( "x_2", DomainMatrix (intDomain 1 3) (intDomain 1 3), ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantInt 2 , ConstantInt 3 , ConstantInt 4 ] ) + , ( "x_2", DomainMatrix (intDomain 1 3) (intDomain 1 3), ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantInt Nothing 2 , ConstantInt Nothing 3 , ConstantInt Nothing 4 ] ) , ( "x_3", DomainMatrix (intDomain 1 3) DomainBool , ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantBool True , ConstantBool False, ConstantBool False] ) - , ( "x_4", DomainMatrix (intDomain 1 3) (intDomain 2 5), ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantInt 4 , ConstantInt 6 , ConstantInt 8 ] ) + , ( "x_4", DomainMatrix (intDomain 1 3) (intDomain 2 5), ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantInt Nothing 4 , ConstantInt Nothing 6 , ConstantInt Nothing 8 ] ) ] in testCases "x" highDomain highConstant Just low low @@ -301,33 +301,33 @@ tests = testGroup "representations" highDomain = DomainMatrix (intDomain 1 3) (DomainTuple [DomainTuple [DomainBool, intDomain 1 3], DomainTuple [DomainBool, intDomain 2 5]]) highConstant = ConstantAbstract $ AbsLitMatrix (intDomain 1 3) - [ ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantInt 2], ConstantAbstract $ AbsLitTuple [ConstantBool True , ConstantInt 4]] - , ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantInt 3], ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantInt 6]] - , ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ConstantBool True , ConstantInt 4], ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantInt 8]] + [ ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantInt Nothing 2], ConstantAbstract $ AbsLitTuple [ConstantBool True , ConstantInt Nothing 4]] + , ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantInt Nothing 3], ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantInt Nothing 6]] + , ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ConstantBool True , ConstantInt Nothing 4], ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantInt Nothing 8]] ] mid = [ ( "x_1" , DomainMatrix (intDomain 1 3) (DomainTuple [DomainBool, intDomain 1 3]) , ConstantAbstract $ AbsLitMatrix (intDomain 1 3) - [ ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantInt 2] - , ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantInt 3] - , ConstantAbstract $ AbsLitTuple [ConstantBool True , ConstantInt 4] + [ ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantInt Nothing 2] + , ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantInt Nothing 3] + , ConstantAbstract $ AbsLitTuple [ConstantBool True , ConstantInt Nothing 4] ] ) , ( "x_2" , DomainMatrix (intDomain 1 3) (DomainTuple [DomainBool, intDomain 2 5]) , ConstantAbstract $ AbsLitMatrix (intDomain 1 3) - [ ConstantAbstract $ AbsLitTuple [ConstantBool True , ConstantInt 4] - , ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantInt 6] - , ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantInt 8] + [ ConstantAbstract $ AbsLitTuple [ConstantBool True , ConstantInt Nothing 4] + , ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantInt Nothing 6] + , ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantInt Nothing 8] ] ) ] low = [ ( "x_1_1", DomainMatrix (intDomain 1 3) DomainBool , ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantBool False, ConstantBool False, ConstantBool True ] ) , ( "x_1_2", DomainMatrix (intDomain 1 3) (intDomain 1 3) - , ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantInt 2 , ConstantInt 3 , ConstantInt 4 ] ) + , ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantInt Nothing 2 , ConstantInt Nothing 3 , ConstantInt Nothing 4 ] ) , ( "x_2_1", DomainMatrix (intDomain 1 3) DomainBool , ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantBool True , ConstantBool False, ConstantBool False] ) , ( "x_2_2", DomainMatrix (intDomain 1 3) (intDomain 2 5) - , ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantInt 4 , ConstantInt 6 , ConstantInt 8 ] ) + , ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantInt Nothing 4 , ConstantInt Nothing 6 , ConstantInt Nothing 8 ] ) ] in testCases "x" highDomain highConstant Just mid low @@ -336,23 +336,23 @@ tests = testGroup "representations" highDomain = DomainMatrix (intDomain 1 3) (DomainTuple [DomainBool, DomainTuple [intDomain 1 3, DomainTuple [DomainBool, intDomain 2 5]]]) highConstant = ConstantAbstract $ AbsLitMatrix (intDomain 1 3) - [ ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantAbstract $ AbsLitTuple [ConstantInt 2, ConstantAbstract $ AbsLitTuple [ConstantBool True , ConstantInt 4]]] - , ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantAbstract $ AbsLitTuple [ConstantInt 3, ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantInt 6]]] - , ConstantAbstract $ AbsLitTuple [ConstantBool True , ConstantAbstract $ AbsLitTuple [ConstantInt 4, ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantInt 8]]] + [ ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantAbstract $ AbsLitTuple [ConstantInt Nothing 2, ConstantAbstract $ AbsLitTuple [ConstantBool True , ConstantInt Nothing 4]]] + , ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantAbstract $ AbsLitTuple [ConstantInt Nothing 3, ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantInt Nothing 6]]] + , ConstantAbstract $ AbsLitTuple [ConstantBool True , ConstantAbstract $ AbsLitTuple [ConstantInt Nothing 4, ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantInt Nothing 8]]] ] mid = [ ( "x_1", DomainMatrix (intDomain 1 3) DomainBool , ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantBool False, ConstantBool False, ConstantBool True] ) , ( "x_2", DomainMatrix (intDomain 1 3) (DomainTuple [intDomain 1 3, DomainTuple [DomainBool, intDomain 2 5]]) , ConstantAbstract $ AbsLitMatrix (intDomain 1 3) - [ ConstantAbstract $ AbsLitTuple [ConstantInt 2, ConstantAbstract $ AbsLitTuple [ConstantBool True , ConstantInt 4]] - , ConstantAbstract $ AbsLitTuple [ConstantInt 3, ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantInt 6]] - , ConstantAbstract $ AbsLitTuple [ConstantInt 4, ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantInt 8]] + [ ConstantAbstract $ AbsLitTuple [ConstantInt Nothing 2, ConstantAbstract $ AbsLitTuple [ConstantBool True , ConstantInt Nothing 4]] + , ConstantAbstract $ AbsLitTuple [ConstantInt Nothing 3, ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantInt Nothing 6]] + , ConstantAbstract $ AbsLitTuple [ConstantInt Nothing 4, ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantInt Nothing 8]] ] ) ] low = [ ( "x_1" , DomainMatrix (intDomain 1 3) DomainBool , ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantBool False, ConstantBool False, ConstantBool True ]) - , ( "x_2_1" , DomainMatrix (intDomain 1 3) (intDomain 1 3), ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantInt 2 , ConstantInt 3 , ConstantInt 4 ]) + , ( "x_2_1" , DomainMatrix (intDomain 1 3) (intDomain 1 3), ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantInt Nothing 2 , ConstantInt Nothing 3 , ConstantInt Nothing 4 ]) , ( "x_2_2_1", DomainMatrix (intDomain 1 3) DomainBool , ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantBool True , ConstantBool False, ConstantBool False]) - , ( "x_2_2_2", DomainMatrix (intDomain 1 3) (intDomain 2 5), ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantInt 4 , ConstantInt 6 , ConstantInt 8 ]) + , ( "x_2_2_2", DomainMatrix (intDomain 1 3) (intDomain 2 5), ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantInt Nothing 4 , ConstantInt Nothing 6 , ConstantInt Nothing 8 ]) ] in testCases "x" highDomain highConstant Just mid low @@ -361,26 +361,26 @@ tests = testGroup "representations" highDomain = DomainMatrix (intDomain 1 3) (DomainTuple [DomainBool, DomainTuple [intDomain 1 3, DomainBool], intDomain 2 5]) highConstant = ConstantAbstract $ AbsLitMatrix (intDomain 1 3) - [ ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantAbstract $ AbsLitTuple [ConstantInt 2, ConstantBool True ], ConstantInt 4] - , ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantAbstract $ AbsLitTuple [ConstantInt 3, ConstantBool False], ConstantInt 6] - , ConstantAbstract $ AbsLitTuple [ConstantBool True , ConstantAbstract $ AbsLitTuple [ConstantInt 4, ConstantBool False], ConstantInt 8] + [ ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantAbstract $ AbsLitTuple [ConstantInt Nothing 2, ConstantBool True ], ConstantInt Nothing 4] + , ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantAbstract $ AbsLitTuple [ConstantInt Nothing 3, ConstantBool False], ConstantInt Nothing 6] + , ConstantAbstract $ AbsLitTuple [ConstantBool True , ConstantAbstract $ AbsLitTuple [ConstantInt Nothing 4, ConstantBool False], ConstantInt Nothing 8] ] mid = [ ( "x_1", DomainMatrix (intDomain 1 3) DomainBool , ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantBool False, ConstantBool False, ConstantBool True] ) , ( "x_2", DomainMatrix (intDomain 1 3) (DomainTuple [intDomain 1 3, DomainBool]) , ConstantAbstract $ AbsLitMatrix (intDomain 1 3) - [ ConstantAbstract $ AbsLitTuple [ConstantInt 2, ConstantBool True ] - , ConstantAbstract $ AbsLitTuple [ConstantInt 3, ConstantBool False] - , ConstantAbstract $ AbsLitTuple [ConstantInt 4, ConstantBool False] + [ ConstantAbstract $ AbsLitTuple [ConstantInt Nothing 2, ConstantBool True ] + , ConstantAbstract $ AbsLitTuple [ConstantInt Nothing 3, ConstantBool False] + , ConstantAbstract $ AbsLitTuple [ConstantInt Nothing 4, ConstantBool False] ] ) , ( "x_3", DomainMatrix (intDomain 1 3) (intDomain 2 5) - , ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantInt 4, ConstantInt 6, ConstantInt 8] + , ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantInt Nothing 4, ConstantInt Nothing 6, ConstantInt Nothing 8] ) ] low = [ ( "x_1" , DomainMatrix (intDomain 1 3) DomainBool , ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantBool False, ConstantBool False, ConstantBool True ]) - , ( "x_2_1", DomainMatrix (intDomain 1 3) (intDomain 1 3), ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantInt 2 , ConstantInt 3 , ConstantInt 4 ]) + , ( "x_2_1", DomainMatrix (intDomain 1 3) (intDomain 1 3), ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantInt Nothing 2 , ConstantInt Nothing 3 , ConstantInt Nothing 4 ]) , ( "x_2_2", DomainMatrix (intDomain 1 3) DomainBool , ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantBool True , ConstantBool False, ConstantBool False]) - , ( "x_3" , DomainMatrix (intDomain 1 3) (intDomain 2 5), ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantInt 4 , ConstantInt 6 , ConstantInt 8 ]) + , ( "x_3" , DomainMatrix (intDomain 1 3) (intDomain 2 5), ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantInt Nothing 4 , ConstantInt Nothing 6 , ConstantInt Nothing 8 ]) ] in testCases "x" highDomain highConstant Just mid low @@ -389,24 +389,24 @@ tests = testGroup "representations" highDomain = DomainMatrix (intDomain 1 3) (DomainTuple [DomainTuple [DomainTuple [DomainBool, intDomain 1 3], DomainBool], intDomain 2 5]) highConstant = ConstantAbstract $ AbsLitMatrix (intDomain 1 3) - [ ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantInt 2], ConstantBool True ], ConstantInt 4] - , ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantInt 3], ConstantBool False], ConstantInt 6] - , ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ConstantBool True , ConstantInt 4], ConstantBool False], ConstantInt 8] + [ ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantInt Nothing 2], ConstantBool True ], ConstantInt Nothing 4] + , ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantInt Nothing 3], ConstantBool False], ConstantInt Nothing 6] + , ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ConstantBool True , ConstantInt Nothing 4], ConstantBool False], ConstantInt Nothing 8] ] mid = [ ( "x_1", DomainMatrix (intDomain 1 3) (DomainTuple [DomainTuple [DomainBool,intDomain 1 3],DomainBool]) , ConstantAbstract $ AbsLitMatrix (intDomain 1 3) - [ ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantInt 2], ConstantBool True ] - , ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantInt 3], ConstantBool False] - , ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ConstantBool True , ConstantInt 4], ConstantBool False] + [ ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantInt Nothing 2], ConstantBool True ] + , ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantInt Nothing 3], ConstantBool False] + , ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ConstantBool True , ConstantInt Nothing 4], ConstantBool False] ]) , ( "x_2", DomainMatrix (intDomain 1 3) (intDomain 2 5) - , ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantInt 4, ConstantInt 6, ConstantInt 8] + , ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantInt Nothing 4, ConstantInt Nothing 6, ConstantInt Nothing 8] ) ] low = [ ( "x_1_1_1", DomainMatrix (intDomain 1 3) DomainBool , ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantBool False, ConstantBool False, ConstantBool True ]) - , ( "x_1_1_2", DomainMatrix (intDomain 1 3) (intDomain 1 3), ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantInt 2 , ConstantInt 3 , ConstantInt 4 ]) + , ( "x_1_1_2", DomainMatrix (intDomain 1 3) (intDomain 1 3), ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantInt Nothing 2 , ConstantInt Nothing 3 , ConstantInt Nothing 4 ]) , ( "x_1_2" , DomainMatrix (intDomain 1 3) DomainBool , ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantBool True , ConstantBool False, ConstantBool False]) - , ( "x_2" , DomainMatrix (intDomain 1 3) (intDomain 2 5), ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantInt 4 , ConstantInt 6 , ConstantInt 8 ]) + , ( "x_2" , DomainMatrix (intDomain 1 3) (intDomain 2 5), ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantInt Nothing 4 , ConstantInt Nothing 6 , ConstantInt Nothing 8 ]) ] in testCases "x" highDomain highConstant Just mid low @@ -419,14 +419,14 @@ tests = testGroup "representations" highConstant = ConstantAbstract $ AbsLitMatrix (intDomain 1 2) [ ConstantAbstract $ AbsLitMatrix (intDomain 1 3) - [ ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantInt 2], ConstantBool True ], ConstantInt 4] - , ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantInt 3], ConstantBool False], ConstantInt 6] - , ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ConstantBool True , ConstantInt 4], ConstantBool False], ConstantInt 8] + [ ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantInt Nothing 2], ConstantBool True ], ConstantInt Nothing 4] + , ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantInt Nothing 3], ConstantBool False], ConstantInt Nothing 6] + , ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ConstantBool True , ConstantInt Nothing 4], ConstantBool False], ConstantInt Nothing 8] ] , ConstantAbstract $ AbsLitMatrix (intDomain 1 3) - [ ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantInt 4], ConstantBool True ], ConstantInt 4] - , ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ConstantBool True , ConstantInt 5], ConstantBool False], ConstantInt 7] - , ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ConstantBool True , ConstantInt 6], ConstantBool False], ConstantInt 9] + [ ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantInt Nothing 4], ConstantBool True ], ConstantInt Nothing 4] + , ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ConstantBool True , ConstantInt Nothing 5], ConstantBool False], ConstantInt Nothing 7] + , ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ConstantBool True , ConstantInt Nothing 6], ConstantBool False], ConstantInt Nothing 9] ] ] mid = @@ -435,22 +435,22 @@ tests = testGroup "representations" (DomainTuple [DomainTuple [DomainBool, intDomain 1 3], DomainBool])) , ConstantAbstract $ AbsLitMatrix (intDomain 1 2) [ ConstantAbstract $ AbsLitMatrix (intDomain 1 3) - [ ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ConstantBool False,ConstantInt 2],ConstantBool True] - , ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ConstantBool False,ConstantInt 3],ConstantBool False] - , ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ConstantBool True,ConstantInt 4],ConstantBool False] + [ ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ConstantBool False,ConstantInt Nothing 2],ConstantBool True] + , ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ConstantBool False,ConstantInt Nothing 3],ConstantBool False] + , ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ConstantBool True,ConstantInt Nothing 4],ConstantBool False] ] , ConstantAbstract $ AbsLitMatrix (intDomain 1 3) - [ ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ConstantBool False,ConstantInt 4],ConstantBool True] - , ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ConstantBool True,ConstantInt 5],ConstantBool False] - , ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ConstantBool True,ConstantInt 6],ConstantBool False] + [ ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ConstantBool False,ConstantInt Nothing 4],ConstantBool True] + , ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ConstantBool True,ConstantInt Nothing 5],ConstantBool False] + , ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ConstantBool True,ConstantInt Nothing 6],ConstantBool False] ] ] ) , ( "x_2" , DomainMatrix (intDomain 1 2) (DomainMatrix (intDomain 1 3) (intDomain 2 5)) , ConstantAbstract $ AbsLitMatrix (intDomain 1 2) - [ ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantInt 4,ConstantInt 6,ConstantInt 8] - , ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantInt 4,ConstantInt 7,ConstantInt 9] + [ ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantInt Nothing 4,ConstantInt Nothing 6,ConstantInt Nothing 8] + , ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantInt Nothing 4,ConstantInt Nothing 7,ConstantInt Nothing 9] ] ) ] low = @@ -461,8 +461,8 @@ tests = testGroup "representations" ] ) , ( "x_1_1_2" , DomainMatrix (intDomain 1 2) (DomainMatrix (intDomain 1 3) (intDomain 1 3)) , ConstantAbstract $ AbsLitMatrix (intDomain 1 2) - [ ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantInt 2,ConstantInt 3,ConstantInt 4] - , ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantInt 4,ConstantInt 5,ConstantInt 6] + [ ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantInt Nothing 2,ConstantInt Nothing 3,ConstantInt Nothing 4] + , ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantInt Nothing 4,ConstantInt Nothing 5,ConstantInt Nothing 6] ] ) , ( "x_1_2" , DomainMatrix (intDomain 1 2) (DomainMatrix (intDomain 1 3) DomainBool) , ConstantAbstract $ AbsLitMatrix (intDomain 1 2) @@ -471,8 +471,8 @@ tests = testGroup "representations" ] ) , ( "x_2" , DomainMatrix (intDomain 1 2) (DomainMatrix (intDomain 1 3) (intDomain 2 5)) , ConstantAbstract $ AbsLitMatrix (intDomain 1 2) - [ ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantInt 4,ConstantInt 6,ConstantInt 8] - , ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantInt 4,ConstantInt 7,ConstantInt 9] + [ ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantInt Nothing 4,ConstantInt Nothing 6,ConstantInt Nothing 8] + , ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantInt Nothing 4,ConstantInt Nothing 7,ConstantInt Nothing 9] ] ) ] in testCases "x" highDomain highConstant Just mid low @@ -488,7 +488,7 @@ tests = testGroup "representations" ] ) ( ConstantAbstract $ AbsLitTuple [ ConstantBool False - , ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantInt 2, ConstantInt 4, ConstantInt 5] + , ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantInt Nothing 2, ConstantInt Nothing 4, ConstantInt Nothing 5] ] ) , testCase "(bool, matrix of int)" $ @@ -501,12 +501,12 @@ tests = testGroup "representations" highConstant = ConstantAbstract $ AbsLitTuple [ ConstantBool False - , ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantInt 2, ConstantInt 4, ConstantInt 5] + , ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantInt Nothing 2, ConstantInt Nothing 4, ConstantInt Nothing 5] ] low = [ ( "x_1", DomainBool,ConstantBool False) , ( "x_2", DomainMatrix (intDomain 1 3) (intDomain 0 9) - , ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantInt 2,ConstantInt 4,ConstantInt 5] ) + , ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantInt Nothing 2,ConstantInt Nothing 4,ConstantInt Nothing 5] ) ] in testCases "x" highDomain highConstant Just low low @@ -518,9 +518,9 @@ tests = testGroup "representations" ( ConstantAbstract $ AbsLitTuple [ ConstantBool False , ConstantAbstract $ AbsLitMatrix (intDomain 1 3) - [ ConstantAbstract $ AbsLitTuple [ConstantInt 2, ConstantBool False] - , ConstantAbstract $ AbsLitTuple [ConstantInt 4, ConstantBool True] - , ConstantAbstract $ AbsLitTuple [ConstantInt 5, ConstantBool False] + [ ConstantAbstract $ AbsLitTuple [ConstantInt Nothing 2, ConstantBool False] + , ConstantAbstract $ AbsLitTuple [ConstantInt Nothing 4, ConstantBool True] + , ConstantAbstract $ AbsLitTuple [ConstantInt Nothing 5, ConstantBool False] ] ] ) @@ -535,23 +535,23 @@ tests = testGroup "representations" ConstantAbstract $ AbsLitTuple [ ConstantBool False , ConstantAbstract $ AbsLitMatrix (intDomain 1 3) - [ ConstantAbstract $ AbsLitTuple [ConstantInt 2, ConstantBool False] - , ConstantAbstract $ AbsLitTuple [ConstantInt 4, ConstantBool True] - , ConstantAbstract $ AbsLitTuple [ConstantInt 5, ConstantBool False] + [ ConstantAbstract $ AbsLitTuple [ConstantInt Nothing 2, ConstantBool False] + , ConstantAbstract $ AbsLitTuple [ConstantInt Nothing 4, ConstantBool True] + , ConstantAbstract $ AbsLitTuple [ConstantInt Nothing 5, ConstantBool False] ] ] mid = [ ( "x_1" , DomainBool , ConstantBool False ) , ( "x_2" , DomainMatrix (intDomain 1 3) (DomainTuple [intDomain 0 9,DomainBool]) , ConstantAbstract $ AbsLitMatrix (intDomain 1 3) - [ ConstantAbstract $ AbsLitTuple [ConstantInt 2,ConstantBool False] - , ConstantAbstract $ AbsLitTuple [ConstantInt 4,ConstantBool True] - , ConstantAbstract $ AbsLitTuple [ConstantInt 5,ConstantBool False] + [ ConstantAbstract $ AbsLitTuple [ConstantInt Nothing 2,ConstantBool False] + , ConstantAbstract $ AbsLitTuple [ConstantInt Nothing 4,ConstantBool True] + , ConstantAbstract $ AbsLitTuple [ConstantInt Nothing 5,ConstantBool False] ] ) ] low = [ ( "x_1" , DomainBool , ConstantBool False ) - , ( "x_2_1" , DomainMatrix (intDomain 1 3) (intDomain 0 9) , ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantInt 2,ConstantInt 4,ConstantInt 5] ) + , ( "x_2_1" , DomainMatrix (intDomain 1 3) (intDomain 0 9) , ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantInt Nothing 2,ConstantInt Nothing 4,ConstantInt Nothing 5] ) , ( "x_2_2" , DomainMatrix (intDomain 1 3) DomainBool , ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantBool False,ConstantBool True,ConstantBool False] ) ] in testCases "x" highDomain highConstant Just mid low @@ -567,9 +567,9 @@ tests = testGroup "representations" ( ConstantAbstract $ AbsLitTuple [ ConstantBool False , ConstantAbstract $ AbsLitMatrix (intDomain 1 3) - [ ConstantAbstract $ AbsLitTuple [ConstantInt 2, ConstantAbstract $ AbsLitMatrix (intDomain 1 2) [ConstantInt 1, ConstantInt 3]] - , ConstantAbstract $ AbsLitTuple [ConstantInt 4, ConstantAbstract $ AbsLitMatrix (intDomain 1 2) [ConstantInt 3, ConstantInt 5]] - , ConstantAbstract $ AbsLitTuple [ConstantInt 5, ConstantAbstract $ AbsLitMatrix (intDomain 1 2) [ConstantInt 5, ConstantInt 6]] + [ ConstantAbstract $ AbsLitTuple [ConstantInt Nothing 2, ConstantAbstract $ AbsLitMatrix (intDomain 1 2) [ConstantInt Nothing 1, ConstantInt Nothing 3]] + , ConstantAbstract $ AbsLitTuple [ConstantInt Nothing 4, ConstantAbstract $ AbsLitMatrix (intDomain 1 2) [ConstantInt Nothing 3, ConstantInt Nothing 5]] + , ConstantAbstract $ AbsLitTuple [ConstantInt Nothing 5, ConstantAbstract $ AbsLitMatrix (intDomain 1 2) [ConstantInt Nothing 5, ConstantInt Nothing 6]] ] ] ) @@ -587,29 +587,29 @@ tests = testGroup "representations" ConstantAbstract $ AbsLitTuple [ ConstantBool False , ConstantAbstract $ AbsLitMatrix (intDomain 1 3) - [ ConstantAbstract $ AbsLitTuple [ConstantInt 2, ConstantAbstract $ AbsLitMatrix (intDomain 1 2) [ConstantInt 1, ConstantInt 3]] - , ConstantAbstract $ AbsLitTuple [ConstantInt 4, ConstantAbstract $ AbsLitMatrix (intDomain 1 2) [ConstantInt 3, ConstantInt 5]] - , ConstantAbstract $ AbsLitTuple [ConstantInt 5, ConstantAbstract $ AbsLitMatrix (intDomain 1 2) [ConstantInt 5, ConstantInt 6]] + [ ConstantAbstract $ AbsLitTuple [ConstantInt Nothing 2, ConstantAbstract $ AbsLitMatrix (intDomain 1 2) [ConstantInt Nothing 1, ConstantInt Nothing 3]] + , ConstantAbstract $ AbsLitTuple [ConstantInt Nothing 4, ConstantAbstract $ AbsLitMatrix (intDomain 1 2) [ConstantInt Nothing 3, ConstantInt Nothing 5]] + , ConstantAbstract $ AbsLitTuple [ConstantInt Nothing 5, ConstantAbstract $ AbsLitMatrix (intDomain 1 2) [ConstantInt Nothing 5, ConstantInt Nothing 6]] ] ] mid = [ ( "x_1" , DomainBool,ConstantBool False ) , ( "x_2" , DomainMatrix (intDomain 1 3) (DomainTuple [intDomain 0 9,DomainMatrix (intDomain 1 2) (intDomain 0 9)]) , ConstantAbstract $ AbsLitMatrix (intDomain 1 3) - [ ConstantAbstract $ AbsLitTuple [ConstantInt 2,ConstantAbstract $ AbsLitMatrix (intDomain 1 2) [ConstantInt 1,ConstantInt 3]] - , ConstantAbstract $ AbsLitTuple [ConstantInt 4,ConstantAbstract $ AbsLitMatrix (intDomain 1 2) [ConstantInt 3,ConstantInt 5]] - , ConstantAbstract $ AbsLitTuple [ConstantInt 5,ConstantAbstract $ AbsLitMatrix (intDomain 1 2) [ConstantInt 5,ConstantInt 6]] + [ ConstantAbstract $ AbsLitTuple [ConstantInt Nothing 2,ConstantAbstract $ AbsLitMatrix (intDomain 1 2) [ConstantInt Nothing 1,ConstantInt Nothing 3]] + , ConstantAbstract $ AbsLitTuple [ConstantInt Nothing 4,ConstantAbstract $ AbsLitMatrix (intDomain 1 2) [ConstantInt Nothing 3,ConstantInt Nothing 5]] + , ConstantAbstract $ AbsLitTuple [ConstantInt Nothing 5,ConstantAbstract $ AbsLitMatrix (intDomain 1 2) [ConstantInt Nothing 5,ConstantInt Nothing 6]] ] ) ] low = [ ( "x_1" , DomainBool,ConstantBool False ) , ( "x_2_1" , DomainMatrix (intDomain 1 3) (intDomain 0 9) - , ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantInt 2,ConstantInt 4,ConstantInt 5]) + , ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantInt Nothing 2,ConstantInt Nothing 4,ConstantInt Nothing 5]) , ( "x_2_2" , DomainMatrix (intDomain 1 3) (DomainMatrix (intDomain 1 2) (intDomain 0 9)) , ConstantAbstract $ AbsLitMatrix (intDomain 1 3) - [ ConstantAbstract $ AbsLitMatrix (intDomain 1 2) [ConstantInt 1,ConstantInt 3] - , ConstantAbstract $ AbsLitMatrix (intDomain 1 2) [ConstantInt 3,ConstantInt 5] - , ConstantAbstract $ AbsLitMatrix (intDomain 1 2) [ConstantInt 5,ConstantInt 6] + [ ConstantAbstract $ AbsLitMatrix (intDomain 1 2) [ConstantInt Nothing 1,ConstantInt Nothing 3] + , ConstantAbstract $ AbsLitMatrix (intDomain 1 2) [ConstantInt Nothing 3,ConstantInt Nothing 5] + , ConstantAbstract $ AbsLitMatrix (intDomain 1 2) [ConstantInt Nothing 5,ConstantInt Nothing 6] ] ) ] in testCases "x" highDomain highConstant Just mid low @@ -618,134 +618,134 @@ tests = testGroup "representations" , testCase "Explicit: set (size 4) of int {auto}" $ testCasesAuto "x" ( DomainSet Set_Explicit - (SetAttr (SizeAttr_Size (ConstantInt 4))) + (SetAttr (SizeAttr_Size (ConstantInt Nothing 4))) (intDomain 0 9) ) ( ConstantAbstract $ AbsLitSet - [ConstantInt 2, ConstantInt 3, ConstantInt 5, ConstantInt 6] ) + [ConstantInt Nothing 2, ConstantInt Nothing 3, ConstantInt Nothing 5, ConstantInt Nothing 6] ) , testCase "Explicit: set (size 4) of int" $ let highDomain = DomainSet Set_Explicit - (SetAttr (SizeAttr_Size (ConstantInt 4))) + (SetAttr (SizeAttr_Size (ConstantInt Nothing 4))) (intDomain 0 9) highConstant = ConstantAbstract $ AbsLitSet - [ConstantInt 2, ConstantInt 3, ConstantInt 5, ConstantInt 6] + [ConstantInt Nothing 2, ConstantInt Nothing 3, ConstantInt Nothing 5, ConstantInt Nothing 6] low = [ ( "x_Explicit" , DomainMatrix (intDomain 1 4) (intDomain 0 9) , ConstantAbstract $ AbsLitMatrix (intDomain 1 4) - [ConstantInt 2,ConstantInt 3,ConstantInt 5,ConstantInt 6] + [ConstantInt Nothing 2,ConstantInt Nothing 3,ConstantInt Nothing 5,ConstantInt Nothing 6] ) ] in testCases "x" highDomain highConstant Just low low , testCase "Explicit: set (size 4) of set (size 2) of int {auto}" $ testCasesAuto "x" - ( DomainSet Set_Explicit (SetAttr (SizeAttr_Size (ConstantInt 4))) - ( DomainSet Set_Explicit (SetAttr (SizeAttr_Size (ConstantInt 2))) + ( DomainSet Set_Explicit (SetAttr (SizeAttr_Size (ConstantInt Nothing 4))) + ( DomainSet Set_Explicit (SetAttr (SizeAttr_Size (ConstantInt Nothing 2))) (intDomain 0 9) ) ) ( ConstantAbstract $ AbsLitSet - [ ConstantAbstract $ AbsLitSet [ConstantInt 2, ConstantInt 3] - , ConstantAbstract $ AbsLitSet [ConstantInt 5, ConstantInt 6] - , ConstantAbstract $ AbsLitSet [ConstantInt 5, ConstantInt 7] - , ConstantAbstract $ AbsLitSet [ConstantInt 5, ConstantInt 8] + [ ConstantAbstract $ AbsLitSet [ConstantInt Nothing 2, ConstantInt Nothing 3] + , ConstantAbstract $ AbsLitSet [ConstantInt Nothing 5, ConstantInt Nothing 6] + , ConstantAbstract $ AbsLitSet [ConstantInt Nothing 5, ConstantInt Nothing 7] + , ConstantAbstract $ AbsLitSet [ConstantInt Nothing 5, ConstantInt Nothing 8] ] ) , testCase "Explicit: set (size 4) of set (size 2) of int" $ let highDomain = - DomainSet Set_Explicit (SetAttr (SizeAttr_Size (ConstantInt 4))) - (DomainSet Set_Explicit (SetAttr (SizeAttr_Size (ConstantInt 2))) + DomainSet Set_Explicit (SetAttr (SizeAttr_Size (ConstantInt Nothing 4))) + (DomainSet Set_Explicit (SetAttr (SizeAttr_Size (ConstantInt Nothing 2))) (intDomain 0 9)) highConstant = ConstantAbstract $ AbsLitSet - [ ConstantAbstract $ AbsLitSet [ConstantInt 2, ConstantInt 3] - , ConstantAbstract $ AbsLitSet [ConstantInt 5, ConstantInt 6] - , ConstantAbstract $ AbsLitSet [ConstantInt 5, ConstantInt 7] - , ConstantAbstract $ AbsLitSet [ConstantInt 5, ConstantInt 8] + [ ConstantAbstract $ AbsLitSet [ConstantInt Nothing 2, ConstantInt Nothing 3] + , ConstantAbstract $ AbsLitSet [ConstantInt Nothing 5, ConstantInt Nothing 6] + , ConstantAbstract $ AbsLitSet [ConstantInt Nothing 5, ConstantInt Nothing 7] + , ConstantAbstract $ AbsLitSet [ConstantInt Nothing 5, ConstantInt Nothing 8] ] mid = [ ( "x_ExplicitR3" - , DomainMatrix (intDomain 1 4) (DomainSet Set_Explicit (SetAttr (SizeAttr_Size (ConstantInt 2))) (intDomain 0 9)) + , DomainMatrix (intDomain 1 4) (DomainSet Set_Explicit (SetAttr (SizeAttr_Size (ConstantInt Nothing 2))) (intDomain 0 9)) , ConstantAbstract $ AbsLitMatrix (intDomain 1 4) - [ ConstantAbstract $ AbsLitSet [ConstantInt 2, ConstantInt 3] - , ConstantAbstract $ AbsLitSet [ConstantInt 5, ConstantInt 6] - , ConstantAbstract $ AbsLitSet [ConstantInt 5, ConstantInt 7] - , ConstantAbstract $ AbsLitSet [ConstantInt 5, ConstantInt 8] + [ ConstantAbstract $ AbsLitSet [ConstantInt Nothing 2, ConstantInt Nothing 3] + , ConstantAbstract $ AbsLitSet [ConstantInt Nothing 5, ConstantInt Nothing 6] + , ConstantAbstract $ AbsLitSet [ConstantInt Nothing 5, ConstantInt Nothing 7] + , ConstantAbstract $ AbsLitSet [ConstantInt Nothing 5, ConstantInt Nothing 8] ] ) ] low = [ ( "x_ExplicitR3_Explicit" , DomainMatrix (intDomain 1 4) (DomainMatrix (intDomain 1 2) (intDomain 0 9)) , ConstantAbstract $ AbsLitMatrix (intDomain 1 4) - [ ConstantAbstract $ AbsLitMatrix (intDomain 1 2) [ConstantInt 2, ConstantInt 3] - , ConstantAbstract $ AbsLitMatrix (intDomain 1 2) [ConstantInt 5, ConstantInt 6] - , ConstantAbstract $ AbsLitMatrix (intDomain 1 2) [ConstantInt 5, ConstantInt 7] - , ConstantAbstract $ AbsLitMatrix (intDomain 1 2) [ConstantInt 5, ConstantInt 8] + [ ConstantAbstract $ AbsLitMatrix (intDomain 1 2) [ConstantInt Nothing 2, ConstantInt Nothing 3] + , ConstantAbstract $ AbsLitMatrix (intDomain 1 2) [ConstantInt Nothing 5, ConstantInt Nothing 6] + , ConstantAbstract $ AbsLitMatrix (intDomain 1 2) [ConstantInt Nothing 5, ConstantInt Nothing 7] + , ConstantAbstract $ AbsLitMatrix (intDomain 1 2) [ConstantInt Nothing 5, ConstantInt Nothing 8] ] ) ] in testCases "x" highDomain highConstant Just mid low , testCase "Explicit: set (size 4) of set (size 2) of (int, bool) {auto}" $ testCasesAuto "x" - ( DomainSet Set_Explicit (SetAttr (SizeAttr_Size (ConstantInt 4))) - ( DomainSet Set_Explicit (SetAttr (SizeAttr_Size (ConstantInt 2))) + ( DomainSet Set_Explicit (SetAttr (SizeAttr_Size (ConstantInt Nothing 4))) + ( DomainSet Set_Explicit (SetAttr (SizeAttr_Size (ConstantInt Nothing 2))) (DomainTuple [intDomain 0 9, DomainBool]) ) ) ( ConstantAbstract $ AbsLitSet - [ ConstantAbstract $ AbsLitSet [ ConstantAbstract $ AbsLitTuple [ConstantInt 2, ConstantBool False] - , ConstantAbstract $ AbsLitTuple [ConstantInt 3, ConstantBool True ] + [ ConstantAbstract $ AbsLitSet [ ConstantAbstract $ AbsLitTuple [ConstantInt Nothing 2, ConstantBool False] + , ConstantAbstract $ AbsLitTuple [ConstantInt Nothing 3, ConstantBool True ] ] - , ConstantAbstract $ AbsLitSet [ ConstantAbstract $ AbsLitTuple [ConstantInt 5, ConstantBool True ] - , ConstantAbstract $ AbsLitTuple [ConstantInt 6, ConstantBool True ] + , ConstantAbstract $ AbsLitSet [ ConstantAbstract $ AbsLitTuple [ConstantInt Nothing 5, ConstantBool True ] + , ConstantAbstract $ AbsLitTuple [ConstantInt Nothing 6, ConstantBool True ] ] - , ConstantAbstract $ AbsLitSet [ ConstantAbstract $ AbsLitTuple [ConstantInt 5, ConstantBool True ] - , ConstantAbstract $ AbsLitTuple [ConstantInt 7, ConstantBool False] + , ConstantAbstract $ AbsLitSet [ ConstantAbstract $ AbsLitTuple [ConstantInt Nothing 5, ConstantBool True ] + , ConstantAbstract $ AbsLitTuple [ConstantInt Nothing 7, ConstantBool False] ] - , ConstantAbstract $ AbsLitSet [ ConstantAbstract $ AbsLitTuple [ConstantInt 5, ConstantBool False] - , ConstantAbstract $ AbsLitTuple [ConstantInt 8, ConstantBool False] + , ConstantAbstract $ AbsLitSet [ ConstantAbstract $ AbsLitTuple [ConstantInt Nothing 5, ConstantBool False] + , ConstantAbstract $ AbsLitTuple [ConstantInt Nothing 8, ConstantBool False] ] ] ) , testCase "Explicit: set (size 4) of (int, set (size 2) of (int, bool)) {auto}" $ testCasesAuto "x" - ( DomainSet Set_Explicit (SetAttr (SizeAttr_Size (ConstantInt 4))) + ( DomainSet Set_Explicit (SetAttr (SizeAttr_Size (ConstantInt Nothing 4))) ( DomainTuple [ intDomain 0 8 - , DomainSet Set_Explicit (SetAttr (SizeAttr_Size (ConstantInt 2))) + , DomainSet Set_Explicit (SetAttr (SizeAttr_Size (ConstantInt Nothing 2))) (DomainTuple [intDomain 0 9, DomainBool]) ] ) ) ( ConstantAbstract $ AbsLitSet [ ConstantAbstract $ AbsLitTuple - [ ConstantInt 1 + [ ConstantInt Nothing 1 , ConstantAbstract $ AbsLitSet - [ ConstantAbstract $ AbsLitTuple [ConstantInt 2, ConstantBool False] - , ConstantAbstract $ AbsLitTuple [ConstantInt 3, ConstantBool True ] + [ ConstantAbstract $ AbsLitTuple [ConstantInt Nothing 2, ConstantBool False] + , ConstantAbstract $ AbsLitTuple [ConstantInt Nothing 3, ConstantBool True ] ] ] , ConstantAbstract $ AbsLitTuple - [ ConstantInt 2 + [ ConstantInt Nothing 2 , ConstantAbstract $ AbsLitSet - [ ConstantAbstract $ AbsLitTuple [ConstantInt 5, ConstantBool True ] - , ConstantAbstract $ AbsLitTuple [ConstantInt 6, ConstantBool True ] + [ ConstantAbstract $ AbsLitTuple [ConstantInt Nothing 5, ConstantBool True ] + , ConstantAbstract $ AbsLitTuple [ConstantInt Nothing 6, ConstantBool True ] ] ] , ConstantAbstract $ AbsLitTuple - [ ConstantInt 3 + [ ConstantInt Nothing 3 , ConstantAbstract $ AbsLitSet - [ ConstantAbstract $ AbsLitTuple [ConstantInt 5, ConstantBool True ] - , ConstantAbstract $ AbsLitTuple [ConstantInt 7, ConstantBool False] + [ ConstantAbstract $ AbsLitTuple [ConstantInt Nothing 5, ConstantBool True ] + , ConstantAbstract $ AbsLitTuple [ConstantInt Nothing 7, ConstantBool False] ] ] , ConstantAbstract $ AbsLitTuple - [ ConstantInt 4 + [ ConstantInt Nothing 4 , ConstantAbstract $ AbsLitSet - [ ConstantAbstract $ AbsLitTuple [ConstantInt 5, ConstantBool False] - , ConstantAbstract $ AbsLitTuple [ConstantInt 8, ConstantBool False] + [ ConstantAbstract $ AbsLitTuple [ConstantInt Nothing 5, ConstantBool False] + , ConstantAbstract $ AbsLitTuple [ConstantInt Nothing 8, ConstantBool False] ] ] ] ) @@ -754,64 +754,64 @@ tests = testGroup "representations" , testCase "ExplicitVarSizeWithMarker: set (maxSize 4) of int {auto}" $ testCasesAuto "x" ( DomainSet Set_ExplicitVarSizeWithMarker - (SetAttr (SizeAttr_MaxSize (ConstantInt 4))) + (SetAttr (SizeAttr_MaxSize (ConstantInt Nothing 4))) (intDomain 0 9) ) - ( ConstantAbstract $ AbsLitSet [ConstantInt 2, ConstantInt 5] ) + ( ConstantAbstract $ AbsLitSet [ConstantInt Nothing 2, ConstantInt Nothing 5] ) , testCase "ExplicitVarSizeWithMarker: set (maxSize 4) of int" $ let highDomain = - DomainSet Set_ExplicitVarSizeWithMarker (SetAttr (SizeAttr_MaxSize (ConstantInt 4))) (intDomain 0 9) + DomainSet Set_ExplicitVarSizeWithMarker (SetAttr (SizeAttr_MaxSize (ConstantInt Nothing 4))) (intDomain 0 9) highConstant = - ConstantAbstract $ AbsLitSet [ConstantInt 2, ConstantInt 5] + ConstantAbstract $ AbsLitSet [ConstantInt Nothing 2, ConstantInt Nothing 5] low = [ ( "x_ExplicitVarSizeWithMarker_Marker" , intDomain 0 4 - , ConstantInt 2 + , ConstantInt Nothing 2 ) , ( "x_ExplicitVarSizeWithMarker_Values" , DomainMatrix (intDomain 1 4) (intDomain 0 9) - , ConstantAbstract $ AbsLitMatrix (intDomain 1 4) [ConstantInt 2,ConstantInt 5,ConstantInt 0,ConstantInt 0] + , ConstantAbstract $ AbsLitMatrix (intDomain 1 4) [ConstantInt Nothing 2,ConstantInt Nothing 5,ConstantInt Nothing 0,ConstantInt Nothing 0] ) ] in testCases "x" highDomain highConstant Just low low , testCase "ExplicitVarSizeWithMarker: set (maxSize 4) of set (maxSize 3) int {auto}" $ testCasesAuto "x" - ( DomainSet Set_ExplicitVarSizeWithMarker (SetAttr (SizeAttr_MaxSize (ConstantInt 4))) - ( DomainSet Set_ExplicitVarSizeWithMarker (SetAttr (SizeAttr_MaxSize (ConstantInt 3))) + ( DomainSet Set_ExplicitVarSizeWithMarker (SetAttr (SizeAttr_MaxSize (ConstantInt Nothing 4))) + ( DomainSet Set_ExplicitVarSizeWithMarker (SetAttr (SizeAttr_MaxSize (ConstantInt Nothing 3))) (intDomain 0 9) ) ) ( ConstantAbstract $ AbsLitSet - [ ConstantAbstract $ AbsLitSet [ConstantInt 2] - , ConstantAbstract $ AbsLitSet [ConstantInt 2, ConstantInt 5] - , ConstantAbstract $ AbsLitSet [ConstantInt 3, ConstantInt 4, ConstantInt 6] + [ ConstantAbstract $ AbsLitSet [ConstantInt Nothing 2] + , ConstantAbstract $ AbsLitSet [ConstantInt Nothing 2, ConstantInt Nothing 5] + , ConstantAbstract $ AbsLitSet [ConstantInt Nothing 3, ConstantInt Nothing 4, ConstantInt Nothing 6] ] ) , testCase "ExplicitVarSizeWithMarker: set (maxSize 4) of set (maxSize 3) int" $ let highDomain = - DomainSet Set_ExplicitVarSizeWithMarker (SetAttr (SizeAttr_MaxSize (ConstantInt 4))) - ( DomainSet Set_ExplicitVarSizeWithMarker (SetAttr (SizeAttr_MaxSize (ConstantInt 3))) + DomainSet Set_ExplicitVarSizeWithMarker (SetAttr (SizeAttr_MaxSize (ConstantInt Nothing 4))) + ( DomainSet Set_ExplicitVarSizeWithMarker (SetAttr (SizeAttr_MaxSize (ConstantInt Nothing 3))) (intDomain 0 9) ) highConstant = ConstantAbstract $ AbsLitSet - [ ConstantAbstract $ AbsLitSet [ConstantInt 2] - , ConstantAbstract $ AbsLitSet [ConstantInt 2, ConstantInt 5] - , ConstantAbstract $ AbsLitSet [ConstantInt 3, ConstantInt 4, ConstantInt 6] + [ ConstantAbstract $ AbsLitSet [ConstantInt Nothing 2] + , ConstantAbstract $ AbsLitSet [ConstantInt Nothing 2, ConstantInt Nothing 5] + , ConstantAbstract $ AbsLitSet [ConstantInt Nothing 3, ConstantInt Nothing 4, ConstantInt Nothing 6] ] mid = [ ( "x_ExplicitVarSizeWithMarkerR5_Marker" , intDomain 0 4 - , ConstantInt 3 + , ConstantInt Nothing 3 ) , ( "x_ExplicitVarSizeWithMarkerR5_Values" - , DomainMatrix (intDomain 1 4) (DomainSet Set_ExplicitVarSizeWithMarker (SetAttr (SizeAttr_MaxSize (ConstantInt 3))) (intDomain 0 9)) + , DomainMatrix (intDomain 1 4) (DomainSet Set_ExplicitVarSizeWithMarker (SetAttr (SizeAttr_MaxSize (ConstantInt Nothing 3))) (intDomain 0 9)) , ConstantAbstract $ AbsLitMatrix (intDomain 1 4) - [ ConstantAbstract $ AbsLitSet [ConstantInt 2] - , ConstantAbstract $ AbsLitSet [ConstantInt 2,ConstantInt 5] - , ConstantAbstract $ AbsLitSet [ConstantInt 3,ConstantInt 4,ConstantInt 6] + [ ConstantAbstract $ AbsLitSet [ConstantInt Nothing 2] + , ConstantAbstract $ AbsLitSet [ConstantInt Nothing 2,ConstantInt Nothing 5] + , ConstantAbstract $ AbsLitSet [ConstantInt Nothing 3,ConstantInt Nothing 4,ConstantInt Nothing 6] , ConstantAbstract $ AbsLitSet [] ] ) @@ -819,19 +819,19 @@ tests = testGroup "representations" low = [ ( "x_ExplicitVarSizeWithMarkerR5_Marker" , intDomain 0 4 - , ConstantInt 3 + , ConstantInt Nothing 3 ) , ( "x_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker" , DomainMatrix (intDomain 1 4) (intDomain 0 3) - , ConstantAbstract $ AbsLitMatrix (intDomain 1 4) [ConstantInt 1,ConstantInt 2,ConstantInt 3,ConstantInt 0] + , ConstantAbstract $ AbsLitMatrix (intDomain 1 4) [ConstantInt Nothing 1,ConstantInt Nothing 2,ConstantInt Nothing 3,ConstantInt Nothing 0] ) , ( "x_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values" , DomainMatrix (intDomain 1 4) (DomainMatrix (intDomain 1 3) (intDomain 0 9)) , ConstantAbstract $ AbsLitMatrix (intDomain 1 4) - [ ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantInt 2,ConstantInt 0,ConstantInt 0] - , ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantInt 2,ConstantInt 5,ConstantInt 0] - , ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantInt 3,ConstantInt 4,ConstantInt 6] - , ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantInt 0,ConstantInt 0,ConstantInt 0] + [ ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantInt Nothing 2,ConstantInt Nothing 0,ConstantInt Nothing 0] + , ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantInt Nothing 2,ConstantInt Nothing 5,ConstantInt Nothing 0] + , ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantInt Nothing 3,ConstantInt Nothing 4,ConstantInt Nothing 6] + , ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantInt Nothing 0,ConstantInt Nothing 0,ConstantInt Nothing 0] ] ) ] @@ -841,16 +841,16 @@ tests = testGroup "representations" , testCase "ExplicitVarSizeWithFlags: set (maxSize 4) of int {auto}" $ testCasesAuto "x" ( DomainSet Set_ExplicitVarSizeWithFlags - (SetAttr (SizeAttr_MaxSize (ConstantInt 4))) + (SetAttr (SizeAttr_MaxSize (ConstantInt Nothing 4))) (intDomain 0 9) ) - ( ConstantAbstract $ AbsLitSet [ConstantInt 2, ConstantInt 5] ) + ( ConstantAbstract $ AbsLitSet [ConstantInt Nothing 2, ConstantInt Nothing 5] ) , testCase "ExplicitVarSizeWithFlags: set (maxSize 4) of int" $ let highDomain = - DomainSet Set_ExplicitVarSizeWithFlags (SetAttr (SizeAttr_MaxSize (ConstantInt 4))) (intDomain 0 9) + DomainSet Set_ExplicitVarSizeWithFlags (SetAttr (SizeAttr_MaxSize (ConstantInt Nothing 4))) (intDomain 0 9) highConstant = - ConstantAbstract $ AbsLitSet [ConstantInt 2, ConstantInt 5] + ConstantAbstract $ AbsLitSet [ConstantInt Nothing 2, ConstantInt Nothing 5] low = [ ( "x_ExplicitVarSizeWithFlags_Flags" , DomainMatrix (intDomain 1 4) DomainBool @@ -858,35 +858,35 @@ tests = testGroup "representations" ) , ( "x_ExplicitVarSizeWithFlags_Values" , DomainMatrix (intDomain 1 4) (intDomain 0 9) - , ConstantAbstract $ AbsLitMatrix (intDomain 1 4) [ConstantInt 2,ConstantInt 5,ConstantInt 0,ConstantInt 0] + , ConstantAbstract $ AbsLitMatrix (intDomain 1 4) [ConstantInt Nothing 2,ConstantInt Nothing 5,ConstantInt Nothing 0,ConstantInt Nothing 0] ) ] in testCases "x" highDomain highConstant Just low low , testCase "ExplicitVarSizeWithFlags: set (maxSize 4) of set (maxSize 3) int {auto}" $ testCasesAuto "x" - ( DomainSet Set_ExplicitVarSizeWithFlags (SetAttr (SizeAttr_MaxSize (ConstantInt 4))) - ( DomainSet Set_ExplicitVarSizeWithFlags (SetAttr (SizeAttr_MaxSize (ConstantInt 3))) + ( DomainSet Set_ExplicitVarSizeWithFlags (SetAttr (SizeAttr_MaxSize (ConstantInt Nothing 4))) + ( DomainSet Set_ExplicitVarSizeWithFlags (SetAttr (SizeAttr_MaxSize (ConstantInt Nothing 3))) (intDomain 0 9) ) ) ( ConstantAbstract $ AbsLitSet - [ ConstantAbstract $ AbsLitSet [ConstantInt 2] - , ConstantAbstract $ AbsLitSet [ConstantInt 2, ConstantInt 5] - , ConstantAbstract $ AbsLitSet [ConstantInt 3, ConstantInt 4, ConstantInt 6] + [ ConstantAbstract $ AbsLitSet [ConstantInt Nothing 2] + , ConstantAbstract $ AbsLitSet [ConstantInt Nothing 2, ConstantInt Nothing 5] + , ConstantAbstract $ AbsLitSet [ConstantInt Nothing 3, ConstantInt Nothing 4, ConstantInt Nothing 6] ] ) , testCase "ExplicitVarSizeWithFlags: set (maxSize 4) of set (maxSize 3) int" $ let highDomain = - DomainSet Set_ExplicitVarSizeWithFlags (SetAttr (SizeAttr_MaxSize (ConstantInt 4))) - ( DomainSet Set_ExplicitVarSizeWithFlags (SetAttr (SizeAttr_MaxSize (ConstantInt 3))) + DomainSet Set_ExplicitVarSizeWithFlags (SetAttr (SizeAttr_MaxSize (ConstantInt Nothing 4))) + ( DomainSet Set_ExplicitVarSizeWithFlags (SetAttr (SizeAttr_MaxSize (ConstantInt Nothing 3))) (intDomain 0 9) ) highConstant = ConstantAbstract $ AbsLitSet - [ ConstantAbstract $ AbsLitSet [ConstantInt 2] - , ConstantAbstract $ AbsLitSet [ConstantInt 2, ConstantInt 5] - , ConstantAbstract $ AbsLitSet [ConstantInt 3, ConstantInt 4, ConstantInt 6] + [ ConstantAbstract $ AbsLitSet [ConstantInt Nothing 2] + , ConstantAbstract $ AbsLitSet [ConstantInt Nothing 2, ConstantInt Nothing 5] + , ConstantAbstract $ AbsLitSet [ConstantInt Nothing 3, ConstantInt Nothing 4, ConstantInt Nothing 6] ] mid = [ ( "x_ExplicitVarSizeWithFlagsR4_Flags" @@ -894,11 +894,11 @@ tests = testGroup "representations" , ConstantAbstract $ AbsLitMatrix (intDomain 1 4) [ConstantBool True,ConstantBool True,ConstantBool True,ConstantBool False] ) , ( "x_ExplicitVarSizeWithFlagsR4_Values" - , DomainMatrix (intDomain 1 4) (DomainSet Set_ExplicitVarSizeWithFlags (SetAttr (SizeAttr_MaxSize (ConstantInt 3))) (intDomain 0 9)) + , DomainMatrix (intDomain 1 4) (DomainSet Set_ExplicitVarSizeWithFlags (SetAttr (SizeAttr_MaxSize (ConstantInt Nothing 3))) (intDomain 0 9)) , ConstantAbstract $ AbsLitMatrix (intDomain 1 4) - [ ConstantAbstract $ AbsLitSet [ConstantInt 2] - , ConstantAbstract $ AbsLitSet [ConstantInt 2,ConstantInt 5] - , ConstantAbstract $ AbsLitSet [ConstantInt 3,ConstantInt 4,ConstantInt 6] + [ ConstantAbstract $ AbsLitSet [ConstantInt Nothing 2] + , ConstantAbstract $ AbsLitSet [ConstantInt Nothing 2,ConstantInt Nothing 5] + , ConstantAbstract $ AbsLitSet [ConstantInt Nothing 3,ConstantInt Nothing 4,ConstantInt Nothing 6] , ConstantAbstract $ AbsLitSet [] ] ) @@ -920,10 +920,10 @@ tests = testGroup "representations" , ( "x_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Values" , DomainMatrix (intDomain 1 4) (DomainMatrix (intDomain 1 3) (intDomain 0 9)) , ConstantAbstract $ AbsLitMatrix (intDomain 1 4) - [ ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantInt 2,ConstantInt 0,ConstantInt 0] - , ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantInt 2,ConstantInt 5,ConstantInt 0] - , ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantInt 3,ConstantInt 4,ConstantInt 6] - , ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantInt 0,ConstantInt 0,ConstantInt 0] + [ ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantInt Nothing 2,ConstantInt Nothing 0,ConstantInt Nothing 0] + , ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantInt Nothing 2,ConstantInt Nothing 5,ConstantInt Nothing 0] + , ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantInt Nothing 3,ConstantInt Nothing 4,ConstantInt Nothing 6] + , ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantInt Nothing 0,ConstantInt Nothing 0,ConstantInt Nothing 0] ] ) ] in testCases "x" highDomain highConstant Just mid low @@ -932,16 +932,16 @@ tests = testGroup "representations" , testCase "Occurrence: set (maxSize 4) of int {auto}" $ testCasesAuto "x" ( DomainSet Set_Occurrence - (SetAttr (SizeAttr_MaxSize (ConstantInt 4))) + (SetAttr (SizeAttr_MaxSize (ConstantInt Nothing 4))) (intDomain 0 9) ) - ( ConstantAbstract $ AbsLitSet [ConstantInt 2, ConstantInt 5] ) + ( ConstantAbstract $ AbsLitSet [ConstantInt Nothing 2, ConstantInt Nothing 5] ) , testCase "Occurrence: set (maxSize 4) of int" $ let highDomain = - DomainSet Set_Occurrence (SetAttr (SizeAttr_MaxSize (ConstantInt 4))) (intDomain 0 9) + DomainSet Set_Occurrence (SetAttr (SizeAttr_MaxSize (ConstantInt Nothing 4))) (intDomain 0 9) highConstant = - ConstantAbstract $ AbsLitSet [ConstantInt 2, ConstantInt 5] + ConstantAbstract $ AbsLitSet [ConstantInt Nothing 2, ConstantInt Nothing 5] low = [ ( "x_Occurrence" , DomainMatrix (intDomain 0 9) DomainBool @@ -962,41 +962,41 @@ tests = testGroup "representations" in testCases "x" highDomain highConstant Just low low , testCase "ExplicitVarSizeWithMarker & Occurrence: set (maxSize 4) of set (maxSize 3) int {auto}" $ testCasesAuto "x" - ( DomainSet Set_ExplicitVarSizeWithMarker (SetAttr (SizeAttr_MaxSize (ConstantInt 4))) - ( DomainSet Set_Occurrence (SetAttr (SizeAttr_MaxSize (ConstantInt 3))) + ( DomainSet Set_ExplicitVarSizeWithMarker (SetAttr (SizeAttr_MaxSize (ConstantInt Nothing 4))) + ( DomainSet Set_Occurrence (SetAttr (SizeAttr_MaxSize (ConstantInt Nothing 3))) (intDomain 0 9) ) ) ( ConstantAbstract $ AbsLitSet - [ ConstantAbstract $ AbsLitSet [ConstantInt 2] - , ConstantAbstract $ AbsLitSet [ConstantInt 2, ConstantInt 5] - , ConstantAbstract $ AbsLitSet [ConstantInt 3, ConstantInt 4, ConstantInt 6] + [ ConstantAbstract $ AbsLitSet [ConstantInt Nothing 2] + , ConstantAbstract $ AbsLitSet [ConstantInt Nothing 2, ConstantInt Nothing 5] + , ConstantAbstract $ AbsLitSet [ConstantInt Nothing 3, ConstantInt Nothing 4, ConstantInt Nothing 6] ] ) , testCase "ExplicitVarSizeWithMarker & Occurrence: set (maxSize 4) of set (maxSize 3) int" $ let highDomain = - DomainSet Set_ExplicitVarSizeWithMarker (SetAttr (SizeAttr_MaxSize (ConstantInt 4))) - ( DomainSet Set_Occurrence (SetAttr (SizeAttr_MaxSize (ConstantInt 3))) + DomainSet Set_ExplicitVarSizeWithMarker (SetAttr (SizeAttr_MaxSize (ConstantInt Nothing 4))) + ( DomainSet Set_Occurrence (SetAttr (SizeAttr_MaxSize (ConstantInt Nothing 3))) (intDomain 0 9) ) highConstant = ConstantAbstract $ AbsLitSet - [ ConstantAbstract $ AbsLitSet [ConstantInt 2] - , ConstantAbstract $ AbsLitSet [ConstantInt 2, ConstantInt 5] - , ConstantAbstract $ AbsLitSet [ConstantInt 3, ConstantInt 4, ConstantInt 6] + [ ConstantAbstract $ AbsLitSet [ConstantInt Nothing 2] + , ConstantAbstract $ AbsLitSet [ConstantInt Nothing 2, ConstantInt Nothing 5] + , ConstantAbstract $ AbsLitSet [ConstantInt Nothing 3, ConstantInt Nothing 4, ConstantInt Nothing 6] ] mid = [ ( "x_ExplicitVarSizeWithMarkerR2_Marker" , intDomain 0 4 - , ConstantInt 3 + , ConstantInt Nothing 3 ) , ( "x_ExplicitVarSizeWithMarkerR2_Values" - , DomainMatrix (intDomain 1 4) (DomainSet Set_Occurrence (SetAttr (SizeAttr_MaxSize (ConstantInt 3))) (intDomain 0 9)) + , DomainMatrix (intDomain 1 4) (DomainSet Set_Occurrence (SetAttr (SizeAttr_MaxSize (ConstantInt Nothing 3))) (intDomain 0 9)) , ConstantAbstract $ AbsLitMatrix (intDomain 1 4) - [ ConstantAbstract $ AbsLitSet [ConstantInt 2] - , ConstantAbstract $ AbsLitSet [ConstantInt 2,ConstantInt 5] - , ConstantAbstract $ AbsLitSet [ConstantInt 3,ConstantInt 4,ConstantInt 6] + [ ConstantAbstract $ AbsLitSet [ConstantInt Nothing 2] + , ConstantAbstract $ AbsLitSet [ConstantInt Nothing 2,ConstantInt Nothing 5] + , ConstantAbstract $ AbsLitSet [ConstantInt Nothing 3,ConstantInt Nothing 4,ConstantInt Nothing 6] , ConstantAbstract $ AbsLitSet [] ] ) @@ -1004,7 +1004,7 @@ tests = testGroup "representations" low = [ ( "x_ExplicitVarSizeWithMarkerR2_Marker" , intDomain 0 4 - , ConstantInt 3 + , ConstantInt Nothing 3 ) , ( "x_ExplicitVarSizeWithMarkerR2_Values_Occurrence" , DomainMatrix (intDomain 1 4) (DomainMatrix (intDomain 0 9) DomainBool) @@ -1027,29 +1027,29 @@ tests = testGroup "representations" in testCases "x" highDomain highConstant Just mid low , testCase "ExplicitVarSizeWithFlags & Occurrence: set (maxSize 4) of set (maxSize 3) int {auto}" $ testCasesAuto "x" - ( DomainSet Set_ExplicitVarSizeWithFlags (SetAttr (SizeAttr_MaxSize (ConstantInt 4))) - ( DomainSet Set_Occurrence (SetAttr (SizeAttr_MaxSize (ConstantInt 3))) + ( DomainSet Set_ExplicitVarSizeWithFlags (SetAttr (SizeAttr_MaxSize (ConstantInt Nothing 4))) + ( DomainSet Set_Occurrence (SetAttr (SizeAttr_MaxSize (ConstantInt Nothing 3))) (intDomain 0 9) ) ) ( ConstantAbstract $ AbsLitSet - [ ConstantAbstract $ AbsLitSet [ConstantInt 2] - , ConstantAbstract $ AbsLitSet [ConstantInt 2, ConstantInt 5] - , ConstantAbstract $ AbsLitSet [ConstantInt 3, ConstantInt 4, ConstantInt 6] + [ ConstantAbstract $ AbsLitSet [ConstantInt Nothing 2] + , ConstantAbstract $ AbsLitSet [ConstantInt Nothing 2, ConstantInt Nothing 5] + , ConstantAbstract $ AbsLitSet [ConstantInt Nothing 3, ConstantInt Nothing 4, ConstantInt Nothing 6] ] ) , testCase "ExplicitVarSizeWithFlags & Occurrence: set (maxSize 4) of set (maxSize 3) int" $ let highDomain = - DomainSet Set_ExplicitVarSizeWithFlags (SetAttr (SizeAttr_MaxSize (ConstantInt 4))) - ( DomainSet Set_Occurrence (SetAttr (SizeAttr_MaxSize (ConstantInt 3))) + DomainSet Set_ExplicitVarSizeWithFlags (SetAttr (SizeAttr_MaxSize (ConstantInt Nothing 4))) + ( DomainSet Set_Occurrence (SetAttr (SizeAttr_MaxSize (ConstantInt Nothing 3))) (intDomain 0 9) ) highConstant = ConstantAbstract $ AbsLitSet - [ ConstantAbstract $ AbsLitSet [ConstantInt 2] - , ConstantAbstract $ AbsLitSet [ConstantInt 2, ConstantInt 5] - , ConstantAbstract $ AbsLitSet [ConstantInt 3, ConstantInt 4, ConstantInt 6] + [ ConstantAbstract $ AbsLitSet [ConstantInt Nothing 2] + , ConstantAbstract $ AbsLitSet [ConstantInt Nothing 2, ConstantInt Nothing 5] + , ConstantAbstract $ AbsLitSet [ConstantInt Nothing 3, ConstantInt Nothing 4, ConstantInt Nothing 6] ] mid = [ ( "x_ExplicitVarSizeWithFlagsR2_Flags" @@ -1057,11 +1057,11 @@ tests = testGroup "representations" , ConstantAbstract $ AbsLitMatrix (intDomain 1 4) [ConstantBool True,ConstantBool True,ConstantBool True,ConstantBool False] ) , ( "x_ExplicitVarSizeWithFlagsR2_Values" - , DomainMatrix (intDomain 1 4) (DomainSet Set_Occurrence (SetAttr (SizeAttr_MaxSize (ConstantInt 3))) (intDomain 0 9)) + , DomainMatrix (intDomain 1 4) (DomainSet Set_Occurrence (SetAttr (SizeAttr_MaxSize (ConstantInt Nothing 3))) (intDomain 0 9)) , ConstantAbstract $ AbsLitMatrix (intDomain 1 4) - [ ConstantAbstract $ AbsLitSet [ConstantInt 2] - , ConstantAbstract $ AbsLitSet [ConstantInt 2,ConstantInt 5] - , ConstantAbstract $ AbsLitSet [ConstantInt 3,ConstantInt 4,ConstantInt 6] + [ ConstantAbstract $ AbsLitSet [ConstantInt Nothing 2] + , ConstantAbstract $ AbsLitSet [ConstantInt Nothing 2,ConstantInt Nothing 5] + , ConstantAbstract $ AbsLitSet [ConstantInt Nothing 3,ConstantInt Nothing 4,ConstantInt Nothing 6] , ConstantAbstract $ AbsLitSet [] ] ) @@ -1193,7 +1193,7 @@ downUpTest high = intDomain :: Default r => Integer -> Integer -> Domain r Constant -intDomain lb ub = defRepr $ mkDomainIntB (ConstantInt lb) (ConstantInt ub) +intDomain lb ub = defRepr $ mkDomainIntB (ConstantInt Nothing lb) (ConstantInt Nothing ub) dropConstant :: (a,b,c) -> (a,b) dropConstant (a,b,_) = (a,b) diff --git a/tests/custom/permutations/basic/26/stdout.expected b/tests/custom/permutations/basic/26/stdout.expected index 9d98db50a0..a70293f5c9 100644 --- a/tests/custom/permutations/basic/26/stdout.expected +++ b/tests/custom/permutations/basic/26/stdout.expected @@ -24,101 +24,81 @@ Copying solution to: permutation-permutation-000019.solution Copying solution to: permutation-permutation-000020.solution language Essence 1.3 -letting p be permutation((1, 5, 9, 4, 8, 3, 7, 2, 6)) -letting x be [1, 2, 3, 4, 5; int(1..5)] -letting y be [5, 6, 7, 8, 9; int(1..5)] +letting x be [THING1, THING2, THING3, THING4, THING5; int(1..5)] +letting y be [THING1, THING2, THING3, THING4, THING5; int(1..5)] language Essence 1.3 -letting p be permutation((1, 5, 9, 4, 8, 3, 7, 2, 6)) -letting x be [1, 2, 3, 5, 4; int(1..5)] -letting y be [5, 6, 7, 9, 8; int(1..5)] +letting x be [THING1, THING2, THING3, THING5, THING4; int(1..5)] +letting y be [THING1, THING2, THING3, THING5, THING4; int(1..5)] language Essence 1.3 -letting p be permutation((1, 5, 9, 4, 8, 3, 7, 2, 6)) -letting x be [1, 2, 4, 3, 5; int(1..5)] -letting y be [5, 6, 8, 7, 9; int(1..5)] +letting x be [THING1, THING2, THING4, THING3, THING5; int(1..5)] +letting y be [THING1, THING2, THING4, THING3, THING5; int(1..5)] language Essence 1.3 -letting p be permutation((1, 5, 9, 4, 8, 3, 7, 2, 6)) -letting x be [1, 2, 4, 5, 3; int(1..5)] -letting y be [5, 6, 8, 9, 7; int(1..5)] +letting x be [THING1, THING2, THING4, THING5, THING3; int(1..5)] +letting y be [THING1, THING2, THING4, THING5, THING3; int(1..5)] language Essence 1.3 -letting p be permutation((1, 5, 9, 4, 8, 3, 7, 2, 6)) -letting x be [1, 2, 5, 3, 4; int(1..5)] -letting y be [5, 6, 9, 7, 8; int(1..5)] +letting x be [THING1, THING2, THING5, THING3, THING4; int(1..5)] +letting y be [THING1, THING2, THING5, THING3, THING4; int(1..5)] language Essence 1.3 -letting p be permutation((1, 5, 9, 4, 8, 3, 7, 2, 6)) -letting x be [1, 2, 5, 4, 3; int(1..5)] -letting y be [5, 6, 9, 8, 7; int(1..5)] +letting x be [THING1, THING2, THING5, THING4, THING3; int(1..5)] +letting y be [THING1, THING2, THING5, THING4, THING3; int(1..5)] language Essence 1.3 -letting p be permutation((1, 5, 9, 4, 8, 3, 7, 2, 6)) -letting x be [1, 3, 2, 4, 5; int(1..5)] -letting y be [5, 7, 6, 8, 9; int(1..5)] +letting x be [THING1, THING3, THING2, THING4, THING5; int(1..5)] +letting y be [THING1, THING3, THING2, THING4, THING5; int(1..5)] language Essence 1.3 -letting p be permutation((1, 5, 9, 4, 8, 3, 7, 2, 6)) -letting x be [1, 3, 2, 5, 4; int(1..5)] -letting y be [5, 7, 6, 9, 8; int(1..5)] +letting x be [THING1, THING3, THING2, THING5, THING4; int(1..5)] +letting y be [THING1, THING3, THING2, THING5, THING4; int(1..5)] language Essence 1.3 -letting p be permutation((1, 5, 9, 4, 8, 3, 7, 2, 6)) -letting x be [1, 3, 4, 2, 5; int(1..5)] -letting y be [5, 7, 8, 6, 9; int(1..5)] +letting x be [THING1, THING3, THING4, THING2, THING5; int(1..5)] +letting y be [THING1, THING3, THING4, THING2, THING5; int(1..5)] language Essence 1.3 -letting p be permutation((1, 5, 9, 4, 8, 3, 7, 2, 6)) -letting x be [1, 3, 4, 5, 2; int(1..5)] -letting y be [5, 7, 8, 9, 6; int(1..5)] +letting x be [THING1, THING3, THING4, THING5, THING2; int(1..5)] +letting y be [THING1, THING3, THING4, THING5, THING2; int(1..5)] language Essence 1.3 -letting p be permutation((1, 5, 9, 4, 8, 3, 7, 2, 6)) -letting x be [1, 3, 5, 2, 4; int(1..5)] -letting y be [5, 7, 9, 6, 8; int(1..5)] +letting x be [THING1, THING3, THING5, THING2, THING4; int(1..5)] +letting y be [THING1, THING3, THING5, THING2, THING4; int(1..5)] language Essence 1.3 -letting p be permutation((1, 5, 9, 4, 8, 3, 7, 2, 6)) -letting x be [1, 3, 5, 4, 2; int(1..5)] -letting y be [5, 7, 9, 8, 6; int(1..5)] +letting x be [THING1, THING3, THING5, THING4, THING2; int(1..5)] +letting y be [THING1, THING3, THING5, THING4, THING2; int(1..5)] language Essence 1.3 -letting p be permutation((1, 5, 9, 4, 8, 3, 7, 2, 6)) -letting x be [1, 4, 2, 3, 5; int(1..5)] -letting y be [5, 8, 6, 7, 9; int(1..5)] +letting x be [THING1, THING4, THING2, THING3, THING5; int(1..5)] +letting y be [THING1, THING4, THING2, THING3, THING5; int(1..5)] language Essence 1.3 -letting p be permutation((1, 5, 9, 4, 8, 3, 7, 2, 6)) -letting x be [1, 4, 2, 5, 3; int(1..5)] -letting y be [5, 8, 6, 9, 7; int(1..5)] +letting x be [THING1, THING4, THING2, THING5, THING3; int(1..5)] +letting y be [THING1, THING4, THING2, THING5, THING3; int(1..5)] language Essence 1.3 -letting p be permutation((1, 5, 9, 4, 8, 3, 7, 2, 6)) -letting x be [1, 4, 3, 2, 5; int(1..5)] -letting y be [5, 8, 7, 6, 9; int(1..5)] +letting x be [THING1, THING4, THING3, THING2, THING5; int(1..5)] +letting y be [THING1, THING4, THING3, THING2, THING5; int(1..5)] language Essence 1.3 -letting p be permutation((1, 5, 9, 4, 8, 3, 7, 2, 6)) -letting x be [1, 4, 3, 5, 2; int(1..5)] -letting y be [5, 8, 7, 9, 6; int(1..5)] +letting x be [THING1, THING4, THING3, THING5, THING2; int(1..5)] +letting y be [THING1, THING4, THING3, THING5, THING2; int(1..5)] language Essence 1.3 -letting p be permutation((1, 5, 9, 4, 8, 3, 7, 2, 6)) -letting x be [1, 4, 5, 2, 3; int(1..5)] -letting y be [5, 8, 9, 6, 7; int(1..5)] +letting x be [THING1, THING4, THING5, THING2, THING3; int(1..5)] +letting y be [THING1, THING4, THING5, THING2, THING3; int(1..5)] language Essence 1.3 -letting p be permutation((1, 5, 9, 4, 8, 3, 7, 2, 6)) -letting x be [1, 4, 5, 3, 2; int(1..5)] -letting y be [5, 8, 9, 7, 6; int(1..5)] +letting x be [THING1, THING4, THING5, THING3, THING2; int(1..5)] +letting y be [THING1, THING4, THING5, THING3, THING2; int(1..5)] language Essence 1.3 -letting p be permutation((1, 5, 9, 4, 8, 3, 7, 2, 6)) -letting x be [1, 5, 2, 3, 4; int(1..5)] -letting y be [5, 9, 6, 7, 8; int(1..5)] +letting x be [THING1, THING5, THING2, THING3, THING4; int(1..5)] +letting y be [THING1, THING5, THING2, THING3, THING4; int(1..5)] language Essence 1.3 -letting p be permutation((1, 5, 9, 4, 8, 3, 7, 2, 6)) -letting x be [1, 5, 2, 4, 3; int(1..5)] -letting y be [5, 9, 6, 8, 7; int(1..5)] +letting x be [THING1, THING5, THING2, THING4, THING3; int(1..5)] +letting y be [THING1, THING5, THING2, THING4, THING3; int(1..5)] From 77f33865ad3d0327b71db2fa03e522ea6719b9d1 Mon Sep 17 00:00:00 2001 From: Fraser Dunlop Date: Mon, 22 Oct 2018 09:50:33 +0100 Subject: [PATCH 010/229] Merging --- Makefile | 12 ++ etc/build/default_envvars.sh | 4 +- etc/build/docker/Dockerfile | 121 +++++++++++++++++ etc/build/docker/README.md | 16 +++ etc/build/docker/sudoku.essence | 15 +++ etc/build/docker/sudoku.param | 11 ++ etc/build/download-minion.sh | 22 --- etc/build/install-bc_minisat_all.sh | 20 +++ etc/build/install-chuffed.sh | 23 ++++ etc/build/install-gecode.sh | 23 ++++ etc/build/install-glucose.sh | 21 +++ etc/build/install-lingeling.sh | 20 +-- etc/build/install-minion.sh | 42 +++--- etc/build/install-nbc_minisat_all.sh | 20 +++ etc/build/install-open-wbo.sh | 19 +++ etc/build/install-oscar-cbls.sh | 10 +- etc/build/install-savilerow.sh | 56 ++++---- etc/build/install-stack.sh | 34 +++-- etc/build/install.sh | 2 +- etc/build/silent-wrapper.sh | 29 ++++ etc/savilerow/savilerow.jar | Bin 652142 -> 653037 bytes src/Conjure/Language/Constant.hs | 127 ++++++++++++++++++ src/Conjure/Language/Domain.hs | 56 ++++++++ .../Language/Expression/DomainSizeOf.hs | 11 +- .../Language/Expression/Op/Internal/Common.hs | 19 ++- src/Conjure/Language/ParserC.hs | 34 ++++- src/Conjure/Language/Type.hs | 41 ++++++ src/Conjure/Rules/Horizontal/Set.hs | 13 +- .../Vertical/Sequence/ExplicitBounded.hs | 40 ++++++ src/Conjure/UI.hs | 15 ++- src/Conjure/UI/MainHelper.hs | 41 ++++-- src/Conjure/UI/Model.hs | 16 ++- .../function-literal-suggestion/func.essence | 1 + .../basic/function-literal-suggestion/p.param | 1 + .../basic/function-literal-suggestion/run.sh | 1 + .../stderr.expected | 3 + .../stdout.expected | 2 + tests/custom/basic/given-seq-seq/run.sh | 10 ++ .../custom/basic/given-seq-seq/seqseq.essence | 4 + tests/custom/basic/given-seq-seq/seqseq.param | 6 + .../basic/given-seq-seq/stdout.expected | 37 +++++ tests/custom/basic/matrix-slicing/run.sh | 10 ++ .../custom/basic/matrix-slicing/slice.essence | 6 + .../basic/matrix-slicing/stdout.expected | 30 +++++ .../parsing-enums-in-param/knapsack.essence | 13 ++ .../parsing-enums-in-param/knapsack.param | 22 +++ .../basic/parsing-enums-in-param/run.sh | 9 ++ .../parsing-enums-in-param/stdout.expected | 41 ++++++ tests/custom/help-text/conjure-help.txt | 16 ++- 49 files changed, 1015 insertions(+), 130 deletions(-) create mode 100644 etc/build/docker/Dockerfile create mode 100644 etc/build/docker/README.md create mode 100644 etc/build/docker/sudoku.essence create mode 100644 etc/build/docker/sudoku.param delete mode 100755 etc/build/download-minion.sh create mode 100755 etc/build/install-bc_minisat_all.sh create mode 100755 etc/build/install-chuffed.sh create mode 100755 etc/build/install-gecode.sh create mode 100755 etc/build/install-glucose.sh create mode 100755 etc/build/install-nbc_minisat_all.sh create mode 100755 etc/build/install-open-wbo.sh create mode 100755 etc/build/silent-wrapper.sh create mode 100644 tests/custom/basic/function-literal-suggestion/func.essence create mode 100644 tests/custom/basic/function-literal-suggestion/p.param create mode 100755 tests/custom/basic/function-literal-suggestion/run.sh create mode 100644 tests/custom/basic/function-literal-suggestion/stderr.expected create mode 100644 tests/custom/basic/function-literal-suggestion/stdout.expected create mode 100755 tests/custom/basic/given-seq-seq/run.sh create mode 100644 tests/custom/basic/given-seq-seq/seqseq.essence create mode 100644 tests/custom/basic/given-seq-seq/seqseq.param create mode 100644 tests/custom/basic/given-seq-seq/stdout.expected create mode 100755 tests/custom/basic/matrix-slicing/run.sh create mode 100644 tests/custom/basic/matrix-slicing/slice.essence create mode 100644 tests/custom/basic/matrix-slicing/stdout.expected create mode 100644 tests/custom/basic/parsing-enums-in-param/knapsack.essence create mode 100644 tests/custom/basic/parsing-enums-in-param/knapsack.param create mode 100755 tests/custom/basic/parsing-enums-in-param/run.sh create mode 100644 tests/custom/basic/parsing-enums-in-param/stdout.expected diff --git a/Makefile b/Makefile index 2c689220d4..d2ce3651b9 100644 --- a/Makefile +++ b/Makefile @@ -116,3 +116,15 @@ hlint: -i "Use ++" \ -i "Redundant return" \ -i "Monad law, left identity" + +.PHONY: solvers +solvers: + @etc/build/silent-wrapper.sh etc/build/install-minion.sh + @etc/build/silent-wrapper.sh etc/build/install-chuffed.sh + @etc/build/silent-wrapper.sh etc/build/install-gecode.sh + @etc/build/silent-wrapper.sh etc/build/install-glucose.sh + @etc/build/silent-wrapper.sh etc/build/install-lingeling.sh + @etc/build/silent-wrapper.sh etc/build/install-open-wbo.sh + @etc/build/silent-wrapper.sh etc/build/install-bc_minisat_all.sh + @etc/build/silent-wrapper.sh etc/build/install-nbc_minisat_all.sh + diff --git a/etc/build/default_envvars.sh b/etc/build/default_envvars.sh index b2f1abf2f3..917e7ce029 100755 --- a/etc/build/default_envvars.sh +++ b/etc/build/default_envvars.sh @@ -10,7 +10,7 @@ export INSTALL_GHC=${INSTALL_GHC:-no} export INSTALL_CABAL=${INSTALL_CABAL:-no} export OPTIMISATION=${OPTIMISATION:-"-O2"} export LLVM=${LLVM:-"llvm-off"} -export BIN_DIR=${BIN_DIR:-${HOME}/.cabal/bin} +export BIN_DIR=${BIN_DIR:-${HOME}/.local/bin} export BUILD_DOCS=${BUILD_DOCS:-no} export BUILD_TESTS=${BUILD_TESTS:-no} export RUN_TESTS=${RUN_TESTS:-no} @@ -21,5 +21,5 @@ export SPLIT_OBJS=${SPLIT_OBJS:-no} export DEVELOPMENT_MODE=${DEVELOPMENT_MODE:-no} export PATH="${HOME}/.tools/ghc/${GHC_VERSION}/bin":$PATH -export PATH="${HOME}/.cabal/bin":$PATH +export PATH="${HOME}/.local/bin":$PATH export PATH="${BIN_DIR}":$PATH diff --git a/etc/build/docker/Dockerfile b/etc/build/docker/Dockerfile new file mode 100644 index 0000000000..7d68802169 --- /dev/null +++ b/etc/build/docker/Dockerfile @@ -0,0 +1,121 @@ +# Dockerfile for Conjure +# +# Conjure requires Haskell, JRE, CMake, C++, etc. +# This is based on a merge of the two main parents +# https://github.com/freebroccolo/docker-haskell/blob/master/8.4/Dockerfile +# https://github.com/docker-library/openjdk/blob/master/11/jre/slim/Dockerfile +# with the other components on top of a slim Debian base image. + +FROM debian:sid-slim + +ENV LANG C.UTF-8 +ENV WORK /conjure + +# create a JAVA_HOME that's cross-architecture-safe +ENV JAVA_HOME /docker-java-home +RUN ln -svT "/usr/lib/jvm/java-11-openjdk-$(dpkg --print-architecture)" $JAVA_HOME +ENV JAVA_VERSION 11 + +RUN set -ex; \ +# slim variants have no man pages (causes "update-alternatives" to fail) + if [ ! -d /usr/share/man/man1 ]; then \ + mkdir -p /usr/share/man/man1; \ + fi; \ + apt-get update; \ + apt-get install -y --no-install-recommends \ + openjdk-11-jre-headless; \ +# update-alternatives so future installs of OpenJDK don't change /usr/bin/java + update-alternatives --get-selections | awk -v home="$(readlink -f "$JAVA_HOME")" 'index($3, home) == 1 { $2 = "manual"; print | "update-alternatives --set-selections" }'; \ +# ... and verify it worked for one of the alternatives + update-alternatives --query java | grep -q 'Status: manual' + +RUN apt-get install -y --no-install-recommends \ + ca-certificates \ + dirmngr \ + git \ + gnupg \ + && echo 'deb http://downloads.haskell.org/debian stretch main' > /etc/apt/sources.list.d/ghc.list \ + && apt-key adv --keyserver keyserver.ubuntu.com --recv-keys BA3CBA3FFE22B574 \ +# the following apt-get update is necessary to pick up the Haskell components + && apt-get update \ + && apt-get install -y --no-install-recommends \ + bison \ + cabal-install-2.2 \ + cmake \ + flex \ + g++ \ + ghc-8.4.3 \ + libsqlite3-dev \ + libtinfo-dev \ + make \ + netbase \ + wget \ + zlib1g-dev + +WORKDIR $WORK + +# default Haskell stack build usually fails on Docker, instead +# install a known-to-work binary build, see: +# https://github.com/commercialhaskell/stack/issues/3510#issuecomment-386266579 +RUN apt-get install -y --no-install-recommends \ + curl \ + && curl -fSL https://github.com/commercialhaskell/stack/releases/download/v1.7.1/stack-1.7.1-linux-x86_64.tar.gz -o stack.tar.gz \ + && curl -fSL https://github.com/commercialhaskell/stack/releases/download/v1.7.1/stack-1.7.1-linux-x86_64.tar.gz.asc -o stack.tar.gz.asc \ + && apt-get purge -y --auto-remove curl \ + && export GNUPGHOME=$WORK \ + && gpg --keyserver ha.pool.sks-keyservers.net --recv-keys C5705533DA4F78D8664B5DC0575159689BEFB442 \ + && gpg --batch --verify stack.tar.gz.asc stack.tar.gz \ + && tar -xf stack.tar.gz -C /usr/local/bin --strip-components=1 \ + && /usr/local/bin/stack config set system-ghc --global true \ + && /usr/local/bin/stack config set install-ghc --global false \ + && rm -f stack.tar.gz.asc stack.tar.gz + +ENV PATH /root/.cabal/bin:/root/.local/bin:/opt/cabal/2.2/bin:/opt/ghc/8.4.3/bin:$PATH +ENV BIN_DIR /root/.local/bin + +RUN git clone https://github.com/conjure-cp/conjure.git +WORKDIR $WORK/conjure +RUN git pull +RUN git checkout 85af98abff5da363329853c27fd5f310c41d65e1 + +RUN make +RUN make solvers + +RUN apt-get purge -y --auto-remove \ + bison \ +# JRE depends on this, don't remove: +# ca-certificates \ + cabal-install-2.2 \ + cmake \ + dirmngr \ + flex \ + g++ \ + ghc-8.4.3 \ + git \ + gnupg \ + libsqlite3-dev \ + libtinfo-dev \ + make \ + netbase \ + wget \ + zlib1g-dev \ + && rm -rf /var/lib/apt/lists/* + +WORKDIR $WORK + +RUN rm -f pubring.kbx* trustdb.gpg /root/.wget-hsts \ + && rm -rf crls.d private-keys-v1.d \ + && rm -rf conjure \ +# remove stack + && rm -rf /root/.stack \ + && rm -rf /usr/local/bin/* + +ENV PATH /root/.local/bin:$PATH + +# do a test-run of the pipeline, unless command is specified +COPY sudoku.essence sudoku.param $WORK/ +CMD conjure solve -ac --solutions-in-one-file --number-of-solutions=all --solver=minion --limit-time=90 sudoku.essence sudoku.param \ + && mv conjure-output/model000001-sudoku.solutions /tmp/result.txt \ + && cat /tmp/result.txt \ + && rm /tmp/result.txt \ + && rm -rf conjure-output diff --git a/etc/build/docker/README.md b/etc/build/docker/README.md new file mode 100644 index 0000000000..e3fe52cd0f --- /dev/null +++ b/etc/build/docker/README.md @@ -0,0 +1,16 @@ +This is a basic Dockerfile for building Conjure. + +To test: in a directory containing the Dockerfile and the two Sudoku files, run + `docker build --tag=conjure .` + `docker run conjure` +which should print a solution ending with + +> $ 5 3 4 6 7 8 9 1 2 +> $ 6 7 2 1 9 5 3 4 8 +> $ 1 9 8 3 4 2 5 6 7 +> $ 8 5 9 7 6 1 4 2 3 +> $ 4 2 6 8 5 3 7 9 1 +> $ 7 1 3 9 2 4 8 5 6 +> $ 9 6 1 5 3 7 2 8 4 +> $ 2 8 7 4 1 9 6 3 5 +> $ 3 4 5 2 8 6 1 7 9 diff --git a/etc/build/docker/sudoku.essence b/etc/build/docker/sudoku.essence new file mode 100644 index 0000000000..fbfb98153b --- /dev/null +++ b/etc/build/docker/sudoku.essence @@ -0,0 +1,15 @@ +language Essence 1.3 +$ simple Sudoku spec +letting n be 9 +letting b be 3 +letting index be domain int(1..n) +letting values be domain int(0..n) + +given x : matrix indexed by [index,index] of int(0..n) $ 0 = blank +find y : matrix indexed by [index,index] of index +such that + forAll i,j : index . x[i,j] != 0 -> y[i,j] = x[i,j], + forAll i : index . allDiff( y[i,..] ), + forAll j : index . allDiff([ y[i,j] | i : index ]), + forAll u,v : int(0..b-1) . + allDiff([ y[u*3 + i,v*3 + j] | i,j : int(1..b) ]) diff --git a/etc/build/docker/sudoku.param b/etc/build/docker/sudoku.param new file mode 100644 index 0000000000..ba271f64ca --- /dev/null +++ b/etc/build/docker/sudoku.param @@ -0,0 +1,11 @@ +letting x be [ +[ 5, 3, 0, 0, 7, 0, 0, 0 ,0 ], +[ 6, 0, 0, 1, 9, 5, 0, 0, 0 ], +[ 0, 9, 8, 0, 0, 0, 0, 6, 0 ], +[ 8, 0, 0, 0, 6, 0, 0, 0, 3 ], +[ 4, 0, 0, 8, 0, 3, 0, 0, 1 ], +[ 7, 0, 0, 0, 2, 0, 0, 0, 6 ], +[ 0, 6, 0, 0, 0, 0, 2, 8, 0 ], +[ 0, 0, 0, 4, 1, 9, 0, 0, 5 ], +[ 0, 0, 0, 0, 8, 0, 0, 7, 9 ] +] diff --git a/etc/build/download-minion.sh b/etc/build/download-minion.sh deleted file mode 100755 index 98a53dcfbd..0000000000 --- a/etc/build/download-minion.sh +++ /dev/null @@ -1,22 +0,0 @@ -#!/bin/bash - -set -o errexit -set -o nounset - -export BIN_DIR=${BIN_DIR:-${HOME}/.cabal/bin} - -OS=$(uname) - -if [ "$OS" == "Darwin" ]; then - wget --no-check-certificate -c https://ozgur.host.cs.st-andrews.ac.uk/Minions/minion-1.8-mac.tar_.gz - tar -xvzf minion-1.8-mac.tar_.gz - mv minion-1.8/bin/minion ${BIN_DIR}/minion -elif [ "$OS" == "Linux" ]; then - wget --no-check-certificate -c https://ozgur.host.cs.st-andrews.ac.uk/Minions/minion-1.8-linux.tar_1.gz - tar -xvzf minion-1.8-linux.tar_1.gz - mv minion-1.8/bin/minion ${BIN_DIR}/minion -else - echo "Cannot determine your OS, uname reports: ${OS}" - exit 1 -fi - diff --git a/etc/build/install-bc_minisat_all.sh b/etc/build/install-bc_minisat_all.sh new file mode 100755 index 0000000000..9d6945e306 --- /dev/null +++ b/etc/build/install-bc_minisat_all.sh @@ -0,0 +1,20 @@ +#!/bin/bash + +set -o errexit +set -o nounset + +export BIN_DIR=${BIN_DIR:-${HOME}/.local/bin} + +rm -rf ${BIN_DIR}/tmp-install-bc_minisat_all +mkdir ${BIN_DIR}/tmp-install-bc_minisat_all +pushd ${BIN_DIR}/tmp-install-bc_minisat_all +wget --no-check-certificate -c http://www.sd.is.uec.ac.jp/toda/code/bc_minisat_all-1.1.2.tar.gz +tar zxf bc_minisat_all-1.1.2.tar.gz +cd bc_minisat_all-1.1.2/ +make bc_minisat_all_release +mv bc_minisat_all_release ${BIN_DIR}/bc_minisat_all_release +echo "bc_minisat_all executable is at ${BIN_DIR}/bc_minisat_all_release" +ls -l ${BIN_DIR}/bc_minisat_all_release +popd +rm -rf ${BIN_DIR}/tmp-install-bc_minisat_all + diff --git a/etc/build/install-chuffed.sh b/etc/build/install-chuffed.sh new file mode 100755 index 0000000000..34cd189dee --- /dev/null +++ b/etc/build/install-chuffed.sh @@ -0,0 +1,23 @@ +#!/bin/bash + +set -o errexit +set -o nounset + +export BIN_DIR=${BIN_DIR:-${HOME}/.local/bin} + +rm -rf ${BIN_DIR}/tmp-install-chuffed +mkdir ${BIN_DIR}/tmp-install-chuffed +pushd ${BIN_DIR}/tmp-install-chuffed +git clone https://github.com/chuffed/chuffed.git +cd chuffed +git checkout 0.10.2 +mkdir build +cd build +cmake .. +cmake --build . +cp fzn-chuffed ${BIN_DIR}/fzn-chuffed +echo "chuffed executable is at ${BIN_DIR}/fzn-chuffed" +ls -l ${BIN_DIR}/fzn-chuffed +popd +rm -rf ${BIN_DIR}/tmp-install-chuffed + diff --git a/etc/build/install-gecode.sh b/etc/build/install-gecode.sh new file mode 100755 index 0000000000..6f4235c6d2 --- /dev/null +++ b/etc/build/install-gecode.sh @@ -0,0 +1,23 @@ +#!/bin/bash + +set -o errexit +set -o nounset + +export BIN_DIR=${BIN_DIR:-${HOME}/.local/bin} + +rm -rf ${BIN_DIR}/tmp-install-gecode +mkdir ${BIN_DIR}/tmp-install-gecode +pushd ${BIN_DIR}/tmp-install-gecode +git clone https://github.com/Gecode/gecode.git +cd gecode +git checkout release-6.0.1 +mkdir build +cd build +../configure --disable-qt --disable-gist --enable-static +make +cp tools/flatzinc/fzn-gecode ${BIN_DIR}/fzn-gecode +echo "gecode executable is at ${BIN_DIR}/fzn-gecode" +ls -l ${BIN_DIR}/fzn-gecode +popd +rm -rf ${BIN_DIR}/tmp-install-gecode + diff --git a/etc/build/install-glucose.sh b/etc/build/install-glucose.sh new file mode 100755 index 0000000000..1c29bbb1ff --- /dev/null +++ b/etc/build/install-glucose.sh @@ -0,0 +1,21 @@ +#!/bin/bash + +set -o errexit +set -o nounset + +export BIN_DIR=${BIN_DIR:-${HOME}/.local/bin} + +rm -rf ${BIN_DIR}/tmp-install-glucose +mkdir ${BIN_DIR}/tmp-install-glucose +pushd ${BIN_DIR}/tmp-install-glucose +wget --no-check-certificate -c http://www.labri.fr/perso/lsimon/downloads/softwares/glucose-syrup-4.1.tgz +tar zxf glucose-syrup-4.1.tgz +cd glucose-syrup-4.1/ +cd parallel +make r +cp glucose-syrup_release ${BIN_DIR}/glucose-syrup +echo "glucose executable is at ${BIN_DIR}/glucose-syrup" +ls -l ${BIN_DIR}/glucose-syrup +popd +rm -rf ${BIN_DIR}/tmp-install-glucose + diff --git a/etc/build/install-lingeling.sh b/etc/build/install-lingeling.sh index 94cb8c0c2a..8f78590494 100755 --- a/etc/build/install-lingeling.sh +++ b/etc/build/install-lingeling.sh @@ -3,18 +3,20 @@ set -o errexit set -o nounset -export BIN_DIR=${BIN_DIR:-${HOME}/.cabal/bin} +export BIN_DIR=${BIN_DIR:-${HOME}/.local/bin} -rm -rf ~/tmp-install-lingeling -mkdir ~/tmp-install-lingeling -pushd ~/tmp-install-lingeling -wget -c http://fmv.jku.at/lingeling/lingeling-ayv-86bf266-140429.zip -unzip lingeling-ayv-86bf266-140429.zip -./build.sh +rm -rf ${BIN_DIR}/tmp-install-lingeling +mkdir ${BIN_DIR}/tmp-install-lingeling +pushd ${BIN_DIR}/tmp-install-lingeling +wget --no-check-certificate -c http://fmv.jku.at/lingeling/lingeling-bbc-9230380-160707.tar.gz +tar xzf lingeling-bbc-9230380-160707.tar.gz +cd lingeling-bbc-9230380-160707 +./configure.sh +make mkdir -p ${BIN_DIR} -cp binary/lingeling ${BIN_DIR}/lingeling +cp lingeling ${BIN_DIR}/lingeling echo "lingeling executable is at ${BIN_DIR}/lingeling" ls -l ${BIN_DIR}/lingeling popd -rm -rf ~/tmp-install-lingeling +rm -rf ${BIN_DIR}/tmp-install-lingeling diff --git a/etc/build/install-minion.sh b/etc/build/install-minion.sh index d1e93c89a1..a1c40a2642 100755 --- a/etc/build/install-minion.sh +++ b/etc/build/install-minion.sh @@ -3,29 +3,29 @@ set -o errexit set -o nounset -export BIN_DIR=${BIN_DIR:-${HOME}/.cabal/bin} -export COMPILER=${COMPILER:-""} +export BIN_DIR=${BIN_DIR:-${HOME}/.local/bin} + +rm -rf ${BIN_DIR}/tmp-install-minion +mkdir ${BIN_DIR}/tmp-install-minion +pushd ${BIN_DIR}/tmp-install-minion + +OS=$(uname) + +if [ "$OS" == "Darwin" ]; then + wget --no-check-certificate -c https://savilerow.cs.st-andrews.ac.uk/savilerow-1.7.0RC-mac.tgz + tar zxf savilerow-1.7.0RC-mac.tgz + mv savilerow-1.7.0RC-mac/bin/minion ${BIN_DIR}/minion +elif [ "$OS" == "Linux" ]; then + wget --no-check-certificate -c https://savilerow.cs.st-andrews.ac.uk/savilerow-1.7.0RC-linux.tgz + tar zxf savilerow-1.7.0RC-linux.tgz + mv savilerow-1.7.0RC-linux/bin/minion ${BIN_DIR}/minion +else + echo "Cannot determine your OS, uname reports: ${OS}" + exit 1 +fi -rm -rf ~/tmp-install-minion -mkdir ~/tmp-install-minion -pushd ~/tmp-install-minion -hg clone https://bitbucket.org/stacs_cp/minion -mkdir -p minion/build -( - cd minion/build - if [ -z "${COMPILER}" ]; then - ../build.py - else - if which ccache; then - COMPILER="ccache ${COMPILER}" - fi - ../build.py --compiler "${COMPILER}" - fi - make minion -) -cp minion/build/minion ${BIN_DIR}/minion echo "minion executable is at ${BIN_DIR}/minion" ls -l ${BIN_DIR}/minion popd -rm -rf ~/tmp-install-minion +rm -rf ${BIN_DIR}/tmp-install-minion diff --git a/etc/build/install-nbc_minisat_all.sh b/etc/build/install-nbc_minisat_all.sh new file mode 100755 index 0000000000..b0c6da6ba4 --- /dev/null +++ b/etc/build/install-nbc_minisat_all.sh @@ -0,0 +1,20 @@ +#!/bin/bash + +set -o errexit +set -o nounset + +export BIN_DIR=${BIN_DIR:-${HOME}/.local/bin} + +rm -rf ${BIN_DIR}/tmp-install-nbc_minisat_all +mkdir ${BIN_DIR}/tmp-install-nbc_minisat_all +pushd ${BIN_DIR}/tmp-install-nbc_minisat_all +wget --no-check-certificate -c http://www.sd.is.uec.ac.jp/toda/code/nbc_minisat_all-1.0.2.tar.gz +tar zxf nbc_minisat_all-1.0.2.tar.gz +cd nbc_minisat_all-1.0.2/ +make nbc_minisat_all_release +mv nbc_minisat_all_release ${BIN_DIR}/nbc_minisat_all_release +echo "nbc_minisat_all executable is at ${BIN_DIR}/nbc_minisat_all_release" +ls -l ${BIN_DIR}/nbc_minisat_all_release +popd +rm -rf ${BIN_DIR}/tmp-install-nbc_minisat_all + diff --git a/etc/build/install-open-wbo.sh b/etc/build/install-open-wbo.sh new file mode 100755 index 0000000000..81101b9397 --- /dev/null +++ b/etc/build/install-open-wbo.sh @@ -0,0 +1,19 @@ +#!/bin/bash + +set -o errexit +set -o nounset + +export BIN_DIR=${BIN_DIR:-${HOME}/.local/bin} + +rm -rf ${BIN_DIR}/tmp-install-open-wbo +mkdir ${BIN_DIR}/tmp-install-open-wbo +pushd ${BIN_DIR}/tmp-install-open-wbo +git clone https://github.com/sat-group/open-wbo.git +cd open-wbo +make r +cp open-wbo_release ${BIN_DIR}/open-wbo +echo "open-wbo executable is at ${BIN_DIR}/open-wbo" +ls -l ${BIN_DIR}/open-wbo +popd +rm -rf ${BIN_DIR}/tmp-install-open-wbo + diff --git a/etc/build/install-oscar-cbls.sh b/etc/build/install-oscar-cbls.sh index b28a126e22..418ac07d11 100755 --- a/etc/build/install-oscar-cbls.sh +++ b/etc/build/install-oscar-cbls.sh @@ -15,11 +15,11 @@ else fi -export BIN_DIR=${BIN_DIR:-${HOME}/.cabal/bin} +export BIN_DIR=${BIN_DIR:-${HOME}/.local/bin} -rm -rf ~/tmp-install-oscar-cbls -mkdir ~/tmp-install-oscar-cbls -pushd ~/tmp-install-oscar-cbls +rm -rf ${BIN_DIR}/tmp-install-oscar-cbls +mkdir ${BIN_DIR}/tmp-install-oscar-cbls +pushd ${BIN_DIR}/tmp-install-oscar-cbls hg clone ssh://hg@bitbucket.org/oscarlib/oscar-releases cd oscar-releases/oscar-cbls-flatzinc bash setup.sh @@ -28,5 +28,5 @@ cp mzn-oscar-cbls ${BIN_DIR}/mzn-oscar-cbls cp -r mznlib-cbls ${BIN_DIR}/mznlib-cbls ls -l ${BIN_DIR}/*cbls popd -rm -rf ~/tmp-install-oscar-cbls +rm -rf ${BIN_DIR}/tmp-install-oscar-cbls diff --git a/etc/build/install-savilerow.sh b/etc/build/install-savilerow.sh index 5f249719ea..db3a9490a7 100755 --- a/etc/build/install-savilerow.sh +++ b/etc/build/install-savilerow.sh @@ -3,28 +3,36 @@ set -o errexit set -o nounset -export BIN_DIR=${BIN_DIR:-${HOME}/.cabal/bin} +export BIN_DIR=${BIN_DIR:-${HOME}/.local/bin} + +rm -rf ${BIN_DIR}/tmp-install-savilerow +mkdir ${BIN_DIR}/tmp-install-savilerow +pushd ${BIN_DIR}/tmp-install-savilerow + +OS=$(uname) + +if [ "$OS" == "Darwin" ]; then + wget --no-check-certificate -c https://savilerow.cs.st-andrews.ac.uk/savilerow-1.7.0RC-mac.tgz + tar zxf savilerow-1.7.0RC-mac.tgz + mv savilerow-1.7.0RC-mac/savilerow.jar ${BIN_DIR}/savilerow.jar + mv savilerow-1.7.0RC-mac/lib ${BIN_DIR}/ + echo '#!/bin/bash' > ${BIN_DIR}/savilerow + echo 'DIR="$( cd "$( dirname "$0" )" && pwd )"' >> ${BIN_DIR}/savilerow + echo 'java -ea -XX:ParallelGCThreads=1 -Xmx8G -jar "$DIR/savilerow.jar" "$@"' >> ${BIN_DIR}/savilerow + chmod +x ${BIN_DIR}/savilerow +elif [ "$OS" == "Linux" ]; then + wget --no-check-certificate -c https://savilerow.cs.st-andrews.ac.uk/savilerow-1.7.0RC-linux.tgz + tar zxf savilerow-1.7.0RC-linux.tgz + mv savilerow-1.7.0RC-linux/savilerow.jar ${BIN_DIR}/savilerow.jar + mv savilerow-1.7.0RC-linux/lib ${BIN_DIR}/ + echo '#!/bin/bash' > ${BIN_DIR}/savilerow + echo 'DIR="$( cd "$( dirname "$0" )" && pwd )"' >> ${BIN_DIR}/savilerow + echo 'java -ea -XX:ParallelGCThreads=1 -Xmx8G -jar "$DIR/savilerow.jar" "$@"' >> ${BIN_DIR}/savilerow + chmod +x ${BIN_DIR}/savilerow +else + echo "Cannot determine your OS, uname reports: ${OS}" + exit 1 +fi + +rm -rf ${BIN_DIR}/tmp-install-savilerow -rm -rf savilerow-repo savilerow*.tgz - -######## this is the release -# wget -c http://savilerow.cs.st-andrews.ac.uk/savilerow-1.6.5-linux.tgz -# tar zxvf savilerow-1.6.5-linux.tgz -# mv savilerow-1.6.5-linux savilerow-repo - -######## we are using an unreleased version... -wget --no-check-certificate -c https://ozgur.host.cs.st-andrews.ac.uk/SavileRows/savilerow-2017-09-22--55d8d4b29032-linux.tgz -tar zxvf savilerow-2017-09-22--55d8d4b29032-linux.tgz -mv savilerow-2017-09-22--55d8d4b29032-linux savilerow-repo - -(cd savilerow-repo ; ./compile.sh) -cp savilerow-repo/savilerow.jar ${BIN_DIR}/savilerow.jar -mkdir -p ${BIN_DIR}/lib -cp savilerow-repo/lib/trove.jar ${BIN_DIR}/lib/trove.jar - -rm -rf savilerow-repo savilerow*.tgz - -echo '#!/bin/bash' > ${BIN_DIR}/savilerow -echo 'DIR="$( cd "$( dirname "$0" )" && pwd )"' >> ${BIN_DIR}/savilerow -echo 'java -ea -XX:ParallelGCThreads=1 -Xmx8G -jar "$DIR/savilerow.jar" "$@"' >> ${BIN_DIR}/savilerow -chmod +x ${BIN_DIR}/savilerow diff --git a/etc/build/install-stack.sh b/etc/build/install-stack.sh index adb050b8a5..a0d9e276fe 100755 --- a/etc/build/install-stack.sh +++ b/etc/build/install-stack.sh @@ -9,24 +9,34 @@ source ${SCRIPT_DIR}/default_envvars.sh export BIN_DIR=${BIN_DIR:-${HOME}/.local/bin} export CI=${CI:-false} +function dlStack { + if [ `uname` = "Darwin" ] ; then + curl --insecure -L https://www.stackage.org/stack/osx-x86_64 | tar xz --strip-components=1 --include '*/stack' -C ${BIN_DIR} + else + curl -L https://www.stackage.org/stack/linux-x86_64 | tar xz --wildcards --strip-components=1 -C ${BIN_DIR} '*/stack' + fi +} +export -f dlStack + if ! which stack 2> /dev/null > /dev/null; then echo "Installing Haskell build tool stack to ${BIN_DIR}" if $CI; then - if [ `uname` = "Darwin" ] ; then - curl --insecure -L https://www.stackage.org/stack/osx-x86_64 | tar xz --strip-components=1 --include '*/stack' -C ~/.local/bin - else - curl -L https://www.stackage.org/stack/linux-x86_64 | tar xz --wildcards --strip-components=1 -C ~/.local/bin '*/stack' - fi + dlStack else - if which curl 2> /dev/null > /dev/null; then - curl -sSL https://get.haskellstack.org/ | sh -s - -d ${BIN_DIR} - elif which wget 2> /dev/null > /dev/null; then - wget -qO- https://get.haskellstack.org/ | sh -s - -d ${BIN_DIR} + if dlStack ; then + echo "Downloaded stack." else - echo "You seem to have neither curl nor wget on this computer." - echo "Cannot install stack without one of them." - exit 1 + echo "Couldn't download stack, attempting build from source." + if which curl 2> /dev/null > /dev/null; then + curl -sSL https://get.haskellstack.org/ | sh -s - -d ${BIN_DIR} + elif which wget 2> /dev/null > /dev/null; then + wget -qO- https://get.haskellstack.org/ | sh -s - -d ${BIN_DIR} + else + echo "You seem to have neither curl nor wget on this computer." + echo "Cannot install stack without one of them." + exit 1 + fi fi fi fi diff --git a/etc/build/install.sh b/etc/build/install.sh index e4bf18b177..272373d498 100755 --- a/etc/build/install.sh +++ b/etc/build/install.sh @@ -150,7 +150,7 @@ elif [ $INSTALL_CABAL = "yes" ]; then mkdir cabal-install-tmp pushd cabal-install-tmp wget --no-check-certificate -c "http://hackage.haskell.org/packages/archive/cabal-install/${CABAL_VERSION}/cabal-install-${CABAL_VERSION}.tar.gz" - tar -zxvf "cabal-install-${CABAL_VERSION}.tar.gz" + tar zxf "cabal-install-${CABAL_VERSION}.tar.gz" pushd "cabal-install-${CABAL_VERSION}" EXTRA_CONFIGURE_OPTS="" bash bootstrap.sh --user --no-doc popd diff --git a/etc/build/silent-wrapper.sh b/etc/build/silent-wrapper.sh new file mode 100755 index 0000000000..c5e583434a --- /dev/null +++ b/etc/build/silent-wrapper.sh @@ -0,0 +1,29 @@ +#!/bin/bash + +# set -o errexit +# set -o nounset + +if [ $# -ne 1 ]; then + echo "Only provide a single argument, the path to a bash script." + exit 1 +fi + +echo "Running $1" + +PID=$$ +export STARTTIME=$(date +%s) +bash $1 > ${PID}.stdout 2> ${PID}.stderr +EXITCODE=$? +export ELAPSED=$(($(date +%s) - ${STARTTIME})) + +if [ ${EXITCODE} -eq 0 ] ; then + echo " Done (took ${ELAPSED} seconds)" + rm -f ${PID}.stdout ${PID}.stderr +else + echo " Failed (took ${ELAPSED} seconds)" + echo " Exit code: ${EXITCODE}" + echo " Outputs saved to: ${PID}.stdout and ${PID}.stderr" +fi + +# exit ${EXITCODE} +exit 0 diff --git a/etc/savilerow/savilerow.jar b/etc/savilerow/savilerow.jar index 02a24a0becd6a9c10b89153f31c2bbe32988b659..087c2b44c38a3c52a41a1dc2fdc8a5868f8dc43d 100644 GIT binary patch delta 98423 zcmYhiWmsHI(>00?4#8c5y9Rf6cY+5C?hbXSwsj3c!)o;NwAQVFm-Q}Kx8D)1R#=VSmbJT$ZM!S3P6N8uyjBlIAitc z+gAfw`$Q1TM3weCGivi31zp%dTABF*PP<7A*~x`mMyG%*TKnn`g%4i>Po1i)pfLjb$ zzh~~4hs9g`vLS|rn_Z9BO+^c2mUP0898}d0G{uZ$P}L9J0MeF8RpNK!V9jRL<8-^x z*8Qv}>E^=X=9!NV{n}WuEx49Jb+(<&kxw1lKeu>7CQa-L%;5 z-q`ofJ?Z<$Om_|~iTF8B zB#nwd#0DLfa?V`v20qs4PfyhDOIkyb^Pk5RFKFs4*`D~_477%l=LA}he39HL%@G?+ zSPnU!aNSK`e9*cdX@x}2-$%x&_(pGFVrBlkL+;+CZ4o)AiY!<0jWK13bWrh)+TeG+ z5Q2MLkxZ#@p?ZYuBvpL^hGe|r6F)|owaV3z=Cn3Iyzt{ZiB}1u-+;{E#)5(J?ql7k zl|WV}JQy0J-=j1O|5^vkBjBrnT zA1OptF5O%l;SPk8-tUwuQiD5yxO?ydTJWrVaYHYrJI z?mf5C$nGU5e^7d5ZzZX6N?vSIu_XG^vnwX~Hg0iHvZVM@(_6^;2W?fe>5<McDe$!93`5s3`g0O9>F?G0 zKUt}BM%Hg}>PVMv<;xna98X9PUT)Qwoc_=0=G!zUeI?o6?QUZUJAD|WnUV$ zjAUXjLBQ=bBl(tD$-z5r<`<^dk>T6(Q>xeYcAzWpJo9ce@s<3(JnN$~N?S{cz9zYtubCWO z$r=HO)`h{zW;{EgB%>WxoKyMrU3qbwjhBkBL?VMt_Dl1A#95UUqndWLuZXN-39F$I z%5}pbX2QgQqn%wYv#6{M=dXp-8D16bSSCjkM*T7>J(~zKS6!)HVKMGh42KjoNiU8M zzt(lsSO7O5Es@1y8_wiKm7;g$2}Mi{rDX*`)+0k~mYD8#DGxW#&$%D)nWH2tuyqS3 zB)m}ST4HvN9?U*)8T%R-cy3==ks};?q(~HRteg1}8$alpNLgO1sS4m1Moz^LAi+L+ z_oftmrAnEa3QUXC`}}#M=D`t)FBB(mJI(h4!oz!FZ9**Fgc2n63CP82Mt$vc9bE%r zpzKU3BU5oy2&f}#>=`pcGW%19EH-S+P;n8`EHfQbd4vf%iedzdeyqI#MqxShV$SxM zAGRBVlYj`xgocD^!iR7;&RRFl+I4!eJW64jm^{giwL>l~>%Dm{w}bPD8Ta+yxF7JY;A7frqRtex} z)LFK^sEGMzL)W)x%Eb9vAL~xHb!$o^Q)gZvFGze1U*#+VN}u|i!oGf zlRthGqW`o`U(s+197giH?)VJ(0xT-~fjp>yP@+GMJ%+vDtdH%cinHu3!svL;+X*nJ(1NPzAFFhgf4i7~Q6%?2pp} zex;<0dz#1KOygQIWd~SRCB_bDN&$+rB{#Rd0cA~k$Wp)Uk<$x5(hY8Y1$s|GPqLzN zech9?q*&n}~km)|J@E(Gn4dU;uO}1Qr!NH+dzE707S1WJ@xUxqVyX!te z-1yiAq(jR5YHlfG#!x;G`RIjVL2_k0>PU`WsNVaUYXzmvgQsybz81cvBj=gfa%l{& zs1Y8I79EW>s|}Jo*dco-11u)*pHDjnt>%|c!(X-C(HbEhPsq1(rGB?O`mO?f@*{%r z>s~dyja!g?*n(mO!8Pv$6@4CkuF_(o*&un>L0L?xody=4+CeAFfpPqHPma)G8eiW`|Ubw=@U8=6Tb*?~RY+T*` zxrtuRf`++n#xIXqO+sJ#%%4TbK&k9t_it8=BHPTB^0*gGL(XJprIkUQ0_^hE(dZm~nbU>%1%qh<_ z^`h@u>5Y7)txJpYXd+x)A*@~O;|i5QS^F|3nEvZL4~*j{bkF`Vvg|x>mdIe7uNod3 zgg041U%j+X53cJrt1e)PYV0U1?b|%p9ME->@a@T!eFy>)DJiL~wo|8IS?_FH3+ORe z;+=+N6fM;VU2_I=EYLHQs&^JOj}$2^mBtN6=oQiPZ_i#%fn_zhbq<>-l1t-6tXn=D z`p(z87Q1k+Fh*&By^0kO;rR6V#c85b_tZn8KDf^id4~59Fp$*xq)6@TofhkC4(aJ{ z8_R31#xw)d^C+L)Lzuq@vG`)znD#VJA~OWeMqz9ocYHKgL5oZ(_1kjlHxh#?TDKSz1@7NEek7X(#5$OV(TS=-)w9Lb)CcR}@&~ zKTkNZ%5yvk-*%!a66b(Ou!?WM1~Jy@PtUkAC-^3EA~C)Yb(8Co-(p5>-*NW|=3q7D zb2y=a6|#tjBEVkvBkho=mt1&m_?d(k)XlE8;ST>yBiv9yWpu>no<21{o%){wYEi+e z=p^f*IpO5KeUoxET;CJ7ZREa?Kane=-|sb8?oR`BPk6<$3HR<%$EDEi_U{pwV@Vnz zB{3r{u+XyRVoc%Q_V~FfOF+-@!)R+Gw7#0K-#iBj}(@J~od3ixqUYs_O+ zSCMgaNgAvls;;6R%S6tou|PTX5ZzK(xIgRR-*^MFloMU#pvqBu*>AK@+S&EQ-NbV= z+@?qVCC$b0j$7j4{~wF6{5_qj(smB5I`K4vPxchgs%S|!@eI`>L1@Roirv5&pUFkQ z_i#Ec;mBg@CC5zZtTv(bqrsghM-pFuz+UU~qvty#fULB(C*u23Yp5F*8rtMDDK%!z-|wewxoehz^)CD%WYz@Jz@xiF_U1> z{@K9OI_0wg75ah(0%xZXy=rP9V+46!Y}M zo?t1BWU85;{`QO*32`MKqX&02(I!IG=cy>dq#JX5<8sh6CC;ER z7MJSBl8x)>c`76qY%LUmLR3(_w=hmYA+lMUTf*c)4(n$mBB+^-Y*Rcc(M@D5nHd;` zrEv+eFzELUFmu_(*?yB1eg^ERDpl0E%f8_d?>g>tD*COwTCinI)Pby{ncu=eTZjx3 ziytx790sPTBuzMKx-l`*YQ=qUkw1HEEQp{MdTg|mWS4$MwAhQ1)WeN}ITM@E5p+gc zJ0d9i@+nn?(6~Unf*@qdffn&MiO*ET!b57~2%p&H^+(U}mTKA!9dDs2K}#>iEJpnn ztdx;}nc1G)SSk9pY+fM06J$#H#3_tcSxcFn(G;m;N(8C^UX6f=-g?RTHV|nqxmOjCeTEJ|n1pBC=#niO$U7-xdbyy3k@haAVjUvkFOt zRq1m6!j>mE6%p6u=54>#Oi1O+CDN>XaK0uO#bse&nP$6dfG053s;@2zf~t6+gpPPv z(8FVAZO8J4FTL7#A>yX9dvTXVlPNv+mTJ386j_Jh7K;uE2IKvzuxAWVoDK`!X(Isy z-XuEg3xvJ|)-nKlXeZ=uKFA$_A(^nAk)j&K#yw>oZy>)}n2@7KfTW?SSxc2Nb+nYz zZZ=&-LmLtXA_%T+5Ny2~6pFZlereQEL}&zbU~M^B(Vdx;>+UPgz{BZdz}@+QJ86&v1!b zFlHwsa~VD|=~PjRxW5mrop}I!y>p994D{qEB@xGb9S)Yn+8N~mp!&0RyzRU0Zc`u> zOuTeTzELnyJj2rgk!`j@IM{7j)>EKPBp7hU5G8pj;-5jIa;W=2tuoRj}b~ ziRS6vI!FNZ@I!0IcgTt+itpcD5rEVcl{){zX^E1VLj#Y{6rW3jnGkB*>S*`NXQ+8{%AZu#p!7!P;PJF7oJ0glq<+ z?FmkONWdE@$T`P$jK)K%u4~hgJc4~7UmMr#`8fu(bjH&&3WR%ittBPcV%GCa$7E@RV*mK74GDLJ7GZF>|=21Xh8#7M4a?M^tgpkZTpT6{Z+g zn|*Ob!xc?vS?6Pdd!9iymSH)$$r8&#T{7FJ7Yx>FLpRsh>aiJPZ>3x#ku^zuw-Emu zZG%8y7(uDr3+dg&U?>;#MP@<-)b>RjBphOOD>8@6&1ex=y6irNpSMR7J3V z3{B}x+Q+!_9yrryJr=Zbk?Cw*IF2&JX41koo7x*xr|;xF5$C9EqUf0CJ(01UHp^GI zpEt`!-c!^4jDLX%p2Q<##zWoLJ?)Y3#*y;`zD9h1b3x>PlI2lF&NojLb>i%MCMyGCck8X0W1q$`38ynd z1-K6f+#cEJm40~fR;Fgz9G4IR(TbmCSKu2)aiSOhH!w5fU4^6LcF z`pFtYGDP8ZW%Tb#p-q{ema@ZauFr@B_4C6Iug~-a1(aF9ff?mtxO@9C-k#YchPmOm zhwD_{o`ocadEubLb!_i?S+w%0&f=-D2#{;Y#PGrCYMsaffdP=|w-O2ve6W7)-C*bK z8BDTLu<0=2#C`a1>|HO8rta+-MY2*94&Gls_Vx@viQ~V%GPttmTq?{z9q$AP+D>)) zT%QRE+D>#Dc+ZuD-yW_*d)I$N;U9x*_m?A8dp={$CGD3JM%?eMnurtU&m0>RF05M& zHEN%7j5`UpymA-#w!I46C3|iz1B#*^h=QB6Cu6o01iM^f+9zP_^YzH20D$qsio zSpVpKS4Yy46MlNI?&E#eLgJqlPI_?dpBpAwuUhR#4=4qM^KcHd$&M7R{?aG*IEZMTeQ!= zznz7mNR+Hf+Qx(g+UHwCq}*UU8CYOe9FgB|`9DCv$R&;WW<4gnwi8(LW!Ykb1;T62T7z~+wGza0Zp}9c^JIw`Bf<8q z0!`tLWNm5yCT>0?6QZASafc1_6|w6PawLr>an7dh&O-#akSZ8s2AJ^3NAQA(N2Q*m zX2rHST#)g#z(fs1c!gN{EV(owf&9vQP7wg>#DK}REujMG2>!*O_iY_xO(}pO#jzFt z1W*s<7)K>AihK*T1m{>zC9sO@fZ{0J=9hBDW#K8*wg}Pum8!WEe+6~z7;>NvNA2hZAQ!^K-h4HY2E(ckEr|B-BPWbj)x&G$nC~g$?(l z?JseN`Ef*iR*G=wDs}Jnf-Y+^qKa>>Mso_W3zFVI1?Wj{duoiJoL!p(LkqW_i@GjA zE=9z*Sn}gND`zZXal}2HT3DqH)I@jGnFgk*c`Ae52=5=u?nx_pKm5{VjF`sd<#WHJ zy2l|Nz!TcHes81>2&Ybrt%-NdPLk2)(=8noos&hK!M1eg#tDGZJFH0~hRS(VJ_QOR zs8yu_T?1vlbWrQAk&a0K?1i3CXaTB;d`}2hJH{@HkzYVcRLgrGCc<%`I~8h$xa)>@ zjF-_wlBPca_z@3I+Px3l;wENEfzbHP;q@L#?~yzbviaYe^I?u*W-VHZQ@O<0-yVcW zLz|ReF|+E>Tye&mpqSmEZoFHg_LojqJY1Co(nrOxj`Db}wj0^#e8-DrLz_=B=}UoX zj+@SNiT;d`Zys=DBkNm|R*&(e7-D5K@=k~2yfEO%q2XH$D`szCJz!0gVFTS_V-fh$aN7v82F&LNh@;G*g81w}?@|1}6lmnWVsif-fo=+((Q! zARA^TTo)mPP*_U}!8PRV6H;+C8Tt1 z4tFgEdcw6yzp3QLT!rczPwB!O>hb_Wod19z{Uj;SuHef})~ko1`~j02>ijo^@JOWR z&oob5vR+*bWp>O{fT<_QWV7@OOIV3q#(ILa@|T`G(Cq`>LnSca-TZO_V)Yo|N$w zhhA`eqzAHspAhyha;`6qr!T63b(oSd-^ZZPkq=0xcy3+3es)JnsgWUbW}^F?{dANv zFt~K#qGu%=F`mfFgie>2GGy1Dh=btUkTO)gRJfB4K)S?izkm>0wXPWAM8OF=6-O$G zzZ{bB#n!XpHQfECxCcY+3b-R@*toYa^+nRNm2GZQSR(#%j^+Im`y7e`$kqb!!%Vh$ zOks)e%Ok{-8N){Co8T>7Ev2CuH7cYNWSep&`P(B2d|w6Cxhco_J2Dc)Gj@iJ?l&_CUi=G8`V(xZd zwQ7HumDypC6*K;DuL910?iFW}gfKFd^sP$sBp}O4>H1}{VM>;PaHd}RMSi%82Ew^; z+F*jtVv9(mN2fLvAwN|y6^)t^!gFaLq$14|oy?{r-rQnKHlUj9onDWMX-nhPPJtjHsm;*kmIlSAESU751-{Mmi5hCW-;J8 zwM)$RkrLS+QKcr#B=NuX-v}e@dVT4 zeVr&Ko>3Zk(JwP@cjsjpr6GJ;3GGL3ht#E7hq~Fb)kFvF{10ibuh*&UK{J4YTZAJ8 z)-^`fHCy(W()Yk_TPD0p_G9pR<0_wp>dY3N$;~t0+D9~^;t3*2zTWZInRmd_S|At1 z@_jCUQ^1wk9hB!oYr6Zv+lS530E(!1lAU)SMfs<-z9u~kYgPJVDhWVLG+bA zejzD*BUgL~&#wf^=z}B`&b@RQLA;7djYm$2Dx1Jv1)w8%VA3AB=3Qf(N4P&B$M064 zE~c(fYb!96;L3)Y;agwPy|04h-r}S~uH5U0qS$C4jqh4pW0lU5*DH_Nm%cecE zk?YN4Sb<;BQ_NGWsGsEVvq9+l?BXakkA&uHywWu)J*eh0Z0QfXxSdp6SBxOr4+51P zXI-K6w+Ol!a|PBMR$zFGeXT&gp#}bdMO)L5)(5sE1o%y@Ogrd>LGuR^tM)JbIKcDkBx@>Q zX_{`9SoGCGb9TIFR;>&v_=Sl8&YO8#kNC9mR=;d%CwUlo5 zT=eyN|Eezea4zc=z`2a{5gaP>8Z*2_of9#j~1qF-}ig1fwxfZs_^MVj<+23 z;Z!M~MUI#IP1WRnl==v^=&PW2V}gX*2$d*MoX;S`S?rN;+BIRk#ix2q>x|TEnpiO`g z(nIDTtS}Jf4i>sua1Y3~oCs2jWe9!&P3}7mR0{0@B^CL<^%v9iR%N}`UVZTt+%7tsb?h3x}5$5?cf08tpC?o5&)Ab=I z`B`P`)yZ29m{v{IS_Us?BF8SOkw23}0ZUK`R+Z18R*V@-^>63UHhCx&BSr3>Xq! zy&C^8D%rt>c^1~&9o4w}E&8fFb6?H2dLuseT0PFxnrll6_uQ)28D4w_ln#1%p1G&8 zez_KXb(pz#nR==YdRZ;KR93k(d3rTTy|f(QV%U3SI4<>~TddD|6=|%V`DF_o{L<=@ zKiK|#gg4hCY8d_MH3>=JJ4&tuTx493S8`FGBEdwOv@T8!PqK7FqYW_{TXs*6*ic?i znAlKR&x7btb`R7;HbtBqkjE`#tv^TUcn`XHAByBRL`z?LbYJQYyTUj4yar7PuZ0h= zw2s~EYhF{662BdZ<|X~Q51??=JXSNZxx~b+R?D*ZG}eB)=@@`lP&g;GycM4e3JPlx z57Wx}GdIfxpuKTLE)~bPc*p7hS407I9HNW6BK&w`un@;qLGA;AKzFXJ_W|x~qD?y@ zP53H+u>gbxK{)SZRC5RDns9^#4mj@`$luUezZJ$-c*leQt|%gp=~>UtSYl&AJCZG{FD{fL7m5*6+QOvtJAtU~$yNt5NWYnZ>lEP)< zn2z4w7S=vmBwcz(9z9>shNmB$Hg=mz^1NREa62_$?bl7f1WiFVJ*(Bv$%{SLTAgCR zgg2TKETQZnmTsQu(dQb$;0%+jXM%-H^4?-RWrE}Wtf)8%poc;^4+jU!SI>6~uRa_< zsLE)V;g1&QxTeXhdJql}qYuwfH>TV(025AVY48E~OtsW~*T^a(V>ZY|#f!G3JyQBx zm$&hi#*348(}tlUVz6KFvYxQ^zmM414cL&`>5->?3RobLjqkT1BYtbx1n~WB{CI0v z2Jiui{|p_!wHyK#{xv?5>lgb{C zhv;XmU$7|_SdXZaLvNRkL0-h3M}Hi4A)(1@q-p()G`c)VV;cr9r_L@nb0LsbN?EJd zil5W4sAuuyy#erIkB+CpBx~#pXJc7$5NBun!k}g&;YzW<5C6q1$u1cDKo}9XtgujZ zoJ-ggb7c-rYCp1Pk2|KMsq&Gbvmuk8`%T$%LQz{1K{?M{1$FZ>eFW*uwWv5#3D*y} zdDjpxs8D7cmuNG;X-4Q1v^11K39iWRBR=|El_V&BVh$Wlw74PiiWgKSF=vSvJfgZl z^a*WlH>5hPnC*i*a=SqA3HEJYA@`YIG$Zv1f9hJHdYt#!a=3xSKBAzX@6|BL9Md{d zPahS^IiAO@;do30%xTxqJf`26_}(MFuM0n z{q6l@>%iudxM8R8ZtatgKf&vdS%e;4RWW>OA;bw|y#8P+e(rxf0;3T|CMzV|hW%pj{oU2vEx0?k+ z_(Hxb^GWU78fgCFZo6*e30RkNKV3(*YDx&~DX)y#nVmg|?b(jm{qJRxjafAMbr7og+(3+*F>mvlc);Icm?u+twFIOxv=T=XXd_OA4;Rtxv7f`xm9D_Tc{ ztAK67b-*6sYGAK0__e#$k@e+k=WwgL>zWU-^tl7^^Swtbx^LzusMmJ3nAbg>KA>~* zxe<~4eR=HUokOhVlSePXOa3O*3kbN${sR7lB)m7*j>dbk{>nr0uIoG`D;5On(o9po z>0;vI%W@P8-SNI5-Z|B=e_kx%YX^lgwvaB1UjL+|jaS~;APTv%A>GBc!Os|9k(#fg zQSKLtUs_rC2I3?w?|RQ;a*hRJ`+e_? zY8h$x*?NhE?kXi2$nhS)Gl~=Z{p~H`E;ZX!gC?@e3UjOzSH!0uabFTfEW2rUKbl5g zsRe$n+i033G?f;=YH1lr5J|m81DzNPPvn<67eH=DEe5 zHolSFJVtgqwA^o?88zHZ;$p)2A)LoK{Ng#{AMEixv|9p?TihC00A23t=CD?exmf(2 za=tHld~x-tsNNT4pK70pCSl)#!1oN8L&ZQWddWhp;TO5kR3w$zzQ1U^_w^Do^8ZNs zGN^9;^5rI6MqBRVt0WY%^Tp-G;^33}{jsl5Im;{AX9m=F-T9*Y0agsP!VY{Jo$OwA zXo>ea2*M&43nb(}#()(hD%{ET-)_r+#wb`P5TPGyq3V%C#o&x-uIqop$wFGaA8+!z zG4kh6%gj9W@cD>N^TLw!@bwAeIZDNlBW6jNfi7)^B~GiIpMli2F&um!F`0tabi>=D z4Y8vBJR-Iy?&T_r8Dl>#e8xS&>OgrT;B8Iev^D-KMq)>m2MlbJ&2CI!&U4IA86~wB zX+Jk3C329Y(1j=rea9T+$Rp^6(Z+$kF_(;f zhSkA=ks;?P)eht!NXK_zGVEN{=EMN(sb5$rQj{u^-Y5rO>T#6X{6wJ0m{NAE5kk=m zGZM1;?NoD^GNP054ILs+su8N_qK05urup4xlsM810ndf@Nt}$Ev#ria^bDml*RXsP z0pjm5U2w__72ezSjn?bT-rf`jD919nXcn&YX)#6*GB&`8uQl%>Cn8+KTXSR_CW1p` zl-a)!DaOA4-A6kS9!>Ks^L}4BQYL;VU@pxzq55 zE{PBH`?cKxAy|bJl&F*we{JDoP_RHeGUSFeLvl8YV{AbeY-3h^_l4vV}Lms>QvAEr2&$CRD+?JS78--IQWjCVG2=Z2nYqMzqi}}-h}_}QhU-nbOJExD?BsYpF8f=@6h?7 z5&vF(ul?`Nd%!&G2be!k74`rQ(AgZqJ1{aHoD399&40rc*>Lor@_7VoupJ4UJ>(xr z@VE_}CiLG&Hca@mzmFhQcsLG_(i#Ff@Rv4%G1fHx%gWHn$cdS=r7ZP3$}i@!Q0U3V zxY1(Ci6R{d5X{#EiLyF#gYyPtD{u=l)xUI5G$kZ94K$Xris7w`Ye`C_8A?m9g~sa) zu>$W}(`-@a-%V9Cb6>tZ`dG)@2f^a)9O=L zTGz{GW$QCei7{s6?@B`mDVJzXf}_X3ThiHYL~~zkTOfSnIbhPiuwdTRDx0%oz8l-` zIIa&CKTY1hX2$o}B*DMk@L-p621@1JvEzK?SrbCImG>0s!Lt3T8VW~6Y35m(lH~5x zvq&k>HBP$I3x2yBZbY(P9%o_9PqI0PiokEqzU73kye5m#3Q~=##dv8$%S>eZHdxX< z`F&HWY@3vK)ROW^wg-y2lwkBCX_r!fP+)b!>H7%J}pH0Uxela z+o<lhS_d18`mz;4}whhBZLXW581k8v`d)gSD)Gtl5$`Rsx z@VmMo&^cnT$Ju}!jVW-btHr*Z>iKJS#pqA3Fk#!fPsf*=-b*mAitWX7-Hv8@b_bh* zslpgm`D!tHVL`2%q=;{OTl^|OqeOe_Sz`#0!4ulSxy6CblkijpD2EA+Dy-bzpLH#+~@Y$Els>BNV!2?3N_O4Lf46@ja7gt2mzRD?<}EbrOu<-jhr)S zIu&N>{mniXv5<#p0?IjJfBu#Bj>S;*OxU-Fbwforf6b-2Yz@h`aE+n4Gvb!^PWVRd zPOn|)NZT>skv^==;<>Y7q>q zW&4`Stg&H<-Fx86iI!vT&R8jf z7kC3`ImiUh?J{kv3qm?!XAo*M*0FSqnb@>L!(nth#Fn%r@w*19MoP-cDAP$O6bgA* z39o4bNZlOuB!VO-5%irQr&=$=f=bAz^v{uaSKq9IZuzv7u_F9EY8#gy>R|}UpJDW3qKb;gIOaaM zW26_Nh!^I&e~}eCz~Br1_UQ)J;$&hQOITkJ(XMsyQ zQ9IZKPXRYzFfD6*0OgOfP5||NFNwX~_AC^5*I2%1Tyt15Wn>b$nqAr}%oSNW6FoLu z?`OEkX(7277_OtZ-c?Gds@IDmU*%3*aUFiTX}_6D3x0U+Lx`7aSY1EPb*7?!jbsO; zbvQjkjaa`ZBY|SPmoSx7-Hv0fUz-jueAG$Fd%x+cy8~VCHdiM@QfI{q za|;oh%~>~R`1KDV;vAdV7AwYg_0ByVF>IZr){k`*rRr)~I#K0$=MuzWrlMXLoR^bX zyb^Rkju{u${&t!r1Ihj6LDBr@EJjj3BaP937j*c&y!#p0uQZubot(BcmrF;-MxB7G zL=7Vfpv+*6Rd7rCtV`e0QAQ)*$iNRJndE$%xi9BShrQ*q?rFCnQ#$2xr#V#OAae%_ z^MV)DRr$|p{V!HVqZ_c9YAh6*YBA0H7Pq0m`6o(BQ0<;-Yc}{wiS=P7vODJr{Wz!G zCtw@vJV9C+1Ftn=qA__zYC^k4q$#JQ8RSC_ zu9*uMiC&BID@xmzD(1PvB*(iu6G`0MunXdM7>?d{reBxsc6-062niv8%9revMYQaI zzJqg+RDnZweFtLhP`pvIbGnwdQLl4%gq2~U#33c^ZW7Jy;tM6s%f&%>EW8j{xl%GE?oJPM zO{tRBHoo#?mpTVojt?RkjrSR39NnT}n~=V{H%Q%L+Uugd6f_z>^cs~l)j)f~a}br2 z@Q3Ox@~WX^)vYat)yL&F4yEoJ5tn*|LWbhQ#K!PP8S}JJN4agvTFK!APKAb z?*Yq&v|koUKNutEgr-+QHyh73nQW0Xv)dRF729mRGeT{rvf*7Eu?ScpFW0(#zso(U zeK3K=p$JlcmtQ0dC+{dU{UQnT8!>;~yXaMM3bIb^T3CUIRFWY>jL_W#h;K+Uz>RR~ z7g9-zZqcjDhznqljNal&F&S2{zFi0@W1;}?cRh?k!qNF$2Dxvth zHY?OiIyX%PGq6BO=A~PuxNOaYnCtOl)Fx>#ts&bOS}Hb+Q8`V8y!5L$ zq}1~8@V|WCAB8S+nn-+hx`7AtJCJIK?e{SC5hgDQ)cP|Fkpcn0F!R$*_K3SZ@jfoq zTZ&meN=a#viumCdg;lL&%w`|uK$+Ko4$9_afAzz`fx=s*&3>83^N-$(UMUebMBhC# zGK{iVFKZ&lfDcuNCOG6ogvUt*zqQp@e?sw@Kqn(EDC;jpU{p4CSvTC9Z&M|A>rW6Q zJZwqd{z}B^{=gFe1j+O;&~_DXtsBth`;i-RK$D9zF2VKOU`$QCmm`?KwIAj24ws5f zy1DeaS8~{68?<3yAZ014V;uykMwyyvWKBp=YYrTbPupI8ANeNyMHn6bK+s@s5fGA~FWgaQ78~3(i*ZI($I3 z-e}Vr^hoEBUl+nP^hlHJnhMv1IPDli$57C6H9SkPbUv3Ad+umrxIBEQTN+ua_$Fqr z{MnqPP{#N~YQ<|{n0a>1Z7I%cYEVNO>awt#sxp9;kW}67sq27BK*A22YDa)jK4o6B z7gd91%&bxdXq>H$QT*MW#-ndZF*Uu5Jo7+>3hc6mWq9OP$Si+GXV{?dl|jzdGQGuU zGuQa^2&oR#f$R&w6_RFd$zpuQNIJt->LQtn|8aen&bXu;C=@U_9%ECOXP zfV$|fkm$&DZ^hz_nlF_zi?X#zNWxlTs3Hb{L}Q3vv07 zT*b_sqX_8^pGLzD_1z(eB}?TT%giD@6VVs?KLUe4KFf}a3;_X+|Nj!0KfFW~7K#Am zPY=KcW01kU{G}kE^GE;(m;nmD66!B`S&4t+DZb+f=wJ+PIAqxWzmo$bvI#%{t*s-V zf`j7VbpB2M!*xi<5dh$iZ~wUk{1tzH0LuaTa)^Kh#>Rz@|DR+w93v>69smb+qyPZ^ zQJpse!~vq;LO=so6~V>)lU(b2<4?%b2q<7-8MtVKzdG0B-#Qfs5fH&_Sa8YzNKj+3-a4_5s++Ra&X>c6i zbXS1eKSTeqL@=o)-1NVhe*$zf^F}cFo&fIu(EQg4ep6@l&)YxVy?F}&rOv#?*Yz6U z{a0O5rQYA#05NsH*%f_&W%_^JJU)DL^Ar!B0t)djBmPrR|2YdbaDe0dUnu`WL_F{& zS}Y2X_#0`^e^@W18wKVRR0hNs_Z?BEa(_dh+6fPcly)dpwux17Ll6}|Egz60W$FD2gq za_Ik;y#I;@8JrFPjQ>>vev29VKYjn@4P0>w@cy?B-mv`9PXsnd2H^co%zxg1-&U2# z-#~)jY&84}-Ji6#j=iNFE(S33Pv;x{4`6#^fX=_X{>k`k?;DV9Jb=c(p#4{cV5U+4 z)jyx!syq3g(*ITm_^rU)|F*$zKH*{fKehX|7!g52qi-wHCkPPnSLlBc!v~>mzGb&I z6YlokTKjX>pxghp+yQKWB@~$Ix3dcHThPD!8~+30zj_2ux5I5Q{GT20=X1Ev|4K0- z9PlT7*r4IAH?RlSu-Jc-{Xe_!K+&TJsGzLQH?ORAVQc?E`BMsi)+~QLT=PFXZ=Kcu z!u{Vkm`@!L@vn5=?5F`hDo?4rdl_)2`xwa>xg-G#Gk?O&$PEd?h9Zpa>+X_ViRMkF zz-qK}S%7*$%lsl7h>Iz?8GJtfx}ki=o^LF+Wh&#dqp&-q(0Xs--17Qxf!#)%r#?1b znnNPUci^Zj&GL}zE-b0niiMAor(~#$!iy42fQV?_$;7`$ti}qg!KyG=T<=(92no7W zVdeHbj-ba4oo;>jzGh2v!Jz797HKM9XA?e&D8-?T!ZnLkVD1piV5MJW(1M{k+n{59 zh^qTxu=qhCp38-gZS@uw4QkN^sru_QHeyEO)0Do-mD5G7q zftF)xldfl7%Wx^s@t{O9Pe$`d5fqvLbG7v|i?-&67;n$8m~t|+G?(JhJ~j&m4$yWm zadGt1XB7+TpdEw3bEw5-{hjp`aJI=@8@v?Chqd%Tspz-UUZLDMk%J0<{h1XTgGOxUuSnIF+hQmCKA4EPWbXd4A)> z+;*PxSIDmy5Lzej5u+-*7rl=XRZUd)H^hmY;cC1hX+(*Vr3Q}ydUPMksv{bkKO7u4 zemJ1%dHDaxddKKWn{I2kJL%ZAZQHi3j*X6;>`v0LI<}o1Ysa=aw(X9MH_!dt=R0SN z@7FczLhZE*bFRHc)vV;!2;e*aRMx|5evOYGuvTq7tUBQ!{UD13Ez-GC1?BDVUIf_1n zkN+?`9TQ;r8Vvo*mpX|5AGQAjBA=iD17g>P68&GKWl!lk`A^Cb3A+1V`1wQ@_LRu~ zFm6Z%l+V9&?h^%a;Ql+eKhg3N(`_M@{`Y-05Y~4{qJQV?Ka6sD4kh~E=l{%bK_qD0 z6oR2ohGjs7Xp8r^Z!2}tQLM{ETb^iqo5S$ex-oJ1DLl)sRkg)%< z{y%Jde(=f0ryWr6|JJKrQ97 ziReL}9JBW?X#E2&k+@Jf|M#a25g`AEr~YZu&oTmNu>~^oU!(uA$BqgL7F7KTQTnfu z|6u56z84~;djtj^L@V_FvH7PvyeWcxpEpytA!7cEYM^NvC@_S7f%HG-DimDa|4$gGEeTcd@Av<7^T-<%-T!s`GyFmZ!D>VP zo3l>&Yz=S?CFO$1QLLtc4WC?4w?^bl$1<_y~qS+|zG5T4RrnIs27 z^JaBT8P;Brc}3h~Nr>opvj%lSk`^)w95SYuq(VtbLD@a-6%jzALsXtqUFVf5n}{>o zx+}bb^Q>99i!rN0oLM<~Nz1hSECtVk$k2#38$SE&Ku4^HDeOf2gGF0u_JQ;|6ZwN2 z*F=#QV*1}gGSRZ z7|D?*3hQ{D^ejMw{05@*gtLrdN})u&CRF1{;JT`n2bnxwp=Sts5SURY-jLd`j4@SZ z;x#Q*W%3~|S4ddZWTMApyrL!FF+SDXs7x1TQYIaB_F?hOF&GVP)FSV(=yA)W43^9j zSG+#`umNep_jHAn>HT8Z3Xxdoio3!hhudGwW_57YT|mYr$JFT+}Kr)M`kc%ALdnV-FXxm zI+d=8@;s?~p?3^KY|v6Vta9ni!`Pl`SDyN7ivj3g?aM>dAifRvsDR_*cnW$Sgy<0- zCfaj|QD#0nEJD6jet{Jgp@li|Eva8Y!&lxvqs*=%b1XJYihz9K<$di@&h4l)waFFR zFyFIg=@As1!h}{JPfU8Co~%KGX`<1em>P#|&`|?&X8V30UUcLoD;ky8hO##UA1qj$ z$N`+gU4z{^<8%wyy9EJ)bs^vkxd2sNWOIzJE>Lghbg%YcD0$7xMCA|Fm~SP@Swlv3 zhc2gc>JdoPIXo3mZm8Z|%!4E!{D!{cWf8{Tlv-eXBC9J~((ihAqcdn`JzG0irJ#)` zg@$${yU`!Gn}jPc8kr-TzoKD7ElybOqX4|qb`=n-v$?$d^Tqzk&nFyCVEK`c?HP8E z9{oKs+AD8q%%(7_eP(}IeHHN+xZi1L3b~hrkdd!)q@Ge`NX$7zszoGlrNXm;THnuY zgTcVzjs6=mBwqCT4wY^<7v71fsS8QG-xv?x!I^G&I$ZH{pl(W6^f+K6YZ~*KD-ysO zLRcu}=OaJOXlPo{B9uBbj`dwv^GW`$;YQ8;nS7Up2m7`%4dV!!hJ}`ulOl+sX&{hR zNN`afkV`|XH<96G#bLjn7gOooW`23Upb5Z}OX>^uI#W8yv{ zgyiYW9Z|4T{am%4S}y{i!;{rO!2=XfuN}Zuu{g;gpQK)AFE67m9v+G>I1qa6+IjlvP5_FL2tp@n zTLpjPkv}6*19eCE`(5Nl7g?%`-y`*6RvqaM2YlG!oIJC3@pS2-dIYKk@a--$EE^J# z22o6M;a#__!MV0Az(La2%np?BJmi0;yDOW|zht%X*g;+l3P4^YnUOiLIhK%n$T$=E z+Zw?&;kq(q?-HajXC|0_{{v_+su94p9o>rJIT8%=mwSlh{)^L0gj6#>e)hXo3CmWR zu*Yui;rOczC(hC@D4fQ+M*yV2u<5K=;9|Y!WcTM~=<%1mgIzz4%MK$d5&W!Q`}km; zvQL_)l=*p2od#>9dQF@1LRB#nn$nM7B1mJsTw}ju!(eyvC+`|LngAe02P>oO)X~`> zAg@_;27k&Y-4Q(|CTyH;0SW#~#k3t98GorixVQKMOaz8TAX2iFr^oNxaLnld%d-L{1zukRyF z_=@QdTo&sHKg54r$*46&c&Ol*p29VxHU41Z8XXPt*CEUKbFB;h(way70G(9ZCorDt zaby5)7*XZVwDbY-x0cUhD(9F9as#V2mzqEjwbfS`KmouXY^$diWKtnlXA0W(REdwh(up!Cy9f?gY{?SLk41PEKX}ImupOyA%b&at$|dc`uphao z2roCZxEzjGGGv@SaM15Am&_?K*(y`!S5QphLbJSd=6)DUs~TViy-$)}dm1`3t8>OD zKoV-;4cNXJ8Ut3fZX1I-S&sB*e5qc#YxC_i#PrZS9--b61nM!&EsjN=Q$#jrks#mn zj&6va+a@Qfx^K#%<k*dsFx!2Y|vqs@N7Q%%WX{V07*gGkSQB z<5mtxRmKWqBHB|EQbJQzwTfRt9t(Lzjdwb5>J&sxzTEV8f|L^CmOqla3z=Ew5*G%K z89FUEUt$mqOJ$ZLdM_@#dNUN*0!}KJWE*t8R$MnGZSMrEz5>a8%|h3hD7{urzC^OI ziy{B!$pqAZ9#_-F#yq=2lHIQ~4G7++=z)qqFzq5JaOJgnxx?8lEC|&szs`W6oKj%G zAS!tMu^HhOa|$6b`<5aeGAfTOX&I4#h`Jp2DUc;olZiz0= zlCg{NtBPY$wZwFZ$5TzzHgu?@vw5!QIS%Qcs3?H5Djm`^!&Wu}4d~vqofTBJ6t>7Z zK>BzqToa_lR@3ftn_UOxshmaUY4TlNaSh&`K5jxI5wkBHrK@sc@#JrlM{~5JCnbY9 z>g#fxS=%Ql%Z=AU-m zHT%%PqH#=zIi(y5sfbJneF7V6zMsS66k2df7HPFX)*ON|nrd>*V(`#PoPM-KODz2i z)sE#|1ti$oJqynI@o=dtq%UR)dO`fJ@3R0MfjXhZU;V~SNl0kB85;hoS@hE*?zJlE ziDzyH3@S6+Jj^X>y>#58w2hWTap`xAQH~_eAO=2B^*SC z+0HWC-vhM=2DZ~r3&#EnD++|5j8*>`qEMqOWo%N&w(QGZ=@+s#)bWPnyqH(rYTFmWOZkWH@>e;3=f1GhUf5w`oLh?`6--Zf|GT9=YIbOd@@LNvq7hniA$%mQy*BZr?Dj$|$~d$b29= zYL}$XlMhE`-W0(YwbL~nu7kAu)ZNQd8(}FBX(^Cl$rEb%#!>D_D7pO#NL&VB<@oVd zrxXz36VA5T zLiSYPaNuenMl4=byYEYX*&}Z!ErrdE#_u`CDw+R$EH&V69XzPjX>)#qx>V(*C|?;aSI3=~f5Pta=x& z)yCyzmyt+;E`OrZZ~d#b1*^zTEwo;PV2sm^e|7fQP9@gzrRBH1CEMx*;>Pk}ZDo7R zbZgG0e}Kp3*xEf5fIqzJTJbIHA@=N;#POofGXuQ(;6f}Lyn5Q7{t)$}{yeY=N{6Qn z$2p#PQT0GHN!n<#~4^K%yxBjv=)bVHUNmzw&G( zbnS_(>WS>VpXusU7Xxlo*@+gEd)hnZTTJr)$Vv0@uZy0Z@6AQ`|$SAK%N+@1*JjWI_Sap;CDpypHY%{?(mXo%W<0xAwM@0}eP&HPD!YRJ@D3V@XcI6+3b=Ct z=|R1jCdS`}yv{mm!cHMeTV?CF3lSWbNNbJ_xOoD5!X>h1Z~#wp&~=q(sQ#Ipe03i| z6Hc)75=4q!Mtma*&e#h3e!uNc<^MhY{krgC^buq+C_ z9NT*VwfV3vxFt_u{1li9>!%OXv?vL8Fe*^ z<{er2=H^{Ri$>-H=if`TuYPGt)?`84g+x9Rr?gX-_+yJuaK}R$VI~=q5QI?TMq%>e z1FcI%x$zp1_F+S`)M5r7t^#OCH0pkt6cR-NWV8(_+*6|`(MWe-F_GB@JlW3Kb zQK|Lz321*%Z^Iv##!&WUoI3?qipDH53s3r%ID`vm| z;EK;VEf1kZLp|!gVn035KVe}y_M-JZL=aE%$}EX`?ou2_zmskjFJGb6)Hqli+laLa zG<#6{C^u{&c^lC=Q)d$(@k&i~i4V2NaeT zxlpIenH*yhDhfBGj=@LYkomnNm!jV>-RkaP#Y@&g(}*wGWBV3@5DV!jLR?4}aBB4O zq#m3S=O8n+2P!o}m}gTsxV%V z`Pa*o7B`O(YR=%B73z%}wzDdq3||~F1{tuxZXjCzoYO&&e)PU$75z-sYb&K)p#Y`_w55lTb&@`Pv7L|AU0LTA4fjnn0QRCAs@w z%DUuto3Rb>7YFRNZTX=OfT^!ZmU6Y;#?0us)w#G~xZ=~FP6B)U+VZK!EVd$+RB~KG z<@AMeR=SF){wDmPBhcn7H=MEFmk32)v2&B~ge8zEU6B23;X z_Ln}`vVTq4{kq*B$>fV-o%sEF@y^*YMFD-R&-j(M5M&QUqQOPffKQnfg<&OzcnrsS zab^^XQ0=Aw+WN0e6Cc5A;A*;1@9?GLWNOn>A*gVlA|&d6uOlJ}!j)EWWyBV)S?5fRD0G zjqZ8Y`TGx#^Axtk0_MEx{2`^4#A{!FVN#?Ai0C3pTDO$W!!m2o_2XAU!!?@F&+}W& zdz%&=40!1p>Q~+M-RZ(O%tA6J7I|vpg`KY$durnSN@?iv6k~g%z`}on*qCwk{jh+< zI#Ww+vu_j30~E2^QY5`4Y3v5so8ud~sol!NG7mvvCvXZc0RoMGmT$&rjQl7IFns^` zsiMPGiRxg_Ev6IvHIt|!S~QpwSISz-sE!kJ$d*GppCFj?+^S;d`crk);^14z4fa~D zf(7^KrJg-3;Y_hfhI>U|4OXU4o{CVD_S-|?5%eVf`o!3K=8d7Fr*Xb_PD{tg5emyl zV(_dnzAar-8bFw^SeUNKTzF!zv;$x?7Z1tvmMh0>$$Xd8iQCv;*gBtPp$2R@nBu_L ztASd%sY{DTq+fM5!RNSiRX5CDbu0wF0d(n(b@9w?EvXeSdsOPMI+j@x z)+689&5$gT-PQIsc|Oef_0zkR!bdw~pE+3iQK`wR7Ul$kFhk_@!oln@o~?jt_iG=6 zO3k4a0*kr%RbZORGv|@%NAk9TGeIJNqg&l+!#Zqw%*X1gOX(e;kCVv#kxuij~La%E_a156*Y z1q{IMxBZCqSJOGTA8_cw@OZnP-uta-%P^ zbU)b6s9PkM>il&IrHvj|7+?fWk52O|UU(%kP~12bMjLX;zn>AVNv0yv*TGA+$3m-yXAjdj zOJ7KvdyR$%4l2c$2itJ>zImb=4z%U_gjrj)aEYt=U>;xJdg$p==u<_d1z??dTat~{ ztCGZSLJj|p!vhM|uL{>!`^D8dl$_U-Fvff!nXgAWeMiW3xE}W@px~;aD_pF_Qb>k9 z69<266>=*b;z}>(jV`7eNp}a+oH2%Ul2DVjO0-zACF55f=tjN<71Y@J__O&UW;Hy4 z!G+J{k*&ERVZW?mZ}#w77C^bT4}XVY(99Z`->?Eib*7dQ$$<&==a;?pRzJR(d$yaB zy;eO~3(BE4*cfUxd%)aG^U*t=Vbl{=PfseJS@cmq2B!o^rR^w|O3F57CEm>V;but8 z1M~?13AbW-!%~o~579z;!nQd!u5A^aF53csbE<6zSM2pl-#$s-0xnXonZm_Wh7yIS zP%9N9`P>ALZ-XmdC8%eVdZpjY=8j8@!u@F{r&6|Hv))A4LlvG?+k2mcj{V#F?1_#i z9ur^ui=ZwmJM{xPka<)%B^cc-uN-E&7I(hI!9`u5%h2Gb$)~^o(rcx$H9cCzd1mw6gz(yQyX=I!>VzXJtnSyy{5z+$ zYvItQCxrHJVo8%K)$LUy0K${9g#2N6_N5zJkaeHzyORW9|B}|g!@jQ(BT1vro;Ky) zNl%E#;SKC|X0aH-B28j$I160J2iRjrsAtE{mLa${FucGNAl1dbulM9H&M@$OB2*1U zNQP#i4E;1-iD0B;0!tv9^Un}tq)SIjU!~Y!>$m$>vt0fk*&I_v@%4~90yN+lp0MO( z;0#QYD?dd515F6SmABa0VCLaNSgX86`bGp+eUbINDr8yL8dOeNp7oe=Al7+>dDr~m zj4|JB5ytR!X)I;|Skh@A*)$t%dwZUq$>G+L^jre5d=@_6vxa;sFpYVU)ws&EckO4{ zb2PWe=FePzwuKYWPVDn}JJXK?KQF4kV{Mn<5341BO|dDmg$@%%$m=sP^K!MsLz-c> z<9fIjYjV>5yUs)m3h!zQ38&#b3x!Io&}f}4V=-@oezRXg#XtJ)M4@A&pB()}>Gvs4 zk%+Yb$bNUBEZUn3KQ{^JaY98 zcM4qq%GCr0oN2pPA22;!MEH1L-Bx8LEuada~)xxHlhEZYGODiuA_Q zSQbBbX1{E+Xa0%XL@;^F%gDMQ0&TMVhr=@RuQXgo2c=H0ohfOhjhiM%)s+-TBmdXB)$k3kM+$qy%Glf;%*n(UIGWp#Q4CGD=P=bKZurHLDI2PlUQ5M zzB**__SQnmY^TX?YK>7LSYBr6jW#%n@_X|`4~C&0-yDT+f-g;G3-{y<@8)oRBU1ic zS-QVlmEcMA<;%6$|6P9a&*nA~-p})1+|OWeKz?}8_F(@#1SZb}S`>g9k36hOM*J=Q zC$U5jF+m(Tu?VxaqYS4p#Yo6mh=tbKc|D#wy51R>32HRNS;xbMPqp+IpXJ4Ra{lQ{ z2Oyhht%J?Q;$S>&){=3v-iOE&`^!C-K4$e{7x~qfk0in_oyW)Z9l)i~@i~+CS?Jru+1&L;0%M4Y!b*RvY^)V+hO-`KY5nlMo?)c%x@QRu_Si^9uaQA zA}djNlNl5)@bl0wvU+LQ`!btTE}E;AUa$AQ3ncy#KHckQArd zM~IcN4~e2;p=tx-Xd)C?76WBjy3udwFIVdcB$00vR7^xTrmbVNg||X8O!6S;!lLN< zNy~Y9(TgzWB3;$!n~ahKp5ltRM*|zxy&52>kTu?sho(%!X<{0;&~2`C9dX|n8;uCw zl64%5sihQA1l82F9b-xhhgj7f8MrqIAGy8hxg?SxJ_-PW^O*XgT^yMDg8&wZ?m)V; zWgCUs-ats3iux^^vzS6?Rk<+2JMpxnTWyIk1BEdIvDn69?v20W4>S88buZJKoTZDNfoO^(0~KxslG{voW8=V zKSHz*1BXLyk-k*ysY2~^V2VVm+?r7Y9)sru<&wf}^D;U}`w}x;k?cJ}FMJr((tj?a z-P~uA63NHll+wIPagmpQ>wA+U2;?&+fJKAyf8e*SiSs& z5L#kuOy3cK^QR2Uk%*MzPyE&8(cIs68!09z+Qq%cnX+_&8r#}$%6Qc*$G?rL)Y`Ac z-aA|DIcS0}Wt1uD$q55+`gM4OCFPmz@AM1n=t1J-DxT(hlQ!&~Gzx>vV{;H;#!+oB zArqjrpN{dWT(129wK`)5A<_$aiA*<4^apC?W`4j1=Kvojp0GW*)rm*KC02=ltiRLA z!?8ysjbM#7;@5rTsZg26NMWLBCNMwwuCPt2;>S6Y0*MwH!TKd^CzQAs7d2nw+AHyT zCI)xnH-Gb5m~Xd@1C%T5uY>5Dx^}D_{+58+vfG!Af#TV}NSGPcWACw;tQ$(V_iO^} zpbuHKSBr>E2F)nt$6?2Cq0)UN+E)qw);@HA-kIZ0U>18n<4OH$s_(Q}?nl_jy;0lJ zDXKkV_TeP4D8XYqJ^numfRYPguB zf@6C?x_1=K5b4dB(>LC1a?iv8%~1fjyjSkPLc+RoUH1;!-Y+w+-% z3Cof^eTi(x9?3LFEc!e5=`}mRTvR%QLZ3dWmU~vPtsTt&lBYj6KIfD!=`(Tmw zl8wYjprwxHKIgoFi-JuFOfol;*qWs`P6N5)+NDG(-7}Iv?opH2slU^htBL^fjTls# z*xIFC^_G4UCDjL0hI{s;4on}+`9OV}T0C_Eo(1Mj_!`WHXXU+G z2i#FOPwAUNJ)MwNoV-E?dI%5X)w0c{Q=pAPMwqPoW5{vKgr|{=Ew*2(g zx00P}D!c#o;W84b;1xc=7N(t&e$5*BP`Ef|a1E>W-TG=ny>&DZ0rM}w@i!m{HnpVinm`B@l+W$9g)WfmHxF%if=@Dw)=>s z{fAk}m!1ux-ImV|txlWT&Eo+WyoolxzNP&&QAwBUukij)Uiti%Drpw4f z**&S{G9>N8uE~WQUjcRcMTGy_ZyihVp+LIEYt+U@3Gri{?p`+`vq8oMl5*xafk_GJ!3I=`%q`O}xfj3^j+L6S~ z0;U*$&I`2G*(33SzVY0WE=ug{g~TUh2a6;w^y~RYTUvlrUR%VZwbn#|(+E#wD1*2Z zil4YE&Tgb&h)SJj_OOrglXhzy#oKiLeXjAOrK3vI$R?kDsUh2!DK0 z;L){fm@Iz9VPM8pg$GWVv2xb{vth!1X`CBe%$^0U-oZI5wlHCr!&T5+hn&2ct1p|4 z8ah3k_|69;2^w^GyDPN(XsqUkWlIu?t)oS+65RyI8fv&|SkX?)<_CzchFPE}5a{x- zJ6f$ej?pbF^apAdw1~`^_q8ia2jTgaP$7acF<}f zLT}a`C?b)yqXVidH;2ynYUi7I-{_2-fyFeyH4^Am?S20sR&7<{@i$*-bN0qN<&@lG zkwc5xh4alR^q!=DLdK7sjCE%&jAtnXv*wbjK!B?8M-j{T&IGP#4xmA2T*YD7d6)+77oyBQAZV^2gw37 z9Y80=s@Qvyhluk}z9e%VJrTkNjnxi&ftNlgpFsquSE}Kur&9Gv%VFN2h-98mLf-|x z$3KF0t#U>~(quOA5oim1#TbU(Mf)jOv7v`{t@Y@)&qk`&_LTBV4=HJcxa5@O;Kc^m zZr%wU;8XrRtZLMmF7_mPp`9%d(-qLD5JTMjWcjM59+uVnTfF7z@KufLBao2l60MCi zo2*-B`aBzz^Mmc=1kBCh9cDt!MDP4eSi+s+4tgfUwsSEf%Yg6_qTUuP@63h?x8y7x z+BGTKp@u9d$`L3?3$d*5K42tYBEMfryk+z@V>C=uj>O}ONr(z{BEi{w+&PQA8FvN(58XAC-^)0DVeVU{%rpr!M5TkX>Byop`zp_z5U-` zqNJt0hhOET(n=kH#^SjuFrTu690(5t9YfX{?-+N(1${D`zDheOa_GYaPLQq<=V#72 z4A`Z3b$r2LJz+gtlPOUT9q0)2F55__Y?9707O${wEdgv{O z$B`yJT^k_|+S(5K!LAKj05V?;rQ&kV<+jovLaFgQmp6W?wSO`B`&4}V}6S`0g5`jN2i}@s)hYl zJ7!T(@BrczHd&}TCG+-IS^&k`W>D&FsmmqPoPa#v3`-;AH2`OtF7x~#Uipckt?^3P zIbX;i-gBYoqsUjgQznpZE+W^wC`h+3MmXB)rP}Pu5wp(7+$w{1dd~V($0)5l(GI;; z5+_TXD*PBGKd`IG2BGy>S_Y(BfvBX6-eI06oVCutGWv%yr)*sAy=RTrxs_2Nimtfe zLtiT#0`i5bA8<%#tz_aIEn|jSsGS9{_8Zp1E)}N-N;AjG+Zl7xkiJzN;*I!tn4AaN zL0S_8>VtSAuwRK9yPn=gC>Gh<{sZ5;4=q$~6sEKjZ7_1VkJl;W2f@Eg#XFE77H0<=6#R zTCSHzA=6U*QZ2|Tk)Q3W-FDblE8U}=XWjctGkaaj3kc|1!O}Nr3v<}lf@o;iWq$Mk z?!zM7<#KZyVx&Lf{utKkB&T&L)hn0LdWZl=K-o|J_GUXxKCfJ_O(2|J!Xqs8?Icr& z#VES$6yOVaJ7#K>FJ|iJnpI!BJ}uF#`raoL@)ZTv#tsKw<_r3vJMfDNmxX4gt4OY9 z2?}=MP$KCV9=6`{{ImBU*Z|{iA`aA`@0NEi1>$2dnr<8xvDDIQVPvrp7vQbq1or_a z@AgE{lFGIly|KRBH-hT5K|2;Sk7-UGpR8} zA}&B&s(+I1`9XC8e7o2Hhgr?SwMKa5EC8lNwwONkqPh=DJwq)S@NzYLJA48d@2h^2lYDSch{_(YoD(!9xIOyIEYsw>qN7p zY<2{bG~QAf9Ty@~bH5Vl`9L)!CE6LtMl*$dP$;j-a5HbF780K+Cr-Y4Sm*{L0m!lv zndKKy-i;LDtd$1?3sLKLaKkKTe@9Wd3UW`21YDn3RyYFdX_79HWD*ORm#+^DyUW7;6hVt>bY87E3Lezk~$VxMagRMD>PMrD-hQkau)1PW1lxC zWZOJC%S0@~Vl{CT@#qQpj&RmdRy|iS8X=4~&1h^DiV(iLvMLXMsL=)-koGZ5?sms9 zIVE28uHt+=Ra(`_DX#MedcTScruDnMD-drky7+aV(t(uf!orQE5_`QvZ!X$let5B; zXM$am!v3-{aiv9J{X)~Dl&@_Rm}k19=~33UenQwdqMosC6WO|$*ws3(nf``3zpDN) zFd$F;5@b2|>%>uW|FzW;usHX4Qaqgp2YFl`URU|@sum%eFkYDsQ{(dj?`d*TD=-t- zov56vO9iQm9VORncvd!T18MppC&gvCF;F|K;nn6|0;?jFS!M-6POP$ z>wDjEm)&Tn`ja%>@$Td+Ei5zju$v-FJ(T7|^{&e_fTFt{T7+B0#`walP*t`t93JqQV4^ZxTp+~wLCtEfb*ArJ5(^%lm?Y2cV%rsmn99cs@F6wXGNYBo(t-+vIcP)) zPXE0@4)SK1e)S?B(LK@=;AQFJYmze=3%?akroOIH94E_G*#}A*1g+q8v`jnPspcd4 z!+76E`o52vQxCg0r$gTr=L^;08;pz3lY_04w#<)x(CF|NSzWZ3!GzH6^{EaUsGic@ zBupxZ3+K}TaI&;3FvTh^uT$nTkpvvw0=Ci|Q+Csqc`VoBcM63|jk&Ljh}R?=Tdc0}$IavnERC9~U9RqC zB)<+9hi6alK+nm8A2EcRYUpg9_ropAf~}0d4Zc^Kex6R7Ta0B-q`7?!ATGEpc!qhZ zGgG*m5yo(^emHX`YK3ugz3+mZ5Da{)V9tL8B((?m-;i=aI)|M2K#7H#SG!Kyh7;Aj ziJZkY3|(N;TZB^AuN-RxZ5~PYqh(d3U%>uK_L}~+n5Yt#$=VhYIP_aHrQgowAc6mI zRspQgw~X?VXS1jA$?ULq;?Q zz{-XRU6Pq)Y523dNecdi0ut1hdEv%hsXjIon=5*;8LHk8;?hgBpu(%v2sHE zlLWyWH)NGLT*X9mxjYtVyy1QGf10+?c`d08{9kDyn*I-?!j`+#EDOMYy7HtS}Crttg~dfOcF{;35I^G zH?m~RIdSMx#WVTfH74U?5{yU-C|1{8csgTIr3He?(J)ocV<|3F_i+g8)gQm^{%T&T z7GopD=^Sn7?^GYiwS1u~_cnAQwl3*~Fo|xp(ouGl%BXPu}vG5M6@lheGtaeXcNqvq|K@vRdW3i%G=MB3XQVC3&r32FL1 zi5ZBc<&TK&o)2f2yUpq;%2li=%jZ)ooU6hpBlD{3g=J6?L;sJwYKJoSFB7`tW~Jql zhImSk{kk{dbl5F4X_Bg@fD+qCxn3}=Ldy?;p1)0t5)oP+@xCZON@&xONuAe*R6v_i#t zLYq=cq>}em-bMXJ1W#=)F`#^MvH72DZq6n2`6niG>K<(tt+6xAPQol$)vBa=$7iNF zRTu0`3yYxeez`!`t$Ol3gNR8=+6l4NSKr+({rt~^>uHe25tp@>Lsbwp%XEjSZ@yp5 zk((-nbL}Pa8yM_l1B{R`t7qx>PF!VhoFQM_v5U~q!cB{x`s^?p{YU&;`(xgvU}%tg zf25nfw@z6|x00_qd(m{TwW__nFkSE6LuJ)S{E@YtKlZ*YaFwXeoa{M=?N>J?YQVa!95tDEzbN9Y#ELhJA&&xepCe>bCEF;LBcxaY zatjS!T8=30$94EC5|k|MiUNCi$$W(!;Oso4jA&3W$zaK!@7*#IQ)ke3j?Ji!Bh0@| zz8wCjT%jYv05rtX2?QH>28Wdfl-EX8$o=v3=C%}oCb_kwfpV?W2*+J!l^s5oiN7oQ zNo%NJZk5I$+^pMi&2G7`>&G`I?ZHUlIhLFVk)r;4r*9PTX914cvW14B{Y{cmB!_HS z?WMQ2N0|CTe6CA`65CKtaDn8Nwb19Ww@SHItC)|0C;+#B0{2-#TutsyD~}=0KUHC= zwydfR=k>Nbmm^VVHY?DHcQ8#ou8QtH2d-cu&T$9a-L6~ud)4LFtCQDxc}5M;3Z(5nqZ-0t?wmQM%5vBpTYp23i{PBsN-4P}5<`u*2vGr}huo zvw-2u41jP5r^2L-@+wBll}!fm=oa#JoV`8#m4T@%g4;#I6=~Jm=+{{so!*&^3vz8a z70HGPLBpCZWLOBhSzx8Z;o(>lvZnexS_Vzw*7))5`g9F6w~Bu&leXqzwZtkr$w4k} zXK-LB2ZuSgv`*4NWntL2WkvwiuzL3)lbB3rz`5?BG%EoQCz00_KF^EFbMHBZr#qH&rx5G=P_!CX7N-w zZ21!&_G6W*=Hmo!aV2?3uL*y>fHjktu0+kWsG~RRaH>qShNE7NNu3YO+KITS^9WN* z1TYpQzAv!b-8an(fjQRRW1>)+y1~o0H8U!UHqyPw)5)>2@|wah9_w=RvCfMkXKl$D zrf$aE41A1rhEn16$VQJ0Fz)s%I0~@H3q3!60lsdua%@+NW79u%1v_PNNeShr83C2p zd0o?F02k-Y;7!AlHg43M0{3__X3@&TfJ_7uq9QpY3AGx2WZ-hhkf@SgNDqoRq0Oi- zT1exf(J(BAZI%P~uKc0&A5HqE8wZ!NU65^Q&0!!~sM5_DimJWGhT!@PCFe-hG-K4w zcXooL99W2kV78!*-|JdK%p3DP((GGJJ(k|UH*{m(ftno_-{%*)XK4LUNhdBS0IvXZ z*uj;G9Py}znN7zwzN*C#dSpr=T|t6Prt8W718+c(zk(uf-Ew>9VqA4}AGDsS2-u72 z*@@(6AJi4jK(})+ql)HGvh#h(wsq~BW_H$$^-6!`ihEV(qr+GGlT|YqAV(q8iCaN> zhOo-&B+=xx6Dlbc`hX(n3xA%B7RcwN^PzvK3+AIsq?3-6h%44=I2jd8RL(jLoEB3! z?pqaw8uOn+3+q6&UGWWQ?#bjhUwj7JHxBDMYu7R4D+|=o^~LZtp>{)Ak#B!2 z$@El2uM@R{EB^mX_mR$>;D|R$KKbTD63Qw%c{e8qmQ{{oTo#&AQ?3&^P8!`$PG{Gj zXj6JPM%USQS9+HFf_`*{BA>s~ZO!^1?85`R9smR|`brz$7=5UX&$al@`SIPe==)lH z?}v3K@sqLc6#6&hfMXwk)Zxv*hUb6Y2Yh(meIPdL0ZzqdI!JsD!{=~Ff?P;}JZH$$ z5aM*c4xcp8)igE!&KlkXvISHFSU9B72nS$=*#fQxNWr(H;ah>l7S(IgwuD2AiKjnCPL;T*)U5HT!9 z4Cf(+haraZ5yQg~!$k;p1Y)=tF+3&)JB4_i6~<0H1PaFhK3=pycl?`1Xl#Y_t&mYD zCicY=&fVh%_>$iGHbLe#=vjZ9?*KJHul3+*g{;zM@TB){f|c8k zO)!eOuS;T$ZEvpQ_{_|0g3%4|F8=I~07ZG7u5t{nGOx2$7UyI2K1KPoL|kxWi86kP zxO#-kDMC(I54~a+ii^jV+#&}cZ##@_!2QU>^%l`{Tq8`t%JB`5OvM8lArFg#oZ^9v z&~FPAtcP^0oUk5}Tj75ooN(eJ)HtcJZC{5R8^D!*a0_xHL$RZ&n_$X%tec9fX@O}C zkeWWd1!hnS{WQbOm^BvBFJd=qk=^rxJd>Y`FKsB1 zmdVefCM?>OCO_Zg7nuA))C_G%BjErL9o23atp^xp!|tY+^ZTTv^k_rsavKuKo|2J< zLVQs~lqZ9Ult+cy0<+h{T$_6jebU}beA@{3zX>oxx@l7yc@$8&9ERc^K9ph2HXaRH^IW<#AeTLH~S)Iq9b&Ne43~Q zN*kbeD=c=Jjx3P$LMnzDk0P)}H=PSL9u zWru#3Ho$){F;2;GMy5faWjBDwBQp)`tNR%Uzs^9t@mVJ7^y?jEL6GGIMho~FU_WQN z?NHGG8Ld!>%D`hZ!?FUi5wdmJAoZZj-CM!$v>#VshDXEMmeY{So1iL;JXId{4|MdH zF^x7MTcO$^Q%x+HqSE^SjKJsH&>h}|{_q~;quhVZfe(;%KZj%B3zX-tPQH)4wlY1%VaLrlXYkPSZ~&!4P^t^c$Uoy z*got~HjovuL2NM_%qrQw>^OX{Wy4uL%Vnpt5$qf`l3l^}W4EyVSrhhpj2+0{!k(YA z3G9D2b`VczQ~3ZkjSpkC;hhfdT`+$SoM`g@p-qR`bRR)YWyi$!UUM3xpaVzZL48U0Z({6|h!VZCnQy{+QRp0kPbudDUau-Oka~Bm(Caxb&-w8t8eR-D1O??{vQ)wtIgI zT(};RTHvAv7>jd`YK8wfU>C;@)(V$6)t44%pUabE_r`wt*l$=XT!!?yJigBrSaoGQ z{8f>88k_;w$M?C~slFz*U+mgrprexbDY}@z4uu}95Ku;76k4{qY%VNh^Whk_5X#vi zsA5Mz2rb=O=7lraQn-kf!_~|OH?e<8w03^9X2(G*tA?jo4N7J$yvVrlGT)`y+Ra@bjHG&_$?W*4ye>_WDLUBvwCVz!!H%1&dKVe6GxYG51KdUh+j zp0%)z>iJfAi3@vMJ^PiOb@ zV)hU}l0D3QY@3$Y9B^B^pd@o-&pmL6$uBec<$IyXkAC~Wg~Kr z4nQ<#-Dj(Ck9i+#M9;2!Cdq%480X4#5mTcV`IJXxx@_N3+mEDZnLN(|OM71#o+NEe zBJP({Yc;_QF}1`D%L|gjYCgFMZbXNFUQGF>0(UFiTQH|$5I zcv3vw&`)fFTM^US3c5x5QuXbPVNd>gtiZ|dSm#1hH8!HcKGtgO-57rZtrz8rsnDxR za`1O;hdVp2Dk;8JjPhva#H>3CO4YZovv8RwI{HtuM!uu@?phB6x4_+DKmH!{<881__=etm6Ksx3;folk z0{Vq6_5@fAeR=j2WU+r|p)Y$5_F*r;5cVSEv6o;Bdle?K*I*`l6Xu`~xq!V3N3##W zi@sz9`jSERDV)wegG<@xa2xvq9${a>lk6LKlYI-Hqo4T;`k8;TU(iBQe$Ls+C|{Rz#ctpRyPKQr0iML3<`#eZh<9VZ@D#R_r*ey@ z@hq-*f1b(r<-PbgEFI2!Yl+(cDSIHx4c??w~W1}h-7vw`eCO!s$&AXhg7T%AEv*v;r4ZL{T^ z??5@nAea5fFeHC&g)O*c_ZDJ2wH06PYl5al_}+}~EzbM>rJ@-gh!kYB&`N~|BLxvH zJVY%IM+zcZc%)Qf)3!)S#FVyEuSX*V;S?MkF;H{f&_(Xi1dlm-saTAY=uBo(XotF_ zErt;vr+_jObxfumRU#jXaRwh}YUPuw;g7Qcw!s!hfltHu=EkVFhgXvw#m@F+W(R+J>W_aV=_Es@S_XX6?`7+A~qlJl9_S z9)^+l+7Evu&jvRi1X+AA491vi6dwwc_%N8mhri7sa1!J)b`F?OU9|gDa z{b3Uy3)}dC@HC$Q&+&=y7M}!v@X4@)Pk~*08ZzE=)}PO0L-{OrAU_1X$wS#;d=6X4 z3t1_j%Z}mmnU|L^A78+hA$$!lWkIxGEBR6EM1FrXJDV?I*YI-oAlkD>xt~43tJw=2 zH3472e&8W3Z)3n}Lq%d}e!oWlL6!&Di*6!gdtosO2Fb?`NI|jkWbBJv-wpZydcM&~ zmR*2SVBqf|{nmq(n@4=Mnb-?m$>%A45iRgSnE7;_@+j%l4bSz+ezKfcFxR8(wF;~gR`{R=K5T-I7E#5= zRPjkn#ivy9nN#7I4rh?hok6~6KggHu2l=X#K{Wb9Vp04WQT!&1ViSDp0ODdW{`<~Z z-1qU$^bbz;kGA7tJHajRQv;O74*fF@{R?Hw>@j~Oq<-_5TjBQ@EdQX2KVvHXqKbbV z?a_XtfxQr>rx~5Z9y|SShbTL#Z!A%EQAI3Kc2h+=qI4K;k2Bof_QSQc8!m&vKaSVJ zSOY9;WxTYRi2|3-_wgnsbywwaZDmI6U?$bLVr!D9#)_>;rW!Xgwrm6vH{H?*n_5^m zJyi-$l^UI@dvvO_4pXIfm@1>gR6Tz>Of|!%QU=Sk$&|r*wxd%9>(zl!S+RuDZ202; z|Ms($d62xlqvY)qWzev4F!P&OUmc7kqn0s;H#2nJf1*~_zX7(!G6$9qZ)F2;$n1!i zuzj2%H97+k9X2Qy!NF9sZ*0vFsu>#Dp82gT2S*$h9dUT^{-yKB++aAryen4jjB5JRPiq(`B;L zWlCI^m@%h10Mpt5=+Q20H`;%62Y5y-a4VbXRL_d7j#x$X5iY{#!QJ^jzoD+I3-XzPW+PZutJj!5E{2#a4WlKEZ2%^wln_$wlXelCoC5*6P*iJ}lgC$+T-I>5xcgBvj6Q=Bfmy<=e zy3WjCKP`K?VzgX?Ifuyc}-+fTDg;nUYTvpkr4bL)KUMutCjK{^e zxNLdUHdRHIR^0&4+oK)xBs|);0UmB;HP|x{URo2YwNFZI7gyZ}8_~mLE5h4IPlOwFRn`9bekYPM{-U zc49L-DdOz1lj(5^dc*A0CUzPXPH%+d0+qqeXo-xT!Op~ik&a0j?5sw>Z9SV-CvB67 zA#ZmY&S-n<9UGBv32|&{t$oI`F)R_FHF?RS!|vD9m~$QZ5W#m3s4|$h3?`u=pk;0 zEO8GE6q{g(*bH>HU<|sJ2jHeo7Z2iwJ`8^g#5PzgwnMpi0#=A8;Uw`itP{_|CE|Iw zQoID$i#I=m>}g4e~n@QHX2eit9YPVo_A;!~!?=PXHl$I`_2the}) z4HiE!v;b_R_=8Oof3iZcgDnz&v!ldr=99pxBxh@+U}s9n8l=f?lS%Axnap03ZuWnx z?8g37Ob&i2Y4JYDwWy<{)mS7!0?vM--1`|$;`KR;Ry;7esTKTht$19C90lLL83 z4&rO&5PpNq;kU?P{2rOhAC`H1o6P5L%l-I!as>ZCj^uyHQGACS&G*Xvg(=60OgTYh z$?>AMJV1=b_p$Oov`PhHuAHd#`X_(T$DN$Eo7Cc#J>WO_y-c6eZWV199Sf~v0d_-w zli$|{wGpj*pUIm{-YmgMfTeb5i6+P9f{JMam}>Htoxn17!(i0YYfXN?xzOYfv;mI= z+(63y0j=zZ>1;!|p2on}`;Rht>rU|SHW=`a?RI?sApU(QoQOlVGVy-^Z##cHUKmbv zIlqpYNZ-mXvTr@)dgNC2KlCEA@>}6pCqmuIE^cO*P+EfCFD;ObZExyy*cNt~lS0bJ zS38ZwE^lI2=yX`qBAr5dj}@p~JB!P%EKrS*Szw?ZBTaCXhu)f4Lnq3sm8~yrue=m0 zuV!}jec{yEA)A50$#5=Qz*c`csgZ?{2_UC~OU{Ju@({?9hr(bv2ZqT)7%huomYfHN z$r4y17r;vVJwYyllVvHKE02K-DY z)0=N+g&qbNm_*6coiMZwx;q)8XftsK?o&$|V)#hpUeRwLb#mx*c~F0!1~^$9EezScPF|3u{ zQW~wa?O9$fqx#2ux2q5 zfLQZkO@Igfg#cG}L4XswAV4|tr(vJ{YhZn4sO$#VCtB8b0rVh|y8y4zT>zxrtsQ80 zTWt2mp(~*C6>yUP5K&d1Al9y_F4g^;mJ@>*SlRw7Tu$`d(hT#rv z9}m;k*ol-)Cow?jiUgmVW%Pa+61gxpOyr_GhscNKg^5gb50iLQE4#f^-!;k))1;Z* z5qppvH%nvNy%B%U=*1Xkr#N5VyJ*eV2W(sAIGL|+YgqaEvPKRD5|VUEzI|6CpR~!y zCUz%oChm{as^s%b*#K+uo7i39 zR)3Ig1F(mjX&;V@_gU+D$VLzyYCqzDY>Q6`{6uGVY&#muJ7mt=U{ z8Ssht*!@Wy>M8rkl+H4!>S+h^8T(X`P7A5}S*Q9r`%sk5Lp6(Ku;-Dz;&|;Jxw$#Q z&2-ut<>!BE#JE(ayp7%1#9k=qF2<#0rg^$+TQzw;78qZC3Hh!Op_a+ue=U5-1RV0ZiEBn4KPFA2uI1AphDgZLD`6A z_HH;u-h-NM6Rek;;aa%`?vVGQdEJUy?ml=5<>py@e_6J|8}dPTPd)^{$cJH%e1vtE z+gN`;xt-<7N7)?t3@ee(vZLgS%r9SJLHRm6LB4@L=)3Gv`5wDge#~x>pRi5xOLo8f ziajR3XV1tV*qic4_Obk#{UCo~f63q29{C5i{rIh_Ki{GT@ki8P{)`&JUsXf-M=Fnh ztMd8pY6Rb-MhchOPh_f5B1?@HL)HFbj2a_~)mU+u8YdQDd9f-GOVk8$vYIHaRFlL; zb+EWwO%&Y z_g4$$0jg9^P>bY5b%dOzj@FjrXXvp9hJ>wfA>RXI!gs2&wDDNm26s4T$pmBaCrtjN z$uBqgQzn1f`?42S4|3MkJ-1;{rb+{FS_@QS}$L3 zl~tUj!rxO`nRANBevE%zn!eT+%hNw0 z1N|I(S5V)Di_K>J(g6Kh*{{xMzs0h0Be?^=J1u{7e$jLi2Ed?h#ns-1tKEdF-HiNk zFN{!Iam7t=Fh*#HsQaNHWGsV z33Eqcx7uM5OK)X=I;emA6}!S6PUYXxRkpC5NbXj)3m3mT);-(f!0rvNC6fPZ!w9kw z*0*vfZRRY7KAda+Unc?M#GDI+lyOcSSN8baupvoFaMP)C#ruC928^P~lW=4!9^5{t z5zXwNC~nbBSPA`b6Q06Ncp5k1IoL-%55v{Vu%CJz4p46(%e{Yv8}K%G)jP;;AE2Oq zh#T-R9Irlwb?P&?P<;tks;^)ps{gw&P`gjH!J|m@=M4#O7z#czT=2EwhF^?su*=9` zE~5uaGcxt&^#HL4%1!>R$=}-z2bui+ov2bc{qyP04!%bps^IT&djrSI3I>UU2VthWQ!2f>EvG-)pl(AU0<6Hb=4@_r6r|DwDW zJ^-<`7oXh-eTpLs*(d%B8$PfU0h{?CjEwl;25{lezKefI!~Dr4Gb0&|gC0hI$TbGQSR)$_GzP-K#=dZbF%*t5hC{iL3qfN9oNSDQ3yo2*-WUzH8Dn6( zF&17n4uEfs1L03&5|hRhW*P_M)=p*vjOlE+F@udWX6Y^N4avLVV77nn-n~*hyCK=+ zAI>v*ORs;Oq_gNB%XfmzTr{m1@`|@uAuHO#hs1syKtcL;nA-q{>pYQj0e?pBlVIjQ z1rt3|M|a!#&;}Up6sTLF^G))9*2z%A1Rvoe&i*X81J#u zH4|sVFfk?l&yC^Yj2JGawwf3=&WK@SYMb8$A7{kyF~JQ_h>;6ilD@*qqm5(V<%nMbFT|Wj@cnW9J*_4_rd^1^N6P4;BhX_tbPFFx#|nJBb2iQo z&~$&H5S%`+$VCViY=&i2(C@iezPIw)(LodhI!Y+gYX*Huw>O=TC%&4oH&4aS1!yxQtzI zT+TKbSFvY}2KJV*fqiCN$9^=fXFGq4jck{36Yps>^5MpE(5#2Lm1;v(Z?vBCIEY&3s95jPs2 zidN%G@r1EKJZF3-UNpWDFB{*AH;wPL5`Gc-wL!L%OFk!hAr~NRe~gfLPEyitn8WtK zBAsOZxKE#6sUH1l%!iaI+zr{X4O$?reSaGop_qMeu~mOPb3R5{`f6jg1GW=Jw4s~Z z?O(eC3|NcC!Lx%7v{h&LPIZ5xvQPM@j)y>B87AQx-^(S5D$3gi$2Rd<#ku;%y5ppg zARf{{pIJGKJKHv%s4ET)>)HNcP%;60j{YR`9JDt~C)q?3FC>lQWP?W2+x0r}OE;3X z!Pq8FrYh5(JzuLz%i}6Aw4r%6Q_1TfH!^*3Wcs;u=@pICa~XVI6cc|+IgX=Q(LV6Q zVw|;N$UtHF4GiOVNHP9ELD>O=jK5*Bu?vcgJ+Q#oi-OVyi!n}JV=}nJ6St4uiO%BR*)CYPIVJT7-8TN1j)6v zO$J}k!Viy*def6|c1(#*Uz_;C1~>pm;ftGvFsRg94j}+ zvr2O!3!0PIN^^e-JIkD=`DO&TGxxxBn{o7aspss5@%S8&xf2Gb?ji9<`QE-0`tO94 z?ug~*VJ?DKP-rR4J~P5a<2!PZBgy|N!tFSxJ=b`<;u;N&0yZZ~!y%+f%$Z2TSxCb} zV30W*Mwy2~u~~$4EQXLd56&X{%e#uc&BfnR{fWQatQSN{ z<#^1N#$r~6nB_+NP0A2=0a%WJQH%$YG@1)gS1tt8JOY*MV#NMP7-=32lgwk_2-B;v zRUpivIoRn-{*{B}7H1Qd;Lv5p^>BnH2z_gg3~c3T{+*sn9yFTti7nhmp+!abMt{!? zUfBYZGx&cpeCD=rKmN4B*iyY#1UwG;xS22Cl)EYZqPbZKE^`^An11MM9*1nR9LAYd z82nYEa<75e<_b94v@gx4f!K{e#8-JH|N3uKevE&^zjg4x2C=7vhI4#-ZS**rSC!^A z^J@CgB2x|zfBN4)k3Rnq^o@be$MYI}sw`1Kzu$k#1Esln&Ac{>ZGTGknX3`oHPGE$ z3m)@$$T3eqnK~Y(nI~xsJ(PFp>tvg**8KjR{%(5+;`lxP!NGLA^ABC1^SlC`#=4?B zbmfDKa-EOnWB#!V^E90AbfnHYNH@;_7ymJmzZt9l@6aWYa z2mrK*IZc;9$^ja;I70|^0tB>(IZc=G(F7WoyJ83nw?ruj))@q}h&fG{ARYr6mw3kr zDt{1Q2rbM^LX!xgNNtq^b#1q)br?Y*pP zS>58gx~>WVzH{z-(~=3W<@@_1_r2TBJ@@o;?;Bq_`P-)eV4%3u2Hn{Q8vD=&oPA)0 zPV6I%eQX2OsC+`jr&RobiqEL{BNd-h@qYysUsCZE6@Q}QYbw5>;?Gq4MPq-pK_)Hn zHygBP-&(QwJHh`>WB;Hd2*{kH+29=b^%DgIPR}VCPfOSL6Mt zxjz*Hs2E7aIaWT17ij!k8!Y65sedwrMi)}wP%Ma`o%k?~54S;peW3FZ_~hqNF_MZ= z)ID0`V>CY2#>esTHdsLjF6Vg~pJ0P}_JIxN@rkt8NgAJQMTF0%qKHU^7x z-^_2(_^)(+tIivAzMasyP3O1U_#ONf!gU8p1}f$n_M^^s>ijO9@6!3*s7CxA8|)NTbg0)A{{6e}K0Apw4&e{5Lv(Naqjh{1Kx3qklSoOy`g5e2>oe z5?6*&A?2;f%J=d8I)8$mzqRoL{7Gs)sPm_2frEtm(?qO8IzLRSJ)`qyb^e^rpV#>j z8gi7_@dCX`fU^3c&R^2`%Q}BW=dbGgcRK&Q&R^5{>pFkK#^2;`5!knB&JHS;==>d> zzpL~2bpF21QC>gP`F}?`|5)dr==@Wi|3T-U>HLp6|6J!^==@8X{*})Er1P(J{*BK6 ztn%7^imL)GB`{6sTDoEMFX0>8}Yg$SPXuTj}dt z9|~0U9aUH7TQk7gmhrD%Ugr-IihW0w&M3y^hK@iW zdWA3KUtC+ahJQgu42+4s;F2l6(*gLQQ}Gy)m7Bi*M$6aD8G{!*v;Y9v@ZtJ6Rmk#(wv!a?P8ZGkMJckt~n~a3B~mE zC`5@e33s;GUnkeKFRZPt!u^)hlR@FX%dgQm&F`y`u#&>C0yQMPm4P~cMTqJ_U#PXd zmHJ6`dw;iXO|T$A&*eOg{0LYCw7tlZX%O(G!4r6FI%GTgp7*MbJdS4A9&oiTOc zQrzOuK65a9!C!s@}kf{AX@(pRY+!#{>#~VJeTW)Ll zZ|N12Vy3mR7u2&PRJ{OMzl_@fPIWsGg!Yc7z%{yLw?M)(OQSrEcaI|@mDNEWi~=q!-Yqx zVG4Ap#yF+6ro>-aU*R_mZ;^kcA4hho#_d%3%NP1_F@L#{V+GdwDB59=U0-AN`xYT( zTXtK+bwp^3CYU6~6uA~cHYpgW?SDJEe$gU-oxifIE)bIY!Oe_YUEyCYV=7H>bY{zu zgrR9vl!mI20qL?~R8>`sM{O4cX@ZjRg|pSr@m0Ri+CWVOgU+q_IJ!PiRVnA9E9%TS{d|87!7j36|u2)HinAvY=WIl zq@tLrrEG>BGdO&kN5wQMrc*JKiZUuLpke{@p+rP+9~I67$JN!7QGwh)+j2UuY-hEigIze;R=emZ zI@v`wk#rGTY!{tH7k^E3jYHSqxm~zKH(D+SqusMQ8Nuv3fi&4gcQ%>e^q`_=nD?<~ z40h3r)!0REq$1lwZ@KJkyXZqy%otZvGPR`8HLiMjXpPG_@z8|ZE?1})7;V|b1Tm3{Nd}$S)$AGu zIc?Gj`4~<|JAWn|RDuinH8I&P&KE^!-%f|U0cm`FRTbesg=Dd~Eg8qfm-_-ptEp^= zT}-25I>}FoDAmLayO_zg+1YjM2D_NWF2QUvArK?_3U45>G$2Vs*o|yKoXXJDBv!ea zO6tFW0kbhc9i1)akXT>Iz#@;YT@2JkftpHu3Rj`aE`R2V_I5Fk^l*Nh3ZYf(G0spd z)qL6~)!_PLs_2j_NP>YgFGMvJ<;28*k~D%ny^pn=Y9TN6qQJr0`*u}Ca# zOPIs7Nj5cdd~H4Mfdpg;iiK;{65JUMM`b}tGBwqO%eaElY`X01J`rFruI0!@KGnm z*#5X-C>_YV5ZU2+0+6{>Zap?%Pg;>3Q#D(qqdS(}IOjXlW@qU230nN&Put|l%ahHY$13#2{thdIsW z;vb46^V-FwVk`qb-=>Mn>|&E)$}Y#4pd7)Dn=q~fMYMeM)TyY~`K7hh{?HO)2_ro5S z-0m?`i_w9OLUc>rZfaVUhXO;OqQ8I3~sIo;9ju(x}lz zh5yQSb}I1<|u?Q&M6<+vWzw#TH*`27OugqP>tr{P~_GUziSb# znA^uy5y@d)3;k8KtMYLP-R!j4#g*bJONM|U0g5FnBB;pW`Cd+ zlEAyx+1WGfSvz}5+{EBKLo=mI#@?|0g{0(5tSWppMC65jmk~ab2!*p0GDuscDxhtm zqk2~lM9O8ZgOpiM4N7I88V7D8JA1RZ#V&p&ZpC5qjd8dQ>-^{xZLZ6-cl!KDqq5$0 z5m`dQ5Uc24fqSu`Qx8|>(*gK`Y_v#0^kQHf z7S29H5hEMP9StkQRqTa@(aZriHPnTHNfM1%*U#I3Jq@vjXS>WE$wKNGfurLB5?3%# zU0+29y@p^%m`%%-`&ZgxSo$=E*m2*A|>@fJe}TZL9clF)jNnBgd?<$r;iTq2ev zA`Z5*m)OgMFKxSzYdFrZg>ffPxvoN~bmf5{-MQ4&(!oL{HDW`hA6etCEH{=*M(|{A zX{AExp9q@fswc@HbO@eGnGn&rk2lAagSO!|3K8bB3tNTtrGAY5Zf8r8fa`2Ir0zL| zt{gjioxOpubG!&FDaRloc7MzzwX>ldFpM}EN!^9>dgSK2``|0@(O(mH*u@Ug`gUR4 zS{gp#ka@c!y7(kiYhQ?B{w{Olk{MscG7SDI{Nt+RW!ccM@kL;hrbdh}gBgi#e9mwP zeTHs%=~UxijTxCh!DBEu!5vY8Tcg%Z$dOR3jIZT^{MD(L3Yvdq5*1s*pS zhnaDKnH<-EQx;R%D}NEdL?}CQi{ipUW7$9@2Jz0=t}(S$RTK`@8YevNHqS*9T*v7F z^Ro<8$_gXW4W92u5lcZ_Cz*~?BCiAkYe_1iL>yCHIljub7`dp)Bf2V7Axo9NW^rf< z9X!%eC@n4}Vp76G40|AGhW>I1TeWXlBn~OaO^EcIGqO>qOMjsynA6Z5(xfvEw*`VF z{wnjhwA-1kSY{b#Ei;4uQHvMX$xIJ+7%Zmob?MJBVjhwF`Y!<%aJ^zH~nA4Kgh&Pq{>pZuz>LiBhypOMhZx7>C@K;T{q`@2rlo!Y6ZdMw&oCqTSsSC))A?KT2hV#0NcJZd-SB z@e>fPw=J`i_#PoM9?OWLsu;yl0RdRQJ@NO?AdBT%qK#0XllrP zDVj5X{EpikhN5W12=x__JK>C$HzvqFOkNV}678w(On;YB39rEZt6Ota4)Y{w6kW6o zKD&FIgomJY{_5J5e)Gmymo8UYlH@qUNq0UG1xyMA$IGNq4x|ftBlSCti!jd`%zJ9o z{ju`y2I(B6^xhwm7E_?hK!1DImqrFwrlrcsJ;P@XM7F#$c#f88<7zG5vHDLI$6`rB)*>2zUDu|FCK!ggfR4H4bzeJU(U#2_F|NhzLi#!u5_>3;4J|>UEU6`O zX(;B4jZ1wi&D%rz6f*IhOAGHm zW{Iz^ln&r)D*RzdiQdei^w&z-1V{i<;(MiYHe)xbDJp&Y5Osf2X$%d>CWG6y6lNys zCg&efJ!zwQw55I1Q1zlt$aSVMm^S$PQ!${eBgxT$nyF|LtmH1t_nLqEQ=0$sTZz=@ z4S(S@UmdYH|KGW}B1UMde04Q4zDf#5Jkkkk7|m9)HVMv-&k z&g;z(jpDdDv78Kl-xs;eCUF}@hBzGE;67u7kNToj*K!J_i)1caf>Vwb?Ize|} z>|Drzj%+X+g71X@z}ZmPNLMEEo8j}=NPjFx$@bCsHinIj)W_l5cs4YLg72l@C^)tG0iquOGa4DN1;m?d|pM`H_E$SD<)Mo>IiWsfW#rnJ! zbxfoq_42e1bgPB$!?0~3tH81nYo7sq?+0+Ldmk|O0pPRuf!GTQzN+|Y*$Z0qReyK0 zyCsn5^flvANe(}jqah8;>7YOfq(UilgjvuN z%D@d5Kwp>xg)kS+g9~9Yl*3H$!2(za%b*fgf*&@*BDe+?M6rTuJAHe>ss!yMc!Zn_b=8jUoO+KcHWZ!b9A zc|?vqpnIsL2|AWNDk)Cr=iqVxOF=`VvY`qFLJe-I7SUY}Q=ty#L69xM5h{r6tWJny zfGssJ<->tvGq7cz!_a9vsA9M05OkV?YbZ^S?KK|zp|kA5s!k|0K^Ix44SyA5qqR`U zI|{l}IRcG&N9g4!b>}&8a#uN05}T6iB=Pr`aqOg$CrsWJ65tf$4) z?O3t25w0t{BYe9Bg$!U7@@+L(VJ)P<2IS=>&;u@m0k8?q zfz2=kwxH-;2@~Ne6wqr>IIl;3-hjfm6)uKta2MPRPa&j_;a2z~G{9d`_>RFH&lnB^Cd(;~xr9HLEd&{y7wRfzK^s7zxG{?-6jOw|}|Q z5~M)4CdgSZ3}2j68c%(bmUIxh&lc{mboJN|JxgaRBwD4j)lRZzAqJJsCO##V&L*)- zEuEc4t!enAX1g4hMt@!D__Pwy@kvUOQMw;`Md{oTELa{yQGW_){WK)OA#lQBwA;_g zz1o1E0FB`eow%1;w%pi}7=oiwv-p$)&r=A7KR0Cvc zLXd{|w}Md=3*!I`p;gmN07Ldb;Q<)hqG{MZ7`_ii6lz}C?9_|}9`O=K_e#A=Pq0uy zWTAYCYjG!EGpd4+1%18iePzz8Q5l}S2gmhjLj6_j2ARYBS z5)sQQPyhj5LJ@lzlHnD|g5N_Qcnt=@>o5-9K$U+Bis5Zk`FGIgyo<*D162MGVK;mP z55p%Y%%7sl{{c?HXN;##U&o?il1YgNh1~-3-aHKByV8!!JflNi$^1 zmtoNzNcqHEHGd?mCl z#EVGfHdNx>nuLhwT6x1Y`9U{Wd>z=q{^Mr@a)5p(i$IgIA&@jM+4<2rBkKBZCaXCe zeyuUK6YP}8<}Prag@SY~TRm4-en4Otep{LLjHf;Mq7%BVJrhi^SZWaPtHfeG>Y`(_ zIVBl#2c5?#a*~zpA{4w<*0sW!MYEh-(>A%K0+KaWsho?PL(n5`{{{66#&ID&y$FI3;*b=T3bD{|OIJvoCib)Ld&l4i=eBr9w=L|77&!K|p zFt|qQPEHI}Rm7P<*5ctbWTHzLeJw;P;~ry(sZi}|M7{opgmFJ(cu~t~2x8;8Q2aB# zThs3+VO)Uay4M{f+-cvaQyx?E7Gzlcf2SB(@1WpGCHI*Tw2+mBL zDFl5;jsrifL8U^%R&C0n$Z1yi{cVq?S*DGcn5v&EgqdnV7E<}^zNV0)kB`hWRv@=3OO-nx3S@eR%89+AO)4`TBLJ}Nto z8G%KD7m_@l{oc|{=QT&Ydz1YpGQKYm#_VX?bpds3L4==@u&`^V^-98IUWFa5+Dr4d zMcbsrq1@HnHfXA((YpT~XTWZCGJt5_&{+;YwXj-A8D?3Iy$%}VI%vQv6U!@wxMT!= zeyMU?r*K4mH7=o_32(P&QJdZx?2;mtJc!=BLEmDe1d*Jxs#q<6I0eYGZH1SRdeGH zfW(N&(@6HYv$s*j*u8Z+$L`%}yjUYYY-!PzMzy_Abu4zzLb1|a7TPn)!qdD&|Jrp% z;&vcCu57Q#E<%;H;Q7pJiS#Gjvk3wSL?1BGf-yOJ4CsMbTOPw?1D%8P&yxPnV@>QzOvOD90#Ao;NMe zC@Or9nMD75M-wG+IR3EJ4K>yr!T_7QmcuYiH};0@)rPOw1y4*7+_J+6f(-ddM|MH0 z(zT7aA0_WRP>&f?Er1~4_?yQXwXXkLRG;&66LP>0DXEaK85XfpQchDw+@s2x1I`1X zpD!xu2Q`A$3d+Rkz+hZJF#gEeqqx`uy6b0MmUXlh1SCmjGDSo8!0>~BE6b4u26CEe zf|_a60#%HZ2Rx1)nAF%MfK8;qeg2~r~t!QUpvDg;9=sc*rB%Q z=JmSZ$sG}OFIP&aJ9d>YTXvl zbnZc(-pdkoZwK)8^sYu-L<>z?Ctjh)^bgdE9vqRbe~2BxqOCBV1GIzi{^BIQNiej{ z=sAEUK`n$}8l9=grmR23c%fYy4pB0&8d@s3N}^2Yk0E;i0NLeiyNH*&05RmoM(eo)aZF%6 zKlnL;?;|H_%G$!U1Hoz%h1xP@g%8O!w!qtUb!@Vi1;xkPxCEY;9MUB%@|=|9HJ9`- z6(HL=DC(%_)h38P3@s5wmIsGh_Cw`CA9{Y=Eu@bHu7+)gxo-)P=Ho!yPp0r2j9HAO zQM9uF0*_DiiE=$g(s)TYE=&*C;L$NgMjDC967 zr+|C6BN$^}7ITR$J=A$)Qbn{`lS6#$KLXzJl2@BEtDan-c)UrN_91fNCyxFdG|PwS zeJ?N{-(?K-yI(2~@zBdKWAH;5`xX(?L{EJH069qFA6Fs`sidGZ*b1r|gqlE_>SBMv zIFHKdMY(AWQB$r|SpACUP$h(HPWQ3L^B8mYj$9-(p~iC?#IU@_tmBvf%@%g^hm#sh z>l1kl3lf)80GM;6bp9tP^^?ZrNM3-w1W(O`T_xBfeYC0%h{K7J1bjwYY~d+AJX1;@ zppRxbmq&+@X4Rn!pH2pt0=A7q$a02#m|`tX`;~&bL}WBoBZd~2sfecD zOofll9W&?l#X_e~AM#Ts(xPX%JgN|HRr*0X8m>;69~+NEfBtwkx^V%N_6z@mzRQdlCr39GT;?6kzkgcrbbyE|p(3&|J5z zWBbdeqL_SVxBx8s#lzWmu;()&0LN#pnua_3h?>}}BNXRwrMYp?sF;dlUnsuUPPouU z7!@z}r~dNnx_}>E_&SM1Idh^^3D0|{w8qee@Xx;RdegrKQ+@H1-bvcC>m&=efDj*L zm8duemHnx^Cm4h0-Y8xJ4G}0`(cxY#EcP`U)%?*fr|T?w-q`Jk`qERPo(!BB!7 zt?s;Iyw-v59a4PTHE&%gx_R7=Yv?40{$BHk$>3^ssNj&`aCY35tAEVtVicl%T4ZNv zT$}R9T!kR|TfZ6i*6OTHG@t9v;)7wVhki97uPl;8$8@8)-Fh(R`7$kIqM^oP-bL?l zBHzTp;l!vO*q5>06M*W;EkW!nm~uy%fPRMZnmis?Zp5l=<@xczN!HaFyuu~R4}1vU7vlzrb9`@=^6?j> zC*Bxn@T^?VLg;~!b)<{@?`zZZJ(9SRDpRc!exR$jQbYr04j?w;4W~|{t~;byffBx7 zJ}bBO4&DrvEiE&Xebix}Ot;mT%a^cscNd6yVFQ$YHu|+|@90)o@vi{NEojPdJd?&J z7{$Hf!lW<6@#l|b7DJH)066A--9F7<_^MxqWX38?I`$Blxu&g4jl6p|gc0+5l#d`6 zFJH7cVyg=}b%5jx=zRW+Q+|lZq72@_BRNyz<0WIkh3xWZDb zBxG`gP603ugEiX}86_etT19GSVVeLZyv#;5*1C?Bd!s}w21l#MxPEglEJfWLFrPdx zfd(}S><5$C_A4yW6NI6Be5MuaZtB#;t@%o^M~S`}4?t~JsQ^S5<8CXc%Tac3$WBe% zE}HQm)_IfNf!t0vN8Uz4%`Pa$Rs6)j@mp&@mY$UrmTNsUZAk>#8O;@w5SeJ9RNxy4 zIz}`b6bxiFGPYBu6{IE!OiE`p;gxnnAgOcx=a8C61>oo4o#0wJ|(E0_p%LU=nB&ie@syZU=96tc5&*1VBO6y6r<%k25LqAAb?JOS8B&@InRN z0^AiIY|~>~R}z_a(z5i{Eou-y&7e%!LDt+F3m#79=8PK{JWk&b0P%Ej2UW7;EMXFOhiMhsRw}a6XTY71IZxsWx~%lF9N9wCDe!zcWKfW z(k^NUS1df`ICu$Xe}Njg77TvGGCQaxG>^}${G(|>;o~(-bll1{xq}#vBP42v7>=sW zVgWjj=;7)^WuB_QZ-?N16KpxX{Md8ni9=35hE37EnY0Uh^vt4mVROcicDSk;pa}rm z$3qT!9Fd_yx7`P6Ksbqv?q^&b5;p<0L%|*TbSLRUUyj3*Kd)^VJ7>c3=!N`x3GV#J+ zNosK_5qua*T?V{qi}XA~I#0?sW(QyfiH2r=_lnQ1KSL{uTeROg0BPr zismIx+z37fE1AS9tildEhz7?GKZzsNK;5*An$%#UDWMR>(~T-NBt4plM+Q&@ipZGX zhQRTpd3MNIs4|kG7wyh=qi?GVm-5_kUc$bT1XWQfL2q)x+tC}_F|VsKUu2R#tZ5iVZBT8Bmfv-O77F&gLKmx z1St+r-DP@;tMt;IQBup3Og2fWt#^4a!s@7)fuQ_py9$tgXP5GxjOqPhm)OzNlJJ0C z?hPj3TqWicOCa`fnuCM#^?B_iR0ZcOOv-SUvMR-JMuGXn(O%F}P`e6&i4w<4%V1U0 zUVyDv&t)L=rWpxua|o!s$xKVL^Msdwy{u?-6l(ND#XF!^TlY|^-xXi_Lr``3;Z*nv zloo}^O!Wpu+8nwr9Sc;lQYJ|2}xB4(eun z98r;%h2@I$B38Q>TEN|xWK)Mknm=EH7;F1?KRdw~;Q^69hQVw6!a$MG-12dZJ`;GX zK^cLzlc29d#uES&P7ryiZT5<_TqVJbbg8Ts}$O>0AqO^WuzW8$U#H1S){dwf989u=?Zv(YUQMszA7-WoTH|`sz@5` zRbO0>j|yg|#nz*`ZkL}pn2_<=kv^vq@4;NlKIc2xIAnSNt1gJ>)?}^jCv%Tt!@TsbunihvZg&4AdK{sgmi6zhB9mp|9sr>eQN8rh$AT4MOv`UT!R%8UWYMw$NQ~mEM76}n( zK=-(>e5A3#>S)355?QbWG{gEiWr#lu;LM{~VoIrpGF7n$_$H;$>X_|dc62WZI;cV_$pgW%fDte1ei%C2de?U?e_=ob?hsCa=DNr7* zobS)&%$9}pQ8l^&EgF1eJy<02CNX6a6rX7LX_Ou41ouBgq&{ySe4_zK*uQ1Jy_d11 zWudu&VR7J<4lvl%b?=zLJq;U@PPq#w!kQ1+*qyYn@@}ZkH%}uK-W1E;2+t0 zWH5@H+NE{MDSk@C$DHIW7CxD8h3qi*S|}S09wK4BqrQ}sFm{<7+$NaSNryf>Eppj` z2i9t&{&HfxNpj!}&AivMWQ)mUmPyN~rionq4TX7nH_kapI)zh+kDoPO$f5&UW?cZE z5=Saq*t?HBxK1Dv_>$+L_ffljbe3-_u`RSd!@m2)zJ8YOJZjAoMD4Jt#-vdZd5QFW zf>Q)sevulRuKEwjeYd3g85Hd^=T0W9F47GfI^$GX&zx0^aUE0;FMSHS_Er(j0<5WH zG3X-llpBs*q)QOg`9?X3pDqGiDI|b#m8ild7IX@#r2?%?gsBu1t=j1T+|*2`pDGYO zsjzziEVyx0KlVY*349Bu!~3W)2j^tCn`mIQS`SQnQe~QPqO~&{L+q76?7A9Lwrl82 zyHaUhGE`>rRBYBB*S;DXgL(?V)*)s1KcuxM(9O{mRWu%7CUJJaFZolV+cg0l8Hh?8 zcgBEoL2ks#HGs{Zt&RKFvsC;t@5cquK@ zbd7kANCmA5x9($o;D<|>8=(X6^{~t4n7p6tL%L(T7G5Fexx;IZ-U-8+w9H)6x>jHOBb0Cd$kmVYrPzhz@zzOB%0pzj{2AF3BnhY?HeW6=bpgYb|?MK zD2~nMD09*mPr50ccZBV@Q6`oR#Si5TExF|GqmItsp#6Btt|r1xA8!Dr8m!0wTE23} zLGB|4T}AJu>Cc(UO%z5a{76YRig;jwQ}u@| zPT3veI%aoWsT-m@rl$gE?t}$AFf3Eu4!|6XYL)teU{dD~l1~!u!5p)yb*?5S+uq!zDWwqVCAo zVi>juFIJ>b?qOUH>Rqg7N>FO_@5dMMlt!@M>Nvk%=nb=4(?4h`)o_pCn2WEPZRj>7 z`3~|J&9{cdLKR$A6MfY{U0ZWy5TY19ulk}|tfc`RV1uGtS5|+z!uC>|H7lUbx+cw@ zY-@vYThn@aT7mycw=(f9i~aCyL+Q``t^faGUlqMu=zhw(Lhwo4(zd+jzsIB(0ozo` zFlH>*W|0w4JLre!JHwP&D614^H71l^*tA13<;|R9-ax6OeZH99CP4He)@Me7TA6V= z;@(CHn5&HNqvQ46!_C{1X9~2dWEPE_^`zuG>=ctNKu4I<6N6CIF&58?)_$@xW|TySDFh%xF8x=h78ul z2LW9vWYWTi5M6mRD&avHttvK3;=z$wab{8k;3N9Gkh$w+U^Hy zDnz|SeQj)k$qI^PkfVcr5MylCUJ!>|J>QsI#hbcv_M}EjYvqI4?YA`fI@OS#cWK8m zAV%pgfv22*YlS3nr&TKhuv>Hs#j4!TOhmc(Jah{k-OauX2^K#JpdapBGP8-wjp+7c z!CIFJEf{5~N(uS5UZxzthdMEfC|G+|x*$ukhM+p%E^Tskt?=6TX2nEvp=NFbT+43> zrD>vyE0BjPp-lQU0rFLZwVId%k2XLC0Oj;S+zXahrJB(1FGo}vv|3R*V-i1wHLAnb z=&I*bH5+8y*f*K3Jok^el!~A*cI1Xr5R!%2qKUw z4nkqi8$>T$xLRjC#0^!LCdewE(;{cHjYOdAi(69+L$RU7d+S2jm9cjMXD*7K02uD? zHx9t=b*$yOG594kvUCVY5hEgxy+`7sdDB`mDR&}76uoIk<#btket?FJ zK>XP@P<(+uUvd*bx!ko^&~ zL=8Y^AolWT1A1a|ctftQiVp`~$Q`;Rwd-5^blP`3xz|hixXqXr2y&I@04&+DnNLDJ z(rULkBXYMWMP9(Hdlly%%i=C@N;I%&36k!X&Jn~gwoEVWb|emkk*cgu-}1<}uqU0Y zX?R`vvcYVCp?MGq8M9{CXetdO3$#RVz)0f0d+qU-hipjUq~4kcgEQX$k0-ZuPgeaG>w?u9n2avU;T z@fgHJq$COz8=g=|N>K8TjN-yXM?MbmZ@AaVz^tG91Rn^}=*}>EFp;7)5R(!tAU}s} zerQ!}-st`G7x5!(`vP|O65aYM+5RWq`6GYtMR4RA5VrY+*K#P^4iNf-n)1^y+i%1j8BDV^ z=MH~$$HX!FR~4-@If+)UmzXA6sg^sJ(*u@CC%;@sok?$KqF}x97j)-4Y1Spcc={f7 z6i={t<4;i7J{L|Hs@ch@;sM$A%Z?PULwRQYuRc&7AI=BzZ{IQ=8#4%38x!z-#RS4| zcV(9;exbR$xx^$%mMc$1_r5t=bC@|J+TZsu(a&GN|8N2sQZ)%}IDvqq-2X2puqA?9 zzO6wV%I-fpU>mU%lrPSIHt*lFIBf(m;6$MRjRpL_nSvGl& zO(6g0Qjjsh|n5v|1JNwkMIy^^d=v$#Q)7XiGt&# zf2V|RyI%m0hWs~g@;xu(e=Ghy2_iLM*rqGr6|nyB3Z?kQHCeR9)e_5Js!r&k;|J!mu94KqspbIEI_guu41Mk~uAt-;ad>=7(>sqDC^ zu^YZ!$8b>NN8*)F{I?s|79 zfzH`MJcEaKS~hj>%N+>ZcRY&f+=ScH9?ED>)7nK0`|ELJzCQRix4Sml@WXRk+IKxG z&i`taX>XM1rNXl@iWq%}M&i}JE^1SaPkiK>@8ZW{r6-PI?@aoVI$!XuWtC@I)UNWq z9RPjKxc!GZpW?`)dbiLBta`W9$ZgdtzyG6OuU_>5;;TQjA;a;Mxo^i-tma;7_xew^ zZk-XrPGju95xY;eTnX+N8DERDpWntE3MGK)r#k5|Tjy}xx}i(233!^Fv#@XF9S1HP z$JILwbVoN))@YY<+&JTN`l0;0q70<1nCeAV6&V!?Y>g z$C$eBAiS|gEFqxyAldhep7B#3;x9q|!PFApZ#cue6{kMj{Gn6!&)_h?Q6=W<1EAbB zBZBc^)=*|l@Nmk(7u-<&p7GoX_-`t(!P1=@{8!ojF8gPA*w^wMJpAtR9lie>2kW1> zuv?o~g81EEcc8t1ihW6(zp^8MCT_p#14ZPd6B-#`Vh9swjK5!ydHPHRx4 z6;D-DxHlr>(743k55-xiP``ox4Zyn&m|ko`2MZRIWOv{=PhHArMnayQy;}~DAu5?WBMBT0e4g8rL%{(O;BMGt@wgh*gM< zSPsF4^;y<8C@)p7%|fU`m|yRMJM{j=x$PTbUE1HjOOZ?=r9@4-L47-P@rbwwGa9iy zyE`(A)WF3gELe+aJh)rkLLJi5;3_;gJgz=T`2Nj0E=*{v8^Da4&s);<%>{NW;S{qy zp$yk?aq6Har3*!Wu7skKx(C>RY5lEd@^$ zwicVq%0QB=&8DRS{zTt7o`oR?dC|AL56+%V7!@V-F}&vRF*uN#wyB zFyJY^OJ1K0Lsl6^JskCw#bvbK)@h54;XJX&0}xnn93fIhGzRcbzZ#t`PWar2l^HQ(3z9BB8FAU%{*IcZ@nON4!A4xm^2x6!8 z=H-FoxnB*}N{r@gC~v=nl8)zlR{KN*NA)@OHY|yrU39A+45fC4BV^u6Bw7y{k&_-l z!Zcivt+oA;ObF_}Xqb}zl?aLhkbkg3%;D>lAIN0l32iy9Q3hn@4O8}@1)|XFd$ZA} zK-S=4aX>^X|ZH%Ko;xryxLZcsC`byuv$O?bkX5f+J4L< zG(-4M(d94WTCpNR$}7+#&TlsF1f-i*Y;G>TzhqbA z3g4`;!0kAW+P{7gUP8S94x+H=4w%t@YRVp$s%Lm;N-}(dON)cNgGKLKzNht!<)}LZ+}r9aaZ8%3MvYg)5?6GiqNnnFq8lvjmpf%6I1cT) zdLq7D-U(c3hRR}E15Dsjb7KWmtP7f^XE`UO%)Y%c#LaW4=v6|iVC74at&#|*uO--O zQ^-S^9t(An3?cDVVE=%&a_D$ygG{=wp<5@132jrzG>+1PFPkNKSgVxX~;=GZ0eQ>>*&lg z@RFC5lNpd?3W(;zXD17%^6-qyOw_4WT}6h=+$oOsRW68jwi7>e`*sehFe!?2P%eo! znU*p?i`!DiBsW1(r6&)BCzcWtwJH;liTa7?>U4G?E6s`3D(tEZ!Fg`NvQ-l0qAwS? ziB~u{>qEc6YCnh`3Dhu6OQ43Sy3Y^D;Z^u!~rQ#)I~a(Gjs7q%Y)s+flJRAYIl1k?bAjDDpkm!Z4i^_kGbRoDWOAR zl4|dlgH^IP=OQf~XvG?eNU)iWxIQ2&6Vs@61e@npf^j7o(O zKE8lZzJ#656m9OlW5er4ghhQA7qB2-FTvZu4q&blm+3_Dit9a^roA_3)8l@u7b}?H zNFW834VmDY(VvY!j-H&9u72X|-Owj!{XyRaEMDhkXCV&d3}#Nc;sD})xz_KWt9=8+ zt1w1!{=5P;34ODqimzk=x$f|BX2Ly1N77+DfnkOw&>;Eh^XdTsn;jM`yg_#j2HQu>>zbSE9L5Z6jTjs_jWY? zqO;r*hPUStB3U!IJw$skj_S(fjXO+GF2J~njc?KDFw!Z1cC&Bi+yPO2QQ3{ z>efRMPCt(M2*Z@~HB zBCy`}PEANt&M|aA1B92>@O)wcsPJUFrNgahpW`H5~(+B)|1=Qn#kramxzIr{~ zPuv{XPM>ZTu?+is4sH&eVCt=4LBP^mk+8X*9_}gv$ER`p>^Oz#H;72&cz^we>T=?7 z6TMf6war}nboB=jH0zhHrBQ|>=Gu(FEuzEyyCU2a0*`d_QNhe}`@6}wtpl)l*NqoK zgEMZ;!sbxVIdO7|8k{M!vNBCbZgzGyf`#JYMl4fq>h%Ih5BWjtQ<#48008k9$RNUa z0JIb7me?HUBc(=rXsufBlw+5g>yjJDmV(E}9|oM=eXOsTQ9+LwkEK_IvDfd3YpmPC zd;Yk4qS#xvnBOO8E#}b5&(XCSGR71;! z7*g#Mc=Sh>ILV&BgME$$W!pL@`eC+15SbE|ATyd0bgCxB*>_?z79ivuA?^ogqYOFL z_{AU%DTfpagbi$M-Wt)hInWu%6q)RT+K_D8LOoe~j)Ks)Ma12!0k%PHilTIg;a3-@ zo9YFX?Ivr%x^d6m@%S7EW}4J8QTwo|#ZDdKinsA@Q^pAQ;)|2dB14RuP={deC}D>r zK=$$xQqUC9l*_{5mo$$+erC3w|+OVF3C=rF6s6>6}hZL_@ zKkx{CATO!BGbxh+Q#J?^SEC1Q+Ck#DY^*$MP~FKdE&71^sIss1SwYvA~~@-u`n+56UrN?(Qo4P9ta~_IP`NVXH0Z zVgs5XJU3&iE?q-?^~pVDfEpthJIxn@STJ#B^Zb1l%J+hxvzHg79rEmb2WpR? z^zwr=;IQCD7|o#4#>MVz|3sWOqO^5z6KoL71&NgD70s{h3f!u9eO z5Dygh{Cp3!Cs1-pc~=SkYtmozcUG5CxA|p9sM)EqdDFuxd&PMe!3Ej;kpA? zFwU~>p<=2 z9GOAcjnO-4zl%@yvDz@p;DlZbGI)T_efAUlGep*8ejX3{cFJFd+aZLp5&!CRzYabB zbIP!rR9Zf&Zay{M{0TF(D=$!peRDcmd@|wkkcUI-4 zit4Y>vZS#rnYg8!E&SCXKCg_-cZSp|3UbBNWR=)L$BGJ^@KJ(T>#N>in=2e2>$nz^ zqM161l{9OCnfDXB*d2d_OF|O}V4j6o`M{JXgl~jpqQl&1r6)t{x5zyL;~?r? zmnVrqkU_Ud*0AR!ztWP6vkR~ddq%qDI+*nrkgxGb8oUOHav2>xh4M@v@~BUgHLoii zJ=UIm4z1JaFUNKhU2Mrhj5{5tLj9m3K+ym_;(B$VI;pC&DvNL9{(kCS<}86P)xz(j*fID#Jin z=WgkTpZjy}M{FN`Ly*Qt%P*J6{rq!+!m$`=)XBcS%o;NDLHqlLZvD|#MY%YCZ^6pN z?(^(R<=_ddGXbd8GNpx4qtP#e2f|v7y*6!!V%j`ckq1&&W;;=i!BMwD9KEpOuLLQ3 zkY;m)GA->wDQelD#nG=a(GM+wDU-hPoNrlp$F_uYo8#U0yFE_r6Zyd<)*kuD6LXPA zz!^b?{lr-O^9T(UiQlsGD%qx`8eX&4gvJMPQHo^|A^>3dcB5*kA4H2x+bAFK&Biau z^c0&N)5pluF4ok{UAhvY<42LMoQhmvUA|fa4~@QBiHI%TY@LTLGCIO$fi#W6nA}VX zF`+1luuI^%#6>_lBV4r4%A?0>s9g@z^=tO^Tb)k~TF+Q=Td>qnro%mB!C?TrSgZD^F>PmD~#!(r-Kg8hiXe|aT zoGa*a4xH(7sw-&gEFOQg9 zQ7o`yczCwho8BmJ(H3Q<`Ilkamem%l*G||eQA5UITqIdl#)Td3TI*UC?P5zlU;YqVEjW`d5BQWLwR?S8d7rJ|-06 zYXVYz_yljk9;%gi> zF2*F7#4bGw$Z7j#W5PMjvXrf;dfW;PFTE2yK^7U@Zk01iJ|v<(0}1P79a54pn5;~I z?1QaywB6Yd8|So{xs>*6#ZuDwk~K4P-6ngLT<4OK^u_uq|M|1^lKlA?)YJY#z`+(6 z%@Up(8YTKJXQ_*TatBe|9yPwndV2V z(nQDEYWRR4)OMc94UKkiw(t-7b?9>zPQO|yi{U&!qyl)z-y-p(+U%xl_C&)B<0u|N zrLWj(k@-V%ICJP8Lm&;17?D1O0EMg6_oV@H)L$|(de}g z>k}6f!AKkXM=zOFZN>*2Nimy}k(*-2 zdE#`B4C%CBxE3yYy|q^22h>y#d)#X(oG)W!k94mN)upMZho{UA>y$uV05nIDeIlWr z`YIX&sbjJDBpj%=bS8}RA`Uq(GKjP6wCfe5Qxkk%a{8FrH3trM`0CD^@B8&OO*_1$ z)}usrhDTX@@8D0wPomI*xs&T10OgGkw)pkVnw_4<%Ra5`O-MZIbGszih~I@mzCxXU z6HG=V$p!$4wO{g)8@537Qe`sw4>RC>zNzJP|g_*G2IO^7anW09vwk zFXi^!v{TMZ7eZTir1lhsv`ozd6Uv0p~CL|(kX8w#AuG6 zq#BEDgI7jor+GKjJn;{UJx*b)jQl^?)DxO@%{in22uIY9ksaVpA&v930S{c)Iq|S` z2nsEq9kVpV?S-vpfJrOOrGa7XA(q55zDX9711GHV>Hx1v8Li6YjoD47crnSa*o)vLPGw8;SeS}D_M=PzOJ+&tk*ZhLooZJ(uXIM&sX` z4;KH4wm1BPcYj^n^TN3WG=3`b^dNC>UEcGCj8C$B^fCB*AnJKT%m=@K_E#YZ;qYF^ zHrrx4!tdU;YO+UcHG_3p=21o4I?3`TK-yhA%O_L%^+C9OkVg94b+UT0XOT{PTfIZ` zUX>28lqW3!JqcO^RUPrX*Sy_4p5xEw9cGarUC@5W!L*&p7LcF&Kv*s%F^llT#*$|v@d zOH2}87%ZuO(2(#&`yeBiR|9X;6> zb#NLnv-1z4ZR(@3K%ow_HJ8(d{Pk!80vAkJ3knb7+6UbH1^N%DN?>L?HID-XG%Wgm zLDhdy$mGNZ^7Qx`Xyi7SaZtbifoA_8X~{?xVCh78&~R;DnjmA){~sl!NO#Kn2FkpQ zLA2ohMbDB6)5z0v!oLGkbU`6e{tI+00ijG6$cBb)c>s|G`*-f2N^M4vAWEeFg?vM} zIBmDRz@X6orfK^|>aHOE!{h$N8E;{MX;J?R{Rf}>x1VuIPg^* z8cqA2bK{nlm5o({uV3+L{(!#RZFu8ksHtqPzTK|fkDlMS2A{j8ia=b5UkeRz+VDQE zYDRTH+W7iwl>GpIe8W+59)>Y=kRFwQpCA|)Oz8rS>`_9GtxaI`=j4b~C)2=v#2&MqA7aTSg^e0OojGp=U^BO5c zaCayb&?-=|PmB)>ZjR~giZ{Z%KRCogFyIW&4Q|SsW}1C3pO)O9IsvO$r&iERRbh}Q zW1+`-?!a=W{d2Fc$mmm!RTLwAI5X9KbPJ=6XQEMEc*TU*x=R*~4!&+C!{@5~xa5UH zN8fsE5^5a~JGIH#TFO%+K6Jb4s8Ue7mmS1xdtI`UCU4i26Dxwu$)j@a2U8Y$8ID;* zv{yD8pIvK9K7qcYqX;Uwjtx`Xg>RuJY_3)P#_CRj-`1vT<<@2Ee&xWvlvmr2FlDb` zo}8O$j8?1AX}#o*(a@ja1b#R^%s#blI=V^kp{@zg8NfE%F~4EPZK}n0)Vtw2>1}Zz zC7+93UUayX%5qpO94&hYi4NE73E9CB*Tn_~XANiZ;K!C>hUu)-IH613vg_hax9sA` zj0*za?}m4;YT)kj>pIrT&Bo6r@C)ib|Jlh?-CPY1-y>I$t&=Gug?=eNCP$TVARV7Q zfgcOFt~I6fV6(jTq#S_-{#Gvowb$Wd`!z1{wyl;IdH@SdKosFT|LDBtNXd(q!`)n4 zBZB8=W7z9l;Pwc)>Jwyh7<*mzAw9X(!oq;4&|X?9j#k{sPfK@)Tz887#CQ|oBN;V9 zGq{;I$%DW8)=D+EaDC!#>t|DUoI`)be#Z@{)?jL>UL>gu6yU4cX9oSVX0%uCsW*fQ zkvFW0lgDw#S_1!xH;1(r0SnI;Z2>x0s6F%uVSwb*hqNdDx!8Z&Fw$RlmlT!`-yNj6 zjy;)DTOTE3ICKfI(+_KAO-5Q4FW z|6;jwv{O=2U5&Kh?O@P{Vplx7a2o-jj(HoSYBeOUQdhv%5j2RVDTcPqnKZG6VkcnI zQwGwBub#v-PQMxGo2a6mI5dU~(Ti&RpcyJE+)8VaU704}wHS3-m!~T%a0pQ*RfuKG zR)BRdmii`$H|_iFxvxA*{OUJ zp^*0R3{g~}BqZSI9FvCaTNOgbbZ6E+9=VBBCQ7I>s8sY_thZbBHNqoGu1H+_7O$?* z)XJA4(om(!aze1%SXbv?l*gMB%b+i}vxZ(+5414Q_tl*ro)maRmhgzzNvZ4VXVsBt z1h?11kb6d}(0;ex%EV@V++ z^`j$4oYVEClUgEY>KIr6n;aY-iIjU(sqV64$4ns74KU(;?@8L({hq|Y+%#mvoL72! z0YtYDeGo_PJn~to$K#jDEB>-@`L)p2@M|jW6p=T~3Bx^<__0+)qe_*c#`OIP7(U-l zw;K8Yv=Z~8wy<=!xD#ZPTFh}do4z5O{+odaBjVT&-3Z^aXH9}T`nliEM};y*4-wIk z(}^(8q?0+s=fYvu8>RJYb{Blp$`WD;W|CJkOg7B=UY; zC8tAXuc)Z0^4RT-_zasv=E#w<=(r@f* zYT!SN*Ex(oP47rw-XrMUo?#=n>=nnMxcN%IYqo_(pWK8{WZmQ}yFR`>Dhrd2gf!RJ zAO7N&bnG6j4RwRM2R9cRmvyg&$rB*4(h*a>dG}g>q5#KFNFB@7PS-KneNVvKr%<;L zBdKiy_pm>lF&k8=Z$mh*0lPl^)BVw>S|%5l{gyvcr+SnwM*d2=NxS=e6g-RhvaVf7 zlSr_^7=7D7g{+<Jl|hyFJWhyc`0dx24k z)Q;Ac?p3L=FzvHy{i-FKVfo2*ZC-!wVK_?+t zYNE`xvq0^*V&@|>4~eel&5QF^`eJxfrG-!A$#izZzB z33uFb26d|)O{0NUu*bk#RdaSIV~rV>Dc6VU(2H(sl=KZJ_k^$Kypf%|yk7cmIfaP@ zYLczu61maGi`Tt}E@c{MZ}#=74mqXmYF*B@y`sO7V5hf~?(S@wXgLDlO!A3(3Vj)J zw2LtJQ9dBc)$BOrC%gX}>}**{t4q2rP@5u&C$)yJNmZm3>e}6)W@3v{YR^{FG}? zLf6NHNuElgk{+zST3D{fYX^M~DYg9|sDj0*vv|w2;)RNN)<#`Db#@-p|9uCmOlA8| z08D=lSx_EKEODP-&ezgnMlE&5vY`RH>pxH7Fb^6hIs?M1SIJoa4TtOh35Po(;L&U5 zXAhnMw5RwMq`L*7^h}V|kR&9&U}Ke8uL*!{d5}o4h9U64T_Bh|GaiFDhk6cTpNP1c zllO0)!8_nnxC;b_yNDp~DTsQsf6oERl!9Ytu>vTb=Xe_U7g?*IgsOslj+?7=*g)o& z5bMuj^xwlZU6wzeNjMNV(q?_3>;95+qwuf(wqA0Ar{Mt0qu^m{RHtNLIK_%> zFq$Xx8v+^lE(abKguM(&@Smp9GQmy9#z9Uzj{^km&f0$%O%Rw&tVa1eL=cz*gnzNq zQ>TF}q3}4>e%vo3{yQ!oT2Ni!>Jx_o2{{-9~?LsV* zEvg^&!!M-9jphIlgo?W&RI5GIxJXo$1EYp_NU$Dq5U>l(ekP`R>7f8bdog*)`)wzw z)x9w?Vpf!46bGYg=!7DiFOFOMSh0VyGQ}$nnTv8|L{DYJkLLP~7ZrACGe1fT2{We@ zm^q7_T!hDYd=J~r{f=w;vzLtPPwBdW8uSmzKcRrw(VujHx% zo4L5cKR0*vAG*Q}if^zVKhU-A^;Wdrpx)kP=(kWrw;%O7nEnCjKLEWS$HM+3jQ=^` z1gJldJQ~;o&b_cJ)=?22X;`R@dgKLb`-7=REKNUMn?qDdWahFHNNaiaEan8o1imf; zh#H=#2#R2bb%l(YiwdK$-4#_EWIE>HvzBRmk$+70_Z>jOKi}Js+yWO@rr2JLIBspO zm$;8Wo=Y!VB40n*PU$!zW;eE#4MfE||L~Fg%k5)2p!rhF(`1TGEaLdQL1@{8ib1!a zaE>T^PlHXN%9TCTuH~w)?24`Kac=chTbre=R_3C?Cp&Ejhc2Xk(VbU$vYw2sr|TMm z<{1GeiWQW$HazB+$oM|5e|Yi^2Q`{g$AblWQh=JNrEc@pmzEzk<|w4+qrV zKo@&1OF-@s<@&|kWaz3Rn`u%N+NbLqkZrV>MBIKb75VQFoAuL3E!LHAhfE;CvN$pd z-np1(;ap`?WDoR?vNM$!TxpsI73%eVgicYB*|%t+FL}2e$C;wZhA@B_EJ+8%{RA^{ zOZ-2+(yCQSnQId@_m|(~C9O-@2~a@P7?VOOCIAVqvIcy7EE-ucl>O+=z8Ms z3D8tgPIPNN=S;dlwNw;h>8I4;a4t8B*RbIYlkMF0F&Tu8wsnW^Gtg_8qx^)YyUX@= zEaz8^gNWz4A;TUtjrQLsXZbQQnnbAI;u#)>U+7uUc4;y_MdLTRk z+5pbpwjMWsoJ}!zG+$|o9(KTo58LoZX_i(Srd0p&R0I(EJ@&eup1^^gIFq(?)e*`+5XH`2>3a z8Vtv1U8YS}06H>G3<1hUCDn5FJ9J`std9UKny!*yGWo)6EzD#ZBcim8nD>UL^u`HP z=3%_a4bpKJkz)<}`rSlC)!~n;rin7feY8D=8^LoT6B$bbFn>!am@f48Ok> zP3KyNg8bpbw$$FgRv3U+-roHo5S*09{exPGwv0bJAy@WfZ5Rm z)$NY8G{R62Nkdq?sX|I`Ks|Mt*3_ca-fw7) z!s}~LP$CT7$1uM!OPZd#ka2|)S#$ApI>BoG=I%R@lf!F=!Pw+{Iy855W*Deu(mI=R zRh+?fPI|AK^ulceUW%W$R}ea)fD=B~WWok_zQLv0(m@l>5k00KWm%!*gO1Z7m@suI!n$NdII%QdN&UAU5{GK5Arx8w2dHE3djV2OuKs66w$ zMrFjeH2TkuJ&g;;-EO>p4sGl{iQ1^Cx>3ICMS z58z!`Ew>!H!@m7)NV*FzfhvoXPT>)$=#*B5Rbb<9cJnd7EO$zDa<9{r;loYcj#IA- zuUlHRQbN{X;Yfv#>}$PafEY*L81j)rJH_%Ecn z{Nni0krX3^BPA)2-5=CU=EBckIyUwNZ}T)d?Ej|kxAYjR|%c5NU?kmX>t~x zyLC+tPh|00yj+xOO&IC zzxJ=F#Il#mXXbXFj4$#7HXA<@lu)zW^Bky>jd%DU&7LF}M)sw$F4uCGux_FkRJ2s& z@9jCchfyi<(OvI&$=|K~rs0D9Kx@Yu*eLEqq~mGof?;;wr@VSpbf(nH9q8dj4JM^3 z{emj+>PT%w8WU5sU649cq3+l!x4XDv3}g=muKbi)t#!rOu3yOmP)e!Sz>)*Hgrx|t z&fql_^n|3Wi(@Wk%54n{XfmM5iFz&DofC1E7|HpHaUNWT9rLuuULaV|9q!)I@8k+z zCTeO!NKDf!VeHCm@lW$*D#hAb+i5dEF>lv0lt`#H^Wk|J7h`M zg^xmNr^HXye7SGzSZX}yXGJ}&#%1X=4_8-B$xg6vV7#6|3z{)Ef&IGjdl@lFI5)u_&o$dSRokXkM@X zmYLpW3KESF5IGG`+-KcZ(M`_fZ`{DteT*}U8!|;N97BXQ?7;(Xe6;1Cxo=5+3GD< z^P@Fr;`bt)Y}8e{3;8bQ`qfN$biDSJui(-&!a=N)=Q^)6D zNYi6Amy5e+BHj=row$R0&NH3~G2@QgkmbfDId+MhKOg95~NCg}Ycj*0ezd~>Y*jXL!UbEiZ)`@Cga^D{?o zu!~br=|mx1yh@4WMyNFV&>LlE8V!`6yggGbvVN*DC- zamb?<5@lNrYUP8y#AJx#Oy&s~R?M$glG<_^UVjH8MC%CNwR(AI z4cb_lUw*xdb<7F4rh$@LZM1N9X{dnp^ ze!WAGl=gugPkV&2jjdWc^2f4oKw^-qu@F}Xf=dX@9y+20*TsF(iRuFiKh4rb)=_fT z=855cIxWLV`oc(dOa~687WNl)OfBRuvl#O+dexC^;<$3ZvEX47m97--#nB)Vz5qID zsomj7J}OiO0%iF$tTIC-R@ZI>7)r3Otr|Wo42?$O7zeb1Uc)#qn!dYr%rDj&G5hgH z7h9vMgDFWv4(>M3>FBQWeW{T#-`Lx@K*~Hg8>WHTHjaEn^0OH=Ejc5UQVhcHQb+qz zj|fj%jD(XkfilXgSIBRkwV0Rnl}};}2%N!MJZI=NsPaB9`7r4L%)bf+5Ufxj0n_5Z z>nGd4Li{6QJS`ang{MHCJ_{ot@UlbYm!$ZwmY~!IRrkD*^l$!d;|;O#EbcsQ{(aEs zSP9lH+;5@Qo>hdu&o0ZDA;Ml%lK+Vcz^GVwcu)Ll+f)3`Joft}oUZ|AG@ z)^?w?+ugPHM_3l*aw9x$jD`?qPQMC@<(O{~Mv`Kn)ld<+%QMJPrJ@n`O-W)(8zyYjE1!)*899&trtL;8A-<**GcT`g+f4AN|2cgwANW2}0jU*c z<1AjsEXeC{CsIB+_=iRm-c+Bv1pp&Ze4S~*9L+JPCH(l@4p#ogCe_7s0F5h`?j%fR z7N@x6m=YlgKtQ_tCo0h-0TKRD?f;tg)hZBT94`(40Hu*-PL#Y`vGU4wy77@uA=Td4S)}QYmG;i2&vznf!vghv4 z_-1K7bfYRV%1OJQBHzV3>=dsL2epV4g1NwM((9%O$kj>5Zlc5iZ~H z`^cKByAmvCter*P%39xEbkd>)Y zd%>oS;ED(EKMwBfrX05Jd6f50IJ7iZR0rB`RHTN>-$s`YmufVMh3NZaO!F7-%v9T5 zmGCQCG4jou#0i;nUv!J|_(kpcrstwDy%n)o{Me;DwT+f9%)-OU>xzVPi%xMy)J$CdMYRE)?E~!x|uojDUYd-YfDia7D6<{hk!@vL-?v>?YxLUF? zUy0U9vi&MFUlzq+rx;h^e2d&Hu69YqT?8OCNwOAUmH$5Z8>tmQ7cTH8)bge==3s)n zT}+nJAS+1CDDS{0Fnve)PXuwgGO9Xj1XlTk|F&LW<-6Wh%3I>zG1ZjQ*!p)W=)>-r zDq*C2Ju1JeeLYQ5_D6@qe^BUe9ern2DQe>z;}p9pfXzj-LikEC!#X3B1b&b)N}YQX zsE#_YX_m4;?k$POob_|pMIJD}ajuJEP#9D3=k=4zb&tsAgNJ_gD(m(CmA{`?csE}_ zxV}ir|8sO8`7TIHxPMh^P(=-->$7_McZEC%Z2*Gd|9VHzogE|*!n4E+_Q`rLQsZBV zH#HC*r{+k|qBQ)U+v1aifshYu{$m=hZ+8CjvG<#Idq``?aZ$%+z3^6K0 zlq%~`1}Tt^(68Y-zh`R*czSS@eOxFmE0S7#B1J-V$~1Ky%F2En6_u5><{3Y%E-l!? z5t7-ij{I2#_?`m({Mi|dI`MkdL5nw4i2*DE+=K=S=rIKjbJ+G{8#kzY)3jlP z(~Ik<&&nd5`}SLL?93qDM%R1?!%L=n?i`ubTeaI(j~q+yaAV2UxIw=gG{G3?fJnH8 zUcwF6Mkok=VBS?gsCG2Pg4x_#DTTycbW^^5oBq}w#{mS_s4I9Qh%?w)@N3705Yv0E}UfUPmTV}bv++>Cj7mq+S zBT0Vlk1k!xDk{wmm7Hxj#6YeP4V|UpGkkIInVbE~QZx^z6(II8W zSy8cabL|;vnE23GThz$9Xw4*WXT3lGGp5r2U zg%Uv^WH0nv^!r3~ncF$wWT#0fPdw`~4tZ|J2Cnl-1NI4=ww)SZ7OhdOtvw4Lz*hIf zjr~pQHYHVL|u=J%rz<1T%#N=7r2kj=<3;+S{PwM_&!)i;slX&QX*p(a$2nz-WJo7GlKHwe~Jp z4zbknKVW|qr6f*N%YlNc9gPFiA7N+Hs??vDoWK=zS#G`U1UGG4SUvdO8xW)Vjb#fy zot|o0Cc0#-KKHDnwUE*@gJUP}a~*ARcwHhrLv-EZ!5$7fm()$+7Q3Yi3*)s0BG;R! z4JT~HJ$H=VeI62n2`307Y{mT>Uf--Opu0{lJ70RQv+)m)H_Yo2ZwM!{w0-SL0X z`Q~k5Pb^pTo)NYb=O7>R`2xb`)LP27kXr_uqRE{DzAm}61b|#0P}+B|NEl;bu1Q=T z&;e8D7A-j@?4oq5v*)-E@z{l;{a!aIk?n}ZGzHnPIW{AdvNQ0+j_sk>t`AUuX3m)( zbVc+lRS27Xo3)h{>U z9Lo~c#+GG|clBVvF>BGC$lLtGCnO#lD#j<&6$*mFz+g)Gf;N-I{JflWJKzUiA1W@|4}NooZ5J5L z>KrjVw}75o6-QgQPlN+wfo$vwm&eu`&TRiamK?#w?bOYgh4hV=KR7G#<(^M8KNe{U)tS-P|px9${UFRXU{3mU4KFGAaymjCHCS#SqP~ z%=LA^J4RIK`>Z2upmr)f^KTC#3vv?bkLJkV7a@N*o+F$DTloqDY9MxWV1e7pQ-utR|6p6bs zL>#xXKf1j~03AhVIS7bK5fVIU8CZzt9&L3SNdA@nrybA@C`N75`zk`8b>9ui2E38^ zmKFR8kxjuuFVnd-=baX8R71#oOohtS;BEp2zFrYhxf<;5J|ng>QyHlCmCm(%A$@cS zB^i^Zw1YH+OB?pbU-O7C1;xMKX2kBtuaIjZuoQt_tpfDV8SvkU?5opap>)jghxZxF zZEL+|j;;7?#f==1IOdYlE1n{&xy$+$$MN(a33YV&_-Er9Ay2*2GPEig2YSYtg; za#Oz*vZn)z=7+o+gQ*XVQv+m^NR~V@8vPtJjk(LaMjys-EU`rK$)YQ=)dL1IruX9- zJLoCY5#5mu1f$gL9snX5H>1*W%w7oG-Q-Re<%5ENSh@=Mzn;eBo=3!6uf+i^!mZ%zpQ zFpdEh@26d%e(p)87riNk;IBe&4xY8w3lfC3!aZ5nBbhs)9EVu$s<_dm4E=FN1X)o| zc*_qRk#j-nJ%+0MHsiI^kVpec*C=|zr6DHi4$PvE;W*p=#qF|*m|nt{2D#i19y#1^ zi3wx}Uil%WQqbWv_RQHYZ=SMz|O--2rbkjWRUg{4v4DG#ps#;Mw#u;^CFUW^JR zFAqK(OG&Wkx<>`2Y}xsj2TiPunKpm@aj&3}D3qS-1vm4Gw>vnOJ@`w03Ba|3pE*GF z`w$Hj(a!6Zf+6_b!jMdPHF)Dwn(k|MQj+zPH{fSQ+sk4{5U4pZ&B_5%Xp})TE^i*T z06~5cj_e=MeL6|bGzuJ(k3|s*Ubi4p924c2K&RF5%Absw)ZX$?ZNS6cQ^=fSDQr?F z`|)7Z2b3JY9fwCUCjAMRd^MIyb!v=4n@Srubf!2Q*e)*VrNi|wB0fPS+4zwR{dIc2 z?06-VaM-K#txiDt{vD+CIT_-X>`@zYEFdLApk9~LaUfLR-s{H)nKZZLS$7+ljoOgn z+JYRyBYL7+TGK<>MI)xgATxeer#loP_TV2gEt?%i8}f=9(?Lcl>3ESeK5(*d^f!42 zy*4e4FJ`x z8RNW0PSv)9LO@G?F!=xG6LNDL%AKIqVn9oXY>&jo=7zqOu>ssgUf`t9Pamp1VAbf3 zp!(Q320M%g?Tnf2N`#r0R1*DYV#?dm4`e{*-*`_UJNw>8<61DW;)4BuL-tqy`9}t{ z3xvP}E|r5B1&LKCnt!QnN}y5}m>^ilgS`JwT>Y0v0SD8FpbApxs{h2%z{OOsqEf>H znelIZD=JVZ_5bQ+J;^A*>mYd48a55D7jomT^dJxmzRisVgvZN;|4Sf%BNbrf;@ugP z&`Xx^S1Do11G6vr5KuTTIty5T0fM;^M3DU=RMv}J@+6;t3nxA8d;^XAT%GAjkO3+d zg9Q>=M=0ZGMCC7t4rX^?Ypf!wUs9F7EX@KP3|;ynVLeqp1Bf};JG&U! zyEs25a}rS^vfb~n{CDf*r*o}R>JhTt&vJhmqUeVK{oV!>V^vg3<20K!e;K8EWIBKA ze)jq%rw91<7u)G^|H#qF_4qFCXW65mGql%xMvDU@{mcEtMup+A^*A~uj9={GYHADR z^bzlmzH1~LithS9s^9~Dl*6sm^kQa#=srp(F4K{p7TeJs=e*~P?PQwf4Gll0n0fUv5a@bx@DUD%VWnR1A(u2NODE2Y5)IOh=3mDcl?r0}8ug zQg;|F5p+c5X%D|C_6vj*e0qfN+zLRey3%#;h@Kp4vczXePVZwq-K$;v9p%4_MD+18 zc(9?>>H_h}4_FFBe1L>_^-2@`rv%2Zo~zsaTTad~8kz(kpB(kwa*0M?d{Dv?d(=Mc z8`wd*(;;YhDsHLN*M`_mhYHIIz!5({Jkp#~28#xmfzw(K_U8NBUyl%(VQB;mGaopL z3p4jSK2?rR%v`YQ779#{lNaIA$>KkBa_IMNFep%Ou*}h=>9NfF#1}urblTQQA;p&* ziLlMQri%w~58rAX+`9{q_Z?H$keJyeGP;sgsCS;Omc35Hp(WN+!$--J6Cd$P3zlll zoZTSf+o)~&g0^cx#cnjaEA+3Z_>Z2~&j zUZ4K|Hv3ys4_qq{8x-UN4q=0A!(nc@6Z2fq?@uwZkKTb`4;J zUq0wh7lObSe!}{D`ro2~;7vGC2_j71vjYRWftR)w*T4r%2w=qi6-=IwfMiWza$a08 z*ryVJ*7#rspSPc`2CZtrOg&!%R<~ao8x@8@1QA=p1V4jkPX|EuSTOo8-r|4#232lC zFTCtL4~6}AnDC%G92kL@as2g-e+?kq3XcGkYKBJvvHgao{Lc`^3}8@!sZR%DU|@c} z{L=h$8${rJBlw8X8Z_NMEk2b~1RE|I=h={8*ZFd9@Ex!~Yj0uLU(N)}K`&+~{{db7 z+*Pnodf5jaXU4yxI|1n9XZR&Zq<_9Pe}T_)ege>+3}|G+zuq(Un-T%&0}^~6g2j{a+&*eugFld~m=r!}4AIZP>Jw1#>5Y z%czsnu=2e;^mDD!ynS<}O}n8iy_#J?vlxEj*t+-IReZ6{01y>4hDkQ7exiQjp6CRg z{jV|lKLM+Fn8HdK>}9n9_SH4Jg1a7L9;?nfKG*$#6Cc#|w_O}pTZRZL?vxQsL^5qb zb&AR5-J5(dfW8tQy6>4D3VA z+tB42T&Fem@UA0l66`!r_;0bDew0YE58A0ie?Ywi5@omNQ~VW zirF8#MH1DzfI5@;1`%`PXvtE0#4n+?w02p9D{@*Hg;a71kjtcm)r zzdNSspH|+KrO7UvFk{2apv`1rqA*&fJ9g1www0W<^{V(urrFsjRp(wxy|cBGl!l+gxw zvFToAUKaupa(QHlyROl-$&{-*hGhubQeaIg$)_~4H*GXp?=mM^<9`m+^XwrX%uJcp zNXpo@U9@Wrj{*yb>y=2;<7p{@qnUb98fKAwfD4P3iEv4=ahQ)F{0cwGgjeKomrED2 zfyWi-OE&3N(B`Bq`ivtZ1m4%#RfpT*=&CKI3k>to$1CRE7j83$5=(GCDlrQ(65=Nd zuW&RED3`RZio$QT!2OcRQjHbFztV{>wsQViE;XUAv0$!tfl#B+NktyJ;!o35@0er@ zc<)y6A-0CqHF~x>{+Ar8R5yhaRdiXn@ZxRoO8iQF{gEZLnS%Y)LcO$GXHmsEvD@$P;U>DPiY z4lKcH&p-oW^hI!7z3w4YqxWMkYS1SE&H6IfJpsZytJ*HXD1=M;y^1 zdevY2o*ZMSc&?zY>K1J`y`f-m0PL^9p%1{9#OIk&$D!O|tY$zB-dC2#{I9 z+&$|%8AGz46%%E@6~qbfr1*F(w|g_q&=pBRIhAw-PdIUEylY2vhr_sgn(3-EY$<+h zZFsFGc_qi)bV+@PLLtLP_MDUYr(Xy@=5uyS2FSA%0m)i_j{pq z`Preg=Vm7+22hIrD!&H{@7n4N8vv9;>&OwK4-FPMQMe1d>nzPq&}BSBZ79`I{k&yH zZYR*>)Qtoi2GZ#2;TOaV=WYDG_lF$iIpNpJok58m@^YJ)avQR#or0;oisFApye@J3 ze7gfIne65#7w=waVuZA#s{)KRP*I#r1VXnkwV9t){%bkBOIxtY&xQW~$ozkQ$Nsu4 zBUk8!f5SZjAlU7}0U1Hykn=bO8t|_x1%1+je)k+Vg1{HHy%c{{hJ`~=%Rsxg@VL*LlVF_uX%iW!vcO{+D?CY7F}N#Uq1@{1O1m z#h@_&ME$Pm)H0jo656d=qvQ>6-%e28(rRP8lOgLQdk-ygPBUnofcwd-Bh;(8U_}tC z@p{#Zd0$WigSHB@fOpi%lUc#I;CdC4`ZQxi_g!ymZbZsIpJ%V zyczww5rtn8zka+qz@1^X*KDsLiuS(2JNObx)$!MN6M-ja61U%=AG&{>0;J3 z@WH9pZ^06P;jgID$BA{uutsD18i@1=QS;X#5#II4pgPl4eDp z#s|nPC61Z$h3(tsAIpu@ezl^W=9Ozs95eI8nf8#|W&hCOLOLxWhs*w<%Y}B@Ob*B{ zn6i(MPoGq7+?2dekiW}fm2Z>OmzX|$DUiR*-uii;FW)I2KL0Su-msWOJ;_=wR!&u} zIq8b!*sLjfpDG`hZDqs-ak@-yT8>@rJ`r%mzS8HyKmA7Tbs`GeDBBxjz7ZGyeVXYs zIcK>~tSh4~;a2JUJkyZV@cCYe3T(4U3al%`E+o^x<(Q2c2ujvbFiAYWFgDM(5!RffG2vISW+gV;|;eHxtNt?5X_=POrT$uyPodHs#RP< ztF`aUG31Hz*%D-|Hy@27c->%E0Z?|X5_*BXWy}Vp(A#X^^M56tQo%zXa<05R*GVTl zHgI|<=g;qcPqQlMxB2bdb8oQ=+FXH@14E4BNPJMfgJU%F&&TFJVs?T3E&rscnn>En%hu}<%IN;vyyoF`L zvt_?NwLC)(%YfU#;Y2<}&1Lu#lEfRACHrko|HS6+Aw9J}8s{wmhc?PQ2wj=Un0#m) z)VSH9`X8HcfjoLK$HMZiuPMZ}#7I~A6i>tRd)!$6}4;%XQ zRcjPsY}M82N!vY=LhL=u5(r66d!{9mgpNq^2^t@plvO19jR;rSh5Zaggqn^^yT`~s zabCpqAR~oE)1yqV92G#?GJN{+dsH5Jo*8txkX-I%H~xt%%|8j&S`Z4rfkEOXeItE= z@6lC69$S8Q5-P`g!qjJ<-JKA<`BgNV4C|DD)u8{nTfHG@8tuGyof_w3wAM$Wy9?6q z^y%cJgkAisGKBkK0Wy2s2@;_`n4=Mc2XlDqz8@kagi`c_c6LxlzK88-3Omx7A#X(m z_oUX1O3$CGukjz_gpBY5Y+(2n@g(c;%~yrPmE4@iwsTCZ-i_I+ljt8dyeAjgyqQZl z3up?XNkqC1nyDga!|c~+rKIVi>yeSqw8!^4&5PE`mW$Dm+Z?n>k#tA2k{hYc9>tHb z_#l-%UhQs10Bcu?o6UlUnNWRc3~3>+DS@JWww%bree{w|7JV z$7Jm8t?GuOckpn$fR#FV@y1nsB%icQ(X?pGTX)TD$7!Aw={c(%O#1@TQ;awZJLY;6 zLtDZ0dL(8!JJ#_gQ@*On%2_t5BwS;oFM4`Z0YoR1wkGpr&{??T$JsMhSJ*u9Y`h=* zG7g~wWZs>&ZuI?bF7OnWPqpLqwH0?%%Wv{3DRLt!3d{JUD@|d zVgSjM7mgfT{Ol)(tZJx%Qway0?i!i7l}y60JMmj$e_UXdor!;zeK3!|A2h`HHBq#p zLeChIF9p05+$yiN4$}|{enfRXAxA0hFbNx}w7-071HfKX2VO<1_Y3g+(A4y2QwXst zr=X4a8;e|XDJM?x`MXMgHtDa90_Y+k{tQSd;xPqSxX#GCkhl7NnHi0Dz`)F|GXv6L;vNp+*)T8ZO~fman|jQl!VtW<2C zAgnA3l?|XTm_8r10M$-{=P0!10@qbEUw zo#TRkK=}F>9uz_qSJKO|q2;EK+tk*=o@$D?%_)GiXce*c+k^ALAZj{K(y1*}#i1Zf zWg4fM8yg$Wz0ztB%alMP9MLwn64;UZX*qG7b)XR_2Jamn#LAOADbp9P<13y zTG16IVK_@*FP%_ON!3?*GL{!9bG!UT>y6gN1HNa^@2Ib9w? z7{`|kb@ukv(fxEq0|)Zlh0xgo72$uYFpF(8%pSW;)rG0OW%64dC5K}&rdsbR6$+aI zWDv&r&Nk_DU9dc|sU%E(4Q0cY9^Rv7nnb59tkhgHBq$Q~QV(EkzwmR#t6G@2j!p}+ zqx_=8e7ljYwf>IZUac+tSTg!1K2GWlVYI1R3E9c7NE>_w4-tnpf7s)t-q+|skz-?5 zRaVA&ep^+kE&I!+jukn}rFMFOaKfQZH(49q{p1pOs(Md{*QPUtCTFtxILJ0Pzri(Z{?`(_bmf>SYGsZG;OK`Nng8j=(6hB{(pvsz@@20@lG zyMezFYxMp&A1OiH=-!Kxqxr~rC^QW5dQb*mGiEXWPjg-^U@=o?c&B&s)vOm4o@J;A$c^_uc4nvVV&-~pnP5;?R z_{WgTS_D71KX$bP-xNpY%_kYqrXF}0l&`OFGWEYn>^gz!)u!#VV?8i%?7ADEO_E+w zK!#k&J54aL!PKw_>edjlRF63lq5z;{FZ=`3b2L9VSmBGbXIzRejwNI-LT?^a>Iul9 z|12Vayo`t-Mqyg^dQb`(B(wjuxgU=2Wmzudb#YeIty8Ei`zx(*rcaZg!RAhBu?7of zXXf32(A$75%mD>Tl`nGk*J@_g*2TsJGbYprt;hPg(->7tDtj5#v@^C%Y`lPJw~KBK z_|;6Fb4PB=QX6ixJ_0Ln4%5_YMfmYXhoe;?IfbuXdmZhIR6=U@0r4oCM2mkF<#ZVF zD#1jsq%l`lEpA-pc4s0ZWytOeqJvc6@V3`;{p`mcI3GZMJ3eaWL^wWS{( zSlqm9{@B=2TRTcGOP#*@-WUm>^`Ioki}vyvsMZ6%hfXOUZgz6AV~n#WkgyuKAl!0W zJr!4qvN8*qTVoFWq?>}4G;BT%kLk^($^j)8mjA8Z&=x40E>A}5-C|Zg?Toz5#EBGsX85VV^Yy7ni z=czs{&bc&zU&6(=lHJf>O3Ur1ac8%rO~@0S8I{D}+KO69njSXAV~t4eBqbeF$t~lWT9_HP9{>;#_)#641|N>h$>6Cm)i1loZh-B);U*#NBdcq z-$dGnrj9!wPOUKzK4n*Sxeg?NinuRtt}3~-=Sm{2LYC_~@9z{JQXMPX+lT^I@_w{L z9NygK)7P*5eB4`s0xy;^TKqdoZ{Vdm*VEh@dJRhO8FuXwmc zHW(`8X;?pH!;lme&-R+&z+6wLvI0fe`d&toTdPyttQu5Qi}*&EUlZQNb8RM|fYMjL0noe(}Gu9=0+$v|n3iedW`$TB&P^ zm(!0%XgZ=L5yg1B5*Rmcl8@;!4ky&FB)zFOf)NNC76Fh_m5Gv}=+}f=n~~{3u3;uf zY0>8)n*V7-zT~%?;8>7w%J2){M@W|T)Stjz_Je#O@^|U4xNh7>-*?}I80njMWwUK? zY#~)8m}J@U&DY!KH;o7&cqg3o_`$Mq*IQ`Vq29#Rn=46kKS~{&?Iuh(n~m&cd)%Z{ z+I(uhpfU$wTS!!QCll5;ITce7^RU~ZLWmOAbD>`RB&C$ed8`3p$1!2p+(&)e`QcmE zqw*%jXpaIvW5vC=03ZesO0!=xO6qbQ;yuo{_U;jP`af@p}ehLvjR2(eh!BcUSz%0;2tm|Yt265}CBMv6vVZfIF6 zF!^h;J_UW+Ti5E^?CAbta{?cGjWwR}5yMc=hVqdl9YYwTO#aPwUAh%q~x{TRC=qr-*Rxb}PBk)$=7XWv*` z)?C%)!RcQPB)U9)+r7oh(#oy+J?y=|r0xob33Ipp;8L+`Gw&^bw03HHbjOvD8?C>E z$BpVWfA7GuSFKm>YVymYw$1MR@c!uV*ub698yfgcTb)|(V$*uVhsCVzRPfu+#B%=5 zlCC~yOD>f>yP!H4o&J2s;va^D8*Ba&H}LOmr`OESA9yQf?Y_wUvvz#`R`X<^;q9Ed z&n*f`JTahmT1d0&{_DqEgm12t;OsNx=lD8KeNtpn)UXakhby*-9C`Zs z%e)q^*TpUU(|h~=ke^DTq9lvf9WKA@`&W}ofB#)j`unG%6@Q1$A5fHEd1i(6yVDAK zmK=XJ@6vkLXY(GH?R%ILbzFP?=!-!4*`N-_1=0O}9n_}%w>zf{T;`t^*RJuUv;7wg|Ge+o z^p{0B@74$1eLbW|({^h;|KKM+qu(VA*pd05`JU;&6!zDeXOxpn4rBZ}l zCT{QOsA`bgFEq+By<&QtKHV5oxwu-cm8zj;xaxYc-7?*2>7DAGX1M0MZKfthiYXUh z6=)H-yh5Nl&@!_^fIibIreU#jFOL|vbSY4ksgJR5r(dqVZk1^l)1s{QTtv-q*n zO?jNL_(uGD>88~<&*HLpJ1Nxgp3q+02cPcJuJYWwC+ZX4OyGBV@Y))L=W`J~l{4zPcvzfi5B6&%~&x5{5VU6eh-ig|`HvEDL_93^~i57$OwkoxQWcFyg`(JWH z13kE|;^W(iB>yD`@uS~@zvTM-rH67;1vQ~M!ii^p=@1g7lc2~saCHeoEx1pBtHYUM^2|6)BV1o&I%dD8z<=Uy#6S zLr>1D>0O;nif_xVO!ngNfTepd@dP_bswdEg_vZAT=ka1n_h7vx`En9=pvt|lbcy8{ z2+4vFd}h$>ukRo}Xyy~S636=a7_f#8;mt9Xb=IW$afOY|`&D&Efz39s5p6VK7^km! zPp-(>lwJp$HqpG<`Z6AdG--3@aIGy^0_9^?6-)~E1XeMy0A zWK#$|HLFu2&{qY0fI$CxBK5qQB=)xKz-8OshwRz$ludQAP^Z%qza9DtBYD1(1_o_Nu$^4?Mc}!lf*6eAaPd;@AKQQw;>74iW%?zbHV#49=F33Pc>5McYQfxeN(aMkp_NI5qR#mQ2ySV zY8>Ni-d&NsI2-@VU{i96H^*EyHMhTl=2@3`Gqj{5ORvZ-e8^L3m)1qJFMupfFexwP z37WHRP(anmizl)pxv@evFhh9ujM|`wTg*U;5N+mP%tb^->mAGtas32%ExXJ6+)v7$ zTyk_Vnth(rX6DM4B&%4i!22p*Mc>m`#A|}CR^oHL9Wg9c)M3|sR@>>2z7v}LLC|Xd zcSO}n=Sx-{mt7dp{K(2p`vT-}#Dkck+kWC;wrpBx?RzLCK zS;sLvv_2c|LzX0(CTe{Y?aPA{@U4%^)i`}D#nLrIX+Lld-%6y){ou1>tPi3m8NUq{ zqhWNILfh*c9#~H}t>EjCVdWJB%U#E%ZlarMTd2t7FIr!6^O)?ym>YsSPx_3^Jpk4g zE64iZ7;QD;pNdqKd{5D?OG9mxF9w7mu$l=$&_l$`VL zfKi=17?1&ozVNco=v^{QP>K;v$79aeaHl&2z5>qnyq+x<4k1l;fEC!E<2liwH+*7 z4DS$KDJWM#vdI*8y1oHNyF%4hP-H~fmq!%O2>wmy!1YD_)Ym_*@D+5m0|J@~*4}6}1m5yz6bkr*Oa|PgvNw}bN=9DNoLA~9%c5jF} z`yW?WeMO<2eNT2{CV%*%nK8^tk|LeHH+i2zW~rLQ59I?=I+91HWd}B3 zLGjUDH(dWO9++~tI>0%@~U@zX!rb#?88@qOW^ zV#FMERnvM>g>253-7Kg)TiA)wC|)eQz7MEcFDY%!QrWZ<&Ar2COT@{8}^M{{yT^HJlW)0q*^3 zC(i`&UT9yOj%5Qi&6)Md-$zVt_9tq-=5?qtP3A1QCuC>FNTog$^au1Z9(oa>jtpZ1 z8j_ZW6qLs84eP8x#u-&nlCTRk`)m2DqV$zvSOvE$G6ma8>WS?-Dw1zqG_CC>(2U~O z8OqzCuSS|?Afr&_aWe*-L8o^&HVt3WdVyKM`tRV{DC3u}!$lLZ&XrB~n?Me58CNPs}E_pndA;le?5qc-G z1)WTH;q&TkJOCgEz)`fCW;oMFHFD&t?7?TX2pbhm^^uB{F2Cq)N%3`)l+s7&RQA;qF+*H zFexo*LwStcq9#M1$^q<5pjVz}iCZ&CIGC~j z3Yw@PHY+TgN!Lsmg|@Hl?>8hG(TYPH$ytEm6{jKRcggNar)2(mI7u%Biz~A;Kbl&G=75%vHg#x#HYM zQ?x`w+Al!nq~XG_l|Qo9_zmnPW051C0xe8ts&FSuu_t7-s!pw2_5$5jSV2^0;W7<5 zP*JW)R+oa70=|%SFFF~Pibcf`ExT}qqTX97H|09jbBdT=SNIp-47c-{Y zXJN0jnKvgqohXxMv(QDk5YGkZ+H{PMz&*vbq}KxENj7ZuD)gN{%lq&XDm^*83Wq>+ zT!RjS>(@YO7>rs{S&;tfDyR2*tF|RB|0sL1@zWR2`-b)C8Ql3(RiGbwozvUJs>_jQ z>p)NWmpJ|EVGY%;MH&%0B8W`;3306)HaGq*hKA)+7ZnU5QT1 z>&e`ao#3ex;HfnPDDz%$di?6if^4g$pZ@6bae1Lh{`Zib4i*&#cV*|V`frC1N9 zE{a?iJA>BY%3HrwEIO7V zXNZ$))P|Be6Ze&v9P{YlmEh2*3+E8M5-Tglc=%>CpX|q*>4$Ad>Sh?84hj2bMQR;5 z`YK2eC$1aI>4TSCFEJOrp>G}~btb$1kzKjGdGo;G_G!)mzt(f-%{`W)SzE-Z zBkroov$)`WZRemb_BtDq@N<$qcPoZx3qhCbBhJlq*OZoCfX?0HYM+)w5I1|b`UAQHXcoQpPL`(-EcVW!Co&cdXcr*7KB^J-^eu|{@ewc=jm z?MLoH+vkO+#Bdf%%Vd&E5LpY z(%6u~6(-bWsDhfY-FauilgW<4T8i@gJ-cP<5}3Fj%7bX6XFW0OquNMfjTW|~5GSup z`+iHNi+1`zs)P=VE0{nOiMgb|Dggld)P5eQ10%wDr=9RZGTpWQfJO zT;%FpBg_0|jH`^|ioLc0$NiKmS(J`h`NwI=?HO3Q9ZOftK+=&cHH+uKRpy}mL8?-i zl9r%((n6+cBN-Em>d~mcr0Uz$t{W1$suP~xwIN-nEAIGgO-B2QP_+bi6l1UNN(Lz@ zUZW*7H{y7fxyS@$FirjjMG0^b7Y_IQCbau+=Ci;x`i^|obSmyWi>F^gkX3;N#6&(k zjnm_reK*b~d@k4|?qJjKBD3aV)=aF`bhKaG!^ur`ynI5BU>$q-!il06f@oy6NaV(! zSTQa)s7^;8QNZ6TZ(&aY=|cmi@NUTDniVJbXx!4T)Q~dj_gPnXGw$s38uwJ18>DoY)l&X|yM$ddTYQ^+?K4DaBGY*H6KEv}71T|kaJ z_h2bz#*|ck1`uv`=gmLQz=;h7xFLDWg53NlgibUE-*$H0#iuXHFhlG&y>O2kkv4g1gOI-I zutO7m=+PGW=>=BHVvcGW$Hm|ZJ3P@f1;@vz!iX~X%3fq;F_>=7(-AMCY{19@8pAaf zau#_jQPHVN3%^DNl|v}HV>KdH-eJiYy-DLto-I*!f9o@=^-6`QPJv!5=J^{rTU?Ik z%^kZpEmId$dGnH4I9sQ4%WdcvUI9MwGYnW;P)Y1==GR8DVuoBare|8i!2=ZKgswjAQjEU-Cbvv+y5zOOB?G(qJPXP}H}KnmzR;Tr9#l(9f~!enlD|rEhE)~&cuj*d)POUH zpeo;E(eF&IFIQ}GqBL~NT15V2xVpF~c=uG1fGbUG*jk58!{^P_>AgYx2&Juxpw`DP zbhM<_VcLJtpz4*Lz|b5RMBiTiM#mOA}a-RRCcrxQf2prVMUTs_`U--KNQx zt;ghZzH!~+W)vkiwA+Se*-FpXNz=B;o($~8(I5RE!dE*2Y%KxoObWnEWmpJr z(K})S8EL}ir)Deg&i&gLZ$Szkih}}gf%E(j&be_SqLb!=s|UIhM{xZIyBSe|Gn;eH zH;3{SHY0Z`3k_L}R8R#~Ty&==?Lht#nWHY2nM3KxJ)L9oa+|7ng8h527m=KcRP;Bg zriHbT5Gkyz)zz(Dz*#22PU1eN$pGds&Ln)MT$y3=8gM_`9?GGiR$Z9w?BUE2>oc-F zyTaD|38jpMQpB0Q9Lbe}+iI*xQ@ruP>T!hej>B_1ys-n^BJ{nJIDOYeiV_$6`K%H> z#Hj`s7n9`sd7Kn?+$c%XmacBY7jk6<9Ms69RVpOXNvmRZyjg~cc*8-f2orH4l#P+# z794J7o-IA;a!|9J_BoS|3zY=-+AZ;O2e8Th51S$DIT|c4`CA9fMo%-Qv{(T2_CPN> zm+j_%>DgsEd_#D;>YVh!P-GbtDOTj?TPVF7y-&`#_aFxQGLQBH@qf?vq7eQN6gzlBCTzT9wCZ+FEh{Eru+*%*nMYR%busd8TN`PmlB@ZkO!iV|q=G3Nq)7EN%9;;f1x`l_a`7WSocb4<0e^Z-EBur!ccPI$AUMlMeDDUb7oUcXm`&c-8M zil+8*G>{=${N@}NzbF@(5 zIiD^2F*5I@>~G7Ea@~<~#n5;9#Xt_^$n_any&3KNd%;ZxV~JJMOmR3BZEYZ`L0aE` zLGF#6P=OY~KnNE}b2_paH)I^~{enHIAR7xZQISENnP6AaZl6h!5mYCE-Iy`zlC4=L zUD;Aau8qV+2HCP3y^6+_@!sM)t6d=sL?4NZld>4Vj8x-avTLhcG@0%EFn1DyVKCM- zBHQIx3?wYmG=t$UFucco1L>uMhtj9UTwGH)m8RVjL(&BcH!^;&$)U?iDftHjnOsA5 z7HT?G+n7~#rhbCeTR?4f1?wm9A@$gi7n`?kSMT*pno82^>EEx7o_z%SSMm>xtY>1d zO#;;DjXEtZp$dXzhJxTq4tp}|r3vExSAdxJBkS}a?_S|BpJGd2fBdW-vHTItLIi9t ze>2T#oa!lc0GQp>B7n!*1#WIAlFn^(3e2&I#oc9bcemp1?#0`_wB_FKJ-_#l zJ-g35Gnq`1$w~6bo}SX4?a`tt$wI?mL%_qsL!`T0$;G4c!~Ff0<%Uw>h!3zPxED)- z^?-nY2zvSanTrSk0T1zaZUO+33MTDk5y&4BKmck?gGL7Vgd!l-8bBUF{d=)02~7Z| zs(>y){`*`@Dj*1r_N43{4F>>qI~XbuPV3A8LSQ2Ee5LIg(R13^kbO0yg4xxrh@a0cc_X8VzK< z{X!$s0uJGoaitJ=0uae5EHXF?2gdy$Hz4*MSZWY`KLQdMl>l%6^^fMCL2!!{oWQ@8 z;LUQ_!dD_Mr=G$)~{5nMPMPSH`mduv( zO4v3MiZPRHHB}#ozyw{h9HqDy@^(X=RQr+ysjHK`+7Nt$#GknbZ$^ zBJ&U|68B*1?@h-D1AbZtrbc&fRHz4TeP(Wt3%>6v--tw!yU8we8yahI^Sr%It!g}e zPT7Ye26=P5|K(=qJz{;;eZTx5AeJXi&@)?5^`HT68(6h-o}iG;+jK$2=jaDM-;*Ir zuP;`~t?%=A;Two4S?L7;B7#-CuSRKAA2Lu->g_>PmOOldh_*A!a zOz5xq>>y^f1nXhS15WfGCQR2dEh<=T0n26z; zF%ZmmcDx`Syt(C_&UG_Y9b6LQpd7s|NQ^&v#Ku;+4fzpSa~`b-TG+vYY4ZW!*m4Pa zLQc%y-v)8naJD)+RN$zwyGrPyy2WlOE5zD7r1-Z8Y)|S`GEPhP$4{ET1DG?6lnw&n>KpsTkULLAPaQOi>EKIUAiR);^?{S516O$tgX^FF=BNu3!K$mQR5$iK}A0MPcrVh#qZ=br->nJW>4L+H--3{;wn#nzOe~%uh}G_ScDI!6gNbDHbso5 z^hC&l@!LPZ|Dx8-D(M(W#kxIA$Y+frA?Y+PJ&xj`21No=_o6oec9`xlt5lP0eZliC z)?q6vF9xojtkb$QM&m8$Oh6>+5x(Ib!ju{iJ-X%eT;D;2Mtb@&5GIIf66%vZBO>APX6q2uUNjp%~$i*I(>S*wn zA7M0drywwu&{pz!JFoQ9E5-GUw%@91YeeeXKDb5 zuRiXNQvtm=6(mp`3oIPC{SuIh{C}PbbTWm21dP^3^1z;V{Z;9v$w?3mfn+WEc`|VR zqvre1cK#TcQcw}tmvr4qCw#Y61bN&~!)Hv%D>P%!v@y$H8VjU5tD~iLPTtVgpnNgO zzhtx~q%Gc__3TJ1aMcmCevC*!hyQtgaw2Ae_ip-Y(_NpVfyqB=GXKn>i0H_&(Q%h1YANi=>xkfg}WD61mhdh{1%aZ zl0BB}G%bqs9y&2XxtmPmLtrNW7QvpW3PV=n*uL3ySz_jwv3;E9@(=-`+%2T5hYZ_H z&=}Gu5MKVMEJHh8eLGcp2czlr9pW!hv3EfG8}nAC^hztM0nPlI`QiK9*cwlXp83lX z+jes9-_j&^-1Jvz*uM(kZaZ+Cv3+DweRO%&N@#mN3#Ng=m9uw!lj$B)5(SCP>pmx)nBRvwP;~nid>|!Ja zKdS$cs@O!CuZcgA3pHp=v}A=sshJ!bMf)ohq3=)WZAUs=8WZ>WG|J1M)I=Mw8_LNd z1|ipSrOAsp$&vi zPfV>)H+tO-lG_%J3&{HF%}wHD^A94Lm&r?e@N9M&DOXAfQ5c_&oR=1Cj6U59D4`cFk0*4qk&ZBjlC=;y;L5O-EP*79C zdn7$N>l&hZ0ei}|apW*_xS90bz81L(ACI)n@)V7%*&SPo;>fkS9H@e;%Z+<#M(LQh zTO_8{NMxoR4i-fzZ4=^2j>9E@6#7GEOi~}q7CtAzON7FdaK!aUx)gE09Zmu=Dp~h6 z%oLkW`I6f-GIH0<5NTfo1~j! zct`3>c89?;UFnD93*sQ6ee!I2r>;OwI`g=tqY0;;w0C}{#Ff%fkSyE^B*HCXZtr6L zghFEW%|@}^OBd3Tr_845IXSiNjlw~d@3j3{Abt2Z2ENgsm=<-6##b8RashE}E9l6A zPN5db*l4{f;oq9LskVa~XtCK77^z)|MUjUsq99!}xly09UbWV^*S@BOnM zKX^Yh72)s5{J;pLp!|_-Kb5G4IzEgVTbVU><=vimE=zJ)zJR0?m?e3WN1tiHE+K|eHBb@5hDv+>cnj7k_nkB+U{-%TFDCb%4JXZYD#ZJto3gTx-T&y@ zXdMD2cG8VDSa%xIw^_@wa%#3>8HZgbRdjk$+cQkC+AkiU{Q6{|0;ma z=5wmw7bnG##jq*FQV%f$L+E?9)J**8Qdh@6k} zJ9yA$`o!GUj$dWqmy6PHjl=|jyX(~<;z zfO1!rM9H2$`#@2h_h$mWX@rd)0z=EYWkaU**enSVa|*jtYE+hF+@>tyZFeQqF{8`r zhjmkVr@gW+>^%}!?p|0s#r1Yx zuFc}8-f;)LJLXxX8`I}V)$#l;wujSyy1GoG_$@fijw+YjZ!{Nlr7dBdzy3YjwPi`@ zduAu!tZEoc$=hu@Z;~ax;n>__Q9(B%688^cYmLI;5%w)2HtQG@`7>Ia;fu7B8MvO1 zXWPIccXya8uDz)3W?%kjN)o5X=??_MF<(FH@PrSuH}S3$a-5$fETB8)*Z1-5VfG;$ zq{dg%tDR=O`{AV+9m=rgG`h?i{O|Z4W#XAy1cIYv_ zsdYRu%C1GaGvYn#8EYi|slF!(NqK9v+Z-S<;##X{dbI2<@f{y< zWLv7^?ZJ_jxHqd%@bYtHe|4DIZ06?y*Z#9;)5{($zF>iA9m7So7|CH4{DEm{rjZCH zkxVRYcCj5P1W%t?UmDr0EL0@S>}tfUSd1_HG92fUf=K=49(V{IyoUm#Pd^Nvtc1P; z62p%AB}qaT613sY-R%vcPb>VT?**)YDsOE#f#ViQH?~#cw;KlbKBRk_6DNHmWGp6` zc~LexeVX=Z?KLS)S05U$e(F6yR`{G;B|S`SmigfI<#&78C6w0kjCmi=Tx5NoH?&F6 z_Ji70g^wHE+ds-+_pIb0c8VX;JjxukZ+mB;;gj*!qz6HuD^RQF&edZuLq+2K@)|W z#m$e-nk_S;yHekl?BJ5zGJ)j-$3w@J{I}?9n;%t6k}Px^z)dz)DtgkjGmC z?m7*d)b~$*m3!Z5szm$QD@*WgzR!RR-sZ$*)f%9+WX^zuy?V#atVXB=bUwM9l1X>+ zKlbo3biNtVQVpfA+q!OqoM6v<8*As`kAEPca*f&c5b09N8b1qq!(q@{o8cYKVc0)% zPta~Mga28>31j5&?ZlD8^nh zxn@TAz!prlbx3}FH^FafW?8$s_z6|N0V~a)DA#TW<6Z#mf}!arERgtu+hWUsgVF~{ z5Wnrb(>-;lBNT1(De79Jla~ID&yQ;iV_o)xPncON+PQnhGL*2n0c*9G<*)i@gk{Q6 z5`KPVrL#g?5l56ym9;;~woP=-L}_o@+CJF;c{p7JrrweTdM}Z1blxq`oOP+DfM}H- z;B0rw#%8Y{IG3k6`GIHCU+_cYqi{LTlgDR0;F;C@Z-6}}H)v#3W4M>#wIl0v&T zM+qE3tlEE=Xu9?FrNR?{PHNjeShf^QWI|iREjj_it#HDoeI4gn^kj&%Z90wX*!t;# zRDaKHy65obquj~j)SNc*uA9o% zH===`l zr6CM(fQN)c_yF18&()EOIxOF(WdF5)Ywg``yEW4pv#o`)tWhLFSxn~?yMX2 zo4Utha82^tz;M*gJVT#93F)da?bTd$WXl|D8ETFeQ3pLw@;Uu5qOvzL@j}lU?Eaz> z#ErLel#EDOz!=-`5W#}<}3O6DDFKf1jGi>|C{-~R2)G;kN^rW zIuAe@`d?=HH<9feK!61kjKTas`Ip`PUm|-l`cg35O9F(x*46&|2As?0KUEL?pT)}?Z*Hskb z1o(78=k=DmcJGOn^EF<@U+2HXAQbw6Tp9k6>UufZ5Fo@))gizU$0jmO_*)qi!(I@K zcTyxlqmh|eFSp6>1j=X4jb<{=PuXwtHb?Fw$TV$IVr_!_E4}XB%E=68CL=46u28D` zT}^Ji$iV{*jYeq~$6h$z+(fa2FpIQ?}aHZB!KZEf(^%^M3c$#^q>86mCAUkTa)k1DrdA%u-_U;b_q=M zCZ`Ugkk$M4&|kvew&Fru-(PVE6>X9Wm2F}Om29yCX0|LwIo_v_YOO>_j(^lDeP^x4 zmd`>EP8%gc4WmhgVhA|3TB91Bb}2`{1v~Kx zPr+8)pB6(Oj{_5d^F8zLxnP%zH;f9V$lx(}ddK^|6hZsomiHQP(F)emZ|nrqqFKC| z-3wD=42Cg*SRXX&bp1!x7wGuV3T<+Sq`ZBgfCLobEIkqBX8jyE*m8xK1EUKHl(Qx@ zN8ZiYqj^`J{R+7Zsa5aQZA{orH4|_Yl`L5`t*ZqnB`NT8@xDI*Y-kL;aJnXI+cC)i z*Zt1!lsKQzy|AV%?5(+K7G-P=6HXS*da;@A3Vo}9IqLO8F{qpt4GuBdQ3qnSr5fuq z7H&hc%9qe*4iwEi1j(|tTqcrQUAD_!gJCWj^;9Mrd9^&&!AsT#Z|H{Uqi(JH?sXCb zcNN5E7`U<^Jrc>czU4bD*hws56Y>7i(GBMBpRFlyt#codBn@Q)p{Uot2}g5A#Iz9V za_$QP+F&;wok$^~t#I3sKjpEr0?L@D%*w{}EW^vb^GLRgEl_Oc#^5@FEqB*Hk{4`; zdg%3G3HSxoy8008AF)-*_azAUMHRX{!-%L~*2P#}l%;qo3|xDNejr?OeMTM=@Qbm) zVLiGBG#q+J#~E&E3J6r|4~%#O|DaIpM;u@Q&R#MY%v=hrZ8Rt*cD;X;CwADJ7w`*Q zKY}MO+j1B1ixsK5Qakb>JU_V4-H^E=_{ihc|FuTkccbgJ^gbcR{nC;c*yW9g7_iIL z9+x0K%xdwggc6p-je3w%Pyw~*K0T%*(EL69d^Ogpz%R%-TnU|f+A$5a13oO$LJ@u} zpbZC3y)bSh#~R6r$|WoDZ^_b#J6EFq#cey&a-7AxGn6kG3eeAZ3Po?If~C5O zk!n0Cz|^^AS%dzIAt4_Z6vBoUJCR4p86b<>Bu>W?Nbgo}J>zA@ih|(prGmc5;4p1zP9% z)EM-b8nY-X@mMS39hzDC>>LOPNlSmFN~O_l?bIvl1a;h1OA)U8hOaJpbE>)OMmcAa znZ-qEXA&G$v&v?EF73Xcw=dXSIozOnZ;K$)IP#Ij;^9l z*C|Mfsm@&7Kq#9SoS76q<}}5i1U8fkPvhEwP+X7b=-#*TVs^T5+Os#<4sGW%#z&d5 zoEKY$mGa9>1zFH(u{NR1$cQ)XJR!$aXT@hqoWbzjlPWPnb&1l!_3mP)??|+Nz7fa1 zswp?(6gFm5>+Iw06pRXB#)-iu!cq7l$_H1|9IRqOeu!&Z|HI;vo(Y%l97sTkNA;6x zoP@e?CrMZQvAB#BtrNlNYm5}BisNZl@if*$b1w?RH`1Cn9RbK2TkM9JV26;e z!4{d8f>Ayi?%cS&EF~y45lD}bhN$mOe}tUhI2Udb8pwX-ml&f)Z?-a^R5a0VWs!g~ zJ-WByOIM5|&RMGOldMtN1)*IH_DQzL6b7xFXg?E+ODmxkKbQ-5uZt$`)#Py0Qhz7O z8W7{Md=kR;ccdeV_xVrhFYqpq`XYZ~@Xz9d^l`n6#hl4LuSm3`mT|%1(`) z4@Eli-)Iw61md-JRvI8R(udM^M;sSuR6Xp2d&)VY)S(TI8(G+VV|6^ z)*bd2Rx=25MuFrj-LY4?)L}RmKA!;$OuvLbOO`z23GV}ysj@@dE^Bj6O7858xf z%3L4bsnDj1X7sL$!W1>|F=`xr`4mYzt^1-8Cd9p?GvK9T!kXm4BmC;=XuY6T+qs!P z{)TdM>^l@?jsPnG|2MYH_nL66w1rhJwNV`JKFM^p$f5ELAj8-d=&-@{Gd)9GU!uF8 zizaT6$GjcIy@0lS7IB3ywHop!kVY&G zR>uEzrFU;*RyX3jX$c#^!`YwoAWr0w#`3lY_L&LFBWC}Xr`u;drGfJnSid#9-pIr~ zP}HdgGf~Yq%>@Hb8|xW`T7h$&Egfz!i+WRvX*4oe1ZyU!n`3Ix6bAIQLDQlgj3Bpc zqa(GCPKx(F4LHe*cmD6Kjcu2GViCL`S?bIc<4s$8M&F4dMyJ-FN&NI@A4#%IPNx91 zNGSj}fB%W1-5}e-a$hj=4>>_P@dS<17LOcu)w|>lNjGLA9yDC%$kv z=&#Vz%QGly<7KBaa=6G>Jn9d;4(dFIh5={i!MVT2<$t%YfPp~<@r)y&fvYP4XRmPg zUwC{>3Q&mpkLKUyy1Orvv_Nq6|GS*U9R>w-xB8L=tlz+TzMlAHISokhI|4k|MFchr z2`1$a!vCis0Q>@cZ9@K|`QO8XtKtB^|ItivvLXPTaR4Ylzo%cYGaxza*H@1Ip7L87 zEbqV02GHN-z;v(W}D#;EiCuWf-M@f&t6n!&<&B`m1meLKpzp zfDO+0AIu2)D>wx362jE|?|EL{AcG}bVO?J3{NGLr@Fh0j@IQqA7!8UY zY|X1BPQFJV1Z8zYBZ7fSurB|Tr-Aw1VKiX=Y4E?3{@|BLVE0Gp{?|SJ@~Kb$GT7q{ zBSHC3C4bYt2@<%&|49E2Ci;S_Vt_eH;R65Z4g4}`;(x{aVvcCwpkDy$S8cpl9u26! z|3zY^B!Hi<-2atWn?0QH>+@fU{A~%bQ-GO!HTnOuFIz1bt5)OIh=2e#i-W~N z{FmeYM?y&8&UHZHD_HyAW`6vlg16mZEnh|bS2b((a8Iu$_=hs+ zMe``2$-$RY|0_R$;6H})M`=fMFG|BVhJA+l$L;^g=6nu-0RCVB`}KcWd>Jfy-RQsd z0MNuAtLI#Re*a42Z^unIC1Ch}nux%czhNm}5%!l>Ax^Lj4J^rPhtGKP%jNrff2u}a z9E+hdUh_{7M1ziddK?TVe4?_hH&~=pxVXI+vv+U{7u{&OVv`W|M`j9lOqDum4jul<0 zQ97ry?yF^ISKm@RQiv!C9Qw#SmN`jOS0VT_`2uaufL zTsU{cG#%V-eU5o@>_7*0M#8n-$K#K zv7{J!IQ4!2#(v~0FinkHiQE?Oa(W-+q%x4}A=g6>*q+fC=E+SjQ(IE#W!0^f@t@B5 zR>O~>C}^>=XeP<2K>{t&)w^hs#()|;Q+iU@#Qf1!#k@2iV%KfOO@pqHt&zvhZCRNy zX+huNR2o=NR#&CJzR+IHJY~&H=-J?w09BvrfY@JNzpbH5(=aAuhmGWvLm9tP`b|Jf zum%GlOzWgP>q5k+P`)vzBf!_MF!QG8lr0x=IM8G?y}@*-sO_sH<1%rrsby)Z%lwtA zwt^}J*1244)ka!l0@vv*2Ms>2UKb35)2NJV`V`P@M7xc)*a$JHlBZ?tG0ODAF`+8G z^SO@TsnR}A#k9S9pFC~CRs>2u02JGLgD7c(?L!TPXo0qW=EZ=`ekB;Lai&etzUb!0 zWpQiEp^C@?zvokh^+P`Obh$k7dlSDoXU;^m!{gCgVhxqOkPs%`N$E0~-W|;2u|#}T zwjN+T3HP@Ck5h%=7-6D!&=BDNBUBsJHe*8$Pj4i&nlZhd!BH?qzj7fmpWI))+%Y_7m`ELOV8|ux%rP zIcM=EHHaR|SgC5EuJO#%&bBR0t2$W=cKN_PBp^x|r0Y0ila=V~JJLsPA^QykTQ;`O zwA@1G8`dvPBHGX$y)4ij-OjKqJv7i0xr?2ZQ)Qa~Xx4}(5X=LL0Z$b`7v&kZvWg;6 zN_$g&sq_4z#DD%m;LbM>8+Y2_jR%$kz6W6kuOpyh_5uzX*qf!LdxYE?C_?C==?GMn zCHTmFhb(9wi5Mq$g8I>8qSNp~6Z(AH0dbh(JD0(T^m{C9P9X0j!uwKj535jVC=}8+ z_vk$NB`7DK?KVgkq!o1T!z{$ep$+@{ZVIh(*bO-~3sn&My}8{!-WU1y0vD9&c zNDUaR)TT~y=58)3=pX&6h5)M@a=9lLY~B;h?3^s?e5XY}lib5#5)Sw%Y0bV>=fN?Q zH+d`WtkI7P&i(GCnR%jxH~OOy{EQxl%cY+%8xgig0wuB9P=2F%b3hJE_p+9Ox5 z+rpvIDpnS!>86`;g4>j-b)s$wbbr4He0+V<`DMd88+6)*CZU5DlI7~BE7h+belL_VG(KoC4geMlnC;qZkorGah7f^Fhh=j zyOoY7B9gTr8(~bTO6F7PfFjP1=yNQ-{t7WKgeGmeeZzN1!IZvA3Smzaz_~9GgtQ(# z<()(^bva||@LfH;og$xWn6s~#hQ%19NoUsr?1K~Gzf|;iX*vjGb(^GmnT6@4+^E>T zp(;#FETyz#y}x8q3nM&ZITXXq{HaC%Hoh`)bt>XnOF}iNav#EnyFK&gmo>D?N>UvM zb$OB2t^6Xrr1`1hO;BU-K}@qasP^AP)(>^S#>T2z8i*RzzPTI*Rxsl%B-+ z-dkaRoCT>N84uwe3iTgFzk}Ubwv9T*C30;)qnXlOwI74q=YEJfL<@zm%Lg221coZ+ zibe(vA$B})T}^!c0IM>zP9GIMNM2qys`X2u3tf^L9V2UUqqTCsiwH=&@4{c$;@q4; zX^9CmWtg}7$!w%{%eqOi_@XScDu5(Lm&Aft>K(h zJvh`0L?WGgNj#u3MW0hL;T+W;Fzsq^<7+_TG&U024xNHwcs0&YnGknf%ircvHZqtY z-+sF@mc-q+NA+;6?ef0AvEj8E-khO@CaKBnDfG5i8ahj!76xW9>dwbrA4SA9pi5=K zy-(Xp4@^Di7xELG!^$#mgautMHzCb$S@;RBM;~9Huaj;rIF0{M-Lv-N>j)sc6tMp? z8M5(&e9fgdzHT`wour7NB+^Iq@C>sLgqone__9?x9a)Ltyau(JQDG{n>G*7lcU>a1 zr%q8=y8O(&l?}W;`C+=Jk~CVDpE(F&;ee4Je5j*8P{I+Gm9*`AKBLCro6@sRucm5e zFKV0iVR(#K+JOXE$R^7|yMkVC6i2@)XMcc9|I?PfjZU5EGm?4DYJYj-S6wH#+9!q4 zKK-z7aKw#xcbkwzJ%O#wBBQp#gM_=}9}NJUpo)bI>2VwVO{TFdv=1cwW*aZ?N0u2FX02{@RvbDz79wj3}D# zs_I~ge5gRuo(=tJ7}u(^K^eeW!LNTNV7zHeJfWCO|7=p+pD@~2NLT%pKSg&_gLhE2 z2U@FhrlAT*xBvpA;D7wq8oF7nlGmjpk9(6{4u=#F5MmxI0f`KQUitW2oW#c8_?{618i8g zLz%F5FXIOD6x_F215qCKW{^W=(KeTBCP0hWvFlu>~uZc z7(ijLcM(hD=Np#?Z9ja1g7zDUrro09^>X4gTv9)A6vM69j?6ZuU2pNw=k2(?Y)-hZ zp(g&hkZar-EqbDUX@(=l5TYJ+u`G-OF7b$nSoWw}jV|1>_IcnjRM5OcZqF*-(q{1c z&{qpo7Yf}RSHBd(nb5q1!eLdrq`>JY-MYIUyLc#v$VWwx0 z`R}5L*e3GPlFRLFhF{6&iWlAM<{RgiXg;1__A|FeW(b70`+we-g-lrAf5?2qGR#y2 zh9cZsu00?f-c$VQi)P&%VQBw?inn2izu`d8Ub1OJ&|a~*&ix!3@_Y6I1!a8)Gr$sBphmrZ#^X{Co zQ%Fj&W3jq`yv`ndS*;SPj**+X;6}5H5{l*#|KZS|)%RnxZW^f$&pl z??R`}Xn6!ZXh_K&5FG@u$<;Om3>R7!9bC{g39We}eIX6a=mS)=>v6m41GGL2+TQ@8 z_S!SYB#WZ`F*ur|1`*d#Pl=87%+>X}`DeLxcGz>L62@jE` z(maQX(%{i=*9q+eZX>N+UwPV=Y8F1J46;2*p$&A>s-t!wL}wJew8L48 znkf-X)zb72#2;@C={!UnSZ&fR1Px;=MTyMg@hn;+c|sc-_JY5^fixwg2PUR+G0iZ%>z~L*C>nJ;xzl2tkw35>X7x3 zUy9IXgqH=mj=;TSnae0~w{A3v>2wh>e?S%F{nL2mV4GuE^8njxVkjmSvi` z1K5D>T-^vk5U*B0!xShbjT_I@ES2|Z@Ni=ByUVdT z2a7DZmL-9n+q@zv{7R{2OgY#j$2*r@;rLlh)n;t8I2a{%8yTAE z;a)deh5s}#XMEwuY2Wkvx7LR$Af9Hg5k_pWUcC$hYx#6*i@?)D$8OxXSz8ZYj$V$i zk(a2<2dc>^qcEr_6lq8kbsO1hO#}_0g^P9d4m535}K$dt(bIXKSHG%^M@OAVjOl|inQ)7Nw86#_f1_2<|(~qg^4utGYM>~0JiTZb+yv+7%hIq+)m=>QJ^Bi;skx`{t=E)FN4N1RB z0W>?JGpJ627^T}y6%wPXPz|f~J4RHp;wW76M%6>--<&}BWcPrcZxDP+BAE2eB8l{) zg28-Wjl315$K~D)0jnh{Vh9RUF%B+>I4SG(3R^kfaI}5E^Q17u1K3IgH@~5cP-8dv z08aT9X)-Eheh{;wjz^u7Sgb(hk3uf>PRy#{y-b7+yvwJ9rOYq(Y_@?1Imq_Y68wfV zUB@we#&2>=y3O}v!zO%Yr1)~beAPgGzTA?BJ9TrV(gj;&Q5q1~Lq zyvN6dAuEo>&Atd5E~|*O6NI!eA;4m0JZ8=+A~&kq=cCVr?(&hv1c9X>h?0HC8k~lJ z9VWJ8E_-0r-#2Q~^tEn@gcx3OxQW>42EA-b)K)(1V?2I=$_R0pOphk~=_g=t^+6(T0%&*)Mo&7f29ku%{b8)9883_3bhOm2H9x8sFDzpvVx z5P}K=7KcB~aEB4jW>mi_SUfG9JsfN~CTlC06h^4LZ+Wy&^7U9RwvdjqROGD_FZC$d zFh$UTwgdp>k{~M!#&ZxoN(~_1xM-@;TW%)3;+`f1Rpp=;H;`s>C~Q9+ zoDU6b^lH_Gx1^4=hRGB!Mf<%z++VM^oNl+w)v;JQ2Ij;TFv(fvsda7azKU=OEF~Vk zr9il~181O_th3aTesghh=j`$>+vOs?KE)C3SdSwPXJbVTG5hdc`E2;HX{za4;XGrH z|Khqe$TXKZr5oqoJA;+r9pd(5xtq}@tA`7agokihOB&KM@_hS)wqoWW%N;MIeP6x<0l{)Hc$o($p93HZ(>wul*x-%1n& zGk@#9;D|=olFQgX_#n1vEPbZ=>3bzHu(VfHW2|1|XNY8MXD+S{7SkLIO*d_y>}^o@9T)lm4R=Y4IkF*M|b1B^^5 zoTyESCpMxGcVOHanstRfw^04{@!gKFoDY^2Ed+6$CG>Q5!p3<}5+HgO(n*@*a#`NBvi4R(NN+qOPYfpdN+M z-FaE^0{=nb0DLdO;SICME@WBZz__fzJv$d)OBi8SUj21q$d#Wiz78;sv6DZ3Vsttw zJ&_^uP6Uh;qTt+!;R06?;Z&q{(Hhh~<*Nx3K~`HHJWj!H{F0gnMnlB3{a&a1Z0hSP z1l5Rk_=w>1v8%p%eX{LV;f>{@mp#U!r`n?JrHgQXi}B+rg8e;pVwYwEp#p8xZ~qB7 z#QO+*g$ufg9yVi$y~%P9h=Q4NGl+ueaurwlmTNG%5E(Rz@##D$w}5A^uuA`O*o*v)IY zeH5viUDBmp4&8usQ~AqG2$E>EL+_|%Cd&8ThlbmSP;7kTC3Q9;-|ONS4NcO57}(|u zGs3X#L#RTL-LTDoht`6fHv$NSt8Q3l$n>+L05psRyx5>^*sv_8e{0_WQCS9>v_h{P zsaX;knEhKHUL-TEtQ^IM5Q$WU%U#x44JS2Vy6L=p1OrSNplV2O&ir`PJUZ(dU%XRY z@MXJB&@%J~n(a#Dlou*xZc1nTAMm!avFMo|->c=vow-4~L4K=NT)~QC~`G(dW zs=Hxw;?D?VhtM=-6^fwk*={5@=$+Z17J?S;t(5{>Zet7KEnf)fMdEED-0KTru!^!8 zkjtA8?UEE(H}Mri)a#6n)Y=Br0U_F}Oh&vI`ueiU6&+D~-^ImjZM-`{5p@O!^pFj-P=>aUz^rYREdrIZxQ;PKo0l(w6AB zOw7#f_|r0YvNFHvVwBV18I+qr=x5Nx=YdeIq%<4QO7FK3eY8|YA$A!Z$zwRB{kWeO zV=^p$yWf*VWi0uSCkgrqi`Tcbxk#4QFJh6C+ zlGz#9s$R^cG2^jmpv46rIj?^1mO&>Q@>ZEB{OhRhrJd3x@nFAu_M7!UmFLeV4`Ri* zcwy572|yPNLu=*sxdfHeN^2U!gdCsKziI@j?&@mq>gt zxo}J5xZGa=CCVRb%V!xTntoEsttej(VJp)Czaij7;aH=J6BOv0bold(`qeC&34)r0 z0<>8eDJ|Sbtl(3H;?MRFLXAKuj9LcCXd~CzF(65IJyB`KFeW7lo&yRv#6B%LoF+E; zNqh>#Z}QkW#jz?Ws$wV2>^&ynsZYl>g2ubKY{slai)arwt#C0E8U$$z9h#>VF;l}p z^WWIi;)U4#;o;(iE6Gge9Yv-E!4LK{AMVNv$Re0TiQ4>Q0wiA!md50?bIJ7;CEDI* zi9B%+1Ag}a<>^~+rsjE|>46(lt`xcg4#I$#oTgZKk^hj1z$k9LV_6D9dT(}vqYR=p zpSH55LEqlcWw2d#wHI35v|;+@?O8C8dtblFR4R>rhSup#Ubv@5B9`I%@CXj10U{zB z{AB@5!=HK1p<*mZV$~+po)k}D=mhB(e1j=(+>bssvwtEgv#*~f&-)3gH z2hfDNdz8@MWT9{OictWj-k~l?HQNRh=cMv|^w&1wX2Kol=9q#V>C@qpDFeGUFZ79A zvUXqMx)1$-WW5Dc98I(}iUhad?(XjH?ykYz-NFDtg2Q0J-CYNF2ov1h2@(iS(7+@4 z^8fd~_hvC`HC@H2Iz>-+&Ds0x6Lwjnj)#O_)a!+JkOF?N(w3oQ&!m$6a5k+ zX+nj9TAiPE4P2^@$^Kc67X8>AgI>72!e3T-pNgU}{4?M_IqS#Jr_3J*>d8p&+sTqn zlvQd^^C=ujx!c*2V&1oll);a=0r$vMR!cC~;A^314Fk4piN)t8vOC7D%PErzx=lwN zfkwrgBQf}2dX?SIJfmG~B;xqS4s6`lf0a$6+iEzrHrD9#RMhfm%qrR~JBixfIL@lt zjzoEEtGNN3p;9YQ8KRS;&$Bf6^U96h%UZ2Ydwxx(`>qII>we!XX9RhyCF#dhTSq}K zew*Y?;}5LblPTXd@*I=gCJiG|Mes?j?w`nS$2kx4%*YZkWa2cR5`mwN_!LmElvJI` zeriKD#4?Hjl1#nl*NXYjhfFYq?$aOG0EZJDkZ%GwO?{l}r^Z}jP%!$LQk1Dz6V>=g z8MC16R=qf+C%gjw0si!Ub!Y$AF&)Tkmj@WTCi{8q>)Q{wGDtC7L_FFT`5=ncEXfx! z?elLex4gK$R+@Oj{SUNyh4R#&8j(Yb`;ij zGkn^qCurIfEb)6Jb2L06IDe#els$^n2ogwb@^~F+zO*B0@-l1+I9vj>bb#&zHD>jx zaNnOxhTI2x{w5!ePLK9D;<`-0TZrfNII#R?HW= z4X-opissZ7YJT>3&*0>)&-IwH`pmj(%95I(I-w>-6jig15;*PZtkIWxt`|F}4 z2B_%jAp@Z+9TFz3_Ix zmRYt&wE{gB9p>8s>Rzfmn|?(w{x{1nB}yUu-?a4dl|BiSVCc+t%9I#53uO%{z=TNn zg(#-ql9Avz>Bv?WyR@(Lk4_42Xa)RumVYKpL;nDI*~85-JAD`$#q|AwenFuyXH ztlBde$n-g=aM`?KY7qS8!OGnB@|Bq11?N>kLcX>dN|~QvT>*2SaYC)OSqw&4m!U>S z{>(ku&CnR)#ZPUZ!RR0wUoNP@3dzQWgAl?6m)6-y7=IsjIyKG`nJ{0Ae^Ui8U?n90 z;g}s$ID&t&keq_~bD3;r*}e+_w}DvkrF?rZM@igL^#*SG`yt1X5#)lo1WWW%a78 zS3g8#Tis1(8n&k(A9IXquz=!ItT4vhk;cr@3UCbcGVQ5wcvL%Rb~~b7jg?^^B$1X7 zfjY#ChO-88ZCW~U%$4WV^1VbD=^0V(%qet&RJp0BLUu(X9?(1O>bn_$^S+{3f+^;( zL!AK+Dw5RbymQ)qN>LcT%XJxFZ}ePPqwjrt?z`>2RKDJrxq|RhGZmN5rc}Pa-sg5A zs9JD^_kJoK^zB+)Jvg4T`0$)r<-wZ7ec;(N+oh$Gxt}3uT4Moiw1MPVuB*!Ey<@VF8Tq6jDGj*$P=9|TIp%5xz z3ax4K)sx=fwJmlQN4xPnQ4JO=NMb`lwZ-9mZSCZ5^0{ak;RNaR_*PNib@nE@;qPae zk%7ZX54c^w6u+!1tXTEj5G5;7=^-1l!Yd*r&6jtP3{!)FnTC~J06FyoR`!?1hFN3| zW=eRDy7%k$LNpDd_)vEQ{ltXfNcuKwj+<~+#-7!h3i)Fu{+L$9jrDeg`zK$2CrXBR zm_4RSiXMVX3$Ii)`UpMSx+L9pj90heu&zXbS>P}(kaG~~RB}!FBKpMxz3np2?@b}y zvrP9&p~;N82ER5W2_ts=ti0`SKkK41q!hLZ@HH0)Zo9rf3~ooBh<$?CaDn*w`X;6Y z2k*gUaNI`#0Z}9QzX7*D0#u+k%ADOllHgyQ>y1+PkE8fkn=1W&?v3l$&j?%kkInd( zLKl<>SNM+=_J;xqYEgU_|F8WoWma|^0WJNFGK&d1jDgAjhpqknODYezynocyze-te ztU;vovrPmz2zihcb+{|>eu{ZAmH(?w8KlDXp z5W`Pc@c)_eA7U!B37pJ70^$Fq8iGjF;ky25mA%b|0MwQPJqG=sb{Q++jT;zYh=2hg z{F<8E;CK?1wr654IQfO1!U=+knzmIQ+$yEc;Uus1E|ssfh$#f7eG$jkr@!!K^W=6j zAnts!hp*jeti^~G{Pyd)PkX@Y_^G+Noa3*j8>FGLu8-FTxA=jN9#bDR;2TtfER_N! z0`1f95iXMjhgIXEh<7!qf(Tw;$5{ZEc9%_5LC)#-ewRp8K}kcbN%vM5y%M{+^3McO zQ;GLXQ6Fe838{jThg_2GoiKVOcYWlaNusuBFX5N%syI0Lfh!`Dfy&UfN4Es+Xi8(WHADj8}=>5Ax51Q2^RYQmU8aApjuh-UZ`T zau*;U7(euyghfRSR+Kv<^P>lk$(g9Q)5=q{$L!;Q8RgDs{HVc)NnO$V3siOFe$3z# zITO_@SRgO3D{6m&Do^za2M7Xo#qA@>ZK_;_Q(=Pz<>HeA(ZRUMfe7Gq;JT!H=sp!# zP<~UoQKC_yQN}%bp9_o+00zjPQTp+M(~|=E!2xocidQ1QCaOcZGg`mk{ohoiWDjKE zPgH10*|dIN_MyO(R0+Vq&-)bMNO=*7D?IQXm1?39g&%OAQ7)H4pVlvPA0KEVpG*0m z0DS9+4gM-8qH=`*tfTSE-FJ`^ph}nLk>io?pfaS=m8%8b$N@y;ub|}fEX6pe@RJ;q z1EVdKILI@Ar-??C?JDk{_G!Q|R38+tyr@1*{UG0BquHX{YS!%WD+`RlN1e>xozLMWsZ)_Yu?Gc4 z1|F(B)NWjDTnTHem(!@U|D?N|rQ6i9+2Fe@bk+Hpa=yX56$!_ZL6mHsS6O?NwV<;k ze^E87&8i-fMKu|1xTg+$-7s|NM5${5pO%MHxeZ3d0Lq|s{meR(D{-z<%cFF#sxZ}w z_<9ia=#ra+Jk_wmP~&OKe49=$vJ{h*k>N`L*0vMcS|83V5)js1qA?tS}^8*tW)*LC0^mVM!IYj%8|3eE?g_4Rd|C@rlq zA1-NZZz$eh1WMx@wqL7PpN$H20Z$GY{D?*MnV152JY{LS(FPxG397zD`O%Xv2g986 zWNbH}ziWA^5wx>daMID|(Oj`9ok0A~^`(x>dl@-7)8z3-^xF1=i})G*wbu+1Va9Tw z`3b<>7H(l4--J8u1Mo46T1(S`uUA;<3lr7KuhrT`-Kt+YebyEB)cZc!HielcRo_Qk z@xj$5N~Diy+HuAJO;!zQYITScevwd9aS;Yro`S=MPLcq-9}$_u%T~~~w!dm12&;&L z03Jw?zeay{eQYiLVY2<8Qawv&7-FCc*)jx(G(HWQ4U{4A_;FEO)zdkmsUk2Il~q|@ zQUZ^WilMlBAJmL`?MlGZ^X{2SiN#u3g(6Rs%6`H_%awh7?D^BzCmFTuyP_eOoOOea zF+VYF%(RiTrJdnDxWf}^t140zrmdH1!l%)Bfv)iTaB+9zQ;)N`R_ z?-vz}Ogx@US3Ncgwz#krijqcMzcX)qCExf zKc70c6B)!CA3_Pa=@#g>-A-v1T!R|4n@;Sj-KX8mcBr4l%Eu($y^cRvDjMajSVy5z zJmS{mN!zAKc@3xxjOEC4&|4rG*ikN+y0O7{6Xc%rGv#G}&cHv7hsMGTw4HA@qM{Ze zkXNO3#H%_K^_3vv%d+>=>;&{-6szrpq(=!0HMZL{j%g`RIH=R&S3Ia2p`f=KnEw1; zk05Dr#-8dz7er&UY>0|H&=`8XZ5jkAXH&P zrn17GSvyL56{95#Q>uDSxi-Jq@T7M4on8$`iGArqGPO?d(ll(7Poe}Y@7E_Vx)qwLN&Ydl z5~F~{j80pmLeTKb^`RU~asxpH9WLyMwtHM?$NVE1qh*0#Z4a(hp zvCC6a({>;EidTmo$;>)SpQllNfp2LxJk^`6!?YzdlaXE5vRhnmft_2-$*{UD$;R^; z9-P9Gm9hDW^5{5heI7A)ks)OxTa1#yE167ic;{q=clgt_cJ6lo(RJ#Nw8RHPyIt{$ z(!SD+4E7Wg;icVySuA{_1$X*lE+HLm&yE31o0{b|hq>Zlnn@xO@d`Qz691*)XoEUu ztvKg#r9F!pseO}ir%2rfM$$!-nl>`)g+&8vUJrZ;=BDp&pNLDLeHg``D5BIj!JO#U z6YLWZa22?|(RxyV%Y4CRqF+|LACXLFfu}UGsF>jq{JM486u!$CG2Ldl4X${5(_czd zTYYmyvD{qc6_&B<90cRvJL~^s5b`rQ~g$<=Mf1`SUEAr}{4_?E==pA}aj52M6T+RIqhlANVGo^-4nT06r#olj>^pKCn(PAuG|6=d0-xW5C!@=3y;u@?spGhM{Zy@3kbK z?G60z7(u?o?{*HMZsNE3ZkMgioLYW9%4<>dpWvvP0KT*rAb?smG$C9Oqo=VJo)W6Zgq5aHvHvP4Fwj-inw=Nz$;h zT)oR|rz`AtfQ4o|Ip<>iPudOipKCw$Rx6Jhm*_uge&Y4&K?ySK>CHCQn1}+QCpO&(=8rmj*Z9o)Uh?VDgTnl%!+nuOn?&X}DFu-+? z2#?bt9HpNeQiLBtz^eUp+2DhFOXN?7B5H5Mrp$Rw#^|@r-acd%#jP)kGJ~NIts@7N z`3V^E9i^BETNvz*Hwd>0?b95fictn=_O*H?NJsWppI7~6nsate(`#+RG{?68;b|Fd zU#hv?xE-&=CcqVHvcRT3(fV$rD$cu%?##_8W#xrv9nf6GQlD>6%&aYkzDs`(tDCZe(29{bZ;CT=c)iX-mXF+6|=QP1K! zE;Quc+{ZqD;eivIS>@nYMZ5@cKYn>eCu#^1rFGquDw(Wn63T&==(+b@+e!s591*~t zKf}(5bI;VRYXtYz>s**~j~W=^M;k^uz6zOW<`xs|fZ?4fe$eAL0#or5EueWs0c9&K zWwji&gWt=Xw=5ui+?ne;KzHtQ`yLFVQKYhnZB4-#C{oHxvqrE(FUYs=(O)$>+q0gv zlR!2nb)l>O@c!W!ajWC?_XV>iFm$Rj4;{<4xe-JE$t;JRf>d8xLMlrwbzFh?6~iB zm3Za~Q%$B+T=tyXQ!{CtOH&J&!bozO4f$i;BcEiA@c-~YM$wfLNaST`Zlf=)KbB@GJ1-YyQI>Xm1r;yb~ zY@&?pleaLQkC{U0wLSR=lrC>}_*oAaD4J!gn_z;fE6ZjqtZ(}Pe%6SZMv=l+tKGiR zq4Ohcz+u-5y%-Ug4vo^aG}4lpfG%O$@M+Xhm8tD&^C*)_o;!&SsGTSDGH?GHq(gUw zYO&pFGe+n9s^JtzsN6iB>Xi8pmf_uYhQ*vJpmNb{qtq4p^92s(ZWCsD67^5fvCLoI zG*Rfs&9YXt3azjKP34Z=$x75lvL;8%uc!R3A8+^^Hk~hv`N=j3W0xH#shoqtYRjTC zwyDPUT^DDR@QAakvAx|1gp~0nJ8X)D>Z%uAKGqJ)8L(zCL)~OrIh25ALAf6XqfSa$ zc8AY?SJA}`2kAR%NDY~X*=eQkDklRlJ9Bm@>AuYH^KB1VBWH8ZQ zsqum-`OFPzH94O;AHd|XE6JjrHf%$yl#)D4E`rDQPL80!-se7*hyIN#$*VyPqbwwQ zh9~rJEL|S}M?N$Li zuSl`&;E+1NX#&TAKVK$VrtG$3@p8L$P-s60u0sAz7e?vMhR~*od}-*@mO4SkjE0dY z`zY#Mm-A@X7xdqRSb6m8Y>p;2!^FFLyO>Z*)DpYtbg`o2fbQVe^ygPA9}&iV*@sV9 zq65C|FIPAXiqE#cj^d}HiSc^(+RKKiNpS^9KI#|&{C`?aeICoh5yY>f{_Tb<5)WAm zaSCgM;7hX2(6vB3vHAq8VJ2D)2AGq1vv$`4%LS3O1KRZyavhoj;@b5*sU)H zf)%!ls_a>#kEHLNDTXWUHj5aH8q7R|=0m+*AF?T{De1Oz-xvfd+&Xj{uImR8M;tb| zWi&nrKpW`=#I|^!cprJ6&^DVXIj!qESFDTorsx-J+vt7leQtdSeHhzR+t|UH!2;V{ z+sNBY+eF)`!LpEbP(rZ2L>KS27lN;YmmrAxIPxKFp^U_k>Y?;te1mBraUn#=Ai{#- zr(uO)K0_jq!FXQD*Fi2q5(X>xN%uKG)`V1jmpu31K;-9B{ zpf+KAdAEgw@1Qo}d_}jRgVCTw-rcipQwFm_1d?yZKzu;H$LLFk>OsEv9$W_zNWEPJ z@d4#NGtl`1(!D_65_AvbMO?58R3PWJA;cEqJx?D9x(E6qC-@vHkas%(Vhib>ZriT! zP6o1v^a48A24V^-C~*h>vcYD^!}y8Bf|qQ_Nl=7FWN_>Gi#L+!%U=nJ(Lpc2Pj8tY z;{5+R82zUjMEYAWnE+%x4KMaDaQhbcB}gwnLLdMM9m6>x{qK?vZ?VrR#Q$Bb!KneB z?r#zZ=&i)V^}jIcTcno&blnaA<6r!Crx%_ZVCX`q{r)B1#X&HuZCIWFPJ^v**i9m5 zmd7rct7dPgCeEWkMPn9XVs*1P%h7w#M8a3H90RS3qJWH?>isU{_mHelh!P*ed2{b^ zFG3UBu)eH(IhfV^mdnq1JrQVQJqb>DU4J6!<8M>X9uj+J+=eF&#{#o8bjGSsDXxPe z4PcKQV~VTy3@@o-vcl(PAjg$Pg4Giqnf1lW8Ex{6>#l7o=*u(5V$G*A3tf^&&^+av z5MfnlBQIcb9oJ!2o;lPSTU4@WWuqaBhMM4?t0x|IJ;2(~{)7@CLFULf8K$r4719c< zakTBQFm)JvsjoJG4f9N@guD9EQD$tUg|4v)sGIzuZ`5> zB$FF`ELix&B(*PI+5!fTu-=_JW36K#=W4*d)T%VIZjn*$u?@BLXTkvag#986Tq&~R{$bmu;E#%R09BT|JcgyvCnzC~;G;Nu>e~pFV)8?%cE0={iRh&_-j=qI&zISC% zx>uMdb&gIqR?g`w#n4>76Hh1?3Xyy_`GadNYF;EEyMi-qQgBEX$aBx4#0;3((HNE~ zj!Z2j3ql-tR)|D8E)dj^J+RK4kn(URow^rU)h}A)^A*xw23*-mH__RRiK8s^L+dJk zBCDx5lLb#VCo7sXIoiuf(VlG*mrB_eocdP!F+5c@dWim=utFC^4{}Nl-T$ z!K<|(vf5`)a44Tvk%i2n+hu+{yh5e9Bq_ZhFTKQf-X`&T3B!Mm)qj>~-8z!q?-@dm z9wss6et%CWa*6BwDz3clp!#Lir-xm|xcQ3p=oMokAQ|gwzU+u9pkGk@^=~5F2a|?D zz&i*C{r`V8hPOKvDX6UhzVjbi_I6Vv0i|}qi$VT}{rtg#(vgo4aMPJr;NSsHk4f|P zYjh@3$I`Z`naagH_LmgC42U}Zs`eK)Ocs=)ufuBIzyczN^uexk}77WEDA6y%wYrgkaR*g(RM316GttMC`U?!bd!+jqC!v+u_55;0O5G56CiK>8dDO=9Aiz@OuM#Nj!li^QHsl zd_s2*#b1kZadTm6TED*W)t`))TrOY24?*$mV}4~391O?-^7Ry|HM!Yl219B`73#)5=^@OgXxzl#t30XE;N+)Th{`~%k}q{dqir^pfFe3IALEKTYY6S8sWWGmG%)sDE+FWKw}QcrFu~@!!M7`A@n?4^?%qU$W0I7?w`50c0?5PKbGGVNdNB(J)KlJb4q9AxJ0XdF!Nx4G#|zw1$U-{oC@#opccycsP(DGyGdEkU!S{s2Tlt zGF|K#0XE(4^bIeC)rJ@OZ^Yz=PXr)S19+u>6Z~Tv^k!S*KZ~F@RMYmqCeYj5t8o6a z`S()(JCKPu{J^{aPX5^nq_Zf)V}N>N;Zy$E`zwa>r{|y1kwIv;aFp2pb^jkPT2Byg zK!!5#E&q-AXXVI2Z?3&5yZ-gy4O}JwB?!S+{u}6zN1(TXGU5Jf|FdYIw?$j~PbCMG z><8WOZ$1ACA-&a#daKK{3g`FVKOHn-0WI*)^xIGb>DC|wd=OD8bP&vc_WpX8Qwxs{ zLUcoTQ*egKP=o zVGie_S4PAFg$DGp1gg8CgO(}C+Hg^c>UQ5C+c@~wL;kzX*s+?Im!F3shuMdLQ+Gl( zbwZskPm*DY=!FB4s#b^X#~R)}F~-4X;Uohq(nphS}8Z| z=qmMUNjH?}*FwF7T?4G8f;N(2SS;TBHuPa-I%gTTm@FqtdbG~ejfnm=_4OTdAOF7Y zG0DgJPWAOq=9oXuyc%@S@PmIqR!~)XUD?;Q^w*stbke%44Y(EJy9yVNK=x;tYGxc^CMS3?seW%`P#bU-^F# z0`UCthZ*U-i+r(%9q3HHc5R7W(nN#Qy5e?;vCa#9(cI39?jeRF=|m(h*`rm}0;6|1 zvGR)Up@!4xdL%Bnqg~VjV|E3xwu zr>Zw+mk`gaN^QE0z38o~jlb36vgK5Sv)$q$Lk2DvhrO?HaSp7owbEXYH7jj0k0DW#RoVz;rh1u3I9e28^&f`KTz)$%BiTiMho4Qv) zz`OK7h##;DA^`Y}ejr+s(C5v>NZjiJIoHqogH)s}5Aa~L;qoLPDa`{N813t{?H>eK z=gJM3kRBMiFDn;RyiW~OP3h9Qk_W2Ffg$@y>R#FVUyA?%q5IlE)~gG)4@`dCmG)E#`G$;s z#2t!Mb+SGc`(x8_3Y%npN>^?Bakg{rSju0-C9bGCCV+K`fhGG@`3aXeU|q$a!hKr# zpvL_&GH?YjkLKYRm`DDQ0jv|>FaS>hpB=$dNzX=F*|ZN2zz@NjNYuS@S25JRQdf%9 zy>A5|Ugd(?_jTohs7F3fKP&+2lAj6iVxD`KsTYf04Bk?&p8ao}6Q5zhE>h>pz%8Z+ z=A#WdKZPs9nSiW)kYW&=|9Q$Y3;0~-To~vAd^WjhRoJ9?u)f)(eZT>O3VpKn?-YB8 zy9KELVpni8Pl@|ziZAf~q^ZyBU{cw0047kB{z3C-gZ^O-C`$Rz1QexxV3`+YeLy*-$I4taIWLrbBJvNJLwrx^;2XDD`5Ix#A*8o}_L#;sk1 zCcYJG43d_?{)=~A zytcH3X%UFLi%BCDnKfRf9!tNVQp$@+aZA4L^uY3?r>(rEW}B7FM+$`RKDvub!vo+0 znm**#!PqhTl14oa4O}|{K}ZbP*oYd94C=I@tUe`WD}z+MO(GSsqG^tLA zm10TS;8Hef;|3wd0cCAKR9ZxYTw_Ivy_+Ug7qUROx@eNEFqaZvg__#vb4RJ`9Eg<9FP9dyfW1A(n0or=(EYz0OshQEC)P^G9?R=_AV7Ftoci(el*LAtW= zmi_dEXJ(q!y}9AQcD_7x*sXr6e&a@$I-N^8zoL*Emd;3b32WvAoE}RBT%q~S9g#JF zGTOm~o}fNU-dG7>M^3Zh?u7eBQU!G;$DBeOVg7E-$xSG;uhLe9M*=b*#lfH+-61)t z^b|P<`?3_adbmqtlodf+n3u>Y-gVhSLr#QnR-0fkKVE&8&Ly7aXwG$9F0L(-ql!`6NJ0x*ce^iEtKxR%J&bX>6<(7cWyh*MvA(;-WOL ziSu`z={8v>$rrfaMgI6HV{$MK7Vfp}*%GL2`817M=G#!?3n(4#3rcL#C_?oLSfwnV z=MwbOew;KqYY60vD_QZ`@lfM%2$p|UVaKtf^q2#{b(7 zrdoFky&svVra?^jaj6TXok}XNU)p``iUlej0kUQt0KJ296)*iXo8xX}6l*fbGRM&# z0_$r_D#dpErIODxq%?btqSAQ^oyg4_*~pnE7$yp#tqrZ5%x_5hP9Kv1T60caK^9s= zf}IV`xmtRKhw0arI_Q++FH)AkRlRZT7`j5H%0Oc7mGxn~RRKY#4%Ue%)v9cL$Y_BW z0Myfske+J7OuD8LnR$ij~qSIg=;ivmP5*T*a{x2VIp&tTiT;FUM2XZ{-Wx3&P(E|$+k zwUx}T4VKR^p%7TY9$L0$_uNEVAaeq&OW3)3ZnP}v1gsBAqZK?n7p<(tCBHA|0&*R3 zyz05IoIe(_^joBNoC8K<2&W# zEY?_H*LAY&-4PhKYN0JyMMBAB3-~c?xOU5lT#GfQOfZVIKYq{ z9XUAbJ5LnfVV3IpqnrzkxJMvnz=|nBZ8)j4l&_k!?F_AcMSSJFLgqCu@t2*kuYiU} z1gN6`R<=I3lkl8{rifcj9^E(`np_`!1UdxG`&JF4>@|T>FFhRPx-HR(3@|z+$L%Ej zRo0d`KX?J$t1KGPS78VDfiAC&E4SJ5}v?n7YQEU2Ai71 z<;tio9pT?7#np;8;0&+OO^Um*jP%6z=&}vN-I&A$eKzO)VIqA=@MoVIxr>5TSLBO1 z{6x1YbBP-5bDY6aU`L?}xHlT8Yrt7FE@CwwSG-ZuBT6l~y)4k9io4ARnDYlMNx?lf z(FlZ^3Loc9t17KCIo|mx-_~Q456jEqwb90Yk?k<%S*|qiz(vi-DD1aE}&k)9?{gaBh#~Q_x08cwl`a3?XrYEwUW1 zf8u2B@v&KEV@Wv|ARKUT$}XLGMEmGq4#7p@5Hey>X4ctum^xldSM^1p^fRzub5~iK zZH-6Fg=xScp^!Ss)}kKXn^qc3omBW9Hs+$)q`JXmn&6bH)u`yh?8(l1wYZ-vs>ttL zY!6(Okui*C4Ee{YVI9mr!`o9(MRT*Kv~#(A#w&G=q^o$61&ATVm=RQ!_S!qX386>t zsdMGy#hOz^&(J9x)iFR1tMeOK?5PL5i`IyBr}Hp|a>Ngzwkp6T_zhEd+;ZcIS6raC z-j+14hfQ-4?tVtkjU!Won;FTP5~F7n?P8ffigmQX0&wbOdS7!MvT zrmn=5f&@EiivScub$L5@n!Cd0%5oD?J6!I0T8!y70>SW?GmJ=k^I|@wB9JMPuQG*K z_c6-xo%On-y|vviQz zg6<;#m!lR(a_2x>EvZ567mSIx+y-An<=%{1VF|hACV($uHxB&X@c~lSiGn&5#SaI=X(J+oA1dv7MJKNQ zg7ay6TY%YU^m0)^DQ<>Ab`CF-#*% zBLG+0rVswsYz3A=#aqBgi1!1RMGYLyU45v<4R(0Aqj7^sUU3s_-w4qvvOKvRWm-v)pBZp(0`*t)E zqmcSj-fJYV5OhOkEyS%JlxI2`7x;~!bOXlpOt{!Xa?xPN_3>E^h-yt>uWgbxw+}{Z z6XwNg4yuQSzw}JDv8EK*Ux!W;bDT$M!&X_SpOP2NefN=W+)ad$Y9K!#4|8Lt1g-ln4i*_{!Xzl;jg@l;-!x4Jr7`m zD4Mxfkg_USIC9}T`dDz2RW#{a4A#@<_*$Ls|5?|BE)z|f_yFAnu36et~aFd}or!S;Z37e~MASOn)KuGxCT3QU6-)DbT%IP4AUIB5))OQ%2{J{q|(`Z+!7z z45H_-<61WGr66jhWs*u$gU6P(Fl<& z@#wL%leR+RX4)`bA;?=Xa>WU_1!iE%W(FSoybejtvC7O)vB=@v7|BkI)R);1ML&L< zmNe<7a)qe_%4&;?yw9^0MC8AJw@fQ_Lw#^xn3PSpI5sBH)e2Nv)MKB#^&=1DK*d)b zAux?G^-$FnpFDJ` z%e$ixa5R0~N-5i-IeRi6BV4(aC<^tw^wo_z30&%;IS0Y&)oAeQ$W=8X2XlGc{x~MU zef$&Xd0R~n%Is98Dk%VVb~}ZcktpI?3|$`R-MF(3cAlo6Z2+6F%xoD3-6BMQ1?R4l5%0X@Z=H{5F#7(Y`^ce$>d4Q5e-J8F_Kiw9M;!OGboRn zI(Mi)=KTuouw`Unt)k1)SLZLYRH0_e?9bq2;C>YC3Vnoc7XV!w)XgLu)AIY+ zK0;Gr(IyunTPFfsF{-GZYHO&IV*70Oe*7G`w@da*(#;5);1$`XcWoOHJdETw}W==NDITnt`CSn$JSIi+iSlJjc)Hlz+p{wBGto%5bF)- z8}m7-o9zS2bKX|ITb~D)aMCJAWGf~JSbs|av!U=$@PPp8Tle=gGrjrMg;@45X`WK4 zL{&mUv+tSml2D3BoF!`P>n&&P|7LTXpI4-V6N{y1leyjoiVM2s?^r zQr+o52lqDsFXD&j_8qyJCAXJkea@C@%1&LV>q4e}j4?H>&9y8|eY{l)=dRvIXX&aZ zC%>|lUY_N-G5f(${cxP9o0iP5tZtG#YPU72wFrxRp-A^B1j#!qG zG7Jfv_h=%)!Bd}H$i5j{v^k*MF%1f@xlXaKd&GIZZT(UMLeP7rU0FHSV^Hoe2D|57 zSvl7MuXtzQBLc#AOzhfp@y`~%dF@RQ7u@vz0J)!#2i6qy#+%fwqeKLJN;;Dn>;}8K z@LYiK+TtQatlB^XXHF3TojaRmZ9W8N#t{J^b<#V$9pxL7@2vzoJcApKZFl%*IH|pG zq~a-^6RzjH>pvqp2VF_o*5Od@$iI7+ph2SnN)pN+eX#}-tinknFEI6YXbZYj@sE87 z9z>P%)X$n^J_^~S*y!pAi=yq|BL9wwcmleQxwdE>o9LMFilor{fY5^$Tt9HGFQMF_ z41Sz*-QrjWq1+JOwxB+?NJv^mV&NYDVLcSguUt*E`_(F&b=h7g$e?W>r86yXe@nkEp5 zCJ@fm%tj)2A&eCAxSrWCH}xKu>;-#U*M@->Bg)$@RX3I+a1x60-x>VT| z@#JVh=2-{xR|vurWbF#NPyKt%<@ei2At-KeNbJ~BYH)oYTeW9q5PhK6p1S*G@a(I=;BUJ}|x^%w0{` zo5b6~5Sw6}&0)lIn2Sva*5+`ZmVqaTXR=_Q)^MMufu}c7hrZ6`flk96Xb6$_+r~~i z!qpf35TsBS&effeq%i(rPo^dxWQA&q54V|%aZASxh-}&2W(%kiP&sh{aHj;qr!o#M zW40xcP>p58jib>-Fry~N2t_zekUmGKvoV{$Gob#cc4nnG+Ye0 z#CU2Gfq2i-J+QbZ6n&{|IYt}8nxa6bp3AAW^s!I^=hbQVC*MhTn zm#!NTnHT7`%{I?*;eq7#r~u z2OY&dBF9|!?NW9aOB!{>5!vMs z)`cS1(%i?OSR~r^v5&BTD68B1FW&=LEi^@C4PxAc_W_NN+k2;<6Phu$;72c8hp2US z z3TA4d&b6ctg800{G)S|8uG)wp3N;G$9tG>{?*(TAdCWdH?E3eI(Zg8U6Vi|275Y@< zn2yf5VgUkSF;rT{%%i#A;5nghsQeSrfe49Kt+(tG2Be++vAU2V6F4FphydvAHx^b$ z4)I)#cNg?1e(Mlt^$;n0pySqb+dlz?icb8IhardGHio3g8i+tOb z_ulurf57kLoFp@u?3wJ7%`s|bB<$bLAg!kl`Ci30IJ%e%!x$4uC(^Mmt) zZ?tdfSnKxio&p+nAKA~N8}(6-ZJszoijDKiZH z>Duz;b>B1`W(hyffp7uWs5{-L8;>Qsnga8Lo@r~xrQ?IetS*p#bdZ3o$`ycgv3Yo& z#3q^EGku;5hoA(W|;?eMrbNb>QTLZ;iGr z)w=|M_)40kkC<)!p@@f{UtzWHe(^8`57kD#%mfNnJJ-7|smWhN7rou^!Giq_pZ&r^KSf(XcZE#Peo6Tn zfL>p*;ZwiEU@`Jhsa?`C`N^jk_T6&ug+Ao^z-R!LJ~Fo+^^aeSl!5EBeeSh&8**cS z7oHkRnECpTl9Pwm0sgXT0qyoXDjQNoe7Wx-QfZQrf4o3jbbeROd4+<|q|SzB(k$VN zeGj2|h=Txec9gXL)yOFOhikoUangRT(FR^NC;-VWH#g41CmtV*(HRtkD#iUu8`j-) zA_Tq6LA}(gBq)ga(ms5Zoavr!MA{W1fUG-WygxoLK68xJfs7LvuY2QE!spr3J?OGj zuX5HE=(<2L$i&-B@r$H!pw*@5Y^E{~7*=(7*gXGtC(h0$jtrq7m3Yt9?IoV%S2 zIL&m?Exfx1*a$0$NQP-nx%dcnGNB)3T66>ay`w+lm&>;t2m1eXX{Ou_xdN7d2Bd3u zj%)AQlA(5d{|k zYxK!RXt+Ybe)J9sYY#+RUh>JXOno$8+52{x76~DDZyJhuXb9w8j)}gXgP#3X1dBKb zd>M=nyEHA-I39Ar$Q&~QIf-|$tboljqYY^&0t@imI*Tn^iq2bY)U+r_2;N%~J4$aJ z&c!8rrq=_bdAgqN`j(A-q<7~mJ@|qC`!f`tB)hFFI3CO&46>ZEF%jB}de7{405tQX zMjN{>u^tq=74YxfDlcGIYc!p&yzEVg?sw+{ez_{$FG{R2T{9rPUz0=cNCr6F!o6Qp z2wj(M@#*PqJG}6w+3z&kc)p2yA>Msr#Cc%)0B{_AG+??=UOF40*@y4x9-`$NW;;nF z=o45K5wIo8#oyzqL4MyUMfJ+E+s=jaAcM>cmh6;+hv1VPLzL(=80i1$W>NHmN>>LI z%Y(vgec|%(aFVkH(?y5xlN-q>+?n zy3lN`{aHfL7vSH~(zkn_HMnTW7Ag83;y32E8YGu})r9DxS)qvgfX5^N&B3lU^<;oX z&{et8_n*oe&eZFW7u?C`N*66jpO_wst}t=iqI`}*>?L42eU7H@dAc(d;w;I#6Y&wk zqpS^P8dR9%Rl|-NtiOF(4N^^koh^rDY{ zwvON-;gb%=E?K119lXVGcF0#%HG`p!`GJX4eDFSk#gtJK&L}NKTX$rHte6f3fr zyX+)aJxi(73heXMF^5+}bB;&1qk|EClCVEPqApE9wwWH}fuwaFgi#Zxs;NOK?AF6g=sWe#VPA8$O0qiBo21JrWz zlCG0f44+E&XK0JFV0>q5{Sh<}VSHWUj|#Js1*@Kdd8H?PT5)(eTrhNe5id{k*srgx z&FHFqxqNRAtBQ}iy;%viIne~$k}>L*r9QcF;`X1B^l9U#f9FWtUhpk~`}s^^haX<| zTbgWHA;At>dw`Ibsy1}k`oy>{1i&vcVH}$fxwyS!b4RW{nL~=dpy0&nov|{SL*iby zKTO#aX=gE+Xnz8A#pE5%H*P@Lwm`Q-(Uf^&QIo*AV7v3-?){@*hqQq4r}&Qx%RAn8 zjE{jGig$I$)W$?AJpu&@zH;n$G^gDHg-|EXOToUv-rw2|g->+x%+{ylPXJUrkVG=L`HbdFx@ zxjwKsD_r)3{>61JmAeJ@i|<^_a69;hVJ-d3aNCa>56)j?=fd|FIW9!!0|ZaRd)vO+ ze)p!q?SjXH(BBMvh>wS$>rDWJW@MhsncbmvBR)8l8-0s*AP&?%*`mo85WhLJo>CyA z@uKzwK_EuIf2jV}2fQtqXyj~<;zU3on7_ZYj>;3)+h5VN<_h|E}W=GLGD`xGCH zYxbzjkV;(7nUD%f%k5J|E9gEEC->e(=7-1!h8XJg1FaF&81%>Ln3+fW81^T(q2MQ^A<&93)cE8uH13nQ z&G@Cpl=YJ{-!La{&W0|*eH8@HlMa_^cTNv-Iu&=#g{n1OdpZk-nC>l|AXm7 z;3N73G2jPxfZ#U4P_Apr6?PWuL*xY16NM!^U=eq>hD-B$b%OQLb^`w4c*6DpeQn<8U`gj2TP{F$xonrI^|z{*O?ZU5SPTo23sV( z+SM))GWf_d!Yh{VBjl2z=nqIepfp6|-?1$y^-;Y^Ac|ZATtO?7zoPlBh!C9Ig?FBv z738*c9h?)=zHgO`6h5Od3Hxn@>hcj~;0%v>wnGoWIhQ=7Z9YPD6+1Hi?A9cSmjcQC z6PoGD@_^R80`uB)UE0PMU4p|GwWMYMTJc%e0C}vc+@%YODnGw?x@BJ49xkPY$6$oh zq_Rm#smjN5%ZdVK0G*Qx!*BILwVOzi2jO?49nXs z(q^)abn8)X*6RzZEZ=YO4$TPjHNP+~@5nUwZ(-h&VY_RW1tYxjj*lwT&>b*jCrf={zjd~W(8eZhbcx(P8-e0=q3IwjcRqf zAB3p)Hj3dI_Nfb19kfkWpCW%ZA`iHos@97B*5!-aM@8PfMUCA-M2X!C?l<)`-wJOZ z*eY+Q0GL=B$nj;n=Xh|OQ`XX*b6onY@oxpU@Au1k=7yzSccRtoJQKV9X1mO&$@S>t z6l*`kr(C;Aj&%2F+~PM>Yd^O|BYI#&BYITXLSNV4QZ>wc7`rcc=)Dhq7`@MaSh|mV z7`z8QOsq@$oS##Cxk1Jfe3T3`d;J zKnPOm6zl@7=bqnVWBj`OXgCrut^Y#VL4Eo_MPq`Z8fQ2qj^)C5aB~0q3CdeKe?gQD z(1mmgSD7hCk~zQG53e|u zlGe7Uj8dDTDS=ZKGhMw4!0BY`DO#V6Ji2j2{c{&FSqCvxrpD>HICX*Q5Qw1@Q4VE8;=h<-94Zbb_!k8sP$rI`s7M495tzhM4(#9@ zs9ukd?05);jKH9ggeG{gB(Mop?3%GzQ*KMa<0>jp7Vo&QL{|kT?I*xFkpR-g87b;V zFuT9S5XgRoO2HoncY@cJa)4-R8zy!7SWbBlw(Vx*6Gl&=7-zm?jYiSt_e_CC)h12m z8OauZFO}dUrV%$eOnZf?E#FB-6`wn7y~8=|h`iGjo23ZV;wR&TIyX$gCd61;IGpT) z)e`YD(Unc%MHbzRUtj!dF_mfj@qzV@S8Iq}-hLeZ0o0BJD6w3)fr3McW}@zaS6#dV zF^v~%OY)kGL#cZL?*XL~)vDZC33Bc2VwXYw2|<;G+u7@1x&^yoVS+W|yLWX~|Ceq7 z1fANi`**lL(Ttz%->G;|c4xdqMR8nUoC&z;zlT6SVer|vL-U~2w6s7#E7%+J0+b(_ zwO%`$`Hh6|r*ZwqjO({!`CX%6^r=&iV3?_0`5>ADUlSPS+u43lH>~wB%Uo|29X-HV z6B(|dQ}wDqvEOvr!3$vje{E6$9bm9PI%2Tdw-f!Zs<3#egwJ5Oz*Qcwkhg9?da|Zo zRD!r4jdb9E{}Por$qxn0I|JkUR}sX9U@fFb_*dc25dO#p%1eV8!~GQt%9l)=sFV#` z53qUvCJ)s0-=QF;BB#M3*0Cd5+HyLjOvZm044~|3aoSnJ4O846%bVR{x9|F zSGG0(2?5D{GtNW>D8=m$V(^jw5F>tov8GBFg4hyLgJ918v;=}ol=i>6u-3oU$^4h` zfMW+>L~rH%A7E^$h}j@A#F#Lc=o@(gbdw$knhK`3KBAyNGOCL~q4D&0!MNUT{+WhU z!wOJ#VQhTx&u=phYRQ_~o(PLoKh$CPUxWN>GaDW7g#T?!n~GQm;#es8fWtui7bP_H zZ@(ZLL8W$Qz(S>d$pwwK&H*g^pTbQB;K6UIgFY}SfMu0gAryWH?cNaLNK#H^Fkv?^ zZHItfIPd^)crC`QL~}&rAR!KEd9?1=i|{LSkJ?e)N2AA+t_Ro%ey~dF7A-Zm5^t|o zZ^hiR45F^CFAz+Awd4p5IAubW{!S|_Qz34}s|pD}^P3uCqJ#~yd0Jg=4u)Bhg7Mv^ zetw_I1Ry^&oq`fYnTgVfQMcf?-Uo3UJAcqy!55X=bwna4l}Nk11KzN4?pUuzndV~z6d5Jaa#r?_pxsBuAqr;hRnA8 zXu#Vzaz#ZGAOW_hqHNxLom5JlAixiUrFqP3|4^1zgpaA&j83C*G*ilBzBe45px_nX zCgCuCICfYTtCe3BK70=~-AB!~>A@>ffD1Un%v10yRD{$SBL;TPOh1 z1pGEljEpcJiuIt|6u}sad(4>76XToTzE-a+-vAwtV|%xH1Yyt}d~}AJA1b-)>`_@^ zZV6~C*l~P$c<4i4{bnJP*FLLx@hX=NSDu{win(&o$&FhP>`9TB!nm-tir95sAuivf zblr|I$#_CYSnVeILyY^el%#P54kBRJLH%D>{l{Yg+l|1p-$;h}4_#bDQdYTTR zbhjaaF`@qRzklD{g=~;VxK#zid=v54&DxcL2xc&=<{QN4b2Hu}wv z{pqFNdMNTu-#@Odp5a>LUk^Z32XNxICx5(ps%$ZcG1#yOrVIbiIDcCkdgiE#b4o$YhHtvTYw=>L-F{@2yoM!~|@XBkib8|r_SG$1?* zc*DQ0{(PoVFTR1M!p#Xh`JecDy-#CrOYi^KuYRj$?`=#VGqBYg^v}L^@Mq3HCj42k zC%`~y)c-2*XJG--+JJ-dmj5Z&*9LOGnd^T$L>3`^vl+<5Y^iQ3u;}$c8zgV{{@VIm zAuN0%iZn9dgn4mf#{w1t64pc;jW_`91T9{cM2a-wT}T8EdE&Ra)cQ7|SueGQwSob% zS<(V~t4b^k&S6>+{)@7voN7ti>f17nQ{!qV^5@rdJETRFS%UL%@7LFt-yY}bfxPZu zTnY#pQ+|=$op3b)Oc$YWaG#5#Dly8Mb$ZyFHTh_<|)1b^swER1buEK2pz7BIKK4vc^RzHZ)4?rN_NbQ;=si>d(s*_g_B?& zS9uD8{j{@*gqw+TtFYIe{K#4>@E!vH* za6u54*5IPP*QUQJgr=CtD(OVT$hDOFwr6W2p|a}fD?G0uj0-tXbsW-em799|Zc#or?qd*w<-13XIgA^4RlFlNnWQ|7< z#Z)4vRY+DVmP$^=c$za`+4X^SCQMTJlQP3T41wUg8iT66qgqT?i4`Y_=Xn8+JkVJ% zUP3Ev)Z7oShyLHX(;=9-O(ZSfsiKWMR0D*JKc>J(4+i0qA&>Do-FjtdWlw7)S%PDK zf$)OBqlf6C^`}Alm7_YEFa4Syh8^V{-CpYH6D~03&H2iXb8)HNCH7C_c zg^|zb4pPesu7{Gaz%UE%31Q8E(H%Iy2=MEA9UJX8x#`cb>B%y{pgxU-GQQU6w=$ZYj#$ zGhhM+m(_Av9{e`3%O2p@lrJ^gE4TRDYqlT=UqX;aTtMdo6zd~m7s$zeiE}-+2N7c6 zq@ebItFUv^k~IhF&RD6;h=(^+}dXXCdT(m^JRy=^es@BHZo0C$Sc11uCi~58I((;tgnx3Gh8u*i> z@4|4Rs*-rbl@)wQ0HY-hW0{@Ky{*U$`;x~kq)eJsbteO8l7!mG|&LMmCLu8n#N^78hhWNL6*I}Ow3v3V8!`|{rJ0djmR!hL1u+LKZJ z+woHc)apxwmg;y_g$ji^@S#VfnL^ePbIg|f&NV1UjUb!I zfj)5B*ihI`8m`{*vL@x*k84^y`EUn~`4ss+{1f7r$rGiR1zB4YgrO`D#V@ z!^Pi0C!PBTXPz;RuLU`(L&S&o9dwZ}tC&$$7H0u=J2Icas5BvaZ{w+V+sxaGo8TGN zXC)SRA&z&VpeCqzc?#o+F_(lpqZCH#&csq;chvcEf67(+$-gEm$e0|+laF~A4lax| zkEn#9K(seRykoBhq!^jC5c2W<#M2?%R8Vq)3Fm<~Ta^uut7k^DKb=uP>M3Zm zSi)_sqW%4oQXP zW$-5R=U}{GWZBxj14em?o0utG3}z6bN`{`C*p`|n<`1i|KdU93`_Jy-=;j3V`2q{s zpe#kTq4n5ln(;lH^`Li_u2$m`hOc-(Bs11T0yztPeBg3IoNDM`#htH`I`D1KxOwB2 z{oBc}Qmb6U?RFbx0p&cj&h6YBBlV*l++qyj zBrkdl?!0W1zm}N;!uDOz@2l2fVhdT?J~&7gk4lMp(vcW z<1te!m}ub({7mAdm&fUU2G|aK^bkJZzS}J1AkN&6x93`>ROu0We@pQrCf(!DrSN1dffk>L;&`3n7o0(OV*>v=qUbvLFJ3lGExdlA4>*s77rvn)Fr?8W~e)=cE`R#RiH@ zxhZuEWgYNN{#x|POPGlv zgI+I0>@5a8x$`1w{ustW{8ydL-dz{V4w0lS8D=oeaO-A`tbpTw5xtKSJv^wr(OckE z*z+3}j_3}kz%7khDEln~JCwH1p&kgC{ofbp4f+83TfTPr-(UC>pzmdZn-%dw?0;CT zd{o~8vu13PE!`Hj#!XOp$6KVnK(p$XAWSqE*#4pGA>xIs zD3fba(?F!i?R3#VMl{JYxb0c@PU?J1K@O515&?IdMaQfv4mHoF0eQ$xguV3Kg>jfnq`=Y>zuZ278FQpuV$S+?y?aEpFa_RJ6p{_%u;>b%`{- z=zqAnt5LX+v*~Vo7RscWhiLj}oAPc>s;jC+C2citM2(?3AA)Kb_99_#$zN3^O;l_T zaCL}LK?6p>%M?4y%^v>fqIEU_5%Fk;CrDf^P^9+|=Co=0;}Bi0uT)D+afS6DxGjpX zdHf-&;J35vkcw3Hg|LEm*P@f@3LZKE0j5}%L44EVVe(F0nw_-lE-h}V*f^!!&t`0S zqx6;gLN|yxOLw$VWodb1Fyow;vb~)T0N##8afWS~Dn{lIHfQUz)iN2Ae0kDvp01O! zu`7#OVH*xp8@OA<4Bf;IZC~$Y(k{vCg(&Rb$t?1?np=EBbB$sB%$fjpu(1=n9^8iS~qv(-%Cm_y%mKRmwoz~hfv5qR_V^wC~2S@ipH{)xH}l@ z;rBxhCTP#*y14rl><_lhXySQlgn##r0O$Wg+tj~s^3VQWz4KY%8;Sto0``t6ADrQ$Y(SrGFu*_D2Lxe5_J2v{ z{{W$sv_C;t{J|98FxP+fJX6QwVbSVmijV)Z5%(XIUEgk>^;Y*Uz&a`dA>zxQVE?_d z_Xi1~*TYm7zF{R0W&;6n(6Ca8V?hu0{RZD2{0|NSe$oW*_|Huc>;r;o54=Gu5Dxy+ zAtG>38_fEx&R@|}WgyXE@4*q?D%J+lrhZ5V?c;rf1k--g@jnvq|CkVH76`UO_rHks zpH6@hP?#3ZV=#s{bN=lc1l3W1u{B`Y{~un``5U_)*r;F|Tr#=u=2lj2w|85>DiUa;> zRPSgt|DWmk1KOWgIl!^u-o1l)_wEm_{GX^ipbL~#=4x>C{|e0WHMH@N*L4j!lxH2_9h%BVaah6D=I`n?#B3YrWG0&O!nJY<61 z!s?WO_rO=Jzyd8(@eFCU2&3~3-;~KUZ%N3jiF9vZu-N>)_bXqJuEoSy7Ps@SG5uWr zhYiMeT)j$I$d^Qk9+SL+9d?yXP4HQtAZljJ^2l8ON3#V=kwLV(mj z7wbV5Fc)L#0Qh+FA|)(4)c5*ws?GGn7}6!*=nuvKF5zbF@SOTf)5ZMk^33AU@LmyW ztwqxms~8^`4#-&O<7s%(3+kbsA7VXFtxGPnnEZ^OiRo+5^sS1%mK;csxdM&y4un(L zY;2~AOJ&W{3$T0cIK+us?~A`1a{)Z3Co!JoLUzR{0-wQSgmS^6 zb;T?qlfffeY!|CNQa5}U*wTM0{h(r5i@1d(yFzp36y8?8Lzvo}dZw$lC6Kysgtn|_ z(njN^bwM+Js9HON0l3$_fSPVv3#d7X$CI13>H$JtRxcc)A(L-*Oi&OO@wzRFxu0B- zqeA^(t{T%1z!2)}}(5LD$M3_^;dv}4bnp=!D znZD&2sl5=OZDNULaCG2=tlu=XtDWl6Lt)?&o~pNHuG(%=3qSy$K;aD+sX?nYEQ~SW z9KgpqmT}d$KHyBeh!O1)cPIE|-};Gp0Ko7w)$bSD6tA?0WS;wBjL`Y?hfD8ujMw@F zA;$z7fo}_&TOy?Qp(PK)CXy)Q0!<4{tpF2H=8c>3ftUvChjbbN;DS}fQ?H5X!AtSL z;E!jz$Y`MXGr$%e_Z;8rR|@00a^Jai7?GTRnY<`KZiKrhprAClTYwu$z_CK;F3lvDDAU8=qVuxc={MiJe5xlViM3(ho(C<4}2w2 zCE10E#0CtNuoTozCdq~o%QDnMGHP47UALRz;*F-fJzn1_X(aYY*0b_&MmHXs-Z7LA#wJ#RF*n^I|9NPyW1EN#9ie2*_+$ylKUoob(7!>NAq`ai+?k zcBk@+y|rB-l{0MNQ|pc{<71QT%RI$;{ttJC#~hz^ir4)FqNyE$qWjp-deePLM7lmu z@vcw|$5cgf0_?k%ST!ZP)hW5UR{;3OVwx_KZdzQI4Ah&iv^5t{PnFQ>zrOom2ErZk zMEI+pB6`sIk{A*X6Ppe?oztG@Whi+LnIW3Bk<$5SD>&VanNp0_^$Bz7Mvk2DbUZKxfRe}!N(TT zlXt=~WrtY}c8xO(t2Ie%F5#J6Q&!?s`;jS?$Aam4-Q_lRVMfWqwc9X)9YKtv14xJD zDXWR$Rhf+%UDv%NB#%kD{cZy8p*>m4e6(g7Q4$+}9+uzwCU;uXB2L=?6T!1m#utXO zr57LWv0}6`1xZ2?^Z7?pMJQk+sU904EmVN4HSz$vKsIcRxYajI>9ct>XR}>F*N;eh z`A5W7t&%6KMuxzzkq`^>EGNblGxiONb}h{%?FCgHuAXHs>Bv-EOl|4`Kpn1RtIbc1 zJqKMhRTmlzAK2E;Yc4!1-G*83R*#9AE6z2vp!zzxv`qoFMJ$m%P^f+h zoj~@&J21&f$N6vT_5o1OcD7=&qwI4m7Mk^E^2!oTS3M5;$N%xb| zN?yYh7#C>P6C~bGdJM?-1K8(tVo-l97GYBp+&Y5tNq$im&~LY}QBVIAT|*D&%oZ3^ zj7hD>>Qm{1Ijx;PB4!H+4?(jh&yZyEv^t%d%8%}&Fs%DZi{-+d!O);(RW-#%;!mqg zKA)_aJW&O!J|FZsh{dqH3vFbN?kxW$7XvucI8}#J=}_-yA3`~iEbCpZ2$YexOWV2{J&L%Z7=|H3 z^UKlSu7*qgNOPYoAAxYXmy7CPO`9$3w(L80sjlfE>x&BRu7(@-b=0L&p@LQC`X`Le z)K3=ffQ>yOz;&z=NfVqX+U{QNMeNFxYU@*I?h4i=0oWOV{+XlkwIB`31@y|3C|>D8 z(~|ZJg|=+DcpR4Ab%()86-(F0H1%C%b9Jw2E^~G9JUTmb7?XIC7-1m&HYJ1RjltUN%HCv%VYOD_PA=O65VJ;TZ$VlXe=$<9%D9D>1DMI39302ad ze_oyT24pEIchYymurnA=-N$Uoy|ULo7F3tX(S zvbNx0M6G5Hu8`q9N_cik;0#p1A-12TFbZG-!C)JREkFMl?Kg7V8emTjXD~KiAR=Su z8LJMdL`4XB$_yDe0DB0S^(oT*AYG6Kb87MMlMBPW61-rwOw5{dC^Uq!7g>^W%EV+r znGSHpa2uku&vPkDIurHvQV-B8HUKp>HGEoVtrLy{*;6}ScSVuk|KO_8ZK$D&mvQ{D zsvM@}G4+TVh$k8ZqM(@0aRKoZk1W7D6x0$|Z0a(4^CXWWN+Sx4lW>7NAseL?)+HHd z8mwyhx|rqZIBG3(^z4bkxf;ug#J@-dmjPZw)fSc9B_bVynja!F#_o7WR5q#2JY}X! z=*7{Cs}20kD?H6~r;4RNQB+9DDWYJGR?__}@QzM$seH6i2q-vUKzxL7tM8{4O!moE z`M7wS4(61?K|Y9yK7EczKY;ySlDvPv(n{V$2T|S(rARB!$5DQmv#$%Iwu-oij}cHC zzE~92&=&uRvSv9v9)7B~ln^beRUMZ3Vcmuz_mjiThiE0~N4O(}k6+TzQ`9_CEvk_o zDpLv$tvTn3t~3_j37s-9H5Y3wvCsU=Uw&< z%6>G%;^EdtkDz*{(=|TU2J(cXT!C^#(o7F-Qy!dY#pp6<6g#MwP}|{hk`P5+@26<~ z3W&6upQuhLLuF$}fbMdxG_N2irbn94RF3H>=iH&w#YpC!W%w?w=^g=rh`Ngf^?g2H zT1R-!B$~)N=jh#sePpgelRQuo)n70NibLIEZG%?_e5EEGg^{02o|d~@*U2ydvkNQ- zsqd&`PBk#aR@0Onr&?ZYKD@9>MS4cc)wtUk>t274f{Mr{7BohAUpaANDG{E6$zW4C z8KWH6ObDHgq7UujimVMy`@7VYIBkLAD|wv@2%&Dvj0{@4{#^Vr;htftZMJYCTDgSR zv7Db*%PJdNlOq?>U0v}o;;>5vc;d6)mrf#hSK(J2foz zFsH~*A{>(D5LrOU#rC|F#fVR<<3J7f4;L@eU!g9Og=JiE#P+hT9J*7(U7k~RGtxNJ zkGx!O9hxP=U{iKa^92BkQpPVMAprgHAEj6Y+orjJBP)~Y%SDr40 zpmWIrAU11@;<3+66P`gFW`*Na7=z9^E>+VrVe~`fh3XKKp@9q+MoXV8VxO~OH$jyR za%om^etrf2k^*pr6d;itj&aK7aCiY{_LZ7zezYZr_%w4&%c52JSkb?C7^FI|y{ABr zya7=$?il&Zo?jIwSUHvpQ0HbkfS*${ZPcw+E_Z0usCKS=ElWgYT=JeW^gkQR+lu21 zddk+QqT8EVi5nTgYo4PyQUmhHXDc*aAOLw13#Oy=(Z8_5#6qen`rEkN}_mih=1He)aRh1L+EF5LVb3RBjSYh}GMp!o6?6?5G--tmFA z=F1NmAWx{uJ7mYbhxSmXvw3xVR;5?V!wyh^ zC9U1njB42V>w;h9(9Ie-mC`}qwIK4VR1((TdF_#0o&G57%>DqOs-mD@#VG8Bj9}R~ z`W#68YP0_>QnX=J6p(}Kb(X&Q>ylkI9n7x^%%8cxxQ@XDHSB~a6 zOtE~rIrWm(rRuNwskY%$hntKg6H$2~oqdo1dGYj#B;$8F=2Vk$d)gcf^-o@WVjbI% z1Ze72swNNxKPeaLQu1LTK3D3D2H2_1#|NU|k}Ik1y2$Swp#msUk#fM<=SW5^C8*u` zM;0hu19ex+I5MxGfvw>y?U{2FY^E+SpOiCKk2E?dC#p+2Q_$d7B&0K!)w6Y1^Uv() zOhdj#>aG@_xm9}4c9bk_Y224rmpn~ZH%%V^%O*;e2(i`k-41xmX)(0E3vs*O&sNYH z8iCuF8sXHqDFFx@=hrE6*+y1usKDH;(w7y+{F}Tpj)}0ZG>>L`o)JQ*Rv6s`VMaJl z*4c^>$@w+$8VSiv3!DRO*ybP{Zi%7B_7B5U5nuExIU5G)$db z@bV!sRif>E8og5!wE}UykU3E+%l(xNPf71QgVfYXD*v*8~WQm z6!Iv%_&UGNeb6!!!XZPHiS`WR*4;3(-iPBV5_B8bl&T{=j}$~n2gf!ftPPLV!h z8d(BZBJ);kfEghfj3y41y|D9DPMOKphIuOY3Nq!+3iyDmiYmt?VTALaW&;}eT0=+U z^!!hRw*cy;4XwFzD~DU0BW8p#B1zVT6hepT?e3s!qeKlJx%lCqi3-pK1_}sXD_eOE zaSJxQImo*_D@U*ymx(rg>tkstu}yJ>tY=PP#kuW_CVRQ0tk(@9_wAPLp!g1^KpLUo zn<%f@>KqE&mA!*a#FK-A@G$?x@5K6ghscy^j{pgb3K6gPm7^9h){}U)6NL2)l5o$x zT6wfgg(9drv3z%V6M^d@I75mfyxFybb416=eRM>yi0S*>b2`IT1gJ$MEA;#|j~hvi zJoJpR3^5^mcA(d$VR7OR=0p~|K#x&KyB^$VWTkKMZjm!OYTSWb2szgH016#nF}5pG zAs{$bLZRKl4(JuWb7l^H|Ku1|M zf?x*k2BVGkJr5|z>mh0BtN79a@RRn`eVl{RFwzIka5r^d%q8n1XQ@Qo&C#@xjtY9; zm?GKsR$`N2cBo&@wMR?U24t!)txw}>p8(BsnGK4|5<1@ z(bq|VS?nqI*SqI)+%H{g3zXxbl;vpKJobn*h9Yn?N<^d#lpYW`cX=ZS)eL#fR{*jo z3#G#^awM|Hx+FXF*7M!f0wf3m(Ow5jfdYg0dLagEr_Dv=CHE1wSc=hONt9Q(EFHgA zsyp*ux{AJQV(i^y^H^D=#45mtvc5Ca>O;yFF2nXHnu`o#uQJe8zcF&w{ilEiSXXUoL>lf; zD_@FPl(qX4$RZD>nRA3H54#buVlysYbLh*EDMR+R3vo@)cj!aF*&8f=&w;7FoM=GP z7~u1`r{8_>wauE+tZ{~cxBm!WsSH@*{RBnfMtUQB1Jhd)1F;V|p|DMHK>etR{+)+P z#$->*Wd4N1FGR6lJX5c;#N&*BXB~wsuR5E$uo|ekT}MQXES1o$W1oW3ZS^+Zc0+@{fc8G3kGY$i9>LX&XPW|GT0uFy<{}w% ze1`EH-P@>78PW09?X_5{zxbtFC-*}|sknEJ%y*1}j%-o=F&z9E0Uhq|x-n4J%#Ir7 zxbInInaK~o&0@oOAA8B)gs(#lcWF7=O@)FPG`iDl1&sEtAt7^PFr(%v5lIccSGDHL zb?$YHnbd7cNx1Bci{TjrFzDl5Ec!MW>TDXymD^W$e*ShAn)R-MJyXFrCITJ_xm<$0 zuQUy7alahLtcfqXVjhz>!Hq+o_-FIzqAK*5)d;%FP3Ek>09Wu8;9#>~Yc@{K+^GIW576HhQ8Jm zPJ<{<9M|K|AW9`24!Yk&F+N)X-rq+pJOUY@VG3g*!iZ6UfVYRGMiCQSg@lPt zg=a~~n3qt|%2yvRjzs}oz7{^AnJ_AINIK_6P9vhECX_DE&Tf-al8ia2VI}co0p^^G z65t-XCXN()t8?F- z+?D{;(YwLj2gzQSqQ1rWZKnxrc!VFQ%QRr0ZdnjQ;~yKH#Eo>>$FAS^nrG-pe~}mN z$hAm@E}SrNQkO55pcD!vUsdm%+qU^hunkJdBW?0&9Ph+B1`vDETYKu}rO+=E>g06X zZZ94lDDw{0ZugyzSor{T5t7@87?HWzmY<1&bz>}jM!kvtGEZ~6Q0_FP2_xK(v#EkO zcjjN&WrVTT*Z9!@=dIBfq@poFb~97+b3JaYVk^f2a-Ve7geZ!EwYcj&>*Jz3>b821 z(~cXZQwAFC3BblTQ7`KO9FyGgUE`35rIsBhp7NL+3FdOR-cJFh2TN1BQmy365}q_O ztVQbbzmXHR8IgHVqX?7tDp>Cim=6OK7OMeB(?1W5?ewbUD_%-SqLwax3X*GI#2&dUdeOpQQc8UM2$=pZq0 zGSrV@ir;{6BRmQ|{&F_JQN14z9YY=kY-Etnq)M?-_=#9*2?#FAen>w+wy^k!Gc|h8 z+!P{WoQ<(24}@w8B>R?x9*GKt=KI@D;ddI)v43Vn;RSOYmFxUmu*|01M{R0t`DVc7{JtxY}yc~_av^XhqCXoCX9TKy%qB!5Y>D{K??U-tI zx~=%B64^L+&jy3O8lGN55C#zzAvjl%u;sGfk@M%yI@sDhDhezE_hY2^Q5_7IrYGy2 zhiK-(vb8qREFQP6ay=mv*NM%PT6%ZMS$D$trE2QaP&iX*9~jR{b#- zE~X;@?QGk+#7|k7ASsPVY;XHv5$*0!ab|UBzBf==Od}x`{c*1&+x%vxbu|&DC9xp( zw8~r2)=5tLf8&Ix*_MPigY4{SZFC*qK!4(;jU>g{$Um)-B`obNHifkmrAO=Rtp@uu zppf4-z1r%wzSV3C;gX6PVl#yloIH^}E*cO4C(2Ls1xo|v)o7bW#q3$f*HDsGvuC^_Yw{!)%N2NGG=j>LEmG%lFo=iR|Fd->meS5_5UI$ZZ(ETb zWeK8mZaw`K1H*v(2Ga%2LPy)DFRv)~2G)i@DPgea{}!;dULE~XW|XZy(df|0C;d&g z;||y&8!6R6*TmQlA(1sg{&3!de3Ujl6ivZ0e}AlI%ZY`aunfZ>$}v=x`bG_CslkvH zmaKD{;fRx+-91~e*v`AnrHOl9>b?UvZ61&b!ZfKh@jQIgJ?=0wFIJE ze?g|!8_pJG9GXn=l60lFQjCL+pIhh+tgu%u##Kl6LF<_%etS}xtw@gcL0#coa|;JE zs%WN>o$p4rt!>{lqqS-*SNc;{T&sYO_F?VsQq7>B9EDITZUyNX!m4vCDJ8F+I%&T| z?^OhS;ct-90{OhORWyF?9CV3vdXZ9Ye??jiC!>Oi%2}&{(*g>-eXFBTL;rPXp`Ehi zaFRwx?}qIFB7WsTtqzHACZao371S$_f&Uy|h1X^Sv$WE|{Lqjw>^9iB^l->{NSd`3 zFysoHS9}GUdonrBXPv>8l>^$&&m9`_mHGp8)-ilys6|&+j_Jxih|i(0@HfBk=^ z`$*@Ga>N@YpM3Lv3FQx+44aef>Rg6mTpAizRi;xmPQtvLoX)nt!=^-VjIOhfv1FF{ zg5~H8MZR&Rqn$ND=*6pe2mk~y`Vz^%K;m@(UUMJ`a-lusIbEKC5NGnU@JbzBM?>R% zN=`k@L0rf zKEfS`7%o5z7sgY>v{@H9c^f0739q;;u>uKD$VK;0XmM-%icA+QF>Dv%zD6}^f)vL1RD zD35v)I^;G%pAwI1fWGx`SQGTaF8UW39s>chi<)47(>SNV^q5$dTjW&b<8#aZo;XKBxf>FK~5}Ck;=^NQ&Uzm!2|`JTCigPof?Me^c|blUQBzn`d*p zX5`kxkXm>LZ$}_NVP31V9E!8dYi*WA`B>bmFrTJ~6OK$##!nGvk8s(A$O#*vQ|v@> z@>r8w=m6yHfnl|{9(g$5Lb?vGgHc#Gq85_rbz~jn;cFk~^~gHtz8wlSLK+s1+6c)_ zFd7Fu>Jh3OQ`dZ$e?yKNz?F7%BXT1{v7@2uVcbS68;`STgbB5fk~XmsCQ%LD8enqF z91H1=*iD&lw>&1wl>1N|0KCYQi@^m;Astpg7F0kUR6zmwkv#)&A_SofR%6W?sD`z0 z3Y-k*;`L%U9X7%la1)#bcfdKY1!tPe*sv*1YFK6*uc`@DwYLT zv*A$7#=}N-3~XXWa04rb8`(*4Gb@K%ST)?vRzV%Z9@zzO7rPwpVb{XF>;~AvZioBW zy|5K2u#G(g+u7r=ll>R&Xa9o+_7Ob5zJUkXkMJ=24R*6;*uy0}#w~c9r@#|D6Q1E+ z;CbE;Uf_e^e`P)#UeUr8g0usWVe<3Xekd^c`U8+>^7HYb870y(`2|#kuXdryFEsf@ zCchXpLo?DyH~>UPwI7D)4hGn;`|07ruI<}*Y)0yG8xqOhK0OtM_>!tV(W`>l{fhSft+__YaUf0o2l;-r-Tp+ociL6BtyMicl@@;ycaEGaO$G{#v5bFoa;fpuqH zSP#~p^<*Ph7As)A*fiFg6|z2T0qe__vcuSNe6D6WtcK;XvsfOxjODXi*+9094Pv|5 z;p_u8oPCR}e`h1L==6uAzhKS*IK||bqEzgM!6v_~-2pffnIEM|F%JsGpQuL|{fdiY zf4J78IU~ch1i8Hy%&xUCKf-r~u^hjmFfpFXi{m-Ep?;Xw2o<%E-UOAXORH>?P!Ik_ zsIGtl2QfsKKVY%KI<<6tmapqXp}%wv;bA)5weY&ul184zM~VI4ab&Smr9Qg$3% z$4cN}vKByOzDjYT4&( z6Z?_f$o^!TxnQ?&H@lT*vO1o{?&SIGEX1P) zC5F2)T*TDqzJiJ}c&ZbAh`FZYuG(e?3+M++5Jk1nBG>4 zEj!KQ%CNL8!+Cm=BG2x)IkwYtjNp!Q+)T4=A6pPV?-Wmpr+v)4f1{vOeEZoJPV*E; z|7q69cQoIf8=?1hxGU^u-;I8@4R#Mcp|@QR_eQ1gMGPc?VerHr0E;~c9T>J_yPz9; z1bVSO(2qR|dF(M5%ASOy*i$f>Jqy#>3ow_x2q&^vz{_5RCF~6dvNz!@_7+^h-iABT z2YiIR3s185;Z5`fe?Mg(z)$Q`_>+Bx=I?Vff?uM+`wETQ_iQkG0}a^EYzq689mjq{ ziToX9^beH1KiSP}AKSwIVh^$d>}ht8eZU#}iF3A(3vO}6JF`D|51zyiwDck^R; zdo6J{K>GvG+2kAXZ!`MKN!rt+H-?Vmbtb=_>>;4RK3aQ_f9o?2!W@%tvS0p$4tt>; z8p;DO#i`zpCaf7&LP~2L*?*aC?{q<~XgauBgQl>U(J!YtzUE$(a|}X}5*V^J!4_Py z`(|LgvlSn<)x-Ar_`Cz3cRJ7amxuz^)$<^@7ZGhdd#ZftX>fzB^+Ydnowhc_KQ}-Ael;KvmDmla22pOIvlDEfE zR@0uquuBW-MrcRQr)#)b2T58zT#;dHgwAJ6mXjfMf9^uxQs&peSS|3W7=PRn75DIL zvZC0TG1w)Yt+3Dc&sNPj=x5ZTrlo>|2V>^`B+fkp^~_T(O1$JCcuPSIkd!apwl_&i$f8_dh$p1I;%}z4wVw3^{@5glC2v%+$ z@!2+FFLWiJruafM!ZTs!(`6X^OQ$R+*CV^jGGf78kFuYl^v%(}Z3WV|5-eT?$$TYb z@BsAWAsE1G;0V4Nj^b-z3SX<|B7h}3X|kIT#hZ~0w4f$^k0E0+fbl>hJd18}w~ZjQ zes7_98BS6TIYryj;`>ujuBl)`B|%9v7J) zL@jKNbw*!9o_d{VK!s^<)We(G;jOf{J!&WXw-Mf{hj-^w!FyEjeoVptsNe&qz%d<8 zCm%YUeAKd&k6U)~Nh_Ub^!vr4_$i|Je_0sCdY$zmK%7j6Ciudc+?Vmr^jA*t*S6zg zJHd_cO)ZqfcKt1O{T*eq>^{FIq<-+2JK@I|EPtYcpJNJsp@LsqqWwxOdp=B0GdhUf zciL|bQGTbku|)ZU3Sx<}mkL@C<&f_Fbh_Kuvb(=pcDMg;yK964wXm!S4kFske+4d` zj^p(Vuw^=99@kFBqkW|_K_xP_L{W(mTVhg)3;9~s0ZE&#se`SJEQy9=j&zS!eo(H{H7_Sm1Gvt!#2ppu-}l3Xgui!2rD!#+_1 zna=WCaZ{VvKrQ**8rYz?0Gb_Mf@Ona1Iz7fh@{Ay4Z--LOA|Z7Rwis{e{4{SwJH{9 zm;*FCE^=if!lRCikAx#}cMn_yY<{HEyr4jPAryYl3XIwaovr;Bm3QO>DeVJR!C?ViWloxD>DFqdmM1viS9o$2Y++w8f*)&PExUHFr%FMpcl^Jm#`{v11szsAP#H&_vWlO4w~PUrt+e*PY-;qSB4_y_1` ze8?{6AF-SH$7~1xggwqbWzX@i*em>N_74A+eagRMKk)B4@E>?8fB%v9=0EWP{1<)% z|CNv7zww#;cYYH8gRkU!`5L~DpUL<0_51+8oFC*Hc{9I90N*7Te_3$;wGjL}A^9&t z@%_RON|>UPaESpTNsJPfI94Q!<3u}ACfbWtB1Nnh9mGb_QEV2O;!e?7><}KYOLP%0 ziLT;9(M|j$x{JM{f2ZUkOSTieWDn6>4ibIjSkYHb5&h+Cku4X999b%I<#I7ht`bMe zbz-bMTa1_M#bkMc5n{fYB#u|p#R+PK@T#?9u{ukXsf&eAT_cvNf7`?|wOy2}heU;XR#d9D zM3wqTgwzkBM*S()7)fHSktx<0S>iNfv^d?ED$X#9#d*ewV!g3koNt80g~kQqBI6oy zv2l~Q!q_6NG#bTK+E4lb`dX=-+wF%=Cco9SAMP{xZP^FlVw2x)^15c0siQ6md~U@W zyVT@&nEXykf4tv?-e5EK(k6_sVc0%MYKBE^!QGueUw6m$wGYPq1urFwcFBK%_b(_q zOy@@LG5Nij?K1a6ACqtC(n(}yrFKED?>=OG?VhUV?G&k)9iswLPy&-t4^I@0Y?7AA zaLHu51aqyQJ*lZ<=HW{(9Q{;cCe{Ue{7lqJDpr#JL)g2XEWxfv%*GJ zFmTt=#kDAVt-9+ku%;&VZSRfruTj*+|Cy3omN&_rwvaTO|OahaKt4s4lY|7wN1++ zQ!B59f9LJq7Cs4&cB_S5O>8-~ToImHJ*%+yF>MD|-4C14zhspo93<>5h9u`@538z$ z%qHe9@g!v$jjXzXtt@cWK{^%b0#A}IinS~Ov?pXEoS4&@+&?6-J+8Pcb{(h!Wrv2_ zS?H;l{16Kj$gccW+QHQ0ks0oq&T8=5)sFWHe`FI|McbEbb%APPYf75fTH3H>>l)a9 zBCakwnJ%ZGFU(G@XQ$E2>2;7?pwiiyjgj8d*;&{z(lIHWom~gGtmn||q-`=W;O(ZZ zzfEGKYa=^1Oy~2q(r${=%X(^MM0Q{65X--*T+qlasD-($_j_R-6#T#JnQaAw&0v4B zfBhJ9j^KVCU}vD%Jhv$zF% zi(8?exD9f|T`*MK10%(KFi~v91>FvF#ZFit?uRn*0IU=b!l~jRI9u$34PrN3BOZgz z;&EscPrzg1NqAa34KIr4;C1mLd?a3ie_zF`uur_kn0S*Z@it2mAFx#MA?qSOW_`sc zEL(ie28plO1o1VSA--kv#dquk@gwtzUs;9tovjsruye&;RxAEucZvh-ana0PlfZtK zjQuGU+b<}b_}j8Ce^>VA@5?^?H;K`GQ@^^c&dJ2`bfsl{yvpxor!nchX+A(}BZ7Fx#w?1vsE-`Nb+ z5v{w^%dMg#R82r{UN|VB&uOZ#z6bBb?@P?v9#B z+sQ7n&m`n}&c6Pawe?ZE|M>~nc zHq^5#bTVxFe4Rjgmldd7JBQ1zEKqfjQDC4RBTaCXho0)$)vYM6CU#9pOXa0dc{Q+W z?++)=j@bqbPJ;{JVit4~Bl92wK#l~LEPxJjG<23@pszd{2FS56M2?3kaw5!@Q(%!i z23FzyWH}v9lZ9}BoC6ojf0=NpoCVj&*>IyQhAna~yeyA}x8yv{L}S2ghQ507^y1q& zp@#u_Cs8VOAM|gA4o(r2n819Ok`uPQlxI-3HY#y!ESZ~Ez<++Mh1J>=2{pRPM%}gO;mrgf4vbgpo!g55-qgt z;H|M~2{{_oY+dtBbZ$_2?mkYp<$0HF>gmk$Oy30k-Po4yWr5DD?#V}8n zLZ$SHskq`cGcM7N~B#7X%|A;)gbLwA?;Qp?baae)IA(o(9|H>9A9t0S)pTcu<}T56km3J$r*Ij-Cf$jL9Eme{6u>_s(%>`&gK^#y+HM z8e%gMr7IGA-YcW0w~)v)a>GO}%yWo5EiX)DqI;OcgPT}gi9QLGAErqIyCZfRIc}7? z<{c5w=*1Xkrzl^aifGE$+iN@JaG9^qQds%=C`GmyE+y%deETFtK53Id_3TbuOk5wS zRmrCrvKH3nf7i3S!kd9<P6-A1-EF3GUR>G09`*!?l= z>T!F+ly)+x=m`h%NqbL`_6n)^DW~{pdrOpdLp6(~vuBXK;&|%|g z@D%5LH``p#o-ODghNotvdOB!ZHo(&%Bh@(q$nHYsN<#O$o;`;Fk{q5wJ1wbNQ>4_w zoQMPXe>^#W?V~El@meF26RjiB(NgG1ZAEk@N3u^i-52cXrn48r4==PNKs?+_u_X>} z_Wr7;eLZ`bjBfjI28!JES4y_CR~y)Ci_b61```_^72cKG;3v5q4#*v>13Dbt<^3!V zBg5(PVOA`6u@mH@tXw|Eg7Rs0vV4Y}D_>++$d}kA`8vB@zQMN2ci02+UG|v#kUb+m ze`0USkJ*RvQ}&(wjQt_MU&4Oj`CZcCBNtS@(1)w|KLZ-y?nC#lh2g<_&f!C zf#Q6r5_}~Z{8N>SuU8hoTqX1CR4TtirSa{m6MsZ?=Fg}u{8iPJf1tAX*Qyu)RrTfv zR3G6|eMN>kOmtTLM1R#^3{}~pNDUCPe^ri{i|-56K(R;-5~r!b;uA}K_J0GU6BEyv{8^JfXY%LC8y*H}i8ml?hTamo;AGPFLNR)~=R5n- z33l*+c7{#l(H9~<#+#tX$6#g?dlU7~TQO%7+1rkq`ESh0D)x?3`0gR;j3)M;Q}=$H zwvPzX{~SRI>wWeCUBa>Mhb?1We{2v@6FLm_HL;Hn$BzqCBj77)olnrqXk?!j7#@Xw zGW(ycgg=XqOF#d+xU@y(HVk!2U>%%-qI@qr4=*|QZ^PjyR6$n&H4j{BKBTGz&|Mu5 z{nUvtL@k6->LeJiN@1odgA%n2DpWbtsO7LuRl+H11)QcT;2hI#sjiVDhR@alGmmP5zR}UpDzG_HyorBTW7( zMpB#RL_-}!_O*y3{Q|BreG%Y`S)tf7sG1bc8nZ8=>-D9*UUVuOwO+nnDyt}+eRb$c zeHmFPiZ>2}aWFBg4DGY_f9f1?t8*bktw)NT4~MCXVT8H_j#8JxIJE&Ls>@)Kx*Vpf zE1^tX<+#Ym;uD>7y|0AX*T7z1k4)_|TrY+9)0^1W&eXn%oti$>7R%G$A_ILFds0xJ zgp18)eP0XRo7fLdZ$HMeaviw?KRGo&w|;VT3Za7BW3q@)R9Ix&JpV|t`)OO^P9mpT|>zStjKM2cA{)WllH2GUd2>La0M`Cx{ zVG&DfV!t@3{2DvM-<-nVqqA&ef7HT=CbkzR|7Waww$Fk6D?FD-{%=1mgWDT5qJfQ! z;uc+mRnQ$5p$Qk^AzXwtsITGzybk|S zZ^GH?Ex1Iz1J|f`;U@JRY*9bL{puHZRQ-yAx)qZ#vWO57hTF>L= zMbfx=kt}Xl26+<6Ah+VR<-3hMxfarzxZ5FkJ6zCn8+rS5o>C8w>#7b;RVr4k&{b*S zs&uESBUa7Qe^nX!bWMtW&J2Tfa=YBaKWr+VH?}Mpsy9^nfy>Cj^b&aGKEve=ac&gN;T%xYNjnJ;nfd*~o*h zjePjs7{a76jG4v}xU@rAPh%v@F^*)zjZu1uyFl`OIGP>NrAw#wp8b$)^7m(%yrI)R z(pmJo_fC+Ri>4JrUhx*2!3wwYKCwslDM;S~Gi%{kohNdR$4|2 zw-$1oe-~;t!+EBYi-q*u#1AWx4ZI)5UpfG6sDnK0ncDUBNT-R0jzn+K7P(JBQabOC zw9eO0+4$rLs>7TAw|#~-IaK4q2h{VN+Gc%EqB`Q#;-81J#uH4~@DFfk?l zFNopd^cXItx~dp9PLE+@s+-dWAE(FgF~Q{|f5gZIE=k`=<2e$|@c%F<-Is!dJLpSmxXj_2~b@s;jFijT1Im?=_wiBo(X&Y+O!r0?7grjfU5r1MGIS>)nUaf7&t z1zD@Z5w$-?Z zJ!@Rd-ZD0@PmC+r_r{fMuW=Ro%ea|kR_X;5mH;Wx1kY=*&7!-^jBsVVw9y1HfA|s`(R)*y1DKCu{l7` zb!Z$sduc;kwTAC_Co21pf8=-w^bKGV&hgz`lBmMG-EdMppInry&#OC58VTZ*TF8np z?lHFUL|rj8tY>?KLCFO0e`)%I$@9_PFr8!*^?W*M948wzgq}9(#4nvl+6}|%`3#}O zo<`5ts?zef3Jh&%p3PA5M#zl}UlpCXk$Nhf&x~S1DaYY7D%uA=E5=zXf^-y? zFTgOqg!aZ)C@9}TALBb1Yy1F3#!oQU_!$M|7g%8Y3TutuV1w~He_U<+0ky`TC?xw( zNd7{BIEdD}8Qw9OW)9?wgD_T8m`-LNgx>atgS&_ALuc_%^04XuW$YZq9*I!|efGEB z{`xa_4-AV@`OX@kUMq^D{GiAi+=!HDZ6Rhyrtd5rZQtKXQ9%TF4ua&`+9sVBH}bjB zUN=7p>to(%_qCoMe_IP9u@^pX6LcVF_!fGZe#!*buh;HoK4yzv<%(YGID86OYfQ#wUbd>iLN_hSSMQaCoXSJvlsO=6Fo{1h@Iq za1(64uns!v;6?9VVZrEnz9`BY+OsnyWS9!Nng&Xr2}hYOe^_8z;5FT_+-wJDn;l?- znFcqS=}>2Ogon%wc+d2}&t_NHXLe(q%wDX&*_RD9v)MRv09$D0urf23Ej0(TpgDxC zGKaDA%n_Pz27)`|08F$QM}IZCem{)BYtM{*&^P4(i9gEs?tRc>AGGg)Sbh@bB6tOb zmcs0FBV07%e^4%RB>5jjxCQ65G`(oe*m~-Gb^H`0o0%7*g#zvp< z&mAncJBzRgyDl|0!*QA*^d&elu$8CzcVaGi(0Ryfjl7IP3t#v=e`Y#;3^_KPFU4za zBVUHMCKy(t=Zb*k$j1$Q`PSU6@yE=~AF|DAlqo+< zFasJx59M9DIoYO-n%}?HUsd-*9KYe;I+%`de}0Ano#$$F8dnzPp(`JlpX+?m9`jQa z<|-U-HBx5{q?v2M#lMT>Z-(jLbwIduURBS78=bSkJD?!S4Tgs4>#R6$H0>5AXwsPOy?>*o7?z!jO z$twpQe+t0Sn#+xi7OliNXkT-2BPx#6KwY3}c!G6$8r(U%6e(T9$Z%7IQAB!$6}9O>qo zAyQo-xuFiKbW)X@XBj4y)shT%P>qw0a-)()NHS6?kCxmql8lmpqa~@8g^v|Ej&sl$ zH-ARaSlQn=sTnW132r)`Cc0@7)wwWZZ9g&q4E@bdrNkc4IcVowPu{3!St`zKfl7ijz*2>}fLR>5?pw zWT}Zhpt;FM%cQD7)@YQRUy>$SquEKzWq)))YF0>ch9oVLv^uCwHtd!{yBlFzDaA9T z7!&|I+&Ga!P6|6|m6TUIX^ni>x-nREb(V}dTRNTNq;s8go|AqiD*3sfc)pu1pbMp_ zFka`Ri=^jzCtWP%Ur2I^Aa|)OdRaDIPFF~BrPN&|$<>lve)_RlZ=rx2(lqA8uXd4-#l5!QB>ao!sIJ zclbL9IgNo)| zW(V53)ikEp_|_2e8v{XJ<78j(5K@?XkzFOE$h`AzJr8f^$y>;6ZfRfUYgy8K6Z*_r;alaa3AEQt)aRUq_^ zm+y@N6@RS|^icasLP07C>U?Lg+7ld57xUpIfQza!KxbaMy&?SCu%Z2}RYq}d;;_pcHCr%;{eV6x|P z>y%WA_pg{avNd|etfOD z{y-KjP9#*gRIIAexZ2#HvYG-`PLnRt}Ak*V@&z za9e{|e_u<|jyu9DSGEV^d#wvdPr{&#_0z5M9(Q+^{)mDtUaU|q%ea$dMGrrmy(SM> z@?$b%v1~d=`7a5Wd!>|<_u`i8Hh&dt!H4BN8n_j=9i($Nht0q}xYxjDN$$jL2JVvNZb|OL{RXyS zyFr`rD?X74!#OGD^-K*0+k>&D49=K??lb6qdO*Z^*T4h#C0otR4jKD&v44i-8O%l= zPrsC8i-9e8kWnj-|IeTYd2V`0@OlovGVqY#^&viDn;V;P#+JHiC zR)ZdqeLTv8=uzGlZNopu=&Y)k>^V0DJb}KS+nXm7az5t{7hA6ZwV;@FfmO$=nG3Z5l zN%rxwL9fuO?Bp2q8oh4Nujvhg-lPW{^cz|3Exwx5oecu`aHQAPg?|Gr%G)c7otW~N z&pn3q_*?oN-!$c``4p8iw!T1{S^InDMtMchFMH(sS%x*RuNw+-k5D-~+(Qj|o8B?- zchS|a1^YkZU3SL|`UCyZz)cKs(1!+nBx`?&j}6*Gf04S6d8@MBqYU~)6i_~O z?%X+Z$CS_Y`x=(>>XYlIl{Y98QQi`04TP9|pVD6$l2n()pue$*Jm23r7%D%ClLnqu z8^L@1hp_E4`rJYPH0TQ{d@1L^v9f%1Lt7Jf_!s?~J+qbNW`F5H`j0_h(boq3SLpK% zearrYLEp)C->2^l+Dktew2$^n?f_w6M#h+&oh%yhwS^3dYA`esE$qj42KIsH*sE!V zrfW6>2M{&1EG8xKi2=+L``$iPW@i6e0+YhTRFhj9r?vQ+ z+3Y(ye4!>~D+;^2=Lv5%%>=5uz9`XV1+dE3R)&iwZu75}@R1#IznJ8yYXU6JkPJaU z=5WH^;%{pXE$0avTH3{1b#?edv#dJ3S+FUQXfRy~V}B*mn3;J_odrk>M65w75*(5; z&T7fHLP>@xWCoW+hRRG3MrMkW4i)Ih1a6zgOF@7Av@4vI{kbr93&iH zEV%gBFlc3m1iWABDN5h6W0hEsIZbljQ#z_pm4Efc5vNJK*}gSwO!x|v%`>kScRQhR zDYJze_0wj_l_GZmSBF~K4k9vh$<@M(S!V1|T8%G~)zlL15Cg)CO`F0Ob_{XLE1cr* zXb1*Yvb7wW`6J9F}p2*vs+xRbeBqzI9qMJe8_y;V2F*RsMN0vc7{vKv~TJe zWU(p4w~EkOyFhx43W*um*e_BOAC9Xi*3 zUdc6;?(NVjUE85o7Q?n3_R3vwEZPC*cDOj}=4|$M7>R67qC;*Xo0rJuS5|FD!G9wt z+=yP4+hBB|$hDyp*}G889ZH^#x8$U^@Eo2+kD%8M^xh6Hm-;N)g}#fpt9J+b?Lg^v z^w-Dt%Xi<2LayvzSk{H|bs9yYUr4bF11edhBer8;C6@`@-9Ik3yYgW%nV!L*m9 zcHqe@-q}-lns>#z;kj&_11d!VZ96LDt8d59U8odj3afTt*sRK`E>v&FaDV>PY=s06 zB2gdKE6@rj+K`VkQHmf-+kv47VK=wfxZhy@_e^}XCTq2kvPy*zfxknU3n{BrapmwX z93`t&c3}kn8<|-32wo2?oD-{g)w6lkb9j|=dDWkx8s}pKE=XDZ+4$;g|#VhEsg)(k;U0Trg7~amIIh;_v00~b!$v&E*#g%1m@bSRV=wpG zw_)6do7pDt!3u9t${x3iQiaVM=%lPaFp=ruba3FlNXhV*0*8G4opp)61TD^f9B2~aLrrz zEf3=1S~Uyc;(ty@$)GMwn?39WI&#=HOt;?#L%#X$+bPGK@dPf<=)%n1II+I^Mc4~x z)w4;M&3dgboYRG$n9V;a{3$0g!YniS<`&N5s%mMQ&q)_f>cYuMJ;vDN5Kb7A<*K!t zEalU4{GF)s*u7aXmNM^r$)$0Ax3AW&IQAQl-L>HszJKc&g9TxAy)5?F-K?_QN^^;Y z5uD($7h@6E^;dOOX2U5P;jl$u)4OnL1cMTrI;}H4`1A;}t?Uy1ES()W@cz~~1(u;V zr=PN&{VU}Crj&1&8hnnU@lWRRmu&Cw7<|GKzOt zuX{+tXMd!Vo&R4jW&yKc5qR_`dAI6dBlyC<1+(-ryy=l{rzG%t=~@rZrbBi@_#W!JoYXuGkGHC(PL8<)~T$wQ?#t? zxAYpMthn9l6f2(4%5b)`pk8oMZ{(5}71S5QsT9Xhf6StCETkjQM1#;mM`8^PQ3z*) z_M<|<@M_A{_#WOjC8R2rP>l40F$wFd#SSxnMUpJ}jIVVlfn2Eqxl#qnQUYbGyhG&; zC4ZbD9o5xjc(XmOuvN(M8m8xDm6DoV9+%e;;mv&5n=OTYoqSz-T&i0`0+wlf^?-&m zEH%iZ5%ADRl+q{+q|q2l$6`7ihj}y>OK2QJb3D$XNw}D%;5wR$+i5!PrW3G*W-7SK zKvA~SZi_A^ZZ;cR-aqkw+#wmlKgUR-oqx?V%9HypnIseHm2IuH>7(r>_G)$dzpXB@ zTUV09>kxdM9;al+^I890EV~hf<^Wsc?bcBq?JjY5qQ+wj*O~x36~H+P)ErNC9Jp+6 zj$jpGsH!~99cZkTn`~fhPKkRX%FQ}|ZH~GF28K5%NNr&c4{DGelM@XE+~COx%YWQW zGM$xgsPtr;{S#etRGm%q;>qC)#>r;P8Ho;AXJ<=h--Tx8%44A_Q zV=hW)J_gW97)A>)ffnHuIt@$dbbt8Chcjsz&ZP!iLQS}wmg9Ol1Dn`Uxt-c@ADxM9 z6vUIX3eVD6c%9D1dvqQ?rVH>-x(MIVdeZ1pHf9Uhh|Q-Gx{dnN?Nmv3&?vf#rqey# zau+S-x+dC8Ep)$P)v3sjvPHFnn*?VFC9>(`@rsMx1KCO5IL0;DISgtOTw)p9UU%f$#S4`Z}KOwo!kM=Qoc&4XoH zFSKgCu}bTM^R>RXLhFYcwEnnFD`P0j@vwFTc4`ChoHhtAX@7(9rdFZgb-~e3;4MqX z_hZxL=bPR8%E3N9MtQy}*tKtBw_nVJ;ggHLJsI&>f77YDW{Z6b-9;GIJ z`Tqk(W!1qttu3;l_9gfmApjo>SS81Ktpl!r0+9uqg-K>zv zg|-jP4t&mjrh{YoWJJD*8B;6}#Q0ltSZ}5BKHQS}OsgInwR@4LMR;4Ad0Y2kxORU= zYx6~%PYZvnp9&6h*)oZfGc3D>mwk|zeTbKRn3vs}BITEHz3=Ab#CHj#>bDEkZvUim z{#RAbs^;=Ku|oOo+oS)iDtG&0Z_|pqe)%cmuy$*0)KuSSiMO@w$kDo($d9r59%nM| z;%oB>-t?19=%+AB+l}M3XW5E8heqvrEZ1JJu0nryM~Yd6wiLPkg@0ReZDy(DmHZ^; z&qWf-ua{8%F%Egri8{&sf*{_0mN!eheY-qJncn_@DtUdlWFtH0!_-5>rSkCPvCE@W zB>HY7`glSH^%Sptg)HrB4A8#8(b{(yr|rcFod2n|AM>>XYQNrC)Z)N@_M@M8(q+nV z)>41={}sNr_Wuk!N^a4M>|Zu164~5vn1#quN=(*h?1bVazL16aGEkSNN_PA zsT>O~UW!CFCuEWzXZY5EUAJMNZpSFyi3z$JbMzdX%4NTvkL9}gbkzs;{m4m?Ymkva zu>ay4%LgoD!6YKPQwe6PHpR20ig$63;x&JnXt=#@tNSd;S>3a}+0xyRpvvrC#b`+A zb(#DI7L&fZQmRZ83`W6-MBj`=AC4h%Jx5$=Ow~&m5f2Q#H-_qcFjnt}g?fLi(903l zkH96Izg8cN>$&Y#y#jaWl?tI6xDKF5A(RBtJ`^MhLruUk!1gV^vtXOZO3CMzrxbr| zb_JV59st(M%YlW%U6QkKaLIfAxLUWzZNB;6f(zsqg7sqzuVHmxE;*}vjyFfT=X!D_ zBi*N0dEA~{1zV{^uZ*1ALN3=tt|`I?-DAtp;K^keb0g7hk?01GoAd5SbZsQMC@mn< zhcl!#4Cx4l^k{~36hm6ekRHd7j>Ugf`UKp=r?QgK2^bb6x@e`wWj2t zxPBkE6Q^3{cKEPoaCs-oQ&q*c&lOcn$SWA?E4y%21Vw4JS1069j)Hz79QrJj>T^)7 z&sY1iK`YHmS#vLbuylDJ>yq7Dd}*F-rAxaU0a0mIs!Ct)QKi2$8IVxvwLO2T^h}ch z`QCi1`vS>X-3z=0(!J1AC>iNKS~0*=*oAB4(JWohUR$NKnF=ptB^O4b&qt#7#FT$& zB)TG|{5g?mOod2!f zgtxiv1ARI6aNp1L75G9wLxF$25IIpcMK1Mb@lMizuf+)>4;bAkl2SM(nJyVfvoEf| z!K}anZn-Z-fl701tt@P>l$?ca_s6|fQ*&&stnTw9XLV>(nC&64|$vsHRLedIUIvUqW8sK3$Khs+tN*0J43&cp%3!8>)?NL7vggl=5x0S zA$>Kj=6t8V7B_R-J^I<$te>M`9uDWB&fNDnE;D%hV;2BM@s%k*t(8<(4Xf65*A84) zSyesErgCXNIqMg~t*=9|eo@+FmRUrtygBfQ4R7gp@VUH&&*j~GF7LtD+;6`gA?TZ}cg36xk$G+U`qGXE5Ujkbc*~863ky1qwhoXqnw5x2N zP0f-fIZLx{^-FtgwkKOMqS=pP6k!YPvBk)d!)(b;VoMT_`1XzU%1!HKk~6`nl|6E5 zPKjO7Dchn`QHi}%{M`bX^RiBO(pkcHpEoBnaef(zUS5AGKeM!0^vUM>>`1gv9d>Z^9(zb&tj?mD+Kfx_`ZJ;>-Cp$m;NfY>#yVY`WyJ0 z{uaK|UnSCiPd5E+a_jF^*>TS{avN2c`!22>Htnnuj-RmXb~&Qmv72dVWXsL zBAs)3+;e{&YI&~r_T;%<)}!aTLjC-0Yn0!yHnGXiDsfvsIw(UjK4wV9ZP+^K)f=Kp`c3g+sAc(FwshV_zcwfQqZcgs(< zxDPwS@?m%P(A|R7ZApi*QpHI%9uW@hA!tP?&$gGRQKZTFyk`)g%Jf z$n}3vO9u$`EZLz)9{>P|LjV9!O9KQH00;*N2mqOM@=TY30Rq-ficed-}QejW3=2?Nb0SOx$jRKI{XHeP{#DKCnVJ_L0Uuwt;F? zKB3}MD*iylXH@)=iqEO|e}alHsrZVDKT+{D72i z;D4vFf6$`e+t?56pVaar4fv4;{ELd8Y>>--*4QsJ;Ft~0VaIK(g`Kb=Sc%+8jkVff zAO{4)Spw%=P@!mCwLuQIP@hJ9I)dX?oX2gr4o^tncFr`ONR=cif08wxVug|HCyl4# zlRIoMil^D|t&_&nacQ1G!#We#E>t*aKv$i2v+?e{2etG>Ye545Q*K zD<95tHGZ}Y7V!~Oe;G-m^QdnW7DUi)e6+^L*dV|@(D_(=@^h#-mx_Gq9;fl~8lPa} z6Zs??tRw_i@NA7wwm}2?zy|aA6xwTn#-~~l;q#~{q!o&2!D1Vq#-|gU8T3}7@luV? zw815Omd0n>U^Aa(gH60l=jZEu4pC<=4W6g-`8r>q^9v9*f33oKS1QVh$_q{QEJ}cF z+)u?~T5kyzOKF1vYFkEFEw}M1u4%m52DcIBw-Hryc#Xzub-sf3xKihJ)D+Ztz0Mm5 z{whLzwT-XgYpGbL^YsMvLY;3wsp1zAf*Un{u@xIP+2CP*iN-Ir!DD_?s7q4Qljzf-+#cAGh(}@`Kd;gwCI&1)d<>pCV#Ct@A^)+F_kPqw{BV{+!OAry)m(9Y^U+0+iJk zbpE2wU()%@I)6pyuj>4FI{&@SU(@;PHvR^Glfb@3b8e?%sm|Zl`8zs)SLg5P{C%CH z$bP8ve~)zjvCcoy`KLPngU&zG`5$%uxz4|!>0j#nE1myI=U?mm8=e1I=YP@pUv>UB zoqtP&=taffiLc*j{2w+p5T%U`M8U!0d!7G4F#f4?B=o;@{*%ss*7+|wKc@5JHr~Qd zX#6CDl%T&Z;H#SLuL}lhYi1QpV8Es_NE}~Ve-o_t)zr`SRWaM#$c;N_bks8bH7n};K|*m*e(B6&TyE4@1fo~?>itV<>((+z ze~W@K#TQ&!3df4#r5yxND26@ElBe;L77`S8_fTf?CEKjT*$IOP$VB>EcGtn$@W z)Hc-A`|D7C3mDkV;nlP+1~cNVc}mipo^YL_mnaYOB|WA&BD`_M^wcOsh*E$%TjH;i z>)IF9)>h$u%jwA=@89LuIGpD9)ks(gAy|PLlHSTdoxh@<>Oo(9dwnbQlk5&?f8QEs zL4uyv*B3myU$ey_jETaQ8f%>rwMApFB43zP>UzC-?K#jk+p?ZiiUb*IZn^WYQICnC`#XT77BQhvDN=5Aoa^d#p?R^%JB5GZ-3&5(7`YA_53T01W%Le@RJ1NC*V; z8`cD>0zNVp>G6<2y|IN6m2y2Wu0xz0ul+yr4Jo+XcvAx>89uRhR(ttx>lG8Crgg9v z)UyOsya)?))E6W`0kWr42><9AnC@VYG031&WNyE#sZ%>(Q9&gl6<8cV+sPpRG;(!% z7?@w70XDFh;;&jk?q=+Ne+D%oJoEoMaX%gS^8X*;W9Zs79$Sh`cfa$$T0XA9I`hUe z!T#j`9Kq8@wf}dM&V&FNb^av?%U>5t2turjtGQ^ax?;eEY%U20j&fq1PX-YK;+em= zVD$Q0qlOti)`EfR6;)`jr5~P)`7@^M=+zN!O>l8-U3Iyy3d5b8e`s#i*ZKY7et+Gd znOL70sgo;UAEVU_HY^I(2kIN@{g`W`wXR>g!e6n}U$GpO*$7z;7ap#LDA1)EG?te`Q%+pkD3=H#2cfg@1*NsWgGvTG9$6Vf}O}O6#kU z0jaVfzp5(AqjrjbG(pMu!r5-{43 zS{d|@8x*!{f5P<|YNDnkV<3bt#lC8PuuvWdbdHJ5qK^bT@q0Q*t@P0qRb~ohE3Iv) ztME?>$b=~>7s;WScD9HiWje(>eX+B1*tsZX?Se%+D`XSwY&;c{*kn7KLParEOW902 zW^nj6pNi>J%%EZx6=hVMPsKv!Ly3sso*&8tC)U-~eSW`N)#J`xZbl63j=!7YsU8J*Jh_c8)+j1(eY-hEivt4vy+w8(Ay4poIBI#nb z#4fsve;%6X8H29DbGzszT(n$ojCRlHWCXMCIMQSnnQSV-=|e@|5bvYU80?}StFepz zNJX}l-UhI@?IMe)m^QJbWLim{Yhv|^`n4|O#6uGU?ZS=QV7IfY?ZQJdydoRL5;c-i z`I`FjGoxy0*#Gy8AG6TuPEhi01G|XidW~J=e-OmP%(shiV!T~UAYc=bT?1})7;V|bBr%zaDF&U{RqSd8nH|yz`4~z^ zf4jyVRDuinHBn#}Q^k2`-%f?S0clc0RTbf1NU~Vek&NTwD|`W@RWU;{O`~Eu$ zIA6>mvA%+VMIK+f7^sT_HI?`jt~{4rf6Nsbb}^6iaDI#mp;hcV(NHYaeA)|YaQ*RB zbjTGX!N8ddP))@J#M*MP&@O!Rwum|^*fLFEa+}q$CX^U@95NHaFBW$s%puw&ni@H& zwgLA*0cvY;fHn(D%3TtR6z(UjaPmNJ;wcI0C6DSlVL5TWRae@G)b z&~?==b{S^I6>{@Py3uD2r_x^$pe;nE+eLtgwoEM7M3r4svrFuvhVLVZ48N9 zOZG=h&L3}Q1!TeYkW=dtig3vHO_RX~>W<%6Z5J!Z^e-YPT|G5{9E}O`z3m5UcEBwOFHxf3RbT5eXtA!i0xf_O zxT}v{Y$oGr88>ZK@dRwLPADiHUovs#M0{uKX^)rTxSSj;HlPZoxZUHY6{GjeM|4Zw zZfaVcjnYEKeU+~&=&#R0e@1&<^T;`0j;{*_;+Q12dv<Ub>j&rL4Bp^! z^>MjoE=9BnbCkd+&y<5~Sx%d;U+SxOEn16Pp&HG@p~$VJe%E4JF>9c!BAmdw7Wu1c zSLfgoy4h*7i!EZSCa$oHD~a~ZV;5J6@tQz)ca6B#F0NxwGtlx#f7)H^?d%!$terh2 zu4izLp_bAgV{b_L>ZRCAtSWppMC3(&mk~RY2!&DsZp+eIG#qVAM72nfreN^vt4G7WFhs8#nCa*h$|SVZm6PDUPG|M%%l*xC$=HE82*A|_@is#UTZL9clF)jNsNpE7<$;WZOS*|>(bmf5{UAWZM(y2lvHDW`hA6etCEH{=*MDS#5X{9{roCuocY9PrV zbO@eGX%NwQpf}T%iMFAU;)4b3f_5=|sUMBl4z>&lxZajY>YkbB%CxiB*&7Hu(~H0o zG7S=9$2?Lye;djH%fvsDx(nv_&B}2P#8=*Th$e2ei`z)+JB4g(Y3O)EChd;M;svPI zzIqDyd(Ml=WPBCNG4iYMPppzRWurpI7l9Q_3mabsGvi(NoaO}jG~M#Xsm8ws(=ma9 z$6!R93!*qzM(vxBBlWd1xR$5!^Wu$2X%mJA84S#de={;p6CH^tsDY~pU*s85HeSw| z5f2=luxqR6W`EjZ8d4CAe&{+eMox^0h@L_>V(2(Kya1!KyFi$+88L}#h~Y#Vgi|cZ z9DAZ4CXFlW^cO4P014swDk}@+HGA9}J;X{>(6yyyxqmGRJZ>%qGvoF$F{S~hETOW0 zJb>{~e|BUQ#>9livVlsB;GNN3<7=y`C>E+Uj(6N09*V}fi_-(Ki0m3da$`*im!vyFq6 zSwVmPk|lLA%|qT}OFkXFMztZ>P$p)eWKvmV4WyIi5UtHtC2J}vAdQo9PaJN4_Z9jq zCOvKk@vN$Lk*})U@cqb_9;duMre)<3mk81oU(eG~ineK-8brnWOm|TBBaM+ z8CFykqd3Z*)rJ-FmM%3`cP6e`fygZmR3VQ2+AWCrL_M9D8ggHX=FA_v;|_k+B zLq+&PIIZn<39=89m-xCwd#XF#ja1zGf3N@Q${dx$JVwf=Tb2=Lc8L@B1hmdyUAxL} zUKi`qwTSNf3RNWO^IwDCZ2-W8(#*m3%iM6Nwz9aGWlvj6O+S8?5(Z7$IsKB46eq z+UC`n#5yVpjcPVLZ>evUc}+;)e>}#&TxsL!$1nBOmC{LjO@%)s6_G1Al=NCjn*cF8 zDYjQSVlz&YTA|WM4iQ%uVoHz<_0&^ITzb52a`a&}llG`@N18Sr)hyz0T&Ej@DT03p z6+=5ZdmI<2nTGmrCD&lS*ZkYx%>0)hMI=YA0;l`xh{ZYo&J`6gLR;;tf2)zPR6;1a zkq%eGD9gC)=@f~vq}elXdMs#^q?PS3Vw@XuFmHxq6tm5Z=49wYzVNLziCaDy-B2Wh z`-~DsI;cb-mHuD=1vY#kgKAUX5QN^)4f+6MXG0ovWh2-~e9r>_&PKr|x*L%n2cN^v z#WG*EkHfd|Y(ls`5#J`Uf5~#(6#3+ISQqX;5C00I#up*n;;8yGe48HA&**9?TrWYu zrEI2zKP#$zHold$sh=NJp9A#GVWd6}>+{>xF=-Ch%Tv10^%cI4#4jK5)9Ti5z=D_fShSbS-;CQk>Aw#N_~%frdzR zhbkBbHMpf(M0W*DgF2WGLADe}s35v$bVD2iY?*;69|Ihlfi3qOhHg7R6?;5~pj#2H zp)^BxukknlJ!BVFbwZ&TddfO&s2Cfqc}n(C(4EQ=Xv#i9e=kR=JKKqqd&!ZK06ntz zg7XMu&|@#SvhRt|LiW3yiX6~IKKD|+?U1fC_b8-g6A{{Wc9-*xLMNxd9D7j;g0%JteAc$GZIvvyzIH)TmD4v?HpXhV`^iUD*@n z+s!Cs0IQL2e`~-B>mUg>A}=q7zHliFh0SmlY=M!m6-Dm~m;zU#fL@Klc^&fedKAWO za1m^WJK-jH3L$+Ax4<8v5&nw8cMNWa7TCpXa3{0F-K;Cz!@5HgbHlyN3-_a)dH`+I zgJ@?SVg>LBD}zT-)AyqI?qdNsAZ4X5q+45{tHzcmf1d!G#;Wk2t}|P&%(ApF@!s_}nT+lVB8ikAO3^^UK|qA_aOkL*~NK_~I;TYW*f9;YsK-N4P`M z)%O7OE1jc|XqC=UyUCh`7*slk_>@pOhr}+qbWRGjrr?vB?Q&cSb*19dN<_yeDM?!C z0q7s0e{)x`VEH79`cp{jry&6jffEj+-F{B))du_oXbgAg#J$wA6~>OlNF0rt#fuI? zHw`4HJd;Zf`oHwJe-dhT6kJeju=pm ze~v(<#Q`~00CY?5qlXD;T6b$-@`z74Ti(( zFcIEBm46G0;cZm;chKj&i^lx}RQ?ZP4}1gP|k-%AxJhLn@g3$YVk46<54MTO|z0*SIdyal?4UW}HK7D$&bqeCs>mriRQ=Sic~Bj!AqmoN&rT8gL*k!g7#|f8+%Z zoxvhljKeYb7@ub$E=|}0x?|!2m_*aaYfYA%>r66@-nfU;Lf*)N{y0x_YSPKr-A)ZX zauX!V2CBH|%@yjhnq4lcI3+%Yu#-M`NLS=Sq#;h#P>NWuJ_%B>Jc(Oxg+3TOxfz4O z$mkJFz!+wMVy44FmH~I7AY8|6gZ|f!+DKh^%Q#xv(b(gB7~yigHSxjZA_Tv_8QOqFg;HRe>FD4j7CyS zq)-WRNjU(e7-Pt)If&k8lInXsCQ%*U5Gb=DjckhUjmFf}Lv!G)2(e`Z$a+Cf))z|H z0GP?LU^W{F=d)}i@*r5t&>6GgNZ7MsCpyo2*=Tf{W8qnL4*UVb`L8jYCqgHKnxPF- zPrw+Bt<~5%r0n`IeY+ube@UDVpPIf#wCFtyvv))qy`mY)ie#4)C!XI3Hk^0w(FANci4@HNqA>0*mznu@j+(t+}e*p7#v?UTot@GP8 zB9aT*HueZf7It3H4CQV6Gq8K%Uhui2qDF(vqYW|-r-|bXe0p2A-wM{=w(UD3gAc-@ zIoPrTG^Gg?u^%cZh)y-F8dBL4k!^#@o^}iiQQ2smh5cE3q4EeUKLGwl@SAlK1o|tE zs-rTLT2OkhE%M2o%wO~zGhHC&Ipx}U9uC)q`Clx>9f*v0T8y97?K z%`A~!#(J>JSq{5`<*_T-WOfxMr`KTOcpY;63JkDrlDsd3f5fhxI`!((0(}*&6tLkc1xsIlfQ zGY#XN&t(YXe^R#D@LtdZyD2|bY5BI8-enr=%dquww#8gLdWyB}lzXtYm0e*DU5QxI z<_3lEJPMYSPJ3dp9@CxhRxNwFrzGs6M5TKKdzoOedm(|{2TAM!=)v}&OZpA;V-JCc zJ&YmHqoy{Cq!!3v8ZLZgm`uG*GFd}Tc~2W`o3VBkf4kZoehuPE!%GfA099+5V|g=F zQFPc0)y+^-7;)_b+;gy5S%_g{2VO%5V;Ek;oWYPVnqr4sYq%}|@C_OhbBlO1S;{xTR>55kH$2Vv!$UI(DA zH~#I1f8c(om!ThY3JqyMOjk)ocd98i40jH~e2S8@C=OWN7Rl$q!j6E09mUx5MMUxy zbo{THX^Ut92O^o7BC)*Q#PVKrGUR3!6P86ts`15W6ecLUAU7M0#hOE~b}y_W-1|rB z>&bRe*ra)*Fl>^EuSPz0kl_Gg5cbC4+f&-?f7d}}Z=tHZ4MW*GFp<5F{`4c5!#%b<=ZWo+X5cC4`72f`~zlztjKj1jXzh(4Tz|XR#k(H2WtMvL7YKZZeUX zZJrkmC63XSwd{~2dAt!Ba%aa-Kii}}i$uz37gcr~y>Scb<_YY%nf=N%G4&`fwBhMe zcF7Y+U`7&o5H`(eyP{J$2$#&kMJ_!Ef172Ddf9%sobU+CtED{#T!4iuki<0@$3tNz z+1f_7!`$s!Q^6-iG&$FF(lHiEX&-Y^PfEf*7}^9jw-N^mr$G1WD^E`Hjm?KY9hJD(s7M^n5hRfY@vsF zU~)h1ye6V&GFIhilX)LV{rNx`%-t}Od*EE21C#h5DB^>mj1Pee zFs`cL!(cH#OVXqZC?_ak+leW`e+kHxO1Uoi7wCtZyo2pBgVt75C@Vh4m?}_68OwgS z);uG;Zmh^v(v=>&p(izXjMnRA0*#^jkj)AP7JtMs#=*u7kHd{IDfF6f3cZbTvBzP% zkxpweTPneP%i`1?hnqN*Q3K{}~VQHkg?o^zbQ#X!r z4!NDmK1dD0w-`rFr-V-e9SvWX^$2_`3cBvJhT+p?MF_rToIjcHQQ}SbdGuz&w|bn` zX!th7)<#WoiI_vEe`n+YMOwsiJ_sIsU5-Lo1)l=)W27SIy58`)?lyzFro>sCsyy-A8IriyOufier9DYk zcSCMOE$Hxwf3meaJ)5k=PFW|Bx`W10(-3JmUTkwN!FPgA)9u%uQevh`gw)`WBzdIAG^q#IpR z-W#^_4;%3p>lS?iUFb0=z$~87Id72+2#uVoIQuZ{f7$_kL(%u0=(NzG?RMOSFF2+O z{ni1PB=%%u&~dkMXXG^;;G;NoQzKkzA@5=2tdq0TDUZc=Ot+19H1s=QU<`P(eYfMD zHfu;v(@YVqF>QLxG-1yAbz98j*!DYUJFe;EPf<5Fb1~Qez7Jfy8N3{$5Pkqk_~Xb5 zbP4fJug5#<~NI@+36MgMNVl$1nh4^qVa+Ao-V>;@up3{Mr6^h$5&W zj4ND6Ae9~zV(bHF6K1}~tJNzn;i%I|18|dOf2S*S1KA8sWoBlLv0Es~mTedg-;3|} zH9}IPc7L1mBK|Ho`FqfhzmLTG0A=|jj1@nD0{$slna`k{e~wn>O9=9>;6na2T*<#d z_4OcF+`E#RVa%uZVOF1Y*q!!-EGynwpx|B43Tb+q>DBzr<<59WD~L81sHav>34 zf4@UY`~xZRJyPNaq{NR%iJy=XKO-fMAthRn5+~64x5ACMwOa*~R7eC%gbKZJ`wxU7 zQ&EW--C)7~s2p6L zZwrjUg@%Sf2b-`$l1PAF!VW`4BIJoASRj&NiAaHP7KAxGrGFmX1F5F=o;7zvZbXo+|NC@qjeNGshD$=`%fWtqrFLiI4ACHdlY)2qRV z&h&u~jZR=!3iqJ%r5dTGnu!q9ienYl1D z)7fsOb2CF*yoFGBu#N7Ea}cX@!71{Q9^+w*m;_VBWGEI>ph`@I^`Z#2iemV+m=61} z@1Q7!Lt>_RwyqCDGsu`X$(?kJ&eG|}VJ2(8Mb^^MOr3i_JaiBqp7SU?f3hDQ#cbs< zI_%zC>4=s8#@_2s}Oes77k2k|_(YRy7!6NTd;Y6mhH(eQ;r#=c#P&E0Z^ef+l z9K=)T6L7+A!!IDrrys#cLcydd3l5kY9gC=fD8sma4kU}Y&_&EcVVDoS#R3$FO2`ry zz(7%sQoaxhgb!xmvrJS#f3@(#O0igOwkIe{HTF;|dTt|be@J5wQ{4VDIFCU(?)nk- zsF~V-WoELMg$+_xo1^RlaHtV9#P)C~Q6*zG6#Z~lw}(C{8!VApXYH2rMQ? z&G$H7qDO=fvyopQe>Q_AE<@qJ9A#n)q=~Iam@82xu7UyLYE*`6(BfSS`Qkbx%neW? zw!tiM6U-GiqZPabtzaY6h#jy=+=>da6Rs0?NFsFx%Lz!9F+x=fjKUWSIu6YpL#$@D z-xQT?XjDi|Mmn|@N4`eLmLDTf0)>?7z6;XmSmNa}nN7Wne^iKkJM&g#S2>gkirr|x z?*gm18*TSJkS>~_r??mTiu=GL?nkq?2ZoE^pxJxK3`4~Uu!gYhi!aB(8iVQq_PA*Q ztBtQO;EOP-B3C7B-!!nbgs^?wI7E?m8`CJJZiX2@|dbk^(x2jjhN3kuA$^UG5)yMqQ?!9isvD13)zX+vBwzshB0zK zy!o_8wv;KkYBWuA($z?0S%NeI@fcDSw@jbBp?sx^{b)lTM_KtT%F00)B%VOUc@oOS zQ)n=shArX{+$ElYm&Eh%x;P4Ni5K8q@e+I@UWU)ae=Cymy+A)nX%bPMg`>&=1NvLg zk|Gn3=)YwLP13JL(o<&ionx!aovnG4&p6d1@QG6;+H3S6+CS&ikof2AfP+$HhzlBV zL8r7vazQt_pm)Fptqpax4!96^+!=8}YsUr6;DW{R0?NNiY*3q8`=ndivf(u};jg30 zz5$8ie@$?Rw@_u@LBW0(P4|1KuJ6MI;saPFKE$BpBaF~KM*sXNye<9+ABivEQ}HEy zF8&067GJ~P#5WN(B!<~AJ(>*`Vgsk&IvdK$zd*Z&Y~b`YV1kiy<&wf41&tVkgnz3M z#$;QY;q6Aum~8Ty9iouq9W#Y-yh~Id?#NR`e@QR2a_nd}8A0|a!g-IWvGj>A}8ohKqyx;-&+%V}c7=9wEZ@t-PPNg8pW{%se ze`Cn-kjL?bG51Sj_mj?a_l~cOhk?1{PccwZrId#~d&C}J37IIe-=e7g9Yys!$PnK{ zw)g=fi+`e+{s@)gUl?Njgr4IUxI-L6&(#9oiB>igP46g$v2hA#<%(ccio!N2D%+}9 z*zM?i?^AU4Ft#@<3G7M5&Yn|}*ij{ge|@W@vL6)(Yf;j;P&#p&lED*|&b*t_Rf>9l zu(!~8%r(d1+!L^pBJ%z%uo9ElB586G(NB%zi80pyDfYB^(&#h}XV`h>v2)0$v(bi6 zH@rB89(gLccV!p65+?6eA*!0D!Kuo#hV4%E5Nyh`NC#e3X35pk<@a-6?}jCkf2f&G zOFEi{Z<^uHd*LtE15notOQLA)_-pilzu9oW0r)mg_mXidA)AMh;onW55qYR8+pM8H z+$6&T#Kwa1{Efui^hw^J9i~FGo zx`y`u($fFF$z=H!uxs9c10e+ZP`pevb>sPutUr7v_=`az~L0NhFzj8_K2d5RlK z6c5Z%ys%iwhO3kuxJwxX4=97-5oHKGsSJhZuhIJ~ap!bi#o_*@wY-za(TgEERK z%4n9NjA2e?Eb}PmqIivGla&cK7~8lLb| zWLUQ3R%pb}aUt=)%kwS%L3rFRAxKA}AT`4=vb=_Y%c0NB=xZ>GG$_q*d_RoI)3OnG zOEa9v)6Jwc&zg<>Er(%qeP|4 zG7Tmx)1g?I0n3#Ve^{Z+gd3DuaEnp~`;_zHpfU%JDD&V0Wj=hNEP%f$7r@U-IkPGY zS$D<91}K$iHI}e4WhvXJ1lSH`8M{ka&h{u(>`|qfJ*CvJ=du4~WhHw<39=8A2KJM( ziYv-$o}jGZot3q`C)WEa7jmz15g)2-W&w_$Fm5--`8Xm8<#9 z$~F8pNl|5pEVkAN9p}XN22Oo!mR#;63SBB{`j2?X( zA#dYuF#ZAbf5@aOxgp14BAUV$$YFi(*|`N=%q<(bpi?ctw`3aT!52#_WSQp%5wOUk zL^PYvg%3>K=5ZJu)h2qB15A%|`>h;6W>QY}eB60S9nO0K=RJunN5YxkNk} zUg11FC$3M&ls(b#eBS-cY9``uh2{*3JBQq5`$=z_f0@5Ib$k5fqK`+(0>4G+i`vX= zjWCy<39;$RB$<{dGA+rIsf_WS6VV=fNPE&)V&pX`66%@w)kIvgydPE$p=&;j^m_(f z^RwuhpF`Jt6kYQRaF+5Cj8tBR(aP^2U->;uR9-_@{W{E6-hy)FZ3rmuLXGkstW-XP z)ygMuf1&azT&(;7E>}K7rTZK{QNBdQ`V&i1zGkV4k(3OFgs2Yz`Wpg+o>n;l1Hu*C z3Fv23`W%OG*bo)Car%GR7)%y7A(L&mn}?!3GWs~fBh%-JZ_!VIBw4@7Zb#L3h^k&m zNPmQo$sxP^T7-7yN2=z>A}B0$@Rj5>PU6wPf2Bmn{b?*!rVVXE?a+)y&Lblo=3;3q z?G&q>=@Lz>$;h*AlzCR@dvjl8TBpcW)0wW69&aV5lEyL&m)0jTw6i>jh?7DYn8c<~ zX{^h?k4)Tc8^G^|M*57%9Ow)awrjL|HN$Z9SQSQmZDM-1o}ouKtlxe+jB+X&Xl*_& ze>3MOm3Kl$+hMms0{SxPjx%&jSoNmX12P0}BocKywF`rtFaYHm^C$)LCx=YyJ{-?R83T9!F)ROJCmpfY=lHl8H>DVxAY<-JWcxBKEWHp#$I01aF)PWJ`@1e@bM= zJE0lZ##;idaA@XYGMLf|E7Dxdre_;_F^=p-wzL;#lQtW#-dG!)ErqT}_^oF|{7jtc z+gM;V8!VVy*wmqrtPX=T^(^S34u?#21i00aFiafGPMAz)k3IKi(r*ne+=u@X>gf3171^0;TLrloK$Bsrj|*54gtH(IO#qC zeWLAe-{^|j(`T%a1--;x4u6(o*jy#P%}rMt!J5W;HGzs%ON|PIe{D^y=~goz zm=QTEOt-eTe^HHO`b+@k>`;`PDWha7+KvaX)`x0sOe>)vKi~64Z2~5?8KuQBz>&5% zrkB13w8SnKpI#jsvO4IFf;PGgXx`_+*Qd5`{4dZ0X$D&1kSvcl6oO=?+%7FG7j8>tVWj1DcQO8Mt?M?`2s>>4)=d;GF%;y^m#43!?0a!ZwL6 z71jGub{>Fk>YmW=?i>j0cj1rwN0}e@I}DKWSK$(pcTXEY58;*{2CMp52oT*l{65U~ zi_8xf{$?J}MY#Wt$?PLY*F-bTMpLGYHNTQ|8~2dY@|1|Ke~_Iw+F6dY5rd)>D~$~{ z@?HAu!T3_kJpG*)K5RH5mCgLF(^Oj{X^w7{$IeG1piMwA2Lkj(*PXcLkSKTKHO~Sg z#Fk$asRxlpPk>#05|Y%Xknm4KSM?C|R1ZUz`Yd{$=V6F?1ij8t@To6AKz$Kbs4u|= z^<{WMeFeqge^vNB*56iNgOAlW;Y;;x_^bL(=;Gl7B$0?X*+~)-$}dq7=b<8^oX{^e zUJLO8_M5*TSlEsi1tu>>w&O*Z^h4W{erP*y`*^$U%kL-D_i_6l;PyYn?SF*Z{}{Lb z32y&W-2P{{{m)T5zJ&ADKS8e^-&gi&@dcF!*Ig<{7Iao+uj>!$DK6u z^ZIu{QfKdmzl0brQAdqTgKo_%H}nbeW6&u=Zn+2O7y3C;;<*ev-jm($^Gcb*GuXy` zyuxDre^5&Y2-Xu0Em$`I05Ns|08mQ<1QY-W2nYb0bn;A-A37Sd?J_Q9T?cec+4sKh z<+YnmNUtPF5z&T;8pa4=Mj5?Co2Co~V@5arzi1&M*d#h5Lj+-n781RT-b?h}5=JlM z|DAKs9q;hg%35;D-rxRqIs2abU^UIgZ`Ad^%{MpcrtPHJl)-+Fd+XqvJ8zY3kI}J| zV#6LjS}@7zOPL#0x7;<09NIc-OQ(&-V69E6ORno&hh&2`c&MjC0A1Limdy2-9ytKKvwn%U=*-2-DHq=u8wsH}I3tR(ow*RbSh4w1FB~LR;7(2^I~UX1ic?H5f}Nc6!p1)EYKs&&!6hEp$9d zjn#Izk5{Xi7&jC@UQGyQf0}Xn`N*NpijwZ5DELc~cAvT?@?PZ-Laz!`XTJ3Nlj--~ z7!_rTNm2am7AlIdL|VnzK-zdv6^y;xp!zyAE~Suft{SXqbi0kAZvF~I-Bv?G7`Rm0 zy|{KsMac_Olt4*dr*MT@+);h#(0bL;*-_EB<-ogcQhklrYtf?NCay~X%l!G83Qd+-0j<27UY4N0rdj$b! zdOSA1a8Q)%Rz(SsmT!sI#829#dTZu(IS!nL=GySI<7$XDJoY?>e{VqrGtJ&ql&?Bb z{&{TSe;IW^A?AwPXj}Y?EpGJYw9veDVR@$_XdMZN>o@xw@POfscAn$OV%(Ehuerqu(wFfv#1q-#H9lGPZ&xfhj*|0K)gEUK*~rYY>yw zM;qP}Z-t&~x{Auo9@oLzT(9%0kEVGM^U|gf^thYFn+kV0*r;%mz9r@W=5ohssIoel zOVe)$^tlIHF;_83n+wiUeYl$vc6dAGfcHQ!fLO8nL`|e)11#lf_7q`PQT>^-laYrj zODIZtyM>5{DQu}X#q3ngRCHPO=At`}h&$WZNl`j_e!RZKEX}C1JJmqVDEHFFg)Yb zf7WZzrVe=bb3YIj52DISf;V1g7{ciF-@0)NuR_8v4>Ueb;1^9_rGrfHW6jCg{mqWl z4+Vf5{)-`R!V)B5T3*QDRiyC|HHa(y`chPxZpft#@U-mZVU-ND zs5au$>6Gr~$~T}ix{46=V5HTBmrX8c+m)kJ2O?CiAd%!PvO1LfKbRVe2$QSu%ho{u*z84zxvvN3(u+C+8(({?df4ei5oI!v_1_z)`ySPgUKb)zdAagC z1&h8Pz-9Q*PxUO8iuMJbo#J)A-qL=pK~ZkOxClvi%@G`I08zBXl@d=1uqhGWC7lA; zrvNJhXfTR1;e~&(L-pfe|49F3>^KN+1=i3}*nN7B6RdR!v6P_;$wK(Kf4juGbUARg}Hk zgd=Yis6iT>qO*{9XRm<_dsQzgdrmE_jmPfCc$EWOj}Hyludjc-6XT^13pvrd)G*F* z_?ayuC%7xh7DSG$v&nHTBZ6F4=r*)qGAdjbHq^XeDoJlH3+|Vl{i#)HIJOELTR{T9 z=!V!3dt4-F)Ux?aYT=mobNM(yo$rdZ_54g`>KcRN^WiR`Va4;*uylmOI)sB9IvGVD zcDeJjN8`f4IGXT8OjbLq7n=0l7%%sfkNeWG-Fh?7^$f;qzY^MA}#& zP!?9zY-BkeKm)hxXuC2&6|F{AiaiMt??iJ8^fSik3MQ9Dh{+>?Xa<^G(IND^g~^Q- zjaor1E^Rea<}KAz!*}c=CWqAIJH5$Ls0UDAoO=%OaYEvle{qZ~KPE`HQ7dQnbvXG5 zoQ#06`=mD)8+N0HXbPrYhoB>^j9P?l`^j43lZbD1`dM@~WX;AAA-nXmc0yj?uS}Xt zdAJ5V>^-M0GQ1_a?-hM(_f8* zhTOn8|0>qzUq&0pI||+pJlqUH7e|W8;4PwDZ>(})&|#cTNp2q_icS`5M{E{r2M0C% zegopi8|7U-n7*DNXsY96b)?Y!x_f<3Kxu~z#6)e27kza?_2x8;3!QysF$6V70tMT7 zK~V?$y&Y(XF$GJIT5@)uFTK^Z03t6s?SSKb= zoE4VVJhHz^BhOx2NsU^7;N6j}kTth^kLKMm_3A-XT+&irXXa+d3`q1g77%w_)R;lqB)q@Kfnsce~ zZ~#pPP??U12OlUI-w{1NVJF!){+hsH^?lW54md`4`IAyAm8Le z^$+RApc$)_Bf>Dw`i?QXRZkl`sovk8{5u7mQav5oMmezR;zic&YAKDSi+BWaC|^?m zaKE6RK$qFcjcB4968-cU>kW=97tDwp7Tp-#Bsk;AJ?_i#zI5k4!y3` zVU57cmSTLsUe$;Dt!QMUU;7}EvJeDvq|R?E)?U1#^SUJ;GTL+!yyCetKy&I?){Un2 z6YC?UT0QB&4H(3n6yK~z<9Hb34JC4@-s~?n%)G3JYAPPw9LD}E4CPU9e5)P>LEABT zYN*iO8oz1Ur!dQ&kKi8lCY%>0+Jo*wOO$$Q%VQ{(AzmNH_o2~Tix0gyiaN)Rw?Wl9 z-p%(_lV5LKVZJ0bTsdrU)(&{iU46z;&)dRbL$)9kS$aNf`R${p06rDMLZr|yxF-kEt>#MKYl|`Pv!H;b0+0vSXuO2x#^Vs2!!fo=JX3s#}^n%Oe*lFsetq<;I zcH_rZ5VQBhkXMy%qfh$=HCgV}Vrbzu*4kZG%WC;E3@w#$U6E)wcM)MoJeLIKzHV$DK_c_XjBsr;}iH3K=jb5$i`u0&zu>I@yCdzoC zR@FQ=<_?CkyP9a;9W~rpy3*{;ZWP=1Hc{Qt4nDMSgKDC_#j33fqs(3tPBFWW%Mg(#50{SzhITXOZQoohix6`Z4p3A@kdLrj#t%jQk~PxS0<`WPT$ zMw#eNo-IhLluSlq*PNZB5y~Clva)s(6s6`E6BTc_h4Q|Rhx4TFk;)W=!g{oz@><*f zOmwVRjp55$cF8;tfCyWP9~suI6cd$sEUr*@^lLP!6qXFdPl%*BJ{9)?chqRjRZ)!V ztm!6d@z#ds~@mv!%*r0}L63-W5 z`EG4SO7I!Fafh3hZ5`5W2YwoGO6!Zv38Gk>J`~X_UUNh112WpHqRQL!( zqi>q%;6z(EMLpC3y}66=ws%bQ_^H){A|XdxU;81(@4q$C_Aa&vYIYa)Gtny|C$=~T z2yr;{%G+T@*KIaa$al61AJ*RgHf6(D1noU!uzV9g+{vuz>s-<1NcVN&n??=yUsT0T%~2wRwWJ3P(w`hi-P!`k<-=>$KN-=a@oMfsW;JJqzElNbwggUytf zWGhF99to>@O$eOO6?dzjM}JJNEfm}PBQ^eGAY%5-Kz1Trgk^Ft=f;|;S)8qm^gzc* z%lf5N!T|Wr1qkIHWqv&~wJ1Vi;chFze9@yJ=O*xj#xk?=-e+KI0L~Vf^9}9IwDi7i z+zPgRSt56XFI~N>dU9?$w|iUtR{(YaV7ZX`_vFU;P~d$%axUJ7j2qu`Q~^}Kxy_a1 z(C~F;3g-6by!%l%N1H_h$r8r1xOBZi@ZC6QLT$DC%p7K(wLuNxSk?`n-z5>*w-E6l zzsG4h5<2gwQCjvjT@OvqC!1OJdC{o#DD<46x-2WJrI@Kxt{&J4tU}zKVWvj|P$9A> z!=(&Q^~5F9e}p^N{_t^;cUfXi>tw=PoAJW?=4%JP?t^?@4PXIwz;Wkv%uF$x)Cf)a zzzNXw^Eq?c)p$QzK0(i*(W^1Mf)9sM{%Vo02IJ0H_9*=us_18u&@Zks38Cb^K($g( zHl9$pX_pp3jQ?#-`smGuQWP;s0K8kab2|rkFB4DGH6&Rc_qeRI4)aRU@KmvU@iiC6 zRd7WiTp?c#4}W4#GfWRpYo6{xzn;?#7{D|qKQq(SOtlJaUxbTBhA8*X#O)ps;{!1u z((d!@m6=j!sPXSS1`G907uaUa1+?yt7EV}UtihK$&DCKiWMMAQ#X9At3U?xdIu^PSy^0dU?JIIo&y?b*75 znN2J4Y|Ym0^sbu|0XqlbHHeI@U7UrEEmtejj5B(H7`*~YZzgceRp{^v+!!z!mYy+t zIzZQHgelr8yU(ju(AU~fjuMur!F=rxw|o6q3tTjZjdH|nYKKtB5fRh2eH$NULM@1u zVYTVR10wDHS`Y2D1Vb?N=@i>fO=k_(}9d9rOL?DFEdIkZjMXQA~{=xvW(KDC)jyZ$3Xq@R?mLR2l z@$Ds(LE!dJV)@5y-0<>giL>zX43E|v)vx!a-x>>4SK%d@^fo*A`r3S1YKnWe&mndr zz}J+xuDY8q3!~37MLI>U8u~gDMeQxxtlHArs_f{(bI=nT>HwRk*Jcb%i;ve~}=nUwK4N zOol$`J`_hO|3D!ZO9GmEPr~ z$4t{T7!NX8S*a>VQ`YDQfg?-RhBiJPLCen>ocI$qH?7B`!JGTTw2m-M)_Kdr%4$$F zb(xAw9!5h{$sQC9pUwLuv$l9ywNvKZ1W~&iPkFnF$vqFp$z`Oeuayj0>X%xB<2#YD z5ol$JoYtm(X?{benK^e7rj7-%snE1hZB)B2taQo5l%))mvLkOnrl?&$HOze@0Wb~# z>q!w1S)Q{MO$qI!)U1^aK|8}aH5KW9+2Y9Wu+htty~&7UcMp=F{hx8Dgw%`Tq)bnU znVk#r($JI0<)&0^jxU`0Bntu$G_g5P1-@@ViX8M&4XxVge%VHPd{%zN#uX~$Mpq)vwsU~}gPy|d#M z#;rvlOov{X%D$ZuU^C&r$lgZJ4_R=z-*+`H;S>(VQ>omaBy|&^os=SgPEY7nn;ljJ zpt4ar`*0%C+#0y?^2Rv`O6>cG6r0-_I@&%)~CA@PB;3AH1ZWQ}BYEb~5WMxe~#%V_I3ezo3L`L0%6Wg*n z7Y3GMB=4k6=8T8awyC&6=WORqhR%qT|KwR-_KhVqIdWKP~<}Q;{q$?EI_Nvo++Lu)(@$KWu-v99LMrLMM zB__XEg&SjTP%I3KZ* z!ss`P(T%R)z~yq9cNlx99yodlZ^)VOa62>Fj{@fCeb?%RkTbd9znHMnD|mp5sW4|w zdk=_sji{GP{OX7HMvPvjgK}dJLKPm1ve0^wZh6#fjPHA)`DfZ|XS>G1H3w4@-f6zz zPjpQN8(ryh+;DObZ&wx-PXs5w1B7hLJ%f!^c&dS@)(9?UoE$gV*f|zKHJ0PO0V6*9 zWxM)IAcEc9$(6RGGZPU_4^xE6iNi-EEQ86ZNGJL9@pQAXlZv+ut~7nAXkT(yR_zjt z4Lh(wekv>LVbdzJ&m>jk_UsvszrZb9fkn>kd{1sl+SYz59YxXC%sI*q{0widw_Mu$ zLhVJj{xwNvnSH{ed9nMr`q^mUXro8uhi^`@1l&JtVYAjye+`h!+AT-CVMC>LxRzwg zGSbK2KaWy6!}H^pTvq~Yl)6^^O#8B}>t8@vBHTt})~TLVqkH!4K4_5r%`21Tob=cy z7Aj9dWu&Ciy`ha3Juybnzw6*^wl>cB--5EtQ&=nCZY*hJqX%C)1WR2$+wxo0eK*4K zQm7di4VT1w#M{Vyz4{rCfy1i;?-qW6Z>pt!d_AAmgTt@P0oea1B0iF|9ho*d%Dy$s zJ5i?D{wv8L(%Ke#Z8Z2VT*|UrV=5dEl3x64qu1lraQ-6ezK=)ha>TPID3luGqwaQkKequM(yrhg~ck@ARD$U&}x^_d`=1sdH$g)7A z%*SFsmEFa7lj}yk!CS*_+dBlPbO;x|{GvVh>>>>>> f8c15eb3160b509a17e3d70103b237ea8d666c04 | ConstantEnum Name {- name for the enum domain -} [Name] {- values in the enum domain -} Name {- the literal -} @@ -89,12 +93,20 @@ instance FromJSON Constant where parseJSON = genericParseJSON jsonOptions instance Arbitrary Constant where arbitrary = oneof [ ConstantBool <$> arbitrary +<<<<<<< HEAD , ConstantInt Nothing <$> arbitrary +======= + , ConstantInt NoTag <$> arbitrary +>>>>>>> f8c15eb3160b509a17e3d70103b237ea8d666c04 ] instance TypeOf Constant where typeOf ConstantBool{} = return TypeBool +<<<<<<< HEAD typeOf (ConstantInt name _) = return $ TypeInt name +======= + typeOf (ConstantInt t _) = return (TypeInt t) +>>>>>>> f8c15eb3160b509a17e3d70103b237ea8d666c04 typeOf (ConstantEnum defn _ _ ) = return (TypeEnum defn) typeOf (ConstantField _ ty) = return ty typeOf (ConstantAbstract x ) = typeOf x @@ -104,7 +116,11 @@ instance TypeOf Constant where instance DomainSizeOf Constant Integer where domainSizeOf DomainBool{} = return 2 +<<<<<<< HEAD domainSizeOf (DomainIntE _ x) = bug ("not implemented, domainSizeOf DomainIntE" <+> pretty (show x)) +======= + domainSizeOf (DomainIntE x) = bug ("not implemented, domainSizeOf DomainIntE" <+> pretty (show x)) +>>>>>>> f8c15eb3160b509a17e3d70103b237ea8d666c04 domainSizeOf (DomainInt _ rs) = domainSizeOfRanges rs domainSizeOf DomainEnum{} = fail "domainSizeOf: Unknown for given enum." domainSizeOf (DomainTuple ds) = product <$> mapM domainSizeOf ds @@ -114,17 +130,28 @@ instance DomainSizeOf Constant Integer where SizeAttr_None -> do innerSize <- domainSizeOf inner return (2 `intPow` innerSize) +<<<<<<< HEAD SizeAttr_Size (ConstantInt Nothing size) -> do +======= + SizeAttr_Size (ConstantInt _ size) -> do +>>>>>>> f8c15eb3160b509a17e3d70103b237ea8d666c04 innerSize <- domainSizeOf inner return (nchoosek (product . enumFromTo 1) innerSize size) SizeAttr_MinSize{} -> do -- TODO: we can do better here innerSize <- domainSizeOf inner return (2 `intPow` innerSize) +<<<<<<< HEAD SizeAttr_MaxSize (ConstantInt Nothing maxSize) -> do innerSize <- domainSizeOf inner return $ sum [ nchoosek (product . enumFromTo 1) innerSize k | k <- [0 .. maxSize] ] SizeAttr_MinMaxSize (ConstantInt Nothing minSize) (ConstantInt Nothing maxSize) -> do +======= + SizeAttr_MaxSize (ConstantInt _ maxSize) -> do + innerSize <- domainSizeOf inner + return $ sum [ nchoosek (product . enumFromTo 1) innerSize k | k <- [0 .. maxSize] ] + SizeAttr_MinMaxSize (ConstantInt _ minSize) (ConstantInt _ maxSize) -> do +>>>>>>> f8c15eb3160b509a17e3d70103b237ea8d666c04 innerSize <- domainSizeOf inner return $ sum [ nchoosek (product . enumFromTo 1) innerSize k | k <- [minSize .. maxSize] ] _ -> fail ("domainSizeOf{Constant}" <+> pretty d) @@ -151,7 +178,11 @@ domainSizeOfRanges :: MonadFail m => [Range Constant] -> m Integer domainSizeOfRanges = fmap genericLength . valuesInIntDomain instance DomainSizeOf Constant Constant where +<<<<<<< HEAD domainSizeOf = fmap (ConstantInt Nothing) . domainSizeOf +======= + domainSizeOf = fmap (ConstantInt NoTag) . domainSizeOf +>>>>>>> f8c15eb3160b509a17e3d70103b237ea8d666c04 instance Pretty Constant where @@ -168,7 +199,11 @@ instance Pretty Constant where (indices,inner) = first (index:) $ collect innerNested collect (TypeMatrix i j) = first (i:) $ collect j collect x = ([],x) +<<<<<<< HEAD pretty' (TypeInt _) = "int()" +======= + pretty' TypeInt{} = "int()" +>>>>>>> f8c15eb3160b509a17e3d70103b237ea8d666c04 pretty' t = pretty t in prParens $ "[] : `" <> pretty' ty <> "`" @@ -184,8 +219,13 @@ instance Pretty Constant where pretty (ConstantUndefined reason ty) = "undefined" <> prParens (pretty reason <+> ":" <+> "`" <> pretty ty <> "`") instance ExpressionLike Constant where +<<<<<<< HEAD fromInt = ConstantInt Nothing intOut _ (ConstantInt Nothing x) = return x +======= + fromInt = ConstantInt NoTag + intOut _ (ConstantInt _ x) = return x +>>>>>>> f8c15eb3160b509a17e3d70103b237ea8d666c04 intOut doc c = fail $ vcat [ "Expecting an integer, but found:" <+> pretty c , "Called from:" <+> doc ] @@ -228,6 +268,7 @@ normaliseConstant (TypedConstant c ty) = TypedConstant (normaliseConstant c) ty normaliseConstant x@ConstantUndefined{} = x instance Num Constant where +<<<<<<< HEAD ConstantInt Nothing x + ConstantInt Nothing y = ConstantInt Nothing (x+y) x + y = bug $ vcat [ "Num Constant (+)", "x:" <+> pretty x, "y:" <+> pretty y ] ConstantInt Nothing x - ConstantInt Nothing y = ConstantInt Nothing (x-y) @@ -239,6 +280,19 @@ instance Num Constant where signum (ConstantInt Nothing x) = ConstantInt Nothing (signum x) signum x = bug $ vcat [ "Num Constant signum", "x:" <+> pretty x ] fromInteger = ConstantInt Nothing . fromInteger +======= + ConstantInt _ x + ConstantInt _ y = ConstantInt NoTag (x+y) + x + y = bug $ vcat [ "Num Constant (+)", "x:" <+> pretty x, "y:" <+> pretty y ] + ConstantInt _ x - ConstantInt _ y = ConstantInt NoTag (x-y) + x - y = bug $ vcat [ "Num Constant (-)", "x:" <+> pretty x, "y:" <+> pretty y ] + ConstantInt _ x * ConstantInt _ y = ConstantInt NoTag (x*y) + x * y = bug $ vcat [ "Num Constant (*)", "x:" <+> pretty x, "y:" <+> pretty y ] + abs (ConstantInt t x) = ConstantInt t (abs x) + abs x = bug $ vcat [ "Num Constant abs", "x:" <+> pretty x ] + signum (ConstantInt t x) = ConstantInt t (signum x) + signum x = bug $ vcat [ "Num Constant signum", "x:" <+> pretty x ] + fromInteger = ConstantInt NoTag . fromInteger +>>>>>>> f8c15eb3160b509a17e3d70103b237ea8d666c04 valuesInIntDomain :: MonadFail m => [Range Constant] -> m [Integer] @@ -254,8 +308,13 @@ valuesInIntDomain ranges = [ vals | r <- ranges , let vals = case r of +<<<<<<< HEAD RangeSingle (ConstantInt Nothing x) -> return [x] RangeBounded (ConstantInt Nothing l) (ConstantInt Nothing u) -> return [l..u] +======= + RangeSingle (ConstantInt _ x) -> return [x] + RangeBounded (ConstantInt _ l) (ConstantInt _ u) -> return [l..u] +>>>>>>> f8c15eb3160b509a17e3d70103b237ea8d666c04 _ -> Nothing ] @@ -267,12 +326,14 @@ valuesInIntDomain ranges = -- | Assuming both the value and the domain are normalised +-- TODO: make this stricter, but write failing test cases first! validateConstantForDomain :: forall m r . (MonadFail m, Pretty r) => Name -> Constant -> Domain r Constant -> m () validateConstantForDomain _ ConstantBool{} DomainBool{} = return () validateConstantForDomain _ _ (DomainInt _ []) = return () -- no restrictions +<<<<<<< HEAD validateConstantForDomain name c@(ConstantInt Nothing i) d@(DomainInt Nothing rs) = let intInRange RangeOpen = True @@ -284,6 +345,19 @@ validateConstantForDomain name c@(ConstantInt Nothing i) d@(DomainInt Nothing rs in unless (any intInRange rs) (constantNotInDomain name c d) validateConstantForDomain _ (ConstantInt (Just cname) i) (DomainUnnamed uname (ConstantInt Nothing a)) | cname == uname && i >= 1 && i <= a = return () +======= +validateConstantForDomain name c@(ConstantInt cTag i) d@(DomainInt dTag rs) | cTag == dTag = + let + intInRange RangeOpen = True + intInRange (RangeSingle (ConstantInt _ a)) = i == a + intInRange (RangeLowerBounded (ConstantInt _ a)) = i >= a + intInRange (RangeUpperBounded (ConstantInt _ a)) = i <= a + intInRange (RangeBounded (ConstantInt _ a) (ConstantInt _ b)) = i >= a && i <= b + intInRange _ = False + in unless (any intInRange rs) (constantNotInDomain name c d) + +validateConstantForDomain _ (ConstantInt _ i) (DomainUnnamed _ (ConstantInt _ a)) | i >= 1 && i <= a = return () +>>>>>>> f8c15eb3160b509a17e3d70103b237ea8d666c04 validateConstantForDomain _ _ (DomainEnum _ Nothing _) = return () -- no restrictions validateConstantForDomain name c d@(DomainEnum _ _ Nothing) = @@ -293,22 +367,36 @@ validateConstantForDomain name c d@(DomainEnum _ _ Nothing) = , pretty d ] validateConstantForDomain name +<<<<<<< HEAD c@ConstantInt{} d@(DomainEnum name'' (Just ranges) (Just mp)) = nested c d $ do +======= + c@(ConstantInt cTag _) + d@(DomainEnum _ (Just ranges) (Just mp)) = nested c d $ do +>>>>>>> f8c15eb3160b509a17e3d70103b237ea8d666c04 let -- lu :: MonadFail m => Name -> m Constant lu (ConstantEnum _ _ nm) = case lookup nm mp of Nothing -> fail $ "No value for:" <+> pretty nm +<<<<<<< HEAD Just v -> return (ConstantInt (Just name'') v) lu (ConstantInt name' v) = return (ConstantInt name' v) +======= + Just v -> return (ConstantInt cTag v) + lu (ConstantInt t v) = return (ConstantInt t v) +>>>>>>> f8c15eb3160b509a17e3d70103b237ea8d666c04 lu x = fail $ "validateConstantForDomain.lu" <+> pretty x -- lu2 :: MonadFail m => Range Name -> m (Range Constant) lu2 = mapM lu rs <- mapM lu2 ranges +<<<<<<< HEAD validateConstantForDomain name c (DomainInt Nothing rs :: Domain r Constant) +======= + validateConstantForDomain name c (DomainInt cTag rs :: Domain r Constant) +>>>>>>> f8c15eb3160b509a17e3d70103b237ea8d666c04 validateConstantForDomain name c@(ConstantAbstract (AbsLitTuple cs)) @@ -335,7 +423,14 @@ validateConstantForDomain name d@(DomainMatrix dIndex dInner) = do nested c d $ mapM_ (\ val -> validateConstantForDomain name val dInner ) vals +<<<<<<< HEAD unless (cIndex == dIndex || cIndex == DomainInt Nothing []) $ fail $ vcat +======= + let + isEmptyIntDomain (DomainInt _ []) = True + isEmptyIntDomain _ = False + unless (cIndex == dIndex || isEmptyIntDomain cIndex) $ fail $ vcat +>>>>>>> f8c15eb3160b509a17e3d70103b237ea8d666c04 [ "The indices do not match between the value and the domain." , "Value :" <+> pretty c , "Domain:" <+> pretty d @@ -346,10 +441,17 @@ validateConstantForDomain name d@(DomainSet _ (SetAttr sizeAttr) dInner) = do let cardinalityOK = case sizeAttr of SizeAttr_None -> True +<<<<<<< HEAD SizeAttr_Size (ConstantInt Nothing s) -> s == genericLength vals SizeAttr_MinSize (ConstantInt Nothing s) -> s <= genericLength vals SizeAttr_MaxSize (ConstantInt Nothing s) -> genericLength vals <= s SizeAttr_MinMaxSize (ConstantInt Nothing smin) (ConstantInt Nothing smax) -> +======= + SizeAttr_Size (ConstantInt _ s) -> s == genericLength vals + SizeAttr_MinSize (ConstantInt _ s) -> s <= genericLength vals + SizeAttr_MaxSize (ConstantInt _ s) -> genericLength vals <= s + SizeAttr_MinMaxSize (ConstantInt _ smin) (ConstantInt _ smax) -> +>>>>>>> f8c15eb3160b509a17e3d70103b237ea8d666c04 smin <= genericLength vals && genericLength vals <= smax _ -> False unless cardinalityOK $ fail $ vcat @@ -366,10 +468,17 @@ validateConstantForDomain name d@(DomainMSet _ (MSetAttr sizeAttr occurAttr) dInner) = do let cardinalityOK = case sizeAttr of SizeAttr_None -> True +<<<<<<< HEAD SizeAttr_Size (ConstantInt Nothing s) -> s == genericLength vals SizeAttr_MinSize (ConstantInt Nothing s) -> s <= genericLength vals SizeAttr_MaxSize (ConstantInt Nothing s) -> genericLength vals <= s SizeAttr_MinMaxSize (ConstantInt Nothing smin) (ConstantInt Nothing smax) -> +======= + SizeAttr_Size (ConstantInt _ s) -> s == genericLength vals + SizeAttr_MinSize (ConstantInt _ s) -> s <= genericLength vals + SizeAttr_MaxSize (ConstantInt _ s) -> genericLength vals <= s + SizeAttr_MinMaxSize (ConstantInt _ smin) (ConstantInt _ smax) -> +>>>>>>> f8c15eb3160b509a17e3d70103b237ea8d666c04 smin <= genericLength vals && genericLength vals <= smax _ -> False unless cardinalityOK $ fail $ vcat @@ -381,9 +490,15 @@ validateConstantForDomain name ] let occurOK = case occurAttr of OccurAttr_None -> True +<<<<<<< HEAD OccurAttr_MinOccur (ConstantInt Nothing s) -> and [ s <= occ | (_, occ) <- histogram vals ] OccurAttr_MaxOccur (ConstantInt Nothing s) -> and [ occ <= s | (_, occ) <- histogram vals ] OccurAttr_MinMaxOccur (ConstantInt Nothing smin) (ConstantInt Nothing smax) -> +======= + OccurAttr_MinOccur (ConstantInt _ s) -> and [ s <= occ | (_, occ) <- histogram vals ] + OccurAttr_MaxOccur (ConstantInt _ s) -> and [ occ <= s | (_, occ) <- histogram vals ] + OccurAttr_MinMaxOccur (ConstantInt _ smin) (ConstantInt _ smax) -> +>>>>>>> f8c15eb3160b509a17e3d70103b237ea8d666c04 and [ smin <= occ && occ <= smax | (_, occ) <- histogram vals ] _ -> False unless occurOK $ fail $ vcat @@ -446,9 +561,15 @@ constantNotInDomain n c d = fail $ vcat viewConstantBool :: MonadFail m => Constant -> m Bool viewConstantBool (ConstantBool i) = return i +<<<<<<< HEAD viewConstantBool (ConstantInt Nothing 0) = return False viewConstantBool (ConstantInt Nothing 1) = return True viewConstantBool constant = fail ("Expecting a boolean integer, but got:" <++> pretty constant) +======= +viewConstantBool (ConstantInt _ 0) = return False +viewConstantBool (ConstantInt _ 1) = return True +viewConstantBool constant = fail ("Expecting a boolean, but got:" <++> pretty constant) +>>>>>>> f8c15eb3160b509a17e3d70103b237ea8d666c04 viewConstantInt :: MonadFail m => Constant -> m Integer viewConstantInt (ConstantInt _ i) = return i @@ -490,9 +611,15 @@ viewConstantFunction (TypedConstant c _) = viewConstantFunction c viewConstantFunction constant = do let suggestion = case constant of +<<<<<<< HEAD ConstantAbstract (AbsLitMatrix (DomainInt Nothing rs) vals) -> do froms <- valuesInIntDomain rs return $ Just $ pretty $ AbsLitFunction (zip (map (ConstantInt Nothing) froms) vals) +======= + ConstantAbstract (AbsLitMatrix (DomainInt _ rs) vals) -> do + froms <- valuesInIntDomain rs + return $ Just $ pretty $ AbsLitFunction (zip (map (ConstantInt NoTag) froms) vals) +>>>>>>> f8c15eb3160b509a17e3d70103b237ea8d666c04 _ -> return Nothing suggestion >>= \case Nothing -> fail ("Expecting a function, but got:" <++> pretty constant) diff --git a/src/Conjure/Language/Domain.hs b/src/Conjure/Language/Domain.hs index af2a8b801f..9f61cfd93a 100644 --- a/src/Conjure/Language/Domain.hs +++ b/src/Conjure/Language/Domain.hs @@ -54,8 +54,13 @@ import Data.Data ( toConstr, constrIndex ) data Domain r x = DomainAny Text Type | DomainBool +<<<<<<< HEAD | DomainIntE (Maybe Name) x | DomainInt (Maybe Name) [Range x] +======= + | DomainIntE x + | DomainInt IntTag [Range x] +>>>>>>> f8c15eb3160b509a17e3d70103b237ea8d666c04 | DomainEnum Name (Maybe [Range x]) -- subset of values for this domain @@ -85,6 +90,7 @@ mkDomainBool :: Domain () x mkDomainBool = DomainBool mkDomainInt :: [Range x] -> Domain () x +<<<<<<< HEAD mkDomainInt = DomainInt Nothing mkDomainIntB :: x -> x -> Domain () x @@ -93,6 +99,12 @@ mkDomainIntB l u = DomainInt Nothing [RangeBounded l u] mkDomainIntBNamed :: Name -> x -> x -> Domain () x mkDomainIntBNamed name l u = DomainInt (Just name) [RangeBounded l u] +======= +mkDomainInt = DomainInt NoTag + +mkDomainIntB :: x -> x -> Domain () x +mkDomainIntB l u = DomainInt NoTag [RangeBounded l u] +>>>>>>> f8c15eb3160b509a17e3d70103b237ea8d666c04 mkDomainAny :: Doc -> Type -> Domain r x mkDomainAny reason = DomainAny (stringToText $ show reason) @@ -106,16 +118,26 @@ instance Arbitrary x => Arbitrary (Domain r x) where arbitrary = sized f where f 0 = oneof [ return DomainBool +<<<<<<< HEAD , DomainInt Nothing <$> arbitrary +======= + , DomainInt NoTag <$> arbitrary +>>>>>>> f8c15eb3160b509a17e3d70103b237ea8d666c04 -- , DomainEnum <$> arbitrary <*> arbitrary ] f s = do arity <- choose (2 :: Int, 10) DomainTuple <$> vectorOf arity (f (div s 10)) shrink DomainBool = [] +<<<<<<< HEAD shrink (DomainInt Nothing []) = [DomainBool] shrink (DomainInt Nothing [r]) = DomainBool : DomainInt Nothing [] : [DomainInt Nothing [r'] | r' <- shrink r] shrink (DomainInt Nothing rs) = [DomainInt Nothing (init rs)] +======= + shrink (DomainInt _ []) = [DomainBool] + shrink (DomainInt t [r]) = DomainBool : DomainInt t [] : [DomainInt t [r'] | r' <- shrink r] + shrink (DomainInt t rs) = [DomainInt t (init rs)] +>>>>>>> f8c15eb3160b509a17e3d70103b237ea8d666c04 shrink _ = [] instance (Pretty r, TypeOf x, Pretty x) => TypeOf (Domain r x) where @@ -127,6 +149,7 @@ typeOfDomain DomainBool = return TypeBool typeOfDomain d@(DomainIntE name x) = do ty <- typeOf x case ty of +<<<<<<< HEAD TypeInt _ -> return () -- pre recoverDomainInt TypeList (TypeInt _) -> return () TypeMatrix _ (TypeInt _) -> return () @@ -140,11 +163,30 @@ typeOfDomain d@(DomainInt name rs) = do ty <- typeOf x case ty of TypeInt _ -> return () +======= + TypeInt{} -> return () -- pre recoverDomainInt + TypeList TypeInt{} -> return () + TypeMatrix _ TypeInt{} -> return () + TypeSet TypeInt{} -> return () + _ -> fail $ vcat [ "Expected an integer, but got:" <++> pretty ty + , "In domain:" <+> pretty d + ] + return (TypeInt NoTag) +typeOfDomain d@(DomainInt t rs) = do + forM_ rs $ \ r -> forM_ r $ \ x -> do + ty <- typeOf x + case ty of + TypeInt{} -> return () +>>>>>>> f8c15eb3160b509a17e3d70103b237ea8d666c04 _ -> fail $ vcat [ "Expected an integer, but got:" <++> pretty ty , "For:" <+> pretty x , "In domain:" <+> pretty d ] +<<<<<<< HEAD return $ TypeInt name +======= + return (TypeInt t) +>>>>>>> f8c15eb3160b509a17e3d70103b237ea8d666c04 typeOfDomain (DomainEnum defn _ _ ) = return (TypeEnum defn) typeOfDomain (DomainUnnamed defn _ ) = return (TypeUnnamed defn) typeOfDomain (DomainTuple xs ) = TypeTuple <$> mapM typeOf xs @@ -180,8 +222,13 @@ changeRepr rep = go where go (DomainAny t ty) = DomainAny t ty go DomainBool = DomainBool +<<<<<<< HEAD go (DomainIntE name x) = DomainIntE name x go (DomainInt name rs) = DomainInt name rs +======= + go (DomainIntE x) = DomainIntE x + go (DomainInt t rs) = DomainInt t rs +>>>>>>> f8c15eb3160b509a17e3d70103b237ea8d666c04 go (DomainEnum defn rs mp) = DomainEnum defn rs mp go (DomainUnnamed defn s) = DomainUnnamed defn s go (DomainTuple ds) = DomainTuple (map go ds) @@ -829,6 +876,11 @@ instance (Pretty r, Pretty a) => Pretty (Domain r a) where pretty (DomainInt _ ranges) = "int" <> prettyList prParens "," ranges +<<<<<<< HEAD +======= + pretty (DomainInt _ []) = "int" + pretty (DomainInt _ ranges) = "int" <> prettyList prParens "," ranges +>>>>>>> f8c15eb3160b509a17e3d70103b237ea8d666c04 pretty (DomainEnum name (Just ranges) _) = pretty name <> prettyList prParens "," ranges pretty (DomainEnum name _ _) = pretty name @@ -974,7 +1026,11 @@ representationToFullText r = representationToShortText r normaliseDomain :: (Ord c, ExpressionLike c) => (c -> c) -> Domain r c -> Domain r c normaliseDomain _norm DomainBool = DomainBool +<<<<<<< HEAD normaliseDomain norm (DomainInt name rs ) = DomainInt name $ sort $ map (normaliseRange norm) (expandRanges rs) +======= +normaliseDomain norm (DomainInt t rs ) = DomainInt t $ sort $ map (normaliseRange norm) (expandRanges rs) +>>>>>>> f8c15eb3160b509a17e3d70103b237ea8d666c04 normaliseDomain _norm (DomainEnum n Nothing mp) = DomainEnum n Nothing mp normaliseDomain _norm (DomainEnum n (Just rs) mp) = DomainEnum n (Just $ sort rs) mp normaliseDomain norm (DomainUnnamed n x ) = DomainUnnamed n (norm x) diff --git a/src/Conjure/Language/Expression/DomainSizeOf.hs b/src/Conjure/Language/Expression/DomainSizeOf.hs index 6cc6185baa..6b052d729e 100644 --- a/src/Conjure/Language/Expression/DomainSizeOf.hs +++ b/src/Conjure/Language/Expression/DomainSizeOf.hs @@ -62,8 +62,15 @@ instance DomainSizeOf Expression Expression where maxSize <- getMaxSize maxOccur <- getMaxOccur return (make opPow maxOccur maxSize) - domainSizeOf (DomainSequence _ (SequenceAttr sizeAttr _) innerTo) = - domainSizeOf $ DomainRelation def (RelationAttr sizeAttr def) [innerTo, innerTo] + domainSizeOf d@(DomainSequence _ (SequenceAttr sizeAttr jectivityAttr) innerTo) = do + size <- case sizeAttr of + SizeAttr_None -> fail ("Infinite domain:" <+> pretty d) + SizeAttr_Size s -> return s + SizeAttr_MinSize _ -> fail ("Infinite domain:" <+> pretty d) + SizeAttr_MaxSize s -> return s + SizeAttr_MinMaxSize _ s -> return s + domainSizeOf $ DomainFunction def (FunctionAttr sizeAttr PartialityAttr_Partial jectivityAttr) + (DomainInt [RangeBounded 1 size]) innerTo domainSizeOf (DomainFunction _ (FunctionAttr sizeAttr _ _) innerFr innerTo) = domainSizeOf $ DomainRelation def (RelationAttr sizeAttr def) [innerFr, innerTo] domainSizeOf (DomainRelation _ (RelationAttr sizeAttr _binRelAttr) inners) = diff --git a/src/Conjure/Language/Expression/Op/Internal/Common.hs b/src/Conjure/Language/Expression/Op/Internal/Common.hs index 2c9bc9b8b0..d40b84432b 100644 --- a/src/Conjure/Language/Expression/Op/Internal/Common.hs +++ b/src/Conjure/Language/Expression/Op/Internal/Common.hs @@ -85,8 +85,13 @@ intToInt :: (MonadFail m, TypeOf a, Pretty p) => p -> a -> m Type intToInt p a = do tya <- typeOf a case tya of +<<<<<<< HEAD TypeInt name -> return $ TypeInt name _ -> fail $ vcat +======= + TypeInt t -> return (TypeInt t) + _ -> fail $ vcat +>>>>>>> f8c15eb3160b509a17e3d70103b237ea8d666c04 [ "When type checking:" <+> pretty p , "Argument expected to be an int, but it is:" <++> pretty tya ] @@ -97,6 +102,7 @@ intToIntToInt p a b = do tya <- typeOf a tyb <- typeOf b case (tya, tyb) of +<<<<<<< HEAD (TypeInt namea, TypeInt nameb) -> if namea == nameb then return $ TypeInt namea @@ -104,9 +110,17 @@ intToIntToInt p a b = do [ "When type checking:" <+> pretty p , "TypeInt names are not equal:" <+> pretty namea <+> pretty nameb ] +======= + (TypeInt aTag, TypeInt bTag) + | aTag == bTag -> return (TypeInt aTag) + | otherwise -> fail $ vcat + [ "When type checking:" <+> pretty p + , "Arguments have different tags." + ] +>>>>>>> f8c15eb3160b509a17e3d70103b237ea8d666c04 (_, TypeInt _) -> fail $ vcat [ "When type checking:" <+> pretty p - , "First argument expected to be an int, but it is:" <++> pretty tya + , "First argument expected to be an int, but it is:" <++> pretty tya ] _ -> fail $ vcat [ "When type checking:" <+> pretty p @@ -128,8 +142,9 @@ boolToBoolToBool p a b = do , "Second argument expected to be a bool, but it is:" <++> pretty tyb ] + sameToSameToBool :: (MonadFail m, TypeOf a, Pretty a, Pretty p) => p -> a -> a -> [Type] -> m Type -sameToSameToBool p a b tys= do +sameToSameToBool p a b tys = do tyA <- typeOf a tyB <- typeOf b let tyAB = mostDefined [tyA,tyB] diff --git a/src/Conjure/Language/ParserC.hs b/src/Conjure/Language/ParserC.hs index 0442c0d9c6..49f4eb98c6 100644 --- a/src/Conjure/Language/ParserC.hs +++ b/src/Conjure/Language/ParserC.hs @@ -59,15 +59,36 @@ parseModel = inCompleteFile $ do -------------------------------------------------------------------------------- parseTopLevels :: Parser [Statement] --- parseTopLevels = trace "parseTopLevels" $ do parseTopLevels = do let one = do lexeme L_letting i <- parseName lexeme L_be - j <- parseExpr - return (Declaration (Letting i j)) - "letting statement" + msum + [ do + lexeme L_new + lexeme L_type + msum + [ do + lexeme L_of + lexeme $ LIdentifier "size" + j <- parseExpr + return $ Declaration (LettingDomainDefnUnnamed i j) + , do + lexeme L_enum + ys <- braces (commaSeparated parseName) <|> return [] + modify (\ st -> st { enumDomains = [i] ++ enumDomains st } ) + return $ Declaration (LettingDomainDefnEnum i ys) + ] + , do + lexeme L_domain + j <- parseDomain + return $ Declaration (Letting i (Domain j)) + , do + j <- parseExpr + return $ Declaration (Letting i j) + ] + "letting statement" some one parseRange :: Parser a -> Parser (Range a) @@ -485,7 +506,7 @@ parseAtomicExpr = parseAtomicExprNoPrePost "expression" parseAtomicExprNoPrePost :: Parser Expression -- parseAtomicExprNoPrePost | trace "parseAtomicExprNoPrePost" True = msum [try parseLiteral, parseTyped] -parseAtomicExprNoPrePost = msum [try parseLiteral, parseTyped] +parseAtomicExprNoPrePost = msum [try parseLiteral, parseReference, parseTyped] parseTyped :: Parser Expression -- parseTyped | trace "parseTyped" True = parens $ do @@ -499,6 +520,9 @@ parseTyped = parens $ do parseName :: Parser Name parseName = Name <$> identifierText +parseReference :: Parser Expression +parseReference = Reference <$> parseName <*> pure Nothing + parseLiteral :: Parser Expression parseLiteral = label "value" (do p <- pCore ; p) diff --git a/src/Conjure/Language/Type.hs b/src/Conjure/Language/Type.hs index 20662fcc10..5e03295195 100644 --- a/src/Conjure/Language/Type.hs +++ b/src/Conjure/Language/Type.hs @@ -2,6 +2,7 @@ module Conjure.Language.Type ( Type(..) + , IntTag(..) , typeUnify , typesUnify , mostDefined @@ -9,7 +10,11 @@ module Conjure.Language.Type , matrixNumDims , innerTypeOf , isPrimitiveType +<<<<<<< HEAD , containsType +======= + , typeCanIndexMatrix +>>>>>>> f8c15eb3160b509a17e3d70103b237ea8d666c04 ) where -- conjure @@ -22,7 +27,11 @@ import Conjure.Language.Pretty data Type = TypeAny | TypeBool +<<<<<<< HEAD | TypeInt (Maybe Name) +======= + | TypeInt IntTag +>>>>>>> f8c15eb3160b509a17e3d70103b237ea8d666c04 | TypeEnum Name | TypeUnnamed Name | TypeTuple [Type] @@ -47,8 +56,12 @@ instance FromJSON Type where parseJSON = genericParseJSON jsonOptions instance Pretty Type where pretty TypeAny = "?" pretty TypeBool = "bool" +<<<<<<< HEAD pretty (TypeInt Nothing) = "int" pretty (TypeInt (Just name)) = "int:" <> pretty name +======= + pretty TypeInt{} = "int" +>>>>>>> f8c15eb3160b509a17e3d70103b237ea8d666c04 pretty (TypeEnum nm ) = pretty nm pretty (TypeUnnamed nm) = pretty nm pretty (TypeTuple xs) = (if length xs <= 1 then "tuple" else prEmpty) @@ -73,16 +86,32 @@ instance Pretty Type where pretty (TypeRelation xs) = "relation of" <+> prettyList prParens " *" xs pretty (TypePermutation x) = "permutation of" <+> pretty x + +data IntTag = NoTag + | TagEnum Name + | TagUnnamed Name + deriving (Eq, Ord, Show, Data, Typeable, Generic) + +instance Serialize IntTag +instance Hashable IntTag +instance ToJSON IntTag where toJSON = genericToJSON jsonOptions +instance FromJSON IntTag where parseJSON = genericParseJSON jsonOptions + + -- | Check whether two types unify or not. typeUnify :: Type -> Type -> Bool typeUnify TypeAny _ = True typeUnify _ TypeAny = True typeUnify TypeBool TypeBool = True +<<<<<<< HEAD typeUnify (TypeInt a) (TypeInt b) = a == b typeUnify (TypeInt (Nothing)) (TypeEnum _) = False typeUnify (TypeInt (Just a)) (TypeEnum b) = a == b typeUnify (TypeEnum _) (TypeInt (Nothing)) = False typeUnify (TypeEnum b) (TypeInt (Just a)) = a == b +======= +typeUnify (TypeInt t1) (TypeInt t2) = t1 == t2 +>>>>>>> f8c15eb3160b509a17e3d70103b237ea8d666c04 typeUnify (TypeEnum a) (TypeEnum b) = a == b || a == "?" || b == "?" -- the "?" is a hack so sameToSameToBool works typeUnify (TypeUnnamed a) (TypeUnnamed b) = a == b typeUnify (TypeTuple [TypeAny]) TypeTuple{} = True @@ -192,7 +221,11 @@ innerTypeOf (TypeMatrix _ t) = return t innerTypeOf (TypeSet t) = return t innerTypeOf (TypeMSet t) = return t innerTypeOf (TypeFunction a b) = return (TypeTuple [a,b]) +<<<<<<< HEAD innerTypeOf (TypeSequence t) = return (TypeTuple [TypeInt Nothing,t]) +======= +innerTypeOf (TypeSequence t) = return (TypeTuple [TypeInt NoTag,t]) +>>>>>>> f8c15eb3160b509a17e3d70103b237ea8d666c04 innerTypeOf (TypeRelation ts) = return (TypeTuple ts) innerTypeOf (TypePartition t) = return (TypeSet t) innerTypeOf (TypePermutation t) = return (TypeTuple [t,t]) @@ -204,6 +237,7 @@ isPrimitiveType TypeInt{} = True isPrimitiveType (TypeMatrix index inner) = and [isPrimitiveType index, isPrimitiveType inner] isPrimitiveType _ = False +<<<<<<< HEAD containsType :: Type -> Type -> Bool containsType container containee = if typesUnify [container, containee] @@ -212,3 +246,10 @@ containsType container containee = Nothing -> False Just so -> containsType so containee +======= +typeCanIndexMatrix :: Type -> Bool +typeCanIndexMatrix TypeBool{} = True +typeCanIndexMatrix TypeInt {} = True +typeCanIndexMatrix TypeEnum{} = True +typeCanIndexMatrix _ = False +>>>>>>> f8c15eb3160b509a17e3d70103b237ea8d666c04 diff --git a/src/Conjure/Rules/Horizontal/Set.hs b/src/Conjure/Rules/Horizontal/Set.hs index c4fdfb50e7..726e5f0671 100644 --- a/src/Conjure/Rules/Horizontal/Set.hs +++ b/src/Conjure/Rules/Horizontal/Set.hs @@ -358,14 +358,15 @@ rule_Card = "set-card" `namedRule` theRule where Domain{} -> na "rule_Card" _ -> return () TypeSet{} <- typeOf s - dom <- domainOf s return ( "Horizontal rule for set cardinality." - , case dom of - DomainSet _ (SetAttr (SizeAttr_Size n)) _ -> return n - _ -> do - (iPat, _) <- quantifiedVar - return [essence| sum &iPat in &s . 1 |] + , do + mdom <- runMaybeT $ domainOf s + case mdom of + Just (DomainSet _ (SetAttr (SizeAttr_Size n)) _) -> return n + _ -> do + (iPat, _) <- quantifiedVar + return [essence| sum &iPat in &s . 1 |] ) diff --git a/src/Conjure/Rules/Vertical/Sequence/ExplicitBounded.hs b/src/Conjure/Rules/Vertical/Sequence/ExplicitBounded.hs index 6e58a584a6..6265f8db34 100644 --- a/src/Conjure/Rules/Vertical/Sequence/ExplicitBounded.hs +++ b/src/Conjure/Rules/Vertical/Sequence/ExplicitBounded.hs @@ -92,3 +92,43 @@ rule_Image_Bool = "sequence-image{ExplicitBounded}-bool" `namedRule` theRule whe ( "Sequence image, ExplicitBounded representation, bool" , return [essence| { &p' @ such that &flagsCombined } |] ) + +rule_Leq :: Rule +rule_Leq = "sequence-leq{ExplicitBounded}" `namedRule` theRule where + theRule [essence| &a ~<= &b |] = do + TypeSequence aInnerTy <- typeOf a + TypeSequence bInnerTy <- typeOf b + unless (typeCanIndexMatrix aInnerTy && typeCanIndexMatrix bInnerTy) $ na "rule_Leq" + Sequence_ExplicitBounded <- representationOf a + Sequence_ExplicitBounded <- representationOf b + [aLength, aValues] <- downX1 a + [bLength, bValues] <- downX1 b + return + ( "Mapping over a sequence, ExplicitBounded representation" + , return [essence| + flatten([&aValues, [&aLength]]) <=lex + flatten([&bValues, [&bLength]]) + |] + ) + theRule _ = na "rule_Leq" + + +rule_Lt :: Rule +rule_Lt = "sequence-lt{ExplicitBounded}" `namedRule` theRule where + theRule [essence| &a ~< &b |] = do + TypeSequence aInnerTy <- typeOf a + TypeSequence bInnerTy <- typeOf b + unless (typeCanIndexMatrix aInnerTy && typeCanIndexMatrix bInnerTy) $ na "rule_Lt" + Sequence_ExplicitBounded <- representationOf a + Sequence_ExplicitBounded <- representationOf b + [aLength, aValues] <- downX1 a + [bLength, bValues] <- downX1 b + return + ( "Mapping over a sequence, ExplicitBounded representation" + , return [essence| + flatten([&aValues, [&aLength]]) ) ) import qualified Filesystem.Path as Sys ( FilePath ) -- directory -import System.Directory ( copyFile ) +import System.Directory ( copyFile, findExecutable ) -- shelly import Shelly ( runHandle, lastStderr, lastExitCode, errExit, Sh ) @@ -128,7 +128,7 @@ mainWithArgs TranslateParameter{..} = do when (null essenceParam) $ userErr1 "Mandatory field --essence-param" let outputFilename = fromMaybe (dropExtension essenceParam ++ ".eprime-param") eprimeParam eprimeF <- readModelInfoFromFile eprime - essenceParamF <- readModelFromFile essenceParam + essenceParamF <- readParamOrSolutionFromFile essenceParam output <- runNameGen () $ translateParameter eprimeF essenceParamF writeModel lineWidth outputFormat (Just outputFilename) output mainWithArgs TranslateSolution{..} = do @@ -144,8 +144,8 @@ mainWithArgs ValidateSolution{..} = do when (null essence ) $ userErr1 "Mandatory field --essence" when (null essenceSolution) $ userErr1 "Mandatory field --solution" essence2 <- readModelFromFile essence - param2 <- maybe (return def) readModelFromFile essenceParamO - solution2 <- readModelFromFile essenceSolution + param2 <- maybe (return def) readParamOrSolutionFromFile essenceParamO + solution2 <- readParamOrSolutionFromFile essenceSolution [essence3, param3, solution3] <- runNameGen () $ resolveNamesMulti [essence2, param2, solution2] runNameGen () $ validateSolution essence3 param3 solution3 mainWithArgs Pretty{..} = do @@ -183,9 +183,24 @@ mainWithArgs ModelStrengthening{..} = strengthenModel logLevel logRuleSuccesses >>= writeModel lineWidth outputFormat (Just essenceOut) mainWithArgs config@Solve{..} = do + let executables = [ ( "minion" , "minion" ) + , ( "gecode" , "fzn-gecode" ) + , ( "chuffed" , "fzn-chuffed" ) + , ( "glucose" , "glucose-syrup" ) + , ( "lingeling" , "lingeling" ) + , ( "minisat" , "minisat" ) + , ( "bc_minisat_all" , "bc_minisat_all_release" ) + , ( "nbc_minisat_all" , "nbc_minisat_all_release" ) + , ( "open-wbo" , "open-wbo" ) + ] -- some sanity checks - unless (solver `elem` ["minion", "lingeling", "minisat", "bc_minisat_all", "nbc_minisat_all"]) $ - userErr1 ("Unsupported solver:" <+> pretty solver) + case lookup solver executables of + Nothing -> userErr1 ("Unsupported solver:" <+> pretty solver) + Just ex -> do + fp <- liftIO $ findExecutable ex + case fp of + Nothing -> userErr1 ("Cannot find executable" <+> pretty ex <+> "(for solver" <+> pretty solver <> ")") + Just _ -> return () unless (nbSolutions == "all" || all isDigit nbSolutions) $ userErr1 (vcat [ "The value for --number-of-solutions must either be a number or the string \"all\"." , "Was given:" <+> pretty nbSolutions @@ -194,7 +209,7 @@ mainWithArgs config@Solve{..} = do userErr1 $ "The solvers bc_minisat_all and nbc_minisat_all only work with --number-of-solutions=all" essenceM <- readModelFromFile essence essenceParamsParsed <- forM essenceParams $ \ f -> do - p <- readModelFromFile f + p <- readParamOrSolutionFromFile f return (f, p) let givens = [ nm | Declaration (FindOrGiven Given nm _) <- mStatements essenceM ] ++ [ nm | Declaration (GivenDomainDefnEnum nm) <- mStatements essenceM ] @@ -460,6 +475,11 @@ srMkArgs Solve{..} outBase modelPath = ) ++ ( case solver of "minion" -> [ "-minion" ] + "gecode" -> [ "-gecode" ] + "chuffed" -> [ "-chuffed"] + "glucose" -> [ "-sat" + , "-sat-family", "glucose" + ] "lingeling" -> [ "-sat" , "-sat-family", "lingeling" ] @@ -472,6 +492,7 @@ srMkArgs Solve{..} outBase modelPath = "nbc_minisat_all" -> [ "-sat" , "-sat-family", "nbc_minisat_all" ] + "open-wbo" -> [ "-maxsat" ] _ -> bug ("Unknown solver:" <+> pretty solver) ) ++ map stringToText (concatMap words savilerowOptions) ++ if null solverOptions then [] else [ "-solver-options", stringToText (unwords (concatMap words solverOptions)) ] @@ -568,7 +589,7 @@ validateSolutionNoParam :: UI -> FilePath -> IO () validateSolutionNoParam Solve{..} solutionPath = do pp logLevel $ hsep ["Validating solution:", pretty solutionPath] essenceM <- readModelFromFile essence - solution <- readModelFromFile solutionPath + solution <- readParamOrSolutionFromFile solutionPath [essenceM2, solution2] <- ignoreLogs $ runNameGen () $ resolveNamesMulti [essenceM, solution] result <- runExceptT $ ignoreLogs $ runNameGen () $ validateSolution essenceM2 def solution2 case result of @@ -581,8 +602,8 @@ validateSolutionWithParams :: UI -> FilePath -> FilePath -> IO () validateSolutionWithParams Solve{..} solutionPath paramPath = do pp logLevel $ hsep ["Validating solution:", pretty paramPath, pretty solutionPath] essenceM <- readModelFromFile essence - param <- readModelFromFile paramPath - solution <- readModelFromFile solutionPath + param <- readParamOrSolutionFromFile paramPath + solution <- readParamOrSolutionFromFile solutionPath [essenceM2, param2, solution2] <- ignoreLogs $ runNameGen () $ resolveNamesMulti [essenceM, param, solution] result <- runExceptT $ ignoreLogs $ runNameGen () $ validateSolution essenceM2 param2 solution2 diff --git a/src/Conjure/UI/Model.hs b/src/Conjure/UI/Model.hs index 6a409415ae..6369b46509 100644 --- a/src/Conjure/UI/Model.hs +++ b/src/Conjure/UI/Model.hs @@ -860,17 +860,25 @@ sliceThemMatrices model = do -- we also descend into components of the matrix-typed expression during slicing onExpr :: Monad m => Expression -> m Expression onExpr p = do + let computeExistingSlices t = + case match opSlicing t of + Nothing -> return 0 + Just (t', _, _) -> (+1) <$> computeExistingSlices t' let isIndexedMatrix = do (m, is) <- match opMatrixIndexing p tyM <- typeOf m - return (m, is, tyM) + nSlices <- computeExistingSlices m + return (m, nSlices, is, tyM) case isIndexedMatrix of Nothing -> descendM onExpr p - Just (m, is, tyM) -> do + Just (m, existingSlices, is, tyM) -> do let nestingLevel (TypeMatrix _ a) = 1 + nestingLevel a nestingLevel (TypeList a) = 1 + nestingLevel a nestingLevel _ = 0 :: Int - let howMany = nestingLevel tyM - length is + -- "is" is the number of existing indices + -- "nestingLevel" is the nesting level of the original matrix + -- "existingSlices" is the number of existing slices + let howMany = nestingLevel tyM - existingSlices - length is let unroll a 0 = a unroll a i = make opSlicing (unroll a (i-1)) Nothing Nothing m' <- descendM onExpr m @@ -1130,6 +1138,8 @@ verticalRules = , Vertical.Sequence.ExplicitBounded.rule_Card , Vertical.Sequence.ExplicitBounded.rule_Image_Bool , Vertical.Sequence.ExplicitBounded.rule_Image_NotABool + , Vertical.Sequence.ExplicitBounded.rule_Leq + , Vertical.Sequence.ExplicitBounded.rule_Lt , Vertical.Relation.RelationAsMatrix.rule_Comprehension , Vertical.Relation.RelationAsMatrix.rule_Image diff --git a/tests/custom/basic/function-literal-suggestion/func.essence b/tests/custom/basic/function-literal-suggestion/func.essence new file mode 100644 index 0000000000..013f2231a3 --- /dev/null +++ b/tests/custom/basic/function-literal-suggestion/func.essence @@ -0,0 +1 @@ +given f : function int(1..3) --> int(1..3) diff --git a/tests/custom/basic/function-literal-suggestion/p.param b/tests/custom/basic/function-literal-suggestion/p.param new file mode 100644 index 0000000000..9afb7c92d6 --- /dev/null +++ b/tests/custom/basic/function-literal-suggestion/p.param @@ -0,0 +1 @@ +letting f be [3,2,1] \ No newline at end of file diff --git a/tests/custom/basic/function-literal-suggestion/run.sh b/tests/custom/basic/function-literal-suggestion/run.sh new file mode 100755 index 0000000000..baf42c4064 --- /dev/null +++ b/tests/custom/basic/function-literal-suggestion/run.sh @@ -0,0 +1 @@ +conjure solve *.essence *.param diff --git a/tests/custom/basic/function-literal-suggestion/stderr.expected b/tests/custom/basic/function-literal-suggestion/stderr.expected new file mode 100644 index 0000000000..1808f1fcfd --- /dev/null +++ b/tests/custom/basic/function-literal-suggestion/stderr.expected @@ -0,0 +1,3 @@ +Error: + Expecting a function, but got: [3, 2, 1; int(1..3)] + Maybe you meant: function(1 --> 3, 2 --> 2, 3 --> 1) diff --git a/tests/custom/basic/function-literal-suggestion/stdout.expected b/tests/custom/basic/function-literal-suggestion/stdout.expected new file mode 100644 index 0000000000..91665138ce --- /dev/null +++ b/tests/custom/basic/function-literal-suggestion/stdout.expected @@ -0,0 +1,2 @@ +Using cached models. +Savile Row: model000001.eprime p.param diff --git a/tests/custom/basic/given-seq-seq/run.sh b/tests/custom/basic/given-seq-seq/run.sh new file mode 100755 index 0000000000..a3f0b14e42 --- /dev/null +++ b/tests/custom/basic/given-seq-seq/run.sh @@ -0,0 +1,10 @@ +rm -rf conjure-output +conjure solve *.essence *.param --validate-solutions --line-width 80 +# conjure solve *.essence --line-width 80 +for file in conjure-output/*.eprime conjure-output/*.solution; do + echo "File: $file" + cat $file | grep -v '\$' + echo "--------------------" + echo "" +done +rm -rf conjure-output *.solution diff --git a/tests/custom/basic/given-seq-seq/seqseq.essence b/tests/custom/basic/given-seq-seq/seqseq.essence new file mode 100644 index 0000000000..e1eac69384 --- /dev/null +++ b/tests/custom/basic/given-seq-seq/seqseq.essence @@ -0,0 +1,4 @@ +given stacks : sequence of sequence of int +find x : int(0..10000) +such that x = sum (_, stack) in stacks . + sum (_, val) in stack . val diff --git a/tests/custom/basic/given-seq-seq/seqseq.param b/tests/custom/basic/given-seq-seq/seqseq.param new file mode 100644 index 0000000000..d8b1179d7b --- /dev/null +++ b/tests/custom/basic/given-seq-seq/seqseq.param @@ -0,0 +1,6 @@ +letting stacks be + sequence( sequence(43, 17, 2, 7, 5, 45, 31, 41, 4, 30, 16, 15, 42) + , sequence(36, 48, 8, 18, 20, 35, 19, 33, 6, 29) + , sequence(37, 24, 49, 23, 34, 21, 46, 22) + , sequence(26, 52, 25, 38, 39, 51, 9, 10, 50) + ) diff --git a/tests/custom/basic/given-seq-seq/stdout.expected b/tests/custom/basic/given-seq-seq/stdout.expected new file mode 100644 index 0000000000..61b887f0bd --- /dev/null +++ b/tests/custom/basic/given-seq-seq/stdout.expected @@ -0,0 +1,37 @@ +Generating models for seqseq.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime seqseq.param +Validating solution: seqseq.param conjure-output/model000001-seqseq-solution000001.solution +Copying solution to: seqseq-seqseq.solution +File: conjure-output/model000001.eprime +language ESSENCE' 1.0 + +given fin1: int +given fin2: int +given fin3: int +given fin4: int +given stacks_ExplicitBoundedR14_Length: int(fin1) +given stacks_ExplicitBoundedR14_Values_ExplicitBounded_Length: + matrix indexed by [int(1..fin1)] of int(0..fin2) +given stacks_ExplicitBoundedR14_Values_ExplicitBounded_Values: + matrix indexed by [int(1..fin1), int(1..fin2)] of int(fin3..fin4) +find x: int(0..10000) +branching on [x] +such that + x = + sum([sum([stacks_ExplicitBoundedR14_Values_ExplicitBounded_Values[q2, q4] + | q4 : int(1..fin2), + q4 <= + stacks_ExplicitBoundedR14_Values_ExplicitBounded_Length + [q2]]) + | q2 : int(1..fin1), q2 <= fin1]) + +-------------------- + +File: conjure-output/model000001-seqseq-solution000001.solution +language Essence 1.3 + +letting x be 1106 +-------------------- + diff --git a/tests/custom/basic/matrix-slicing/run.sh b/tests/custom/basic/matrix-slicing/run.sh new file mode 100755 index 0000000000..b7d121afa1 --- /dev/null +++ b/tests/custom/basic/matrix-slicing/run.sh @@ -0,0 +1,10 @@ +rm -rf conjure-output +# conjure solve *.essence --validate-solutions --line-width 80 +conjure solve *.essence --line-width 80 +for file in conjure-output/*.eprime conjure-output/*.solution; do + echo "File: $file" + cat $file | grep -v '\$' + echo "--------------------" + echo "" +done +rm -rf conjure-output *.solution diff --git a/tests/custom/basic/matrix-slicing/slice.essence b/tests/custom/basic/matrix-slicing/slice.essence new file mode 100644 index 0000000000..062744c3ad --- /dev/null +++ b/tests/custom/basic/matrix-slicing/slice.essence @@ -0,0 +1,6 @@ +find m : matrix indexed by [int(1..5), int(1..5)] of int(1..9) +such that allDiff(m[..,1]) +such that allDiff(m[..,2]) +such that allDiff(m[..,3]) +such that allDiff(m[..,4]) +such that allDiff(m[..,5]) diff --git a/tests/custom/basic/matrix-slicing/stdout.expected b/tests/custom/basic/matrix-slicing/stdout.expected new file mode 100644 index 0000000000..19824a0e0c --- /dev/null +++ b/tests/custom/basic/matrix-slicing/stdout.expected @@ -0,0 +1,30 @@ +Generating models for slice.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Copying solution to: slice.solution +File: conjure-output/model000001.eprime +language ESSENCE' 1.0 + +find m: matrix indexed by [int(1..5), int(1..5)] of int(1..9) +branching on [m] +such that + allDiff(m[.., 1]), + allDiff(m[.., 2]), + allDiff(m[.., 3]), + allDiff(m[.., 4]), + allDiff(m[.., 5]) + +-------------------- + +File: conjure-output/model000001-solution000001.solution +language Essence 1.3 + +letting m be + [[1, 1, 1, 1, 1; int(1..5)], [2, 2, 2, 2, 2; int(1..5)], + [3, 3, 3, 3, 3; int(1..5)], [4, 4, 4, 4, 4; int(1..5)], + [5, 5, 5, 5, 5; int(1..5)]; + int(1..5)] + +-------------------- + diff --git a/tests/custom/basic/parsing-enums-in-param/knapsack.essence b/tests/custom/basic/parsing-enums-in-param/knapsack.essence new file mode 100644 index 0000000000..40e40eba7f --- /dev/null +++ b/tests/custom/basic/parsing-enums-in-param/knapsack.essence @@ -0,0 +1,13 @@ +language Essence 1.3 + +given items new type enum + +given capacity : int + +given gain, weight : function (total) items --> int(0..capacity) + +find knapsack : set of items + +such that sum([ weight(i) | i <- knapsack ]) <= capacity +such that sum([ gain(i) | i <- knapsack ]) >= 80 + diff --git a/tests/custom/basic/parsing-enums-in-param/knapsack.param b/tests/custom/basic/parsing-enums-in-param/knapsack.param new file mode 100644 index 0000000000..bf9170a904 --- /dev/null +++ b/tests/custom/basic/parsing-enums-in-param/knapsack.param @@ -0,0 +1,22 @@ +language Essence 1.3 + +letting items be new type enum {a,b,c,d,e} + +letting capacity be 100 + +letting gain be function + ( a --> 10 + , b --> 20 + , c --> 40 + , d --> 40 + , e --> 50 + ) + +letting weight be function + ( a --> 15 + , b --> 25 + , c --> 45 + , d --> 50 + , e --> 60 + ) + diff --git a/tests/custom/basic/parsing-enums-in-param/run.sh b/tests/custom/basic/parsing-enums-in-param/run.sh new file mode 100755 index 0000000000..30541af9a3 --- /dev/null +++ b/tests/custom/basic/parsing-enums-in-param/run.sh @@ -0,0 +1,9 @@ +rm -rf conjure-output +conjure solve *.essence *.param --line-width 80 --number-of-solutions=all +for file in conjure-output/*.eprime conjure-output/*.solution; do + echo "File: $file" + cat $file | grep -v '\$' + echo "--------------------" + echo "" +done +rm -rf conjure-output *.solution diff --git a/tests/custom/basic/parsing-enums-in-param/stdout.expected b/tests/custom/basic/parsing-enums-in-param/stdout.expected new file mode 100644 index 0000000000..e1d4efc065 --- /dev/null +++ b/tests/custom/basic/parsing-enums-in-param/stdout.expected @@ -0,0 +1,41 @@ +Generating models for knapsack.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime knapsack.param +Copying solution to: knapsack-knapsack-000001.solution +Copying solution to: knapsack-knapsack-000002.solution +File: conjure-output/model000001.eprime +language ESSENCE' 1.0 + +given items_EnumSize: int +given capacity: int +given fin1: int +given gain_Function1D: + matrix indexed by [int(1..items_EnumSize)] of int(0..capacity) +given fin2: int +given weight_Function1D: + matrix indexed by [int(1..items_EnumSize)] of int(0..capacity) +find knapsack_Occurrence: matrix indexed by [int(1..items_EnumSize)] of bool +branching on [knapsack_Occurrence] +such that + sum([toInt(knapsack_Occurrence[i]) * catchUndef(weight_Function1D[i], 0) + | i : int(1..items_EnumSize)]) + <= capacity, + sum([toInt(knapsack_Occurrence[i]) * catchUndef(gain_Function1D[i], 0) + | i : int(1..items_EnumSize)]) + >= 80 + +-------------------- + +File: conjure-output/model000001-knapsack-solution000001.solution +language Essence 1.3 + +letting knapsack be {c, d} +-------------------- + +File: conjure-output/model000001-knapsack-solution000002.solution +language Essence 1.3 + +letting knapsack be {a, b, e} +-------------------- + diff --git a/tests/custom/help-text/conjure-help.txt b/tests/custom/help-text/conjure-help.txt index 31e26eb3d2..0831005aff 100644 --- a/tests/custom/help-text/conjure-help.txt +++ b/tests/custom/help-text/conjure-help.txt @@ -62,7 +62,7 @@ --representations-quantifieds=STRATEGY Strategy for choosing a representation for a quantified variable. Default value: same as --representations --representations-cuts=STRATEGY Strategy for choosing a representation for cuts in 'branching on'. - Default value: same as --representations-cuts + Default value: same as --representations --channelling Whether to produce channelled models (true by default). --representation-levels Whether to use built-in precedence levels when choosing representations. Used to cut down the number of generated models. @@ -197,7 +197,7 @@ --representations-quantifieds=STRATEGY Strategy for choosing a representation for a quantified variable. Default value: same as --representations --representations-cuts=STRATEGY Strategy for choosing a representation for cuts in 'branching on'. - Default value: same as --representations-cuts + Default value: same as --representations --channelling Whether to produce channelled models (true by default). --representation-levels Whether to use built-in precedence levels when choosing representations. Used to cut down the number of generated models. @@ -212,7 +212,17 @@ --savilerow-options=ITEM Options passed to Savile Row. --solver-options=ITEM Options passed to the backend solver. --solver=ITEM Backend solver. Possible values: - minion/lingeling/minisat/bc_minisat_all/nbc_minisat_all + - minion (CP solver) + - gecode (CP solver) + - chuffed (CP solver) + - glucose (SAT solver) + - lingeling (SAT solver) + - minisat (SAT solver) + - bc_minisat_all (AllSAT solver, only works with + --number-of-solutions=all) + - nbc_minisat_all (AllSAT solver, only works with + --number-of-solutions=all) + - open-wbo (MaxSAT solver, only works with optimisation problems) Default: minion conjure pretty [OPTIONS] FILE From 668ae50375630e5a1846f47589cdd579de83818a Mon Sep 17 00:00:00 2001 From: Fraser Dunlop Date: Thu, 1 Nov 2018 15:42:35 +0000 Subject: [PATCH 011/229] Merge completed --- src/Conjure/Compute/DomainOf.hs | 5 --- src/Conjure/Language/Domain.hs | 10 +++--- src/Conjure/Language/Expression/Op/Product.hs | 9 +---- src/Conjure/Language/Lenses.hs | 4 --- src/Conjure/Language/ParserC.hs | 36 +++++++++++++++++++ src/Conjure/Language/Type.hs | 22 ++++++------ src/Conjure/Process/Enums.hs | 16 ++------- .../Sequence/ExplicitBounded.hs | 5 --- src/Conjure/Rules/DontCare.hs | 4 +-- src/Conjure/Rules/Horizontal/Permutation.hs | 4 +-- src/Conjure/UI/TypeCheck.hs | 2 +- src/test/Conjure/RepresentationsTest.hs | 25 ------------- .../stdout.expected | 7 ---- 13 files changed, 59 insertions(+), 90 deletions(-) diff --git a/src/Conjure/Compute/DomainOf.hs b/src/Conjure/Compute/DomainOf.hs index 9cd3ff024b..d9c4c084c3 100644 --- a/src/Conjure/Compute/DomainOf.hs +++ b/src/Conjure/Compute/DomainOf.hs @@ -67,11 +67,6 @@ instance DomainOf Expression where in return (tyToDom ty) - indexDomainsOf (Reference _ (Just refTo)) = indexDomainsOf refTo - tyToDom _ = [] - in - return (tyToDom ty) - indexDomainsOf (Reference _ (Just refTo)) = indexDomainsOf refTo indexDomainsOf (Constant x) = indexDomainsOf x indexDomainsOf (AbstractLiteral x) = indexDomainsOf x diff --git a/src/Conjure/Language/Domain.hs b/src/Conjure/Language/Domain.hs index 77c1712c07..59bf285276 100644 --- a/src/Conjure/Language/Domain.hs +++ b/src/Conjure/Language/Domain.hs @@ -123,7 +123,7 @@ instance (Pretty r, TypeOf x, Pretty x) => TypeOf (Domain r x) where typeOfDomain :: (MonadFail m, Pretty r, TypeOf x, Pretty x) => Domain r x -> m Type typeOfDomain (DomainAny _ ty) = return ty typeOfDomain DomainBool = return TypeBool -typeOfDomain d@(DomainIntE name x) = do +typeOfDomain d@(DomainIntE x) = do ty <- typeOf x case ty of TypeInt{} -> return () -- pre recoverDomainInt @@ -822,16 +822,14 @@ instance (Pretty r, Pretty a) => Pretty (Domain r a) where pretty DomainBool = "bool" - pretty (DomainIntE _ x) = "int" <> prParens (pretty x) + pretty (DomainIntE x) = "int" <> prParens (pretty x) pretty (DomainInt _ []) = "int" pretty (DomainInt _ ranges) = "int" <> prettyList prParens "," ranges - - pretty (DomainInt _ []) = "int" - pretty (DomainInt _ ranges) = "int" <> prettyList prParens "," ranges - + pretty (DomainEnum name (Just ranges) _) = pretty name <> prettyList prParens "," ranges + pretty (DomainEnum name _ _) = pretty name pretty (DomainUnnamed name _) = pretty name diff --git a/src/Conjure/Language/Expression/Op/Product.hs b/src/Conjure/Language/Expression/Op/Product.hs index aaba4b8419..92b8649621 100644 --- a/src/Conjure/Language/Expression/Op/Product.hs +++ b/src/Conjure/Language/Expression/Op/Product.hs @@ -45,16 +45,9 @@ instance EvaluateOp OpProduct where evaluateOp p@(OpProduct x) | Just xs <- listOut x -<<<<<<< HEAD - , any isUndef xs = return $ mkUndef (TypeInt Nothing) $ "Has undefined children:" <+> pretty p - evaluateOp (OpProduct x) = ConstantInt Nothing . product <$> intsOut "OpProduct" x -||||||| merged common ancestors - , any isUndef xs = return $ mkUndef TypeInt $ "Has undefined children:" <+> pretty p - evaluateOp (OpProduct x) = ConstantInt . product <$> intsOut "OpProduct" x -======= , any isUndef xs = return $ mkUndef (TypeInt NoTag) $ "Has undefined children:" <+> pretty p evaluateOp (OpProduct x) = ConstantInt NoTag . product <$> intsOut "OpProduct" x ->>>>>>> taggedints + instance (OpProduct x :< x) => SimplifyOp OpProduct x where simplifyOp (OpProduct x) diff --git a/src/Conjure/Language/Lenses.hs b/src/Conjure/Language/Lenses.hs index ee9e873b1d..b71af872f6 100644 --- a/src/Conjure/Language/Lenses.hs +++ b/src/Conjure/Language/Lenses.hs @@ -1173,10 +1173,6 @@ constantInt _ = ) -matrixLiteral - _ -> na ("Lenses.constantInt:" <++> pretty p) - ) - matrixLiteral :: MonadFail m diff --git a/src/Conjure/Language/ParserC.hs b/src/Conjure/Language/ParserC.hs index c3de91b085..8aa2c91b8c 100644 --- a/src/Conjure/Language/ParserC.hs +++ b/src/Conjure/Language/ParserC.hs @@ -125,6 +125,7 @@ parseDomainWithRepr = pDomainAtom , pSequence , pRelation , pPartition + , pPermutation , DomainMetaVar <$> parseMetaVariable, parens parseDomainWithRepr ] @@ -263,6 +264,13 @@ parseDomainWithRepr = pDomainAtom lexeme L_from y <- parseDomainWithRepr return $ DomainPartition r x y + pPermutation = do + lexeme L_permutation + r <- parseRepr + x <- parsePermutationAttr + lexeme L_of -- $ trace (textToString $ representationToShortText r) L_of + y <- parseDomainWithRepr + return $ DomainPermutation r x y parseAttributes :: Parser (DomainAttributes Expression) parseAttributes = do @@ -445,6 +453,26 @@ parsePartitionAttr = do let isRegular = DAName "regular" `elem` attrs return PartitionAttr {..} +parsePermutationAttr :: Parser (PermutationAttr Expression) +parsePermutationAttr = do + pos <- getPosition + DomainAttributes attrs <- parseAttributes + checkExtraAttributes pos "permutation" attrs + [ "size", "minSize", "maxSize" + ] + size <- case filterSizey attrs of + [DANameValue "size" a] -> return (SizeAttr_Size a) + [DANameValue "minSize" a] -> return (SizeAttr_MinSize a) + [DANameValue "maxSize" a] -> return (SizeAttr_MaxSize a) + [DANameValue "maxSize" b, DANameValue "minSize" a] -> return (SizeAttr_MinMaxSize a b) + [] -> return SizeAttr_None + as -> do + setPosition pos + fail ("incompatible attributes:" <+> stringToDoc (show as)) + return (PermutationAttr size) + + + checkExtraAttributes :: SourcePos -> Doc -> [DomainAttribute a] -> [Name] -> Parser () checkExtraAttributes pos ty attrs supported = do @@ -551,6 +579,7 @@ parseLiteral = label "value" (do p <- pCore ; p) L_sequence -> Just pSequence L_relation -> Just pRelation L_partition -> Just pPartition + L_permutation -> Just pPermutation L_Minus -> Just $ do p <- pCore res <- p @@ -636,6 +665,13 @@ parseLiteral = label "value" (do p <- pCore ; p) where inner = braces (commaSeparated0 parseExpr) + pPermutation = mkAbstractLiteral <$> do + -- lexeme L_permutation + xs <- parens (commaSeparated0 inner) + return (AbsLitPermutation xs) + where + inner = parens (commaSeparated0 parseExpr) + identifierText :: Parser T.Text identifierText = do diff --git a/src/Conjure/Language/Type.hs b/src/Conjure/Language/Type.hs index 7f69cb56d3..a244775d32 100644 --- a/src/Conjure/Language/Type.hs +++ b/src/Conjure/Language/Type.hs @@ -11,6 +11,7 @@ module Conjure.Language.Type , innerTypeOf , isPrimitiveType , typeCanIndexMatrix + , containsType ) where -- conjure @@ -74,18 +75,6 @@ instance Pretty Type where pretty (TypePermutation x) = "permutation of" <+> pretty x -data IntTag = NoTag - | TagEnum Name - | TagUnnamed Name - deriving (Eq, Ord, Show, Data, Typeable, Generic) - -instance Serialize IntTag -instance Hashable IntTag -instance ToJSON IntTag where toJSON = genericToJSON jsonOptions -instance FromJSON IntTag where parseJSON = genericParseJSON jsonOptions - - - data IntTag = NoTag | TagEnum Text | TagUnnamed Text @@ -239,3 +228,12 @@ typeCanIndexMatrix TypeBool{} = True typeCanIndexMatrix TypeInt {} = True typeCanIndexMatrix TypeEnum{} = True typeCanIndexMatrix _ = False + + +containsType :: Type -> Type -> Bool +containsType container containee = + if typesUnify [container, containee] + then True + else case innerTypeOf container of + Nothing -> False + Just so -> containsType so containee diff --git a/src/Conjure/Process/Enums.hs b/src/Conjure/Process/Enums.hs index dfb42e44d0..f7cded5502 100644 --- a/src/Conjure/Process/Enums.hs +++ b/src/Conjure/Process/Enums.hs @@ -41,9 +41,6 @@ removeEnumsFromModel = let outDomain = mkDomainIntBTagged (TagEnum enameText) (fromIntWithTag 1 (TagEnum enameText)) (fromIntWithTag (genericLength names) (TagEnum enameText)) - case names `intersect` namesBefore of - [] -> modify ( ( [(ename, outDomain)] - , zip names (zip (cycle [ename]) allNats) case names `intersect` namesBefore of [] -> modify ( ( [(ename, outDomain)] , zip names (zip (cycle [ename]) allNats) @@ -71,11 +68,6 @@ removeEnumsFromModel = onD (DomainEnum nm Nothing _) | Just d <- lookup nm enumDomainNames = return (DomainReference nm (Just d)) - onD (DomainReference nm Nothing) - | Just d <- lookup nm enumDomainNames - onD (DomainEnum nm Nothing _) - | Just d <- lookup nm enumDomainNames - = return (DomainReference nm (Just d)) onD (DomainReference nm Nothing) | Just d <- lookup nm enumDomainNames = return (DomainReference nm (Just d)) @@ -95,20 +87,17 @@ removeEnumsFromModel = (fromIntWithTag 1 (TagEnum nameText)) (Reference nameS (Just (Alias (Domain outDomainS)))) modify ([(name, outDomain)] `mappend`) - return [ Declaration (FindOrGiven Given nameS outDomainS) - , Declaration (Letting name (Domain outDomain)) - ] - (Reference nameS (Just (Alias (Domain outDomainS)))) - modify ([(name, outDomain)] `mappend`) return [ Declaration (FindOrGiven Given nameS outDomainS) , Declaration (Letting name (Domain outDomain)) ] _ -> return [st] let + onD :: Domain () Expression -> Domain () Expression onD (DomainEnum nm@(Name nmText) (Just ranges) _) | Just _ <- lookup nm enumDomainNames + = DomainInt (TagEnum nmText) ranges onD (DomainEnum nm Nothing _) | Just d <- lookup nm enumDomainNames = DomainReference nm (Just d) @@ -117,6 +106,7 @@ removeEnumsFromModel = = DomainReference nm (Just d) onD p = p + let model' = model { mStatements = concat statements' |> transformBi onD } diff --git a/src/Conjure/Representations/Sequence/ExplicitBounded.hs b/src/Conjure/Representations/Sequence/ExplicitBounded.hs index 5f85510dc2..573e33201e 100644 --- a/src/Conjure/Representations/Sequence/ExplicitBounded.hs +++ b/src/Conjure/Representations/Sequence/ExplicitBounded.hs @@ -211,11 +211,6 @@ sequenceExplicitBounded = Representation chck downD structuralCons downC up maxSizeInt <- case maxSize of ConstantInt _ x -> return x - _ -> fail $ vcat - [ "Expecting an integer for the maxSize attribute." - , "But got:" <+> pretty maxSize - , "When working on:" <+> pretty name - , "With domain:" <+> pretty domain _ -> fail $ vcat [ "Expecting an integer for the maxSize attribute." , "But got:" <+> pretty maxSize diff --git a/src/Conjure/Rules/DontCare.hs b/src/Conjure/Rules/DontCare.hs index be29633b30..c33bd2bc50 100644 --- a/src/Conjure/Rules/DontCare.hs +++ b/src/Conjure/Rules/DontCare.hs @@ -32,7 +32,7 @@ rule_Int = "dontCare-int" `namedRule` theRule where RangeLowerBounded v -> v RangeUpperBounded v -> v RangeBounded v _ -> v - DomainIntE _ v -> [essence| min(&v) |] + DomainIntE v -> [essence| min(&v) |] _ -> raiseBug return ( "dontCare value for this integer is" <+> pretty val @@ -133,7 +133,7 @@ handleDontCares p = RangeLowerBounded v -> v RangeUpperBounded v -> v RangeBounded v _ -> v - DomainIntE _ v -> [essence| min(&v) |] + DomainIntE v -> [essence| min(&v) |] _ -> raiseBug return $ make opEq x val TypeTuple{} -> do diff --git a/src/Conjure/Rules/Horizontal/Permutation.hs b/src/Conjure/Rules/Horizontal/Permutation.hs index 3fedf9b3f5..59eda9d2e5 100644 --- a/src/Conjure/Rules/Horizontal/Permutation.hs +++ b/src/Conjure/Rules/Horizontal/Permutation.hs @@ -31,8 +31,8 @@ rule_Permute_Literal = "permutation-permute-literal{AsFunction}" `namedRule` the let prmTup pt = take (length pt) $ zip (cycle pt) (drop 1 $ cycle pt) permTups = join $ prmTup <$> elems let outLiteral = make matrixLiteral - (TypeMatrix (TypeInt Nothing) (TypeTuple [inner,inner])) - (DomainInt Nothing [RangeBounded 1 (fromInt (genericLength permTups))]) + (TypeMatrix (TypeInt NoTag) (TypeTuple [inner,inner])) + (DomainInt NoTag [RangeBounded 1 (fromInt (genericLength permTups))]) [ AbstractLiteral (AbsLitTuple [a,b]) | (a,b) <- permTups ] diff --git a/src/Conjure/UI/TypeCheck.hs b/src/Conjure/UI/TypeCheck.hs index 036e618357..5876a9f5ad 100644 --- a/src/Conjure/UI/TypeCheck.hs +++ b/src/Conjure/UI/TypeCheck.hs @@ -162,7 +162,7 @@ typeCheckModel model1 = do -- DomainInt [RangeSingle x] from DomainIntE x, if x has type int let domainIntERecover :: forall m . MonadFail m => Domain () Expression -> m (Domain () Expression) - domainIntERecover d@(DomainIntE name x) = do + domainIntERecover d@(DomainIntE x) = do ty <- typeOf x return $ case ty of TypeInt t -> DomainInt t [RangeSingle x] diff --git a/src/test/Conjure/RepresentationsTest.hs b/src/test/Conjure/RepresentationsTest.hs index d31f1df283..cf1f092dfa 100644 --- a/src/test/Conjure/RepresentationsTest.hs +++ b/src/test/Conjure/RepresentationsTest.hs @@ -366,13 +366,6 @@ tests = testGroup "representations" , ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantAbstract $ AbsLitTuple [(ConstantInt NoTag) 3, ConstantBool False], (ConstantInt NoTag) 6] , ConstantAbstract $ AbsLitTuple [ConstantBool True , ConstantAbstract $ AbsLitTuple [(ConstantInt NoTag) 4, ConstantBool False], (ConstantInt NoTag) 8] ] - mid = [ ( "x_1", DomainMatrix (intDomain 1 3) DomainBool - , ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantBool False, ConstantBool False, ConstantBool True] ) - , ( "x_2", DomainMatrix (intDomain 1 3) (DomainTuple [intDomain 1 3, DomainBool]) - , ConstantAbstract $ AbsLitMatrix (intDomain 1 3) - [ ConstantAbstract $ AbsLitTuple [(ConstantInt NoTag) 2, ConstantBool True ] - , ConstantAbstract $ AbsLitTuple [(ConstantInt NoTag) 3, ConstantBool False] - ] mid = [ ( "x_1", DomainMatrix (intDomain 1 3) DomainBool , ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantBool False, ConstantBool False, ConstantBool True] ) , ( "x_2", DomainMatrix (intDomain 1 3) (DomainTuple [intDomain 1 3, DomainBool]) @@ -436,11 +429,6 @@ tests = testGroup "representations" , ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ConstantBool True , (ConstantInt NoTag) 5], ConstantBool False], (ConstantInt NoTag) 7] , ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ConstantBool True , (ConstantInt NoTag) 6], ConstantBool False], (ConstantInt NoTag) 9] ] - , ConstantAbstract $ AbsLitMatrix (intDomain 1 3) - [ ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ConstantBool False, (ConstantInt NoTag) 4], ConstantBool True ], (ConstantInt NoTag) 4] - , ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ConstantBool True , (ConstantInt NoTag) 5], ConstantBool False], (ConstantInt NoTag) 7] - , ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ConstantBool True , (ConstantInt NoTag) 6], ConstantBool False], (ConstantInt NoTag) 9] - ] ] mid = [ ( "x_1" , DomainMatrix (intDomain 1 2) @@ -605,13 +593,6 @@ tests = testGroup "representations" , ConstantAbstract $ AbsLitTuple [(ConstantInt NoTag) 5, ConstantAbstract $ AbsLitMatrix (intDomain 1 2) [(ConstantInt NoTag) 5, (ConstantInt NoTag) 6]] ] ] - mid = - [ ( "x_1" , DomainBool,ConstantBool False ) - , ( "x_2" , DomainMatrix (intDomain 1 3) (DomainTuple [intDomain 0 9,DomainMatrix (intDomain 1 2) (intDomain 0 9)]) - , ConstantAbstract $ AbsLitMatrix (intDomain 1 3) - [ ConstantAbstract $ AbsLitTuple [(ConstantInt NoTag) 2,ConstantAbstract $ AbsLitMatrix (intDomain 1 2) [(ConstantInt NoTag) 1,(ConstantInt NoTag) 3]] - ] - ] mid = [ ( "x_1" , DomainBool,ConstantBool False ) , ( "x_2" , DomainMatrix (intDomain 1 3) (DomainTuple [intDomain 0 9,DomainMatrix (intDomain 1 2) (intDomain 0 9)]) @@ -697,11 +678,6 @@ tests = testGroup "representations" , ConstantAbstract $ AbsLitSet [(ConstantInt NoTag) 5, (ConstantInt NoTag) 8] ] ) ] - low = - [ ( "x_ExplicitR3_Explicit" - , DomainMatrix (intDomain 1 4) (DomainMatrix (intDomain 1 2) (intDomain 0 9)) - ] - ) ] low = [ ( "x_ExplicitR3_Explicit" , DomainMatrix (intDomain 1 4) (DomainMatrix (intDomain 1 2) (intDomain 0 9)) @@ -1248,4 +1224,3 @@ instance Show (Pr (Name, Constant)) where instance Show (Pr [(Name, Constant)]) where show (Pr xs) = intercalate "\n" $ map (show . Pr) xs - diff --git a/tests/custom/basic/function-literal-suggestion/stdout.expected b/tests/custom/basic/function-literal-suggestion/stdout.expected index eb5c6794d3..5b00a977ec 100644 --- a/tests/custom/basic/function-literal-suggestion/stdout.expected +++ b/tests/custom/basic/function-literal-suggestion/stdout.expected @@ -2,10 +2,3 @@ Generating models for func.essence Generated models: model000001.eprime Saved under: conjure-output Savile Row: model000001.eprime p.param -||||||| merged common ancestors -======= -Generating models for func.essence -Generated models: model000001.eprime -Saved under: conjure-output -Savile Row: model000001.eprime p.param ->>>>>>> taggedints From 568fdf2aa401ccd3839d99a424ad816388989e31 Mon Sep 17 00:00:00 2001 From: Fraser Dunlop Date: Fri, 2 Nov 2018 10:59:19 +0000 Subject: [PATCH 012/229] Refactor --- src/Conjure/Rules/Vertical/Matrix.hs | 141 ------------------ .../Rules/Vertical/Permutation/AsFunction.hs | 44 +++++- src/Conjure/UI/Model.hs | 3 +- .../permutations/basic/27/permutation.essence | 12 ++ tests/custom/permutations/basic/runthese.sh | 2 +- 5 files changed, 57 insertions(+), 145 deletions(-) create mode 100644 tests/custom/permutations/basic/27/permutation.essence diff --git a/src/Conjure/Rules/Vertical/Matrix.hs b/src/Conjure/Rules/Vertical/Matrix.hs index 7f661fba3b..e31d9c4baa 100644 --- a/src/Conjure/Rules/Vertical/Matrix.hs +++ b/src/Conjure/Rules/Vertical/Matrix.hs @@ -376,80 +376,8 @@ rule_Matrix_Lt_Primitive = "matrix-Lt-primitive" `namedRule` theRule where , return [essence| &x' pretty ty) - y' <- flattenIfNeeded y - DomainMatrix dyindex dyinner <- domainOf y' - DomainPermutation _ _ dpinner <- domainOf perm - dun <- domainUnion dpinner dyinner - return - ( "Horizontal rule for permute matrix" - , do - (dPat, d) <- quantifiedVar - (pyName, py) <- auxiliaryVar - return $ WithLocals - [essence| &py |] - (AuxiliaryVars - --TODO need union of permutation and dy domains - [ Declaration (FindOrGiven LocalFind pyName - (DomainMatrix dyindex dun)) - , SuchThat - [ [essence| - forAll &dPat : &dyindex . - &py[&d] = permute(&perm,&y'[&d]) - |] - ] - ] - ) - ) - else if yinner `containsType` pinner - then error "rule_Matrix_Permute recursion not defined yet" - else return ( "horixontal rule for permute matrix no type match" - , return [essence| &y |] - ) - theRule _ = na "rule_Matrix_Permute" - rule_Matrix_Leq_Primitive :: Rule rule_Matrix_Leq_Primitive = "matrix-Leq-primitive" `namedRule` theRule where --- theRule [essence| &x .<= permute(&perm, &y) |] = do --- tx@TypeMatrix{} <- typeOf x -- TODO: check if x and y have the same arity --- ty@(TypeMatrix _ yinner) <- typeOf y --- (TypePermutation pinner) <- typeOf perm --- if typesUnify [yinner, pinner] --- then do --- unless (isPrimitiveType tx) $ fail ("not a primitive type:" <+> pretty tx) --- unless (isPrimitiveType ty) $ fail ("not a primitive type:" <+> pretty ty) --- x' <- flattenIfNeeded x --- y' <- flattenIfNeeded y --- dy'@(DomainMatrix dyindex _) <- domainOf y' --- return --- ( "Horizontal rule for matrix <=" --- , do --- (dPat, d) <- quantifiedVar --- (pyName, py) <- auxiliaryVar --- return $ WithLocals --- [essence| &x' <=lex &py |] --- (AuxiliaryVars --- --TODO need union of permutation and dy domains --- [ Declaration (FindOrGiven LocalFind pyName dy') --- , SuchThat --- [ [essence| --- forAll &dPat : &dyindex . --- &py[&d] = permute(&perm,&y'[&d]) --- |] --- ] --- ] --- ) --- ) --- else na "rule_Matrix_Leq_Symbreak_Primitive" theRule p = do (x,y) <- case (match opLeq p, match opDotLeq p) of (Just a, _) -> return a @@ -517,18 +445,6 @@ rule_Matrix_DotLt_Decompose = "matrix-DotLt-tuple" `namedRule` theRule where rule_Matrix_DotLeq_Decompose :: Rule rule_Matrix_DotLeq_Decompose = "matrix-DotLeq-tuple" `namedRule` theRule where --- theRule p@[essence| &x .<= permute(&perm, &y) |] = do --- tx@TypeMatrix{} <- typeOf x -- TODO: check matrix index & tuple arity --- ty@TypeMatrix{} <- typeOf y --- TypePermutation{} <- typeOf perm --- when (isPrimitiveType tx) $ fail ("this is a primitive type:" <+> pretty tx) --- when (isPrimitiveType ty) $ fail ("this is a primitive type:" <+> pretty ty) --- xs <- downX1 x --- ys <- downX1 y --- return --- ( "Horizontal rule for matrix .<=, decomposing" --- , return $ decomposeLexDotLeqSym p perm xs ys --- ) theRule p = do (x,y) <- match opDotLeq p tx@TypeMatrix{} <- typeOf x -- TODO: check matrix index & tuple arity @@ -542,63 +458,6 @@ rule_Matrix_DotLeq_Decompose = "matrix-DotLeq-tuple" `namedRule` theRule where , return $ decomposeLexDotLeq p xs ys ) --- HACK --- Moved inside rule_Matrix_DotLeq_Decompose since we need to do this refinement first --- otherwise compact will choose the other as it will also match and we fail ---rule_Matrix_DotLeq_Symbreak_Decompose :: Rule ---rule_Matrix_DotLeq_Symbreak_Decompose = "matrix-DotLeq-tuple" `namedRule` theRule where --- theRule p@[essence| &x .<= permute(&perm, &y) |] = do --- tx@TypeMatrix{} <- typeOf x -- TODO: check matrix index & tuple arity --- ty@TypeMatrix{} <- typeOf y --- when (isPrimitiveType tx) $ fail ("this is a primitive type:" <+> pretty tx) --- when (isPrimitiveType ty) $ fail ("this is a primitive type:" <+> pretty ty) --- xs <- downX1 x --- ys <- downX1 y --- return --- ( "Horizontal rule for matrix .<=, decomposing" --- , return $ decomposeLexDotLeqSym p perm xs ys --- ) --- theRule _ = na "rule_Matrix_DotLeq_Symbreak_Decompose" - --- HACK --- Moved inside rule_Matrix_Leq_Primitive since we need to do this refinement first --- otherwise compact will choose the other as it will also match and we fail ---rule_Matrix_Leq_Symbreak_Primitive :: Rule ---rule_Matrix_Leq_Symbreak_Primitive = "matrix-Leq-symbreak-primitive" `namedRule` theRule where --- theRule [essence| &x .<= permute(&perm, &y) |] = do --- tx@TypeMatrix{} <- typeOf x -- TODO: check if x and y have the same arity --- ty@(TypeMatrix _ yinner) <- typeOf y --- (TypePermutation pinner) <- typeOf perm --- if typesUnify [yinner, pinner] --- then do --- unless (isPrimitiveType tx) $ fail ("not a primitive type:" <+> pretty tx) --- unless (isPrimitiveType ty) $ fail ("not a primitive type:" <+> pretty ty) --- x' <- flattenIfNeeded x --- y' <- flattenIfNeeded y --- dy'@(DomainMatrix dyindex _) <- domainOf y' --- return --- ( "Horizontal rule for matrix <=" --- , do --- (dPat, d) <- quantifiedVar --- (pyName, py) <- auxiliaryVar --- return $ WithLocals --- [essence| &x' <=lex &py |] --- (AuxiliaryVars --- --TODO need union of permutation and dy domains --- [ Declaration (FindOrGiven LocalFind pyName dy') --- , SuchThat --- [ [essence| --- forAll &dPat : &dyindex . --- &py[&d] = permute(&perm,&y'[&d]) --- |] --- ] --- ] --- ) --- ) --- else na "rule_Matrix_Leq_Symbreak_Primitive" --- theRule _ = na "rule_Matrix_Leq_Symbreak_Primitive" - - rule_Comprehension_SingletonDomain :: Rule rule_Comprehension_SingletonDomain = "matrix-comprehension-singleton-domain" `namedRule` theRule where theRule (Comprehension body gensOrConds) = do diff --git a/src/Conjure/Rules/Vertical/Permutation/AsFunction.hs b/src/Conjure/Rules/Vertical/Permutation/AsFunction.hs index d411d1fc29..fd5136ae52 100644 --- a/src/Conjure/Rules/Vertical/Permutation/AsFunction.hs +++ b/src/Conjure/Rules/Vertical/Permutation/AsFunction.hs @@ -3,6 +3,7 @@ module Conjure.Rules.Vertical.Permutation.AsFunction where import Conjure.Rules.Import +import Conjure.Rules.Vertical.Matrix (flattenIfNeeded) rule_Permute_Comprehension_Tuples :: Rule rule_Permute_Comprehension_Tuples = "permutation-comprehension-tuples{AsFunction}" `namedRule` theRule where @@ -29,8 +30,6 @@ rule_Permute_Comprehension_Tuples = "permutation-comprehension-tuples{AsFunction rule_Permute :: Rule rule_Permute = "permutation-permute{AsFunction}" `namedRule` theRule where theRule [essence| permute(&p, &i) |] = do - --TODO is bubble-delay necessary here? --- case p of WithLocals{} -> na "bubble-delay" ; _ -> return () TypePermutation inner <- typeOf p typeI <- typeOf i [f] <- downX1 p @@ -44,6 +43,47 @@ rule_Permute = "permutation-permute{AsFunction}" `namedRule` theRule where theRule _ = na "rule_Permute" +-- TODO need to permute on the indices too +rule_Matrix_Permute :: Rule +rule_Matrix_Permute = "matrix-permute" `namedRule` theRule where + theRule [essence| permute(&perm, &y) |] = do + ty@(TypeMatrix _ yinner) <- typeOf y + (TypePermutation pinner) <- typeOf perm + if typesUnify [yinner, pinner] + then do + unless (isPrimitiveType ty) $ fail ("not a primitive type:" <+> pretty ty) + y' <- flattenIfNeeded y + DomainMatrix dyindex dyinner <- domainOf y' + DomainPermutation _ _ dpinner <- domainOf perm + dun <- domainUnion dpinner dyinner + return + ( "Horizontal rule for permute matrix" + , do + (dPat, d) <- quantifiedVar + (pyName, py) <- auxiliaryVar + return $ WithLocals + [essence| &py |] + (AuxiliaryVars + --TODO need union of permutation and dy domains + [ Declaration (FindOrGiven LocalFind pyName + (DomainMatrix dyindex dun)) + , SuchThat + [ [essence| + forAll &dPat : &dyindex . + &py[&d] = permute(&perm,&y'[&d]) + |] + ] + ] + ) + ) + else if yinner `containsType` pinner + then error "rule_Matrix_Permute recursion not defined yet" + else return ( "horixontal rule for permute matrix no type match" + , return [essence| &y |] + ) + theRule _ = na "rule_Matrix_Permute" + + --rule_Permute_Set :: Rule --rule_Permute_Set = "permutation-permute-set{AsFunction}" `namedRule` theRule where -- theRule [essence| permute(&p,&i) |] = do diff --git a/src/Conjure/UI/Model.hs b/src/Conjure/UI/Model.hs index 1de75bff8a..4457b81491 100644 --- a/src/Conjure/UI/Model.hs +++ b/src/Conjure/UI/Model.hs @@ -1113,7 +1113,6 @@ verticalRules = , Vertical.Matrix.rule_Comprehension_ToSet_List_DuplicateFree , Vertical.Matrix.rule_Matrix_Eq , Vertical.Matrix.rule_Matrix_Neq - , Vertical.Matrix.rule_Matrix_Permute , Vertical.Matrix.rule_Matrix_Leq_Primitive , Vertical.Matrix.rule_Matrix_Leq_Decompose , Vertical.Matrix.rule_Matrix_Lt_Primitive @@ -1183,6 +1182,7 @@ verticalRules = , Vertical.Permutation.AsFunction.rule_Permute_Comprehension_Tuples + , Vertical.Permutation.AsFunction.rule_Matrix_Permute ] @@ -1314,6 +1314,7 @@ horizontalRules = , Horizontal.Permutation.rule_Apply + ] diff --git a/tests/custom/permutations/basic/27/permutation.essence b/tests/custom/permutations/basic/27/permutation.essence new file mode 100644 index 0000000000..1db0c54a4d --- /dev/null +++ b/tests/custom/permutations/basic/27/permutation.essence @@ -0,0 +1,12 @@ +letting MYTYPE be new type enum {THING1, THING2, THING3, THING4, THING5} + +letting p be permutation ((3,4)) + +find x : set (size 4) of MYTYPE + +find y : set (size 4) of MYTYPE + + +such that + y = permute(p,x) + diff --git a/tests/custom/permutations/basic/runthese.sh b/tests/custom/permutations/basic/runthese.sh index 999a81cb2f..042718136a 100644 --- a/tests/custom/permutations/basic/runthese.sh +++ b/tests/custom/permutations/basic/runthese.sh @@ -1 +1 @@ -stack test --fast --test-arguments "-p custom.permutations.basic" +stack test --test-arguments "-p custom.permutations.basic" From a698352df3e0c2658a9122f58990d5058937a3ff Mon Sep 17 00:00:00 2001 From: Fraser Dunlop Date: Fri, 2 Nov 2018 12:50:48 +0000 Subject: [PATCH 013/229] Updated Permute Matrix --- .../Rules/Vertical/Permutation/AsFunction.hs | 82 ++++++------ .../permutations/basic/22/permutation.essence | 6 +- .../permutations/basic/22/permutation.param | 1 + .../permutations/basic/22/stdout.expected | 80 ++++++------ .../permutations/basic/24/stdout.expected | 21 +-- .../permutations/basic/25/permutation.essence | 9 +- .../permutations/basic/25/permutation.param | 4 +- .../permutations/basic/25/stdout.expected | 120 +++++++++--------- .../permutations/basic/26/stdout.expected | 40 +++--- tests/custom/permutations/basic/27/run.sh | 3 + .../permutations/basic/27/stdout.expected | 29 +++++ .../permutations/basic/28/permutation.essence | 12 ++ tests/custom/permutations/basic/28/run.sh | 3 + .../permutations/basic/28/stdout.expected | 29 +++++ 14 files changed, 249 insertions(+), 190 deletions(-) create mode 100755 tests/custom/permutations/basic/27/run.sh create mode 100644 tests/custom/permutations/basic/27/stdout.expected create mode 100644 tests/custom/permutations/basic/28/permutation.essence create mode 100755 tests/custom/permutations/basic/28/run.sh create mode 100644 tests/custom/permutations/basic/28/stdout.expected diff --git a/src/Conjure/Rules/Vertical/Permutation/AsFunction.hs b/src/Conjure/Rules/Vertical/Permutation/AsFunction.hs index fd5136ae52..cb184fe893 100644 --- a/src/Conjure/Rules/Vertical/Permutation/AsFunction.hs +++ b/src/Conjure/Rules/Vertical/Permutation/AsFunction.hs @@ -32,55 +32,49 @@ rule_Permute = "permutation-permute{AsFunction}" `namedRule` theRule where theRule [essence| permute(&p, &i) |] = do TypePermutation inner <- typeOf p typeI <- typeOf i - [f] <- downX1 p - if typesUnify [inner, typeI] - then return - ( "Vertical rule for permutation application to a single value (permute), AsFunction representation" - , do - return [essence| [&i, catchUndef(image(&f,&i),0)][toInt(&i in defined(&f))+1] |] - ) - else na "rule_Permute" + if typeI `containsType` inner + then do + [f] <- downX1 p + if typesUnify [inner, typeI] + then return + ( "Vertical rule for permutation application to a single value" + , do + return [essence| [&i, catchUndef(image(&f,&i),0)][toInt(&i in defined(&f))+1] |] + ) + else na "rule_Permute" --If we hit this then we should hit a refinement error + else return + ( "Vertical rule for permutation application to a type the permutation doesn't care about" + , do + return [essence| &i |] + ) theRule _ = na "rule_Permute" - --- TODO need to permute on the indices too rule_Matrix_Permute :: Rule rule_Matrix_Permute = "matrix-permute" `namedRule` theRule where theRule [essence| permute(&perm, &y) |] = do - ty@(TypeMatrix _ yinner) <- typeOf y - (TypePermutation pinner) <- typeOf perm - if typesUnify [yinner, pinner] - then do - unless (isPrimitiveType ty) $ fail ("not a primitive type:" <+> pretty ty) - y' <- flattenIfNeeded y - DomainMatrix dyindex dyinner <- domainOf y' - DomainPermutation _ _ dpinner <- domainOf perm - dun <- domainUnion dpinner dyinner - return - ( "Horizontal rule for permute matrix" - , do - (dPat, d) <- quantifiedVar - (pyName, py) <- auxiliaryVar - return $ WithLocals - [essence| &py |] - (AuxiliaryVars - --TODO need union of permutation and dy domains - [ Declaration (FindOrGiven LocalFind pyName - (DomainMatrix dyindex dun)) - , SuchThat - [ [essence| - forAll &dPat : &dyindex . - &py[&d] = permute(&perm,&y'[&d]) - |] - ] - ] - ) - ) - else if yinner `containsType` pinner - then error "rule_Matrix_Permute recursion not defined yet" - else return ( "horixontal rule for permute matrix no type match" - , return [essence| &y |] - ) + ty@(TypeMatrix _ _) <- typeOf y + (TypePermutation _) <- typeOf perm + unless (isPrimitiveType ty) $ fail ("not a primitive type:" <+> pretty ty) + y' <- flattenIfNeeded y + dm@(DomainMatrix dyindex _) <- domainOf y' + return + ( "Horizontal rule for permute matrix" + , do + (dPat, d) <- quantifiedVar + (pyName, py) <- auxiliaryVar + return $ WithLocals + [essence| &py |] + (AuxiliaryVars + [ Declaration (FindOrGiven LocalFind pyName dm) + , SuchThat + [ [essence| + forAll &dPat : &dyindex . + &py[&d] = permute(&perm,&y'[permute(&perm,&d)]) + |] + ] + ] + ) + ) theRule _ = na "rule_Matrix_Permute" diff --git a/tests/custom/permutations/basic/22/permutation.essence b/tests/custom/permutations/basic/22/permutation.essence index 4eac7b2e81..6eb43412f5 100644 --- a/tests/custom/permutations/basic/22/permutation.essence +++ b/tests/custom/permutations/basic/22/permutation.essence @@ -1,9 +1,11 @@ given n : int +letting MYTYPE be new type enum {THING1, THING2, THING3, THING4, THING5} -find x : matrix indexed by [int(1..n)] of int(1..n) -find y : matrix indexed by [int(1..n)] of int(1..n) +find x : matrix indexed by [int(1..n)] of MYTYPE + +find y : matrix indexed by [int(1..n)] of MYTYPE such that diff --git a/tests/custom/permutations/basic/22/permutation.param b/tests/custom/permutations/basic/22/permutation.param index 36d2429361..6ea3a6e608 100644 --- a/tests/custom/permutations/basic/22/permutation.param +++ b/tests/custom/permutations/basic/22/permutation.param @@ -1 +1,2 @@ letting n be 5 + diff --git a/tests/custom/permutations/basic/22/stdout.expected b/tests/custom/permutations/basic/22/stdout.expected index 0b96e4d933..d2bbe0f9e1 100644 --- a/tests/custom/permutations/basic/22/stdout.expected +++ b/tests/custom/permutations/basic/22/stdout.expected @@ -24,81 +24,81 @@ Copying solution to: permutation-permutation-000019.solution Copying solution to: permutation-permutation-000020.solution language Essence 1.3 -letting x be [1, 1, 1, 1, 1; int(1..5)] -letting y be [1, 1, 1, 1, 1; int(1..5)] +letting x be [THING1, THING1, THING1, THING1, THING1; int(1..5)] +letting y be [THING1, THING1, THING1, THING1, THING1; int(1..5)] language Essence 1.3 -letting x be [1, 1, 1, 1, 2; int(1..5)] -letting y be [1, 1, 1, 1, 1; int(1..5)] +letting x be [THING1, THING1, THING1, THING1, THING2; int(1..5)] +letting y be [THING1, THING1, THING1, THING1, THING1; int(1..5)] language Essence 1.3 -letting x be [1, 1, 1, 1, 2; int(1..5)] -letting y be [1, 1, 1, 1, 2; int(1..5)] +letting x be [THING1, THING1, THING1, THING1, THING2; int(1..5)] +letting y be [THING1, THING1, THING1, THING1, THING2; int(1..5)] language Essence 1.3 -letting x be [1, 1, 1, 1, 3; int(1..5)] -letting y be [1, 1, 1, 1, 1; int(1..5)] +letting x be [THING1, THING1, THING1, THING1, THING3; int(1..5)] +letting y be [THING1, THING1, THING1, THING1, THING1; int(1..5)] language Essence 1.3 -letting x be [1, 1, 1, 1, 3; int(1..5)] -letting y be [1, 1, 1, 1, 2; int(1..5)] +letting x be [THING1, THING1, THING1, THING1, THING3; int(1..5)] +letting y be [THING1, THING1, THING1, THING1, THING2; int(1..5)] language Essence 1.3 -letting x be [1, 1, 1, 1, 4; int(1..5)] -letting y be [1, 1, 1, 1, 1; int(1..5)] +letting x be [THING1, THING1, THING1, THING1, THING3; int(1..5)] +letting y be [THING1, THING1, THING1, THING1, THING3; int(1..5)] language Essence 1.3 -letting x be [1, 1, 1, 1, 4; int(1..5)] -letting y be [1, 1, 1, 1, 2; int(1..5)] +letting x be [THING1, THING1, THING1, THING1, THING4; int(1..5)] +letting y be [THING1, THING1, THING1, THING1, THING1; int(1..5)] language Essence 1.3 -letting x be [1, 1, 1, 1, 5; int(1..5)] -letting y be [1, 1, 1, 1, 1; int(1..5)] +letting x be [THING1, THING1, THING1, THING1, THING4; int(1..5)] +letting y be [THING1, THING1, THING1, THING1, THING2; int(1..5)] language Essence 1.3 -letting x be [1, 1, 1, 1, 5; int(1..5)] -letting y be [1, 1, 1, 1, 2; int(1..5)] +letting x be [THING1, THING1, THING1, THING1, THING4; int(1..5)] +letting y be [THING1, THING1, THING1, THING1, THING3; int(1..5)] language Essence 1.3 -letting x be [1, 1, 1, 2, 1; int(1..5)] -letting y be [1, 1, 1, 1, 1; int(1..5)] +letting x be [THING1, THING1, THING1, THING1, THING4; int(1..5)] +letting y be [THING1, THING1, THING1, THING1, THING4; int(1..5)] language Essence 1.3 -letting x be [1, 1, 1, 2, 1; int(1..5)] -letting y be [1, 1, 1, 1, 2; int(1..5)] +letting x be [THING1, THING1, THING1, THING1, THING5; int(1..5)] +letting y be [THING1, THING1, THING1, THING1, THING1; int(1..5)] language Essence 1.3 -letting x be [1, 1, 1, 2, 1; int(1..5)] -letting y be [1, 1, 1, 1, 3; int(1..5)] +letting x be [THING1, THING1, THING1, THING1, THING5; int(1..5)] +letting y be [THING1, THING1, THING1, THING1, THING2; int(1..5)] language Essence 1.3 -letting x be [1, 1, 1, 2, 1; int(1..5)] -letting y be [1, 1, 1, 1, 4; int(1..5)] +letting x be [THING1, THING1, THING1, THING1, THING5; int(1..5)] +letting y be [THING1, THING1, THING1, THING1, THING3; int(1..5)] language Essence 1.3 -letting x be [1, 1, 1, 2, 1; int(1..5)] -letting y be [1, 1, 1, 1, 5; int(1..5)] +letting x be [THING1, THING1, THING1, THING1, THING5; int(1..5)] +letting y be [THING1, THING1, THING1, THING1, THING4; int(1..5)] language Essence 1.3 -letting x be [1, 1, 1, 2, 1; int(1..5)] -letting y be [1, 1, 1, 2, 1; int(1..5)] +letting x be [THING1, THING1, THING1, THING1, THING5; int(1..5)] +letting y be [THING1, THING1, THING1, THING1, THING5; int(1..5)] language Essence 1.3 -letting x be [1, 1, 1, 2, 2; int(1..5)] -letting y be [1, 1, 1, 1, 1; int(1..5)] +letting x be [THING1, THING1, THING1, THING2, THING1; int(1..5)] +letting y be [THING1, THING1, THING1, THING1, THING1; int(1..5)] language Essence 1.3 -letting x be [1, 1, 1, 2, 2; int(1..5)] -letting y be [1, 1, 1, 1, 2; int(1..5)] +letting x be [THING1, THING1, THING1, THING2, THING1; int(1..5)] +letting y be [THING1, THING1, THING1, THING1, THING2; int(1..5)] language Essence 1.3 -letting x be [1, 1, 1, 2, 2; int(1..5)] -letting y be [1, 1, 1, 1, 3; int(1..5)] +letting x be [THING1, THING1, THING1, THING2, THING2; int(1..5)] +letting y be [THING1, THING1, THING1, THING1, THING1; int(1..5)] language Essence 1.3 -letting x be [1, 1, 1, 2, 2; int(1..5)] -letting y be [1, 1, 1, 1, 4; int(1..5)] +letting x be [THING1, THING1, THING1, THING2, THING2; int(1..5)] +letting y be [THING1, THING1, THING1, THING1, THING2; int(1..5)] language Essence 1.3 -letting x be [1, 1, 1, 2, 2; int(1..5)] -letting y be [1, 1, 1, 1, 5; int(1..5)] +letting x be [THING1, THING1, THING1, THING2, THING2; int(1..5)] +letting y be [THING1, THING1, THING1, THING1, THING3; int(1..5)] diff --git a/tests/custom/permutations/basic/24/stdout.expected b/tests/custom/permutations/basic/24/stdout.expected index 58bb53cf5f..443cd04178 100644 --- a/tests/custom/permutations/basic/24/stdout.expected +++ b/tests/custom/permutations/basic/24/stdout.expected @@ -2,23 +2,8 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output Savile Row: model000001.eprime permutation.param -Copying solution to: permutation-permutation-000001.solution -Copying solution to: permutation-permutation-000002.solution -Copying solution to: permutation-permutation-000003.solution -Copying solution to: permutation-permutation-000004.solution +Copying solution to: permutation-permutation.solution language Essence 1.3 -letting x be (1, 1, 1) -letting y be (1, 1, 1) -language Essence 1.3 - -letting x be (1, 1, 2) -letting y be (1, 1, 1) -language Essence 1.3 - -letting x be (1, 1, 2) -letting y be (1, 1, 2) -language Essence 1.3 - -letting x be (1, 1, 3) -letting y be (1, 1, 1) +letting x be {1, 2, 3, 4} +letting y be {1, 2, 3, 4} diff --git a/tests/custom/permutations/basic/25/permutation.essence b/tests/custom/permutations/basic/25/permutation.essence index fad89799a5..79eb62c707 100644 --- a/tests/custom/permutations/basic/25/permutation.essence +++ b/tests/custom/permutations/basic/25/permutation.essence @@ -2,14 +2,15 @@ given n : int given m : int -find p : permutation of int(1..m) +find p : permutation of int(1..n) -find x : matrix indexed by [int(1..n)] of int(1..n) +find x : matrix indexed by [int((n+1)..m)] of int(1..n) -find y : matrix indexed by [int(1..n)] of int(n..m) +find y : matrix indexed by [int((n+1)..m)] of int(1..n) such that y = permute(p,x) /\ allDiff(y) - /\ allDiff(x) + /\ x != y + diff --git a/tests/custom/permutations/basic/25/permutation.param b/tests/custom/permutations/basic/25/permutation.param index 4c5bdd272d..581936cf9d 100644 --- a/tests/custom/permutations/basic/25/permutation.param +++ b/tests/custom/permutations/basic/25/permutation.param @@ -1,2 +1,2 @@ -letting n be 5 -letting m be 10 +letting n be 3 +letting m be 6 diff --git a/tests/custom/permutations/basic/25/stdout.expected b/tests/custom/permutations/basic/25/stdout.expected index 9d98db50a0..75a4205281 100644 --- a/tests/custom/permutations/basic/25/stdout.expected +++ b/tests/custom/permutations/basic/25/stdout.expected @@ -24,101 +24,101 @@ Copying solution to: permutation-permutation-000019.solution Copying solution to: permutation-permutation-000020.solution language Essence 1.3 -letting p be permutation((1, 5, 9, 4, 8, 3, 7, 2, 6)) -letting x be [1, 2, 3, 4, 5; int(1..5)] -letting y be [5, 6, 7, 8, 9; int(1..5)] +letting p be permutation((2, 3)) +letting x be [1, 2, 3; int(4..6)] +letting y be [1, 3, 2; int(4..6)] language Essence 1.3 -letting p be permutation((1, 5, 9, 4, 8, 3, 7, 2, 6)) -letting x be [1, 2, 3, 5, 4; int(1..5)] -letting y be [5, 6, 7, 9, 8; int(1..5)] +letting p be permutation((2, 3)) +letting x be [1, 3, 2; int(4..6)] +letting y be [1, 2, 3; int(4..6)] language Essence 1.3 -letting p be permutation((1, 5, 9, 4, 8, 3, 7, 2, 6)) -letting x be [1, 2, 4, 3, 5; int(1..5)] -letting y be [5, 6, 8, 7, 9; int(1..5)] +letting p be permutation((2, 3)) +letting x be [2, 1, 3; int(4..6)] +letting y be [3, 1, 2; int(4..6)] language Essence 1.3 -letting p be permutation((1, 5, 9, 4, 8, 3, 7, 2, 6)) -letting x be [1, 2, 4, 5, 3; int(1..5)] -letting y be [5, 6, 8, 9, 7; int(1..5)] +letting p be permutation((2, 3)) +letting x be [2, 3, 1; int(4..6)] +letting y be [3, 2, 1; int(4..6)] language Essence 1.3 -letting p be permutation((1, 5, 9, 4, 8, 3, 7, 2, 6)) -letting x be [1, 2, 5, 3, 4; int(1..5)] -letting y be [5, 6, 9, 7, 8; int(1..5)] +letting p be permutation((2, 3)) +letting x be [3, 1, 2; int(4..6)] +letting y be [2, 1, 3; int(4..6)] language Essence 1.3 -letting p be permutation((1, 5, 9, 4, 8, 3, 7, 2, 6)) -letting x be [1, 2, 5, 4, 3; int(1..5)] -letting y be [5, 6, 9, 8, 7; int(1..5)] +letting p be permutation((2, 3)) +letting x be [3, 2, 1; int(4..6)] +letting y be [2, 3, 1; int(4..6)] language Essence 1.3 -letting p be permutation((1, 5, 9, 4, 8, 3, 7, 2, 6)) -letting x be [1, 3, 2, 4, 5; int(1..5)] -letting y be [5, 7, 6, 8, 9; int(1..5)] +letting p be permutation((1, 2)) +letting x be [1, 2, 3; int(4..6)] +letting y be [2, 1, 3; int(4..6)] language Essence 1.3 -letting p be permutation((1, 5, 9, 4, 8, 3, 7, 2, 6)) -letting x be [1, 3, 2, 5, 4; int(1..5)] -letting y be [5, 7, 6, 9, 8; int(1..5)] +letting p be permutation((1, 2)) +letting x be [1, 3, 2; int(4..6)] +letting y be [2, 3, 1; int(4..6)] language Essence 1.3 -letting p be permutation((1, 5, 9, 4, 8, 3, 7, 2, 6)) -letting x be [1, 3, 4, 2, 5; int(1..5)] -letting y be [5, 7, 8, 6, 9; int(1..5)] +letting p be permutation((1, 2)) +letting x be [2, 1, 3; int(4..6)] +letting y be [1, 2, 3; int(4..6)] language Essence 1.3 -letting p be permutation((1, 5, 9, 4, 8, 3, 7, 2, 6)) -letting x be [1, 3, 4, 5, 2; int(1..5)] -letting y be [5, 7, 8, 9, 6; int(1..5)] +letting p be permutation((1, 2)) +letting x be [2, 3, 1; int(4..6)] +letting y be [1, 3, 2; int(4..6)] language Essence 1.3 -letting p be permutation((1, 5, 9, 4, 8, 3, 7, 2, 6)) -letting x be [1, 3, 5, 2, 4; int(1..5)] -letting y be [5, 7, 9, 6, 8; int(1..5)] +letting p be permutation((1, 2)) +letting x be [3, 1, 2; int(4..6)] +letting y be [3, 2, 1; int(4..6)] language Essence 1.3 -letting p be permutation((1, 5, 9, 4, 8, 3, 7, 2, 6)) -letting x be [1, 3, 5, 4, 2; int(1..5)] -letting y be [5, 7, 9, 8, 6; int(1..5)] +letting p be permutation((1, 2)) +letting x be [3, 2, 1; int(4..6)] +letting y be [3, 1, 2; int(4..6)] language Essence 1.3 -letting p be permutation((1, 5, 9, 4, 8, 3, 7, 2, 6)) -letting x be [1, 4, 2, 3, 5; int(1..5)] -letting y be [5, 8, 6, 7, 9; int(1..5)] +letting p be permutation((1, 2, 3)) +letting x be [1, 2, 3; int(4..6)] +letting y be [2, 3, 1; int(4..6)] language Essence 1.3 -letting p be permutation((1, 5, 9, 4, 8, 3, 7, 2, 6)) -letting x be [1, 4, 2, 5, 3; int(1..5)] -letting y be [5, 8, 6, 9, 7; int(1..5)] +letting p be permutation((1, 2, 3)) +letting x be [1, 3, 2; int(4..6)] +letting y be [2, 1, 3; int(4..6)] language Essence 1.3 -letting p be permutation((1, 5, 9, 4, 8, 3, 7, 2, 6)) -letting x be [1, 4, 3, 2, 5; int(1..5)] -letting y be [5, 8, 7, 6, 9; int(1..5)] +letting p be permutation((1, 2, 3)) +letting x be [2, 1, 3; int(4..6)] +letting y be [3, 2, 1; int(4..6)] language Essence 1.3 -letting p be permutation((1, 5, 9, 4, 8, 3, 7, 2, 6)) -letting x be [1, 4, 3, 5, 2; int(1..5)] -letting y be [5, 8, 7, 9, 6; int(1..5)] +letting p be permutation((1, 2, 3)) +letting x be [2, 3, 1; int(4..6)] +letting y be [3, 1, 2; int(4..6)] language Essence 1.3 -letting p be permutation((1, 5, 9, 4, 8, 3, 7, 2, 6)) -letting x be [1, 4, 5, 2, 3; int(1..5)] -letting y be [5, 8, 9, 6, 7; int(1..5)] +letting p be permutation((1, 2, 3)) +letting x be [3, 1, 2; int(4..6)] +letting y be [1, 2, 3; int(4..6)] language Essence 1.3 -letting p be permutation((1, 5, 9, 4, 8, 3, 7, 2, 6)) -letting x be [1, 4, 5, 3, 2; int(1..5)] -letting y be [5, 8, 9, 7, 6; int(1..5)] +letting p be permutation((1, 2, 3)) +letting x be [3, 2, 1; int(4..6)] +letting y be [1, 3, 2; int(4..6)] language Essence 1.3 -letting p be permutation((1, 5, 9, 4, 8, 3, 7, 2, 6)) -letting x be [1, 5, 2, 3, 4; int(1..5)] -letting y be [5, 9, 6, 7, 8; int(1..5)] +letting p be permutation((1, 3, 2)) +letting x be [1, 2, 3; int(4..6)] +letting y be [3, 1, 2; int(4..6)] language Essence 1.3 -letting p be permutation((1, 5, 9, 4, 8, 3, 7, 2, 6)) -letting x be [1, 5, 2, 4, 3; int(1..5)] -letting y be [5, 9, 6, 8, 7; int(1..5)] +letting p be permutation((1, 3, 2)) +letting x be [1, 3, 2; int(4..6)] +letting y be [3, 2, 1; int(4..6)] diff --git a/tests/custom/permutations/basic/26/stdout.expected b/tests/custom/permutations/basic/26/stdout.expected index a70293f5c9..40dfd2cbff 100644 --- a/tests/custom/permutations/basic/26/stdout.expected +++ b/tests/custom/permutations/basic/26/stdout.expected @@ -25,80 +25,80 @@ Copying solution to: permutation-permutation-000020.solution language Essence 1.3 letting x be [THING1, THING2, THING3, THING4, THING5; int(1..5)] -letting y be [THING1, THING2, THING3, THING4, THING5; int(1..5)] +letting y be [THING1, THING2, THING4, THING3, THING5; int(1..5)] language Essence 1.3 letting x be [THING1, THING2, THING3, THING5, THING4; int(1..5)] -letting y be [THING1, THING2, THING3, THING5, THING4; int(1..5)] +letting y be [THING1, THING2, THING5, THING3, THING4; int(1..5)] language Essence 1.3 letting x be [THING1, THING2, THING4, THING3, THING5; int(1..5)] -letting y be [THING1, THING2, THING4, THING3, THING5; int(1..5)] +letting y be [THING1, THING2, THING3, THING4, THING5; int(1..5)] language Essence 1.3 letting x be [THING1, THING2, THING4, THING5, THING3; int(1..5)] -letting y be [THING1, THING2, THING4, THING5, THING3; int(1..5)] +letting y be [THING1, THING2, THING5, THING4, THING3; int(1..5)] language Essence 1.3 letting x be [THING1, THING2, THING5, THING3, THING4; int(1..5)] -letting y be [THING1, THING2, THING5, THING3, THING4; int(1..5)] +letting y be [THING1, THING2, THING3, THING5, THING4; int(1..5)] language Essence 1.3 letting x be [THING1, THING2, THING5, THING4, THING3; int(1..5)] -letting y be [THING1, THING2, THING5, THING4, THING3; int(1..5)] +letting y be [THING1, THING2, THING4, THING5, THING3; int(1..5)] language Essence 1.3 letting x be [THING1, THING3, THING2, THING4, THING5; int(1..5)] -letting y be [THING1, THING3, THING2, THING4, THING5; int(1..5)] +letting y be [THING1, THING3, THING4, THING2, THING5; int(1..5)] language Essence 1.3 letting x be [THING1, THING3, THING2, THING5, THING4; int(1..5)] -letting y be [THING1, THING3, THING2, THING5, THING4; int(1..5)] +letting y be [THING1, THING3, THING5, THING2, THING4; int(1..5)] language Essence 1.3 letting x be [THING1, THING3, THING4, THING2, THING5; int(1..5)] -letting y be [THING1, THING3, THING4, THING2, THING5; int(1..5)] +letting y be [THING1, THING3, THING2, THING4, THING5; int(1..5)] language Essence 1.3 letting x be [THING1, THING3, THING4, THING5, THING2; int(1..5)] -letting y be [THING1, THING3, THING4, THING5, THING2; int(1..5)] +letting y be [THING1, THING3, THING5, THING4, THING2; int(1..5)] language Essence 1.3 letting x be [THING1, THING3, THING5, THING2, THING4; int(1..5)] -letting y be [THING1, THING3, THING5, THING2, THING4; int(1..5)] +letting y be [THING1, THING3, THING2, THING5, THING4; int(1..5)] language Essence 1.3 letting x be [THING1, THING3, THING5, THING4, THING2; int(1..5)] -letting y be [THING1, THING3, THING5, THING4, THING2; int(1..5)] +letting y be [THING1, THING3, THING4, THING5, THING2; int(1..5)] language Essence 1.3 letting x be [THING1, THING4, THING2, THING3, THING5; int(1..5)] -letting y be [THING1, THING4, THING2, THING3, THING5; int(1..5)] +letting y be [THING1, THING4, THING3, THING2, THING5; int(1..5)] language Essence 1.3 letting x be [THING1, THING4, THING2, THING5, THING3; int(1..5)] -letting y be [THING1, THING4, THING2, THING5, THING3; int(1..5)] +letting y be [THING1, THING4, THING5, THING2, THING3; int(1..5)] language Essence 1.3 letting x be [THING1, THING4, THING3, THING2, THING5; int(1..5)] -letting y be [THING1, THING4, THING3, THING2, THING5; int(1..5)] +letting y be [THING1, THING4, THING2, THING3, THING5; int(1..5)] language Essence 1.3 letting x be [THING1, THING4, THING3, THING5, THING2; int(1..5)] -letting y be [THING1, THING4, THING3, THING5, THING2; int(1..5)] +letting y be [THING1, THING4, THING5, THING3, THING2; int(1..5)] language Essence 1.3 letting x be [THING1, THING4, THING5, THING2, THING3; int(1..5)] -letting y be [THING1, THING4, THING5, THING2, THING3; int(1..5)] +letting y be [THING1, THING4, THING2, THING5, THING3; int(1..5)] language Essence 1.3 letting x be [THING1, THING4, THING5, THING3, THING2; int(1..5)] -letting y be [THING1, THING4, THING5, THING3, THING2; int(1..5)] +letting y be [THING1, THING4, THING3, THING5, THING2; int(1..5)] language Essence 1.3 letting x be [THING1, THING5, THING2, THING3, THING4; int(1..5)] -letting y be [THING1, THING5, THING2, THING3, THING4; int(1..5)] +letting y be [THING1, THING5, THING3, THING2, THING4; int(1..5)] language Essence 1.3 letting x be [THING1, THING5, THING2, THING4, THING3; int(1..5)] -letting y be [THING1, THING5, THING2, THING4, THING3; int(1..5)] +letting y be [THING1, THING5, THING4, THING2, THING3; int(1..5)] diff --git a/tests/custom/permutations/basic/27/run.sh b/tests/custom/permutations/basic/27/run.sh new file mode 100755 index 0000000000..a440de2e64 --- /dev/null +++ b/tests/custom/permutations/basic/27/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence --number-of-solutions=20 +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/basic/27/stdout.expected b/tests/custom/permutations/basic/27/stdout.expected new file mode 100644 index 0000000000..b7d1e6e137 --- /dev/null +++ b/tests/custom/permutations/basic/27/stdout.expected @@ -0,0 +1,29 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Copying solution to: permutation-000001.solution +Copying solution to: permutation-000002.solution +Copying solution to: permutation-000003.solution +Copying solution to: permutation-000004.solution +Copying solution to: permutation-000005.solution +language Essence 1.3 + +letting x be {THING2, THING3, THING4, THING5} +letting y be {THING2, THING3, THING4, THING5} +language Essence 1.3 + +letting x be {THING1, THING3, THING4, THING5} +letting y be {THING1, THING3, THING4, THING5} +language Essence 1.3 + +letting x be {THING1, THING2, THING4, THING5} +letting y be {THING1, THING2, THING4, THING5} +language Essence 1.3 + +letting x be {THING1, THING2, THING3, THING5} +letting y be {THING1, THING2, THING3, THING5} +language Essence 1.3 + +letting x be {THING1, THING2, THING3, THING4} +letting y be {THING1, THING2, THING3, THING4} diff --git a/tests/custom/permutations/basic/28/permutation.essence b/tests/custom/permutations/basic/28/permutation.essence new file mode 100644 index 0000000000..25557ec986 --- /dev/null +++ b/tests/custom/permutations/basic/28/permutation.essence @@ -0,0 +1,12 @@ +letting MYTYPE be new type enum {THING1, THING2, THING3, THING4, THING5} + +letting p be permutation ((THING3,THING4)) + +find x : set (size 4) of MYTYPE + +find y : set (size 4) of MYTYPE + + +such that + y = permute(p,x) + diff --git a/tests/custom/permutations/basic/28/run.sh b/tests/custom/permutations/basic/28/run.sh new file mode 100755 index 0000000000..a440de2e64 --- /dev/null +++ b/tests/custom/permutations/basic/28/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence --number-of-solutions=20 +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/basic/28/stdout.expected b/tests/custom/permutations/basic/28/stdout.expected new file mode 100644 index 0000000000..b7d1e6e137 --- /dev/null +++ b/tests/custom/permutations/basic/28/stdout.expected @@ -0,0 +1,29 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Copying solution to: permutation-000001.solution +Copying solution to: permutation-000002.solution +Copying solution to: permutation-000003.solution +Copying solution to: permutation-000004.solution +Copying solution to: permutation-000005.solution +language Essence 1.3 + +letting x be {THING2, THING3, THING4, THING5} +letting y be {THING2, THING3, THING4, THING5} +language Essence 1.3 + +letting x be {THING1, THING3, THING4, THING5} +letting y be {THING1, THING3, THING4, THING5} +language Essence 1.3 + +letting x be {THING1, THING2, THING4, THING5} +letting y be {THING1, THING2, THING4, THING5} +language Essence 1.3 + +letting x be {THING1, THING2, THING3, THING5} +letting y be {THING1, THING2, THING3, THING5} +language Essence 1.3 + +letting x be {THING1, THING2, THING3, THING4} +letting y be {THING1, THING2, THING3, THING4} From 8d671dc14022e684acb4030da1decdfeb9a22aa9 Mon Sep 17 00:00:00 2001 From: Fraser Dunlop Date: Tue, 6 Nov 2018 11:27:29 +0000 Subject: [PATCH 014/229] Set permute rule working --- src/Conjure/Rules/Horizontal/Permutation.hs | 127 +++++++++++++----- .../Rules/Vertical/Permutation/AsFunction.hs | 76 +++++++++-- src/Conjure/UI/Model.hs | 6 + .../permutations/basic/28/permutation.essence | 3 +- .../permutations/basic/28/stdout.expected | 19 +-- 5 files changed, 170 insertions(+), 61 deletions(-) diff --git a/src/Conjure/Rules/Horizontal/Permutation.hs b/src/Conjure/Rules/Horizontal/Permutation.hs index 59eda9d2e5..d2df51c8a9 100644 --- a/src/Conjure/Rules/Horizontal/Permutation.hs +++ b/src/Conjure/Rules/Horizontal/Permutation.hs @@ -25,39 +25,102 @@ rule_Permute_Literal = "permutation-permute-literal{AsFunction}" `namedRule` the theRule [essence| permute(&p, &i) |] = do (TypePermutation inner, elems) <- match permutationLiteral p typeI <- typeOf i - if typesUnify [inner, typeI] - then do - innerD <- domainOf i - let prmTup pt = take (length pt) $ zip (cycle pt) (drop 1 $ cycle pt) - permTups = join $ prmTup <$> elems - let outLiteral = make matrixLiteral - (TypeMatrix (TypeInt NoTag) (TypeTuple [inner,inner])) - (DomainInt NoTag [RangeBounded 1 (fromInt (genericLength permTups))]) - [ AbstractLiteral (AbsLitTuple [a,b]) - | (a,b) <- permTups - ] - return - ( "Vertical rule for permutation literal application to a single value (permute), AsFunction representation" - , do - (hName, h) <- auxiliaryVar - (fPat, f) <- quantifiedVar - (tPat, t) <- quantifiedVar - (gPat, g) <- quantifiedVar - (ePat, _) <- quantifiedVar - return $ WithLocals - [essence| &h |] - (AuxiliaryVars - [ Declaration (FindOrGiven LocalFind hName innerD) - , SuchThat - [ [essence| - (forAll (&fPat, &tPat) in &outLiteral . &f = &i <-> &h = &t) - /\ (!(exists (&gPat, &ePat) in &outLiteral . &g = &h) <-> &h = &i) - |] + if typeI `containsType` inner + then do + if typesUnify [inner, typeI] + then do + innerD <- domainOf i + let prmTup pt = take (length pt) $ zip (cycle pt) (drop 1 $ cycle pt) + permTups = join $ prmTup <$> elems + let outLiteral = make matrixLiteral + (TypeMatrix (TypeInt NoTag) (TypeTuple [inner,inner])) + (DomainInt NoTag [RangeBounded 1 (fromInt (genericLength permTups))]) + [ AbstractLiteral (AbsLitTuple [a,b]) + | (a,b) <- permTups + ] + return + ( "Horizontal rule for permutation literal application to a single value (permute), AsFunction representation" + , do + (hName, h) <- auxiliaryVar + (fPat, f) <- quantifiedVar + (tPat, t) <- quantifiedVar + (gPat, g) <- quantifiedVar + (ePat, _) <- quantifiedVar + return $ WithLocals + [essence| &h |] + (AuxiliaryVars + [ Declaration (FindOrGiven LocalFind hName innerD) + , SuchThat + [ [essence| + (forAll (&fPat, &tPat) in &outLiteral . &f = &i <-> &h = &t) + /\ (!(exists (&gPat, &ePat) in &outLiteral . &g = &h) <-> &h = &i) + |] + ] ] - ] - ) - ) - else na "rule_Permute_Literal" + ) + ) + else na "rule_Permute_Literal" + else return + ( "Horizontal rule for permutation application to a type the permutation doesn't care about" + , do + return [essence| &i |] + ) + theRule _ = na "rule_Permute_Literal" + + +rule_Permute_Literal_Comprehension :: Rule +rule_Permute_Literal_Comprehension = "permutation-permute-literal-comprehension{AsFunction}" `namedRule` theRule where + theRule (Comprehension body gensOrConds) = do + (gocBefore, (pat, p, i), gocAfter) <- matchFirst gensOrConds $ \ goc -> case goc of + Generator (GenInExpr pat [essence| permute(&p, &i) |]) -> return (pat, p, i) + _ -> na "rule_Comprehension" + (TypePermutation inner, elems) <- match permutationLiteral p + typeI <- typeOf i + if typeI `containsType` inner + then do + if typesUnify [inner, typeI] + then do + innerD <- domainOf i + let prmTup pt = take (length pt) $ zip (cycle pt) (drop 1 $ cycle pt) + permTups = join $ prmTup <$> elems + let outLiteral = make matrixLiteral + (TypeMatrix (TypeInt NoTag) (TypeTuple [inner,inner])) + (DomainInt NoTag [RangeBounded 1 (fromInt (genericLength permTups))]) + [ AbstractLiteral (AbsLitTuple [a,b]) + | (a,b) <- permTups + ] + return + ( "Horizontal rule for permutation literal application to a single value (permute), AsFunction representation" + , do + (hName, h) <- auxiliaryVar + (fPat, f) <- quantifiedVar + (tPat, t) <- quantifiedVar + (gPat, g) <- quantifiedVar + (ePat, _) <- quantifiedVar + return $ WithLocals + (Comprehension body $ gocBefore + ++ [Generator (GenInExpr pat + [essence| &h |])] + ++ gocAfter) + (AuxiliaryVars + [ Declaration (FindOrGiven LocalFind hName innerD) + , SuchThat + [ [essence| + (forAll (&fPat, &tPat) in &outLiteral . &f = &i <-> &h = &t) + /\ (!(exists (&gPat, &ePat) in &outLiteral . &g = &h) <-> &h = &i) + |] + ] + ] + ) + ) + else na "rule_Permute_Literal" + else return + ( "Horizontal rule for permutation application to a type the permutation doesn't care about" + , return + (Comprehension body $ gocBefore + ++ [Generator (GenInExpr pat [essence| &i |])] + ++ gocAfter) + ) theRule _ = na "rule_Permute_Literal" diff --git a/src/Conjure/Rules/Vertical/Permutation/AsFunction.hs b/src/Conjure/Rules/Vertical/Permutation/AsFunction.hs index cb184fe893..d43fa24c64 100644 --- a/src/Conjure/Rules/Vertical/Permutation/AsFunction.hs +++ b/src/Conjure/Rules/Vertical/Permutation/AsFunction.hs @@ -49,6 +49,38 @@ rule_Permute = "permutation-permute{AsFunction}" `namedRule` theRule where ) theRule _ = na "rule_Permute" + +rule_Permute_Comprehension :: Rule +rule_Permute_Comprehension = "permutation-permute{AsFunction}" `namedRule` theRule where + theRule (Comprehension body gensOrConds) = do + (gocBefore, (pat, p, i), gocAfter) <- matchFirst gensOrConds $ \ goc -> case goc of + Generator (GenInExpr pat [essence| permute(&p, &i) |]) -> return (pat, p, i) + _ -> na "rule_Comprehension" + + TypePermutation inner <- typeOf p + typeI <- typeOf i + if typeI `containsType` inner + then do + [f] <- downX1 p + if typesUnify [inner, typeI] + then return + ( "Vertical rule for permutation application to a single value" + , return + (Comprehension body $ gocBefore + ++ [Generator (GenInExpr pat + [essence| [&i, catchUndef(image(&f,&i),0)][toInt(&i in defined(&f))+1] |])] + ++ gocAfter) + ) + else na "rule_Permute" --If we hit this then we should hit a refinement error + else return + ( "Vertical rule for permutation application to a type the permutation doesn't care about" + , return + (Comprehension body $ gocBefore + ++ [Generator (GenInExpr pat [essence| &i |])] + ++ gocAfter) + ) + theRule _ = na "rule_Permute" + rule_Matrix_Permute :: Rule rule_Matrix_Permute = "matrix-permute" `namedRule` theRule where theRule [essence| permute(&perm, &y) |] = do @@ -78,14 +110,36 @@ rule_Matrix_Permute = "matrix-permute" `namedRule` theRule where theRule _ = na "rule_Matrix_Permute" ---rule_Permute_Set :: Rule ---rule_Permute_Set = "permutation-permute-set{AsFunction}" `namedRule` theRule where --- theRule [essence| permute(&p,&i) |] = do --- TypePermutation (TypeUnnamed nameperm) <- typeOf p --- TypeSet (TypeUnnamed nameset) <- i --- if nameperm == nameset --- then applyPermutationOverSet --- else na "rule_Permute_Set" --- theRule _ = na "rule_Permute_Set" --- ---applyPermutationOverSet = error "applyPermutationOverSet" +rule_Set_Permute :: Rule +rule_Set_Permute = "set-permute" `namedRule` theRule where + theRule (Comprehension body gensOrConds) = do + (gocBefore, (pat, perm, y), gocAfter) <- matchFirst gensOrConds $ \ goc -> case goc of + Generator (GenInExpr pat [essence| permute(&perm, &y) |]) -> return (pat, perm, y) + _ -> na "rule_Comprehension" + (TypeSet _) <- typeOf y + (TypePermutation _) <- typeOf perm + + ds <- domainOf y + return + ( "Horizontal rule for permute set" + , do + (dPat, d) <- quantifiedVar + (pyName, py) <- auxiliaryVar + return $ WithLocals + (Comprehension body $ gocBefore + ++ [Generator (GenInExpr pat [essence| &py |])] + ++ gocAfter) + (AuxiliaryVars + [ Declaration (FindOrGiven LocalFind pyName ds) + , SuchThat + [ [essence| + |&y| = |&py| + /\ forAll &dPat in &y . + permute(&perm, &d) in &py + |] + ] + ] + ) + ) + theRule _ = na "rule_Set_Permute" + diff --git a/src/Conjure/UI/Model.hs b/src/Conjure/UI/Model.hs index 4457b81491..09af2724dc 100644 --- a/src/Conjure/UI/Model.hs +++ b/src/Conjure/UI/Model.hs @@ -1182,6 +1182,8 @@ verticalRules = , Vertical.Permutation.AsFunction.rule_Permute_Comprehension_Tuples + , Vertical.Permutation.AsFunction.rule_Set_Permute + , Vertical.Permutation.AsFunction.rule_Matrix_Permute @@ -1311,6 +1313,7 @@ horizontalRules = , Horizontal.Partition.rule_In , Horizontal.Permutation.rule_Permute_Literal + , Horizontal.Permutation.rule_Permute_Literal_Comprehension , Horizontal.Permutation.rule_Apply @@ -1388,7 +1391,10 @@ delayedRules = , Vertical.Matrix.rule_Concatenate_Singleton , Vertical.Matrix.rule_MatrixIndexing +-- , Horizontal.Permutation.rule_Permute_Literal +-- , Horizontal.Permutation.rule_Permute_Literal_Comprehension , Vertical.Permutation.AsFunction.rule_Permute + , Vertical.Permutation.AsFunction.rule_Permute_Comprehension ] , [ rule_ReducerToComprehension ] diff --git a/tests/custom/permutations/basic/28/permutation.essence b/tests/custom/permutations/basic/28/permutation.essence index 25557ec986..af1c2a6d96 100644 --- a/tests/custom/permutations/basic/28/permutation.essence +++ b/tests/custom/permutations/basic/28/permutation.essence @@ -8,5 +8,6 @@ find y : set (size 4) of MYTYPE such that - y = permute(p,x) + y = permute(p,x) + /\ y != x diff --git a/tests/custom/permutations/basic/28/stdout.expected b/tests/custom/permutations/basic/28/stdout.expected index b7d1e6e137..77d313faaa 100644 --- a/tests/custom/permutations/basic/28/stdout.expected +++ b/tests/custom/permutations/basic/28/stdout.expected @@ -4,26 +4,11 @@ Saved under: conjure-output Savile Row: model000001.eprime Copying solution to: permutation-000001.solution Copying solution to: permutation-000002.solution -Copying solution to: permutation-000003.solution -Copying solution to: permutation-000004.solution -Copying solution to: permutation-000005.solution -language Essence 1.3 - -letting x be {THING2, THING3, THING4, THING5} -letting y be {THING2, THING3, THING4, THING5} -language Essence 1.3 - -letting x be {THING1, THING3, THING4, THING5} -letting y be {THING1, THING3, THING4, THING5} language Essence 1.3 letting x be {THING1, THING2, THING4, THING5} -letting y be {THING1, THING2, THING4, THING5} -language Essence 1.3 - -letting x be {THING1, THING2, THING3, THING5} letting y be {THING1, THING2, THING3, THING5} language Essence 1.3 -letting x be {THING1, THING2, THING3, THING4} -letting y be {THING1, THING2, THING3, THING4} +letting x be {THING1, THING2, THING3, THING5} +letting y be {THING1, THING2, THING4, THING5} From 91f29dddb0fbabacd27b40427840b9f0749af772 Mon Sep 17 00:00:00 2001 From: Fraser Dunlop Date: Tue, 6 Nov 2018 11:49:08 +0000 Subject: [PATCH 015/229] set/matrix permute inner type unify traps --- .../Rules/Vertical/Permutation/AsFunction.hs | 107 ++++++++++-------- 1 file changed, 59 insertions(+), 48 deletions(-) diff --git a/src/Conjure/Rules/Vertical/Permutation/AsFunction.hs b/src/Conjure/Rules/Vertical/Permutation/AsFunction.hs index d43fa24c64..7abcda2da5 100644 --- a/src/Conjure/Rules/Vertical/Permutation/AsFunction.hs +++ b/src/Conjure/Rules/Vertical/Permutation/AsFunction.hs @@ -71,7 +71,7 @@ rule_Permute_Comprehension = "permutation-permute{AsFunction}" `namedRule` theRu [essence| [&i, catchUndef(image(&f,&i),0)][toInt(&i in defined(&f))+1] |])] ++ gocAfter) ) - else na "rule_Permute" --If we hit this then we should hit a refinement error + else na "rule_Permute" else return ( "Vertical rule for permutation application to a type the permutation doesn't care about" , return @@ -85,28 +85,31 @@ rule_Matrix_Permute :: Rule rule_Matrix_Permute = "matrix-permute" `namedRule` theRule where theRule [essence| permute(&perm, &y) |] = do ty@(TypeMatrix _ _) <- typeOf y - (TypePermutation _) <- typeOf perm - unless (isPrimitiveType ty) $ fail ("not a primitive type:" <+> pretty ty) - y' <- flattenIfNeeded y - dm@(DomainMatrix dyindex _) <- domainOf y' - return - ( "Horizontal rule for permute matrix" - , do - (dPat, d) <- quantifiedVar - (pyName, py) <- auxiliaryVar - return $ WithLocals - [essence| &py |] - (AuxiliaryVars - [ Declaration (FindOrGiven LocalFind pyName dm) - , SuchThat - [ [essence| - forAll &dPat : &dyindex . - &py[&d] = permute(&perm,&y'[permute(&perm,&d)]) - |] - ] - ] - ) - ) + (TypePermutation inn) <- typeOf perm + if not $ typesUnify [ty, inn] + then do + unless (isPrimitiveType ty) $ fail ("not a primitive type:" <+> pretty ty) + y' <- flattenIfNeeded y + dm@(DomainMatrix dyindex _) <- domainOf y' + return + ( "Horizontal rule for permute matrix" + , do + (dPat, d) <- quantifiedVar + (pyName, py) <- auxiliaryVar + return $ WithLocals + [essence| &py |] + (AuxiliaryVars + [ Declaration (FindOrGiven LocalFind pyName dm) + , SuchThat + [ [essence| + forAll &dPat : &dyindex . + &py[&d] = permute(&perm,&y'[permute(&perm,&d)]) + |] + ] + ] + ) + ) + else na "rule_Matrix_Permute" theRule _ = na "rule_Matrix_Permute" @@ -116,30 +119,38 @@ rule_Set_Permute = "set-permute" `namedRule` theRule where (gocBefore, (pat, perm, y), gocAfter) <- matchFirst gensOrConds $ \ goc -> case goc of Generator (GenInExpr pat [essence| permute(&perm, &y) |]) -> return (pat, perm, y) _ -> na "rule_Comprehension" - (TypeSet _) <- typeOf y - (TypePermutation _) <- typeOf perm - - ds <- domainOf y - return - ( "Horizontal rule for permute set" - , do - (dPat, d) <- quantifiedVar - (pyName, py) <- auxiliaryVar - return $ WithLocals - (Comprehension body $ gocBefore - ++ [Generator (GenInExpr pat [essence| &py |])] - ++ gocAfter) - (AuxiliaryVars - [ Declaration (FindOrGiven LocalFind pyName ds) - , SuchThat - [ [essence| - |&y| = |&py| - /\ forAll &dPat in &y . - permute(&perm, &d) in &py - |] - ] - ] - ) - ) + ts@(TypeSet _) <- typeOf y + (TypePermutation inn) <- typeOf perm + if not $ typesUnify [ts, inn] + then do + ds <- domainOf y + return + ( "Horizontal rule for permute set" + , do + (dPat, d) <- quantifiedVar + (pyName, py) <- auxiliaryVar + return $ WithLocals + (Comprehension body $ gocBefore + ++ [Generator (GenInExpr pat [essence| &py |])] + ++ gocAfter) + (AuxiliaryVars + [ Declaration (FindOrGiven LocalFind pyName ds) + , SuchThat + [ [essence| + |&y| = |&py| + /\ forAll &dPat in &y . + permute(&perm, &d) in &py + |] + ] + ] + ) + ) + else na "rule_Set_Permute" theRule _ = na "rule_Set_Permute" + +--rule_Function_Permute :: Rule +--rule_Relation_Permute :: Rule +--rule_Partition_Permute :: Rule +--rule_MSet_Permute :: Rule +--rule_Sequence_Permute :: Rule From 65f43f529e32739a39fd3b3bbdb80698d015c26b Mon Sep 17 00:00:00 2001 From: Fraser Dunlop Date: Tue, 6 Nov 2018 16:27:47 +0000 Subject: [PATCH 016/229] Trying to track down strange refinement error permute relation --- src/Conjure/Rules/Horizontal/Permutation.hs | 3 + .../Rules/Vertical/Permutation/AsFunction.hs | 220 +++++++++++++++--- src/Conjure/UI/Model.hs | 9 +- .../permutations/basic/29/permutation.essence | 13 ++ tests/custom/permutations/basic/29/run.sh | 3 + .../permutations/basic/29/stdout.expected | 14 ++ 6 files changed, 234 insertions(+), 28 deletions(-) create mode 100644 tests/custom/permutations/basic/29/permutation.essence create mode 100755 tests/custom/permutations/basic/29/run.sh create mode 100644 tests/custom/permutations/basic/29/stdout.expected diff --git a/src/Conjure/Rules/Horizontal/Permutation.hs b/src/Conjure/Rules/Horizontal/Permutation.hs index d2df51c8a9..525d69d704 100644 --- a/src/Conjure/Rules/Horizontal/Permutation.hs +++ b/src/Conjure/Rules/Horizontal/Permutation.hs @@ -24,7 +24,9 @@ rule_Permute_Literal :: Rule rule_Permute_Literal = "permutation-permute-literal{AsFunction}" `namedRule` theRule where theRule [essence| permute(&p, &i) |] = do (TypePermutation inner, elems) <- match permutationLiteral p + case i of WithLocals{} -> na "bubble-delay" ; _ -> return () typeI <- typeOf i +-- traceM $ show typeI if typeI `containsType` inner then do if typesUnify [inner, typeI] @@ -74,6 +76,7 @@ rule_Permute_Literal_Comprehension = "permutation-permute-literal-comprehension{ (gocBefore, (pat, p, i), gocAfter) <- matchFirst gensOrConds $ \ goc -> case goc of Generator (GenInExpr pat [essence| permute(&p, &i) |]) -> return (pat, p, i) _ -> na "rule_Comprehension" + case i of WithLocals{} -> na "bubble-delay" ; _ -> return () (TypePermutation inner, elems) <- match permutationLiteral p typeI <- typeOf i if typeI `containsType` inner diff --git a/src/Conjure/Rules/Vertical/Permutation/AsFunction.hs b/src/Conjure/Rules/Vertical/Permutation/AsFunction.hs index 7abcda2da5..55f8adcd77 100644 --- a/src/Conjure/Rules/Vertical/Permutation/AsFunction.hs +++ b/src/Conjure/Rules/Vertical/Permutation/AsFunction.hs @@ -84,41 +84,76 @@ rule_Permute_Comprehension = "permutation-permute{AsFunction}" `namedRule` theRu rule_Matrix_Permute :: Rule rule_Matrix_Permute = "matrix-permute" `namedRule` theRule where theRule [essence| permute(&perm, &y) |] = do - ty@(TypeMatrix _ _) <- typeOf y - (TypePermutation inn) <- typeOf perm - if not $ typesUnify [ty, inn] - then do - unless (isPrimitiveType ty) $ fail ("not a primitive type:" <+> pretty ty) - y' <- flattenIfNeeded y - dm@(DomainMatrix dyindex _) <- domainOf y' - return - ( "Horizontal rule for permute matrix" - , do - (dPat, d) <- quantifiedVar - (pyName, py) <- auxiliaryVar - return $ WithLocals - [essence| &py |] - (AuxiliaryVars - [ Declaration (FindOrGiven LocalFind pyName dm) - , SuchThat - [ [essence| - forAll &dPat : &dyindex . - &py[&d] = permute(&perm,&y'[permute(&perm,&d)]) - |] - ] + ty@(TypeMatrix _ _) <- typeOf y + (TypePermutation inn) <- typeOf perm + if not $ typesUnify [ty, inn] + then do + unless (isPrimitiveType ty) $ fail ("not a primitive type:" <+> pretty ty) + y' <- flattenIfNeeded y + dm@(DomainMatrix dyindex _) <- domainOf y' + return + ( "Horizontal rule for permute matrix" + , do + (dPat, d) <- quantifiedVar + (pyName, py) <- auxiliaryVar + return $ WithLocals + [essence| &py |] + (AuxiliaryVars + [ Declaration (FindOrGiven LocalFind pyName dm) + , SuchThat + [ [essence| + forAll &dPat : &dyindex . + &py[permute(&perm,&d)] = permute(&perm,&y'[&d]) + |] ] - ) - ) - else na "rule_Matrix_Permute" + ] + ) + ) + else na "rule_Matrix_Permute" theRule _ = na "rule_Matrix_Permute" +rule_Matrix_Permute_Comprehension :: Rule +rule_Matrix_Permute_Comprehension = "matrix-permute-comprehension" `namedRule` theRule where + theRule (Comprehension body gensOrConds) = do + (gocBefore, (pat, perm, y), gocAfter) <- matchFirst gensOrConds $ \ goc -> case goc of + Generator (GenInExpr pat [essence| permute(&perm, &y) |]) -> return (pat, perm, y) + _ -> na "rule_Matrix_Permute" + ty@(TypeMatrix _ _) <- typeOf y + (TypePermutation inn) <- typeOf perm + if not $ typesUnify [ty, inn] + then do + unless (isPrimitiveType ty) $ fail ("not a primitive type:" <+> pretty ty) + y' <- flattenIfNeeded y + dm@(DomainMatrix dyindex _) <- domainOf y' + return + ( "Horizontal rule for permute matrix in comprehension" + , do + (dPat, d) <- quantifiedVar + (pyName, py) <- auxiliaryVar + return $ WithLocals + (Comprehension body $ gocBefore + ++ [Generator (GenInExpr pat [essence| &py |])] + ++ gocAfter) + (AuxiliaryVars + [ Declaration (FindOrGiven LocalFind pyName dm) + , SuchThat + [ [essence| + forAll &dPat : &dyindex . + &py[permute(&perm,&d)] = permute(&perm,&y'[&d]) + |] + ] + ] + ) + ) + else na "rule_Matrix_Permute_Comprehension" + theRule _ = na "rule_Matrix_Permute_Comprehension" rule_Set_Permute :: Rule rule_Set_Permute = "set-permute" `namedRule` theRule where theRule (Comprehension body gensOrConds) = do (gocBefore, (pat, perm, y), gocAfter) <- matchFirst gensOrConds $ \ goc -> case goc of Generator (GenInExpr pat [essence| permute(&perm, &y) |]) -> return (pat, perm, y) - _ -> na "rule_Comprehension" + _ -> na "rule_Set_Permute" ts@(TypeSet _) <- typeOf y (TypePermutation inn) <- typeOf perm if not $ typesUnify [ts, inn] @@ -149,8 +184,139 @@ rule_Set_Permute = "set-permute" `namedRule` theRule where theRule _ = na "rule_Set_Permute" +rule_Relation_Permute :: Rule +rule_Relation_Permute = "relation-permute" `namedRule` theRule where + theRule [essence| permute(&perm, &y) |] = do + case y of WithLocals{} -> na "bubble-delay" ; _ -> return () + ts@(TypeRelation _) <- typeOf y + (TypePermutation inn) <- typeOf perm + if not $ typesUnify [ts, inn] + then do + ds <- domainOf y + return + ( "Horizontal rule for permute relation in comprehension" + , do + (dPat, d) <- quantifiedVar + (pyName, py) <- auxiliaryVar + return $ WithLocals + [essence| &py |] + (AuxiliaryVars + [ Declaration (FindOrGiven LocalFind pyName ds) + , SuchThat + [ [essence| + |&y| = |&py| + /\ and([permute(&perm, &d) in &py | &dPat <- &y]) + + |] + ] + ] + ) + ) + else na "rule_Relation_Permute" + theRule _ = na "rule_Relation_Permute" + +rule_Relation_Permute_Comprehension :: Rule +rule_Relation_Permute_Comprehension = "relation-permute-comprehension" `namedRule` theRule where + theRule (Comprehension body gensOrConds) = do + (gocBefore, (pat, perm, y), gocAfter) <- matchFirst gensOrConds $ \ goc -> case goc of + Generator (GenInExpr pat [essence| permute(&perm, &y) |]) -> return (pat, perm, y) + _ -> na "rule_Relation_Permute_Comprehension" + case y of WithLocals{} -> na "bubble-delay" ; _ -> return () + ts@(TypeRelation _) <- typeOf y + (TypePermutation inn) <- typeOf perm + if not $ typesUnify [ts, inn] + then do + ds <- domainOf y + return + ( "Horizontal rule for permute relation in comprehension" + , do + (dPat, d) <- quantifiedVar + (pyName, py) <- auxiliaryVar + return $ WithLocals + (Comprehension body $ gocBefore + ++ [Generator (GenInExpr pat [essence| &py |])] + ++ gocAfter) + (AuxiliaryVars + [ Declaration (FindOrGiven LocalFind pyName ds) + , SuchThat + [ [essence| + |&y| = |&py| + /\ and([permute(&perm, &d) in &py | &dPat <- &y]) + |] + ] + ] + ) + ) + else na "rule_Relation_Permute_Comprehension" + theRule _ = na "rule_Relation_Permute_Comprehension" + + +rule_Tuple_Permute :: Rule +rule_Tuple_Permute = "tuple-permute" `namedRule` theRule where + theRule [essence| permute(&perm, &y) |] = do + case y of WithLocals{} -> na "bubble-delay" ; _ -> return () + ty' <- typeOf y +-- traceM $ "rule_Tuple_Permute: " ++ show ty' + ty@(TypeTuple it) <- typeOf y + (TypePermutation inn) <- typeOf perm + if not $ typesUnify [ty, inn] + then do +-- traceM $ "rule_Tuple_Permute: applying" + dm <- domainOf y + return + ( "Horizontal rule for permute tuple in comprehension" + , do + (pyName, py) <- auxiliaryVar + return $ WithLocals + [essence| &py |] + (AuxiliaryVars $ + [ Declaration (FindOrGiven LocalFind pyName dm)] + ++ ((\x -> let d = Constant $ ConstantInt NoTag x + in SuchThat [[essence| &py[&d] = permute(&perm,&y[&d]) |] ]) + <$> [1..(genericLength it)]) + + + ) + ) + else na "rule_Tuple_Permute" + theRule _ = na "rule_Tuple_Permute" + +rule_Tuple_Permute_Comprehension :: Rule +rule_Tuple_Permute_Comprehension = "tuple-permute-comprehension" `namedRule` theRule where + theRule (Comprehension body gensOrConds) = do + (gocBefore, (pat, perm, y), gocAfter) <- matchFirst gensOrConds $ \ goc -> case goc of + Generator (GenInExpr pat [essence| permute(&perm, &y) |]) -> return (pat, perm, y) + _ -> na "rule_Tuple_Permute" + case y of WithLocals{} -> na "bubble-delay" ; _ -> return () + ty' <- typeOf y +-- traceM $ "rule_Tuple_Permute_Comprehension: " ++ show ty' + ty@(TypeTuple it) <- typeOf y + (TypePermutation inn) <- typeOf perm + if not $ typesUnify [ty, inn] + then do +-- traceM $ "rule_Tuple_Permute_Comprehension: applying" + dm <- domainOf y + return + ( "Horizontal rule for permute tuple in comprehension" + , do + (pyName, py) <- auxiliaryVar + return $ WithLocals + (Comprehension body $ gocBefore + ++ [Generator (GenInExpr pat [essence| &py |])] + ++ gocAfter) + (AuxiliaryVars $ + [ Declaration (FindOrGiven LocalFind pyName dm)] + ++ ((\x -> let d = Constant $ ConstantInt NoTag x + in SuchThat [[essence| &py[&d] = permute(&perm,&y[&d]) |] ]) + <$> [1..(genericLength it)]) + ) + ) + else na "rule_Tuple_Permute_Comprehension" + theRule _ = na "rule_Tuple_Permute_Comprehension" + + + --rule_Function_Permute :: Rule ---rule_Relation_Permute :: Rule --rule_Partition_Permute :: Rule --rule_MSet_Permute :: Rule --rule_Sequence_Permute :: Rule diff --git a/src/Conjure/UI/Model.hs b/src/Conjure/UI/Model.hs index 09af2724dc..f1405f0c50 100644 --- a/src/Conjure/UI/Model.hs +++ b/src/Conjure/UI/Model.hs @@ -1182,9 +1182,15 @@ verticalRules = , Vertical.Permutation.AsFunction.rule_Permute_Comprehension_Tuples + , Vertical.Permutation.AsFunction.rule_Relation_Permute + , Vertical.Permutation.AsFunction.rule_Relation_Permute_Comprehension , Vertical.Permutation.AsFunction.rule_Set_Permute - + , Vertical.Permutation.AsFunction.rule_Tuple_Permute + , Vertical.Permutation.AsFunction.rule_Tuple_Permute_Comprehension , Vertical.Permutation.AsFunction.rule_Matrix_Permute + , Vertical.Permutation.AsFunction.rule_Matrix_Permute_Comprehension + + ] @@ -1312,6 +1318,7 @@ horizontalRules = , Horizontal.Partition.rule_Card , Horizontal.Partition.rule_In + , Horizontal.Permutation.rule_Permute_Literal , Horizontal.Permutation.rule_Permute_Literal_Comprehension , Horizontal.Permutation.rule_Apply diff --git a/tests/custom/permutations/basic/29/permutation.essence b/tests/custom/permutations/basic/29/permutation.essence new file mode 100644 index 0000000000..5b00bf961b --- /dev/null +++ b/tests/custom/permutations/basic/29/permutation.essence @@ -0,0 +1,13 @@ +letting MYTYPE be new type enum {THING1, THING2, THING3, THING4, THING5} + +letting p be permutation ((THING3,THING4)) + +find x : relation (size 4) of (MYTYPE*MYTYPE) + +find y : relation (size 4) of (MYTYPE*MYTYPE) + + +such that + y = permute(p,x) +$ /\ y != x + diff --git a/tests/custom/permutations/basic/29/run.sh b/tests/custom/permutations/basic/29/run.sh new file mode 100755 index 0000000000..a440de2e64 --- /dev/null +++ b/tests/custom/permutations/basic/29/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence --number-of-solutions=20 +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/basic/29/stdout.expected b/tests/custom/permutations/basic/29/stdout.expected new file mode 100644 index 0000000000..77d313faaa --- /dev/null +++ b/tests/custom/permutations/basic/29/stdout.expected @@ -0,0 +1,14 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Copying solution to: permutation-000001.solution +Copying solution to: permutation-000002.solution +language Essence 1.3 + +letting x be {THING1, THING2, THING4, THING5} +letting y be {THING1, THING2, THING3, THING5} +language Essence 1.3 + +letting x be {THING1, THING2, THING3, THING5} +letting y be {THING1, THING2, THING4, THING5} From 52ad5b0c890dbc2109ab93e005765af918118c82 Mon Sep 17 00:00:00 2001 From: Fraser Dunlop Date: Mon, 12 Nov 2018 13:10:27 +0000 Subject: [PATCH 017/229] Merge in permutation-safe to stack.yamls --- etc/hs-deps/stack-8.0.yaml | 2 ++ etc/hs-deps/stack-8.2.yaml | 2 ++ etc/hs-deps/stack-8.4.yaml | 3 ++- 3 files changed, 6 insertions(+), 1 deletion(-) diff --git a/etc/hs-deps/stack-8.0.yaml b/etc/hs-deps/stack-8.0.yaml index 50f9d6ab25..523c701942 100644 --- a/etc/hs-deps/stack-8.0.yaml +++ b/etc/hs-deps/stack-8.0.yaml @@ -12,3 +12,5 @@ extra-deps: - tasty-1.1.0.1 - tasty-ant-xml-1.1.4 - optparse-applicative-0.14.2.0 +- git: git@github.com:fraser-dunlop/permutation-safe.git + commit: 8b0f5afe8d5262df70860aeab456596fe19cf512 diff --git a/etc/hs-deps/stack-8.2.yaml b/etc/hs-deps/stack-8.2.yaml index 424df2b619..ed187a1b27 100644 --- a/etc/hs-deps/stack-8.2.yaml +++ b/etc/hs-deps/stack-8.2.yaml @@ -8,3 +8,5 @@ extra-deps: - transformers-0.5.5.0 - tasty-1.1.0.1 - tasty-ant-xml-1.1.4 +- git: git@github.com:fraser-dunlop/permutation-safe.git + commit: 8b0f5afe8d5262df70860aeab456596fe19cf512 diff --git a/etc/hs-deps/stack-8.4.yaml b/etc/hs-deps/stack-8.4.yaml index 85728ea8b2..bdccaa1ed2 100644 --- a/etc/hs-deps/stack-8.4.yaml +++ b/etc/hs-deps/stack-8.4.yaml @@ -7,4 +7,5 @@ extra-deps: - megaparsec-4.4.0 - tasty-1.1.0.1 - tasty-ant-xml-1.1.4 -- git: https://github.com/fraser-dunlop/permutation-safe +- git: git@github.com:fraser-dunlop/permutation-safe.git + commit: 8b0f5afe8d5262df70860aeab456596fe19cf512 From d763f0d923767fa04dea829f9cbf36f0b42309a5 Mon Sep 17 00:00:00 2001 From: Fraser Dunlop Date: Thu, 15 Nov 2018 14:13:03 +0000 Subject: [PATCH 018/229] Removed expected stdout --- src/Conjure/UI/Model.hs | 24 +++++++++---------- .../permutations/basic/29/stdout.expected | 14 ----------- 2 files changed, 11 insertions(+), 27 deletions(-) delete mode 100644 tests/custom/permutations/basic/29/stdout.expected diff --git a/src/Conjure/UI/Model.hs b/src/Conjure/UI/Model.hs index a16e1e8587..8768262af8 100644 --- a/src/Conjure/UI/Model.hs +++ b/src/Conjure/UI/Model.hs @@ -1077,7 +1077,17 @@ paramRules = verticalRules :: [Rule] verticalRules = - [ Vertical.Tuple.rule_Tuple_Eq + [ + Vertical.Permutation.AsFunction.rule_Permute_Comprehension_Tuples + , Vertical.Permutation.AsFunction.rule_Relation_Permute + , Vertical.Permutation.AsFunction.rule_Relation_Permute_Comprehension + , Vertical.Permutation.AsFunction.rule_Set_Permute + , Vertical.Permutation.AsFunction.rule_Tuple_Permute + , Vertical.Permutation.AsFunction.rule_Tuple_Permute_Comprehension + , Vertical.Permutation.AsFunction.rule_Matrix_Permute + , Vertical.Permutation.AsFunction.rule_Matrix_Permute_Comprehension + + , Vertical.Tuple.rule_Tuple_Eq , Vertical.Tuple.rule_Tuple_Neq , Vertical.Tuple.rule_Tuple_Leq , Vertical.Tuple.rule_Tuple_Lt @@ -1183,18 +1193,6 @@ verticalRules = , Vertical.Partition.Occurrence.rule_Comprehension - , Vertical.Permutation.AsFunction.rule_Permute_Comprehension_Tuples - , Vertical.Permutation.AsFunction.rule_Relation_Permute - , Vertical.Permutation.AsFunction.rule_Relation_Permute_Comprehension - , Vertical.Permutation.AsFunction.rule_Set_Permute - , Vertical.Permutation.AsFunction.rule_Tuple_Permute - , Vertical.Permutation.AsFunction.rule_Tuple_Permute_Comprehension - , Vertical.Permutation.AsFunction.rule_Matrix_Permute - , Vertical.Permutation.AsFunction.rule_Matrix_Permute_Comprehension - - - - ] horizontalRules :: [Rule] diff --git a/tests/custom/permutations/basic/29/stdout.expected b/tests/custom/permutations/basic/29/stdout.expected deleted file mode 100644 index 77d313faaa..0000000000 --- a/tests/custom/permutations/basic/29/stdout.expected +++ /dev/null @@ -1,14 +0,0 @@ -Generating models for permutation.essence -Generated models: model000001.eprime -Saved under: conjure-output -Savile Row: model000001.eprime -Copying solution to: permutation-000001.solution -Copying solution to: permutation-000002.solution -language Essence 1.3 - -letting x be {THING1, THING2, THING4, THING5} -letting y be {THING1, THING2, THING3, THING5} -language Essence 1.3 - -letting x be {THING1, THING2, THING3, THING5} -letting y be {THING1, THING2, THING4, THING5} From e75acd89cef3b62699b87e19b6edfd9c57ff17d7 Mon Sep 17 00:00:00 2001 From: Fraser Dunlop Date: Mon, 19 Nov 2018 10:26:25 +0000 Subject: [PATCH 019/229] Some unnamed tests --- src/Conjure/UI/Model.hs | 24 +- .../permutations/basic/30/permutation.essence | 8 + .../permutations/basic/30/permutation.param | 1 + tests/custom/permutations/basic/30/run.sh | 3 + .../permutations/basic/31/permutation.essence | 13 + .../permutations/basic/31/permutation.param | 1 + tests/custom/permutations/basic/31/run.sh | 3 + .../permutations/basic/32/permutation.essence | 9 + .../permutations/basic/32/permutation.param | 1 + tests/custom/permutations/basic/32/run.sh | 3 + .../permutations/basic/33/permutation.essence | 11 + .../permutations/basic/33/permutation.param | 1 + tests/custom/permutations/basic/33/run.sh | 3 + .../permutations/basic/33/stdout.expected | 284 ++++++++++++++++++ .../permutations/basic/34/permutation.essence | 6 + .../permutations/basic/34/permutation.param | 1 + tests/custom/permutations/basic/34/run.sh | 3 + .../permutations/basic/35/permutation.essence | 23 ++ .../permutations/basic/35/permutation.param | 1 + tests/custom/permutations/basic/35/run.sh | 3 + 20 files changed, 391 insertions(+), 11 deletions(-) create mode 100644 tests/custom/permutations/basic/30/permutation.essence create mode 100644 tests/custom/permutations/basic/30/permutation.param create mode 100755 tests/custom/permutations/basic/30/run.sh create mode 100644 tests/custom/permutations/basic/31/permutation.essence create mode 100644 tests/custom/permutations/basic/31/permutation.param create mode 100755 tests/custom/permutations/basic/31/run.sh create mode 100644 tests/custom/permutations/basic/32/permutation.essence create mode 100644 tests/custom/permutations/basic/32/permutation.param create mode 100755 tests/custom/permutations/basic/32/run.sh create mode 100644 tests/custom/permutations/basic/33/permutation.essence create mode 100644 tests/custom/permutations/basic/33/permutation.param create mode 100755 tests/custom/permutations/basic/33/run.sh create mode 100644 tests/custom/permutations/basic/33/stdout.expected create mode 100644 tests/custom/permutations/basic/34/permutation.essence create mode 100644 tests/custom/permutations/basic/34/permutation.param create mode 100755 tests/custom/permutations/basic/34/run.sh create mode 100644 tests/custom/permutations/basic/35/permutation.essence create mode 100644 tests/custom/permutations/basic/35/permutation.param create mode 100755 tests/custom/permutations/basic/35/run.sh diff --git a/src/Conjure/UI/Model.hs b/src/Conjure/UI/Model.hs index 8768262af8..a16e1e8587 100644 --- a/src/Conjure/UI/Model.hs +++ b/src/Conjure/UI/Model.hs @@ -1077,17 +1077,7 @@ paramRules = verticalRules :: [Rule] verticalRules = - [ - Vertical.Permutation.AsFunction.rule_Permute_Comprehension_Tuples - , Vertical.Permutation.AsFunction.rule_Relation_Permute - , Vertical.Permutation.AsFunction.rule_Relation_Permute_Comprehension - , Vertical.Permutation.AsFunction.rule_Set_Permute - , Vertical.Permutation.AsFunction.rule_Tuple_Permute - , Vertical.Permutation.AsFunction.rule_Tuple_Permute_Comprehension - , Vertical.Permutation.AsFunction.rule_Matrix_Permute - , Vertical.Permutation.AsFunction.rule_Matrix_Permute_Comprehension - - , Vertical.Tuple.rule_Tuple_Eq + [ Vertical.Tuple.rule_Tuple_Eq , Vertical.Tuple.rule_Tuple_Neq , Vertical.Tuple.rule_Tuple_Leq , Vertical.Tuple.rule_Tuple_Lt @@ -1193,6 +1183,18 @@ verticalRules = , Vertical.Partition.Occurrence.rule_Comprehension + , Vertical.Permutation.AsFunction.rule_Permute_Comprehension_Tuples + , Vertical.Permutation.AsFunction.rule_Relation_Permute + , Vertical.Permutation.AsFunction.rule_Relation_Permute_Comprehension + , Vertical.Permutation.AsFunction.rule_Set_Permute + , Vertical.Permutation.AsFunction.rule_Tuple_Permute + , Vertical.Permutation.AsFunction.rule_Tuple_Permute_Comprehension + , Vertical.Permutation.AsFunction.rule_Matrix_Permute + , Vertical.Permutation.AsFunction.rule_Matrix_Permute_Comprehension + + + + ] horizontalRules :: [Rule] diff --git a/tests/custom/permutations/basic/30/permutation.essence b/tests/custom/permutations/basic/30/permutation.essence new file mode 100644 index 0000000000..15c38c1a52 --- /dev/null +++ b/tests/custom/permutations/basic/30/permutation.essence @@ -0,0 +1,8 @@ +letting n be 4 + +given p : permutation of int(1..n) + +find s : permutation of int(1..n) + +such that + p = s diff --git a/tests/custom/permutations/basic/30/permutation.param b/tests/custom/permutations/basic/30/permutation.param new file mode 100644 index 0000000000..220d828501 --- /dev/null +++ b/tests/custom/permutations/basic/30/permutation.param @@ -0,0 +1 @@ +letting p be permutation((1,2)) diff --git a/tests/custom/permutations/basic/30/run.sh b/tests/custom/permutations/basic/30/run.sh new file mode 100755 index 0000000000..98ec8c2243 --- /dev/null +++ b/tests/custom/permutations/basic/30/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence *.param --number-of-solutions=20 +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/basic/31/permutation.essence b/tests/custom/permutations/basic/31/permutation.essence new file mode 100644 index 0000000000..e6c5883f97 --- /dev/null +++ b/tests/custom/permutations/basic/31/permutation.essence @@ -0,0 +1,13 @@ +find m : +matrix +indexed +by [int(1..9)] +of +set of +int(1) + + + +such that + forAll i, j : int(1..9) . + i != j -> m <=lex [m[permute(permutation((i,j)),k)] | k : int(1..9)] diff --git a/tests/custom/permutations/basic/31/permutation.param b/tests/custom/permutations/basic/31/permutation.param new file mode 100644 index 0000000000..220d828501 --- /dev/null +++ b/tests/custom/permutations/basic/31/permutation.param @@ -0,0 +1 @@ +letting p be permutation((1,2)) diff --git a/tests/custom/permutations/basic/31/run.sh b/tests/custom/permutations/basic/31/run.sh new file mode 100755 index 0000000000..a440de2e64 --- /dev/null +++ b/tests/custom/permutations/basic/31/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence --number-of-solutions=20 +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/basic/32/permutation.essence b/tests/custom/permutations/basic/32/permutation.essence new file mode 100644 index 0000000000..0cf273c710 --- /dev/null +++ b/tests/custom/permutations/basic/32/permutation.essence @@ -0,0 +1,9 @@ +given n : int + +find x : set of int(1..n) + +find y : set of int(1..n) + +such that + forAll i, j : int(1..n) . + i != j -> (x,y) .<= permute(permutation((i,j)), (x,y)) diff --git a/tests/custom/permutations/basic/32/permutation.param b/tests/custom/permutations/basic/32/permutation.param new file mode 100644 index 0000000000..3c551dae32 --- /dev/null +++ b/tests/custom/permutations/basic/32/permutation.param @@ -0,0 +1 @@ +letting n be 3 diff --git a/tests/custom/permutations/basic/32/run.sh b/tests/custom/permutations/basic/32/run.sh new file mode 100755 index 0000000000..98ec8c2243 --- /dev/null +++ b/tests/custom/permutations/basic/32/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence *.param --number-of-solutions=20 +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/basic/33/permutation.essence b/tests/custom/permutations/basic/33/permutation.essence new file mode 100644 index 0000000000..21cbd871d8 --- /dev/null +++ b/tests/custom/permutations/basic/33/permutation.essence @@ -0,0 +1,11 @@ +given n : int + +letting MYTYPE be new type enum {THING1, THING2} + +find x : matrix indexed by [int(1..n)] of MYTYPE + +find y : matrix indexed by [int(1..n)] of MYTYPE + +such that + forAll i, j : int(1..n) . + i != j -> tuple(x,y) .<= permute(permutation((i,j)),tuple(x,y)) diff --git a/tests/custom/permutations/basic/33/permutation.param b/tests/custom/permutations/basic/33/permutation.param new file mode 100644 index 0000000000..05cd66931a --- /dev/null +++ b/tests/custom/permutations/basic/33/permutation.param @@ -0,0 +1 @@ +letting n be 5 diff --git a/tests/custom/permutations/basic/33/run.sh b/tests/custom/permutations/basic/33/run.sh new file mode 100755 index 0000000000..1f1c63f942 --- /dev/null +++ b/tests/custom/permutations/basic/33/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence *.param --number-of-solutions=60 +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/basic/33/stdout.expected b/tests/custom/permutations/basic/33/stdout.expected new file mode 100644 index 0000000000..6f8d4866b7 --- /dev/null +++ b/tests/custom/permutations/basic/33/stdout.expected @@ -0,0 +1,284 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime permutation.param +Copying solution to: permutation-permutation-000001.solution +Copying solution to: permutation-permutation-000002.solution +Copying solution to: permutation-permutation-000003.solution +Copying solution to: permutation-permutation-000004.solution +Copying solution to: permutation-permutation-000005.solution +Copying solution to: permutation-permutation-000006.solution +Copying solution to: permutation-permutation-000007.solution +Copying solution to: permutation-permutation-000008.solution +Copying solution to: permutation-permutation-000009.solution +Copying solution to: permutation-permutation-000010.solution +Copying solution to: permutation-permutation-000011.solution +Copying solution to: permutation-permutation-000012.solution +Copying solution to: permutation-permutation-000013.solution +Copying solution to: permutation-permutation-000014.solution +Copying solution to: permutation-permutation-000015.solution +Copying solution to: permutation-permutation-000016.solution +Copying solution to: permutation-permutation-000017.solution +Copying solution to: permutation-permutation-000018.solution +Copying solution to: permutation-permutation-000019.solution +Copying solution to: permutation-permutation-000020.solution +Copying solution to: permutation-permutation-000021.solution +Copying solution to: permutation-permutation-000022.solution +Copying solution to: permutation-permutation-000023.solution +Copying solution to: permutation-permutation-000024.solution +Copying solution to: permutation-permutation-000025.solution +Copying solution to: permutation-permutation-000026.solution +Copying solution to: permutation-permutation-000027.solution +Copying solution to: permutation-permutation-000028.solution +Copying solution to: permutation-permutation-000029.solution +Copying solution to: permutation-permutation-000030.solution +Copying solution to: permutation-permutation-000031.solution +Copying solution to: permutation-permutation-000032.solution +Copying solution to: permutation-permutation-000033.solution +Copying solution to: permutation-permutation-000034.solution +Copying solution to: permutation-permutation-000035.solution +Copying solution to: permutation-permutation-000036.solution +Copying solution to: permutation-permutation-000037.solution +Copying solution to: permutation-permutation-000038.solution +Copying solution to: permutation-permutation-000039.solution +Copying solution to: permutation-permutation-000040.solution +Copying solution to: permutation-permutation-000041.solution +Copying solution to: permutation-permutation-000042.solution +Copying solution to: permutation-permutation-000043.solution +Copying solution to: permutation-permutation-000044.solution +Copying solution to: permutation-permutation-000045.solution +Copying solution to: permutation-permutation-000046.solution +Copying solution to: permutation-permutation-000047.solution +Copying solution to: permutation-permutation-000048.solution +Copying solution to: permutation-permutation-000049.solution +Copying solution to: permutation-permutation-000050.solution +Copying solution to: permutation-permutation-000051.solution +Copying solution to: permutation-permutation-000052.solution +Copying solution to: permutation-permutation-000053.solution +Copying solution to: permutation-permutation-000054.solution +Copying solution to: permutation-permutation-000055.solution +Copying solution to: permutation-permutation-000056.solution +language Essence 1.3 + +letting x be [THING1, THING1, THING1, THING1, THING1; int(1..5)] +letting y be [THING1, THING1, THING1, THING1, THING1; int(1..5)] +language Essence 1.3 + +letting x be [THING1, THING1, THING1, THING1, THING1; int(1..5)] +letting y be [THING1, THING1, THING1, THING1, THING2; int(1..5)] +language Essence 1.3 + +letting x be [THING1, THING1, THING1, THING1, THING1; int(1..5)] +letting y be [THING1, THING1, THING1, THING2, THING2; int(1..5)] +language Essence 1.3 + +letting x be [THING1, THING1, THING1, THING1, THING1; int(1..5)] +letting y be [THING1, THING1, THING2, THING2, THING2; int(1..5)] +language Essence 1.3 + +letting x be [THING1, THING1, THING1, THING1, THING1; int(1..5)] +letting y be [THING1, THING2, THING2, THING2, THING2; int(1..5)] +language Essence 1.3 + +letting x be [THING1, THING1, THING1, THING1, THING1; int(1..5)] +letting y be [THING2, THING2, THING2, THING2, THING2; int(1..5)] +language Essence 1.3 + +letting x be [THING1, THING1, THING1, THING1, THING2; int(1..5)] +letting y be [THING1, THING1, THING1, THING1, THING1; int(1..5)] +language Essence 1.3 + +letting x be [THING1, THING1, THING1, THING1, THING2; int(1..5)] +letting y be [THING1, THING1, THING1, THING1, THING2; int(1..5)] +language Essence 1.3 + +letting x be [THING1, THING1, THING1, THING1, THING2; int(1..5)] +letting y be [THING1, THING1, THING1, THING2, THING1; int(1..5)] +language Essence 1.3 + +letting x be [THING1, THING1, THING1, THING1, THING2; int(1..5)] +letting y be [THING1, THING1, THING1, THING2, THING2; int(1..5)] +language Essence 1.3 + +letting x be [THING1, THING1, THING1, THING1, THING2; int(1..5)] +letting y be [THING1, THING1, THING2, THING2, THING1; int(1..5)] +language Essence 1.3 + +letting x be [THING1, THING1, THING1, THING1, THING2; int(1..5)] +letting y be [THING1, THING1, THING2, THING2, THING2; int(1..5)] +language Essence 1.3 + +letting x be [THING1, THING1, THING1, THING1, THING2; int(1..5)] +letting y be [THING1, THING2, THING2, THING2, THING1; int(1..5)] +language Essence 1.3 + +letting x be [THING1, THING1, THING1, THING1, THING2; int(1..5)] +letting y be [THING1, THING2, THING2, THING2, THING2; int(1..5)] +language Essence 1.3 + +letting x be [THING1, THING1, THING1, THING1, THING2; int(1..5)] +letting y be [THING2, THING2, THING2, THING2, THING1; int(1..5)] +language Essence 1.3 + +letting x be [THING1, THING1, THING1, THING1, THING2; int(1..5)] +letting y be [THING2, THING2, THING2, THING2, THING2; int(1..5)] +language Essence 1.3 + +letting x be [THING1, THING1, THING1, THING2, THING2; int(1..5)] +letting y be [THING1, THING1, THING1, THING1, THING1; int(1..5)] +language Essence 1.3 + +letting x be [THING1, THING1, THING1, THING2, THING2; int(1..5)] +letting y be [THING1, THING1, THING1, THING1, THING2; int(1..5)] +language Essence 1.3 + +letting x be [THING1, THING1, THING1, THING2, THING2; int(1..5)] +letting y be [THING1, THING1, THING1, THING2, THING2; int(1..5)] +language Essence 1.3 + +letting x be [THING1, THING1, THING1, THING2, THING2; int(1..5)] +letting y be [THING1, THING1, THING2, THING1, THING1; int(1..5)] +language Essence 1.3 + +letting x be [THING1, THING1, THING1, THING2, THING2; int(1..5)] +letting y be [THING1, THING1, THING2, THING1, THING2; int(1..5)] +language Essence 1.3 + +letting x be [THING1, THING1, THING1, THING2, THING2; int(1..5)] +letting y be [THING1, THING1, THING2, THING2, THING2; int(1..5)] +language Essence 1.3 + +letting x be [THING1, THING1, THING1, THING2, THING2; int(1..5)] +letting y be [THING1, THING2, THING2, THING1, THING1; int(1..5)] +language Essence 1.3 + +letting x be [THING1, THING1, THING1, THING2, THING2; int(1..5)] +letting y be [THING1, THING2, THING2, THING1, THING2; int(1..5)] +language Essence 1.3 + +letting x be [THING1, THING1, THING1, THING2, THING2; int(1..5)] +letting y be [THING1, THING2, THING2, THING2, THING2; int(1..5)] +language Essence 1.3 + +letting x be [THING1, THING1, THING1, THING2, THING2; int(1..5)] +letting y be [THING2, THING2, THING2, THING1, THING1; int(1..5)] +language Essence 1.3 + +letting x be [THING1, THING1, THING1, THING2, THING2; int(1..5)] +letting y be [THING2, THING2, THING2, THING1, THING2; int(1..5)] +language Essence 1.3 + +letting x be [THING1, THING1, THING1, THING2, THING2; int(1..5)] +letting y be [THING2, THING2, THING2, THING2, THING2; int(1..5)] +language Essence 1.3 + +letting x be [THING1, THING1, THING2, THING2, THING2; int(1..5)] +letting y be [THING1, THING1, THING1, THING1, THING1; int(1..5)] +language Essence 1.3 + +letting x be [THING1, THING1, THING2, THING2, THING2; int(1..5)] +letting y be [THING1, THING1, THING1, THING1, THING2; int(1..5)] +language Essence 1.3 + +letting x be [THING1, THING1, THING2, THING2, THING2; int(1..5)] +letting y be [THING1, THING1, THING1, THING2, THING2; int(1..5)] +language Essence 1.3 + +letting x be [THING1, THING1, THING2, THING2, THING2; int(1..5)] +letting y be [THING1, THING1, THING2, THING2, THING2; int(1..5)] +language Essence 1.3 + +letting x be [THING1, THING1, THING2, THING2, THING2; int(1..5)] +letting y be [THING1, THING2, THING1, THING1, THING1; int(1..5)] +language Essence 1.3 + +letting x be [THING1, THING1, THING2, THING2, THING2; int(1..5)] +letting y be [THING1, THING2, THING1, THING1, THING2; int(1..5)] +language Essence 1.3 + +letting x be [THING1, THING1, THING2, THING2, THING2; int(1..5)] +letting y be [THING1, THING2, THING1, THING2, THING2; int(1..5)] +language Essence 1.3 + +letting x be [THING1, THING1, THING2, THING2, THING2; int(1..5)] +letting y be [THING1, THING2, THING2, THING2, THING2; int(1..5)] +language Essence 1.3 + +letting x be [THING1, THING1, THING2, THING2, THING2; int(1..5)] +letting y be [THING2, THING2, THING1, THING1, THING1; int(1..5)] +language Essence 1.3 + +letting x be [THING1, THING1, THING2, THING2, THING2; int(1..5)] +letting y be [THING2, THING2, THING1, THING1, THING2; int(1..5)] +language Essence 1.3 + +letting x be [THING1, THING1, THING2, THING2, THING2; int(1..5)] +letting y be [THING2, THING2, THING1, THING2, THING2; int(1..5)] +language Essence 1.3 + +letting x be [THING1, THING1, THING2, THING2, THING2; int(1..5)] +letting y be [THING2, THING2, THING2, THING2, THING2; int(1..5)] +language Essence 1.3 + +letting x be [THING1, THING2, THING2, THING2, THING2; int(1..5)] +letting y be [THING1, THING1, THING1, THING1, THING1; int(1..5)] +language Essence 1.3 + +letting x be [THING1, THING2, THING2, THING2, THING2; int(1..5)] +letting y be [THING1, THING1, THING1, THING1, THING2; int(1..5)] +language Essence 1.3 + +letting x be [THING1, THING2, THING2, THING2, THING2; int(1..5)] +letting y be [THING1, THING1, THING1, THING2, THING2; int(1..5)] +language Essence 1.3 + +letting x be [THING1, THING2, THING2, THING2, THING2; int(1..5)] +letting y be [THING1, THING1, THING2, THING2, THING2; int(1..5)] +language Essence 1.3 + +letting x be [THING1, THING2, THING2, THING2, THING2; int(1..5)] +letting y be [THING1, THING2, THING2, THING2, THING2; int(1..5)] +language Essence 1.3 + +letting x be [THING1, THING2, THING2, THING2, THING2; int(1..5)] +letting y be [THING2, THING1, THING1, THING1, THING1; int(1..5)] +language Essence 1.3 + +letting x be [THING1, THING2, THING2, THING2, THING2; int(1..5)] +letting y be [THING2, THING1, THING1, THING1, THING2; int(1..5)] +language Essence 1.3 + +letting x be [THING1, THING2, THING2, THING2, THING2; int(1..5)] +letting y be [THING2, THING1, THING1, THING2, THING2; int(1..5)] +language Essence 1.3 + +letting x be [THING1, THING2, THING2, THING2, THING2; int(1..5)] +letting y be [THING2, THING1, THING2, THING2, THING2; int(1..5)] +language Essence 1.3 + +letting x be [THING1, THING2, THING2, THING2, THING2; int(1..5)] +letting y be [THING2, THING2, THING2, THING2, THING2; int(1..5)] +language Essence 1.3 + +letting x be [THING2, THING2, THING2, THING2, THING2; int(1..5)] +letting y be [THING1, THING1, THING1, THING1, THING1; int(1..5)] +language Essence 1.3 + +letting x be [THING2, THING2, THING2, THING2, THING2; int(1..5)] +letting y be [THING1, THING1, THING1, THING1, THING2; int(1..5)] +language Essence 1.3 + +letting x be [THING2, THING2, THING2, THING2, THING2; int(1..5)] +letting y be [THING1, THING1, THING1, THING2, THING2; int(1..5)] +language Essence 1.3 + +letting x be [THING2, THING2, THING2, THING2, THING2; int(1..5)] +letting y be [THING1, THING1, THING2, THING2, THING2; int(1..5)] +language Essence 1.3 + +letting x be [THING2, THING2, THING2, THING2, THING2; int(1..5)] +letting y be [THING1, THING2, THING2, THING2, THING2; int(1..5)] +language Essence 1.3 + +letting x be [THING2, THING2, THING2, THING2, THING2; int(1..5)] +letting y be [THING2, THING2, THING2, THING2, THING2; int(1..5)] diff --git a/tests/custom/permutations/basic/34/permutation.essence b/tests/custom/permutations/basic/34/permutation.essence new file mode 100644 index 0000000000..f9ad569e31 --- /dev/null +++ b/tests/custom/permutations/basic/34/permutation.essence @@ -0,0 +1,6 @@ +given n : int + +find j : int(0..100) + +such that + n = permute(permutation(()),j) diff --git a/tests/custom/permutations/basic/34/permutation.param b/tests/custom/permutations/basic/34/permutation.param new file mode 100644 index 0000000000..05cd66931a --- /dev/null +++ b/tests/custom/permutations/basic/34/permutation.param @@ -0,0 +1 @@ +letting n be 5 diff --git a/tests/custom/permutations/basic/34/run.sh b/tests/custom/permutations/basic/34/run.sh new file mode 100755 index 0000000000..1f1c63f942 --- /dev/null +++ b/tests/custom/permutations/basic/34/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence *.param --number-of-solutions=60 +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/basic/35/permutation.essence b/tests/custom/permutations/basic/35/permutation.essence new file mode 100644 index 0000000000..0bd7a2d49b --- /dev/null +++ b/tests/custom/permutations/basic/35/permutation.essence @@ -0,0 +1,23 @@ +letting e +be +new type +enum {E1, E2, E3, E4} + + + +find s : permutation +of e + + + +such +that permute(s, E1) += E2, + + + +forAll i : +int(-10..10). permute(s, i) += i + + diff --git a/tests/custom/permutations/basic/35/permutation.param b/tests/custom/permutations/basic/35/permutation.param new file mode 100644 index 0000000000..05cd66931a --- /dev/null +++ b/tests/custom/permutations/basic/35/permutation.param @@ -0,0 +1 @@ +letting n be 5 diff --git a/tests/custom/permutations/basic/35/run.sh b/tests/custom/permutations/basic/35/run.sh new file mode 100755 index 0000000000..a1691af90c --- /dev/null +++ b/tests/custom/permutations/basic/35/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence +cat conjure-output/*.solution +rm -rf conjure-output *.solution From 3ec8020bdbedf8f1779a608d5f07f8395151c1c4 Mon Sep 17 00:00:00 2001 From: Fraser Dunlop Date: Mon, 19 Nov 2018 10:49:15 +0000 Subject: [PATCH 020/229] Renamed some tests --- .../{01 => 0001_given_permutation_in_param}/permutation.essence | 0 .../{01 => 0001_given_permutation_in_param}/permutation.param | 0 .../basic/{01 => 0001_given_permutation_in_param}/run.sh | 0 .../basic/{01 => 0001_given_permutation_in_param}/stdout.expected | 0 .../{02 => 0002_given_permutation_in_param}/permutation.essence | 0 .../{02 => 0002_given_permutation_in_param}/permutation.param | 0 .../basic/{02 => 0002_given_permutation_in_param}/run.sh | 0 .../basic/{02 => 0002_given_permutation_in_param}/stdout.expected | 0 .../permutation.essence | 0 .../permutation.param | 0 .../basic/{03 => 0003_given_permutation_in_param_2_cycle}/run.sh | 0 .../stderr.expected | 0 .../stdout.expected | 0 .../permutation.essence | 0 .../permutation.param | 0 .../basic/{04 => 0004_given_permutation_in_param_2_cycle}/run.sh | 0 .../stdout.expected | 0 .../permutation.essence | 0 .../permutation.param | 0 .../{05 => 0005_find_int_image_under_given_permutation}/run.sh | 0 .../stdout.expected | 0 .../permutation.essence | 0 .../permutation.param | 0 .../{06 => 0006_find_int_image_under_given_permutation}/run.sh | 0 .../stdout.expected | 0 .../permutation.essence | 0 .../permutation.param | 0 .../{07 => 0007_find_int_image_under_given_permutation}/run.sh | 0 .../stdout.expected | 0 .../permutation.essence | 0 .../permutation.param | 0 .../run.sh | 0 .../stdout.expected | 0 .../permutation.essence | 0 .../permutation.param | 0 .../run.sh | 0 .../stdout.expected | 0 .../permutation.essence | 0 .../permutation.param | 0 .../run.sh | 0 .../stdout.expected | 0 .../permutation.essence | 0 .../run.sh | 0 .../stdout.expected | 0 44 files changed, 0 insertions(+), 0 deletions(-) rename tests/custom/permutations/basic/{01 => 0001_given_permutation_in_param}/permutation.essence (100%) rename tests/custom/permutations/basic/{01 => 0001_given_permutation_in_param}/permutation.param (100%) rename tests/custom/permutations/basic/{01 => 0001_given_permutation_in_param}/run.sh (100%) rename tests/custom/permutations/basic/{01 => 0001_given_permutation_in_param}/stdout.expected (100%) rename tests/custom/permutations/basic/{02 => 0002_given_permutation_in_param}/permutation.essence (100%) rename tests/custom/permutations/basic/{02 => 0002_given_permutation_in_param}/permutation.param (100%) rename tests/custom/permutations/basic/{02 => 0002_given_permutation_in_param}/run.sh (100%) rename tests/custom/permutations/basic/{02 => 0002_given_permutation_in_param}/stdout.expected (100%) rename tests/custom/permutations/basic/{03 => 0003_given_permutation_in_param_2_cycle}/permutation.essence (100%) rename tests/custom/permutations/basic/{03 => 0003_given_permutation_in_param_2_cycle}/permutation.param (100%) rename tests/custom/permutations/basic/{03 => 0003_given_permutation_in_param_2_cycle}/run.sh (100%) rename tests/custom/permutations/basic/{03 => 0003_given_permutation_in_param_2_cycle}/stderr.expected (100%) rename tests/custom/permutations/basic/{03 => 0003_given_permutation_in_param_2_cycle}/stdout.expected (100%) rename tests/custom/permutations/basic/{04 => 0004_given_permutation_in_param_2_cycle}/permutation.essence (100%) rename tests/custom/permutations/basic/{04 => 0004_given_permutation_in_param_2_cycle}/permutation.param (100%) rename tests/custom/permutations/basic/{04 => 0004_given_permutation_in_param_2_cycle}/run.sh (100%) rename tests/custom/permutations/basic/{04 => 0004_given_permutation_in_param_2_cycle}/stdout.expected (100%) rename tests/custom/permutations/basic/{05 => 0005_find_int_image_under_given_permutation}/permutation.essence (100%) rename tests/custom/permutations/basic/{05 => 0005_find_int_image_under_given_permutation}/permutation.param (100%) rename tests/custom/permutations/basic/{05 => 0005_find_int_image_under_given_permutation}/run.sh (100%) rename tests/custom/permutations/basic/{05 => 0005_find_int_image_under_given_permutation}/stdout.expected (100%) rename tests/custom/permutations/basic/{06 => 0006_find_int_image_under_given_permutation}/permutation.essence (100%) rename tests/custom/permutations/basic/{06 => 0006_find_int_image_under_given_permutation}/permutation.param (100%) rename tests/custom/permutations/basic/{06 => 0006_find_int_image_under_given_permutation}/run.sh (100%) rename tests/custom/permutations/basic/{06 => 0006_find_int_image_under_given_permutation}/stdout.expected (100%) rename tests/custom/permutations/basic/{07 => 0007_find_int_image_under_given_permutation}/permutation.essence (100%) rename tests/custom/permutations/basic/{07 => 0007_find_int_image_under_given_permutation}/permutation.param (100%) rename tests/custom/permutations/basic/{07 => 0007_find_int_image_under_given_permutation}/run.sh (100%) rename tests/custom/permutations/basic/{07 => 0007_find_int_image_under_given_permutation}/stdout.expected (100%) rename tests/custom/permutations/basic/{08 => 0008_find_int_image_under_two_composed_given_permutations}/permutation.essence (100%) rename tests/custom/permutations/basic/{08 => 0008_find_int_image_under_two_composed_given_permutations}/permutation.param (100%) rename tests/custom/permutations/basic/{08 => 0008_find_int_image_under_two_composed_given_permutations}/run.sh (100%) rename tests/custom/permutations/basic/{08 => 0008_find_int_image_under_two_composed_given_permutations}/stdout.expected (100%) rename tests/custom/permutations/basic/{09 => 0009_find_int_image_under_three_composed_given_permutations}/permutation.essence (100%) rename tests/custom/permutations/basic/{09 => 0009_find_int_image_under_three_composed_given_permutations}/permutation.param (100%) rename tests/custom/permutations/basic/{09 => 0009_find_int_image_under_three_composed_given_permutations}/run.sh (100%) rename tests/custom/permutations/basic/{09 => 0009_find_int_image_under_three_composed_given_permutations}/stdout.expected (100%) rename tests/custom/permutations/basic/{10 => 0010_find_int_image_under_three_composed_given_permutations}/permutation.essence (100%) rename tests/custom/permutations/basic/{10 => 0010_find_int_image_under_three_composed_given_permutations}/permutation.param (100%) rename tests/custom/permutations/basic/{10 => 0010_find_int_image_under_three_composed_given_permutations}/run.sh (100%) rename tests/custom/permutations/basic/{10 => 0010_find_int_image_under_three_composed_given_permutations}/stdout.expected (100%) rename tests/custom/permutations/basic/{11 => 0011_find_int_and_permutation_such_that_int_image_equals_const}/permutation.essence (100%) rename tests/custom/permutations/basic/{11 => 0011_find_int_and_permutation_such_that_int_image_equals_const}/run.sh (100%) rename tests/custom/permutations/basic/{11 => 0011_find_int_and_permutation_such_that_int_image_equals_const}/stdout.expected (100%) diff --git a/tests/custom/permutations/basic/01/permutation.essence b/tests/custom/permutations/basic/0001_given_permutation_in_param/permutation.essence similarity index 100% rename from tests/custom/permutations/basic/01/permutation.essence rename to tests/custom/permutations/basic/0001_given_permutation_in_param/permutation.essence diff --git a/tests/custom/permutations/basic/01/permutation.param b/tests/custom/permutations/basic/0001_given_permutation_in_param/permutation.param similarity index 100% rename from tests/custom/permutations/basic/01/permutation.param rename to tests/custom/permutations/basic/0001_given_permutation_in_param/permutation.param diff --git a/tests/custom/permutations/basic/01/run.sh b/tests/custom/permutations/basic/0001_given_permutation_in_param/run.sh similarity index 100% rename from tests/custom/permutations/basic/01/run.sh rename to tests/custom/permutations/basic/0001_given_permutation_in_param/run.sh diff --git a/tests/custom/permutations/basic/01/stdout.expected b/tests/custom/permutations/basic/0001_given_permutation_in_param/stdout.expected similarity index 100% rename from tests/custom/permutations/basic/01/stdout.expected rename to tests/custom/permutations/basic/0001_given_permutation_in_param/stdout.expected diff --git a/tests/custom/permutations/basic/02/permutation.essence b/tests/custom/permutations/basic/0002_given_permutation_in_param/permutation.essence similarity index 100% rename from tests/custom/permutations/basic/02/permutation.essence rename to tests/custom/permutations/basic/0002_given_permutation_in_param/permutation.essence diff --git a/tests/custom/permutations/basic/02/permutation.param b/tests/custom/permutations/basic/0002_given_permutation_in_param/permutation.param similarity index 100% rename from tests/custom/permutations/basic/02/permutation.param rename to tests/custom/permutations/basic/0002_given_permutation_in_param/permutation.param diff --git a/tests/custom/permutations/basic/02/run.sh b/tests/custom/permutations/basic/0002_given_permutation_in_param/run.sh similarity index 100% rename from tests/custom/permutations/basic/02/run.sh rename to tests/custom/permutations/basic/0002_given_permutation_in_param/run.sh diff --git a/tests/custom/permutations/basic/02/stdout.expected b/tests/custom/permutations/basic/0002_given_permutation_in_param/stdout.expected similarity index 100% rename from tests/custom/permutations/basic/02/stdout.expected rename to tests/custom/permutations/basic/0002_given_permutation_in_param/stdout.expected diff --git a/tests/custom/permutations/basic/03/permutation.essence b/tests/custom/permutations/basic/0003_given_permutation_in_param_2_cycle/permutation.essence similarity index 100% rename from tests/custom/permutations/basic/03/permutation.essence rename to tests/custom/permutations/basic/0003_given_permutation_in_param_2_cycle/permutation.essence diff --git a/tests/custom/permutations/basic/03/permutation.param b/tests/custom/permutations/basic/0003_given_permutation_in_param_2_cycle/permutation.param similarity index 100% rename from tests/custom/permutations/basic/03/permutation.param rename to tests/custom/permutations/basic/0003_given_permutation_in_param_2_cycle/permutation.param diff --git a/tests/custom/permutations/basic/03/run.sh b/tests/custom/permutations/basic/0003_given_permutation_in_param_2_cycle/run.sh similarity index 100% rename from tests/custom/permutations/basic/03/run.sh rename to tests/custom/permutations/basic/0003_given_permutation_in_param_2_cycle/run.sh diff --git a/tests/custom/permutations/basic/03/stderr.expected b/tests/custom/permutations/basic/0003_given_permutation_in_param_2_cycle/stderr.expected similarity index 100% rename from tests/custom/permutations/basic/03/stderr.expected rename to tests/custom/permutations/basic/0003_given_permutation_in_param_2_cycle/stderr.expected diff --git a/tests/custom/permutations/basic/03/stdout.expected b/tests/custom/permutations/basic/0003_given_permutation_in_param_2_cycle/stdout.expected similarity index 100% rename from tests/custom/permutations/basic/03/stdout.expected rename to tests/custom/permutations/basic/0003_given_permutation_in_param_2_cycle/stdout.expected diff --git a/tests/custom/permutations/basic/04/permutation.essence b/tests/custom/permutations/basic/0004_given_permutation_in_param_2_cycle/permutation.essence similarity index 100% rename from tests/custom/permutations/basic/04/permutation.essence rename to tests/custom/permutations/basic/0004_given_permutation_in_param_2_cycle/permutation.essence diff --git a/tests/custom/permutations/basic/04/permutation.param b/tests/custom/permutations/basic/0004_given_permutation_in_param_2_cycle/permutation.param similarity index 100% rename from tests/custom/permutations/basic/04/permutation.param rename to tests/custom/permutations/basic/0004_given_permutation_in_param_2_cycle/permutation.param diff --git a/tests/custom/permutations/basic/04/run.sh b/tests/custom/permutations/basic/0004_given_permutation_in_param_2_cycle/run.sh similarity index 100% rename from tests/custom/permutations/basic/04/run.sh rename to tests/custom/permutations/basic/0004_given_permutation_in_param_2_cycle/run.sh diff --git a/tests/custom/permutations/basic/04/stdout.expected b/tests/custom/permutations/basic/0004_given_permutation_in_param_2_cycle/stdout.expected similarity index 100% rename from tests/custom/permutations/basic/04/stdout.expected rename to tests/custom/permutations/basic/0004_given_permutation_in_param_2_cycle/stdout.expected diff --git a/tests/custom/permutations/basic/05/permutation.essence b/tests/custom/permutations/basic/0005_find_int_image_under_given_permutation/permutation.essence similarity index 100% rename from tests/custom/permutations/basic/05/permutation.essence rename to tests/custom/permutations/basic/0005_find_int_image_under_given_permutation/permutation.essence diff --git a/tests/custom/permutations/basic/05/permutation.param b/tests/custom/permutations/basic/0005_find_int_image_under_given_permutation/permutation.param similarity index 100% rename from tests/custom/permutations/basic/05/permutation.param rename to tests/custom/permutations/basic/0005_find_int_image_under_given_permutation/permutation.param diff --git a/tests/custom/permutations/basic/05/run.sh b/tests/custom/permutations/basic/0005_find_int_image_under_given_permutation/run.sh similarity index 100% rename from tests/custom/permutations/basic/05/run.sh rename to tests/custom/permutations/basic/0005_find_int_image_under_given_permutation/run.sh diff --git a/tests/custom/permutations/basic/05/stdout.expected b/tests/custom/permutations/basic/0005_find_int_image_under_given_permutation/stdout.expected similarity index 100% rename from tests/custom/permutations/basic/05/stdout.expected rename to tests/custom/permutations/basic/0005_find_int_image_under_given_permutation/stdout.expected diff --git a/tests/custom/permutations/basic/06/permutation.essence b/tests/custom/permutations/basic/0006_find_int_image_under_given_permutation/permutation.essence similarity index 100% rename from tests/custom/permutations/basic/06/permutation.essence rename to tests/custom/permutations/basic/0006_find_int_image_under_given_permutation/permutation.essence diff --git a/tests/custom/permutations/basic/06/permutation.param b/tests/custom/permutations/basic/0006_find_int_image_under_given_permutation/permutation.param similarity index 100% rename from tests/custom/permutations/basic/06/permutation.param rename to tests/custom/permutations/basic/0006_find_int_image_under_given_permutation/permutation.param diff --git a/tests/custom/permutations/basic/06/run.sh b/tests/custom/permutations/basic/0006_find_int_image_under_given_permutation/run.sh similarity index 100% rename from tests/custom/permutations/basic/06/run.sh rename to tests/custom/permutations/basic/0006_find_int_image_under_given_permutation/run.sh diff --git a/tests/custom/permutations/basic/06/stdout.expected b/tests/custom/permutations/basic/0006_find_int_image_under_given_permutation/stdout.expected similarity index 100% rename from tests/custom/permutations/basic/06/stdout.expected rename to tests/custom/permutations/basic/0006_find_int_image_under_given_permutation/stdout.expected diff --git a/tests/custom/permutations/basic/07/permutation.essence b/tests/custom/permutations/basic/0007_find_int_image_under_given_permutation/permutation.essence similarity index 100% rename from tests/custom/permutations/basic/07/permutation.essence rename to tests/custom/permutations/basic/0007_find_int_image_under_given_permutation/permutation.essence diff --git a/tests/custom/permutations/basic/07/permutation.param b/tests/custom/permutations/basic/0007_find_int_image_under_given_permutation/permutation.param similarity index 100% rename from tests/custom/permutations/basic/07/permutation.param rename to tests/custom/permutations/basic/0007_find_int_image_under_given_permutation/permutation.param diff --git a/tests/custom/permutations/basic/07/run.sh b/tests/custom/permutations/basic/0007_find_int_image_under_given_permutation/run.sh similarity index 100% rename from tests/custom/permutations/basic/07/run.sh rename to tests/custom/permutations/basic/0007_find_int_image_under_given_permutation/run.sh diff --git a/tests/custom/permutations/basic/07/stdout.expected b/tests/custom/permutations/basic/0007_find_int_image_under_given_permutation/stdout.expected similarity index 100% rename from tests/custom/permutations/basic/07/stdout.expected rename to tests/custom/permutations/basic/0007_find_int_image_under_given_permutation/stdout.expected diff --git a/tests/custom/permutations/basic/08/permutation.essence b/tests/custom/permutations/basic/0008_find_int_image_under_two_composed_given_permutations/permutation.essence similarity index 100% rename from tests/custom/permutations/basic/08/permutation.essence rename to tests/custom/permutations/basic/0008_find_int_image_under_two_composed_given_permutations/permutation.essence diff --git a/tests/custom/permutations/basic/08/permutation.param b/tests/custom/permutations/basic/0008_find_int_image_under_two_composed_given_permutations/permutation.param similarity index 100% rename from tests/custom/permutations/basic/08/permutation.param rename to tests/custom/permutations/basic/0008_find_int_image_under_two_composed_given_permutations/permutation.param diff --git a/tests/custom/permutations/basic/08/run.sh b/tests/custom/permutations/basic/0008_find_int_image_under_two_composed_given_permutations/run.sh similarity index 100% rename from tests/custom/permutations/basic/08/run.sh rename to tests/custom/permutations/basic/0008_find_int_image_under_two_composed_given_permutations/run.sh diff --git a/tests/custom/permutations/basic/08/stdout.expected b/tests/custom/permutations/basic/0008_find_int_image_under_two_composed_given_permutations/stdout.expected similarity index 100% rename from tests/custom/permutations/basic/08/stdout.expected rename to tests/custom/permutations/basic/0008_find_int_image_under_two_composed_given_permutations/stdout.expected diff --git a/tests/custom/permutations/basic/09/permutation.essence b/tests/custom/permutations/basic/0009_find_int_image_under_three_composed_given_permutations/permutation.essence similarity index 100% rename from tests/custom/permutations/basic/09/permutation.essence rename to tests/custom/permutations/basic/0009_find_int_image_under_three_composed_given_permutations/permutation.essence diff --git a/tests/custom/permutations/basic/09/permutation.param b/tests/custom/permutations/basic/0009_find_int_image_under_three_composed_given_permutations/permutation.param similarity index 100% rename from tests/custom/permutations/basic/09/permutation.param rename to tests/custom/permutations/basic/0009_find_int_image_under_three_composed_given_permutations/permutation.param diff --git a/tests/custom/permutations/basic/09/run.sh b/tests/custom/permutations/basic/0009_find_int_image_under_three_composed_given_permutations/run.sh similarity index 100% rename from tests/custom/permutations/basic/09/run.sh rename to tests/custom/permutations/basic/0009_find_int_image_under_three_composed_given_permutations/run.sh diff --git a/tests/custom/permutations/basic/09/stdout.expected b/tests/custom/permutations/basic/0009_find_int_image_under_three_composed_given_permutations/stdout.expected similarity index 100% rename from tests/custom/permutations/basic/09/stdout.expected rename to tests/custom/permutations/basic/0009_find_int_image_under_three_composed_given_permutations/stdout.expected diff --git a/tests/custom/permutations/basic/10/permutation.essence b/tests/custom/permutations/basic/0010_find_int_image_under_three_composed_given_permutations/permutation.essence similarity index 100% rename from tests/custom/permutations/basic/10/permutation.essence rename to tests/custom/permutations/basic/0010_find_int_image_under_three_composed_given_permutations/permutation.essence diff --git a/tests/custom/permutations/basic/10/permutation.param b/tests/custom/permutations/basic/0010_find_int_image_under_three_composed_given_permutations/permutation.param similarity index 100% rename from tests/custom/permutations/basic/10/permutation.param rename to tests/custom/permutations/basic/0010_find_int_image_under_three_composed_given_permutations/permutation.param diff --git a/tests/custom/permutations/basic/10/run.sh b/tests/custom/permutations/basic/0010_find_int_image_under_three_composed_given_permutations/run.sh similarity index 100% rename from tests/custom/permutations/basic/10/run.sh rename to tests/custom/permutations/basic/0010_find_int_image_under_three_composed_given_permutations/run.sh diff --git a/tests/custom/permutations/basic/10/stdout.expected b/tests/custom/permutations/basic/0010_find_int_image_under_three_composed_given_permutations/stdout.expected similarity index 100% rename from tests/custom/permutations/basic/10/stdout.expected rename to tests/custom/permutations/basic/0010_find_int_image_under_three_composed_given_permutations/stdout.expected diff --git a/tests/custom/permutations/basic/11/permutation.essence b/tests/custom/permutations/basic/0011_find_int_and_permutation_such_that_int_image_equals_const/permutation.essence similarity index 100% rename from tests/custom/permutations/basic/11/permutation.essence rename to tests/custom/permutations/basic/0011_find_int_and_permutation_such_that_int_image_equals_const/permutation.essence diff --git a/tests/custom/permutations/basic/11/run.sh b/tests/custom/permutations/basic/0011_find_int_and_permutation_such_that_int_image_equals_const/run.sh similarity index 100% rename from tests/custom/permutations/basic/11/run.sh rename to tests/custom/permutations/basic/0011_find_int_and_permutation_such_that_int_image_equals_const/run.sh diff --git a/tests/custom/permutations/basic/11/stdout.expected b/tests/custom/permutations/basic/0011_find_int_and_permutation_such_that_int_image_equals_const/stdout.expected similarity index 100% rename from tests/custom/permutations/basic/11/stdout.expected rename to tests/custom/permutations/basic/0011_find_int_and_permutation_such_that_int_image_equals_const/stdout.expected From 2caeb63c71ed62b80066773b81fbf658e94945d5 Mon Sep 17 00:00:00 2001 From: Fraser Dunlop Date: Mon, 19 Nov 2018 11:46:59 +0000 Subject: [PATCH 021/229] Renamed some more tests --- .../permutation.essence | 0 .../run.sh | 0 .../stdout.expected | 0 .../permutation.essence | 0 .../run.sh | 0 .../stdout.expected | 0 .../permutation.essence | 0 .../run.sh | 0 .../stdout.expected | 0 .../permutation.essence | 0 .../{15 => 0015_find_set_of_permuted_elements_of_matrix}/run.sh | 0 .../stdout.expected | 0 .../permutation.essence | 0 .../run.sh | 0 .../stdout.expected | 0 .../permutation.essence | 0 .../run.sh | 0 .../stdout.expected | 0 .../permutation.essence | 0 .../{18 => 0018_find_matrix_lex_less_than_under_any_swap}/run.sh | 0 .../stdout.expected | 0 .../permutation.essence | 0 .../run.sh | 0 .../stdout.expected | 0 .../permutation.essence | 0 .../run.sh | 0 .../stdout.expected | 0 .../permutation.essence | 0 .../permutation.param | 0 .../run.sh | 0 .../stdout.expected | 0 .../permutation.essence | 0 .../permutation.param | 0 .../run.sh | 0 .../stdout.expected | 0 .../permutation.essence | 0 .../permutation.param | 0 .../run.sh | 0 .../stdout.expected | 0 .../permutation.essence | 0 .../permutation.param | 0 .../run.sh | 0 .../stdout.expected | 0 .../permutation.essence | 0 .../permutation.param | 0 .../run.sh | 0 .../stdout.expected | 0 47 files changed, 0 insertions(+), 0 deletions(-) rename tests/custom/permutations/basic/{12 => 0012_find_int_and_permutation_such_that_int_image_equals_const}/permutation.essence (100%) rename tests/custom/permutations/basic/{12 => 0012_find_int_and_permutation_such_that_int_image_equals_const}/run.sh (100%) rename tests/custom/permutations/basic/{12 => 0012_find_int_and_permutation_such_that_int_image_equals_const}/stdout.expected (100%) rename tests/custom/permutations/basic/{13 => 0013_find_permutation_such_that_image_of_matrix1_equals_matrix2}/permutation.essence (100%) rename tests/custom/permutations/basic/{13 => 0013_find_permutation_such_that_image_of_matrix1_equals_matrix2}/run.sh (100%) rename tests/custom/permutations/basic/{13 => 0013_find_permutation_such_that_image_of_matrix1_equals_matrix2}/stdout.expected (100%) rename tests/custom/permutations/basic/{14 => 0014_find_matrix_such_that_swapping_any_index_pairs_becomes_lex_greater}/permutation.essence (100%) rename tests/custom/permutations/basic/{14 => 0014_find_matrix_such_that_swapping_any_index_pairs_becomes_lex_greater}/run.sh (100%) rename tests/custom/permutations/basic/{14 => 0014_find_matrix_such_that_swapping_any_index_pairs_becomes_lex_greater}/stdout.expected (100%) rename tests/custom/permutations/basic/{15 => 0015_find_set_of_permuted_elements_of_matrix}/permutation.essence (100%) rename tests/custom/permutations/basic/{15 => 0015_find_set_of_permuted_elements_of_matrix}/run.sh (100%) rename tests/custom/permutations/basic/{15 => 0015_find_set_of_permuted_elements_of_matrix}/stdout.expected (100%) rename tests/custom/permutations/basic/{16 => 0016_find_permutation_such_that_image_is_identity_for_given_matrix}/permutation.essence (100%) rename tests/custom/permutations/basic/{16 => 0016_find_permutation_such_that_image_is_identity_for_given_matrix}/run.sh (100%) rename tests/custom/permutations/basic/{16 => 0016_find_permutation_such_that_image_is_identity_for_given_matrix}/stdout.expected (100%) rename tests/custom/permutations/basic/{17 => 0017_find_two_permutations_with_overlapping_domains_and_same_image_over_domain_union}/permutation.essence (100%) rename tests/custom/permutations/basic/{17 => 0017_find_two_permutations_with_overlapping_domains_and_same_image_over_domain_union}/run.sh (100%) rename tests/custom/permutations/basic/{17 => 0017_find_two_permutations_with_overlapping_domains_and_same_image_over_domain_union}/stdout.expected (100%) rename tests/custom/permutations/basic/{18 => 0018_find_matrix_lex_less_than_under_any_swap}/permutation.essence (100%) rename tests/custom/permutations/basic/{18 => 0018_find_matrix_lex_less_than_under_any_swap}/run.sh (100%) rename tests/custom/permutations/basic/{18 => 0018_find_matrix_lex_less_than_under_any_swap}/stdout.expected (100%) rename tests/custom/permutations/basic/{19 => 0019_find_set_of_permutation_tuples_using_comprehension}/permutation.essence (100%) rename tests/custom/permutations/basic/{19 => 0019_find_set_of_permutation_tuples_using_comprehension}/run.sh (100%) rename tests/custom/permutations/basic/{19 => 0019_find_set_of_permutation_tuples_using_comprehension}/stdout.expected (100%) rename tests/custom/permutations/basic/{20 => 0020_find_permutation_inverse_using_comprehension}/permutation.essence (100%) rename tests/custom/permutations/basic/{20 => 0020_find_permutation_inverse_using_comprehension}/run.sh (100%) rename tests/custom/permutations/basic/{20 => 0020_find_permutation_inverse_using_comprehension}/stdout.expected (100%) rename tests/custom/permutations/basic/{21 => 0021_image_of_int_under_composition_of_two_given_permutations}/permutation.essence (100%) rename tests/custom/permutations/basic/{21 => 0021_image_of_int_under_composition_of_two_given_permutations}/permutation.param (100%) rename tests/custom/permutations/basic/{21 => 0021_image_of_int_under_composition_of_two_given_permutations}/run.sh (100%) rename tests/custom/permutations/basic/{21 => 0021_image_of_int_under_composition_of_two_given_permutations}/stdout.expected (100%) rename tests/custom/permutations/basic/{22 => 0022_find_matrices_of_enum_x_y_such_that_y_lexless_than_x_under_any_index_swap}/permutation.essence (100%) rename tests/custom/permutations/basic/{22 => 0022_find_matrices_of_enum_x_y_such_that_y_lexless_than_x_under_any_index_swap}/permutation.param (100%) rename tests/custom/permutations/basic/{22 => 0022_find_matrices_of_enum_x_y_such_that_y_lexless_than_x_under_any_index_swap}/run.sh (100%) rename tests/custom/permutations/basic/{22 => 0022_find_matrices_of_enum_x_y_such_that_y_lexless_than_x_under_any_index_swap}/stdout.expected (100%) rename tests/custom/permutations/basic/{23 => 0023_find_triples_x_y_such_that_y_lex_less_x_under_any_swap}/permutation.essence (100%) rename tests/custom/permutations/basic/{23 => 0023_find_triples_x_y_such_that_y_lex_less_x_under_any_swap}/permutation.param (100%) rename tests/custom/permutations/basic/{23 => 0023_find_triples_x_y_such_that_y_lex_less_x_under_any_swap}/run.sh (100%) rename tests/custom/permutations/basic/{23 => 0023_find_triples_x_y_such_that_y_lex_less_x_under_any_swap}/stdout.expected (100%) rename tests/custom/permutations/basic/{24 => 0024_find_sets_x_y_such_that_y_lexless_x_under_any_swap}/permutation.essence (100%) rename tests/custom/permutations/basic/{24 => 0024_find_sets_x_y_such_that_y_lexless_x_under_any_swap}/permutation.param (100%) rename tests/custom/permutations/basic/{24 => 0024_find_sets_x_y_such_that_y_lexless_x_under_any_swap}/run.sh (100%) rename tests/custom/permutations/basic/{24 => 0024_find_sets_x_y_such_that_y_lexless_x_under_any_swap}/stdout.expected (100%) rename tests/custom/permutations/basic/{25 => 0025_find_permutation_and_matrices_x_y_such_that_image_x_eq_y}/permutation.essence (100%) rename tests/custom/permutations/basic/{25 => 0025_find_permutation_and_matrices_x_y_such_that_image_x_eq_y}/permutation.param (100%) rename tests/custom/permutations/basic/{25 => 0025_find_permutation_and_matrices_x_y_such_that_image_x_eq_y}/run.sh (100%) rename tests/custom/permutations/basic/{25 => 0025_find_permutation_and_matrices_x_y_such_that_image_x_eq_y}/stdout.expected (100%) diff --git a/tests/custom/permutations/basic/12/permutation.essence b/tests/custom/permutations/basic/0012_find_int_and_permutation_such_that_int_image_equals_const/permutation.essence similarity index 100% rename from tests/custom/permutations/basic/12/permutation.essence rename to tests/custom/permutations/basic/0012_find_int_and_permutation_such_that_int_image_equals_const/permutation.essence diff --git a/tests/custom/permutations/basic/12/run.sh b/tests/custom/permutations/basic/0012_find_int_and_permutation_such_that_int_image_equals_const/run.sh similarity index 100% rename from tests/custom/permutations/basic/12/run.sh rename to tests/custom/permutations/basic/0012_find_int_and_permutation_such_that_int_image_equals_const/run.sh diff --git a/tests/custom/permutations/basic/12/stdout.expected b/tests/custom/permutations/basic/0012_find_int_and_permutation_such_that_int_image_equals_const/stdout.expected similarity index 100% rename from tests/custom/permutations/basic/12/stdout.expected rename to tests/custom/permutations/basic/0012_find_int_and_permutation_such_that_int_image_equals_const/stdout.expected diff --git a/tests/custom/permutations/basic/13/permutation.essence b/tests/custom/permutations/basic/0013_find_permutation_such_that_image_of_matrix1_equals_matrix2/permutation.essence similarity index 100% rename from tests/custom/permutations/basic/13/permutation.essence rename to tests/custom/permutations/basic/0013_find_permutation_such_that_image_of_matrix1_equals_matrix2/permutation.essence diff --git a/tests/custom/permutations/basic/13/run.sh b/tests/custom/permutations/basic/0013_find_permutation_such_that_image_of_matrix1_equals_matrix2/run.sh similarity index 100% rename from tests/custom/permutations/basic/13/run.sh rename to tests/custom/permutations/basic/0013_find_permutation_such_that_image_of_matrix1_equals_matrix2/run.sh diff --git a/tests/custom/permutations/basic/13/stdout.expected b/tests/custom/permutations/basic/0013_find_permutation_such_that_image_of_matrix1_equals_matrix2/stdout.expected similarity index 100% rename from tests/custom/permutations/basic/13/stdout.expected rename to tests/custom/permutations/basic/0013_find_permutation_such_that_image_of_matrix1_equals_matrix2/stdout.expected diff --git a/tests/custom/permutations/basic/14/permutation.essence b/tests/custom/permutations/basic/0014_find_matrix_such_that_swapping_any_index_pairs_becomes_lex_greater/permutation.essence similarity index 100% rename from tests/custom/permutations/basic/14/permutation.essence rename to tests/custom/permutations/basic/0014_find_matrix_such_that_swapping_any_index_pairs_becomes_lex_greater/permutation.essence diff --git a/tests/custom/permutations/basic/14/run.sh b/tests/custom/permutations/basic/0014_find_matrix_such_that_swapping_any_index_pairs_becomes_lex_greater/run.sh similarity index 100% rename from tests/custom/permutations/basic/14/run.sh rename to tests/custom/permutations/basic/0014_find_matrix_such_that_swapping_any_index_pairs_becomes_lex_greater/run.sh diff --git a/tests/custom/permutations/basic/14/stdout.expected b/tests/custom/permutations/basic/0014_find_matrix_such_that_swapping_any_index_pairs_becomes_lex_greater/stdout.expected similarity index 100% rename from tests/custom/permutations/basic/14/stdout.expected rename to tests/custom/permutations/basic/0014_find_matrix_such_that_swapping_any_index_pairs_becomes_lex_greater/stdout.expected diff --git a/tests/custom/permutations/basic/15/permutation.essence b/tests/custom/permutations/basic/0015_find_set_of_permuted_elements_of_matrix/permutation.essence similarity index 100% rename from tests/custom/permutations/basic/15/permutation.essence rename to tests/custom/permutations/basic/0015_find_set_of_permuted_elements_of_matrix/permutation.essence diff --git a/tests/custom/permutations/basic/15/run.sh b/tests/custom/permutations/basic/0015_find_set_of_permuted_elements_of_matrix/run.sh similarity index 100% rename from tests/custom/permutations/basic/15/run.sh rename to tests/custom/permutations/basic/0015_find_set_of_permuted_elements_of_matrix/run.sh diff --git a/tests/custom/permutations/basic/15/stdout.expected b/tests/custom/permutations/basic/0015_find_set_of_permuted_elements_of_matrix/stdout.expected similarity index 100% rename from tests/custom/permutations/basic/15/stdout.expected rename to tests/custom/permutations/basic/0015_find_set_of_permuted_elements_of_matrix/stdout.expected diff --git a/tests/custom/permutations/basic/16/permutation.essence b/tests/custom/permutations/basic/0016_find_permutation_such_that_image_is_identity_for_given_matrix/permutation.essence similarity index 100% rename from tests/custom/permutations/basic/16/permutation.essence rename to tests/custom/permutations/basic/0016_find_permutation_such_that_image_is_identity_for_given_matrix/permutation.essence diff --git a/tests/custom/permutations/basic/16/run.sh b/tests/custom/permutations/basic/0016_find_permutation_such_that_image_is_identity_for_given_matrix/run.sh similarity index 100% rename from tests/custom/permutations/basic/16/run.sh rename to tests/custom/permutations/basic/0016_find_permutation_such_that_image_is_identity_for_given_matrix/run.sh diff --git a/tests/custom/permutations/basic/16/stdout.expected b/tests/custom/permutations/basic/0016_find_permutation_such_that_image_is_identity_for_given_matrix/stdout.expected similarity index 100% rename from tests/custom/permutations/basic/16/stdout.expected rename to tests/custom/permutations/basic/0016_find_permutation_such_that_image_is_identity_for_given_matrix/stdout.expected diff --git a/tests/custom/permutations/basic/17/permutation.essence b/tests/custom/permutations/basic/0017_find_two_permutations_with_overlapping_domains_and_same_image_over_domain_union/permutation.essence similarity index 100% rename from tests/custom/permutations/basic/17/permutation.essence rename to tests/custom/permutations/basic/0017_find_two_permutations_with_overlapping_domains_and_same_image_over_domain_union/permutation.essence diff --git a/tests/custom/permutations/basic/17/run.sh b/tests/custom/permutations/basic/0017_find_two_permutations_with_overlapping_domains_and_same_image_over_domain_union/run.sh similarity index 100% rename from tests/custom/permutations/basic/17/run.sh rename to tests/custom/permutations/basic/0017_find_two_permutations_with_overlapping_domains_and_same_image_over_domain_union/run.sh diff --git a/tests/custom/permutations/basic/17/stdout.expected b/tests/custom/permutations/basic/0017_find_two_permutations_with_overlapping_domains_and_same_image_over_domain_union/stdout.expected similarity index 100% rename from tests/custom/permutations/basic/17/stdout.expected rename to tests/custom/permutations/basic/0017_find_two_permutations_with_overlapping_domains_and_same_image_over_domain_union/stdout.expected diff --git a/tests/custom/permutations/basic/18/permutation.essence b/tests/custom/permutations/basic/0018_find_matrix_lex_less_than_under_any_swap/permutation.essence similarity index 100% rename from tests/custom/permutations/basic/18/permutation.essence rename to tests/custom/permutations/basic/0018_find_matrix_lex_less_than_under_any_swap/permutation.essence diff --git a/tests/custom/permutations/basic/18/run.sh b/tests/custom/permutations/basic/0018_find_matrix_lex_less_than_under_any_swap/run.sh similarity index 100% rename from tests/custom/permutations/basic/18/run.sh rename to tests/custom/permutations/basic/0018_find_matrix_lex_less_than_under_any_swap/run.sh diff --git a/tests/custom/permutations/basic/18/stdout.expected b/tests/custom/permutations/basic/0018_find_matrix_lex_less_than_under_any_swap/stdout.expected similarity index 100% rename from tests/custom/permutations/basic/18/stdout.expected rename to tests/custom/permutations/basic/0018_find_matrix_lex_less_than_under_any_swap/stdout.expected diff --git a/tests/custom/permutations/basic/19/permutation.essence b/tests/custom/permutations/basic/0019_find_set_of_permutation_tuples_using_comprehension/permutation.essence similarity index 100% rename from tests/custom/permutations/basic/19/permutation.essence rename to tests/custom/permutations/basic/0019_find_set_of_permutation_tuples_using_comprehension/permutation.essence diff --git a/tests/custom/permutations/basic/19/run.sh b/tests/custom/permutations/basic/0019_find_set_of_permutation_tuples_using_comprehension/run.sh similarity index 100% rename from tests/custom/permutations/basic/19/run.sh rename to tests/custom/permutations/basic/0019_find_set_of_permutation_tuples_using_comprehension/run.sh diff --git a/tests/custom/permutations/basic/19/stdout.expected b/tests/custom/permutations/basic/0019_find_set_of_permutation_tuples_using_comprehension/stdout.expected similarity index 100% rename from tests/custom/permutations/basic/19/stdout.expected rename to tests/custom/permutations/basic/0019_find_set_of_permutation_tuples_using_comprehension/stdout.expected diff --git a/tests/custom/permutations/basic/20/permutation.essence b/tests/custom/permutations/basic/0020_find_permutation_inverse_using_comprehension/permutation.essence similarity index 100% rename from tests/custom/permutations/basic/20/permutation.essence rename to tests/custom/permutations/basic/0020_find_permutation_inverse_using_comprehension/permutation.essence diff --git a/tests/custom/permutations/basic/20/run.sh b/tests/custom/permutations/basic/0020_find_permutation_inverse_using_comprehension/run.sh similarity index 100% rename from tests/custom/permutations/basic/20/run.sh rename to tests/custom/permutations/basic/0020_find_permutation_inverse_using_comprehension/run.sh diff --git a/tests/custom/permutations/basic/20/stdout.expected b/tests/custom/permutations/basic/0020_find_permutation_inverse_using_comprehension/stdout.expected similarity index 100% rename from tests/custom/permutations/basic/20/stdout.expected rename to tests/custom/permutations/basic/0020_find_permutation_inverse_using_comprehension/stdout.expected diff --git a/tests/custom/permutations/basic/21/permutation.essence b/tests/custom/permutations/basic/0021_image_of_int_under_composition_of_two_given_permutations/permutation.essence similarity index 100% rename from tests/custom/permutations/basic/21/permutation.essence rename to tests/custom/permutations/basic/0021_image_of_int_under_composition_of_two_given_permutations/permutation.essence diff --git a/tests/custom/permutations/basic/21/permutation.param b/tests/custom/permutations/basic/0021_image_of_int_under_composition_of_two_given_permutations/permutation.param similarity index 100% rename from tests/custom/permutations/basic/21/permutation.param rename to tests/custom/permutations/basic/0021_image_of_int_under_composition_of_two_given_permutations/permutation.param diff --git a/tests/custom/permutations/basic/21/run.sh b/tests/custom/permutations/basic/0021_image_of_int_under_composition_of_two_given_permutations/run.sh similarity index 100% rename from tests/custom/permutations/basic/21/run.sh rename to tests/custom/permutations/basic/0021_image_of_int_under_composition_of_two_given_permutations/run.sh diff --git a/tests/custom/permutations/basic/21/stdout.expected b/tests/custom/permutations/basic/0021_image_of_int_under_composition_of_two_given_permutations/stdout.expected similarity index 100% rename from tests/custom/permutations/basic/21/stdout.expected rename to tests/custom/permutations/basic/0021_image_of_int_under_composition_of_two_given_permutations/stdout.expected diff --git a/tests/custom/permutations/basic/22/permutation.essence b/tests/custom/permutations/basic/0022_find_matrices_of_enum_x_y_such_that_y_lexless_than_x_under_any_index_swap/permutation.essence similarity index 100% rename from tests/custom/permutations/basic/22/permutation.essence rename to tests/custom/permutations/basic/0022_find_matrices_of_enum_x_y_such_that_y_lexless_than_x_under_any_index_swap/permutation.essence diff --git a/tests/custom/permutations/basic/22/permutation.param b/tests/custom/permutations/basic/0022_find_matrices_of_enum_x_y_such_that_y_lexless_than_x_under_any_index_swap/permutation.param similarity index 100% rename from tests/custom/permutations/basic/22/permutation.param rename to tests/custom/permutations/basic/0022_find_matrices_of_enum_x_y_such_that_y_lexless_than_x_under_any_index_swap/permutation.param diff --git a/tests/custom/permutations/basic/22/run.sh b/tests/custom/permutations/basic/0022_find_matrices_of_enum_x_y_such_that_y_lexless_than_x_under_any_index_swap/run.sh similarity index 100% rename from tests/custom/permutations/basic/22/run.sh rename to tests/custom/permutations/basic/0022_find_matrices_of_enum_x_y_such_that_y_lexless_than_x_under_any_index_swap/run.sh diff --git a/tests/custom/permutations/basic/22/stdout.expected b/tests/custom/permutations/basic/0022_find_matrices_of_enum_x_y_such_that_y_lexless_than_x_under_any_index_swap/stdout.expected similarity index 100% rename from tests/custom/permutations/basic/22/stdout.expected rename to tests/custom/permutations/basic/0022_find_matrices_of_enum_x_y_such_that_y_lexless_than_x_under_any_index_swap/stdout.expected diff --git a/tests/custom/permutations/basic/23/permutation.essence b/tests/custom/permutations/basic/0023_find_triples_x_y_such_that_y_lex_less_x_under_any_swap/permutation.essence similarity index 100% rename from tests/custom/permutations/basic/23/permutation.essence rename to tests/custom/permutations/basic/0023_find_triples_x_y_such_that_y_lex_less_x_under_any_swap/permutation.essence diff --git a/tests/custom/permutations/basic/23/permutation.param b/tests/custom/permutations/basic/0023_find_triples_x_y_such_that_y_lex_less_x_under_any_swap/permutation.param similarity index 100% rename from tests/custom/permutations/basic/23/permutation.param rename to tests/custom/permutations/basic/0023_find_triples_x_y_such_that_y_lex_less_x_under_any_swap/permutation.param diff --git a/tests/custom/permutations/basic/23/run.sh b/tests/custom/permutations/basic/0023_find_triples_x_y_such_that_y_lex_less_x_under_any_swap/run.sh similarity index 100% rename from tests/custom/permutations/basic/23/run.sh rename to tests/custom/permutations/basic/0023_find_triples_x_y_such_that_y_lex_less_x_under_any_swap/run.sh diff --git a/tests/custom/permutations/basic/23/stdout.expected b/tests/custom/permutations/basic/0023_find_triples_x_y_such_that_y_lex_less_x_under_any_swap/stdout.expected similarity index 100% rename from tests/custom/permutations/basic/23/stdout.expected rename to tests/custom/permutations/basic/0023_find_triples_x_y_such_that_y_lex_less_x_under_any_swap/stdout.expected diff --git a/tests/custom/permutations/basic/24/permutation.essence b/tests/custom/permutations/basic/0024_find_sets_x_y_such_that_y_lexless_x_under_any_swap/permutation.essence similarity index 100% rename from tests/custom/permutations/basic/24/permutation.essence rename to tests/custom/permutations/basic/0024_find_sets_x_y_such_that_y_lexless_x_under_any_swap/permutation.essence diff --git a/tests/custom/permutations/basic/24/permutation.param b/tests/custom/permutations/basic/0024_find_sets_x_y_such_that_y_lexless_x_under_any_swap/permutation.param similarity index 100% rename from tests/custom/permutations/basic/24/permutation.param rename to tests/custom/permutations/basic/0024_find_sets_x_y_such_that_y_lexless_x_under_any_swap/permutation.param diff --git a/tests/custom/permutations/basic/24/run.sh b/tests/custom/permutations/basic/0024_find_sets_x_y_such_that_y_lexless_x_under_any_swap/run.sh similarity index 100% rename from tests/custom/permutations/basic/24/run.sh rename to tests/custom/permutations/basic/0024_find_sets_x_y_such_that_y_lexless_x_under_any_swap/run.sh diff --git a/tests/custom/permutations/basic/24/stdout.expected b/tests/custom/permutations/basic/0024_find_sets_x_y_such_that_y_lexless_x_under_any_swap/stdout.expected similarity index 100% rename from tests/custom/permutations/basic/24/stdout.expected rename to tests/custom/permutations/basic/0024_find_sets_x_y_such_that_y_lexless_x_under_any_swap/stdout.expected diff --git a/tests/custom/permutations/basic/25/permutation.essence b/tests/custom/permutations/basic/0025_find_permutation_and_matrices_x_y_such_that_image_x_eq_y/permutation.essence similarity index 100% rename from tests/custom/permutations/basic/25/permutation.essence rename to tests/custom/permutations/basic/0025_find_permutation_and_matrices_x_y_such_that_image_x_eq_y/permutation.essence diff --git a/tests/custom/permutations/basic/25/permutation.param b/tests/custom/permutations/basic/0025_find_permutation_and_matrices_x_y_such_that_image_x_eq_y/permutation.param similarity index 100% rename from tests/custom/permutations/basic/25/permutation.param rename to tests/custom/permutations/basic/0025_find_permutation_and_matrices_x_y_such_that_image_x_eq_y/permutation.param diff --git a/tests/custom/permutations/basic/25/run.sh b/tests/custom/permutations/basic/0025_find_permutation_and_matrices_x_y_such_that_image_x_eq_y/run.sh similarity index 100% rename from tests/custom/permutations/basic/25/run.sh rename to tests/custom/permutations/basic/0025_find_permutation_and_matrices_x_y_such_that_image_x_eq_y/run.sh diff --git a/tests/custom/permutations/basic/25/stdout.expected b/tests/custom/permutations/basic/0025_find_permutation_and_matrices_x_y_such_that_image_x_eq_y/stdout.expected similarity index 100% rename from tests/custom/permutations/basic/25/stdout.expected rename to tests/custom/permutations/basic/0025_find_permutation_and_matrices_x_y_such_that_image_x_eq_y/stdout.expected From 91b1a1f9119994f2c580960925242446a7f3d267 Mon Sep 17 00:00:00 2001 From: Fraser Dunlop Date: Mon, 19 Nov 2018 13:10:33 +0000 Subject: [PATCH 022/229] Renamed permutation tests --- .../permutation.essence | 0 .../permutation.param | 0 .../run.sh | 0 .../stdout.expected | 0 .../permutation.essence | 0 .../run.sh | 0 .../stdout.expected | 0 .../permutation.essence | 0 .../run.sh | 0 .../stdout.expected | 0 .../permutation.essence | 0 .../run.sh | 0 .../permutation.essence | 0 .../permutation.param | 0 .../run.sh | 0 .../permutation.essence | 10 +------- .../permutation.param | 0 .../run.sh | 0 .../permutation.essence | 0 .../permutation.param | 0 .../run.sh | 0 .../permutation.essence | 0 .../permutation.param | 0 .../run.sh | 0 .../stdout.expected | 0 .../permutation.essence | 0 .../permutation.param | 0 .../run.sh | 0 .../permutation.essence | 10 ++++++++ .../permutation.param | 0 .../run.sh | 0 .../permutations/basic/35/permutation.essence | 23 ------------------- 32 files changed, 11 insertions(+), 32 deletions(-) rename tests/custom/permutations/basic/{26 => 0026_find_matrices_of_enums_x_y_such_that_y_image_x_under_p}/permutation.essence (100%) rename tests/custom/permutations/basic/{26 => 0026_find_matrices_of_enums_x_y_such_that_y_image_x_under_p}/permutation.param (100%) rename tests/custom/permutations/basic/{26 => 0026_find_matrices_of_enums_x_y_such_that_y_image_x_under_p}/run.sh (100%) rename tests/custom/permutations/basic/{26 => 0026_find_matrices_of_enums_x_y_such_that_y_image_x_under_p}/stdout.expected (100%) rename tests/custom/permutations/basic/{27 => 0027_find_sets_of_enum_x_y_such_that_y_image_x_under_p}/permutation.essence (100%) rename tests/custom/permutations/basic/{27 => 0027_find_sets_of_enum_x_y_such_that_y_image_x_under_p}/run.sh (100%) rename tests/custom/permutations/basic/{27 => 0027_find_sets_of_enum_x_y_such_that_y_image_x_under_p}/stdout.expected (100%) rename tests/custom/permutations/basic/{28 => 0028_find_sets_of_enum_x_y_such_that_y_image_x_under_p}/permutation.essence (100%) rename tests/custom/permutations/basic/{28 => 0028_find_sets_of_enum_x_y_such_that_y_image_x_under_p}/run.sh (100%) rename tests/custom/permutations/basic/{28 => 0028_find_sets_of_enum_x_y_such_that_y_image_x_under_p}/stdout.expected (100%) rename tests/custom/permutations/basic/{29 => 0029_find_relations_x_y_such_that_y_image_x_under_p}/permutation.essence (100%) rename tests/custom/permutations/basic/{29 => 0029_find_relations_x_y_such_that_y_image_x_under_p}/run.sh (100%) rename tests/custom/permutations/basic/{30 => 0030_find_permutation_equal_given_permutation}/permutation.essence (100%) rename tests/custom/permutations/basic/{30 => 0030_find_permutation_equal_given_permutation}/permutation.param (100%) rename tests/custom/permutations/basic/{30 => 0030_find_permutation_equal_given_permutation}/run.sh (100%) rename tests/custom/permutations/basic/{31 => 0031_find_matrix_lexless_indices_swapped_in_comprehension}/permutation.essence (64%) rename tests/custom/permutations/basic/{31 => 0031_find_matrix_lexless_indices_swapped_in_comprehension}/permutation.param (100%) rename tests/custom/permutations/basic/{31 => 0031_find_matrix_lexless_indices_swapped_in_comprehension}/run.sh (100%) rename tests/custom/permutations/basic/{32 => 0032_find_sets_of_ints_such_that_tuple_of_sets_lexless_any_int_swapped_tuple}/permutation.essence (100%) rename tests/custom/permutations/basic/{32 => 0032_find_sets_of_ints_such_that_tuple_of_sets_lexless_any_int_swapped_tuple}/permutation.param (100%) rename tests/custom/permutations/basic/{32 => 0032_find_sets_of_ints_such_that_tuple_of_sets_lexless_any_int_swapped_tuple}/run.sh (100%) rename tests/custom/permutations/basic/{33 => 0033_find_matrixes_of_enum_such_that_tuple_of_matrices_lexless_any_int_swapped_tuple}/permutation.essence (100%) rename tests/custom/permutations/basic/{33 => 0033_find_matrixes_of_enum_such_that_tuple_of_matrices_lexless_any_int_swapped_tuple}/permutation.param (100%) rename tests/custom/permutations/basic/{33 => 0033_find_matrixes_of_enum_such_that_tuple_of_matrices_lexless_any_int_swapped_tuple}/run.sh (100%) rename tests/custom/permutations/basic/{33 => 0033_find_matrixes_of_enum_such_that_tuple_of_matrices_lexless_any_int_swapped_tuple}/stdout.expected (100%) rename tests/custom/permutations/basic/{34 => 0034_image_of_empty_permutation}/permutation.essence (100%) rename tests/custom/permutations/basic/{34 => 0034_image_of_empty_permutation}/permutation.param (100%) rename tests/custom/permutations/basic/{34 => 0034_image_of_empty_permutation}/run.sh (100%) create mode 100644 tests/custom/permutations/basic/0035_permutation_of_enum_is_identity_for_integers/permutation.essence rename tests/custom/permutations/basic/{35 => 0035_permutation_of_enum_is_identity_for_integers}/permutation.param (100%) rename tests/custom/permutations/basic/{35 => 0035_permutation_of_enum_is_identity_for_integers}/run.sh (100%) delete mode 100644 tests/custom/permutations/basic/35/permutation.essence diff --git a/tests/custom/permutations/basic/26/permutation.essence b/tests/custom/permutations/basic/0026_find_matrices_of_enums_x_y_such_that_y_image_x_under_p/permutation.essence similarity index 100% rename from tests/custom/permutations/basic/26/permutation.essence rename to tests/custom/permutations/basic/0026_find_matrices_of_enums_x_y_such_that_y_image_x_under_p/permutation.essence diff --git a/tests/custom/permutations/basic/26/permutation.param b/tests/custom/permutations/basic/0026_find_matrices_of_enums_x_y_such_that_y_image_x_under_p/permutation.param similarity index 100% rename from tests/custom/permutations/basic/26/permutation.param rename to tests/custom/permutations/basic/0026_find_matrices_of_enums_x_y_such_that_y_image_x_under_p/permutation.param diff --git a/tests/custom/permutations/basic/26/run.sh b/tests/custom/permutations/basic/0026_find_matrices_of_enums_x_y_such_that_y_image_x_under_p/run.sh similarity index 100% rename from tests/custom/permutations/basic/26/run.sh rename to tests/custom/permutations/basic/0026_find_matrices_of_enums_x_y_such_that_y_image_x_under_p/run.sh diff --git a/tests/custom/permutations/basic/26/stdout.expected b/tests/custom/permutations/basic/0026_find_matrices_of_enums_x_y_such_that_y_image_x_under_p/stdout.expected similarity index 100% rename from tests/custom/permutations/basic/26/stdout.expected rename to tests/custom/permutations/basic/0026_find_matrices_of_enums_x_y_such_that_y_image_x_under_p/stdout.expected diff --git a/tests/custom/permutations/basic/27/permutation.essence b/tests/custom/permutations/basic/0027_find_sets_of_enum_x_y_such_that_y_image_x_under_p/permutation.essence similarity index 100% rename from tests/custom/permutations/basic/27/permutation.essence rename to tests/custom/permutations/basic/0027_find_sets_of_enum_x_y_such_that_y_image_x_under_p/permutation.essence diff --git a/tests/custom/permutations/basic/27/run.sh b/tests/custom/permutations/basic/0027_find_sets_of_enum_x_y_such_that_y_image_x_under_p/run.sh similarity index 100% rename from tests/custom/permutations/basic/27/run.sh rename to tests/custom/permutations/basic/0027_find_sets_of_enum_x_y_such_that_y_image_x_under_p/run.sh diff --git a/tests/custom/permutations/basic/27/stdout.expected b/tests/custom/permutations/basic/0027_find_sets_of_enum_x_y_such_that_y_image_x_under_p/stdout.expected similarity index 100% rename from tests/custom/permutations/basic/27/stdout.expected rename to tests/custom/permutations/basic/0027_find_sets_of_enum_x_y_such_that_y_image_x_under_p/stdout.expected diff --git a/tests/custom/permutations/basic/28/permutation.essence b/tests/custom/permutations/basic/0028_find_sets_of_enum_x_y_such_that_y_image_x_under_p/permutation.essence similarity index 100% rename from tests/custom/permutations/basic/28/permutation.essence rename to tests/custom/permutations/basic/0028_find_sets_of_enum_x_y_such_that_y_image_x_under_p/permutation.essence diff --git a/tests/custom/permutations/basic/28/run.sh b/tests/custom/permutations/basic/0028_find_sets_of_enum_x_y_such_that_y_image_x_under_p/run.sh similarity index 100% rename from tests/custom/permutations/basic/28/run.sh rename to tests/custom/permutations/basic/0028_find_sets_of_enum_x_y_such_that_y_image_x_under_p/run.sh diff --git a/tests/custom/permutations/basic/28/stdout.expected b/tests/custom/permutations/basic/0028_find_sets_of_enum_x_y_such_that_y_image_x_under_p/stdout.expected similarity index 100% rename from tests/custom/permutations/basic/28/stdout.expected rename to tests/custom/permutations/basic/0028_find_sets_of_enum_x_y_such_that_y_image_x_under_p/stdout.expected diff --git a/tests/custom/permutations/basic/29/permutation.essence b/tests/custom/permutations/basic/0029_find_relations_x_y_such_that_y_image_x_under_p/permutation.essence similarity index 100% rename from tests/custom/permutations/basic/29/permutation.essence rename to tests/custom/permutations/basic/0029_find_relations_x_y_such_that_y_image_x_under_p/permutation.essence diff --git a/tests/custom/permutations/basic/29/run.sh b/tests/custom/permutations/basic/0029_find_relations_x_y_such_that_y_image_x_under_p/run.sh similarity index 100% rename from tests/custom/permutations/basic/29/run.sh rename to tests/custom/permutations/basic/0029_find_relations_x_y_such_that_y_image_x_under_p/run.sh diff --git a/tests/custom/permutations/basic/30/permutation.essence b/tests/custom/permutations/basic/0030_find_permutation_equal_given_permutation/permutation.essence similarity index 100% rename from tests/custom/permutations/basic/30/permutation.essence rename to tests/custom/permutations/basic/0030_find_permutation_equal_given_permutation/permutation.essence diff --git a/tests/custom/permutations/basic/30/permutation.param b/tests/custom/permutations/basic/0030_find_permutation_equal_given_permutation/permutation.param similarity index 100% rename from tests/custom/permutations/basic/30/permutation.param rename to tests/custom/permutations/basic/0030_find_permutation_equal_given_permutation/permutation.param diff --git a/tests/custom/permutations/basic/30/run.sh b/tests/custom/permutations/basic/0030_find_permutation_equal_given_permutation/run.sh similarity index 100% rename from tests/custom/permutations/basic/30/run.sh rename to tests/custom/permutations/basic/0030_find_permutation_equal_given_permutation/run.sh diff --git a/tests/custom/permutations/basic/31/permutation.essence b/tests/custom/permutations/basic/0031_find_matrix_lexless_indices_swapped_in_comprehension/permutation.essence similarity index 64% rename from tests/custom/permutations/basic/31/permutation.essence rename to tests/custom/permutations/basic/0031_find_matrix_lexless_indices_swapped_in_comprehension/permutation.essence index e6c5883f97..3c65b84b3b 100644 --- a/tests/custom/permutations/basic/31/permutation.essence +++ b/tests/custom/permutations/basic/0031_find_matrix_lexless_indices_swapped_in_comprehension/permutation.essence @@ -1,12 +1,4 @@ -find m : -matrix -indexed -by [int(1..9)] -of -set of -int(1) - - +find m : matrix indexed by [int(1..9)] of set of int(1) such that forAll i, j : int(1..9) . diff --git a/tests/custom/permutations/basic/31/permutation.param b/tests/custom/permutations/basic/0031_find_matrix_lexless_indices_swapped_in_comprehension/permutation.param similarity index 100% rename from tests/custom/permutations/basic/31/permutation.param rename to tests/custom/permutations/basic/0031_find_matrix_lexless_indices_swapped_in_comprehension/permutation.param diff --git a/tests/custom/permutations/basic/31/run.sh b/tests/custom/permutations/basic/0031_find_matrix_lexless_indices_swapped_in_comprehension/run.sh similarity index 100% rename from tests/custom/permutations/basic/31/run.sh rename to tests/custom/permutations/basic/0031_find_matrix_lexless_indices_swapped_in_comprehension/run.sh diff --git a/tests/custom/permutations/basic/32/permutation.essence b/tests/custom/permutations/basic/0032_find_sets_of_ints_such_that_tuple_of_sets_lexless_any_int_swapped_tuple/permutation.essence similarity index 100% rename from tests/custom/permutations/basic/32/permutation.essence rename to tests/custom/permutations/basic/0032_find_sets_of_ints_such_that_tuple_of_sets_lexless_any_int_swapped_tuple/permutation.essence diff --git a/tests/custom/permutations/basic/32/permutation.param b/tests/custom/permutations/basic/0032_find_sets_of_ints_such_that_tuple_of_sets_lexless_any_int_swapped_tuple/permutation.param similarity index 100% rename from tests/custom/permutations/basic/32/permutation.param rename to tests/custom/permutations/basic/0032_find_sets_of_ints_such_that_tuple_of_sets_lexless_any_int_swapped_tuple/permutation.param diff --git a/tests/custom/permutations/basic/32/run.sh b/tests/custom/permutations/basic/0032_find_sets_of_ints_such_that_tuple_of_sets_lexless_any_int_swapped_tuple/run.sh similarity index 100% rename from tests/custom/permutations/basic/32/run.sh rename to tests/custom/permutations/basic/0032_find_sets_of_ints_such_that_tuple_of_sets_lexless_any_int_swapped_tuple/run.sh diff --git a/tests/custom/permutations/basic/33/permutation.essence b/tests/custom/permutations/basic/0033_find_matrixes_of_enum_such_that_tuple_of_matrices_lexless_any_int_swapped_tuple/permutation.essence similarity index 100% rename from tests/custom/permutations/basic/33/permutation.essence rename to tests/custom/permutations/basic/0033_find_matrixes_of_enum_such_that_tuple_of_matrices_lexless_any_int_swapped_tuple/permutation.essence diff --git a/tests/custom/permutations/basic/33/permutation.param b/tests/custom/permutations/basic/0033_find_matrixes_of_enum_such_that_tuple_of_matrices_lexless_any_int_swapped_tuple/permutation.param similarity index 100% rename from tests/custom/permutations/basic/33/permutation.param rename to tests/custom/permutations/basic/0033_find_matrixes_of_enum_such_that_tuple_of_matrices_lexless_any_int_swapped_tuple/permutation.param diff --git a/tests/custom/permutations/basic/33/run.sh b/tests/custom/permutations/basic/0033_find_matrixes_of_enum_such_that_tuple_of_matrices_lexless_any_int_swapped_tuple/run.sh similarity index 100% rename from tests/custom/permutations/basic/33/run.sh rename to tests/custom/permutations/basic/0033_find_matrixes_of_enum_such_that_tuple_of_matrices_lexless_any_int_swapped_tuple/run.sh diff --git a/tests/custom/permutations/basic/33/stdout.expected b/tests/custom/permutations/basic/0033_find_matrixes_of_enum_such_that_tuple_of_matrices_lexless_any_int_swapped_tuple/stdout.expected similarity index 100% rename from tests/custom/permutations/basic/33/stdout.expected rename to tests/custom/permutations/basic/0033_find_matrixes_of_enum_such_that_tuple_of_matrices_lexless_any_int_swapped_tuple/stdout.expected diff --git a/tests/custom/permutations/basic/34/permutation.essence b/tests/custom/permutations/basic/0034_image_of_empty_permutation/permutation.essence similarity index 100% rename from tests/custom/permutations/basic/34/permutation.essence rename to tests/custom/permutations/basic/0034_image_of_empty_permutation/permutation.essence diff --git a/tests/custom/permutations/basic/34/permutation.param b/tests/custom/permutations/basic/0034_image_of_empty_permutation/permutation.param similarity index 100% rename from tests/custom/permutations/basic/34/permutation.param rename to tests/custom/permutations/basic/0034_image_of_empty_permutation/permutation.param diff --git a/tests/custom/permutations/basic/34/run.sh b/tests/custom/permutations/basic/0034_image_of_empty_permutation/run.sh similarity index 100% rename from tests/custom/permutations/basic/34/run.sh rename to tests/custom/permutations/basic/0034_image_of_empty_permutation/run.sh diff --git a/tests/custom/permutations/basic/0035_permutation_of_enum_is_identity_for_integers/permutation.essence b/tests/custom/permutations/basic/0035_permutation_of_enum_is_identity_for_integers/permutation.essence new file mode 100644 index 0000000000..e9875f044a --- /dev/null +++ b/tests/custom/permutations/basic/0035_permutation_of_enum_is_identity_for_integers/permutation.essence @@ -0,0 +1,10 @@ +letting e be new type enum {E1, E2, E3, E4} + +find s : permutationof e + +such that + permute(s, E1)= E2, + forAll i : int(-10..10) . + permute(s, i) = i + + diff --git a/tests/custom/permutations/basic/35/permutation.param b/tests/custom/permutations/basic/0035_permutation_of_enum_is_identity_for_integers/permutation.param similarity index 100% rename from tests/custom/permutations/basic/35/permutation.param rename to tests/custom/permutations/basic/0035_permutation_of_enum_is_identity_for_integers/permutation.param diff --git a/tests/custom/permutations/basic/35/run.sh b/tests/custom/permutations/basic/0035_permutation_of_enum_is_identity_for_integers/run.sh similarity index 100% rename from tests/custom/permutations/basic/35/run.sh rename to tests/custom/permutations/basic/0035_permutation_of_enum_is_identity_for_integers/run.sh diff --git a/tests/custom/permutations/basic/35/permutation.essence b/tests/custom/permutations/basic/35/permutation.essence deleted file mode 100644 index 0bd7a2d49b..0000000000 --- a/tests/custom/permutations/basic/35/permutation.essence +++ /dev/null @@ -1,23 +0,0 @@ -letting e -be -new type -enum {E1, E2, E3, E4} - - - -find s : permutation -of e - - - -such -that permute(s, E1) -= E2, - - - -forAll i : -int(-10..10). permute(s, i) -= i - - From 1a74a78ed655fd229fefae213faedad2d75b4e9b Mon Sep 17 00:00:00 2001 From: Fraser Dunlop Date: Tue, 20 Nov 2018 11:32:46 +0000 Subject: [PATCH 023/229] More tests from Chris --- .../permutation.essence | 2 +- .../run.sh | 2 +- .../stdout.expected | 28 +++++ .../permutation.essence | 19 +++ .../0036_big_test_of_enums_in_matrices/run.sh | 3 + .../stdout.expected | 114 ++++++++++++++++++ .../permutation.essence | 12 ++ .../run.sh | 3 + .../stdout.expected | 64 ++++++++++ .../permutation.essence | 11 ++ .../run.sh | 3 + .../stdout.expected | 64 ++++++++++ 12 files changed, 323 insertions(+), 2 deletions(-) create mode 100644 tests/custom/permutations/basic/0035_permutation_of_enum_is_identity_for_integers/stdout.expected create mode 100644 tests/custom/permutations/basic/0036_big_test_of_enums_in_matrices/permutation.essence create mode 100755 tests/custom/permutations/basic/0036_big_test_of_enums_in_matrices/run.sh create mode 100644 tests/custom/permutations/basic/0036_big_test_of_enums_in_matrices/stdout.expected create mode 100644 tests/custom/permutations/basic/0037_matrices_of_enums_indexed_by_enums/permutation.essence create mode 100755 tests/custom/permutations/basic/0037_matrices_of_enums_indexed_by_enums/run.sh create mode 100644 tests/custom/permutations/basic/0037_matrices_of_enums_indexed_by_enums/stdout.expected create mode 100644 tests/custom/permutations/basic/0038_matricies_of_tuples_of_enums_indexed_by_enums/permutation.essence create mode 100755 tests/custom/permutations/basic/0038_matricies_of_tuples_of_enums_indexed_by_enums/run.sh create mode 100644 tests/custom/permutations/basic/0038_matricies_of_tuples_of_enums_indexed_by_enums/stdout.expected diff --git a/tests/custom/permutations/basic/0035_permutation_of_enum_is_identity_for_integers/permutation.essence b/tests/custom/permutations/basic/0035_permutation_of_enum_is_identity_for_integers/permutation.essence index e9875f044a..7e6c0c0ceb 100644 --- a/tests/custom/permutations/basic/0035_permutation_of_enum_is_identity_for_integers/permutation.essence +++ b/tests/custom/permutations/basic/0035_permutation_of_enum_is_identity_for_integers/permutation.essence @@ -1,6 +1,6 @@ letting e be new type enum {E1, E2, E3, E4} -find s : permutationof e +find s : permutation of e such that permute(s, E1)= E2, diff --git a/tests/custom/permutations/basic/0035_permutation_of_enum_is_identity_for_integers/run.sh b/tests/custom/permutations/basic/0035_permutation_of_enum_is_identity_for_integers/run.sh index a1691af90c..3c60e3f90e 100755 --- a/tests/custom/permutations/basic/0035_permutation_of_enum_is_identity_for_integers/run.sh +++ b/tests/custom/permutations/basic/0035_permutation_of_enum_is_identity_for_integers/run.sh @@ -1,3 +1,3 @@ -conjure solve *.essence +conjure solve *.essence --number-of-solutions=10 cat conjure-output/*.solution rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/basic/0035_permutation_of_enum_is_identity_for_integers/stdout.expected b/tests/custom/permutations/basic/0035_permutation_of_enum_is_identity_for_integers/stdout.expected new file mode 100644 index 0000000000..22c4c0a298 --- /dev/null +++ b/tests/custom/permutations/basic/0035_permutation_of_enum_is_identity_for_integers/stdout.expected @@ -0,0 +1,28 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Copying solution to: permutation-000001.solution +Copying solution to: permutation-000002.solution +Copying solution to: permutation-000003.solution +Copying solution to: permutation-000004.solution +Copying solution to: permutation-000005.solution +Copying solution to: permutation-000006.solution +language Essence 1.3 + +letting s be permutation((E1, E2)) +language Essence 1.3 + +letting s be permutation((E1, E2), (E3, E4)) +language Essence 1.3 + +letting s be permutation((E1, E2, E3)) +language Essence 1.3 + +letting s be permutation((E1, E2, E3, E4)) +language Essence 1.3 + +letting s be permutation((E1, E2, E4, E3)) +language Essence 1.3 + +letting s be permutation((E1, E2, E4)) diff --git a/tests/custom/permutations/basic/0036_big_test_of_enums_in_matrices/permutation.essence b/tests/custom/permutations/basic/0036_big_test_of_enums_in_matrices/permutation.essence new file mode 100644 index 0000000000..d20443d51b --- /dev/null +++ b/tests/custom/permutations/basic/0036_big_test_of_enums_in_matrices/permutation.essence @@ -0,0 +1,19 @@ +letting e be new type enum {E1, E2, E3, E4} + +find s,t: permutation of e +find m1 : matrix indexed by [e] of int(1..4) +find m2 : matrix indexed by [e] of int(1..4) +find n1 : matrix indexed by [int(1..2)] of e +find n2 : matrix indexed by [int(1..2)] of e +find x1 : matrix indexed by [e] of e +find x2 : matrix indexed by [e] of e + +such that + permute(s, m1) = m2 + , permute(s, n1) = n2 + , permute(s, x1) = x2 + , forAll i : e . + permute(s, i) != i + , allDiff(m1), allDiff(n1), allDiff(x1) + , x1[E1]=E3 + diff --git a/tests/custom/permutations/basic/0036_big_test_of_enums_in_matrices/run.sh b/tests/custom/permutations/basic/0036_big_test_of_enums_in_matrices/run.sh new file mode 100755 index 0000000000..3c60e3f90e --- /dev/null +++ b/tests/custom/permutations/basic/0036_big_test_of_enums_in_matrices/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence --number-of-solutions=10 +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/basic/0036_big_test_of_enums_in_matrices/stdout.expected b/tests/custom/permutations/basic/0036_big_test_of_enums_in_matrices/stdout.expected new file mode 100644 index 0000000000..fe2f448795 --- /dev/null +++ b/tests/custom/permutations/basic/0036_big_test_of_enums_in_matrices/stdout.expected @@ -0,0 +1,114 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Copying solution to: permutation-000001.solution +Copying solution to: permutation-000002.solution +Copying solution to: permutation-000003.solution +Copying solution to: permutation-000004.solution +Copying solution to: permutation-000005.solution +Copying solution to: permutation-000006.solution +Copying solution to: permutation-000007.solution +Copying solution to: permutation-000008.solution +Copying solution to: permutation-000009.solution +Copying solution to: permutation-000010.solution +language Essence 1.3 + +letting m1 be [1, 2, 3, 4; int(1..4)] +letting m2 be [2, 1, 4, 3; int(1..4)] +letting n1 be [E1, E2; int(1..2)] +letting n2 be [E2, E1; int(1..2)] +letting s be permutation((E1, E2), (E3, E4)) +letting t be permutation() +letting x1 be [E3, E1, E2, E4; int(1..4)] +letting x2 be [E2, E4, E3, E1; int(1..4)] +language Essence 1.3 + +letting m1 be [1, 2, 3, 4; int(1..4)] +letting m2 be [2, 1, 4, 3; int(1..4)] +letting n1 be [E1, E2; int(1..2)] +letting n2 be [E2, E1; int(1..2)] +letting s be permutation((E1, E2), (E3, E4)) +letting t be permutation() +letting x1 be [E3, E1, E4, E2; int(1..4)] +letting x2 be [E2, E4, E1, E3; int(1..4)] +language Essence 1.3 + +letting m1 be [1, 2, 3, 4; int(1..4)] +letting m2 be [2, 1, 4, 3; int(1..4)] +letting n1 be [E1, E2; int(1..2)] +letting n2 be [E2, E1; int(1..2)] +letting s be permutation((E1, E2), (E3, E4)) +letting t be permutation() +letting x1 be [E3, E2, E1, E4; int(1..4)] +letting x2 be [E1, E4, E3, E2; int(1..4)] +language Essence 1.3 + +letting m1 be [1, 2, 3, 4; int(1..4)] +letting m2 be [2, 1, 4, 3; int(1..4)] +letting n1 be [E1, E2; int(1..2)] +letting n2 be [E2, E1; int(1..2)] +letting s be permutation((E1, E2), (E3, E4)) +letting t be permutation() +letting x1 be [E3, E2, E4, E1; int(1..4)] +letting x2 be [E1, E4, E2, E3; int(1..4)] +language Essence 1.3 + +letting m1 be [1, 2, 3, 4; int(1..4)] +letting m2 be [2, 1, 4, 3; int(1..4)] +letting n1 be [E1, E2; int(1..2)] +letting n2 be [E2, E1; int(1..2)] +letting s be permutation((E1, E2), (E3, E4)) +letting t be permutation() +letting x1 be [E3, E4, E1, E2; int(1..4)] +letting x2 be [E3, E4, E1, E2; int(1..4)] +language Essence 1.3 + +letting m1 be [1, 2, 3, 4; int(1..4)] +letting m2 be [2, 1, 4, 3; int(1..4)] +letting n1 be [E1, E2; int(1..2)] +letting n2 be [E2, E1; int(1..2)] +letting s be permutation((E1, E2), (E3, E4)) +letting t be permutation() +letting x1 be [E3, E4, E2, E1; int(1..4)] +letting x2 be [E3, E4, E2, E1; int(1..4)] +language Essence 1.3 + +letting m1 be [1, 2, 3, 4; int(1..4)] +letting m2 be [2, 1, 4, 3; int(1..4)] +letting n1 be [E1, E3; int(1..2)] +letting n2 be [E2, E4; int(1..2)] +letting s be permutation((E1, E2), (E3, E4)) +letting t be permutation() +letting x1 be [E3, E1, E2, E4; int(1..4)] +letting x2 be [E2, E4, E3, E1; int(1..4)] +language Essence 1.3 + +letting m1 be [1, 2, 3, 4; int(1..4)] +letting m2 be [2, 1, 4, 3; int(1..4)] +letting n1 be [E1, E3; int(1..2)] +letting n2 be [E2, E4; int(1..2)] +letting s be permutation((E1, E2), (E3, E4)) +letting t be permutation() +letting x1 be [E3, E1, E4, E2; int(1..4)] +letting x2 be [E2, E4, E1, E3; int(1..4)] +language Essence 1.3 + +letting m1 be [1, 2, 3, 4; int(1..4)] +letting m2 be [2, 1, 4, 3; int(1..4)] +letting n1 be [E1, E3; int(1..2)] +letting n2 be [E2, E4; int(1..2)] +letting s be permutation((E1, E2), (E3, E4)) +letting t be permutation() +letting x1 be [E3, E2, E1, E4; int(1..4)] +letting x2 be [E1, E4, E3, E2; int(1..4)] +language Essence 1.3 + +letting m1 be [1, 2, 3, 4; int(1..4)] +letting m2 be [2, 1, 4, 3; int(1..4)] +letting n1 be [E1, E3; int(1..2)] +letting n2 be [E2, E4; int(1..2)] +letting s be permutation((E1, E2), (E3, E4)) +letting t be permutation() +letting x1 be [E3, E2, E4, E1; int(1..4)] +letting x2 be [E1, E4, E2, E3; int(1..4)] diff --git a/tests/custom/permutations/basic/0037_matrices_of_enums_indexed_by_enums/permutation.essence b/tests/custom/permutations/basic/0037_matrices_of_enums_indexed_by_enums/permutation.essence new file mode 100644 index 0000000000..5f0c7770e7 --- /dev/null +++ b/tests/custom/permutations/basic/0037_matrices_of_enums_indexed_by_enums/permutation.essence @@ -0,0 +1,12 @@ +letting e be new type enum {E1, E2, E3, E4} + +find s: permutation of e +find x1 : matrix indexed by [e] of e +find x2 : matrix indexed by [e] of e + +such that + forAll i : e . + permute(s,i) != i + , permute(s, x1) = x2 + , x1 != x2 + diff --git a/tests/custom/permutations/basic/0037_matrices_of_enums_indexed_by_enums/run.sh b/tests/custom/permutations/basic/0037_matrices_of_enums_indexed_by_enums/run.sh new file mode 100755 index 0000000000..3c60e3f90e --- /dev/null +++ b/tests/custom/permutations/basic/0037_matrices_of_enums_indexed_by_enums/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence --number-of-solutions=10 +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/basic/0037_matrices_of_enums_indexed_by_enums/stdout.expected b/tests/custom/permutations/basic/0037_matrices_of_enums_indexed_by_enums/stdout.expected new file mode 100644 index 0000000000..e9a6a9a1e9 --- /dev/null +++ b/tests/custom/permutations/basic/0037_matrices_of_enums_indexed_by_enums/stdout.expected @@ -0,0 +1,64 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Copying solution to: permutation-000001.solution +Copying solution to: permutation-000002.solution +Copying solution to: permutation-000003.solution +Copying solution to: permutation-000004.solution +Copying solution to: permutation-000005.solution +Copying solution to: permutation-000006.solution +Copying solution to: permutation-000007.solution +Copying solution to: permutation-000008.solution +Copying solution to: permutation-000009.solution +Copying solution to: permutation-000010.solution +language Essence 1.3 + +letting s be permutation((E1, E2), (E3, E4)) +letting x1 be [E1, E1, E1, E1; int(1..4)] +letting x2 be [E2, E2, E2, E2; int(1..4)] +language Essence 1.3 + +letting s be permutation((E1, E2), (E3, E4)) +letting x1 be [E1, E1, E1, E2; int(1..4)] +letting x2 be [E2, E2, E1, E2; int(1..4)] +language Essence 1.3 + +letting s be permutation((E1, E2), (E3, E4)) +letting x1 be [E1, E1, E1, E3; int(1..4)] +letting x2 be [E2, E2, E4, E2; int(1..4)] +language Essence 1.3 + +letting s be permutation((E1, E2), (E3, E4)) +letting x1 be [E1, E1, E1, E4; int(1..4)] +letting x2 be [E2, E2, E3, E2; int(1..4)] +language Essence 1.3 + +letting s be permutation((E1, E2), (E3, E4)) +letting x1 be [E1, E1, E2, E1; int(1..4)] +letting x2 be [E2, E2, E2, E1; int(1..4)] +language Essence 1.3 + +letting s be permutation((E1, E2), (E3, E4)) +letting x1 be [E1, E1, E2, E2; int(1..4)] +letting x2 be [E2, E2, E1, E1; int(1..4)] +language Essence 1.3 + +letting s be permutation((E1, E2), (E3, E4)) +letting x1 be [E1, E1, E2, E3; int(1..4)] +letting x2 be [E2, E2, E4, E1; int(1..4)] +language Essence 1.3 + +letting s be permutation((E1, E2), (E3, E4)) +letting x1 be [E1, E1, E2, E4; int(1..4)] +letting x2 be [E2, E2, E3, E1; int(1..4)] +language Essence 1.3 + +letting s be permutation((E1, E2), (E3, E4)) +letting x1 be [E1, E1, E3, E1; int(1..4)] +letting x2 be [E2, E2, E2, E4; int(1..4)] +language Essence 1.3 + +letting s be permutation((E1, E2), (E3, E4)) +letting x1 be [E1, E1, E3, E2; int(1..4)] +letting x2 be [E2, E2, E1, E4; int(1..4)] diff --git a/tests/custom/permutations/basic/0038_matricies_of_tuples_of_enums_indexed_by_enums/permutation.essence b/tests/custom/permutations/basic/0038_matricies_of_tuples_of_enums_indexed_by_enums/permutation.essence new file mode 100644 index 0000000000..18cf9e25af --- /dev/null +++ b/tests/custom/permutations/basic/0038_matricies_of_tuples_of_enums_indexed_by_enums/permutation.essence @@ -0,0 +1,11 @@ +letting e be new type enum {E1, E2, E3, E4} + +find s: permutation of e +find x1 : matrix indexed by [e] of (e,e) +find x2 : matrix indexed by [e] of (e,e) + +such that + forAll i : e . + permute(s,i) != i + , permute(s, x1) = x2 + , x1 != x2 diff --git a/tests/custom/permutations/basic/0038_matricies_of_tuples_of_enums_indexed_by_enums/run.sh b/tests/custom/permutations/basic/0038_matricies_of_tuples_of_enums_indexed_by_enums/run.sh new file mode 100755 index 0000000000..3c60e3f90e --- /dev/null +++ b/tests/custom/permutations/basic/0038_matricies_of_tuples_of_enums_indexed_by_enums/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence --number-of-solutions=10 +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/basic/0038_matricies_of_tuples_of_enums_indexed_by_enums/stdout.expected b/tests/custom/permutations/basic/0038_matricies_of_tuples_of_enums_indexed_by_enums/stdout.expected new file mode 100644 index 0000000000..e9a6a9a1e9 --- /dev/null +++ b/tests/custom/permutations/basic/0038_matricies_of_tuples_of_enums_indexed_by_enums/stdout.expected @@ -0,0 +1,64 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Copying solution to: permutation-000001.solution +Copying solution to: permutation-000002.solution +Copying solution to: permutation-000003.solution +Copying solution to: permutation-000004.solution +Copying solution to: permutation-000005.solution +Copying solution to: permutation-000006.solution +Copying solution to: permutation-000007.solution +Copying solution to: permutation-000008.solution +Copying solution to: permutation-000009.solution +Copying solution to: permutation-000010.solution +language Essence 1.3 + +letting s be permutation((E1, E2), (E3, E4)) +letting x1 be [E1, E1, E1, E1; int(1..4)] +letting x2 be [E2, E2, E2, E2; int(1..4)] +language Essence 1.3 + +letting s be permutation((E1, E2), (E3, E4)) +letting x1 be [E1, E1, E1, E2; int(1..4)] +letting x2 be [E2, E2, E1, E2; int(1..4)] +language Essence 1.3 + +letting s be permutation((E1, E2), (E3, E4)) +letting x1 be [E1, E1, E1, E3; int(1..4)] +letting x2 be [E2, E2, E4, E2; int(1..4)] +language Essence 1.3 + +letting s be permutation((E1, E2), (E3, E4)) +letting x1 be [E1, E1, E1, E4; int(1..4)] +letting x2 be [E2, E2, E3, E2; int(1..4)] +language Essence 1.3 + +letting s be permutation((E1, E2), (E3, E4)) +letting x1 be [E1, E1, E2, E1; int(1..4)] +letting x2 be [E2, E2, E2, E1; int(1..4)] +language Essence 1.3 + +letting s be permutation((E1, E2), (E3, E4)) +letting x1 be [E1, E1, E2, E2; int(1..4)] +letting x2 be [E2, E2, E1, E1; int(1..4)] +language Essence 1.3 + +letting s be permutation((E1, E2), (E3, E4)) +letting x1 be [E1, E1, E2, E3; int(1..4)] +letting x2 be [E2, E2, E4, E1; int(1..4)] +language Essence 1.3 + +letting s be permutation((E1, E2), (E3, E4)) +letting x1 be [E1, E1, E2, E4; int(1..4)] +letting x2 be [E2, E2, E3, E1; int(1..4)] +language Essence 1.3 + +letting s be permutation((E1, E2), (E3, E4)) +letting x1 be [E1, E1, E3, E1; int(1..4)] +letting x2 be [E2, E2, E2, E4; int(1..4)] +language Essence 1.3 + +letting s be permutation((E1, E2), (E3, E4)) +letting x1 be [E1, E1, E3, E2; int(1..4)] +letting x2 be [E2, E2, E1, E4; int(1..4)] From fe7d64c8748efc83be78f1f7244a061aed3e84da Mon Sep 17 00:00:00 2001 From: Fraser Dunlop Date: Tue, 20 Nov 2018 12:38:33 +0000 Subject: [PATCH 024/229] renamed apply to compose --- .../permutation.essence | 2 +- .../permutation.essence | 2 +- .../permutation.essence | 2 +- .../permutation.essence | 2 +- 4 files changed, 4 insertions(+), 4 deletions(-) diff --git a/tests/custom/permutations/basic/0008_find_int_image_under_two_composed_given_permutations/permutation.essence b/tests/custom/permutations/basic/0008_find_int_image_under_two_composed_given_permutations/permutation.essence index 29e49ca1f8..d78d78cbf4 100644 --- a/tests/custom/permutations/basic/0008_find_int_image_under_two_composed_given_permutations/permutation.essence +++ b/tests/custom/permutations/basic/0008_find_int_image_under_two_composed_given_permutations/permutation.essence @@ -11,4 +11,4 @@ letting j be 7 find i : int(1..8) -such that permute(apply(q,p),i) = j +such that permute(compose(q,p),i) = j diff --git a/tests/custom/permutations/basic/0009_find_int_image_under_three_composed_given_permutations/permutation.essence b/tests/custom/permutations/basic/0009_find_int_image_under_three_composed_given_permutations/permutation.essence index 98e482e940..b7d0b1d02a 100644 --- a/tests/custom/permutations/basic/0009_find_int_image_under_three_composed_given_permutations/permutation.essence +++ b/tests/custom/permutations/basic/0009_find_int_image_under_three_composed_given_permutations/permutation.essence @@ -11,4 +11,4 @@ letting j be 12 find i : int(1..8) -such that permute(apply(w,apply(w,apply(q,p))),i) = j +such that permute(compose(w,compose(w,compose(q,p))),i) = j diff --git a/tests/custom/permutations/basic/0010_find_int_image_under_three_composed_given_permutations/permutation.essence b/tests/custom/permutations/basic/0010_find_int_image_under_three_composed_given_permutations/permutation.essence index 9475d5e8bd..e7181a78c0 100644 --- a/tests/custom/permutations/basic/0010_find_int_image_under_three_composed_given_permutations/permutation.essence +++ b/tests/custom/permutations/basic/0010_find_int_image_under_three_composed_given_permutations/permutation.essence @@ -11,4 +11,4 @@ letting j be 20 find i : int(1..30) -such that permute(apply(w,apply(w,apply(q,p))),i) = j +such that permute(compose(w,compose(w,compose(q,p))),i) = j diff --git a/tests/custom/permutations/basic/0021_image_of_int_under_composition_of_two_given_permutations/permutation.essence b/tests/custom/permutations/basic/0021_image_of_int_under_composition_of_two_given_permutations/permutation.essence index 8877f6fb99..89e0ee7d15 100644 --- a/tests/custom/permutations/basic/0021_image_of_int_under_composition_of_two_given_permutations/permutation.essence +++ b/tests/custom/permutations/basic/0021_image_of_int_under_composition_of_two_given_permutations/permutation.essence @@ -10,4 +10,4 @@ letting j be 20 find i : int(1..30) -such that permute(apply(q,p),i) = j +such that permute(compose(q,p),i) = j From 0ab627b3c21bfff8ce4f940047db93b84fd6eb63 Mon Sep 17 00:00:00 2001 From: Fraser Dunlop Date: Wed, 21 Nov 2018 14:42:03 +0000 Subject: [PATCH 025/229] Renamed permute to overload image --- conjure-cp.cabal | 2 +- src/Conjure/Compute/DomainOf.hs | 8 +-- src/Conjure/Language/Expression/Op.hs | 8 +-- .../Expression/Op/{Apply.hs => Compose.hs} | 40 ++++++------ src/Conjure/Language/Expression/Op/Image.hs | 18 +++++- .../Language/Expression/Op/Internal/Common.hs | 4 +- src/Conjure/Language/Expression/Op/Permute.hs | 2 +- src/Conjure/Language/Lexer.hs | 6 +- src/Conjure/Rules/Horizontal/Permutation.hs | 24 +++---- src/Conjure/Rules/Horizontal/Set.hs | 6 +- .../Rules/Vertical/Permutation/AsFunction.hs | 64 +++++++++---------- src/Conjure/Rules/Vertical/Tuple.hs | 6 +- src/Conjure/UI/Model.hs | 2 +- .../permutation.essence | 2 +- .../permutation.essence | 2 +- .../permutation.essence | 2 +- .../permutation.essence | 2 +- .../permutation.essence | 2 +- .../permutation.essence | 2 +- .../permutation.essence | 2 +- .../permutation.essence | 2 +- .../permutation.essence | 2 +- .../permutation.essence | 2 +- .../permutation.essence | 2 +- .../permutation.essence | 2 +- .../permutation.essence | 2 +- .../permutation.essence | 2 +- .../permutation.essence | 2 +- .../permutation.essence | 2 +- .../permutation.essence | 2 +- .../permutation.essence | 2 +- .../permutation.essence | 2 +- .../permutation.essence | 2 +- .../permutation.essence | 2 +- .../permutation.essence | 2 +- .../permutation.essence | 2 +- .../permutation.essence | 2 +- .../permutation.essence | 2 +- .../permutation.essence | 2 +- .../permutation.essence | 2 +- .../permutation.essence | 2 +- .../permutation.essence | 2 +- .../permutation.essence | 4 +- .../permutation.essence | 8 +-- .../permutation.essence | 4 +- .../permutation.essence | 4 +- 46 files changed, 139 insertions(+), 129 deletions(-) rename src/Conjure/Language/Expression/Op/{Apply.hs => Compose.hs} (56%) diff --git a/conjure-cp.cabal b/conjure-cp.cabal index c3773d25f3..81cfab2fe8 100644 --- a/conjure-cp.cabal +++ b/conjure-cp.cabal @@ -50,7 +50,7 @@ Library , Conjure.Language.Expression.Op.AllDiffExcept , Conjure.Language.Expression.Op.And , Conjure.Language.Expression.Op.Apart - , Conjure.Language.Expression.Op.Apply + , Conjure.Language.Expression.Op.Compose , Conjure.Language.Expression.Op.AttributeAsConstraint , Conjure.Language.Expression.Op.CatchUndef , Conjure.Language.Expression.Op.Defined diff --git a/src/Conjure/Compute/DomainOf.hs b/src/Conjure/Compute/DomainOf.hs index dba5928e54..dc36b6ec7f 100644 --- a/src/Conjure/Compute/DomainOf.hs +++ b/src/Conjure/Compute/DomainOf.hs @@ -81,7 +81,7 @@ instance (DomainOf x, TypeOf x, Pretty x, ExpressionLike x, Domain () x :< x, Do domainOf (MkOpAllDiffExcept x) = domainOf x domainOf (MkOpAnd x) = domainOf x domainOf (MkOpApart x) = domainOf x - domainOf (MkOpApply x) = domainOf x + domainOf (MkOpCompose x) = domainOf x domainOf (MkOpAttributeAsConstraint x) = domainOf x domainOf (MkOpCatchUndef x) = domainOf x domainOf (MkOpDefined x) = domainOf x @@ -155,7 +155,7 @@ instance (DomainOf x, TypeOf x, Pretty x, ExpressionLike x, Domain () x :< x, Do indexDomainsOf (MkOpAllDiffExcept x) = indexDomainsOf x indexDomainsOf (MkOpAnd x) = indexDomainsOf x indexDomainsOf (MkOpApart x) = indexDomainsOf x - indexDomainsOf (MkOpApply x) = indexDomainsOf x + indexDomainsOf (MkOpCompose x) = indexDomainsOf x indexDomainsOf (MkOpAttributeAsConstraint x) = indexDomainsOf x indexDomainsOf (MkOpCatchUndef x) = indexDomainsOf x indexDomainsOf (MkOpDefined x) = indexDomainsOf x @@ -517,8 +517,8 @@ instance (Pretty x, TypeOf x) => DomainOf (OpPermutationTuples x) where -instance (Pretty x, TypeOf x) => DomainOf (OpApply x) where - domainOf op = mkDomainAny ("OpApply:" <++> pretty op) <$> typeOf op +instance (Pretty x, TypeOf x) => DomainOf (OpCompose x) where + domainOf op = mkDomainAny ("OpCompose:" <++> pretty op) <$> typeOf op instance (Pretty x, TypeOf x) => DomainOf (OpPow x) where domainOf op = mkDomainAny ("OpPow:" <++> pretty op) <$> typeOf op diff --git a/src/Conjure/Language/Expression/Op.hs b/src/Conjure/Language/Expression/Op.hs index 8a9a8c56e4..5a8461348b 100644 --- a/src/Conjure/Language/Expression/Op.hs +++ b/src/Conjure/Language/Expression/Op.hs @@ -117,11 +117,11 @@ mkOp op xs = L_party -> inject $ MkOpParty $ OpParty (arg xs 0 "party") (arg xs 1 "party") L_participants -> inject $ MkOpParticipants $ OpParticipants (arg xs 0 "participants") - L_permute -> inject $ MkOpPermute $ OpPermute (arg xs 0 "permute") - (arg xs 1 "permute") + L_image -> inject $ MkOpPermute $ OpPermute (arg xs 0 "image") + (arg xs 1 "image") L_permutationTuples -> inject $ MkOpPermutationTuples $ OpPermutationTuples (arg xs 0 "permutationTuples") - L_apply -> inject $ MkOpApply $ OpApply (arg xs 0 "apply") - (arg xs 1 "apply") + L_compose -> inject $ MkOpCompose $ OpCompose (arg xs 0 "compose") + (arg xs 1 "compose") L_active -> inject $ MkOpActive $ OpActive (arg xs 0 "active") (arg xs 1 "active" |> nameOut |> fromMaybe (bug "active")) diff --git a/src/Conjure/Language/Expression/Op/Apply.hs b/src/Conjure/Language/Expression/Op/Compose.hs similarity index 56% rename from src/Conjure/Language/Expression/Op/Apply.hs rename to src/Conjure/Language/Expression/Op/Compose.hs index 2a9f2581dc..37e63fc82e 100644 --- a/src/Conjure/Language/Expression/Op/Apply.hs +++ b/src/Conjure/Language/Expression/Op/Compose.hs @@ -1,6 +1,6 @@ {-# LANGUAGE DeriveGeneric, DeriveDataTypeable, DeriveFunctor, DeriveTraversable, DeriveFoldable, ViewPatterns #-} -module Conjure.Language.Expression.Op.Apply where +module Conjure.Language.Expression.Op.Compose where import Conjure.Prelude import Conjure.Language.Expression.Op.Internal.Common @@ -12,16 +12,16 @@ import qualified Data.Vector as V -- vector import Data.List (cycle) -data OpApply x = OpApply x x +data OpCompose x = OpCompose x x deriving (Eq, Ord, Show, Data, Functor, Traversable, Foldable, Typeable, Generic) -instance Serialize x => Serialize (OpApply x) -instance Hashable x => Hashable (OpApply x) -instance ToJSON x => ToJSON (OpApply x) where toJSON = genericToJSON jsonOptions -instance FromJSON x => FromJSON (OpApply x) where parseJSON = genericParseJSON jsonOptions +instance Serialize x => Serialize (OpCompose x) +instance Hashable x => Hashable (OpCompose x) +instance ToJSON x => ToJSON (OpCompose x) where toJSON = genericToJSON jsonOptions +instance FromJSON x => FromJSON (OpCompose x) where parseJSON = genericParseJSON jsonOptions -instance (TypeOf x, Pretty x) => TypeOf (OpApply x) where - typeOf inp@(OpApply p q) = do +instance (TypeOf x, Pretty x) => TypeOf (OpCompose x) where + typeOf inp@(OpCompose p q) = do pTy <- typeOf p qTy <- typeOf q case (pTy, qTy) of @@ -31,8 +31,8 @@ instance (TypeOf x, Pretty x) => TypeOf (OpApply x) where else raiseTypeError inp _ -> raiseTypeError inp -instance EvaluateOp OpApply where - evaluateOp op@(OpApply g@(viewConstantPermutation -> Just gss) +instance EvaluateOp OpCompose where + evaluateOp op@(OpCompose g@(viewConstantPermutation -> Just gss) h@(viewConstantPermutation -> Just hss)) = do gt <- typeOf g ht <- typeOf h @@ -41,21 +41,21 @@ instance EvaluateOp OpApply where let appI xss i = case filter (i `elem`) xss of [] -> return i [k] -> return $ head $ drop 1 $ dropWhile (/= i) $ cycle k - _ -> bug "evaluateOp{OpApply} element should only be in one cycle of permutation" + _ -> bug "evaluateOp{OpCompose} element should only be in one cycle of permutation" in ConstantAbstract . AbsLitPermutation <$> (mapM (mapM (appI gss)) hss) - _ -> na $ "evaluateOp{OpApply} only defined for Ints right now:" <++> pretty (show op) - evaluateOp op = na $ "evaluateOp{OpApply}:" <++> pretty (show op) + _ -> na $ "evaluateOp{OpCompose} only defined for Ints right now:" <++> pretty (show op) + evaluateOp op = na $ "evaluateOp{OpCompose}:" <++> pretty (show op) -instance SimplifyOp OpApply x where - simplifyOp _ = na "simplifyOp{OpApply}" +instance SimplifyOp OpCompose x where + simplifyOp _ = na "simplifyOp{OpCompose}" -instance Pretty x => Pretty (OpApply x) where - prettyPrec _ (OpApply a i) = "apply" <> prettyList prParens "," [a,i] +instance Pretty x => Pretty (OpCompose x) where + prettyPrec _ (OpCompose a i) = "compose" <> prettyList prParens "," [a,i] -instance VarSymBreakingDescription x => VarSymBreakingDescription (OpApply x) where - varSymBreakingDescription (OpApply a i) = JSON.Object $ M.fromList - [ ("type", JSON.String "OpApply") +instance VarSymBreakingDescription x => VarSymBreakingDescription (OpCompose x) where + varSymBreakingDescription (OpCompose a i) = JSON.Object $ M.fromList + [ ("type", JSON.String "OpCompose") , ("children", JSON.Array $ V.fromList [ varSymBreakingDescription a , varSymBreakingDescription i diff --git a/src/Conjure/Language/Expression/Op/Image.hs b/src/Conjure/Language/Expression/Op/Image.hs index 4dc15d5186..70e5ac2c7e 100644 --- a/src/Conjure/Language/Expression/Op/Image.hs +++ b/src/Conjure/Language/Expression/Op/Image.hs @@ -4,11 +4,14 @@ module Conjure.Language.Expression.Op.Image where import Conjure.Prelude import Conjure.Language.Expression.Op.Internal.Common +import Conjure.Bug import qualified Data.Aeson as JSON -- aeson import qualified Data.HashMap.Strict as M -- unordered-containers import qualified Data.Vector as V -- vector +import Data.List (cycle) + data OpImage x = OpImage x x deriving (Eq, Ord, Show, Data, Functor, Traversable, Foldable, Typeable, Generic) @@ -21,19 +24,20 @@ instance FromJSON x => FromJSON (OpImage x) where parseJSON = genericParseJSON instance (TypeOf x, Pretty x) => TypeOf (OpImage x) where typeOf p@(OpImage f x) = do tyF <- typeOf f + tyX <- typeOf x (from, to) <- case tyF of TypeFunction from to -> return (from, to) TypeSequence to -> return (TypeInt NoTag, to) + TypePermutation _ -> return (tyX, tyX) _ -> raiseTypeError $ "(function application)" <+> pretty p - xTy <- typeOf x - if typesUnify [xTy, from] + if typesUnify [tyX, from] then return to else raiseTypeError $ vcat [ pretty p , "function :" <+> pretty f , "function type:" <+> pretty (TypeFunction from to) , "argument :" <+> pretty x - , "argument type:" <+> pretty xTy + , "argument type:" <+> pretty tyX ] instance EvaluateOp OpImage where @@ -67,6 +71,14 @@ instance EvaluateOp OpImage where [ "Sequence is multiply defined at this point:" <+> pretty a , "Sequence value:" <+> pretty f ] + evaluateOp op@(OpImage (viewConstantPermutation -> Just xss) i) = do + case filter (i `elem`) xss of + [] -> return i + [h] -> do + case length $ filter (== i) h of + 1 -> return $ head $ drop 1 $ dropWhile (/= i) $ cycle h + _ -> bug "evaluateOp{OpImage} element in cycle of permutationmore than once" + _ -> bug "evaluateOp{OpPermute} element in more than one cycle of permutation" evaluateOp op = na $ "evaluateOp{OpImage}:" <++> pretty (show op) instance SimplifyOp OpImage x where diff --git a/src/Conjure/Language/Expression/Op/Internal/Common.hs b/src/Conjure/Language/Expression/Op/Internal/Common.hs index 3e7979b59c..db3d085f42 100644 --- a/src/Conjure/Language/Expression/Op/Internal/Common.hs +++ b/src/Conjure/Language/Expression/Op/Internal/Common.hs @@ -246,7 +246,7 @@ functionals = , L_max , L_allDiff , L_alldifferent_except - , L_apply + , L_compose , L_catchUndef , L_dontCare , L_hist @@ -267,7 +267,7 @@ functionals = , L_party , L_participants , L_parts - , L_permute + , L_image , L_permutationTuples , L_freq , L_toInt diff --git a/src/Conjure/Language/Expression/Op/Permute.hs b/src/Conjure/Language/Expression/Op/Permute.hs index 5f359a829d..5e5262c4ce 100644 --- a/src/Conjure/Language/Expression/Op/Permute.hs +++ b/src/Conjure/Language/Expression/Op/Permute.hs @@ -43,7 +43,7 @@ instance SimplifyOp OpPermute x where simplifyOp _ = na "simplifyOp{OpPermute}" instance Pretty x => Pretty (OpPermute x) where - prettyPrec _ (OpPermute a i) = "permute" <> prettyList prParens "," [a,i] + prettyPrec _ (OpPermute a i) = "image" <> prettyList prParens "," [a,i] instance VarSymBreakingDescription x => VarSymBreakingDescription (OpPermute x) where varSymBreakingDescription (OpPermute a i) = JSON.Object $ M.fromList diff --git a/src/Conjure/Language/Lexer.hs b/src/Conjure/Language/Lexer.hs index df2b6cac0a..96431a736d 100644 --- a/src/Conjure/Language/Lexer.hs +++ b/src/Conjure/Language/Lexer.hs @@ -118,9 +118,8 @@ data Lexeme -- type: permutation | L_permutation - | L_permute | L_permutationTuples - | L_apply + | L_compose -- operators, page 21 of the holy paper | L_union @@ -363,8 +362,7 @@ lexemes = sortBy (flip (comparing (T.length . fst))) $ map swap , ( L_permutation, "permutation" ) , ( L_permutationTuples, "permutationTuples" ) - , ( L_permute, "permute") - , ( L_apply, "apply") + , ( L_compose, "compose") -- , ( L_regular, "regular" ) -- , ( L_partSize, "partSize" ) -- , ( L_minPartSize, "minPartSize" ) diff --git a/src/Conjure/Rules/Horizontal/Permutation.hs b/src/Conjure/Rules/Horizontal/Permutation.hs index 525d69d704..bb4291c683 100644 --- a/src/Conjure/Rules/Horizontal/Permutation.hs +++ b/src/Conjure/Rules/Horizontal/Permutation.hs @@ -3,9 +3,9 @@ module Conjure.Rules.Horizontal.Permutation where import Conjure.Rules.Import import Data.List (cycle) -rule_Apply :: Rule -rule_Apply = "permutation-apply{rule_Apply}" `namedRule` theRule where - theRule [essence| permute(apply(&g, &h),&i) |] = do +rule_Compose :: Rule +rule_Compose = "permutation-compose{rule_Compose}" `namedRule` theRule where + theRule [essence| image(compose(&g, &h),&i) |] = do TypePermutation innerG <- typeOf g TypePermutation innerH <- typeOf g typeI <- typeOf i @@ -13,16 +13,16 @@ rule_Apply = "permutation-apply{rule_Apply}" `namedRule` theRule where then return ( "Horizontal rule for permutation composition/application" , do - return [essence| permute(&g, permute(&h,&i)) |] + return [essence| image(&g, image(&h,&i)) |] ) - else na "rule_Apply" - theRule _ = na "rule_Apply" + else na "rule_Compose" + theRule _ = na "rule_Compose" rule_Permute_Literal :: Rule -rule_Permute_Literal = "permutation-permute-literal{AsFunction}" `namedRule` theRule where - theRule [essence| permute(&p, &i) |] = do +rule_Permute_Literal = "permutation-image-literal{AsFunction}" `namedRule` theRule where + theRule [essence| image(&p, &i) |] = do (TypePermutation inner, elems) <- match permutationLiteral p case i of WithLocals{} -> na "bubble-delay" ; _ -> return () typeI <- typeOf i @@ -41,7 +41,7 @@ rule_Permute_Literal = "permutation-permute-literal{AsFunction}" `namedRule` the | (a,b) <- permTups ] return - ( "Horizontal rule for permutation literal application to a single value (permute), AsFunction representation" + ( "Horizontal rule for permutation literal application to a single value (image), AsFunction representation" , do (hName, h) <- auxiliaryVar (fPat, f) <- quantifiedVar @@ -71,10 +71,10 @@ rule_Permute_Literal = "permutation-permute-literal{AsFunction}" `namedRule` the rule_Permute_Literal_Comprehension :: Rule -rule_Permute_Literal_Comprehension = "permutation-permute-literal-comprehension{AsFunction}" `namedRule` theRule where +rule_Permute_Literal_Comprehension = "permutation-image-literal-comprehension{AsFunction}" `namedRule` theRule where theRule (Comprehension body gensOrConds) = do (gocBefore, (pat, p, i), gocAfter) <- matchFirst gensOrConds $ \ goc -> case goc of - Generator (GenInExpr pat [essence| permute(&p, &i) |]) -> return (pat, p, i) + Generator (GenInExpr pat [essence| image(&p, &i) |]) -> return (pat, p, i) _ -> na "rule_Comprehension" case i of WithLocals{} -> na "bubble-delay" ; _ -> return () (TypePermutation inner, elems) <- match permutationLiteral p @@ -93,7 +93,7 @@ rule_Permute_Literal_Comprehension = "permutation-permute-literal-comprehension{ | (a,b) <- permTups ] return - ( "Horizontal rule for permutation literal application to a single value (permute), AsFunction representation" + ( "Horizontal rule for permutation literal application to a single value (image), AsFunction representation" , do (hName, h) <- auxiliaryVar (fPat, f) <- quantifiedVar diff --git a/src/Conjure/Rules/Horizontal/Set.hs b/src/Conjure/Rules/Horizontal/Set.hs index ddc992d118..6f40a17f01 100644 --- a/src/Conjure/Rules/Horizontal/Set.hs +++ b/src/Conjure/Rules/Horizontal/Set.hs @@ -130,7 +130,7 @@ rule_DotLt = "set-DotLt" `namedRule` theRule where rule_DotLeq :: Rule rule_DotLeq = "set-DotLeq" `namedRule` theRule where --This works but not for occurrence rep - theRule [essence| &a .<= permute(&perm, &b) |] = do + theRule [essence| &a .<= image(&perm, &b) |] = do TypeSet{} <- typeOf a TypeSet{} <- typeOf b TypePermutation{} <- typeOf perm @@ -139,9 +139,9 @@ rule_DotLeq = "set-DotLeq" `namedRule` theRule where mb <- tupleLitIfNeeded <$> downX1 b return ( "Horizontal rule for set .<=" - <+> pretty ([essence| &ma .<= permute(&perm, &mb) |]) + <+> pretty ([essence| &ma .<= image(&perm, &mb) |]) - , return $ [essence| &ma .<= permute(&perm, &mb) |] + , return $ [essence| &ma .<= image(&perm, &mb) |] ) theRule p = do (a,b) <- match opDotLeq p diff --git a/src/Conjure/Rules/Vertical/Permutation/AsFunction.hs b/src/Conjure/Rules/Vertical/Permutation/AsFunction.hs index 55f8adcd77..174419888b 100644 --- a/src/Conjure/Rules/Vertical/Permutation/AsFunction.hs +++ b/src/Conjure/Rules/Vertical/Permutation/AsFunction.hs @@ -28,8 +28,8 @@ rule_Permute_Comprehension_Tuples = "permutation-comprehension-tuples{AsFunction rule_Permute :: Rule -rule_Permute = "permutation-permute{AsFunction}" `namedRule` theRule where - theRule [essence| permute(&p, &i) |] = do +rule_Permute = "permutation-image{AsFunction}" `namedRule` theRule where + theRule [essence| image(&p, &i) |] = do TypePermutation inner <- typeOf p typeI <- typeOf i if typeI `containsType` inner @@ -51,10 +51,10 @@ rule_Permute = "permutation-permute{AsFunction}" `namedRule` theRule where rule_Permute_Comprehension :: Rule -rule_Permute_Comprehension = "permutation-permute{AsFunction}" `namedRule` theRule where +rule_Permute_Comprehension = "permutation-image{AsFunction}" `namedRule` theRule where theRule (Comprehension body gensOrConds) = do (gocBefore, (pat, p, i), gocAfter) <- matchFirst gensOrConds $ \ goc -> case goc of - Generator (GenInExpr pat [essence| permute(&p, &i) |]) -> return (pat, p, i) + Generator (GenInExpr pat [essence| image(&p, &i) |]) -> return (pat, p, i) _ -> na "rule_Comprehension" TypePermutation inner <- typeOf p @@ -82,8 +82,8 @@ rule_Permute_Comprehension = "permutation-permute{AsFunction}" `namedRule` theRu theRule _ = na "rule_Permute" rule_Matrix_Permute :: Rule -rule_Matrix_Permute = "matrix-permute" `namedRule` theRule where - theRule [essence| permute(&perm, &y) |] = do +rule_Matrix_Permute = "matrix-image" `namedRule` theRule where + theRule [essence| image(&perm, &y) |] = do ty@(TypeMatrix _ _) <- typeOf y (TypePermutation inn) <- typeOf perm if not $ typesUnify [ty, inn] @@ -92,7 +92,7 @@ rule_Matrix_Permute = "matrix-permute" `namedRule` theRule where y' <- flattenIfNeeded y dm@(DomainMatrix dyindex _) <- domainOf y' return - ( "Horizontal rule for permute matrix" + ( "Horizontal rule for image matrix" , do (dPat, d) <- quantifiedVar (pyName, py) <- auxiliaryVar @@ -103,7 +103,7 @@ rule_Matrix_Permute = "matrix-permute" `namedRule` theRule where , SuchThat [ [essence| forAll &dPat : &dyindex . - &py[permute(&perm,&d)] = permute(&perm,&y'[&d]) + &py[image(&perm,&d)] = image(&perm,&y'[&d]) |] ] ] @@ -113,10 +113,10 @@ rule_Matrix_Permute = "matrix-permute" `namedRule` theRule where theRule _ = na "rule_Matrix_Permute" rule_Matrix_Permute_Comprehension :: Rule -rule_Matrix_Permute_Comprehension = "matrix-permute-comprehension" `namedRule` theRule where +rule_Matrix_Permute_Comprehension = "matrix-image-comprehension" `namedRule` theRule where theRule (Comprehension body gensOrConds) = do (gocBefore, (pat, perm, y), gocAfter) <- matchFirst gensOrConds $ \ goc -> case goc of - Generator (GenInExpr pat [essence| permute(&perm, &y) |]) -> return (pat, perm, y) + Generator (GenInExpr pat [essence| image(&perm, &y) |]) -> return (pat, perm, y) _ -> na "rule_Matrix_Permute" ty@(TypeMatrix _ _) <- typeOf y (TypePermutation inn) <- typeOf perm @@ -126,7 +126,7 @@ rule_Matrix_Permute_Comprehension = "matrix-permute-comprehension" `namedRule` t y' <- flattenIfNeeded y dm@(DomainMatrix dyindex _) <- domainOf y' return - ( "Horizontal rule for permute matrix in comprehension" + ( "Horizontal rule for image matrix in comprehension" , do (dPat, d) <- quantifiedVar (pyName, py) <- auxiliaryVar @@ -139,7 +139,7 @@ rule_Matrix_Permute_Comprehension = "matrix-permute-comprehension" `namedRule` t , SuchThat [ [essence| forAll &dPat : &dyindex . - &py[permute(&perm,&d)] = permute(&perm,&y'[&d]) + &py[image(&perm,&d)] = image(&perm,&y'[&d]) |] ] ] @@ -149,10 +149,10 @@ rule_Matrix_Permute_Comprehension = "matrix-permute-comprehension" `namedRule` t theRule _ = na "rule_Matrix_Permute_Comprehension" rule_Set_Permute :: Rule -rule_Set_Permute = "set-permute" `namedRule` theRule where +rule_Set_Permute = "set-image" `namedRule` theRule where theRule (Comprehension body gensOrConds) = do (gocBefore, (pat, perm, y), gocAfter) <- matchFirst gensOrConds $ \ goc -> case goc of - Generator (GenInExpr pat [essence| permute(&perm, &y) |]) -> return (pat, perm, y) + Generator (GenInExpr pat [essence| image(&perm, &y) |]) -> return (pat, perm, y) _ -> na "rule_Set_Permute" ts@(TypeSet _) <- typeOf y (TypePermutation inn) <- typeOf perm @@ -160,7 +160,7 @@ rule_Set_Permute = "set-permute" `namedRule` theRule where then do ds <- domainOf y return - ( "Horizontal rule for permute set" + ( "Horizontal rule for image set" , do (dPat, d) <- quantifiedVar (pyName, py) <- auxiliaryVar @@ -174,7 +174,7 @@ rule_Set_Permute = "set-permute" `namedRule` theRule where [ [essence| |&y| = |&py| /\ forAll &dPat in &y . - permute(&perm, &d) in &py + image(&perm, &d) in &py |] ] ] @@ -185,8 +185,8 @@ rule_Set_Permute = "set-permute" `namedRule` theRule where rule_Relation_Permute :: Rule -rule_Relation_Permute = "relation-permute" `namedRule` theRule where - theRule [essence| permute(&perm, &y) |] = do +rule_Relation_Permute = "relation-image" `namedRule` theRule where + theRule [essence| image(&perm, &y) |] = do case y of WithLocals{} -> na "bubble-delay" ; _ -> return () ts@(TypeRelation _) <- typeOf y (TypePermutation inn) <- typeOf perm @@ -194,7 +194,7 @@ rule_Relation_Permute = "relation-permute" `namedRule` theRule where then do ds <- domainOf y return - ( "Horizontal rule for permute relation in comprehension" + ( "Horizontal rule for image relation in comprehension" , do (dPat, d) <- quantifiedVar (pyName, py) <- auxiliaryVar @@ -205,7 +205,7 @@ rule_Relation_Permute = "relation-permute" `namedRule` theRule where , SuchThat [ [essence| |&y| = |&py| - /\ and([permute(&perm, &d) in &py | &dPat <- &y]) + /\ and([image(&perm, &d) in &py | &dPat <- &y]) |] ] @@ -216,10 +216,10 @@ rule_Relation_Permute = "relation-permute" `namedRule` theRule where theRule _ = na "rule_Relation_Permute" rule_Relation_Permute_Comprehension :: Rule -rule_Relation_Permute_Comprehension = "relation-permute-comprehension" `namedRule` theRule where +rule_Relation_Permute_Comprehension = "relation-image-comprehension" `namedRule` theRule where theRule (Comprehension body gensOrConds) = do (gocBefore, (pat, perm, y), gocAfter) <- matchFirst gensOrConds $ \ goc -> case goc of - Generator (GenInExpr pat [essence| permute(&perm, &y) |]) -> return (pat, perm, y) + Generator (GenInExpr pat [essence| image(&perm, &y) |]) -> return (pat, perm, y) _ -> na "rule_Relation_Permute_Comprehension" case y of WithLocals{} -> na "bubble-delay" ; _ -> return () ts@(TypeRelation _) <- typeOf y @@ -228,7 +228,7 @@ rule_Relation_Permute_Comprehension = "relation-permute-comprehension" `namedRul then do ds <- domainOf y return - ( "Horizontal rule for permute relation in comprehension" + ( "Horizontal rule for image relation in comprehension" , do (dPat, d) <- quantifiedVar (pyName, py) <- auxiliaryVar @@ -241,7 +241,7 @@ rule_Relation_Permute_Comprehension = "relation-permute-comprehension" `namedRul , SuchThat [ [essence| |&y| = |&py| - /\ and([permute(&perm, &d) in &py | &dPat <- &y]) + /\ and([image(&perm, &d) in &py | &dPat <- &y]) |] ] ] @@ -252,8 +252,8 @@ rule_Relation_Permute_Comprehension = "relation-permute-comprehension" `namedRul rule_Tuple_Permute :: Rule -rule_Tuple_Permute = "tuple-permute" `namedRule` theRule where - theRule [essence| permute(&perm, &y) |] = do +rule_Tuple_Permute = "tuple-image" `namedRule` theRule where + theRule [essence| image(&perm, &y) |] = do case y of WithLocals{} -> na "bubble-delay" ; _ -> return () ty' <- typeOf y -- traceM $ "rule_Tuple_Permute: " ++ show ty' @@ -264,7 +264,7 @@ rule_Tuple_Permute = "tuple-permute" `namedRule` theRule where -- traceM $ "rule_Tuple_Permute: applying" dm <- domainOf y return - ( "Horizontal rule for permute tuple in comprehension" + ( "Horizontal rule for image tuple in comprehension" , do (pyName, py) <- auxiliaryVar return $ WithLocals @@ -272,7 +272,7 @@ rule_Tuple_Permute = "tuple-permute" `namedRule` theRule where (AuxiliaryVars $ [ Declaration (FindOrGiven LocalFind pyName dm)] ++ ((\x -> let d = Constant $ ConstantInt NoTag x - in SuchThat [[essence| &py[&d] = permute(&perm,&y[&d]) |] ]) + in SuchThat [[essence| &py[&d] = image(&perm,&y[&d]) |] ]) <$> [1..(genericLength it)]) @@ -282,10 +282,10 @@ rule_Tuple_Permute = "tuple-permute" `namedRule` theRule where theRule _ = na "rule_Tuple_Permute" rule_Tuple_Permute_Comprehension :: Rule -rule_Tuple_Permute_Comprehension = "tuple-permute-comprehension" `namedRule` theRule where +rule_Tuple_Permute_Comprehension = "tuple-image-comprehension" `namedRule` theRule where theRule (Comprehension body gensOrConds) = do (gocBefore, (pat, perm, y), gocAfter) <- matchFirst gensOrConds $ \ goc -> case goc of - Generator (GenInExpr pat [essence| permute(&perm, &y) |]) -> return (pat, perm, y) + Generator (GenInExpr pat [essence| image(&perm, &y) |]) -> return (pat, perm, y) _ -> na "rule_Tuple_Permute" case y of WithLocals{} -> na "bubble-delay" ; _ -> return () ty' <- typeOf y @@ -297,7 +297,7 @@ rule_Tuple_Permute_Comprehension = "tuple-permute-comprehension" `namedRule` the -- traceM $ "rule_Tuple_Permute_Comprehension: applying" dm <- domainOf y return - ( "Horizontal rule for permute tuple in comprehension" + ( "Horizontal rule for image tuple in comprehension" , do (pyName, py) <- auxiliaryVar return $ WithLocals @@ -307,7 +307,7 @@ rule_Tuple_Permute_Comprehension = "tuple-permute-comprehension" `namedRule` the (AuxiliaryVars $ [ Declaration (FindOrGiven LocalFind pyName dm)] ++ ((\x -> let d = Constant $ ConstantInt NoTag x - in SuchThat [[essence| &py[&d] = permute(&perm,&y[&d]) |] ]) + in SuchThat [[essence| &py[&d] = image(&perm,&y[&d]) |] ]) <$> [1..(genericLength it)]) ) ) diff --git a/src/Conjure/Rules/Vertical/Tuple.hs b/src/Conjure/Rules/Vertical/Tuple.hs index 3c48511ba2..2fe8cf6443 100644 --- a/src/Conjure/Rules/Vertical/Tuple.hs +++ b/src/Conjure/Rules/Vertical/Tuple.hs @@ -82,7 +82,7 @@ rule_Tuple_DotLt = "tuple-DotLt" `namedRule` theRule where rule_Tuple_DotLeq :: Rule rule_Tuple_DotLeq = "tuple-DotLeq" `namedRule` theRule where --- theRule p@[essence| &x .<= permute(&perm, &y) |] = do +-- theRule p@[essence| &x .<= image(&perm, &y) |] = do -- TypeTuple{} <- typeOf x -- TODO: check matrix index & tuple arity -- TypeTuple{} <- typeOf y -- TypePermutation{} <- typeOf perm @@ -184,9 +184,9 @@ decomposeLexDotLeq p = unroll -- -> [Expression] -> [Expression] -> Expression --decomposeLexDotLeqSym p perm = unroll -- where --- unroll [a] [b] = [essence| &a .<= permute(&perm, &b) |] +-- unroll [a] [b] = [essence| &a .<= image(&perm, &b) |] -- unroll (a:as) (b:bs) = let rest = unroll as bs --- in [essence| (&a .< permute(&perm,&b)) \/ ((&a = permute(&perm,&b)) /\ &rest) |] +-- in [essence| (&a .< image(&perm,&b)) \/ ((&a = image(&perm,&b)) /\ &rest) |] -- unroll _ _ = bug ("arity mismatch in:" <+> pretty p) -- diff --git a/src/Conjure/UI/Model.hs b/src/Conjure/UI/Model.hs index a16e1e8587..a518f60433 100644 --- a/src/Conjure/UI/Model.hs +++ b/src/Conjure/UI/Model.hs @@ -1323,7 +1323,7 @@ horizontalRules = , Horizontal.Permutation.rule_Permute_Literal , Horizontal.Permutation.rule_Permute_Literal_Comprehension - , Horizontal.Permutation.rule_Apply + , Horizontal.Permutation.rule_Compose diff --git a/tests/custom/permutations/basic/0005_find_int_image_under_given_permutation/permutation.essence b/tests/custom/permutations/basic/0005_find_int_image_under_given_permutation/permutation.essence index 7ec01e48e4..45d202c60c 100644 --- a/tests/custom/permutations/basic/0005_find_int_image_under_given_permutation/permutation.essence +++ b/tests/custom/permutations/basic/0005_find_int_image_under_given_permutation/permutation.essence @@ -8,4 +8,4 @@ letting j be 0 find i : int(0..5) -such that permute(p,i) = j +such that image(p,i) = j diff --git a/tests/custom/permutations/basic/0006_find_int_image_under_given_permutation/permutation.essence b/tests/custom/permutations/basic/0006_find_int_image_under_given_permutation/permutation.essence index 34ccb38417..663688a056 100644 --- a/tests/custom/permutations/basic/0006_find_int_image_under_given_permutation/permutation.essence +++ b/tests/custom/permutations/basic/0006_find_int_image_under_given_permutation/permutation.essence @@ -8,4 +8,4 @@ letting j be 1 find i : int(0..5) -such that permute(p,i) = j +such that image(p,i) = j diff --git a/tests/custom/permutations/basic/0007_find_int_image_under_given_permutation/permutation.essence b/tests/custom/permutations/basic/0007_find_int_image_under_given_permutation/permutation.essence index 2ba9ab44a9..08579eb37f 100644 --- a/tests/custom/permutations/basic/0007_find_int_image_under_given_permutation/permutation.essence +++ b/tests/custom/permutations/basic/0007_find_int_image_under_given_permutation/permutation.essence @@ -8,4 +8,4 @@ letting j be 2 find i : int(0..5) -such that permute(p,i) = j +such that image(p,i) = j diff --git a/tests/custom/permutations/basic/0008_find_int_image_under_two_composed_given_permutations/permutation.essence b/tests/custom/permutations/basic/0008_find_int_image_under_two_composed_given_permutations/permutation.essence index d78d78cbf4..eae172c797 100644 --- a/tests/custom/permutations/basic/0008_find_int_image_under_two_composed_given_permutations/permutation.essence +++ b/tests/custom/permutations/basic/0008_find_int_image_under_two_composed_given_permutations/permutation.essence @@ -11,4 +11,4 @@ letting j be 7 find i : int(1..8) -such that permute(compose(q,p),i) = j +such that image(compose(q,p),i) = j diff --git a/tests/custom/permutations/basic/0009_find_int_image_under_three_composed_given_permutations/permutation.essence b/tests/custom/permutations/basic/0009_find_int_image_under_three_composed_given_permutations/permutation.essence index b7d0b1d02a..d567b59de9 100644 --- a/tests/custom/permutations/basic/0009_find_int_image_under_three_composed_given_permutations/permutation.essence +++ b/tests/custom/permutations/basic/0009_find_int_image_under_three_composed_given_permutations/permutation.essence @@ -11,4 +11,4 @@ letting j be 12 find i : int(1..8) -such that permute(compose(w,compose(w,compose(q,p))),i) = j +such that image(compose(w,compose(w,compose(q,p))),i) = j diff --git a/tests/custom/permutations/basic/0010_find_int_image_under_three_composed_given_permutations/permutation.essence b/tests/custom/permutations/basic/0010_find_int_image_under_three_composed_given_permutations/permutation.essence index e7181a78c0..d9e5268e4b 100644 --- a/tests/custom/permutations/basic/0010_find_int_image_under_three_composed_given_permutations/permutation.essence +++ b/tests/custom/permutations/basic/0010_find_int_image_under_three_composed_given_permutations/permutation.essence @@ -11,4 +11,4 @@ letting j be 20 find i : int(1..30) -such that permute(compose(w,compose(w,compose(q,p))),i) = j +such that image(compose(w,compose(w,compose(q,p))),i) = j diff --git a/tests/custom/permutations/basic/0011_find_int_and_permutation_such_that_int_image_equals_const/permutation.essence b/tests/custom/permutations/basic/0011_find_int_and_permutation_such_that_int_image_equals_const/permutation.essence index d1708afb60..c418d03cc8 100644 --- a/tests/custom/permutations/basic/0011_find_int_and_permutation_such_that_int_image_equals_const/permutation.essence +++ b/tests/custom/permutations/basic/0011_find_int_and_permutation_such_that_int_image_equals_const/permutation.essence @@ -5,4 +5,4 @@ letting j be 20 find i : int(1..30) -such that permute(p,i) = j +such that image(p,i) = j diff --git a/tests/custom/permutations/basic/0012_find_int_and_permutation_such_that_int_image_equals_const/permutation.essence b/tests/custom/permutations/basic/0012_find_int_and_permutation_such_that_int_image_equals_const/permutation.essence index f17eee3982..d4ac226d84 100644 --- a/tests/custom/permutations/basic/0012_find_int_and_permutation_such_that_int_image_equals_const/permutation.essence +++ b/tests/custom/permutations/basic/0012_find_int_and_permutation_such_that_int_image_equals_const/permutation.essence @@ -5,4 +5,4 @@ letting j be 20 find i : int(1..30) -such that permute(p,i) = j +such that image(p,i) = j diff --git a/tests/custom/permutations/basic/0013_find_permutation_such_that_image_of_matrix1_equals_matrix2/permutation.essence b/tests/custom/permutations/basic/0013_find_permutation_such_that_image_of_matrix1_equals_matrix2/permutation.essence index c613663867..cc1f23eb45 100644 --- a/tests/custom/permutations/basic/0013_find_permutation_such_that_image_of_matrix1_equals_matrix2/permutation.essence +++ b/tests/custom/permutations/basic/0013_find_permutation_such_that_image_of_matrix1_equals_matrix2/permutation.essence @@ -7,4 +7,4 @@ letting k be [24,5,4,6] such that forAll i : int(1..4) . - j[i] = permute(p,k[i]) + j[i] = image(p,k[i]) diff --git a/tests/custom/permutations/basic/0014_find_matrix_such_that_swapping_any_index_pairs_becomes_lex_greater/permutation.essence b/tests/custom/permutations/basic/0014_find_matrix_such_that_swapping_any_index_pairs_becomes_lex_greater/permutation.essence index a729fb7bca..897f322677 100644 --- a/tests/custom/permutations/basic/0014_find_matrix_such_that_swapping_any_index_pairs_becomes_lex_greater/permutation.essence +++ b/tests/custom/permutations/basic/0014_find_matrix_such_that_swapping_any_index_pairs_becomes_lex_greater/permutation.essence @@ -4,4 +4,4 @@ find m : matrix indexed by [int(1..9)] of int(0..1) such that forAll i, j : int(1..9) . - i != j -> m <=lex [m[permute(permutation((i,j)),k)] | k : int(1..9)] + i != j -> m <=lex [m[image(permutation((i,j)),k)] | k : int(1..9)] diff --git a/tests/custom/permutations/basic/0015_find_set_of_permuted_elements_of_matrix/permutation.essence b/tests/custom/permutations/basic/0015_find_set_of_permuted_elements_of_matrix/permutation.essence index 5adbfc504a..88f10307d8 100644 --- a/tests/custom/permutations/basic/0015_find_set_of_permuted_elements_of_matrix/permutation.essence +++ b/tests/custom/permutations/basic/0015_find_set_of_permuted_elements_of_matrix/permutation.essence @@ -7,4 +7,4 @@ find k : set of int(1..30) such that forAll i in j . - permute(p, i) in k + image(p, i) in k diff --git a/tests/custom/permutations/basic/0016_find_permutation_such_that_image_is_identity_for_given_matrix/permutation.essence b/tests/custom/permutations/basic/0016_find_permutation_such_that_image_is_identity_for_given_matrix/permutation.essence index c6973b00b4..7dab320548 100644 --- a/tests/custom/permutations/basic/0016_find_permutation_such_that_image_is_identity_for_given_matrix/permutation.essence +++ b/tests/custom/permutations/basic/0016_find_permutation_such_that_image_is_identity_for_given_matrix/permutation.essence @@ -5,5 +5,5 @@ letting j be [20,3,4,7,2,15,12,5] such that forAll i : int(1..4) . - permute(p,j[i]) = j[i] + image(p,j[i]) = j[i] diff --git a/tests/custom/permutations/basic/0017_find_two_permutations_with_overlapping_domains_and_same_image_over_domain_union/permutation.essence b/tests/custom/permutations/basic/0017_find_two_permutations_with_overlapping_domains_and_same_image_over_domain_union/permutation.essence index fab8a15f3a..45f9c2ee03 100644 --- a/tests/custom/permutations/basic/0017_find_two_permutations_with_overlapping_domains_and_same_image_over_domain_union/permutation.essence +++ b/tests/custom/permutations/basic/0017_find_two_permutations_with_overlapping_domains_and_same_image_over_domain_union/permutation.essence @@ -4,5 +4,5 @@ find q : permutation of int(3..7) such that forAll i : int(1..7) . - permute(p,i) = permute(q,i) + image(p,i) = image(q,i) diff --git a/tests/custom/permutations/basic/0018_find_matrix_lex_less_than_under_any_swap/permutation.essence b/tests/custom/permutations/basic/0018_find_matrix_lex_less_than_under_any_swap/permutation.essence index 300a4d28f1..362d8df9cd 100644 --- a/tests/custom/permutations/basic/0018_find_matrix_lex_less_than_under_any_swap/permutation.essence +++ b/tests/custom/permutations/basic/0018_find_matrix_lex_less_than_under_any_swap/permutation.essence @@ -3,4 +3,4 @@ find m : matrix indexed by [int(1..5)] of int(0..1) such that forAll i, j : int(1..5) . - i != j -> m <=lex [m[permute(permutation((i,j)),k)] | k : int(1..5)] + i != j -> m <=lex [m[image(permutation((i,j)),k)] | k : int(1..5)] diff --git a/tests/custom/permutations/basic/0019_find_set_of_permutation_tuples_using_comprehension/permutation.essence b/tests/custom/permutations/basic/0019_find_set_of_permutation_tuples_using_comprehension/permutation.essence index 49e7888ea6..85f4d0ce52 100644 --- a/tests/custom/permutations/basic/0019_find_set_of_permutation_tuples_using_comprehension/permutation.essence +++ b/tests/custom/permutations/basic/0019_find_set_of_permutation_tuples_using_comprehension/permutation.essence @@ -4,4 +4,4 @@ find s : set of (int(1..4), int(1..4)) such that and([ x in s | x <- p]) - /\ and([ permute(p, a) = b | (a,b) <- s]) + /\ and([ image(p, a) = b | (a,b) <- s]) diff --git a/tests/custom/permutations/basic/0020_find_permutation_inverse_using_comprehension/permutation.essence b/tests/custom/permutations/basic/0020_find_permutation_inverse_using_comprehension/permutation.essence index 876cbaab24..5da5e765ba 100644 --- a/tests/custom/permutations/basic/0020_find_permutation_inverse_using_comprehension/permutation.essence +++ b/tests/custom/permutations/basic/0020_find_permutation_inverse_using_comprehension/permutation.essence @@ -3,4 +3,4 @@ find p : permutation (size 10) of int(1..10) find q : permutation (size 10) of int(1..10) such that - and([ permute(p, b) = a | (a,b) <- q]) + and([ image(p, b) = a | (a,b) <- q]) diff --git a/tests/custom/permutations/basic/0021_image_of_int_under_composition_of_two_given_permutations/permutation.essence b/tests/custom/permutations/basic/0021_image_of_int_under_composition_of_two_given_permutations/permutation.essence index 89e0ee7d15..c9605b6589 100644 --- a/tests/custom/permutations/basic/0021_image_of_int_under_composition_of_two_given_permutations/permutation.essence +++ b/tests/custom/permutations/basic/0021_image_of_int_under_composition_of_two_given_permutations/permutation.essence @@ -10,4 +10,4 @@ letting j be 20 find i : int(1..30) -such that permute(compose(q,p),i) = j +such that image(compose(q,p),i) = j diff --git a/tests/custom/permutations/basic/0022_find_matrices_of_enum_x_y_such_that_y_lexless_than_x_under_any_index_swap/permutation.essence b/tests/custom/permutations/basic/0022_find_matrices_of_enum_x_y_such_that_y_lexless_than_x_under_any_index_swap/permutation.essence index 6eb43412f5..b8879b7d12 100644 --- a/tests/custom/permutations/basic/0022_find_matrices_of_enum_x_y_such_that_y_lexless_than_x_under_any_index_swap/permutation.essence +++ b/tests/custom/permutations/basic/0022_find_matrices_of_enum_x_y_such_that_y_lexless_than_x_under_any_index_swap/permutation.essence @@ -10,4 +10,4 @@ find y : matrix indexed by [int(1..n)] of MYTYPE such that forAll i, j : int(1..n) . - i != j -> y .<= permute(permutation((i,j)), x) + i != j -> y .<= image(permutation((i,j)), x) diff --git a/tests/custom/permutations/basic/0023_find_triples_x_y_such_that_y_lex_less_x_under_any_swap/permutation.essence b/tests/custom/permutations/basic/0023_find_triples_x_y_such_that_y_lex_less_x_under_any_swap/permutation.essence index 7b6299176f..8959658bf4 100644 --- a/tests/custom/permutations/basic/0023_find_triples_x_y_such_that_y_lex_less_x_under_any_swap/permutation.essence +++ b/tests/custom/permutations/basic/0023_find_triples_x_y_such_that_y_lex_less_x_under_any_swap/permutation.essence @@ -9,4 +9,4 @@ find y : (int(1..n), int(1..n), int(1..n)) such that forAll i, j : int(1..n) . - i != j -> y .<= permute(permutation((i,j)), x) + i != j -> y .<= image(permutation((i,j)), x) diff --git a/tests/custom/permutations/basic/0024_find_sets_x_y_such_that_y_lexless_x_under_any_swap/permutation.essence b/tests/custom/permutations/basic/0024_find_sets_x_y_such_that_y_lexless_x_under_any_swap/permutation.essence index a220ea12cb..d38c30508f 100644 --- a/tests/custom/permutations/basic/0024_find_sets_x_y_such_that_y_lexless_x_under_any_swap/permutation.essence +++ b/tests/custom/permutations/basic/0024_find_sets_x_y_such_that_y_lexless_x_under_any_swap/permutation.essence @@ -9,4 +9,4 @@ find y : set (size n) of int(1..n) such that forAll i, j : int(1..n) . - i != j -> y .<= permute(permutation((i,j)), x) + i != j -> y .<= image(permutation((i,j)), x) diff --git a/tests/custom/permutations/basic/0025_find_permutation_and_matrices_x_y_such_that_image_x_eq_y/permutation.essence b/tests/custom/permutations/basic/0025_find_permutation_and_matrices_x_y_such_that_image_x_eq_y/permutation.essence index 79eb62c707..f93fac900c 100644 --- a/tests/custom/permutations/basic/0025_find_permutation_and_matrices_x_y_such_that_image_x_eq_y/permutation.essence +++ b/tests/custom/permutations/basic/0025_find_permutation_and_matrices_x_y_such_that_image_x_eq_y/permutation.essence @@ -10,7 +10,7 @@ find y : matrix indexed by [int((n+1)..m)] of int(1..n) such that - y = permute(p,x) + y = image(p,x) /\ allDiff(y) /\ x != y diff --git a/tests/custom/permutations/basic/0026_find_matrices_of_enums_x_y_such_that_y_image_x_under_p/permutation.essence b/tests/custom/permutations/basic/0026_find_matrices_of_enums_x_y_such_that_y_image_x_under_p/permutation.essence index 03db6ad78f..937da2aaad 100644 --- a/tests/custom/permutations/basic/0026_find_matrices_of_enums_x_y_such_that_y_image_x_under_p/permutation.essence +++ b/tests/custom/permutations/basic/0026_find_matrices_of_enums_x_y_such_that_y_image_x_under_p/permutation.essence @@ -11,6 +11,6 @@ find y : matrix indexed by [int(1..n)] of MYTYPE such that - y = permute(p,x) + y = image(p,x) /\ allDiff(y) /\ allDiff(x) diff --git a/tests/custom/permutations/basic/0027_find_sets_of_enum_x_y_such_that_y_image_x_under_p/permutation.essence b/tests/custom/permutations/basic/0027_find_sets_of_enum_x_y_such_that_y_image_x_under_p/permutation.essence index 1db0c54a4d..e33b3b35c6 100644 --- a/tests/custom/permutations/basic/0027_find_sets_of_enum_x_y_such_that_y_image_x_under_p/permutation.essence +++ b/tests/custom/permutations/basic/0027_find_sets_of_enum_x_y_such_that_y_image_x_under_p/permutation.essence @@ -8,5 +8,5 @@ find y : set (size 4) of MYTYPE such that - y = permute(p,x) + y = image(p,x) diff --git a/tests/custom/permutations/basic/0028_find_sets_of_enum_x_y_such_that_y_image_x_under_p/permutation.essence b/tests/custom/permutations/basic/0028_find_sets_of_enum_x_y_such_that_y_image_x_under_p/permutation.essence index af1c2a6d96..d009652492 100644 --- a/tests/custom/permutations/basic/0028_find_sets_of_enum_x_y_such_that_y_image_x_under_p/permutation.essence +++ b/tests/custom/permutations/basic/0028_find_sets_of_enum_x_y_such_that_y_image_x_under_p/permutation.essence @@ -8,6 +8,6 @@ find y : set (size 4) of MYTYPE such that - y = permute(p,x) + y = image(p,x) /\ y != x diff --git a/tests/custom/permutations/basic/0029_find_relations_x_y_such_that_y_image_x_under_p/permutation.essence b/tests/custom/permutations/basic/0029_find_relations_x_y_such_that_y_image_x_under_p/permutation.essence index 5b00bf961b..25233ab564 100644 --- a/tests/custom/permutations/basic/0029_find_relations_x_y_such_that_y_image_x_under_p/permutation.essence +++ b/tests/custom/permutations/basic/0029_find_relations_x_y_such_that_y_image_x_under_p/permutation.essence @@ -8,6 +8,6 @@ find y : relation (size 4) of (MYTYPE*MYTYPE) such that - y = permute(p,x) + y = image(p,x) $ /\ y != x diff --git a/tests/custom/permutations/basic/0031_find_matrix_lexless_indices_swapped_in_comprehension/permutation.essence b/tests/custom/permutations/basic/0031_find_matrix_lexless_indices_swapped_in_comprehension/permutation.essence index 3c65b84b3b..ae70851ae4 100644 --- a/tests/custom/permutations/basic/0031_find_matrix_lexless_indices_swapped_in_comprehension/permutation.essence +++ b/tests/custom/permutations/basic/0031_find_matrix_lexless_indices_swapped_in_comprehension/permutation.essence @@ -2,4 +2,4 @@ find m : matrix indexed by [int(1..9)] of set of int(1) such that forAll i, j : int(1..9) . - i != j -> m <=lex [m[permute(permutation((i,j)),k)] | k : int(1..9)] + i != j -> m <=lex [m[image(permutation((i,j)),k)] | k : int(1..9)] diff --git a/tests/custom/permutations/basic/0032_find_sets_of_ints_such_that_tuple_of_sets_lexless_any_int_swapped_tuple/permutation.essence b/tests/custom/permutations/basic/0032_find_sets_of_ints_such_that_tuple_of_sets_lexless_any_int_swapped_tuple/permutation.essence index 0cf273c710..3cef85e612 100644 --- a/tests/custom/permutations/basic/0032_find_sets_of_ints_such_that_tuple_of_sets_lexless_any_int_swapped_tuple/permutation.essence +++ b/tests/custom/permutations/basic/0032_find_sets_of_ints_such_that_tuple_of_sets_lexless_any_int_swapped_tuple/permutation.essence @@ -6,4 +6,4 @@ find y : set of int(1..n) such that forAll i, j : int(1..n) . - i != j -> (x,y) .<= permute(permutation((i,j)), (x,y)) + i != j -> (x,y) .<= image(permutation((i,j)), (x,y)) diff --git a/tests/custom/permutations/basic/0033_find_matrixes_of_enum_such_that_tuple_of_matrices_lexless_any_int_swapped_tuple/permutation.essence b/tests/custom/permutations/basic/0033_find_matrixes_of_enum_such_that_tuple_of_matrices_lexless_any_int_swapped_tuple/permutation.essence index 21cbd871d8..e47950062d 100644 --- a/tests/custom/permutations/basic/0033_find_matrixes_of_enum_such_that_tuple_of_matrices_lexless_any_int_swapped_tuple/permutation.essence +++ b/tests/custom/permutations/basic/0033_find_matrixes_of_enum_such_that_tuple_of_matrices_lexless_any_int_swapped_tuple/permutation.essence @@ -8,4 +8,4 @@ find y : matrix indexed by [int(1..n)] of MYTYPE such that forAll i, j : int(1..n) . - i != j -> tuple(x,y) .<= permute(permutation((i,j)),tuple(x,y)) + i != j -> tuple(x,y) .<= image(permutation((i,j)),tuple(x,y)) diff --git a/tests/custom/permutations/basic/0034_image_of_empty_permutation/permutation.essence b/tests/custom/permutations/basic/0034_image_of_empty_permutation/permutation.essence index f9ad569e31..c9d1fe6895 100644 --- a/tests/custom/permutations/basic/0034_image_of_empty_permutation/permutation.essence +++ b/tests/custom/permutations/basic/0034_image_of_empty_permutation/permutation.essence @@ -3,4 +3,4 @@ given n : int find j : int(0..100) such that - n = permute(permutation(()),j) + n = image(permutation(()),j) diff --git a/tests/custom/permutations/basic/0035_permutation_of_enum_is_identity_for_integers/permutation.essence b/tests/custom/permutations/basic/0035_permutation_of_enum_is_identity_for_integers/permutation.essence index 7e6c0c0ceb..feff622574 100644 --- a/tests/custom/permutations/basic/0035_permutation_of_enum_is_identity_for_integers/permutation.essence +++ b/tests/custom/permutations/basic/0035_permutation_of_enum_is_identity_for_integers/permutation.essence @@ -3,8 +3,8 @@ letting e be new type enum {E1, E2, E3, E4} find s : permutation of e such that - permute(s, E1)= E2, + image(s, E1)= E2, forAll i : int(-10..10) . - permute(s, i) = i + image(s, i) = i diff --git a/tests/custom/permutations/basic/0036_big_test_of_enums_in_matrices/permutation.essence b/tests/custom/permutations/basic/0036_big_test_of_enums_in_matrices/permutation.essence index d20443d51b..db47699eb5 100644 --- a/tests/custom/permutations/basic/0036_big_test_of_enums_in_matrices/permutation.essence +++ b/tests/custom/permutations/basic/0036_big_test_of_enums_in_matrices/permutation.essence @@ -9,11 +9,11 @@ find x1 : matrix indexed by [e] of e find x2 : matrix indexed by [e] of e such that - permute(s, m1) = m2 - , permute(s, n1) = n2 - , permute(s, x1) = x2 + image(s, m1) = m2 + , image(s, n1) = n2 + , image(s, x1) = x2 , forAll i : e . - permute(s, i) != i + image(s, i) != i , allDiff(m1), allDiff(n1), allDiff(x1) , x1[E1]=E3 diff --git a/tests/custom/permutations/basic/0037_matrices_of_enums_indexed_by_enums/permutation.essence b/tests/custom/permutations/basic/0037_matrices_of_enums_indexed_by_enums/permutation.essence index 5f0c7770e7..0620281665 100644 --- a/tests/custom/permutations/basic/0037_matrices_of_enums_indexed_by_enums/permutation.essence +++ b/tests/custom/permutations/basic/0037_matrices_of_enums_indexed_by_enums/permutation.essence @@ -6,7 +6,7 @@ find x2 : matrix indexed by [e] of e such that forAll i : e . - permute(s,i) != i - , permute(s, x1) = x2 + image(s,i) != i + , image(s, x1) = x2 , x1 != x2 diff --git a/tests/custom/permutations/basic/0038_matricies_of_tuples_of_enums_indexed_by_enums/permutation.essence b/tests/custom/permutations/basic/0038_matricies_of_tuples_of_enums_indexed_by_enums/permutation.essence index 18cf9e25af..63626dab1d 100644 --- a/tests/custom/permutations/basic/0038_matricies_of_tuples_of_enums_indexed_by_enums/permutation.essence +++ b/tests/custom/permutations/basic/0038_matricies_of_tuples_of_enums_indexed_by_enums/permutation.essence @@ -6,6 +6,6 @@ find x2 : matrix indexed by [e] of (e,e) such that forAll i : e . - permute(s,i) != i - , permute(s, x1) = x2 + image(s,i) != i + , image(s, x1) = x2 , x1 != x2 From 06b07e559b1b256894108dee14256e3ba8679450 Mon Sep 17 00:00:00 2001 From: Fraser Dunlop Date: Wed, 21 Nov 2018 17:57:59 +0000 Subject: [PATCH 026/229] Renamed permute to image overloaded --- conjure-cp.cabal | 1 - src/Conjure/Compute/DomainOf.hs | 5 -- src/Conjure/Language/Expression/Op.hs | 2 - src/Conjure/Language/Expression/Op/Permute.hs | 55 ------------------- 4 files changed, 63 deletions(-) delete mode 100644 src/Conjure/Language/Expression/Op/Permute.hs diff --git a/conjure-cp.cabal b/conjure-cp.cabal index 81cfab2fe8..fb05e6223b 100644 --- a/conjure-cp.cabal +++ b/conjure-cp.cabal @@ -88,7 +88,6 @@ Library , Conjure.Language.Expression.Op.Participants , Conjure.Language.Expression.Op.Parts , Conjure.Language.Expression.Op.Party - , Conjure.Language.Expression.Op.Permute , Conjure.Language.Expression.Op.PermutationTuples , Conjure.Language.Expression.Op.Pow , Conjure.Language.Expression.Op.PowerSet diff --git a/src/Conjure/Compute/DomainOf.hs b/src/Conjure/Compute/DomainOf.hs index dc36b6ec7f..3d0cd0204c 100644 --- a/src/Conjure/Compute/DomainOf.hs +++ b/src/Conjure/Compute/DomainOf.hs @@ -119,7 +119,6 @@ instance (DomainOf x, TypeOf x, Pretty x, ExpressionLike x, Domain () x :< x, Do domainOf (MkOpParticipants x) = domainOf x domainOf (MkOpParts x) = domainOf x domainOf (MkOpParty x) = domainOf x - domainOf (MkOpPermute x) = domainOf x domainOf (MkOpPermutationTuples x) = domainOf x domainOf (MkOpPow x) = domainOf x domainOf (MkOpPowerSet x) = domainOf x @@ -193,7 +192,6 @@ instance (DomainOf x, TypeOf x, Pretty x, ExpressionLike x, Domain () x :< x, Do indexDomainsOf (MkOpParticipants x) = indexDomainsOf x indexDomainsOf (MkOpParts x) = indexDomainsOf x indexDomainsOf (MkOpParty x) = indexDomainsOf x - indexDomainsOf (MkOpPermute x) = indexDomainsOf x indexDomainsOf (MkOpPermutationTuples x) = indexDomainsOf x indexDomainsOf (MkOpPow x) = indexDomainsOf x indexDomainsOf (MkOpPowerSet x) = indexDomainsOf x @@ -509,9 +507,6 @@ instance DomainOf x => DomainOf (OpParts x) where instance (Pretty x, TypeOf x) => DomainOf (OpParty x) where domainOf op = mkDomainAny ("OpParty:" <++> pretty op) <$> typeOf op -instance (Pretty x, TypeOf x) => DomainOf (OpPermute x) where - domainOf op = mkDomainAny ("OpPermute:" <++> pretty op) <$> typeOf op - instance (Pretty x, TypeOf x) => DomainOf (OpPermutationTuples x) where domainOf op = mkDomainAny ("OpPermutationTuples:" <++> pretty op) <$> typeOf op diff --git a/src/Conjure/Language/Expression/Op.hs b/src/Conjure/Language/Expression/Op.hs index 5a8461348b..a8442157fa 100644 --- a/src/Conjure/Language/Expression/Op.hs +++ b/src/Conjure/Language/Expression/Op.hs @@ -117,8 +117,6 @@ mkOp op xs = L_party -> inject $ MkOpParty $ OpParty (arg xs 0 "party") (arg xs 1 "party") L_participants -> inject $ MkOpParticipants $ OpParticipants (arg xs 0 "participants") - L_image -> inject $ MkOpPermute $ OpPermute (arg xs 0 "image") - (arg xs 1 "image") L_permutationTuples -> inject $ MkOpPermutationTuples $ OpPermutationTuples (arg xs 0 "permutationTuples") L_compose -> inject $ MkOpCompose $ OpCompose (arg xs 0 "compose") (arg xs 1 "compose") diff --git a/src/Conjure/Language/Expression/Op/Permute.hs b/src/Conjure/Language/Expression/Op/Permute.hs deleted file mode 100644 index 5e5262c4ce..0000000000 --- a/src/Conjure/Language/Expression/Op/Permute.hs +++ /dev/null @@ -1,55 +0,0 @@ -{-# LANGUAGE DeriveGeneric, DeriveDataTypeable, DeriveFunctor, DeriveTraversable, DeriveFoldable, ViewPatterns #-} - -module Conjure.Language.Expression.Op.Permute where - -import Conjure.Prelude -import Conjure.Language.Expression.Op.Internal.Common -import Conjure.Bug - -import qualified Data.Aeson as JSON -- aeson -import qualified Data.HashMap.Strict as M -- unordered-containers -import qualified Data.Vector as V -- vector - -import Data.List (cycle) - -data OpPermute x = OpPermute x x - deriving (Eq, Ord, Show, Data, Functor, Traversable, Foldable, Typeable, Generic) - -instance Serialize x => Serialize (OpPermute x) -instance Hashable x => Hashable (OpPermute x) -instance ToJSON x => ToJSON (OpPermute x) where toJSON = genericToJSON jsonOptions -instance FromJSON x => FromJSON (OpPermute x) where parseJSON = genericParseJSON jsonOptions - -instance (TypeOf x, Pretty x) => TypeOf (OpPermute x) where - typeOf inp@(OpPermute p i) = do - pTy <- typeOf p - iTy <- typeOf i - case (pTy,iTy) of - (TypePermutation _, thing) -> return thing - _ -> raiseTypeError inp - -instance EvaluateOp OpPermute where - evaluateOp op@(OpPermute (viewConstantPermutation -> Just xss) i) = do - ti <- typeOf i - case ti of - TypeInt _-> case filter (i `elem`) xss of - [] -> return i - [h] -> return $ head $ drop 1 $ dropWhile (/= i) $ cycle h - _ -> bug "evaluateOp{OpPermute} element should only be in one cycle of permutation" - _ -> na $ "evaluateOp{OpPermute} only defined for Ints right now:" <++> pretty (show op) - evaluateOp op = na $ "evaluateOp{OpPermute}:" <++> pretty (show op) - -instance SimplifyOp OpPermute x where - simplifyOp _ = na "simplifyOp{OpPermute}" - -instance Pretty x => Pretty (OpPermute x) where - prettyPrec _ (OpPermute a i) = "image" <> prettyList prParens "," [a,i] - -instance VarSymBreakingDescription x => VarSymBreakingDescription (OpPermute x) where - varSymBreakingDescription (OpPermute a i) = JSON.Object $ M.fromList - [ ("type", JSON.String "OpPermute") - , ("children", JSON.Array $ V.fromList - [ varSymBreakingDescription a - , varSymBreakingDescription i - ]) - ] From 333eaf2b2524f870d7dda66c1815daa1328bd1d3 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?O=CC=88zgu=CC=88r=20Akgu=CC=88n?= Date: Mon, 26 Nov 2018 13:25:24 +0000 Subject: [PATCH 027/229] Use https for the permutation-safe repository dependency --- etc/hs-deps/stack-8.0.yaml | 2 +- etc/hs-deps/stack-8.2.yaml | 2 +- etc/hs-deps/stack-8.4.yaml | 2 +- 3 files changed, 3 insertions(+), 3 deletions(-) diff --git a/etc/hs-deps/stack-8.0.yaml b/etc/hs-deps/stack-8.0.yaml index 523c701942..9016a71325 100644 --- a/etc/hs-deps/stack-8.0.yaml +++ b/etc/hs-deps/stack-8.0.yaml @@ -12,5 +12,5 @@ extra-deps: - tasty-1.1.0.1 - tasty-ant-xml-1.1.4 - optparse-applicative-0.14.2.0 -- git: git@github.com:fraser-dunlop/permutation-safe.git +- git: https://github.com/fraser-dunlop/permutation-safe.git commit: 8b0f5afe8d5262df70860aeab456596fe19cf512 diff --git a/etc/hs-deps/stack-8.2.yaml b/etc/hs-deps/stack-8.2.yaml index ed187a1b27..9f0644703e 100644 --- a/etc/hs-deps/stack-8.2.yaml +++ b/etc/hs-deps/stack-8.2.yaml @@ -8,5 +8,5 @@ extra-deps: - transformers-0.5.5.0 - tasty-1.1.0.1 - tasty-ant-xml-1.1.4 -- git: git@github.com:fraser-dunlop/permutation-safe.git +- git: https://github.com/fraser-dunlop/permutation-safe.git commit: 8b0f5afe8d5262df70860aeab456596fe19cf512 diff --git a/etc/hs-deps/stack-8.4.yaml b/etc/hs-deps/stack-8.4.yaml index bdccaa1ed2..a4b2643a94 100644 --- a/etc/hs-deps/stack-8.4.yaml +++ b/etc/hs-deps/stack-8.4.yaml @@ -7,5 +7,5 @@ extra-deps: - megaparsec-4.4.0 - tasty-1.1.0.1 - tasty-ant-xml-1.1.4 -- git: git@github.com:fraser-dunlop/permutation-safe.git +- git: https://github.com/fraser-dunlop/permutation-safe.git commit: 8b0f5afe8d5262df70860aeab456596fe19cf512 From 3d4e1e5ea6225135d50eeb8ef757640bf94d660f Mon Sep 17 00:00:00 2001 From: Fraser Dunlop Date: Mon, 26 Nov 2018 14:27:50 +0000 Subject: [PATCH 028/229] Rules for permutation equality --- .../Rules/Vertical/Permutation/AsFunction.hs | 39 +++++++++++++++++++ src/Conjure/UI/Model.hs | 3 +- 2 files changed, 41 insertions(+), 1 deletion(-) diff --git a/src/Conjure/Rules/Vertical/Permutation/AsFunction.hs b/src/Conjure/Rules/Vertical/Permutation/AsFunction.hs index 174419888b..de6d4b40cd 100644 --- a/src/Conjure/Rules/Vertical/Permutation/AsFunction.hs +++ b/src/Conjure/Rules/Vertical/Permutation/AsFunction.hs @@ -5,6 +5,45 @@ module Conjure.Rules.Vertical.Permutation.AsFunction where import Conjure.Rules.Import import Conjure.Rules.Vertical.Matrix (flattenIfNeeded) +rule_Permutation_Equality :: Rule +rule_Permutation_Equality = "permutation-equality{AsFunction}" `namedRule` theRule where + theRule [essence| &p1 = &p2|] = do + TypePermutation{} <- typeOf p1 + Permutation_AsFunction <- representationOf p1 + TypePermutation{} <- typeOf p2 + Permutation_AsFunction <- representationOf p2 + [f1] <- downX1 p2 + [f2] <- downX1 p2 + return + ( "Vertical rule for permutation-equality, AsFunction representation" + , return [essence| &f1 = &f2 |] + ) + theRule _ = na "rule_Permutation_Equality" + + +rule_Permutation_Equality_Comprehension :: Rule +rule_Permutation_Equality_Comprehension = "permutation-equality-comprehension{AsFunction}" `namedRule` theRule where + theRule (Comprehension body gensOrConds) = do + (gocBefore, (pat, p1, p2), gocAfter) <- matchFirst gensOrConds $ \ goc -> case goc of + Generator (GenInExpr pat [essence| &p1 = &p2|] ) -> return (pat, p1, p2) + _ -> na "rule_Comprehension" + TypePermutation{} <- typeOf p1 + Permutation_AsFunction <- representationOf p1 + TypePermutation{} <- typeOf p2 + Permutation_AsFunction <- representationOf p2 + [f1] <- downX1 p2 + [f2] <- downX1 p2 + return + ( "Vertical rule for permutation-equality-comprehension, AsFunction representation" + , do + return $ Comprehension body + $ gocBefore + ++ [ Generator (GenInExpr pat [essence| &f1 = &f2 |]) + ] + ++ gocAfter + ) + theRule _ = na "rule_Permutation_Equality_Comprehension" + rule_Permute_Comprehension_Tuples :: Rule rule_Permute_Comprehension_Tuples = "permutation-comprehension-tuples{AsFunction}" `namedRule` theRule where theRule (Comprehension body gensOrConds) = do diff --git a/src/Conjure/UI/Model.hs b/src/Conjure/UI/Model.hs index 75e853b9d1..4de43b83bc 100644 --- a/src/Conjure/UI/Model.hs +++ b/src/Conjure/UI/Model.hs @@ -1187,7 +1187,8 @@ verticalRules = , Vertical.Partition.PartitionAsSet.rule_Comprehension , Vertical.Partition.Occurrence.rule_Comprehension - + , Vertical.Permutation.AsFunction.rule_Permutation_Equality + , Vertical.Permutation.AsFunction.rule_Permutation_Equality_Comprehension , Vertical.Permutation.AsFunction.rule_Permute_Comprehension_Tuples , Vertical.Permutation.AsFunction.rule_Relation_Permute , Vertical.Permutation.AsFunction.rule_Relation_Permute_Comprehension From e46d57beec6984fa95113f956d865955439ee26d Mon Sep 17 00:00:00 2001 From: Fraser Dunlop Date: Mon, 26 Nov 2018 14:30:32 +0000 Subject: [PATCH 029/229] Changed permutation-safe version --- etc/hs-deps/stack-8.0.yaml | 2 +- etc/hs-deps/stack-8.2.yaml | 2 +- etc/hs-deps/stack-8.4.yaml | 2 +- 3 files changed, 3 insertions(+), 3 deletions(-) diff --git a/etc/hs-deps/stack-8.0.yaml b/etc/hs-deps/stack-8.0.yaml index 523c701942..e04925ebd1 100644 --- a/etc/hs-deps/stack-8.0.yaml +++ b/etc/hs-deps/stack-8.0.yaml @@ -13,4 +13,4 @@ extra-deps: - tasty-ant-xml-1.1.4 - optparse-applicative-0.14.2.0 - git: git@github.com:fraser-dunlop/permutation-safe.git - commit: 8b0f5afe8d5262df70860aeab456596fe19cf512 + commit: 52b577751f6ebb55e333471829fff4dc1b44fc98 diff --git a/etc/hs-deps/stack-8.2.yaml b/etc/hs-deps/stack-8.2.yaml index ed187a1b27..f267911435 100644 --- a/etc/hs-deps/stack-8.2.yaml +++ b/etc/hs-deps/stack-8.2.yaml @@ -9,4 +9,4 @@ extra-deps: - tasty-1.1.0.1 - tasty-ant-xml-1.1.4 - git: git@github.com:fraser-dunlop/permutation-safe.git - commit: 8b0f5afe8d5262df70860aeab456596fe19cf512 + commit: 52b577751f6ebb55e333471829fff4dc1b44fc98 diff --git a/etc/hs-deps/stack-8.4.yaml b/etc/hs-deps/stack-8.4.yaml index bdccaa1ed2..399342e591 100644 --- a/etc/hs-deps/stack-8.4.yaml +++ b/etc/hs-deps/stack-8.4.yaml @@ -8,4 +8,4 @@ extra-deps: - tasty-1.1.0.1 - tasty-ant-xml-1.1.4 - git: git@github.com:fraser-dunlop/permutation-safe.git - commit: 8b0f5afe8d5262df70860aeab456596fe19cf512 + commit: 52b577751f6ebb55e333471829fff4dc1b44fc98 From 77003e0aa4d9a53013601dd57944631245a2a3bd Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?O=CC=88zgu=CC=88r=20Akgu=CC=88n?= Date: Mon, 26 Nov 2018 16:09:06 +0000 Subject: [PATCH 030/229] Remove merge conflict files --- etc/hs-deps/stack-8.0.yaml.orig | 24 ------------------------ etc/hs-deps/stack-8.2.yaml.orig | 20 -------------------- etc/hs-deps/stack-8.4.yaml.orig | 19 ------------------- 3 files changed, 63 deletions(-) delete mode 100644 etc/hs-deps/stack-8.0.yaml.orig delete mode 100644 etc/hs-deps/stack-8.2.yaml.orig delete mode 100644 etc/hs-deps/stack-8.4.yaml.orig diff --git a/etc/hs-deps/stack-8.0.yaml.orig b/etc/hs-deps/stack-8.0.yaml.orig deleted file mode 100644 index a960cba97b..0000000000 --- a/etc/hs-deps/stack-8.0.yaml.orig +++ /dev/null @@ -1,24 +0,0 @@ -resolver: lts-9.21 -packages: -- '.' -system-ghc: true -install-ghc: true -extra-deps: -- containers-0.5.11.0 -- megaparsec-4.4.0 -- aeson-1.2.4.0 -- transformers-0.5.5.0 -- semigroups-0.18.4 -- tasty-1.1.0.1 -- tasty-ant-xml-1.1.4 -- optparse-applicative-0.14.2.0 -<<<<<<< HEAD -- git: git@github.com:fraser-dunlop/permutation-safe.git - commit: 52b577751f6ebb55e333471829fff4dc1b44fc98 -||||||| merged common ancestors -- git: git@github.com:fraser-dunlop/permutation-safe.git - commit: 8b0f5afe8d5262df70860aeab456596fe19cf512 -======= -- git: https://github.com/fraser-dunlop/permutation-safe.git - commit: 8b0f5afe8d5262df70860aeab456596fe19cf512 ->>>>>>> 333eaf2b2524f870d7dda66c1815daa1328bd1d3 diff --git a/etc/hs-deps/stack-8.2.yaml.orig b/etc/hs-deps/stack-8.2.yaml.orig deleted file mode 100644 index 81ab9a645c..0000000000 --- a/etc/hs-deps/stack-8.2.yaml.orig +++ /dev/null @@ -1,20 +0,0 @@ -resolver: lts-11.22 -packages: -- '.' -system-ghc: true -install-ghc: true -extra-deps: -- megaparsec-4.4.0 -- transformers-0.5.5.0 -- tasty-1.1.0.1 -- tasty-ant-xml-1.1.4 -<<<<<<< HEAD -- git: git@github.com:fraser-dunlop/permutation-safe.git - commit: 52b577751f6ebb55e333471829fff4dc1b44fc98 -||||||| merged common ancestors -- git: git@github.com:fraser-dunlop/permutation-safe.git - commit: 8b0f5afe8d5262df70860aeab456596fe19cf512 -======= -- git: https://github.com/fraser-dunlop/permutation-safe.git - commit: 8b0f5afe8d5262df70860aeab456596fe19cf512 ->>>>>>> 333eaf2b2524f870d7dda66c1815daa1328bd1d3 diff --git a/etc/hs-deps/stack-8.4.yaml.orig b/etc/hs-deps/stack-8.4.yaml.orig deleted file mode 100644 index c6b9434746..0000000000 --- a/etc/hs-deps/stack-8.4.yaml.orig +++ /dev/null @@ -1,19 +0,0 @@ -resolver: lts-12.17 -packages: -- '.' -system-ghc: true -install-ghc: true -extra-deps: -- megaparsec-4.4.0 -- tasty-1.1.0.1 -- tasty-ant-xml-1.1.4 -<<<<<<< HEAD -- git: git@github.com:fraser-dunlop/permutation-safe.git - commit: 52b577751f6ebb55e333471829fff4dc1b44fc98 -||||||| merged common ancestors -- git: git@github.com:fraser-dunlop/permutation-safe.git - commit: 8b0f5afe8d5262df70860aeab456596fe19cf512 -======= -- git: https://github.com/fraser-dunlop/permutation-safe.git - commit: 8b0f5afe8d5262df70860aeab456596fe19cf512 ->>>>>>> 333eaf2b2524f870d7dda66c1815daa1328bd1d3 From 57af4db09e7b61a14eebafabd552f60be8261a91 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?O=CC=88zgu=CC=88r=20Akgu=CC=88n?= Date: Mon, 26 Nov 2018 16:28:37 +0000 Subject: [PATCH 031/229] Removing more *.orig files -- assuming these were added by mistake in the first place --- src/Conjure/Compute/DomainOf.hs.orig | 712 ----- src/Conjure/Compute/DomainUnion.hs.orig | 188 -- src/Conjure/Language/Arbitrary.hs.orig | 345 --- src/Conjure/Language/Constant.hs.orig | 844 ------ src/Conjure/Language/Domain.hs.orig | 1180 -------- src/Conjure/Language/Expression.hs.orig | 877 ------ .../Language/Expression/DomainSizeOf.hs.orig | 131 - .../Expression/Op/AllDiffExcept.hs.orig | 67 - .../Language/Expression/Op/Defined.hs.orig | 55 - .../Language/Expression/Op/Div.hs.orig | 65 - .../Language/Expression/Op/Factorial.hs.orig | 54 - .../Language/Expression/Op/Flatten.hs.orig | 82 - .../Language/Expression/Op/Freq.hs.orig | 63 - .../Language/Expression/Op/Geq.hs.orig | 59 - src/Conjure/Language/Expression/Op/Gt.hs.orig | 58 - .../Language/Expression/Op/Hist.hs.orig | 77 - .../Language/Expression/Op/Image.hs.orig | 91 - .../Language/Expression/Op/ImageSet.hs.orig | 71 - .../Language/Expression/Op/Indexing.hs.orig | 153 -- .../Expression/Op/Internal/Common.hs.orig | 334 --- .../Language/Expression/Op/Leq.hs.orig | 58 - src/Conjure/Language/Expression/Op/Lt.hs.orig | 58 - .../Language/Expression/Op/Max.hs.orig | 187 -- .../Language/Expression/Op/Min.hs.orig | 188 -- .../Language/Expression/Op/Minus.hs.orig | 98 - .../Language/Expression/Op/Mod.hs.orig | 65 - .../Language/Expression/Op/Negate.hs.orig | 54 - .../Language/Expression/Op/Pow.hs.orig | 65 - .../Language/Expression/Op/PreImage.hs.orig | 70 - .../Language/Expression/Op/Pred.hs.orig | 65 - .../Language/Expression/Op/Product.hs.orig | 102 - .../Language/Expression/Op/Slicing.hs.orig | 85 - .../Language/Expression/Op/Succ.hs.orig | 65 - .../Language/Expression/Op/Sum.hs.orig | 97 - .../Language/Expression/Op/TildeLt.hs.orig | 135 - .../Language/Expression/Op/ToInt.hs.orig | 66 - .../Language/Expression/Op/TwoBars.hs.orig | 109 - src/Conjure/Language/Instantiate.hs.orig | 448 --- src/Conjure/Language/Lenses.hs.orig | 1544 ----------- src/Conjure/Language/NameResolution.hs.orig | 294 -- src/Conjure/Language/Parser.hs.orig | 1146 -------- src/Conjure/Language/ParserC.hs.orig | 755 ------ src/Conjure/Language/Type.hs.orig | 323 --- src/Conjure/Language/ZeroVal.hs.orig | 93 - src/Conjure/Process/Enumerate.hs.orig | 246 -- src/Conjure/Process/Enums.hs.orig | 333 --- src/Conjure/Process/FiniteGivens.hs.orig | 760 ------ src/Conjure/Process/InferAttributes.hs.orig | 84 - .../Process/ModelStrengthening.hs.orig | 909 ------- src/Conjure/Process/Unnameds.hs.orig | 32 - .../Function/Function1D.hs.orig | 188 -- .../MSet/ExplicitWithFlags.hs.orig | 224 -- .../MSet/ExplicitWithRepetition.hs.orig | 251 -- .../Partition/Occurrence.hs.orig | 380 --- .../Partition/PartitionAsSet.hs.orig | 200 -- src/Conjure/Representations/Primitive.hs.orig | 39 - .../Sequence/ExplicitBounded.hs.orig | 338 --- .../Representations/Set/Explicit.hs.orig | 113 - .../Set/ExplicitVarSizeWithDummy.hs.orig | 216 -- .../Set/ExplicitVarSizeWithFlags.hs.orig | 192 -- .../Set/ExplicitVarSizeWithMarker.hs.orig | 177 -- .../Representations/Set/Occurrence.hs.orig | 117 - src/Conjure/Rules/DontCare.hs.orig | 178 -- src/Conjure/Rules/Horizontal/Function.hs.orig | 874 ------ src/Conjure/Rules/Horizontal/MSet.hs.orig | 278 -- .../Rules/Horizontal/Partition.hs.orig | 219 -- src/Conjure/Rules/Horizontal/Relation.hs.orig | 275 -- src/Conjure/Rules/Horizontal/Sequence.hs.orig | 635 ----- src/Conjure/Rules/Horizontal/Set.hs.orig | 471 ---- src/Conjure/Rules/Vertical/Matrix.hs.orig | 572 ---- src/Conjure/Rules/Vertical/Tuple.hs.orig | 253 -- src/Conjure/UI/Model.hs.orig | 2303 ---------------- src/Conjure/UI/TranslateParameter.hs.orig | 183 -- src/Conjure/UI/TypeCheck.hs.orig | 180 -- src/Conjure/UI/ValidateSolution.hs.orig | 199 -- .../Conjure/Language/DomainSizeTest.hs.orig | 82 - src/test/Conjure/RepresentationsTest.hs.orig | 2407 ----------------- 77 files changed, 25584 deletions(-) delete mode 100644 src/Conjure/Compute/DomainOf.hs.orig delete mode 100644 src/Conjure/Compute/DomainUnion.hs.orig delete mode 100644 src/Conjure/Language/Arbitrary.hs.orig delete mode 100644 src/Conjure/Language/Constant.hs.orig delete mode 100644 src/Conjure/Language/Domain.hs.orig delete mode 100644 src/Conjure/Language/Expression.hs.orig delete mode 100644 src/Conjure/Language/Expression/DomainSizeOf.hs.orig delete mode 100644 src/Conjure/Language/Expression/Op/AllDiffExcept.hs.orig delete mode 100644 src/Conjure/Language/Expression/Op/Defined.hs.orig delete mode 100644 src/Conjure/Language/Expression/Op/Div.hs.orig delete mode 100644 src/Conjure/Language/Expression/Op/Factorial.hs.orig delete mode 100644 src/Conjure/Language/Expression/Op/Flatten.hs.orig delete mode 100644 src/Conjure/Language/Expression/Op/Freq.hs.orig delete mode 100644 src/Conjure/Language/Expression/Op/Geq.hs.orig delete mode 100644 src/Conjure/Language/Expression/Op/Gt.hs.orig delete mode 100644 src/Conjure/Language/Expression/Op/Hist.hs.orig delete mode 100644 src/Conjure/Language/Expression/Op/Image.hs.orig delete mode 100644 src/Conjure/Language/Expression/Op/ImageSet.hs.orig delete mode 100644 src/Conjure/Language/Expression/Op/Indexing.hs.orig delete mode 100644 src/Conjure/Language/Expression/Op/Internal/Common.hs.orig delete mode 100644 src/Conjure/Language/Expression/Op/Leq.hs.orig delete mode 100644 src/Conjure/Language/Expression/Op/Lt.hs.orig delete mode 100644 src/Conjure/Language/Expression/Op/Max.hs.orig delete mode 100644 src/Conjure/Language/Expression/Op/Min.hs.orig delete mode 100644 src/Conjure/Language/Expression/Op/Minus.hs.orig delete mode 100644 src/Conjure/Language/Expression/Op/Mod.hs.orig delete mode 100644 src/Conjure/Language/Expression/Op/Negate.hs.orig delete mode 100644 src/Conjure/Language/Expression/Op/Pow.hs.orig delete mode 100644 src/Conjure/Language/Expression/Op/PreImage.hs.orig delete mode 100644 src/Conjure/Language/Expression/Op/Pred.hs.orig delete mode 100644 src/Conjure/Language/Expression/Op/Product.hs.orig delete mode 100644 src/Conjure/Language/Expression/Op/Slicing.hs.orig delete mode 100644 src/Conjure/Language/Expression/Op/Succ.hs.orig delete mode 100644 src/Conjure/Language/Expression/Op/Sum.hs.orig delete mode 100644 src/Conjure/Language/Expression/Op/TildeLt.hs.orig delete mode 100644 src/Conjure/Language/Expression/Op/ToInt.hs.orig delete mode 100644 src/Conjure/Language/Expression/Op/TwoBars.hs.orig delete mode 100644 src/Conjure/Language/Instantiate.hs.orig delete mode 100644 src/Conjure/Language/Lenses.hs.orig delete mode 100644 src/Conjure/Language/NameResolution.hs.orig delete mode 100644 src/Conjure/Language/Parser.hs.orig delete mode 100644 src/Conjure/Language/ParserC.hs.orig delete mode 100644 src/Conjure/Language/Type.hs.orig delete mode 100644 src/Conjure/Language/ZeroVal.hs.orig delete mode 100644 src/Conjure/Process/Enumerate.hs.orig delete mode 100644 src/Conjure/Process/Enums.hs.orig delete mode 100644 src/Conjure/Process/FiniteGivens.hs.orig delete mode 100644 src/Conjure/Process/InferAttributes.hs.orig delete mode 100644 src/Conjure/Process/ModelStrengthening.hs.orig delete mode 100644 src/Conjure/Process/Unnameds.hs.orig delete mode 100644 src/Conjure/Representations/Function/Function1D.hs.orig delete mode 100644 src/Conjure/Representations/MSet/ExplicitWithFlags.hs.orig delete mode 100644 src/Conjure/Representations/MSet/ExplicitWithRepetition.hs.orig delete mode 100644 src/Conjure/Representations/Partition/Occurrence.hs.orig delete mode 100644 src/Conjure/Representations/Partition/PartitionAsSet.hs.orig delete mode 100644 src/Conjure/Representations/Primitive.hs.orig delete mode 100644 src/Conjure/Representations/Sequence/ExplicitBounded.hs.orig delete mode 100644 src/Conjure/Representations/Set/Explicit.hs.orig delete mode 100644 src/Conjure/Representations/Set/ExplicitVarSizeWithDummy.hs.orig delete mode 100644 src/Conjure/Representations/Set/ExplicitVarSizeWithFlags.hs.orig delete mode 100644 src/Conjure/Representations/Set/ExplicitVarSizeWithMarker.hs.orig delete mode 100644 src/Conjure/Representations/Set/Occurrence.hs.orig delete mode 100644 src/Conjure/Rules/DontCare.hs.orig delete mode 100644 src/Conjure/Rules/Horizontal/Function.hs.orig delete mode 100644 src/Conjure/Rules/Horizontal/MSet.hs.orig delete mode 100644 src/Conjure/Rules/Horizontal/Partition.hs.orig delete mode 100644 src/Conjure/Rules/Horizontal/Relation.hs.orig delete mode 100644 src/Conjure/Rules/Horizontal/Sequence.hs.orig delete mode 100644 src/Conjure/Rules/Horizontal/Set.hs.orig delete mode 100644 src/Conjure/Rules/Vertical/Matrix.hs.orig delete mode 100644 src/Conjure/Rules/Vertical/Tuple.hs.orig delete mode 100644 src/Conjure/UI/Model.hs.orig delete mode 100644 src/Conjure/UI/TranslateParameter.hs.orig delete mode 100644 src/Conjure/UI/TypeCheck.hs.orig delete mode 100644 src/Conjure/UI/ValidateSolution.hs.orig delete mode 100644 src/test/Conjure/Language/DomainSizeTest.hs.orig delete mode 100644 src/test/Conjure/RepresentationsTest.hs.orig diff --git a/src/Conjure/Compute/DomainOf.hs.orig b/src/Conjure/Compute/DomainOf.hs.orig deleted file mode 100644 index ac04bbd38f..0000000000 --- a/src/Conjure/Compute/DomainOf.hs.orig +++ /dev/null @@ -1,712 +0,0 @@ -{-# LANGUAGE QuasiQuotes #-} -{-# LANGUAGE UndecidableInstances #-} - -module Conjure.Compute.DomainOf ( DomainOf(..) ) where - --- conjure -import Conjure.Prelude -import Conjure.Bug - -import Conjure.Language -import Conjure.Language.TypeOf -import Conjure.Compute.DomainUnion - - -type Dom = Domain () Expression - -class DomainOf a where - - -- | calculate the domain of `a` - domainOf - :: (MonadFail m, NameGen m) - => a -> m Dom - - -- | calculate the index domains of `a` - -- the index is the index of a matrix. - -- returns [] for non-matrix inputs. - -- has a default implementation in terms of domainOf, so doesn't need to be implemented specifically. - -- but sometimes it is better to implement this directly. - indexDomainsOf - :: (MonadFail m, NameGen m, Pretty a) - => a -> m [Dom] - indexDomainsOf = defIndexDomainsOf - -defIndexDomainsOf :: (MonadFail m, NameGen m, DomainOf a) => a -> m [Dom] -defIndexDomainsOf x = do - dom <- domainOf x - let - collect (DomainMatrix index inner) = index : collect inner - collect _ = [] - return (collect dom) - -instance DomainOf ReferenceTo where - domainOf (Alias x) = domainOf x - domainOf (InComprehension (GenDomainNoRepr Single{} dom)) = return dom - domainOf (InComprehension (GenDomainHasRepr _ dom)) = return (forgetRepr dom) - domainOf (InComprehension (GenInExpr Single{} x)) = domainOf x >>= innerDomainOf - domainOf x@InComprehension{} = fail $ vcat [ "domainOf-ReferenceTo-InComprehension", pretty x, pretty (show x) ] - domainOf (DeclNoRepr _ _ dom _) = return dom - domainOf (DeclHasRepr _ _ dom ) = return (forgetRepr dom) - domainOf RecordField{} = fail "domainOf-ReferenceTo-RecordField" - domainOf VariantField{} = fail "domainOf-ReferenceTo-VariantField" - - -instance DomainOf Expression where - domainOf (Reference _ (Just refTo)) = domainOf refTo - domainOf (Constant x) = domainOf x - domainOf (AbstractLiteral x) = domainOf x - domainOf (Op x) = domainOf x - domainOf (WithLocals h _) = domainOf h - domainOf x = fail ("domainOf{Expression}:" <+> pretty (show x)) - - -- if an empty matrix literal has a type annotation - indexDomainsOf (Typed lit ty) | emptyCollectionX lit = - let -<<<<<<< HEAD - tyToDom (TypeMatrix (TypeInt name) t) = DomainInt name [RangeBounded 1 0] : tyToDom t -||||||| merged common ancestors - tyToDom (TypeMatrix TypeInt t) = DomainInt [RangeBounded 1 0] : tyToDom t -======= - tyToDom (TypeMatrix (TypeInt nm) t) = DomainInt nm [RangeBounded 1 0] : tyToDom t ->>>>>>> taggedints - tyToDom _ = [] - in - return (tyToDom ty) - - indexDomainsOf (Reference _ (Just refTo)) = indexDomainsOf refTo - indexDomainsOf (Constant x) = indexDomainsOf x - indexDomainsOf (AbstractLiteral x) = indexDomainsOf x - indexDomainsOf (Op x) = indexDomainsOf x - indexDomainsOf (WithLocals h _) = indexDomainsOf h - indexDomainsOf x = fail ("indexDomainsOf{Expression}:" <+> pretty (show x)) - --- this should be better implemented by some ghc-generics magic -instance (DomainOf x, TypeOf x, Pretty x, ExpressionLike x, Domain () x :< x, Dom :< x) => DomainOf (Op x) where - domainOf (MkOpActive x) = domainOf x - domainOf (MkOpAllDiff x) = domainOf x - domainOf (MkOpAllDiffExcept x) = domainOf x - domainOf (MkOpAnd x) = domainOf x - domainOf (MkOpApart x) = domainOf x - domainOf (MkOpApply x) = domainOf x - domainOf (MkOpAttributeAsConstraint x) = domainOf x - domainOf (MkOpCatchUndef x) = domainOf x - domainOf (MkOpDefined x) = domainOf x - domainOf (MkOpDiv x) = domainOf x - domainOf (MkOpDontCare x) = domainOf x - domainOf (MkOpDotLeq x) = domainOf x - domainOf (MkOpDotLt x) = domainOf x - domainOf (MkOpEq x) = domainOf x - domainOf (MkOpFactorial x) = domainOf x - domainOf (MkOpFlatten x) = domainOf x - domainOf (MkOpFreq x) = domainOf x - domainOf (MkOpGeq x) = domainOf x - domainOf (MkOpGt x) = domainOf x - domainOf (MkOpHist x) = domainOf x - domainOf (MkOpIff x) = domainOf x - domainOf (MkOpImage x) = domainOf x - domainOf (MkOpImageSet x) = domainOf x - domainOf (MkOpImply x) = domainOf x - domainOf (MkOpIn x) = domainOf x - domainOf (MkOpIndexing x) = domainOf x - domainOf (MkOpIntersect x) = domainOf x - domainOf (MkOpInverse x) = domainOf x - domainOf (MkOpLeq x) = domainOf x - domainOf (MkOpLexLeq x) = domainOf x - domainOf (MkOpLexLt x) = domainOf x - domainOf (MkOpLt x) = domainOf x - domainOf (MkOpMax x) = domainOf x - domainOf (MkOpMin x) = domainOf x - domainOf (MkOpMinus x) = domainOf x - domainOf (MkOpMod x) = domainOf x - domainOf (MkOpNegate x) = domainOf x - domainOf (MkOpNeq x) = domainOf x - domainOf (MkOpNot x) = domainOf x - domainOf (MkOpOr x) = domainOf x - domainOf (MkOpParticipants x) = domainOf x - domainOf (MkOpParts x) = domainOf x - domainOf (MkOpParty x) = domainOf x - domainOf (MkOpPermute x) = domainOf x - domainOf (MkOpPermutationTuples x) = domainOf x - domainOf (MkOpPow x) = domainOf x - domainOf (MkOpPowerSet x) = domainOf x - domainOf (MkOpPred x) = domainOf x - domainOf (MkOpPreImage x) = domainOf x - domainOf (MkOpProduct x) = domainOf x - domainOf (MkOpRange x) = domainOf x - domainOf (MkOpRelationProj x) = domainOf x - domainOf (MkOpRestrict x) = domainOf x - domainOf (MkOpSlicing x) = domainOf x - domainOf (MkOpSubsequence x) = domainOf x - domainOf (MkOpSubset x) = domainOf x - domainOf (MkOpSubsetEq x) = domainOf x - domainOf (MkOpSubstring x) = domainOf x - domainOf (MkOpSucc x) = domainOf x - domainOf (MkOpSum x) = domainOf x - domainOf (MkOpSumForced x) = domainOf x - domainOf (MkOpSupset x) = domainOf x - domainOf (MkOpSupsetEq x) = domainOf x - domainOf (MkOpTildeLeq x) = domainOf x - domainOf (MkOpTildeLt x) = domainOf x - domainOf (MkOpTogether x) = domainOf x - domainOf (MkOpToInt x) = domainOf x - domainOf (MkOpToMSet x) = domainOf x - domainOf (MkOpToRelation x) = domainOf x - domainOf (MkOpToSet x) = domainOf x - domainOf (MkOpTrue x) = domainOf x - domainOf (MkOpTwoBars x) = domainOf x - domainOf (MkOpUnion x) = domainOf x - domainOf (MkOpXor x) = domainOf x - - indexDomainsOf (MkOpActive x) = indexDomainsOf x - indexDomainsOf (MkOpAllDiff x) = indexDomainsOf x - indexDomainsOf (MkOpAllDiffExcept x) = indexDomainsOf x - indexDomainsOf (MkOpAnd x) = indexDomainsOf x - indexDomainsOf (MkOpApart x) = indexDomainsOf x - indexDomainsOf (MkOpApply x) = indexDomainsOf x - indexDomainsOf (MkOpAttributeAsConstraint x) = indexDomainsOf x - indexDomainsOf (MkOpCatchUndef x) = indexDomainsOf x - indexDomainsOf (MkOpDefined x) = indexDomainsOf x - indexDomainsOf (MkOpDiv x) = indexDomainsOf x - indexDomainsOf (MkOpDontCare x) = indexDomainsOf x - indexDomainsOf (MkOpDotLeq x) = indexDomainsOf x - indexDomainsOf (MkOpDotLt x) = indexDomainsOf x - indexDomainsOf (MkOpEq x) = indexDomainsOf x - indexDomainsOf (MkOpFactorial x) = indexDomainsOf x - indexDomainsOf (MkOpFlatten x) = indexDomainsOf x - indexDomainsOf (MkOpFreq x) = indexDomainsOf x - indexDomainsOf (MkOpGeq x) = indexDomainsOf x - indexDomainsOf (MkOpGt x) = indexDomainsOf x - indexDomainsOf (MkOpHist x) = indexDomainsOf x - indexDomainsOf (MkOpIff x) = indexDomainsOf x - indexDomainsOf (MkOpImage x) = indexDomainsOf x - indexDomainsOf (MkOpImageSet x) = indexDomainsOf x - indexDomainsOf (MkOpImply x) = indexDomainsOf x - indexDomainsOf (MkOpIn x) = indexDomainsOf x - indexDomainsOf (MkOpIndexing x) = indexDomainsOf x - indexDomainsOf (MkOpIntersect x) = indexDomainsOf x - indexDomainsOf (MkOpInverse x) = indexDomainsOf x - indexDomainsOf (MkOpLeq x) = indexDomainsOf x - indexDomainsOf (MkOpLexLeq x) = indexDomainsOf x - indexDomainsOf (MkOpLexLt x) = indexDomainsOf x - indexDomainsOf (MkOpLt x) = indexDomainsOf x - indexDomainsOf (MkOpMax x) = indexDomainsOf x - indexDomainsOf (MkOpMin x) = indexDomainsOf x - indexDomainsOf (MkOpMinus x) = indexDomainsOf x - indexDomainsOf (MkOpMod x) = indexDomainsOf x - indexDomainsOf (MkOpNegate x) = indexDomainsOf x - indexDomainsOf (MkOpNeq x) = indexDomainsOf x - indexDomainsOf (MkOpNot x) = indexDomainsOf x - indexDomainsOf (MkOpOr x) = indexDomainsOf x - indexDomainsOf (MkOpParticipants x) = indexDomainsOf x - indexDomainsOf (MkOpParts x) = indexDomainsOf x - indexDomainsOf (MkOpParty x) = indexDomainsOf x - indexDomainsOf (MkOpPermute x) = indexDomainsOf x - indexDomainsOf (MkOpPermutationTuples x) = indexDomainsOf x - indexDomainsOf (MkOpPow x) = indexDomainsOf x - indexDomainsOf (MkOpPowerSet x) = indexDomainsOf x - indexDomainsOf (MkOpPred x) = indexDomainsOf x - indexDomainsOf (MkOpPreImage x) = indexDomainsOf x - indexDomainsOf (MkOpProduct x) = indexDomainsOf x - indexDomainsOf (MkOpRange x) = indexDomainsOf x - indexDomainsOf (MkOpRelationProj x) = indexDomainsOf x - indexDomainsOf (MkOpRestrict x) = indexDomainsOf x - indexDomainsOf (MkOpSlicing x) = indexDomainsOf x - indexDomainsOf (MkOpSubsequence x) = indexDomainsOf x - indexDomainsOf (MkOpSubset x) = indexDomainsOf x - indexDomainsOf (MkOpSubsetEq x) = indexDomainsOf x - indexDomainsOf (MkOpSubstring x) = indexDomainsOf x - indexDomainsOf (MkOpSucc x) = indexDomainsOf x - indexDomainsOf (MkOpSum x) = indexDomainsOf x - indexDomainsOf (MkOpSumForced x) = indexDomainsOf x - indexDomainsOf (MkOpSupset x) = indexDomainsOf x - indexDomainsOf (MkOpSupsetEq x) = indexDomainsOf x - indexDomainsOf (MkOpTildeLeq x) = indexDomainsOf x - indexDomainsOf (MkOpTildeLt x) = indexDomainsOf x - indexDomainsOf (MkOpTogether x) = indexDomainsOf x - indexDomainsOf (MkOpToInt x) = indexDomainsOf x - indexDomainsOf (MkOpToMSet x) = indexDomainsOf x - indexDomainsOf (MkOpToRelation x) = indexDomainsOf x - indexDomainsOf (MkOpToSet x) = indexDomainsOf x - indexDomainsOf (MkOpTrue x) = indexDomainsOf x - indexDomainsOf (MkOpTwoBars x) = indexDomainsOf x - indexDomainsOf (MkOpUnion x) = indexDomainsOf x - indexDomainsOf (MkOpXor x) = indexDomainsOf x - -instance DomainOf Constant where - domainOf ConstantBool{} = return DomainBool -<<<<<<< HEAD - domainOf i@ConstantInt{} = return $ DomainInt Nothing [RangeSingle (Constant i)] -||||||| merged common ancestors - domainOf i@ConstantInt{} = return $ DomainInt [RangeSingle (Constant i)] -======= - domainOf i@(ConstantInt t _) = return $ DomainInt t [RangeSingle (Constant i)] ->>>>>>> taggedints - domainOf (ConstantEnum defn _ _ ) = return (DomainEnum defn Nothing Nothing) - domainOf ConstantField{} = fail "DomainOf-Constant-ConstantField" - domainOf (ConstantAbstract x) = domainOf (fmap Constant x) - domainOf (DomainInConstant dom) = return (fmap Constant dom) - domainOf (TypedConstant x ty) = domainOf (Typed (Constant x) ty) - domainOf ConstantUndefined{} = fail "DomainOf-Constant-ConstantUndefined" - - indexDomainsOf ConstantBool{} = return [] - indexDomainsOf ConstantInt{} = return [] - indexDomainsOf ConstantEnum{} = return [] - indexDomainsOf ConstantField{} = return [] - indexDomainsOf (ConstantAbstract x) = indexDomainsOf (fmap Constant x) - indexDomainsOf DomainInConstant{} = return [] - indexDomainsOf (TypedConstant x ty) = indexDomainsOf (Typed (Constant x) ty) - indexDomainsOf ConstantUndefined{} = return [] - -instance DomainOf (AbstractLiteral Expression) where - - domainOf (AbsLitTuple xs) = DomainTuple <$> mapM domainOf xs - - domainOf (AbsLitRecord xs) = DomainRecord <$> sequence [ do t <- domainOf x ; return (n,t) - | (n,x) <- xs ] - - domainOf (AbsLitVariant Nothing _ _) = fail "Cannot calculate the domain of variant literal." - domainOf (AbsLitVariant (Just t) _ _) = return (DomainVariant t) - - domainOf (AbsLitMatrix ind inn ) = DomainMatrix ind <$> (domainUnions =<< mapM domainOf inn) - - domainOf (AbsLitSet [] ) = return $ DomainSet def attr (DomainAny "domainOf-AbsLitSet-[]" TypeAny) - where attr = SetAttr (SizeAttr_Size 0) - domainOf (AbsLitSet xs ) = DomainSet def attr <$> (domainUnions =<< mapM domainOf xs) - where attr = SetAttr (SizeAttr_MaxSize $ fromInt $ genericLength xs) - - domainOf (AbsLitMSet [] ) = return $ DomainMSet def attr (DomainAny "domainOf-AbsLitMSet-[]" TypeAny) - where attr = MSetAttr (SizeAttr_Size 0) OccurAttr_None - domainOf (AbsLitMSet xs ) = DomainMSet def attr <$> (domainUnions =<< mapM domainOf xs) - where attr = MSetAttr (SizeAttr_MaxSize $ fromInt $ genericLength xs) OccurAttr_None - - domainOf (AbsLitFunction [] ) = return $ DomainFunction def attr - (DomainAny "domainOf-AbsLitFunction-[]-1" TypeAny) - (DomainAny "domainOf-AbsLitFunction-[]-2" TypeAny) - where attr = FunctionAttr (SizeAttr_Size 0) def def - domainOf (AbsLitFunction xs ) = DomainFunction def attr - <$> (domainUnions =<< mapM (domainOf . fst) xs) - <*> (domainUnions =<< mapM (domainOf . snd) xs) - where attr = FunctionAttr (SizeAttr_MaxSize $ fromInt $ genericLength xs) def def - - domainOf (AbsLitSequence [] ) = return $ DomainSequence def attr - (DomainAny "domainOf-AbsLitSequence-[]" TypeAny) - where attr = SequenceAttr (SizeAttr_Size 0) def - domainOf (AbsLitSequence xs ) = DomainSequence def attr - <$> (domainUnions =<< mapM domainOf xs) - where attr = SequenceAttr (SizeAttr_MaxSize (fromInt $ genericLength xs)) def - - domainOf (AbsLitRelation [] ) = return $ DomainRelation def attr [] - where attr = RelationAttr (SizeAttr_Size 0) def - domainOf (AbsLitRelation xss) = do - ty <- domainUnions =<< mapM (domainOf . AbsLitTuple) xss - case ty of - DomainTuple ts -> return (DomainRelation def attr ts) - _ -> bug "expecting DomainTuple in domainOf" - where attr = RelationAttr (SizeAttr_MaxSize (fromInt $ genericLength xss)) def - - domainOf (AbsLitPartition [] ) = return $ DomainPartition def attr - (DomainAny "domainOf-AbsLitPartition-[]" TypeAny) - where attr = PartitionAttr (SizeAttr_Size 0) (SizeAttr_Size 0) False - domainOf (AbsLitPartition xss) = DomainPartition def attr <$> (domainUnions =<< mapM domainOf (concat xss)) - where attr = PartitionAttr (SizeAttr_MaxSize (fromInt $ genericLength xss)) - (SizeAttr_MaxSize (fromInt $ maximum [genericLength xs | xs <- xss])) - False - domainOf (AbsLitPermutation xss) = DomainPermutation def def <$> (domainUnions =<< mapM domainOf (concat xss)) - indexDomainsOf (AbsLitMatrix ind inn) = (ind :) <$> (mapM domainUnions =<< mapM indexDomainsOf inn) - indexDomainsOf _ = return [] - - - - --- all the `Op`s - -instance DomainOf (OpActive x) where - domainOf _ = return DomainBool - -instance DomainOf (OpAllDiff x) where - domainOf _ = return DomainBool - -instance DomainOf (OpAllDiffExcept x) where - domainOf _ = return DomainBool - -instance DomainOf x => DomainOf (OpCatchUndef x) where - domainOf (OpCatchUndef x _) = domainOf x - -instance DomainOf (OpAnd x) where - domainOf _ = return DomainBool - -instance DomainOf (OpApart x) where - domainOf _ = return DomainBool - -instance DomainOf (OpAttributeAsConstraint x) where - domainOf _ = return DomainBool - -instance DomainOf x => DomainOf (OpDefined x) where - domainOf (OpDefined f) = do - fDom <- domainOf f - case fDom of - DomainFunction _ _ fr _ -> return $ DomainSet def def fr - _ -> fail "domainOf, OpDefined, not a function" - -instance DomainOf x => DomainOf (OpDiv x) where - domainOf (OpDiv x y) = do - xDom :: Dom <- domainOf x - yDom :: Dom <- domainOf y - (iPat, i) <- quantifiedVar - (jPat, j) <- quantifiedVar - let vals = [essence| [ &i / &j - | &iPat : &xDom - , &jPat : &yDom - ] |] - let low = [essence| min(&vals) |] - let upp = [essence| max(&vals) |] -<<<<<<< HEAD - return (DomainInt Nothing [RangeBounded low upp] :: Dom) -||||||| merged common ancestors - return (DomainInt [RangeBounded low upp] :: Dom) -======= - return (DomainInt NoTag [RangeBounded low upp] :: Dom) ->>>>>>> taggedints - -instance DomainOf (OpDontCare x) where - domainOf _ = return DomainBool - -instance DomainOf (OpDotLeq x) where - domainOf _ = return DomainBool - -instance DomainOf (OpDotLt x) where - domainOf _ = return DomainBool - -instance DomainOf (OpEq x) where - domainOf _ = return DomainBool - -instance (Pretty x, TypeOf x) => DomainOf (OpFactorial x) where - domainOf op = mkDomainAny ("OpFactorial:" <++> pretty op) <$> typeOf op - -instance (Pretty x, TypeOf x) => DomainOf (OpFlatten x) where - domainOf op = mkDomainAny ("OpFlatten:" <++> pretty op) <$> typeOf op - -instance (Pretty x, TypeOf x) => DomainOf (OpFreq x) where - domainOf op = mkDomainAny ("OpFreq:" <++> pretty op) <$> typeOf op - -instance DomainOf (OpGeq x) where - domainOf _ = return DomainBool - -instance DomainOf (OpGt x) where - domainOf _ = return DomainBool - -instance (Pretty x, TypeOf x) => DomainOf (OpHist x) where - domainOf op = mkDomainAny ("OpHist:" <++> pretty op) <$> typeOf op - -instance DomainOf (OpIff x) where - domainOf _ = return DomainBool - -instance (Pretty x, TypeOf x) => DomainOf (OpImage x) where - domainOf op = mkDomainAny ("OpImage:" <++> pretty op) <$> typeOf op - -instance (Pretty x, TypeOf x) => DomainOf (OpImageSet x) where - domainOf op = mkDomainAny ("OpImageSet:" <++> pretty op) <$> typeOf op - -instance DomainOf (OpImply x) where - domainOf _ = return DomainBool - -instance DomainOf (OpIn x) where - domainOf _ = return DomainBool - -instance (Pretty x, TypeOf x, ExpressionLike x, DomainOf x) => DomainOf (OpIndexing x) where - domainOf (OpIndexing m i) = do - iType <- typeOf i - case iType of - TypeBool{} -> return () - TypeInt{} -> return () - _ -> fail "domainOf, OpIndexing, not a bool or int index" - mDom <- domainOf m - case mDom of - DomainMatrix _ inner -> return inner - DomainTuple inners -> do - iInt <- intOut "domainOf OpIndexing" i - return $ atNote "domainOf" inners (fromInteger (iInt-1)) - _ -> fail "domainOf, OpIndexing, not a matrix or tuple" - - indexDomainsOf p@(OpIndexing m i) = do - iType <- typeOf i - case iType of - TypeBool{} -> return () - TypeInt{} -> return () - _ -> fail "domainOf, OpIndexing, not a bool or int index" - is <- indexDomainsOf m - case is of - [] -> fail ("indexDomainsOf{OpIndexing}, not a matrix domain:" <++> pretty p) - (_:is') -> return is' - -instance (Pretty x, TypeOf x) => DomainOf (OpIntersect x) where - domainOf op = mkDomainAny ("OpIntersect:" <++> pretty op) <$> typeOf op - -instance DomainOf (OpInverse x) where - domainOf _ = return DomainBool - -instance DomainOf (OpLeq x) where - domainOf _ = return DomainBool - -instance DomainOf (OpLexLeq x) where - domainOf _ = return DomainBool - -instance DomainOf (OpLexLt x) where - domainOf _ = return DomainBool - -instance DomainOf (OpLt x) where - domainOf _ = return DomainBool - -instance (Pretty x, TypeOf x, ExpressionLike x, DomainOf x, Domain () x :< x) => DomainOf (OpMax x) where - domainOf (OpMax x) - | Just xs <- listOut x - , not (null xs) = do - doms <- mapM domainOf xs - let lows = fromList [ [essence| min(`&d`) |] | d <- doms ] - let low = [essence| max(&lows) |] - let upps = fromList [ [essence| max(`&d`) |] | d <- doms ] - let upp = [essence| max(&upps) |] -<<<<<<< HEAD - return (DomainInt Nothing [RangeBounded low upp] :: Dom) -||||||| merged common ancestors - return (DomainInt [RangeBounded low upp] :: Dom) -======= - TypeInt t <- typeOf (head doms) - return (DomainInt t [RangeBounded low upp] :: Dom) ->>>>>>> taggedints - domainOf op = mkDomainAny ("OpMax:" <++> pretty op) <$> typeOf op - -instance (Pretty x, TypeOf x, ExpressionLike x, DomainOf x, Domain () x :< x) => DomainOf (OpMin x) where - domainOf (OpMin x) - | Just xs <- listOut x - , not (null xs) = do - doms <- mapM domainOf xs - let lows = fromList [ [essence| min(`&d`) |] | d <- doms ] - let low = [essence| min(&lows) |] - let upps = fromList [ [essence| max(`&d`) |] | d <- doms ] - let upp = [essence| min(&upps) |] -<<<<<<< HEAD - return (DomainInt Nothing [RangeBounded low upp] :: Dom) -||||||| merged common ancestors - return (DomainInt [RangeBounded low upp] :: Dom) -======= - TypeInt t <- typeOf (head doms) - return (DomainInt t [RangeBounded low upp] :: Dom) ->>>>>>> taggedints - domainOf op = mkDomainAny ("OpMin:" <++> pretty op) <$> typeOf op - -instance DomainOf x => DomainOf (OpMinus x) where - domainOf (OpMinus x y) = do - xDom :: Dom <- domainOf x - yDom :: Dom <- domainOf y - - xDom_Min <- minOfDomain xDom - xDom_Max <- maxOfDomain xDom - yDom_Min <- minOfDomain yDom - yDom_Max <- maxOfDomain yDom - - let low = [essence| &xDom_Min - &yDom_Max |] - let upp = [essence| &xDom_Max - &yDom_Min |] - -<<<<<<< HEAD - return (DomainInt Nothing [RangeBounded low upp] :: Dom) -||||||| merged common ancestors - return (DomainInt [RangeBounded low upp] :: Dom) -======= - return (DomainInt NoTag [RangeBounded low upp] :: Dom) ->>>>>>> taggedints - -instance (Pretty x, TypeOf x) => DomainOf (OpMod x) where - domainOf op = mkDomainAny ("OpMod:" <++> pretty op) <$> typeOf op - -instance (Pretty x, TypeOf x) => DomainOf (OpNegate x) where - domainOf op = mkDomainAny ("OpNegate:" <++> pretty op) <$> typeOf op - -instance DomainOf (OpNeq x) where - domainOf _ = return DomainBool - -instance DomainOf (OpNot x) where - domainOf _ = return DomainBool - -instance DomainOf (OpOr x) where - domainOf _ = return DomainBool - -instance DomainOf (OpXor x) where - domainOf _ = return DomainBool - -instance (Pretty x, TypeOf x) => DomainOf (OpParticipants x) where - domainOf op = mkDomainAny ("OpParticipants:" <++> pretty op) <$> typeOf op - -instance DomainOf x => DomainOf (OpParts x) where - domainOf (OpParts p) = do - dom <- domainOf p - case dom of - DomainPartition _ _ inner -> return $ DomainSet def def $ DomainSet def def inner - _ -> fail "domainOf, OpParts, not a partition" - -instance (Pretty x, TypeOf x) => DomainOf (OpParty x) where - domainOf op = mkDomainAny ("OpParty:" <++> pretty op) <$> typeOf op - -instance (Pretty x, TypeOf x) => DomainOf (OpPermute x) where - domainOf op = mkDomainAny ("OpPermute:" <++> pretty op) <$> typeOf op - -instance (Pretty x, TypeOf x) => DomainOf (OpPermutationTuples x) where - domainOf op = mkDomainAny ("OpPermutationTuples:" <++> pretty op) <$> typeOf op - - - -instance (Pretty x, TypeOf x) => DomainOf (OpApply x) where - domainOf op = mkDomainAny ("OpApply:" <++> pretty op) <$> typeOf op - -instance (Pretty x, TypeOf x) => DomainOf (OpPow x) where - domainOf op = mkDomainAny ("OpPow:" <++> pretty op) <$> typeOf op - -instance (Pretty x, TypeOf x) => DomainOf (OpPowerSet x) where - domainOf op = mkDomainAny ("OpPowerSet:" <++> pretty op) <$> typeOf op - -instance (Pretty x, TypeOf x) => DomainOf (OpPreImage x) where - domainOf op = mkDomainAny ("OpPreImage:" <++> pretty op) <$> typeOf op - -instance DomainOf x => DomainOf (OpPred x) where - domainOf (OpPred x) = domainOf x -- TODO: improve - -instance (ExpressionLike x, DomainOf x) => DomainOf (OpProduct x) where - domainOf (OpProduct x) - | Just xs <- listOut x - , not (null xs) = do - (iPat, i) <- quantifiedVar - doms <- mapM domainOf xs - -- maximum absolute value in each domain - let upps = fromList [ [essence| max([ |&i| | &iPat : &d ]) |] - | d <- doms ] - -- a (too lax) upper bound is multiplying all those together - let upp = [essence| product(&upps) |] - -- a (too lax) lower bound is -upp - let low = [essence| -1 * &upp |] -<<<<<<< HEAD - return $ DomainInt Nothing [RangeBounded low upp] - domainOf _ = return $ DomainInt Nothing [RangeBounded 1 1] -||||||| merged common ancestors - return $ DomainInt [RangeBounded low upp] - domainOf _ = return $ DomainInt [RangeBounded 1 1] -======= - return $ DomainInt NoTag [RangeBounded low upp] - domainOf _ = return $ DomainInt NoTag [RangeBounded 1 1] ->>>>>>> taggedints - -instance DomainOf x => DomainOf (OpRange x) where - domainOf (OpRange f) = do - fDom <- domainOf f - case fDom of - DomainFunction _ _ _ to -> return $ DomainSet def def to - _ -> fail "domainOf, OpRange, not a function" - -instance (Pretty x, TypeOf x) => DomainOf (OpRelationProj x) where - domainOf op = mkDomainAny ("OpRelationProj:" <++> pretty op) <$> typeOf op - -instance (DomainOf x, Dom :< x) => DomainOf (OpRestrict x) where - domainOf (OpRestrict f x) = do - d <- project x - fDom <- domainOf f - case fDom of - DomainFunction fRepr a _ to -> return (DomainFunction fRepr a d to) - _ -> fail "domainOf, OpRestrict, not a function" - -instance (Pretty x, DomainOf x) => DomainOf (OpSlicing x) where - domainOf (OpSlicing x _ _) = domainOf x - indexDomainsOf (OpSlicing x _ _) = indexDomainsOf x - -instance DomainOf (OpSubsequence x) where - domainOf _ = fail "domainOf{OpSubsequence}" - -instance (Pretty x, TypeOf x) => DomainOf (OpSubset x) where - domainOf op = mkDomainAny ("OpSubset:" <++> pretty op) <$> typeOf op - -instance (Pretty x, TypeOf x) => DomainOf (OpSubsetEq x) where - domainOf op = mkDomainAny ("OpSubsetEq:" <++> pretty op) <$> typeOf op - -instance DomainOf (OpSubstring x) where - domainOf _ = fail "domainOf{OpSubstring}" - -instance DomainOf x => DomainOf (OpSucc x) where - domainOf (OpSucc x) = domainOf x -- TODO: improve - -instance (ExpressionLike x, DomainOf x) => DomainOf (OpSum x) where - domainOf (OpSum x) - | Just xs <- listOut x - , not (null xs) = do - doms <- mapM domainOf xs - let lows = fromList [ [essence| min(`&d`) |] | d <- doms ] - let low = [essence| sum(&lows) |] - let upps = fromList [ [essence| max(`&d`) |] | d <- doms ] - let upp = [essence| sum(&upps) |] -<<<<<<< HEAD - return (DomainInt Nothing [RangeBounded low upp] :: Dom) - domainOf _ = return $ DomainInt Nothing [RangeBounded 0 0] -||||||| merged common ancestors - return (DomainInt [RangeBounded low upp] :: Dom) - domainOf _ = return $ DomainInt [RangeBounded 0 0] -======= - return (DomainInt NoTag [RangeBounded low upp] :: Dom) - domainOf _ = return $ DomainInt NoTag [RangeBounded 0 0] - - -instance (ExpressionLike x, DomainOf x, TypeOf x) => DomainOf (OpSumForced x) where - domainOf (OpSumForced x) - | Just xs <- listOut x - , Just tag <- containsTag =<< typeOf x - , not (null xs) = do - doms <- mapM domainOf xs - let lows = fromList [ [essence| min(`&d`) |] | d <- doms ] - let low = [essence| sum(&lows) |] - let upps = fromList [ [essence| max(`&d`) |] | d <- doms ] - let upp = [essence| sum(&upps) |] - return (DomainInt tag [RangeBounded low upp] :: Dom) - domainOf (OpSumForced x) - | Just tag <- containsTag =<< typeOf x - = return (DomainInt tag (addTag tag [RangeBounded 0 0])) - domainOf _ = bug "domainOf: OpSumForced: expected an integer tag to be present" ->>>>>>> taggedints - -instance DomainOf (OpSupset x) where - domainOf _ = return DomainBool - -instance DomainOf (OpSupsetEq x) where - domainOf _ = return DomainBool - -instance DomainOf (OpTildeLeq x) where - domainOf _ = return DomainBool - -instance DomainOf (OpTildeLt x) where - domainOf _ = return DomainBool - -instance DomainOf (OpToInt x) where -<<<<<<< HEAD - domainOf _ = return $ DomainInt Nothing [RangeBounded 0 1] -||||||| merged common ancestors - domainOf _ = return $ DomainInt [RangeBounded 0 1] -======= - domainOf _ = return $ DomainInt NoTag [RangeBounded 0 1] ->>>>>>> taggedints - -instance (Pretty x, TypeOf x) => DomainOf (OpToMSet x) where - domainOf op = mkDomainAny ("OpToMSet:" <++> pretty op) <$> typeOf op - -instance (Pretty x, TypeOf x) => DomainOf (OpToRelation x) where - domainOf op = mkDomainAny ("OpToRelation:" <++> pretty op) <$> typeOf op - -instance (Pretty x, TypeOf x) => DomainOf (OpToSet x) where - domainOf op = mkDomainAny ("OpToSet:" <++> pretty op) <$> typeOf op - -instance DomainOf (OpTogether x) where - domainOf _ = return DomainBool - -instance DomainOf (OpTrue x) where - domainOf _ = return DomainBool - -instance (Pretty x, TypeOf x) => DomainOf (OpTwoBars x) where - domainOf op = mkDomainAny ("OpTwoBars:" <++> pretty op) <$> typeOf op - -instance (Pretty x, TypeOf x) => DomainOf (OpUnion x) where - domainOf op = mkDomainAny ("OpUnion:" <++> pretty op) <$> typeOf op - diff --git a/src/Conjure/Compute/DomainUnion.hs.orig b/src/Conjure/Compute/DomainUnion.hs.orig deleted file mode 100644 index 5242bdac0d..0000000000 --- a/src/Conjure/Compute/DomainUnion.hs.orig +++ /dev/null @@ -1,188 +0,0 @@ -{-# LANGUAGE TupleSections #-} -{-# LANGUAGE NoMonomorphismRestriction #-} -{-# LANGUAGE UndecidableInstances #-} - -module Conjure.Compute.DomainUnion - ( domainUnion, domainUnions - ) where - --- conjure -import Conjure.Prelude -import Conjure.Bug -import Conjure.Language.Domain -import Conjure.Language.Type -import Conjure.Language.Expression.Op -import Conjure.Language.AdHoc -import Conjure.Language.Pretty -import Conjure.Language.Lenses - -import Data.List as L ( union ) - --- containers -import Data.Set as S ( union ) - -class DomainUnion a where - domainUnion :: (Applicative m, Monad m) => a -> a -> m a - -domainUnions - :: ( Applicative m, Monad m - , Pretty r, Default r - , Eq x, Pretty x, ExpressionLike x, Op x :< x - ) => [Domain r x] -> m (Domain r x) -domainUnions [] = return $ DomainAny "domainUnions []" TypeAny -domainUnions [a] = return a -domainUnions (a:as) = do b <- domainUnions as ; domainUnion a b - -instance - ( Eq x - , ExpressionLike x - , Op x :< x - , Pretty x - , Pretty r - , Default r - ) => DomainUnion (Domain r x) where - domainUnion DomainAny{} d = return d - domainUnion d DomainAny{} = return d - domainUnion DomainBool DomainBool = return DomainBool -<<<<<<< HEAD - domainUnion (DomainInt Nothing r1) (DomainInt Nothing r2) = - return $ DomainInt Nothing (r1 `L.union` r2) -||||||| merged common ancestors - domainUnion (DomainInt r1) (DomainInt r2) = return $ DomainInt (r1 `L.union` r2) -======= - domainUnion (DomainInt t1 r1) (DomainInt t2 r2) | t1 == t2 - = return $ DomainInt t1 (r1 `L.union` r2) ->>>>>>> taggedints - domainUnion (DomainTuple []) d@DomainTuple{} = return d - domainUnion d@DomainTuple{} (DomainTuple []) = return d - domainUnion (DomainTuple xs) (DomainTuple ys) - | length xs == length ys - = DomainTuple <$> zipWithM domainUnion xs ys - domainUnion (DomainMatrix x1 x2) (DomainMatrix y1 y2) - = DomainMatrix <$> domainUnion x1 y1 <*> domainUnion x2 y2 - domainUnion (DomainSet _ xA x) (DomainSet _ yA y) - = DomainSet def <$> domainUnion xA yA <*> domainUnion x y - domainUnion (DomainMSet _ xA x) (DomainMSet _ yA y) - = DomainMSet def <$> domainUnion xA yA <*> domainUnion x y - domainUnion (DomainFunction _ xA x1 x2) (DomainFunction _ yA y1 y2) - = DomainFunction def <$> domainUnion xA yA <*> domainUnion x1 y1 <*> domainUnion x2 y2 - domainUnion (DomainSequence _ xA x) (DomainSequence _ yA y) - = DomainSequence def <$> domainUnion xA yA <*> domainUnion x y - domainUnion (DomainRelation _ _ []) d@DomainRelation{} = return d - domainUnion d@DomainRelation{} (DomainRelation _ _ []) = return d - domainUnion (DomainRelation _ xA xs) (DomainRelation _ yA ys) - | length xs == length ys - = DomainRelation def <$> domainUnion xA yA <*> zipWithM domainUnion xs ys - domainUnion (DomainPartition _ xA x) (DomainPartition _ yA y) - = DomainPartition def <$> domainUnion xA yA <*> domainUnion x y - domainUnion d1 d2 = bug $ vcat ["Domain.domainUnion", pretty d1, pretty d2] - - -instance - ( ExpressionLike x - , Op x :< x - , Pretty x - ) => DomainUnion (SetAttr x) where - domainUnion (SetAttr a) (SetAttr b) = SetAttr <$> domainUnion a b - - -instance - ( ExpressionLike x - , Op x :< x - , Pretty x - ) => DomainUnion (SizeAttr x) where - domainUnion SizeAttr_None s = return s - domainUnion s SizeAttr_None = return s - domainUnion a b = return $ SizeAttr_MinMaxSize - (make opMin (fromList [minA, minB])) - (make opMax (fromList [maxA, maxB])) - where - (minA, maxA) = getMinMax a - (minB, maxB) = getMinMax b - getMinMax p = case p of - SizeAttr_None -> bug "Monoid SizeAttr" - SizeAttr_Size x -> (x,x) - SizeAttr_MinSize x -> (x,x) - SizeAttr_MaxSize x -> (x,x) - SizeAttr_MinMaxSize x y -> (x,y) - - -instance - ( ExpressionLike x - , Op x :< x - , Pretty x - ) => DomainUnion (MSetAttr x) where - domainUnion (MSetAttr a1 a2) (MSetAttr b1 b2) = MSetAttr <$> domainUnion a1 b1 <*> domainUnion a2 b2 - - -instance - ( ExpressionLike x - , Op x :< x - , Pretty x - ) => DomainUnion (OccurAttr x) where - domainUnion OccurAttr_None s = return s - domainUnion s OccurAttr_None = return s - domainUnion a b = return $ OccurAttr_MinMaxOccur - (make opMin (fromList [minA, minB])) - (make opMax (fromList [maxA, maxB])) - where - (minA, maxA) = getMinMax a - (minB, maxB) = getMinMax b - getMinMax p = case p of - OccurAttr_None -> bug "Monoid OccurAttr" - OccurAttr_MinOccur x -> (x,x) - OccurAttr_MaxOccur x -> (x,x) - OccurAttr_MinMaxOccur x y -> (x,y) - - -instance - ( ExpressionLike x - , Op x :< x - , Pretty x - ) => DomainUnion (FunctionAttr x) where - domainUnion (FunctionAttr a1 a2 a3) (FunctionAttr b1 b2 b3) = - FunctionAttr <$> domainUnion a1 b1 <*> domainUnion a2 b2 <*> domainUnion a3 b3 - - -instance DomainUnion PartialityAttr where - domainUnion PartialityAttr_Partial _ = return PartialityAttr_Partial - domainUnion _ PartialityAttr_Partial = return PartialityAttr_Partial - domainUnion PartialityAttr_Total PartialityAttr_Total = return PartialityAttr_Total - - -instance DomainUnion JectivityAttr where - domainUnion x y | x == y = return x - domainUnion _ _ = bug "domainUnion JectivityAttr_Injective" - - -instance - ( ExpressionLike x - , Op x :< x - , Pretty x - ) => DomainUnion (SequenceAttr x) where - domainUnion (SequenceAttr a1 a2) (SequenceAttr b1 b2) = - SequenceAttr <$> domainUnion a1 b1 <*> domainUnion a2 b2 - - -instance - ( ExpressionLike x - , Op x :< x - , Pretty x - ) => DomainUnion (RelationAttr x) where - domainUnion (RelationAttr a1 a2) (RelationAttr b1 b2) = - RelationAttr <$> domainUnion a1 b1 <*> domainUnion a2 b2 - - -instance DomainUnion BinaryRelationAttrs where - domainUnion (BinaryRelationAttrs a) (BinaryRelationAttrs b) = - return $ BinaryRelationAttrs (S.union a b) - - -instance - ( ExpressionLike x - , Op x :< x - , Pretty x - ) => DomainUnion (PartitionAttr x) where - domainUnion (PartitionAttr a1 a2 a3) (PartitionAttr b1 b2 b3) = - PartitionAttr <$> domainUnion a1 b1 <*> domainUnion a2 b2 <*> pure (a3 || b3) - diff --git a/src/Conjure/Language/Arbitrary.hs.orig b/src/Conjure/Language/Arbitrary.hs.orig deleted file mode 100644 index 18447d9244..0000000000 --- a/src/Conjure/Language/Arbitrary.hs.orig +++ /dev/null @@ -1,345 +0,0 @@ -{-# LANGUAGE OverloadedStrings #-} -{-# LANGUAGE TupleSections #-} - -module Conjure.Language.Arbitrary - ( AnyDomainTuple(..) - , AnyConstantTuple(..) - , AnyDomainAndConstant(..) - , arbitraryDomainAndConstant - , sampleArbitraryDomainAndConstant - ) where - --- conjure -import Conjure.Prelude -import Conjure.Bug -import Conjure.Language.Definition -import Conjure.Language.Type -import Conjure.Language.Domain -import Conjure.Language.Pretty -import Conjure.Language.DomainSizeOf ( domainSizeOf ) - --- QuickCheck -import Test.QuickCheck ( Arbitrary(..), Gen, sized, choose, oneof, vectorOf, sample' ) - - -newtype AnyDomainTuple a = AnyDomainTuple (Domain () a) - deriving (Show) - -instance Arbitrary a => Arbitrary (AnyDomainTuple a) where - arbitrary = do - arity <- choose (2 :: Int, 10) - xs <- vectorOf arity arbitrary - return $ AnyDomainTuple $ DomainTuple xs - shrink (AnyDomainTuple d) = - case d of - DomainTuple xs -> - [ AnyDomainTuple (DomainTuple ys) - | ys <- subsequences xs - , not (null ys) - , length ys < length xs - ] - _ -> [] - - -newtype AnyConstantTuple = AnyConstantTuple Constant - deriving (Show) - -instance Arbitrary AnyConstantTuple where - arbitrary = do - arity <- choose (2 :: Int, 10) - xs <- vectorOf arity arbitrary - return $ AnyConstantTuple $ ConstantAbstract $ AbsLitTuple xs - shrink (AnyConstantTuple c) = - case c of - ConstantAbstract (AbsLitTuple xs) -> - [ AnyConstantTuple $ ConstantAbstract $ AbsLitTuple ys - | ys <- subsequences xs - , not (null ys) - , length ys < length xs - ] - _ -> [] - - --- | Some of these arbitrary generators are a bit crap. --- They recursively call themselves if some property doesn't hold in the generated value. --- This is the number of maximum retries. -maxRetries :: Int -maxRetries = 1000000 - -data AnyDomainAndConstant = AnyDomainAndConstant (Domain HasRepresentation Constant) Constant - -instance Show AnyDomainAndConstant where - show (AnyDomainAndConstant domain constant) = show $ vcat - [ "AnyDomainAndConstant" - , " domain :" <+> pretty domain - , " constant :" <+> pretty constant - ] -instance Arbitrary AnyDomainAndConstant where - arbitrary = do - (domain, constantGen) <- arbitraryDomainAndConstant - constant <- constantGen - return (AnyDomainAndConstant domain constant) - --- | This is a great function! --- It generates a random domain, and a generator of random constants of that domain. --- Follow the function calls starting from dispatch to see how it's implemented. It is pretty straightforward really. --- Note: The nesting level is controlled via the `sized` combinator from QuickCheck. -arbitraryDomainAndConstant :: Gen (Domain HasRepresentation Constant, Gen Constant) -arbitraryDomainAndConstant = sized dispatch - - where - - -- this is how size gets reduced in recursive calls - smaller :: Int -> Int - smaller depth = max 0 (div depth 10) - - dispatch :: Int -> Gen (Domain HasRepresentation Constant, Gen Constant) - dispatch 0 = oneof [bool, int] - dispatch d = oneof [bool, int, tuple d, matrix d, set d] - - bool :: Gen (Domain HasRepresentation Constant, Gen Constant) - bool = return (DomainBool, ConstantBool <$> arbitrary) - - int :: Gen (Domain r Constant, Gen Constant) - int = oneof [intBounded, intSingles, intMixed] - - intBounded :: Gen (Domain r Constant, Gen Constant) - intBounded = do - l <- choose (0 :: Integer, 100) - u <- choose (l, 200) -<<<<<<< HEAD - return ( DomainInt Nothing [RangeBounded (ConstantInt Nothing l) (ConstantInt Nothing u)] - , ConstantInt Nothing <$> choose (l,u) -||||||| merged common ancestors - return ( DomainInt [RangeBounded (ConstantInt l) (ConstantInt u)] - , ConstantInt <$> choose (l,u) -======= - return ( DomainInt NoTag [RangeBounded (ConstantInt NoTag l) (ConstantInt NoTag u)] - , ConstantInt NoTag <$> choose (l,u) ->>>>>>> taggedints - ) - - intSingles :: Gen (Domain r Constant, Gen Constant) - intSingles = do - count <- choose (1 :: Integer, 20) - vals <- vectorOf (fromInteger count) (choose (0 :: Integer, 100)) -<<<<<<< HEAD - return ( DomainInt Nothing (map (RangeSingle . ConstantInt Nothing) vals) - , ConstantInt Nothing <$> pickFromList vals -||||||| merged common ancestors - return ( DomainInt (map (RangeSingle . ConstantInt) vals) - , ConstantInt <$> pickFromList vals -======= - return ( DomainInt NoTag (map (RangeSingle . ConstantInt NoTag) vals) - , ConstantInt NoTag <$> pickFromList vals ->>>>>>> taggedints - ) - - intMixed :: Gen (Domain r Constant, Gen Constant) - intMixed = do -<<<<<<< HEAD - let single = RangeSingle . ConstantInt Nothing <$> choose (0 :: Integer, 100) -||||||| merged common ancestors - let single = RangeSingle . ConstantInt <$> choose (0 :: Integer, 100) -======= - let single = RangeSingle . ConstantInt NoTag <$> choose (0 :: Integer, 100) ->>>>>>> taggedints - let pair = do l <- choose (0 :: Integer, 100) - u <- choose (l, 200) -<<<<<<< HEAD - return $ RangeBounded (ConstantInt Nothing l) (ConstantInt Nothing u) -||||||| merged common ancestors - return $ RangeBounded (ConstantInt l) (ConstantInt u) -======= - return $ RangeBounded (ConstantInt NoTag l) (ConstantInt NoTag u) ->>>>>>> taggedints - - numSingles <- choose (1 :: Int, 10) - numPairs <- choose (1 :: Int, 10) - - let - -- first argument, number of `RangeSingle`s to generate - -- second argument, number of `RangeBounded`s to generate - genRanges 0 0 = return [] - genRanges 0 p = vectorOf p pair - genRanges s 0 = vectorOf s single - genRanges s p = do - which <- arbitrary - if which - then (:) <$> single <*> genRanges (s-1) p - else (:) <$> pair <*> genRanges s (p-1) - - rs <- genRanges numSingles numPairs - - let allVals = sortNub $ concat - [ vals - | r <- rs - , let vals = case r of -<<<<<<< HEAD - RangeSingle (ConstantInt Nothing i) -> [i] - RangeBounded (ConstantInt Nothing l) (ConstantInt Nothing u) -> [l..u] -||||||| merged common ancestors - RangeSingle (ConstantInt i) -> [i] - RangeBounded (ConstantInt l) (ConstantInt u) -> [l..u] -======= - RangeSingle (ConstantInt NoTag i) -> [i] - RangeBounded (ConstantInt NoTag l) (ConstantInt NoTag u) -> [l..u] ->>>>>>> taggedints - _ -> [] - ] - - if null allVals - then bug "allVals null" -<<<<<<< HEAD - else return ( DomainInt Nothing rs - , ConstantInt Nothing <$> pickFromList allVals -||||||| merged common ancestors - else return ( DomainInt rs - , ConstantInt <$> pickFromList allVals -======= - else return ( DomainInt NoTag rs - , ConstantInt NoTag <$> pickFromList allVals ->>>>>>> taggedints - ) - - -- enum :: Gen (Domain HasRepresentation Constant, Gen Constant) - -- enum = undefined - - tuple :: Int -> Gen (Domain HasRepresentation Constant, Gen Constant) - tuple depth = do - arity <- choose (2 :: Int, 4) - (ds, cs) <- unzip <$> vectorOf arity (dispatch (smaller depth)) - return ( DomainTuple ds - , ConstantAbstract . AbsLitTuple <$> sequence cs - ) - - matrix :: Int -> Gen (Domain HasRepresentation Constant, Gen Constant) - matrix depth = do - (indexDomain, _) <- int - case domainSizeOf indexDomain of - Left err -> bug err - Right indexSize -> do - (innerDomain, innerConstantGen) <- dispatch (smaller depth) - return ( DomainMatrix indexDomain innerDomain - , do innerConstants <- vectorOf (fromInteger indexSize) innerConstantGen - return $ ConstantAbstract $ AbsLitMatrix indexDomain innerConstants - ) - - set :: Int -> Gen (Domain HasRepresentation Constant, Gen Constant) - set depth = oneof [setFixed depth, setBounded depth] - - setFixed :: Int -> Gen (Domain HasRepresentation Constant, Gen Constant) - setFixed depth = do - (dom, constantGen) <- dispatch (smaller depth) - let sizeUpTo = case domainSizeOf dom of - Left err -> bug err - Right s -> min 10 s - size <- choose (0 :: Integer, sizeUpTo) - repr <- pickFromList [Set_Explicit] - let domainOut = - DomainSet - repr -<<<<<<< HEAD - (SetAttr (SizeAttr_Size (ConstantInt Nothing size))) -||||||| merged common ancestors - (SetAttr (SizeAttr_Size (ConstantInt size))) -======= - (SetAttr (SizeAttr_Size (ConstantInt NoTag size))) ->>>>>>> taggedints - dom - return ( domainOut - , let try n = - if n >= maxRetries - then fail (vcat [ "setFixed: maxRetries" - , pretty domainOut - ]) - else do - elems <- vectorOf (fromInteger size) constantGen - let sorted = sortNub elems - if length sorted == length elems - then return $ ConstantAbstract $ AbsLitSet sorted - else try (n+1) - in try (1 :: Int) - ) - - setBounded :: Int -> Gen (Domain HasRepresentation Constant, Gen Constant) - setBounded depth = oneof [setBoundedMax depth, setBoundedMinMax depth] - - setBoundedMax :: Int -> Gen (Domain HasRepresentation Constant, Gen Constant) - setBoundedMax depth = do - (dom, constantGen) <- dispatch (smaller depth) - let sizeUpTo = case domainSizeOf dom of - Left err -> bug err - Right s -> min 10 s - maxSize <- choose (0 :: Integer, sizeUpTo) - repr <- pickFromList [Set_ExplicitVarSizeWithFlags, Set_ExplicitVarSizeWithMarker] - return ( DomainSet repr -<<<<<<< HEAD - (SetAttr (SizeAttr_MaxSize (ConstantInt Nothing maxSize))) -||||||| merged common ancestors - (SetAttr (SizeAttr_MaxSize (ConstantInt maxSize))) -======= - (SetAttr (SizeAttr_MaxSize (ConstantInt NoTag maxSize))) ->>>>>>> taggedints - dom - , do numElems <- choose (0, maxSize) - elems <- vectorOf (fromInteger numElems) constantGen - let sorted = sortNub elems - return $ ConstantAbstract $ AbsLitSet sorted - ) - - setBoundedMinMax :: Int -> Gen (Domain HasRepresentation Constant, Gen Constant) - setBoundedMinMax depth = do - (dom, constantGen) <- dispatch (smaller depth) - let sizeUpTo = case domainSizeOf dom of - Left err -> bug err - Right s -> min 10 s - minSize <- choose (0 :: Integer, sizeUpTo) - maxSize <- choose (minSize, sizeUpTo) - repr <- pickFromList [Set_ExplicitVarSizeWithMarker, Set_ExplicitVarSizeWithFlags] - let domainOut = - DomainSet - repr - (SetAttr (SizeAttr_MinMaxSize -<<<<<<< HEAD - (ConstantInt Nothing minSize) - (ConstantInt Nothing maxSize))) -||||||| merged common ancestors - (ConstantInt minSize) - (ConstantInt maxSize))) -======= - (ConstantInt NoTag minSize) - (ConstantInt NoTag maxSize))) ->>>>>>> taggedints - dom - return ( domainOut - , let try n = - if n >= maxRetries - then fail (vcat [ "setFixed: maxRetries" - , pretty domainOut - ]) - else do - numElems <- choose (minSize, maxSize) - elems <- vectorOf (fromInteger numElems) constantGen - let sorted = sortNub elems - if genericLength sorted >= minSize - then return $ ConstantAbstract $ AbsLitSet sorted - else try (n+1) - in try (1 :: Int) - ) - -pickFromList :: [a] -> Gen a -pickFromList [] = fail "pickFromList []" -pickFromList xs = do - index <- choose (0, length xs - 1) - return (xs `at` index) - -sampleArbitraryDomainAndConstant :: IO () -sampleArbitraryDomainAndConstant = do - samples <- sample' arbitraryDomainAndConstant - forM_ samples $ \ (dom, consGen) -> do - print $ "domain :" <+> pretty dom - constants <- sample' consGen - print $ "constants :" <+> vcat (map (("-" <+>) . pretty) constants) - - diff --git a/src/Conjure/Language/Constant.hs.orig b/src/Conjure/Language/Constant.hs.orig deleted file mode 100644 index b973ac51b7..0000000000 --- a/src/Conjure/Language/Constant.hs.orig +++ /dev/null @@ -1,844 +0,0 @@ -{-# LANGUAGE DeriveGeneric, DeriveDataTypeable #-} -{-# LANGUAGE ViewPatterns #-} - -module Conjure.Language.Constant - ( Constant(..) - , valuesInIntDomain - , normaliseConstant - , validateConstantForDomain - , mkUndef, isUndef - , emptyCollection - , viewConstantBool - , viewConstantInt - , viewConstantTuple - , viewConstantRecord - , viewConstantVariant - , viewConstantMatrix - , viewConstantSet - , viewConstantMSet - , viewConstantFunction - , viewConstantSequence - , viewConstantRelation - , viewConstantPartition - , viewConstantPermutation - ) where - --- conjure -import Conjure.Prelude -import Conjure.Bug -import Conjure.Language.Name -import Conjure.Language.Domain -import Conjure.Language.Type -import Conjure.Language.AbstractLiteral - -import Conjure.Language.DomainSizeOf -import Conjure.Language.TypeOf -import Conjure.Language.AdHoc -import Conjure.Language.Pretty - --- base -import Data.Data ( toConstr, constrIndex ) - --- QuickCheck -import Test.QuickCheck ( Arbitrary(..), oneof ) - - -data Constant - = ConstantBool Bool -<<<<<<< HEAD -<<<<<<< HEAD - | ConstantInt (Maybe Name) Integer -======= - | ConstantInt IntTag Integer ->>>>>>> f8c15eb3160b509a17e3d70103b237ea8d666c04 -||||||| merged common ancestors - | ConstantInt Integer -======= - | ConstantInt IntTag Integer ->>>>>>> taggedints - | ConstantEnum Name {- name for the enum domain -} - [Name] {- values in the enum domain -} - Name {- the literal -} - | ConstantField Name Type -- the name of a field of Record or Variant and its type - | ConstantAbstract (AbstractLiteral Constant) - | DomainInConstant (Domain () Constant) - | TypedConstant Constant Type - | ConstantUndefined Text Type -- never use this for a bool - -- use false instead for them - deriving (Show, Data, Typeable, Generic) - -instance Eq Constant where - a == b = compare a b == EQ - --- implementing the Eq&Ord instances by hand, because we want to special case the TypedConstant constructor -instance Ord Constant where - - -- do not use type info when comparing - compare (TypedConstant a _) (TypedConstant b _) = compare a b - compare (TypedConstant a _) b = compare a b - compare a (TypedConstant b _) = compare a b - - -- the "usual" comparisons - compare (ConstantBool a) (ConstantBool b) = compare a b - compare (ConstantInt _ a) (ConstantInt _ b) = compare a b - compare (ConstantEnum _ aVals aVal) (ConstantEnum _ bVals bVal) = - compare (elemIndex aVal aVals, aVal) (elemIndex bVal bVals, bVal) - compare (ConstantField a1 a2) (ConstantField b1 b2) = compare (a1,a2) (b1,b2) - compare (ConstantAbstract a) (ConstantAbstract b) = compare a b - compare (DomainInConstant a) (DomainInConstant b) = compare a b - compare (ConstantUndefined a1 a2) (ConstantUndefined b1 b2) = compare (a1,a2) (b1,b2) - - -- if the constructors do not match - compare a b = compare (constrIndex (toConstr a)) (constrIndex (toConstr b)) - -instance Serialize Constant -instance Hashable Constant -instance ToJSON Constant where toJSON = genericToJSON jsonOptions -instance FromJSON Constant where parseJSON = genericParseJSON jsonOptions - -instance Arbitrary Constant where - arbitrary = oneof - [ ConstantBool <$> arbitrary -<<<<<<< HEAD -<<<<<<< HEAD - , ConstantInt Nothing <$> arbitrary -======= - , ConstantInt NoTag <$> arbitrary ->>>>>>> f8c15eb3160b509a17e3d70103b237ea8d666c04 -||||||| merged common ancestors - , ConstantInt <$> arbitrary -======= - , ConstantInt NoTag <$> arbitrary ->>>>>>> taggedints - ] - -instance TypeOf Constant where - typeOf ConstantBool{} = return TypeBool -<<<<<<< HEAD -<<<<<<< HEAD - typeOf (ConstantInt name _) = return $ TypeInt name -======= - typeOf (ConstantInt t _) = return (TypeInt t) ->>>>>>> f8c15eb3160b509a17e3d70103b237ea8d666c04 -||||||| merged common ancestors - typeOf ConstantInt{} = return TypeInt -======= - typeOf (ConstantInt t _) = return (TypeInt t) ->>>>>>> taggedints - typeOf (ConstantEnum defn _ _ ) = return (TypeEnum defn) - typeOf (ConstantField _ ty) = return ty - typeOf (ConstantAbstract x ) = typeOf x - typeOf (DomainInConstant dom) = typeOf dom - typeOf (TypedConstant _ ty) = return ty - typeOf (ConstantUndefined _ ty) = return ty - -instance DomainSizeOf Constant Integer where - domainSizeOf DomainBool{} = return 2 -<<<<<<< HEAD - domainSizeOf (DomainIntE _ x) = bug ("not implemented, domainSizeOf DomainIntE" <+> pretty (show x)) -======= - domainSizeOf (DomainIntE x) = bug ("not implemented, domainSizeOf DomainIntE" <+> pretty (show x)) -<<<<<<< HEAD ->>>>>>> f8c15eb3160b509a17e3d70103b237ea8d666c04 - domainSizeOf (DomainInt _ rs) = domainSizeOfRanges rs -||||||| merged common ancestors - domainSizeOf (DomainInt rs) = domainSizeOfRanges rs -======= - domainSizeOf (DomainInt _ rs) = domainSizeOfRanges rs ->>>>>>> taggedints - domainSizeOf DomainEnum{} = fail "domainSizeOf: Unknown for given enum." - domainSizeOf (DomainTuple ds) = product <$> mapM domainSizeOf ds - domainSizeOf (DomainMatrix index inner) = intPow <$> domainSizeOf inner <*> domainSizeOf index - domainSizeOf d@(DomainSet _ (SetAttr attrs) inner) = - case attrs of - SizeAttr_None -> do - innerSize <- domainSizeOf inner - return (2 `intPow` innerSize) -<<<<<<< HEAD -<<<<<<< HEAD - SizeAttr_Size (ConstantInt Nothing size) -> do -======= - SizeAttr_Size (ConstantInt _ size) -> do ->>>>>>> f8c15eb3160b509a17e3d70103b237ea8d666c04 -||||||| merged common ancestors - SizeAttr_Size (ConstantInt size) -> do -======= - SizeAttr_Size (ConstantInt _ size) -> do ->>>>>>> taggedints - innerSize <- domainSizeOf inner - return (nchoosek (product . enumFromTo 1) innerSize size) - SizeAttr_MinSize{} -> do - -- TODO: we can do better here - innerSize <- domainSizeOf inner - return (2 `intPow` innerSize) -<<<<<<< HEAD -<<<<<<< HEAD - SizeAttr_MaxSize (ConstantInt Nothing maxSize) -> do -||||||| merged common ancestors - SizeAttr_MaxSize (ConstantInt maxSize) -> do -======= - SizeAttr_MaxSize (ConstantInt _ maxSize) -> do ->>>>>>> taggedints - innerSize <- domainSizeOf inner - return $ sum [ nchoosek (product . enumFromTo 1) innerSize k | k <- [0 .. maxSize] ] -<<<<<<< HEAD - SizeAttr_MinMaxSize (ConstantInt Nothing minSize) (ConstantInt Nothing maxSize) -> do -======= - SizeAttr_MaxSize (ConstantInt _ maxSize) -> do - innerSize <- domainSizeOf inner - return $ sum [ nchoosek (product . enumFromTo 1) innerSize k | k <- [0 .. maxSize] ] - SizeAttr_MinMaxSize (ConstantInt _ minSize) (ConstantInt _ maxSize) -> do ->>>>>>> f8c15eb3160b509a17e3d70103b237ea8d666c04 -||||||| merged common ancestors - SizeAttr_MinMaxSize (ConstantInt minSize) (ConstantInt maxSize) -> do -======= - SizeAttr_MinMaxSize (ConstantInt _ minSize) (ConstantInt _ maxSize) -> do ->>>>>>> taggedints - innerSize <- domainSizeOf inner - return $ sum [ nchoosek (product . enumFromTo 1) innerSize k | k <- [minSize .. maxSize] ] - _ -> fail ("domainSizeOf{Constant}" <+> pretty d) - domainSizeOf DomainMSet {} = bug "not implemented: domainSizeOf DomainMSet" - domainSizeOf DomainFunction {} = bug "not implemented: domainSizeOf DomainFunction" - domainSizeOf DomainRelation {} = bug "not implemented: domainSizeOf DomainRelation" - domainSizeOf DomainPartition {} = bug "not implemented: domainSizeOf DomainPartition" - domainSizeOf _ = bug "not implemented: domainSizeOf" - -emptyCollection :: Constant -> Bool -emptyCollection ConstantBool{} = False -emptyCollection ConstantInt{} = False -emptyCollection ConstantEnum{} = False -emptyCollection ConstantField{} = False -emptyCollection (ConstantAbstract x) = emptyCollectionAbsLit x -emptyCollection DomainInConstant{} = False -emptyCollection (TypedConstant x _) = emptyCollection x -emptyCollection ConstantUndefined{} = False - -intPow :: Integer -> Integer -> Integer -intPow = (^) - -domainSizeOfRanges :: MonadFail m => [Range Constant] -> m Integer -domainSizeOfRanges = fmap genericLength . valuesInIntDomain - -instance DomainSizeOf Constant Constant where -<<<<<<< HEAD -<<<<<<< HEAD - domainSizeOf = fmap (ConstantInt Nothing) . domainSizeOf -======= - domainSizeOf = fmap (ConstantInt NoTag) . domainSizeOf ->>>>>>> f8c15eb3160b509a17e3d70103b237ea8d666c04 -||||||| merged common ancestors - domainSizeOf = fmap ConstantInt . domainSizeOf -======= - domainSizeOf = fmap (ConstantInt NoTag) . domainSizeOf ->>>>>>> taggedints - -instance Pretty Constant where - - -- hack, oh sweet hack! - -- print a domain instead of a type when printing an empty matrix literal. - -- this means we print "int()" instead of "int" inside the index of a matrix type - -- SR expects it this way... - pretty (TypedConstant (ConstantAbstract (AbsLitMatrix _ [])) ty) = - let - pretty' (TypeMatrix index innerNested) - = "matrix indexed by" <+> prettyList prBrackets "," (map pretty' indices) - <+> "of" <+> pretty inner - where - (indices,inner) = first (index:) $ collect innerNested - collect (TypeMatrix i j) = first (i:) $ collect j - collect x = ([],x) -<<<<<<< HEAD -<<<<<<< HEAD - pretty' (TypeInt _) = "int()" -======= - pretty' TypeInt{} = "int()" ->>>>>>> f8c15eb3160b509a17e3d70103b237ea8d666c04 -||||||| merged common ancestors - pretty' TypeInt = "int()" -======= - pretty' TypeInt{} = "int()" ->>>>>>> taggedints - pretty' t = pretty t - in - prParens $ "[] : `" <> pretty' ty <> "`" - - pretty (ConstantBool False) = "false" - pretty (ConstantBool True ) = "true" - pretty (ConstantInt _ x ) = pretty x - pretty (ConstantEnum _ _ x) = pretty x - pretty (ConstantField n _) = pretty n - pretty (ConstantAbstract x) = pretty x - pretty (DomainInConstant d) = "`" <> pretty d <> "`" - pretty (TypedConstant x ty) = prParens $ pretty x <+> ":" <+> "`" <> pretty ty <> "`" - pretty (ConstantUndefined reason ty) = "undefined" <> prParens (pretty reason <+> ":" <+> "`" <> pretty ty <> "`") - -instance ExpressionLike Constant where -<<<<<<< HEAD -<<<<<<< HEAD - fromInt = ConstantInt Nothing - intOut _ (ConstantInt Nothing x) = return x -======= - fromInt = ConstantInt NoTag - intOut _ (ConstantInt _ x) = return x ->>>>>>> f8c15eb3160b509a17e3d70103b237ea8d666c04 -||||||| merged common ancestors - fromInt = ConstantInt - intOut _ (ConstantInt x) = return x -======= - fromInt = ConstantInt NoTag - fromIntWithTag i t = ConstantInt t i - intOut _ (ConstantInt _ x) = return x ->>>>>>> taggedints - intOut doc c = fail $ vcat [ "Expecting an integer, but found:" <+> pretty c - , "Called from:" <+> doc - ] - - fromBool = ConstantBool - boolOut (ConstantBool x) = return x - boolOut ConstantUndefined{} = return False - boolOut c = fail ("Expecting a boolean, but found:" <+> pretty c) - - fromList xs = ConstantAbstract $ AbsLitMatrix (mkDomainIntB 1 (fromInt $ genericLength xs)) xs - listOut (ConstantAbstract (AbsLitMatrix _ xs)) = return xs - listOut c = fail ("Expecting a matrix literal, but found:" <+> pretty c) - -instance ReferenceContainer Constant where - fromName name = bug ("ReferenceContainer{Constant} fromName --" <+> pretty name) - nameOut (ConstantField nm _) = return nm - nameOut p = bug ("ReferenceContainer{Constant} nameOut --" <+> pretty p) - -instance DomainContainer Constant (Domain ()) where - fromDomain = DomainInConstant - domainOut (DomainInConstant dom) = return dom - domainOut _ = fail "domainOut{Constant}" - -mkUndef :: Type -> Doc -> Constant -mkUndef TypeBool _ = ConstantBool False -mkUndef ty reason = ConstantUndefined (stringToText $ show reason) ty - -isUndef :: Constant -> Bool -isUndef ConstantUndefined{} = True -isUndef _ = False - -normaliseConstant :: Constant -> Constant -normaliseConstant x@ConstantBool{} = x -normaliseConstant x@ConstantInt{} = x -normaliseConstant x@ConstantEnum{} = x -normaliseConstant x@ConstantField{} = x -normaliseConstant (ConstantAbstract x) = ConstantAbstract (normaliseAbsLit normaliseConstant x) -normaliseConstant (DomainInConstant d) = DomainInConstant (normaliseDomain normaliseConstant d) -normaliseConstant (TypedConstant c ty) = TypedConstant (normaliseConstant c) ty -normaliseConstant x@ConstantUndefined{} = x - -instance Num Constant where -<<<<<<< HEAD -<<<<<<< HEAD - ConstantInt Nothing x + ConstantInt Nothing y = ConstantInt Nothing (x+y) - x + y = bug $ vcat [ "Num Constant (+)", "x:" <+> pretty x, "y:" <+> pretty y ] - ConstantInt Nothing x - ConstantInt Nothing y = ConstantInt Nothing (x-y) - x - y = bug $ vcat [ "Num Constant (-)", "x:" <+> pretty x, "y:" <+> pretty y ] - ConstantInt Nothing x * ConstantInt Nothing y = ConstantInt Nothing (x*y) - x * y = bug $ vcat [ "Num Constant (*)", "x:" <+> pretty x, "y:" <+> pretty y ] - abs (ConstantInt Nothing x) = ConstantInt Nothing (abs x) - abs x = bug $ vcat [ "Num Constant abs", "x:" <+> pretty x ] - signum (ConstantInt Nothing x) = ConstantInt Nothing (signum x) - signum x = bug $ vcat [ "Num Constant signum", "x:" <+> pretty x ] - fromInteger = ConstantInt Nothing . fromInteger -======= - ConstantInt _ x + ConstantInt _ y = ConstantInt NoTag (x+y) -||||||| merged common ancestors - ConstantInt x + ConstantInt y = ConstantInt (x+y) -======= - ConstantInt _ x + ConstantInt _ y = ConstantInt NoTag (x+y) ->>>>>>> taggedints - x + y = bug $ vcat [ "Num Constant (+)", "x:" <+> pretty x, "y:" <+> pretty y ] - ConstantInt _ x - ConstantInt _ y = ConstantInt NoTag (x-y) - x - y = bug $ vcat [ "Num Constant (-)", "x:" <+> pretty x, "y:" <+> pretty y ] - ConstantInt _ x * ConstantInt _ y = ConstantInt NoTag (x*y) - x * y = bug $ vcat [ "Num Constant (*)", "x:" <+> pretty x, "y:" <+> pretty y ] - abs (ConstantInt t x) = ConstantInt t (abs x) - abs x = bug $ vcat [ "Num Constant abs", "x:" <+> pretty x ] - signum (ConstantInt t x) = ConstantInt t (signum x) - signum x = bug $ vcat [ "Num Constant signum", "x:" <+> pretty x ] -<<<<<<< HEAD - fromInteger = ConstantInt NoTag . fromInteger ->>>>>>> f8c15eb3160b509a17e3d70103b237ea8d666c04 -||||||| merged common ancestors - fromInteger = ConstantInt . fromInteger -======= - fromInteger = ConstantInt NoTag . fromInteger ->>>>>>> taggedints - - -valuesInIntDomain :: MonadFail m => [Range Constant] -> m [Integer] -valuesInIntDomain ranges = - if isFinite - then return allValues - else fail $ "Expected finite integer ranges, but got:" <++> prettyList id "," ranges - - where - - allRanges :: [Maybe [Integer]] - allRanges = - [ vals - | r <- ranges - , let vals = case r of -<<<<<<< HEAD -<<<<<<< HEAD - RangeSingle (ConstantInt Nothing x) -> return [x] - RangeBounded (ConstantInt Nothing l) (ConstantInt Nothing u) -> return [l..u] -======= - RangeSingle (ConstantInt _ x) -> return [x] - RangeBounded (ConstantInt _ l) (ConstantInt _ u) -> return [l..u] ->>>>>>> f8c15eb3160b509a17e3d70103b237ea8d666c04 -||||||| merged common ancestors - RangeSingle (ConstantInt x) -> return [x] - RangeBounded (ConstantInt l) (ConstantInt u) -> return [l..u] -======= - RangeSingle (ConstantInt _ x) -> return [x] - RangeBounded (ConstantInt _ l) (ConstantInt _ u) -> return [l..u] ->>>>>>> taggedints - _ -> Nothing - ] - - isFinite :: Bool - isFinite = Nothing `notElem` allRanges - - allValues :: [Integer] - allValues = sortNub $ concat $ catMaybes allRanges - - --- | Assuming both the value and the domain are normalised --- TODO: make this stricter, but write failing test cases first! -validateConstantForDomain :: forall m r . (MonadFail m, Pretty r) => Name -> Constant -> Domain r Constant -> m () - -validateConstantForDomain _ ConstantBool{} DomainBool{} = return () - -validateConstantForDomain _ _ (DomainInt _ []) = return () -- no restrictions - -<<<<<<< HEAD -<<<<<<< HEAD -validateConstantForDomain name c@(ConstantInt Nothing i) d@(DomainInt Nothing rs) = -||||||| merged common ancestors -validateConstantForDomain name c@(ConstantInt i) d@(DomainInt rs) = -======= -validateConstantForDomain name c@(ConstantInt cTag i) d@(DomainInt dTag rs) | cTag == dTag = ->>>>>>> taggedints - let -<<<<<<< HEAD - intInRange RangeOpen = True - intInRange (RangeSingle (ConstantInt Nothing a)) = i == a - intInRange (RangeLowerBounded (ConstantInt Nothing a)) = i >= a - intInRange (RangeUpperBounded (ConstantInt Nothing a)) = i <= a - intInRange (RangeBounded (ConstantInt Nothing a) (ConstantInt Nothing b)) = i >= a && i <= b - intInRange _ = False -||||||| merged common ancestors - intInRange RangeOpen = True - intInRange (RangeSingle (ConstantInt a)) = i == a - intInRange (RangeLowerBounded (ConstantInt a)) = i >= a - intInRange (RangeUpperBounded (ConstantInt a)) = i <= a - intInRange (RangeBounded (ConstantInt a) (ConstantInt b)) = i >= a && i <= b - intInRange _ = False -======= - intInRange RangeOpen = True - intInRange (RangeSingle (ConstantInt _ a)) = i == a - intInRange (RangeLowerBounded (ConstantInt _ a)) = i >= a - intInRange (RangeUpperBounded (ConstantInt _ a)) = i <= a - intInRange (RangeBounded (ConstantInt _ a) (ConstantInt _ b)) = i >= a && i <= b - intInRange _ = False ->>>>>>> taggedints - in unless (any intInRange rs) (constantNotInDomain name c d) - -<<<<<<< HEAD -validateConstantForDomain _ (ConstantInt (Just cname) i) (DomainUnnamed uname (ConstantInt Nothing a)) | cname == uname && i >= 1 && i <= a = return () -======= -validateConstantForDomain name c@(ConstantInt cTag i) d@(DomainInt dTag rs) | cTag == dTag = - let - intInRange RangeOpen = True - intInRange (RangeSingle (ConstantInt _ a)) = i == a - intInRange (RangeLowerBounded (ConstantInt _ a)) = i >= a - intInRange (RangeUpperBounded (ConstantInt _ a)) = i <= a - intInRange (RangeBounded (ConstantInt _ a) (ConstantInt _ b)) = i >= a && i <= b - intInRange _ = False - in unless (any intInRange rs) (constantNotInDomain name c d) - -validateConstantForDomain _ (ConstantInt _ i) (DomainUnnamed _ (ConstantInt _ a)) | i >= 1 && i <= a = return () ->>>>>>> f8c15eb3160b509a17e3d70103b237ea8d666c04 -||||||| merged common ancestors -validateConstantForDomain _ (ConstantInt i) (DomainUnnamed _ (ConstantInt a)) | i >= 1 && i <= a = return () -======= -validateConstantForDomain _ (ConstantInt _ i) (DomainUnnamed _ (ConstantInt _ a)) | i >= 1 && i <= a = return () ->>>>>>> taggedints - -validateConstantForDomain _ _ (DomainEnum _ Nothing _) = return () -- no restrictions -validateConstantForDomain name c d@(DomainEnum _ _ Nothing) = - fail $ vcat [ "validateConstantForDomain: enum not handled" - , pretty name - , pretty c - , pretty d - ] -validateConstantForDomain name -<<<<<<< HEAD -<<<<<<< HEAD - c@ConstantInt{} - d@(DomainEnum name'' (Just ranges) (Just mp)) = nested c d $ do -======= - c@(ConstantInt cTag _) -||||||| merged common ancestors - c@ConstantInt{} -======= - c@(ConstantInt cTag _) ->>>>>>> taggedints - d@(DomainEnum _ (Just ranges) (Just mp)) = nested c d $ do ->>>>>>> f8c15eb3160b509a17e3d70103b237ea8d666c04 - let - -- lu :: MonadFail m => Name -> m Constant - lu (ConstantEnum _ _ nm) = - case lookup nm mp of - Nothing -> fail $ "No value for:" <+> pretty nm -<<<<<<< HEAD -<<<<<<< HEAD - Just v -> return (ConstantInt (Just name'') v) - lu (ConstantInt name' v) = return (ConstantInt name' v) -======= - Just v -> return (ConstantInt cTag v) - lu (ConstantInt t v) = return (ConstantInt t v) ->>>>>>> f8c15eb3160b509a17e3d70103b237ea8d666c04 -||||||| merged common ancestors - Just v -> return (ConstantInt v) - lu (ConstantInt v) = return (ConstantInt v) -======= - Just v -> return (ConstantInt cTag v) - lu (ConstantInt t v) = return (ConstantInt t v) ->>>>>>> taggedints - lu x = fail $ "validateConstantForDomain.lu" <+> pretty x - - -- lu2 :: MonadFail m => Range Name -> m (Range Constant) - lu2 = mapM lu - - rs <- mapM lu2 ranges -<<<<<<< HEAD -<<<<<<< HEAD - validateConstantForDomain name c (DomainInt Nothing rs :: Domain r Constant) -======= - validateConstantForDomain name c (DomainInt cTag rs :: Domain r Constant) ->>>>>>> f8c15eb3160b509a17e3d70103b237ea8d666c04 -||||||| merged common ancestors - validateConstantForDomain name c (DomainInt rs :: Domain r Constant) -======= - validateConstantForDomain name c (DomainInt cTag rs :: Domain r Constant) ->>>>>>> taggedints - -validateConstantForDomain name - c@(ConstantAbstract (AbsLitTuple cs)) - d@(DomainTuple ds) = nested c d $ zipWithM_ (validateConstantForDomain name) cs ds - -validateConstantForDomain name - c@(ConstantAbstract (AbsLitRecord (sortOn fst -> cs))) - d@(DomainRecord (sortOn fst -> ds)) - | map fst cs == map fst ds - = nested c d $ zipWithM_ (validateConstantForDomain name) (map snd cs) (map snd ds) - | otherwise - = constantNotInDomain name c d - -validateConstantForDomain name - c@(ConstantAbstract (AbsLitVariant _ n c')) - d@(DomainVariant ds) - | Just d' <- lookup n ds - = nested c d $ validateConstantForDomain name c' d' - | otherwise - = constantNotInDomain name c d - -validateConstantForDomain name - c@(ConstantAbstract (AbsLitMatrix cIndex vals)) - d@(DomainMatrix dIndex dInner) = do - nested c d $ - mapM_ (\ val -> validateConstantForDomain name val dInner ) vals -<<<<<<< HEAD -<<<<<<< HEAD - unless (cIndex == dIndex || cIndex == DomainInt Nothing []) $ fail $ vcat -======= - let - isEmptyIntDomain (DomainInt _ []) = True - isEmptyIntDomain _ = False - unless (cIndex == dIndex || isEmptyIntDomain cIndex) $ fail $ vcat ->>>>>>> f8c15eb3160b509a17e3d70103b237ea8d666c04 -||||||| merged common ancestors - unless (cIndex == dIndex || cIndex == DomainInt []) $ fail $ vcat -======= - let - isEmptyIntDomain (DomainInt _ []) = True - isEmptyIntDomain _ = False - unless (cIndex == dIndex || isEmptyIntDomain cIndex) $ fail $ vcat ->>>>>>> taggedints - [ "The indices do not match between the value and the domain." - , "Value :" <+> pretty c - , "Domain:" <+> pretty d - ] - -validateConstantForDomain name - c@(ConstantAbstract (AbsLitSet vals)) - d@(DomainSet _ (SetAttr sizeAttr) dInner) = do - let cardinalityOK = case sizeAttr of - SizeAttr_None -> True -<<<<<<< HEAD -<<<<<<< HEAD - SizeAttr_Size (ConstantInt Nothing s) -> s == genericLength vals - SizeAttr_MinSize (ConstantInt Nothing s) -> s <= genericLength vals - SizeAttr_MaxSize (ConstantInt Nothing s) -> genericLength vals <= s - SizeAttr_MinMaxSize (ConstantInt Nothing smin) (ConstantInt Nothing smax) -> -======= - SizeAttr_Size (ConstantInt _ s) -> s == genericLength vals - SizeAttr_MinSize (ConstantInt _ s) -> s <= genericLength vals - SizeAttr_MaxSize (ConstantInt _ s) -> genericLength vals <= s - SizeAttr_MinMaxSize (ConstantInt _ smin) (ConstantInt _ smax) -> ->>>>>>> f8c15eb3160b509a17e3d70103b237ea8d666c04 -||||||| merged common ancestors - SizeAttr_Size (ConstantInt s) -> s == genericLength vals - SizeAttr_MinSize (ConstantInt s) -> s <= genericLength vals - SizeAttr_MaxSize (ConstantInt s) -> genericLength vals <= s - SizeAttr_MinMaxSize (ConstantInt smin) (ConstantInt smax) -> -======= - SizeAttr_Size (ConstantInt _ s) -> s == genericLength vals - SizeAttr_MinSize (ConstantInt _ s) -> s <= genericLength vals - SizeAttr_MaxSize (ConstantInt _ s) -> genericLength vals <= s - SizeAttr_MinMaxSize (ConstantInt _ smin) (ConstantInt _ smax) -> ->>>>>>> taggedints - smin <= genericLength vals && genericLength vals <= smax - _ -> False - unless cardinalityOK $ fail $ vcat - [ "The value is not a member of the domain." - , "Value :" <+> pretty c - , "Domain:" <+> pretty d - , "Reason: Domain attributes are not satisfied." - , "Specifically:" <+> pretty sizeAttr - ] - nested c d $ mapM_ (\ val -> validateConstantForDomain name val dInner ) vals - -validateConstantForDomain name - c@(ConstantAbstract (AbsLitMSet vals)) - d@(DomainMSet _ (MSetAttr sizeAttr occurAttr) dInner) = do - let cardinalityOK = case sizeAttr of - SizeAttr_None -> True -<<<<<<< HEAD -<<<<<<< HEAD - SizeAttr_Size (ConstantInt Nothing s) -> s == genericLength vals - SizeAttr_MinSize (ConstantInt Nothing s) -> s <= genericLength vals - SizeAttr_MaxSize (ConstantInt Nothing s) -> genericLength vals <= s - SizeAttr_MinMaxSize (ConstantInt Nothing smin) (ConstantInt Nothing smax) -> -======= - SizeAttr_Size (ConstantInt _ s) -> s == genericLength vals - SizeAttr_MinSize (ConstantInt _ s) -> s <= genericLength vals - SizeAttr_MaxSize (ConstantInt _ s) -> genericLength vals <= s - SizeAttr_MinMaxSize (ConstantInt _ smin) (ConstantInt _ smax) -> ->>>>>>> f8c15eb3160b509a17e3d70103b237ea8d666c04 -||||||| merged common ancestors - SizeAttr_Size (ConstantInt s) -> s == genericLength vals - SizeAttr_MinSize (ConstantInt s) -> s <= genericLength vals - SizeAttr_MaxSize (ConstantInt s) -> genericLength vals <= s - SizeAttr_MinMaxSize (ConstantInt smin) (ConstantInt smax) -> -======= - SizeAttr_Size (ConstantInt _ s) -> s == genericLength vals - SizeAttr_MinSize (ConstantInt _ s) -> s <= genericLength vals - SizeAttr_MaxSize (ConstantInt _ s) -> genericLength vals <= s - SizeAttr_MinMaxSize (ConstantInt _ smin) (ConstantInt _ smax) -> ->>>>>>> taggedints - smin <= genericLength vals && genericLength vals <= smax - _ -> False - unless cardinalityOK $ fail $ vcat - [ "The value is not a member of the domain." - , "Value :" <+> pretty c - , "Domain:" <+> pretty d - , "Reason: Domain attributes are not satisfied." - , "Specifically:" <+> pretty sizeAttr - ] - let occurOK = case occurAttr of - OccurAttr_None -> True -<<<<<<< HEAD -<<<<<<< HEAD - OccurAttr_MinOccur (ConstantInt Nothing s) -> and [ s <= occ | (_, occ) <- histogram vals ] - OccurAttr_MaxOccur (ConstantInt Nothing s) -> and [ occ <= s | (_, occ) <- histogram vals ] - OccurAttr_MinMaxOccur (ConstantInt Nothing smin) (ConstantInt Nothing smax) -> -======= - OccurAttr_MinOccur (ConstantInt _ s) -> and [ s <= occ | (_, occ) <- histogram vals ] - OccurAttr_MaxOccur (ConstantInt _ s) -> and [ occ <= s | (_, occ) <- histogram vals ] - OccurAttr_MinMaxOccur (ConstantInt _ smin) (ConstantInt _ smax) -> ->>>>>>> f8c15eb3160b509a17e3d70103b237ea8d666c04 -||||||| merged common ancestors - OccurAttr_MinOccur (ConstantInt s) -> and [ s <= occ | (_, occ) <- histogram vals ] - OccurAttr_MaxOccur (ConstantInt s) -> and [ occ <= s | (_, occ) <- histogram vals ] - OccurAttr_MinMaxOccur (ConstantInt smin) (ConstantInt smax) -> -======= - OccurAttr_MinOccur (ConstantInt _ s) -> and [ s <= occ | (_, occ) <- histogram vals ] - OccurAttr_MaxOccur (ConstantInt _ s) -> and [ occ <= s | (_, occ) <- histogram vals ] - OccurAttr_MinMaxOccur (ConstantInt _ smin) (ConstantInt _ smax) -> ->>>>>>> taggedints - and [ smin <= occ && occ <= smax | (_, occ) <- histogram vals ] - _ -> False - unless occurOK $ fail $ vcat - [ "The value is not a member of the domain." - , "Value :" <+> pretty c - , "Domain:" <+> pretty d - , "Reason: Domain attributes are not satisfied." - , "Specifically:" <+> pretty occurAttr - ] - nested c d $ mapM_ (\ val -> validateConstantForDomain name val dInner ) vals - -validateConstantForDomain name - c@(ConstantAbstract (AbsLitFunction vals)) - d@(DomainFunction _ _ dFrom dTo) = nested c d $ do - mapM_ (\ val -> validateConstantForDomain name (fst val) dFrom) vals - mapM_ (\ val -> validateConstantForDomain name (snd val) dTo ) vals - -validateConstantForDomain name - c@(ConstantAbstract (AbsLitSequence vals)) - d@(DomainSequence _ _ dInner) = nested c d $ - mapM_ (\ val -> validateConstantForDomain name val dInner ) vals - -validateConstantForDomain name - c@(ConstantAbstract (AbsLitRelation valss)) - d@(DomainRelation _ _ dInners) = nested c d $ - forM_ valss $ \ vals -> - zipWithM_ (validateConstantForDomain name) vals dInners - -validateConstantForDomain name - c@(ConstantAbstract (AbsLitPartition valss)) - d@(DomainPartition _ _ dInner) = nested c d $ - mapM_ (\ val -> validateConstantForDomain name val dInner ) (concat valss) -validateConstantForDomain name - c@(ConstantAbstract (AbsLitPermutation valss)) - d@(DomainPermutation _ _ dInner) = nested c d $ - mapM_ (\ val -> validateConstantForDomain name val dInner ) (concat valss) -validateConstantForDomain name c@(TypedConstant c' _) d = nested c d $ validateConstantForDomain name c' d - -validateConstantForDomain name c d = constantNotInDomain name c d - - -nested :: (MonadFail m, Pretty r) => Constant -> Domain r Constant -> Either Doc () -> m () -nested _ _ Right{} = return () -nested c d (Left err) = fail $ vcat - [ "The value is not a member of the domain." - , "Value :" <+> pretty c - , "Domain:" <+> pretty d - , "Reason:" - , nest 4 err - ] - -constantNotInDomain :: (MonadFail m, Pretty r) => Name -> Constant -> Domain r Constant -> m () -constantNotInDomain n c d = fail $ vcat - [ "The value is not a member of the domain." - , "Name :" <+> pretty n - , "Value :" <+> pretty c - , "Domain:" <+> pretty d - ] - - -viewConstantBool :: MonadFail m => Constant -> m Bool -viewConstantBool (ConstantBool i) = return i -<<<<<<< HEAD -<<<<<<< HEAD -viewConstantBool (ConstantInt Nothing 0) = return False -viewConstantBool (ConstantInt Nothing 1) = return True -viewConstantBool constant = fail ("Expecting a boolean integer, but got:" <++> pretty constant) -======= -viewConstantBool (ConstantInt _ 0) = return False -viewConstantBool (ConstantInt _ 1) = return True -viewConstantBool constant = fail ("Expecting a boolean, but got:" <++> pretty constant) ->>>>>>> f8c15eb3160b509a17e3d70103b237ea8d666c04 -||||||| merged common ancestors -viewConstantBool (ConstantInt 0) = return False -viewConstantBool (ConstantInt 1) = return True -viewConstantBool constant = fail ("Expecting a boolean integer, but got:" <++> pretty constant) -======= -viewConstantBool (ConstantInt _ 0) = return False -viewConstantBool (ConstantInt _ 1) = return True -viewConstantBool constant = fail ("Expecting a boolean, but got:" <++> pretty constant) ->>>>>>> taggedints - -viewConstantInt :: MonadFail m => Constant -> m Integer -viewConstantInt (ConstantInt _ i) = return i -viewConstantInt constant = fail ("Expecting an integer, but got:" <++> pretty constant) - -viewConstantTuple :: MonadFail m => Constant -> m [Constant] -viewConstantTuple (ConstantAbstract (AbsLitTuple xs)) = return xs -viewConstantTuple (TypedConstant c _) = viewConstantTuple c -viewConstantTuple constant = fail ("Expecting a tuple, but got:" <++> pretty constant) - -viewConstantRecord :: MonadFail m => Constant -> m [(Name, Constant)] -viewConstantRecord (ConstantAbstract (AbsLitRecord xs)) = return xs -viewConstantRecord (TypedConstant c _) = viewConstantRecord c -viewConstantRecord constant = fail ("Expecting a record, but got:" <++> pretty constant) - -viewConstantVariant :: MonadFail m => Constant -> m (Maybe [(Name, Domain () Constant)], Name, Constant) -viewConstantVariant (ConstantAbstract (AbsLitVariant lu nm x)) = return (lu, nm, x) -viewConstantVariant (TypedConstant c _) = viewConstantVariant c -viewConstantVariant constant = fail ("Expecting a variant, but got:" <++> pretty constant) - -viewConstantMatrix :: MonadFail m => Constant -> m (Domain () Constant, [Constant]) -viewConstantMatrix (ConstantAbstract (AbsLitMatrix ind xs)) = return (ind, xs) -viewConstantMatrix (TypedConstant c _) = viewConstantMatrix c -viewConstantMatrix constant = fail ("Expecting a matrix, but got:" <++> pretty constant) - -viewConstantSet :: MonadFail m => Constant -> m [Constant] -viewConstantSet (ConstantAbstract (AbsLitSet xs)) = return xs -viewConstantSet (TypedConstant c _) = viewConstantSet c -viewConstantSet constant = fail ("Expecting a set, but got:" <++> pretty constant) - -viewConstantMSet :: MonadFail m => Constant -> m [Constant] -viewConstantMSet (ConstantAbstract (AbsLitMSet xs)) = return xs -viewConstantMSet (TypedConstant c _) = viewConstantMSet c -viewConstantMSet constant = fail ("Expecting an mset, but got:" <++> pretty constant) - -viewConstantFunction :: MonadFail m => Constant -> m [(Constant, Constant)] -viewConstantFunction (ConstantAbstract (AbsLitFunction xs)) = return xs -viewConstantFunction (TypedConstant c _) = viewConstantFunction c -viewConstantFunction constant = do - let - suggestion = case constant of -<<<<<<< HEAD -<<<<<<< HEAD - ConstantAbstract (AbsLitMatrix (DomainInt Nothing rs) vals) -> do - froms <- valuesInIntDomain rs - return $ Just $ pretty $ AbsLitFunction (zip (map (ConstantInt Nothing) froms) vals) -======= - ConstantAbstract (AbsLitMatrix (DomainInt _ rs) vals) -> do -||||||| merged common ancestors - ConstantAbstract (AbsLitMatrix (DomainInt rs) vals) -> do -======= - ConstantAbstract (AbsLitMatrix (DomainInt _ rs) vals) -> do ->>>>>>> taggedints - froms <- valuesInIntDomain rs -<<<<<<< HEAD - return $ Just $ pretty $ AbsLitFunction (zip (map (ConstantInt NoTag) froms) vals) ->>>>>>> f8c15eb3160b509a17e3d70103b237ea8d666c04 -||||||| merged common ancestors - return $ Just $ pretty $ AbsLitFunction (zip (map ConstantInt froms) vals) -======= - return $ Just $ pretty $ AbsLitFunction (zip (map (ConstantInt NoTag) froms) vals) ->>>>>>> taggedints - _ -> return Nothing - suggestion >>= \case - Nothing -> fail ("Expecting a function, but got:" <++> pretty constant) - Just sug -> fail (vcat [ "Expecting a function, but got:" <++> pretty constant - , "Maybe you meant:" <++> sug - ]) - -viewConstantSequence :: MonadFail m => Constant -> m [Constant] -viewConstantSequence (ConstantAbstract (AbsLitSequence xs)) = return xs -viewConstantSequence (TypedConstant c _) = viewConstantSequence c -viewConstantSequence constant = fail ("Expecting a sequence, but got:" <++> pretty constant) - -viewConstantRelation :: MonadFail m => Constant -> m [[Constant]] -viewConstantRelation (ConstantAbstract (AbsLitRelation xs)) = return xs -viewConstantRelation (TypedConstant c _) = viewConstantRelation c -viewConstantRelation constant = fail ("Expecting a relation, but got:" <++> pretty constant) - -viewConstantPartition :: MonadFail m => Constant -> m [[Constant]] -viewConstantPartition (ConstantAbstract (AbsLitPartition xs)) = return xs -viewConstantPartition (TypedConstant c _) = viewConstantPartition c -viewConstantPartition constant = fail ("Expecting a partition, but got:" <++> pretty constant) - -viewConstantPermutation :: MonadFail m => Constant -> m [[Constant]] -viewConstantPermutation (ConstantAbstract (AbsLitPermutation xs)) = return xs -viewConstantPermutation (TypedConstant c _) = viewConstantPermutation c -viewConstantPermutation constant = fail ("Expecting a permutation, but got:" <++> pretty constant) diff --git a/src/Conjure/Language/Domain.hs.orig b/src/Conjure/Language/Domain.hs.orig deleted file mode 100644 index badcbbe0e3..0000000000 --- a/src/Conjure/Language/Domain.hs.orig +++ /dev/null @@ -1,1180 +0,0 @@ -{-# LANGUAGE DeriveGeneric, DeriveDataTypeable, DeriveFunctor, DeriveTraversable, DeriveFoldable #-} -{-# LANGUAGE TupleSections #-} -{-# LANGUAGE NoMonomorphismRestriction #-} -{-# LANGUAGE ViewPatterns #-} - -module Conjure.Language.Domain - ( Domain(..) - , HasRepresentation(..) - , Range(..), rangesInts - , SetAttr(..), SizeAttr(..), getMaxFrom_SizeAttr - , MSetAttr(..), OccurAttr(..), getMaxFrom_OccurAttr - , FunctionAttr(..), PartialityAttr(..), JectivityAttr(..) - , SequenceAttr(..) - , RelationAttr(..), BinaryRelationAttrs(..), BinaryRelationAttr(..) - , PartitionAttr(..) - , PermutationAttr(..) - , AttrName(..) - , DomainAttributes(..), DomainAttribute(..) -- only for parsing - , textToRepresentation, representationToShortText, representationToFullText - , isPrimitiveDomain, domainCanIndexMatrix, getIndices - , Tree(..), reprTree, reprAtTopLevel, applyReprTree - , reprTreeEncoded - , forgetRepr, changeRepr, defRepr -<<<<<<< HEAD - , mkDomainBool, mkDomainInt, mkDomainIntB, mkDomainIntBNamed, mkDomainAny -||||||| merged common ancestors - , mkDomainBool, mkDomainInt, mkDomainIntB, mkDomainAny -======= - , mkDomainBool, mkDomainInt, mkDomainIntB, mkDomainIntBTagged, mkDomainAny ->>>>>>> taggedints - , typeOfDomain - , readBinRel - , normaliseDomain, normaliseRange - , innerDomainOf - , singletonDomainInt - ) where - --- conjure -import Conjure.Prelude -import Conjure.Bug -import Conjure.Language.Name -import Conjure.Language.Type -import Conjure.Language.TypeOf -import Conjure.Language.AdHoc -import Conjure.Language.Pretty - --- base -import qualified Data.Semigroup as Semigroup ( (<>) ) - --- QuickCheck -import Test.QuickCheck ( Arbitrary(..), choose, oneof, vectorOf, sized ) - --- containers -import Data.Set as S ( Set, empty, toList, union ) - --- syb -import Data.Data ( toConstr, constrIndex ) - - -data Domain r x - = DomainAny Text Type - | DomainBool -<<<<<<< HEAD - | DomainIntE (Maybe Name) x - | DomainInt (Maybe Name) [Range x] -======= - | DomainIntE x -<<<<<<< HEAD - | DomainInt IntTag [Range x] ->>>>>>> f8c15eb3160b509a17e3d70103b237ea8d666c04 -||||||| merged common ancestors - | DomainInt [Range x] -======= - | DomainInt IntTag [Range x] ->>>>>>> taggedints - | DomainEnum - Name - (Maybe [Range x]) -- subset of values for this domain - -- Nothing *only* when GivenDomainDefnEnum and not LettingDomainDefnEnum - (Maybe [(Name, Integer)]) -- the mapping to integers, if available - | DomainUnnamed Name x - | DomainTuple [Domain r x] - | DomainRecord [(Name, Domain r x)] - | DomainVariant [(Name, Domain r x)] - | DomainMatrix (Domain () x) (Domain r x) - | DomainSet r (SetAttr x) (Domain r x) - | DomainMSet r (MSetAttr x) (Domain r x) - | DomainFunction r (FunctionAttr x) (Domain r x) (Domain r x) - | DomainSequence r (SequenceAttr x) (Domain r x) - | DomainRelation r (RelationAttr x) [Domain r x] - | DomainPartition r (PartitionAttr x) (Domain r x) - | DomainPermutation r (PermutationAttr x) (Domain r x) - | DomainOp Name [Domain r x] - | DomainReference Name (Maybe (Domain r x)) - | DomainMetaVar String - deriving (Eq, Ord, Show, Data, Functor, Traversable, Foldable, Typeable, Generic) - -instance (VarSymBreakingDescription x, ToJSON r) => VarSymBreakingDescription (Domain r x) where - varSymBreakingDescription domain = toJSON $ fmap varSymBreakingDescription domain - -mkDomainBool :: Domain () x -mkDomainBool = DomainBool - -mkDomainInt :: [Range x] -> Domain () x -<<<<<<< HEAD -<<<<<<< HEAD -mkDomainInt = DomainInt Nothing -||||||| merged common ancestors -mkDomainInt = DomainInt -======= -mkDomainInt = DomainInt NoTag ->>>>>>> taggedints - -mkDomainIntB :: x -> x -> Domain () x -<<<<<<< HEAD -mkDomainIntB l u = DomainInt Nothing [RangeBounded l u] - -mkDomainIntBNamed :: Name -> x -> x -> Domain () x -mkDomainIntBNamed name l u = DomainInt (Just name) [RangeBounded l u] - -======= -mkDomainInt = DomainInt NoTag - -mkDomainIntB :: x -> x -> Domain () x -mkDomainIntB l u = DomainInt NoTag [RangeBounded l u] ->>>>>>> f8c15eb3160b509a17e3d70103b237ea8d666c04 -||||||| merged common ancestors -mkDomainIntB l u = DomainInt [RangeBounded l u] -======= -mkDomainIntB l u = DomainInt NoTag [RangeBounded l u] - -mkDomainIntBTagged :: IntTag -> x -> x -> Domain () x -mkDomainIntBTagged t l u = DomainInt t [RangeBounded l u] ->>>>>>> taggedints - -mkDomainAny :: Doc -> Type -> Domain r x -mkDomainAny reason = DomainAny (stringToText $ show reason) - -instance (Serialize r, Serialize x) => Serialize (Domain r x) -instance (Hashable r, Hashable x) => Hashable (Domain r x) -instance (ToJSON r, ToJSON x) => ToJSON (Domain r x) where toJSON = genericToJSON jsonOptions -instance (FromJSON r, FromJSON x) => FromJSON (Domain r x) where parseJSON = genericParseJSON jsonOptions - -instance Arbitrary x => Arbitrary (Domain r x) where - arbitrary = sized f - where - f 0 = oneof [ return DomainBool -<<<<<<< HEAD -<<<<<<< HEAD - , DomainInt Nothing <$> arbitrary -======= - , DomainInt NoTag <$> arbitrary ->>>>>>> f8c15eb3160b509a17e3d70103b237ea8d666c04 -||||||| merged common ancestors - , DomainInt <$> arbitrary -======= - , DomainInt NoTag <$> arbitrary ->>>>>>> taggedints - -- , DomainEnum <$> arbitrary <*> arbitrary - ] - f s = do - arity <- choose (2 :: Int, 10) - DomainTuple <$> vectorOf arity (f (div s 10)) - shrink DomainBool = [] -<<<<<<< HEAD -<<<<<<< HEAD - shrink (DomainInt Nothing []) = [DomainBool] - shrink (DomainInt Nothing [r]) = DomainBool : DomainInt Nothing [] : [DomainInt Nothing [r'] | r' <- shrink r] - shrink (DomainInt Nothing rs) = [DomainInt Nothing (init rs)] -======= - shrink (DomainInt _ []) = [DomainBool] - shrink (DomainInt t [r]) = DomainBool : DomainInt t [] : [DomainInt t [r'] | r' <- shrink r] - shrink (DomainInt t rs) = [DomainInt t (init rs)] ->>>>>>> f8c15eb3160b509a17e3d70103b237ea8d666c04 -||||||| merged common ancestors - shrink (DomainInt []) = [DomainBool] - shrink (DomainInt [r]) = DomainBool : DomainInt [] : [DomainInt [r'] | r' <- shrink r] - shrink (DomainInt rs) = [DomainInt (init rs)] -======= - shrink (DomainInt _ []) = [DomainBool] - shrink (DomainInt t [r]) = DomainBool : DomainInt t [] : [DomainInt t [r'] | r' <- shrink r] - shrink (DomainInt t rs) = [DomainInt t (init rs)] ->>>>>>> taggedints - shrink _ = [] - -instance (Pretty r, TypeOf x, Pretty x) => TypeOf (Domain r x) where - typeOf = typeOfDomain - -typeOfDomain :: (MonadFail m, Pretty r, TypeOf x, Pretty x) => Domain r x -> m Type -typeOfDomain (DomainAny _ ty) = return ty -typeOfDomain DomainBool = return TypeBool -typeOfDomain d@(DomainIntE name x) = do - ty <- typeOf x - case ty of -<<<<<<< HEAD -<<<<<<< HEAD - TypeInt _ -> return () -- pre recoverDomainInt - TypeList (TypeInt _) -> return () - TypeMatrix _ (TypeInt _) -> return () - TypeSet (TypeInt _) -> return () -||||||| merged common ancestors - TypeInt -> return () -- pre recoverDomainInt - TypeList TypeInt -> return () - TypeMatrix _ TypeInt -> return () - TypeSet TypeInt -> return () -======= - TypeInt{} -> return () -- pre recoverDomainInt - TypeList TypeInt{} -> return () - TypeMatrix _ TypeInt{} -> return () - TypeSet TypeInt{} -> return () ->>>>>>> taggedints - _ -> fail $ vcat [ "Expected an integer, but got:" <++> pretty ty - , "In domain:" <+> pretty d - ] -<<<<<<< HEAD - return $ TypeInt name -typeOfDomain d@(DomainInt name rs) = do -||||||| merged common ancestors - return TypeInt -typeOfDomain d@(DomainInt rs) = do -======= - return (TypeInt NoTag) -typeOfDomain d@(DomainInt t rs) = do ->>>>>>> taggedints - forM_ rs $ \ r -> forM_ r $ \ x -> do - ty <- typeOf x - case ty of -<<<<<<< HEAD - TypeInt _ -> return () -======= - TypeInt{} -> return () -- pre recoverDomainInt - TypeList TypeInt{} -> return () - TypeMatrix _ TypeInt{} -> return () - TypeSet TypeInt{} -> return () - _ -> fail $ vcat [ "Expected an integer, but got:" <++> pretty ty - , "In domain:" <+> pretty d - ] - return (TypeInt NoTag) -typeOfDomain d@(DomainInt t rs) = do - forM_ rs $ \ r -> forM_ r $ \ x -> do - ty <- typeOf x - case ty of - TypeInt{} -> return () ->>>>>>> f8c15eb3160b509a17e3d70103b237ea8d666c04 -||||||| merged common ancestors - TypeInt -> return () -======= - TypeInt{} -> return () ->>>>>>> taggedints - _ -> fail $ vcat [ "Expected an integer, but got:" <++> pretty ty - , "For:" <+> pretty x - , "In domain:" <+> pretty d - ] -<<<<<<< HEAD -<<<<<<< HEAD - return $ TypeInt name -======= - return (TypeInt t) ->>>>>>> f8c15eb3160b509a17e3d70103b237ea8d666c04 -||||||| merged common ancestors - return TypeInt -======= - return (TypeInt t) ->>>>>>> taggedints -typeOfDomain (DomainEnum defn _ _ ) = return (TypeEnum defn) -typeOfDomain (DomainUnnamed defn _ ) = return (TypeUnnamed defn) -typeOfDomain (DomainTuple xs ) = TypeTuple <$> mapM typeOf xs -typeOfDomain (DomainRecord xs ) = TypeRecord <$> sequence [ do t <- typeOf d ; return (n, t) - | (n,d) <- xs ] -typeOfDomain (DomainVariant xs ) = TypeVariant <$> sequence [ do t <- typeOf d ; return (n, t) - | (n,d) <- xs ] -typeOfDomain (DomainMatrix ind inn ) = TypeMatrix <$> typeOf ind <*> typeOf inn -typeOfDomain (DomainSet _ _ x ) = TypeSet <$> typeOf x -typeOfDomain (DomainMSet _ _ x ) = TypeMSet <$> typeOf x -typeOfDomain (DomainFunction _ _ x y) = TypeFunction <$> typeOf x <*> typeOf y -typeOfDomain (DomainSequence _ _ x ) = TypeSequence <$> typeOf x -typeOfDomain (DomainRelation _ _ xs ) = TypeRelation <$> mapM typeOf xs -typeOfDomain (DomainPartition _ _ x ) = TypePartition <$> typeOf x -typeOfDomain (DomainPermutation _ _ x ) = TypePermutation <$> typeOf x -typeOfDomain p@(DomainOp _ ds) = do - ts <- mapM typeOfDomain ds - if typesUnify ts - then return (mostDefined ts) - else fail ("Type error in" <+> pretty p) -typeOfDomain (DomainReference _ (Just d)) = typeOf d -typeOfDomain (DomainReference nm Nothing) = bug $ "typeOf: DomainReference" <+> pretty nm -typeOfDomain (DomainMetaVar nm) = bug $ "typeOf: DomainMetaVar &" <> pretty nm - -forgetRepr :: Domain r x -> Domain () x -forgetRepr = defRepr - -defRepr :: Default r2 => Domain r x -> Domain r2 x -defRepr = changeRepr def - -changeRepr :: r2 -> Domain r x -> Domain r2 x -changeRepr rep = go - where - go (DomainAny t ty) = DomainAny t ty - go DomainBool = DomainBool -<<<<<<< HEAD - go (DomainIntE name x) = DomainIntE name x - go (DomainInt name rs) = DomainInt name rs -======= - go (DomainIntE x) = DomainIntE x -<<<<<<< HEAD - go (DomainInt t rs) = DomainInt t rs ->>>>>>> f8c15eb3160b509a17e3d70103b237ea8d666c04 -||||||| merged common ancestors - go (DomainInt rs) = DomainInt rs -======= - go (DomainInt t rs) = DomainInt t rs ->>>>>>> taggedints - go (DomainEnum defn rs mp) = DomainEnum defn rs mp - go (DomainUnnamed defn s) = DomainUnnamed defn s - go (DomainTuple ds) = DomainTuple (map go ds) - go (DomainRecord xs) = DomainRecord (map (second go) xs) - go (DomainVariant xs) = DomainVariant (map (second go) xs) - go (DomainMatrix index inner) = DomainMatrix index (go inner) - go (DomainSet _ attr d) = - DomainSet rep attr (go d) - go (DomainMSet _ attr d) = - DomainMSet rep attr (go d) - go (DomainFunction _ attr d1 d2) = - DomainFunction rep attr (go d1) (go d2) - go (DomainSequence _ attr d) = - DomainSequence rep attr (go d) - go (DomainRelation _ attr ds) = - DomainRelation rep attr (map go ds) - go (DomainPartition _ attr d) = DomainPartition rep attr (go d) - go (DomainPermutation _ attr d) = DomainPermutation rep attr (go d) - go (DomainOp op ds) = DomainOp op (map go ds) - go (DomainReference x r) = DomainReference x (fmap go r) - go (DomainMetaVar x) = DomainMetaVar x - - -data Tree a = Tree { rootLabel :: a, subForest :: [Tree a] } - deriving (Eq, Ord, Show, Data, Functor, Traversable, Foldable, Typeable, Generic) - -instance Serialize a => Serialize (Tree a) -instance Hashable a => Hashable (Tree a) -instance ToJSON a => ToJSON (Tree a) where toJSON = genericToJSON jsonOptions -instance FromJSON a => FromJSON (Tree a) where parseJSON = genericParseJSON jsonOptions - --- | This is to be used when defining `Conjure.Representations.Internal.mkOutName`. --- Reason is to avoid sharing variables for parts of the same decision variable with differing representations. --- Example case: --- (1) find x : set {A} of (int(a..b) , set {B} of int(c..d)) --- (2) find x : set {A} of (int(a..b) , set {C} of int(c..d)) --- Here x_1's should not be shared! --- If they are, the channelling and symmetry breaking constraints will clash and solutions will be lost. -reprTreeEncoded :: Domain HasRepresentation x -> Text -reprTreeEncoded = mconcat . enc1 . reprTree - where - enc1 (Tree lbl sub) = - maybe - (bug "reprTreeEncoded: top-most representation is Nothing") - representationToShortText - lbl - : concatMap enc sub - enc (Tree lbl sub) = - maybe [] representationConstrIndex lbl - ++ concatMap enc sub - -reprTree :: Domain r x -> Tree (Maybe r) -reprTree DomainAny{} = Tree Nothing [] -reprTree DomainBool{} = Tree Nothing [] -reprTree DomainIntE{} = Tree Nothing [] -reprTree DomainInt{} = Tree Nothing [] -reprTree DomainEnum{} = Tree Nothing [] -reprTree DomainUnnamed{} = Tree Nothing [] -reprTree (DomainTuple as ) = Tree Nothing (map reprTree as) -reprTree (DomainRecord as ) = Tree Nothing (map (reprTree . snd) as) -reprTree (DomainVariant as) = Tree Nothing (map (reprTree . snd) as) -reprTree (DomainMatrix _ a) = Tree Nothing [reprTree a] -reprTree (DomainSet r _ a ) = Tree (Just r) [reprTree a] -reprTree (DomainMSet r _ a ) = Tree (Just r) [reprTree a] -reprTree (DomainFunction r _ a b) = Tree (Just r) [reprTree a, reprTree b] -reprTree (DomainSequence r _ a ) = Tree (Just r) [reprTree a] -reprTree (DomainRelation r _ as ) = Tree (Just r) (map reprTree as) -reprTree (DomainPartition r _ a ) = Tree (Just r) [reprTree a] -reprTree (DomainPermutation r _ a) = Tree (Just r) [reprTree a] -reprTree DomainOp{} = Tree Nothing [] -reprTree DomainReference{} = Tree Nothing [] -reprTree DomainMetaVar{} = Tree Nothing [] - -reprAtTopLevel :: Domain r x -> Maybe r -reprAtTopLevel = rootLabel . reprTree - -applyReprTree :: (MonadFail m, Pretty x, Pretty r2, Default r) => Domain r2 x -> Tree (Maybe r) -> m (Domain r x) -applyReprTree dom@DomainBool{} (Tree Nothing []) = return (defRepr dom) -applyReprTree dom@DomainInt{} (Tree Nothing []) = return (defRepr dom) -applyReprTree dom@DomainEnum{} (Tree Nothing []) = return (defRepr dom) -applyReprTree dom@DomainUnnamed{} (Tree Nothing []) = return (defRepr dom) -applyReprTree (DomainTuple as ) (Tree Nothing asRepr) = - DomainTuple <$> zipWithM applyReprTree as asRepr -applyReprTree (DomainRecord as ) (Tree Nothing asRepr) = - (DomainRecord . zip (map fst as)) <$> zipWithM applyReprTree (map snd as) asRepr -applyReprTree (DomainVariant as) (Tree Nothing asRepr) = - (DomainVariant . zip (map fst as)) <$> zipWithM applyReprTree (map snd as) asRepr -applyReprTree (DomainMatrix b a) (Tree Nothing [aRepr]) = DomainMatrix b <$> applyReprTree a aRepr -applyReprTree (DomainSet _ attr a ) (Tree (Just r) [aRepr]) = DomainSet r attr <$> applyReprTree a aRepr -applyReprTree (DomainMSet _ attr a ) (Tree (Just r) [aRepr]) = DomainMSet r attr <$> applyReprTree a aRepr -applyReprTree (DomainFunction _ attr a b) (Tree (Just r) [aRepr, bRepr]) = DomainFunction r attr <$> applyReprTree a aRepr <*> applyReprTree b bRepr -applyReprTree (DomainSequence _ attr a ) (Tree (Just r) [aRepr]) = DomainSequence r attr <$> applyReprTree a aRepr -applyReprTree (DomainRelation _ attr as ) (Tree (Just r) asRepr) = DomainRelation r attr <$> zipWithM applyReprTree as asRepr -applyReprTree (DomainPartition _ attr a ) (Tree (Just r) [aRepr]) = DomainPartition r attr <$> applyReprTree a aRepr -applyReprTree (DomainPermutation _ attr a ) (Tree (Just r) [aRepr]) = DomainPermutation r attr <$> applyReprTree a aRepr -applyReprTree dom@DomainOp{} (Tree Nothing []) = return (defRepr dom) -applyReprTree dom@DomainReference{} (Tree Nothing []) = return (defRepr dom) -applyReprTree dom@DomainMetaVar{} (Tree Nothing []) = return (defRepr dom) -applyReprTree dom _ = fail $ "applyReprTree:" <++> pretty dom - -isPrimitiveDomain :: Domain r x -> Bool -isPrimitiveDomain DomainBool{} = True -isPrimitiveDomain DomainIntE{} = True -isPrimitiveDomain DomainInt{} = True -isPrimitiveDomain (DomainMatrix index inner) = and [isPrimitiveDomain index, isPrimitiveDomain inner] -isPrimitiveDomain _ = False - -getIndices :: Domain r x -> ([Domain () x], Domain r x) -getIndices (DomainMatrix index inner) = first (index:) (getIndices inner) -getIndices d = ([], d) - -domainCanIndexMatrix :: Domain r x -> Bool -domainCanIndexMatrix DomainBool{} = True -domainCanIndexMatrix DomainInt {} = True -domainCanIndexMatrix DomainIntE{} = True -domainCanIndexMatrix DomainEnum{} = True -domainCanIndexMatrix _ = False - - --------------------------------------------------------------------------------- --- attribute-as-constraint handling -------------------------------------------- --------------------------------------------------------------------------------- - -data AttrName - = AttrName_size - | AttrName_minSize - | AttrName_maxSize - | AttrName_minOccur - | AttrName_maxOccur - | AttrName_numParts - | AttrName_minNumParts - | AttrName_maxNumParts - | AttrName_partSize - | AttrName_minPartSize - | AttrName_maxPartSize - | AttrName_total - | AttrName_injective - | AttrName_surjective - | AttrName_bijective - | AttrName_regular - -- bin rel ones - | AttrName_reflexive - | AttrName_irreflexive - | AttrName_coreflexive - | AttrName_symmetric - | AttrName_antiSymmetric - | AttrName_aSymmetric - | AttrName_transitive - | AttrName_connex - | AttrName_Euclidean - | AttrName_serial - | AttrName_equivalence - | AttrName_partialOrder - deriving (Eq, Ord, Show, Data, Typeable, Generic) - -instance Serialize AttrName -instance Hashable AttrName -instance ToJSON AttrName where toJSON = genericToJSON jsonOptions -instance FromJSON AttrName where parseJSON = genericParseJSON jsonOptions - -instance Pretty AttrName where - pretty AttrName_size = "size" - pretty AttrName_minSize = "minSize" - pretty AttrName_maxSize = "maxSize" - pretty AttrName_minOccur = "minOccur" - pretty AttrName_maxOccur = "maxOccur" - pretty AttrName_numParts = "numParts" - pretty AttrName_minNumParts = "minNumParts" - pretty AttrName_maxNumParts = "maxNumParts" - pretty AttrName_partSize = "partSize" - pretty AttrName_minPartSize = "minPartSize" - pretty AttrName_maxPartSize = "maxPartSize" - pretty AttrName_total = "total" - pretty AttrName_injective = "injective" - pretty AttrName_surjective = "surjective" - pretty AttrName_bijective = "bijective" - pretty AttrName_regular = "regular" - pretty AttrName_reflexive = "reflexive" - pretty AttrName_irreflexive = "irreflexive" - pretty AttrName_coreflexive = "coreflexive" - pretty AttrName_symmetric = "symmetric" - pretty AttrName_antiSymmetric = "antiSymmetric" - pretty AttrName_aSymmetric = "aSymmetric" - pretty AttrName_transitive = "transitive" - pretty AttrName_connex = "connex" - pretty AttrName_Euclidean = "Euclidean" - pretty AttrName_serial = "serial" - pretty AttrName_equivalence = "equivalence" - pretty AttrName_partialOrder = "partialOrder" - -instance IsString AttrName where - fromString "size" = AttrName_size - fromString "minSize" = AttrName_minSize - fromString "maxSize" = AttrName_maxSize - fromString "minOccur" = AttrName_minOccur - fromString "maxOccur" = AttrName_maxOccur - fromString "numParts" = AttrName_numParts - fromString "minNumParts" = AttrName_minNumParts - fromString "maxNumParts" = AttrName_maxNumParts - fromString "partSize" = AttrName_partSize - fromString "minPartSize" = AttrName_minPartSize - fromString "maxPartSize" = AttrName_maxPartSize - fromString "total" = AttrName_total - fromString "injective" = AttrName_injective - fromString "surjective" = AttrName_surjective - fromString "bijective" = AttrName_bijective - fromString "regular" = AttrName_regular - fromString "reflexive" = AttrName_reflexive - fromString "irreflexive" = AttrName_irreflexive - fromString "coreflexive" = AttrName_coreflexive - fromString "symmetric" = AttrName_symmetric - fromString "antiSymmetric" = AttrName_antiSymmetric - fromString "aSymmetric" = AttrName_aSymmetric - fromString "transitive" = AttrName_transitive - fromString "connex" = AttrName_connex - fromString "Euclidean" = AttrName_Euclidean - fromString "serial" = AttrName_serial - fromString "equivalence" = AttrName_equivalence - fromString "partialOrder" = AttrName_partialOrder - fromString s = bug $ "fromString{AttrName}:" <+> pretty s - - --------------------------------------------------------------------------------- --- attribute definitions ------------------------------------------------------- --------------------------------------------------------------------------------- - -data SetAttr a = SetAttr (SizeAttr a) - deriving (Eq, Ord, Show, Data, Functor, Traversable, Foldable, Typeable, Generic) -instance Serialize a => Serialize (SetAttr a) -instance Hashable a => Hashable (SetAttr a) -instance ToJSON a => ToJSON (SetAttr a) where toJSON = genericToJSON jsonOptions -instance FromJSON a => FromJSON (SetAttr a) where parseJSON = genericParseJSON jsonOptions -instance Default (SetAttr a) where def = SetAttr def -instance Pretty a => Pretty (SetAttr a) where - pretty (SetAttr SizeAttr_None) = prEmpty - pretty (SetAttr a) = prParens (pretty a) - - -data SizeAttr a - = SizeAttr_None - | SizeAttr_Size a - | SizeAttr_MinSize a - | SizeAttr_MaxSize a - | SizeAttr_MinMaxSize a a - deriving (Eq, Ord, Show, Data, Functor, Traversable, Foldable, Typeable, Generic) -instance Serialize a => Serialize (SizeAttr a) -instance Hashable a => Hashable (SizeAttr a) -instance ToJSON a => ToJSON (SizeAttr a) where toJSON = genericToJSON jsonOptions -instance FromJSON a => FromJSON (SizeAttr a) where parseJSON = genericParseJSON jsonOptions -instance Default (SizeAttr a) where def = SizeAttr_None -instance Pretty a => Pretty (SizeAttr a) where - pretty SizeAttr_None = prEmpty - pretty (SizeAttr_Size x ) = "size" <+> pretty x - pretty (SizeAttr_MinSize x ) = "minSize" <+> pretty x - pretty (SizeAttr_MaxSize x ) = "maxSize" <+> pretty x - pretty (SizeAttr_MinMaxSize x y) = "minSize" <+> pretty x <> ", maxSize" <+> pretty y - - -getMaxFrom_SizeAttr :: MonadFail m => SizeAttr a -> m a -getMaxFrom_SizeAttr (SizeAttr_Size n) = return n -getMaxFrom_SizeAttr (SizeAttr_MaxSize n) = return n -getMaxFrom_SizeAttr (SizeAttr_MinMaxSize _ n) = return n -getMaxFrom_SizeAttr _ = fail "getMaxFrom_SizeAttr" - - -data MSetAttr a = MSetAttr (SizeAttr a) (OccurAttr a) - deriving (Eq, Ord, Show, Data, Functor, Traversable, Foldable, Typeable, Generic) -instance Serialize a => Serialize (MSetAttr a) -instance Hashable a => Hashable (MSetAttr a) -instance ToJSON a => ToJSON (MSetAttr a) where toJSON = genericToJSON jsonOptions -instance FromJSON a => FromJSON (MSetAttr a) where parseJSON = genericParseJSON jsonOptions -instance Default (MSetAttr a) where def = MSetAttr def def -instance Pretty a => Pretty (MSetAttr a) where - pretty (MSetAttr a b) = - let inside = filter (/=prEmpty) [ pretty a - , pretty b - ] - in if null inside - then prEmpty - else prettyList prParens "," inside - - -data OccurAttr a - = OccurAttr_None - | OccurAttr_MinOccur a - | OccurAttr_MaxOccur a - | OccurAttr_MinMaxOccur a a - deriving (Eq, Ord, Show, Data, Functor, Traversable, Foldable, Typeable, Generic) -instance Serialize a => Serialize (OccurAttr a) -instance Hashable a => Hashable (OccurAttr a) -instance ToJSON a => ToJSON (OccurAttr a) where toJSON = genericToJSON jsonOptions -instance FromJSON a => FromJSON (OccurAttr a) where parseJSON = genericParseJSON jsonOptions -instance Default (OccurAttr a) where def = OccurAttr_None -instance Pretty a => Pretty (OccurAttr a) where - pretty OccurAttr_None = prEmpty - pretty (OccurAttr_MinOccur x ) = "minOccur" <+> pretty x - pretty (OccurAttr_MaxOccur x ) = "maxOccur" <+> pretty x - pretty (OccurAttr_MinMaxOccur x y) = "minOccur" <+> pretty x <> ", maxOccur" <+> pretty y - - -getMaxFrom_OccurAttr :: MonadFail m => OccurAttr a -> m a -getMaxFrom_OccurAttr (OccurAttr_MaxOccur n) = return n -getMaxFrom_OccurAttr (OccurAttr_MinMaxOccur _ n) = return n -getMaxFrom_OccurAttr _ = fail "getMaxFrom_OccurAttr" - - -data FunctionAttr x - = FunctionAttr (SizeAttr x) PartialityAttr JectivityAttr - deriving (Eq, Ord, Show, Data, Functor, Traversable, Foldable, Typeable, Generic) -instance Serialize a => Serialize (FunctionAttr a) -instance Hashable a => Hashable (FunctionAttr a) -instance ToJSON a => ToJSON (FunctionAttr a) where toJSON = genericToJSON jsonOptions -instance FromJSON a => FromJSON (FunctionAttr a) where parseJSON = genericParseJSON jsonOptions -instance Default (FunctionAttr a) where def = FunctionAttr def def def -instance Pretty a => Pretty (FunctionAttr a) where - pretty (FunctionAttr a b c) = - let inside = filter (/=prEmpty) [pretty a, pretty b, pretty c] - in if null inside - then prEmpty - else prettyList prParens "," inside - - -data PartialityAttr - = PartialityAttr_Partial - | PartialityAttr_Total - deriving (Eq, Ord, Show, Data, Typeable, Generic) -instance Serialize PartialityAttr -instance Hashable PartialityAttr -instance ToJSON PartialityAttr where toJSON = genericToJSON jsonOptions -instance FromJSON PartialityAttr where parseJSON = genericParseJSON jsonOptions -instance Default PartialityAttr where def = PartialityAttr_Partial -instance Pretty PartialityAttr where - pretty PartialityAttr_Partial = prEmpty -- partial is the default - pretty PartialityAttr_Total = "total" - - -data JectivityAttr - = JectivityAttr_None - | JectivityAttr_Injective - | JectivityAttr_Surjective - | JectivityAttr_Bijective - deriving (Eq, Ord, Show, Data, Typeable, Generic) -instance Serialize JectivityAttr -instance Hashable JectivityAttr -instance ToJSON JectivityAttr where toJSON = genericToJSON jsonOptions -instance FromJSON JectivityAttr where parseJSON = genericParseJSON jsonOptions -instance Default JectivityAttr where def = JectivityAttr_None -instance Pretty JectivityAttr where - pretty JectivityAttr_None = prEmpty - pretty JectivityAttr_Injective = "injective" - pretty JectivityAttr_Surjective = "surjective" - pretty JectivityAttr_Bijective = "bijective" - - -data SequenceAttr x - = SequenceAttr (SizeAttr x) JectivityAttr - deriving (Eq, Ord, Show, Data, Functor, Traversable, Foldable, Typeable, Generic) -instance Serialize a => Serialize (SequenceAttr a) -instance Hashable a => Hashable (SequenceAttr a) -instance ToJSON a => ToJSON (SequenceAttr a) where toJSON = genericToJSON jsonOptions -instance FromJSON a => FromJSON (SequenceAttr a) where parseJSON = genericParseJSON jsonOptions -instance Default (SequenceAttr a) where def = SequenceAttr def def -instance Pretty a => Pretty (SequenceAttr a) where - pretty (SequenceAttr a b) = - let inside = filter (/=prEmpty) [pretty a, pretty b] - in if null inside - then prEmpty - else prettyList prParens "," inside - - -data RelationAttr a = RelationAttr (SizeAttr a) BinaryRelationAttrs - deriving (Eq, Ord, Show, Data, Functor, Traversable, Foldable, Typeable, Generic) -instance Serialize a => Serialize (RelationAttr a) -instance Hashable a => Hashable (RelationAttr a) -instance ToJSON a => ToJSON (RelationAttr a) where toJSON = genericToJSON jsonOptions -instance FromJSON a => FromJSON (RelationAttr a) where parseJSON = genericParseJSON jsonOptions -instance Default (RelationAttr a) where def = RelationAttr def def -instance Pretty a => Pretty (RelationAttr a) where - pretty (RelationAttr a b) = - let inside = filter (/=prEmpty) [pretty a, pretty b] - in if null inside - then prEmpty - else prettyList prParens "," inside - - -data BinaryRelationAttrs = BinaryRelationAttrs (S.Set BinaryRelationAttr) - deriving (Eq, Ord, Show, Data, Typeable, Generic) -instance Serialize BinaryRelationAttrs -instance Hashable BinaryRelationAttrs where hashWithSalt salt (BinaryRelationAttrs a) = hashWithSalt salt (S.toList a) -instance ToJSON BinaryRelationAttrs where toJSON = genericToJSON jsonOptions -instance FromJSON BinaryRelationAttrs where parseJSON = genericParseJSON jsonOptions -instance Default BinaryRelationAttrs where def = BinaryRelationAttrs S.empty -instance Pretty BinaryRelationAttrs where - pretty (BinaryRelationAttrs attrs) = prettyList id "," (S.toList attrs) -instance Semigroup BinaryRelationAttrs where - (<>) = mappend -instance Monoid BinaryRelationAttrs where - mempty = BinaryRelationAttrs def - mappend (BinaryRelationAttrs a) (BinaryRelationAttrs b) = BinaryRelationAttrs (S.union a b) - - -data BinaryRelationAttr - = BinRelAttr_Reflexive - | BinRelAttr_Irreflexive - | BinRelAttr_Coreflexive - | BinRelAttr_Symmetric - | BinRelAttr_AntiSymmetric - | BinRelAttr_ASymmetric - | BinRelAttr_Transitive - | BinRelAttr_Total - | BinRelAttr_Connex - | BinRelAttr_Euclidean - | BinRelAttr_Serial - | BinRelAttr_Equivalence - | BinRelAttr_PartialOrder - deriving (Eq, Ord, Show, Data, Typeable, Generic) -instance Serialize BinaryRelationAttr -instance Hashable BinaryRelationAttr -instance ToJSON BinaryRelationAttr where toJSON = genericToJSON jsonOptions -instance FromJSON BinaryRelationAttr where parseJSON = genericParseJSON jsonOptions -instance Pretty BinaryRelationAttr where - pretty BinRelAttr_Reflexive = "reflexive" - pretty BinRelAttr_Irreflexive = "irreflexive" - pretty BinRelAttr_Coreflexive = "coreflexive" - pretty BinRelAttr_Symmetric = "symmetric" - pretty BinRelAttr_AntiSymmetric = "antiSymmetric" - pretty BinRelAttr_ASymmetric = "aSymmetric" - pretty BinRelAttr_Transitive = "transitive" - pretty BinRelAttr_Total = "total" - pretty BinRelAttr_Connex = "connex" - pretty BinRelAttr_Euclidean = "Euclidean" - pretty BinRelAttr_Serial = "serial" - pretty BinRelAttr_Equivalence = "equivalence" - pretty BinRelAttr_PartialOrder = "partialOrder" - -readBinRel :: MonadFail m => AttrName -> m BinaryRelationAttr -readBinRel AttrName_reflexive = return BinRelAttr_Reflexive -readBinRel AttrName_irreflexive = return BinRelAttr_Irreflexive -readBinRel AttrName_coreflexive = return BinRelAttr_Coreflexive -readBinRel AttrName_symmetric = return BinRelAttr_Symmetric -readBinRel AttrName_antiSymmetric = return BinRelAttr_AntiSymmetric -readBinRel AttrName_aSymmetric = return BinRelAttr_ASymmetric -readBinRel AttrName_transitive = return BinRelAttr_Transitive -readBinRel AttrName_total = return BinRelAttr_Total -readBinRel AttrName_connex = return BinRelAttr_Connex -readBinRel AttrName_Euclidean = return BinRelAttr_Euclidean -readBinRel AttrName_serial = return BinRelAttr_Serial -readBinRel AttrName_equivalence = return BinRelAttr_Equivalence -readBinRel AttrName_partialOrder = return BinRelAttr_PartialOrder -readBinRel a = fail $ "Not a binary relation attribute:" <+> pretty a - --- reflexive forAll x : T . rel(x,x) --- irreflexive forAll x : T . !rel(x,x) --- coreflexive forAll x,y : T . rel(x,y) -> x = y --- --- symmetric forAll x,y : T . rel(x,y) -> rel(y,x) --- antisymmetric forAll x,y : T . rel(x,y) /\ rel(y,x) -> x = y --- asymmetric forAll x,y : T . rel(x,y) -> !rel(y,x) --- --- transitive forAll x,y,z : T . rel(x,y) /\ rel(y,z) -> rel(x,z) --- --- total forAll x,y : T . rel(x,y) \/ rel(y,x) --- connex forAll x,y : T . rel(x,y) \/ rel(y,x) \/ x = y --- Euclidean forAll x,y,z : T . rel(x,y) /\ rel(x,z) -> rel(y,z) --- serial forAll x : T . exists y : T . rel(x,y) --- equivalence reflexive + symmetric + transitive --- partialOrder reflexive + antisymmetric + transitive - - -data PartitionAttr a = PartitionAttr - { partsNum :: SizeAttr a - , partsSize :: SizeAttr a - , isRegular :: Bool - } - deriving (Eq, Ord, Show, Data, Functor, Traversable, Foldable, Typeable, Generic) -instance Serialize a => Serialize (PartitionAttr a) -instance Hashable a => Hashable (PartitionAttr a) -instance ToJSON a => ToJSON (PartitionAttr a) where toJSON = genericToJSON jsonOptions -instance FromJSON a => FromJSON (PartitionAttr a) where parseJSON = genericParseJSON jsonOptions -instance Default (PartitionAttr a) where def = PartitionAttr def def False -instance Pretty a => Pretty (PartitionAttr a) where - pretty (PartitionAttr a b c) = - let inside = filter (/=prEmpty) [ prettyNum a - , prettySize b - , prettyReg c - ] - - prettyNum SizeAttr_None = prEmpty - prettyNum (SizeAttr_Size x ) = "numParts" <+> pretty x - prettyNum (SizeAttr_MinSize x ) = "minNumParts" <+> pretty x - prettyNum (SizeAttr_MaxSize x ) = "maxNumParts" <+> pretty x - prettyNum (SizeAttr_MinMaxSize x y) = "minNumParts" <+> pretty x <> ", maxNumParts" <+> pretty y - - prettySize SizeAttr_None = prEmpty - prettySize (SizeAttr_Size x ) = "partSize" <+> pretty x - prettySize (SizeAttr_MinSize x ) = "minPartSize" <+> pretty x - prettySize (SizeAttr_MaxSize x ) = "maxPartSize" <+> pretty x - prettySize (SizeAttr_MinMaxSize x y) = "minPartSize" <+> pretty x <> ", maxPartSize" <+> pretty y - - prettyReg False = prEmpty - prettyReg True = "regular" - - in if null inside - then prEmpty - else prettyList prParens "," inside - - - -data PermutationAttr x - = PermutationAttr (SizeAttr x) - deriving (Eq, Ord, Show, Data, Functor, Traversable, Foldable, Typeable, Generic) -instance Serialize a => Serialize (PermutationAttr a) -instance Hashable a => Hashable (PermutationAttr a) -instance ToJSON a => ToJSON (PermutationAttr a) where toJSON = genericToJSON jsonOptions -instance FromJSON a => FromJSON (PermutationAttr a) where parseJSON = genericParseJSON jsonOptions -instance Default (PermutationAttr a) where def = PermutationAttr def -instance Pretty a => Pretty (PermutationAttr a) where - pretty (PermutationAttr a ) = - let inside = filter (/=prEmpty) [pretty a] - in if null inside - then prEmpty - else prettyList prParens "," inside - - - - -data DomainAttributes a = DomainAttributes [DomainAttribute a] - deriving (Eq, Ord, Show, Data, Functor, Traversable, Foldable, Typeable, Generic) - -instance Serialize a => Serialize (DomainAttributes a) -instance Hashable a => Hashable (DomainAttributes a) -instance ToJSON a => ToJSON (DomainAttributes a) where toJSON = genericToJSON jsonOptions -instance FromJSON a => FromJSON (DomainAttributes a) where parseJSON = genericParseJSON jsonOptions - -instance Default (DomainAttributes a) where - def = DomainAttributes [] - - -data DomainAttribute a - = DAName Name - | DANameValue Name a - | DADotDot - deriving (Eq, Ord, Show, Data, Functor, Traversable, Foldable, Typeable, Generic) - -instance Serialize a => Serialize (DomainAttribute a) -instance Hashable a => Hashable (DomainAttribute a) -instance ToJSON a => ToJSON (DomainAttribute a) where toJSON = genericToJSON jsonOptions -instance FromJSON a => FromJSON (DomainAttribute a) where parseJSON = genericParseJSON jsonOptions - - -data Range a - = RangeOpen - | RangeSingle a - | RangeLowerBounded a - | RangeUpperBounded a - | RangeBounded a a - deriving (Eq, Ord, Show, Data, Functor, Traversable, Foldable, Typeable, Generic) - -instance Serialize a => Serialize (Range a) -instance Hashable a => Hashable (Range a) -instance ToJSON a => ToJSON (Range a) where toJSON = genericToJSON jsonOptions -instance FromJSON a => FromJSON (Range a) where parseJSON = genericParseJSON jsonOptions - -instance Arbitrary a => Arbitrary (Range a) where - arbitrary = oneof - [ return RangeOpen - , RangeSingle <$> arbitrary - , RangeLowerBounded <$> arbitrary - , RangeUpperBounded <$> arbitrary - , RangeBounded <$> arbitrary <*> arbitrary - ] - -rangesInts :: (MonadFail m, ExpressionLike c) => [Range c] -> m [Integer] -rangesInts = fmap (sortNub . concat) . mapM rangeInts - where - rangeInts (RangeSingle x) = return <$> intOut "rangeInts 1" x - rangeInts (RangeBounded x y) = do x' <- intOut "rangeInts 2" x - y' <- intOut "rangeInts 3" y - return [x' .. y'] - rangeInts _ = fail "Infinite range (or not an integer range)" - -expandRanges :: ExpressionLike c => [Range c] -> [Range c] -expandRanges r = - case rangesInts r of - Nothing -> r - Just [] -> [] - Just is -> - if [ minimum is .. maximum is ] == is - then [RangeBounded (fromInt (minimum is)) (fromInt (maximum is))] - else map (RangeSingle . fromInt) is - - -data HasRepresentation - = NoRepresentation - - | Set_Occurrence - | Set_Explicit - | Set_ExplicitVarSizeWithFlags - | Set_ExplicitVarSizeWithMarker - | Set_ExplicitVarSizeWithDummy - - | MSet_ExplicitWithFlags - | MSet_ExplicitWithRepetition - - | Function_1D - | Function_1DPartial - | Function_ND - | Function_NDPartial - | Function_AsRelation HasRepresentation -- carries: representation for the inner relation - - | Sequence_ExplicitBounded - - | Relation_AsMatrix - | Relation_AsSet HasRepresentation -- carries: representation for the inner set - - | Partition_AsSet HasRepresentation HasRepresentation -- carries: representations for the inner sets - | Partition_Occurrence - | Permutation_AsFunction - - deriving (Eq, Ord, Show, Data, Typeable, Generic) - -instance Serialize HasRepresentation -instance Hashable HasRepresentation -instance ToJSON HasRepresentation where toJSON = genericToJSON jsonOptions -instance FromJSON HasRepresentation where parseJSON = genericParseJSON jsonOptions - -instance Default HasRepresentation where - def = NoRepresentation - -representationConstrIndex :: HasRepresentation -> [Text] -representationConstrIndex r = oneLevel r : concatMap representationConstrIndex (children r) - where - oneLevel :: HasRepresentation -> Text - oneLevel = stringToText . ("R"++) . show . constrIndex . toConstr - -instance (Pretty r, Pretty a) => Pretty (Domain r a) where - - pretty DomainAny{} = "?" - - pretty DomainBool = "bool" - - pretty (DomainIntE _ x) = "int" <> prParens (pretty x) - - pretty (DomainInt _ []) = "int" - - pretty (DomainInt _ ranges) = "int" <> prettyList prParens "," ranges - -<<<<<<< HEAD -<<<<<<< HEAD -======= - pretty (DomainInt _ []) = "int" - pretty (DomainInt _ ranges) = "int" <> prettyList prParens "," ranges ->>>>>>> f8c15eb3160b509a17e3d70103b237ea8d666c04 -||||||| merged common ancestors - pretty (DomainInt []) = "int" - pretty (DomainInt ranges) = "int" <> prettyList prParens "," ranges -======= - pretty (DomainInt _ []) = "int" - pretty (DomainInt _ ranges) = "int" <> prettyList prParens "," ranges ->>>>>>> taggedints - - pretty (DomainEnum name (Just ranges) _) = pretty name <> prettyList prParens "," ranges - pretty (DomainEnum name _ _) = pretty name - - pretty (DomainUnnamed name _) = pretty name - - pretty (DomainTuple inners) - = (if length inners < 2 then "tuple" else prEmpty) - <+> prettyList prParens "," inners - - pretty (DomainRecord xs) = "record" <+> prettyList prBraces "," - [ pretty nm <+> ":" <+> pretty d | (nm, d) <- xs ] - - pretty (DomainVariant xs) = "variant" <+> prettyList prBraces "," - [ pretty nm <+> ":" <+> pretty d | (nm, d) <- xs ] - - pretty (DomainMatrix index innerNested) - = "matrix indexed by" <+> prettyList prBrackets "," indices - <+> "of" <+> pretty inner - where - (indices,inner) = first (index:) $ collect innerNested - collect (DomainMatrix i j) = first (i:) $ collect j - collect x = ([],x) - - pretty (DomainSet r attrs inner) = - hang ("set" <+> prettyAttrs r attrs <+> "of") 4 (pretty inner) - - pretty (DomainMSet r attrs inner) = - hang ("mset" <+> prettyAttrs r attrs <+> "of") 4 (pretty inner) - - pretty (DomainFunction r attrs innerFrom innerTo) = - hang ("function" <+> prettyAttrs r attrs) 4 $ - hang (pretty innerFrom) 4 $ - "-->" <+> pretty innerTo - - pretty (DomainSequence r attrs inner) = - hang ("sequence" <+> prettyAttrs r attrs <+> "of") 4 (pretty inner) - - pretty (DomainRelation r attrs inners) - = hang ("relation" <+> prettyAttrs r attrs <+> "of") 4 (prettyList prParens " *" inners) - - pretty (DomainPartition r attrs inner) - = hang ("partition" <+> prettyAttrs r attrs <+> "from") 4 (pretty inner) - pretty (DomainPermutation r attrs inner) = hang ("permutation" <+> prettyAttrs r attrs <+> "of") 4 (pretty inner) - - pretty d@DomainOp{} = pretty (show d) - - pretty (DomainReference x _) = pretty x - - pretty (DomainMetaVar x) = "&" <> pretty x - - -prettyAttrs :: (Pretty a, Pretty b) => a -> b -> Doc -prettyAttrs a bs = - let prettya = pretty a - in if prettya == "()" - then pretty bs - else prBraces prettya <+> pretty bs - -instance Pretty a => Pretty (DomainAttributes a) where - pretty (DomainAttributes []) = prEmpty - pretty (DomainAttributes attrs) = prettyList prParens "," attrs - -instance Pretty a => Pretty (DomainAttribute a) where - pretty (DAName name) = pretty name - pretty (DANameValue name value) = pretty name <+> pretty value - pretty DADotDot = ".." - -instance Pretty a => Pretty (Range a) where - pretty RangeOpen = ".." - pretty (RangeSingle x) = pretty x - pretty (RangeLowerBounded x) = pretty x <> ".." - pretty (RangeUpperBounded x) = ".." <> pretty x - pretty (RangeBounded x y) | show x == show y = pretty x - pretty (RangeBounded x y) = pretty x <> ".." <> pretty y - -instance Pretty HasRepresentation where - pretty NoRepresentation = "∅" - pretty r = pretty (representationToFullText r) - -textToRepresentation :: Text -> [HasRepresentation] -> Maybe HasRepresentation -textToRepresentation t [] | t == "Occurrence" = return Set_Occurrence -textToRepresentation t [] | t == "Explicit" = return Set_Explicit -textToRepresentation t [] | t == "ExplicitVarSizeWithFlags" = return Set_ExplicitVarSizeWithFlags -textToRepresentation t [] | t == "ExplicitVarSizeWithMarker" = return Set_ExplicitVarSizeWithMarker -textToRepresentation t [] | t == "ExplicitVarSizeWithDummy" = return Set_ExplicitVarSizeWithDummy -textToRepresentation t [] | t == "ExplicitWithFlags" = return MSet_ExplicitWithFlags -textToRepresentation t [] | t == "ExplicitWithRepetition" = return MSet_ExplicitWithRepetition -textToRepresentation t [] | t == "Function1D" = return Function_1D -textToRepresentation t [] | t == "Function1DPartial" = return Function_1DPartial -textToRepresentation t [] | t == "FunctionND" = return Function_ND -textToRepresentation t [] | t == "FunctionNDPartial" = return Function_NDPartial -textToRepresentation t [repr] | t == "FunctionAsRelation" = return (Function_AsRelation repr) -textToRepresentation t [] | t == "ExplicitBounded" = return Sequence_ExplicitBounded -textToRepresentation t [] | t == "RelationAsMatrix" = return Relation_AsMatrix -textToRepresentation t [repr] | t == "RelationAsSet" = return (Relation_AsSet repr) -textToRepresentation t [repr1, repr2] | t == "PartitionAsSet" = return (Partition_AsSet repr1 repr2) -textToRepresentation t [] | t == "PartitionOccurrence" = return Partition_Occurrence -textToRepresentation t [] | t == "PermutationAsFunction" = return Permutation_AsFunction -textToRepresentation t _ = bug ("textToRepresentation:" <+> pretty t) - -representationToShortText :: HasRepresentation -> Text -representationToShortText Set_Occurrence = "Occurrence" -representationToShortText Set_Explicit = "Explicit" -representationToShortText Set_ExplicitVarSizeWithFlags = "ExplicitVarSizeWithFlags" -representationToShortText Set_ExplicitVarSizeWithMarker = "ExplicitVarSizeWithMarker" -representationToShortText Set_ExplicitVarSizeWithDummy = "ExplicitVarSizeWithDummy" -representationToShortText MSet_ExplicitWithFlags = "ExplicitWithFlags" -representationToShortText MSet_ExplicitWithRepetition = "ExplicitWithRepetition" -representationToShortText Function_1D = "Function1D" -representationToShortText Function_1DPartial = "Function1DPartial" -representationToShortText Function_ND = "FunctionND" -representationToShortText Function_NDPartial = "FunctionNDPartial" -representationToShortText Function_AsRelation{} = "FunctionAsRelation" -representationToShortText Sequence_ExplicitBounded = "ExplicitBounded" -representationToShortText Relation_AsMatrix = "RelationAsMatrix" -representationToShortText Relation_AsSet{} = "RelationAsSet" -representationToShortText Partition_AsSet{} = "PartitionAsSet" -representationToShortText Partition_Occurrence = "PartitionOccurrence" -representationToShortText Permutation_AsFunction = "PermutationAsFunction" -representationToShortText r = bug ("representationToShortText:" <+> pretty (show r)) - -representationToFullText :: HasRepresentation -> Text -representationToFullText (Function_AsRelation repr) = mconcat [ "FunctionAsRelation" - , "[" - , representationToFullText repr - , "]" - ] -representationToFullText (Relation_AsSet repr) = mconcat [ "RelationAsSet" - , "[" - , representationToFullText repr - , "]" - ] -representationToFullText (Partition_AsSet repr1 repr2) = mconcat [ "PartitionAsSet" - , "[" - , representationToFullText repr1 - , "," - , representationToFullText repr2 - , "]" - ] -representationToFullText r = representationToShortText r - - -normaliseDomain :: (Ord c, ExpressionLike c) => (c -> c) -> Domain r c -> Domain r c -normaliseDomain _norm DomainBool = DomainBool -<<<<<<< HEAD -<<<<<<< HEAD -normaliseDomain norm (DomainInt name rs ) = DomainInt name $ sort $ map (normaliseRange norm) (expandRanges rs) -======= -normaliseDomain norm (DomainInt t rs ) = DomainInt t $ sort $ map (normaliseRange norm) (expandRanges rs) ->>>>>>> f8c15eb3160b509a17e3d70103b237ea8d666c04 -||||||| merged common ancestors -normaliseDomain norm (DomainInt rs ) = DomainInt $ sort $ map (normaliseRange norm) (expandRanges rs) -======= -normaliseDomain norm (DomainInt t rs ) = DomainInt t $ sort $ map (normaliseRange norm) (expandRanges rs) ->>>>>>> taggedints -normaliseDomain _norm (DomainEnum n Nothing mp) = DomainEnum n Nothing mp -normaliseDomain _norm (DomainEnum n (Just rs) mp) = DomainEnum n (Just $ sort rs) mp -normaliseDomain norm (DomainUnnamed n x ) = DomainUnnamed n (norm x) -normaliseDomain norm (DomainRecord doms ) = DomainRecord [ (n, normaliseDomain norm d) - | (n, d) <- doms ] -normaliseDomain norm (DomainVariant doms ) = DomainVariant [ (n, normaliseDomain norm d) - | (n, d) <- doms ] -normaliseDomain norm (DomainTuple doms ) = DomainTuple $ map (normaliseDomain norm) doms -normaliseDomain norm (DomainMatrix dom1 dom2) = DomainMatrix (normaliseDomain norm dom1) - (normaliseDomain norm dom2) -normaliseDomain norm (DomainSet r attr dom ) = DomainSet r (fmap norm attr) - (normaliseDomain norm dom) -normaliseDomain norm (DomainMSet r attr dom ) = DomainMSet r (fmap norm attr) - (normaliseDomain norm dom) -normaliseDomain norm (DomainFunction r attr dom1 dom2) = DomainFunction r (fmap norm attr) - (normaliseDomain norm dom1) - (normaliseDomain norm dom2) -normaliseDomain norm (DomainSequence r attr dom ) = DomainSequence r (fmap norm attr) - (normaliseDomain norm dom) -normaliseDomain norm (DomainRelation r attr doms ) = DomainRelation r (fmap norm attr) - (map (normaliseDomain norm) doms) -normaliseDomain norm (DomainPartition r attr dom ) = DomainPartition r (fmap norm attr) - (normaliseDomain norm dom) -normaliseDomain _norm d = d - -normaliseRange :: (c -> c) -> Range c -> Range c -normaliseRange _norm RangeOpen = RangeOpen -normaliseRange norm (RangeSingle x) = RangeBounded (norm x) (norm x) -normaliseRange norm (RangeLowerBounded x) = RangeLowerBounded (norm x) -normaliseRange norm (RangeUpperBounded x) = RangeUpperBounded (norm x) -normaliseRange norm (RangeBounded x y) = RangeBounded (norm x) (norm y) - -innerDomainOf :: (MonadFail m, Show x) => Domain () x -> m (Domain () x) -innerDomainOf (DomainMatrix _ t) = return t -innerDomainOf (DomainSet _ _ t) = return t -innerDomainOf (DomainMSet _ _ t) = return t -innerDomainOf (DomainFunction _ _ a b) = return (DomainTuple [a,b]) -innerDomainOf (DomainRelation _ _ ts) = return (DomainTuple ts) -innerDomainOf (DomainPartition _ _ t) = return (DomainSet () def t) -innerDomainOf t = fail ("innerDomainOf:" <+> pretty (show t)) - -singletonDomainInt :: (Eq x, CanBeAnAlias x) => Domain r x -> Maybe x -singletonDomainInt (DomainInt _ [RangeSingle a]) = Just a -singletonDomainInt (DomainInt _ [RangeBounded a b]) = - let - followAlias (isAlias -> Just x) = followAlias x - followAlias x = x - in - if followAlias a == followAlias b - then Just a - else Nothing -singletonDomainInt _ = Nothing diff --git a/src/Conjure/Language/Expression.hs.orig b/src/Conjure/Language/Expression.hs.orig deleted file mode 100644 index d35ede465f..0000000000 --- a/src/Conjure/Language/Expression.hs.orig +++ /dev/null @@ -1,877 +0,0 @@ -{-# OPTIONS_GHC -fno-warn-orphans #-} -{-# LANGUAGE DeriveGeneric, DeriveDataTypeable #-} -{-# LANGUAGE ViewPatterns #-} - -module Conjure.Language.Expression - ( Statement(..), SearchOrder(..), Objective(..) - , Declaration(..), FindOrGiven(..) - , Expression(..), ReferenceTo(..), Region(..), InBubble(..) - , AbstractLiteral(..) - , AbstractPattern(..) - , GeneratorOrCondition(..), Generator(..), generatorPat - , e2c - , quantifiedVar, quantifiedVarOverDomain, auxiliaryVar - , lambdaToFunction - , tupleLitIfNeeded - , patternToExpr - , emptyCollectionX - , nbUses - ) where - --- conjure -import Conjure.Prelude -import Conjure.Bug -import Conjure.Language.Pretty -import Conjure.Language.AdHoc - -import Conjure.Language.Name -import Conjure.Language.NameGen ( NameGen(..) ) -import Conjure.Language.Constant -import Conjure.Language.AbstractLiteral -import Conjure.Language.Type -import Conjure.Language.Domain -import Conjure.Language.Expression.Op - -import Conjure.Language.TypeOf -import Conjure.Language.RepresentationOf - --- aeson -import qualified Data.Aeson as JSON -import qualified Data.HashMap.Strict as M -- unordered-containers -import qualified Data.Vector as V -- vector - --- pretty -import qualified Text.PrettyPrint as Pr ( cat ) - - ------------------------------------------------------------------------------------------------------------------------- --- Statement ----------------------------------------------------------------------------------------------------------- ------------------------------------------------------------------------------------------------------------------------- - -data Statement - = Declaration Declaration - | SearchOrder [SearchOrder] - | SearchHeuristic Name - | Where [Expression] - | Objective Objective Expression - | SuchThat [Expression] - deriving (Eq, Ord, Show, Data, Typeable, Generic) - -instance Serialize Statement -instance Hashable Statement -instance ToJSON Statement where toJSON = genericToJSON jsonOptions -instance FromJSON Statement where parseJSON = genericParseJSON jsonOptions - -instance Pretty Statement where - pretty (Declaration x) = pretty x - pretty (SearchOrder nms) = "branching on" <++> prettyList prBrackets "," nms - pretty (SearchHeuristic nm) = "heuristic" <+> pretty nm - pretty (Where xs) = "where" <++> vcat (punctuate "," $ map pretty xs) - pretty (Objective obj x) = pretty obj <++> pretty x - pretty (SuchThat xs) = "such that" <++> vcat (punctuate "," $ map pretty xs) - -instance VarSymBreakingDescription Statement where - varSymBreakingDescription (Declaration x) = JSON.Object $ M.fromList - [ ("type", JSON.String "Declaration") - , ("children", varSymBreakingDescription x) - ] - varSymBreakingDescription SearchOrder{} = JSON.Null - varSymBreakingDescription SearchHeuristic{} = JSON.Null - varSymBreakingDescription (Where xs) = JSON.Object $ M.fromList - [ ("type", JSON.String "Where") - , ("symmetricChildren", JSON.Bool True) - , ("children", JSON.Array $ V.fromList $ map varSymBreakingDescription xs) - ] - varSymBreakingDescription (Objective obj x) = JSON.Object $ M.fromList - [ ("type", JSON.String $ "Objective-" `mappend` stringToText (show obj)) - , ("children", varSymBreakingDescription x) - ] - varSymBreakingDescription (SuchThat xs) = JSON.Object $ M.fromList - [ ("type", JSON.String "SuchThat") - , ("symmetricChildren", JSON.Bool True) - , ("children", JSON.Array $ V.fromList $ map varSymBreakingDescription xs) - ] - - ------------------------------------------------------------------------------------------------------------------------- --- SearchOrder --------------------------------------------------------------------------------------------------------- ------------------------------------------------------------------------------------------------------------------------- - -data SearchOrder = BranchingOn Name | Cut Expression - deriving (Eq, Ord, Show, Data, Typeable, Generic) - -instance Serialize SearchOrder -instance Hashable SearchOrder -instance ToJSON SearchOrder where toJSON = genericToJSON jsonOptions -instance FromJSON SearchOrder where parseJSON = genericParseJSON jsonOptions - -instance Pretty SearchOrder where - pretty (BranchingOn x) = pretty x - pretty (Cut x) = pretty x - - ------------------------------------------------------------------------------------------------------------------------- --- Objective ----------------------------------------------------------------------------------------------------------- ------------------------------------------------------------------------------------------------------------------------- - -data Objective = Minimising | Maximising - deriving (Eq, Ord, Show, Data, Typeable, Generic) - -instance Serialize Objective -instance Hashable Objective -instance ToJSON Objective where toJSON = genericToJSON jsonOptions -instance FromJSON Objective where parseJSON = genericParseJSON jsonOptions - -instance Pretty Objective where - pretty Minimising = "minimising" - pretty Maximising = "maximising" - - ------------------------------------------------------------------------------------------------------------------------- --- Declaration --------------------------------------------------------------------------------------------------------- ------------------------------------------------------------------------------------------------------------------------- - -data Declaration - = FindOrGiven FindOrGiven Name (Domain () Expression) - | Letting Name Expression - | GivenDomainDefnEnum Name - | LettingDomainDefnEnum Name [Name] - | LettingDomainDefnUnnamed Name Expression - deriving (Eq, Ord, Show, Data, Typeable, Generic) - -instance Serialize Declaration -instance Hashable Declaration -instance ToJSON Declaration where toJSON = genericToJSON jsonOptions -instance FromJSON Declaration where parseJSON = genericParseJSON jsonOptions - --- this is only used in the instance below -type Prim = Either Bool (Either Integer Constant) - -instance Pretty Declaration where - pretty (FindOrGiven forg nm d) = hang (pretty forg <+> pretty nm <> ":" ) 8 (pretty d) - pretty (Letting nm (Domain x)) = hang ("letting" <+> pretty nm <+> "be domain") 8 (pretty x) - pretty (Letting nm x) = - let - extract :: Constant -> Maybe [Constant] - extract (viewConstantMatrix -> Just (_, rows)) = Just rows - extract (viewConstantTuple -> Just rows ) = Just rows - extract (viewConstantSet -> Just rows ) = Just rows - extract (viewConstantMSet -> Just rows ) = Just rows - extract (viewConstantFunction -> Just rows ) = Just (map snd rows) - extract (viewConstantSequence -> Just rows ) = Just rows - extract _ = Nothing - - isPrim :: Constant -> Maybe Prim - isPrim (ConstantBool val) = Just (Left val) -<<<<<<< HEAD - isPrim (ConstantInt Nothing val) = Just (Right (Left val)) -||||||| merged common ancestors - isPrim (ConstantInt val) = Just (Right (Left val)) -======= - isPrim (ConstantInt _ val) = Just (Right (Left val)) ->>>>>>> taggedints - isPrim val@ConstantEnum{} = Just (Right (Right val)) - isPrim _ = Nothing - - isPrim1DT :: Constant -> Maybe [Prim] - -- isPrim1DT p@(viewConstantMatrix -> Just{}) = isPrim1D p - -- isPrim1DT p@(viewConstantTuple -> Just{}) = isPrim1D p - -- isPrim1DT p@(viewConstantSet -> Just{}) = isPrim1D p - -- isPrim1DT p@(viewConstantMSet -> Just{}) = isPrim1D p - -- isPrim1DT p@(viewConstantFunction -> Just{}) = isPrim1D p - -- isPrim1DT p@(viewConstantSequence -> Just{}) = isPrim1D p - isPrim1DT _ = Nothing - - isPrim1D :: Constant -> Maybe [Prim] - isPrim1D (extract -> Just cells) = mapM isPrim cells - isPrim1D _ = Nothing - - isPrim2D :: Constant -> Maybe [[Prim]] - isPrim2D (extract -> Just rows) = mapM isPrim1D rows - isPrim2D (viewConstantRelation -> Just table) = mapM (mapM isPrim) table - isPrim2D (viewConstantPartition -> Just table) = mapM (mapM isPrim) table - isPrim2D _ = Nothing - - isPrim3D :: Constant -> Maybe [[[Prim]]] - isPrim3D (extract -> Just table) = mapM isPrim2D table - isPrim3D _ = Nothing - - showPrim :: Int -> Prim -> String - showPrim _ (Left True) = "T" - showPrim _ (Left False) = "_" - showPrim n (Right (Left i)) = padLeft n ' ' (show i) - showPrim n (Right (Right i)) = padRight n ' ' (show (pretty i)) - - maxIntWidth :: Data a => a -> Int - maxIntWidth primTable = - maximum (0 : [ length (show i) | i <- universeBi primTable :: [Integer] ] - ++ [ length (show (pretty i)) | i@ConstantEnum{} <- universeBi primTable ]) - - comment1D :: Int -> [Prim] -> String - comment1D width primTable = - unlines - [ "$ Visualisation for " ++ show (pretty nm) - , "$ " ++ unwords [ showPrim width cell | cell <- primTable ] - ] - - comment2D :: Int -> [[Prim]] -> String - comment2D width primTable = - unlines - $ ( "$ Visualisation for " ++ show (pretty nm)) - : [ "$ " ++ unwords [ showPrim width cell | cell <- row ] - | row <- primTable ] - - comment3D :: Int -> [[[Prim]]] -> String - comment3D width primTable = - unlines - $ ( "$ Visualisation for " ++ show (pretty nm)) - : concat [ [ "$ " ++ unwords [ showPrim width cell | cell <- row ] - | row <- table - ] ++ ["$ "] - | table <- primTable ] - - modifierX = - case x of - Constant c -> modifierC c - _ -> id - - modifierC c = - case (isPrim1DT c, isPrim2D c, isPrim3D c) of - (Just primTable, _, _) -> - if null primTable - then id - else \ s -> vcat [s, pretty (comment1D (maxIntWidth primTable) primTable)] - (_, Just primTable, _) -> - if null (concat primTable) - then id - else \ s -> vcat [s, pretty (comment2D (maxIntWidth primTable) primTable)] - (_, _, Just primTable) -> - if null (concat (concat primTable)) - then id - else \ s -> vcat [s, pretty (comment3D (maxIntWidth primTable) primTable)] - _ -> id - in - modifierX $ hang ("letting" <+> pretty nm <+> "be") 8 (pretty x) - pretty (GivenDomainDefnEnum name) = - hang ("given" <+> pretty name) 8 "new type enum" - pretty (LettingDomainDefnEnum name values) = - hang ("letting" <+> pretty name <+> "be new type enum") 8 - (prettyList prBraces "," values) - pretty (LettingDomainDefnUnnamed name size) = - hang ("letting" <+> pretty name <+> "be new type of size") 8 (pretty size) - -instance VarSymBreakingDescription Declaration where - varSymBreakingDescription (FindOrGiven forg name domain) = JSON.Object $ M.fromList - [ ("type", JSON.String "FindOrGiven") - , ("forg", toJSON forg) - , ("name", toJSON name) - , ("domain", toJSON domain) - ] - varSymBreakingDescription (Letting name x) = JSON.Object $ M.fromList - [ ("type", JSON.String "Letting") - , ("name", toJSON name) - , ("value", toJSON x) - ] - varSymBreakingDescription (GivenDomainDefnEnum name) = JSON.Object $ M.fromList - [ ("type", JSON.String "GivenDomainDefnEnum") - , ("name", toJSON name) - ] - varSymBreakingDescription (LettingDomainDefnEnum name xs) = JSON.Object $ M.fromList - [ ("type", JSON.String "GivenDomainDefnEnum") - , ("name", toJSON name) - , ("values", JSON.Array $ V.fromList $ map toJSON xs) - ] - varSymBreakingDescription (LettingDomainDefnUnnamed name x) = JSON.Object $ M.fromList - [ ("type", JSON.String "LettingDomainDefnUnnamed") - , ("name", toJSON name) - , ("value", toJSON x) - ] - - -data FindOrGiven = Find | Given | Quantified - | CutFind -- references to variables used in the definition of a cut - | LocalFind -- references to variables used inside WithLocals. i.e. auxiliaries. - deriving (Eq, Ord, Show, Data, Typeable, Generic) - -instance Serialize FindOrGiven -instance Hashable FindOrGiven -instance ToJSON FindOrGiven where toJSON = genericToJSON jsonOptions -instance FromJSON FindOrGiven where parseJSON = genericParseJSON jsonOptions - -instance Pretty FindOrGiven where - pretty Find = "find" - pretty Given = "given" - pretty Quantified = "quantified" - pretty CutFind = "find" - pretty LocalFind = "find" - - ------------------------------------------------------------------------------------------------------------------------- --- Expression ---------------------------------------------------------------------------------------------------------- ------------------------------------------------------------------------------------------------------------------------- - -data Expression - = Constant Constant - | AbstractLiteral (AbstractLiteral Expression) - | Domain (Domain () Expression) - | Reference Name (Maybe ReferenceTo) - | WithLocals Expression InBubble - | Comprehension Expression [GeneratorOrCondition] - | Typed Expression Type - | Op (Op Expression) - | ExpressionMetaVar String - deriving (Eq, Ord, Show, Data, Typeable, Generic) - -instance Serialize Expression -instance Hashable Expression -instance ToJSON Expression where toJSON = genericToJSON jsonOptions -instance FromJSON Expression where parseJSON = genericParseJSON jsonOptions - -viewIndexed :: Expression -> (Expression, [Doc]) -viewIndexed (Op (MkOpIndexing (OpIndexing m i ))) = - let this = pretty i - in second (++ [this]) (viewIndexed m) -viewIndexed (Op (MkOpSlicing (OpSlicing m a b))) = - let this = maybe prEmpty pretty a <> ".." <> maybe prEmpty pretty b - in second (++ [this]) (viewIndexed m) -viewIndexed m = (m, []) - -instance Pretty Expression where - - prettyPrec _ (viewIndexed -> (m,is@(_:_))) = Pr.cat [pretty m, nest 4 (prettyList prBrackets "," is)] - - -- mostly for debugging: print what a reference is pointing at - -- prettyPrec _ (Reference x Nothing) = pretty x <> "#`NOTHING`" - -- prettyPrec _ (Reference x (Just (DeclHasRepr _ _ dom))) = pretty x <> "#`" <> pretty dom <> "`" - -- prettyPrec _ (Reference x (Just r)) = pretty x <> "#`" <> pretty r <> "`" - - prettyPrec _ (Constant x) = pretty x - prettyPrec _ (AbstractLiteral x) = pretty x - prettyPrec _ (Domain x) = "`" <> pretty x <> "`" - prettyPrec _ (Reference x _) = pretty x - prettyPrec _ (WithLocals x (AuxiliaryVars locals)) = - vcat - [ "{" <+> pretty x - , "@" <+> vcat (map pretty locals) - , "}" - ] - prettyPrec _ (WithLocals x (DefinednessConstraints locals)) = - vcat - [ "{" <+> pretty x - , "@" <+> pretty (SuchThat locals) - , "}" - ] - prettyPrec _ (Comprehension x is) = prBrackets $ pretty x <++> "|" <+> prettyList id "," is - prettyPrec _ (Typed x ty) = prParens $ pretty x <+> ":" <+> "`" <> pretty ty <> "`" - prettyPrec prec (Op op) = prettyPrec prec op - prettyPrec _ (ExpressionMetaVar x) = "&" <> pretty x - -instance VarSymBreakingDescription Expression where - varSymBreakingDescription (Constant x) = toJSON x - varSymBreakingDescription (AbstractLiteral x) = varSymBreakingDescription x - varSymBreakingDescription (Domain domain) = varSymBreakingDescription domain - varSymBreakingDescription (Reference name _) = JSON.Object $ M.singleton "Reference" (toJSON name) - varSymBreakingDescription (WithLocals h (AuxiliaryVars locs)) = JSON.Object $ M.fromList - [ ("type", JSON.String "WithLocals") - , ("head", varSymBreakingDescription h) - , ("children", JSON.Array $ V.fromList $ map varSymBreakingDescription locs) - , ("symmetricChildren", JSON.Bool True) - ] - varSymBreakingDescription (WithLocals h (DefinednessConstraints locs)) = JSON.Object $ M.fromList - [ ("type", JSON.String "WithLocals") - , ("head", varSymBreakingDescription h) - , ("children", JSON.Array $ V.fromList $ map varSymBreakingDescription locs) - , ("symmetricChildren", JSON.Bool True) - ] - varSymBreakingDescription (Comprehension h gocs) = JSON.Object $ M.fromList - [ ("type", JSON.String "Comprehension") - , ("head", varSymBreakingDescription h) - , ("gocs", JSON.Array $ V.fromList $ map varSymBreakingDescription gocs) - ] - varSymBreakingDescription (Typed x _) = varSymBreakingDescription x - varSymBreakingDescription (Op op) = varSymBreakingDescription op - varSymBreakingDescription (ExpressionMetaVar s) = JSON.Object $ M.fromList - [ ("type", JSON.String "ExpressionMetaVar") - , ("name", JSON.String (stringToText s)) - ] - -instance TypeOf Expression where - typeOf (Constant x) = typeOf x - typeOf (AbstractLiteral x) = typeOf x - typeOf (Domain x) = typeOf x - typeOf (Reference nm Nothing) = fail ("Type error, identifier not bound:" <+> pretty nm) - typeOf (Reference nm (Just refTo)) = - case refTo of - Alias x -> typeOf x - InComprehension gen -> - let - lu pat ty = maybe - (bug $ vcat ["Type error, InComprehension:", pretty nm, pretty pat, pretty ty]) - return - (lu' pat ty) - lu' (Single nm') ty | nm == nm' = Just ty - lu' (AbsPatTuple pats) (TypeTuple tys) = zipWith lu' pats tys |> catMaybes |> listToMaybe - lu' (AbsPatMatrix pats) (TypeMatrix _ ty ) = [lu' p ty | p <- pats] |> catMaybes |> listToMaybe - lu' (AbsPatSet pats) (TypeSet ty ) = [lu' p ty | p <- pats] |> catMaybes |> listToMaybe - lu' _ _ = Nothing - in - case gen of - GenDomainNoRepr pat domain -> typeOf domain >>= lu pat - GenDomainHasRepr pat domain -> typeOf domain >>= lu (Single pat) - GenInExpr pat expr -> do - tyExpr <- typeOf expr - case innerTypeOf tyExpr of - Just tyExprInner -> lu pat tyExprInner - Nothing -> fail $ vcat - [ "Type error in the generator of a comprehension or a quantified expression" - , "Consider using" <+> pretty pat <+> ":" <+> pretty expr - ] - DeclNoRepr _ _ dom _ -> typeOf dom - DeclHasRepr _ _ dom -> typeOf dom - RecordField _ ty -> return ty - VariantField _ ty -> return ty - typeOf p@(WithLocals h (DefinednessConstraints cs)) = do - forM_ cs $ \ c -> do - ty <- typeOf c - unless (typeUnify TypeBool ty) $ fail $ vcat - [ "Local constraint is not boolean." - , "Condition:" <+> pretty c - , "In:" <+> pretty p - ] - typeOf h - typeOf p@(WithLocals h (AuxiliaryVars stmts)) = do - forM_ stmts $ \ stmt -> - case stmt of - Declaration{} -> return () -- TODO: what other checks make sense? - SuchThat xs -> forM_ xs $ \ x -> do - ty <- typeOf x - case ty of - TypeBool{} -> return () - _ -> fail $ vcat - [ "Inside a bubble, in a 'such that' statement:" <++> pretty x - , "Expected type `bool`, but got:" <++> pretty ty - ] - _ -> fail $ vcat - [ "Unexpected statement inside a bubble." - , "Expected type `find` or `such that`, but got:" <++> pretty stmt - , "The complete expression:" <+> pretty p - ] - typeOf h - typeOf p@(Comprehension x gensOrConds) = do - forM_ gensOrConds $ \ goc -> case goc of - Generator{} -> return () -- TODO: do this properly - Condition c -> do - ty <- typeOf c - unless (typeUnify TypeBool ty) $ fail $ vcat - [ "Condition is not boolean." - , "Condition:" <+> pretty c - , "In:" <+> pretty p - ] - ComprehensionLetting{} -> return () - TypeList <$> typeOf x - typeOf (Typed _ ty) = return ty - typeOf (Op op) = typeOf op - typeOf x@ExpressionMetaVar{} = bug ("typeOf:" <+> pretty x) - -instance RepresentationOf Expression where - representationTreeOf (Reference _ (Just (DeclHasRepr _ _ dom))) = return (reprTree dom) - representationTreeOf (Op (MkOpIndexing (OpIndexing m i))) = do - iType <- typeOf i - case iType of - TypeBool{} -> return () - TypeInt{} -> return () - _ -> fail "representationOf, OpIndexing, not a bool or int index" - mTree <- representationTreeOf m - case mTree of - Tree _ [r] -> return r - _ -> fail "domainOf, OpIndexing, not a matrix" - representationTreeOf _ = fail "doesn't seem to have a representation" - -instance Domain () Expression :< Expression where - inject = Domain - project (Domain x) = return x - project x = fail ("projecting Domain out of Expression:" <+> pretty x) - -instance Op Expression :< Expression where - inject = Op - project (Op x) = return x - project x = fail ("projecting Op out of Expression:" <+> pretty x) - -instance Op Constant :< Constant where - inject x = bug ("injecting Op into a Constant:" <+> pretty x) - project x = fail ("projecting Op out of a Constant:" <+> pretty x) - -instance CanBeAnAlias Expression where - isAlias (Reference _ (Just (Alias x))) = Just x - isAlias _ = Nothing - -instance ReferenceContainer Expression where - fromName nm = Reference nm Nothing - nameOut (Reference nm _) = return nm - nameOut (Constant (ConstantField nm _)) = return nm - nameOut p = fail ("This expression isn't a 'name':" <+> pretty p) - -instance ExpressionLike Expression where - fromInt = Constant . fromInt - fromIntWithTag i t = Constant $ fromIntWithTag i t - intOut doc (Constant c) = intOut ("intOut{Expression}" <+> doc) c - intOut doc x = fail $ vcat [ "Expecting a constant, but got:" <++> pretty x - , "Called from:" <+> doc - ] - - fromBool = Constant . fromBool - boolOut (Constant c) = boolOut c - boolOut x = fail ("Expecting a constant, but got:" <++> pretty x) - - fromList xs = AbstractLiteral $ AbsLitMatrix (mkDomainIntB 1 (fromInt $ genericLength xs)) xs - listOut (AbstractLiteral (AbsLitMatrix _ xs)) = return xs - listOut (Constant (ConstantAbstract (AbsLitMatrix _ xs))) = return (map Constant xs) - listOut c = fail ("Expecting a matrix literal, but found:" <+> pretty c) - -instance Num Expression where - x + y = Op $ MkOpSum $ OpSum $ fromList [x,y] - x - y = Op $ MkOpMinus $ OpMinus x y - x * y = Op $ MkOpProduct $ OpProduct $ fromList [x,y] - abs x = Op $ MkOpTwoBars $ OpTwoBars x - signum _ = bug "signum {Expression}" - fromInteger = fromInt . fromInteger - -instance Integral Expression where - divMod a b = ( Op $ MkOpDiv $ OpDiv a b - , Op $ MkOpMod $ OpMod a b ) - quotRem = divMod - toInteger = bug "toInteger {Expression}" - -instance Real Expression where - toRational = bug "toRational {Expression}" - -instance Enum Expression where - fromEnum = bug "fromEnum {Expression}" - toEnum = fromInt . fromIntegral - succ a = a + 1 - pred a = a - 1 - enumFrom x = x : enumFrom (succ x) - enumFromThen x n = x : enumFromThen (x+n) n - enumFromTo _x _y = bug "enumFromTo {Expression}" - enumFromThenTo _x _n _y = bug "enumFromThenTo {Expression}" - - ------------------------------------------------------------------------------------------------------------------------- --- InBubble ------------------------------------------------------------------------------------------------------------ ------------------------------------------------------------------------------------------------------------------------- - -data InBubble - = AuxiliaryVars [Statement] -- can only be a LocalFind or a SuchThat - -- the variable declarations are lifted to top level, eventually - | DefinednessConstraints [Expression] -- lifted to the closest relational context - deriving (Eq, Ord, Show, Data, Typeable, Generic) - -instance Serialize InBubble -instance Hashable InBubble -instance ToJSON InBubble where toJSON = genericToJSON jsonOptions -instance FromJSON InBubble where parseJSON = genericParseJSON jsonOptions - - ------------------------------------------------------------------------------------------------------------------------- --- some helper functions to do with Expressions ------------------------------------------------------------------------ ------------------------------------------------------------------------------------------------------------------------- - --- | This is only for when you know the Expression you have is actually a Constant, but --- is refusing to believe that it is one. --- Remind it where it comes from! --- (Srsly: Can be useful after parsing a solution file, for example.) -e2c :: MonadFail m => Expression -> m Constant -e2c (Constant c) = return c -e2c (AbstractLiteral c) = ConstantAbstract <$> mapM e2c c -<<<<<<< HEAD -e2c (Op (MkOpNegate (OpNegate (Constant (ConstantInt Nothing x))))) = return $ ConstantInt Nothing $ negate x -||||||| merged common ancestors -e2c (Op (MkOpNegate (OpNegate (Constant (ConstantInt x))))) = return $ ConstantInt $ negate x -======= -e2c (Op (MkOpNegate (OpNegate (Constant (ConstantInt t x))))) = return $ ConstantInt t $ negate x ->>>>>>> taggedints -e2c x = fail ("e2c, not a constant:" <+> pretty x) - --- | generate a fresh name for a quantified variable. --- fst: the pattern to be used inside a generator --- snd: the expression to be used everywhere else -quantifiedVar :: NameGen m => m (AbstractPattern, Expression) -quantifiedVar = do - nm <- nextName "q" - let pat = Single nm - ref = Reference nm Nothing - return (pat, ref) - --- | like `quantifiedVar`, but already name-resolved as a quantified variable over the given domain -quantifiedVarOverDomain :: NameGen m => Domain () Expression -> m (AbstractPattern, Expression) -quantifiedVarOverDomain domain = do - nm <- nextName "q" - let pat = Single nm - ref = Reference nm (Just (InComprehension (GenDomainNoRepr (Single nm) domain))) - return (pat, ref) - --- | generate a fresh name for an auxiliary variable. --- fst: the name to be used when declaring the variable --- snd: the expression to be used everywhere else -auxiliaryVar :: NameGen m => m (Name, Expression) -auxiliaryVar = do - -- Savile Row has a bug which is triggered when there are variables with names of the form aux* - nm <- nextName "conjure_aux" - let ref = Reference nm Nothing - return (nm, ref) - - -lambdaToFunction :: AbstractPattern -> Expression -> Expression -> Expression -lambdaToFunction (Single nm) body = \ p -> - let - replacer :: Expression -> Expression - replacer (Reference n _) | n == nm = p - replacer x = x - in - transform replacer body -lambdaToFunction (AbsPatTuple ts) body = \ p -> - let - unroll :: [AbstractPattern] -> [Expression] -> Expression -> Expression - unroll [] [] b = b - unroll (pat:pats) (val:vals) b = unroll pats vals (lambdaToFunction pat b val) - unroll _ _ _ = bug "lambdaToFunction, AbsPatTuple, unroll" - - ps :: [Expression] - ps = case p of - Constant (ConstantAbstract (AbsLitTuple xs)) -> map Constant xs - AbstractLiteral (AbsLitTuple xs) -> xs - _ -> [ Op (MkOpIndexing (OpIndexing p i)) - | i' <- [ 1 .. genericLength ts ] - , let i = fromInt i' - ] - in - unroll ts ps body -lambdaToFunction (AbsPatMatrix ts) body = \ p -> - let - unroll :: [AbstractPattern] -> [Expression] -> Expression -> Expression - unroll [] [] b = b - unroll (pat:pats) (val:vals) b = unroll pats vals (lambdaToFunction pat b val) - unroll _ _ _ = bug "lambdaToFunction, AbsPatMatrix, unroll" - - ps :: [Expression] - ps = case p of - Constant (ConstantAbstract (AbsLitMatrix _ xs)) -> map Constant xs - AbstractLiteral (AbsLitMatrix _ xs) -> xs - _ -> bug "lambdaToFunction, AbsPatMatrix" - in - unroll ts ps body -lambdaToFunction (AbsPatSet ts) body = \ p -> - let - unroll :: [AbstractPattern] -> [Expression] -> Expression -> Expression - unroll [] [] b = b - unroll (pat:pats) (val:vals) b = unroll pats vals (lambdaToFunction pat b val) - unroll _ _ _ = bug "lambdaToFunction, AbsPatSet, unroll" - - ps :: [Expression] - ps = case p of - Constant (ConstantAbstract (AbsLitSet xs)) -> map Constant xs - AbstractLiteral (AbsLitSet xs) -> xs - _ -> bug "lambdaToFunction, AbsPatSet" - in - unroll ts ps body -lambdaToFunction p@AbstractPatternMetaVar{} _ = bug $ "Unsupported AbstractPattern, got " <+> pretty (show p) - - ------------------------------------------------------------------------------------------------------------------------- --- ReferenceTo --------------------------------------------------------------------------------------------------------- ------------------------------------------------------------------------------------------------------------------------- - -data ReferenceTo - = Alias Expression - | InComprehension Generator - | DeclNoRepr FindOrGiven Name (Domain () Expression) - Region -- the region of this reference - -- references with the same region identifier will get the same representation - | DeclHasRepr FindOrGiven Name (Domain HasRepresentation Expression) - | RecordField Name Type -- the type of the field with this name - | VariantField Name Type -- the type of the variant with this name - deriving (Eq, Ord, Show, Data, Typeable, Generic) - -instance Serialize ReferenceTo -instance Hashable ReferenceTo -instance ToJSON ReferenceTo where toJSON = genericToJSON jsonOptions -instance FromJSON ReferenceTo where parseJSON = genericParseJSON jsonOptions - -instance Pretty ReferenceTo where - pretty (Alias x) = "Alias" <+> prParens (pretty x) - pretty (InComprehension gen) = "InComprehension" <+> prParens (pretty gen) - pretty (DeclNoRepr forg nm dom _) = "DeclNoRepr" <+> prParens (pretty forg <+> pretty nm <> ":" <+> pretty dom) - pretty (DeclHasRepr forg nm dom ) = "DeclHasRepr" <+> prParens (pretty forg <+> pretty nm <> ":" <+> pretty dom) - pretty (RecordField nm ty) = "RecordField" <+> prParens (pretty nm <+> ":" <+> pretty ty) - pretty (VariantField nm ty) = "VariantField" <+> prParens (pretty nm <+> ":" <+> pretty ty) - -data Region - = NoRegion - | Region Int - deriving (Eq, Ord, Show, Data, Typeable, Generic) - -instance Serialize Region -instance Hashable Region -instance ToJSON Region where toJSON = genericToJSON jsonOptions -instance FromJSON Region where parseJSON = genericParseJSON jsonOptions - - ------------------------------------------------------------------------------------------------------------------------- --- AbstractPattern ----------------------------------------------------------------------------------------------------- ------------------------------------------------------------------------------------------------------------------------- - -data AbstractPattern - = Single Name - | AbsPatTuple [AbstractPattern] - | AbsPatMatrix - -- (Domain () a) -- TODO: Should there be a domain here? - [AbstractPattern] - | AbsPatSet [AbstractPattern] - -- | AbsPatMSet [a] - -- | AbsPatFunction [(a, a)] - -- | AbsPatRelation [[a]] - -- | AbsPatPartition [[a]] - -- TODO: Consider introducing the above as abstract patterns... - | AbstractPatternMetaVar String - deriving (Eq, Ord, Show, Data, Typeable, Generic) - -instance Serialize AbstractPattern -instance Hashable AbstractPattern -instance ToJSON AbstractPattern where toJSON = genericToJSON jsonOptions -instance FromJSON AbstractPattern where parseJSON = genericParseJSON jsonOptions - -instance Pretty AbstractPattern where - pretty (Single nm) = pretty nm - pretty (AbsPatTuple xs) = (if length xs <= 1 then "tuple" else prEmpty) <> - prettyList prParens "," xs - pretty (AbsPatMatrix xs) = prettyList prBrackets "," xs - pretty (AbsPatSet xs) = prettyList prBraces "," xs - pretty (AbstractPatternMetaVar s) = "&" <> pretty s - -instance VarSymBreakingDescription AbstractPattern where - varSymBreakingDescription (Single nm) = toJSON nm - varSymBreakingDescription (AbsPatTuple xs) = JSON.Object $ M.fromList - [ ("type", JSON.String "AbsPatTuple") - , ("children", JSON.Array $ V.fromList $ map varSymBreakingDescription xs) - ] - varSymBreakingDescription (AbsPatMatrix xs) = JSON.Object $ M.fromList - [ ("type", JSON.String "AbsPatMatrix") - , ("children", JSON.Array $ V.fromList $ map varSymBreakingDescription xs) - ] - varSymBreakingDescription (AbsPatSet xs) = JSON.Object $ M.fromList - [ ("type", JSON.String "AbsPatSet") - , ("children", JSON.Array $ V.fromList $ map varSymBreakingDescription xs) - , ("symmetricChildren", JSON.Bool True) - ] - varSymBreakingDescription (AbstractPatternMetaVar s) = JSON.Object $ M.fromList - [ ("type", JSON.String "AbstractPatternMetaVar") - , ("name", JSON.String (stringToText s)) - ] - - -patternToExpr :: AbstractPattern -> Expression -patternToExpr (Single nm) = Reference nm Nothing -patternToExpr (AbsPatTuple ts) = AbstractLiteral $ AbsLitTuple $ map patternToExpr ts -<<<<<<< HEAD -patternToExpr (AbsPatMatrix ts) = AbstractLiteral $ AbsLitMatrix (DomainInt Nothing [RangeBounded 1 (fromInt (genericLength ts))]) -||||||| merged common ancestors -patternToExpr (AbsPatMatrix ts) = AbstractLiteral $ AbsLitMatrix (DomainInt [RangeBounded 1 (fromInt (genericLength ts))]) -======= -patternToExpr (AbsPatMatrix ts) = AbstractLiteral $ AbsLitMatrix - (DomainInt NoTag [RangeBounded 1 (fromInt (genericLength ts))]) ->>>>>>> taggedints - $ map patternToExpr ts -patternToExpr (AbsPatSet ts) = AbstractLiteral $ AbsLitSet $ map patternToExpr ts -patternToExpr AbstractPatternMetaVar{} = bug "patternToExpr" - ------------------------------------------------------------------------------------------------------------------------- --- Generator ----------------------------------------------------------------------------------------------------------- ------------------------------------------------------------------------------------------------------------------------- - -data GeneratorOrCondition - = Generator Generator - | Condition Expression - | ComprehensionLetting Name Expression - deriving (Eq, Ord, Show, Data, Typeable, Generic) - -instance Pretty GeneratorOrCondition where - pretty (Generator x) = pretty x - pretty (Condition x) = pretty x - pretty (ComprehensionLetting n x) = "letting" <+> pretty n <+> "be" <+> pretty x - -instance VarSymBreakingDescription GeneratorOrCondition where - varSymBreakingDescription (Generator x) = JSON.Object $ M.fromList - [ ("type", JSON.String "Generator") - , ("child", varSymBreakingDescription x) - ] - varSymBreakingDescription (Condition x) = JSON.Object $ M.fromList - [ ("type", JSON.String "Condition") - , ("child", varSymBreakingDescription x) - ] - varSymBreakingDescription (ComprehensionLetting n x) = JSON.Object $ M.fromList - [ ("type", JSON.String "ComprehensionLetting") - , ("children", JSON.Array $ V.fromList [toJSON n, varSymBreakingDescription x]) - ] - -instance Serialize GeneratorOrCondition -instance Hashable GeneratorOrCondition -instance ToJSON GeneratorOrCondition where toJSON = genericToJSON jsonOptions -instance FromJSON GeneratorOrCondition where parseJSON = genericParseJSON jsonOptions - - -data Generator - = GenDomainNoRepr AbstractPattern (Domain () Expression) - | GenDomainHasRepr Name (Domain HasRepresentation Expression) - | GenInExpr AbstractPattern Expression - deriving (Eq, Ord, Show, Data, Typeable, Generic) - -instance Pretty Generator where - pretty (GenDomainNoRepr pat x) = pretty pat <+> ":" <+> pretty x - pretty (GenDomainHasRepr pat x) = pretty pat <+> ":" <+> pretty x - pretty (GenInExpr pat x) = pretty pat <+> "<-" <+> pretty x - -instance VarSymBreakingDescription Generator where - varSymBreakingDescription (GenDomainNoRepr pat x) = JSON.Object $ M.fromList - [ ("type", JSON.String "GenDomainNoRepr") - , ("pattern", varSymBreakingDescription pat) - , ("generator", varSymBreakingDescription x) - ] - varSymBreakingDescription (GenDomainHasRepr pat x) = JSON.Object $ M.fromList - [ ("type", JSON.String "GenDomainHasRepr") - , ("pattern", toJSON pat) - , ("generator", varSymBreakingDescription x) - ] - varSymBreakingDescription (GenInExpr pat x) = JSON.Object $ M.fromList - [ ("type", JSON.String "GenInExpr") - , ("pattern", varSymBreakingDescription pat) - , ("generator", varSymBreakingDescription x) - ] - -instance Serialize Generator -instance Hashable Generator -instance ToJSON Generator where toJSON = genericToJSON jsonOptions -instance FromJSON Generator where parseJSON = genericParseJSON jsonOptions - -generatorPat :: Generator -> AbstractPattern -generatorPat (GenDomainNoRepr pat _) = pat -generatorPat (GenDomainHasRepr pat _) = Single pat -generatorPat (GenInExpr pat _) = pat - - ------------------------------------------------------------------------------------------------------------------------- --- Misc --------------------------------------------------------------------------------------------------------------- ------------------------------------------------------------------------------------------------------------------------- - -tupleLitIfNeeded :: [Expression] -> Expression -tupleLitIfNeeded [] = bug "tupleLitIfNeeded []" -tupleLitIfNeeded [x] = x -tupleLitIfNeeded xs = AbstractLiteral (AbsLitTuple xs) - -nbUses :: Data x => Name -> x -> Int -nbUses nm here = length [ () | Reference nm2 _ <- universeBi here, nm == nm2 ] - -emptyCollectionX :: Expression -> Bool -emptyCollectionX (Constant x) = emptyCollection x -emptyCollectionX (AbstractLiteral x) = emptyCollectionAbsLit x -emptyCollectionX (Typed x _) = emptyCollectionX x -emptyCollectionX _ = False diff --git a/src/Conjure/Language/Expression/DomainSizeOf.hs.orig b/src/Conjure/Language/Expression/DomainSizeOf.hs.orig deleted file mode 100644 index 4aa9b1d8d0..0000000000 --- a/src/Conjure/Language/Expression/DomainSizeOf.hs.orig +++ /dev/null @@ -1,131 +0,0 @@ -{-# OPTIONS_GHC -fno-warn-orphans #-} -{-# LANGUAGE QuasiQuotes #-} - -module Conjure.Language.Expression.DomainSizeOf - ( DomainSizeOf(..) - , getMaxNumberOfElementsInContainer - ) where - --- conjure -import Conjure.Prelude -import Conjure.Bug -import Conjure.Language.Definition -import Conjure.Language.AdHoc -import Conjure.Language.Domain -import Conjure.Language.Expression.Op -import Conjure.Language.Lenses -import Conjure.Language.TH -import Conjure.Language.Type - -import Conjure.Language.DomainSizeOf -import Conjure.Language.Pretty - - -instance DomainSizeOf Expression Expression where - domainSizeOf DomainBool = return 2 - domainSizeOf (DomainInt _ [] ) = fail "domainSizeOf infinite integer domain" - domainSizeOf (DomainInt _ [r]) = domainSizeOfRange r - domainSizeOf (DomainInt _ rs ) = make opSum . fromList <$> mapM domainSizeOfRange rs - domainSizeOf (DomainEnum n Nothing _) = return $ - let n' = n `mappend` "_EnumSize" -<<<<<<< HEAD - in Reference n' (Just (DeclHasRepr Given n' (DomainInt (Just n) []))) -||||||| merged common ancestors - in Reference n' (Just (DeclHasRepr Given n' (DomainInt []))) -======= - in Reference n' (Just (DeclHasRepr Given n' (DomainInt NoTag []))) ->>>>>>> taggedints - domainSizeOf (DomainUnnamed _ x) = return x - domainSizeOf (DomainTuple []) = return 1 - domainSizeOf (DomainTuple xs) = make opProduct . fromList <$> mapM domainSizeOf xs - domainSizeOf (DomainRecord xs) = make opProduct . fromList <$> mapM (domainSizeOf . snd) xs - domainSizeOf (DomainVariant xs) = make opSum . fromList <$> mapM (domainSizeOf . snd) xs - domainSizeOf (DomainMatrix index inner) = make opPow <$> domainSizeOf inner <*> domainSizeOf index - domainSizeOf (DomainSet _ (SetAttr sizeAttr) inner) = do - innerSize <- domainSizeOf inner - case sizeAttr of - SizeAttr_None -> return (make opPow 2 innerSize) - SizeAttr_Size size -> return (nchoosek (make opFactorial) innerSize size) - SizeAttr_MinSize _ -> return (make opPow 2 innerSize) -- TODO: can be better - SizeAttr_MaxSize _ -> return (make opPow 2 innerSize) -- TODO: can be better - SizeAttr_MinMaxSize _ _ -> return (make opPow 2 innerSize) -- TODO: can be better - domainSizeOf (DomainMSet _ attrs inner) = do - innerSize <- domainSizeOf inner - let - getMaxSize = case attrs of - MSetAttr (SizeAttr_Size x) _ -> return x - MSetAttr (SizeAttr_MaxSize x) _ -> return x - MSetAttr (SizeAttr_MinMaxSize _ x) _ -> return x - MSetAttr _ (OccurAttr_MaxOccur x) -> return (x * innerSize) - MSetAttr _ (OccurAttr_MinMaxOccur _ x) -> return (x * innerSize) - _ -> fail ("domainSizeOf.getMaxSize, mset not supported. attributes:" <+> pretty attrs) - getMaxOccur = case attrs of - MSetAttr _ (OccurAttr_MaxOccur x) -> return x - MSetAttr _ (OccurAttr_MinMaxOccur _ x) -> return x - MSetAttr (SizeAttr_Size x) _ -> return (make opMin $ fromList [x, innerSize]) - MSetAttr (SizeAttr_MaxSize x) _ -> return (make opMin $ fromList [x, innerSize]) - MSetAttr (SizeAttr_MinMaxSize _ x) _ -> return (make opMin $ fromList [x, innerSize]) - _ -> fail ("domainSizeOf.getMaxSize, mset not supported. attributes:" <+> pretty attrs) - maxSize <- getMaxSize - maxOccur <- getMaxOccur - return (make opPow maxOccur maxSize) -<<<<<<< HEAD - domainSizeOf d@(DomainSequence _ (SequenceAttr sizeAttr jectivityAttr) innerTo) = do - size <- case sizeAttr of - SizeAttr_None -> fail ("Infinite domain:" <+> pretty d) - SizeAttr_Size s -> return s - SizeAttr_MinSize _ -> fail ("Infinite domain:" <+> pretty d) - SizeAttr_MaxSize s -> return s - SizeAttr_MinMaxSize _ s -> return s - domainSizeOf $ DomainFunction def (FunctionAttr sizeAttr PartialityAttr_Partial jectivityAttr) - (DomainInt [RangeBounded 1 size]) innerTo -||||||| merged common ancestors - domainSizeOf (DomainSequence _ (SequenceAttr sizeAttr _) innerTo) = - domainSizeOf $ DomainRelation def (RelationAttr sizeAttr def) [innerTo, innerTo] -======= - domainSizeOf d@(DomainSequence _ (SequenceAttr sizeAttr jectivityAttr) innerTo) = do - size <- case sizeAttr of - SizeAttr_None -> fail ("Infinite domain:" <+> pretty d) - SizeAttr_Size s -> return s - SizeAttr_MinSize _ -> fail ("Infinite domain:" <+> pretty d) - SizeAttr_MaxSize s -> return s - SizeAttr_MinMaxSize _ s -> return s - domainSizeOf $ DomainFunction def (FunctionAttr sizeAttr PartialityAttr_Partial jectivityAttr) - (DomainInt NoTag [RangeBounded 1 size]) innerTo ->>>>>>> taggedints - domainSizeOf (DomainFunction _ (FunctionAttr sizeAttr _ _) innerFr innerTo) = - domainSizeOf $ DomainRelation def (RelationAttr sizeAttr def) [innerFr, innerTo] - domainSizeOf (DomainRelation _ (RelationAttr sizeAttr _binRelAttr) inners) = - domainSizeOf (DomainSet def (SetAttr sizeAttr) (DomainTuple inners)) - domainSizeOf (DomainPartition _ a inner) = - domainSizeOf $ DomainSet def (SetAttr (partsNum a)) - $ DomainSet def (SetAttr (partsSize a)) inner - domainSizeOf (DomainPermutation _ (PermutationAttr sizeAttr) inner) = - domainSizeOf $ DomainSet def (SetAttr sizeAttr) inner - domainSizeOf d = bug ("not implemented: domainSizeOf:" <+> vcat [pretty d, pretty (show d)]) - - -domainSizeOfRange :: (Op a :< a, ExpressionLike a, Pretty a, MonadFail m, Num a, Eq a) => Range a -> m a -domainSizeOfRange RangeSingle{} = return 1 -domainSizeOfRange (RangeBounded 1 u) = return u -domainSizeOfRange (RangeBounded l u) = return $ make opSum $ fromList [1, make opMinus u l] -domainSizeOfRange r = fail ("domainSizeOf infinite range:" <+> pretty r) - - -getMaxNumberOfElementsInContainer :: Domain () Expression -> Expression -getMaxNumberOfElementsInContainer domain@(DomainSet _ (SetAttr sizeAttr) inner) = - case (getMaxFrom_SizeAttr sizeAttr, domainSizeOf inner) of - (Just n, _) -> n - (_, Just n) -> n - _ -> bug $ "getMaxNumberOfElementsInContainer, DomainSet:" <+> pretty domain -getMaxNumberOfElementsInContainer domain@(DomainMSet _ (MSetAttr sizeAttr occurAttr) inner) = - case (getMaxFrom_SizeAttr sizeAttr, getMaxFrom_OccurAttr occurAttr, domainSizeOf inner) of - (Just n, _ , _ ) -> n - (_ , Just o, Just n) -> [essence| &o * &n |] - _ -> bug $ "getMaxNumberOfElementsInContainer, DomainMSet:" <+> pretty domain -getMaxNumberOfElementsInContainer domain@(DomainSequence _ (SequenceAttr sizeAttr _) _) = - case getMaxFrom_SizeAttr sizeAttr of - Just n -> n - _ -> bug $ "getMaxNumberOfElementsInContainer, DomainSequence:" <+> pretty domain -getMaxNumberOfElementsInContainer domain = bug $ "getMaxNumberOfElementsInContainer:" <+> pretty domain - diff --git a/src/Conjure/Language/Expression/Op/AllDiffExcept.hs.orig b/src/Conjure/Language/Expression/Op/AllDiffExcept.hs.orig deleted file mode 100644 index dba3b7554c..0000000000 --- a/src/Conjure/Language/Expression/Op/AllDiffExcept.hs.orig +++ /dev/null @@ -1,67 +0,0 @@ -{-# LANGUAGE DeriveGeneric, DeriveDataTypeable, DeriveFunctor, DeriveTraversable, DeriveFoldable, ViewPatterns #-} - -module Conjure.Language.Expression.Op.AllDiffExcept where - -import Conjure.Prelude -import Conjure.Language.Expression.Op.Internal.Common - -import qualified Data.Aeson as JSON -- aeson -import qualified Data.HashMap.Strict as M -- unordered-containers -import qualified Data.Vector as V -- vector - - -data OpAllDiffExcept x = OpAllDiffExcept x x - deriving (Eq, Ord, Show, Data, Functor, Traversable, Foldable, Typeable, Generic) - -instance Serialize x => Serialize (OpAllDiffExcept x) -instance Hashable x => Hashable (OpAllDiffExcept x) -instance ToJSON x => ToJSON (OpAllDiffExcept x) where toJSON = genericToJSON jsonOptions -instance FromJSON x => FromJSON (OpAllDiffExcept x) where parseJSON = genericParseJSON jsonOptions - -instance (TypeOf x, Pretty x) => TypeOf (OpAllDiffExcept x) where - typeOf p@(OpAllDiffExcept x n) = do - tyX <- typeOf x - tyN <- typeOf n - case tyN of -<<<<<<< HEAD - TypeInt _ -> return () -||||||| merged common ancestors - TypeInt -> return () -======= - TypeInt NoTag -> return () - TypeInt (TagEnum _) -> return () ->>>>>>> taggedints - _ -> raiseTypeError p - case tyX of - TypeList{} -> return TypeBool - TypeMatrix{} -> return TypeBool - _ -> raiseTypeError p - -instance EvaluateOp OpAllDiffExcept where -<<<<<<< HEAD - evaluateOp (OpAllDiffExcept (viewConstantMatrix -> Just (_, vals)) someint) = do - let vals' = filter (someint/=) vals -||||||| merged common ancestors - evaluateOp (OpAllDiffExcept (viewConstantMatrix -> Just (_, vals)) (viewConstantInt -> Just n)) = do - let vals' = filter (ConstantInt n/=) vals -======= - evaluateOp (OpAllDiffExcept (viewConstantMatrix -> Just (_, vals)) i@(viewConstantInt -> Just n)) = do - TypeInt t <- typeOf i - let vals' = filter (ConstantInt t n/=) vals ->>>>>>> taggedints - return $ ConstantBool $ length vals' == length (sortNub vals') - evaluateOp op = na $ "evaluateOp{OpAllDiffExcept}:" <++> pretty (show op) - -instance SimplifyOp OpAllDiffExcept x where - simplifyOp _ = na "simplifyOp{OpAllDiffExcept}" - -instance Pretty x => Pretty (OpAllDiffExcept x) where - prettyPrec _ (OpAllDiffExcept a b) = "alldifferent_except" <> prettyList prParens "," [a, b] - -instance (VarSymBreakingDescription x, ExpressionLike x) => VarSymBreakingDescription (OpAllDiffExcept x) where - varSymBreakingDescription (OpAllDiffExcept x y) = JSON.Object $ M.fromList - [ ("type", JSON.String "OpAllDiffExcept") - , ("children", JSON.Array $ V.fromList [ varSymBreakingDescription x - , varSymBreakingDescription y - ]) - ] diff --git a/src/Conjure/Language/Expression/Op/Defined.hs.orig b/src/Conjure/Language/Expression/Op/Defined.hs.orig deleted file mode 100644 index 48e4dd7bec..0000000000 --- a/src/Conjure/Language/Expression/Op/Defined.hs.orig +++ /dev/null @@ -1,55 +0,0 @@ -{-# LANGUAGE DeriveGeneric, DeriveDataTypeable, DeriveFunctor, DeriveTraversable, DeriveFoldable, ViewPatterns #-} - -module Conjure.Language.Expression.Op.Defined where - -import Conjure.Prelude -import Conjure.Language.Expression.Op.Internal.Common - -import qualified Data.Aeson as JSON -- aeson -import qualified Data.HashMap.Strict as M -- unordered-containers -import qualified Data.Vector as V -- vector - - -data OpDefined x = OpDefined x - deriving (Eq, Ord, Show, Data, Functor, Traversable, Foldable, Typeable, Generic) - -instance Serialize x => Serialize (OpDefined x) -instance Hashable x => Hashable (OpDefined x) -instance ToJSON x => ToJSON (OpDefined x) where toJSON = genericToJSON jsonOptions -instance FromJSON x => FromJSON (OpDefined x) where parseJSON = genericParseJSON jsonOptions - -instance (Pretty x, TypeOf x) => TypeOf (OpDefined x) where - typeOf p@(OpDefined x) = do - ty <- typeOf x - case ty of - TypeFunction a _ -> return (TypeSet a) -<<<<<<< HEAD - TypeSequence _ -> return (TypeSet $ TypeInt Nothing) -||||||| merged common ancestors - TypeSequence _ -> return (TypeSet TypeInt) -======= - TypeSequence _ -> return (TypeSet (TypeInt NoTag)) ->>>>>>> taggedints - _ -> raiseTypeError p - -instance EvaluateOp OpDefined where - evaluateOp p | any isUndef (childrenBi p) = do - ty <- typeOf p - return $ mkUndef ty $ "Has undefined children:" <+> pretty p - evaluateOp (OpDefined (viewConstantFunction -> Just xs)) = - return $ ConstantAbstract $ AbsLitSet $ sortNub $ map fst xs - evaluateOp op = na $ "evaluateOp{OpDefined}:" <++> pretty (show op) - -instance SimplifyOp OpDefined x where - simplifyOp _ = na "simplifyOp{OpDefined}" - -instance Pretty x => Pretty (OpDefined x) where - prettyPrec _ (OpDefined a) = "defined" <> prParens (pretty a) - -instance VarSymBreakingDescription x => VarSymBreakingDescription (OpDefined x) where - varSymBreakingDescription (OpDefined a) = JSON.Object $ M.fromList - [ ("type", JSON.String "OpDefined") - , ("children", JSON.Array $ V.fromList - [ varSymBreakingDescription a - ]) - ] diff --git a/src/Conjure/Language/Expression/Op/Div.hs.orig b/src/Conjure/Language/Expression/Op/Div.hs.orig deleted file mode 100644 index a230c7edf9..0000000000 --- a/src/Conjure/Language/Expression/Op/Div.hs.orig +++ /dev/null @@ -1,65 +0,0 @@ -{-# LANGUAGE DeriveGeneric, DeriveDataTypeable, DeriveFunctor, DeriveTraversable, DeriveFoldable #-} - -module Conjure.Language.Expression.Op.Div where - -import Conjure.Prelude -import Conjure.Language.Expression.Op.Internal.Common - -import qualified Data.Aeson as JSON -- aeson -import qualified Data.HashMap.Strict as M -- unordered-containers -import qualified Data.Vector as V -- vector - - -data OpDiv x = OpDiv x x - deriving (Eq, Ord, Show, Data, Functor, Traversable, Foldable, Typeable, Generic) - -instance Serialize x => Serialize (OpDiv x) -instance Hashable x => Hashable (OpDiv x) -instance ToJSON x => ToJSON (OpDiv x) where toJSON = genericToJSON jsonOptions -instance FromJSON x => FromJSON (OpDiv x) where parseJSON = genericParseJSON jsonOptions - -instance BinaryOperator (OpDiv x) where - opLexeme _ = L_Div - -instance (TypeOf x, Pretty x) => TypeOf (OpDiv x) where - typeOf p@(OpDiv a b) = do - ta <- typeOf a - tb <- typeOf b - case (ta, tb) of - (TypeInt NoTag, TypeInt NoTag) -> intToIntToInt p a b - _ -> raiseTypeError p - -instance EvaluateOp OpDiv where -<<<<<<< HEAD - evaluateOp p | any isUndef (childrenBi p) = return $ mkUndef (TypeInt Nothing) $ "Has undefined children:" <+> pretty p -||||||| merged common ancestors - evaluateOp p | any isUndef (childrenBi p) = return $ mkUndef TypeInt $ "Has undefined children:" <+> pretty p -======= - evaluateOp p | any isUndef (childrenBi p) = return $ mkUndef (TypeInt NoTag) $ "Has undefined children:" <+> pretty p ->>>>>>> taggedints - evaluateOp p@(OpDiv x y) -<<<<<<< HEAD - | y /= 0 = ConstantInt Nothing <$> (div <$> intOut "div x" x <*> intOut "div y" y) - | otherwise = return $ mkUndef (TypeInt Nothing) $ "division by zero:" <+> pretty p -||||||| merged common ancestors - | y /= 0 = ConstantInt <$> (div <$> intOut "div x" x <*> intOut "div y" y) - | otherwise = return $ mkUndef TypeInt $ "division by zero:" <+> pretty p -======= - | y /= 0 = ConstantInt NoTag <$> (div <$> intOut "div x" x <*> intOut "div y" y) - | otherwise = return $ mkUndef (TypeInt NoTag) $ "division by zero:" <+> pretty p ->>>>>>> taggedints - -instance SimplifyOp OpDiv x where - simplifyOp _ = na "simplifyOp{OpDiv}" - -instance Pretty x => Pretty (OpDiv x) where - prettyPrec prec op@(OpDiv a b) = prettyPrecBinOp prec [op] a b - -instance VarSymBreakingDescription x => VarSymBreakingDescription (OpDiv x) where - varSymBreakingDescription (OpDiv a b) = JSON.Object $ M.fromList - [ ("type", JSON.String "OpDiv") - , ("children", JSON.Array $ V.fromList - [ varSymBreakingDescription a - , varSymBreakingDescription b - ]) - ] diff --git a/src/Conjure/Language/Expression/Op/Factorial.hs.orig b/src/Conjure/Language/Expression/Op/Factorial.hs.orig deleted file mode 100644 index 6030baca01..0000000000 --- a/src/Conjure/Language/Expression/Op/Factorial.hs.orig +++ /dev/null @@ -1,54 +0,0 @@ -{-# LANGUAGE DeriveGeneric, DeriveDataTypeable, DeriveFunctor, DeriveTraversable, DeriveFoldable #-} - -module Conjure.Language.Expression.Op.Factorial where - -import Conjure.Prelude -import Conjure.Language.Expression.Op.Internal.Common - -import qualified Data.Aeson as JSON -- aeson -import qualified Data.HashMap.Strict as M -- unordered-containers -import qualified Data.Vector as V -- vector - - -data OpFactorial x = OpFactorial x - deriving (Eq, Ord, Show, Data, Functor, Traversable, Foldable, Typeable, Generic) - -instance Serialize x => Serialize (OpFactorial x) -instance Hashable x => Hashable (OpFactorial x) -instance ToJSON x => ToJSON (OpFactorial x) where toJSON = genericToJSON jsonOptions -instance FromJSON x => FromJSON (OpFactorial x) where parseJSON = genericParseJSON jsonOptions - -instance TypeOf x => TypeOf (OpFactorial x) where -<<<<<<< HEAD - typeOf (OpFactorial a) = do TypeInt Nothing <- typeOf a ; return $ TypeInt Nothing -||||||| merged common ancestors - typeOf (OpFactorial a) = do TypeInt <- typeOf a ; return TypeInt -======= - typeOf (OpFactorial a) = do TypeInt NoTag <- typeOf a ; return (TypeInt NoTag) ->>>>>>> taggedints - -instance EvaluateOp OpFactorial where -<<<<<<< HEAD - evaluateOp p | any isUndef (childrenBi p) = return $ mkUndef (TypeInt Nothing) $ "Has undefined children:" <+> pretty p - evaluateOp (OpFactorial x) = ConstantInt Nothing . product . enumFromTo 1 <$> intOut "factorial" x -||||||| merged common ancestors - evaluateOp p | any isUndef (childrenBi p) = return $ mkUndef TypeInt $ "Has undefined children:" <+> pretty p - evaluateOp (OpFactorial x) = ConstantInt . product . enumFromTo 1 <$> intOut "factorial" x -======= - evaluateOp p | any isUndef (childrenBi p) = return $ mkUndef (TypeInt NoTag) $ "Has undefined children:" <+> pretty p - evaluateOp (OpFactorial x) = ConstantInt NoTag . product . enumFromTo 1 <$> intOut "factorial" x ->>>>>>> taggedints - -instance SimplifyOp OpFactorial x where - simplifyOp _ = na "simplifyOp{OpFactorial}" - -instance Pretty x => Pretty (OpFactorial x) where - prettyPrec _ (OpFactorial a) = "factorial" <> prParens (pretty a) - -instance VarSymBreakingDescription x => VarSymBreakingDescription (OpFactorial x) where - varSymBreakingDescription (OpFactorial a) = JSON.Object $ M.fromList - [ ("type", JSON.String "OpFactorial") - , ("children", JSON.Array $ V.fromList - [ varSymBreakingDescription a - ]) - ] diff --git a/src/Conjure/Language/Expression/Op/Flatten.hs.orig b/src/Conjure/Language/Expression/Op/Flatten.hs.orig deleted file mode 100644 index 4026a2f371..0000000000 --- a/src/Conjure/Language/Expression/Op/Flatten.hs.orig +++ /dev/null @@ -1,82 +0,0 @@ -{-# LANGUAGE DeriveGeneric, DeriveDataTypeable, DeriveFunctor, DeriveTraversable, DeriveFoldable, ViewPatterns #-} - -module Conjure.Language.Expression.Op.Flatten where - -import Conjure.Prelude -import Conjure.Language.Expression.Op.Internal.Common - -import qualified Data.Aeson as JSON -- aeson -import qualified Data.HashMap.Strict as M -- unordered-containers -import qualified Data.Vector as V -- vector - - -data OpFlatten x = OpFlatten (Maybe Int) x - deriving (Eq, Ord, Show, Data, Functor, Traversable, Foldable, Typeable, Generic) - -instance Serialize x => Serialize (OpFlatten x) -instance Hashable x => Hashable (OpFlatten x) -instance ToJSON x => ToJSON (OpFlatten x) where toJSON = genericToJSON jsonOptions -instance FromJSON x => FromJSON (OpFlatten x) where parseJSON = genericParseJSON jsonOptions - -instance (TypeOf x, Pretty x) => TypeOf (OpFlatten x) where - typeOf p@(OpFlatten Nothing m) = do - let flattenType (TypeList inner) = flattenType inner - flattenType (TypeMatrix _ inner) = flattenType inner - flattenType ty = ty - ty <- typeOf m - case ty of - TypeList n -> return (TypeList (flattenType n)) - TypeMatrix _ n -> return (TypeList (flattenType n)) - _ -> raiseTypeError p - typeOf p@(OpFlatten (Just n) m) = do - let flattenType lvl ty | lvl < 0 = return ty - flattenType lvl (TypeList inner) = flattenType (lvl-1) inner - flattenType lvl (TypeMatrix _ inner) = flattenType (lvl-1) inner - flattenType _ _ = raiseTypeError $ vcat [pretty p, "Cannot flatten" <+> pretty n <+> "levels."] - ty <- typeOf m - TypeList <$> flattenType n ty - -instance EvaluateOp OpFlatten where - evaluateOp (OpFlatten Nothing m) = do - let flat (viewConstantMatrix -> Just (_, xs)) = concatMap flat xs - flat c = [c] - let flattened = flat m - return (ConstantAbstract $ AbsLitMatrix -<<<<<<< HEAD - (DomainInt Nothing [RangeBounded 1 (fromInt (genericLength flattened))]) -||||||| merged common ancestors - (DomainInt [RangeBounded 1 (fromInt (genericLength flattened))]) -======= - (DomainInt NoTag [RangeBounded 1 (fromInt (genericLength flattened))]) ->>>>>>> taggedints - flattened) - evaluateOp (OpFlatten (Just n) m) = do - let flat lvl c | lvl < 0 = return [c] - flat lvl (viewConstantMatrix -> Just (_, xs)) = concatMapM (flat (lvl-1)) xs - flat _ _ = fail $ "Cannot flatten" <+> pretty n <+> "levels." - flattened <- flat n m - return (ConstantAbstract $ AbsLitMatrix -<<<<<<< HEAD - (DomainInt Nothing [RangeBounded 1 (fromInt (genericLength flattened))]) -||||||| merged common ancestors - (DomainInt [RangeBounded 1 (fromInt (genericLength flattened))]) -======= - (DomainInt NoTag [RangeBounded 1 (fromInt (genericLength flattened))]) ->>>>>>> taggedints - flattened) - -instance SimplifyOp OpFlatten x where - simplifyOp _ = na "simplifyOp{OpFlatten}" - -instance Pretty x => Pretty (OpFlatten x) where - prettyPrec _ (OpFlatten Nothing m) = "flatten" <> prParens (pretty m) - prettyPrec _ (OpFlatten (Just n) m) = "flatten" <> prettyList prParens "," [pretty n, pretty m] - -instance VarSymBreakingDescription x => VarSymBreakingDescription (OpFlatten x) where - varSymBreakingDescription (OpFlatten n m) = JSON.Object $ M.fromList - [ ("type", JSON.String "OpFlatten") - , ("children", JSON.Array $ V.fromList - [ toJSON n - , varSymBreakingDescription m - ]) - ] diff --git a/src/Conjure/Language/Expression/Op/Freq.hs.orig b/src/Conjure/Language/Expression/Op/Freq.hs.orig deleted file mode 100644 index 8171128b44..0000000000 --- a/src/Conjure/Language/Expression/Op/Freq.hs.orig +++ /dev/null @@ -1,63 +0,0 @@ -{-# LANGUAGE DeriveGeneric, DeriveDataTypeable, DeriveFunctor, DeriveTraversable, DeriveFoldable, ViewPatterns #-} - -module Conjure.Language.Expression.Op.Freq where - -import Conjure.Prelude -import Conjure.Language.Expression.Op.Internal.Common - -import qualified Data.Aeson as JSON -- aeson -import qualified Data.HashMap.Strict as M -- unordered-containers -import qualified Data.Vector as V -- vector - - -data OpFreq x = OpFreq x x - deriving (Eq, Ord, Show, Data, Functor, Traversable, Foldable, Typeable, Generic) - -instance Serialize x => Serialize (OpFreq x) -instance Hashable x => Hashable (OpFreq x) -instance ToJSON x => ToJSON (OpFreq x) where toJSON = genericToJSON jsonOptions -instance FromJSON x => FromJSON (OpFreq x) where parseJSON = genericParseJSON jsonOptions - -instance (TypeOf x, Pretty x) => TypeOf (OpFreq x) where - typeOf p@(OpFreq m e) = do - tyM <- typeOf m - tyE <- typeOf e - case tyM of - TypeMSet tyE' -<<<<<<< HEAD - | tyE `typeUnify` tyE' -> return $ TypeInt Nothing -||||||| merged common ancestors - | tyE `typeUnify` tyE' -> return TypeInt -======= - | tyE `typeUnify` tyE' -> return $ TypeInt NoTag ->>>>>>> taggedints - | otherwise -> raiseTypeError $ vcat - [ "The first argument of freq is expected to be a multi-set." - , pretty p - ] - _ -> raiseTypeError p - -instance EvaluateOp OpFreq where -<<<<<<< HEAD - evaluateOp (OpFreq (viewConstantMSet -> Just cs) c) = return $ ConstantInt Nothing $ sum [ 1 | i <- cs, c == i ] -||||||| merged common ancestors - evaluateOp (OpFreq (viewConstantMSet -> Just cs) c) = return $ ConstantInt $ sum [ 1 | i <- cs, c == i ] -======= - evaluateOp (OpFreq (viewConstantMSet -> Just cs) c) = return $ (ConstantInt NoTag) $ sum [ 1 | i <- cs, c == i ] ->>>>>>> taggedints - evaluateOp op = na $ "evaluateOp{OpFreq}:" <++> pretty (show op) - -instance SimplifyOp OpFreq x where - simplifyOp _ = na "simplifyOp{OpFreq}" - -instance Pretty x => Pretty (OpFreq x) where - prettyPrec _ (OpFreq a b) = "freq" <> prettyList prParens "," [a,b] - -instance VarSymBreakingDescription x => VarSymBreakingDescription (OpFreq x) where - varSymBreakingDescription (OpFreq a b) = JSON.Object $ M.fromList - [ ("type", JSON.String "OpFreq") - , ("children", JSON.Array $ V.fromList - [ varSymBreakingDescription a - , varSymBreakingDescription b - ]) - ] diff --git a/src/Conjure/Language/Expression/Op/Geq.hs.orig b/src/Conjure/Language/Expression/Op/Geq.hs.orig deleted file mode 100644 index 7308c1b804..0000000000 --- a/src/Conjure/Language/Expression/Op/Geq.hs.orig +++ /dev/null @@ -1,59 +0,0 @@ -{-# LANGUAGE DeriveGeneric, DeriveDataTypeable, DeriveFunctor, DeriveTraversable, DeriveFoldable #-} - -module Conjure.Language.Expression.Op.Geq where - -import Conjure.Prelude -import Conjure.Language.Expression.Op.Internal.Common - -import qualified Data.Aeson as JSON -- aeson -import qualified Data.HashMap.Strict as M -- unordered-containers -import qualified Data.Vector as V -- vector - - -data OpGeq x = OpGeq x x - deriving (Eq, Ord, Show, Data, Functor, Traversable, Foldable, Typeable, Generic) - -instance Serialize x => Serialize (OpGeq x) -instance Hashable x => Hashable (OpGeq x) -instance ToJSON x => ToJSON (OpGeq x) where toJSON = genericToJSON jsonOptions -instance FromJSON x => FromJSON (OpGeq x) where parseJSON = genericParseJSON jsonOptions - -instance BinaryOperator (OpGeq x) where - opLexeme _ = L_Geq - -instance (TypeOf x, Pretty x) => TypeOf (OpGeq x) where -<<<<<<< HEAD - typeOf p@(OpGeq a b) = sameToSameToBool p a b - [TypeBool, TypeInt Nothing, TypeEnum "?"] -||||||| merged common ancestors - typeOf p@(OpGeq a b) = sameToSameToBool p a b - [TypeBool, TypeInt, TypeEnum "?"] -======= - typeOf p@(OpGeq a b) = do - ta <- typeOf a - tb <- typeOf b - case (ta, tb) of - (TypeInt (TagEnum aTag), TypeInt (TagEnum bTag)) | aTag == bTag - -> return TypeBool - _ -> sameToSameToBool p a b - [TypeBool, TypeInt NoTag, TypeEnum "?"] - ->>>>>>> taggedints - -instance EvaluateOp OpGeq where - evaluateOp (OpGeq x y) = return $ ConstantBool $ x >= y - -instance SimplifyOp OpGeq x where - simplifyOp _ = na "simplifyOp{OpGeq}" - -instance Pretty x => Pretty (OpGeq x) where - prettyPrec prec op@(OpGeq a b) = prettyPrecBinOp prec [op] a b - -instance VarSymBreakingDescription x => VarSymBreakingDescription (OpGeq x) where - varSymBreakingDescription (OpGeq a b) = JSON.Object $ M.fromList - [ ("type", JSON.String "OpGeq") - , ("children", JSON.Array $ V.fromList - [ varSymBreakingDescription a - , varSymBreakingDescription b - ]) - ] diff --git a/src/Conjure/Language/Expression/Op/Gt.hs.orig b/src/Conjure/Language/Expression/Op/Gt.hs.orig deleted file mode 100644 index f69a4a0aed..0000000000 --- a/src/Conjure/Language/Expression/Op/Gt.hs.orig +++ /dev/null @@ -1,58 +0,0 @@ -{-# LANGUAGE DeriveGeneric, DeriveDataTypeable, DeriveFunctor, DeriveTraversable, DeriveFoldable #-} - -module Conjure.Language.Expression.Op.Gt where - -import Conjure.Prelude -import Conjure.Language.Expression.Op.Internal.Common - -import qualified Data.Aeson as JSON -- aeson -import qualified Data.HashMap.Strict as M -- unordered-containers -import qualified Data.Vector as V -- vector - - -data OpGt x = OpGt x x - deriving (Eq, Ord, Show, Data, Functor, Traversable, Foldable, Typeable, Generic) - -instance Serialize x => Serialize (OpGt x) -instance Hashable x => Hashable (OpGt x) -instance ToJSON x => ToJSON (OpGt x) where toJSON = genericToJSON jsonOptions -instance FromJSON x => FromJSON (OpGt x) where parseJSON = genericParseJSON jsonOptions - -instance BinaryOperator (OpGt x) where - opLexeme _ = L_Gt - -instance (TypeOf x, Pretty x) => TypeOf (OpGt x) where -<<<<<<< HEAD - typeOf p@(OpGt a b) = sameToSameToBool p a b - [TypeBool, TypeInt Nothing, TypeEnum "?"] -||||||| merged common ancestors - typeOf p@(OpGt a b) = sameToSameToBool p a b - [TypeBool, TypeInt, TypeEnum "?"] -======= - typeOf p@(OpGt a b) = do - ta <- typeOf a - tb <- typeOf b - case (ta, tb) of - (TypeInt (TagEnum aTag), TypeInt (TagEnum bTag)) | aTag == bTag - -> return TypeBool - _ -> sameToSameToBool p a b - [TypeBool, TypeInt NoTag, TypeEnum "?"] ->>>>>>> taggedints - -instance EvaluateOp OpGt where - evaluateOp (OpGt x y) = return $ ConstantBool $ x > y - -instance SimplifyOp OpGt x where - simplifyOp _ = na "simplifyOp{OpGt}" - -instance Pretty x => Pretty (OpGt x) where - prettyPrec prec op@(OpGt a b) = prettyPrecBinOp prec [op] a b - -instance VarSymBreakingDescription x => VarSymBreakingDescription (OpGt x) where - varSymBreakingDescription (OpGt a b) = JSON.Object $ M.fromList - [ ("type", JSON.String "OpGt") - , ("children", JSON.Array $ V.fromList - [ varSymBreakingDescription a - , varSymBreakingDescription b - ]) - ] diff --git a/src/Conjure/Language/Expression/Op/Hist.hs.orig b/src/Conjure/Language/Expression/Op/Hist.hs.orig deleted file mode 100644 index fd57c93acb..0000000000 --- a/src/Conjure/Language/Expression/Op/Hist.hs.orig +++ /dev/null @@ -1,77 +0,0 @@ -{-# LANGUAGE DeriveGeneric, DeriveDataTypeable, DeriveFunctor, DeriveTraversable, DeriveFoldable, ViewPatterns #-} - -module Conjure.Language.Expression.Op.Hist where - -import Conjure.Prelude -import Conjure.Language.Expression.Op.Internal.Common - -import qualified Data.Aeson as JSON -- aeson -import qualified Data.HashMap.Strict as M -- unordered-containers -import qualified Data.Vector as V -- vector - - -data OpHist x = OpHist x - deriving (Eq, Ord, Show, Data, Functor, Traversable, Foldable, Typeable, Generic) - -instance Serialize x => Serialize (OpHist x) -instance Hashable x => Hashable (OpHist x) -instance ToJSON x => ToJSON (OpHist x) where toJSON = genericToJSON jsonOptions -instance FromJSON x => FromJSON (OpHist x) where parseJSON = genericParseJSON jsonOptions - -instance (TypeOf x, Pretty x) => TypeOf (OpHist x) where - typeOf p@(OpHist a) = do - tyA <- typeOf a - case tyA of -<<<<<<< HEAD - TypeMSet aInner -> return $ TypeMatrix (TypeInt Nothing) $ TypeTuple [aInner, TypeInt Nothing] - TypeMatrix _ aInner -> return $ TypeMatrix (TypeInt Nothing) $ TypeTuple [aInner, TypeInt Nothing] - TypeList aInner -> return $ TypeMatrix (TypeInt Nothing) $ TypeTuple [aInner, TypeInt Nothing] -||||||| merged common ancestors - TypeMSet aInner -> return $ TypeMatrix TypeInt $ TypeTuple [aInner, TypeInt] - TypeMatrix _ aInner -> return $ TypeMatrix TypeInt $ TypeTuple [aInner, TypeInt] - TypeList aInner -> return $ TypeMatrix TypeInt $ TypeTuple [aInner, TypeInt] -======= - TypeMSet aInner -> return $ TypeMatrix (TypeInt NoTag) $ TypeTuple [aInner, (TypeInt NoTag)] - TypeMatrix _ aInner -> return $ TypeMatrix (TypeInt NoTag) $ TypeTuple [aInner, (TypeInt NoTag)] - TypeList aInner -> return $ TypeMatrix (TypeInt NoTag) $ TypeTuple [aInner, (TypeInt NoTag)] ->>>>>>> taggedints - _ -> raiseTypeError p - -instance EvaluateOp OpHist where - evaluateOp (OpHist (viewConstantMSet -> Just cs)) = return $ ConstantAbstract $ AbsLitMatrix -<<<<<<< HEAD - (DomainInt Nothing [RangeBounded 1 (fromInt $ genericLength $ histogram cs)]) - [ ConstantAbstract $ AbsLitTuple [e, ConstantInt Nothing n] | (e, n) <- histogram cs ] -||||||| merged common ancestors - (DomainInt [RangeBounded 1 (fromInt $ genericLength $ histogram cs)]) - [ ConstantAbstract $ AbsLitTuple [e, ConstantInt n] | (e, n) <- histogram cs ] -======= - (DomainInt NoTag [RangeBounded 1 (fromInt $ genericLength $ histogram cs)]) - [ ConstantAbstract $ AbsLitTuple [e, ConstantInt NoTag n] | (e, n) <- histogram cs ] ->>>>>>> taggedints - evaluateOp (OpHist (viewConstantMatrix -> Just (_, cs))) = return $ ConstantAbstract $ AbsLitMatrix -<<<<<<< HEAD - (DomainInt Nothing [RangeBounded 1 (fromInt $ genericLength $ histogram cs)]) - [ ConstantAbstract $ AbsLitTuple [e, ConstantInt Nothing n] | (e, n) <- histogram cs ] -||||||| merged common ancestors - (DomainInt [RangeBounded 1 (fromInt $ genericLength $ histogram cs)]) - [ ConstantAbstract $ AbsLitTuple [e, ConstantInt n] | (e, n) <- histogram cs ] -======= - (DomainInt NoTag [RangeBounded 1 (fromInt $ genericLength $ histogram cs)]) - [ ConstantAbstract $ AbsLitTuple [e, ConstantInt NoTag n] | (e, n) <- histogram cs ] ->>>>>>> taggedints - evaluateOp op = na $ "evaluateOp{OpHist}:" <++> pretty (show op) - -instance SimplifyOp OpHist x where - simplifyOp _ = na "simplifyOp{OpHist}" - -instance Pretty x => Pretty (OpHist x) where - prettyPrec _ (OpHist a) = "hist" <> prParens (pretty a) - -instance VarSymBreakingDescription x => VarSymBreakingDescription (OpHist x) where - varSymBreakingDescription (OpHist a) = JSON.Object $ M.fromList - [ ("type", JSON.String "OpHist") - , ("children", JSON.Array $ V.fromList - [ varSymBreakingDescription a - ]) - ] diff --git a/src/Conjure/Language/Expression/Op/Image.hs.orig b/src/Conjure/Language/Expression/Op/Image.hs.orig deleted file mode 100644 index e850be6e9a..0000000000 --- a/src/Conjure/Language/Expression/Op/Image.hs.orig +++ /dev/null @@ -1,91 +0,0 @@ -{-# LANGUAGE DeriveGeneric, DeriveDataTypeable, DeriveFunctor, DeriveTraversable, DeriveFoldable, ViewPatterns #-} - -module Conjure.Language.Expression.Op.Image where - -import Conjure.Prelude -import Conjure.Language.Expression.Op.Internal.Common - -import qualified Data.Aeson as JSON -- aeson -import qualified Data.HashMap.Strict as M -- unordered-containers -import qualified Data.Vector as V -- vector - - -data OpImage x = OpImage x x - deriving (Eq, Ord, Show, Data, Functor, Traversable, Foldable, Typeable, Generic) - -instance Serialize x => Serialize (OpImage x) -instance Hashable x => Hashable (OpImage x) -instance ToJSON x => ToJSON (OpImage x) where toJSON = genericToJSON jsonOptions -instance FromJSON x => FromJSON (OpImage x) where parseJSON = genericParseJSON jsonOptions - -instance (TypeOf x, Pretty x) => TypeOf (OpImage x) where - typeOf p@(OpImage f x) = do - tyF <- typeOf f - (from, to) <- case tyF of - TypeFunction from to -> return (from, to) -<<<<<<< HEAD - TypeSequence to -> return (TypeInt Nothing, to) -||||||| merged common ancestors - TypeSequence to -> return (TypeInt, to) -======= - TypeSequence to -> return (TypeInt NoTag, to) ->>>>>>> taggedints - _ -> raiseTypeError $ "(function application)" <+> pretty p - xTy <- typeOf x - if typesUnify [xTy, from] - then return to - else raiseTypeError $ vcat - [ pretty p - , "function :" <+> pretty f - , "function type:" <+> pretty (TypeFunction from to) - , "argument :" <+> pretty x - , "argument type:" <+> pretty xTy - ] - -instance EvaluateOp OpImage where - evaluateOp (OpImage f@(viewConstantFunction -> Just xs) a) = - case [ y | (x,y) <- xs, a == x ] of - [y] -> return y - [] -> do - TypeFunction _ tyTo <- typeOf f - return $ mkUndef tyTo $ vcat - [ "Function is not defined at this point:" <+> pretty a - , "Function value:" <+> pretty f - ] - _ -> do - TypeFunction _ tyTo <- typeOf f - return $ mkUndef tyTo $ vcat - [ "Function is multiply defined at this point:" <+> pretty a - , "Function value:" <+> pretty f - ] - evaluateOp (OpImage f@(viewConstantSequence -> Just xs) a) = - case [ y | (x,y) <- zip allNats xs, a == fromInt x ] of - [y] -> return y - [] -> do - TypeSequence tyTo <- typeOf f - return $ mkUndef tyTo $ vcat - [ "Sequence is not defined at this point:" <+> pretty a - , "Sequence value:" <+> pretty f - ] - _ -> do - TypeSequence tyTo <- typeOf f - return $ mkUndef tyTo $ vcat - [ "Sequence is multiply defined at this point:" <+> pretty a - , "Sequence value:" <+> pretty f - ] - evaluateOp op = na $ "evaluateOp{OpImage}:" <++> pretty (show op) - -instance SimplifyOp OpImage x where - simplifyOp _ = na "simplifyOp{OpImage}" - -instance Pretty x => Pretty (OpImage x) where - prettyPrec _ (OpImage a b) = "image" <> prettyList prParens "," [a,b] - -instance VarSymBreakingDescription x => VarSymBreakingDescription (OpImage x) where - varSymBreakingDescription (OpImage a b) = JSON.Object $ M.fromList - [ ("type", JSON.String "OpImage") - , ("children", JSON.Array $ V.fromList - [ varSymBreakingDescription a - , varSymBreakingDescription b - ]) - ] diff --git a/src/Conjure/Language/Expression/Op/ImageSet.hs.orig b/src/Conjure/Language/Expression/Op/ImageSet.hs.orig deleted file mode 100644 index d4565a88ca..0000000000 --- a/src/Conjure/Language/Expression/Op/ImageSet.hs.orig +++ /dev/null @@ -1,71 +0,0 @@ -{-# LANGUAGE DeriveGeneric, DeriveDataTypeable, DeriveFunctor, DeriveTraversable, DeriveFoldable, ViewPatterns #-} - -module Conjure.Language.Expression.Op.ImageSet where - -import Conjure.Prelude -import Conjure.Language.Expression.Op.Internal.Common - -import qualified Data.Aeson as JSON -- aeson -import qualified Data.HashMap.Strict as M -- unordered-containers -import qualified Data.Vector as V -- vector - - -data OpImageSet x = OpImageSet x x - deriving (Eq, Ord, Show, Data, Functor, Traversable, Foldable, Typeable, Generic) - -instance Serialize x => Serialize (OpImageSet x) -instance Hashable x => Hashable (OpImageSet x) -instance ToJSON x => ToJSON (OpImageSet x) where toJSON = genericToJSON jsonOptions -instance FromJSON x => FromJSON (OpImageSet x) where parseJSON = genericParseJSON jsonOptions - -instance (TypeOf x, Pretty x) => TypeOf (OpImageSet x) where - typeOf p@(OpImageSet f x) = do - tyF <- typeOf f - (from, to) <- case tyF of - TypeFunction from to -> return (from, to) -<<<<<<< HEAD - TypeSequence to -> return (TypeInt Nothing, to) -||||||| merged common ancestors - TypeSequence to -> return (TypeInt, to) -======= - TypeSequence to -> return (TypeInt NoTag, to) ->>>>>>> taggedints - _ -> raiseTypeError $ "(function application)" <+> pretty p - xTy <- typeOf x - if typesUnify [xTy, from] - then return (TypeSet to) - else raiseTypeError $ vcat - [ pretty p - , "f :" <+> pretty f - , "f type:" <+> pretty (TypeFunction from to) - , "x :" <+> pretty x - , "x type:" <+> pretty xTy - ] - -instance EvaluateOp OpImageSet where - evaluateOp (OpImageSet f@(viewConstantFunction -> Just xs) a) = do - TypeFunction _ tyTo <- typeOf f - case [ y | (x,y) <- xs, a == x ] of - [y] -> return $ ConstantAbstract $ AbsLitSet [y] - _ -> return $ TypedConstant (ConstantAbstract $ AbsLitSet []) (TypeSet tyTo) - evaluateOp (OpImageSet f@(viewConstantSequence -> Just xs) a) = do - TypeSequence tyTo <- typeOf f - case [ y | (x,y) <- zip allNats xs, a == fromInt x ] of - [y] -> return $ ConstantAbstract $ AbsLitSet [y] - _ -> return $ TypedConstant (ConstantAbstract $ AbsLitSet []) (TypeSet tyTo) - evaluateOp op = na $ "evaluateOp{OpImageSet}:" <++> pretty (show op) - -instance SimplifyOp OpImageSet x where - simplifyOp _ = na "simplifyOp{OpImageSet}" - -instance Pretty x => Pretty (OpImageSet x) where - prettyPrec _ (OpImageSet a b) = "imageSet" <> prettyList prParens "," [a,b] - -instance VarSymBreakingDescription x => VarSymBreakingDescription (OpImageSet x) where - varSymBreakingDescription (OpImageSet a b) = JSON.Object $ M.fromList - [ ("type", JSON.String "OpImageSet") - , ("children", JSON.Array $ V.fromList - [ varSymBreakingDescription a - , varSymBreakingDescription b - ]) - ] diff --git a/src/Conjure/Language/Expression/Op/Indexing.hs.orig b/src/Conjure/Language/Expression/Op/Indexing.hs.orig deleted file mode 100644 index 1aa6431aa8..0000000000 --- a/src/Conjure/Language/Expression/Op/Indexing.hs.orig +++ /dev/null @@ -1,153 +0,0 @@ -{-# LANGUAGE DeriveGeneric, DeriveDataTypeable, DeriveFunctor, DeriveTraversable, DeriveFoldable, ViewPatterns #-} - -module Conjure.Language.Expression.Op.Indexing where - -import Conjure.Prelude -import Conjure.Bug -import Conjure.Language.Expression.Op.Internal.Common - -import qualified Data.Aeson as JSON -- aeson -import qualified Data.HashMap.Strict as M -- unordered-containers -import qualified Data.Vector as V -- vector - --- pretty -import qualified Text.PrettyPrint as Pr ( cat ) - - -data OpIndexing x = OpIndexing x x - deriving (Eq, Ord, Show, Data, Functor, Traversable, Foldable, Typeable, Generic) - -instance Serialize x => Serialize (OpIndexing x) -instance Hashable x => Hashable (OpIndexing x) -instance ToJSON x => ToJSON (OpIndexing x) where toJSON = genericToJSON jsonOptions -instance FromJSON x => FromJSON (OpIndexing x) where parseJSON = genericParseJSON jsonOptions - -instance (TypeOf x, Pretty x, ExpressionLike x, ReferenceContainer x) => TypeOf (OpIndexing x) where - typeOf p@(OpIndexing m i) = do - tyM <- typeOf m - tyI <- typeOf i - case tyM of - TypeMatrix tyIndex inn - | typesUnify [tyIndex, tyI] -> return inn - | otherwise -> fail $ "Indexing with inappropriate type:" <++> vcat - [ "The expression:" <+> pretty p - , "Indexing:" <+> pretty m - , "Expected type of index:" <+> pretty tyIndex - , "Actual type of index :" <+> pretty tyI - ] - TypeList inn -<<<<<<< HEAD - | typesUnify [TypeInt Nothing, tyI] -> return inn -||||||| merged common ancestors - | typesUnify [TypeInt, tyI] -> return inn -======= - | typesUnify [TypeInt NoTag, tyI] -> return inn ->>>>>>> taggedints - | otherwise -> fail $ "Indexing with inappropriate type:" <++> vcat - [ "The expression:" <+> pretty p - , "Indexing:" <+> pretty m -<<<<<<< HEAD - , "Expected type of index:" <+> pretty (TypeInt Nothing) -||||||| merged common ancestors - , "Expected type of index:" <+> pretty TypeInt -======= - , "Expected type of index:" <+> pretty (TypeInt NoTag) ->>>>>>> taggedints - , "Actual type of index :" <+> pretty tyI - ] - TypeTuple inns -> do - TypeInt NoTag <- typeOf i - case intOut "OpIndexing" i of - Nothing -> fail $ "Tuples can only be indexed by constants:" <++> pretty p - Just iInt | iInt <= 0 || iInt > genericLength inns -> fail $ "Out of bounds tuple indexing:" <++> pretty p - | otherwise -> return (at inns (fromInteger (iInt-1))) - TypeRecord inns -> do - nm <- nameOut i - case lookup nm inns of - Nothing -> fail $ "Record indexing with non-member field:" <++> vcat - [ "The expression:" <+> pretty p - , "Indexing:" <+> pretty m - , "With type:" <+> pretty tyM - ] - Just ty -> return ty - TypeVariant inns -> do - nm <- nameOut i - case lookup nm inns of - Nothing -> fail $ "Variant indexing with non-member field:" <++> vcat - [ "The expression:" <+> pretty p - , "Indexing:" <+> pretty m - , "With type:" <+> pretty tyM - ] - Just ty -> return ty - _ -> fail $ "Indexing something other than a matrix or a tuple:" <++> vcat - [ "The expression:" <+> pretty p - , "Indexing:" <+> pretty m - , "With type:" <+> pretty tyM - ] - -instance EvaluateOp OpIndexing where - evaluateOp p@(OpIndexing m i) | isUndef i = do - ty <- typeOf m - tyTo <- case ty of TypeMatrix _ tyTo -> return tyTo - TypeList tyTo -> return tyTo - _ -> fail "evaluateOp{OpIndexing}" - return $ mkUndef tyTo $ "Has undefined children (index):" <+> pretty p -<<<<<<< HEAD - evaluateOp (OpIndexing m@(viewConstantMatrix -> Just (DomainInt _ index, vals)) (ConstantInt _ x)) = do -||||||| merged common ancestors - evaluateOp (OpIndexing m@(viewConstantMatrix -> Just (DomainInt index, vals)) (ConstantInt x)) = do -======= - evaluateOp (OpIndexing m@(viewConstantMatrix -> Just (DomainInt tagd index, vals)) (ConstantInt tagc x)) | tagd == tagc = do ->>>>>>> taggedints - ty <- typeOf m - tyTo <- case ty of TypeMatrix _ tyTo -> return tyTo - TypeList tyTo -> return tyTo - _ -> fail "evaluateOp{OpIndexing}" - indexVals <- valuesInIntDomain index - case [ v | (i, v) <- zip indexVals vals, i == x ] of - [v] -> return v - [] -> return $ mkUndef tyTo $ vcat - [ "Matrix is not defined at this point:" <+> pretty x - , "Matrix value:" <+> pretty m - ] - _ -> return $ mkUndef tyTo $ vcat - [ "Matrix is multiply defined at this point:" <+> pretty x - , "Matrix value:" <+> pretty m - ] -<<<<<<< HEAD - evaluateOp (OpIndexing (viewConstantTuple -> Just vals) (ConstantInt _ x)) = return (at vals (fromInteger (x-1))) -||||||| merged common ancestors - evaluateOp (OpIndexing (viewConstantTuple -> Just vals) (ConstantInt x)) = return (at vals (fromInteger (x-1))) -======= - evaluateOp (OpIndexing (viewConstantTuple -> Just vals) (ConstantInt NoTag x)) = return (at vals (fromInteger (x-1))) ->>>>>>> taggedints - evaluateOp rec@(OpIndexing (viewConstantRecord -> Just vals) (ConstantField name _)) = - case lookup name vals of - Nothing -> bug $ vcat - [ "Record doesn't have a member with this name:" <+> pretty name - , "Record:" <+> pretty rec - ] - Just val -> return val - evaluateOp var@(OpIndexing (viewConstantVariant -> Just (_, name', x)) (ConstantField name ty)) = - if name == name' - then return x - else return $ mkUndef ty $ vcat - [ "Variant isn't set to a member with this name:" <+> pretty name - , "Variant:" <+> pretty var - ] - evaluateOp op = na $ "evaluateOp{OpIndexing}:" <++> pretty (show op) - -instance SimplifyOp OpIndexing x where - simplifyOp _ = na "simplifyOp{OpIndexing}" - -instance Pretty x => Pretty (OpIndexing x) where - prettyPrec _ (OpIndexing a b) = Pr.cat [pretty a, nest 4 (prBrackets (pretty b))] - -instance VarSymBreakingDescription x => VarSymBreakingDescription (OpIndexing x) where - varSymBreakingDescription (OpIndexing a b) = JSON.Object $ M.fromList - [ ("type", JSON.String "OpIndexing") - , ("children", JSON.Array $ V.fromList - [ varSymBreakingDescription a - , varSymBreakingDescription b - ]) - ] diff --git a/src/Conjure/Language/Expression/Op/Internal/Common.hs.orig b/src/Conjure/Language/Expression/Op/Internal/Common.hs.orig deleted file mode 100644 index 2d28a55980..0000000000 --- a/src/Conjure/Language/Expression/Op/Internal/Common.hs.orig +++ /dev/null @@ -1,334 +0,0 @@ -{-# LANGUAGE ViewPatterns #-} - -module Conjure.Language.Expression.Op.Internal.Common - ( module X - - , EvaluateOp(..) - , SimplifyOp(..) - , BinaryOperator(..) - , boolsOut, intsOut - - , prettyPrecBinOp - , Fixity(..), operators, functionals - , EssenceOperatorParsingDescr(..) - - , raiseTypeError - - , intToInt - , intToIntToInt - , boolToBoolToBool - , sameToSameToBool - , sameToSameToSame - - ) where - --- conjure -import Conjure.Prelude -import Conjure.Bug -import Conjure.Language.Name as X -import Conjure.Language.AbstractLiteral as X -import Conjure.Language.Constant as X -import Conjure.Language.Type as X -import Conjure.Language.Domain as X -import Conjure.Language.TypeOf as X -import Conjure.Language.Pretty as X -import Conjure.Language.AdHoc as X -import Conjure.Language.Lexer as X ( Lexeme(..), textToLexeme, lexemeFace ) - - --- | Assume: the input is already normalised. --- Make sure the output is normalised. -class EvaluateOp op where - evaluateOp :: MonadFail m => op Constant -> m Constant - -class SimplifyOp op x where - simplifyOp :: ( MonadFail m - , Eq x - , Num x - , ExpressionLike x - ) => op x -- the input - -> m x -- the simplified output (or failure if it cannot be simplified) - -class BinaryOperator op where - opLexeme :: proxy op -> Lexeme - --- | just the operator not the arguments -opPretty :: BinaryOperator op => proxy op -> Doc -opPretty = lexemeFace . opLexeme - -opFixityPrec :: BinaryOperator op => proxy op -> (Fixity, Int) -opFixityPrec op = - case [ (f,p) | (Binary l f, p) <- operators, l == opLexeme op ] of - [x] -> x - _ -> bug "opFixityPrec" - -prettyPrecBinOp :: (BinaryOperator op, Pretty x) => Int -> proxy op -> x -> x -> Doc -prettyPrecBinOp envPrec op a b = - let - (fixity, prec) = opFixityPrec op - in - case fixity of - FLeft -> parensIf (envPrec > prec) $ fsep [ prettyPrec prec a - , opPretty op - , prettyPrec (prec+1) b - ] - FNone -> parensIf (envPrec > prec) $ fsep [ prettyPrec (prec+1) a - , opPretty op - , prettyPrec (prec+1) b - ] - FRight -> parensIf (envPrec > prec) $ fsep [ prettyPrec (prec+1) a - , opPretty op - , prettyPrec prec b - ] - -intToInt :: (MonadFail m, TypeOf a, Pretty p) => p -> a -> m Type -intToInt p a = do - tya <- typeOf a - case tya of -<<<<<<< HEAD -<<<<<<< HEAD - TypeInt name -> return $ TypeInt name - _ -> fail $ vcat -======= - TypeInt t -> return (TypeInt t) - _ -> fail $ vcat ->>>>>>> f8c15eb3160b509a17e3d70103b237ea8d666c04 -||||||| merged common ancestors - TypeInt -> return TypeInt - _ -> fail $ vcat -======= - TypeInt t -> return (TypeInt t) - _ -> fail $ vcat ->>>>>>> taggedints - [ "When type checking:" <+> pretty p - , "Argument expected to be an int, but it is:" <++> pretty tya - ] - - -intToIntToInt :: (MonadFail m, TypeOf a, Pretty p) => p -> a -> a -> m Type -intToIntToInt p a b = do - tya <- typeOf a - tyb <- typeOf b - case (tya, tyb) of -<<<<<<< HEAD -<<<<<<< HEAD - (TypeInt namea, TypeInt nameb) -> - if namea == nameb - then return $ TypeInt namea - else fail$ vcat - [ "When type checking:" <+> pretty p - , "TypeInt names are not equal:" <+> pretty namea <+> pretty nameb - ] -======= - (TypeInt aTag, TypeInt bTag) - | aTag == bTag -> return (TypeInt aTag) - | otherwise -> fail $ vcat - [ "When type checking:" <+> pretty p - , "Arguments have different tags." - ] ->>>>>>> f8c15eb3160b509a17e3d70103b237ea8d666c04 - (_, TypeInt _) -> fail $ vcat -||||||| merged common ancestors - (TypeInt, TypeInt) -> return TypeInt - (_, TypeInt) -> fail $ vcat -======= - (TypeInt aTag, TypeInt bTag) - | aTag == bTag -> return (TypeInt aTag) - | otherwise -> fail $ vcat - [ "When type checking:" <+> pretty p - , "Arguments have different tags." - ] - (_, TypeInt _) -> fail $ vcat ->>>>>>> taggedints - [ "When type checking:" <+> pretty p - , "First argument expected to be an int, but it is:" <++> pretty tya - ] - _ -> fail $ vcat - [ "When type checking:" <+> pretty p - , "Second argument expected to be an int, but it is:" <++> pretty tyb - ] - -boolToBoolToBool :: (MonadFail m, TypeOf a, Pretty p) => p -> a -> a -> m Type -boolToBoolToBool p a b = do - tya <- typeOf a - tyb <- typeOf b - case (tya, tyb) of - (TypeBool, TypeBool) -> return TypeBool - (_, TypeBool) -> fail $ vcat - [ "When type checking:" <+> pretty p - , "First argument expected to be a bool, but it is:" <++> pretty tya - ] - _ -> fail $ vcat - [ "When type checking:" <+> pretty p - , "Second argument expected to be a bool, but it is:" <++> pretty tyb - ] - - -sameToSameToBool :: (MonadFail m, TypeOf a, Pretty a, Pretty p) => p -> a -> a -> [Type] -> m Type -sameToSameToBool p a b tys = do - tyA <- typeOf a - tyB <- typeOf b - let tyAB = mostDefined [tyA,tyB] - case (tyA `typeUnify` tyB, null tys || any (typeUnify tyAB) tys) of - (True, True) -> return TypeBool - (False, _) -> fail $ vcat - [ "When type checking:" <+> pretty p - , "Cannot unify the types of the following." - , "lhs :" <+> pretty a - , "type of lhs:" <+> pretty tyA - , "rhs :" <+> pretty b - , "type of rhs:" <+> pretty tyB - ] - (_, False) -> fail $ vcat - [ "When type checking:" <+> pretty p - , "Arguments expected to be one of these types:" <+> prettyList id "," tys - , "lhs :" <+> pretty a - , "type of lhs:" <+> pretty tyA - , "rhs :" <+> pretty b - , "type of rhs:" <+> pretty tyB - ] - -sameToSameToSame :: (MonadFail m, TypeOf a, Pretty a, Pretty p) => p -> a -> a -> [Type] -> m Type -sameToSameToSame p a b tys = do - tyA <- typeOf a - tyB <- typeOf b - let tyAB = mostDefined [tyA,tyB] - case (tyA `typeUnify` tyB, null tys || any (typeUnify tyAB) tys) of - (True, True) -> return tyAB - (False, _) -> fail $ vcat - [ "When type checking:" <+> pretty p - , "Cannot unify the types of the following." - , "lhs :" <+> pretty a - , "type of lhs:" <+> pretty tyA - , "rhs :" <+> pretty b - , "type of rhs:" <+> pretty tyB - ] - (_, False) -> fail $ vcat - [ "When type checking:" <+> pretty p - , "Arguments expected to be one of these types:" <+> prettyList id "," tys - , "lhs :" <+> pretty a - , "type of lhs:" <+> pretty tyA - , "rhs :" <+> pretty b - , "type of rhs:" <+> pretty tyB - ] - -data Fixity = FNone | FLeft | FRight - deriving Show - -data EssenceOperatorParsingDescr = Binary Lexeme Fixity | UnaryPrefix Lexeme - -operators :: [(EssenceOperatorParsingDescr, Int)] -operators = - [ ( Binary L_Plus FLeft , 600 ) - , ( Binary L_PlusForced FLeft , 600 ) - , ( Binary L_Minus FLeft , 600 ) - , ( Binary L_Times FLeft , 700 ) - , ( Binary L_Div FLeft , 700 ) - , ( Binary L_Mod FLeft , 700 ) - , ( Binary L_Pow FRight , 2001 ) - , ( Binary L_Lt FNone , 400 ) - , ( Binary L_Leq FNone , 400 ) - , ( Binary L_Gt FNone , 400 ) - , ( Binary L_Geq FNone , 400 ) - , ( Binary L_Neq FNone , 400 ) - , ( Binary L_Eq FNone , 400 ) - , ( Binary L_Or FLeft , 110 ) - , ( Binary L_And FLeft , 120 ) - , ( Binary L_Imply FNone , 50 ) - , ( Binary L_Iff FNone , 50 ) - , ( Binary L_union FLeft , 600 ) - , ( Binary L_intersect FLeft , 700 ) - , ( Binary L_subset FNone , 400 ) - , ( Binary L_subsetEq FNone , 400 ) - , ( Binary L_supset FNone , 400 ) - , ( Binary L_supsetEq FNone , 400 ) - , ( Binary L_subsequence FNone , 400 ) - , ( Binary L_substring FNone , 400 ) - , ( Binary L_in FNone , 550 ) - , ( Binary L_HasRepr FNone , 10 ) - , ( Binary L_HasType FNone , 10 ) - , ( Binary L_HasDomain FNone , 10 ) - , ( Binary L_LexLt FNone , 400 ) - , ( Binary L_LexLeq FNone , 400 ) - , ( Binary L_LexGt FNone , 400 ) - , ( Binary L_LexGeq FNone , 400 ) - , ( Binary L_DotLt FNone , 400 ) - , ( Binary L_DotLeq FNone , 400 ) - , ( Binary L_DotGt FNone , 400 ) - , ( Binary L_DotGeq FNone , 400 ) - , ( Binary L_TildeLt FNone , 400 ) - , ( Binary L_TildeLeq FNone , 400 ) - , ( Binary L_TildeGt FNone , 400 ) - , ( Binary L_TildeGeq FNone , 400 ) - , ( UnaryPrefix L_Minus , 2000 ) - , ( UnaryPrefix L_ExclamationMark , 2000 ) - ] - -functionals :: [Lexeme] -functionals = - [ L_toInt - , L_min - , L_max - , L_allDiff - , L_alldifferent_except - , L_apply - , L_catchUndef - , L_dontCare - , L_hist - , L_factorial - - , L_toSet - , L_toMSet - , L_toRelation - , L_defined - , L_range - , L_restrict - , L_image - , L_imageSet - , L_preImage - , L_inverse - , L_together - , L_apart - , L_party - , L_participants - , L_parts - , L_permute - , L_permutationTuples - , L_freq - , L_toInt - , L_flatten - , L_concatenate - , L_normIndices - , L_indices - , L_inverse - - , L_true - - , LIdentifier "and" - , LIdentifier "or" - , LIdentifier "sum" - , LIdentifier "product" - , LIdentifier "xor" - - , L_active - - , L_pred - , L_succ - - , L_powerSet - - ] - - -boolsOut :: MonadFail m => Constant -> m [Bool] -boolsOut (viewConstantMatrix -> Just (_, cs)) = concat <$> mapM boolsOut cs -boolsOut b = return <$> boolOut b - -intsOut :: MonadFail m => Doc -> Constant -> m [Integer] -intsOut doc (viewConstantMatrix -> Just (_, cs)) = concat <$> mapM (intsOut doc) cs -intsOut doc (viewConstantSet -> Just cs) = concat <$> mapM (intsOut doc) cs -intsOut doc (viewConstantMSet -> Just cs) = concat <$> mapM (intsOut doc) cs -intsOut doc b = return <$> intOut ("intsOut" <+> doc) b - -raiseTypeError :: MonadFail m => Pretty a => a -> m b -raiseTypeError p = fail ("Type error in" <+> pretty p) diff --git a/src/Conjure/Language/Expression/Op/Leq.hs.orig b/src/Conjure/Language/Expression/Op/Leq.hs.orig deleted file mode 100644 index efe4c09bc5..0000000000 --- a/src/Conjure/Language/Expression/Op/Leq.hs.orig +++ /dev/null @@ -1,58 +0,0 @@ -{-# LANGUAGE DeriveGeneric, DeriveDataTypeable, DeriveFunctor, DeriveTraversable, DeriveFoldable #-} - -module Conjure.Language.Expression.Op.Leq where - -import Conjure.Prelude -import Conjure.Language.Expression.Op.Internal.Common - -import qualified Data.Aeson as JSON -- aeson -import qualified Data.HashMap.Strict as M -- unordered-containers -import qualified Data.Vector as V -- vector - - -data OpLeq x = OpLeq x x - deriving (Eq, Ord, Show, Data, Functor, Traversable, Foldable, Typeable, Generic) - -instance Serialize x => Serialize (OpLeq x) -instance Hashable x => Hashable (OpLeq x) -instance ToJSON x => ToJSON (OpLeq x) where toJSON = genericToJSON jsonOptions -instance FromJSON x => FromJSON (OpLeq x) where parseJSON = genericParseJSON jsonOptions - -instance BinaryOperator (OpLeq x) where - opLexeme _ = L_Leq - -instance (TypeOf x, Pretty x) => TypeOf (OpLeq x) where -<<<<<<< HEAD - typeOf p@(OpLeq a b) = sameToSameToBool p a b - [TypeBool, TypeInt Nothing, TypeEnum "?"] -||||||| merged common ancestors - typeOf p@(OpLeq a b) = sameToSameToBool p a b - [TypeBool, TypeInt, TypeEnum "?"] -======= - typeOf p@(OpLeq a b) = do - ta <- typeOf a - tb <- typeOf b - case (ta, tb) of - (TypeInt (TagEnum aTag), TypeInt (TagEnum bTag)) | aTag == bTag - -> return TypeBool - _ -> sameToSameToBool p a b - [TypeBool, TypeInt NoTag, TypeEnum "?"] ->>>>>>> taggedints - -instance EvaluateOp OpLeq where - evaluateOp (OpLeq x y) = return $ ConstantBool $ x <= y - -instance SimplifyOp OpLeq x where - simplifyOp _ = na "simplifyOp{OpLeq}" - -instance Pretty x => Pretty (OpLeq x) where - prettyPrec prec op@(OpLeq a b) = prettyPrecBinOp prec [op] a b - -instance VarSymBreakingDescription x => VarSymBreakingDescription (OpLeq x) where - varSymBreakingDescription (OpLeq a b) = JSON.Object $ M.fromList - [ ("type", JSON.String "OpLeq") - , ("children", JSON.Array $ V.fromList - [ varSymBreakingDescription a - , varSymBreakingDescription b - ]) - ] diff --git a/src/Conjure/Language/Expression/Op/Lt.hs.orig b/src/Conjure/Language/Expression/Op/Lt.hs.orig deleted file mode 100644 index d48d4c4a17..0000000000 --- a/src/Conjure/Language/Expression/Op/Lt.hs.orig +++ /dev/null @@ -1,58 +0,0 @@ -{-# LANGUAGE DeriveGeneric, DeriveDataTypeable, DeriveFunctor, DeriveTraversable, DeriveFoldable #-} - -module Conjure.Language.Expression.Op.Lt where - -import Conjure.Prelude -import Conjure.Language.Expression.Op.Internal.Common - -import qualified Data.Aeson as JSON -- aeson -import qualified Data.HashMap.Strict as M -- unordered-containers -import qualified Data.Vector as V -- vector - - -data OpLt x = OpLt x x - deriving (Eq, Ord, Show, Data, Functor, Traversable, Foldable, Typeable, Generic) - -instance Serialize x => Serialize (OpLt x) -instance Hashable x => Hashable (OpLt x) -instance ToJSON x => ToJSON (OpLt x) where toJSON = genericToJSON jsonOptions -instance FromJSON x => FromJSON (OpLt x) where parseJSON = genericParseJSON jsonOptions - -instance BinaryOperator (OpLt x) where - opLexeme _ = L_Lt - -instance (TypeOf x, Pretty x) => TypeOf (OpLt x) where -<<<<<<< HEAD - typeOf p@(OpLt a b) = sameToSameToBool p a b - [TypeBool, TypeInt Nothing, TypeEnum "?"] -||||||| merged common ancestors - typeOf p@(OpLt a b) = sameToSameToBool p a b - [TypeBool, TypeInt, TypeEnum "?"] -======= - typeOf p@(OpLt a b) = do - ta <- typeOf a - tb <- typeOf b - case (ta, tb) of - (TypeInt (TagEnum aTag), TypeInt (TagEnum bTag)) | aTag == bTag - -> return TypeBool - _ -> sameToSameToBool p a b - [TypeBool, TypeInt NoTag, TypeEnum "?"] ->>>>>>> taggedints - -instance EvaluateOp OpLt where - evaluateOp (OpLt x y) = return $ ConstantBool $ x < y - -instance SimplifyOp OpLt x where - simplifyOp _ = na "simplifyOp{OpLt}" - -instance Pretty x => Pretty (OpLt x) where - prettyPrec prec op@(OpLt a b) = prettyPrecBinOp prec [op] a b - -instance VarSymBreakingDescription x => VarSymBreakingDescription (OpLt x) where - varSymBreakingDescription (OpLt a b) = JSON.Object $ M.fromList - [ ("type", JSON.String "OpLt") - , ("children", JSON.Array $ V.fromList - [ varSymBreakingDescription a - , varSymBreakingDescription b - ]) - ] diff --git a/src/Conjure/Language/Expression/Op/Max.hs.orig b/src/Conjure/Language/Expression/Op/Max.hs.orig deleted file mode 100644 index 2c5961db40..0000000000 --- a/src/Conjure/Language/Expression/Op/Max.hs.orig +++ /dev/null @@ -1,187 +0,0 @@ -{-# LANGUAGE DeriveGeneric, DeriveDataTypeable, DeriveFunctor, DeriveTraversable, DeriveFoldable, ViewPatterns #-} -{-# LANGUAGE UndecidableInstances #-} - -module Conjure.Language.Expression.Op.Max where - -import Conjure.Prelude -import Conjure.Language.Expression.Op.Internal.Common - -import qualified Data.Aeson as JSON -- aeson -import qualified Data.HashMap.Strict as M -- unordered-containers -import qualified Data.Vector as V -- vector - - -data OpMax x = OpMax x - deriving (Eq, Ord, Show, Data, Functor, Traversable, Foldable, Typeable, Generic) - -instance Serialize x => Serialize (OpMax x) -instance Hashable x => Hashable (OpMax x) -instance ToJSON x => ToJSON (OpMax x) where toJSON = genericToJSON jsonOptions -instance FromJSON x => FromJSON (OpMax x) where parseJSON = genericParseJSON jsonOptions - -instance ( TypeOf x, Pretty x - , Domain () x :< x - ) => TypeOf (OpMax x) where - typeOf p@(OpMax x) | Just (dom :: Domain () x) <- project x = do - ty <- typeOf dom - case ty of - TypeInt NoTag -> return ty - TypeInt (TagEnum _) -> return ty - TypeEnum{} -> return ty - _ -> raiseTypeError p - typeOf p@(OpMax x) = do - ty <- typeOf x - tyInner <- case ty of - TypeList tyInner -> return tyInner - TypeMatrix _ tyInner -> return tyInner - TypeSet tyInner -> return tyInner - TypeMSet tyInner -> return tyInner - _ -> raiseTypeError $ vcat [ pretty p - , "Unexpected type inside max:" <+> pretty ty - ] - case tyInner of -<<<<<<< HEAD - TypeInt Nothing -> return () -||||||| merged common ancestors - TypeInt -> return () -======= - TypeInt NoTag -> return () - TypeInt (TagEnum _) -> return () ->>>>>>> taggedints - _ -> raiseTypeError $ vcat [ pretty p - , "Unexpected type inside max:" <+> pretty ty - ] - return tyInner - -instance EvaluateOp OpMax where -<<<<<<< HEAD - evaluateOp p | any isUndef (childrenBi p) = return $ mkUndef (TypeInt Nothing) $ "Has undefined children:" <+> pretty p -||||||| merged common ancestors - evaluateOp p | any isUndef (childrenBi p) = return $ mkUndef TypeInt $ "Has undefined children:" <+> pretty p -======= - evaluateOp p | any isUndef (childrenBi p) = return $ mkUndef (TypeInt NoTag) $ "Has undefined children:" <+> pretty p ->>>>>>> taggedints - evaluateOp (OpMax (DomainInConstant DomainBool)) = return (ConstantBool True) -<<<<<<< HEAD - evaluateOp (OpMax (DomainInConstant (DomainInt Nothing rs))) = do -||||||| merged common ancestors - evaluateOp (OpMax (DomainInConstant (DomainInt rs))) = do -======= - evaluateOp (OpMax (DomainInConstant (DomainInt NoTag rs))) = do ->>>>>>> taggedints - is <- rangesInts rs - return $ if null is -<<<<<<< HEAD - then mkUndef (TypeInt Nothing) "Empty collection in max" - else ConstantInt Nothing (maximum is) -||||||| merged common ancestors - then mkUndef TypeInt "Empty collection in max" - else ConstantInt (maximum is) -======= - then mkUndef (TypeInt NoTag) "Empty collection in max" - else ConstantInt NoTag (maximum is) - evaluateOp (OpMax (DomainInConstant (DomainInt (TagEnum t) rs))) = do - is <- rangesInts rs - return $ if null is - then mkUndef (TypeInt (TagEnum t)) "Empty collection in max" - else ConstantInt (TagEnum t) (maximum is) ->>>>>>> taggedints - evaluateOp (OpMax coll@(viewConstantMatrix -> Just (_, xs))) = - case xs of - [] -> do - tyInner <- typeOf coll >>= innerTypeOf - return $ mkUndef tyInner "Empty collection in max" - (x:_) -> do - tyInner <- typeOf x - case tyInner of -<<<<<<< HEAD - TypeInt Nothing -> do -||||||| merged common ancestors - TypeInt -> do -======= - TypeInt NoTag -> do - is <- concatMapM (intsOut "OpMax 1") xs - return $ ConstantInt NoTag (maximum is) - TypeInt (TagEnum t) -> do ->>>>>>> taggedints - is <- concatMapM (intsOut "OpMax 1") xs -<<<<<<< HEAD - return $ ConstantInt Nothing (maximum is) -||||||| merged common ancestors - return $ ConstantInt (maximum is) -======= - return $ ConstantInt (TagEnum t) (maximum is) ->>>>>>> taggedints - _ -> na "evaluateOp{OpMax}" - evaluateOp (OpMax coll@(viewConstantSet -> Just xs)) = do - case xs of - [] -> do - tyInner <- typeOf coll >>= innerTypeOf - return $ mkUndef tyInner "Empty collection in max" - (x:_) -> do - tyInner <- typeOf x - case tyInner of -<<<<<<< HEAD - TypeInt Nothing -> do -||||||| merged common ancestors - TypeInt -> do -======= - TypeInt NoTag -> do ->>>>>>> taggedints - is <- concatMapM (intsOut "OpMax 1") xs -<<<<<<< HEAD - return $ ConstantInt Nothing (maximum is) -||||||| merged common ancestors - return $ ConstantInt (maximum is) -======= - return $ ConstantInt NoTag (maximum is) - TypeInt (TagEnum t) -> do - is <- concatMapM (intsOut "OpMax 1") xs - return $ ConstantInt (TagEnum t) (maximum is) ->>>>>>> taggedints - _ -> na "evaluateOp{OpMax}" - evaluateOp (OpMax coll@(viewConstantMSet -> Just xs)) = do - case xs of - [] -> do - tyInner <- typeOf coll >>= innerTypeOf - return $ mkUndef tyInner "Empty collection in max" - (x:_) -> do - tyInner <- typeOf x - case tyInner of -<<<<<<< HEAD - TypeInt Nothing -> do -||||||| merged common ancestors - TypeInt -> do -======= - TypeInt NoTag -> do - is <- concatMapM (intsOut "OpMax 1") xs - return $ ConstantInt NoTag (maximum is) - TypeInt (TagEnum t) -> do ->>>>>>> taggedints - is <- concatMapM (intsOut "OpMax 1") xs -<<<<<<< HEAD - return $ ConstantInt Nothing (maximum is) -||||||| merged common ancestors - return $ ConstantInt (maximum is) -======= - return $ ConstantInt (TagEnum t) (maximum is) ->>>>>>> taggedints - _ -> na "evaluateOp{OpMax}" - evaluateOp _ = na "evaluateOp{OpMax}" - -instance SimplifyOp OpMax x where - simplifyOp _ = na "simplifyOp{OpMax}" - -instance Pretty x => Pretty (OpMax x) where - prettyPrec _ (OpMax x) = "max" <> prParens (pretty x) - -instance (VarSymBreakingDescription x, ExpressionLike x) => VarSymBreakingDescription (OpMax x) where - varSymBreakingDescription (OpMax x) | Just xs <- listOut x = JSON.Object $ M.fromList - [ ("type", JSON.String "OpMax") - , ("children", JSON.Array $ V.fromList $ map varSymBreakingDescription xs) - , ("symmetricChildren", JSON.Bool True) - ] - varSymBreakingDescription (OpMax x) = JSON.Object $ M.fromList - [ ("type", JSON.String "OpMax") - , ("children", varSymBreakingDescription x) - ] diff --git a/src/Conjure/Language/Expression/Op/Min.hs.orig b/src/Conjure/Language/Expression/Op/Min.hs.orig deleted file mode 100644 index b32d7e2412..0000000000 --- a/src/Conjure/Language/Expression/Op/Min.hs.orig +++ /dev/null @@ -1,188 +0,0 @@ -{-# LANGUAGE DeriveGeneric, DeriveDataTypeable, DeriveFunctor, DeriveTraversable, DeriveFoldable, ViewPatterns #-} -{-# LANGUAGE UndecidableInstances #-} - -module Conjure.Language.Expression.Op.Min where - -import Conjure.Prelude -import Conjure.Language.Expression.Op.Internal.Common - -import qualified Data.Aeson as JSON -- aeson -import qualified Data.HashMap.Strict as M -- unordered-containers -import qualified Data.Vector as V -- vector - - -data OpMin x = OpMin x - deriving (Eq, Ord, Show, Data, Functor, Traversable, Foldable, Typeable, Generic) - -instance Serialize x => Serialize (OpMin x) -instance Hashable x => Hashable (OpMin x) -instance ToJSON x => ToJSON (OpMin x) where toJSON = genericToJSON jsonOptions -instance FromJSON x => FromJSON (OpMin x) where parseJSON = genericParseJSON jsonOptions - -instance ( TypeOf x, Pretty x - , Domain () x :< x - ) => TypeOf (OpMin x) where - typeOf p@(OpMin x) | Just (dom :: Domain () x) <- project x = do - ty <- typeOf dom - case ty of - TypeInt NoTag -> return ty - TypeInt (TagEnum _) -> return ty - TypeEnum{} -> return ty - _ -> raiseTypeError p - typeOf p@(OpMin x) = do - ty <- typeOf x - tyInner <- case ty of - TypeList tyInner -> return tyInner - TypeMatrix _ tyInner -> return tyInner - TypeSet tyInner -> return tyInner - TypeMSet tyInner -> return tyInner - _ -> raiseTypeError $ vcat [ pretty p - , "Unexpected type inside min:" <+> pretty ty - ] - case tyInner of -<<<<<<< HEAD - TypeInt Nothing -> return () -||||||| merged common ancestors - TypeInt -> return () -======= - TypeInt NoTag -> return () - TypeInt (TagEnum _) -> return () ->>>>>>> taggedints - _ -> raiseTypeError $ vcat [ pretty p - , "Unexpected type inside min:" <+> pretty ty - ] - return tyInner - -instance EvaluateOp OpMin where -<<<<<<< HEAD - evaluateOp p | any isUndef (childrenBi p) = return $ mkUndef (TypeInt Nothing) $ "Has undefined children:" <+> pretty p -||||||| merged common ancestors - evaluateOp p | any isUndef (childrenBi p) = return $ mkUndef TypeInt $ "Has undefined children:" <+> pretty p -======= - evaluateOp p | any isUndef (childrenBi p) = - return $ mkUndef (TypeInt NoTag) $ "Has undefined children:" <+> pretty p ->>>>>>> taggedints - evaluateOp (OpMin (DomainInConstant DomainBool)) = return (ConstantBool False) -<<<<<<< HEAD - evaluateOp (OpMin (DomainInConstant (DomainInt Nothing rs))) = do -||||||| merged common ancestors - evaluateOp (OpMin (DomainInConstant (DomainInt rs))) = do -======= - evaluateOp (OpMin (DomainInConstant (DomainInt NoTag rs))) = do ->>>>>>> taggedints - is <- rangesInts rs - return $ if null is -<<<<<<< HEAD - then mkUndef (TypeInt Nothing) "Empty collection in min" - else ConstantInt Nothing (minimum is) -||||||| merged common ancestors - then mkUndef TypeInt "Empty collection in min" - else ConstantInt (minimum is) -======= - then mkUndef (TypeInt NoTag) "Empty collection in min" - else ConstantInt NoTag (minimum is) - evaluateOp (OpMin (DomainInConstant (DomainInt (TagEnum t) rs))) = do - is <- rangesInts rs - return $ if null is - then mkUndef (TypeInt (TagEnum t)) "Empty collection in min" - else ConstantInt (TagEnum t) (minimum is) ->>>>>>> taggedints - evaluateOp (OpMin coll@(viewConstantMatrix -> Just (_, xs))) = do - case xs of - [] -> do - tyInner <- typeOf coll >>= innerTypeOf - return $ mkUndef tyInner "Empty collection in min" - (x:_) -> do - tyInner <- typeOf x - case tyInner of -<<<<<<< HEAD - TypeInt _ -> do -||||||| merged common ancestors - TypeInt -> do -======= - TypeInt NoTag -> do - is <- concatMapM (intsOut "OpMin 1") xs - return $ ConstantInt NoTag (minimum is) - TypeInt (TagEnum t) -> do ->>>>>>> taggedints - is <- concatMapM (intsOut "OpMin 1") xs -<<<<<<< HEAD - return $ ConstantInt Nothing (minimum is) -||||||| merged common ancestors - return $ ConstantInt (minimum is) -======= - return $ ConstantInt (TagEnum t) (minimum is) ->>>>>>> taggedints - _ -> na "evaluateOp{OpMin}" - evaluateOp (OpMin coll@(viewConstantSet -> Just xs)) = do - case xs of - [] -> do - tyInner <- typeOf coll >>= innerTypeOf - return $ mkUndef tyInner "Empty collection in min" - (x:_) -> do - tyInner <- typeOf x - case tyInner of -<<<<<<< HEAD - TypeInt Nothing -> do -||||||| merged common ancestors - TypeInt -> do -======= - TypeInt NoTag -> do ->>>>>>> taggedints - is <- concatMapM (intsOut "OpMin 1") xs -<<<<<<< HEAD - return $ ConstantInt Nothing (minimum is) -||||||| merged common ancestors - return $ ConstantInt (minimum is) -======= - return $ ConstantInt NoTag (minimum is) - TypeInt (TagEnum t) -> do - is <- concatMapM (intsOut "OpMin 1") xs - return $ ConstantInt (TagEnum t) (minimum is) ->>>>>>> taggedints - _ -> na "evaluateOp{OpMin}" - evaluateOp (OpMin coll@(viewConstantMSet -> Just xs)) = do - case xs of - [] -> do - tyInner <- typeOf coll >>= innerTypeOf - return $ mkUndef tyInner "Empty collection in min" - (x:_) -> do - tyInner <- typeOf x - case tyInner of -<<<<<<< HEAD - TypeInt Nothing -> do -||||||| merged common ancestors - TypeInt -> do -======= - TypeInt NoTag -> do - is <- concatMapM (intsOut "OpMin 1") xs - return $ ConstantInt NoTag (minimum is) - TypeInt (TagEnum t) -> do ->>>>>>> taggedints - is <- concatMapM (intsOut "OpMin 1") xs -<<<<<<< HEAD - return $ ConstantInt Nothing (minimum is) -||||||| merged common ancestors - return $ ConstantInt (minimum is) -======= - return $ ConstantInt (TagEnum t) (minimum is) ->>>>>>> taggedints - _ -> na "evaluateOp{OpMin}" - evaluateOp op = na $ "evaluateOp{OpMin}" <+> pretty (show op) - -instance SimplifyOp OpMin x where - simplifyOp _ = na "simplifyOp{OpMin}" - -instance Pretty x => Pretty (OpMin x) where - prettyPrec _ (OpMin x) = "min" <> prParens (pretty x) - -instance (VarSymBreakingDescription x, ExpressionLike x) => VarSymBreakingDescription (OpMin x) where - varSymBreakingDescription (OpMin x) | Just xs <- listOut x = JSON.Object $ M.fromList - [ ("type", JSON.String "OpMin") - , ("children", JSON.Array $ V.fromList $ map varSymBreakingDescription xs) - , ("symmetricChildren", JSON.Bool True) - ] - varSymBreakingDescription (OpMin x) = JSON.Object $ M.fromList - [ ("type", JSON.String "OpMin") - , ("children", varSymBreakingDescription x) - ] diff --git a/src/Conjure/Language/Expression/Op/Minus.hs.orig b/src/Conjure/Language/Expression/Op/Minus.hs.orig deleted file mode 100644 index 263416d300..0000000000 --- a/src/Conjure/Language/Expression/Op/Minus.hs.orig +++ /dev/null @@ -1,98 +0,0 @@ -{-# LANGUAGE DeriveGeneric, DeriveDataTypeable, DeriveFunctor, DeriveTraversable, DeriveFoldable, ViewPatterns #-} - -module Conjure.Language.Expression.Op.Minus where - -import Conjure.Prelude -import Conjure.Language.Expression.Op.Internal.Common - -import qualified Data.Aeson as JSON -- aeson -import qualified Data.HashMap.Strict as M -- unordered-containers -import qualified Data.Vector as V -- vector - - -data OpMinus x = OpMinus x x - deriving (Eq, Ord, Show, Data, Functor, Traversable, Foldable, Typeable, Generic) - -instance Serialize x => Serialize (OpMinus x) -instance Hashable x => Hashable (OpMinus x) -instance ToJSON x => ToJSON (OpMinus x) where toJSON = genericToJSON jsonOptions -instance FromJSON x => FromJSON (OpMinus x) where parseJSON = genericParseJSON jsonOptions - -instance BinaryOperator (OpMinus x) where - opLexeme _ = L_Minus - -instance (TypeOf x, Pretty x) => TypeOf (OpMinus x) where - typeOf p@(OpMinus a b) = sameToSameToSame p a b -<<<<<<< HEAD - [ TypeInt Nothing -||||||| merged common ancestors - [ TypeInt -======= - [ TypeInt NoTag ->>>>>>> taggedints - , TypeSet TypeAny - , TypeMSet TypeAny - , TypeFunction TypeAny TypeAny - , TypeRelation [TypeAny] - ] - -instance EvaluateOp OpMinus where - evaluateOp p | any isUndef (childrenBi p) = do - ty <- typeOf p - return $ mkUndef ty $ "Has undefined children:" <+> pretty p -<<<<<<< HEAD - evaluateOp (OpMinus (ConstantInt Nothing a) (ConstantInt Nothing b)) = return $ ConstantInt Nothing (a - b) -||||||| merged common ancestors - evaluateOp (OpMinus (ConstantInt a) (ConstantInt b)) = return $ ConstantInt (a - b) -======= - evaluateOp (OpMinus (ConstantInt NoTag a) (ConstantInt NoTag b)) - = return $ ConstantInt NoTag (a - b) ->>>>>>> taggedints - evaluateOp (OpMinus (viewConstantSet -> Just as) (viewConstantSet -> Just bs)) = do - let outs = - [ a - | a <- as - , a `notElem` bs - ] - return $ ConstantAbstract $ AbsLitSet outs - evaluateOp (OpMinus (viewConstantMSet -> Just as) (viewConstantMSet -> Just bs)) = do - let asHist = histogram as - bsHist = histogram bs - allElems = sortNub (as++bs) - outs = - [ replicate (fromInteger (countA - countB)) e - | e <- allElems - , let countA = fromMaybe 0 (e `lookup` asHist) - , let countB = fromMaybe 0 (e `lookup` bsHist) - ] - return $ ConstantAbstract $ AbsLitMSet $ concat outs - evaluateOp (OpMinus (viewConstantFunction -> Just as) (viewConstantFunction -> Just bs)) = do - let outs = - [ a - | a <- as - , a `notElem` bs - ] - return $ ConstantAbstract $ AbsLitFunction outs - evaluateOp (OpMinus (viewConstantRelation -> Just as) (viewConstantRelation -> Just bs)) = do - let outs = - [ a - | a <- as - , a `notElem` bs - ] - return $ ConstantAbstract $ AbsLitRelation outs - evaluateOp op = na $ "evaluateOp{OpMinus}:" <++> pretty (show op) - -instance SimplifyOp OpMinus x where - simplifyOp _ = na "simplifyOp{OpMinus}" - -instance Pretty x => Pretty (OpMinus x) where - prettyPrec prec op@(OpMinus a b) = prettyPrecBinOp prec [op] a b - -instance VarSymBreakingDescription x => VarSymBreakingDescription (OpMinus x) where - varSymBreakingDescription (OpMinus a b) = JSON.Object $ M.fromList - [ ("type", JSON.String "OpMinus") - , ("children", JSON.Array $ V.fromList - [ varSymBreakingDescription a - , varSymBreakingDescription b - ]) - ] diff --git a/src/Conjure/Language/Expression/Op/Mod.hs.orig b/src/Conjure/Language/Expression/Op/Mod.hs.orig deleted file mode 100644 index 2aaeae7c6d..0000000000 --- a/src/Conjure/Language/Expression/Op/Mod.hs.orig +++ /dev/null @@ -1,65 +0,0 @@ -{-# LANGUAGE DeriveGeneric, DeriveDataTypeable, DeriveFunctor, DeriveTraversable, DeriveFoldable #-} - -module Conjure.Language.Expression.Op.Mod where - -import Conjure.Prelude -import Conjure.Language.Expression.Op.Internal.Common - -import qualified Data.Aeson as JSON -- aeson -import qualified Data.HashMap.Strict as M -- unordered-containers -import qualified Data.Vector as V -- vector - - -data OpMod x = OpMod x x - deriving (Eq, Ord, Show, Data, Functor, Traversable, Foldable, Typeable, Generic) - -instance Serialize x => Serialize (OpMod x) -instance Hashable x => Hashable (OpMod x) -instance ToJSON x => ToJSON (OpMod x) where toJSON = genericToJSON jsonOptions -instance FromJSON x => FromJSON (OpMod x) where parseJSON = genericParseJSON jsonOptions - -instance BinaryOperator (OpMod x) where - opLexeme _ = L_Mod - -instance (TypeOf x, Pretty x) => TypeOf (OpMod x) where - typeOf p@(OpMod a b) = do - ta <- typeOf a - tb <- typeOf b - case (ta, tb) of - (TypeInt NoTag, TypeInt NoTag) -> intToIntToInt p a b - _ -> raiseTypeError p - -instance EvaluateOp OpMod where -<<<<<<< HEAD - evaluateOp p | any isUndef (childrenBi p) = return $ mkUndef (TypeInt Nothing) $ "Has undefined children:" <+> pretty p -||||||| merged common ancestors - evaluateOp p | any isUndef (childrenBi p) = return $ mkUndef TypeInt $ "Has undefined children:" <+> pretty p -======= - evaluateOp p | any isUndef (childrenBi p) = return $ mkUndef (TypeInt NoTag) $ "Has undefined children:" <+> pretty p ->>>>>>> taggedints - evaluateOp p@(OpMod x y) -<<<<<<< HEAD - | y /= 0 = ConstantInt Nothing <$> (mod <$> intOut "mod x" x <*> intOut "mod y" y) - | otherwise = return $ mkUndef (TypeInt Nothing) $ "modulo zero:" <+> pretty p -||||||| merged common ancestors - | y /= 0 = ConstantInt <$> (mod <$> intOut "mod x" x <*> intOut "mod y" y) - | otherwise = return $ mkUndef TypeInt $ "modulo zero:" <+> pretty p -======= - | y /= 0 = ConstantInt NoTag <$> (mod <$> intOut "mod x" x <*> intOut "mod y" y) - | otherwise = return $ mkUndef (TypeInt NoTag) $ "modulo zero:" <+> pretty p ->>>>>>> taggedints - -instance SimplifyOp OpMod x where - simplifyOp _ = na "simplifyOp{OpMod}" - -instance Pretty x => Pretty (OpMod x) where - prettyPrec prec op@(OpMod a b) = prettyPrecBinOp prec [op] a b - -instance VarSymBreakingDescription x => VarSymBreakingDescription (OpMod x) where - varSymBreakingDescription (OpMod a b) = JSON.Object $ M.fromList - [ ("type", JSON.String "OpMod") - , ("children", JSON.Array $ V.fromList - [ varSymBreakingDescription a - , varSymBreakingDescription b - ]) - ] diff --git a/src/Conjure/Language/Expression/Op/Negate.hs.orig b/src/Conjure/Language/Expression/Op/Negate.hs.orig deleted file mode 100644 index de53447866..0000000000 --- a/src/Conjure/Language/Expression/Op/Negate.hs.orig +++ /dev/null @@ -1,54 +0,0 @@ -{-# LANGUAGE DeriveGeneric, DeriveDataTypeable, DeriveFunctor, DeriveTraversable, DeriveFoldable #-} - -module Conjure.Language.Expression.Op.Negate where - -import Conjure.Prelude -import Conjure.Language.Expression.Op.Internal.Common - -import qualified Data.Aeson as JSON -- aeson -import qualified Data.HashMap.Strict as M -- unordered-containers -import qualified Data.Vector as V -- vector - - -data OpNegate x = OpNegate x - deriving (Eq, Ord, Show, Data, Functor, Traversable, Foldable, Typeable, Generic) - -instance Serialize x => Serialize (OpNegate x) -instance Hashable x => Hashable (OpNegate x) -instance ToJSON x => ToJSON (OpNegate x) where toJSON = genericToJSON jsonOptions -instance FromJSON x => FromJSON (OpNegate x) where parseJSON = genericParseJSON jsonOptions - -instance TypeOf x => TypeOf (OpNegate x) where -<<<<<<< HEAD - typeOf (OpNegate a) = do TypeInt Nothing <- typeOf a ; return (TypeInt Nothing) -||||||| merged common ancestors - typeOf (OpNegate a) = do TypeInt <- typeOf a ; return TypeInt -======= - typeOf (OpNegate a) = do TypeInt NoTag <- typeOf a ; return (TypeInt NoTag) ->>>>>>> taggedints - -instance EvaluateOp OpNegate where -<<<<<<< HEAD - evaluateOp p | any isUndef (childrenBi p) = return $ mkUndef (TypeInt Nothing) $ "Has undefined children:" <+> pretty p - evaluateOp (OpNegate x) = ConstantInt Nothing . negate <$> intOut "OpNegate" x -||||||| merged common ancestors - evaluateOp p | any isUndef (childrenBi p) = return $ mkUndef TypeInt $ "Has undefined children:" <+> pretty p - evaluateOp (OpNegate x) = ConstantInt . negate <$> intOut "OpNegate" x -======= - evaluateOp p | any isUndef (childrenBi p) = return $ mkUndef (TypeInt NoTag) $ "Has undefined children:" <+> pretty p - evaluateOp (OpNegate x) = ConstantInt NoTag . negate <$> intOut "OpNegate" x ->>>>>>> taggedints - -instance SimplifyOp OpNegate x where - simplifyOp _ = na "simplifyOp{OpNegate}" - -instance Pretty x => Pretty (OpNegate x) where - prettyPrec prec (OpNegate a) = parensIf (prec > 2000) ("-" <> prettyPrec 2000 a) - -instance VarSymBreakingDescription x => VarSymBreakingDescription (OpNegate x) where - varSymBreakingDescription (OpNegate a) = JSON.Object $ M.fromList - [ ("type", JSON.String "OpNegate") - , ("children", JSON.Array $ V.fromList - [ varSymBreakingDescription a - ]) - ] diff --git a/src/Conjure/Language/Expression/Op/Pow.hs.orig b/src/Conjure/Language/Expression/Op/Pow.hs.orig deleted file mode 100644 index 9da38f5cfd..0000000000 --- a/src/Conjure/Language/Expression/Op/Pow.hs.orig +++ /dev/null @@ -1,65 +0,0 @@ -{-# LANGUAGE DeriveGeneric, DeriveDataTypeable, DeriveFunctor, DeriveTraversable, DeriveFoldable #-} - -module Conjure.Language.Expression.Op.Pow where - -import Conjure.Prelude -import Conjure.Language.Expression.Op.Internal.Common - -import qualified Data.Aeson as JSON -- aeson -import qualified Data.HashMap.Strict as M -- unordered-containers -import qualified Data.Vector as V -- vector - - -data OpPow x = OpPow x x - deriving (Eq, Ord, Show, Data, Functor, Traversable, Foldable, Typeable, Generic) - -instance Serialize x => Serialize (OpPow x) -instance Hashable x => Hashable (OpPow x) -instance ToJSON x => ToJSON (OpPow x) where toJSON = genericToJSON jsonOptions -instance FromJSON x => FromJSON (OpPow x) where parseJSON = genericParseJSON jsonOptions - -instance BinaryOperator (OpPow x) where - opLexeme _ = L_Pow - -instance (TypeOf x, Pretty x) => TypeOf (OpPow x) where - typeOf p@(OpPow a b) = do - ta <- typeOf a - tb <- typeOf b - case (ta, tb) of - (TypeInt NoTag, TypeInt NoTag) -> intToIntToInt p a b - _ -> raiseTypeError p - -instance EvaluateOp OpPow where -<<<<<<< HEAD - evaluateOp p | any isUndef (childrenBi p) = return $ mkUndef (TypeInt Nothing) $ "Has undefined children:" <+> pretty p -||||||| merged common ancestors - evaluateOp p | any isUndef (childrenBi p) = return $ mkUndef TypeInt $ "Has undefined children:" <+> pretty p -======= - evaluateOp p | any isUndef (childrenBi p) = return $ mkUndef (TypeInt NoTag) $ "Has undefined children:" <+> pretty p ->>>>>>> taggedints - evaluateOp p@(OpPow x y) -<<<<<<< HEAD - | y >= 0 = ConstantInt Nothing <$> ((^) <$> intOut "pow x" x <*> intOut "pow y" y) - | otherwise = return $ mkUndef (TypeInt Nothing) $ "negative exponent:" <+> pretty p -||||||| merged common ancestors - | y >= 0 = ConstantInt <$> ((^) <$> intOut "pow x" x <*> intOut "pow y" y) - | otherwise = return $ mkUndef TypeInt $ "negative exponent:" <+> pretty p -======= - | y >= 0 = ConstantInt NoTag <$> ((^) <$> intOut "pow x" x <*> intOut "pow y" y) - | otherwise = return $ mkUndef (TypeInt NoTag) $ "negative exponent:" <+> pretty p ->>>>>>> taggedints - -instance SimplifyOp OpPow x where - simplifyOp _ = na "simplifyOp{OpPow}" - -instance Pretty x => Pretty (OpPow x) where - prettyPrec prec op@(OpPow a b) = prettyPrecBinOp prec [op] a b - -instance VarSymBreakingDescription x => VarSymBreakingDescription (OpPow x) where - varSymBreakingDescription (OpPow a b) = JSON.Object $ M.fromList - [ ("type", JSON.String "OpPow") - , ("children", JSON.Array $ V.fromList - [ varSymBreakingDescription a - , varSymBreakingDescription b - ]) - ] diff --git a/src/Conjure/Language/Expression/Op/PreImage.hs.orig b/src/Conjure/Language/Expression/Op/PreImage.hs.orig deleted file mode 100644 index 2de7e413a7..0000000000 --- a/src/Conjure/Language/Expression/Op/PreImage.hs.orig +++ /dev/null @@ -1,70 +0,0 @@ -{-# LANGUAGE DeriveGeneric, DeriveDataTypeable, DeriveFunctor, DeriveTraversable, DeriveFoldable, ViewPatterns #-} - -module Conjure.Language.Expression.Op.PreImage where - -import Conjure.Prelude -import Conjure.Language.Expression.Op.Internal.Common - -import qualified Data.Aeson as JSON -- aeson -import qualified Data.HashMap.Strict as M -- unordered-containers -import qualified Data.Vector as V -- vector - - -data OpPreImage x = OpPreImage x x - deriving (Eq, Ord, Show, Data, Functor, Traversable, Foldable, Typeable, Generic) - -instance Serialize x => Serialize (OpPreImage x) -instance Hashable x => Hashable (OpPreImage x) -instance ToJSON x => ToJSON (OpPreImage x) where toJSON = genericToJSON jsonOptions -instance FromJSON x => FromJSON (OpPreImage x) where parseJSON = genericParseJSON jsonOptions - -instance (TypeOf x, Pretty x) => TypeOf (OpPreImage x) where - typeOf p@(OpPreImage f x) = do - fTy <- typeOf f - xTy <- typeOf x - case fTy of - TypeFunction from to -> do - if typesUnify [xTy, to] - then return (TypeSet from) - else raiseTypeError p - TypeSequence to -> do - if typesUnify [xTy, to] -<<<<<<< HEAD - then return (TypeSet (TypeInt Nothing)) -||||||| merged common ancestors - then return (TypeSet TypeInt) -======= - then return (TypeSet (TypeInt NoTag)) ->>>>>>> taggedints - else raiseTypeError p - _ -> raiseTypeError p - -instance EvaluateOp OpPreImage where - evaluateOp (OpPreImage (viewConstantFunction -> Just xs) a) = - return $ ConstantAbstract $ AbsLitSet [ x | (x,y) <- xs, a == y ] - evaluateOp (OpPreImage (viewConstantSequence -> Just xs) a) = - return $ ConstantAbstract $ AbsLitSet [ x | (n,y) <- zip allNats xs -<<<<<<< HEAD - , let x = ConstantInt Nothing n -||||||| merged common ancestors - , let x = ConstantInt n -======= - , let x = ConstantInt NoTag n ->>>>>>> taggedints - , a == y ] - evaluateOp op = na $ "evaluateOp{OpPreImage}:" <++> pretty (show op) - -instance SimplifyOp OpPreImage x where - simplifyOp _ = na "simplifyOp{OpPreImage}" - -instance Pretty x => Pretty (OpPreImage x) where - prettyPrec _ (OpPreImage a b) = "preImage" <> prettyList prParens "," [a,b] - -instance VarSymBreakingDescription x => VarSymBreakingDescription (OpPreImage x) where - varSymBreakingDescription (OpPreImage a b) = JSON.Object $ M.fromList - [ ("type", JSON.String "OpPreImage") - , ("children", JSON.Array $ V.fromList - [ varSymBreakingDescription a - , varSymBreakingDescription b - ]) - ] diff --git a/src/Conjure/Language/Expression/Op/Pred.hs.orig b/src/Conjure/Language/Expression/Op/Pred.hs.orig deleted file mode 100644 index bdd34b869c..0000000000 --- a/src/Conjure/Language/Expression/Op/Pred.hs.orig +++ /dev/null @@ -1,65 +0,0 @@ -{-# LANGUAGE DeriveGeneric, DeriveDataTypeable, DeriveFunctor, DeriveTraversable, DeriveFoldable #-} - -module Conjure.Language.Expression.Op.Pred where - -import Conjure.Prelude -import Conjure.Language.Expression.Op.Internal.Common - -import qualified Data.Aeson as JSON -- aeson -import qualified Data.HashMap.Strict as M -- unordered-containers -import qualified Data.Vector as V -- vector - - -data OpPred x = OpPred x - deriving (Eq, Ord, Show, Data, Functor, Traversable, Foldable, Typeable, Generic) - -instance Serialize x => Serialize (OpPred x) -instance Hashable x => Hashable (OpPred x) -instance ToJSON x => ToJSON (OpPred x) where toJSON = genericToJSON jsonOptions -instance FromJSON x => FromJSON (OpPred x) where parseJSON = genericParseJSON jsonOptions - -instance (TypeOf x, Pretty x) => TypeOf (OpPred x) where - typeOf p@(OpPred x) = do - ty <- typeOf x - case ty of - TypeBool{} -> return ty - TypeInt NoTag -> return ty - TypeInt (TagEnum _) -> return ty - TypeEnum{} -> return ty - _ -> raiseTypeError p - -instance EvaluateOp OpPred where -<<<<<<< HEAD - evaluateOp p | any isUndef (childrenBi p) = return $ mkUndef (TypeInt Nothing) $ "Has undefined children:" <+> pretty p -||||||| merged common ancestors - evaluateOp p | any isUndef (childrenBi p) = return $ mkUndef TypeInt $ "Has undefined children:" <+> pretty p -======= - evaluateOp p | any isUndef (childrenBi p) - = return $ mkUndef (TypeInt NoTag) $ "Has undefined children:" <+> pretty p ->>>>>>> taggedints - evaluateOp (OpPred (ConstantBool _)) = return (ConstantBool False) -- True --> False - -- False --> undef, hence False -<<<<<<< HEAD - evaluateOp (OpPred (ConstantInt name x)) = return (ConstantInt name (pred x)) -||||||| merged common ancestors - evaluateOp (OpPred (ConstantInt x)) = return (ConstantInt (pred x)) -======= - evaluateOp (OpPred (ConstantInt NoTag x)) = return (ConstantInt NoTag (pred x)) - evaluateOp (OpPred (ConstantInt (TagEnum t) x)) - = return (ConstantInt (TagEnum t) (pred x)) ->>>>>>> taggedints - evaluateOp op = na $ "evaluateOp{OpPred}" <+> pretty (show op) - -instance SimplifyOp OpPred x where - simplifyOp _ = na "simplifyOp{OpPred}" - -instance Pretty x => Pretty (OpPred x) where - prettyPrec _ (OpPred x) = "pred" <> prParens (pretty x) - -instance VarSymBreakingDescription x => VarSymBreakingDescription (OpPred x) where - varSymBreakingDescription (OpPred a) = JSON.Object $ M.fromList - [ ("type", JSON.String "OpPred") - , ("children", JSON.Array $ V.fromList - [ varSymBreakingDescription a - ]) - ] diff --git a/src/Conjure/Language/Expression/Op/Product.hs.orig b/src/Conjure/Language/Expression/Op/Product.hs.orig deleted file mode 100644 index 2f97048067..0000000000 --- a/src/Conjure/Language/Expression/Op/Product.hs.orig +++ /dev/null @@ -1,102 +0,0 @@ -{-# LANGUAGE DeriveGeneric, DeriveDataTypeable, DeriveFunctor, DeriveTraversable, DeriveFoldable #-} -{-# LANGUAGE UndecidableInstances #-} - -module Conjure.Language.Expression.Op.Product where - -import Conjure.Prelude -import Conjure.Language.Expression.Op.Internal.Common - -import qualified Data.Aeson as JSON -- aeson -import qualified Data.HashMap.Strict as M -- unordered-containers -import qualified Data.Vector as V -- vector - - -data OpProduct x = OpProduct x - deriving (Eq, Ord, Show, Data, Functor, Traversable, Foldable, Typeable, Generic) - -instance Serialize x => Serialize (OpProduct x) -instance Hashable x => Hashable (OpProduct x) -instance ToJSON x => ToJSON (OpProduct x) where toJSON = genericToJSON jsonOptions -instance FromJSON x => FromJSON (OpProduct x) where parseJSON = genericParseJSON jsonOptions - -instance (TypeOf x, Pretty x, ExpressionLike x) => TypeOf (OpProduct x) where - typeOf p@(OpProduct x) = do - ty <- typeOf x - case ty of -<<<<<<< HEAD - TypeList TypeAny -> return $ TypeInt Nothing - TypeList (TypeInt Nothing) -> return (TypeInt Nothing) - TypeMatrix _ TypeAny -> return $ TypeInt Nothing - TypeMatrix _ (TypeInt Nothing) -> return (TypeInt Nothing) - TypeSet (TypeInt Nothing) -> return (TypeInt Nothing) - TypeMSet (TypeInt Nothing) -> return (TypeInt Nothing) -||||||| merged common ancestors - TypeList TypeAny -> return TypeInt - TypeList TypeInt -> return TypeInt - TypeMatrix _ TypeAny -> return TypeInt - TypeMatrix _ TypeInt -> return TypeInt - TypeSet TypeInt -> return TypeInt - TypeMSet TypeInt -> return TypeInt -======= - TypeList TypeAny -> return (TypeInt NoTag) - TypeList (TypeInt NoTag) -> return (TypeInt NoTag) - TypeMatrix _ TypeAny -> return (TypeInt NoTag) - TypeMatrix _ (TypeInt NoTag) -> return (TypeInt NoTag) - TypeSet (TypeInt NoTag) -> return (TypeInt NoTag) - TypeMSet (TypeInt NoTag) -> return (TypeInt NoTag) ->>>>>>> taggedints - _ -> raiseTypeError $ vcat [ pretty p - , "The argument has type:" <+> pretty ty - ] - -instance BinaryOperator (OpProduct x) where - opLexeme _ = L_Times - -instance EvaluateOp OpProduct where -<<<<<<< HEAD - evaluateOp p | any isUndef (childrenBi p) = return $ mkUndef (TypeInt Nothing) $ "Has undefined children:" <+> pretty p -||||||| merged common ancestors - evaluateOp p | any isUndef (childrenBi p) = return $ mkUndef TypeInt $ "Has undefined children:" <+> pretty p -======= - evaluateOp p | any isUndef (childrenBi p) = return $ mkUndef (TypeInt NoTag) $ "Has undefined children:" <+> pretty p ->>>>>>> taggedints - evaluateOp p@(OpProduct x) - | Just xs <- listOut x -<<<<<<< HEAD - , any isUndef xs = return $ mkUndef (TypeInt Nothing) $ "Has undefined children:" <+> pretty p - evaluateOp (OpProduct x) = ConstantInt Nothing . product <$> intsOut "OpProduct" x -||||||| merged common ancestors - , any isUndef xs = return $ mkUndef TypeInt $ "Has undefined children:" <+> pretty p - evaluateOp (OpProduct x) = ConstantInt . product <$> intsOut "OpProduct" x -======= - , any isUndef xs = return $ mkUndef (TypeInt NoTag) $ "Has undefined children:" <+> pretty p - evaluateOp (OpProduct x) = ConstantInt NoTag . product <$> intsOut "OpProduct" x ->>>>>>> taggedints - -instance (OpProduct x :< x) => SimplifyOp OpProduct x where - simplifyOp (OpProduct x) - | Just xs <- listOut x - , let filtered = filter (/=0) xs - , length filtered /= length xs -- there were 0's - = return 0 - simplifyOp (OpProduct x) - | Just xs <- listOut x - , let filtered = filter (/=1) xs - , length filtered /= length xs -- there were 1's - = return $ inject $ OpProduct $ fromList filtered - simplifyOp _ = na "simplifyOp{OpProduct}" - -instance (Pretty x, ExpressionLike x) => Pretty (OpProduct x) where - prettyPrec prec op@(OpProduct x) | Just [a,b] <- listOut x = prettyPrecBinOp prec [op] a b - prettyPrec _ (OpProduct x) = "product" <> prParens (pretty x) - -instance (VarSymBreakingDescription x, ExpressionLike x) => VarSymBreakingDescription (OpProduct x) where - varSymBreakingDescription (OpProduct x) | Just xs <- listOut x = JSON.Object $ M.fromList - [ ("type", JSON.String "OpProduct") - , ("children", JSON.Array $ V.fromList $ map varSymBreakingDescription xs) - , ("symmetricChildren", JSON.Bool True) - ] - varSymBreakingDescription (OpProduct x) = JSON.Object $ M.fromList - [ ("type", JSON.String "OpProduct") - , ("children", varSymBreakingDescription x) - ] diff --git a/src/Conjure/Language/Expression/Op/Slicing.hs.orig b/src/Conjure/Language/Expression/Op/Slicing.hs.orig deleted file mode 100644 index 1fb2c0e8e1..0000000000 --- a/src/Conjure/Language/Expression/Op/Slicing.hs.orig +++ /dev/null @@ -1,85 +0,0 @@ -{-# LANGUAGE DeriveGeneric, DeriveDataTypeable, DeriveFunctor, DeriveTraversable, DeriveFoldable, ViewPatterns #-} - -module Conjure.Language.Expression.Op.Slicing where - -import Conjure.Prelude -import Conjure.Language.Expression.Op.Internal.Common - -import qualified Data.Aeson as JSON -- aeson -import qualified Data.HashMap.Strict as M -- unordered-containers -import qualified Data.Vector as V -- vector - - -data OpSlicing x = OpSlicing x (Maybe x) (Maybe x) - deriving (Eq, Ord, Show, Data, Functor, Traversable, Foldable, Typeable, Generic) - -instance Serialize x => Serialize (OpSlicing x) -instance Hashable x => Hashable (OpSlicing x) -instance ToJSON x => ToJSON (OpSlicing x) where toJSON = genericToJSON jsonOptions -instance FromJSON x => FromJSON (OpSlicing x) where parseJSON = genericParseJSON jsonOptions - -instance (TypeOf x, Pretty x) => TypeOf (OpSlicing x) where - typeOf p@(OpSlicing m _ _) = do - ty <- typeOf m - case ty of - TypeMatrix{} -> return () - TypeList{} -> return () - _ -> raiseTypeError p - return ty - -instance EvaluateOp OpSlicing where -<<<<<<< HEAD - evaluateOp (OpSlicing (viewConstantMatrix -> Just (DomainInt _ index, vals)) lb ub) = do -||||||| merged common ancestors - evaluateOp (OpSlicing (viewConstantMatrix -> Just (DomainInt index, vals)) lb ub) = do -======= - evaluateOp (OpSlicing (viewConstantMatrix -> Just (DomainInt n index, vals)) lb ub) - = do ->>>>>>> taggedints - indexVals <- valuesInIntDomain index -<<<<<<< HEAD - outVals <- fmap catMaybes $ forM (zip indexVals vals) $ \ (thisIndex, thisVal) -> - case lb of - Just (ConstantInt Nothing lower) | lower > thisIndex -> return Nothing - _ -> case ub of - Just (ConstantInt Nothing upper) | upper < thisIndex -> return Nothing - _ -> return $ Just (thisIndex, thisVal) - let outDomain = DomainInt Nothing $ map (RangeSingle . ConstantInt Nothing . fst) outVals -||||||| merged common ancestors - outVals <- fmap catMaybes $ forM (zip indexVals vals) $ \ (thisIndex, thisVal) -> - case lb of - Just (ConstantInt lower) | lower > thisIndex -> return Nothing - _ -> case ub of - Just (ConstantInt upper) | upper < thisIndex -> return Nothing - _ -> return $ Just (thisIndex, thisVal) - let outDomain = DomainInt $ map (RangeSingle . ConstantInt . fst) outVals -======= - outVals <- fmap catMaybes $ forM (zip indexVals vals) - $ \ (thisIndex, thisVal) -> - case lb of - Just (ConstantInt cn lower) - | cn == n && lower > thisIndex -> return Nothing - _ -> case ub of - Just (ConstantInt cn upper) - | cn == n && upper < thisIndex -> return Nothing - _ -> return $ Just (thisIndex, thisVal) - let outDomain = DomainInt n $ map (RangeSingle . (ConstantInt n) . fst) outVals ->>>>>>> taggedints - return $ ConstantAbstract $ AbsLitMatrix outDomain (map snd outVals) - evaluateOp op = na $ "evaluateOp{OpSlicing}:" <++> pretty (show op) - -instance SimplifyOp OpSlicing x where - simplifyOp _ = na "simplifyOp{OpSlicing}" - -instance Pretty x => Pretty (OpSlicing x) where - prettyPrec _ (OpSlicing m a b) = pretty m <> prBrackets (pretty a <> ".." <> pretty b) - -instance VarSymBreakingDescription x => VarSymBreakingDescription (OpSlicing x) where - varSymBreakingDescription (OpSlicing a b c) = JSON.Object $ M.fromList - [ ("type", JSON.String "OpSlicing") - , ("children", JSON.Array $ V.fromList - [ varSymBreakingDescription a - , maybe JSON.Null varSymBreakingDescription b - , maybe JSON.Null varSymBreakingDescription c - ]) - ] diff --git a/src/Conjure/Language/Expression/Op/Succ.hs.orig b/src/Conjure/Language/Expression/Op/Succ.hs.orig deleted file mode 100644 index 65d31a6264..0000000000 --- a/src/Conjure/Language/Expression/Op/Succ.hs.orig +++ /dev/null @@ -1,65 +0,0 @@ -{-# LANGUAGE DeriveGeneric, DeriveDataTypeable, DeriveFunctor, DeriveTraversable, DeriveFoldable #-} - -module Conjure.Language.Expression.Op.Succ where - -import Conjure.Prelude -import Conjure.Language.Expression.Op.Internal.Common - -import qualified Data.Aeson as JSON -- aeson -import qualified Data.HashMap.Strict as M -- unordered-containers -import qualified Data.Vector as V -- vector - - -data OpSucc x = OpSucc x - deriving (Eq, Ord, Show, Data, Functor, Traversable, Foldable, Typeable, Generic) - -instance Serialize x => Serialize (OpSucc x) -instance Hashable x => Hashable (OpSucc x) -instance ToJSON x => ToJSON (OpSucc x) where toJSON = genericToJSON jsonOptions -instance FromJSON x => FromJSON (OpSucc x) where parseJSON = genericParseJSON jsonOptions - -instance (TypeOf x, Pretty x) => TypeOf (OpSucc x) where - typeOf p@(OpSucc x) = do - ty <- typeOf x - case ty of - TypeBool{} -> return ty - TypeInt NoTag -> return ty - TypeInt (TagEnum _) -> return ty - TypeEnum{} -> return ty - _ -> raiseTypeError p - -instance EvaluateOp OpSucc where -<<<<<<< HEAD - evaluateOp p | any isUndef (childrenBi p) = return $ mkUndef (TypeInt Nothing) $ "Has undefined children:" <+> pretty p -||||||| merged common ancestors - evaluateOp p | any isUndef (childrenBi p) = return $ mkUndef TypeInt $ "Has undefined children:" <+> pretty p -======= - evaluateOp p | any isUndef (childrenBi p) - = return $ mkUndef (TypeInt NoTag) $ "Has undefined children:" <+> pretty p ->>>>>>> taggedints - evaluateOp (OpSucc (ConstantBool False)) = return (ConstantBool True) - evaluateOp (OpSucc (ConstantBool True )) = return (ConstantBool False) -- undef -<<<<<<< HEAD - evaluateOp (OpSucc (ConstantInt name x)) = return (ConstantInt name (succ x)) -||||||| merged common ancestors - evaluateOp (OpSucc (ConstantInt x)) = return (ConstantInt (succ x)) -======= - evaluateOp (OpSucc (ConstantInt NoTag x)) = return (ConstantInt NoTag (succ x)) - evaluateOp (OpSucc (ConstantInt (TagEnum t) x)) - = return (ConstantInt (TagEnum t) (succ x)) ->>>>>>> taggedints - evaluateOp op = na $ "evaluateOp{OpSucc}" <+> pretty (show op) - -instance SimplifyOp OpSucc x where - simplifyOp _ = na "simplifyOp{OpSucc}" - -instance Pretty x => Pretty (OpSucc x) where - prettyPrec _ (OpSucc x) = "succ" <> prParens (pretty x) - -instance VarSymBreakingDescription x => VarSymBreakingDescription (OpSucc x) where - varSymBreakingDescription (OpSucc a) = JSON.Object $ M.fromList - [ ("type", JSON.String "OpSucc") - , ("children", JSON.Array $ V.fromList - [ varSymBreakingDescription a - ]) - ] diff --git a/src/Conjure/Language/Expression/Op/Sum.hs.orig b/src/Conjure/Language/Expression/Op/Sum.hs.orig deleted file mode 100644 index c0e2812352..0000000000 --- a/src/Conjure/Language/Expression/Op/Sum.hs.orig +++ /dev/null @@ -1,97 +0,0 @@ -{-# LANGUAGE DeriveGeneric, DeriveDataTypeable, DeriveFunctor, DeriveTraversable, DeriveFoldable #-} -{-# LANGUAGE UndecidableInstances #-} - -module Conjure.Language.Expression.Op.Sum where - -import Conjure.Prelude -import Conjure.Language.Expression.Op.Internal.Common - -import qualified Data.Aeson as JSON -- aeson -import qualified Data.HashMap.Strict as M -- unordered-containers -import qualified Data.Vector as V -- vector - - -data OpSum x = OpSum x - deriving (Eq, Ord, Show, Data, Functor, Traversable, Foldable, Typeable, Generic) - -instance Serialize x => Serialize (OpSum x) -instance Hashable x => Hashable (OpSum x) -instance ToJSON x => ToJSON (OpSum x) where toJSON = genericToJSON jsonOptions -instance FromJSON x => FromJSON (OpSum x) where parseJSON = genericParseJSON jsonOptions - -instance (TypeOf x, Pretty x, ExpressionLike x) => TypeOf (OpSum x) where - typeOf p@(OpSum x) = do - ty <- typeOf x - case ty of -<<<<<<< HEAD - TypeList TypeAny -> return $ TypeInt Nothing - TypeList (TypeInt Nothing) -> return $ TypeInt Nothing - TypeMatrix _ TypeAny -> return $ TypeInt Nothing - TypeMatrix _ (TypeInt Nothing) -> return $ TypeInt Nothing - TypeSet (TypeInt Nothing) -> return $ TypeInt Nothing - TypeMSet (TypeInt Nothing) -> return $ TypeInt Nothing -||||||| merged common ancestors - TypeList TypeAny -> return TypeInt - TypeList TypeInt -> return TypeInt - TypeMatrix _ TypeAny -> return TypeInt - TypeMatrix _ TypeInt -> return TypeInt - TypeSet TypeInt -> return TypeInt - TypeMSet TypeInt -> return TypeInt -======= - TypeList TypeAny -> return (TypeInt NoTag) - TypeList (TypeInt NoTag) -> return (TypeInt NoTag) - TypeMatrix _ TypeAny -> return (TypeInt NoTag) - TypeMatrix _ (TypeInt NoTag) -> return (TypeInt NoTag) - TypeSet (TypeInt NoTag) -> return (TypeInt NoTag) - TypeMSet (TypeInt NoTag) -> return (TypeInt NoTag) ->>>>>>> taggedints - _ -> raiseTypeError $ vcat [ pretty p - , "The argument has type:" <+> pretty ty - ] - -instance BinaryOperator (OpSum x) where - opLexeme _ = L_Plus - -instance EvaluateOp OpSum where -<<<<<<< HEAD - evaluateOp p | any isUndef (childrenBi p) = return $ mkUndef (TypeInt Nothing) $ "Has undefined children:" <+> pretty p -||||||| merged common ancestors - evaluateOp p | any isUndef (childrenBi p) = return $ mkUndef TypeInt $ "Has undefined children:" <+> pretty p -======= - evaluateOp p | any isUndef (childrenBi p) = return $ mkUndef (TypeInt NoTag) $ "Has undefined children:" <+> pretty p ->>>>>>> taggedints - evaluateOp p@(OpSum x) - | Just xs <- listOut x -<<<<<<< HEAD - , any isUndef xs = return $ mkUndef (TypeInt Nothing) $ "Has undefined children:" <+> pretty p - evaluateOp (OpSum x) = ConstantInt Nothing . sum <$> intsOut "OpSum" x -||||||| merged common ancestors - , any isUndef xs = return $ mkUndef TypeInt $ "Has undefined children:" <+> pretty p - evaluateOp (OpSum x) = ConstantInt . sum <$> intsOut "OpSum" x -======= - , any isUndef xs = return $ mkUndef (TypeInt NoTag) $ "Has undefined children:" <+> pretty p - evaluateOp (OpSum x) = ConstantInt NoTag . sum <$> intsOut "OpSum" x ->>>>>>> taggedints - -instance (OpSum x :< x) => SimplifyOp OpSum x where - simplifyOp (OpSum x) - | Just xs <- listOut x - , let filtered = filter (/=0) xs - , length filtered /= length xs -- there were 0's - = return $ inject $ OpSum $ fromList filtered - simplifyOp _ = na "simplifyOp{OpSum}" - -instance (Pretty x, ExpressionLike x) => Pretty (OpSum x) where - prettyPrec prec op@(OpSum x) | Just [a,b] <- listOut x = prettyPrecBinOp prec [op] a b - prettyPrec _ (OpSum x) = "sum" <> prParens (pretty x) - -instance (VarSymBreakingDescription x, ExpressionLike x) => VarSymBreakingDescription (OpSum x) where - varSymBreakingDescription (OpSum x) | Just xs <- listOut x = JSON.Object $ M.fromList - [ ("type", JSON.String "OpSum") - , ("children", JSON.Array $ V.fromList $ map varSymBreakingDescription xs) - , ("symmetricChildren", JSON.Bool True) - ] - varSymBreakingDescription (OpSum x) = JSON.Object $ M.fromList - [ ("type", JSON.String "OpSum") - , ("children", varSymBreakingDescription x) - ] diff --git a/src/Conjure/Language/Expression/Op/TildeLt.hs.orig b/src/Conjure/Language/Expression/Op/TildeLt.hs.orig deleted file mode 100644 index 8e63c674fa..0000000000 --- a/src/Conjure/Language/Expression/Op/TildeLt.hs.orig +++ /dev/null @@ -1,135 +0,0 @@ -{-# LANGUAGE DeriveGeneric, DeriveDataTypeable, DeriveFunctor, DeriveTraversable, DeriveFoldable, ViewPatterns #-} - -module Conjure.Language.Expression.Op.TildeLt where - -import Conjure.Prelude -import Conjure.Language.Expression.Op.Internal.Common - -import qualified Data.Aeson as JSON -- aeson -import qualified Data.HashMap.Strict as M -- unordered-containers -import qualified Data.Vector as V -- vector - - -data OpTildeLt x = OpTildeLt x x - deriving (Eq, Ord, Show, Data, Functor, Traversable, Foldable, Typeable, Generic) - -instance Serialize x => Serialize (OpTildeLt x) -instance Hashable x => Hashable (OpTildeLt x) -instance ToJSON x => ToJSON (OpTildeLt x) where toJSON = genericToJSON jsonOptions -instance FromJSON x => FromJSON (OpTildeLt x) where parseJSON = genericParseJSON jsonOptions - -instance BinaryOperator (OpTildeLt x) where - opLexeme _ = L_TildeLt - -instance (TypeOf x, Pretty x) => TypeOf (OpTildeLt x) where - typeOf p@(OpTildeLt a b) = sameToSameToBool p a b [] - -instance EvaluateOp OpTildeLt where - evaluateOp (OpTildeLt x y) = return $ ConstantBool $ tilLt x y - where - freq :: Eq a => a -> [a] -> Int - freq i xs = sum [ 1 | j <- xs , i == j ] - - tupleE (i,j) = ConstantAbstract $ AbsLitTuple [i,j] - - tilLt (ConstantBool a) (ConstantBool b) = a < b -<<<<<<< HEAD - tilLt (ConstantInt Nothing a) (ConstantInt Nothing b) = a < b -||||||| merged common ancestors - tilLt (ConstantInt a) (ConstantInt b) = a < b -======= - tilLt (ConstantInt NoTag a) (ConstantInt NoTag b) = a < b - tilLt (ConstantInt (TagEnum an) a) (ConstantInt (TagEnum bn) b) - | an == bn = a < b ->>>>>>> taggedints - tilLt (viewConstantTuple -> Just []) - (viewConstantTuple -> Just []) = False - tilLt (viewConstantTuple -> Just (a:as)) - (viewConstantTuple -> Just (b:bs)) = - if tilLt a b - then True - else a == b && - tilLt (ConstantAbstract $ AbsLitTuple as) - (ConstantAbstract $ AbsLitTuple bs) - tilLt (viewConstantSet -> Just as) - (viewConstantSet -> Just bs) = - or [ and [ freq i as < freq i bs - , and [ if tilLt j i - then freq j as == freq j bs - else True - | j <- cs - ] - ] - | let cs = sortNub (as ++ bs) - , i <- cs - ] - tilLt (viewConstantMSet -> Just as) - (viewConstantMSet -> Just bs) = - or [ and [ freq i as < freq i bs - , and [ if tilLt j i - then freq j as == freq j bs - else True - | j <- cs - ] - ] - | let cs = as ++ bs - , i <- cs - ] - tilLt (viewConstantFunction -> Just as') - (viewConstantFunction -> Just bs') = - or [ and [ freq i as < freq i bs - , and [ if tilLt j i - then freq j as == freq j bs - else True - | j <- cs - ] - ] - | let as = map tupleE as' - , let bs = map tupleE bs' - , let cs = as ++ bs - , i <- cs - ] - tilLt (viewConstantRelation -> Just as') - (viewConstantRelation -> Just bs') = - or [ and [ freq i as < freq i bs - , and [ if tilLt j i - then freq j as == freq j bs - else True - | j <- cs - ] - ] - | let as = map (ConstantAbstract . AbsLitTuple) as' - , let bs = map (ConstantAbstract . AbsLitTuple) bs' - , let cs = as ++ bs - , i <- cs - ] - tilLt (viewConstantPartition -> Just as') - (viewConstantPartition -> Just bs') = - or [ and [ freq i as < freq i bs - , and [ if tilLt j i - then freq j as == freq j bs - else True - | j <- cs - ] - ] - | let as = map (ConstantAbstract . AbsLitSet) as' - , let bs = map (ConstantAbstract . AbsLitSet) bs' - , let cs = as ++ bs - , i <- cs - ] - tilLt a b = a < b - -instance SimplifyOp OpTildeLt x where - simplifyOp _ = na "simplifyOp{OpTildeLt}" - -instance Pretty x => Pretty (OpTildeLt x) where - prettyPrec prec op@(OpTildeLt a b) = prettyPrecBinOp prec [op] a b - -instance VarSymBreakingDescription x => VarSymBreakingDescription (OpTildeLt x) where - varSymBreakingDescription (OpTildeLt a b) = JSON.Object $ M.fromList - [ ("type", JSON.String "OpTildeLt") - , ("children", JSON.Array $ V.fromList - [ varSymBreakingDescription a - , varSymBreakingDescription b - ]) - ] diff --git a/src/Conjure/Language/Expression/Op/ToInt.hs.orig b/src/Conjure/Language/Expression/Op/ToInt.hs.orig deleted file mode 100644 index 79d9af652d..0000000000 --- a/src/Conjure/Language/Expression/Op/ToInt.hs.orig +++ /dev/null @@ -1,66 +0,0 @@ -{-# LANGUAGE DeriveGeneric, DeriveDataTypeable, DeriveFunctor, DeriveTraversable, DeriveFoldable #-} - -module Conjure.Language.Expression.Op.ToInt where - -import Conjure.Prelude -import Conjure.Language.Expression.Op.Internal.Common - -import qualified Data.Aeson as JSON -- aeson -import qualified Data.HashMap.Strict as M -- unordered-containers -import qualified Data.Vector as V -- vector - - -data OpToInt x = OpToInt x - deriving (Eq, Ord, Show, Data, Functor, Traversable, Foldable, Typeable, Generic) - -instance Serialize x => Serialize (OpToInt x) -instance Hashable x => Hashable (OpToInt x) -instance ToJSON x => ToJSON (OpToInt x) where toJSON = genericToJSON jsonOptions -instance FromJSON x => FromJSON (OpToInt x) where parseJSON = genericParseJSON jsonOptions - -instance (TypeOf x, Pretty x) => TypeOf (OpToInt x) where - typeOf p@(OpToInt x) = do - ty <- typeOf x - case ty of -<<<<<<< HEAD - TypeBool -> return $ TypeInt Nothing -||||||| merged common ancestors - TypeBool -> return TypeInt -======= - TypeBool -> return $ TypeInt NoTag ->>>>>>> taggedints - _ -> raiseTypeError $ vcat - [ pretty p - , "Expected type bool." - , "But got:" <+> pretty ty - ] - -instance EvaluateOp OpToInt where -<<<<<<< HEAD - evaluateOp (OpToInt (ConstantBool False)) = return (ConstantInt Nothing 0) - evaluateOp (OpToInt (ConstantBool True )) = return (ConstantInt Nothing 1) - evaluateOp (OpToInt ConstantUndefined{}) = return (ConstantInt Nothing 0) -||||||| merged common ancestors - evaluateOp (OpToInt (ConstantBool False)) = return (ConstantInt 0) - evaluateOp (OpToInt (ConstantBool True )) = return (ConstantInt 1) - evaluateOp (OpToInt ConstantUndefined{}) = return (ConstantInt 0) -======= - evaluateOp (OpToInt (ConstantBool False)) = return (ConstantInt NoTag 0) - evaluateOp (OpToInt (ConstantBool True )) = return (ConstantInt NoTag 1) - evaluateOp (OpToInt ConstantUndefined{}) = return (ConstantInt NoTag 0) ->>>>>>> taggedints - evaluateOp op = na $ "evaluateOp{OpToInt}:" <++> pretty (show op) - -instance SimplifyOp OpToInt x where - simplifyOp _ = na "simplifyOp{OpToInt}" - -instance Pretty x => Pretty (OpToInt x) where - prettyPrec _ (OpToInt a) = "toInt" <> prParens (pretty a) - -instance VarSymBreakingDescription x => VarSymBreakingDescription (OpToInt x) where - varSymBreakingDescription (OpToInt a) = JSON.Object $ M.fromList - [ ("type", JSON.String "OpToInt") - , ("children", JSON.Array $ V.fromList - [ varSymBreakingDescription a - ]) - ] diff --git a/src/Conjure/Language/Expression/Op/TwoBars.hs.orig b/src/Conjure/Language/Expression/Op/TwoBars.hs.orig deleted file mode 100644 index 922e5326e2..0000000000 --- a/src/Conjure/Language/Expression/Op/TwoBars.hs.orig +++ /dev/null @@ -1,109 +0,0 @@ -{-# LANGUAGE DeriveGeneric, DeriveDataTypeable, DeriveFunctor, DeriveTraversable, DeriveFoldable, ViewPatterns #-} - -module Conjure.Language.Expression.Op.TwoBars where - -import Conjure.Prelude -import Conjure.Language.Expression.Op.Internal.Common -import Conjure.Language.DomainSizeOf -import Conjure.Language.NameGen ( runNameGen) - -import qualified Data.Aeson as JSON -- aeson -import qualified Data.HashMap.Strict as M -- unordered-containers -import qualified Data.Vector as V -- vector - - -data OpTwoBars x = OpTwoBars x - deriving (Eq, Ord, Show, Data, Functor, Traversable, Foldable, Typeable, Generic) - -instance Serialize x => Serialize (OpTwoBars x) -instance Hashable x => Hashable (OpTwoBars x) -instance ToJSON x => ToJSON (OpTwoBars x) where toJSON = genericToJSON jsonOptions -instance FromJSON x => FromJSON (OpTwoBars x) where parseJSON = genericParseJSON jsonOptions - -instance (TypeOf x, Pretty x) => TypeOf (OpTwoBars x) where - typeOf p@(OpTwoBars a) = do - ty <- typeOf a - case ty of - TypeInt NoTag -> return () - TypeList{} -> return () - TypeSet{} -> return () - TypeMSet{} -> return () - TypeFunction{} -> return () - TypeSequence{} -> return () - TypeRelation{} -> return () - TypePartition{} -> return () - _ -> raiseTypeError $ vcat [ pretty p - , "Expected an integer or a collection." - , "But got:" <+> pretty ty - ] -<<<<<<< HEAD - return $ TypeInt Nothing -||||||| merged common ancestors - return TypeInt -======= - return $ TypeInt NoTag ->>>>>>> taggedints - -instance EvaluateOp OpTwoBars where - evaluateOp (OpTwoBars x) = - case x of - -- absolute value -<<<<<<< HEAD - ConstantInt Nothing y -> return $ ConstantInt Nothing $ abs y -||||||| merged common ancestors - ConstantInt y -> return $ ConstantInt $ abs y -======= - ConstantInt NoTag y -> return $ ConstantInt NoTag $ abs y ->>>>>>> taggedints - - -- cardinality of a constant -<<<<<<< HEAD - (viewConstantMatrix -> Just (_, xs)) -> return $ ConstantInt Nothing $ genericLength xs - (viewConstantSet -> Just xs) -> return $ ConstantInt Nothing $ genericLength $ sortNub xs - (viewConstantMSet -> Just xs) -> return $ ConstantInt Nothing $ genericLength xs - (viewConstantFunction -> Just xs) -> return $ ConstantInt Nothing $ genericLength $ sortNub xs - (viewConstantSequence -> Just xs) -> return $ ConstantInt Nothing $ genericLength xs - (viewConstantRelation -> Just xs) -> return $ ConstantInt Nothing $ genericLength $ sortNub xs - (viewConstantPartition -> Just xs) -> return $ ConstantInt Nothing $ genericLength $ sortNub $ concat xs -||||||| merged common ancestors - (viewConstantMatrix -> Just (_, xs)) -> return $ ConstantInt $ genericLength xs - (viewConstantSet -> Just xs) -> return $ ConstantInt $ genericLength $ sortNub xs - (viewConstantMSet -> Just xs) -> return $ ConstantInt $ genericLength xs - (viewConstantFunction -> Just xs) -> return $ ConstantInt $ genericLength $ sortNub xs - (viewConstantSequence -> Just xs) -> return $ ConstantInt $ genericLength xs - (viewConstantRelation -> Just xs) -> return $ ConstantInt $ genericLength $ sortNub xs - (viewConstantPartition -> Just xs) -> return $ ConstantInt $ genericLength $ sortNub $ concat xs -======= - (viewConstantMatrix -> Just (_, xs)) -> return $ ConstantInt NoTag $ genericLength xs - (viewConstantSet -> Just xs) -> return $ ConstantInt NoTag $ genericLength $ sortNub xs - (viewConstantMSet -> Just xs) -> return $ ConstantInt NoTag $ genericLength xs - (viewConstantFunction -> Just xs) -> return $ ConstantInt NoTag $ genericLength $ sortNub xs - (viewConstantSequence -> Just xs) -> return $ ConstantInt NoTag $ genericLength xs - (viewConstantRelation -> Just xs) -> return $ ConstantInt NoTag $ genericLength $ sortNub xs - (viewConstantPartition -> Just xs) -> return $ ConstantInt NoTag $ genericLength $ sortNub $ concat xs ->>>>>>> taggedints - - -- cardinality of a domain -<<<<<<< HEAD - DomainInConstant (DomainInt _ rs) -> ConstantInt Nothing . genericLength <$> rangesInts rs -||||||| merged common ancestors - DomainInConstant (DomainInt rs) -> ConstantInt . genericLength <$> rangesInts rs -======= - DomainInConstant (DomainInt _ rs) -> ConstantInt NoTag . genericLength <$> rangesInts rs ->>>>>>> taggedints - DomainInConstant dom -> runNameGen () $ domainSizeOf dom - _ -> na $ "evaluateOp OpTwoBars" <+> pretty (show x) - -instance SimplifyOp OpTwoBars x where - simplifyOp _ = na "simplifyOp{OpTwoBars}" - -instance Pretty x => Pretty (OpTwoBars x) where - prettyPrec _ (OpTwoBars a) = "|" <> pretty a <> "|" - -instance VarSymBreakingDescription x => VarSymBreakingDescription (OpTwoBars x) where - varSymBreakingDescription (OpTwoBars a) = JSON.Object $ M.fromList - [ ("type", JSON.String "OpTwoBars") - , ("children", JSON.Array $ V.fromList - [ varSymBreakingDescription a - ]) - ] diff --git a/src/Conjure/Language/Instantiate.hs.orig b/src/Conjure/Language/Instantiate.hs.orig deleted file mode 100644 index 47e9b2fd36..0000000000 --- a/src/Conjure/Language/Instantiate.hs.orig +++ /dev/null @@ -1,448 +0,0 @@ -{-# LANGUAGE GeneralizedNewtypeDeriving #-} - -module Conjure.Language.Instantiate - ( instantiateExpression - , instantiateDomain - , trySimplify - , entailed - ) where - --- conjure -import Conjure.Prelude -import Conjure.Bug -import Conjure.UserError -import Conjure.Language.Definition -import Conjure.Language.Expression.Op -import Conjure.Language.Domain -import Conjure.Language.Constant -import Conjure.Language.Type -import Conjure.Language.TypeOf -import Conjure.Language.Pretty -import Conjure.Process.Enumerate ( EnumerateDomain, enumerateDomain, enumerateInConstant ) - - --- | Try to simplify an expression recursively. -trySimplify :: (MonadUserError m, EnumerateDomain m) => Expression -> m Expression -trySimplify x = do - res <- runMaybeT $ instantiateExpression [] x - case res of - Just c -- if the expression can be evaluated into a Constant - | null [() | ConstantUndefined{} <- universe c] -- and if it doesn't contain undefined's in it - -> return (Constant c) -- evaluate to the constant - _ -> descendM trySimplify x -- otherwise, try the same on its children - - -instantiateExpression - :: (MonadFail m, EnumerateDomain m) - => [(Name, Expression)] - -> Expression - -> m Constant -instantiateExpression ctxt x = do - constant <- normaliseConstant <$> evalStateT (instantiateE x) ctxt - case (emptyCollection constant, constant) of - (_, TypedConstant{}) -> return constant - (True, _) -> do - ty <- typeOf x - return (TypedConstant constant ty) - (False, _) -> return constant - - -instantiateDomain - :: ( MonadFail m - , EnumerateDomain m - , Pretty r - , Default r - ) - => [(Name, Expression)] - -> Domain r Expression - -> m (Domain r Constant) -instantiateDomain ctxt x = normaliseDomain normaliseConstant <$> evalStateT (instantiateD x) ctxt - - -newtype HasUndef = HasUndef Any - deriving (Semigroup, Monoid) - -instantiateE - :: ( MonadFail m - , MonadState [(Name, Expression)] m - , EnumerateDomain m - ) - => Expression - -> m Constant - -instantiateE (Comprehension body gensOrConds) = do - let - loop :: ( MonadFail m - , MonadState [(Name, Expression)] m - , EnumerateDomain m - ) => [GeneratorOrCondition] -> WriterT HasUndef m [Constant] - loop [] = return <$> instantiateE body - loop (Generator (GenDomainNoRepr pat domain) : rest) = do - DomainInConstant domainConstant <- instantiateE (Domain domain) - let undefinedsInsideTheDomain = - [ und - | und@ConstantUndefined{} <- universeBi domainConstant - ] - if null undefinedsInsideTheDomain - then do - enumeration <- enumerateDomain domainConstant - concatMapM - (\ val -> scope $ do - valid <- bind pat val - if valid - then loop rest - else return [] ) - enumeration - else do - tell (HasUndef (Any True)) - return [] - loop (Generator (GenDomainHasRepr pat domain) : rest) = - loop (Generator (GenDomainNoRepr (Single pat) (forgetRepr domain)) : rest) - loop (Generator (GenInExpr pat expr) : rest) = do - exprConstant <- instantiateE expr - enumeration <- enumerateInConstant exprConstant - concatMapM - (\ val -> scope $ do - valid <- bind pat val - if valid - then loop rest - else return [] ) - enumeration - loop (Condition expr : rest) = do - constant <- instantiateE expr - if constant == ConstantBool True - then loop rest - else return [] - loop (ComprehensionLetting n expr : rest) = do - constant <- instantiateE expr - valid <- bind (Single n) constant - unless valid (bug "ComprehensionLetting.bind expected to be valid") - loop rest - - - (constants, HasUndef (Any undefinedsInsideGeneratorDomains)) <- runWriterT (loop gensOrConds) - if undefinedsInsideGeneratorDomains - then do - ty <- typeOf (Comprehension body gensOrConds) - return $ ConstantUndefined - "Comprehension contains undefined values inside generator domains." - ty - else - return $ ConstantAbstract $ AbsLitMatrix -<<<<<<< HEAD - (DomainInt Nothing [RangeBounded 1 (fromInt (genericLength constants))]) -||||||| merged common ancestors - (DomainInt [RangeBounded 1 (fromInt (genericLength constants))]) -======= - (DomainInt NoTag [RangeBounded 1 (fromInt (genericLength constants))]) ->>>>>>> taggedints - constants - -instantiateE (Reference name (Just (RecordField _ ty))) = return $ ConstantField name ty -instantiateE (Reference name (Just (VariantField _ ty))) = return $ ConstantField name ty -instantiateE (Reference _ (Just (Alias x))) = instantiateE x -instantiateE (Reference name _) = do - ctxt <- gets id - case name `lookup` ctxt of - Nothing -> fail $ vcat - $ ("No value for:" <+> pretty name) - : "Bindings in context:" - : prettyContext ctxt - Just x -> instantiateE x - -instantiateE (Constant c) = return c -instantiateE (AbstractLiteral lit) = instantiateAbsLit lit -instantiateE (Typed x ty) = TypedConstant <$> instantiateE x <*> pure ty -instantiateE (Op op) = instantiateOp op - --- "Domain () Expression"s inside expressions are handled specially -instantiateE (Domain (DomainReference _ (Just d))) = instantiateE (Domain d) -instantiateE (Domain (DomainReference name Nothing)) = do - ctxt <- gets id - case name `lookup` ctxt of - Just (Domain d) -> instantiateE (Domain d) - _ -> fail $ vcat - $ ("No value for:" <+> pretty name) - : "Bindings in context:" - : prettyContext ctxt -instantiateE (Domain domain) = DomainInConstant <$> instantiateD domain - -instantiateE (WithLocals b (AuxiliaryVars locals)) = do - forM_ locals $ \ local -> case local of - SuchThat xs -> forM_ xs $ \ x -> do - constant <- instantiateE x - case constant of - ConstantBool True -> return () - _ -> fail $ "local:" <+> pretty constant - _ -> fail $ "local:" <+> pretty local - instantiateE b - -instantiateE (WithLocals b (DefinednessConstraints locals)) = do - forM_ locals $ \ x -> do - constant <- instantiateE x - case constant of - ConstantBool True -> return () - _ -> fail $ "local:" <+> pretty constant - instantiateE b - -instantiateE x = fail $ "instantiateE:" <+> pretty (show x) - - -instantiateOp - :: ( MonadFail m - , MonadState [(Name, Expression)] m - , EnumerateDomain m - ) - => Op Expression - -> m Constant -instantiateOp opx = mapM instantiateE opx >>= evaluateOp . fmap normaliseConstant - - -instantiateAbsLit - :: ( MonadFail m - , MonadState [(Name, Expression)] m - , EnumerateDomain m - ) - => AbstractLiteral Expression - -> m Constant -instantiateAbsLit x = do - c <- mapM instantiateE x - case c of - -- for functions, if the same thing is mapped to multiple values, the result is undefined - AbsLitFunction vals -> do - let nubVals = sortNub vals - if length (sortNub (map fst nubVals)) == length nubVals - then return $ ConstantAbstract $ AbsLitFunction nubVals - else do - ty <- typeOf c - return $ ConstantUndefined "Multiple mappings for the same value." ty - _ -> return $ ConstantAbstract c - - -instantiateD - :: ( MonadFail m - , MonadState [(Name, Expression)] m - , EnumerateDomain m - , Pretty r - , Default r - ) - => Domain r Expression - -> m (Domain r Constant) -instantiateD (DomainAny t ty) = return (DomainAny t ty) -instantiateD DomainBool = return DomainBool -instantiateD (DomainIntE name x) = do - x' <- instantiateE x - let vals = case (x', viewConstantMatrix x', viewConstantSet x') of - (ConstantInt{}, _, _) -> [x'] - (_, Just (_, xs), _) -> xs - (_, _, Just xs) -> xs - _ -> [] -<<<<<<< HEAD - return (DomainInt name (map RangeSingle vals)) -instantiateD (DomainInt name ranges) = DomainInt name <$> mapM instantiateR ranges -||||||| merged common ancestors - return (DomainInt (map RangeSingle vals)) -instantiateD (DomainInt ranges) = DomainInt <$> mapM instantiateR ranges -======= - return (DomainInt NoTag (map RangeSingle vals)) -instantiateD (DomainInt t ranges) = DomainInt t <$> mapM instantiateR ranges ->>>>>>> taggedints -instantiateD (DomainEnum nm Nothing _) = do - st <- gets id - case lookup nm st of - Just (Domain dom) -> instantiateD (defRepr dom) - Just _ -> fail $ ("DomainEnum not found in state, Just:" <+> pretty nm) <++> vcat (map pretty st) - Nothing -> fail $ ("DomainEnum not found in state, Nothing:" <+> pretty nm) <++> vcat (map pretty st) -instantiateD (DomainEnum nm rs0 _) = do - let fmap4 = fmap . fmap . fmap . fmap - let e2c' x = either bug id (e2c x) - rs <- transformBiM (\ x -> Constant <$> instantiateE x ) (rs0 :: Maybe [Range Expression]) - |> fmap4 e2c' - st <- gets id - mp <- forM (universeBi rs :: [Name]) $ \ n -> case lookup n st of - Just (Constant (ConstantInt _ i)) -> return (n, i) - Nothing -> fail $ "No value for member of enum domain:" <+> pretty n - Just c -> fail $ vcat [ "Incompatible value for member of enum domain:" <+> pretty nm - , " Looking up for member:" <+> pretty n - , " Expected an integer, but got:" <+> pretty c - ] - return (DomainEnum nm (rs :: Maybe [Range Constant]) (Just mp)) -instantiateD (DomainUnnamed nm s) = DomainUnnamed nm <$> instantiateE s -instantiateD (DomainTuple inners) = DomainTuple <$> mapM instantiateD inners -instantiateD (DomainRecord inners) = DomainRecord <$> sequence [ do d' <- instantiateD d ; return (n,d') - | (n,d) <- inners ] -instantiateD (DomainVariant inners) = DomainVariant <$> sequence [ do d' <- instantiateD d ; return (n,d') - | (n,d) <- inners ] -instantiateD (DomainMatrix index inner) = DomainMatrix <$> instantiateD index <*> instantiateD inner -instantiateD (DomainSet r attrs inner) = DomainSet r <$> instantiateSetAttr attrs <*> instantiateD inner -instantiateD (DomainMSet r attrs inner) = DomainMSet r <$> instantiateMSetAttr attrs <*> instantiateD inner -instantiateD (DomainFunction r attrs innerFr innerTo) = DomainFunction r <$> instantiateFunctionAttr attrs <*> instantiateD innerFr <*> instantiateD innerTo -instantiateD (DomainSequence r attrs inner) = DomainSequence r <$> instantiateSequenceAttr attrs <*> instantiateD inner -instantiateD (DomainRelation r attrs inners) = DomainRelation r <$> instantiateRelationAttr attrs <*> mapM instantiateD inners -instantiateD (DomainPartition r attrs inner) = DomainPartition r <$> instantiatePartitionAttr attrs <*> instantiateD inner -instantiateD (DomainPermutation r attrs inner) = DomainPermutation r <$> instantiatePermutationAttr attrs <*> instantiateD inner -instantiateD (DomainOp nm ds) = DomainOp nm <$> mapM instantiateD ds -instantiateD (DomainReference _ (Just d)) = instantiateD d -instantiateD (DomainReference name Nothing) = do - ctxt <- gets id - case name `lookup` ctxt of - Just (Domain d) -> instantiateD (defRepr d) - _ -> fail $ vcat - $ ("No value for:" <+> pretty name) - : "Bindings in context:" - : prettyContext ctxt -instantiateD DomainMetaVar{} = bug "instantiateD DomainMetaVar" - - -instantiateSetAttr - :: ( MonadFail m - , MonadState [(Name, Expression)] m - , EnumerateDomain m - ) - => SetAttr Expression - -> m (SetAttr Constant) -instantiateSetAttr (SetAttr s) = SetAttr <$> instantiateSizeAttr s - - -instantiateSizeAttr - :: ( MonadFail m - , MonadState [(Name, Expression)] m - , EnumerateDomain m - ) - => SizeAttr Expression - -> m (SizeAttr Constant) -instantiateSizeAttr SizeAttr_None = return SizeAttr_None -instantiateSizeAttr (SizeAttr_Size x) = SizeAttr_Size <$> instantiateE x -instantiateSizeAttr (SizeAttr_MinSize x) = SizeAttr_MinSize <$> instantiateE x -instantiateSizeAttr (SizeAttr_MaxSize x) = SizeAttr_MaxSize <$> instantiateE x -instantiateSizeAttr (SizeAttr_MinMaxSize x y) = SizeAttr_MinMaxSize <$> instantiateE x <*> instantiateE y - - -instantiateMSetAttr - :: ( MonadFail m - , MonadState [(Name, Expression)] m - , EnumerateDomain m - ) - => MSetAttr Expression - -> m (MSetAttr Constant) -instantiateMSetAttr (MSetAttr s o) = MSetAttr <$> instantiateSizeAttr s <*> instantiateOccurAttr o - - -instantiateOccurAttr - :: ( MonadFail m - , MonadState [(Name, Expression)] m - , EnumerateDomain m - ) - => OccurAttr Expression - -> m (OccurAttr Constant) -instantiateOccurAttr OccurAttr_None = return OccurAttr_None -instantiateOccurAttr (OccurAttr_MinOccur x) = OccurAttr_MinOccur <$> instantiateE x -instantiateOccurAttr (OccurAttr_MaxOccur x) = OccurAttr_MaxOccur <$> instantiateE x -instantiateOccurAttr (OccurAttr_MinMaxOccur x y) = OccurAttr_MinMaxOccur <$> instantiateE x <*> instantiateE y - - -instantiateFunctionAttr - :: ( MonadFail m - , MonadState [(Name, Expression)] m - , EnumerateDomain m - ) - => FunctionAttr Expression - -> m (FunctionAttr Constant) -instantiateFunctionAttr (FunctionAttr s p j) = - FunctionAttr <$> instantiateSizeAttr s - <*> pure p - <*> pure j - - -instantiateSequenceAttr - :: ( MonadFail m - , MonadUserError m - , MonadState [(Name, Expression)] m - , EnumerateDomain m - ) - => SequenceAttr Expression - -> m (SequenceAttr Constant) -instantiateSequenceAttr (SequenceAttr s j) = - SequenceAttr <$> instantiateSizeAttr s - <*> pure j - - -instantiateRelationAttr - :: ( MonadFail m - , MonadUserError m - , MonadState [(Name, Expression)] m - , EnumerateDomain m - ) - => RelationAttr Expression - -> m (RelationAttr Constant) -instantiateRelationAttr (RelationAttr s b) = RelationAttr <$> instantiateSizeAttr s <*> pure b - - -instantiatePartitionAttr - :: ( MonadFail m - , MonadUserError m - , MonadState [(Name, Expression)] m - , EnumerateDomain m - ) - => PartitionAttr Expression - -> m (PartitionAttr Constant) -instantiatePartitionAttr (PartitionAttr a b r) = - PartitionAttr <$> instantiateSizeAttr a - <*> instantiateSizeAttr b - <*> pure r - - -instantiatePermutationAttr - :: ( MonadFail m - , MonadUserError m - , MonadState [(Name, Expression)] m - , EnumerateDomain m - ) - => PermutationAttr Expression - -> m (PermutationAttr Constant) -instantiatePermutationAttr (PermutationAttr s) = - PermutationAttr <$> instantiateSizeAttr s - - - -instantiateR - :: ( MonadFail m - , MonadUserError m - , MonadState [(Name, Expression)] m - , EnumerateDomain m - ) - => Range Expression - -> m (Range Constant) -instantiateR RangeOpen = return RangeOpen -instantiateR (RangeSingle x) = RangeSingle <$> instantiateE x -instantiateR (RangeLowerBounded x) = RangeLowerBounded <$> instantiateE x -instantiateR (RangeUpperBounded x) = RangeUpperBounded <$> instantiateE x -instantiateR (RangeBounded x y) = RangeBounded <$> instantiateE x <*> instantiateE y - - -bind :: (Functor m, MonadState [(Name, Expression)] m) - => AbstractPattern - -> Constant - -> m Bool -- False means skip -bind (Single nm) val = modify ((nm, Constant val) :) >> return True -bind (AbsPatTuple pats) (ConstantAbstract (AbsLitTuple vals)) - | length pats == length vals = and <$> zipWithM bind pats vals -bind (AbsPatMatrix pats) (ConstantAbstract (AbsLitMatrix _ vals)) - | length pats == length vals = and <$> zipWithM bind pats vals -bind (AbsPatSet pats) (ConstantAbstract (AbsLitSet vals)) - | length pats == length vals = and <$> zipWithM bind pats vals - | otherwise = return False -bind pat val = bug $ "Instantiate.bind:" <++> vcat ["pat:" <+> pretty pat, "val:" <+> pretty val] - - --- check if the given expression can be evaluated to True --- False means it is not entailed, as opposed to "it is known to be false" -entailed :: (MonadUserError m, EnumerateDomain m) => Expression -> m Bool -entailed x = do - -- traceM $ show $ "entailed x:" <+> pretty x - c <- trySimplify x - -- traceM $ show $ "entailed c:" <+> pretty c - case c of - Constant (ConstantBool True) -> return True - _ -> return False - diff --git a/src/Conjure/Language/Lenses.hs.orig b/src/Conjure/Language/Lenses.hs.orig deleted file mode 100644 index 44e8daeb5b..0000000000 --- a/src/Conjure/Language/Lenses.hs.orig +++ /dev/null @@ -1,1544 +0,0 @@ -{-# LANGUAGE KindSignatures #-} -{-# LANGUAGE ViewPatterns #-} - -module Conjure.Language.Lenses where - -import Conjure.Prelude -import Conjure.Language.Definition -import Conjure.Language.Domain -import Conjure.Language.Type -import Conjure.Language.TypeOf -import Conjure.Language.Expression.Op -import Conjure.Language.Pretty -import Conjure.Language.AdHoc - - --- | To use a lens for constructing stuf. -make :: (Proxy Identity -> (a, b)) -> a -make f = fst (f (Proxy :: Proxy Identity)) - --- | To use a lens for deconstructing stuf. -match :: (Proxy (m :: * -> *) -> (a, b -> m c)) -> b -> m c -match f = snd (f Proxy) - -followAliases :: CanBeAnAlias b => (b -> c) -> b -> c -followAliases m (isAlias -> Just x) = followAliases m x -followAliases m x = m x - -tryMatch :: (Proxy Maybe -> (a, b -> Maybe c)) -> b -> Maybe c -tryMatch f = match f - -matchOr :: c -> (Proxy Maybe -> (a, b -> Maybe c)) -> b -> c -matchOr defOut f inp = fromMaybe defOut (match f inp) - -matchDef :: (Proxy Maybe -> (a, b -> Maybe b)) -> b -> b -matchDef f inp = matchOr inp f inp - -matchDefs :: CanBeAnAlias b => [Proxy Maybe -> (a, b -> Maybe b)] -> b -> b -matchDefs fs inp = - case mapMaybe (`match` inp) fs of - [] -> inp - (out:_) -> matchDefs fs out - - --------------------------------------------------------------------------------- --- Lenses (for a weird definition of lens) ------------------------------------- --------------------------------------------------------------------------------- - - -opMinus - :: ( Op x :< x - , Pretty x - , MonadFail m - ) - => Proxy (m :: * -> *) - -> ( x -> x -> x - , x -> m (x,x) - ) -opMinus _ = - ( \ x y -> inject (MkOpMinus (OpMinus x y)) - , \ p -> do - op <- project p - case op of - MkOpMinus (OpMinus x y) -> return (x,y) - _ -> na ("Lenses.opMinus:" <++> pretty p) - ) - - -opDiv - :: ( Op x :< x - , Pretty x - , MonadFail m - ) - => Proxy (m :: * -> *) - -> ( x -> x -> x - , x -> m (x,x) - ) -opDiv _ = - ( \ x y -> inject (MkOpDiv (OpDiv x y)) - , \ p -> do - op <- project p - case op of - MkOpDiv (OpDiv x y) -> return (x,y) - _ -> na ("Lenses.opDiv:" <++> pretty p) - ) - - -opMod - :: ( Op x :< x - , Pretty x - , MonadFail m - ) - => Proxy (m :: * -> *) - -> ( x -> x -> x - , x -> m (x,x) - ) -opMod _ = - ( \ x y -> inject (MkOpMod (OpMod x y)) - , \ p -> do - op <- project p - case op of - MkOpMod (OpMod x y) -> return (x,y) - _ -> na ("Lenses.opMod:" <++> pretty p) - ) - - -opPow - :: ( Op x :< x - , Pretty x - , MonadFail m - ) - => Proxy (m :: * -> *) - -> ( x -> x -> x - , x -> m (x,x) - ) -opPow _ = - ( \ x y -> inject (MkOpPow (OpPow x y)) - , \ p -> do - op <- project p - case op of - MkOpPow (OpPow x y) -> return (x,y) - _ -> na ("Lenses.opPow:" <++> pretty p) - ) - - -opNegate - :: ( Op x :< x - , Pretty x - , MonadFail m - ) - => Proxy (m :: * -> *) - -> ( x -> x - , x -> m x - ) -opNegate _ = - ( inject . MkOpNegate . OpNegate - , \ p -> do - op <- project p - case op of - MkOpNegate (OpNegate x) -> return x - _ -> na ("Lenses.opNegate:" <++> pretty p) - ) - - -opDontCare - :: ( Op x :< x - , Pretty x - , MonadFail m - ) - => Proxy (m :: * -> *) - -> ( x -> x - , x -> m x - ) -opDontCare _ = - ( inject . MkOpDontCare . OpDontCare - , \ p -> do - op <- project p - case op of - MkOpDontCare (OpDontCare x) -> return x - _ -> na ("Lenses.opDontCare:" <++> pretty p) - ) - - -opDefined - :: MonadFail m - => Proxy (m :: * -> *) - -> ( Expression -> Expression - , Expression -> m Expression - ) -opDefined _ = - ( inject . MkOpDefined . OpDefined - , followAliases extract - ) - where - extract (Op (MkOpDefined (OpDefined x))) = return x - extract p = na ("Lenses.opDefined:" <++> pretty p) - - -opRange - :: MonadFail m - => Proxy (m :: * -> *) - -> ( Expression -> Expression - , Expression -> m Expression - ) -opRange _ = - ( inject . MkOpRange . OpRange - , followAliases extract - ) - where - extract (Op (MkOpRange (OpRange x))) = return x - extract p = na ("Lenses.opRange:" <++> pretty p) - - -opDefinedOrRange - :: ( Op x :< x - , Pretty x - , MonadFail m - ) - => Proxy (m :: * -> *) - -> ( (x -> x, x) -> x - , x -> m (x -> x, x) - ) -opDefinedOrRange _ = - ( \ (mk, x) -> mk x - , \ p -> case project p of - Just (MkOpDefined (OpDefined x)) -> return (inject . MkOpDefined . OpDefined , x) - Just (MkOpRange (OpRange x)) -> return (inject . MkOpRange . OpRange , x) - _ -> na ("Lenses.opDefinedOrRange" <++> pretty p) - ) - - -opRestrict - :: MonadFail m - => Proxy (m :: * -> *) - -> ( Expression -> Domain () Expression -> Expression - , Expression -> m (Expression, Domain () Expression) - ) -opRestrict _ = - ( \ x d -> inject $ MkOpRestrict $ OpRestrict x (Domain d) - , followAliases extract - ) - where - extract (Op (MkOpRestrict (OpRestrict x (Domain d)))) = return (x, d) - extract p = na ("Lenses.opRestrict:" <++> pretty p) - - -opToInt - :: ( Op x :< x - , Pretty x - , MonadFail m - ) - => Proxy (m :: * -> *) - -> ( x -> x - , x -> m x - ) -opToInt _ = - ( inject . MkOpToInt . OpToInt - , \ p -> do - op <- project p - case op of - MkOpToInt (OpToInt x) -> return x - _ -> na ("Lenses.opToInt:" <++> pretty p) - ) - - -opPowerSet - :: ( Op x :< x - , Pretty x - , MonadFail m - ) - => Proxy (m :: * -> *) - -> ( x -> x - , x -> m x - ) -opPowerSet _ = - ( inject . MkOpPowerSet . OpPowerSet - , \ p -> do - op <- project p - case op of - MkOpPowerSet (OpPowerSet x) -> return x - _ -> na ("Lenses.opPowerSet:" <++> pretty p) - ) - - -opToSet - :: ( Op x :< x - , Pretty x - , MonadFail m - ) - => Proxy (m :: * -> *) - -> ( x -> x - , x -> m x - ) -opToSet _ = - ( inject . MkOpToSet . OpToSet False - , \ p -> do - op <- project p - case op of - MkOpToSet (OpToSet _ x) -> return x - _ -> na ("Lenses.opToSet:" <++> pretty p) - ) - - -opPermutationTuples - :: ( Op x :< x - , Pretty x - , MonadFail m - ) - => Proxy (m :: * -> *) - -> ( x -> x - , x -> m x - ) -opPermutationTuples _ = - ( inject . MkOpPermutationTuples . OpPermutationTuples - , \ p -> do - op <- project p - case op of - MkOpPermutationTuples (OpPermutationTuples x) -> return x - _ -> na ("Lenses.opPermutationTuples:" <++> pretty p) - ) - - - -opToSetWithFlag - :: ( Op x :< x - , Pretty x - , MonadFail m - ) - => Proxy (m :: * -> *) - -> ( Bool -> x -> x - , x -> m (Bool, x) - ) -opToSetWithFlag _ = - ( \ b x -> inject $ MkOpToSet $ OpToSet b x - , \ p -> do - op <- project p - case op of - MkOpToSet (OpToSet b x) -> return (b, x) - _ -> na ("Lenses.opToSet:" <++> pretty p) - ) - - -opToMSet - :: ( Op x :< x - , Pretty x - , MonadFail m - ) - => Proxy (m :: * -> *) - -> ( x -> x - , x -> m x - ) -opToMSet _ = - ( inject . MkOpToMSet . OpToMSet - , \ p -> do - op <- project p - case op of - MkOpToMSet (OpToMSet x) -> return x - _ -> na ("Lenses.opToMSet:" <++> pretty p) - ) - - -opToRelation - :: ( Op x :< x - , Pretty x - , MonadFail m - ) - => Proxy (m :: * -> *) - -> ( x -> x - , x -> m x - ) -opToRelation _ = - ( inject . MkOpToRelation . OpToRelation - , \ p -> do - op <- project p - case op of - MkOpToRelation (OpToRelation x) -> return x - _ -> na ("Lenses.opToRelation:" <++> pretty p) - ) - - -opParts - :: ( Op x :< x - , Pretty x - , MonadFail m - ) - => Proxy (m :: * -> *) - -> ( x -> x - , x -> m x - ) -opParts _ = - ( inject . MkOpParts . OpParts - , \ p -> do - op <- project p - case op of - MkOpParts (OpParts x) -> return x - _ -> na ("Lenses.opParts:" <++> pretty p) - ) - - -opParty - :: ( Op x :< x - , Pretty x - , MonadFail m - ) - => Proxy (m :: * -> *) - -> ( x -> x -> x - , x -> m (x, x) - ) -opParty _ = - ( \ x y -> inject $ MkOpParty $ OpParty x y - , \ p -> do - op <- project p - case op of - MkOpParty (OpParty x y) -> return (x,y) - _ -> na ("Lenses.opParty:" <++> pretty p) - ) - - -opParticipants - :: ( Op x :< x - , Pretty x - , MonadFail m - ) - => Proxy (m :: * -> *) - -> ( x -> x - , x -> m x - ) -opParticipants _ = - ( inject . MkOpParticipants . OpParticipants - , \ p -> do - op <- project p - case op of - MkOpParticipants (OpParticipants x) -> return x - _ -> na ("Lenses.opParticipants:" <++> pretty p) - ) - - -opImage - :: ( Op x :< x - , Pretty x - , MonadFail m - ) - => Proxy (m :: * -> *) - -> ( x -> x -> x - , x -> m (x, x) - ) -opImage _ = - ( \ x y -> inject $ MkOpImage $ OpImage x y - , \ p -> do - op <- project p - case op of - MkOpImage (OpImage x y) -> return (x,y) - _ -> na ("Lenses.opImage:" <++> pretty p) - ) - - -opImageSet - :: ( Op x :< x - , Pretty x - , MonadFail m - ) - => Proxy (m :: * -> *) - -> ( x -> x -> x - , x -> m (x, x) - ) -opImageSet _ = - ( \ x y -> inject $ MkOpImageSet $ OpImageSet x y - , \ p -> do - op <- project p - case op of - MkOpImageSet (OpImageSet x y) -> return (x,y) - _ -> na ("Lenses.opImageSet:" <++> pretty p) - ) - - -opRelationProj - :: ( Op x :< x - , Pretty x - , MonadFail m - ) - => Proxy (m :: * -> *) - -> ( x -> [Maybe x] -> x - , x -> m (x, [Maybe x]) - ) -opRelationProj _ = - ( \ x ys -> inject $ MkOpRelationProj $ OpRelationProj x ys - , \ p -> do - op <- project p - case op of - MkOpRelationProj (OpRelationProj x ys) -> return (x,ys) - _ -> na ("Lenses.opRelationProj:" <++> pretty p) - ) - - -opRelationImage - :: ( Op x :< x - , Pretty x - , MonadFail m - ) - => Proxy (m :: * -> *) - -> ( x -> [x] -> x - , x -> m (x, [x]) - ) -opRelationImage _ = - ( \ x ys -> inject $ MkOpRelationProj $ OpRelationProj x (map Just ys) - , \ p -> do - op <- project p - case op of - MkOpRelationProj (OpRelationProj x ys) - | let ys' = catMaybes ys - , length ys' == length ys -- they were all Just's - -> return (x,ys') - _ -> na ("Lenses.opRelationProj:" <++> pretty p) - ) - - -opIndexing - :: ( Op x :< x - , Pretty x - , MonadFail m - ) - => Proxy (m :: * -> *) - -> ( x -> x -> x - , x -> m (x,x) - ) -opIndexing _ = - ( \ x y -> inject (MkOpIndexing (OpIndexing x y)) - , \ p -> do - op <- project p - case op of - MkOpIndexing (OpIndexing x y) -> return (x,y) - _ -> na ("Lenses.opIndexing:" <++> pretty p) - ) - - -opMatrixIndexing - :: ( Op x :< x - , Pretty x - , TypeOf x - , MonadFail m - ) - => Proxy (m :: * -> *) - -> ( x -> [x] -> x - , x -> m (x,[x]) - ) -opMatrixIndexing _ = - ( foldl (make opIndexing) - , \ p -> do - (m, is) <- go p - if null is - then na ("Lenses.opMatrixIndexing:" <+> pretty p) - else return (m, is) - ) - where - go p = case project p of - Just (MkOpIndexing (OpIndexing x i)) -> do - ty <- typeOf x - case ty of - TypeMatrix{} -> return () - TypeList{} -> return () - _ -> na ("Lenses.opMatrixIndexing:" <+> pretty p) - (m,is) <- go x - return (m, is ++ [i]) - _ -> return (p, []) - - -opSlicing - :: ( Op x :< x - , Pretty x - , MonadFail m - ) - => Proxy (m :: * -> *) - -> ( x -> Maybe x -> Maybe x -> x - , x -> m (x, Maybe x, Maybe x) - ) -opSlicing _ = - ( \ x y z -> inject (MkOpSlicing (OpSlicing x y z)) - , \ p -> do - op <- project p - case op of - MkOpSlicing (OpSlicing x y z) -> return (x,y,z) - _ -> na ("Lenses.opSlicing:" <++> pretty p) - ) - - -opFlatten - :: ( Op x :< x - , Pretty x - , MonadFail m - ) - => Proxy (m :: * -> *) - -> ( x -> x - , x -> m x - ) -opFlatten _ = - ( inject . MkOpFlatten . OpFlatten Nothing - , \ p -> do - op <- project p - case op of - MkOpFlatten (OpFlatten Nothing x) -> return x - _ -> na ("Lenses.opFlatten:" <++> pretty p) - ) - - -opConcatenate - :: ( Op x :< x - , Pretty x - , MonadFail m - ) - => Proxy (m :: * -> *) - -> ( x -> x - , x -> m x - ) -opConcatenate _ = - ( inject . MkOpFlatten . OpFlatten (Just 1) - , \ p -> do - op <- project p - case op of - MkOpFlatten (OpFlatten (Just 1) x) -> return x - _ -> na ("Lenses.opConcatenate:" <++> pretty p) - ) - - -opIn - :: ( Op x :< x - , Pretty x - , MonadFail m - ) - => Proxy (m :: * -> *) - -> ( x -> x -> x - , x -> m (x,x) - ) -opIn _ = - ( \ x y -> inject (MkOpIn (OpIn x y)) - , \ p -> do - op <- project p - case op of - MkOpIn (OpIn x y) -> return (x,y) - _ -> na ("Lenses.opIn:" <++> pretty p) - ) - - -opFreq - :: ( Op x :< x - , Pretty x - , MonadFail m - ) - => Proxy (m :: * -> *) - -> ( x -> x -> x - , x -> m (x,x) - ) -opFreq _ = - ( \ x y -> inject (MkOpFreq (OpFreq x y)) - , \ p -> do - op <- project p - case op of - MkOpFreq (OpFreq x y) -> return (x,y) - _ -> na ("Lenses.opFreq:" <++> pretty p) - ) - - -opHist - :: ( Op x :< x - , Pretty x - , MonadFail m - ) - => Proxy (m :: * -> *) - -> ( x -> x - , x -> m x - ) -opHist _ = - ( inject . MkOpHist . OpHist - , \ p -> do - op <- project p - case op of - MkOpHist (OpHist x) -> return x - _ -> na ("Lenses.opHist:" <++> pretty p) - ) - - -opIntersect - :: ( Op x :< x - , Pretty x - , MonadFail m - ) - => Proxy (m :: * -> *) - -> ( x -> x -> x - , x -> m (x,x) - ) -opIntersect _ = - ( \ x y -> inject (MkOpIntersect (OpIntersect x y)) - , \ p -> do - op <- project p - case op of - MkOpIntersect (OpIntersect x y) -> return (x,y) - _ -> na ("Lenses.opIntersect:" <++> pretty p) - ) - - -opUnion - :: ( Op x :< x - , Pretty x - , MonadFail m - ) - => Proxy (m :: * -> *) - -> ( x -> x -> x - , x -> m (x,x) - ) -opUnion _ = - ( \ x y -> inject (MkOpUnion (OpUnion x y)) - , \ p -> do - op <- project p - case op of - MkOpUnion (OpUnion x y) -> return (x,y) - _ -> na ("Lenses.opUnion:" <++> pretty p) - ) - - -opSubsetEq - :: ( Op x :< x - , Pretty x - , MonadFail m - ) - => Proxy (m :: * -> *) - -> ( x -> x -> x - , x -> m (x,x) - ) -opSubsetEq _ = - ( \ x y -> inject (MkOpSubsetEq (OpSubsetEq x y)) - , \ p -> do - op <- project p - case op of - MkOpSubsetEq (OpSubsetEq x y) -> return (x,y) - _ -> na ("Lenses.opSubsetEq:" <++> pretty p) - ) - - -opEq - :: ( Op x :< x - , Pretty x - , MonadFail m - ) - => Proxy (m :: * -> *) - -> ( x -> x -> x - , x -> m (x,x) - ) -opEq _ = - ( \ x y -> inject (MkOpEq (OpEq x y)) - , \ p -> do - op <- project p - case op of - MkOpEq (OpEq x y) -> return (x,y) - _ -> na ("Lenses.opEq:" <++> pretty p) - ) - - -opNeq - :: ( Op x :< x - , Pretty x - , MonadFail m - ) - => Proxy (m :: * -> *) - -> ( x -> x -> x - , x -> m (x,x) - ) -opNeq _ = - ( \ x y -> inject (MkOpNeq (OpNeq x y)) - , \ p -> do - op <- project p - case op of - MkOpNeq (OpNeq x y) -> return (x,y) - _ -> na ("Lenses.opNeq:" <++> pretty p) - ) - - -opLt - :: ( Op x :< x - , Pretty x - , MonadFail m - ) - => Proxy (m :: * -> *) - -> ( x -> x -> x - , x -> m (x,x) - ) -opLt _ = - ( \ x y -> inject (MkOpLt (OpLt x y)) - , \ p -> do - op <- project p - case op of - MkOpLt (OpLt x y) -> return (x,y) - _ -> na ("Lenses.opLt:" <++> pretty p) - ) - - -opLeq - :: ( Op x :< x - , Pretty x - , MonadFail m - ) - => Proxy (m :: * -> *) - -> ( x -> x -> x - , x -> m (x,x) - ) -opLeq _ = - ( \ x y -> inject (MkOpLeq (OpLeq x y)) - , \ p -> do - op <- project p - case op of - MkOpLeq (OpLeq x y) -> return (x,y) - _ -> na ("Lenses.opLeq:" <++> pretty p) - ) - - -opGt - :: ( Op x :< x - , Pretty x - , MonadFail m - ) - => Proxy (m :: * -> *) - -> ( x -> x -> x - , x -> m (x,x) - ) -opGt _ = - ( \ x y -> inject (MkOpGt (OpGt x y)) - , \ p -> do - op <- project p - case op of - MkOpGt (OpGt x y) -> return (x,y) - _ -> na ("Lenses.opGt:" <++> pretty p) - ) - - -opGeq - :: ( Op x :< x - , Pretty x - , MonadFail m - ) - => Proxy (m :: * -> *) - -> ( x -> x -> x - , x -> m (x,x) - ) -opGeq _ = - ( \ x y -> inject (MkOpGeq (OpGeq x y)) - , \ p -> do - op <- project p - case op of - MkOpGeq (OpGeq x y) -> return (x,y) - _ -> na ("Lenses.opGeq:" <++> pretty p) - ) - - -opDotLt - :: ( Op x :< x - , Pretty x - , MonadFail m - ) - => Proxy (m :: * -> *) - -> ( x -> x -> x - , x -> m (x,x) - ) -opDotLt _ = - ( \ x y -> inject (MkOpDotLt (OpDotLt x y)) - , \ p -> do - op <- project p - case op of - MkOpDotLt (OpDotLt x y) -> return (x,y) - _ -> na ("Lenses.opDotLt:" <++> pretty p) - ) - - -opDotLeq - :: ( Op x :< x - , Pretty x - , MonadFail m - ) - => Proxy (m :: * -> *) - -> ( x -> x -> x - , x -> m (x,x) - ) -opDotLeq _ = - ( \ x y -> inject (MkOpDotLeq (OpDotLeq x y)) - , \ p -> do - op <- project p - case op of - MkOpDotLeq (OpDotLeq x y) -> return (x,y) - _ -> na ("Lenses.opDotLeq:" <++> pretty p) - ) - - -opTildeLt - :: ( Op x :< x - , Pretty x - , MonadFail m - ) - => Proxy (m :: * -> *) - -> ( x -> x -> x - , x -> m (x,x) - ) -opTildeLt _ = - ( \ x y -> inject (MkOpTildeLt (OpTildeLt x y)) - , \ p -> do - op <- project p - case op of - MkOpTildeLt (OpTildeLt x y) -> return (x,y) - _ -> na ("Lenses.opTildeLt:" <++> pretty p) - ) - - -opTildeLeq - :: ( Op x :< x - , Pretty x - , MonadFail m - ) - => Proxy (m :: * -> *) - -> ( x -> x -> x - , x -> m (x,x) - ) -opTildeLeq _ = - ( \ x y -> inject (MkOpTildeLeq (OpTildeLeq x y)) - , \ p -> do - op <- project p - case op of - MkOpTildeLeq (OpTildeLeq x y) -> return (x,y) - _ -> na ("Lenses.opTildeLeq:" <++> pretty p) - ) - - -opOr - :: ( Op x :< x - , Pretty x - , MonadFail m - ) - => Proxy (m :: * -> *) - -> ( x -> x - , x -> m x - ) -opOr _ = - ( inject . MkOpOr . OpOr - , \ p -> do - op <- project p - case op of - MkOpOr (OpOr xs) -> return xs - _ -> na ("Lenses.opOr:" <++> pretty p) - ) - - -opAnd - :: ( Op x :< x - , Pretty x - , MonadFail m - ) - => Proxy (m :: * -> *) - -> ( x -> x - , x -> m x - ) -opAnd _ = - ( inject . MkOpAnd . OpAnd - , \ p -> do - op <- project p - case op of - MkOpAnd (OpAnd xs) -> return xs - _ -> na ("Lenses.opAnd:" <++> pretty p) - ) - - -opMax - :: ( Op x :< x - , Pretty x - , MonadFail m - ) - => Proxy (m :: * -> *) - -> ( x -> x - , x -> m x - ) -opMax _ = - ( inject . MkOpMax . OpMax - , \ p -> do - op <- project p - case op of - MkOpMax (OpMax xs) -> return xs - _ -> na ("Lenses.opMax:" <++> pretty p) - ) - - -opMin - :: ( Op x :< x - , Pretty x - , MonadFail m - ) - => Proxy (m :: * -> *) - -> ( x -> x - , x -> m x - ) -opMin _ = - ( inject . MkOpMin . OpMin - , \ p -> do - op <- project p - case op of - MkOpMin (OpMin xs) -> return xs - _ -> na ("Lenses.opMin:" <++> pretty p) - ) - - -opImply - :: ( Op x :< x - , Pretty x - , MonadFail m - ) - => Proxy (m :: * -> *) - -> ( x -> x -> x - , x -> m (x,x) - ) -opImply _ = - ( \ x y -> inject (MkOpImply (OpImply x y)) - , \ p -> do - op <- project p - case op of - MkOpImply (OpImply x y) -> return (x,y) - _ -> na ("Lenses.opImply:" <++> pretty p) - ) - - -opNot - :: ( Op x :< x - , Pretty x - , MonadFail m - ) - => Proxy (m :: * -> *) - -> ( x -> x - , x -> m x - ) -opNot _ = - ( inject . MkOpNot . OpNot - , \ p -> do - op <- project p - case op of - MkOpNot (OpNot x) -> return x - _ -> na ("Lenses.opNot:" <++> pretty p) - ) - - -opProduct - :: ( Op x :< x - , Pretty x - , MonadFail m - ) - => Proxy (m :: * -> *) - -> ( x -> x - , x -> m x - ) -opProduct _ = - ( inject . MkOpProduct . OpProduct - , \ p -> do - op <- project p - case op of - MkOpProduct (OpProduct x) -> return x - _ -> na ("Lenses.opProduct:" <++> pretty p) - ) - - -opSum - :: ( Op x :< x - , Pretty x - , MonadFail m - ) - => Proxy (m :: * -> *) - -> ( x -> x - , x -> m x - ) -opSum _ = - ( inject . MkOpSum . OpSum - , \ p -> do - op <- project p - case op of - MkOpSum (OpSum x) -> return x - _ -> na ("Lenses.opSum:" <++> pretty p) - ) - - -data ReducerType = RepetitionIsFine | RepetitionIsNotFine - deriving (Eq, Ord, Show) - -opReducer - :: ( Op x :< x - , Pretty x - , MonadFail m - ) - => Proxy (m :: * -> *) - -> ( (x -> x, x) -> x - , x -> m (ReducerType, x -> x, x) - ) -opReducer _ = - ( \ (mk, x) -> mk x - , \ p -> do - op <- project p - case op of - MkOpAnd (OpAnd x) -> return (RepetitionIsNotFine, inject . MkOpAnd . OpAnd , x) - MkOpOr (OpOr x) -> return (RepetitionIsNotFine, inject . MkOpOr . OpOr , x) - MkOpXor (OpXor x) -> return (RepetitionIsNotFine, inject . MkOpXor . OpXor , x) - MkOpSum (OpSum x) -> return (RepetitionIsFine , inject . MkOpSum . OpSum , x) - MkOpProduct (OpProduct x) -> return (RepetitionIsFine , inject . MkOpProduct . OpProduct , x) - MkOpMax (OpMax x) -> return (RepetitionIsNotFine, inject . MkOpMax . OpMax , x) - MkOpMin (OpMin x) -> return (RepetitionIsNotFine, inject . MkOpMin . OpMin , x) - _ -> na ("Lenses.opReducer:" <++> pretty p) - ) - - -opModifier - :: ( Op x :< x - , MonadFail m - ) - => Proxy (m :: * -> *) - -> ( (x -> x, x) -> x - , x -> m (x -> x, x) - ) -opModifier _ = - ( \ (mk, x) -> mk x - , \ p -> case project p of - Just (MkOpToSet (OpToSet _ x)) -> return (inject . MkOpToSet . OpToSet False , x) - Just (MkOpToMSet (OpToMSet x)) -> return (inject . MkOpToMSet . OpToMSet , x) - Just (MkOpToRelation (OpToRelation x)) -> return (inject . MkOpToRelation . OpToRelation , x) - Just (MkOpParts (OpParts x)) -> return (inject . MkOpParts . OpParts , x) - _ -> return (id , p) - ) - - -opModifierNoP - :: ( Op x :< x - , MonadFail m - ) - => Proxy (m :: * -> *) - -> ( (x -> x, x) -> x - , x -> m (x -> x, x) - ) -opModifierNoP _ = - ( \ (mk, x) -> mk x - , \ p -> case project p of - Just (MkOpToSet (OpToSet _ x)) -> return (inject . MkOpToSet . OpToSet False , x) - Just (MkOpToMSet (OpToMSet x)) -> return (inject . MkOpToMSet . OpToMSet , x) - Just (MkOpToRelation (OpToRelation x)) -> return (inject . MkOpToRelation . OpToRelation , x) - _ -> return (id , p) - ) - - -opAllDiff - :: ( Op x :< x - , Pretty x - , MonadFail m - ) - => Proxy (m :: * -> *) - -> ( x -> x - , x -> m x - ) -opAllDiff _ = - ( inject . MkOpAllDiff . OpAllDiff - , \ p -> do - op <- project p - case op of - MkOpAllDiff (OpAllDiff x) -> return x - _ -> na ("Lenses.opAllDiff:" <++> pretty p) - ) - - -opAllDiffExcept - :: ( Op x :< x - , Pretty x - , MonadFail m - ) - => Proxy (m :: * -> *) - -> ( x -> x -> x - , x -> m (x, x) - ) -opAllDiffExcept _ = - ( \ x y -> inject $ MkOpAllDiffExcept $ OpAllDiffExcept x y - , \ p -> do - op <- project p - case op of - MkOpAllDiffExcept (OpAllDiffExcept x y) -> return (x, y) - _ -> na ("Lenses.opAllDiffExcept:" <++> pretty p) - ) - - -constantInt - :: MonadFail m - => Proxy (m :: * -> *) - -> ( Integer -> Expression - , Expression -> m Integer - ) -constantInt _ = -<<<<<<< HEAD - ( Constant . ConstantInt Nothing -||||||| merged common ancestors - ( Constant . ConstantInt -======= - ( Constant . ConstantInt NoTag ->>>>>>> taggedints - , \ p -> case p of -<<<<<<< HEAD - (Constant (ConstantInt Nothing i)) -> return i -||||||| merged common ancestors - (Constant (ConstantInt i)) -> return i -======= - (Constant (ConstantInt NoTag i)) -> return i ->>>>>>> taggedints - _ -> na ("Lenses.constantInt:" <++> pretty p) - ) - - -matrixLiteral - :: MonadFail m - => Proxy (m :: * -> *) - -> ( Type -> Domain () Expression -> [Expression] -> Expression - , Expression -> m (Type, Domain () Expression, [Expression]) - ) -matrixLiteral _ = - ( \ ty index elems -> - if null elems - then Typed (AbstractLiteral (AbsLitMatrix index elems)) ty - else AbstractLiteral (AbsLitMatrix index elems) - , \ p -> do - ty <- typeOf p - (index, xs) <- followAliases extract p - return (ty, index, xs) - ) - where - extract (Constant (ConstantAbstract (AbsLitMatrix index xs))) = return (fmap Constant index, map Constant xs) - extract (AbstractLiteral (AbsLitMatrix index xs)) = return (index, xs) - extract (Typed x _) = extract x - extract (Constant (TypedConstant x _)) = extract (Constant x) - extract p = na ("Lenses.matrixLiteral:" <+> pretty p) - - -onMatrixLiteral - :: (Functor m, Applicative m, Monad m, NameGen m) - => Maybe Int -- how many levels to go down. all the way if Nothing. - -> (Expression -> m Expression) - -> Expression -> m Expression -onMatrixLiteral mlvl f = case mlvl of - Nothing -> followAliases go - Just lvl -> followAliases (goL lvl) - where - go (Constant (ConstantAbstract (AbsLitMatrix index xs))) = - AbstractLiteral . AbsLitMatrix (fmap Constant index) <$> mapM (go . Constant) xs - go (AbstractLiteral (AbsLitMatrix index xs)) = - AbstractLiteral . AbsLitMatrix index <$> mapM go xs - go (Typed x _) = go x - go (Constant (TypedConstant x _)) = go (Constant x) - go p = f p - - goL 0 p = f p - goL lvl (Constant (ConstantAbstract (AbsLitMatrix index xs))) = - AbstractLiteral . AbsLitMatrix (fmap Constant index) <$> mapM (goL (lvl-1) . Constant) xs - goL lvl (AbstractLiteral (AbsLitMatrix index xs)) = - AbstractLiteral . AbsLitMatrix index <$> mapM (goL (lvl-1)) xs - goL lvl (Typed x _) = goL lvl x - goL lvl (Constant (TypedConstant x _)) = goL lvl (Constant x) - goL lvl p = do - (iPat, i) <- quantifiedVar - body <- goL (lvl-1) i - return $ Comprehension body [Generator (GenInExpr iPat p)] - - -setLiteral - :: MonadFail m - => Proxy (m :: * -> *) - -> ( Type -> [Expression] -> Expression - , Expression -> m (Type, [Expression]) - ) -setLiteral _ = - ( \ ty elems -> - if null elems - then Typed (AbstractLiteral (AbsLitSet elems)) ty - else AbstractLiteral (AbsLitSet elems) - , \ p -> do - ty <- typeOf p - xs <- followAliases extract p - return (ty, xs) - ) - where - extract (Constant (ConstantAbstract (AbsLitSet xs))) = return (map Constant xs) - extract (AbstractLiteral (AbsLitSet xs)) = return xs - extract (Typed x _) = extract x - extract (Constant (TypedConstant x _)) = extract (Constant x) - extract p = na ("Lenses.setLiteral:" <+> pretty p) - - -msetLiteral - :: MonadFail m - => Proxy (m :: * -> *) - -> ( Type -> [Expression] -> Expression - , Expression -> m (Type, [Expression]) - ) -msetLiteral _ = - ( \ ty elems -> - if null elems - then Typed (AbstractLiteral (AbsLitMSet elems)) ty - else AbstractLiteral (AbsLitMSet elems) - , \ p -> do - ty <- typeOf p - xs <- followAliases extract p - return (ty, xs) - ) - where - extract (Constant (ConstantAbstract (AbsLitMSet xs))) = return (map Constant xs) - extract (AbstractLiteral (AbsLitMSet xs)) = return xs - extract (Typed x _) = extract x - extract (Constant (TypedConstant x _)) = extract (Constant x) - extract p = na ("Lenses.msetLiteral:" <+> pretty p) - - -functionLiteral - :: MonadFail m - => Proxy (m :: * -> *) - -> ( Type -> [(Expression,Expression)] -> Expression - , Expression -> m (Type, [(Expression,Expression)]) - ) -functionLiteral _ = - ( \ ty elems -> - if null elems - then Typed (AbstractLiteral (AbsLitFunction elems)) ty - else AbstractLiteral (AbsLitFunction elems) - , \ p -> do - ty <- typeOf p - xs <- followAliases extract p - return (ty, xs) - ) - where - extract (Constant (ConstantAbstract (AbsLitFunction xs))) = return [ (Constant a, Constant b) | (a,b) <- xs ] - extract (AbstractLiteral (AbsLitFunction xs)) = return xs - extract (Typed x _) = extract x - extract (Constant (TypedConstant x _)) = extract (Constant x) - extract p = na ("Lenses.functionLiteral:" <+> pretty p) - - -permutationLiteral - :: MonadFail m - => Proxy (m :: * -> *) - -> ( Type -> [[Expression]] -> Expression - , Expression -> m (Type, [[Expression]]) - ) -permutationLiteral _ = - ( \ ty elems -> - if null elems - then Typed (AbstractLiteral (AbsLitPermutation elems)) ty - else AbstractLiteral (AbsLitPermutation elems) - , \ p -> do - ty <- typeOf p - xs <- followAliases extract p - return (ty, xs) - ) - where - extract (Constant (ConstantAbstract (AbsLitPermutation xs))) = return [ [Constant z | z <- x] | x <- xs ] - extract (AbstractLiteral (AbsLitPermutation xs)) = return xs - extract (Typed x _) = extract x - extract (Constant (TypedConstant x _)) = extract (Constant x) - extract p = na ("Lenses.permutationLiteral:" <+> pretty p) - - - - -sequenceLiteral - :: MonadFail m - => Proxy (m :: * -> *) - -> ( Type -> [Expression] -> Expression - , Expression -> m (Type, [Expression]) - ) -sequenceLiteral _ = - ( \ ty elems -> - if null elems - then Typed (AbstractLiteral (AbsLitSequence elems)) ty - else AbstractLiteral (AbsLitSequence elems) - , \ p -> do - ty <- typeOf p - xs <- followAliases extract p - return (ty, xs) - ) - where - extract (Constant (ConstantAbstract (AbsLitSequence xs))) = return (map Constant xs) - extract (AbstractLiteral (AbsLitSequence xs)) = return xs - extract (Typed x _) = extract x - extract (Constant (TypedConstant x _)) = extract (Constant x) - extract p = na ("Lenses.sequenceLiteral:" <+> pretty p) - - -relationLiteral - :: MonadFail m - => Proxy (m :: * -> *) - -> ( Type -> [[Expression]] -> Expression - , Expression -> m (Type, [[Expression]]) - ) -relationLiteral _ = - ( \ ty elems -> - if null elems - then Typed (AbstractLiteral (AbsLitRelation elems)) ty - else AbstractLiteral (AbsLitRelation elems) - , \ p -> do - ty <- typeOf p - xs <- followAliases extract p - return (ty, xs) - ) - where - extract (Constant (ConstantAbstract (AbsLitRelation xs))) = return (map (map Constant) xs) - extract (AbstractLiteral (AbsLitRelation xs)) = return xs - extract (Typed x _) = extract x - extract (Constant (TypedConstant x _)) = extract (Constant x) - extract p = na ("Lenses.relationLiteral:" <+> pretty p) - - -partitionLiteral - :: MonadFail m - => Proxy (m :: * -> *) - -> ( Type -> [[Expression]] -> Expression - , Expression -> m (Type, [[Expression]]) - ) -partitionLiteral _ = - ( \ ty elems -> - if null elems - then Typed (AbstractLiteral (AbsLitPartition elems)) ty - else AbstractLiteral (AbsLitPartition elems) - , \ p -> do - ty <- typeOf p - xs <- followAliases extract p - return (ty, xs) - ) - where - extract (Constant (ConstantAbstract (AbsLitPartition xs))) = return (map (map Constant) xs) - extract (AbstractLiteral (AbsLitPartition xs)) = return xs - extract (Typed x _) = extract x - extract (Constant (TypedConstant x _)) = extract (Constant x) - extract p = na ("Lenses.partitionLiteral:" <+> pretty p) - - -opTwoBars - :: ( Op x :< x - , Pretty x - , MonadFail m - ) - => Proxy (m :: * -> *) - -> ( x -> x - , x -> m x - ) -opTwoBars _ = - ( inject . MkOpTwoBars . OpTwoBars - , \ p -> do - op <- project p - case op of - MkOpTwoBars (OpTwoBars x) -> return x - _ -> na ("Lenses.opTwoBars:" <++> pretty p) - ) - - -opPreImage - :: ( Op x :< x - , Pretty x - , MonadFail m - ) - => Proxy (m :: * -> *) - -> ( x -> x -> x - , x -> m (x,x) - ) -opPreImage _ = - ( \ x y -> inject (MkOpPreImage (OpPreImage x y)) - , \ p -> do - op <- project p - case op of - MkOpPreImage (OpPreImage x y) -> return (x,y) - _ -> na ("Lenses.opPreImage:" <++> pretty p) - ) - - -opActive - :: ( Op x :< x - , Pretty x - , MonadFail m - ) - => Proxy (m :: * -> *) - -> ( x -> Name -> x - , x -> m (x,Name) - ) -opActive _ = - ( \ x y -> inject (MkOpActive (OpActive x y)) - , \ p -> do - op <- project p - case op of - MkOpActive (OpActive x y) -> return (x,y) - _ -> na ("Lenses.opActive:" <++> pretty p) - ) - - -opFactorial - :: ( Op x :< x - , Pretty x - , MonadFail m - ) - => Proxy (m :: * -> *) - -> ( x -> x - , x -> m x - ) -opFactorial _ = - ( inject . MkOpFactorial . OpFactorial - , \ p -> do - op <- project p - case op of - MkOpFactorial (OpFactorial x) -> return x - _ -> na ("Lenses.opFactorial:" <++> pretty p) - ) - - -opLex - :: ( Op x :< x - , Pretty x - , MonadFail m - ) - => Proxy (m :: * -> *) - -> ( (x -> x -> x, (x,x)) -> x - , x -> m (x -> x -> x, (x,x)) - ) -opLex _ = - ( \ (mk, (x,y)) -> mk x y - , \ p -> case project p of - Just (MkOpLexLt (OpLexLt x y)) -> return (\ x' y' -> inject (MkOpLexLt (OpLexLt x' y')), (x,y) ) - Just (MkOpLexLeq (OpLexLeq x y)) -> return (\ x' y' -> inject (MkOpLexLeq (OpLexLeq x' y')), (x,y) ) - _ -> na ("Lenses.opLex:" <++> pretty p) - ) - - -fixRelationProj :: Data a => a -> a -fixRelationProj = transformBi f - where - f :: Expression -> Expression - f p = - case match opRelationProj p of - Just (func, [Just arg]) -> - case typeOf func of - Just TypeFunction{} -> make opImage func arg - Just TypeSequence{} -> make opImage func arg - _ -> p - _ -> p - - -maxOfDomain :: (MonadFail m, Pretty r) => Domain r Expression -> m Expression -maxOfDomain (DomainInt _ [] ) = fail "rule_DomainMinMax.maxOfDomain []" -maxOfDomain (DomainInt _ [r]) = maxOfRange r -maxOfDomain (DomainInt _ rs ) = do - xs <- mapM maxOfRange rs - return (make opMax (fromList xs)) -maxOfDomain d = fail ("rule_DomainMinMax.maxOfDomain" <+> pretty d) - -maxOfRange :: MonadFail m => Range Expression -> m Expression -maxOfRange (RangeSingle x) = return x -maxOfRange (RangeBounded _ x) = return x -maxOfRange r = fail ("rule_DomainMinMax.maxOfRange" <+> pretty r) - -minOfDomain :: (MonadFail m, Pretty r) => Domain r Expression -> m Expression -minOfDomain (DomainInt _ [] ) = fail "rule_DomainMinMax.minOfDomain []" -minOfDomain (DomainInt _ [r]) = minOfRange r -minOfDomain (DomainInt _ rs ) = do - xs <- mapM minOfRange rs - return (make opMin (fromList xs)) -minOfDomain d = fail ("rule_DomainMinMax.minOfDomain" <+> pretty d) - -minOfRange :: MonadFail m => Range Expression -> m Expression -minOfRange (RangeSingle x) = return x -minOfRange (RangeBounded x _) = return x -minOfRange r = fail ("rule_DomainMinMax.minOfRange" <+> pretty r) diff --git a/src/Conjure/Language/NameResolution.hs.orig b/src/Conjure/Language/NameResolution.hs.orig deleted file mode 100644 index 259d74f261..0000000000 --- a/src/Conjure/Language/NameResolution.hs.orig +++ /dev/null @@ -1,294 +0,0 @@ -{-# LANGUAGE TupleSections #-} - -module Conjure.Language.NameResolution - ( resolveNames - , resolveNamesMulti - , resolveNamesX - , resolveX, resolveD -- actually internal, use with care - ) where - -import Conjure.Prelude -import Conjure.Bug -import Conjure.UserError -import Conjure.Language.Definition -import Conjure.Language.Domain -import Conjure.Language.Type -import Conjure.Language.TypeOf -import Conjure.Language.Pretty - - -resolveNamesMulti :: (MonadLog m, MonadFail m, MonadUserError m, NameGen m) => [Model] -> m [Model] -resolveNamesMulti = flip evalStateT [] . go - where - go [] = return [] - go (m:ms) = (:) <$> resolveNames_ m <*> go ms - -resolveNames :: (MonadLog m, MonadFail m, MonadUserError m, NameGen m) => Model -> m Model -resolveNames = flip evalStateT [] . resolveNames_ - -resolveNames_ - :: ( MonadFail m - , MonadUserError m - , MonadState [(Name, ReferenceTo)] m - , NameGen m - ) - => Model -> m Model -resolveNames_ model = do - statements <- mapM resolveStatement (mStatements model) - mapM_ check (universeBi statements) - return model { mStatements = statements } - --- this is for when a name will shadow an already existing name that is outside of this expression --- we rename the new names to avoid name shadowing -shadowing - :: ( MonadFail m - , MonadState [(Name, ReferenceTo)] m - , NameGen m - ) - => Expression - -> m Expression -shadowing p@(Comprehension _ is) = do - -- list of names originating from this comprehension - let generators = concat - [ names - | Generator gen <- is - , let pat = generatorPat gen - , let names = [ n | n@Name{} <- universeBi pat ] - ] - ctxt <- gets id - -- a subset of names originating from this comprehension that will shadow already existing names - let shadows = [ g | g <- generators, g `elem` map fst ctxt ] - shadowsNew <- forM shadows $ \ s -> do n <- nextName "shadow" ; return (s,n) - let f n = fromMaybe n (lookup n shadowsNew) - return (transformBi f p) -shadowing p = return p - - -resolveNamesX :: (MonadFail m, MonadUserError m, NameGen m) => Expression -> m Expression -resolveNamesX x = do - x' <- evalStateT (resolveX x) [] - mapM_ check (universe x') - return x' - - -check :: MonadFail m => Expression -> m () -check (Reference nm Nothing) = fail ("Undefined:" <+> pretty nm) -check _ = return () - - -resolveStatement - :: ( MonadFail m - , MonadUserError m - , MonadState [(Name, ReferenceTo)] m - , NameGen m - ) - => Statement - -> m Statement - -resolveStatement st = - case st of - Declaration decl -> - case decl of - FindOrGiven forg nm dom -> do - dom' <- resolveD dom - modify ((nm, DeclNoRepr forg nm dom' NoRegion) :) - return (Declaration (FindOrGiven forg nm dom')) - Letting nm x -> do - x' <- resolveX x - modify ((nm, Alias x') :) - return (Declaration (Letting nm x')) - LettingDomainDefnUnnamed nm x -> do - x' <- resolveX x - modify ((nm, Alias (Domain (DomainUnnamed nm x'))) :) - return (Declaration (LettingDomainDefnUnnamed nm x')) -<<<<<<< HEAD - LettingDomainDefnEnum _ nms -> do - modify ( [ (nm, Alias (Constant (ConstantInt (Just nm) i))) -||||||| merged common ancestors - LettingDomainDefnEnum _ nms -> do - modify ( [ (nm, Alias (Constant (ConstantInt i))) -======= - LettingDomainDefnEnum (Name ename) nms -> do - modify ( [ (nm, Alias (Constant (ConstantInt (TagEnum ename) i))) ->>>>>>> taggedints - | (nm, i) <- zip nms [1..] - ] ++) - return st - LettingDomainDefnEnum{} -> bug "resolveStatement, Name" - GivenDomainDefnEnum{} -> return st -- ignoring - SearchOrder xs -> SearchOrder <$> mapM resolveSearchOrder xs - SearchHeuristic nm -> do - let allowed = ["static", "sdf", "conflict", "srf", "ldf", "wdeg", "domoverwdeg"] - if nm `elem` allowed - then return (SearchHeuristic nm) - else userErr1 $ vcat [ "Invalid heuristic:" <+> pretty nm - , "Allowed values are:" <+> prettyList id "," allowed - ] - Where xs -> Where <$> mapM resolveX xs - Objective obj x -> Objective obj <$> resolveX x - SuchThat xs -> SuchThat <$> mapM resolveX xs - - -resolveSearchOrder - :: ( MonadFail m - , MonadUserError m - , MonadState [(Name, ReferenceTo)] m - , NameGen m - ) - => SearchOrder - -> m SearchOrder -resolveSearchOrder (BranchingOn nm) = do - ctxt <- gets id - mval <- gets (lookup nm) - case mval of - Nothing -> userErr1 $ vcat $ ("Undefined reference:" <+> pretty nm) - : ("Bindings in context:" : prettyContext ctxt) - Just{} -> return (BranchingOn nm) -resolveSearchOrder (Cut x) = - let f Find = CutFind - f forg = forg - in Cut . transformBi f <$> resolveX x - - -resolveX - :: ( MonadFail m - , MonadUserError m - , MonadState [(Name, ReferenceTo)] m - , NameGen m - ) - => Expression - -> m Expression - -resolveX (Reference nm Nothing) = do - ctxt <- gets id - mval <- gets (lookup nm) - case mval of - Nothing -> userErr1 $ vcat $ ("Undefined reference:" <+> pretty nm) - : ("Bindings in context:" : prettyContext ctxt) - Just r -> return (Reference nm (Just r)) - -resolveX p@(Reference nm (Just refto)) = do -- this is for re-resolving - mval <- gets (lookup nm) - case mval of - Nothing -> return p -- hence, do not fail if not in the context - Just DeclNoRepr{} -- if the newly found guy doesn't have a repr - | DeclHasRepr{} <- refto -- but the old one did, do not update - -> return p - Just (DeclNoRepr forg_ nm_ dom_ _) -- if the newly found guy doesn't have a repr - | DeclNoRepr _ _ _ region <- refto -- and the old one didn't have one either - -- preserve the region information - -> return (Reference nm (Just (DeclNoRepr forg_ nm_ dom_ region))) - Just (Alias r) -> do - r' <- resolveX r - return (Reference nm (Just (Alias r'))) - Just r -> - return (Reference nm (Just r)) - -resolveX (AbstractLiteral lit) = AbstractLiteral <$> resolveAbsLit lit - -resolveX (Domain x) = Domain <$> resolveD x - -resolveX p@Comprehension{} = scope $ do - p' <- shadowing p - case p' of - Comprehension x is -> do - is' <- forM is $ \ i -> case i of - Generator gen -> do - (gen', refto) <- case gen of - GenDomainNoRepr pat dom -> do - dom' <- resolveD dom - let gen'' = GenDomainNoRepr pat dom' - return - ( gen'' - , case pat of - Single nm' -> DeclNoRepr Quantified nm' dom' NoRegion - _ -> InComprehension gen'' - ) - GenDomainHasRepr nm dom -> do - dom' <- resolveD dom - return - ( GenDomainHasRepr nm dom' - , DeclHasRepr Quantified nm dom' - ) - GenInExpr pat expr -> do - expr' <- resolveX expr - let gen'' = GenInExpr pat expr' - return ( gen'' , InComprehension gen'' ) - forM_ (universeBi (generatorPat gen)) $ \ nm -> - modify ((nm, refto) :) - return (Generator gen') - Condition y -> Condition <$> resolveX y - ComprehensionLetting nm expr -> do - expr' <- resolveX expr - modify ((nm, Alias expr') :) - return (ComprehensionLetting nm expr') - x' <- resolveX x - return (Comprehension x' is') - _ -> bug "NameResolution.resolveX.shadowing" - -resolveX (WithLocals body (AuxiliaryVars locals)) = scope $ do - locals' <- mapM resolveStatement locals - body' <- resolveX body - return (WithLocals body' (AuxiliaryVars locals')) - -resolveX (WithLocals body (DefinednessConstraints locals)) = scope $ do - locals' <- mapM resolveX locals - body' <- resolveX body - return (WithLocals body' (DefinednessConstraints locals')) - -resolveX x = descendM resolveX x - - -resolveD - :: ( MonadFail m - , MonadUserError m - , MonadState [(Name, ReferenceTo)] m - , NameGen m - , Data r - , Pretty r - , Default r - ) - => Domain r Expression - -> m (Domain r Expression) -resolveD (DomainReference _ (Just d)) = resolveD d -resolveD (DomainReference nm Nothing) = do - mval <- gets (lookup nm) - case mval of - Nothing -> userErr1 ("Undefined reference to a domain:" <+> pretty nm) - Just (Alias (Domain r)) -> resolveD (changeRepr def r) - Just x -> userErr1 ("Expected a domain, but got an expression:" <+> pretty x) -resolveD (DomainRecord ds) = fmap DomainRecord $ forM ds $ \ (n, d) -> do - d' <- resolveD d - t <- typeOf d' - modify ((n, RecordField n t) :) - return (n, d') -resolveD (DomainVariant ds) = fmap DomainVariant $ forM ds $ \ (n, d) -> do - d' <- resolveD d - t <- typeOf d' - modify ((n, VariantField n t) :) - return (n, d') -resolveD d = do - d' <- descendM resolveD d - mapM resolveX d' - - -resolveAbsLit - :: ( MonadFail m - , MonadUserError m - , MonadState [(Name, ReferenceTo)] m - , NameGen m - ) - => AbstractLiteral Expression - -> m (AbstractLiteral Expression) -resolveAbsLit (AbsLitVariant Nothing n x) = do - x' <- resolveX x - mval <- gets id - let - isTheVariant (Alias (Domain d@(DomainVariant nms))) | Just{} <- lookup n nms = Just d - isTheVariant _ = Nothing - case mapMaybe (isTheVariant . snd) mval of - (DomainVariant dom:_) -> return (AbsLitVariant (Just dom) n x') - _ -> return (AbsLitVariant Nothing n x') -resolveAbsLit lit = (descendBiM resolveX >=> descendBiM resolveD') lit - where - resolveD' d = resolveD (d :: Domain () Expression) diff --git a/src/Conjure/Language/Parser.hs.orig b/src/Conjure/Language/Parser.hs.orig deleted file mode 100644 index 1be6bf19bf..0000000000 --- a/src/Conjure/Language/Parser.hs.orig +++ /dev/null @@ -1,1146 +0,0 @@ -{-# LANGUAGE RecordWildCards #-} - -module Conjure.Language.Parser - ( runLexerAndParser - , parseIO - , parseModel - , parseTopLevels - , parseExpr - , parseDomain - , parseDomainWithRepr - , Parser, ParserState(..) - ) where - --- conjure -import Conjure.Prelude -import Conjure.Bug -import Conjure.Language.Definition -import Conjure.Language.Domain -import Conjure.Language.Domain.AddAttributes -import Conjure.Language.Type -import Conjure.Language.TypeOf -import Conjure.Language.Expression.Op -import Conjure.Language.Pretty -import Conjure.Language.Lexer ( Lexeme(..), LexemePos(..), lexemeFace, lexemeText, runLexer ) - --- megaparsec -import Text.Megaparsec.Prim ( (), label, token, try, eof, ParsecT, getPosition, setPosition ) -import Text.Megaparsec.Error ( ParseError(..), Message(..), errorPos ) -import Text.Megaparsec.Pos ( SourcePos(..), sourceLine, sourceColumn ) -import Text.Megaparsec.Combinator ( between, sepBy, sepBy1, sepEndBy, sepEndBy1 ) -import Text.Megaparsec.ShowToken ( showToken ) -import Text.Megaparsec.Expr ( makeExprParser, Operator(..) ) -import qualified Text.Megaparsec.Prim as P ( runParser ) - --- text -import qualified Data.Text as T - --- containers -import qualified Data.Set as S ( null, fromList, toList ) - - -parseModel :: Parser Model -parseModel = inCompleteFile $ do - let - pLanguage :: Parser LanguageVersion - pLanguage = do - lexeme L_language - pos1 <- getPosition - l <- identifierText - -- ESSENCE' is accepted, just for convenience - unless (l `elem` ["Essence", "ESSENCE", "ESSENCE'"]) $ do - setPosition pos1 - fail $ "language name has to be Essence, but given:" <+> pretty l - pos2 <- getPosition - is <- sepBy1 integer dot - unless (is >= [1]) $ do - setPosition pos2 - fail $ "language version expected to be at least 1.0, but given:" <+> - pretty (intercalate "." (map show is)) - return (LanguageVersion (Name l) (map fromInteger is)) - l <- optional pLanguage - xs <- many parseTopLevels - return Model - { mLanguage = fromMaybe def l - , mStatements = concat xs - , mInfo = def - } - - -parseIO :: MonadFail m => Parser a -> String -> m a -parseIO p s = - case runLexerAndParser (inCompleteFile p) "" (T.pack s) of - Left err -> fail err - Right x -> return x - - -translateQnName :: Text -> Text -translateQnName qnName = case qnName of - "forAll" -> "and" - "exists" -> "or" - _ -> qnName - - - - - --------------------------------------------------------------------------------- --- Actual parsers -------------------------------------------------------------- --------------------------------------------------------------------------------- - -parseTopLevels :: Parser [Statement] -parseTopLevels = do - let one = msum - [ do - lexeme L_find - decls <- flip sepEndBy1 comma $ do - is <- commaSeparated parseNameOrMeta - j <- colon >> parseDomain - return [ Declaration (FindOrGiven Find i j) - | i <- is ] - return $ concat decls - "find statement" - , do - lexeme L_given - decls <- commaSeparated $ do - is <- commaSeparated parseName - msum - [ do - colon - j <- parseDomain - return [ Declaration (FindOrGiven Given i j) - | i <- is ] - , do - lexeme L_new - msum - [ do - lexeme L_type - lexeme L_enum - modify (\ st -> st { enumDomains = is ++ enumDomains st } ) - return [ Declaration (GivenDomainDefnEnum i) - | i <- is ] - ] - ] - return $ concat decls - "given statement" - , do - lexeme L_letting - decls <- commaSeparated $ do - is <- commaSeparated parseName - lexeme L_be - msum - [ do - lexeme L_new - lexeme L_type - msum - [ do - lexeme L_of - lexeme $ LIdentifier "size" - j <- parseExpr - return [ Declaration (LettingDomainDefnUnnamed i j) - | i <- is - ] - , do - lexeme L_enum - ys <- braces (commaSeparated parseName) <|> return [] - modify (\ st -> st { enumDomains = is ++ enumDomains st } ) - return [ Declaration (LettingDomainDefnEnum i ys) - | i <- is - ] - ] - , do - lexeme L_domain - j <- parseDomain - return [ Declaration (Letting i (Domain j)) - | i <- is - ] - , do - j <- parseExpr - return [ Declaration (Letting i j) - | i <- is - ] - ] - return $ concat decls - "letting statement" - , do - lexeme L_where - xs <- commaSeparated parseExpr - return [Where xs] - "where statement" - , do - lexeme L_such - lexeme L_that - xs <- commaSeparated parseExpr - return [SuchThat xs] - "such that statement" - , do - lexeme L_minimising - x <- parseExpr - return [ Objective Minimising x ] - "objective" - , do - lexeme L_maximising - x <- parseExpr - return [ Objective Maximising x ] - "objective" - , do - lexeme L_branching - lexeme L_on - xs <- brackets $ commaSeparated parseSearchOrder - return [ SearchOrder xs ] - "branching on" - , do - lexeme L_heuristic - nm <- parseName - return [ SearchHeuristic nm ] - "heuristic" - ] "statement" - concat <$> some one - -parseSearchOrder :: Parser SearchOrder -parseSearchOrder = msum [try pBranchingOn, pCut] - where - pBranchingOn = BranchingOn <$> parseName - pCut = Cut <$> parseExpr - -parseRange :: Parser a -> Parser (Range a) -parseRange p = msum [try pRange, pSingle] "range" - where - pRange = do - fr <- optional p - dotdot - to <- optional p - return $ case (fr,to) of - (Nothing, Nothing) -> RangeOpen - (Just x , Nothing) -> RangeLowerBounded x - (Nothing, Just y ) -> RangeUpperBounded y - (Just x , Just y ) -> RangeBounded x y - pSingle = do - x <- p - return (RangeSingle x) - -parseDomain :: Parser (Domain () Expression) -parseDomain = (forgetRepr <$> parseDomainWithRepr) "domain" - -parseDomainWithRepr :: Parser (Domain HasRepresentation Expression) -parseDomainWithRepr = pDomainAtom - -- TODO: uncomment the following to parse (union, intersect and minus) for domains - -- let - -- mergeOp op before after = DomainOp (Name (lexemeText op)) [before,after] - -- - -- in - -- makeExprParser (pDomainAtom "domain") - -- [ [ InfixL $ do lexeme L_Minus - -- return $ mergeOp L_Minus - -- , InfixL $ do lexeme L_union - -- return $ mergeOp L_union - -- ] - -- , [ InfixL $ do lexeme L_intersect - -- return $ mergeOp L_intersect - -- ] - -- ] - - where - - pDomainAtom = msum - [ pBool, try pIntFromExpr, pInt, try pEnum, try pReference - , pMatrix, try pTupleWithout, pTupleWith - , pRecord, pVariant - , pSet - , pMSet - , try pFunction', pFunction - , pSequence - , pRelation - , pPartition - , pPermutation - , DomainMetaVar <$> parseMetaVariable, parens parseDomainWithRepr - ] - - parseRepr = msum [ braces parseReprInner - , return NoRepresentation - ] - - parseReprInner = do - pos <- getPosition - nm <- identifierText - inners <- fromMaybe [] <$> optional (brackets (commaSeparated parseReprInner)) - case textToRepresentation nm inners of - Nothing -> do - setPosition pos - fail ("Not a valid representation:" <+> pretty nm) - Just r -> return r - - pBool = do - lexeme L_bool - -- parse and discard, compatibility with SR - _ <- optional $ parens $ commaSeparated0 $ parseRange parseExpr - return DomainBool - - pIntFromExpr = do - lexeme L_int - x <- parens parseExpr - case typeOf x of -<<<<<<< HEAD - Just (TypeInt Nothing)-> return $ DomainInt Nothing [RangeSingle x] - _ -> return $ DomainIntE Nothing x -||||||| merged common ancestors - Just TypeInt -> return $ DomainInt [RangeSingle x] - _ -> return $ DomainIntE x -======= - Just (TypeInt NoTag) -> return $ DomainInt NoTag [RangeSingle x] - _ -> return $ DomainIntE x ->>>>>>> taggedints - - pInt = do - lexeme L_int - mxs <- optional $ parens $ commaSeparated0 $ parseRange parseExpr - let xs = fromMaybe [] mxs -<<<<<<< HEAD - return $ DomainInt Nothing xs -||||||| merged common ancestors - return $ DomainInt xs -======= - return $ DomainInt NoTag xs ->>>>>>> taggedints - - pReference = do - r <- identifierText - return $ DomainReference (Name r) Nothing - - pEnum = do - r <- identifierText - xs <- optional $ parens $ commaSeparated0 $ parseRange parseExpr - st <- get - guard (Name r `elem` enumDomains st) - return $ DomainEnum (Name r) xs Nothing - - pMatrix = do - lexeme L_matrix - lexeme L_indexed - lexeme L_by - xs <- brackets (commaSeparated parseDomain) - lexeme L_of - y <- parseDomainWithRepr - return $ foldr DomainMatrix y xs - - pTupleWith = do - lexeme L_tuple - xs <- parens $ commaSeparated0 parseDomainWithRepr - return $ DomainTuple xs - - pTupleWithout = do - xs <- parens $ countSepAtLeast 2 parseDomainWithRepr comma - return $ DomainTuple xs - - pRecord = do - lexeme L_record - let one = do n <- parseName - lexeme L_Colon - d <- parseDomainWithRepr - return (n,d) - xs <- braces $ commaSeparated0 one - return $ DomainRecord xs - - pVariant = do - lexeme L_variant - let one = do n <- parseName - lexeme L_Colon - d <- parseDomainWithRepr - return (n,d) - xs <- braces $ commaSeparated0 one - return $ DomainVariant xs - - pSet = do - lexeme L_set - r <- parseRepr - x <- parseSetAttr - y <- lexeme L_of >> parseDomainWithRepr - return $ DomainSet r x y - - pMSet = do - lexeme L_mset - r <- parseRepr - x <- parseMSetAttr - y <- lexeme L_of >> parseDomainWithRepr - return $ DomainMSet r x y - - pFunction' = do - lexeme L_function - r <- parseRepr - (y,z) <- arrowedPair parseDomainWithRepr - return $ DomainFunction r def y z - - pFunction = do - lexeme L_function - r <- parseRepr - x <- parseFunctionAttr - (y,z) <- arrowedPair parseDomainWithRepr - return $ DomainFunction r x y z - - pSequence = do - lexeme L_sequence - r <- parseRepr - x <- parseSequenceAttr - y <- lexeme L_of >> parseDomainWithRepr - return $ DomainSequence r x y - - pRelation = do - lexeme L_relation - r <- parseRepr - pos <- getPosition - x <- parseRelationAttr - lexeme L_of - ys <- parens (parseDomainWithRepr `sepBy` lexeme L_Times) - let RelationAttr _ (BinaryRelationAttrs binAttrs) = x - when (length ys /= 2 && not (S.null binAttrs)) $ do - setPosition pos - fail $ "Only binary relations can have these attributes:" <+> - prettyList id "," (S.toList binAttrs) - return $ DomainRelation r x ys - - pPartition = do - lexeme L_partition - r <- parseRepr - x <- parsePartitionAttr - lexeme L_from - y <- parseDomainWithRepr - return $ DomainPartition r x y - pPermutation = do - lexeme L_permutation - r <- parseRepr - x <- parsePermutationAttr - lexeme L_of -- $ trace (textToString $ representationToShortText r) L_of - y <- parseDomainWithRepr - return $ DomainPermutation r x y - -parseAttributes :: Parser (DomainAttributes Expression) -parseAttributes = do - xs <- parens (commaSeparated0 parseAttribute) <|> return [] - return $ DomainAttributes xs - where - parseAttribute = msum [parseDontCare, try parseNameValue, parseDAName] - parseNameValue = DANameValue <$> (Name <$> identifierText) <*> parseExpr - parseDAName = DAName <$> (Name <$> identifierText) - parseDontCare = do dotdot ; return DADotDot - -parseSetAttr :: Parser (SetAttr Expression) -parseSetAttr = do - pos <- getPosition - DomainAttributes attrs <- parseAttributes - checkExtraAttributes pos "set" attrs - ["size", "minSize", "maxSize"] - SetAttr <$> case filterSizey attrs of - [] -> return SizeAttr_None - [DANameValue "size" a] -> return (SizeAttr_Size a) - [DANameValue "minSize" a] -> return (SizeAttr_MinSize a) - [DANameValue "maxSize" a] -> return (SizeAttr_MaxSize a) - [DANameValue "maxSize" b, DANameValue "minSize" a] -> return (SizeAttr_MinMaxSize a b) - as -> do - setPosition pos - fail ("incompatible attributes:" <+> stringToDoc (show as)) - -parseMSetAttr :: Parser (MSetAttr Expression) -parseMSetAttr = do - pos <- getPosition - DomainAttributes attrs <- parseAttributes - checkExtraAttributes pos "mset" attrs - [ "size", "minSize", "maxSize" - , "minOccur", "maxOccur" - ] - size <- case filterSizey attrs of - [] -> return SizeAttr_None - [DANameValue "size" a] -> return (SizeAttr_Size a) - [DANameValue "minSize" a] -> return (SizeAttr_MinSize a) - [DANameValue "maxSize" a] -> return (SizeAttr_MaxSize a) - [DANameValue "maxSize" b, DANameValue "minSize" a] -> return (SizeAttr_MinMaxSize a b) - as -> do - setPosition pos - fail ("incompatible attributes:" <+> stringToDoc (show as)) - occur <- case filterAttrName ["minOccur", "maxOccur"] attrs of - [] -> return OccurAttr_None - [DANameValue "minOccur" a] -> return (OccurAttr_MinOccur a) - [DANameValue "maxOccur" a] -> return (OccurAttr_MaxOccur a) - [DANameValue "maxOccur" b, DANameValue "minOccur" a] -> return (OccurAttr_MinMaxOccur a b) - as -> do - setPosition pos - fail ("incompatible attributes:" <+> stringToDoc (show as)) - return (MSetAttr size occur) - -parseFunctionAttr :: Parser (FunctionAttr Expression) -parseFunctionAttr = do - pos <- getPosition - DomainAttributes attrs <- parseAttributes - checkExtraAttributes pos "function" attrs - [ "size", "minSize", "maxSize" - , "injective", "surjective", "bijective" - , "total" - ] - size <- case filterSizey attrs of - [DANameValue "size" a] -> return (SizeAttr_Size a) - [DANameValue "minSize" a] -> return (SizeAttr_MinSize a) - [DANameValue "maxSize" a] -> return (SizeAttr_MaxSize a) - [DANameValue "maxSize" b, DANameValue "minSize" a] -> return (SizeAttr_MinMaxSize a b) - [] -> return SizeAttr_None - as -> do - setPosition pos - fail ("incompatible attributes:" <+> stringToDoc (show as)) - let partiality = if DAName "total" `elem` attrs - then PartialityAttr_Total - else PartialityAttr_Partial - jectivity <- case filterJectivity attrs of - [] -> return JectivityAttr_None - [DAName "bijective" ] -> return JectivityAttr_Bijective - [DAName "injective" ] -> return JectivityAttr_Injective - [DAName "surjective"] -> return JectivityAttr_Surjective - [DAName "injective", DAName "surjective"] -> return JectivityAttr_Bijective - as -> do - setPosition pos - fail ("incompatible attributes:" <+> stringToDoc (show as)) - return (FunctionAttr size partiality jectivity) - -parseSequenceAttr :: Parser (SequenceAttr Expression) -parseSequenceAttr = do - pos <- getPosition - DomainAttributes attrs <- parseAttributes - checkExtraAttributes pos "sequence" attrs - [ "size", "minSize", "maxSize" - , "injective", "surjective", "bijective" - ] - size <- case filterSizey attrs of - [DANameValue "size" a] -> return (SizeAttr_Size a) - [DANameValue "minSize" a] -> return (SizeAttr_MinSize a) - [DANameValue "maxSize" a] -> return (SizeAttr_MaxSize a) - [DANameValue "maxSize" b, DANameValue "minSize" a] -> return (SizeAttr_MinMaxSize a b) - [] -> return SizeAttr_None - as -> do - setPosition pos - fail ("incompatible attributes:" <+> stringToDoc (show as)) - jectivity <- case filterJectivity attrs of - [] -> return JectivityAttr_None - [DAName "bijective" ] -> return JectivityAttr_Bijective - [DAName "injective" ] -> return JectivityAttr_Injective - [DAName "surjective"] -> return JectivityAttr_Surjective - [DAName "injective", DAName "surjective"] -> return JectivityAttr_Bijective - as -> do - setPosition pos - fail ("incompatible attributes:" <+> stringToDoc (show as)) - return (SequenceAttr size jectivity) - -parseRelationAttr :: Parser (RelationAttr Expression) -parseRelationAttr = do - pos <- getPosition - DomainAttributes attrs <- parseAttributes - checkExtraAttributes pos "relation" attrs - [ "size", "minSize", "maxSize" - , "reflexive", "irreflexive", "coreflexive" - , "symmetric", "antiSymmetric", "aSymmetric" - , "transitive", "total", "connex", "Euclidean" - , "serial", "equivalence", "partialOrder" - ] - size <- case filterSizey attrs of - [] -> return SizeAttr_None - [DANameValue "size" a] -> return (SizeAttr_Size a) - [DANameValue "minSize" a] -> return (SizeAttr_MinSize a) - [DANameValue "maxSize" a] -> return (SizeAttr_MaxSize a) - [DANameValue "maxSize" b, DANameValue "minSize" a] -> return (SizeAttr_MinMaxSize a b) - as -> do - setPosition pos - fail ("incompatible attributes:" <+> stringToDoc (show as)) - let readBinRel' (DAName (Name a)) = readBinRel (fromString (textToString a)) - readBinRel' a = do - setPosition pos - fail $ "Not a binary relation attribute:" <+> pretty a - binRels <- mapM readBinRel' (filterBinRel attrs) - return (RelationAttr size (BinaryRelationAttrs (S.fromList binRels))) - -parsePartitionAttr :: Parser (PartitionAttr Expression) -parsePartitionAttr = do - pos <- getPosition - DomainAttributes attrs <- parseAttributes - checkExtraAttributes pos "partition" attrs - [ "size", "minSize", "maxSize" - , "regular" - , "numParts", "minNumParts", "maxNumParts" - , "partSize", "minPartSize", "maxPartSize" - ] - unless (null $ filterAttrName ["complete"] attrs) $ do - setPosition pos - fail $ vcat [ "Partitions do not support the 'complete' attribute." - , "They are complete by default." - ] - unless (null $ filterSizey attrs) $ do - setPosition pos - fail $ vcat [ "Partitions do not support these attributes:" <+> prettyList id "," (filterSizey attrs) - , "This is because partitions are complete by default." - ] - partsNum <- case filterAttrName ["numParts", "minNumParts", "maxNumParts"] attrs of - [] -> return SizeAttr_None - [DANameValue "numParts" a] -> return (SizeAttr_Size a) - [DANameValue "minNumParts" a] -> return (SizeAttr_MinSize a) - [DANameValue "maxNumParts" a] -> return (SizeAttr_MaxSize a) - [DANameValue "maxNumParts" b, DANameValue "minNumParts" a] -> return (SizeAttr_MinMaxSize a b) - as -> do - setPosition pos - fail ("incompatible attributes:" <+> stringToDoc (show as)) - partsSize <- case filterAttrName ["partSize", "minPartSize", "maxPartSize"] attrs of - [] -> return SizeAttr_None - [DANameValue "partSize" a] -> return (SizeAttr_Size a) - [DANameValue "minPartSize" a] -> return (SizeAttr_MinSize a) - [DANameValue "maxPartSize" a] -> return (SizeAttr_MaxSize a) - [DANameValue "maxPartSize" b, DANameValue "minPartSize" a] -> return (SizeAttr_MinMaxSize a b) - as -> do - setPosition pos - fail ("incompatible attributes:" <+> stringToDoc (show as)) - let isRegular = DAName "regular" `elem` attrs - return PartitionAttr {..} - - -parsePermutationAttr :: Parser (PermutationAttr Expression) -parsePermutationAttr = do - pos <- getPosition - DomainAttributes attrs <- parseAttributes - checkExtraAttributes pos "permutation" attrs - [ "size", "minSize", "maxSize" - ] - size <- case filterSizey attrs of - [DANameValue "size" a] -> return (SizeAttr_Size a) - [DANameValue "minSize" a] -> return (SizeAttr_MinSize a) - [DANameValue "maxSize" a] -> return (SizeAttr_MaxSize a) - [DANameValue "maxSize" b, DANameValue "minSize" a] -> return (SizeAttr_MinMaxSize a b) - [] -> return SizeAttr_None - as -> do - setPosition pos - fail ("incompatible attributes:" <+> stringToDoc (show as)) - return (PermutationAttr size) - - - -checkExtraAttributes :: SourcePos -> Doc -> [DomainAttribute a] -> [Name] -> Parser () -checkExtraAttributes pos ty attrs supported = do - let extras = mapMaybe f attrs - unless (null extras) $ do - setPosition pos - fail $ vcat [ "Unsupported attributes for" <+> ty <> ":" <+> prettyList id "," extras - , "Only these are supported:" <+> prettyList id "," supported - ] - where - f (DANameValue nm _) | nm `notElem` supported = Just nm - f (DAName nm ) | nm `notElem` supported = Just nm - f _ = Nothing - -filterAttrName :: Ord a => [Name] -> [DomainAttribute a] -> [DomainAttribute a] -filterAttrName keep = sort . filter f - where - f (DANameValue nm _) | nm `elem` keep = True - f (DAName nm ) | nm `elem` keep = True - f _ = False - -filterSizey :: Ord a => [DomainAttribute a] -> [DomainAttribute a] -filterSizey = filterAttrName ["size", "minSize", "maxSize"] - -filterJectivity :: Ord a => [DomainAttribute a] -> [DomainAttribute a] -filterJectivity = filterAttrName ["injective", "surjective", "bijective"] - -filterBinRel :: Ord a => [DomainAttribute a] -> [DomainAttribute a] -filterBinRel = filterAttrName - [ "reflexive" - , "irreflexive" - , "coreflexive" - , "symmetric" - , "antiSymmetric" - , "aSymmetric" - , "transitive" - , "total" - , "connex" - , "Euclidean" - , "serial" - , "equivalence" - , "partialOrder" - ] - -parseMetaVariable :: Parser String -parseMetaVariable = do - let isMeta LMetaVar{} = True - isMeta _ = False - LMetaVar iden <- satisfyT isMeta - return (T.unpack iden) - -metaVarInE :: String -> Expression -metaVarInE = ExpressionMetaVar - -parseExpr :: Parser Expression -parseExpr = - let - mergeOp op = mkBinOp (lexemeText op) - - operatorsGrouped = operators - |> sortBy (\ (_,a) (_,b) -> compare a b ) - |> groupBy (\ (_,a) (_,b) -> a == b ) - |> reverse - - parseUnaryNegate = do - lexeme L_Minus - return $ \ x -> mkOp "negate" [x] - - parseUnaryNot = do - lexeme L_ExclamationMark - return $ \ x -> mkOp "not" [x] - - in - makeExprParser (parseAtomicExpr "expression") - [ [ case descr of - Binary op FLeft -> InfixL $ do lexeme op - return $ mergeOp op - Binary op FNone -> InfixN $ do lexeme op - return $ mergeOp op - Binary op FRight -> InfixR $ do lexeme op - return $ mergeOp op - UnaryPrefix L_Minus -> Prefix $ foldr1 (.) <$> some parseUnaryNegate - UnaryPrefix L_ExclamationMark -> Prefix $ foldr1 (.) <$> some parseUnaryNot - UnaryPrefix l -> bug ("Unknown UnaryPrefix" <+> pretty (show l)) - | (descr, _) <- operatorsInGroup - ] - | operatorsInGroup <- operatorsGrouped - ] - -parseAtomicExpr :: Parser Expression -parseAtomicExpr = do - let - prefixes = do - fs <- some $ msum parsePrefixes - return $ foldr1 (.) fs - postfixes = do - fs <- some $ msum parsePostfixes - return $ foldr1 (.) (reverse fs) - withPrefix x = try x <|> do f <- prefixes; i <- x; return $ f i - withPostfix x = do i <- x; mf <- optional postfixes; return $ case mf of Nothing -> i - Just f -> f i - withPrefix (withPostfix parseAtomicExprNoPrePost) "expression" - - -parseAtomicExprNoPrePost :: Parser Expression -parseAtomicExprNoPrePost = msum $ map try $ concat - [ [parseQuantifiedExpr] - , parseOthers - , [metaVarInE <$> parseMetaVariable] - , [parseAAC] - , [parseReference] - , [parseLiteral] - , [parseDomainAsExpr] - , [parseWithLocals] - , [parseComprehension] - , [parens parseExpr] - ] - -parseComprehension :: Parser Expression -parseComprehension = brackets $ do - x <- parseExpr - lexeme L_Bar - gens <- commaSeparated (letting <|> try generator <|> condition) - return (Comprehension x (concat gens)) - where - generator :: Parser [GeneratorOrCondition] - generator = do - pats <- commaSeparated parseAbstractPattern - msum - [ do - lexeme L_Colon - domain <- parseDomain - return [Generator (GenDomainNoRepr pat domain) | pat <- pats] - , do - lexeme L_LeftArrow - expr <- parseExpr - return [Generator (GenInExpr pat expr) | pat <- pats] - ] - condition :: Parser [GeneratorOrCondition] - condition = return . Condition <$> parseExpr - letting :: Parser [GeneratorOrCondition] - letting = do - lexeme L_letting - nm <- parseNameOrMeta - lexeme L_be - x <- parseExpr - return [ComprehensionLetting nm x] - -parseDomainAsExpr :: Parser Expression -parseDomainAsExpr = Domain <$> betweenTicks parseDomain - -parsePrefixes :: [Parser (Expression -> Expression)] -parsePrefixes = [parseUnaryMinus, parseUnaryNot] - where - parseUnaryMinus = do - lexeme L_Minus - return $ \ x -> mkOp "negate" [x] - parseUnaryNot = do - lexeme L_ExclamationMark - return $ \ x -> mkOp "not" [x] - -parsePostfixes :: [Parser (Expression -> Expression)] -parsePostfixes = [parseIndexed,parseFactorial,parseFuncApply] - where - parseIndexed :: Parser (Expression -> Expression) - parseIndexed = do - let - pIndexer = try pRList <|> (do i <- parseExpr ; return $ \ m -> Op (MkOpIndexing (OpIndexing m i))) - pRList = do - i <- optional parseExpr - dotdot - j <- optional parseExpr - return $ \ m -> Op (MkOpSlicing (OpSlicing m i j)) - is <- brackets $ commaSeparated pIndexer - return $ \ x -> foldl (\ m f -> f m ) x is - parseFactorial :: Parser (Expression -> Expression) - parseFactorial = do - lexeme L_ExclamationMark - return $ \ x -> mkOp "factorial" [x] - parseFuncApply :: Parser (Expression -> Expression) - parseFuncApply = parens $ do - xs <- commaSeparated parseExpr - let underscore = Reference "_" Nothing - let ys = [ if underscore == x then Nothing else Just x | x <- xs ] - return $ \ x -> Op $ MkOpRelationProj $ OpRelationProj x ys - -parseAAC :: Parser Expression -parseAAC = do - let - isAttr (LIdentifier txt) | Just _ <- Name txt `lookup` allSupportedAttributes = True - isAttr _ = False - LIdentifier attr <- satisfyT isAttr - let n = fromMaybe (bug "parseAAC") (lookup (Name attr) allSupportedAttributes) - args <- parens $ countSep (n+1) parseExpr comma - case (n, args) of - (0, [e ]) -> return $ Op $ MkOpAttributeAsConstraint $ OpAttributeAsConstraint e - (fromString (textToString attr)) Nothing - (1, [e,v]) -> return $ Op $ MkOpAttributeAsConstraint $ OpAttributeAsConstraint e - (fromString (textToString attr)) (Just v) - _ -> fail "parseAAC" - -parseOthers :: [Parser Expression] -parseOthers = [ parseFunctional l - | l <- functionals - ] ++ [parseTyped, parseTwoBars] - where - - parseTwoBars :: Parser Expression - parseTwoBars = do - x <- between (lexeme L_Bar) (lexeme L_Bar) parseExpr - return (mkOp "twoBars" [x]) - - parseTyped :: Parser Expression - parseTyped = parens $ do - x <- parseExpr - lexeme L_Colon - d <- betweenTicks parseDomain - ty <- typeOfDomain d - return (Typed x ty) - - parseFunctional :: Lexeme -> Parser Expression - parseFunctional l = do - lexeme l - xs <- parens $ commaSeparated parseExpr - return $ case (l,xs) of - (L_image, [y,z]) -> Op $ MkOpImage $ OpImage y z - _ -> mkOp (fromString $ show $ lexemeFace l) xs - -parseWithLocals :: Parser Expression -parseWithLocals = braces $ do - i <- parseExpr - lexeme L_At - js <- parseTopLevels - let decls = - [ Declaration (FindOrGiven LocalFind nm dom) - | Declaration (FindOrGiven Find nm dom) <- js ] - let cons = concat - [ xs - | SuchThat xs <- js - ] - let locals = if null decls - then DefinednessConstraints cons - else AuxiliaryVars (decls ++ [SuchThat cons]) - return (WithLocals i locals) - -parseNameOrMeta :: Parser Name -parseNameOrMeta = parseName <|> NameMetaVar <$> parseMetaVariable - -parseName :: Parser Name -parseName = Name <$> identifierText - -parseReference :: Parser Expression -parseReference = Reference <$> parseName <*> pure Nothing - -parseQuantifiedExpr :: Parser Expression -parseQuantifiedExpr = do - Name qnName <- parseName - qnPats <- commaSeparated parseAbstractPattern - qnOver <- msum [ Left <$> (colon *> parseDomain) - , Right <$> do - lexeme L_in - over <- parseExpr - return (\ pat -> GenInExpr pat over ) - , Right <$> do - lexeme L_subsetEq - over <- parseExpr - return (\ pat -> GenInExpr pat (Op $ MkOpPowerSet $ OpPowerSet over) ) - ] - qnGuard <- optional (comma *> parseExpr) - qnBody <- dot *> parseExpr "body of a quantified expression" - - let qnMap pat = case qnOver of - Left dom -> GenDomainNoRepr pat dom - Right op -> op pat - - return $ mkOp (translateQnName qnName) - $ return - $ Comprehension qnBody - $ [ Generator (qnMap pat) | pat <- qnPats ] ++ - [ Condition g | Just g <- [qnGuard] ] - - -parseAbstractPattern :: Parser AbstractPattern -parseAbstractPattern = label "pattern" $ msum - [ AbstractPatternMetaVar <$> parseMetaVariable - , Single <$> parseName - , do - void $ optional $ lexeme L_tuple - xs <- parens $ commaSeparated parseAbstractPattern - return (AbsPatTuple xs) - , do - xs <- brackets $ commaSeparated parseAbstractPattern - return (AbsPatMatrix xs) - , do - xs <- braces $ commaSeparated parseAbstractPattern - return (AbsPatSet xs) - ] - -parseLiteral :: Parser Expression -parseLiteral = label "value" $ msum - [ Constant <$> pBool - , Constant <$> pInt - , mkAbstractLiteral <$> pMatrix - , mkAbstractLiteral <$> pTupleWith - , mkAbstractLiteral <$> pTupleWithout - , mkAbstractLiteral <$> pRecord - , AbstractLiteral <$> pVariant - , mkAbstractLiteral <$> pSet - , mkAbstractLiteral <$> pMSet - , mkAbstractLiteral <$> pFunction - , mkAbstractLiteral <$> pSequence - , mkAbstractLiteral <$> pRelation - , mkAbstractLiteral <$> pPartition - , mkAbstractLiteral <$> pPermutation - ] - where - - -- convert x to a constant if possible - -- might save us from evaluating it again and again later - mkAbstractLiteral x = - case e2c (AbstractLiteral x) of - Nothing -> AbstractLiteral x - Just c -> Constant c - - pBool = do - x <- False <$ lexeme L_false - <|> - True <$ lexeme L_true - return (ConstantBool x) - -<<<<<<< HEAD - pInt = ConstantInt Nothing . fromInteger <$> integer -||||||| merged common ancestors - pInt = ConstantInt . fromInteger <$> integer -======= - pInt = ConstantInt NoTag . fromInteger <$> integer ->>>>>>> taggedints - - pMatrix = do - lexeme L_OpenBracket - xs <- commaSeparated0 parseExpr - msum - [ do - let r = mkDomainIntB 1 (fromInt (genericLength xs)) - lexeme L_CloseBracket - return (AbsLitMatrix r xs) - , do - lexeme L_SemiColon - r <- parseDomain - lexeme L_CloseBracket - return (AbsLitMatrix r xs) - ] - - pTupleWith = do - lexeme L_tuple - xs <- parens $ commaSeparated0 parseExpr - return (AbsLitTuple xs) - - pTupleWithout = do - xs <- parens $ countSepAtLeast 2 parseExpr comma - return (AbsLitTuple xs) - - pRecord = do - lexeme L_record - let one = do n <- parseName - lexeme L_Eq - x <- parseExpr - return (n,x) - xs <- braces $ commaSeparated0 one - return $ AbsLitRecord xs - - pVariant = do - lexeme L_variant - let one = do n <- parseName - lexeme L_Eq - x <- parseExpr - return (n,x) - (n,x) <- braces one - return $ AbsLitVariant Nothing n x - - pSet = do - xs <- braces (commaSeparated0 parseExpr) - return (AbsLitSet xs) - - pMSet = do - lexeme L_mset - xs <- parens (commaSeparated0 parseExpr) - return (AbsLitMSet xs) - - pFunction = do - lexeme L_function - xs <- parens (commaSeparated0 inner) - return (AbsLitFunction xs) - where - inner = arrowedPair parseExpr - - pSequence = do - lexeme L_sequence - xs <- parens (commaSeparated0 parseExpr) - return (AbsLitSequence xs) - - pRelation = do - lexeme L_relation - xs <- parens (commaSeparated0 (pTupleWith <|> pTupleWithout)) - return (AbsLitRelation [is | AbsLitTuple is <- xs]) - - pPartition = do - lexeme L_partition - xs <- parens (commaSeparated0 inner) - return (AbsLitPartition xs) - where - inner = braces (commaSeparated0 parseExpr) - pPermutation = do - lexeme L_permutation - xs <- parens (commaSeparated0 inner) - return (AbsLitPermutation xs) - where - inner = parens (commaSeparated0 parseExpr) - - - -data ParserState = ParserState { enumDomains :: [Name] } -type Parser a = StateT ParserState (ParsecT [LexemePos] Identity) a - -runLexerAndParser :: MonadFail m => Parser a -> String -> T.Text -> m a -runLexerAndParser p file inp = do - ls <- runLexer inp - case runParser p file ls of - Left (msg, line, col) -> - let theLine = T.lines inp |> drop (line-1) |> take 1 - in fail $ vcat - [ msg - , vcat (map pretty theLine) - , pretty $ replicate (col-1) ' ' ++ "^" - ] - Right x -> return x - -runParser :: Parser a -> String -> [LexemePos] -> Either (Doc, Int, Int) a -runParser p file ls = either modifyErr Right (P.runParser (evalStateT p (ParserState [])) file ls) - where - modifyErr :: ParseError -> Either (Doc, Int, Int) a - modifyErr e = Left $ - let pos = errorPos e - in ( if file `isPrefixOf` show e - then pretty (show e) - else pretty file <> ":" <> pretty (show e) - , sourceLine pos - , sourceColumn pos - ) - -identifierText :: Parser T.Text -identifierText = do - LIdentifier i <- satisfyT isIdentifier - return i - where isIdentifier LIdentifier {} = True - isIdentifier _ = False - -satisfyT :: (Lexeme -> Bool) -> Parser Lexeme -satisfyT predicate = token nextPos testTok - where - testTok :: LexemePos -> Either [Message] Lexeme - testTok (LexemePos tok _ _) = if predicate tok then Right tok else Left [Unexpected (showToken tok)] - nextPos :: Int -> SourcePos -> LexemePos -> SourcePos - nextPos _ _ (LexemePos _ _ pos) = pos - -integer :: Parser Integer -integer = do - LIntLiteral i <- satisfyT isInt - return i - where isInt LIntLiteral {} = True - isInt _ = False - --- parse a comma separated list of things. can be 0 things. -commaSeparated0 :: Parser a -> Parser [a] -commaSeparated0 p = sepEndBy p comma - --- parse a comma separated list of things. has to be at least 1 thing. -commaSeparated :: Parser a -> Parser [a] -commaSeparated p = sepEndBy1 p comma - -comma :: Parser () -comma = lexeme L_Comma "comma" - -dot :: Parser () -dot = lexeme L_Dot "dot" - -dotdot :: Parser () -dotdot = (dot >> dot) ".." - -colon :: Parser () -colon = lexeme L_Colon "colon" - - --- parses a specified number of elements separated by the given separator -countSep :: Int -> Parser a -> Parser sep -> Parser [a] -countSep 1 p _ = (:[]) <$> p -countSep i p separator | i > 1 = (:) <$> (p <* separator) <*> countSep (i-1) p separator -countSep _ _ _ = return [] - --- parses at least a given number of elements separated by the given separator -countSepAtLeast :: Int -> Parser a -> Parser sep -> Parser [a] -countSepAtLeast i p separator = (++) <$> countSep i p separator <*> many (separator *> p) - -betweenTicks :: Parser a -> Parser a -betweenTicks = between (lexeme L_BackTick) (lexeme L_BackTick) - -parens :: Parser a -> Parser a -parens = between (lexeme L_OpenParen) (lexeme L_CloseParen) - -braces :: Parser a -> Parser a -braces = between (lexeme L_OpenCurly) (lexeme L_CloseCurly) - -brackets :: Parser a -> Parser a -brackets = between (lexeme L_OpenBracket) (lexeme L_CloseBracket) - -lexeme :: Lexeme -> Parser () -lexeme l = void (satisfyT (l==)) show (lexemeFace l) - -arrowedPair :: Parser a -> Parser (a,a) -arrowedPair p = do - i <- p - lexeme L_LongArrow - j <- p - return (i,j) - -inCompleteFile :: Parser a -> Parser a -inCompleteFile parser = do - result <- parser - eof - return result diff --git a/src/Conjure/Language/ParserC.hs.orig b/src/Conjure/Language/ParserC.hs.orig deleted file mode 100644 index 01ce1a77d6..0000000000 --- a/src/Conjure/Language/ParserC.hs.orig +++ /dev/null @@ -1,755 +0,0 @@ -{-# LANGUAGE RecordWildCards #-} - -module Conjure.Language.ParserC ( parseModel ) where - --- conjure -import Conjure.Prelude -import Conjure.Language.Definition -import Conjure.Language.Domain -import Conjure.Language.Type -import Conjure.Language.TypeOf -import Conjure.Language.Pretty -import Conjure.Language.Lexer ( Lexeme(..), LexemePos(..), lexemeFace ) -import Conjure.Language.Parser ( Parser, ParserState(..) ) - --- megaparsec -import Text.Megaparsec.Prim ( (), label, token, try, eof, getPosition, setPosition ) -import Text.Megaparsec.Error ( Message(..) ) -import Text.Megaparsec.Pos ( SourcePos(..) ) -import Text.Megaparsec.Combinator ( between, sepBy, sepBy1, sepEndBy, sepEndBy1 ) -import Text.Megaparsec.ShowToken ( showToken ) - --- text -import qualified Data.Text as T - --- containers -import qualified Data.Set as S ( null, fromList, toList ) - - -parseModel :: Parser Model -parseModel = inCompleteFile $ do - let - pLanguage :: Parser LanguageVersion - pLanguage = do - lexeme L_language - pos1 <- getPosition - l <- identifierText - -- ESSENCE' is accepted, just for convenience - unless (l `elem` ["Essence", "ESSENCE", "ESSENCE'"]) $ do - setPosition pos1 - fail $ "language name has to be Essence, but given:" <+> pretty l - pos2 <- getPosition - is <- sepBy1 integer dot - unless (is >= [1]) $ do - setPosition pos2 - fail $ "language version expected to be at least 1.0, but given:" <+> - pretty (intercalate "." (map show is)) - return (LanguageVersion (Name l) (map fromInteger is)) - l <- optional pLanguage - xs <- many parseTopLevels - return Model - { mLanguage = fromMaybe def l - , mStatements = concat xs - , mInfo = def - } - - --------------------------------------------------------------------------------- --- Actual parsers -------------------------------------------------------------- --------------------------------------------------------------------------------- - -parseTopLevels :: Parser [Statement] -parseTopLevels = do - let one = do - lexeme L_letting - i <- parseName - lexeme L_be - msum - [ do - lexeme L_new - lexeme L_type - msum - [ do - lexeme L_of - lexeme $ LIdentifier "size" - j <- parseExpr - return $ Declaration (LettingDomainDefnUnnamed i j) - , do - lexeme L_enum - ys <- braces (commaSeparated parseName) <|> return [] - modify (\ st -> st { enumDomains = [i] ++ enumDomains st } ) - return $ Declaration (LettingDomainDefnEnum i ys) - ] - , do - lexeme L_domain - j <- parseDomain - return $ Declaration (Letting i (Domain j)) - , do - j <- parseExpr - return $ Declaration (Letting i j) - ] - "letting statement" - some one - -parseRange :: Parser a -> Parser (Range a) -parseRange p = msum [try pRange, pSingle] "range" - where - pRange = do - fr <- optional p - dotdot - to <- optional p - return $ case (fr,to) of - (Nothing, Nothing) -> RangeOpen - (Just x , Nothing) -> RangeLowerBounded x - (Nothing, Just y ) -> RangeUpperBounded y - (Just x , Just y ) -> RangeBounded x y - pSingle = do - x <- p - return (RangeSingle x) - -parseDomain :: Parser (Domain () Expression) -parseDomain = (forgetRepr <$> parseDomainWithRepr) "domain" - -parseDomainWithRepr :: Parser (Domain HasRepresentation Expression) -parseDomainWithRepr = pDomainAtom - - where - - pDomainAtom = msum - [ pBool, try pIntFromExpr, pInt, try pEnum, try pReference - , pMatrix, try pTupleWithout, pTupleWith - , pRecord, pVariant - , pSet - , pMSet - , try pFunction', pFunction - , pSequence - , pRelation - , pPartition - , DomainMetaVar <$> parseMetaVariable, parens parseDomainWithRepr - ] - - parseRepr = msum [ braces parseReprInner - , return NoRepresentation - ] - - parseReprInner = do - pos <- getPosition - nm <- identifierText - inners <- fromMaybe [] <$> optional (brackets (commaSeparated parseReprInner)) - case textToRepresentation nm inners of - Nothing -> do - setPosition pos - fail ("Not a valid representation:" <+> pretty nm) - Just r -> return r - - pBool = do - lexeme L_bool - -- parse and discard, compatibility with SR - _ <- optional $ parens $ commaSeparated0 $ parseRange parseExpr - return DomainBool - - pIntFromExpr = do - lexeme L_int - x <- parens parseExpr - case typeOf x of -<<<<<<< HEAD - Just (TypeInt Nothing) -> return $ DomainInt Nothing [RangeSingle x] - _ -> return $ DomainIntE Nothing x -||||||| merged common ancestors - Just TypeInt -> return $ DomainInt [RangeSingle x] - _ -> return $ DomainIntE x -======= - Just (TypeInt NoTag) -> return $ DomainInt NoTag [RangeSingle x] - _ -> return $ DomainIntE x ->>>>>>> taggedints - - pInt = do - lexeme L_int - mxs <- optional $ parens $ commaSeparated0 $ parseRange parseExpr - let xs = fromMaybe [] mxs -<<<<<<< HEAD - return $ DomainInt Nothing xs -||||||| merged common ancestors - return $ DomainInt xs -======= - return $ DomainInt NoTag xs ->>>>>>> taggedints - - pReference = do - r <- identifierText - return $ DomainReference (Name r) Nothing - - pEnum = do - r <- identifierText - xs <- optional $ parens $ commaSeparated0 $ parseRange parseExpr - st <- get - guard (Name r `elem` enumDomains st) - return $ DomainEnum (Name r) xs Nothing - - pMatrix = do - lexeme L_matrix - lexeme L_indexed - lexeme L_by - xs <- brackets (commaSeparated parseDomain) - lexeme L_of - y <- parseDomainWithRepr - return $ foldr DomainMatrix y xs - - pTupleWith = do - lexeme L_tuple - xs <- parens $ commaSeparated0 parseDomainWithRepr - return $ DomainTuple xs - - pTupleWithout = do - xs <- parens $ countSepAtLeast 2 parseDomainWithRepr comma - return $ DomainTuple xs - - pRecord = do - lexeme L_record - let one = do n <- parseName - lexeme L_Colon - d <- parseDomainWithRepr - return (n,d) - xs <- braces $ commaSeparated0 one - return $ DomainRecord xs - - pVariant = do - lexeme L_variant - let one = do n <- parseName - lexeme L_Colon - d <- parseDomainWithRepr - return (n,d) - xs <- braces $ commaSeparated0 one - return $ DomainVariant xs - - pSet = do - lexeme L_set - r <- parseRepr - x <- parseSetAttr - y <- lexeme L_of >> parseDomainWithRepr - return $ DomainSet r x y - - pMSet = do - lexeme L_mset - r <- parseRepr - x <- parseMSetAttr - y <- lexeme L_of >> parseDomainWithRepr - return $ DomainMSet r x y - - pFunction' = do - lexeme L_function - r <- parseRepr - (y,z) <- arrowedPair parseDomainWithRepr - return $ DomainFunction r def y z - - pFunction = do - lexeme L_function - r <- parseRepr - x <- parseFunctionAttr - (y,z) <- arrowedPair parseDomainWithRepr - return $ DomainFunction r x y z - - pSequence = do - lexeme L_sequence - r <- parseRepr - x <- parseSequenceAttr - y <- lexeme L_of >> parseDomainWithRepr - return $ DomainSequence r x y - - pRelation = do - lexeme L_relation - r <- parseRepr - pos <- getPosition - x <- parseRelationAttr - lexeme L_of - ys <- parens (parseDomainWithRepr `sepBy` lexeme L_Times) - let RelationAttr _ (BinaryRelationAttrs binAttrs) = x - when (length ys /= 2 && not (S.null binAttrs)) $ do - setPosition pos - fail $ "Only binary relations can have these attributes:" <+> - prettyList id "," (S.toList binAttrs) - return $ DomainRelation r x ys - - pPartition = do - lexeme L_partition - r <- parseRepr - x <- parsePartitionAttr - lexeme L_from - y <- parseDomainWithRepr - return $ DomainPartition r x y - -parseAttributes :: Parser (DomainAttributes Expression) -parseAttributes = do - xs <- parens (commaSeparated0 parseAttribute) <|> return [] - return $ DomainAttributes xs - where - parseAttribute = msum [parseDontCare, try parseNameValue, parseDAName] - parseNameValue = DANameValue <$> (Name <$> identifierText) <*> parseExpr - parseDAName = DAName <$> (Name <$> identifierText) - parseDontCare = do dotdot ; return DADotDot - -parseSetAttr :: Parser (SetAttr Expression) -parseSetAttr = do - pos <- getPosition - DomainAttributes attrs <- parseAttributes - checkExtraAttributes pos "set" attrs - ["size", "minSize", "maxSize"] - SetAttr <$> case filterSizey attrs of - [] -> return SizeAttr_None - [DANameValue "size" a] -> return (SizeAttr_Size a) - [DANameValue "minSize" a] -> return (SizeAttr_MinSize a) - [DANameValue "maxSize" a] -> return (SizeAttr_MaxSize a) - [DANameValue "maxSize" b, DANameValue "minSize" a] -> return (SizeAttr_MinMaxSize a b) - as -> do - setPosition pos - fail ("incompatible attributes:" <+> stringToDoc (show as)) - -parseMSetAttr :: Parser (MSetAttr Expression) -parseMSetAttr = do - pos <- getPosition - DomainAttributes attrs <- parseAttributes - checkExtraAttributes pos "mset" attrs - [ "size", "minSize", "maxSize" - , "minOccur", "maxOccur" - ] - size <- case filterSizey attrs of - [] -> return SizeAttr_None - [DANameValue "size" a] -> return (SizeAttr_Size a) - [DANameValue "minSize" a] -> return (SizeAttr_MinSize a) - [DANameValue "maxSize" a] -> return (SizeAttr_MaxSize a) - [DANameValue "maxSize" b, DANameValue "minSize" a] -> return (SizeAttr_MinMaxSize a b) - as -> do - setPosition pos - fail ("incompatible attributes:" <+> stringToDoc (show as)) - occur <- case filterAttrName ["minOccur", "maxOccur"] attrs of - [] -> return OccurAttr_None - [DANameValue "minOccur" a] -> return (OccurAttr_MinOccur a) - [DANameValue "maxOccur" a] -> return (OccurAttr_MaxOccur a) - [DANameValue "maxOccur" b, DANameValue "minOccur" a] -> return (OccurAttr_MinMaxOccur a b) - as -> do - setPosition pos - fail ("incompatible attributes:" <+> stringToDoc (show as)) - return (MSetAttr size occur) - -parseFunctionAttr :: Parser (FunctionAttr Expression) -parseFunctionAttr = do - pos <- getPosition - DomainAttributes attrs <- parseAttributes - checkExtraAttributes pos "function" attrs - [ "size", "minSize", "maxSize" - , "injective", "surjective", "bijective" - , "total" - ] - size <- case filterSizey attrs of - [DANameValue "size" a] -> return (SizeAttr_Size a) - [DANameValue "minSize" a] -> return (SizeAttr_MinSize a) - [DANameValue "maxSize" a] -> return (SizeAttr_MaxSize a) - [DANameValue "maxSize" b, DANameValue "minSize" a] -> return (SizeAttr_MinMaxSize a b) - [] -> return SizeAttr_None - as -> do - setPosition pos - fail ("incompatible attributes:" <+> stringToDoc (show as)) - let partiality = if DAName "total" `elem` attrs - then PartialityAttr_Total - else PartialityAttr_Partial - jectivity <- case filterJectivity attrs of - [] -> return JectivityAttr_None - [DAName "bijective" ] -> return JectivityAttr_Bijective - [DAName "injective" ] -> return JectivityAttr_Injective - [DAName "surjective"] -> return JectivityAttr_Surjective - [DAName "injective", DAName "surjective"] -> return JectivityAttr_Bijective - as -> do - setPosition pos - fail ("incompatible attributes:" <+> stringToDoc (show as)) - return (FunctionAttr size partiality jectivity) - -parseSequenceAttr :: Parser (SequenceAttr Expression) -parseSequenceAttr = do - pos <- getPosition - DomainAttributes attrs <- parseAttributes - checkExtraAttributes pos "sequence" attrs - [ "size", "minSize", "maxSize" - , "injective", "surjective", "bijective" - ] - size <- case filterSizey attrs of - [DANameValue "size" a] -> return (SizeAttr_Size a) - [DANameValue "minSize" a] -> return (SizeAttr_MinSize a) - [DANameValue "maxSize" a] -> return (SizeAttr_MaxSize a) - [DANameValue "maxSize" b, DANameValue "minSize" a] -> return (SizeAttr_MinMaxSize a b) - [] -> return SizeAttr_None - as -> do - setPosition pos - fail ("incompatible attributes:" <+> stringToDoc (show as)) - jectivity <- case filterJectivity attrs of - [] -> return JectivityAttr_None - [DAName "bijective" ] -> return JectivityAttr_Bijective - [DAName "injective" ] -> return JectivityAttr_Injective - [DAName "surjective"] -> return JectivityAttr_Surjective - [DAName "injective", DAName "surjective"] -> return JectivityAttr_Bijective - as -> do - setPosition pos - fail ("incompatible attributes:" <+> stringToDoc (show as)) - return (SequenceAttr size jectivity) - -parseRelationAttr :: Parser (RelationAttr Expression) -parseRelationAttr = do - pos <- getPosition - DomainAttributes attrs <- parseAttributes - checkExtraAttributes pos "relation" attrs - [ "size", "minSize", "maxSize" - , "reflexive", "irreflexive", "coreflexive" - , "symmetric", "antiSymmetric", "aSymmetric" - , "transitive", "total", "connex", "Euclidean" - , "serial", "equivalence", "partialOrder" - ] - size <- case filterSizey attrs of - [] -> return SizeAttr_None - [DANameValue "size" a] -> return (SizeAttr_Size a) - [DANameValue "minSize" a] -> return (SizeAttr_MinSize a) - [DANameValue "maxSize" a] -> return (SizeAttr_MaxSize a) - [DANameValue "maxSize" b, DANameValue "minSize" a] -> return (SizeAttr_MinMaxSize a b) - as -> do - setPosition pos - fail ("incompatible attributes:" <+> stringToDoc (show as)) - let readBinRel' (DAName (Name a)) = readBinRel (fromString (textToString a)) - readBinRel' a = do - setPosition pos - fail $ "Not a binary relation attribute:" <+> pretty a - binRels <- mapM readBinRel' (filterBinRel attrs) - return (RelationAttr size (BinaryRelationAttrs (S.fromList binRels))) - -parsePartitionAttr :: Parser (PartitionAttr Expression) -parsePartitionAttr = do - pos <- getPosition - DomainAttributes attrs <- parseAttributes - checkExtraAttributes pos "partition" attrs - [ "size", "minSize", "maxSize" - , "regular" - , "numParts", "minNumParts", "maxNumParts" - , "partSize", "minPartSize", "maxPartSize" - ] - unless (null $ filterAttrName ["complete"] attrs) $ do - setPosition pos - fail $ vcat [ "Partitions do not support the 'complete' attribute." - , "They are complete by default." - ] - unless (null $ filterSizey attrs) $ do - setPosition pos - fail $ vcat [ "Partitions do not support these attributes:" <+> prettyList id "," (filterSizey attrs) - , "This is because partitions are complete by default." - ] - partsNum <- case filterAttrName ["numParts", "minNumParts", "maxNumParts"] attrs of - [] -> return SizeAttr_None - [DANameValue "numParts" a] -> return (SizeAttr_Size a) - [DANameValue "minNumParts" a] -> return (SizeAttr_MinSize a) - [DANameValue "maxNumParts" a] -> return (SizeAttr_MaxSize a) - [DANameValue "maxNumParts" b, DANameValue "minNumParts" a] -> return (SizeAttr_MinMaxSize a b) - as -> do - setPosition pos - fail ("incompatible attributes:" <+> stringToDoc (show as)) - partsSize <- case filterAttrName ["partSize", "minPartSize", "maxPartSize"] attrs of - [] -> return SizeAttr_None - [DANameValue "partSize" a] -> return (SizeAttr_Size a) - [DANameValue "minPartSize" a] -> return (SizeAttr_MinSize a) - [DANameValue "maxPartSize" a] -> return (SizeAttr_MaxSize a) - [DANameValue "maxPartSize" b, DANameValue "minPartSize" a] -> return (SizeAttr_MinMaxSize a b) - as -> do - setPosition pos - fail ("incompatible attributes:" <+> stringToDoc (show as)) - let isRegular = DAName "regular" `elem` attrs - return PartitionAttr {..} - - -checkExtraAttributes :: SourcePos -> Doc -> [DomainAttribute a] -> [Name] -> Parser () -checkExtraAttributes pos ty attrs supported = do - let extras = mapMaybe f attrs - unless (null extras) $ do - setPosition pos - fail $ vcat [ "Unsupported attributes for" <+> ty <> ":" <+> prettyList id "," extras - , "Only these are supported:" <+> prettyList id "," supported - ] - where - f (DANameValue nm _) | nm `notElem` supported = Just nm - f (DAName nm ) | nm `notElem` supported = Just nm - f _ = Nothing - -filterAttrName :: Ord a => [Name] -> [DomainAttribute a] -> [DomainAttribute a] -filterAttrName keep = sort . filter f - where - f (DANameValue nm _) | nm `elem` keep = True - f (DAName nm ) | nm `elem` keep = True - f _ = False - -filterSizey :: Ord a => [DomainAttribute a] -> [DomainAttribute a] -filterSizey = filterAttrName ["size", "minSize", "maxSize"] - -filterJectivity :: Ord a => [DomainAttribute a] -> [DomainAttribute a] -filterJectivity = filterAttrName ["injective", "surjective", "bijective"] - -filterBinRel :: Ord a => [DomainAttribute a] -> [DomainAttribute a] -filterBinRel = filterAttrName - [ "reflexive" - , "irreflexive" - , "coreflexive" - , "symmetric" - , "antiSymmetric" - , "aSymmetric" - , "transitive" - , "total" - , "connex" - , "Euclidean" - , "serial" - , "equivalence" - , "partialOrder" - ] - -parseMetaVariable :: Parser String -parseMetaVariable = do - let isMeta LMetaVar{} = True - isMeta _ = False - LMetaVar iden <- satisfyT isMeta - return (T.unpack iden) - -parseExpr :: Parser Expression --- parseExpr | trace "parseExpr" True = parseAtomicExpr "expression" -parseExpr = parseAtomicExpr "expression" - -parseAtomicExpr :: Parser Expression --- parseAtomicExpr | trace "parseAtomicExpr" True = parseAtomicExprNoPrePost "expression" -parseAtomicExpr = parseAtomicExprNoPrePost "expression" - -parseAtomicExprNoPrePost :: Parser Expression --- parseAtomicExprNoPrePost | trace "parseAtomicExprNoPrePost" True = msum [try parseLiteral, parseTyped] -parseAtomicExprNoPrePost = msum [try parseLiteral, parseReference, parseTyped] - -parseTyped :: Parser Expression --- parseTyped | trace "parseTyped" True = parens $ do -parseTyped = parens $ do - x <- parseExpr - lexeme L_Colon - d <- betweenTicks parseDomain - ty <- typeOfDomain d - return (Typed x ty) - -parseName :: Parser Name -parseName = Name <$> identifierText - -parseReference :: Parser Expression -parseReference = Reference <$> parseName <*> pure Nothing - -parseLiteral :: Parser Expression -parseLiteral = label "value" (do p <- pCore ; p) - - where - - -- convert x to a constant if possible - -- might save us from evaluating it again and again later - mkAbstractLiteral x = - case e2c (AbstractLiteral x) of - Nothing -> AbstractLiteral x - Just c -> Constant c - - pCore :: Parser (Parser Expression) - pCore = satisfyL $ \case - L_false -> Just $ return $ Constant $ ConstantBool False - L_true -> Just $ return $ Constant $ ConstantBool True -<<<<<<< HEAD - LIntLiteral i -> Just $ return $ Constant $ ConstantInt Nothing (fromInteger i) -||||||| merged common ancestors - LIntLiteral i -> Just $ return $ Constant $ ConstantInt (fromInteger i) -======= - LIntLiteral i -> Just $ return $ Constant $ ConstantInt NoTag (fromInteger i) ->>>>>>> taggedints - L_OpenBracket -> Just pMatrix - L_tuple -> Just pTupleWith - L_OpenParen -> Just pTupleWithout - L_record -> Just pRecord - L_variant -> Just pVariant - L_OpenCurly -> Just pSet - L_mset -> Just pMSet - L_function -> Just pFunction - L_sequence -> Just pSequence - L_relation -> Just pRelation - L_partition -> Just pPartition - L_Minus -> Just $ do - p <- pCore - res <- p - return (negate res) - _ -> Nothing - - pMatrix = mkAbstractLiteral <$> do - -- lexeme L_OpenBracket - xs <- commaSeparated0 parseExpr - msum - [ do - let r = mkDomainIntB 1 (fromInt (genericLength xs)) - lexeme L_CloseBracket - return (AbsLitMatrix r xs) - , do - lexeme L_SemiColon - r <- parseDomain - lexeme L_CloseBracket - return (AbsLitMatrix r xs) - ] - - pTupleWith = mkAbstractLiteral <$> do - -- lexeme L_tuple - xs <- parens $ commaSeparated0 parseExpr - return (AbsLitTuple xs) - - pTupleWithout = mkAbstractLiteral <$> do - -- xs <- parens $ countSepAtLeast 2 parseExpr comma - xs <- countSepAtLeast 2 parseExpr comma - lexeme L_CloseParen - return (AbsLitTuple xs) - - pRecord = mkAbstractLiteral <$> do - -- lexeme L_record - let one = do n <- parseName - lexeme L_Eq - x <- parseExpr - return (n,x) - xs <- braces $ commaSeparated0 one - return $ AbsLitRecord xs - - pVariant = mkAbstractLiteral <$> do - -- lexeme L_variant - let one = do n <- parseName - lexeme L_Eq - x <- parseExpr - return (n,x) - (n,x) <- braces one - return $ AbsLitVariant Nothing n x - - pSet = mkAbstractLiteral <$> do - -- xs <- braces (commaSeparated0 parseExpr) - xs <- commaSeparated0 parseExpr - lexeme L_CloseCurly - return (AbsLitSet xs) - - pMSet = mkAbstractLiteral <$> do - -- lexeme L_mset - xs <- parens (commaSeparated0 parseExpr) - return (AbsLitMSet xs) - - pFunction = mkAbstractLiteral <$> do - -- lexeme L_function - xs <- parens (commaSeparated0 inner) - return (AbsLitFunction xs) - where - inner = arrowedPair parseExpr - - pSequence = mkAbstractLiteral <$> do - -- lexeme L_sequence - xs <- parens (commaSeparated0 parseExpr) - return (AbsLitSequence xs) - - pRelation = mkAbstractLiteral <$> do - -- lexeme L_relation - xs <- parens (commaSeparated0 (parseLiteral)) - return (AbsLitRelation [is | AbstractLiteral (AbsLitTuple is) <- xs]) - - pPartition = mkAbstractLiteral <$> do - -- lexeme L_partition - xs <- parens (commaSeparated0 inner) - return (AbsLitPartition xs) - where - inner = braces (commaSeparated0 parseExpr) - - -identifierText :: Parser T.Text -identifierText = do - LIdentifier i <- satisfyT isIdentifier - return i - where isIdentifier LIdentifier {} = True - isIdentifier _ = False - -satisfyT :: (Lexeme -> Bool) -> Parser Lexeme -satisfyT predicate = token nextPos testTok - where - testTok :: LexemePos -> Either [Message] Lexeme - testTok (LexemePos tok _ _) = - -- trace ("satisfyT: " ++ show pos ++ "\t" ++ show tok) $ - if predicate tok - then Right tok - else Left [Unexpected (showToken tok)] - - nextPos :: Int -> SourcePos -> LexemePos -> SourcePos - nextPos _ _ (LexemePos _ _ pos) = pos - -satisfyL :: forall a . (Lexeme -> Maybe a) -> Parser a -satisfyL predicate = token nextPos testTok - where - testTok :: LexemePos -> Either [Message] a - testTok (LexemePos tok _ _) = - -- trace ("satisfyL: " ++ show pos ++ "\t" ++ show tok) $ - case predicate tok of - Nothing -> Left [Unexpected (showToken tok)] - Just res -> Right res - - nextPos :: Int -> SourcePos -> LexemePos -> SourcePos - nextPos _ _ (LexemePos _ _ pos) = pos - -integer :: Parser Integer -integer = do - LIntLiteral i <- satisfyT isInt - return i - where isInt LIntLiteral {} = True - isInt _ = False - --- parse a comma separated list of things. can be 0 things. -commaSeparated0 :: Parser a -> Parser [a] -commaSeparated0 p = sepEndBy p comma - --- parse a comma separated list of things. has to be at least 1 thing. -commaSeparated :: Parser a -> Parser [a] -commaSeparated p = sepEndBy1 p comma - -comma :: Parser () -comma = lexeme L_Comma "comma" - -dot :: Parser () -dot = lexeme L_Dot "dot" - -dotdot :: Parser () -dotdot = (dot >> dot) ".." - - --- parses a specified number of elements separated by the given separator -countSep :: Int -> Parser a -> Parser sep -> Parser [a] -countSep 1 p _ = (:[]) <$> p -countSep i p separator | i > 1 = (:) <$> (p <* separator) <*> countSep (i-1) p separator -countSep _ _ _ = return [] - --- parses at least a given number of elements separated by the given separator -countSepAtLeast :: Int -> Parser a -> Parser sep -> Parser [a] -countSepAtLeast i p separator = (++) <$> countSep i p separator <*> many (separator *> p) - -betweenTicks :: Parser a -> Parser a -betweenTicks = between (lexeme L_BackTick) (lexeme L_BackTick) - -parens :: Parser a -> Parser a -parens = between (lexeme L_OpenParen) (lexeme L_CloseParen) - -braces :: Parser a -> Parser a -braces = between (lexeme L_OpenCurly) (lexeme L_CloseCurly) - -brackets :: Parser a -> Parser a -brackets = between (lexeme L_OpenBracket) (lexeme L_CloseBracket) - -lexeme :: Lexeme -> Parser () --- lexeme l = trace ("lexeme: " ++ show l) (void (satisfyT (l==)) show (lexemeFace l)) -lexeme l = void (satisfyT (l==)) show (lexemeFace l) - -arrowedPair :: Parser a -> Parser (a,a) -arrowedPair p = do - i <- p - lexeme L_LongArrow - j <- p - return (i,j) - -inCompleteFile :: Parser a -> Parser a -inCompleteFile parser = do - result <- parser - eof - return result diff --git a/src/Conjure/Language/Type.hs.orig b/src/Conjure/Language/Type.hs.orig deleted file mode 100644 index 7010adb590..0000000000 --- a/src/Conjure/Language/Type.hs.orig +++ /dev/null @@ -1,323 +0,0 @@ -{-# LANGUAGE DeriveGeneric, DeriveDataTypeable #-} - -module Conjure.Language.Type - ( Type(..) -<<<<<<< HEAD - , IntTag(..) -||||||| merged common ancestors -======= - , IntTag(..), dropTag, addTag, containsTag ->>>>>>> taggedints - , typeUnify - , typesUnify - , mostDefined - , homoType - , matrixNumDims - , innerTypeOf - , isPrimitiveType -<<<<<<< HEAD -<<<<<<< HEAD - , containsType -======= - , typeCanIndexMatrix ->>>>>>> f8c15eb3160b509a17e3d70103b237ea8d666c04 -||||||| merged common ancestors -======= - , typeCanIndexMatrix ->>>>>>> taggedints - ) where - --- conjure -import Conjure.Prelude -import Conjure.Bug -import Conjure.Language.Name -import Conjure.Language.Pretty - - -data Type - = TypeAny - | TypeBool -<<<<<<< HEAD -<<<<<<< HEAD - | TypeInt (Maybe Name) -======= - | TypeInt IntTag ->>>>>>> f8c15eb3160b509a17e3d70103b237ea8d666c04 -||||||| merged common ancestors - | TypeInt -======= - | TypeInt IntTag ->>>>>>> taggedints - | TypeEnum Name - | TypeUnnamed Name - | TypeTuple [Type] - | TypeRecord [(Name, Type)] - | TypeVariant [(Name, Type)] - | TypeList Type - | TypeMatrix Type Type - | TypeSet Type - | TypeMSet Type - | TypeFunction Type Type - | TypeSequence Type - | TypeRelation [Type] - | TypePartition Type - | TypePermutation Type - deriving (Eq, Ord, Show, Data, Typeable, Generic) - -instance Serialize Type -instance Hashable Type -instance ToJSON Type where toJSON = genericToJSON jsonOptions -instance FromJSON Type where parseJSON = genericParseJSON jsonOptions - -instance Pretty Type where - pretty TypeAny = "?" - pretty TypeBool = "bool" -<<<<<<< HEAD -<<<<<<< HEAD - pretty (TypeInt Nothing) = "int" - pretty (TypeInt (Just name)) = "int:" <> pretty name -======= - pretty TypeInt{} = "int" ->>>>>>> f8c15eb3160b509a17e3d70103b237ea8d666c04 -||||||| merged common ancestors - pretty TypeInt = "int" -======= - pretty TypeInt{} = "int" ->>>>>>> taggedints - pretty (TypeEnum nm ) = pretty nm - pretty (TypeUnnamed nm) = pretty nm - pretty (TypeTuple xs) = (if length xs <= 1 then "tuple" else prEmpty) - <> prettyList prParens "," xs - pretty (TypeRecord xs) = "record" <+> prettyList prBraces "," - [ pretty nm <+> ":" <+> pretty ty | (nm, ty) <- xs ] - pretty (TypeVariant xs) = "variant" <+> prettyList prBraces "," - [ pretty nm <+> ":" <+> pretty ty | (nm, ty) <- xs ] - pretty (TypeList x) = prBrackets (pretty x) - pretty (TypeMatrix index innerNested) - = "matrix indexed by" <+> prettyList prBrackets "," indices - <+> "of" <+> pretty inner - where - (indices,inner) = first (index:) $ collect innerNested - collect (TypeMatrix i j) = first (i:) $ collect j - collect x = ([],x) - pretty (TypeSet x) = "set of" <+> pretty x - pretty (TypeMSet x) = "mset of" <+> pretty x - pretty (TypeFunction fr to) = "function" <+> pretty fr <+> "-->" <+> pretty to - pretty (TypeSequence x) = "sequence of" <+> pretty x - pretty (TypePartition x) = "partition from" <+> pretty x - pretty (TypeRelation xs) = "relation of" <+> prettyList prParens " *" xs - pretty (TypePermutation x) = "permutation of" <+> pretty x - - -data IntTag = NoTag - | TagEnum Name - | TagUnnamed Name - deriving (Eq, Ord, Show, Data, Typeable, Generic) - -instance Serialize IntTag -instance Hashable IntTag -instance ToJSON IntTag where toJSON = genericToJSON jsonOptions -instance FromJSON IntTag where parseJSON = genericParseJSON jsonOptions - - - -data IntTag = NoTag - | TagEnum Text - | TagUnnamed Text - deriving (Eq, Ord, Show, Data, Typeable, Generic) - -instance Serialize IntTag -instance Hashable IntTag -instance ToJSON IntTag where toJSON = genericToJSON jsonOptions -instance FromJSON IntTag where parseJSON = genericParseJSON jsonOptions - -dropTag :: Data a => a -> a -dropTag = transformBi (const NoTag) - -addTag :: Data a => IntTag -> a -> a -addTag t = transformBi (const t) - -containsTag :: (MonadFail m, Data a) => a -> m IntTag -containsTag dat = return $ head $ universeBi dat - --- | Check whether two types unify or not. -typeUnify :: Type -> Type -> Bool -typeUnify TypeAny _ = True -typeUnify _ TypeAny = True -typeUnify TypeBool TypeBool = True -<<<<<<< HEAD -<<<<<<< HEAD -typeUnify (TypeInt a) (TypeInt b) = a == b -typeUnify (TypeInt (Nothing)) (TypeEnum _) = False -typeUnify (TypeInt (Just a)) (TypeEnum b) = a == b -typeUnify (TypeEnum _) (TypeInt (Nothing)) = False -typeUnify (TypeEnum b) (TypeInt (Just a)) = a == b -======= -typeUnify (TypeInt t1) (TypeInt t2) = t1 == t2 ->>>>>>> f8c15eb3160b509a17e3d70103b237ea8d666c04 -||||||| merged common ancestors -typeUnify TypeInt TypeInt = True -typeUnify TypeInt TypeEnum{} = True -typeUnify TypeEnum{} TypeInt = True -======= -typeUnify (TypeInt t1) (TypeInt t2) = t1 == t2 ->>>>>>> taggedints -typeUnify (TypeEnum a) (TypeEnum b) = a == b || a == "?" || b == "?" -- the "?" is a hack so sameToSameToBool works -typeUnify (TypeUnnamed a) (TypeUnnamed b) = a == b -typeUnify (TypeTuple [TypeAny]) TypeTuple{} = True -typeUnify TypeTuple{} (TypeTuple [TypeAny]) = True -typeUnify (TypeTuple as) (TypeTuple bs) = (length as == length bs) && and (zipWith typeUnify as bs) -typeUnify (TypeRecord as) (TypeRecord bs) - | length as /= length bs = False - | otherwise = and [ case lookup n bs of - Nothing -> False - Just b -> typeUnify a b - | (n,a) <- as - ] -typeUnify (TypeVariant as) (TypeVariant bs) - | length as /= length bs = False - | otherwise = and [ case lookup n bs of - Nothing -> False - Just b -> typeUnify a b - | (n,a) <- as - ] -typeUnify (TypeList a) (TypeList b) = typeUnify a b -typeUnify (TypeMatrix a1 a2) (TypeMatrix b1 b2) = and (zipWith typeUnify [a1,a2] [b1,b2]) -typeUnify (TypeList a) (TypeMatrix _ b) = typeUnify a b -typeUnify (TypeMatrix _ a) (TypeList b) = typeUnify a b -typeUnify (TypeList a) (TypeSequence b) = typeUnify a b -typeUnify (TypeSequence a) (TypeList b) = typeUnify a b -typeUnify (TypeSet a) (TypeSet b) = typeUnify a b -typeUnify (TypeMSet a) (TypeMSet b) = typeUnify a b -typeUnify (TypeFunction a1 a2) (TypeFunction b1 b2) = and (zipWith typeUnify [a1,a2] [b1,b2]) -typeUnify (TypeSequence a) (TypeSequence b) = typeUnify a b -typeUnify (TypeRelation [TypeAny]) TypeRelation{} = True -- also hacks to make sameToSameToBool work -typeUnify TypeRelation{} (TypeRelation [TypeAny]) = True -typeUnify (TypeRelation as) (TypeRelation bs) = (length as == length bs) && and (zipWith typeUnify as bs) -typeUnify (TypePartition a) (TypePartition b) = typeUnify a b -typeUnify (TypePermutation a) (TypePermutation b) = typeUnify a b -typeUnify _ _ = False - --- | Check whether a given list of types unify with each other or not. -typesUnify :: [Type] -> Bool -typesUnify ts = and [ typeUnify i j | i <- ts, j <- ts ] - --- | Given a list of types return "the most defined" one in this list. --- This is to get rid of TypeAny's if there are any. --- Precondition: `typesUnify` -mostDefined :: [Type] -> Type -mostDefined = foldr f TypeAny - where - f :: Type -> Type -> Type - f TypeAny x = x - f x TypeAny = x - f _ x@TypeBool{} = x - f _ x@TypeInt{} = x - f _ x@TypeEnum{} = x - f _ x@TypeUnnamed{} = x - f (TypeTuple [TypeAny]) x = x - f x (TypeTuple [TypeAny]) = x - f (TypeTuple as) (TypeTuple bs) | length as == length bs = TypeTuple (zipWith f as bs) - f (TypeRecord as) (TypeRecord bs) - | sort (map fst as) == sort (map fst bs) = - TypeRecord [ case lookup n bs of - Nothing -> bug "mostDefined.TypeRecord" - Just b -> (n, f a b) - | (n,a) <- as - ] - | typeUnify (TypeRecord as) (TypeRecord bs) = TypeAny - | otherwise = TypeAny - f (TypeVariant as) (TypeVariant bs) - | sort (map fst as) == sort (map fst bs) = - TypeVariant [ case lookup n bs of - Nothing -> bug "mostDefined.TypeVariant" - Just b -> (n, f a b) - | (n,a) <- as - ] - | typeUnify (TypeVariant as) (TypeVariant bs) = TypeAny - | otherwise = TypeAny - f (TypeList a) (TypeList b) = TypeList (f a b) - f (TypeMatrix a1 a2) (TypeMatrix b1 b2) = TypeMatrix (f a1 b1) (f a2 b2) - f (TypeList a) (TypeMatrix _ b) = TypeList (f a b) - f (TypeMatrix _ a) (TypeList b) = TypeList (f a b) - f (TypeSet a) (TypeSet b) = TypeSet (f a b) - f (TypeMSet a) (TypeMSet b) = TypeMSet (f a b) - f (TypeFunction a1 a2) (TypeFunction b1 b2) = TypeFunction (f a1 b1) (f a2 b2) - f (TypeSequence a) (TypeSequence b) = TypeSequence (f a b) - f (TypeRelation [TypeAny]) x = x - f x (TypeRelation [TypeAny]) = x - f (TypeRelation as) (TypeRelation bs) | length as == length bs = TypeRelation (zipWith f as bs) - f (TypePartition a) (TypePartition b) = TypePartition (f a b) - f (TypePermutation a) (TypePermutation b) = TypePermutation (f a b) - f _ _ = TypeAny - -matrixNumDims :: Type -> Int -matrixNumDims (TypeMatrix _ t) = 1 + matrixNumDims t -matrixNumDims (TypeList t) = 1 + matrixNumDims t -matrixNumDims _ = 0 - -homoType :: MonadFail m => Doc -> [Type] -> m Type -homoType msg [] = fail $ "empty collection, what's the type?" <++> ("When working on:" <+> msg) -homoType msg xs = - if typesUnify xs - then return (mostDefined xs) - else fail $ vcat [ "Not uniformly typed:" <+> msg --- , "Involved types are:" <+> vcat (map (\tx -> pretty tx <> " " <> stringToDoc (show tx)) xs) - , "Involved types are:" <+> vcat (map pretty xs) - - ] - -innerTypeOf :: MonadFail m => Type -> m Type -innerTypeOf (TypeList t) = return t -innerTypeOf (TypeMatrix _ t) = return t -innerTypeOf (TypeSet t) = return t -innerTypeOf (TypeMSet t) = return t -innerTypeOf (TypeFunction a b) = return (TypeTuple [a,b]) -<<<<<<< HEAD -<<<<<<< HEAD -innerTypeOf (TypeSequence t) = return (TypeTuple [TypeInt Nothing,t]) -======= -innerTypeOf (TypeSequence t) = return (TypeTuple [TypeInt NoTag,t]) ->>>>>>> f8c15eb3160b509a17e3d70103b237ea8d666c04 -||||||| merged common ancestors -innerTypeOf (TypeSequence t) = return (TypeTuple [TypeInt,t]) -======= -innerTypeOf (TypeSequence t) = return (TypeTuple [TypeInt NoTag,t]) ->>>>>>> taggedints -innerTypeOf (TypeRelation ts) = return (TypeTuple ts) -innerTypeOf (TypePartition t) = return (TypeSet t) -innerTypeOf (TypePermutation t) = return (TypeTuple [t,t]) -innerTypeOf t = fail ("innerTypeOf:" <+> pretty (show t)) - -isPrimitiveType :: Type -> Bool -isPrimitiveType TypeBool{} = True -isPrimitiveType TypeInt{} = True -isPrimitiveType (TypeMatrix index inner) = and [isPrimitiveType index, isPrimitiveType inner] -isPrimitiveType _ = False -<<<<<<< HEAD - -<<<<<<< HEAD -containsType :: Type -> Type -> Bool -containsType container containee = - if typesUnify [container, containee] - then True - else case innerTypeOf container of - Nothing -> False - Just so -> containsType so containee - -======= -typeCanIndexMatrix :: Type -> Bool -typeCanIndexMatrix TypeBool{} = True -typeCanIndexMatrix TypeInt {} = True -typeCanIndexMatrix TypeEnum{} = True -typeCanIndexMatrix _ = False ->>>>>>> f8c15eb3160b509a17e3d70103b237ea8d666c04 -||||||| merged common ancestors -======= - -typeCanIndexMatrix :: Type -> Bool -typeCanIndexMatrix TypeBool{} = True -typeCanIndexMatrix TypeInt {} = True -typeCanIndexMatrix TypeEnum{} = True -typeCanIndexMatrix _ = False ->>>>>>> taggedints diff --git a/src/Conjure/Language/ZeroVal.hs.orig b/src/Conjure/Language/ZeroVal.hs.orig deleted file mode 100644 index 7780fcd980..0000000000 --- a/src/Conjure/Language/ZeroVal.hs.orig +++ /dev/null @@ -1,93 +0,0 @@ -module Conjure.Language.ZeroVal ( zeroVal, EnumerateDomain ) where - --- conjure -import Conjure.Prelude -import Conjure.Bug -import Conjure.Language.Definition -import Conjure.Language.Domain -import Conjure.Language.Pretty -import Conjure.Process.Enumerate ( EnumerateDomain, enumerateDomain ) - - -zeroVal :: (MonadFail m, EnumerateDomain m, Pretty r) => Domain r Constant -> m Constant -zeroVal DomainBool = return $ ConstantBool False -<<<<<<< HEAD -zeroVal (DomainInt Nothing []) = return $ ConstantInt Nothing 0 -zeroVal (DomainInt Nothing (r:_)) = zeroValR r -||||||| merged common ancestors -zeroVal (DomainInt []) = return $ ConstantInt 0 -zeroVal (DomainInt (r:_)) = zeroValR r -======= -zeroVal (DomainInt t []) = return $ ConstantInt t 0 -zeroVal (DomainInt _ (r:_)) = zeroValR r ->>>>>>> taggedints -zeroVal (DomainTuple ds) = ConstantAbstract . AbsLitTuple <$> mapM zeroVal ds -zeroVal (DomainRecord xs) = do - values <- forM xs $ \ (nm, dom) -> do - z <- zeroVal dom - return (nm, z) - return $ ConstantAbstract $ AbsLitRecord values -zeroVal (DomainVariant xs@((nm, dom):_)) = do - z <- zeroVal dom - return $ ConstantAbstract $ AbsLitVariant (Just [(n, forgetRepr d) | (n,d) <- xs]) nm z -zeroVal (DomainMatrix index inner) = do - z <- zeroVal inner - is <- case index of - DomainInt _ rs -> rangesInts rs - _ -> fail $ "Matrix indexed by a domain that isn't int:" <+> pretty index - return $ ConstantAbstract $ AbsLitMatrix index $ replicate (length is) z -zeroVal d@(DomainSet _ (SetAttr sizeAttr) inner) = do - z <- zeroVal inner - minSize <- getMin d sizeAttr - return $ ConstantAbstract $ AbsLitSet $ replicate (fromInteger minSize) z -zeroVal d@(DomainSequence _ (SequenceAttr sizeAttr _) inner) = do - z <- zeroVal inner - minSize <- getMin d sizeAttr - return $ ConstantAbstract $ AbsLitSequence $ replicate (fromInteger minSize) z -zeroVal d@(DomainFunction _ (FunctionAttr sizeAttr partialityAttr _) innerFr innerTo) = - case partialityAttr of - PartialityAttr_Partial -> do - minSize <- getMin d sizeAttr - zFr <- zeroVal innerFr - zTo <- zeroVal innerTo - return $ ConstantAbstract $ AbsLitFunction $ replicate (fromInteger minSize) (zFr, zTo) - PartialityAttr_Total -> do - froms <- enumerateDomain (forgetRepr innerFr) - zTo <- zeroVal innerTo - return $ ConstantAbstract $ AbsLitFunction [ (fr, zTo) | fr <- froms ] -zeroVal d@(DomainMSet _ (MSetAttr sizeAttr _) inner) = do - z <- zeroVal inner - minSize <- getMin d sizeAttr - return $ ConstantAbstract $ AbsLitMSet $ replicate (fromInteger minSize) z -zeroVal d@(DomainRelation _ (RelationAttr sizeAttr _) inners) = do - zs <- mapM zeroVal inners - minSize <- getMin d sizeAttr - return $ ConstantAbstract $ AbsLitRelation $ replicate (fromInteger minSize) zs -zeroVal d@(DomainPartition _ (PartitionAttr numPartsAttr partSizeAttr _) inner) = do - z <- zeroVal inner - minSize1 <- getMin d numPartsAttr - minSize2 <- getMin d partSizeAttr - return $ ConstantAbstract $ AbsLitPartition $ replicate (fromInteger minSize1) - (replicate (fromInteger minSize2) z) -zeroVal d = bug $ "No 'zero' value for domain:" <+> pretty d - - -zeroValR :: MonadFail m => Range a -> m a -zeroValR RangeOpen = fail "No 'zero' value for an open range." -zeroValR (RangeSingle x) = return x -zeroValR (RangeLowerBounded x) = return x -zeroValR (RangeUpperBounded x) = return x -zeroValR (RangeBounded x _) = return x - - -getMin :: (MonadFail m, Pretty r, Pretty x) => Domain r x -> SizeAttr Constant -> m Integer -getMin _ SizeAttr_None = return 0 -getMin d (SizeAttr_Size x) = returnInt d x -getMin d (SizeAttr_MinSize x) = returnInt d x -getMin _ (SizeAttr_MaxSize _) = return 0 -getMin d (SizeAttr_MinMaxSize x _) = returnInt d x - - -returnInt :: (MonadFail m, Pretty r, Pretty x) => Domain r x -> Constant -> m Integer -returnInt _ (ConstantInt _ x) = return x -returnInt d _ = fail $ "Attribute expected to be an int in:" <+> pretty d diff --git a/src/Conjure/Process/Enumerate.hs.orig b/src/Conjure/Process/Enumerate.hs.orig deleted file mode 100644 index cd03398421..0000000000 --- a/src/Conjure/Process/Enumerate.hs.orig +++ /dev/null @@ -1,246 +0,0 @@ -module Conjure.Process.Enumerate - ( EnumerateDomain - , enumerateDomain - , enumerateInConstant - , EnumerateDomainNoIO(..) - ) where - -import Conjure.Prelude -import Conjure.Bug -import Conjure.UserError -import Conjure.Language.AdHoc -import Conjure.Language.AbstractLiteral -import Conjure.Language.Constant -import Conjure.Language.Domain -import Conjure.Language.Pretty -import Conjure.Language.Definition -import Conjure.Language.NameGen - -import Conjure.UI.IO -import Conjure.UI as UI ( UI(..), OutputFormat(..) ) -import {-# SOURCE #-} Conjure.UI.MainHelper - --- temporary -import System.IO.Temp ( withSystemTempDirectory ) - --- pipes -import qualified Pipes - - --- | This class is only to track where `enumerateDomain` might get called. --- It is essentially MonadIO, but doesn't allow arbitrary IO. -class (Functor m, Applicative m, Monad m, MonadUserError m) => EnumerateDomain m where liftIO' :: IO a -> m a -instance EnumerateDomain IO where liftIO' = id -instance EnumerateDomain m => EnumerateDomain (IdentityT m) where liftIO' = lift . liftIO' -instance EnumerateDomain m => EnumerateDomain (MaybeT m) where liftIO' = lift . liftIO' -instance EnumerateDomain m => EnumerateDomain (ExceptT m) where liftIO' = lift . liftIO' -instance EnumerateDomain m => EnumerateDomain (ReaderT r m) where liftIO' = lift . liftIO' -instance (EnumerateDomain m, Monoid w) => EnumerateDomain (WriterT w m) where liftIO' = lift . liftIO' -instance EnumerateDomain m => EnumerateDomain (StateT st m) where liftIO' = lift . liftIO' -instance EnumerateDomain m => EnumerateDomain (Pipes.Proxy a b c d m) where liftIO' = lift . liftIO' -instance EnumerateDomain m => EnumerateDomain (NameGenM m) where liftIO' = lift . liftIO' -instance (EnumerateDomain m, MonadFail m) => EnumerateDomain (UserErrorT m) where liftIO' = lift . liftIO' - --- | Use this if you don't want to allow a (EnumerateDomain m => m a) computation actually do IO. -data EnumerateDomainNoIO a = Done a | TriedIO | Failed Doc - deriving (Eq, Show) - -instance Functor EnumerateDomainNoIO where - fmap _ (Failed msg) = Failed msg - fmap _ TriedIO = TriedIO - fmap f (Done x) = Done (f x) - -instance Applicative EnumerateDomainNoIO where - pure = return - (<*>) = ap - -instance Monad EnumerateDomainNoIO where - return = Done - Failed msg >>= _ = Failed msg - TriedIO >>= _ = TriedIO - Done x >>= f = f x - -instance MonadFail EnumerateDomainNoIO where - fail = Failed - -instance MonadUserError EnumerateDomainNoIO where - userErr docs = Failed (vcat $ "User error:" : docs) - -instance NameGen EnumerateDomainNoIO where - nextName _ = fail "nextName{EnumerateDomainNoIO}" - exportNameGenState = fail "exportNameGenState{EnumerateDomainNoIO}" - importNameGenState _ = fail "importNameGenState{EnumerateDomainNoIO}" - -instance EnumerateDomain EnumerateDomainNoIO where liftIO' _ = TriedIO - -enumerateDomainMax :: Int -enumerateDomainMax = 10000 - -minionTimelimit :: Int -minionTimelimit = 60 - -savilerowTimelimit :: Int -savilerowTimelimit = 60 * 1000 - -enumerateDomain :: (MonadFail m, EnumerateDomain m) => Domain () Constant -> m [Constant] - -enumerateDomain d | not (null [ () | ConstantUndefined{} <- universeBi d ]) = - bug $ vcat [ "called enumerateDomain with a domain that has undefinedness values in it." - , pretty d - ] - -enumerateDomain DomainBool = return [ConstantBool False, ConstantBool True] -<<<<<<< HEAD -enumerateDomain (DomainInt _ []) = fail "enumerateDomain: infinite domain" -enumerateDomain (DomainInt Nothing rs) = concatMapM enumerateRange rs -enumerateDomain (DomainUnnamed nm (ConstantInt _ n)) = return (map (ConstantInt (Just nm)) [1..n]) -||||||| merged common ancestors -enumerateDomain (DomainInt []) = fail "enumerateDomain: infinite domain" -enumerateDomain (DomainInt rs) = concatMapM enumerateRange rs -enumerateDomain (DomainUnnamed _ (ConstantInt n)) = return (map ConstantInt [1..n]) -======= -enumerateDomain (DomainInt _ []) = fail "enumerateDomain: infinite domain" -enumerateDomain (DomainInt _ rs) = concatMapM enumerateRange rs -enumerateDomain (DomainUnnamed _ (ConstantInt t n)) = return (map (ConstantInt t) [1..n]) ->>>>>>> taggedints -enumerateDomain (DomainEnum _dName (Just rs) _mp) = concatMapM enumerateRange rs -enumerateDomain (DomainTuple ds) = do - inners <- mapM enumerateDomain ds - return $ map (ConstantAbstract . AbsLitTuple) (sequence inners) -<<<<<<< HEAD -enumerateDomain (DomainMatrix (DomainInt name indexDom) innerDom) = do -||||||| merged common ancestors -enumerateDomain (DomainMatrix (DomainInt indexDom) innerDom) = do -======= -enumerateDomain (DomainMatrix (DomainInt t indexDom) innerDom) = do ->>>>>>> taggedints - inners <- enumerateDomain innerDom - indexInts <- rangesInts indexDom - return -<<<<<<< HEAD - [ ConstantAbstract (AbsLitMatrix (DomainInt name indexDom) vals) -||||||| merged common ancestors - [ ConstantAbstract (AbsLitMatrix (DomainInt indexDom) vals) -======= - [ ConstantAbstract (AbsLitMatrix (DomainInt t indexDom) vals) ->>>>>>> taggedints - | vals <- replicateM (length indexInts) inners - ] - --- the sledgehammer approach -enumerateDomain d = liftIO' $ withSystemTempDirectory ("conjure-enumerateDomain-" ++ show (hash d)) $ \ tmpDir -> do - let model = Model { mLanguage = LanguageVersion "Essence" [1,0] - , mStatements = [Declaration (FindOrGiven Find "x" (fmap Constant d))] - , mInfo = def - } - let essenceFile = tmpDir "out.essence" - let outDir = tmpDir "outDir" - writeModel 120 Plain (Just essenceFile) model - let - solve :: IO () - solve = ignoreLogs $ mainWithArgs Solve - { UI.essence = essenceFile - , validateSolutionsOpt = False - , outputDirectory = outDir - , savilerowOptions = - [ "-O0" - , "-preprocess" , "None" - , "-timelimit" , show savilerowTimelimit - ] - , solverOptions = - [ "-cpulimit" , show minionTimelimit - ] - , solver = "minion" - , nbSolutions = show enumerateDomainMax - , copySolutions = False - , solutionsInOneFile = False - , logLevel = LogNone - -- default values for the rest - , essenceParams = [] - , numberingStart = 1 - , smartFilenames = False - , verboseTrail = False - , rewritesTrail = False - , logRuleFails = False - , logRuleSuccesses = False - , logRuleAttempts = False - , logChoices = False - , strategyQ = "f" - , strategyA = "c" - , representations = Nothing - , representationsFinds = Nothing - , representationsGivens = Nothing - , representationsAuxiliaries = Nothing - , representationsQuantifieds = Nothing - , representationsCuts = Nothing - , channelling = False - , representationLevels = True - , useExistingModels = [] - , seed = Nothing - , limitModels = Nothing - , limitTime = Nothing - , outputFormat = UI.Plain - , lineWidth = 120 - , responses = "" - } - -- catching the (SR timeout) error, and raising a user error - catch solve $ \ (e :: SomeException) -> userErr1 $ vcat - [ "Enumerate domain: too many." - , "When working on domain:" <++> pretty d - , "Exception:" <++> pretty (show e) - ] - solutions <- filter (".solution" `isSuffixOf`) <$> getDirectoryContents outDir - when (length solutions >= enumerateDomainMax) $ userErr1 $ vcat - [ "Enumerate domain: too many." - , "Nb solutions found:" <+> pretty (length solutions) - , "When working on domain:" <++> pretty d - ] - enumeration <- fmap concat $ forM solutions $ \ solutionFile -> do - Model _ decls _ <- readModelFromFile (outDir solutionFile) - let (enumeration, errs) = mconcat - [ case decl of - Declaration (Letting "x" x) | Just c <- e2c x -> ([c], []) - _ -> ([], [decl]) - | decl <- decls ] - if null errs - then return enumeration - else fail $ vcat $ "enumerateDomain, not Constants!" - : ("When working on domain:" <++> pretty d) - : map pretty errs - ++ map (pretty . show) errs - removeDirectoryIfExists outDir - removeDirectoryIfExists tmpDir - return enumeration - - -enumerateRange :: MonadFail m => Range Constant -> m [Constant] -enumerateRange (RangeSingle x) = return [x] -<<<<<<< HEAD -enumerateRange (RangeBounded (ConstantInt Nothing x) (ConstantInt Nothing y)) = return $ map (ConstantInt Nothing) [x..y] -||||||| merged common ancestors -enumerateRange (RangeBounded (ConstantInt x) (ConstantInt y)) = return $ map ConstantInt [x..y] -======= -enumerateRange (RangeBounded (ConstantInt tx x) (ConstantInt ty y)) | tx == ty - = return $ ConstantInt tx <$> [x..y] ->>>>>>> taggedints -enumerateRange RangeBounded{} = fail "enumerateRange RangeBounded" -enumerateRange RangeOpen{} = fail "enumerateRange RangeOpen" -enumerateRange RangeLowerBounded{} = fail "enumerateRange RangeLowerBounded" -enumerateRange RangeUpperBounded{} = fail "enumerateRange RangeUpperBounded" - -enumerateInConstant :: MonadFail m => Constant -> m [Constant] -enumerateInConstant constant = case constant of - ConstantAbstract (AbsLitMatrix _ xs) -> return xs - ConstantAbstract (AbsLitSet xs) -> return xs - ConstantAbstract (AbsLitMSet xs) -> return xs - ConstantAbstract (AbsLitFunction xs) -> return [ ConstantAbstract (AbsLitTuple [i,j]) | (i,j) <- xs ] - ConstantAbstract (AbsLitSequence xs) -> return [ ConstantAbstract (AbsLitTuple [i,j]) - | (i',j) <- zip allNats xs - , let i = fromInt i' - ] - ConstantAbstract (AbsLitRelation xs) -> return $ map (ConstantAbstract . AbsLitTuple) xs - ConstantAbstract (AbsLitPartition xs) -> return $ map (ConstantAbstract . AbsLitSet) xs - TypedConstant c _ -> enumerateInConstant c - _ -> fail $ vcat [ "enumerateInConstant" - , "constant:" <+> pretty constant - ] diff --git a/src/Conjure/Process/Enums.hs.orig b/src/Conjure/Process/Enums.hs.orig deleted file mode 100644 index a8f4213d75..0000000000 --- a/src/Conjure/Process/Enums.hs.orig +++ /dev/null @@ -1,333 +0,0 @@ -{-# LANGUAGE TupleSections #-} - -module Conjure.Process.Enums - ( removeEnumsFromModel - , removeEnumsFromParam - , addEnumsAndUnnamedsBack - ) where - -import Conjure.Prelude -import Conjure.Bug -import Conjure.UserError -import Conjure.Language.Definition -import Conjure.Language.Domain -import Conjure.Language.Pretty -import Conjure.Language.Type - --- text -import Data.Text as T ( pack ) - -import Data.List (cycle) - - --- | The argument is a model before nameResolution. --- Only intended to work on problem specifications. -removeEnumsFromModel :: (MonadFail m, MonadLog m, MonadUserError m) => Model -> m Model -removeEnumsFromModel = - removeEnumsFromModel_LettingEnums >=> - removeEnumsFromModel_GivenEnums >=> - checkEnums - - where - - removeEnumsFromModel_LettingEnums model = do - (statements', ( enumDomainNames :: [(Name, Domain () Expression)] - , nameToIntMapping :: [(Name, (Name, Integer))] - )) <- - flip runStateT ([], []) $ forM (mStatements model) $ \ st -> - case st of - Declaration (LettingDomainDefnEnum ename@(Name enameText) names) -> do - namesBefore <- gets (map fst . snd) -<<<<<<< HEAD - let outDomain = mkDomainIntBNamed ename 1 (fromInt (genericLength names)) -||||||| merged common ancestors - let outDomain = mkDomainIntB 1 (fromInt (genericLength names)) -======= - let outDomain = mkDomainIntBTagged (TagEnum enameText) - (fromIntWithTag 1 (TagEnum enameText)) - (fromIntWithTag (genericLength names) (TagEnum enameText)) ->>>>>>> taggedints - case names `intersect` namesBefore of - [] -> modify ( ( [(ename, outDomain)] - , zip names (zip (cycle [ename]) allNats) - ) `mappend` ) - repeated -> userErr1 $ vcat - [ "Some members of this enum domain (" <> pretty ename <> ") seem to be defined" - , "as part of other enum domains." - , "Repeated:" <+> prettyList id "," repeated - , "While working on domain:" <+> pretty st - ] - return (Declaration (Letting ename (Domain outDomain))) - _ -> return st - - let - onX :: Monad m => Expression -> m Expression - onX (Reference nm Nothing) - | Just (Name ename, i) <- lookup nm nameToIntMapping - = return (fromIntWithTag i (TagEnum ename)) - onX p = return p - - onD :: MonadFail m => Domain () Expression -> m (Domain () Expression) - onD (DomainEnum nm@(Name nmText) (Just ranges) _) - | Just _ <- lookup nm enumDomainNames -<<<<<<< HEAD - = DomainInt (Just nm) <$> mapM (mapM (nameToX nameToIntMapping)) ranges -||||||| merged common ancestors - = DomainInt <$> mapM (mapM (nameToX nameToIntMapping)) ranges -======= - = DomainInt (TagEnum nmText) <$> mapM (mapM (nameToX nameToIntMapping)) ranges ->>>>>>> taggedints - onD (DomainEnum nm Nothing _) - | Just d <- lookup nm enumDomainNames - = return (DomainReference nm (Just d)) - onD (DomainReference nm Nothing) - | Just d <- lookup nm enumDomainNames - = return (DomainReference nm (Just d)) - onD p = return p - - statements'' <- (transformBiM onD >=> transformBiM onX) statements' - return model { mStatements = statements'' } - - removeEnumsFromModel_GivenEnums model = do - (statements', enumDomainNames) <- - flip runStateT [] $ forM (mStatements model) $ \ st -> - case st of - Declaration (GivenDomainDefnEnum name@(Name nameText)) -> do - let nameS = name `mappend` "_EnumSize" -<<<<<<< HEAD - let outDomainS = DomainInt (Just name) [] - let outDomain = mkDomainIntBNamed name 1 -||||||| merged common ancestors - let outDomainS = DomainInt [] - let outDomain = mkDomainIntB 1 -======= - let outDomainS = DomainInt (TagEnum nameText) [] - let outDomain = mkDomainIntBTagged (TagEnum nameText) - (fromIntWithTag 1 (TagEnum nameText)) ->>>>>>> taggedints - (Reference nameS (Just (Alias (Domain outDomainS)))) - modify ([(name, outDomain)] `mappend`) - return [ Declaration (FindOrGiven Given nameS outDomainS) - , Declaration (Letting name (Domain outDomain)) - ] - _ -> return [st] - - let - onD :: Domain () Expression -> Domain () Expression - onD (DomainEnum nm@(Name nmText) (Just ranges) _) - | Just _ <- lookup nm enumDomainNames -<<<<<<< HEAD - = DomainInt (Just nm) ranges - onD (DomainEnum nm Nothing _) -||||||| merged common ancestors - = DomainInt ranges - onD (DomainEnum nm Nothing _) -======= - = DomainInt (TagEnum nmText) ranges - onD (DomainEnum nm Nothing _) ->>>>>>> taggedints - | Just d <- lookup nm enumDomainNames - = DomainReference nm (Just d) - onD (DomainReference nm Nothing) - | Just d <- lookup nm enumDomainNames - = DomainReference nm (Just d) - onD p = p - - let model' = model { mStatements = concat statements' - |> transformBi onD - } - - logDebug $ "Recording enumGivens:" <+> prettyList id "," (map fst enumDomainNames) - - return model' - - checkEnums model = do - let - leftovers :: [Domain () Expression] - leftovers = [ d | d@DomainEnum{} <- universeBi (mStatements model) ] - unless (null leftovers) $ bug $ vcat - $ "Could not remove some enum domains:" - : map (nest 4 . pretty) leftovers - return model - - -removeEnumsFromParam - :: (MonadFail m, MonadUserError m) - => Model -> Model -> m (Model, Model) -removeEnumsFromParam model param = do - let allStatements = map (False,) (map Declaration (miEnumLettings (mInfo model))) - ++ map (True,) (mStatements param) - - (statements', (enumDomainNames, nameToIntMapping)) <- - flip runStateT ([], []) $ forM allStatements $ \ (keep,st) -> - case st of - Declaration (LettingDomainDefnEnum ename@(Name enameText) names) -> do - namesBefore <- gets (map fst . snd) -<<<<<<< HEAD - let outDomain = mkDomainIntBNamed ename 1 (fromInt (genericLength names)) -||||||| merged common ancestors - let outDomain = mkDomainIntB 1 (fromInt (genericLength names)) -======= - let outDomain = mkDomainIntBTagged (TagEnum enameText) - (fromIntWithTag 1 (TagEnum enameText)) - (fromIntWithTag (genericLength names) (TagEnum enameText)) ->>>>>>> taggedints - case names `intersect` namesBefore of - [] -> modify ( ( [(ename, outDomain)] - , zip names (zip (cycle [ename]) allNats) - ) `mappend` ) - repeated -> userErr1 $ vcat - [ "Some members of this enum domain (" <> pretty ename <> ") seem to be defined" - , "as part of other enum domains." - , "Repeated:" <+> prettyList id "," repeated - , "While working on domain:" <+> pretty st - ] - return (Just (Declaration (Letting ename (Domain outDomain)))) - _ -> return (if keep then Just st else Nothing) - - let - onX :: Monad m => Expression -> m Expression - onX (Reference nm Nothing) - | Just (Name ename, i) <- lookup nm nameToIntMapping - = return (fromIntWithTag i (TagEnum ename)) - onX p = return p - - onD :: MonadFail m => Domain () Expression -> m (Domain () Expression) - onD (DomainEnum nm@(Name nmText) (Just ranges) _) - | Just _ <- lookup nm enumDomainNames -<<<<<<< HEAD - = DomainInt (Just nm) <$> mapM (mapM (nameToX nameToIntMapping)) ranges -||||||| merged common ancestors - = DomainInt <$> mapM (mapM (nameToX nameToIntMapping)) ranges -======= - = DomainInt (TagEnum nmText) <$> mapM (mapM (nameToX nameToIntMapping)) ranges ->>>>>>> taggedints - onD (DomainEnum nm Nothing _) - | Just d <- lookup nm enumDomainNames - = return (DomainReference nm (Just d)) - onD (DomainReference nm Nothing) - | Just d <- lookup nm enumDomainNames - = return (DomainReference nm (Just d)) - onD p = return p - - let param' = param { mStatements = catMaybes statements' } - let f = transformBiM onD >=> transformBiM onX - (,) <$> f model <*> f param' - - --- | Using the original domains from the Essence file. --- Converting integers back to enum constants. --- TODO: complete addEnumsAndUnnamedsBack - -addEnumsAndUnnamedsBack - :: ( Pretty r, Pretty x ) - => [Name] -- unnamed types - -> [((Integer, Name), Constant)] -- a lookup table for enums - -> Domain r x -- the domain we are working on - -> Constant -- the constant with ints in place of enums & unnameds - -> Constant -- the constant with enums & unnameds again -addEnumsAndUnnamedsBack unnameds ctxt = helper - - where - - helper domain constant = case (domain, constant) of - - (_, c@ConstantUndefined{}) -> c - - (DomainBool , c) -> c - (DomainIntE{}, c) -> c - (DomainInt{} , c) -> c - -<<<<<<< HEAD - (DomainEnum ename _ _, ConstantInt nname i) -> - if (Just ename) == nname - then fromMaybe (bug $ "addEnumsAndUnnamedsBack 1:" <+> pretty (i, ename)) (lookup (i, ename) ctxt) - else bug $ "addEnumsAndUnnamedsBack 1: ConstantInt tag didn't match" <+> pretty (i, ename) -||||||| merged common ancestors - (DomainEnum ename _ _, ConstantInt i) -> - fromMaybe (bug $ "addEnumsAndUnnamedsBack 1:" <+> pretty (i, ename)) - (lookup (i, ename) ctxt) -======= - (DomainEnum ename _ _, ConstantInt _ i) -> - fromMaybe (bug $ "addEnumsAndUnnamedsBack 1:" <+> pretty (i, ename)) - (lookup (i, ename) ctxt) ->>>>>>> taggedints - -<<<<<<< HEAD - (DomainReference ename _ , ConstantInt nname i) -> -||||||| merged common ancestors - (DomainReference ename _ , ConstantInt i) -> -======= - (DomainReference ename _ , ConstantInt _ i) -> ->>>>>>> taggedints - if ename `elem` unnameds - then ConstantEnum ename [] (mconcat [ename, "_", Name (T.pack (show i))]) -<<<<<<< HEAD - else ConstantInt nname i -- assume this was an int if if is not in the unnameds list -||||||| merged common ancestors - else ConstantInt i -- assume this was an int if if is not in the unnameds list -======= - else bug $ "addEnumsAndUnnamedsBack Unnamed:" <++> vcat [ "domain :" <+> pretty domain - , "constant:" <+> pretty constant - ] ->>>>>>> taggedints - - (DomainTuple ds, ConstantAbstract (AbsLitTuple cs)) -> - ConstantAbstract $ AbsLitTuple - [ helper d c - | (d,c) <- zip ds cs ] - - (DomainRecord ds, ConstantAbstract (AbsLitRecord cs)) -> - ConstantAbstract $ AbsLitRecord - [ (n, helper d c) - | ((n,d),(_,c)) <- zip ds cs ] - - (DomainVariant ds, ConstantAbstract (AbsLitVariant t n c)) -> - case lookup n ds of - Nothing -> bug $ "addEnumsAndUnnamedsBack Variant:" <++> vcat [ "domain :" <+> pretty domain - , "constant:" <+> pretty constant - ] - Just d -> ConstantAbstract $ AbsLitVariant t n (helper d c) - - (DomainMatrix _ inner, ConstantAbstract (AbsLitMatrix index vals)) -> - ConstantAbstract $ AbsLitMatrix index $ map (helper inner) vals - - (DomainSet _ _ inner, ConstantAbstract (AbsLitSet vals)) -> - ConstantAbstract $ AbsLitSet $ map (helper inner) vals - - (DomainMSet _ _ inner, ConstantAbstract (AbsLitMSet vals)) -> - ConstantAbstract $ AbsLitMSet $ map (helper inner) vals - - (DomainFunction _ _ fr to, ConstantAbstract (AbsLitFunction vals)) -> - ConstantAbstract $ AbsLitFunction - [ (helper fr a, helper to b) - | (a,b) <- vals ] - - (DomainSequence _ _ inner, ConstantAbstract (AbsLitSequence vals)) -> - ConstantAbstract $ AbsLitSequence $ map (helper inner) vals - - (DomainRelation _ _ inners, ConstantAbstract (AbsLitRelation vals)) -> - ConstantAbstract $ AbsLitRelation - [ [ helper d c | (d,c) <- zip inners line ] - | line <- vals ] - - (DomainPartition _ _ inner, ConstantAbstract (AbsLitPartition vals)) -> - ConstantAbstract $ AbsLitPartition - [ [ helper inner c | c <- line ] - | line <- vals ] - - (DomainPermutation _ _ inner, ConstantAbstract (AbsLitPermutation vals)) -> - ConstantAbstract $ AbsLitPermutation - [ [helper inner c | c <- line ] - | line <- vals] - _ -> bug ("addEnumsAndUnnamedsBack 3:" <++> vcat [ "domain :" <+> pretty domain - , "constant:" <+> pretty constant - ]) - --- first Name is the value, the second Name is the name of the enum domain -nameToX :: MonadFail m => [(Name, (Name, Integer))] -> Expression -> m Expression -nameToX nameToIntMapping (Reference nm _) = case lookup nm nameToIntMapping of - Nothing -> fail (pretty nm <+> "is used in a domain, but it isn't a member of the enum domain.") - Just (Name ename, i) -> return (fromIntWithTag i (TagEnum ename)) - Just (ename, i) -> bug $ "nameToX, nm:" <+> vcat [pretty (show ename), pretty i] -nameToX _ x = return x diff --git a/src/Conjure/Process/FiniteGivens.hs.orig b/src/Conjure/Process/FiniteGivens.hs.orig deleted file mode 100644 index 076c96150d..0000000000 --- a/src/Conjure/Process/FiniteGivens.hs.orig +++ /dev/null @@ -1,760 +0,0 @@ -module Conjure.Process.FiniteGivens - ( finiteGivens - , finiteGivensParam - ) where - -import Conjure.Prelude -import Conjure.Bug -import Conjure.UserError -import Conjure.Language.Definition -import Conjure.Language.Constant -import Conjure.Language.Domain -import Conjure.Language.Pretty -import Conjure.Language.Instantiate ( instantiateExpression, instantiateDomain ) -import Conjure.Language.ZeroVal ( zeroVal ) -import Conjure.Language.Type -import Conjure.Process.Enumerate ( EnumerateDomain ) - - --- | givens should have finite domains. except ints. --- this transformation introduces extra given ints to make them finite. --- the values for the extra givens will be computed during translate-solution -finiteGivens - :: ( MonadFail m - , MonadLog m - , NameGen m - , MonadUserError m - , EnumerateDomain m - ) - => Model - -> m Model -finiteGivens m = flip evalStateT 1 $ do - statements <- forM (mStatements m) $ \ st -> - case st of - Declaration (FindOrGiven Given name domain) -> do - (domain', extras, _) <- mkFinite domain -<<<<<<< HEAD - return $ [ Declaration $ FindOrGiven Given e (DomainInt Nothing []) | e <- extras ] -||||||| merged common ancestors - return $ [ Declaration $ FindOrGiven Given e (DomainInt []) | e <- extras ] -======= - return $ [ Declaration $ FindOrGiven Given e (DomainInt NoTag []) | e <- extras ] ->>>>>>> taggedints - ++ [ Declaration $ FindOrGiven Given name domain' ] - _ -> return [st] - namegenst <- exportNameGenState - return m { mStatements = concat statements - , mInfo = (mInfo m) { miNameGenState = namegenst - , miNbExtraGivens = maybe 0 (\ n -> n - 1 ) (lookup "fin" namegenst) - } - } - - -finiteGivensParam - :: (MonadFail m, MonadUserError m, MonadLog m, NameGen m, EnumerateDomain m) - => Model -- eprime - -> Model -- essence-param - -> m (Model, [Name]) -- essence-param -finiteGivensParam eprimeModel essenceParam = flip evalStateT 1 $ do - let essenceGivenNames = eprimeModel |> mInfo |> miGivens - let essenceGivens = eprimeModel |> mInfo |> miOriginalDomains - let essenceLettings = extractLettings essenceParam - ++ eprimeModel |> mInfo |> miLettings - let nbExtraGivens = eprimeModel |> mInfo |> miNbExtraGivens - let expectedExtras = [ MachineName "fin" extraGiven [] - | extraGiven <- [1..nbExtraGivens] - ] - extras <- fmap concat $ forM essenceGivenNames $ \ name -> do - logDebugVerbose $ "finiteGivensParam name" <+> pretty name - case (lookup name essenceGivens, lookup name essenceLettings) of - (Nothing, _) -> bug $ "Not found:" <+> pretty name - (_, Nothing) -> return [] - (Just domain', Just expr) -> do - logDebugVerbose $ "finiteGivensParam domain' " <+> pretty domain' - domain <- fmap Constant <$> instantiateDomain essenceLettings domain' - logDebugVerbose $ "finiteGivensParam domain " <+> pretty domain - logDebugVerbose $ "finiteGivensParam expr " <+> pretty expr - constant <- instantiateExpression essenceLettings expr - logDebugVerbose $ "finiteGivensParam constant" <+> pretty constant - (_, _, f) <- mkFinite domain - outs <- f constant - logDebugVerbose $ "finiteGivensParam outs " <+> vcat (map pretty outs) - return outs - logDebugVerbose $ "finiteGivensParam extras " <+> vcat (map (pretty . show) extras) - return - ( essenceParam - { mStatements = [ Declaration (Letting name (Constant value)) - | name <- expectedExtras - -- we are storing the number of "extra givens" in the model info. - -- also, defaulting their values to 0 if they do not come out of - -- the usual finiteGivens process. - -- the idea is: if they don't come out from that, - -- they must be a part of an emply collection, hence 0. - , let value = fromMaybe 0 (lookup name extras) - ] - ++ mStatements essenceParam - } - , expectedExtras - ) - - --- | given a domain, add it additional attributes to make it _smaller_ --- for example, this means adding a size attribute at the outer-most level --- and adding a maxSize attribute at the inner levels. -mkFinite - :: ( MonadState Int m - , MonadFail m - , NameGen m - , MonadLog m - , MonadUserError m - , EnumerateDomain m - ) - => Domain () Expression - -> m ( Domain () Expression -- "finite" domain - , [Name] -- extra givens - , Constant -> m [(Name, Constant)] -- value calculator for the extra givens - -- input is a list of values for the domain - ) -mkFinite d@DomainTuple{} = mkFiniteOutermost d -mkFinite d@DomainRecord{} = mkFiniteOutermost d -mkFinite d@DomainVariant{} = mkFiniteOutermost d -mkFinite d@DomainMatrix{} = mkFiniteOutermost d -mkFinite d@DomainSet{} = mkFiniteOutermost d -mkFinite d@DomainMSet{} = mkFiniteOutermost d -mkFinite d@DomainSequence{} = mkFiniteOutermost d -mkFinite d@DomainFunction{} = mkFiniteOutermost d -mkFinite d@DomainRelation{} = mkFiniteOutermost d -mkFinite d@DomainPartition{} = mkFiniteOutermost d -mkFinite d = return (d, [], const (return [])) - - -mkFiniteOutermost - :: ( MonadState Int m - , MonadFail m - , NameGen m - , MonadLog m - , MonadUserError m - , EnumerateDomain m - ) - => Domain () Expression - -> m ( Domain () Expression - , [Name] - , Constant -> m [(Name, Constant)] - ) -mkFiniteOutermost (DomainTuple inners) = do - mids <- mapM mkFiniteInner inners - return - ( DomainTuple (map fst3 mids) - , concatMap snd3 mids - , \ constant -> do - logDebug $ "mkFiniteOutermost DomainTuple" <+> pretty constant - xs <- failToUserError $ viewConstantTuple constant - let innerFs = map thd3 mids - innerValues <- sequence [ innerF [x] | (innerF, x) <- zip innerFs xs ] - return (concat innerValues) - ) -mkFiniteOutermost (DomainRecord inners) = do - mids <- mapM (mkFiniteInner . snd) inners - return - ( DomainRecord (zip (map fst inners) (map fst3 mids)) - , concatMap snd3 mids - , \ constant -> do - logDebug $ "mkFiniteOutermost DomainRecord" <+> pretty constant - xs' <- failToUserError $ viewConstantRecord constant - let - xs :: [Constant] - xs = map snd xs' - let innerFs = map thd3 mids - innerValues <- sequence [ innerF [x] | (innerF, x) <- zip innerFs xs ] - return (concat innerValues) - ) -mkFiniteOutermost (DomainVariant inners) = do - mids <- mapM (mkFiniteInner . snd) inners - return - ( DomainVariant (zip (map fst inners) (map fst3 mids)) - , concatMap snd3 mids - , \ constant -> do - logDebug $ "mkFiniteOutermost DomainVariant" <+> pretty constant - xs' <- failToUserError $ viewConstantVariant constant - xs :: [Constant] <- sequence - [ case xs' of - (_, nm', c') | nm == nm' -> return c' - _ -> instantiateDomain [] d >>= zeroVal - | (nm, d) <- inners ] - let innerFs = map thd3 mids - innerValues <- sequence [ innerF [x] | (innerF, x) <- zip innerFs xs ] - return (concat innerValues) - ) -mkFiniteOutermost (DomainMatrix index inner) = do - (inner', innerExtras, innerF) <- mkFiniteInner inner - return - ( DomainMatrix index inner' - , innerExtras - , \ constant -> do - logDebug $ "mkFiniteOutermost DomainMatrix" <+> pretty constant - (_, matr) <- failToUserError $ viewConstantMatrix constant - innerValues <- innerF matr - return innerValues - ) -mkFiniteOutermost (DomainSet () attr@(SetAttr SizeAttr_Size{}) inner) = do - (inner', innerExtras, innerF) <- mkFiniteInner inner - return - ( DomainSet () attr inner' - , innerExtras - , \ constant -> do - logDebug $ "mkFiniteOutermost DomainSet" <+> pretty constant - set <- failToUserError $ viewConstantSet constant - innerValues <- innerF set - return innerValues - ) -mkFiniteOutermost (DomainSet () _ inner) = do - s <- nextName "fin" - (inner', innerExtras, innerF) <- mkFiniteInner inner - return - ( DomainSet () (SetAttr (SizeAttr_Size (fromName s))) inner' - , s:innerExtras - , \ constant -> do - logDebug $ "mkFiniteOutermost DomainSet" <+> pretty constant - set <- failToUserError $ viewConstantSet constant - let setSize = genericLength set - innerValues <- innerF set -<<<<<<< HEAD - return $ innerValues ++ [(s, ConstantInt Nothing setSize)] -||||||| merged common ancestors - return $ innerValues ++ [(s, ConstantInt setSize)] -======= - return $ innerValues ++ [(s, ConstantInt NoTag setSize)] ->>>>>>> taggedints - ) -mkFiniteOutermost (DomainMSet () attr@(MSetAttr SizeAttr_Size{} _) inner) = do - (inner', innerExtras, innerF) <- mkFiniteInner inner - return - ( DomainMSet () attr inner' - , innerExtras - , \ constant -> do - logDebug $ "mkFiniteOutermost DomainMSet" <+> pretty constant - set <- failToUserError $ viewConstantMSet constant - innerValues <- innerF set - return innerValues - ) -mkFiniteOutermost (DomainMSet () (MSetAttr _ occurAttr) inner) = do - s <- nextName "fin" - (inner', innerExtras, innerF) <- mkFiniteInner inner - return - ( DomainMSet () (MSetAttr (SizeAttr_Size (fromName s)) occurAttr) inner' - , s:innerExtras - , \ constant -> do - logDebug $ "mkFiniteOutermost DomainMSet" <+> pretty constant - set <- failToUserError $ viewConstantMSet constant - let setSize = genericLength set - innerValues <- innerF set -<<<<<<< HEAD - return $ innerValues ++ [(s, ConstantInt Nothing setSize)] -||||||| merged common ancestors - return $ innerValues ++ [(s, ConstantInt setSize)] -======= - return $ innerValues ++ [(s, ConstantInt NoTag setSize)] ->>>>>>> taggedints - ) -mkFiniteOutermost (DomainSequence () attr@(SequenceAttr SizeAttr_Size{} _) inner) = do - (inner', innerExtras, innerF) <- mkFiniteInner inner - return - ( DomainSequence () attr inner' - , innerExtras - , \ constant -> do - logDebug $ "mkFiniteOutermost DomainSequence" <+> pretty constant - set <- failToUserError $ viewConstantSequence constant - innerValues <- innerF set - return innerValues - ) -mkFiniteOutermost (DomainSequence () (SequenceAttr _ jectivityAttr) inner) = do - s <- nextName "fin" - (inner', innerExtras, innerF) <- mkFiniteInner inner - return - ( DomainSequence () (SequenceAttr (SizeAttr_Size (fromName s)) jectivityAttr) inner' - , s:innerExtras - , \ constant -> do - logDebug $ "mkFiniteOutermost DomainSequence" <+> pretty constant - set <- failToUserError $ viewConstantSequence constant - let setSize = genericLength set - innerValues <- innerF set -<<<<<<< HEAD - return $ innerValues ++ [(s, ConstantInt Nothing setSize)] -||||||| merged common ancestors - return $ innerValues ++ [(s, ConstantInt setSize)] -======= - return $ innerValues ++ [(s, ConstantInt NoTag setSize)] ->>>>>>> taggedints - ) -mkFiniteOutermost (DomainFunction () attr@(FunctionAttr SizeAttr_Size{} _ _) innerFr innerTo) = do - (innerFr', innerFrExtras, innerFrF) <- mkFiniteInner innerFr - (innerTo', innerToExtras, innerToF) <- mkFiniteInner innerTo - return - ( DomainFunction () attr innerFr' innerTo' - , innerFrExtras ++ innerToExtras - , \ constant -> do - logDebug $ "mkFiniteOutermost DomainFunction" <+> pretty constant - function <- failToUserError $ viewConstantFunction constant - innerFrValues <- innerFrF (map fst function) - innerToValues <- innerToF (map snd function) - return $ innerFrValues ++ innerToValues - ) -mkFiniteOutermost (DomainFunction () (FunctionAttr _ partialityAttr jectivityAttr) innerFr innerTo) = do - s <- nextName "fin" - (innerFr', innerFrExtras, innerFrF) <- mkFiniteInner innerFr - (innerTo', innerToExtras, innerToF) <- mkFiniteInner innerTo - return - ( DomainFunction () - (FunctionAttr (SizeAttr_Size (fromName s)) partialityAttr jectivityAttr) - innerFr' innerTo' - , s : innerFrExtras ++ innerToExtras - , \ constant -> do - logDebug $ "mkFiniteOutermost DomainFunction" <+> pretty constant - function <- failToUserError $ viewConstantFunction constant - let functionSize = genericLength function - innerFrValues <- innerFrF (map fst function) - innerToValues <- innerToF (map snd function) -<<<<<<< HEAD - return $ innerFrValues ++ innerToValues ++ [(s, ConstantInt Nothing functionSize)] -||||||| merged common ancestors - return $ innerFrValues ++ innerToValues ++ [(s, ConstantInt functionSize)] -======= - return $ innerFrValues ++ innerToValues ++ [(s, ConstantInt NoTag functionSize)] ->>>>>>> taggedints - ) -mkFiniteOutermost (DomainRelation () attr@(RelationAttr SizeAttr_Size{} _) inners) = do - (inners', innersExtras, innersF) <- unzip3 <$> mapM mkFiniteInner inners - return - ( DomainRelation () attr inners' - , concat innersExtras - , \ constant -> do - logDebug $ "mkFiniteOutermost DomainRelation" <+> pretty constant - relation <- failToUserError $ viewConstantRelation constant - innersValues <- zipWithM ($) innersF (transpose relation) - return (concat innersValues) - ) -mkFiniteOutermost (DomainRelation () (RelationAttr _ binRelAttr) inners) = do - s <- nextName "fin" - (inners', innersExtras, innersF) <- unzip3 <$> mapM mkFiniteInner inners - return - ( DomainRelation () - (RelationAttr (SizeAttr_Size (fromName s)) binRelAttr) - inners' - , s : concat innersExtras - , \ constant -> do - logDebug $ "mkFiniteOutermost DomainRelation" <+> pretty constant - relation <- failToUserError $ viewConstantRelation constant - let relationSize = genericLength relation - innersValues <- zipWithM ($) innersF (transpose relation) -<<<<<<< HEAD - return $ concat innersValues ++ [(s, ConstantInt Nothing relationSize)] -||||||| merged common ancestors - return $ concat innersValues ++ [(s, ConstantInt relationSize)] -======= - return $ concat innersValues ++ [(s, ConstantInt NoTag relationSize)] ->>>>>>> taggedints - ) -mkFiniteOutermost (DomainPartition () attr@(PartitionAttr SizeAttr_Size{} SizeAttr_Size{} _) inner) = do - (inner', innerExtras, innerF) <- mkFiniteInner inner - return - ( DomainPartition () attr inner' - , innerExtras - , \ constant -> do - logDebug $ "mkFiniteOutermost DomainPartition" <+> pretty constant - parts <- failToUserError $ viewConstantPartition constant - innerValues <- mapM innerF parts - return (concat innerValues) - ) -mkFiniteOutermost (DomainPartition () (PartitionAttr _ _ isRegularAttr) inner) = do - numPartsFin <- nextName "fin" - partsSizeFin <- nextName "fin" - (inner', innerExtras, innerF) <- mkFiniteInner inner - return - ( DomainPartition () - (PartitionAttr (SizeAttr_Size (fromName numPartsFin)) - (SizeAttr_MaxSize (fromName partsSizeFin)) - isRegularAttr) - inner' - , numPartsFin:partsSizeFin:innerExtras - , \ constant -> do - logDebug $ "mkFiniteOutermost DomainPartition" <+> pretty constant - parts <- failToUserError $ viewConstantPartition constant - let numPartsVal = genericLength parts - let partsSizeVal = maximum0 $ map genericLength parts - innerValues <- mapM innerF parts -<<<<<<< HEAD - return $ concat innerValues ++ [ (numPartsFin, ConstantInt Nothing numPartsVal) - , (partsSizeFin, ConstantInt Nothing partsSizeVal) -||||||| merged common ancestors - return $ concat innerValues ++ [ (numPartsFin, ConstantInt numPartsVal) - , (partsSizeFin, ConstantInt partsSizeVal) -======= - return $ concat innerValues ++ [ (numPartsFin, ConstantInt NoTag numPartsVal) - , (partsSizeFin, ConstantInt NoTag partsSizeVal) ->>>>>>> taggedints - ] - ) -mkFiniteOutermost d = return (d, [], const (return [])) - - -mkFiniteInner - :: ( MonadState Int m - , MonadFail m - , NameGen m - , MonadLog m - , MonadUserError m - , EnumerateDomain m - ) - => Domain () Expression - -> m ( Domain () Expression - , [Name] - , [Constant] -> m [(Name, Constant)] - ) -<<<<<<< HEAD -mkFiniteInner (DomainInt name []) = do -||||||| merged common ancestors -mkFiniteInner (DomainInt []) = do -======= -mkFiniteInner (DomainInt t []) = do ->>>>>>> taggedints - fr <- nextName "fin" - to <- nextName "fin" - return -<<<<<<< HEAD - ( DomainInt name [RangeBounded (fromName fr) (fromName to)] -||||||| merged common ancestors - ( DomainInt [RangeBounded (fromName fr) (fromName to)] -======= - ( DomainInt t [RangeBounded (fromName fr) (fromName to)] ->>>>>>> taggedints - , [fr, to] - , \ constants -> do - logDebug $ "mkFiniteInner DomainInt" <+> vcat (map pretty constants) - ints <- failToUserError $ mapM viewConstantInt constants -<<<<<<< HEAD - return [ (fr, ConstantInt Nothing (minimum ints)) - , (to, ConstantInt Nothing (maximum0 ints)) -||||||| merged common ancestors - return [ (fr, ConstantInt (minimum ints)) - , (to, ConstantInt (maximum0 ints)) -======= - return [ (fr, ConstantInt t (minimum ints)) - , (to, ConstantInt t (maximum0 ints)) ->>>>>>> taggedints - ] - ) -<<<<<<< HEAD -mkFiniteInner (DomainInt name [RangeLowerBounded low]) = do -||||||| merged common ancestors -mkFiniteInner (DomainInt [RangeLowerBounded low]) = do -======= -mkFiniteInner (DomainInt t [RangeLowerBounded low]) = do ->>>>>>> taggedints - new <- nextName "fin" - return -<<<<<<< HEAD - ( DomainInt name [RangeBounded low (fromName new)] -||||||| merged common ancestors - ( DomainInt [RangeBounded low (fromName new)] -======= - ( DomainInt t [RangeBounded low (fromName new)] ->>>>>>> taggedints - , [new] - , \ constants -> do - logDebug $ "mkFiniteInner DomainInt" <+> vcat (map pretty constants) - ints <- failToUserError $ mapM viewConstantInt constants -<<<<<<< HEAD - return [ (new, ConstantInt Nothing (maximum0 ints)) ] -||||||| merged common ancestors - return [ (new, ConstantInt (maximum0 ints)) ] -======= - return [ (new, ConstantInt t (maximum0 ints)) ] ->>>>>>> taggedints - ) -<<<<<<< HEAD -mkFiniteInner (DomainInt name [RangeUpperBounded upp]) = do -||||||| merged common ancestors -mkFiniteInner (DomainInt [RangeUpperBounded upp]) = do -======= -mkFiniteInner (DomainInt t [RangeUpperBounded upp]) = do ->>>>>>> taggedints - new <- nextName "fin" - return -<<<<<<< HEAD - ( DomainInt name [RangeBounded (fromName new) upp] -||||||| merged common ancestors - ( DomainInt [RangeBounded (fromName new) upp] -======= - ( DomainInt t [RangeBounded (fromName new) upp] ->>>>>>> taggedints - , [new] - , \ constants -> do - logDebug $ "mkFiniteInner DomainInt" <+> vcat (map pretty constants) - ints <- failToUserError $ mapM viewConstantInt constants -<<<<<<< HEAD - return [ (new, ConstantInt Nothing (minimum ints)) ] -||||||| merged common ancestors - return [ (new, ConstantInt (minimum ints)) ] -======= - return [ (new, ConstantInt t (minimum ints)) ] ->>>>>>> taggedints - ) -mkFiniteInner (DomainTuple inners) = do - mids <- mapM mkFiniteInner inners - return - ( DomainTuple (map fst3 mids) - , concatMap snd3 mids - , \ constants -> do - logDebug $ "mkFiniteInner DomainTuple" <+> vcat (map pretty constants) - xss <- failToUserError $ mapM viewConstantTuple constants - let innerFs = map thd3 mids - innerValues <- sequence [ innerF xs | (innerF, xs) <- zip innerFs (transpose xss) ] - return (concat innerValues) - ) -mkFiniteInner (DomainRecord inners) = do - mids <- mapM (mkFiniteInner . snd) inners - return - ( DomainRecord (zip (map fst inners) (map fst3 mids)) - , concatMap snd3 mids - , \ constants -> do - logDebug $ "mkFiniteInner DomainRecord" <+> vcat (map pretty constants) - xss' :: [[(Name, Constant)]] <- failToUserError $ mapM viewConstantRecord constants - let - xss :: [[Constant]] - xss = map (map snd) xss' - let innerFs = map thd3 mids - innerValues <- sequence [ innerF xs | (innerF, xs) <- zip innerFs (transpose xss) ] - return (concat innerValues) - ) -mkFiniteInner (DomainVariant inners) = do - mids <- mapM (mkFiniteInner . snd) inners - return - ( DomainVariant (zip (map fst inners) (map fst3 mids)) - , concatMap snd3 mids - , \ constants -> do - logDebug $ "mkFiniteInner DomainVariant" <+> vcat (map pretty constants) - xss' <- failToUserError $ mapM viewConstantVariant constants - xss :: [[Constant]] - <- sequence - [ sequence - [ case xs' of - (_, nm', c') | nm == nm' -> return c' - _ -> instantiateDomain [] d >>= zeroVal - | (nm, d) <- inners ] - | xs' <- xss' ] - let innerFs = map thd3 mids - innerValues <- sequence [ innerF xs | (innerF, xs) <- zip innerFs (transpose xss) ] - return (concat innerValues) - ) -mkFiniteInner (DomainMatrix index inner) = do - (inner', innerExtras, innerF) <- mkFiniteInner inner - return - ( DomainMatrix index inner' - , innerExtras - , \ constants -> do - logDebug $ "mkFiniteInner DomainMatrix" <+> vcat (map pretty constants) - xss <- failToUserError $ mapM viewConstantMatrix constants - innerF (concatMap snd xss) - ) -mkFiniteInner (DomainSet () attr@(SetAttr SizeAttr_Size{}) inner) = do - (inner', innerExtras, innerF) <- mkFiniteInner inner - return - ( DomainSet () attr inner' - , innerExtras - , \ constants -> do - logDebug $ "mkFiniteInner DomainSet" <+> vcat (map pretty constants) - sets <- failToUserError $ mapM viewConstantSet constants - innerF (concat sets) - ) -mkFiniteInner (DomainSet () _ inner) = do - s <- nextName "fin" - (inner', innerExtras, innerF) <- mkFiniteInner inner - return - ( DomainSet () (SetAttr (SizeAttr_MaxSize (fromName s))) inner' - , s:innerExtras - , \ constants -> do - logDebug $ "mkFiniteInner DomainSet" <+> vcat (map pretty constants) - sets <- failToUserError $ mapM viewConstantSet constants - let setMaxSize = maximum0 $ map genericLength sets - innerValues <- innerF (concat sets) -<<<<<<< HEAD - return $ innerValues ++ [(s, ConstantInt Nothing setMaxSize)] -||||||| merged common ancestors - return $ innerValues ++ [(s, ConstantInt setMaxSize)] -======= - return $ innerValues ++ [(s, ConstantInt NoTag setMaxSize)] ->>>>>>> taggedints - ) -mkFiniteInner (DomainMSet () attr@(MSetAttr SizeAttr_Size{} _) inner) = do - (inner', innerExtras, innerF) <- mkFiniteInner inner - return - ( DomainMSet () attr inner' - , innerExtras - , \ constants -> do - logDebug $ "mkFiniteInner DomainMSet" <+> vcat (map pretty constants) - sets <- failToUserError $ mapM viewConstantMSet constants - innerF (concat sets) - ) -mkFiniteInner (DomainMSet () (MSetAttr _ occurAttr) inner) = do - s <- nextName "fin" - (inner', innerExtras, innerF) <- mkFiniteInner inner - return - ( DomainMSet () (MSetAttr (SizeAttr_MaxSize (fromName s)) occurAttr) inner' - , s:innerExtras - , \ constants -> do - logDebug $ "mkFiniteInner DomainMSet" <+> vcat (map pretty constants) - sets <- failToUserError $ mapM viewConstantMSet constants - let setMaxSize = maximum0 $ map genericLength sets - innerValues <- innerF (concat sets) -<<<<<<< HEAD - return $ innerValues ++ [(s, ConstantInt Nothing setMaxSize)] -||||||| merged common ancestors - return $ innerValues ++ [(s, ConstantInt setMaxSize)] -======= - return $ innerValues ++ [(s, ConstantInt NoTag setMaxSize)] ->>>>>>> taggedints - ) -mkFiniteInner (DomainSequence () attr@(SequenceAttr SizeAttr_Size{} _) inner) = do - (inner', innerExtras, innerF) <- mkFiniteInner inner - return - ( DomainSequence () attr inner' - , innerExtras - , \ constants -> do - logDebug $ "mkFiniteInner DomainSequence" <+> vcat (map pretty constants) - seqs <- failToUserError $ mapM viewConstantSequence constants - innerF (concat seqs) - ) -mkFiniteInner (DomainSequence () (SequenceAttr _ jectivityAttr) inner) = do - s <- nextName "fin" - (inner', innerExtras, innerF) <- mkFiniteInner inner - return - ( DomainSequence () (SequenceAttr (SizeAttr_MaxSize (fromName s)) jectivityAttr) inner' - , s:innerExtras - , \ constants -> do - logDebug $ "mkFiniteInner DomainSequence" <+> vcat (map pretty constants) - seqs <- failToUserError $ mapM viewConstantSequence constants - let seqMaxSize = maximum0 $ map genericLength seqs - innerValues <- innerF (concat seqs) -<<<<<<< HEAD - return $ innerValues ++ [(s, ConstantInt Nothing seqMaxSize)] -||||||| merged common ancestors - return $ innerValues ++ [(s, ConstantInt seqMaxSize)] -======= - return $ innerValues ++ [(s, ConstantInt NoTag seqMaxSize)] ->>>>>>> taggedints - ) -mkFiniteInner (DomainFunction () attr@(FunctionAttr SizeAttr_Size{} _ _) innerFr innerTo) = do - (innerFr', innerFrExtras, innerFrF) <- mkFiniteInner innerFr - (innerTo', innerToExtras, innerToF) <- mkFiniteInner innerTo - return - ( DomainFunction () attr innerFr' innerTo' - , innerFrExtras ++ innerToExtras - , \ constants -> do - logDebug $ "mkFiniteInner DomainFunction" <+> vcat (map pretty constants) - functions <- failToUserError $ mapM viewConstantFunction constants - innerFrValues <- innerFrF (map fst (concat functions)) - innerToValues <- innerToF (map snd (concat functions)) - return $ innerFrValues ++ innerToValues - ) -mkFiniteInner (DomainFunction () (FunctionAttr _ partialityAttr jectivityAttr) innerFr innerTo) = do - s <- nextName "fin" - (innerFr', innerFrExtras, innerFrF) <- mkFiniteInner innerFr - (innerTo', innerToExtras, innerToF) <- mkFiniteInner innerTo - return - ( DomainFunction () - (FunctionAttr (SizeAttr_MaxSize (fromName s)) partialityAttr jectivityAttr) - innerFr' innerTo' - , s : innerFrExtras ++ innerToExtras - , \ constants -> do - logDebug $ "mkFiniteInner DomainFunction" <+> vcat (map pretty constants) - functions <- failToUserError $ mapM viewConstantFunction constants - let functionMaxSize = maximum0 $ map genericLength functions - innerFrValues <- innerFrF (map fst (concat functions)) - innerToValues <- innerToF (map snd (concat functions)) -<<<<<<< HEAD - return $ innerFrValues ++ innerToValues ++ [(s, ConstantInt Nothing functionMaxSize)] -||||||| merged common ancestors - return $ innerFrValues ++ innerToValues ++ [(s, ConstantInt functionMaxSize)] -======= - return $ innerFrValues ++ innerToValues ++ [(s, ConstantInt NoTag functionMaxSize)] ->>>>>>> taggedints - ) -mkFiniteInner (DomainRelation () attr@(RelationAttr SizeAttr_Size{} _) inners) = do - (inners', innersExtras, innersF) <- unzip3 <$> mapM mkFiniteInner inners - return - ( DomainRelation () attr inners' - , concat innersExtras - , \ constants -> do - logDebug $ "mkFiniteInner DomainRelation" <+> vcat (map pretty constants) - relations <- failToUserError $ mapM viewConstantRelation constants - innersValues <- zipWithM ($) innersF (transpose $ concat relations) - return $ concat innersValues - ) -mkFiniteInner (DomainRelation () (RelationAttr _ binRelAttr) inners) = do - s <- nextName "fin" - (inners', innersExtras, innersF) <- unzip3 <$> mapM mkFiniteInner inners - return - ( DomainRelation () - (RelationAttr (SizeAttr_MaxSize (fromName s)) binRelAttr) - inners' - , s : concat innersExtras - , \ constants -> do - logDebug $ "mkFiniteInner DomainRelation" <+> vcat (map pretty constants) - relations <- failToUserError $ mapM viewConstantRelation constants - let relationMaxSize = maximum0 $ map genericLength relations - innersValues <- zipWithM ($) innersF (transpose $ concat relations) -<<<<<<< HEAD - return $ concat innersValues ++ [(s, ConstantInt Nothing relationMaxSize)] -||||||| merged common ancestors - return $ concat innersValues ++ [(s, ConstantInt relationMaxSize)] -======= - return $ concat innersValues ++ [(s, ConstantInt NoTag relationMaxSize)] ->>>>>>> taggedints - ) -mkFiniteInner (DomainPartition () attr@(PartitionAttr SizeAttr_Size{} SizeAttr_Size{} _) inner) = do - (inner', innerExtras, innerF) <- mkFiniteInner inner - return - ( DomainPartition () attr inner' - , innerExtras - , \ constants -> do - logDebug $ "mkFiniteInner DomainPartition" <+> vcat (map pretty constants) - parts <- failToUserError $ mapM viewConstantPartition constants - innersValues <- mapM innerF (concat parts) - return $ concat innersValues - ) -mkFiniteInner (DomainPartition () (PartitionAttr _ _ isRegularAttr) inner) = do - numPartsFin <- nextName "fin" - partsSizeFin <- nextName "fin" - (inner', innerExtras, innerF) <- mkFiniteInner inner - return - ( DomainPartition () - (PartitionAttr (SizeAttr_MaxSize (fromName numPartsFin)) - (SizeAttr_MaxSize (fromName partsSizeFin)) - isRegularAttr) - inner' - , numPartsFin:partsSizeFin:innerExtras - , \ constants -> do - logDebug $ "mkFiniteInner DomainPartition" <+> vcat (map pretty constants) - parts <- failToUserError $ mapM viewConstantPartition constants - let numPartsVal = maximum0 $ map genericLength parts - let partsSizeVal = maximum0 $ map genericLength parts - innerValues <- mapM innerF (concat parts) -<<<<<<< HEAD - return $ concat innerValues ++ [ (numPartsFin, ConstantInt Nothing numPartsVal) - , (partsSizeFin, ConstantInt Nothing partsSizeVal) -||||||| merged common ancestors - return $ concat innerValues ++ [ (numPartsFin, ConstantInt numPartsVal) - , (partsSizeFin, ConstantInt partsSizeVal) -======= - return $ concat innerValues ++ [ (numPartsFin, ConstantInt NoTag numPartsVal) - , (partsSizeFin, ConstantInt NoTag partsSizeVal) ->>>>>>> taggedints - ] - ) -mkFiniteInner d = return (d, [], const (return [])) - - --- specialised the type for maximum0, to avoid possible bugs --- this function is always intended to be used with Integers -maximum0 :: [Integer] -> Integer -maximum0 xs = maximum (0:xs) diff --git a/src/Conjure/Process/InferAttributes.hs.orig b/src/Conjure/Process/InferAttributes.hs.orig deleted file mode 100644 index 92f126693c..0000000000 --- a/src/Conjure/Process/InferAttributes.hs.orig +++ /dev/null @@ -1,84 +0,0 @@ -{-# LANGUAGE QuasiQuotes #-} - --- | This is an extremely simplified version of type-strengthening -module Conjure.Process.InferAttributes ( inferAttributes ) where - -import Conjure.Bug -import Conjure.Prelude -import Conjure.Language -import Conjure.Language.Domain.AddAttributes ( mkMin ) -import Conjure.Language.Expression.DomainSizeOf ( domainSizeOf ) -import Conjure.Language.NameResolution ( resolveX, resolveD ) - - -inferAttributes :: (MonadFail m, MonadUserError m, NameGen m) => Model -> m Model -inferAttributes = flip evalStateT [] . go where - go :: - MonadFail m => - MonadUserError m => - NameGen m => - MonadState [(Name, ReferenceTo)] m => - Model -> m Model - go m = do - forM_ (mStatements m) $ \ st -> - case st of - Declaration decl -> - case decl of - FindOrGiven forg nm dom -> do - dom' <- resolveD dom - modify ((nm, DeclNoRepr forg nm dom' NoRegion) :) - Letting nm x -> do - x' <- resolveX x - modify ((nm, Alias x') :) - LettingDomainDefnUnnamed nm x -> do - x' <- resolveX x - modify ((nm, Alias (Domain (DomainUnnamed nm x'))) :) -<<<<<<< HEAD - LettingDomainDefnEnum _ nms -> do - modify ( [ (nm, Alias (Constant (ConstantInt (Just nm) i))) -||||||| merged common ancestors - LettingDomainDefnEnum _ nms -> do - modify ( [ (nm, Alias (Constant (ConstantInt i))) -======= - LettingDomainDefnEnum (Name ename) nms -> do - modify ( [ (nm, Alias (Constant (ConstantInt (TagEnum ename) i))) ->>>>>>> taggedints - | (nm, i) <- zip nms [1..] - ] ++) - LettingDomainDefnEnum{} -> bug "inferAttributes" - GivenDomainDefnEnum{} -> return () -- ignoring - _ -> return () - transformBiM inferAttributesD m - -inferAttributesD :: - MonadFail m => - MonadUserError m => - NameGen m => - MonadState [(Name, ReferenceTo)] m => - Domain () Expression -> - m (Domain () Expression) -inferAttributesD (DomainPartition () (PartitionAttr partsNum1 partsSize1 isRegular1) innerDomain0) = do - innerDomain <- resolveD innerDomain0 - -- there cannot be more parts than there are members - let partsNum2 = - case domainSizeOf innerDomain of - Left _err -> partsNum1 - Right n -> case partsNum1 of - SizeAttr_None -> SizeAttr_MaxSize n - SizeAttr_Size x -> SizeAttr_Size x - SizeAttr_MinSize x -> SizeAttr_MinMaxSize x n - SizeAttr_MaxSize x -> SizeAttr_MaxSize (mkMin x n) - SizeAttr_MinMaxSize x y -> SizeAttr_MinMaxSize x (mkMin y n) - -- there cannot be more in a part than there are members - let partsSize2 = - case domainSizeOf innerDomain of - Left _err -> partsNum2 - Right n -> case partsSize1 of - SizeAttr_None -> SizeAttr_MaxSize n - SizeAttr_Size x -> SizeAttr_Size x - SizeAttr_MinSize x -> SizeAttr_MinMaxSize x n - SizeAttr_MaxSize x -> SizeAttr_MaxSize (mkMin x n) - SizeAttr_MinMaxSize x y -> SizeAttr_MinMaxSize x (mkMin y n) - return (DomainPartition () (PartitionAttr partsNum2 partsSize2 isRegular1) innerDomain0) -inferAttributesD d = return d - diff --git a/src/Conjure/Process/ModelStrengthening.hs.orig b/src/Conjure/Process/ModelStrengthening.hs.orig deleted file mode 100644 index 0304f8eeef..0000000000 --- a/src/Conjure/Process/ModelStrengthening.hs.orig +++ /dev/null @@ -1,909 +0,0 @@ -{- - - Module : Conjure.Process.ModelStrengthening - - Description : Strengthen a model using type- and domain-inference. - - Copyright : Billy Brown 2017 - - License : BSD3 - - Processing step that attempts to strengthen an Essence model, using methods described in the "Reformulating Essence Specifications for Robustness" paper. --} - -{-# LANGUAGE QuasiQuotes #-} - -module Conjure.Process.ModelStrengthening - ( - strengthenModel - ) where - -import Data.List ( find, union ) -import Data.Map.Strict ( Map ) -import qualified Data.Map.Strict as M ( (!?), empty, union ) - -import Conjure.Prelude -import Conjure.Language -import Conjure.Language.Domain.AddAttributes -import Conjure.Language.NameResolution ( resolveNames ) --- These two are needed together -import Conjure.Language.Expression.DomainSizeOf () -import Conjure.Language.DomainSizeOf ( domainSizeOf ) -import Conjure.Compute.DomainOf ( domainOf ) -import Conjure.UI.VarSymBreaking ( outputVarSymBreaking ) - --- aeson -import qualified Data.Aeson as JSON ( decodeStrict ) --- shelly -import Shelly ( run ) --- directory -import System.Directory ( removeFile ) --- text -import qualified Data.Text.Encoding as T ( encodeUtf8 ) --- uniplate zipper -import Data.Generics.Uniplate.Zipper ( Zipper, zipper, down, fromZipper, hole, replaceHole, right, up ) - -type ExpressionZ = Zipper Expression Expression -type FindVar = (Name, Domain () Expression) -type AttrPair = (AttrName, Maybe Expression) -type ToAddToRem = ([ExpressionZ], [ExpressionZ]) - --- | Strengthen a model using type- and domain-inference. -strengthenModel :: (MonadFail m, MonadIO m, MonadLog m, MonadUserError m) - => LogLevel -- ^ Log level to use. - -> Bool -- ^ Generate logs for rule applications. - -> Model -- ^ Model to strengthen. - -> m Model -- ^ Strengthened model. -strengthenModel logLevel logRuleSuccesses model = runNameGen model $ (resolveNames >=> core . fixRelationProj) model - where - core :: (MonadFail m, MonadIO m, MonadLog m, MonadUserError m, NameGen m) => Model -> m Model - core model1 = do - -- Apply attribute rules to each decision (find) variable - (model2, toAddToRem) <- foldM (\modelAndToKeep findAndCstrs@((n, d), _) -> - foldM (\(m1, tatr1) (rule, name) -> do - (attrs, tatr2) <- nested rule m1 findAndCstrs - let m2 = foldr (uncurry3 addAttrsToModel) m1 attrs - when (((not (null attrs) && m1 /= m2) || - (tatr2 /= mempty && toAddRem tatr2 tatr1 /= tatr1)) && - logRuleSuccesses) - (log logLevel $ name <+> if null attrs - then vcat $ map (pretty . hole) (fst tatr2) - else pretty n <+> ":" <+> pretty d) - return (m2, toAddRem tatr2 tatr1)) - modelAndToKeep [ (surjectiveIsTotalBijective, "function marked total and bijective") - , (totalInjectiveIsBijective, "function marked bijective") - , (definedForAllIsTotal, "function marked total") - , (diffArgResultIsInjective, "function marked injective") - , (varSize, "added or refined domain size attribute") - , (setSize, "added or refined set domain size attribute") - , (mSetSizeOccur, "added or refined multiset occurrence attribute") - , (mSetOccur, "added or refined multiset occurrence attribute") - , (partRegular, "marked partition regular") - , (numPartsToAttr, "added or refined partition domain numParts attribute") - , (partSizeToAttr, "added or refined partition domain partSize attribute") - , (funcRangeEqSet, "equated function range and set") - , (forAllIneqToIneqSum, "lifted arithmetic relation from two forAlls to a sum") - , (fasterIteration, "refined distinctness condition on forAll") - ]) - (model1, ([], [])) - (zip (collectFindVariables model1) - (repeat $ map zipper $ collectConstraints model1)) - - -- Apply constraint additions and removals - model3 <- resolveNames $ - addConstraints (fst toAddToRem) $ - remConstraints (snd toAddToRem) model2 - - -- Apply type change rules to each decision (find) variable - (model4, toAddToRem') <- foldM (\modelAndToKeep findAndCstrs@((n, d), _) -> - foldM (\(m1, tatr1) (rule, name) -> do - (dom, tatr2) <- rule m1 findAndCstrs - when ((dom /= d || toAddRem tatr2 tatr1 /= tatr1) && - logRuleSuccesses) - (log logLevel $ name <+> pretty n <+> ":" <+> pretty d) - return (updateDecl (n, dom) m1, toAddRem tatr2 tatr1)) - modelAndToKeep [ (mSetToSet, "multiset changed to set") - ]) - (model3, ([], [])) - (zip (collectFindVariables model3) - (repeat $ map zipper $ collectConstraints model3)) - - -- Apply constraint additions and removals - model5 <- resolveNames $ - addConstraints (fst toAddToRem') $ - remConstraints (snd toAddToRem') model4 - - -- Make another pass if the model was updated, but stop if it contains machine names - if model1 == model5 || any containsMachineName (collectConstraints model5) - then return model5 - else core model5 - -- Does an expression contain a reference with a machine name? - containsMachineName = any isMachineName . universe - isMachineName (Reference MachineName{} _) = True - isMachineName _ = False - --- | 'uncurry' for functions of three arguments and triples. -uncurry3 :: (a -> b -> c -> d) -> ((a, b, c) -> d) -uncurry3 f (x, y, z) = f x y z - --- | Collect decision (find) variables from a model, returning their name and domain. -collectFindVariables :: Model -> [FindVar] -collectFindVariables = mapMaybe collectFind . mStatements - where - collectFind (Declaration (FindOrGiven Find n d)) = Just (n, d) - collectFind _ = Nothing - --- | Collect the constraints in a model. -collectConstraints :: Model -> [Expression] -collectConstraints = concatMap getSuchThat . mStatements - where - getSuchThat (SuchThat cs) = cs - getSuchThat _ = [] - --- | Add constraints to a model. -addConstraints :: [ExpressionZ] -> Model -> Model -addConstraints [] m = m -addConstraints cs m@Model { mStatements = stmts } - = m { mStatements = addConstraints' stmts } - where - addConstraints' (SuchThat cs':ss) = SuchThat (cs' `union` map fromZipper cs) : ss - addConstraints' (s:ss) = s : addConstraints' ss - addConstraints' [] = [SuchThat (map fromZipper cs)] - --- | Remove a list of constraints from a model. -remConstraints :: [ExpressionZ] -> Model -> Model -remConstraints cs m@Model { mStatements = stmts } - = m { mStatements = filter (not . emptySuchThat) $ map remConstraints' stmts } - where - remConstraints' (SuchThat cs') = SuchThat $ filter (`notElem` map fromZipper cs) cs' - remConstraints' s = s - emptySuchThat (SuchThat []) = True - emptySuchThat _ = False - --- | Update the domain of a declaration in a model. -updateDecl :: FindVar -> Model -> Model -updateDecl (n, d) m@Model { mStatements = stmts } = m { mStatements = map updateDecl' stmts } - where - updateDecl' (Declaration (FindOrGiven Find n' _)) - | n == n' = Declaration (FindOrGiven Find n d) - updateDecl' decl = decl - --- | Try adding an attribute at a given depth of a variable's domain, in a model. -addAttrsToModel :: FindVar -> Int -> [AttrPair] -> Model -> Model -addAttrsToModel (n, _) depth attrs m - = let d = snd <$> find (\(n', _) -> n == n') (collectFindVariables m) - in case d >>= flip (addAttrsToDomain depth) attrs of - Just d' -> updateDecl (n, d') m - Nothing -> m - where - addAttrsToDomain :: (MonadFail m) => Int -> Domain () Expression -> [AttrPair] -> m (Domain () Expression) - addAttrsToDomain 0 dom = addAttributesToDomain dom . map mkAttr - addAttrsToDomain level (DomainSet r as inner) = addAttrsToDomain (level - 1) inner >=> (pure . DomainSet r as) - addAttrsToDomain level (DomainMSet r as inner) = addAttrsToDomain (level - 1) inner >=> (pure . DomainMSet r as) - addAttrsToDomain level (DomainMatrix index inner) = addAttrsToDomain (level - 1) inner >=> (pure . DomainMatrix index) - addAttrsToDomain level (DomainFunction r as from inner) = addAttrsToDomain (level - 1) inner >=> (pure . DomainFunction r as from) - addAttrsToDomain level (DomainPartition r as inner) = addAttrsToDomain (level - 1) inner >=> (pure . DomainPartition r as) - addAttrsToDomain _ _ = const (fail "[addAttrsToDomain] not a supported nested domain") - -- Special treatment for functions - mkAttr (attr, Just [essence| image(&f, &_) |]) = (attr, Just [essence| max(range(&f)) |]) - mkAttr (attr, Just [essence| image(&f, &_) - 1 |]) = (attr, Just [essence| max(range(&f)) - 1 |]) - mkAttr (attr, Just [essence| image(&f, &_) + 1 |]) = (attr, Just [essence| max(range(&f)) + 1 |]) - mkAttr (attr, e') = (attr, e') - --- | Does an expression directly reference a given name variable? -nameExpEq :: Name -> Expression -> Bool -nameExpEq n (Reference n' _) = n == n' -nameExpEq n [essence| image(&f, &x) |] = nameExpEq n f || nameExpEq n x -nameExpEq n [essence| &f(&x) |] = nameExpEq n f || nameExpEq n x -nameExpEq n [essence| defined(&f) |] = nameExpEq n f -nameExpEq n [essence| range(&f) |] = nameExpEq n f -nameExpEq n [essence| |&x| |] = nameExpEq n x -nameExpEq _ _ = False - --- | Does a reference refer to an abstract pattern? -refersTo :: Expression -> AbstractPattern -> Bool -refersTo (Reference n _) a = n `elem` namesFromAbstractPattern a -refersTo _ _ = False - --- | Get a single name from an abstract pattern. -nameFromAbstractPattern :: (MonadFail m) => AbstractPattern -> m Name -nameFromAbstractPattern a = case namesFromAbstractPattern a of - [n] -> pure n - [] -> fail "[nameFromAbstractPattern] no names in abstract pattern" - _ -> fail "[nameFromAbstractPattern] more than one name in abstract pattern" - --- | Get the list of names from an abstract pattern. -namesFromAbstractPattern :: AbstractPattern -> [Name] -namesFromAbstractPattern (Single n) = [n] -namesFromAbstractPattern (AbsPatTuple ns) = concatMap namesFromAbstractPattern ns -namesFromAbstractPattern (AbsPatMatrix ns) = concatMap namesFromAbstractPattern ns -namesFromAbstractPattern (AbsPatSet ns) = concatMap namesFromAbstractPattern ns -namesFromAbstractPattern _ = [] - --- | Get the list of names from a generator. -namesFromGenerator :: Generator -> [Name] -namesFromGenerator (GenDomainNoRepr a _) = namesFromAbstractPattern a -namesFromGenerator (GenDomainHasRepr n _) = [n] -namesFromGenerator (GenInExpr a _) = namesFromAbstractPattern a - --- | Find an expression at any depth of unconditional forAll expressions. -findInUncondForAll :: (Expression -> Bool) -> [ExpressionZ] -> [Expression] -findInUncondForAll p = map hole . findInUncondForAllZ p - --- | Find an expression at any depth of unconditional forAll expressions, --- returning a Zipper containing the expression's context. -findInUncondForAllZ :: (Expression -> Bool) -> [ExpressionZ] -> [ExpressionZ] -findInUncondForAllZ p = concatMap findInForAll - where - findInForAll z | p (hole z) = [z] - findInForAll z - = case hole z of - [essence| forAll &_ in defined(&_) . &_ |] - -> [] - [essence| forAll &x, &y : &_, &x' != &y' . &_ |] - | x' `refersTo` x && y' `refersTo` y - -> maybe [] findInForAll (down z >>= down) - [essence| forAll &x, &y in &_, &x' != &y' . &_ |] - | x' `refersTo` x && y' `refersTo` y - -> maybe [] findInForAll (down z >>= down) - Op (MkOpAnd (OpAnd (Comprehension _ gorcs))) - | all (not . isCondition) gorcs - -> maybe [] findInForAll (down z >>= down) - [essence| &_ /\ &_ |] - -> maybe [] findInForAll (down z) - `union` - maybe [] findInForAll (right z >>= down) - -- Only accept OR cases if both sides contain a match - [essence| &_ \/ &_ |] - -> let leftResult = maybe [] findInForAll (down z) - rightResult = maybe [] findInForAll (right z >>= down) - in if not (null leftResult) && not (null rightResult) - then leftResult `union` rightResult - else [] - _ -> [] - isCondition Condition{} = True - isCondition _ = False - --- | Lens function over a binary expression. -type BinExprLens m = Proxy m -> (Expression -> Expression -> Expression, - Expression -> m (Expression, Expression)) - --- | Get the lens for an expression and the values it matches. -matching :: Expression - -> [(BinExprLens Maybe, a)] - -> Maybe (a, (Expression, Expression)) -matching e ops = case mapMaybe (\(f1, f2) -> (,) f2 <$> match f1 e) ops of - [x] -> pure x - _ -> fail $ "no matching operator for expression: " <+> pretty e - --- | (In)equality operator lens pairs. -ineqOps :: [(BinExprLens Maybe, BinExprLens Identity)] -ineqOps = [ (opEq, opEq) - , (opLt, opLt) - , (opLeq, opLeq) - , (opGt, opGt) - , (opGeq, opGeq) - ] - --- | Opposites of (in)equality operator lens pairs. -oppIneqOps :: [(BinExprLens Maybe, BinExprLens Identity)] -oppIneqOps = [ (opEq, opEq) - , (opLt, opGt) - , (opLeq, opGeq) - , (opGt, opLt) - , (opGeq, opLeq) - ] - --- | (In)equality operator to size attribute modifier pairs. -ineqSizeAttrs :: [(BinExprLens Maybe, (AttrName, Expression -> Maybe Expression))] -ineqSizeAttrs = [ (opEq, ("size", Just)) - , (opLt, ("maxSize", Just . \x -> x - 1)) - , (opLeq, ("maxSize", Just)) - , (opGt, ("minSize", Just . (+ 1))) - , (opGeq, ("minSize", Just)) - ] - --- | (In)equality operator to size attribute modifier pairs. -ineqOccurAttrs :: [(BinExprLens Maybe, [(AttrName, Expression -> Maybe Expression)])] -ineqOccurAttrs = [ (opEq, [ ("minOccur", Just), ("maxOccur", Just) ]) - , (opLt, [ ("maxOccur", Just . \x -> x - 1) ]) - , (opLeq, [ ("maxOccur", Just) ]) - , (opGt, [ ("minOccur", Just . (+ 1)) ]) - , (opGeq, [ ("minOccur", Just) ]) - ] - --- | Unzip where the key is a 'Maybe' but the values should all be combined. -unzipMaybeK :: Monoid m => [(Maybe a, m)] -> ([a], m) -unzipMaybeK = foldr (\(mx, y) (xs, z) -> - case mx of - Just x -> (x:xs, y `mappend` z) - Nothing -> ( xs, y `mappend` z)) - ([], mempty) - --- | Does an expression contain a find variable? -isFind :: Expression -> Bool -isFind (Reference _ (Just (DeclNoRepr Find _ _ _))) = True -isFind (Reference _ (Just (DeclHasRepr Find _ _))) = True -isFind Reference{} = False -isFind Constant{} = False -isFind [essence| &f(&_) |] = isFind f -isFind [essence| image(&f, &_) |] = isFind f -isFind e = any isFind $ children e - --- | Add expressions to the ToAdd list. -toAdd :: [ExpressionZ] -> ToAddToRem -> ToAddToRem -toAdd e = first (`union` e) - --- | Add expressions to the ToRemove list. -toRem :: [ExpressionZ] -> ToAddToRem -> ToAddToRem -toRem e = second (`union` e) - --- | Combine two 'ToAddToRem' values. -toAddRem :: ToAddToRem -> ToAddToRem -> ToAddToRem -toAddRem (ta, tr) = toAdd ta . toRem tr - --- | Apply a rule to arbitrary levels of nested domains. -nested :: (MonadFail m, MonadLog m, NameGen m) - => (Model -> (FindVar, [ExpressionZ]) - -> m ([AttrPair], ToAddToRem)) - -> Model - -> (FindVar, [ExpressionZ]) - -> m ([(FindVar, Int, [AttrPair])], ToAddToRem) -nested rule m fc@(fv, cs) = do - -- Apply the rule at the top level - (attrs, toAddToRem) <- rule m fc - -- Look deeper into the domain if possible, for forAll constraints involving it - nestedResults <- fmap mconcat $ forM cs $ \c -> - case hole c of - [essence| forAll &x in &gen . &_ |] | nameExpEq (fst fv) gen -> - -- Create the new decision variable at this level - case (,) <$> nameFromAbstractPattern x - <*> (domainOf gen >>= innerDomainOf) of - Left _ -> return mempty - Right fv' -> do - -- Apply the rule from here - out <- nested rule m (fv', mapMaybe (down >=> down) [c]) - case out of - ([], _) -> return mempty - -- The rule was applied, so unwrap the variable and increase the depth - (vs, tatr') -> return ( [ (fv, d + 1, as) | (_, d, as) <- vs ] - , tatr') - _ -> return mempty - -- Do not add a modification if there are no attributes - let attrs' = if null attrs then [] else [(fv, 0, attrs)] - return $ mappend nestedResults (attrs', toAddToRem) - --- | If a function is surjective or bijective, and its domain and codomain --- are of equal size, then it is total and bijective. -surjectiveIsTotalBijective :: (MonadFail m, MonadLog m) - => Model - -> (FindVar, [ExpressionZ]) - -> m ([AttrPair], ToAddToRem) -surjectiveIsTotalBijective _ ((_, dom), _) - = case dom of - DomainFunction _ (FunctionAttr _ p j) from to - | (p == PartialityAttr_Partial && j == JectivityAttr_Bijective) || - j == JectivityAttr_Surjective -> do - (fromSize, toSize) <- functionDomainSizes from to - if fromSize == toSize - then return ([("total", Nothing), ("bijective", Nothing)], mempty) - else return mempty - _ -> return mempty - --- | Calculate the sizes of the domain and codomain of a function. -functionDomainSizes :: (MonadFail m) - => Domain () Expression -- ^ The function's domain. - -> Domain () Expression -- ^ The function's codomain. - -> m (Expression, Expression) -- ^ The sizes of the two. -functionDomainSizes from to = (,) <$> domainSizeOf from <*> domainSizeOf to - --- | If a function is total and injective, and its domain and codomain --- are of equal size, then it is bijective. -totalInjectiveIsBijective :: (MonadFail m, MonadLog m) - => Model - -> (FindVar, [ExpressionZ]) - -> m ([AttrPair], ToAddToRem) -totalInjectiveIsBijective _ ((_, dom), _) - = case dom of - DomainFunction _ (FunctionAttr _ PartialityAttr_Total JectivityAttr_Injective) from to -> do - (fromSize, toSize) <- functionDomainSizes from to - if fromSize == toSize - then return ([("bijective", Nothing)], mempty) - else return mempty - _ -> return mempty - --- | If a function is defined for all values in its domain, then it is total. -definedForAllIsTotal :: (MonadFail m, MonadLog m) - => Model - -> (FindVar, [ExpressionZ]) - -> m ([AttrPair], ToAddToRem) -definedForAllIsTotal _ ((n, dom), cs) - -- Is the function called with parameters generated from its domain in an expression? - = let definedIn from e = any (funcCalledWithGenParams from) (children e) - in case dom of - DomainFunction _ (FunctionAttr _ PartialityAttr_Partial _) from _ - | any (definedIn from) $ findInUncondForAll isOp cs - -> return ([("total", Nothing)], mempty) - _ -> return mempty - where - -- Look for operator expressions but leave comprehensions, ANDs and ORs up to findInUncondForAll - isOp (Op (MkOpAnd (OpAnd Comprehension{}))) = False - isOp [essence| &_ /\ &_ |] = False - isOp [essence| &_ \/ &_ |] = False - -- Disallow implications which may remove some cases - isOp [essence| &_ -> &_ |] = False - isOp Op{} = True - isOp _ = False - -- Determine whether a function is called with values generated from its domain - funcCalledWithGenParams d [essence| image(&f, ¶m) |] - = nameExpEq n f && case domainOf param of - Right d' -> d' == d - Left _ -> False - funcCalledWithGenParams _ _ = False - --- | If all distinct inputs to a function have distinct results, then it is injective. --- It will also be total if there are no conditions other than the disequality between --- the two inputs. -diffArgResultIsInjective :: (MonadFail m, MonadLog m) - => Model - -> (FindVar, [ExpressionZ]) - -> m ([AttrPair], ToAddToRem) -diffArgResultIsInjective _ ((n, DomainFunction _ (FunctionAttr _ _ ject) from _), cs) - | (ject == JectivityAttr_None || ject == JectivityAttr_Surjective) && - not (null $ findInUncondForAll isDistinctDisequality cs) - -- It is known that no inputs are ignored - = return ([("injective", Nothing), ("total", Nothing)], mempty) - where - -- Match a very specific pattern, which will also add the total attribute - isDistinctDisequality [essence| &i != &j -> image(&f, &i') != image(&f', &j') |] - = f == f' && i == i' && j == j' && - nameExpEq n f && -- the function is the one under consideration - domIsGen i && domIsGen j -- the values are generated from the function's domain - isDistinctDisequality _ = False - domIsGen x = case domainOf x of - Right dom -> dom == from - Left _ -> False -diffArgResultIsInjective _ _ = return mempty - --- | Set a size attribute on a variable. -varSize :: (MonadFail m, MonadLog m) - => Model - -> (FindVar, [ExpressionZ]) - -> m ([AttrPair], ToAddToRem) -varSize _ ((n, _), cs) = do - results <- forM cs $ \c -> - case matching (hole c) ineqSizeAttrs of - -- Do not allow find variables to be put in attributes - Just ((attr, f), ([essence| |&x| |], e)) | nameExpEq n x && not (isFind e) - -> pure (Just (attr, f e), ([], [c])) - _ -> pure (Nothing, mempty) - return $ unzipMaybeK results - --- | Set the minimum size of a set based on it being a superset of another. -setSize :: (MonadFail m, MonadLog m, NameGen m) - => Model - -> (FindVar, [ExpressionZ]) - -> m ([AttrPair], ToAddToRem) -setSize _ ((n, DomainSet{}), cs) - = fmap mconcat $ forM (findInUncondForAllZ isSubSupSet cs) $ \c -> - case hole c of - -- subset(Eq) - [essence| &l subset &r |] | nameExpEq n r -> return (minSize l (+ 1), mempty) - [essence| &l subset &r |] | nameExpEq n l -> return (maxSize r (\x -> x - 1), mempty) - [essence| &l subsetEq &r |] | nameExpEq n r -> return (minSize l id, mempty) - [essence| &l subsetEq &r |] | nameExpEq n l -> return (maxSize r id, mempty) - -- supset(Eq) - [essence| &l supset &r |] | nameExpEq n l -> return (minSize r (+ 1), mempty) - [essence| &l supset &r |] | nameExpEq n r -> return (maxSize l (\x -> x - 1), mempty) - [essence| &l supsetEq &r |] | nameExpEq n l -> return (minSize r id, mempty) - [essence| &l supsetEq &r |] | nameExpEq n r -> return (maxSize l id, mempty) - _ -> return mempty - where - isSubSupSet [essence| &_ subset &_ |] = True - isSubSupSet [essence| &_ subsetEq &_ |] = True - isSubSupSet [essence| &_ supset &_ |] = True - isSubSupSet [essence| &_ supsetEq &_ |] = True - isSubSupSet _ = False - minSize [essence| defined(&g) |] f - = case domainOf g of - Right (DomainFunction _ (FunctionAttr _ PartialityAttr_Total _) from _) -> - case domainSizeOf from of - Just s -> [("minSize", Just (f s))] - Nothing -> mempty - _ -> mempty - minSize [essence| range(&g) |] f - = case domainOf g of - Right (DomainFunction _ (FunctionAttr _ PartialityAttr_Total j) from to) - | j == JectivityAttr_Bijective || j == JectivityAttr_Surjective -> - case domainSizeOf to of - Just s -> [("minSize", Just (f s))] - Nothing -> mempty - | j == JectivityAttr_Injective -> - case domainSizeOf from of - Just s -> [("minSize", Just (f s))] - Nothing -> mempty - | otherwise -> [("minSize", Just (f 1))] - _ -> mempty - minSize e f = case domainOf e of - Right (DomainSet _ (SetAttr (SizeAttr_Size mn)) _) -> - [("minSize", Just (f mn))] - Right (DomainSet _ (SetAttr (SizeAttr_MinSize mn)) _) -> - [("minSize", Just (f mn))] - Right (DomainSet _ (SetAttr (SizeAttr_MinMaxSize mn _)) _) -> - [("minSize", Just (f mn))] - _ -> mempty - -- TODO: extend for Matrix, MSet, Partition and Sequence - maxSize [essence| defined(&g) |] f - = case domainOf g >>= innerDomainOf of - Right (DomainTuple [d, _]) -> - case domainSizeOf d of - Just s -> [("maxSize", Just (f s))] - Nothing -> mempty - _ -> mempty - maxSize [essence| range(&g) |] f - = case domainOf g >>= innerDomainOf of - Right (DomainTuple [_, d]) -> - case domainSizeOf d of - Just s -> [("maxSize", Just (f s))] - Nothing -> mempty - _ -> mempty - maxSize e f = case domainOf e of - Right (DomainSet _ (SetAttr (SizeAttr_Size mx)) _) -> - [("maxSize", Just (f mx))] - Right (DomainSet _ (SetAttr (SizeAttr_MaxSize mx)) _) -> - [("maxSize", Just (f mx))] - Right (DomainSet _ (SetAttr (SizeAttr_MinMaxSize _ mx)) _) -> - [("maxSize", Just (f mx))] - Right d@(DomainSet _ (SetAttr SizeAttr_None) _) -> - case domainSizeOf d of - Just mx -> [("maxSize", Just (f mx))] - Nothing -> mempty - _ -> mempty - -- TODO: extend for Matrix, MSet, Partition and Sequence -setSize _ _ = return mempty - --- | The maxSize, and minOccur attributes of an mset affect its maxOccur and minSize attributes. -mSetSizeOccur :: (MonadFail m, MonadLog m) - => Model - -> (FindVar, [ExpressionZ]) - -> m ([AttrPair], ToAddToRem) -mSetSizeOccur _ ((_, d), _) - = case d of - -- Ordering is important here, as there is a rule that applies - -- to maxSize and minOccur, but none that applies to minSize - -- and maxOccur. size uses the maxSize rule, but can ignore a - -- minOccur because it cannot have its minSize changed. - -- size -> maxOccur - DomainMSet _ (MSetAttr (SizeAttr_Size mx) _) _ - -> return ([("maxOccur", Just mx)], mempty) - -- minOccur -> minSize - DomainMSet _ (MSetAttr _ (OccurAttr_MinOccur mn)) _ - -> return ([("minSize", Just mn)], mempty) - DomainMSet _ (MSetAttr _ (OccurAttr_MinMaxOccur mn _)) _ - -> return ([("minSize", Just mn)], mempty) - -- maxSize -> maxOccur - DomainMSet _ (MSetAttr (SizeAttr_MaxSize mx) _) _ - -> return ([("maxOccur", Just mx)], mempty) - DomainMSet _ (MSetAttr (SizeAttr_MinMaxSize _ mx) _) _ - -> return ([("maxOccur", Just mx)], mempty) - _ -> return mempty - --- | Infer multiset occurrence attributes from constraints. -mSetOccur :: (MonadFail m, MonadLog m) - => Model - -> (FindVar, [ExpressionZ]) - -> m ([AttrPair], ToAddToRem) -mSetOccur _ ((n, DomainMSet _ _ d), cs) - = return $ mconcat $ flip mapMaybe (findInUncondForAllZ (not . null . isFreq) cs) $ \e -> - case isFreq (hole e) of - [] -> Nothing - -- Only remove constraints if they are all used up. - -- Because freq(a, b) = c adds two attributes, removing constraints - -- in an AND expression cannot work, in the case of freq(a, b) = c /\ e - -- because there are two attributes and two terms, but term e may not - -- be removed. - as -> let tattr = case hole e of - AbstractLiteral AbsLitMatrix{} -> mempty - _ -> ([], [e]) - in Just (as, tattr) - where - isFreq :: Expression -> [AttrPair] - isFreq (AbstractLiteral (AbsLitMatrix _ es)) = concatMap isFreq es - isFreq e = case matching e oppIneqOps of - Just (_, ([essence| freq(&x, &v) |], e')) - | valid x v e' -> case matching e ineqOccurAttrs of - Just (as, _) -> map (second ($ e')) as - Nothing -> [] - -- Flip the terms - Just (oper, (l, r@[essence| freq(&x, &v) |])) - | valid x v l -> isFreq $ make oper r l - _ -> [] - -- Make sure that the expression's components are valid - valid :: Expression -> Expression -> Expression -> Bool - valid x v e = nameExpEq n x && isGen v && isConst e - -- Make sure that the value is generated from the mset's domain - isGen (Reference _ (Just (InComprehension (GenDomainNoRepr _ d')))) = d == d' - isGen (Reference _ (Just (DeclNoRepr Quantified _ d' _))) = d == d' - isGen (Reference _ (Just (InComprehension (GenInExpr _ e )))) = nameExpEq n e - isGen _ = False - -- Make sure that the mset is being equated to a constant - isConst (Reference _ (Just (DeclNoRepr Given _ _ _))) = True - isConst (Constant ConstantInt{}) = True - isConst _ = False -mSetOccur _ _ = return mempty - --- | Mark a partition regular if its numParts * partSize = |domain|, or if there --- is a constraint on its parts constraining them to be of equal size. -partRegular :: (MonadFail m, MonadLog m) - => Model - -> (FindVar, [ExpressionZ]) - -> m ([AttrPair], ToAddToRem) -partRegular _ ((n, d@DomainPartition{}), cs) - = if inferFromDomain /= mempty - then return inferFromDomain - else do - attrs <- forM cs $ \c -> - case hole c of - [essence| forAll &x in parts(&p) . forAll &y in parts(&p') . &e |] - | nameExpEq n p && p == p' - -> case e of - [essence| |&x'| = |&y'| |] | x' `refersTo` x && y' `refersTo` y - -> pure (Just ("regular", Nothing), ([], [c])) - [essence| &x'' != &y'' -> |&x'| = |&y'| |] - | x' `refersTo` x && y' `refersTo` y && - ((x' == x'' && y' == y'') || (x' == y'' && y' == x'')) - -> pure (Just ("regular", Nothing), ([], [c])) - _ -> pure (Nothing, mempty) - _ -> pure (Nothing, mempty) - return $ unzipMaybeK attrs - where - inferFromDomain :: ([AttrPair], ToAddToRem) - inferFromDomain = case d of - DomainPartition _ PartitionAttr { partsNum = SizeAttr_Size pNum@Constant{} - , partsSize = SizeAttr_Size pSize@Constant{} - } dom - | Just n1 <- domainSizeOf dom >>= e2c - , Just pNum' <- e2c pNum - , Just pSize' <- e2c pSize - , Just n2 <- evaluateOp $ MkOpProduct $ OpProduct $ fromList [ pNum', pSize' ] - , n1 == n2 - -> ([("regular", Nothing)], mempty) - _ -> mempty -partRegular _ _ = return mempty - --- | Convert constraints acting on the number of parts in a partition to an attribute. -numPartsToAttr :: (MonadFail m, MonadLog m) - => Model - -> (FindVar, [ExpressionZ]) - -> m ([AttrPair], ToAddToRem) -numPartsToAttr _ ((n, DomainPartition{}), cs) = do - attrs <- forM cs $ \c -> - case matching (hole c) ineqSizeAttrs of - -- Do not allow find variables to be put in attributes - Just ((attr, f), ([essence| |parts(&x)| |], e)) | nameExpEq n x && not (isFind e) - -> pure (Just (changeAttr attr, f e), ([], [c])) - _ -> pure (Nothing, mempty) - return $ unzipMaybeK attrs - where - -- Change a size attribute name to a numParts attribute name - changeAttr "size" = "numParts" - changeAttr "minSize" = "minNumParts" - changeAttr "maxSize" = "maxNumParts" - changeAttr a = a -numPartsToAttr _ _ = return mempty - --- | Convert constraints acting on the sizes of parts in a partition to an attribute. -partSizeToAttr :: (MonadFail m, MonadLog m) - => Model - -> (FindVar, [ExpressionZ]) - -> m ([AttrPair], ToAddToRem) -partSizeToAttr _ ((n, DomainPartition{}), cs) = do - attrs <- forM cs $ \c -> - case hole c of - [essence| forAll &x in parts(&p) . |&x'| = &e |] | valid p x x' e - -> pure (Just ("partSize", Just e), ([], [c])) - [essence| forAll &x in parts(&p) . |&x'| < &e |] | valid p x x' e - -> pure (Just ("maxPartSize", Just (e - 1)), ([], [c])) - [essence| forAll &x in parts(&p) . |&x'| <= &e |] | valid p x x' e - -> pure (Just ("maxPartSize", Just e), ([], [c])) - [essence| forAll &x in parts(&p) . |&x'| > &e |] | valid p x x' e - -> pure (Just ("minPartSize", Just (e + 1)), ([], [c])) - [essence| forAll &x in parts(&p) . |&x'| >= &e |] | valid p x x' e - -> pure (Just ("minPartSize", Just e), ([], [c])) - _ -> pure (Nothing, mempty) - return $ unzipMaybeK attrs - where - -- Make sure that the expression's components are valid - valid :: Expression -> AbstractPattern -> Expression -> Expression -> Bool - valid p x v e = nameExpEq n p && v `refersTo` x && not (isFind e) -partSizeToAttr _ _ = return mempty - --- | Equate the range of a function to a set of the former is a subset of the latter --- and all values in the set are results of the function. -funcRangeEqSet :: (MonadFail m, MonadLog m) - => Model - -> (FindVar, [ExpressionZ]) - -> m ([AttrPair], ToAddToRem) -funcRangeEqSet _ ((n, DomainSet{}), cs) - -- Get references to the set and the function whose range it is a superset of - = let funcSubsets = mapMaybe funcSubsetEqOf $ - findInUncondForAllZ (isJust . funcSubsetEqOf . zipper) cs - -- Reduce the functions to those whose values are equated to the values in the set - fsToUse = flip filter funcSubsets $ \(_, f) -> - not $ null $ findInUncondForAll (funcValEqSetVal (hole f)) cs - -- Transform the functions into new constraints, preserving structure - csToAdd = flip mapMaybe fsToUse $ \(s, f) -> - let f' = hole f - in replaceHole [essence| range(&f') = &s |] <$> - (up f >>= up) - in return ([], (csToAdd, [])) - where - -- Get the function whose range is a subsetEq of the set - funcSubsetEqOf z = case hole z of - [essence| range(&_) subsetEq &s |] | nameExpEq n s - -> (,) s <$> (down z >>= down) - [essence| &s supsetEq range(&_) |] | nameExpEq n s - -> (,) s <$> (down z >>= right >>= down) - _ -> Nothing - -- Are the values of the function equal to the values of the set? - funcValEqSetVal f [essence| forAll &x in &s . image(&f', &_) = &x' |] - = nameExpEq n s && f == f' && x' `refersTo` x - funcValEqSetVal f [essence| forAll &x in &s . &x' = image(&f', &_) |] - = nameExpEq n s && f == f' && x' `refersTo` x - funcValEqSetVal _ _ = False -funcRangeEqSet _ _ = return mempty - - --- | An (in)equality in a forAll implies that the (in)equality also applies to --- the sums of both terms. -forAllIneqToIneqSum :: (MonadFail m, MonadLog m, NameGen m) - => Model - -> (FindVar, [ExpressionZ]) - -> m ([AttrPair], ToAddToRem) -forAllIneqToIneqSum _ (_, cs) = do - let matches = mapMaybe matchParts $ findInUncondForAllZ (isJust . matchParts . zipper) cs - csToAdd <- mapMaybe mkConstraint <$> filterM partsAreNumeric matches - return ([], (csToAdd, [])) - where - -- Match and extract the desired parts of the expression - matchParts :: ExpressionZ -> Maybe (Generator, Maybe ExpressionZ, Expression, Expression) - matchParts z = case hole z of - Op (MkOpAnd (OpAnd (Comprehension e [Generator g]))) - -> matching e ineqOps >>= - uncurry (matchComponents g z) . snd - _ -> Nothing - -- Match the components of the expression of interest - matchComponents :: Generator -> ExpressionZ -> Expression -> Expression - -> Maybe (Generator, Maybe ExpressionZ, Expression, Expression) - matchComponents g z e1 e2 - | refInExpr (namesFromGenerator g) e1 && refInExpr (namesFromGenerator g) e2 - = Just (g, down z >>= down, e1, e2) - matchComponents _ _ _ _ = Nothing - -- Is a name referred to in an expression? - refInExpr names = any (\e -> any (`nameExpEq` e) names) . universe - -- Are the parts of the matched expression numeric? - partsAreNumeric (_, _, e1, e2) = (&&) <$> domainIsNumeric e1 <*> domainIsNumeric e2 - domainIsNumeric e = case domainOf e of - Right DomainInt{} -> return True -<<<<<<< HEAD - Right (DomainAny _ (TypeInt _)) -> return True - _ -> return False -||||||| merged common ancestors - Right (DomainAny _ TypeInt) -> return True - _ -> return False -======= - Right (DomainAny _ (TypeInt _)) -> return True - _ -> return False ->>>>>>> taggedints - -- Replace the forAll with the (in)equality between sums - mkConstraint :: (Generator, Maybe ExpressionZ, Expression, Expression) -> Maybe ExpressionZ - mkConstraint (gen, Just z, _, _) - -- Use matching with ineqOps to get the operation that is used on the two expressions - = case matching (hole z) ineqOps of - Just (f, (e1, e2)) - -> let mkSumOf = Op . MkOpSum . OpSum . flip Comprehension [Generator gen] - -- Two steps to get out of the forAll, and replace it with the constraint - in replaceHole (make f (mkSumOf e1) (mkSumOf e2)) <$> (up z >>= up) - _ -> Nothing - mkConstraint _ = Nothing - --- | Iterate slightly faster over a domain if generating two distinct variables. -fasterIteration :: (MonadFail m, MonadIO m, MonadLog m) - => Model - -> (FindVar, [ExpressionZ]) - -> m ([AttrPair], ToAddToRem) -fasterIteration m (_, cs) = do - let iters = findInUncondForAllZ (isJust . doubleDistinctIter . zipper) cs - fmap ((,) [] . mconcat) $ forM iters $ \z -> do - -- Find the equivalent variables - [equivs] <- sequence [ findEquivVars (hole z) ] - -- Only apply to equivalent variables and make the new constraint - case doubleDistinctIter z >>= onlyEquivalent equivs >>= changeIterator of - Nothing -> return mempty - -- Remove the old constraint - Just z' -> return ([z'], [z]) - where - -- Match the elemenents of interest in the constraint - doubleDistinctIter z - = case hole z of - Op (MkOpAnd (OpAnd (Comprehension _ [ Generator (GenInExpr x v) - , Generator (GenInExpr y v') - , Condition [essence| &x' != &y' |] - ]))) - | v == v' && x' `refersTo` x && y' `refersTo` y - -> Just ((x, x'), (y, y'), v, down z >>= down) - Op (MkOpAnd (OpAnd (Comprehension _ [ Generator (GenDomainNoRepr x d) - , Generator (GenDomainNoRepr y d') - , Condition [essence| &x' != &y' |] - ]))) - | d == d' && x' `refersTo` x && y' `refersTo` y - -> Just ((x, x'), (y, y'), Domain d, down z >>= down) - _ -> Nothing - -- Find which variables are equivalent in an expression - findEquivVars :: (MonadIO m) => Expression -> m (Map Text Text) - findEquivVars e = case e of - [essence| forAll &_, &_ : &_, &_ . &e' |] -> liftIO $ findSyms e' - [essence| forAll &_, &_ in &_, &_ . &e' |] -> liftIO $ findSyms e' - _ -> return M.empty - -- Find the symmetries in an expression - findSyms :: Expression -> IO (Map Text Text) - findSyms e = do - let m' = addConstraints [zipper e] $ remConstraints cs m - let filename = ".tmp-variable-strengthening.json" - outputVarSymBreaking filename m' - symmetries <- ferret $ stringToText filename - removeFile filename - case (JSON.decodeStrict $ T.encodeUtf8 symmetries) :: Maybe [Map Text Text] of - Nothing -> return M.empty - Just ss -> return $ foldr M.union M.empty ss - -- Only perform the modification if the variables are equivalent in the expression - onlyEquivalent es v@((x, _), (y, _), _, _) - = case namesFromAbstractPattern x of - [Name nx] -> case namesFromAbstractPattern y of - [Name ny] -> case es M.!? nx of - Just ny' | ny == ny' -> Just v - _ -> Nothing - _ -> Nothing - _ -> Nothing - -- Change the iterator to use the new, faster notation - changeIterator ((x, x'), (y, y'), v, Just z) - = let e = hole z - in case v of - r@Reference{} - -> case domainOf r of - Left _ -> Nothing - Right DomainSet{} - -> replaceHole [essence| forAll {&x, &y} subsetEq &v . &e |] <$> - (up z >>= up) - Right _ - -> replaceHole [essence| forAll &x, &y in &v, &y' > &x' . &e |] <$> - (up z >>= up) - Op MkOpDefined{} - -> replaceHole [essence| forAll &x, &y in &v, &y' > &x' . &e |] <$> - (up z >>= up) - Domain d - -> replaceHole [essence| forAll &x, &y : &d, &y' > &x' . &e |] <$> - (up z >>= up) - _ -> Nothing - changeIterator _ = Nothing - --- | Call ferret's symmetry detection on a JSON file -ferret :: Text -> IO Text -ferret path = sh (run "symmetry_detect" [ "--json", path ]) `catch` - (\(_ :: SomeException) -> return "{}") - --- | Change the type of a multiset with `maxOccur 1` to set. -mSetToSet :: (MonadFail m, MonadLog m) - => Model - -> (FindVar, [ExpressionZ]) - -> m (Domain () Expression, ToAddToRem) -mSetToSet _ ((n, DomainMSet r (MSetAttr sa oa) d), cs) | maxOccur1 oa = do - let dom' = DomainSet r (SetAttr sa) d - let torem = filter (any (nameExpEq n) . universe . hole) cs - let toadd = map (zipper . transform (\e -> if nameExpEq n e - then [essence| toMSet(&e) |] - else e) - . hole) - cs - return (dom', (toadd, torem)) - where - maxOccur1 (OccurAttr_MaxOccur 1) = True - maxOccur1 (OccurAttr_MinMaxOccur _ 1) = True - maxOccur1 _ = False -mSetToSet _ ((_, dom), _) = return (dom, mempty) diff --git a/src/Conjure/Process/Unnameds.hs.orig b/src/Conjure/Process/Unnameds.hs.orig deleted file mode 100644 index 0b1e17002e..0000000000 --- a/src/Conjure/Process/Unnameds.hs.orig +++ /dev/null @@ -1,32 +0,0 @@ -{-# LANGUAGE TupleSections #-} - -module Conjure.Process.Unnameds - ( removeUnnamedsFromModel - ) where - -import Conjure.Prelude -import Conjure.Language.Definition -import Conjure.Language.Domain -import Conjure.Language.Type - - --- | The argument is a model before nameResolution. --- Only intended to work on problem specifications. --- Replaces unnamed types with integers. -removeUnnamedsFromModel :: MonadFail m => Model -> m Model -removeUnnamedsFromModel model = do - statements' <- forM (mStatements model) $ \ st -> - case st of -<<<<<<< HEAD - Declaration (LettingDomainDefnUnnamed name size) -> do - let outDomain = mkDomainIntBNamed name 1 size -||||||| merged common ancestors - Declaration (LettingDomainDefnUnnamed name size) -> do - let outDomain = mkDomainIntB 1 size -======= - Declaration (LettingDomainDefnUnnamed name@(Name nameText) size) -> do - let outDomain = mkDomainIntBTagged (TagUnnamed nameText) 1 size ->>>>>>> taggedints - return $ Declaration $ Letting name $ Domain outDomain - _ -> return st - return model { mStatements = statements' } diff --git a/src/Conjure/Representations/Function/Function1D.hs.orig b/src/Conjure/Representations/Function/Function1D.hs.orig deleted file mode 100644 index d9b69a0509..0000000000 --- a/src/Conjure/Representations/Function/Function1D.hs.orig +++ /dev/null @@ -1,188 +0,0 @@ -{-# LANGUAGE QuasiQuotes #-} - -module Conjure.Representations.Function.Function1D - ( function1D - , domainValues - ) where - --- conjure -import Conjure.Prelude -import Conjure.Language.Definition -import Conjure.Language.Domain -import Conjure.Language.Type -import Conjure.Language.TypeOf -import Conjure.Language.Constant -import Conjure.Language.DomainSizeOf -import Conjure.Language.Expression.DomainSizeOf () -import Conjure.Language.TH -import Conjure.Language.Pretty -import Conjure.Representations.Internal -import Conjure.Representations.Common - - -function1D :: forall m . (MonadFail m, NameGen m) => Representation m -function1D = Representation chck downD structuralCons downC up - - where - - chck :: TypeOf_ReprCheck m - chck f (DomainFunction _ - attrs@(FunctionAttr _ PartialityAttr_Total _) - innerDomainFr - innerDomainTo) | domainCanIndexMatrix innerDomainFr = do - innerDomainFr' <- f innerDomainFr - innerDomainTo' <- f innerDomainTo - return [ DomainFunction Function_1D attrs fr to - | fr <- innerDomainFr' - , to <- innerDomainTo' - ] - chck _ _ = return [] - - outName :: Domain HasRepresentation x -> Name -> Name - outName = mkOutName Nothing - - downD :: TypeOf_DownD m - downD (name, domain@(DomainFunction Function_1D - (FunctionAttr _ PartialityAttr_Total _) - innerDomainFr - innerDomainTo)) | domainCanIndexMatrix innerDomainFr = return $ Just - [ ( outName domain name - , DomainMatrix - (forgetRepr innerDomainFr) - innerDomainTo - ) ] - downD _ = na "{downD} Function1D" - - structuralCons :: TypeOf_Structural m - structuralCons f downX1 - (DomainFunction Function_1D - (FunctionAttr sizeAttr PartialityAttr_Total jectivityAttr) - innerDomainFr - innerDomainTo) | domainCanIndexMatrix innerDomainFr = do - - let injectiveCons m = do - tyTo <- typeOf innerDomainTo - let canAllDiff = case tyTo of - TypeBool{} -> True - TypeInt{} -> True - TypeEnum{} -> True - _ -> False - if canAllDiff - then - return $ return $ -- list - [essence| allDiff(&m) |] - else do - (iPat, i) <- quantifiedVar - (jPat, j) <- quantifiedVar - return $ return $ -- list - [essence| - forAll &iPat, &jPat : &innerDomainFr . - &i .< &j -> &m[&i] != &m[&j] - |] - - let surjectiveCons m = do - (iPat, i) <- quantifiedVar - (jPat, j) <- quantifiedVar - return $ return $ -- list - [essence| - forAll &iPat : &innerDomainTo . - exists &jPat : &innerDomainFr . - &m[&j] = &i - |] - let jectivityCons m = case jectivityAttr of - JectivityAttr_None -> return [] - JectivityAttr_Injective -> injectiveCons m - JectivityAttr_Surjective -> surjectiveCons m - JectivityAttr_Bijective -> (++) <$> injectiveCons m <*> surjectiveCons m - - cardinality <- domainSizeOf innerDomainFr - - let innerStructuralCons m = do - (iPat, i) <- quantifiedVarOverDomain (forgetRepr innerDomainFr) - let activeZone b = [essence| forAll &iPat : &innerDomainFr . &b |] - - -- preparing structural constraints for the inner guys - innerStructuralConsGen <- f innerDomainTo - - let inLoop = [essence| &m[&i] |] - outs <- innerStructuralConsGen inLoop - return (map activeZone outs) - - return $ \ func -> do - refs <- downX1 func - case refs of - [m] -> - concat <$> sequence - [ jectivityCons m - , return (mkSizeCons sizeAttr cardinality) - , innerStructuralCons m - ] - _ -> na "{structuralCons} Function1D" - - structuralCons _ _ _ = na "{structuralCons} Function1D" - - downC :: TypeOf_DownC m - downC ( name - , domain@(DomainFunction Function_1D - (FunctionAttr _ PartialityAttr_Total _) - innerDomainFr - innerDomainTo) - , ConstantAbstract (AbsLitFunction vals) - ) | domainCanIndexMatrix innerDomainFr = do - froms <- domainValues innerDomainFr - valsOut <- sequence - [ val - | fr <- froms - , let val = case lookup fr vals of - Nothing -> fail $ vcat [ "No value for " <+> pretty fr - , "In:" <+> pretty (AbsLitFunction vals) - ] - Just v -> return v - ] - return $ Just - [ ( outName domain name - , DomainMatrix (forgetRepr innerDomainFr) innerDomainTo - , ConstantAbstract $ AbsLitMatrix (forgetRepr innerDomainFr) valsOut - ) ] - downC _ = na "{downC} Function1D" - - up :: TypeOf_Up m - up ctxt (name, domain@(DomainFunction Function_1D - (FunctionAttr _ PartialityAttr_Total _) - innerDomainFr _)) = - case lookup (outName domain name) ctxt of - Nothing -> fail $ vcat $ - [ "(in Function1D up)" - , "No value for:" <+> pretty (outName domain name) - , "When working on:" <+> pretty name - , "With domain:" <+> pretty domain - ] ++ - ("Bindings in context:" : prettyContext ctxt) - Just constant -> - case viewConstantMatrix constant of - Just (_, vals) -> do - froms <- domainValues innerDomainFr - return ( name - , ConstantAbstract $ AbsLitFunction $ zip froms vals - ) - _ -> fail $ vcat - [ "Expecting a matrix literal for:" <+> pretty (outName domain name) - , "But got:" <+> pretty constant - , "When working on:" <+> pretty name - , "With domain:" <+> pretty domain - ] - up _ _ = na "{up} Function1D" - - -domainValues :: (MonadFail m, Pretty r) => Domain r Constant -> m [Constant] -domainValues dom = - case dom of - DomainBool -> return [ConstantBool False, ConstantBool True] -<<<<<<< HEAD - DomainInt name rs -> map (ConstantInt name) <$> valuesInIntDomain rs -||||||| merged common ancestors - DomainInt rs -> map ConstantInt <$> valuesInIntDomain rs -======= - DomainInt t rs -> map (ConstantInt t) <$> valuesInIntDomain rs ->>>>>>> taggedints - _ -> fail ("domainValues, not supported:" <+> pretty dom) diff --git a/src/Conjure/Representations/MSet/ExplicitWithFlags.hs.orig b/src/Conjure/Representations/MSet/ExplicitWithFlags.hs.orig deleted file mode 100644 index 965fe063a2..0000000000 --- a/src/Conjure/Representations/MSet/ExplicitWithFlags.hs.orig +++ /dev/null @@ -1,224 +0,0 @@ -{-# LANGUAGE QuasiQuotes #-} - -module Conjure.Representations.MSet.ExplicitWithFlags ( msetExplicitWithFlags ) where - --- conjure -import Conjure.Prelude -import Conjure.Language -import Conjure.Language.DomainSizeOf -import Conjure.Language.Expression.DomainSizeOf () -import Conjure.Language.ZeroVal ( zeroVal, EnumerateDomain ) -import Conjure.Representations.Internal -import Conjure.Representations.Common - - -msetExplicitWithFlags :: forall m . (MonadFail m, NameGen m, EnumerateDomain m) => Representation m -msetExplicitWithFlags = Representation chck downD structuralCons downC up - - where - - chck :: TypeOf_ReprCheck m - chck f (DomainMSet _ attrs innerDomain) = - map (DomainMSet MSet_ExplicitWithFlags attrs) <$> f innerDomain - chck _ _ = return [] - - nameFlag = mkOutName (Just "Flags") - nameValues = mkOutName (Just "Values") - - getMaxSize attrs innerDomain = case attrs of - MSetAttr (SizeAttr_Size x) _ -> return x - MSetAttr (SizeAttr_MaxSize x) _ -> return x - MSetAttr (SizeAttr_MinMaxSize _ x) _ -> return x - MSetAttr _ (OccurAttr_MaxOccur x) -> do y <- domainSizeOf innerDomain ; return (x * y) - MSetAttr _ (OccurAttr_MinMaxOccur _ x) -> do y <- domainSizeOf innerDomain ; return (x * y) - _ -> fail ("getMaxSize, mset not supported. attributes:" <+> pretty attrs) - - getMinOccur attrs = case attrs of - MSetAttr _ (OccurAttr_MinOccur x) -> Just x - MSetAttr _ (OccurAttr_MinMaxOccur x _) -> Just x - _ -> Nothing - - getMaxOccur attrs = case attrs of - MSetAttr _ (OccurAttr_MaxOccur x) -> return x - MSetAttr _ (OccurAttr_MinMaxOccur _ x) -> return x - MSetAttr (SizeAttr_Size x) _ -> return x - MSetAttr (SizeAttr_MaxSize x) _ -> return x - MSetAttr (SizeAttr_MinMaxSize _ x) _ -> return x - _ -> fail ("getMaxOccur, mset not supported. attributes:" <+> pretty attrs) - - downD :: TypeOf_DownD m - downD (name, domain@(DomainMSet _ attrs innerDomain)) = do - maxSize <- getMaxSize attrs innerDomain - maxOccur <- getMaxOccur attrs - let indexDomain = mkDomainIntB 1 maxSize - let flagDomain = defRepr $ mkDomainIntB 0 maxOccur - return $ Just - [ ( nameFlag domain name - , DomainMatrix indexDomain flagDomain - ) - , ( nameValues domain name - , DomainMatrix indexDomain innerDomain - ) - ] - downD _ = na "{downD} ExplicitVarSizeWithFlags" - - structuralCons :: TypeOf_Structural m - structuralCons f downX1 (DomainMSet MSet_ExplicitWithFlags attrs@(MSetAttr sizeAttrs _) innerDomain) = do - maxSize <- getMaxSize attrs innerDomain - let - orderingWhenFlagged flags values = do - (iPat, i) <- quantifiedVar - return $ return $ -- list - [essence| - forAll &iPat : int(1..&maxSize-1) . &flags[&i+1] > 0 -> &values[&i] .< &values[&i+1] - |] - - dontCareWhenNotFlagged flags values = do - (iPat, i) <- quantifiedVar - return $ return $ -- list - [essence| - forAll &iPat : int(1..&maxSize) . &flags[&i] = 0 -> dontCare(&values[&i]) - |] - - flagsToTheLeft flags = do - (iPat, i) <- quantifiedVar - return $ return $ -- list - [essence| - forAll &iPat : int(1..&maxSize-1) . &flags[&i+1] > 0 -> &flags[&i] > 0 - |] - - cardinality flags = do - (iPat, i) <- quantifiedVar - return [essence| sum &iPat : int(1..&maxSize) . &flags[&i] |] - - -- maxOccur is enforced by the domain of the flag - minOccurrenceCons flags = do - (iPat, i) <- quantifiedVar - return - [ [essence| forAll &iPat : int(1..&maxSize) . &flags[&i] = 0 \/ &flags[&i] >= &minOccur |] - | Just minOccur <- [getMinOccur attrs] - ] - - innerStructuralCons flags values = do - (iPat, i) <- quantifiedVarOverDomain [essenceDomain| int(1..&maxSize) |] - let activeZone b = [essence| forAll &iPat : int(1..&maxSize) . &flags[&i] > 0 -> &b |] - - -- preparing structural constraints for the inner guys - innerStructuralConsGen <- f innerDomain - - let inLoop = [essence| &values[&i] |] - outs <- innerStructuralConsGen inLoop - return (map activeZone outs) - - return $ \ mset -> do - refs <- downX1 mset - case refs of - [flags, values] -> - concat <$> sequence - [ orderingWhenFlagged flags values - , dontCareWhenNotFlagged flags values - , flagsToTheLeft flags - , minOccurrenceCons flags - , mkSizeCons sizeAttrs <$> cardinality flags - , innerStructuralCons flags values - ] - _ -> na "{structuralCons} ExplicitVarSizeWithFlags" - - structuralCons _ _ _ = na "{structuralCons} ExplicitVarSizeWithFlags" - - downC :: TypeOf_DownC m - downC ( name - , domain@(DomainMSet _ attrs innerDomain) - , ConstantAbstract (AbsLitMSet constants') - ) = do - maxSize <- getMaxSize attrs innerDomain - let indexDomain = mkDomainIntB 1 maxSize - - let constants = histogram constants' - - maxSizeInt <- - case maxSize of -<<<<<<< HEAD - ConstantInt Nothing x -> return x -||||||| merged common ancestors - ConstantInt x -> return x -======= - ConstantInt _ x -> return x ->>>>>>> taggedints - _ -> fail $ vcat - [ "Expecting an integer for the maxSize attribute." - , "But got:" <+> pretty maxSize - , "When working on:" <+> pretty name - , "With domain:" <+> pretty domain - ] - z <- zeroVal innerDomain - let zeroes = replicate (fromInteger (maxSizeInt - genericLength constants)) z - -<<<<<<< HEAD - let counts = map (ConstantInt Nothing . snd) constants - let falses = replicate (fromInteger (maxSizeInt - genericLength constants)) (ConstantInt Nothing 0) -||||||| merged common ancestors - let counts = map (ConstantInt . snd) constants - let falses = replicate (fromInteger (maxSizeInt - genericLength constants)) (ConstantInt 0) -======= - let counts = map (ConstantInt NoTag . snd) constants - let falses = replicate (fromInteger (maxSizeInt - genericLength constants)) (ConstantInt NoTag 0) ->>>>>>> taggedints - - return $ Just - [ ( nameFlag domain name - , DomainMatrix indexDomain DomainBool - , ConstantAbstract $ AbsLitMatrix indexDomain (counts ++ falses) - ) - , ( nameValues domain name - , DomainMatrix indexDomain innerDomain - , ConstantAbstract $ AbsLitMatrix indexDomain (map fst constants ++ zeroes) - ) - ] - downC _ = na "{downC} ExplicitVarSizeWithFlags" - - up :: TypeOf_Up m - up ctxt (name, domain) = - case (lookup (nameFlag domain name) ctxt, lookup (nameValues domain name) ctxt) of - (Just flagMatrix, Just constantMatrix) -> - case viewConstantMatrix flagMatrix of - -- TODO: check if indices match - Just (_, flags) -> - case viewConstantMatrix constantMatrix of - Just (_, vals) -> - return (name, ConstantAbstract $ AbsLitMSet $ concat - [ replicate (fromInteger i) v -<<<<<<< HEAD - | (ConstantInt Nothing i,v) <- zip flags vals -||||||| merged common ancestors - | (ConstantInt i,v) <- zip flags vals -======= - | (ConstantInt NoTag i,v) <- zip flags vals ->>>>>>> taggedints - ] ) - _ -> fail $ vcat - [ "Expecting a matrix literal for:" <+> pretty (nameValues domain name) - , "But got:" <+> pretty constantMatrix - , "When working on:" <+> pretty name - , "With domain:" <+> pretty domain - ] - _ -> fail $ vcat - [ "Expecting a matrix literal for:" <+> pretty (nameFlag domain name) - , "But got:" <+> pretty flagMatrix - , "When working on:" <+> pretty name - , "With domain:" <+> pretty domain - ] - (Nothing, _) -> fail $ vcat $ - [ "(in MSet ExplicitVarSizeWithFlags up 1)" - , "No value for:" <+> pretty (nameFlag domain name) - , "When working on:" <+> pretty name - , "With domain:" <+> pretty domain - ] ++ - ("Bindings in context:" : prettyContext ctxt) - (_, Nothing) -> fail $ vcat $ - [ "(in MSet ExplicitVarSizeWithFlags up 2)" - , "No value for:" <+> pretty (nameValues domain name) - , "When working on:" <+> pretty name - , "With domain:" <+> pretty domain - ] ++ - ("Bindings in context:" : prettyContext ctxt) diff --git a/src/Conjure/Representations/MSet/ExplicitWithRepetition.hs.orig b/src/Conjure/Representations/MSet/ExplicitWithRepetition.hs.orig deleted file mode 100644 index a5cfb4a0a3..0000000000 --- a/src/Conjure/Representations/MSet/ExplicitWithRepetition.hs.orig +++ /dev/null @@ -1,251 +0,0 @@ -{-# LANGUAGE QuasiQuotes #-} - -module Conjure.Representations.MSet.ExplicitWithRepetition ( msetExplicitWithRepetition ) where - --- conjure -import Conjure.Prelude -import Conjure.Language -import Conjure.Language.DomainSizeOf -import Conjure.Language.Expression.DomainSizeOf () -import Conjure.Language.ZeroVal ( zeroVal, EnumerateDomain ) -import Conjure.Representations.Internal -import Conjure.Representations.Common - - -msetExplicitWithRepetition :: forall m . (MonadFail m, NameGen m, EnumerateDomain m) => Representation m -msetExplicitWithRepetition = Representation chck downD structuralCons downC up - - where - - chck :: TypeOf_ReprCheck m - chck f (DomainMSet _ attrs innerDomain) = - map (DomainMSet MSet_ExplicitWithRepetition attrs) <$> f innerDomain - chck _ _ = return [] - - nameFlag = mkOutName (Just "Flag") - nameValues = mkOutName (Just "Values") - - getMaxSize attrs innerDomain = case attrs of - MSetAttr (SizeAttr_Size x) _ -> return x - MSetAttr (SizeAttr_MaxSize x) _ -> return x - MSetAttr (SizeAttr_MinMaxSize _ x) _ -> return x - MSetAttr _ (OccurAttr_MaxOccur x) -> do y <- domainSizeOf innerDomain ; return (x * y) - MSetAttr _ (OccurAttr_MinMaxOccur _ x) -> do y <- domainSizeOf innerDomain ; return (x * y) - _ -> fail ("getMaxSize, mset not supported. attributes:" <+> pretty attrs) - - getMinOccur attrs = case attrs of - MSetAttr _ (OccurAttr_MinOccur x) -> Just x - MSetAttr _ (OccurAttr_MinMaxOccur x _) -> Just x - _ -> Nothing - - getMaxOccur attrs = case attrs of - MSetAttr _ (OccurAttr_MaxOccur x) -> return x - MSetAttr _ (OccurAttr_MinMaxOccur _ x) -> return x - _ -> fail ("getMaxOccur, mset not supported. attributes:" <+> pretty attrs) - - downD :: TypeOf_DownD m - downD (name, domain@(DomainMSet _ attrs innerDomain)) = do - (indexDomain, flagDomain) <- - case attrs of - MSetAttr (SizeAttr_Size size) _ -> do - let indexDomain = mkDomainIntB 1 size -<<<<<<< HEAD - let flagDomain = defRepr $ DomainInt Nothing [RangeSingle size] -||||||| merged common ancestors - let flagDomain = defRepr $ DomainInt [RangeSingle size] -======= - let flagDomain = defRepr $ DomainInt NoTag [RangeSingle size] ->>>>>>> taggedints - return (indexDomain, flagDomain) - _ -> do - maxSize <- getMaxSize attrs innerDomain - let indexDomain = mkDomainIntB 1 maxSize - let flagDomain = defRepr $ mkDomainIntB 0 maxSize - return (indexDomain, flagDomain) - return $ Just - [ ( nameFlag domain name - , flagDomain - ) - , ( nameValues domain name - , DomainMatrix indexDomain innerDomain - ) - ] - downD _ = na "{downD} ExplicitVarSizeWithRepetition" - - structuralCons :: TypeOf_Structural m - structuralCons f downX1 (DomainMSet MSet_ExplicitWithRepetition attrs@(MSetAttr sizeAttrs _) innerDomain) = do - maxSize <- getMaxSize attrs innerDomain - let maxIndex = maxSize - let - orderingUpToFlag flag values = do - (iPat, i) <- quantifiedVar - return $ return $ -- list - [essence| - forAll &iPat : int(1..&maxIndex-1) , &i+1 <= &flag . &values[&i] .<= &values[&i+1] - |] - - dontCareAfterFlag flag values = do - (iPat, i) <- quantifiedVar - return $ return $ -- list - [essence| - forAll &iPat : int(1..&maxIndex) , &i > &flag . dontCare(&values[&i]) - |] - - minOccurrenceCons mset flag values = do - (iPat, i) <- quantifiedVar - return - [ [essence| - forAll &iPat : int(1..&maxIndex) , &i <= &flag . - (freq(&mset, &values[&i]) = 0 \/ freq(&mset, &values[&i]) >= &minOccur) - |] - | Just minOccur <- [getMinOccur attrs] - ] - - maxOccurrenceCons mset flag values = do - (iPat, i) <- quantifiedVar - return - [ [essence| - forAll &iPat : int(1..&maxIndex) , &i <= &flag . - freq(&mset, &values[&i]) <= &maxOccur_ - |] - | Just maxOccur_ <- [getMaxOccur attrs] - ] - - innerStructuralCons flag values = do - (iPat, i) <- quantifiedVarOverDomain [essenceDomain| int(1..&maxIndex) |] - let activeZone b = [essence| forAll &iPat : int(1..&maxIndex) , &i <= &flag . &b |] - - -- preparing structural constraints for the inner guys - innerStructuralConsGen <- f innerDomain - - let inLoop = [essence| &values[&i] |] - outs <- innerStructuralConsGen inLoop - return (map activeZone outs) - - return $ \ mset -> do - refs <- downX1 mset - case refs of - [flag, values] -> - concat <$> sequence - [ orderingUpToFlag flag values - , dontCareAfterFlag flag values - , minOccurrenceCons mset flag values - , maxOccurrenceCons mset flag values - , return (mkSizeCons sizeAttrs flag) - , innerStructuralCons flag values - ] - _ -> na "{structuralCons} ExplicitVarSizeWithRepetition" - - structuralCons _ _ _ = na "{structuralCons} ExplicitVarSizeWithRepetition" - - downC :: TypeOf_DownC m - downC ( name - , domain@(DomainMSet _ attrs innerDomain) - , ConstantAbstract (AbsLitMSet constants) - ) = case attrs of - MSetAttr (SizeAttr_Size size) _ -> do - let indexDomain = mkDomainIntB 1 size -<<<<<<< HEAD - let flagDomain = DomainInt Nothing [RangeSingle size] -||||||| merged common ancestors - let flagDomain = DomainInt [RangeSingle size] -======= - let flagDomain = DomainInt NoTag [RangeSingle size] ->>>>>>> taggedints - - return $ Just - [ ( nameFlag domain name - , defRepr flagDomain -<<<<<<< HEAD - , ConstantInt Nothing (genericLength constants) -||||||| merged common ancestors - , ConstantInt (genericLength constants) -======= - , ConstantInt NoTag (genericLength constants) ->>>>>>> taggedints - ) - , ( nameValues domain name - , DomainMatrix indexDomain innerDomain - , ConstantAbstract $ AbsLitMatrix indexDomain constants - ) - ] - - _ -> do - maxSize <- getMaxSize attrs innerDomain - maxSizeInt <- - case maxSize of -<<<<<<< HEAD - ConstantInt Nothing x -> return x -||||||| merged common ancestors - ConstantInt x -> return x -======= - ConstantInt _ x -> return x ->>>>>>> taggedints - _ -> fail $ vcat - [ "Expecting an integer for the maxSize attribute." - , "But got:" <+> pretty maxSize - , "When working on:" <+> pretty name - , "With domain:" <+> pretty domain - ] - let indexDomain = mkDomainIntB 1 maxSize - let flagDomain = mkDomainIntB 0 maxSize - - z <- zeroVal innerDomain - let zeroes = replicate (fromInteger (maxSizeInt - genericLength constants)) z - - return $ Just - [ ( nameFlag domain name - , defRepr flagDomain -<<<<<<< HEAD - , ConstantInt Nothing (genericLength constants) -||||||| merged common ancestors - , ConstantInt (genericLength constants) -======= - , ConstantInt NoTag (genericLength constants) ->>>>>>> taggedints - ) - , ( nameValues domain name - , DomainMatrix indexDomain innerDomain - , ConstantAbstract $ AbsLitMatrix indexDomain (constants ++ zeroes) - ) - ] - - downC _ = na "{downC} ExplicitVarSizeWithRepetition" - - up :: TypeOf_Up m - up ctxt (name, domain) = - case (lookup (nameFlag domain name) ctxt, lookup (nameValues domain name) ctxt) of - (Just flag, Just constantMatrix) -> - case viewConstantInt flag of - -- TODO: check if indices match - Just flagInt -> - case viewConstantMatrix constantMatrix of - Just (_, vals) -> - return (name, ConstantAbstract $ AbsLitMSet - (genericTake flagInt vals) ) - _ -> fail $ vcat - [ "Expecting a matrix literal for:" <+> pretty (nameValues domain name) - , "But got:" <+> pretty constantMatrix - , "When working on:" <+> pretty name - , "With domain:" <+> pretty domain - ] - _ -> fail $ vcat - [ "Expecting an integer literal for:" <+> pretty (nameFlag domain name) - , "But got:" <+> pretty flag - , "When working on:" <+> pretty name - , "With domain:" <+> pretty domain - ] - (Nothing, _) -> fail $ vcat $ - [ "(in MSet ExplicitVarSizeWithRepetition up 1)" - , "No value for:" <+> pretty (nameFlag domain name) - , "When working on:" <+> pretty name - , "With domain:" <+> pretty domain - ] ++ - ("Bindings in context:" : prettyContext ctxt) - (_, Nothing) -> fail $ vcat $ - [ "(in MSet ExplicitVarSizeWithRepetition up 2)" - , "No value for:" <+> pretty (nameValues domain name) - , "When working on:" <+> pretty name - , "With domain:" <+> pretty domain - ] ++ - ("Bindings in context:" : prettyContext ctxt) diff --git a/src/Conjure/Representations/Partition/Occurrence.hs.orig b/src/Conjure/Representations/Partition/Occurrence.hs.orig deleted file mode 100644 index a2b0c423f3..0000000000 --- a/src/Conjure/Representations/Partition/Occurrence.hs.orig +++ /dev/null @@ -1,380 +0,0 @@ --- {-# LANGUAGE Rank2Types #-} -{-# LANGUAGE RecordWildCards #-} -{-# LANGUAGE QuasiQuotes #-} -{-# LANGUAGE ViewPatterns #-} - -module Conjure.Representations.Partition.Occurrence ( partitionOccurrence ) where - --- conjure -import Conjure.Prelude -import Conjure.Bug -import Conjure.Language -import Conjure.Language.DomainSizeOf -import Conjure.Language.Expression.DomainSizeOf () -import Conjure.Language.ZeroVal ( zeroVal, EnumerateDomain ) -import Conjure.Representations.Internal -import Conjure.Representations.Common -import Conjure.Representations.Function.Function1D ( domainValues ) - - --- | works for "partition from A", where A can be used as an index of a matrix --- _WhichPart: matrix indexed by [A] of int(1..maxNumParts) --- (indicating which part an element belongs to) --- _NumParts : int(1..maxNumParts) --- (indicating the total number of parts) --- only use part numbers from 1.._NumParts, never use the others --- part(i) is used -> part(i-1) is used, forAll i:int(3..maxNumParts) -partitionOccurrence :: forall m . (MonadFail m, NameGen m, EnumerateDomain m) => Representation m -partitionOccurrence = Representation chck downD structuralCons downC up - - where - - chck :: TypeOf_ReprCheck m - chck f (DomainPartition _ attrs innerDomain) - | domainCanIndexMatrix innerDomain - = map (DomainPartition Partition_Occurrence attrs) <$> f innerDomain - chck _ _ = return [] - - nameNumParts = mkOutName (Just "NumParts") - nameWhichPart = mkOutName (Just "WhichPart") - namePartSizes = mkOutName (Just "PartSizes") - nameFirstIndex = mkOutName (Just "FirstIndex") - - getMaxNumParts attrs d = - case partsNum attrs of - SizeAttr_Size x -> return x - SizeAttr_MaxSize x -> return x - SizeAttr_MinMaxSize _ x -> return x - _ -> domainSizeOf d - - getMaxPartSizes attrs d = - case partsSize attrs of - SizeAttr_Size x -> return x - SizeAttr_MaxSize x -> return x - SizeAttr_MinMaxSize _ x -> return x - _ -> domainSizeOf d - - -- downD :: TypeOf_DownD m - downD (name, domain@(DomainPartition Partition_Occurrence attrs innerDomain)) - | domainCanIndexMatrix innerDomain = do - maxNumParts <- getMaxNumParts attrs innerDomain - maxPartSizes <- getMaxPartSizes attrs innerDomain - return $ Just - [ - -- number of active parts - ( nameNumParts domain name -<<<<<<< HEAD - , DomainInt Nothing [RangeBounded 1 maxNumParts] -||||||| merged common ancestors - , DomainInt [RangeBounded 1 maxNumParts] -======= - , DomainInt NoTag [RangeBounded 1 maxNumParts] ->>>>>>> taggedints - ) - -- for each element, the part it belongs to - , ( nameWhichPart domain name - , DomainMatrix - (forgetRepr innerDomain) -<<<<<<< HEAD - (DomainInt Nothing [RangeBounded 1 maxNumParts]) -||||||| merged common ancestors - (DomainInt [RangeBounded 1 maxNumParts]) -======= - (DomainInt NoTag [RangeBounded 1 maxNumParts]) ->>>>>>> taggedints - ) - -- for each part, number of elements in the part - , ( namePartSizes domain name - , DomainMatrix -<<<<<<< HEAD - (DomainInt Nothing [RangeBounded 1 maxNumParts]) - (DomainInt Nothing [RangeBounded 0 maxPartSizes]) -||||||| merged common ancestors - (DomainInt [RangeBounded 1 maxNumParts]) - (DomainInt [RangeBounded 0 maxPartSizes]) -======= - (DomainInt NoTag [RangeBounded 1 maxNumParts]) - (DomainInt NoTag [RangeBounded 0 maxPartSizes]) ->>>>>>> taggedints - ) - -- wtf was this? - , ( nameFirstIndex domain name - , DomainMatrix -<<<<<<< HEAD - (DomainInt Nothing [RangeBounded 1 maxNumParts]) -||||||| merged common ancestors - (DomainInt [RangeBounded 1 maxNumParts]) -======= - (DomainInt NoTag [RangeBounded 1 maxNumParts]) ->>>>>>> taggedints - innerDomain -- dontCare if not used - ) - ] - downD _ = na "{downD} Occurrence" - - structuralCons :: TypeOf_Structural m - structuralCons _ downX1 (DomainPartition _ attrs innerDomain) - | domainCanIndexMatrix innerDomain = do - maxNumParts <- getMaxNumParts attrs innerDomain - let - numPartsChannelling whichPart numPartsVar = do - (iPat, i) <- quantifiedVar - return $ return -- for list - [essence| - &numPartsVar = - max([ &whichPart[&i] | &iPat : &innerDomain ]) - |] - - partSizesChannelling whichPart partSizesVar = do - (iPat, i) <- quantifiedVar - (jPat, j) <- quantifiedVar - return $ return -- for list - [essence| - and([ &partSizesVar[&i] = sum([ 1 | &jPat : &innerDomain , &whichPart[&j] = &i ]) - | &iPat : int(1..&maxNumParts) - ]) - |] - - firstIndexChannelling whichPart numPartsVar firstIndexVar = do - (iPat, i) <- quantifiedVar - (jPat, j) <- quantifiedVar - return - [ -- firstIndexVar[i] is <= all indices belonging to part i - [essence| - forAll &iPat : int(1..&maxNumParts) , &i <= &numPartsVar . - forAll &jPat : &innerDomain . - &whichPart[&j] = &i -> &firstIndexVar[&i] <= &j - |] - , -- firstIndexVar[i] is equal to one of those - [essence| - forAll &iPat : int(1..&maxNumParts) , &i <= &numPartsVar . - exists &jPat : &innerDomain . - &whichPart[&j] = &i /\ &firstIndexVar[&i] = &j - |] - , -- firstIndexVar[i] is dontCare, if nothing is in part i - [essence| - forAll &iPat : int(1..&maxNumParts) , &i > &numPartsVar . - dontCare(&firstIndexVar[&i]) - |] - ] - - symmetryBreaking numPartsVar firstIndexVar = do - (iPat, i) <- quantifiedVar - (jPat, j) <- quantifiedVar - return $ return -- for list - [essence| - forAll &iPat, &jPat : int(1..&maxNumParts) , &i <= &numPartsVar /\ &j <= &numPartsVar . - &i < &j <-> &firstIndexVar[&i] < &firstIndexVar[&j] - |] - - numPartsCons numPartsVar = - return $ mkSizeCons (partsNum attrs) numPartsVar - - partSizeCons numPartsVar partSizesVar = do - (iPat, i) <- quantifiedVar - let theConsForI = make opAnd $ fromList $ - mkSizeCons (partsSize attrs) [essence| &partSizesVar[&i] |] - return - [ [essence| - and([ &theConsForI - | &iPat : int(1..&maxNumParts) $ forAll part numbers - , &i <= &numPartsVar $ that are active - ]) - |] - , [essence| - and([ &partSizesVar[&i] = 0 - | &iPat : int(1..&maxNumParts) $ forAll part numbers - , &i > &numPartsVar $ that are inactive - ]) - |] - ] - - noGaps whichPart numPartsVar = do - (iPat, i) <- quantifiedVar - (jPat, j) <- quantifiedVar - return $ return -- for list - [essence| - and([ or([ &whichPart[&j] = &i $ there must be a member in that part - | &jPat : &innerDomain - ]) - | &iPat : int(3..&maxNumParts) $ forAll part numbers (except 1 and 2) - , &i <= &numPartsVar $ that are active - ]) - |] - - fixedPartSize = - case attrs of - PartitionAttr _ SizeAttr_Size{} _ -> True - _ -> False - - regular numPartsVar partSizesVar | isRegular attrs && not fixedPartSize = do - (iPat, i) <- quantifiedVar - return $ return -- for list - [essence| - and([ &partSizesVar[&i-1] = &partSizesVar[&i] - | &iPat : int(2..&maxNumParts) - , &i <= &numPartsVar - ]) - |] - regular _ _ = return [] - - return $ \ inpPartition -> do - [numPartsVar, whichPart, partSizesVar, firstIndexVar] <- downX1 inpPartition - concat <$> sequence - [ partSizeCons numPartsVar partSizesVar - , numPartsCons numPartsVar - , noGaps whichPart numPartsVar - , regular numPartsVar partSizesVar - , numPartsChannelling whichPart numPartsVar - , partSizesChannelling whichPart partSizesVar - , firstIndexChannelling whichPart numPartsVar firstIndexVar - , symmetryBreaking numPartsVar firstIndexVar - ] - structuralCons _ _ domain = na $ vcat [ "{structuralCons} Occurrence" - , "domain:" <+> pretty domain - ] - - downC :: TypeOf_DownC m - downC ( name - , inDom@(DomainPartition Partition_Occurrence attrs innerDomain) - , inConstant@(ConstantAbstract (AbsLitPartition vals)) - ) = do - Just [ ( numPartsVar , numPartsDom ) - , ( whichPart , whichPartDom ) - , ( partSizesVar , partSizesDom ) - , ( firstIndexVar , firstIndexDom ) - ] <- downD (name, inDom) - members <- domainValues innerDomain - maxNumParts' <- getMaxNumParts attrs innerDomain - maxNumParts <- case viewConstantInt maxNumParts' of - Just i -> return i - Nothing -> bug ("expecting an integer literal, but got:" <++> pretty maxNumParts') - z <- zeroVal innerDomain - let - whichPartValInside :: [(Integer, Constant)] - whichPartValInside = - [ case whichPartIsIt of - [p] -> p - [] -> bug $ vcat [ "Not found:" <+> pretty mem - , "Inside:" <+> pretty inConstant - ] - _ -> bug $ vcat [ "Found multiple times:" <+> pretty mem - , "Inside:" <+> pretty inConstant - ] - | mem <- members - , let whichPartIsIt = [ (p, mem) - | (p, pVals) <- zip [1..] vals - , mem `elem` pVals - ] - ] -<<<<<<< HEAD - numPartsVal = ConstantInt Nothing (genericLength vals) -||||||| merged common ancestors - numPartsVal = ConstantInt (genericLength vals) -======= - numPartsVal = ConstantInt NoTag (genericLength vals) ->>>>>>> taggedints - whichPartVal = ConstantAbstract (AbsLitMatrix - (forgetRepr innerDomain) -<<<<<<< HEAD - (map (ConstantInt Nothing . fst) whichPartValInside)) -||||||| merged common ancestors - (map (ConstantInt . fst) whichPartValInside)) -======= - (map (ConstantInt NoTag . fst) whichPartValInside)) ->>>>>>> taggedints - partSizesVal = ConstantAbstract (AbsLitMatrix -<<<<<<< HEAD - (DomainInt Nothing [RangeBounded 1 maxNumParts']) - (map (ConstantInt Nothing . genericLength) vals -||||||| merged common ancestors - (DomainInt [RangeBounded 1 maxNumParts']) - (map (ConstantInt . genericLength) vals -======= - (DomainInt NoTag [RangeBounded 1 maxNumParts']) - (map (ConstantInt NoTag . genericLength) vals ->>>>>>> taggedints - ++ replicate (fromInteger (maxNumParts - genericLength vals)) -<<<<<<< HEAD - (ConstantInt Nothing 0))) -||||||| merged common ancestors - (ConstantInt 0))) -======= - (ConstantInt NoTag 0))) ->>>>>>> taggedints - firstIndexVal = ConstantAbstract (AbsLitMatrix -<<<<<<< HEAD - (DomainInt Nothing [RangeBounded 1 maxNumParts']) -||||||| merged common ancestors - (DomainInt [RangeBounded 1 maxNumParts']) -======= - (DomainInt NoTag [RangeBounded 1 maxNumParts']) ->>>>>>> taggedints - ([ case lookup p whichPartValInside of - Nothing -> bug $ vcat [ "Not found:" <+> pretty p - , "Inside:" <+> prettyList id "," whichPartValInside - ] - Just i -> i - | p <- [1..genericLength vals] ] - ++ replicate (fromInteger (maxNumParts - genericLength vals)) - z)) - return $ Just - [ ( numPartsVar , numPartsDom , numPartsVal ) - , ( whichPart , whichPartDom , whichPartVal ) - , ( partSizesVar , partSizesDom , partSizesVal ) - , ( firstIndexVar , firstIndexDom , firstIndexVal ) - ] - downC (name, domain, constant) = na $ vcat [ "{downC} Occurrence" - , "name:" <+> pretty name - , "domain:" <+> pretty domain - , "constant:" <+> pretty constant - ] - - up :: TypeOf_Up m - up ctxt (name, domain@(DomainPartition Partition_Occurrence _ innerDomain)) = - case (lookup (nameNumParts domain name) ctxt, lookup (nameWhichPart domain name) ctxt) of - ( Just (viewConstantInt -> Just numPartsValue) , - Just (viewConstantMatrix -> Just (_, whichPartValues)) ) -> do - members <- domainValues innerDomain - return - ( name - , normaliseConstant $ ConstantAbstract $ AbsLitPartition -<<<<<<< HEAD - [ [ member | (member, b) <- zip members whichPartValues, b == ConstantInt Nothing bucket ] -||||||| merged common ancestors - [ [ member | (member, b) <- zip members whichPartValues, b == ConstantInt bucket ] -======= - [ [ member | (member, b) <- zip members whichPartValues, b == ConstantInt NoTag bucket ] ->>>>>>> taggedints - | bucket <- [1..numPartsValue] - ] - ) - (Just val, _) -> fail $ vcat $ - [ "(in Partition Occurrence up)" - , "Expecting an integer literal for:" <+> pretty (nameNumParts domain name) - , "But got:" <+> pretty val - , "When working on:" <+> pretty name - , "With domain:" <+> pretty domain - ] ++ - ("Bindings in context:" : prettyContext ctxt) - (_, Just val) -> fail $ vcat $ - [ "(in Partition Occurrence up)" - , "Expecting a matrix literal for:" <+> pretty (nameWhichPart domain name) - , "But got:" <+> pretty val - , "When working on:" <+> pretty name - , "With domain:" <+> pretty domain - ] ++ - ("Bindings in context:" : prettyContext ctxt) - (Nothing, _) -> fail $ vcat $ - [ "(in Partition Occurrence up)" - , "No value for:" <+> pretty (nameNumParts domain name) - , "When working on:" <+> pretty name - , "With domain:" <+> pretty domain - ] ++ - ("Bindings in context:" : prettyContext ctxt) - up ctxt (name, domain) = - na $ vcat [ "{up} Occurrence" - , "name:" <+> pretty name - , "domain:" <+> pretty domain - , "ctxt:" <+> vcat (map pretty ctxt) - ] diff --git a/src/Conjure/Representations/Partition/PartitionAsSet.hs.orig b/src/Conjure/Representations/Partition/PartitionAsSet.hs.orig deleted file mode 100644 index 2f84326c24..0000000000 --- a/src/Conjure/Representations/Partition/PartitionAsSet.hs.orig +++ /dev/null @@ -1,200 +0,0 @@ -{-# LANGUAGE Rank2Types #-} -{-# LANGUAGE RecordWildCards #-} -{-# LANGUAGE QuasiQuotes #-} -{-# LANGUAGE ViewPatterns #-} - -module Conjure.Representations.Partition.PartitionAsSet ( partitionAsSet ) where - --- conjure -import Conjure.Prelude -import Conjure.Language.Definition -import Conjure.Language.Constant -import Conjure.Language.Domain -import Conjure.Language.TH -import Conjure.Language.Pretty -import Conjure.Language.Type ( Type(..)) -import Conjure.Language.TypeOf ( typeOf ) -import Conjure.Language.Expression.DomainSizeOf ( domainSizeOf ) -import Conjure.Representations.Internal - - -partitionAsSet - :: forall m . (MonadFail m, NameGen m) - => (forall x . DispatchFunction m x) - -> (forall r x . ReprOptionsFunction m r x) - -> Bool - -> Representation m -partitionAsSet dispatch reprOptions useLevels = Representation chck downD structuralCons downC up - - where - - chck :: TypeOf_ReprCheck m - chck _ dom1@(DomainPartition _ attrs _) = do - -- this is a "lookahead" - -- do the horizontal representation move: go from "partition of T" to "set of set of T" - -- do representation selection on the set - -- lookup the chosen representations and store them inside Partition_AsSet - dom2 <- outDomain_ dom1 - dom3 <- reprOptions dom2 - return [ DomainPartition (Partition_AsSet r1 r2) attrs innerDomain - | DomainSet r1 _ (DomainSet r2 _ innerDomain) <- dom3 - -- special hack: do not use Set_ExplicitVarSizeWithFlags when --representation-levels=yes - , if useLevels - then r1 /= Set_ExplicitVarSizeWithFlags && r2 /= Set_ExplicitVarSizeWithFlags - else True - ] - chck _ _ = return [] - - outName :: Domain HasRepresentation x -> Name -> Name - outName = mkOutName Nothing - - outDomain_ :: Pretty x => Domain () x -> m (Domain () x) - outDomain_ (DomainPartition () PartitionAttr{..} innerDomain) = - return (DomainSet () (SetAttr partsNum) (DomainSet () (SetAttr partsSize) innerDomain)) - outDomain_ domain = na $ vcat [ "{outDomain_} PartitionAsSet" - , "domain:" <+> pretty domain - ] - - outDomain :: Pretty x => Domain HasRepresentation x -> m (Domain HasRepresentation x) - outDomain (DomainPartition (Partition_AsSet repr1 repr2) PartitionAttr{..} innerDomain) = - return (DomainSet repr1 (SetAttr partsNum) (DomainSet repr2 (SetAttr partsSize) innerDomain)) - outDomain domain = na $ vcat [ "{outDomain} PartitionAsSet" - , "domain:" <+> pretty domain - ] - - downD :: TypeOf_DownD m - downD (name, inDom) = do - outDom <- outDomain inDom - return $ Just [ ( outName inDom name , outDom ) ] - - structuralCons :: TypeOf_Structural m - structuralCons f downX1 inDom@(DomainPartition _ attrs innerDomain) = return $ \ inpRel -> do - refs <- downX1 inpRel - let - - fixedPartSize = - case attrs of - PartitionAttr _ SizeAttr_Size{} _ -> True - _ -> False - - exactlyOnce rel = do - innerType <- typeOf innerDomain -<<<<<<< HEAD - if innerType `typeUnify` TypeInt Nothing - then do -||||||| merged common ancestors - if innerType `typeUnify` TypeInt - then do -======= - case innerType of - TypeInt _ -> do ->>>>>>> taggedints - (iPat, i) <- quantifiedVar - (jPat, j) <- quantifiedVar - return $ return $ -- for list - [essence| - allDiff([ &j - | &iPat <- &rel - , &jPat <- &i - ]) - |] - - _ -> do - (iPat, i) <- quantifiedVar - (jPat, j) <- quantifiedVar - return $ return $ -- for list - [essence| - forAll &iPat : &innerDomain . - 1 = sum ([ 1 - | &jPat <- &rel - , &i in &j - ]) - |] - - regular rel | isRegular attrs && not fixedPartSize = do - (iPat, i) <- quantifiedVar - (jPat, j) <- quantifiedVar - return $ return -- for list - [essence| - and([ |&i| = |&j| - | &iPat <- &rel - , &jPat <- &rel - ]) - |] - regular _ = return [] - - partsAren'tEmpty rel = do - (iPat, i) <- quantifiedVar - return $ return [essence| and([ |&i| >= 1 | &iPat <- &rel ]) |] - - sumOfParts rel = do - case domainSizeOf innerDomain of - Left _err -> return [] - Right n -> do - (iPat, i) <- quantifiedVar - return $ return [essence| &n = sum([ |&i| | &iPat <- &rel ]) |] - - case refs of - [rel] -> do - outDom <- outDomain inDom - innerStructuralConsGen <- f outDom - concat <$> sequence - [ exactlyOnce rel - , regular rel - , partsAren'tEmpty rel - , innerStructuralConsGen rel - , sumOfParts rel - ] - _ -> na $ vcat [ "{structuralCons} PartitionAsSet" - , pretty inDom - ] - structuralCons _ _ domain = na $ vcat [ "{structuralCons} PartitionAsSet" - , "domain:" <+> pretty domain - ] - - downC :: TypeOf_DownC m - downC ( name - , inDom - , ConstantAbstract (AbsLitPartition vals) - ) = do - outDom <- outDomain inDom - rDownC - (dispatch outDom) - ( outName inDom name - , outDom - , ConstantAbstract $ AbsLitSet $ map (ConstantAbstract . AbsLitSet) vals - ) - downC (name, domain, constant) = na $ vcat [ "{downC} PartitionAsSet" - , "name:" <+> pretty name - , "domain:" <+> pretty domain - , "constant:" <+> pretty constant - ] - - up :: TypeOf_Up m - up ctxt (name, domain@(DomainPartition Partition_AsSet{} _ _)) = - case lookup (outName domain name) ctxt of - Nothing -> fail $ vcat $ - [ "(in PartitionAsSet up)" - , "No value for:" <+> pretty (outName domain name) - , "When working on:" <+> pretty name - , "With domain:" <+> pretty domain - ] ++ - ("Bindings in context:" : prettyContext ctxt) - Just (viewConstantSet -> Just sets) -> do - let setOut (viewConstantSet -> Just xs) = return xs - setOut c = fail $ "Expecting a set, but got:" <++> pretty c - vals <- mapM setOut sets - return (name, ConstantAbstract (AbsLitPartition vals)) - Just (ConstantUndefined msg ty) -> -- undefined propagates - return (name, ConstantUndefined ("PartitionAsSet " `mappend` msg) ty) - Just constant -> fail $ vcat $ - [ "Incompatible value for:" <+> pretty (outName domain name) - , "When working on:" <+> pretty name - , "With domain:" <+> pretty domain - , "Expected a set value, but got:" <++> pretty constant - ] ++ - ("Bindings in context:" : prettyContext ctxt) - up _ (name, domain) = na $ vcat [ "{up} PartitionAsSet" - , "name:" <+> pretty name - , "domain:" <+> pretty domain - ] diff --git a/src/Conjure/Representations/Primitive.hs.orig b/src/Conjure/Representations/Primitive.hs.orig deleted file mode 100644 index 7de1e7b409..0000000000 --- a/src/Conjure/Representations/Primitive.hs.orig +++ /dev/null @@ -1,39 +0,0 @@ -module Conjure.Representations.Primitive - ( primitive - ) where - --- conjure -import Conjure.Prelude -import Conjure.Language.Domain -import Conjure.Language.Pretty -import Conjure.Representations.Internal - - -primitive :: forall m . MonadFail m => Representation m -primitive = Representation - { rCheck = \ _ domain -> return $ - case domain of - DomainBool -> [DomainBool] -<<<<<<< HEAD - DomainIntE name x -> [DomainIntE name x] - DomainInt name rs -> [DomainInt name rs] -||||||| merged common ancestors - DomainIntE x -> [DomainIntE x] - DomainInt rs -> [DomainInt rs] -======= - DomainIntE x -> [DomainIntE x] - DomainInt t rs -> [DomainInt t rs] ->>>>>>> taggedints - _ -> [] - , rDownD = const $ return Nothing - , rStructural = \ _ _ _ -> return (\ _ -> return [] ) - , rDownC = const $ return Nothing - , rUp = \ ctxt (name, _) -> - case lookup name ctxt of - Nothing -> fail $ vcat - $ ("No value for:" <+> pretty name) - : "Bindings in context:" - : prettyContext ctxt - Just c -> return (name, c) - } - diff --git a/src/Conjure/Representations/Sequence/ExplicitBounded.hs.orig b/src/Conjure/Representations/Sequence/ExplicitBounded.hs.orig deleted file mode 100644 index bf9fb2e3e6..0000000000 --- a/src/Conjure/Representations/Sequence/ExplicitBounded.hs.orig +++ /dev/null @@ -1,338 +0,0 @@ -{-# LANGUAGE QuasiQuotes #-} - -module Conjure.Representations.Sequence.ExplicitBounded ( sequenceExplicitBounded ) where - --- conjure -import Conjure.Prelude -import Conjure.Language -import Conjure.Language.ZeroVal ( zeroVal, EnumerateDomain ) -import Conjure.Language.TypeOf ( typeOf ) -import Conjure.Representations.Internal -import Conjure.Representations.Common - - -sequenceExplicitBounded :: forall m . (MonadFail m, NameGen m, EnumerateDomain m) => Representation m -sequenceExplicitBounded = Representation chck downD structuralCons downC up - - where - - chck :: TypeOf_ReprCheck m - chck f (DomainSequence _ attrs@(SequenceAttr sizeAttr _) innerDomain) | hasMaxSize sizeAttr = - map (DomainSequence Sequence_ExplicitBounded attrs) <$> f innerDomain - chck _ _ = return [] - - nameMarker = mkOutName (Just "Length") - nameValues = mkOutName (Just "Values") - - hasMaxSize SizeAttr_Size{} = True - hasMaxSize SizeAttr_MaxSize{} = True - hasMaxSize SizeAttr_MinMaxSize{} = True - hasMaxSize _ = False - - getMaxSize (SizeAttr_MaxSize x) = return x - getMaxSize (SizeAttr_MinMaxSize _ x) = return x - getMaxSize _ = fail "Unknown maxSize" - - downD :: TypeOf_DownD m - downD (name, domain@(DomainSequence - Sequence_ExplicitBounded - (SequenceAttr (SizeAttr_Size size) _) - innerDomain)) = - return $ Just - [ ( nameMarker domain name -<<<<<<< HEAD - , DomainInt Nothing [RangeBounded size size] -||||||| merged common ancestors - , DomainInt [RangeBounded size size] -======= - , DomainInt NoTag [RangeBounded size size] ->>>>>>> taggedints - ) - , ( nameValues domain name - , DomainMatrix -<<<<<<< HEAD - (DomainInt Nothing [RangeBounded 1 size]) -||||||| merged common ancestors - (DomainInt [RangeBounded 1 size]) -======= - (DomainInt NoTag [RangeBounded 1 size]) ->>>>>>> taggedints - innerDomain - ) ] - downD (name, domain@(DomainSequence - Sequence_ExplicitBounded - (SequenceAttr sizeAttr _) - innerDomain)) = do - maxSize <- getMaxSize sizeAttr - return $ Just - [ ( nameMarker domain name -<<<<<<< HEAD - , DomainInt Nothing [RangeBounded 0 maxSize] -||||||| merged common ancestors - , DomainInt [RangeBounded 0 maxSize] -======= - , DomainInt NoTag [RangeBounded 0 maxSize] ->>>>>>> taggedints - ) - , ( nameValues domain name - , DomainMatrix -<<<<<<< HEAD - (DomainInt Nothing [RangeBounded 1 maxSize]) -||||||| merged common ancestors - (DomainInt [RangeBounded 1 maxSize]) -======= - (DomainInt NoTag [RangeBounded 1 maxSize]) ->>>>>>> taggedints - innerDomain - ) ] - downD _ = na "{downD} ExplicitBounded" - - structuralCons :: TypeOf_Structural m - structuralCons f downX1 (DomainSequence Sequence_ExplicitBounded (SequenceAttr (SizeAttr_Size size) jectivityAttr) innerDomain) = do - let injectiveCons values = do - innerType <- typeOf innerDomain -<<<<<<< HEAD - if typeUnify innerType (TypeInt Nothing) - then do -||||||| merged common ancestors - if typeUnify innerType TypeInt - then do -======= - case innerType of - TypeInt _ -> do ->>>>>>> taggedints - return $ return $ -- list - [essence| allDiff(&values) |] - - _ -> do - (iPat, i) <- quantifiedVar - (jPat, j) <- quantifiedVar - return $ return $ -- list - [essence| - and([ &values[&i] != &values[&j] - | &iPat : int(1..&size) - , &jPat : int(1..&size) - , &i .< &j - ]) - |] - - let surjectiveCons values = do - (iPat, i) <- quantifiedVar - (jPat, j) <- quantifiedVar - return $ return $ -- list - [essence| - forAll &iPat : &innerDomain . - exists &jPat : int(1..&size) . - &values[&j] = &i - |] - - let jectivityCons values = case jectivityAttr of - JectivityAttr_None -> return [] - JectivityAttr_Injective -> injectiveCons values - JectivityAttr_Surjective -> surjectiveCons values - JectivityAttr_Bijective -> (++) <$> injectiveCons values - <*> surjectiveCons values - - let innerStructuralCons values = do - (iPat, i) <- quantifiedVarOverDomain [essenceDomain| int(1..&size) |] - let activeZone b = [essence| forAll &iPat : int(1..&size) . &b |] - - -- preparing structural constraints for the inner guys - innerStructuralConsGen <- f innerDomain - - let inLoop = [essence| &values[&i] |] - outs <- innerStructuralConsGen inLoop - return (map activeZone outs) - - return $ \ sequ -> do - refs <- downX1 sequ - case refs of - [_marker,values] -> - concat <$> sequence - [ jectivityCons values - , innerStructuralCons values - ] - _ -> na "{structuralCons} ExplicitBounded" - structuralCons f downX1 (DomainSequence Sequence_ExplicitBounded (SequenceAttr sizeAttr jectivityAttr) innerDomain) = do - maxSize <- getMaxSize sizeAttr - let injectiveCons marker values = do - (iPat, i) <- quantifiedVar - (jPat, j) <- quantifiedVar - return $ return $ -- list - [essence| - and([ &values[&i] != &values[&j] - | &iPat : int(1..&maxSize) - , &jPat : int(1..&maxSize) - , &i .< &j - , &i <= &marker - , &j <= &marker - ]) - |] - - let surjectiveCons marker values = do - (iPat, i) <- quantifiedVar - (jPat, j) <- quantifiedVar - return $ return $ -- list - [essence| - forAll &iPat : &innerDomain . - exists &jPat : int(1..&maxSize) . - (&j <= &marker) /\ &values[&j] = &i - |] - - let jectivityCons marker values = case jectivityAttr of - JectivityAttr_None -> return [] - JectivityAttr_Injective -> injectiveCons marker values - JectivityAttr_Surjective -> surjectiveCons marker values - JectivityAttr_Bijective -> (++) <$> injectiveCons marker values - <*> surjectiveCons marker values - - let dontCareAfterMarker marker values = do - (iPat, i) <- quantifiedVar - return $ return $ -- list - [essence| - forAll &iPat : int(1..&maxSize) . &i > &marker -> - dontCare(&values[&i]) - |] - - let innerStructuralCons marker values = do - (iPat, i) <- quantifiedVarOverDomain [essenceDomain| int(1..&maxSize) |] - let activeZone b = [essence| forAll &iPat : int(1..&maxSize) . &i <= &marker -> &b |] - - -- preparing structural constraints for the inner guys - innerStructuralConsGen <- f innerDomain - - let inLoop = [essence| &values[&i] |] - outs <- innerStructuralConsGen inLoop - return (map activeZone outs) - - return $ \ sequ -> do - refs <- downX1 sequ - case refs of - [marker,values] -> - concat <$> sequence - [ dontCareAfterMarker marker values - , return (mkSizeCons sizeAttr marker) - , jectivityCons marker values - , innerStructuralCons marker values - ] - _ -> na "{structuralCons} ExplicitBounded" - - structuralCons _ _ _ = na "{structuralCons} ExplicitBounded" - - downC :: TypeOf_DownC m - downC ( name - , domain@(DomainSequence _ (SequenceAttr (SizeAttr_Size size) _) innerDomain) - , ConstantAbstract (AbsLitSequence constants) - ) = - return $ Just - [ ( nameMarker domain name -<<<<<<< HEAD - , DomainInt Nothing [RangeBounded size size] - , ConstantInt Nothing (genericLength constants) -||||||| merged common ancestors - , DomainInt [RangeBounded size size] - , ConstantInt (genericLength constants) -======= - , DomainInt NoTag [RangeBounded size size] - , ConstantInt NoTag (genericLength constants) ->>>>>>> taggedints - ) - , ( nameValues domain name -<<<<<<< HEAD - , DomainMatrix (DomainInt Nothing [RangeBounded 1 size]) innerDomain - , ConstantAbstract $ AbsLitMatrix (DomainInt Nothing [RangeBounded 1 size]) constants -||||||| merged common ancestors - , DomainMatrix (DomainInt [RangeBounded 1 size]) innerDomain - , ConstantAbstract $ AbsLitMatrix (DomainInt [RangeBounded 1 size]) constants -======= - , DomainMatrix (DomainInt NoTag [RangeBounded 1 size]) innerDomain - , ConstantAbstract $ AbsLitMatrix (DomainInt NoTag [RangeBounded 1 size]) constants ->>>>>>> taggedints - ) - ] - downC ( name - , domain@(DomainSequence _ (SequenceAttr sizeAttr _) innerDomain) - , ConstantAbstract (AbsLitSequence constants) - ) = do - maxSize <- getMaxSize sizeAttr - let indexDomain i = mkDomainIntB (fromInt i) maxSize - maxSizeInt <- - case maxSize of -<<<<<<< HEAD - ConstantInt Nothing x -> return x -||||||| merged common ancestors - ConstantInt x -> return x -======= - ConstantInt _ x -> return x ->>>>>>> taggedints - _ -> fail $ vcat - [ "Expecting an integer for the maxSize attribute." - , "But got:" <+> pretty maxSize - , "When working on:" <+> pretty name - , "With domain:" <+> pretty domain - ] - z <- zeroVal innerDomain - let zeroes = replicate (fromInteger (maxSizeInt - genericLength constants)) z - return $ Just - [ ( nameMarker domain name - , defRepr (indexDomain 0) -<<<<<<< HEAD - , ConstantInt Nothing (genericLength constants) -||||||| merged common ancestors - , ConstantInt (genericLength constants) -======= - , ConstantInt NoTag (genericLength constants) ->>>>>>> taggedints - ) - , ( nameValues domain name - , DomainMatrix (indexDomain 1) innerDomain - , ConstantAbstract $ AbsLitMatrix (indexDomain 1) (constants ++ zeroes) - ) - ] - downC (name, domain, constant) = na $ vcat [ "{downC} ExplicitBounded" - , "name :" <+> pretty name - , "domain :" <+> pretty domain - , "constant:" <+> pretty constant - ] - - up :: TypeOf_Up m - up ctxt (name, domain) = - case (lookup (nameMarker domain name) ctxt, lookup (nameValues domain name) ctxt) of - (Just marker, Just constantMatrix) -> - case marker of -<<<<<<< HEAD - ConstantInt Nothing card -> -||||||| merged common ancestors - ConstantInt card -> -======= - ConstantInt _ card -> ->>>>>>> taggedints - case viewConstantMatrix constantMatrix of - Just (_, vals) -> - return (name, ConstantAbstract (AbsLitSequence (genericTake card vals))) - _ -> fail $ vcat - [ "Expecting a matrix literal for:" <+> pretty (nameValues domain name) - , "But got:" <+> pretty constantMatrix - , "When working on:" <+> pretty name - , "With domain:" <+> pretty domain - ] - _ -> fail $ vcat - [ "Expecting an integer literal for:" <+> pretty (nameMarker domain name) - , "But got:" <+> pretty marker - , "When working on:" <+> pretty name - , "With domain:" <+> pretty domain - ] - (Nothing, _) -> fail $ vcat $ - [ "(in Sequence ExplicitBounded up 1)" - , "No value for:" <+> pretty (nameMarker domain name) - , "When working on:" <+> pretty name - , "With domain:" <+> pretty domain - ] ++ - ("Bindings in context:" : prettyContext ctxt) - (_, Nothing) -> fail $ vcat $ - [ "(in Sequence ExplicitBounded up 2)" - , "No value for:" <+> pretty (nameValues domain name) - , "When working on:" <+> pretty name - , "With domain:" <+> pretty domain - ] ++ - ("Bindings in context:" : prettyContext ctxt) diff --git a/src/Conjure/Representations/Set/Explicit.hs.orig b/src/Conjure/Representations/Set/Explicit.hs.orig deleted file mode 100644 index d7753adf87..0000000000 --- a/src/Conjure/Representations/Set/Explicit.hs.orig +++ /dev/null @@ -1,113 +0,0 @@ -{-# LANGUAGE QuasiQuotes #-} - -module Conjure.Representations.Set.Explicit ( setExplicit ) where - --- conjure -import Conjure.Prelude -import Conjure.Language -import Conjure.Representations.Internal - - -setExplicit :: forall m . (MonadFail m, NameGen m) => Representation m -setExplicit = Representation chck downD structuralCons downC up - - where - - -- | We can represent any inner domain but set must be fixed size - chck :: TypeOf_ReprCheck m - chck f (DomainSet _ attrs@(SetAttr SizeAttr_Size{}) innerDomain) = - map (DomainSet Set_Explicit attrs) <$> f innerDomain - chck _ _ = return [] - - outName :: Domain HasRepresentation x -> Name -> Name - outName = mkOutName Nothing - - -- | A 1D matrix of size of set containing innerDomain objects - downD :: TypeOf_DownD m - downD (name, domain@(DomainSet Set_Explicit (SetAttr (SizeAttr_Size size)) innerDomain)) = return $ Just - [ ( outName domain name - , DomainMatrix -<<<<<<< HEAD - (DomainInt Nothing [RangeBounded 1 size]) -||||||| merged common ancestors - (DomainInt [RangeBounded 1 size]) -======= - (DomainInt NoTag [RangeBounded 1 size]) ->>>>>>> taggedints - innerDomain - ) ] - downD _ = na "{downD} Explicit" - - -- | Enforce lex ordering of matrix (symmetry breaking) and inner structural constraints of - -- 'active' elements of inner domain - structuralCons :: TypeOf_Structural m - structuralCons f downX1 (DomainSet Set_Explicit (SetAttr (SizeAttr_Size size)) innerDomain) = do - let - -- | Makes sure i'th value is lex less than (i+1)'th value - -- a symmetry breaking structural constraint - ordering m = do - (iPat, i) <- quantifiedVar - return $ return -- for list - [essence| - forAll &iPat : int(1..&size-1) . - &m[&i] .< &m[&i+1] - |] - - -- | Enforces structural constraints for the elements of the inner domain - -- that are in the set. - innerStructuralCons m = do - (iPat, i) <- quantifiedVarOverDomain [essenceDomain| int(1..&size) |] - let activeZone b = [essence| forAll &iPat : int(1..&size) . &b |] - - -- preparing structural constraints for the inner guys - innerStructuralConsGen <- f innerDomain - - let inLoop = [essence| &m[&i] |] - outs <- innerStructuralConsGen inLoop - return (map activeZone outs) - - return $ \ ref -> do - refs <- downX1 ref - case refs of - [m] -> - concat <$> sequence - [ ordering m - , innerStructuralCons m - ] - _ -> na "{structuralCons} Explicit" - structuralCons _ _ _ = na "{structuralCons} Explicit" - - downC :: TypeOf_DownC m - downC ( name - , domain@(DomainSet Set_Explicit (SetAttr (SizeAttr_Size size)) innerDomain) - , ConstantAbstract (AbsLitSet constants) - ) = - let outIndexDomain = mkDomainIntB 1 size - in return $ Just - [ ( outName domain name - , DomainMatrix outIndexDomain innerDomain - , ConstantAbstract $ AbsLitMatrix outIndexDomain constants - ) ] - downC _ = na "{downC} Explicit" - - up :: TypeOf_Up m - up ctxt (name, domain@(DomainSet Set_Explicit (SetAttr (SizeAttr_Size _)) _)) = - case lookup (outName domain name) ctxt of - Nothing -> fail $ vcat $ - [ "(in Set Explicit up)" - , "No value for:" <+> pretty (outName domain name) - , "When working on:" <+> pretty name - , "With domain:" <+> pretty domain - ] ++ - ("Bindings in context:" : prettyContext ctxt) - Just constant -> - case viewConstantMatrix constant of - Just (_, vals) -> - return (name, ConstantAbstract (AbsLitSet vals)) - _ -> fail $ vcat - [ "Expecting a matrix literal for:" <+> pretty (outName domain name) - , "But got:" <+> pretty constant - , "When working on:" <+> pretty name - , "With domain:" <+> pretty domain - ] - up _ _ = na "{up} Explicit" diff --git a/src/Conjure/Representations/Set/ExplicitVarSizeWithDummy.hs.orig b/src/Conjure/Representations/Set/ExplicitVarSizeWithDummy.hs.orig deleted file mode 100644 index bb344a8892..0000000000 --- a/src/Conjure/Representations/Set/ExplicitVarSizeWithDummy.hs.orig +++ /dev/null @@ -1,216 +0,0 @@ -{-# LANGUAGE QuasiQuotes #-} - -module Conjure.Representations.Set.ExplicitVarSizeWithDummy ( setExplicitVarSizeWithDummy ) where - --- conjure -import Conjure.Prelude -import Conjure.Bug -import Conjure.Language -import Conjure.Language.TypeOf -import Conjure.Language.DomainSizeOf -import Conjure.Language.Expression.DomainSizeOf () -import Conjure.Representations.Internal -import Conjure.Representations.Common - - -setExplicitVarSizeWithDummy :: forall m . (MonadFail m, NameGen m) => Representation m -setExplicitVarSizeWithDummy = Representation chck downD structuralCons downC up - - where - - chck :: TypeOf_ReprCheck m - chck _ (DomainSet _ (SetAttr SizeAttr_Size{}) _) = return [] - chck f (DomainSet _ attrs innerDomain@DomainInt{}) = - map (DomainSet Set_ExplicitVarSizeWithDummy attrs) <$> f innerDomain - chck _ _ = return [] - - outName :: Domain HasRepresentation x -> Name -> Name - outName = mkOutName Nothing - - getMaxSize attrs innerDomain = case attrs of - SizeAttr_MaxSize x -> return x - SizeAttr_MinMaxSize _ x -> return x - _ -> domainSizeOf innerDomain - - calcDummyDomain :: Pretty r => Domain r Expression -> Domain r Expression -<<<<<<< HEAD - calcDummyDomain (DomainInt name [RangeBounded lb ub]) = - DomainInt name [RangeBounded lb [essence| &ub + 1 |]] - calcDummyDomain dom@(DomainInt name ranges) = -||||||| merged common ancestors - calcDummyDomain (DomainInt [RangeBounded lb ub]) = - DomainInt [RangeBounded lb [essence| &ub + 1 |]] - calcDummyDomain dom@(DomainInt ranges) = -======= - calcDummyDomain (DomainInt t [RangeBounded lb ub]) = - let ut = addTag t ub - u1 = addTag t [essence| 1 |] - in DomainInt t $ addTag t [RangeBounded lb [essence| &ut +forced &u1 |]] - calcDummyDomain dom@(DomainInt t ranges) = ->>>>>>> taggedints - let dummyElem = calcDummyElem dom -<<<<<<< HEAD - in DomainInt name (ranges ++ [RangeSingle dummyElem]) -||||||| merged common ancestors - in DomainInt (ranges ++ [RangeSingle dummyElem]) -======= - in DomainInt t (ranges ++ [RangeSingle dummyElem]) ->>>>>>> taggedints - calcDummyDomain dom = bug ("ExplicitVarSizeWithDummy.calcDummyDomain" <+> pretty dom) - - calcDummyElem :: Pretty r => Domain r Expression -> Expression - calcDummyElem dom = - let theMax = bugFail "calcDummyElem: maxOfDomain" (maxOfDomain dom) - tag = bugFail "calcDummyElem: containsTag" (containsTag =<< typeOf dom) - in addTag tag [essence| &theMax +forced 1 |] - - calcDummyElemC :: Pretty r => Domain r Constant -> Constant -<<<<<<< HEAD - calcDummyElemC (DomainInt _ []) = bug "ExplicitVarSizeWithDummy.calcDummyElemC []" - calcDummyElemC (DomainInt _ rs) = ConstantInt Nothing $ -||||||| merged common ancestors - calcDummyElemC (DomainInt []) = bug "ExplicitVarSizeWithDummy.calcDummyElemC []" - calcDummyElemC (DomainInt rs) = ConstantInt $ -======= - calcDummyElemC (DomainInt _ []) = bug "ExplicitVarSizeWithDummy.calcDummyElemC []" - calcDummyElemC (DomainInt t rs) = ConstantInt t $ ->>>>>>> taggedints - 1 + maximum [ i - | r <- rs - , i <- case r of -<<<<<<< HEAD - RangeSingle (ConstantInt Nothing x) -> [x] - RangeBounded (ConstantInt Nothing x) (ConstantInt Nothing y) -> [x..y] -||||||| merged common ancestors - RangeSingle (ConstantInt x) -> [x] - RangeBounded (ConstantInt x) (ConstantInt y) -> [x..y] -======= - RangeSingle (ConstantInt _ x) -> [x] - RangeBounded (ConstantInt _ x) (ConstantInt _ y) -> [x..y] ->>>>>>> taggedints - _ -> bug ("ExplicitVarSizeWithDummy.calcDummyElemC" <+> pretty r) - ] - calcDummyElemC d = bug ("ExplicitVarSizeWithDummy.calcDummyElemC" <+> pretty d) - - downD :: TypeOf_DownD m - downD (name, domain@(DomainSet Set_ExplicitVarSizeWithDummy (SetAttr attrs) innerDomain@DomainInt{})) = do - let domainWithDummy = calcDummyDomain innerDomain - maxSize <- dropTag <$> getMaxSize attrs innerDomain - return $ Just - [ ( outName domain name - , DomainMatrix -<<<<<<< HEAD - (DomainInt Nothing [RangeBounded 1 maxSize]) -||||||| merged common ancestors - (DomainInt [RangeBounded 1 maxSize]) -======= - (DomainInt NoTag [RangeBounded 1 maxSize]) ->>>>>>> taggedints - domainWithDummy - ) ] - downD _ = na "{downD} ExplicitVarSizeWithDummy" - - structuralCons :: TypeOf_Structural m - structuralCons f downX1 (DomainSet Set_ExplicitVarSizeWithDummy (SetAttr attrs) innerDomain) = do - maxSize <- dropTag <$> getMaxSize attrs innerDomain - let - dummyElem = calcDummyElem innerDomain - - ordering m = do - (iPat, i) <- quantifiedVar - return $ return -- for list - [essence| - forAll &iPat : int(1..&maxSize-1) . - (&m[&i] .< &m[&i+1]) \/ (&m[&i] = &dummyElem) - |] - - dummyToTheRight m = do - (iPat, i) <- quantifiedVar - return $ return -- for list - [essence| - forAll &iPat : int(1..&maxSize-1) . - (&m[&i] = &dummyElem) -> (&m[&i+1] = &dummyElem) - |] - - cardinality m = do - (iPat, i) <- quantifiedVar - return [essence| sum &iPat : int(1..&maxSize) . toInt(&m[&i] != &dummyElem) |] - - innerStructuralCons m = do - (iPat, i) <- quantifiedVarOverDomain [essenceDomain| int(1..&maxSize) |] - let activeZone b = [essence| forAll &iPat : int(1..&maxSize) . &m[&i] != &dummyElem -> &b |] - - -- preparing structural constraints for the inner guys - innerStructuralConsGen <- f innerDomain - - let inLoop = [essence| &m[&i] |] - outs <- innerStructuralConsGen inLoop - return (map activeZone outs) - - return $ \ ref -> do - refs <- downX1 ref - case refs of - [m] -> - concat <$> sequence - [ ordering m - , dummyToTheRight m - , mkSizeCons attrs <$> cardinality m - , innerStructuralCons m - ] - _ -> na "{structuralCons} ExplicitVarSizeWithDummy" - structuralCons _ _ _ = na "{structuralCons} ExplicitVarSizeWithDummy" - - downC :: TypeOf_DownC m - downC ( name - , domain@(DomainSet Set_ExplicitVarSizeWithDummy (SetAttr attrs) innerDomain) - , ConstantAbstract (AbsLitSet constants) - ) = do - maxSize <- dropTag <$> getMaxSize attrs innerDomain - let indexDomain i = mkDomainIntB (fromInt i) maxSize - maxSizeInt <- - case maxSize of -<<<<<<< HEAD - ConstantInt Nothing x -> return x -||||||| merged common ancestors - ConstantInt x -> return x -======= - ConstantInt _ x -> return x ->>>>>>> taggedints - _ -> fail $ vcat - [ "Expecting an integer for the maxSize attribute." - , "But got:" <+> pretty maxSize - , "When working on:" <+> pretty name - , "With domain:" <+> pretty domain - ] - let dummyElem = calcDummyElemC innerDomain - let dummies = replicate (fromInteger (maxSizeInt - genericLength constants)) dummyElem - return $ Just - [ ( outName domain name - , DomainMatrix (indexDomain 1) innerDomain - , ConstantAbstract $ AbsLitMatrix (indexDomain 1) (constants ++ dummies) - ) - ] - downC _ = na "{downC} ExplicitVarSizeWithDummy" - - up :: TypeOf_Up m - up ctxt (name, domain@(DomainSet Set_ExplicitVarSizeWithDummy _ innerDomain)) = do - let dummyElem = calcDummyElemC innerDomain - case lookup (outName domain name) ctxt of - Nothing -> fail $ vcat $ - [ "(in Set ExplicitVarSizeWithDummy up)" - , "No value for:" <+> pretty (outName domain name) - , "When working on:" <+> pretty name - , "With domain:" <+> pretty domain - ] ++ - ("Bindings in context:" : prettyContext ctxt) - Just constant -> - case viewConstantMatrix constant of - Just (_, vals) -> - return (name, ConstantAbstract (AbsLitSet [ v | v <- vals, v /= dummyElem ])) - _ -> fail $ vcat - [ "Expecting a matrix literal for:" <+> pretty (outName domain name) - , "But got:" <+> pretty constant - , "When working on:" <+> pretty name - , "With domain:" <+> pretty domain - ] - up _ _ = na "{up} ExplicitVarSizeWithDummy" diff --git a/src/Conjure/Representations/Set/ExplicitVarSizeWithFlags.hs.orig b/src/Conjure/Representations/Set/ExplicitVarSizeWithFlags.hs.orig deleted file mode 100644 index 302e8aa265..0000000000 --- a/src/Conjure/Representations/Set/ExplicitVarSizeWithFlags.hs.orig +++ /dev/null @@ -1,192 +0,0 @@ -{-# LANGUAGE QuasiQuotes #-} - -module Conjure.Representations.Set.ExplicitVarSizeWithFlags ( setExplicitVarSizeWithFlags ) where - --- conjure -import Conjure.Prelude -import Conjure.Language -import Conjure.Language.DomainSizeOf -import Conjure.Language.Expression.DomainSizeOf () -import Conjure.Language.ZeroVal ( zeroVal, EnumerateDomain ) -import Conjure.Representations.Internal -import Conjure.Representations.Common - - -setExplicitVarSizeWithFlags :: forall m . (MonadFail m, NameGen m, EnumerateDomain m) => Representation m -setExplicitVarSizeWithFlags = Representation chck downD structuralCons downC up - - where - - chck :: TypeOf_ReprCheck m - chck _ (DomainSet _ (SetAttr SizeAttr_Size{}) _) = return [] - chck f (DomainSet _ attrs innerDomain) = - map (DomainSet Set_ExplicitVarSizeWithFlags attrs) <$> f innerDomain - chck _ _ = return [] - - nameFlag = mkOutName (Just "Flags") - nameValues = mkOutName (Just "Values") - - getMaxSize attrs innerDomain = case attrs of - SizeAttr_MaxSize x -> return x - SizeAttr_MinMaxSize _ x -> return x - _ -> domainSizeOf innerDomain - - - downD :: TypeOf_DownD m - downD (name, domain@(DomainSet _ (SetAttr attrs) innerDomain)) = do - maxSize <- getMaxSize attrs innerDomain - let indexDomain = mkDomainIntB 1 maxSize - return $ Just - [ ( nameFlag domain name - , DomainMatrix (forgetRepr indexDomain) DomainBool - ) - , ( nameValues domain name - , DomainMatrix (forgetRepr indexDomain) innerDomain - ) - ] - downD _ = na "{downD} ExplicitVarSizeWithFlags" - - structuralCons :: TypeOf_Structural m - structuralCons f downX1 (DomainSet Set_ExplicitVarSizeWithFlags (SetAttr attrs) innerDomain) = do - maxSize <- dropTag <$> getMaxSize attrs innerDomain - let - orderingWhenFlagged flags values = do - (iPat, i) <- quantifiedVar - return $ return $ -- list - [essence| - forAll &iPat : int(1..&maxSize-1) . &flags[&i+1] -> &values[&i] .< &values[&i+1] - |] - - dontCareWhenNotFlagged flags values = do - (iPat, i) <- quantifiedVar - return $ return $ -- list - [essence| - forAll &iPat : int(1..&maxSize) . &flags[&i] = false -> dontCare(&values[&i]) - |] - - flagsToTheLeft flags = do - (iPat, i) <- quantifiedVar - return $ return $ -- list - [essence| - forAll &iPat : int(1..&maxSize-1) . &flags[&i+1] -> &flags[&i] - |] - - cardinality flags = do - (iPat, i) <- quantifiedVar - return [essence| sum &iPat : int(1..&maxSize) . toInt(&flags[&i]) |] - - innerStructuralCons flags values = do - (iPat, i) <- quantifiedVarOverDomain [essenceDomain| int(1..&maxSize) |] - let activeZone b = [essence| forAll &iPat : int(1..&maxSize) . &flags[&i] -> &b |] - - -- preparing structural constraints for the inner guys - innerStructuralConsGen <- f innerDomain - - let inLoop = [essence| &values[&i] |] - outs <- innerStructuralConsGen inLoop - return (map activeZone outs) - - return $ \ set -> do - refs <- downX1 set - case refs of - [flags, values] -> - concat <$> sequence - [ orderingWhenFlagged flags values - , dontCareWhenNotFlagged flags values - , flagsToTheLeft flags - , mkSizeCons attrs <$> cardinality flags - , innerStructuralCons flags values - ] - _ -> na "{structuralCons} ExplicitVarSizeWithFlags" - - structuralCons _ _ _ = na "{structuralCons} ExplicitVarSizeWithFlags" - - downC :: TypeOf_DownC m - downC ( name - , domain@(DomainSet _ (SetAttr attrs) innerDomain) - , ConstantAbstract (AbsLitSet constants) - ) = do - maxSize <- getMaxSize attrs innerDomain - let indexDomain = mkDomainIntB 1 maxSize - - maxSizeInt <- - case maxSize of -<<<<<<< HEAD - ConstantInt Nothing x -> return x -||||||| merged common ancestors - ConstantInt x -> return x -======= - ConstantInt _ x -> return x ->>>>>>> taggedints - _ -> fail $ vcat - [ "Expecting an integer for the maxSize attribute." - , "But got:" <+> pretty maxSize - , "When working on:" <+> pretty name - , "With domain:" <+> pretty domain - ] - z <- zeroVal innerDomain - let zeroes = replicate (fromInteger (maxSizeInt - genericLength constants)) z - - let trues = replicate (length constants) (ConstantBool True) - let falses = replicate (fromInteger (maxSizeInt - genericLength constants)) (ConstantBool False) - - return $ Just - [ ( nameFlag domain name - , DomainMatrix - (forgetRepr indexDomain) - DomainBool - , ConstantAbstract $ AbsLitMatrix - (forgetRepr indexDomain) - (trues ++ falses) - ) - , ( nameValues domain name - , DomainMatrix - (forgetRepr indexDomain) - innerDomain - , ConstantAbstract $ AbsLitMatrix - (forgetRepr indexDomain) - (constants ++ zeroes) - ) - ] - downC _ = na "{downC} ExplicitVarSizeWithFlags" - - up :: TypeOf_Up m - up ctxt (name, domain) = - case (lookup (nameFlag domain name) ctxt, lookup (nameValues domain name) ctxt) of - (Just flagMatrix, Just constantMatrix) -> - case viewConstantMatrix flagMatrix of - -- TODO: check if indices match - Just (_, flags) -> - case viewConstantMatrix constantMatrix of - Just (_, vals) -> - return (name, ConstantAbstract $ AbsLitSet - [ v - | (i,v) <- zip flags vals - , viewConstantBool i == Just True - ] ) - _ -> fail $ vcat - [ "Expecting a matrix literal for:" <+> pretty (nameValues domain name) - , "But got:" <+> pretty constantMatrix - , "When working on:" <+> pretty name - , "With domain:" <+> pretty domain - ] - _ -> fail $ vcat - [ "Expecting a matrix literal for:" <+> pretty (nameFlag domain name) - , "But got:" <+> pretty flagMatrix - , "When working on:" <+> pretty name - , "With domain:" <+> pretty domain - ] - (Nothing, _) -> fail $ vcat $ - [ "(in Set ExplicitVarSizeWithFlags up 1)" - , "No value for:" <+> pretty (nameFlag domain name) - , "When working on:" <+> pretty name - , "With domain:" <+> pretty domain - ] ++ - ("Bindings in context:" : prettyContext ctxt) - (_, Nothing) -> fail $ vcat $ - [ "(in Set ExplicitVarSizeWithFlags up 2)" - , "No value for:" <+> pretty (nameValues domain name) - , "When working on:" <+> pretty name - , "With domain:" <+> pretty domain - ] ++ - ("Bindings in context:" : prettyContext ctxt) diff --git a/src/Conjure/Representations/Set/ExplicitVarSizeWithMarker.hs.orig b/src/Conjure/Representations/Set/ExplicitVarSizeWithMarker.hs.orig deleted file mode 100644 index 4510b0818f..0000000000 --- a/src/Conjure/Representations/Set/ExplicitVarSizeWithMarker.hs.orig +++ /dev/null @@ -1,177 +0,0 @@ -{-# LANGUAGE QuasiQuotes #-} - -module Conjure.Representations.Set.ExplicitVarSizeWithMarker ( setExplicitVarSizeWithMarker ) where - --- conjure -import Conjure.Prelude -import Conjure.Language -import Conjure.Language.DomainSizeOf -import Conjure.Language.Expression.DomainSizeOf () -import Conjure.Language.ZeroVal ( zeroVal, EnumerateDomain ) -import Conjure.Representations.Internal -import Conjure.Representations.Common - - -setExplicitVarSizeWithMarker :: forall m . (MonadFail m, NameGen m, EnumerateDomain m) => Representation m -setExplicitVarSizeWithMarker = Representation chck downD structuralCons downC up - - where - - chck :: TypeOf_ReprCheck m - chck _ (DomainSet _ (SetAttr SizeAttr_Size{}) _) = return [] - chck f (DomainSet _ attrs innerDomain) = map (DomainSet Set_ExplicitVarSizeWithMarker attrs) <$> f innerDomain - chck _ _ = return [] - - nameMarker = mkOutName (Just "Marker") - nameValues = mkOutName (Just "Values") - - getMaxSize attrs innerDomain = case attrs of - SizeAttr_MaxSize x -> return x - SizeAttr_MinMaxSize _ x -> return x - _ -> domainSizeOf innerDomain - - downD :: TypeOf_DownD m - downD (name, domain@(DomainSet _ (SetAttr attrs) innerDomain)) = do - maxSize <- getMaxSize attrs innerDomain - let indexDomain i = mkDomainIntB (fromInt i) maxSize - return $ Just - [ ( nameMarker domain name - , defRepr (indexDomain 0) - ) - , ( nameValues domain name - , DomainMatrix (indexDomain 1) innerDomain - ) - ] - downD _ = na "{downD} ExplicitVarSizeWithMarker" - - structuralCons :: TypeOf_Structural m - structuralCons f downX1 (DomainSet Set_ExplicitVarSizeWithMarker (SetAttr attrs) innerDomain) = do - maxSize <- dropTag <$> getMaxSize attrs innerDomain - let - orderingUpToMarker marker values = do - (iPat, i) <- quantifiedVar - return $ return $ -- list - [essence| - forAll &iPat : int(1..&maxSize-1) . &i + 1 <= &marker -> - &values[&i] .< &values[&i+1] - |] - - dontCareAfterMarker marker values = do - (iPat, i) <- quantifiedVar - return $ return $ -- list - [essence| - forAll &iPat : int(1..&maxSize) . &i > &marker -> - dontCare(&values[&i]) - |] - - innerStructuralCons marker values = do - let overDomain = [essenceDomain| int(1..&maxSize) |] - (iPat, i) <- quantifiedVarOverDomain overDomain - let activeZone b = [essence| forAll &iPat : &overDomain . &i <= &marker -> &b |] - - -- preparing structural constraints for the inner guys - innerStructuralConsGen <- f innerDomain - - let inLoop = [essence| &values[&i] |] - outs <- innerStructuralConsGen inLoop - return (map activeZone outs) - - return $ \ set -> do - refs <- downX1 set - case refs of - [marker,values] -> - concat <$> sequence - [ orderingUpToMarker marker values - , dontCareAfterMarker marker values - , return (mkSizeCons attrs marker) - , innerStructuralCons marker values - ] - _ -> na "{structuralCons} ExplicitVarSizeWithMarker" - - structuralCons _ _ _ = na "{structuralCons} ExplicitVarSizeWithMarker" - - downC :: TypeOf_DownC m - downC ( name - , domain@(DomainSet _ (SetAttr attrs) innerDomain) - , ConstantAbstract (AbsLitSet constants) - ) = do - maxSize <- getMaxSize attrs innerDomain - let indexDomain i = mkDomainIntB (fromInt i) maxSize - maxSizeInt <- - case maxSize of -<<<<<<< HEAD - ConstantInt Nothing x -> return x -||||||| merged common ancestors - ConstantInt x -> return x -======= - ConstantInt _ x -> return x ->>>>>>> taggedints - _ -> fail $ vcat - [ "Expecting an integer for the maxSize attribute." - , "But got:" <+> pretty maxSize - , "When working on:" <+> pretty name - , "With domain:" <+> pretty domain - ] - z <- zeroVal innerDomain - let zeroes = replicate (fromInteger (maxSizeInt - genericLength constants)) z - return $ Just - [ ( nameMarker domain name - , defRepr (indexDomain 0) -<<<<<<< HEAD - , ConstantInt Nothing (genericLength constants) -||||||| merged common ancestors - , ConstantInt (genericLength constants) -======= - , ConstantInt NoTag (genericLength constants) ->>>>>>> taggedints - ) - , ( nameValues domain name - , DomainMatrix (indexDomain 1) innerDomain - , ConstantAbstract $ AbsLitMatrix (indexDomain 1) (constants ++ zeroes) - ) - ] - downC _ = na "{downC} ExplicitVarSizeWithMarker" - - up :: TypeOf_Up m - up ctxt (name, domain) = - case (lookup (nameMarker domain name) ctxt, lookup (nameValues domain name) ctxt) of - (Just marker, Just constantMatrix) -> - case marker of -<<<<<<< HEAD - ConstantInt Nothing card -> -||||||| merged common ancestors - ConstantInt card -> -======= - ConstantInt _ card -> ->>>>>>> taggedints - case (viewConstantMatrix constantMatrix, constantMatrix) of - (Just (_, vals), _) -> - return (name, ConstantAbstract (AbsLitSet (genericTake card vals))) - (_, ConstantUndefined msg ty) -> -- undefined propagates - return (name, ConstantUndefined ("Set-ExplicitVarSizeWithMarker " `mappend` msg) ty) - _ -> fail $ vcat - [ "Expecting a matrix literal for:" <+> pretty (nameValues domain name) - , "But got:" <+> pretty constantMatrix - , "When working on:" <+> pretty name - , "With domain:" <+> pretty domain - ] - _ -> fail $ vcat - [ "Expecting an integer literal for:" <+> pretty (nameMarker domain name) - , "But got:" <+> pretty marker - , "When working on:" <+> pretty name - , "With domain:" <+> pretty domain - ] - (Nothing, _) -> fail $ vcat $ - [ "(in Set ExplicitVarSizeWithMarker up 1)" - , "No value for:" <+> pretty (nameMarker domain name) - , "When working on:" <+> pretty name - , "With domain:" <+> pretty domain - ] ++ - ("Bindings in context:" : prettyContext ctxt) - (_, Nothing) -> fail $ vcat $ - [ "(in Set ExplicitVarSizeWithMarker up 2)" - , "No value for:" <+> pretty (nameValues domain name) - , "When working on:" <+> pretty name - , "With domain:" <+> pretty domain - ] ++ - ("Bindings in context:" : prettyContext ctxt) diff --git a/src/Conjure/Representations/Set/Occurrence.hs.orig b/src/Conjure/Representations/Set/Occurrence.hs.orig deleted file mode 100644 index 1c85f7b8a5..0000000000 --- a/src/Conjure/Representations/Set/Occurrence.hs.orig +++ /dev/null @@ -1,117 +0,0 @@ -{-# LANGUAGE QuasiQuotes #-} - -module Conjure.Representations.Set.Occurrence ( setOccurrence ) where - --- conjure -import Conjure.Prelude -import Conjure.Language -import Conjure.Representations.Internal -import Conjure.Representations.Common - - -setOccurrence :: forall m . (MonadFail m, NameGen m) => Representation m -setOccurrence = Representation chck downD structuralCons downC up - - where - - -- | We can only represent Set of Int as occurrence - chck :: TypeOf_ReprCheck m - chck f (DomainSet _ attrs innerDomain@DomainInt{}) = - map (DomainSet Set_Occurrence attrs) <$> f innerDomain - chck _ _ = return [] - - outName :: Domain HasRepresentation x -> Name -> Name - outName = mkOutName Nothing - - -- | Matrix of Bool indexed by inner domain of set (which must be an int domain) - downD :: TypeOf_DownD m - downD (name, domain@(DomainSet Set_Occurrence _attrs innerDomain@DomainInt{})) = return $ Just - [ ( outName domain name - , DomainMatrix (forgetRepr innerDomain) DomainBool - ) - ] - downD _ = na "{downD} Occurrence" - - -- | Constrain number of trues in matrix to be congruent with cardinality constraint - structuralCons :: TypeOf_Structural m - structuralCons _ downX1 (DomainSet Set_Occurrence (SetAttr attrs) innerDomain@DomainInt{}) = - return $ \ set -> do - refs <- downX1 set - case refs of - [m] -> do - (iPat, i) <- quantifiedVar - let cardinality = [essence| sum &iPat : &innerDomain . toInt(&m[&i]) |] - return (mkSizeCons attrs cardinality) - _ -> na "{structuralCons} Occurrence" - structuralCons _ _ _ = na "{structuralCons} Occurrence" - - -- | If value is in the set then that value's index maps to a bool - downC :: TypeOf_DownC m - downC ( name -<<<<<<< HEAD - , domain@(DomainSet Set_Occurrence _attrs innerDomain@(DomainInt _ intRanges)) -||||||| merged common ancestors - , domain@(DomainSet Set_Occurrence _attrs innerDomain@(DomainInt intRanges)) -======= - , domain@(DomainSet Set_Occurrence _attrs innerDomain@(DomainInt t intRanges)) ->>>>>>> taggedints - , ConstantAbstract (AbsLitSet constants) - ) = do - innerDomainVals <- valuesInIntDomain intRanges - return $ Just - [ ( outName domain name - , DomainMatrix (forgetRepr innerDomain) DomainBool - , ConstantAbstract $ AbsLitMatrix (forgetRepr innerDomain) - [ ConstantBool isIn - | v <- innerDomainVals -<<<<<<< HEAD - , let isIn = ConstantInt Nothing v `elem` constants -||||||| merged common ancestors - , let isIn = ConstantInt v `elem` constants -======= - , let isIn = ConstantInt t v `elem` constants ->>>>>>> taggedints - ] - ) - ] - downC _ = na "{downC} Occurrence" - - -- | Reversal of downC - if innerDom value zips with matrix true then it's in - up :: TypeOf_Up m -<<<<<<< HEAD - up ctxt (name, domain@(DomainSet _ _ (DomainInt _ intRanges)))= -||||||| merged common ancestors - up ctxt (name, domain@(DomainSet _ _ (DomainInt intRanges)))= -======= - up ctxt (name, domain@(DomainSet _ _ (DomainInt t intRanges)))= ->>>>>>> taggedints - case lookup (outName domain name) ctxt of - Just constantMatrix -> - case viewConstantMatrix constantMatrix of - Just (_, vals) -> do - innerDomainVals <- valuesInIntDomain intRanges - return (name, ConstantAbstract $ AbsLitSet -<<<<<<< HEAD - [ ConstantInt Nothing v -||||||| merged common ancestors - [ ConstantInt v -======= - [ ConstantInt t v ->>>>>>> taggedints - | (v,b) <- zip innerDomainVals vals - , viewConstantBool b == Just True - ] ) - _ -> fail $ vcat - [ "Expecting a matrix literal for:" <+> pretty (outName domain name) - , "But got:" <+> pretty constantMatrix - , "When working on:" <+> pretty name - , "With domain:" <+> pretty domain - ] - Nothing -> fail $ vcat $ - [ "(in Set Occurrence up)" - , "No value for:" <+> pretty (outName domain name) - , "When working on:" <+> pretty name - , "With domain:" <+> pretty domain - ] ++ - ("Bindings in context:" : prettyContext ctxt) - up _ _ = na "{up} Occurrence" diff --git a/src/Conjure/Rules/DontCare.hs.orig b/src/Conjure/Rules/DontCare.hs.orig deleted file mode 100644 index a575b3d9d8..0000000000 --- a/src/Conjure/Rules/DontCare.hs.orig +++ /dev/null @@ -1,178 +0,0 @@ -{-# LANGUAGE QuasiQuotes #-} - -module Conjure.Rules.DontCare where - -import Conjure.Rules.Import -import Conjure.Process.Enumerate ( EnumerateDomain ) - - -rule_Bool :: Rule -rule_Bool = "dontCare-bool" `namedRule` theRule where - theRule p = do - x <- match opDontCare p - DomainBool <- domainOf x - return - ( "dontCare value for bools is false." - , return $ make opEq x (fromBool False) - ) - - -rule_Int :: Rule -rule_Int = "dontCare-int" `namedRule` theRule where - theRule p = do -<<<<<<< HEAD - x <- match opDontCare p - TypeInt _ <- typeOf x - xDomain <- domainOf x -||||||| merged common ancestors - x <- match opDontCare p - TypeInt <- typeOf x - xDomain <- domainOf x -======= - x <- match opDontCare p - TypeInt _ <- typeOf x - xDomain <- domainOf x ->>>>>>> taggedints - let raiseBug = bug ("dontCare on domain:" <+> pretty xDomain) - let val = case xDomain of - DomainInt _ [] -> raiseBug - DomainInt _ (r:_) -> case r of - RangeOpen -> raiseBug - RangeSingle v -> v - RangeLowerBounded v -> v - RangeUpperBounded v -> v - RangeBounded v _ -> v - DomainIntE _ v -> [essence| min(&v) |] - _ -> raiseBug - return - ( "dontCare value for this integer is" <+> pretty val - , return $ make opEq x val - ) - - -rule_Tuple :: Rule -rule_Tuple = "dontCare-tuple" `namedRule` theRule where - theRule p = do - x <- match opDontCare p - TypeTuple{} <- typeOf x - xs <- downX1 x - return - ( "dontCare handling for tuple" - , return $ make opAnd $ fromList $ map (make opDontCare) xs - ) - - -rule_Record :: Rule -rule_Record = "dontCare-record" `namedRule` theRule where - theRule p = do - x <- match opDontCare p - TypeRecord{} <- typeOf x - xs <- downX1 x - return - ( "dontCare handling for record" - , return $ make opAnd $ fromList $ map (make opDontCare) xs - ) - - -rule_Variant :: Rule -rule_Variant = "dontCare-variant" `namedRule` theRule where - theRule p = do - x <- match opDontCare p - TypeVariant{} <- typeOf x - xs <- downX1 x - return - ( "dontCare handling for variant" - , return $ make opAnd $ fromList $ map (make opDontCare) xs - ) - - -rule_Matrix :: Rule -rule_Matrix = "dontCare-matrix" `namedRule` theRule where - theRule p = do - x <- match opDontCare p - DomainMatrix index _ <- domainOf x - return - ( "dontCare handling for matrix" - , do - (iPat, i) <- quantifiedVar - return [essence| forAll &iPat : &index . dontCare(&x[&i]) |] - ) - - -rule_Abstract :: Rule -rule_Abstract = "dontCare-abstract" `namedRule` theRule where - theRule p = do - x <- match opDontCare p - ty <- typeOf x - case ty of - TypeSet {} -> return () - TypeMSet {} -> return () - TypeSequence {} -> return () - TypeFunction {} -> return () - TypeRelation {} -> return () - TypePartition{} -> return () - _ -> na "not a known abstract domain" - hasRepresentation x - xs <- downX1 x - return - ( "dontCare handling for an abstract domain" - , return $ make opAnd $ fromList $ map (make opDontCare) xs - ) - - -handleDontCares :: - MonadFail m => - NameGen m => - EnumerateDomain m => - Expression -> m Expression -handleDontCares p = - case match opDontCare p of - Nothing -> return p - Just x -> do - typX <- typeOf x - case typX of - TypeBool -> return (make opEq x (fromBool False)) - TypeInt _ -> do - domX <- domainOf x - let raiseBug = bug ("dontCare on domain:" <+> pretty domX) - let val = case domX of - DomainInt _ [] -> raiseBug - DomainInt _ (r:_) -> case r of - RangeOpen -> raiseBug - RangeSingle v -> v - RangeLowerBounded v -> v - RangeUpperBounded v -> v - RangeBounded v _ -> v - DomainIntE _ v -> [essence| min(&v) |] - _ -> raiseBug - return $ make opEq x val - TypeTuple{} -> do - xs <- downX1 x - xs' <- mapM (handleDontCares . make opDontCare) xs - return $ make opAnd $ fromList xs' - TypeRecord{} -> do - xs <- downX1 x - xs' <- mapM (handleDontCares . make opDontCare) xs - return $ make opAnd $ fromList xs' - TypeVariant{} -> do - xs <- downX1 x - xs' <- mapM (handleDontCares . make opDontCare) xs - return $ make opAnd $ fromList xs' - TypeMatrix{} -> do - domX <- domainOf x - case domX of - DomainMatrix index _ -> do - (iPat@(Single nm), _) <- quantifiedVar - -- direct name resolution - let i = Reference nm (Just (DeclNoRepr Find nm index NoRegion)) - inner <- handleDontCares [essence| dontCare(&x[&i]) |] - return [essence| forAll &iPat : &index . &inner |] - _ -> bug ("dontCare on domain, expecting matrix, but got:" <+> pretty domX) - _ -> do - case representationOf x of - Nothing -> fail "doesn't seem to have a representation, during handleDontCares" - Just _ -> do - xs <- downX1 x - xs' <- mapM (handleDontCares . make opDontCare) xs - return $ make opAnd $ fromList xs' - diff --git a/src/Conjure/Rules/Horizontal/Function.hs.orig b/src/Conjure/Rules/Horizontal/Function.hs.orig deleted file mode 100644 index 61f79c3a28..0000000000 --- a/src/Conjure/Rules/Horizontal/Function.hs.orig +++ /dev/null @@ -1,874 +0,0 @@ -{-# LANGUAGE QuasiQuotes #-} - -module Conjure.Rules.Horizontal.Function where - -import Conjure.Rules.Import -import Conjure.Rules.Definition - --- uniplate -import Data.Generics.Uniplate.Zipper as Zipper ( up, hole ) - - -rule_Comprehension_Literal :: Rule -rule_Comprehension_Literal = "function-comprehension-literal" `namedRule` theRule where - theRule (Comprehension body gensOrConds) = do - (gocBefore, (pat, expr), gocAfter) <- matchFirst gensOrConds $ \ goc -> case goc of - Generator (GenInExpr pat@Single{} expr) -> return (pat, matchDefs [opToSet,opToMSet,opToRelation] expr) - _ -> na "rule_Comprehension_Literal" - (TypeFunction fr to, elems) <- match functionLiteral expr - let outLiteral = make matrixLiteral -<<<<<<< HEAD - (TypeMatrix (TypeInt Nothing) (TypeTuple [fr,to])) - (DomainInt Nothing [RangeBounded 1 (fromInt (genericLength elems))]) -||||||| merged common ancestors - (TypeMatrix TypeInt (TypeTuple [fr,to])) - (DomainInt [RangeBounded 1 (fromInt (genericLength elems))]) -======= - (TypeMatrix (TypeInt NoTag) (TypeTuple [fr,to])) - (DomainInt NoTag [RangeBounded 1 (fromInt (genericLength elems))]) ->>>>>>> taggedints - [ AbstractLiteral (AbsLitTuple [a,b]) - | (a,b) <- elems - ] - let upd val old = lambdaToFunction pat old val - return - ( "Comprehension on function literals" - , do - (iPat, i) <- quantifiedVar - return $ Comprehension (upd i body) - $ gocBefore - ++ [Generator (GenInExpr iPat outLiteral)] - ++ transformBi (upd i) gocAfter - ) - theRule _ = na "rule_Comprehension_Literal" - - -rule_Eq :: Rule -rule_Eq = "function-eq" `namedRule` theRule where - theRule [essence| &x = &y |] = do - case x of WithLocals{} -> na "bubble-delay" ; _ -> return () - case y of WithLocals{} -> na "bubble-delay" ; _ -> return () - TypeFunction{} <- typeOf x - TypeFunction{} <- typeOf y - return - ( "Horizontal rule for function equality" - , do - (iPat, i) <- quantifiedVar - return [essence| - (forAll &iPat in &x . &y(&i[1]) = &i[2]) - /\ - (forAll &iPat in &y . &x(&i[1]) = &i[2]) - |] - ) - theRule _ = na "rule_Eq" - - -rule_Neq :: Rule -rule_Neq = "function-neq" `namedRule` theRule where - theRule [essence| &x != &y |] = do - case x of WithLocals{} -> na "bubble-delay" ; _ -> return () - case y of WithLocals{} -> na "bubble-delay" ; _ -> return () - TypeFunction{} <- typeOf x - TypeFunction{} <- typeOf y - return - ( "Horizontal rule for function dis-equality" - , do - (iPat, i) <- quantifiedVar - return [essence| - (exists &iPat in &x . !(&i in &y)) - \/ - (exists &iPat in &y . !(&i in &x)) - |] - ) - theRule _ = na "rule_Neq" - - -rule_SubsetEq :: Rule -rule_SubsetEq = "function-subsetEq" `namedRule` theRule where - theRule [essence| &x subsetEq &y |] = do - case x of WithLocals{} -> na "bubble-delay" ; _ -> return () - case y of WithLocals{} -> na "bubble-delay" ; _ -> return () - TypeFunction{} <- typeOf x - TypeFunction{} <- typeOf y - return - ( "Horizontal rule for function subsetEq" - , do - (iPat, i) <- quantifiedVar - return [essence| - (forAll &iPat in &x . &y(&i[1]) = &i[2]) - |] - ) - theRule _ = na "rule_SubsetEq" - - -rule_Subset :: Rule -rule_Subset = "function-subset" `namedRule` theRule where - theRule [essence| &x subset &y |] = do - case x of WithLocals{} -> na "bubble-delay" ; _ -> return () - case y of WithLocals{} -> na "bubble-delay" ; _ -> return () - TypeFunction{} <- typeOf x - TypeFunction{} <- typeOf y - return - ( "Horizontal rule for function subset" - , return [essence| &x subsetEq &y /\ &x != &y |] - ) - theRule _ = na "rule_Subset" - - -rule_Supset :: Rule -rule_Supset = "function-supset" `namedRule` theRule where - theRule [essence| &x supset &y |] = do - case x of WithLocals{} -> na "bubble-delay" ; _ -> return () - case y of WithLocals{} -> na "bubble-delay" ; _ -> return () - TypeFunction{} <- typeOf x - TypeFunction{} <- typeOf y - return - ( "Horizontal rule for function supset" - , return [essence| &y subset &x |] - ) - theRule _ = na "rule_Supset" - - -rule_SupsetEq :: Rule -rule_SupsetEq = "function-subsetEq" `namedRule` theRule where - theRule [essence| &x supsetEq &y |] = do - case x of WithLocals{} -> na "bubble-delay" ; _ -> return () - case y of WithLocals{} -> na "bubble-delay" ; _ -> return () - TypeFunction{} <- typeOf x - TypeFunction{} <- typeOf y - return - ( "Horizontal rule for function supsetEq" - , return [essence| &y subsetEq &x |] - ) - theRule _ = na "rule_SupsetEq" - - -rule_DotLt :: Rule -rule_DotLt = "function-DotLt" `namedRule` theRule where - theRule p = do - (a,b) <- match opDotLt p - TypeFunction{} <- typeOf a - TypeFunction{} <- typeOf b - sameRepresentation a b - ma <- tupleLitIfNeeded <$> downX1 a - mb <- tupleLitIfNeeded <$> downX1 b - return - ( "Horizontal rule for function .<" <+> pretty (make opDotLt ma mb) - , return $ make opDotLt ma mb - ) - - -rule_DotLeq :: Rule -rule_DotLeq = "function-DotLeq" `namedRule` theRule where - theRule p = do - (a,b) <- match opDotLeq p - TypeFunction{} <- typeOf a - TypeFunction{} <- typeOf b - sameRepresentation a b - ma <- tupleLitIfNeeded <$> downX1 a - mb <- tupleLitIfNeeded <$> downX1 b - return - ( "Horizontal rule for function .<=" <+> pretty (make opDotLeq ma mb) - , return $ make opDotLeq ma mb - ) - - -rule_Inverse :: Rule -rule_Inverse = "function-inverse" `namedRule` theRule where - theRule [essence| inverse(&a, &b) |] = do - case a of WithLocals{} -> na "bubble-delay" ; _ -> return () - case b of WithLocals{} -> na "bubble-delay" ; _ -> return () - TypeFunction{} <- typeOf a - TypeFunction{} <- typeOf b - return - ( "Horizontal rule for function inverse" - , do - (iPat, i) <- quantifiedVar - return - [essence| - (forAll &iPat in &a . &b(&i[2]) = &i[1]) - /\ - (forAll &iPat in &b . &a(&i[2]) = &i[1]) - |] - ) - theRule _ = na "rule_Inverse" - - -rule_Comprehension_PreImage :: Rule -rule_Comprehension_PreImage = "function-preImage" `namedRule` theRule where - theRule (Comprehension body gensOrConds) = do - (gocBefore, (pat, expr), gocAfter) <- matchFirst gensOrConds $ \ goc -> case goc of - Generator (GenInExpr pat@Single{} expr) -> return (pat, matchDefs [opToSet,opToMSet] expr) - _ -> na "rule_Comprehension_PreImage" - (func, img) <- match opPreImage expr - TypeFunction{} <- typeOf func - let upd val old = lambdaToFunction pat old val - return - ( "Mapping over the preImage of a function" - , do - (jPat, j) <- quantifiedVar - let val = [essence| &j[1] |] - return $ - Comprehension - (upd val body) - $ gocBefore - ++ [ Generator (GenInExpr jPat func) - , Condition [essence| &j[2] = &img |] - ] - ++ transformBi (upd val) gocAfter - ) - theRule _ = na "rule_Comprehension_PreImage" - - -rule_Card :: Rule -rule_Card = "function-cardinality" `namedRule` theRule where - theRule [essence| |&f| |] = do - TypeFunction{} <- typeOf f - dom <- domainOf f - return - ( "Function cardinality" - , case dom of - DomainFunction _ (FunctionAttr (SizeAttr_Size n) _ _) _ _ - -> return n - DomainFunction _ (FunctionAttr _ _ jectivity) _ innerTo - | jectivity `elem` [JectivityAttr_Surjective, JectivityAttr_Bijective] - -> domainSizeOf innerTo - DomainFunction _ (FunctionAttr _ PartialityAttr_Total _) innerFr _ - -> domainSizeOf innerFr - _ -> return [essence| |toSet(&f)| |] - ) - theRule _ = na "rule_Card" - - -rule_Comprehension_Defined :: Rule -rule_Comprehension_Defined = "function-defined" `namedRule` theRule where - theRule (Comprehension body gensOrConds) = do - (gocBefore, (pat, expr), gocAfter) <- matchFirst gensOrConds $ \ goc -> case goc of - Generator (GenInExpr pat@Single{} expr) -> return (pat, expr) - _ -> na "rule_Comprehension_Defined" - func <- match opDefined expr - TypeFunction{} <- typeOf func - let upd val old = lambdaToFunction pat old val - return - ( "Mapping over defined(f)" - , do - (iPat, i) <- quantifiedVar - let i1 = [essence| &i[1] |] - return $ - Comprehension - (upd i1 body) - $ gocBefore - ++ [ Generator (GenInExpr iPat func) ] - ++ transformBi (upd i1) gocAfter - ) - theRule _ = na "rule_Comprehension_Defined" - - -rule_Comprehension_Range :: Rule -rule_Comprehension_Range = "function-range" `Rule` theRule where - - theRule z p = do - should <- shouldRemoveDuplicates z - if should - then theRule_shouldRemoveDuplicates p - else theRule_noRemoveDuplicates p - - -- keep going up, until finding a quantifier - -- when found, return whether this quantifier requires us to remove duplicates or not - -- if none exists, do not apply the rule. - -- (or maybe we should call bug right ahead, it can't be anything else.) - shouldRemoveDuplicates z0 = - case Zipper.up z0 of - Nothing -> na "rule_Comprehension_Range shouldRemoveDuplicates 1" - Just z -> do - let h = Zipper.hole z - case ( match opAnd h, match opOr h, match opSum h - , match opMin h, match opMax h ) of - (Just{}, _, _, _, _) -> return False - (_, Just{}, _, _, _) -> return False - (_, _, Just{}, _, _) -> return True - (_, _, _, Just{}, _) -> return False - (_, _, _, _, Just{}) -> return False - _ -> na "rule_Comprehension_Range shouldRemoveDuplicates 2" - -- case Zipper.up z of - -- Nothing -> na "queryQ" - -- Just u -> queryQ u - - theRule_shouldRemoveDuplicates (Comprehension body gensOrConds) = do - - (gocBefore, (pat, expr), gocAfter) <- matchFirst gensOrConds $ \ goc -> case goc of - Generator (GenInExpr pat@Single{} expr) -> return (pat, expr) - _ -> na "rule_Comprehension_Range" - func <- match opRange expr - DomainFunction _ attrs _domFr domTo <- domainOf func - let upd val old = lambdaToFunction pat old val - let - isInjective = - case attrs of - FunctionAttr _ _ JectivityAttr_Injective -> True - FunctionAttr _ _ JectivityAttr_Bijective -> True - _ -> False - - -- the range is already alldiff - caseInjective = do - (iPat, i) <- quantifiedVar - let i2 = [essence| &i[2] |] - return $ - Comprehension - (upd i2 body) - $ gocBefore - ++ [ Generator (GenInExpr iPat func) ] - ++ transformBi (upd i2) gocAfter - - -- this is the expensive case: introduce an aux set for the range to make it alldiff - caseNonInjective = do - (auxName, aux) <- auxiliaryVar - (jPat, j) <- quantifiedVar - (kPat, k) <- quantifiedVar - (lPat, l) <- quantifiedVar - let k2 = [essence| &k[2] |] - let l2 = [essence| &l[2] |] - return $ WithLocals - (Comprehension - (upd j body) - $ gocBefore - ++ [ Generator (GenInExpr jPat aux) ] - ++ transformBi (upd j) gocAfter) - (AuxiliaryVars - [ Declaration (FindOrGiven LocalFind auxName (DomainSet def def (forgetRepr domTo))) - , SuchThat - [ make opAnd $ Comprehension - [essence| &k2 in &aux |] - [ Generator (GenInExpr kPat func) ] - , make opAnd $ - Comprehension - (make opOr $ Comprehension - [essence| &l2 = &k |] - [ Generator (GenInExpr lPat func) ] - ) - [ Generator (GenInExpr kPat aux) ] - ] - ]) - - when isInjective $ - unless (null [ () | DomainAny{} <- universe domTo ]) $ - na "Cannot compute the domain of range(f)" - - return - [ RuleResult - { ruleResultDescr = "Mapping over range(f)" - , ruleResultType = ExpressionRefinement - , ruleResult = if isInjective - then caseInjective - else caseNonInjective - , ruleResultHook = Nothing - } ] - theRule_shouldRemoveDuplicates _ = na "rule_Comprehension_Range" - - theRule_noRemoveDuplicates (Comprehension body gensOrConds) = do - (gocBefore, (pat, expr), gocAfter) <- matchFirst gensOrConds $ \ goc -> case goc of - Generator (GenInExpr pat@Single{} expr) -> return (pat, expr) - _ -> na "rule_Comprehension_Range" - func <- match opRange expr - let upd val old = lambdaToFunction pat old val - return - [ RuleResult - { ruleResultDescr = "Mapping over range(f)" - , ruleResultType = ExpressionRefinement - , ruleResult = do - (iPat, i) <- quantifiedVar - let i2 = [essence| &i[2] |] - return $ Comprehension (upd i2 body) - $ gocBefore - ++ [Generator (GenInExpr iPat func)] - ++ transformBi (upd i2) gocAfter - , ruleResultHook = Nothing - } ] - theRule_noRemoveDuplicates _ = na "rule_Comprehension_Range" - - --- TODO: What about duplicates for sum, product, etc? -rule_Param_DefinedRange :: Rule -rule_Param_DefinedRange = "param-DefinedRange-of-function" `namedRule` theRule where - theRule p = do - unless (categoryOf p == CatParameter) $ na "rule_Param_DefinedRange" - (_reducerType, mk, p2) <- match opReducer p - (index, f) <- case p2 of - [essence| defined(&f) |] -> return (1, f) - [essence| range(&f) |] -> return (2, f) - _ -> na "rule_Param_DefinedRange" - return - ( "rule_Param_DefinedRange" - , do - (iPat, i) <- quantifiedVar - return $ mk $ [essence| [ &i[&index] | &iPat <- &f ] |] - ) - - -rule_Comprehension_Defined_Size :: Rule -rule_Comprehension_Defined_Size = "function-defined-size" `namedRule` theRule where - theRule [essence| size(defined(&func), &n) |] = do - DomainFunction _ _ domFr _domTo <- domainOf func - return - ( "size(defined(func), n)" - , do - (auxName, aux) <- auxiliaryVar - (kPat, k) <- quantifiedVar - (lPat, l) <- quantifiedVar - let k1 = [essence| &k[1] |] - let l1 = [essence| &l[1] |] - return $ WithLocals - (fromBool True) - (AuxiliaryVars - [ Declaration (FindOrGiven LocalFind auxName - (DomainSet def (SetAttr (SizeAttr_Size n)) (forgetRepr domFr))) - , SuchThat - [ make opAnd $ Comprehension - [essence| &k1 in &aux |] - [ Generator (GenInExpr kPat func) ] - , make opAnd $ - Comprehension - (make opOr $ Comprehension - [essence| &l1 = &k |] - [ Generator (GenInExpr lPat func) ] - ) - [ Generator (GenInExpr kPat aux) ] - ] - ]) - ) - theRule _ = na "rule_Comprehension_Defined_Size" - - -rule_Comprehension_Range_Size :: Rule -rule_Comprehension_Range_Size = "function-range-size" `namedRule` theRule where - theRule [essence| size(range(&func), &n) |] = do - DomainFunction _ _ _domFr domTo <- domainOf func - return - ( "size(range(func), n)" - , do - (auxName, aux) <- auxiliaryVar - (kPat, k) <- quantifiedVar - (lPat, l) <- quantifiedVar - let k2 = [essence| &k[2] |] - let l2 = [essence| &l[2] |] - return $ WithLocals - (fromBool True) - (AuxiliaryVars - [ Declaration (FindOrGiven LocalFind auxName - (DomainSet def (SetAttr (SizeAttr_Size n)) (forgetRepr domTo))) - , SuchThat - [ make opAnd $ Comprehension - [essence| &k2 in &aux |] - [ Generator (GenInExpr kPat func) ] - , make opAnd $ - Comprehension - (make opOr $ Comprehension - [essence| &l2 = &k |] - [ Generator (GenInExpr lPat func) ] - ) - [ Generator (GenInExpr kPat aux) ] - ] - ]) - ) - theRule _ = na "rule_Comprehension_Range_Size" - - -rule_In :: Rule -rule_In = "function-in" `namedRule` theRule where - theRule [essence| &x in &f |] = do - TypeFunction{} <- typeOf f - return - ( "Function membership to function image." - , return [essence| &f(&x[1]) = &x[2] |] - ) - theRule _ = na "rule_In" - - -rule_Restrict_Image :: Rule -rule_Restrict_Image = "function-restrict-image" `namedRule` theRule where - theRule p = do - (func', arg) <- match opImage p - (func , dom) <- match opRestrict func' - TypeFunction{} <- typeOf func - return - ( "Function image on a restricted function." - , do - (iPat, i) <- quantifiedVar - let bob = [essence| exists &iPat : &dom . &i = &arg |] - return $ WithLocals (make opImage func arg) (DefinednessConstraints [bob]) - ) - - -rule_Restrict_Comprehension :: Rule -rule_Restrict_Comprehension = "function-restrict-comprehension" `namedRule` theRule where - theRule (Comprehension body gensOrConds) = do - (gocBefore, (iPat, iPatName, expr), gocAfter) <- matchFirst gensOrConds $ \ goc -> case goc of - Generator (GenInExpr iPat@(Single iPatName) expr) -> return (iPat, iPatName, expr) - _ -> na "rule_Restrict_Comprehension" - (func, dom) <- match opRestrict expr - TypeFunction{} <- typeOf func - return - ( "Mapping over restrict(func, dom)" - , do - (jPat, j) <- quantifiedVar - let i = Reference iPatName Nothing - return $ Comprehension body - $ gocBefore - ++ [ Generator (GenInExpr iPat func) - , Condition [essence| exists &jPat : &dom . &j = &i[1] |] - ] - ++ gocAfter - ) - theRule _ = na "rule_Restrict_Comprehension" - - --- image(f,x) can be nasty for non-total functions. --- 1. if f is a total function, it can readily be replaced by a set expression. --- 2.1. if f isn't total, and if the return type is right, it will always end up as a generator for a comprehension. --- a vertical rule is needed for such cases. --- 2.2. if the return type is not "right", i.e. it is a bool or an int, i.e. sth we cannot quantify over, --- the vertical rule is harder. - - --- | f(x) : bool ~~> or([ b | (a,b) <- f, a = x]) -rule_Image_Bool :: Rule -rule_Image_Bool = "function-image-bool" `namedRule` theRule where - theRule p = do - (func, arg) <- match opImage p - case match opRestrict func of - Nothing -> return () - Just{} -> na "rule_Image_Bool" -- do not use this rule for restricted functions - TypeFunction _ TypeBool <- typeOf func - return - ( "Function image, bool." - , do - (iPat, i) <- quantifiedVar - return $ make opOr $ Comprehension [essence| &i[2] |] - [ Generator (GenInExpr iPat func) - , Condition [essence| &i[1] = &arg |] - ] - ) - - --- | f(x)[i] : bool ~~> or([ b[i] | (a,b) <- f, a = x]) "matrix indexing" -rule_Image_BoolMatrixIndexed :: Rule -rule_Image_BoolMatrixIndexed = "function-image-BoolMatrixIndexed" `namedRule` theRule where - theRule p = do - (matrix, indices) <- match opMatrixIndexing p - (func, arg) <- match opImage matrix - TypeFunction _ (TypeMatrix _ TypeBool) <- typeOf func - return - ( "Function image, matrix of bool." - , do - (iPat, i) <- quantifiedVar - let i2 = make opMatrixIndexing [essence| &i[2] |] indices - return $ make opOr $ Comprehension i2 - [ Generator (GenInExpr iPat func) - , Condition [essence| &i[1] = &arg |] - ] - ) - - --- | f(x)[i] : bool ~~> or([ b[i] | (a,b) <- f, a = x]) "tuple indexing" -rule_Image_BoolTupleIndexed :: Rule -rule_Image_BoolTupleIndexed = "function-image-BoolTupleIndexed" `namedRule` theRule where - theRule p = do - (matrix, index) <- match opIndexing p - (func, arg) <- match opImage matrix - TypeFunction _ (TypeTuple ts) <- typeOf func - iInt <- match constantInt index - case atMay ts (fromInteger (iInt-1)) of - Just TypeBool -> return () - _ -> na "rule_Image_BoolTupleIndexed" - return - ( "Function image, tuple of bool." - , do - (iPat, i) <- quantifiedVar - let i2 = make opIndexing [essence| &i[2] |] index - return $ make opOr $ Comprehension i2 - [ Generator (GenInExpr iPat func) - , Condition [essence| &i[1] = &arg |] - ] - ) - - --- | f(x) : int ~~> sum([ b | (a,b) <- f, a = x]) -rule_Image_Int :: Rule -rule_Image_Int = "function-image-int" `namedRule` theRule where - theRule p = do - (func, arg) <- match opImage p - case match opRestrict func of - Nothing -> return () - Just{} -> na "rule_Image_Int" -- do not use this rule for restricted functions -<<<<<<< HEAD - TypeFunction _ (TypeInt Nothing) <- typeOf func -||||||| merged common ancestors - TypeFunction _ TypeInt <- typeOf func -======= - TypeFunction _ (TypeInt _) <- typeOf func ->>>>>>> taggedints - return - ( "Function image, int." - , do - (iPat, i) <- quantifiedVar - let val = make opSum $ Comprehension [essence| &i[2] |] - [ Generator (GenInExpr iPat func) - , Condition [essence| &i[1] = &arg |] - ] - let isDefined = [essence| &arg in defined(&func) |] - return $ WithLocals val (DefinednessConstraints [isDefined]) - ) - - --- | f(x)[i] : int ~~> sum([ b[i] | (a,b) <- f, a = x]) "matrix indexing" -rule_Image_IntMatrixIndexed :: Rule -rule_Image_IntMatrixIndexed = "function-image-IntMatrixIndexed" `namedRule` theRule where - theRule p = do - (matrix, indices) <- match opMatrixIndexing p - (func, arg) <- match opImage matrix -<<<<<<< HEAD - TypeFunction _ (TypeMatrix _ (TypeInt Nothing)) <- typeOf func -||||||| merged common ancestors - TypeFunction _ (TypeMatrix _ TypeInt) <- typeOf func -======= - TypeFunction _ (TypeMatrix _ (TypeInt _)) <- typeOf func ->>>>>>> taggedints - return - ( "Function image, matrix of int." - , do - (iPat, i) <- quantifiedVar - let i2 = make opMatrixIndexing [essence| &i[2] |] indices - let val = make opSum $ Comprehension i2 - [ Generator (GenInExpr iPat func) - , Condition [essence| &i[1] = &arg |] - ] - let isDefined = [essence| &arg in defined(&func) |] - return $ WithLocals val (DefinednessConstraints [isDefined]) - ) - - --- | f(x)[i] : int ~~> sum([ b[i] | (a,b) <- f, a = x]) "tuple indexing" -rule_Image_IntTupleIndexed :: Rule -rule_Image_IntTupleIndexed = "function-image-IntTupleIndexed" `namedRule` theRule where - theRule p = do - (matrix, index) <- match opIndexing p - (func, arg) <- match opImage matrix - TypeFunction _ (TypeTuple ts) <- typeOf func - iInt <- match constantInt index - case atMay ts (fromInteger (iInt-1)) of -<<<<<<< HEAD - Just (TypeInt Nothing) -> return () -||||||| merged common ancestors - Just TypeInt -> return () -======= - Just (TypeInt _) -> return () ->>>>>>> taggedints - _ -> na "rule_Image_IntTupleIndexed" - return - ( "Function image, tuple of int." - , do - (iPat, i) <- quantifiedVar - let i2 = make opIndexing [essence| &i[2] |] index - let val = make opSum $ Comprehension i2 - [ Generator (GenInExpr iPat func) - , Condition [essence| &i[1] = &arg |] - ] - let isDefined = [essence| &arg in defined(&func) |] - return $ WithLocals val (DefinednessConstraints [isDefined]) - ) - - --- | [ ..i.. | i <- f(x), ..i.. ] ~~> --- [ ..j.. | (a,b) <- f, a = i, j <- b, ..j.. ] -rule_Comprehension_Image :: Rule -rule_Comprehension_Image = "function-image-comprehension" `namedRule` theRule where - theRule (Comprehension body gensOrConds) = do - (gocBefore, (pat, expr), gocAfter) <- matchFirst gensOrConds $ \ goc -> case goc of - Generator (GenInExpr pat@Single{} expr) -> return (pat, expr) - _ -> na "rule_Comprehension_Image" - (mkModifier, expr2) <- match opModifier expr - (func, arg) <- match opImage expr2 - TypeFunction{} <- typeOf func - case match opRestrict func of - Nothing -> return () - Just{} -> na "rule_Comprehension_Image" -- do not use this rule for restricted functions - let upd val old = lambdaToFunction pat old val - return - ( "Mapping over the image of a function" - , do - (iPat, i) <- quantifiedVar - (jPat, j) <- quantifiedVar - return $ Comprehension - (upd j body) - $ gocBefore - ++ [ Generator (GenInExpr iPat func) - , Condition [essence| &i[1] = &arg |] - , Generator (GenInExpr jPat (mkModifier [essence| &i[2] |])) - ] - ++ transformBi (upd j) gocAfter - ) - theRule _ = na "rule_Comprehension_Image" - - --- | [ ..i.. | i <- imageSet(f,x), ..i.. ] ~~> --- [ ..b.. | (a,b) <- f, a = i, ..b.. ] -rule_Comprehension_ImageSet :: Rule -rule_Comprehension_ImageSet = "function-imageSet-comprehension" `namedRule` theRule where - theRule (Comprehension body gensOrConds) = do - (gocBefore, (pat, expr), gocAfter) <- matchFirst gensOrConds $ \ goc -> case goc of - Generator (GenInExpr pat@Single{} expr) -> return (pat, expr) - _ -> na "rule_Comprehension_ImageSet" - (mkModifier, expr2) <- match opModifierNoP expr - (func, arg) <- match opImageSet expr2 - TypeFunction{} <- typeOf func - case match opRestrict func of - Nothing -> return () - Just{} -> na "rule_Comprehension_ImageSet" -- do not use this rule for restricted functions - let upd val old = lambdaToFunction pat old val - return - ( "Mapping over the imageSet of a function" - , do - (iPat, i) <- quantifiedVar - return $ Comprehension - (upd [essence| &i[2] |] body) - $ gocBefore - ++ [ Generator (GenInExpr iPat (mkModifier func)) - , Condition [essence| &i[1] = &arg |] - ] - ++ transformBi (upd [essence| &i[2] |]) gocAfter - ) - theRule _ = na "rule_Comprehension_ImageSet" - - --- | f(x) <=lex m ~~> and([ b <=lex m | (a,b) <- f, a = x]) -rule_Image_Matrix_LexLhs :: Rule -rule_Image_Matrix_LexLhs = "function-image-matrix-lexlhs" `namedRule` theRule where - theRule p = do - (mkLex, (lhs,rhs)) <- match opLex p - (func, arg) <- match opImage lhs - return - ( "Function image, matrix as an argument to a lex operator." - , do - (iPat, i) <- quantifiedVar - let val = make opAnd $ Comprehension (mkLex [essence| &i[2] |] rhs) - [ Generator (GenInExpr iPat func) - , Condition [essence| &i[1] = &arg |] - ] - let isDefined = [essence| &arg in defined(&func) |] - return $ WithLocals val (DefinednessConstraints [isDefined]) - ) - - --- | f(x) <=lex m ~~> and([ b <=lex m | (a,b) <- f, a = x]) -rule_Image_Matrix_LexRhs :: Rule -rule_Image_Matrix_LexRhs = "function-image-matrix-lexrhs" `namedRule` theRule where - theRule p = do - (mkLex, (lhs,rhs)) <- match opLex p - (func, arg) <- match opImage rhs - return - ( "Function image, matrix as an argument to a lex operator." - , do - (iPat, i) <- quantifiedVar - let val = make opAnd $ Comprehension (mkLex lhs [essence| &i[2] |]) - [ Generator (GenInExpr iPat func) - , Condition [essence| &i[1] = &arg |] - ] - let isDefined = [essence| &arg in defined(&func) |] - return $ WithLocals val (DefinednessConstraints [isDefined]) - ) - - -rule_Defined_Intersect :: Rule -rule_Defined_Intersect = "function-Defined-intersect" `namedRule` theRule where - theRule (Comprehension body gensOrConds) = do - (gocBefore, (pat, iPat, expr), gocAfter) <- matchFirst gensOrConds $ \ goc -> case goc of - Generator (GenInExpr pat@(Single iPat) expr) -> return (pat, iPat, expr) - _ -> na "rule_Defined_Intersect" - f <- match opDefined expr - (x, y) <- match opIntersect f - tx <- typeOf x - case tx of - TypeFunction{} -> return () - _ -> fail "type incompatibility in intersect operator" - let i = Reference iPat Nothing - return - ( "Horizontal rule for function intersection" - , return $ - Comprehension body - $ gocBefore - ++ [ Generator (GenInExpr pat (make opDefined x)) - , Condition [essence| (&i, image(&x,&i)) in &y |] - ] - ++ gocAfter - ) - theRule _ = na "rule_Defined_Intersect" - - -rule_DefinedOrRange_Union :: Rule -rule_DefinedOrRange_Union = "function-DefinedOrRange-union" `namedRule` theRule where - theRule (Comprehension body gensOrConds) = do - (gocBefore, (pat, iPat, expr), gocAfter) <- matchFirst gensOrConds $ \ goc -> case goc of - Generator (GenInExpr pat@(Single iPat) expr) -> return (pat, iPat, expr) - _ -> na "rule_DefinedOrRange_Union" - (mk, f) <- match opDefinedOrRange expr - (x, y) <- match opUnion f - tx <- typeOf x - case tx of - TypeFunction{} -> return () - _ -> fail "type incompatibility in union operator" - let mkx = mk x - let mky = mk y - let i = Reference iPat Nothing - return - ( "Horizontal rule for function union" - , return $ make opFlatten $ AbstractLiteral $ AbsLitMatrix -<<<<<<< HEAD - (DomainInt Nothing [RangeBounded 1 2]) -||||||| merged common ancestors - (DomainInt [RangeBounded 1 2]) -======= - (DomainInt NoTag [RangeBounded 1 2]) ->>>>>>> taggedints - [ Comprehension body - $ gocBefore - ++ [ Generator (GenInExpr pat mkx) ] - ++ gocAfter - , Comprehension body - $ gocBefore - ++ [ Generator (GenInExpr pat mky) - , Condition [essence| !(&i in &mkx) |] - ] - ++ gocAfter - ] - ) - theRule _ = na "rule_DefinedOrRange_Union" - - -rule_DefinedOrRange_Difference :: Rule -rule_DefinedOrRange_Difference = "function-DefinedOrRange-difference" `namedRule` theRule where - theRule (Comprehension body gensOrConds) = do - (gocBefore, (pat, iPat, expr), gocAfter) <- matchFirst gensOrConds $ \ goc -> case goc of - Generator (GenInExpr pat@(Single iPat) expr) -> return (pat, iPat, expr) - _ -> na "rule_DefinedOrRange_Difference" - (mk, f) <- match opDefinedOrRange expr - (x, y) <- match opMinus f - tx <- typeOf x - case tx of - TypeFunction{} -> return () - _ -> fail "type incompatibility in difference operator" - let mkx = mk x - let mky = mk y - let i = Reference iPat Nothing - return - ( "Horizontal rule for function difference" - , return $ - Comprehension body - $ gocBefore - ++ [ Generator (GenInExpr pat mkx) - , Condition [essence| !(&i in &mky) |] - ] - ++ gocAfter - ) - theRule _ = na "rule_DefinedOrRange_Difference" - - diff --git a/src/Conjure/Rules/Horizontal/MSet.hs.orig b/src/Conjure/Rules/Horizontal/MSet.hs.orig deleted file mode 100644 index 4e71b07bd3..0000000000 --- a/src/Conjure/Rules/Horizontal/MSet.hs.orig +++ /dev/null @@ -1,278 +0,0 @@ -{-# LANGUAGE QuasiQuotes #-} - -module Conjure.Rules.Horizontal.MSet where - -import Conjure.Rules.Import - - -rule_Comprehension_Literal :: Rule -rule_Comprehension_Literal = "mset-comprehension-literal" `namedRule` theRule where - theRule (Comprehension body gensOrConds) = do - (gocBefore, (pat, expr), gocAfter) <- matchFirst gensOrConds $ \ goc -> case goc of - Generator (GenInExpr pat@Single{} expr) -> return (pat, expr) - _ -> na "rule_Comprehension_Literal" - (TypeMSet tau, elems) <- match msetLiteral expr - let outLiteral = make matrixLiteral -<<<<<<< HEAD - (TypeMatrix (TypeInt Nothing) tau) - (DomainInt Nothing [RangeBounded 1 (fromInt (genericLength elems))]) -||||||| merged common ancestors - (TypeMatrix TypeInt tau) - (DomainInt [RangeBounded 1 (fromInt (genericLength elems))]) -======= - (TypeMatrix (TypeInt NoTag) tau) - (DomainInt NoTag [RangeBounded 1 (fromInt (genericLength elems))]) ->>>>>>> taggedints - elems - let upd val old = lambdaToFunction pat old val - return - ( "Comprehension on mset literals" - , do - (iPat, i) <- quantifiedVar - return $ Comprehension (upd i body) - $ gocBefore - ++ [Generator (GenInExpr iPat outLiteral)] - ++ transformBi (upd i) gocAfter - ) - theRule _ = na "rule_Comprehension_Literal" - - -rule_Comprehension_ToSet_Literal :: Rule -rule_Comprehension_ToSet_Literal = "mset-comprehension-toSet-literal" `namedRule` theRule where - theRule (Comprehension body gensOrConds) = do - (gocBefore, (pat, expr), gocAfter) <- matchFirst gensOrConds $ \ goc -> case goc of - Generator (GenInExpr pat@Single{} expr) -> return (pat, expr) - _ -> na "rule_Comprehension_ToSet_Literal" - mset <- match opToSet expr - (TypeMSet tau, elems) <- match msetLiteral mset - let outLiteralDomain = mkDomainIntB 1 (fromInt $ genericLength elems) -<<<<<<< HEAD - let outLiteral = make matrixLiteral (TypeMatrix (TypeInt Nothing) tau) outLiteralDomain elems -||||||| merged common ancestors - let outLiteral = make matrixLiteral (TypeMatrix TypeInt tau) outLiteralDomain elems -======= - let outLiteral = make matrixLiteral (TypeMatrix (TypeInt NoTag) tau) outLiteralDomain elems ->>>>>>> taggedints - let upd val old = lambdaToFunction pat old val - return - ( "Comprehension on toSet of mset literals" - , do - (iPat, i) <- quantifiedVar - (jPat, j) <- quantifiedVar - let iIndexed = [essence| &outLiteral[&i] |] - let jIndexed = [essence| &outLiteral[&j] |] - return $ Comprehension (upd iIndexed body) - $ gocBefore - ++ [ Generator (GenDomainNoRepr iPat outLiteralDomain) - , Condition [essence| - !(exists &jPat : &outLiteralDomain . - (&j < &i) /\ (&iIndexed = &jIndexed)) - |] - ] - ++ transformBi (upd iIndexed) gocAfter - ) - theRule _ = na "rule_Comprehension_ToSet_Literal" - - -rule_Eq :: Rule -rule_Eq = "mset-eq" `namedRule` theRule where - theRule p = do - (x,y) <- match opEq p - TypeMSet{} <- typeOf x - TypeMSet{} <- typeOf y - return - ( "Horizontal rule for mset equality" - , do - (iPat, i) <- quantifiedVar - return - [essence| - (forAll &iPat in &x . freq(&x,&i) = freq(&y,&i)) /\ - (forAll &iPat in &y . freq(&x,&i) = freq(&y,&i)) - |] - ) - - -rule_Neq :: Rule -rule_Neq = "mset-neq" `namedRule` theRule where - theRule [essence| &x != &y |] = do - TypeMSet{} <- typeOf x - TypeMSet{} <- typeOf y - return - ( "Horizontal rule for mset dis-equality" - , do - (iPat, i) <- quantifiedVar - return - [essence| - (exists &iPat in &x . freq(&x,&i) != freq(&y,&i)) \/ - (exists &iPat in &y . freq(&x,&i) != freq(&y,&i)) - |] - ) - theRule _ = na "rule_Neq" - - -rule_SubsetEq :: Rule -rule_SubsetEq = "mset-subsetEq" `namedRule` theRule where - theRule p = do - (x,y) <- match opSubsetEq p - TypeMSet{} <- typeOf x - TypeMSet{} <- typeOf y - return - ( "Horizontal rule for mset subsetEq" - , do - (iPat, i) <- quantifiedVar - return [essence| forAll &iPat in &x . freq(&x,&i) <= freq(&y,&i) |] - ) - - -rule_Subset :: Rule -rule_Subset = "mset-subset" `namedRule` theRule where - theRule [essence| &x subset &y |] = do - TypeMSet{} <- typeOf x - TypeMSet{} <- typeOf y - return - ( "Horizontal rule for mset subset" - , do - (iPat, i) <- quantifiedVar - return - [essence| - (forAll &iPat in &x . freq(&x,&i) <= freq(&y,&i)) /\ - (exists &iPat in &x . freq(&x,&i) < freq(&y,&i)) - |] - ) - theRule _ = na "rule_Subset" - - -rule_Supset :: Rule -rule_Supset = "mset-supset" `namedRule` theRule where - theRule [essence| &a supset &b |] = do - TypeMSet{} <- typeOf a - TypeMSet{} <- typeOf b - return - ( "Horizontal rule for mset supset" - , return [essence| &b subset &a |] - ) - theRule _ = na "rule_Supset" - - -rule_SupsetEq :: Rule -rule_SupsetEq = "mset-subsetEq" `namedRule` theRule where - theRule [essence| &a supsetEq &b |] = do - TypeMSet{} <- typeOf a - TypeMSet{} <- typeOf b - return - ( "Horizontal rule for mset supsetEq" - , return [essence| &b subsetEq &a |] - ) - theRule _ = na "rule_SupsetEq" - - -rule_DotLt :: Rule -rule_DotLt = "mset-DotLt" `namedRule` theRule where - theRule p = do - (a,b) <- match opDotLt p - TypeMSet{} <- typeOf a - TypeMSet{} <- typeOf b - sameRepresentation a b - ma <- tupleLitIfNeeded <$> downX1 a - mb <- tupleLitIfNeeded <$> downX1 b - return - ( "Horizontal rule for mset .<" <+> pretty (make opDotLt ma mb) - , return $ make opDotLt ma mb - ) - - -rule_DotLeq :: Rule -rule_DotLeq = "mset-DotLeq" `namedRule` theRule where - theRule p = do - (a,b) <- match opDotLeq p - TypeMSet{} <- typeOf a - TypeMSet{} <- typeOf b - sameRepresentation a b - ma <- tupleLitIfNeeded <$> downX1 a - mb <- tupleLitIfNeeded <$> downX1 b - return - ( "Horizontal rule for mset .<=" <+> pretty (make opDotLeq ma mb) - , return $ make opDotLeq ma mb - ) - - -rule_MaxMin :: Rule -rule_MaxMin = "mset-max-min" `namedRule` theRule where - theRule [essence| max(&s) |] = do -<<<<<<< HEAD - TypeMSet (TypeInt Nothing) <- typeOf s -||||||| merged common ancestors - TypeMSet TypeInt <- typeOf s -======= - TypeMSet (TypeInt _) <- typeOf s ->>>>>>> taggedints - return - ( "Horizontal rule for mset max" - , do - (iPat, i) <- quantifiedVar - return [essence| max([&i | &iPat <- &s]) |] - ) - theRule [essence| min(&s) |] = do -<<<<<<< HEAD - TypeMSet (TypeInt Nothing) <- typeOf s -||||||| merged common ancestors - TypeMSet TypeInt <- typeOf s -======= - TypeMSet (TypeInt _) <- typeOf s ->>>>>>> taggedints - return - ( "Horizontal rule for mset min" - , do - (iPat, i) <- quantifiedVar - return [essence| min([&i | &iPat <- &s]) |] - ) - theRule _ = na "rule_MaxMin" - - --- freq(mset,arg) ~~> sum([ toInt(arg = i) | i in mset ]) -rule_Freq :: Rule -rule_Freq = "mset-freq" `namedRule` theRule where - theRule p = do - (mset, arg) <- match opFreq p - TypeMSet{} <- typeOf mset - -- avoid applying this rule when "mset" is of the form "toMSet of set" - case mset of - [essence| toMSet(&s) |] -> do - tyS <- typeOf s - case tyS of - TypeSet{} -> na "rule_Freq" - _ -> return () - _ -> return () - return - ( "Horizontal rule for mset-freq." - , do - (iPat, i) <- quantifiedVar - return [essence| sum &iPat in &mset . toInt(&i = &arg) |] - ) - - --- x in s ~~> or([ x = i | i in s ]) -rule_In :: Rule -rule_In = "mset-in" `namedRule` theRule where - theRule p = do - (x,s) <- match opIn p - TypeMSet{} <- typeOf s - return - ( "Horizontal rule for mset-in." - , do - (iPat, i) <- quantifiedVar - return [essence| exists &iPat in &s . &i = &x |] - ) - - -rule_Card :: Rule -rule_Card = "mset-card" `namedRule` theRule where - theRule p = do - s <- match opTwoBars p - TypeMSet{} <- typeOf s - return - ( "Horizontal rule for mset cardinality." - , do - (iPat, _) <- quantifiedVar - return [essence| sum &iPat in &s . 1 |] - ) diff --git a/src/Conjure/Rules/Horizontal/Partition.hs.orig b/src/Conjure/Rules/Horizontal/Partition.hs.orig deleted file mode 100644 index 33aa2eaf6a..0000000000 --- a/src/Conjure/Rules/Horizontal/Partition.hs.orig +++ /dev/null @@ -1,219 +0,0 @@ -{-# LANGUAGE QuasiQuotes #-} - -module Conjure.Rules.Horizontal.Partition where - -import Conjure.Rules.Import - - -rule_Comprehension_Literal :: Rule -rule_Comprehension_Literal = "partition-comprehension-literal" `namedRule` theRule where - theRule (Comprehension body gensOrConds) = do - (gocBefore, (pat, p), gocAfter) <- matchFirst gensOrConds $ \ goc -> case goc of - Generator (GenInExpr pat@Single{} expr) -> return (pat, matchDef opParts expr) - _ -> na "rule_Comprehension_Literal" - (TypePartition tau, elems) <- match partitionLiteral p - let outLiteral = make matrixLiteral -<<<<<<< HEAD - (TypeMatrix (TypeInt Nothing) (TypeSet tau)) - (DomainInt Nothing [RangeBounded 1 (fromInt (genericLength elems))]) -||||||| merged common ancestors - (TypeMatrix TypeInt (TypeSet tau)) - (DomainInt [RangeBounded 1 (fromInt (genericLength elems))]) -======= - (TypeMatrix (TypeInt NoTag) (TypeSet tau)) - (DomainInt NoTag [RangeBounded 1 (fromInt (genericLength elems))]) ->>>>>>> taggedints - [ AbstractLiteral (AbsLitSet e) - | e <- elems - ] - let upd val old = lambdaToFunction pat old val - return - ( "Comprehension on partition literals" - , do - (iPat, i) <- quantifiedVar - return $ Comprehension (upd i body) - $ gocBefore - ++ [Generator (GenInExpr iPat outLiteral)] - ++ transformBi (upd i) gocAfter - ) - theRule _ = na "rule_Comprehension_PartitionLiteral" - - -rule_Eq :: Rule -rule_Eq = "partition-eq" `namedRule` theRule where - theRule p = do - (x,y) <- match opEq p - TypePartition{} <- typeOf x - TypePartition{} <- typeOf y - return - ( "Horizontal rule for partition equality" - , return $ make opEq (make opParts x) (make opParts y) - ) - - -rule_Neq :: Rule -rule_Neq = "partition-neq" `namedRule` theRule where - theRule [essence| &x != &y |] = do - TypePartition{} <- typeOf x - TypePartition{} <- typeOf y - return - ( "Horizontal rule for partition dis-equality" - , do - (iPat, i) <- quantifiedVar - return [essence| - (exists &iPat in &x . !(&i in &y)) - \/ - (exists &iPat in &y . !(&i in &x)) - |] - ) - theRule _ = na "rule_Neq" - - -rule_DotLt :: Rule -rule_DotLt = "partition-DotLt" `namedRule` theRule where - theRule p = do - (a,b) <- match opDotLt p - TypePartition{} <- typeOf a - TypePartition{} <- typeOf b - sameRepresentation a b - ma <- tupleLitIfNeeded <$> downX1 a - mb <- tupleLitIfNeeded <$> downX1 b - return - ( "Horizontal rule for partition .<" <+> pretty (make opDotLt ma mb) - , return $ make opDotLt ma mb - ) - - -rule_DotLeq :: Rule -rule_DotLeq = "partition-DotLeq" `namedRule` theRule where - theRule p = do - (a,b) <- match opDotLeq p - TypePartition{} <- typeOf a - TypePartition{} <- typeOf b - sameRepresentation a b - ma <- tupleLitIfNeeded <$> downX1 a - mb <- tupleLitIfNeeded <$> downX1 b - return - ( "Horizontal rule for partition .<=" <+> pretty (make opDotLeq ma mb) - , return $ make opDotLeq ma mb - ) - - -rule_Together :: Rule -rule_Together = "partition-together" `namedRule` theRule where - theRule [essence| together(&x,&p) |] = do - TypePartition{} <- typeOf p - DomainPartition _ _ inner <- domainOf p - return - ( "Horizontal rule for partition-together" - , do - (iPat, i) <- quantifiedVar - (jPat, j) <- quantifiedVar - (kPat, k) <- quantifiedVar - return [essence| - (exists &iPat in parts(&p) . &x subsetEq &i) - /\ - $ the items in x appear somewhere in the partition - (forAll &jPat in &x . exists &kPat : &inner . &j = &k) - |] - ) - theRule _ = na "rule_Together" - - -rule_Apart :: Rule -rule_Apart = "partition-apart" `namedRule` theRule where - theRule [essence| apart(&x,&p) |] = do - case p of - -- this is because this rule would change the parity of the DefinednessConstraints - -- they should be bubbled up first. - WithLocals{} -> na "rule_Apart" - _ -> return () - TypePartition{} <- typeOf p - DomainPartition _ _ inner <- domainOf p - return - ( "Horizontal rule for partition-apart" - , do - (iPat, i) <- quantifiedVar - (jPat, j) <- quantifiedVar - (kPat, k) <- quantifiedVar - return [essence| - (forAll &iPat in parts(&p) . !(&x subsetEq &i)) - /\ - $ the items in x appear somewhere in the partition - (forAll &jPat in &x . exists &kPat : &inner . &j = &k) - |] - ) - theRule _ = na "rule_Apart" - - -rule_Party :: Rule -rule_Party = "partition-party" `namedRule` theRule where - theRule (Comprehension body gensOrConds) = do - (gocBefore, (pat, expr), gocAfter) <- matchFirst gensOrConds $ \ goc -> case goc of - Generator (GenInExpr pat@Single{} expr) -> return (pat, expr) - _ -> na "rule_Comprehension_Literal" - (mkModifier, expr2) <- match opModifier expr - (wanted, p) <- match opParty expr2 - TypePartition{} <- typeOf p - let upd val old = lambdaToFunction pat old val - return - ( "Comprehension on a particular part of a partition" - , do - (iPat, i) <- quantifiedVar - (jPat, j) <- quantifiedVar - return $ - Comprehension (upd j body) - $ gocBefore - ++ [ Generator (GenInExpr iPat (make opParts p)) - , Condition [essence| &wanted in &i |] - , Generator (GenInExpr jPat (mkModifier i)) - ] - ++ transformBi (upd j) gocAfter - ) - theRule _ = na "rule_Party" - - -rule_Participants :: Rule -rule_Participants = "partition-participants" `namedRule` theRule where - theRule (Comprehension body gensOrConds) = do - (gocBefore, (pat, expr), gocAfter) <- matchFirst gensOrConds $ \ goc -> case goc of - Generator (GenInExpr pat@Single{} expr) -> return (pat, expr) - _ -> na "rule_Comprehension_Literal" - p <- match opParticipants expr - TypePartition{} <- typeOf p - let upd val old = lambdaToFunction pat old val - return - ( "Comprehension on participants of a partition" - , do - (iPat, i) <- quantifiedVar - (jPat, j) <- quantifiedVar - return $ Comprehension (upd j body) - $ gocBefore - ++ [ Generator (GenInExpr iPat (make opParts p)) - , Generator (GenInExpr jPat i) - ] - ++ transformBi (upd j) gocAfter - ) - theRule _ = na "rule_Participants" - - -rule_Card :: Rule -rule_Card = "partition-card" `namedRule` theRule where - theRule p = do - partition_ <- match opTwoBars p - TypePartition{} <- typeOf partition_ - return - ( "Cardinality of a partition" - , return $ make opTwoBars $ make opParticipants partition_ - ) - - -rule_In :: Rule -rule_In = "partition-in" `namedRule` theRule where - theRule [essence| &x in &p |] = do - TypePartition{} <- typeOf p - return - ( "Horizontal rule for partition-in." - , return [essence| &x in parts(&p) |] - ) - theRule _ = na "rule_In" diff --git a/src/Conjure/Rules/Horizontal/Relation.hs.orig b/src/Conjure/Rules/Horizontal/Relation.hs.orig deleted file mode 100644 index 76db67b778..0000000000 --- a/src/Conjure/Rules/Horizontal/Relation.hs.orig +++ /dev/null @@ -1,275 +0,0 @@ -{-# LANGUAGE QuasiQuotes #-} - -module Conjure.Rules.Horizontal.Relation where - -import Conjure.Rules.Import - - -rule_Comprehension_Literal :: Rule -rule_Comprehension_Literal = "relation-comprehension-literal" `namedRule` theRule where - theRule (Comprehension body gensOrConds) = do - (gocBefore, (pat, expr), gocAfter) <- matchFirst gensOrConds $ \ goc -> case goc of - Generator (GenInExpr pat@Single{} expr) -> return (pat, matchDefs [opToSet,opToMSet,opToRelation] expr) - _ -> na "rule_Comprehension_Literal" - (TypeRelation taus, elems) <- match relationLiteral expr - let outLiteral = make matrixLiteral -<<<<<<< HEAD - (TypeMatrix (TypeInt Nothing) (TypeTuple taus)) - (DomainInt Nothing [RangeBounded 1 (fromInt (genericLength elems))]) -||||||| merged common ancestors - (TypeMatrix TypeInt (TypeTuple taus)) - (DomainInt [RangeBounded 1 (fromInt (genericLength elems))]) -======= - (TypeMatrix (TypeInt NoTag) (TypeTuple taus)) - (DomainInt NoTag [RangeBounded 1 (fromInt (genericLength elems))]) ->>>>>>> taggedints - [ AbstractLiteral (AbsLitTuple row) - | row <- elems - ] - let upd val old = lambdaToFunction pat old val - return - ( "Comprehension on relation literals" - , do - (iPat, i) <- quantifiedVar - return $ Comprehension (upd i body) - $ gocBefore - ++ [Generator (GenInExpr iPat outLiteral)] - ++ transformBi (upd i) gocAfter - ) - theRule _ = na "rule_Comprehension_Literal" - - --- [ body | i <- rel(...) ] --- [ body | jPat <- rel(...), j = ] -rule_Comprehension_Projection :: Rule -rule_Comprehension_Projection = "relation-comprehension-projection" `namedRule` theRule where - theRule (Comprehension body gensOrConds) = do - (gocBefore, (pat, expr), gocAfter) <- matchFirst gensOrConds $ \ goc -> case goc of - Generator (GenInExpr pat@Single{} expr) -> return (pat, matchDef opToSet expr) - _ -> na "rule_Comprehension_Projection" - (rel, args) <- match opRelationProj expr - TypeRelation{} <- typeOf rel - let upd val old = lambdaToFunction pat old val - return - ( "Comprehension on relation literals" - , do - (jPat, j) <- quantifiedVar - -- those indices to keep - let val = AbstractLiteral $ AbsLitTuple - [ [essence| &j[&iExpr] |] - | (i, Nothing) <- zip allNats args - , let iExpr = fromInt i - ] - let conditions = - [ Condition [essence| &j[&iExpr] = &arg |] - | (i, Just arg) <- zip allNats args - , let iExpr = fromInt i - ] - return $ Comprehension - (upd val body) - $ gocBefore - ++ [Generator (GenInExpr jPat rel)] - ++ conditions - ++ transformBi (upd val) gocAfter - ) - theRule _ = na "rule_Comprehension_Projection" - - -rule_PowerSet_Comprehension :: Rule -rule_PowerSet_Comprehension = "relation-powerSet-comprehension" `namedRule` theRule where - theRule (Comprehension body gensOrConds) = do - (gocBefore, (setPat, setPatNum, expr), gocAfter) <- matchFirst gensOrConds $ \ goc -> case goc of - Generator (GenInExpr setPat@(AbsPatSet pats) expr) -> return (setPat, length pats, expr) - _ -> na "rule_PowerSet_Comprehension" - let upd val old = lambdaToFunction setPat old val - rel <- match opPowerSet expr - TypeRelation{} <- typeOf rel - return - ( "Horizontal rule for powerSet relation-comprehension" - , do - outPats <- replicateM setPatNum quantifiedVar - let val = AbstractLiteral $ AbsLitSet [ j | (_,j) <- outPats ] - return $ - Comprehension (upd val body) $ concat - [ gocBefore - , concat - [ [ Generator (GenInExpr pat rel) ] - | (pat,_) <- take 1 outPats - ] - , concat - [ [ Generator (GenInExpr pat rel) - , Condition [essence| &beforeX < &patX |] - ] - | ((_, beforeX), (pat, patX)) <- zip outPats (tail outPats) - ] - , transformBi (upd val) gocAfter - ] - ) - theRule _ = na "rule_PowerSet_Comprehension" - - -rule_Eq :: Rule -rule_Eq = "relation-eq" `namedRule` theRule where - theRule p = do - (x,y) <- match opEq p - TypeRelation{} <- typeOf x - TypeRelation{} <- typeOf y - return - ( "Horizontal rule for relation equality" - , do - (iPat, i) <- quantifiedVar - return - [essence| - (forAll &iPat in &x . &i in &y) - /\ - (forAll &iPat in &y . &i in &x) - |] - ) - - -rule_Neq :: Rule -rule_Neq = "relation-neq" `namedRule` theRule where - theRule [essence| &x != &y |] = do - TypeRelation{} <- typeOf x - TypeRelation{} <- typeOf y - return - ( "Horizontal rule for relation dis-equality" - , do - (iPat, i) <- quantifiedVar - return - [essence| - (exists &iPat in &x . !(&i in &y)) - \/ - (exists &iPat in &y . !(&i in &x)) - |] - ) - theRule _ = na "rule_Neq" - - -rule_DotLt :: Rule -rule_DotLt = "relation-DotLt" `namedRule` theRule where - theRule p = do - (a,b) <- match opDotLt p - TypeRelation{} <- typeOf a - TypeRelation{} <- typeOf b - sameRepresentation a b - ma <- tupleLitIfNeeded <$> downX1 a - mb <- tupleLitIfNeeded <$> downX1 b - return - ( "Horizontal rule for relation .<" <+> pretty (make opDotLt ma mb) - , return $ make opDotLt ma mb - ) - - -rule_DotLeq :: Rule -rule_DotLeq = "relation-DotLeq" `namedRule` theRule where - theRule p = do - (a,b) <- match opDotLeq p - TypeRelation{} <- typeOf a - TypeRelation{} <- typeOf b - sameRepresentation a b - ma <- tupleLitIfNeeded <$> downX1 a - mb <- tupleLitIfNeeded <$> downX1 b - return - ( "Horizontal rule for relation .<=" <+> pretty (make opDotLeq ma mb) - , return $ make opDotLeq ma mb - ) - - -rule_SubsetEq :: Rule -rule_SubsetEq = "relation-subsetEq" `namedRule` theRule where - theRule [essence| &x subsetEq &y |] = do - TypeRelation{} <- typeOf x - TypeRelation{} <- typeOf y - return - ( "Horizontal rule for relation subsetEq" - , do - (iPat, i) <- quantifiedVar - return [essence| forAll &iPat in (&x) . &i in &y |] - ) - theRule _ = na "rule_SubsetEq" - - -rule_Subset :: Rule -rule_Subset = "relation-subset" `namedRule` theRule where - theRule [essence| &a subset &b |] = do - TypeRelation{} <- typeOf a - TypeRelation{} <- typeOf b - return - ( "Horizontal rule for relation subset" - , return [essence| &a subsetEq &b /\ &a != &b |] - ) - theRule _ = na "rule_Subset" - - -rule_Supset :: Rule -rule_Supset = "relation-supset" `namedRule` theRule where - theRule [essence| &a supset &b |] = do - TypeRelation{} <- typeOf a - TypeRelation{} <- typeOf b - return - ( "Horizontal rule for relation supset" - , return [essence| &b subset &a |] - ) - theRule _ = na "rule_Supset" - - -rule_SupsetEq :: Rule -rule_SupsetEq = "relation-subsetEq" `namedRule` theRule where - theRule [essence| &a supsetEq &b |] = do - TypeRelation{} <- typeOf a - TypeRelation{} <- typeOf b - return - ( "Horizontal rule for relation supsetEq" - , return [essence| &b subsetEq &a |] - ) - theRule _ = na "rule_SupsetEq" - - -rule_Image :: Rule -rule_Image = "relation-image" `namedRule` theRule where - theRule p = do - (rel, args) <- match opRelationImage p - TypeRelation{} <- typeOf rel - let arg = AbstractLiteral (AbsLitTuple args) - return - ( "relation image to relation membership" - , return [essence| &arg in &rel |] - ) - - -rule_In :: Rule -rule_In = "relation-in" `namedRule` theRule where - theRule [essence| &x in &rel |] = do - TypeRelation{} <- typeOf rel - return - ( "relation membership to existential quantification" - , do - (iPat, i) <- quantifiedVar - return [essence| exists &iPat in toSet(&rel) . &i = &x |] - ) - theRule _ = na "rule_In" - - -rule_Card :: Rule -rule_Card = "relation-cardinality" `namedRule` theRule where - theRule [essence| |&x| |] = do - TypeRelation{} <- typeOf x - return - ( "Relation cardinality" - , return [essence| |toSet(&x)| |] - ) - theRule _ = na "rule_Card" - - -rule_Param_Card :: Rule -rule_Param_Card = "param-card-of-relation" `namedRule` theRule where - theRule [essence| |&x| |] = do - TypeRelation _ <- typeOf x - unless (categoryOf x == CatParameter) $ na "rule_Param_Card" - DomainRelation _ (RelationAttr (SizeAttr_Size n) _) _ <- domainOf x - return - ( "cardinality of a parameter relation" - , return n - ) - theRule _ = na "rule_Param_Card" diff --git a/src/Conjure/Rules/Horizontal/Sequence.hs.orig b/src/Conjure/Rules/Horizontal/Sequence.hs.orig deleted file mode 100644 index bc6578b9e6..0000000000 --- a/src/Conjure/Rules/Horizontal/Sequence.hs.orig +++ /dev/null @@ -1,635 +0,0 @@ -{-# LANGUAGE QuasiQuotes #-} - -module Conjure.Rules.Horizontal.Sequence where - -import Conjure.Rules.Import - - -rule_Comprehension_Literal :: Rule -rule_Comprehension_Literal = "sequence-comprehension-literal" `namedRule` theRule where - theRule (Comprehension body gensOrConds) = do - (gofBefore, (pat, expr), gofAfter) <- matchFirst gensOrConds $ \ gof -> case gof of - Generator (GenInExpr pat@Single{} expr) -> return (pat, matchDefs [opToSet,opToMSet,opToRelation] expr) - _ -> na "rule_Comprehension_Literal" - (TypeSequence t, elems) <- match sequenceLiteral expr - let outLiteral = make matrixLiteral -<<<<<<< HEAD - (TypeMatrix (TypeInt Nothing) t) - (DomainInt Nothing [RangeBounded 1 (fromInt (genericLength elems))]) -||||||| merged common ancestors - (TypeMatrix TypeInt t) - (DomainInt [RangeBounded 1 (fromInt (genericLength elems))]) -======= - (TypeMatrix (TypeInt NoTag) t) - (DomainInt NoTag [RangeBounded 1 (fromInt (genericLength elems))]) ->>>>>>> taggedints - elems - let upd val old = lambdaToFunction pat old val - return - ( "Comprehension on sequence literals" - , do - (iPat, i) <- quantifiedVar - let val = [essence| (&i, &outLiteral[&i]) |] - return $ Comprehension (upd val body) - $ gofBefore - ++ [Generator (GenDomainNoRepr iPat $ mkDomainIntB 1 (fromInt $ genericLength elems))] - ++ transformBi (upd val) gofAfter - ) - theRule _ = na "rule_Comprehension_Literal" - - -rule_Image_Literal_Bool :: Rule -rule_Image_Literal_Bool = "sequence-image-literal-bool" `namedRule` theRule where - theRule p = do - (func, arg) <- match opImage p - (TypeSequence TypeBool, elems) <- match sequenceLiteral func - -- let argIsUndef = make opNot $ make opOr $ fromList - -- [ [essence| &a = &arg |] - -- | (a,_) <- elems - -- ] - return $ - if null elems - then - ( "Image of empty sequence literal" - , return [essence| false |] -- undefined is false. - ) - else - ( "Image of sequence literal" - , return $ make opOr $ fromList - [ [essence| (&a = &arg) /\ &b |] -- if this is ever true, the output is true. - -- undefined is still false. - | (a',b) <- zip allNats elems - , let a = fromInt a' - ] - ) - - -rule_Image_Literal_Int :: Rule -rule_Image_Literal_Int = "sequence-image-literal-int" `namedRule` theRule where - theRule p = do - (func, arg) <- match opImage p -<<<<<<< HEAD - (TypeSequence (TypeInt Nothing), elems) <- match sequenceLiteral func -||||||| merged common ancestors - (TypeSequence TypeInt, elems) <- match sequenceLiteral func -======= - (TypeSequence (TypeInt _), elems) <- match sequenceLiteral func ->>>>>>> taggedints - return - ( "Image of sequence literal" - , return $ - let - val = make opSum $ fromList - -- if this is ever true, the output is the value of b. - [ [essence| toInt(&a = &arg) * &b |] - | (a',b) <- zip allNats elems - , let a = fromInt a' - ] - len = fromInt $ genericLength elems - argIsDef = [essence| &arg <= &len |] - in - WithLocals val (DefinednessConstraints [argIsDef]) - ) - - -rule_Eq_Empty :: Rule -rule_Eq_Empty = "sequence-eq-empty" `namedRule` theRule where - theRule p = do - (x,y) <- match opEq p - TypeSequence{} <- typeOf x - TypeSequence{} <- typeOf y - other <- case (match sequenceLiteral x, match sequenceLiteral y) of - (Just (_, []), _) -> return y - (_, Just (_, [])) -> return x - _ -> na "sequence not empty" - return - ( "Horizontal rule for sequence equality, one side empty" - , return [essence| |&other| = 0 |] - ) - - -rule_Eq :: Rule -rule_Eq = "sequence-eq" `namedRule` theRule where - theRule p = do - (x,y) <- match opEq p - TypeSequence{} <- typeOf x - TypeSequence{} <- typeOf y - case (match sequenceLiteral x, match sequenceLiteral y) of - (Just (_, []), _) -> na "Sequence{rule_Eq}: one side empty" - (_, Just (_, [])) -> na "Sequence{rule_Eq}: one side empty" - _ -> return () - return - ( "Horizontal rule for sequence equality" - , do - (iPat, i) <- quantifiedVar - return - [essence| - (forAll &iPat in &x . &y(&i[1]) = &i[2]) - /\ - (forAll &iPat in &y . &x(&i[1]) = &i[2]) - /\ - defined(&x) = defined(&y) - |] - ) - - -rule_Eq_Comprehension :: Rule -rule_Eq_Comprehension = "sequence-eq-comprehension" `namedRule` theRule where - theRule p = do - (x, y@(Comprehension _ goc)) <- do - (x,y) <- match opEq p - case x of - Comprehension{} -> return (y, x) -- swap if x is a Comprehension - _ -> return (x, y) - TypeSequence{} <- typeOf x - return - ( "Horizontal rule for sequence equality, with a comprehension on the rhs" - , do - (iPat, i) <- quantifiedVar - let cardinality = Comprehension 1 goc - return - [essence| - |&x| = sum (&cardinality) /\ - and([ &y[&i[1]] = &i[2] - | &iPat <- &x - ]) - |] - ) - - -rule_Neq :: Rule -rule_Neq = "sequence-neq" `namedRule` theRule where - theRule [essence| &x != &y |] = do - TypeSequence{} <- typeOf x - TypeSequence{} <- typeOf y - return - ( "Horizontal rule for sequence dis-equality" - , do - (iPat, i) <- quantifiedVar - return - [essence| - (exists &iPat in &x . !(&i in &y)) - \/ - (exists &iPat in &y . !(&i in &x)) - |] - ) - theRule _ = na "rule_Neq" - - -rule_SubsetEq :: Rule -rule_SubsetEq = "sequence-subsetEq" `namedRule` theRule where - theRule p = do - (x,y) <- match opSubsetEq p - TypeSequence{} <- typeOf x - TypeSequence{} <- typeOf y - return - ( "Horizontal rule for sequence subsetEq" - , do - (iPat, i) <- quantifiedVar - return - [essence| - (forAll &iPat in &x . &y(&i[1]) = &i[2]) - /\ - defined(&x) subsetEq defined(&y) - |] - ) - - -rule_Subset :: Rule -rule_Subset = "sequence-subset" `namedRule` theRule where - theRule [essence| &a subset &b |] = do - TypeSequence{} <- typeOf a - TypeSequence{} <- typeOf b - return - ( "Horizontal rule for sequence subset" - , return [essence| &a subsetEq &b /\ &a != &b |] - ) - theRule _ = na "rule_Subset" - - -rule_Supset :: Rule -rule_Supset = "sequence-supset" `namedRule` theRule where - theRule [essence| &a supset &b |] = do - TypeSequence{} <- typeOf a - TypeSequence{} <- typeOf b - return - ( "Horizontal rule for sequence supset" - , return [essence| &b subset &a |] - ) - theRule _ = na "rule_Supset" - - -rule_SupsetEq :: Rule -rule_SupsetEq = "sequence-subsetEq" `namedRule` theRule where - theRule [essence| &a supsetEq &b |] = do - TypeSequence{} <- typeOf a - TypeSequence{} <- typeOf b - return - ( "Horizontal rule for sequence supsetEq" - , return [essence| &b subsetEq &a |] - ) - theRule _ = na "rule_SupsetEq" - - -rule_DotLt :: Rule -rule_DotLt = "sequence-DotLt" `namedRule` theRule where - theRule p = do - (a,b) <- match opDotLt p - TypeSequence{} <- typeOf a - TypeSequence{} <- typeOf b - sameRepresentation a b - ma <- tupleLitIfNeeded <$> downX1 a - mb <- tupleLitIfNeeded <$> downX1 b - return - ( "Horizontal rule for sequence .<" <+> pretty (make opDotLt ma mb) - , return $ make opDotLt ma mb - ) - - -rule_DotLeq :: Rule -rule_DotLeq = "sequence-DotLeq" `namedRule` theRule where - theRule p = do - (a,b) <- match opDotLeq p - TypeSequence{} <- typeOf a - TypeSequence{} <- typeOf b - sameRepresentation a b - ma <- tupleLitIfNeeded <$> downX1 a - mb <- tupleLitIfNeeded <$> downX1 b - return - ( "Horizontal rule for sequence .<=" <+> pretty (make opDotLeq ma mb) - , return $ make opDotLeq ma mb - ) - - -rule_Comprehension_PreImage :: Rule -rule_Comprehension_PreImage = "sequence-preImage" `namedRule` theRule where - theRule (Comprehension body gensOrConds) = do - (gofBefore, (pat, expr), gofAfter) <- matchFirst gensOrConds $ \ gof -> case gof of - Generator (GenInExpr pat@Single{} expr) -> return (pat, expr) - _ -> na "rule_Comprehension_PreImage" - (func, img) <- match opPreImage expr - TypeSequence{} <- typeOf func - let upd val old = lambdaToFunction pat old val - return - ( "Mapping over the preImage of a sequence" - , do - (jPat, j) <- quantifiedVar - let val = [essence| &j[1] |] - return $ Comprehension - (upd val body) - $ gofBefore - ++ [ Generator (GenInExpr jPat func) - , Condition [essence| &j[2] = &img |] - ] - ++ transformBi (upd val) gofAfter - ) - theRule _ = na "rule_Comprehension_PreImage" - - -rule_Card :: Rule -rule_Card = "sequence-cardinality" `namedRule` theRule where - theRule [essence| |&s| |] = do - TypeSequence{} <- typeOf s - dom <- domainOf s - return - ( "Horizontal rule for sequence cardinality." - , case dom of - DomainSequence _ (SequenceAttr (SizeAttr_Size n) _) _ - -> return n - DomainSequence _ (SequenceAttr _ jectivity) inner - | jectivity `elem` [JectivityAttr_Surjective, JectivityAttr_Bijective] - -> domainSizeOf inner - _ -> do - (iPat, _) <- quantifiedVar - return [essence| sum &iPat in &s . 1 |] - ) - theRule _ = na "rule_Card" - - -rule_Comprehension_Defined :: Rule -rule_Comprehension_Defined = "sequence-defined" `namedRule` theRule where - theRule (Comprehension body gensOrConds) = do - (gofBefore, (pat, expr), gofAfter) <- matchFirst gensOrConds $ \ gof -> case gof of - Generator (GenInExpr pat@Single{} expr) -> return (pat, expr) - _ -> na "rule_Comprehension_Defined" - s <- match opDefined expr - DomainSequence _ (SequenceAttr sizeAttr _) _ <- domainOf s - maxSize <- case sizeAttr of - SizeAttr_Size x -> return x - SizeAttr_MaxSize x -> return x - SizeAttr_MinMaxSize _ x -> return x - _ -> fail "rule_Comprehension_Defined maxSize" - let upd val old = lambdaToFunction pat old val - return - ( "Mapping over defined(f)" - , do - (jPat, j) <- quantifiedVar - let val = j - return $ Comprehension - (upd val body) - $ gofBefore - ++ [ Generator (GenDomainNoRepr jPat $ mkDomainIntB 1 maxSize) - , Condition [essence| &j <= |&s| |] - ] - ++ transformBi (upd val) gofAfter - ) - theRule _ = na "rule_Comprehension_Defined" - - --- | TODO: This may allow repetitions. -rule_Comprehension_Range :: Rule -rule_Comprehension_Range = "sequence-range" `namedRule` theRule where - theRule (Comprehension body gensOrConds) = do - (gofBefore, (pat, expr), gofAfter) <- matchFirst gensOrConds $ \ gof -> case gof of - Generator (GenInExpr pat@Single{} expr) -> return (pat, expr) - _ -> na "rule_Comprehension_PreImage" - func <- match opRange expr - TypeSequence{} <- typeOf func - let upd val old = lambdaToFunction pat old val - return - ( "Mapping over range(f)" - , do - (jPat, j) <- quantifiedVar - let val = [essence| &j[2] |] - return $ Comprehension - (upd val body) - $ gofBefore - ++ [ Generator (GenInExpr jPat func) ] - ++ transformBi (upd val) gofAfter - ) - theRule _ = na "rule_Comprehension_Range" - - -rule_In :: Rule -rule_In = "sequence-in" `namedRule` theRule where - theRule [essence| &x in &f |] = do - TypeSequence{} <- typeOf f - return - ( "Sequence membership to sequence image." - , return [essence| &f(&x[1]) = &x[2] |] - ) - theRule _ = na "rule_In" - - -rule_Restrict_Image :: Rule -rule_Restrict_Image = "sequence-restrict-image" `namedRule` theRule where - theRule p = do - (func', arg) <- match opImage p - (func , dom) <- match opRestrict func' - TypeSequence{} <- typeOf func - return - ( "Sequence image on a restricted sequence." - , do - (iPat, i) <- quantifiedVar - let bob = [essence| exists &iPat : &dom . &i = &arg |] - return $ WithLocals (make opImage func arg) (DefinednessConstraints [bob]) - ) - - -rule_Restrict_Comprehension :: Rule -rule_Restrict_Comprehension = "sequence-restrict-comprehension" `namedRule` theRule where - theRule (Comprehension body gensOrConds) = do - (gofBefore, (iPat, iPatName, expr), gofAfter) <- matchFirst gensOrConds $ \ gof -> case gof of - Generator (GenInExpr iPat@(Single iPatName) expr) -> return (iPat, iPatName, expr) - _ -> na "rule_Comprehension_PreImage" - (func, dom) <- match opRestrict expr - TypeSequence{} <- typeOf func - return - ( "Mapping over restrict(func, dom)" - , do - (jPat, j) <- quantifiedVar - let i = Reference iPatName Nothing - return $ Comprehension body - $ gofBefore - ++ [ Generator (GenInExpr iPat func) - , Condition [essence| exists &jPat : &dom . &j = &i[1] |] - ] - ++ gofAfter - ) - theRule _ = na "rule_Restrict_Comprehension" - - --- | image(f,x) can be nasty for non-total sequences. --- 1. if f is a total sequence, it can readily be replaced by a set expression. --- 2.1. if f isn't total, and if the return type is right, it will always end up as a generator for a comprehension. --- a vertical rule is needed for such cases. --- 2.2. if the return type is not "right", i.e. it is a bool or an int, i.e. sth we cannot quantify over, --- the vertical rule is harder. - -rule_Image_Bool :: Rule -rule_Image_Bool = "sequence-image-bool" `namedRule` theRule where - theRule Reference{} = na "rule_Image_Int" - theRule p = do - let - onChildren - :: MonadState (Maybe (Expression, Expression)) m - => Expression - -> m (Expression -> Expression) - onChildren ch = do - let - try = do - (func, arg) <- match opImage ch - case match opRestrict func of - Nothing -> return () - Just{} -> na "rule_Image_Bool" -- do not use this rule for restricted sequences - TypeSequence TypeBool <- typeOf func - return (func, arg) - case try of - Nothing -> return (const ch) -- do not fail if a child is not of proper form - Just (func, arg) -> do -- just return it back unchanged - seenBefore <- gets id - case seenBefore of - Nothing -> do - modify $ const $ Just (func, arg) - return id - Just{} -> - return (const ch) - - let (children_, gen) = uniplate p - (genChildren, mFunc) <- runStateT (mapM onChildren children_) Nothing - let - mkP :: Expression -> Expression - mkP new = gen $ fmap ($ new) genChildren - (func, arg) <- maybe (na "rule_Image_Bool") return mFunc -- Nothing signifies no relevant children - return - ( "Sequence image, bool." - , do - (iPat, i) <- quantifiedVar - return $ mkP $ make opOr $ Comprehension [essence| &i[2] |] - [ Generator (GenInExpr iPat func) - , Condition [essence| &i[1] = &arg |] - ] - ) - - -rule_Image_Int :: Rule -rule_Image_Int = "sequence-image-int" `namedRule` theRule where - theRule Reference{} = na "rule_Image_Int" - theRule p = do - let - onChildren - :: MonadState (Maybe (Expression, Expression)) m - => Expression - -> m (Expression -> Expression) - onChildren ch = do - let - try = do - (func, arg) <- match opImage ch - case match opRestrict func of - Nothing -> return () - Just{} -> na "rule_Image_Int" -- do not use this rule for restricted sequences -<<<<<<< HEAD - TypeSequence (TypeInt Nothing) <- typeOf func -||||||| merged common ancestors - TypeSequence TypeInt <- typeOf func -======= - TypeSequence (TypeInt _) <- typeOf func ->>>>>>> taggedints - return (func, arg) - case try of - Nothing -> return (const ch) -- do not fail if a child is not of proper form - Just (func, arg) -> do -- just return it back unchanged - seenBefore <- gets id - case seenBefore of - Nothing -> do - modify $ const $ Just (func, arg) - return id - Just{} -> - return (const ch) - - let (children_, gen) = uniplate p - (genChildren, mFunc) <- runStateT (mapM onChildren children_) Nothing - let - mkP :: Expression -> Expression - mkP new = gen $ fmap ($ new) genChildren - (func, arg) <- maybe (na "rule_Image_Int") return mFunc -- Nothing signifies no relevant children - return - ( "Sequence image, int." - , do - (iPat, i) <- quantifiedVar - let val = make opSum $ Comprehension [essence| &i[2] |] - [ Generator (GenInExpr iPat func) - , Condition [essence| &i[1] = &arg |] - ] - isDefined = [essence| &arg in defined(&func) |] - return $ mkP $ WithLocals val (DefinednessConstraints [isDefined]) - ) - - -rule_Comprehension_Image :: Rule -rule_Comprehension_Image = "sequence-image-comprehension" `namedRule` theRule where - theRule (Comprehension body gensOrConds) = do - (gofBefore, (pat, expr), gofAfter) <- matchFirst gensOrConds $ \ gof -> case gof of - Generator (GenInExpr pat@Single{} expr) -> return (pat, expr) - _ -> na "rule_Comprehension_Image" - (mkModifier, expr2) <- match opModifier expr - (func, arg) <- match opImage expr2 - TypeSequence{} <- typeOf func - case match opRestrict func of - Nothing -> return () - Just{} -> na "rule_Image_Bool" -- do not use this rule for restricted sequences - let upd val old = lambdaToFunction pat old val - return - ( "Mapping over the image of a sequence" - , do - (iPat, i) <- quantifiedVar - (jPat, j) <- quantifiedVar - return $ Comprehension - (upd j body) - $ gofBefore - ++ [ Generator (GenInExpr iPat (mkModifier func)) - , Condition [essence| &i[1] = &arg |] - , Generator (GenInExpr jPat [essence| &i[2] |]) - ] - ++ transformBi (upd j) gofAfter - ) - theRule _ = na "rule_Comprehension_Image" - - -rule_Substring :: Rule -rule_Substring = "substring" `namedRule` theRule where - theRule [essence| &a substring &b |] = do - TypeSequence{} <- typeOf a - TypeSequence{} <- typeOf b - - DomainSequence _ (SequenceAttr aSizeAttr _) _ <- domainOf a - aMaxSize <- case aSizeAttr of - SizeAttr_Size x -> return x - SizeAttr_MaxSize x -> return x - SizeAttr_MinMaxSize _ x -> return x - _ -> fail "rule_Substring maxSize" - - DomainSequence _ (SequenceAttr bSizeAttr _) _ <- domainOf b - bMaxSize <- case bSizeAttr of - SizeAttr_Size x -> return x - SizeAttr_MaxSize x -> return x - SizeAttr_MinMaxSize _ x -> return x - _ -> fail "rule_Substring maxSize" - - let maxSize = [essence| max([&aMaxSize, &bMaxSize]) |] - - return - ( "Horizontal rule for substring on 2 sequences" - , do - (iPat, i) <- quantifiedVar - (jPat, j) <- quantifiedVar - return $ make opOr $ Comprehension - (make opAnd $ Comprehension - [essence| &j[2] = image(&b, &i + &j[1]) |] - [ Generator (GenInExpr jPat a) - ] - ) - [ Generator (GenDomainNoRepr iPat $ mkDomainIntB 0 [essence| &maxSize - 1 |])] - ) - theRule _ = na "rule_Substring" - - -rule_Subsequence :: Rule -rule_Subsequence = "subsequence" `namedRule` theRule where - theRule [essence| &a subsequence &b |] = do - TypeSequence{} <- typeOf a - TypeSequence{} <- typeOf b - - DomainSequence _ (SequenceAttr aSizeAttr _) _ <- domainOf a - aMaxSize <- case aSizeAttr of - SizeAttr_Size x -> return x - SizeAttr_MaxSize x -> return x - SizeAttr_MinMaxSize _ x -> return x - _ -> fail "rule_Subsequence maxSize" - - DomainSequence _ (SequenceAttr bSizeAttr _) _ <- domainOf b - bMaxSize <- case bSizeAttr of - SizeAttr_Size x -> return x - SizeAttr_MaxSize x -> return x - SizeAttr_MinMaxSize _ x -> return x - _ -> fail "rule_Subsequence maxSize" - - -- for each value in a, find an index into b such that these indices are in increasing order - -- when there are multiple mappings that produce the same "a" (i.e. when there are duplicates in b) - -- this is does not functionally define the aux variable - return - ( "Horizontal rule for subsequence on 2 sequences" - , do - (auxName, aux) <- auxiliaryVar - (iPat, i) <- quantifiedVar - return $ WithLocals - [essence| - and([ &i[2] = image(&b, image(&aux, &i[1])) - | &iPat <- &a - ]) - |] - (AuxiliaryVars - [ Declaration (FindOrGiven LocalFind auxName - (DomainSequence def (SequenceAttr aSizeAttr def) (mkDomainIntB 1 bMaxSize))) - , SuchThat - [ [essence| and([ image(&aux, &i-1) < image(&aux, &i) - | &iPat : int(2..&aMaxSize) - , &i <= |&aux| - ]) - |] - , [essence| |&a| = |&aux| - |] - ] - ]) - ) - theRule _ = na "rule_Subsequence" diff --git a/src/Conjure/Rules/Horizontal/Set.hs.orig b/src/Conjure/Rules/Horizontal/Set.hs.orig deleted file mode 100644 index 8b2aa84c72..0000000000 --- a/src/Conjure/Rules/Horizontal/Set.hs.orig +++ /dev/null @@ -1,471 +0,0 @@ -{-# LANGUAGE QuasiQuotes #-} - -module Conjure.Rules.Horizontal.Set where - -import Conjure.Rules.Import -import Conjure.Process.Sanity ( isInfinite ) - -rule_Comprehension_Literal :: Rule -rule_Comprehension_Literal = "set-comprehension-literal" `namedRule` theRule where - theRule (Comprehension body gensOrConds) = do - (gocBefore, (pat, expr), gocAfter) <- matchFirst gensOrConds $ \ goc -> case goc of - Generator (GenInExpr pat@Single{} expr) -> return (pat, matchDefs [opToSet, opToMSet] expr) - _ -> na "rule_Comprehension_Literal" - (TypeSet tau, elems) <- match setLiteral expr - let outLiteral = make matrixLiteral - (TypeMatrix (TypeInt NoTag) tau) - (DomainInt NoTag [RangeBounded 1 (fromInt (genericLength elems))]) - elems - let upd val old = lambdaToFunction pat old val - return - ( "Comprehension on set literals" - , do - (iPat, i) <- quantifiedVar - return $ Comprehension (upd i body) - $ gocBefore - ++ [Generator (GenInExpr iPat outLiteral)] - ++ transformBi (upd i) gocAfter - ) - theRule _ = na "rule_Comprehension_Literal" - - -rule_Eq :: Rule -rule_Eq = "set-eq" `namedRule` theRule where - theRule p = do - (x,y) <- match opEq p - TypeSet{} <- typeOf x - TypeSet{} <- typeOf y - return - ( "Horizontal rule for set equality" - , return $ make opAnd $ fromList - [ make opSubsetEq x y - , make opSubsetEq y x - ] - ) - - -rule_Neq :: Rule -rule_Neq = "set-neq" `namedRule` theRule where - theRule [essence| &x != &y |] = do - TypeSet{} <- typeOf x - TypeSet{} <- typeOf y - return - ( "Horizontal rule for set dis-equality" - , do - (iPat, i) <- quantifiedVar - return [essence| - (exists &iPat in &x . !(&i in &y)) - \/ - (exists &iPat in &y . !(&i in &x)) - |] - ) - theRule _ = na "rule_Neq" - - -rule_SubsetEq :: Rule -rule_SubsetEq = "set-subsetEq" `namedRule` theRule where - theRule p = do - (x,y) <- match opSubsetEq p - TypeSet{} <- typeOf x - TypeSet{} <- typeOf y - return - ( "Horizontal rule for set subsetEq" - , do - (iPat, i) <- quantifiedVar - return [essence| forAll &iPat in &x . &i in &y |] - ) - - -rule_Subset :: Rule -rule_Subset = "set-subset" `namedRule` theRule where - theRule [essence| &a subset &b |] = do - TypeSet{} <- typeOf a - TypeSet{} <- typeOf b - return - ( "Horizontal rule for set subset" - , return [essence| &a subsetEq &b /\ &a != &b |] - ) - theRule _ = na "rule_Subset" - - -rule_Supset :: Rule -rule_Supset = "set-supset" `namedRule` theRule where - theRule [essence| &a supset &b |] = do - TypeSet{} <- typeOf a - TypeSet{} <- typeOf b - return - ( "Horizontal rule for set supset" - , return [essence| &b subset &a |] - ) - theRule _ = na "rule_Supset" - - -rule_SupsetEq :: Rule -rule_SupsetEq = "set-subsetEq" `namedRule` theRule where - theRule [essence| &a supsetEq &b |] = do - TypeSet{} <- typeOf a - TypeSet{} <- typeOf b - return - ( "Horizontal rule for set supsetEq" - , return [essence| &b subsetEq &a |] - ) - theRule _ = na "rule_SupsetEq" - - -<<<<<<< HEAD -rule_DotLt :: Rule -rule_DotLt = "set-DotLt" `namedRule` theRule where - theRule p = do - (a,b) <- match opDotLt p - TypeSet{} <- typeOf a - TypeSet{} <- typeOf b - sameRepresentation a b - ma <- tupleLitIfNeeded <$> downX1 a - mb <- tupleLitIfNeeded <$> downX1 b - return - ( "Horizontal rule for set .<" <+> pretty (make opDotLt ma mb) - , return $ make opDotLt ma mb - ) - - -rule_DotLeq :: Rule -rule_DotLeq = "set-DotLeq" `namedRule` theRule where - --This works but not for occurrence rep - theRule [essence| &a .<= image(&perm, &b) |] = do - TypeSet{} <- typeOf a - TypeSet{} <- typeOf b - TypePermutation{} <- typeOf perm - sameRepresentation a b - ma <- tupleLitIfNeeded <$> downX1 a - mb <- tupleLitIfNeeded <$> downX1 b - return - ( "Horizontal rule for set .<=" - <+> pretty ([essence| &ma .<= image(&perm, &mb) |]) - - , return $ [essence| &ma .<= image(&perm, &mb) |] - ) - theRule p = do - (a,b) <- match opDotLeq p - TypeSet{} <- typeOf a - TypeSet{} <- typeOf b - sameRepresentation a b - ma <- tupleLitIfNeeded <$> downX1 a - mb <- tupleLitIfNeeded <$> downX1 b - return - ( "Horizontal rule for set .<=" <+> pretty (make opDotLeq ma mb) - , return $ make opDotLeq ma mb - ) - - -||||||| merged common ancestors -rule_DotLt :: Rule -rule_DotLt = "set-DotLt" `namedRule` theRule where - theRule p = do - (a,b) <- match opDotLt p - TypeSet{} <- typeOf a - TypeSet{} <- typeOf b - sameRepresentation a b - ma <- tupleLitIfNeeded <$> downX1 a - mb <- tupleLitIfNeeded <$> downX1 b - return - ( "Horizontal rule for set .<" <+> pretty (make opDotLt ma mb) - , return $ make opDotLt ma mb - ) - - -rule_DotLeq :: Rule -rule_DotLeq = "set-DotLeq" `namedRule` theRule where - theRule p = do - (a,b) <- match opDotLeq p - TypeSet{} <- typeOf a - TypeSet{} <- typeOf b - sameRepresentation a b - ma <- tupleLitIfNeeded <$> downX1 a - mb <- tupleLitIfNeeded <$> downX1 b - return - ( "Horizontal rule for set .<=" <+> pretty (make opDotLeq ma mb) - , return $ make opDotLeq ma mb - ) - - -======= ->>>>>>> master -rule_Intersect :: Rule -rule_Intersect = "set-intersect" `namedRule` theRule where - theRule (Comprehension body gensOrConds) = do - (gocBefore, (pat, iPat, expr), gocAfter) <- matchFirst gensOrConds $ \ goc -> case goc of - Generator (GenInExpr pat@(Single iPat) expr) -> - return (pat, iPat, matchDefs [opToSet,opToMSet,opToRelation] expr) - _ -> na "rule_Intersect" - (mkModifier, s) <- match opModifier expr - (x, y) <- match opIntersect s - tx <- typeOf x - case tx of - TypeSet{} -> return () - TypeMSet{} -> return () - TypeFunction{} -> return () - TypeRelation{} -> return () - _ -> fail "type incompatibility in intersect operator" - let i = Reference iPat Nothing - return - ( "Horizontal rule for set intersection" - , return $ - Comprehension body - $ gocBefore - ++ [ Generator (GenInExpr pat (mkModifier x)) - , Condition [essence| &i in &y |] - ] - ++ gocAfter - ) - theRule _ = na "rule_Intersect" - - -rule_Union :: Rule -rule_Union = "set-union" `namedRule` theRule where - theRule (Comprehension body gensOrConds) = do - (gocBefore, (pat, iPat, expr), gocAfter) <- matchFirst gensOrConds $ \ goc -> case goc of - Generator (GenInExpr pat@(Single iPat) expr) -> return (pat, iPat, matchDef opToSet expr) - _ -> na "rule_Union" - (mkModifier, s) <- match opModifier expr - (x, y) <- match opUnion s - tx <- typeOf x - case tx of - TypeSet{} -> return () - TypeMSet{} -> return () - TypeFunction{} -> return () - TypeRelation{} -> return () - _ -> fail "type incompatibility in union operator" - let i = Reference iPat Nothing - return - ( "Horizontal rule for set union" - , return $ make opFlatten $ AbstractLiteral $ AbsLitMatrix - (DomainInt NoTag [RangeBounded 1 2]) - [ Comprehension body - $ gocBefore - ++ [ Generator (GenInExpr pat (mkModifier x)) ] - ++ gocAfter - , Comprehension body - $ gocBefore - ++ [ Generator (GenInExpr pat (mkModifier y)) - , Condition [essence| !(&i in &x) |] - ] - ++ gocAfter - ] - ) - theRule _ = na "rule_Union" - - -rule_Difference :: Rule -rule_Difference = "set-difference" `namedRule` theRule where - theRule (Comprehension body gensOrConds) = do - (gocBefore, (pat, iPat, expr), gocAfter) <- matchFirst gensOrConds $ \ goc -> case goc of - Generator (GenInExpr pat@(Single iPat) expr) -> return (pat, iPat, expr) - _ -> na "rule_Difference" - (mkModifier, s) <- match opModifier expr - (x, y) <- match opMinus s - tx <- typeOf x - case tx of - TypeSet{} -> return () - TypeMSet{} -> return () - TypeFunction{} -> return () - TypeRelation{} -> return () - _ -> fail "type incompatibility in difference operator" - let i = Reference iPat Nothing - return - ( "Horizontal rule for set difference" - , return $ - Comprehension body - $ gocBefore - ++ [ Generator (GenInExpr pat (mkModifier x)) - , Condition [essence| !(&i in &y) |] - ] - ++ gocAfter - ) - theRule _ = na "rule_Difference" - - -rule_PowerSet_Difference :: Rule -rule_PowerSet_Difference = "set-powerSet-difference" `namedRule` theRule where - theRule (Comprehension body gensOrConds) = do - (gocBefore, (pat, expr), gocAfter) <- matchFirst gensOrConds $ \ goc -> case goc of - Generator (GenInExpr pat expr) -> return (pat, expr) - _ -> na "rule_PowerSet_Difference" - setExpr <- match opPowerSet expr - (x, y) <- match opMinus setExpr - let patAsExpr = patternToExpr pat - return - ( "Horizontal rule for set powerSet difference" - , return $ - Comprehension body - $ gocBefore - ++ [ Generator (GenInExpr pat (make opPowerSet x)) - , Condition [essence| !(&patAsExpr subsetEq &y) |] - ] - ++ gocAfter - ) - theRule _ = na "rule_PowerSet_Difference" - - -rule_PowerSet_Comprehension :: Rule -rule_PowerSet_Comprehension = "set-powerSet-comprehension" `namedRule` theRule where - theRule (Comprehension body gensOrConds) = do - (gocBefore, (patName, expr), gocAfter) <- matchFirst gensOrConds $ \ goc -> case goc of - Generator (GenInExpr (Single patName) expr) -> return (patName, expr) - _ -> na "rule_PowerSet_Comprehension" - s <- match opPowerSet expr - sDom <- domainOf s - let sDom' = - -- only keep the maxsize attribute - case sDom of - DomainSet () (SetAttr sAttr) sInner -> - let - sAttr' = - case sAttr of - SizeAttr_None -> SizeAttr_None - SizeAttr_Size x -> SizeAttr_MaxSize x - SizeAttr_MinSize _ -> SizeAttr_None - SizeAttr_MaxSize x -> SizeAttr_MaxSize x - SizeAttr_MinMaxSize _ x -> SizeAttr_MaxSize x - in - DomainSet () (SetAttr sAttr') sInner - _ -> sDom - let pat = Single patName - let patAsExpr = Reference patName Nothing - return - ( "Horizontal rule for set-comprehension over powerSet" - , return $ - Comprehension body - $ gocBefore - ++ [ Generator (GenDomainNoRepr pat sDom') - , Condition [essence| &patAsExpr subsetEq &s |] - ] - ++ gocAfter - ) - theRule _ = na "rule_PowerSet_Comprehension" - - -rule_MaxMin :: Rule -rule_MaxMin = "set-max-min" `namedRule` theRule where - theRule [essence| max(&s) |] = do - TypeSet (TypeInt _) <- typeOf s - return - ( "Horizontal rule for set max" - , do - (iPat, i) <- quantifiedVar - return [essence| max([&i | &iPat <- &s]) |] - ) - theRule [essence| min(&s) |] = do - TypeSet (TypeInt _) <- typeOf s - return - ( "Horizontal rule for set min" - , do - (iPat, i) <- quantifiedVar - return [essence| min([&i | &iPat <- &s]) |] - ) - theRule _ = na "rule_MaxMin" - - --- x in s ~~> or([ x = i | i in s ]) -rule_In :: Rule -rule_In = "set-in" `namedRule` theRule where - theRule p = do - (x,s) <- match opIn p - TypeSet{} <- typeOf s - -- do not apply this rule to quantified variables - -- or else we might miss the opportunity to apply a more specific vertical rule - if referenceToComprehensionVar s - then na "rule_In" - else return () - return - ( "Horizontal rule for set-in." - , do - (iPat, i) <- quantifiedVar - return [essence| exists &iPat in &s . &i = &x |] - ) - - -rule_Card :: Rule -rule_Card = "set-card" `namedRule` theRule where - theRule p = do - s <- match opTwoBars p - case s of - Domain{} -> na "rule_Card" - _ -> return () - TypeSet{} <- typeOf s - return - ( "Horizontal rule for set cardinality." - , do - mdom <- runMaybeT $ domainOf s - case mdom of - Just (DomainSet _ (SetAttr (SizeAttr_Size n)) _) -> return n - _ -> do - (iPat, _) <- quantifiedVar - return [essence| sum &iPat in &s . 1 |] - ) - - -rule_CardViaFreq :: Rule -rule_CardViaFreq = "set-card-via-freq" `namedRule` theRule where - theRule [essence| freq(toMSet(&s),&x) |] = do - case s of - Domain{} -> na "rule_CardViaFreq" - _ -> return () - TypeSet{} <- typeOf s - return - ( "Horizontal rule for set cardinality." - , return [essence| toInt(&x in &s) |] - ) - theRule _ = na "rule_CardViaFreq" - - -rule_Param_MinOfSet :: Rule -rule_Param_MinOfSet = "param-min-of-set" `namedRule` theRule where - theRule [essence| min(&s) |] = do - TypeSet (TypeInt _) <- typeOf s - unless (categoryOf s == CatParameter) $ na "rule_Param_MinOfSet" - DomainSet _ _ inner <- domainOf s - case inner of - DomainInt _ rs | isInfinite rs -> na "rule_Param_MaxOfSet" - _ -> return () - return - ( "min of a parameter set" - , case inner of - DomainInt _ [RangeBounded l _] -> return l - _ -> do - (iPat, i) <- quantifiedVar - return [essence| min([ &i | &iPat : &inner ]) |] - ) - theRule _ = na "rule_Param_MinOfSet" - - -rule_Param_MaxOfSet :: Rule -rule_Param_MaxOfSet = "param-max-of-set" `namedRule` theRule where - theRule [essence| max(&s) |] = do - TypeSet (TypeInt _) <- typeOf s - unless (categoryOf s == CatParameter) $ na "rule_Param_MaxOfSet" - DomainSet _ _ inner <- domainOf s - case inner of - DomainInt _ rs | isInfinite rs -> na "rule_Param_MaxOfSet" - _ -> return () - return - ( "max of a parameter set" - , case inner of - DomainInt _ [RangeBounded _ u] -> return u - _ -> do - (iPat, i) <- quantifiedVar - return [essence| max([ &i | &iPat : &inner ]) |] - ) - theRule _ = na "rule_Param_MaxOfSet" - - -rule_Param_Card :: Rule -rule_Param_Card = "param-card-of-set" `namedRule` theRule where - theRule [essence| |&s| |] = do - TypeSet (TypeInt _) <- typeOf s - unless (categoryOf s == CatParameter) $ na "rule_Param_Card" - DomainSet _ (SetAttr (SizeAttr_Size n)) _ <- domainOf s - return - ( "cardinality of a parameter set" - , return n - ) - theRule _ = na "rule_Param_Card" diff --git a/src/Conjure/Rules/Vertical/Matrix.hs.orig b/src/Conjure/Rules/Vertical/Matrix.hs.orig deleted file mode 100644 index cea956ec40..0000000000 --- a/src/Conjure/Rules/Vertical/Matrix.hs.orig +++ /dev/null @@ -1,572 +0,0 @@ -{-# LANGUAGE QuasiQuotes #-} -{-# LANGUAGE ViewPatterns #-} - -module Conjure.Rules.Vertical.Matrix where - -import Conjure.Rules.Import -<<<<<<< HEAD -import Conjure.Rules.Vertical.Tuple ( decomposeLexLt, decomposeLexLeq, decomposeLexDotLt, decomposeLexDotLeq) -||||||| merged common ancestors -import Conjure.Rules.Vertical.Tuple ( decomposeLexLt, decomposeLexLeq, decomposeLexDotLt, decomposeLexDotLeq ) -======= -import Conjure.Rules.Vertical.Tuple ( decomposeLexLt, decomposeLexLeq ) ->>>>>>> master - - -rule_Comprehension_Literal :: Rule -rule_Comprehension_Literal = "matrix-comprehension-literal" `namedRule` theRule where - theRule (Comprehension body gensOrConds) = do - (gocBefore, (pat, expr), gocAfter) <- matchFirst gensOrConds $ \ goc -> case goc of - Generator (GenInExpr (Single pat) expr) -> return (pat, expr) - _ -> na "rule_Comprehension_Literal" - (_, _index, elems) <- match matrixLiteral expr - tyInner <- typeOf body - let ty = TypeMatrix (TypeInt NoTag) tyInner - return - ( "Vertical rule for matrix-comprehension on matrix literal" - , return $ if null elems - then make matrixLiteral ty (mkDomainIntB 1 0) [] - else make opConcatenate $ AbstractLiteral $ AbsLitMatrix - (mkDomainIntB 1 (fromInt $ genericLength elems)) - [ Comprehension body - $ gocBefore - ++ [ComprehensionLetting pat el] - ++ gocAfter - | el <- elems - ] - ) - theRule _ = na "rule_Comprehension_Literal" - - --- | input: [ i | i <- m[j] ] with m = [a,b,c] --- output: [ [ i | i <- a ] --- , [ i | i <- b ] --- , [ i | i <- c ] --- ][j] --- namely: [ [ m[k] --- | k : int(1..3) --- ] --- , [ i | i <- b ] --- , [ i | i <- c ] --- ][j] - -rule_ModifierAroundIndexedMatrixLiteral :: Rule -rule_ModifierAroundIndexedMatrixLiteral = "modifier-around-indexed-matrix-literal" `namedRule` theRule where - theRule p = do - (mkM, p2) <- match opModifier p - (matrix, indices) <- match opMatrixIndexing p2 - case match opMatrixIndexing p of - Nothing -> return () - Just{} -> na "rule_ModifierAroundIndexedMatrixLiteral, no modifier" - let - fullyMatrixLiteral 0 _ = return True - fullyMatrixLiteral n m = - case match matrixLiteral m of - Nothing -> return False - Just (_, _, elems) -> and <$> mapM (fullyMatrixLiteral (n-1)) elems - True <- fullyMatrixLiteral (length indices) matrix - return - ( "Pushing a modifier inwards, through a matrix literal" - , do - matrix' <- onMatrixLiteral Nothing (return . mkM) matrix - return $ make opMatrixIndexing matrix' indices - ) - - -rule_QuantifierAroundIndexedMatrixLiteral :: Rule -rule_QuantifierAroundIndexedMatrixLiteral = "quantifier-around-indexed-matrix-literal" `namedRule` theRule where - theRule p = do - (_, mkM, p2) <- match opReducer p - (matrix, indices) <- match opMatrixIndexing p2 - case match opMatrixIndexing p of - Nothing -> return () - Just{} -> na "rule_ModifierAroundIndexedMatrixLiteral, no quantifier" - -- let - -- fullyMatrixLiteral 0 _ = return True - -- fullyMatrixLiteral n m = - -- case match matrixLiteral m of - -- Nothing -> return False - -- Just (_, _, elems) -> and <$> mapM (fullyMatrixLiteral (n-1)) elems - -- True <- fullyMatrixLiteral (length indices) matrix - return - ( "Pushing a modifier inwards, through a matrix literal" - , do - matrix' <- onMatrixLiteral (Just (length indices)) (return . mkM) matrix - return $ make opMatrixIndexing matrix' indices - ) - - -rule_Comprehension_LiteralIndexed :: Rule -rule_Comprehension_LiteralIndexed = "matrix-comprehension-literal-indexed" `namedRule` theRule where - theRule (Comprehension body gensOrConds) = do - (gocBefore, (pat, expr), gocAfter) <- matchFirst gensOrConds $ \ goc -> case goc of - Generator (GenInExpr pat@Single{} expr) -> return (pat, expr) - _ -> na "rule_Comprehension_LiteralIndexed" - tyExpr <- typeOf expr - (matrix, indices) <- match opMatrixIndexing expr - (_, _index, elems) <- match matrixLiteral matrix - return - ( "Vertical rule for matrix-comprehension on matrix literal" - , case indices of - [] -> bug "rule_Comprehension_LiteralIndexed indices=[]" - [index] -> - return $ make opFlatten $ AbstractLiteral $ AbsLitMatrix - (mkDomainIntB 1 (fromInt $ genericLength elems)) - [ Comprehension body - $ gocBefore - ++ [ Generator (GenInExpr pat el) - , Condition [essence| &num = &index |] - ] - ++ gocAfter - | (num', el') <- zip [1..] elems - , let num = fromInt num' - -- let's not lose the type information for empty collections - , let el = if emptyCollectionX el' - then case el' of Typed{} -> el' - _ -> Typed el' tyExpr - else el' - ] - (index:rest) -> - return $ make opFlatten $ AbstractLiteral $ AbsLitMatrix - (mkDomainIntB 1 (fromInt $ genericLength elems)) - [ Comprehension body - $ gocBefore - ++ [ Generator (GenInExpr pat (make opMatrixIndexing el rest)) - , Condition [essence| &num = &index |] - ] - ++ gocAfter - | (num', el') <- zip [1..] elems - , let num = fromInt num' - -- let's not lose the type information for empty collections - , let el = if emptyCollectionX el' - then case el' of Typed{} -> el' - _ -> Typed el' tyExpr - else el' - ] - ) - theRule _ = na "rule_Comprehension_LiteralIndexed" - - -rule_Comprehension_ToSet_Matrix :: Rule -rule_Comprehension_ToSet_Matrix = "matrix-toSet-matrixInside" `namedRule` theRule where - theRule (Comprehension body gensOrConds) = do - (gocBefore, (pat, expr), gocAfter) <- matchFirst gensOrConds $ \ goc -> case goc of - Generator (GenInExpr pat@Single{} expr) -> return (pat, expr) - _ -> na "rule_Comprehension_ToSet" - matrix <- match opToSet expr - TypeMatrix{} <- typeOf matrix - let upd val old = lambdaToFunction pat old val - return - ( "Vertical rule for comprehension over matrix-toSet, matrix inside" - , do - (iPat, i) <- quantifiedVar - let val = make opIndexing i 1 - let over = make opHist matrix - return $ Comprehension (upd val body) - $ gocBefore - ++ [Generator (GenInExpr iPat over)] - ++ transformBi (upd val) gocAfter - ) - theRule _ = na "rule_Comprehension_ToSet" - - -rule_Comprehension_ToSet_List :: Rule -rule_Comprehension_ToSet_List = "matrix-toSet-listInside" `namedRule` theRule where - theRule p = do - -- we cannot assume that the list is duplciate-free - (False, Comprehension body gensOrConds) <- match opToSetWithFlag p - bodyDomain <- domainOf body - let auxDomain = DomainSet () (SetAttr SizeAttr_None) bodyDomain - return - ( "Vertical rule for comprehension over matrix-toSet, list inside" - , do - (auxName, aux) <- auxiliaryVar - (iPat, i) <- quantifiedVar - return $ WithLocals aux $ - AuxiliaryVars - [ Declaration (FindOrGiven LocalFind auxName auxDomain) - , SuchThat - -- forAll i in list . i in aux - [ make opAnd $ Comprehension - [essence| &body in &aux |] - gensOrConds - -- forAll i in aux . exists j in list . i = j - , make opAnd $ Comprehension - (make opOr (Comprehension [essence| &i = &body |] gensOrConds)) - [Generator (GenInExpr iPat aux)] - ] - ] - ) - - -rule_Comprehension_ToSet_List_DuplicateFree :: Rule -rule_Comprehension_ToSet_List_DuplicateFree = "matrix-toSet-listInside-nodups" `namedRule` theRule where - theRule (Comprehension body gensOrConds) = do - (gocBefore, (pat, expr), gocAfter) <- matchFirst gensOrConds $ \ goc -> case goc of - Generator (GenInExpr pat@Single{} expr) -> return (pat, matchDefs [opToMSet] expr) - _ -> na "rule_Comprehension_ToSet" - -- we *can* assume that the list is duplicate-free! - (True, list) <- match opToSetWithFlag expr - TypeList{} <- typeOf list - return - ( "Vertical rule for comprehension over matrix-toSet, list inside, assumed no duplicates" - , return $ Comprehension body - $ gocBefore - ++ [Generator (GenInExpr pat list)] - ++ gocAfter - ) - theRule _ = na "rule_Comprehension_ToSet_List_DuplicateFree" - - --- [ i | ... , i <- [ j | ... j ... ], ... i ... ] --- [ j | ... , ... j ..., ... j ... ] -rule_Comprehension_Nested :: Rule -rule_Comprehension_Nested = "matrix-comprehension-nested" `namedRule` theRule where - theRule (Comprehension body gensOrConds) = do - (gocBefore, (pat, Comprehension innerBody innerGocs), gocAfter) <- matchFirst gensOrConds $ \case - Generator (GenInExpr pat@Single{} expr) -> return (pat, matchDefs [opToMSet] expr) - _ -> na "rule_Comprehension_Nested" - let upd val old = lambdaToFunction pat old val - let - -- update the quantified variable names inside innerBody&innerGocs_ here, - -- because they may be shadowed. - updateQuantified innerBody_ innerGocs_ = do - let olds = concatMap collectOldQuantifiers innerGocs_ - if null olds - then return (innerBody_, innerGocs_) - else do - oldnews <- forM olds $ \ old -> do - (Single new, _) <- quantifiedVar - return (old, new) - let - f :: Name -> Name - f nm = fromMaybe nm (lookup nm oldnews) - return (transformBi f (innerBody_, innerGocs_)) - - collectOldQuantifiers = \case - Generator (GenDomainNoRepr pt _) -> universeBi pt - Generator (GenDomainHasRepr nm _) -> [nm] - Generator (GenInExpr pt _) -> universeBi pt - Condition _ -> [] - ComprehensionLetting nm _ -> [nm] - - (innerBody', innerGocs') <- updateQuantified innerBody innerGocs - return - ( "Nested matrix comprehension" - , return $ Comprehension (upd innerBody' body) - $ gocBefore - ++ innerGocs' - ++ transformBi (upd innerBody') gocAfter - ) - theRule _ = na "rule_Comprehension_Nested" - - -rule_Comprehension_Hist :: Rule -rule_Comprehension_Hist = "matrix-hist" `namedRule` theRule where - theRule (Comprehension body gensOrConds) = do - (gocBefore, (pat, expr), gocAfter) <- matchFirst gensOrConds $ \ goc -> case goc of - Generator (GenInExpr pat@Single{} expr) -> return (pat, expr) - _ -> na "rule_Comprehension_Hist" - matrix <- match opHist expr - TypeMatrix{} <- typeOf matrix - index:_ <- indexDomainsOf matrix - let upd val old = lambdaToFunction pat old val - return - ( "Vertical rule for comprehension over matrix-hist" - , do - (iPat, i) <- quantifiedVar - (jPat, j) <- quantifiedVar - let value = [essence| &matrix[&i] |] - -- if this is the left-most occurrence of value - -- count all - -- otherwise, 0 - count = [essence| - sum([ 1 $ number of occurrences of this value in the matrix - | &jPat : &index - , &matrix[&i] = &matrix[&j] - ]) - |] - val = AbstractLiteral $ AbsLitTuple [value, count] - appearsBefore = [essence| - or([ &matrix[&j] = &matrix[&i] - | &jPat : &index - , &j < &i - ]) - |] - return $ Comprehension (upd val body) - $ gocBefore - ++ [ Generator (GenDomainNoRepr iPat index) - , Condition [essence| ! &appearsBefore |] - ] - ++ transformBi (upd val) gocAfter - ) - theRule _ = na "rule_Comprehension_Hist" - - -rule_Matrix_Eq :: Rule -rule_Matrix_Eq = "matrix-eq" `namedRule` theRule where - theRule p = do - (x,y) <- match opEq p - TypeMatrix{} <- typeOf x -- TODO: check if x and y have the same arity - TypeMatrix{} <- typeOf y - indexX:_ <- indexDomainsOf x - indexY:_ <- indexDomainsOf y - return - ( "Horizontal rule for matrix =" - , do - (iPat, i) <- quantifiedVar - (jPat, j) <- quantifiedVar - -- avoid generating the index equality constraint, if the indices are literally the same - if indexX == indexY - then - return [essence| - (forAll &iPat : &indexX . &x[&i] = &y[&i]) - |] - else - return [essence| - (forAll &iPat : &indexX . &x[&i] = &y[&i]) - /\ - (forAll &iPat : &indexX . exists &jPat : &indexY . &i = &j) - /\ - (forAll &iPat : &indexY . exists &jPat : &indexX . &i = &j) - |] - ) - - -rule_Matrix_Neq :: Rule -rule_Matrix_Neq = "matrix-neq" `namedRule` theRule where - theRule p = do - (x,y) <- match opNeq p - TypeMatrix{} <- typeOf x -- TODO: check if x and y have the same arity - TypeMatrix{} <- typeOf y - indexX:_ <- indexDomainsOf x - indexY:_ <- indexDomainsOf y - return - ( "Horizontal rule for matrix !=" - , do - (iPat, i) <- quantifiedVar - return [essence| - (exists &iPat : &indexX . &x[&i] != &y[&i]) - \/ - (exists &iPat : &indexY . &x[&i] != &y[&i]) - |] - ) - - -flattenIfNeeded :: MonadFail m => Expression -> m Expression -flattenIfNeeded m = do - tyM <- typeOf m - let nestingLevel (TypeMatrix _ a) = 1 + nestingLevel a - nestingLevel (TypeList a) = 1 + nestingLevel a - nestingLevel _ = 0 :: Int - return $ if nestingLevel tyM > 1 - then make opFlatten m - else m - - -rule_Matrix_Lt_Primitive :: Rule -rule_Matrix_Lt_Primitive = "matrix-Lt-primitive" `namedRule` theRule where - theRule p = do - (x,y) <- case (match opLt p, match opDotLt p) of - (Just a, _) -> return a - (_, Just a) -> return a - _ -> na "rule_Matrix_Lt_Primitive" - tx@TypeMatrix{} <- typeOf x -- TODO: check if x and y have the same arity - ty@TypeMatrix{} <- typeOf y - unless (isPrimitiveType tx) $ fail ("not a primitive type:" <+> pretty tx) - unless (isPrimitiveType ty) $ fail ("not a primitive type:" <+> pretty ty) - x' <- flattenIfNeeded x - y' <- flattenIfNeeded y - return - ( "Horizontal rule for matrix <" - , return [essence| &x' return a - (_, Just a) -> return a - _ -> na "rule_Matrix_Leq_Primitive" - tx@TypeMatrix{} <- typeOf x -- TODO: check if x and y have the same arity - ty@TypeMatrix{} <- typeOf y - unless (isPrimitiveType tx) $ fail ("not a primitive type:" <+> pretty tx) - unless (isPrimitiveType ty) $ fail ("not a primitive type:" <+> pretty ty) - x' <- flattenIfNeeded x - y' <- flattenIfNeeded y - return - ( "Horizontal rule for matrix <=" - , return [essence| &x' <=lex &y' |] - ) - - -rule_Matrix_Lt_Decompose :: Rule -rule_Matrix_Lt_Decompose = "matrix-Lt-tuple" `namedRule` theRule where - theRule p = do - (x,y) <- match opLt p - tx@TypeMatrix{} <- typeOf x -- TODO: check matrix index & tuple arity - ty@TypeMatrix{} <- typeOf y - when (isPrimitiveType tx) $ fail ("this is a primitive type:" <+> pretty tx) - when (isPrimitiveType ty) $ fail ("this is a primitive type:" <+> pretty ty) - xs <- downX1 x - ys <- downX1 y - return - ( "Horizontal rule for matrix <, decomposing" - , return $ decomposeLexLt p xs ys - ) - - -rule_Matrix_Leq_Decompose :: Rule -rule_Matrix_Leq_Decompose = "matrix-Leq-tuple" `namedRule` theRule where - theRule p = do - (x,y) <- match opLeq p - tx@TypeMatrix{} <- typeOf x -- TODO: check matrix index & tuple arity - ty@TypeMatrix{} <- typeOf y - when (isPrimitiveType tx) $ fail ("this is a primitive type:" <+> pretty tx) - when (isPrimitiveType ty) $ fail ("this is a primitive type:" <+> pretty ty) - xs <- downX1 x - ys <- downX1 y - return - ( "Horizontal rule for matrix <=, decomposing" - , return $ decomposeLexLeq p xs ys - ) - - -<<<<<<< HEAD -rule_Matrix_DotLt_Decompose :: Rule -rule_Matrix_DotLt_Decompose = "matrix-DotLt-tuple" `namedRule` theRule where - theRule p = do - (x,y) <- match opDotLt p - tx@TypeMatrix{} <- typeOf x -- TODO: check matrix index & tuple arity - ty@TypeMatrix{} <- typeOf y - when (isPrimitiveType tx) $ fail ("this is a primitive type:" <+> pretty tx) - when (isPrimitiveType ty) $ fail ("this is a primitive type:" <+> pretty ty) - xs <- downX1 x - ys <- downX1 y - return - ( "Horizontal rule for matrix .<, decomposing" - , return $ decomposeLexDotLt p xs ys - ) - - -rule_Matrix_DotLeq_Decompose :: Rule -rule_Matrix_DotLeq_Decompose = "matrix-DotLeq-tuple" `namedRule` theRule where - theRule p = do - (x,y) <- match opDotLeq p - tx@TypeMatrix{} <- typeOf x -- TODO: check matrix index & tuple arity - ty@TypeMatrix{} <- typeOf y - when (isPrimitiveType tx) $ fail ("this is a primitive type:" <+> pretty tx) - when (isPrimitiveType ty) $ fail ("this is a primitive type:" <+> pretty ty) - xs <- downX1 x - ys <- downX1 y - return - ( "Horizontal rule for matrix .<=, decomposing" - , return $ decomposeLexDotLeq p xs ys - ) - -||||||| merged common ancestors -rule_Matrix_DotLt_Decompose :: Rule -rule_Matrix_DotLt_Decompose = "matrix-DotLt-tuple" `namedRule` theRule where - theRule p = do - (x,y) <- match opDotLt p - tx@TypeMatrix{} <- typeOf x -- TODO: check matrix index & tuple arity - ty@TypeMatrix{} <- typeOf y - when (isPrimitiveType tx) $ fail ("this is a primitive type:" <+> pretty tx) - when (isPrimitiveType ty) $ fail ("this is a primitive type:" <+> pretty ty) - xs <- downX1 x - ys <- downX1 y - return - ( "Horizontal rule for matrix .<, decomposing" - , return $ decomposeLexDotLt p xs ys - ) - - -rule_Matrix_DotLeq_Decompose :: Rule -rule_Matrix_DotLeq_Decompose = "matrix-DotLeq-tuple" `namedRule` theRule where - theRule p = do - (x,y) <- match opDotLeq p - tx@TypeMatrix{} <- typeOf x -- TODO: check matrix index & tuple arity - ty@TypeMatrix{} <- typeOf y - when (isPrimitiveType tx) $ fail ("this is a primitive type:" <+> pretty tx) - when (isPrimitiveType ty) $ fail ("this is a primitive type:" <+> pretty ty) - xs <- downX1 x - ys <- downX1 y - return - ( "Horizontal rule for matrix .<=, decomposing" - , return $ decomposeLexDotLeq p xs ys - ) - - -======= ->>>>>>> master -rule_Comprehension_SingletonDomain :: Rule -rule_Comprehension_SingletonDomain = "matrix-comprehension-singleton-domain" `namedRule` theRule where - theRule (Comprehension body gensOrConds) = do - (gocBefore, (pat, singleVal), gocAfter) <- matchFirst gensOrConds $ \ goc -> case goc of - Generator (GenDomainHasRepr patName (singletonDomainInt -> Just a)) -> return (Single patName, a) - _ -> na "rule_Comprehension_SingletonDomain" - let upd val old = lambdaToFunction pat old val - return - ( "Removing matrix-comprehension of a singleton int domain" - , return $ - if null gocBefore && null gocAfter - then AbstractLiteral $ AbsLitMatrix (mkDomainIntB 1 1) [upd singleVal body] - else Comprehension (upd singleVal body) - $ gocBefore - ++ transformBi (upd singleVal) gocAfter - ) - theRule _ = na "rule_Comprehension_SingletonDomain" - - -rule_Comprehension_Singleton :: Rule -rule_Comprehension_Singleton = "matrix-comprehension-singleton" `namedRule` theRule where - theRule p = do - (_, _mkQuan, AbstractLiteral (AbsLitMatrix _ [singleVal])) <- match opReducer p - return - ( "Removing quantifier of a single item" - , return singleVal - ) - - -rule_Concatenate_Singleton :: Rule -rule_Concatenate_Singleton = "matrix-concatenate-singleton" `namedRule` theRule where - theRule p = do - AbstractLiteral (AbsLitMatrix _ [singleVal]) <- match opConcatenate p - return - ( "Removing concatenate of a single item" - , return singleVal - ) - - -rule_MatrixIndexing :: Rule -rule_MatrixIndexing = "matrix-indexing" `namedRule` theRule where - theRule p = do - (matrix, indexer) <- match opIndexing p - (_, DomainInt _ ranges, elems) <- match matrixLiteral matrix - indexInts <- rangesInts ranges - indexerInt <- intOut "rule_MatrixIndexing" indexer - if length indexInts == length elems - then - case lookup indexerInt (zip indexInts elems) of - Nothing -> na "rule_MatrixIndexing" - Just v -> - return - ( "Matrix indexing" - , return v - ) - else na "rule_MatrixIndexing" - - -rule_IndexingIdentical :: Rule -rule_IndexingIdentical = "matrix-indexing-identical" `namedRule` theRule where - theRule p = do - (matrix, indexer) <- match opIndexing p - (_, indexDomain, firstElem:restElems) <- match matrixLiteral matrix - indexerDomain <- domainOf indexer - if indexDomain == forgetRepr indexerDomain && all (firstElem==) restElems - then return - ( "rule_IndexingIdentical" - , return firstElem - ) - else na "rule_IndexingIdentical" diff --git a/src/Conjure/Rules/Vertical/Tuple.hs.orig b/src/Conjure/Rules/Vertical/Tuple.hs.orig deleted file mode 100644 index 9cb134c73d..0000000000 --- a/src/Conjure/Rules/Vertical/Tuple.hs.orig +++ /dev/null @@ -1,253 +0,0 @@ -{-# LANGUAGE QuasiQuotes #-} - -module Conjure.Rules.Vertical.Tuple where - -import Conjure.Rules.Import - - -rule_Tuple_Eq :: Rule -rule_Tuple_Eq = "tuple-eq" `namedRule` theRule where - theRule p = do - (x,y) <- match opEq p - TypeTuple{} <- typeOf x -- TODO: check if x and y have the same arity - TypeTuple{} <- typeOf y --- failExceptForTuplesOfSameArity x y - xs <- downX1 x - ys <- downX1 y - return - ( "Horizontal rule for tuple equality" - , return $ make opAnd $ fromList $ zipWith (make opEq) xs ys - ) - - -rule_Tuple_Neq :: Rule -rule_Tuple_Neq = "tuple-neq" `namedRule` theRule where - theRule p = do - (x,y) <- match opNeq p - TypeTuple{} <- typeOf x -- TODO: check if x and y have the same arity - TypeTuple{} <- typeOf y --- failExceptForTuplesOfSameArity x y - xs <- downX1 x - ys <- downX1 y - return - ( "Horizontal rule for tuple !=" - , return $ make opNot $ make opAnd $ fromList $ zipWith (make opEq) xs ys - ) - - -rule_Tuple_Lt :: Rule -rule_Tuple_Lt = "tuple-Lt" `namedRule` theRule where - theRule p = do - (x,y) <- match opLt p - TypeTuple{} <- typeOf x -- TODO: check if x and y have the same arity - TypeTuple{} <- typeOf y --- failExceptForTuplesOfSameArity x y - xs <- downX1 x - ys <- downX1 y - return - ( "Horizontal rule for tuple <" - , return $ decomposeLexLt p xs ys - ) - - -rule_Tuple_Leq :: Rule -rule_Tuple_Leq = "tuple-Leq" `namedRule` theRule where - theRule p = do - (x,y) <- match opLeq p - TypeTuple{} <- typeOf x -- TODO: check if x and y have the same arity - TypeTuple{} <- typeOf y --- failExceptForTuplesOfSameArity x y - xs <- downX1 x - ys <- downX1 y - return - ( "Horizontal rule for tuple <=" - , return $ decomposeLexLeq p xs ys - ) - - -<<<<<<< HEAD -rule_Tuple_DotLt :: Rule -rule_Tuple_DotLt = "tuple-DotLt" `namedRule` theRule where - theRule p = do - (x,y) <- match opDotLt p - TypeTuple{} <- typeOf x -- TODO: check if x and y have the same arity - TypeTuple{} <- typeOf y --- failExceptForTuplesOfSameArity x y - xs <- downX1 x - ys <- downX1 y - return - ( "Horizontal rule for tuple .<" - , return $ decomposeLexDotLt p xs ys - ) - - -rule_Tuple_DotLeq :: Rule -rule_Tuple_DotLeq = "tuple-DotLeq" `namedRule` theRule where --- theRule p@[essence| &x .<= image(&perm, &y) |] = do --- TypeTuple{} <- typeOf x -- TODO: check matrix index & tuple arity --- TypeTuple{} <- typeOf y --- TypePermutation{} <- typeOf perm --- xs <- downX1 x --- ys <- downX1 y --- return --- ( "Horizontal rule for matrix .<=, decomposing" --- , return $ decomposeLexDotLeqSym p perm xs ys --- ) --- - theRule p = do - (x,y) <- match opDotLeq p - TypeTuple{} <- typeOf x -- TODO: check if x and y have the same arity - TypeTuple{} <- typeOf y --- failExceptForTuplesOfSameArity x y - xs <- downX1 x - ys <- downX1 y - return - ( "Horizontal rule for tuple .<=" - , return $ decomposeLexDotLeq p xs ys - ) - - -||||||| merged common ancestors -rule_Tuple_DotLt :: Rule -rule_Tuple_DotLt = "tuple-DotLt" `namedRule` theRule where - theRule p = do - (x,y) <- match opDotLt p - TypeTuple{} <- typeOf x -- TODO: check if x and y have the same arity - TypeTuple{} <- typeOf y - xs <- downX1 x - ys <- downX1 y - return - ( "Horizontal rule for tuple .<" - , return $ decomposeLexDotLt p xs ys - ) - - -rule_Tuple_DotLeq :: Rule -rule_Tuple_DotLeq = "tuple-DotLeq" `namedRule` theRule where - theRule p = do - (x,y) <- match opDotLeq p - TypeTuple{} <- typeOf x -- TODO: check if x and y have the same arity - TypeTuple{} <- typeOf y - xs <- downX1 x - ys <- downX1 y - return - ( "Horizontal rule for tuple .<=" - , return $ decomposeLexDotLeq p xs ys - ) - - -======= ->>>>>>> master -rule_Tuple_TildeLt :: Rule -rule_Tuple_TildeLt = "tuple-TildeLt" `namedRule` theRule where - theRule p = do - (x,y) <- match opTildeLt p - TypeTuple{} <- typeOf x -- TODO: check if x and y have the same arity - TypeTuple{} <- typeOf y --- failExceptForTuplesOfSameArity x y - xs <- downX1 x - ys <- downX1 y - return - ( "Horizontal rule for tuple .<" - , return $ decomposeLexTildeLt p xs ys - ) - - -rule_Tuple_TildeLeq :: Rule -rule_Tuple_TildeLeq = "tuple-TildeLeq" `namedRule` theRule where - theRule p = do - (x,y) <- match opTildeLeq p - TypeTuple{} <- typeOf x -- TODO: check if x and y have the same arity - TypeTuple{} <- typeOf y --- failExceptForTuplesOfSameArity x y - xs <- downX1 x - ys <- downX1 y - return - ( "Horizontal rule for tuple .<=" - , return $ decomposeLexTildeLeq p xs ys - ) - -failExceptForTuplesOfSameArity :: MonadFail m => Expression -> Expression -> m () -failExceptForTuplesOfSameArity (AbstractLiteral (AbsLitTuple a)) (AbstractLiteral (AbsLitTuple b)) = - if length a == length b - then return () - else fail "failExceptForTuplesOfSameArity: These tuples are not of the same arity." -failExceptForTuplesOfSameArity (Domain (DomainTuple a)) (Domain (DomainTuple b)) = - if length a == length b - then return () - else fail "failExceptForTuplesOfSameArity: These tuples are not of the same arity." -failExceptForTuplesOfSameArity _ _ = fail "failExceptForTuplesOfSameArity: These things are not tuples." - - -decomposeLexLt :: Expression -> [Expression] -> [Expression] -> Expression -decomposeLexLt p = unroll - where - unroll [a] [b] = [essence| &a < &b |] - unroll (a:as) (b:bs) = let rest = unroll as bs - in [essence| (&a < &b) \/ ((&a = &b) /\ &rest) |] - unroll _ _ = bug ("arity mismatch in:" <+> pretty p) - -decomposeLexLeq :: Expression -> [Expression] -> [Expression] -> Expression -decomposeLexLeq p = unroll - where - unroll [a] [b] = [essence| &a <= &b |] - unroll (a:as) (b:bs) = let rest = unroll as bs - in [essence| (&a < &b) \/ ((&a = &b) /\ &rest) |] - unroll _ _ = bug ("arity mismatch in:" <+> pretty p) - - -decomposeLexDotLt :: Expression -> [Expression] -> [Expression] -> Expression -decomposeLexDotLt p = unroll - where - unroll [a] [b] = [essence| &a .< &b |] - unroll (a:as) (b:bs) = let rest = unroll as bs - in [essence| (&a .< &b) \/ ((&a = &b) /\ &rest) |] - unroll _ _ = bug ("arity mismatch in:" <+> pretty p) - -decomposeLexDotLeq :: Expression -> [Expression] -> [Expression] -> Expression -decomposeLexDotLeq p = unroll - where - unroll [a] [b] = [essence| &a .<= &b |] - unroll (a:as) (b:bs) = let rest = unroll as bs - in [essence| (&a .< &b) \/ ((&a = &b) /\ &rest) |] - unroll _ _ = bug ("arity mismatch in:" <+> pretty p) - ---decomposeLexDotLeqSym :: Expression -> Expression --- -> [Expression] -> [Expression] -> Expression ---decomposeLexDotLeqSym p perm = unroll --- where --- unroll [a] [b] = [essence| &a .<= image(&perm, &b) |] --- unroll (a:as) (b:bs) = let rest = unroll as bs --- in [essence| (&a .< image(&perm,&b)) \/ ((&a = image(&perm,&b)) /\ &rest) |] --- unroll _ _ = bug ("arity mismatch in:" <+> pretty p) --- - - -decomposeLexTildeLt :: Expression -> [Expression] -> [Expression] -> Expression -decomposeLexTildeLt p = unroll - where - unroll [a] [b] = [essence| &a ~< &b |] - unroll (a:as) (b:bs) = let rest = unroll as bs - in [essence| (&a ~< &b) \/ ((&a = &b) /\ &rest) |] - unroll _ _ = bug ("arity mismatch in:" <+> pretty p) - -decomposeLexTildeLeq :: Expression -> [Expression] -> [Expression] -> Expression -decomposeLexTildeLeq p = unroll - where - unroll [a] [b] = [essence| &a ~<= &b |] - unroll (a:as) (b:bs) = let rest = unroll as bs - in [essence| (&a ~< &b) \/ ((&a = &b) /\ &rest) |] - unroll _ _ = bug ("arity mismatch in:" <+> pretty p) - - -rule_Tuple_Index :: Rule -rule_Tuple_Index = "tuple-index" `namedRule` theRule where - theRule p = do - (t,i) <- match opIndexing p - TypeTuple{} <- typeOf t - iInt <- match constantInt i - ts <- downX1 t - return - ( "Tuple indexing on:" <+> pretty p - , return $ atNote "Tuple indexing" ts (fromInteger (iInt-1)) - ) diff --git a/src/Conjure/UI/Model.hs.orig b/src/Conjure/UI/Model.hs.orig deleted file mode 100644 index aec742ec77..0000000000 --- a/src/Conjure/UI/Model.hs.orig +++ /dev/null @@ -1,2303 +0,0 @@ -{-# LANGUAGE Rank2Types #-} -{-# LANGUAGE TupleSections #-} -{-# LANGUAGE QuasiQuotes #-} -{-# LANGUAGE ViewPatterns #-} -{-# LANGUAGE RecordWildCards #-} - -module Conjure.UI.Model - ( outputModels - , Strategy(..), Config(..), parseStrategy - , nbUses - ) where - -import Conjure.Prelude -import Conjure.Bug -import Conjure.UserError -import Conjure.Language.Definition -import Conjure.Language.Expression.Internal.Generated () -import Conjure.Language.Domain -import Conjure.Language.Type -import Conjure.Language.Pretty -import Conjure.Language.CategoryOf -import Conjure.Language.TypeOf -import Conjure.Compute.DomainOf -import Conjure.Language.Lenses -import Conjure.Language.TH ( essence ) -import Conjure.Language.Expression.Op -import Conjure.Language.ModelStats ( modelInfo ) -import Conjure.Language.Instantiate ( instantiateExpression, trySimplify ) -import Conjure.Process.Sanity ( sanityChecks ) -import Conjure.Process.Enums ( removeEnumsFromModel ) -import Conjure.Process.Unnameds ( removeUnnamedsFromModel ) -import Conjure.Process.FiniteGivens ( finiteGivens ) -import Conjure.Process.LettingsForComplexInDoms ( lettingsForComplexInDoms - , inlineLettingDomainsForDecls - , removeDomainLettings - ) -import Conjure.Process.AttributeAsConstraints ( attributeAsConstraints, mkAttributeToConstraint ) -import Conjure.Process.InferAttributes ( inferAttributes ) -import Conjure.Process.DealWithCuts ( dealWithCuts ) -import Conjure.Process.Enumerate ( EnumerateDomain ) -import Conjure.Language.NameResolution ( resolveNames, resolveNamesX ) -import Conjure.UI.TypeCheck ( typeCheckModel, typeCheckModel_StandAlone ) -import Conjure.UI.LogFollow ( logFollow, storeChoice ) -import Conjure.UI ( OutputFormat(..) ) -import Conjure.UI.IO ( writeModel ) -import Conjure.UI.NormaliseQuantified ( distinctQuantifiedVars ) - -import Conjure.Representations - ( downX, downX1, downD, reprOptions, getStructurals - , reprsStandardOrderNoLevels, reprsStandardOrder, reprsSparseOrder - ) - -import Conjure.Rules.Definition - -import qualified Conjure.Rules.Vertical.Tuple as Vertical.Tuple -import qualified Conjure.Rules.Vertical.Record as Vertical.Record -import qualified Conjure.Rules.Vertical.Variant as Vertical.Variant -import qualified Conjure.Rules.Vertical.Matrix as Vertical.Matrix - -import qualified Conjure.Rules.Horizontal.Set as Horizontal.Set -import qualified Conjure.Rules.Vertical.Set.Explicit as Vertical.Set.Explicit -import qualified Conjure.Rules.Vertical.Set.ExplicitVarSizeWithDummy as Vertical.Set.ExplicitVarSizeWithDummy -import qualified Conjure.Rules.Vertical.Set.ExplicitVarSizeWithFlags as Vertical.Set.ExplicitVarSizeWithFlags -import qualified Conjure.Rules.Vertical.Set.ExplicitVarSizeWithMarker as Vertical.Set.ExplicitVarSizeWithMarker -import qualified Conjure.Rules.Vertical.Set.Occurrence as Vertical.Set.Occurrence - -import qualified Conjure.Rules.Horizontal.MSet as Horizontal.MSet -import qualified Conjure.Rules.Vertical.MSet.ExplicitWithFlags as Vertical.MSet.ExplicitWithFlags -import qualified Conjure.Rules.Vertical.MSet.ExplicitWithRepetition as Vertical.MSet.ExplicitWithRepetition - -import qualified Conjure.Rules.Horizontal.Function as Horizontal.Function -import qualified Conjure.Rules.Vertical.Function.Function1D as Vertical.Function.Function1D -import qualified Conjure.Rules.Vertical.Function.Function1DPartial as Vertical.Function.Function1DPartial -import qualified Conjure.Rules.Vertical.Function.FunctionND as Vertical.Function.FunctionND -import qualified Conjure.Rules.Vertical.Function.FunctionNDPartial as Vertical.Function.FunctionNDPartial -import qualified Conjure.Rules.Vertical.Function.FunctionAsRelation as Vertical.Function.FunctionAsRelation - -import qualified Conjure.Rules.Horizontal.Sequence as Horizontal.Sequence -import qualified Conjure.Rules.Vertical.Sequence.ExplicitBounded as Vertical.Sequence.ExplicitBounded - -import qualified Conjure.Rules.Horizontal.Relation as Horizontal.Relation -import qualified Conjure.Rules.Vertical.Relation.RelationAsMatrix as Vertical.Relation.RelationAsMatrix -import qualified Conjure.Rules.Vertical.Relation.RelationAsSet as Vertical.Relation.RelationAsSet - -import qualified Conjure.Rules.Horizontal.Partition as Horizontal.Partition -import qualified Conjure.Rules.Vertical.Partition.PartitionAsSet as Vertical.Partition.PartitionAsSet -import qualified Conjure.Rules.Vertical.Partition.Occurrence as Vertical.Partition.Occurrence - -import qualified Conjure.Rules.Vertical.Permutation.AsFunction as Vertical.Permutation.AsFunction -import qualified Conjure.Rules.Horizontal.Permutation as Horizontal.Permutation - -import qualified Conjure.Rules.BubbleUp as BubbleUp -import qualified Conjure.Rules.DontCare as DontCare -import qualified Conjure.Rules.TildeOrdering as TildeOrdering - --- base -import System.IO ( hFlush, stdout ) -import Data.IORef ( IORef, newIORef, readIORef, writeIORef ) -import System.IO.Unsafe ( unsafePerformIO ) - - --- uniplate -import Data.Generics.Uniplate.Zipper ( hole, replaceHole ) -import Data.Generics.Uniplate.Zipper as Zipper ( right, up ) - --- pipes -import Pipes ( Producer, await, yield, (>->), cat ) -import qualified Pipes.Prelude as Pipes ( foldM ) - - -outputModels - :: (MonadIO m, MonadFail m, MonadLog m, NameGen m, EnumerateDomain m, MonadUserError m) - => Config - -> Model - -> m () -outputModels config model = do - - liftIO $ writeIORef recordedResponses (responses config) - - -- Savile Row does not support ' characters in identifiers - -- We could implement a workaround where we insert a marker (like __PRIME__) for each ' character - -- and recover these after a solution is found. - -- But this will be too hairy, instead we will reject such identifiers for now. - -- If somebody really needs to use a ' character as part of an identifier, we can revisit this decision. - let - primeyIdentifiers = catMaybes - [ if '\'' `elem` textToString identifier - then Just identifier - else Nothing - | Declaration decl <- mStatements model - , Name identifier <- universeBi decl - ] - unless (null primeyIdentifiers) $ userErr1 $ vcat - ["Identifiers cannot contain a quotation mark character in them:" <+> prettyList id "," primeyIdentifiers] - - let dir = outputDirectory config - liftIO $ createDirectoryIfMissing True dir - - let - limitModelsIfNeeded = maybe Pipes.cat limitModelsNeeded (limitModels config) - limitModelsNeeded 0 = return () - limitModelsNeeded n = do - x <- Pipes.await - Pipes.yield x - case x of - Left {} -> limitModelsNeeded n -- yielded a log, still n models to produce - Right{} -> limitModelsNeeded (n-1) -- yielded a model, produce n-1 more models - - each i logOrModel = - case logOrModel of - Left (l,msg) -> do - log l msg - return i - Right eprime -> do - let gen = - if smartFilenames config - then [ choice - | (_question, choice, numOptions) <- - eprime |> mInfo |> miTrailCompact - , numOptions > 1 - ] |> map (('_':) . show) - |> concat - else padLeft 6 '0' (show i) - let filename = dir "model" ++ gen ++ ".eprime" - writeModel (lineWidth config) Plain (Just filename) eprime - return (i+1) - - Pipes.foldM each - (return (numberingStart config)) - (const $ return ()) - (toCompletion config model - >-> limitModelsIfNeeded) - - -toCompletion - :: forall m . (MonadIO m, MonadFail m, NameGen m, EnumerateDomain m) - => Config - -> Model - -> Producer LogOrModel m () -toCompletion config m = do - m2 <- prologue m - namegenst <- exportNameGenState - let m2Info = mInfo m2 - let m3 = m2 { mInfo = m2Info { miStrategyQ = strategyQ config - , miStrategyA = strategyA config - , miNameGenState = namegenst - } } - logDebug $ modelInfo m3 - loopy (StartOver m3) - where - driver :: Driver - driver = strategyToDriver config - - loopy :: ModelWIP -> Producer LogOrModel m () - loopy modelWIP = do - logDebug $ "[loopy]" <+> pretty ((modelWIPOut modelWIP) {mInfo = def}) - qs <- remainingWIP config modelWIP - if null qs - then do - let model = modelWIPOut modelWIP - model' <- epilogue model - yield (Right model') - else do - nextModels <- driver qs - mapM_ loopy nextModels - - --- | If a rule is applied at a position P, the MonadZipper will be retained focused at that location --- and new rules will be tried using P as the top of the zipper-tree. --- The whole model (containing P too) will be tried later for completeness. -remainingWIP - :: (MonadFail m, MonadLog m, NameGen m, EnumerateDomain m) - => Config - -> ModelWIP - -> m [Question] -remainingWIP config (StartOver model) - | Just modelZipper <- mkModelZipper model = do - qs <- remaining config modelZipper (mInfo model) - return qs - | otherwise = return [] -remainingWIP config wip@(TryThisFirst modelZipper info) = do - qs <- remaining config modelZipper info - case (null qs, Zipper.right modelZipper, Zipper.up modelZipper) of - (False, _, _) -> return qs -- not null, return - (_, Just r, _) -> remainingWIP config (TryThisFirst r info) -- there is a sibling to the right - (_, _, Just u) -> remainingWIP config (TryThisFirst u info) -- there is a parent - _ -> remainingWIP config (StartOver (modelWIPOut wip)) -- we are done here, - -- start-over the whole model in case - -- something on the left needs attention. - - -remaining - :: (MonadFail m, MonadLog m, NameGen m, EnumerateDomain m) - => Config - -> ModelZipper - -> ModelInfo - -> m [Question] -remaining config modelZipper minfo = do - -- note: the call to getQuestions can update the NameGen state - importNameGenState (minfo |> miNameGenState) - questions <- getQuestions config modelZipper - namegenst0 <- exportNameGenState - forM questions $ \ (focus, answers0) -> do - answers1 <- forM answers0 $ \ (ruleName, RuleResult{..}) -> do - importNameGenState namegenst0 - ruleResultExpr <- ruleResult - -- ruleResultExpr <- fmap fixRelationProj ruleResult -- TODO: do we need the fixRelationProj? - let fullModelBeforeHook = replaceHole ruleResultExpr focus - let mtyBefore = typeOf (hole focus) - let mtyAfter = typeOf ruleResultExpr - case (mtyBefore, mtyAfter) of - (Right tyBefore, Right tyAfter) -> - unless (typesUnify [tyBefore, tyAfter]) $ - bug $ vcat - [ "Rule application changes type:" <+> pretty ruleName - , "Before:" <+> pretty (hole focus) - , "After :" <+> pretty ruleResultExpr - , "Type before:" <+> pretty (show tyBefore) - , "Type after :" <+> pretty (show tyAfter) - ] - (Left msg, _) -> bug $ vcat - [ "Type error before rule application:" <+> pretty ruleName - , "Before:" <+> pretty (hole focus) - , "After :" <+> pretty ruleResultExpr - , "Error :" <+> pretty msg - ] - (_, Left msg) -> bug $ vcat - [ "Type error after rule application:" <+> pretty ruleName - , "Before:" <+> pretty (hole focus) - , "After :" <+> pretty ruleResultExpr - , "Error :" <+> pretty msg - ] - - fullModelAfterHook <- case ruleResultHook of - Nothing -> do - namegenst <- exportNameGenState - return (TryThisFirst fullModelBeforeHook minfo { miNameGenState = namegenst }) - Just hook -> do - namegenst1 <- exportNameGenState - let m1 = fromModelZipper fullModelBeforeHook minfo { miNameGenState = namegenst1 } - m2 <- hook m1 - namegenst2 <- exportNameGenState - let m3 = m2 { mInfo = (mInfo m2) { miNameGenState = namegenst2 } } - return (StartOver m3) - - return - ( Answer - { aText = ruleName <> ":" <+> ruleResultDescr - , aRuleName = ruleName - , aBefore = hole focus - , aAnswer = ruleResultExpr - , aFullModel = fullModelAfterHook - } - , ruleResultType - ) - let qTypes = map snd answers1 - qType' <- if all (head qTypes ==) (tail qTypes) - then return (head qTypes) - else bug "Rules of different rule kinds applicable, this is a bug." - return Question - { qType = qType' - , qHole = hole focus - , qAscendants = tail (ascendants focus) - , qAnswers = map fst answers1 - } - - --- | Computes all applicable questions. --- strategyQ == PickFirst is special-cased for performance. -getQuestions - :: (MonadLog m, MonadFail m, NameGen m, EnumerateDomain m) - => Config - -> ModelZipper - -> m [(ModelZipper, [(Doc, RuleResult m)])] -getQuestions config modelZipper | strategyQ config == PickFirst = maybeToList <$> - let - loopLevels :: Monad m => [m (Maybe a)] -> m (Maybe a) - loopLevels [] = return Nothing - loopLevels (a:as) = do bs <- a - case bs of - Nothing -> loopLevels as - Just {} -> return bs - - processLevel :: (MonadFail m, MonadLog m, NameGen m, EnumerateDomain m) - => [Rule] - -> m (Maybe (ModelZipper, [(Doc, RuleResult m)])) - processLevel rulesAtLevel = - let - go [] = return Nothing - go (x:xs) = do - ys <- applicableRules config rulesAtLevel x - if null ys - then go xs - else return (Just (x, ys)) - in - go (allContextsExceptReferences modelZipper) - in - loopLevels (map processLevel (allRules config)) -getQuestions config modelZipper = - let - loopLevels :: Monad m => [m [a]] -> m [a] - loopLevels [] = return [] - loopLevels (a:as) = do bs <- a - if null bs - then loopLevels as - else return bs - - processLevel :: (MonadFail m, MonadLog m, NameGen m, EnumerateDomain m) - => [Rule] - -> m [(ModelZipper, [(Doc, RuleResult m)])] - processLevel rulesAtLevel = - fmap catMaybes $ forM (allContextsExceptReferences modelZipper) $ \ x -> do - ys <- applicableRules config rulesAtLevel x - return $ if null ys - then Nothing - else Just (x, ys) - in - loopLevels (map processLevel (allRules config)) - - -strategyToDriver :: Config -> Driver -strategyToDriver config questions = do - let optionsQ = - [ (doc, q) - | (n, q) <- zip allNats questions - , let doc = - vcat $ ("Question" <+> pretty n <> ":" <+> pretty (qHole q)) - : [ nest 4 ("Context #" <> pretty i <> ":" <+> pretty c) - | (i,c) <- zip allNats (qAscendants q) - ] - ] - pickedQs <- executeStrategy optionsQ (strategyQ config) - fmap concat $ forM pickedQs $ \ (pickedQNumber, pickedQDescr, pickedQ) -> do - let optionsA = - [ (doc, a) - | (n, a) <- zip allNats (qAnswers pickedQ) - , let doc = - nest 4 $ "Answer" <+> pretty n <> ":" <+> vcat [ pretty (aText a) - , pretty (aAnswer a) ] - ] - let strategyA' = case qType pickedQ of - ChooseRepr -> representations - ChooseRepr_Find -> representationsFinds - ChooseRepr_Given -> representationsGivens - ChooseRepr_Auxiliary -> representationsAuxiliaries - ChooseRepr_Quantified -> representationsQuantifieds - ChooseRepr_Cut -> representationsCuts - ExpressionRefinement -> strategyA - pickedAs <- executeAnswerStrategy config pickedQ optionsA (strategyA' config) - return - [ theModel - | (pickedANumber, pickedADescr, pickedA) <- pickedAs - , let upd = addToTrail - config - (strategyQ config) pickedQNumber pickedQDescr - (strategyA' config) pickedANumber (length optionsA) pickedADescr - (aText pickedA) - (aBefore pickedA) - (aAnswer pickedA) - , let theModel = updateModelWIPInfo upd (aFullModel pickedA) - ] - - -recordedResponses :: IORef (Maybe [Int]) -{-# NOINLINE recordedResponses #-} -recordedResponses = unsafePerformIO (newIORef Nothing) - - -executeStrategy :: (MonadIO m, MonadLog m) => [(Doc, a)] -> Strategy -> m [(Int, Doc, a)] -executeStrategy [] _ = bug "executeStrategy: nothing to choose from" -executeStrategy [(doc, option)] (viewAuto -> (_, True)) = do - logDebug ("Picking the only option:" <+> doc) - return [(1, doc, option)] -executeStrategy options@((doc, option):_) (viewAuto -> (strategy, _)) = - case strategy of - Auto _ -> bug "executeStrategy: Auto" - PickFirst -> do - logDebug ("Picking the first option:" <+> doc) - return [(1, doc, option)] - Sparse -> do - logDebug ("Picking the first option (in sparse order):" <+> doc) - return [(1, doc, option)] - PickAll -> return [ (i,d,o) | (i,(d,o)) <- zip [1..] options ] - Interactive -> liftIO $ do - print (vcat (map fst options)) - let - nextRecordedResponse :: IO (Maybe Int) - nextRecordedResponse = do - mres <- readIORef recordedResponses - case mres of - Just (next:rest) -> do - writeIORef recordedResponses (Just rest) - return (Just next) - _ -> return Nothing - - pickIndex :: IO Int - pickIndex = do - mrecorded <- nextRecordedResponse - case mrecorded of - Just recorded -> do - putStrLn ("Response: " ++ show recorded) - return recorded - Nothing -> do - putStr "Pick option: " - hFlush stdout - line <- getLine - case (line, readMay line) of - ("", _) -> return 1 - (_, Just lineInt) | lineInt >= 1 && lineInt <= length options -> return lineInt - (_, Nothing) -> do - putStrLn "Enter an integer value." - pickIndex - (_, Just _) -> do - print $ pretty $ "Enter a value between 1 and" <+> pretty (length options) - pickIndex - - pickedIndex <- pickIndex - let (pickedDescr, picked) = at options (pickedIndex - 1) - return [(pickedIndex, pickedDescr, picked)] - AtRandom -> do - let nbOptions = length options - pickedIndex <- liftIO $ randomRIO (1, nbOptions) - let (pickedDescr, picked) = at options (pickedIndex - 1) - logDebug ("Randomly picking option #" <> pretty pickedIndex <+> "out of" <+> pretty nbOptions) - return [(pickedIndex, pickedDescr, picked)] - Compact -> bug "executeStrategy: Compact" - FollowLog -> bug "executeStrategy: FollowLog" - - -executeAnswerStrategy :: (MonadIO m, MonadLog m) - => Config -> Question -> [(Doc, Answer)] -> Strategy -> m [(Int, Doc, Answer)] -executeAnswerStrategy _ _ [] _ = bug "executeStrategy: nothing to choose from" -executeAnswerStrategy config q [(doc, option)] (viewAuto -> (_, True)) = do - logDebug ("Picking the only option:" <+> doc) - c <- storeChoice config q option - return [(1, doc, c)] -executeAnswerStrategy config question options st@(viewAuto -> (strategy, _)) = - case strategy of - Compact -> do - let (n,(doc,c)) = minimumBy (compactCompareAnswer `on` (snd . snd)) (zip [1..] options) - c' <- storeChoice config question c - return [(n, doc, c')] - FollowLog -> logFollow config question options - AtRandom -> do - [(n, doc, ans0)] <- executeStrategy options st - ans1 <- storeChoice config question ans0 - return [(n, doc, ans1)] - _ -> do - cs <- executeStrategy options st - forM cs $ \ (n, d, c) -> do - c' <- storeChoice config question c - return (n, d, c') - - -compactCompareAnswer :: Answer -> Answer -> Ordering -compactCompareAnswer = comparing (expressionDepth . aAnswer) - where - expressionDepth :: Data a => a -> Int - expressionDepth x = 1 + maximum (0 : map expressionDepth (children x)) - - -addToTrail - :: Config - -> Strategy -> Int -> Doc - -> Strategy -> Int -> Int -> Doc - -> Doc -> Expression -> Expression - -> ModelInfo -> ModelInfo -addToTrail Config{..} - questionStrategy questionNumber questionDescr - answerStrategy answerNumber answerNumbers answerDescr - ruleDescr oldExpr newExpr - oldInfo = newInfo - where - newInfo = oldInfo { miTrailCompact = (questionNumber, answerNumber, answerNumbers) - : miTrailCompact oldInfo - , miTrailVerbose = if verboseTrail - then theA : theQ : miTrailVerbose oldInfo - else [] - , miTrailRewrites = if rewritesTrail - then theRewrite : miTrailRewrites oldInfo - else [] - } - theQ = Decision - { dDescription = map (stringToText . renderWide) - $ ("Question #" <> pretty questionNumber) - : (" (Using strategy:" <+> pretty (show questionStrategy) <> ")") - : map pretty (lines (renderWide questionDescr)) - , dDecision = questionNumber - , dNumOptions = Nothing - } - theA = Decision - { dDescription = map (stringToText . renderWide) - $ ("Answer #" <> pretty answerNumber <+> "out of" <+> pretty (show answerNumbers)) - : (" (Using strategy:" <+> pretty (show answerStrategy) <> ")") - : map pretty (lines (renderWide answerDescr)) - , dDecision = answerNumber - , dNumOptions = Just answerNumbers - } - theRewrite = TrailRewrites - { trRule = stringToText $ renderWide ruleDescr - , trBefore = map stringToText $ lines $ renderWide $ pretty oldExpr - , trAfter = map stringToText $ lines $ renderWide $ pretty newExpr - } - - --- | Add a true-constraint, for every decision variable (whether it is used or not in the model) and --- for every parameter (that is not used in the model). --- A true-constraint has no effect, other than forcing Conjure to produce a representation. --- It can be used to make sure that a declaration doesn't get lost (if it isn't used anywhere in the model) --- It can also be used to produce "extra" representations (if it is used in the model) -addTrueConstraints :: Model -> Model -addTrueConstraints m = - let - mkTrueConstraint forg nm dom = Op $ MkOpTrue $ OpTrue (Reference nm (Just (DeclNoRepr forg nm dom NoRegion))) - trueConstraints = [ mkTrueConstraint forg nm d - | (Declaration (FindOrGiven forg nm d), after) <- withAfter (mStatements m) - , forg == Find || (forg == Given && nbUses nm after == 0) - ] - in - m { mStatements = mStatements m ++ [SuchThat trueConstraints] } - - -reverseTrails :: Model -> Model -reverseTrails m = - let - oldInfo = mInfo m - newInfo = oldInfo { miTrailCompact = reverse (miTrailCompact oldInfo) - , miTrailVerbose = reverse (miTrailVerbose oldInfo) - , miTrailRewrites = reverse (miTrailRewrites oldInfo) - } - in - m { mInfo = newInfo } - - -oneSuchThat :: Model -> Model -oneSuchThat m = m { mStatements = onStatements (mStatements m) } - - where - - onStatements :: [Statement] -> [Statement] - onStatements xs = - let - (suchThats0, objectives, others) = xs |> map collect |> mconcat - suchThats = suchThats0 - |> map breakConjunctions -- break top level /\'s - |> mconcat - |> filter (/= Constant (ConstantBool True)) -- remove top level true's - |> nub -- uniq - in - others ++ objectives ++ [SuchThat (combine suchThats)] - - collect :: Statement -> ( [Expression] -- SuchThats - , [Statement] -- Objectives - , [Statement] -- other statements - ) - collect (SuchThat s) = (s, [], []) - collect s@Objective{} = ([], [s], []) - collect s = ([], [], [s]) - - combine :: [Expression] -> [Expression] - combine xs = if null xs - then [Constant (ConstantBool True)] - else xs - - breakConjunctions :: Expression -> [Expression] - breakConjunctions p@(Op (MkOpAnd (OpAnd x))) = - case listOut x of - Nothing -> [p] -- doesn't contain a list - Just xs -> concatMap breakConjunctions xs - breakConjunctions x = [x] - - -emptyMatrixLiterals :: Model -> Model -emptyMatrixLiterals model = - let - f (TypeList ty) = TypeMatrix (TypeInt NoTag) ty - f x = x - in - model { mStatements = mStatements model |> transformBi f } - - --- | Add a default search order (branching on [...]) --- to include all the primary variables and none of the aux variables that will potentailly be generated by Conjure. --- Do not change the model if it already contains a SearchOrder in it. -addSearchOrder :: Model -> Model -addSearchOrder model - | let hasSearchOrder = not $ null [ () | SearchOrder{} <- mStatements model ] - , hasSearchOrder = model - | otherwise = - let finds = [ nm | Declaration (FindOrGiven Find nm _domain) <- mStatements model ] - in model { mStatements = mStatements model ++ [SearchOrder (map BranchingOn finds)] } - - -inlineDecVarLettings :: Model -> Model -inlineDecVarLettings model = - let - inline p@(Reference nm _) = do - x <- gets (lookup nm) - return (fromMaybe p x) - inline p = return p - - statements = catMaybes - $ flip evalState [] - $ forM (mStatements model) - $ \ st -> - case st of - Declaration (Letting nm x) - | categoryOf x == CatDecision - -> modify ((nm,x) :) >> return Nothing - -- The following doesn't work when the identifier is used in a domain - -- Declaration (Letting nm x@Reference{}) - -- -> modify ((nm,x) :) >> return Nothing - _ -> Just <$> transformBiM inline st - in - model { mStatements = statements } - - -dropTagForSR :: MonadFail m => Model -> m Model -dropTagForSR m = do - let - replacePredSucc [essence| pred(&x) |] = do - ty <- typeOf x - case ty of - TypeBool{} -> return [essence| false |] - -- since True becomes False - -- False becomes out-of-bounds, hence False - TypeInt{} -> do - let xNoTag = reTag NoTag x - return [essence| &xNoTag - 1 |] - _ -> bug "predSucc" - replacePredSucc [essence| succ(&x) |] = do - ty <- typeOf x - case ty of - TypeBool{} -> return [essence| !&x |] - -- since False becomes True - -- True becomes out-of-bounds, hence False - -- "succ" is exactly "negate" on bools - TypeInt{} -> do - let xNoTag = reTag NoTag x - return [essence| &xNoTag + 1 |] - _ -> bug "predSucc" - replacePredSucc [essence| &a .< &b |] = return [essence| &a < &b |] - replacePredSucc [essence| &a .<= &b |] = return [essence| &a <= &b |] - replacePredSucc x = return x - - st <- transformBiM replacePredSucc (mStatements m) - return m { mStatements = st } - where - - -updateDeclarations :: (MonadUserError m, MonadFail m, NameGen m, EnumerateDomain m) => Model -> m Model -updateDeclarations model = do - let - representations = model |> mInfo |> miRepresentations - - onEachStatement (inStatement, afters) = - case inStatement of - Declaration (FindOrGiven forg nm _) -> do - let - -- the refined domains for the high level declaration - domains = [ d | (n, d) <- representations, n == nm ] - nub <$> concatMapM (onEachDomain forg nm) domains - Declaration (GivenDomainDefnEnum name) -> return - [ Declaration (FindOrGiven Given (name `mappend` "_EnumSize") (DomainInt NoTag [])) ] - Declaration (Letting nm x) -> do - let usedAfter = nbUses nm afters > 0 - let isRefined = (0 :: Int) == sum - [ case y of - Constant (ConstantAbstract AbsLitMatrix{}) -> 0 - Constant ConstantAbstract{} -> 1 - AbstractLiteral AbsLitMatrix{} -> 0 - AbstractLiteral{} -> 1 - _ -> 0 - | y <- universe x ] - return [inStatement | and [usedAfter, isRefined]] - Declaration LettingDomainDefnEnum{} -> return [] - Declaration LettingDomainDefnUnnamed{} -> return [] - SearchOrder orders -> do - orders' <- forM orders $ \case - BranchingOn nm -> do - let domains = [ d | (n, d) <- representations, n == nm ] - -- last one is the representation of what's in true(?) - -- put that first! - let reorder xs = - case reverse xs of - [] -> [] - (y:ys) -> y : reverse ys - outNames <- concatMapM (onEachDomainSearch nm) (reorder domains) - return $ map BranchingOn $ nub outNames - Cut{} -> bug "updateDeclarations, Cut shouldn't be here" - return [ SearchOrder (concat orders') ] - _ -> return [inStatement] - - onEachDomain forg nm domain = - runExceptT (downD (nm, domain)) >>= \case - Left err -> bug err - Right outs -> forM outs $ \ (n, d) -> do - d' <- transformBiM trySimplify $ forgetRepr d - return $ Declaration (FindOrGiven forg n d') - - onEachDomainSearch nm domain = - runExceptT (downD (nm, domain)) >>= \case - Left err -> bug err - Right outs -> return [ n - | (n, _) <- outs - ] - - statements <- concatMapM onEachStatement (withAfter (mStatements model)) - return model { mStatements = statements } - - --- | checking whether any `Reference`s with `DeclHasRepr`s are left in the model -checkIfAllRefined :: MonadFail m => Model -> m Model -checkIfAllRefined m | Just modelZipper <- mkModelZipper m = do -- we exclude the mInfo here - let returnMsg x = return - $ "" - : ("Not refined:" <+> pretty (hole x)) - : [ nest 4 ("Context #" <> pretty i <> ":" <+> pretty c) - | (i, c) <- zip allNats (tail (ascendants x)) - ] - - fails <- fmap concat $ forM (allContextsExceptReferences modelZipper) $ \ x -> - case hole x of - Reference _ (Just (DeclHasRepr _ _ dom)) - | not (isPrimitiveDomain dom) -> - return $ "" - : ("Not refined:" <+> pretty (hole x)) - : ("Domain :" <+> pretty dom) - : [ nest 4 ("Context #" <> pretty i <> ":" <+> pretty c) - | (i, c) <- zip allNats (tail (ascendants x)) - ] - Constant (ConstantAbstract AbsLitMatrix{}) -> return [] - Constant ConstantAbstract{} -> returnMsg x - AbstractLiteral AbsLitMatrix{} -> return [] - AbstractLiteral{} -> returnMsg x - WithLocals{} -> returnMsg x - Comprehension _ stmts -> do - decisionConditions <- - fmap catMaybes $ forM stmts $ \ stmt -> case stmt of - Condition c -> - if categoryOf c >= CatDecision - then return (Just c) - else return Nothing - _ -> return Nothing - comprehensionLettings <- - fmap catMaybes $ forM stmts $ \ stmt -> case stmt of - ComprehensionLetting{} -> return (Just stmt) - _ -> return Nothing - unsupportedGenerator <- - fmap catMaybes $ forM stmts $ \ stmt -> case stmt of - Generator GenInExpr{} -> return (Just stmt) - _ -> return Nothing - let msgs = [ "decision expressions as conditions" - | not (null decisionConditions) ] - ++ [ "local lettings" - | not (null comprehensionLettings) ] - ++ [ "unsupported generators" - | not (null unsupportedGenerator) ] - let msg = "Comprehension contains" <+> prettyListDoc id "," msgs <> "." - case msgs of - [] -> return [] - _ -> return $ [ msg ] - ++ [ nest 4 (pretty (hole x)) ] - ++ [ nest 4 ("Context #" <> pretty i <> ":" <+> pretty c) - | (i, c) <- zip allNats (tail (ascendants x)) - ] - _ -> return [] - unless (null fails) (bug (vcat fails)) - return m -checkIfAllRefined m = return m - - --- | checking whether any undefined values creeped into the final model -checkIfHasUndefined :: MonadFail m => Model -> m Model -checkIfHasUndefined m | Just modelZipper <- mkModelZipper m = do - let returnMsg x = return - $ "" - : ("Undefined value in the final model:" <+> pretty (hole x)) - : [ nest 4 ("Context #" <> pretty i <> ":" <+> pretty c) - | (i, c) <- zip allNats (tail (ascendants x)) - ] - - fails <- fmap concat $ forM (allContextsExceptReferences modelZipper) $ \ x -> - case hole x of - Constant ConstantUndefined{} -> returnMsg x - _ -> return [] - unless (null fails) (bug (vcat fails)) - return m -checkIfHasUndefined m = return m - - -topLevelBubbles :: (MonadFail m, MonadUserError m, NameGen m) => Model -> m Model -topLevelBubbles m = do - let - onStmt (SuchThat xs) = onExprs xs - onStmt (Where xs) = concatMapM onWheres xs - onStmt (Objective obj (WithLocals h locals)) = - case locals of - AuxiliaryVars locs -> ( locs ++ [Objective obj h] ) |> onStmts - DefinednessConstraints locs -> ( [SuchThat locs] ++ [Objective obj h] ) |> onStmts - onStmt (Declaration decl) = - let - f (WithLocals h locs) = tell [locs] >> return h - f x = return x - - (decl', locals) = runWriter (transformBiM f decl) - - conv :: InBubble -> [Statement] - conv (AuxiliaryVars locs) = locs - conv (DefinednessConstraints locs) = [SuchThat locs] - - newStmts :: [Statement] - newStmts = concatMap conv locals - in - if null newStmts - then return [Declaration decl] - else onStmts (newStmts ++ [Declaration decl']) - onStmt s = return [s] - - -- a where that has a bubble at the top-most level will be replaced - -- with a Comprehension. this is to avoid creating a where with decision variables inside. - onWheres (WithLocals h (DefinednessConstraints locals)) = - return $ map (Where . return) (locals ++ [h]) - onWheres (WithLocals h (AuxiliaryVars locals)) = do - let (localfinds, gens) = mconcat - [ case local of - Declaration (FindOrGiven LocalFind nm dom) -> - ([nm], [Generator (GenDomainNoRepr (Single nm) dom)]) - SuchThat xs -> - ([], map Condition xs) - _ -> bug ("topLevelBubbles.onWheres:" <+> pretty local) - | local <- locals - ] - let forgetReprsOfLocalFinds (Reference nm _) | nm `elem` localfinds = Reference nm Nothing - forgetReprsOfLocalFinds x = descend forgetReprsOfLocalFinds x - let out = Comprehension h gens - out' <- resolveNamesX (forgetReprsOfLocalFinds out) - return [Where [out']] - onWheres x = return [Where [x]] - - onExpr (WithLocals h (AuxiliaryVars locals)) = ( locals ++ [SuchThat [h]]) |> onStmts - onExpr (WithLocals h (DefinednessConstraints locals)) = ([SuchThat locals] ++ [SuchThat [h]]) |> onStmts - onExpr x = return [SuchThat [x]] - - onStmts = concatMapM onStmt - onExprs = concatMapM onExpr - - statements' <- onStmts (mStatements m) - return m { mStatements = statements' } - - -sliceThemMatrices :: Monad m => Model -> m Model -sliceThemMatrices model = do - let - -- nothing stays with a matrix type - -- we are doing this top down - -- when we reach a matrix-typed expression, we know it needs to be sliced - -- we descend otherwise - -- we also descend into components of the matrix-typed expression during slicing - onExpr :: Monad m => Expression -> m Expression - onExpr p = do - let computeExistingSlices t = - case match opSlicing t of - Nothing -> return 0 - Just (t', _, _) -> (+1) <$> computeExistingSlices t' - let isIndexedMatrix = do - (m, is) <- match opMatrixIndexing p - tyM <- typeOf m - nSlices <- computeExistingSlices m - return (m, nSlices, is, tyM) - case isIndexedMatrix of - Nothing -> descendM onExpr p - Just (m, existingSlices, is, tyM) -> do - let nestingLevel (TypeMatrix _ a) = 1 + nestingLevel a - nestingLevel (TypeList a) = 1 + nestingLevel a - nestingLevel _ = 0 :: Int - -- "is" is the number of existing indices - -- "nestingLevel" is the nesting level of the original matrix - -- "existingSlices" is the number of existing slices - let howMany = nestingLevel tyM - existingSlices - length is - let unroll a 0 = a - unroll a i = make opSlicing (unroll a (i-1)) Nothing Nothing - m' <- descendM onExpr m - is' <- mapM onExpr is - let p' = make opMatrixIndexing m' is' - return $ unroll p' howMany - - statements <- descendBiM onExpr (mStatements model) - return model { mStatements = statements } - - -removeExtraSlices :: Monad m => Model -> m Model -removeExtraSlices model = do - let - -- a slice at the end of a chain of slices & indexings - -- does no good in Essence and should be removed - onExpr :: Monad m => Expression -> m Expression - onExpr (match opSlicing -> Just (m,_,_)) = onExpr m - onExpr p@(match opIndexing -> Just _) = return p - onExpr p = descendM onExpr p - - statements <- descendBiM onExpr (mStatements model) - return model { mStatements = statements } - - -logDebugIdModel :: MonadLog m => Doc -> Model -> m Model -logDebugIdModel msg a = logDebug (msg <++> pretty (a {mInfo = def})) >> return a - -prologue :: (MonadFail m, MonadLog m, NameGen m, EnumerateDomain m) => Model -> m Model -prologue model = do - void $ typeCheckModel_StandAlone model - return model >>= logDebugIdModel "[input]" - >>= return . addSearchOrder >>= logDebugIdModel "[addSearchOrder]" - >>= attributeAsConstraints >>= logDebugIdModel "[attributeAsConstraints]" - >>= inferAttributes >>= logDebugIdModel "[inferAttributes]" - >>= inlineLettingDomainsForDecls >>= logDebugIdModel "[inlineLettingDomainsForDecls]" - >>= lettingsForComplexInDoms >>= logDebugIdModel "[lettingsForComplexInDoms]" - >>= distinctQuantifiedVars >>= logDebugIdModel "[distinctQuantifiedVars]" - >>= return . initInfo >>= logDebugIdModel "[initInfo]" - >>= removeUnnamedsFromModel >>= logDebugIdModel "[removeUnnamedsFromModel]" - >>= removeEnumsFromModel >>= logDebugIdModel "[removeEnumsFromModel]" - >>= finiteGivens >>= logDebugIdModel "[finiteGivens]" - >>= resolveNames >>= logDebugIdModel "[resolveNames]" - >>= return . initInfo_Lettings >>= logDebugIdModel "[initInfo_Lettings]" - >>= removeDomainLettings >>= logDebugIdModel "[removeDomainLettings]" - >>= typeCheckModel >>= logDebugIdModel "[typeCheckModel]" - >>= categoryChecking >>= logDebugIdModel "[categoryChecking]" - >>= sanityChecks >>= logDebugIdModel "[sanityChecks]" - >>= dealWithCuts >>= logDebugIdModel "[dealWithCuts]" - >>= removeExtraSlices >>= logDebugIdModel "[removeExtraSlices]" - >>= return . addTrueConstraints >>= logDebugIdModel "[addTrueConstraints]" - - -epilogue :: (MonadFail m, MonadLog m, NameGen m, EnumerateDomain m) => Model -> m Model -epilogue model = return model - >>= logDebugIdModel "[epilogue]" - >>= dropTagForSR >>= logDebugIdModel "[dropTagForSR]" - >>= updateDeclarations >>= logDebugIdModel "[updateDeclarations]" - >>= return . inlineDecVarLettings >>= logDebugIdModel "[inlineDecVarLettings]" - >>= topLevelBubbles >>= logDebugIdModel "[topLevelBubbles]" - >>= checkIfAllRefined >>= logDebugIdModel "[checkIfAllRefined]" - >>= checkIfHasUndefined >>= logDebugIdModel "[checkIfHasUndefined]" - >>= sliceThemMatrices >>= logDebugIdModel "[sliceThemMatrices]" - >>= return . emptyMatrixLiterals >>= logDebugIdModel "[emptyMatrixLiterals]" - >>= return . reverseTrails >>= logDebugIdModel "[reverseTrails]" - >>= return . oneSuchThat >>= logDebugIdModel "[oneSuchThat]" - >>= return . languageEprime >>= logDebugIdModel "[languageEprime]" - - -applicableRules - :: forall m n . ( MonadUserError n, MonadLog n, NameGen n, EnumerateDomain n - , MonadUserError m, MonadLog m, NameGen m, EnumerateDomain m, MonadFail m - ) - => Config - -> [Rule] - -> ModelZipper - -> n [(Doc, RuleResult m)] -applicableRules Config{..} rulesAtLevel x = do - let logAttempt = if logRuleAttempts then logInfo else const (return ()) - let logFail = if logRuleFails then logInfo else const (return ()) - let logSuccess = if logRuleSuccesses then logInfo else const (return ()) - - mys <- sequence [ do logAttempt ("attempting rule" <+> rName r <+> "on" <+> pretty (hole x)) - applied <- runExceptT $ runReaderT (rApply r x (hole x)) x - return (rName r, applied) - | r <- rulesAtLevel ] - forM_ mys $ \ (rule, my) -> - case my of - Left failed -> unless ("N/A" `isPrefixOf` show failed) $ logFail $ vcat - [ " rule failed:" <+> rule - , " on:" <+> pretty (hole x) - , " message:" <+> failed - ] - Right ys -> logSuccess $ vcat - [ "rule applied:" <+> rule - , " on:" <+> pretty (hole x) - , " message:" <+> vcat (map ruleResultDescr ys) - ] - return [ (name, res {ruleResult = ruleResult'}) - | (name, Right ress) <- mys - , res <- ress - , let ruleResult' = do - rResult <- ruleResult res - case (hole x, rResult) of - (Reference nm1 _, Reference nm2 _) - | name /= "choose-repr" - , nm1 == nm2 -> bug $ vcat - [ "Rule applied inside a Reference." - , "Rule :" <+> pretty name - , "Rule input :" <+> pretty (hole x) - , "Rule output :" <+> pretty rResult - , "Rule input (show):" <+> pretty (show (hole x)) - , "Rule output (show):" <+> pretty (show rResult) - ] - _ -> return () - merr <- runExceptT (resolveNamesX rResult) - case merr of - Left err -> bug $ vcat - [ "Name resolution failed after rule application." - , "Rule :" <+> pretty name - , "Rule input :" <+> pretty (hole x) - , "Rule output :" <+> pretty rResult - , "Rule input (show):" <+> pretty (show (hole x)) - , "Rule output (show):" <+> pretty (show rResult) - , "The error :" <+> err - ] - Right r -> return r - ] - - -allRules :: Config -> [[Rule]] -allRules config = - [ [ rule_FullEvaluate - ] - , [ rule_PartialEvaluate - ] - ] ++ paramRules ++ - [ [ rule_ChooseRepr config - , rule_ChooseReprForComprehension config - , rule_ChooseReprForLocals config - ] - , bubbleUpRules - , [ rule_Eq - , rule_Neq - ] - , verticalRules - , horizontalRules - ] ++ otherRules - ++ delayedRules - - --- | For information that can be readily pulled out from parameters. --- Some things are easier when everything involved is a param. --- These rules aren't necessary for correctness, but they can help remove some verbose expressions from the output. --- Make Savile Row happier so it makes us happier. :) -paramRules :: [[Rule]] -paramRules = - [ [ Horizontal.Set.rule_Param_MinOfSet - , Horizontal.Set.rule_Param_MaxOfSet - , Horizontal.Set.rule_Param_Card - ] - , [ Horizontal.Function.rule_Param_DefinedRange - , Horizontal.Relation.rule_Param_Card - ] - ] - -verticalRules :: [Rule] -verticalRules = - [ Vertical.Tuple.rule_Tuple_Eq - , Vertical.Tuple.rule_Tuple_Neq - , Vertical.Tuple.rule_Tuple_Leq - , Vertical.Tuple.rule_Tuple_Lt - , Vertical.Tuple.rule_Tuple_TildeLeq - , Vertical.Tuple.rule_Tuple_TildeLt - , Vertical.Tuple.rule_Tuple_Index - - , Vertical.Record.rule_Record_Eq - , Vertical.Record.rule_Record_Neq - , Vertical.Record.rule_Record_Leq - , Vertical.Record.rule_Record_Lt - , Vertical.Record.rule_Record_DotLeq - , Vertical.Record.rule_Record_DotLt - , Vertical.Record.rule_Record_Index - - , Vertical.Variant.rule_Variant_Eq - , Vertical.Variant.rule_Variant_Neq - , Vertical.Variant.rule_Variant_Leq - , Vertical.Variant.rule_Variant_Lt - , Vertical.Variant.rule_Variant_DotLeq - , Vertical.Variant.rule_Variant_DotLt - , Vertical.Variant.rule_Variant_Index - , Vertical.Variant.rule_Variant_Active - - , Vertical.Matrix.rule_Comprehension_Literal - , Vertical.Matrix.rule_ModifierAroundIndexedMatrixLiteral - -- , Vertical.Matrix.rule_QuantifierAroundIndexedMatrixLiteral - , Vertical.Matrix.rule_Comprehension_LiteralIndexed - , Vertical.Matrix.rule_Comprehension_Nested - , Vertical.Matrix.rule_Comprehension_Hist - , Vertical.Matrix.rule_Comprehension_ToSet_Matrix - , Vertical.Matrix.rule_Comprehension_ToSet_List - , Vertical.Matrix.rule_Comprehension_ToSet_List_DuplicateFree - , Vertical.Matrix.rule_Matrix_Eq - , Vertical.Matrix.rule_Matrix_Neq - , Vertical.Matrix.rule_Matrix_Leq_Primitive - , Vertical.Matrix.rule_Matrix_Leq_Decompose - , Vertical.Matrix.rule_Matrix_Lt_Primitive - , Vertical.Matrix.rule_Matrix_Lt_Decompose -<<<<<<< HEAD - , Vertical.Matrix.rule_Matrix_DotLeq_Decompose --- , Vertical.Matrix.rule_Matrix_DotLeq_Symbreak_Decompose - , Vertical.Matrix.rule_Matrix_DotLt_Decompose -||||||| merged common ancestors - , Vertical.Matrix.rule_Matrix_DotLeq_Decompose - , Vertical.Matrix.rule_Matrix_DotLt_Decompose -======= ->>>>>>> master - , Vertical.Matrix.rule_IndexingIdentical - - , Vertical.Set.Explicit.rule_Min - , Vertical.Set.Explicit.rule_Max - , Vertical.Set.Explicit.rule_Card - , Vertical.Set.Explicit.rule_Comprehension - , Vertical.Set.Explicit.rule_PowerSet_Comprehension - , Vertical.Set.ExplicitVarSizeWithDummy.rule_Comprehension - , Vertical.Set.ExplicitVarSizeWithDummy.rule_PowerSet_Comprehension - , Vertical.Set.ExplicitVarSizeWithFlags.rule_Comprehension - , Vertical.Set.ExplicitVarSizeWithFlags.rule_PowerSet_Comprehension - , Vertical.Set.ExplicitVarSizeWithMarker.rule_Card - , Vertical.Set.ExplicitVarSizeWithMarker.rule_Comprehension - , Vertical.Set.ExplicitVarSizeWithMarker.rule_PowerSet_Comprehension - , Vertical.Set.Occurrence.rule_Comprehension - , Vertical.Set.Occurrence.rule_PowerSet_Comprehension - , Vertical.Set.Occurrence.rule_In - - , Vertical.MSet.ExplicitWithFlags.rule_Comprehension - , Vertical.MSet.ExplicitWithFlags.rule_Freq - - , Vertical.MSet.ExplicitWithRepetition.rule_Comprehension - - , Vertical.Function.Function1D.rule_Comprehension - , Vertical.Function.Function1D.rule_Comprehension_Defined - , Vertical.Function.Function1D.rule_Image - - , Vertical.Function.Function1DPartial.rule_Comprehension - , Vertical.Function.Function1DPartial.rule_Image_NotABool - , Vertical.Function.Function1DPartial.rule_Image_Bool - , Vertical.Function.Function1DPartial.rule_InDefined - , Vertical.Function.Function1DPartial.rule_DefinedEqDefined - - , Vertical.Function.FunctionND.rule_Comprehension - , Vertical.Function.FunctionND.rule_Comprehension_Defined - , Vertical.Function.FunctionND.rule_Image - - , Vertical.Function.FunctionNDPartial.rule_Comprehension - , Vertical.Function.FunctionNDPartial.rule_Image_NotABool - , Vertical.Function.FunctionNDPartial.rule_Image_Bool - , Vertical.Function.FunctionNDPartial.rule_InDefined - - , Vertical.Function.FunctionAsRelation.rule_Comprehension - , Vertical.Function.FunctionAsRelation.rule_Image_Eq - - , Vertical.Sequence.ExplicitBounded.rule_Comprehension - , Vertical.Sequence.ExplicitBounded.rule_Card - , Vertical.Sequence.ExplicitBounded.rule_Image_Bool - , Vertical.Sequence.ExplicitBounded.rule_Image_NotABool - , Vertical.Sequence.ExplicitBounded.rule_Leq - , Vertical.Sequence.ExplicitBounded.rule_Lt - - , Vertical.Relation.RelationAsMatrix.rule_Comprehension - , Vertical.Relation.RelationAsMatrix.rule_Image - - , Vertical.Relation.RelationAsSet.rule_Comprehension - , Vertical.Relation.RelationAsSet.rule_Card - - , Vertical.Partition.PartitionAsSet.rule_Comprehension - , Vertical.Partition.Occurrence.rule_Comprehension - - - , Vertical.Permutation.AsFunction.rule_Permute_Comprehension_Tuples - , Vertical.Permutation.AsFunction.rule_Relation_Permute - , Vertical.Permutation.AsFunction.rule_Relation_Permute_Comprehension - , Vertical.Permutation.AsFunction.rule_Set_Permute - , Vertical.Permutation.AsFunction.rule_Tuple_Permute - , Vertical.Permutation.AsFunction.rule_Tuple_Permute_Comprehension - , Vertical.Permutation.AsFunction.rule_Matrix_Permute - , Vertical.Permutation.AsFunction.rule_Matrix_Permute_Comprehension - - - - - ] - -horizontalRules :: [Rule] -horizontalRules = - [ Horizontal.Set.rule_Comprehension_Literal - , Horizontal.Set.rule_Eq - , Horizontal.Set.rule_Neq - , Horizontal.Set.rule_Subset - , Horizontal.Set.rule_SubsetEq - , Horizontal.Set.rule_Supset - , Horizontal.Set.rule_SupsetEq - , Horizontal.Set.rule_In - , Horizontal.Set.rule_Card - , Horizontal.Set.rule_CardViaFreq - , Horizontal.Set.rule_Intersect - , Horizontal.Set.rule_Union - , Horizontal.Set.rule_Difference - , Horizontal.Set.rule_PowerSet_Comprehension - , Horizontal.Set.rule_PowerSet_Difference - , Horizontal.Set.rule_MaxMin - - , Horizontal.MSet.rule_Comprehension_Literal - , Horizontal.MSet.rule_Comprehension_ToSet_Literal - , Horizontal.MSet.rule_Eq - , Horizontal.MSet.rule_Neq - , Horizontal.MSet.rule_Subset - , Horizontal.MSet.rule_SubsetEq - , Horizontal.MSet.rule_Supset - , Horizontal.MSet.rule_SupsetEq - , Horizontal.MSet.rule_Freq - , Horizontal.MSet.rule_In - , Horizontal.MSet.rule_Card - , Horizontal.MSet.rule_MaxMin - - , Horizontal.Function.rule_Comprehension_Literal - , Horizontal.Function.rule_Image_Bool - , Horizontal.Function.rule_Image_BoolMatrixIndexed - , Horizontal.Function.rule_Image_BoolTupleIndexed - , Horizontal.Function.rule_Image_Int - , Horizontal.Function.rule_Image_IntMatrixIndexed - , Horizontal.Function.rule_Image_IntTupleIndexed - , Horizontal.Function.rule_Image_Matrix_LexLhs - , Horizontal.Function.rule_Image_Matrix_LexRhs - - , Horizontal.Function.rule_Comprehension_Image - , Horizontal.Function.rule_Comprehension_ImageSet - , Horizontal.Function.rule_Eq - , Horizontal.Function.rule_Neq - , Horizontal.Function.rule_Subset - , Horizontal.Function.rule_SubsetEq - , Horizontal.Function.rule_Supset - , Horizontal.Function.rule_SupsetEq - , Horizontal.Function.rule_Inverse - , Horizontal.Function.rule_Card - , Horizontal.Function.rule_Comprehension_PreImage - , Horizontal.Function.rule_Comprehension_Defined - , Horizontal.Function.rule_Comprehension_Range - , Horizontal.Function.rule_In - , Horizontal.Function.rule_Restrict_Image - , Horizontal.Function.rule_Restrict_Comprehension - , Horizontal.Function.rule_Comprehension_Defined_Size - , Horizontal.Function.rule_Comprehension_Range_Size - , Horizontal.Function.rule_Defined_Intersect - , Horizontal.Function.rule_DefinedOrRange_Union - , Horizontal.Function.rule_DefinedOrRange_Difference - - , Horizontal.Sequence.rule_Comprehension_Literal - , Horizontal.Sequence.rule_Image_Bool - , Horizontal.Sequence.rule_Image_Int - , Horizontal.Sequence.rule_Comprehension_Image - , Horizontal.Sequence.rule_Image_Literal_Bool - , Horizontal.Sequence.rule_Image_Literal_Int - , Horizontal.Sequence.rule_Eq_Empty - , Horizontal.Sequence.rule_Eq - , Horizontal.Sequence.rule_Eq_Comprehension - , Horizontal.Sequence.rule_Neq - , Horizontal.Sequence.rule_Subset - , Horizontal.Sequence.rule_SubsetEq - , Horizontal.Sequence.rule_Supset - , Horizontal.Sequence.rule_SupsetEq - , Horizontal.Sequence.rule_Card - , Horizontal.Sequence.rule_Comprehension_PreImage - , Horizontal.Sequence.rule_Comprehension_Defined - , Horizontal.Sequence.rule_Comprehension_Range - , Horizontal.Sequence.rule_In - , Horizontal.Sequence.rule_Restrict_Image - , Horizontal.Sequence.rule_Restrict_Comprehension - , Horizontal.Sequence.rule_Substring - , Horizontal.Sequence.rule_Subsequence - - , Horizontal.Relation.rule_Comprehension_Literal - , Horizontal.Relation.rule_Comprehension_Projection - , Horizontal.Relation.rule_PowerSet_Comprehension - , Horizontal.Relation.rule_Image - , Horizontal.Relation.rule_In - , Horizontal.Relation.rule_Eq - , Horizontal.Relation.rule_Neq - , Horizontal.Relation.rule_Subset - , Horizontal.Relation.rule_SubsetEq - , Horizontal.Relation.rule_Supset - , Horizontal.Relation.rule_SupsetEq - , Horizontal.Relation.rule_Card - - , Horizontal.Partition.rule_Comprehension_Literal - , Horizontal.Partition.rule_Eq - , Horizontal.Partition.rule_Neq - , Horizontal.Partition.rule_Together - , Horizontal.Partition.rule_Apart - , Horizontal.Partition.rule_Party - , Horizontal.Partition.rule_Participants - , Horizontal.Partition.rule_Card - , Horizontal.Partition.rule_In - - - , Horizontal.Permutation.rule_Permute_Literal - , Horizontal.Permutation.rule_Permute_Literal_Comprehension - , Horizontal.Permutation.rule_Compose - - - - ] - - -bubbleUpRules :: [Rule] -bubbleUpRules = - [ BubbleUp.rule_MergeNested - , BubbleUp.rule_ToAnd - , BubbleUp.rule_ToMultiply_HeadOfIntComprehension - , BubbleUp.rule_NotBoolYet - , BubbleUp.rule_ConditionInsideGeneratorDomain - , BubbleUp.rule_LiftVars - ] - - -otherRules :: [[Rule]] -otherRules = - [ - [ rule_Xor_To_Sum ] - , - [ TildeOrdering.rule_BoolInt - , TildeOrdering.rule_MSet - , TildeOrdering.rule_ViaMSet - , TildeOrdering.rule_TildeLeq - ] - , - [ DontCare.rule_Bool - , DontCare.rule_Int - , DontCare.rule_Tuple - , DontCare.rule_Record - , DontCare.rule_Variant - , DontCare.rule_Matrix - , DontCare.rule_Abstract - ] - , - [ rule_TrueIsNoOp - , rule_FlattenOf1D - , rule_Decompose_AllDiff - - , rule_GeneratorsFirst - - , rule_DomainCardinality - , rule_DomainMinMax - - , rule_ComplexAbsPat - - , rule_AttributeToConstraint - - , rule_QuantifierShift - , rule_QuantifierShift2 - , rule_QuantifierShift3 - - ] - - , [ rule_Comprehension_Simplify - ] - - , [ rule_InlineConditions - , rule_InlineConditions_AllDiff - , rule_InlineConditions_MaxMin - ] - ] - --- | These rules depend on other rules firing first. -delayedRules :: [[Rule]] -delayedRules = - [ - [ Vertical.Matrix.rule_Comprehension_Singleton - , Vertical.Matrix.rule_Comprehension_SingletonDomain - , Vertical.Matrix.rule_Concatenate_Singleton - , Vertical.Matrix.rule_MatrixIndexing - --- , Horizontal.Permutation.rule_Permute_Literal --- , Horizontal.Permutation.rule_Permute_Literal_Comprehension - , Vertical.Permutation.AsFunction.rule_Permute - , Vertical.Permutation.AsFunction.rule_Permute_Comprehension - ] - , [ rule_ReducerToComprehension - ] - , [ rule_DotLtLeq - ] - ] - - -rule_ChooseRepr :: Config -> Rule -rule_ChooseRepr config = Rule "choose-repr" (const theRule) where - - theRule (Reference nm (Just (DeclNoRepr forg _ inpDom region))) | forg `elem` [Find, Given, CutFind] = do - let reprsWhichOrder - | (forg, representationsGivens config) == (Given, Sparse) = reprsSparseOrder - | representationLevels config == False = reprsStandardOrderNoLevels - | otherwise = reprsStandardOrder - domOpts <- reprOptions reprsWhichOrder inpDom - when (null domOpts) $ - bug $ "No representation matches this beast:" <++> pretty inpDom - let options = - [ RuleResult { ruleResultDescr = msg - , ruleResultType = case forg of - Find -> ChooseRepr_Find - Given -> ChooseRepr_Given - CutFind -> ChooseRepr_Cut - _ -> bug "rule_ChooseRepr ruleResultType" - , ruleResult = return out - , ruleResultHook = Just hook - } - | dom <- domOpts - , let msg = "Choosing representation for" <+> pretty nm <> ":" <++> pretty dom - , let out = Reference nm (Just (DeclHasRepr forg nm dom)) - , let hook = mkHook (channelling config) forg nm dom region - ] - return options - theRule _ = na "rule_ChooseRepr" - - mkHook - :: ( MonadLog m - , MonadFail m - , NameGen m - , EnumerateDomain m - ) - => Bool - -> FindOrGiven - -> Name - -> Domain HasRepresentation Expression - -> Region - -> Model - -> m Model - mkHook useChannelling -- whether to use channelling or not - forg -- find or given - name -- name of the original declaration - domain -- domain with representation selected - region -- the region of the Reference we are working on - model = do - let - - representations = model |> mInfo |> miRepresentations - representationsTree = model |> mInfo |> miRepresentationsTree - |> concatMap (\ (n, ds) -> map (n,) ds ) - - usedBefore = (name, reprTree domain) `elem` representationsTree - - mkStructurals :: (MonadLog m, MonadFail m, NameGen m, EnumerateDomain m) - => m [Expression] - mkStructurals = do - let ref = Reference name (Just (DeclHasRepr forg name domain)) - logDebugVerbose $ "Generating structural constraints for:" <+> vcat [pretty ref, pretty domain] - structurals <- getStructurals downX1 domain >>= \ gen -> gen ref - logDebugVerbose $ "Before name resolution:" <+> vcat (map pretty structurals) - resolved <- mapM resolveNamesX structurals -- re-resolving names - logDebugVerbose $ "After name resolution:" <+> vcat (map pretty resolved) - return resolved - - addStructurals :: (MonadLog m, MonadFail m, NameGen m, EnumerateDomain m) - => Model -> m Model - addStructurals - | forg == Given = return - | usedBefore = return - | otherwise = \ m -> do - structurals <- mkStructurals - return $ if null structurals - then m - else m { mStatements = mStatements m ++ [SuchThat structurals] } - - channels = - [ make opEq this that - | (n, d) <- representations - , n == name - , let this = Reference name (Just (DeclHasRepr forg name domain)) - , let that = Reference name (Just (DeclHasRepr forg name d)) - ] - - addChannels - | forg == Given = return - | usedBefore = return - | null channels = return - | otherwise = \ m -> return - m { mStatements = mStatements m ++ [SuchThat channels] } - - recordThis - | usedBefore = return - | otherwise = \ m -> - let - oldInfo = mInfo m - newInfo = oldInfo - { miRepresentations = representations ++ [(name, domain)] - , miRepresentationsTree = (representationsTree ++ [(name, reprTree domain)]) - |> sortBy (comparing fst) - |> groupBy ((==) `on` fst) - |> map (\ grp -> (fst (head grp), map snd grp) ) - } - in return m { mInfo = newInfo } - - fixReprForAllOthers - | useChannelling = return -- no-op, if channelling=yes - | otherwise = \ m -> - let - f (Reference nm _) - | nm == name - = Reference nm (Just (DeclHasRepr forg name domain)) - f x = x - in - return m { mStatements = transformBi f (mStatements m) } - - fixReprForSameRegion - | region == NoRegion = return -- no-op, if we aren't in a particular region - | otherwise = \ m -> - let - f (Reference nm (Just (DeclNoRepr _ _ _ region'))) - | nm == name - , region' == region - = Reference nm (Just (DeclHasRepr forg name domain)) - f x = x - in - return m { mStatements = transformBi f (mStatements m) } - - - logDebugVerbose $ vcat - [ "Name :" <+> pretty name - , "Previously :" <+> vcat [ pretty (show d) | (n,d) <- representations, n == name ] - , "This guy :" <+> pretty (show domain) - , "usedBefore? :" <+> pretty usedBefore - ] - - return model - >>= addStructurals -- unless usedBefore: add structurals - >>= addChannels -- for each in previously recorded representation - >>= recordThis -- unless usedBefore: record (name, domain) as being used in the model - >>= fixReprForAllOthers -- fix the representation of this guy in the whole model, if channelling=no - >>= fixReprForSameRegion -- fix the representation of this guy in the whole model, - -- for those references with the same "region" - >>= resolveNames -- we need to re-resolve names to avoid repeatedly selecting representations - -- for abstract stuff inside aliases. - - -rule_ChooseReprForComprehension :: Config -> Rule -rule_ChooseReprForComprehension config = Rule "choose-repr-for-comprehension" (const theRule) where - - theRule (Comprehension body gensOrConds) = do - (gocBefore, (nm, domain), gocAfter) <- matchFirst gensOrConds $ \ goc -> case goc of - Generator (GenDomainNoRepr (Single nm) domain) -> return (nm, domain) - _ -> na "rule_ChooseReprForComprehension" - - ty <- typeOf domain - - let reprsWhichOrder - | representationsGivens config == Sparse = reprsSparseOrder - | representationLevels config == False = reprsStandardOrderNoLevels - | otherwise = reprsStandardOrder - domOpts <- reprOptions reprsWhichOrder domain - when (null domOpts) $ - bug $ "No representation matches this beast:" <++> pretty domain - - let genOptions = - [ do - outs <- downD (nm, dom) - structurals <- mkStructurals nm dom - return (dom, outs, structurals) - | dom <- domOpts - ] - - return - [ RuleResult - { ruleResultDescr = "Choosing representation for quantified variable" <+> pretty nm - <+> "(with type:" <+> pretty ty <> ")" - , ruleResultType = ChooseRepr_Quantified - , ruleResult = bugFailT "rule_ChooseReprForComprehension" $ do - option <- genOption - let (thisDom, outDomains, structurals) = option - let updateRepr (Reference nm' _) - | nm == nm' - = Reference nm (Just (DeclHasRepr Quantified nm thisDom)) - updateRepr p = p - let out' = Comprehension (transform updateRepr body) - $ gocBefore - ++ [ Generator (GenDomainHasRepr name dom) - | (name, dom) <- outDomains ] - ++ map Condition structurals - ++ transformBi updateRepr gocAfter - out <- resolveNamesX out' - return out - , ruleResultHook = Nothing - } - | genOption <- genOptions - ] - theRule _ = na "rule_ChooseReprForComprehension" - - mkStructurals name domain = do - let ref = Reference name (Just (DeclHasRepr Quantified name domain)) - gen <- getStructurals downX1 domain - gen ref - - -rule_ChooseReprForLocals :: Config -> Rule -rule_ChooseReprForLocals config = Rule "choose-repr-for-locals" (const theRule) where - - theRule (WithLocals body (AuxiliaryVars locals)) = do - (stmtBefore, (nm, domain), stmtAfter) <- matchFirst locals $ \ local -> case local of - Declaration (FindOrGiven LocalFind nm domain) -> return (nm, domain) - _ -> na "rule_ChooseReprForLocals" - - let - isReferencedWithoutRepr (Reference nm' (Just DeclNoRepr{})) | nm == nm' = True - isReferencedWithoutRepr _ = False - - unless (any isReferencedWithoutRepr (universeBi (body, stmtBefore, stmtAfter))) $ - na $ "This local variable seems to be handled before:" <+> pretty nm - - let reprsWhichOrder - | representationsAuxiliaries config == Sparse = reprsSparseOrder - | representationLevels config == False = reprsStandardOrderNoLevels - | otherwise = reprsStandardOrder - domOpts <- reprOptions reprsWhichOrder domain - when (null domOpts) $ - bug $ "No representation matches this beast:" <++> pretty domain - - let genOptions = - [ do - outs <- downD (nm, dom) - structurals <- mkStructurals nm dom - return (dom, outs, structurals) - | dom <- domOpts - ] - - return - [ RuleResult - { ruleResultDescr = "Choosing representation for local variable" <+> pretty nm - , ruleResultType = ChooseRepr_Auxiliary - , ruleResult = bugFailT "rule_ChooseReprForLocals" $ do - option <- genOption - let (thisDom, outDomains, structurals) = option - let updateRepr (Reference nm' _) - | nm == nm' - = Reference nm (Just (DeclHasRepr LocalFind nm thisDom)) - updateRepr p = p - let out' = WithLocals (transform updateRepr body) $ AuxiliaryVars - ( stmtBefore - ++ [ Declaration (FindOrGiven - LocalFind - name - (forgetRepr dom)) - | (name, dom) <- outDomains ] - ++ [ SuchThat structurals | not (null structurals) ] - ++ transformBi updateRepr stmtAfter - ) - out <- resolveNamesX out' - return out - , ruleResultHook = Nothing - } - | genOption <- genOptions - ] - theRule _ = na "rule_ChooseReprForLocals" - - mkStructurals name domain = do - let ref = Reference name (Just (DeclHasRepr LocalFind name domain)) - gen <- getStructurals downX1 domain - gen ref - - -rule_GeneratorsFirst :: Rule -rule_GeneratorsFirst = "generators-first" `namedRule` theRule where - theRule (Comprehension body []) - = return - ( "Empty generators." - , return $ AbstractLiteral $ AbsLitMatrix (mkDomainIntB 1 1) [body] - ) - theRule (Comprehension body gensOrConds) - | let (gens, rest) = mconcat - [ case x of - Generator{} -> ([x],[]) - _ -> ([],[x]) - | x <- gensOrConds - ] - , let gensOrConds' = gens ++ rest - , gensOrConds /= gensOrConds' - = return - ( "Generators come first." - , return $ Comprehension body gensOrConds' - ) - theRule (Comprehension body gensOrConds) - | let (lettings, rest) = mconcat - [ case x of - ComprehensionLetting nm _ -> ([nm],[] ) - _ -> ([] ,[x]) - | x <- gensOrConds - ] - , let f (Reference nm (Just (Alias x))) | nm `elem` lettings = f x - f x = x - , not (null lettings) - = return - ( "Inlining comprehension lettings." - , return $ transformBi f $ Comprehension body rest - ) - theRule _ = na "rule_GeneratorsFirst" - - -rule_Eq :: Rule -rule_Eq = "identical-domain-eq" `namedRule` theRule where - theRule p = do - (x,y) <- match opEq p - domX <- domainOf x - domY <- domainOf y - unless (domX == domY) $ na "rule_Eq domains not identical" - sameRepresentationTree x y - xs <- downX x - ys <- downX y - unless (length xs == length ys) $ na "rule_Eq" - when (xs == [x]) $ na "rule_Eq" - when (ys == [y]) $ na "rule_Eq" - return - ( "Generic vertical rule for identical-domain equality" - , return $ make opAnd $ fromList $ zipWith (\ i j -> [essence| &i = &j |] ) xs ys - ) - - -rule_Neq :: Rule -rule_Neq = "identical-domain-neq" `namedRule` theRule where - theRule p = do - (x,y) <- match opNeq p - domX <- domainOf x - domY <- domainOf y - unless (domX == domY) $ na "rule_Neq domains not identical" - sameRepresentationTree x y - xs <- downX x - ys <- downX y - unless (length xs == length ys) $ na "rule_Neq" - when (xs == [x]) $ na "rule_Neq" - when (ys == [y]) $ na "rule_Neq" - return - ( "Generic vertical rule for identical-domain equality" - , return $ make opOr $ fromList $ zipWith (\ i j -> [essence| &i != &j |] ) xs ys - ) - - -rule_DotLtLeq :: Rule -rule_DotLtLeq = "generic-DotLtLeq" `namedRule` theRule where - theRule p = do - (a,b,mk) <- case p of - [essence| &a .< &b |] -> return ( a, b, \ i j -> [essence| &i return ( a, b, \ i j -> [essence| &i <=lex &j |] ) - _ -> na "rule_DotLtLeq" - aType <- typeOf a - case aType of - TypeTuple{} -> return () - TypeMatrix{} -> return () - TypeSet{} -> return () - TypeMSet{} -> return () - TypeFunction{} -> return () - TypeSequence{} -> return () - TypeRelation{} -> return () - TypePartition{} -> return () - _ -> na "rule_DotLtLeq" - -- sameRepresentationTree a b - let - nestingLevel (TypeMatrix _ t) = 1 + nestingLevel t - nestingLevel (TypeList t) = 1 + nestingLevel t - nestingLevel _ = 0 :: Int - - innerMostTy (TypeMatrix _ t) = innerMostTy t - innerMostTy (TypeList t) = innerMostTy t - innerMostTy t = t - - matrixForAll [] x = return (x, []) - matrixForAll (dom:doms) x = do - (iPat, i) <- quantifiedVar - (xIndexed, gens) <- matrixForAll doms [essence| &x[&i] |] - let gen = Generator (GenDomainNoRepr iPat dom) - return (xIndexed, gen : gens) - - mk1D x = do - ty <- typeOf x - case nestingLevel ty of - 0 -> case ty of - TypeBool -> return [essence| [toInt(&x)] |] - TypeInt{} -> return [essence| [&x] |] - _ -> bug ("What type? [0]" <+> pretty ty) - nl -> do - xInt <- case innerMostTy ty of - TypeBool -> do - doms <- indexDomainsOf x - (xIndexed, gens) <- matrixForAll doms x - return $ Comprehension [essence| toInt(&xIndexed) |] gens - TypeInt{} -> return x - _ -> bug ("What type? [1]" <+> pretty ty) - if nl == 1 - then return xInt - else return [essence| flatten(&xInt) |] - - wrap [x] = x - wrap xs = make opFlatten (fromList xs) - - ma <- downX a >>= mapM mk1D >>= return . wrap - mb <- downX b >>= mapM mk1D >>= return . wrap - return - ( "Generic vertical rule for dotLt and dotLeq:" <+> pretty p - , return $ mk ma mb - ) - - -rule_ReducerToComprehension :: Rule -rule_ReducerToComprehension = "reducer-to-comprehension" `namedRule` theRule where - theRule p = do - (_, mk, coll) <- match opReducer p - -- leave comprehensions alone - let - isComprehension Comprehension{} = True - isComprehension _ = False - case followAliases isComprehension coll of - True -> na "rule_ReducerToComprehension" - False -> return () - -- leave matrix literals alone - case tryMatch matrixLiteral coll of - Nothing -> return () - Just {} -> na "rule_ReducerToComprehension" - tyColl <- typeOf coll - howToIndex <- case tyColl of - TypeMatrix{} -> return $ Left () - TypeList{} -> return $ Right () - TypeSet{} -> return $ Right () - TypeMSet{} -> return $ Right () - _ -> na "rule_ReducerToComprehension" - return - ( "Creating a comprehension for the collection inside the reducer operator." - , do - (iPat, i) <- quantifiedVar - case howToIndex of - Left{} -> return $ mk [essence| [ &i[2] | &iPat <- &coll ] |] - Right{} -> return $ mk [essence| [ &i | &iPat <- &coll ] |] - ) - - -rule_TrueIsNoOp :: Rule -rule_TrueIsNoOp = "true-is-noop" `namedRule` theRule where - theRule (Op (MkOpTrue (OpTrue ref))) = - case ref of - Reference _ (Just DeclHasRepr{}) -> - return ( "Remove the argument from true." - , return $ Constant $ ConstantBool True - ) - _ -> na "The argument of true doesn't have a representation." - theRule _ = na "rule_TrueIsNoOp" - - -rule_FlattenOf1D :: Rule -rule_FlattenOf1D = "flatten-of-1D" `namedRule` theRule where - theRule p = do - x <- match opFlatten p - tyx <- typeOf x - case tyx of - TypeList TypeBool{} -> return () - TypeList TypeInt{} -> return () - TypeMatrix _ TypeBool{} -> return () - TypeMatrix _ TypeInt{} -> return () - _ -> na "rule_FlattenOf1D" - return ( "1D matrices do not need a flatten." - , return x - ) - - -rule_Decompose_AllDiff :: Rule -rule_Decompose_AllDiff = "decompose-allDiff" `namedRule` theRule where - theRule [essence| allDiff(&m) |] = do - ty <- typeOf m - case ty of - TypeMatrix _ TypeBool -> na "allDiff can stay" - TypeMatrix _ (TypeInt _) -> na "allDiff can stay" - TypeMatrix _ _ -> return () - _ -> na "allDiff on something other than a matrix." - index:_ <- indexDomainsOf m - return - ( "Decomposing allDiff. Type:" <+> pretty ty - , do - (iPat, i) <- quantifiedVar - (jPat, j) <- quantifiedVar - return - [essence| - and([ &m[&i] != &m[&j] - | &iPat : &index - , &jPat : &index - , &i < &j - ]) - |] - ) - theRule _ = na "rule_Decompose_AllDiff" - - -rule_DomainCardinality :: Rule -rule_DomainCardinality = "domain-cardinality" `namedRule` theRule where - theRule p = do - maybeDomain <- match opTwoBars p - d <- case maybeDomain of - Domain d -> return d - Reference _ (Just (Alias (Domain d))) -> return d - _ -> na "rule_DomainCardinality" - return - ( "Cardinality of a domain" - , case d of - DomainInt _ [RangeBounded 1 u] -> return u - _ -> do - (iPat, _) <- quantifiedVar - return [essence| sum([ 1 | &iPat : &d ]) |] - ) - - -rule_DomainMinMax :: Rule -rule_DomainMinMax = "domain-MinMax" `namedRule` theRule where - theRule [essence| max(&maybeDomain) |] = do - d <- getDomain maybeDomain - return - ( "max of a domain" - , maxOfDomain d - ) - theRule [essence| min(&maybeDomain) |] = do - d <- getDomain maybeDomain - return - ( "min of a domain" - , minOfDomain d - ) - theRule _ = na "rule_DomainMinMax" - - getDomain :: MonadFail m => Expression -> m (Domain () Expression) - getDomain (Domain d) = return d - getDomain (Reference _ (Just (Alias (Domain d)))) = getDomain (Domain d) - getDomain _ = na "rule_DomainMinMax.getDomain" - - -rule_ComplexAbsPat :: Rule -rule_ComplexAbsPat = "complex-pattern" `namedRule` theRule where - theRule (Comprehension body gensOrConds) = do - (gocBefore, (pat, domainOrExpr), gocAfter) <- matchFirst gensOrConds $ \ goc -> case goc of - Generator (GenDomainNoRepr pat@AbsPatTuple{} domain) -> return (pat, Left domain) - Generator (GenInExpr pat@AbsPatTuple{} expr) -> return (pat, Right expr) - _ -> na "rule_ComplexAbsPat" - return - ( "complex pattern on tuple patterns" - , do - (iPat, i) <- quantifiedVar - let replacements = [ (p, make opMatrixIndexing i (map (fromInt . fromIntegral) is)) - | (p, is) <- genMappings pat - ] - let f x@(Reference nm _) = fromMaybe x (lookup nm replacements) - f x = x - return $ Comprehension (transform f body) - $ gocBefore - ++ [ either (Generator . GenDomainNoRepr iPat) - (Generator . GenInExpr iPat) - domainOrExpr ] - ++ transformBi f gocAfter - ) - theRule _ = na "rule_ComplexAbsPat" - - -- i --> i -> [] - -- (i,j) --> i -> [1] - -- j -> [2] - -- (i,(j,k)) --> i -> [1] - -- j -> [2,1] - -- k -> [2,2] - genMappings :: AbstractPattern -> [(Name, [Int])] - genMappings (Single nm) = [(nm, [])] - genMappings (AbsPatTuple pats) - = concat - [ [ (patCore, i:is) | (patCore, is) <- genMappings pat ] - | (i, pat) <- zip [1..] pats - ] - genMappings (AbsPatMatrix pats) - = concat - [ [ (patCore, i:is) | (patCore, is) <- genMappings pat ] - | (i, pat) <- zip [1..] pats - ] - genMappings pat = bug ("rule_ComplexLambda.genMappings:" <+> pretty (show pat)) - - --- this rule doesn't use `namedRule` because it need access to ascendants through the zipper -rule_InlineConditions :: Rule -rule_InlineConditions = Rule "inline-conditions" theRule where - theRule z (Comprehension body gensOrConds) = do - let (toInline, toKeep) = mconcat - [ case goc of - Condition x | categoryOf x == CatDecision -> ([x],[]) - _ -> ([],[goc]) - | goc <- gensOrConds - ] - theGuard <- case toInline of - [] -> na "No condition to inline." - [x] -> return x - xs -> return $ make opAnd $ fromList xs - (nameQ, opSkip) <- queryQ z - let bodySkipped = opSkip theGuard body - return - [ RuleResult - { ruleResultDescr = "Inlining conditions, inside" <+> nameQ - , ruleResultType = ExpressionRefinement - , ruleResult = return $ Comprehension bodySkipped toKeep - , ruleResultHook = Nothing - } ] - theRule _ _ = na "rule_InlineConditions" - - -- keep going up, until finding a quantifier - -- when found, return the skipping operator for the quantifier - -- if none exists, do not apply the rule. - -- (or maybe we should call bug right ahead, it can't be anything else.) - queryQ z0 = - case Zipper.up z0 of - Nothing -> na "rule_InlineConditions (meh-1)" - Just z -> do - let h = hole z - case ( match opAnd h, match opOr h, match opSum h - , match opMin h, match opMax h ) of - (Just{}, _, _, _, _) -> return ("and", opAndSkip) - (_, Just{}, _, _, _) -> return ("or" , opOrSkip ) - (_, _, Just{}, _, _) -> return ("sum", opSumSkip) - (_, _, _, Just{}, _) -> na "rule_InlineConditions (min)" - (_, _, _, _, Just{}) -> na "rule_InlineConditions (max)" - _ -> na "rule_InlineConditions (meh-2)" - -- case Zipper.up z of - -- Nothing -> na "queryQ" - -- Just u -> queryQ u - - opAndSkip b x = [essence| &b -> &x |] - opOrSkip b x = [essence| &b /\ &x |] - opSumSkip b x = [essence| toInt(&b) * catchUndef(&x, 0) |] - - -rule_InlineConditions_AllDiff :: Rule -rule_InlineConditions_AllDiff = "inline-conditions-allDiff" `namedRule` theRule where - theRule (Op (MkOpAllDiff (OpAllDiff (Comprehension body gensOrConds)))) = do - let (toInline, toKeep) = mconcat - [ case goc of - Condition x | categoryOf x == CatDecision -> ([x],[]) - _ -> ([],[goc]) - | goc <- gensOrConds - ] - theGuard <- case toInline of - [] -> na "No condition to inline." - [x] -> return x - xs -> return $ make opAnd $ fromList xs - - domBody <- domainOf body - let - collectLowerBounds (RangeSingle x) = return x - collectLowerBounds (RangeBounded x _) = return x - collectLowerBounds _ = userErr1 ("Unexpected infinite domain:" <+> pretty domBody) - - collectLowerBoundsD (DomainInt _ rs) = mapM collectLowerBounds rs - collectLowerBoundsD _ = userErr1 ("Expected an integer domain, but got:" <+> pretty domBody) - - bounds <- collectLowerBoundsD domBody - let lowerBound = make opMin (fromList bounds) - - -- for each element, we do element-lowerBound+1 - -- this makes sure the smallest element is 1 - -- hence we can use 0 as the except value! - let bodySkipped = [essence| toInt(&theGuard) * catchUndef(&body + (1 - &lowerBound), 0) |] - - return - ( "Inlining conditions, inside allDiff" - , return $ make opAllDiffExcept (Comprehension bodySkipped toKeep) 0 - ) - theRule _ = na "rule_InlineConditions_AllDiff" - - -rule_InlineConditions_MaxMin :: Rule -rule_InlineConditions_MaxMin = "aux-for-MaxMin" `namedRule` theRule where - theRule p = do - (nameQ, binOp, Comprehension body gensOrConds) <- - case (match opMax p, match opMin p) of - (Just res, _) -> return ("max", \ a b -> [essence| &a <= &b |], res ) - (_, Just res) -> return ("min", \ a b -> [essence| &a >= &b |], res ) - _ -> na "rule_InlineConditions_MaxMin" - let - (toInline, _toKeep) = mconcat - [ case goc of - Condition x | categoryOf x == CatDecision -> ([x],[]) - _ -> ([],[goc]) - | goc <- gensOrConds - ] - when (null toInline) $ na "rule_InlineConditions_MaxMin" - auxDomain <- domainOf body - return - ( "Creating auxiliary variable for a" <+> nameQ - , do - (auxName, aux) <- auxiliaryVar - let auxDefinedLHS = make opSum (Comprehension 1 gensOrConds) - let auxDefined = [essence| &auxDefinedLHS > 0 |] - let auxUndefined = [essence| &auxDefinedLHS = 0 |] - let aux' = WithLocals aux (DefinednessConstraints [auxDefined]) - return $ WithLocals aux' - (AuxiliaryVars - [ Declaration (FindOrGiven LocalFind auxName auxDomain) - , SuchThat - [ make opAnd $ Comprehension - (binOp body aux) - gensOrConds - - -- either one of the members of this comprehension, or dontCare - -- if it is indeed dontCare, care should be taken to make sure it isn't used as a normal value - , make opAnd $ fromList - [ make opImply auxDefined - (make opOr $ Comprehension - [essence| &body = &aux |] - gensOrConds) - , make opImply auxUndefined (make opDontCare aux) - ] - ] - ]) - ) - - -rule_AttributeToConstraint :: Rule -rule_AttributeToConstraint = "attribute-to-constraint" `namedRule` theRule where - theRule (Op (MkOpAttributeAsConstraint (OpAttributeAsConstraint thing attr mval))) = do - dom <- domainOf thing - let conv = mkAttributeToConstraint dom attr mval thing - return - ( "Converting an attribute to a constraint" - , bugFailT "rule_AttributeToConstraint" conv - ) - theRule _ = na "rule_AttributeToConstraint" - - -rule_FullEvaluate :: Rule -rule_FullEvaluate = "full-evaluate" `namedRule` theRule where - theRule Constant{} = na "rule_FullEvaluate" - theRule Domain{} = na "rule_FullEvaluate" - theRule p = do - constant <- instantiateExpression [] p - unless (null [() | ConstantUndefined{} <- universe constant]) $ - na "rule_PartialEvaluate, undefined" - return - ( "Full evaluator" - , return $ Constant constant - ) - - -rule_PartialEvaluate :: Rule -rule_PartialEvaluate = "partial-evaluate" `namedRuleZ` theRule where - -- if a variable only has a single value in its domain, replace it with the value - theRule z (Reference _ (Just (DeclHasRepr _ _ (singletonDomainInt -> Just val)))) = - case hole <$> Zipper.up z of - Just (Op (MkOpTrue _)) -> na "rule_PartialEvaluate, inside a true(ref)" - _ -> return ( "Partial evaluator" - , return val - ) - theRule _ (Op op) - | Just (x, y) <- case op of - MkOpLeq (OpLeq x y) -> Just (x,y) - MkOpGeq (OpGeq x y) -> Just (x,y) - MkOpEq (OpEq x y) -> Just (x,y) - _ -> Nothing - , Reference nmX _ <- x - , Reference nmY _ <- y - , nmX == nmY - , categoryOf x <= CatQuantified - , categoryOf y <= CatQuantified - = return - ( "Parameter = parameter (or quantified)" - , return (fromBool True) - ) - theRule _ (Op x) = do - x' <- simplifyOp x - when (Op x == x') $ bug $ vcat - [ "rule_PartialEvaluate, simplifier returns the input unchanged." - , "input:" <+> vcat [ pretty (Op x) - , pretty (show (Op x)) - ] - ] - return - ( "Partial evaluator" - , return x' - ) - theRule _ _ = na "rule_PartialEvaluate" - - --- | shifting quantifiers inwards, if they operate on a row of a 2d matrix, --- make them operate on the rows directly then index -rule_QuantifierShift :: Rule -rule_QuantifierShift = "quantifier-shift" `namedRule` theRule where - theRule p = do - (_, mkQuan, inner) <- match opReducer p - (matrix, indexer) <- match opIndexing inner - (TypeMatrix _ ty, index, elems) <- match matrixLiteral matrix - case ty of - TypeMatrix{} -> return () - TypeList{} -> return () - _ -> na "rule_QuantifierShift" - return - ( "Shifting quantifier inwards" - , return $ make opIndexing - (make matrixLiteral - ty - index - (map mkQuan elems)) - indexer - ) - - --- | shifting quantifiers inwards, if they operate on a flattened multi-dim matrix. -rule_QuantifierShift2 :: Rule -rule_QuantifierShift2 = "quantifier-shift2" `namedRule` theRule where - theRule p = do - (_, mkQuan, inner) <- match opReducer p - matrix <- match opFlatten inner - (TypeMatrix _ ty, index, elems) <- match matrixLiteral matrix - case ty of - TypeMatrix{} -> return () -- the matrix literal should contain further matrix/list stuff. - TypeList{} -> return () - _ -> na "rule_QuantifierShift2" - let flattenIfNeeded = if matrixNumDims ty > 1 - then make opFlatten - else id - return - ( "Shifting quantifier inwards" - , return $ mkQuan - (make matrixLiteral - ty - index - (map (mkQuan . flattenIfNeeded) elems)) - ) - - --- | shifting quantifiers inwards, if they operate on a concatenated multi-dim matrix. -rule_QuantifierShift3 :: Rule -rule_QuantifierShift3 = "quantifier-shift3" `namedRule` theRule where - theRule p = do - (_, mkQuan, inner) <- match opReducer p - matrix <- match opConcatenate inner - (TypeMatrix _ ty, index, elems) <- match matrixLiteral matrix - return - ( "Shifting quantifier inwards" - , return $ mkQuan - (make matrixLiteral - ty - index - (map mkQuan elems)) - ) - - -rule_Comprehension_Simplify :: Rule -rule_Comprehension_Simplify = "comprehension-simplify" `namedRule` theRule where - theRule (Comprehension x gocs) - | let isTrueCondition (Condition (Constant (ConstantBool True))) = True - isTrueCondition _ = False - , let gocs' = filter (not . isTrueCondition) gocs - , length gocs' < length gocs - = return - ( "Removing true conditions" - , return $ Comprehension x gocs' - ) - theRule _ = na "rule_Comprehension_Simplify" - - -rule_Xor_To_Sum :: Rule -rule_Xor_To_Sum = "xor-to-sum" `namedRule` theRule where - theRule [essence| xor(&arg) |] = - case arg of - Comprehension body goc -> do - let argOut = Comprehension [essence| toInt(&body) |] goc - return - ( "xor to sum" - , return [essence| 1 = sum(&argOut) |] - ) - AbstractLiteral (AbsLitMatrix dom elems) -> do - let argOut = AbstractLiteral $ AbsLitMatrix dom - [ [essence| toInt(&el) |] | el <- elems ] - return - ( "xor to sum" - , return [essence| 1 = sum(&argOut) |] - ) - _ -> do - (iPat, i) <- quantifiedVar - return - ( "xor to sum" - , return [essence| 1 = sum([ toInt(&i) | &iPat <- &arg ]) |] - ) - theRule _ = na "rule_Xor_To_Sum" diff --git a/src/Conjure/UI/TranslateParameter.hs.orig b/src/Conjure/UI/TranslateParameter.hs.orig deleted file mode 100644 index 24d79f0104..0000000000 --- a/src/Conjure/UI/TranslateParameter.hs.orig +++ /dev/null @@ -1,183 +0,0 @@ -module Conjure.UI.TranslateParameter ( translateParameter ) where - --- conjure -import Conjure.Prelude -import Conjure.Bug -import Conjure.UserError -import Conjure.Language.Definition -import Conjure.Language.Domain -import Conjure.Language.Constant -import Conjure.Language.Type -import Conjure.Language.TypeOf ( typeOf ) -import Conjure.Language.Pretty -import Conjure.Language.Instantiate -import Conjure.Process.Enums ( removeEnumsFromParam ) -import Conjure.Process.FiniteGivens ( finiteGivensParam ) -import Conjure.Process.Enumerate ( EnumerateDomain ) -import Conjure.Representations ( downC ) - - -translateParameter - :: ( MonadFail m - , MonadLog m - , NameGen m - , EnumerateDomain m - ) - => Model -- eprime model - -> Model -- essence param - -> m Model -- eprime param - -translateParameter eprimeModel0 essenceParam0 = do - logDebug $ "[eprimeModel 0]" <+> pretty essenceParam0 - logDebug $ "[essenceParam 0]" <+> pretty essenceParam0 - (eprimeModel, essenceParam1) <- removeEnumsFromParam eprimeModel0 essenceParam0 - logDebug $ "[eprimeModel 1]" <+> pretty eprimeModel - logDebug $ "[essenceParam 1]" <+> pretty essenceParam1 - (essenceParam, generatedLettingNames) <- finiteGivensParam eprimeModel essenceParam1 - logDebug $ "[essenceParam 2]" <+> pretty essenceParam - - let essenceLettings = extractLettings essenceParam - let essenceGivenNames = eprimeModel |> mInfo |> miGivens - let essenceGivens = eprimeModel |> mInfo |> miRepresentations - |> filter (\ (n,_) -> n `elem` essenceGivenNames ) - - logDebug $ "[essenceLettings ]" <+> vcat [ pretty n <> ":" <+> pretty x | (n,x) <- essenceLettings ] - logDebug $ "[essenceGivenNames]" <+> vcat (map pretty essenceGivenNames) - logDebug $ "[essenceGivens ]" <+> vcat [ pretty n <> ":" <+> pretty x | (n,x) <- essenceGivens ] - - -- some sanity checks here - -- TODO: check if for every given there is a letting (there can be more) - -- TODO: check if the same letting has multiple values for it - let missingLettings = - (essenceGivenNames ++ generatedLettingNames) \\ - map fst essenceLettings - unless (null missingLettings) $ - userErr1 $ "Missing values for parameters:" <++> prettyList id "," missingLettings - - let extraLettings = - map fst essenceLettings \\ - (essenceGivenNames ++ generatedLettingNames) - unless (null extraLettings) $ - userErr1 $ "Too many letting statements in the parameter file:" <++> prettyList id "," extraLettings - - - let eprimeLettingsForEnums = - [ (nm, fromInt (genericLength vals)) - | nm1 <- eprimeModel |> mInfo |> miEnumGivens - , Declaration (LettingDomainDefnEnum nm2 vals) <- essenceParam0 |> mStatements - , nm1 == nm2 - , let nm = nm1 `mappend` "_EnumSize" - ] - - let allLettings = (eprimeModel |> mInfo |> miLettings) - ++ essenceLettings - ++ map (second Constant) eprimeLettingsForEnums - - essenceLettings' <- forM essenceLettings $ \ (name, val) -> do - constant <- instantiateExpression allLettings val - return (name, constant) - logDebug $ "[essenceLettings' ]" <+> vcat [ pretty n <> ":" <+> pretty x | (n,x) <- essenceLettings' ] - - essenceGivens' <- forM essenceGivens $ \ (name, dom) -> do - constant <- instantiateDomain allLettings dom - return (name, constant) - logDebug $ "[essenceGivens' ]" <+> vcat [ pretty n <> ":" <+> pretty x | (n,x) <- essenceGivens' ] - - essenceGivensAndLettings <- sequence - [ case lookup n essenceLettings' of - Nothing -> - if n `elem` map fst eprimeLettingsForEnums - then return Nothing - else userErr1 $ vcat - [ "No value for parameter:" <+> pretty n - , "With domain:" <+> pretty d - ] - Just v -> - if emptyCollection v - then do - (c, cTyMaybe) <- case v of - TypedConstant c cTy - | elem TypeAny (universe cTy) -- we may be able to do better! - -> return (c, Just cTy) - | otherwise - -> return (v, Nothing) -- already sufficiently typed - _ -> return (v, Just TypeAny) -- empty collection, unknown type - case cTyMaybe of - Nothing -> return $ Just (n, d, v) - Just cTy1 -> do - -- calculate the type of the domain, unify with the type we already have - cTy2 <- typeOf d - let cTy = mostDefined [cTy1, cTy2] - if elem TypeAny (universe cTy) - then userErr1 $ vcat - [ "Cannot fully determine the type of parameter" <+> pretty n - , "Domain:" <+> pretty d - , "Value :" <+> pretty v - ] - else return $ Just (n, d, TypedConstant c cTy) - else return $ Just (n, d, v) -<<<<<<< HEAD - | (n, d) <- essenceGivens' ++ [ (n, DomainInt Nothing []) | n <- generatedLettingNames ] -||||||| merged common ancestors - | (n, d) <- essenceGivens' ++ [ (n, DomainInt []) | n <- generatedLettingNames ] -======= - | (n, d) <- essenceGivens' ++ [ (n, DomainInt NoTag []) | n <- generatedLettingNames ] ->>>>>>> taggedints - ] - logDebug $ "[essenceGivensAndLettings ]" <+> vcat [ vcat [ "name :" <+> pretty n - , "domain :" <+> pretty d - , "constant:" <+> pretty c - ] - | Just (n,d,c) <- essenceGivensAndLettings - ] - - let f (Reference nm Nothing) = - case [ val | (nm2, val) <- eprimeLettingsForEnums, nm == nm2 ] of - [] -> bug ("translateParameter: No value for" <+> pretty nm) - [val] -> Constant val - _ -> bug ("translateParameter: Multiple values for" <+> pretty nm) - f p = p - - let - essenceGivensAndLettings' :: [(Name, Domain HasRepresentation Constant, Constant)] - essenceGivensAndLettings' = transformBi f (catMaybes essenceGivensAndLettings) - - logDebug $ "[essenceGivensAndLettings']" <+> vcat [ vcat [ "name :" <+> pretty n - , "domain :" <+> pretty d - , "constant:" <+> pretty c - ] - | (n,d,c) <- essenceGivensAndLettings' - ] - - errs <- execWriterT $ forM_ essenceGivensAndLettings' $ \ (nm, dom, val) -> - case validateConstantForDomain nm val dom of - Left err -> tell [err] - Right () -> return () - unless (null errs) (userErr errs) - - let - decorateWithType p@(_, _, TypedConstant{}) = return p - decorateWithType (name, domain, constant) | emptyCollection constant = do - ty <- typeOf domain - return (name, domain, TypedConstant constant ty) - decorateWithType p = return p - - eprimeLettings - :: [(Name, Domain HasRepresentation Constant, Constant)] - <- failToUserError $ concatMapM downC essenceGivensAndLettings' >>= mapM decorateWithType - logDebug $ "[eprimeLettings ]" <+> vcat [ vcat [ "name :" <+> pretty n - , "domain :" <+> pretty d - , "constant:" <+> pretty c - ] - | (n,d,c) <- eprimeLettings - ] - - return $ languageEprime def - { mStatements = - [ Declaration (Letting n (Constant x)) - | (n, _, x) <- eprimeLettings - ] ++ - [ Declaration (Letting n (Constant x)) - | (n, x) <- eprimeLettingsForEnums - ] - } diff --git a/src/Conjure/UI/TypeCheck.hs.orig b/src/Conjure/UI/TypeCheck.hs.orig deleted file mode 100644 index 736944f850..0000000000 --- a/src/Conjure/UI/TypeCheck.hs.orig +++ /dev/null @@ -1,180 +0,0 @@ -{-# LANGUAGE TupleSections #-} - -module Conjure.UI.TypeCheck ( typeCheckModel_StandAlone, typeCheckModel ) where - --- conjure -import Conjure.Prelude -import Conjure.UserError -import Conjure.Language.Definition -import Conjure.Language.Domain -import Conjure.Language.Type -import Conjure.Language.TypeOf -import Conjure.Language.CategoryOf ( categoryChecking ) -import Conjure.Language.Pretty -import Conjure.Language.Lenses -import Conjure.Process.Enums ( removeEnumsFromModel ) -import Conjure.Process.Unnameds ( removeUnnamedsFromModel ) -import Conjure.Language.NameResolution ( resolveNames ) -import Conjure.Process.Sanity ( sanityChecks ) - - - -typeCheckModel_StandAlone - :: ( MonadFail m - , MonadUserError m - , MonadLog m - , NameGen m - ) - => Model - -> m Model -typeCheckModel_StandAlone model0 = do - -- for better error messages, type-check and category-check before sanity-checking. - -- sanity checking will modify the model. - -- then, type-check once more just in case the newly generated - -- stuff is broken. - model1 <- return model0 >>= logDebugId "[input]" - >>= removeUnnamedsFromModel >>= logDebugId "[removeUnnamedsFromModel]" - >>= removeEnumsFromModel >>= logDebugId "[removeEnumsFromModel]" - >>= resolveNames >>= logDebugId "[resolveNames]" - >>= typeCheckModel >>= logDebugId "[typeCheckModel]" - >>= categoryChecking >>= logDebugId "[categoryChecking]" - >>= sanityChecks >>= logDebugId "[sanityChecks]" - >>= typeCheckModel >>= logDebugId "[typeCheckModel]" - return model1 - - -typeCheckModel - :: ( MonadFail m - , MonadUserError m - ) - => Model - -> m Model -typeCheckModel model1 = do - let model2 = fixRelationProj model1 - (statements3, errs) <- runWriterT $ forM (mStatements model2) $ \ st -> - case st of - Declaration decl -> do - case decl of - FindOrGiven _ _ domain -> do - mty <- runExceptT $ typeOf domain - case mty of - Right _ -> return () - Left err -> tell $ return $ vcat - [ "In a declaration statement:" <++> pretty st - , "Error:" <++> pretty err - ] - Letting _ x -> do - mty <- runExceptT $ typeOf x - case mty of - Right _ -> return () - Left err -> tell $ return $ vcat - [ "In a letting statement:" <++> pretty st - , "Error:" <++> pretty err - ] - GivenDomainDefnEnum{} -> return () - LettingDomainDefnEnum{} -> return () - LettingDomainDefnUnnamed _ x -> do - mty <- runExceptT $ typeOf x - case mty of - Right TypeInt{} -> return () - Left err -> tell $ return $ vcat - [ "In the declaration of an unnamed type:" <++> pretty st - , "Error:" <++> pretty err - ] - Right ty -> tell $ return $ vcat - [ "In the declaration of an unnamed type:" <++> pretty st - , "Expected type `int`, but got:" <++> pretty ty - ] - return st - SearchOrder xs -> do - forM_ xs $ \case - BranchingOn{} -> return () -- TODO: check if the name is defined - Cut x -> do - mty <- runExceptT $ typeOf x - case mty of - Right TypeBool{} -> return () - Left err -> tell $ return $ vcat - [ "In a 'branching on' statement:" <++> pretty x - , "Error:" <++> pretty err - ] - Right ty -> tell $ return $ vcat - [ "In a 'branching on' statement:" <++> pretty x - , "Expected type `bool`, but got:" <++> pretty ty - ] - return st - SearchHeuristic{} -> return st - Where xs -> do - xs' <- forM xs $ \ x -> do - mty <- runExceptT $ typeOf x - case mty of - Right TypeBool{} -> return x - Right (TypeList TypeBool) -> return (make opAnd x) - Right (TypeMatrix _ TypeBool) -> return (make opAnd x) - Left err -> do - tell $ return $ vcat - [ "In a 'where' statement:" <++> pretty x - , "Error:" <++> pretty err - ] - return x - Right ty -> do - tell $ return $ vcat - [ "In a 'where' statement:" <++> pretty x - , "Expected type `bool`, but got:" <++> pretty ty - ] - return x - return (Where xs') - Objective _ x -> do - mty <- runExceptT $ typeOf x - case mty of - Right TypeInt{} -> return () - Left err -> tell $ return $ vcat - [ "In the objective:" <++> pretty st - , "Error:" <++> pretty err - ] - Right ty -> tell $ return $ vcat - [ "In the objective:" <++> pretty st - , "Expected type `int`, but got:" <++> pretty ty - ] - return st - SuchThat xs -> do - xs' <- forM xs $ \ x -> do - mty <- runExceptT $ typeOf x - case mty of - Right TypeBool{} -> return x - Right (TypeList TypeBool) -> return (make opAnd x) - Right (TypeMatrix _ TypeBool) -> return (make opAnd x) - Left err -> do - tell $ return $ vcat - [ "In a 'such that' statement:" <++> pretty x - , "Error:" <++> pretty err - ] - return x - Right ty -> do - tell $ return $ vcat - [ "In a 'such that' statement:" <++> pretty x - , "Expected type `bool`, but got:" <++> pretty ty - ] - return x - return (SuchThat xs') - unless (null errs) (userErr errs) - - -- now that everything knows its type, we can recover - -- DomainInt [RangeSingle x] from DomainIntE x, if x has type int - let - domainIntERecover :: forall m . MonadFail m => Domain () Expression -> m (Domain () Expression) - domainIntERecover d@(DomainIntE name x) = do - ty <- typeOf x - return $ case ty of -<<<<<<< HEAD - TypeInt _ -> DomainInt name [RangeSingle x] -||||||| merged common ancestors - TypeInt -> DomainInt [RangeSingle x] -======= - TypeInt t -> DomainInt t [RangeSingle x] ->>>>>>> taggedints - _ -> d - domainIntERecover d = return d - statements4 <- transformBiM domainIntERecover statements3 - - return model2 { mStatements = statements4 } - diff --git a/src/Conjure/UI/ValidateSolution.hs.orig b/src/Conjure/UI/ValidateSolution.hs.orig deleted file mode 100644 index edcbef0603..0000000000 --- a/src/Conjure/UI/ValidateSolution.hs.orig +++ /dev/null @@ -1,199 +0,0 @@ -module Conjure.UI.ValidateSolution ( validateSolution ) where - --- conjure -import Conjure.Bug -import Conjure.Prelude -import Conjure.UserError -import Conjure.Language.Definition -import Conjure.Language.Domain -import Conjure.Language.Constant -import Conjure.Language.Pretty -import Conjure.Language.Type -import Conjure.Language.TypeOf -import Conjure.Language.Instantiate -import Conjure.Process.Enumerate ( EnumerateDomain ) - - -validateSolution - :: ( MonadFail m - , EnumerateDomain m - ) - => Model -- essence model - -> Model -- essence param - -> Model -- essence solution - -> m () -validateSolution essenceModel essenceParam essenceSolution = flip evalStateT [] $ - forM_ (mStatements essenceModel) $ \ st -> do - mapM_ introduceRecordFields (universeBi st :: [Domain () Expression]) - case st of - Declaration (FindOrGiven Given nm dom) -> - case [ val | Declaration (Letting nm2 val) <- mStatements essenceParam, nm == nm2 ] of - [val] -> do - valC <- gets id >>= flip instantiateExpression val - valC_typed <- case valC of - TypedConstant c tyc -> do - ty <- typeOf dom - return $ TypedConstant c (mostDefined [ty, tyc]) - _ -> return valC - DomainInConstant domC <- gets id >>= flip instantiateExpression (Domain dom) - either userErr1 return (validateConstantForDomain nm valC domC) - modify ((nm, Constant valC_typed) :) - [] -> userErr1 $ vcat [ "No value for" <+> pretty nm <+> "in the parameter file." - , "Its domain:" <++> pretty dom - ] - vals -> userErr1 $ vcat [ "Multiple values for" <+> pretty nm <+> "in the parameter file." - , "Its domain:" <++> pretty dom - , "Values:" <++> vcat (map pretty vals) - ] - Declaration (FindOrGiven Find nm dom) -> - case [ val | Declaration (Letting nm2 val) <- mStatements essenceSolution, nm == nm2 ] of - [val] -> do - valC <- gets id >>= flip instantiateExpression val - valC_typed <- case valC of - TypedConstant c tyc -> do - ty <- typeOf dom - return $ TypedConstant c (mostDefined [ty, tyc]) - _ -> return valC - DomainInConstant domC <- gets id >>= flip instantiateExpression (Domain dom) - either userErr1 return (validateConstantForDomain nm valC domC) - modify ((nm, Constant valC_typed) :) - [] -> userErr1 $ vcat [ "No value for" <+> pretty nm <+> "in the solution file." - , "Its domain:" <++> pretty dom - ] - vals -> userErr1 $ vcat [ "Multiple values for" <+> pretty nm <+> "in the solution file." - , "Its domain:" <++> pretty dom - , "Values:" <++> vcat (map pretty vals) - ] - Declaration (FindOrGiven Quantified _ _) -> - userErr1 $ vcat - [ "A quantified declaration at the top level." - , "This should never happen." - , "Statement:" <+> pretty st - ] - Declaration (FindOrGiven LocalFind _ _) -> - userErr1 $ vcat - [ "A local decision variable at the top level." - , "This should never happen." - , "Statement:" <+> pretty st - ] - Declaration (FindOrGiven CutFind _ _) -> - userErr1 $ vcat - [ "A 'cut' decision variable at the top level." - , "This should never happen." - , "Statement:" <+> pretty st - ] - Declaration (Letting nm val) -> modify ((nm, val) :) - Declaration (GivenDomainDefnEnum nm@(Name nmText)) -> - case [ val | Declaration (LettingDomainDefnEnum nm2 val) <- mStatements essenceParam, nm == nm2 ] of - [val] -> do -<<<<<<< HEAD - let domain = mkDomainIntB 1 (fromInt (genericLength val)) - let values = [ (n, Constant (ConstantInt (Just n) i)) -||||||| merged common ancestors - let domain = mkDomainIntB 1 (fromInt (genericLength val)) - let values = [ (n, Constant (ConstantInt i)) -======= - let domain = mkDomainIntBTagged (TagEnum nmText) 1 (fromInt (genericLength val)) - let values = [ (n, Constant (ConstantInt (TagEnum nmText) i)) ->>>>>>> taggedints - | (n, i) <- zip val allNats - ] - modify (((nm, Domain domain) : values) ++) - [] -> userErr1 $ vcat [ "No value for enum domain" <+> pretty nm <+> "in the parameter file." - ] - vals -> userErr1 $ vcat [ "Multiple values for enum domain" <+> pretty nm <+> "in the parameter file." - , "Values:" <++> vcat (map (prettyList prBraces ",") vals) - ] -<<<<<<< HEAD - Declaration (LettingDomainDefnEnum nm val) -> do - let domain = mkDomainIntB 1 (fromInt (genericLength val)) - let values = [ (n, Constant (ConstantInt (Just n) i)) -||||||| merged common ancestors - Declaration (LettingDomainDefnEnum nm val) -> do - let domain = mkDomainIntB 1 (fromInt (genericLength val)) - let values = [ (n, Constant (ConstantInt i)) -======= - Declaration GivenDomainDefnEnum{} -> - bug "validateSolution GivenDomainDefnEnum, some other type of Name" - Declaration (LettingDomainDefnEnum nm@(Name nmText) val) -> do - let domain = mkDomainIntBTagged (TagEnum nmText) 1 (fromInt (genericLength val)) - let values = [ (n, Constant (ConstantInt (TagEnum nmText) i)) ->>>>>>> taggedints - | (n, i) <- zip val allNats - ] - modify (((nm, Domain domain) : values) ++) - Declaration (LettingDomainDefnEnum{}) -> - bug "validateSolution LettingDomainDefnEnum, some other type of Name" - Declaration (LettingDomainDefnUnnamed nm@(Name nmText) _) -> - case [ nms | Declaration (LettingDomainDefnEnum nm2 nms) <- mStatements essenceSolution , nm == nm2 ] of - [nms] -> do -<<<<<<< HEAD - let domain = mkDomainIntB 1 (fromInt (genericLength nms)) - let values = [ (n, Constant (ConstantInt (Just n) i)) -||||||| merged common ancestors - let domain = mkDomainIntB 1 (fromInt (genericLength nms)) - let values = [ (n, Constant (ConstantInt i)) -======= - let domain = mkDomainIntBTagged (TagUnnamed nmText) 1 (fromInt (genericLength nms)) - let values = [ (n, Constant (ConstantInt (TagUnnamed nmText) i)) ->>>>>>> taggedints - | (i,n) <- zip allNats nms - ] - modify (((nm, Domain domain) : values) ++) - [] -> userErr1 $ vcat [ "No value for unnamed domain" <+> pretty nm <+> "in the solution file." - ] - vals -> userErr1 $ vcat [ "Multiple values for unnamed domain" <+> pretty nm <+> "in the solution file." - , "Values:" <++> vcat (map (prettyList prBraces ",") vals) - ] - Declaration (LettingDomainDefnUnnamed{}) -> - bug "validateSolution LettingDomainDefnUnnamed, some other type of Name" - SearchOrder{} -> return () - SearchHeuristic{} -> return () - Where xs -> do - vals <- gets id - forM_ xs $ \ x -> do - constant <- instantiateExpression vals x - case constant of - ConstantBool True -> return () - _ -> userErr1 $ "Invalid." <++> vcat [ "Statement evaluates to:" <+> pretty constant - , "Original statement was:" <+> pretty x - , "Relevant values:" <++> vcat - [ "letting" <+> pretty nm <+> "be" <+> pretty val - | (nm, val) <- vals - , nm `elem` (universeBi x :: [Name]) - ] - ] - Objective{} -> return () - SuchThat xs -> do - vals <- gets id - forM_ xs $ \ x -> do - constant <- instantiateExpression vals x - case constant of - ConstantBool True -> return () - _ -> userErr1 $ "Invalid." <++> vcat [ "Statement evaluates to:" <+> pretty constant - , "Original statement was:" <+> pretty x - , "Relevant values:" <++> vcat - [ "letting" <+> pretty nm <+> "be" <+> pretty val - | (nm, val) <- vals - , nm `elem` (universeBi x :: [Name]) - ] - ] - - -introduceRecordFields - :: ( MonadFail m - , MonadState [(Name, Expression)] m - , Pretty r - , Pretty x - , TypeOf x - ) - => Domain r x -> m () -introduceRecordFields (DomainRecord inners) = - forM_ inners $ \ (n, d) -> do - t <- typeOf d - modify ((n, Constant (ConstantField n t)) :) -introduceRecordFields (DomainVariant inners) = - forM_ inners $ \ (n, d) -> do - t <- typeOf d - modify ((n, Constant (ConstantField n t)) :) -introduceRecordFields _ = return () diff --git a/src/test/Conjure/Language/DomainSizeTest.hs.orig b/src/test/Conjure/Language/DomainSizeTest.hs.orig deleted file mode 100644 index a970bdb0e4..0000000000 --- a/src/test/Conjure/Language/DomainSizeTest.hs.orig +++ /dev/null @@ -1,82 +0,0 @@ -module Conjure.Language.DomainSizeTest ( tests ) where - --- conjure -import Conjure.Prelude -import Conjure.Language.Constant -import Conjure.Language.Type -import Conjure.Language.Domain -import Conjure.Language.DomainSizeOf ( domainSizeOf ) - --- tasty -import Test.Tasty ( TestTree, testGroup ) -import Test.Tasty.HUnit ( testCase, (@?=) ) - - -domainSizeConstant :: MonadFail m => Domain () Constant -> m Integer -domainSizeConstant = domainSizeOf - -tests :: TestTree -tests = testGroup "domainSize" - [ testCase "domain size of bool is 2" $ - domainSizeConstant DomainBool @?= Right 2 - , testCase "domain size of int(1..100)" $ -<<<<<<< HEAD - domainSizeConstant (DomainInt Nothing [RangeBounded (ConstantInt Nothing 1) (ConstantInt Nothing 100)]) @?= Right 100 -||||||| merged common ancestors - domainSizeConstant (DomainInt [RangeBounded (ConstantInt 1) (ConstantInt 100)]) @?= Right 100 -======= - domainSizeConstant (DomainInt NoTag [RangeBounded ((ConstantInt NoTag) 1) ((ConstantInt NoTag) 100)]) @?= Right 100 ->>>>>>> taggedints - , testCase "domain size of int(1,...,100)" $ -<<<<<<< HEAD - domainSizeConstant (DomainInt Nothing (map (RangeSingle . ConstantInt Nothing) [1 .. 100])) @?= Right 100 -||||||| merged common ancestors - domainSizeConstant (DomainInt (map (RangeSingle . ConstantInt) [1 .. 100])) @?= Right 100 -======= - domainSizeConstant (DomainInt NoTag (map (RangeSingle . (ConstantInt NoTag)) [1 .. 100])) @?= Right 100 ->>>>>>> taggedints - , testCase "domain size of int(13)" $ -<<<<<<< HEAD - domainSizeConstant (DomainInt Nothing [RangeSingle (ConstantInt Nothing 13)]) @?= Right 1 -||||||| merged common ancestors - domainSizeConstant (DomainInt [RangeSingle (ConstantInt 13)]) @?= Right 1 -======= - domainSizeConstant (DomainInt NoTag [RangeSingle ((ConstantInt NoTag) 13)]) @?= Right 1 ->>>>>>> taggedints - , testCase "domain size of int(13,1..100)" $ -<<<<<<< HEAD - domainSizeConstant (DomainInt Nothing [ RangeSingle (ConstantInt Nothing 13) - , RangeBounded (ConstantInt Nothing 1) (ConstantInt Nothing 100) -||||||| merged common ancestors - domainSizeConstant (DomainInt [ RangeSingle (ConstantInt 13) - , RangeBounded (ConstantInt 1) (ConstantInt 100) -======= - domainSizeConstant (DomainInt NoTag [ RangeSingle ((ConstantInt NoTag) 13) - , RangeBounded ((ConstantInt NoTag) 1) ((ConstantInt NoTag) 100) ->>>>>>> taggedints - ]) @?= Right 100 - , testCase "domain size of int(113,1..100)" $ -<<<<<<< HEAD - domainSizeConstant (DomainInt Nothing [ RangeSingle (ConstantInt Nothing 113) - , RangeBounded (ConstantInt Nothing 1) (ConstantInt Nothing 100) -||||||| merged common ancestors - domainSizeConstant (DomainInt [ RangeSingle (ConstantInt 113) - , RangeBounded (ConstantInt 1) (ConstantInt 100) -======= - domainSizeConstant (DomainInt NoTag [ RangeSingle ((ConstantInt NoTag) 113) - , RangeBounded ((ConstantInt NoTag) 1) ((ConstantInt NoTag) 100) ->>>>>>> taggedints - ]) @?= Right 101 - , testCase "domain size of set of bool #1" $ - domainSizeConstant (DomainSet () (SetAttr SizeAttr_None) DomainBool) @?= Right 4 - , testCase "domain size of set of bool #2" $ - let setOfSize n = DomainSet () (SetAttr (SizeAttr_Size n)) -<<<<<<< HEAD - in domainSizeConstant (setOfSize (ConstantInt Nothing 2) DomainBool) @?= Right 1 -||||||| merged common ancestors - in domainSizeConstant (setOfSize (ConstantInt 2) DomainBool) @?= Right 1 -======= - in domainSizeConstant (setOfSize ((ConstantInt NoTag) 2) DomainBool) @?= Right 1 ->>>>>>> taggedints - ] - diff --git a/src/test/Conjure/RepresentationsTest.hs.orig b/src/test/Conjure/RepresentationsTest.hs.orig deleted file mode 100644 index 017b95b310..0000000000 --- a/src/test/Conjure/RepresentationsTest.hs.orig +++ /dev/null @@ -1,2407 +0,0 @@ -{-# LANGUAGE FlexibleInstances #-} -{-# LANGUAGE RankNTypes #-} - -module Conjure.RepresentationsTest ( tests ) where - --- conjure -import Conjure.Prelude -import Conjure.Language.Definition -import Conjure.Language.Type -import Conjure.Language.Domain -import Conjure.Language.Pretty -import Conjure.Process.Enumerate ( EnumerateDomainNoIO(..) ) -import Conjure.Representations ( downC, up, downC1, up1 ) - --- tasty -import Test.Tasty -import Test.Tasty.HUnit ( Assertion, testCase, assertFailure, (@?=) ) --- import Test.Tasty.QuickCheck as QC --- import Test.Tasty.SmallCheck as SC - - -tests :: TestTree -tests = testGroup "representations" - - [ testCase "bool #1" $ - let - highDomain = DomainBool - highConstant = ConstantBool False - low = [("x", highDomain, highConstant)] - in testCases "x" highDomain highConstant (const Nothing) low low - - , testCase "bool #2" $ - let - highDomain = DomainBool - highConstant = ConstantBool True - low = [("x", highDomain, highConstant)] - in testCases "x" highDomain highConstant (const Nothing) low low - - , testCase "int #1" $ - let - highDomain = intDomain 1 4 -<<<<<<< HEAD - highConstant = ConstantInt Nothing 3 -||||||| merged common ancestors - highConstant = ConstantInt 3 -======= - highConstant = (ConstantInt NoTag) 3 ->>>>>>> taggedints - low = [("x", highDomain, highConstant)] - in testCases "x" highDomain highConstant (const Nothing) low low - - , testCase "matrix of bool" $ - let - highDomain = DomainMatrix (intDomain 1 3) DomainBool - highConstant = ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantBool False, ConstantBool False, ConstantBool True] - low = [("x", highDomain, highConstant)] - in testCases "x" highDomain highConstant (const Nothing) low low - - , testCase "matrix of int" $ - let - highDomain = DomainMatrix (intDomain 1 3) (intDomain 1 5) -<<<<<<< HEAD - highConstant = ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantInt Nothing 2, ConstantInt Nothing 3, ConstantInt Nothing 5] -||||||| merged common ancestors - highConstant = ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantInt 2, ConstantInt 3, ConstantInt 5] -======= - highConstant = ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [(ConstantInt NoTag) 2, (ConstantInt NoTag) 3, (ConstantInt NoTag) 5] ->>>>>>> taggedints - low = [("x", highDomain, highConstant)] - in testCases "x" highDomain highConstant (const Nothing) low low - - , testCase "matrix 2d of bool" $ - let - highDomain = - DomainMatrix (intDomain 1 3) (DomainMatrix (intDomain 1 2) DomainBool) - highConstant = - ConstantAbstract $ AbsLitMatrix (intDomain 1 3) - [ ConstantAbstract $ AbsLitMatrix (intDomain 1 2) [ConstantBool False, ConstantBool True ] - , ConstantAbstract $ AbsLitMatrix (intDomain 1 2) [ConstantBool True , ConstantBool False] - , ConstantAbstract $ AbsLitMatrix (intDomain 1 2) [ConstantBool True , ConstantBool True ] - ] - low = [("x", highDomain, highConstant)] - in testCases "x" highDomain highConstant (const Nothing) low low - - , testCase "matrix 2d of int" $ - let - highDomain = - DomainMatrix (intDomain 1 3) (DomainMatrix (intDomain 1 2) (intDomain 0 9)) - highConstant = - ConstantAbstract $ AbsLitMatrix (intDomain 1 3) -<<<<<<< HEAD - [ ConstantAbstract $ AbsLitMatrix (intDomain 1 2) [ConstantInt Nothing 3, ConstantInt Nothing 7] - , ConstantAbstract $ AbsLitMatrix (intDomain 1 2) [ConstantInt Nothing 2, ConstantInt Nothing 8] - , ConstantAbstract $ AbsLitMatrix (intDomain 1 2) [ConstantInt Nothing 0, ConstantInt Nothing 1] -||||||| merged common ancestors - [ ConstantAbstract $ AbsLitMatrix (intDomain 1 2) [ConstantInt 3, ConstantInt 7] - , ConstantAbstract $ AbsLitMatrix (intDomain 1 2) [ConstantInt 2, ConstantInt 8] - , ConstantAbstract $ AbsLitMatrix (intDomain 1 2) [ConstantInt 0, ConstantInt 1] -======= - [ ConstantAbstract $ AbsLitMatrix (intDomain 1 2) [(ConstantInt NoTag) 3, (ConstantInt NoTag) 7] - , ConstantAbstract $ AbsLitMatrix (intDomain 1 2) [(ConstantInt NoTag) 2, (ConstantInt NoTag) 8] - , ConstantAbstract $ AbsLitMatrix (intDomain 1 2) [(ConstantInt NoTag) 0, (ConstantInt NoTag) 1] ->>>>>>> taggedints - ] - low = [("x", highDomain, highConstant)] - in testCases "x" highDomain highConstant (const Nothing) low low - - , testCase "(bool, int)" $ - let - highDomain = DomainTuple [DomainBool, intDomain 1 3] -<<<<<<< HEAD - highConstant = ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantInt Nothing 2] -||||||| merged common ancestors - highConstant = ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantInt 2] -======= - highConstant = ConstantAbstract $ AbsLitTuple [ConstantBool False, (ConstantInt NoTag) 2] ->>>>>>> taggedints - low = [ ( "x_1", DomainBool , ConstantBool False ) -<<<<<<< HEAD - , ( "x_2", intDomain 1 3, ConstantInt Nothing 2 ) -||||||| merged common ancestors - , ( "x_2", intDomain 1 3, ConstantInt 2 ) -======= - , ( "x_2", intDomain 1 3, (ConstantInt NoTag) 2 ) ->>>>>>> taggedints - ] - in testCases "x" highDomain highConstant Just low low - - , testCase "(bool, int, bool)" $ - let - highDomain = DomainTuple [DomainBool, intDomain 1 3, DomainBool] -<<<<<<< HEAD - highConstant = ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantInt Nothing 2, ConstantBool True] -||||||| merged common ancestors - highConstant = ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantInt 2, ConstantBool True] -======= - highConstant = ConstantAbstract $ AbsLitTuple [ConstantBool False, (ConstantInt NoTag) 2, ConstantBool True] ->>>>>>> taggedints - low = [ ( "x_1", DomainBool , ConstantBool False ) -<<<<<<< HEAD - , ( "x_2", intDomain 1 3, ConstantInt Nothing 2 ) -||||||| merged common ancestors - , ( "x_2", intDomain 1 3, ConstantInt 2 ) -======= - , ( "x_2", intDomain 1 3, (ConstantInt NoTag) 2 ) ->>>>>>> taggedints - , ( "x_3", DomainBool , ConstantBool True ) - ] - in testCases "x" highDomain highConstant Just low low - - , testCase "((bool, int), bool)" $ - let - highDomain = DomainTuple [DomainTuple [DomainBool, intDomain 1 3], DomainBool] -<<<<<<< HEAD - highConstant = ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantInt Nothing 2], ConstantBool True] - mid = [ ( "x_1", DomainTuple [DomainBool, intDomain 1 3], ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantInt Nothing 2] ) -||||||| merged common ancestors - highConstant = ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantInt 2], ConstantBool True] - mid = [ ( "x_1", DomainTuple [DomainBool, intDomain 1 3], ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantInt 2] ) -======= - highConstant = ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ConstantBool False, (ConstantInt NoTag) 2], ConstantBool True] - mid = [ ( "x_1", DomainTuple [DomainBool, intDomain 1 3], ConstantAbstract $ AbsLitTuple [ConstantBool False, (ConstantInt NoTag) 2] ) ->>>>>>> taggedints - , ( "x_2", DomainBool, ConstantBool True ) - ] - low = [ ( "x_1_1", DomainBool , ConstantBool False ) -<<<<<<< HEAD - , ( "x_1_2", intDomain 1 3, ConstantInt Nothing 2 ) -||||||| merged common ancestors - , ( "x_1_2", intDomain 1 3, ConstantInt 2 ) -======= - , ( "x_1_2", intDomain 1 3, (ConstantInt NoTag) 2 ) ->>>>>>> taggedints - , ( "x_2" , DomainBool , ConstantBool True ) - ] - in testCases "x" highDomain highConstant Just mid low - - , testCase "(bool, (int, bool))" $ - let - highDomain = DomainTuple [DomainBool, DomainTuple [intDomain 1 3, DomainBool]] -<<<<<<< HEAD - highConstant = ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantAbstract $ AbsLitTuple [ConstantInt Nothing 2, ConstantBool True]] -||||||| merged common ancestors - highConstant = ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantAbstract $ AbsLitTuple [ConstantInt 2, ConstantBool True]] -======= - highConstant = ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantAbstract $ AbsLitTuple [(ConstantInt NoTag) 2, ConstantBool True]] ->>>>>>> taggedints - mid = [ ( "x_1", DomainBool, ConstantBool False ) -<<<<<<< HEAD - , ( "x_2", DomainTuple [intDomain 1 3, DomainBool], ConstantAbstract $ AbsLitTuple [ConstantInt Nothing 2, ConstantBool True] ) -||||||| merged common ancestors - , ( "x_2", DomainTuple [intDomain 1 3, DomainBool], ConstantAbstract $ AbsLitTuple [ConstantInt 2, ConstantBool True] ) -======= - , ( "x_2", DomainTuple [intDomain 1 3, DomainBool], ConstantAbstract $ AbsLitTuple [(ConstantInt NoTag) 2, ConstantBool True] ) ->>>>>>> taggedints - ] - low = [ ( "x_1" , DomainBool , ConstantBool False ) -<<<<<<< HEAD - , ( "x_2_1", intDomain 1 3, ConstantInt Nothing 2 ) -||||||| merged common ancestors - , ( "x_2_1", intDomain 1 3, ConstantInt 2 ) -======= - , ( "x_2_1", intDomain 1 3, (ConstantInt NoTag) 2 ) ->>>>>>> taggedints - , ( "x_2_2", DomainBool , ConstantBool True ) - ] - in testCases "x" highDomain highConstant Just mid low - - , testCase "(bool, int, bool, int)" $ - let - highDomain = DomainTuple [DomainBool, intDomain 1 3, DomainBool, intDomain 2 5] -<<<<<<< HEAD - highConstant = ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantInt Nothing 2, ConstantBool True, ConstantInt Nothing 4] -||||||| merged common ancestors - highConstant = ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantInt 2, ConstantBool True, ConstantInt 4] -======= - highConstant = ConstantAbstract $ AbsLitTuple [ConstantBool False, (ConstantInt NoTag) 2, ConstantBool True, (ConstantInt NoTag) 4] ->>>>>>> taggedints - low = [ ( "x_1", DomainBool , ConstantBool False ) -<<<<<<< HEAD - , ( "x_2", intDomain 1 3, ConstantInt Nothing 2 ) -||||||| merged common ancestors - , ( "x_2", intDomain 1 3, ConstantInt 2 ) -======= - , ( "x_2", intDomain 1 3, (ConstantInt NoTag) 2 ) ->>>>>>> taggedints - , ( "x_3", DomainBool , ConstantBool True ) -<<<<<<< HEAD - , ( "x_4", intDomain 2 5, ConstantInt Nothing 4 ) -||||||| merged common ancestors - , ( "x_4", intDomain 2 5, ConstantInt 4 ) -======= - , ( "x_4", intDomain 2 5, (ConstantInt NoTag) 4 ) ->>>>>>> taggedints - ] - in testCases "x" highDomain highConstant Just low low - - , testCase "((bool, int), (bool, int))" $ - let - highDomain = DomainTuple [DomainTuple [DomainBool, intDomain 1 3], DomainTuple [DomainBool, intDomain 2 5]] -<<<<<<< HEAD - highConstant = ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantInt Nothing 2], ConstantAbstract $ AbsLitTuple [ConstantBool True, ConstantInt Nothing 4]] - mid = [ ( "x_1", DomainTuple [DomainBool, intDomain 1 3], ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantInt Nothing 2] ) - , ( "x_2", DomainTuple [DomainBool, intDomain 2 5], ConstantAbstract $ AbsLitTuple [ConstantBool True , ConstantInt Nothing 4] ) -||||||| merged common ancestors - highConstant = ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantInt 2], ConstantAbstract $ AbsLitTuple [ConstantBool True, ConstantInt 4]] - mid = [ ( "x_1", DomainTuple [DomainBool, intDomain 1 3], ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantInt 2] ) - , ( "x_2", DomainTuple [DomainBool, intDomain 2 5], ConstantAbstract $ AbsLitTuple [ConstantBool True , ConstantInt 4] ) -======= - highConstant = ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ConstantBool False, (ConstantInt NoTag) 2], ConstantAbstract $ AbsLitTuple [ConstantBool True, (ConstantInt NoTag) 4]] - mid = [ ( "x_1", DomainTuple [DomainBool, intDomain 1 3], ConstantAbstract $ AbsLitTuple [ConstantBool False, (ConstantInt NoTag) 2] ) - , ( "x_2", DomainTuple [DomainBool, intDomain 2 5], ConstantAbstract $ AbsLitTuple [ConstantBool True , (ConstantInt NoTag) 4] ) ->>>>>>> taggedints - ] - low = [ ( "x_1_1", DomainBool , ConstantBool False ) -<<<<<<< HEAD - , ( "x_1_2", intDomain 1 3, ConstantInt Nothing 2 ) -||||||| merged common ancestors - , ( "x_1_2", intDomain 1 3, ConstantInt 2 ) -======= - , ( "x_1_2", intDomain 1 3, (ConstantInt NoTag) 2 ) ->>>>>>> taggedints - , ( "x_2_1", DomainBool , ConstantBool True ) -<<<<<<< HEAD - , ( "x_2_2", intDomain 2 5, ConstantInt Nothing 4 ) -||||||| merged common ancestors - , ( "x_2_2", intDomain 2 5, ConstantInt 4 ) -======= - , ( "x_2_2", intDomain 2 5, (ConstantInt NoTag) 4 ) ->>>>>>> taggedints - ] - in testCases "x" highDomain highConstant Just mid low - - , testCase "(bool, (int, (bool, int)))" $ - let - highDomain = DomainTuple [DomainBool, DomainTuple [intDomain 1 3, DomainTuple [DomainBool, intDomain 2 5]]] -<<<<<<< HEAD - highConstant = ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantAbstract $ AbsLitTuple [ConstantInt Nothing 2, ConstantAbstract $ AbsLitTuple [ConstantBool True, ConstantInt Nothing 4]]] -||||||| merged common ancestors - highConstant = ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantAbstract $ AbsLitTuple [ConstantInt 2, ConstantAbstract $ AbsLitTuple [ConstantBool True, ConstantInt 4]]] -======= - highConstant = ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantAbstract $ AbsLitTuple [(ConstantInt NoTag) 2, ConstantAbstract $ AbsLitTuple [ConstantBool True, (ConstantInt NoTag) 4]]] ->>>>>>> taggedints - mid = [ ( "x_1", DomainBool , ConstantBool False ) - , ( "x_2", DomainTuple [intDomain 1 3, DomainTuple [DomainBool, intDomain 2 5]] -<<<<<<< HEAD - , ConstantAbstract $ AbsLitTuple [ConstantInt Nothing 2, ConstantAbstract $ AbsLitTuple [ConstantBool True, ConstantInt Nothing 4]] ) -||||||| merged common ancestors - , ConstantAbstract $ AbsLitTuple [ConstantInt 2, ConstantAbstract $ AbsLitTuple [ConstantBool True, ConstantInt 4]] ) -======= - , ConstantAbstract $ AbsLitTuple [(ConstantInt NoTag) 2, ConstantAbstract $ AbsLitTuple [ConstantBool True, (ConstantInt NoTag) 4]] ) ->>>>>>> taggedints - ] - low = [ ( "x_1" , DomainBool , ConstantBool False ) -<<<<<<< HEAD - , ( "x_2_1" , intDomain 1 3, ConstantInt Nothing 2 ) -||||||| merged common ancestors - , ( "x_2_1" , intDomain 1 3, ConstantInt 2 ) -======= - , ( "x_2_1" , intDomain 1 3, (ConstantInt NoTag) 2 ) ->>>>>>> taggedints - , ( "x_2_2_1", DomainBool , ConstantBool True ) -<<<<<<< HEAD - , ( "x_2_2_2", intDomain 2 5, ConstantInt Nothing 4 ) -||||||| merged common ancestors - , ( "x_2_2_2", intDomain 2 5, ConstantInt 4 ) -======= - , ( "x_2_2_2", intDomain 2 5, (ConstantInt NoTag) 4 ) ->>>>>>> taggedints - ] - in testCases "x" highDomain highConstant Just mid low - - , testCase "(bool, (int, bool), int)" $ - let - highDomain = DomainTuple [DomainBool, DomainTuple [intDomain 1 3, DomainBool], intDomain 2 5] -<<<<<<< HEAD - highConstant = ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantAbstract $ AbsLitTuple [ConstantInt Nothing 2, ConstantBool True], ConstantInt Nothing 4] -||||||| merged common ancestors - highConstant = ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantAbstract $ AbsLitTuple [ConstantInt 2, ConstantBool True], ConstantInt 4] -======= - highConstant = ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantAbstract $ AbsLitTuple [(ConstantInt NoTag) 2, ConstantBool True], (ConstantInt NoTag) 4] ->>>>>>> taggedints - mid = [ ( "x_1", DomainBool , ConstantBool False ) -<<<<<<< HEAD - , ( "x_2", DomainTuple [intDomain 1 3, DomainBool], ConstantAbstract $ AbsLitTuple [ConstantInt Nothing 2, ConstantBool True] ) - , ( "x_3", intDomain 2 5, ConstantInt Nothing 4 ) -||||||| merged common ancestors - , ( "x_2", DomainTuple [intDomain 1 3, DomainBool], ConstantAbstract $ AbsLitTuple [ConstantInt 2, ConstantBool True] ) - , ( "x_3", intDomain 2 5, ConstantInt 4 ) -======= - , ( "x_2", DomainTuple [intDomain 1 3, DomainBool], ConstantAbstract $ AbsLitTuple [(ConstantInt NoTag) 2, ConstantBool True] ) - , ( "x_3", intDomain 2 5, (ConstantInt NoTag) 4 ) ->>>>>>> taggedints - ] - low = [ ( "x_1" , DomainBool , ConstantBool False ) -<<<<<<< HEAD - , ( "x_2_1", intDomain 1 3, ConstantInt Nothing 2 ) -||||||| merged common ancestors - , ( "x_2_1", intDomain 1 3, ConstantInt 2 ) -======= - , ( "x_2_1", intDomain 1 3, (ConstantInt NoTag) 2 ) ->>>>>>> taggedints - , ( "x_2_2", DomainBool , ConstantBool True ) -<<<<<<< HEAD - , ( "x_3" , intDomain 2 5, ConstantInt Nothing 4 ) -||||||| merged common ancestors - , ( "x_3" , intDomain 2 5, ConstantInt 4 ) -======= - , ( "x_3" , intDomain 2 5, (ConstantInt NoTag) 4 ) ->>>>>>> taggedints - ] - in testCases "x" highDomain highConstant Just mid low - - , testCase "(((bool, int), bool), int)" $ - let - highDomain = DomainTuple [DomainTuple [ DomainTuple [DomainBool, intDomain 1 3], DomainBool], intDomain 2 5] -<<<<<<< HEAD - highConstant = ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantInt Nothing 2], ConstantBool True], ConstantInt Nothing 4] -||||||| merged common ancestors - highConstant = ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantInt 2], ConstantBool True], ConstantInt 4] -======= - highConstant = ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ ConstantAbstract $ AbsLitTuple [ConstantBool False, (ConstantInt NoTag) 2], ConstantBool True], (ConstantInt NoTag) 4] ->>>>>>> taggedints - mid = [ ( "x_1", DomainTuple [ DomainTuple [DomainBool, intDomain 1 3], DomainBool] -<<<<<<< HEAD - , ConstantAbstract $ AbsLitTuple [ ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantInt Nothing 2], ConstantBool True] ) - , ( "x_2", intDomain 2 5, ConstantInt Nothing 4 ) -||||||| merged common ancestors - , ConstantAbstract $ AbsLitTuple [ ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantInt 2], ConstantBool True] ) - , ( "x_2", intDomain 2 5, ConstantInt 4 ) -======= - , ConstantAbstract $ AbsLitTuple [ ConstantAbstract $ AbsLitTuple [ConstantBool False, (ConstantInt NoTag) 2], ConstantBool True] ) - , ( "x_2", intDomain 2 5, (ConstantInt NoTag) 4 ) ->>>>>>> taggedints - ] - low = [ ( "x_1_1_1", DomainBool , ConstantBool False ) -<<<<<<< HEAD - , ( "x_1_1_2", intDomain 1 3, ConstantInt Nothing 2 ) -||||||| merged common ancestors - , ( "x_1_1_2", intDomain 1 3, ConstantInt 2 ) -======= - , ( "x_1_1_2", intDomain 1 3, (ConstantInt NoTag) 2 ) ->>>>>>> taggedints - , ( "x_1_2" , DomainBool , ConstantBool True ) -<<<<<<< HEAD - , ( "x_2" , intDomain 2 5, ConstantInt Nothing 4 ) -||||||| merged common ancestors - , ( "x_2" , intDomain 2 5, ConstantInt 4 ) -======= - , ( "x_2" , intDomain 2 5, (ConstantInt NoTag) 4 ) ->>>>>>> taggedints - ] - in testCases "x" highDomain highConstant Just mid low - - , testCase "matrix of (bool, int)" $ - let - highDomain = - DomainMatrix (intDomain 1 3) (DomainTuple [DomainBool, intDomain 0 9]) - highConstant = - ConstantAbstract $ AbsLitMatrix (intDomain 1 3) -<<<<<<< HEAD - [ ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantInt Nothing 0] - , ConstantAbstract $ AbsLitTuple [ConstantBool True , ConstantInt Nothing 3] - , ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantInt Nothing 4] -||||||| merged common ancestors - [ ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantInt 0] - , ConstantAbstract $ AbsLitTuple [ConstantBool True , ConstantInt 3] - , ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantInt 4] -======= - [ ConstantAbstract $ AbsLitTuple [ConstantBool False, (ConstantInt NoTag) 0] - , ConstantAbstract $ AbsLitTuple [ConstantBool True , (ConstantInt NoTag) 3] - , ConstantAbstract $ AbsLitTuple [ConstantBool False, (ConstantInt NoTag) 4] ->>>>>>> taggedints - ] - low = [ ( "x_1", DomainMatrix (intDomain 1 3) DomainBool - , ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantBool False, ConstantBool True, ConstantBool False] ) - , ( "x_2", DomainMatrix (intDomain 1 3) (intDomain 0 9) -<<<<<<< HEAD - , ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantInt Nothing 0, ConstantInt Nothing 3, ConstantInt Nothing 4] ) -||||||| merged common ancestors - , ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantInt 0, ConstantInt 3, ConstantInt 4] ) -======= - , ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [(ConstantInt NoTag) 0, (ConstantInt NoTag) 3, (ConstantInt NoTag) 4] ) ->>>>>>> taggedints - ] - in testCases "x" highDomain highConstant Just low low - - , testCase "matrix of (bool, int, bool)" $ - let - highDomain = DomainMatrix (intDomain 1 3) (DomainTuple [DomainBool, intDomain 1 3, DomainBool]) - highConstant = - ConstantAbstract $ AbsLitMatrix (intDomain 1 3) -<<<<<<< HEAD - [ ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantInt Nothing 2, ConstantBool True] - , ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantInt Nothing 3, ConstantBool False] - , ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantInt Nothing 4, ConstantBool False] -||||||| merged common ancestors - [ ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantInt 2, ConstantBool True] - , ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantInt 3, ConstantBool False] - , ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantInt 4, ConstantBool False] -======= - [ ConstantAbstract $ AbsLitTuple [ConstantBool False, (ConstantInt NoTag) 2, ConstantBool True] - , ConstantAbstract $ AbsLitTuple [ConstantBool False, (ConstantInt NoTag) 3, ConstantBool False] - , ConstantAbstract $ AbsLitTuple [ConstantBool False, (ConstantInt NoTag) 4, ConstantBool False] ->>>>>>> taggedints - ] - low = [ ( "x_1", DomainMatrix (intDomain 1 3) DomainBool , ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantBool False, ConstantBool False, ConstantBool False] ) -<<<<<<< HEAD - , ( "x_2", DomainMatrix (intDomain 1 3) (intDomain 1 3), ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantInt Nothing 2 , ConstantInt Nothing 3 , ConstantInt Nothing 4 ] ) -||||||| merged common ancestors - , ( "x_2", DomainMatrix (intDomain 1 3) (intDomain 1 3), ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantInt 2 , ConstantInt 3 , ConstantInt 4 ] ) -======= - , ( "x_2", DomainMatrix (intDomain 1 3) (intDomain 1 3), ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [(ConstantInt NoTag) 2 , (ConstantInt NoTag) 3 , (ConstantInt NoTag) 4 ] ) ->>>>>>> taggedints - , ( "x_3", DomainMatrix (intDomain 1 3) DomainBool , ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantBool True , ConstantBool False, ConstantBool False] ) - ] - in testCases "x" highDomain highConstant Just low low - - , testCase "matrix of ((bool, int), bool)" $ - let - highDomain = DomainMatrix (intDomain 1 3) (DomainTuple [DomainTuple [DomainBool, intDomain 1 3], DomainBool]) - highConstant = - ConstantAbstract $ AbsLitMatrix (intDomain 1 3) -<<<<<<< HEAD - [ ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantInt Nothing 2], ConstantBool True] - , ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantInt Nothing 3], ConstantBool False] - , ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ConstantBool True , ConstantInt Nothing 4], ConstantBool False] -||||||| merged common ancestors - [ ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantInt 2], ConstantBool True] - , ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantInt 3], ConstantBool False] - , ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ConstantBool True , ConstantInt 4], ConstantBool False] -======= - [ ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ConstantBool False, (ConstantInt NoTag) 2], ConstantBool True] - , ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ConstantBool False, (ConstantInt NoTag) 3], ConstantBool False] - , ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ConstantBool True , (ConstantInt NoTag) 4], ConstantBool False] ->>>>>>> taggedints - ] - mid = [ ( "x_1", DomainMatrix (intDomain 1 3) (DomainTuple [DomainBool, intDomain 1 3]) - , ConstantAbstract $ AbsLitMatrix (intDomain 1 3) -<<<<<<< HEAD - [ ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantInt Nothing 2] - , ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantInt Nothing 3] - , ConstantAbstract $ AbsLitTuple [ConstantBool True , ConstantInt Nothing 4] -||||||| merged common ancestors - [ ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantInt 2] - , ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantInt 3] - , ConstantAbstract $ AbsLitTuple [ConstantBool True , ConstantInt 4] -======= - [ ConstantAbstract $ AbsLitTuple [ConstantBool False, (ConstantInt NoTag) 2] - , ConstantAbstract $ AbsLitTuple [ConstantBool False, (ConstantInt NoTag) 3] - , ConstantAbstract $ AbsLitTuple [ConstantBool True , (ConstantInt NoTag) 4] ->>>>>>> taggedints - ] ) - , ( "x_2", DomainMatrix (intDomain 1 3) DomainBool - , ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantBool True , ConstantBool False, ConstantBool False] ) - ] - low = [ ( "x_1_1", DomainMatrix (intDomain 1 3) DomainBool , ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantBool False, ConstantBool False, ConstantBool True ] ) -<<<<<<< HEAD - , ( "x_1_2", DomainMatrix (intDomain 1 3) (intDomain 1 3), ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantInt Nothing 2 , ConstantInt Nothing 3 , ConstantInt Nothing 4 ] ) -||||||| merged common ancestors - , ( "x_1_2", DomainMatrix (intDomain 1 3) (intDomain 1 3), ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantInt 2 , ConstantInt 3 , ConstantInt 4 ] ) -======= - , ( "x_1_2", DomainMatrix (intDomain 1 3) (intDomain 1 3), ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [(ConstantInt NoTag) 2 , (ConstantInt NoTag) 3 , (ConstantInt NoTag) 4 ] ) ->>>>>>> taggedints - , ( "x_2" , DomainMatrix (intDomain 1 3) DomainBool , ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantBool True , ConstantBool False, ConstantBool False] ) - ] - in testCases "x" highDomain highConstant Just mid low - - , testCase "matrix of (bool, (int, bool))" $ - let - highDomain = DomainMatrix (intDomain 1 3) (DomainTuple [DomainBool, DomainTuple [intDomain 0 9, DomainBool]]) - highConstant = - ConstantAbstract $ AbsLitMatrix (intDomain 1 3) -<<<<<<< HEAD - [ ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantAbstract $ AbsLitTuple [ConstantInt Nothing 0, ConstantBool True]] - , ConstantAbstract $ AbsLitTuple [ConstantBool True , ConstantAbstract $ AbsLitTuple [ConstantInt Nothing 3, ConstantBool False]] - , ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantAbstract $ AbsLitTuple [ConstantInt Nothing 4, ConstantBool True]] -||||||| merged common ancestors - [ ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantAbstract $ AbsLitTuple [ConstantInt 0, ConstantBool True]] - , ConstantAbstract $ AbsLitTuple [ConstantBool True , ConstantAbstract $ AbsLitTuple [ConstantInt 3, ConstantBool False]] - , ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantAbstract $ AbsLitTuple [ConstantInt 4, ConstantBool True]] -======= - [ ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantAbstract $ AbsLitTuple [(ConstantInt NoTag) 0, ConstantBool True]] - , ConstantAbstract $ AbsLitTuple [ConstantBool True , ConstantAbstract $ AbsLitTuple [(ConstantInt NoTag) 3, ConstantBool False]] - , ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantAbstract $ AbsLitTuple [(ConstantInt NoTag) 4, ConstantBool True]] ->>>>>>> taggedints - ] - mid = [ ( "x_1", DomainMatrix (intDomain 1 3) DomainBool - , ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantBool False, ConstantBool True, ConstantBool False] ) - , ( "x_2", DomainMatrix (intDomain 1 3) (DomainTuple [intDomain 0 9, DomainBool]) - , ConstantAbstract $ AbsLitMatrix (intDomain 1 3) -<<<<<<< HEAD - [ ConstantAbstract $ AbsLitTuple [ConstantInt Nothing 0, ConstantBool True] - , ConstantAbstract $ AbsLitTuple [ConstantInt Nothing 3, ConstantBool False] - , ConstantAbstract $ AbsLitTuple [ConstantInt Nothing 4, ConstantBool True] -||||||| merged common ancestors - [ ConstantAbstract $ AbsLitTuple [ConstantInt 0, ConstantBool True] - , ConstantAbstract $ AbsLitTuple [ConstantInt 3, ConstantBool False] - , ConstantAbstract $ AbsLitTuple [ConstantInt 4, ConstantBool True] -======= - [ ConstantAbstract $ AbsLitTuple [(ConstantInt NoTag) 0, ConstantBool True] - , ConstantAbstract $ AbsLitTuple [(ConstantInt NoTag) 3, ConstantBool False] - , ConstantAbstract $ AbsLitTuple [(ConstantInt NoTag) 4, ConstantBool True] ->>>>>>> taggedints - ] ) - ] - low = [ ( "x_1" , DomainMatrix (intDomain 1 3) DomainBool - , ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantBool False, ConstantBool True, ConstantBool False] ) - , ( "x_2_1", DomainMatrix (intDomain 1 3) (intDomain 0 9) -<<<<<<< HEAD - , ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantInt Nothing 0, ConstantInt Nothing 3, ConstantInt Nothing 4] ) -||||||| merged common ancestors - , ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantInt 0, ConstantInt 3, ConstantInt 4] ) -======= - , ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [(ConstantInt NoTag) 0, (ConstantInt NoTag) 3, (ConstantInt NoTag) 4] ) ->>>>>>> taggedints - , ( "x_2_2", DomainMatrix (intDomain 1 3) DomainBool - , ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantBool True, ConstantBool False, ConstantBool True] ) - ] - in testCases "x" highDomain highConstant Just mid low - - , testCase "matrix of (bool, int, bool, int)" $ - let - highDomain = DomainMatrix (intDomain 1 3) (DomainTuple [DomainBool, intDomain 1 3, DomainBool, intDomain 2 5]) - highConstant = - ConstantAbstract $ AbsLitMatrix (intDomain 1 3) -<<<<<<< HEAD - [ ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantInt Nothing 2, ConstantBool True , ConstantInt Nothing 4] - , ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantInt Nothing 3, ConstantBool False, ConstantInt Nothing 6] - , ConstantAbstract $ AbsLitTuple [ConstantBool True , ConstantInt Nothing 4, ConstantBool False, ConstantInt Nothing 8] -||||||| merged common ancestors - [ ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantInt 2, ConstantBool True , ConstantInt 4] - , ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantInt 3, ConstantBool False, ConstantInt 6] - , ConstantAbstract $ AbsLitTuple [ConstantBool True , ConstantInt 4, ConstantBool False, ConstantInt 8] -======= - [ ConstantAbstract $ AbsLitTuple [ConstantBool False, (ConstantInt NoTag) 2, ConstantBool True , (ConstantInt NoTag) 4] - , ConstantAbstract $ AbsLitTuple [ConstantBool False, (ConstantInt NoTag) 3, ConstantBool False, (ConstantInt NoTag) 6] - , ConstantAbstract $ AbsLitTuple [ConstantBool True , (ConstantInt NoTag) 4, ConstantBool False, (ConstantInt NoTag) 8] ->>>>>>> taggedints - ] - low = [ ( "x_1", DomainMatrix (intDomain 1 3) DomainBool , ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantBool False, ConstantBool False, ConstantBool True ] ) -<<<<<<< HEAD - , ( "x_2", DomainMatrix (intDomain 1 3) (intDomain 1 3), ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantInt Nothing 2 , ConstantInt Nothing 3 , ConstantInt Nothing 4 ] ) -||||||| merged common ancestors - , ( "x_2", DomainMatrix (intDomain 1 3) (intDomain 1 3), ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantInt 2 , ConstantInt 3 , ConstantInt 4 ] ) -======= - , ( "x_2", DomainMatrix (intDomain 1 3) (intDomain 1 3), ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [(ConstantInt NoTag) 2 , (ConstantInt NoTag) 3 , (ConstantInt NoTag) 4 ] ) ->>>>>>> taggedints - , ( "x_3", DomainMatrix (intDomain 1 3) DomainBool , ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantBool True , ConstantBool False, ConstantBool False] ) -<<<<<<< HEAD - , ( "x_4", DomainMatrix (intDomain 1 3) (intDomain 2 5), ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantInt Nothing 4 , ConstantInt Nothing 6 , ConstantInt Nothing 8 ] ) -||||||| merged common ancestors - , ( "x_4", DomainMatrix (intDomain 1 3) (intDomain 2 5), ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantInt 4 , ConstantInt 6 , ConstantInt 8 ] ) -======= - , ( "x_4", DomainMatrix (intDomain 1 3) (intDomain 2 5), ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [(ConstantInt NoTag) 4 , (ConstantInt NoTag) 6 , (ConstantInt NoTag) 8 ] ) ->>>>>>> taggedints - ] - in testCases "x" highDomain highConstant Just low low - - , testCase "matrix of ((bool, int), (bool, int))" $ - let - highDomain = DomainMatrix (intDomain 1 3) (DomainTuple [DomainTuple [DomainBool, intDomain 1 3], DomainTuple [DomainBool, intDomain 2 5]]) - highConstant = - ConstantAbstract $ AbsLitMatrix (intDomain 1 3) -<<<<<<< HEAD - [ ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantInt Nothing 2], ConstantAbstract $ AbsLitTuple [ConstantBool True , ConstantInt Nothing 4]] - , ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantInt Nothing 3], ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantInt Nothing 6]] - , ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ConstantBool True , ConstantInt Nothing 4], ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantInt Nothing 8]] -||||||| merged common ancestors - [ ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantInt 2], ConstantAbstract $ AbsLitTuple [ConstantBool True , ConstantInt 4]] - , ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantInt 3], ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantInt 6]] - , ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ConstantBool True , ConstantInt 4], ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantInt 8]] -======= - [ ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ConstantBool False, (ConstantInt NoTag) 2], ConstantAbstract $ AbsLitTuple [ConstantBool True , (ConstantInt NoTag) 4]] - , ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ConstantBool False, (ConstantInt NoTag) 3], ConstantAbstract $ AbsLitTuple [ConstantBool False, (ConstantInt NoTag) 6]] - , ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ConstantBool True , (ConstantInt NoTag) 4], ConstantAbstract $ AbsLitTuple [ConstantBool False, (ConstantInt NoTag) 8]] ->>>>>>> taggedints - ] - mid = [ ( "x_1" - , DomainMatrix (intDomain 1 3) (DomainTuple [DomainBool, intDomain 1 3]) - , ConstantAbstract $ AbsLitMatrix (intDomain 1 3) -<<<<<<< HEAD - [ ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantInt Nothing 2] - , ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantInt Nothing 3] - , ConstantAbstract $ AbsLitTuple [ConstantBool True , ConstantInt Nothing 4] -||||||| merged common ancestors - [ ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantInt 2] - , ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantInt 3] - , ConstantAbstract $ AbsLitTuple [ConstantBool True , ConstantInt 4] -======= - [ ConstantAbstract $ AbsLitTuple [ConstantBool False, (ConstantInt NoTag) 2] - , ConstantAbstract $ AbsLitTuple [ConstantBool False, (ConstantInt NoTag) 3] - , ConstantAbstract $ AbsLitTuple [ConstantBool True , (ConstantInt NoTag) 4] ->>>>>>> taggedints - ] ) - , ( "x_2" - , DomainMatrix (intDomain 1 3) (DomainTuple [DomainBool, intDomain 2 5]) - , ConstantAbstract $ AbsLitMatrix (intDomain 1 3) -<<<<<<< HEAD - [ ConstantAbstract $ AbsLitTuple [ConstantBool True , ConstantInt Nothing 4] - , ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantInt Nothing 6] - , ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantInt Nothing 8] -||||||| merged common ancestors - [ ConstantAbstract $ AbsLitTuple [ConstantBool True , ConstantInt 4] - , ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantInt 6] - , ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantInt 8] -======= - [ ConstantAbstract $ AbsLitTuple [ConstantBool True , (ConstantInt NoTag) 4] - , ConstantAbstract $ AbsLitTuple [ConstantBool False, (ConstantInt NoTag) 6] - , ConstantAbstract $ AbsLitTuple [ConstantBool False, (ConstantInt NoTag) 8] ->>>>>>> taggedints - ] ) - ] - low = [ ( "x_1_1", DomainMatrix (intDomain 1 3) DomainBool - , ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantBool False, ConstantBool False, ConstantBool True ] ) - , ( "x_1_2", DomainMatrix (intDomain 1 3) (intDomain 1 3) -<<<<<<< HEAD - , ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantInt Nothing 2 , ConstantInt Nothing 3 , ConstantInt Nothing 4 ] ) -||||||| merged common ancestors - , ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantInt 2 , ConstantInt 3 , ConstantInt 4 ] ) -======= - , ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [(ConstantInt NoTag) 2 , (ConstantInt NoTag) 3 , (ConstantInt NoTag) 4 ] ) ->>>>>>> taggedints - , ( "x_2_1", DomainMatrix (intDomain 1 3) DomainBool - , ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantBool True , ConstantBool False, ConstantBool False] ) - , ( "x_2_2", DomainMatrix (intDomain 1 3) (intDomain 2 5) -<<<<<<< HEAD - , ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantInt Nothing 4 , ConstantInt Nothing 6 , ConstantInt Nothing 8 ] ) -||||||| merged common ancestors - , ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantInt 4 , ConstantInt 6 , ConstantInt 8 ] ) -======= - , ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [(ConstantInt NoTag) 4 , (ConstantInt NoTag) 6 , (ConstantInt NoTag) 8 ] ) ->>>>>>> taggedints - ] - in testCases "x" highDomain highConstant Just mid low - - , testCase "matrix of (bool, (int, (bool, int)))" $ - let - highDomain = DomainMatrix (intDomain 1 3) (DomainTuple [DomainBool, DomainTuple [intDomain 1 3, DomainTuple [DomainBool, intDomain 2 5]]]) - highConstant = - ConstantAbstract $ AbsLitMatrix (intDomain 1 3) -<<<<<<< HEAD - [ ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantAbstract $ AbsLitTuple [ConstantInt Nothing 2, ConstantAbstract $ AbsLitTuple [ConstantBool True , ConstantInt Nothing 4]]] - , ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantAbstract $ AbsLitTuple [ConstantInt Nothing 3, ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantInt Nothing 6]]] - , ConstantAbstract $ AbsLitTuple [ConstantBool True , ConstantAbstract $ AbsLitTuple [ConstantInt Nothing 4, ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantInt Nothing 8]]] -||||||| merged common ancestors - [ ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantAbstract $ AbsLitTuple [ConstantInt 2, ConstantAbstract $ AbsLitTuple [ConstantBool True , ConstantInt 4]]] - , ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantAbstract $ AbsLitTuple [ConstantInt 3, ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantInt 6]]] - , ConstantAbstract $ AbsLitTuple [ConstantBool True , ConstantAbstract $ AbsLitTuple [ConstantInt 4, ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantInt 8]]] -======= - [ ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantAbstract $ AbsLitTuple [(ConstantInt NoTag) 2, ConstantAbstract $ AbsLitTuple [ConstantBool True , (ConstantInt NoTag) 4]]] - , ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantAbstract $ AbsLitTuple [(ConstantInt NoTag) 3, ConstantAbstract $ AbsLitTuple [ConstantBool False, (ConstantInt NoTag) 6]]] - , ConstantAbstract $ AbsLitTuple [ConstantBool True , ConstantAbstract $ AbsLitTuple [(ConstantInt NoTag) 4, ConstantAbstract $ AbsLitTuple [ConstantBool False, (ConstantInt NoTag) 8]]] ->>>>>>> taggedints - ] - mid = [ ( "x_1", DomainMatrix (intDomain 1 3) DomainBool - , ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantBool False, ConstantBool False, ConstantBool True] ) - , ( "x_2", DomainMatrix (intDomain 1 3) (DomainTuple [intDomain 1 3, DomainTuple [DomainBool, intDomain 2 5]]) - , ConstantAbstract $ AbsLitMatrix (intDomain 1 3) -<<<<<<< HEAD - [ ConstantAbstract $ AbsLitTuple [ConstantInt Nothing 2, ConstantAbstract $ AbsLitTuple [ConstantBool True , ConstantInt Nothing 4]] - , ConstantAbstract $ AbsLitTuple [ConstantInt Nothing 3, ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantInt Nothing 6]] - , ConstantAbstract $ AbsLitTuple [ConstantInt Nothing 4, ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantInt Nothing 8]] -||||||| merged common ancestors - [ ConstantAbstract $ AbsLitTuple [ConstantInt 2, ConstantAbstract $ AbsLitTuple [ConstantBool True , ConstantInt 4]] - , ConstantAbstract $ AbsLitTuple [ConstantInt 3, ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantInt 6]] - , ConstantAbstract $ AbsLitTuple [ConstantInt 4, ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantInt 8]] -======= - [ ConstantAbstract $ AbsLitTuple [(ConstantInt NoTag) 2, ConstantAbstract $ AbsLitTuple [ConstantBool True , (ConstantInt NoTag) 4]] - , ConstantAbstract $ AbsLitTuple [(ConstantInt NoTag) 3, ConstantAbstract $ AbsLitTuple [ConstantBool False, (ConstantInt NoTag) 6]] - , ConstantAbstract $ AbsLitTuple [(ConstantInt NoTag) 4, ConstantAbstract $ AbsLitTuple [ConstantBool False, (ConstantInt NoTag) 8]] ->>>>>>> taggedints - ] ) - ] - low = [ ( "x_1" , DomainMatrix (intDomain 1 3) DomainBool , ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantBool False, ConstantBool False, ConstantBool True ]) -<<<<<<< HEAD - , ( "x_2_1" , DomainMatrix (intDomain 1 3) (intDomain 1 3), ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantInt Nothing 2 , ConstantInt Nothing 3 , ConstantInt Nothing 4 ]) -||||||| merged common ancestors - , ( "x_2_1" , DomainMatrix (intDomain 1 3) (intDomain 1 3), ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantInt 2 , ConstantInt 3 , ConstantInt 4 ]) -======= - , ( "x_2_1" , DomainMatrix (intDomain 1 3) (intDomain 1 3), ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [(ConstantInt NoTag) 2 , (ConstantInt NoTag) 3 , (ConstantInt NoTag) 4 ]) ->>>>>>> taggedints - , ( "x_2_2_1", DomainMatrix (intDomain 1 3) DomainBool , ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantBool True , ConstantBool False, ConstantBool False]) -<<<<<<< HEAD - , ( "x_2_2_2", DomainMatrix (intDomain 1 3) (intDomain 2 5), ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantInt Nothing 4 , ConstantInt Nothing 6 , ConstantInt Nothing 8 ]) -||||||| merged common ancestors - , ( "x_2_2_2", DomainMatrix (intDomain 1 3) (intDomain 2 5), ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantInt 4 , ConstantInt 6 , ConstantInt 8 ]) -======= - , ( "x_2_2_2", DomainMatrix (intDomain 1 3) (intDomain 2 5), ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [(ConstantInt NoTag) 4 , (ConstantInt NoTag) 6 , (ConstantInt NoTag) 8 ]) ->>>>>>> taggedints - ] - in testCases "x" highDomain highConstant Just mid low - - , testCase "matrix of (bool, (int, bool), int)" $ - let - highDomain = DomainMatrix (intDomain 1 3) (DomainTuple [DomainBool, DomainTuple [intDomain 1 3, DomainBool], intDomain 2 5]) - highConstant = - ConstantAbstract $ AbsLitMatrix (intDomain 1 3) -<<<<<<< HEAD - [ ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantAbstract $ AbsLitTuple [ConstantInt Nothing 2, ConstantBool True ], ConstantInt Nothing 4] - , ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantAbstract $ AbsLitTuple [ConstantInt Nothing 3, ConstantBool False], ConstantInt Nothing 6] - , ConstantAbstract $ AbsLitTuple [ConstantBool True , ConstantAbstract $ AbsLitTuple [ConstantInt Nothing 4, ConstantBool False], ConstantInt Nothing 8] -||||||| merged common ancestors - [ ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantAbstract $ AbsLitTuple [ConstantInt 2, ConstantBool True ], ConstantInt 4] - , ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantAbstract $ AbsLitTuple [ConstantInt 3, ConstantBool False], ConstantInt 6] - , ConstantAbstract $ AbsLitTuple [ConstantBool True , ConstantAbstract $ AbsLitTuple [ConstantInt 4, ConstantBool False], ConstantInt 8] -======= - [ ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantAbstract $ AbsLitTuple [(ConstantInt NoTag) 2, ConstantBool True ], (ConstantInt NoTag) 4] - , ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantAbstract $ AbsLitTuple [(ConstantInt NoTag) 3, ConstantBool False], (ConstantInt NoTag) 6] - , ConstantAbstract $ AbsLitTuple [ConstantBool True , ConstantAbstract $ AbsLitTuple [(ConstantInt NoTag) 4, ConstantBool False], (ConstantInt NoTag) 8] ->>>>>>> taggedints - ] - mid = [ ( "x_1", DomainMatrix (intDomain 1 3) DomainBool - , ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantBool False, ConstantBool False, ConstantBool True] ) - , ( "x_2", DomainMatrix (intDomain 1 3) (DomainTuple [intDomain 1 3, DomainBool]) - , ConstantAbstract $ AbsLitMatrix (intDomain 1 3) -<<<<<<< HEAD - [ ConstantAbstract $ AbsLitTuple [ConstantInt Nothing 2, ConstantBool True ] - , ConstantAbstract $ AbsLitTuple [ConstantInt Nothing 3, ConstantBool False] - , ConstantAbstract $ AbsLitTuple [ConstantInt Nothing 4, ConstantBool False] -||||||| merged common ancestors - [ ConstantAbstract $ AbsLitTuple [ConstantInt 2, ConstantBool True ] - , ConstantAbstract $ AbsLitTuple [ConstantInt 3, ConstantBool False] - , ConstantAbstract $ AbsLitTuple [ConstantInt 4, ConstantBool False] -======= - [ ConstantAbstract $ AbsLitTuple [(ConstantInt NoTag) 2, ConstantBool True ] - , ConstantAbstract $ AbsLitTuple [(ConstantInt NoTag) 3, ConstantBool False] - , ConstantAbstract $ AbsLitTuple [(ConstantInt NoTag) 4, ConstantBool False] ->>>>>>> taggedints - ] ) - , ( "x_3", DomainMatrix (intDomain 1 3) (intDomain 2 5) -<<<<<<< HEAD - , ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantInt Nothing 4, ConstantInt Nothing 6, ConstantInt Nothing 8] -||||||| merged common ancestors - , ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantInt 4, ConstantInt 6, ConstantInt 8] -======= - , ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [(ConstantInt NoTag) 4, (ConstantInt NoTag) 6, (ConstantInt NoTag) 8] ->>>>>>> taggedints - ) - ] - low = [ ( "x_1" , DomainMatrix (intDomain 1 3) DomainBool , ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantBool False, ConstantBool False, ConstantBool True ]) -<<<<<<< HEAD - , ( "x_2_1", DomainMatrix (intDomain 1 3) (intDomain 1 3), ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantInt Nothing 2 , ConstantInt Nothing 3 , ConstantInt Nothing 4 ]) -||||||| merged common ancestors - , ( "x_2_1", DomainMatrix (intDomain 1 3) (intDomain 1 3), ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantInt 2 , ConstantInt 3 , ConstantInt 4 ]) -======= - , ( "x_2_1", DomainMatrix (intDomain 1 3) (intDomain 1 3), ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [(ConstantInt NoTag) 2 , (ConstantInt NoTag) 3 , (ConstantInt NoTag) 4 ]) ->>>>>>> taggedints - , ( "x_2_2", DomainMatrix (intDomain 1 3) DomainBool , ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantBool True , ConstantBool False, ConstantBool False]) -<<<<<<< HEAD - , ( "x_3" , DomainMatrix (intDomain 1 3) (intDomain 2 5), ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantInt Nothing 4 , ConstantInt Nothing 6 , ConstantInt Nothing 8 ]) -||||||| merged common ancestors - , ( "x_3" , DomainMatrix (intDomain 1 3) (intDomain 2 5), ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantInt 4 , ConstantInt 6 , ConstantInt 8 ]) -======= - , ( "x_3" , DomainMatrix (intDomain 1 3) (intDomain 2 5), ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [(ConstantInt NoTag) 4 , (ConstantInt NoTag) 6 , (ConstantInt NoTag) 8 ]) ->>>>>>> taggedints - ] - in testCases "x" highDomain highConstant Just mid low - - , testCase "matrix of (((bool, int), bool), int)" $ - let - highDomain = DomainMatrix (intDomain 1 3) (DomainTuple [DomainTuple [DomainTuple [DomainBool, intDomain 1 3], DomainBool], intDomain 2 5]) - highConstant = - ConstantAbstract $ AbsLitMatrix (intDomain 1 3) -<<<<<<< HEAD - [ ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantInt Nothing 2], ConstantBool True ], ConstantInt Nothing 4] - , ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantInt Nothing 3], ConstantBool False], ConstantInt Nothing 6] - , ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ConstantBool True , ConstantInt Nothing 4], ConstantBool False], ConstantInt Nothing 8] -||||||| merged common ancestors - [ ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantInt 2], ConstantBool True ], ConstantInt 4] - , ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantInt 3], ConstantBool False], ConstantInt 6] - , ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ConstantBool True , ConstantInt 4], ConstantBool False], ConstantInt 8] -======= - [ ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ConstantBool False, (ConstantInt NoTag) 2], ConstantBool True ], (ConstantInt NoTag) 4] - , ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ConstantBool False, (ConstantInt NoTag) 3], ConstantBool False], (ConstantInt NoTag) 6] - , ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ConstantBool True , (ConstantInt NoTag) 4], ConstantBool False], (ConstantInt NoTag) 8] ->>>>>>> taggedints - ] - mid = [ ( "x_1", DomainMatrix (intDomain 1 3) (DomainTuple [DomainTuple [DomainBool,intDomain 1 3],DomainBool]) - , ConstantAbstract $ AbsLitMatrix (intDomain 1 3) -<<<<<<< HEAD - [ ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantInt Nothing 2], ConstantBool True ] - , ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantInt Nothing 3], ConstantBool False] - , ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ConstantBool True , ConstantInt Nothing 4], ConstantBool False] -||||||| merged common ancestors - [ ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantInt 2], ConstantBool True ] - , ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantInt 3], ConstantBool False] - , ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ConstantBool True , ConstantInt 4], ConstantBool False] -======= - [ ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ConstantBool False, (ConstantInt NoTag) 2], ConstantBool True ] - , ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ConstantBool False, (ConstantInt NoTag) 3], ConstantBool False] - , ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ConstantBool True , (ConstantInt NoTag) 4], ConstantBool False] ->>>>>>> taggedints - ]) - , ( "x_2", DomainMatrix (intDomain 1 3) (intDomain 2 5) -<<<<<<< HEAD - , ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantInt Nothing 4, ConstantInt Nothing 6, ConstantInt Nothing 8] -||||||| merged common ancestors - , ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantInt 4, ConstantInt 6, ConstantInt 8] -======= - , ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [(ConstantInt NoTag) 4, (ConstantInt NoTag) 6, (ConstantInt NoTag) 8] ->>>>>>> taggedints - ) - ] - low = [ ( "x_1_1_1", DomainMatrix (intDomain 1 3) DomainBool , ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantBool False, ConstantBool False, ConstantBool True ]) -<<<<<<< HEAD - , ( "x_1_1_2", DomainMatrix (intDomain 1 3) (intDomain 1 3), ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantInt Nothing 2 , ConstantInt Nothing 3 , ConstantInt Nothing 4 ]) -||||||| merged common ancestors - , ( "x_1_1_2", DomainMatrix (intDomain 1 3) (intDomain 1 3), ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantInt 2 , ConstantInt 3 , ConstantInt 4 ]) -======= - , ( "x_1_1_2", DomainMatrix (intDomain 1 3) (intDomain 1 3), ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [(ConstantInt NoTag) 2 , (ConstantInt NoTag) 3 , (ConstantInt NoTag) 4 ]) ->>>>>>> taggedints - , ( "x_1_2" , DomainMatrix (intDomain 1 3) DomainBool , ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantBool True , ConstantBool False, ConstantBool False]) -<<<<<<< HEAD - , ( "x_2" , DomainMatrix (intDomain 1 3) (intDomain 2 5), ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantInt Nothing 4 , ConstantInt Nothing 6 , ConstantInt Nothing 8 ]) -||||||| merged common ancestors - , ( "x_2" , DomainMatrix (intDomain 1 3) (intDomain 2 5), ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantInt 4 , ConstantInt 6 , ConstantInt 8 ]) -======= - , ( "x_2" , DomainMatrix (intDomain 1 3) (intDomain 2 5), ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [(ConstantInt NoTag) 4 , (ConstantInt NoTag) 6 , (ConstantInt NoTag) 8 ]) ->>>>>>> taggedints - ] - in testCases "x" highDomain highConstant Just mid low - - , testCase "matrix 2d of (((bool, int), bool), int)" $ - let - highDomain = - DomainMatrix (intDomain 1 2) - (DomainMatrix (intDomain 1 3) - (DomainTuple [DomainTuple [DomainTuple [DomainBool, intDomain 1 3], DomainBool], intDomain 2 5])) - highConstant = - ConstantAbstract $ AbsLitMatrix (intDomain 1 2) - [ ConstantAbstract $ AbsLitMatrix (intDomain 1 3) -<<<<<<< HEAD - [ ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantInt Nothing 2], ConstantBool True ], ConstantInt Nothing 4] - , ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantInt Nothing 3], ConstantBool False], ConstantInt Nothing 6] - , ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ConstantBool True , ConstantInt Nothing 4], ConstantBool False], ConstantInt Nothing 8] -||||||| merged common ancestors - [ ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantInt 2], ConstantBool True ], ConstantInt 4] - , ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantInt 3], ConstantBool False], ConstantInt 6] - , ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ConstantBool True , ConstantInt 4], ConstantBool False], ConstantInt 8] -======= - [ ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ConstantBool False, (ConstantInt NoTag) 2], ConstantBool True ], (ConstantInt NoTag) 4] - , ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ConstantBool False, (ConstantInt NoTag) 3], ConstantBool False], (ConstantInt NoTag) 6] - , ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ConstantBool True , (ConstantInt NoTag) 4], ConstantBool False], (ConstantInt NoTag) 8] ->>>>>>> taggedints - ] - , ConstantAbstract $ AbsLitMatrix (intDomain 1 3) -<<<<<<< HEAD - [ ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantInt Nothing 4], ConstantBool True ], ConstantInt Nothing 4] - , ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ConstantBool True , ConstantInt Nothing 5], ConstantBool False], ConstantInt Nothing 7] - , ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ConstantBool True , ConstantInt Nothing 6], ConstantBool False], ConstantInt Nothing 9] -||||||| merged common ancestors - [ ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantInt 4], ConstantBool True ], ConstantInt 4] - , ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ConstantBool True , ConstantInt 5], ConstantBool False], ConstantInt 7] - , ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ConstantBool True , ConstantInt 6], ConstantBool False], ConstantInt 9] -======= - [ ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ConstantBool False, (ConstantInt NoTag) 4], ConstantBool True ], (ConstantInt NoTag) 4] - , ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ConstantBool True , (ConstantInt NoTag) 5], ConstantBool False], (ConstantInt NoTag) 7] - , ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ConstantBool True , (ConstantInt NoTag) 6], ConstantBool False], (ConstantInt NoTag) 9] ->>>>>>> taggedints - ] - ] - mid = - [ ( "x_1" , DomainMatrix (intDomain 1 2) - (DomainMatrix (intDomain 1 3) - (DomainTuple [DomainTuple [DomainBool, intDomain 1 3], DomainBool])) - , ConstantAbstract $ AbsLitMatrix (intDomain 1 2) - [ ConstantAbstract $ AbsLitMatrix (intDomain 1 3) -<<<<<<< HEAD - [ ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ConstantBool False,ConstantInt Nothing 2],ConstantBool True] - , ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ConstantBool False,ConstantInt Nothing 3],ConstantBool False] - , ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ConstantBool True,ConstantInt Nothing 4],ConstantBool False] -||||||| merged common ancestors - [ ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ConstantBool False,ConstantInt 2],ConstantBool True] - , ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ConstantBool False,ConstantInt 3],ConstantBool False] - , ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ConstantBool True,ConstantInt 4],ConstantBool False] -======= - [ ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ConstantBool False,(ConstantInt NoTag) 2],ConstantBool True] - , ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ConstantBool False,(ConstantInt NoTag) 3],ConstantBool False] - , ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ConstantBool True,(ConstantInt NoTag) 4],ConstantBool False] ->>>>>>> taggedints - ] - , ConstantAbstract $ AbsLitMatrix (intDomain 1 3) -<<<<<<< HEAD - [ ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ConstantBool False,ConstantInt Nothing 4],ConstantBool True] - , ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ConstantBool True,ConstantInt Nothing 5],ConstantBool False] - , ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ConstantBool True,ConstantInt Nothing 6],ConstantBool False] -||||||| merged common ancestors - [ ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ConstantBool False,ConstantInt 4],ConstantBool True] - , ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ConstantBool True,ConstantInt 5],ConstantBool False] - , ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ConstantBool True,ConstantInt 6],ConstantBool False] -======= - [ ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ConstantBool False,(ConstantInt NoTag) 4],ConstantBool True] - , ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ConstantBool True,(ConstantInt NoTag) 5],ConstantBool False] - , ConstantAbstract $ AbsLitTuple [ConstantAbstract $ AbsLitTuple [ConstantBool True,(ConstantInt NoTag) 6],ConstantBool False] ->>>>>>> taggedints - ] - ] ) - , ( "x_2" , DomainMatrix (intDomain 1 2) - (DomainMatrix (intDomain 1 3) - (intDomain 2 5)) - , ConstantAbstract $ AbsLitMatrix (intDomain 1 2) -<<<<<<< HEAD - [ ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantInt Nothing 4,ConstantInt Nothing 6,ConstantInt Nothing 8] - , ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantInt Nothing 4,ConstantInt Nothing 7,ConstantInt Nothing 9] -||||||| merged common ancestors - [ ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantInt 4,ConstantInt 6,ConstantInt 8] - , ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantInt 4,ConstantInt 7,ConstantInt 9] -======= - [ ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [(ConstantInt NoTag) 4,(ConstantInt NoTag) 6,(ConstantInt NoTag) 8] - , ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [(ConstantInt NoTag) 4,(ConstantInt NoTag) 7,(ConstantInt NoTag) 9] ->>>>>>> taggedints - ] ) - ] - low = - [ ( "x_1_1_1" , DomainMatrix (intDomain 1 2) (DomainMatrix (intDomain 1 3) DomainBool) - , ConstantAbstract $ AbsLitMatrix (intDomain 1 2) - [ ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantBool False,ConstantBool False,ConstantBool True] - , ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantBool False,ConstantBool True,ConstantBool True] - ] ) - , ( "x_1_1_2" , DomainMatrix (intDomain 1 2) (DomainMatrix (intDomain 1 3) (intDomain 1 3)) - , ConstantAbstract $ AbsLitMatrix (intDomain 1 2) -<<<<<<< HEAD - [ ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantInt Nothing 2,ConstantInt Nothing 3,ConstantInt Nothing 4] - , ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantInt Nothing 4,ConstantInt Nothing 5,ConstantInt Nothing 6] -||||||| merged common ancestors - [ ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantInt 2,ConstantInt 3,ConstantInt 4] - , ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantInt 4,ConstantInt 5,ConstantInt 6] -======= - [ ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [(ConstantInt NoTag) 2,(ConstantInt NoTag) 3,(ConstantInt NoTag) 4] - , ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [(ConstantInt NoTag) 4,(ConstantInt NoTag) 5,(ConstantInt NoTag) 6] ->>>>>>> taggedints - ] ) - , ( "x_1_2" , DomainMatrix (intDomain 1 2) (DomainMatrix (intDomain 1 3) DomainBool) - , ConstantAbstract $ AbsLitMatrix (intDomain 1 2) - [ ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantBool True,ConstantBool False,ConstantBool False] - , ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantBool True,ConstantBool False,ConstantBool False] - ] ) - , ( "x_2" , DomainMatrix (intDomain 1 2) (DomainMatrix (intDomain 1 3) (intDomain 2 5)) - , ConstantAbstract $ AbsLitMatrix (intDomain 1 2) -<<<<<<< HEAD - [ ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantInt Nothing 4,ConstantInt Nothing 6,ConstantInt Nothing 8] - , ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantInt Nothing 4,ConstantInt Nothing 7,ConstantInt Nothing 9] -||||||| merged common ancestors - [ ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantInt 4,ConstantInt 6,ConstantInt 8] - , ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantInt 4,ConstantInt 7,ConstantInt 9] -======= - [ ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [(ConstantInt NoTag) 4,(ConstantInt NoTag) 6,(ConstantInt NoTag) 8] - , ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [(ConstantInt NoTag) 4,(ConstantInt NoTag) 7,(ConstantInt NoTag) 9] ->>>>>>> taggedints - ] ) - ] - in testCases "x" highDomain highConstant Just mid low - - , testCase "(bool, bool, bool)" $ testCasesAuto "x" - ( DomainTuple [DomainBool, DomainBool, DomainBool] ) - ( ConstantAbstract $ AbsLitTuple [ConstantBool False, ConstantBool False, ConstantBool True] ) - - , testCase "(bool, matrix of int) {auto}" $ testCasesAuto "x" - ( DomainTuple - [ DomainBool - , DomainMatrix (intDomain 1 3) (intDomain 0 9) - ] ) - ( ConstantAbstract $ AbsLitTuple - [ ConstantBool False -<<<<<<< HEAD - , ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantInt Nothing 2, ConstantInt Nothing 4, ConstantInt Nothing 5] -||||||| merged common ancestors - , ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantInt 2, ConstantInt 4, ConstantInt 5] -======= - , ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [(ConstantInt NoTag) 2, (ConstantInt NoTag) 4, (ConstantInt NoTag) 5] ->>>>>>> taggedints - ] ) - - , testCase "(bool, matrix of int)" $ - let - highDomain = - DomainTuple - [ DomainBool - , DomainMatrix (intDomain 1 3) (intDomain 0 9) - ] - highConstant = - ConstantAbstract $ AbsLitTuple - [ ConstantBool False -<<<<<<< HEAD - , ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantInt Nothing 2, ConstantInt Nothing 4, ConstantInt Nothing 5] -||||||| merged common ancestors - , ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantInt 2, ConstantInt 4, ConstantInt 5] -======= - , ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [(ConstantInt NoTag) 2, (ConstantInt NoTag) 4, (ConstantInt NoTag) 5] ->>>>>>> taggedints - ] - low = - [ ( "x_1", DomainBool,ConstantBool False) - , ( "x_2", DomainMatrix (intDomain 1 3) (intDomain 0 9) -<<<<<<< HEAD - , ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantInt Nothing 2,ConstantInt Nothing 4,ConstantInt Nothing 5] ) -||||||| merged common ancestors - , ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantInt 2,ConstantInt 4,ConstantInt 5] ) -======= - , ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [(ConstantInt NoTag) 2,(ConstantInt NoTag) 4,(ConstantInt NoTag) 5] ) ->>>>>>> taggedints - ] - in testCases "x" highDomain highConstant Just low low - - , testCase "(bool, matrix of (int, bool)) {auto}" $ testCasesAuto "x" - ( DomainTuple - [ DomainBool - , DomainMatrix (intDomain 1 3) (DomainTuple [intDomain 0 9, DomainBool]) - ] ) - ( ConstantAbstract $ AbsLitTuple - [ ConstantBool False - , ConstantAbstract $ AbsLitMatrix (intDomain 1 3) -<<<<<<< HEAD - [ ConstantAbstract $ AbsLitTuple [ConstantInt Nothing 2, ConstantBool False] - , ConstantAbstract $ AbsLitTuple [ConstantInt Nothing 4, ConstantBool True] - , ConstantAbstract $ AbsLitTuple [ConstantInt Nothing 5, ConstantBool False] -||||||| merged common ancestors - [ ConstantAbstract $ AbsLitTuple [ConstantInt 2, ConstantBool False] - , ConstantAbstract $ AbsLitTuple [ConstantInt 4, ConstantBool True] - , ConstantAbstract $ AbsLitTuple [ConstantInt 5, ConstantBool False] -======= - [ ConstantAbstract $ AbsLitTuple [(ConstantInt NoTag) 2, ConstantBool False] - , ConstantAbstract $ AbsLitTuple [(ConstantInt NoTag) 4, ConstantBool True] - , ConstantAbstract $ AbsLitTuple [(ConstantInt NoTag) 5, ConstantBool False] ->>>>>>> taggedints - ] - ] ) - - , testCase "(bool, matrix of (int, bool))" $ - let - highDomain = - DomainTuple - [ DomainBool - , DomainMatrix (intDomain 1 3) (DomainTuple [intDomain 0 9, DomainBool]) - ] - highConstant = - ConstantAbstract $ AbsLitTuple - [ ConstantBool False - , ConstantAbstract $ AbsLitMatrix (intDomain 1 3) -<<<<<<< HEAD - [ ConstantAbstract $ AbsLitTuple [ConstantInt Nothing 2, ConstantBool False] - , ConstantAbstract $ AbsLitTuple [ConstantInt Nothing 4, ConstantBool True] - , ConstantAbstract $ AbsLitTuple [ConstantInt Nothing 5, ConstantBool False] -||||||| merged common ancestors - [ ConstantAbstract $ AbsLitTuple [ConstantInt 2, ConstantBool False] - , ConstantAbstract $ AbsLitTuple [ConstantInt 4, ConstantBool True] - , ConstantAbstract $ AbsLitTuple [ConstantInt 5, ConstantBool False] -======= - [ ConstantAbstract $ AbsLitTuple [(ConstantInt NoTag) 2, ConstantBool False] - , ConstantAbstract $ AbsLitTuple [(ConstantInt NoTag) 4, ConstantBool True] - , ConstantAbstract $ AbsLitTuple [(ConstantInt NoTag) 5, ConstantBool False] ->>>>>>> taggedints - ] - ] - mid = - [ ( "x_1" , DomainBool , ConstantBool False ) - , ( "x_2" , DomainMatrix (intDomain 1 3) (DomainTuple [intDomain 0 9,DomainBool]) - , ConstantAbstract $ AbsLitMatrix (intDomain 1 3) -<<<<<<< HEAD - [ ConstantAbstract $ AbsLitTuple [ConstantInt Nothing 2,ConstantBool False] - , ConstantAbstract $ AbsLitTuple [ConstantInt Nothing 4,ConstantBool True] - , ConstantAbstract $ AbsLitTuple [ConstantInt Nothing 5,ConstantBool False] -||||||| merged common ancestors - [ ConstantAbstract $ AbsLitTuple [ConstantInt 2,ConstantBool False] - , ConstantAbstract $ AbsLitTuple [ConstantInt 4,ConstantBool True] - , ConstantAbstract $ AbsLitTuple [ConstantInt 5,ConstantBool False] -======= - [ ConstantAbstract $ AbsLitTuple [(ConstantInt NoTag) 2,ConstantBool False] - , ConstantAbstract $ AbsLitTuple [(ConstantInt NoTag) 4,ConstantBool True] - , ConstantAbstract $ AbsLitTuple [(ConstantInt NoTag) 5,ConstantBool False] ->>>>>>> taggedints - ] ) - ] - low = - [ ( "x_1" , DomainBool , ConstantBool False ) -<<<<<<< HEAD - , ( "x_2_1" , DomainMatrix (intDomain 1 3) (intDomain 0 9) , ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantInt Nothing 2,ConstantInt Nothing 4,ConstantInt Nothing 5] ) -||||||| merged common ancestors - , ( "x_2_1" , DomainMatrix (intDomain 1 3) (intDomain 0 9) , ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantInt 2,ConstantInt 4,ConstantInt 5] ) -======= - , ( "x_2_1" , DomainMatrix (intDomain 1 3) (intDomain 0 9) , ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [(ConstantInt NoTag) 2,(ConstantInt NoTag) 4,(ConstantInt NoTag) 5] ) ->>>>>>> taggedints - , ( "x_2_2" , DomainMatrix (intDomain 1 3) DomainBool , ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantBool False,ConstantBool True,ConstantBool False] ) - ] - in testCases "x" highDomain highConstant Just mid low - - , testCase "(bool, matrix of (int, matrix of int)) {auto}" $ testCasesAuto "x" - ( DomainTuple - [ DomainBool - , DomainMatrix (intDomain 1 3) (DomainTuple - [ intDomain 0 9 - , DomainMatrix (intDomain 1 2) (intDomain 0 9) - ]) - ] ) - ( ConstantAbstract $ AbsLitTuple - [ ConstantBool False - , ConstantAbstract $ AbsLitMatrix (intDomain 1 3) -<<<<<<< HEAD - [ ConstantAbstract $ AbsLitTuple [ConstantInt Nothing 2, ConstantAbstract $ AbsLitMatrix (intDomain 1 2) [ConstantInt Nothing 1, ConstantInt Nothing 3]] - , ConstantAbstract $ AbsLitTuple [ConstantInt Nothing 4, ConstantAbstract $ AbsLitMatrix (intDomain 1 2) [ConstantInt Nothing 3, ConstantInt Nothing 5]] - , ConstantAbstract $ AbsLitTuple [ConstantInt Nothing 5, ConstantAbstract $ AbsLitMatrix (intDomain 1 2) [ConstantInt Nothing 5, ConstantInt Nothing 6]] -||||||| merged common ancestors - [ ConstantAbstract $ AbsLitTuple [ConstantInt 2, ConstantAbstract $ AbsLitMatrix (intDomain 1 2) [ConstantInt 1, ConstantInt 3]] - , ConstantAbstract $ AbsLitTuple [ConstantInt 4, ConstantAbstract $ AbsLitMatrix (intDomain 1 2) [ConstantInt 3, ConstantInt 5]] - , ConstantAbstract $ AbsLitTuple [ConstantInt 5, ConstantAbstract $ AbsLitMatrix (intDomain 1 2) [ConstantInt 5, ConstantInt 6]] -======= - [ ConstantAbstract $ AbsLitTuple [(ConstantInt NoTag) 2, ConstantAbstract $ AbsLitMatrix (intDomain 1 2) [(ConstantInt NoTag) 1, (ConstantInt NoTag) 3]] - , ConstantAbstract $ AbsLitTuple [(ConstantInt NoTag) 4, ConstantAbstract $ AbsLitMatrix (intDomain 1 2) [(ConstantInt NoTag) 3, (ConstantInt NoTag) 5]] - , ConstantAbstract $ AbsLitTuple [(ConstantInt NoTag) 5, ConstantAbstract $ AbsLitMatrix (intDomain 1 2) [(ConstantInt NoTag) 5, (ConstantInt NoTag) 6]] ->>>>>>> taggedints - ] - ] ) - - , testCase "(bool, matrix of (int, matrix of int))" $ - let - highDomain = - DomainTuple - [ DomainBool - , DomainMatrix (intDomain 1 3) (DomainTuple - [ intDomain 0 9 - , DomainMatrix (intDomain 1 2) (intDomain 0 9) - ]) - ] - highConstant = - ConstantAbstract $ AbsLitTuple - [ ConstantBool False - , ConstantAbstract $ AbsLitMatrix (intDomain 1 3) -<<<<<<< HEAD - [ ConstantAbstract $ AbsLitTuple [ConstantInt Nothing 2, ConstantAbstract $ AbsLitMatrix (intDomain 1 2) [ConstantInt Nothing 1, ConstantInt Nothing 3]] - , ConstantAbstract $ AbsLitTuple [ConstantInt Nothing 4, ConstantAbstract $ AbsLitMatrix (intDomain 1 2) [ConstantInt Nothing 3, ConstantInt Nothing 5]] - , ConstantAbstract $ AbsLitTuple [ConstantInt Nothing 5, ConstantAbstract $ AbsLitMatrix (intDomain 1 2) [ConstantInt Nothing 5, ConstantInt Nothing 6]] -||||||| merged common ancestors - [ ConstantAbstract $ AbsLitTuple [ConstantInt 2, ConstantAbstract $ AbsLitMatrix (intDomain 1 2) [ConstantInt 1, ConstantInt 3]] - , ConstantAbstract $ AbsLitTuple [ConstantInt 4, ConstantAbstract $ AbsLitMatrix (intDomain 1 2) [ConstantInt 3, ConstantInt 5]] - , ConstantAbstract $ AbsLitTuple [ConstantInt 5, ConstantAbstract $ AbsLitMatrix (intDomain 1 2) [ConstantInt 5, ConstantInt 6]] -======= - [ ConstantAbstract $ AbsLitTuple [(ConstantInt NoTag) 2, ConstantAbstract $ AbsLitMatrix (intDomain 1 2) [(ConstantInt NoTag) 1, (ConstantInt NoTag) 3]] - , ConstantAbstract $ AbsLitTuple [(ConstantInt NoTag) 4, ConstantAbstract $ AbsLitMatrix (intDomain 1 2) [(ConstantInt NoTag) 3, (ConstantInt NoTag) 5]] - , ConstantAbstract $ AbsLitTuple [(ConstantInt NoTag) 5, ConstantAbstract $ AbsLitMatrix (intDomain 1 2) [(ConstantInt NoTag) 5, (ConstantInt NoTag) 6]] ->>>>>>> taggedints - ] - ] - mid = - [ ( "x_1" , DomainBool,ConstantBool False ) - , ( "x_2" , DomainMatrix (intDomain 1 3) (DomainTuple [intDomain 0 9,DomainMatrix (intDomain 1 2) (intDomain 0 9)]) - , ConstantAbstract $ AbsLitMatrix (intDomain 1 3) -<<<<<<< HEAD - [ ConstantAbstract $ AbsLitTuple [ConstantInt Nothing 2,ConstantAbstract $ AbsLitMatrix (intDomain 1 2) [ConstantInt Nothing 1,ConstantInt Nothing 3]] - , ConstantAbstract $ AbsLitTuple [ConstantInt Nothing 4,ConstantAbstract $ AbsLitMatrix (intDomain 1 2) [ConstantInt Nothing 3,ConstantInt Nothing 5]] - , ConstantAbstract $ AbsLitTuple [ConstantInt Nothing 5,ConstantAbstract $ AbsLitMatrix (intDomain 1 2) [ConstantInt Nothing 5,ConstantInt Nothing 6]] -||||||| merged common ancestors - [ ConstantAbstract $ AbsLitTuple [ConstantInt 2,ConstantAbstract $ AbsLitMatrix (intDomain 1 2) [ConstantInt 1,ConstantInt 3]] - , ConstantAbstract $ AbsLitTuple [ConstantInt 4,ConstantAbstract $ AbsLitMatrix (intDomain 1 2) [ConstantInt 3,ConstantInt 5]] - , ConstantAbstract $ AbsLitTuple [ConstantInt 5,ConstantAbstract $ AbsLitMatrix (intDomain 1 2) [ConstantInt 5,ConstantInt 6]] -======= - [ ConstantAbstract $ AbsLitTuple [(ConstantInt NoTag) 2,ConstantAbstract $ AbsLitMatrix (intDomain 1 2) [(ConstantInt NoTag) 1,(ConstantInt NoTag) 3]] - , ConstantAbstract $ AbsLitTuple [(ConstantInt NoTag) 4,ConstantAbstract $ AbsLitMatrix (intDomain 1 2) [(ConstantInt NoTag) 3,(ConstantInt NoTag) 5]] - , ConstantAbstract $ AbsLitTuple [(ConstantInt NoTag) 5,ConstantAbstract $ AbsLitMatrix (intDomain 1 2) [(ConstantInt NoTag) 5,(ConstantInt NoTag) 6]] ->>>>>>> taggedints - ] ) - ] - low = - [ ( "x_1" , DomainBool,ConstantBool False ) - , ( "x_2_1" , DomainMatrix (intDomain 1 3) (intDomain 0 9) -<<<<<<< HEAD - , ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantInt Nothing 2,ConstantInt Nothing 4,ConstantInt Nothing 5]) -||||||| merged common ancestors - , ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantInt 2,ConstantInt 4,ConstantInt 5]) -======= - , ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [(ConstantInt NoTag) 2,(ConstantInt NoTag) 4,(ConstantInt NoTag) 5]) ->>>>>>> taggedints - , ( "x_2_2" , DomainMatrix (intDomain 1 3) (DomainMatrix (intDomain 1 2) (intDomain 0 9)) - , ConstantAbstract $ AbsLitMatrix (intDomain 1 3) -<<<<<<< HEAD - [ ConstantAbstract $ AbsLitMatrix (intDomain 1 2) [ConstantInt Nothing 1,ConstantInt Nothing 3] - , ConstantAbstract $ AbsLitMatrix (intDomain 1 2) [ConstantInt Nothing 3,ConstantInt Nothing 5] - , ConstantAbstract $ AbsLitMatrix (intDomain 1 2) [ConstantInt Nothing 5,ConstantInt Nothing 6] -||||||| merged common ancestors - [ ConstantAbstract $ AbsLitMatrix (intDomain 1 2) [ConstantInt 1,ConstantInt 3] - , ConstantAbstract $ AbsLitMatrix (intDomain 1 2) [ConstantInt 3,ConstantInt 5] - , ConstantAbstract $ AbsLitMatrix (intDomain 1 2) [ConstantInt 5,ConstantInt 6] -======= - [ ConstantAbstract $ AbsLitMatrix (intDomain 1 2) [(ConstantInt NoTag) 1,(ConstantInt NoTag) 3] - , ConstantAbstract $ AbsLitMatrix (intDomain 1 2) [(ConstantInt NoTag) 3,(ConstantInt NoTag) 5] - , ConstantAbstract $ AbsLitMatrix (intDomain 1 2) [(ConstantInt NoTag) 5,(ConstantInt NoTag) 6] ->>>>>>> taggedints - ] ) - ] - in testCases "x" highDomain highConstant Just mid low - --- Explicit - , testCase "Explicit: set (size 4) of int {auto}" $ testCasesAuto "x" - ( DomainSet - Set_Explicit -<<<<<<< HEAD - (SetAttr (SizeAttr_Size (ConstantInt Nothing 4))) -||||||| merged common ancestors - (SetAttr (SizeAttr_Size (ConstantInt 4))) -======= - (SetAttr (SizeAttr_Size ((ConstantInt NoTag) 4))) ->>>>>>> taggedints - (intDomain 0 9) ) - ( ConstantAbstract $ AbsLitSet -<<<<<<< HEAD - [ConstantInt Nothing 2, ConstantInt Nothing 3, ConstantInt Nothing 5, ConstantInt Nothing 6] ) -||||||| merged common ancestors - [ConstantInt 2, ConstantInt 3, ConstantInt 5, ConstantInt 6] ) -======= - [(ConstantInt NoTag) 2, (ConstantInt NoTag) 3, (ConstantInt NoTag) 5, (ConstantInt NoTag) 6] ) ->>>>>>> taggedints - - , testCase "Explicit: set (size 4) of int" $ - let - highDomain = - DomainSet - Set_Explicit -<<<<<<< HEAD - (SetAttr (SizeAttr_Size (ConstantInt Nothing 4))) -||||||| merged common ancestors - (SetAttr (SizeAttr_Size (ConstantInt 4))) -======= - (SetAttr (SizeAttr_Size ((ConstantInt NoTag) 4))) ->>>>>>> taggedints - (intDomain 0 9) - highConstant = - ConstantAbstract $ AbsLitSet -<<<<<<< HEAD - [ConstantInt Nothing 2, ConstantInt Nothing 3, ConstantInt Nothing 5, ConstantInt Nothing 6] -||||||| merged common ancestors - [ConstantInt 2, ConstantInt 3, ConstantInt 5, ConstantInt 6] -======= - [(ConstantInt NoTag) 2, (ConstantInt NoTag) 3, (ConstantInt NoTag) 5, (ConstantInt NoTag) 6] ->>>>>>> taggedints - low = - [ ( "x_Explicit" - , DomainMatrix (intDomain 1 4) (intDomain 0 9) - , ConstantAbstract $ AbsLitMatrix (intDomain 1 4) -<<<<<<< HEAD - [ConstantInt Nothing 2,ConstantInt Nothing 3,ConstantInt Nothing 5,ConstantInt Nothing 6] -||||||| merged common ancestors - [ConstantInt 2,ConstantInt 3,ConstantInt 5,ConstantInt 6] -======= - [(ConstantInt NoTag) 2,(ConstantInt NoTag) 3,(ConstantInt NoTag) 5,(ConstantInt NoTag) 6] ->>>>>>> taggedints - ) ] - in testCases "x" highDomain highConstant Just low low - - , testCase "Explicit: set (size 4) of set (size 2) of int {auto}" $ testCasesAuto "x" -<<<<<<< HEAD - ( DomainSet Set_Explicit (SetAttr (SizeAttr_Size (ConstantInt Nothing 4))) - ( DomainSet Set_Explicit (SetAttr (SizeAttr_Size (ConstantInt Nothing 2))) -||||||| merged common ancestors - ( DomainSet Set_Explicit (SetAttr (SizeAttr_Size (ConstantInt 4))) - ( DomainSet Set_Explicit (SetAttr (SizeAttr_Size (ConstantInt 2))) -======= - ( DomainSet Set_Explicit (SetAttr (SizeAttr_Size ((ConstantInt NoTag) 4))) - ( DomainSet Set_Explicit (SetAttr (SizeAttr_Size ((ConstantInt NoTag) 2))) ->>>>>>> taggedints - (intDomain 0 9) - ) - ) - ( ConstantAbstract $ AbsLitSet -<<<<<<< HEAD - [ ConstantAbstract $ AbsLitSet [ConstantInt Nothing 2, ConstantInt Nothing 3] - , ConstantAbstract $ AbsLitSet [ConstantInt Nothing 5, ConstantInt Nothing 6] - , ConstantAbstract $ AbsLitSet [ConstantInt Nothing 5, ConstantInt Nothing 7] - , ConstantAbstract $ AbsLitSet [ConstantInt Nothing 5, ConstantInt Nothing 8] -||||||| merged common ancestors - [ ConstantAbstract $ AbsLitSet [ConstantInt 2, ConstantInt 3] - , ConstantAbstract $ AbsLitSet [ConstantInt 5, ConstantInt 6] - , ConstantAbstract $ AbsLitSet [ConstantInt 5, ConstantInt 7] - , ConstantAbstract $ AbsLitSet [ConstantInt 5, ConstantInt 8] -======= - [ ConstantAbstract $ AbsLitSet [(ConstantInt NoTag) 2, (ConstantInt NoTag) 3] - , ConstantAbstract $ AbsLitSet [(ConstantInt NoTag) 5, (ConstantInt NoTag) 6] - , ConstantAbstract $ AbsLitSet [(ConstantInt NoTag) 5, (ConstantInt NoTag) 7] - , ConstantAbstract $ AbsLitSet [(ConstantInt NoTag) 5, (ConstantInt NoTag) 8] ->>>>>>> taggedints - ] ) - - , testCase "Explicit: set (size 4) of set (size 2) of int" $ - let - highDomain = -<<<<<<< HEAD - DomainSet Set_Explicit (SetAttr (SizeAttr_Size (ConstantInt Nothing 4))) - (DomainSet Set_Explicit (SetAttr (SizeAttr_Size (ConstantInt Nothing 2))) -||||||| merged common ancestors - DomainSet Set_Explicit (SetAttr (SizeAttr_Size (ConstantInt 4))) - (DomainSet Set_Explicit (SetAttr (SizeAttr_Size (ConstantInt 2))) -======= - DomainSet Set_Explicit (SetAttr (SizeAttr_Size ((ConstantInt NoTag) 4))) - (DomainSet Set_Explicit (SetAttr (SizeAttr_Size ((ConstantInt NoTag) 2))) ->>>>>>> taggedints - (intDomain 0 9)) - highConstant = - ConstantAbstract $ AbsLitSet -<<<<<<< HEAD - [ ConstantAbstract $ AbsLitSet [ConstantInt Nothing 2, ConstantInt Nothing 3] - , ConstantAbstract $ AbsLitSet [ConstantInt Nothing 5, ConstantInt Nothing 6] - , ConstantAbstract $ AbsLitSet [ConstantInt Nothing 5, ConstantInt Nothing 7] - , ConstantAbstract $ AbsLitSet [ConstantInt Nothing 5, ConstantInt Nothing 8] -||||||| merged common ancestors - [ ConstantAbstract $ AbsLitSet [ConstantInt 2, ConstantInt 3] - , ConstantAbstract $ AbsLitSet [ConstantInt 5, ConstantInt 6] - , ConstantAbstract $ AbsLitSet [ConstantInt 5, ConstantInt 7] - , ConstantAbstract $ AbsLitSet [ConstantInt 5, ConstantInt 8] -======= - [ ConstantAbstract $ AbsLitSet [(ConstantInt NoTag) 2, (ConstantInt NoTag) 3] - , ConstantAbstract $ AbsLitSet [(ConstantInt NoTag) 5, (ConstantInt NoTag) 6] - , ConstantAbstract $ AbsLitSet [(ConstantInt NoTag) 5, (ConstantInt NoTag) 7] - , ConstantAbstract $ AbsLitSet [(ConstantInt NoTag) 5, (ConstantInt NoTag) 8] ->>>>>>> taggedints - ] - mid = - [ ( "x_ExplicitR3" -<<<<<<< HEAD - , DomainMatrix (intDomain 1 4) (DomainSet Set_Explicit (SetAttr (SizeAttr_Size (ConstantInt Nothing 2))) (intDomain 0 9)) -||||||| merged common ancestors - , DomainMatrix (intDomain 1 4) (DomainSet Set_Explicit (SetAttr (SizeAttr_Size (ConstantInt 2))) (intDomain 0 9)) -======= - , DomainMatrix (intDomain 1 4) (DomainSet Set_Explicit (SetAttr (SizeAttr_Size ((ConstantInt NoTag) 2))) (intDomain 0 9)) ->>>>>>> taggedints - , ConstantAbstract $ AbsLitMatrix (intDomain 1 4) -<<<<<<< HEAD - [ ConstantAbstract $ AbsLitSet [ConstantInt Nothing 2, ConstantInt Nothing 3] - , ConstantAbstract $ AbsLitSet [ConstantInt Nothing 5, ConstantInt Nothing 6] - , ConstantAbstract $ AbsLitSet [ConstantInt Nothing 5, ConstantInt Nothing 7] - , ConstantAbstract $ AbsLitSet [ConstantInt Nothing 5, ConstantInt Nothing 8] -||||||| merged common ancestors - [ ConstantAbstract $ AbsLitSet [ConstantInt 2, ConstantInt 3] - , ConstantAbstract $ AbsLitSet [ConstantInt 5, ConstantInt 6] - , ConstantAbstract $ AbsLitSet [ConstantInt 5, ConstantInt 7] - , ConstantAbstract $ AbsLitSet [ConstantInt 5, ConstantInt 8] -======= - [ ConstantAbstract $ AbsLitSet [(ConstantInt NoTag) 2, (ConstantInt NoTag) 3] - , ConstantAbstract $ AbsLitSet [(ConstantInt NoTag) 5, (ConstantInt NoTag) 6] - , ConstantAbstract $ AbsLitSet [(ConstantInt NoTag) 5, (ConstantInt NoTag) 7] - , ConstantAbstract $ AbsLitSet [(ConstantInt NoTag) 5, (ConstantInt NoTag) 8] ->>>>>>> taggedints - ] - ) ] - low = - [ ( "x_ExplicitR3_Explicit" - , DomainMatrix (intDomain 1 4) (DomainMatrix (intDomain 1 2) (intDomain 0 9)) - , ConstantAbstract $ AbsLitMatrix (intDomain 1 4) -<<<<<<< HEAD - [ ConstantAbstract $ AbsLitMatrix (intDomain 1 2) [ConstantInt Nothing 2, ConstantInt Nothing 3] - , ConstantAbstract $ AbsLitMatrix (intDomain 1 2) [ConstantInt Nothing 5, ConstantInt Nothing 6] - , ConstantAbstract $ AbsLitMatrix (intDomain 1 2) [ConstantInt Nothing 5, ConstantInt Nothing 7] - , ConstantAbstract $ AbsLitMatrix (intDomain 1 2) [ConstantInt Nothing 5, ConstantInt Nothing 8] -||||||| merged common ancestors - [ ConstantAbstract $ AbsLitMatrix (intDomain 1 2) [ConstantInt 2, ConstantInt 3] - , ConstantAbstract $ AbsLitMatrix (intDomain 1 2) [ConstantInt 5, ConstantInt 6] - , ConstantAbstract $ AbsLitMatrix (intDomain 1 2) [ConstantInt 5, ConstantInt 7] - , ConstantAbstract $ AbsLitMatrix (intDomain 1 2) [ConstantInt 5, ConstantInt 8] -======= - [ ConstantAbstract $ AbsLitMatrix (intDomain 1 2) [(ConstantInt NoTag) 2, (ConstantInt NoTag) 3] - , ConstantAbstract $ AbsLitMatrix (intDomain 1 2) [(ConstantInt NoTag) 5, (ConstantInt NoTag) 6] - , ConstantAbstract $ AbsLitMatrix (intDomain 1 2) [(ConstantInt NoTag) 5, (ConstantInt NoTag) 7] - , ConstantAbstract $ AbsLitMatrix (intDomain 1 2) [(ConstantInt NoTag) 5, (ConstantInt NoTag) 8] ->>>>>>> taggedints - ] - ) ] - in testCases "x" highDomain highConstant Just mid low - - , testCase "Explicit: set (size 4) of set (size 2) of (int, bool) {auto}" $ testCasesAuto "x" -<<<<<<< HEAD - ( DomainSet Set_Explicit (SetAttr (SizeAttr_Size (ConstantInt Nothing 4))) - ( DomainSet Set_Explicit (SetAttr (SizeAttr_Size (ConstantInt Nothing 2))) -||||||| merged common ancestors - ( DomainSet Set_Explicit (SetAttr (SizeAttr_Size (ConstantInt 4))) - ( DomainSet Set_Explicit (SetAttr (SizeAttr_Size (ConstantInt 2))) -======= - ( DomainSet Set_Explicit (SetAttr (SizeAttr_Size ((ConstantInt NoTag) 4))) - ( DomainSet Set_Explicit (SetAttr (SizeAttr_Size ((ConstantInt NoTag) 2))) ->>>>>>> taggedints - (DomainTuple [intDomain 0 9, DomainBool]) - ) - ) - ( ConstantAbstract $ AbsLitSet -<<<<<<< HEAD - [ ConstantAbstract $ AbsLitSet [ ConstantAbstract $ AbsLitTuple [ConstantInt Nothing 2, ConstantBool False] - , ConstantAbstract $ AbsLitTuple [ConstantInt Nothing 3, ConstantBool True ] -||||||| merged common ancestors - [ ConstantAbstract $ AbsLitSet [ ConstantAbstract $ AbsLitTuple [ConstantInt 2, ConstantBool False] - , ConstantAbstract $ AbsLitTuple [ConstantInt 3, ConstantBool True ] -======= - [ ConstantAbstract $ AbsLitSet [ ConstantAbstract $ AbsLitTuple [(ConstantInt NoTag) 2, ConstantBool False] - , ConstantAbstract $ AbsLitTuple [(ConstantInt NoTag) 3, ConstantBool True ] ->>>>>>> taggedints - ] -<<<<<<< HEAD - , ConstantAbstract $ AbsLitSet [ ConstantAbstract $ AbsLitTuple [ConstantInt Nothing 5, ConstantBool True ] - , ConstantAbstract $ AbsLitTuple [ConstantInt Nothing 6, ConstantBool True ] -||||||| merged common ancestors - , ConstantAbstract $ AbsLitSet [ ConstantAbstract $ AbsLitTuple [ConstantInt 5, ConstantBool True ] - , ConstantAbstract $ AbsLitTuple [ConstantInt 6, ConstantBool True ] -======= - , ConstantAbstract $ AbsLitSet [ ConstantAbstract $ AbsLitTuple [(ConstantInt NoTag) 5, ConstantBool True ] - , ConstantAbstract $ AbsLitTuple [(ConstantInt NoTag) 6, ConstantBool True ] ->>>>>>> taggedints - ] -<<<<<<< HEAD - , ConstantAbstract $ AbsLitSet [ ConstantAbstract $ AbsLitTuple [ConstantInt Nothing 5, ConstantBool True ] - , ConstantAbstract $ AbsLitTuple [ConstantInt Nothing 7, ConstantBool False] -||||||| merged common ancestors - , ConstantAbstract $ AbsLitSet [ ConstantAbstract $ AbsLitTuple [ConstantInt 5, ConstantBool True ] - , ConstantAbstract $ AbsLitTuple [ConstantInt 7, ConstantBool False] -======= - , ConstantAbstract $ AbsLitSet [ ConstantAbstract $ AbsLitTuple [(ConstantInt NoTag) 5, ConstantBool True ] - , ConstantAbstract $ AbsLitTuple [(ConstantInt NoTag) 7, ConstantBool False] ->>>>>>> taggedints - ] -<<<<<<< HEAD - , ConstantAbstract $ AbsLitSet [ ConstantAbstract $ AbsLitTuple [ConstantInt Nothing 5, ConstantBool False] - , ConstantAbstract $ AbsLitTuple [ConstantInt Nothing 8, ConstantBool False] -||||||| merged common ancestors - , ConstantAbstract $ AbsLitSet [ ConstantAbstract $ AbsLitTuple [ConstantInt 5, ConstantBool False] - , ConstantAbstract $ AbsLitTuple [ConstantInt 8, ConstantBool False] -======= - , ConstantAbstract $ AbsLitSet [ ConstantAbstract $ AbsLitTuple [(ConstantInt NoTag) 5, ConstantBool False] - , ConstantAbstract $ AbsLitTuple [(ConstantInt NoTag) 8, ConstantBool False] ->>>>>>> taggedints - ] - ] ) - - , testCase "Explicit: set (size 4) of (int, set (size 2) of (int, bool)) {auto}" $ testCasesAuto "x" -<<<<<<< HEAD - ( DomainSet Set_Explicit (SetAttr (SizeAttr_Size (ConstantInt Nothing 4))) -||||||| merged common ancestors - ( DomainSet Set_Explicit (SetAttr (SizeAttr_Size (ConstantInt 4))) -======= - ( DomainSet Set_Explicit (SetAttr (SizeAttr_Size ((ConstantInt NoTag) 4))) ->>>>>>> taggedints - ( DomainTuple - [ intDomain 0 8 -<<<<<<< HEAD - , DomainSet Set_Explicit (SetAttr (SizeAttr_Size (ConstantInt Nothing 2))) -||||||| merged common ancestors - , DomainSet Set_Explicit (SetAttr (SizeAttr_Size (ConstantInt 2))) -======= - , DomainSet Set_Explicit (SetAttr (SizeAttr_Size ((ConstantInt NoTag) 2))) ->>>>>>> taggedints - (DomainTuple [intDomain 0 9, DomainBool]) - ] - ) - ) - ( ConstantAbstract $ AbsLitSet - [ ConstantAbstract $ AbsLitTuple -<<<<<<< HEAD - [ ConstantInt Nothing 1 -||||||| merged common ancestors - [ ConstantInt 1 -======= - [ (ConstantInt NoTag) 1 ->>>>>>> taggedints - , ConstantAbstract $ AbsLitSet -<<<<<<< HEAD - [ ConstantAbstract $ AbsLitTuple [ConstantInt Nothing 2, ConstantBool False] - , ConstantAbstract $ AbsLitTuple [ConstantInt Nothing 3, ConstantBool True ] -||||||| merged common ancestors - [ ConstantAbstract $ AbsLitTuple [ConstantInt 2, ConstantBool False] - , ConstantAbstract $ AbsLitTuple [ConstantInt 3, ConstantBool True ] -======= - [ ConstantAbstract $ AbsLitTuple [(ConstantInt NoTag) 2, ConstantBool False] - , ConstantAbstract $ AbsLitTuple [(ConstantInt NoTag) 3, ConstantBool True ] ->>>>>>> taggedints - ] - ] - , ConstantAbstract $ AbsLitTuple -<<<<<<< HEAD - [ ConstantInt Nothing 2 -||||||| merged common ancestors - [ ConstantInt 2 -======= - [ (ConstantInt NoTag) 2 ->>>>>>> taggedints - , ConstantAbstract $ AbsLitSet -<<<<<<< HEAD - [ ConstantAbstract $ AbsLitTuple [ConstantInt Nothing 5, ConstantBool True ] - , ConstantAbstract $ AbsLitTuple [ConstantInt Nothing 6, ConstantBool True ] -||||||| merged common ancestors - [ ConstantAbstract $ AbsLitTuple [ConstantInt 5, ConstantBool True ] - , ConstantAbstract $ AbsLitTuple [ConstantInt 6, ConstantBool True ] -======= - [ ConstantAbstract $ AbsLitTuple [(ConstantInt NoTag) 5, ConstantBool True ] - , ConstantAbstract $ AbsLitTuple [(ConstantInt NoTag) 6, ConstantBool True ] ->>>>>>> taggedints - ] - ] - , ConstantAbstract $ AbsLitTuple -<<<<<<< HEAD - [ ConstantInt Nothing 3 -||||||| merged common ancestors - [ ConstantInt 3 -======= - [ (ConstantInt NoTag) 3 ->>>>>>> taggedints - , ConstantAbstract $ AbsLitSet -<<<<<<< HEAD - [ ConstantAbstract $ AbsLitTuple [ConstantInt Nothing 5, ConstantBool True ] - , ConstantAbstract $ AbsLitTuple [ConstantInt Nothing 7, ConstantBool False] -||||||| merged common ancestors - [ ConstantAbstract $ AbsLitTuple [ConstantInt 5, ConstantBool True ] - , ConstantAbstract $ AbsLitTuple [ConstantInt 7, ConstantBool False] -======= - [ ConstantAbstract $ AbsLitTuple [(ConstantInt NoTag) 5, ConstantBool True ] - , ConstantAbstract $ AbsLitTuple [(ConstantInt NoTag) 7, ConstantBool False] ->>>>>>> taggedints - ] - ] - , ConstantAbstract $ AbsLitTuple -<<<<<<< HEAD - [ ConstantInt Nothing 4 -||||||| merged common ancestors - [ ConstantInt 4 -======= - [ (ConstantInt NoTag) 4 ->>>>>>> taggedints - , ConstantAbstract $ AbsLitSet -<<<<<<< HEAD - [ ConstantAbstract $ AbsLitTuple [ConstantInt Nothing 5, ConstantBool False] - , ConstantAbstract $ AbsLitTuple [ConstantInt Nothing 8, ConstantBool False] -||||||| merged common ancestors - [ ConstantAbstract $ AbsLitTuple [ConstantInt 5, ConstantBool False] - , ConstantAbstract $ AbsLitTuple [ConstantInt 8, ConstantBool False] -======= - [ ConstantAbstract $ AbsLitTuple [(ConstantInt NoTag) 5, ConstantBool False] - , ConstantAbstract $ AbsLitTuple [(ConstantInt NoTag) 8, ConstantBool False] ->>>>>>> taggedints - ] - ] - ] ) - --- ExplicitVarSizeWithMarker - , testCase "ExplicitVarSizeWithMarker: set (maxSize 4) of int {auto}" $ testCasesAuto "x" - ( DomainSet - Set_ExplicitVarSizeWithMarker -<<<<<<< HEAD - (SetAttr (SizeAttr_MaxSize (ConstantInt Nothing 4))) -||||||| merged common ancestors - (SetAttr (SizeAttr_MaxSize (ConstantInt 4))) -======= - (SetAttr (SizeAttr_MaxSize ((ConstantInt NoTag) 4))) ->>>>>>> taggedints - (intDomain 0 9) ) -<<<<<<< HEAD - ( ConstantAbstract $ AbsLitSet [ConstantInt Nothing 2, ConstantInt Nothing 5] ) -||||||| merged common ancestors - ( ConstantAbstract $ AbsLitSet [ConstantInt 2, ConstantInt 5] ) -======= - ( ConstantAbstract $ AbsLitSet [(ConstantInt NoTag) 2, (ConstantInt NoTag) 5] ) ->>>>>>> taggedints - - , testCase "ExplicitVarSizeWithMarker: set (maxSize 4) of int" $ - let - highDomain = -<<<<<<< HEAD - DomainSet Set_ExplicitVarSizeWithMarker (SetAttr (SizeAttr_MaxSize (ConstantInt Nothing 4))) (intDomain 0 9) -||||||| merged common ancestors - DomainSet Set_ExplicitVarSizeWithMarker (SetAttr (SizeAttr_MaxSize (ConstantInt 4))) (intDomain 0 9) -======= - DomainSet Set_ExplicitVarSizeWithMarker (SetAttr (SizeAttr_MaxSize ((ConstantInt NoTag) 4))) (intDomain 0 9) ->>>>>>> taggedints - highConstant = -<<<<<<< HEAD - ConstantAbstract $ AbsLitSet [ConstantInt Nothing 2, ConstantInt Nothing 5] -||||||| merged common ancestors - ConstantAbstract $ AbsLitSet [ConstantInt 2, ConstantInt 5] -======= - ConstantAbstract $ AbsLitSet [(ConstantInt NoTag) 2, (ConstantInt NoTag) 5] ->>>>>>> taggedints - low = - [ ( "x_ExplicitVarSizeWithMarker_Marker" - , intDomain 0 4 -<<<<<<< HEAD - , ConstantInt Nothing 2 -||||||| merged common ancestors - , ConstantInt 2 -======= - , (ConstantInt NoTag) 2 ->>>>>>> taggedints - ) - , ( "x_ExplicitVarSizeWithMarker_Values" - , DomainMatrix (intDomain 1 4) (intDomain 0 9) -<<<<<<< HEAD - , ConstantAbstract $ AbsLitMatrix (intDomain 1 4) [ConstantInt Nothing 2,ConstantInt Nothing 5,ConstantInt Nothing 0,ConstantInt Nothing 0] -||||||| merged common ancestors - , ConstantAbstract $ AbsLitMatrix (intDomain 1 4) [ConstantInt 2,ConstantInt 5,ConstantInt 0,ConstantInt 0] -======= - , ConstantAbstract $ AbsLitMatrix (intDomain 1 4) [(ConstantInt NoTag) 2,(ConstantInt NoTag) 5,(ConstantInt NoTag) 0,(ConstantInt NoTag) 0] ->>>>>>> taggedints - ) - ] - in testCases "x" highDomain highConstant Just low low - - , testCase "ExplicitVarSizeWithMarker: set (maxSize 4) of set (maxSize 3) int {auto}" $ testCasesAuto "x" -<<<<<<< HEAD - ( DomainSet Set_ExplicitVarSizeWithMarker (SetAttr (SizeAttr_MaxSize (ConstantInt Nothing 4))) - ( DomainSet Set_ExplicitVarSizeWithMarker (SetAttr (SizeAttr_MaxSize (ConstantInt Nothing 3))) -||||||| merged common ancestors - ( DomainSet Set_ExplicitVarSizeWithMarker (SetAttr (SizeAttr_MaxSize (ConstantInt 4))) - ( DomainSet Set_ExplicitVarSizeWithMarker (SetAttr (SizeAttr_MaxSize (ConstantInt 3))) -======= - ( DomainSet Set_ExplicitVarSizeWithMarker (SetAttr (SizeAttr_MaxSize ((ConstantInt NoTag) 4))) - ( DomainSet Set_ExplicitVarSizeWithMarker (SetAttr (SizeAttr_MaxSize ((ConstantInt NoTag) 3))) ->>>>>>> taggedints - (intDomain 0 9) - ) - ) - ( ConstantAbstract $ AbsLitSet -<<<<<<< HEAD - [ ConstantAbstract $ AbsLitSet [ConstantInt Nothing 2] - , ConstantAbstract $ AbsLitSet [ConstantInt Nothing 2, ConstantInt Nothing 5] - , ConstantAbstract $ AbsLitSet [ConstantInt Nothing 3, ConstantInt Nothing 4, ConstantInt Nothing 6] -||||||| merged common ancestors - [ ConstantAbstract $ AbsLitSet [ConstantInt 2] - , ConstantAbstract $ AbsLitSet [ConstantInt 2, ConstantInt 5] - , ConstantAbstract $ AbsLitSet [ConstantInt 3, ConstantInt 4, ConstantInt 6] -======= - [ ConstantAbstract $ AbsLitSet [(ConstantInt NoTag) 2] - , ConstantAbstract $ AbsLitSet [(ConstantInt NoTag) 2, (ConstantInt NoTag) 5] - , ConstantAbstract $ AbsLitSet [(ConstantInt NoTag) 3, (ConstantInt NoTag) 4, (ConstantInt NoTag) 6] ->>>>>>> taggedints - ] - ) - - , testCase "ExplicitVarSizeWithMarker: set (maxSize 4) of set (maxSize 3) int" $ - let - highDomain = -<<<<<<< HEAD - DomainSet Set_ExplicitVarSizeWithMarker (SetAttr (SizeAttr_MaxSize (ConstantInt Nothing 4))) - ( DomainSet Set_ExplicitVarSizeWithMarker (SetAttr (SizeAttr_MaxSize (ConstantInt Nothing 3))) -||||||| merged common ancestors - DomainSet Set_ExplicitVarSizeWithMarker (SetAttr (SizeAttr_MaxSize (ConstantInt 4))) - ( DomainSet Set_ExplicitVarSizeWithMarker (SetAttr (SizeAttr_MaxSize (ConstantInt 3))) -======= - DomainSet Set_ExplicitVarSizeWithMarker (SetAttr (SizeAttr_MaxSize ((ConstantInt NoTag) 4))) - ( DomainSet Set_ExplicitVarSizeWithMarker (SetAttr (SizeAttr_MaxSize ((ConstantInt NoTag) 3))) ->>>>>>> taggedints - (intDomain 0 9) ) - highConstant = - ConstantAbstract $ AbsLitSet -<<<<<<< HEAD - [ ConstantAbstract $ AbsLitSet [ConstantInt Nothing 2] - , ConstantAbstract $ AbsLitSet [ConstantInt Nothing 2, ConstantInt Nothing 5] - , ConstantAbstract $ AbsLitSet [ConstantInt Nothing 3, ConstantInt Nothing 4, ConstantInt Nothing 6] -||||||| merged common ancestors - [ ConstantAbstract $ AbsLitSet [ConstantInt 2] - , ConstantAbstract $ AbsLitSet [ConstantInt 2, ConstantInt 5] - , ConstantAbstract $ AbsLitSet [ConstantInt 3, ConstantInt 4, ConstantInt 6] -======= - [ ConstantAbstract $ AbsLitSet [(ConstantInt NoTag) 2] - , ConstantAbstract $ AbsLitSet [(ConstantInt NoTag) 2, (ConstantInt NoTag) 5] - , ConstantAbstract $ AbsLitSet [(ConstantInt NoTag) 3, (ConstantInt NoTag) 4, (ConstantInt NoTag) 6] ->>>>>>> taggedints - ] - mid = - [ ( "x_ExplicitVarSizeWithMarkerR5_Marker" - , intDomain 0 4 -<<<<<<< HEAD - , ConstantInt Nothing 3 -||||||| merged common ancestors - , ConstantInt 3 -======= - , (ConstantInt NoTag) 3 ->>>>>>> taggedints - ) - , ( "x_ExplicitVarSizeWithMarkerR5_Values" -<<<<<<< HEAD - , DomainMatrix (intDomain 1 4) (DomainSet Set_ExplicitVarSizeWithMarker (SetAttr (SizeAttr_MaxSize (ConstantInt Nothing 3))) (intDomain 0 9)) -||||||| merged common ancestors - , DomainMatrix (intDomain 1 4) (DomainSet Set_ExplicitVarSizeWithMarker (SetAttr (SizeAttr_MaxSize (ConstantInt 3))) (intDomain 0 9)) -======= - , DomainMatrix (intDomain 1 4) (DomainSet Set_ExplicitVarSizeWithMarker (SetAttr (SizeAttr_MaxSize ((ConstantInt NoTag) 3))) (intDomain 0 9)) ->>>>>>> taggedints - , ConstantAbstract $ AbsLitMatrix (intDomain 1 4) -<<<<<<< HEAD - [ ConstantAbstract $ AbsLitSet [ConstantInt Nothing 2] - , ConstantAbstract $ AbsLitSet [ConstantInt Nothing 2,ConstantInt Nothing 5] - , ConstantAbstract $ AbsLitSet [ConstantInt Nothing 3,ConstantInt Nothing 4,ConstantInt Nothing 6] -||||||| merged common ancestors - [ ConstantAbstract $ AbsLitSet [ConstantInt 2] - , ConstantAbstract $ AbsLitSet [ConstantInt 2,ConstantInt 5] - , ConstantAbstract $ AbsLitSet [ConstantInt 3,ConstantInt 4,ConstantInt 6] -======= - [ ConstantAbstract $ AbsLitSet [(ConstantInt NoTag) 2] - , ConstantAbstract $ AbsLitSet [(ConstantInt NoTag) 2,(ConstantInt NoTag) 5] - , ConstantAbstract $ AbsLitSet [(ConstantInt NoTag) 3,(ConstantInt NoTag) 4,(ConstantInt NoTag) 6] ->>>>>>> taggedints - , ConstantAbstract $ AbsLitSet [] - ] - ) - ] - low = - [ ( "x_ExplicitVarSizeWithMarkerR5_Marker" - , intDomain 0 4 -<<<<<<< HEAD - , ConstantInt Nothing 3 -||||||| merged common ancestors - , ConstantInt 3 -======= - , (ConstantInt NoTag) 3 ->>>>>>> taggedints - ) - , ( "x_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker" - , DomainMatrix (intDomain 1 4) (intDomain 0 3) -<<<<<<< HEAD - , ConstantAbstract $ AbsLitMatrix (intDomain 1 4) [ConstantInt Nothing 1,ConstantInt Nothing 2,ConstantInt Nothing 3,ConstantInt Nothing 0] -||||||| merged common ancestors - , ConstantAbstract $ AbsLitMatrix (intDomain 1 4) [ConstantInt 1,ConstantInt 2,ConstantInt 3,ConstantInt 0] -======= - , ConstantAbstract $ AbsLitMatrix (intDomain 1 4) [(ConstantInt NoTag) 1,(ConstantInt NoTag) 2,(ConstantInt NoTag) 3,(ConstantInt NoTag) 0] ->>>>>>> taggedints - ) - , ( "x_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values" - , DomainMatrix (intDomain 1 4) (DomainMatrix (intDomain 1 3) (intDomain 0 9)) - , ConstantAbstract $ AbsLitMatrix (intDomain 1 4) -<<<<<<< HEAD - [ ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantInt Nothing 2,ConstantInt Nothing 0,ConstantInt Nothing 0] - , ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantInt Nothing 2,ConstantInt Nothing 5,ConstantInt Nothing 0] - , ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantInt Nothing 3,ConstantInt Nothing 4,ConstantInt Nothing 6] - , ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantInt Nothing 0,ConstantInt Nothing 0,ConstantInt Nothing 0] -||||||| merged common ancestors - [ ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantInt 2,ConstantInt 0,ConstantInt 0] - , ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantInt 2,ConstantInt 5,ConstantInt 0] - , ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantInt 3,ConstantInt 4,ConstantInt 6] - , ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantInt 0,ConstantInt 0,ConstantInt 0] -======= - [ ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [(ConstantInt NoTag) 2,(ConstantInt NoTag) 0,(ConstantInt NoTag) 0] - , ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [(ConstantInt NoTag) 2,(ConstantInt NoTag) 5,(ConstantInt NoTag) 0] - , ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [(ConstantInt NoTag) 3,(ConstantInt NoTag) 4,(ConstantInt NoTag) 6] - , ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [(ConstantInt NoTag) 0,(ConstantInt NoTag) 0,(ConstantInt NoTag) 0] ->>>>>>> taggedints - ] - ) - ] - in testCases "x" highDomain highConstant Just mid low - --- ExplicitVarSizeWithFlags - , testCase "ExplicitVarSizeWithFlags: set (maxSize 4) of int {auto}" $ testCasesAuto "x" - ( DomainSet - Set_ExplicitVarSizeWithFlags -<<<<<<< HEAD - (SetAttr (SizeAttr_MaxSize (ConstantInt Nothing 4))) -||||||| merged common ancestors - (SetAttr (SizeAttr_MaxSize (ConstantInt 4))) -======= - (SetAttr (SizeAttr_MaxSize ((ConstantInt NoTag) 4))) ->>>>>>> taggedints - (intDomain 0 9) ) -<<<<<<< HEAD - ( ConstantAbstract $ AbsLitSet [ConstantInt Nothing 2, ConstantInt Nothing 5] ) -||||||| merged common ancestors - ( ConstantAbstract $ AbsLitSet [ConstantInt 2, ConstantInt 5] ) -======= - ( ConstantAbstract $ AbsLitSet [(ConstantInt NoTag) 2, (ConstantInt NoTag) 5] ) ->>>>>>> taggedints - - , testCase "ExplicitVarSizeWithFlags: set (maxSize 4) of int" $ - let - highDomain = -<<<<<<< HEAD - DomainSet Set_ExplicitVarSizeWithFlags (SetAttr (SizeAttr_MaxSize (ConstantInt Nothing 4))) (intDomain 0 9) -||||||| merged common ancestors - DomainSet Set_ExplicitVarSizeWithFlags (SetAttr (SizeAttr_MaxSize (ConstantInt 4))) (intDomain 0 9) -======= - DomainSet Set_ExplicitVarSizeWithFlags (SetAttr (SizeAttr_MaxSize ((ConstantInt NoTag) 4))) (intDomain 0 9) ->>>>>>> taggedints - highConstant = -<<<<<<< HEAD - ConstantAbstract $ AbsLitSet [ConstantInt Nothing 2, ConstantInt Nothing 5] -||||||| merged common ancestors - ConstantAbstract $ AbsLitSet [ConstantInt 2, ConstantInt 5] -======= - ConstantAbstract $ AbsLitSet [(ConstantInt NoTag) 2, (ConstantInt NoTag) 5] ->>>>>>> taggedints - low = - [ ( "x_ExplicitVarSizeWithFlags_Flags" - , DomainMatrix (intDomain 1 4) DomainBool - , ConstantAbstract $ AbsLitMatrix (intDomain 1 4) [ConstantBool True,ConstantBool True,ConstantBool False,ConstantBool False] - ) - , ( "x_ExplicitVarSizeWithFlags_Values" - , DomainMatrix (intDomain 1 4) (intDomain 0 9) -<<<<<<< HEAD - , ConstantAbstract $ AbsLitMatrix (intDomain 1 4) [ConstantInt Nothing 2,ConstantInt Nothing 5,ConstantInt Nothing 0,ConstantInt Nothing 0] -||||||| merged common ancestors - , ConstantAbstract $ AbsLitMatrix (intDomain 1 4) [ConstantInt 2,ConstantInt 5,ConstantInt 0,ConstantInt 0] -======= - , ConstantAbstract $ AbsLitMatrix (intDomain 1 4) [(ConstantInt NoTag) 2,(ConstantInt NoTag) 5,(ConstantInt NoTag) 0,(ConstantInt NoTag) 0] ->>>>>>> taggedints - ) - ] - in testCases "x" highDomain highConstant Just low low - - , testCase "ExplicitVarSizeWithFlags: set (maxSize 4) of set (maxSize 3) int {auto}" $ testCasesAuto "x" -<<<<<<< HEAD - ( DomainSet Set_ExplicitVarSizeWithFlags (SetAttr (SizeAttr_MaxSize (ConstantInt Nothing 4))) - ( DomainSet Set_ExplicitVarSizeWithFlags (SetAttr (SizeAttr_MaxSize (ConstantInt Nothing 3))) -||||||| merged common ancestors - ( DomainSet Set_ExplicitVarSizeWithFlags (SetAttr (SizeAttr_MaxSize (ConstantInt 4))) - ( DomainSet Set_ExplicitVarSizeWithFlags (SetAttr (SizeAttr_MaxSize (ConstantInt 3))) -======= - ( DomainSet Set_ExplicitVarSizeWithFlags (SetAttr (SizeAttr_MaxSize ((ConstantInt NoTag) 4))) - ( DomainSet Set_ExplicitVarSizeWithFlags (SetAttr (SizeAttr_MaxSize ((ConstantInt NoTag) 3))) ->>>>>>> taggedints - (intDomain 0 9) - ) - ) - ( ConstantAbstract $ AbsLitSet -<<<<<<< HEAD - [ ConstantAbstract $ AbsLitSet [ConstantInt Nothing 2] - , ConstantAbstract $ AbsLitSet [ConstantInt Nothing 2, ConstantInt Nothing 5] - , ConstantAbstract $ AbsLitSet [ConstantInt Nothing 3, ConstantInt Nothing 4, ConstantInt Nothing 6] -||||||| merged common ancestors - [ ConstantAbstract $ AbsLitSet [ConstantInt 2] - , ConstantAbstract $ AbsLitSet [ConstantInt 2, ConstantInt 5] - , ConstantAbstract $ AbsLitSet [ConstantInt 3, ConstantInt 4, ConstantInt 6] -======= - [ ConstantAbstract $ AbsLitSet [(ConstantInt NoTag) 2] - , ConstantAbstract $ AbsLitSet [(ConstantInt NoTag) 2, (ConstantInt NoTag) 5] - , ConstantAbstract $ AbsLitSet [(ConstantInt NoTag) 3, (ConstantInt NoTag) 4, (ConstantInt NoTag) 6] ->>>>>>> taggedints - ] - ) - - , testCase "ExplicitVarSizeWithFlags: set (maxSize 4) of set (maxSize 3) int" $ - let - highDomain = -<<<<<<< HEAD - DomainSet Set_ExplicitVarSizeWithFlags (SetAttr (SizeAttr_MaxSize (ConstantInt Nothing 4))) - ( DomainSet Set_ExplicitVarSizeWithFlags (SetAttr (SizeAttr_MaxSize (ConstantInt Nothing 3))) -||||||| merged common ancestors - DomainSet Set_ExplicitVarSizeWithFlags (SetAttr (SizeAttr_MaxSize (ConstantInt 4))) - ( DomainSet Set_ExplicitVarSizeWithFlags (SetAttr (SizeAttr_MaxSize (ConstantInt 3))) -======= - DomainSet Set_ExplicitVarSizeWithFlags (SetAttr (SizeAttr_MaxSize ((ConstantInt NoTag) 4))) - ( DomainSet Set_ExplicitVarSizeWithFlags (SetAttr (SizeAttr_MaxSize ((ConstantInt NoTag) 3))) ->>>>>>> taggedints - (intDomain 0 9) ) - highConstant = - ConstantAbstract $ AbsLitSet -<<<<<<< HEAD - [ ConstantAbstract $ AbsLitSet [ConstantInt Nothing 2] - , ConstantAbstract $ AbsLitSet [ConstantInt Nothing 2, ConstantInt Nothing 5] - , ConstantAbstract $ AbsLitSet [ConstantInt Nothing 3, ConstantInt Nothing 4, ConstantInt Nothing 6] -||||||| merged common ancestors - [ ConstantAbstract $ AbsLitSet [ConstantInt 2] - , ConstantAbstract $ AbsLitSet [ConstantInt 2, ConstantInt 5] - , ConstantAbstract $ AbsLitSet [ConstantInt 3, ConstantInt 4, ConstantInt 6] -======= - [ ConstantAbstract $ AbsLitSet [(ConstantInt NoTag) 2] - , ConstantAbstract $ AbsLitSet [(ConstantInt NoTag) 2, (ConstantInt NoTag) 5] - , ConstantAbstract $ AbsLitSet [(ConstantInt NoTag) 3, (ConstantInt NoTag) 4, (ConstantInt NoTag) 6] ->>>>>>> taggedints - ] - mid = - [ ( "x_ExplicitVarSizeWithFlagsR4_Flags" - , DomainMatrix (intDomain 1 4) DomainBool - , ConstantAbstract $ AbsLitMatrix (intDomain 1 4) [ConstantBool True,ConstantBool True,ConstantBool True,ConstantBool False] - ) - , ( "x_ExplicitVarSizeWithFlagsR4_Values" -<<<<<<< HEAD - , DomainMatrix (intDomain 1 4) (DomainSet Set_ExplicitVarSizeWithFlags (SetAttr (SizeAttr_MaxSize (ConstantInt Nothing 3))) (intDomain 0 9)) -||||||| merged common ancestors - , DomainMatrix (intDomain 1 4) (DomainSet Set_ExplicitVarSizeWithFlags (SetAttr (SizeAttr_MaxSize (ConstantInt 3))) (intDomain 0 9)) -======= - , DomainMatrix (intDomain 1 4) (DomainSet Set_ExplicitVarSizeWithFlags (SetAttr (SizeAttr_MaxSize ((ConstantInt NoTag) 3))) (intDomain 0 9)) ->>>>>>> taggedints - , ConstantAbstract $ AbsLitMatrix (intDomain 1 4) -<<<<<<< HEAD - [ ConstantAbstract $ AbsLitSet [ConstantInt Nothing 2] - , ConstantAbstract $ AbsLitSet [ConstantInt Nothing 2,ConstantInt Nothing 5] - , ConstantAbstract $ AbsLitSet [ConstantInt Nothing 3,ConstantInt Nothing 4,ConstantInt Nothing 6] -||||||| merged common ancestors - [ ConstantAbstract $ AbsLitSet [ConstantInt 2] - , ConstantAbstract $ AbsLitSet [ConstantInt 2,ConstantInt 5] - , ConstantAbstract $ AbsLitSet [ConstantInt 3,ConstantInt 4,ConstantInt 6] -======= - [ ConstantAbstract $ AbsLitSet [(ConstantInt NoTag) 2] - , ConstantAbstract $ AbsLitSet [(ConstantInt NoTag) 2,(ConstantInt NoTag) 5] - , ConstantAbstract $ AbsLitSet [(ConstantInt NoTag) 3,(ConstantInt NoTag) 4,(ConstantInt NoTag) 6] ->>>>>>> taggedints - , ConstantAbstract $ AbsLitSet [] - ] - ) - ] - low = - [ ( "x_ExplicitVarSizeWithFlagsR4_Flags" - , DomainMatrix (intDomain 1 4) DomainBool - , ConstantAbstract $ AbsLitMatrix (intDomain 1 4) [ConstantBool True,ConstantBool True,ConstantBool True,ConstantBool False] - ) - , ( "x_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Flags" - , DomainMatrix (intDomain 1 4) (DomainMatrix (intDomain 1 3) DomainBool) - , ConstantAbstract $ AbsLitMatrix (intDomain 1 4) - [ ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantBool True,ConstantBool False,ConstantBool False] - , ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantBool True,ConstantBool True,ConstantBool False] - , ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantBool True,ConstantBool True,ConstantBool True] - , ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantBool False,ConstantBool False,ConstantBool False] - ] - ) - , ( "x_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Values" - , DomainMatrix (intDomain 1 4) (DomainMatrix (intDomain 1 3) (intDomain 0 9)) - , ConstantAbstract $ AbsLitMatrix (intDomain 1 4) -<<<<<<< HEAD - [ ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantInt Nothing 2,ConstantInt Nothing 0,ConstantInt Nothing 0] - , ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantInt Nothing 2,ConstantInt Nothing 5,ConstantInt Nothing 0] - , ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantInt Nothing 3,ConstantInt Nothing 4,ConstantInt Nothing 6] - , ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantInt Nothing 0,ConstantInt Nothing 0,ConstantInt Nothing 0] -||||||| merged common ancestors - [ ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantInt 2,ConstantInt 0,ConstantInt 0] - , ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantInt 2,ConstantInt 5,ConstantInt 0] - , ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantInt 3,ConstantInt 4,ConstantInt 6] - , ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [ConstantInt 0,ConstantInt 0,ConstantInt 0] -======= - [ ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [(ConstantInt NoTag) 2,(ConstantInt NoTag) 0,(ConstantInt NoTag) 0] - , ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [(ConstantInt NoTag) 2,(ConstantInt NoTag) 5,(ConstantInt NoTag) 0] - , ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [(ConstantInt NoTag) 3,(ConstantInt NoTag) 4,(ConstantInt NoTag) 6] - , ConstantAbstract $ AbsLitMatrix (intDomain 1 3) [(ConstantInt NoTag) 0,(ConstantInt NoTag) 0,(ConstantInt NoTag) 0] ->>>>>>> taggedints - ] - ) ] - in testCases "x" highDomain highConstant Just mid low - --- Occurrence - , testCase "Occurrence: set (maxSize 4) of int {auto}" $ testCasesAuto "x" - ( DomainSet - Set_Occurrence -<<<<<<< HEAD - (SetAttr (SizeAttr_MaxSize (ConstantInt Nothing 4))) -||||||| merged common ancestors - (SetAttr (SizeAttr_MaxSize (ConstantInt 4))) -======= - (SetAttr (SizeAttr_MaxSize ((ConstantInt NoTag) 4))) ->>>>>>> taggedints - (intDomain 0 9) ) -<<<<<<< HEAD - ( ConstantAbstract $ AbsLitSet [ConstantInt Nothing 2, ConstantInt Nothing 5] ) -||||||| merged common ancestors - ( ConstantAbstract $ AbsLitSet [ConstantInt 2, ConstantInt 5] ) -======= - ( ConstantAbstract $ AbsLitSet [(ConstantInt NoTag) 2, (ConstantInt NoTag) 5] ) ->>>>>>> taggedints - - , testCase "Occurrence: set (maxSize 4) of int" $ - let - highDomain = -<<<<<<< HEAD - DomainSet Set_Occurrence (SetAttr (SizeAttr_MaxSize (ConstantInt Nothing 4))) (intDomain 0 9) -||||||| merged common ancestors - DomainSet Set_Occurrence (SetAttr (SizeAttr_MaxSize (ConstantInt 4))) (intDomain 0 9) -======= - DomainSet Set_Occurrence (SetAttr (SizeAttr_MaxSize ((ConstantInt NoTag) 4))) (intDomain 0 9) ->>>>>>> taggedints - highConstant = -<<<<<<< HEAD - ConstantAbstract $ AbsLitSet [ConstantInt Nothing 2, ConstantInt Nothing 5] -||||||| merged common ancestors - ConstantAbstract $ AbsLitSet [ConstantInt 2, ConstantInt 5] -======= - ConstantAbstract $ AbsLitSet [(ConstantInt NoTag) 2, (ConstantInt NoTag) 5] ->>>>>>> taggedints - low = - [ ( "x_Occurrence" - , DomainMatrix (intDomain 0 9) DomainBool - , ConstantAbstract $ AbsLitMatrix (intDomain 0 9) - [ ConstantBool False - , ConstantBool False - , ConstantBool True -- 2 - , ConstantBool False - , ConstantBool False - , ConstantBool True -- 5 - , ConstantBool False - , ConstantBool False - , ConstantBool False - , ConstantBool False - ] - ) - ] - in testCases "x" highDomain highConstant Just low low - - , testCase "ExplicitVarSizeWithMarker & Occurrence: set (maxSize 4) of set (maxSize 3) int {auto}" $ testCasesAuto "x" -<<<<<<< HEAD - ( DomainSet Set_ExplicitVarSizeWithMarker (SetAttr (SizeAttr_MaxSize (ConstantInt Nothing 4))) - ( DomainSet Set_Occurrence (SetAttr (SizeAttr_MaxSize (ConstantInt Nothing 3))) -||||||| merged common ancestors - ( DomainSet Set_ExplicitVarSizeWithMarker (SetAttr (SizeAttr_MaxSize (ConstantInt 4))) - ( DomainSet Set_Occurrence (SetAttr (SizeAttr_MaxSize (ConstantInt 3))) -======= - ( DomainSet Set_ExplicitVarSizeWithMarker (SetAttr (SizeAttr_MaxSize ((ConstantInt NoTag) 4))) - ( DomainSet Set_Occurrence (SetAttr (SizeAttr_MaxSize ((ConstantInt NoTag) 3))) ->>>>>>> taggedints - (intDomain 0 9) - ) - ) - ( ConstantAbstract $ AbsLitSet -<<<<<<< HEAD - [ ConstantAbstract $ AbsLitSet [ConstantInt Nothing 2] - , ConstantAbstract $ AbsLitSet [ConstantInt Nothing 2, ConstantInt Nothing 5] - , ConstantAbstract $ AbsLitSet [ConstantInt Nothing 3, ConstantInt Nothing 4, ConstantInt Nothing 6] -||||||| merged common ancestors - [ ConstantAbstract $ AbsLitSet [ConstantInt 2] - , ConstantAbstract $ AbsLitSet [ConstantInt 2, ConstantInt 5] - , ConstantAbstract $ AbsLitSet [ConstantInt 3, ConstantInt 4, ConstantInt 6] -======= - [ ConstantAbstract $ AbsLitSet [(ConstantInt NoTag) 2] - , ConstantAbstract $ AbsLitSet [(ConstantInt NoTag) 2, (ConstantInt NoTag) 5] - , ConstantAbstract $ AbsLitSet [(ConstantInt NoTag) 3, (ConstantInt NoTag) 4, (ConstantInt NoTag) 6] ->>>>>>> taggedints - ] - ) - - , testCase "ExplicitVarSizeWithMarker & Occurrence: set (maxSize 4) of set (maxSize 3) int" $ - let - highDomain = -<<<<<<< HEAD - DomainSet Set_ExplicitVarSizeWithMarker (SetAttr (SizeAttr_MaxSize (ConstantInt Nothing 4))) - ( DomainSet Set_Occurrence (SetAttr (SizeAttr_MaxSize (ConstantInt Nothing 3))) -||||||| merged common ancestors - DomainSet Set_ExplicitVarSizeWithMarker (SetAttr (SizeAttr_MaxSize (ConstantInt 4))) - ( DomainSet Set_Occurrence (SetAttr (SizeAttr_MaxSize (ConstantInt 3))) -======= - DomainSet Set_ExplicitVarSizeWithMarker (SetAttr (SizeAttr_MaxSize ((ConstantInt NoTag) 4))) - ( DomainSet Set_Occurrence (SetAttr (SizeAttr_MaxSize ((ConstantInt NoTag) 3))) ->>>>>>> taggedints - (intDomain 0 9) ) - highConstant = - ConstantAbstract $ AbsLitSet -<<<<<<< HEAD - [ ConstantAbstract $ AbsLitSet [ConstantInt Nothing 2] - , ConstantAbstract $ AbsLitSet [ConstantInt Nothing 2, ConstantInt Nothing 5] - , ConstantAbstract $ AbsLitSet [ConstantInt Nothing 3, ConstantInt Nothing 4, ConstantInt Nothing 6] -||||||| merged common ancestors - [ ConstantAbstract $ AbsLitSet [ConstantInt 2] - , ConstantAbstract $ AbsLitSet [ConstantInt 2, ConstantInt 5] - , ConstantAbstract $ AbsLitSet [ConstantInt 3, ConstantInt 4, ConstantInt 6] -======= - [ ConstantAbstract $ AbsLitSet [(ConstantInt NoTag) 2] - , ConstantAbstract $ AbsLitSet [(ConstantInt NoTag) 2, (ConstantInt NoTag) 5] - , ConstantAbstract $ AbsLitSet [(ConstantInt NoTag) 3, (ConstantInt NoTag) 4, (ConstantInt NoTag) 6] ->>>>>>> taggedints - ] - mid = - [ ( "x_ExplicitVarSizeWithMarkerR2_Marker" - , intDomain 0 4 -<<<<<<< HEAD - , ConstantInt Nothing 3 -||||||| merged common ancestors - , ConstantInt 3 -======= - , (ConstantInt NoTag) 3 ->>>>>>> taggedints - ) - , ( "x_ExplicitVarSizeWithMarkerR2_Values" -<<<<<<< HEAD - , DomainMatrix (intDomain 1 4) (DomainSet Set_Occurrence (SetAttr (SizeAttr_MaxSize (ConstantInt Nothing 3))) (intDomain 0 9)) -||||||| merged common ancestors - , DomainMatrix (intDomain 1 4) (DomainSet Set_Occurrence (SetAttr (SizeAttr_MaxSize (ConstantInt 3))) (intDomain 0 9)) -======= - , DomainMatrix (intDomain 1 4) (DomainSet Set_Occurrence (SetAttr (SizeAttr_MaxSize ((ConstantInt NoTag) 3))) (intDomain 0 9)) ->>>>>>> taggedints - , ConstantAbstract $ AbsLitMatrix (intDomain 1 4) -<<<<<<< HEAD - [ ConstantAbstract $ AbsLitSet [ConstantInt Nothing 2] - , ConstantAbstract $ AbsLitSet [ConstantInt Nothing 2,ConstantInt Nothing 5] - , ConstantAbstract $ AbsLitSet [ConstantInt Nothing 3,ConstantInt Nothing 4,ConstantInt Nothing 6] -||||||| merged common ancestors - [ ConstantAbstract $ AbsLitSet [ConstantInt 2] - , ConstantAbstract $ AbsLitSet [ConstantInt 2,ConstantInt 5] - , ConstantAbstract $ AbsLitSet [ConstantInt 3,ConstantInt 4,ConstantInt 6] -======= - [ ConstantAbstract $ AbsLitSet [(ConstantInt NoTag) 2] - , ConstantAbstract $ AbsLitSet [(ConstantInt NoTag) 2,(ConstantInt NoTag) 5] - , ConstantAbstract $ AbsLitSet [(ConstantInt NoTag) 3,(ConstantInt NoTag) 4,(ConstantInt NoTag) 6] ->>>>>>> taggedints - , ConstantAbstract $ AbsLitSet [] - ] - ) - ] - low = - [ ( "x_ExplicitVarSizeWithMarkerR2_Marker" - , intDomain 0 4 -<<<<<<< HEAD - , ConstantInt Nothing 3 -||||||| merged common ancestors - , ConstantInt 3 -======= - , (ConstantInt NoTag) 3 ->>>>>>> taggedints - ) - , ( "x_ExplicitVarSizeWithMarkerR2_Values_Occurrence" - , DomainMatrix (intDomain 1 4) (DomainMatrix (intDomain 0 9) DomainBool) - , ConstantAbstract $ AbsLitMatrix (intDomain 1 4) - [ ConstantAbstract $ AbsLitMatrix (intDomain 0 9) -- 2 - [ ConstantBool False, ConstantBool False, ConstantBool True , ConstantBool False, ConstantBool False - , ConstantBool False, ConstantBool False, ConstantBool False, ConstantBool False, ConstantBool False ] - , ConstantAbstract $ AbsLitMatrix (intDomain 0 9) -- 2,5 - [ ConstantBool False, ConstantBool False, ConstantBool True , ConstantBool False, ConstantBool False - , ConstantBool True , ConstantBool False, ConstantBool False, ConstantBool False, ConstantBool False ] - , ConstantAbstract $ AbsLitMatrix (intDomain 0 9) -- 3,4,6 - [ ConstantBool False, ConstantBool False, ConstantBool False, ConstantBool True , ConstantBool True - , ConstantBool False, ConstantBool True , ConstantBool False, ConstantBool False, ConstantBool False ] - , ConstantAbstract $ AbsLitMatrix (intDomain 0 9) -- {} - [ ConstantBool False, ConstantBool False, ConstantBool False, ConstantBool False, ConstantBool False - , ConstantBool False, ConstantBool False, ConstantBool False, ConstantBool False, ConstantBool False ] - ] - ) - ] - in testCases "x" highDomain highConstant Just mid low - - , testCase "ExplicitVarSizeWithFlags & Occurrence: set (maxSize 4) of set (maxSize 3) int {auto}" $ testCasesAuto "x" -<<<<<<< HEAD - ( DomainSet Set_ExplicitVarSizeWithFlags (SetAttr (SizeAttr_MaxSize (ConstantInt Nothing 4))) - ( DomainSet Set_Occurrence (SetAttr (SizeAttr_MaxSize (ConstantInt Nothing 3))) -||||||| merged common ancestors - ( DomainSet Set_ExplicitVarSizeWithFlags (SetAttr (SizeAttr_MaxSize (ConstantInt 4))) - ( DomainSet Set_Occurrence (SetAttr (SizeAttr_MaxSize (ConstantInt 3))) -======= - ( DomainSet Set_ExplicitVarSizeWithFlags (SetAttr (SizeAttr_MaxSize ((ConstantInt NoTag) 4))) - ( DomainSet Set_Occurrence (SetAttr (SizeAttr_MaxSize ((ConstantInt NoTag) 3))) ->>>>>>> taggedints - (intDomain 0 9) - ) - ) - ( ConstantAbstract $ AbsLitSet -<<<<<<< HEAD - [ ConstantAbstract $ AbsLitSet [ConstantInt Nothing 2] - , ConstantAbstract $ AbsLitSet [ConstantInt Nothing 2, ConstantInt Nothing 5] - , ConstantAbstract $ AbsLitSet [ConstantInt Nothing 3, ConstantInt Nothing 4, ConstantInt Nothing 6] -||||||| merged common ancestors - [ ConstantAbstract $ AbsLitSet [ConstantInt 2] - , ConstantAbstract $ AbsLitSet [ConstantInt 2, ConstantInt 5] - , ConstantAbstract $ AbsLitSet [ConstantInt 3, ConstantInt 4, ConstantInt 6] -======= - [ ConstantAbstract $ AbsLitSet [(ConstantInt NoTag) 2] - , ConstantAbstract $ AbsLitSet [(ConstantInt NoTag) 2, (ConstantInt NoTag) 5] - , ConstantAbstract $ AbsLitSet [(ConstantInt NoTag) 3, (ConstantInt NoTag) 4, (ConstantInt NoTag) 6] ->>>>>>> taggedints - ] - ) - - , testCase "ExplicitVarSizeWithFlags & Occurrence: set (maxSize 4) of set (maxSize 3) int" $ - let - highDomain = -<<<<<<< HEAD - DomainSet Set_ExplicitVarSizeWithFlags (SetAttr (SizeAttr_MaxSize (ConstantInt Nothing 4))) - ( DomainSet Set_Occurrence (SetAttr (SizeAttr_MaxSize (ConstantInt Nothing 3))) -||||||| merged common ancestors - DomainSet Set_ExplicitVarSizeWithFlags (SetAttr (SizeAttr_MaxSize (ConstantInt 4))) - ( DomainSet Set_Occurrence (SetAttr (SizeAttr_MaxSize (ConstantInt 3))) -======= - DomainSet Set_ExplicitVarSizeWithFlags (SetAttr (SizeAttr_MaxSize ((ConstantInt NoTag) 4))) - ( DomainSet Set_Occurrence (SetAttr (SizeAttr_MaxSize ((ConstantInt NoTag) 3))) ->>>>>>> taggedints - (intDomain 0 9) ) - highConstant = - ConstantAbstract $ AbsLitSet -<<<<<<< HEAD - [ ConstantAbstract $ AbsLitSet [ConstantInt Nothing 2] - , ConstantAbstract $ AbsLitSet [ConstantInt Nothing 2, ConstantInt Nothing 5] - , ConstantAbstract $ AbsLitSet [ConstantInt Nothing 3, ConstantInt Nothing 4, ConstantInt Nothing 6] -||||||| merged common ancestors - [ ConstantAbstract $ AbsLitSet [ConstantInt 2] - , ConstantAbstract $ AbsLitSet [ConstantInt 2, ConstantInt 5] - , ConstantAbstract $ AbsLitSet [ConstantInt 3, ConstantInt 4, ConstantInt 6] -======= - [ ConstantAbstract $ AbsLitSet [(ConstantInt NoTag) 2] - , ConstantAbstract $ AbsLitSet [(ConstantInt NoTag) 2, (ConstantInt NoTag) 5] - , ConstantAbstract $ AbsLitSet [(ConstantInt NoTag) 3, (ConstantInt NoTag) 4, (ConstantInt NoTag) 6] ->>>>>>> taggedints - ] - mid = - [ ( "x_ExplicitVarSizeWithFlagsR2_Flags" - , DomainMatrix (intDomain 1 4) DomainBool - , ConstantAbstract $ AbsLitMatrix (intDomain 1 4) [ConstantBool True,ConstantBool True,ConstantBool True,ConstantBool False] - ) - , ( "x_ExplicitVarSizeWithFlagsR2_Values" -<<<<<<< HEAD - , DomainMatrix (intDomain 1 4) (DomainSet Set_Occurrence (SetAttr (SizeAttr_MaxSize (ConstantInt Nothing 3))) (intDomain 0 9)) -||||||| merged common ancestors - , DomainMatrix (intDomain 1 4) (DomainSet Set_Occurrence (SetAttr (SizeAttr_MaxSize (ConstantInt 3))) (intDomain 0 9)) -======= - , DomainMatrix (intDomain 1 4) (DomainSet Set_Occurrence (SetAttr (SizeAttr_MaxSize ((ConstantInt NoTag) 3))) (intDomain 0 9)) ->>>>>>> taggedints - , ConstantAbstract $ AbsLitMatrix (intDomain 1 4) -<<<<<<< HEAD - [ ConstantAbstract $ AbsLitSet [ConstantInt Nothing 2] - , ConstantAbstract $ AbsLitSet [ConstantInt Nothing 2,ConstantInt Nothing 5] - , ConstantAbstract $ AbsLitSet [ConstantInt Nothing 3,ConstantInt Nothing 4,ConstantInt Nothing 6] -||||||| merged common ancestors - [ ConstantAbstract $ AbsLitSet [ConstantInt 2] - , ConstantAbstract $ AbsLitSet [ConstantInt 2,ConstantInt 5] - , ConstantAbstract $ AbsLitSet [ConstantInt 3,ConstantInt 4,ConstantInt 6] -======= - [ ConstantAbstract $ AbsLitSet [(ConstantInt NoTag) 2] - , ConstantAbstract $ AbsLitSet [(ConstantInt NoTag) 2,(ConstantInt NoTag) 5] - , ConstantAbstract $ AbsLitSet [(ConstantInt NoTag) 3,(ConstantInt NoTag) 4,(ConstantInt NoTag) 6] ->>>>>>> taggedints - , ConstantAbstract $ AbsLitSet [] - ] - ) - ] - low = - [ ( "x_ExplicitVarSizeWithFlagsR2_Flags" - , DomainMatrix (intDomain 1 4) DomainBool - , ConstantAbstract $ AbsLitMatrix (intDomain 1 4) [ConstantBool True,ConstantBool True,ConstantBool True,ConstantBool False] - ) - , ( "x_ExplicitVarSizeWithFlagsR2_Values_Occurrence" - , DomainMatrix (intDomain 1 4) (DomainMatrix (intDomain 0 9) DomainBool) - , ConstantAbstract $ AbsLitMatrix (intDomain 1 4) - [ ConstantAbstract $ AbsLitMatrix (intDomain 0 9) -- 2 - [ ConstantBool False, ConstantBool False, ConstantBool True , ConstantBool False, ConstantBool False - , ConstantBool False, ConstantBool False, ConstantBool False, ConstantBool False, ConstantBool False ] - , ConstantAbstract $ AbsLitMatrix (intDomain 0 9) -- 2,5 - [ ConstantBool False, ConstantBool False, ConstantBool True , ConstantBool False, ConstantBool False - , ConstantBool True , ConstantBool False, ConstantBool False, ConstantBool False, ConstantBool False ] - , ConstantAbstract $ AbsLitMatrix (intDomain 0 9) -- 3,4,6 - [ ConstantBool False, ConstantBool False, ConstantBool False, ConstantBool True , ConstantBool True - , ConstantBool False, ConstantBool True , ConstantBool False, ConstantBool False, ConstantBool False ] - , ConstantAbstract $ AbsLitMatrix (intDomain 0 9) -- {} - [ ConstantBool False, ConstantBool False, ConstantBool False, ConstantBool False, ConstantBool False - , ConstantBool False, ConstantBool False, ConstantBool False, ConstantBool False, ConstantBool False ] - ] - ) - ] - in testCases "x" highDomain highConstant Just mid low - - ] - - -testCases - :: Name -- high level variable name - -> Domain HasRepresentation Constant -- high level domain - -> Constant -- high level value (constant) - -> (forall a . a -> Maybe a) -- `const Nothing` -- if going one level downC produces Nothing - -- `Just` -- if going one level downC produces (Just mid) - -> [(Name, Domain HasRepresentation Constant, Constant)] -- "mid" result, if we go one level down - -> [(Name, Domain HasRepresentation Constant, Constant)] -- "low" result, if we go all the way down - -> Assertion -testCases highName highDomain highConstant mkMid mid low = do - downC1Test (highName, highDomain, highConstant) (mkMid mid) - downTest (highName, highDomain, highConstant) low - up1Test (highName, highDomain) (map dropDomain mid) (highName, highConstant) - upTest (highName, highDomain) (map dropDomain low) (highName, highConstant) - downUp1Test (highName, highDomain, highConstant) - downUpTest (highName, highDomain, highConstant) - -downC1Test - :: (Name, Domain HasRepresentation Constant, Constant) - -> Maybe [(Name, Domain HasRepresentation Constant, Constant)] - -> Assertion -downC1Test high low' = - case downC1 high of - TriedIO -> assertFailure "TriedIO" - Failed err -> assertFailure (show err) - Done low -> Pr low @?= Pr low' - -downTest - :: (Name, Domain HasRepresentation Constant, Constant) - -> [(Name, Domain HasRepresentation Constant, Constant)] - -> Assertion -downTest high lows' = - case downC high of - TriedIO -> assertFailure "TriedIO" - Failed err -> assertFailure (show err) - Done lows -> Pr lows @?= Pr lows' - -up1Test - :: (Name, Domain HasRepresentation Constant) - -> [(Name, Constant)] - -> (Name, Constant) - -> Assertion -up1Test info lows high' = - case up1 info lows of - TriedIO -> assertFailure "TriedIO" - Failed err -> assertFailure (show err) - Done high -> Pr high @?= Pr high' - -upTest - :: (Name, Domain HasRepresentation Constant) - -> [(Name, Constant)] - -> (Name, Constant) - -> Assertion -upTest info lows high' = - case up lows info of - TriedIO -> assertFailure "TriedIO" - Failed err -> assertFailure (show err) - Done high -> Pr high @?= Pr high' - - -testCasesAuto - :: Name -- high level variable name - -> Domain HasRepresentation Constant -- high level domain - -> Constant -- high level value (constant) - -> Assertion -testCasesAuto highName highDomain highConstant = do - downUp1Test (highName, highDomain, highConstant) - downUpTest (highName, highDomain, highConstant) - - -downUp1Test - :: (Name, Domain HasRepresentation Constant, Constant) - -> Assertion -downUp1Test high = - case downC1 high of - TriedIO -> assertFailure "TriedIO" - Failed err -> assertFailure (show err) - Done mlows -> do - let lows = maybe [dropDomain high] (map dropDomain) mlows -- use high if we cannot go downC1 - case up1 (dropConstant high) lows of - TriedIO -> assertFailure "TriedIO" - Failed err -> assertFailure (show err) - Done high' -> Pr high' @?= Pr (dropDomain high) - -downUpTest - :: (Name, Domain HasRepresentation Constant, Constant) - -> Assertion -downUpTest high = - case downC high of - TriedIO -> assertFailure "TriedIO" - Failed err -> assertFailure (show err) - Done lows -> - case up (map dropDomain lows) (dropConstant high) of - TriedIO -> assertFailure "TriedIO" - Failed err -> assertFailure (show err) - Done high' -> Pr high' @?= Pr (dropDomain high) - - -intDomain :: Default r => Integer -> Integer -> Domain r Constant -<<<<<<< HEAD -intDomain lb ub = defRepr $ mkDomainIntB (ConstantInt Nothing lb) (ConstantInt Nothing ub) -||||||| merged common ancestors -intDomain lb ub = defRepr $ mkDomainIntB (ConstantInt lb) (ConstantInt ub) -======= -intDomain lb ub = defRepr $ mkDomainIntB ((ConstantInt NoTag) lb) ((ConstantInt NoTag) ub) ->>>>>>> taggedints - -dropConstant :: (a,b,c) -> (a,b) -dropConstant (a,b,_) = (a,b) - -dropDomain :: (a,b,c) -> (a,c) -dropDomain (a,_,c) = (a,c) - - -data Pr a = Pr a - deriving Eq - -instance Show (Pr [(Name, Domain HasRepresentation Constant, Constant)]) where - show (Pr xs) = show $ vcat $ concatMap show' xs - where - show' (name, dom, cons) = [ hang (pretty name) 4 $ vcat - [ ":" <+> pretty dom - , "=" <+> pretty cons - ] ] - -instance Show (Pr (Maybe [(Name, Domain HasRepresentation Constant, Constant)])) where - show (Pr Nothing) = "Nothing" - show (Pr (Just xs)) = show (Pr xs) - -instance Show (Pr (Name, Constant)) where - show (Pr (name, cons)) = show $ pretty name <+> "=" <+> pretty cons - -instance Show (Pr [(Name, Constant)]) where - show (Pr xs) = intercalate "\n" $ map (show . Pr) xs - - From 702b05339542246753f7288b7919b8c243c66d39 Mon Sep 17 00:00:00 2001 From: Fraser Dunlop Date: Tue, 27 Nov 2018 11:51:16 +0000 Subject: [PATCH 032/229] Overloaded toSet to handle permutation --- conjure-cp.cabal | 1 - src/Conjure/Compute/DomainOf.hs | 6 --- src/Conjure/Language/Expression/Op.hs | 1 - .../Language/Expression/Op/Internal/Common.hs | 1 - .../Expression/Op/PermutationTuples.hs | 45 ------------------- src/Conjure/Language/Expression/Op/ToSet.hs | 6 +++ src/Conjure/Language/Lenses.hs | 19 -------- src/Conjure/Language/Lexer.hs | 2 - .../permutation.essence | 8 ++++ .../run.sh | 3 ++ .../permutation.essence | 6 +++ .../run.sh | 3 ++ .../stdout.expected | 14 ++++++ 13 files changed, 40 insertions(+), 75 deletions(-) delete mode 100644 src/Conjure/Language/Expression/Op/PermutationTuples.hs create mode 100644 tests/custom/permutations/basic/0039_toSet_on_given_permutation_of_enum/permutation.essence create mode 100755 tests/custom/permutations/basic/0039_toSet_on_given_permutation_of_enum/run.sh create mode 100644 tests/custom/permutations/basic/0040_toSet_on_given_permutation_of_int/permutation.essence create mode 100755 tests/custom/permutations/basic/0040_toSet_on_given_permutation_of_int/run.sh create mode 100644 tests/custom/permutations/basic/0040_toSet_on_given_permutation_of_int/stdout.expected diff --git a/conjure-cp.cabal b/conjure-cp.cabal index fb05e6223b..56a41c3790 100644 --- a/conjure-cp.cabal +++ b/conjure-cp.cabal @@ -88,7 +88,6 @@ Library , Conjure.Language.Expression.Op.Participants , Conjure.Language.Expression.Op.Parts , Conjure.Language.Expression.Op.Party - , Conjure.Language.Expression.Op.PermutationTuples , Conjure.Language.Expression.Op.Pow , Conjure.Language.Expression.Op.PowerSet , Conjure.Language.Expression.Op.Pred diff --git a/src/Conjure/Compute/DomainOf.hs b/src/Conjure/Compute/DomainOf.hs index 3d0cd0204c..fe9fe21226 100644 --- a/src/Conjure/Compute/DomainOf.hs +++ b/src/Conjure/Compute/DomainOf.hs @@ -119,7 +119,6 @@ instance (DomainOf x, TypeOf x, Pretty x, ExpressionLike x, Domain () x :< x, Do domainOf (MkOpParticipants x) = domainOf x domainOf (MkOpParts x) = domainOf x domainOf (MkOpParty x) = domainOf x - domainOf (MkOpPermutationTuples x) = domainOf x domainOf (MkOpPow x) = domainOf x domainOf (MkOpPowerSet x) = domainOf x domainOf (MkOpPred x) = domainOf x @@ -192,7 +191,6 @@ instance (DomainOf x, TypeOf x, Pretty x, ExpressionLike x, Domain () x :< x, Do indexDomainsOf (MkOpParticipants x) = indexDomainsOf x indexDomainsOf (MkOpParts x) = indexDomainsOf x indexDomainsOf (MkOpParty x) = indexDomainsOf x - indexDomainsOf (MkOpPermutationTuples x) = indexDomainsOf x indexDomainsOf (MkOpPow x) = indexDomainsOf x indexDomainsOf (MkOpPowerSet x) = indexDomainsOf x indexDomainsOf (MkOpPred x) = indexDomainsOf x @@ -507,10 +505,6 @@ instance DomainOf x => DomainOf (OpParts x) where instance (Pretty x, TypeOf x) => DomainOf (OpParty x) where domainOf op = mkDomainAny ("OpParty:" <++> pretty op) <$> typeOf op -instance (Pretty x, TypeOf x) => DomainOf (OpPermutationTuples x) where - domainOf op = mkDomainAny ("OpPermutationTuples:" <++> pretty op) <$> typeOf op - - instance (Pretty x, TypeOf x) => DomainOf (OpCompose x) where domainOf op = mkDomainAny ("OpCompose:" <++> pretty op) <$> typeOf op diff --git a/src/Conjure/Language/Expression/Op.hs b/src/Conjure/Language/Expression/Op.hs index a8442157fa..7270437fff 100644 --- a/src/Conjure/Language/Expression/Op.hs +++ b/src/Conjure/Language/Expression/Op.hs @@ -117,7 +117,6 @@ mkOp op xs = L_party -> inject $ MkOpParty $ OpParty (arg xs 0 "party") (arg xs 1 "party") L_participants -> inject $ MkOpParticipants $ OpParticipants (arg xs 0 "participants") - L_permutationTuples -> inject $ MkOpPermutationTuples $ OpPermutationTuples (arg xs 0 "permutationTuples") L_compose -> inject $ MkOpCompose $ OpCompose (arg xs 0 "compose") (arg xs 1 "compose") diff --git a/src/Conjure/Language/Expression/Op/Internal/Common.hs b/src/Conjure/Language/Expression/Op/Internal/Common.hs index db3d085f42..c8af983907 100644 --- a/src/Conjure/Language/Expression/Op/Internal/Common.hs +++ b/src/Conjure/Language/Expression/Op/Internal/Common.hs @@ -268,7 +268,6 @@ functionals = , L_participants , L_parts , L_image - , L_permutationTuples , L_freq , L_toInt , L_flatten diff --git a/src/Conjure/Language/Expression/Op/PermutationTuples.hs b/src/Conjure/Language/Expression/Op/PermutationTuples.hs deleted file mode 100644 index d698f60bf9..0000000000 --- a/src/Conjure/Language/Expression/Op/PermutationTuples.hs +++ /dev/null @@ -1,45 +0,0 @@ -{-# LANGUAGE DeriveGeneric, DeriveDataTypeable, DeriveFunctor, DeriveTraversable, DeriveFoldable, ViewPatterns #-} - -module Conjure.Language.Expression.Op.PermutationTuples where - -import Conjure.Prelude -import Conjure.Language.Expression.Op.Internal.Common - -import qualified Data.Aeson as JSON -- aeson -import qualified Data.HashMap.Strict as M -- unordered-containers -import qualified Data.Vector as V -- vector - - -data OpPermutationTuples x = OpPermutationTuples x - deriving (Eq, Ord, Show, Data, Functor, Traversable, Foldable, Typeable, Generic) - -instance Serialize x => Serialize (OpPermutationTuples x) -instance Hashable x => Hashable (OpPermutationTuples x) -instance ToJSON x => ToJSON (OpPermutationTuples x) where toJSON = genericToJSON jsonOptions -instance FromJSON x => FromJSON (OpPermutationTuples x) where parseJSON = genericParseJSON jsonOptions - -instance (TypeOf x, Pretty x) => TypeOf (OpPermutationTuples x) where - typeOf inp@(OpPermutationTuples p) = do - pTy <- typeOf p - case (pTy) of - (TypePermutation pTyInner) -> - return $ TypeSet $ TypeTuple [pTyInner, pTyInner] - _ -> raiseTypeError inp - -instance EvaluateOp OpPermutationTuples where - evaluateOp op = na $ "evaluateOp{OpPermutationTuples}:" <++> pretty (show op) - -instance SimplifyOp OpPermutationTuples x where - simplifyOp _ = na "simplifyOp{OpPermutationTuples}" - -instance Pretty x => Pretty (OpPermutationTuples x) where - prettyPrec _ (OpPermutationTuples a) = "permutationTuples" <> prettyList prParens "," [a] - - -instance VarSymBreakingDescription x => VarSymBreakingDescription (OpPermutationTuples x) where - varSymBreakingDescription (OpPermutationTuples a) = JSON.Object $ M.fromList - [ ("type", JSON.String "OpPermutationTuples") - , ("children", JSON.Array $ V.fromList - [ varSymBreakingDescription a - ]) - ] diff --git a/src/Conjure/Language/Expression/Op/ToSet.hs b/src/Conjure/Language/Expression/Op/ToSet.hs index b5b8af5b26..d546983614 100644 --- a/src/Conjure/Language/Expression/Op/ToSet.hs +++ b/src/Conjure/Language/Expression/Op/ToSet.hs @@ -9,6 +9,8 @@ import qualified Data.Aeson as JSON -- aeson import qualified Data.HashMap.Strict as M -- unordered-containers import qualified Data.Vector as V -- vector +import Data.Permutation + data OpToSet x = OpToSet Bool -- True means we can assume there won't be any duplicates @@ -45,6 +47,10 @@ instance EvaluateOp OpToSet where return $ ConstantAbstract $ AbsLitSet $ sortNub [ConstantAbstract $ AbsLitTuple [a,b] | (a,b) <- xs] evaluateOp (OpToSet _ (viewConstantRelation -> Just xs)) = return $ ConstantAbstract $ AbsLitSet $ sortNub $ map (ConstantAbstract . AbsLitTuple) xs + evaluateOp (OpToSet _ (viewConstantPermutation -> Just xs)) = + case toFunction <$> fromCycles xs of + Left (PermutationError e) -> na $ "evaluateOp{OpToSet}:" <++> pretty e + Right fn -> return $ ConstantAbstract $ AbsLitSet $ (ConstantAbstract . AbsLitTuple) <$> ((\x -> [x, fn x]) <$> join xs) evaluateOp op = na $ "evaluateOp{OpToSet}:" <++> pretty (show op) instance SimplifyOp OpToSet x where diff --git a/src/Conjure/Language/Lenses.hs b/src/Conjure/Language/Lenses.hs index c1edde5144..f2c01d8c62 100644 --- a/src/Conjure/Language/Lenses.hs +++ b/src/Conjure/Language/Lenses.hs @@ -280,25 +280,6 @@ opToSet _ = ) -opPermutationTuples - :: ( Op x :< x - , Pretty x - , MonadFail m - ) - => Proxy (m :: * -> *) - -> ( x -> x - , x -> m x - ) -opPermutationTuples _ = - ( inject . MkOpPermutationTuples . OpPermutationTuples - , \ p -> do - op <- project p - case op of - MkOpPermutationTuples (OpPermutationTuples x) -> return x - _ -> na ("Lenses.opPermutationTuples:" <++> pretty p) - ) - - opToSetWithFlag :: ( Op x :< x diff --git a/src/Conjure/Language/Lexer.hs b/src/Conjure/Language/Lexer.hs index 96431a736d..a970ffff90 100644 --- a/src/Conjure/Language/Lexer.hs +++ b/src/Conjure/Language/Lexer.hs @@ -118,7 +118,6 @@ data Lexeme -- type: permutation | L_permutation - | L_permutationTuples | L_compose -- operators, page 21 of the holy paper @@ -361,7 +360,6 @@ lexemes = sortBy (flip (comparing (T.length . fst))) $ map swap , ( L_partition, "partition" ) , ( L_permutation, "permutation" ) - , ( L_permutationTuples, "permutationTuples" ) , ( L_compose, "compose") -- , ( L_regular, "regular" ) -- , ( L_partSize, "partSize" ) diff --git a/tests/custom/permutations/basic/0039_toSet_on_given_permutation_of_enum/permutation.essence b/tests/custom/permutations/basic/0039_toSet_on_given_permutation_of_enum/permutation.essence new file mode 100644 index 0000000000..17f1905d9d --- /dev/null +++ b/tests/custom/permutations/basic/0039_toSet_on_given_permutation_of_enum/permutation.essence @@ -0,0 +1,8 @@ +letting e be new type enum {E1, E2, E3, E4} + +letting p be permutation((E1,E2),(E3,E4)) + +find s : set of (e,e) + +such that s = toSet(p) + diff --git a/tests/custom/permutations/basic/0039_toSet_on_given_permutation_of_enum/run.sh b/tests/custom/permutations/basic/0039_toSet_on_given_permutation_of_enum/run.sh new file mode 100755 index 0000000000..3c60e3f90e --- /dev/null +++ b/tests/custom/permutations/basic/0039_toSet_on_given_permutation_of_enum/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence --number-of-solutions=10 +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/basic/0040_toSet_on_given_permutation_of_int/permutation.essence b/tests/custom/permutations/basic/0040_toSet_on_given_permutation_of_int/permutation.essence new file mode 100644 index 0000000000..c50cd03727 --- /dev/null +++ b/tests/custom/permutations/basic/0040_toSet_on_given_permutation_of_int/permutation.essence @@ -0,0 +1,6 @@ +letting p be permutation((1,2),(3,4)) + +find s : set of (int(1..4),int(1..4)) + +such that s = toSet(p) + diff --git a/tests/custom/permutations/basic/0040_toSet_on_given_permutation_of_int/run.sh b/tests/custom/permutations/basic/0040_toSet_on_given_permutation_of_int/run.sh new file mode 100755 index 0000000000..3c60e3f90e --- /dev/null +++ b/tests/custom/permutations/basic/0040_toSet_on_given_permutation_of_int/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence --number-of-solutions=10 +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/basic/0040_toSet_on_given_permutation_of_int/stdout.expected b/tests/custom/permutations/basic/0040_toSet_on_given_permutation_of_int/stdout.expected new file mode 100644 index 0000000000..7dd7245819 --- /dev/null +++ b/tests/custom/permutations/basic/0040_toSet_on_given_permutation_of_int/stdout.expected @@ -0,0 +1,14 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Copying solution to: permutation.solution +language Essence 1.3 + +letting s be {(1, 2), (2, 1), (3, 4), (4, 3)} +$ Visualisation for s +$ 1 2 +$ 2 1 +$ 3 4 +$ 4 3 + From 661d3123a791add542bfe34c57d9da516e3c01c6 Mon Sep 17 00:00:00 2001 From: Fraser Dunlop Date: Tue, 27 Nov 2018 12:03:03 +0000 Subject: [PATCH 033/229] More toSet tests --- .../permutation.essence | 10 ++++++++++ .../0041_toSet_on_found_permutation_of_enum/run.sh | 3 +++ .../permutation.essence | 8 ++++++++ .../0042_toSet_on_found_permutation_of_int/run.sh | 3 +++ 4 files changed, 24 insertions(+) create mode 100644 tests/custom/permutations/basic/0041_toSet_on_found_permutation_of_enum/permutation.essence create mode 100755 tests/custom/permutations/basic/0041_toSet_on_found_permutation_of_enum/run.sh create mode 100644 tests/custom/permutations/basic/0042_toSet_on_found_permutation_of_int/permutation.essence create mode 100755 tests/custom/permutations/basic/0042_toSet_on_found_permutation_of_int/run.sh diff --git a/tests/custom/permutations/basic/0041_toSet_on_found_permutation_of_enum/permutation.essence b/tests/custom/permutations/basic/0041_toSet_on_found_permutation_of_enum/permutation.essence new file mode 100644 index 0000000000..a987081ebf --- /dev/null +++ b/tests/custom/permutations/basic/0041_toSet_on_found_permutation_of_enum/permutation.essence @@ -0,0 +1,10 @@ +letting e be new type enum {E1,E2,E3,E4} + +find p : permutation of e + +find s : set of (e,e) + +such that + s = toSet(p) + /\ |s| = 3 + diff --git a/tests/custom/permutations/basic/0041_toSet_on_found_permutation_of_enum/run.sh b/tests/custom/permutations/basic/0041_toSet_on_found_permutation_of_enum/run.sh new file mode 100755 index 0000000000..3c60e3f90e --- /dev/null +++ b/tests/custom/permutations/basic/0041_toSet_on_found_permutation_of_enum/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence --number-of-solutions=10 +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/basic/0042_toSet_on_found_permutation_of_int/permutation.essence b/tests/custom/permutations/basic/0042_toSet_on_found_permutation_of_int/permutation.essence new file mode 100644 index 0000000000..5a0edceeef --- /dev/null +++ b/tests/custom/permutations/basic/0042_toSet_on_found_permutation_of_int/permutation.essence @@ -0,0 +1,8 @@ +find p : permutation of int(1..4) + +find s : set of (int(1..4),int(1..4)) + +such that + s = toSet(p) + /\ |s| = 3 + diff --git a/tests/custom/permutations/basic/0042_toSet_on_found_permutation_of_int/run.sh b/tests/custom/permutations/basic/0042_toSet_on_found_permutation_of_int/run.sh new file mode 100755 index 0000000000..3c60e3f90e --- /dev/null +++ b/tests/custom/permutations/basic/0042_toSet_on_found_permutation_of_int/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence --number-of-solutions=10 +cat conjure-output/*.solution +rm -rf conjure-output *.solution From a8a3dda75bbfb9b97445d874df960f0c626516d5 Mon Sep 17 00:00:00 2001 From: Fraser Dunlop Date: Tue, 27 Nov 2018 13:53:23 +0000 Subject: [PATCH 034/229] Some broken inverse rules for permutation + failing test --- .../permutation.essence | 6 ++++++ .../basic/0043_inverse_on_given_permutation_of_int/run.sh | 3 +++ 2 files changed, 9 insertions(+) create mode 100644 tests/custom/permutations/basic/0043_inverse_on_given_permutation_of_int/permutation.essence create mode 100755 tests/custom/permutations/basic/0043_inverse_on_given_permutation_of_int/run.sh diff --git a/tests/custom/permutations/basic/0043_inverse_on_given_permutation_of_int/permutation.essence b/tests/custom/permutations/basic/0043_inverse_on_given_permutation_of_int/permutation.essence new file mode 100644 index 0000000000..15af8b6379 --- /dev/null +++ b/tests/custom/permutations/basic/0043_inverse_on_given_permutation_of_int/permutation.essence @@ -0,0 +1,6 @@ +letting p be permutation ((1,2),(3,4)) + +find q : permutation of int(1..4) + +such that inverse(p,q) + diff --git a/tests/custom/permutations/basic/0043_inverse_on_given_permutation_of_int/run.sh b/tests/custom/permutations/basic/0043_inverse_on_given_permutation_of_int/run.sh new file mode 100755 index 0000000000..3c60e3f90e --- /dev/null +++ b/tests/custom/permutations/basic/0043_inverse_on_given_permutation_of_int/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence --number-of-solutions=10 +cat conjure-output/*.solution +rm -rf conjure-output *.solution From bd1e399d877502cb4d517cdbecbb9ca7b22242b5 Mon Sep 17 00:00:00 2001 From: Fraser Dunlop Date: Wed, 28 Nov 2018 11:48:31 +0000 Subject: [PATCH 035/229] Oz made change to Logging --- .../log | 24365 ++++++++++++++++ .../log-lite | 7863 +++++ 2 files changed, 32228 insertions(+) create mode 100644 tests/custom/permutations/basic/0029_find_relations_x_y_such_that_y_image_x_under_p/log create mode 100644 tests/custom/permutations/basic/0029_find_relations_x_y_such_that_y_image_x_under_p/log-lite diff --git a/tests/custom/permutations/basic/0029_find_relations_x_y_such_that_y_image_x_under_p/log b/tests/custom/permutations/basic/0029_find_relations_x_y_such_that_y_image_x_under_p/log new file mode 100644 index 0000000000..69b0598ff1 --- /dev/null +++ b/tests/custom/permutations/basic/0029_find_relations_x_y_such_that_y_image_x_under_p/log @@ -0,0 +1,24365 @@ +Command line options: Modelling {essence = "permutation.essence", outputDirectory = "conjure-output", numberingStart = 1, smartFilenames = False, responses = "", logLevel = LogDebug, verboseTrail = False, rewritesTrail = False, logRuleFails = False, logRuleSuccesses = False, logRuleAttempts = False, logChoices = False, strategyQ = "f", strategyA = "ai", representations = Nothing, representationsFinds = Nothing, representationsGivens = Nothing, representationsAuxiliaries = Nothing, representationsQuantifieds = Nothing, representationsCuts = Nothing, channelling = True, representationLevels = True, seed = Nothing, limitModels = Nothing, limitTime = Nothing, savedChoices = Nothing, outputFormat = Plain, lineWidth = 120} +[input] + language Essence 1.3 + + letting MYTYPE be new type enum {THING1, THING2, THING3, THING4, THING5} + letting p be permutation((THING3, THING4)) + find x: relation (size 4) of (MYTYPE * MYTYPE) + find y: relation (size 4) of (MYTYPE * MYTYPE) + such that y = image(p, x) + +[removeUnnamedsFromModel] + language Essence 1.3 + + letting MYTYPE be new type enum {THING1, THING2, THING3, THING4, THING5} + letting p be permutation((THING3, THING4)) + find x: relation (size 4) of (MYTYPE * MYTYPE) + find y: relation (size 4) of (MYTYPE * MYTYPE) + such that y = image(p, x) + +Recording enumGivens: +[removeEnumsFromModel] + language Essence 1.3 + + letting MYTYPE be domain int(1..5) + letting p be permutation((3, 4)) + find x: relation (size 4) of (MYTYPE * MYTYPE) + find y: relation (size 4) of (MYTYPE * MYTYPE) + such that y = image(p, x) + +[resolveNames] + language Essence 1.3 + + letting MYTYPE be domain int(1..5) + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that y = image(p, x) + +[typeCheckModel] + language Essence 1.3 + + letting MYTYPE be domain int(1..5) + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that y = image(p, x) + +[categoryChecking] + language Essence 1.3 + + letting MYTYPE be domain int(1..5) + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that y = image(p, x) + +[sanityChecks] + language Essence 1.3 + + letting MYTYPE be domain int(1..5) + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that y = image(p, x) + +[typeCheckModel] + language Essence 1.3 + + letting MYTYPE be domain int(1..5) + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that y = image(p, x) + +[input] + language Essence 1.3 + + letting MYTYPE be new type enum {THING1, THING2, THING3, THING4, THING5} + letting p be permutation((THING3, THING4)) + find x: relation (size 4) of (MYTYPE * MYTYPE) + find y: relation (size 4) of (MYTYPE * MYTYPE) + such that y = image(p, x) + +[addSearchOrder] + language Essence 1.3 + + letting MYTYPE be new type enum {THING1, THING2, THING3, THING4, THING5} + letting p be permutation((THING3, THING4)) + find x: relation (size 4) of (MYTYPE * MYTYPE) + find y: relation (size 4) of (MYTYPE * MYTYPE) + such that y = image(p, x) + branching on [x, y] + +[attributeAsConstraints] + language Essence 1.3 + + letting MYTYPE be new type enum {THING1, THING2, THING3, THING4, THING5} + letting p be permutation((THING3, THING4)) + find x: relation (size 4) of (MYTYPE * MYTYPE) + find y: relation (size 4) of (MYTYPE * MYTYPE) + such that y = image(p, x) + branching on [x, y] + +[inferAttributes] + language Essence 1.3 + + letting MYTYPE be new type enum {THING1, THING2, THING3, THING4, THING5} + letting p be permutation((THING3, THING4)) + find x: relation (size 4) of (MYTYPE * MYTYPE) + find y: relation (size 4) of (MYTYPE * MYTYPE) + such that y = image(p, x) + branching on [x, y] + +[inlineLettingDomainsForDecls] + language Essence 1.3 + + letting MYTYPE be new type enum {THING1, THING2, THING3, THING4, THING5} + letting p be permutation((THING3, THING4)) + find x: relation (size 4) of (MYTYPE * MYTYPE) + find y: relation (size 4) of (MYTYPE * MYTYPE) + such that y = image(p, x) + branching on [x, y] + +[lettingsForComplexInDoms] + language Essence 1.3 + + letting MYTYPE be new type enum {THING1, THING2, THING3, THING4, THING5} + letting p be permutation((THING3, THING4)) + find x: relation (size 4) of (MYTYPE * MYTYPE) + find y: relation (size 4) of (MYTYPE * MYTYPE) + such that y = image(p, x) + branching on [x, y] + +[distinctQuantifiedVars] + language Essence 1.3 + + letting MYTYPE be new type enum {THING1, THING2, THING3, THING4, THING5} + letting p be permutation((THING3, THING4)) + find x: relation (size 4) of (MYTYPE * MYTYPE) + find y: relation (size 4) of (MYTYPE * MYTYPE) + such that y = image(p, x) + branching on [x, y] + +[initInfo] + language Essence 1.3 + + letting MYTYPE be new type enum {THING1, THING2, THING3, THING4, THING5} + letting p be permutation((THING3, THING4)) + find x: relation (size 4) of (MYTYPE * MYTYPE) + find y: relation (size 4) of (MYTYPE * MYTYPE) + such that y = image(p, x) + branching on [x, y] + +[removeUnnamedsFromModel] + language Essence 1.3 + + letting MYTYPE be new type enum {THING1, THING2, THING3, THING4, THING5} + letting p be permutation((THING3, THING4)) + find x: relation (size 4) of (MYTYPE * MYTYPE) + find y: relation (size 4) of (MYTYPE * MYTYPE) + such that y = image(p, x) + branching on [x, y] + +Recording enumGivens: +[removeEnumsFromModel] + language Essence 1.3 + + letting MYTYPE be domain int(1..5) + letting p be permutation((3, 4)) + find x: relation (size 4) of (MYTYPE * MYTYPE) + find y: relation (size 4) of (MYTYPE * MYTYPE) + such that y = image(p, x) + branching on [x, y] + +[finiteGivens] + language Essence 1.3 + + letting MYTYPE be domain int(1..5) + letting p be permutation((3, 4)) + find x: relation (size 4) of (MYTYPE * MYTYPE) + find y: relation (size 4) of (MYTYPE * MYTYPE) + such that y = image(p, x) + branching on [x, y] + +[resolveNames] + language Essence 1.3 + + letting MYTYPE be domain int(1..5) + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that y = image(p, x) + branching on [x, y] + +[initInfo_Lettings] + language Essence 1.3 + + letting MYTYPE be domain int(1..5) + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that y = image(p, x) + branching on [x, y] + +[removeDomainLettings] + language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that y = image(p, x) + branching on [x, y] + +[typeCheckModel] + language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that y = image(p, x) + branching on [x, y] + +[categoryChecking] + language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that y = image(p, x) + branching on [x, y] + +[sanityChecks] + language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that y = image(p, x) + branching on [x, y] + +[dealWithCuts] + language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that y = image(p, x) + branching on [x, y] + such that + +[removeExtraSlices] + language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that y = image(p, x) + branching on [x, y] + such that + +[addTrueConstraints] + language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that y = image(p, x) + branching on [x, y] + such that + such that + true(x), + true(y) + +Contains 0 parameters (0 abstract) + 2 decision variables (2 abstract) +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that y = image(p, x) + branching on [x, y] + such that + such that + true(x), + true(y) + +Picking the first option: Question 1: permutation((3, 4)) +Picking the only option: Answer 1: full-evaluate: Full evaluator + permutation((3, 4)) +storedChoice: +permutation((3, 4)) -604127175528974338 +AnsweredRule {qHole_ = -604127175528974338, qAscendants_ = fromList [], aRuleName_ = "full-evaluate"} +LF: {"AnsweredRule":{"aRuleName_":"full-evaluate","qAscendants_":[],"qHole_":-604127175528974338}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that y = image(p, x) + branching on [x, y] + such that + such that + true(x), + true(y) + +Picking the first option: Question 1: p + Context #1: image(p, x) + Context #2: y = image(p, x) +Picking the only option: Answer 1: full-evaluate: Full evaluator + permutation((3, 4)) +storedChoice: +p -7234408895829330219 +AnsweredRule {qHole_ = -7234408895829330219, qAscendants_ = fromList [-7340749217212310711,-5834110796085551311], aRuleName_ = "full-evaluate"} +LF: {"AnsweredRule":{"aRuleName_":"full-evaluate","qAscendants_":[-7340749217212310711,-5834110796085551311],"qHole_":-7234408895829330219}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that y = image(permutation((3, 4)), x) + branching on [x, y] + such that + such that + true(x), + true(y) + +Picking the first option: Question 1: x + Context #1: image(permutation((3, 4)), x) + Context #2: y = image(permutation((3, 4)), x) +Picking the only option: Answer 1: choose-repr: Choosing representation for x: + relation {RelationAsMatrix} (size 4) of (int(1..5) * int(1..5)) + x +storedChoice: +x -7234408895963551171 +AnsweredReprStored {qHole_ = -7234408895963551171, qAscendants_ = fromList [-7111069252946253414,-6043361806322913446], aDomStored_ = "relation {RelationAsMatrix} (size 4) of (int(1..5) * int(1..5))", aRuleName_ = "choose-repr"} +LF: {"AnsweredReprStored":{"aDomStored_":"relation {RelationAsMatrix} (size 4) of (int(1..5) * int(1..5))","aRuleName_":"choose-repr","qAscendants_":[-7111069252946253414,-6043361806322913446],"qHole_":-7234408895963551171}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that y = image(permutation((3, 4)), x) + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + +Picking the first option: Question 1: y + Context #1: y = image(permutation((3, 4)), x) +Picking the only option: Answer 1: choose-repr: Choosing representation for y: + relation {RelationAsMatrix} (size 4) of (int(1..5) * int(1..5)) + y +storedChoice: +y -7234408895946773554 +AnsweredReprStored {qHole_ = -7234408895946773554, qAscendants_ = fromList [-7111069252946253414], aDomStored_ = "relation {RelationAsMatrix} (size 4) of (int(1..5) * int(1..5))", aRuleName_ = "choose-repr"} +LF: {"AnsweredReprStored":{"aDomStored_":"relation {RelationAsMatrix} (size 4) of (int(1..5) * int(1..5))","aRuleName_":"choose-repr","qAscendants_":[-7111069252946253414],"qHole_":-7234408895946773554}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that y = image(permutation((3, 4)), x) + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: x + Context #1: true(x) +Picking the only option: Answer 1: choose-repr: Choosing representation for x: + relation {RelationAsMatrix} (size 4) of (int(1..5) * int(1..5)) + x +storedChoice: +x -7234408895963551171 +AnsweredReprStored {qHole_ = -7234408895963551171, qAscendants_ = fromList [-1508832156878423928], aDomStored_ = "relation {RelationAsMatrix} (size 4) of (int(1..5) * int(1..5))", aRuleName_ = "choose-repr"} +LF: {"AnsweredReprStored":{"aDomStored_":"relation {RelationAsMatrix} (size 4) of (int(1..5) * int(1..5))","aRuleName_":"choose-repr","qAscendants_":[-1508832156878423928],"qHole_":-7234408895963551171}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that y = image(permutation((3, 4)), x) + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: y + Context #1: true(y) +Picking the only option: Answer 1: choose-repr: Choosing representation for y: + relation {RelationAsMatrix} (size 4) of (int(1..5) * int(1..5)) + y +storedChoice: +y -7234408895946773554 +AnsweredReprStored {qHole_ = -7234408895946773554, qAscendants_ = fromList [-1508550667338902379], aDomStored_ = "relation {RelationAsMatrix} (size 4) of (int(1..5) * int(1..5))", aRuleName_ = "choose-repr"} +LF: {"AnsweredReprStored":{"aDomStored_":"relation {RelationAsMatrix} (size 4) of (int(1..5) * int(1..5))","aRuleName_":"choose-repr","qAscendants_":[-1508550667338902379],"qHole_":-7234408895946773554}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that y = image(permutation((3, 4)), x) + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: [sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)] + Context #1: sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + Context #2: 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) +Picking the only option: Answer 1: choose-repr-for-comprehension: Choosing representation for quantified variable q1 (with type: int) + [sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)] +storedChoice: +[sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)] 6263396600925448594 +AnsweredRule {qHole_ = 6263396600925448594, qAscendants_ = fromList [5049395136776340146,5865511705196666561], aRuleName_ = "choose-repr-for-comprehension"} +LF: {"AnsweredRule":{"aRuleName_":"choose-repr-for-comprehension","qAscendants_":[5049395136776340146,5865511705196666561],"qHole_":6263396600925448594}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that y = image(permutation((3, 4)), x) + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: [toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)] + Context #1: sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) + Context #2: [sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)] + Context #3: sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + Context #4: 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) +Picking the only option: Answer 1: choose-repr-for-comprehension: Choosing representation for quantified variable q2 (with type: int) + [toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)] +storedChoice: +[toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)] 7855671108991671235 +AnsweredRule {qHole_ = 7855671108991671235, qAscendants_ = fromList [5049395136776340146,5865511705196666561,6263396600925448594,7085372780514568240], aRuleName_ = "choose-repr-for-comprehension"} +LF: {"AnsweredRule":{"aRuleName_":"choose-repr-for-comprehension","qAscendants_":[5049395136776340146,5865511705196666561,6263396600925448594,7085372780514568240],"qHole_":7855671108991671235}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that y = image(permutation((3, 4)), x) + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: [sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)] + Context #1: sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + Context #2: 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) +Picking the only option: Answer 1: choose-repr-for-comprehension: Choosing representation for quantified variable q3 (with type: int) + [sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)] +storedChoice: +[sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)] -3620919297952344383 +AnsweredRule {qHole_ = -3620919297952344383, qAscendants_ = fromList [-5513655157779400708,7219712989341858895], aRuleName_ = "choose-repr-for-comprehension"} +LF: {"AnsweredRule":{"aRuleName_":"choose-repr-for-comprehension","qAscendants_":[-5513655157779400708,7219712989341858895],"qHole_":-3620919297952344383}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that y = image(permutation((3, 4)), x) + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: [toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)] + Context #1: sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) + Context #2: [sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)] + Context #3: sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + Context #4: 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) +Picking the only option: Answer 1: choose-repr-for-comprehension: Choosing representation for quantified variable q4 (with type: int) + [toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)] +storedChoice: +[toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)] -2356590267706027710 +AnsweredRule {qHole_ = -2356590267706027710, qAscendants_ = fromList [-5513655157779400708,-3620919297952344383,7219712989341858895,8125267169441206107], aRuleName_ = "choose-repr-for-comprehension"} +LF: {"AnsweredRule":{"aRuleName_":"choose-repr-for-comprehension","qAscendants_":[-5513655157779400708,-3620919297952344383,7219712989341858895,8125267169441206107],"qHole_":-2356590267706027710}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that y = image(permutation((3, 4)), x) + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: image(permutation((3, 4)), x) + Context #1: y = image(permutation((3, 4)), x) +Picking the only option: Answer 1: relation-image: Horizontal rule for image relation in comprehension + { conjure_aux1 + @ find conjure_aux1: relation (size 4) of (int(1..5) * int(1..5)) + such that |x| = |conjure_aux1| /\ and([image(permutation((3, 4)), q5) in conjure_aux1 | q5 <- x]) + } +storedChoice: +image(permutation((3, 4)), x) -6043361806322913446 +AnsweredRule {qHole_ = -6043361806322913446, qAscendants_ = fromList [-7111069252946253414], aRuleName_ = "relation-image"} +LF: {"AnsweredRule":{"aRuleName_":"relation-image","qAscendants_":[-7111069252946253414],"qHole_":-6043361806322913446}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1: relation (size 4) of (int(1..5) * int(1..5)) + such that |x| = |conjure_aux1| /\ and([image(permutation((3, 4)), q5) in conjure_aux1 | q5 <- x]) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: { conjure_aux1 + @ find conjure_aux1: relation (size 4) of (int(1..5) * int(1..5)) + such that |x| = |conjure_aux1| /\ and([image(permutation((3, 4)), q5) in conjure_aux1 | q5 <- x]) + } + Context #1: y = + { conjure_aux1 + @ find conjure_aux1: relation (size 4) of (int(1..5) * int(1..5)) + such that |x| = |conjure_aux1| /\ and([image(permutation((3, 4)), q5) in conjure_aux1 | q5 <- x]) + } +Picking the only option: Answer 1: choose-repr-for-locals: Choosing representation for local variable conjure_aux1 + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that |x| = |conjure_aux1| /\ and([image(permutation((3, 4)), q5) in conjure_aux1 | q5 <- x]) + } +storedChoice: +{ conjure_aux1 +@ find conjure_aux1: relation (size 4) of (int(1..5) * int(1..5)) + such that |x| = |conjure_aux1| /\ and([image(permutation((3, 4)), q5) in conjure_aux1 | q5 <- x]) +} 1714623876200418132 +AnsweredRule {qHole_ = 1714623876200418132, qAscendants_ = fromList [5536329259437519582], aRuleName_ = "choose-repr-for-locals"} +LF: {"AnsweredRule":{"aRuleName_":"choose-repr-for-locals","qAscendants_":[5536329259437519582],"qHole_":1714623876200418132}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that |x| = |conjure_aux1| /\ and([image(permutation((3, 4)), q5) in conjure_aux1 | q5 <- x]) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: [sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)] + Context #1: sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + Context #2: 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + Context #3: { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that |x| = |conjure_aux1| /\ and([image(permutation((3, 4)), q5) in conjure_aux1 | q5 <- x]) + } + Context #4: y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that |x| = |conjure_aux1| /\ and([image(permutation((3, 4)), q5) in conjure_aux1 | q5 <- x]) + } +Picking the only option: Answer 1: choose-repr-for-comprehension: Choosing representation for quantified variable q6 (with type: int) + [sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)] +storedChoice: +[sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)] -878601234175159627 +AnsweredRule {qHole_ = -878601234175159627, qAscendants_ = fromList [-5775367836057753714,-1245214478984509661,79132428954328345,1049837485042621691], aRuleName_ = "choose-repr-for-comprehension"} +LF: {"AnsweredRule":{"aRuleName_":"choose-repr-for-comprehension","qAscendants_":[-5775367836057753714,-1245214478984509661,79132428954328345,1049837485042621691],"qHole_":-878601234175159627}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that |x| = |conjure_aux1| /\ and([image(permutation((3, 4)), q5) in conjure_aux1 | q5 <- x]) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: [toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)] + Context #1: sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) + Context #2: [sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)] + Context #3: sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + Context #4: 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + Context #5: { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that |x| = |conjure_aux1| /\ and([image(permutation((3, 4)), q5) in conjure_aux1 | q5 <- x]) + } + Context #6: y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that |x| = |conjure_aux1| /\ and([image(permutation((3, 4)), q5) in conjure_aux1 | q5 <- x]) + } +Picking the only option: Answer 1: choose-repr-for-comprehension: Choosing representation for quantified variable q7 (with type: int) + [toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)] +storedChoice: +[toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)] 2379582110528111197 +AnsweredRule {qHole_ = 2379582110528111197, qAscendants_ = fromList [-5775367836057753714,-1245214478984509661,-878601234175159627,79132428954328345,1049837485042621691,4483484998279672051], aRuleName_ = "choose-repr-for-comprehension"} +LF: {"AnsweredRule":{"aRuleName_":"choose-repr-for-comprehension","qAscendants_":[-5775367836057753714,-1245214478984509661,-878601234175159627,79132428954328345,1049837485042621691,4483484998279672051],"qHole_":2379582110528111197}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that |x| = |conjure_aux1| /\ and([image(permutation((3, 4)), q5) in conjure_aux1 | q5 <- x]) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: [image(permutation((3, 4)), q5) in conjure_aux1 | q5 <- x] + Context #1: and([image(permutation((3, 4)), q5) in conjure_aux1 | q5 <- x]) + Context #2: [|x| = |conjure_aux1|, and([image(permutation((3, 4)), q5) in conjure_aux1 | q5 <- x]); int(1..2)] + Context #3: |x| = |conjure_aux1| /\ and([image(permutation((3, 4)), q5) in conjure_aux1 | q5 <- x]) + Context #4: { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that |x| = |conjure_aux1| /\ and([image(permutation((3, 4)), q5) in conjure_aux1 | q5 <- x]) + } + Context #5: y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that |x| = |conjure_aux1| /\ and([image(permutation((3, 4)), q5) in conjure_aux1 | q5 <- x]) + } +Picking the only option: Answer 1: relation-map_in_expr{RelationAsMatrix}: Vertical rule for map_in_expr for relation domains, RelationAsMatrix representation. + [image(permutation((3, 4)), (q8[1], q8[2])) in conjure_aux1 | q8 : (int(1..5), int(1..5)), x_RelationAsMatrix[q8[1], q8[2]]] +storedChoice: +[image(permutation((3, 4)), q5) in conjure_aux1 | q5 <- x] 2569794631160861273 +AnsweredRule {qHole_ = 2569794631160861273, qAscendants_ = fromList [-4776664362067532454,-1245214478984509661,-1036657270873470960,79132428954328345,5830139973578569810], aRuleName_ = "relation-map_in_expr{RelationAsMatrix}"} +LF: {"AnsweredRule":{"aRuleName_":"relation-map_in_expr{RelationAsMatrix}","qAscendants_":[-4776664362067532454,-1245214478984509661,-1036657270873470960,79132428954328345,5830139973578569810],"qHole_":2569794631160861273}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([image(permutation((3, 4)), (q8[1], q8[2])) in conjure_aux1 | q8 : (int(1..5), int(1..5)), x_RelationAsMatrix[q8[1], q8[2]]]) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: [image(permutation((3, 4)), (q8[1], q8[2])) in conjure_aux1 + | q8 : (int(1..5), int(1..5)), x_RelationAsMatrix[q8[1], q8[2]]] + Context #1: and([image(permutation((3, 4)), (q8[1], q8[2])) in conjure_aux1 + | q8 : (int(1..5), int(1..5)), x_RelationAsMatrix[q8[1], q8[2]]]) + Context #2: [|x| = |conjure_aux1|, + and([image(permutation((3, 4)), (q8[1], q8[2])) in conjure_aux1 | q8 : (int(1..5), int(1..5)), x_RelationAsMatrix[q8[1], q8[2]]]); + int(1..2)] + Context #3: |x| = |conjure_aux1| /\ + and([image(permutation((3, 4)), (q8[1], q8[2])) in conjure_aux1 | q8 : (int(1..5), int(1..5)), x_RelationAsMatrix[q8[1], q8[2]]]) + Context #4: { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([image(permutation((3, 4)), (q8[1], q8[2])) in conjure_aux1 | q8 : (int(1..5), int(1..5)), x_RelationAsMatrix[q8[1], q8[2]]]) + } + Context #5: y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([image(permutation((3, 4)), (q8[1], q8[2])) in conjure_aux1 | q8 : (int(1..5), int(1..5)), x_RelationAsMatrix[q8[1], q8[2]]]) + } +Picking the only option: Answer 1: choose-repr-for-comprehension: Choosing representation for quantified variable q8 (with type: (int, + int)) + [image(permutation((3, 4)), (q8[1], q8[2])) in conjure_aux1 | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]] +storedChoice: +[image(permutation((3, 4)), (q8[1], q8[2])) in conjure_aux1 + | q8 : (int(1..5), int(1..5)), x_RelationAsMatrix[q8[1], q8[2]]] -6121410142271556240 +AnsweredRule {qHole_ = -6121410142271556240, qAscendants_ = fromList [-8542780548609610841,-2372866271326699518,-688805377682383984,1829424135801856670,4203509818187934421], aRuleName_ = "choose-repr-for-comprehension"} +LF: {"AnsweredRule":{"aRuleName_":"choose-repr-for-comprehension","qAscendants_":[-8542780548609610841,-2372866271326699518,-688805377682383984,1829424135801856670,4203509818187934421],"qHole_":-6121410142271556240}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([image(permutation((3, 4)), (q8[1], q8[2])) in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: image(permutation((3, 4)), (q8[1], q8[2])) + Context #1: image(permutation((3, 4)), (q8[1], q8[2])) in conjure_aux1 + Context #2: [image(permutation((3, 4)), (q8[1], q8[2])) in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]] + Context #3: and([image(permutation((3, 4)), (q8[1], q8[2])) in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + Context #4: [|x| = |conjure_aux1|, + and([image(permutation((3, 4)), (q8[1], q8[2])) in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]); + int(1..2)] + Context #5: |x| = |conjure_aux1| /\ + and([image(permutation((3, 4)), (q8[1], q8[2])) in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + Context #6: { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([image(permutation((3, 4)), (q8[1], q8[2])) in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + Context #7: y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([image(permutation((3, 4)), (q8[1], q8[2])) in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } +Picking the only option: Answer 1: tuple-image: Horizontal rule for image tuple in comprehension + { conjure_aux2 + @ find conjure_aux2: (int(1..5), int(1..5)) + such that conjure_aux2[1] = image(permutation((3, 4)), (q8[1], q8[2])[1]) + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } +storedChoice: +image(permutation((3, 4)), (q8[1], q8[2])) 7641797427128728383 +AnsweredRule {qHole_ = 7641797427128728383, qAscendants_ = fromList [-6118234929664435696,-1399392580596120430,-1387706708486858898,-1208703870972871253,-742133995496027829,4437220630107512706,5070918677941821273], aRuleName_ = "tuple-image"} +LF: {"AnsweredRule":{"aRuleName_":"tuple-image","qAscendants_":[-6118234929664435696,-1399392580596120430,-1387706708486858898,-1208703870972871253,-742133995496027829,4437220630107512706,5070918677941821273],"qHole_":7641797427128728383}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2: (int(1..5), int(1..5)) + such that conjure_aux2[1] = image(permutation((3, 4)), (q8[1], q8[2])[1]) + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: { conjure_aux2 + @ find conjure_aux2: (int(1..5), int(1..5)) + such that conjure_aux2[1] = image(permutation((3, 4)), (q8[1], q8[2])[1]) + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + Context #1: { conjure_aux2 + @ find conjure_aux2: (int(1..5), int(1..5)) + such that conjure_aux2[1] = image(permutation((3, 4)), (q8[1], q8[2])[1]) + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + Context #2: [{ conjure_aux2 + @ find conjure_aux2: (int(1..5), int(1..5)) + such that conjure_aux2[1] = image(permutation((3, 4)), (q8[1], q8[2])[1]) + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]] + Context #3: and([{ conjure_aux2 + @ find conjure_aux2: (int(1..5), int(1..5)) + such that conjure_aux2[1] = image(permutation((3, 4)), (q8[1], q8[2])[1]) + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + Context #4: [|x| = |conjure_aux1|, + and([{ conjure_aux2 + @ find conjure_aux2: (int(1..5), int(1..5)) + such that conjure_aux2[1] = image(permutation((3, 4)), (q8[1], q8[2])[1]) + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]); + int(1..2)] + Context #5: |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2: (int(1..5), int(1..5)) + such that conjure_aux2[1] = image(permutation((3, 4)), (q8[1], q8[2])[1]) + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + Context #6: { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2: (int(1..5), int(1..5)) + such that conjure_aux2[1] = image(permutation((3, 4)), (q8[1], q8[2])[1]) + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + Context #7: y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2: (int(1..5), int(1..5)) + such that conjure_aux2[1] = image(permutation((3, 4)), (q8[1], q8[2])[1]) + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } +Picking the only option: Answer 1: choose-repr-for-locals: Choosing representation for local variable conjure_aux2 + { conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that conjure_aux2[1] = image(permutation((3, 4)), (q8[1], q8[2])[1]) + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } +storedChoice: +{ conjure_aux2 +@ find conjure_aux2: (int(1..5), int(1..5)) + such that conjure_aux2[1] = image(permutation((3, 4)), (q8[1], q8[2])[1]) + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) +} 7832450608952021018 +AnsweredRule {qHole_ = 7832450608952021018, qAscendants_ = fromList [-4717314876217502109,-4294582922489450379,1651264905194084305,2977457561748621690,4087019737558016944,5019534480518702783,6820345709468359473], aRuleName_ = "choose-repr-for-locals"} +LF: {"AnsweredRule":{"aRuleName_":"choose-repr-for-locals","qAscendants_":[-4717314876217502109,-4294582922489450379,1651264905194084305,2977457561748621690,4087019737558016944,5019534480518702783,6820345709468359473],"qHole_":7832450608952021018}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that conjure_aux2[1] = image(permutation((3, 4)), (q8[1], q8[2])[1]) + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: conjure_aux2[1] + Context #1: conjure_aux2[1] = image(permutation((3, 4)), (q8[1], q8[2])[1]) + Context #2: { conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that conjure_aux2[1] = image(permutation((3, 4)), (q8[1], q8[2])[1]) + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + Context #3: { conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that conjure_aux2[1] = image(permutation((3, 4)), (q8[1], q8[2])[1]) + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + Context #4: [{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that conjure_aux2[1] = image(permutation((3, 4)), (q8[1], q8[2])[1]) + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]] + Context #5: and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that conjure_aux2[1] = image(permutation((3, 4)), (q8[1], q8[2])[1]) + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + Context #6: [|x| = |conjure_aux1|, + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that conjure_aux2[1] = image(permutation((3, 4)), (q8[1], q8[2])[1]) + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]); + int(1..2)] + Context #7: |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that conjure_aux2[1] = image(permutation((3, 4)), (q8[1], q8[2])[1]) + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + Context #8: { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that conjure_aux2[1] = image(permutation((3, 4)), (q8[1], q8[2])[1]) + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + Context #9: y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that conjure_aux2[1] = image(permutation((3, 4)), (q8[1], q8[2])[1]) + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } +Picking the only option: Answer 1: tuple-index: Tuple indexing on: conjure_aux2[1] + conjure_aux2_1 +storedChoice: +conjure_aux2[1] 2042848205583864547 +AnsweredRule {qHole_ = 2042848205583864547, qAscendants_ = fromList [-7836606021998938252,-4083899676628141502,-3337431591692655861,-1871379374487492755,31163859450310923,347176683161250196,1078578095348213584,3723112517704369347,8818185052449544140], aRuleName_ = "tuple-index"} +LF: {"AnsweredRule":{"aRuleName_":"tuple-index","qAscendants_":[-7836606021998938252,-4083899676628141502,-3337431591692655861,-1871379374487492755,31163859450310923,347176683161250196,1078578095348213584,3723112517704369347,8818185052449544140],"qHole_":2042848205583864547}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that conjure_aux2_1 = image(permutation((3, 4)), (q8[1], q8[2])[1]) + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: (q8[1], q8[2])[1] + Context #1: image(permutation((3, 4)), (q8[1], q8[2])[1]) + Context #2: conjure_aux2_1 = image(permutation((3, 4)), (q8[1], q8[2])[1]) + Context #3: { conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that conjure_aux2_1 = image(permutation((3, 4)), (q8[1], q8[2])[1]) + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + Context #4: { conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that conjure_aux2_1 = image(permutation((3, 4)), (q8[1], q8[2])[1]) + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + Context #5: [{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that conjure_aux2_1 = image(permutation((3, 4)), (q8[1], q8[2])[1]) + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]] + Context #6: and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that conjure_aux2_1 = image(permutation((3, 4)), (q8[1], q8[2])[1]) + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + Context #7: [|x| = |conjure_aux1|, + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that conjure_aux2_1 = image(permutation((3, 4)), (q8[1], q8[2])[1]) + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]); + int(1..2)] + Context #8: |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that conjure_aux2_1 = image(permutation((3, 4)), (q8[1], q8[2])[1]) + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + Context #9: { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that conjure_aux2_1 = image(permutation((3, 4)), (q8[1], q8[2])[1]) + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + Context #10: y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that conjure_aux2_1 = image(permutation((3, 4)), (q8[1], q8[2])[1]) + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } +Picking the only option: Answer 1: tuple-index: Tuple indexing on: (q8[1], q8[2])[1] + q8[1] +storedChoice: +(q8[1], q8[2])[1] -5501922928837560372 +AnsweredRule {qHole_ = -5501922928837560372, qAscendants_ = fromList [-8079003502337880871,-5992757738829033069,-4052786222025792276,-4045994663639704708,-1887930543228865818,2614825847120268012,2969550575619082812,4897364746913734457,7503648025096004321,8070588202073729915], aRuleName_ = "tuple-index"} +LF: {"AnsweredRule":{"aRuleName_":"tuple-index","qAscendants_":[-8079003502337880871,-5992757738829033069,-4052786222025792276,-4045994663639704708,-1887930543228865818,2614825847120268012,2969550575619082812,4897364746913734457,7503648025096004321,8070588202073729915],"qHole_":-5501922928837560372}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that conjure_aux2_1 = image(permutation((3, 4)), q8[1]) + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: q8[1] + Context #1: image(permutation((3, 4)), q8[1]) + Context #2: conjure_aux2_1 = image(permutation((3, 4)), q8[1]) + Context #3: { conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that conjure_aux2_1 = image(permutation((3, 4)), q8[1]) + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + Context #4: { conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that conjure_aux2_1 = image(permutation((3, 4)), q8[1]) + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + Context #5: [{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that conjure_aux2_1 = image(permutation((3, 4)), q8[1]) + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]] + Context #6: and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that conjure_aux2_1 = image(permutation((3, 4)), q8[1]) + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + Context #7: [|x| = |conjure_aux1|, + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that conjure_aux2_1 = image(permutation((3, 4)), q8[1]) + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]); + int(1..2)] + Context #8: |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that conjure_aux2_1 = image(permutation((3, 4)), q8[1]) + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + Context #9: { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that conjure_aux2_1 = image(permutation((3, 4)), q8[1]) + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + Context #10: y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that conjure_aux2_1 = image(permutation((3, 4)), q8[1]) + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } +Picking the only option: Answer 1: tuple-index: Tuple indexing on: q8[1] + q8_1 +storedChoice: +q8[1] 6051865069970393497 +AnsweredRule {qHole_ = 6051865069970393497, qAscendants_ = fromList [-6240564754428641774,-3828924106000349868,-2497616537930163555,-2455337427536589680,-1546470019878997061,409221243111017286,1096079797629796883,1353067250173028676,4249511820642706384,6954638962073438443], aRuleName_ = "tuple-index"} +LF: {"AnsweredRule":{"aRuleName_":"tuple-index","qAscendants_":[-6240564754428641774,-3828924106000349868,-2497616537930163555,-2455337427536589680,-1546470019878997061,409221243111017286,1096079797629796883,1353067250173028676,4249511820642706384,6954638962073438443],"qHole_":6051865069970393497}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that conjure_aux2_1 = image(permutation((3, 4)), q8_1) + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: image(permutation((3, 4)), q8_1) + Context #1: conjure_aux2_1 = image(permutation((3, 4)), q8_1) + Context #2: { conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that conjure_aux2_1 = image(permutation((3, 4)), q8_1) + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + Context #3: { conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that conjure_aux2_1 = image(permutation((3, 4)), q8_1) + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + Context #4: [{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that conjure_aux2_1 = image(permutation((3, 4)), q8_1) + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]] + Context #5: and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that conjure_aux2_1 = image(permutation((3, 4)), q8_1) + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + Context #6: [|x| = |conjure_aux1|, + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that conjure_aux2_1 = image(permutation((3, 4)), q8_1) + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]); + int(1..2)] + Context #7: |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that conjure_aux2_1 = image(permutation((3, 4)), q8_1) + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + Context #8: { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that conjure_aux2_1 = image(permutation((3, 4)), q8_1) + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + Context #9: y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that conjure_aux2_1 = image(permutation((3, 4)), q8_1) + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } +Picking the only option: Answer 1: permutation-image-literal{AsFunction}: Horizontal rule for permutation literal application to a single value (image), AsFunction representation + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and([q9 = q8_1 <-> conjure_aux3 = q10 | (q9, q10) <- [(3, 4), (4, 3); int(1..2)]]) /\ + (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) + } +storedChoice: +image(permutation((3, 4)), q8_1) -6565377216106402436 +AnsweredRule {qHole_ = -6565377216106402436, qAscendants_ = fromList [-8683446058401842621,-8501667396727033866,-6589174251984098358,-5196229448616722462,-2562107481961042620,-1290778481550223845,5400239128163960843,7319032080622836357,8711639898256895276], aRuleName_ = "permutation-image-literal{AsFunction}"} +LF: {"AnsweredRule":{"aRuleName_":"permutation-image-literal{AsFunction}","qAscendants_":[-8683446058401842621,-8501667396727033866,-6589174251984098358,-5196229448616722462,-2562107481961042620,-1290778481550223845,5400239128163960843,7319032080622836357,8711639898256895276],"qHole_":-6565377216106402436}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and([q9 = q8_1 <-> conjure_aux3 = q10 | (q9, q10) <- [(3, 4), (4, 3); int(1..2)]]) /\ + (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: [(3, 4), (4, 3); int(1..2)] + Context #1: [q9 = q8_1 <-> conjure_aux3 = q10 | (q9, q10) <- [(3, 4), (4, 3); int(1..2)]] + Context #2: and([q9 = q8_1 <-> conjure_aux3 = q10 | (q9, q10) <- [(3, 4), (4, 3); int(1..2)]]) + Context #3: [and([q9 = q8_1 <-> conjure_aux3 = q10 | (q9, q10) <- [(3, 4), (4, 3); int(1..2)]]), + !or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1; + int(1..2)] + Context #4: and([q9 = q8_1 <-> conjure_aux3 = q10 | (q9, q10) <- [(3, 4), (4, 3); int(1..2)]]) /\ + (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) + Context #5: { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and([q9 = q8_1 <-> conjure_aux3 = q10 | (q9, q10) <- [(3, 4), (4, 3); int(1..2)]]) /\ + (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) + } + Context #6: conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and([q9 = q8_1 <-> conjure_aux3 = q10 | (q9, q10) <- [(3, 4), (4, 3); int(1..2)]]) /\ + (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) + } + Context #7: { conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and([q9 = q8_1 <-> conjure_aux3 = q10 | (q9, q10) <- [(3, 4), (4, 3); int(1..2)]]) /\ + (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + Context #8: { conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and([q9 = q8_1 <-> conjure_aux3 = q10 | (q9, q10) <- [(3, 4), (4, 3); int(1..2)]]) /\ + (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + Context #9: [{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and([q9 = q8_1 <-> conjure_aux3 = q10 | (q9, q10) <- [(3, 4), (4, 3); int(1..2)]]) /\ + (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]] + Context #10: and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and([q9 = q8_1 <-> conjure_aux3 = q10 | (q9, q10) <- [(3, 4), (4, 3); int(1..2)]]) /\ + (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + Context #11: [|x| = |conjure_aux1|, + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and([q9 = q8_1 <-> conjure_aux3 = q10 | (q9, q10) <- [(3, 4), (4, 3); int(1..2)]]) /\ + (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]); + int(1..2)] + Context #12: |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and([q9 = q8_1 <-> conjure_aux3 = q10 | (q9, q10) <- [(3, 4), (4, 3); int(1..2)]]) /\ + (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + Context #13: { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and([q9 = q8_1 <-> conjure_aux3 = q10 | (q9, q10) <- [(3, 4), (4, 3); int(1..2)]]) /\ + (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + Context #14: y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and([q9 = q8_1 <-> conjure_aux3 = q10 | (q9, q10) <- [(3, 4), (4, 3); int(1..2)]]) /\ + (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } +Picking the only option: Answer 1: full-evaluate: Full evaluator + [(3, 4), (4, 3); int(1..2)] +storedChoice: +[(3, 4), (4, 3); int(1..2)] 6597397470067790033 +AnsweredRule {qHole_ = 6597397470067790033, qAscendants_ = fromList [-8621354921797967448,-6160248818055544346,-6049820697610812758,-4894284809815571873,-4858508204008314707,-4635274203177452231,-1665058964617223774,996353907888938120,1107585814561782716,1593343993162845666,1994644797538381771,2641311773319376803,3730217346423440641,5862930277568425410], aRuleName_ = "full-evaluate"} +LF: {"AnsweredRule":{"aRuleName_":"full-evaluate","qAscendants_":[-8621354921797967448,-6160248818055544346,-6049820697610812758,-4894284809815571873,-4858508204008314707,-4635274203177452231,-1665058964617223774,996353907888938120,1107585814561782716,1593343993162845666,1994644797538381771,2641311773319376803,3730217346423440641,5862930277568425410],"qHole_":6597397470067790033}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and([q9 = q8_1 <-> conjure_aux3 = q10 | (q9, q10) <- [(3, 4), (4, 3); int(1..2)]]) /\ + (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: [q9 = q8_1 <-> conjure_aux3 = q10 | (q9, q10) <- [(3, 4), (4, 3); int(1..2)]] + Context #1: and([q9 = q8_1 <-> conjure_aux3 = q10 | (q9, q10) <- [(3, 4), (4, 3); int(1..2)]]) + Context #2: [and([q9 = q8_1 <-> conjure_aux3 = q10 | (q9, q10) <- [(3, 4), (4, 3); int(1..2)]]), + !or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1; + int(1..2)] + Context #3: and([q9 = q8_1 <-> conjure_aux3 = q10 | (q9, q10) <- [(3, 4), (4, 3); int(1..2)]]) /\ + (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) + Context #4: { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and([q9 = q8_1 <-> conjure_aux3 = q10 | (q9, q10) <- [(3, 4), (4, 3); int(1..2)]]) /\ + (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) + } + Context #5: conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and([q9 = q8_1 <-> conjure_aux3 = q10 | (q9, q10) <- [(3, 4), (4, 3); int(1..2)]]) /\ + (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) + } + Context #6: { conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and([q9 = q8_1 <-> conjure_aux3 = q10 | (q9, q10) <- [(3, 4), (4, 3); int(1..2)]]) /\ + (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + Context #7: { conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and([q9 = q8_1 <-> conjure_aux3 = q10 | (q9, q10) <- [(3, 4), (4, 3); int(1..2)]]) /\ + (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + Context #8: [{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and([q9 = q8_1 <-> conjure_aux3 = q10 | (q9, q10) <- [(3, 4), (4, 3); int(1..2)]]) /\ + (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]] + Context #9: and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and([q9 = q8_1 <-> conjure_aux3 = q10 | (q9, q10) <- [(3, 4), (4, 3); int(1..2)]]) /\ + (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + Context #10: [|x| = |conjure_aux1|, + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and([q9 = q8_1 <-> conjure_aux3 = q10 | (q9, q10) <- [(3, 4), (4, 3); int(1..2)]]) /\ + (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]); + int(1..2)] + Context #11: |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and([q9 = q8_1 <-> conjure_aux3 = q10 | (q9, q10) <- [(3, 4), (4, 3); int(1..2)]]) /\ + (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + Context #12: { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and([q9 = q8_1 <-> conjure_aux3 = q10 | (q9, q10) <- [(3, 4), (4, 3); int(1..2)]]) /\ + (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + Context #13: y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and([q9 = q8_1 <-> conjure_aux3 = q10 | (q9, q10) <- [(3, 4), (4, 3); int(1..2)]]) /\ + (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } +Picking the only option: Answer 1: complex-pattern: complex pattern on tuple patterns + [q13[1] = q8_1 <-> conjure_aux3 = q13[2] | q13 <- [(3, 4), (4, 3); int(1..2)]] +storedChoice: +[q9 = q8_1 <-> conjure_aux3 = q10 | (q9, q10) <- [(3, 4), (4, 3); int(1..2)]] 996353907888938120 +AnsweredRule {qHole_ = 996353907888938120, qAscendants_ = fromList [-8621354921797967448,-6160248818055544346,-6049820697610812758,-4894284809815571873,-4858508204008314707,-4635274203177452231,-1665058964617223774,1107585814561782716,1593343993162845666,1994644797538381771,2641311773319376803,3730217346423440641,5862930277568425410], aRuleName_ = "complex-pattern"} +LF: {"AnsweredRule":{"aRuleName_":"complex-pattern","qAscendants_":[-8621354921797967448,-6160248818055544346,-6049820697610812758,-4894284809815571873,-4858508204008314707,-4635274203177452231,-1665058964617223774,1107585814561782716,1593343993162845666,1994644797538381771,2641311773319376803,3730217346423440641,5862930277568425410],"qHole_":996353907888938120}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and([q13[1] = q8_1 <-> conjure_aux3 = q13[2] | q13 <- [(3, 4), (4, 3); int(1..2)]]) /\ + (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: [q13[1] = q8_1 <-> conjure_aux3 = q13[2] | q13 <- [(3, 4), (4, 3); int(1..2)]] + Context #1: and([q13[1] = q8_1 <-> conjure_aux3 = q13[2] | q13 <- [(3, 4), (4, 3); int(1..2)]]) + Context #2: [and([q13[1] = q8_1 <-> conjure_aux3 = q13[2] | q13 <- [(3, 4), (4, 3); int(1..2)]]), + !or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1; + int(1..2)] + Context #3: and([q13[1] = q8_1 <-> conjure_aux3 = q13[2] | q13 <- [(3, 4), (4, 3); int(1..2)]]) /\ + (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) + Context #4: { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and([q13[1] = q8_1 <-> conjure_aux3 = q13[2] | q13 <- [(3, 4), (4, 3); int(1..2)]]) /\ + (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) + } + Context #5: conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and([q13[1] = q8_1 <-> conjure_aux3 = q13[2] | q13 <- [(3, 4), (4, 3); int(1..2)]]) /\ + (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) + } + Context #6: { conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and([q13[1] = q8_1 <-> conjure_aux3 = q13[2] | q13 <- [(3, 4), (4, 3); int(1..2)]]) /\ + (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + Context #7: { conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and([q13[1] = q8_1 <-> conjure_aux3 = q13[2] | q13 <- [(3, 4), (4, 3); int(1..2)]]) /\ + (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + Context #8: [{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and([q13[1] = q8_1 <-> conjure_aux3 = q13[2] | q13 <- [(3, 4), (4, 3); int(1..2)]]) /\ + (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]] + Context #9: and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and([q13[1] = q8_1 <-> conjure_aux3 = q13[2] | q13 <- [(3, 4), (4, 3); int(1..2)]]) /\ + (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + Context #10: [|x| = |conjure_aux1|, + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and([q13[1] = q8_1 <-> conjure_aux3 = q13[2] | q13 <- [(3, 4), (4, 3); int(1..2)]]) /\ + (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]); + int(1..2)] + Context #11: |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and([q13[1] = q8_1 <-> conjure_aux3 = q13[2] | q13 <- [(3, 4), (4, 3); int(1..2)]]) /\ + (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + Context #12: { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and([q13[1] = q8_1 <-> conjure_aux3 = q13[2] | q13 <- [(3, 4), (4, 3); int(1..2)]]) /\ + (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + Context #13: y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and([q13[1] = q8_1 <-> conjure_aux3 = q13[2] | q13 <- [(3, 4), (4, 3); int(1..2)]]) /\ + (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } +Picking the only option: Answer 1: matrix-comprehension-literal: Vertical rule for matrix-comprehension on matrix literal + flatten(1, + [[q13[1] = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (3, 4)], + [q13[1] = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (4, 3)]; + int(1..2)]) +storedChoice: +[q13[1] = q8_1 <-> conjure_aux3 = q13[2] | q13 <- [(3, 4), (4, 3); int(1..2)]] 3456861798216985162 +AnsweredRule {qHole_ = 3456861798216985162, qAscendants_ = fromList [-8808315865059383030,-8227483119145124211,-7793095449913038876,-5679502255425066053,-3572216896086163269,-3021143752573374113,-2561056581393168238,-842750970546105960,3371366859945964624,5522715912807809257,6264069036653869010,7196566142350255202,8156173651558168583], aRuleName_ = "matrix-comprehension-literal"} +LF: {"AnsweredRule":{"aRuleName_":"matrix-comprehension-literal","qAscendants_":[-8808315865059383030,-8227483119145124211,-7793095449913038876,-5679502255425066053,-3572216896086163269,-3021143752573374113,-2561056581393168238,-842750970546105960,3371366859945964624,5522715912807809257,6264069036653869010,7196566142350255202,8156173651558168583],"qHole_":3456861798216985162}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, + [[q13[1] = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (3, 4)], + [q13[1] = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (4, 3)]; + int(1..2)])) + /\ (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: q13[1] + Context #1: q13[1] = q8_1 + Context #2: q13[1] = q8_1 <-> conjure_aux3 = q13[2] + Context #3: [q13[1] = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (3, 4)] + Context #4: [[q13[1] = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (3, 4)], + [q13[1] = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (4, 3)]; + int(1..2)] + Context #5: flatten(1, + [[q13[1] = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (3, 4)], + [q13[1] = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (4, 3)]; + int(1..2)]) + Context #6: and(flatten(1, + [[q13[1] = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (3, 4)], + [q13[1] = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (4, 3)]; + int(1..2)])) + Context #7: [and(flatten(1, + [[q13[1] = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (3, 4)], + [q13[1] = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (4, 3)]; + int(1..2)])), + !or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1; + int(1..2)] + Context #8: and(flatten(1, + [[q13[1] = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (3, 4)], + [q13[1] = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (4, 3)]; + int(1..2)])) + /\ (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) + Context #9: { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, + [[q13[1] = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (3, 4)], + [q13[1] = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (4, 3)]; + int(1..2)])) + /\ (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) + } + Context #10: conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, + [[q13[1] = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (3, 4)], + [q13[1] = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (4, 3)]; + int(1..2)])) + /\ (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) + } + Context #11: { conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, + [[q13[1] = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (3, 4)], + [q13[1] = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (4, 3)]; + int(1..2)])) + /\ (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + Context #12: { conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, + [[q13[1] = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (3, 4)], + [q13[1] = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (4, 3)]; + int(1..2)])) + /\ (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + Context #13: [{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, + [[q13[1] = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (3, 4)], + [q13[1] = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (4, 3)]; + int(1..2)])) + /\ (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]] + Context #14: and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, + [[q13[1] = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (3, 4)], + [q13[1] = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (4, 3)]; + int(1..2)])) + /\ (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + Context #15: [|x| = |conjure_aux1|, + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, + [[q13[1] = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (3, 4)], + [q13[1] = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (4, 3)]; + int(1..2)])) + /\ (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]); + int(1..2)] + Context #16: |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, + [[q13[1] = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (3, 4)], + [q13[1] = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (4, 3)]; + int(1..2)])) + /\ (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + Context #17: { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, + [[q13[1] = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (3, 4)], + [q13[1] = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (4, 3)]; + int(1..2)])) + /\ (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + Context #18: y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, + [[q13[1] = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (3, 4)], + [q13[1] = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (4, 3)]; + int(1..2)])) + /\ (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } +Picking the only option: Answer 1: full-evaluate: Full evaluator + 3 +storedChoice: +q13[1] -1254902052079317740 +AnsweredRule {qHole_ = -1254902052079317740, qAscendants_ = fromList [-7844826506044189197,-6543998516580374433,-5468160839539146108,-4646329838907093569,-4421494240673914403,-4030269164244882685,-3696611495810109143,-3345198454859526376,-2923685885462842550,-2579765278873905792,-2489053689031557395,-2037117675633093401,-1199749775392010500,-1159821892128975232,-61377228416248265,964892601978301791,3910121320990104243,4511388692183383834], aRuleName_ = "full-evaluate"} +LF: {"AnsweredRule":{"aRuleName_":"full-evaluate","qAscendants_":[-7844826506044189197,-6543998516580374433,-5468160839539146108,-4646329838907093569,-4421494240673914403,-4030269164244882685,-3696611495810109143,-3345198454859526376,-2923685885462842550,-2579765278873905792,-2489053689031557395,-2037117675633093401,-1199749775392010500,-1159821892128975232,-61377228416248265,964892601978301791,3910121320990104243,4511388692183383834],"qHole_":-1254902052079317740}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, + [[3 = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (3, 4)], [q13[1] = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (4, 3)]; + int(1..2)])) + /\ (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: q13[2] + Context #1: conjure_aux3 = q13[2] + Context #2: 3 = q8_1 <-> conjure_aux3 = q13[2] + Context #3: [3 = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (3, 4)] + Context #4: [[3 = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (3, 4)], + [q13[1] = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (4, 3)]; + int(1..2)] + Context #5: flatten(1, + [[3 = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (3, 4)], [q13[1] = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (4, 3)]; + int(1..2)]) + Context #6: and(flatten(1, + [[3 = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (3, 4)], [q13[1] = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (4, 3)]; + int(1..2)])) + Context #7: [and(flatten(1, + [[3 = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (3, 4)], [q13[1] = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (4, 3)]; + int(1..2)])), + !or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1; + int(1..2)] + Context #8: and(flatten(1, + [[3 = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (3, 4)], [q13[1] = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (4, 3)]; + int(1..2)])) + /\ (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) + Context #9: { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, + [[3 = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (3, 4)], [q13[1] = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (4, 3)]; + int(1..2)])) + /\ (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) + } + Context #10: conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, + [[3 = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (3, 4)], [q13[1] = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (4, 3)]; + int(1..2)])) + /\ (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) + } + Context #11: { conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, + [[3 = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (3, 4)], [q13[1] = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (4, 3)]; + int(1..2)])) + /\ (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + Context #12: { conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, + [[3 = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (3, 4)], [q13[1] = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (4, 3)]; + int(1..2)])) + /\ (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + Context #13: [{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, + [[3 = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (3, 4)], [q13[1] = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (4, 3)]; + int(1..2)])) + /\ (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]] + Context #14: and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, + [[3 = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (3, 4)], + [q13[1] = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (4, 3)]; + int(1..2)])) + /\ (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + Context #15: [|x| = |conjure_aux1|, + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, + [[3 = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (3, 4)], + [q13[1] = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (4, 3)]; + int(1..2)])) + /\ (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]); + int(1..2)] + Context #16: |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, + [[3 = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (3, 4)], + [q13[1] = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (4, 3)]; + int(1..2)])) + /\ (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + Context #17: { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, + [[3 = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (3, 4)], + [q13[1] = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (4, 3)]; + int(1..2)])) + /\ (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + Context #18: y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, + [[3 = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (3, 4)], + [q13[1] = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (4, 3)]; + int(1..2)])) + /\ (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } +Picking the only option: Answer 1: full-evaluate: Full evaluator + 4 +storedChoice: +q13[2] -1254620565291325713 +AnsweredRule {qHole_ = -1254620565291325713, qAscendants_ = fromList [-8360775170969626109,-8218634654132870929,-7641638248746524641,-4934801957947094136,-4254522952928052133,-4092969587983186253,-3780104048260027650,-2622265047463603714,-848316662104045049,563172654367211215,1222024046659559696,4078666449752848978,4662787952378127984,5249190568318080416,5574891365015849631,7061285353711906011,7866305697050141526,9112935851435552216], aRuleName_ = "full-evaluate"} +LF: {"AnsweredRule":{"aRuleName_":"full-evaluate","qAscendants_":[-8360775170969626109,-8218634654132870929,-7641638248746524641,-4934801957947094136,-4254522952928052133,-4092969587983186253,-3780104048260027650,-2622265047463603714,-848316662104045049,563172654367211215,1222024046659559696,4078666449752848978,4662787952378127984,5249190568318080416,5574891365015849631,7061285353711906011,7866305697050141526,9112935851435552216],"qHole_":-1254620565291325713}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, + [[3 = q8_1 <-> conjure_aux3 = 4 | letting q13 be (3, 4)], [q13[1] = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (4, 3)]; + int(1..2)])) + /\ (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: q13[1] + Context #1: q13[1] = q8_1 + Context #2: q13[1] = q8_1 <-> conjure_aux3 = q13[2] + Context #3: [q13[1] = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (4, 3)] + Context #4: [[3 = q8_1 <-> conjure_aux3 = 4 | letting q13 be (3, 4)], + [q13[1] = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (4, 3)]; + int(1..2)] + Context #5: flatten(1, + [[3 = q8_1 <-> conjure_aux3 = 4 | letting q13 be (3, 4)], [q13[1] = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (4, 3)]; + int(1..2)]) + Context #6: and(flatten(1, + [[3 = q8_1 <-> conjure_aux3 = 4 | letting q13 be (3, 4)], [q13[1] = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (4, 3)]; + int(1..2)])) + Context #7: [and(flatten(1, + [[3 = q8_1 <-> conjure_aux3 = 4 | letting q13 be (3, 4)], [q13[1] = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (4, 3)]; + int(1..2)])), + !or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1; + int(1..2)] + Context #8: and(flatten(1, + [[3 = q8_1 <-> conjure_aux3 = 4 | letting q13 be (3, 4)], [q13[1] = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (4, 3)]; + int(1..2)])) + /\ (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) + Context #9: { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, + [[3 = q8_1 <-> conjure_aux3 = 4 | letting q13 be (3, 4)], [q13[1] = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (4, 3)]; + int(1..2)])) + /\ (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) + } + Context #10: conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, + [[3 = q8_1 <-> conjure_aux3 = 4 | letting q13 be (3, 4)], [q13[1] = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (4, 3)]; + int(1..2)])) + /\ (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) + } + Context #11: { conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, + [[3 = q8_1 <-> conjure_aux3 = 4 | letting q13 be (3, 4)], [q13[1] = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (4, 3)]; + int(1..2)])) + /\ (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + Context #12: { conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, + [[3 = q8_1 <-> conjure_aux3 = 4 | letting q13 be (3, 4)], [q13[1] = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (4, 3)]; + int(1..2)])) + /\ (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + Context #13: [{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, + [[3 = q8_1 <-> conjure_aux3 = 4 | letting q13 be (3, 4)], [q13[1] = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (4, 3)]; + int(1..2)])) + /\ (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]] + Context #14: and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, + [[3 = q8_1 <-> conjure_aux3 = 4 | letting q13 be (3, 4)], [q13[1] = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (4, 3)]; + int(1..2)])) + /\ (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + Context #15: [|x| = |conjure_aux1|, + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, + [[3 = q8_1 <-> conjure_aux3 = 4 | letting q13 be (3, 4)], [q13[1] = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (4, 3)]; + int(1..2)])) + /\ (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]); + int(1..2)] + Context #16: |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, + [[3 = q8_1 <-> conjure_aux3 = 4 | letting q13 be (3, 4)], [q13[1] = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (4, 3)]; + int(1..2)])) + /\ (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + Context #17: { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, + [[3 = q8_1 <-> conjure_aux3 = 4 | letting q13 be (3, 4)], + [q13[1] = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (4, 3)]; + int(1..2)])) + /\ (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + Context #18: y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, + [[3 = q8_1 <-> conjure_aux3 = 4 | letting q13 be (3, 4)], + [q13[1] = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (4, 3)]; + int(1..2)])) + /\ (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } +Picking the only option: Answer 1: full-evaluate: Full evaluator + 4 +storedChoice: +q13[1] -1254902052079317740 +AnsweredRule {qHole_ = -1254902052079317740, qAscendants_ = fromList [-8638629789947627417,-7681680422406975063,-7045052392114671596,-5468160839539146108,-5360000098558189830,-5130716656066417701,-3536433963763386607,-3341254942655847808,-1332675206370029612,-61377228416248265,518672155518189655,1368815305078223764,1506712726218393853,2813413964084179331,4256368997522955231,6094767248156078778,6822727452915095676,7566490689068664978], aRuleName_ = "full-evaluate"} +LF: {"AnsweredRule":{"aRuleName_":"full-evaluate","qAscendants_":[-8638629789947627417,-7681680422406975063,-7045052392114671596,-5468160839539146108,-5360000098558189830,-5130716656066417701,-3536433963763386607,-3341254942655847808,-1332675206370029612,-61377228416248265,518672155518189655,1368815305078223764,1506712726218393853,2813413964084179331,4256368997522955231,6094767248156078778,6822727452915095676,7566490689068664978],"qHole_":-1254902052079317740}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, + [[3 = q8_1 <-> conjure_aux3 = 4 | letting q13 be (3, 4)], [4 = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (4, 3)]; int(1..2)])) + /\ (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: q13[2] + Context #1: conjure_aux3 = q13[2] + Context #2: 4 = q8_1 <-> conjure_aux3 = q13[2] + Context #3: [4 = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (4, 3)] + Context #4: [[3 = q8_1 <-> conjure_aux3 = 4 | letting q13 be (3, 4)], [4 = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (4, 3)]; + int(1..2)] + Context #5: flatten(1, + [[3 = q8_1 <-> conjure_aux3 = 4 | letting q13 be (3, 4)], [4 = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (4, 3)]; int(1..2)]) + Context #6: and(flatten(1, + [[3 = q8_1 <-> conjure_aux3 = 4 | letting q13 be (3, 4)], [4 = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (4, 3)]; int(1..2)])) + Context #7: [and(flatten(1, + [[3 = q8_1 <-> conjure_aux3 = 4 | letting q13 be (3, 4)], [4 = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (4, 3)]; int(1..2)])), + !or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1; + int(1..2)] + Context #8: and(flatten(1, + [[3 = q8_1 <-> conjure_aux3 = 4 | letting q13 be (3, 4)], [4 = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (4, 3)]; int(1..2)])) + /\ (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) + Context #9: { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, + [[3 = q8_1 <-> conjure_aux3 = 4 | letting q13 be (3, 4)], [4 = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (4, 3)]; int(1..2)])) + /\ (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) + } + Context #10: conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, + [[3 = q8_1 <-> conjure_aux3 = 4 | letting q13 be (3, 4)], [4 = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (4, 3)]; int(1..2)])) + /\ (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) + } + Context #11: { conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, + [[3 = q8_1 <-> conjure_aux3 = 4 | letting q13 be (3, 4)], [4 = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (4, 3)]; int(1..2)])) + /\ (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + Context #12: { conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, + [[3 = q8_1 <-> conjure_aux3 = 4 | letting q13 be (3, 4)], [4 = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (4, 3)]; int(1..2)])) + /\ (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + Context #13: [{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, + [[3 = q8_1 <-> conjure_aux3 = 4 | letting q13 be (3, 4)], [4 = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (4, 3)]; int(1..2)])) + /\ (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]] + Context #14: and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, + [[3 = q8_1 <-> conjure_aux3 = 4 | letting q13 be (3, 4)], [4 = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (4, 3)]; + int(1..2)])) + /\ (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + Context #15: [|x| = |conjure_aux1|, + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, + [[3 = q8_1 <-> conjure_aux3 = 4 | letting q13 be (3, 4)], [4 = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (4, 3)]; + int(1..2)])) + /\ (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]); + int(1..2)] + Context #16: |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, + [[3 = q8_1 <-> conjure_aux3 = 4 | letting q13 be (3, 4)], [4 = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (4, 3)]; + int(1..2)])) + /\ (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + Context #17: { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, + [[3 = q8_1 <-> conjure_aux3 = 4 | letting q13 be (3, 4)], [4 = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (4, 3)]; + int(1..2)])) + /\ (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + Context #18: y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, + [[3 = q8_1 <-> conjure_aux3 = 4 | letting q13 be (3, 4)], [4 = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (4, 3)]; + int(1..2)])) + /\ (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } +Picking the only option: Answer 1: full-evaluate: Full evaluator + 3 +storedChoice: +q13[2] -1254620565291325713 +AnsweredRule {qHole_ = -1254620565291325713, qAscendants_ = fromList [-8870698451967212431,-8218634654132870929,-8157916199347819983,-6958532007910279584,-4735583185965836928,-3733766703817256233,-1365219118307736560,-1326414908464043218,-756643065960997164,-238771092705033653,525451447959791552,2934402913780861128,4090216973995379955,4246953395184334158,4325482688218662469,4385767247150328058,4926105801959606859,4926669858781506740], aRuleName_ = "full-evaluate"} +LF: {"AnsweredRule":{"aRuleName_":"full-evaluate","qAscendants_":[-8870698451967212431,-8218634654132870929,-8157916199347819983,-6958532007910279584,-4735583185965836928,-3733766703817256233,-1365219118307736560,-1326414908464043218,-756643065960997164,-238771092705033653,525451447959791552,2934402913780861128,4090216973995379955,4246953395184334158,4325482688218662469,4385767247150328058,4926105801959606859,4926669858781506740],"qHole_":-1254620565291325713}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, + [[3 = q8_1 <-> conjure_aux3 = 4 | letting q13 be (3, 4)], [4 = q8_1 <-> conjure_aux3 = 3 | letting q13 be (4, 3)]; int(1..2)])) + /\ (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: [4 = q8_1 <-> conjure_aux3 = 3 | letting q13 be (4, 3)] + Context #1: [[3 = q8_1 <-> conjure_aux3 = 4 | letting q13 be (3, 4)], [4 = q8_1 <-> conjure_aux3 = 3 | letting q13 be (4, 3)]; + int(1..2)] + Context #2: flatten(1, + [[3 = q8_1 <-> conjure_aux3 = 4 | letting q13 be (3, 4)], [4 = q8_1 <-> conjure_aux3 = 3 | letting q13 be (4, 3)]; int(1..2)]) + Context #3: and(flatten(1, + [[3 = q8_1 <-> conjure_aux3 = 4 | letting q13 be (3, 4)], [4 = q8_1 <-> conjure_aux3 = 3 | letting q13 be (4, 3)]; int(1..2)])) + Context #4: [and(flatten(1, + [[3 = q8_1 <-> conjure_aux3 = 4 | letting q13 be (3, 4)], [4 = q8_1 <-> conjure_aux3 = 3 | letting q13 be (4, 3)]; int(1..2)])), + !or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1; + int(1..2)] + Context #5: and(flatten(1, + [[3 = q8_1 <-> conjure_aux3 = 4 | letting q13 be (3, 4)], [4 = q8_1 <-> conjure_aux3 = 3 | letting q13 be (4, 3)]; int(1..2)])) + /\ (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) + Context #6: { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, + [[3 = q8_1 <-> conjure_aux3 = 4 | letting q13 be (3, 4)], [4 = q8_1 <-> conjure_aux3 = 3 | letting q13 be (4, 3)]; int(1..2)])) + /\ (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) + } + Context #7: conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, + [[3 = q8_1 <-> conjure_aux3 = 4 | letting q13 be (3, 4)], [4 = q8_1 <-> conjure_aux3 = 3 | letting q13 be (4, 3)]; int(1..2)])) + /\ (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) + } + Context #8: { conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, + [[3 = q8_1 <-> conjure_aux3 = 4 | letting q13 be (3, 4)], [4 = q8_1 <-> conjure_aux3 = 3 | letting q13 be (4, 3)]; int(1..2)])) + /\ (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + Context #9: { conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, + [[3 = q8_1 <-> conjure_aux3 = 4 | letting q13 be (3, 4)], [4 = q8_1 <-> conjure_aux3 = 3 | letting q13 be (4, 3)]; int(1..2)])) + /\ (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + Context #10: [{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, + [[3 = q8_1 <-> conjure_aux3 = 4 | letting q13 be (3, 4)], [4 = q8_1 <-> conjure_aux3 = 3 | letting q13 be (4, 3)]; int(1..2)])) + /\ (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]] + Context #11: and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, + [[3 = q8_1 <-> conjure_aux3 = 4 | letting q13 be (3, 4)], [4 = q8_1 <-> conjure_aux3 = 3 | letting q13 be (4, 3)]; int(1..2)])) + /\ (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + Context #12: [|x| = |conjure_aux1|, + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, + [[3 = q8_1 <-> conjure_aux3 = 4 | letting q13 be (3, 4)], [4 = q8_1 <-> conjure_aux3 = 3 | letting q13 be (4, 3)]; int(1..2)])) + /\ (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]); + int(1..2)] + Context #13: |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, + [[3 = q8_1 <-> conjure_aux3 = 4 | letting q13 be (3, 4)], [4 = q8_1 <-> conjure_aux3 = 3 | letting q13 be (4, 3)]; int(1..2)])) + /\ (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + Context #14: { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, + [[3 = q8_1 <-> conjure_aux3 = 4 | letting q13 be (3, 4)], [4 = q8_1 <-> conjure_aux3 = 3 | letting q13 be (4, 3)]; + int(1..2)])) + /\ (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + Context #15: y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, + [[3 = q8_1 <-> conjure_aux3 = 4 | letting q13 be (3, 4)], [4 = q8_1 <-> conjure_aux3 = 3 | letting q13 be (4, 3)]; + int(1..2)])) + /\ (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } +Picking the only option: Answer 1: generators-first: Inlining comprehension lettings. + [4 = q8_1 <-> conjure_aux3 = 3 |] +storedChoice: +[4 = q8_1 <-> conjure_aux3 = 3 | letting q13 be (4, 3)] 7815870421468516721 +AnsweredRule {qHole_ = 7815870421468516721, qAscendants_ = fromList [-7319924227898755161,-6204074559855855953,-5721547888581640964,-4667135429861035401,-3119038628659086386,-2914873009721382719,-275708737112837829,358797451837378,588328580564008008,1171576539747863800,3860402082075414220,5255108035061878259,7534557817041195235,8046872103256922185,9076826399099772257], aRuleName_ = "generators-first"} +LF: {"AnsweredRule":{"aRuleName_":"generators-first","qAscendants_":[-7319924227898755161,-6204074559855855953,-5721547888581640964,-4667135429861035401,-3119038628659086386,-2914873009721382719,-275708737112837829,358797451837378,588328580564008008,1171576539747863800,3860402082075414220,5255108035061878259,7534557817041195235,8046872103256922185,9076826399099772257],"qHole_":7815870421468516721}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4 | letting q13 be (3, 4)], [4 = q8_1 <-> conjure_aux3 = 3 |]; int(1..2)])) /\ + (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: [4 = q8_1 <-> conjure_aux3 = 3 |] + Context #1: [[3 = q8_1 <-> conjure_aux3 = 4 | letting q13 be (3, 4)], [4 = q8_1 <-> conjure_aux3 = 3 |]; int(1..2)] + Context #2: flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4 | letting q13 be (3, 4)], [4 = q8_1 <-> conjure_aux3 = 3 |]; int(1..2)]) + Context #3: and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4 | letting q13 be (3, 4)], [4 = q8_1 <-> conjure_aux3 = 3 |]; int(1..2)])) + Context #4: [and(flatten(1, + [[3 = q8_1 <-> conjure_aux3 = 4 | letting q13 be (3, 4)], [4 = q8_1 <-> conjure_aux3 = 3 |]; int(1..2)])), + !or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1; + int(1..2)] + Context #5: and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4 | letting q13 be (3, 4)], [4 = q8_1 <-> conjure_aux3 = 3 |]; int(1..2)])) + /\ (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) + Context #6: { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4 | letting q13 be (3, 4)], [4 = q8_1 <-> conjure_aux3 = 3 |]; int(1..2)])) /\ + (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) + } + Context #7: conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4 | letting q13 be (3, 4)], [4 = q8_1 <-> conjure_aux3 = 3 |]; int(1..2)])) /\ + (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) + } + Context #8: { conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4 | letting q13 be (3, 4)], [4 = q8_1 <-> conjure_aux3 = 3 |]; int(1..2)])) /\ + (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + Context #9: { conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4 | letting q13 be (3, 4)], [4 = q8_1 <-> conjure_aux3 = 3 |]; int(1..2)])) /\ + (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + Context #10: [{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4 | letting q13 be (3, 4)], [4 = q8_1 <-> conjure_aux3 = 3 |]; int(1..2)])) /\ + (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]] + Context #11: and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4 | letting q13 be (3, 4)], [4 = q8_1 <-> conjure_aux3 = 3 |]; int(1..2)])) /\ + (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + Context #12: [|x| = |conjure_aux1|, + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4 | letting q13 be (3, 4)], [4 = q8_1 <-> conjure_aux3 = 3 |]; int(1..2)])) /\ + (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]); + int(1..2)] + Context #13: |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4 | letting q13 be (3, 4)], [4 = q8_1 <-> conjure_aux3 = 3 |]; int(1..2)])) /\ + (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + Context #14: { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4 | letting q13 be (3, 4)], [4 = q8_1 <-> conjure_aux3 = 3 |]; int(1..2)])) /\ + (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + Context #15: y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4 | letting q13 be (3, 4)], [4 = q8_1 <-> conjure_aux3 = 3 |]; int(1..2)])) /\ + (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } +Picking the only option: Answer 1: generators-first: Empty generators. + [4 = q8_1 <-> conjure_aux3 = 3; int(1)] +storedChoice: +[4 = q8_1 <-> conjure_aux3 = 3 |] 2538271587388693524 +AnsweredRule {qHole_ = 2538271587388693524, qAscendants_ = fromList [-8521000068701228812,-8466935177678778299,-8378067175040646304,-7795155064905057512,-7398425908569645990,-5020343327513684658,-1331085484917687815,-382563719840663416,1239306329275872739,3167048961433864186,4591749041469508459,5482352134908236922,5648481728193344963,6702522234416193183,8765316459520566910], aRuleName_ = "generators-first"} +LF: {"AnsweredRule":{"aRuleName_":"generators-first","qAscendants_":[-8521000068701228812,-8466935177678778299,-8378067175040646304,-7795155064905057512,-7398425908569645990,-5020343327513684658,-1331085484917687815,-382563719840663416,1239306329275872739,3167048961433864186,4591749041469508459,5482352134908236922,5648481728193344963,6702522234416193183,8765316459520566910],"qHole_":2538271587388693524}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4 | letting q13 be (3, 4)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: [3 = q8_1 <-> conjure_aux3 = 4 | letting q13 be (3, 4)] + Context #1: [[3 = q8_1 <-> conjure_aux3 = 4 | letting q13 be (3, 4)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)] + Context #2: flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4 | letting q13 be (3, 4)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)]) + Context #3: and(flatten(1, + [[3 = q8_1 <-> conjure_aux3 = 4 | letting q13 be (3, 4)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) + Context #4: [and(flatten(1, + [[3 = q8_1 <-> conjure_aux3 = 4 | letting q13 be (3, 4)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])), + !or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1; + int(1..2)] + Context #5: and(flatten(1, + [[3 = q8_1 <-> conjure_aux3 = 4 | letting q13 be (3, 4)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) + /\ (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) + Context #6: { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4 | letting q13 be (3, 4)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) + } + Context #7: conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4 | letting q13 be (3, 4)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) + } + Context #8: { conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4 | letting q13 be (3, 4)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + Context #9: { conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4 | letting q13 be (3, 4)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + Context #10: [{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4 | letting q13 be (3, 4)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]] + Context #11: and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4 | letting q13 be (3, 4)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + Context #12: [|x| = |conjure_aux1|, + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4 | letting q13 be (3, 4)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]); + int(1..2)] + Context #13: |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4 | letting q13 be (3, 4)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + Context #14: { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4 | letting q13 be (3, 4)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + Context #15: y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4 | letting q13 be (3, 4)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } +Picking the only option: Answer 1: generators-first: Inlining comprehension lettings. + [3 = q8_1 <-> conjure_aux3 = 4 |] +storedChoice: +[3 = q8_1 <-> conjure_aux3 = 4 | letting q13 be (3, 4)] 1317873634227795931 +AnsweredRule {qHole_ = 1317873634227795931, qAscendants_ = fromList [-6229747794032826968,-5833692553090476381,-4830840744837226265,-4695719515395703877,-1447797878088113254,-1026424407203100673,-114180086101386755,1230900640119672810,2384858822123183656,2641682090906853361,4932647657883680462,5503876696275907482,5561643139389034608,8062918047402720448,8618709991360516938], aRuleName_ = "generators-first"} +LF: {"AnsweredRule":{"aRuleName_":"generators-first","qAscendants_":[-6229747794032826968,-5833692553090476381,-4830840744837226265,-4695719515395703877,-1447797878088113254,-1026424407203100673,-114180086101386755,1230900640119672810,2384858822123183656,2641682090906853361,4932647657883680462,5503876696275907482,5561643139389034608,8062918047402720448,8618709991360516938],"qHole_":1317873634227795931}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4 |], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: [3 = q8_1 <-> conjure_aux3 = 4 |] + Context #1: [[3 = q8_1 <-> conjure_aux3 = 4 |], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)] + Context #2: flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4 |], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)]) + Context #3: and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4 |], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) + Context #4: [and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4 |], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])), + !or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1; + int(1..2)] + Context #5: and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4 |], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) + Context #6: { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4 |], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) + } + Context #7: conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4 |], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) + } + Context #8: { conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4 |], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + Context #9: { conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4 |], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + Context #10: [{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4 |], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]] + Context #11: and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4 |], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + Context #12: [|x| = |conjure_aux1|, + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4 |], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]); + int(1..2)] + Context #13: |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4 |], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + Context #14: { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4 |], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + Context #15: y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4 |], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } +Picking the only option: Answer 1: generators-first: Empty generators. + [3 = q8_1 <-> conjure_aux3 = 4; int(1)] +storedChoice: +[3 = q8_1 <-> conjure_aux3 = 4 |] 7527005283398106432 +AnsweredRule {qHole_ = 7527005283398106432, qAscendants_ = fromList [-5151808191572404398,-4353286235323785771,-4339955062448219396,-4142041909263092979,-3736320932349712947,-3440388200198466301,-2029225889893250969,-1817262023712192284,-116834249900757749,483550512093615086,1497957860809309721,2283573903554163553,3854374349353612498,7382215623493355130,8339321953980948829], aRuleName_ = "generators-first"} +LF: {"AnsweredRule":{"aRuleName_":"generators-first","qAscendants_":[-5151808191572404398,-4353286235323785771,-4339955062448219396,-4142041909263092979,-3736320932349712947,-3440388200198466301,-2029225889893250969,-1817262023712192284,-116834249900757749,483550512093615086,1497957860809309721,2283573903554163553,3854374349353612498,7382215623493355130,8339321953980948829],"qHole_":7527005283398106432}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: [(3, 4), (4, 3); int(1..2)] + Context #1: [q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]] + Context #2: or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) + Context #3: !or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) + Context #4: !or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1 + Context #5: [and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])), + !or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1; + int(1..2)] + Context #6: and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) + Context #7: { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) + } + Context #8: conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) + } + Context #9: { conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + Context #10: { conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + Context #11: [{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]] + Context #12: and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + Context #13: [|x| = |conjure_aux1|, + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]); + int(1..2)] + Context #14: |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + Context #15: { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + Context #16: y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } +Picking the only option: Answer 1: full-evaluate: Full evaluator + [(3, 4), (4, 3); int(1..2)] +storedChoice: +[(3, 4), (4, 3); int(1..2)] 6597397470067790033 +AnsweredRule {qHole_ = 6597397470067790033, qAscendants_ = fromList [-9213624152780173787,-5982135693274236766,-5396430067534345835,-2363572399258163690,-2255081376624876153,-320252043164433323,1280603170430058832,2648872121679578871,4076507060053755550,5033554600497872881,6390584767367481427,6475772422542545541,6480002864764397731,6871118355510909196,7049518756068236715,8591929121087659168], aRuleName_ = "full-evaluate"} +LF: {"AnsweredRule":{"aRuleName_":"full-evaluate","qAscendants_":[-9213624152780173787,-5982135693274236766,-5396430067534345835,-2363572399258163690,-2255081376624876153,-320252043164433323,1280603170430058832,2648872121679578871,4076507060053755550,5033554600497872881,6390584767367481427,6475772422542545541,6480002864764397731,6871118355510909196,7049518756068236715,8591929121087659168],"qHole_":6597397470067790033}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: [q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]] + Context #1: or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) + Context #2: !or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) + Context #3: !or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1 + Context #4: [and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])), + !or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1; + int(1..2)] + Context #5: and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) + Context #6: { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) + } + Context #7: conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) + } + Context #8: { conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + Context #9: { conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + Context #10: [{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]] + Context #11: and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + Context #12: [|x| = |conjure_aux1|, + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]); + int(1..2)] + Context #13: |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + Context #14: { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + Context #15: y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } +Picking the only option: Answer 1: complex-pattern: complex pattern on tuple patterns + [q14[1] = conjure_aux3 | q14 <- [(3, 4), (4, 3); int(1..2)]] +storedChoice: +[q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]] 5033554600497872881 +AnsweredRule {qHole_ = 5033554600497872881, qAscendants_ = fromList [-9213624152780173787,-5982135693274236766,-5396430067534345835,-2363572399258163690,-2255081376624876153,-320252043164433323,1280603170430058832,2648872121679578871,4076507060053755550,6390584767367481427,6475772422542545541,6480002864764397731,6871118355510909196,7049518756068236715,8591929121087659168], aRuleName_ = "complex-pattern"} +LF: {"AnsweredRule":{"aRuleName_":"complex-pattern","qAscendants_":[-9213624152780173787,-5982135693274236766,-5396430067534345835,-2363572399258163690,-2255081376624876153,-320252043164433323,1280603170430058832,2648872121679578871,4076507060053755550,6390584767367481427,6475772422542545541,6480002864764397731,6871118355510909196,7049518756068236715,8591929121087659168],"qHole_":5033554600497872881}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!or([q14[1] = conjure_aux3 | q14 <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: [q14[1] = conjure_aux3 | q14 <- [(3, 4), (4, 3); int(1..2)]] + Context #1: or([q14[1] = conjure_aux3 | q14 <- [(3, 4), (4, 3); int(1..2)]]) + Context #2: !or([q14[1] = conjure_aux3 | q14 <- [(3, 4), (4, 3); int(1..2)]]) + Context #3: !or([q14[1] = conjure_aux3 | q14 <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1 + Context #4: [and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])), + !or([q14[1] = conjure_aux3 | q14 <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1; + int(1..2)] + Context #5: and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!or([q14[1] = conjure_aux3 | q14 <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) + Context #6: { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!or([q14[1] = conjure_aux3 | q14 <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) + } + Context #7: conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!or([q14[1] = conjure_aux3 | q14 <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) + } + Context #8: { conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!or([q14[1] = conjure_aux3 | q14 <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + Context #9: { conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!or([q14[1] = conjure_aux3 | q14 <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + Context #10: [{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!or([q14[1] = conjure_aux3 | q14 <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]] + Context #11: and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!or([q14[1] = conjure_aux3 | q14 <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + Context #12: [|x| = |conjure_aux1|, + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!or([q14[1] = conjure_aux3 | q14 <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]); + int(1..2)] + Context #13: |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!or([q14[1] = conjure_aux3 | q14 <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + Context #14: { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!or([q14[1] = conjure_aux3 | q14 <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + Context #15: y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!or([q14[1] = conjure_aux3 | q14 <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } +Picking the only option: Answer 1: matrix-comprehension-literal: Vertical rule for matrix-comprehension on matrix literal + flatten(1, [[q14[1] = conjure_aux3 | letting q14 be (3, 4)], [q14[1] = conjure_aux3 | letting q14 be (4, 3)]; int(1..2)]) +storedChoice: +[q14[1] = conjure_aux3 | q14 <- [(3, 4), (4, 3); int(1..2)]] 8665374887955696009 +AnsweredRule {qHole_ = 8665374887955696009, qAscendants_ = fromList [-8790838049079552472,-7586671731712078955,-7257845330645731074,-6187411109644722069,-5035649525051787097,-4935714982215491801,-4790057621145645718,-2980197002499358476,-1690854938850194471,-619668906698634467,1003810935162304708,3378856114517929630,5359983985600686059,5489110086534554143,8428096257079881520], aRuleName_ = "matrix-comprehension-literal"} +LF: {"AnsweredRule":{"aRuleName_":"matrix-comprehension-literal","qAscendants_":[-8790838049079552472,-7586671731712078955,-7257845330645731074,-6187411109644722069,-5035649525051787097,-4935714982215491801,-4790057621145645718,-2980197002499358476,-1690854938850194471,-619668906698634467,1003810935162304708,3378856114517929630,5359983985600686059,5489110086534554143,8428096257079881520],"qHole_":8665374887955696009}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!or(flatten(1, [[q14[1] = conjure_aux3 | letting q14 be (3, 4)], [q14[1] = conjure_aux3 | letting q14 be (4, 3)]; int(1..2)])) <-> + conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: q14[1] + Context #1: q14[1] = conjure_aux3 + Context #2: [q14[1] = conjure_aux3 | letting q14 be (3, 4)] + Context #3: [[q14[1] = conjure_aux3 | letting q14 be (3, 4)], [q14[1] = conjure_aux3 | letting q14 be (4, 3)]; int(1..2)] + Context #4: flatten(1, [[q14[1] = conjure_aux3 | letting q14 be (3, 4)], [q14[1] = conjure_aux3 | letting q14 be (4, 3)]; int(1..2)]) + Context #5: or(flatten(1, + [[q14[1] = conjure_aux3 | letting q14 be (3, 4)], [q14[1] = conjure_aux3 | letting q14 be (4, 3)]; int(1..2)])) + Context #6: !or(flatten(1, + [[q14[1] = conjure_aux3 | letting q14 be (3, 4)], [q14[1] = conjure_aux3 | letting q14 be (4, 3)]; int(1..2)])) + Context #7: !or(flatten(1, + [[q14[1] = conjure_aux3 | letting q14 be (3, 4)], [q14[1] = conjure_aux3 | letting q14 be (4, 3)]; int(1..2)])) + <-> conjure_aux3 = q8_1 + Context #8: [and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])), + !or(flatten(1, [[q14[1] = conjure_aux3 | letting q14 be (3, 4)], [q14[1] = conjure_aux3 | letting q14 be (4, 3)]; int(1..2)])) <-> + conjure_aux3 = q8_1; + int(1..2)] + Context #9: and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!or(flatten(1, [[q14[1] = conjure_aux3 | letting q14 be (3, 4)], [q14[1] = conjure_aux3 | letting q14 be (4, 3)]; int(1..2)])) <-> + conjure_aux3 = q8_1) + Context #10: { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!or(flatten(1, [[q14[1] = conjure_aux3 | letting q14 be (3, 4)], [q14[1] = conjure_aux3 | letting q14 be (4, 3)]; int(1..2)])) <-> + conjure_aux3 = q8_1) + } + Context #11: conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!or(flatten(1, [[q14[1] = conjure_aux3 | letting q14 be (3, 4)], [q14[1] = conjure_aux3 | letting q14 be (4, 3)]; int(1..2)])) <-> + conjure_aux3 = q8_1) + } + Context #12: { conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!or(flatten(1, [[q14[1] = conjure_aux3 | letting q14 be (3, 4)], [q14[1] = conjure_aux3 | letting q14 be (4, 3)]; int(1..2)])) <-> + conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + Context #13: { conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!or(flatten(1, [[q14[1] = conjure_aux3 | letting q14 be (3, 4)], [q14[1] = conjure_aux3 | letting q14 be (4, 3)]; int(1..2)])) <-> + conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + Context #14: [{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!or(flatten(1, [[q14[1] = conjure_aux3 | letting q14 be (3, 4)], [q14[1] = conjure_aux3 | letting q14 be (4, 3)]; int(1..2)])) <-> + conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]] + Context #15: and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!or(flatten(1, [[q14[1] = conjure_aux3 | letting q14 be (3, 4)], [q14[1] = conjure_aux3 | letting q14 be (4, 3)]; int(1..2)])) <-> + conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + Context #16: [|x| = |conjure_aux1|, + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!or(flatten(1, [[q14[1] = conjure_aux3 | letting q14 be (3, 4)], [q14[1] = conjure_aux3 | letting q14 be (4, 3)]; int(1..2)])) <-> + conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]); + int(1..2)] + Context #17: |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!or(flatten(1, [[q14[1] = conjure_aux3 | letting q14 be (3, 4)], [q14[1] = conjure_aux3 | letting q14 be (4, 3)]; int(1..2)])) <-> + conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + Context #18: { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!or(flatten(1, [[q14[1] = conjure_aux3 | letting q14 be (3, 4)], [q14[1] = conjure_aux3 | letting q14 be (4, 3)]; int(1..2)])) <-> + conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + Context #19: y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!or(flatten(1, [[q14[1] = conjure_aux3 | letting q14 be (3, 4)], [q14[1] = conjure_aux3 | letting q14 be (4, 3)]; int(1..2)])) <-> + conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } +Picking the only option: Answer 1: full-evaluate: Full evaluator + 3 +storedChoice: +q14[1] -883253742927518753 +AnsweredRule {qHole_ = -883253742927518753, qAscendants_ = fromList [-9176123018977089417,-9101977553270866225,-9093406545418508012,-9026590884990837132,-7266038392684934735,-7030617368587845027,-6315177474832767189,-6185538668149951971,-5045957588695750237,-2422194591007956529,-2140558072442299093,-1323860184563866252,370104820105510026,1657237947942821584,1725179241386393490,3615940558330371386,6441285251735452902,7836445554474639282,8733492850970682893], aRuleName_ = "full-evaluate"} +LF: {"AnsweredRule":{"aRuleName_":"full-evaluate","qAscendants_":[-9176123018977089417,-9101977553270866225,-9093406545418508012,-9026590884990837132,-7266038392684934735,-7030617368587845027,-6315177474832767189,-6185538668149951971,-5045957588695750237,-2422194591007956529,-2140558072442299093,-1323860184563866252,370104820105510026,1657237947942821584,1725179241386393490,3615940558330371386,6441285251735452902,7836445554474639282,8733492850970682893],"qHole_":-883253742927518753}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!or(flatten(1, [[3 = conjure_aux3 | letting q14 be (3, 4)], [q14[1] = conjure_aux3 | letting q14 be (4, 3)]; int(1..2)])) <-> + conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: q14[1] + Context #1: q14[1] = conjure_aux3 + Context #2: [q14[1] = conjure_aux3 | letting q14 be (4, 3)] + Context #3: [[3 = conjure_aux3 | letting q14 be (3, 4)], [q14[1] = conjure_aux3 | letting q14 be (4, 3)]; int(1..2)] + Context #4: flatten(1, [[3 = conjure_aux3 | letting q14 be (3, 4)], [q14[1] = conjure_aux3 | letting q14 be (4, 3)]; int(1..2)]) + Context #5: or(flatten(1, [[3 = conjure_aux3 | letting q14 be (3, 4)], [q14[1] = conjure_aux3 | letting q14 be (4, 3)]; int(1..2)])) + Context #6: !or(flatten(1, [[3 = conjure_aux3 | letting q14 be (3, 4)], [q14[1] = conjure_aux3 | letting q14 be (4, 3)]; int(1..2)])) + Context #7: !or(flatten(1, [[3 = conjure_aux3 | letting q14 be (3, 4)], [q14[1] = conjure_aux3 | letting q14 be (4, 3)]; int(1..2)])) + <-> conjure_aux3 = q8_1 + Context #8: [and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])), + !or(flatten(1, [[3 = conjure_aux3 | letting q14 be (3, 4)], [q14[1] = conjure_aux3 | letting q14 be (4, 3)]; int(1..2)])) <-> + conjure_aux3 = q8_1; + int(1..2)] + Context #9: and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!or(flatten(1, [[3 = conjure_aux3 | letting q14 be (3, 4)], [q14[1] = conjure_aux3 | letting q14 be (4, 3)]; int(1..2)])) <-> + conjure_aux3 = q8_1) + Context #10: { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!or(flatten(1, [[3 = conjure_aux3 | letting q14 be (3, 4)], [q14[1] = conjure_aux3 | letting q14 be (4, 3)]; int(1..2)])) <-> + conjure_aux3 = q8_1) + } + Context #11: conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!or(flatten(1, [[3 = conjure_aux3 | letting q14 be (3, 4)], [q14[1] = conjure_aux3 | letting q14 be (4, 3)]; int(1..2)])) <-> + conjure_aux3 = q8_1) + } + Context #12: { conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!or(flatten(1, [[3 = conjure_aux3 | letting q14 be (3, 4)], [q14[1] = conjure_aux3 | letting q14 be (4, 3)]; int(1..2)])) <-> + conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + Context #13: { conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!or(flatten(1, [[3 = conjure_aux3 | letting q14 be (3, 4)], [q14[1] = conjure_aux3 | letting q14 be (4, 3)]; int(1..2)])) <-> + conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + Context #14: [{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!or(flatten(1, [[3 = conjure_aux3 | letting q14 be (3, 4)], [q14[1] = conjure_aux3 | letting q14 be (4, 3)]; int(1..2)])) <-> + conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]] + Context #15: and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!or(flatten(1, [[3 = conjure_aux3 | letting q14 be (3, 4)], [q14[1] = conjure_aux3 | letting q14 be (4, 3)]; int(1..2)])) <-> + conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + Context #16: [|x| = |conjure_aux1|, + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!or(flatten(1, [[3 = conjure_aux3 | letting q14 be (3, 4)], [q14[1] = conjure_aux3 | letting q14 be (4, 3)]; int(1..2)])) <-> + conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]); + int(1..2)] + Context #17: |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!or(flatten(1, [[3 = conjure_aux3 | letting q14 be (3, 4)], [q14[1] = conjure_aux3 | letting q14 be (4, 3)]; int(1..2)])) <-> + conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + Context #18: { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!or(flatten(1, [[3 = conjure_aux3 | letting q14 be (3, 4)], [q14[1] = conjure_aux3 | letting q14 be (4, 3)]; int(1..2)])) <-> + conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + Context #19: y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!or(flatten(1, [[3 = conjure_aux3 | letting q14 be (3, 4)], [q14[1] = conjure_aux3 | letting q14 be (4, 3)]; int(1..2)])) <-> + conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } +Picking the only option: Answer 1: full-evaluate: Full evaluator + 4 +storedChoice: +q14[1] -883253742927518753 +AnsweredRule {qHole_ = -883253742927518753, qAscendants_ = fromList [-8969758503132111487,-6784916903301812310,-4362502606594339694,-2424885897194395863,-2417099766119933872,-661357570700780995,659540462714969701,741299023684531871,841316382876489834,1080971480076294633,2455636718555289611,4781036327687591913,6314971418857005121,6957705147325524125,7520484523970872436,7814781884486080266,8472710336593287104,8733492850970682893,9124601515932951508], aRuleName_ = "full-evaluate"} +LF: {"AnsweredRule":{"aRuleName_":"full-evaluate","qAscendants_":[-8969758503132111487,-6784916903301812310,-4362502606594339694,-2424885897194395863,-2417099766119933872,-661357570700780995,659540462714969701,741299023684531871,841316382876489834,1080971480076294633,2455636718555289611,4781036327687591913,6314971418857005121,6957705147325524125,7520484523970872436,7814781884486080266,8472710336593287104,8733492850970682893,9124601515932951508],"qHole_":-883253742927518753}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!or(flatten(1, [[3 = conjure_aux3 | letting q14 be (3, 4)], [4 = conjure_aux3 | letting q14 be (4, 3)]; int(1..2)])) <-> + conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: [4 = conjure_aux3 | letting q14 be (4, 3)] + Context #1: [[3 = conjure_aux3 | letting q14 be (3, 4)], [4 = conjure_aux3 | letting q14 be (4, 3)]; int(1..2)] + Context #2: flatten(1, [[3 = conjure_aux3 | letting q14 be (3, 4)], [4 = conjure_aux3 | letting q14 be (4, 3)]; int(1..2)]) + Context #3: or(flatten(1, [[3 = conjure_aux3 | letting q14 be (3, 4)], [4 = conjure_aux3 | letting q14 be (4, 3)]; int(1..2)])) + Context #4: !or(flatten(1, [[3 = conjure_aux3 | letting q14 be (3, 4)], [4 = conjure_aux3 | letting q14 be (4, 3)]; int(1..2)])) + Context #5: !or(flatten(1, [[3 = conjure_aux3 | letting q14 be (3, 4)], [4 = conjure_aux3 | letting q14 be (4, 3)]; int(1..2)])) <-> + conjure_aux3 = q8_1 + Context #6: [and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])), + !or(flatten(1, [[3 = conjure_aux3 | letting q14 be (3, 4)], [4 = conjure_aux3 | letting q14 be (4, 3)]; int(1..2)])) <-> + conjure_aux3 = q8_1; + int(1..2)] + Context #7: and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!or(flatten(1, [[3 = conjure_aux3 | letting q14 be (3, 4)], [4 = conjure_aux3 | letting q14 be (4, 3)]; int(1..2)])) <-> + conjure_aux3 = q8_1) + Context #8: { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!or(flatten(1, [[3 = conjure_aux3 | letting q14 be (3, 4)], [4 = conjure_aux3 | letting q14 be (4, 3)]; int(1..2)])) <-> + conjure_aux3 = q8_1) + } + Context #9: conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!or(flatten(1, [[3 = conjure_aux3 | letting q14 be (3, 4)], [4 = conjure_aux3 | letting q14 be (4, 3)]; int(1..2)])) <-> + conjure_aux3 = q8_1) + } + Context #10: { conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!or(flatten(1, [[3 = conjure_aux3 | letting q14 be (3, 4)], [4 = conjure_aux3 | letting q14 be (4, 3)]; int(1..2)])) <-> + conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + Context #11: { conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!or(flatten(1, [[3 = conjure_aux3 | letting q14 be (3, 4)], [4 = conjure_aux3 | letting q14 be (4, 3)]; int(1..2)])) <-> + conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + Context #12: [{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!or(flatten(1, [[3 = conjure_aux3 | letting q14 be (3, 4)], [4 = conjure_aux3 | letting q14 be (4, 3)]; int(1..2)])) <-> + conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]] + Context #13: and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!or(flatten(1, [[3 = conjure_aux3 | letting q14 be (3, 4)], [4 = conjure_aux3 | letting q14 be (4, 3)]; int(1..2)])) <-> + conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + Context #14: [|x| = |conjure_aux1|, + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!or(flatten(1, [[3 = conjure_aux3 | letting q14 be (3, 4)], [4 = conjure_aux3 | letting q14 be (4, 3)]; int(1..2)])) <-> + conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]); + int(1..2)] + Context #15: |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!or(flatten(1, [[3 = conjure_aux3 | letting q14 be (3, 4)], [4 = conjure_aux3 | letting q14 be (4, 3)]; int(1..2)])) <-> + conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + Context #16: { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!or(flatten(1, [[3 = conjure_aux3 | letting q14 be (3, 4)], [4 = conjure_aux3 | letting q14 be (4, 3)]; int(1..2)])) <-> + conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + Context #17: y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!or(flatten(1, [[3 = conjure_aux3 | letting q14 be (3, 4)], [4 = conjure_aux3 | letting q14 be (4, 3)]; int(1..2)])) <-> + conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } +Picking the only option: Answer 1: generators-first: Inlining comprehension lettings. + [4 = conjure_aux3 |] +storedChoice: +[4 = conjure_aux3 | letting q14 be (4, 3)] 5094133043100232579 +AnsweredRule {qHole_ = 5094133043100232579, qAscendants_ = fromList [-8909122354700020440,-7460733051808423716,-5113575940370069634,-3275789614875181527,-1485928817419295239,-1453326525258547920,-1190111094765899527,-425934852058965166,-227269000323710205,1017324948146570036,2402920626236815200,4379418785875775437,5239709721973149055,5447511985754467121,6138327529543829831,6983653976480365703,7190718169255452642], aRuleName_ = "generators-first"} +LF: {"AnsweredRule":{"aRuleName_":"generators-first","qAscendants_":[-8909122354700020440,-7460733051808423716,-5113575940370069634,-3275789614875181527,-1485928817419295239,-1453326525258547920,-1190111094765899527,-425934852058965166,-227269000323710205,1017324948146570036,2402920626236815200,4379418785875775437,5239709721973149055,5447511985754467121,6138327529543829831,6983653976480365703,7190718169255452642],"qHole_":5094133043100232579}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!or(flatten(1, [[3 = conjure_aux3 | letting q14 be (3, 4)], [4 = conjure_aux3 |]; int(1..2)])) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: [4 = conjure_aux3 |] + Context #1: [[3 = conjure_aux3 | letting q14 be (3, 4)], [4 = conjure_aux3 |]; int(1..2)] + Context #2: flatten(1, [[3 = conjure_aux3 | letting q14 be (3, 4)], [4 = conjure_aux3 |]; int(1..2)]) + Context #3: or(flatten(1, [[3 = conjure_aux3 | letting q14 be (3, 4)], [4 = conjure_aux3 |]; int(1..2)])) + Context #4: !or(flatten(1, [[3 = conjure_aux3 | letting q14 be (3, 4)], [4 = conjure_aux3 |]; int(1..2)])) + Context #5: !or(flatten(1, [[3 = conjure_aux3 | letting q14 be (3, 4)], [4 = conjure_aux3 |]; int(1..2)])) <-> conjure_aux3 = q8_1 + Context #6: [and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])), + !or(flatten(1, [[3 = conjure_aux3 | letting q14 be (3, 4)], [4 = conjure_aux3 |]; int(1..2)])) <-> conjure_aux3 = q8_1; + int(1..2)] + Context #7: and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!or(flatten(1, [[3 = conjure_aux3 | letting q14 be (3, 4)], [4 = conjure_aux3 |]; int(1..2)])) <-> conjure_aux3 = q8_1) + Context #8: { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!or(flatten(1, [[3 = conjure_aux3 | letting q14 be (3, 4)], [4 = conjure_aux3 |]; int(1..2)])) <-> conjure_aux3 = q8_1) + } + Context #9: conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!or(flatten(1, [[3 = conjure_aux3 | letting q14 be (3, 4)], [4 = conjure_aux3 |]; int(1..2)])) <-> conjure_aux3 = q8_1) + } + Context #10: { conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!or(flatten(1, [[3 = conjure_aux3 | letting q14 be (3, 4)], [4 = conjure_aux3 |]; int(1..2)])) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + Context #11: { conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!or(flatten(1, [[3 = conjure_aux3 | letting q14 be (3, 4)], [4 = conjure_aux3 |]; int(1..2)])) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + Context #12: [{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!or(flatten(1, [[3 = conjure_aux3 | letting q14 be (3, 4)], [4 = conjure_aux3 |]; int(1..2)])) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]] + Context #13: and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!or(flatten(1, [[3 = conjure_aux3 | letting q14 be (3, 4)], [4 = conjure_aux3 |]; int(1..2)])) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + Context #14: [|x| = |conjure_aux1|, + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!or(flatten(1, [[3 = conjure_aux3 | letting q14 be (3, 4)], [4 = conjure_aux3 |]; int(1..2)])) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]); + int(1..2)] + Context #15: |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!or(flatten(1, [[3 = conjure_aux3 | letting q14 be (3, 4)], [4 = conjure_aux3 |]; int(1..2)])) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + Context #16: { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!or(flatten(1, [[3 = conjure_aux3 | letting q14 be (3, 4)], [4 = conjure_aux3 |]; int(1..2)])) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + Context #17: y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!or(flatten(1, [[3 = conjure_aux3 | letting q14 be (3, 4)], [4 = conjure_aux3 |]; int(1..2)])) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } +Picking the only option: Answer 1: generators-first: Empty generators. + [4 = conjure_aux3; int(1)] +storedChoice: +[4 = conjure_aux3 |] 6112956542716486877 +AnsweredRule {qHole_ = 6112956542716486877, qAscendants_ = fromList [-9207305118438100391,-6369735332026353512,-5991924291783106431,-5776209435213632803,-3830978856990678993,-3641847297966420112,-338462998493300906,2767710529868660813,4005580531872772405,4397758740249101114,4804584669642102451,5890086814982925863,6459294084780550343,6686373777934096773,7031238571308724387,7962655793307038867,8888369891598567800], aRuleName_ = "generators-first"} +LF: {"AnsweredRule":{"aRuleName_":"generators-first","qAscendants_":[-9207305118438100391,-6369735332026353512,-5991924291783106431,-5776209435213632803,-3830978856990678993,-3641847297966420112,-338462998493300906,2767710529868660813,4005580531872772405,4397758740249101114,4804584669642102451,5890086814982925863,6459294084780550343,6686373777934096773,7031238571308724387,7962655793307038867,8888369891598567800],"qHole_":6112956542716486877}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!or(flatten(1, [[3 = conjure_aux3 | letting q14 be (3, 4)], [4 = conjure_aux3; int(1)]; int(1..2)])) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: [3 = conjure_aux3 | letting q14 be (3, 4)] + Context #1: [[3 = conjure_aux3 | letting q14 be (3, 4)], [4 = conjure_aux3; int(1)]; int(1..2)] + Context #2: flatten(1, [[3 = conjure_aux3 | letting q14 be (3, 4)], [4 = conjure_aux3; int(1)]; int(1..2)]) + Context #3: or(flatten(1, [[3 = conjure_aux3 | letting q14 be (3, 4)], [4 = conjure_aux3; int(1)]; int(1..2)])) + Context #4: !or(flatten(1, [[3 = conjure_aux3 | letting q14 be (3, 4)], [4 = conjure_aux3; int(1)]; int(1..2)])) + Context #5: !or(flatten(1, [[3 = conjure_aux3 | letting q14 be (3, 4)], [4 = conjure_aux3; int(1)]; int(1..2)])) <-> + conjure_aux3 = q8_1 + Context #6: [and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])), + !or(flatten(1, [[3 = conjure_aux3 | letting q14 be (3, 4)], [4 = conjure_aux3; int(1)]; int(1..2)])) <-> conjure_aux3 = q8_1; + int(1..2)] + Context #7: and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!or(flatten(1, [[3 = conjure_aux3 | letting q14 be (3, 4)], [4 = conjure_aux3; int(1)]; int(1..2)])) <-> conjure_aux3 = q8_1) + Context #8: { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!or(flatten(1, [[3 = conjure_aux3 | letting q14 be (3, 4)], [4 = conjure_aux3; int(1)]; int(1..2)])) <-> conjure_aux3 = q8_1) + } + Context #9: conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!or(flatten(1, [[3 = conjure_aux3 | letting q14 be (3, 4)], [4 = conjure_aux3; int(1)]; int(1..2)])) <-> conjure_aux3 = q8_1) + } + Context #10: { conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!or(flatten(1, [[3 = conjure_aux3 | letting q14 be (3, 4)], [4 = conjure_aux3; int(1)]; int(1..2)])) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + Context #11: { conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!or(flatten(1, [[3 = conjure_aux3 | letting q14 be (3, 4)], [4 = conjure_aux3; int(1)]; int(1..2)])) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + Context #12: [{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!or(flatten(1, [[3 = conjure_aux3 | letting q14 be (3, 4)], [4 = conjure_aux3; int(1)]; int(1..2)])) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]] + Context #13: and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!or(flatten(1, [[3 = conjure_aux3 | letting q14 be (3, 4)], [4 = conjure_aux3; int(1)]; int(1..2)])) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + Context #14: [|x| = |conjure_aux1|, + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!or(flatten(1, [[3 = conjure_aux3 | letting q14 be (3, 4)], [4 = conjure_aux3; int(1)]; int(1..2)])) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]); + int(1..2)] + Context #15: |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!or(flatten(1, [[3 = conjure_aux3 | letting q14 be (3, 4)], [4 = conjure_aux3; int(1)]; int(1..2)])) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + Context #16: { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!or(flatten(1, [[3 = conjure_aux3 | letting q14 be (3, 4)], [4 = conjure_aux3; int(1)]; int(1..2)])) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + Context #17: y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!or(flatten(1, [[3 = conjure_aux3 | letting q14 be (3, 4)], [4 = conjure_aux3; int(1)]; int(1..2)])) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } +Picking the only option: Answer 1: generators-first: Inlining comprehension lettings. + [3 = conjure_aux3 |] +storedChoice: +[3 = conjure_aux3 | letting q14 be (3, 4)] 4832497823804752928 +AnsweredRule {qHole_ = 4832497823804752928, qAscendants_ = fromList [-6677145406315480965,-5384732204964843677,-3071059650417301550,-2603160466482895011,-2221619722341004417,-1557091775694725768,-1403621344696630627,711266062685662619,1333581340284470498,1611305677733360901,2753561903646462793,3866947117330481491,5332477917871449756,5559142600358984796,6001232326845461178,7602738452352881434,8088691831228319750], aRuleName_ = "generators-first"} +LF: {"AnsweredRule":{"aRuleName_":"generators-first","qAscendants_":[-6677145406315480965,-5384732204964843677,-3071059650417301550,-2603160466482895011,-2221619722341004417,-1557091775694725768,-1403621344696630627,711266062685662619,1333581340284470498,1611305677733360901,2753561903646462793,3866947117330481491,5332477917871449756,5559142600358984796,6001232326845461178,7602738452352881434,8088691831228319750],"qHole_":4832497823804752928}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!or(flatten(1, [[3 = conjure_aux3 |], [4 = conjure_aux3; int(1)]; int(1..2)])) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: [3 = conjure_aux3 |] + Context #1: [[3 = conjure_aux3 |], [4 = conjure_aux3; int(1)]; int(1..2)] + Context #2: flatten(1, [[3 = conjure_aux3 |], [4 = conjure_aux3; int(1)]; int(1..2)]) + Context #3: or(flatten(1, [[3 = conjure_aux3 |], [4 = conjure_aux3; int(1)]; int(1..2)])) + Context #4: !or(flatten(1, [[3 = conjure_aux3 |], [4 = conjure_aux3; int(1)]; int(1..2)])) + Context #5: !or(flatten(1, [[3 = conjure_aux3 |], [4 = conjure_aux3; int(1)]; int(1..2)])) <-> conjure_aux3 = q8_1 + Context #6: [and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])), + !or(flatten(1, [[3 = conjure_aux3 |], [4 = conjure_aux3; int(1)]; int(1..2)])) <-> conjure_aux3 = q8_1; + int(1..2)] + Context #7: and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!or(flatten(1, [[3 = conjure_aux3 |], [4 = conjure_aux3; int(1)]; int(1..2)])) <-> conjure_aux3 = q8_1) + Context #8: { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!or(flatten(1, [[3 = conjure_aux3 |], [4 = conjure_aux3; int(1)]; int(1..2)])) <-> conjure_aux3 = q8_1) + } + Context #9: conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!or(flatten(1, [[3 = conjure_aux3 |], [4 = conjure_aux3; int(1)]; int(1..2)])) <-> conjure_aux3 = q8_1) + } + Context #10: { conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!or(flatten(1, [[3 = conjure_aux3 |], [4 = conjure_aux3; int(1)]; int(1..2)])) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + Context #11: { conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!or(flatten(1, [[3 = conjure_aux3 |], [4 = conjure_aux3; int(1)]; int(1..2)])) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + Context #12: [{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!or(flatten(1, [[3 = conjure_aux3 |], [4 = conjure_aux3; int(1)]; int(1..2)])) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]] + Context #13: and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!or(flatten(1, [[3 = conjure_aux3 |], [4 = conjure_aux3; int(1)]; int(1..2)])) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + Context #14: [|x| = |conjure_aux1|, + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!or(flatten(1, [[3 = conjure_aux3 |], [4 = conjure_aux3; int(1)]; int(1..2)])) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]); + int(1..2)] + Context #15: |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!or(flatten(1, [[3 = conjure_aux3 |], [4 = conjure_aux3; int(1)]; int(1..2)])) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + Context #16: { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!or(flatten(1, [[3 = conjure_aux3 |], [4 = conjure_aux3; int(1)]; int(1..2)])) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + Context #17: y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!or(flatten(1, [[3 = conjure_aux3 |], [4 = conjure_aux3; int(1)]; int(1..2)])) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } +Picking the only option: Answer 1: generators-first: Empty generators. + [3 = conjure_aux3; int(1)] +storedChoice: +[3 = conjure_aux3 |] -185461686146028532 +AnsweredRule {qHole_ = -185461686146028532, qAscendants_ = fromList [-8289289739114023416,-8221845150149788696,-8019537499083765163,-7053954318911112143,-6092536859292112896,-4070943207855695476,-4028159753280221929,-3732495125634815821,-3238009362727088795,-282387919327309193,1775857482582255809,1882693949567706262,2362052944268224547,4832344585872237142,7445111209011732230,7705507659096261482,8654062028269091919], aRuleName_ = "generators-first"} +LF: {"AnsweredRule":{"aRuleName_":"generators-first","qAscendants_":[-8289289739114023416,-8221845150149788696,-8019537499083765163,-7053954318911112143,-6092536859292112896,-4070943207855695476,-4028159753280221929,-3732495125634815821,-3238009362727088795,-282387919327309193,1775857482582255809,1882693949567706262,2362052944268224547,4832344585872237142,7445111209011732230,7705507659096261482,8654062028269091919],"qHole_":-185461686146028532}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!or(flatten(1, [[3 = conjure_aux3; int(1)], [4 = conjure_aux3; int(1)]; int(1..2)])) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: or(flatten(1, [[3 = conjure_aux3; int(1)], [4 = conjure_aux3; int(1)]; int(1..2)])) + Context #1: !or(flatten(1, [[3 = conjure_aux3; int(1)], [4 = conjure_aux3; int(1)]; int(1..2)])) + Context #2: !or(flatten(1, [[3 = conjure_aux3; int(1)], [4 = conjure_aux3; int(1)]; int(1..2)])) <-> conjure_aux3 = q8_1 + Context #3: [and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])), + !or(flatten(1, [[3 = conjure_aux3; int(1)], [4 = conjure_aux3; int(1)]; int(1..2)])) <-> conjure_aux3 = q8_1; + int(1..2)] + Context #4: and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!or(flatten(1, [[3 = conjure_aux3; int(1)], [4 = conjure_aux3; int(1)]; int(1..2)])) <-> conjure_aux3 = q8_1) + Context #5: { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!or(flatten(1, [[3 = conjure_aux3; int(1)], [4 = conjure_aux3; int(1)]; int(1..2)])) <-> conjure_aux3 = q8_1) + } + Context #6: conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!or(flatten(1, [[3 = conjure_aux3; int(1)], [4 = conjure_aux3; int(1)]; int(1..2)])) <-> conjure_aux3 = q8_1) + } + Context #7: { conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!or(flatten(1, [[3 = conjure_aux3; int(1)], [4 = conjure_aux3; int(1)]; int(1..2)])) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + Context #8: { conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!or(flatten(1, [[3 = conjure_aux3; int(1)], [4 = conjure_aux3; int(1)]; int(1..2)])) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + Context #9: [{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!or(flatten(1, [[3 = conjure_aux3; int(1)], [4 = conjure_aux3; int(1)]; int(1..2)])) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]] + Context #10: and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!or(flatten(1, [[3 = conjure_aux3; int(1)], [4 = conjure_aux3; int(1)]; int(1..2)])) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + Context #11: [|x| = |conjure_aux1|, + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!or(flatten(1, [[3 = conjure_aux3; int(1)], [4 = conjure_aux3; int(1)]; int(1..2)])) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]); + int(1..2)] + Context #12: |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!or(flatten(1, [[3 = conjure_aux3; int(1)], [4 = conjure_aux3; int(1)]; int(1..2)])) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + Context #13: { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!or(flatten(1, [[3 = conjure_aux3; int(1)], [4 = conjure_aux3; int(1)]; int(1..2)])) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + Context #14: y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!or(flatten(1, [[3 = conjure_aux3; int(1)], [4 = conjure_aux3; int(1)]; int(1..2)])) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } +Picking the only option: Answer 1: quantifier-shift3: Shifting quantifier inwards + or([3 = conjure_aux3; int(1)]) \/ or([4 = conjure_aux3; int(1)]) +storedChoice: +or(flatten(1, [[3 = conjure_aux3; int(1)], [4 = conjure_aux3; int(1)]; int(1..2)])) 6206761561595236625 +AnsweredRule {qHole_ = 6206761561595236625, qAscendants_ = fromList [-9091665958233421775,-8534800408556100581,-8389275971974927944,-7928483109077342673,-7581357772290646644,-7037234840397785533,-6263532840176792370,-5427006571018076668,-4431680199820092864,-4076541738995400933,-1064366526874994538,5387747797148225385,6292098423078440671,8420337927154511626], aRuleName_ = "quantifier-shift3"} +LF: {"AnsweredRule":{"aRuleName_":"quantifier-shift3","qAscendants_":[-9091665958233421775,-8534800408556100581,-8389275971974927944,-7928483109077342673,-7581357772290646644,-7037234840397785533,-6263532840176792370,-5427006571018076668,-4431680199820092864,-4076541738995400933,-1064366526874994538,5387747797148225385,6292098423078440671,8420337927154511626],"qHole_":6206761561595236625}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!(or([3 = conjure_aux3; int(1)]) \/ or([4 = conjure_aux3; int(1)])) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: or([3 = conjure_aux3; int(1)]) + Context #1: [or([3 = conjure_aux3; int(1)]), or([4 = conjure_aux3; int(1)]); int(1..2)] + Context #2: or([3 = conjure_aux3; int(1)]) \/ or([4 = conjure_aux3; int(1)]) + Context #3: !(or([3 = conjure_aux3; int(1)]) \/ or([4 = conjure_aux3; int(1)])) + Context #4: !(or([3 = conjure_aux3; int(1)]) \/ or([4 = conjure_aux3; int(1)])) <-> conjure_aux3 = q8_1 + Context #5: [and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])), + !(or([3 = conjure_aux3; int(1)]) \/ or([4 = conjure_aux3; int(1)])) <-> conjure_aux3 = q8_1; + int(1..2)] + Context #6: and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!(or([3 = conjure_aux3; int(1)]) \/ or([4 = conjure_aux3; int(1)])) <-> conjure_aux3 = q8_1) + Context #7: { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!(or([3 = conjure_aux3; int(1)]) \/ or([4 = conjure_aux3; int(1)])) <-> conjure_aux3 = q8_1) + } + Context #8: conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!(or([3 = conjure_aux3; int(1)]) \/ or([4 = conjure_aux3; int(1)])) <-> conjure_aux3 = q8_1) + } + Context #9: { conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!(or([3 = conjure_aux3; int(1)]) \/ or([4 = conjure_aux3; int(1)])) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + Context #10: { conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!(or([3 = conjure_aux3; int(1)]) \/ or([4 = conjure_aux3; int(1)])) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + Context #11: [{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!(or([3 = conjure_aux3; int(1)]) \/ or([4 = conjure_aux3; int(1)])) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]] + Context #12: and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!(or([3 = conjure_aux3; int(1)]) \/ or([4 = conjure_aux3; int(1)])) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + Context #13: [|x| = |conjure_aux1|, + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!(or([3 = conjure_aux3; int(1)]) \/ or([4 = conjure_aux3; int(1)])) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]); + int(1..2)] + Context #14: |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!(or([3 = conjure_aux3; int(1)]) \/ or([4 = conjure_aux3; int(1)])) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + Context #15: { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!(or([3 = conjure_aux3; int(1)]) \/ or([4 = conjure_aux3; int(1)])) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + Context #16: y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!(or([3 = conjure_aux3; int(1)]) \/ or([4 = conjure_aux3; int(1)])) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } +Picking the only option: Answer 1: matrix-comprehension-singleton: Removing quantifier of a single item + 3 = conjure_aux3 +storedChoice: +or([3 = conjure_aux3; int(1)]) -3434962391173132894 +AnsweredRule {qHole_ = -3434962391173132894, qAscendants_ = fromList [-7235853985473547952,-6866498255018164123,-4960622746477117042,-4585543795134183636,-4105761649660625353,-3524766623875920799,-2347278582408429201,-1565913897093032045,-636316196669785718,259925545372009536,2634241883209911323,4718505660743647939,6517008955702082360,6653106233829268540,7728404530962223160,8536818627412251687], aRuleName_ = "matrix-comprehension-singleton"} +LF: {"AnsweredRule":{"aRuleName_":"matrix-comprehension-singleton","qAscendants_":[-7235853985473547952,-6866498255018164123,-4960622746477117042,-4585543795134183636,-4105761649660625353,-3524766623875920799,-2347278582408429201,-1565913897093032045,-636316196669785718,259925545372009536,2634241883209911323,4718505660743647939,6517008955702082360,6653106233829268540,7728404530962223160,8536818627412251687],"qHole_":-3434962391173132894}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!(3 = conjure_aux3 \/ or([4 = conjure_aux3; int(1)])) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: or([4 = conjure_aux3; int(1)]) + Context #1: [3 = conjure_aux3, or([4 = conjure_aux3; int(1)]); int(1..2)] + Context #2: 3 = conjure_aux3 \/ or([4 = conjure_aux3; int(1)]) + Context #3: !(3 = conjure_aux3 \/ or([4 = conjure_aux3; int(1)])) + Context #4: !(3 = conjure_aux3 \/ or([4 = conjure_aux3; int(1)])) <-> conjure_aux3 = q8_1 + Context #5: [and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])), + !(3 = conjure_aux3 \/ or([4 = conjure_aux3; int(1)])) <-> conjure_aux3 = q8_1; + int(1..2)] + Context #6: and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!(3 = conjure_aux3 \/ or([4 = conjure_aux3; int(1)])) <-> conjure_aux3 = q8_1) + Context #7: { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!(3 = conjure_aux3 \/ or([4 = conjure_aux3; int(1)])) <-> conjure_aux3 = q8_1) + } + Context #8: conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!(3 = conjure_aux3 \/ or([4 = conjure_aux3; int(1)])) <-> conjure_aux3 = q8_1) + } + Context #9: { conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!(3 = conjure_aux3 \/ or([4 = conjure_aux3; int(1)])) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + Context #10: { conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!(3 = conjure_aux3 \/ or([4 = conjure_aux3; int(1)])) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + Context #11: [{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!(3 = conjure_aux3 \/ or([4 = conjure_aux3; int(1)])) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]] + Context #12: and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!(3 = conjure_aux3 \/ or([4 = conjure_aux3; int(1)])) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + Context #13: [|x| = |conjure_aux1|, + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!(3 = conjure_aux3 \/ or([4 = conjure_aux3; int(1)])) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]); + int(1..2)] + Context #14: |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!(3 = conjure_aux3 \/ or([4 = conjure_aux3; int(1)])) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + Context #15: { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!(3 = conjure_aux3 \/ or([4 = conjure_aux3; int(1)])) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + Context #16: y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!(3 = conjure_aux3 \/ or([4 = conjure_aux3; int(1)])) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } +Picking the only option: Answer 1: matrix-comprehension-singleton: Removing quantifier of a single item + 4 = conjure_aux3 +storedChoice: +or([4 = conjure_aux3; int(1)]) 8578967638246734293 +AnsweredRule {qHole_ = 8578967638246734293, qAscendants_ = fromList [-7767892036023956761,-6284781492183215029,-1727905482554729427,-1356654288157906426,2281150997448020466,2372014189263015226,2446665452257606178,2838934993441470606,4742034938664987168,4756703484454204779,6116173103300050025,6542907600674666418,7911556895678534380,8081136239962017343,8569698893899834293,8949973037119072966], aRuleName_ = "matrix-comprehension-singleton"} +LF: {"AnsweredRule":{"aRuleName_":"matrix-comprehension-singleton","qAscendants_":[-7767892036023956761,-6284781492183215029,-1727905482554729427,-1356654288157906426,2281150997448020466,2372014189263015226,2446665452257606178,2838934993441470606,4742034938664987168,4756703484454204779,6116173103300050025,6542907600674666418,7911556895678534380,8081136239962017343,8569698893899834293,8949973037119072966],"qHole_":8578967638246734293}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: and(flatten(1, + [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) + Context #1: [and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])), + !(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1; + int(1..2)] + Context #2: and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + Context #3: { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + Context #4: conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + Context #5: { conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + Context #6: { conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + Context #7: [{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]] + Context #8: and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + Context #9: [|x| = |conjure_aux1|, + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]); + int(1..2)] + Context #10: |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + Context #11: { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + Context #12: y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } +Picking the only option: Answer 1: quantifier-shift3: Shifting quantifier inwards + and([3 = q8_1 <-> conjure_aux3 = 4; int(1)]) /\ and([4 = q8_1 <-> conjure_aux3 = 3; int(1)]) +storedChoice: +and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) -2199657802844878530 +AnsweredRule {qHole_ = -2199657802844878530, qAscendants_ = fromList [-8444650881280502798,-8271565969096831831,-6564446395948378541,-3553121516791984732,-3091505528568185300,-28537057046234944,2611036720111951620,3048392108732098635,4941408088135413888,6187348870363663871,6391218772456415880,9128754183040712545], aRuleName_ = "quantifier-shift3"} +LF: {"AnsweredRule":{"aRuleName_":"quantifier-shift3","qAscendants_":[-8444650881280502798,-8271565969096831831,-6564446395948378541,-3553121516791984732,-3091505528568185300,-28537057046234944,2611036720111951620,3048392108732098635,4941408088135413888,6187348870363663871,6391218772456415880,9128754183040712545],"qHole_":-2199657802844878530}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and([3 = q8_1 <-> conjure_aux3 = 4; int(1)]) /\ and([4 = q8_1 <-> conjure_aux3 = 3; int(1)]) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: and([3 = q8_1 <-> conjure_aux3 = 4; int(1)]) + Context #1: [and([3 = q8_1 <-> conjure_aux3 = 4; int(1)]), and([4 = q8_1 <-> conjure_aux3 = 3; int(1)]); int(1..2)] + Context #2: and([3 = q8_1 <-> conjure_aux3 = 4; int(1)]) /\ and([4 = q8_1 <-> conjure_aux3 = 3; int(1)]) + Context #3: [and([3 = q8_1 <-> conjure_aux3 = 4; int(1)]) /\ and([4 = q8_1 <-> conjure_aux3 = 3; int(1)]), + !(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1; + int(1..2)] + Context #4: and([3 = q8_1 <-> conjure_aux3 = 4; int(1)]) /\ and([4 = q8_1 <-> conjure_aux3 = 3; int(1)]) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + Context #5: { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and([3 = q8_1 <-> conjure_aux3 = 4; int(1)]) /\ and([4 = q8_1 <-> conjure_aux3 = 3; int(1)]) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + Context #6: conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and([3 = q8_1 <-> conjure_aux3 = 4; int(1)]) /\ and([4 = q8_1 <-> conjure_aux3 = 3; int(1)]) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + Context #7: { conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and([3 = q8_1 <-> conjure_aux3 = 4; int(1)]) /\ and([4 = q8_1 <-> conjure_aux3 = 3; int(1)]) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + Context #8: { conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and([3 = q8_1 <-> conjure_aux3 = 4; int(1)]) /\ and([4 = q8_1 <-> conjure_aux3 = 3; int(1)]) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + Context #9: [{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and([3 = q8_1 <-> conjure_aux3 = 4; int(1)]) /\ and([4 = q8_1 <-> conjure_aux3 = 3; int(1)]) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]] + Context #10: and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and([3 = q8_1 <-> conjure_aux3 = 4; int(1)]) /\ and([4 = q8_1 <-> conjure_aux3 = 3; int(1)]) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + Context #11: [|x| = |conjure_aux1|, + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and([3 = q8_1 <-> conjure_aux3 = 4; int(1)]) /\ and([4 = q8_1 <-> conjure_aux3 = 3; int(1)]) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]); + int(1..2)] + Context #12: |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and([3 = q8_1 <-> conjure_aux3 = 4; int(1)]) /\ and([4 = q8_1 <-> conjure_aux3 = 3; int(1)]) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + Context #13: { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and([3 = q8_1 <-> conjure_aux3 = 4; int(1)]) /\ and([4 = q8_1 <-> conjure_aux3 = 3; int(1)]) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + Context #14: y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and([3 = q8_1 <-> conjure_aux3 = 4; int(1)]) /\ and([4 = q8_1 <-> conjure_aux3 = 3; int(1)]) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } +Picking the only option: Answer 1: matrix-comprehension-singleton: Removing quantifier of a single item + 3 = q8_1 <-> conjure_aux3 = 4 +storedChoice: +and([3 = q8_1 <-> conjure_aux3 = 4; int(1)]) -82084885825755383 +AnsweredRule {qHole_ = -82084885825755383, qAscendants_ = fromList [-7910416632419113217,-6789993106391976797,-6474394686920849630,-4532119084740741428,-4148488185654761721,-3872345874892611968,-3008944008775182264,-2299093800387471961,-1551233151285274759,-649051754905350518,1456233810038530873,2986022555450137983,3688733153117744851,8953876927154124061], aRuleName_ = "matrix-comprehension-singleton"} +LF: {"AnsweredRule":{"aRuleName_":"matrix-comprehension-singleton","qAscendants_":[-7910416632419113217,-6789993106391976797,-6474394686920849630,-4532119084740741428,-4148488185654761721,-3872345874892611968,-3008944008775182264,-2299093800387471961,-1551233151285274759,-649051754905350518,1456233810038530873,2986022555450137983,3688733153117744851,8953876927154124061],"qHole_":-82084885825755383}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ and([4 = q8_1 <-> conjure_aux3 = 3; int(1)]) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: and([4 = q8_1 <-> conjure_aux3 = 3; int(1)]) + Context #1: [3 = q8_1 <-> conjure_aux3 = 4, and([4 = q8_1 <-> conjure_aux3 = 3; int(1)]); int(1..2)] + Context #2: (3 = q8_1 <-> conjure_aux3 = 4) /\ and([4 = q8_1 <-> conjure_aux3 = 3; int(1)]) + Context #3: [(3 = q8_1 <-> conjure_aux3 = 4) /\ and([4 = q8_1 <-> conjure_aux3 = 3; int(1)]), + !(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1; + int(1..2)] + Context #4: (3 = q8_1 <-> conjure_aux3 = 4) /\ and([4 = q8_1 <-> conjure_aux3 = 3; int(1)]) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + Context #5: { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ and([4 = q8_1 <-> conjure_aux3 = 3; int(1)]) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + Context #6: conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ and([4 = q8_1 <-> conjure_aux3 = 3; int(1)]) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + Context #7: { conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ and([4 = q8_1 <-> conjure_aux3 = 3; int(1)]) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + Context #8: { conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ and([4 = q8_1 <-> conjure_aux3 = 3; int(1)]) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + Context #9: [{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ and([4 = q8_1 <-> conjure_aux3 = 3; int(1)]) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]] + Context #10: and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ and([4 = q8_1 <-> conjure_aux3 = 3; int(1)]) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + Context #11: [|x| = |conjure_aux1|, + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ and([4 = q8_1 <-> conjure_aux3 = 3; int(1)]) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]); + int(1..2)] + Context #12: |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ and([4 = q8_1 <-> conjure_aux3 = 3; int(1)]) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + Context #13: { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ and([4 = q8_1 <-> conjure_aux3 = 3; int(1)]) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + Context #14: y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ and([4 = q8_1 <-> conjure_aux3 = 3; int(1)]) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } +Picking the only option: Answer 1: matrix-comprehension-singleton: Removing quantifier of a single item + 4 = q8_1 <-> conjure_aux3 = 3 +storedChoice: +and([4 = q8_1 <-> conjure_aux3 = 3; int(1)]) 4451202942487357861 +AnsweredRule {qHole_ = 4451202942487357861, qAscendants_ = fromList [-7368630815449645005,-4752206960723048197,-2804301512506126649,-1530922004872999299,-236411210949206668,204928372325319241,2335949798361580872,2698852189043337488,3049593885211881070,3728149952134739241,4353487588625663382,5225198894548896615,5925873450508265460,6881890190583065447], aRuleName_ = "matrix-comprehension-singleton"} +LF: {"AnsweredRule":{"aRuleName_":"matrix-comprehension-singleton","qAscendants_":[-7368630815449645005,-4752206960723048197,-2804301512506126649,-1530922004872999299,-236411210949206668,204928372325319241,2335949798361580872,2698852189043337488,3049593885211881070,3728149952134739241,4353487588625663382,5225198894548896615,5925873450508265460,6881890190583065447],"qHole_":4451202942487357861}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + Context #1: conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + Context #2: { conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + Context #3: { conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + Context #4: [{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]] + Context #5: and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + Context #6: [|x| = |conjure_aux1|, + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]); + int(1..2)] + Context #7: |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + Context #8: { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + Context #9: y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } +Picking the only option: Answer 1: choose-repr-for-locals: Choosing representation for local variable conjure_aux3 + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } +storedChoice: +{ conjure_aux3 +@ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) +} -3398171252428132748 +AnsweredRule {qHole_ = -3398171252428132748, qAscendants_ = fromList [-4801520196462386255,-3106386946478834998,-1836288510476607810,-1423400445383478062,1875892051782461076,3043802995379454474,7974629594191079167,8285823029631020243,8636179585519730549], aRuleName_ = "choose-repr-for-locals"} +LF: {"AnsweredRule":{"aRuleName_":"choose-repr-for-locals","qAscendants_":[-4801520196462386255,-3106386946478834998,-1836288510476607810,-1423400445383478062,1875892051782461076,3043802995379454474,7974629594191079167,8285823029631020243,8636179585519730549],"qHole_":-3398171252428132748}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + Context #1: { conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + Context #2: { conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + Context #3: [{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]] + Context #4: and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + Context #5: [|x| = |conjure_aux1|, + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]); + int(1..2)] + Context #6: |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + Context #7: { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + Context #8: y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } +Picking the only option: Answer 1: bubble-up-LiftVars: Bubbling up auxiliary variables. + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } +storedChoice: +conjure_aux2_1 = +{ conjure_aux3 +@ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) +} 7974629594191079167 +AnsweredRule {qHole_ = 7974629594191079167, qAscendants_ = fromList [-4801520196462386255,-3106386946478834998,-1836288510476607810,-1423400445383478062,1875892051782461076,3043802995379454474,8285823029631020243,8636179585519730549], aRuleName_ = "bubble-up-LiftVars"} +LF: {"AnsweredRule":{"aRuleName_":"bubble-up-LiftVars","qAscendants_":[-4801520196462386255,-3106386946478834998,-1836288510476607810,-1423400445383478062,1875892051782461076,3043802995379454474,8285823029631020243,8636179585519730549],"qHole_":7974629594191079167}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: conjure_aux2[2] + Context #1: conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + Context #2: { conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + Context #3: { conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + Context #4: [{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]] + Context #5: and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + Context #6: [|x| = |conjure_aux1|, + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]); + int(1..2)] + Context #7: |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + Context #8: { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + Context #9: y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } +Picking the only option: Answer 1: tuple-index: Tuple indexing on: conjure_aux2[2] + conjure_aux2_2 +storedChoice: +conjure_aux2[2] 2042003740924818024 +AnsweredRule {qHole_ = 2042003740924818024, qAscendants_ = fromList [-7047224780753215240,-3882919266147774615,-2299063140006189613,681365846263239803,6336625794965795994,6485140089845002516,7009155380893464902,7082442116022567493,8239398540167710302], aRuleName_ = "tuple-index"} +LF: {"AnsweredRule":{"aRuleName_":"tuple-index","qAscendants_":[-7047224780753215240,-3882919266147774615,-2299063140006189613,681365846263239803,6336625794965795994,6485140089845002516,7009155380893464902,7082442116022567493,8239398540167710302],"qHole_":2042003740924818024}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2_2 = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: (q8[1], q8[2])[2] + Context #1: image(permutation((3, 4)), (q8[1], q8[2])[2]) + Context #2: conjure_aux2_2 = image(permutation((3, 4)), (q8[1], q8[2])[2]) + Context #3: { conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2_2 = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + Context #4: { conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2_2 = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + Context #5: [{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2_2 = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]] + Context #6: and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2_2 = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + Context #7: [|x| = |conjure_aux1|, + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2_2 = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]); + int(1..2)] + Context #8: |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2_2 = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + Context #9: { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2_2 = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + Context #10: y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2_2 = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } +Picking the only option: Answer 1: tuple-index: Tuple indexing on: (q8[1], q8[2])[2] + q8[2] +storedChoice: +(q8[1], q8[2])[2] -5502204419920622825 +AnsweredRule {qHole_ = -5502204419920622825, qAscendants_ = fromList [-8588231375425367299,-8510895911811768656,-8426633625849827304,-8207238726412672978,-5936144574452389035,-2652871536273271001,-1630485539153521150,-1126023409437003920,6016260006111454055,8400731779430988570], aRuleName_ = "tuple-index"} +LF: {"AnsweredRule":{"aRuleName_":"tuple-index","qAscendants_":[-8588231375425367299,-8510895911811768656,-8426633625849827304,-8207238726412672978,-5936144574452389035,-2652871536273271001,-1630485539153521150,-1126023409437003920,6016260006111454055,8400731779430988570],"qHole_":-5502204419920622825}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2_2 = image(permutation((3, 4)), q8[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: q8[2] + Context #1: image(permutation((3, 4)), q8[2]) + Context #2: conjure_aux2_2 = image(permutation((3, 4)), q8[2]) + Context #3: { conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2_2 = image(permutation((3, 4)), q8[2]) + } + Context #4: { conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2_2 = image(permutation((3, 4)), q8[2]) + } + in conjure_aux1 + Context #5: [{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2_2 = image(permutation((3, 4)), q8[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]] + Context #6: and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2_2 = image(permutation((3, 4)), q8[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + Context #7: [|x| = |conjure_aux1|, + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2_2 = image(permutation((3, 4)), q8[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]); + int(1..2)] + Context #8: |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2_2 = image(permutation((3, 4)), q8[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + Context #9: { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2_2 = image(permutation((3, 4)), q8[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + Context #10: y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2_2 = image(permutation((3, 4)), q8[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } +Picking the only option: Answer 1: tuple-index: Tuple indexing on: q8[2] + q8_2 +storedChoice: +q8[2] 6051020602090044114 +AnsweredRule {qHole_ = 6051020602090044114, qAscendants_ = fromList [-8305205627063512429,-4351892905554585329,-3978385945799741575,-2899802451648727176,-2610387685810348227,-2009358436958284574,-1222951737421888386,-579623331933497389,4724832166697728323,7712861814088489767], aRuleName_ = "tuple-index"} +LF: {"AnsweredRule":{"aRuleName_":"tuple-index","qAscendants_":[-8305205627063512429,-4351892905554585329,-3978385945799741575,-2899802451648727176,-2610387685810348227,-2009358436958284574,-1222951737421888386,-579623331933497389,4724832166697728323,7712861814088489767],"qHole_":6051020602090044114}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2_2 = image(permutation((3, 4)), q8_2) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: image(permutation((3, 4)), q8_2) + Context #1: conjure_aux2_2 = image(permutation((3, 4)), q8_2) + Context #2: { conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2_2 = image(permutation((3, 4)), q8_2) + } + Context #3: { conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2_2 = image(permutation((3, 4)), q8_2) + } + in conjure_aux1 + Context #4: [{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2_2 = image(permutation((3, 4)), q8_2) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]] + Context #5: and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2_2 = image(permutation((3, 4)), q8_2) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + Context #6: [|x| = |conjure_aux1|, + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2_2 = image(permutation((3, 4)), q8_2) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]); + int(1..2)] + Context #7: |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2_2 = image(permutation((3, 4)), q8_2) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + Context #8: { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2_2 = image(permutation((3, 4)), q8_2) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + Context #9: y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2_2 = image(permutation((3, 4)), q8_2) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } +Picking the only option: Answer 1: permutation-image-literal{AsFunction}: Horizontal rule for permutation literal application to a single value (image), AsFunction representation + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and([q15 = q8_2 <-> conjure_aux4 = q16 | (q15, q16) <- [(3, 4), (4, 3); int(1..2)]]) /\ + (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) + } +storedChoice: +image(permutation((3, 4)), q8_2) -6566221682376100457 +AnsweredRule {qHole_ = -6566221682376100457, qAscendants_ = fromList [-7375621483096556180,-6476209656930651827,-6169031786475517693,-4051333596644929202,-1139526513744825718,614654197146956279,4282607200389588721,4519547606898719585,5902970686666028765], aRuleName_ = "permutation-image-literal{AsFunction}"} +LF: {"AnsweredRule":{"aRuleName_":"permutation-image-literal{AsFunction}","qAscendants_":[-7375621483096556180,-6476209656930651827,-6169031786475517693,-4051333596644929202,-1139526513744825718,614654197146956279,4282607200389588721,4519547606898719585,5902970686666028765],"qHole_":-6566221682376100457}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and([q15 = q8_2 <-> conjure_aux4 = q16 | (q15, q16) <- [(3, 4), (4, 3); int(1..2)]]) /\ + (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: [(3, 4), (4, 3); int(1..2)] + Context #1: [q15 = q8_2 <-> conjure_aux4 = q16 | (q15, q16) <- [(3, 4), (4, 3); int(1..2)]] + Context #2: and([q15 = q8_2 <-> conjure_aux4 = q16 | (q15, q16) <- [(3, 4), (4, 3); int(1..2)]]) + Context #3: [and([q15 = q8_2 <-> conjure_aux4 = q16 | (q15, q16) <- [(3, 4), (4, 3); int(1..2)]]), + !or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2; + int(1..2)] + Context #4: and([q15 = q8_2 <-> conjure_aux4 = q16 | (q15, q16) <- [(3, 4), (4, 3); int(1..2)]]) /\ + (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) + Context #5: { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and([q15 = q8_2 <-> conjure_aux4 = q16 | (q15, q16) <- [(3, 4), (4, 3); int(1..2)]]) /\ + (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) + } + Context #6: conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and([q15 = q8_2 <-> conjure_aux4 = q16 | (q15, q16) <- [(3, 4), (4, 3); int(1..2)]]) /\ + (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) + } + Context #7: { conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and([q15 = q8_2 <-> conjure_aux4 = q16 | (q15, q16) <- [(3, 4), (4, 3); int(1..2)]]) /\ + (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) + } + } + Context #8: { conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and([q15 = q8_2 <-> conjure_aux4 = q16 | (q15, q16) <- [(3, 4), (4, 3); int(1..2)]]) /\ + (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + Context #9: [{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and([q15 = q8_2 <-> conjure_aux4 = q16 | (q15, q16) <- [(3, 4), (4, 3); int(1..2)]]) /\ + (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]] + Context #10: and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and([q15 = q8_2 <-> conjure_aux4 = q16 | (q15, q16) <- [(3, 4), (4, 3); int(1..2)]]) /\ + (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + Context #11: [|x| = |conjure_aux1|, + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and([q15 = q8_2 <-> conjure_aux4 = q16 | (q15, q16) <- [(3, 4), (4, 3); int(1..2)]]) /\ + (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]); + int(1..2)] + Context #12: |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and([q15 = q8_2 <-> conjure_aux4 = q16 | (q15, q16) <- [(3, 4), (4, 3); int(1..2)]]) /\ + (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + Context #13: { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and([q15 = q8_2 <-> conjure_aux4 = q16 | (q15, q16) <- [(3, 4), (4, 3); int(1..2)]]) /\ + (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + Context #14: y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and([q15 = q8_2 <-> conjure_aux4 = q16 | (q15, q16) <- [(3, 4), (4, 3); int(1..2)]]) /\ + (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } +Picking the only option: Answer 1: full-evaluate: Full evaluator + [(3, 4), (4, 3); int(1..2)] +storedChoice: +[(3, 4), (4, 3); int(1..2)] 6597397470067790033 +AnsweredRule {qHole_ = 6597397470067790033, qAscendants_ = fromList [-8545307407731927617,-8177498968743831179,-5742947888929994190,-4442383996991551152,396642913451874760,889145374549031649,902104300452840084,1328695702543446488,2152276483370682723,4084473456285295179,4905601367831877360,6850337191508996871,7001603146156804613,8689879020318308638], aRuleName_ = "full-evaluate"} +LF: {"AnsweredRule":{"aRuleName_":"full-evaluate","qAscendants_":[-8545307407731927617,-8177498968743831179,-5742947888929994190,-4442383996991551152,396642913451874760,889145374549031649,902104300452840084,1328695702543446488,2152276483370682723,4084473456285295179,4905601367831877360,6850337191508996871,7001603146156804613,8689879020318308638],"qHole_":6597397470067790033}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and([q15 = q8_2 <-> conjure_aux4 = q16 | (q15, q16) <- [(3, 4), (4, 3); int(1..2)]]) /\ + (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: [q15 = q8_2 <-> conjure_aux4 = q16 | (q15, q16) <- [(3, 4), (4, 3); int(1..2)]] + Context #1: and([q15 = q8_2 <-> conjure_aux4 = q16 | (q15, q16) <- [(3, 4), (4, 3); int(1..2)]]) + Context #2: [and([q15 = q8_2 <-> conjure_aux4 = q16 | (q15, q16) <- [(3, 4), (4, 3); int(1..2)]]), + !or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2; + int(1..2)] + Context #3: and([q15 = q8_2 <-> conjure_aux4 = q16 | (q15, q16) <- [(3, 4), (4, 3); int(1..2)]]) /\ + (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) + Context #4: { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and([q15 = q8_2 <-> conjure_aux4 = q16 | (q15, q16) <- [(3, 4), (4, 3); int(1..2)]]) /\ + (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) + } + Context #5: conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and([q15 = q8_2 <-> conjure_aux4 = q16 | (q15, q16) <- [(3, 4), (4, 3); int(1..2)]]) /\ + (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) + } + Context #6: { conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and([q15 = q8_2 <-> conjure_aux4 = q16 | (q15, q16) <- [(3, 4), (4, 3); int(1..2)]]) /\ + (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) + } + } + Context #7: { conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and([q15 = q8_2 <-> conjure_aux4 = q16 | (q15, q16) <- [(3, 4), (4, 3); int(1..2)]]) /\ + (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + Context #8: [{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and([q15 = q8_2 <-> conjure_aux4 = q16 | (q15, q16) <- [(3, 4), (4, 3); int(1..2)]]) /\ + (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]] + Context #9: and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and([q15 = q8_2 <-> conjure_aux4 = q16 | (q15, q16) <- [(3, 4), (4, 3); int(1..2)]]) /\ + (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + Context #10: [|x| = |conjure_aux1|, + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and([q15 = q8_2 <-> conjure_aux4 = q16 | (q15, q16) <- [(3, 4), (4, 3); int(1..2)]]) /\ + (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]); + int(1..2)] + Context #11: |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and([q15 = q8_2 <-> conjure_aux4 = q16 | (q15, q16) <- [(3, 4), (4, 3); int(1..2)]]) /\ + (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + Context #12: { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and([q15 = q8_2 <-> conjure_aux4 = q16 | (q15, q16) <- [(3, 4), (4, 3); int(1..2)]]) /\ + (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + Context #13: y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and([q15 = q8_2 <-> conjure_aux4 = q16 | (q15, q16) <- [(3, 4), (4, 3); int(1..2)]]) /\ + (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } +Picking the only option: Answer 1: complex-pattern: complex pattern on tuple patterns + [q19[1] = q8_2 <-> conjure_aux4 = q19[2] | q19 <- [(3, 4), (4, 3); int(1..2)]] +storedChoice: +[q15 = q8_2 <-> conjure_aux4 = q16 | (q15, q16) <- [(3, 4), (4, 3); int(1..2)]] 1328695702543446488 +AnsweredRule {qHole_ = 1328695702543446488, qAscendants_ = fromList [-8545307407731927617,-8177498968743831179,-5742947888929994190,-4442383996991551152,396642913451874760,889145374549031649,902104300452840084,2152276483370682723,4084473456285295179,4905601367831877360,6850337191508996871,7001603146156804613,8689879020318308638], aRuleName_ = "complex-pattern"} +LF: {"AnsweredRule":{"aRuleName_":"complex-pattern","qAscendants_":[-8545307407731927617,-8177498968743831179,-5742947888929994190,-4442383996991551152,396642913451874760,889145374549031649,902104300452840084,2152276483370682723,4084473456285295179,4905601367831877360,6850337191508996871,7001603146156804613,8689879020318308638],"qHole_":1328695702543446488}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and([q19[1] = q8_2 <-> conjure_aux4 = q19[2] | q19 <- [(3, 4), (4, 3); int(1..2)]]) /\ + (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: [q19[1] = q8_2 <-> conjure_aux4 = q19[2] | q19 <- [(3, 4), (4, 3); int(1..2)]] + Context #1: and([q19[1] = q8_2 <-> conjure_aux4 = q19[2] | q19 <- [(3, 4), (4, 3); int(1..2)]]) + Context #2: [and([q19[1] = q8_2 <-> conjure_aux4 = q19[2] | q19 <- [(3, 4), (4, 3); int(1..2)]]), + !or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2; + int(1..2)] + Context #3: and([q19[1] = q8_2 <-> conjure_aux4 = q19[2] | q19 <- [(3, 4), (4, 3); int(1..2)]]) /\ + (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) + Context #4: { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and([q19[1] = q8_2 <-> conjure_aux4 = q19[2] | q19 <- [(3, 4), (4, 3); int(1..2)]]) /\ + (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) + } + Context #5: conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and([q19[1] = q8_2 <-> conjure_aux4 = q19[2] | q19 <- [(3, 4), (4, 3); int(1..2)]]) /\ + (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) + } + Context #6: { conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and([q19[1] = q8_2 <-> conjure_aux4 = q19[2] | q19 <- [(3, 4), (4, 3); int(1..2)]]) /\ + (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) + } + } + Context #7: { conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and([q19[1] = q8_2 <-> conjure_aux4 = q19[2] | q19 <- [(3, 4), (4, 3); int(1..2)]]) /\ + (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + Context #8: [{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and([q19[1] = q8_2 <-> conjure_aux4 = q19[2] | q19 <- [(3, 4), (4, 3); int(1..2)]]) /\ + (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]] + Context #9: and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and([q19[1] = q8_2 <-> conjure_aux4 = q19[2] | q19 <- [(3, 4), (4, 3); int(1..2)]]) /\ + (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + Context #10: [|x| = |conjure_aux1|, + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and([q19[1] = q8_2 <-> conjure_aux4 = q19[2] | q19 <- [(3, 4), (4, 3); int(1..2)]]) /\ + (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]); + int(1..2)] + Context #11: |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and([q19[1] = q8_2 <-> conjure_aux4 = q19[2] | q19 <- [(3, 4), (4, 3); int(1..2)]]) /\ + (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + Context #12: { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and([q19[1] = q8_2 <-> conjure_aux4 = q19[2] | q19 <- [(3, 4), (4, 3); int(1..2)]]) /\ + (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + Context #13: y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and([q19[1] = q8_2 <-> conjure_aux4 = q19[2] | q19 <- [(3, 4), (4, 3); int(1..2)]]) /\ + (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } +Picking the only option: Answer 1: matrix-comprehension-literal: Vertical rule for matrix-comprehension on matrix literal + flatten(1, + [[q19[1] = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (3, 4)], + [q19[1] = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (4, 3)]; + int(1..2)]) +storedChoice: +[q19[1] = q8_2 <-> conjure_aux4 = q19[2] | q19 <- [(3, 4), (4, 3); int(1..2)]] 2193708270475412974 +AnsweredRule {qHole_ = 2193708270475412974, qAscendants_ = fromList [-6135273235547916413,-3511824826747542530,-2817684250930868121,-1400917739936160745,-1319813811263441476,-481597523330641054,222999019742587203,2503474596382683671,4309903314606971320,7082348445248550107,7474061097534958542,8348619552204205832,9141480563237676781], aRuleName_ = "matrix-comprehension-literal"} +LF: {"AnsweredRule":{"aRuleName_":"matrix-comprehension-literal","qAscendants_":[-6135273235547916413,-3511824826747542530,-2817684250930868121,-1400917739936160745,-1319813811263441476,-481597523330641054,222999019742587203,2503474596382683671,4309903314606971320,7082348445248550107,7474061097534958542,8348619552204205832,9141480563237676781],"qHole_":2193708270475412974}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, + [[q19[1] = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (3, 4)], + [q19[1] = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (4, 3)]; + int(1..2)])) + /\ (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: q19[1] + Context #1: q19[1] = q8_2 + Context #2: q19[1] = q8_2 <-> conjure_aux4 = q19[2] + Context #3: [q19[1] = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (3, 4)] + Context #4: [[q19[1] = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (3, 4)], + [q19[1] = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (4, 3)]; + int(1..2)] + Context #5: flatten(1, + [[q19[1] = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (3, 4)], + [q19[1] = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (4, 3)]; + int(1..2)]) + Context #6: and(flatten(1, + [[q19[1] = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (3, 4)], + [q19[1] = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (4, 3)]; + int(1..2)])) + Context #7: [and(flatten(1, + [[q19[1] = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (3, 4)], + [q19[1] = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (4, 3)]; + int(1..2)])), + !or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2; + int(1..2)] + Context #8: and(flatten(1, + [[q19[1] = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (3, 4)], + [q19[1] = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (4, 3)]; + int(1..2)])) + /\ (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) + Context #9: { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, + [[q19[1] = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (3, 4)], + [q19[1] = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (4, 3)]; + int(1..2)])) + /\ (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) + } + Context #10: conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, + [[q19[1] = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (3, 4)], + [q19[1] = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (4, 3)]; + int(1..2)])) + /\ (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) + } + Context #11: { conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, + [[q19[1] = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (3, 4)], + [q19[1] = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (4, 3)]; + int(1..2)])) + /\ (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) + } + } + Context #12: { conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, + [[q19[1] = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (3, 4)], + [q19[1] = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (4, 3)]; + int(1..2)])) + /\ (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + Context #13: [{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, + [[q19[1] = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (3, 4)], + [q19[1] = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (4, 3)]; + int(1..2)])) + /\ (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]] + Context #14: and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, + [[q19[1] = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (3, 4)], + [q19[1] = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (4, 3)]; + int(1..2)])) + /\ (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + Context #15: [|x| = |conjure_aux1|, + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, + [[q19[1] = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (3, 4)], + [q19[1] = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (4, 3)]; + int(1..2)])) + /\ (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]); + int(1..2)] + Context #16: |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, + [[q19[1] = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (3, 4)], + [q19[1] = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (4, 3)]; + int(1..2)])) + /\ (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + Context #17: { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, + [[q19[1] = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (3, 4)], + [q19[1] = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (4, 3)]; + int(1..2)])) + /\ (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + Context #18: y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, + [[q19[1] = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (3, 4)], + [q19[1] = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (4, 3)]; + int(1..2)])) + /\ (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } +Picking the only option: Answer 1: full-evaluate: Full evaluator + 3 +storedChoice: +q19[1] 6191924817638487798 +AnsweredRule {qHole_ = 6191924817638487798, qAscendants_ = fromList [-7807298629892727492,-7342314879418443169,-6863795700888677384,-4312957023244042045,-4187455163410375661,-3675178923764728484,-2875109432163106677,-562821977670977521,-430646313158070946,645934730965016486,1213611367040462212,1245826829098445208,2464444564009404876,4591515159436918289,5954646064348546905,6209885551316441807,7780749284175319389,8140212805021622098], aRuleName_ = "full-evaluate"} +LF: {"AnsweredRule":{"aRuleName_":"full-evaluate","qAscendants_":[-7807298629892727492,-7342314879418443169,-6863795700888677384,-4312957023244042045,-4187455163410375661,-3675178923764728484,-2875109432163106677,-562821977670977521,-430646313158070946,645934730965016486,1213611367040462212,1245826829098445208,2464444564009404876,4591515159436918289,5954646064348546905,6209885551316441807,7780749284175319389,8140212805021622098],"qHole_":6191924817638487798}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, + [[3 = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (3, 4)], [q19[1] = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (4, 3)]; + int(1..2)])) + /\ (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: q19[2] + Context #1: conjure_aux4 = q19[2] + Context #2: 3 = q8_2 <-> conjure_aux4 = q19[2] + Context #3: [3 = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (3, 4)] + Context #4: [[3 = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (3, 4)], + [q19[1] = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (4, 3)]; + int(1..2)] + Context #5: flatten(1, + [[3 = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (3, 4)], [q19[1] = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (4, 3)]; + int(1..2)]) + Context #6: and(flatten(1, + [[3 = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (3, 4)], [q19[1] = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (4, 3)]; + int(1..2)])) + Context #7: [and(flatten(1, + [[3 = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (3, 4)], [q19[1] = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (4, 3)]; + int(1..2)])), + !or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2; + int(1..2)] + Context #8: and(flatten(1, + [[3 = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (3, 4)], [q19[1] = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (4, 3)]; + int(1..2)])) + /\ (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) + Context #9: { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, + [[3 = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (3, 4)], [q19[1] = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (4, 3)]; + int(1..2)])) + /\ (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) + } + Context #10: conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, + [[3 = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (3, 4)], [q19[1] = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (4, 3)]; + int(1..2)])) + /\ (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) + } + Context #11: { conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, + [[3 = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (3, 4)], [q19[1] = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (4, 3)]; + int(1..2)])) + /\ (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) + } + } + Context #12: { conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, + [[3 = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (3, 4)], [q19[1] = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (4, 3)]; + int(1..2)])) + /\ (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + Context #13: [{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, + [[3 = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (3, 4)], [q19[1] = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (4, 3)]; + int(1..2)])) + /\ (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]] + Context #14: and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, + [[3 = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (3, 4)], + [q19[1] = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (4, 3)]; + int(1..2)])) + /\ (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + Context #15: [|x| = |conjure_aux1|, + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, + [[3 = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (3, 4)], + [q19[1] = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (4, 3)]; + int(1..2)])) + /\ (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]); + int(1..2)] + Context #16: |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, + [[3 = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (3, 4)], + [q19[1] = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (4, 3)]; + int(1..2)])) + /\ (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + Context #17: { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, + [[3 = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (3, 4)], + [q19[1] = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (4, 3)]; + int(1..2)])) + /\ (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + Context #18: y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, + [[3 = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (3, 4)], + [q19[1] = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (4, 3)]; + int(1..2)])) + /\ (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } +Picking the only option: Answer 1: full-evaluate: Full evaluator + 4 +storedChoice: +q19[2] 6191080349758138413 +AnsweredRule {qHole_ = 6191080349758138413, qAscendants_ = fromList [-6520176996801677506,-5843168008449148354,-5683324553460351353,-4951129330098074556,-4643211621054911287,-3822866046842193137,-3751755282991126720,-2857878400374217220,-1860910263859276895,-1737565941370477352,1050126061434755877,2341740140041990923,2502411580506467583,2525054445025194025,3419152102230274364,7279809536600806905,8523948582780839689,8905640568803089599], aRuleName_ = "full-evaluate"} +LF: {"AnsweredRule":{"aRuleName_":"full-evaluate","qAscendants_":[-6520176996801677506,-5843168008449148354,-5683324553460351353,-4951129330098074556,-4643211621054911287,-3822866046842193137,-3751755282991126720,-2857878400374217220,-1860910263859276895,-1737565941370477352,1050126061434755877,2341740140041990923,2502411580506467583,2525054445025194025,3419152102230274364,7279809536600806905,8523948582780839689,8905640568803089599],"qHole_":6191080349758138413}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, + [[3 = q8_2 <-> conjure_aux4 = 4 | letting q19 be (3, 4)], [q19[1] = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (4, 3)]; + int(1..2)])) + /\ (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: q19[1] + Context #1: q19[1] = q8_2 + Context #2: q19[1] = q8_2 <-> conjure_aux4 = q19[2] + Context #3: [q19[1] = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (4, 3)] + Context #4: [[3 = q8_2 <-> conjure_aux4 = 4 | letting q19 be (3, 4)], + [q19[1] = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (4, 3)]; + int(1..2)] + Context #5: flatten(1, + [[3 = q8_2 <-> conjure_aux4 = 4 | letting q19 be (3, 4)], [q19[1] = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (4, 3)]; + int(1..2)]) + Context #6: and(flatten(1, + [[3 = q8_2 <-> conjure_aux4 = 4 | letting q19 be (3, 4)], [q19[1] = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (4, 3)]; + int(1..2)])) + Context #7: [and(flatten(1, + [[3 = q8_2 <-> conjure_aux4 = 4 | letting q19 be (3, 4)], [q19[1] = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (4, 3)]; + int(1..2)])), + !or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2; + int(1..2)] + Context #8: and(flatten(1, + [[3 = q8_2 <-> conjure_aux4 = 4 | letting q19 be (3, 4)], [q19[1] = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (4, 3)]; + int(1..2)])) + /\ (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) + Context #9: { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, + [[3 = q8_2 <-> conjure_aux4 = 4 | letting q19 be (3, 4)], [q19[1] = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (4, 3)]; + int(1..2)])) + /\ (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) + } + Context #10: conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, + [[3 = q8_2 <-> conjure_aux4 = 4 | letting q19 be (3, 4)], [q19[1] = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (4, 3)]; + int(1..2)])) + /\ (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) + } + Context #11: { conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, + [[3 = q8_2 <-> conjure_aux4 = 4 | letting q19 be (3, 4)], [q19[1] = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (4, 3)]; + int(1..2)])) + /\ (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) + } + } + Context #12: { conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, + [[3 = q8_2 <-> conjure_aux4 = 4 | letting q19 be (3, 4)], [q19[1] = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (4, 3)]; + int(1..2)])) + /\ (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + Context #13: [{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, + [[3 = q8_2 <-> conjure_aux4 = 4 | letting q19 be (3, 4)], [q19[1] = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (4, 3)]; + int(1..2)])) + /\ (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]] + Context #14: and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, + [[3 = q8_2 <-> conjure_aux4 = 4 | letting q19 be (3, 4)], [q19[1] = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (4, 3)]; + int(1..2)])) + /\ (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + Context #15: [|x| = |conjure_aux1|, + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, + [[3 = q8_2 <-> conjure_aux4 = 4 | letting q19 be (3, 4)], [q19[1] = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (4, 3)]; + int(1..2)])) + /\ (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]); + int(1..2)] + Context #16: |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, + [[3 = q8_2 <-> conjure_aux4 = 4 | letting q19 be (3, 4)], [q19[1] = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (4, 3)]; + int(1..2)])) + /\ (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + Context #17: { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, + [[3 = q8_2 <-> conjure_aux4 = 4 | letting q19 be (3, 4)], + [q19[1] = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (4, 3)]; + int(1..2)])) + /\ (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + Context #18: y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, + [[3 = q8_2 <-> conjure_aux4 = 4 | letting q19 be (3, 4)], + [q19[1] = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (4, 3)]; + int(1..2)])) + /\ (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } +Picking the only option: Answer 1: full-evaluate: Full evaluator + 4 +storedChoice: +q19[1] 6191924817638487798 +AnsweredRule {qHole_ = 6191924817638487798, qAscendants_ = fromList [-8623968074095065085,-7329444732361257248,-4918646323490343107,-3863503547689138135,-3675178923764728484,-3569961048242171061,-3144694525976125140,-3142709837274542140,-3025737286103464396,-2863059074413010081,-2845931958765307537,-1992102340549551315,-1320176390405360702,-727033692116714751,-430646313158070946,4099404035470031281,7496678802752551639,8353918602880186919], aRuleName_ = "full-evaluate"} +LF: {"AnsweredRule":{"aRuleName_":"full-evaluate","qAscendants_":[-8623968074095065085,-7329444732361257248,-4918646323490343107,-3863503547689138135,-3675178923764728484,-3569961048242171061,-3144694525976125140,-3142709837274542140,-3025737286103464396,-2863059074413010081,-2845931958765307537,-1992102340549551315,-1320176390405360702,-727033692116714751,-430646313158070946,4099404035470031281,7496678802752551639,8353918602880186919],"qHole_":6191924817638487798}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, + [[3 = q8_2 <-> conjure_aux4 = 4 | letting q19 be (3, 4)], [4 = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (4, 3)]; int(1..2)])) + /\ (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: q19[2] + Context #1: conjure_aux4 = q19[2] + Context #2: 4 = q8_2 <-> conjure_aux4 = q19[2] + Context #3: [4 = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (4, 3)] + Context #4: [[3 = q8_2 <-> conjure_aux4 = 4 | letting q19 be (3, 4)], [4 = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (4, 3)]; + int(1..2)] + Context #5: flatten(1, + [[3 = q8_2 <-> conjure_aux4 = 4 | letting q19 be (3, 4)], [4 = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (4, 3)]; int(1..2)]) + Context #6: and(flatten(1, + [[3 = q8_2 <-> conjure_aux4 = 4 | letting q19 be (3, 4)], [4 = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (4, 3)]; int(1..2)])) + Context #7: [and(flatten(1, + [[3 = q8_2 <-> conjure_aux4 = 4 | letting q19 be (3, 4)], [4 = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (4, 3)]; int(1..2)])), + !or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2; + int(1..2)] + Context #8: and(flatten(1, + [[3 = q8_2 <-> conjure_aux4 = 4 | letting q19 be (3, 4)], [4 = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (4, 3)]; int(1..2)])) + /\ (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) + Context #9: { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, + [[3 = q8_2 <-> conjure_aux4 = 4 | letting q19 be (3, 4)], [4 = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (4, 3)]; int(1..2)])) + /\ (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) + } + Context #10: conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, + [[3 = q8_2 <-> conjure_aux4 = 4 | letting q19 be (3, 4)], [4 = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (4, 3)]; int(1..2)])) + /\ (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) + } + Context #11: { conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, + [[3 = q8_2 <-> conjure_aux4 = 4 | letting q19 be (3, 4)], [4 = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (4, 3)]; int(1..2)])) + /\ (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) + } + } + Context #12: { conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, + [[3 = q8_2 <-> conjure_aux4 = 4 | letting q19 be (3, 4)], [4 = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (4, 3)]; int(1..2)])) + /\ (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + Context #13: [{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, + [[3 = q8_2 <-> conjure_aux4 = 4 | letting q19 be (3, 4)], [4 = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (4, 3)]; int(1..2)])) + /\ (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]] + Context #14: and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, + [[3 = q8_2 <-> conjure_aux4 = 4 | letting q19 be (3, 4)], [4 = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (4, 3)]; + int(1..2)])) + /\ (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + Context #15: [|x| = |conjure_aux1|, + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, + [[3 = q8_2 <-> conjure_aux4 = 4 | letting q19 be (3, 4)], [4 = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (4, 3)]; + int(1..2)])) + /\ (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]); + int(1..2)] + Context #16: |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, + [[3 = q8_2 <-> conjure_aux4 = 4 | letting q19 be (3, 4)], [4 = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (4, 3)]; + int(1..2)])) + /\ (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + Context #17: { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, + [[3 = q8_2 <-> conjure_aux4 = 4 | letting q19 be (3, 4)], [4 = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (4, 3)]; + int(1..2)])) + /\ (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + Context #18: y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, + [[3 = q8_2 <-> conjure_aux4 = 4 | letting q19 be (3, 4)], [4 = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (4, 3)]; + int(1..2)])) + /\ (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } +Picking the only option: Answer 1: full-evaluate: Full evaluator + 3 +storedChoice: +q19[2] 6191080349758138413 +AnsweredRule {qHole_ = 6191080349758138413, qAscendants_ = fromList [-8757640153264855213,-8246403386320852045,-7634455432471374117,-6807206396586148212,-6520176996801677506,-3765915116603809328,-3206961831370542574,-2880744773295792633,10288890695967554,1236510066935204208,2127338015569558053,2891526256517846499,4193370254288787506,4672949733519819188,4775978928665173836,5268252065626460890,7614915012244226995,8901849277253604507], aRuleName_ = "full-evaluate"} +LF: {"AnsweredRule":{"aRuleName_":"full-evaluate","qAscendants_":[-8757640153264855213,-8246403386320852045,-7634455432471374117,-6807206396586148212,-6520176996801677506,-3765915116603809328,-3206961831370542574,-2880744773295792633,10288890695967554,1236510066935204208,2127338015569558053,2891526256517846499,4193370254288787506,4672949733519819188,4775978928665173836,5268252065626460890,7614915012244226995,8901849277253604507],"qHole_":6191080349758138413}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, + [[3 = q8_2 <-> conjure_aux4 = 4 | letting q19 be (3, 4)], [4 = q8_2 <-> conjure_aux4 = 3 | letting q19 be (4, 3)]; int(1..2)])) + /\ (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: [4 = q8_2 <-> conjure_aux4 = 3 | letting q19 be (4, 3)] + Context #1: [[3 = q8_2 <-> conjure_aux4 = 4 | letting q19 be (3, 4)], [4 = q8_2 <-> conjure_aux4 = 3 | letting q19 be (4, 3)]; + int(1..2)] + Context #2: flatten(1, + [[3 = q8_2 <-> conjure_aux4 = 4 | letting q19 be (3, 4)], [4 = q8_2 <-> conjure_aux4 = 3 | letting q19 be (4, 3)]; int(1..2)]) + Context #3: and(flatten(1, + [[3 = q8_2 <-> conjure_aux4 = 4 | letting q19 be (3, 4)], [4 = q8_2 <-> conjure_aux4 = 3 | letting q19 be (4, 3)]; int(1..2)])) + Context #4: [and(flatten(1, + [[3 = q8_2 <-> conjure_aux4 = 4 | letting q19 be (3, 4)], [4 = q8_2 <-> conjure_aux4 = 3 | letting q19 be (4, 3)]; int(1..2)])), + !or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2; + int(1..2)] + Context #5: and(flatten(1, + [[3 = q8_2 <-> conjure_aux4 = 4 | letting q19 be (3, 4)], [4 = q8_2 <-> conjure_aux4 = 3 | letting q19 be (4, 3)]; int(1..2)])) + /\ (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) + Context #6: { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, + [[3 = q8_2 <-> conjure_aux4 = 4 | letting q19 be (3, 4)], [4 = q8_2 <-> conjure_aux4 = 3 | letting q19 be (4, 3)]; int(1..2)])) + /\ (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) + } + Context #7: conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, + [[3 = q8_2 <-> conjure_aux4 = 4 | letting q19 be (3, 4)], [4 = q8_2 <-> conjure_aux4 = 3 | letting q19 be (4, 3)]; int(1..2)])) + /\ (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) + } + Context #8: { conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, + [[3 = q8_2 <-> conjure_aux4 = 4 | letting q19 be (3, 4)], [4 = q8_2 <-> conjure_aux4 = 3 | letting q19 be (4, 3)]; int(1..2)])) + /\ (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) + } + } + Context #9: { conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, + [[3 = q8_2 <-> conjure_aux4 = 4 | letting q19 be (3, 4)], [4 = q8_2 <-> conjure_aux4 = 3 | letting q19 be (4, 3)]; int(1..2)])) + /\ (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + Context #10: [{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, + [[3 = q8_2 <-> conjure_aux4 = 4 | letting q19 be (3, 4)], [4 = q8_2 <-> conjure_aux4 = 3 | letting q19 be (4, 3)]; int(1..2)])) + /\ (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]] + Context #11: and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, + [[3 = q8_2 <-> conjure_aux4 = 4 | letting q19 be (3, 4)], [4 = q8_2 <-> conjure_aux4 = 3 | letting q19 be (4, 3)]; int(1..2)])) + /\ (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + Context #12: [|x| = |conjure_aux1|, + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, + [[3 = q8_2 <-> conjure_aux4 = 4 | letting q19 be (3, 4)], [4 = q8_2 <-> conjure_aux4 = 3 | letting q19 be (4, 3)]; int(1..2)])) + /\ (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]); + int(1..2)] + Context #13: |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, + [[3 = q8_2 <-> conjure_aux4 = 4 | letting q19 be (3, 4)], [4 = q8_2 <-> conjure_aux4 = 3 | letting q19 be (4, 3)]; int(1..2)])) + /\ (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + Context #14: { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, + [[3 = q8_2 <-> conjure_aux4 = 4 | letting q19 be (3, 4)], [4 = q8_2 <-> conjure_aux4 = 3 | letting q19 be (4, 3)]; + int(1..2)])) + /\ (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + Context #15: y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, + [[3 = q8_2 <-> conjure_aux4 = 4 | letting q19 be (3, 4)], [4 = q8_2 <-> conjure_aux4 = 3 | letting q19 be (4, 3)]; + int(1..2)])) + /\ (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } +Picking the only option: Answer 1: generators-first: Inlining comprehension lettings. + [4 = q8_2 <-> conjure_aux4 = 3 |] +storedChoice: +[4 = q8_2 <-> conjure_aux4 = 3 | letting q19 be (4, 3)] 1588099557195084353 +AnsweredRule {qHole_ = 1588099557195084353, qAscendants_ = fromList [-8793688442874950149,-7572881584565844112,-7548342805617471592,-4348732945489509501,-2395694351007614565,88957386040583823,374422725277413608,1323284114810179273,2396707417125615551,2821870942280363336,4471571311804301542,5264705085330663748,5735937483858420141,6159114761266478893,6376856799016601882], aRuleName_ = "generators-first"} +LF: {"AnsweredRule":{"aRuleName_":"generators-first","qAscendants_":[-8793688442874950149,-7572881584565844112,-7548342805617471592,-4348732945489509501,-2395694351007614565,88957386040583823,374422725277413608,1323284114810179273,2396707417125615551,2821870942280363336,4471571311804301542,5264705085330663748,5735937483858420141,6159114761266478893,6376856799016601882],"qHole_":1588099557195084353}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4 | letting q19 be (3, 4)], [4 = q8_2 <-> conjure_aux4 = 3 |]; int(1..2)])) /\ + (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: [4 = q8_2 <-> conjure_aux4 = 3 |] + Context #1: [[3 = q8_2 <-> conjure_aux4 = 4 | letting q19 be (3, 4)], [4 = q8_2 <-> conjure_aux4 = 3 |]; int(1..2)] + Context #2: flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4 | letting q19 be (3, 4)], [4 = q8_2 <-> conjure_aux4 = 3 |]; int(1..2)]) + Context #3: and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4 | letting q19 be (3, 4)], [4 = q8_2 <-> conjure_aux4 = 3 |]; int(1..2)])) + Context #4: [and(flatten(1, + [[3 = q8_2 <-> conjure_aux4 = 4 | letting q19 be (3, 4)], [4 = q8_2 <-> conjure_aux4 = 3 |]; int(1..2)])), + !or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2; + int(1..2)] + Context #5: and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4 | letting q19 be (3, 4)], [4 = q8_2 <-> conjure_aux4 = 3 |]; int(1..2)])) + /\ (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) + Context #6: { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4 | letting q19 be (3, 4)], [4 = q8_2 <-> conjure_aux4 = 3 |]; int(1..2)])) /\ + (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) + } + Context #7: conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4 | letting q19 be (3, 4)], [4 = q8_2 <-> conjure_aux4 = 3 |]; int(1..2)])) /\ + (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) + } + Context #8: { conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4 | letting q19 be (3, 4)], [4 = q8_2 <-> conjure_aux4 = 3 |]; int(1..2)])) /\ + (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) + } + } + Context #9: { conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4 | letting q19 be (3, 4)], [4 = q8_2 <-> conjure_aux4 = 3 |]; int(1..2)])) /\ + (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + Context #10: [{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4 | letting q19 be (3, 4)], [4 = q8_2 <-> conjure_aux4 = 3 |]; int(1..2)])) /\ + (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]] + Context #11: and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4 | letting q19 be (3, 4)], [4 = q8_2 <-> conjure_aux4 = 3 |]; int(1..2)])) /\ + (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + Context #12: [|x| = |conjure_aux1|, + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4 | letting q19 be (3, 4)], [4 = q8_2 <-> conjure_aux4 = 3 |]; int(1..2)])) /\ + (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]); + int(1..2)] + Context #13: |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4 | letting q19 be (3, 4)], [4 = q8_2 <-> conjure_aux4 = 3 |]; int(1..2)])) /\ + (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + Context #14: { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4 | letting q19 be (3, 4)], [4 = q8_2 <-> conjure_aux4 = 3 |]; int(1..2)])) /\ + (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + Context #15: y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4 | letting q19 be (3, 4)], [4 = q8_2 <-> conjure_aux4 = 3 |]; int(1..2)])) /\ + (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } +Picking the only option: Answer 1: generators-first: Empty generators. + [4 = q8_2 <-> conjure_aux4 = 3; int(1)] +storedChoice: +[4 = q8_2 <-> conjure_aux4 = 3 |] 5497036040823098170 +AnsweredRule {qHole_ = 5497036040823098170, qAscendants_ = fromList [-8392241438280449004,-7601484554155610431,-6546222595955103458,-5296722524234462815,-2359991535599832467,-1063257280645700723,-17895501989558244,635280768506310618,1960340259087120798,3697301678543081257,4285418689022343979,6976383550303671088,8132222765465596941,8451535935592013102,8523836484272235728], aRuleName_ = "generators-first"} +LF: {"AnsweredRule":{"aRuleName_":"generators-first","qAscendants_":[-8392241438280449004,-7601484554155610431,-6546222595955103458,-5296722524234462815,-2359991535599832467,-1063257280645700723,-17895501989558244,635280768506310618,1960340259087120798,3697301678543081257,4285418689022343979,6976383550303671088,8132222765465596941,8451535935592013102,8523836484272235728],"qHole_":5497036040823098170}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4 | letting q19 be (3, 4)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: [3 = q8_2 <-> conjure_aux4 = 4 | letting q19 be (3, 4)] + Context #1: [[3 = q8_2 <-> conjure_aux4 = 4 | letting q19 be (3, 4)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)] + Context #2: flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4 | letting q19 be (3, 4)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)]) + Context #3: and(flatten(1, + [[3 = q8_2 <-> conjure_aux4 = 4 | letting q19 be (3, 4)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) + Context #4: [and(flatten(1, + [[3 = q8_2 <-> conjure_aux4 = 4 | letting q19 be (3, 4)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])), + !or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2; + int(1..2)] + Context #5: and(flatten(1, + [[3 = q8_2 <-> conjure_aux4 = 4 | letting q19 be (3, 4)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) + /\ (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) + Context #6: { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4 | letting q19 be (3, 4)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) + } + Context #7: conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4 | letting q19 be (3, 4)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) + } + Context #8: { conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4 | letting q19 be (3, 4)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) + } + } + Context #9: { conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4 | letting q19 be (3, 4)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + Context #10: [{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4 | letting q19 be (3, 4)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]] + Context #11: and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4 | letting q19 be (3, 4)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + Context #12: [|x| = |conjure_aux1|, + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4 | letting q19 be (3, 4)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]); + int(1..2)] + Context #13: |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4 | letting q19 be (3, 4)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + Context #14: { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4 | letting q19 be (3, 4)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + Context #15: y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4 | letting q19 be (3, 4)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } +Picking the only option: Answer 1: generators-first: Inlining comprehension lettings. + [3 = q8_2 <-> conjure_aux4 = 4 |] +storedChoice: +[3 = q8_2 <-> conjure_aux4 = 4 | letting q19 be (3, 4)] 4563840366785778455 +AnsweredRule {qHole_ = 4563840366785778455, qAscendants_ = fromList [-8318635854976707433,-5946611935025738568,-5571483100812435886,-5359593091160120138,-5038848917712120091,-4505559122101590956,-4490512703364564363,-3882495187869643600,1795022445773124374,2052386823818313881,3017254667178360325,5004474385002050470,5786646087302900637,8288841898596402765,8964004080555796084], aRuleName_ = "generators-first"} +LF: {"AnsweredRule":{"aRuleName_":"generators-first","qAscendants_":[-8318635854976707433,-5946611935025738568,-5571483100812435886,-5359593091160120138,-5038848917712120091,-4505559122101590956,-4490512703364564363,-3882495187869643600,1795022445773124374,2052386823818313881,3017254667178360325,5004474385002050470,5786646087302900637,8288841898596402765,8964004080555796084],"qHole_":4563840366785778455}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4 |], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: [3 = q8_2 <-> conjure_aux4 = 4 |] + Context #1: [[3 = q8_2 <-> conjure_aux4 = 4 |], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)] + Context #2: flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4 |], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)]) + Context #3: and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4 |], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) + Context #4: [and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4 |], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])), + !or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2; + int(1..2)] + Context #5: and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4 |], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) + Context #6: { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4 |], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) + } + Context #7: conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4 |], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) + } + Context #8: { conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4 |], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) + } + } + Context #9: { conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4 |], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + Context #10: [{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4 |], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]] + Context #11: and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4 |], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + Context #12: [|x| = |conjure_aux1|, + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4 |], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]); + int(1..2)] + Context #13: |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4 |], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + Context #14: { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4 |], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + Context #15: y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4 |], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } +Picking the only option: Answer 1: generators-first: Empty generators. + [3 = q8_2 <-> conjure_aux4 = 4; int(1)] +storedChoice: +[3 = q8_2 <-> conjure_aux4 = 4 |] -4963556797043179790 +AnsweredRule {qHole_ = -4963556797043179790, qAscendants_ = fromList [-8774772560597070458,-8569754725622420077,-7014391000977899535,-5142692957413181259,-4041649316716467790,-3712748679124722967,-622761194274709583,-434728569439334546,1040357877965562186,2786263529603136423,3452832737484532816,4830299290996501437,5939727597018131278,7229121740432553148,8127256833064397799], aRuleName_ = "generators-first"} +LF: {"AnsweredRule":{"aRuleName_":"generators-first","qAscendants_":[-8774772560597070458,-8569754725622420077,-7014391000977899535,-5142692957413181259,-4041649316716467790,-3712748679124722967,-622761194274709583,-434728569439334546,1040357877965562186,2786263529603136423,3452832737484532816,4830299290996501437,5939727597018131278,7229121740432553148,8127256833064397799],"qHole_":-4963556797043179790}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: [(3, 4), (4, 3); int(1..2)] + Context #1: [q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]] + Context #2: or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) + Context #3: !or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) + Context #4: !or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2 + Context #5: [and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])), + !or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2; + int(1..2)] + Context #6: and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) + Context #7: { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) + } + Context #8: conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) + } + Context #9: { conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) + } + } + Context #10: { conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + Context #11: [{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]] + Context #12: and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + Context #13: [|x| = |conjure_aux1|, + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]); + int(1..2)] + Context #14: |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + Context #15: { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + Context #16: y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } +Picking the only option: Answer 1: full-evaluate: Full evaluator + [(3, 4), (4, 3); int(1..2)] +storedChoice: +[(3, 4), (4, 3); int(1..2)] 6597397470067790033 +AnsweredRule {qHole_ = 6597397470067790033, qAscendants_ = fromList [-8633754808918514186,-8188184727507762196,-5677541651570710819,-4916174755379616322,-4850199604535152020,-3462648503323623219,-2367628624258445968,-2307855029918049024,1883982971068606087,1912870777007720445,2809445194379708718,3667006364909395131,3677477140697149393,7256127331114215867,8364657527657792986,9047491038558976704], aRuleName_ = "full-evaluate"} +LF: {"AnsweredRule":{"aRuleName_":"full-evaluate","qAscendants_":[-8633754808918514186,-8188184727507762196,-5677541651570710819,-4916174755379616322,-4850199604535152020,-3462648503323623219,-2367628624258445968,-2307855029918049024,1883982971068606087,1912870777007720445,2809445194379708718,3667006364909395131,3677477140697149393,7256127331114215867,8364657527657792986,9047491038558976704],"qHole_":6597397470067790033}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: [q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]] + Context #1: or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) + Context #2: !or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) + Context #3: !or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2 + Context #4: [and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])), + !or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2; + int(1..2)] + Context #5: and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) + Context #6: { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) + } + Context #7: conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) + } + Context #8: { conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) + } + } + Context #9: { conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + Context #10: [{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]] + Context #11: and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + Context #12: [|x| = |conjure_aux1|, + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]); + int(1..2)] + Context #13: |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + Context #14: { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + Context #15: y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } +Picking the only option: Answer 1: complex-pattern: complex pattern on tuple patterns + [q20[1] = conjure_aux4 | q20 <- [(3, 4), (4, 3); int(1..2)]] +storedChoice: +[q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]] -4850199604535152020 +AnsweredRule {qHole_ = -4850199604535152020, qAscendants_ = fromList [-8633754808918514186,-8188184727507762196,-5677541651570710819,-4916174755379616322,-3462648503323623219,-2367628624258445968,-2307855029918049024,1883982971068606087,1912870777007720445,2809445194379708718,3667006364909395131,3677477140697149393,7256127331114215867,8364657527657792986,9047491038558976704], aRuleName_ = "complex-pattern"} +LF: {"AnsweredRule":{"aRuleName_":"complex-pattern","qAscendants_":[-8633754808918514186,-8188184727507762196,-5677541651570710819,-4916174755379616322,-3462648503323623219,-2367628624258445968,-2307855029918049024,1883982971068606087,1912870777007720445,2809445194379708718,3667006364909395131,3677477140697149393,7256127331114215867,8364657527657792986,9047491038558976704],"qHole_":-4850199604535152020}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!or([q20[1] = conjure_aux4 | q20 <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: [q20[1] = conjure_aux4 | q20 <- [(3, 4), (4, 3); int(1..2)]] + Context #1: or([q20[1] = conjure_aux4 | q20 <- [(3, 4), (4, 3); int(1..2)]]) + Context #2: !or([q20[1] = conjure_aux4 | q20 <- [(3, 4), (4, 3); int(1..2)]]) + Context #3: !or([q20[1] = conjure_aux4 | q20 <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2 + Context #4: [and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])), + !or([q20[1] = conjure_aux4 | q20 <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2; + int(1..2)] + Context #5: and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!or([q20[1] = conjure_aux4 | q20 <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) + Context #6: { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!or([q20[1] = conjure_aux4 | q20 <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) + } + Context #7: conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!or([q20[1] = conjure_aux4 | q20 <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) + } + Context #8: { conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!or([q20[1] = conjure_aux4 | q20 <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) + } + } + Context #9: { conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!or([q20[1] = conjure_aux4 | q20 <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + Context #10: [{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!or([q20[1] = conjure_aux4 | q20 <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]] + Context #11: and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!or([q20[1] = conjure_aux4 | q20 <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + Context #12: [|x| = |conjure_aux1|, + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!or([q20[1] = conjure_aux4 | q20 <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]); + int(1..2)] + Context #13: |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!or([q20[1] = conjure_aux4 | q20 <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + Context #14: { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!or([q20[1] = conjure_aux4 | q20 <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + Context #15: y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!or([q20[1] = conjure_aux4 | q20 <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } +Picking the only option: Answer 1: matrix-comprehension-literal: Vertical rule for matrix-comprehension on matrix literal + flatten(1, [[q20[1] = conjure_aux4 | letting q20 be (3, 4)], [q20[1] = conjure_aux4 | letting q20 be (4, 3)]; int(1..2)]) +storedChoice: +[q20[1] = conjure_aux4 | q20 <- [(3, 4), (4, 3); int(1..2)]] -7042519532359788232 +AnsweredRule {qHole_ = -7042519532359788232, qAscendants_ = fromList [-8908244575740954826,-5683928670681234592,-5283973279755061591,-3518626964796470528,-1965680338567566419,-1619218070244699183,-1290540526775639182,-1001280480543716507,-920250991117702438,-37243485035014411,3109960451075183399,3577717700431629359,4854879008546753238,5736831950861882173,7673200081862847690], aRuleName_ = "matrix-comprehension-literal"} +LF: {"AnsweredRule":{"aRuleName_":"matrix-comprehension-literal","qAscendants_":[-8908244575740954826,-5683928670681234592,-5283973279755061591,-3518626964796470528,-1965680338567566419,-1619218070244699183,-1290540526775639182,-1001280480543716507,-920250991117702438,-37243485035014411,3109960451075183399,3577717700431629359,4854879008546753238,5736831950861882173,7673200081862847690],"qHole_":-7042519532359788232}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!or(flatten(1, [[q20[1] = conjure_aux4 | letting q20 be (3, 4)], [q20[1] = conjure_aux4 | letting q20 be (4, 3)]; int(1..2)])) <-> + conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: q20[1] + Context #1: q20[1] = conjure_aux4 + Context #2: [q20[1] = conjure_aux4 | letting q20 be (3, 4)] + Context #3: [[q20[1] = conjure_aux4 | letting q20 be (3, 4)], [q20[1] = conjure_aux4 | letting q20 be (4, 3)]; int(1..2)] + Context #4: flatten(1, [[q20[1] = conjure_aux4 | letting q20 be (3, 4)], [q20[1] = conjure_aux4 | letting q20 be (4, 3)]; int(1..2)]) + Context #5: or(flatten(1, + [[q20[1] = conjure_aux4 | letting q20 be (3, 4)], [q20[1] = conjure_aux4 | letting q20 be (4, 3)]; int(1..2)])) + Context #6: !or(flatten(1, + [[q20[1] = conjure_aux4 | letting q20 be (3, 4)], [q20[1] = conjure_aux4 | letting q20 be (4, 3)]; int(1..2)])) + Context #7: !or(flatten(1, + [[q20[1] = conjure_aux4 | letting q20 be (3, 4)], [q20[1] = conjure_aux4 | letting q20 be (4, 3)]; int(1..2)])) + <-> conjure_aux4 = q8_2 + Context #8: [and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])), + !or(flatten(1, [[q20[1] = conjure_aux4 | letting q20 be (3, 4)], [q20[1] = conjure_aux4 | letting q20 be (4, 3)]; int(1..2)])) <-> + conjure_aux4 = q8_2; + int(1..2)] + Context #9: and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!or(flatten(1, [[q20[1] = conjure_aux4 | letting q20 be (3, 4)], [q20[1] = conjure_aux4 | letting q20 be (4, 3)]; int(1..2)])) <-> + conjure_aux4 = q8_2) + Context #10: { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!or(flatten(1, [[q20[1] = conjure_aux4 | letting q20 be (3, 4)], [q20[1] = conjure_aux4 | letting q20 be (4, 3)]; int(1..2)])) <-> + conjure_aux4 = q8_2) + } + Context #11: conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!or(flatten(1, [[q20[1] = conjure_aux4 | letting q20 be (3, 4)], [q20[1] = conjure_aux4 | letting q20 be (4, 3)]; int(1..2)])) <-> + conjure_aux4 = q8_2) + } + Context #12: { conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!or(flatten(1, [[q20[1] = conjure_aux4 | letting q20 be (3, 4)], [q20[1] = conjure_aux4 | letting q20 be (4, 3)]; int(1..2)])) <-> + conjure_aux4 = q8_2) + } + } + Context #13: { conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!or(flatten(1, [[q20[1] = conjure_aux4 | letting q20 be (3, 4)], [q20[1] = conjure_aux4 | letting q20 be (4, 3)]; int(1..2)])) <-> + conjure_aux4 = q8_2) + } + } + in conjure_aux1 + Context #14: [{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!or(flatten(1, [[q20[1] = conjure_aux4 | letting q20 be (3, 4)], [q20[1] = conjure_aux4 | letting q20 be (4, 3)]; int(1..2)])) <-> + conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]] + Context #15: and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!or(flatten(1, [[q20[1] = conjure_aux4 | letting q20 be (3, 4)], [q20[1] = conjure_aux4 | letting q20 be (4, 3)]; int(1..2)])) <-> + conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + Context #16: [|x| = |conjure_aux1|, + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!or(flatten(1, [[q20[1] = conjure_aux4 | letting q20 be (3, 4)], [q20[1] = conjure_aux4 | letting q20 be (4, 3)]; int(1..2)])) <-> + conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]); + int(1..2)] + Context #17: |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!or(flatten(1, [[q20[1] = conjure_aux4 | letting q20 be (3, 4)], [q20[1] = conjure_aux4 | letting q20 be (4, 3)]; int(1..2)])) <-> + conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + Context #18: { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!or(flatten(1, [[q20[1] = conjure_aux4 | letting q20 be (3, 4)], [q20[1] = conjure_aux4 | letting q20 be (4, 3)]; int(1..2)])) <-> + conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + Context #19: y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!or(flatten(1, [[q20[1] = conjure_aux4 | letting q20 be (3, 4)], [q20[1] = conjure_aux4 | letting q20 be (4, 3)]; int(1..2)])) <-> + conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } +Picking the only option: Answer 1: full-evaluate: Full evaluator + 3 +storedChoice: +q20[1] -5066820997822192518 +AnsweredRule {qHole_ = -5066820997822192518, qAscendants_ = fromList [-8114810939578997179,-5955986499643421728,-5766477344136638660,-3619457499884836706,-3596989804158315723,-3512526206489503481,-2484614995521209041,-1748033148869835596,-58454364784882596,76873978234325305,2489610439802360191,3564003602712422871,3732529855370416098,3884465148016108231,4296494138735898078,4399359040184583027,4639251469994992570,7395797297508748841,7886700597594415296], aRuleName_ = "full-evaluate"} +LF: {"AnsweredRule":{"aRuleName_":"full-evaluate","qAscendants_":[-8114810939578997179,-5955986499643421728,-5766477344136638660,-3619457499884836706,-3596989804158315723,-3512526206489503481,-2484614995521209041,-1748033148869835596,-58454364784882596,76873978234325305,2489610439802360191,3564003602712422871,3732529855370416098,3884465148016108231,4296494138735898078,4399359040184583027,4639251469994992570,7395797297508748841,7886700597594415296],"qHole_":-5066820997822192518}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!or(flatten(1, [[3 = conjure_aux4 | letting q20 be (3, 4)], [q20[1] = conjure_aux4 | letting q20 be (4, 3)]; int(1..2)])) <-> + conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: q20[1] + Context #1: q20[1] = conjure_aux4 + Context #2: [q20[1] = conjure_aux4 | letting q20 be (4, 3)] + Context #3: [[3 = conjure_aux4 | letting q20 be (3, 4)], [q20[1] = conjure_aux4 | letting q20 be (4, 3)]; int(1..2)] + Context #4: flatten(1, [[3 = conjure_aux4 | letting q20 be (3, 4)], [q20[1] = conjure_aux4 | letting q20 be (4, 3)]; int(1..2)]) + Context #5: or(flatten(1, [[3 = conjure_aux4 | letting q20 be (3, 4)], [q20[1] = conjure_aux4 | letting q20 be (4, 3)]; int(1..2)])) + Context #6: !or(flatten(1, [[3 = conjure_aux4 | letting q20 be (3, 4)], [q20[1] = conjure_aux4 | letting q20 be (4, 3)]; int(1..2)])) + Context #7: !or(flatten(1, [[3 = conjure_aux4 | letting q20 be (3, 4)], [q20[1] = conjure_aux4 | letting q20 be (4, 3)]; int(1..2)])) + <-> conjure_aux4 = q8_2 + Context #8: [and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])), + !or(flatten(1, [[3 = conjure_aux4 | letting q20 be (3, 4)], [q20[1] = conjure_aux4 | letting q20 be (4, 3)]; int(1..2)])) <-> + conjure_aux4 = q8_2; + int(1..2)] + Context #9: and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!or(flatten(1, [[3 = conjure_aux4 | letting q20 be (3, 4)], [q20[1] = conjure_aux4 | letting q20 be (4, 3)]; int(1..2)])) <-> + conjure_aux4 = q8_2) + Context #10: { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!or(flatten(1, [[3 = conjure_aux4 | letting q20 be (3, 4)], [q20[1] = conjure_aux4 | letting q20 be (4, 3)]; int(1..2)])) <-> + conjure_aux4 = q8_2) + } + Context #11: conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!or(flatten(1, [[3 = conjure_aux4 | letting q20 be (3, 4)], [q20[1] = conjure_aux4 | letting q20 be (4, 3)]; int(1..2)])) <-> + conjure_aux4 = q8_2) + } + Context #12: { conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!or(flatten(1, [[3 = conjure_aux4 | letting q20 be (3, 4)], [q20[1] = conjure_aux4 | letting q20 be (4, 3)]; int(1..2)])) <-> + conjure_aux4 = q8_2) + } + } + Context #13: { conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!or(flatten(1, [[3 = conjure_aux4 | letting q20 be (3, 4)], [q20[1] = conjure_aux4 | letting q20 be (4, 3)]; int(1..2)])) <-> + conjure_aux4 = q8_2) + } + } + in conjure_aux1 + Context #14: [{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!or(flatten(1, [[3 = conjure_aux4 | letting q20 be (3, 4)], [q20[1] = conjure_aux4 | letting q20 be (4, 3)]; int(1..2)])) <-> + conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]] + Context #15: and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!or(flatten(1, [[3 = conjure_aux4 | letting q20 be (3, 4)], [q20[1] = conjure_aux4 | letting q20 be (4, 3)]; int(1..2)])) <-> + conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + Context #16: [|x| = |conjure_aux1|, + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!or(flatten(1, [[3 = conjure_aux4 | letting q20 be (3, 4)], [q20[1] = conjure_aux4 | letting q20 be (4, 3)]; int(1..2)])) <-> + conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]); + int(1..2)] + Context #17: |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!or(flatten(1, [[3 = conjure_aux4 | letting q20 be (3, 4)], [q20[1] = conjure_aux4 | letting q20 be (4, 3)]; int(1..2)])) <-> + conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + Context #18: { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!or(flatten(1, [[3 = conjure_aux4 | letting q20 be (3, 4)], [q20[1] = conjure_aux4 | letting q20 be (4, 3)]; int(1..2)])) <-> + conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + Context #19: y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!or(flatten(1, [[3 = conjure_aux4 | letting q20 be (3, 4)], [q20[1] = conjure_aux4 | letting q20 be (4, 3)]; int(1..2)])) <-> + conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } +Picking the only option: Answer 1: full-evaluate: Full evaluator + 4 +storedChoice: +q20[1] -5066820997822192518 +AnsweredRule {qHole_ = -5066820997822192518, qAscendants_ = fromList [-8725074021340919078,-8574349549577316045,-7990711773149197775,-7723660686298995374,-6875295913338400819,-5695102429637848602,-5273340809049818279,-3512526206489503481,-2862537938983036678,-2765562469061820724,-807453819412548209,-307031570223611599,37627954002053673,516678838692838411,3479854824023329968,6753745594226090750,8107007183604066764,8502378019651797201,9046378511697116254], aRuleName_ = "full-evaluate"} +LF: {"AnsweredRule":{"aRuleName_":"full-evaluate","qAscendants_":[-8725074021340919078,-8574349549577316045,-7990711773149197775,-7723660686298995374,-6875295913338400819,-5695102429637848602,-5273340809049818279,-3512526206489503481,-2862537938983036678,-2765562469061820724,-807453819412548209,-307031570223611599,37627954002053673,516678838692838411,3479854824023329968,6753745594226090750,8107007183604066764,8502378019651797201,9046378511697116254],"qHole_":-5066820997822192518}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!or(flatten(1, [[3 = conjure_aux4 | letting q20 be (3, 4)], [4 = conjure_aux4 | letting q20 be (4, 3)]; int(1..2)])) <-> + conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: [4 = conjure_aux4 | letting q20 be (4, 3)] + Context #1: [[3 = conjure_aux4 | letting q20 be (3, 4)], [4 = conjure_aux4 | letting q20 be (4, 3)]; int(1..2)] + Context #2: flatten(1, [[3 = conjure_aux4 | letting q20 be (3, 4)], [4 = conjure_aux4 | letting q20 be (4, 3)]; int(1..2)]) + Context #3: or(flatten(1, [[3 = conjure_aux4 | letting q20 be (3, 4)], [4 = conjure_aux4 | letting q20 be (4, 3)]; int(1..2)])) + Context #4: !or(flatten(1, [[3 = conjure_aux4 | letting q20 be (3, 4)], [4 = conjure_aux4 | letting q20 be (4, 3)]; int(1..2)])) + Context #5: !or(flatten(1, [[3 = conjure_aux4 | letting q20 be (3, 4)], [4 = conjure_aux4 | letting q20 be (4, 3)]; int(1..2)])) <-> + conjure_aux4 = q8_2 + Context #6: [and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])), + !or(flatten(1, [[3 = conjure_aux4 | letting q20 be (3, 4)], [4 = conjure_aux4 | letting q20 be (4, 3)]; int(1..2)])) <-> + conjure_aux4 = q8_2; + int(1..2)] + Context #7: and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!or(flatten(1, [[3 = conjure_aux4 | letting q20 be (3, 4)], [4 = conjure_aux4 | letting q20 be (4, 3)]; int(1..2)])) <-> + conjure_aux4 = q8_2) + Context #8: { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!or(flatten(1, [[3 = conjure_aux4 | letting q20 be (3, 4)], [4 = conjure_aux4 | letting q20 be (4, 3)]; int(1..2)])) <-> + conjure_aux4 = q8_2) + } + Context #9: conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!or(flatten(1, [[3 = conjure_aux4 | letting q20 be (3, 4)], [4 = conjure_aux4 | letting q20 be (4, 3)]; int(1..2)])) <-> + conjure_aux4 = q8_2) + } + Context #10: { conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!or(flatten(1, [[3 = conjure_aux4 | letting q20 be (3, 4)], [4 = conjure_aux4 | letting q20 be (4, 3)]; int(1..2)])) <-> + conjure_aux4 = q8_2) + } + } + Context #11: { conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!or(flatten(1, [[3 = conjure_aux4 | letting q20 be (3, 4)], [4 = conjure_aux4 | letting q20 be (4, 3)]; int(1..2)])) <-> + conjure_aux4 = q8_2) + } + } + in conjure_aux1 + Context #12: [{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!or(flatten(1, [[3 = conjure_aux4 | letting q20 be (3, 4)], [4 = conjure_aux4 | letting q20 be (4, 3)]; int(1..2)])) <-> + conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]] + Context #13: and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!or(flatten(1, [[3 = conjure_aux4 | letting q20 be (3, 4)], [4 = conjure_aux4 | letting q20 be (4, 3)]; int(1..2)])) <-> + conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + Context #14: [|x| = |conjure_aux1|, + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!or(flatten(1, [[3 = conjure_aux4 | letting q20 be (3, 4)], [4 = conjure_aux4 | letting q20 be (4, 3)]; int(1..2)])) <-> + conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]); + int(1..2)] + Context #15: |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!or(flatten(1, [[3 = conjure_aux4 | letting q20 be (3, 4)], [4 = conjure_aux4 | letting q20 be (4, 3)]; int(1..2)])) <-> + conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + Context #16: { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!or(flatten(1, [[3 = conjure_aux4 | letting q20 be (3, 4)], [4 = conjure_aux4 | letting q20 be (4, 3)]; int(1..2)])) <-> + conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + Context #17: y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!or(flatten(1, [[3 = conjure_aux4 | letting q20 be (3, 4)], [4 = conjure_aux4 | letting q20 be (4, 3)]; int(1..2)])) <-> + conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } +Picking the only option: Answer 1: generators-first: Inlining comprehension lettings. + [4 = conjure_aux4 |] +storedChoice: +[4 = conjure_aux4 | letting q20 be (4, 3)] -4659269292751863231 +AnsweredRule {qHole_ = -4659269292751863231, qAscendants_ = fromList [-8139107762275405780,-6067050360933011415,-4668927100952759839,-2832336555945972970,-2685263499350289956,-712998101401819851,-662867422474666417,-634413128047463436,1314890692039055455,1461492958057141352,1536420920342600247,1612507314243025908,6104410666907258834,6818646762744932078,7002085677101186921,7870098581639353518,8074964079189467219], aRuleName_ = "generators-first"} +LF: {"AnsweredRule":{"aRuleName_":"generators-first","qAscendants_":[-8139107762275405780,-6067050360933011415,-4668927100952759839,-2832336555945972970,-2685263499350289956,-712998101401819851,-662867422474666417,-634413128047463436,1314890692039055455,1461492958057141352,1536420920342600247,1612507314243025908,6104410666907258834,6818646762744932078,7002085677101186921,7870098581639353518,8074964079189467219],"qHole_":-4659269292751863231}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!or(flatten(1, [[3 = conjure_aux4 | letting q20 be (3, 4)], [4 = conjure_aux4 |]; int(1..2)])) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: [4 = conjure_aux4 |] + Context #1: [[3 = conjure_aux4 | letting q20 be (3, 4)], [4 = conjure_aux4 |]; int(1..2)] + Context #2: flatten(1, [[3 = conjure_aux4 | letting q20 be (3, 4)], [4 = conjure_aux4 |]; int(1..2)]) + Context #3: or(flatten(1, [[3 = conjure_aux4 | letting q20 be (3, 4)], [4 = conjure_aux4 |]; int(1..2)])) + Context #4: !or(flatten(1, [[3 = conjure_aux4 | letting q20 be (3, 4)], [4 = conjure_aux4 |]; int(1..2)])) + Context #5: !or(flatten(1, [[3 = conjure_aux4 | letting q20 be (3, 4)], [4 = conjure_aux4 |]; int(1..2)])) <-> conjure_aux4 = q8_2 + Context #6: [and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])), + !or(flatten(1, [[3 = conjure_aux4 | letting q20 be (3, 4)], [4 = conjure_aux4 |]; int(1..2)])) <-> conjure_aux4 = q8_2; + int(1..2)] + Context #7: and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!or(flatten(1, [[3 = conjure_aux4 | letting q20 be (3, 4)], [4 = conjure_aux4 |]; int(1..2)])) <-> conjure_aux4 = q8_2) + Context #8: { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!or(flatten(1, [[3 = conjure_aux4 | letting q20 be (3, 4)], [4 = conjure_aux4 |]; int(1..2)])) <-> conjure_aux4 = q8_2) + } + Context #9: conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!or(flatten(1, [[3 = conjure_aux4 | letting q20 be (3, 4)], [4 = conjure_aux4 |]; int(1..2)])) <-> conjure_aux4 = q8_2) + } + Context #10: { conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!or(flatten(1, [[3 = conjure_aux4 | letting q20 be (3, 4)], [4 = conjure_aux4 |]; int(1..2)])) <-> conjure_aux4 = q8_2) + } + } + Context #11: { conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!or(flatten(1, [[3 = conjure_aux4 | letting q20 be (3, 4)], [4 = conjure_aux4 |]; int(1..2)])) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + Context #12: [{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!or(flatten(1, [[3 = conjure_aux4 | letting q20 be (3, 4)], [4 = conjure_aux4 |]; int(1..2)])) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]] + Context #13: and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!or(flatten(1, [[3 = conjure_aux4 | letting q20 be (3, 4)], [4 = conjure_aux4 |]; int(1..2)])) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + Context #14: [|x| = |conjure_aux1|, + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!or(flatten(1, [[3 = conjure_aux4 | letting q20 be (3, 4)], [4 = conjure_aux4 |]; int(1..2)])) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]); + int(1..2)] + Context #15: |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!or(flatten(1, [[3 = conjure_aux4 | letting q20 be (3, 4)], [4 = conjure_aux4 |]; int(1..2)])) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + Context #16: { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!or(flatten(1, [[3 = conjure_aux4 | letting q20 be (3, 4)], [4 = conjure_aux4 |]; int(1..2)])) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + Context #17: y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!or(flatten(1, [[3 = conjure_aux4 | letting q20 be (3, 4)], [4 = conjure_aux4 |]; int(1..2)])) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } +Picking the only option: Answer 1: generators-first: Empty generators. + [4 = conjure_aux4; int(1)] +storedChoice: +[4 = conjure_aux4 |] 3103944569848083730 +AnsweredRule {qHole_ = 3103944569848083730, qAscendants_ = fromList [-6499292278244277577,-5447382347614094034,-3901800536920366688,-3381517728243229044,-2903466984087021575,-1629155788585143592,-595707724612505928,-531462185798445081,-436711175201990026,-305874969643107400,713364048257302949,3760728491479375708,4192007196113212495,5520591029544627590,7106210168219555744,7226177407162985748,8785470622724542357], aRuleName_ = "generators-first"} +LF: {"AnsweredRule":{"aRuleName_":"generators-first","qAscendants_":[-6499292278244277577,-5447382347614094034,-3901800536920366688,-3381517728243229044,-2903466984087021575,-1629155788585143592,-595707724612505928,-531462185798445081,-436711175201990026,-305874969643107400,713364048257302949,3760728491479375708,4192007196113212495,5520591029544627590,7106210168219555744,7226177407162985748,8785470622724542357],"qHole_":3103944569848083730}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!or(flatten(1, [[3 = conjure_aux4 | letting q20 be (3, 4)], [4 = conjure_aux4; int(1)]; int(1..2)])) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: [3 = conjure_aux4 | letting q20 be (3, 4)] + Context #1: [[3 = conjure_aux4 | letting q20 be (3, 4)], [4 = conjure_aux4; int(1)]; int(1..2)] + Context #2: flatten(1, [[3 = conjure_aux4 | letting q20 be (3, 4)], [4 = conjure_aux4; int(1)]; int(1..2)]) + Context #3: or(flatten(1, [[3 = conjure_aux4 | letting q20 be (3, 4)], [4 = conjure_aux4; int(1)]; int(1..2)])) + Context #4: !or(flatten(1, [[3 = conjure_aux4 | letting q20 be (3, 4)], [4 = conjure_aux4; int(1)]; int(1..2)])) + Context #5: !or(flatten(1, [[3 = conjure_aux4 | letting q20 be (3, 4)], [4 = conjure_aux4; int(1)]; int(1..2)])) <-> + conjure_aux4 = q8_2 + Context #6: [and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])), + !or(flatten(1, [[3 = conjure_aux4 | letting q20 be (3, 4)], [4 = conjure_aux4; int(1)]; int(1..2)])) <-> conjure_aux4 = q8_2; + int(1..2)] + Context #7: and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!or(flatten(1, [[3 = conjure_aux4 | letting q20 be (3, 4)], [4 = conjure_aux4; int(1)]; int(1..2)])) <-> conjure_aux4 = q8_2) + Context #8: { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!or(flatten(1, [[3 = conjure_aux4 | letting q20 be (3, 4)], [4 = conjure_aux4; int(1)]; int(1..2)])) <-> conjure_aux4 = q8_2) + } + Context #9: conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!or(flatten(1, [[3 = conjure_aux4 | letting q20 be (3, 4)], [4 = conjure_aux4; int(1)]; int(1..2)])) <-> conjure_aux4 = q8_2) + } + Context #10: { conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!or(flatten(1, [[3 = conjure_aux4 | letting q20 be (3, 4)], [4 = conjure_aux4; int(1)]; int(1..2)])) <-> conjure_aux4 = q8_2) + } + } + Context #11: { conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!or(flatten(1, [[3 = conjure_aux4 | letting q20 be (3, 4)], [4 = conjure_aux4; int(1)]; int(1..2)])) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + Context #12: [{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!or(flatten(1, [[3 = conjure_aux4 | letting q20 be (3, 4)], [4 = conjure_aux4; int(1)]; int(1..2)])) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]] + Context #13: and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!or(flatten(1, [[3 = conjure_aux4 | letting q20 be (3, 4)], [4 = conjure_aux4; int(1)]; int(1..2)])) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + Context #14: [|x| = |conjure_aux1|, + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!or(flatten(1, [[3 = conjure_aux4 | letting q20 be (3, 4)], [4 = conjure_aux4; int(1)]; int(1..2)])) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]); + int(1..2)] + Context #15: |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!or(flatten(1, [[3 = conjure_aux4 | letting q20 be (3, 4)], [4 = conjure_aux4; int(1)]; int(1..2)])) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + Context #16: { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!or(flatten(1, [[3 = conjure_aux4 | letting q20 be (3, 4)], [4 = conjure_aux4; int(1)]; int(1..2)])) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + Context #17: y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!or(flatten(1, [[3 = conjure_aux4 | letting q20 be (3, 4)], [4 = conjure_aux4; int(1)]; int(1..2)])) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } +Picking the only option: Answer 1: generators-first: Inlining comprehension lettings. + [3 = conjure_aux4 |] +storedChoice: +[3 = conjure_aux4 | letting q20 be (3, 4)] -6255934535417186594 +AnsweredRule {qHole_ = -6255934535417186594, qAscendants_ = fromList [-7136276057455168685,-7072459974569890512,-6196259248273364037,-5834210587143255228,-2665342865711637679,-1906879012656170539,-1522455433242873900,752122676500601510,1351313430292206143,2164743633705935677,2917302706197316348,3522536415221397176,3844998889588585321,5240671478404014136,7264763306810372171,7563078030555210243,8716248641960869542], aRuleName_ = "generators-first"} +LF: {"AnsweredRule":{"aRuleName_":"generators-first","qAscendants_":[-7136276057455168685,-7072459974569890512,-6196259248273364037,-5834210587143255228,-2665342865711637679,-1906879012656170539,-1522455433242873900,752122676500601510,1351313430292206143,2164743633705935677,2917302706197316348,3522536415221397176,3844998889588585321,5240671478404014136,7264763306810372171,7563078030555210243,8716248641960869542],"qHole_":-6255934535417186594}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!or(flatten(1, [[3 = conjure_aux4 |], [4 = conjure_aux4; int(1)]; int(1..2)])) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: [3 = conjure_aux4 |] + Context #1: [[3 = conjure_aux4 |], [4 = conjure_aux4; int(1)]; int(1..2)] + Context #2: flatten(1, [[3 = conjure_aux4 |], [4 = conjure_aux4; int(1)]; int(1..2)]) + Context #3: or(flatten(1, [[3 = conjure_aux4 |], [4 = conjure_aux4; int(1)]; int(1..2)])) + Context #4: !or(flatten(1, [[3 = conjure_aux4 |], [4 = conjure_aux4; int(1)]; int(1..2)])) + Context #5: !or(flatten(1, [[3 = conjure_aux4 |], [4 = conjure_aux4; int(1)]; int(1..2)])) <-> conjure_aux4 = q8_2 + Context #6: [and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])), + !or(flatten(1, [[3 = conjure_aux4 |], [4 = conjure_aux4; int(1)]; int(1..2)])) <-> conjure_aux4 = q8_2; + int(1..2)] + Context #7: and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!or(flatten(1, [[3 = conjure_aux4 |], [4 = conjure_aux4; int(1)]; int(1..2)])) <-> conjure_aux4 = q8_2) + Context #8: { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!or(flatten(1, [[3 = conjure_aux4 |], [4 = conjure_aux4; int(1)]; int(1..2)])) <-> conjure_aux4 = q8_2) + } + Context #9: conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!or(flatten(1, [[3 = conjure_aux4 |], [4 = conjure_aux4; int(1)]; int(1..2)])) <-> conjure_aux4 = q8_2) + } + Context #10: { conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!or(flatten(1, [[3 = conjure_aux4 |], [4 = conjure_aux4; int(1)]; int(1..2)])) <-> conjure_aux4 = q8_2) + } + } + Context #11: { conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!or(flatten(1, [[3 = conjure_aux4 |], [4 = conjure_aux4; int(1)]; int(1..2)])) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + Context #12: [{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!or(flatten(1, [[3 = conjure_aux4 |], [4 = conjure_aux4; int(1)]; int(1..2)])) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]] + Context #13: and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!or(flatten(1, [[3 = conjure_aux4 |], [4 = conjure_aux4; int(1)]; int(1..2)])) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + Context #14: [|x| = |conjure_aux1|, + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!or(flatten(1, [[3 = conjure_aux4 |], [4 = conjure_aux4; int(1)]; int(1..2)])) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]); + int(1..2)] + Context #15: |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!or(flatten(1, [[3 = conjure_aux4 |], [4 = conjure_aux4; int(1)]; int(1..2)])) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + Context #16: { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!or(flatten(1, [[3 = conjure_aux4 |], [4 = conjure_aux4; int(1)]; int(1..2)])) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + Context #17: y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!or(flatten(1, [[3 = conjure_aux4 |], [4 = conjure_aux4; int(1)]; int(1..2)])) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } +Picking the only option: Answer 1: generators-first: Empty generators. + [3 = conjure_aux4; int(1)] +storedChoice: +[3 = conjure_aux4 |] -2658614992963116405 +AnsweredRule {qHole_ = -2658614992963116405, qAscendants_ = fromList [-8200797483737906583,-7142891394430515063,-5048865527690557400,-3204141723258765628,-2755421715163082104,-2150417528239571907,-427238415401958863,345854652969155162,444587743724873706,1433275916120849547,2082716253070264500,3621608353720498501,3817394469011428558,4338626750910725978,6129719379140106144,6899422834286368127,8748622476088678609], aRuleName_ = "generators-first"} +LF: {"AnsweredRule":{"aRuleName_":"generators-first","qAscendants_":[-8200797483737906583,-7142891394430515063,-5048865527690557400,-3204141723258765628,-2755421715163082104,-2150417528239571907,-427238415401958863,345854652969155162,444587743724873706,1433275916120849547,2082716253070264500,3621608353720498501,3817394469011428558,4338626750910725978,6129719379140106144,6899422834286368127,8748622476088678609],"qHole_":-2658614992963116405}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!or(flatten(1, [[3 = conjure_aux4; int(1)], [4 = conjure_aux4; int(1)]; int(1..2)])) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: or(flatten(1, [[3 = conjure_aux4; int(1)], [4 = conjure_aux4; int(1)]; int(1..2)])) + Context #1: !or(flatten(1, [[3 = conjure_aux4; int(1)], [4 = conjure_aux4; int(1)]; int(1..2)])) + Context #2: !or(flatten(1, [[3 = conjure_aux4; int(1)], [4 = conjure_aux4; int(1)]; int(1..2)])) <-> conjure_aux4 = q8_2 + Context #3: [and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])), + !or(flatten(1, [[3 = conjure_aux4; int(1)], [4 = conjure_aux4; int(1)]; int(1..2)])) <-> conjure_aux4 = q8_2; + int(1..2)] + Context #4: and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!or(flatten(1, [[3 = conjure_aux4; int(1)], [4 = conjure_aux4; int(1)]; int(1..2)])) <-> conjure_aux4 = q8_2) + Context #5: { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!or(flatten(1, [[3 = conjure_aux4; int(1)], [4 = conjure_aux4; int(1)]; int(1..2)])) <-> conjure_aux4 = q8_2) + } + Context #6: conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!or(flatten(1, [[3 = conjure_aux4; int(1)], [4 = conjure_aux4; int(1)]; int(1..2)])) <-> conjure_aux4 = q8_2) + } + Context #7: { conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!or(flatten(1, [[3 = conjure_aux4; int(1)], [4 = conjure_aux4; int(1)]; int(1..2)])) <-> conjure_aux4 = q8_2) + } + } + Context #8: { conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!or(flatten(1, [[3 = conjure_aux4; int(1)], [4 = conjure_aux4; int(1)]; int(1..2)])) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + Context #9: [{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!or(flatten(1, [[3 = conjure_aux4; int(1)], [4 = conjure_aux4; int(1)]; int(1..2)])) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]] + Context #10: and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!or(flatten(1, [[3 = conjure_aux4; int(1)], [4 = conjure_aux4; int(1)]; int(1..2)])) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + Context #11: [|x| = |conjure_aux1|, + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!or(flatten(1, [[3 = conjure_aux4; int(1)], [4 = conjure_aux4; int(1)]; int(1..2)])) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]); + int(1..2)] + Context #12: |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!or(flatten(1, [[3 = conjure_aux4; int(1)], [4 = conjure_aux4; int(1)]; int(1..2)])) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + Context #13: { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!or(flatten(1, [[3 = conjure_aux4; int(1)], [4 = conjure_aux4; int(1)]; int(1..2)])) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + Context #14: y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!or(flatten(1, [[3 = conjure_aux4; int(1)], [4 = conjure_aux4; int(1)]; int(1..2)])) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } +Picking the only option: Answer 1: quantifier-shift3: Shifting quantifier inwards + or([3 = conjure_aux4; int(1)]) \/ or([4 = conjure_aux4; int(1)]) +storedChoice: +or(flatten(1, [[3 = conjure_aux4; int(1)], [4 = conjure_aux4; int(1)]; int(1..2)])) 1792302133485940861 +AnsweredRule {qHole_ = 1792302133485940861, qAscendants_ = fromList [-9215156694345218491,-7884159941367425225,-4061787575651201278,-2348548688413524686,-1616656984063374174,1019247903219888070,1202444192825383566,2448039896892401119,2522006493315280277,2872569756943491545,3292387117872397760,5871641527667180654,6531511286127386564,8891172200144465433], aRuleName_ = "quantifier-shift3"} +LF: {"AnsweredRule":{"aRuleName_":"quantifier-shift3","qAscendants_":[-9215156694345218491,-7884159941367425225,-4061787575651201278,-2348548688413524686,-1616656984063374174,1019247903219888070,1202444192825383566,2448039896892401119,2522006493315280277,2872569756943491545,3292387117872397760,5871641527667180654,6531511286127386564,8891172200144465433],"qHole_":1792302133485940861}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!(or([3 = conjure_aux4; int(1)]) \/ or([4 = conjure_aux4; int(1)])) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: or([3 = conjure_aux4; int(1)]) + Context #1: [or([3 = conjure_aux4; int(1)]), or([4 = conjure_aux4; int(1)]); int(1..2)] + Context #2: or([3 = conjure_aux4; int(1)]) \/ or([4 = conjure_aux4; int(1)]) + Context #3: !(or([3 = conjure_aux4; int(1)]) \/ or([4 = conjure_aux4; int(1)])) + Context #4: !(or([3 = conjure_aux4; int(1)]) \/ or([4 = conjure_aux4; int(1)])) <-> conjure_aux4 = q8_2 + Context #5: [and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])), + !(or([3 = conjure_aux4; int(1)]) \/ or([4 = conjure_aux4; int(1)])) <-> conjure_aux4 = q8_2; + int(1..2)] + Context #6: and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!(or([3 = conjure_aux4; int(1)]) \/ or([4 = conjure_aux4; int(1)])) <-> conjure_aux4 = q8_2) + Context #7: { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!(or([3 = conjure_aux4; int(1)]) \/ or([4 = conjure_aux4; int(1)])) <-> conjure_aux4 = q8_2) + } + Context #8: conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!(or([3 = conjure_aux4; int(1)]) \/ or([4 = conjure_aux4; int(1)])) <-> conjure_aux4 = q8_2) + } + Context #9: { conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!(or([3 = conjure_aux4; int(1)]) \/ or([4 = conjure_aux4; int(1)])) <-> conjure_aux4 = q8_2) + } + } + Context #10: { conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!(or([3 = conjure_aux4; int(1)]) \/ or([4 = conjure_aux4; int(1)])) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + Context #11: [{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!(or([3 = conjure_aux4; int(1)]) \/ or([4 = conjure_aux4; int(1)])) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]] + Context #12: and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!(or([3 = conjure_aux4; int(1)]) \/ or([4 = conjure_aux4; int(1)])) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + Context #13: [|x| = |conjure_aux1|, + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!(or([3 = conjure_aux4; int(1)]) \/ or([4 = conjure_aux4; int(1)])) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]); + int(1..2)] + Context #14: |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!(or([3 = conjure_aux4; int(1)]) \/ or([4 = conjure_aux4; int(1)])) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + Context #15: { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!(or([3 = conjure_aux4; int(1)]) \/ or([4 = conjure_aux4; int(1)])) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + Context #16: y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!(or([3 = conjure_aux4; int(1)]) \/ or([4 = conjure_aux4; int(1)])) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } +Picking the only option: Answer 1: matrix-comprehension-singleton: Removing quantifier of a single item + 3 = conjure_aux4 +storedChoice: +or([3 = conjure_aux4; int(1)]) -2238338300082489653 +AnsweredRule {qHole_ = -2238338300082489653, qAscendants_ = fromList [-9135090969161870748,-7040580929681195434,-5844866756595959210,-5200489563969105483,-5135428809631204876,-4567662440315024812,-2637178807861984772,-1043830869774709897,117930584853289771,1197239461988022471,4464393825362555947,5063705836807996732,5078493517063792951,6402729242588877157,6830536617247247401,7925032212346973439], aRuleName_ = "matrix-comprehension-singleton"} +LF: {"AnsweredRule":{"aRuleName_":"matrix-comprehension-singleton","qAscendants_":[-9135090969161870748,-7040580929681195434,-5844866756595959210,-5200489563969105483,-5135428809631204876,-4567662440315024812,-2637178807861984772,-1043830869774709897,117930584853289771,1197239461988022471,4464393825362555947,5063705836807996732,5078493517063792951,6402729242588877157,6830536617247247401,7925032212346973439],"qHole_":-2238338300082489653}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!(3 = conjure_aux4 \/ or([4 = conjure_aux4; int(1)])) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: or([4 = conjure_aux4; int(1)]) + Context #1: [3 = conjure_aux4, or([4 = conjure_aux4; int(1)]); int(1..2)] + Context #2: 3 = conjure_aux4 \/ or([4 = conjure_aux4; int(1)]) + Context #3: !(3 = conjure_aux4 \/ or([4 = conjure_aux4; int(1)])) + Context #4: !(3 = conjure_aux4 \/ or([4 = conjure_aux4; int(1)])) <-> conjure_aux4 = q8_2 + Context #5: [and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])), + !(3 = conjure_aux4 \/ or([4 = conjure_aux4; int(1)])) <-> conjure_aux4 = q8_2; + int(1..2)] + Context #6: and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!(3 = conjure_aux4 \/ or([4 = conjure_aux4; int(1)])) <-> conjure_aux4 = q8_2) + Context #7: { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!(3 = conjure_aux4 \/ or([4 = conjure_aux4; int(1)])) <-> conjure_aux4 = q8_2) + } + Context #8: conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!(3 = conjure_aux4 \/ or([4 = conjure_aux4; int(1)])) <-> conjure_aux4 = q8_2) + } + Context #9: { conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!(3 = conjure_aux4 \/ or([4 = conjure_aux4; int(1)])) <-> conjure_aux4 = q8_2) + } + } + Context #10: { conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!(3 = conjure_aux4 \/ or([4 = conjure_aux4; int(1)])) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + Context #11: [{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!(3 = conjure_aux4 \/ or([4 = conjure_aux4; int(1)])) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]] + Context #12: and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!(3 = conjure_aux4 \/ or([4 = conjure_aux4; int(1)])) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + Context #13: [|x| = |conjure_aux1|, + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!(3 = conjure_aux4 \/ or([4 = conjure_aux4; int(1)])) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]); + int(1..2)] + Context #14: |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!(3 = conjure_aux4 \/ or([4 = conjure_aux4; int(1)])) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + Context #15: { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!(3 = conjure_aux4 \/ or([4 = conjure_aux4; int(1)])) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + Context #16: y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!(3 = conjure_aux4 \/ or([4 = conjure_aux4; int(1)])) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } +Picking the only option: Answer 1: matrix-comprehension-singleton: Removing quantifier of a single item + 4 = conjure_aux4 +storedChoice: +or([4 = conjure_aux4; int(1)]) 6931996324238769216 +AnsweredRule {qHole_ = 6931996324238769216, qAscendants_ = fromList [-8301199506799591941,-7558092101252853604,-6067998700973920226,-5155701249953128914,-4576047313272360415,-4347126985617275804,-2751859814401093547,137469789217709822,144729713112841205,2146657550292868874,3729312864595267230,4118600647582069537,4766806173317946186,4942755527663293565,6086894017411589008,8428538202899570704], aRuleName_ = "matrix-comprehension-singleton"} +LF: {"AnsweredRule":{"aRuleName_":"matrix-comprehension-singleton","qAscendants_":[-8301199506799591941,-7558092101252853604,-6067998700973920226,-5155701249953128914,-4576047313272360415,-4347126985617275804,-2751859814401093547,137469789217709822,144729713112841205,2146657550292868874,3729312864595267230,4118600647582069537,4766806173317946186,4942755527663293565,6086894017411589008,8428538202899570704],"qHole_":6931996324238769216}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: and(flatten(1, + [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) + Context #1: [and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])), + !(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2; + int(1..2)] + Context #2: and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) + Context #3: { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) + } + Context #4: conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) + } + Context #5: { conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) + } + } + Context #6: { conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + Context #7: [{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]] + Context #8: and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + Context #9: [|x| = |conjure_aux1|, + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]); + int(1..2)] + Context #10: |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + Context #11: { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + Context #12: y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } +Picking the only option: Answer 1: quantifier-shift3: Shifting quantifier inwards + and([3 = q8_2 <-> conjure_aux4 = 4; int(1)]) /\ and([4 = q8_2 <-> conjure_aux4 = 3; int(1)]) +storedChoice: +and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) 6498896587051443094 +AnsweredRule {qHole_ = 6498896587051443094, qAscendants_ = fromList [-9122266668816456873,-8763687680398485956,-6768148177044187855,-5775912378426088215,-3542921895788471154,-2263838003336096906,-202295424977994982,851884620329916301,5528267415991175666,6533818616419587005,7566808087161406219,8046934030769361906], aRuleName_ = "quantifier-shift3"} +LF: {"AnsweredRule":{"aRuleName_":"quantifier-shift3","qAscendants_":[-9122266668816456873,-8763687680398485956,-6768148177044187855,-5775912378426088215,-3542921895788471154,-2263838003336096906,-202295424977994982,851884620329916301,5528267415991175666,6533818616419587005,7566808087161406219,8046934030769361906],"qHole_":6498896587051443094}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and([3 = q8_2 <-> conjure_aux4 = 4; int(1)]) /\ and([4 = q8_2 <-> conjure_aux4 = 3; int(1)]) /\ + (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: and([3 = q8_2 <-> conjure_aux4 = 4; int(1)]) + Context #1: [and([3 = q8_2 <-> conjure_aux4 = 4; int(1)]), and([4 = q8_2 <-> conjure_aux4 = 3; int(1)]); int(1..2)] + Context #2: and([3 = q8_2 <-> conjure_aux4 = 4; int(1)]) /\ and([4 = q8_2 <-> conjure_aux4 = 3; int(1)]) + Context #3: [and([3 = q8_2 <-> conjure_aux4 = 4; int(1)]) /\ and([4 = q8_2 <-> conjure_aux4 = 3; int(1)]), + !(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2; + int(1..2)] + Context #4: and([3 = q8_2 <-> conjure_aux4 = 4; int(1)]) /\ and([4 = q8_2 <-> conjure_aux4 = 3; int(1)]) /\ + (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) + Context #5: { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and([3 = q8_2 <-> conjure_aux4 = 4; int(1)]) /\ and([4 = q8_2 <-> conjure_aux4 = 3; int(1)]) /\ + (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) + } + Context #6: conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and([3 = q8_2 <-> conjure_aux4 = 4; int(1)]) /\ and([4 = q8_2 <-> conjure_aux4 = 3; int(1)]) /\ + (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) + } + Context #7: { conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and([3 = q8_2 <-> conjure_aux4 = 4; int(1)]) /\ and([4 = q8_2 <-> conjure_aux4 = 3; int(1)]) /\ + (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) + } + } + Context #8: { conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and([3 = q8_2 <-> conjure_aux4 = 4; int(1)]) /\ and([4 = q8_2 <-> conjure_aux4 = 3; int(1)]) /\ + (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + Context #9: [{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and([3 = q8_2 <-> conjure_aux4 = 4; int(1)]) /\ and([4 = q8_2 <-> conjure_aux4 = 3; int(1)]) /\ + (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]] + Context #10: and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and([3 = q8_2 <-> conjure_aux4 = 4; int(1)]) /\ and([4 = q8_2 <-> conjure_aux4 = 3; int(1)]) /\ + (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + Context #11: [|x| = |conjure_aux1|, + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and([3 = q8_2 <-> conjure_aux4 = 4; int(1)]) /\ and([4 = q8_2 <-> conjure_aux4 = 3; int(1)]) /\ + (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]); + int(1..2)] + Context #12: |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and([3 = q8_2 <-> conjure_aux4 = 4; int(1)]) /\ and([4 = q8_2 <-> conjure_aux4 = 3; int(1)]) /\ + (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + Context #13: { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and([3 = q8_2 <-> conjure_aux4 = 4; int(1)]) /\ and([4 = q8_2 <-> conjure_aux4 = 3; int(1)]) /\ + (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + Context #14: y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and([3 = q8_2 <-> conjure_aux4 = 4; int(1)]) /\ and([4 = q8_2 <-> conjure_aux4 = 3; int(1)]) /\ + (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } +Picking the only option: Answer 1: matrix-comprehension-singleton: Removing quantifier of a single item + 3 = q8_2 <-> conjure_aux4 = 4 +storedChoice: +and([3 = q8_2 <-> conjure_aux4 = 4; int(1)]) 4625414366441981983 +AnsweredRule {qHole_ = 4625414366441981983, qAscendants_ = fromList [-5032104045245797729,-4260367211447941052,-3800321491279460974,-3527728036515378511,-3186771756499085870,-2663126455000061452,-2397177437658285933,-953818733459672679,51316433765895449,382670796215945555,1275044521375561569,2333080611421701721,2485864324914475150,5509053191108998898], aRuleName_ = "matrix-comprehension-singleton"} +LF: {"AnsweredRule":{"aRuleName_":"matrix-comprehension-singleton","qAscendants_":[-5032104045245797729,-4260367211447941052,-3800321491279460974,-3527728036515378511,-3186771756499085870,-2663126455000061452,-2397177437658285933,-953818733459672679,51316433765895449,382670796215945555,1275044521375561569,2333080611421701721,2485864324914475150,5509053191108998898],"qHole_":4625414366441981983}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + (3 = q8_2 <-> conjure_aux4 = 4) /\ and([4 = q8_2 <-> conjure_aux4 = 3; int(1)]) /\ + (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: and([4 = q8_2 <-> conjure_aux4 = 3; int(1)]) + Context #1: [3 = q8_2 <-> conjure_aux4 = 4, and([4 = q8_2 <-> conjure_aux4 = 3; int(1)]); int(1..2)] + Context #2: (3 = q8_2 <-> conjure_aux4 = 4) /\ and([4 = q8_2 <-> conjure_aux4 = 3; int(1)]) + Context #3: [(3 = q8_2 <-> conjure_aux4 = 4) /\ and([4 = q8_2 <-> conjure_aux4 = 3; int(1)]), + !(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2; + int(1..2)] + Context #4: (3 = q8_2 <-> conjure_aux4 = 4) /\ and([4 = q8_2 <-> conjure_aux4 = 3; int(1)]) /\ + (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) + Context #5: { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + (3 = q8_2 <-> conjure_aux4 = 4) /\ and([4 = q8_2 <-> conjure_aux4 = 3; int(1)]) /\ + (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) + } + Context #6: conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + (3 = q8_2 <-> conjure_aux4 = 4) /\ and([4 = q8_2 <-> conjure_aux4 = 3; int(1)]) /\ + (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) + } + Context #7: { conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + (3 = q8_2 <-> conjure_aux4 = 4) /\ and([4 = q8_2 <-> conjure_aux4 = 3; int(1)]) /\ + (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) + } + } + Context #8: { conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + (3 = q8_2 <-> conjure_aux4 = 4) /\ and([4 = q8_2 <-> conjure_aux4 = 3; int(1)]) /\ + (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + Context #9: [{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + (3 = q8_2 <-> conjure_aux4 = 4) /\ and([4 = q8_2 <-> conjure_aux4 = 3; int(1)]) /\ + (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]] + Context #10: and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + (3 = q8_2 <-> conjure_aux4 = 4) /\ and([4 = q8_2 <-> conjure_aux4 = 3; int(1)]) /\ + (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + Context #11: [|x| = |conjure_aux1|, + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + (3 = q8_2 <-> conjure_aux4 = 4) /\ and([4 = q8_2 <-> conjure_aux4 = 3; int(1)]) /\ + (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]); + int(1..2)] + Context #12: |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + (3 = q8_2 <-> conjure_aux4 = 4) /\ and([4 = q8_2 <-> conjure_aux4 = 3; int(1)]) /\ + (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + Context #13: { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + (3 = q8_2 <-> conjure_aux4 = 4) /\ and([4 = q8_2 <-> conjure_aux4 = 3; int(1)]) /\ + (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + Context #14: y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + (3 = q8_2 <-> conjure_aux4 = 4) /\ and([4 = q8_2 <-> conjure_aux4 = 3; int(1)]) /\ + (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } +Picking the only option: Answer 1: matrix-comprehension-singleton: Removing quantifier of a single item + 4 = q8_2 <-> conjure_aux4 = 3 +storedChoice: +and([4 = q8_2 <-> conjure_aux4 = 3; int(1)]) -8650590815054601249 +AnsweredRule {qHole_ = -8650590815054601249, qAscendants_ = fromList [-7526881736718068312,-7405557604309373817,-7201686808491642883,-6330762734028692340,-5804239247306276412,-5043128294307900798,-4578161512601023984,-2463121278901514889,303127519297990446,594877140964359361,1533543948414682137,4243960396898301951,6573830124911821771,7997158881778982126], aRuleName_ = "matrix-comprehension-singleton"} +LF: {"AnsweredRule":{"aRuleName_":"matrix-comprehension-singleton","qAscendants_":[-7526881736718068312,-7405557604309373817,-7201686808491642883,-6330762734028692340,-5804239247306276412,-5043128294307900798,-4578161512601023984,-2463121278901514889,303127519297990446,594877140964359361,1533543948414682137,4243960396898301951,6573830124911821771,7997158881778982126],"qHole_":-8650590815054601249}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ + (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ + (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) + } + Context #1: conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ + (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) + } + Context #2: { conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ + (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) + } + } + Context #3: { conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ + (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + Context #4: [{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ + (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]] + Context #5: and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ + (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + Context #6: [|x| = |conjure_aux1|, + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ + (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]); + int(1..2)] + Context #7: |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ + (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + Context #8: { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ + (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + Context #9: y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ + (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } +Picking the only option: Answer 1: choose-repr-for-locals: Choosing representation for local variable conjure_aux4 + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ + (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) + } +storedChoice: +{ conjure_aux4 +@ find conjure_aux4: int(1..5) + such that + (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ + (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) +} -5523540219623150802 +AnsweredRule {qHole_ = -5523540219623150802, qAscendants_ = fromList [-8941059882607301911,-4338998493244249628,-2962415465773075069,-2259331243426380901,-565469044512126150,-60812526271457966,2469584683440447504,4682955345466050776,5578803032032481190], aRuleName_ = "choose-repr-for-locals"} +LF: {"AnsweredRule":{"aRuleName_":"choose-repr-for-locals","qAscendants_":[-8941059882607301911,-4338998493244249628,-2962415465773075069,-2259331243426380901,-565469044512126150,-60812526271457966,2469584683440447504,4682955345466050776,5578803032032481190],"qHole_":-5523540219623150802}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ + (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ + (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) + } + Context #1: { conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ + (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) + } + } + Context #2: { conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ + (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + Context #3: [{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ + (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]] + Context #4: and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ + (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + Context #5: [|x| = |conjure_aux1|, + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ + (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]); + int(1..2)] + Context #6: |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ + (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + Context #7: { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ + (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + Context #8: y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ + (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } +Picking the only option: Answer 1: bubble-up-LiftVars: Bubbling up auxiliary variables. + { conjure_aux2_2 = conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ + (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) + } +storedChoice: +conjure_aux2_2 = +{ conjure_aux4 +@ find conjure_aux4: int(1..5) + such that + (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ + (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) +} 4682955345466050776 +AnsweredRule {qHole_ = 4682955345466050776, qAscendants_ = fromList [-8941059882607301911,-4338998493244249628,-2962415465773075069,-2259331243426380901,-565469044512126150,-60812526271457966,2469584683440447504,5578803032032481190], aRuleName_ = "bubble-up-LiftVars"} +LF: {"AnsweredRule":{"aRuleName_":"bubble-up-LiftVars","qAscendants_":[-8941059882607301911,-4338998493244249628,-2962415465773075069,-2259331243426380901,-565469044512126150,-60812526271457966,2469584683440447504,5578803032032481190],"qHole_":4682955345466050776}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + { conjure_aux2_2 = conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ + (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: { conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + { conjure_aux2_2 = conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ + (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + Context #1: [{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + { conjure_aux2_2 = conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ + (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]] + Context #2: and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + { conjure_aux2_2 = conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ + (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + Context #3: [|x| = |conjure_aux1|, + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + { conjure_aux2_2 = conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ + (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]); + int(1..2)] + Context #4: |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + { conjure_aux2_2 = conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ + (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + Context #5: { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + { conjure_aux2_2 = conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ + (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + Context #6: y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + { conjure_aux2_2 = conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ + (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } +Picking the only option: Answer 1: bubble-up-LiftVars: Bubbling up auxiliary variables. + { conjure_aux2 in conjure_aux1 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + { conjure_aux2_2 = conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ + (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) + } + } +storedChoice: +{ conjure_aux2 +@ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + { conjure_aux2_2 = conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ + (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) + } +} +in conjure_aux1 -8498631454693468162 +AnsweredRule {qHole_ = -8498631454693468162, qAscendants_ = fromList [-8906484870153215238,-5210480414835359833,-1572320097158340186,7262859821198064716,7664399396112355801,9199488081424848815], aRuleName_ = "bubble-up-LiftVars"} +LF: {"AnsweredRule":{"aRuleName_":"bubble-up-LiftVars","qAscendants_":[-8906484870153215238,-5210480414835359833,-1572320097158340186,7262859821198064716,7664399396112355801,9199488081424848815],"qHole_":-8498631454693468162}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 in conjure_aux1 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + { conjure_aux2_2 = conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ + (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) + } + } | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: q8[1] + Context #1: x_RelationAsMatrix[q8[1]] + Context #2: x_RelationAsMatrix[q8[1], q8[2]] + Context #3: [{ conjure_aux2 in conjure_aux1 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + { conjure_aux2_2 = conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ + (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) + } + } | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]] + Context #4: and([{ conjure_aux2 in conjure_aux1 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + { conjure_aux2_2 = conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ + (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) + } + } | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + Context #5: [|x| = |conjure_aux1|, + and([{ conjure_aux2 in conjure_aux1 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + { conjure_aux2_2 = conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ + (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) + } + } | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]); + int(1..2)] + Context #6: |x| = |conjure_aux1| /\ + and([{ conjure_aux2 in conjure_aux1 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + { conjure_aux2_2 = conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ + (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) + } + } | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + Context #7: { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 in conjure_aux1 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + { conjure_aux2_2 = conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ + (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) + } + } | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + Context #8: y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 in conjure_aux1 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + { conjure_aux2_2 = conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ + (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) + } + } | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } +Picking the only option: Answer 1: tuple-index: Tuple indexing on: q8[1] + q8_1 +storedChoice: +q8[1] 6051865069970393497 +AnsweredRule {qHole_ = 6051865069970393497, qAscendants_ = fromList [-8640702807944529160,-7554917160340714381,-7282620252070677492,-4679672213039578282,-3902820972913913543,-1648680758926951321,-323488035431343639,4558015980602682727], aRuleName_ = "tuple-index"} +LF: {"AnsweredRule":{"aRuleName_":"tuple-index","qAscendants_":[-8640702807944529160,-7554917160340714381,-7282620252070677492,-4679672213039578282,-3902820972913913543,-1648680758926951321,-323488035431343639,4558015980602682727],"qHole_":6051865069970393497}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 in conjure_aux1 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + { conjure_aux2_2 = conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ + (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) + } + } | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8[2]]]) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: q8[2] + Context #1: x_RelationAsMatrix[q8_1, q8[2]] + Context #2: [{ conjure_aux2 in conjure_aux1 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + { conjure_aux2_2 = conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ + (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) + } + } | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8[2]]] + Context #3: and([{ conjure_aux2 in conjure_aux1 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + { conjure_aux2_2 = conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ + (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) + } + } | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8[2]]]) + Context #4: [|x| = |conjure_aux1|, + and([{ conjure_aux2 in conjure_aux1 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + { conjure_aux2_2 = conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ + (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) + } + } | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8[2]]]); + int(1..2)] + Context #5: |x| = |conjure_aux1| /\ + and([{ conjure_aux2 in conjure_aux1 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + { conjure_aux2_2 = conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ + (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) + } + } | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8[2]]]) + Context #6: { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 in conjure_aux1 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + { conjure_aux2_2 = conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ + (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) + } + } | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8[2]]]) + } + Context #7: y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 in conjure_aux1 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + { conjure_aux2_2 = conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ + (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) + } + } | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8[2]]]) + } +Picking the only option: Answer 1: tuple-index: Tuple indexing on: q8[2] + q8_2 +storedChoice: +q8[2] 6051020602090044114 +AnsweredRule {qHole_ = 6051020602090044114, qAscendants_ = fromList [-1657839898828256711,-1442033437105002979,-382389179101208790,2791764908100697416,2932884812988402663,3044000407645637671,4978224969731597410], aRuleName_ = "tuple-index"} +LF: {"AnsweredRule":{"aRuleName_":"tuple-index","qAscendants_":[-1657839898828256711,-1442033437105002979,-382389179101208790,2791764908100697416,2932884812988402663,3044000407645637671,4978224969731597410],"qHole_":6051020602090044114}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 in conjure_aux1 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + { conjure_aux2_2 = conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ + (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) + } + } | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]]) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: [{ conjure_aux2 in conjure_aux1 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + { conjure_aux2_2 = conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ + (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) + } + } | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] + Context #1: and([{ conjure_aux2 in conjure_aux1 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + { conjure_aux2_2 = conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ + (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) + } + } | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]]) + Context #2: [|x| = |conjure_aux1|, + and([{ conjure_aux2 in conjure_aux1 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + { conjure_aux2_2 = conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ + (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) + } + } | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]]); + int(1..2)] + Context #3: |x| = |conjure_aux1| /\ + and([{ conjure_aux2 in conjure_aux1 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + { conjure_aux2_2 = conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ + (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) + } + } | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]]) + Context #4: { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 in conjure_aux1 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + { conjure_aux2_2 = conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ + (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) + } + } | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]]) + } + Context #5: y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 in conjure_aux1 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + { conjure_aux2_2 = conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ + (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) + } + } | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]]) + } +Picking the only option: Answer 1: bubble-up-LiftVars: Bubbling up auxiliary variables through a comprehension. + { [conjure_aux2 in conjure_aux1 | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([{ conjure_aux2_1[q8_1, q8_2] = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } | q8_1 : int(1..5), q8_2 : int(1..5)]), + and([{ conjure_aux2_2[q8_1, q8_2] = conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ + (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) + } | q8_1 : int(1..5), q8_2 : int(1..5)]) + } +storedChoice: +[{ conjure_aux2 in conjure_aux1 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + { conjure_aux2_2 = conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ + (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) + } + } | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] 4632560015221358179 +AnsweredRule {qHole_ = 4632560015221358179, qAscendants_ = fromList [-7796146364068057171,-6981365833241776808,-5029665938164178889,-3928434564447926958,-2893776785872977312], aRuleName_ = "bubble-up-LiftVars"} +LF: {"AnsweredRule":{"aRuleName_":"bubble-up-LiftVars","qAscendants_":[-7796146364068057171,-6981365833241776808,-5029665938164178889,-3928434564447926958,-2893776785872977312],"qHole_":4632560015221358179}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and({ [conjure_aux2 in conjure_aux1 | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([{ conjure_aux2_1[q8_1, q8_2] = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } | q8_1 : int(1..5), q8_2 : int(1..5)]), + and([{ conjure_aux2_2[q8_1, q8_2] = conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ + (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) + } | q8_1 : int(1..5), q8_2 : int(1..5)]) + }) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: { [conjure_aux2 in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([{ conjure_aux2_1[q8_1, q8_2] = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } | q8_1 : int(1..5), q8_2 : int(1..5)]), + and([{ conjure_aux2_2[q8_1, q8_2] = conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ + (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) + } | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + Context #1: and({ [conjure_aux2 in conjure_aux1 | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([{ conjure_aux2_1[q8_1, q8_2] = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } | q8_1 : int(1..5), q8_2 : int(1..5)]), + and([{ conjure_aux2_2[q8_1, q8_2] = conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ + (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) + } | q8_1 : int(1..5), q8_2 : int(1..5)]) + }) + Context #2: [|x| = |conjure_aux1|, + and({ [conjure_aux2 in conjure_aux1 | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([{ conjure_aux2_1[q8_1, q8_2] = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } | q8_1 : int(1..5), q8_2 : int(1..5)]), + and([{ conjure_aux2_2[q8_1, q8_2] = conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ + (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) + } | q8_1 : int(1..5), q8_2 : int(1..5)]) + }); + int(1..2)] + Context #3: |x| = |conjure_aux1| /\ + and({ [conjure_aux2 in conjure_aux1 | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([{ conjure_aux2_1[q8_1, q8_2] = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } | q8_1 : int(1..5), q8_2 : int(1..5)]), + and([{ conjure_aux2_2[q8_1, q8_2] = conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ + (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) + } | q8_1 : int(1..5), q8_2 : int(1..5)]) + }) + Context #4: { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and({ [conjure_aux2 in conjure_aux1 | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([{ conjure_aux2_1[q8_1, q8_2] = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } | q8_1 : int(1..5), q8_2 : int(1..5)]), + and([{ conjure_aux2_2[q8_1, q8_2] = conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ + (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) + } | q8_1 : int(1..5), q8_2 : int(1..5)]) + }) + } + Context #5: y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and({ [conjure_aux2 in conjure_aux1 | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([{ conjure_aux2_1[q8_1, q8_2] = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } | q8_1 : int(1..5), q8_2 : int(1..5)]), + and([{ conjure_aux2_2[q8_1, q8_2] = conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ + (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) + } | q8_1 : int(1..5), q8_2 : int(1..5)]) + }) + } +Picking the only option: Answer 1: choose-repr-for-locals: Choosing representation for local variable conjure_aux2_1 + { [conjure_aux2 in conjure_aux1 | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([{ conjure_aux2_1[q8_1, q8_2] = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } | q8_1 : int(1..5), q8_2 : int(1..5)]), + and([{ conjure_aux2_2[q8_1, q8_2] = conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ + (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) + } | q8_1 : int(1..5), q8_2 : int(1..5)]) + } +storedChoice: +{ [conjure_aux2 in conjure_aux1 | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] +@ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([{ conjure_aux2_1[q8_1, q8_2] = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } | q8_1 : int(1..5), q8_2 : int(1..5)]), + and([{ conjure_aux2_2[q8_1, q8_2] = conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ + (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) + } | q8_1 : int(1..5), q8_2 : int(1..5)]) +} 5183357163976320088 +AnsweredRule {qHole_ = 5183357163976320088, qAscendants_ = fromList [-5465830923914696498,-4063366109563536561,-2043995450352341839,378335084364868291,1311484366701431644], aRuleName_ = "choose-repr-for-locals"} +LF: {"AnsweredRule":{"aRuleName_":"choose-repr-for-locals","qAscendants_":[-5465830923914696498,-4063366109563536561,-2043995450352341839,378335084364868291,1311484366701431644],"qHole_":5183357163976320088}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and({ [conjure_aux2 in conjure_aux1 | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([{ conjure_aux2_1[q8_1, q8_2] = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } | q8_1 : int(1..5), q8_2 : int(1..5)]), + and([{ conjure_aux2_2[q8_1, q8_2] = conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ + (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) + } | q8_1 : int(1..5), q8_2 : int(1..5)]) + }) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: [{ conjure_aux2_1[q8_1, q8_2] = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } | q8_1 : int(1..5), q8_2 : int(1..5)] + Context #1: and([{ conjure_aux2_1[q8_1, q8_2] = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } | q8_1 : int(1..5), q8_2 : int(1..5)]) + Context #2: { [conjure_aux2 in conjure_aux1 | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([{ conjure_aux2_1[q8_1, q8_2] = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } | q8_1 : int(1..5), q8_2 : int(1..5)]), + and([{ conjure_aux2_2[q8_1, q8_2] = conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ + (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) + } | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + Context #3: and({ [conjure_aux2 in conjure_aux1 | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([{ conjure_aux2_1[q8_1, q8_2] = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } | q8_1 : int(1..5), q8_2 : int(1..5)]), + and([{ conjure_aux2_2[q8_1, q8_2] = conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ + (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) + } | q8_1 : int(1..5), q8_2 : int(1..5)]) + }) + Context #4: [|x| = |conjure_aux1|, + and({ [conjure_aux2 in conjure_aux1 | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([{ conjure_aux2_1[q8_1, q8_2] = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } | q8_1 : int(1..5), q8_2 : int(1..5)]), + and([{ conjure_aux2_2[q8_1, q8_2] = conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ + (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) + } | q8_1 : int(1..5), q8_2 : int(1..5)]) + }); + int(1..2)] + Context #5: |x| = |conjure_aux1| /\ + and({ [conjure_aux2 in conjure_aux1 | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([{ conjure_aux2_1[q8_1, q8_2] = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } | q8_1 : int(1..5), q8_2 : int(1..5)]), + and([{ conjure_aux2_2[q8_1, q8_2] = conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ + (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) + } | q8_1 : int(1..5), q8_2 : int(1..5)]) + }) + Context #6: { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and({ [conjure_aux2 in conjure_aux1 | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([{ conjure_aux2_1[q8_1, q8_2] = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } | q8_1 : int(1..5), q8_2 : int(1..5)]), + and([{ conjure_aux2_2[q8_1, q8_2] = conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ + (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) + } | q8_1 : int(1..5), q8_2 : int(1..5)]) + }) + } + Context #7: y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and({ [conjure_aux2 in conjure_aux1 | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([{ conjure_aux2_1[q8_1, q8_2] = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } | q8_1 : int(1..5), q8_2 : int(1..5)]), + and([{ conjure_aux2_2[q8_1, q8_2] = conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ + (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) + } | q8_1 : int(1..5), q8_2 : int(1..5)]) + }) + } +Picking the only option: Answer 1: bubble-up-LiftVars: Bubbling up auxiliary variables through a comprehension. + { [conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)] + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } +storedChoice: +[{ conjure_aux2_1[q8_1, q8_2] = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } | q8_1 : int(1..5), q8_2 : int(1..5)] -2066028230956466058 +AnsweredRule {qHole_ = -2066028230956466058, qAscendants_ = fromList [-8778252753919104373,-5465830923914696498,-4063366109563536561,-2043995450352341839,378335084364868291,1311484366701431644,5183357163976320088], aRuleName_ = "bubble-up-LiftVars"} +LF: {"AnsweredRule":{"aRuleName_":"bubble-up-LiftVars","qAscendants_":[-8778252753919104373,-5465830923914696498,-4063366109563536561,-2043995450352341839,378335084364868291,1311484366701431644,5183357163976320088],"qHole_":-2066028230956466058}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and({ [conjure_aux2 in conjure_aux1 | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and({ [conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)] + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }), + and([{ conjure_aux2_2[q8_1, q8_2] = conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ + (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) + } | q8_1 : int(1..5), q8_2 : int(1..5)]) + }) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: { [conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)] + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + Context #1: and({ [conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)] + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }) + Context #2: { [conjure_aux2 in conjure_aux1 | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and({ [conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)] + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }), + and([{ conjure_aux2_2[q8_1, q8_2] = conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ + (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) + } | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + Context #3: and({ [conjure_aux2 in conjure_aux1 | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and({ [conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)] + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }), + and([{ conjure_aux2_2[q8_1, q8_2] = conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ + (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) + } | q8_1 : int(1..5), q8_2 : int(1..5)]) + }) + Context #4: [|x| = |conjure_aux1|, + and({ [conjure_aux2 in conjure_aux1 | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and({ [conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)] + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }), + and([{ conjure_aux2_2[q8_1, q8_2] = conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ + (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) + } | q8_1 : int(1..5), q8_2 : int(1..5)]) + }); + int(1..2)] + Context #5: |x| = |conjure_aux1| /\ + and({ [conjure_aux2 in conjure_aux1 | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and({ [conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)] + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }), + and([{ conjure_aux2_2[q8_1, q8_2] = conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ + (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) + } | q8_1 : int(1..5), q8_2 : int(1..5)]) + }) + Context #6: { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and({ [conjure_aux2 in conjure_aux1 | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and({ [conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)] + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }), + and([{ conjure_aux2_2[q8_1, q8_2] = conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ + (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) + } | q8_1 : int(1..5), q8_2 : int(1..5)]) + }) + } + Context #7: y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and({ [conjure_aux2 in conjure_aux1 | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and({ [conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)] + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }), + and([{ conjure_aux2_2[q8_1, q8_2] = conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ + (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) + } | q8_1 : int(1..5), q8_2 : int(1..5)]) + }) + } +Picking the only option: Answer 1: choose-repr-for-locals: Choosing representation for local variable conjure_aux3 + { [conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)] + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } +storedChoice: +{ [conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)] +@ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) +} -2683400798428888576 +AnsweredRule {qHole_ = -2683400798428888576, qAscendants_ = fromList [-7630765854898757381,-5152289056460337438,-4378029185233493510,-2193789157648306228,-780484605375639491,4611290103392876019,8129436120778745950], aRuleName_ = "choose-repr-for-locals"} +LF: {"AnsweredRule":{"aRuleName_":"choose-repr-for-locals","qAscendants_":[-7630765854898757381,-5152289056460337438,-4378029185233493510,-2193789157648306228,-780484605375639491,4611290103392876019,8129436120778745950],"qHole_":-2683400798428888576}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and({ [conjure_aux2 in conjure_aux1 | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and({ [conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)] + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }), + and([{ conjure_aux2_2[q8_1, q8_2] = conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ + (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) + } | q8_1 : int(1..5), q8_2 : int(1..5)]) + }) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: and({ [conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] + | q8_1 : int(1..5), q8_2 : int(1..5)] + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }) + Context #1: { [conjure_aux2 in conjure_aux1 | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and({ [conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)] + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }), + and([{ conjure_aux2_2[q8_1, q8_2] = conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ + (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) + } | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + Context #2: and({ [conjure_aux2 in conjure_aux1 | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and({ [conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)] + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }), + and([{ conjure_aux2_2[q8_1, q8_2] = conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ + (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) + } | q8_1 : int(1..5), q8_2 : int(1..5)]) + }) + Context #3: [|x| = |conjure_aux1|, + and({ [conjure_aux2 in conjure_aux1 | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and({ [conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)] + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }), + and([{ conjure_aux2_2[q8_1, q8_2] = conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ + (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) + } | q8_1 : int(1..5), q8_2 : int(1..5)]) + }); + int(1..2)] + Context #4: |x| = |conjure_aux1| /\ + and({ [conjure_aux2 in conjure_aux1 | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and({ [conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)] + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }), + and([{ conjure_aux2_2[q8_1, q8_2] = conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ + (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) + } | q8_1 : int(1..5), q8_2 : int(1..5)]) + }) + Context #5: { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and({ [conjure_aux2 in conjure_aux1 | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and({ [conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)] + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }), + and([{ conjure_aux2_2[q8_1, q8_2] = conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ + (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) + } | q8_1 : int(1..5), q8_2 : int(1..5)]) + }) + } + Context #6: y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and({ [conjure_aux2 in conjure_aux1 | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and({ [conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)] + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }), + and([{ conjure_aux2_2[q8_1, q8_2] = conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ + (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) + } | q8_1 : int(1..5), q8_2 : int(1..5)]) + }) + } +Picking the only option: Answer 1: bubble-up-LiftVars: Bubbling up auxiliary variables. + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } +storedChoice: +and({ [conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)] + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }) -7630765854898757381 +AnsweredRule {qHole_ = -7630765854898757381, qAscendants_ = fromList [-5152289056460337438,-4378029185233493510,-2193789157648306228,-780484605375639491,4611290103392876019,8129436120778745950], aRuleName_ = "bubble-up-LiftVars"} +LF: {"AnsweredRule":{"aRuleName_":"bubble-up-LiftVars","qAscendants_":[-5152289056460337438,-4378029185233493510,-2193789157648306228,-780484605375639491,4611290103392876019,8129436120778745950],"qHole_":-7630765854898757381}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and({ [conjure_aux2 in conjure_aux1 | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + and([{ conjure_aux2_2[q8_1, q8_2] = conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ + (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) + } | q8_1 : int(1..5), q8_2 : int(1..5)]) + }) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: [{ conjure_aux2_2[q8_1, q8_2] = conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ + (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) + } | q8_1 : int(1..5), q8_2 : int(1..5)] + Context #1: and([{ conjure_aux2_2[q8_1, q8_2] = conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ + (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) + } | q8_1 : int(1..5), q8_2 : int(1..5)]) + Context #2: { [conjure_aux2 in conjure_aux1 | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + and([{ conjure_aux2_2[q8_1, q8_2] = conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ + (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) + } | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + Context #3: and({ [conjure_aux2 in conjure_aux1 | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + and([{ conjure_aux2_2[q8_1, q8_2] = conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ + (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) + } | q8_1 : int(1..5), q8_2 : int(1..5)]) + }) + Context #4: [|x| = |conjure_aux1|, + and({ [conjure_aux2 in conjure_aux1 | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + and([{ conjure_aux2_2[q8_1, q8_2] = conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ + (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) + } | q8_1 : int(1..5), q8_2 : int(1..5)]) + }); + int(1..2)] + Context #5: |x| = |conjure_aux1| /\ + and({ [conjure_aux2 in conjure_aux1 | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + and([{ conjure_aux2_2[q8_1, q8_2] = conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ + (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) + } | q8_1 : int(1..5), q8_2 : int(1..5)]) + }) + Context #6: { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and({ [conjure_aux2 in conjure_aux1 | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + and([{ conjure_aux2_2[q8_1, q8_2] = conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ + (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) + } | q8_1 : int(1..5), q8_2 : int(1..5)]) + }) + } + Context #7: y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and({ [conjure_aux2 in conjure_aux1 | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + and([{ conjure_aux2_2[q8_1, q8_2] = conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ + (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) + } | q8_1 : int(1..5), q8_2 : int(1..5)]) + }) + } +Picking the only option: Answer 1: bubble-up-LiftVars: Bubbling up auxiliary variables through a comprehension. + { [conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)] + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } +storedChoice: +[{ conjure_aux2_2[q8_1, q8_2] = conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ + (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) + } | q8_1 : int(1..5), q8_2 : int(1..5)] 4586595665260781575 +AnsweredRule {qHole_ = 4586595665260781575, qAscendants_ = fromList [-5189262863924670079,-4576870578376860616,-3657040581488238581,667350004362937900,5588145911994567168,7042957946885141470,7965291691177128164], aRuleName_ = "bubble-up-LiftVars"} +LF: {"AnsweredRule":{"aRuleName_":"bubble-up-LiftVars","qAscendants_":[-5189262863924670079,-4576870578376860616,-3657040581488238581,667350004362937900,5588145911994567168,7042957946885141470,7965291691177128164],"qHole_":4586595665260781575}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and({ [conjure_aux2 in conjure_aux1 | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + and({ [conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)] + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }) + }) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: { [conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)] + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + Context #1: and({ [conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)] + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }) + Context #2: { [conjure_aux2 in conjure_aux1 | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + and({ [conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)] + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }) + } + Context #3: and({ [conjure_aux2 in conjure_aux1 | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + and({ [conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)] + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }) + }) + Context #4: [|x| = |conjure_aux1|, + and({ [conjure_aux2 in conjure_aux1 | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + and({ [conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)] + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }) + }); + int(1..2)] + Context #5: |x| = |conjure_aux1| /\ + and({ [conjure_aux2 in conjure_aux1 | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + and({ [conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)] + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }) + }) + Context #6: { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and({ [conjure_aux2 in conjure_aux1 | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + and({ [conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)] + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }) + }) + } + Context #7: y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and({ [conjure_aux2 in conjure_aux1 | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + and({ [conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)] + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }) + }) + } +Picking the only option: Answer 1: choose-repr-for-locals: Choosing representation for local variable conjure_aux4 + { [conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)] + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } +storedChoice: +{ [conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)] +@ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) +} -1434005429531325525 +AnsweredRule {qHole_ = -1434005429531325525, qAscendants_ = fromList [-7860778431127922714,-4340120710083553155,-3276746255609047616,-2418004144569851915,-329464522225361142,8566682329173394842,8971959176905079767], aRuleName_ = "choose-repr-for-locals"} +LF: {"AnsweredRule":{"aRuleName_":"choose-repr-for-locals","qAscendants_":[-7860778431127922714,-4340120710083553155,-3276746255609047616,-2418004144569851915,-329464522225361142,8566682329173394842,8971959176905079767],"qHole_":-1434005429531325525}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and({ [conjure_aux2 in conjure_aux1 | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + and({ [conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)] + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }) + }) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: and({ [conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] + | q8_1 : int(1..5), q8_2 : int(1..5)] + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }) + Context #1: { [conjure_aux2 in conjure_aux1 | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + and({ [conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)] + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }) + } + Context #2: and({ [conjure_aux2 in conjure_aux1 | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + and({ [conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)] + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }) + }) + Context #3: [|x| = |conjure_aux1|, + and({ [conjure_aux2 in conjure_aux1 | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + and({ [conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)] + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }) + }); + int(1..2)] + Context #4: |x| = |conjure_aux1| /\ + and({ [conjure_aux2 in conjure_aux1 | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + and({ [conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)] + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }) + }) + Context #5: { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and({ [conjure_aux2 in conjure_aux1 | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + and({ [conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)] + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }) + }) + } + Context #6: y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and({ [conjure_aux2 in conjure_aux1 | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + and({ [conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)] + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }) + }) + } +Picking the only option: Answer 1: bubble-up-LiftVars: Bubbling up auxiliary variables. + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } +storedChoice: +and({ [conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)] + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }) -329464522225361142 +AnsweredRule {qHole_ = -329464522225361142, qAscendants_ = fromList [-7860778431127922714,-4340120710083553155,-3276746255609047616,-2418004144569851915,8566682329173394842,8971959176905079767], aRuleName_ = "bubble-up-LiftVars"} +LF: {"AnsweredRule":{"aRuleName_":"bubble-up-LiftVars","qAscendants_":[-7860778431127922714,-4340120710083553155,-3276746255609047616,-2418004144569851915,8566682329173394842,8971959176905079767],"qHole_":-329464522225361142}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and({ [conjure_aux2 in conjure_aux1 | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + }) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: conjure_aux2 in conjure_aux1 + Context #1: [conjure_aux2 in conjure_aux1 | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] + Context #2: { [conjure_aux2 in conjure_aux1 | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + } + Context #3: and({ [conjure_aux2 in conjure_aux1 | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + }) + Context #4: [|x| = |conjure_aux1|, + and({ [conjure_aux2 in conjure_aux1 | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + }); + int(1..2)] + Context #5: |x| = |conjure_aux1| /\ + and({ [conjure_aux2 in conjure_aux1 | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + }) + Context #6: { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and({ [conjure_aux2 in conjure_aux1 | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + }) + } + Context #7: y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and({ [conjure_aux2 in conjure_aux1 | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + }) + } +Picking the only option: Answer 1: relation-in: relation membership to existential quantification + or([q27 = conjure_aux2 | q27 <- toSet(conjure_aux1)]) +storedChoice: +conjure_aux2 in conjure_aux1 7266634060293924720 +AnsweredRule {qHole_ = 7266634060293924720, qAscendants_ = fromList [-7266324578771459181,-6713121642540228318,-5826297241095436731,-5526349309453330732,1756707357159771390,2149626909839152329,4938058042264599181], aRuleName_ = "relation-in"} +LF: {"AnsweredRule":{"aRuleName_":"relation-in","qAscendants_":[-7266324578771459181,-6713121642540228318,-5826297241095436731,-5526349309453330732,1756707357159771390,2149626909839152329,4938058042264599181],"qHole_":7266634060293924720}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and({ [or([q27 = conjure_aux2 | q27 <- toSet(conjure_aux1)]) | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + }) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: [q27 = conjure_aux2 | q27 <- toSet(conjure_aux1)] + Context #1: or([q27 = conjure_aux2 | q27 <- toSet(conjure_aux1)]) + Context #2: [or([q27 = conjure_aux2 | q27 <- toSet(conjure_aux1)]) + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] + Context #3: { [or([q27 = conjure_aux2 | q27 <- toSet(conjure_aux1)]) + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + } + Context #4: and({ [or([q27 = conjure_aux2 | q27 <- toSet(conjure_aux1)]) + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + }) + Context #5: [|x| = |conjure_aux1|, + and({ [or([q27 = conjure_aux2 | q27 <- toSet(conjure_aux1)]) | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + }); + int(1..2)] + Context #6: |x| = |conjure_aux1| /\ + and({ [or([q27 = conjure_aux2 | q27 <- toSet(conjure_aux1)]) | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + }) + Context #7: { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and({ [or([q27 = conjure_aux2 | q27 <- toSet(conjure_aux1)]) | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + }) + } + Context #8: y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and({ [or([q27 = conjure_aux2 | q27 <- toSet(conjure_aux1)]) | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + }) + } +Picking the only option: Answer 1: relation-map_in_expr{RelationAsMatrix}: Vertical rule for map_in_expr for relation domains, RelationAsMatrix representation. + [(q28[1], q28[2]) = conjure_aux2 | q28 : (int(1..5), int(1..5)), conjure_aux1_RelationAsMatrix[q28[1], q28[2]]] +storedChoice: +[q27 = conjure_aux2 | q27 <- toSet(conjure_aux1)] -3470261408387399930 +AnsweredRule {qHole_ = -3470261408387399930, qAscendants_ = fromList [-8536113027950480792,-7330204231396072871,-4786623393387445427,-4223003553667075844,4116516722814445548,4281838781863596501,6175095517354461663,6559035824535384582], aRuleName_ = "relation-map_in_expr{RelationAsMatrix}"} +LF: {"AnsweredRule":{"aRuleName_":"relation-map_in_expr{RelationAsMatrix}","qAscendants_":[-8536113027950480792,-7330204231396072871,-4786623393387445427,-4223003553667075844,4116516722814445548,4281838781863596501,6175095517354461663,6559035824535384582],"qHole_":-3470261408387399930}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and({ [or([(q28[1], q28[2]) = conjure_aux2 | q28 : (int(1..5), int(1..5)), conjure_aux1_RelationAsMatrix[q28[1], q28[2]]]) + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + }) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: [(q28[1], q28[2]) = conjure_aux2 + | q28 : (int(1..5), int(1..5)), conjure_aux1_RelationAsMatrix[q28[1], q28[2]]] + Context #1: or([(q28[1], q28[2]) = conjure_aux2 | q28 : (int(1..5), int(1..5)), conjure_aux1_RelationAsMatrix[q28[1], q28[2]]]) + Context #2: [or([(q28[1], q28[2]) = conjure_aux2 | q28 : (int(1..5), int(1..5)), conjure_aux1_RelationAsMatrix[q28[1], q28[2]]]) + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] + Context #3: { [or([(q28[1], q28[2]) = conjure_aux2 | q28 : (int(1..5), int(1..5)), conjure_aux1_RelationAsMatrix[q28[1], q28[2]]]) + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + } + Context #4: and({ [or([(q28[1], q28[2]) = conjure_aux2 + | q28 : (int(1..5), int(1..5)), conjure_aux1_RelationAsMatrix[q28[1], q28[2]]]) + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + }) + Context #5: [|x| = |conjure_aux1|, + and({ [or([(q28[1], q28[2]) = conjure_aux2 | q28 : (int(1..5), int(1..5)), conjure_aux1_RelationAsMatrix[q28[1], q28[2]]]) + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + }); + int(1..2)] + Context #6: |x| = |conjure_aux1| /\ + and({ [or([(q28[1], q28[2]) = conjure_aux2 | q28 : (int(1..5), int(1..5)), conjure_aux1_RelationAsMatrix[q28[1], q28[2]]]) + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + }) + Context #7: { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and({ [or([(q28[1], q28[2]) = conjure_aux2 | q28 : (int(1..5), int(1..5)), conjure_aux1_RelationAsMatrix[q28[1], q28[2]]]) + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + }) + } + Context #8: y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and({ [or([(q28[1], q28[2]) = conjure_aux2 | q28 : (int(1..5), int(1..5)), conjure_aux1_RelationAsMatrix[q28[1], q28[2]]]) + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + }) + } +Picking the only option: Answer 1: choose-repr-for-comprehension: Choosing representation for quantified variable q28 (with type: (int, + int)) + [(q28[1], q28[2]) = conjure_aux2 | q28_1 : int(1..5), q28_2 : int(1..5), conjure_aux1_RelationAsMatrix[q28[1], q28[2]]] +storedChoice: +[(q28[1], q28[2]) = conjure_aux2 | q28 : (int(1..5), int(1..5)), conjure_aux1_RelationAsMatrix[q28[1], q28[2]]] 4348009411125732066 +AnsweredRule {qHole_ = 4348009411125732066, qAscendants_ = fromList [-6592612559904363413,-6472871177545322172,-6453293890463000807,-2235240472846537890,3259852529283772574,4455209103885624492,6352194885377054835,8420829954716127361], aRuleName_ = "choose-repr-for-comprehension"} +LF: {"AnsweredRule":{"aRuleName_":"choose-repr-for-comprehension","qAscendants_":[-6592612559904363413,-6472871177545322172,-6453293890463000807,-2235240472846537890,3259852529283772574,4455209103885624492,6352194885377054835,8420829954716127361],"qHole_":4348009411125732066}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and({ [or([(q28[1], q28[2]) = conjure_aux2 | q28_1 : int(1..5), q28_2 : int(1..5), conjure_aux1_RelationAsMatrix[q28[1], q28[2]]]) + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + }) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: (q28[1], q28[2]) = conjure_aux2 + Context #1: [(q28[1], q28[2]) = conjure_aux2 | q28_1 : int(1..5), q28_2 : int(1..5), conjure_aux1_RelationAsMatrix[q28[1], q28[2]]] + Context #2: or([(q28[1], q28[2]) = conjure_aux2 + | q28_1 : int(1..5), q28_2 : int(1..5), conjure_aux1_RelationAsMatrix[q28[1], q28[2]]]) + Context #3: [or([(q28[1], q28[2]) = conjure_aux2 + | q28_1 : int(1..5), q28_2 : int(1..5), conjure_aux1_RelationAsMatrix[q28[1], q28[2]]]) + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] + Context #4: { [or([(q28[1], q28[2]) = conjure_aux2 + | q28_1 : int(1..5), q28_2 : int(1..5), conjure_aux1_RelationAsMatrix[q28[1], q28[2]]]) + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + } + Context #5: and({ [or([(q28[1], q28[2]) = conjure_aux2 + | q28_1 : int(1..5), q28_2 : int(1..5), conjure_aux1_RelationAsMatrix[q28[1], q28[2]]]) + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + }) + Context #6: [|x| = |conjure_aux1|, + and({ [or([(q28[1], q28[2]) = conjure_aux2 | q28_1 : int(1..5), q28_2 : int(1..5), conjure_aux1_RelationAsMatrix[q28[1], q28[2]]]) + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + }); + int(1..2)] + Context #7: |x| = |conjure_aux1| /\ + and({ [or([(q28[1], q28[2]) = conjure_aux2 | q28_1 : int(1..5), q28_2 : int(1..5), conjure_aux1_RelationAsMatrix[q28[1], q28[2]]]) + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + }) + Context #8: { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and({ [or([(q28[1], q28[2]) = conjure_aux2 | q28_1 : int(1..5), q28_2 : int(1..5), conjure_aux1_RelationAsMatrix[q28[1], q28[2]]]) + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + }) + } + Context #9: y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and({ [or([(q28[1], q28[2]) = conjure_aux2 | q28_1 : int(1..5), q28_2 : int(1..5), conjure_aux1_RelationAsMatrix[q28[1], q28[2]]]) + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + }) + } +Picking the only option: Answer 1: tuple-eq: Horizontal rule for tuple equality + q28[1] = conjure_aux2_1 /\ q28[2] = conjure_aux2_2 +storedChoice: +(q28[1], q28[2]) = conjure_aux2 -4124337097652933443 +AnsweredRule {qHole_ = -4124337097652933443, qAscendants_ = fromList [-6634517003356473421,-4157154907530130258,-932339049260687039,4056979115757602560,5419805607560390341,5700344114265930133,8275228852675492835,8651388538213571462,8952456806918978808], aRuleName_ = "tuple-eq"} +LF: {"AnsweredRule":{"aRuleName_":"tuple-eq","qAscendants_":[-6634517003356473421,-4157154907530130258,-932339049260687039,4056979115757602560,5419805607560390341,5700344114265930133,8275228852675492835,8651388538213571462,8952456806918978808],"qHole_":-4124337097652933443}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and({ [or([q28[1] = conjure_aux2_1 /\ q28[2] = conjure_aux2_2 + | q28_1 : int(1..5), q28_2 : int(1..5), conjure_aux1_RelationAsMatrix[q28[1], q28[2]]]) + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + }) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: q28[1] + Context #1: q28[1] = conjure_aux2_1 + Context #2: [q28[1] = conjure_aux2_1, q28[2] = conjure_aux2_2; int(1..2)] + Context #3: q28[1] = conjure_aux2_1 /\ q28[2] = conjure_aux2_2 + Context #4: [q28[1] = conjure_aux2_1 /\ q28[2] = conjure_aux2_2 + | q28_1 : int(1..5), q28_2 : int(1..5), conjure_aux1_RelationAsMatrix[q28[1], q28[2]]] + Context #5: or([q28[1] = conjure_aux2_1 /\ q28[2] = conjure_aux2_2 + | q28_1 : int(1..5), q28_2 : int(1..5), conjure_aux1_RelationAsMatrix[q28[1], q28[2]]]) + Context #6: [or([q28[1] = conjure_aux2_1 /\ q28[2] = conjure_aux2_2 + | q28_1 : int(1..5), q28_2 : int(1..5), conjure_aux1_RelationAsMatrix[q28[1], q28[2]]]) + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] + Context #7: { [or([q28[1] = conjure_aux2_1 /\ q28[2] = conjure_aux2_2 + | q28_1 : int(1..5), q28_2 : int(1..5), conjure_aux1_RelationAsMatrix[q28[1], q28[2]]]) + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + } + Context #8: and({ [or([q28[1] = conjure_aux2_1 /\ q28[2] = conjure_aux2_2 + | q28_1 : int(1..5), q28_2 : int(1..5), conjure_aux1_RelationAsMatrix[q28[1], q28[2]]]) + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + }) + Context #9: [|x| = |conjure_aux1|, + and({ [or([q28[1] = conjure_aux2_1 /\ q28[2] = conjure_aux2_2 + | q28_1 : int(1..5), q28_2 : int(1..5), conjure_aux1_RelationAsMatrix[q28[1], q28[2]]]) + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + }); + int(1..2)] + Context #10: |x| = |conjure_aux1| /\ + and({ [or([q28[1] = conjure_aux2_1 /\ q28[2] = conjure_aux2_2 + | q28_1 : int(1..5), q28_2 : int(1..5), conjure_aux1_RelationAsMatrix[q28[1], q28[2]]]) + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + }) + Context #11: { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and({ [or([q28[1] = conjure_aux2_1 /\ q28[2] = conjure_aux2_2 + | q28_1 : int(1..5), q28_2 : int(1..5), conjure_aux1_RelationAsMatrix[q28[1], q28[2]]]) + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + }) + } + Context #12: y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and({ [or([q28[1] = conjure_aux2_1 /\ q28[2] = conjure_aux2_2 + | q28_1 : int(1..5), q28_2 : int(1..5), conjure_aux1_RelationAsMatrix[q28[1], q28[2]]]) + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + }) + } +Picking the only option: Answer 1: tuple-index: Tuple indexing on: q28[1] + q28_1 +storedChoice: +q28[1] 8787010607011614834 +AnsweredRule {qHole_ = 8787010607011614834, qAscendants_ = fromList [-8956326597613561383,-6532059540256123763,-6109385609926416455,-3678896154897738560,-419523469793567323,-407169135612228618,2034669589965157861,4997220444967745554,6148375269450574671,6513082934840114429,8747477145020099131,8922317001415918920], aRuleName_ = "tuple-index"} +LF: {"AnsweredRule":{"aRuleName_":"tuple-index","qAscendants_":[-8956326597613561383,-6532059540256123763,-6109385609926416455,-3678896154897738560,-419523469793567323,-407169135612228618,2034669589965157861,4997220444967745554,6148375269450574671,6513082934840114429,8747477145020099131,8922317001415918920],"qHole_":8787010607011614834}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and({ [or([q28_1 = conjure_aux2_1 /\ q28[2] = conjure_aux2_2 + | q28_1 : int(1..5), q28_2 : int(1..5), conjure_aux1_RelationAsMatrix[q28[1], q28[2]]]) + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + }) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: q28[2] + Context #1: q28[2] = conjure_aux2_2 + Context #2: [q28_1 = conjure_aux2_1, q28[2] = conjure_aux2_2; int(1..2)] + Context #3: q28_1 = conjure_aux2_1 /\ q28[2] = conjure_aux2_2 + Context #4: [q28_1 = conjure_aux2_1 /\ q28[2] = conjure_aux2_2 + | q28_1 : int(1..5), q28_2 : int(1..5), conjure_aux1_RelationAsMatrix[q28[1], q28[2]]] + Context #5: or([q28_1 = conjure_aux2_1 /\ q28[2] = conjure_aux2_2 + | q28_1 : int(1..5), q28_2 : int(1..5), conjure_aux1_RelationAsMatrix[q28[1], q28[2]]]) + Context #6: [or([q28_1 = conjure_aux2_1 /\ q28[2] = conjure_aux2_2 + | q28_1 : int(1..5), q28_2 : int(1..5), conjure_aux1_RelationAsMatrix[q28[1], q28[2]]]) + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] + Context #7: { [or([q28_1 = conjure_aux2_1 /\ q28[2] = conjure_aux2_2 + | q28_1 : int(1..5), q28_2 : int(1..5), conjure_aux1_RelationAsMatrix[q28[1], q28[2]]]) + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + } + Context #8: and({ [or([q28_1 = conjure_aux2_1 /\ q28[2] = conjure_aux2_2 + | q28_1 : int(1..5), q28_2 : int(1..5), conjure_aux1_RelationAsMatrix[q28[1], q28[2]]]) + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + }) + Context #9: [|x| = |conjure_aux1|, + and({ [or([q28_1 = conjure_aux2_1 /\ q28[2] = conjure_aux2_2 + | q28_1 : int(1..5), q28_2 : int(1..5), conjure_aux1_RelationAsMatrix[q28[1], q28[2]]]) + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + }); + int(1..2)] + Context #10: |x| = |conjure_aux1| /\ + and({ [or([q28_1 = conjure_aux2_1 /\ q28[2] = conjure_aux2_2 + | q28_1 : int(1..5), q28_2 : int(1..5), conjure_aux1_RelationAsMatrix[q28[1], q28[2]]]) + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + }) + Context #11: { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and({ [or([q28_1 = conjure_aux2_1 /\ q28[2] = conjure_aux2_2 + | q28_1 : int(1..5), q28_2 : int(1..5), conjure_aux1_RelationAsMatrix[q28[1], q28[2]]]) + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + }) + } + Context #12: y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and({ [or([q28_1 = conjure_aux2_1 /\ q28[2] = conjure_aux2_2 + | q28_1 : int(1..5), q28_2 : int(1..5), conjure_aux1_RelationAsMatrix[q28[1], q28[2]]]) + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + }) + } +Picking the only option: Answer 1: tuple-index: Tuple indexing on: q28[2] + q28_2 +storedChoice: +q28[2] 8786166143426335913 +AnsweredRule {qHole_ = 8786166143426335913, qAscendants_ = fromList [-7531325615783388500,-6124769537006831453,-2577262930135244673,-590286472771932315,-83534367005148570,715122028962684739,1709615173437954783,5607005680561137835,7486385006046341809,7705725891024727552,8323234866884020390,8780789924434106151], aRuleName_ = "tuple-index"} +LF: {"AnsweredRule":{"aRuleName_":"tuple-index","qAscendants_":[-7531325615783388500,-6124769537006831453,-2577262930135244673,-590286472771932315,-83534367005148570,715122028962684739,1709615173437954783,5607005680561137835,7486385006046341809,7705725891024727552,8323234866884020390,8780789924434106151],"qHole_":8786166143426335913}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and({ [or([q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2 + | q28_1 : int(1..5), q28_2 : int(1..5), conjure_aux1_RelationAsMatrix[q28[1], q28[2]]]) + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + }) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: q28[1] + Context #1: conjure_aux1_RelationAsMatrix[q28[1]] + Context #2: conjure_aux1_RelationAsMatrix[q28[1], q28[2]] + Context #3: [q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2 + | q28_1 : int(1..5), q28_2 : int(1..5), conjure_aux1_RelationAsMatrix[q28[1], q28[2]]] + Context #4: or([q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2 + | q28_1 : int(1..5), q28_2 : int(1..5), conjure_aux1_RelationAsMatrix[q28[1], q28[2]]]) + Context #5: [or([q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2 + | q28_1 : int(1..5), q28_2 : int(1..5), conjure_aux1_RelationAsMatrix[q28[1], q28[2]]]) + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] + Context #6: { [or([q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2 + | q28_1 : int(1..5), q28_2 : int(1..5), conjure_aux1_RelationAsMatrix[q28[1], q28[2]]]) + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + } + Context #7: and({ [or([q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2 + | q28_1 : int(1..5), q28_2 : int(1..5), conjure_aux1_RelationAsMatrix[q28[1], q28[2]]]) + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + }) + Context #8: [|x| = |conjure_aux1|, + and({ [or([q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2 + | q28_1 : int(1..5), q28_2 : int(1..5), conjure_aux1_RelationAsMatrix[q28[1], q28[2]]]) + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + }); + int(1..2)] + Context #9: |x| = |conjure_aux1| /\ + and({ [or([q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2 + | q28_1 : int(1..5), q28_2 : int(1..5), conjure_aux1_RelationAsMatrix[q28[1], q28[2]]]) + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + }) + Context #10: { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and({ [or([q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2 + | q28_1 : int(1..5), q28_2 : int(1..5), conjure_aux1_RelationAsMatrix[q28[1], q28[2]]]) + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + }) + } + Context #11: y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and({ [or([q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2 + | q28_1 : int(1..5), q28_2 : int(1..5), conjure_aux1_RelationAsMatrix[q28[1], q28[2]]]) + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + }) + } +Picking the only option: Answer 1: tuple-index: Tuple indexing on: q28[1] + q28_1 +storedChoice: +q28[1] 8787010607011614834 +AnsweredRule {qHole_ = 8787010607011614834, qAscendants_ = fromList [-6233761776568569553,-6207878452900388515,-3381866216268371578,-560496032557153780,-80631966925160875,1067854355870431415,1108013619790213016,4161317878060049142,4647826867886404607,5228020545282852391,8646369751965333728], aRuleName_ = "tuple-index"} +LF: {"AnsweredRule":{"aRuleName_":"tuple-index","qAscendants_":[-6233761776568569553,-6207878452900388515,-3381866216268371578,-560496032557153780,-80631966925160875,1067854355870431415,1108013619790213016,4161317878060049142,4647826867886404607,5228020545282852391,8646369751965333728],"qHole_":8787010607011614834}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and({ [or([q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2 + | q28_1 : int(1..5), q28_2 : int(1..5), conjure_aux1_RelationAsMatrix[q28_1, q28[2]]]) + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + }) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: q28[2] + Context #1: conjure_aux1_RelationAsMatrix[q28_1, q28[2]] + Context #2: [q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2 + | q28_1 : int(1..5), q28_2 : int(1..5), conjure_aux1_RelationAsMatrix[q28_1, q28[2]]] + Context #3: or([q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2 + | q28_1 : int(1..5), q28_2 : int(1..5), conjure_aux1_RelationAsMatrix[q28_1, q28[2]]]) + Context #4: [or([q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2 + | q28_1 : int(1..5), q28_2 : int(1..5), conjure_aux1_RelationAsMatrix[q28_1, q28[2]]]) + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] + Context #5: { [or([q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2 + | q28_1 : int(1..5), q28_2 : int(1..5), conjure_aux1_RelationAsMatrix[q28_1, q28[2]]]) + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + } + Context #6: and({ [or([q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2 + | q28_1 : int(1..5), q28_2 : int(1..5), conjure_aux1_RelationAsMatrix[q28_1, q28[2]]]) + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + }) + Context #7: [|x| = |conjure_aux1|, + and({ [or([q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2 + | q28_1 : int(1..5), q28_2 : int(1..5), conjure_aux1_RelationAsMatrix[q28_1, q28[2]]]) + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + }); + int(1..2)] + Context #8: |x| = |conjure_aux1| /\ + and({ [or([q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2 + | q28_1 : int(1..5), q28_2 : int(1..5), conjure_aux1_RelationAsMatrix[q28_1, q28[2]]]) + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + }) + Context #9: { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and({ [or([q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2 + | q28_1 : int(1..5), q28_2 : int(1..5), conjure_aux1_RelationAsMatrix[q28_1, q28[2]]]) + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + }) + } + Context #10: y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and({ [or([q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2 + | q28_1 : int(1..5), q28_2 : int(1..5), conjure_aux1_RelationAsMatrix[q28_1, q28[2]]]) + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + }) + } +Picking the only option: Answer 1: tuple-index: Tuple indexing on: q28[2] + q28_2 +storedChoice: +q28[2] 8786166143426335913 +AnsweredRule {qHole_ = 8786166143426335913, qAscendants_ = fromList [-8932183048783716768,-6021176910053718006,-1484921959836170832,-1243263695470418987,-307241860641088143,5123914162100475129,6415834318102058907,6682610423178443283,7959220516069049554,8895625464985590456], aRuleName_ = "tuple-index"} +LF: {"AnsweredRule":{"aRuleName_":"tuple-index","qAscendants_":[-8932183048783716768,-6021176910053718006,-1484921959836170832,-1243263695470418987,-307241860641088143,5123914162100475129,6415834318102058907,6682610423178443283,7959220516069049554,8895625464985590456],"qHole_":8786166143426335913}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and({ [or([q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2 + | q28_1 : int(1..5), q28_2 : int(1..5), conjure_aux1_RelationAsMatrix[q28_1, q28_2]]) + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + }) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: [q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2 + | q28_1 : int(1..5), q28_2 : int(1..5), conjure_aux1_RelationAsMatrix[q28_1, q28_2]] + Context #1: or([q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2 + | q28_1 : int(1..5), q28_2 : int(1..5), conjure_aux1_RelationAsMatrix[q28_1, q28_2]]) + Context #2: [or([q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2 + | q28_1 : int(1..5), q28_2 : int(1..5), conjure_aux1_RelationAsMatrix[q28_1, q28_2]]) + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] + Context #3: { [or([q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2 + | q28_1 : int(1..5), q28_2 : int(1..5), conjure_aux1_RelationAsMatrix[q28_1, q28_2]]) + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + } + Context #4: and({ [or([q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2 + | q28_1 : int(1..5), q28_2 : int(1..5), conjure_aux1_RelationAsMatrix[q28_1, q28_2]]) + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + }) + Context #5: [|x| = |conjure_aux1|, + and({ [or([q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2 + | q28_1 : int(1..5), q28_2 : int(1..5), conjure_aux1_RelationAsMatrix[q28_1, q28_2]]) + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + }); + int(1..2)] + Context #6: |x| = |conjure_aux1| /\ + and({ [or([q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2 + | q28_1 : int(1..5), q28_2 : int(1..5), conjure_aux1_RelationAsMatrix[q28_1, q28_2]]) + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + }) + Context #7: { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and({ [or([q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2 + | q28_1 : int(1..5), q28_2 : int(1..5), conjure_aux1_RelationAsMatrix[q28_1, q28_2]]) + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + }) + } + Context #8: y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and({ [or([q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2 + | q28_1 : int(1..5), q28_2 : int(1..5), conjure_aux1_RelationAsMatrix[q28_1, q28_2]]) + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + }) + } +Picking the only option: Answer 1: inline-conditions: Inlining conditions, inside or + [conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)] +storedChoice: +[q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2 + | q28_1 : int(1..5), q28_2 : int(1..5), conjure_aux1_RelationAsMatrix[q28_1, q28_2]] -9107354217279316955 +AnsweredRule {qHole_ = -9107354217279316955, qAscendants_ = fromList [-7614046741660552896,-7556360939789777851,-6910364700408604777,-6183630476596424374,-2673910102480230275,7059218223957164648,8407785490318688805,8504193122766115214], aRuleName_ = "inline-conditions"} +LF: {"AnsweredRule":{"aRuleName_":"inline-conditions","qAscendants_":[-7614046741660552896,-7556360939789777851,-6910364700408604777,-6183630476596424374,-2673910102480230275,7059218223957164648,8407785490318688805,8504193122766115214],"qHole_":-9107354217279316955}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and({ [or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + }) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: and({ [or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ + (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + }) + Context #1: [|x| = |conjure_aux1|, + and({ [or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + }); + int(1..2)] + Context #2: |x| = |conjure_aux1| /\ + and({ [or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + }) + Context #3: { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and({ [or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + }) + } + Context #4: y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and({ [or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + }) + } +Picking the only option: Answer 1: bubble-up-LiftVars: Bubbling up auxiliary variables. + { and([or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]]) + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + } +storedChoice: +and({ [or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + }) 7825224301270217826 +AnsweredRule {qHole_ = 7825224301270217826, qAscendants_ = fromList [-7337214924393354854,-6793331199204698657,4098536301578040545,4694401685199555588], aRuleName_ = "bubble-up-LiftVars"} +LF: {"AnsweredRule":{"aRuleName_":"bubble-up-LiftVars","qAscendants_":[-7337214924393354854,-6793331199204698657,4098536301578040545,4694401685199555588],"qHole_":7825224301270217826}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + { and([or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]]) + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + } + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: [or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ + (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] + Context #1: and([or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]]) + Context #2: { and([or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]]) + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + } + Context #3: [|x| = |conjure_aux1|, + { and([or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]]) + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + }; int(1..2)] + Context #4: |x| = |conjure_aux1| /\ + { and([or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]]) + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + } + Context #5: { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + { and([or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]]) + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + } + } + Context #6: y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + { and([or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]]) + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + } + } +Picking the only option: Answer 1: inline-conditions: Inlining conditions, inside and + [x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)] +storedChoice: +[or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] -7818394351581759390 +AnsweredRule {qHole_ = -7818394351581759390, qAscendants_ = fromList [-8854367752148363141,868987242372315934,1952008385480716564,2094581585082781447,3197112935473569797,5197989222011368608], aRuleName_ = "inline-conditions"} +LF: {"AnsweredRule":{"aRuleName_":"inline-conditions","qAscendants_":[-8854367752148363141,868987242372315934,1952008385480716564,2094581585082781447,3197112935473569797,5197989222011368608],"qHole_":-7818394351581759390}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + { and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + } + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: [|x| = |conjure_aux1|, + { and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + }; int(1..2)] + Context #1: |x| = |conjure_aux1| /\ + { and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + } + Context #2: { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + { and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + } + } + Context #3: y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + { and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + } + } +Picking the only option: Answer 1: bubble-up-LiftVars: Bubbling up auxiliary variables. + { [|x| = |conjure_aux1|, + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]); + int(1..2)] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + } +storedChoice: +[|x| = |conjure_aux1|, + { and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + }; int(1..2)] 8700659888572119213 +AnsweredRule {qHole_ = 8700659888572119213, qAscendants_ = fromList [1085907639859271742,5213477129051060331,8301951387372896488], aRuleName_ = "bubble-up-LiftVars"} +LF: {"AnsweredRule":{"aRuleName_":"bubble-up-LiftVars","qAscendants_":[1085907639859271742,5213477129051060331,8301951387372896488],"qHole_":8700659888572119213}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + and({ [|x| = |conjure_aux1|, + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]); + int(1..2)] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + }) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: |x| + Context #1: |x| = |conjure_aux1| + Context #2: [|x| = |conjure_aux1|, + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]); + int(1..2)] + Context #3: { [|x| = |conjure_aux1|, + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]); + int(1..2)] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + } + Context #4: and({ [|x| = |conjure_aux1|, + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]); + int(1..2)] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + }) + Context #5: { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + and({ [|x| = |conjure_aux1|, + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]); + int(1..2)] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + }) + } + Context #6: y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + and({ [|x| = |conjure_aux1|, + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]); + int(1..2)] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + }) + } +Picking the only option: Answer 1: relation-cardinality: Relation cardinality + |toSet(x)| +storedChoice: +|x| -1852370716973049233 +AnsweredRule {qHole_ = -1852370716973049233, qAscendants_ = fromList [-8274899275771564111,-7189265364834618222,-4195293662753593531,-2250203036499850017,4837893138970417558,5156053544824672407], aRuleName_ = "relation-cardinality"} +LF: {"AnsweredRule":{"aRuleName_":"relation-cardinality","qAscendants_":[-8274899275771564111,-7189265364834618222,-4195293662753593531,-2250203036499850017,4837893138970417558,5156053544824672407],"qHole_":-1852370716973049233}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + and({ [|toSet(x)| = |conjure_aux1|, + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]); + int(1..2)] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + }) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: |toSet(x)| + Context #1: |toSet(x)| = |conjure_aux1| + Context #2: [|toSet(x)| = |conjure_aux1|, + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]); + int(1..2)] + Context #3: { [|toSet(x)| = |conjure_aux1|, + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]); + int(1..2)] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + } + Context #4: and({ [|toSet(x)| = |conjure_aux1|, + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]); + int(1..2)] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + }) + Context #5: { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + and({ [|toSet(x)| = |conjure_aux1|, + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]); + int(1..2)] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + }) + } + Context #6: y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + and({ [|toSet(x)| = |conjure_aux1|, + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]); + int(1..2)] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + }) + } +Picking the only option: Answer 1: set-card: Horizontal rule for set cardinality. + sum([1 | q29 <- toSet(x)]) +storedChoice: +|toSet(x)| 1897988597909520616 +AnsweredRule {qHole_ = 1897988597909520616, qAscendants_ = fromList [-6188688663705288789,-5846429895491118400,361855989135376679,6530150935582701688,7219968226893579546,7779309324238844246], aRuleName_ = "set-card"} +LF: {"AnsweredRule":{"aRuleName_":"set-card","qAscendants_":[-6188688663705288789,-5846429895491118400,361855989135376679,6530150935582701688,7219968226893579546,7779309324238844246],"qHole_":1897988597909520616}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + and({ [sum([1 | q29 <- toSet(x)]) = |conjure_aux1|, + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]); + int(1..2)] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + }) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: [1 | q29 <- toSet(x)] + Context #1: sum([1 | q29 <- toSet(x)]) + Context #2: sum([1 | q29 <- toSet(x)]) = |conjure_aux1| + Context #3: [sum([1 | q29 <- toSet(x)]) = |conjure_aux1|, + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]); + int(1..2)] + Context #4: { [sum([1 | q29 <- toSet(x)]) = |conjure_aux1|, + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]); + int(1..2)] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + } + Context #5: and({ [sum([1 | q29 <- toSet(x)]) = |conjure_aux1|, + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]); + int(1..2)] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + }) + Context #6: { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + and({ [sum([1 | q29 <- toSet(x)]) = |conjure_aux1|, + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]); + int(1..2)] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + }) + } + Context #7: y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + and({ [sum([1 | q29 <- toSet(x)]) = |conjure_aux1|, + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]); + int(1..2)] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + }) + } +Picking the only option: Answer 1: relation-map_in_expr{RelationAsMatrix}: Vertical rule for map_in_expr for relation domains, RelationAsMatrix representation. + [1 | q30 : (int(1..5), int(1..5)), x_RelationAsMatrix[q30[1], q30[2]]] +storedChoice: +[1 | q29 <- toSet(x)] 7483192753320191769 +AnsweredRule {qHole_ = 7483192753320191769, qAscendants_ = fromList [-7918094600437589284,-6091097458145320110,-4725927117271772380,-3818842550960350061,-801403655548510881,4177802111281067004,8691639764190092042], aRuleName_ = "relation-map_in_expr{RelationAsMatrix}"} +LF: {"AnsweredRule":{"aRuleName_":"relation-map_in_expr{RelationAsMatrix}","qAscendants_":[-7918094600437589284,-6091097458145320110,-4725927117271772380,-3818842550960350061,-801403655548510881,4177802111281067004,8691639764190092042],"qHole_":7483192753320191769}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + and({ [sum([1 | q30 : (int(1..5), int(1..5)), x_RelationAsMatrix[q30[1], q30[2]]]) = |conjure_aux1|, + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]); + int(1..2)] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + }) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: [1 | q30 : (int(1..5), int(1..5)), x_RelationAsMatrix[q30[1], q30[2]]] + Context #1: sum([1 | q30 : (int(1..5), int(1..5)), x_RelationAsMatrix[q30[1], q30[2]]]) + Context #2: sum([1 | q30 : (int(1..5), int(1..5)), x_RelationAsMatrix[q30[1], q30[2]]]) = |conjure_aux1| + Context #3: [sum([1 | q30 : (int(1..5), int(1..5)), x_RelationAsMatrix[q30[1], q30[2]]]) = |conjure_aux1|, + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]); + int(1..2)] + Context #4: { [sum([1 | q30 : (int(1..5), int(1..5)), x_RelationAsMatrix[q30[1], q30[2]]]) = |conjure_aux1|, + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]); + int(1..2)] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + } + Context #5: and({ [sum([1 | q30 : (int(1..5), int(1..5)), x_RelationAsMatrix[q30[1], q30[2]]]) = |conjure_aux1|, + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]); + int(1..2)] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + }) + Context #6: { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + and({ [sum([1 | q30 : (int(1..5), int(1..5)), x_RelationAsMatrix[q30[1], q30[2]]]) = |conjure_aux1|, + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]); + int(1..2)] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + }) + } + Context #7: y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + and({ [sum([1 | q30 : (int(1..5), int(1..5)), x_RelationAsMatrix[q30[1], q30[2]]]) = |conjure_aux1|, + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]); + int(1..2)] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + }) + } +Picking the only option: Answer 1: choose-repr-for-comprehension: Choosing representation for quantified variable q30 (with type: (int, + int)) + [1 | q30_1 : int(1..5), q30_2 : int(1..5), x_RelationAsMatrix[q30[1], q30[2]]] +storedChoice: +[1 | q30 : (int(1..5), int(1..5)), x_RelationAsMatrix[q30[1], q30[2]]] -2219318056453463832 +AnsweredRule {qHole_ = -2219318056453463832, qAscendants_ = fromList [-7631595452381029825,-6332648069028765836,-5599362277318624933,-1170492770147107149,188905738781826972,1046361987104095667,9181513732839926293], aRuleName_ = "choose-repr-for-comprehension"} +LF: {"AnsweredRule":{"aRuleName_":"choose-repr-for-comprehension","qAscendants_":[-7631595452381029825,-6332648069028765836,-5599362277318624933,-1170492770147107149,188905738781826972,1046361987104095667,9181513732839926293],"qHole_":-2219318056453463832}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + and({ [sum([1 | q30_1 : int(1..5), q30_2 : int(1..5), x_RelationAsMatrix[q30[1], q30[2]]]) = |conjure_aux1|, + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]); + int(1..2)] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + }) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: q30[1] + Context #1: x_RelationAsMatrix[q30[1]] + Context #2: x_RelationAsMatrix[q30[1], q30[2]] + Context #3: [1 | q30_1 : int(1..5), q30_2 : int(1..5), x_RelationAsMatrix[q30[1], q30[2]]] + Context #4: sum([1 | q30_1 : int(1..5), q30_2 : int(1..5), x_RelationAsMatrix[q30[1], q30[2]]]) + Context #5: sum([1 | q30_1 : int(1..5), q30_2 : int(1..5), x_RelationAsMatrix[q30[1], q30[2]]]) = |conjure_aux1| + Context #6: [sum([1 | q30_1 : int(1..5), q30_2 : int(1..5), x_RelationAsMatrix[q30[1], q30[2]]]) = |conjure_aux1|, + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]); + int(1..2)] + Context #7: { [sum([1 | q30_1 : int(1..5), q30_2 : int(1..5), x_RelationAsMatrix[q30[1], q30[2]]]) = |conjure_aux1|, + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]); + int(1..2)] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + } + Context #8: and({ [sum([1 | q30_1 : int(1..5), q30_2 : int(1..5), x_RelationAsMatrix[q30[1], q30[2]]]) = |conjure_aux1|, + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]); + int(1..2)] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + }) + Context #9: { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + and({ [sum([1 | q30_1 : int(1..5), q30_2 : int(1..5), x_RelationAsMatrix[q30[1], q30[2]]]) = |conjure_aux1|, + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]); + int(1..2)] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + }) + } + Context #10: y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + and({ [sum([1 | q30_1 : int(1..5), q30_2 : int(1..5), x_RelationAsMatrix[q30[1], q30[2]]]) = |conjure_aux1|, + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]); + int(1..2)] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + }) + } +Picking the only option: Answer 1: tuple-index: Tuple indexing on: q30[1] + q30_1 +storedChoice: +q30[1] 8985411351629801837 +AnsweredRule {qHole_ = 8985411351629801837, qAscendants_ = fromList [-7287907811082918289,-3433749237930268197,-1514549063082826885,-254808116082235497,1395102958002486929,3724900484480857440,3763839719817425200,3764103551892886579,7098469255683427931,8809290278576126972], aRuleName_ = "tuple-index"} +LF: {"AnsweredRule":{"aRuleName_":"tuple-index","qAscendants_":[-7287907811082918289,-3433749237930268197,-1514549063082826885,-254808116082235497,1395102958002486929,3724900484480857440,3763839719817425200,3764103551892886579,7098469255683427931,8809290278576126972],"qHole_":8985411351629801837}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + and({ [sum([1 | q30_1 : int(1..5), q30_2 : int(1..5), x_RelationAsMatrix[q30_1, q30[2]]]) = |conjure_aux1|, + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]); + int(1..2)] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + }) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: q30[2] + Context #1: x_RelationAsMatrix[q30_1, q30[2]] + Context #2: [1 | q30_1 : int(1..5), q30_2 : int(1..5), x_RelationAsMatrix[q30_1, q30[2]]] + Context #3: sum([1 | q30_1 : int(1..5), q30_2 : int(1..5), x_RelationAsMatrix[q30_1, q30[2]]]) + Context #4: sum([1 | q30_1 : int(1..5), q30_2 : int(1..5), x_RelationAsMatrix[q30_1, q30[2]]]) = |conjure_aux1| + Context #5: [sum([1 | q30_1 : int(1..5), q30_2 : int(1..5), x_RelationAsMatrix[q30_1, q30[2]]]) = |conjure_aux1|, + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]); + int(1..2)] + Context #6: { [sum([1 | q30_1 : int(1..5), q30_2 : int(1..5), x_RelationAsMatrix[q30_1, q30[2]]]) = |conjure_aux1|, + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]); + int(1..2)] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + } + Context #7: and({ [sum([1 | q30_1 : int(1..5), q30_2 : int(1..5), x_RelationAsMatrix[q30_1, q30[2]]]) = |conjure_aux1|, + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]); + int(1..2)] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + }) + Context #8: { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + and({ [sum([1 | q30_1 : int(1..5), q30_2 : int(1..5), x_RelationAsMatrix[q30_1, q30[2]]]) = |conjure_aux1|, + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]); + int(1..2)] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + }) + } + Context #9: y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + and({ [sum([1 | q30_1 : int(1..5), q30_2 : int(1..5), x_RelationAsMatrix[q30_1, q30[2]]]) = |conjure_aux1|, + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]); + int(1..2)] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + }) + } +Picking the only option: Answer 1: tuple-index: Tuple indexing on: q30[2] + q30_2 +storedChoice: +q30[2] 8986255815215080758 +AnsweredRule {qHole_ = 8986255815215080758, qAscendants_ = fromList [-1904605123138931514,-1605383351683875510,-1500814072571245463,-1159370656118278861,-345152881798089093,3653718321561964858,5560045049720260591,6001294353827372355,7845034033468093823], aRuleName_ = "tuple-index"} +LF: {"AnsweredRule":{"aRuleName_":"tuple-index","qAscendants_":[-1904605123138931514,-1605383351683875510,-1500814072571245463,-1159370656118278861,-345152881798089093,3653718321561964858,5560045049720260591,6001294353827372355,7845034033468093823],"qHole_":8986255815215080758}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + and({ [sum([1 | q30_1 : int(1..5), q30_2 : int(1..5), x_RelationAsMatrix[q30_1, q30_2]]) = |conjure_aux1|, + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]); + int(1..2)] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + }) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: [1 | q30_1 : int(1..5), q30_2 : int(1..5), x_RelationAsMatrix[q30_1, q30_2]] + Context #1: sum([1 | q30_1 : int(1..5), q30_2 : int(1..5), x_RelationAsMatrix[q30_1, q30_2]]) + Context #2: sum([1 | q30_1 : int(1..5), q30_2 : int(1..5), x_RelationAsMatrix[q30_1, q30_2]]) = |conjure_aux1| + Context #3: [sum([1 | q30_1 : int(1..5), q30_2 : int(1..5), x_RelationAsMatrix[q30_1, q30_2]]) = |conjure_aux1|, + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]); + int(1..2)] + Context #4: { [sum([1 | q30_1 : int(1..5), q30_2 : int(1..5), x_RelationAsMatrix[q30_1, q30_2]]) = |conjure_aux1|, + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]); + int(1..2)] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + } + Context #5: and({ [sum([1 | q30_1 : int(1..5), q30_2 : int(1..5), x_RelationAsMatrix[q30_1, q30_2]]) = |conjure_aux1|, + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]); + int(1..2)] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + }) + Context #6: { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + and({ [sum([1 | q30_1 : int(1..5), q30_2 : int(1..5), x_RelationAsMatrix[q30_1, q30_2]]) = |conjure_aux1|, + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]); + int(1..2)] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + }) + } + Context #7: y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + and({ [sum([1 | q30_1 : int(1..5), q30_2 : int(1..5), x_RelationAsMatrix[q30_1, q30_2]]) = |conjure_aux1|, + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]); + int(1..2)] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + }) + } +Picking the only option: Answer 1: inline-conditions: Inlining conditions, inside sum + [toInt(x_RelationAsMatrix[q30_1, q30_2]) * catchUndef(1, 0) | q30_1 : int(1..5), q30_2 : int(1..5)] +storedChoice: +[1 | q30_1 : int(1..5), q30_2 : int(1..5), x_RelationAsMatrix[q30_1, q30_2]] 6730778895089912004 +AnsweredRule {qHole_ = 6730778895089912004, qAscendants_ = fromList [-5543455485138138697,-1367499344277324489,-577770218778700729,3965135726409895025,4154476703970574900,4424005630299656964,8591791291160167043], aRuleName_ = "inline-conditions"} +LF: {"AnsweredRule":{"aRuleName_":"inline-conditions","qAscendants_":[-5543455485138138697,-1367499344277324489,-577770218778700729,3965135726409895025,4154476703970574900,4424005630299656964,8591791291160167043],"qHole_":6730778895089912004}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + and({ [sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) * catchUndef(1, 0) | q30_1 : int(1..5), q30_2 : int(1..5)]) = |conjure_aux1|, + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]); + int(1..2)] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + }) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: catchUndef(1, 0) + Context #1: [toInt(x_RelationAsMatrix[q30_1, q30_2]), catchUndef(1, 0); int(1..2)] + Context #2: toInt(x_RelationAsMatrix[q30_1, q30_2]) * catchUndef(1, 0) + Context #3: [toInt(x_RelationAsMatrix[q30_1, q30_2]) * catchUndef(1, 0) | q30_1 : int(1..5), q30_2 : int(1..5)] + Context #4: sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) * catchUndef(1, 0) | q30_1 : int(1..5), q30_2 : int(1..5)]) + Context #5: sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) * catchUndef(1, 0) | q30_1 : int(1..5), q30_2 : int(1..5)]) = |conjure_aux1| + Context #6: [sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) * catchUndef(1, 0) | q30_1 : int(1..5), q30_2 : int(1..5)]) = + |conjure_aux1|, + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]); + int(1..2)] + Context #7: { [sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) * catchUndef(1, 0) | q30_1 : int(1..5), q30_2 : int(1..5)]) = + |conjure_aux1|, + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]); + int(1..2)] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + } + Context #8: and({ [sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) * catchUndef(1, 0) | q30_1 : int(1..5), q30_2 : int(1..5)]) = + |conjure_aux1|, + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]); + int(1..2)] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + }) + Context #9: { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + and({ [sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) * catchUndef(1, 0) | q30_1 : int(1..5), q30_2 : int(1..5)]) = |conjure_aux1|, + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]); + int(1..2)] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + }) + } + Context #10: y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + and({ [sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) * catchUndef(1, 0) | q30_1 : int(1..5), q30_2 : int(1..5)]) = |conjure_aux1|, + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]); + int(1..2)] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + }) + } +Picking the only option: Answer 1: full-evaluate: Full evaluator + 1 +storedChoice: +catchUndef(1, 0) -4103543015608659681 +AnsweredRule {qHole_ = -4103543015608659681, qAscendants_ = fromList [-6246651641675555191,-4991494778996523170,-4841212563091249093,-3913142375130629094,-3482484897580979170,-192545505272530247,4617164660703414243,7663465281870587155,7888233777833351600,8484251082711739255], aRuleName_ = "full-evaluate"} +LF: {"AnsweredRule":{"aRuleName_":"full-evaluate","qAscendants_":[-6246651641675555191,-4991494778996523170,-4841212563091249093,-3913142375130629094,-3482484897580979170,-192545505272530247,4617164660703414243,7663465281870587155,7888233777833351600,8484251082711739255],"qHole_":-4103543015608659681}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + and({ [sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) * 1 | q30_1 : int(1..5), q30_2 : int(1..5)]) = |conjure_aux1|, + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]); + int(1..2)] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + }) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: toInt(x_RelationAsMatrix[q30_1, q30_2]) * 1 + Context #1: [toInt(x_RelationAsMatrix[q30_1, q30_2]) * 1 | q30_1 : int(1..5), q30_2 : int(1..5)] + Context #2: sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) * 1 | q30_1 : int(1..5), q30_2 : int(1..5)]) + Context #3: sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) * 1 | q30_1 : int(1..5), q30_2 : int(1..5)]) = |conjure_aux1| + Context #4: [sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) * 1 | q30_1 : int(1..5), q30_2 : int(1..5)]) = |conjure_aux1|, + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]); + int(1..2)] + Context #5: { [sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) * 1 | q30_1 : int(1..5), q30_2 : int(1..5)]) = |conjure_aux1|, + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]); + int(1..2)] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + } + Context #6: and({ [sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) * 1 | q30_1 : int(1..5), q30_2 : int(1..5)]) = |conjure_aux1|, + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]); + int(1..2)] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + }) + Context #7: { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + and({ [sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) * 1 | q30_1 : int(1..5), q30_2 : int(1..5)]) = |conjure_aux1|, + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]); + int(1..2)] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + }) + } + Context #8: y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + and({ [sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) * 1 | q30_1 : int(1..5), q30_2 : int(1..5)]) = |conjure_aux1|, + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]); + int(1..2)] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + }) + } +Picking the only option: Answer 1: partial-evaluate: Partial evaluator + product([toInt(x_RelationAsMatrix[q30_1, q30_2]); int(1)]) +storedChoice: +toInt(x_RelationAsMatrix[q30_1, q30_2]) * 1 -1687514346990485250 +AnsweredRule {qHole_ = -1687514346990485250, qAscendants_ = fromList [-8383279591293107624,-5870374077749082103,-5035592936147091491,-3450507034164856240,-3171744958437112094,-148321104615195040,923428228047877070,2221664695150773241], aRuleName_ = "partial-evaluate"} +LF: {"AnsweredRule":{"aRuleName_":"partial-evaluate","qAscendants_":[-8383279591293107624,-5870374077749082103,-5035592936147091491,-3450507034164856240,-3171744958437112094,-148321104615195040,923428228047877070,2221664695150773241],"qHole_":-1687514346990485250}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + and({ [sum([product([toInt(x_RelationAsMatrix[q30_1, q30_2]); int(1)]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = |conjure_aux1|, + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]); + int(1..2)] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + }) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: product([toInt(x_RelationAsMatrix[q30_1, q30_2]); int(1)]) + Context #1: [product([toInt(x_RelationAsMatrix[q30_1, q30_2]); int(1)]) | q30_1 : int(1..5), q30_2 : int(1..5)] + Context #2: sum([product([toInt(x_RelationAsMatrix[q30_1, q30_2]); int(1)]) | q30_1 : int(1..5), q30_2 : int(1..5)]) + Context #3: sum([product([toInt(x_RelationAsMatrix[q30_1, q30_2]); int(1)]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = |conjure_aux1| + Context #4: [sum([product([toInt(x_RelationAsMatrix[q30_1, q30_2]); int(1)]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = + |conjure_aux1|, + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]); + int(1..2)] + Context #5: { [sum([product([toInt(x_RelationAsMatrix[q30_1, q30_2]); int(1)]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = + |conjure_aux1|, + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]); + int(1..2)] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + } + Context #6: and({ [sum([product([toInt(x_RelationAsMatrix[q30_1, q30_2]); int(1)]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = + |conjure_aux1|, + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]); + int(1..2)] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + }) + Context #7: { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + and({ [sum([product([toInt(x_RelationAsMatrix[q30_1, q30_2]); int(1)]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = |conjure_aux1|, + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]); + int(1..2)] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + }) + } + Context #8: y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + and({ [sum([product([toInt(x_RelationAsMatrix[q30_1, q30_2]); int(1)]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = |conjure_aux1|, + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]); + int(1..2)] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + }) + } +Picking the only option: Answer 1: matrix-comprehension-singleton: Removing quantifier of a single item + toInt(x_RelationAsMatrix[q30_1, q30_2]) +storedChoice: +product([toInt(x_RelationAsMatrix[q30_1, q30_2]); int(1)]) -601225972055529548 +AnsweredRule {qHole_ = -601225972055529548, qAscendants_ = fromList [-7799870564036439127,-7432780384698737696,-6354763341195320334,-5508479272970515476,-2004497734168533005,1354218247559476283,3284517275149475981,4357080134642246606], aRuleName_ = "matrix-comprehension-singleton"} +LF: {"AnsweredRule":{"aRuleName_":"matrix-comprehension-singleton","qAscendants_":[-7799870564036439127,-7432780384698737696,-6354763341195320334,-5508479272970515476,-2004497734168533005,1354218247559476283,3284517275149475981,4357080134642246606],"qHole_":-601225972055529548}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + and({ [sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = |conjure_aux1|, + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]); + int(1..2)] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + }) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: |conjure_aux1| + Context #1: sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = |conjure_aux1| + Context #2: [sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = |conjure_aux1|, + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]); + int(1..2)] + Context #3: { [sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = |conjure_aux1|, + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]); + int(1..2)] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + } + Context #4: and({ [sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = |conjure_aux1|, + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]); + int(1..2)] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + }) + Context #5: { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + and({ [sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = |conjure_aux1|, + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]); + int(1..2)] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + }) + } + Context #6: y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + and({ [sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = |conjure_aux1|, + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]); + int(1..2)] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + }) + } +Picking the only option: Answer 1: relation-cardinality: Relation cardinality + |toSet(conjure_aux1)| +storedChoice: +|conjure_aux1| 547691173299348338 +AnsweredRule {qHole_ = 547691173299348338, qAscendants_ = fromList [-7326096647933004975,-3638343112521383479,-2681179249513342582,-1433468233918517477,416753721122881089,6250330639306929770], aRuleName_ = "relation-cardinality"} +LF: {"AnsweredRule":{"aRuleName_":"relation-cardinality","qAscendants_":[-7326096647933004975,-3638343112521383479,-2681179249513342582,-1433468233918517477,416753721122881089,6250330639306929770],"qHole_":547691173299348338}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + and({ [sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = |toSet(conjure_aux1)|, + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]); + int(1..2)] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + }) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: |toSet(conjure_aux1)| + Context #1: sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = |toSet(conjure_aux1)| + Context #2: [sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = |toSet(conjure_aux1)|, + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]); + int(1..2)] + Context #3: { [sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = |toSet(conjure_aux1)|, + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]); + int(1..2)] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + } + Context #4: and({ [sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = |toSet(conjure_aux1)|, + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]); + int(1..2)] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + }) + Context #5: { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + and({ [sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = |toSet(conjure_aux1)|, + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]); + int(1..2)] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + }) + } + Context #6: y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + and({ [sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = |toSet(conjure_aux1)|, + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]); + int(1..2)] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + }) + } +Picking the only option: Answer 1: set-card: Horizontal rule for set cardinality. + sum([1 | q31 <- toSet(conjure_aux1)]) +storedChoice: +|toSet(conjure_aux1)| -1999756309500896427 +AnsweredRule {qHole_ = -1999756309500896427, qAscendants_ = fromList [-7320026331482846196,-1560614952215100976,3610191966919989235,3922795876024111867,4652593413741964988,8460019197720106806], aRuleName_ = "set-card"} +LF: {"AnsweredRule":{"aRuleName_":"set-card","qAscendants_":[-7320026331482846196,-1560614952215100976,3610191966919989235,3922795876024111867,4652593413741964988,8460019197720106806],"qHole_":-1999756309500896427}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + and({ [sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = sum([1 | q31 <- toSet(conjure_aux1)]), + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]); + int(1..2)] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + }) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: [1 | q31 <- toSet(conjure_aux1)] + Context #1: sum([1 | q31 <- toSet(conjure_aux1)]) + Context #2: sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = + sum([1 | q31 <- toSet(conjure_aux1)]) + Context #3: [sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = + sum([1 | q31 <- toSet(conjure_aux1)]), + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]); + int(1..2)] + Context #4: { [sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = + sum([1 | q31 <- toSet(conjure_aux1)]), + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]); + int(1..2)] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + } + Context #5: and({ [sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = + sum([1 | q31 <- toSet(conjure_aux1)]), + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]); + int(1..2)] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + }) + Context #6: { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + and({ [sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = sum([1 | q31 <- toSet(conjure_aux1)]), + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]); + int(1..2)] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + }) + } + Context #7: y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + and({ [sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = sum([1 | q31 <- toSet(conjure_aux1)]), + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]); + int(1..2)] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + }) + } +Picking the only option: Answer 1: relation-map_in_expr{RelationAsMatrix}: Vertical rule for map_in_expr for relation domains, RelationAsMatrix representation. + [1 | q32 : (int(1..5), int(1..5)), conjure_aux1_RelationAsMatrix[q32[1], q32[2]]] +storedChoice: +[1 | q31 <- toSet(conjure_aux1)] 4978495210772817269 +AnsweredRule {qHole_ = 4978495210772817269, qAscendants_ = fromList [-7947851092910419335,-4272160902177458760,-654328132560036401,4133420425219294144,6369167416454940534,6390095031407007755,7113998651427981501], aRuleName_ = "relation-map_in_expr{RelationAsMatrix}"} +LF: {"AnsweredRule":{"aRuleName_":"relation-map_in_expr{RelationAsMatrix}","qAscendants_":[-7947851092910419335,-4272160902177458760,-654328132560036401,4133420425219294144,6369167416454940534,6390095031407007755,7113998651427981501],"qHole_":4978495210772817269}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + and({ [sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = + sum([1 | q32 : (int(1..5), int(1..5)), conjure_aux1_RelationAsMatrix[q32[1], q32[2]]]), + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]); + int(1..2)] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + }) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: [1 | q32 : (int(1..5), int(1..5)), conjure_aux1_RelationAsMatrix[q32[1], q32[2]]] + Context #1: sum([1 | q32 : (int(1..5), int(1..5)), conjure_aux1_RelationAsMatrix[q32[1], q32[2]]]) + Context #2: sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = + sum([1 | q32 : (int(1..5), int(1..5)), conjure_aux1_RelationAsMatrix[q32[1], q32[2]]]) + Context #3: [sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = + sum([1 | q32 : (int(1..5), int(1..5)), conjure_aux1_RelationAsMatrix[q32[1], q32[2]]]), + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]); + int(1..2)] + Context #4: { [sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = + sum([1 | q32 : (int(1..5), int(1..5)), conjure_aux1_RelationAsMatrix[q32[1], q32[2]]]), + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]); + int(1..2)] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + } + Context #5: and({ [sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = + sum([1 | q32 : (int(1..5), int(1..5)), conjure_aux1_RelationAsMatrix[q32[1], q32[2]]]), + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]); + int(1..2)] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + }) + Context #6: { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + and({ [sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = + sum([1 | q32 : (int(1..5), int(1..5)), conjure_aux1_RelationAsMatrix[q32[1], q32[2]]]), + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]); + int(1..2)] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + }) + } + Context #7: y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + and({ [sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = + sum([1 | q32 : (int(1..5), int(1..5)), conjure_aux1_RelationAsMatrix[q32[1], q32[2]]]), + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]); + int(1..2)] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + }) + } +Picking the only option: Answer 1: choose-repr-for-comprehension: Choosing representation for quantified variable q32 (with type: (int, + int)) + [1 | q32_1 : int(1..5), q32_2 : int(1..5), conjure_aux1_RelationAsMatrix[q32[1], q32[2]]] +storedChoice: +[1 | q32 : (int(1..5), int(1..5)), conjure_aux1_RelationAsMatrix[q32[1], q32[2]]] 3282965607985773269 +AnsweredRule {qHole_ = 3282965607985773269, qAscendants_ = fromList [-7122899784982260955,-5889198071192861072,-531055723096273851,147713573061616732,2477913925342540157,3767703974941705567,9091983968002426702], aRuleName_ = "choose-repr-for-comprehension"} +LF: {"AnsweredRule":{"aRuleName_":"choose-repr-for-comprehension","qAscendants_":[-7122899784982260955,-5889198071192861072,-531055723096273851,147713573061616732,2477913925342540157,3767703974941705567,9091983968002426702],"qHole_":3282965607985773269}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + and({ [sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = + sum([1 | q32_1 : int(1..5), q32_2 : int(1..5), conjure_aux1_RelationAsMatrix[q32[1], q32[2]]]), + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]); + int(1..2)] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + }) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: q32[1] + Context #1: conjure_aux1_RelationAsMatrix[q32[1]] + Context #2: conjure_aux1_RelationAsMatrix[q32[1], q32[2]] + Context #3: [1 | q32_1 : int(1..5), q32_2 : int(1..5), conjure_aux1_RelationAsMatrix[q32[1], q32[2]]] + Context #4: sum([1 | q32_1 : int(1..5), q32_2 : int(1..5), conjure_aux1_RelationAsMatrix[q32[1], q32[2]]]) + Context #5: sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = + sum([1 | q32_1 : int(1..5), q32_2 : int(1..5), conjure_aux1_RelationAsMatrix[q32[1], q32[2]]]) + Context #6: [sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = + sum([1 | q32_1 : int(1..5), q32_2 : int(1..5), conjure_aux1_RelationAsMatrix[q32[1], q32[2]]]), + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]); + int(1..2)] + Context #7: { [sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = + sum([1 | q32_1 : int(1..5), q32_2 : int(1..5), conjure_aux1_RelationAsMatrix[q32[1], q32[2]]]), + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]); + int(1..2)] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + } + Context #8: and({ [sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = + sum([1 | q32_1 : int(1..5), q32_2 : int(1..5), conjure_aux1_RelationAsMatrix[q32[1], q32[2]]]), + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]); + int(1..2)] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + }) + Context #9: { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + and({ [sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = + sum([1 | q32_1 : int(1..5), q32_2 : int(1..5), conjure_aux1_RelationAsMatrix[q32[1], q32[2]]]), + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]); + int(1..2)] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + }) + } + Context #10: y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + and({ [sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = + sum([1 | q32_1 : int(1..5), q32_2 : int(1..5), conjure_aux1_RelationAsMatrix[q32[1], q32[2]]]), + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]); + int(1..2)] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + }) + } +Picking the only option: Answer 1: tuple-index: Tuple indexing on: q32[1] + q32_1 +storedChoice: +q32[1] 4038868374035555703 +AnsweredRule {qHole_ = 4038868374035555703, qAscendants_ = fromList [-8553658543572221773,-6138711856874023512,-4335853381078465244,-2646146961819662754,-2343456358494450273,-1664802311461525085,-1649342081664357811,3161695419280017087,3741265834386353390,8703630850884516346], aRuleName_ = "tuple-index"} +LF: {"AnsweredRule":{"aRuleName_":"tuple-index","qAscendants_":[-8553658543572221773,-6138711856874023512,-4335853381078465244,-2646146961819662754,-2343456358494450273,-1664802311461525085,-1649342081664357811,3161695419280017087,3741265834386353390,8703630850884516346],"qHole_":4038868374035555703}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + and({ [sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = + sum([1 | q32_1 : int(1..5), q32_2 : int(1..5), conjure_aux1_RelationAsMatrix[q32_1, q32[2]]]), + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]); + int(1..2)] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + }) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: q32[2] + Context #1: conjure_aux1_RelationAsMatrix[q32_1, q32[2]] + Context #2: [1 | q32_1 : int(1..5), q32_2 : int(1..5), conjure_aux1_RelationAsMatrix[q32_1, q32[2]]] + Context #3: sum([1 | q32_1 : int(1..5), q32_2 : int(1..5), conjure_aux1_RelationAsMatrix[q32_1, q32[2]]]) + Context #4: sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = + sum([1 | q32_1 : int(1..5), q32_2 : int(1..5), conjure_aux1_RelationAsMatrix[q32_1, q32[2]]]) + Context #5: [sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = + sum([1 | q32_1 : int(1..5), q32_2 : int(1..5), conjure_aux1_RelationAsMatrix[q32_1, q32[2]]]), + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]); + int(1..2)] + Context #6: { [sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = + sum([1 | q32_1 : int(1..5), q32_2 : int(1..5), conjure_aux1_RelationAsMatrix[q32_1, q32[2]]]), + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]); + int(1..2)] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + } + Context #7: and({ [sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = + sum([1 | q32_1 : int(1..5), q32_2 : int(1..5), conjure_aux1_RelationAsMatrix[q32_1, q32[2]]]), + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]); + int(1..2)] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + }) + Context #8: { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + and({ [sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = + sum([1 | q32_1 : int(1..5), q32_2 : int(1..5), conjure_aux1_RelationAsMatrix[q32_1, q32[2]]]), + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]); + int(1..2)] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + }) + } + Context #9: y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + and({ [sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = + sum([1 | q32_1 : int(1..5), q32_2 : int(1..5), conjure_aux1_RelationAsMatrix[q32_1, q32[2]]]), + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]); + int(1..2)] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + }) + } +Picking the only option: Answer 1: tuple-index: Tuple indexing on: q32[2] + q32_2 +storedChoice: +q32[2] 4038586886173796060 +AnsweredRule {qHole_ = 4038586886173796060, qAscendants_ = fromList [58246981470148902,365936135746281162,897915292494521279,2148255109439096362,2599338170801596327,4347596293011070033,8156974448309241515,8375135551163386670,8976994852842826417], aRuleName_ = "tuple-index"} +LF: {"AnsweredRule":{"aRuleName_":"tuple-index","qAscendants_":[58246981470148902,365936135746281162,897915292494521279,2148255109439096362,2599338170801596327,4347596293011070033,8156974448309241515,8375135551163386670,8976994852842826417],"qHole_":4038586886173796060}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + and({ [sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = + sum([1 | q32_1 : int(1..5), q32_2 : int(1..5), conjure_aux1_RelationAsMatrix[q32_1, q32_2]]), + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]); + int(1..2)] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + }) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: [1 | q32_1 : int(1..5), q32_2 : int(1..5), conjure_aux1_RelationAsMatrix[q32_1, q32_2]] + Context #1: sum([1 | q32_1 : int(1..5), q32_2 : int(1..5), conjure_aux1_RelationAsMatrix[q32_1, q32_2]]) + Context #2: sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = + sum([1 | q32_1 : int(1..5), q32_2 : int(1..5), conjure_aux1_RelationAsMatrix[q32_1, q32_2]]) + Context #3: [sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = + sum([1 | q32_1 : int(1..5), q32_2 : int(1..5), conjure_aux1_RelationAsMatrix[q32_1, q32_2]]), + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]); + int(1..2)] + Context #4: { [sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = + sum([1 | q32_1 : int(1..5), q32_2 : int(1..5), conjure_aux1_RelationAsMatrix[q32_1, q32_2]]), + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]); + int(1..2)] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + } + Context #5: and({ [sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = + sum([1 | q32_1 : int(1..5), q32_2 : int(1..5), conjure_aux1_RelationAsMatrix[q32_1, q32_2]]), + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]); + int(1..2)] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + }) + Context #6: { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + and({ [sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = + sum([1 | q32_1 : int(1..5), q32_2 : int(1..5), conjure_aux1_RelationAsMatrix[q32_1, q32_2]]), + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]); + int(1..2)] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + }) + } + Context #7: y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + and({ [sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = + sum([1 | q32_1 : int(1..5), q32_2 : int(1..5), conjure_aux1_RelationAsMatrix[q32_1, q32_2]]), + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]); + int(1..2)] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + }) + } +Picking the only option: Answer 1: inline-conditions: Inlining conditions, inside sum + [toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) * catchUndef(1, 0) | q32_1 : int(1..5), q32_2 : int(1..5)] +storedChoice: +[1 | q32_1 : int(1..5), q32_2 : int(1..5), conjure_aux1_RelationAsMatrix[q32_1, q32_2]] -5719405584779695493 +AnsweredRule {qHole_ = -5719405584779695493, qAscendants_ = fromList [-9027745215861162370,-8099216132366058965,-5857000228242749317,-5553782237459419472,4623787234387693138,7124000196337888585,8079567542521963183], aRuleName_ = "inline-conditions"} +LF: {"AnsweredRule":{"aRuleName_":"inline-conditions","qAscendants_":[-9027745215861162370,-8099216132366058965,-5857000228242749317,-5553782237459419472,4623787234387693138,7124000196337888585,8079567542521963183],"qHole_":-5719405584779695493}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + and({ [sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = + sum([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) * catchUndef(1, 0) | q32_1 : int(1..5), q32_2 : int(1..5)]), + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]); + int(1..2)] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + }) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: catchUndef(1, 0) + Context #1: [toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]), catchUndef(1, 0); int(1..2)] + Context #2: toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) * catchUndef(1, 0) + Context #3: [toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) * catchUndef(1, 0) | q32_1 : int(1..5), q32_2 : int(1..5)] + Context #4: sum([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) * catchUndef(1, 0) | q32_1 : int(1..5), q32_2 : int(1..5)]) + Context #5: sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = + sum([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) * catchUndef(1, 0) | q32_1 : int(1..5), q32_2 : int(1..5)]) + Context #6: [sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = + sum([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) * catchUndef(1, 0) | q32_1 : int(1..5), q32_2 : int(1..5)]), + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]); + int(1..2)] + Context #7: { [sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = + sum([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) * catchUndef(1, 0) | q32_1 : int(1..5), q32_2 : int(1..5)]), + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]); + int(1..2)] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + } + Context #8: and({ [sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = + sum([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) * catchUndef(1, 0) | q32_1 : int(1..5), q32_2 : int(1..5)]), + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]); + int(1..2)] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + }) + Context #9: { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + and({ [sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = + sum([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) * catchUndef(1, 0) | q32_1 : int(1..5), q32_2 : int(1..5)]), + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]); + int(1..2)] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + }) + } + Context #10: y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + and({ [sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = + sum([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) * catchUndef(1, 0) | q32_1 : int(1..5), q32_2 : int(1..5)]), + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]); + int(1..2)] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + }) + } +Picking the only option: Answer 1: full-evaluate: Full evaluator + 1 +storedChoice: +catchUndef(1, 0) -4103543015608659681 +AnsweredRule {qHole_ = -4103543015608659681, qAscendants_ = fromList [-8969688714663757079,-8620054688580705850,-7803342152587091485,-6406402188841036454,-3137912990386087120,-2245754891843782432,-893701506107809144,-421079377584717971,4859060653783625533,9081980220064719370], aRuleName_ = "full-evaluate"} +LF: {"AnsweredRule":{"aRuleName_":"full-evaluate","qAscendants_":[-8969688714663757079,-8620054688580705850,-7803342152587091485,-6406402188841036454,-3137912990386087120,-2245754891843782432,-893701506107809144,-421079377584717971,4859060653783625533,9081980220064719370],"qHole_":-4103543015608659681}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + and({ [sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = + sum([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) * 1 | q32_1 : int(1..5), q32_2 : int(1..5)]), + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]); + int(1..2)] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + }) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) * 1 + Context #1: [toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) * 1 | q32_1 : int(1..5), q32_2 : int(1..5)] + Context #2: sum([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) * 1 | q32_1 : int(1..5), q32_2 : int(1..5)]) + Context #3: sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = + sum([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) * 1 | q32_1 : int(1..5), q32_2 : int(1..5)]) + Context #4: [sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = + sum([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) * 1 | q32_1 : int(1..5), q32_2 : int(1..5)]), + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]); + int(1..2)] + Context #5: { [sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = + sum([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) * 1 | q32_1 : int(1..5), q32_2 : int(1..5)]), + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]); + int(1..2)] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + } + Context #6: and({ [sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = + sum([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) * 1 | q32_1 : int(1..5), q32_2 : int(1..5)]), + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]); + int(1..2)] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + }) + Context #7: { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + and({ [sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = + sum([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) * 1 | q32_1 : int(1..5), q32_2 : int(1..5)]), + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]); + int(1..2)] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + }) + } + Context #8: y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + and({ [sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = + sum([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) * 1 | q32_1 : int(1..5), q32_2 : int(1..5)]), + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]); + int(1..2)] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + }) + } +Picking the only option: Answer 1: partial-evaluate: Partial evaluator + product([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]); int(1)]) +storedChoice: +toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) * 1 -4682469706785037945 +AnsweredRule {qHole_ = -4682469706785037945, qAscendants_ = fromList [-9179050654683062954,-8797033748133430528,-8329454991333631126,-5647606918064816013,-3380861767487578940,6010365049512866508,6747419370843152779,7119833088853932687], aRuleName_ = "partial-evaluate"} +LF: {"AnsweredRule":{"aRuleName_":"partial-evaluate","qAscendants_":[-9179050654683062954,-8797033748133430528,-8329454991333631126,-5647606918064816013,-3380861767487578940,6010365049512866508,6747419370843152779,7119833088853932687],"qHole_":-4682469706785037945}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + and({ [sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = + sum([product([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]); int(1)]) | q32_1 : int(1..5), q32_2 : int(1..5)]), + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]); + int(1..2)] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + }) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: product([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]); int(1)]) + Context #1: [product([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]); int(1)]) | q32_1 : int(1..5), q32_2 : int(1..5)] + Context #2: sum([product([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]); int(1)]) | q32_1 : int(1..5), q32_2 : int(1..5)]) + Context #3: sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = + sum([product([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]); int(1)]) | q32_1 : int(1..5), q32_2 : int(1..5)]) + Context #4: [sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = + sum([product([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]); int(1)]) | q32_1 : int(1..5), q32_2 : int(1..5)]), + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]); + int(1..2)] + Context #5: { [sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = + sum([product([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]); int(1)]) | q32_1 : int(1..5), q32_2 : int(1..5)]), + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]); + int(1..2)] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + } + Context #6: and({ [sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = + sum([product([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]); int(1)]) | q32_1 : int(1..5), q32_2 : int(1..5)]), + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]); + int(1..2)] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + }) + Context #7: { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + and({ [sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = + sum([product([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]); int(1)]) | q32_1 : int(1..5), q32_2 : int(1..5)]), + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]); + int(1..2)] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + }) + } + Context #8: y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + and({ [sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = + sum([product([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]); int(1)]) | q32_1 : int(1..5), q32_2 : int(1..5)]), + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]); + int(1..2)] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + }) + } +Picking the only option: Answer 1: matrix-comprehension-singleton: Removing quantifier of a single item + toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) +storedChoice: +product([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]); int(1)]) -3618757702268377732 +AnsweredRule {qHole_ = -3618757702268377732, qAscendants_ = fromList [-3180788541249390624,-1419697389512850335,2051112281511221751,3011082682326874338,4702464191332467431,4730858055169822202,6821954100224183740,8108702534288021537], aRuleName_ = "matrix-comprehension-singleton"} +LF: {"AnsweredRule":{"aRuleName_":"matrix-comprehension-singleton","qAscendants_":[-3180788541249390624,-1419697389512850335,2051112281511221751,3011082682326874338,4702464191332467431,4730858055169822202,6821954100224183740,8108702534288021537],"qHole_":-3618757702268377732}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + and({ [sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = + sum([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) | q32_1 : int(1..5), q32_2 : int(1..5)]), + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]); + int(1..2)] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + }) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: and({ [sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = + sum([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) | q32_1 : int(1..5), q32_2 : int(1..5)]), + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]); + int(1..2)] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + }) + Context #1: { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + and({ [sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = + sum([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) | q32_1 : int(1..5), q32_2 : int(1..5)]), + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]); + int(1..2)] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + }) + } + Context #2: y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + and({ [sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = + sum([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) | q32_1 : int(1..5), q32_2 : int(1..5)]), + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]); + int(1..2)] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + }) + } +Picking the only option: Answer 1: bubble-up-LiftVars: Bubbling up auxiliary variables. + { sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = + sum([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) | q32_1 : int(1..5), q32_2 : int(1..5)]) + /\ + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + } +storedChoice: +and({ [sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = + sum([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) | q32_1 : int(1..5), q32_2 : int(1..5)]), + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]); + int(1..2)] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + }) -4558336889735046944 +AnsweredRule {qHole_ = -4558336889735046944, qAscendants_ = fromList [-3486949521822083211,2980043443155673363], aRuleName_ = "bubble-up-LiftVars"} +LF: {"AnsweredRule":{"aRuleName_":"bubble-up-LiftVars","qAscendants_":[-3486949521822083211,2980043443155673363],"qHole_":-4558336889735046944}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + { sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = + sum([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) | q32_1 : int(1..5), q32_2 : int(1..5)]) + /\ + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + } + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + { sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = + sum([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) | q32_1 : int(1..5), q32_2 : int(1..5)]) + /\ + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + } + } +Picking the only option: Answer 1: bubble-up-LiftVars: Bubbling up auxiliary variables. + { y = conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + { sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = + sum([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) | q32_1 : int(1..5), q32_2 : int(1..5)]) + /\ + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + } + } +storedChoice: +y = +{ conjure_aux1 +@ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + { sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = + sum([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) | q32_1 : int(1..5), q32_2 : int(1..5)]) + /\ + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + } +} 8908675996089062110 +AnsweredRule {qHole_ = 8908675996089062110, qAscendants_ = fromList [], aRuleName_ = "bubble-up-LiftVars"} +LF: {"AnsweredRule":{"aRuleName_":"bubble-up-LiftVars","qAscendants_":[],"qHole_":8908675996089062110}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + { y = conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + { sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = + sum([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) | q32_1 : int(1..5), q32_2 : int(1..5)]) + /\ + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + } + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: y = conjure_aux1 + Context #1: { y = conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + { sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = + sum([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) | q32_1 : int(1..5), q32_2 : int(1..5)]) + /\ + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + } + } +Picking the only option: Answer 1: identical-domain-eq: Generic vertical rule for identical-domain equality + and([y_RelationAsMatrix = conjure_aux1_RelationAsMatrix; int(1)]) +storedChoice: +y = conjure_aux1 3717099060101766216 +AnsweredRule {qHole_ = 3717099060101766216, qAscendants_ = fromList [2671848414499686108], aRuleName_ = "identical-domain-eq"} +LF: {"AnsweredRule":{"aRuleName_":"identical-domain-eq","qAscendants_":[2671848414499686108],"qHole_":3717099060101766216}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + { and([y_RelationAsMatrix = conjure_aux1_RelationAsMatrix; int(1)]) + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + { sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = + sum([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) | q32_1 : int(1..5), q32_2 : int(1..5)]) + /\ + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + } + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: y_RelationAsMatrix = conjure_aux1_RelationAsMatrix + Context #1: [y_RelationAsMatrix = conjure_aux1_RelationAsMatrix; int(1)] + Context #2: and([y_RelationAsMatrix = conjure_aux1_RelationAsMatrix; int(1)]) + Context #3: { and([y_RelationAsMatrix = conjure_aux1_RelationAsMatrix; int(1)]) + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + { sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = + sum([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) | q32_1 : int(1..5), q32_2 : int(1..5)]) + /\ + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + } + } +Picking the only option: Answer 1: matrix-eq: Horizontal rule for matrix = + and([y_RelationAsMatrix[q33] = conjure_aux1_RelationAsMatrix[q33] | q33 : int(1..5)]) +storedChoice: +y_RelationAsMatrix = conjure_aux1_RelationAsMatrix 847538541028825252 +AnsweredRule {qHole_ = 847538541028825252, qAscendants_ = fromList [-7545604584042643741,-3140704007737949652,8589500105863926587], aRuleName_ = "matrix-eq"} +LF: {"AnsweredRule":{"aRuleName_":"matrix-eq","qAscendants_":[-7545604584042643741,-3140704007737949652,8589500105863926587],"qHole_":847538541028825252}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + { and([and([y_RelationAsMatrix[q33] = conjure_aux1_RelationAsMatrix[q33] | q33 : int(1..5)]); int(1)]) + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + { sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = + sum([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) | q32_1 : int(1..5), q32_2 : int(1..5)]) + /\ + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + } + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: [y_RelationAsMatrix[q33] = conjure_aux1_RelationAsMatrix[q33] | q33 : int(1..5)] + Context #1: and([y_RelationAsMatrix[q33] = conjure_aux1_RelationAsMatrix[q33] | q33 : int(1..5)]) + Context #2: [and([y_RelationAsMatrix[q33] = conjure_aux1_RelationAsMatrix[q33] | q33 : int(1..5)]); int(1)] + Context #3: and([and([y_RelationAsMatrix[q33] = conjure_aux1_RelationAsMatrix[q33] | q33 : int(1..5)]); int(1)]) + Context #4: { and([and([y_RelationAsMatrix[q33] = conjure_aux1_RelationAsMatrix[q33] | q33 : int(1..5)]); int(1)]) + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + { sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = + sum([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) | q32_1 : int(1..5), q32_2 : int(1..5)]) + /\ + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + } + } +Picking the only option: Answer 1: choose-repr-for-comprehension: Choosing representation for quantified variable q33 (with type: int) + [y_RelationAsMatrix[q33] = conjure_aux1_RelationAsMatrix[q33] | q33 : int(1..5)] +storedChoice: +[y_RelationAsMatrix[q33] = conjure_aux1_RelationAsMatrix[q33] | q33 : int(1..5)] 45103260545151270 +AnsweredRule {qHole_ = 45103260545151270, qAscendants_ = fromList [-5973861858959396663,-4660253290178341140,-3962474706459959320,-1163992588452778161], aRuleName_ = "choose-repr-for-comprehension"} +LF: {"AnsweredRule":{"aRuleName_":"choose-repr-for-comprehension","qAscendants_":[-5973861858959396663,-4660253290178341140,-3962474706459959320,-1163992588452778161],"qHole_":45103260545151270}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + { and([and([y_RelationAsMatrix[q33] = conjure_aux1_RelationAsMatrix[q33] | q33 : int(1..5)]); int(1)]) + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + { sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = + sum([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) | q32_1 : int(1..5), q32_2 : int(1..5)]) + /\ + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + } + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: y_RelationAsMatrix[q33] = conjure_aux1_RelationAsMatrix[q33] + Context #1: [y_RelationAsMatrix[q33] = conjure_aux1_RelationAsMatrix[q33] | q33 : int(1..5)] + Context #2: and([y_RelationAsMatrix[q33] = conjure_aux1_RelationAsMatrix[q33] | q33 : int(1..5)]) + Context #3: [and([y_RelationAsMatrix[q33] = conjure_aux1_RelationAsMatrix[q33] | q33 : int(1..5)]); int(1)] + Context #4: and([and([y_RelationAsMatrix[q33] = conjure_aux1_RelationAsMatrix[q33] | q33 : int(1..5)]); int(1)]) + Context #5: { and([and([y_RelationAsMatrix[q33] = conjure_aux1_RelationAsMatrix[q33] | q33 : int(1..5)]); int(1)]) + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + { sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = + sum([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) | q32_1 : int(1..5), q32_2 : int(1..5)]) + /\ + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + } + } +Picking the only option: Answer 1: matrix-eq: Horizontal rule for matrix = + and([y_RelationAsMatrix[q33, q35] = conjure_aux1_RelationAsMatrix[q33, q35] | q35 : int(1..5)]) +storedChoice: +y_RelationAsMatrix[q33] = conjure_aux1_RelationAsMatrix[q33] 971298532972344754 +AnsweredRule {qHole_ = 971298532972344754, qAscendants_ = fromList [-5973861858959396663,-4660253290178341140,-3962474706459959320,-1163992588452778161,45103260545151270], aRuleName_ = "matrix-eq"} +LF: {"AnsweredRule":{"aRuleName_":"matrix-eq","qAscendants_":[-5973861858959396663,-4660253290178341140,-3962474706459959320,-1163992588452778161,45103260545151270],"qHole_":971298532972344754}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + { and([and([and([y_RelationAsMatrix[q33, q35] = conjure_aux1_RelationAsMatrix[q33, q35] | q35 : int(1..5)]) | q33 : int(1..5)]); + int(1)]) + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + { sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = + sum([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) | q32_1 : int(1..5), q32_2 : int(1..5)]) + /\ + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + } + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: [y_RelationAsMatrix[q33, q35] = conjure_aux1_RelationAsMatrix[q33, q35] | q35 : int(1..5)] + Context #1: and([y_RelationAsMatrix[q33, q35] = conjure_aux1_RelationAsMatrix[q33, q35] | q35 : int(1..5)]) + Context #2: [and([y_RelationAsMatrix[q33, q35] = conjure_aux1_RelationAsMatrix[q33, q35] | q35 : int(1..5)]) | q33 : int(1..5)] + Context #3: and([and([y_RelationAsMatrix[q33, q35] = conjure_aux1_RelationAsMatrix[q33, q35] | q35 : int(1..5)]) | q33 : int(1..5)]) + Context #4: [and([and([y_RelationAsMatrix[q33, q35] = conjure_aux1_RelationAsMatrix[q33, q35] | q35 : int(1..5)]) + | q33 : int(1..5)]); + int(1)] + Context #5: and([and([and([y_RelationAsMatrix[q33, q35] = conjure_aux1_RelationAsMatrix[q33, q35] | q35 : int(1..5)]) + | q33 : int(1..5)]); + int(1)]) + Context #6: { and([and([and([y_RelationAsMatrix[q33, q35] = conjure_aux1_RelationAsMatrix[q33, q35] | q35 : int(1..5)]) + | q33 : int(1..5)]); + int(1)]) + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + { sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = + sum([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) | q32_1 : int(1..5), q32_2 : int(1..5)]) + /\ + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + } + } +Picking the only option: Answer 1: choose-repr-for-comprehension: Choosing representation for quantified variable q35 (with type: int) + [y_RelationAsMatrix[q33, q35] = conjure_aux1_RelationAsMatrix[q33, q35] | q35 : int(1..5)] +storedChoice: +[y_RelationAsMatrix[q33, q35] = conjure_aux1_RelationAsMatrix[q33, q35] | q35 : int(1..5)] -1275491152285478671 +AnsweredRule {qHole_ = -1275491152285478671, qAscendants_ = fromList [-9124538447972763747,1151872964749555522,2218928338283019637,3574995822047355118,8452562685486794942,8526913528687567140], aRuleName_ = "choose-repr-for-comprehension"} +LF: {"AnsweredRule":{"aRuleName_":"choose-repr-for-comprehension","qAscendants_":[-9124538447972763747,1151872964749555522,2218928338283019637,3574995822047355118,8452562685486794942,8526913528687567140],"qHole_":-1275491152285478671}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + { and([and([and([y_RelationAsMatrix[q33, q35] = conjure_aux1_RelationAsMatrix[q33, q35] | q35 : int(1..5)]) | q33 : int(1..5)]); + int(1)]) + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + { sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = + sum([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) | q32_1 : int(1..5), q32_2 : int(1..5)]) + /\ + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + } + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: and([and([and([y_RelationAsMatrix[q33, q35] = conjure_aux1_RelationAsMatrix[q33, q35] + | q35 : int(1..5)]) + | q33 : int(1..5)]); + int(1)]) + Context #1: { and([and([and([y_RelationAsMatrix[q33, q35] = conjure_aux1_RelationAsMatrix[q33, q35] | q35 : int(1..5)]) + | q33 : int(1..5)]); + int(1)]) + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + { sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = + sum([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) | q32_1 : int(1..5), q32_2 : int(1..5)]) + /\ + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + } + } +Picking the only option: Answer 1: matrix-comprehension-singleton: Removing quantifier of a single item + and([and([y_RelationAsMatrix[q33, q35] = conjure_aux1_RelationAsMatrix[q33, q35] | q35 : int(1..5)]) | q33 : int(1..5)]) +storedChoice: +and([and([and([y_RelationAsMatrix[q33, q35] = conjure_aux1_RelationAsMatrix[q33, q35] | q35 : int(1..5)]) | q33 : int(1..5)]); + int(1)]) 3574995822047355118 +AnsweredRule {qHole_ = 3574995822047355118, qAscendants_ = fromList [1151872964749555522], aRuleName_ = "matrix-comprehension-singleton"} +LF: {"AnsweredRule":{"aRuleName_":"matrix-comprehension-singleton","qAscendants_":[1151872964749555522],"qHole_":3574995822047355118}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + { and([and([y_RelationAsMatrix[q33, q35] = conjure_aux1_RelationAsMatrix[q33, q35] | q35 : int(1..5)]) | q33 : int(1..5)]) + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + { sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = + sum([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) | q32_1 : int(1..5), q32_2 : int(1..5)]) + /\ + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + } + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: true(x) +Picking the only option: Answer 1: true-is-noop: Remove the argument from true. + true +storedChoice: +true(x) -1508832156878423928 +AnsweredRule {qHole_ = -1508832156878423928, qAscendants_ = fromList [], aRuleName_ = "true-is-noop"} +LF: {"AnsweredRule":{"aRuleName_":"true-is-noop","qAscendants_":[],"qHole_":-1508832156878423928}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + { and([and([y_RelationAsMatrix[q33, q35] = conjure_aux1_RelationAsMatrix[q33, q35] | q35 : int(1..5)]) | q33 : int(1..5)]) + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + { sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = + sum([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) | q32_1 : int(1..5), q32_2 : int(1..5)]) + /\ + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + } + } + branching on [x, y] + such that + such that + true, + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: true(y) +Picking the only option: Answer 1: true-is-noop: Remove the argument from true. + true +storedChoice: +true(y) -1508550667338902379 +AnsweredRule {qHole_ = -1508550667338902379, qAscendants_ = fromList [], aRuleName_ = "true-is-noop"} +LF: {"AnsweredRule":{"aRuleName_":"true-is-noop","qAscendants_":[],"qHole_":-1508550667338902379}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + { and([and([y_RelationAsMatrix[q33, q35] = conjure_aux1_RelationAsMatrix[q33, q35] | q35 : int(1..5)]) | q33 : int(1..5)]) + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + { sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = + sum([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) | q32_1 : int(1..5), q32_2 : int(1..5)]) + /\ + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + } + } + branching on [x, y] + such that + such that + true, + true + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +[epilogue] + language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + { and([and([y_RelationAsMatrix[q33, q35] = conjure_aux1_RelationAsMatrix[q33, q35] | q35 : int(1..5)]) | q33 : int(1..5)]) + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + { sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = + sum([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) | q32_1 : int(1..5), q32_2 : int(1..5)]) + /\ + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + } + } + branching on [x, y] + such that + such that + true, + true + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +[dropTagForSR] + language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + { and([and([y_RelationAsMatrix[q33, q35] = conjure_aux1_RelationAsMatrix[q33, q35] | q35 : int(1..5)]) | q33 : int(1..5)]) + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + { sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = + sum([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) | q32_1 : int(1..5), q32_2 : int(1..5)]) + /\ + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + } + } + branching on [x, y] + such that + such that + true, + true + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +[updateDeclarations] + language Essence 1.3 + + find x_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + find y_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that + { and([and([y_RelationAsMatrix[q33, q35] = conjure_aux1_RelationAsMatrix[q33, q35] | q35 : int(1..5)]) | q33 : int(1..5)]) + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + { sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = + sum([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) | q32_1 : int(1..5), q32_2 : int(1..5)]) + /\ + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + } + } + branching on [x_RelationAsMatrix, y_RelationAsMatrix] + such that + such that + true, + true + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +[inlineDecVarLettings] + language Essence 1.3 + + find x_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + find y_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that + { and([and([y_RelationAsMatrix[q33, q35] = conjure_aux1_RelationAsMatrix[q33, q35] | q35 : int(1..5)]) | q33 : int(1..5)]) + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + { sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = + sum([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) | q32_1 : int(1..5), q32_2 : int(1..5)]) + /\ + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + } + } + branching on [x_RelationAsMatrix, y_RelationAsMatrix] + such that + such that + true, + true + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +[topLevelBubbles] + language Essence 1.3 + + find x_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + find y_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + such that and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + such that and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + such that + sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = + sum([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) | q32_1 : int(1..5), q32_2 : int(1..5)]) + /\ + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + such that and([and([y_RelationAsMatrix[q33, q35] = conjure_aux1_RelationAsMatrix[q33, q35] | q35 : int(1..5)]) | q33 : int(1..5)]) + branching on [x_RelationAsMatrix, y_RelationAsMatrix] + such that true + such that true + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +[checkIfAllRefined] + language Essence 1.3 + + find x_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + find y_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + such that and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + such that and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + such that + sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = + sum([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) | q32_1 : int(1..5), q32_2 : int(1..5)]) + /\ + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + such that and([and([y_RelationAsMatrix[q33, q35] = conjure_aux1_RelationAsMatrix[q33, q35] | q35 : int(1..5)]) | q33 : int(1..5)]) + branching on [x_RelationAsMatrix, y_RelationAsMatrix] + such that true + such that true + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +[checkIfHasUndefined] + language Essence 1.3 + + find x_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + find y_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + such that and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + such that and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + such that + sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = + sum([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) | q32_1 : int(1..5), q32_2 : int(1..5)]) + /\ + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + such that and([and([y_RelationAsMatrix[q33, q35] = conjure_aux1_RelationAsMatrix[q33, q35] | q35 : int(1..5)]) | q33 : int(1..5)]) + branching on [x_RelationAsMatrix, y_RelationAsMatrix] + such that true + such that true + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +[sliceThemMatrices] + language Essence 1.3 + + find x_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + find y_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + such that and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + such that and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + such that + sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = + sum([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) | q32_1 : int(1..5), q32_2 : int(1..5)]) + /\ + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + such that and([and([y_RelationAsMatrix[q33, q35] = conjure_aux1_RelationAsMatrix[q33, q35] | q35 : int(1..5)]) | q33 : int(1..5)]) + branching on [x_RelationAsMatrix, y_RelationAsMatrix] + such that true + such that true + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +[emptyMatrixLiterals] + language Essence 1.3 + + find x_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + find y_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + such that and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + such that and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + such that + sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = + sum([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) | q32_1 : int(1..5), q32_2 : int(1..5)]) + /\ + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + such that and([and([y_RelationAsMatrix[q33, q35] = conjure_aux1_RelationAsMatrix[q33, q35] | q35 : int(1..5)]) | q33 : int(1..5)]) + branching on [x_RelationAsMatrix, y_RelationAsMatrix] + such that true + such that true + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +[reverseTrails] + language Essence 1.3 + + find x_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + find y_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + such that and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + such that and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + such that + sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = + sum([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) | q32_1 : int(1..5), q32_2 : int(1..5)]) + /\ + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + such that and([and([y_RelationAsMatrix[q33, q35] = conjure_aux1_RelationAsMatrix[q33, q35] | q35 : int(1..5)]) | q33 : int(1..5)]) + branching on [x_RelationAsMatrix, y_RelationAsMatrix] + such that true + such that true + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +[oneSuchThat] + language Essence 1.3 + + find x_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + find y_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + branching on [x_RelationAsMatrix, y_RelationAsMatrix] + such that + 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]), + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]), + and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]), + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]), + and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]), + sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = + sum([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) | q32_1 : int(1..5), q32_2 : int(1..5)]), + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]), + and([and([y_RelationAsMatrix[q33, q35] = conjure_aux1_RelationAsMatrix[q33, q35] | q35 : int(1..5)]) | q33 : int(1..5)]), + 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]), + 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +[languageEprime] + language ESSENCE' 1.0 + + find x_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + find y_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + branching on [x_RelationAsMatrix, y_RelationAsMatrix] + such that + 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]), + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]), + and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]), + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]), + and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]), + sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = + sum([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) | q32_1 : int(1..5), q32_2 : int(1..5)]), + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]), + and([and([y_RelationAsMatrix[q33, q35] = conjure_aux1_RelationAsMatrix[q33, q35] | q35 : int(1..5)]) | q33 : int(1..5)]), + 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]), + 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + diff --git a/tests/custom/permutations/basic/0029_find_relations_x_y_such_that_y_image_x_under_p/log-lite b/tests/custom/permutations/basic/0029_find_relations_x_y_such_that_y_image_x_under_p/log-lite new file mode 100644 index 0000000000..d9c9edd24e --- /dev/null +++ b/tests/custom/permutations/basic/0029_find_relations_x_y_such_that_y_image_x_under_p/log-lite @@ -0,0 +1,7863 @@ +Command line options: Modelling {essence = "permutation.essence", outputDirectory = "conjure-output", numberingStart = 1, smartFilenames = False, responses = "", logLevel = LogDebug, verboseTrail = False, rewritesTrail = False, logRuleFails = False, logRuleSuccesses = False, logRuleAttempts = False, logChoices = False, strategyQ = "f", strategyA = "ai", representations = Nothing, representationsFinds = Nothing, representationsGivens = Nothing, representationsAuxiliaries = Nothing, representationsQuantifieds = Nothing, representationsCuts = Nothing, channelling = True, representationLevels = True, seed = Nothing, limitModels = Nothing, limitTime = Nothing, savedChoices = Nothing, outputFormat = Plain, lineWidth = 120} +[input] + language Essence 1.3 + + letting MYTYPE be new type enum {THING1, THING2, THING3, THING4, THING5} + letting p be permutation((THING3, THING4)) + find x: relation (size 4) of (MYTYPE * MYTYPE) + find y: relation (size 4) of (MYTYPE * MYTYPE) + such that y = image(p, x) + +[removeUnnamedsFromModel] + language Essence 1.3 + + letting MYTYPE be new type enum {THING1, THING2, THING3, THING4, THING5} + letting p be permutation((THING3, THING4)) + find x: relation (size 4) of (MYTYPE * MYTYPE) + find y: relation (size 4) of (MYTYPE * MYTYPE) + such that y = image(p, x) + +Recording enumGivens: +[removeEnumsFromModel] + language Essence 1.3 + + letting MYTYPE be domain int(1..5) + letting p be permutation((3, 4)) + find x: relation (size 4) of (MYTYPE * MYTYPE) + find y: relation (size 4) of (MYTYPE * MYTYPE) + such that y = image(p, x) + +[resolveNames] + language Essence 1.3 + + letting MYTYPE be domain int(1..5) + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that y = image(p, x) + +[typeCheckModel] + language Essence 1.3 + + letting MYTYPE be domain int(1..5) + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that y = image(p, x) + +[categoryChecking] + language Essence 1.3 + + letting MYTYPE be domain int(1..5) + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that y = image(p, x) + +[sanityChecks] + language Essence 1.3 + + letting MYTYPE be domain int(1..5) + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that y = image(p, x) + +[typeCheckModel] + language Essence 1.3 + + letting MYTYPE be domain int(1..5) + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that y = image(p, x) + +[input] + language Essence 1.3 + + letting MYTYPE be new type enum {THING1, THING2, THING3, THING4, THING5} + letting p be permutation((THING3, THING4)) + find x: relation (size 4) of (MYTYPE * MYTYPE) + find y: relation (size 4) of (MYTYPE * MYTYPE) + such that y = image(p, x) + +[addSearchOrder] + language Essence 1.3 + + letting MYTYPE be new type enum {THING1, THING2, THING3, THING4, THING5} + letting p be permutation((THING3, THING4)) + find x: relation (size 4) of (MYTYPE * MYTYPE) + find y: relation (size 4) of (MYTYPE * MYTYPE) + such that y = image(p, x) + branching on [x, y] + +[attributeAsConstraints] + language Essence 1.3 + + letting MYTYPE be new type enum {THING1, THING2, THING3, THING4, THING5} + letting p be permutation((THING3, THING4)) + find x: relation (size 4) of (MYTYPE * MYTYPE) + find y: relation (size 4) of (MYTYPE * MYTYPE) + such that y = image(p, x) + branching on [x, y] + +[inferAttributes] + language Essence 1.3 + + letting MYTYPE be new type enum {THING1, THING2, THING3, THING4, THING5} + letting p be permutation((THING3, THING4)) + find x: relation (size 4) of (MYTYPE * MYTYPE) + find y: relation (size 4) of (MYTYPE * MYTYPE) + such that y = image(p, x) + branching on [x, y] + +[inlineLettingDomainsForDecls] + language Essence 1.3 + + letting MYTYPE be new type enum {THING1, THING2, THING3, THING4, THING5} + letting p be permutation((THING3, THING4)) + find x: relation (size 4) of (MYTYPE * MYTYPE) + find y: relation (size 4) of (MYTYPE * MYTYPE) + such that y = image(p, x) + branching on [x, y] + +[lettingsForComplexInDoms] + language Essence 1.3 + + letting MYTYPE be new type enum {THING1, THING2, THING3, THING4, THING5} + letting p be permutation((THING3, THING4)) + find x: relation (size 4) of (MYTYPE * MYTYPE) + find y: relation (size 4) of (MYTYPE * MYTYPE) + such that y = image(p, x) + branching on [x, y] + +[distinctQuantifiedVars] + language Essence 1.3 + + letting MYTYPE be new type enum {THING1, THING2, THING3, THING4, THING5} + letting p be permutation((THING3, THING4)) + find x: relation (size 4) of (MYTYPE * MYTYPE) + find y: relation (size 4) of (MYTYPE * MYTYPE) + such that y = image(p, x) + branching on [x, y] + +[initInfo] + language Essence 1.3 + + letting MYTYPE be new type enum {THING1, THING2, THING3, THING4, THING5} + letting p be permutation((THING3, THING4)) + find x: relation (size 4) of (MYTYPE * MYTYPE) + find y: relation (size 4) of (MYTYPE * MYTYPE) + such that y = image(p, x) + branching on [x, y] + +[removeUnnamedsFromModel] + language Essence 1.3 + + letting MYTYPE be new type enum {THING1, THING2, THING3, THING4, THING5} + letting p be permutation((THING3, THING4)) + find x: relation (size 4) of (MYTYPE * MYTYPE) + find y: relation (size 4) of (MYTYPE * MYTYPE) + such that y = image(p, x) + branching on [x, y] + +Recording enumGivens: +[removeEnumsFromModel] + language Essence 1.3 + + letting MYTYPE be domain int(1..5) + letting p be permutation((3, 4)) + find x: relation (size 4) of (MYTYPE * MYTYPE) + find y: relation (size 4) of (MYTYPE * MYTYPE) + such that y = image(p, x) + branching on [x, y] + +[finiteGivens] + language Essence 1.3 + + letting MYTYPE be domain int(1..5) + letting p be permutation((3, 4)) + find x: relation (size 4) of (MYTYPE * MYTYPE) + find y: relation (size 4) of (MYTYPE * MYTYPE) + such that y = image(p, x) + branching on [x, y] + +[resolveNames] + language Essence 1.3 + + letting MYTYPE be domain int(1..5) + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that y = image(p, x) + branching on [x, y] + +[initInfo_Lettings] + language Essence 1.3 + + letting MYTYPE be domain int(1..5) + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that y = image(p, x) + branching on [x, y] + +[removeDomainLettings] + language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that y = image(p, x) + branching on [x, y] + +[typeCheckModel] + language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that y = image(p, x) + branching on [x, y] + +[categoryChecking] + language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that y = image(p, x) + branching on [x, y] + +[sanityChecks] + language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that y = image(p, x) + branching on [x, y] + +[dealWithCuts] + language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that y = image(p, x) + branching on [x, y] + such that + +[removeExtraSlices] + language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that y = image(p, x) + branching on [x, y] + such that + +[addTrueConstraints] + language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that y = image(p, x) + branching on [x, y] + such that + such that + true(x), + true(y) + +Contains 0 parameters (0 abstract) + 2 decision variables (2 abstract) +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that y = image(p, x) + branching on [x, y] + such that + such that + true(x), + true(y) + +Picking the first option: Question 1: permutation((3, 4)) +Picking the only option: Answer 1: full-evaluate: Full evaluator + permutation((3, 4)) +storedChoice: +permutation((3, 4)) -604127175528974338 +AnsweredRule {qHole_ = -604127175528974338, qAscendants_ = fromList [], aRuleName_ = "full-evaluate"} +LF: {"AnsweredRule":{"aRuleName_":"full-evaluate","qAscendants_":[],"qHole_":-604127175528974338}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that y = image(p, x) + branching on [x, y] + such that + such that + true(x), + true(y) + +Picking the first option: Question 1: p + Context #1: image(p, x) +Picking the only option: Answer 1: full-evaluate: Full evaluator + permutation((3, 4)) +storedChoice: +p -7234408895829330219 +AnsweredRule {qHole_ = -7234408895829330219, qAscendants_ = fromList [-7340749217212310711,-5834110796085551311], aRuleName_ = "full-evaluate"} +LF: {"AnsweredRule":{"aRuleName_":"full-evaluate","qAscendants_":[-7340749217212310711,-5834110796085551311],"qHole_":-7234408895829330219}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that y = image(permutation((3, 4)), x) + branching on [x, y] + such that + such that + true(x), + true(y) + +Picking the first option: Question 1: x + Context #1: image(permutation((3, 4)), x) +Picking the only option: Answer 1: choose-repr: Choosing representation for x: + relation {RelationAsMatrix} (size 4) of (int(1..5) * int(1..5)) + x +storedChoice: +x -7234408895963551171 +AnsweredReprStored {qHole_ = -7234408895963551171, qAscendants_ = fromList [-7111069252946253414,-6043361806322913446], aDomStored_ = "relation {RelationAsMatrix} (size 4) of (int(1..5) * int(1..5))", aRuleName_ = "choose-repr"} +LF: {"AnsweredReprStored":{"aDomStored_":"relation {RelationAsMatrix} (size 4) of (int(1..5) * int(1..5))","aRuleName_":"choose-repr","qAscendants_":[-7111069252946253414,-6043361806322913446],"qHole_":-7234408895963551171}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that y = image(permutation((3, 4)), x) + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + +Picking the first option: Question 1: y + Context #1: y = image(permutation((3, 4)), x) +Picking the only option: Answer 1: choose-repr: Choosing representation for y: + relation {RelationAsMatrix} (size 4) of (int(1..5) * int(1..5)) + y +storedChoice: +y -7234408895946773554 +AnsweredReprStored {qHole_ = -7234408895946773554, qAscendants_ = fromList [-7111069252946253414], aDomStored_ = "relation {RelationAsMatrix} (size 4) of (int(1..5) * int(1..5))", aRuleName_ = "choose-repr"} +LF: {"AnsweredReprStored":{"aDomStored_":"relation {RelationAsMatrix} (size 4) of (int(1..5) * int(1..5))","aRuleName_":"choose-repr","qAscendants_":[-7111069252946253414],"qHole_":-7234408895946773554}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that y = image(permutation((3, 4)), x) + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: x + Context #1: true(x) +Picking the only option: Answer 1: choose-repr: Choosing representation for x: + relation {RelationAsMatrix} (size 4) of (int(1..5) * int(1..5)) + x +storedChoice: +x -7234408895963551171 +AnsweredReprStored {qHole_ = -7234408895963551171, qAscendants_ = fromList [-1508832156878423928], aDomStored_ = "relation {RelationAsMatrix} (size 4) of (int(1..5) * int(1..5))", aRuleName_ = "choose-repr"} +LF: {"AnsweredReprStored":{"aDomStored_":"relation {RelationAsMatrix} (size 4) of (int(1..5) * int(1..5))","aRuleName_":"choose-repr","qAscendants_":[-1508832156878423928],"qHole_":-7234408895963551171}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that y = image(permutation((3, 4)), x) + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: y + Context #1: true(y) +Picking the only option: Answer 1: choose-repr: Choosing representation for y: + relation {RelationAsMatrix} (size 4) of (int(1..5) * int(1..5)) + y +storedChoice: +y -7234408895946773554 +AnsweredReprStored {qHole_ = -7234408895946773554, qAscendants_ = fromList [-1508550667338902379], aDomStored_ = "relation {RelationAsMatrix} (size 4) of (int(1..5) * int(1..5))", aRuleName_ = "choose-repr"} +LF: {"AnsweredReprStored":{"aDomStored_":"relation {RelationAsMatrix} (size 4) of (int(1..5) * int(1..5))","aRuleName_":"choose-repr","qAscendants_":[-1508550667338902379],"qHole_":-7234408895946773554}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that y = image(permutation((3, 4)), x) + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: [sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)] + Context #1: sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) +Picking the only option: Answer 1: choose-repr-for-comprehension: Choosing representation for quantified variable q1 (with type: int) + [sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)] +storedChoice: +[sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)] 6263396600925448594 +AnsweredRule {qHole_ = 6263396600925448594, qAscendants_ = fromList [5049395136776340146,5865511705196666561], aRuleName_ = "choose-repr-for-comprehension"} +LF: {"AnsweredRule":{"aRuleName_":"choose-repr-for-comprehension","qAscendants_":[5049395136776340146,5865511705196666561],"qHole_":6263396600925448594}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that y = image(permutation((3, 4)), x) + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: [toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)] + Context #1: sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) +Picking the only option: Answer 1: choose-repr-for-comprehension: Choosing representation for quantified variable q2 (with type: int) + [toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)] +storedChoice: +[toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)] 7855671108991671235 +AnsweredRule {qHole_ = 7855671108991671235, qAscendants_ = fromList [5049395136776340146,5865511705196666561,6263396600925448594,7085372780514568240], aRuleName_ = "choose-repr-for-comprehension"} +LF: {"AnsweredRule":{"aRuleName_":"choose-repr-for-comprehension","qAscendants_":[5049395136776340146,5865511705196666561,6263396600925448594,7085372780514568240],"qHole_":7855671108991671235}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that y = image(permutation((3, 4)), x) + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: [sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)] + Context #1: sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) +Picking the only option: Answer 1: choose-repr-for-comprehension: Choosing representation for quantified variable q3 (with type: int) + [sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)] +storedChoice: +[sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)] -3620919297952344383 +AnsweredRule {qHole_ = -3620919297952344383, qAscendants_ = fromList [-5513655157779400708,7219712989341858895], aRuleName_ = "choose-repr-for-comprehension"} +LF: {"AnsweredRule":{"aRuleName_":"choose-repr-for-comprehension","qAscendants_":[-5513655157779400708,7219712989341858895],"qHole_":-3620919297952344383}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that y = image(permutation((3, 4)), x) + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: [toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)] + Context #1: sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) +Picking the only option: Answer 1: choose-repr-for-comprehension: Choosing representation for quantified variable q4 (with type: int) + [toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)] +storedChoice: +[toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)] -2356590267706027710 +AnsweredRule {qHole_ = -2356590267706027710, qAscendants_ = fromList [-5513655157779400708,-3620919297952344383,7219712989341858895,8125267169441206107], aRuleName_ = "choose-repr-for-comprehension"} +LF: {"AnsweredRule":{"aRuleName_":"choose-repr-for-comprehension","qAscendants_":[-5513655157779400708,-3620919297952344383,7219712989341858895,8125267169441206107],"qHole_":-2356590267706027710}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that y = image(permutation((3, 4)), x) + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: image(permutation((3, 4)), x) + Context #1: y = image(permutation((3, 4)), x) +Picking the only option: Answer 1: relation-image: Horizontal rule for image relation in comprehension + { conjure_aux1 + @ find conjure_aux1: relation (size 4) of (int(1..5) * int(1..5)) + such that |x| = |conjure_aux1| /\ and([image(permutation((3, 4)), q5) in conjure_aux1 | q5 <- x]) + } +storedChoice: +image(permutation((3, 4)), x) -6043361806322913446 +AnsweredRule {qHole_ = -6043361806322913446, qAscendants_ = fromList [-7111069252946253414], aRuleName_ = "relation-image"} +LF: {"AnsweredRule":{"aRuleName_":"relation-image","qAscendants_":[-7111069252946253414],"qHole_":-6043361806322913446}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1: relation (size 4) of (int(1..5) * int(1..5)) + such that |x| = |conjure_aux1| /\ and([image(permutation((3, 4)), q5) in conjure_aux1 | q5 <- x]) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: { conjure_aux1 + @ find conjure_aux1: relation (size 4) of (int(1..5) * int(1..5)) + such that |x| = |conjure_aux1| /\ and([image(permutation((3, 4)), q5) in conjure_aux1 | q5 <- x]) + } + Context #1: y = + { conjure_aux1 + @ find conjure_aux1: relation (size 4) of (int(1..5) * int(1..5)) + such that |x| = |conjure_aux1| /\ and([image(permutation((3, 4)), q5) in conjure_aux1 | q5 <- x]) + } +Picking the only option: Answer 1: choose-repr-for-locals: Choosing representation for local variable conjure_aux1 + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that |x| = |conjure_aux1| /\ and([image(permutation((3, 4)), q5) in conjure_aux1 | q5 <- x]) + } +storedChoice: +{ conjure_aux1 +@ find conjure_aux1: relation (size 4) of (int(1..5) * int(1..5)) + such that |x| = |conjure_aux1| /\ and([image(permutation((3, 4)), q5) in conjure_aux1 | q5 <- x]) +} 1714623876200418132 +AnsweredRule {qHole_ = 1714623876200418132, qAscendants_ = fromList [5536329259437519582], aRuleName_ = "choose-repr-for-locals"} +LF: {"AnsweredRule":{"aRuleName_":"choose-repr-for-locals","qAscendants_":[5536329259437519582],"qHole_":1714623876200418132}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that |x| = |conjure_aux1| /\ and([image(permutation((3, 4)), q5) in conjure_aux1 | q5 <- x]) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: [sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)] + Context #1: sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) +Picking the only option: Answer 1: choose-repr-for-comprehension: Choosing representation for quantified variable q6 (with type: int) + [sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)] +storedChoice: +[sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)] -878601234175159627 +AnsweredRule {qHole_ = -878601234175159627, qAscendants_ = fromList [-5775367836057753714,-1245214478984509661,79132428954328345,1049837485042621691], aRuleName_ = "choose-repr-for-comprehension"} +LF: {"AnsweredRule":{"aRuleName_":"choose-repr-for-comprehension","qAscendants_":[-5775367836057753714,-1245214478984509661,79132428954328345,1049837485042621691],"qHole_":-878601234175159627}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that |x| = |conjure_aux1| /\ and([image(permutation((3, 4)), q5) in conjure_aux1 | q5 <- x]) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: [toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)] + Context #1: sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) +Picking the only option: Answer 1: choose-repr-for-comprehension: Choosing representation for quantified variable q7 (with type: int) + [toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)] +storedChoice: +[toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)] 2379582110528111197 +AnsweredRule {qHole_ = 2379582110528111197, qAscendants_ = fromList [-5775367836057753714,-1245214478984509661,-878601234175159627,79132428954328345,1049837485042621691,4483484998279672051], aRuleName_ = "choose-repr-for-comprehension"} +LF: {"AnsweredRule":{"aRuleName_":"choose-repr-for-comprehension","qAscendants_":[-5775367836057753714,-1245214478984509661,-878601234175159627,79132428954328345,1049837485042621691,4483484998279672051],"qHole_":2379582110528111197}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that |x| = |conjure_aux1| /\ and([image(permutation((3, 4)), q5) in conjure_aux1 | q5 <- x]) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: [image(permutation((3, 4)), q5) in conjure_aux1 | q5 <- x] + Context #1: and([image(permutation((3, 4)), q5) in conjure_aux1 | q5 <- x]) +Picking the only option: Answer 1: relation-map_in_expr{RelationAsMatrix}: Vertical rule for map_in_expr for relation domains, RelationAsMatrix representation. + [image(permutation((3, 4)), (q8[1], q8[2])) in conjure_aux1 | q8 : (int(1..5), int(1..5)), x_RelationAsMatrix[q8[1], q8[2]]] +storedChoice: +[image(permutation((3, 4)), q5) in conjure_aux1 | q5 <- x] 2569794631160861273 +AnsweredRule {qHole_ = 2569794631160861273, qAscendants_ = fromList [-4776664362067532454,-1245214478984509661,-1036657270873470960,79132428954328345,5830139973578569810], aRuleName_ = "relation-map_in_expr{RelationAsMatrix}"} +LF: {"AnsweredRule":{"aRuleName_":"relation-map_in_expr{RelationAsMatrix}","qAscendants_":[-4776664362067532454,-1245214478984509661,-1036657270873470960,79132428954328345,5830139973578569810],"qHole_":2569794631160861273}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([image(permutation((3, 4)), (q8[1], q8[2])) in conjure_aux1 | q8 : (int(1..5), int(1..5)), x_RelationAsMatrix[q8[1], q8[2]]]) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: [image(permutation((3, 4)), (q8[1], q8[2])) in conjure_aux1 + | q8 : (int(1..5), int(1..5)), x_RelationAsMatrix[q8[1], q8[2]]] + Context #1: and([image(permutation((3, 4)), (q8[1], q8[2])) in conjure_aux1 + | q8 : (int(1..5), int(1..5)), x_RelationAsMatrix[q8[1], q8[2]]]) +Picking the only option: Answer 1: choose-repr-for-comprehension: Choosing representation for quantified variable q8 (with type: (int, + int)) + [image(permutation((3, 4)), (q8[1], q8[2])) in conjure_aux1 | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]] +storedChoice: +[image(permutation((3, 4)), (q8[1], q8[2])) in conjure_aux1 + | q8 : (int(1..5), int(1..5)), x_RelationAsMatrix[q8[1], q8[2]]] -6121410142271556240 +AnsweredRule {qHole_ = -6121410142271556240, qAscendants_ = fromList [-8542780548609610841,-2372866271326699518,-688805377682383984,1829424135801856670,4203509818187934421], aRuleName_ = "choose-repr-for-comprehension"} +LF: {"AnsweredRule":{"aRuleName_":"choose-repr-for-comprehension","qAscendants_":[-8542780548609610841,-2372866271326699518,-688805377682383984,1829424135801856670,4203509818187934421],"qHole_":-6121410142271556240}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([image(permutation((3, 4)), (q8[1], q8[2])) in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: image(permutation((3, 4)), (q8[1], q8[2])) + Context #1: image(permutation((3, 4)), (q8[1], q8[2])) in conjure_aux1 +Picking the only option: Answer 1: tuple-image: Horizontal rule for image tuple in comprehension + { conjure_aux2 + @ find conjure_aux2: (int(1..5), int(1..5)) + such that conjure_aux2[1] = image(permutation((3, 4)), (q8[1], q8[2])[1]) + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } +storedChoice: +image(permutation((3, 4)), (q8[1], q8[2])) 7641797427128728383 +AnsweredRule {qHole_ = 7641797427128728383, qAscendants_ = fromList [-6118234929664435696,-1399392580596120430,-1387706708486858898,-1208703870972871253,-742133995496027829,4437220630107512706,5070918677941821273], aRuleName_ = "tuple-image"} +LF: {"AnsweredRule":{"aRuleName_":"tuple-image","qAscendants_":[-6118234929664435696,-1399392580596120430,-1387706708486858898,-1208703870972871253,-742133995496027829,4437220630107512706,5070918677941821273],"qHole_":7641797427128728383}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2: (int(1..5), int(1..5)) + such that conjure_aux2[1] = image(permutation((3, 4)), (q8[1], q8[2])[1]) + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: { conjure_aux2 + @ find conjure_aux2: (int(1..5), int(1..5)) + such that conjure_aux2[1] = image(permutation((3, 4)), (q8[1], q8[2])[1]) + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + Context #1: { conjure_aux2 + @ find conjure_aux2: (int(1..5), int(1..5)) + such that conjure_aux2[1] = image(permutation((3, 4)), (q8[1], q8[2])[1]) + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 +Picking the only option: Answer 1: choose-repr-for-locals: Choosing representation for local variable conjure_aux2 + { conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that conjure_aux2[1] = image(permutation((3, 4)), (q8[1], q8[2])[1]) + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } +storedChoice: +{ conjure_aux2 +@ find conjure_aux2: (int(1..5), int(1..5)) + such that conjure_aux2[1] = image(permutation((3, 4)), (q8[1], q8[2])[1]) + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) +} 7832450608952021018 +AnsweredRule {qHole_ = 7832450608952021018, qAscendants_ = fromList [-4717314876217502109,-4294582922489450379,1651264905194084305,2977457561748621690,4087019737558016944,5019534480518702783,6820345709468359473], aRuleName_ = "choose-repr-for-locals"} +LF: {"AnsweredRule":{"aRuleName_":"choose-repr-for-locals","qAscendants_":[-4717314876217502109,-4294582922489450379,1651264905194084305,2977457561748621690,4087019737558016944,5019534480518702783,6820345709468359473],"qHole_":7832450608952021018}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that conjure_aux2[1] = image(permutation((3, 4)), (q8[1], q8[2])[1]) + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: conjure_aux2[1] + Context #1: conjure_aux2[1] = image(permutation((3, 4)), (q8[1], q8[2])[1]) +Picking the only option: Answer 1: tuple-index: Tuple indexing on: conjure_aux2[1] + conjure_aux2_1 +storedChoice: +conjure_aux2[1] 2042848205583864547 +AnsweredRule {qHole_ = 2042848205583864547, qAscendants_ = fromList [-7836606021998938252,-4083899676628141502,-3337431591692655861,-1871379374487492755,31163859450310923,347176683161250196,1078578095348213584,3723112517704369347,8818185052449544140], aRuleName_ = "tuple-index"} +LF: {"AnsweredRule":{"aRuleName_":"tuple-index","qAscendants_":[-7836606021998938252,-4083899676628141502,-3337431591692655861,-1871379374487492755,31163859450310923,347176683161250196,1078578095348213584,3723112517704369347,8818185052449544140],"qHole_":2042848205583864547}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that conjure_aux2_1 = image(permutation((3, 4)), (q8[1], q8[2])[1]) + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: (q8[1], q8[2])[1] + Context #1: image(permutation((3, 4)), (q8[1], q8[2])[1]) +Picking the only option: Answer 1: tuple-index: Tuple indexing on: (q8[1], q8[2])[1] + q8[1] +storedChoice: +(q8[1], q8[2])[1] -5501922928837560372 +AnsweredRule {qHole_ = -5501922928837560372, qAscendants_ = fromList [-8079003502337880871,-5992757738829033069,-4052786222025792276,-4045994663639704708,-1887930543228865818,2614825847120268012,2969550575619082812,4897364746913734457,7503648025096004321,8070588202073729915], aRuleName_ = "tuple-index"} +LF: {"AnsweredRule":{"aRuleName_":"tuple-index","qAscendants_":[-8079003502337880871,-5992757738829033069,-4052786222025792276,-4045994663639704708,-1887930543228865818,2614825847120268012,2969550575619082812,4897364746913734457,7503648025096004321,8070588202073729915],"qHole_":-5501922928837560372}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that conjure_aux2_1 = image(permutation((3, 4)), q8[1]) + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: q8[1] + Context #1: image(permutation((3, 4)), q8[1]) +Picking the only option: Answer 1: tuple-index: Tuple indexing on: q8[1] + q8_1 +storedChoice: +q8[1] 6051865069970393497 +AnsweredRule {qHole_ = 6051865069970393497, qAscendants_ = fromList [-6240564754428641774,-3828924106000349868,-2497616537930163555,-2455337427536589680,-1546470019878997061,409221243111017286,1096079797629796883,1353067250173028676,4249511820642706384,6954638962073438443], aRuleName_ = "tuple-index"} +LF: {"AnsweredRule":{"aRuleName_":"tuple-index","qAscendants_":[-6240564754428641774,-3828924106000349868,-2497616537930163555,-2455337427536589680,-1546470019878997061,409221243111017286,1096079797629796883,1353067250173028676,4249511820642706384,6954638962073438443],"qHole_":6051865069970393497}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that conjure_aux2_1 = image(permutation((3, 4)), q8_1) + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: image(permutation((3, 4)), q8_1) + Context #1: conjure_aux2_1 = image(permutation((3, 4)), q8_1) +Picking the only option: Answer 1: permutation-image-literal{AsFunction}: Horizontal rule for permutation literal application to a single value (image), AsFunction representation + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and([q9 = q8_1 <-> conjure_aux3 = q10 | (q9, q10) <- [(3, 4), (4, 3); int(1..2)]]) /\ + (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) + } +storedChoice: +image(permutation((3, 4)), q8_1) -6565377216106402436 +AnsweredRule {qHole_ = -6565377216106402436, qAscendants_ = fromList [-8683446058401842621,-8501667396727033866,-6589174251984098358,-5196229448616722462,-2562107481961042620,-1290778481550223845,5400239128163960843,7319032080622836357,8711639898256895276], aRuleName_ = "permutation-image-literal{AsFunction}"} +LF: {"AnsweredRule":{"aRuleName_":"permutation-image-literal{AsFunction}","qAscendants_":[-8683446058401842621,-8501667396727033866,-6589174251984098358,-5196229448616722462,-2562107481961042620,-1290778481550223845,5400239128163960843,7319032080622836357,8711639898256895276],"qHole_":-6565377216106402436}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and([q9 = q8_1 <-> conjure_aux3 = q10 | (q9, q10) <- [(3, 4), (4, 3); int(1..2)]]) /\ + (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: [(3, 4), (4, 3); int(1..2)] + Context #1: [q9 = q8_1 <-> conjure_aux3 = q10 | (q9, q10) <- [(3, 4), (4, 3); int(1..2)]] +Picking the only option: Answer 1: full-evaluate: Full evaluator + [(3, 4), (4, 3); int(1..2)] +storedChoice: +[(3, 4), (4, 3); int(1..2)] 6597397470067790033 +AnsweredRule {qHole_ = 6597397470067790033, qAscendants_ = fromList [-8621354921797967448,-6160248818055544346,-6049820697610812758,-4894284809815571873,-4858508204008314707,-4635274203177452231,-1665058964617223774,996353907888938120,1107585814561782716,1593343993162845666,1994644797538381771,2641311773319376803,3730217346423440641,5862930277568425410], aRuleName_ = "full-evaluate"} +LF: {"AnsweredRule":{"aRuleName_":"full-evaluate","qAscendants_":[-8621354921797967448,-6160248818055544346,-6049820697610812758,-4894284809815571873,-4858508204008314707,-4635274203177452231,-1665058964617223774,996353907888938120,1107585814561782716,1593343993162845666,1994644797538381771,2641311773319376803,3730217346423440641,5862930277568425410],"qHole_":6597397470067790033}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and([q9 = q8_1 <-> conjure_aux3 = q10 | (q9, q10) <- [(3, 4), (4, 3); int(1..2)]]) /\ + (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: [q9 = q8_1 <-> conjure_aux3 = q10 | (q9, q10) <- [(3, 4), (4, 3); int(1..2)]] + Context #1: and([q9 = q8_1 <-> conjure_aux3 = q10 | (q9, q10) <- [(3, 4), (4, 3); int(1..2)]]) +Picking the only option: Answer 1: complex-pattern: complex pattern on tuple patterns + [q13[1] = q8_1 <-> conjure_aux3 = q13[2] | q13 <- [(3, 4), (4, 3); int(1..2)]] +storedChoice: +[q9 = q8_1 <-> conjure_aux3 = q10 | (q9, q10) <- [(3, 4), (4, 3); int(1..2)]] 996353907888938120 +AnsweredRule {qHole_ = 996353907888938120, qAscendants_ = fromList [-8621354921797967448,-6160248818055544346,-6049820697610812758,-4894284809815571873,-4858508204008314707,-4635274203177452231,-1665058964617223774,1107585814561782716,1593343993162845666,1994644797538381771,2641311773319376803,3730217346423440641,5862930277568425410], aRuleName_ = "complex-pattern"} +LF: {"AnsweredRule":{"aRuleName_":"complex-pattern","qAscendants_":[-8621354921797967448,-6160248818055544346,-6049820697610812758,-4894284809815571873,-4858508204008314707,-4635274203177452231,-1665058964617223774,1107585814561782716,1593343993162845666,1994644797538381771,2641311773319376803,3730217346423440641,5862930277568425410],"qHole_":996353907888938120}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and([q13[1] = q8_1 <-> conjure_aux3 = q13[2] | q13 <- [(3, 4), (4, 3); int(1..2)]]) /\ + (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: [q13[1] = q8_1 <-> conjure_aux3 = q13[2] | q13 <- [(3, 4), (4, 3); int(1..2)]] + Context #1: and([q13[1] = q8_1 <-> conjure_aux3 = q13[2] | q13 <- [(3, 4), (4, 3); int(1..2)]]) +Picking the only option: Answer 1: matrix-comprehension-literal: Vertical rule for matrix-comprehension on matrix literal + flatten(1, + [[q13[1] = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (3, 4)], + [q13[1] = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (4, 3)]; + int(1..2)]) +storedChoice: +[q13[1] = q8_1 <-> conjure_aux3 = q13[2] | q13 <- [(3, 4), (4, 3); int(1..2)]] 3456861798216985162 +AnsweredRule {qHole_ = 3456861798216985162, qAscendants_ = fromList [-8808315865059383030,-8227483119145124211,-7793095449913038876,-5679502255425066053,-3572216896086163269,-3021143752573374113,-2561056581393168238,-842750970546105960,3371366859945964624,5522715912807809257,6264069036653869010,7196566142350255202,8156173651558168583], aRuleName_ = "matrix-comprehension-literal"} +LF: {"AnsweredRule":{"aRuleName_":"matrix-comprehension-literal","qAscendants_":[-8808315865059383030,-8227483119145124211,-7793095449913038876,-5679502255425066053,-3572216896086163269,-3021143752573374113,-2561056581393168238,-842750970546105960,3371366859945964624,5522715912807809257,6264069036653869010,7196566142350255202,8156173651558168583],"qHole_":3456861798216985162}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, + [[q13[1] = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (3, 4)], + [q13[1] = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (4, 3)]; + int(1..2)])) + /\ (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: q13[1] + Context #1: q13[1] = q8_1 +Picking the only option: Answer 1: full-evaluate: Full evaluator + 3 +storedChoice: +q13[1] -1254902052079317740 +AnsweredRule {qHole_ = -1254902052079317740, qAscendants_ = fromList [-7844826506044189197,-6543998516580374433,-5468160839539146108,-4646329838907093569,-4421494240673914403,-4030269164244882685,-3696611495810109143,-3345198454859526376,-2923685885462842550,-2579765278873905792,-2489053689031557395,-2037117675633093401,-1199749775392010500,-1159821892128975232,-61377228416248265,964892601978301791,3910121320990104243,4511388692183383834], aRuleName_ = "full-evaluate"} +LF: {"AnsweredRule":{"aRuleName_":"full-evaluate","qAscendants_":[-7844826506044189197,-6543998516580374433,-5468160839539146108,-4646329838907093569,-4421494240673914403,-4030269164244882685,-3696611495810109143,-3345198454859526376,-2923685885462842550,-2579765278873905792,-2489053689031557395,-2037117675633093401,-1199749775392010500,-1159821892128975232,-61377228416248265,964892601978301791,3910121320990104243,4511388692183383834],"qHole_":-1254902052079317740}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, + [[3 = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (3, 4)], [q13[1] = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (4, 3)]; + int(1..2)])) + /\ (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: q13[2] + Context #1: conjure_aux3 = q13[2] +Picking the only option: Answer 1: full-evaluate: Full evaluator + 4 +storedChoice: +q13[2] -1254620565291325713 +AnsweredRule {qHole_ = -1254620565291325713, qAscendants_ = fromList [-8360775170969626109,-8218634654132870929,-7641638248746524641,-4934801957947094136,-4254522952928052133,-4092969587983186253,-3780104048260027650,-2622265047463603714,-848316662104045049,563172654367211215,1222024046659559696,4078666449752848978,4662787952378127984,5249190568318080416,5574891365015849631,7061285353711906011,7866305697050141526,9112935851435552216], aRuleName_ = "full-evaluate"} +LF: {"AnsweredRule":{"aRuleName_":"full-evaluate","qAscendants_":[-8360775170969626109,-8218634654132870929,-7641638248746524641,-4934801957947094136,-4254522952928052133,-4092969587983186253,-3780104048260027650,-2622265047463603714,-848316662104045049,563172654367211215,1222024046659559696,4078666449752848978,4662787952378127984,5249190568318080416,5574891365015849631,7061285353711906011,7866305697050141526,9112935851435552216],"qHole_":-1254620565291325713}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, + [[3 = q8_1 <-> conjure_aux3 = 4 | letting q13 be (3, 4)], [q13[1] = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (4, 3)]; + int(1..2)])) + /\ (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: q13[1] + Context #1: q13[1] = q8_1 +Picking the only option: Answer 1: full-evaluate: Full evaluator + 4 +storedChoice: +q13[1] -1254902052079317740 +AnsweredRule {qHole_ = -1254902052079317740, qAscendants_ = fromList [-8638629789947627417,-7681680422406975063,-7045052392114671596,-5468160839539146108,-5360000098558189830,-5130716656066417701,-3536433963763386607,-3341254942655847808,-1332675206370029612,-61377228416248265,518672155518189655,1368815305078223764,1506712726218393853,2813413964084179331,4256368997522955231,6094767248156078778,6822727452915095676,7566490689068664978], aRuleName_ = "full-evaluate"} +LF: {"AnsweredRule":{"aRuleName_":"full-evaluate","qAscendants_":[-8638629789947627417,-7681680422406975063,-7045052392114671596,-5468160839539146108,-5360000098558189830,-5130716656066417701,-3536433963763386607,-3341254942655847808,-1332675206370029612,-61377228416248265,518672155518189655,1368815305078223764,1506712726218393853,2813413964084179331,4256368997522955231,6094767248156078778,6822727452915095676,7566490689068664978],"qHole_":-1254902052079317740}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, + [[3 = q8_1 <-> conjure_aux3 = 4 | letting q13 be (3, 4)], [4 = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (4, 3)]; int(1..2)])) + /\ (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: q13[2] + Context #1: conjure_aux3 = q13[2] +Picking the only option: Answer 1: full-evaluate: Full evaluator + 3 +storedChoice: +q13[2] -1254620565291325713 +AnsweredRule {qHole_ = -1254620565291325713, qAscendants_ = fromList [-8870698451967212431,-8218634654132870929,-8157916199347819983,-6958532007910279584,-4735583185965836928,-3733766703817256233,-1365219118307736560,-1326414908464043218,-756643065960997164,-238771092705033653,525451447959791552,2934402913780861128,4090216973995379955,4246953395184334158,4325482688218662469,4385767247150328058,4926105801959606859,4926669858781506740], aRuleName_ = "full-evaluate"} +LF: {"AnsweredRule":{"aRuleName_":"full-evaluate","qAscendants_":[-8870698451967212431,-8218634654132870929,-8157916199347819983,-6958532007910279584,-4735583185965836928,-3733766703817256233,-1365219118307736560,-1326414908464043218,-756643065960997164,-238771092705033653,525451447959791552,2934402913780861128,4090216973995379955,4246953395184334158,4325482688218662469,4385767247150328058,4926105801959606859,4926669858781506740],"qHole_":-1254620565291325713}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, + [[3 = q8_1 <-> conjure_aux3 = 4 | letting q13 be (3, 4)], [4 = q8_1 <-> conjure_aux3 = 3 | letting q13 be (4, 3)]; int(1..2)])) + /\ (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: [4 = q8_1 <-> conjure_aux3 = 3 | letting q13 be (4, 3)] + Context #1: [[3 = q8_1 <-> conjure_aux3 = 4 | letting q13 be (3, 4)], [4 = q8_1 <-> conjure_aux3 = 3 | letting q13 be (4, 3)]; + int(1..2)] +Picking the only option: Answer 1: generators-first: Inlining comprehension lettings. + [4 = q8_1 <-> conjure_aux3 = 3 |] +storedChoice: +[4 = q8_1 <-> conjure_aux3 = 3 | letting q13 be (4, 3)] 7815870421468516721 +AnsweredRule {qHole_ = 7815870421468516721, qAscendants_ = fromList [-7319924227898755161,-6204074559855855953,-5721547888581640964,-4667135429861035401,-3119038628659086386,-2914873009721382719,-275708737112837829,358797451837378,588328580564008008,1171576539747863800,3860402082075414220,5255108035061878259,7534557817041195235,8046872103256922185,9076826399099772257], aRuleName_ = "generators-first"} +LF: {"AnsweredRule":{"aRuleName_":"generators-first","qAscendants_":[-7319924227898755161,-6204074559855855953,-5721547888581640964,-4667135429861035401,-3119038628659086386,-2914873009721382719,-275708737112837829,358797451837378,588328580564008008,1171576539747863800,3860402082075414220,5255108035061878259,7534557817041195235,8046872103256922185,9076826399099772257],"qHole_":7815870421468516721}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4 | letting q13 be (3, 4)], [4 = q8_1 <-> conjure_aux3 = 3 |]; int(1..2)])) /\ + (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: [4 = q8_1 <-> conjure_aux3 = 3 |] + Context #1: [[3 = q8_1 <-> conjure_aux3 = 4 | letting q13 be (3, 4)], [4 = q8_1 <-> conjure_aux3 = 3 |]; int(1..2)] +Picking the only option: Answer 1: generators-first: Empty generators. + [4 = q8_1 <-> conjure_aux3 = 3; int(1)] +storedChoice: +[4 = q8_1 <-> conjure_aux3 = 3 |] 2538271587388693524 +AnsweredRule {qHole_ = 2538271587388693524, qAscendants_ = fromList [-8521000068701228812,-8466935177678778299,-8378067175040646304,-7795155064905057512,-7398425908569645990,-5020343327513684658,-1331085484917687815,-382563719840663416,1239306329275872739,3167048961433864186,4591749041469508459,5482352134908236922,5648481728193344963,6702522234416193183,8765316459520566910], aRuleName_ = "generators-first"} +LF: {"AnsweredRule":{"aRuleName_":"generators-first","qAscendants_":[-8521000068701228812,-8466935177678778299,-8378067175040646304,-7795155064905057512,-7398425908569645990,-5020343327513684658,-1331085484917687815,-382563719840663416,1239306329275872739,3167048961433864186,4591749041469508459,5482352134908236922,5648481728193344963,6702522234416193183,8765316459520566910],"qHole_":2538271587388693524}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4 | letting q13 be (3, 4)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: [3 = q8_1 <-> conjure_aux3 = 4 | letting q13 be (3, 4)] + Context #1: [[3 = q8_1 <-> conjure_aux3 = 4 | letting q13 be (3, 4)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)] +Picking the only option: Answer 1: generators-first: Inlining comprehension lettings. + [3 = q8_1 <-> conjure_aux3 = 4 |] +storedChoice: +[3 = q8_1 <-> conjure_aux3 = 4 | letting q13 be (3, 4)] 1317873634227795931 +AnsweredRule {qHole_ = 1317873634227795931, qAscendants_ = fromList [-6229747794032826968,-5833692553090476381,-4830840744837226265,-4695719515395703877,-1447797878088113254,-1026424407203100673,-114180086101386755,1230900640119672810,2384858822123183656,2641682090906853361,4932647657883680462,5503876696275907482,5561643139389034608,8062918047402720448,8618709991360516938], aRuleName_ = "generators-first"} +LF: {"AnsweredRule":{"aRuleName_":"generators-first","qAscendants_":[-6229747794032826968,-5833692553090476381,-4830840744837226265,-4695719515395703877,-1447797878088113254,-1026424407203100673,-114180086101386755,1230900640119672810,2384858822123183656,2641682090906853361,4932647657883680462,5503876696275907482,5561643139389034608,8062918047402720448,8618709991360516938],"qHole_":1317873634227795931}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4 |], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: [3 = q8_1 <-> conjure_aux3 = 4 |] + Context #1: [[3 = q8_1 <-> conjure_aux3 = 4 |], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)] +Picking the only option: Answer 1: generators-first: Empty generators. + [3 = q8_1 <-> conjure_aux3 = 4; int(1)] +storedChoice: +[3 = q8_1 <-> conjure_aux3 = 4 |] 7527005283398106432 +AnsweredRule {qHole_ = 7527005283398106432, qAscendants_ = fromList [-5151808191572404398,-4353286235323785771,-4339955062448219396,-4142041909263092979,-3736320932349712947,-3440388200198466301,-2029225889893250969,-1817262023712192284,-116834249900757749,483550512093615086,1497957860809309721,2283573903554163553,3854374349353612498,7382215623493355130,8339321953980948829], aRuleName_ = "generators-first"} +LF: {"AnsweredRule":{"aRuleName_":"generators-first","qAscendants_":[-5151808191572404398,-4353286235323785771,-4339955062448219396,-4142041909263092979,-3736320932349712947,-3440388200198466301,-2029225889893250969,-1817262023712192284,-116834249900757749,483550512093615086,1497957860809309721,2283573903554163553,3854374349353612498,7382215623493355130,8339321953980948829],"qHole_":7527005283398106432}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: [(3, 4), (4, 3); int(1..2)] + Context #1: [q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]] +Picking the only option: Answer 1: full-evaluate: Full evaluator + [(3, 4), (4, 3); int(1..2)] +storedChoice: +[(3, 4), (4, 3); int(1..2)] 6597397470067790033 +AnsweredRule {qHole_ = 6597397470067790033, qAscendants_ = fromList [-9213624152780173787,-5982135693274236766,-5396430067534345835,-2363572399258163690,-2255081376624876153,-320252043164433323,1280603170430058832,2648872121679578871,4076507060053755550,5033554600497872881,6390584767367481427,6475772422542545541,6480002864764397731,6871118355510909196,7049518756068236715,8591929121087659168], aRuleName_ = "full-evaluate"} +LF: {"AnsweredRule":{"aRuleName_":"full-evaluate","qAscendants_":[-9213624152780173787,-5982135693274236766,-5396430067534345835,-2363572399258163690,-2255081376624876153,-320252043164433323,1280603170430058832,2648872121679578871,4076507060053755550,5033554600497872881,6390584767367481427,6475772422542545541,6480002864764397731,6871118355510909196,7049518756068236715,8591929121087659168],"qHole_":6597397470067790033}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: [q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]] + Context #1: or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) +Picking the only option: Answer 1: complex-pattern: complex pattern on tuple patterns + [q14[1] = conjure_aux3 | q14 <- [(3, 4), (4, 3); int(1..2)]] +storedChoice: +[q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]] 5033554600497872881 +AnsweredRule {qHole_ = 5033554600497872881, qAscendants_ = fromList [-9213624152780173787,-5982135693274236766,-5396430067534345835,-2363572399258163690,-2255081376624876153,-320252043164433323,1280603170430058832,2648872121679578871,4076507060053755550,6390584767367481427,6475772422542545541,6480002864764397731,6871118355510909196,7049518756068236715,8591929121087659168], aRuleName_ = "complex-pattern"} +LF: {"AnsweredRule":{"aRuleName_":"complex-pattern","qAscendants_":[-9213624152780173787,-5982135693274236766,-5396430067534345835,-2363572399258163690,-2255081376624876153,-320252043164433323,1280603170430058832,2648872121679578871,4076507060053755550,6390584767367481427,6475772422542545541,6480002864764397731,6871118355510909196,7049518756068236715,8591929121087659168],"qHole_":5033554600497872881}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!or([q14[1] = conjure_aux3 | q14 <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: [q14[1] = conjure_aux3 | q14 <- [(3, 4), (4, 3); int(1..2)]] + Context #1: or([q14[1] = conjure_aux3 | q14 <- [(3, 4), (4, 3); int(1..2)]]) +Picking the only option: Answer 1: matrix-comprehension-literal: Vertical rule for matrix-comprehension on matrix literal + flatten(1, [[q14[1] = conjure_aux3 | letting q14 be (3, 4)], [q14[1] = conjure_aux3 | letting q14 be (4, 3)]; int(1..2)]) +storedChoice: +[q14[1] = conjure_aux3 | q14 <- [(3, 4), (4, 3); int(1..2)]] 8665374887955696009 +AnsweredRule {qHole_ = 8665374887955696009, qAscendants_ = fromList [-8790838049079552472,-7586671731712078955,-7257845330645731074,-6187411109644722069,-5035649525051787097,-4935714982215491801,-4790057621145645718,-2980197002499358476,-1690854938850194471,-619668906698634467,1003810935162304708,3378856114517929630,5359983985600686059,5489110086534554143,8428096257079881520], aRuleName_ = "matrix-comprehension-literal"} +LF: {"AnsweredRule":{"aRuleName_":"matrix-comprehension-literal","qAscendants_":[-8790838049079552472,-7586671731712078955,-7257845330645731074,-6187411109644722069,-5035649525051787097,-4935714982215491801,-4790057621145645718,-2980197002499358476,-1690854938850194471,-619668906698634467,1003810935162304708,3378856114517929630,5359983985600686059,5489110086534554143,8428096257079881520],"qHole_":8665374887955696009}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!or(flatten(1, [[q14[1] = conjure_aux3 | letting q14 be (3, 4)], [q14[1] = conjure_aux3 | letting q14 be (4, 3)]; int(1..2)])) <-> + conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: q14[1] + Context #1: q14[1] = conjure_aux3 +Picking the only option: Answer 1: full-evaluate: Full evaluator + 3 +storedChoice: +q14[1] -883253742927518753 +AnsweredRule {qHole_ = -883253742927518753, qAscendants_ = fromList [-9176123018977089417,-9101977553270866225,-9093406545418508012,-9026590884990837132,-7266038392684934735,-7030617368587845027,-6315177474832767189,-6185538668149951971,-5045957588695750237,-2422194591007956529,-2140558072442299093,-1323860184563866252,370104820105510026,1657237947942821584,1725179241386393490,3615940558330371386,6441285251735452902,7836445554474639282,8733492850970682893], aRuleName_ = "full-evaluate"} +LF: {"AnsweredRule":{"aRuleName_":"full-evaluate","qAscendants_":[-9176123018977089417,-9101977553270866225,-9093406545418508012,-9026590884990837132,-7266038392684934735,-7030617368587845027,-6315177474832767189,-6185538668149951971,-5045957588695750237,-2422194591007956529,-2140558072442299093,-1323860184563866252,370104820105510026,1657237947942821584,1725179241386393490,3615940558330371386,6441285251735452902,7836445554474639282,8733492850970682893],"qHole_":-883253742927518753}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!or(flatten(1, [[3 = conjure_aux3 | letting q14 be (3, 4)], [q14[1] = conjure_aux3 | letting q14 be (4, 3)]; int(1..2)])) <-> + conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: q14[1] + Context #1: q14[1] = conjure_aux3 +Picking the only option: Answer 1: full-evaluate: Full evaluator + 4 +storedChoice: +q14[1] -883253742927518753 +AnsweredRule {qHole_ = -883253742927518753, qAscendants_ = fromList [-8969758503132111487,-6784916903301812310,-4362502606594339694,-2424885897194395863,-2417099766119933872,-661357570700780995,659540462714969701,741299023684531871,841316382876489834,1080971480076294633,2455636718555289611,4781036327687591913,6314971418857005121,6957705147325524125,7520484523970872436,7814781884486080266,8472710336593287104,8733492850970682893,9124601515932951508], aRuleName_ = "full-evaluate"} +LF: {"AnsweredRule":{"aRuleName_":"full-evaluate","qAscendants_":[-8969758503132111487,-6784916903301812310,-4362502606594339694,-2424885897194395863,-2417099766119933872,-661357570700780995,659540462714969701,741299023684531871,841316382876489834,1080971480076294633,2455636718555289611,4781036327687591913,6314971418857005121,6957705147325524125,7520484523970872436,7814781884486080266,8472710336593287104,8733492850970682893,9124601515932951508],"qHole_":-883253742927518753}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!or(flatten(1, [[3 = conjure_aux3 | letting q14 be (3, 4)], [4 = conjure_aux3 | letting q14 be (4, 3)]; int(1..2)])) <-> + conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: [4 = conjure_aux3 | letting q14 be (4, 3)] + Context #1: [[3 = conjure_aux3 | letting q14 be (3, 4)], [4 = conjure_aux3 | letting q14 be (4, 3)]; int(1..2)] +Picking the only option: Answer 1: generators-first: Inlining comprehension lettings. + [4 = conjure_aux3 |] +storedChoice: +[4 = conjure_aux3 | letting q14 be (4, 3)] 5094133043100232579 +AnsweredRule {qHole_ = 5094133043100232579, qAscendants_ = fromList [-8909122354700020440,-7460733051808423716,-5113575940370069634,-3275789614875181527,-1485928817419295239,-1453326525258547920,-1190111094765899527,-425934852058965166,-227269000323710205,1017324948146570036,2402920626236815200,4379418785875775437,5239709721973149055,5447511985754467121,6138327529543829831,6983653976480365703,7190718169255452642], aRuleName_ = "generators-first"} +LF: {"AnsweredRule":{"aRuleName_":"generators-first","qAscendants_":[-8909122354700020440,-7460733051808423716,-5113575940370069634,-3275789614875181527,-1485928817419295239,-1453326525258547920,-1190111094765899527,-425934852058965166,-227269000323710205,1017324948146570036,2402920626236815200,4379418785875775437,5239709721973149055,5447511985754467121,6138327529543829831,6983653976480365703,7190718169255452642],"qHole_":5094133043100232579}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!or(flatten(1, [[3 = conjure_aux3 | letting q14 be (3, 4)], [4 = conjure_aux3 |]; int(1..2)])) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: [4 = conjure_aux3 |] + Context #1: [[3 = conjure_aux3 | letting q14 be (3, 4)], [4 = conjure_aux3 |]; int(1..2)] +Picking the only option: Answer 1: generators-first: Empty generators. + [4 = conjure_aux3; int(1)] +storedChoice: +[4 = conjure_aux3 |] 6112956542716486877 +AnsweredRule {qHole_ = 6112956542716486877, qAscendants_ = fromList [-9207305118438100391,-6369735332026353512,-5991924291783106431,-5776209435213632803,-3830978856990678993,-3641847297966420112,-338462998493300906,2767710529868660813,4005580531872772405,4397758740249101114,4804584669642102451,5890086814982925863,6459294084780550343,6686373777934096773,7031238571308724387,7962655793307038867,8888369891598567800], aRuleName_ = "generators-first"} +LF: {"AnsweredRule":{"aRuleName_":"generators-first","qAscendants_":[-9207305118438100391,-6369735332026353512,-5991924291783106431,-5776209435213632803,-3830978856990678993,-3641847297966420112,-338462998493300906,2767710529868660813,4005580531872772405,4397758740249101114,4804584669642102451,5890086814982925863,6459294084780550343,6686373777934096773,7031238571308724387,7962655793307038867,8888369891598567800],"qHole_":6112956542716486877}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!or(flatten(1, [[3 = conjure_aux3 | letting q14 be (3, 4)], [4 = conjure_aux3; int(1)]; int(1..2)])) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: [3 = conjure_aux3 | letting q14 be (3, 4)] + Context #1: [[3 = conjure_aux3 | letting q14 be (3, 4)], [4 = conjure_aux3; int(1)]; int(1..2)] +Picking the only option: Answer 1: generators-first: Inlining comprehension lettings. + [3 = conjure_aux3 |] +storedChoice: +[3 = conjure_aux3 | letting q14 be (3, 4)] 4832497823804752928 +AnsweredRule {qHole_ = 4832497823804752928, qAscendants_ = fromList [-6677145406315480965,-5384732204964843677,-3071059650417301550,-2603160466482895011,-2221619722341004417,-1557091775694725768,-1403621344696630627,711266062685662619,1333581340284470498,1611305677733360901,2753561903646462793,3866947117330481491,5332477917871449756,5559142600358984796,6001232326845461178,7602738452352881434,8088691831228319750], aRuleName_ = "generators-first"} +LF: {"AnsweredRule":{"aRuleName_":"generators-first","qAscendants_":[-6677145406315480965,-5384732204964843677,-3071059650417301550,-2603160466482895011,-2221619722341004417,-1557091775694725768,-1403621344696630627,711266062685662619,1333581340284470498,1611305677733360901,2753561903646462793,3866947117330481491,5332477917871449756,5559142600358984796,6001232326845461178,7602738452352881434,8088691831228319750],"qHole_":4832497823804752928}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!or(flatten(1, [[3 = conjure_aux3 |], [4 = conjure_aux3; int(1)]; int(1..2)])) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: [3 = conjure_aux3 |] + Context #1: [[3 = conjure_aux3 |], [4 = conjure_aux3; int(1)]; int(1..2)] +Picking the only option: Answer 1: generators-first: Empty generators. + [3 = conjure_aux3; int(1)] +storedChoice: +[3 = conjure_aux3 |] -185461686146028532 +AnsweredRule {qHole_ = -185461686146028532, qAscendants_ = fromList [-8289289739114023416,-8221845150149788696,-8019537499083765163,-7053954318911112143,-6092536859292112896,-4070943207855695476,-4028159753280221929,-3732495125634815821,-3238009362727088795,-282387919327309193,1775857482582255809,1882693949567706262,2362052944268224547,4832344585872237142,7445111209011732230,7705507659096261482,8654062028269091919], aRuleName_ = "generators-first"} +LF: {"AnsweredRule":{"aRuleName_":"generators-first","qAscendants_":[-8289289739114023416,-8221845150149788696,-8019537499083765163,-7053954318911112143,-6092536859292112896,-4070943207855695476,-4028159753280221929,-3732495125634815821,-3238009362727088795,-282387919327309193,1775857482582255809,1882693949567706262,2362052944268224547,4832344585872237142,7445111209011732230,7705507659096261482,8654062028269091919],"qHole_":-185461686146028532}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!or(flatten(1, [[3 = conjure_aux3; int(1)], [4 = conjure_aux3; int(1)]; int(1..2)])) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: or(flatten(1, [[3 = conjure_aux3; int(1)], [4 = conjure_aux3; int(1)]; int(1..2)])) + Context #1: !or(flatten(1, [[3 = conjure_aux3; int(1)], [4 = conjure_aux3; int(1)]; int(1..2)])) +Picking the only option: Answer 1: quantifier-shift3: Shifting quantifier inwards + or([3 = conjure_aux3; int(1)]) \/ or([4 = conjure_aux3; int(1)]) +storedChoice: +or(flatten(1, [[3 = conjure_aux3; int(1)], [4 = conjure_aux3; int(1)]; int(1..2)])) 6206761561595236625 +AnsweredRule {qHole_ = 6206761561595236625, qAscendants_ = fromList [-9091665958233421775,-8534800408556100581,-8389275971974927944,-7928483109077342673,-7581357772290646644,-7037234840397785533,-6263532840176792370,-5427006571018076668,-4431680199820092864,-4076541738995400933,-1064366526874994538,5387747797148225385,6292098423078440671,8420337927154511626], aRuleName_ = "quantifier-shift3"} +LF: {"AnsweredRule":{"aRuleName_":"quantifier-shift3","qAscendants_":[-9091665958233421775,-8534800408556100581,-8389275971974927944,-7928483109077342673,-7581357772290646644,-7037234840397785533,-6263532840176792370,-5427006571018076668,-4431680199820092864,-4076541738995400933,-1064366526874994538,5387747797148225385,6292098423078440671,8420337927154511626],"qHole_":6206761561595236625}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!(or([3 = conjure_aux3; int(1)]) \/ or([4 = conjure_aux3; int(1)])) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: or([3 = conjure_aux3; int(1)]) + Context #1: [or([3 = conjure_aux3; int(1)]), or([4 = conjure_aux3; int(1)]); int(1..2)] +Picking the only option: Answer 1: matrix-comprehension-singleton: Removing quantifier of a single item + 3 = conjure_aux3 +storedChoice: +or([3 = conjure_aux3; int(1)]) -3434962391173132894 +AnsweredRule {qHole_ = -3434962391173132894, qAscendants_ = fromList [-7235853985473547952,-6866498255018164123,-4960622746477117042,-4585543795134183636,-4105761649660625353,-3524766623875920799,-2347278582408429201,-1565913897093032045,-636316196669785718,259925545372009536,2634241883209911323,4718505660743647939,6517008955702082360,6653106233829268540,7728404530962223160,8536818627412251687], aRuleName_ = "matrix-comprehension-singleton"} +LF: {"AnsweredRule":{"aRuleName_":"matrix-comprehension-singleton","qAscendants_":[-7235853985473547952,-6866498255018164123,-4960622746477117042,-4585543795134183636,-4105761649660625353,-3524766623875920799,-2347278582408429201,-1565913897093032045,-636316196669785718,259925545372009536,2634241883209911323,4718505660743647939,6517008955702082360,6653106233829268540,7728404530962223160,8536818627412251687],"qHole_":-3434962391173132894}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!(3 = conjure_aux3 \/ or([4 = conjure_aux3; int(1)])) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: or([4 = conjure_aux3; int(1)]) + Context #1: [3 = conjure_aux3, or([4 = conjure_aux3; int(1)]); int(1..2)] +Picking the only option: Answer 1: matrix-comprehension-singleton: Removing quantifier of a single item + 4 = conjure_aux3 +storedChoice: +or([4 = conjure_aux3; int(1)]) 8578967638246734293 +AnsweredRule {qHole_ = 8578967638246734293, qAscendants_ = fromList [-7767892036023956761,-6284781492183215029,-1727905482554729427,-1356654288157906426,2281150997448020466,2372014189263015226,2446665452257606178,2838934993441470606,4742034938664987168,4756703484454204779,6116173103300050025,6542907600674666418,7911556895678534380,8081136239962017343,8569698893899834293,8949973037119072966], aRuleName_ = "matrix-comprehension-singleton"} +LF: {"AnsweredRule":{"aRuleName_":"matrix-comprehension-singleton","qAscendants_":[-7767892036023956761,-6284781492183215029,-1727905482554729427,-1356654288157906426,2281150997448020466,2372014189263015226,2446665452257606178,2838934993441470606,4742034938664987168,4756703484454204779,6116173103300050025,6542907600674666418,7911556895678534380,8081136239962017343,8569698893899834293,8949973037119072966],"qHole_":8578967638246734293}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: and(flatten(1, + [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) + Context #1: [and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])), + !(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1; + int(1..2)] +Picking the only option: Answer 1: quantifier-shift3: Shifting quantifier inwards + and([3 = q8_1 <-> conjure_aux3 = 4; int(1)]) /\ and([4 = q8_1 <-> conjure_aux3 = 3; int(1)]) +storedChoice: +and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) -2199657802844878530 +AnsweredRule {qHole_ = -2199657802844878530, qAscendants_ = fromList [-8444650881280502798,-8271565969096831831,-6564446395948378541,-3553121516791984732,-3091505528568185300,-28537057046234944,2611036720111951620,3048392108732098635,4941408088135413888,6187348870363663871,6391218772456415880,9128754183040712545], aRuleName_ = "quantifier-shift3"} +LF: {"AnsweredRule":{"aRuleName_":"quantifier-shift3","qAscendants_":[-8444650881280502798,-8271565969096831831,-6564446395948378541,-3553121516791984732,-3091505528568185300,-28537057046234944,2611036720111951620,3048392108732098635,4941408088135413888,6187348870363663871,6391218772456415880,9128754183040712545],"qHole_":-2199657802844878530}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + and([3 = q8_1 <-> conjure_aux3 = 4; int(1)]) /\ and([4 = q8_1 <-> conjure_aux3 = 3; int(1)]) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: and([3 = q8_1 <-> conjure_aux3 = 4; int(1)]) + Context #1: [and([3 = q8_1 <-> conjure_aux3 = 4; int(1)]), and([4 = q8_1 <-> conjure_aux3 = 3; int(1)]); int(1..2)] +Picking the only option: Answer 1: matrix-comprehension-singleton: Removing quantifier of a single item + 3 = q8_1 <-> conjure_aux3 = 4 +storedChoice: +and([3 = q8_1 <-> conjure_aux3 = 4; int(1)]) -82084885825755383 +AnsweredRule {qHole_ = -82084885825755383, qAscendants_ = fromList [-7910416632419113217,-6789993106391976797,-6474394686920849630,-4532119084740741428,-4148488185654761721,-3872345874892611968,-3008944008775182264,-2299093800387471961,-1551233151285274759,-649051754905350518,1456233810038530873,2986022555450137983,3688733153117744851,8953876927154124061], aRuleName_ = "matrix-comprehension-singleton"} +LF: {"AnsweredRule":{"aRuleName_":"matrix-comprehension-singleton","qAscendants_":[-7910416632419113217,-6789993106391976797,-6474394686920849630,-4532119084740741428,-4148488185654761721,-3872345874892611968,-3008944008775182264,-2299093800387471961,-1551233151285274759,-649051754905350518,1456233810038530873,2986022555450137983,3688733153117744851,8953876927154124061],"qHole_":-82084885825755383}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ and([4 = q8_1 <-> conjure_aux3 = 3; int(1)]) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: and([4 = q8_1 <-> conjure_aux3 = 3; int(1)]) + Context #1: [3 = q8_1 <-> conjure_aux3 = 4, and([4 = q8_1 <-> conjure_aux3 = 3; int(1)]); int(1..2)] +Picking the only option: Answer 1: matrix-comprehension-singleton: Removing quantifier of a single item + 4 = q8_1 <-> conjure_aux3 = 3 +storedChoice: +and([4 = q8_1 <-> conjure_aux3 = 3; int(1)]) 4451202942487357861 +AnsweredRule {qHole_ = 4451202942487357861, qAscendants_ = fromList [-7368630815449645005,-4752206960723048197,-2804301512506126649,-1530922004872999299,-236411210949206668,204928372325319241,2335949798361580872,2698852189043337488,3049593885211881070,3728149952134739241,4353487588625663382,5225198894548896615,5925873450508265460,6881890190583065447], aRuleName_ = "matrix-comprehension-singleton"} +LF: {"AnsweredRule":{"aRuleName_":"matrix-comprehension-singleton","qAscendants_":[-7368630815449645005,-4752206960723048197,-2804301512506126649,-1530922004872999299,-236411210949206668,204928372325319241,2335949798361580872,2698852189043337488,3049593885211881070,3728149952134739241,4353487588625663382,5225198894548896615,5925873450508265460,6881890190583065447],"qHole_":4451202942487357861}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + Context #1: conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } +Picking the only option: Answer 1: choose-repr-for-locals: Choosing representation for local variable conjure_aux3 + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } +storedChoice: +{ conjure_aux3 +@ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) +} -3398171252428132748 +AnsweredRule {qHole_ = -3398171252428132748, qAscendants_ = fromList [-4801520196462386255,-3106386946478834998,-1836288510476607810,-1423400445383478062,1875892051782461076,3043802995379454474,7974629594191079167,8285823029631020243,8636179585519730549], aRuleName_ = "choose-repr-for-locals"} +LF: {"AnsweredRule":{"aRuleName_":"choose-repr-for-locals","qAscendants_":[-4801520196462386255,-3106386946478834998,-1836288510476607810,-1423400445383478062,1875892051782461076,3043802995379454474,7974629594191079167,8285823029631020243,8636179585519730549],"qHole_":-3398171252428132748}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + Context #1: { conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + conjure_aux2_1 = + { conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } +Picking the only option: Answer 1: bubble-up-LiftVars: Bubbling up auxiliary variables. + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } +storedChoice: +conjure_aux2_1 = +{ conjure_aux3 +@ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) +} 7974629594191079167 +AnsweredRule {qHole_ = 7974629594191079167, qAscendants_ = fromList [-4801520196462386255,-3106386946478834998,-1836288510476607810,-1423400445383478062,1875892051782461076,3043802995379454474,8285823029631020243,8636179585519730549], aRuleName_ = "bubble-up-LiftVars"} +LF: {"AnsweredRule":{"aRuleName_":"bubble-up-LiftVars","qAscendants_":[-4801520196462386255,-3106386946478834998,-1836288510476607810,-1423400445383478062,1875892051782461076,3043802995379454474,8285823029631020243,8636179585519730549],"qHole_":7974629594191079167}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: conjure_aux2[2] + Context #1: conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) +Picking the only option: Answer 1: tuple-index: Tuple indexing on: conjure_aux2[2] + conjure_aux2_2 +storedChoice: +conjure_aux2[2] 2042003740924818024 +AnsweredRule {qHole_ = 2042003740924818024, qAscendants_ = fromList [-7047224780753215240,-3882919266147774615,-2299063140006189613,681365846263239803,6336625794965795994,6485140089845002516,7009155380893464902,7082442116022567493,8239398540167710302], aRuleName_ = "tuple-index"} +LF: {"AnsweredRule":{"aRuleName_":"tuple-index","qAscendants_":[-7047224780753215240,-3882919266147774615,-2299063140006189613,681365846263239803,6336625794965795994,6485140089845002516,7009155380893464902,7082442116022567493,8239398540167710302],"qHole_":2042003740924818024}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2_2 = image(permutation((3, 4)), (q8[1], q8[2])[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: (q8[1], q8[2])[2] + Context #1: image(permutation((3, 4)), (q8[1], q8[2])[2]) +Picking the only option: Answer 1: tuple-index: Tuple indexing on: (q8[1], q8[2])[2] + q8[2] +storedChoice: +(q8[1], q8[2])[2] -5502204419920622825 +AnsweredRule {qHole_ = -5502204419920622825, qAscendants_ = fromList [-8588231375425367299,-8510895911811768656,-8426633625849827304,-8207238726412672978,-5936144574452389035,-2652871536273271001,-1630485539153521150,-1126023409437003920,6016260006111454055,8400731779430988570], aRuleName_ = "tuple-index"} +LF: {"AnsweredRule":{"aRuleName_":"tuple-index","qAscendants_":[-8588231375425367299,-8510895911811768656,-8426633625849827304,-8207238726412672978,-5936144574452389035,-2652871536273271001,-1630485539153521150,-1126023409437003920,6016260006111454055,8400731779430988570],"qHole_":-5502204419920622825}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2_2 = image(permutation((3, 4)), q8[2]) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: q8[2] + Context #1: image(permutation((3, 4)), q8[2]) +Picking the only option: Answer 1: tuple-index: Tuple indexing on: q8[2] + q8_2 +storedChoice: +q8[2] 6051020602090044114 +AnsweredRule {qHole_ = 6051020602090044114, qAscendants_ = fromList [-8305205627063512429,-4351892905554585329,-3978385945799741575,-2899802451648727176,-2610387685810348227,-2009358436958284574,-1222951737421888386,-579623331933497389,4724832166697728323,7712861814088489767], aRuleName_ = "tuple-index"} +LF: {"AnsweredRule":{"aRuleName_":"tuple-index","qAscendants_":[-8305205627063512429,-4351892905554585329,-3978385945799741575,-2899802451648727176,-2610387685810348227,-2009358436958284574,-1222951737421888386,-579623331933497389,4724832166697728323,7712861814088489767],"qHole_":6051020602090044114}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that conjure_aux2_2 = image(permutation((3, 4)), q8_2) + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: image(permutation((3, 4)), q8_2) + Context #1: conjure_aux2_2 = image(permutation((3, 4)), q8_2) +Picking the only option: Answer 1: permutation-image-literal{AsFunction}: Horizontal rule for permutation literal application to a single value (image), AsFunction representation + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and([q15 = q8_2 <-> conjure_aux4 = q16 | (q15, q16) <- [(3, 4), (4, 3); int(1..2)]]) /\ + (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) + } +storedChoice: +image(permutation((3, 4)), q8_2) -6566221682376100457 +AnsweredRule {qHole_ = -6566221682376100457, qAscendants_ = fromList [-7375621483096556180,-6476209656930651827,-6169031786475517693,-4051333596644929202,-1139526513744825718,614654197146956279,4282607200389588721,4519547606898719585,5902970686666028765], aRuleName_ = "permutation-image-literal{AsFunction}"} +LF: {"AnsweredRule":{"aRuleName_":"permutation-image-literal{AsFunction}","qAscendants_":[-7375621483096556180,-6476209656930651827,-6169031786475517693,-4051333596644929202,-1139526513744825718,614654197146956279,4282607200389588721,4519547606898719585,5902970686666028765],"qHole_":-6566221682376100457}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and([q15 = q8_2 <-> conjure_aux4 = q16 | (q15, q16) <- [(3, 4), (4, 3); int(1..2)]]) /\ + (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: [(3, 4), (4, 3); int(1..2)] + Context #1: [q15 = q8_2 <-> conjure_aux4 = q16 | (q15, q16) <- [(3, 4), (4, 3); int(1..2)]] +Picking the only option: Answer 1: full-evaluate: Full evaluator + [(3, 4), (4, 3); int(1..2)] +storedChoice: +[(3, 4), (4, 3); int(1..2)] 6597397470067790033 +AnsweredRule {qHole_ = 6597397470067790033, qAscendants_ = fromList [-8545307407731927617,-8177498968743831179,-5742947888929994190,-4442383996991551152,396642913451874760,889145374549031649,902104300452840084,1328695702543446488,2152276483370682723,4084473456285295179,4905601367831877360,6850337191508996871,7001603146156804613,8689879020318308638], aRuleName_ = "full-evaluate"} +LF: {"AnsweredRule":{"aRuleName_":"full-evaluate","qAscendants_":[-8545307407731927617,-8177498968743831179,-5742947888929994190,-4442383996991551152,396642913451874760,889145374549031649,902104300452840084,1328695702543446488,2152276483370682723,4084473456285295179,4905601367831877360,6850337191508996871,7001603146156804613,8689879020318308638],"qHole_":6597397470067790033}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and([q15 = q8_2 <-> conjure_aux4 = q16 | (q15, q16) <- [(3, 4), (4, 3); int(1..2)]]) /\ + (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: [q15 = q8_2 <-> conjure_aux4 = q16 | (q15, q16) <- [(3, 4), (4, 3); int(1..2)]] + Context #1: and([q15 = q8_2 <-> conjure_aux4 = q16 | (q15, q16) <- [(3, 4), (4, 3); int(1..2)]]) +Picking the only option: Answer 1: complex-pattern: complex pattern on tuple patterns + [q19[1] = q8_2 <-> conjure_aux4 = q19[2] | q19 <- [(3, 4), (4, 3); int(1..2)]] +storedChoice: +[q15 = q8_2 <-> conjure_aux4 = q16 | (q15, q16) <- [(3, 4), (4, 3); int(1..2)]] 1328695702543446488 +AnsweredRule {qHole_ = 1328695702543446488, qAscendants_ = fromList [-8545307407731927617,-8177498968743831179,-5742947888929994190,-4442383996991551152,396642913451874760,889145374549031649,902104300452840084,2152276483370682723,4084473456285295179,4905601367831877360,6850337191508996871,7001603146156804613,8689879020318308638], aRuleName_ = "complex-pattern"} +LF: {"AnsweredRule":{"aRuleName_":"complex-pattern","qAscendants_":[-8545307407731927617,-8177498968743831179,-5742947888929994190,-4442383996991551152,396642913451874760,889145374549031649,902104300452840084,2152276483370682723,4084473456285295179,4905601367831877360,6850337191508996871,7001603146156804613,8689879020318308638],"qHole_":1328695702543446488}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and([q19[1] = q8_2 <-> conjure_aux4 = q19[2] | q19 <- [(3, 4), (4, 3); int(1..2)]]) /\ + (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: [q19[1] = q8_2 <-> conjure_aux4 = q19[2] | q19 <- [(3, 4), (4, 3); int(1..2)]] + Context #1: and([q19[1] = q8_2 <-> conjure_aux4 = q19[2] | q19 <- [(3, 4), (4, 3); int(1..2)]]) +Picking the only option: Answer 1: matrix-comprehension-literal: Vertical rule for matrix-comprehension on matrix literal + flatten(1, + [[q19[1] = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (3, 4)], + [q19[1] = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (4, 3)]; + int(1..2)]) +storedChoice: +[q19[1] = q8_2 <-> conjure_aux4 = q19[2] | q19 <- [(3, 4), (4, 3); int(1..2)]] 2193708270475412974 +AnsweredRule {qHole_ = 2193708270475412974, qAscendants_ = fromList [-6135273235547916413,-3511824826747542530,-2817684250930868121,-1400917739936160745,-1319813811263441476,-481597523330641054,222999019742587203,2503474596382683671,4309903314606971320,7082348445248550107,7474061097534958542,8348619552204205832,9141480563237676781], aRuleName_ = "matrix-comprehension-literal"} +LF: {"AnsweredRule":{"aRuleName_":"matrix-comprehension-literal","qAscendants_":[-6135273235547916413,-3511824826747542530,-2817684250930868121,-1400917739936160745,-1319813811263441476,-481597523330641054,222999019742587203,2503474596382683671,4309903314606971320,7082348445248550107,7474061097534958542,8348619552204205832,9141480563237676781],"qHole_":2193708270475412974}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, + [[q19[1] = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (3, 4)], + [q19[1] = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (4, 3)]; + int(1..2)])) + /\ (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: q19[1] + Context #1: q19[1] = q8_2 +Picking the only option: Answer 1: full-evaluate: Full evaluator + 3 +storedChoice: +q19[1] 6191924817638487798 +AnsweredRule {qHole_ = 6191924817638487798, qAscendants_ = fromList [-7807298629892727492,-7342314879418443169,-6863795700888677384,-4312957023244042045,-4187455163410375661,-3675178923764728484,-2875109432163106677,-562821977670977521,-430646313158070946,645934730965016486,1213611367040462212,1245826829098445208,2464444564009404876,4591515159436918289,5954646064348546905,6209885551316441807,7780749284175319389,8140212805021622098], aRuleName_ = "full-evaluate"} +LF: {"AnsweredRule":{"aRuleName_":"full-evaluate","qAscendants_":[-7807298629892727492,-7342314879418443169,-6863795700888677384,-4312957023244042045,-4187455163410375661,-3675178923764728484,-2875109432163106677,-562821977670977521,-430646313158070946,645934730965016486,1213611367040462212,1245826829098445208,2464444564009404876,4591515159436918289,5954646064348546905,6209885551316441807,7780749284175319389,8140212805021622098],"qHole_":6191924817638487798}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, + [[3 = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (3, 4)], [q19[1] = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (4, 3)]; + int(1..2)])) + /\ (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: q19[2] + Context #1: conjure_aux4 = q19[2] +Picking the only option: Answer 1: full-evaluate: Full evaluator + 4 +storedChoice: +q19[2] 6191080349758138413 +AnsweredRule {qHole_ = 6191080349758138413, qAscendants_ = fromList [-6520176996801677506,-5843168008449148354,-5683324553460351353,-4951129330098074556,-4643211621054911287,-3822866046842193137,-3751755282991126720,-2857878400374217220,-1860910263859276895,-1737565941370477352,1050126061434755877,2341740140041990923,2502411580506467583,2525054445025194025,3419152102230274364,7279809536600806905,8523948582780839689,8905640568803089599], aRuleName_ = "full-evaluate"} +LF: {"AnsweredRule":{"aRuleName_":"full-evaluate","qAscendants_":[-6520176996801677506,-5843168008449148354,-5683324553460351353,-4951129330098074556,-4643211621054911287,-3822866046842193137,-3751755282991126720,-2857878400374217220,-1860910263859276895,-1737565941370477352,1050126061434755877,2341740140041990923,2502411580506467583,2525054445025194025,3419152102230274364,7279809536600806905,8523948582780839689,8905640568803089599],"qHole_":6191080349758138413}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, + [[3 = q8_2 <-> conjure_aux4 = 4 | letting q19 be (3, 4)], [q19[1] = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (4, 3)]; + int(1..2)])) + /\ (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: q19[1] + Context #1: q19[1] = q8_2 +Picking the only option: Answer 1: full-evaluate: Full evaluator + 4 +storedChoice: +q19[1] 6191924817638487798 +AnsweredRule {qHole_ = 6191924817638487798, qAscendants_ = fromList [-8623968074095065085,-7329444732361257248,-4918646323490343107,-3863503547689138135,-3675178923764728484,-3569961048242171061,-3144694525976125140,-3142709837274542140,-3025737286103464396,-2863059074413010081,-2845931958765307537,-1992102340549551315,-1320176390405360702,-727033692116714751,-430646313158070946,4099404035470031281,7496678802752551639,8353918602880186919], aRuleName_ = "full-evaluate"} +LF: {"AnsweredRule":{"aRuleName_":"full-evaluate","qAscendants_":[-8623968074095065085,-7329444732361257248,-4918646323490343107,-3863503547689138135,-3675178923764728484,-3569961048242171061,-3144694525976125140,-3142709837274542140,-3025737286103464396,-2863059074413010081,-2845931958765307537,-1992102340549551315,-1320176390405360702,-727033692116714751,-430646313158070946,4099404035470031281,7496678802752551639,8353918602880186919],"qHole_":6191924817638487798}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, + [[3 = q8_2 <-> conjure_aux4 = 4 | letting q19 be (3, 4)], [4 = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (4, 3)]; int(1..2)])) + /\ (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: q19[2] + Context #1: conjure_aux4 = q19[2] +Picking the only option: Answer 1: full-evaluate: Full evaluator + 3 +storedChoice: +q19[2] 6191080349758138413 +AnsweredRule {qHole_ = 6191080349758138413, qAscendants_ = fromList [-8757640153264855213,-8246403386320852045,-7634455432471374117,-6807206396586148212,-6520176996801677506,-3765915116603809328,-3206961831370542574,-2880744773295792633,10288890695967554,1236510066935204208,2127338015569558053,2891526256517846499,4193370254288787506,4672949733519819188,4775978928665173836,5268252065626460890,7614915012244226995,8901849277253604507], aRuleName_ = "full-evaluate"} +LF: {"AnsweredRule":{"aRuleName_":"full-evaluate","qAscendants_":[-8757640153264855213,-8246403386320852045,-7634455432471374117,-6807206396586148212,-6520176996801677506,-3765915116603809328,-3206961831370542574,-2880744773295792633,10288890695967554,1236510066935204208,2127338015569558053,2891526256517846499,4193370254288787506,4672949733519819188,4775978928665173836,5268252065626460890,7614915012244226995,8901849277253604507],"qHole_":6191080349758138413}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, + [[3 = q8_2 <-> conjure_aux4 = 4 | letting q19 be (3, 4)], [4 = q8_2 <-> conjure_aux4 = 3 | letting q19 be (4, 3)]; int(1..2)])) + /\ (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: [4 = q8_2 <-> conjure_aux4 = 3 | letting q19 be (4, 3)] + Context #1: [[3 = q8_2 <-> conjure_aux4 = 4 | letting q19 be (3, 4)], [4 = q8_2 <-> conjure_aux4 = 3 | letting q19 be (4, 3)]; + int(1..2)] +Picking the only option: Answer 1: generators-first: Inlining comprehension lettings. + [4 = q8_2 <-> conjure_aux4 = 3 |] +storedChoice: +[4 = q8_2 <-> conjure_aux4 = 3 | letting q19 be (4, 3)] 1588099557195084353 +AnsweredRule {qHole_ = 1588099557195084353, qAscendants_ = fromList [-8793688442874950149,-7572881584565844112,-7548342805617471592,-4348732945489509501,-2395694351007614565,88957386040583823,374422725277413608,1323284114810179273,2396707417125615551,2821870942280363336,4471571311804301542,5264705085330663748,5735937483858420141,6159114761266478893,6376856799016601882], aRuleName_ = "generators-first"} +LF: {"AnsweredRule":{"aRuleName_":"generators-first","qAscendants_":[-8793688442874950149,-7572881584565844112,-7548342805617471592,-4348732945489509501,-2395694351007614565,88957386040583823,374422725277413608,1323284114810179273,2396707417125615551,2821870942280363336,4471571311804301542,5264705085330663748,5735937483858420141,6159114761266478893,6376856799016601882],"qHole_":1588099557195084353}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4 | letting q19 be (3, 4)], [4 = q8_2 <-> conjure_aux4 = 3 |]; int(1..2)])) /\ + (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: [4 = q8_2 <-> conjure_aux4 = 3 |] + Context #1: [[3 = q8_2 <-> conjure_aux4 = 4 | letting q19 be (3, 4)], [4 = q8_2 <-> conjure_aux4 = 3 |]; int(1..2)] +Picking the only option: Answer 1: generators-first: Empty generators. + [4 = q8_2 <-> conjure_aux4 = 3; int(1)] +storedChoice: +[4 = q8_2 <-> conjure_aux4 = 3 |] 5497036040823098170 +AnsweredRule {qHole_ = 5497036040823098170, qAscendants_ = fromList [-8392241438280449004,-7601484554155610431,-6546222595955103458,-5296722524234462815,-2359991535599832467,-1063257280645700723,-17895501989558244,635280768506310618,1960340259087120798,3697301678543081257,4285418689022343979,6976383550303671088,8132222765465596941,8451535935592013102,8523836484272235728], aRuleName_ = "generators-first"} +LF: {"AnsweredRule":{"aRuleName_":"generators-first","qAscendants_":[-8392241438280449004,-7601484554155610431,-6546222595955103458,-5296722524234462815,-2359991535599832467,-1063257280645700723,-17895501989558244,635280768506310618,1960340259087120798,3697301678543081257,4285418689022343979,6976383550303671088,8132222765465596941,8451535935592013102,8523836484272235728],"qHole_":5497036040823098170}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4 | letting q19 be (3, 4)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: [3 = q8_2 <-> conjure_aux4 = 4 | letting q19 be (3, 4)] + Context #1: [[3 = q8_2 <-> conjure_aux4 = 4 | letting q19 be (3, 4)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)] +Picking the only option: Answer 1: generators-first: Inlining comprehension lettings. + [3 = q8_2 <-> conjure_aux4 = 4 |] +storedChoice: +[3 = q8_2 <-> conjure_aux4 = 4 | letting q19 be (3, 4)] 4563840366785778455 +AnsweredRule {qHole_ = 4563840366785778455, qAscendants_ = fromList [-8318635854976707433,-5946611935025738568,-5571483100812435886,-5359593091160120138,-5038848917712120091,-4505559122101590956,-4490512703364564363,-3882495187869643600,1795022445773124374,2052386823818313881,3017254667178360325,5004474385002050470,5786646087302900637,8288841898596402765,8964004080555796084], aRuleName_ = "generators-first"} +LF: {"AnsweredRule":{"aRuleName_":"generators-first","qAscendants_":[-8318635854976707433,-5946611935025738568,-5571483100812435886,-5359593091160120138,-5038848917712120091,-4505559122101590956,-4490512703364564363,-3882495187869643600,1795022445773124374,2052386823818313881,3017254667178360325,5004474385002050470,5786646087302900637,8288841898596402765,8964004080555796084],"qHole_":4563840366785778455}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4 |], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: [3 = q8_2 <-> conjure_aux4 = 4 |] + Context #1: [[3 = q8_2 <-> conjure_aux4 = 4 |], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)] +Picking the only option: Answer 1: generators-first: Empty generators. + [3 = q8_2 <-> conjure_aux4 = 4; int(1)] +storedChoice: +[3 = q8_2 <-> conjure_aux4 = 4 |] -4963556797043179790 +AnsweredRule {qHole_ = -4963556797043179790, qAscendants_ = fromList [-8774772560597070458,-8569754725622420077,-7014391000977899535,-5142692957413181259,-4041649316716467790,-3712748679124722967,-622761194274709583,-434728569439334546,1040357877965562186,2786263529603136423,3452832737484532816,4830299290996501437,5939727597018131278,7229121740432553148,8127256833064397799], aRuleName_ = "generators-first"} +LF: {"AnsweredRule":{"aRuleName_":"generators-first","qAscendants_":[-8774772560597070458,-8569754725622420077,-7014391000977899535,-5142692957413181259,-4041649316716467790,-3712748679124722967,-622761194274709583,-434728569439334546,1040357877965562186,2786263529603136423,3452832737484532816,4830299290996501437,5939727597018131278,7229121740432553148,8127256833064397799],"qHole_":-4963556797043179790}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: [(3, 4), (4, 3); int(1..2)] + Context #1: [q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]] +Picking the only option: Answer 1: full-evaluate: Full evaluator + [(3, 4), (4, 3); int(1..2)] +storedChoice: +[(3, 4), (4, 3); int(1..2)] 6597397470067790033 +AnsweredRule {qHole_ = 6597397470067790033, qAscendants_ = fromList [-8633754808918514186,-8188184727507762196,-5677541651570710819,-4916174755379616322,-4850199604535152020,-3462648503323623219,-2367628624258445968,-2307855029918049024,1883982971068606087,1912870777007720445,2809445194379708718,3667006364909395131,3677477140697149393,7256127331114215867,8364657527657792986,9047491038558976704], aRuleName_ = "full-evaluate"} +LF: {"AnsweredRule":{"aRuleName_":"full-evaluate","qAscendants_":[-8633754808918514186,-8188184727507762196,-5677541651570710819,-4916174755379616322,-4850199604535152020,-3462648503323623219,-2367628624258445968,-2307855029918049024,1883982971068606087,1912870777007720445,2809445194379708718,3667006364909395131,3677477140697149393,7256127331114215867,8364657527657792986,9047491038558976704],"qHole_":6597397470067790033}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: [q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]] + Context #1: or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) +Picking the only option: Answer 1: complex-pattern: complex pattern on tuple patterns + [q20[1] = conjure_aux4 | q20 <- [(3, 4), (4, 3); int(1..2)]] +storedChoice: +[q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]] -4850199604535152020 +AnsweredRule {qHole_ = -4850199604535152020, qAscendants_ = fromList [-8633754808918514186,-8188184727507762196,-5677541651570710819,-4916174755379616322,-3462648503323623219,-2367628624258445968,-2307855029918049024,1883982971068606087,1912870777007720445,2809445194379708718,3667006364909395131,3677477140697149393,7256127331114215867,8364657527657792986,9047491038558976704], aRuleName_ = "complex-pattern"} +LF: {"AnsweredRule":{"aRuleName_":"complex-pattern","qAscendants_":[-8633754808918514186,-8188184727507762196,-5677541651570710819,-4916174755379616322,-3462648503323623219,-2367628624258445968,-2307855029918049024,1883982971068606087,1912870777007720445,2809445194379708718,3667006364909395131,3677477140697149393,7256127331114215867,8364657527657792986,9047491038558976704],"qHole_":-4850199604535152020}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!or([q20[1] = conjure_aux4 | q20 <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: [q20[1] = conjure_aux4 | q20 <- [(3, 4), (4, 3); int(1..2)]] + Context #1: or([q20[1] = conjure_aux4 | q20 <- [(3, 4), (4, 3); int(1..2)]]) +Picking the only option: Answer 1: matrix-comprehension-literal: Vertical rule for matrix-comprehension on matrix literal + flatten(1, [[q20[1] = conjure_aux4 | letting q20 be (3, 4)], [q20[1] = conjure_aux4 | letting q20 be (4, 3)]; int(1..2)]) +storedChoice: +[q20[1] = conjure_aux4 | q20 <- [(3, 4), (4, 3); int(1..2)]] -7042519532359788232 +AnsweredRule {qHole_ = -7042519532359788232, qAscendants_ = fromList [-8908244575740954826,-5683928670681234592,-5283973279755061591,-3518626964796470528,-1965680338567566419,-1619218070244699183,-1290540526775639182,-1001280480543716507,-920250991117702438,-37243485035014411,3109960451075183399,3577717700431629359,4854879008546753238,5736831950861882173,7673200081862847690], aRuleName_ = "matrix-comprehension-literal"} +LF: {"AnsweredRule":{"aRuleName_":"matrix-comprehension-literal","qAscendants_":[-8908244575740954826,-5683928670681234592,-5283973279755061591,-3518626964796470528,-1965680338567566419,-1619218070244699183,-1290540526775639182,-1001280480543716507,-920250991117702438,-37243485035014411,3109960451075183399,3577717700431629359,4854879008546753238,5736831950861882173,7673200081862847690],"qHole_":-7042519532359788232}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!or(flatten(1, [[q20[1] = conjure_aux4 | letting q20 be (3, 4)], [q20[1] = conjure_aux4 | letting q20 be (4, 3)]; int(1..2)])) <-> + conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: q20[1] + Context #1: q20[1] = conjure_aux4 +Picking the only option: Answer 1: full-evaluate: Full evaluator + 3 +storedChoice: +q20[1] -5066820997822192518 +AnsweredRule {qHole_ = -5066820997822192518, qAscendants_ = fromList [-8114810939578997179,-5955986499643421728,-5766477344136638660,-3619457499884836706,-3596989804158315723,-3512526206489503481,-2484614995521209041,-1748033148869835596,-58454364784882596,76873978234325305,2489610439802360191,3564003602712422871,3732529855370416098,3884465148016108231,4296494138735898078,4399359040184583027,4639251469994992570,7395797297508748841,7886700597594415296], aRuleName_ = "full-evaluate"} +LF: {"AnsweredRule":{"aRuleName_":"full-evaluate","qAscendants_":[-8114810939578997179,-5955986499643421728,-5766477344136638660,-3619457499884836706,-3596989804158315723,-3512526206489503481,-2484614995521209041,-1748033148869835596,-58454364784882596,76873978234325305,2489610439802360191,3564003602712422871,3732529855370416098,3884465148016108231,4296494138735898078,4399359040184583027,4639251469994992570,7395797297508748841,7886700597594415296],"qHole_":-5066820997822192518}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!or(flatten(1, [[3 = conjure_aux4 | letting q20 be (3, 4)], [q20[1] = conjure_aux4 | letting q20 be (4, 3)]; int(1..2)])) <-> + conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: q20[1] + Context #1: q20[1] = conjure_aux4 +Picking the only option: Answer 1: full-evaluate: Full evaluator + 4 +storedChoice: +q20[1] -5066820997822192518 +AnsweredRule {qHole_ = -5066820997822192518, qAscendants_ = fromList [-8725074021340919078,-8574349549577316045,-7990711773149197775,-7723660686298995374,-6875295913338400819,-5695102429637848602,-5273340809049818279,-3512526206489503481,-2862537938983036678,-2765562469061820724,-807453819412548209,-307031570223611599,37627954002053673,516678838692838411,3479854824023329968,6753745594226090750,8107007183604066764,8502378019651797201,9046378511697116254], aRuleName_ = "full-evaluate"} +LF: {"AnsweredRule":{"aRuleName_":"full-evaluate","qAscendants_":[-8725074021340919078,-8574349549577316045,-7990711773149197775,-7723660686298995374,-6875295913338400819,-5695102429637848602,-5273340809049818279,-3512526206489503481,-2862537938983036678,-2765562469061820724,-807453819412548209,-307031570223611599,37627954002053673,516678838692838411,3479854824023329968,6753745594226090750,8107007183604066764,8502378019651797201,9046378511697116254],"qHole_":-5066820997822192518}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!or(flatten(1, [[3 = conjure_aux4 | letting q20 be (3, 4)], [4 = conjure_aux4 | letting q20 be (4, 3)]; int(1..2)])) <-> + conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: [4 = conjure_aux4 | letting q20 be (4, 3)] + Context #1: [[3 = conjure_aux4 | letting q20 be (3, 4)], [4 = conjure_aux4 | letting q20 be (4, 3)]; int(1..2)] +Picking the only option: Answer 1: generators-first: Inlining comprehension lettings. + [4 = conjure_aux4 |] +storedChoice: +[4 = conjure_aux4 | letting q20 be (4, 3)] -4659269292751863231 +AnsweredRule {qHole_ = -4659269292751863231, qAscendants_ = fromList [-8139107762275405780,-6067050360933011415,-4668927100952759839,-2832336555945972970,-2685263499350289956,-712998101401819851,-662867422474666417,-634413128047463436,1314890692039055455,1461492958057141352,1536420920342600247,1612507314243025908,6104410666907258834,6818646762744932078,7002085677101186921,7870098581639353518,8074964079189467219], aRuleName_ = "generators-first"} +LF: {"AnsweredRule":{"aRuleName_":"generators-first","qAscendants_":[-8139107762275405780,-6067050360933011415,-4668927100952759839,-2832336555945972970,-2685263499350289956,-712998101401819851,-662867422474666417,-634413128047463436,1314890692039055455,1461492958057141352,1536420920342600247,1612507314243025908,6104410666907258834,6818646762744932078,7002085677101186921,7870098581639353518,8074964079189467219],"qHole_":-4659269292751863231}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!or(flatten(1, [[3 = conjure_aux4 | letting q20 be (3, 4)], [4 = conjure_aux4 |]; int(1..2)])) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: [4 = conjure_aux4 |] + Context #1: [[3 = conjure_aux4 | letting q20 be (3, 4)], [4 = conjure_aux4 |]; int(1..2)] +Picking the only option: Answer 1: generators-first: Empty generators. + [4 = conjure_aux4; int(1)] +storedChoice: +[4 = conjure_aux4 |] 3103944569848083730 +AnsweredRule {qHole_ = 3103944569848083730, qAscendants_ = fromList [-6499292278244277577,-5447382347614094034,-3901800536920366688,-3381517728243229044,-2903466984087021575,-1629155788585143592,-595707724612505928,-531462185798445081,-436711175201990026,-305874969643107400,713364048257302949,3760728491479375708,4192007196113212495,5520591029544627590,7106210168219555744,7226177407162985748,8785470622724542357], aRuleName_ = "generators-first"} +LF: {"AnsweredRule":{"aRuleName_":"generators-first","qAscendants_":[-6499292278244277577,-5447382347614094034,-3901800536920366688,-3381517728243229044,-2903466984087021575,-1629155788585143592,-595707724612505928,-531462185798445081,-436711175201990026,-305874969643107400,713364048257302949,3760728491479375708,4192007196113212495,5520591029544627590,7106210168219555744,7226177407162985748,8785470622724542357],"qHole_":3103944569848083730}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!or(flatten(1, [[3 = conjure_aux4 | letting q20 be (3, 4)], [4 = conjure_aux4; int(1)]; int(1..2)])) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: [3 = conjure_aux4 | letting q20 be (3, 4)] + Context #1: [[3 = conjure_aux4 | letting q20 be (3, 4)], [4 = conjure_aux4; int(1)]; int(1..2)] +Picking the only option: Answer 1: generators-first: Inlining comprehension lettings. + [3 = conjure_aux4 |] +storedChoice: +[3 = conjure_aux4 | letting q20 be (3, 4)] -6255934535417186594 +AnsweredRule {qHole_ = -6255934535417186594, qAscendants_ = fromList [-7136276057455168685,-7072459974569890512,-6196259248273364037,-5834210587143255228,-2665342865711637679,-1906879012656170539,-1522455433242873900,752122676500601510,1351313430292206143,2164743633705935677,2917302706197316348,3522536415221397176,3844998889588585321,5240671478404014136,7264763306810372171,7563078030555210243,8716248641960869542], aRuleName_ = "generators-first"} +LF: {"AnsweredRule":{"aRuleName_":"generators-first","qAscendants_":[-7136276057455168685,-7072459974569890512,-6196259248273364037,-5834210587143255228,-2665342865711637679,-1906879012656170539,-1522455433242873900,752122676500601510,1351313430292206143,2164743633705935677,2917302706197316348,3522536415221397176,3844998889588585321,5240671478404014136,7264763306810372171,7563078030555210243,8716248641960869542],"qHole_":-6255934535417186594}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!or(flatten(1, [[3 = conjure_aux4 |], [4 = conjure_aux4; int(1)]; int(1..2)])) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: [3 = conjure_aux4 |] + Context #1: [[3 = conjure_aux4 |], [4 = conjure_aux4; int(1)]; int(1..2)] +Picking the only option: Answer 1: generators-first: Empty generators. + [3 = conjure_aux4; int(1)] +storedChoice: +[3 = conjure_aux4 |] -2658614992963116405 +AnsweredRule {qHole_ = -2658614992963116405, qAscendants_ = fromList [-8200797483737906583,-7142891394430515063,-5048865527690557400,-3204141723258765628,-2755421715163082104,-2150417528239571907,-427238415401958863,345854652969155162,444587743724873706,1433275916120849547,2082716253070264500,3621608353720498501,3817394469011428558,4338626750910725978,6129719379140106144,6899422834286368127,8748622476088678609], aRuleName_ = "generators-first"} +LF: {"AnsweredRule":{"aRuleName_":"generators-first","qAscendants_":[-8200797483737906583,-7142891394430515063,-5048865527690557400,-3204141723258765628,-2755421715163082104,-2150417528239571907,-427238415401958863,345854652969155162,444587743724873706,1433275916120849547,2082716253070264500,3621608353720498501,3817394469011428558,4338626750910725978,6129719379140106144,6899422834286368127,8748622476088678609],"qHole_":-2658614992963116405}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!or(flatten(1, [[3 = conjure_aux4; int(1)], [4 = conjure_aux4; int(1)]; int(1..2)])) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: or(flatten(1, [[3 = conjure_aux4; int(1)], [4 = conjure_aux4; int(1)]; int(1..2)])) + Context #1: !or(flatten(1, [[3 = conjure_aux4; int(1)], [4 = conjure_aux4; int(1)]; int(1..2)])) +Picking the only option: Answer 1: quantifier-shift3: Shifting quantifier inwards + or([3 = conjure_aux4; int(1)]) \/ or([4 = conjure_aux4; int(1)]) +storedChoice: +or(flatten(1, [[3 = conjure_aux4; int(1)], [4 = conjure_aux4; int(1)]; int(1..2)])) 1792302133485940861 +AnsweredRule {qHole_ = 1792302133485940861, qAscendants_ = fromList [-9215156694345218491,-7884159941367425225,-4061787575651201278,-2348548688413524686,-1616656984063374174,1019247903219888070,1202444192825383566,2448039896892401119,2522006493315280277,2872569756943491545,3292387117872397760,5871641527667180654,6531511286127386564,8891172200144465433], aRuleName_ = "quantifier-shift3"} +LF: {"AnsweredRule":{"aRuleName_":"quantifier-shift3","qAscendants_":[-9215156694345218491,-7884159941367425225,-4061787575651201278,-2348548688413524686,-1616656984063374174,1019247903219888070,1202444192825383566,2448039896892401119,2522006493315280277,2872569756943491545,3292387117872397760,5871641527667180654,6531511286127386564,8891172200144465433],"qHole_":1792302133485940861}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!(or([3 = conjure_aux4; int(1)]) \/ or([4 = conjure_aux4; int(1)])) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: or([3 = conjure_aux4; int(1)]) + Context #1: [or([3 = conjure_aux4; int(1)]), or([4 = conjure_aux4; int(1)]); int(1..2)] +Picking the only option: Answer 1: matrix-comprehension-singleton: Removing quantifier of a single item + 3 = conjure_aux4 +storedChoice: +or([3 = conjure_aux4; int(1)]) -2238338300082489653 +AnsweredRule {qHole_ = -2238338300082489653, qAscendants_ = fromList [-9135090969161870748,-7040580929681195434,-5844866756595959210,-5200489563969105483,-5135428809631204876,-4567662440315024812,-2637178807861984772,-1043830869774709897,117930584853289771,1197239461988022471,4464393825362555947,5063705836807996732,5078493517063792951,6402729242588877157,6830536617247247401,7925032212346973439], aRuleName_ = "matrix-comprehension-singleton"} +LF: {"AnsweredRule":{"aRuleName_":"matrix-comprehension-singleton","qAscendants_":[-9135090969161870748,-7040580929681195434,-5844866756595959210,-5200489563969105483,-5135428809631204876,-4567662440315024812,-2637178807861984772,-1043830869774709897,117930584853289771,1197239461988022471,4464393825362555947,5063705836807996732,5078493517063792951,6402729242588877157,6830536617247247401,7925032212346973439],"qHole_":-2238338300082489653}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!(3 = conjure_aux4 \/ or([4 = conjure_aux4; int(1)])) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: or([4 = conjure_aux4; int(1)]) + Context #1: [3 = conjure_aux4, or([4 = conjure_aux4; int(1)]); int(1..2)] +Picking the only option: Answer 1: matrix-comprehension-singleton: Removing quantifier of a single item + 4 = conjure_aux4 +storedChoice: +or([4 = conjure_aux4; int(1)]) 6931996324238769216 +AnsweredRule {qHole_ = 6931996324238769216, qAscendants_ = fromList [-8301199506799591941,-7558092101252853604,-6067998700973920226,-5155701249953128914,-4576047313272360415,-4347126985617275804,-2751859814401093547,137469789217709822,144729713112841205,2146657550292868874,3729312864595267230,4118600647582069537,4766806173317946186,4942755527663293565,6086894017411589008,8428538202899570704], aRuleName_ = "matrix-comprehension-singleton"} +LF: {"AnsweredRule":{"aRuleName_":"matrix-comprehension-singleton","qAscendants_":[-8301199506799591941,-7558092101252853604,-6067998700973920226,-5155701249953128914,-4576047313272360415,-4347126985617275804,-2751859814401093547,137469789217709822,144729713112841205,2146657550292868874,3729312864595267230,4118600647582069537,4766806173317946186,4942755527663293565,6086894017411589008,8428538202899570704],"qHole_":6931996324238769216}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ + (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: and(flatten(1, + [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) + Context #1: [and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])), + !(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2; + int(1..2)] +Picking the only option: Answer 1: quantifier-shift3: Shifting quantifier inwards + and([3 = q8_2 <-> conjure_aux4 = 4; int(1)]) /\ and([4 = q8_2 <-> conjure_aux4 = 3; int(1)]) +storedChoice: +and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) 6498896587051443094 +AnsweredRule {qHole_ = 6498896587051443094, qAscendants_ = fromList [-9122266668816456873,-8763687680398485956,-6768148177044187855,-5775912378426088215,-3542921895788471154,-2263838003336096906,-202295424977994982,851884620329916301,5528267415991175666,6533818616419587005,7566808087161406219,8046934030769361906], aRuleName_ = "quantifier-shift3"} +LF: {"AnsweredRule":{"aRuleName_":"quantifier-shift3","qAscendants_":[-9122266668816456873,-8763687680398485956,-6768148177044187855,-5775912378426088215,-3542921895788471154,-2263838003336096906,-202295424977994982,851884620329916301,5528267415991175666,6533818616419587005,7566808087161406219,8046934030769361906],"qHole_":6498896587051443094}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + and([3 = q8_2 <-> conjure_aux4 = 4; int(1)]) /\ and([4 = q8_2 <-> conjure_aux4 = 3; int(1)]) /\ + (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: and([3 = q8_2 <-> conjure_aux4 = 4; int(1)]) + Context #1: [and([3 = q8_2 <-> conjure_aux4 = 4; int(1)]), and([4 = q8_2 <-> conjure_aux4 = 3; int(1)]); int(1..2)] +Picking the only option: Answer 1: matrix-comprehension-singleton: Removing quantifier of a single item + 3 = q8_2 <-> conjure_aux4 = 4 +storedChoice: +and([3 = q8_2 <-> conjure_aux4 = 4; int(1)]) 4625414366441981983 +AnsweredRule {qHole_ = 4625414366441981983, qAscendants_ = fromList [-5032104045245797729,-4260367211447941052,-3800321491279460974,-3527728036515378511,-3186771756499085870,-2663126455000061452,-2397177437658285933,-953818733459672679,51316433765895449,382670796215945555,1275044521375561569,2333080611421701721,2485864324914475150,5509053191108998898], aRuleName_ = "matrix-comprehension-singleton"} +LF: {"AnsweredRule":{"aRuleName_":"matrix-comprehension-singleton","qAscendants_":[-5032104045245797729,-4260367211447941052,-3800321491279460974,-3527728036515378511,-3186771756499085870,-2663126455000061452,-2397177437658285933,-953818733459672679,51316433765895449,382670796215945555,1275044521375561569,2333080611421701721,2485864324914475150,5509053191108998898],"qHole_":4625414366441981983}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + (3 = q8_2 <-> conjure_aux4 = 4) /\ and([4 = q8_2 <-> conjure_aux4 = 3; int(1)]) /\ + (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: and([4 = q8_2 <-> conjure_aux4 = 3; int(1)]) + Context #1: [3 = q8_2 <-> conjure_aux4 = 4, and([4 = q8_2 <-> conjure_aux4 = 3; int(1)]); int(1..2)] +Picking the only option: Answer 1: matrix-comprehension-singleton: Removing quantifier of a single item + 4 = q8_2 <-> conjure_aux4 = 3 +storedChoice: +and([4 = q8_2 <-> conjure_aux4 = 3; int(1)]) -8650590815054601249 +AnsweredRule {qHole_ = -8650590815054601249, qAscendants_ = fromList [-7526881736718068312,-7405557604309373817,-7201686808491642883,-6330762734028692340,-5804239247306276412,-5043128294307900798,-4578161512601023984,-2463121278901514889,303127519297990446,594877140964359361,1533543948414682137,4243960396898301951,6573830124911821771,7997158881778982126], aRuleName_ = "matrix-comprehension-singleton"} +LF: {"AnsweredRule":{"aRuleName_":"matrix-comprehension-singleton","qAscendants_":[-7526881736718068312,-7405557604309373817,-7201686808491642883,-6330762734028692340,-5804239247306276412,-5043128294307900798,-4578161512601023984,-2463121278901514889,303127519297990446,594877140964359361,1533543948414682137,4243960396898301951,6573830124911821771,7997158881778982126],"qHole_":-8650590815054601249}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ + (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ + (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) + } + Context #1: conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ + (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) + } +Picking the only option: Answer 1: choose-repr-for-locals: Choosing representation for local variable conjure_aux4 + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ + (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) + } +storedChoice: +{ conjure_aux4 +@ find conjure_aux4: int(1..5) + such that + (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ + (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) +} -5523540219623150802 +AnsweredRule {qHole_ = -5523540219623150802, qAscendants_ = fromList [-8941059882607301911,-4338998493244249628,-2962415465773075069,-2259331243426380901,-565469044512126150,-60812526271457966,2469584683440447504,4682955345466050776,5578803032032481190], aRuleName_ = "choose-repr-for-locals"} +LF: {"AnsweredRule":{"aRuleName_":"choose-repr-for-locals","qAscendants_":[-8941059882607301911,-4338998493244249628,-2962415465773075069,-2259331243426380901,-565469044512126150,-60812526271457966,2469584683440447504,4682955345466050776,5578803032032481190],"qHole_":-5523540219623150802}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ + (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ + (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) + } + Context #1: { conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + conjure_aux2_2 = + { conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ + (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) + } + } +Picking the only option: Answer 1: bubble-up-LiftVars: Bubbling up auxiliary variables. + { conjure_aux2_2 = conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ + (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) + } +storedChoice: +conjure_aux2_2 = +{ conjure_aux4 +@ find conjure_aux4: int(1..5) + such that + (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ + (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) +} 4682955345466050776 +AnsweredRule {qHole_ = 4682955345466050776, qAscendants_ = fromList [-8941059882607301911,-4338998493244249628,-2962415465773075069,-2259331243426380901,-565469044512126150,-60812526271457966,2469584683440447504,5578803032032481190], aRuleName_ = "bubble-up-LiftVars"} +LF: {"AnsweredRule":{"aRuleName_":"bubble-up-LiftVars","qAscendants_":[-8941059882607301911,-4338998493244249628,-2962415465773075069,-2259331243426380901,-565469044512126150,-60812526271457966,2469584683440447504,5578803032032481190],"qHole_":4682955345466050776}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + { conjure_aux2_2 = conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ + (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: { conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + { conjure_aux2_2 = conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ + (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + Context #1: [{ conjure_aux2 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + { conjure_aux2_2 = conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ + (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) + } + } + in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]] +Picking the only option: Answer 1: bubble-up-LiftVars: Bubbling up auxiliary variables. + { conjure_aux2 in conjure_aux1 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + { conjure_aux2_2 = conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ + (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) + } + } +storedChoice: +{ conjure_aux2 +@ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + { conjure_aux2_2 = conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ + (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) + } +} +in conjure_aux1 -8498631454693468162 +AnsweredRule {qHole_ = -8498631454693468162, qAscendants_ = fromList [-8906484870153215238,-5210480414835359833,-1572320097158340186,7262859821198064716,7664399396112355801,9199488081424848815], aRuleName_ = "bubble-up-LiftVars"} +LF: {"AnsweredRule":{"aRuleName_":"bubble-up-LiftVars","qAscendants_":[-8906484870153215238,-5210480414835359833,-1572320097158340186,7262859821198064716,7664399396112355801,9199488081424848815],"qHole_":-8498631454693468162}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 in conjure_aux1 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + { conjure_aux2_2 = conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ + (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) + } + } | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: q8[1] + Context #1: x_RelationAsMatrix[q8[1]] +Picking the only option: Answer 1: tuple-index: Tuple indexing on: q8[1] + q8_1 +storedChoice: +q8[1] 6051865069970393497 +AnsweredRule {qHole_ = 6051865069970393497, qAscendants_ = fromList [-8640702807944529160,-7554917160340714381,-7282620252070677492,-4679672213039578282,-3902820972913913543,-1648680758926951321,-323488035431343639,4558015980602682727], aRuleName_ = "tuple-index"} +LF: {"AnsweredRule":{"aRuleName_":"tuple-index","qAscendants_":[-8640702807944529160,-7554917160340714381,-7282620252070677492,-4679672213039578282,-3902820972913913543,-1648680758926951321,-323488035431343639,4558015980602682727],"qHole_":6051865069970393497}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 in conjure_aux1 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + { conjure_aux2_2 = conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ + (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) + } + } | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8[2]]]) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: q8[2] + Context #1: x_RelationAsMatrix[q8_1, q8[2]] +Picking the only option: Answer 1: tuple-index: Tuple indexing on: q8[2] + q8_2 +storedChoice: +q8[2] 6051020602090044114 +AnsweredRule {qHole_ = 6051020602090044114, qAscendants_ = fromList [-1657839898828256711,-1442033437105002979,-382389179101208790,2791764908100697416,2932884812988402663,3044000407645637671,4978224969731597410], aRuleName_ = "tuple-index"} +LF: {"AnsweredRule":{"aRuleName_":"tuple-index","qAscendants_":[-1657839898828256711,-1442033437105002979,-382389179101208790,2791764908100697416,2932884812988402663,3044000407645637671,4978224969731597410],"qHole_":6051020602090044114}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and([{ conjure_aux2 in conjure_aux1 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + { conjure_aux2_2 = conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ + (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) + } + } | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]]) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: [{ conjure_aux2 in conjure_aux1 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + { conjure_aux2_2 = conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ + (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) + } + } | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] + Context #1: and([{ conjure_aux2 in conjure_aux1 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + { conjure_aux2_2 = conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ + (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) + } + } | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]]) +Picking the only option: Answer 1: bubble-up-LiftVars: Bubbling up auxiliary variables through a comprehension. + { [conjure_aux2 in conjure_aux1 | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([{ conjure_aux2_1[q8_1, q8_2] = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } | q8_1 : int(1..5), q8_2 : int(1..5)]), + and([{ conjure_aux2_2[q8_1, q8_2] = conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ + (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) + } | q8_1 : int(1..5), q8_2 : int(1..5)]) + } +storedChoice: +[{ conjure_aux2 in conjure_aux1 + @ find conjure_aux2_1: int(1..5) + find conjure_aux2_2: int(1..5) + such that + { conjure_aux2_1 = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } + such that + { conjure_aux2_2 = conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ + (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) + } + } | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] 4632560015221358179 +AnsweredRule {qHole_ = 4632560015221358179, qAscendants_ = fromList [-7796146364068057171,-6981365833241776808,-5029665938164178889,-3928434564447926958,-2893776785872977312], aRuleName_ = "bubble-up-LiftVars"} +LF: {"AnsweredRule":{"aRuleName_":"bubble-up-LiftVars","qAscendants_":[-7796146364068057171,-6981365833241776808,-5029665938164178889,-3928434564447926958,-2893776785872977312],"qHole_":4632560015221358179}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and({ [conjure_aux2 in conjure_aux1 | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([{ conjure_aux2_1[q8_1, q8_2] = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } | q8_1 : int(1..5), q8_2 : int(1..5)]), + and([{ conjure_aux2_2[q8_1, q8_2] = conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ + (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) + } | q8_1 : int(1..5), q8_2 : int(1..5)]) + }) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: { [conjure_aux2 in conjure_aux1 + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([{ conjure_aux2_1[q8_1, q8_2] = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } | q8_1 : int(1..5), q8_2 : int(1..5)]), + and([{ conjure_aux2_2[q8_1, q8_2] = conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ + (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) + } | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + Context #1: and({ [conjure_aux2 in conjure_aux1 | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([{ conjure_aux2_1[q8_1, q8_2] = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } | q8_1 : int(1..5), q8_2 : int(1..5)]), + and([{ conjure_aux2_2[q8_1, q8_2] = conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ + (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) + } | q8_1 : int(1..5), q8_2 : int(1..5)]) + }) +Picking the only option: Answer 1: choose-repr-for-locals: Choosing representation for local variable conjure_aux2_1 + { [conjure_aux2 in conjure_aux1 | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([{ conjure_aux2_1[q8_1, q8_2] = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } | q8_1 : int(1..5), q8_2 : int(1..5)]), + and([{ conjure_aux2_2[q8_1, q8_2] = conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ + (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) + } | q8_1 : int(1..5), q8_2 : int(1..5)]) + } +storedChoice: +{ [conjure_aux2 in conjure_aux1 | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] +@ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([{ conjure_aux2_1[q8_1, q8_2] = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } | q8_1 : int(1..5), q8_2 : int(1..5)]), + and([{ conjure_aux2_2[q8_1, q8_2] = conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ + (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) + } | q8_1 : int(1..5), q8_2 : int(1..5)]) +} 5183357163976320088 +AnsweredRule {qHole_ = 5183357163976320088, qAscendants_ = fromList [-5465830923914696498,-4063366109563536561,-2043995450352341839,378335084364868291,1311484366701431644], aRuleName_ = "choose-repr-for-locals"} +LF: {"AnsweredRule":{"aRuleName_":"choose-repr-for-locals","qAscendants_":[-5465830923914696498,-4063366109563536561,-2043995450352341839,378335084364868291,1311484366701431644],"qHole_":5183357163976320088}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and({ [conjure_aux2 in conjure_aux1 | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([{ conjure_aux2_1[q8_1, q8_2] = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } | q8_1 : int(1..5), q8_2 : int(1..5)]), + and([{ conjure_aux2_2[q8_1, q8_2] = conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ + (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) + } | q8_1 : int(1..5), q8_2 : int(1..5)]) + }) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: [{ conjure_aux2_1[q8_1, q8_2] = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } | q8_1 : int(1..5), q8_2 : int(1..5)] + Context #1: and([{ conjure_aux2_1[q8_1, q8_2] = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } | q8_1 : int(1..5), q8_2 : int(1..5)]) +Picking the only option: Answer 1: bubble-up-LiftVars: Bubbling up auxiliary variables through a comprehension. + { [conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)] + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } +storedChoice: +[{ conjure_aux2_1[q8_1, q8_2] = conjure_aux3 + @ find conjure_aux3: int(1..5) + such that + (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ + (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) + } | q8_1 : int(1..5), q8_2 : int(1..5)] -2066028230956466058 +AnsweredRule {qHole_ = -2066028230956466058, qAscendants_ = fromList [-8778252753919104373,-5465830923914696498,-4063366109563536561,-2043995450352341839,378335084364868291,1311484366701431644,5183357163976320088], aRuleName_ = "bubble-up-LiftVars"} +LF: {"AnsweredRule":{"aRuleName_":"bubble-up-LiftVars","qAscendants_":[-8778252753919104373,-5465830923914696498,-4063366109563536561,-2043995450352341839,378335084364868291,1311484366701431644,5183357163976320088],"qHole_":-2066028230956466058}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and({ [conjure_aux2 in conjure_aux1 | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and({ [conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)] + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }), + and([{ conjure_aux2_2[q8_1, q8_2] = conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ + (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) + } | q8_1 : int(1..5), q8_2 : int(1..5)]) + }) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: { [conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)] + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + Context #1: and({ [conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)] + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }) +Picking the only option: Answer 1: choose-repr-for-locals: Choosing representation for local variable conjure_aux3 + { [conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)] + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } +storedChoice: +{ [conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)] +@ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) +} -2683400798428888576 +AnsweredRule {qHole_ = -2683400798428888576, qAscendants_ = fromList [-7630765854898757381,-5152289056460337438,-4378029185233493510,-2193789157648306228,-780484605375639491,4611290103392876019,8129436120778745950], aRuleName_ = "choose-repr-for-locals"} +LF: {"AnsweredRule":{"aRuleName_":"choose-repr-for-locals","qAscendants_":[-7630765854898757381,-5152289056460337438,-4378029185233493510,-2193789157648306228,-780484605375639491,4611290103392876019,8129436120778745950],"qHole_":-2683400798428888576}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and({ [conjure_aux2 in conjure_aux1 | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and({ [conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)] + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }), + and([{ conjure_aux2_2[q8_1, q8_2] = conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ + (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) + } | q8_1 : int(1..5), q8_2 : int(1..5)]) + }) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: and({ [conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] + | q8_1 : int(1..5), q8_2 : int(1..5)] + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }) + Context #1: { [conjure_aux2 in conjure_aux1 | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and({ [conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)] + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }), + and([{ conjure_aux2_2[q8_1, q8_2] = conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ + (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) + } | q8_1 : int(1..5), q8_2 : int(1..5)]) + } +Picking the only option: Answer 1: bubble-up-LiftVars: Bubbling up auxiliary variables. + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } +storedChoice: +and({ [conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)] + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }) -7630765854898757381 +AnsweredRule {qHole_ = -7630765854898757381, qAscendants_ = fromList [-5152289056460337438,-4378029185233493510,-2193789157648306228,-780484605375639491,4611290103392876019,8129436120778745950], aRuleName_ = "bubble-up-LiftVars"} +LF: {"AnsweredRule":{"aRuleName_":"bubble-up-LiftVars","qAscendants_":[-5152289056460337438,-4378029185233493510,-2193789157648306228,-780484605375639491,4611290103392876019,8129436120778745950],"qHole_":-7630765854898757381}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and({ [conjure_aux2 in conjure_aux1 | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + and([{ conjure_aux2_2[q8_1, q8_2] = conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ + (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) + } | q8_1 : int(1..5), q8_2 : int(1..5)]) + }) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: [{ conjure_aux2_2[q8_1, q8_2] = conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ + (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) + } | q8_1 : int(1..5), q8_2 : int(1..5)] + Context #1: and([{ conjure_aux2_2[q8_1, q8_2] = conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ + (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) + } | q8_1 : int(1..5), q8_2 : int(1..5)]) +Picking the only option: Answer 1: bubble-up-LiftVars: Bubbling up auxiliary variables through a comprehension. + { [conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)] + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } +storedChoice: +[{ conjure_aux2_2[q8_1, q8_2] = conjure_aux4 + @ find conjure_aux4: int(1..5) + such that + (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ + (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) + } | q8_1 : int(1..5), q8_2 : int(1..5)] 4586595665260781575 +AnsweredRule {qHole_ = 4586595665260781575, qAscendants_ = fromList [-5189262863924670079,-4576870578376860616,-3657040581488238581,667350004362937900,5588145911994567168,7042957946885141470,7965291691177128164], aRuleName_ = "bubble-up-LiftVars"} +LF: {"AnsweredRule":{"aRuleName_":"bubble-up-LiftVars","qAscendants_":[-5189262863924670079,-4576870578376860616,-3657040581488238581,667350004362937900,5588145911994567168,7042957946885141470,7965291691177128164],"qHole_":4586595665260781575}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and({ [conjure_aux2 in conjure_aux1 | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + and({ [conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)] + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }) + }) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: { [conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)] + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + Context #1: and({ [conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)] + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }) +Picking the only option: Answer 1: choose-repr-for-locals: Choosing representation for local variable conjure_aux4 + { [conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)] + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } +storedChoice: +{ [conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)] +@ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) +} -1434005429531325525 +AnsweredRule {qHole_ = -1434005429531325525, qAscendants_ = fromList [-7860778431127922714,-4340120710083553155,-3276746255609047616,-2418004144569851915,-329464522225361142,8566682329173394842,8971959176905079767], aRuleName_ = "choose-repr-for-locals"} +LF: {"AnsweredRule":{"aRuleName_":"choose-repr-for-locals","qAscendants_":[-7860778431127922714,-4340120710083553155,-3276746255609047616,-2418004144569851915,-329464522225361142,8566682329173394842,8971959176905079767],"qHole_":-1434005429531325525}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and({ [conjure_aux2 in conjure_aux1 | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + and({ [conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)] + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }) + }) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: and({ [conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] + | q8_1 : int(1..5), q8_2 : int(1..5)] + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }) + Context #1: { [conjure_aux2 in conjure_aux1 | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + and({ [conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)] + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }) + } +Picking the only option: Answer 1: bubble-up-LiftVars: Bubbling up auxiliary variables. + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } +storedChoice: +and({ [conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)] + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }) -329464522225361142 +AnsweredRule {qHole_ = -329464522225361142, qAscendants_ = fromList [-7860778431127922714,-4340120710083553155,-3276746255609047616,-2418004144569851915,8566682329173394842,8971959176905079767], aRuleName_ = "bubble-up-LiftVars"} +LF: {"AnsweredRule":{"aRuleName_":"bubble-up-LiftVars","qAscendants_":[-7860778431127922714,-4340120710083553155,-3276746255609047616,-2418004144569851915,8566682329173394842,8971959176905079767],"qHole_":-329464522225361142}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and({ [conjure_aux2 in conjure_aux1 | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + }) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: conjure_aux2 in conjure_aux1 + Context #1: [conjure_aux2 in conjure_aux1 | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] +Picking the only option: Answer 1: relation-in: relation membership to existential quantification + or([q27 = conjure_aux2 | q27 <- toSet(conjure_aux1)]) +storedChoice: +conjure_aux2 in conjure_aux1 7266634060293924720 +AnsweredRule {qHole_ = 7266634060293924720, qAscendants_ = fromList [-7266324578771459181,-6713121642540228318,-5826297241095436731,-5526349309453330732,1756707357159771390,2149626909839152329,4938058042264599181], aRuleName_ = "relation-in"} +LF: {"AnsweredRule":{"aRuleName_":"relation-in","qAscendants_":[-7266324578771459181,-6713121642540228318,-5826297241095436731,-5526349309453330732,1756707357159771390,2149626909839152329,4938058042264599181],"qHole_":7266634060293924720}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and({ [or([q27 = conjure_aux2 | q27 <- toSet(conjure_aux1)]) | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + }) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: [q27 = conjure_aux2 | q27 <- toSet(conjure_aux1)] + Context #1: or([q27 = conjure_aux2 | q27 <- toSet(conjure_aux1)]) +Picking the only option: Answer 1: relation-map_in_expr{RelationAsMatrix}: Vertical rule for map_in_expr for relation domains, RelationAsMatrix representation. + [(q28[1], q28[2]) = conjure_aux2 | q28 : (int(1..5), int(1..5)), conjure_aux1_RelationAsMatrix[q28[1], q28[2]]] +storedChoice: +[q27 = conjure_aux2 | q27 <- toSet(conjure_aux1)] -3470261408387399930 +AnsweredRule {qHole_ = -3470261408387399930, qAscendants_ = fromList [-8536113027950480792,-7330204231396072871,-4786623393387445427,-4223003553667075844,4116516722814445548,4281838781863596501,6175095517354461663,6559035824535384582], aRuleName_ = "relation-map_in_expr{RelationAsMatrix}"} +LF: {"AnsweredRule":{"aRuleName_":"relation-map_in_expr{RelationAsMatrix}","qAscendants_":[-8536113027950480792,-7330204231396072871,-4786623393387445427,-4223003553667075844,4116516722814445548,4281838781863596501,6175095517354461663,6559035824535384582],"qHole_":-3470261408387399930}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and({ [or([(q28[1], q28[2]) = conjure_aux2 | q28 : (int(1..5), int(1..5)), conjure_aux1_RelationAsMatrix[q28[1], q28[2]]]) + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + }) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: [(q28[1], q28[2]) = conjure_aux2 + | q28 : (int(1..5), int(1..5)), conjure_aux1_RelationAsMatrix[q28[1], q28[2]]] + Context #1: or([(q28[1], q28[2]) = conjure_aux2 | q28 : (int(1..5), int(1..5)), conjure_aux1_RelationAsMatrix[q28[1], q28[2]]]) +Picking the only option: Answer 1: choose-repr-for-comprehension: Choosing representation for quantified variable q28 (with type: (int, + int)) + [(q28[1], q28[2]) = conjure_aux2 | q28_1 : int(1..5), q28_2 : int(1..5), conjure_aux1_RelationAsMatrix[q28[1], q28[2]]] +storedChoice: +[(q28[1], q28[2]) = conjure_aux2 | q28 : (int(1..5), int(1..5)), conjure_aux1_RelationAsMatrix[q28[1], q28[2]]] 4348009411125732066 +AnsweredRule {qHole_ = 4348009411125732066, qAscendants_ = fromList [-6592612559904363413,-6472871177545322172,-6453293890463000807,-2235240472846537890,3259852529283772574,4455209103885624492,6352194885377054835,8420829954716127361], aRuleName_ = "choose-repr-for-comprehension"} +LF: {"AnsweredRule":{"aRuleName_":"choose-repr-for-comprehension","qAscendants_":[-6592612559904363413,-6472871177545322172,-6453293890463000807,-2235240472846537890,3259852529283772574,4455209103885624492,6352194885377054835,8420829954716127361],"qHole_":4348009411125732066}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and({ [or([(q28[1], q28[2]) = conjure_aux2 | q28_1 : int(1..5), q28_2 : int(1..5), conjure_aux1_RelationAsMatrix[q28[1], q28[2]]]) + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + }) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: (q28[1], q28[2]) = conjure_aux2 + Context #1: [(q28[1], q28[2]) = conjure_aux2 | q28_1 : int(1..5), q28_2 : int(1..5), conjure_aux1_RelationAsMatrix[q28[1], q28[2]]] +Picking the only option: Answer 1: tuple-eq: Horizontal rule for tuple equality + q28[1] = conjure_aux2_1 /\ q28[2] = conjure_aux2_2 +storedChoice: +(q28[1], q28[2]) = conjure_aux2 -4124337097652933443 +AnsweredRule {qHole_ = -4124337097652933443, qAscendants_ = fromList [-6634517003356473421,-4157154907530130258,-932339049260687039,4056979115757602560,5419805607560390341,5700344114265930133,8275228852675492835,8651388538213571462,8952456806918978808], aRuleName_ = "tuple-eq"} +LF: {"AnsweredRule":{"aRuleName_":"tuple-eq","qAscendants_":[-6634517003356473421,-4157154907530130258,-932339049260687039,4056979115757602560,5419805607560390341,5700344114265930133,8275228852675492835,8651388538213571462,8952456806918978808],"qHole_":-4124337097652933443}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and({ [or([q28[1] = conjure_aux2_1 /\ q28[2] = conjure_aux2_2 + | q28_1 : int(1..5), q28_2 : int(1..5), conjure_aux1_RelationAsMatrix[q28[1], q28[2]]]) + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + }) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: q28[1] + Context #1: q28[1] = conjure_aux2_1 +Picking the only option: Answer 1: tuple-index: Tuple indexing on: q28[1] + q28_1 +storedChoice: +q28[1] 8787010607011614834 +AnsweredRule {qHole_ = 8787010607011614834, qAscendants_ = fromList [-8956326597613561383,-6532059540256123763,-6109385609926416455,-3678896154897738560,-419523469793567323,-407169135612228618,2034669589965157861,4997220444967745554,6148375269450574671,6513082934840114429,8747477145020099131,8922317001415918920], aRuleName_ = "tuple-index"} +LF: {"AnsweredRule":{"aRuleName_":"tuple-index","qAscendants_":[-8956326597613561383,-6532059540256123763,-6109385609926416455,-3678896154897738560,-419523469793567323,-407169135612228618,2034669589965157861,4997220444967745554,6148375269450574671,6513082934840114429,8747477145020099131,8922317001415918920],"qHole_":8787010607011614834}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and({ [or([q28_1 = conjure_aux2_1 /\ q28[2] = conjure_aux2_2 + | q28_1 : int(1..5), q28_2 : int(1..5), conjure_aux1_RelationAsMatrix[q28[1], q28[2]]]) + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + }) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: q28[2] + Context #1: q28[2] = conjure_aux2_2 +Picking the only option: Answer 1: tuple-index: Tuple indexing on: q28[2] + q28_2 +storedChoice: +q28[2] 8786166143426335913 +AnsweredRule {qHole_ = 8786166143426335913, qAscendants_ = fromList [-7531325615783388500,-6124769537006831453,-2577262930135244673,-590286472771932315,-83534367005148570,715122028962684739,1709615173437954783,5607005680561137835,7486385006046341809,7705725891024727552,8323234866884020390,8780789924434106151], aRuleName_ = "tuple-index"} +LF: {"AnsweredRule":{"aRuleName_":"tuple-index","qAscendants_":[-7531325615783388500,-6124769537006831453,-2577262930135244673,-590286472771932315,-83534367005148570,715122028962684739,1709615173437954783,5607005680561137835,7486385006046341809,7705725891024727552,8323234866884020390,8780789924434106151],"qHole_":8786166143426335913}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and({ [or([q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2 + | q28_1 : int(1..5), q28_2 : int(1..5), conjure_aux1_RelationAsMatrix[q28[1], q28[2]]]) + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + }) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: q28[1] + Context #1: conjure_aux1_RelationAsMatrix[q28[1]] +Picking the only option: Answer 1: tuple-index: Tuple indexing on: q28[1] + q28_1 +storedChoice: +q28[1] 8787010607011614834 +AnsweredRule {qHole_ = 8787010607011614834, qAscendants_ = fromList [-6233761776568569553,-6207878452900388515,-3381866216268371578,-560496032557153780,-80631966925160875,1067854355870431415,1108013619790213016,4161317878060049142,4647826867886404607,5228020545282852391,8646369751965333728], aRuleName_ = "tuple-index"} +LF: {"AnsweredRule":{"aRuleName_":"tuple-index","qAscendants_":[-6233761776568569553,-6207878452900388515,-3381866216268371578,-560496032557153780,-80631966925160875,1067854355870431415,1108013619790213016,4161317878060049142,4647826867886404607,5228020545282852391,8646369751965333728],"qHole_":8787010607011614834}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and({ [or([q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2 + | q28_1 : int(1..5), q28_2 : int(1..5), conjure_aux1_RelationAsMatrix[q28_1, q28[2]]]) + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + }) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: q28[2] + Context #1: conjure_aux1_RelationAsMatrix[q28_1, q28[2]] +Picking the only option: Answer 1: tuple-index: Tuple indexing on: q28[2] + q28_2 +storedChoice: +q28[2] 8786166143426335913 +AnsweredRule {qHole_ = 8786166143426335913, qAscendants_ = fromList [-8932183048783716768,-6021176910053718006,-1484921959836170832,-1243263695470418987,-307241860641088143,5123914162100475129,6415834318102058907,6682610423178443283,7959220516069049554,8895625464985590456], aRuleName_ = "tuple-index"} +LF: {"AnsweredRule":{"aRuleName_":"tuple-index","qAscendants_":[-8932183048783716768,-6021176910053718006,-1484921959836170832,-1243263695470418987,-307241860641088143,5123914162100475129,6415834318102058907,6682610423178443283,7959220516069049554,8895625464985590456],"qHole_":8786166143426335913}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and({ [or([q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2 + | q28_1 : int(1..5), q28_2 : int(1..5), conjure_aux1_RelationAsMatrix[q28_1, q28_2]]) + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + }) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: [q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2 + | q28_1 : int(1..5), q28_2 : int(1..5), conjure_aux1_RelationAsMatrix[q28_1, q28_2]] + Context #1: or([q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2 + | q28_1 : int(1..5), q28_2 : int(1..5), conjure_aux1_RelationAsMatrix[q28_1, q28_2]]) +Picking the only option: Answer 1: inline-conditions: Inlining conditions, inside or + [conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)] +storedChoice: +[q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2 + | q28_1 : int(1..5), q28_2 : int(1..5), conjure_aux1_RelationAsMatrix[q28_1, q28_2]] -9107354217279316955 +AnsweredRule {qHole_ = -9107354217279316955, qAscendants_ = fromList [-7614046741660552896,-7556360939789777851,-6910364700408604777,-6183630476596424374,-2673910102480230275,7059218223957164648,8407785490318688805,8504193122766115214], aRuleName_ = "inline-conditions"} +LF: {"AnsweredRule":{"aRuleName_":"inline-conditions","qAscendants_":[-7614046741660552896,-7556360939789777851,-6910364700408604777,-6183630476596424374,-2673910102480230275,7059218223957164648,8407785490318688805,8504193122766115214],"qHole_":-9107354217279316955}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + and({ [or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + }) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: and({ [or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ + (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + }) + Context #1: [|x| = |conjure_aux1|, + and({ [or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + }); + int(1..2)] +Picking the only option: Answer 1: bubble-up-LiftVars: Bubbling up auxiliary variables. + { and([or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]]) + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + } +storedChoice: +and({ [or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + }) 7825224301270217826 +AnsweredRule {qHole_ = 7825224301270217826, qAscendants_ = fromList [-7337214924393354854,-6793331199204698657,4098536301578040545,4694401685199555588], aRuleName_ = "bubble-up-LiftVars"} +LF: {"AnsweredRule":{"aRuleName_":"bubble-up-LiftVars","qAscendants_":[-7337214924393354854,-6793331199204698657,4098536301578040545,4694401685199555588],"qHole_":7825224301270217826}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + { and([or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]]) + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + } + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: [or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ + (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] + Context #1: and([or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]]) +Picking the only option: Answer 1: inline-conditions: Inlining conditions, inside and + [x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)] +storedChoice: +[or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] -7818394351581759390 +AnsweredRule {qHole_ = -7818394351581759390, qAscendants_ = fromList [-8854367752148363141,868987242372315934,1952008385480716564,2094581585082781447,3197112935473569797,5197989222011368608], aRuleName_ = "inline-conditions"} +LF: {"AnsweredRule":{"aRuleName_":"inline-conditions","qAscendants_":[-8854367752148363141,868987242372315934,1952008385480716564,2094581585082781447,3197112935473569797,5197989222011368608],"qHole_":-7818394351581759390}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + |x| = |conjure_aux1| /\ + { and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + } + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: [|x| = |conjure_aux1|, + { and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + }; int(1..2)] + Context #1: |x| = |conjure_aux1| /\ + { and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + } +Picking the only option: Answer 1: bubble-up-LiftVars: Bubbling up auxiliary variables. + { [|x| = |conjure_aux1|, + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]); + int(1..2)] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + } +storedChoice: +[|x| = |conjure_aux1|, + { and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + }; int(1..2)] 8700659888572119213 +AnsweredRule {qHole_ = 8700659888572119213, qAscendants_ = fromList [1085907639859271742,5213477129051060331,8301951387372896488], aRuleName_ = "bubble-up-LiftVars"} +LF: {"AnsweredRule":{"aRuleName_":"bubble-up-LiftVars","qAscendants_":[1085907639859271742,5213477129051060331,8301951387372896488],"qHole_":8700659888572119213}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + and({ [|x| = |conjure_aux1|, + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]); + int(1..2)] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + }) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: |x| + Context #1: |x| = |conjure_aux1| +Picking the only option: Answer 1: relation-cardinality: Relation cardinality + |toSet(x)| +storedChoice: +|x| -1852370716973049233 +AnsweredRule {qHole_ = -1852370716973049233, qAscendants_ = fromList [-8274899275771564111,-7189265364834618222,-4195293662753593531,-2250203036499850017,4837893138970417558,5156053544824672407], aRuleName_ = "relation-cardinality"} +LF: {"AnsweredRule":{"aRuleName_":"relation-cardinality","qAscendants_":[-8274899275771564111,-7189265364834618222,-4195293662753593531,-2250203036499850017,4837893138970417558,5156053544824672407],"qHole_":-1852370716973049233}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + and({ [|toSet(x)| = |conjure_aux1|, + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]); + int(1..2)] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + }) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: |toSet(x)| + Context #1: |toSet(x)| = |conjure_aux1| +Picking the only option: Answer 1: set-card: Horizontal rule for set cardinality. + sum([1 | q29 <- toSet(x)]) +storedChoice: +|toSet(x)| 1897988597909520616 +AnsweredRule {qHole_ = 1897988597909520616, qAscendants_ = fromList [-6188688663705288789,-5846429895491118400,361855989135376679,6530150935582701688,7219968226893579546,7779309324238844246], aRuleName_ = "set-card"} +LF: {"AnsweredRule":{"aRuleName_":"set-card","qAscendants_":[-6188688663705288789,-5846429895491118400,361855989135376679,6530150935582701688,7219968226893579546,7779309324238844246],"qHole_":1897988597909520616}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + and({ [sum([1 | q29 <- toSet(x)]) = |conjure_aux1|, + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]); + int(1..2)] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + }) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: [1 | q29 <- toSet(x)] + Context #1: sum([1 | q29 <- toSet(x)]) +Picking the only option: Answer 1: relation-map_in_expr{RelationAsMatrix}: Vertical rule for map_in_expr for relation domains, RelationAsMatrix representation. + [1 | q30 : (int(1..5), int(1..5)), x_RelationAsMatrix[q30[1], q30[2]]] +storedChoice: +[1 | q29 <- toSet(x)] 7483192753320191769 +AnsweredRule {qHole_ = 7483192753320191769, qAscendants_ = fromList [-7918094600437589284,-6091097458145320110,-4725927117271772380,-3818842550960350061,-801403655548510881,4177802111281067004,8691639764190092042], aRuleName_ = "relation-map_in_expr{RelationAsMatrix}"} +LF: {"AnsweredRule":{"aRuleName_":"relation-map_in_expr{RelationAsMatrix}","qAscendants_":[-7918094600437589284,-6091097458145320110,-4725927117271772380,-3818842550960350061,-801403655548510881,4177802111281067004,8691639764190092042],"qHole_":7483192753320191769}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + and({ [sum([1 | q30 : (int(1..5), int(1..5)), x_RelationAsMatrix[q30[1], q30[2]]]) = |conjure_aux1|, + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]); + int(1..2)] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + }) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: [1 | q30 : (int(1..5), int(1..5)), x_RelationAsMatrix[q30[1], q30[2]]] + Context #1: sum([1 | q30 : (int(1..5), int(1..5)), x_RelationAsMatrix[q30[1], q30[2]]]) +Picking the only option: Answer 1: choose-repr-for-comprehension: Choosing representation for quantified variable q30 (with type: (int, + int)) + [1 | q30_1 : int(1..5), q30_2 : int(1..5), x_RelationAsMatrix[q30[1], q30[2]]] +storedChoice: +[1 | q30 : (int(1..5), int(1..5)), x_RelationAsMatrix[q30[1], q30[2]]] -2219318056453463832 +AnsweredRule {qHole_ = -2219318056453463832, qAscendants_ = fromList [-7631595452381029825,-6332648069028765836,-5599362277318624933,-1170492770147107149,188905738781826972,1046361987104095667,9181513732839926293], aRuleName_ = "choose-repr-for-comprehension"} +LF: {"AnsweredRule":{"aRuleName_":"choose-repr-for-comprehension","qAscendants_":[-7631595452381029825,-6332648069028765836,-5599362277318624933,-1170492770147107149,188905738781826972,1046361987104095667,9181513732839926293],"qHole_":-2219318056453463832}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + and({ [sum([1 | q30_1 : int(1..5), q30_2 : int(1..5), x_RelationAsMatrix[q30[1], q30[2]]]) = |conjure_aux1|, + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]); + int(1..2)] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + }) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: q30[1] + Context #1: x_RelationAsMatrix[q30[1]] +Picking the only option: Answer 1: tuple-index: Tuple indexing on: q30[1] + q30_1 +storedChoice: +q30[1] 8985411351629801837 +AnsweredRule {qHole_ = 8985411351629801837, qAscendants_ = fromList [-7287907811082918289,-3433749237930268197,-1514549063082826885,-254808116082235497,1395102958002486929,3724900484480857440,3763839719817425200,3764103551892886579,7098469255683427931,8809290278576126972], aRuleName_ = "tuple-index"} +LF: {"AnsweredRule":{"aRuleName_":"tuple-index","qAscendants_":[-7287907811082918289,-3433749237930268197,-1514549063082826885,-254808116082235497,1395102958002486929,3724900484480857440,3763839719817425200,3764103551892886579,7098469255683427931,8809290278576126972],"qHole_":8985411351629801837}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + and({ [sum([1 | q30_1 : int(1..5), q30_2 : int(1..5), x_RelationAsMatrix[q30_1, q30[2]]]) = |conjure_aux1|, + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]); + int(1..2)] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + }) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: q30[2] + Context #1: x_RelationAsMatrix[q30_1, q30[2]] +Picking the only option: Answer 1: tuple-index: Tuple indexing on: q30[2] + q30_2 +storedChoice: +q30[2] 8986255815215080758 +AnsweredRule {qHole_ = 8986255815215080758, qAscendants_ = fromList [-1904605123138931514,-1605383351683875510,-1500814072571245463,-1159370656118278861,-345152881798089093,3653718321561964858,5560045049720260591,6001294353827372355,7845034033468093823], aRuleName_ = "tuple-index"} +LF: {"AnsweredRule":{"aRuleName_":"tuple-index","qAscendants_":[-1904605123138931514,-1605383351683875510,-1500814072571245463,-1159370656118278861,-345152881798089093,3653718321561964858,5560045049720260591,6001294353827372355,7845034033468093823],"qHole_":8986255815215080758}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + and({ [sum([1 | q30_1 : int(1..5), q30_2 : int(1..5), x_RelationAsMatrix[q30_1, q30_2]]) = |conjure_aux1|, + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]); + int(1..2)] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + }) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: [1 | q30_1 : int(1..5), q30_2 : int(1..5), x_RelationAsMatrix[q30_1, q30_2]] + Context #1: sum([1 | q30_1 : int(1..5), q30_2 : int(1..5), x_RelationAsMatrix[q30_1, q30_2]]) +Picking the only option: Answer 1: inline-conditions: Inlining conditions, inside sum + [toInt(x_RelationAsMatrix[q30_1, q30_2]) * catchUndef(1, 0) | q30_1 : int(1..5), q30_2 : int(1..5)] +storedChoice: +[1 | q30_1 : int(1..5), q30_2 : int(1..5), x_RelationAsMatrix[q30_1, q30_2]] 6730778895089912004 +AnsweredRule {qHole_ = 6730778895089912004, qAscendants_ = fromList [-5543455485138138697,-1367499344277324489,-577770218778700729,3965135726409895025,4154476703970574900,4424005630299656964,8591791291160167043], aRuleName_ = "inline-conditions"} +LF: {"AnsweredRule":{"aRuleName_":"inline-conditions","qAscendants_":[-5543455485138138697,-1367499344277324489,-577770218778700729,3965135726409895025,4154476703970574900,4424005630299656964,8591791291160167043],"qHole_":6730778895089912004}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + and({ [sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) * catchUndef(1, 0) | q30_1 : int(1..5), q30_2 : int(1..5)]) = |conjure_aux1|, + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]); + int(1..2)] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + }) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: catchUndef(1, 0) + Context #1: [toInt(x_RelationAsMatrix[q30_1, q30_2]), catchUndef(1, 0); int(1..2)] +Picking the only option: Answer 1: full-evaluate: Full evaluator + 1 +storedChoice: +catchUndef(1, 0) -4103543015608659681 +AnsweredRule {qHole_ = -4103543015608659681, qAscendants_ = fromList [-6246651641675555191,-4991494778996523170,-4841212563091249093,-3913142375130629094,-3482484897580979170,-192545505272530247,4617164660703414243,7663465281870587155,7888233777833351600,8484251082711739255], aRuleName_ = "full-evaluate"} +LF: {"AnsweredRule":{"aRuleName_":"full-evaluate","qAscendants_":[-6246651641675555191,-4991494778996523170,-4841212563091249093,-3913142375130629094,-3482484897580979170,-192545505272530247,4617164660703414243,7663465281870587155,7888233777833351600,8484251082711739255],"qHole_":-4103543015608659681}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + and({ [sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) * 1 | q30_1 : int(1..5), q30_2 : int(1..5)]) = |conjure_aux1|, + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]); + int(1..2)] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + }) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: toInt(x_RelationAsMatrix[q30_1, q30_2]) * 1 + Context #1: [toInt(x_RelationAsMatrix[q30_1, q30_2]) * 1 | q30_1 : int(1..5), q30_2 : int(1..5)] +Picking the only option: Answer 1: partial-evaluate: Partial evaluator + product([toInt(x_RelationAsMatrix[q30_1, q30_2]); int(1)]) +storedChoice: +toInt(x_RelationAsMatrix[q30_1, q30_2]) * 1 -1687514346990485250 +AnsweredRule {qHole_ = -1687514346990485250, qAscendants_ = fromList [-8383279591293107624,-5870374077749082103,-5035592936147091491,-3450507034164856240,-3171744958437112094,-148321104615195040,923428228047877070,2221664695150773241], aRuleName_ = "partial-evaluate"} +LF: {"AnsweredRule":{"aRuleName_":"partial-evaluate","qAscendants_":[-8383279591293107624,-5870374077749082103,-5035592936147091491,-3450507034164856240,-3171744958437112094,-148321104615195040,923428228047877070,2221664695150773241],"qHole_":-1687514346990485250}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + and({ [sum([product([toInt(x_RelationAsMatrix[q30_1, q30_2]); int(1)]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = |conjure_aux1|, + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]); + int(1..2)] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + }) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: product([toInt(x_RelationAsMatrix[q30_1, q30_2]); int(1)]) + Context #1: [product([toInt(x_RelationAsMatrix[q30_1, q30_2]); int(1)]) | q30_1 : int(1..5), q30_2 : int(1..5)] +Picking the only option: Answer 1: matrix-comprehension-singleton: Removing quantifier of a single item + toInt(x_RelationAsMatrix[q30_1, q30_2]) +storedChoice: +product([toInt(x_RelationAsMatrix[q30_1, q30_2]); int(1)]) -601225972055529548 +AnsweredRule {qHole_ = -601225972055529548, qAscendants_ = fromList [-7799870564036439127,-7432780384698737696,-6354763341195320334,-5508479272970515476,-2004497734168533005,1354218247559476283,3284517275149475981,4357080134642246606], aRuleName_ = "matrix-comprehension-singleton"} +LF: {"AnsweredRule":{"aRuleName_":"matrix-comprehension-singleton","qAscendants_":[-7799870564036439127,-7432780384698737696,-6354763341195320334,-5508479272970515476,-2004497734168533005,1354218247559476283,3284517275149475981,4357080134642246606],"qHole_":-601225972055529548}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + and({ [sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = |conjure_aux1|, + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]); + int(1..2)] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + }) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: |conjure_aux1| + Context #1: sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = |conjure_aux1| +Picking the only option: Answer 1: relation-cardinality: Relation cardinality + |toSet(conjure_aux1)| +storedChoice: +|conjure_aux1| 547691173299348338 +AnsweredRule {qHole_ = 547691173299348338, qAscendants_ = fromList [-7326096647933004975,-3638343112521383479,-2681179249513342582,-1433468233918517477,416753721122881089,6250330639306929770], aRuleName_ = "relation-cardinality"} +LF: {"AnsweredRule":{"aRuleName_":"relation-cardinality","qAscendants_":[-7326096647933004975,-3638343112521383479,-2681179249513342582,-1433468233918517477,416753721122881089,6250330639306929770],"qHole_":547691173299348338}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + and({ [sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = |toSet(conjure_aux1)|, + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]); + int(1..2)] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + }) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: |toSet(conjure_aux1)| + Context #1: sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = |toSet(conjure_aux1)| +Picking the only option: Answer 1: set-card: Horizontal rule for set cardinality. + sum([1 | q31 <- toSet(conjure_aux1)]) +storedChoice: +|toSet(conjure_aux1)| -1999756309500896427 +AnsweredRule {qHole_ = -1999756309500896427, qAscendants_ = fromList [-7320026331482846196,-1560614952215100976,3610191966919989235,3922795876024111867,4652593413741964988,8460019197720106806], aRuleName_ = "set-card"} +LF: {"AnsweredRule":{"aRuleName_":"set-card","qAscendants_":[-7320026331482846196,-1560614952215100976,3610191966919989235,3922795876024111867,4652593413741964988,8460019197720106806],"qHole_":-1999756309500896427}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + and({ [sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = sum([1 | q31 <- toSet(conjure_aux1)]), + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]); + int(1..2)] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + }) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: [1 | q31 <- toSet(conjure_aux1)] + Context #1: sum([1 | q31 <- toSet(conjure_aux1)]) +Picking the only option: Answer 1: relation-map_in_expr{RelationAsMatrix}: Vertical rule for map_in_expr for relation domains, RelationAsMatrix representation. + [1 | q32 : (int(1..5), int(1..5)), conjure_aux1_RelationAsMatrix[q32[1], q32[2]]] +storedChoice: +[1 | q31 <- toSet(conjure_aux1)] 4978495210772817269 +AnsweredRule {qHole_ = 4978495210772817269, qAscendants_ = fromList [-7947851092910419335,-4272160902177458760,-654328132560036401,4133420425219294144,6369167416454940534,6390095031407007755,7113998651427981501], aRuleName_ = "relation-map_in_expr{RelationAsMatrix}"} +LF: {"AnsweredRule":{"aRuleName_":"relation-map_in_expr{RelationAsMatrix}","qAscendants_":[-7947851092910419335,-4272160902177458760,-654328132560036401,4133420425219294144,6369167416454940534,6390095031407007755,7113998651427981501],"qHole_":4978495210772817269}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + and({ [sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = + sum([1 | q32 : (int(1..5), int(1..5)), conjure_aux1_RelationAsMatrix[q32[1], q32[2]]]), + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]); + int(1..2)] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + }) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: [1 | q32 : (int(1..5), int(1..5)), conjure_aux1_RelationAsMatrix[q32[1], q32[2]]] + Context #1: sum([1 | q32 : (int(1..5), int(1..5)), conjure_aux1_RelationAsMatrix[q32[1], q32[2]]]) +Picking the only option: Answer 1: choose-repr-for-comprehension: Choosing representation for quantified variable q32 (with type: (int, + int)) + [1 | q32_1 : int(1..5), q32_2 : int(1..5), conjure_aux1_RelationAsMatrix[q32[1], q32[2]]] +storedChoice: +[1 | q32 : (int(1..5), int(1..5)), conjure_aux1_RelationAsMatrix[q32[1], q32[2]]] 3282965607985773269 +AnsweredRule {qHole_ = 3282965607985773269, qAscendants_ = fromList [-7122899784982260955,-5889198071192861072,-531055723096273851,147713573061616732,2477913925342540157,3767703974941705567,9091983968002426702], aRuleName_ = "choose-repr-for-comprehension"} +LF: {"AnsweredRule":{"aRuleName_":"choose-repr-for-comprehension","qAscendants_":[-7122899784982260955,-5889198071192861072,-531055723096273851,147713573061616732,2477913925342540157,3767703974941705567,9091983968002426702],"qHole_":3282965607985773269}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + and({ [sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = + sum([1 | q32_1 : int(1..5), q32_2 : int(1..5), conjure_aux1_RelationAsMatrix[q32[1], q32[2]]]), + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]); + int(1..2)] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + }) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: q32[1] + Context #1: conjure_aux1_RelationAsMatrix[q32[1]] +Picking the only option: Answer 1: tuple-index: Tuple indexing on: q32[1] + q32_1 +storedChoice: +q32[1] 4038868374035555703 +AnsweredRule {qHole_ = 4038868374035555703, qAscendants_ = fromList [-8553658543572221773,-6138711856874023512,-4335853381078465244,-2646146961819662754,-2343456358494450273,-1664802311461525085,-1649342081664357811,3161695419280017087,3741265834386353390,8703630850884516346], aRuleName_ = "tuple-index"} +LF: {"AnsweredRule":{"aRuleName_":"tuple-index","qAscendants_":[-8553658543572221773,-6138711856874023512,-4335853381078465244,-2646146961819662754,-2343456358494450273,-1664802311461525085,-1649342081664357811,3161695419280017087,3741265834386353390,8703630850884516346],"qHole_":4038868374035555703}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + and({ [sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = + sum([1 | q32_1 : int(1..5), q32_2 : int(1..5), conjure_aux1_RelationAsMatrix[q32_1, q32[2]]]), + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]); + int(1..2)] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + }) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: q32[2] + Context #1: conjure_aux1_RelationAsMatrix[q32_1, q32[2]] +Picking the only option: Answer 1: tuple-index: Tuple indexing on: q32[2] + q32_2 +storedChoice: +q32[2] 4038586886173796060 +AnsweredRule {qHole_ = 4038586886173796060, qAscendants_ = fromList [58246981470148902,365936135746281162,897915292494521279,2148255109439096362,2599338170801596327,4347596293011070033,8156974448309241515,8375135551163386670,8976994852842826417], aRuleName_ = "tuple-index"} +LF: {"AnsweredRule":{"aRuleName_":"tuple-index","qAscendants_":[58246981470148902,365936135746281162,897915292494521279,2148255109439096362,2599338170801596327,4347596293011070033,8156974448309241515,8375135551163386670,8976994852842826417],"qHole_":4038586886173796060}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + and({ [sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = + sum([1 | q32_1 : int(1..5), q32_2 : int(1..5), conjure_aux1_RelationAsMatrix[q32_1, q32_2]]), + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]); + int(1..2)] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + }) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: [1 | q32_1 : int(1..5), q32_2 : int(1..5), conjure_aux1_RelationAsMatrix[q32_1, q32_2]] + Context #1: sum([1 | q32_1 : int(1..5), q32_2 : int(1..5), conjure_aux1_RelationAsMatrix[q32_1, q32_2]]) +Picking the only option: Answer 1: inline-conditions: Inlining conditions, inside sum + [toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) * catchUndef(1, 0) | q32_1 : int(1..5), q32_2 : int(1..5)] +storedChoice: +[1 | q32_1 : int(1..5), q32_2 : int(1..5), conjure_aux1_RelationAsMatrix[q32_1, q32_2]] -5719405584779695493 +AnsweredRule {qHole_ = -5719405584779695493, qAscendants_ = fromList [-9027745215861162370,-8099216132366058965,-5857000228242749317,-5553782237459419472,4623787234387693138,7124000196337888585,8079567542521963183], aRuleName_ = "inline-conditions"} +LF: {"AnsweredRule":{"aRuleName_":"inline-conditions","qAscendants_":[-9027745215861162370,-8099216132366058965,-5857000228242749317,-5553782237459419472,4623787234387693138,7124000196337888585,8079567542521963183],"qHole_":-5719405584779695493}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + and({ [sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = + sum([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) * catchUndef(1, 0) | q32_1 : int(1..5), q32_2 : int(1..5)]), + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]); + int(1..2)] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + }) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: catchUndef(1, 0) + Context #1: [toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]), catchUndef(1, 0); int(1..2)] +Picking the only option: Answer 1: full-evaluate: Full evaluator + 1 +storedChoice: +catchUndef(1, 0) -4103543015608659681 +AnsweredRule {qHole_ = -4103543015608659681, qAscendants_ = fromList [-8969688714663757079,-8620054688580705850,-7803342152587091485,-6406402188841036454,-3137912990386087120,-2245754891843782432,-893701506107809144,-421079377584717971,4859060653783625533,9081980220064719370], aRuleName_ = "full-evaluate"} +LF: {"AnsweredRule":{"aRuleName_":"full-evaluate","qAscendants_":[-8969688714663757079,-8620054688580705850,-7803342152587091485,-6406402188841036454,-3137912990386087120,-2245754891843782432,-893701506107809144,-421079377584717971,4859060653783625533,9081980220064719370],"qHole_":-4103543015608659681}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + and({ [sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = + sum([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) * 1 | q32_1 : int(1..5), q32_2 : int(1..5)]), + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]); + int(1..2)] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + }) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) * 1 + Context #1: [toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) * 1 | q32_1 : int(1..5), q32_2 : int(1..5)] +Picking the only option: Answer 1: partial-evaluate: Partial evaluator + product([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]); int(1)]) +storedChoice: +toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) * 1 -4682469706785037945 +AnsweredRule {qHole_ = -4682469706785037945, qAscendants_ = fromList [-9179050654683062954,-8797033748133430528,-8329454991333631126,-5647606918064816013,-3380861767487578940,6010365049512866508,6747419370843152779,7119833088853932687], aRuleName_ = "partial-evaluate"} +LF: {"AnsweredRule":{"aRuleName_":"partial-evaluate","qAscendants_":[-9179050654683062954,-8797033748133430528,-8329454991333631126,-5647606918064816013,-3380861767487578940,6010365049512866508,6747419370843152779,7119833088853932687],"qHole_":-4682469706785037945}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + and({ [sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = + sum([product([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]); int(1)]) | q32_1 : int(1..5), q32_2 : int(1..5)]), + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]); + int(1..2)] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + }) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: product([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]); int(1)]) + Context #1: [product([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]); int(1)]) | q32_1 : int(1..5), q32_2 : int(1..5)] +Picking the only option: Answer 1: matrix-comprehension-singleton: Removing quantifier of a single item + toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) +storedChoice: +product([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]); int(1)]) -3618757702268377732 +AnsweredRule {qHole_ = -3618757702268377732, qAscendants_ = fromList [-3180788541249390624,-1419697389512850335,2051112281511221751,3011082682326874338,4702464191332467431,4730858055169822202,6821954100224183740,8108702534288021537], aRuleName_ = "matrix-comprehension-singleton"} +LF: {"AnsweredRule":{"aRuleName_":"matrix-comprehension-singleton","qAscendants_":[-3180788541249390624,-1419697389512850335,2051112281511221751,3011082682326874338,4702464191332467431,4730858055169822202,6821954100224183740,8108702534288021537],"qHole_":-3618757702268377732}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + and({ [sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = + sum([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) | q32_1 : int(1..5), q32_2 : int(1..5)]), + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]); + int(1..2)] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + }) + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: and({ [sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = + sum([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) | q32_1 : int(1..5), q32_2 : int(1..5)]), + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]); + int(1..2)] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + }) + Context #1: { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + and({ [sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = + sum([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) | q32_1 : int(1..5), q32_2 : int(1..5)]), + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]); + int(1..2)] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + }) + } +Picking the only option: Answer 1: bubble-up-LiftVars: Bubbling up auxiliary variables. + { sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = + sum([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) | q32_1 : int(1..5), q32_2 : int(1..5)]) + /\ + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + } +storedChoice: +and({ [sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = + sum([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) | q32_1 : int(1..5), q32_2 : int(1..5)]), + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]); + int(1..2)] + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + }) -4558336889735046944 +AnsweredRule {qHole_ = -4558336889735046944, qAscendants_ = fromList [-3486949521822083211,2980043443155673363], aRuleName_ = "bubble-up-LiftVars"} +LF: {"AnsweredRule":{"aRuleName_":"bubble-up-LiftVars","qAscendants_":[-3486949521822083211,2980043443155673363],"qHole_":-4558336889735046944}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + { sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = + sum([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) | q32_1 : int(1..5), q32_2 : int(1..5)]) + /\ + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + } + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: y = + { conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + { sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = + sum([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) | q32_1 : int(1..5), q32_2 : int(1..5)]) + /\ + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + } + } +Picking the only option: Answer 1: bubble-up-LiftVars: Bubbling up auxiliary variables. + { y = conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + { sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = + sum([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) | q32_1 : int(1..5), q32_2 : int(1..5)]) + /\ + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + } + } +storedChoice: +y = +{ conjure_aux1 +@ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + { sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = + sum([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) | q32_1 : int(1..5), q32_2 : int(1..5)]) + /\ + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + } +} 8908675996089062110 +AnsweredRule {qHole_ = 8908675996089062110, qAscendants_ = fromList [], aRuleName_ = "bubble-up-LiftVars"} +LF: {"AnsweredRule":{"aRuleName_":"bubble-up-LiftVars","qAscendants_":[],"qHole_":8908675996089062110}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + { y = conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + { sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = + sum([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) | q32_1 : int(1..5), q32_2 : int(1..5)]) + /\ + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + } + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: y = conjure_aux1 + Context #1: { y = conjure_aux1 + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + { sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = + sum([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) | q32_1 : int(1..5), q32_2 : int(1..5)]) + /\ + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + } + } +Picking the only option: Answer 1: identical-domain-eq: Generic vertical rule for identical-domain equality + and([y_RelationAsMatrix = conjure_aux1_RelationAsMatrix; int(1)]) +storedChoice: +y = conjure_aux1 3717099060101766216 +AnsweredRule {qHole_ = 3717099060101766216, qAscendants_ = fromList [2671848414499686108], aRuleName_ = "identical-domain-eq"} +LF: {"AnsweredRule":{"aRuleName_":"identical-domain-eq","qAscendants_":[2671848414499686108],"qHole_":3717099060101766216}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + { and([y_RelationAsMatrix = conjure_aux1_RelationAsMatrix; int(1)]) + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + { sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = + sum([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) | q32_1 : int(1..5), q32_2 : int(1..5)]) + /\ + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + } + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: y_RelationAsMatrix = conjure_aux1_RelationAsMatrix + Context #1: [y_RelationAsMatrix = conjure_aux1_RelationAsMatrix; int(1)] +Picking the only option: Answer 1: matrix-eq: Horizontal rule for matrix = + and([y_RelationAsMatrix[q33] = conjure_aux1_RelationAsMatrix[q33] | q33 : int(1..5)]) +storedChoice: +y_RelationAsMatrix = conjure_aux1_RelationAsMatrix 847538541028825252 +AnsweredRule {qHole_ = 847538541028825252, qAscendants_ = fromList [-7545604584042643741,-3140704007737949652,8589500105863926587], aRuleName_ = "matrix-eq"} +LF: {"AnsweredRule":{"aRuleName_":"matrix-eq","qAscendants_":[-7545604584042643741,-3140704007737949652,8589500105863926587],"qHole_":847538541028825252}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + { and([and([y_RelationAsMatrix[q33] = conjure_aux1_RelationAsMatrix[q33] | q33 : int(1..5)]); int(1)]) + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + { sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = + sum([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) | q32_1 : int(1..5), q32_2 : int(1..5)]) + /\ + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + } + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: [y_RelationAsMatrix[q33] = conjure_aux1_RelationAsMatrix[q33] | q33 : int(1..5)] + Context #1: and([y_RelationAsMatrix[q33] = conjure_aux1_RelationAsMatrix[q33] | q33 : int(1..5)]) +Picking the only option: Answer 1: choose-repr-for-comprehension: Choosing representation for quantified variable q33 (with type: int) + [y_RelationAsMatrix[q33] = conjure_aux1_RelationAsMatrix[q33] | q33 : int(1..5)] +storedChoice: +[y_RelationAsMatrix[q33] = conjure_aux1_RelationAsMatrix[q33] | q33 : int(1..5)] 45103260545151270 +AnsweredRule {qHole_ = 45103260545151270, qAscendants_ = fromList [-5973861858959396663,-4660253290178341140,-3962474706459959320,-1163992588452778161], aRuleName_ = "choose-repr-for-comprehension"} +LF: {"AnsweredRule":{"aRuleName_":"choose-repr-for-comprehension","qAscendants_":[-5973861858959396663,-4660253290178341140,-3962474706459959320,-1163992588452778161],"qHole_":45103260545151270}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + { and([and([y_RelationAsMatrix[q33] = conjure_aux1_RelationAsMatrix[q33] | q33 : int(1..5)]); int(1)]) + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + { sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = + sum([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) | q32_1 : int(1..5), q32_2 : int(1..5)]) + /\ + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + } + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: y_RelationAsMatrix[q33] = conjure_aux1_RelationAsMatrix[q33] + Context #1: [y_RelationAsMatrix[q33] = conjure_aux1_RelationAsMatrix[q33] | q33 : int(1..5)] +Picking the only option: Answer 1: matrix-eq: Horizontal rule for matrix = + and([y_RelationAsMatrix[q33, q35] = conjure_aux1_RelationAsMatrix[q33, q35] | q35 : int(1..5)]) +storedChoice: +y_RelationAsMatrix[q33] = conjure_aux1_RelationAsMatrix[q33] 971298532972344754 +AnsweredRule {qHole_ = 971298532972344754, qAscendants_ = fromList [-5973861858959396663,-4660253290178341140,-3962474706459959320,-1163992588452778161,45103260545151270], aRuleName_ = "matrix-eq"} +LF: {"AnsweredRule":{"aRuleName_":"matrix-eq","qAscendants_":[-5973861858959396663,-4660253290178341140,-3962474706459959320,-1163992588452778161,45103260545151270],"qHole_":971298532972344754}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + { and([and([and([y_RelationAsMatrix[q33, q35] = conjure_aux1_RelationAsMatrix[q33, q35] | q35 : int(1..5)]) | q33 : int(1..5)]); + int(1)]) + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + { sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = + sum([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) | q32_1 : int(1..5), q32_2 : int(1..5)]) + /\ + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + } + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: [y_RelationAsMatrix[q33, q35] = conjure_aux1_RelationAsMatrix[q33, q35] | q35 : int(1..5)] + Context #1: and([y_RelationAsMatrix[q33, q35] = conjure_aux1_RelationAsMatrix[q33, q35] | q35 : int(1..5)]) +Picking the only option: Answer 1: choose-repr-for-comprehension: Choosing representation for quantified variable q35 (with type: int) + [y_RelationAsMatrix[q33, q35] = conjure_aux1_RelationAsMatrix[q33, q35] | q35 : int(1..5)] +storedChoice: +[y_RelationAsMatrix[q33, q35] = conjure_aux1_RelationAsMatrix[q33, q35] | q35 : int(1..5)] -1275491152285478671 +AnsweredRule {qHole_ = -1275491152285478671, qAscendants_ = fromList [-9124538447972763747,1151872964749555522,2218928338283019637,3574995822047355118,8452562685486794942,8526913528687567140], aRuleName_ = "choose-repr-for-comprehension"} +LF: {"AnsweredRule":{"aRuleName_":"choose-repr-for-comprehension","qAscendants_":[-9124538447972763747,1151872964749555522,2218928338283019637,3574995822047355118,8452562685486794942,8526913528687567140],"qHole_":-1275491152285478671}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + { and([and([and([y_RelationAsMatrix[q33, q35] = conjure_aux1_RelationAsMatrix[q33, q35] | q35 : int(1..5)]) | q33 : int(1..5)]); + int(1)]) + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + { sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = + sum([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) | q32_1 : int(1..5), q32_2 : int(1..5)]) + /\ + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + } + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: and([and([and([y_RelationAsMatrix[q33, q35] = conjure_aux1_RelationAsMatrix[q33, q35] + | q35 : int(1..5)]) + | q33 : int(1..5)]); + int(1)]) + Context #1: { and([and([and([y_RelationAsMatrix[q33, q35] = conjure_aux1_RelationAsMatrix[q33, q35] | q35 : int(1..5)]) + | q33 : int(1..5)]); + int(1)]) + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + { sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = + sum([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) | q32_1 : int(1..5), q32_2 : int(1..5)]) + /\ + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + } + } +Picking the only option: Answer 1: matrix-comprehension-singleton: Removing quantifier of a single item + and([and([y_RelationAsMatrix[q33, q35] = conjure_aux1_RelationAsMatrix[q33, q35] | q35 : int(1..5)]) | q33 : int(1..5)]) +storedChoice: +and([and([and([y_RelationAsMatrix[q33, q35] = conjure_aux1_RelationAsMatrix[q33, q35] | q35 : int(1..5)]) | q33 : int(1..5)]); + int(1)]) 3574995822047355118 +AnsweredRule {qHole_ = 3574995822047355118, qAscendants_ = fromList [1151872964749555522], aRuleName_ = "matrix-comprehension-singleton"} +LF: {"AnsweredRule":{"aRuleName_":"matrix-comprehension-singleton","qAscendants_":[1151872964749555522],"qHole_":3574995822047355118}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + { and([and([y_RelationAsMatrix[q33, q35] = conjure_aux1_RelationAsMatrix[q33, q35] | q35 : int(1..5)]) | q33 : int(1..5)]) + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + { sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = + sum([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) | q32_1 : int(1..5), q32_2 : int(1..5)]) + /\ + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + } + } + branching on [x, y] + such that + such that + true(x), + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: true(x) +Picking the only option: Answer 1: true-is-noop: Remove the argument from true. + true +storedChoice: +true(x) -1508832156878423928 +AnsweredRule {qHole_ = -1508832156878423928, qAscendants_ = fromList [], aRuleName_ = "true-is-noop"} +LF: {"AnsweredRule":{"aRuleName_":"true-is-noop","qAscendants_":[],"qHole_":-1508832156878423928}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + { and([and([y_RelationAsMatrix[q33, q35] = conjure_aux1_RelationAsMatrix[q33, q35] | q35 : int(1..5)]) | q33 : int(1..5)]) + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + { sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = + sum([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) | q32_1 : int(1..5), q32_2 : int(1..5)]) + /\ + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + } + } + branching on [x, y] + such that + such that + true, + true(y) + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +Picking the first option: Question 1: true(y) +Picking the only option: Answer 1: true-is-noop: Remove the argument from true. + true +storedChoice: +true(y) -1508550667338902379 +AnsweredRule {qHole_ = -1508550667338902379, qAscendants_ = fromList [], aRuleName_ = "true-is-noop"} +LF: {"AnsweredRule":{"aRuleName_":"true-is-noop","qAscendants_":[],"qHole_":-1508550667338902379}} END: +[loopy] language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + { and([and([y_RelationAsMatrix[q33, q35] = conjure_aux1_RelationAsMatrix[q33, q35] | q35 : int(1..5)]) | q33 : int(1..5)]) + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + { sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = + sum([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) | q32_1 : int(1..5), q32_2 : int(1..5)]) + /\ + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + } + } + branching on [x, y] + such that + such that + true, + true + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +[epilogue] + language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + { and([and([y_RelationAsMatrix[q33, q35] = conjure_aux1_RelationAsMatrix[q33, q35] | q35 : int(1..5)]) | q33 : int(1..5)]) + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + { sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = + sum([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) | q32_1 : int(1..5), q32_2 : int(1..5)]) + /\ + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + } + } + branching on [x, y] + such that + such that + true, + true + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +[dropTagForSR] + language Essence 1.3 + + letting p be permutation((3, 4)) + find x: relation (size 4) of (int(1..5) * int(1..5)) + find y: relation (size 4) of (int(1..5) * int(1..5)) + such that + { and([and([y_RelationAsMatrix[q33, q35] = conjure_aux1_RelationAsMatrix[q33, q35] | q35 : int(1..5)]) | q33 : int(1..5)]) + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + { sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = + sum([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) | q32_1 : int(1..5), q32_2 : int(1..5)]) + /\ + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + } + } + branching on [x, y] + such that + such that + true, + true + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +[updateDeclarations] + language Essence 1.3 + + find x_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + find y_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that + { and([and([y_RelationAsMatrix[q33, q35] = conjure_aux1_RelationAsMatrix[q33, q35] | q35 : int(1..5)]) | q33 : int(1..5)]) + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + { sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = + sum([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) | q32_1 : int(1..5), q32_2 : int(1..5)]) + /\ + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + } + } + branching on [x_RelationAsMatrix, y_RelationAsMatrix] + such that + such that + true, + true + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +[inlineDecVarLettings] + language Essence 1.3 + + find x_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + find y_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that + { and([and([y_RelationAsMatrix[q33, q35] = conjure_aux1_RelationAsMatrix[q33, q35] | q35 : int(1..5)]) | q33 : int(1..5)]) + @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + such that + { sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = + sum([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) | q32_1 : int(1..5), q32_2 : int(1..5)]) + /\ + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + }, + { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + } + } + } + branching on [x_RelationAsMatrix, y_RelationAsMatrix] + such that + such that + true, + true + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +[topLevelBubbles] + language Essence 1.3 + + find x_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + find y_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + such that and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + such that and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + such that + sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = + sum([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) | q32_1 : int(1..5), q32_2 : int(1..5)]) + /\ + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + such that and([and([y_RelationAsMatrix[q33, q35] = conjure_aux1_RelationAsMatrix[q33, q35] | q35 : int(1..5)]) | q33 : int(1..5)]) + branching on [x_RelationAsMatrix, y_RelationAsMatrix] + such that true + such that true + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +[checkIfAllRefined] + language Essence 1.3 + + find x_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + find y_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + such that and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + such that and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + such that + sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = + sum([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) | q32_1 : int(1..5), q32_2 : int(1..5)]) + /\ + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + such that and([and([y_RelationAsMatrix[q33, q35] = conjure_aux1_RelationAsMatrix[q33, q35] | q35 : int(1..5)]) | q33 : int(1..5)]) + branching on [x_RelationAsMatrix, y_RelationAsMatrix] + such that true + such that true + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +[checkIfHasUndefined] + language Essence 1.3 + + find x_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + find y_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + such that and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + such that and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + such that + sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = + sum([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) | q32_1 : int(1..5), q32_2 : int(1..5)]) + /\ + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + such that and([and([y_RelationAsMatrix[q33, q35] = conjure_aux1_RelationAsMatrix[q33, q35] | q35 : int(1..5)]) | q33 : int(1..5)]) + branching on [x_RelationAsMatrix, y_RelationAsMatrix] + such that true + such that true + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +[sliceThemMatrices] + language Essence 1.3 + + find x_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + find y_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + such that and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + such that and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + such that + sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = + sum([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) | q32_1 : int(1..5), q32_2 : int(1..5)]) + /\ + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + such that and([and([y_RelationAsMatrix[q33, q35] = conjure_aux1_RelationAsMatrix[q33, q35] | q35 : int(1..5)]) | q33 : int(1..5)]) + branching on [x_RelationAsMatrix, y_RelationAsMatrix] + such that true + such that true + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +[emptyMatrixLiterals] + language Essence 1.3 + + find x_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + find y_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + such that and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + such that and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + such that + sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = + sum([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) | q32_1 : int(1..5), q32_2 : int(1..5)]) + /\ + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + such that and([and([y_RelationAsMatrix[q33, q35] = conjure_aux1_RelationAsMatrix[q33, q35] | q35 : int(1..5)]) | q33 : int(1..5)]) + branching on [x_RelationAsMatrix, y_RelationAsMatrix] + such that true + such that true + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +[reverseTrails] + language Essence 1.3 + + find x_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + find y_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) + find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + such that and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + such that + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + such that and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) + such that + sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = + sum([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) | q32_1 : int(1..5), q32_2 : int(1..5)]) + /\ + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]) + such that and([and([y_RelationAsMatrix[q33, q35] = conjure_aux1_RelationAsMatrix[q33, q35] | q35 : int(1..5)]) | q33 : int(1..5)]) + branching on [x_RelationAsMatrix, y_RelationAsMatrix] + such that true + such that true + such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) + such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +[oneSuchThat] + language Essence 1.3 + + find x_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + find y_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + branching on [x_RelationAsMatrix, y_RelationAsMatrix] + such that + 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]), + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]), + and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]), + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]), + and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]), + sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = + sum([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) | q32_1 : int(1..5), q32_2 : int(1..5)]), + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]), + and([and([y_RelationAsMatrix[q33, q35] = conjure_aux1_RelationAsMatrix[q33, q35] | q35 : int(1..5)]) | q33 : int(1..5)]), + 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]), + 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + +[languageEprime] + language ESSENCE' 1.0 + + find x_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + find y_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool + find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) + branching on [x_RelationAsMatrix, y_RelationAsMatrix] + such that + 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]), + and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) + | q8_1 : int(1..5), q8_2 : int(1..5)]), + and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]), + and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ + (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) + | q8_1 : int(1..5), q8_2 : int(1..5)]), + and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]), + sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = + sum([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) | q32_1 : int(1..5), q32_2 : int(1..5)]), + and([x_RelationAsMatrix[q8_1, q8_2] -> + or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) + | q28_1 : int(1..5), q28_2 : int(1..5)]) + | q8_1 : int(1..5), q8_2 : int(1..5)]), + and([and([y_RelationAsMatrix[q33, q35] = conjure_aux1_RelationAsMatrix[q33, q35] | q35 : int(1..5)]) | q33 : int(1..5)]), + 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]), + 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) + From 4ccc2520c3fbf0fd995ce6a944ae964e6f1a700b Mon Sep 17 00:00:00 2001 From: Fraser Dunlop Date: Mon, 3 Dec 2018 12:13:22 +0000 Subject: [PATCH 036/229] inverse --- src/Conjure/Language/Expression/Op/Inverse.hs | 25 ++++++++--- src/Conjure/Rules/Horizontal/Permutation.hs | 19 ++++++++ .../Rules/Vertical/Permutation/AsFunction.hs | 42 ++++++++++++++++++ src/Conjure/UI/Model.hs | 4 +- tests/custom/permutations/basic/.DS_Store | Bin 0 -> 6148 bytes 5 files changed, 83 insertions(+), 7 deletions(-) create mode 100644 tests/custom/permutations/basic/.DS_Store diff --git a/src/Conjure/Language/Expression/Op/Inverse.hs b/src/Conjure/Language/Expression/Op/Inverse.hs index 8bec860cd7..4f20ec9669 100644 --- a/src/Conjure/Language/Expression/Op/Inverse.hs +++ b/src/Conjure/Language/Expression/Op/Inverse.hs @@ -9,6 +9,8 @@ import qualified Data.Aeson as JSON -- aeson import qualified Data.HashMap.Strict as M -- unordered-containers import qualified Data.Vector as V -- vector +import Data.Permutation + data OpInverse x = OpInverse x x deriving (Eq, Ord, Show, Data, Functor, Traversable, Foldable, Typeable, Generic) @@ -20,17 +22,30 @@ instance FromJSON x => FromJSON (OpInverse x) where parseJSON = genericParseJS instance (TypeOf x, Pretty x) => TypeOf (OpInverse x) where typeOf p@(OpInverse f g) = do - TypeFunction fFrom fTo <- typeOf f - TypeFunction gFrom gTo <- typeOf g - if typesUnify [fFrom, gTo] && typesUnify [fTo, gFrom] - then return TypeBool - else raiseTypeError p + ft <- typeOf f + case ft of + TypeFunction fFrom fTo -> do + TypeFunction gFrom gTo <- typeOf g + if typesUnify [fFrom, gTo] && typesUnify [fTo, gFrom] + then return TypeBool + else raiseTypeError p + TypePermutation fi -> do + TypePermutation gi <- typeOf g + if typesUnify [fi,gi] + then return TypeBool + else raiseTypeError p + _ -> raiseTypeError p instance EvaluateOp OpInverse where evaluateOp (OpInverse (viewConstantFunction -> Just xs) (viewConstantFunction -> Just ys)) = return $ ConstantBool $ and $ concat [ [ (j,i) `elem` ys | (i,j) <- xs ] , [ (j,i) `elem` xs | (i,j) <- ys ] ] + evaluateOp (OpInverse (viewConstantPermutation -> Just xs) (viewConstantPermutation -> Just ys)) = + case (toFunction <$> fromCycles xs, toFunction <$> fromCycles ys) of + (Right xfn, Right lfn) -> return $ ConstantBool $ and $ (\x -> x == lfn (xfn x)) <$> join xs + (Left (PermutationError e),_) -> na $ "evaluateOp{OpInverse}:" <++> pretty e + (_,Left (PermutationError e)) -> na $ "evaluateOp{OpInverse}:" <++> pretty e evaluateOp op = na $ "evaluateOp{OpInverse}:" <++> pretty (show op) instance SimplifyOp OpInverse x where diff --git a/src/Conjure/Rules/Horizontal/Permutation.hs b/src/Conjure/Rules/Horizontal/Permutation.hs index bb4291c683..6c5eafdca2 100644 --- a/src/Conjure/Rules/Horizontal/Permutation.hs +++ b/src/Conjure/Rules/Horizontal/Permutation.hs @@ -19,6 +19,25 @@ rule_Compose = "permutation-compose{rule_Compose}" `namedRule` theRule where theRule _ = na "rule_Compose" +rule_Permutation_Inverse :: Rule +rule_Permutation_Inverse = "permutation-inverse{AsFunction}" `namedRule` theRule where + theRule [essence| inverse(&p1, &p2)|] = do + case p1 of WithLocals{} -> na "bubble-delay" ; _ -> return () + case p2 of WithLocals{} -> na "bubble-delay" ; _ -> return () + TypePermutation{} <- typeOf p1 + TypePermutation{} <- typeOf p2 + return + ( "Vertical rule for permutation-inverse, AsFunction representation" + , do + (iPat, i) <- quantifiedVar + return [essence| + (forAll &iPat in &p1 . image(&p2,&i[2]) = &i[1]) + /\ + (forAll &iPat in &p2 . image(&p1,&i[2]) = &i[1]) + |] + ) + theRule _ = na "rule_Permutation_Equality" + rule_Permute_Literal :: Rule rule_Permute_Literal = "permutation-image-literal{AsFunction}" `namedRule` theRule where diff --git a/src/Conjure/Rules/Vertical/Permutation/AsFunction.hs b/src/Conjure/Rules/Vertical/Permutation/AsFunction.hs index de6d4b40cd..ad3d56da02 100644 --- a/src/Conjure/Rules/Vertical/Permutation/AsFunction.hs +++ b/src/Conjure/Rules/Vertical/Permutation/AsFunction.hs @@ -5,6 +5,48 @@ module Conjure.Rules.Vertical.Permutation.AsFunction where import Conjure.Rules.Import import Conjure.Rules.Vertical.Matrix (flattenIfNeeded) + +rule_Permutation_Inverse :: Rule +rule_Permutation_Inverse = "permutation-inverse{AsFunction}" `namedRule` theRule where + theRule [essence| inverse(&p1, &p2)|] = do + TypePermutation{} <- typeOf p1 + Permutation_AsFunction <- representationOf p1 + TypePermutation{} <- typeOf p2 + Permutation_AsFunction <- representationOf p2 + [f1] <- downX1 p2 + [f2] <- downX1 p2 + return + ( "Vertical rule for permutation-inverse, AsFunction representation" + , return [essence| inverse(&f1, &f2) |] + ) + theRule _ = na "rule_Permutation_Equality" + + +rule_Permutation_Inverse_Comprehension :: Rule +rule_Permutation_Inverse_Comprehension = "permutation-inverse-comprehension{AsFunction}" `namedRule` theRule where + theRule (Comprehension body gensOrConds) = do + (gocBefore, (pat, p1, p2), gocAfter) <- matchFirst gensOrConds $ \ goc -> case goc of + Generator (GenInExpr pat [essence| inverse(&p1, &p2)|] ) -> return (pat, p1, p2) + _ -> na "rule_Inverse_Comprehension" + TypePermutation{} <- typeOf p1 + Permutation_AsFunction <- representationOf p1 + TypePermutation{} <- typeOf p2 + Permutation_AsFunction <- representationOf p2 + [f1] <- downX1 p2 + [f2] <- downX1 p2 + return + ( "Vertical rule for permutation-inverse-comprehension, AsFunction representation" + , do + return $ Comprehension body + $ gocBefore + ++ [ Generator (GenInExpr pat [essence| inverse(&f1, &f2) |]) + ] + ++ gocAfter + ) + theRule _ = na "rule_Permutation_Inverse_Comprehension" + + + rule_Permutation_Equality :: Rule rule_Permutation_Equality = "permutation-equality{AsFunction}" `namedRule` theRule where theRule [essence| &p1 = &p2|] = do diff --git a/src/Conjure/UI/Model.hs b/src/Conjure/UI/Model.hs index 4de43b83bc..97b4cf999c 100644 --- a/src/Conjure/UI/Model.hs +++ b/src/Conjure/UI/Model.hs @@ -366,7 +366,7 @@ strategyToDriver config questions = do , let doc = vcat $ ("Question" <+> pretty n <> ":" <+> pretty (qHole q)) : [ nest 4 ("Context #" <> pretty i <> ":" <+> pretty c) - | (i,c) <- zip allNats (qAscendants q) + | (i,c) <- zip allNats (qAscendants q), i < 2 ] ] pickedQs <- executeStrategy optionsQ (strategyQ config) @@ -1314,7 +1314,7 @@ horizontalRules = , Horizontal.Partition.rule_Card , Horizontal.Partition.rule_In - + , Horizontal.Permutation.rule_Permutation_Inverse , Horizontal.Permutation.rule_Permute_Literal , Horizontal.Permutation.rule_Permute_Literal_Comprehension , Horizontal.Permutation.rule_Compose diff --git a/tests/custom/permutations/basic/.DS_Store b/tests/custom/permutations/basic/.DS_Store new file mode 100644 index 0000000000000000000000000000000000000000..0f7ba840a9442d2bf7141c57606c1abd9cdea677 GIT binary patch literal 6148 zcmeHKyH3MU3_XSpl~_75-cR5$u|-w+f_?xXT1usoqO?Jw@ zb7X`fUP|;*i4jA*obeKQRbc1n<&YRYB%UlWp@==5=NC(dRE}wrfn=c1z^S_v?f Date: Mon, 3 Dec 2018 13:20:51 +0000 Subject: [PATCH 037/229] Renamed vertical rule file --- conjure-cp.cabal | 2 +- .../AsFunction.hs => Permutation.hs} | 2 +- src/Conjure/UI/Model.hs | 26 +++++++++---------- 3 files changed, 15 insertions(+), 15 deletions(-) rename src/Conjure/Rules/Vertical/{Permutation/AsFunction.hs => Permutation.hs} (99%) diff --git a/conjure-cp.cabal b/conjure-cp.cabal index 56a41c3790..84a7eb5972 100644 --- a/conjure-cp.cabal +++ b/conjure-cp.cabal @@ -213,7 +213,7 @@ Library , Conjure.Rules.Vertical.Partition.Occurrence , Conjure.Rules.Horizontal.Permutation - , Conjure.Rules.Vertical.Permutation.AsFunction + , Conjure.Rules.Vertical.Permutation , Conjure.Rules.BubbleUp , Conjure.Rules.DontCare diff --git a/src/Conjure/Rules/Vertical/Permutation/AsFunction.hs b/src/Conjure/Rules/Vertical/Permutation.hs similarity index 99% rename from src/Conjure/Rules/Vertical/Permutation/AsFunction.hs rename to src/Conjure/Rules/Vertical/Permutation.hs index ad3d56da02..611f1c20ab 100644 --- a/src/Conjure/Rules/Vertical/Permutation/AsFunction.hs +++ b/src/Conjure/Rules/Vertical/Permutation.hs @@ -1,6 +1,6 @@ {-# LANGUAGE QuasiQuotes #-} -module Conjure.Rules.Vertical.Permutation.AsFunction where +module Conjure.Rules.Vertical.Permutation where import Conjure.Rules.Import import Conjure.Rules.Vertical.Matrix (flattenIfNeeded) diff --git a/src/Conjure/UI/Model.hs b/src/Conjure/UI/Model.hs index 97b4cf999c..a7464de9fd 100644 --- a/src/Conjure/UI/Model.hs +++ b/src/Conjure/UI/Model.hs @@ -86,7 +86,7 @@ import qualified Conjure.Rules.Horizontal.Partition as Horizontal.Partition import qualified Conjure.Rules.Vertical.Partition.PartitionAsSet as Vertical.Partition.PartitionAsSet import qualified Conjure.Rules.Vertical.Partition.Occurrence as Vertical.Partition.Occurrence -import qualified Conjure.Rules.Vertical.Permutation.AsFunction as Vertical.Permutation.AsFunction +import qualified Conjure.Rules.Vertical.Permutation as Vertical.Permutation import qualified Conjure.Rules.Horizontal.Permutation as Horizontal.Permutation import qualified Conjure.Rules.BubbleUp as BubbleUp @@ -1187,16 +1187,16 @@ verticalRules = , Vertical.Partition.PartitionAsSet.rule_Comprehension , Vertical.Partition.Occurrence.rule_Comprehension - , Vertical.Permutation.AsFunction.rule_Permutation_Equality - , Vertical.Permutation.AsFunction.rule_Permutation_Equality_Comprehension - , Vertical.Permutation.AsFunction.rule_Permute_Comprehension_Tuples - , Vertical.Permutation.AsFunction.rule_Relation_Permute - , Vertical.Permutation.AsFunction.rule_Relation_Permute_Comprehension - , Vertical.Permutation.AsFunction.rule_Set_Permute - , Vertical.Permutation.AsFunction.rule_Tuple_Permute - , Vertical.Permutation.AsFunction.rule_Tuple_Permute_Comprehension - , Vertical.Permutation.AsFunction.rule_Matrix_Permute - , Vertical.Permutation.AsFunction.rule_Matrix_Permute_Comprehension + , Vertical.Permutation.rule_Permutation_Equality + , Vertical.Permutation.rule_Permutation_Equality_Comprehension + , Vertical.Permutation.rule_Permute_Comprehension_Tuples + , Vertical.Permutation.rule_Relation_Permute + , Vertical.Permutation.rule_Relation_Permute_Comprehension + , Vertical.Permutation.rule_Set_Permute + , Vertical.Permutation.rule_Tuple_Permute + , Vertical.Permutation.rule_Tuple_Permute_Comprehension + , Vertical.Permutation.rule_Matrix_Permute + , Vertical.Permutation.rule_Matrix_Permute_Comprehension @@ -1394,8 +1394,8 @@ delayedRules = -- , Horizontal.Permutation.rule_Permute_Literal -- , Horizontal.Permutation.rule_Permute_Literal_Comprehension - , Vertical.Permutation.AsFunction.rule_Permute - , Vertical.Permutation.AsFunction.rule_Permute_Comprehension + , Vertical.Permutation.rule_Permute + , Vertical.Permutation.rule_Permute_Comprehension ] , [ rule_ReducerToComprehension ] From c33fc9a1353c2925a71aba88a74d1c55a4db250e Mon Sep 17 00:00:00 2001 From: Fraser Dunlop Date: Tue, 4 Dec 2018 11:47:30 +0000 Subject: [PATCH 038/229] Removed rules and started test driven reconstruction --- .../permutation.essence | 9 ++ .../permutation.param | 1 + .../0001_given_permutation_in_param/run.sh | 3 + .../stdout.expected | 7 ++ .../permutation.essence | 5 + .../permutation.param | 1 + .../0002_given_permutation_in_param/run.sh | 3 + .../stdout.expected | 7 ++ .../permutation.essence | 5 + .../permutation.param | 1 + .../run.sh | 3 + .../stderr.expected | 10 ++ .../stdout.expected | 4 + .../permutation.essence | 5 + .../permutation.param | 1 + .../run.sh | 3 + .../stdout.expected | 7 ++ .../permutation.essence | 5 + .../permutation.param | 1 + .../run.sh | 3 + .../stdout.expected | 40 +++++++ .../permutation.essence | 5 + .../permutation.param | 1 + .../run.sh | 3 + .../stdout.expected | 8 ++ .../permutation.essence | 3 + .../permutation.param | 1 + .../0007_letting_permutation_be_empty/run.sh | 3 + .../stdout.expected | 7 ++ .../permutation.essence | 5 + .../permutation.param | 1 + .../0008_find_permutation_of_int1_4/run.sh | 3 + .../stdout.expected | 100 ++++++++++++++++++ .../permutation.essence | 3 + .../0009_letting_permutation_in_model/run.sh | 3 + .../stdout.expected | 7 ++ .../permutation.essence | 5 + .../permutation.param | 1 + .../run.sh | 3 + .../stdout.expected | 20 ++++ .../permutation.essence | 5 + .../permutation.param | 1 + .../run.sh | 3 + .../stdout.expected | 24 +++++ .../permutation.essence | 5 + .../permutation.param | 1 + .../run.sh | 3 + .../stdout.expected | 60 +++++++++++ .../permutations/01_representation/README.md | 4 + .../01_representation/runthese.sh | 1 + .../permutation.essence | 11 ++ .../permutation.param | 1 + .../0001_given_permutation_in_param/run.sh | 3 + .../stdout.expected | 8 ++ .../permutation.essence | 9 ++ .../0002_letting_permutation_in_model/run.sh | 3 + .../stdout.expected | 8 ++ .../0003_find_permutation/permutation.essence | 9 ++ .../0003_find_permutation/run.sh | 3 + .../0003_find_permutation/stdout.expected | 9 ++ .../permutations/02_cardinality/runthese.sh | 2 + tests/custom/permutations/README.md | 14 +++ 62 files changed, 493 insertions(+) create mode 100644 tests/custom/permutations/01_representation/0001_given_permutation_in_param/permutation.essence create mode 100644 tests/custom/permutations/01_representation/0001_given_permutation_in_param/permutation.param create mode 100755 tests/custom/permutations/01_representation/0001_given_permutation_in_param/run.sh create mode 100644 tests/custom/permutations/01_representation/0001_given_permutation_in_param/stdout.expected create mode 100644 tests/custom/permutations/01_representation/0002_given_permutation_in_param/permutation.essence create mode 100644 tests/custom/permutations/01_representation/0002_given_permutation_in_param/permutation.param create mode 100755 tests/custom/permutations/01_representation/0002_given_permutation_in_param/run.sh create mode 100644 tests/custom/permutations/01_representation/0002_given_permutation_in_param/stdout.expected create mode 100644 tests/custom/permutations/01_representation/0003_given_permutation_in_param_2_cycle/permutation.essence create mode 100644 tests/custom/permutations/01_representation/0003_given_permutation_in_param_2_cycle/permutation.param create mode 100755 tests/custom/permutations/01_representation/0003_given_permutation_in_param_2_cycle/run.sh create mode 100644 tests/custom/permutations/01_representation/0003_given_permutation_in_param_2_cycle/stderr.expected create mode 100644 tests/custom/permutations/01_representation/0003_given_permutation_in_param_2_cycle/stdout.expected create mode 100644 tests/custom/permutations/01_representation/0004_given_permutation_in_param_2_cycle/permutation.essence create mode 100644 tests/custom/permutations/01_representation/0004_given_permutation_in_param_2_cycle/permutation.param create mode 100755 tests/custom/permutations/01_representation/0004_given_permutation_in_param_2_cycle/run.sh create mode 100644 tests/custom/permutations/01_representation/0004_given_permutation_in_param_2_cycle/stdout.expected create mode 100644 tests/custom/permutations/01_representation/0005_find_permutation_size_4_of_int1_4/permutation.essence create mode 100644 tests/custom/permutations/01_representation/0005_find_permutation_size_4_of_int1_4/permutation.param create mode 100755 tests/custom/permutations/01_representation/0005_find_permutation_size_4_of_int1_4/run.sh create mode 100644 tests/custom/permutations/01_representation/0005_find_permutation_size_4_of_int1_4/stdout.expected create mode 100644 tests/custom/permutations/01_representation/0006_find_permutation_size_0_of_int1_4/permutation.essence create mode 100644 tests/custom/permutations/01_representation/0006_find_permutation_size_0_of_int1_4/permutation.param create mode 100755 tests/custom/permutations/01_representation/0006_find_permutation_size_0_of_int1_4/run.sh create mode 100644 tests/custom/permutations/01_representation/0006_find_permutation_size_0_of_int1_4/stdout.expected create mode 100644 tests/custom/permutations/01_representation/0007_letting_permutation_be_empty/permutation.essence create mode 100644 tests/custom/permutations/01_representation/0007_letting_permutation_be_empty/permutation.param create mode 100755 tests/custom/permutations/01_representation/0007_letting_permutation_be_empty/run.sh create mode 100644 tests/custom/permutations/01_representation/0007_letting_permutation_be_empty/stdout.expected create mode 100644 tests/custom/permutations/01_representation/0008_find_permutation_of_int1_4/permutation.essence create mode 100644 tests/custom/permutations/01_representation/0008_find_permutation_of_int1_4/permutation.param create mode 100755 tests/custom/permutations/01_representation/0008_find_permutation_of_int1_4/run.sh create mode 100644 tests/custom/permutations/01_representation/0008_find_permutation_of_int1_4/stdout.expected create mode 100644 tests/custom/permutations/01_representation/0009_letting_permutation_in_model/permutation.essence create mode 100755 tests/custom/permutations/01_representation/0009_letting_permutation_in_model/run.sh create mode 100644 tests/custom/permutations/01_representation/0009_letting_permutation_in_model/stdout.expected create mode 100644 tests/custom/permutations/01_representation/0010_find_permutation_maxSize_2_of_int1_3/permutation.essence create mode 100644 tests/custom/permutations/01_representation/0010_find_permutation_maxSize_2_of_int1_3/permutation.param create mode 100755 tests/custom/permutations/01_representation/0010_find_permutation_maxSize_2_of_int1_3/run.sh create mode 100644 tests/custom/permutations/01_representation/0010_find_permutation_maxSize_2_of_int1_3/stdout.expected create mode 100644 tests/custom/permutations/01_representation/0011_find_permutation_minSize_2_of_int1_3/permutation.essence create mode 100644 tests/custom/permutations/01_representation/0011_find_permutation_minSize_2_of_int1_3/permutation.param create mode 100755 tests/custom/permutations/01_representation/0011_find_permutation_minSize_2_of_int1_3/run.sh create mode 100644 tests/custom/permutations/01_representation/0011_find_permutation_minSize_2_of_int1_3/stdout.expected create mode 100644 tests/custom/permutations/01_representation/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/permutation.essence create mode 100644 tests/custom/permutations/01_representation/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/permutation.param create mode 100755 tests/custom/permutations/01_representation/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/run.sh create mode 100644 tests/custom/permutations/01_representation/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/stdout.expected create mode 100644 tests/custom/permutations/01_representation/README.md create mode 100644 tests/custom/permutations/01_representation/runthese.sh create mode 100644 tests/custom/permutations/02_cardinality/0001_given_permutation_in_param/permutation.essence create mode 100644 tests/custom/permutations/02_cardinality/0001_given_permutation_in_param/permutation.param create mode 100755 tests/custom/permutations/02_cardinality/0001_given_permutation_in_param/run.sh create mode 100644 tests/custom/permutations/02_cardinality/0001_given_permutation_in_param/stdout.expected create mode 100644 tests/custom/permutations/02_cardinality/0002_letting_permutation_in_model/permutation.essence create mode 100755 tests/custom/permutations/02_cardinality/0002_letting_permutation_in_model/run.sh create mode 100644 tests/custom/permutations/02_cardinality/0002_letting_permutation_in_model/stdout.expected create mode 100644 tests/custom/permutations/02_cardinality/0003_find_permutation/permutation.essence create mode 100755 tests/custom/permutations/02_cardinality/0003_find_permutation/run.sh create mode 100644 tests/custom/permutations/02_cardinality/0003_find_permutation/stdout.expected create mode 100644 tests/custom/permutations/02_cardinality/runthese.sh create mode 100644 tests/custom/permutations/README.md diff --git a/tests/custom/permutations/01_representation/0001_given_permutation_in_param/permutation.essence b/tests/custom/permutations/01_representation/0001_given_permutation_in_param/permutation.essence new file mode 100644 index 0000000000..ec84d3ae7d --- /dev/null +++ b/tests/custom/permutations/01_representation/0001_given_permutation_in_param/permutation.essence @@ -0,0 +1,9 @@ +letting n be 4 + +given p : permutation of int(1..n) + +such that true + + + + diff --git a/tests/custom/permutations/01_representation/0001_given_permutation_in_param/permutation.param b/tests/custom/permutations/01_representation/0001_given_permutation_in_param/permutation.param new file mode 100644 index 0000000000..8a8c516801 --- /dev/null +++ b/tests/custom/permutations/01_representation/0001_given_permutation_in_param/permutation.param @@ -0,0 +1 @@ +letting p be permutation((1,3,4)) diff --git a/tests/custom/permutations/01_representation/0001_given_permutation_in_param/run.sh b/tests/custom/permutations/01_representation/0001_given_permutation_in_param/run.sh new file mode 100755 index 0000000000..9dc67e67f5 --- /dev/null +++ b/tests/custom/permutations/01_representation/0001_given_permutation_in_param/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence *.param +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/01_representation/0001_given_permutation_in_param/stdout.expected b/tests/custom/permutations/01_representation/0001_given_permutation_in_param/stdout.expected new file mode 100644 index 0000000000..1d9c5a0937 --- /dev/null +++ b/tests/custom/permutations/01_representation/0001_given_permutation_in_param/stdout.expected @@ -0,0 +1,7 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime permutation.param +Copying solution to: permutation-permutation.solution +language Essence 1.3 + diff --git a/tests/custom/permutations/01_representation/0002_given_permutation_in_param/permutation.essence b/tests/custom/permutations/01_representation/0002_given_permutation_in_param/permutation.essence new file mode 100644 index 0000000000..4d613e1dc6 --- /dev/null +++ b/tests/custom/permutations/01_representation/0002_given_permutation_in_param/permutation.essence @@ -0,0 +1,5 @@ +letting n be 3 + +given p : permutation of int(1..n) + +such that true diff --git a/tests/custom/permutations/01_representation/0002_given_permutation_in_param/permutation.param b/tests/custom/permutations/01_representation/0002_given_permutation_in_param/permutation.param new file mode 100644 index 0000000000..2099896d75 --- /dev/null +++ b/tests/custom/permutations/01_representation/0002_given_permutation_in_param/permutation.param @@ -0,0 +1 @@ +letting p be permutation((1,3,2)) diff --git a/tests/custom/permutations/01_representation/0002_given_permutation_in_param/run.sh b/tests/custom/permutations/01_representation/0002_given_permutation_in_param/run.sh new file mode 100755 index 0000000000..9dc67e67f5 --- /dev/null +++ b/tests/custom/permutations/01_representation/0002_given_permutation_in_param/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence *.param +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/01_representation/0002_given_permutation_in_param/stdout.expected b/tests/custom/permutations/01_representation/0002_given_permutation_in_param/stdout.expected new file mode 100644 index 0000000000..1d9c5a0937 --- /dev/null +++ b/tests/custom/permutations/01_representation/0002_given_permutation_in_param/stdout.expected @@ -0,0 +1,7 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime permutation.param +Copying solution to: permutation-permutation.solution +language Essence 1.3 + diff --git a/tests/custom/permutations/01_representation/0003_given_permutation_in_param_2_cycle/permutation.essence b/tests/custom/permutations/01_representation/0003_given_permutation_in_param_2_cycle/permutation.essence new file mode 100644 index 0000000000..4d613e1dc6 --- /dev/null +++ b/tests/custom/permutations/01_representation/0003_given_permutation_in_param_2_cycle/permutation.essence @@ -0,0 +1,5 @@ +letting n be 3 + +given p : permutation of int(1..n) + +such that true diff --git a/tests/custom/permutations/01_representation/0003_given_permutation_in_param_2_cycle/permutation.param b/tests/custom/permutations/01_representation/0003_given_permutation_in_param_2_cycle/permutation.param new file mode 100644 index 0000000000..a862179e25 --- /dev/null +++ b/tests/custom/permutations/01_representation/0003_given_permutation_in_param_2_cycle/permutation.param @@ -0,0 +1 @@ +letting p be permutation((1,3),(2,4)) diff --git a/tests/custom/permutations/01_representation/0003_given_permutation_in_param_2_cycle/run.sh b/tests/custom/permutations/01_representation/0003_given_permutation_in_param_2_cycle/run.sh new file mode 100755 index 0000000000..9dc67e67f5 --- /dev/null +++ b/tests/custom/permutations/01_representation/0003_given_permutation_in_param_2_cycle/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence *.param +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/01_representation/0003_given_permutation_in_param_2_cycle/stderr.expected b/tests/custom/permutations/01_representation/0003_given_permutation_in_param_2_cycle/stderr.expected new file mode 100644 index 0000000000..fa292aad7b --- /dev/null +++ b/tests/custom/permutations/01_representation/0003_given_permutation_in_param_2_cycle/stderr.expected @@ -0,0 +1,10 @@ +Error: + The value is not a member of the domain. + Value : permutation((1, 3), (2, 4)) + Domain: permutation {PermutationAsFunction} of int(1..3) + Reason: + The value is not a member of the domain. + Name : p + Value : 4 + Domain: int(1..3) +cat: conjure-output/*.solution: No such file or directory diff --git a/tests/custom/permutations/01_representation/0003_given_permutation_in_param_2_cycle/stdout.expected b/tests/custom/permutations/01_representation/0003_given_permutation_in_param_2_cycle/stdout.expected new file mode 100644 index 0000000000..a1634e8c4c --- /dev/null +++ b/tests/custom/permutations/01_representation/0003_given_permutation_in_param_2_cycle/stdout.expected @@ -0,0 +1,4 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime permutation.param diff --git a/tests/custom/permutations/01_representation/0004_given_permutation_in_param_2_cycle/permutation.essence b/tests/custom/permutations/01_representation/0004_given_permutation_in_param_2_cycle/permutation.essence new file mode 100644 index 0000000000..fff346c07e --- /dev/null +++ b/tests/custom/permutations/01_representation/0004_given_permutation_in_param_2_cycle/permutation.essence @@ -0,0 +1,5 @@ +letting n be 4 + +given p : permutation of int(1..n) + +such that true diff --git a/tests/custom/permutations/01_representation/0004_given_permutation_in_param_2_cycle/permutation.param b/tests/custom/permutations/01_representation/0004_given_permutation_in_param_2_cycle/permutation.param new file mode 100644 index 0000000000..a862179e25 --- /dev/null +++ b/tests/custom/permutations/01_representation/0004_given_permutation_in_param_2_cycle/permutation.param @@ -0,0 +1 @@ +letting p be permutation((1,3),(2,4)) diff --git a/tests/custom/permutations/01_representation/0004_given_permutation_in_param_2_cycle/run.sh b/tests/custom/permutations/01_representation/0004_given_permutation_in_param_2_cycle/run.sh new file mode 100755 index 0000000000..9dc67e67f5 --- /dev/null +++ b/tests/custom/permutations/01_representation/0004_given_permutation_in_param_2_cycle/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence *.param +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/01_representation/0004_given_permutation_in_param_2_cycle/stdout.expected b/tests/custom/permutations/01_representation/0004_given_permutation_in_param_2_cycle/stdout.expected new file mode 100644 index 0000000000..1d9c5a0937 --- /dev/null +++ b/tests/custom/permutations/01_representation/0004_given_permutation_in_param_2_cycle/stdout.expected @@ -0,0 +1,7 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime permutation.param +Copying solution to: permutation-permutation.solution +language Essence 1.3 + diff --git a/tests/custom/permutations/01_representation/0005_find_permutation_size_4_of_int1_4/permutation.essence b/tests/custom/permutations/01_representation/0005_find_permutation_size_4_of_int1_4/permutation.essence new file mode 100644 index 0000000000..63899fe581 --- /dev/null +++ b/tests/custom/permutations/01_representation/0005_find_permutation_size_4_of_int1_4/permutation.essence @@ -0,0 +1,5 @@ +letting n be 4 + +find p : permutation (size n) of int(1..n) + +such that true diff --git a/tests/custom/permutations/01_representation/0005_find_permutation_size_4_of_int1_4/permutation.param b/tests/custom/permutations/01_representation/0005_find_permutation_size_4_of_int1_4/permutation.param new file mode 100644 index 0000000000..a862179e25 --- /dev/null +++ b/tests/custom/permutations/01_representation/0005_find_permutation_size_4_of_int1_4/permutation.param @@ -0,0 +1 @@ +letting p be permutation((1,3),(2,4)) diff --git a/tests/custom/permutations/01_representation/0005_find_permutation_size_4_of_int1_4/run.sh b/tests/custom/permutations/01_representation/0005_find_permutation_size_4_of_int1_4/run.sh new file mode 100755 index 0000000000..7238b9c9c7 --- /dev/null +++ b/tests/custom/permutations/01_representation/0005_find_permutation_size_4_of_int1_4/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence --number-of-solutions=100 +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/01_representation/0005_find_permutation_size_4_of_int1_4/stdout.expected b/tests/custom/permutations/01_representation/0005_find_permutation_size_4_of_int1_4/stdout.expected new file mode 100644 index 0000000000..669733e43e --- /dev/null +++ b/tests/custom/permutations/01_representation/0005_find_permutation_size_4_of_int1_4/stdout.expected @@ -0,0 +1,40 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Copying solution to: permutation-000001.solution +Copying solution to: permutation-000002.solution +Copying solution to: permutation-000003.solution +Copying solution to: permutation-000004.solution +Copying solution to: permutation-000005.solution +Copying solution to: permutation-000006.solution +Copying solution to: permutation-000007.solution +Copying solution to: permutation-000008.solution +Copying solution to: permutation-000009.solution +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4)) +language Essence 1.3 + +letting p be permutation((1, 2, 3, 4)) +language Essence 1.3 + +letting p be permutation((1, 2, 4, 3)) +language Essence 1.3 + +letting p be permutation((1, 3, 4, 2)) +language Essence 1.3 + +letting p be permutation((1, 3), (2, 4)) +language Essence 1.3 + +letting p be permutation((1, 3, 2, 4)) +language Essence 1.3 + +letting p be permutation((1, 4, 3, 2)) +language Essence 1.3 + +letting p be permutation((1, 4, 2, 3)) +language Essence 1.3 + +letting p be permutation((1, 4), (2, 3)) diff --git a/tests/custom/permutations/01_representation/0006_find_permutation_size_0_of_int1_4/permutation.essence b/tests/custom/permutations/01_representation/0006_find_permutation_size_0_of_int1_4/permutation.essence new file mode 100644 index 0000000000..8c60c7b839 --- /dev/null +++ b/tests/custom/permutations/01_representation/0006_find_permutation_size_0_of_int1_4/permutation.essence @@ -0,0 +1,5 @@ +letting n be 4 + +find p : permutation (size 0) of int(1..n) + +such that true diff --git a/tests/custom/permutations/01_representation/0006_find_permutation_size_0_of_int1_4/permutation.param b/tests/custom/permutations/01_representation/0006_find_permutation_size_0_of_int1_4/permutation.param new file mode 100644 index 0000000000..a862179e25 --- /dev/null +++ b/tests/custom/permutations/01_representation/0006_find_permutation_size_0_of_int1_4/permutation.param @@ -0,0 +1 @@ +letting p be permutation((1,3),(2,4)) diff --git a/tests/custom/permutations/01_representation/0006_find_permutation_size_0_of_int1_4/run.sh b/tests/custom/permutations/01_representation/0006_find_permutation_size_0_of_int1_4/run.sh new file mode 100755 index 0000000000..7238b9c9c7 --- /dev/null +++ b/tests/custom/permutations/01_representation/0006_find_permutation_size_0_of_int1_4/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence --number-of-solutions=100 +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/01_representation/0006_find_permutation_size_0_of_int1_4/stdout.expected b/tests/custom/permutations/01_representation/0006_find_permutation_size_0_of_int1_4/stdout.expected new file mode 100644 index 0000000000..6003fd8115 --- /dev/null +++ b/tests/custom/permutations/01_representation/0006_find_permutation_size_0_of_int1_4/stdout.expected @@ -0,0 +1,8 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Copying solution to: permutation.solution +language Essence 1.3 + +letting p be permutation() diff --git a/tests/custom/permutations/01_representation/0007_letting_permutation_be_empty/permutation.essence b/tests/custom/permutations/01_representation/0007_letting_permutation_be_empty/permutation.essence new file mode 100644 index 0000000000..a39f3ae0b1 --- /dev/null +++ b/tests/custom/permutations/01_representation/0007_letting_permutation_be_empty/permutation.essence @@ -0,0 +1,3 @@ +letting p be permutation() + +such that true diff --git a/tests/custom/permutations/01_representation/0007_letting_permutation_be_empty/permutation.param b/tests/custom/permutations/01_representation/0007_letting_permutation_be_empty/permutation.param new file mode 100644 index 0000000000..a862179e25 --- /dev/null +++ b/tests/custom/permutations/01_representation/0007_letting_permutation_be_empty/permutation.param @@ -0,0 +1 @@ +letting p be permutation((1,3),(2,4)) diff --git a/tests/custom/permutations/01_representation/0007_letting_permutation_be_empty/run.sh b/tests/custom/permutations/01_representation/0007_letting_permutation_be_empty/run.sh new file mode 100755 index 0000000000..7238b9c9c7 --- /dev/null +++ b/tests/custom/permutations/01_representation/0007_letting_permutation_be_empty/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence --number-of-solutions=100 +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/01_representation/0007_letting_permutation_be_empty/stdout.expected b/tests/custom/permutations/01_representation/0007_letting_permutation_be_empty/stdout.expected new file mode 100644 index 0000000000..3a55885cbc --- /dev/null +++ b/tests/custom/permutations/01_representation/0007_letting_permutation_be_empty/stdout.expected @@ -0,0 +1,7 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Copying solution to: permutation.solution +language Essence 1.3 + diff --git a/tests/custom/permutations/01_representation/0008_find_permutation_of_int1_4/permutation.essence b/tests/custom/permutations/01_representation/0008_find_permutation_of_int1_4/permutation.essence new file mode 100644 index 0000000000..cf835570bd --- /dev/null +++ b/tests/custom/permutations/01_representation/0008_find_permutation_of_int1_4/permutation.essence @@ -0,0 +1,5 @@ +letting n be 4 + +find p : permutation of int(1..n) + +such that true diff --git a/tests/custom/permutations/01_representation/0008_find_permutation_of_int1_4/permutation.param b/tests/custom/permutations/01_representation/0008_find_permutation_of_int1_4/permutation.param new file mode 100644 index 0000000000..a862179e25 --- /dev/null +++ b/tests/custom/permutations/01_representation/0008_find_permutation_of_int1_4/permutation.param @@ -0,0 +1 @@ +letting p be permutation((1,3),(2,4)) diff --git a/tests/custom/permutations/01_representation/0008_find_permutation_of_int1_4/run.sh b/tests/custom/permutations/01_representation/0008_find_permutation_of_int1_4/run.sh new file mode 100755 index 0000000000..7238b9c9c7 --- /dev/null +++ b/tests/custom/permutations/01_representation/0008_find_permutation_of_int1_4/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence --number-of-solutions=100 +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/01_representation/0008_find_permutation_of_int1_4/stdout.expected b/tests/custom/permutations/01_representation/0008_find_permutation_of_int1_4/stdout.expected new file mode 100644 index 0000000000..326ee1f90d --- /dev/null +++ b/tests/custom/permutations/01_representation/0008_find_permutation_of_int1_4/stdout.expected @@ -0,0 +1,100 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Copying solution to: permutation-000001.solution +Copying solution to: permutation-000002.solution +Copying solution to: permutation-000003.solution +Copying solution to: permutation-000004.solution +Copying solution to: permutation-000005.solution +Copying solution to: permutation-000006.solution +Copying solution to: permutation-000007.solution +Copying solution to: permutation-000008.solution +Copying solution to: permutation-000009.solution +Copying solution to: permutation-000010.solution +Copying solution to: permutation-000011.solution +Copying solution to: permutation-000012.solution +Copying solution to: permutation-000013.solution +Copying solution to: permutation-000014.solution +Copying solution to: permutation-000015.solution +Copying solution to: permutation-000016.solution +Copying solution to: permutation-000017.solution +Copying solution to: permutation-000018.solution +Copying solution to: permutation-000019.solution +Copying solution to: permutation-000020.solution +Copying solution to: permutation-000021.solution +Copying solution to: permutation-000022.solution +Copying solution to: permutation-000023.solution +Copying solution to: permutation-000024.solution +language Essence 1.3 + +letting p be permutation() +language Essence 1.3 + +letting p be permutation((3, 4)) +language Essence 1.3 + +letting p be permutation((2, 3)) +language Essence 1.3 + +letting p be permutation((2, 3, 4)) +language Essence 1.3 + +letting p be permutation((2, 4, 3)) +language Essence 1.3 + +letting p be permutation((2, 4)) +language Essence 1.3 + +letting p be permutation((1, 2)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4)) +language Essence 1.3 + +letting p be permutation((1, 2, 3)) +language Essence 1.3 + +letting p be permutation((1, 2, 3, 4)) +language Essence 1.3 + +letting p be permutation((1, 2, 4, 3)) +language Essence 1.3 + +letting p be permutation((1, 2, 4)) +language Essence 1.3 + +letting p be permutation((1, 3, 2)) +language Essence 1.3 + +letting p be permutation((1, 3, 4, 2)) +language Essence 1.3 + +letting p be permutation((1, 3)) +language Essence 1.3 + +letting p be permutation((1, 3, 4)) +language Essence 1.3 + +letting p be permutation((1, 3), (2, 4)) +language Essence 1.3 + +letting p be permutation((1, 3, 2, 4)) +language Essence 1.3 + +letting p be permutation((1, 4, 3, 2)) +language Essence 1.3 + +letting p be permutation((1, 4, 2)) +language Essence 1.3 + +letting p be permutation((1, 4, 3)) +language Essence 1.3 + +letting p be permutation((1, 4)) +language Essence 1.3 + +letting p be permutation((1, 4, 2, 3)) +language Essence 1.3 + +letting p be permutation((1, 4), (2, 3)) diff --git a/tests/custom/permutations/01_representation/0009_letting_permutation_in_model/permutation.essence b/tests/custom/permutations/01_representation/0009_letting_permutation_in_model/permutation.essence new file mode 100644 index 0000000000..ab8ecc292d --- /dev/null +++ b/tests/custom/permutations/01_representation/0009_letting_permutation_in_model/permutation.essence @@ -0,0 +1,3 @@ +letting p be permutation((1,3),(2,4)) + +such that true diff --git a/tests/custom/permutations/01_representation/0009_letting_permutation_in_model/run.sh b/tests/custom/permutations/01_representation/0009_letting_permutation_in_model/run.sh new file mode 100755 index 0000000000..b4899d6266 --- /dev/null +++ b/tests/custom/permutations/01_representation/0009_letting_permutation_in_model/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/01_representation/0009_letting_permutation_in_model/stdout.expected b/tests/custom/permutations/01_representation/0009_letting_permutation_in_model/stdout.expected new file mode 100644 index 0000000000..3a55885cbc --- /dev/null +++ b/tests/custom/permutations/01_representation/0009_letting_permutation_in_model/stdout.expected @@ -0,0 +1,7 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Copying solution to: permutation.solution +language Essence 1.3 + diff --git a/tests/custom/permutations/01_representation/0010_find_permutation_maxSize_2_of_int1_3/permutation.essence b/tests/custom/permutations/01_representation/0010_find_permutation_maxSize_2_of_int1_3/permutation.essence new file mode 100644 index 0000000000..c5f650a6ea --- /dev/null +++ b/tests/custom/permutations/01_representation/0010_find_permutation_maxSize_2_of_int1_3/permutation.essence @@ -0,0 +1,5 @@ +letting n be 3 + +find p : permutation (maxSize 2) of int(1..n) + +such that true diff --git a/tests/custom/permutations/01_representation/0010_find_permutation_maxSize_2_of_int1_3/permutation.param b/tests/custom/permutations/01_representation/0010_find_permutation_maxSize_2_of_int1_3/permutation.param new file mode 100644 index 0000000000..a862179e25 --- /dev/null +++ b/tests/custom/permutations/01_representation/0010_find_permutation_maxSize_2_of_int1_3/permutation.param @@ -0,0 +1 @@ +letting p be permutation((1,3),(2,4)) diff --git a/tests/custom/permutations/01_representation/0010_find_permutation_maxSize_2_of_int1_3/run.sh b/tests/custom/permutations/01_representation/0010_find_permutation_maxSize_2_of_int1_3/run.sh new file mode 100755 index 0000000000..7238b9c9c7 --- /dev/null +++ b/tests/custom/permutations/01_representation/0010_find_permutation_maxSize_2_of_int1_3/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence --number-of-solutions=100 +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/01_representation/0010_find_permutation_maxSize_2_of_int1_3/stdout.expected b/tests/custom/permutations/01_representation/0010_find_permutation_maxSize_2_of_int1_3/stdout.expected new file mode 100644 index 0000000000..bdf3689279 --- /dev/null +++ b/tests/custom/permutations/01_representation/0010_find_permutation_maxSize_2_of_int1_3/stdout.expected @@ -0,0 +1,20 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Copying solution to: permutation-000001.solution +Copying solution to: permutation-000002.solution +Copying solution to: permutation-000003.solution +Copying solution to: permutation-000004.solution +language Essence 1.3 + +letting p be permutation() +language Essence 1.3 + +letting p be permutation((2, 3)) +language Essence 1.3 + +letting p be permutation((1, 2)) +language Essence 1.3 + +letting p be permutation((1, 3)) diff --git a/tests/custom/permutations/01_representation/0011_find_permutation_minSize_2_of_int1_3/permutation.essence b/tests/custom/permutations/01_representation/0011_find_permutation_minSize_2_of_int1_3/permutation.essence new file mode 100644 index 0000000000..73007c1924 --- /dev/null +++ b/tests/custom/permutations/01_representation/0011_find_permutation_minSize_2_of_int1_3/permutation.essence @@ -0,0 +1,5 @@ +letting n be 3 + +find p : permutation (minSize 2) of int(1..n) + +such that true diff --git a/tests/custom/permutations/01_representation/0011_find_permutation_minSize_2_of_int1_3/permutation.param b/tests/custom/permutations/01_representation/0011_find_permutation_minSize_2_of_int1_3/permutation.param new file mode 100644 index 0000000000..a862179e25 --- /dev/null +++ b/tests/custom/permutations/01_representation/0011_find_permutation_minSize_2_of_int1_3/permutation.param @@ -0,0 +1 @@ +letting p be permutation((1,3),(2,4)) diff --git a/tests/custom/permutations/01_representation/0011_find_permutation_minSize_2_of_int1_3/run.sh b/tests/custom/permutations/01_representation/0011_find_permutation_minSize_2_of_int1_3/run.sh new file mode 100755 index 0000000000..7238b9c9c7 --- /dev/null +++ b/tests/custom/permutations/01_representation/0011_find_permutation_minSize_2_of_int1_3/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence --number-of-solutions=100 +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/01_representation/0011_find_permutation_minSize_2_of_int1_3/stdout.expected b/tests/custom/permutations/01_representation/0011_find_permutation_minSize_2_of_int1_3/stdout.expected new file mode 100644 index 0000000000..f99a816f8e --- /dev/null +++ b/tests/custom/permutations/01_representation/0011_find_permutation_minSize_2_of_int1_3/stdout.expected @@ -0,0 +1,24 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Copying solution to: permutation-000001.solution +Copying solution to: permutation-000002.solution +Copying solution to: permutation-000003.solution +Copying solution to: permutation-000004.solution +Copying solution to: permutation-000005.solution +language Essence 1.3 + +letting p be permutation((2, 3)) +language Essence 1.3 + +letting p be permutation((1, 2)) +language Essence 1.3 + +letting p be permutation((1, 2, 3)) +language Essence 1.3 + +letting p be permutation((1, 3, 2)) +language Essence 1.3 + +letting p be permutation((1, 3)) diff --git a/tests/custom/permutations/01_representation/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/permutation.essence b/tests/custom/permutations/01_representation/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/permutation.essence new file mode 100644 index 0000000000..4460f93ee0 --- /dev/null +++ b/tests/custom/permutations/01_representation/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/permutation.essence @@ -0,0 +1,5 @@ +letting n be 4 + +find p : permutation (minSize 2, maxSize 3) of int(1..n) + +such that true diff --git a/tests/custom/permutations/01_representation/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/permutation.param b/tests/custom/permutations/01_representation/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/permutation.param new file mode 100644 index 0000000000..a862179e25 --- /dev/null +++ b/tests/custom/permutations/01_representation/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/permutation.param @@ -0,0 +1 @@ +letting p be permutation((1,3),(2,4)) diff --git a/tests/custom/permutations/01_representation/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/run.sh b/tests/custom/permutations/01_representation/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/run.sh new file mode 100755 index 0000000000..7238b9c9c7 --- /dev/null +++ b/tests/custom/permutations/01_representation/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence --number-of-solutions=100 +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/01_representation/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/stdout.expected b/tests/custom/permutations/01_representation/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/stdout.expected new file mode 100644 index 0000000000..31f8f8e8c2 --- /dev/null +++ b/tests/custom/permutations/01_representation/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/stdout.expected @@ -0,0 +1,60 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Copying solution to: permutation-000001.solution +Copying solution to: permutation-000002.solution +Copying solution to: permutation-000003.solution +Copying solution to: permutation-000004.solution +Copying solution to: permutation-000005.solution +Copying solution to: permutation-000006.solution +Copying solution to: permutation-000007.solution +Copying solution to: permutation-000008.solution +Copying solution to: permutation-000009.solution +Copying solution to: permutation-000010.solution +Copying solution to: permutation-000011.solution +Copying solution to: permutation-000012.solution +Copying solution to: permutation-000013.solution +Copying solution to: permutation-000014.solution +language Essence 1.3 + +letting p be permutation((3, 4)) +language Essence 1.3 + +letting p be permutation((2, 3)) +language Essence 1.3 + +letting p be permutation((2, 3, 4)) +language Essence 1.3 + +letting p be permutation((2, 4, 3)) +language Essence 1.3 + +letting p be permutation((2, 4)) +language Essence 1.3 + +letting p be permutation((1, 2)) +language Essence 1.3 + +letting p be permutation((1, 2, 3)) +language Essence 1.3 + +letting p be permutation((1, 2, 4)) +language Essence 1.3 + +letting p be permutation((1, 3, 2)) +language Essence 1.3 + +letting p be permutation((1, 3)) +language Essence 1.3 + +letting p be permutation((1, 3, 4)) +language Essence 1.3 + +letting p be permutation((1, 4, 2)) +language Essence 1.3 + +letting p be permutation((1, 4, 3)) +language Essence 1.3 + +letting p be permutation((1, 4)) diff --git a/tests/custom/permutations/01_representation/README.md b/tests/custom/permutations/01_representation/README.md new file mode 100644 index 0000000000..7edafd9c69 --- /dev/null +++ b/tests/custom/permutations/01_representation/README.md @@ -0,0 +1,4 @@ +# Minimal permutation test set +These tests should work without any vertical or horizontal permutation rules. + +They rely only on the permutation type and representation rules. diff --git a/tests/custom/permutations/01_representation/runthese.sh b/tests/custom/permutations/01_representation/runthese.sh new file mode 100644 index 0000000000..4682c19d59 --- /dev/null +++ b/tests/custom/permutations/01_representation/runthese.sh @@ -0,0 +1 @@ +stack test --test-arguments "-p custom.permutations.01_representation" diff --git a/tests/custom/permutations/02_cardinality/0001_given_permutation_in_param/permutation.essence b/tests/custom/permutations/02_cardinality/0001_given_permutation_in_param/permutation.essence new file mode 100644 index 0000000000..f69bae145b --- /dev/null +++ b/tests/custom/permutations/02_cardinality/0001_given_permutation_in_param/permutation.essence @@ -0,0 +1,11 @@ +letting n be 4 + +given p : permutation of int(1..n) + +find i : int(0..10) + +such that i = |p| + + + + diff --git a/tests/custom/permutations/02_cardinality/0001_given_permutation_in_param/permutation.param b/tests/custom/permutations/02_cardinality/0001_given_permutation_in_param/permutation.param new file mode 100644 index 0000000000..8a8c516801 --- /dev/null +++ b/tests/custom/permutations/02_cardinality/0001_given_permutation_in_param/permutation.param @@ -0,0 +1 @@ +letting p be permutation((1,3,4)) diff --git a/tests/custom/permutations/02_cardinality/0001_given_permutation_in_param/run.sh b/tests/custom/permutations/02_cardinality/0001_given_permutation_in_param/run.sh new file mode 100755 index 0000000000..9dc67e67f5 --- /dev/null +++ b/tests/custom/permutations/02_cardinality/0001_given_permutation_in_param/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence *.param +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/02_cardinality/0001_given_permutation_in_param/stdout.expected b/tests/custom/permutations/02_cardinality/0001_given_permutation_in_param/stdout.expected new file mode 100644 index 0000000000..d20985577b --- /dev/null +++ b/tests/custom/permutations/02_cardinality/0001_given_permutation_in_param/stdout.expected @@ -0,0 +1,8 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime permutation.param +Copying solution to: permutation-permutation.solution +language Essence 1.3 + +letting i be 3 diff --git a/tests/custom/permutations/02_cardinality/0002_letting_permutation_in_model/permutation.essence b/tests/custom/permutations/02_cardinality/0002_letting_permutation_in_model/permutation.essence new file mode 100644 index 0000000000..4f1c879426 --- /dev/null +++ b/tests/custom/permutations/02_cardinality/0002_letting_permutation_in_model/permutation.essence @@ -0,0 +1,9 @@ +letting p be permutation((1,3,4)) + +find i : int(0..10) + +such that i = |p| + + + + diff --git a/tests/custom/permutations/02_cardinality/0002_letting_permutation_in_model/run.sh b/tests/custom/permutations/02_cardinality/0002_letting_permutation_in_model/run.sh new file mode 100755 index 0000000000..b4899d6266 --- /dev/null +++ b/tests/custom/permutations/02_cardinality/0002_letting_permutation_in_model/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/02_cardinality/0002_letting_permutation_in_model/stdout.expected b/tests/custom/permutations/02_cardinality/0002_letting_permutation_in_model/stdout.expected new file mode 100644 index 0000000000..d07c5feeb5 --- /dev/null +++ b/tests/custom/permutations/02_cardinality/0002_letting_permutation_in_model/stdout.expected @@ -0,0 +1,8 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Copying solution to: permutation.solution +language Essence 1.3 + +letting i be 3 diff --git a/tests/custom/permutations/02_cardinality/0003_find_permutation/permutation.essence b/tests/custom/permutations/02_cardinality/0003_find_permutation/permutation.essence new file mode 100644 index 0000000000..59127b82f2 --- /dev/null +++ b/tests/custom/permutations/02_cardinality/0003_find_permutation/permutation.essence @@ -0,0 +1,9 @@ +find p : permutation (size 4) of int(1..6) + +find i : int(0..10) + +such that i = |p| + + + + diff --git a/tests/custom/permutations/02_cardinality/0003_find_permutation/run.sh b/tests/custom/permutations/02_cardinality/0003_find_permutation/run.sh new file mode 100755 index 0000000000..b4899d6266 --- /dev/null +++ b/tests/custom/permutations/02_cardinality/0003_find_permutation/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/02_cardinality/0003_find_permutation/stdout.expected b/tests/custom/permutations/02_cardinality/0003_find_permutation/stdout.expected new file mode 100644 index 0000000000..8030f81a88 --- /dev/null +++ b/tests/custom/permutations/02_cardinality/0003_find_permutation/stdout.expected @@ -0,0 +1,9 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Copying solution to: permutation.solution +language Essence 1.3 + +letting i be 4 +letting p be permutation((3, 4), (5, 6)) diff --git a/tests/custom/permutations/02_cardinality/runthese.sh b/tests/custom/permutations/02_cardinality/runthese.sh new file mode 100644 index 0000000000..c39242ca37 --- /dev/null +++ b/tests/custom/permutations/02_cardinality/runthese.sh @@ -0,0 +1,2 @@ +stack install +stack test --test-arguments "-p custom.permutations.02_cardinality" diff --git a/tests/custom/permutations/README.md b/tests/custom/permutations/README.md new file mode 100644 index 0000000000..b2476e7e1b --- /dev/null +++ b/tests/custom/permutations/README.md @@ -0,0 +1,14 @@ +# Permutations spec +Organized by level - each level adding functionality +## 01 representation +Tests permutation behaviour that should work with no rewrite rules. +- permutations must parse correctly in model and parameter files +- the size attribute must constrain the size of the permutation +- enumeration tests for finding permutations +## 02 cardinality +Test that we can get the number of permuted elements by |p| +- basic cardinality for find, letting, given +## 03 equality +Tests equality on permutations +- basic equality for find, letting, given +- tests [|p| = i | p <- sp] where sp is a set of permutations From 28d8437308e138dfe67f2cf5d3150ee1c7243798 Mon Sep 17 00:00:00 2001 From: Fraser Dunlop Date: Tue, 4 Dec 2018 12:20:17 +0000 Subject: [PATCH 039/229] Renamed permutation representation file --- conjure-cp.cabal | 2 +- src/Conjure/Compute/DomainOf.hs | 2 + src/Conjure/Language/AbstractLiteral.hs | 1 + src/Conjure/Language/Expression/Op/TwoBars.hs | 27 +- src/Conjure/Representations/Combined.hs | 2 +- .../AsFunction.hs => Permutation.hs} | 2 +- src/Conjure/Rules/Horizontal/Permutation.hs | 297 +++---- src/Conjure/Rules/Vertical/Permutation.hs | 791 +++++++++--------- src/Conjure/UI/Model.hs | 36 +- 9 files changed, 599 insertions(+), 561 deletions(-) rename src/Conjure/Representations/{Permutation/AsFunction.hs => Permutation.hs} (98%) diff --git a/conjure-cp.cabal b/conjure-cp.cabal index 84a7eb5972..a368030f82 100644 --- a/conjure-cp.cabal +++ b/conjure-cp.cabal @@ -172,7 +172,7 @@ Library , Conjure.Representations.Relation.RelationAsSet , Conjure.Representations.Partition.Occurrence , Conjure.Representations.Partition.PartitionAsSet - , Conjure.Representations.Permutation.AsFunction + , Conjure.Representations.Permutation -- definitions of rules , Conjure.Rules.Definition diff --git a/src/Conjure/Compute/DomainOf.hs b/src/Conjure/Compute/DomainOf.hs index fe9fe21226..a28062bb4e 100644 --- a/src/Conjure/Compute/DomainOf.hs +++ b/src/Conjure/Compute/DomainOf.hs @@ -293,6 +293,8 @@ instance DomainOf (AbstractLiteral Expression) where where attr = PartitionAttr (SizeAttr_MaxSize (fromInt $ genericLength xss)) (SizeAttr_MaxSize (fromInt $ maximum [genericLength xs | xs <- xss])) False + domainOf (AbsLitPermutation [] ) = return $ DomainPermutation def attr (DomainAny "domainOf-AbsLitPermutation-[]" TypeAny) + where attr = PermutationAttr (SizeAttr_Size 0) domainOf (AbsLitPermutation xss) = DomainPermutation def def <$> (domainUnions =<< mapM domainOf (concat xss)) indexDomainsOf (AbsLitMatrix ind inn) = (ind :) <$> (mapM domainUnions =<< mapM indexDomainsOf inn) indexDomainsOf _ = return [] diff --git a/src/Conjure/Language/AbstractLiteral.hs b/src/Conjure/Language/AbstractLiteral.hs index 019375c842..26c071f3fe 100644 --- a/src/Conjure/Language/AbstractLiteral.hs +++ b/src/Conjure/Language/AbstractLiteral.hs @@ -144,6 +144,7 @@ instance (TypeOf a, Pretty a) => TypeOf (AbstractLiteral a) where typeOf (AbsLitPartition [] ) = return (TypePartition TypeAny) typeOf p@(AbsLitPartition xss) = TypePartition <$> (homoType (pretty p) =<< mapM typeOf (concat xss)) + typeOf (AbsLitPermutation [] ) = return (TypePermutation TypeAny) typeOf p@(AbsLitPermutation xss) = TypePermutation <$> (homoType (pretty p) =<< mapM typeOf (concat xss)) diff --git a/src/Conjure/Language/Expression/Op/TwoBars.hs b/src/Conjure/Language/Expression/Op/TwoBars.hs index eeaf59b649..7a25228d11 100644 --- a/src/Conjure/Language/Expression/Op/TwoBars.hs +++ b/src/Conjure/Language/Expression/Op/TwoBars.hs @@ -24,19 +24,20 @@ instance (TypeOf x, Pretty x) => TypeOf (OpTwoBars x) where typeOf p@(OpTwoBars a) = do ty <- typeOf a case ty of - TypeInt NoTag -> return () - TypeInt AnyTag -> return () - TypeList{} -> return () - TypeSet{} -> return () - TypeMSet{} -> return () - TypeFunction{} -> return () - TypeSequence{} -> return () - TypeRelation{} -> return () - TypePartition{} -> return () - _ -> raiseTypeError $ vcat [ pretty p - , "Expected an integer or a collection." - , "But got:" <+> pretty ty - ] + TypeInt NoTag -> return () + TypeInt AnyTag -> return () + TypeList{} -> return () + TypeSet{} -> return () + TypeMSet{} -> return () + TypeFunction{} -> return () + TypeSequence{} -> return () + TypeRelation{} -> return () + TypePartition{} -> return () + TypePermutation{} -> return () + _ -> raiseTypeError $ vcat [ pretty p + , "Expected an integer or a collection." + , "But got:" <+> pretty ty + ] return $ TypeInt NoTag instance EvaluateOp OpTwoBars where diff --git a/src/Conjure/Representations/Combined.hs b/src/Conjure/Representations/Combined.hs index 2fb8373520..49223a792d 100644 --- a/src/Conjure/Representations/Combined.hs +++ b/src/Conjure/Representations/Combined.hs @@ -36,7 +36,7 @@ import Conjure.Representations.Relation.RelationAsMatrix import Conjure.Representations.Relation.RelationAsSet import Conjure.Representations.Partition.Occurrence import Conjure.Representations.Partition.PartitionAsSet -import Conjure.Representations.Permutation.AsFunction +import Conjure.Representations.Permutation -- | Refine (down) a domain, outputting refinement expressions (X) one level (1). diff --git a/src/Conjure/Representations/Permutation/AsFunction.hs b/src/Conjure/Representations/Permutation.hs similarity index 98% rename from src/Conjure/Representations/Permutation/AsFunction.hs rename to src/Conjure/Representations/Permutation.hs index c1967880a4..9b741092ad 100644 --- a/src/Conjure/Representations/Permutation/AsFunction.hs +++ b/src/Conjure/Representations/Permutation.hs @@ -3,7 +3,7 @@ {-# LANGUAGE ViewPatterns #-} {-# LANGUAGE Rank2Types #-} -module Conjure.Representations.Permutation.AsFunction ( permutationAsFunction ) where +module Conjure.Representations.Permutation ( permutationAsFunction ) where -- conjure import Conjure.Prelude diff --git a/src/Conjure/Rules/Horizontal/Permutation.hs b/src/Conjure/Rules/Horizontal/Permutation.hs index 6c5eafdca2..f48db66521 100644 --- a/src/Conjure/Rules/Horizontal/Permutation.hs +++ b/src/Conjure/Rules/Horizontal/Permutation.hs @@ -2,147 +2,164 @@ module Conjure.Rules.Horizontal.Permutation where import Conjure.Rules.Import import Data.List (cycle) +import Data.Permutation (size, fromCycles) -rule_Compose :: Rule -rule_Compose = "permutation-compose{rule_Compose}" `namedRule` theRule where - theRule [essence| image(compose(&g, &h),&i) |] = do - TypePermutation innerG <- typeOf g - TypePermutation innerH <- typeOf g - typeI <- typeOf i - if typesUnify [innerG, innerH, typeI] - then return - ( "Horizontal rule for permutation composition/application" - , do - return [essence| image(&g, image(&h,&i)) |] - ) - else na "rule_Compose" - theRule _ = na "rule_Compose" - -rule_Permutation_Inverse :: Rule -rule_Permutation_Inverse = "permutation-inverse{AsFunction}" `namedRule` theRule where - theRule [essence| inverse(&p1, &p2)|] = do - case p1 of WithLocals{} -> na "bubble-delay" ; _ -> return () - case p2 of WithLocals{} -> na "bubble-delay" ; _ -> return () - TypePermutation{} <- typeOf p1 - TypePermutation{} <- typeOf p2 - return - ( "Vertical rule for permutation-inverse, AsFunction representation" - , do - (iPat, i) <- quantifiedVar - return [essence| - (forAll &iPat in &p1 . image(&p2,&i[2]) = &i[1]) - /\ - (forAll &iPat in &p2 . image(&p1,&i[2]) = &i[1]) - |] - ) - theRule _ = na "rule_Permutation_Equality" - - -rule_Permute_Literal :: Rule -rule_Permute_Literal = "permutation-image-literal{AsFunction}" `namedRule` theRule where - theRule [essence| image(&p, &i) |] = do +rule_Cardinality_Literal :: Rule +rule_Cardinality_Literal = "permutation-cardinality-literal" `namedRule` theRule where + theRule p' = do + p <- match opTwoBars p' (TypePermutation inner, elems) <- match permutationLiteral p - case i of WithLocals{} -> na "bubble-delay" ; _ -> return () - typeI <- typeOf i --- traceM $ show typeI - if typeI `containsType` inner - then do - if typesUnify [inner, typeI] - then do - innerD <- domainOf i - let prmTup pt = take (length pt) $ zip (cycle pt) (drop 1 $ cycle pt) - permTups = join $ prmTup <$> elems - let outLiteral = make matrixLiteral - (TypeMatrix (TypeInt NoTag) (TypeTuple [inner,inner])) - (DomainInt NoTag [RangeBounded 1 (fromInt (genericLength permTups))]) - [ AbstractLiteral (AbsLitTuple [a,b]) - | (a,b) <- permTups - ] - return - ( "Horizontal rule for permutation literal application to a single value (image), AsFunction representation" - , do - (hName, h) <- auxiliaryVar - (fPat, f) <- quantifiedVar - (tPat, t) <- quantifiedVar - (gPat, g) <- quantifiedVar - (ePat, _) <- quantifiedVar - return $ WithLocals - [essence| &h |] - (AuxiliaryVars - [ Declaration (FindOrGiven LocalFind hName innerD) - , SuchThat - [ [essence| - (forAll (&fPat, &tPat) in &outLiteral . &f = &i <-> &h = &t) - /\ (!(exists (&gPat, &ePat) in &outLiteral . &g = &h) <-> &h = &i) - |] - ] - ] - ) - ) - else na "rule_Permute_Literal" - else return - ( "Horizontal rule for permutation application to a type the permutation doesn't care about" - , do - return [essence| &i |] - ) - theRule _ = na "rule_Permute_Literal" - - -rule_Permute_Literal_Comprehension :: Rule -rule_Permute_Literal_Comprehension = "permutation-image-literal-comprehension{AsFunction}" `namedRule` theRule where - theRule (Comprehension body gensOrConds) = do - (gocBefore, (pat, p, i), gocAfter) <- matchFirst gensOrConds $ \ goc -> case goc of - Generator (GenInExpr pat [essence| image(&p, &i) |]) -> return (pat, p, i) - _ -> na "rule_Comprehension" - case i of WithLocals{} -> na "bubble-delay" ; _ -> return () - (TypePermutation inner, elems) <- match permutationLiteral p - typeI <- typeOf i - if typeI `containsType` inner - then do - if typesUnify [inner, typeI] - then do - innerD <- domainOf i - let prmTup pt = take (length pt) $ zip (cycle pt) (drop 1 $ cycle pt) - permTups = join $ prmTup <$> elems - let outLiteral = make matrixLiteral - (TypeMatrix (TypeInt NoTag) (TypeTuple [inner,inner])) - (DomainInt NoTag [RangeBounded 1 (fromInt (genericLength permTups))]) - [ AbstractLiteral (AbsLitTuple [a,b]) - | (a,b) <- permTups - ] - return - ( "Horizontal rule for permutation literal application to a single value (image), AsFunction representation" - , do - (hName, h) <- auxiliaryVar - (fPat, f) <- quantifiedVar - (tPat, t) <- quantifiedVar - (gPat, g) <- quantifiedVar - (ePat, _) <- quantifiedVar - return $ WithLocals - (Comprehension body $ gocBefore - ++ [Generator (GenInExpr pat - [essence| &h |])] - ++ gocAfter) - (AuxiliaryVars - [ Declaration (FindOrGiven LocalFind hName innerD) - , SuchThat - [ [essence| - (forAll (&fPat, &tPat) in &outLiteral . &f = &i <-> &h = &t) - /\ (!(exists (&gPat, &ePat) in &outLiteral . &g = &h) <-> &h = &i) - |] - ] - ] - ) - ) - else na "rule_Permute_Literal" - else return - ( "Horizontal rule for permutation application to a type the permutation doesn't care about" - , return - (Comprehension body $ gocBefore - ++ [Generator (GenInExpr pat [essence| &i |])] - ++ gocAfter) - ) - theRule _ = na "rule_Permute_Literal" - + let i' = Constant . ConstantInt AnyTag . fromIntegral . size <$> fromCycles elems + case i' of + Left er -> fail $ "Permutation literal invalid." <++> stringToDoc (show er) + Right i -> return + ( "Vertical rule for permutation cardinality, AsFunction representation." + , do + return [essence| &i |] + ) +-- +-- +--rule_Compose :: Rule +--rule_Compose = "permutation-compose{rule_Compose}" `namedRule` theRule where +-- theRule [essence| image(compose(&g, &h),&i) |] = do +-- TypePermutation innerG <- typeOf g +-- TypePermutation innerH <- typeOf g +-- typeI <- typeOf i +-- if typesUnify [innerG, innerH, typeI] +-- then return +-- ( "Horizontal rule for permutation composition/application" +-- , do +-- return [essence| image(&g, image(&h,&i)) |] +-- ) +-- else na "rule_Compose" +-- theRule _ = na "rule_Compose" +-- +-- +--rule_Permutation_Inverse :: Rule +--rule_Permutation_Inverse = "permutation-inverse{AsFunction}" `namedRule` theRule where +-- theRule [essence| inverse(&p1, &p2)|] = do +-- case p1 of WithLocals{} -> na "bubble-delay" ; _ -> return () +-- case p2 of WithLocals{} -> na "bubble-delay" ; _ -> return () +-- TypePermutation{} <- typeOf p1 +-- TypePermutation{} <- typeOf p2 +-- return +-- ( "Vertical rule for permutation-inverse, AsFunction representation" +-- , do +-- (iPat, i) <- quantifiedVar +-- return [essence| +-- (forAll &iPat in &p1 . image(&p2,&i[2]) = &i[1]) +-- /\ +-- (forAll &iPat in &p2 . image(&p1,&i[2]) = &i[1]) +-- |] +-- ) +-- theRule _ = na "rule_Permutation_Equality" +-- +--rule_Permute_Literal :: Rule +--rule_Permute_Literal = "permutation-image-literal{AsFunction}" `namedRule` theRule where +-- theRule [essence| image(&p, &i) |] = do +-- (TypePermutation inner, elems) <- match permutationLiteral p +-- case i of WithLocals{} -> na "bubble-delay" ; _ -> return () +-- typeI <- typeOf i +---- traceM $ show typeI +-- if typeI `containsType` inner +-- then do +-- if typesUnify [inner, typeI] +-- then do +-- innerD <- domainOf i +-- let prmTup pt = take (length pt) $ zip (cycle pt) (drop 1 $ cycle pt) +-- permTups = join $ prmTup <$> elems +-- let outLiteral = make matrixLiteral +-- (TypeMatrix (TypeInt NoTag) (TypeTuple [inner,inner])) +-- (DomainInt NoTag [RangeBounded 1 (fromInt (genericLength permTups))]) +-- [ AbstractLiteral (AbsLitTuple [a,b]) +-- | (a,b) <- permTups +-- ] +-- return +-- ( "Horizontal rule for permutation literal application to a single value (image), AsFunction representation" +-- , do +-- (hName, h) <- auxiliaryVar +-- (fPat, f) <- quantifiedVar +-- (tPat, t) <- quantifiedVar +-- (gPat, g) <- quantifiedVar +-- (ePat, _) <- quantifiedVar +-- return $ WithLocals +-- [essence| &h |] +-- (AuxiliaryVars +-- [ Declaration (FindOrGiven LocalFind hName innerD) +-- , SuchThat +-- [ [essence| +-- (forAll (&fPat, &tPat) in &outLiteral . &f = &i <-> &h = &t) +-- /\ (!(exists (&gPat, &ePat) in &outLiteral . &g = &h) <-> &h = &i) +-- |] +-- ] +-- ] +-- ) +-- ) +-- else na "rule_Permute_Literal" +-- else return +-- ( "Horizontal rule for permutation application to a type the permutation doesn't care about" +-- , do +-- return [essence| &i |] +-- ) +-- theRule _ = na "rule_Permute_Literal" +-- +-- +--rule_Permute_Literal_Comprehension :: Rule +--rule_Permute_Literal_Comprehension = "permutation-image-literal-comprehension{AsFunction}" `namedRule` theRule where +-- theRule (Comprehension body gensOrConds) = do +-- (gocBefore, (pat, p, i), gocAfter) <- matchFirst gensOrConds $ \ goc -> case goc of +-- Generator (GenInExpr pat [essence| image(&p, &i) |]) -> return (pat, p, i) +-- _ -> na "rule_Comprehension" +-- case i of WithLocals{} -> na "bubble-delay" ; _ -> return () +-- (TypePermutation inner, elems) <- match permutationLiteral p +-- typeI <- typeOf i +-- if typeI `containsType` inner +-- then do +-- if typesUnify [inner, typeI] +-- then do +-- innerD <- domainOf i +-- let prmTup pt = take (length pt) $ zip (cycle pt) (drop 1 $ cycle pt) +-- permTups = join $ prmTup <$> elems +-- let outLiteral = make matrixLiteral +-- (TypeMatrix (TypeInt NoTag) (TypeTuple [inner,inner])) +-- (DomainInt NoTag [RangeBounded 1 (fromInt (genericLength permTups))]) +-- [ AbstractLiteral (AbsLitTuple [a,b]) +-- | (a,b) <- permTups +-- ] +-- return +-- ( "Horizontal rule for permutation literal application to a single value (image), AsFunction representation" +-- , do +-- (hName, h) <- auxiliaryVar +-- (fPat, f) <- quantifiedVar +-- (tPat, t) <- quantifiedVar +-- (gPat, g) <- quantifiedVar +-- (ePat, _) <- quantifiedVar +-- return $ WithLocals +-- (Comprehension body $ gocBefore +-- ++ [Generator (GenInExpr pat +-- [essence| &h |])] +-- ++ gocAfter) +-- (AuxiliaryVars +-- [ Declaration (FindOrGiven LocalFind hName innerD) +-- , SuchThat +-- [ [essence| +-- (forAll (&fPat, &tPat) in &outLiteral . &f = &i <-> &h = &t) +-- /\ (!(exists (&gPat, &ePat) in &outLiteral . &g = &h) <-> &h = &i) +-- |] +-- ] +-- ] +-- ) +-- ) +-- else na "rule_Permute_Literal" +-- else return +-- ( "Horizontal rule for permutation application to a type the permutation doesn't care about" +-- , return +-- (Comprehension body $ gocBefore +-- ++ [Generator (GenInExpr pat [essence| &i |])] +-- ++ gocAfter) +-- ) +-- theRule _ = na "rule_Permute_Literal" +-- +-- diff --git a/src/Conjure/Rules/Vertical/Permutation.hs b/src/Conjure/Rules/Vertical/Permutation.hs index 611f1c20ab..7929ccb2f8 100644 --- a/src/Conjure/Rules/Vertical/Permutation.hs +++ b/src/Conjure/Rules/Vertical/Permutation.hs @@ -5,396 +5,413 @@ module Conjure.Rules.Vertical.Permutation where import Conjure.Rules.Import import Conjure.Rules.Vertical.Matrix (flattenIfNeeded) - -rule_Permutation_Inverse :: Rule -rule_Permutation_Inverse = "permutation-inverse{AsFunction}" `namedRule` theRule where - theRule [essence| inverse(&p1, &p2)|] = do - TypePermutation{} <- typeOf p1 - Permutation_AsFunction <- representationOf p1 - TypePermutation{} <- typeOf p2 - Permutation_AsFunction <- representationOf p2 - [f1] <- downX1 p2 - [f2] <- downX1 p2 - return - ( "Vertical rule for permutation-inverse, AsFunction representation" - , return [essence| inverse(&f1, &f2) |] - ) - theRule _ = na "rule_Permutation_Equality" - - -rule_Permutation_Inverse_Comprehension :: Rule -rule_Permutation_Inverse_Comprehension = "permutation-inverse-comprehension{AsFunction}" `namedRule` theRule where - theRule (Comprehension body gensOrConds) = do - (gocBefore, (pat, p1, p2), gocAfter) <- matchFirst gensOrConds $ \ goc -> case goc of - Generator (GenInExpr pat [essence| inverse(&p1, &p2)|] ) -> return (pat, p1, p2) - _ -> na "rule_Inverse_Comprehension" - TypePermutation{} <- typeOf p1 - Permutation_AsFunction <- representationOf p1 - TypePermutation{} <- typeOf p2 - Permutation_AsFunction <- representationOf p2 - [f1] <- downX1 p2 - [f2] <- downX1 p2 - return - ( "Vertical rule for permutation-inverse-comprehension, AsFunction representation" - , do - return $ Comprehension body - $ gocBefore - ++ [ Generator (GenInExpr pat [essence| inverse(&f1, &f2) |]) - ] - ++ gocAfter - ) - theRule _ = na "rule_Permutation_Inverse_Comprehension" - - - -rule_Permutation_Equality :: Rule -rule_Permutation_Equality = "permutation-equality{AsFunction}" `namedRule` theRule where - theRule [essence| &p1 = &p2|] = do - TypePermutation{} <- typeOf p1 - Permutation_AsFunction <- representationOf p1 - TypePermutation{} <- typeOf p2 - Permutation_AsFunction <- representationOf p2 - [f1] <- downX1 p2 - [f2] <- downX1 p2 - return - ( "Vertical rule for permutation-equality, AsFunction representation" - , return [essence| &f1 = &f2 |] - ) - theRule _ = na "rule_Permutation_Equality" - - -rule_Permutation_Equality_Comprehension :: Rule -rule_Permutation_Equality_Comprehension = "permutation-equality-comprehension{AsFunction}" `namedRule` theRule where - theRule (Comprehension body gensOrConds) = do - (gocBefore, (pat, p1, p2), gocAfter) <- matchFirst gensOrConds $ \ goc -> case goc of - Generator (GenInExpr pat [essence| &p1 = &p2|] ) -> return (pat, p1, p2) - _ -> na "rule_Comprehension" - TypePermutation{} <- typeOf p1 - Permutation_AsFunction <- representationOf p1 - TypePermutation{} <- typeOf p2 - Permutation_AsFunction <- representationOf p2 - [f1] <- downX1 p2 - [f2] <- downX1 p2 - return - ( "Vertical rule for permutation-equality-comprehension, AsFunction representation" - , do - return $ Comprehension body - $ gocBefore - ++ [ Generator (GenInExpr pat [essence| &f1 = &f2 |]) - ] - ++ gocAfter - ) - theRule _ = na "rule_Permutation_Equality_Comprehension" - -rule_Permute_Comprehension_Tuples :: Rule -rule_Permute_Comprehension_Tuples = "permutation-comprehension-tuples{AsFunction}" `namedRule` theRule where - theRule (Comprehension body gensOrConds) = do - (gocBefore, (pat, perm), gocAfter) <- matchFirst gensOrConds $ \ goc -> case goc of - Generator (GenInExpr pat [essence| &perm |] ) -> return (pat, perm) - _ -> na "rule_Comprehension" - TypePermutation{} <- typeOf perm - Permutation_AsFunction <- representationOf perm - [f] <- downX1 perm +rule_Cardinality :: Rule +rule_Cardinality = "permutation-cardinality" `namedRule` theRule where + theRule p = do + p <- match opTwoBars p + TypePermutation{} <- typeOf p + Permutation_AsFunction <- representationOf p + DomainPermutation _ _ innerDom <- domainOf p + [fun] <- downX1 p return - ( "Vertical rule for permutation-comprehension-tuples, AsFunction representation" + ( "Vertical rule for permutation cardinality, AsFunction representation." , do - return $ Comprehension body - $ gocBefore - ++ [ Generator (GenInExpr pat [essence| &f|]) - ] - ++ gocAfter + (iPat, i) <- quantifiedVarOverDomain (forgetRepr innerDom) + return [essence| + sum([ toInt(&i != image(&fun, &i)) | &iPat : &innerDom ]) + |] ) - theRule _ = na "rule_Comprehension" - - - -rule_Permute :: Rule -rule_Permute = "permutation-image{AsFunction}" `namedRule` theRule where - theRule [essence| image(&p, &i) |] = do - TypePermutation inner <- typeOf p - typeI <- typeOf i - if typeI `containsType` inner - then do - [f] <- downX1 p - if typesUnify [inner, typeI] - then return - ( "Vertical rule for permutation application to a single value" - , do - return [essence| [&i, catchUndef(image(&f,&i),0)][toInt(&i in defined(&f))+1] |] - ) - else na "rule_Permute" --If we hit this then we should hit a refinement error - else return - ( "Vertical rule for permutation application to a type the permutation doesn't care about" - , do - return [essence| &i |] - ) - theRule _ = na "rule_Permute" - - -rule_Permute_Comprehension :: Rule -rule_Permute_Comprehension = "permutation-image{AsFunction}" `namedRule` theRule where - theRule (Comprehension body gensOrConds) = do - (gocBefore, (pat, p, i), gocAfter) <- matchFirst gensOrConds $ \ goc -> case goc of - Generator (GenInExpr pat [essence| image(&p, &i) |]) -> return (pat, p, i) - _ -> na "rule_Comprehension" - - TypePermutation inner <- typeOf p - typeI <- typeOf i - if typeI `containsType` inner - then do - [f] <- downX1 p - if typesUnify [inner, typeI] - then return - ( "Vertical rule for permutation application to a single value" - , return - (Comprehension body $ gocBefore - ++ [Generator (GenInExpr pat - [essence| [&i, catchUndef(image(&f,&i),0)][toInt(&i in defined(&f))+1] |])] - ++ gocAfter) - ) - else na "rule_Permute" - else return - ( "Vertical rule for permutation application to a type the permutation doesn't care about" - , return - (Comprehension body $ gocBefore - ++ [Generator (GenInExpr pat [essence| &i |])] - ++ gocAfter) - ) - theRule _ = na "rule_Permute" - -rule_Matrix_Permute :: Rule -rule_Matrix_Permute = "matrix-image" `namedRule` theRule where - theRule [essence| image(&perm, &y) |] = do - ty@(TypeMatrix _ _) <- typeOf y - (TypePermutation inn) <- typeOf perm - if not $ typesUnify [ty, inn] - then do - unless (isPrimitiveType ty) $ fail ("not a primitive type:" <+> pretty ty) - y' <- flattenIfNeeded y - dm@(DomainMatrix dyindex _) <- domainOf y' - return - ( "Horizontal rule for image matrix" - , do - (dPat, d) <- quantifiedVar - (pyName, py) <- auxiliaryVar - return $ WithLocals - [essence| &py |] - (AuxiliaryVars - [ Declaration (FindOrGiven LocalFind pyName dm) - , SuchThat - [ [essence| - forAll &dPat : &dyindex . - &py[image(&perm,&d)] = image(&perm,&y'[&d]) - |] - ] - ] - ) - ) - else na "rule_Matrix_Permute" - theRule _ = na "rule_Matrix_Permute" - -rule_Matrix_Permute_Comprehension :: Rule -rule_Matrix_Permute_Comprehension = "matrix-image-comprehension" `namedRule` theRule where - theRule (Comprehension body gensOrConds) = do - (gocBefore, (pat, perm, y), gocAfter) <- matchFirst gensOrConds $ \ goc -> case goc of - Generator (GenInExpr pat [essence| image(&perm, &y) |]) -> return (pat, perm, y) - _ -> na "rule_Matrix_Permute" - ty@(TypeMatrix _ _) <- typeOf y - (TypePermutation inn) <- typeOf perm - if not $ typesUnify [ty, inn] - then do - unless (isPrimitiveType ty) $ fail ("not a primitive type:" <+> pretty ty) - y' <- flattenIfNeeded y - dm@(DomainMatrix dyindex _) <- domainOf y' - return - ( "Horizontal rule for image matrix in comprehension" - , do - (dPat, d) <- quantifiedVar - (pyName, py) <- auxiliaryVar - return $ WithLocals - (Comprehension body $ gocBefore - ++ [Generator (GenInExpr pat [essence| &py |])] - ++ gocAfter) - (AuxiliaryVars - [ Declaration (FindOrGiven LocalFind pyName dm) - , SuchThat - [ [essence| - forAll &dPat : &dyindex . - &py[image(&perm,&d)] = image(&perm,&y'[&d]) - |] - ] - ] - ) - ) - else na "rule_Matrix_Permute_Comprehension" - theRule _ = na "rule_Matrix_Permute_Comprehension" - -rule_Set_Permute :: Rule -rule_Set_Permute = "set-image" `namedRule` theRule where - theRule (Comprehension body gensOrConds) = do - (gocBefore, (pat, perm, y), gocAfter) <- matchFirst gensOrConds $ \ goc -> case goc of - Generator (GenInExpr pat [essence| image(&perm, &y) |]) -> return (pat, perm, y) - _ -> na "rule_Set_Permute" - ts@(TypeSet _) <- typeOf y - (TypePermutation inn) <- typeOf perm - if not $ typesUnify [ts, inn] - then do - ds <- domainOf y - return - ( "Horizontal rule for image set" - , do - (dPat, d) <- quantifiedVar - (pyName, py) <- auxiliaryVar - return $ WithLocals - (Comprehension body $ gocBefore - ++ [Generator (GenInExpr pat [essence| &py |])] - ++ gocAfter) - (AuxiliaryVars - [ Declaration (FindOrGiven LocalFind pyName ds) - , SuchThat - [ [essence| - |&y| = |&py| - /\ forAll &dPat in &y . - image(&perm, &d) in &py - |] - ] - ] - ) - ) - else na "rule_Set_Permute" - theRule _ = na "rule_Set_Permute" - - -rule_Relation_Permute :: Rule -rule_Relation_Permute = "relation-image" `namedRule` theRule where - theRule [essence| image(&perm, &y) |] = do - case y of WithLocals{} -> na "bubble-delay" ; _ -> return () - ts@(TypeRelation _) <- typeOf y - (TypePermutation inn) <- typeOf perm - if not $ typesUnify [ts, inn] - then do - ds <- domainOf y - return - ( "Horizontal rule for image relation in comprehension" - , do - (dPat, d) <- quantifiedVar - (pyName, py) <- auxiliaryVar - return $ WithLocals - [essence| &py |] - (AuxiliaryVars - [ Declaration (FindOrGiven LocalFind pyName ds) - , SuchThat - [ [essence| - |&y| = |&py| - /\ and([image(&perm, &d) in &py | &dPat <- &y]) - - |] - ] - ] - ) - ) - else na "rule_Relation_Permute" - theRule _ = na "rule_Relation_Permute" - -rule_Relation_Permute_Comprehension :: Rule -rule_Relation_Permute_Comprehension = "relation-image-comprehension" `namedRule` theRule where - theRule (Comprehension body gensOrConds) = do - (gocBefore, (pat, perm, y), gocAfter) <- matchFirst gensOrConds $ \ goc -> case goc of - Generator (GenInExpr pat [essence| image(&perm, &y) |]) -> return (pat, perm, y) - _ -> na "rule_Relation_Permute_Comprehension" - case y of WithLocals{} -> na "bubble-delay" ; _ -> return () - ts@(TypeRelation _) <- typeOf y - (TypePermutation inn) <- typeOf perm - if not $ typesUnify [ts, inn] - then do - ds <- domainOf y - return - ( "Horizontal rule for image relation in comprehension" - , do - (dPat, d) <- quantifiedVar - (pyName, py) <- auxiliaryVar - return $ WithLocals - (Comprehension body $ gocBefore - ++ [Generator (GenInExpr pat [essence| &py |])] - ++ gocAfter) - (AuxiliaryVars - [ Declaration (FindOrGiven LocalFind pyName ds) - , SuchThat - [ [essence| - |&y| = |&py| - /\ and([image(&perm, &d) in &py | &dPat <- &y]) - |] - ] - ] - ) - ) - else na "rule_Relation_Permute_Comprehension" - theRule _ = na "rule_Relation_Permute_Comprehension" - - -rule_Tuple_Permute :: Rule -rule_Tuple_Permute = "tuple-image" `namedRule` theRule where - theRule [essence| image(&perm, &y) |] = do - case y of WithLocals{} -> na "bubble-delay" ; _ -> return () - ty' <- typeOf y --- traceM $ "rule_Tuple_Permute: " ++ show ty' - ty@(TypeTuple it) <- typeOf y - (TypePermutation inn) <- typeOf perm - if not $ typesUnify [ty, inn] - then do --- traceM $ "rule_Tuple_Permute: applying" - dm <- domainOf y - return - ( "Horizontal rule for image tuple in comprehension" - , do - (pyName, py) <- auxiliaryVar - return $ WithLocals - [essence| &py |] - (AuxiliaryVars $ - [ Declaration (FindOrGiven LocalFind pyName dm)] - ++ ((\x -> let d = Constant $ ConstantInt NoTag x - in SuchThat [[essence| &py[&d] = image(&perm,&y[&d]) |] ]) - <$> [1..(genericLength it)]) - - - ) - ) - else na "rule_Tuple_Permute" - theRule _ = na "rule_Tuple_Permute" - -rule_Tuple_Permute_Comprehension :: Rule -rule_Tuple_Permute_Comprehension = "tuple-image-comprehension" `namedRule` theRule where - theRule (Comprehension body gensOrConds) = do - (gocBefore, (pat, perm, y), gocAfter) <- matchFirst gensOrConds $ \ goc -> case goc of - Generator (GenInExpr pat [essence| image(&perm, &y) |]) -> return (pat, perm, y) - _ -> na "rule_Tuple_Permute" - case y of WithLocals{} -> na "bubble-delay" ; _ -> return () - ty' <- typeOf y --- traceM $ "rule_Tuple_Permute_Comprehension: " ++ show ty' - ty@(TypeTuple it) <- typeOf y - (TypePermutation inn) <- typeOf perm - if not $ typesUnify [ty, inn] - then do --- traceM $ "rule_Tuple_Permute_Comprehension: applying" - dm <- domainOf y - return - ( "Horizontal rule for image tuple in comprehension" - , do - (pyName, py) <- auxiliaryVar - return $ WithLocals - (Comprehension body $ gocBefore - ++ [Generator (GenInExpr pat [essence| &py |])] - ++ gocAfter) - (AuxiliaryVars $ - [ Declaration (FindOrGiven LocalFind pyName dm)] - ++ ((\x -> let d = Constant $ ConstantInt NoTag x - in SuchThat [[essence| &py[&d] = image(&perm,&y[&d]) |] ]) - <$> [1..(genericLength it)]) - ) - ) - else na "rule_Tuple_Permute_Comprehension" - theRule _ = na "rule_Tuple_Permute_Comprehension" - +-- +-- +--rule_Permutation_Inverse :: Rule +--rule_Permutation_Inverse = "permutation-inverse{AsFunction}" `namedRule` theRule where +-- theRule [essence| inverse(&p1, &p2)|] = do +-- TypePermutation{} <- typeOf p1 +-- Permutation_AsFunction <- representationOf p1 +-- TypePermutation{} <- typeOf p2 +-- Permutation_AsFunction <- representationOf p2 +-- [f1] <- downX1 p2 +-- [f2] <- downX1 p2 +-- return +-- ( "Vertical rule for permutation-inverse, AsFunction representation" +-- , return [essence| inverse(&f1, &f2) |] +-- ) +-- theRule _ = na "rule_Permutation_Equality" +-- +-- +--rule_Permutation_Inverse_Comprehension :: Rule +--rule_Permutation_Inverse_Comprehension = "permutation-inverse-comprehension{AsFunction}" `namedRule` theRule where +-- theRule (Comprehension body gensOrConds) = do +-- (gocBefore, (pat, p1, p2), gocAfter) <- matchFirst gensOrConds $ \ goc -> case goc of +-- Generator (GenInExpr pat [essence| inverse(&p1, &p2)|] ) -> return (pat, p1, p2) +-- _ -> na "rule_Inverse_Comprehension" +-- TypePermutation{} <- typeOf p1 +-- Permutation_AsFunction <- representationOf p1 +-- TypePermutation{} <- typeOf p2 +-- Permutation_AsFunction <- representationOf p2 +-- [f1] <- downX1 p2 +-- [f2] <- downX1 p2 +-- return +-- ( "Vertical rule for permutation-inverse-comprehension, AsFunction representation" +-- , do +-- return $ Comprehension body +-- $ gocBefore +-- ++ [ Generator (GenInExpr pat [essence| inverse(&f1, &f2) |]) +-- ] +-- ++ gocAfter +-- ) +-- theRule _ = na "rule_Permutation_Inverse_Comprehension" +-- +-- +-- +--rule_Permutation_Equality :: Rule +--rule_Permutation_Equality = "permutation-equality{AsFunction}" `namedRule` theRule where +-- theRule [essence| &p1 = &p2|] = do +-- TypePermutation{} <- typeOf p1 +-- Permutation_AsFunction <- representationOf p1 +-- TypePermutation{} <- typeOf p2 +-- Permutation_AsFunction <- representationOf p2 +-- [f1] <- downX1 p2 +-- [f2] <- downX1 p2 +-- return +-- ( "Vertical rule for permutation-equality, AsFunction representation" +-- , return [essence| &f1 = &f2 |] +-- ) +-- theRule _ = na "rule_Permutation_Equality" +-- +-- +--rule_Permutation_Equality_Comprehension :: Rule +--rule_Permutation_Equality_Comprehension = "permutation-equality-comprehension{AsFunction}" `namedRule` theRule where +-- theRule (Comprehension body gensOrConds) = do +-- (gocBefore, (pat, p1, p2), gocAfter) <- matchFirst gensOrConds $ \ goc -> case goc of +-- Generator (GenInExpr pat [essence| &p1 = &p2|] ) -> return (pat, p1, p2) +-- _ -> na "rule_Comprehension" +-- TypePermutation{} <- typeOf p1 +-- Permutation_AsFunction <- representationOf p1 +-- TypePermutation{} <- typeOf p2 +-- Permutation_AsFunction <- representationOf p2 +-- [f1] <- downX1 p2 +-- [f2] <- downX1 p2 +-- return +-- ( "Vertical rule for permutation-equality-comprehension, AsFunction representation" +-- , do +-- return $ Comprehension body +-- $ gocBefore +-- ++ [ Generator (GenInExpr pat [essence| &f1 = &f2 |]) +-- ] +-- ++ gocAfter +-- ) +-- theRule _ = na "rule_Permutation_Equality_Comprehension" +-- +--rule_Permute_Comprehension_Tuples :: Rule +--rule_Permute_Comprehension_Tuples = "permutation-comprehension-tuples{AsFunction}" `namedRule` theRule where +-- theRule (Comprehension body gensOrConds) = do +-- (gocBefore, (pat, perm), gocAfter) <- matchFirst gensOrConds $ \ goc -> case goc of +-- Generator (GenInExpr pat [essence| &perm |] ) -> return (pat, perm) +-- _ -> na "rule_Comprehension" +-- TypePermutation{} <- typeOf perm +-- Permutation_AsFunction <- representationOf perm +-- [f] <- downX1 perm +-- return +-- ( "Vertical rule for permutation-comprehension-tuples, AsFunction representation" +-- , do +-- return $ Comprehension body +-- $ gocBefore +-- ++ [ Generator (GenInExpr pat [essence| &f|]) +-- ] +-- ++ gocAfter +-- ) +-- theRule _ = na "rule_Comprehension" +-- +-- +-- +--rule_Permute :: Rule +--rule_Permute = "permutation-image{AsFunction}" `namedRule` theRule where +-- theRule [essence| image(&p, &i) |] = do +-- TypePermutation inner <- typeOf p +-- typeI <- typeOf i +-- if typeI `containsType` inner +-- then do +-- [f] <- downX1 p +-- if typesUnify [inner, typeI] +-- then return +-- ( "Vertical rule for permutation application to a single value" +-- , do +-- return [essence| [&i, catchUndef(image(&f,&i),0)][toInt(&i in defined(&f))+1] |] +-- ) +-- else na "rule_Permute" --If we hit this then we should hit a refinement error +-- else return +-- ( "Vertical rule for permutation application to a type the permutation doesn't care about" +-- , do +-- return [essence| &i |] +-- ) +-- theRule _ = na "rule_Permute" +-- +-- +--rule_Permute_Comprehension :: Rule +--rule_Permute_Comprehension = "permutation-image{AsFunction}" `namedRule` theRule where +-- theRule (Comprehension body gensOrConds) = do +-- (gocBefore, (pat, p, i), gocAfter) <- matchFirst gensOrConds $ \ goc -> case goc of +-- Generator (GenInExpr pat [essence| image(&p, &i) |]) -> return (pat, p, i) +-- _ -> na "rule_Comprehension" +-- +-- TypePermutation inner <- typeOf p +-- typeI <- typeOf i +-- if typeI `containsType` inner +-- then do +-- [f] <- downX1 p +-- if typesUnify [inner, typeI] +-- then return +-- ( "Vertical rule for permutation application to a single value" +-- , return +-- (Comprehension body $ gocBefore +-- ++ [Generator (GenInExpr pat +-- [essence| [&i, catchUndef(image(&f,&i),0)][toInt(&i in defined(&f))+1] |])] +-- ++ gocAfter) +-- ) +-- else na "rule_Permute" +-- else return +-- ( "Vertical rule for permutation application to a type the permutation doesn't care about" +-- , return +-- (Comprehension body $ gocBefore +-- ++ [Generator (GenInExpr pat [essence| &i |])] +-- ++ gocAfter) +-- ) +-- theRule _ = na "rule_Permute" +-- +--rule_Matrix_Permute :: Rule +--rule_Matrix_Permute = "matrix-image" `namedRule` theRule where +-- theRule [essence| image(&perm, &y) |] = do +-- ty@(TypeMatrix _ _) <- typeOf y +-- (TypePermutation inn) <- typeOf perm +-- if not $ typesUnify [ty, inn] +-- then do +-- unless (isPrimitiveType ty) $ fail ("not a primitive type:" <+> pretty ty) +-- y' <- flattenIfNeeded y +-- dm@(DomainMatrix dyindex _) <- domainOf y' +-- return +-- ( "Horizontal rule for image matrix" +-- , do +-- (dPat, d) <- quantifiedVar +-- (pyName, py) <- auxiliaryVar +-- return $ WithLocals +-- [essence| &py |] +-- (AuxiliaryVars +-- [ Declaration (FindOrGiven LocalFind pyName dm) +-- , SuchThat +-- [ [essence| +-- forAll &dPat : &dyindex . +-- &py[image(&perm,&d)] = image(&perm,&y'[&d]) +-- |] +-- ] +-- ] +-- ) +-- ) +-- else na "rule_Matrix_Permute" +-- theRule _ = na "rule_Matrix_Permute" +-- +--rule_Matrix_Permute_Comprehension :: Rule +--rule_Matrix_Permute_Comprehension = "matrix-image-comprehension" `namedRule` theRule where +-- theRule (Comprehension body gensOrConds) = do +-- (gocBefore, (pat, perm, y), gocAfter) <- matchFirst gensOrConds $ \ goc -> case goc of +-- Generator (GenInExpr pat [essence| image(&perm, &y) |]) -> return (pat, perm, y) +-- _ -> na "rule_Matrix_Permute" +-- ty@(TypeMatrix _ _) <- typeOf y +-- (TypePermutation inn) <- typeOf perm +-- if not $ typesUnify [ty, inn] +-- then do +-- unless (isPrimitiveType ty) $ fail ("not a primitive type:" <+> pretty ty) +-- y' <- flattenIfNeeded y +-- dm@(DomainMatrix dyindex _) <- domainOf y' +-- return +-- ( "Horizontal rule for image matrix in comprehension" +-- , do +-- (dPat, d) <- quantifiedVar +-- (pyName, py) <- auxiliaryVar +-- return $ WithLocals +-- (Comprehension body $ gocBefore +-- ++ [Generator (GenInExpr pat [essence| &py |])] +-- ++ gocAfter) +-- (AuxiliaryVars +-- [ Declaration (FindOrGiven LocalFind pyName dm) +-- , SuchThat +-- [ [essence| +-- forAll &dPat : &dyindex . +-- &py[image(&perm,&d)] = image(&perm,&y'[&d]) +-- |] +-- ] +-- ] +-- ) +-- ) +-- else na "rule_Matrix_Permute_Comprehension" +-- theRule _ = na "rule_Matrix_Permute_Comprehension" +-- +--rule_Set_Permute :: Rule +--rule_Set_Permute = "set-image" `namedRule` theRule where +-- theRule (Comprehension body gensOrConds) = do +-- (gocBefore, (pat, perm, y), gocAfter) <- matchFirst gensOrConds $ \ goc -> case goc of +-- Generator (GenInExpr pat [essence| image(&perm, &y) |]) -> return (pat, perm, y) +-- _ -> na "rule_Set_Permute" +-- ts@(TypeSet _) <- typeOf y +-- (TypePermutation inn) <- typeOf perm +-- if not $ typesUnify [ts, inn] +-- then do +-- ds <- domainOf y +-- return +-- ( "Horizontal rule for image set" +-- , do +-- (dPat, d) <- quantifiedVar +-- (pyName, py) <- auxiliaryVar +-- return $ WithLocals +-- (Comprehension body $ gocBefore +-- ++ [Generator (GenInExpr pat [essence| &py |])] +-- ++ gocAfter) +-- (AuxiliaryVars +-- [ Declaration (FindOrGiven LocalFind pyName ds) +-- , SuchThat +-- [ [essence| +-- |&y| = |&py| +-- /\ forAll &dPat in &y . +-- image(&perm, &d) in &py +-- |] +-- ] +-- ] +-- ) +-- ) +-- else na "rule_Set_Permute" +-- theRule _ = na "rule_Set_Permute" +-- +-- +--rule_Relation_Permute :: Rule +--rule_Relation_Permute = "relation-image" `namedRule` theRule where +-- theRule [essence| image(&perm, &y) |] = do +-- case y of WithLocals{} -> na "bubble-delay" ; _ -> return () +-- ts@(TypeRelation _) <- typeOf y +-- (TypePermutation inn) <- typeOf perm +-- if not $ typesUnify [ts, inn] +-- then do +-- ds <- domainOf y +-- return +-- ( "Horizontal rule for image relation in comprehension" +-- , do +-- (dPat, d) <- quantifiedVar +-- (pyName, py) <- auxiliaryVar +-- return $ WithLocals +-- [essence| &py |] +-- (AuxiliaryVars +-- [ Declaration (FindOrGiven LocalFind pyName ds) +-- , SuchThat +-- [ [essence| +-- |&y| = |&py| +-- /\ and([image(&perm, &d) in &py | &dPat <- &y]) +-- +-- |] +-- ] +-- ] +-- ) +-- ) +-- else na "rule_Relation_Permute" +-- theRule _ = na "rule_Relation_Permute" +-- +--rule_Relation_Permute_Comprehension :: Rule +--rule_Relation_Permute_Comprehension = "relation-image-comprehension" `namedRule` theRule where +-- theRule (Comprehension body gensOrConds) = do +-- (gocBefore, (pat, perm, y), gocAfter) <- matchFirst gensOrConds $ \ goc -> case goc of +-- Generator (GenInExpr pat [essence| image(&perm, &y) |]) -> return (pat, perm, y) +-- _ -> na "rule_Relation_Permute_Comprehension" +-- case y of WithLocals{} -> na "bubble-delay" ; _ -> return () +-- ts@(TypeRelation _) <- typeOf y +-- (TypePermutation inn) <- typeOf perm +-- if not $ typesUnify [ts, inn] +-- then do +-- ds <- domainOf y +-- return +-- ( "Horizontal rule for image relation in comprehension" +-- , do +-- (dPat, d) <- quantifiedVar +-- (pyName, py) <- auxiliaryVar +-- return $ WithLocals +-- (Comprehension body $ gocBefore +-- ++ [Generator (GenInExpr pat [essence| &py |])] +-- ++ gocAfter) +-- (AuxiliaryVars +-- [ Declaration (FindOrGiven LocalFind pyName ds) +-- , SuchThat +-- [ [essence| +-- |&y| = |&py| +-- /\ and([image(&perm, &d) in &py | &dPat <- &y]) +-- |] +-- ] +-- ] +-- ) +-- ) +-- else na "rule_Relation_Permute_Comprehension" +-- theRule _ = na "rule_Relation_Permute_Comprehension" +-- +-- +--rule_Tuple_Permute :: Rule +--rule_Tuple_Permute = "tuple-image" `namedRule` theRule where +-- theRule [essence| image(&perm, &y) |] = do +-- case y of WithLocals{} -> na "bubble-delay" ; _ -> return () +-- ty' <- typeOf y +---- traceM $ "rule_Tuple_Permute: " ++ show ty' +-- ty@(TypeTuple it) <- typeOf y +-- (TypePermutation inn) <- typeOf perm +-- if not $ typesUnify [ty, inn] +-- then do +---- traceM $ "rule_Tuple_Permute: applying" +-- dm <- domainOf y +-- return +-- ( "Horizontal rule for image tuple in comprehension" +-- , do +-- (pyName, py) <- auxiliaryVar +-- return $ WithLocals +-- [essence| &py |] +-- (AuxiliaryVars $ +-- [ Declaration (FindOrGiven LocalFind pyName dm)] +-- ++ ((\x -> let d = Constant $ ConstantInt NoTag x +-- in SuchThat [[essence| &py[&d] = image(&perm,&y[&d]) |] ]) +-- <$> [1..(genericLength it)]) +-- +-- +-- ) +-- ) +-- else na "rule_Tuple_Permute" +-- theRule _ = na "rule_Tuple_Permute" +-- +--rule_Tuple_Permute_Comprehension :: Rule +--rule_Tuple_Permute_Comprehension = "tuple-image-comprehension" `namedRule` theRule where +-- theRule (Comprehension body gensOrConds) = do +-- (gocBefore, (pat, perm, y), gocAfter) <- matchFirst gensOrConds $ \ goc -> case goc of +-- Generator (GenInExpr pat [essence| image(&perm, &y) |]) -> return (pat, perm, y) +-- _ -> na "rule_Tuple_Permute" +-- case y of WithLocals{} -> na "bubble-delay" ; _ -> return () +-- ty' <- typeOf y +---- traceM $ "rule_Tuple_Permute_Comprehension: " ++ show ty' +-- ty@(TypeTuple it) <- typeOf y +-- (TypePermutation inn) <- typeOf perm +-- if not $ typesUnify [ty, inn] +-- then do +---- traceM $ "rule_Tuple_Permute_Comprehension: applying" +-- dm <- domainOf y +-- return +-- ( "Horizontal rule for image tuple in comprehension" +-- , do +-- (pyName, py) <- auxiliaryVar +-- return $ WithLocals +-- (Comprehension body $ gocBefore +-- ++ [Generator (GenInExpr pat [essence| &py |])] +-- ++ gocAfter) +-- (AuxiliaryVars $ +-- [ Declaration (FindOrGiven LocalFind pyName dm)] +-- ++ ((\x -> let d = Constant $ ConstantInt NoTag x +-- in SuchThat [[essence| &py[&d] = image(&perm,&y[&d]) |] ]) +-- <$> [1..(genericLength it)]) +-- ) +-- ) +-- else na "rule_Tuple_Permute_Comprehension" +-- theRule _ = na "rule_Tuple_Permute_Comprehension" +-- --rule_Function_Permute :: Rule diff --git a/src/Conjure/UI/Model.hs b/src/Conjure/UI/Model.hs index a7464de9fd..a9f3ccf720 100644 --- a/src/Conjure/UI/Model.hs +++ b/src/Conjure/UI/Model.hs @@ -1187,16 +1187,17 @@ verticalRules = , Vertical.Partition.PartitionAsSet.rule_Comprehension , Vertical.Partition.Occurrence.rule_Comprehension - , Vertical.Permutation.rule_Permutation_Equality - , Vertical.Permutation.rule_Permutation_Equality_Comprehension - , Vertical.Permutation.rule_Permute_Comprehension_Tuples - , Vertical.Permutation.rule_Relation_Permute - , Vertical.Permutation.rule_Relation_Permute_Comprehension - , Vertical.Permutation.rule_Set_Permute - , Vertical.Permutation.rule_Tuple_Permute - , Vertical.Permutation.rule_Tuple_Permute_Comprehension - , Vertical.Permutation.rule_Matrix_Permute - , Vertical.Permutation.rule_Matrix_Permute_Comprehension + , Vertical.Permutation.rule_Cardinality +-- , Vertical.Permutation.rule_Permutation_Equality +-- , Vertical.Permutation.rule_Permutation_Equality_Comprehension +-- , Vertical.Permutation.rule_Permute_Comprehension_Tuples +-- , Vertical.Permutation.rule_Relation_Permute +-- , Vertical.Permutation.rule_Relation_Permute_Comprehension +-- , Vertical.Permutation.rule_Set_Permute +-- , Vertical.Permutation.rule_Tuple_Permute +-- , Vertical.Permutation.rule_Tuple_Permute_Comprehension +-- , Vertical.Permutation.rule_Matrix_Permute +-- , Vertical.Permutation.rule_Matrix_Permute_Comprehension @@ -1314,10 +1315,11 @@ horizontalRules = , Horizontal.Partition.rule_Card , Horizontal.Partition.rule_In - , Horizontal.Permutation.rule_Permutation_Inverse - , Horizontal.Permutation.rule_Permute_Literal - , Horizontal.Permutation.rule_Permute_Literal_Comprehension - , Horizontal.Permutation.rule_Compose + , Horizontal.Permutation.rule_Cardinality_Literal +-- , Horizontal.Permutation.rule_Permutation_Inverse +-- , Horizontal.Permutation.rule_Permute_Literal +-- , Horizontal.Permutation.rule_Permute_Literal_Comprehension +-- , Horizontal.Permutation.rule_Compose @@ -1392,10 +1394,8 @@ delayedRules = , Vertical.Matrix.rule_Concatenate_Singleton , Vertical.Matrix.rule_MatrixIndexing --- , Horizontal.Permutation.rule_Permute_Literal --- , Horizontal.Permutation.rule_Permute_Literal_Comprehension - , Vertical.Permutation.rule_Permute - , Vertical.Permutation.rule_Permute_Comprehension +-- , Vertical.Permutation.rule_Permute +-- , Vertical.Permutation.rule_Permute_Comprehension ] , [ rule_ReducerToComprehension ] From 36c88e742c1ae628ee6daddf13fe1f3b27e07b3d Mon Sep 17 00:00:00 2001 From: Fraser Dunlop Date: Tue, 4 Dec 2018 14:49:40 +0000 Subject: [PATCH 040/229] Some reorganization and tests --- src/Conjure/Rules/Horizontal/Permutation.hs | 46 +++++++++- src/Conjure/Rules/Vertical/Permutation.hs | 49 +++++----- src/Conjure/UI/Model.hs | 4 +- .../.DS_Store | Bin .../permutation.essence | 0 .../permutation.param | 0 .../0001_given_permutation_in_param/run.sh | 0 .../stdout.expected | 0 .../permutation.essence | 0 .../permutation.param | 0 .../0002_given_permutation_in_param/run.sh | 0 .../stdout.expected | 0 .../permutation.essence | 0 .../permutation.param | 0 .../run.sh | 0 .../stderr.expected | 0 .../stdout.expected | 0 .../permutation.essence | 0 .../permutation.param | 0 .../run.sh | 0 .../stdout.expected | 0 .../permutation.essence | 0 .../permutation.param | 0 .../run.sh | 0 .../stdout.expected | 0 .../permutation.essence | 0 .../permutation.param | 0 .../run.sh | 0 .../stdout.expected | 0 .../permutation.essence | 0 .../permutation.param | 0 .../run.sh | 0 .../stdout.expected | 0 .../permutation.essence | 0 .../permutation.param | 0 .../run.sh | 0 .../stdout.expected | 0 .../permutation.essence | 0 .../permutation.param | 0 .../run.sh | 0 .../stdout.expected | 0 .../permutation.essence | 0 .../permutation.param | 0 .../run.sh | 0 .../stdout.expected | 0 .../permutation.essence | 0 .../run.sh | 0 .../stdout.expected | 0 .../permutation.essence | 0 .../run.sh | 0 .../stdout.expected | 0 .../permutation.essence | 0 .../run.sh | 0 .../stdout.expected | 0 .../permutation.essence | 0 .../run.sh | 0 .../stdout.expected | 0 .../permutation.essence | 0 .../run.sh | 0 .../stdout.expected | 0 .../permutation.essence | 0 .../run.sh | 0 .../stdout.expected | 0 .../permutation.essence | 0 .../run.sh | 0 .../stdout.expected | 0 .../permutation.essence | 0 .../run.sh | 0 .../stdout.expected | 0 .../permutation.essence | 0 .../run.sh | 0 .../stdout.expected | 0 .../permutation.essence | 0 .../run.sh | 0 .../stdout.expected | 0 .../permutation.essence | 0 .../permutation.param | 0 .../run.sh | 0 .../stdout.expected | 0 .../permutation.essence | 0 .../permutation.param | 0 .../run.sh | 0 .../stdout.expected | 0 .../permutation.essence | 0 .../permutation.param | 0 .../run.sh | 0 .../stdout.expected | 0 .../permutation.essence | 0 .../permutation.param | 0 .../run.sh | 0 .../stdout.expected | 0 .../permutation.essence | 0 .../permutation.param | 0 .../run.sh | 0 .../stdout.expected | 0 .../permutation.essence | 0 .../permutation.param | 0 .../run.sh | 0 .../stdout.expected | 0 .../permutation.essence | 0 .../run.sh | 0 .../stdout.expected | 0 .../permutation.essence | 0 .../run.sh | 0 .../stdout.expected | 0 .../log | 0 .../log-lite | 0 .../permutation.essence | 0 .../run.sh | 0 .../permutation.essence | 0 .../permutation.param | 0 .../run.sh | 0 .../permutation.essence | 0 .../permutation.param | 0 .../run.sh | 0 .../permutation.essence | 0 .../permutation.param | 0 .../run.sh | 0 .../permutation.essence | 0 .../permutation.param | 0 .../run.sh | 0 .../stdout.expected | 0 .../permutation.essence | 0 .../permutation.param | 0 .../0034_image_of_empty_permutation/run.sh | 0 .../permutation.essence | 0 .../permutation.param | 0 .../run.sh | 0 .../stdout.expected | 0 .../permutation.essence | 0 .../0036_big_test_of_enums_in_matrices/run.sh | 0 .../stdout.expected | 0 .../permutation.essence | 0 .../run.sh | 0 .../stdout.expected | 0 .../permutation.essence | 0 .../run.sh | 0 .../stdout.expected | 0 .../permutation.essence | 0 .../run.sh | 0 .../permutation.essence | 0 .../run.sh | 0 .../stdout.expected | 0 .../permutation.essence | 0 .../run.sh | 0 .../permutation.essence | 0 .../run.sh | 0 .../permutation.essence | 0 .../run.sh | 0 .../runthese.sh | 0 .../permutation.essence | 11 +++ .../permutation.param | 1 + .../run.sh | 3 + .../stdout.expected | 13 +++ .../permutation.essence | 11 +++ .../run.sh | 3 + .../stdout.expected | 13 +++ .../permutation.essence | 9 ++ .../0003_find_permutation_in_generator/run.sh | 3 + .../stdout.expected | 84 ++++++++++++++++++ .../permutations/03_generators/runthese.sh | 2 + .../permutation.essence | 12 +++ .../permutation.param | 2 + .../0001_given_permutations_in_param/run.sh | 3 + .../stdout.expected | 8 ++ .../permutation.essence | 12 +++ .../permutation.param | 2 + .../0002_given_permutations_in_param/run.sh | 3 + .../stdout.expected | 8 ++ .../permutation.essence | 12 +++ .../permutation.param | 1 + .../0003_given_equal_letting/run.sh | 3 + .../0003_given_equal_letting/stdout.expected | 8 ++ .../permutations/04_equality/runthese.sh | 2 + tests/custom/permutations/README.md | 16 +++- tests/custom/permutations/runthese.sh | 2 + 176 files changed, 322 insertions(+), 24 deletions(-) rename tests/custom/{permutations/basic => deprecated_permutations_basic}/.DS_Store (100%) rename tests/custom/{permutations/basic => deprecated_permutations_basic}/0001_given_permutation_in_param/permutation.essence (100%) rename tests/custom/{permutations/basic => deprecated_permutations_basic}/0001_given_permutation_in_param/permutation.param (100%) rename tests/custom/{permutations/basic => deprecated_permutations_basic}/0001_given_permutation_in_param/run.sh (100%) rename tests/custom/{permutations/basic => deprecated_permutations_basic}/0001_given_permutation_in_param/stdout.expected (100%) rename tests/custom/{permutations/basic => deprecated_permutations_basic}/0002_given_permutation_in_param/permutation.essence (100%) rename tests/custom/{permutations/basic => deprecated_permutations_basic}/0002_given_permutation_in_param/permutation.param (100%) rename tests/custom/{permutations/basic => deprecated_permutations_basic}/0002_given_permutation_in_param/run.sh (100%) rename tests/custom/{permutations/basic => deprecated_permutations_basic}/0002_given_permutation_in_param/stdout.expected (100%) rename tests/custom/{permutations/basic => deprecated_permutations_basic}/0003_given_permutation_in_param_2_cycle/permutation.essence (100%) rename tests/custom/{permutations/basic => deprecated_permutations_basic}/0003_given_permutation_in_param_2_cycle/permutation.param (100%) rename tests/custom/{permutations/basic => deprecated_permutations_basic}/0003_given_permutation_in_param_2_cycle/run.sh (100%) rename tests/custom/{permutations/basic => deprecated_permutations_basic}/0003_given_permutation_in_param_2_cycle/stderr.expected (100%) rename tests/custom/{permutations/basic => deprecated_permutations_basic}/0003_given_permutation_in_param_2_cycle/stdout.expected (100%) rename tests/custom/{permutations/basic => deprecated_permutations_basic}/0004_given_permutation_in_param_2_cycle/permutation.essence (100%) rename tests/custom/{permutations/basic => deprecated_permutations_basic}/0004_given_permutation_in_param_2_cycle/permutation.param (100%) rename tests/custom/{permutations/basic => deprecated_permutations_basic}/0004_given_permutation_in_param_2_cycle/run.sh (100%) rename tests/custom/{permutations/basic => deprecated_permutations_basic}/0004_given_permutation_in_param_2_cycle/stdout.expected (100%) rename tests/custom/{permutations/basic => deprecated_permutations_basic}/0005_find_int_image_under_given_permutation/permutation.essence (100%) rename tests/custom/{permutations/basic => deprecated_permutations_basic}/0005_find_int_image_under_given_permutation/permutation.param (100%) rename tests/custom/{permutations/basic => deprecated_permutations_basic}/0005_find_int_image_under_given_permutation/run.sh (100%) rename tests/custom/{permutations/basic => deprecated_permutations_basic}/0005_find_int_image_under_given_permutation/stdout.expected (100%) rename tests/custom/{permutations/basic => deprecated_permutations_basic}/0006_find_int_image_under_given_permutation/permutation.essence (100%) rename tests/custom/{permutations/basic => deprecated_permutations_basic}/0006_find_int_image_under_given_permutation/permutation.param (100%) rename tests/custom/{permutations/basic => deprecated_permutations_basic}/0006_find_int_image_under_given_permutation/run.sh (100%) rename tests/custom/{permutations/basic => deprecated_permutations_basic}/0006_find_int_image_under_given_permutation/stdout.expected (100%) rename tests/custom/{permutations/basic => deprecated_permutations_basic}/0007_find_int_image_under_given_permutation/permutation.essence (100%) rename tests/custom/{permutations/basic => deprecated_permutations_basic}/0007_find_int_image_under_given_permutation/permutation.param (100%) rename tests/custom/{permutations/basic => deprecated_permutations_basic}/0007_find_int_image_under_given_permutation/run.sh (100%) rename tests/custom/{permutations/basic => deprecated_permutations_basic}/0007_find_int_image_under_given_permutation/stdout.expected (100%) rename tests/custom/{permutations/basic => deprecated_permutations_basic}/0008_find_int_image_under_two_composed_given_permutations/permutation.essence (100%) rename tests/custom/{permutations/basic => deprecated_permutations_basic}/0008_find_int_image_under_two_composed_given_permutations/permutation.param (100%) rename tests/custom/{permutations/basic => deprecated_permutations_basic}/0008_find_int_image_under_two_composed_given_permutations/run.sh (100%) rename tests/custom/{permutations/basic => deprecated_permutations_basic}/0008_find_int_image_under_two_composed_given_permutations/stdout.expected (100%) rename tests/custom/{permutations/basic => deprecated_permutations_basic}/0009_find_int_image_under_three_composed_given_permutations/permutation.essence (100%) rename tests/custom/{permutations/basic => deprecated_permutations_basic}/0009_find_int_image_under_three_composed_given_permutations/permutation.param (100%) rename tests/custom/{permutations/basic => deprecated_permutations_basic}/0009_find_int_image_under_three_composed_given_permutations/run.sh (100%) rename tests/custom/{permutations/basic => deprecated_permutations_basic}/0009_find_int_image_under_three_composed_given_permutations/stdout.expected (100%) rename tests/custom/{permutations/basic => deprecated_permutations_basic}/0010_find_int_image_under_three_composed_given_permutations/permutation.essence (100%) rename tests/custom/{permutations/basic => deprecated_permutations_basic}/0010_find_int_image_under_three_composed_given_permutations/permutation.param (100%) rename tests/custom/{permutations/basic => deprecated_permutations_basic}/0010_find_int_image_under_three_composed_given_permutations/run.sh (100%) rename tests/custom/{permutations/basic => deprecated_permutations_basic}/0010_find_int_image_under_three_composed_given_permutations/stdout.expected (100%) rename tests/custom/{permutations/basic => deprecated_permutations_basic}/0011_find_int_and_permutation_such_that_int_image_equals_const/permutation.essence (100%) rename tests/custom/{permutations/basic => deprecated_permutations_basic}/0011_find_int_and_permutation_such_that_int_image_equals_const/run.sh (100%) rename tests/custom/{permutations/basic => deprecated_permutations_basic}/0011_find_int_and_permutation_such_that_int_image_equals_const/stdout.expected (100%) rename tests/custom/{permutations/basic => deprecated_permutations_basic}/0012_find_int_and_permutation_such_that_int_image_equals_const/permutation.essence (100%) rename tests/custom/{permutations/basic => deprecated_permutations_basic}/0012_find_int_and_permutation_such_that_int_image_equals_const/run.sh (100%) rename tests/custom/{permutations/basic => deprecated_permutations_basic}/0012_find_int_and_permutation_such_that_int_image_equals_const/stdout.expected (100%) rename tests/custom/{permutations/basic => deprecated_permutations_basic}/0013_find_permutation_such_that_image_of_matrix1_equals_matrix2/permutation.essence (100%) rename tests/custom/{permutations/basic => deprecated_permutations_basic}/0013_find_permutation_such_that_image_of_matrix1_equals_matrix2/run.sh (100%) rename tests/custom/{permutations/basic => deprecated_permutations_basic}/0013_find_permutation_such_that_image_of_matrix1_equals_matrix2/stdout.expected (100%) rename tests/custom/{permutations/basic => deprecated_permutations_basic}/0014_find_matrix_such_that_swapping_any_index_pairs_becomes_lex_greater/permutation.essence (100%) rename tests/custom/{permutations/basic => deprecated_permutations_basic}/0014_find_matrix_such_that_swapping_any_index_pairs_becomes_lex_greater/run.sh (100%) rename tests/custom/{permutations/basic => deprecated_permutations_basic}/0014_find_matrix_such_that_swapping_any_index_pairs_becomes_lex_greater/stdout.expected (100%) rename tests/custom/{permutations/basic => deprecated_permutations_basic}/0015_find_set_of_permuted_elements_of_matrix/permutation.essence (100%) rename tests/custom/{permutations/basic => deprecated_permutations_basic}/0015_find_set_of_permuted_elements_of_matrix/run.sh (100%) rename tests/custom/{permutations/basic => deprecated_permutations_basic}/0015_find_set_of_permuted_elements_of_matrix/stdout.expected (100%) rename tests/custom/{permutations/basic => deprecated_permutations_basic}/0016_find_permutation_such_that_image_is_identity_for_given_matrix/permutation.essence (100%) rename tests/custom/{permutations/basic => deprecated_permutations_basic}/0016_find_permutation_such_that_image_is_identity_for_given_matrix/run.sh (100%) rename tests/custom/{permutations/basic => deprecated_permutations_basic}/0016_find_permutation_such_that_image_is_identity_for_given_matrix/stdout.expected (100%) rename tests/custom/{permutations/basic => deprecated_permutations_basic}/0017_find_two_permutations_with_overlapping_domains_and_same_image_over_domain_union/permutation.essence (100%) rename tests/custom/{permutations/basic => deprecated_permutations_basic}/0017_find_two_permutations_with_overlapping_domains_and_same_image_over_domain_union/run.sh (100%) rename tests/custom/{permutations/basic => deprecated_permutations_basic}/0017_find_two_permutations_with_overlapping_domains_and_same_image_over_domain_union/stdout.expected (100%) rename tests/custom/{permutations/basic => deprecated_permutations_basic}/0018_find_matrix_lex_less_than_under_any_swap/permutation.essence (100%) rename tests/custom/{permutations/basic => deprecated_permutations_basic}/0018_find_matrix_lex_less_than_under_any_swap/run.sh (100%) rename tests/custom/{permutations/basic => deprecated_permutations_basic}/0018_find_matrix_lex_less_than_under_any_swap/stdout.expected (100%) rename tests/custom/{permutations/basic => deprecated_permutations_basic}/0019_find_set_of_permutation_tuples_using_comprehension/permutation.essence (100%) rename tests/custom/{permutations/basic => deprecated_permutations_basic}/0019_find_set_of_permutation_tuples_using_comprehension/run.sh (100%) rename tests/custom/{permutations/basic => deprecated_permutations_basic}/0019_find_set_of_permutation_tuples_using_comprehension/stdout.expected (100%) rename tests/custom/{permutations/basic => deprecated_permutations_basic}/0020_find_permutation_inverse_using_comprehension/permutation.essence (100%) rename tests/custom/{permutations/basic => deprecated_permutations_basic}/0020_find_permutation_inverse_using_comprehension/run.sh (100%) rename tests/custom/{permutations/basic => deprecated_permutations_basic}/0020_find_permutation_inverse_using_comprehension/stdout.expected (100%) rename tests/custom/{permutations/basic => deprecated_permutations_basic}/0021_image_of_int_under_composition_of_two_given_permutations/permutation.essence (100%) rename tests/custom/{permutations/basic => deprecated_permutations_basic}/0021_image_of_int_under_composition_of_two_given_permutations/permutation.param (100%) rename tests/custom/{permutations/basic => deprecated_permutations_basic}/0021_image_of_int_under_composition_of_two_given_permutations/run.sh (100%) rename tests/custom/{permutations/basic => deprecated_permutations_basic}/0021_image_of_int_under_composition_of_two_given_permutations/stdout.expected (100%) rename tests/custom/{permutations/basic => deprecated_permutations_basic}/0022_find_matrices_of_enum_x_y_such_that_y_lexless_than_x_under_any_index_swap/permutation.essence (100%) rename tests/custom/{permutations/basic => deprecated_permutations_basic}/0022_find_matrices_of_enum_x_y_such_that_y_lexless_than_x_under_any_index_swap/permutation.param (100%) rename tests/custom/{permutations/basic => deprecated_permutations_basic}/0022_find_matrices_of_enum_x_y_such_that_y_lexless_than_x_under_any_index_swap/run.sh (100%) rename tests/custom/{permutations/basic => deprecated_permutations_basic}/0022_find_matrices_of_enum_x_y_such_that_y_lexless_than_x_under_any_index_swap/stdout.expected (100%) rename tests/custom/{permutations/basic => deprecated_permutations_basic}/0023_find_triples_x_y_such_that_y_lex_less_x_under_any_swap/permutation.essence (100%) rename tests/custom/{permutations/basic => deprecated_permutations_basic}/0023_find_triples_x_y_such_that_y_lex_less_x_under_any_swap/permutation.param (100%) rename tests/custom/{permutations/basic => deprecated_permutations_basic}/0023_find_triples_x_y_such_that_y_lex_less_x_under_any_swap/run.sh (100%) rename tests/custom/{permutations/basic => deprecated_permutations_basic}/0023_find_triples_x_y_such_that_y_lex_less_x_under_any_swap/stdout.expected (100%) rename tests/custom/{permutations/basic => deprecated_permutations_basic}/0024_find_sets_x_y_such_that_y_lexless_x_under_any_swap/permutation.essence (100%) rename tests/custom/{permutations/basic => deprecated_permutations_basic}/0024_find_sets_x_y_such_that_y_lexless_x_under_any_swap/permutation.param (100%) rename tests/custom/{permutations/basic => deprecated_permutations_basic}/0024_find_sets_x_y_such_that_y_lexless_x_under_any_swap/run.sh (100%) rename tests/custom/{permutations/basic => deprecated_permutations_basic}/0024_find_sets_x_y_such_that_y_lexless_x_under_any_swap/stdout.expected (100%) rename tests/custom/{permutations/basic => deprecated_permutations_basic}/0025_find_permutation_and_matrices_x_y_such_that_image_x_eq_y/permutation.essence (100%) rename tests/custom/{permutations/basic => deprecated_permutations_basic}/0025_find_permutation_and_matrices_x_y_such_that_image_x_eq_y/permutation.param (100%) rename tests/custom/{permutations/basic => deprecated_permutations_basic}/0025_find_permutation_and_matrices_x_y_such_that_image_x_eq_y/run.sh (100%) rename tests/custom/{permutations/basic => deprecated_permutations_basic}/0025_find_permutation_and_matrices_x_y_such_that_image_x_eq_y/stdout.expected (100%) rename tests/custom/{permutations/basic => deprecated_permutations_basic}/0026_find_matrices_of_enums_x_y_such_that_y_image_x_under_p/permutation.essence (100%) rename tests/custom/{permutations/basic => deprecated_permutations_basic}/0026_find_matrices_of_enums_x_y_such_that_y_image_x_under_p/permutation.param (100%) rename tests/custom/{permutations/basic => deprecated_permutations_basic}/0026_find_matrices_of_enums_x_y_such_that_y_image_x_under_p/run.sh (100%) rename tests/custom/{permutations/basic => deprecated_permutations_basic}/0026_find_matrices_of_enums_x_y_such_that_y_image_x_under_p/stdout.expected (100%) rename tests/custom/{permutations/basic => deprecated_permutations_basic}/0027_find_sets_of_enum_x_y_such_that_y_image_x_under_p/permutation.essence (100%) rename tests/custom/{permutations/basic => deprecated_permutations_basic}/0027_find_sets_of_enum_x_y_such_that_y_image_x_under_p/run.sh (100%) rename tests/custom/{permutations/basic => deprecated_permutations_basic}/0027_find_sets_of_enum_x_y_such_that_y_image_x_under_p/stdout.expected (100%) rename tests/custom/{permutations/basic => deprecated_permutations_basic}/0028_find_sets_of_enum_x_y_such_that_y_image_x_under_p/permutation.essence (100%) rename tests/custom/{permutations/basic => deprecated_permutations_basic}/0028_find_sets_of_enum_x_y_such_that_y_image_x_under_p/run.sh (100%) rename tests/custom/{permutations/basic => deprecated_permutations_basic}/0028_find_sets_of_enum_x_y_such_that_y_image_x_under_p/stdout.expected (100%) rename tests/custom/{permutations/basic => deprecated_permutations_basic}/0029_find_relations_x_y_such_that_y_image_x_under_p/log (100%) rename tests/custom/{permutations/basic => deprecated_permutations_basic}/0029_find_relations_x_y_such_that_y_image_x_under_p/log-lite (100%) rename tests/custom/{permutations/basic => deprecated_permutations_basic}/0029_find_relations_x_y_such_that_y_image_x_under_p/permutation.essence (100%) rename tests/custom/{permutations/basic => deprecated_permutations_basic}/0029_find_relations_x_y_such_that_y_image_x_under_p/run.sh (100%) rename tests/custom/{permutations/basic => deprecated_permutations_basic}/0030_find_permutation_equal_given_permutation/permutation.essence (100%) rename tests/custom/{permutations/basic => deprecated_permutations_basic}/0030_find_permutation_equal_given_permutation/permutation.param (100%) rename tests/custom/{permutations/basic => deprecated_permutations_basic}/0030_find_permutation_equal_given_permutation/run.sh (100%) rename tests/custom/{permutations/basic => deprecated_permutations_basic}/0031_find_matrix_lexless_indices_swapped_in_comprehension/permutation.essence (100%) rename tests/custom/{permutations/basic => deprecated_permutations_basic}/0031_find_matrix_lexless_indices_swapped_in_comprehension/permutation.param (100%) rename tests/custom/{permutations/basic => deprecated_permutations_basic}/0031_find_matrix_lexless_indices_swapped_in_comprehension/run.sh (100%) rename tests/custom/{permutations/basic => deprecated_permutations_basic}/0032_find_sets_of_ints_such_that_tuple_of_sets_lexless_any_int_swapped_tuple/permutation.essence (100%) rename tests/custom/{permutations/basic => deprecated_permutations_basic}/0032_find_sets_of_ints_such_that_tuple_of_sets_lexless_any_int_swapped_tuple/permutation.param (100%) rename tests/custom/{permutations/basic => deprecated_permutations_basic}/0032_find_sets_of_ints_such_that_tuple_of_sets_lexless_any_int_swapped_tuple/run.sh (100%) rename tests/custom/{permutations/basic => deprecated_permutations_basic}/0033_find_matrixes_of_enum_such_that_tuple_of_matrices_lexless_any_int_swapped_tuple/permutation.essence (100%) rename tests/custom/{permutations/basic => deprecated_permutations_basic}/0033_find_matrixes_of_enum_such_that_tuple_of_matrices_lexless_any_int_swapped_tuple/permutation.param (100%) rename tests/custom/{permutations/basic => deprecated_permutations_basic}/0033_find_matrixes_of_enum_such_that_tuple_of_matrices_lexless_any_int_swapped_tuple/run.sh (100%) rename tests/custom/{permutations/basic => deprecated_permutations_basic}/0033_find_matrixes_of_enum_such_that_tuple_of_matrices_lexless_any_int_swapped_tuple/stdout.expected (100%) rename tests/custom/{permutations/basic => deprecated_permutations_basic}/0034_image_of_empty_permutation/permutation.essence (100%) rename tests/custom/{permutations/basic => deprecated_permutations_basic}/0034_image_of_empty_permutation/permutation.param (100%) rename tests/custom/{permutations/basic => deprecated_permutations_basic}/0034_image_of_empty_permutation/run.sh (100%) rename tests/custom/{permutations/basic => deprecated_permutations_basic}/0035_permutation_of_enum_is_identity_for_integers/permutation.essence (100%) rename tests/custom/{permutations/basic => deprecated_permutations_basic}/0035_permutation_of_enum_is_identity_for_integers/permutation.param (100%) rename tests/custom/{permutations/basic => deprecated_permutations_basic}/0035_permutation_of_enum_is_identity_for_integers/run.sh (100%) rename tests/custom/{permutations/basic => deprecated_permutations_basic}/0035_permutation_of_enum_is_identity_for_integers/stdout.expected (100%) rename tests/custom/{permutations/basic => deprecated_permutations_basic}/0036_big_test_of_enums_in_matrices/permutation.essence (100%) rename tests/custom/{permutations/basic => deprecated_permutations_basic}/0036_big_test_of_enums_in_matrices/run.sh (100%) rename tests/custom/{permutations/basic => deprecated_permutations_basic}/0036_big_test_of_enums_in_matrices/stdout.expected (100%) rename tests/custom/{permutations/basic => deprecated_permutations_basic}/0037_matrices_of_enums_indexed_by_enums/permutation.essence (100%) rename tests/custom/{permutations/basic => deprecated_permutations_basic}/0037_matrices_of_enums_indexed_by_enums/run.sh (100%) rename tests/custom/{permutations/basic => deprecated_permutations_basic}/0037_matrices_of_enums_indexed_by_enums/stdout.expected (100%) rename tests/custom/{permutations/basic => deprecated_permutations_basic}/0038_matricies_of_tuples_of_enums_indexed_by_enums/permutation.essence (100%) rename tests/custom/{permutations/basic => deprecated_permutations_basic}/0038_matricies_of_tuples_of_enums_indexed_by_enums/run.sh (100%) rename tests/custom/{permutations/basic => deprecated_permutations_basic}/0038_matricies_of_tuples_of_enums_indexed_by_enums/stdout.expected (100%) rename tests/custom/{permutations/basic => deprecated_permutations_basic}/0039_toSet_on_given_permutation_of_enum/permutation.essence (100%) rename tests/custom/{permutations/basic => deprecated_permutations_basic}/0039_toSet_on_given_permutation_of_enum/run.sh (100%) rename tests/custom/{permutations/basic => deprecated_permutations_basic}/0040_toSet_on_given_permutation_of_int/permutation.essence (100%) rename tests/custom/{permutations/basic => deprecated_permutations_basic}/0040_toSet_on_given_permutation_of_int/run.sh (100%) rename tests/custom/{permutations/basic => deprecated_permutations_basic}/0040_toSet_on_given_permutation_of_int/stdout.expected (100%) rename tests/custom/{permutations/basic => deprecated_permutations_basic}/0041_toSet_on_found_permutation_of_enum/permutation.essence (100%) rename tests/custom/{permutations/basic => deprecated_permutations_basic}/0041_toSet_on_found_permutation_of_enum/run.sh (100%) rename tests/custom/{permutations/basic => deprecated_permutations_basic}/0042_toSet_on_found_permutation_of_int/permutation.essence (100%) rename tests/custom/{permutations/basic => deprecated_permutations_basic}/0042_toSet_on_found_permutation_of_int/run.sh (100%) rename tests/custom/{permutations/basic => deprecated_permutations_basic}/0043_inverse_on_given_permutation_of_int/permutation.essence (100%) rename tests/custom/{permutations/basic => deprecated_permutations_basic}/0043_inverse_on_given_permutation_of_int/run.sh (100%) rename tests/custom/{permutations/basic => deprecated_permutations_basic}/runthese.sh (100%) create mode 100644 tests/custom/permutations/03_generators/0001_given_permutation_in_generator/permutation.essence create mode 100644 tests/custom/permutations/03_generators/0001_given_permutation_in_generator/permutation.param create mode 100755 tests/custom/permutations/03_generators/0001_given_permutation_in_generator/run.sh create mode 100644 tests/custom/permutations/03_generators/0001_given_permutation_in_generator/stdout.expected create mode 100644 tests/custom/permutations/03_generators/0002_letting_permutation_in_generator/permutation.essence create mode 100755 tests/custom/permutations/03_generators/0002_letting_permutation_in_generator/run.sh create mode 100644 tests/custom/permutations/03_generators/0002_letting_permutation_in_generator/stdout.expected create mode 100644 tests/custom/permutations/03_generators/0003_find_permutation_in_generator/permutation.essence create mode 100755 tests/custom/permutations/03_generators/0003_find_permutation_in_generator/run.sh create mode 100644 tests/custom/permutations/03_generators/0003_find_permutation_in_generator/stdout.expected create mode 100644 tests/custom/permutations/03_generators/runthese.sh create mode 100644 tests/custom/permutations/04_equality/0001_given_permutations_in_param/permutation.essence create mode 100644 tests/custom/permutations/04_equality/0001_given_permutations_in_param/permutation.param create mode 100755 tests/custom/permutations/04_equality/0001_given_permutations_in_param/run.sh create mode 100644 tests/custom/permutations/04_equality/0001_given_permutations_in_param/stdout.expected create mode 100644 tests/custom/permutations/04_equality/0002_given_permutations_in_param/permutation.essence create mode 100644 tests/custom/permutations/04_equality/0002_given_permutations_in_param/permutation.param create mode 100755 tests/custom/permutations/04_equality/0002_given_permutations_in_param/run.sh create mode 100644 tests/custom/permutations/04_equality/0002_given_permutations_in_param/stdout.expected create mode 100644 tests/custom/permutations/04_equality/0003_given_equal_letting/permutation.essence create mode 100644 tests/custom/permutations/04_equality/0003_given_equal_letting/permutation.param create mode 100755 tests/custom/permutations/04_equality/0003_given_equal_letting/run.sh create mode 100644 tests/custom/permutations/04_equality/0003_given_equal_letting/stdout.expected create mode 100644 tests/custom/permutations/04_equality/runthese.sh create mode 100644 tests/custom/permutations/runthese.sh diff --git a/src/Conjure/Rules/Horizontal/Permutation.hs b/src/Conjure/Rules/Horizontal/Permutation.hs index f48db66521..63e77d0785 100644 --- a/src/Conjure/Rules/Horizontal/Permutation.hs +++ b/src/Conjure/Rules/Horizontal/Permutation.hs @@ -2,7 +2,8 @@ module Conjure.Rules.Horizontal.Permutation where import Conjure.Rules.Import import Data.List (cycle) -import Data.Permutation (size, fromCycles) +import Data.Permutation (size, fromCycles, toFunction) +import Conjure.Process.Enumerate ( enumerateDomain ) rule_Cardinality_Literal :: Rule @@ -19,6 +20,49 @@ rule_Cardinality_Literal = "permutation-cardinality-literal" `namedRule` theRule return [essence| &i |] ) +rule_Equality :: Rule +rule_Equality = "permutation-equality" `namedRule` theRule where + theRule e = do + (p,q) <- match opEq e + TypePermutation{} <- typeOf p + TypePermutation{} <- typeOf q + return ( "Horizontal rule for permutation equality" + , do + (rPat, r) <- quantifiedVar + (lPat, l) <- quantifiedVar + return [essence| and([ image(&p,&l) = &r | (&lPat,&rPat) <- &q]) |] + ) + + +rule_Permute_Comprehension_Tuples_Literal :: Rule +rule_Permute_Comprehension_Tuples_Literal = "permutation-comprehension-tuples{AsFunction}" `namedRule` theRule where + theRule (Comprehension body gensOrConds) = do + (gocBefore, (pat, perm), gocAfter) <- matchFirst gensOrConds $ \ goc -> case goc of + Generator (GenInExpr pat [essence| &perm |] ) -> return (pat, perm) + _ -> na "rule_Comprehension_Tuples_Literal" + (TypePermutation inner, elems) <- match permutationLiteral perm + DomainPermutation _ _ innerD <- domainOf perm + let f' = toFunction <$> fromCycles elems + case f' of + Left er -> fail $ "Permutation literal invalid." <++> stringToDoc (show er) + Right f -> do + let outLiteral = make matrixLiteral + (TypeMatrix (TypeInt AnyTag) (TypeTuple [inner,inner])) innerD + [ AbstractLiteral (AbsLitTuple [de + ,f de]) + | de <- join elems + ] + return + ( "Vertical rule for permutation-comprehension-tuples-literal" + , do + return $ Comprehension body + $ gocBefore + ++ [ Generator (GenInExpr pat [essence| &outLiteral|]) + ] + ++ gocAfter + ) + theRule _ = na "rule_Comprehension_Tuples_Literal" + -- -- --rule_Compose :: Rule diff --git a/src/Conjure/Rules/Vertical/Permutation.hs b/src/Conjure/Rules/Vertical/Permutation.hs index 7929ccb2f8..705e57e187 100644 --- a/src/Conjure/Rules/Vertical/Permutation.hs +++ b/src/Conjure/Rules/Vertical/Permutation.hs @@ -21,6 +21,33 @@ rule_Cardinality = "permutation-cardinality" `namedRule` theRule where sum([ toInt(&i != image(&fun, &i)) | &iPat : &innerDom ]) |] ) + + +rule_Permute_Comprehension_Tuples :: Rule +rule_Permute_Comprehension_Tuples = "permutation-comprehension-tuples{AsFunction}" `namedRule` theRule where + theRule (Comprehension body gensOrConds) = do + (gocBefore, (pat, perm), gocAfter) <- matchFirst gensOrConds $ \ goc -> case goc of + Generator (GenInExpr pat [essence| &perm |] ) -> return (pat, perm) + _ -> na "rule_Comprehension" + TypePermutation{} <- typeOf perm + Permutation_AsFunction <- representationOf perm + [f] <- downX1 perm + return + ( "Vertical rule for permutation-comprehension-tuples, AsFunction representation" + , do + (lPat, l) <- quantifiedVar + (rPat, r) <- quantifiedVar + return $ Comprehension body + $ gocBefore + ++ [ Generator (GenInExpr pat [essence| [(&l,&r) + | (&lPat, &rPat) <- &f + , &l != &r] |]) + ] + ++ gocAfter + ) + theRule _ = na "rule_Comprehension" + + -- -- --rule_Permutation_Inverse :: Rule @@ -102,27 +129,7 @@ rule_Cardinality = "permutation-cardinality" `namedRule` theRule where -- ++ gocAfter -- ) -- theRule _ = na "rule_Permutation_Equality_Comprehension" --- ---rule_Permute_Comprehension_Tuples :: Rule ---rule_Permute_Comprehension_Tuples = "permutation-comprehension-tuples{AsFunction}" `namedRule` theRule where --- theRule (Comprehension body gensOrConds) = do --- (gocBefore, (pat, perm), gocAfter) <- matchFirst gensOrConds $ \ goc -> case goc of --- Generator (GenInExpr pat [essence| &perm |] ) -> return (pat, perm) --- _ -> na "rule_Comprehension" --- TypePermutation{} <- typeOf perm --- Permutation_AsFunction <- representationOf perm --- [f] <- downX1 perm --- return --- ( "Vertical rule for permutation-comprehension-tuples, AsFunction representation" --- , do --- return $ Comprehension body --- $ gocBefore --- ++ [ Generator (GenInExpr pat [essence| &f|]) --- ] --- ++ gocAfter --- ) --- theRule _ = na "rule_Comprehension" --- + -- -- --rule_Permute :: Rule diff --git a/src/Conjure/UI/Model.hs b/src/Conjure/UI/Model.hs index a9f3ccf720..7ab70b26c2 100644 --- a/src/Conjure/UI/Model.hs +++ b/src/Conjure/UI/Model.hs @@ -1188,9 +1188,9 @@ verticalRules = , Vertical.Partition.Occurrence.rule_Comprehension , Vertical.Permutation.rule_Cardinality + , Vertical.Permutation.rule_Permute_Comprehension_Tuples -- , Vertical.Permutation.rule_Permutation_Equality -- , Vertical.Permutation.rule_Permutation_Equality_Comprehension --- , Vertical.Permutation.rule_Permute_Comprehension_Tuples -- , Vertical.Permutation.rule_Relation_Permute -- , Vertical.Permutation.rule_Relation_Permute_Comprehension -- , Vertical.Permutation.rule_Set_Permute @@ -1316,6 +1316,8 @@ horizontalRules = , Horizontal.Partition.rule_In , Horizontal.Permutation.rule_Cardinality_Literal + , Horizontal.Permutation.rule_Equality + , Horizontal.Permutation.rule_Permute_Comprehension_Tuples_Literal -- , Horizontal.Permutation.rule_Permutation_Inverse -- , Horizontal.Permutation.rule_Permute_Literal -- , Horizontal.Permutation.rule_Permute_Literal_Comprehension diff --git a/tests/custom/permutations/basic/.DS_Store b/tests/custom/deprecated_permutations_basic/.DS_Store similarity index 100% rename from tests/custom/permutations/basic/.DS_Store rename to tests/custom/deprecated_permutations_basic/.DS_Store diff --git a/tests/custom/permutations/basic/0001_given_permutation_in_param/permutation.essence b/tests/custom/deprecated_permutations_basic/0001_given_permutation_in_param/permutation.essence similarity index 100% rename from tests/custom/permutations/basic/0001_given_permutation_in_param/permutation.essence rename to tests/custom/deprecated_permutations_basic/0001_given_permutation_in_param/permutation.essence diff --git a/tests/custom/permutations/basic/0001_given_permutation_in_param/permutation.param b/tests/custom/deprecated_permutations_basic/0001_given_permutation_in_param/permutation.param similarity index 100% rename from tests/custom/permutations/basic/0001_given_permutation_in_param/permutation.param rename to tests/custom/deprecated_permutations_basic/0001_given_permutation_in_param/permutation.param diff --git a/tests/custom/permutations/basic/0001_given_permutation_in_param/run.sh b/tests/custom/deprecated_permutations_basic/0001_given_permutation_in_param/run.sh similarity index 100% rename from tests/custom/permutations/basic/0001_given_permutation_in_param/run.sh rename to tests/custom/deprecated_permutations_basic/0001_given_permutation_in_param/run.sh diff --git a/tests/custom/permutations/basic/0001_given_permutation_in_param/stdout.expected b/tests/custom/deprecated_permutations_basic/0001_given_permutation_in_param/stdout.expected similarity index 100% rename from tests/custom/permutations/basic/0001_given_permutation_in_param/stdout.expected rename to tests/custom/deprecated_permutations_basic/0001_given_permutation_in_param/stdout.expected diff --git a/tests/custom/permutations/basic/0002_given_permutation_in_param/permutation.essence b/tests/custom/deprecated_permutations_basic/0002_given_permutation_in_param/permutation.essence similarity index 100% rename from tests/custom/permutations/basic/0002_given_permutation_in_param/permutation.essence rename to tests/custom/deprecated_permutations_basic/0002_given_permutation_in_param/permutation.essence diff --git a/tests/custom/permutations/basic/0002_given_permutation_in_param/permutation.param b/tests/custom/deprecated_permutations_basic/0002_given_permutation_in_param/permutation.param similarity index 100% rename from tests/custom/permutations/basic/0002_given_permutation_in_param/permutation.param rename to tests/custom/deprecated_permutations_basic/0002_given_permutation_in_param/permutation.param diff --git a/tests/custom/permutations/basic/0002_given_permutation_in_param/run.sh b/tests/custom/deprecated_permutations_basic/0002_given_permutation_in_param/run.sh similarity index 100% rename from tests/custom/permutations/basic/0002_given_permutation_in_param/run.sh rename to tests/custom/deprecated_permutations_basic/0002_given_permutation_in_param/run.sh diff --git a/tests/custom/permutations/basic/0002_given_permutation_in_param/stdout.expected b/tests/custom/deprecated_permutations_basic/0002_given_permutation_in_param/stdout.expected similarity index 100% rename from tests/custom/permutations/basic/0002_given_permutation_in_param/stdout.expected rename to tests/custom/deprecated_permutations_basic/0002_given_permutation_in_param/stdout.expected diff --git a/tests/custom/permutations/basic/0003_given_permutation_in_param_2_cycle/permutation.essence b/tests/custom/deprecated_permutations_basic/0003_given_permutation_in_param_2_cycle/permutation.essence similarity index 100% rename from tests/custom/permutations/basic/0003_given_permutation_in_param_2_cycle/permutation.essence rename to tests/custom/deprecated_permutations_basic/0003_given_permutation_in_param_2_cycle/permutation.essence diff --git a/tests/custom/permutations/basic/0003_given_permutation_in_param_2_cycle/permutation.param b/tests/custom/deprecated_permutations_basic/0003_given_permutation_in_param_2_cycle/permutation.param similarity index 100% rename from tests/custom/permutations/basic/0003_given_permutation_in_param_2_cycle/permutation.param rename to tests/custom/deprecated_permutations_basic/0003_given_permutation_in_param_2_cycle/permutation.param diff --git a/tests/custom/permutations/basic/0003_given_permutation_in_param_2_cycle/run.sh b/tests/custom/deprecated_permutations_basic/0003_given_permutation_in_param_2_cycle/run.sh similarity index 100% rename from tests/custom/permutations/basic/0003_given_permutation_in_param_2_cycle/run.sh rename to tests/custom/deprecated_permutations_basic/0003_given_permutation_in_param_2_cycle/run.sh diff --git a/tests/custom/permutations/basic/0003_given_permutation_in_param_2_cycle/stderr.expected b/tests/custom/deprecated_permutations_basic/0003_given_permutation_in_param_2_cycle/stderr.expected similarity index 100% rename from tests/custom/permutations/basic/0003_given_permutation_in_param_2_cycle/stderr.expected rename to tests/custom/deprecated_permutations_basic/0003_given_permutation_in_param_2_cycle/stderr.expected diff --git a/tests/custom/permutations/basic/0003_given_permutation_in_param_2_cycle/stdout.expected b/tests/custom/deprecated_permutations_basic/0003_given_permutation_in_param_2_cycle/stdout.expected similarity index 100% rename from tests/custom/permutations/basic/0003_given_permutation_in_param_2_cycle/stdout.expected rename to tests/custom/deprecated_permutations_basic/0003_given_permutation_in_param_2_cycle/stdout.expected diff --git a/tests/custom/permutations/basic/0004_given_permutation_in_param_2_cycle/permutation.essence b/tests/custom/deprecated_permutations_basic/0004_given_permutation_in_param_2_cycle/permutation.essence similarity index 100% rename from tests/custom/permutations/basic/0004_given_permutation_in_param_2_cycle/permutation.essence rename to tests/custom/deprecated_permutations_basic/0004_given_permutation_in_param_2_cycle/permutation.essence diff --git a/tests/custom/permutations/basic/0004_given_permutation_in_param_2_cycle/permutation.param b/tests/custom/deprecated_permutations_basic/0004_given_permutation_in_param_2_cycle/permutation.param similarity index 100% rename from tests/custom/permutations/basic/0004_given_permutation_in_param_2_cycle/permutation.param rename to tests/custom/deprecated_permutations_basic/0004_given_permutation_in_param_2_cycle/permutation.param diff --git a/tests/custom/permutations/basic/0004_given_permutation_in_param_2_cycle/run.sh b/tests/custom/deprecated_permutations_basic/0004_given_permutation_in_param_2_cycle/run.sh similarity index 100% rename from tests/custom/permutations/basic/0004_given_permutation_in_param_2_cycle/run.sh rename to tests/custom/deprecated_permutations_basic/0004_given_permutation_in_param_2_cycle/run.sh diff --git a/tests/custom/permutations/basic/0004_given_permutation_in_param_2_cycle/stdout.expected b/tests/custom/deprecated_permutations_basic/0004_given_permutation_in_param_2_cycle/stdout.expected similarity index 100% rename from tests/custom/permutations/basic/0004_given_permutation_in_param_2_cycle/stdout.expected rename to tests/custom/deprecated_permutations_basic/0004_given_permutation_in_param_2_cycle/stdout.expected diff --git a/tests/custom/permutations/basic/0005_find_int_image_under_given_permutation/permutation.essence b/tests/custom/deprecated_permutations_basic/0005_find_int_image_under_given_permutation/permutation.essence similarity index 100% rename from tests/custom/permutations/basic/0005_find_int_image_under_given_permutation/permutation.essence rename to tests/custom/deprecated_permutations_basic/0005_find_int_image_under_given_permutation/permutation.essence diff --git a/tests/custom/permutations/basic/0005_find_int_image_under_given_permutation/permutation.param b/tests/custom/deprecated_permutations_basic/0005_find_int_image_under_given_permutation/permutation.param similarity index 100% rename from tests/custom/permutations/basic/0005_find_int_image_under_given_permutation/permutation.param rename to tests/custom/deprecated_permutations_basic/0005_find_int_image_under_given_permutation/permutation.param diff --git a/tests/custom/permutations/basic/0005_find_int_image_under_given_permutation/run.sh b/tests/custom/deprecated_permutations_basic/0005_find_int_image_under_given_permutation/run.sh similarity index 100% rename from tests/custom/permutations/basic/0005_find_int_image_under_given_permutation/run.sh rename to tests/custom/deprecated_permutations_basic/0005_find_int_image_under_given_permutation/run.sh diff --git a/tests/custom/permutations/basic/0005_find_int_image_under_given_permutation/stdout.expected b/tests/custom/deprecated_permutations_basic/0005_find_int_image_under_given_permutation/stdout.expected similarity index 100% rename from tests/custom/permutations/basic/0005_find_int_image_under_given_permutation/stdout.expected rename to tests/custom/deprecated_permutations_basic/0005_find_int_image_under_given_permutation/stdout.expected diff --git a/tests/custom/permutations/basic/0006_find_int_image_under_given_permutation/permutation.essence b/tests/custom/deprecated_permutations_basic/0006_find_int_image_under_given_permutation/permutation.essence similarity index 100% rename from tests/custom/permutations/basic/0006_find_int_image_under_given_permutation/permutation.essence rename to tests/custom/deprecated_permutations_basic/0006_find_int_image_under_given_permutation/permutation.essence diff --git a/tests/custom/permutations/basic/0006_find_int_image_under_given_permutation/permutation.param b/tests/custom/deprecated_permutations_basic/0006_find_int_image_under_given_permutation/permutation.param similarity index 100% rename from tests/custom/permutations/basic/0006_find_int_image_under_given_permutation/permutation.param rename to tests/custom/deprecated_permutations_basic/0006_find_int_image_under_given_permutation/permutation.param diff --git a/tests/custom/permutations/basic/0006_find_int_image_under_given_permutation/run.sh b/tests/custom/deprecated_permutations_basic/0006_find_int_image_under_given_permutation/run.sh similarity index 100% rename from tests/custom/permutations/basic/0006_find_int_image_under_given_permutation/run.sh rename to tests/custom/deprecated_permutations_basic/0006_find_int_image_under_given_permutation/run.sh diff --git a/tests/custom/permutations/basic/0006_find_int_image_under_given_permutation/stdout.expected b/tests/custom/deprecated_permutations_basic/0006_find_int_image_under_given_permutation/stdout.expected similarity index 100% rename from tests/custom/permutations/basic/0006_find_int_image_under_given_permutation/stdout.expected rename to tests/custom/deprecated_permutations_basic/0006_find_int_image_under_given_permutation/stdout.expected diff --git a/tests/custom/permutations/basic/0007_find_int_image_under_given_permutation/permutation.essence b/tests/custom/deprecated_permutations_basic/0007_find_int_image_under_given_permutation/permutation.essence similarity index 100% rename from tests/custom/permutations/basic/0007_find_int_image_under_given_permutation/permutation.essence rename to tests/custom/deprecated_permutations_basic/0007_find_int_image_under_given_permutation/permutation.essence diff --git a/tests/custom/permutations/basic/0007_find_int_image_under_given_permutation/permutation.param b/tests/custom/deprecated_permutations_basic/0007_find_int_image_under_given_permutation/permutation.param similarity index 100% rename from tests/custom/permutations/basic/0007_find_int_image_under_given_permutation/permutation.param rename to tests/custom/deprecated_permutations_basic/0007_find_int_image_under_given_permutation/permutation.param diff --git a/tests/custom/permutations/basic/0007_find_int_image_under_given_permutation/run.sh b/tests/custom/deprecated_permutations_basic/0007_find_int_image_under_given_permutation/run.sh similarity index 100% rename from tests/custom/permutations/basic/0007_find_int_image_under_given_permutation/run.sh rename to tests/custom/deprecated_permutations_basic/0007_find_int_image_under_given_permutation/run.sh diff --git a/tests/custom/permutations/basic/0007_find_int_image_under_given_permutation/stdout.expected b/tests/custom/deprecated_permutations_basic/0007_find_int_image_under_given_permutation/stdout.expected similarity index 100% rename from tests/custom/permutations/basic/0007_find_int_image_under_given_permutation/stdout.expected rename to tests/custom/deprecated_permutations_basic/0007_find_int_image_under_given_permutation/stdout.expected diff --git a/tests/custom/permutations/basic/0008_find_int_image_under_two_composed_given_permutations/permutation.essence b/tests/custom/deprecated_permutations_basic/0008_find_int_image_under_two_composed_given_permutations/permutation.essence similarity index 100% rename from tests/custom/permutations/basic/0008_find_int_image_under_two_composed_given_permutations/permutation.essence rename to tests/custom/deprecated_permutations_basic/0008_find_int_image_under_two_composed_given_permutations/permutation.essence diff --git a/tests/custom/permutations/basic/0008_find_int_image_under_two_composed_given_permutations/permutation.param b/tests/custom/deprecated_permutations_basic/0008_find_int_image_under_two_composed_given_permutations/permutation.param similarity index 100% rename from tests/custom/permutations/basic/0008_find_int_image_under_two_composed_given_permutations/permutation.param rename to tests/custom/deprecated_permutations_basic/0008_find_int_image_under_two_composed_given_permutations/permutation.param diff --git a/tests/custom/permutations/basic/0008_find_int_image_under_two_composed_given_permutations/run.sh b/tests/custom/deprecated_permutations_basic/0008_find_int_image_under_two_composed_given_permutations/run.sh similarity index 100% rename from tests/custom/permutations/basic/0008_find_int_image_under_two_composed_given_permutations/run.sh rename to tests/custom/deprecated_permutations_basic/0008_find_int_image_under_two_composed_given_permutations/run.sh diff --git a/tests/custom/permutations/basic/0008_find_int_image_under_two_composed_given_permutations/stdout.expected b/tests/custom/deprecated_permutations_basic/0008_find_int_image_under_two_composed_given_permutations/stdout.expected similarity index 100% rename from tests/custom/permutations/basic/0008_find_int_image_under_two_composed_given_permutations/stdout.expected rename to tests/custom/deprecated_permutations_basic/0008_find_int_image_under_two_composed_given_permutations/stdout.expected diff --git a/tests/custom/permutations/basic/0009_find_int_image_under_three_composed_given_permutations/permutation.essence b/tests/custom/deprecated_permutations_basic/0009_find_int_image_under_three_composed_given_permutations/permutation.essence similarity index 100% rename from tests/custom/permutations/basic/0009_find_int_image_under_three_composed_given_permutations/permutation.essence rename to tests/custom/deprecated_permutations_basic/0009_find_int_image_under_three_composed_given_permutations/permutation.essence diff --git a/tests/custom/permutations/basic/0009_find_int_image_under_three_composed_given_permutations/permutation.param b/tests/custom/deprecated_permutations_basic/0009_find_int_image_under_three_composed_given_permutations/permutation.param similarity index 100% rename from tests/custom/permutations/basic/0009_find_int_image_under_three_composed_given_permutations/permutation.param rename to tests/custom/deprecated_permutations_basic/0009_find_int_image_under_three_composed_given_permutations/permutation.param diff --git a/tests/custom/permutations/basic/0009_find_int_image_under_three_composed_given_permutations/run.sh b/tests/custom/deprecated_permutations_basic/0009_find_int_image_under_three_composed_given_permutations/run.sh similarity index 100% rename from tests/custom/permutations/basic/0009_find_int_image_under_three_composed_given_permutations/run.sh rename to tests/custom/deprecated_permutations_basic/0009_find_int_image_under_three_composed_given_permutations/run.sh diff --git a/tests/custom/permutations/basic/0009_find_int_image_under_three_composed_given_permutations/stdout.expected b/tests/custom/deprecated_permutations_basic/0009_find_int_image_under_three_composed_given_permutations/stdout.expected similarity index 100% rename from tests/custom/permutations/basic/0009_find_int_image_under_three_composed_given_permutations/stdout.expected rename to tests/custom/deprecated_permutations_basic/0009_find_int_image_under_three_composed_given_permutations/stdout.expected diff --git a/tests/custom/permutations/basic/0010_find_int_image_under_three_composed_given_permutations/permutation.essence b/tests/custom/deprecated_permutations_basic/0010_find_int_image_under_three_composed_given_permutations/permutation.essence similarity index 100% rename from tests/custom/permutations/basic/0010_find_int_image_under_three_composed_given_permutations/permutation.essence rename to tests/custom/deprecated_permutations_basic/0010_find_int_image_under_three_composed_given_permutations/permutation.essence diff --git a/tests/custom/permutations/basic/0010_find_int_image_under_three_composed_given_permutations/permutation.param b/tests/custom/deprecated_permutations_basic/0010_find_int_image_under_three_composed_given_permutations/permutation.param similarity index 100% rename from tests/custom/permutations/basic/0010_find_int_image_under_three_composed_given_permutations/permutation.param rename to tests/custom/deprecated_permutations_basic/0010_find_int_image_under_three_composed_given_permutations/permutation.param diff --git a/tests/custom/permutations/basic/0010_find_int_image_under_three_composed_given_permutations/run.sh b/tests/custom/deprecated_permutations_basic/0010_find_int_image_under_three_composed_given_permutations/run.sh similarity index 100% rename from tests/custom/permutations/basic/0010_find_int_image_under_three_composed_given_permutations/run.sh rename to tests/custom/deprecated_permutations_basic/0010_find_int_image_under_three_composed_given_permutations/run.sh diff --git a/tests/custom/permutations/basic/0010_find_int_image_under_three_composed_given_permutations/stdout.expected b/tests/custom/deprecated_permutations_basic/0010_find_int_image_under_three_composed_given_permutations/stdout.expected similarity index 100% rename from tests/custom/permutations/basic/0010_find_int_image_under_three_composed_given_permutations/stdout.expected rename to tests/custom/deprecated_permutations_basic/0010_find_int_image_under_three_composed_given_permutations/stdout.expected diff --git a/tests/custom/permutations/basic/0011_find_int_and_permutation_such_that_int_image_equals_const/permutation.essence b/tests/custom/deprecated_permutations_basic/0011_find_int_and_permutation_such_that_int_image_equals_const/permutation.essence similarity index 100% rename from tests/custom/permutations/basic/0011_find_int_and_permutation_such_that_int_image_equals_const/permutation.essence rename to tests/custom/deprecated_permutations_basic/0011_find_int_and_permutation_such_that_int_image_equals_const/permutation.essence diff --git a/tests/custom/permutations/basic/0011_find_int_and_permutation_such_that_int_image_equals_const/run.sh b/tests/custom/deprecated_permutations_basic/0011_find_int_and_permutation_such_that_int_image_equals_const/run.sh similarity index 100% rename from tests/custom/permutations/basic/0011_find_int_and_permutation_such_that_int_image_equals_const/run.sh rename to tests/custom/deprecated_permutations_basic/0011_find_int_and_permutation_such_that_int_image_equals_const/run.sh diff --git a/tests/custom/permutations/basic/0011_find_int_and_permutation_such_that_int_image_equals_const/stdout.expected b/tests/custom/deprecated_permutations_basic/0011_find_int_and_permutation_such_that_int_image_equals_const/stdout.expected similarity index 100% rename from tests/custom/permutations/basic/0011_find_int_and_permutation_such_that_int_image_equals_const/stdout.expected rename to tests/custom/deprecated_permutations_basic/0011_find_int_and_permutation_such_that_int_image_equals_const/stdout.expected diff --git a/tests/custom/permutations/basic/0012_find_int_and_permutation_such_that_int_image_equals_const/permutation.essence b/tests/custom/deprecated_permutations_basic/0012_find_int_and_permutation_such_that_int_image_equals_const/permutation.essence similarity index 100% rename from tests/custom/permutations/basic/0012_find_int_and_permutation_such_that_int_image_equals_const/permutation.essence rename to tests/custom/deprecated_permutations_basic/0012_find_int_and_permutation_such_that_int_image_equals_const/permutation.essence diff --git a/tests/custom/permutations/basic/0012_find_int_and_permutation_such_that_int_image_equals_const/run.sh b/tests/custom/deprecated_permutations_basic/0012_find_int_and_permutation_such_that_int_image_equals_const/run.sh similarity index 100% rename from tests/custom/permutations/basic/0012_find_int_and_permutation_such_that_int_image_equals_const/run.sh rename to tests/custom/deprecated_permutations_basic/0012_find_int_and_permutation_such_that_int_image_equals_const/run.sh diff --git a/tests/custom/permutations/basic/0012_find_int_and_permutation_such_that_int_image_equals_const/stdout.expected b/tests/custom/deprecated_permutations_basic/0012_find_int_and_permutation_such_that_int_image_equals_const/stdout.expected similarity index 100% rename from tests/custom/permutations/basic/0012_find_int_and_permutation_such_that_int_image_equals_const/stdout.expected rename to tests/custom/deprecated_permutations_basic/0012_find_int_and_permutation_such_that_int_image_equals_const/stdout.expected diff --git a/tests/custom/permutations/basic/0013_find_permutation_such_that_image_of_matrix1_equals_matrix2/permutation.essence b/tests/custom/deprecated_permutations_basic/0013_find_permutation_such_that_image_of_matrix1_equals_matrix2/permutation.essence similarity index 100% rename from tests/custom/permutations/basic/0013_find_permutation_such_that_image_of_matrix1_equals_matrix2/permutation.essence rename to tests/custom/deprecated_permutations_basic/0013_find_permutation_such_that_image_of_matrix1_equals_matrix2/permutation.essence diff --git a/tests/custom/permutations/basic/0013_find_permutation_such_that_image_of_matrix1_equals_matrix2/run.sh b/tests/custom/deprecated_permutations_basic/0013_find_permutation_such_that_image_of_matrix1_equals_matrix2/run.sh similarity index 100% rename from tests/custom/permutations/basic/0013_find_permutation_such_that_image_of_matrix1_equals_matrix2/run.sh rename to tests/custom/deprecated_permutations_basic/0013_find_permutation_such_that_image_of_matrix1_equals_matrix2/run.sh diff --git a/tests/custom/permutations/basic/0013_find_permutation_such_that_image_of_matrix1_equals_matrix2/stdout.expected b/tests/custom/deprecated_permutations_basic/0013_find_permutation_such_that_image_of_matrix1_equals_matrix2/stdout.expected similarity index 100% rename from tests/custom/permutations/basic/0013_find_permutation_such_that_image_of_matrix1_equals_matrix2/stdout.expected rename to tests/custom/deprecated_permutations_basic/0013_find_permutation_such_that_image_of_matrix1_equals_matrix2/stdout.expected diff --git a/tests/custom/permutations/basic/0014_find_matrix_such_that_swapping_any_index_pairs_becomes_lex_greater/permutation.essence b/tests/custom/deprecated_permutations_basic/0014_find_matrix_such_that_swapping_any_index_pairs_becomes_lex_greater/permutation.essence similarity index 100% rename from tests/custom/permutations/basic/0014_find_matrix_such_that_swapping_any_index_pairs_becomes_lex_greater/permutation.essence rename to tests/custom/deprecated_permutations_basic/0014_find_matrix_such_that_swapping_any_index_pairs_becomes_lex_greater/permutation.essence diff --git a/tests/custom/permutations/basic/0014_find_matrix_such_that_swapping_any_index_pairs_becomes_lex_greater/run.sh b/tests/custom/deprecated_permutations_basic/0014_find_matrix_such_that_swapping_any_index_pairs_becomes_lex_greater/run.sh similarity index 100% rename from tests/custom/permutations/basic/0014_find_matrix_such_that_swapping_any_index_pairs_becomes_lex_greater/run.sh rename to tests/custom/deprecated_permutations_basic/0014_find_matrix_such_that_swapping_any_index_pairs_becomes_lex_greater/run.sh diff --git a/tests/custom/permutations/basic/0014_find_matrix_such_that_swapping_any_index_pairs_becomes_lex_greater/stdout.expected b/tests/custom/deprecated_permutations_basic/0014_find_matrix_such_that_swapping_any_index_pairs_becomes_lex_greater/stdout.expected similarity index 100% rename from tests/custom/permutations/basic/0014_find_matrix_such_that_swapping_any_index_pairs_becomes_lex_greater/stdout.expected rename to tests/custom/deprecated_permutations_basic/0014_find_matrix_such_that_swapping_any_index_pairs_becomes_lex_greater/stdout.expected diff --git a/tests/custom/permutations/basic/0015_find_set_of_permuted_elements_of_matrix/permutation.essence b/tests/custom/deprecated_permutations_basic/0015_find_set_of_permuted_elements_of_matrix/permutation.essence similarity index 100% rename from tests/custom/permutations/basic/0015_find_set_of_permuted_elements_of_matrix/permutation.essence rename to tests/custom/deprecated_permutations_basic/0015_find_set_of_permuted_elements_of_matrix/permutation.essence diff --git a/tests/custom/permutations/basic/0015_find_set_of_permuted_elements_of_matrix/run.sh b/tests/custom/deprecated_permutations_basic/0015_find_set_of_permuted_elements_of_matrix/run.sh similarity index 100% rename from tests/custom/permutations/basic/0015_find_set_of_permuted_elements_of_matrix/run.sh rename to tests/custom/deprecated_permutations_basic/0015_find_set_of_permuted_elements_of_matrix/run.sh diff --git a/tests/custom/permutations/basic/0015_find_set_of_permuted_elements_of_matrix/stdout.expected b/tests/custom/deprecated_permutations_basic/0015_find_set_of_permuted_elements_of_matrix/stdout.expected similarity index 100% rename from tests/custom/permutations/basic/0015_find_set_of_permuted_elements_of_matrix/stdout.expected rename to tests/custom/deprecated_permutations_basic/0015_find_set_of_permuted_elements_of_matrix/stdout.expected diff --git a/tests/custom/permutations/basic/0016_find_permutation_such_that_image_is_identity_for_given_matrix/permutation.essence b/tests/custom/deprecated_permutations_basic/0016_find_permutation_such_that_image_is_identity_for_given_matrix/permutation.essence similarity index 100% rename from tests/custom/permutations/basic/0016_find_permutation_such_that_image_is_identity_for_given_matrix/permutation.essence rename to tests/custom/deprecated_permutations_basic/0016_find_permutation_such_that_image_is_identity_for_given_matrix/permutation.essence diff --git a/tests/custom/permutations/basic/0016_find_permutation_such_that_image_is_identity_for_given_matrix/run.sh b/tests/custom/deprecated_permutations_basic/0016_find_permutation_such_that_image_is_identity_for_given_matrix/run.sh similarity index 100% rename from tests/custom/permutations/basic/0016_find_permutation_such_that_image_is_identity_for_given_matrix/run.sh rename to tests/custom/deprecated_permutations_basic/0016_find_permutation_such_that_image_is_identity_for_given_matrix/run.sh diff --git a/tests/custom/permutations/basic/0016_find_permutation_such_that_image_is_identity_for_given_matrix/stdout.expected b/tests/custom/deprecated_permutations_basic/0016_find_permutation_such_that_image_is_identity_for_given_matrix/stdout.expected similarity index 100% rename from tests/custom/permutations/basic/0016_find_permutation_such_that_image_is_identity_for_given_matrix/stdout.expected rename to tests/custom/deprecated_permutations_basic/0016_find_permutation_such_that_image_is_identity_for_given_matrix/stdout.expected diff --git a/tests/custom/permutations/basic/0017_find_two_permutations_with_overlapping_domains_and_same_image_over_domain_union/permutation.essence b/tests/custom/deprecated_permutations_basic/0017_find_two_permutations_with_overlapping_domains_and_same_image_over_domain_union/permutation.essence similarity index 100% rename from tests/custom/permutations/basic/0017_find_two_permutations_with_overlapping_domains_and_same_image_over_domain_union/permutation.essence rename to tests/custom/deprecated_permutations_basic/0017_find_two_permutations_with_overlapping_domains_and_same_image_over_domain_union/permutation.essence diff --git a/tests/custom/permutations/basic/0017_find_two_permutations_with_overlapping_domains_and_same_image_over_domain_union/run.sh b/tests/custom/deprecated_permutations_basic/0017_find_two_permutations_with_overlapping_domains_and_same_image_over_domain_union/run.sh similarity index 100% rename from tests/custom/permutations/basic/0017_find_two_permutations_with_overlapping_domains_and_same_image_over_domain_union/run.sh rename to tests/custom/deprecated_permutations_basic/0017_find_two_permutations_with_overlapping_domains_and_same_image_over_domain_union/run.sh diff --git a/tests/custom/permutations/basic/0017_find_two_permutations_with_overlapping_domains_and_same_image_over_domain_union/stdout.expected b/tests/custom/deprecated_permutations_basic/0017_find_two_permutations_with_overlapping_domains_and_same_image_over_domain_union/stdout.expected similarity index 100% rename from tests/custom/permutations/basic/0017_find_two_permutations_with_overlapping_domains_and_same_image_over_domain_union/stdout.expected rename to tests/custom/deprecated_permutations_basic/0017_find_two_permutations_with_overlapping_domains_and_same_image_over_domain_union/stdout.expected diff --git a/tests/custom/permutations/basic/0018_find_matrix_lex_less_than_under_any_swap/permutation.essence b/tests/custom/deprecated_permutations_basic/0018_find_matrix_lex_less_than_under_any_swap/permutation.essence similarity index 100% rename from tests/custom/permutations/basic/0018_find_matrix_lex_less_than_under_any_swap/permutation.essence rename to tests/custom/deprecated_permutations_basic/0018_find_matrix_lex_less_than_under_any_swap/permutation.essence diff --git a/tests/custom/permutations/basic/0018_find_matrix_lex_less_than_under_any_swap/run.sh b/tests/custom/deprecated_permutations_basic/0018_find_matrix_lex_less_than_under_any_swap/run.sh similarity index 100% rename from tests/custom/permutations/basic/0018_find_matrix_lex_less_than_under_any_swap/run.sh rename to tests/custom/deprecated_permutations_basic/0018_find_matrix_lex_less_than_under_any_swap/run.sh diff --git a/tests/custom/permutations/basic/0018_find_matrix_lex_less_than_under_any_swap/stdout.expected b/tests/custom/deprecated_permutations_basic/0018_find_matrix_lex_less_than_under_any_swap/stdout.expected similarity index 100% rename from tests/custom/permutations/basic/0018_find_matrix_lex_less_than_under_any_swap/stdout.expected rename to tests/custom/deprecated_permutations_basic/0018_find_matrix_lex_less_than_under_any_swap/stdout.expected diff --git a/tests/custom/permutations/basic/0019_find_set_of_permutation_tuples_using_comprehension/permutation.essence b/tests/custom/deprecated_permutations_basic/0019_find_set_of_permutation_tuples_using_comprehension/permutation.essence similarity index 100% rename from tests/custom/permutations/basic/0019_find_set_of_permutation_tuples_using_comprehension/permutation.essence rename to tests/custom/deprecated_permutations_basic/0019_find_set_of_permutation_tuples_using_comprehension/permutation.essence diff --git a/tests/custom/permutations/basic/0019_find_set_of_permutation_tuples_using_comprehension/run.sh b/tests/custom/deprecated_permutations_basic/0019_find_set_of_permutation_tuples_using_comprehension/run.sh similarity index 100% rename from tests/custom/permutations/basic/0019_find_set_of_permutation_tuples_using_comprehension/run.sh rename to tests/custom/deprecated_permutations_basic/0019_find_set_of_permutation_tuples_using_comprehension/run.sh diff --git a/tests/custom/permutations/basic/0019_find_set_of_permutation_tuples_using_comprehension/stdout.expected b/tests/custom/deprecated_permutations_basic/0019_find_set_of_permutation_tuples_using_comprehension/stdout.expected similarity index 100% rename from tests/custom/permutations/basic/0019_find_set_of_permutation_tuples_using_comprehension/stdout.expected rename to tests/custom/deprecated_permutations_basic/0019_find_set_of_permutation_tuples_using_comprehension/stdout.expected diff --git a/tests/custom/permutations/basic/0020_find_permutation_inverse_using_comprehension/permutation.essence b/tests/custom/deprecated_permutations_basic/0020_find_permutation_inverse_using_comprehension/permutation.essence similarity index 100% rename from tests/custom/permutations/basic/0020_find_permutation_inverse_using_comprehension/permutation.essence rename to tests/custom/deprecated_permutations_basic/0020_find_permutation_inverse_using_comprehension/permutation.essence diff --git a/tests/custom/permutations/basic/0020_find_permutation_inverse_using_comprehension/run.sh b/tests/custom/deprecated_permutations_basic/0020_find_permutation_inverse_using_comprehension/run.sh similarity index 100% rename from tests/custom/permutations/basic/0020_find_permutation_inverse_using_comprehension/run.sh rename to tests/custom/deprecated_permutations_basic/0020_find_permutation_inverse_using_comprehension/run.sh diff --git a/tests/custom/permutations/basic/0020_find_permutation_inverse_using_comprehension/stdout.expected b/tests/custom/deprecated_permutations_basic/0020_find_permutation_inverse_using_comprehension/stdout.expected similarity index 100% rename from tests/custom/permutations/basic/0020_find_permutation_inverse_using_comprehension/stdout.expected rename to tests/custom/deprecated_permutations_basic/0020_find_permutation_inverse_using_comprehension/stdout.expected diff --git a/tests/custom/permutations/basic/0021_image_of_int_under_composition_of_two_given_permutations/permutation.essence b/tests/custom/deprecated_permutations_basic/0021_image_of_int_under_composition_of_two_given_permutations/permutation.essence similarity index 100% rename from tests/custom/permutations/basic/0021_image_of_int_under_composition_of_two_given_permutations/permutation.essence rename to tests/custom/deprecated_permutations_basic/0021_image_of_int_under_composition_of_two_given_permutations/permutation.essence diff --git a/tests/custom/permutations/basic/0021_image_of_int_under_composition_of_two_given_permutations/permutation.param b/tests/custom/deprecated_permutations_basic/0021_image_of_int_under_composition_of_two_given_permutations/permutation.param similarity index 100% rename from tests/custom/permutations/basic/0021_image_of_int_under_composition_of_two_given_permutations/permutation.param rename to tests/custom/deprecated_permutations_basic/0021_image_of_int_under_composition_of_two_given_permutations/permutation.param diff --git a/tests/custom/permutations/basic/0021_image_of_int_under_composition_of_two_given_permutations/run.sh b/tests/custom/deprecated_permutations_basic/0021_image_of_int_under_composition_of_two_given_permutations/run.sh similarity index 100% rename from tests/custom/permutations/basic/0021_image_of_int_under_composition_of_two_given_permutations/run.sh rename to tests/custom/deprecated_permutations_basic/0021_image_of_int_under_composition_of_two_given_permutations/run.sh diff --git a/tests/custom/permutations/basic/0021_image_of_int_under_composition_of_two_given_permutations/stdout.expected b/tests/custom/deprecated_permutations_basic/0021_image_of_int_under_composition_of_two_given_permutations/stdout.expected similarity index 100% rename from tests/custom/permutations/basic/0021_image_of_int_under_composition_of_two_given_permutations/stdout.expected rename to tests/custom/deprecated_permutations_basic/0021_image_of_int_under_composition_of_two_given_permutations/stdout.expected diff --git a/tests/custom/permutations/basic/0022_find_matrices_of_enum_x_y_such_that_y_lexless_than_x_under_any_index_swap/permutation.essence b/tests/custom/deprecated_permutations_basic/0022_find_matrices_of_enum_x_y_such_that_y_lexless_than_x_under_any_index_swap/permutation.essence similarity index 100% rename from tests/custom/permutations/basic/0022_find_matrices_of_enum_x_y_such_that_y_lexless_than_x_under_any_index_swap/permutation.essence rename to tests/custom/deprecated_permutations_basic/0022_find_matrices_of_enum_x_y_such_that_y_lexless_than_x_under_any_index_swap/permutation.essence diff --git a/tests/custom/permutations/basic/0022_find_matrices_of_enum_x_y_such_that_y_lexless_than_x_under_any_index_swap/permutation.param b/tests/custom/deprecated_permutations_basic/0022_find_matrices_of_enum_x_y_such_that_y_lexless_than_x_under_any_index_swap/permutation.param similarity index 100% rename from tests/custom/permutations/basic/0022_find_matrices_of_enum_x_y_such_that_y_lexless_than_x_under_any_index_swap/permutation.param rename to tests/custom/deprecated_permutations_basic/0022_find_matrices_of_enum_x_y_such_that_y_lexless_than_x_under_any_index_swap/permutation.param diff --git a/tests/custom/permutations/basic/0022_find_matrices_of_enum_x_y_such_that_y_lexless_than_x_under_any_index_swap/run.sh b/tests/custom/deprecated_permutations_basic/0022_find_matrices_of_enum_x_y_such_that_y_lexless_than_x_under_any_index_swap/run.sh similarity index 100% rename from tests/custom/permutations/basic/0022_find_matrices_of_enum_x_y_such_that_y_lexless_than_x_under_any_index_swap/run.sh rename to tests/custom/deprecated_permutations_basic/0022_find_matrices_of_enum_x_y_such_that_y_lexless_than_x_under_any_index_swap/run.sh diff --git a/tests/custom/permutations/basic/0022_find_matrices_of_enum_x_y_such_that_y_lexless_than_x_under_any_index_swap/stdout.expected b/tests/custom/deprecated_permutations_basic/0022_find_matrices_of_enum_x_y_such_that_y_lexless_than_x_under_any_index_swap/stdout.expected similarity index 100% rename from tests/custom/permutations/basic/0022_find_matrices_of_enum_x_y_such_that_y_lexless_than_x_under_any_index_swap/stdout.expected rename to tests/custom/deprecated_permutations_basic/0022_find_matrices_of_enum_x_y_such_that_y_lexless_than_x_under_any_index_swap/stdout.expected diff --git a/tests/custom/permutations/basic/0023_find_triples_x_y_such_that_y_lex_less_x_under_any_swap/permutation.essence b/tests/custom/deprecated_permutations_basic/0023_find_triples_x_y_such_that_y_lex_less_x_under_any_swap/permutation.essence similarity index 100% rename from tests/custom/permutations/basic/0023_find_triples_x_y_such_that_y_lex_less_x_under_any_swap/permutation.essence rename to tests/custom/deprecated_permutations_basic/0023_find_triples_x_y_such_that_y_lex_less_x_under_any_swap/permutation.essence diff --git a/tests/custom/permutations/basic/0023_find_triples_x_y_such_that_y_lex_less_x_under_any_swap/permutation.param b/tests/custom/deprecated_permutations_basic/0023_find_triples_x_y_such_that_y_lex_less_x_under_any_swap/permutation.param similarity index 100% rename from tests/custom/permutations/basic/0023_find_triples_x_y_such_that_y_lex_less_x_under_any_swap/permutation.param rename to tests/custom/deprecated_permutations_basic/0023_find_triples_x_y_such_that_y_lex_less_x_under_any_swap/permutation.param diff --git a/tests/custom/permutations/basic/0023_find_triples_x_y_such_that_y_lex_less_x_under_any_swap/run.sh b/tests/custom/deprecated_permutations_basic/0023_find_triples_x_y_such_that_y_lex_less_x_under_any_swap/run.sh similarity index 100% rename from tests/custom/permutations/basic/0023_find_triples_x_y_such_that_y_lex_less_x_under_any_swap/run.sh rename to tests/custom/deprecated_permutations_basic/0023_find_triples_x_y_such_that_y_lex_less_x_under_any_swap/run.sh diff --git a/tests/custom/permutations/basic/0023_find_triples_x_y_such_that_y_lex_less_x_under_any_swap/stdout.expected b/tests/custom/deprecated_permutations_basic/0023_find_triples_x_y_such_that_y_lex_less_x_under_any_swap/stdout.expected similarity index 100% rename from tests/custom/permutations/basic/0023_find_triples_x_y_such_that_y_lex_less_x_under_any_swap/stdout.expected rename to tests/custom/deprecated_permutations_basic/0023_find_triples_x_y_such_that_y_lex_less_x_under_any_swap/stdout.expected diff --git a/tests/custom/permutations/basic/0024_find_sets_x_y_such_that_y_lexless_x_under_any_swap/permutation.essence b/tests/custom/deprecated_permutations_basic/0024_find_sets_x_y_such_that_y_lexless_x_under_any_swap/permutation.essence similarity index 100% rename from tests/custom/permutations/basic/0024_find_sets_x_y_such_that_y_lexless_x_under_any_swap/permutation.essence rename to tests/custom/deprecated_permutations_basic/0024_find_sets_x_y_such_that_y_lexless_x_under_any_swap/permutation.essence diff --git a/tests/custom/permutations/basic/0024_find_sets_x_y_such_that_y_lexless_x_under_any_swap/permutation.param b/tests/custom/deprecated_permutations_basic/0024_find_sets_x_y_such_that_y_lexless_x_under_any_swap/permutation.param similarity index 100% rename from tests/custom/permutations/basic/0024_find_sets_x_y_such_that_y_lexless_x_under_any_swap/permutation.param rename to tests/custom/deprecated_permutations_basic/0024_find_sets_x_y_such_that_y_lexless_x_under_any_swap/permutation.param diff --git a/tests/custom/permutations/basic/0024_find_sets_x_y_such_that_y_lexless_x_under_any_swap/run.sh b/tests/custom/deprecated_permutations_basic/0024_find_sets_x_y_such_that_y_lexless_x_under_any_swap/run.sh similarity index 100% rename from tests/custom/permutations/basic/0024_find_sets_x_y_such_that_y_lexless_x_under_any_swap/run.sh rename to tests/custom/deprecated_permutations_basic/0024_find_sets_x_y_such_that_y_lexless_x_under_any_swap/run.sh diff --git a/tests/custom/permutations/basic/0024_find_sets_x_y_such_that_y_lexless_x_under_any_swap/stdout.expected b/tests/custom/deprecated_permutations_basic/0024_find_sets_x_y_such_that_y_lexless_x_under_any_swap/stdout.expected similarity index 100% rename from tests/custom/permutations/basic/0024_find_sets_x_y_such_that_y_lexless_x_under_any_swap/stdout.expected rename to tests/custom/deprecated_permutations_basic/0024_find_sets_x_y_such_that_y_lexless_x_under_any_swap/stdout.expected diff --git a/tests/custom/permutations/basic/0025_find_permutation_and_matrices_x_y_such_that_image_x_eq_y/permutation.essence b/tests/custom/deprecated_permutations_basic/0025_find_permutation_and_matrices_x_y_such_that_image_x_eq_y/permutation.essence similarity index 100% rename from tests/custom/permutations/basic/0025_find_permutation_and_matrices_x_y_such_that_image_x_eq_y/permutation.essence rename to tests/custom/deprecated_permutations_basic/0025_find_permutation_and_matrices_x_y_such_that_image_x_eq_y/permutation.essence diff --git a/tests/custom/permutations/basic/0025_find_permutation_and_matrices_x_y_such_that_image_x_eq_y/permutation.param b/tests/custom/deprecated_permutations_basic/0025_find_permutation_and_matrices_x_y_such_that_image_x_eq_y/permutation.param similarity index 100% rename from tests/custom/permutations/basic/0025_find_permutation_and_matrices_x_y_such_that_image_x_eq_y/permutation.param rename to tests/custom/deprecated_permutations_basic/0025_find_permutation_and_matrices_x_y_such_that_image_x_eq_y/permutation.param diff --git a/tests/custom/permutations/basic/0025_find_permutation_and_matrices_x_y_such_that_image_x_eq_y/run.sh b/tests/custom/deprecated_permutations_basic/0025_find_permutation_and_matrices_x_y_such_that_image_x_eq_y/run.sh similarity index 100% rename from tests/custom/permutations/basic/0025_find_permutation_and_matrices_x_y_such_that_image_x_eq_y/run.sh rename to tests/custom/deprecated_permutations_basic/0025_find_permutation_and_matrices_x_y_such_that_image_x_eq_y/run.sh diff --git a/tests/custom/permutations/basic/0025_find_permutation_and_matrices_x_y_such_that_image_x_eq_y/stdout.expected b/tests/custom/deprecated_permutations_basic/0025_find_permutation_and_matrices_x_y_such_that_image_x_eq_y/stdout.expected similarity index 100% rename from tests/custom/permutations/basic/0025_find_permutation_and_matrices_x_y_such_that_image_x_eq_y/stdout.expected rename to tests/custom/deprecated_permutations_basic/0025_find_permutation_and_matrices_x_y_such_that_image_x_eq_y/stdout.expected diff --git a/tests/custom/permutations/basic/0026_find_matrices_of_enums_x_y_such_that_y_image_x_under_p/permutation.essence b/tests/custom/deprecated_permutations_basic/0026_find_matrices_of_enums_x_y_such_that_y_image_x_under_p/permutation.essence similarity index 100% rename from tests/custom/permutations/basic/0026_find_matrices_of_enums_x_y_such_that_y_image_x_under_p/permutation.essence rename to tests/custom/deprecated_permutations_basic/0026_find_matrices_of_enums_x_y_such_that_y_image_x_under_p/permutation.essence diff --git a/tests/custom/permutations/basic/0026_find_matrices_of_enums_x_y_such_that_y_image_x_under_p/permutation.param b/tests/custom/deprecated_permutations_basic/0026_find_matrices_of_enums_x_y_such_that_y_image_x_under_p/permutation.param similarity index 100% rename from tests/custom/permutations/basic/0026_find_matrices_of_enums_x_y_such_that_y_image_x_under_p/permutation.param rename to tests/custom/deprecated_permutations_basic/0026_find_matrices_of_enums_x_y_such_that_y_image_x_under_p/permutation.param diff --git a/tests/custom/permutations/basic/0026_find_matrices_of_enums_x_y_such_that_y_image_x_under_p/run.sh b/tests/custom/deprecated_permutations_basic/0026_find_matrices_of_enums_x_y_such_that_y_image_x_under_p/run.sh similarity index 100% rename from tests/custom/permutations/basic/0026_find_matrices_of_enums_x_y_such_that_y_image_x_under_p/run.sh rename to tests/custom/deprecated_permutations_basic/0026_find_matrices_of_enums_x_y_such_that_y_image_x_under_p/run.sh diff --git a/tests/custom/permutations/basic/0026_find_matrices_of_enums_x_y_such_that_y_image_x_under_p/stdout.expected b/tests/custom/deprecated_permutations_basic/0026_find_matrices_of_enums_x_y_such_that_y_image_x_under_p/stdout.expected similarity index 100% rename from tests/custom/permutations/basic/0026_find_matrices_of_enums_x_y_such_that_y_image_x_under_p/stdout.expected rename to tests/custom/deprecated_permutations_basic/0026_find_matrices_of_enums_x_y_such_that_y_image_x_under_p/stdout.expected diff --git a/tests/custom/permutations/basic/0027_find_sets_of_enum_x_y_such_that_y_image_x_under_p/permutation.essence b/tests/custom/deprecated_permutations_basic/0027_find_sets_of_enum_x_y_such_that_y_image_x_under_p/permutation.essence similarity index 100% rename from tests/custom/permutations/basic/0027_find_sets_of_enum_x_y_such_that_y_image_x_under_p/permutation.essence rename to tests/custom/deprecated_permutations_basic/0027_find_sets_of_enum_x_y_such_that_y_image_x_under_p/permutation.essence diff --git a/tests/custom/permutations/basic/0027_find_sets_of_enum_x_y_such_that_y_image_x_under_p/run.sh b/tests/custom/deprecated_permutations_basic/0027_find_sets_of_enum_x_y_such_that_y_image_x_under_p/run.sh similarity index 100% rename from tests/custom/permutations/basic/0027_find_sets_of_enum_x_y_such_that_y_image_x_under_p/run.sh rename to tests/custom/deprecated_permutations_basic/0027_find_sets_of_enum_x_y_such_that_y_image_x_under_p/run.sh diff --git a/tests/custom/permutations/basic/0027_find_sets_of_enum_x_y_such_that_y_image_x_under_p/stdout.expected b/tests/custom/deprecated_permutations_basic/0027_find_sets_of_enum_x_y_such_that_y_image_x_under_p/stdout.expected similarity index 100% rename from tests/custom/permutations/basic/0027_find_sets_of_enum_x_y_such_that_y_image_x_under_p/stdout.expected rename to tests/custom/deprecated_permutations_basic/0027_find_sets_of_enum_x_y_such_that_y_image_x_under_p/stdout.expected diff --git a/tests/custom/permutations/basic/0028_find_sets_of_enum_x_y_such_that_y_image_x_under_p/permutation.essence b/tests/custom/deprecated_permutations_basic/0028_find_sets_of_enum_x_y_such_that_y_image_x_under_p/permutation.essence similarity index 100% rename from tests/custom/permutations/basic/0028_find_sets_of_enum_x_y_such_that_y_image_x_under_p/permutation.essence rename to tests/custom/deprecated_permutations_basic/0028_find_sets_of_enum_x_y_such_that_y_image_x_under_p/permutation.essence diff --git a/tests/custom/permutations/basic/0028_find_sets_of_enum_x_y_such_that_y_image_x_under_p/run.sh b/tests/custom/deprecated_permutations_basic/0028_find_sets_of_enum_x_y_such_that_y_image_x_under_p/run.sh similarity index 100% rename from tests/custom/permutations/basic/0028_find_sets_of_enum_x_y_such_that_y_image_x_under_p/run.sh rename to tests/custom/deprecated_permutations_basic/0028_find_sets_of_enum_x_y_such_that_y_image_x_under_p/run.sh diff --git a/tests/custom/permutations/basic/0028_find_sets_of_enum_x_y_such_that_y_image_x_under_p/stdout.expected b/tests/custom/deprecated_permutations_basic/0028_find_sets_of_enum_x_y_such_that_y_image_x_under_p/stdout.expected similarity index 100% rename from tests/custom/permutations/basic/0028_find_sets_of_enum_x_y_such_that_y_image_x_under_p/stdout.expected rename to tests/custom/deprecated_permutations_basic/0028_find_sets_of_enum_x_y_such_that_y_image_x_under_p/stdout.expected diff --git a/tests/custom/permutations/basic/0029_find_relations_x_y_such_that_y_image_x_under_p/log b/tests/custom/deprecated_permutations_basic/0029_find_relations_x_y_such_that_y_image_x_under_p/log similarity index 100% rename from tests/custom/permutations/basic/0029_find_relations_x_y_such_that_y_image_x_under_p/log rename to tests/custom/deprecated_permutations_basic/0029_find_relations_x_y_such_that_y_image_x_under_p/log diff --git a/tests/custom/permutations/basic/0029_find_relations_x_y_such_that_y_image_x_under_p/log-lite b/tests/custom/deprecated_permutations_basic/0029_find_relations_x_y_such_that_y_image_x_under_p/log-lite similarity index 100% rename from tests/custom/permutations/basic/0029_find_relations_x_y_such_that_y_image_x_under_p/log-lite rename to tests/custom/deprecated_permutations_basic/0029_find_relations_x_y_such_that_y_image_x_under_p/log-lite diff --git a/tests/custom/permutations/basic/0029_find_relations_x_y_such_that_y_image_x_under_p/permutation.essence b/tests/custom/deprecated_permutations_basic/0029_find_relations_x_y_such_that_y_image_x_under_p/permutation.essence similarity index 100% rename from tests/custom/permutations/basic/0029_find_relations_x_y_such_that_y_image_x_under_p/permutation.essence rename to tests/custom/deprecated_permutations_basic/0029_find_relations_x_y_such_that_y_image_x_under_p/permutation.essence diff --git a/tests/custom/permutations/basic/0029_find_relations_x_y_such_that_y_image_x_under_p/run.sh b/tests/custom/deprecated_permutations_basic/0029_find_relations_x_y_such_that_y_image_x_under_p/run.sh similarity index 100% rename from tests/custom/permutations/basic/0029_find_relations_x_y_such_that_y_image_x_under_p/run.sh rename to tests/custom/deprecated_permutations_basic/0029_find_relations_x_y_such_that_y_image_x_under_p/run.sh diff --git a/tests/custom/permutations/basic/0030_find_permutation_equal_given_permutation/permutation.essence b/tests/custom/deprecated_permutations_basic/0030_find_permutation_equal_given_permutation/permutation.essence similarity index 100% rename from tests/custom/permutations/basic/0030_find_permutation_equal_given_permutation/permutation.essence rename to tests/custom/deprecated_permutations_basic/0030_find_permutation_equal_given_permutation/permutation.essence diff --git a/tests/custom/permutations/basic/0030_find_permutation_equal_given_permutation/permutation.param b/tests/custom/deprecated_permutations_basic/0030_find_permutation_equal_given_permutation/permutation.param similarity index 100% rename from tests/custom/permutations/basic/0030_find_permutation_equal_given_permutation/permutation.param rename to tests/custom/deprecated_permutations_basic/0030_find_permutation_equal_given_permutation/permutation.param diff --git a/tests/custom/permutations/basic/0030_find_permutation_equal_given_permutation/run.sh b/tests/custom/deprecated_permutations_basic/0030_find_permutation_equal_given_permutation/run.sh similarity index 100% rename from tests/custom/permutations/basic/0030_find_permutation_equal_given_permutation/run.sh rename to tests/custom/deprecated_permutations_basic/0030_find_permutation_equal_given_permutation/run.sh diff --git a/tests/custom/permutations/basic/0031_find_matrix_lexless_indices_swapped_in_comprehension/permutation.essence b/tests/custom/deprecated_permutations_basic/0031_find_matrix_lexless_indices_swapped_in_comprehension/permutation.essence similarity index 100% rename from tests/custom/permutations/basic/0031_find_matrix_lexless_indices_swapped_in_comprehension/permutation.essence rename to tests/custom/deprecated_permutations_basic/0031_find_matrix_lexless_indices_swapped_in_comprehension/permutation.essence diff --git a/tests/custom/permutations/basic/0031_find_matrix_lexless_indices_swapped_in_comprehension/permutation.param b/tests/custom/deprecated_permutations_basic/0031_find_matrix_lexless_indices_swapped_in_comprehension/permutation.param similarity index 100% rename from tests/custom/permutations/basic/0031_find_matrix_lexless_indices_swapped_in_comprehension/permutation.param rename to tests/custom/deprecated_permutations_basic/0031_find_matrix_lexless_indices_swapped_in_comprehension/permutation.param diff --git a/tests/custom/permutations/basic/0031_find_matrix_lexless_indices_swapped_in_comprehension/run.sh b/tests/custom/deprecated_permutations_basic/0031_find_matrix_lexless_indices_swapped_in_comprehension/run.sh similarity index 100% rename from tests/custom/permutations/basic/0031_find_matrix_lexless_indices_swapped_in_comprehension/run.sh rename to tests/custom/deprecated_permutations_basic/0031_find_matrix_lexless_indices_swapped_in_comprehension/run.sh diff --git a/tests/custom/permutations/basic/0032_find_sets_of_ints_such_that_tuple_of_sets_lexless_any_int_swapped_tuple/permutation.essence b/tests/custom/deprecated_permutations_basic/0032_find_sets_of_ints_such_that_tuple_of_sets_lexless_any_int_swapped_tuple/permutation.essence similarity index 100% rename from tests/custom/permutations/basic/0032_find_sets_of_ints_such_that_tuple_of_sets_lexless_any_int_swapped_tuple/permutation.essence rename to tests/custom/deprecated_permutations_basic/0032_find_sets_of_ints_such_that_tuple_of_sets_lexless_any_int_swapped_tuple/permutation.essence diff --git a/tests/custom/permutations/basic/0032_find_sets_of_ints_such_that_tuple_of_sets_lexless_any_int_swapped_tuple/permutation.param b/tests/custom/deprecated_permutations_basic/0032_find_sets_of_ints_such_that_tuple_of_sets_lexless_any_int_swapped_tuple/permutation.param similarity index 100% rename from tests/custom/permutations/basic/0032_find_sets_of_ints_such_that_tuple_of_sets_lexless_any_int_swapped_tuple/permutation.param rename to tests/custom/deprecated_permutations_basic/0032_find_sets_of_ints_such_that_tuple_of_sets_lexless_any_int_swapped_tuple/permutation.param diff --git a/tests/custom/permutations/basic/0032_find_sets_of_ints_such_that_tuple_of_sets_lexless_any_int_swapped_tuple/run.sh b/tests/custom/deprecated_permutations_basic/0032_find_sets_of_ints_such_that_tuple_of_sets_lexless_any_int_swapped_tuple/run.sh similarity index 100% rename from tests/custom/permutations/basic/0032_find_sets_of_ints_such_that_tuple_of_sets_lexless_any_int_swapped_tuple/run.sh rename to tests/custom/deprecated_permutations_basic/0032_find_sets_of_ints_such_that_tuple_of_sets_lexless_any_int_swapped_tuple/run.sh diff --git a/tests/custom/permutations/basic/0033_find_matrixes_of_enum_such_that_tuple_of_matrices_lexless_any_int_swapped_tuple/permutation.essence b/tests/custom/deprecated_permutations_basic/0033_find_matrixes_of_enum_such_that_tuple_of_matrices_lexless_any_int_swapped_tuple/permutation.essence similarity index 100% rename from tests/custom/permutations/basic/0033_find_matrixes_of_enum_such_that_tuple_of_matrices_lexless_any_int_swapped_tuple/permutation.essence rename to tests/custom/deprecated_permutations_basic/0033_find_matrixes_of_enum_such_that_tuple_of_matrices_lexless_any_int_swapped_tuple/permutation.essence diff --git a/tests/custom/permutations/basic/0033_find_matrixes_of_enum_such_that_tuple_of_matrices_lexless_any_int_swapped_tuple/permutation.param b/tests/custom/deprecated_permutations_basic/0033_find_matrixes_of_enum_such_that_tuple_of_matrices_lexless_any_int_swapped_tuple/permutation.param similarity index 100% rename from tests/custom/permutations/basic/0033_find_matrixes_of_enum_such_that_tuple_of_matrices_lexless_any_int_swapped_tuple/permutation.param rename to tests/custom/deprecated_permutations_basic/0033_find_matrixes_of_enum_such_that_tuple_of_matrices_lexless_any_int_swapped_tuple/permutation.param diff --git a/tests/custom/permutations/basic/0033_find_matrixes_of_enum_such_that_tuple_of_matrices_lexless_any_int_swapped_tuple/run.sh b/tests/custom/deprecated_permutations_basic/0033_find_matrixes_of_enum_such_that_tuple_of_matrices_lexless_any_int_swapped_tuple/run.sh similarity index 100% rename from tests/custom/permutations/basic/0033_find_matrixes_of_enum_such_that_tuple_of_matrices_lexless_any_int_swapped_tuple/run.sh rename to tests/custom/deprecated_permutations_basic/0033_find_matrixes_of_enum_such_that_tuple_of_matrices_lexless_any_int_swapped_tuple/run.sh diff --git a/tests/custom/permutations/basic/0033_find_matrixes_of_enum_such_that_tuple_of_matrices_lexless_any_int_swapped_tuple/stdout.expected b/tests/custom/deprecated_permutations_basic/0033_find_matrixes_of_enum_such_that_tuple_of_matrices_lexless_any_int_swapped_tuple/stdout.expected similarity index 100% rename from tests/custom/permutations/basic/0033_find_matrixes_of_enum_such_that_tuple_of_matrices_lexless_any_int_swapped_tuple/stdout.expected rename to tests/custom/deprecated_permutations_basic/0033_find_matrixes_of_enum_such_that_tuple_of_matrices_lexless_any_int_swapped_tuple/stdout.expected diff --git a/tests/custom/permutations/basic/0034_image_of_empty_permutation/permutation.essence b/tests/custom/deprecated_permutations_basic/0034_image_of_empty_permutation/permutation.essence similarity index 100% rename from tests/custom/permutations/basic/0034_image_of_empty_permutation/permutation.essence rename to tests/custom/deprecated_permutations_basic/0034_image_of_empty_permutation/permutation.essence diff --git a/tests/custom/permutations/basic/0034_image_of_empty_permutation/permutation.param b/tests/custom/deprecated_permutations_basic/0034_image_of_empty_permutation/permutation.param similarity index 100% rename from tests/custom/permutations/basic/0034_image_of_empty_permutation/permutation.param rename to tests/custom/deprecated_permutations_basic/0034_image_of_empty_permutation/permutation.param diff --git a/tests/custom/permutations/basic/0034_image_of_empty_permutation/run.sh b/tests/custom/deprecated_permutations_basic/0034_image_of_empty_permutation/run.sh similarity index 100% rename from tests/custom/permutations/basic/0034_image_of_empty_permutation/run.sh rename to tests/custom/deprecated_permutations_basic/0034_image_of_empty_permutation/run.sh diff --git a/tests/custom/permutations/basic/0035_permutation_of_enum_is_identity_for_integers/permutation.essence b/tests/custom/deprecated_permutations_basic/0035_permutation_of_enum_is_identity_for_integers/permutation.essence similarity index 100% rename from tests/custom/permutations/basic/0035_permutation_of_enum_is_identity_for_integers/permutation.essence rename to tests/custom/deprecated_permutations_basic/0035_permutation_of_enum_is_identity_for_integers/permutation.essence diff --git a/tests/custom/permutations/basic/0035_permutation_of_enum_is_identity_for_integers/permutation.param b/tests/custom/deprecated_permutations_basic/0035_permutation_of_enum_is_identity_for_integers/permutation.param similarity index 100% rename from tests/custom/permutations/basic/0035_permutation_of_enum_is_identity_for_integers/permutation.param rename to tests/custom/deprecated_permutations_basic/0035_permutation_of_enum_is_identity_for_integers/permutation.param diff --git a/tests/custom/permutations/basic/0035_permutation_of_enum_is_identity_for_integers/run.sh b/tests/custom/deprecated_permutations_basic/0035_permutation_of_enum_is_identity_for_integers/run.sh similarity index 100% rename from tests/custom/permutations/basic/0035_permutation_of_enum_is_identity_for_integers/run.sh rename to tests/custom/deprecated_permutations_basic/0035_permutation_of_enum_is_identity_for_integers/run.sh diff --git a/tests/custom/permutations/basic/0035_permutation_of_enum_is_identity_for_integers/stdout.expected b/tests/custom/deprecated_permutations_basic/0035_permutation_of_enum_is_identity_for_integers/stdout.expected similarity index 100% rename from tests/custom/permutations/basic/0035_permutation_of_enum_is_identity_for_integers/stdout.expected rename to tests/custom/deprecated_permutations_basic/0035_permutation_of_enum_is_identity_for_integers/stdout.expected diff --git a/tests/custom/permutations/basic/0036_big_test_of_enums_in_matrices/permutation.essence b/tests/custom/deprecated_permutations_basic/0036_big_test_of_enums_in_matrices/permutation.essence similarity index 100% rename from tests/custom/permutations/basic/0036_big_test_of_enums_in_matrices/permutation.essence rename to tests/custom/deprecated_permutations_basic/0036_big_test_of_enums_in_matrices/permutation.essence diff --git a/tests/custom/permutations/basic/0036_big_test_of_enums_in_matrices/run.sh b/tests/custom/deprecated_permutations_basic/0036_big_test_of_enums_in_matrices/run.sh similarity index 100% rename from tests/custom/permutations/basic/0036_big_test_of_enums_in_matrices/run.sh rename to tests/custom/deprecated_permutations_basic/0036_big_test_of_enums_in_matrices/run.sh diff --git a/tests/custom/permutations/basic/0036_big_test_of_enums_in_matrices/stdout.expected b/tests/custom/deprecated_permutations_basic/0036_big_test_of_enums_in_matrices/stdout.expected similarity index 100% rename from tests/custom/permutations/basic/0036_big_test_of_enums_in_matrices/stdout.expected rename to tests/custom/deprecated_permutations_basic/0036_big_test_of_enums_in_matrices/stdout.expected diff --git a/tests/custom/permutations/basic/0037_matrices_of_enums_indexed_by_enums/permutation.essence b/tests/custom/deprecated_permutations_basic/0037_matrices_of_enums_indexed_by_enums/permutation.essence similarity index 100% rename from tests/custom/permutations/basic/0037_matrices_of_enums_indexed_by_enums/permutation.essence rename to tests/custom/deprecated_permutations_basic/0037_matrices_of_enums_indexed_by_enums/permutation.essence diff --git a/tests/custom/permutations/basic/0037_matrices_of_enums_indexed_by_enums/run.sh b/tests/custom/deprecated_permutations_basic/0037_matrices_of_enums_indexed_by_enums/run.sh similarity index 100% rename from tests/custom/permutations/basic/0037_matrices_of_enums_indexed_by_enums/run.sh rename to tests/custom/deprecated_permutations_basic/0037_matrices_of_enums_indexed_by_enums/run.sh diff --git a/tests/custom/permutations/basic/0037_matrices_of_enums_indexed_by_enums/stdout.expected b/tests/custom/deprecated_permutations_basic/0037_matrices_of_enums_indexed_by_enums/stdout.expected similarity index 100% rename from tests/custom/permutations/basic/0037_matrices_of_enums_indexed_by_enums/stdout.expected rename to tests/custom/deprecated_permutations_basic/0037_matrices_of_enums_indexed_by_enums/stdout.expected diff --git a/tests/custom/permutations/basic/0038_matricies_of_tuples_of_enums_indexed_by_enums/permutation.essence b/tests/custom/deprecated_permutations_basic/0038_matricies_of_tuples_of_enums_indexed_by_enums/permutation.essence similarity index 100% rename from tests/custom/permutations/basic/0038_matricies_of_tuples_of_enums_indexed_by_enums/permutation.essence rename to tests/custom/deprecated_permutations_basic/0038_matricies_of_tuples_of_enums_indexed_by_enums/permutation.essence diff --git a/tests/custom/permutations/basic/0038_matricies_of_tuples_of_enums_indexed_by_enums/run.sh b/tests/custom/deprecated_permutations_basic/0038_matricies_of_tuples_of_enums_indexed_by_enums/run.sh similarity index 100% rename from tests/custom/permutations/basic/0038_matricies_of_tuples_of_enums_indexed_by_enums/run.sh rename to tests/custom/deprecated_permutations_basic/0038_matricies_of_tuples_of_enums_indexed_by_enums/run.sh diff --git a/tests/custom/permutations/basic/0038_matricies_of_tuples_of_enums_indexed_by_enums/stdout.expected b/tests/custom/deprecated_permutations_basic/0038_matricies_of_tuples_of_enums_indexed_by_enums/stdout.expected similarity index 100% rename from tests/custom/permutations/basic/0038_matricies_of_tuples_of_enums_indexed_by_enums/stdout.expected rename to tests/custom/deprecated_permutations_basic/0038_matricies_of_tuples_of_enums_indexed_by_enums/stdout.expected diff --git a/tests/custom/permutations/basic/0039_toSet_on_given_permutation_of_enum/permutation.essence b/tests/custom/deprecated_permutations_basic/0039_toSet_on_given_permutation_of_enum/permutation.essence similarity index 100% rename from tests/custom/permutations/basic/0039_toSet_on_given_permutation_of_enum/permutation.essence rename to tests/custom/deprecated_permutations_basic/0039_toSet_on_given_permutation_of_enum/permutation.essence diff --git a/tests/custom/permutations/basic/0039_toSet_on_given_permutation_of_enum/run.sh b/tests/custom/deprecated_permutations_basic/0039_toSet_on_given_permutation_of_enum/run.sh similarity index 100% rename from tests/custom/permutations/basic/0039_toSet_on_given_permutation_of_enum/run.sh rename to tests/custom/deprecated_permutations_basic/0039_toSet_on_given_permutation_of_enum/run.sh diff --git a/tests/custom/permutations/basic/0040_toSet_on_given_permutation_of_int/permutation.essence b/tests/custom/deprecated_permutations_basic/0040_toSet_on_given_permutation_of_int/permutation.essence similarity index 100% rename from tests/custom/permutations/basic/0040_toSet_on_given_permutation_of_int/permutation.essence rename to tests/custom/deprecated_permutations_basic/0040_toSet_on_given_permutation_of_int/permutation.essence diff --git a/tests/custom/permutations/basic/0040_toSet_on_given_permutation_of_int/run.sh b/tests/custom/deprecated_permutations_basic/0040_toSet_on_given_permutation_of_int/run.sh similarity index 100% rename from tests/custom/permutations/basic/0040_toSet_on_given_permutation_of_int/run.sh rename to tests/custom/deprecated_permutations_basic/0040_toSet_on_given_permutation_of_int/run.sh diff --git a/tests/custom/permutations/basic/0040_toSet_on_given_permutation_of_int/stdout.expected b/tests/custom/deprecated_permutations_basic/0040_toSet_on_given_permutation_of_int/stdout.expected similarity index 100% rename from tests/custom/permutations/basic/0040_toSet_on_given_permutation_of_int/stdout.expected rename to tests/custom/deprecated_permutations_basic/0040_toSet_on_given_permutation_of_int/stdout.expected diff --git a/tests/custom/permutations/basic/0041_toSet_on_found_permutation_of_enum/permutation.essence b/tests/custom/deprecated_permutations_basic/0041_toSet_on_found_permutation_of_enum/permutation.essence similarity index 100% rename from tests/custom/permutations/basic/0041_toSet_on_found_permutation_of_enum/permutation.essence rename to tests/custom/deprecated_permutations_basic/0041_toSet_on_found_permutation_of_enum/permutation.essence diff --git a/tests/custom/permutations/basic/0041_toSet_on_found_permutation_of_enum/run.sh b/tests/custom/deprecated_permutations_basic/0041_toSet_on_found_permutation_of_enum/run.sh similarity index 100% rename from tests/custom/permutations/basic/0041_toSet_on_found_permutation_of_enum/run.sh rename to tests/custom/deprecated_permutations_basic/0041_toSet_on_found_permutation_of_enum/run.sh diff --git a/tests/custom/permutations/basic/0042_toSet_on_found_permutation_of_int/permutation.essence b/tests/custom/deprecated_permutations_basic/0042_toSet_on_found_permutation_of_int/permutation.essence similarity index 100% rename from tests/custom/permutations/basic/0042_toSet_on_found_permutation_of_int/permutation.essence rename to tests/custom/deprecated_permutations_basic/0042_toSet_on_found_permutation_of_int/permutation.essence diff --git a/tests/custom/permutations/basic/0042_toSet_on_found_permutation_of_int/run.sh b/tests/custom/deprecated_permutations_basic/0042_toSet_on_found_permutation_of_int/run.sh similarity index 100% rename from tests/custom/permutations/basic/0042_toSet_on_found_permutation_of_int/run.sh rename to tests/custom/deprecated_permutations_basic/0042_toSet_on_found_permutation_of_int/run.sh diff --git a/tests/custom/permutations/basic/0043_inverse_on_given_permutation_of_int/permutation.essence b/tests/custom/deprecated_permutations_basic/0043_inverse_on_given_permutation_of_int/permutation.essence similarity index 100% rename from tests/custom/permutations/basic/0043_inverse_on_given_permutation_of_int/permutation.essence rename to tests/custom/deprecated_permutations_basic/0043_inverse_on_given_permutation_of_int/permutation.essence diff --git a/tests/custom/permutations/basic/0043_inverse_on_given_permutation_of_int/run.sh b/tests/custom/deprecated_permutations_basic/0043_inverse_on_given_permutation_of_int/run.sh similarity index 100% rename from tests/custom/permutations/basic/0043_inverse_on_given_permutation_of_int/run.sh rename to tests/custom/deprecated_permutations_basic/0043_inverse_on_given_permutation_of_int/run.sh diff --git a/tests/custom/permutations/basic/runthese.sh b/tests/custom/deprecated_permutations_basic/runthese.sh similarity index 100% rename from tests/custom/permutations/basic/runthese.sh rename to tests/custom/deprecated_permutations_basic/runthese.sh diff --git a/tests/custom/permutations/03_generators/0001_given_permutation_in_generator/permutation.essence b/tests/custom/permutations/03_generators/0001_given_permutation_in_generator/permutation.essence new file mode 100644 index 0000000000..685d9a113d --- /dev/null +++ b/tests/custom/permutations/03_generators/0001_given_permutation_in_generator/permutation.essence @@ -0,0 +1,11 @@ +letting n be 4 + +given p : permutation of int(1..n) +find s : set of (int(1..4),int(1..4)) + +such that + and([e in s | e <- p]) + + + + diff --git a/tests/custom/permutations/03_generators/0001_given_permutation_in_generator/permutation.param b/tests/custom/permutations/03_generators/0001_given_permutation_in_generator/permutation.param new file mode 100644 index 0000000000..8a8c516801 --- /dev/null +++ b/tests/custom/permutations/03_generators/0001_given_permutation_in_generator/permutation.param @@ -0,0 +1 @@ +letting p be permutation((1,3,4)) diff --git a/tests/custom/permutations/03_generators/0001_given_permutation_in_generator/run.sh b/tests/custom/permutations/03_generators/0001_given_permutation_in_generator/run.sh new file mode 100755 index 0000000000..9dc67e67f5 --- /dev/null +++ b/tests/custom/permutations/03_generators/0001_given_permutation_in_generator/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence *.param +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/03_generators/0001_given_permutation_in_generator/stdout.expected b/tests/custom/permutations/03_generators/0001_given_permutation_in_generator/stdout.expected new file mode 100644 index 0000000000..1a25417044 --- /dev/null +++ b/tests/custom/permutations/03_generators/0001_given_permutation_in_generator/stdout.expected @@ -0,0 +1,13 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime permutation.param +Copying solution to: permutation-permutation.solution +language Essence 1.3 + +letting s be {(1, 3), (3, 4), (4, 1)} +$ Visualisation for s +$ 1 3 +$ 3 4 +$ 4 1 + diff --git a/tests/custom/permutations/03_generators/0002_letting_permutation_in_generator/permutation.essence b/tests/custom/permutations/03_generators/0002_letting_permutation_in_generator/permutation.essence new file mode 100644 index 0000000000..3b3a5d2682 --- /dev/null +++ b/tests/custom/permutations/03_generators/0002_letting_permutation_in_generator/permutation.essence @@ -0,0 +1,11 @@ +letting n be 4 + +letting p be permutation((1,3,4)) +find s : set of (int(1..4),int(1..4)) + +such that + and([e in s | e <- p]) + + + + diff --git a/tests/custom/permutations/03_generators/0002_letting_permutation_in_generator/run.sh b/tests/custom/permutations/03_generators/0002_letting_permutation_in_generator/run.sh new file mode 100755 index 0000000000..b4899d6266 --- /dev/null +++ b/tests/custom/permutations/03_generators/0002_letting_permutation_in_generator/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/03_generators/0002_letting_permutation_in_generator/stdout.expected b/tests/custom/permutations/03_generators/0002_letting_permutation_in_generator/stdout.expected new file mode 100644 index 0000000000..17316ee027 --- /dev/null +++ b/tests/custom/permutations/03_generators/0002_letting_permutation_in_generator/stdout.expected @@ -0,0 +1,13 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Copying solution to: permutation.solution +language Essence 1.3 + +letting s be {(1, 3), (3, 4), (4, 1)} +$ Visualisation for s +$ 1 3 +$ 3 4 +$ 4 1 + diff --git a/tests/custom/permutations/03_generators/0003_find_permutation_in_generator/permutation.essence b/tests/custom/permutations/03_generators/0003_find_permutation_in_generator/permutation.essence new file mode 100644 index 0000000000..33a9d426d3 --- /dev/null +++ b/tests/custom/permutations/03_generators/0003_find_permutation_in_generator/permutation.essence @@ -0,0 +1,9 @@ +find p : permutation (size 3) of int(1..4) +find s : set (size 3) of (int(1..4),int(1..4)) + +such that + and([e in s | e <- p]) + + + + diff --git a/tests/custom/permutations/03_generators/0003_find_permutation_in_generator/run.sh b/tests/custom/permutations/03_generators/0003_find_permutation_in_generator/run.sh new file mode 100755 index 0000000000..de361d4354 --- /dev/null +++ b/tests/custom/permutations/03_generators/0003_find_permutation_in_generator/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence --number-of-solutions=40 +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/03_generators/0003_find_permutation_in_generator/stdout.expected b/tests/custom/permutations/03_generators/0003_find_permutation_in_generator/stdout.expected new file mode 100644 index 0000000000..68a640a558 --- /dev/null +++ b/tests/custom/permutations/03_generators/0003_find_permutation_in_generator/stdout.expected @@ -0,0 +1,84 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Copying solution to: permutation-000001.solution +Copying solution to: permutation-000002.solution +Copying solution to: permutation-000003.solution +Copying solution to: permutation-000004.solution +Copying solution to: permutation-000005.solution +Copying solution to: permutation-000006.solution +Copying solution to: permutation-000007.solution +Copying solution to: permutation-000008.solution +language Essence 1.3 + +letting p be permutation((2, 3, 4)) +letting s be {(2, 3), (3, 4), (4, 2)} +$ Visualisation for s +$ 2 3 +$ 3 4 +$ 4 2 + +language Essence 1.3 + +letting p be permutation((2, 4, 3)) +letting s be {(2, 4), (3, 2), (4, 3)} +$ Visualisation for s +$ 2 4 +$ 3 2 +$ 4 3 + +language Essence 1.3 + +letting p be permutation((1, 2, 3)) +letting s be {(1, 2), (2, 3), (3, 1)} +$ Visualisation for s +$ 1 2 +$ 2 3 +$ 3 1 + +language Essence 1.3 + +letting p be permutation((1, 2, 4)) +letting s be {(1, 2), (2, 4), (4, 1)} +$ Visualisation for s +$ 1 2 +$ 2 4 +$ 4 1 + +language Essence 1.3 + +letting p be permutation((1, 3, 2)) +letting s be {(1, 3), (2, 1), (3, 2)} +$ Visualisation for s +$ 1 3 +$ 2 1 +$ 3 2 + +language Essence 1.3 + +letting p be permutation((1, 3, 4)) +letting s be {(1, 3), (3, 4), (4, 1)} +$ Visualisation for s +$ 1 3 +$ 3 4 +$ 4 1 + +language Essence 1.3 + +letting p be permutation((1, 4, 2)) +letting s be {(1, 4), (2, 1), (4, 2)} +$ Visualisation for s +$ 1 4 +$ 2 1 +$ 4 2 + +language Essence 1.3 + +letting p be permutation((1, 4, 3)) +letting s be {(1, 4), (3, 1), (4, 3)} +$ Visualisation for s +$ 1 4 +$ 3 1 +$ 4 3 + diff --git a/tests/custom/permutations/03_generators/runthese.sh b/tests/custom/permutations/03_generators/runthese.sh new file mode 100644 index 0000000000..3e52ea37a4 --- /dev/null +++ b/tests/custom/permutations/03_generators/runthese.sh @@ -0,0 +1,2 @@ +stack install +stack test --test-arguments "-p custom.permutations.03_generators" diff --git a/tests/custom/permutations/04_equality/0001_given_permutations_in_param/permutation.essence b/tests/custom/permutations/04_equality/0001_given_permutations_in_param/permutation.essence new file mode 100644 index 0000000000..759f7dfacc --- /dev/null +++ b/tests/custom/permutations/04_equality/0001_given_permutations_in_param/permutation.essence @@ -0,0 +1,12 @@ +letting n be 4 + +given p : permutation of int(1..n) +given q : permutation of int(1..n) + +find b : bool + +such that b = (p = q) + + + + diff --git a/tests/custom/permutations/04_equality/0001_given_permutations_in_param/permutation.param b/tests/custom/permutations/04_equality/0001_given_permutations_in_param/permutation.param new file mode 100644 index 0000000000..98b582712a --- /dev/null +++ b/tests/custom/permutations/04_equality/0001_given_permutations_in_param/permutation.param @@ -0,0 +1,2 @@ +letting p be permutation((1,3,4)) +letting q be permutation((1,3,4)) diff --git a/tests/custom/permutations/04_equality/0001_given_permutations_in_param/run.sh b/tests/custom/permutations/04_equality/0001_given_permutations_in_param/run.sh new file mode 100755 index 0000000000..9dc67e67f5 --- /dev/null +++ b/tests/custom/permutations/04_equality/0001_given_permutations_in_param/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence *.param +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/04_equality/0001_given_permutations_in_param/stdout.expected b/tests/custom/permutations/04_equality/0001_given_permutations_in_param/stdout.expected new file mode 100644 index 0000000000..901f2ae574 --- /dev/null +++ b/tests/custom/permutations/04_equality/0001_given_permutations_in_param/stdout.expected @@ -0,0 +1,8 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime permutation.param +Copying solution to: permutation-permutation.solution +language Essence 1.3 + +letting b be true diff --git a/tests/custom/permutations/04_equality/0002_given_permutations_in_param/permutation.essence b/tests/custom/permutations/04_equality/0002_given_permutations_in_param/permutation.essence new file mode 100644 index 0000000000..759f7dfacc --- /dev/null +++ b/tests/custom/permutations/04_equality/0002_given_permutations_in_param/permutation.essence @@ -0,0 +1,12 @@ +letting n be 4 + +given p : permutation of int(1..n) +given q : permutation of int(1..n) + +find b : bool + +such that b = (p = q) + + + + diff --git a/tests/custom/permutations/04_equality/0002_given_permutations_in_param/permutation.param b/tests/custom/permutations/04_equality/0002_given_permutations_in_param/permutation.param new file mode 100644 index 0000000000..a58ae460a2 --- /dev/null +++ b/tests/custom/permutations/04_equality/0002_given_permutations_in_param/permutation.param @@ -0,0 +1,2 @@ +letting p be permutation((1,3,4)) +letting q be permutation((1,2,4)) diff --git a/tests/custom/permutations/04_equality/0002_given_permutations_in_param/run.sh b/tests/custom/permutations/04_equality/0002_given_permutations_in_param/run.sh new file mode 100755 index 0000000000..9dc67e67f5 --- /dev/null +++ b/tests/custom/permutations/04_equality/0002_given_permutations_in_param/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence *.param +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/04_equality/0002_given_permutations_in_param/stdout.expected b/tests/custom/permutations/04_equality/0002_given_permutations_in_param/stdout.expected new file mode 100644 index 0000000000..1cc90d46bc --- /dev/null +++ b/tests/custom/permutations/04_equality/0002_given_permutations_in_param/stdout.expected @@ -0,0 +1,8 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime permutation.param +Copying solution to: permutation-permutation.solution +language Essence 1.3 + +letting b be false diff --git a/tests/custom/permutations/04_equality/0003_given_equal_letting/permutation.essence b/tests/custom/permutations/04_equality/0003_given_equal_letting/permutation.essence new file mode 100644 index 0000000000..699aa4ffc8 --- /dev/null +++ b/tests/custom/permutations/04_equality/0003_given_equal_letting/permutation.essence @@ -0,0 +1,12 @@ +letting n be 4 + +given p : permutation of int(1..n) +letting q be permutation((1,2,4)) + +find b : bool + +such that b = (p = q) + + + + diff --git a/tests/custom/permutations/04_equality/0003_given_equal_letting/permutation.param b/tests/custom/permutations/04_equality/0003_given_equal_letting/permutation.param new file mode 100644 index 0000000000..8a8c516801 --- /dev/null +++ b/tests/custom/permutations/04_equality/0003_given_equal_letting/permutation.param @@ -0,0 +1 @@ +letting p be permutation((1,3,4)) diff --git a/tests/custom/permutations/04_equality/0003_given_equal_letting/run.sh b/tests/custom/permutations/04_equality/0003_given_equal_letting/run.sh new file mode 100755 index 0000000000..9dc67e67f5 --- /dev/null +++ b/tests/custom/permutations/04_equality/0003_given_equal_letting/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence *.param +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/04_equality/0003_given_equal_letting/stdout.expected b/tests/custom/permutations/04_equality/0003_given_equal_letting/stdout.expected new file mode 100644 index 0000000000..1cc90d46bc --- /dev/null +++ b/tests/custom/permutations/04_equality/0003_given_equal_letting/stdout.expected @@ -0,0 +1,8 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime permutation.param +Copying solution to: permutation-permutation.solution +language Essence 1.3 + +letting b be false diff --git a/tests/custom/permutations/04_equality/runthese.sh b/tests/custom/permutations/04_equality/runthese.sh new file mode 100644 index 0000000000..81e7b6b8c9 --- /dev/null +++ b/tests/custom/permutations/04_equality/runthese.sh @@ -0,0 +1,2 @@ +stack install +stack test --test-arguments "-p custom.permutations.04_equality" diff --git a/tests/custom/permutations/README.md b/tests/custom/permutations/README.md index b2476e7e1b..75f248442d 100644 --- a/tests/custom/permutations/README.md +++ b/tests/custom/permutations/README.md @@ -1,14 +1,28 @@ # Permutations spec Organized by level - each level adding functionality +At the moment a permutation's inner type is restricted +to types that can index a matrix i.e. int, enum, unnamed types + ## 01 representation Tests permutation behaviour that should work with no rewrite rules. - permutations must parse correctly in model and parameter files - the size attribute must constrain the size of the permutation - enumeration tests for finding permutations +- TODO add tests for enums, unameds + ## 02 cardinality Test that we can get the number of permuted elements by |p| - basic cardinality for find, letting, given -## 03 equality +- TODO add tests for enums, unameds + +## 03 generators +Tests permutations in generator of a comprehension +- TODO add tests for enums, unameds + +## 04 image of value of inner type under permutation + + +## 05 equality Tests equality on permutations - basic equality for find, letting, given - tests [|p| = i | p <- sp] where sp is a set of permutations diff --git a/tests/custom/permutations/runthese.sh b/tests/custom/permutations/runthese.sh new file mode 100644 index 0000000000..e2d0c6b574 --- /dev/null +++ b/tests/custom/permutations/runthese.sh @@ -0,0 +1,2 @@ +stack install +stack test --test-arguments "-p custom.permutations" From 3e5629328684a72eed26f38c0e65008771611ab7 Mon Sep 17 00:00:00 2001 From: Fraser Dunlop Date: Tue, 4 Dec 2018 15:57:30 +0000 Subject: [PATCH 041/229] More tests --- tests/custom/permutations/04_equality/runthese.sh | 2 -- .../permutation.essence | 0 .../permutation.param | 0 .../0001_given_permutations_in_param/run.sh | 0 .../0001_given_permutations_in_param/stdout.expected | 0 .../permutation.essence | 0 .../permutation.param | 0 .../0002_given_permutations_in_param/run.sh | 0 .../0002_given_permutations_in_param/stdout.expected | 0 .../0003_given_equal_letting/permutation.essence | 0 .../0003_given_equal_letting/permutation.param | 0 .../0003_given_equal_letting/run.sh | 0 .../0003_given_equal_letting/stdout.expected | 0 .../0004_letting_equal_given/permutation.essence | 12 ++++++++++++ .../0004_letting_equal_given/permutation.param | 1 + .../05_equality/0004_letting_equal_given/run.sh | 3 +++ .../0004_letting_equal_given/stdout.expected | 8 ++++++++ tests/custom/permutations/05_equality/runthese.sh | 2 ++ 18 files changed, 26 insertions(+), 2 deletions(-) delete mode 100644 tests/custom/permutations/04_equality/runthese.sh rename tests/custom/permutations/{04_equality => 05_equality}/0001_given_permutations_in_param/permutation.essence (100%) rename tests/custom/permutations/{04_equality => 05_equality}/0001_given_permutations_in_param/permutation.param (100%) rename tests/custom/permutations/{04_equality => 05_equality}/0001_given_permutations_in_param/run.sh (100%) rename tests/custom/permutations/{04_equality => 05_equality}/0001_given_permutations_in_param/stdout.expected (100%) rename tests/custom/permutations/{04_equality => 05_equality}/0002_given_permutations_in_param/permutation.essence (100%) rename tests/custom/permutations/{04_equality => 05_equality}/0002_given_permutations_in_param/permutation.param (100%) rename tests/custom/permutations/{04_equality => 05_equality}/0002_given_permutations_in_param/run.sh (100%) rename tests/custom/permutations/{04_equality => 05_equality}/0002_given_permutations_in_param/stdout.expected (100%) rename tests/custom/permutations/{04_equality => 05_equality}/0003_given_equal_letting/permutation.essence (100%) rename tests/custom/permutations/{04_equality => 05_equality}/0003_given_equal_letting/permutation.param (100%) rename tests/custom/permutations/{04_equality => 05_equality}/0003_given_equal_letting/run.sh (100%) rename tests/custom/permutations/{04_equality => 05_equality}/0003_given_equal_letting/stdout.expected (100%) create mode 100644 tests/custom/permutations/05_equality/0004_letting_equal_given/permutation.essence create mode 100644 tests/custom/permutations/05_equality/0004_letting_equal_given/permutation.param create mode 100755 tests/custom/permutations/05_equality/0004_letting_equal_given/run.sh create mode 100644 tests/custom/permutations/05_equality/0004_letting_equal_given/stdout.expected create mode 100644 tests/custom/permutations/05_equality/runthese.sh diff --git a/tests/custom/permutations/04_equality/runthese.sh b/tests/custom/permutations/04_equality/runthese.sh deleted file mode 100644 index 81e7b6b8c9..0000000000 --- a/tests/custom/permutations/04_equality/runthese.sh +++ /dev/null @@ -1,2 +0,0 @@ -stack install -stack test --test-arguments "-p custom.permutations.04_equality" diff --git a/tests/custom/permutations/04_equality/0001_given_permutations_in_param/permutation.essence b/tests/custom/permutations/05_equality/0001_given_permutations_in_param/permutation.essence similarity index 100% rename from tests/custom/permutations/04_equality/0001_given_permutations_in_param/permutation.essence rename to tests/custom/permutations/05_equality/0001_given_permutations_in_param/permutation.essence diff --git a/tests/custom/permutations/04_equality/0001_given_permutations_in_param/permutation.param b/tests/custom/permutations/05_equality/0001_given_permutations_in_param/permutation.param similarity index 100% rename from tests/custom/permutations/04_equality/0001_given_permutations_in_param/permutation.param rename to tests/custom/permutations/05_equality/0001_given_permutations_in_param/permutation.param diff --git a/tests/custom/permutations/04_equality/0001_given_permutations_in_param/run.sh b/tests/custom/permutations/05_equality/0001_given_permutations_in_param/run.sh similarity index 100% rename from tests/custom/permutations/04_equality/0001_given_permutations_in_param/run.sh rename to tests/custom/permutations/05_equality/0001_given_permutations_in_param/run.sh diff --git a/tests/custom/permutations/04_equality/0001_given_permutations_in_param/stdout.expected b/tests/custom/permutations/05_equality/0001_given_permutations_in_param/stdout.expected similarity index 100% rename from tests/custom/permutations/04_equality/0001_given_permutations_in_param/stdout.expected rename to tests/custom/permutations/05_equality/0001_given_permutations_in_param/stdout.expected diff --git a/tests/custom/permutations/04_equality/0002_given_permutations_in_param/permutation.essence b/tests/custom/permutations/05_equality/0002_given_permutations_in_param/permutation.essence similarity index 100% rename from tests/custom/permutations/04_equality/0002_given_permutations_in_param/permutation.essence rename to tests/custom/permutations/05_equality/0002_given_permutations_in_param/permutation.essence diff --git a/tests/custom/permutations/04_equality/0002_given_permutations_in_param/permutation.param b/tests/custom/permutations/05_equality/0002_given_permutations_in_param/permutation.param similarity index 100% rename from tests/custom/permutations/04_equality/0002_given_permutations_in_param/permutation.param rename to tests/custom/permutations/05_equality/0002_given_permutations_in_param/permutation.param diff --git a/tests/custom/permutations/04_equality/0002_given_permutations_in_param/run.sh b/tests/custom/permutations/05_equality/0002_given_permutations_in_param/run.sh similarity index 100% rename from tests/custom/permutations/04_equality/0002_given_permutations_in_param/run.sh rename to tests/custom/permutations/05_equality/0002_given_permutations_in_param/run.sh diff --git a/tests/custom/permutations/04_equality/0002_given_permutations_in_param/stdout.expected b/tests/custom/permutations/05_equality/0002_given_permutations_in_param/stdout.expected similarity index 100% rename from tests/custom/permutations/04_equality/0002_given_permutations_in_param/stdout.expected rename to tests/custom/permutations/05_equality/0002_given_permutations_in_param/stdout.expected diff --git a/tests/custom/permutations/04_equality/0003_given_equal_letting/permutation.essence b/tests/custom/permutations/05_equality/0003_given_equal_letting/permutation.essence similarity index 100% rename from tests/custom/permutations/04_equality/0003_given_equal_letting/permutation.essence rename to tests/custom/permutations/05_equality/0003_given_equal_letting/permutation.essence diff --git a/tests/custom/permutations/04_equality/0003_given_equal_letting/permutation.param b/tests/custom/permutations/05_equality/0003_given_equal_letting/permutation.param similarity index 100% rename from tests/custom/permutations/04_equality/0003_given_equal_letting/permutation.param rename to tests/custom/permutations/05_equality/0003_given_equal_letting/permutation.param diff --git a/tests/custom/permutations/04_equality/0003_given_equal_letting/run.sh b/tests/custom/permutations/05_equality/0003_given_equal_letting/run.sh similarity index 100% rename from tests/custom/permutations/04_equality/0003_given_equal_letting/run.sh rename to tests/custom/permutations/05_equality/0003_given_equal_letting/run.sh diff --git a/tests/custom/permutations/04_equality/0003_given_equal_letting/stdout.expected b/tests/custom/permutations/05_equality/0003_given_equal_letting/stdout.expected similarity index 100% rename from tests/custom/permutations/04_equality/0003_given_equal_letting/stdout.expected rename to tests/custom/permutations/05_equality/0003_given_equal_letting/stdout.expected diff --git a/tests/custom/permutations/05_equality/0004_letting_equal_given/permutation.essence b/tests/custom/permutations/05_equality/0004_letting_equal_given/permutation.essence new file mode 100644 index 0000000000..400d6fdcf4 --- /dev/null +++ b/tests/custom/permutations/05_equality/0004_letting_equal_given/permutation.essence @@ -0,0 +1,12 @@ +letting n be 4 + +given p : permutation of int(1..n) +letting q be permutation((1,2,4)) + +find b : bool + +such that b = (q = p) + + + + diff --git a/tests/custom/permutations/05_equality/0004_letting_equal_given/permutation.param b/tests/custom/permutations/05_equality/0004_letting_equal_given/permutation.param new file mode 100644 index 0000000000..8a8c516801 --- /dev/null +++ b/tests/custom/permutations/05_equality/0004_letting_equal_given/permutation.param @@ -0,0 +1 @@ +letting p be permutation((1,3,4)) diff --git a/tests/custom/permutations/05_equality/0004_letting_equal_given/run.sh b/tests/custom/permutations/05_equality/0004_letting_equal_given/run.sh new file mode 100755 index 0000000000..9dc67e67f5 --- /dev/null +++ b/tests/custom/permutations/05_equality/0004_letting_equal_given/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence *.param +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/05_equality/0004_letting_equal_given/stdout.expected b/tests/custom/permutations/05_equality/0004_letting_equal_given/stdout.expected new file mode 100644 index 0000000000..1cc90d46bc --- /dev/null +++ b/tests/custom/permutations/05_equality/0004_letting_equal_given/stdout.expected @@ -0,0 +1,8 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime permutation.param +Copying solution to: permutation-permutation.solution +language Essence 1.3 + +letting b be false diff --git a/tests/custom/permutations/05_equality/runthese.sh b/tests/custom/permutations/05_equality/runthese.sh new file mode 100644 index 0000000000..fe88c0e1a7 --- /dev/null +++ b/tests/custom/permutations/05_equality/runthese.sh @@ -0,0 +1,2 @@ +stack install +stack test --test-arguments "-p custom.permutations.05_equality" From 71bfd76affb51a7bc8aecb8b30d0b86d22cb1925 Mon Sep 17 00:00:00 2001 From: Fraser Dunlop Date: Tue, 4 Dec 2018 16:59:36 +0000 Subject: [PATCH 042/229] image tests --- .../permutation.essence | 11 +++++++++++ .../permutation.param | 2 ++ .../permutation2.param | 2 ++ .../0001_given_permutation_given_int/run.sh | 3 +++ .../stdout.expected | 13 +++++++++++++ .../permutation.essence | 11 +++++++++++ .../permutation.param | 1 + .../0002_given_permutation_letting_int/run.sh | 3 +++ .../stdout.expected | 8 ++++++++ .../permutation.essence | 11 +++++++++++ .../permutation.param | 1 + .../0003_given_permutation_letting_int/run.sh | 3 +++ .../stdout.expected | 8 ++++++++ .../permutation.essence | 11 +++++++++++ .../permutation.param | 2 ++ .../permutation2.essence | 2 ++ .../04_image/0004_given_permutation_find_int/run.sh | 3 +++ .../0004_given_permutation_find_int/stdout.expected | 13 +++++++++++++ .../permutation.essence | 12 ++++++++++++ .../permutation.param | 2 ++ .../permutation2.param | 2 ++ .../0005_find_permutation_given_ints/run.sh | 3 +++ .../stdout.expected | 13 +++++++++++++ .../permutation.essence | 11 +++++++++++ .../permutation.param | 1 + .../permutation2.param | 1 + .../0006_letting_permutation_given_int/run.sh | 3 +++ .../stdout.expected | 13 +++++++++++++ tests/custom/permutations/04_image/runthese.sh | 2 ++ tests/custom/permutations/README.md | 8 ++++---- 30 files changed, 175 insertions(+), 4 deletions(-) create mode 100644 tests/custom/permutations/04_image/0001_given_permutation_given_int/permutation.essence create mode 100644 tests/custom/permutations/04_image/0001_given_permutation_given_int/permutation.param create mode 100644 tests/custom/permutations/04_image/0001_given_permutation_given_int/permutation2.param create mode 100755 tests/custom/permutations/04_image/0001_given_permutation_given_int/run.sh create mode 100644 tests/custom/permutations/04_image/0001_given_permutation_given_int/stdout.expected create mode 100644 tests/custom/permutations/04_image/0002_given_permutation_letting_int/permutation.essence create mode 100644 tests/custom/permutations/04_image/0002_given_permutation_letting_int/permutation.param create mode 100755 tests/custom/permutations/04_image/0002_given_permutation_letting_int/run.sh create mode 100644 tests/custom/permutations/04_image/0002_given_permutation_letting_int/stdout.expected create mode 100644 tests/custom/permutations/04_image/0003_given_permutation_letting_int/permutation.essence create mode 100644 tests/custom/permutations/04_image/0003_given_permutation_letting_int/permutation.param create mode 100755 tests/custom/permutations/04_image/0003_given_permutation_letting_int/run.sh create mode 100644 tests/custom/permutations/04_image/0003_given_permutation_letting_int/stdout.expected create mode 100644 tests/custom/permutations/04_image/0004_given_permutation_find_int/permutation.essence create mode 100644 tests/custom/permutations/04_image/0004_given_permutation_find_int/permutation.param create mode 100644 tests/custom/permutations/04_image/0004_given_permutation_find_int/permutation2.essence create mode 100755 tests/custom/permutations/04_image/0004_given_permutation_find_int/run.sh create mode 100644 tests/custom/permutations/04_image/0004_given_permutation_find_int/stdout.expected create mode 100644 tests/custom/permutations/04_image/0005_find_permutation_given_ints/permutation.essence create mode 100644 tests/custom/permutations/04_image/0005_find_permutation_given_ints/permutation.param create mode 100644 tests/custom/permutations/04_image/0005_find_permutation_given_ints/permutation2.param create mode 100755 tests/custom/permutations/04_image/0005_find_permutation_given_ints/run.sh create mode 100644 tests/custom/permutations/04_image/0005_find_permutation_given_ints/stdout.expected create mode 100644 tests/custom/permutations/04_image/0006_letting_permutation_given_int/permutation.essence create mode 100644 tests/custom/permutations/04_image/0006_letting_permutation_given_int/permutation.param create mode 100644 tests/custom/permutations/04_image/0006_letting_permutation_given_int/permutation2.param create mode 100755 tests/custom/permutations/04_image/0006_letting_permutation_given_int/run.sh create mode 100644 tests/custom/permutations/04_image/0006_letting_permutation_given_int/stdout.expected create mode 100644 tests/custom/permutations/04_image/runthese.sh diff --git a/tests/custom/permutations/04_image/0001_given_permutation_given_int/permutation.essence b/tests/custom/permutations/04_image/0001_given_permutation_given_int/permutation.essence new file mode 100644 index 0000000000..38e2624e94 --- /dev/null +++ b/tests/custom/permutations/04_image/0001_given_permutation_given_int/permutation.essence @@ -0,0 +1,11 @@ +given i : int(0..10) + +given p : permutation of int(1..4) + +find j : int(0..10) + +such that j = image(p, i) + + + + diff --git a/tests/custom/permutations/04_image/0001_given_permutation_given_int/permutation.param b/tests/custom/permutations/04_image/0001_given_permutation_given_int/permutation.param new file mode 100644 index 0000000000..600438bb4b --- /dev/null +++ b/tests/custom/permutations/04_image/0001_given_permutation_given_int/permutation.param @@ -0,0 +1,2 @@ +letting p be permutation((1,3,4)) +letting i be 1 diff --git a/tests/custom/permutations/04_image/0001_given_permutation_given_int/permutation2.param b/tests/custom/permutations/04_image/0001_given_permutation_given_int/permutation2.param new file mode 100644 index 0000000000..96f2fdd075 --- /dev/null +++ b/tests/custom/permutations/04_image/0001_given_permutation_given_int/permutation2.param @@ -0,0 +1,2 @@ +letting p be permutation((1,3,4)) +letting i be 6 diff --git a/tests/custom/permutations/04_image/0001_given_permutation_given_int/run.sh b/tests/custom/permutations/04_image/0001_given_permutation_given_int/run.sh new file mode 100755 index 0000000000..9dc67e67f5 --- /dev/null +++ b/tests/custom/permutations/04_image/0001_given_permutation_given_int/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence *.param +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/04_image/0001_given_permutation_given_int/stdout.expected b/tests/custom/permutations/04_image/0001_given_permutation_given_int/stdout.expected new file mode 100644 index 0000000000..0342fd6429 --- /dev/null +++ b/tests/custom/permutations/04_image/0001_given_permutation_given_int/stdout.expected @@ -0,0 +1,13 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime permutation.param +Savile Row: model000001.eprime permutation2.param +Copying solution to: permutation-permutation.solution +Copying solution to: permutation-permutation2.solution +language Essence 1.3 + +letting j be 3 +language Essence 1.3 + +letting j be 6 diff --git a/tests/custom/permutations/04_image/0002_given_permutation_letting_int/permutation.essence b/tests/custom/permutations/04_image/0002_given_permutation_letting_int/permutation.essence new file mode 100644 index 0000000000..8ac5f78cc5 --- /dev/null +++ b/tests/custom/permutations/04_image/0002_given_permutation_letting_int/permutation.essence @@ -0,0 +1,11 @@ +letting i be 1 + +given p : permutation of int(1..4) + +find j : int(0..10) + +such that j = image(p, i) + + + + diff --git a/tests/custom/permutations/04_image/0002_given_permutation_letting_int/permutation.param b/tests/custom/permutations/04_image/0002_given_permutation_letting_int/permutation.param new file mode 100644 index 0000000000..8a8c516801 --- /dev/null +++ b/tests/custom/permutations/04_image/0002_given_permutation_letting_int/permutation.param @@ -0,0 +1 @@ +letting p be permutation((1,3,4)) diff --git a/tests/custom/permutations/04_image/0002_given_permutation_letting_int/run.sh b/tests/custom/permutations/04_image/0002_given_permutation_letting_int/run.sh new file mode 100755 index 0000000000..9dc67e67f5 --- /dev/null +++ b/tests/custom/permutations/04_image/0002_given_permutation_letting_int/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence *.param +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/04_image/0002_given_permutation_letting_int/stdout.expected b/tests/custom/permutations/04_image/0002_given_permutation_letting_int/stdout.expected new file mode 100644 index 0000000000..5cd5a59686 --- /dev/null +++ b/tests/custom/permutations/04_image/0002_given_permutation_letting_int/stdout.expected @@ -0,0 +1,8 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime permutation.param +Copying solution to: permutation-permutation.solution +language Essence 1.3 + +letting j be 3 diff --git a/tests/custom/permutations/04_image/0003_given_permutation_letting_int/permutation.essence b/tests/custom/permutations/04_image/0003_given_permutation_letting_int/permutation.essence new file mode 100644 index 0000000000..786c6b7c52 --- /dev/null +++ b/tests/custom/permutations/04_image/0003_given_permutation_letting_int/permutation.essence @@ -0,0 +1,11 @@ +letting i be 6 + +given p : permutation of int(1..4) + +find j : int(0..10) + +such that j = image(p, i) + + + + diff --git a/tests/custom/permutations/04_image/0003_given_permutation_letting_int/permutation.param b/tests/custom/permutations/04_image/0003_given_permutation_letting_int/permutation.param new file mode 100644 index 0000000000..8a8c516801 --- /dev/null +++ b/tests/custom/permutations/04_image/0003_given_permutation_letting_int/permutation.param @@ -0,0 +1 @@ +letting p be permutation((1,3,4)) diff --git a/tests/custom/permutations/04_image/0003_given_permutation_letting_int/run.sh b/tests/custom/permutations/04_image/0003_given_permutation_letting_int/run.sh new file mode 100755 index 0000000000..9dc67e67f5 --- /dev/null +++ b/tests/custom/permutations/04_image/0003_given_permutation_letting_int/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence *.param +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/04_image/0003_given_permutation_letting_int/stdout.expected b/tests/custom/permutations/04_image/0003_given_permutation_letting_int/stdout.expected new file mode 100644 index 0000000000..cc1cb62951 --- /dev/null +++ b/tests/custom/permutations/04_image/0003_given_permutation_letting_int/stdout.expected @@ -0,0 +1,8 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime permutation.param +Copying solution to: permutation-permutation.solution +language Essence 1.3 + +letting j be 6 diff --git a/tests/custom/permutations/04_image/0004_given_permutation_find_int/permutation.essence b/tests/custom/permutations/04_image/0004_given_permutation_find_int/permutation.essence new file mode 100644 index 0000000000..0d83139a52 --- /dev/null +++ b/tests/custom/permutations/04_image/0004_given_permutation_find_int/permutation.essence @@ -0,0 +1,11 @@ +find i : int(0..10) + +given p : permutation of int(1..4) + +given j : int(0..10) + +such that j = image(p, i) + + + + diff --git a/tests/custom/permutations/04_image/0004_given_permutation_find_int/permutation.param b/tests/custom/permutations/04_image/0004_given_permutation_find_int/permutation.param new file mode 100644 index 0000000000..417c2de221 --- /dev/null +++ b/tests/custom/permutations/04_image/0004_given_permutation_find_int/permutation.param @@ -0,0 +1,2 @@ +letting p be permutation((1,3,4)) +letting j be 3 diff --git a/tests/custom/permutations/04_image/0004_given_permutation_find_int/permutation2.essence b/tests/custom/permutations/04_image/0004_given_permutation_find_int/permutation2.essence new file mode 100644 index 0000000000..d9758bd4b1 --- /dev/null +++ b/tests/custom/permutations/04_image/0004_given_permutation_find_int/permutation2.essence @@ -0,0 +1,2 @@ +letting p be permutation((1,3,4)) +letting j be 6 diff --git a/tests/custom/permutations/04_image/0004_given_permutation_find_int/run.sh b/tests/custom/permutations/04_image/0004_given_permutation_find_int/run.sh new file mode 100755 index 0000000000..9dc67e67f5 --- /dev/null +++ b/tests/custom/permutations/04_image/0004_given_permutation_find_int/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence *.param +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/04_image/0004_given_permutation_find_int/stdout.expected b/tests/custom/permutations/04_image/0004_given_permutation_find_int/stdout.expected new file mode 100644 index 0000000000..5ddaa104a4 --- /dev/null +++ b/tests/custom/permutations/04_image/0004_given_permutation_find_int/stdout.expected @@ -0,0 +1,13 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime permutation2.essence +Savile Row: model000001.eprime permutation.param +Copying solution to: permutation-permutation2.solution +Copying solution to: permutation-permutation.solution +language Essence 1.3 + +letting i be 1 +language Essence 1.3 + +letting i be 6 diff --git a/tests/custom/permutations/04_image/0005_find_permutation_given_ints/permutation.essence b/tests/custom/permutations/04_image/0005_find_permutation_given_ints/permutation.essence new file mode 100644 index 0000000000..4cd6172d9d --- /dev/null +++ b/tests/custom/permutations/04_image/0005_find_permutation_given_ints/permutation.essence @@ -0,0 +1,12 @@ +given i : int(0..10) + +find p : permutation of int(1..4) + +given j : int(0..10) + +such that + j = image(p, i) /\ |p| = 3 + + + + diff --git a/tests/custom/permutations/04_image/0005_find_permutation_given_ints/permutation.param b/tests/custom/permutations/04_image/0005_find_permutation_given_ints/permutation.param new file mode 100644 index 0000000000..4e680d5b1b --- /dev/null +++ b/tests/custom/permutations/04_image/0005_find_permutation_given_ints/permutation.param @@ -0,0 +1,2 @@ +letting i be 4 +letting j be 3 diff --git a/tests/custom/permutations/04_image/0005_find_permutation_given_ints/permutation2.param b/tests/custom/permutations/04_image/0005_find_permutation_given_ints/permutation2.param new file mode 100644 index 0000000000..0ff59e0909 --- /dev/null +++ b/tests/custom/permutations/04_image/0005_find_permutation_given_ints/permutation2.param @@ -0,0 +1,2 @@ +letting i be 3 +letting j be 3 diff --git a/tests/custom/permutations/04_image/0005_find_permutation_given_ints/run.sh b/tests/custom/permutations/04_image/0005_find_permutation_given_ints/run.sh new file mode 100755 index 0000000000..9dc67e67f5 --- /dev/null +++ b/tests/custom/permutations/04_image/0005_find_permutation_given_ints/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence *.param +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/04_image/0005_find_permutation_given_ints/stdout.expected b/tests/custom/permutations/04_image/0005_find_permutation_given_ints/stdout.expected new file mode 100644 index 0000000000..4ed8b97ac7 --- /dev/null +++ b/tests/custom/permutations/04_image/0005_find_permutation_given_ints/stdout.expected @@ -0,0 +1,13 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime permutation.param +Savile Row: model000001.eprime permutation2.param +Copying solution to: permutation-permutation.solution +Copying solution to: permutation-permutation2.solution +language Essence 1.3 + +letting p be permutation((2, 4, 3)) +language Essence 1.3 + +letting p be permutation((1, 2, 4)) diff --git a/tests/custom/permutations/04_image/0006_letting_permutation_given_int/permutation.essence b/tests/custom/permutations/04_image/0006_letting_permutation_given_int/permutation.essence new file mode 100644 index 0000000000..a32d539c49 --- /dev/null +++ b/tests/custom/permutations/04_image/0006_letting_permutation_given_int/permutation.essence @@ -0,0 +1,11 @@ +given i : int(0..10) +letting p be permutation((1,3,4)) + + +find j : int(0..10) + +such that j = image(p, i) + + + + diff --git a/tests/custom/permutations/04_image/0006_letting_permutation_given_int/permutation.param b/tests/custom/permutations/04_image/0006_letting_permutation_given_int/permutation.param new file mode 100644 index 0000000000..d185471560 --- /dev/null +++ b/tests/custom/permutations/04_image/0006_letting_permutation_given_int/permutation.param @@ -0,0 +1 @@ +letting i be 1 diff --git a/tests/custom/permutations/04_image/0006_letting_permutation_given_int/permutation2.param b/tests/custom/permutations/04_image/0006_letting_permutation_given_int/permutation2.param new file mode 100644 index 0000000000..4f045e546c --- /dev/null +++ b/tests/custom/permutations/04_image/0006_letting_permutation_given_int/permutation2.param @@ -0,0 +1 @@ +letting i be 6 diff --git a/tests/custom/permutations/04_image/0006_letting_permutation_given_int/run.sh b/tests/custom/permutations/04_image/0006_letting_permutation_given_int/run.sh new file mode 100755 index 0000000000..9dc67e67f5 --- /dev/null +++ b/tests/custom/permutations/04_image/0006_letting_permutation_given_int/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence *.param +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/04_image/0006_letting_permutation_given_int/stdout.expected b/tests/custom/permutations/04_image/0006_letting_permutation_given_int/stdout.expected new file mode 100644 index 0000000000..0342fd6429 --- /dev/null +++ b/tests/custom/permutations/04_image/0006_letting_permutation_given_int/stdout.expected @@ -0,0 +1,13 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime permutation.param +Savile Row: model000001.eprime permutation2.param +Copying solution to: permutation-permutation.solution +Copying solution to: permutation-permutation2.solution +language Essence 1.3 + +letting j be 3 +language Essence 1.3 + +letting j be 6 diff --git a/tests/custom/permutations/04_image/runthese.sh b/tests/custom/permutations/04_image/runthese.sh new file mode 100644 index 0000000000..0ca42228a0 --- /dev/null +++ b/tests/custom/permutations/04_image/runthese.sh @@ -0,0 +1,2 @@ +stack install +stack test --test-arguments "-p custom.permutations.04_image" diff --git a/tests/custom/permutations/README.md b/tests/custom/permutations/README.md index 75f248442d..13da9b61f9 100644 --- a/tests/custom/permutations/README.md +++ b/tests/custom/permutations/README.md @@ -8,19 +8,19 @@ Tests permutation behaviour that should work with no rewrite rules. - permutations must parse correctly in model and parameter files - the size attribute must constrain the size of the permutation - enumeration tests for finding permutations -- TODO add tests for enums, unameds +- TODO add tests for enums, unnameds ## 02 cardinality Test that we can get the number of permuted elements by |p| - basic cardinality for find, letting, given -- TODO add tests for enums, unameds +- TODO add tests for enums, unnameds ## 03 generators Tests permutations in generator of a comprehension -- TODO add tests for enums, unameds +- TODO add tests for enums, unnameds ## 04 image of value of inner type under permutation - +- TODO add tests for enums & unnameds ## 05 equality Tests equality on permutations From f7021d2a5135f98c5b4f68c0c0cbd02124002f29 Mon Sep 17 00:00:00 2001 From: Fraser Dunlop Date: Wed, 5 Dec 2018 10:43:24 +0000 Subject: [PATCH 043/229] Added enum and unnamed representation tests for permutation --- .../stderr.expected | 10 -- .../permutation.essence | 9 ++ .../permutation.param | 1 + .../0001_given_permutation_in_param/run.sh | 0 .../stdout.expected | 0 .../permutation.essence | 5 + .../permutation.param | 1 + .../0002_given_permutation_in_param/run.sh | 0 .../stdout.expected | 0 .../permutation.essence | 5 + .../permutation.param | 1 + .../run.sh | 0 .../stdout.expected | 0 .../permutation.essence | 5 + .../permutation.param | 1 + .../run.sh | 0 .../stdout.expected | 3 + .../permutation.essence | 5 + .../run.sh | 0 .../stdout.expected | 40 ++++++ .../permutation.essence | 5 + .../run.sh | 0 .../stdout.expected | 0 .../permutation.essence | 0 .../0007_letting_permutation_be_empty/run.sh | 0 .../stdout.expected | 0 .../permutation.essence | 5 + .../0008_find_permutation_of_int1_4/run.sh | 0 .../stdout.expected | 100 ++++++++++++++ .../permutation.essence | 4 + .../0009_letting_permutation_in_model/run.sh | 0 .../stdout.expected | 0 .../permutation.essence | 5 + .../run.sh | 0 .../stdout.expected | 20 +++ .../permutation.essence | 5 + .../run.sh | 0 .../stdout.expected | 24 ++++ .../permutation.essence | 5 + .../run.sh | 0 .../stdout.expected | 60 +++++++++ .../permutation.essence | 0 .../permutation.param | 0 .../0001_given_permutation_in_param/run.sh | 3 + .../stdout.expected | 7 + .../permutation.essence | 0 .../permutation.param | 0 .../0002_given_permutation_in_param/run.sh | 3 + .../stdout.expected | 7 + .../permutation.essence | 0 .../permutation.param | 0 .../run.sh | 3 + .../stdout.expected | 7 + .../permutation.essence | 2 +- .../permutation.param | 0 .../run.sh | 3 + .../stdout.expected | 7 + .../permutation.essence | 0 .../permutation.param | 0 .../run.sh | 3 + .../stdout.expected | 0 .../permutation.essence | 0 .../permutation.param | 0 .../run.sh | 3 + .../stdout.expected | 8 ++ .../permutation.essence | 3 + .../permutation.param | 0 .../0007_letting_permutation_be_empty/run.sh | 3 + .../stdout.expected | 7 + .../permutation.essence | 0 .../permutation.param | 0 .../0008_find_permutation_of_int1_4/run.sh | 3 + .../stdout.expected | 0 .../permutation.essence | 0 .../0009_letting_permutation_in_model/run.sh | 3 + .../stdout.expected | 7 + .../permutation.essence | 0 .../permutation.param | 0 .../run.sh | 3 + .../stdout.expected | 0 .../permutation.essence | 0 .../permutation.param | 0 .../run.sh | 3 + .../stdout.expected | 0 .../permutation.essence | 0 .../permutation.param | 0 .../run.sh | 3 + .../stdout.expected | 0 .../permutation.essence | 5 + .../run.sh | 3 + .../stdout.expected | 49 +++++++ .../permutation.essence | 5 + .../run.sh | 3 + .../stdout.expected | 9 ++ .../permutation.essence | 3 + .../0007_letting_permutation_be_empty/run.sh | 3 + .../stdout.expected | 7 + .../permutation.essence | 5 + .../0008_find_permutation_of_int1_4/run.sh | 3 + .../stdout.expected | 124 ++++++++++++++++++ .../permutation.essence | 5 + .../run.sh | 3 + .../stdout.expected | 24 ++++ .../permutation.essence | 5 + .../run.sh | 3 + .../stdout.expected | 29 ++++ .../permutation.essence | 5 + .../run.sh | 3 + .../stdout.expected | 74 +++++++++++ 109 files changed, 769 insertions(+), 11 deletions(-) delete mode 100644 tests/custom/permutations/01_representation/0003_given_permutation_in_param_2_cycle/stderr.expected create mode 100644 tests/custom/permutations/01_representation/enum/0001_given_permutation_in_param/permutation.essence create mode 100644 tests/custom/permutations/01_representation/enum/0001_given_permutation_in_param/permutation.param rename tests/custom/permutations/01_representation/{ => enum}/0001_given_permutation_in_param/run.sh (100%) rename tests/custom/permutations/01_representation/{ => enum}/0001_given_permutation_in_param/stdout.expected (100%) create mode 100644 tests/custom/permutations/01_representation/enum/0002_given_permutation_in_param/permutation.essence create mode 100644 tests/custom/permutations/01_representation/enum/0002_given_permutation_in_param/permutation.param rename tests/custom/permutations/01_representation/{ => enum}/0002_given_permutation_in_param/run.sh (100%) rename tests/custom/permutations/01_representation/{ => enum}/0002_given_permutation_in_param/stdout.expected (100%) create mode 100644 tests/custom/permutations/01_representation/enum/0003_given_permutation_in_param_2_cycle/permutation.essence create mode 100644 tests/custom/permutations/01_representation/enum/0003_given_permutation_in_param_2_cycle/permutation.param rename tests/custom/permutations/01_representation/{ => enum}/0003_given_permutation_in_param_2_cycle/run.sh (100%) rename tests/custom/permutations/01_representation/{0004_given_permutation_in_param_2_cycle => enum/0003_given_permutation_in_param_2_cycle}/stdout.expected (100%) create mode 100644 tests/custom/permutations/01_representation/enum/0004_given_permutation_in_param_2_cycle/permutation.essence create mode 100644 tests/custom/permutations/01_representation/enum/0004_given_permutation_in_param_2_cycle/permutation.param rename tests/custom/permutations/01_representation/{ => enum}/0004_given_permutation_in_param_2_cycle/run.sh (100%) rename tests/custom/permutations/01_representation/{0003_given_permutation_in_param_2_cycle => enum/0004_given_permutation_in_param_2_cycle}/stdout.expected (67%) create mode 100644 tests/custom/permutations/01_representation/enum/0005_find_permutation_size_4_of_int1_4/permutation.essence rename tests/custom/permutations/01_representation/{ => enum}/0005_find_permutation_size_4_of_int1_4/run.sh (100%) create mode 100644 tests/custom/permutations/01_representation/enum/0005_find_permutation_size_4_of_int1_4/stdout.expected create mode 100644 tests/custom/permutations/01_representation/enum/0006_find_permutation_size_0_of_int1_4/permutation.essence rename tests/custom/permutations/01_representation/{ => enum}/0006_find_permutation_size_0_of_int1_4/run.sh (100%) rename tests/custom/permutations/01_representation/{ => enum}/0006_find_permutation_size_0_of_int1_4/stdout.expected (100%) rename tests/custom/permutations/01_representation/{ => enum}/0007_letting_permutation_be_empty/permutation.essence (100%) rename tests/custom/permutations/01_representation/{ => enum}/0007_letting_permutation_be_empty/run.sh (100%) rename tests/custom/permutations/01_representation/{ => enum}/0007_letting_permutation_be_empty/stdout.expected (100%) create mode 100644 tests/custom/permutations/01_representation/enum/0008_find_permutation_of_int1_4/permutation.essence rename tests/custom/permutations/01_representation/{ => enum}/0008_find_permutation_of_int1_4/run.sh (100%) create mode 100644 tests/custom/permutations/01_representation/enum/0008_find_permutation_of_int1_4/stdout.expected create mode 100644 tests/custom/permutations/01_representation/enum/0009_letting_permutation_in_model/permutation.essence rename tests/custom/permutations/01_representation/{ => enum}/0009_letting_permutation_in_model/run.sh (100%) rename tests/custom/permutations/01_representation/{ => enum}/0009_letting_permutation_in_model/stdout.expected (100%) create mode 100644 tests/custom/permutations/01_representation/enum/0010_find_permutation_maxSize_2_of_int1_3/permutation.essence rename tests/custom/permutations/01_representation/{ => enum}/0010_find_permutation_maxSize_2_of_int1_3/run.sh (100%) create mode 100644 tests/custom/permutations/01_representation/enum/0010_find_permutation_maxSize_2_of_int1_3/stdout.expected create mode 100644 tests/custom/permutations/01_representation/enum/0011_find_permutation_minSize_2_of_int1_3/permutation.essence rename tests/custom/permutations/01_representation/{ => enum}/0011_find_permutation_minSize_2_of_int1_3/run.sh (100%) create mode 100644 tests/custom/permutations/01_representation/enum/0011_find_permutation_minSize_2_of_int1_3/stdout.expected create mode 100644 tests/custom/permutations/01_representation/enum/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/permutation.essence rename tests/custom/permutations/01_representation/{ => enum}/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/run.sh (100%) create mode 100644 tests/custom/permutations/01_representation/enum/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/stdout.expected rename tests/custom/permutations/01_representation/{ => int}/0001_given_permutation_in_param/permutation.essence (100%) rename tests/custom/permutations/01_representation/{ => int}/0001_given_permutation_in_param/permutation.param (100%) create mode 100755 tests/custom/permutations/01_representation/int/0001_given_permutation_in_param/run.sh create mode 100644 tests/custom/permutations/01_representation/int/0001_given_permutation_in_param/stdout.expected rename tests/custom/permutations/01_representation/{ => int}/0002_given_permutation_in_param/permutation.essence (100%) rename tests/custom/permutations/01_representation/{ => int}/0002_given_permutation_in_param/permutation.param (100%) create mode 100755 tests/custom/permutations/01_representation/int/0002_given_permutation_in_param/run.sh create mode 100644 tests/custom/permutations/01_representation/int/0002_given_permutation_in_param/stdout.expected rename tests/custom/permutations/01_representation/{0004_given_permutation_in_param_2_cycle => int/0003_given_permutation_in_param_2_cycle}/permutation.essence (100%) rename tests/custom/permutations/01_representation/{ => int}/0003_given_permutation_in_param_2_cycle/permutation.param (100%) create mode 100755 tests/custom/permutations/01_representation/int/0003_given_permutation_in_param_2_cycle/run.sh create mode 100644 tests/custom/permutations/01_representation/int/0003_given_permutation_in_param_2_cycle/stdout.expected rename tests/custom/permutations/01_representation/{0003_given_permutation_in_param_2_cycle => int/0004_given_permutation_in_param_2_cycle}/permutation.essence (77%) rename tests/custom/permutations/01_representation/{ => int}/0004_given_permutation_in_param_2_cycle/permutation.param (100%) create mode 100755 tests/custom/permutations/01_representation/int/0004_given_permutation_in_param_2_cycle/run.sh create mode 100644 tests/custom/permutations/01_representation/int/0004_given_permutation_in_param_2_cycle/stdout.expected rename tests/custom/permutations/01_representation/{ => int}/0005_find_permutation_size_4_of_int1_4/permutation.essence (100%) rename tests/custom/permutations/01_representation/{ => int}/0005_find_permutation_size_4_of_int1_4/permutation.param (100%) create mode 100755 tests/custom/permutations/01_representation/int/0005_find_permutation_size_4_of_int1_4/run.sh rename tests/custom/permutations/01_representation/{ => int}/0005_find_permutation_size_4_of_int1_4/stdout.expected (100%) rename tests/custom/permutations/01_representation/{ => int}/0006_find_permutation_size_0_of_int1_4/permutation.essence (100%) rename tests/custom/permutations/01_representation/{ => int}/0006_find_permutation_size_0_of_int1_4/permutation.param (100%) create mode 100755 tests/custom/permutations/01_representation/int/0006_find_permutation_size_0_of_int1_4/run.sh create mode 100644 tests/custom/permutations/01_representation/int/0006_find_permutation_size_0_of_int1_4/stdout.expected create mode 100644 tests/custom/permutations/01_representation/int/0007_letting_permutation_be_empty/permutation.essence rename tests/custom/permutations/01_representation/{ => int}/0007_letting_permutation_be_empty/permutation.param (100%) create mode 100755 tests/custom/permutations/01_representation/int/0007_letting_permutation_be_empty/run.sh create mode 100644 tests/custom/permutations/01_representation/int/0007_letting_permutation_be_empty/stdout.expected rename tests/custom/permutations/01_representation/{ => int}/0008_find_permutation_of_int1_4/permutation.essence (100%) rename tests/custom/permutations/01_representation/{ => int}/0008_find_permutation_of_int1_4/permutation.param (100%) create mode 100755 tests/custom/permutations/01_representation/int/0008_find_permutation_of_int1_4/run.sh rename tests/custom/permutations/01_representation/{ => int}/0008_find_permutation_of_int1_4/stdout.expected (100%) rename tests/custom/permutations/01_representation/{ => int}/0009_letting_permutation_in_model/permutation.essence (100%) create mode 100755 tests/custom/permutations/01_representation/int/0009_letting_permutation_in_model/run.sh create mode 100644 tests/custom/permutations/01_representation/int/0009_letting_permutation_in_model/stdout.expected rename tests/custom/permutations/01_representation/{ => int}/0010_find_permutation_maxSize_2_of_int1_3/permutation.essence (100%) rename tests/custom/permutations/01_representation/{ => int}/0010_find_permutation_maxSize_2_of_int1_3/permutation.param (100%) create mode 100755 tests/custom/permutations/01_representation/int/0010_find_permutation_maxSize_2_of_int1_3/run.sh rename tests/custom/permutations/01_representation/{ => int}/0010_find_permutation_maxSize_2_of_int1_3/stdout.expected (100%) rename tests/custom/permutations/01_representation/{ => int}/0011_find_permutation_minSize_2_of_int1_3/permutation.essence (100%) rename tests/custom/permutations/01_representation/{ => int}/0011_find_permutation_minSize_2_of_int1_3/permutation.param (100%) create mode 100755 tests/custom/permutations/01_representation/int/0011_find_permutation_minSize_2_of_int1_3/run.sh rename tests/custom/permutations/01_representation/{ => int}/0011_find_permutation_minSize_2_of_int1_3/stdout.expected (100%) rename tests/custom/permutations/01_representation/{ => int}/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/permutation.essence (100%) rename tests/custom/permutations/01_representation/{ => int}/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/permutation.param (100%) create mode 100755 tests/custom/permutations/01_representation/int/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/run.sh rename tests/custom/permutations/01_representation/{ => int}/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/stdout.expected (100%) create mode 100644 tests/custom/permutations/01_representation/unnamed/0005_find_permutation_size_4_of_int1_4/permutation.essence create mode 100755 tests/custom/permutations/01_representation/unnamed/0005_find_permutation_size_4_of_int1_4/run.sh create mode 100644 tests/custom/permutations/01_representation/unnamed/0005_find_permutation_size_4_of_int1_4/stdout.expected create mode 100644 tests/custom/permutations/01_representation/unnamed/0006_find_permutation_size_0_of_int1_4/permutation.essence create mode 100755 tests/custom/permutations/01_representation/unnamed/0006_find_permutation_size_0_of_int1_4/run.sh create mode 100644 tests/custom/permutations/01_representation/unnamed/0006_find_permutation_size_0_of_int1_4/stdout.expected create mode 100644 tests/custom/permutations/01_representation/unnamed/0007_letting_permutation_be_empty/permutation.essence create mode 100755 tests/custom/permutations/01_representation/unnamed/0007_letting_permutation_be_empty/run.sh create mode 100644 tests/custom/permutations/01_representation/unnamed/0007_letting_permutation_be_empty/stdout.expected create mode 100644 tests/custom/permutations/01_representation/unnamed/0008_find_permutation_of_int1_4/permutation.essence create mode 100755 tests/custom/permutations/01_representation/unnamed/0008_find_permutation_of_int1_4/run.sh create mode 100644 tests/custom/permutations/01_representation/unnamed/0008_find_permutation_of_int1_4/stdout.expected create mode 100644 tests/custom/permutations/01_representation/unnamed/0010_find_permutation_maxSize_2_of_int1_3/permutation.essence create mode 100755 tests/custom/permutations/01_representation/unnamed/0010_find_permutation_maxSize_2_of_int1_3/run.sh create mode 100644 tests/custom/permutations/01_representation/unnamed/0010_find_permutation_maxSize_2_of_int1_3/stdout.expected create mode 100644 tests/custom/permutations/01_representation/unnamed/0011_find_permutation_minSize_2_of_int1_3/permutation.essence create mode 100755 tests/custom/permutations/01_representation/unnamed/0011_find_permutation_minSize_2_of_int1_3/run.sh create mode 100644 tests/custom/permutations/01_representation/unnamed/0011_find_permutation_minSize_2_of_int1_3/stdout.expected create mode 100644 tests/custom/permutations/01_representation/unnamed/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/permutation.essence create mode 100755 tests/custom/permutations/01_representation/unnamed/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/run.sh create mode 100644 tests/custom/permutations/01_representation/unnamed/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/stdout.expected diff --git a/tests/custom/permutations/01_representation/0003_given_permutation_in_param_2_cycle/stderr.expected b/tests/custom/permutations/01_representation/0003_given_permutation_in_param_2_cycle/stderr.expected deleted file mode 100644 index fa292aad7b..0000000000 --- a/tests/custom/permutations/01_representation/0003_given_permutation_in_param_2_cycle/stderr.expected +++ /dev/null @@ -1,10 +0,0 @@ -Error: - The value is not a member of the domain. - Value : permutation((1, 3), (2, 4)) - Domain: permutation {PermutationAsFunction} of int(1..3) - Reason: - The value is not a member of the domain. - Name : p - Value : 4 - Domain: int(1..3) -cat: conjure-output/*.solution: No such file or directory diff --git a/tests/custom/permutations/01_representation/enum/0001_given_permutation_in_param/permutation.essence b/tests/custom/permutations/01_representation/enum/0001_given_permutation_in_param/permutation.essence new file mode 100644 index 0000000000..cfb90df3cc --- /dev/null +++ b/tests/custom/permutations/01_representation/enum/0001_given_permutation_in_param/permutation.essence @@ -0,0 +1,9 @@ +letting n be new type enum {E1,E2,E3,E4} + +given p : permutation of n + +such that true + + + + diff --git a/tests/custom/permutations/01_representation/enum/0001_given_permutation_in_param/permutation.param b/tests/custom/permutations/01_representation/enum/0001_given_permutation_in_param/permutation.param new file mode 100644 index 0000000000..19349bb872 --- /dev/null +++ b/tests/custom/permutations/01_representation/enum/0001_given_permutation_in_param/permutation.param @@ -0,0 +1 @@ +letting p be permutation((E1,E3,E4)) diff --git a/tests/custom/permutations/01_representation/0001_given_permutation_in_param/run.sh b/tests/custom/permutations/01_representation/enum/0001_given_permutation_in_param/run.sh similarity index 100% rename from tests/custom/permutations/01_representation/0001_given_permutation_in_param/run.sh rename to tests/custom/permutations/01_representation/enum/0001_given_permutation_in_param/run.sh diff --git a/tests/custom/permutations/01_representation/0001_given_permutation_in_param/stdout.expected b/tests/custom/permutations/01_representation/enum/0001_given_permutation_in_param/stdout.expected similarity index 100% rename from tests/custom/permutations/01_representation/0001_given_permutation_in_param/stdout.expected rename to tests/custom/permutations/01_representation/enum/0001_given_permutation_in_param/stdout.expected diff --git a/tests/custom/permutations/01_representation/enum/0002_given_permutation_in_param/permutation.essence b/tests/custom/permutations/01_representation/enum/0002_given_permutation_in_param/permutation.essence new file mode 100644 index 0000000000..b02f26c6a6 --- /dev/null +++ b/tests/custom/permutations/01_representation/enum/0002_given_permutation_in_param/permutation.essence @@ -0,0 +1,5 @@ +letting n be new type enum {E1,E2,E3} + +given p : permutation of n + +such that true diff --git a/tests/custom/permutations/01_representation/enum/0002_given_permutation_in_param/permutation.param b/tests/custom/permutations/01_representation/enum/0002_given_permutation_in_param/permutation.param new file mode 100644 index 0000000000..95a86975a7 --- /dev/null +++ b/tests/custom/permutations/01_representation/enum/0002_given_permutation_in_param/permutation.param @@ -0,0 +1 @@ +letting p be permutation((E1,E3,E2)) diff --git a/tests/custom/permutations/01_representation/0002_given_permutation_in_param/run.sh b/tests/custom/permutations/01_representation/enum/0002_given_permutation_in_param/run.sh similarity index 100% rename from tests/custom/permutations/01_representation/0002_given_permutation_in_param/run.sh rename to tests/custom/permutations/01_representation/enum/0002_given_permutation_in_param/run.sh diff --git a/tests/custom/permutations/01_representation/0002_given_permutation_in_param/stdout.expected b/tests/custom/permutations/01_representation/enum/0002_given_permutation_in_param/stdout.expected similarity index 100% rename from tests/custom/permutations/01_representation/0002_given_permutation_in_param/stdout.expected rename to tests/custom/permutations/01_representation/enum/0002_given_permutation_in_param/stdout.expected diff --git a/tests/custom/permutations/01_representation/enum/0003_given_permutation_in_param_2_cycle/permutation.essence b/tests/custom/permutations/01_representation/enum/0003_given_permutation_in_param_2_cycle/permutation.essence new file mode 100644 index 0000000000..35d81d7264 --- /dev/null +++ b/tests/custom/permutations/01_representation/enum/0003_given_permutation_in_param_2_cycle/permutation.essence @@ -0,0 +1,5 @@ +letting n be new type enum {E1,E2,E3,E4} + +given p : permutation of n + +such that true diff --git a/tests/custom/permutations/01_representation/enum/0003_given_permutation_in_param_2_cycle/permutation.param b/tests/custom/permutations/01_representation/enum/0003_given_permutation_in_param_2_cycle/permutation.param new file mode 100644 index 0000000000..34ca085d38 --- /dev/null +++ b/tests/custom/permutations/01_representation/enum/0003_given_permutation_in_param_2_cycle/permutation.param @@ -0,0 +1 @@ +letting p be permutation((E1,E3),(E2,E4)) diff --git a/tests/custom/permutations/01_representation/0003_given_permutation_in_param_2_cycle/run.sh b/tests/custom/permutations/01_representation/enum/0003_given_permutation_in_param_2_cycle/run.sh similarity index 100% rename from tests/custom/permutations/01_representation/0003_given_permutation_in_param_2_cycle/run.sh rename to tests/custom/permutations/01_representation/enum/0003_given_permutation_in_param_2_cycle/run.sh diff --git a/tests/custom/permutations/01_representation/0004_given_permutation_in_param_2_cycle/stdout.expected b/tests/custom/permutations/01_representation/enum/0003_given_permutation_in_param_2_cycle/stdout.expected similarity index 100% rename from tests/custom/permutations/01_representation/0004_given_permutation_in_param_2_cycle/stdout.expected rename to tests/custom/permutations/01_representation/enum/0003_given_permutation_in_param_2_cycle/stdout.expected diff --git a/tests/custom/permutations/01_representation/enum/0004_given_permutation_in_param_2_cycle/permutation.essence b/tests/custom/permutations/01_representation/enum/0004_given_permutation_in_param_2_cycle/permutation.essence new file mode 100644 index 0000000000..35d81d7264 --- /dev/null +++ b/tests/custom/permutations/01_representation/enum/0004_given_permutation_in_param_2_cycle/permutation.essence @@ -0,0 +1,5 @@ +letting n be new type enum {E1,E2,E3,E4} + +given p : permutation of n + +such that true diff --git a/tests/custom/permutations/01_representation/enum/0004_given_permutation_in_param_2_cycle/permutation.param b/tests/custom/permutations/01_representation/enum/0004_given_permutation_in_param_2_cycle/permutation.param new file mode 100644 index 0000000000..34ca085d38 --- /dev/null +++ b/tests/custom/permutations/01_representation/enum/0004_given_permutation_in_param_2_cycle/permutation.param @@ -0,0 +1 @@ +letting p be permutation((E1,E3),(E2,E4)) diff --git a/tests/custom/permutations/01_representation/0004_given_permutation_in_param_2_cycle/run.sh b/tests/custom/permutations/01_representation/enum/0004_given_permutation_in_param_2_cycle/run.sh similarity index 100% rename from tests/custom/permutations/01_representation/0004_given_permutation_in_param_2_cycle/run.sh rename to tests/custom/permutations/01_representation/enum/0004_given_permutation_in_param_2_cycle/run.sh diff --git a/tests/custom/permutations/01_representation/0003_given_permutation_in_param_2_cycle/stdout.expected b/tests/custom/permutations/01_representation/enum/0004_given_permutation_in_param_2_cycle/stdout.expected similarity index 67% rename from tests/custom/permutations/01_representation/0003_given_permutation_in_param_2_cycle/stdout.expected rename to tests/custom/permutations/01_representation/enum/0004_given_permutation_in_param_2_cycle/stdout.expected index a1634e8c4c..1d9c5a0937 100644 --- a/tests/custom/permutations/01_representation/0003_given_permutation_in_param_2_cycle/stdout.expected +++ b/tests/custom/permutations/01_representation/enum/0004_given_permutation_in_param_2_cycle/stdout.expected @@ -2,3 +2,6 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output Savile Row: model000001.eprime permutation.param +Copying solution to: permutation-permutation.solution +language Essence 1.3 + diff --git a/tests/custom/permutations/01_representation/enum/0005_find_permutation_size_4_of_int1_4/permutation.essence b/tests/custom/permutations/01_representation/enum/0005_find_permutation_size_4_of_int1_4/permutation.essence new file mode 100644 index 0000000000..26786093fd --- /dev/null +++ b/tests/custom/permutations/01_representation/enum/0005_find_permutation_size_4_of_int1_4/permutation.essence @@ -0,0 +1,5 @@ +letting n be new type enum {E1,E2,E3,E4} + +find p : permutation (size 4) of n + +such that true diff --git a/tests/custom/permutations/01_representation/0005_find_permutation_size_4_of_int1_4/run.sh b/tests/custom/permutations/01_representation/enum/0005_find_permutation_size_4_of_int1_4/run.sh similarity index 100% rename from tests/custom/permutations/01_representation/0005_find_permutation_size_4_of_int1_4/run.sh rename to tests/custom/permutations/01_representation/enum/0005_find_permutation_size_4_of_int1_4/run.sh diff --git a/tests/custom/permutations/01_representation/enum/0005_find_permutation_size_4_of_int1_4/stdout.expected b/tests/custom/permutations/01_representation/enum/0005_find_permutation_size_4_of_int1_4/stdout.expected new file mode 100644 index 0000000000..ce19884f53 --- /dev/null +++ b/tests/custom/permutations/01_representation/enum/0005_find_permutation_size_4_of_int1_4/stdout.expected @@ -0,0 +1,40 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Copying solution to: permutation-000001.solution +Copying solution to: permutation-000002.solution +Copying solution to: permutation-000003.solution +Copying solution to: permutation-000004.solution +Copying solution to: permutation-000005.solution +Copying solution to: permutation-000006.solution +Copying solution to: permutation-000007.solution +Copying solution to: permutation-000008.solution +Copying solution to: permutation-000009.solution +language Essence 1.3 + +letting p be permutation((E1, E2), (E3, E4)) +language Essence 1.3 + +letting p be permutation((E1, E2, E3, E4)) +language Essence 1.3 + +letting p be permutation((E1, E2, E4, E3)) +language Essence 1.3 + +letting p be permutation((E1, E3, E4, E2)) +language Essence 1.3 + +letting p be permutation((E1, E3), (E2, E4)) +language Essence 1.3 + +letting p be permutation((E1, E3, E2, E4)) +language Essence 1.3 + +letting p be permutation((E1, E4, E3, E2)) +language Essence 1.3 + +letting p be permutation((E1, E4, E2, E3)) +language Essence 1.3 + +letting p be permutation((E1, E4), (E2, E3)) diff --git a/tests/custom/permutations/01_representation/enum/0006_find_permutation_size_0_of_int1_4/permutation.essence b/tests/custom/permutations/01_representation/enum/0006_find_permutation_size_0_of_int1_4/permutation.essence new file mode 100644 index 0000000000..9a91f2f8d1 --- /dev/null +++ b/tests/custom/permutations/01_representation/enum/0006_find_permutation_size_0_of_int1_4/permutation.essence @@ -0,0 +1,5 @@ +letting n be new type enum {E1,E2,E3,E4} + +find p : permutation (size 0) of n + +such that true diff --git a/tests/custom/permutations/01_representation/0006_find_permutation_size_0_of_int1_4/run.sh b/tests/custom/permutations/01_representation/enum/0006_find_permutation_size_0_of_int1_4/run.sh similarity index 100% rename from tests/custom/permutations/01_representation/0006_find_permutation_size_0_of_int1_4/run.sh rename to tests/custom/permutations/01_representation/enum/0006_find_permutation_size_0_of_int1_4/run.sh diff --git a/tests/custom/permutations/01_representation/0006_find_permutation_size_0_of_int1_4/stdout.expected b/tests/custom/permutations/01_representation/enum/0006_find_permutation_size_0_of_int1_4/stdout.expected similarity index 100% rename from tests/custom/permutations/01_representation/0006_find_permutation_size_0_of_int1_4/stdout.expected rename to tests/custom/permutations/01_representation/enum/0006_find_permutation_size_0_of_int1_4/stdout.expected diff --git a/tests/custom/permutations/01_representation/0007_letting_permutation_be_empty/permutation.essence b/tests/custom/permutations/01_representation/enum/0007_letting_permutation_be_empty/permutation.essence similarity index 100% rename from tests/custom/permutations/01_representation/0007_letting_permutation_be_empty/permutation.essence rename to tests/custom/permutations/01_representation/enum/0007_letting_permutation_be_empty/permutation.essence diff --git a/tests/custom/permutations/01_representation/0007_letting_permutation_be_empty/run.sh b/tests/custom/permutations/01_representation/enum/0007_letting_permutation_be_empty/run.sh similarity index 100% rename from tests/custom/permutations/01_representation/0007_letting_permutation_be_empty/run.sh rename to tests/custom/permutations/01_representation/enum/0007_letting_permutation_be_empty/run.sh diff --git a/tests/custom/permutations/01_representation/0007_letting_permutation_be_empty/stdout.expected b/tests/custom/permutations/01_representation/enum/0007_letting_permutation_be_empty/stdout.expected similarity index 100% rename from tests/custom/permutations/01_representation/0007_letting_permutation_be_empty/stdout.expected rename to tests/custom/permutations/01_representation/enum/0007_letting_permutation_be_empty/stdout.expected diff --git a/tests/custom/permutations/01_representation/enum/0008_find_permutation_of_int1_4/permutation.essence b/tests/custom/permutations/01_representation/enum/0008_find_permutation_of_int1_4/permutation.essence new file mode 100644 index 0000000000..87e671ee38 --- /dev/null +++ b/tests/custom/permutations/01_representation/enum/0008_find_permutation_of_int1_4/permutation.essence @@ -0,0 +1,5 @@ +letting n be new type enum {E1,E2,E3,E4} + +find p : permutation of n + +such that true diff --git a/tests/custom/permutations/01_representation/0008_find_permutation_of_int1_4/run.sh b/tests/custom/permutations/01_representation/enum/0008_find_permutation_of_int1_4/run.sh similarity index 100% rename from tests/custom/permutations/01_representation/0008_find_permutation_of_int1_4/run.sh rename to tests/custom/permutations/01_representation/enum/0008_find_permutation_of_int1_4/run.sh diff --git a/tests/custom/permutations/01_representation/enum/0008_find_permutation_of_int1_4/stdout.expected b/tests/custom/permutations/01_representation/enum/0008_find_permutation_of_int1_4/stdout.expected new file mode 100644 index 0000000000..e2b59fc509 --- /dev/null +++ b/tests/custom/permutations/01_representation/enum/0008_find_permutation_of_int1_4/stdout.expected @@ -0,0 +1,100 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Copying solution to: permutation-000001.solution +Copying solution to: permutation-000002.solution +Copying solution to: permutation-000003.solution +Copying solution to: permutation-000004.solution +Copying solution to: permutation-000005.solution +Copying solution to: permutation-000006.solution +Copying solution to: permutation-000007.solution +Copying solution to: permutation-000008.solution +Copying solution to: permutation-000009.solution +Copying solution to: permutation-000010.solution +Copying solution to: permutation-000011.solution +Copying solution to: permutation-000012.solution +Copying solution to: permutation-000013.solution +Copying solution to: permutation-000014.solution +Copying solution to: permutation-000015.solution +Copying solution to: permutation-000016.solution +Copying solution to: permutation-000017.solution +Copying solution to: permutation-000018.solution +Copying solution to: permutation-000019.solution +Copying solution to: permutation-000020.solution +Copying solution to: permutation-000021.solution +Copying solution to: permutation-000022.solution +Copying solution to: permutation-000023.solution +Copying solution to: permutation-000024.solution +language Essence 1.3 + +letting p be permutation() +language Essence 1.3 + +letting p be permutation((E3, E4)) +language Essence 1.3 + +letting p be permutation((E2, E3)) +language Essence 1.3 + +letting p be permutation((E2, E3, E4)) +language Essence 1.3 + +letting p be permutation((E2, E4, E3)) +language Essence 1.3 + +letting p be permutation((E2, E4)) +language Essence 1.3 + +letting p be permutation((E1, E2)) +language Essence 1.3 + +letting p be permutation((E1, E2), (E3, E4)) +language Essence 1.3 + +letting p be permutation((E1, E2, E3)) +language Essence 1.3 + +letting p be permutation((E1, E2, E3, E4)) +language Essence 1.3 + +letting p be permutation((E1, E2, E4, E3)) +language Essence 1.3 + +letting p be permutation((E1, E2, E4)) +language Essence 1.3 + +letting p be permutation((E1, E3, E2)) +language Essence 1.3 + +letting p be permutation((E1, E3, E4, E2)) +language Essence 1.3 + +letting p be permutation((E1, E3)) +language Essence 1.3 + +letting p be permutation((E1, E3, E4)) +language Essence 1.3 + +letting p be permutation((E1, E3), (E2, E4)) +language Essence 1.3 + +letting p be permutation((E1, E3, E2, E4)) +language Essence 1.3 + +letting p be permutation((E1, E4, E3, E2)) +language Essence 1.3 + +letting p be permutation((E1, E4, E2)) +language Essence 1.3 + +letting p be permutation((E1, E4, E3)) +language Essence 1.3 + +letting p be permutation((E1, E4)) +language Essence 1.3 + +letting p be permutation((E1, E4, E2, E3)) +language Essence 1.3 + +letting p be permutation((E1, E4), (E2, E3)) diff --git a/tests/custom/permutations/01_representation/enum/0009_letting_permutation_in_model/permutation.essence b/tests/custom/permutations/01_representation/enum/0009_letting_permutation_in_model/permutation.essence new file mode 100644 index 0000000000..93739e5f4e --- /dev/null +++ b/tests/custom/permutations/01_representation/enum/0009_letting_permutation_in_model/permutation.essence @@ -0,0 +1,4 @@ +letting n be new type enum {E1,E2,E3,E4} +letting p be permutation((E1,E3),(E2,E4)) + +such that true diff --git a/tests/custom/permutations/01_representation/0009_letting_permutation_in_model/run.sh b/tests/custom/permutations/01_representation/enum/0009_letting_permutation_in_model/run.sh similarity index 100% rename from tests/custom/permutations/01_representation/0009_letting_permutation_in_model/run.sh rename to tests/custom/permutations/01_representation/enum/0009_letting_permutation_in_model/run.sh diff --git a/tests/custom/permutations/01_representation/0009_letting_permutation_in_model/stdout.expected b/tests/custom/permutations/01_representation/enum/0009_letting_permutation_in_model/stdout.expected similarity index 100% rename from tests/custom/permutations/01_representation/0009_letting_permutation_in_model/stdout.expected rename to tests/custom/permutations/01_representation/enum/0009_letting_permutation_in_model/stdout.expected diff --git a/tests/custom/permutations/01_representation/enum/0010_find_permutation_maxSize_2_of_int1_3/permutation.essence b/tests/custom/permutations/01_representation/enum/0010_find_permutation_maxSize_2_of_int1_3/permutation.essence new file mode 100644 index 0000000000..5e23322970 --- /dev/null +++ b/tests/custom/permutations/01_representation/enum/0010_find_permutation_maxSize_2_of_int1_3/permutation.essence @@ -0,0 +1,5 @@ +letting n be new type enum {E1,E2,E3} + +find p : permutation (maxSize 2) of n + +such that true diff --git a/tests/custom/permutations/01_representation/0010_find_permutation_maxSize_2_of_int1_3/run.sh b/tests/custom/permutations/01_representation/enum/0010_find_permutation_maxSize_2_of_int1_3/run.sh similarity index 100% rename from tests/custom/permutations/01_representation/0010_find_permutation_maxSize_2_of_int1_3/run.sh rename to tests/custom/permutations/01_representation/enum/0010_find_permutation_maxSize_2_of_int1_3/run.sh diff --git a/tests/custom/permutations/01_representation/enum/0010_find_permutation_maxSize_2_of_int1_3/stdout.expected b/tests/custom/permutations/01_representation/enum/0010_find_permutation_maxSize_2_of_int1_3/stdout.expected new file mode 100644 index 0000000000..4c32b78bd3 --- /dev/null +++ b/tests/custom/permutations/01_representation/enum/0010_find_permutation_maxSize_2_of_int1_3/stdout.expected @@ -0,0 +1,20 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Copying solution to: permutation-000001.solution +Copying solution to: permutation-000002.solution +Copying solution to: permutation-000003.solution +Copying solution to: permutation-000004.solution +language Essence 1.3 + +letting p be permutation() +language Essence 1.3 + +letting p be permutation((E2, E3)) +language Essence 1.3 + +letting p be permutation((E1, E2)) +language Essence 1.3 + +letting p be permutation((E1, E3)) diff --git a/tests/custom/permutations/01_representation/enum/0011_find_permutation_minSize_2_of_int1_3/permutation.essence b/tests/custom/permutations/01_representation/enum/0011_find_permutation_minSize_2_of_int1_3/permutation.essence new file mode 100644 index 0000000000..3da37a3987 --- /dev/null +++ b/tests/custom/permutations/01_representation/enum/0011_find_permutation_minSize_2_of_int1_3/permutation.essence @@ -0,0 +1,5 @@ +letting n be new type enum {E1,E2,E3} + +find p : permutation (minSize 2) of n + +such that true diff --git a/tests/custom/permutations/01_representation/0011_find_permutation_minSize_2_of_int1_3/run.sh b/tests/custom/permutations/01_representation/enum/0011_find_permutation_minSize_2_of_int1_3/run.sh similarity index 100% rename from tests/custom/permutations/01_representation/0011_find_permutation_minSize_2_of_int1_3/run.sh rename to tests/custom/permutations/01_representation/enum/0011_find_permutation_minSize_2_of_int1_3/run.sh diff --git a/tests/custom/permutations/01_representation/enum/0011_find_permutation_minSize_2_of_int1_3/stdout.expected b/tests/custom/permutations/01_representation/enum/0011_find_permutation_minSize_2_of_int1_3/stdout.expected new file mode 100644 index 0000000000..413528d411 --- /dev/null +++ b/tests/custom/permutations/01_representation/enum/0011_find_permutation_minSize_2_of_int1_3/stdout.expected @@ -0,0 +1,24 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Copying solution to: permutation-000001.solution +Copying solution to: permutation-000002.solution +Copying solution to: permutation-000003.solution +Copying solution to: permutation-000004.solution +Copying solution to: permutation-000005.solution +language Essence 1.3 + +letting p be permutation((E2, E3)) +language Essence 1.3 + +letting p be permutation((E1, E2)) +language Essence 1.3 + +letting p be permutation((E1, E2, E3)) +language Essence 1.3 + +letting p be permutation((E1, E3, E2)) +language Essence 1.3 + +letting p be permutation((E1, E3)) diff --git a/tests/custom/permutations/01_representation/enum/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/permutation.essence b/tests/custom/permutations/01_representation/enum/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/permutation.essence new file mode 100644 index 0000000000..6fc7ffd73a --- /dev/null +++ b/tests/custom/permutations/01_representation/enum/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/permutation.essence @@ -0,0 +1,5 @@ +letting n be new type enum {E1,E2,E3,E4} + +find p : permutation (minSize 2, maxSize 3) of n + +such that true diff --git a/tests/custom/permutations/01_representation/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/run.sh b/tests/custom/permutations/01_representation/enum/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/run.sh similarity index 100% rename from tests/custom/permutations/01_representation/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/run.sh rename to tests/custom/permutations/01_representation/enum/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/run.sh diff --git a/tests/custom/permutations/01_representation/enum/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/stdout.expected b/tests/custom/permutations/01_representation/enum/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/stdout.expected new file mode 100644 index 0000000000..37f88cd8fb --- /dev/null +++ b/tests/custom/permutations/01_representation/enum/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/stdout.expected @@ -0,0 +1,60 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Copying solution to: permutation-000001.solution +Copying solution to: permutation-000002.solution +Copying solution to: permutation-000003.solution +Copying solution to: permutation-000004.solution +Copying solution to: permutation-000005.solution +Copying solution to: permutation-000006.solution +Copying solution to: permutation-000007.solution +Copying solution to: permutation-000008.solution +Copying solution to: permutation-000009.solution +Copying solution to: permutation-000010.solution +Copying solution to: permutation-000011.solution +Copying solution to: permutation-000012.solution +Copying solution to: permutation-000013.solution +Copying solution to: permutation-000014.solution +language Essence 1.3 + +letting p be permutation((E3, E4)) +language Essence 1.3 + +letting p be permutation((E2, E3)) +language Essence 1.3 + +letting p be permutation((E2, E3, E4)) +language Essence 1.3 + +letting p be permutation((E2, E4, E3)) +language Essence 1.3 + +letting p be permutation((E2, E4)) +language Essence 1.3 + +letting p be permutation((E1, E2)) +language Essence 1.3 + +letting p be permutation((E1, E2, E3)) +language Essence 1.3 + +letting p be permutation((E1, E2, E4)) +language Essence 1.3 + +letting p be permutation((E1, E3, E2)) +language Essence 1.3 + +letting p be permutation((E1, E3)) +language Essence 1.3 + +letting p be permutation((E1, E3, E4)) +language Essence 1.3 + +letting p be permutation((E1, E4, E2)) +language Essence 1.3 + +letting p be permutation((E1, E4, E3)) +language Essence 1.3 + +letting p be permutation((E1, E4)) diff --git a/tests/custom/permutations/01_representation/0001_given_permutation_in_param/permutation.essence b/tests/custom/permutations/01_representation/int/0001_given_permutation_in_param/permutation.essence similarity index 100% rename from tests/custom/permutations/01_representation/0001_given_permutation_in_param/permutation.essence rename to tests/custom/permutations/01_representation/int/0001_given_permutation_in_param/permutation.essence diff --git a/tests/custom/permutations/01_representation/0001_given_permutation_in_param/permutation.param b/tests/custom/permutations/01_representation/int/0001_given_permutation_in_param/permutation.param similarity index 100% rename from tests/custom/permutations/01_representation/0001_given_permutation_in_param/permutation.param rename to tests/custom/permutations/01_representation/int/0001_given_permutation_in_param/permutation.param diff --git a/tests/custom/permutations/01_representation/int/0001_given_permutation_in_param/run.sh b/tests/custom/permutations/01_representation/int/0001_given_permutation_in_param/run.sh new file mode 100755 index 0000000000..9dc67e67f5 --- /dev/null +++ b/tests/custom/permutations/01_representation/int/0001_given_permutation_in_param/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence *.param +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/01_representation/int/0001_given_permutation_in_param/stdout.expected b/tests/custom/permutations/01_representation/int/0001_given_permutation_in_param/stdout.expected new file mode 100644 index 0000000000..1d9c5a0937 --- /dev/null +++ b/tests/custom/permutations/01_representation/int/0001_given_permutation_in_param/stdout.expected @@ -0,0 +1,7 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime permutation.param +Copying solution to: permutation-permutation.solution +language Essence 1.3 + diff --git a/tests/custom/permutations/01_representation/0002_given_permutation_in_param/permutation.essence b/tests/custom/permutations/01_representation/int/0002_given_permutation_in_param/permutation.essence similarity index 100% rename from tests/custom/permutations/01_representation/0002_given_permutation_in_param/permutation.essence rename to tests/custom/permutations/01_representation/int/0002_given_permutation_in_param/permutation.essence diff --git a/tests/custom/permutations/01_representation/0002_given_permutation_in_param/permutation.param b/tests/custom/permutations/01_representation/int/0002_given_permutation_in_param/permutation.param similarity index 100% rename from tests/custom/permutations/01_representation/0002_given_permutation_in_param/permutation.param rename to tests/custom/permutations/01_representation/int/0002_given_permutation_in_param/permutation.param diff --git a/tests/custom/permutations/01_representation/int/0002_given_permutation_in_param/run.sh b/tests/custom/permutations/01_representation/int/0002_given_permutation_in_param/run.sh new file mode 100755 index 0000000000..9dc67e67f5 --- /dev/null +++ b/tests/custom/permutations/01_representation/int/0002_given_permutation_in_param/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence *.param +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/01_representation/int/0002_given_permutation_in_param/stdout.expected b/tests/custom/permutations/01_representation/int/0002_given_permutation_in_param/stdout.expected new file mode 100644 index 0000000000..1d9c5a0937 --- /dev/null +++ b/tests/custom/permutations/01_representation/int/0002_given_permutation_in_param/stdout.expected @@ -0,0 +1,7 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime permutation.param +Copying solution to: permutation-permutation.solution +language Essence 1.3 + diff --git a/tests/custom/permutations/01_representation/0004_given_permutation_in_param_2_cycle/permutation.essence b/tests/custom/permutations/01_representation/int/0003_given_permutation_in_param_2_cycle/permutation.essence similarity index 100% rename from tests/custom/permutations/01_representation/0004_given_permutation_in_param_2_cycle/permutation.essence rename to tests/custom/permutations/01_representation/int/0003_given_permutation_in_param_2_cycle/permutation.essence diff --git a/tests/custom/permutations/01_representation/0003_given_permutation_in_param_2_cycle/permutation.param b/tests/custom/permutations/01_representation/int/0003_given_permutation_in_param_2_cycle/permutation.param similarity index 100% rename from tests/custom/permutations/01_representation/0003_given_permutation_in_param_2_cycle/permutation.param rename to tests/custom/permutations/01_representation/int/0003_given_permutation_in_param_2_cycle/permutation.param diff --git a/tests/custom/permutations/01_representation/int/0003_given_permutation_in_param_2_cycle/run.sh b/tests/custom/permutations/01_representation/int/0003_given_permutation_in_param_2_cycle/run.sh new file mode 100755 index 0000000000..9dc67e67f5 --- /dev/null +++ b/tests/custom/permutations/01_representation/int/0003_given_permutation_in_param_2_cycle/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence *.param +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/01_representation/int/0003_given_permutation_in_param_2_cycle/stdout.expected b/tests/custom/permutations/01_representation/int/0003_given_permutation_in_param_2_cycle/stdout.expected new file mode 100644 index 0000000000..1d9c5a0937 --- /dev/null +++ b/tests/custom/permutations/01_representation/int/0003_given_permutation_in_param_2_cycle/stdout.expected @@ -0,0 +1,7 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime permutation.param +Copying solution to: permutation-permutation.solution +language Essence 1.3 + diff --git a/tests/custom/permutations/01_representation/0003_given_permutation_in_param_2_cycle/permutation.essence b/tests/custom/permutations/01_representation/int/0004_given_permutation_in_param_2_cycle/permutation.essence similarity index 77% rename from tests/custom/permutations/01_representation/0003_given_permutation_in_param_2_cycle/permutation.essence rename to tests/custom/permutations/01_representation/int/0004_given_permutation_in_param_2_cycle/permutation.essence index 4d613e1dc6..fff346c07e 100644 --- a/tests/custom/permutations/01_representation/0003_given_permutation_in_param_2_cycle/permutation.essence +++ b/tests/custom/permutations/01_representation/int/0004_given_permutation_in_param_2_cycle/permutation.essence @@ -1,4 +1,4 @@ -letting n be 3 +letting n be 4 given p : permutation of int(1..n) diff --git a/tests/custom/permutations/01_representation/0004_given_permutation_in_param_2_cycle/permutation.param b/tests/custom/permutations/01_representation/int/0004_given_permutation_in_param_2_cycle/permutation.param similarity index 100% rename from tests/custom/permutations/01_representation/0004_given_permutation_in_param_2_cycle/permutation.param rename to tests/custom/permutations/01_representation/int/0004_given_permutation_in_param_2_cycle/permutation.param diff --git a/tests/custom/permutations/01_representation/int/0004_given_permutation_in_param_2_cycle/run.sh b/tests/custom/permutations/01_representation/int/0004_given_permutation_in_param_2_cycle/run.sh new file mode 100755 index 0000000000..9dc67e67f5 --- /dev/null +++ b/tests/custom/permutations/01_representation/int/0004_given_permutation_in_param_2_cycle/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence *.param +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/01_representation/int/0004_given_permutation_in_param_2_cycle/stdout.expected b/tests/custom/permutations/01_representation/int/0004_given_permutation_in_param_2_cycle/stdout.expected new file mode 100644 index 0000000000..1d9c5a0937 --- /dev/null +++ b/tests/custom/permutations/01_representation/int/0004_given_permutation_in_param_2_cycle/stdout.expected @@ -0,0 +1,7 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime permutation.param +Copying solution to: permutation-permutation.solution +language Essence 1.3 + diff --git a/tests/custom/permutations/01_representation/0005_find_permutation_size_4_of_int1_4/permutation.essence b/tests/custom/permutations/01_representation/int/0005_find_permutation_size_4_of_int1_4/permutation.essence similarity index 100% rename from tests/custom/permutations/01_representation/0005_find_permutation_size_4_of_int1_4/permutation.essence rename to tests/custom/permutations/01_representation/int/0005_find_permutation_size_4_of_int1_4/permutation.essence diff --git a/tests/custom/permutations/01_representation/0005_find_permutation_size_4_of_int1_4/permutation.param b/tests/custom/permutations/01_representation/int/0005_find_permutation_size_4_of_int1_4/permutation.param similarity index 100% rename from tests/custom/permutations/01_representation/0005_find_permutation_size_4_of_int1_4/permutation.param rename to tests/custom/permutations/01_representation/int/0005_find_permutation_size_4_of_int1_4/permutation.param diff --git a/tests/custom/permutations/01_representation/int/0005_find_permutation_size_4_of_int1_4/run.sh b/tests/custom/permutations/01_representation/int/0005_find_permutation_size_4_of_int1_4/run.sh new file mode 100755 index 0000000000..7238b9c9c7 --- /dev/null +++ b/tests/custom/permutations/01_representation/int/0005_find_permutation_size_4_of_int1_4/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence --number-of-solutions=100 +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/01_representation/0005_find_permutation_size_4_of_int1_4/stdout.expected b/tests/custom/permutations/01_representation/int/0005_find_permutation_size_4_of_int1_4/stdout.expected similarity index 100% rename from tests/custom/permutations/01_representation/0005_find_permutation_size_4_of_int1_4/stdout.expected rename to tests/custom/permutations/01_representation/int/0005_find_permutation_size_4_of_int1_4/stdout.expected diff --git a/tests/custom/permutations/01_representation/0006_find_permutation_size_0_of_int1_4/permutation.essence b/tests/custom/permutations/01_representation/int/0006_find_permutation_size_0_of_int1_4/permutation.essence similarity index 100% rename from tests/custom/permutations/01_representation/0006_find_permutation_size_0_of_int1_4/permutation.essence rename to tests/custom/permutations/01_representation/int/0006_find_permutation_size_0_of_int1_4/permutation.essence diff --git a/tests/custom/permutations/01_representation/0006_find_permutation_size_0_of_int1_4/permutation.param b/tests/custom/permutations/01_representation/int/0006_find_permutation_size_0_of_int1_4/permutation.param similarity index 100% rename from tests/custom/permutations/01_representation/0006_find_permutation_size_0_of_int1_4/permutation.param rename to tests/custom/permutations/01_representation/int/0006_find_permutation_size_0_of_int1_4/permutation.param diff --git a/tests/custom/permutations/01_representation/int/0006_find_permutation_size_0_of_int1_4/run.sh b/tests/custom/permutations/01_representation/int/0006_find_permutation_size_0_of_int1_4/run.sh new file mode 100755 index 0000000000..7238b9c9c7 --- /dev/null +++ b/tests/custom/permutations/01_representation/int/0006_find_permutation_size_0_of_int1_4/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence --number-of-solutions=100 +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/01_representation/int/0006_find_permutation_size_0_of_int1_4/stdout.expected b/tests/custom/permutations/01_representation/int/0006_find_permutation_size_0_of_int1_4/stdout.expected new file mode 100644 index 0000000000..6003fd8115 --- /dev/null +++ b/tests/custom/permutations/01_representation/int/0006_find_permutation_size_0_of_int1_4/stdout.expected @@ -0,0 +1,8 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Copying solution to: permutation.solution +language Essence 1.3 + +letting p be permutation() diff --git a/tests/custom/permutations/01_representation/int/0007_letting_permutation_be_empty/permutation.essence b/tests/custom/permutations/01_representation/int/0007_letting_permutation_be_empty/permutation.essence new file mode 100644 index 0000000000..a39f3ae0b1 --- /dev/null +++ b/tests/custom/permutations/01_representation/int/0007_letting_permutation_be_empty/permutation.essence @@ -0,0 +1,3 @@ +letting p be permutation() + +such that true diff --git a/tests/custom/permutations/01_representation/0007_letting_permutation_be_empty/permutation.param b/tests/custom/permutations/01_representation/int/0007_letting_permutation_be_empty/permutation.param similarity index 100% rename from tests/custom/permutations/01_representation/0007_letting_permutation_be_empty/permutation.param rename to tests/custom/permutations/01_representation/int/0007_letting_permutation_be_empty/permutation.param diff --git a/tests/custom/permutations/01_representation/int/0007_letting_permutation_be_empty/run.sh b/tests/custom/permutations/01_representation/int/0007_letting_permutation_be_empty/run.sh new file mode 100755 index 0000000000..7238b9c9c7 --- /dev/null +++ b/tests/custom/permutations/01_representation/int/0007_letting_permutation_be_empty/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence --number-of-solutions=100 +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/01_representation/int/0007_letting_permutation_be_empty/stdout.expected b/tests/custom/permutations/01_representation/int/0007_letting_permutation_be_empty/stdout.expected new file mode 100644 index 0000000000..3a55885cbc --- /dev/null +++ b/tests/custom/permutations/01_representation/int/0007_letting_permutation_be_empty/stdout.expected @@ -0,0 +1,7 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Copying solution to: permutation.solution +language Essence 1.3 + diff --git a/tests/custom/permutations/01_representation/0008_find_permutation_of_int1_4/permutation.essence b/tests/custom/permutations/01_representation/int/0008_find_permutation_of_int1_4/permutation.essence similarity index 100% rename from tests/custom/permutations/01_representation/0008_find_permutation_of_int1_4/permutation.essence rename to tests/custom/permutations/01_representation/int/0008_find_permutation_of_int1_4/permutation.essence diff --git a/tests/custom/permutations/01_representation/0008_find_permutation_of_int1_4/permutation.param b/tests/custom/permutations/01_representation/int/0008_find_permutation_of_int1_4/permutation.param similarity index 100% rename from tests/custom/permutations/01_representation/0008_find_permutation_of_int1_4/permutation.param rename to tests/custom/permutations/01_representation/int/0008_find_permutation_of_int1_4/permutation.param diff --git a/tests/custom/permutations/01_representation/int/0008_find_permutation_of_int1_4/run.sh b/tests/custom/permutations/01_representation/int/0008_find_permutation_of_int1_4/run.sh new file mode 100755 index 0000000000..7238b9c9c7 --- /dev/null +++ b/tests/custom/permutations/01_representation/int/0008_find_permutation_of_int1_4/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence --number-of-solutions=100 +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/01_representation/0008_find_permutation_of_int1_4/stdout.expected b/tests/custom/permutations/01_representation/int/0008_find_permutation_of_int1_4/stdout.expected similarity index 100% rename from tests/custom/permutations/01_representation/0008_find_permutation_of_int1_4/stdout.expected rename to tests/custom/permutations/01_representation/int/0008_find_permutation_of_int1_4/stdout.expected diff --git a/tests/custom/permutations/01_representation/0009_letting_permutation_in_model/permutation.essence b/tests/custom/permutations/01_representation/int/0009_letting_permutation_in_model/permutation.essence similarity index 100% rename from tests/custom/permutations/01_representation/0009_letting_permutation_in_model/permutation.essence rename to tests/custom/permutations/01_representation/int/0009_letting_permutation_in_model/permutation.essence diff --git a/tests/custom/permutations/01_representation/int/0009_letting_permutation_in_model/run.sh b/tests/custom/permutations/01_representation/int/0009_letting_permutation_in_model/run.sh new file mode 100755 index 0000000000..b4899d6266 --- /dev/null +++ b/tests/custom/permutations/01_representation/int/0009_letting_permutation_in_model/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/01_representation/int/0009_letting_permutation_in_model/stdout.expected b/tests/custom/permutations/01_representation/int/0009_letting_permutation_in_model/stdout.expected new file mode 100644 index 0000000000..3a55885cbc --- /dev/null +++ b/tests/custom/permutations/01_representation/int/0009_letting_permutation_in_model/stdout.expected @@ -0,0 +1,7 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Copying solution to: permutation.solution +language Essence 1.3 + diff --git a/tests/custom/permutations/01_representation/0010_find_permutation_maxSize_2_of_int1_3/permutation.essence b/tests/custom/permutations/01_representation/int/0010_find_permutation_maxSize_2_of_int1_3/permutation.essence similarity index 100% rename from tests/custom/permutations/01_representation/0010_find_permutation_maxSize_2_of_int1_3/permutation.essence rename to tests/custom/permutations/01_representation/int/0010_find_permutation_maxSize_2_of_int1_3/permutation.essence diff --git a/tests/custom/permutations/01_representation/0010_find_permutation_maxSize_2_of_int1_3/permutation.param b/tests/custom/permutations/01_representation/int/0010_find_permutation_maxSize_2_of_int1_3/permutation.param similarity index 100% rename from tests/custom/permutations/01_representation/0010_find_permutation_maxSize_2_of_int1_3/permutation.param rename to tests/custom/permutations/01_representation/int/0010_find_permutation_maxSize_2_of_int1_3/permutation.param diff --git a/tests/custom/permutations/01_representation/int/0010_find_permutation_maxSize_2_of_int1_3/run.sh b/tests/custom/permutations/01_representation/int/0010_find_permutation_maxSize_2_of_int1_3/run.sh new file mode 100755 index 0000000000..7238b9c9c7 --- /dev/null +++ b/tests/custom/permutations/01_representation/int/0010_find_permutation_maxSize_2_of_int1_3/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence --number-of-solutions=100 +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/01_representation/0010_find_permutation_maxSize_2_of_int1_3/stdout.expected b/tests/custom/permutations/01_representation/int/0010_find_permutation_maxSize_2_of_int1_3/stdout.expected similarity index 100% rename from tests/custom/permutations/01_representation/0010_find_permutation_maxSize_2_of_int1_3/stdout.expected rename to tests/custom/permutations/01_representation/int/0010_find_permutation_maxSize_2_of_int1_3/stdout.expected diff --git a/tests/custom/permutations/01_representation/0011_find_permutation_minSize_2_of_int1_3/permutation.essence b/tests/custom/permutations/01_representation/int/0011_find_permutation_minSize_2_of_int1_3/permutation.essence similarity index 100% rename from tests/custom/permutations/01_representation/0011_find_permutation_minSize_2_of_int1_3/permutation.essence rename to tests/custom/permutations/01_representation/int/0011_find_permutation_minSize_2_of_int1_3/permutation.essence diff --git a/tests/custom/permutations/01_representation/0011_find_permutation_minSize_2_of_int1_3/permutation.param b/tests/custom/permutations/01_representation/int/0011_find_permutation_minSize_2_of_int1_3/permutation.param similarity index 100% rename from tests/custom/permutations/01_representation/0011_find_permutation_minSize_2_of_int1_3/permutation.param rename to tests/custom/permutations/01_representation/int/0011_find_permutation_minSize_2_of_int1_3/permutation.param diff --git a/tests/custom/permutations/01_representation/int/0011_find_permutation_minSize_2_of_int1_3/run.sh b/tests/custom/permutations/01_representation/int/0011_find_permutation_minSize_2_of_int1_3/run.sh new file mode 100755 index 0000000000..7238b9c9c7 --- /dev/null +++ b/tests/custom/permutations/01_representation/int/0011_find_permutation_minSize_2_of_int1_3/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence --number-of-solutions=100 +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/01_representation/0011_find_permutation_minSize_2_of_int1_3/stdout.expected b/tests/custom/permutations/01_representation/int/0011_find_permutation_minSize_2_of_int1_3/stdout.expected similarity index 100% rename from tests/custom/permutations/01_representation/0011_find_permutation_minSize_2_of_int1_3/stdout.expected rename to tests/custom/permutations/01_representation/int/0011_find_permutation_minSize_2_of_int1_3/stdout.expected diff --git a/tests/custom/permutations/01_representation/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/permutation.essence b/tests/custom/permutations/01_representation/int/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/permutation.essence similarity index 100% rename from tests/custom/permutations/01_representation/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/permutation.essence rename to tests/custom/permutations/01_representation/int/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/permutation.essence diff --git a/tests/custom/permutations/01_representation/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/permutation.param b/tests/custom/permutations/01_representation/int/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/permutation.param similarity index 100% rename from tests/custom/permutations/01_representation/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/permutation.param rename to tests/custom/permutations/01_representation/int/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/permutation.param diff --git a/tests/custom/permutations/01_representation/int/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/run.sh b/tests/custom/permutations/01_representation/int/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/run.sh new file mode 100755 index 0000000000..7238b9c9c7 --- /dev/null +++ b/tests/custom/permutations/01_representation/int/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence --number-of-solutions=100 +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/01_representation/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/stdout.expected b/tests/custom/permutations/01_representation/int/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/stdout.expected similarity index 100% rename from tests/custom/permutations/01_representation/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/stdout.expected rename to tests/custom/permutations/01_representation/int/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/stdout.expected diff --git a/tests/custom/permutations/01_representation/unnamed/0005_find_permutation_size_4_of_int1_4/permutation.essence b/tests/custom/permutations/01_representation/unnamed/0005_find_permutation_size_4_of_int1_4/permutation.essence new file mode 100644 index 0000000000..355a19fd10 --- /dev/null +++ b/tests/custom/permutations/01_representation/unnamed/0005_find_permutation_size_4_of_int1_4/permutation.essence @@ -0,0 +1,5 @@ +letting n be new type of size 4 + +find p : permutation (size 4) of n + +such that true diff --git a/tests/custom/permutations/01_representation/unnamed/0005_find_permutation_size_4_of_int1_4/run.sh b/tests/custom/permutations/01_representation/unnamed/0005_find_permutation_size_4_of_int1_4/run.sh new file mode 100755 index 0000000000..7238b9c9c7 --- /dev/null +++ b/tests/custom/permutations/01_representation/unnamed/0005_find_permutation_size_4_of_int1_4/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence --number-of-solutions=100 +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/01_representation/unnamed/0005_find_permutation_size_4_of_int1_4/stdout.expected b/tests/custom/permutations/01_representation/unnamed/0005_find_permutation_size_4_of_int1_4/stdout.expected new file mode 100644 index 0000000000..56e46df53d --- /dev/null +++ b/tests/custom/permutations/01_representation/unnamed/0005_find_permutation_size_4_of_int1_4/stdout.expected @@ -0,0 +1,49 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Copying solution to: permutation-000001.solution +Copying solution to: permutation-000002.solution +Copying solution to: permutation-000003.solution +Copying solution to: permutation-000004.solution +Copying solution to: permutation-000005.solution +Copying solution to: permutation-000006.solution +Copying solution to: permutation-000007.solution +Copying solution to: permutation-000008.solution +Copying solution to: permutation-000009.solution +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_1, n_2), (n_3, n_4)) +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_1, n_2, n_3, n_4)) +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_1, n_2, n_4, n_3)) +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_1, n_3, n_4, n_2)) +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_1, n_3), (n_2, n_4)) +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_1, n_3, n_2, n_4)) +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_1, n_4, n_3, n_2)) +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_1, n_4, n_2, n_3)) +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_1, n_4), (n_2, n_3)) diff --git a/tests/custom/permutations/01_representation/unnamed/0006_find_permutation_size_0_of_int1_4/permutation.essence b/tests/custom/permutations/01_representation/unnamed/0006_find_permutation_size_0_of_int1_4/permutation.essence new file mode 100644 index 0000000000..264e52e6b7 --- /dev/null +++ b/tests/custom/permutations/01_representation/unnamed/0006_find_permutation_size_0_of_int1_4/permutation.essence @@ -0,0 +1,5 @@ +letting n be new type of size 4 + +find p : permutation (size 0) of n + +such that true diff --git a/tests/custom/permutations/01_representation/unnamed/0006_find_permutation_size_0_of_int1_4/run.sh b/tests/custom/permutations/01_representation/unnamed/0006_find_permutation_size_0_of_int1_4/run.sh new file mode 100755 index 0000000000..7238b9c9c7 --- /dev/null +++ b/tests/custom/permutations/01_representation/unnamed/0006_find_permutation_size_0_of_int1_4/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence --number-of-solutions=100 +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/01_representation/unnamed/0006_find_permutation_size_0_of_int1_4/stdout.expected b/tests/custom/permutations/01_representation/unnamed/0006_find_permutation_size_0_of_int1_4/stdout.expected new file mode 100644 index 0000000000..1584142e60 --- /dev/null +++ b/tests/custom/permutations/01_representation/unnamed/0006_find_permutation_size_0_of_int1_4/stdout.expected @@ -0,0 +1,9 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Copying solution to: permutation.solution +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation() diff --git a/tests/custom/permutations/01_representation/unnamed/0007_letting_permutation_be_empty/permutation.essence b/tests/custom/permutations/01_representation/unnamed/0007_letting_permutation_be_empty/permutation.essence new file mode 100644 index 0000000000..a39f3ae0b1 --- /dev/null +++ b/tests/custom/permutations/01_representation/unnamed/0007_letting_permutation_be_empty/permutation.essence @@ -0,0 +1,3 @@ +letting p be permutation() + +such that true diff --git a/tests/custom/permutations/01_representation/unnamed/0007_letting_permutation_be_empty/run.sh b/tests/custom/permutations/01_representation/unnamed/0007_letting_permutation_be_empty/run.sh new file mode 100755 index 0000000000..7238b9c9c7 --- /dev/null +++ b/tests/custom/permutations/01_representation/unnamed/0007_letting_permutation_be_empty/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence --number-of-solutions=100 +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/01_representation/unnamed/0007_letting_permutation_be_empty/stdout.expected b/tests/custom/permutations/01_representation/unnamed/0007_letting_permutation_be_empty/stdout.expected new file mode 100644 index 0000000000..3a55885cbc --- /dev/null +++ b/tests/custom/permutations/01_representation/unnamed/0007_letting_permutation_be_empty/stdout.expected @@ -0,0 +1,7 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Copying solution to: permutation.solution +language Essence 1.3 + diff --git a/tests/custom/permutations/01_representation/unnamed/0008_find_permutation_of_int1_4/permutation.essence b/tests/custom/permutations/01_representation/unnamed/0008_find_permutation_of_int1_4/permutation.essence new file mode 100644 index 0000000000..a3348d0d12 --- /dev/null +++ b/tests/custom/permutations/01_representation/unnamed/0008_find_permutation_of_int1_4/permutation.essence @@ -0,0 +1,5 @@ +letting n be new type of size 4 + +find p : permutation of n + +such that true diff --git a/tests/custom/permutations/01_representation/unnamed/0008_find_permutation_of_int1_4/run.sh b/tests/custom/permutations/01_representation/unnamed/0008_find_permutation_of_int1_4/run.sh new file mode 100755 index 0000000000..7238b9c9c7 --- /dev/null +++ b/tests/custom/permutations/01_representation/unnamed/0008_find_permutation_of_int1_4/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence --number-of-solutions=100 +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/01_representation/unnamed/0008_find_permutation_of_int1_4/stdout.expected b/tests/custom/permutations/01_representation/unnamed/0008_find_permutation_of_int1_4/stdout.expected new file mode 100644 index 0000000000..b9f43828a6 --- /dev/null +++ b/tests/custom/permutations/01_representation/unnamed/0008_find_permutation_of_int1_4/stdout.expected @@ -0,0 +1,124 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Copying solution to: permutation-000001.solution +Copying solution to: permutation-000002.solution +Copying solution to: permutation-000003.solution +Copying solution to: permutation-000004.solution +Copying solution to: permutation-000005.solution +Copying solution to: permutation-000006.solution +Copying solution to: permutation-000007.solution +Copying solution to: permutation-000008.solution +Copying solution to: permutation-000009.solution +Copying solution to: permutation-000010.solution +Copying solution to: permutation-000011.solution +Copying solution to: permutation-000012.solution +Copying solution to: permutation-000013.solution +Copying solution to: permutation-000014.solution +Copying solution to: permutation-000015.solution +Copying solution to: permutation-000016.solution +Copying solution to: permutation-000017.solution +Copying solution to: permutation-000018.solution +Copying solution to: permutation-000019.solution +Copying solution to: permutation-000020.solution +Copying solution to: permutation-000021.solution +Copying solution to: permutation-000022.solution +Copying solution to: permutation-000023.solution +Copying solution to: permutation-000024.solution +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation() +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_3, n_4)) +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_2, n_3)) +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_2, n_3, n_4)) +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_2, n_4, n_3)) +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_2, n_4)) +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_1, n_2)) +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_1, n_2), (n_3, n_4)) +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_1, n_2, n_3)) +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_1, n_2, n_3, n_4)) +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_1, n_2, n_4, n_3)) +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_1, n_2, n_4)) +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_1, n_3, n_2)) +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_1, n_3, n_4, n_2)) +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_1, n_3)) +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_1, n_3, n_4)) +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_1, n_3), (n_2, n_4)) +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_1, n_3, n_2, n_4)) +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_1, n_4, n_3, n_2)) +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_1, n_4, n_2)) +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_1, n_4, n_3)) +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_1, n_4)) +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_1, n_4, n_2, n_3)) +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_1, n_4), (n_2, n_3)) diff --git a/tests/custom/permutations/01_representation/unnamed/0010_find_permutation_maxSize_2_of_int1_3/permutation.essence b/tests/custom/permutations/01_representation/unnamed/0010_find_permutation_maxSize_2_of_int1_3/permutation.essence new file mode 100644 index 0000000000..7e78359040 --- /dev/null +++ b/tests/custom/permutations/01_representation/unnamed/0010_find_permutation_maxSize_2_of_int1_3/permutation.essence @@ -0,0 +1,5 @@ +letting n be new type of size 3 + +find p : permutation (maxSize 2) of n + +such that true diff --git a/tests/custom/permutations/01_representation/unnamed/0010_find_permutation_maxSize_2_of_int1_3/run.sh b/tests/custom/permutations/01_representation/unnamed/0010_find_permutation_maxSize_2_of_int1_3/run.sh new file mode 100755 index 0000000000..7238b9c9c7 --- /dev/null +++ b/tests/custom/permutations/01_representation/unnamed/0010_find_permutation_maxSize_2_of_int1_3/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence --number-of-solutions=100 +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/01_representation/unnamed/0010_find_permutation_maxSize_2_of_int1_3/stdout.expected b/tests/custom/permutations/01_representation/unnamed/0010_find_permutation_maxSize_2_of_int1_3/stdout.expected new file mode 100644 index 0000000000..57ea7909f1 --- /dev/null +++ b/tests/custom/permutations/01_representation/unnamed/0010_find_permutation_maxSize_2_of_int1_3/stdout.expected @@ -0,0 +1,24 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Copying solution to: permutation-000001.solution +Copying solution to: permutation-000002.solution +Copying solution to: permutation-000003.solution +Copying solution to: permutation-000004.solution +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3} +letting p be permutation() +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3} +letting p be permutation((n_2, n_3)) +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3} +letting p be permutation((n_1, n_2)) +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3} +letting p be permutation((n_1, n_3)) diff --git a/tests/custom/permutations/01_representation/unnamed/0011_find_permutation_minSize_2_of_int1_3/permutation.essence b/tests/custom/permutations/01_representation/unnamed/0011_find_permutation_minSize_2_of_int1_3/permutation.essence new file mode 100644 index 0000000000..b2a3c523d4 --- /dev/null +++ b/tests/custom/permutations/01_representation/unnamed/0011_find_permutation_minSize_2_of_int1_3/permutation.essence @@ -0,0 +1,5 @@ +letting n be new type of size 3 + +find p : permutation (minSize 2) of n + +such that true diff --git a/tests/custom/permutations/01_representation/unnamed/0011_find_permutation_minSize_2_of_int1_3/run.sh b/tests/custom/permutations/01_representation/unnamed/0011_find_permutation_minSize_2_of_int1_3/run.sh new file mode 100755 index 0000000000..7238b9c9c7 --- /dev/null +++ b/tests/custom/permutations/01_representation/unnamed/0011_find_permutation_minSize_2_of_int1_3/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence --number-of-solutions=100 +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/01_representation/unnamed/0011_find_permutation_minSize_2_of_int1_3/stdout.expected b/tests/custom/permutations/01_representation/unnamed/0011_find_permutation_minSize_2_of_int1_3/stdout.expected new file mode 100644 index 0000000000..e677a2f4e9 --- /dev/null +++ b/tests/custom/permutations/01_representation/unnamed/0011_find_permutation_minSize_2_of_int1_3/stdout.expected @@ -0,0 +1,29 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Copying solution to: permutation-000001.solution +Copying solution to: permutation-000002.solution +Copying solution to: permutation-000003.solution +Copying solution to: permutation-000004.solution +Copying solution to: permutation-000005.solution +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3} +letting p be permutation((n_2, n_3)) +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3} +letting p be permutation((n_1, n_2)) +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3} +letting p be permutation((n_1, n_2, n_3)) +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3} +letting p be permutation((n_1, n_3, n_2)) +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3} +letting p be permutation((n_1, n_3)) diff --git a/tests/custom/permutations/01_representation/unnamed/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/permutation.essence b/tests/custom/permutations/01_representation/unnamed/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/permutation.essence new file mode 100644 index 0000000000..5083fed5ca --- /dev/null +++ b/tests/custom/permutations/01_representation/unnamed/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/permutation.essence @@ -0,0 +1,5 @@ +letting n be new type of size 4 + +find p : permutation (minSize 2, maxSize 3) of n + +such that true diff --git a/tests/custom/permutations/01_representation/unnamed/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/run.sh b/tests/custom/permutations/01_representation/unnamed/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/run.sh new file mode 100755 index 0000000000..7238b9c9c7 --- /dev/null +++ b/tests/custom/permutations/01_representation/unnamed/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence --number-of-solutions=100 +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/01_representation/unnamed/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/stdout.expected b/tests/custom/permutations/01_representation/unnamed/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/stdout.expected new file mode 100644 index 0000000000..1ec8c8ce1b --- /dev/null +++ b/tests/custom/permutations/01_representation/unnamed/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/stdout.expected @@ -0,0 +1,74 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Copying solution to: permutation-000001.solution +Copying solution to: permutation-000002.solution +Copying solution to: permutation-000003.solution +Copying solution to: permutation-000004.solution +Copying solution to: permutation-000005.solution +Copying solution to: permutation-000006.solution +Copying solution to: permutation-000007.solution +Copying solution to: permutation-000008.solution +Copying solution to: permutation-000009.solution +Copying solution to: permutation-000010.solution +Copying solution to: permutation-000011.solution +Copying solution to: permutation-000012.solution +Copying solution to: permutation-000013.solution +Copying solution to: permutation-000014.solution +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_3, n_4)) +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_2, n_3)) +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_2, n_3, n_4)) +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_2, n_4, n_3)) +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_2, n_4)) +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_1, n_2)) +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_1, n_2, n_3)) +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_1, n_2, n_4)) +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_1, n_3, n_2)) +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_1, n_3)) +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_1, n_3, n_4)) +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_1, n_4, n_2)) +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_1, n_4, n_3)) +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_1, n_4)) From 51cef21d37759be7dec9fbf3abadbdab32e26f49 Mon Sep 17 00:00:00 2001 From: Fraser Dunlop Date: Wed, 5 Dec 2018 10:52:38 +0000 Subject: [PATCH 044/229] Added enum & unnamed cardinality tests for permutations --- .../permutation.essence | 11 +++++++++++ .../0001_given_permutation_in_param/permutation.param | 1 + .../{ => enum}/0001_given_permutation_in_param/run.sh | 0 .../0001_given_permutation_in_param/stdout.expected | 0 .../permutation.essence | 10 ++++++++++ .../0002_letting_permutation_in_model/run.sh | 0 .../0002_letting_permutation_in_model/stdout.expected | 0 .../enum/0003_find_permutation/permutation.essence | 10 ++++++++++ .../{ => enum}/0003_find_permutation/run.sh | 0 .../enum/0003_find_permutation/stdout.expected | 9 +++++++++ .../permutation.essence | 0 .../0001_given_permutation_in_param/permutation.param | 0 .../int/0001_given_permutation_in_param/run.sh | 3 +++ .../0001_given_permutation_in_param/stdout.expected | 8 ++++++++ .../permutation.essence | 0 .../int/0002_letting_permutation_in_model/run.sh | 3 +++ .../0002_letting_permutation_in_model/stdout.expected | 8 ++++++++ .../0003_find_permutation/permutation.essence | 0 .../02_cardinality/int/0003_find_permutation/run.sh | 3 +++ .../{ => int}/0003_find_permutation/stdout.expected | 0 .../unnamed/0003_find_permutation/permutation.essence | 10 ++++++++++ .../unnamed/0003_find_permutation/run.sh | 3 +++ .../unnamed/0003_find_permutation/stdout.expected | 10 ++++++++++ 23 files changed, 89 insertions(+) create mode 100644 tests/custom/permutations/02_cardinality/enum/0001_given_permutation_in_param/permutation.essence create mode 100644 tests/custom/permutations/02_cardinality/enum/0001_given_permutation_in_param/permutation.param rename tests/custom/permutations/02_cardinality/{ => enum}/0001_given_permutation_in_param/run.sh (100%) rename tests/custom/permutations/02_cardinality/{ => enum}/0001_given_permutation_in_param/stdout.expected (100%) create mode 100644 tests/custom/permutations/02_cardinality/enum/0002_letting_permutation_in_model/permutation.essence rename tests/custom/permutations/02_cardinality/{ => enum}/0002_letting_permutation_in_model/run.sh (100%) rename tests/custom/permutations/02_cardinality/{ => enum}/0002_letting_permutation_in_model/stdout.expected (100%) create mode 100644 tests/custom/permutations/02_cardinality/enum/0003_find_permutation/permutation.essence rename tests/custom/permutations/02_cardinality/{ => enum}/0003_find_permutation/run.sh (100%) create mode 100644 tests/custom/permutations/02_cardinality/enum/0003_find_permutation/stdout.expected rename tests/custom/permutations/02_cardinality/{ => int}/0001_given_permutation_in_param/permutation.essence (100%) rename tests/custom/permutations/02_cardinality/{ => int}/0001_given_permutation_in_param/permutation.param (100%) create mode 100755 tests/custom/permutations/02_cardinality/int/0001_given_permutation_in_param/run.sh create mode 100644 tests/custom/permutations/02_cardinality/int/0001_given_permutation_in_param/stdout.expected rename tests/custom/permutations/02_cardinality/{ => int}/0002_letting_permutation_in_model/permutation.essence (100%) create mode 100755 tests/custom/permutations/02_cardinality/int/0002_letting_permutation_in_model/run.sh create mode 100644 tests/custom/permutations/02_cardinality/int/0002_letting_permutation_in_model/stdout.expected rename tests/custom/permutations/02_cardinality/{ => int}/0003_find_permutation/permutation.essence (100%) create mode 100755 tests/custom/permutations/02_cardinality/int/0003_find_permutation/run.sh rename tests/custom/permutations/02_cardinality/{ => int}/0003_find_permutation/stdout.expected (100%) create mode 100644 tests/custom/permutations/02_cardinality/unnamed/0003_find_permutation/permutation.essence create mode 100755 tests/custom/permutations/02_cardinality/unnamed/0003_find_permutation/run.sh create mode 100644 tests/custom/permutations/02_cardinality/unnamed/0003_find_permutation/stdout.expected diff --git a/tests/custom/permutations/02_cardinality/enum/0001_given_permutation_in_param/permutation.essence b/tests/custom/permutations/02_cardinality/enum/0001_given_permutation_in_param/permutation.essence new file mode 100644 index 0000000000..115d51f9b8 --- /dev/null +++ b/tests/custom/permutations/02_cardinality/enum/0001_given_permutation_in_param/permutation.essence @@ -0,0 +1,11 @@ +letting n be new type enum {E1,E2,E3,E4} + +given p : permutation of n + +find i : int(0..10) + +such that i = |p| + + + + diff --git a/tests/custom/permutations/02_cardinality/enum/0001_given_permutation_in_param/permutation.param b/tests/custom/permutations/02_cardinality/enum/0001_given_permutation_in_param/permutation.param new file mode 100644 index 0000000000..19349bb872 --- /dev/null +++ b/tests/custom/permutations/02_cardinality/enum/0001_given_permutation_in_param/permutation.param @@ -0,0 +1 @@ +letting p be permutation((E1,E3,E4)) diff --git a/tests/custom/permutations/02_cardinality/0001_given_permutation_in_param/run.sh b/tests/custom/permutations/02_cardinality/enum/0001_given_permutation_in_param/run.sh similarity index 100% rename from tests/custom/permutations/02_cardinality/0001_given_permutation_in_param/run.sh rename to tests/custom/permutations/02_cardinality/enum/0001_given_permutation_in_param/run.sh diff --git a/tests/custom/permutations/02_cardinality/0001_given_permutation_in_param/stdout.expected b/tests/custom/permutations/02_cardinality/enum/0001_given_permutation_in_param/stdout.expected similarity index 100% rename from tests/custom/permutations/02_cardinality/0001_given_permutation_in_param/stdout.expected rename to tests/custom/permutations/02_cardinality/enum/0001_given_permutation_in_param/stdout.expected diff --git a/tests/custom/permutations/02_cardinality/enum/0002_letting_permutation_in_model/permutation.essence b/tests/custom/permutations/02_cardinality/enum/0002_letting_permutation_in_model/permutation.essence new file mode 100644 index 0000000000..91903a1aa5 --- /dev/null +++ b/tests/custom/permutations/02_cardinality/enum/0002_letting_permutation_in_model/permutation.essence @@ -0,0 +1,10 @@ +letting n be new type enum {E1,E2,E3,E4} +letting p be permutation((E1,E3,E4)) + +find i : int(0..10) + +such that i = |p| + + + + diff --git a/tests/custom/permutations/02_cardinality/0002_letting_permutation_in_model/run.sh b/tests/custom/permutations/02_cardinality/enum/0002_letting_permutation_in_model/run.sh similarity index 100% rename from tests/custom/permutations/02_cardinality/0002_letting_permutation_in_model/run.sh rename to tests/custom/permutations/02_cardinality/enum/0002_letting_permutation_in_model/run.sh diff --git a/tests/custom/permutations/02_cardinality/0002_letting_permutation_in_model/stdout.expected b/tests/custom/permutations/02_cardinality/enum/0002_letting_permutation_in_model/stdout.expected similarity index 100% rename from tests/custom/permutations/02_cardinality/0002_letting_permutation_in_model/stdout.expected rename to tests/custom/permutations/02_cardinality/enum/0002_letting_permutation_in_model/stdout.expected diff --git a/tests/custom/permutations/02_cardinality/enum/0003_find_permutation/permutation.essence b/tests/custom/permutations/02_cardinality/enum/0003_find_permutation/permutation.essence new file mode 100644 index 0000000000..663987f4f6 --- /dev/null +++ b/tests/custom/permutations/02_cardinality/enum/0003_find_permutation/permutation.essence @@ -0,0 +1,10 @@ +letting n be new type enum {E1,E2,E3,E4,E5,E6} +find p : permutation (size 4) of n + +find i : int(0..10) + +such that i = |p| + + + + diff --git a/tests/custom/permutations/02_cardinality/0003_find_permutation/run.sh b/tests/custom/permutations/02_cardinality/enum/0003_find_permutation/run.sh similarity index 100% rename from tests/custom/permutations/02_cardinality/0003_find_permutation/run.sh rename to tests/custom/permutations/02_cardinality/enum/0003_find_permutation/run.sh diff --git a/tests/custom/permutations/02_cardinality/enum/0003_find_permutation/stdout.expected b/tests/custom/permutations/02_cardinality/enum/0003_find_permutation/stdout.expected new file mode 100644 index 0000000000..4e026e23dd --- /dev/null +++ b/tests/custom/permutations/02_cardinality/enum/0003_find_permutation/stdout.expected @@ -0,0 +1,9 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Copying solution to: permutation.solution +language Essence 1.3 + +letting i be 4 +letting p be permutation((E3, E4), (E5, E6)) diff --git a/tests/custom/permutations/02_cardinality/0001_given_permutation_in_param/permutation.essence b/tests/custom/permutations/02_cardinality/int/0001_given_permutation_in_param/permutation.essence similarity index 100% rename from tests/custom/permutations/02_cardinality/0001_given_permutation_in_param/permutation.essence rename to tests/custom/permutations/02_cardinality/int/0001_given_permutation_in_param/permutation.essence diff --git a/tests/custom/permutations/02_cardinality/0001_given_permutation_in_param/permutation.param b/tests/custom/permutations/02_cardinality/int/0001_given_permutation_in_param/permutation.param similarity index 100% rename from tests/custom/permutations/02_cardinality/0001_given_permutation_in_param/permutation.param rename to tests/custom/permutations/02_cardinality/int/0001_given_permutation_in_param/permutation.param diff --git a/tests/custom/permutations/02_cardinality/int/0001_given_permutation_in_param/run.sh b/tests/custom/permutations/02_cardinality/int/0001_given_permutation_in_param/run.sh new file mode 100755 index 0000000000..9dc67e67f5 --- /dev/null +++ b/tests/custom/permutations/02_cardinality/int/0001_given_permutation_in_param/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence *.param +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/02_cardinality/int/0001_given_permutation_in_param/stdout.expected b/tests/custom/permutations/02_cardinality/int/0001_given_permutation_in_param/stdout.expected new file mode 100644 index 0000000000..d20985577b --- /dev/null +++ b/tests/custom/permutations/02_cardinality/int/0001_given_permutation_in_param/stdout.expected @@ -0,0 +1,8 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime permutation.param +Copying solution to: permutation-permutation.solution +language Essence 1.3 + +letting i be 3 diff --git a/tests/custom/permutations/02_cardinality/0002_letting_permutation_in_model/permutation.essence b/tests/custom/permutations/02_cardinality/int/0002_letting_permutation_in_model/permutation.essence similarity index 100% rename from tests/custom/permutations/02_cardinality/0002_letting_permutation_in_model/permutation.essence rename to tests/custom/permutations/02_cardinality/int/0002_letting_permutation_in_model/permutation.essence diff --git a/tests/custom/permutations/02_cardinality/int/0002_letting_permutation_in_model/run.sh b/tests/custom/permutations/02_cardinality/int/0002_letting_permutation_in_model/run.sh new file mode 100755 index 0000000000..b4899d6266 --- /dev/null +++ b/tests/custom/permutations/02_cardinality/int/0002_letting_permutation_in_model/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/02_cardinality/int/0002_letting_permutation_in_model/stdout.expected b/tests/custom/permutations/02_cardinality/int/0002_letting_permutation_in_model/stdout.expected new file mode 100644 index 0000000000..d07c5feeb5 --- /dev/null +++ b/tests/custom/permutations/02_cardinality/int/0002_letting_permutation_in_model/stdout.expected @@ -0,0 +1,8 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Copying solution to: permutation.solution +language Essence 1.3 + +letting i be 3 diff --git a/tests/custom/permutations/02_cardinality/0003_find_permutation/permutation.essence b/tests/custom/permutations/02_cardinality/int/0003_find_permutation/permutation.essence similarity index 100% rename from tests/custom/permutations/02_cardinality/0003_find_permutation/permutation.essence rename to tests/custom/permutations/02_cardinality/int/0003_find_permutation/permutation.essence diff --git a/tests/custom/permutations/02_cardinality/int/0003_find_permutation/run.sh b/tests/custom/permutations/02_cardinality/int/0003_find_permutation/run.sh new file mode 100755 index 0000000000..b4899d6266 --- /dev/null +++ b/tests/custom/permutations/02_cardinality/int/0003_find_permutation/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/02_cardinality/0003_find_permutation/stdout.expected b/tests/custom/permutations/02_cardinality/int/0003_find_permutation/stdout.expected similarity index 100% rename from tests/custom/permutations/02_cardinality/0003_find_permutation/stdout.expected rename to tests/custom/permutations/02_cardinality/int/0003_find_permutation/stdout.expected diff --git a/tests/custom/permutations/02_cardinality/unnamed/0003_find_permutation/permutation.essence b/tests/custom/permutations/02_cardinality/unnamed/0003_find_permutation/permutation.essence new file mode 100644 index 0000000000..05bc8e04fa --- /dev/null +++ b/tests/custom/permutations/02_cardinality/unnamed/0003_find_permutation/permutation.essence @@ -0,0 +1,10 @@ +letting n be new type of size 6 +find p : permutation (size 4) of n + +find i : int(0..10) + +such that i = |p| + + + + diff --git a/tests/custom/permutations/02_cardinality/unnamed/0003_find_permutation/run.sh b/tests/custom/permutations/02_cardinality/unnamed/0003_find_permutation/run.sh new file mode 100755 index 0000000000..b4899d6266 --- /dev/null +++ b/tests/custom/permutations/02_cardinality/unnamed/0003_find_permutation/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/02_cardinality/unnamed/0003_find_permutation/stdout.expected b/tests/custom/permutations/02_cardinality/unnamed/0003_find_permutation/stdout.expected new file mode 100644 index 0000000000..08c17fa62d --- /dev/null +++ b/tests/custom/permutations/02_cardinality/unnamed/0003_find_permutation/stdout.expected @@ -0,0 +1,10 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Copying solution to: permutation.solution +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6} +letting i be 4 +letting p be permutation((n_3, n_4), (n_5, n_6)) From 0b6bf2da6239a9f14b467ee4f9c4db0e05a562f4 Mon Sep 17 00:00:00 2001 From: Fraser Dunlop Date: Wed, 5 Dec 2018 11:45:29 +0000 Subject: [PATCH 045/229] Found bug in sets of tuples of enums when writing generators test --- .../permutation.essence | 11 +++ .../permutation.param | 1 + .../run.sh | 0 .../permutation.essence | 11 +++ .../run.sh | 0 .../permutation.essence | 10 ++ .../0003_find_permutation_in_generator/run.sh | 0 .../stdout.expected | 84 +++++++++++++++++ .../permutations/03_generators/enum/BUGS.md | 22 +++++ .../minimal_bug_example/permutation.essence | 16 ++++ .../enum/minimal_bug_example/run.sh | 3 + .../permutation.essence | 0 .../permutation.param | 0 .../run.sh | 3 + .../stdout.expected | 0 .../permutation.essence | 0 .../run.sh | 3 + .../stdout.expected | 0 .../permutation.essence | 0 .../0003_find_permutation_in_generator/run.sh | 3 + .../stdout.expected | 0 .../permutation.essence | 7 ++ .../0004_find_permutation_in_forall/run.sh | 3 + .../stdout.expected | 84 +++++++++++++++++ .../permutation.essence | 7 ++ .../0005_find_permutation_in_forall/run.sh | 3 + .../stdout.expected | 84 +++++++++++++++++ .../permutation.essence | 10 ++ .../0003_find_permutation_in_generator/run.sh | 3 + .../stdout.expected | 92 +++++++++++++++++++ 30 files changed, 460 insertions(+) create mode 100644 tests/custom/permutations/03_generators/enum/0001_given_permutation_in_generator/permutation.essence create mode 100644 tests/custom/permutations/03_generators/enum/0001_given_permutation_in_generator/permutation.param rename tests/custom/permutations/03_generators/{ => enum}/0001_given_permutation_in_generator/run.sh (100%) create mode 100644 tests/custom/permutations/03_generators/enum/0002_letting_permutation_in_generator/permutation.essence rename tests/custom/permutations/03_generators/{ => enum}/0002_letting_permutation_in_generator/run.sh (100%) create mode 100644 tests/custom/permutations/03_generators/enum/0003_find_permutation_in_generator/permutation.essence rename tests/custom/permutations/03_generators/{ => enum}/0003_find_permutation_in_generator/run.sh (100%) create mode 100644 tests/custom/permutations/03_generators/enum/0003_find_permutation_in_generator/stdout.expected create mode 100644 tests/custom/permutations/03_generators/enum/BUGS.md create mode 100644 tests/custom/permutations/03_generators/enum/minimal_bug_example/permutation.essence create mode 100755 tests/custom/permutations/03_generators/enum/minimal_bug_example/run.sh rename tests/custom/permutations/03_generators/{ => int}/0001_given_permutation_in_generator/permutation.essence (100%) rename tests/custom/permutations/03_generators/{ => int}/0001_given_permutation_in_generator/permutation.param (100%) create mode 100755 tests/custom/permutations/03_generators/int/0001_given_permutation_in_generator/run.sh rename tests/custom/permutations/03_generators/{ => int}/0001_given_permutation_in_generator/stdout.expected (100%) rename tests/custom/permutations/03_generators/{ => int}/0002_letting_permutation_in_generator/permutation.essence (100%) create mode 100755 tests/custom/permutations/03_generators/int/0002_letting_permutation_in_generator/run.sh rename tests/custom/permutations/03_generators/{ => int}/0002_letting_permutation_in_generator/stdout.expected (100%) rename tests/custom/permutations/03_generators/{ => int}/0003_find_permutation_in_generator/permutation.essence (100%) create mode 100755 tests/custom/permutations/03_generators/int/0003_find_permutation_in_generator/run.sh rename tests/custom/permutations/03_generators/{ => int}/0003_find_permutation_in_generator/stdout.expected (100%) create mode 100644 tests/custom/permutations/03_generators/int/0004_find_permutation_in_forall/permutation.essence create mode 100755 tests/custom/permutations/03_generators/int/0004_find_permutation_in_forall/run.sh create mode 100644 tests/custom/permutations/03_generators/int/0004_find_permutation_in_forall/stdout.expected create mode 100644 tests/custom/permutations/03_generators/int/0005_find_permutation_in_forall/permutation.essence create mode 100755 tests/custom/permutations/03_generators/int/0005_find_permutation_in_forall/run.sh create mode 100644 tests/custom/permutations/03_generators/int/0005_find_permutation_in_forall/stdout.expected create mode 100644 tests/custom/permutations/03_generators/unnamed/0003_find_permutation_in_generator/permutation.essence create mode 100755 tests/custom/permutations/03_generators/unnamed/0003_find_permutation_in_generator/run.sh create mode 100644 tests/custom/permutations/03_generators/unnamed/0003_find_permutation_in_generator/stdout.expected diff --git a/tests/custom/permutations/03_generators/enum/0001_given_permutation_in_generator/permutation.essence b/tests/custom/permutations/03_generators/enum/0001_given_permutation_in_generator/permutation.essence new file mode 100644 index 0000000000..44d41e1738 --- /dev/null +++ b/tests/custom/permutations/03_generators/enum/0001_given_permutation_in_generator/permutation.essence @@ -0,0 +1,11 @@ +letting n be new type enum {E1,E2,E3,E4} + +given p : permutation of n +find s : set of (n,n) + +such that + and([e in s | e <- p]) + + + + diff --git a/tests/custom/permutations/03_generators/enum/0001_given_permutation_in_generator/permutation.param b/tests/custom/permutations/03_generators/enum/0001_given_permutation_in_generator/permutation.param new file mode 100644 index 0000000000..19349bb872 --- /dev/null +++ b/tests/custom/permutations/03_generators/enum/0001_given_permutation_in_generator/permutation.param @@ -0,0 +1 @@ +letting p be permutation((E1,E3,E4)) diff --git a/tests/custom/permutations/03_generators/0001_given_permutation_in_generator/run.sh b/tests/custom/permutations/03_generators/enum/0001_given_permutation_in_generator/run.sh similarity index 100% rename from tests/custom/permutations/03_generators/0001_given_permutation_in_generator/run.sh rename to tests/custom/permutations/03_generators/enum/0001_given_permutation_in_generator/run.sh diff --git a/tests/custom/permutations/03_generators/enum/0002_letting_permutation_in_generator/permutation.essence b/tests/custom/permutations/03_generators/enum/0002_letting_permutation_in_generator/permutation.essence new file mode 100644 index 0000000000..a2a39f8dd4 --- /dev/null +++ b/tests/custom/permutations/03_generators/enum/0002_letting_permutation_in_generator/permutation.essence @@ -0,0 +1,11 @@ +letting n be new type enum {E1,E2,E3,E4} + +letting p be permutation((E1,E3,E4)) +find s : set of (n,n) + +such that + and([e in s | e <- p]) + + + + diff --git a/tests/custom/permutations/03_generators/0002_letting_permutation_in_generator/run.sh b/tests/custom/permutations/03_generators/enum/0002_letting_permutation_in_generator/run.sh similarity index 100% rename from tests/custom/permutations/03_generators/0002_letting_permutation_in_generator/run.sh rename to tests/custom/permutations/03_generators/enum/0002_letting_permutation_in_generator/run.sh diff --git a/tests/custom/permutations/03_generators/enum/0003_find_permutation_in_generator/permutation.essence b/tests/custom/permutations/03_generators/enum/0003_find_permutation_in_generator/permutation.essence new file mode 100644 index 0000000000..6bfee9c393 --- /dev/null +++ b/tests/custom/permutations/03_generators/enum/0003_find_permutation_in_generator/permutation.essence @@ -0,0 +1,10 @@ +letting n be new type enum {E1,E2,E3,E4} +find p : permutation (size 3) of n +find s : set (size 3) of (n,n) + +such that + and([e in s | e <- p]) + + + + diff --git a/tests/custom/permutations/03_generators/0003_find_permutation_in_generator/run.sh b/tests/custom/permutations/03_generators/enum/0003_find_permutation_in_generator/run.sh similarity index 100% rename from tests/custom/permutations/03_generators/0003_find_permutation_in_generator/run.sh rename to tests/custom/permutations/03_generators/enum/0003_find_permutation_in_generator/run.sh diff --git a/tests/custom/permutations/03_generators/enum/0003_find_permutation_in_generator/stdout.expected b/tests/custom/permutations/03_generators/enum/0003_find_permutation_in_generator/stdout.expected new file mode 100644 index 0000000000..a73dd92207 --- /dev/null +++ b/tests/custom/permutations/03_generators/enum/0003_find_permutation_in_generator/stdout.expected @@ -0,0 +1,84 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Copying solution to: permutation-000001.solution +Copying solution to: permutation-000002.solution +Copying solution to: permutation-000003.solution +Copying solution to: permutation-000004.solution +Copying solution to: permutation-000005.solution +Copying solution to: permutation-000006.solution +Copying solution to: permutation-000007.solution +Copying solution to: permutation-000008.solution +language Essence 1.3 + +letting p be permutation((E2, E3, E4)) +letting s be {(E2, E3), (E3, E4), (E4, E2)} +$ Visualisation for s +$ E2 E3 +$ E3 E4 +$ E4 E2 + +language Essence 1.3 + +letting p be permutation((E2, E4, E3)) +letting s be {(E2, E4), (E3, E2), (E4, E3)} +$ Visualisation for s +$ E2 E4 +$ E3 E2 +$ E4 E3 + +language Essence 1.3 + +letting p be permutation((E1, E2, E3)) +letting s be {(E1, E2), (E2, E3), (E3, E1)} +$ Visualisation for s +$ E1 E2 +$ E2 E3 +$ E3 E1 + +language Essence 1.3 + +letting p be permutation((E1, E2, E4)) +letting s be {(E1, E2), (E2, E4), (E4, E1)} +$ Visualisation for s +$ E1 E2 +$ E2 E4 +$ E4 E1 + +language Essence 1.3 + +letting p be permutation((E1, E3, E2)) +letting s be {(E1, E3), (E2, E1), (E3, E2)} +$ Visualisation for s +$ E1 E3 +$ E2 E1 +$ E3 E2 + +language Essence 1.3 + +letting p be permutation((E1, E3, E4)) +letting s be {(E1, E3), (E3, E4), (E4, E1)} +$ Visualisation for s +$ E1 E3 +$ E3 E4 +$ E4 E1 + +language Essence 1.3 + +letting p be permutation((E1, E4, E2)) +letting s be {(E1, E4), (E2, E1), (E4, E2)} +$ Visualisation for s +$ E1 E4 +$ E2 E1 +$ E4 E2 + +language Essence 1.3 + +letting p be permutation((E1, E4, E3)) +letting s be {(E1, E4), (E3, E1), (E4, E3)} +$ Visualisation for s +$ E1 E4 +$ E3 E1 +$ E4 E3 + diff --git a/tests/custom/permutations/03_generators/enum/BUGS.md b/tests/custom/permutations/03_generators/enum/BUGS.md new file mode 100644 index 0000000000..9417909c38 --- /dev/null +++ b/tests/custom/permutations/03_generators/enum/BUGS.md @@ -0,0 +1,22 @@ +There appears to be a bug in refinement +- 0001 +- 0002 +are affected +These examples both work with ints instead of enums + +A minimal bug example is in this folder - the problem is sets of tuples of enums + +$minimal bug example + letting n be new type enum {E1,E2,E3,E4} + letting i be (E1,E2) + find s : set of (n,n) + such that i in s + + +IO Error +Type error in 4 * 4 + The argument has type: matrix indexed by [int] of int + +CallStack (from HasCallStack): + error, called at src/Conjure/Bug.hs:21:15 in conjure-cp-2.2.0-4cfnInyB42NJSP2i6f0krZ:Conjure.Bug + bug, called at src/Conjure/Bug.hs:47:16 in conjure-cp-2.2.0-4cfnInyB42NJSP2i6f0krZ:Conjure.Bug diff --git a/tests/custom/permutations/03_generators/enum/minimal_bug_example/permutation.essence b/tests/custom/permutations/03_generators/enum/minimal_bug_example/permutation.essence new file mode 100644 index 0000000000..9040ee25a7 --- /dev/null +++ b/tests/custom/permutations/03_generators/enum/minimal_bug_example/permutation.essence @@ -0,0 +1,16 @@ +letting n be new type enum {E1,E2,E3,E4} + +$ We don't need a permutation to reach this bug +$letting p be permutation((E1,E3,E4)) +$ A tuple of enums is sufficient +letting i be (E1,E2) + +find s : set of (n,n) + + +such that i in s +$ and([e in s | e <- p]) + + + + diff --git a/tests/custom/permutations/03_generators/enum/minimal_bug_example/run.sh b/tests/custom/permutations/03_generators/enum/minimal_bug_example/run.sh new file mode 100755 index 0000000000..b4899d6266 --- /dev/null +++ b/tests/custom/permutations/03_generators/enum/minimal_bug_example/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/03_generators/0001_given_permutation_in_generator/permutation.essence b/tests/custom/permutations/03_generators/int/0001_given_permutation_in_generator/permutation.essence similarity index 100% rename from tests/custom/permutations/03_generators/0001_given_permutation_in_generator/permutation.essence rename to tests/custom/permutations/03_generators/int/0001_given_permutation_in_generator/permutation.essence diff --git a/tests/custom/permutations/03_generators/0001_given_permutation_in_generator/permutation.param b/tests/custom/permutations/03_generators/int/0001_given_permutation_in_generator/permutation.param similarity index 100% rename from tests/custom/permutations/03_generators/0001_given_permutation_in_generator/permutation.param rename to tests/custom/permutations/03_generators/int/0001_given_permutation_in_generator/permutation.param diff --git a/tests/custom/permutations/03_generators/int/0001_given_permutation_in_generator/run.sh b/tests/custom/permutations/03_generators/int/0001_given_permutation_in_generator/run.sh new file mode 100755 index 0000000000..9dc67e67f5 --- /dev/null +++ b/tests/custom/permutations/03_generators/int/0001_given_permutation_in_generator/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence *.param +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/03_generators/0001_given_permutation_in_generator/stdout.expected b/tests/custom/permutations/03_generators/int/0001_given_permutation_in_generator/stdout.expected similarity index 100% rename from tests/custom/permutations/03_generators/0001_given_permutation_in_generator/stdout.expected rename to tests/custom/permutations/03_generators/int/0001_given_permutation_in_generator/stdout.expected diff --git a/tests/custom/permutations/03_generators/0002_letting_permutation_in_generator/permutation.essence b/tests/custom/permutations/03_generators/int/0002_letting_permutation_in_generator/permutation.essence similarity index 100% rename from tests/custom/permutations/03_generators/0002_letting_permutation_in_generator/permutation.essence rename to tests/custom/permutations/03_generators/int/0002_letting_permutation_in_generator/permutation.essence diff --git a/tests/custom/permutations/03_generators/int/0002_letting_permutation_in_generator/run.sh b/tests/custom/permutations/03_generators/int/0002_letting_permutation_in_generator/run.sh new file mode 100755 index 0000000000..b4899d6266 --- /dev/null +++ b/tests/custom/permutations/03_generators/int/0002_letting_permutation_in_generator/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/03_generators/0002_letting_permutation_in_generator/stdout.expected b/tests/custom/permutations/03_generators/int/0002_letting_permutation_in_generator/stdout.expected similarity index 100% rename from tests/custom/permutations/03_generators/0002_letting_permutation_in_generator/stdout.expected rename to tests/custom/permutations/03_generators/int/0002_letting_permutation_in_generator/stdout.expected diff --git a/tests/custom/permutations/03_generators/0003_find_permutation_in_generator/permutation.essence b/tests/custom/permutations/03_generators/int/0003_find_permutation_in_generator/permutation.essence similarity index 100% rename from tests/custom/permutations/03_generators/0003_find_permutation_in_generator/permutation.essence rename to tests/custom/permutations/03_generators/int/0003_find_permutation_in_generator/permutation.essence diff --git a/tests/custom/permutations/03_generators/int/0003_find_permutation_in_generator/run.sh b/tests/custom/permutations/03_generators/int/0003_find_permutation_in_generator/run.sh new file mode 100755 index 0000000000..de361d4354 --- /dev/null +++ b/tests/custom/permutations/03_generators/int/0003_find_permutation_in_generator/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence --number-of-solutions=40 +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/03_generators/0003_find_permutation_in_generator/stdout.expected b/tests/custom/permutations/03_generators/int/0003_find_permutation_in_generator/stdout.expected similarity index 100% rename from tests/custom/permutations/03_generators/0003_find_permutation_in_generator/stdout.expected rename to tests/custom/permutations/03_generators/int/0003_find_permutation_in_generator/stdout.expected diff --git a/tests/custom/permutations/03_generators/int/0004_find_permutation_in_forall/permutation.essence b/tests/custom/permutations/03_generators/int/0004_find_permutation_in_forall/permutation.essence new file mode 100644 index 0000000000..d4ccc8d532 --- /dev/null +++ b/tests/custom/permutations/03_generators/int/0004_find_permutation_in_forall/permutation.essence @@ -0,0 +1,7 @@ +find p : permutation (size 3) of int(1..4) +find s : set (size 3) of (int(1..4),int(1..4)) + +such that + forAll e in p . + e in s + diff --git a/tests/custom/permutations/03_generators/int/0004_find_permutation_in_forall/run.sh b/tests/custom/permutations/03_generators/int/0004_find_permutation_in_forall/run.sh new file mode 100755 index 0000000000..de361d4354 --- /dev/null +++ b/tests/custom/permutations/03_generators/int/0004_find_permutation_in_forall/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence --number-of-solutions=40 +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/03_generators/int/0004_find_permutation_in_forall/stdout.expected b/tests/custom/permutations/03_generators/int/0004_find_permutation_in_forall/stdout.expected new file mode 100644 index 0000000000..68a640a558 --- /dev/null +++ b/tests/custom/permutations/03_generators/int/0004_find_permutation_in_forall/stdout.expected @@ -0,0 +1,84 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Copying solution to: permutation-000001.solution +Copying solution to: permutation-000002.solution +Copying solution to: permutation-000003.solution +Copying solution to: permutation-000004.solution +Copying solution to: permutation-000005.solution +Copying solution to: permutation-000006.solution +Copying solution to: permutation-000007.solution +Copying solution to: permutation-000008.solution +language Essence 1.3 + +letting p be permutation((2, 3, 4)) +letting s be {(2, 3), (3, 4), (4, 2)} +$ Visualisation for s +$ 2 3 +$ 3 4 +$ 4 2 + +language Essence 1.3 + +letting p be permutation((2, 4, 3)) +letting s be {(2, 4), (3, 2), (4, 3)} +$ Visualisation for s +$ 2 4 +$ 3 2 +$ 4 3 + +language Essence 1.3 + +letting p be permutation((1, 2, 3)) +letting s be {(1, 2), (2, 3), (3, 1)} +$ Visualisation for s +$ 1 2 +$ 2 3 +$ 3 1 + +language Essence 1.3 + +letting p be permutation((1, 2, 4)) +letting s be {(1, 2), (2, 4), (4, 1)} +$ Visualisation for s +$ 1 2 +$ 2 4 +$ 4 1 + +language Essence 1.3 + +letting p be permutation((1, 3, 2)) +letting s be {(1, 3), (2, 1), (3, 2)} +$ Visualisation for s +$ 1 3 +$ 2 1 +$ 3 2 + +language Essence 1.3 + +letting p be permutation((1, 3, 4)) +letting s be {(1, 3), (3, 4), (4, 1)} +$ Visualisation for s +$ 1 3 +$ 3 4 +$ 4 1 + +language Essence 1.3 + +letting p be permutation((1, 4, 2)) +letting s be {(1, 4), (2, 1), (4, 2)} +$ Visualisation for s +$ 1 4 +$ 2 1 +$ 4 2 + +language Essence 1.3 + +letting p be permutation((1, 4, 3)) +letting s be {(1, 4), (3, 1), (4, 3)} +$ Visualisation for s +$ 1 4 +$ 3 1 +$ 4 3 + diff --git a/tests/custom/permutations/03_generators/int/0005_find_permutation_in_forall/permutation.essence b/tests/custom/permutations/03_generators/int/0005_find_permutation_in_forall/permutation.essence new file mode 100644 index 0000000000..3c63df7e7d --- /dev/null +++ b/tests/custom/permutations/03_generators/int/0005_find_permutation_in_forall/permutation.essence @@ -0,0 +1,7 @@ +find p : permutation (size 3) of int(1..4) +find s : set (size 3) of (int(1..4),int(1..4)) + +such that + forAll e in s . + e in p + diff --git a/tests/custom/permutations/03_generators/int/0005_find_permutation_in_forall/run.sh b/tests/custom/permutations/03_generators/int/0005_find_permutation_in_forall/run.sh new file mode 100755 index 0000000000..de361d4354 --- /dev/null +++ b/tests/custom/permutations/03_generators/int/0005_find_permutation_in_forall/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence --number-of-solutions=40 +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/03_generators/int/0005_find_permutation_in_forall/stdout.expected b/tests/custom/permutations/03_generators/int/0005_find_permutation_in_forall/stdout.expected new file mode 100644 index 0000000000..68a640a558 --- /dev/null +++ b/tests/custom/permutations/03_generators/int/0005_find_permutation_in_forall/stdout.expected @@ -0,0 +1,84 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Copying solution to: permutation-000001.solution +Copying solution to: permutation-000002.solution +Copying solution to: permutation-000003.solution +Copying solution to: permutation-000004.solution +Copying solution to: permutation-000005.solution +Copying solution to: permutation-000006.solution +Copying solution to: permutation-000007.solution +Copying solution to: permutation-000008.solution +language Essence 1.3 + +letting p be permutation((2, 3, 4)) +letting s be {(2, 3), (3, 4), (4, 2)} +$ Visualisation for s +$ 2 3 +$ 3 4 +$ 4 2 + +language Essence 1.3 + +letting p be permutation((2, 4, 3)) +letting s be {(2, 4), (3, 2), (4, 3)} +$ Visualisation for s +$ 2 4 +$ 3 2 +$ 4 3 + +language Essence 1.3 + +letting p be permutation((1, 2, 3)) +letting s be {(1, 2), (2, 3), (3, 1)} +$ Visualisation for s +$ 1 2 +$ 2 3 +$ 3 1 + +language Essence 1.3 + +letting p be permutation((1, 2, 4)) +letting s be {(1, 2), (2, 4), (4, 1)} +$ Visualisation for s +$ 1 2 +$ 2 4 +$ 4 1 + +language Essence 1.3 + +letting p be permutation((1, 3, 2)) +letting s be {(1, 3), (2, 1), (3, 2)} +$ Visualisation for s +$ 1 3 +$ 2 1 +$ 3 2 + +language Essence 1.3 + +letting p be permutation((1, 3, 4)) +letting s be {(1, 3), (3, 4), (4, 1)} +$ Visualisation for s +$ 1 3 +$ 3 4 +$ 4 1 + +language Essence 1.3 + +letting p be permutation((1, 4, 2)) +letting s be {(1, 4), (2, 1), (4, 2)} +$ Visualisation for s +$ 1 4 +$ 2 1 +$ 4 2 + +language Essence 1.3 + +letting p be permutation((1, 4, 3)) +letting s be {(1, 4), (3, 1), (4, 3)} +$ Visualisation for s +$ 1 4 +$ 3 1 +$ 4 3 + diff --git a/tests/custom/permutations/03_generators/unnamed/0003_find_permutation_in_generator/permutation.essence b/tests/custom/permutations/03_generators/unnamed/0003_find_permutation_in_generator/permutation.essence new file mode 100644 index 0000000000..3d0835eaf5 --- /dev/null +++ b/tests/custom/permutations/03_generators/unnamed/0003_find_permutation_in_generator/permutation.essence @@ -0,0 +1,10 @@ +letting n be new type of size 4 +find p : permutation (size 3) of n +find s : set (size 3) of (n,n) + +such that + and([e in s | e <- p]) + + + + diff --git a/tests/custom/permutations/03_generators/unnamed/0003_find_permutation_in_generator/run.sh b/tests/custom/permutations/03_generators/unnamed/0003_find_permutation_in_generator/run.sh new file mode 100755 index 0000000000..de361d4354 --- /dev/null +++ b/tests/custom/permutations/03_generators/unnamed/0003_find_permutation_in_generator/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence --number-of-solutions=40 +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/03_generators/unnamed/0003_find_permutation_in_generator/stdout.expected b/tests/custom/permutations/03_generators/unnamed/0003_find_permutation_in_generator/stdout.expected new file mode 100644 index 0000000000..e83fdac69e --- /dev/null +++ b/tests/custom/permutations/03_generators/unnamed/0003_find_permutation_in_generator/stdout.expected @@ -0,0 +1,92 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Copying solution to: permutation-000001.solution +Copying solution to: permutation-000002.solution +Copying solution to: permutation-000003.solution +Copying solution to: permutation-000004.solution +Copying solution to: permutation-000005.solution +Copying solution to: permutation-000006.solution +Copying solution to: permutation-000007.solution +Copying solution to: permutation-000008.solution +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_2, n_3, n_4)) +letting s be {(n_2, n_3), (n_3, n_4), (n_4, n_2)} +$ Visualisation for s +$ n_2 n_3 +$ n_3 n_4 +$ n_4 n_2 + +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_2, n_4, n_3)) +letting s be {(n_2, n_4), (n_3, n_2), (n_4, n_3)} +$ Visualisation for s +$ n_2 n_4 +$ n_3 n_2 +$ n_4 n_3 + +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_1, n_2, n_3)) +letting s be {(n_1, n_2), (n_2, n_3), (n_3, n_1)} +$ Visualisation for s +$ n_1 n_2 +$ n_2 n_3 +$ n_3 n_1 + +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_1, n_2, n_4)) +letting s be {(n_1, n_2), (n_2, n_4), (n_4, n_1)} +$ Visualisation for s +$ n_1 n_2 +$ n_2 n_4 +$ n_4 n_1 + +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_1, n_3, n_2)) +letting s be {(n_1, n_3), (n_2, n_1), (n_3, n_2)} +$ Visualisation for s +$ n_1 n_3 +$ n_2 n_1 +$ n_3 n_2 + +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_1, n_3, n_4)) +letting s be {(n_1, n_3), (n_3, n_4), (n_4, n_1)} +$ Visualisation for s +$ n_1 n_3 +$ n_3 n_4 +$ n_4 n_1 + +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_1, n_4, n_2)) +letting s be {(n_1, n_4), (n_2, n_1), (n_4, n_2)} +$ Visualisation for s +$ n_1 n_4 +$ n_2 n_1 +$ n_4 n_2 + +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_1, n_4, n_3)) +letting s be {(n_1, n_4), (n_3, n_1), (n_4, n_3)} +$ Visualisation for s +$ n_1 n_4 +$ n_3 n_1 +$ n_4 n_3 + From 5fa1ca8b3b271fb233a32b4b24b0148a4b8eeb1b Mon Sep 17 00:00:00 2001 From: Fraser Dunlop Date: Wed, 5 Dec 2018 11:56:10 +0000 Subject: [PATCH 046/229] Stop Literals matching Vertical image rule for permutation --- src/Conjure/Rules/Horizontal/Permutation.hs | 211 +++++++++++--------- src/Conjure/Rules/Vertical/Permutation.hs | 51 ++--- src/Conjure/UI/Model.hs | 55 +++-- 3 files changed, 171 insertions(+), 146 deletions(-) diff --git a/src/Conjure/Rules/Horizontal/Permutation.hs b/src/Conjure/Rules/Horizontal/Permutation.hs index 63e77d0785..d5edbe930e 100644 --- a/src/Conjure/Rules/Horizontal/Permutation.hs +++ b/src/Conjure/Rules/Horizontal/Permutation.hs @@ -1,16 +1,14 @@ {-# LANGUAGE QuasiQuotes #-} module Conjure.Rules.Horizontal.Permutation where import Conjure.Rules.Import -import Data.List (cycle) import Data.Permutation (size, fromCycles, toFunction) -import Conjure.Process.Enumerate ( enumerateDomain ) rule_Cardinality_Literal :: Rule rule_Cardinality_Literal = "permutation-cardinality-literal" `namedRule` theRule where theRule p' = do p <- match opTwoBars p' - (TypePermutation inner, elems) <- match permutationLiteral p + (TypePermutation _, elems) <- match permutationLiteral p let i' = Constant . ConstantInt AnyTag . fromIntegral . size <$> fromCycles elems case i' of Left er -> fail $ "Permutation literal invalid." <++> stringToDoc (show er) @@ -30,7 +28,9 @@ rule_Equality = "permutation-equality" `namedRule` theRule where , do (rPat, r) <- quantifiedVar (lPat, l) <- quantifiedVar - return [essence| and([ image(&p,&l) = &r | (&lPat,&rPat) <- &q]) |] + return [essence| and([ 1 = sum([ toInt(&r = &l) + | &lPat <- &p]) + | &rPat <- &q]) |] ) @@ -63,95 +63,80 @@ rule_Permute_Comprehension_Tuples_Literal = "permutation-comprehension-tuples{As ) theRule _ = na "rule_Comprehension_Tuples_Literal" +rule_Image_Literal :: Rule +rule_Image_Literal = "permutation-image-literal" `namedRule` theRule where + theRule [essence| image(&p, &i) |] = do + (TypePermutation inner, elems) <- match permutationLiteral p + DomainPermutation _ _ innerP <- domainOf p + let f' = toFunction <$> fromCycles elems + case f' of + Left er -> fail $ "Permutation literal invalid." <++> stringToDoc (show er) + Right f -> do + let outLiteral = make matrixLiteral + (TypeMatrix (TypeInt AnyTag) (TypeTuple [inner,inner])) innerP + [ AbstractLiteral (AbsLitTuple [de + ,f de]) + | de <- join elems + ] + typeI <- typeOf i + if typeI `containsType` inner + then do + if typesUnify [inner, typeI] + then do + innerD <- domainOf i + return + ( "Horizontal rule for permutation literal application to a single value (image), AsFunction representation" + , do + (hName, h) <- auxiliaryVar + (fPat, f) <- quantifiedVar + (tPat, t) <- quantifiedVar + (gPat, g) <- quantifiedVar + (ePat, _) <- quantifiedVar + return $ WithLocals + [essence| &h |] + (AuxiliaryVars + [ Declaration (FindOrGiven LocalFind hName innerD) + , SuchThat + [ [essence| + (forAll (&fPat, &tPat) in &outLiteral . &f = &i <-> &h = &t) + /\ (!(exists (&gPat, &ePat) in &outLiteral . &g = &h) <-> &h = &i) + |] + ] + ] + ) + ) + else na "rule_Permute_Literal" + else return + ( "Horizontal rule for permutation application to a type the permutation doesn't care about" + , do + return [essence| &i |] + ) + theRule _ = na "rule_Image_Literal" + + +rule_In :: Rule +rule_In = "permutation-in" `namedRule` theRule where + theRule p = do + (x,s) <- match opIn p + TypePermutation{} <- typeOf s + -- do not apply this rule to quantified variables + -- or else we might miss the opportunity to apply a more specific vertical rule + if referenceToComprehensionVar s + then na "rule_In" + else return () + return + ( "Horizontal rule for permutation-in." + , do + (iPat, i) <- quantifiedVar + return [essence| exists &iPat in &s . &i = &x |] + ) + + + + -- --- ---rule_Compose :: Rule ---rule_Compose = "permutation-compose{rule_Compose}" `namedRule` theRule where --- theRule [essence| image(compose(&g, &h),&i) |] = do --- TypePermutation innerG <- typeOf g --- TypePermutation innerH <- typeOf g --- typeI <- typeOf i --- if typesUnify [innerG, innerH, typeI] --- then return --- ( "Horizontal rule for permutation composition/application" --- , do --- return [essence| image(&g, image(&h,&i)) |] --- ) --- else na "rule_Compose" --- theRule _ = na "rule_Compose" --- --- ---rule_Permutation_Inverse :: Rule ---rule_Permutation_Inverse = "permutation-inverse{AsFunction}" `namedRule` theRule where --- theRule [essence| inverse(&p1, &p2)|] = do --- case p1 of WithLocals{} -> na "bubble-delay" ; _ -> return () --- case p2 of WithLocals{} -> na "bubble-delay" ; _ -> return () --- TypePermutation{} <- typeOf p1 --- TypePermutation{} <- typeOf p2 --- return --- ( "Vertical rule for permutation-inverse, AsFunction representation" --- , do --- (iPat, i) <- quantifiedVar --- return [essence| --- (forAll &iPat in &p1 . image(&p2,&i[2]) = &i[1]) --- /\ --- (forAll &iPat in &p2 . image(&p1,&i[2]) = &i[1]) --- |] --- ) --- theRule _ = na "rule_Permutation_Equality" --- ---rule_Permute_Literal :: Rule ---rule_Permute_Literal = "permutation-image-literal{AsFunction}" `namedRule` theRule where --- theRule [essence| image(&p, &i) |] = do --- (TypePermutation inner, elems) <- match permutationLiteral p --- case i of WithLocals{} -> na "bubble-delay" ; _ -> return () --- typeI <- typeOf i ----- traceM $ show typeI --- if typeI `containsType` inner --- then do --- if typesUnify [inner, typeI] --- then do --- innerD <- domainOf i --- let prmTup pt = take (length pt) $ zip (cycle pt) (drop 1 $ cycle pt) --- permTups = join $ prmTup <$> elems --- let outLiteral = make matrixLiteral --- (TypeMatrix (TypeInt NoTag) (TypeTuple [inner,inner])) --- (DomainInt NoTag [RangeBounded 1 (fromInt (genericLength permTups))]) --- [ AbstractLiteral (AbsLitTuple [a,b]) --- | (a,b) <- permTups --- ] --- return --- ( "Horizontal rule for permutation literal application to a single value (image), AsFunction representation" --- , do --- (hName, h) <- auxiliaryVar --- (fPat, f) <- quantifiedVar --- (tPat, t) <- quantifiedVar --- (gPat, g) <- quantifiedVar --- (ePat, _) <- quantifiedVar --- return $ WithLocals --- [essence| &h |] --- (AuxiliaryVars --- [ Declaration (FindOrGiven LocalFind hName innerD) --- , SuchThat --- [ [essence| --- (forAll (&fPat, &tPat) in &outLiteral . &f = &i <-> &h = &t) --- /\ (!(exists (&gPat, &ePat) in &outLiteral . &g = &h) <-> &h = &i) --- |] --- ] --- ] --- ) --- ) --- else na "rule_Permute_Literal" --- else return --- ( "Horizontal rule for permutation application to a type the permutation doesn't care about" --- , do --- return [essence| &i |] --- ) --- theRule _ = na "rule_Permute_Literal" --- --- ---rule_Permute_Literal_Comprehension :: Rule ---rule_Permute_Literal_Comprehension = "permutation-image-literal-comprehension{AsFunction}" `namedRule` theRule where +--rule_Image_Literal_Comprehension :: Rule +--rule_Image_Literal_Comprehension = "permutation-image-literal-comprehension{AsFunction}" `namedRule` theRule where -- theRule (Comprehension body gensOrConds) = do -- (gocBefore, (pat, p, i), gocAfter) <- matchFirst gensOrConds $ \ goc -> case goc of -- Generator (GenInExpr pat [essence| image(&p, &i) |]) -> return (pat, p, i) @@ -196,7 +181,7 @@ rule_Permute_Comprehension_Tuples_Literal = "permutation-comprehension-tuples{As -- ] -- ) -- ) --- else na "rule_Permute_Literal" +-- else na "rule_Image_Literal" -- else return -- ( "Horizontal rule for permutation application to a type the permutation doesn't care about" -- , return @@ -204,6 +189,44 @@ rule_Permute_Comprehension_Tuples_Literal = "permutation-comprehension-tuples{As -- ++ [Generator (GenInExpr pat [essence| &i |])] -- ++ gocAfter) -- ) --- theRule _ = na "rule_Permute_Literal" +-- theRule _ = na "rule_Image_Literal" -- + -- +-- +--rule_Compose :: Rule +--rule_Compose = "permutation-compose{rule_Compose}" `namedRule` theRule where +-- theRule [essence| image(compose(&g, &h),&i) |] = do +-- TypePermutation innerG <- typeOf g +-- TypePermutation innerH <- typeOf g +-- typeI <- typeOf i +-- if typesUnify [innerG, innerH, typeI] +-- then return +-- ( "Horizontal rule for permutation composition/application" +-- , do +-- return [essence| image(&g, image(&h,&i)) |] +-- ) +-- else na "rule_Compose" +-- theRule _ = na "rule_Compose" +-- +-- +--rule_Permutation_Inverse :: Rule +--rule_Permutation_Inverse = "permutation-inverse{AsFunction}" `namedRule` theRule where +-- theRule [essence| inverse(&p1, &p2)|] = do +-- case p1 of WithLocals{} -> na "bubble-delay" ; _ -> return () +-- case p2 of WithLocals{} -> na "bubble-delay" ; _ -> return () +-- TypePermutation{} <- typeOf p1 +-- TypePermutation{} <- typeOf p2 +-- return +-- ( "Vertical rule for permutation-inverse, AsFunction representation" +-- , do +-- (iPat, i) <- quantifiedVar +-- return [essence| +-- (forAll &iPat in &p1 . image(&p2,&i[2]) = &i[1]) +-- /\ +-- (forAll &iPat in &p2 . image(&p1,&i[2]) = &i[1]) +-- |] +-- ) +-- theRule _ = na "rule_Permutation_Equality" + + diff --git a/src/Conjure/Rules/Vertical/Permutation.hs b/src/Conjure/Rules/Vertical/Permutation.hs index 705e57e187..09bf9ec5e6 100644 --- a/src/Conjure/Rules/Vertical/Permutation.hs +++ b/src/Conjure/Rules/Vertical/Permutation.hs @@ -48,6 +48,33 @@ rule_Permute_Comprehension_Tuples = "permutation-comprehension-tuples{AsFunction theRule _ = na "rule_Comprehension" +rule_Image :: Rule +rule_Image = "permutation-image{AsFunction}" `namedRule` theRule where + theRule [essence| image(&p, &i) |] = do + TypePermutation inner <- typeOf p + case match permutationLiteral p of + Nothing -> do + typeI <- typeOf i + if typeI `containsType` inner + then do + [f] <- downX1 p + if typesUnify [inner, typeI] + then return + ( "Vertical rule for permutation application to a single value" + , do + return [essence| [&i, catchUndef(image(&f,&i),0)][toInt(&i in defined(&f))+1] |] + ) + else na "rule_Image" + else return + ( "Vertical rule for permutation application to a type the permutation doesn't care about" + , do + return [essence| &i |] + ) + _ -> na "rule_Image" + theRule _ = na "rule_Image" + + + -- -- --rule_Permutation_Inverse :: Rule @@ -130,30 +157,6 @@ rule_Permute_Comprehension_Tuples = "permutation-comprehension-tuples{AsFunction -- ) -- theRule _ = na "rule_Permutation_Equality_Comprehension" --- --- ---rule_Permute :: Rule ---rule_Permute = "permutation-image{AsFunction}" `namedRule` theRule where --- theRule [essence| image(&p, &i) |] = do --- TypePermutation inner <- typeOf p --- typeI <- typeOf i --- if typeI `containsType` inner --- then do --- [f] <- downX1 p --- if typesUnify [inner, typeI] --- then return --- ( "Vertical rule for permutation application to a single value" --- , do --- return [essence| [&i, catchUndef(image(&f,&i),0)][toInt(&i in defined(&f))+1] |] --- ) --- else na "rule_Permute" --If we hit this then we should hit a refinement error --- else return --- ( "Vertical rule for permutation application to a type the permutation doesn't care about" --- , do --- return [essence| &i |] --- ) --- theRule _ = na "rule_Permute" --- -- --rule_Permute_Comprehension :: Rule --rule_Permute_Comprehension = "permutation-image{AsFunction}" `namedRule` theRule where diff --git a/src/Conjure/UI/Model.hs b/src/Conjure/UI/Model.hs index 7ab70b26c2..7c69ef4edd 100644 --- a/src/Conjure/UI/Model.hs +++ b/src/Conjure/UI/Model.hs @@ -1086,7 +1086,21 @@ paramRules = verticalRules :: [Rule] verticalRules = - [ Vertical.Tuple.rule_Tuple_Eq + [ Vertical.Permutation.rule_Image +-- , Vertical.Permutation.rule_Permute_Comprehension + , Vertical.Permutation.rule_Cardinality + , Vertical.Permutation.rule_Permute_Comprehension_Tuples +-- , Vertical.Permutation.rule_Permutation_Equality +-- , Vertical.Permutation.rule_Permutation_Equality_Comprehension +-- , Vertical.Permutation.rule_Relation_Permute +-- , Vertical.Permutation.rule_Relation_Permute_Comprehension +-- , Vertical.Permutation.rule_Set_Permute +-- , Vertical.Permutation.rule_Tuple_Permute +-- , Vertical.Permutation.rule_Tuple_Permute_Comprehension +-- , Vertical.Permutation.rule_Matrix_Permute +-- , Vertical.Permutation.rule_Matrix_Permute_Comprehension + + , Vertical.Tuple.rule_Tuple_Eq , Vertical.Tuple.rule_Tuple_Neq , Vertical.Tuple.rule_Tuple_Leq , Vertical.Tuple.rule_Tuple_Lt @@ -1187,26 +1201,22 @@ verticalRules = , Vertical.Partition.PartitionAsSet.rule_Comprehension , Vertical.Partition.Occurrence.rule_Comprehension - , Vertical.Permutation.rule_Cardinality - , Vertical.Permutation.rule_Permute_Comprehension_Tuples --- , Vertical.Permutation.rule_Permutation_Equality --- , Vertical.Permutation.rule_Permutation_Equality_Comprehension --- , Vertical.Permutation.rule_Relation_Permute --- , Vertical.Permutation.rule_Relation_Permute_Comprehension --- , Vertical.Permutation.rule_Set_Permute --- , Vertical.Permutation.rule_Tuple_Permute --- , Vertical.Permutation.rule_Tuple_Permute_Comprehension --- , Vertical.Permutation.rule_Matrix_Permute --- , Vertical.Permutation.rule_Matrix_Permute_Comprehension - - - - ] horizontalRules :: [Rule] horizontalRules = - [ Horizontal.Set.rule_Comprehension_Literal + [ Horizontal.Permutation.rule_Cardinality_Literal + , Horizontal.Permutation.rule_Equality + , Horizontal.Permutation.rule_Permute_Comprehension_Tuples_Literal + , Horizontal.Permutation.rule_Image_Literal + , Horizontal.Permutation.rule_In +-- , Horizontal.Permutation.rule_Image_Literal_Comprehension +-- , Horizontal.Permutation.rule_Permutation_Inverse + +-- , Horizontal.Permutation.rule_Compose + + + , Horizontal.Set.rule_Comprehension_Literal , Horizontal.Set.rule_Eq , Horizontal.Set.rule_Neq , Horizontal.Set.rule_Subset @@ -1315,15 +1325,6 @@ horizontalRules = , Horizontal.Partition.rule_Card , Horizontal.Partition.rule_In - , Horizontal.Permutation.rule_Cardinality_Literal - , Horizontal.Permutation.rule_Equality - , Horizontal.Permutation.rule_Permute_Comprehension_Tuples_Literal --- , Horizontal.Permutation.rule_Permutation_Inverse --- , Horizontal.Permutation.rule_Permute_Literal --- , Horizontal.Permutation.rule_Permute_Literal_Comprehension --- , Horizontal.Permutation.rule_Compose - - ] @@ -1396,8 +1397,6 @@ delayedRules = , Vertical.Matrix.rule_Concatenate_Singleton , Vertical.Matrix.rule_MatrixIndexing --- , Vertical.Permutation.rule_Permute --- , Vertical.Permutation.rule_Permute_Comprehension ] , [ rule_ReducerToComprehension ] From cf96915e87388a1f1dc6a0331d422559d91e2213 Mon Sep 17 00:00:00 2001 From: Fraser Dunlop Date: Thu, 6 Dec 2018 10:07:44 +0000 Subject: [PATCH 047/229] enum and unnamed tests for image --- .../permutation.essence | 10 ++++++ .../0004_find_permutation_in_generator/run.sh | 3 ++ .../stdout.expected | 36 +++++++++++++++++++ .../minimaler_bug_example/permutation.essence | 16 +++++++++ .../enum/minimaler_bug_example/run.sh | 3 ++ .../permutation.essence | 13 +++++++ .../permutation.param | 2 ++ .../permutation2.param | 2 ++ .../0001_given_permutation_given_enum}/run.sh | 0 .../stdout.expected | 13 +++++++ .../permutation.essence | 12 +++++++ .../permutation.param | 1 + .../run.sh | 0 .../stdout.expected | 8 +++++ .../permutation.essence | 12 +++++++ .../permutation.param | 1 + .../run.sh | 0 .../stdout.expected | 8 +++++ .../permutation.essence | 13 +++++++ .../permutation.param | 2 ++ .../permutation2.essence | 2 ++ .../0004_given_permutation_find_enum}/run.sh | 0 .../stdout.expected | 13 +++++++ .../permutation.essence | 14 ++++++++ .../permutation.param | 2 ++ .../permutation2.param | 2 ++ .../0005_find_permutation_given_enums}/run.sh | 0 .../stdout.expected | 13 +++++++ .../permutation.essence | 12 +++++++ .../permutation.param | 1 + .../permutation2.param | 1 + .../run.sh | 0 .../stdout.expected | 13 +++++++ .../permutation.essence | 14 ++++++++ .../0007_find_permutation_find_enums/run.sh | 3 ++ .../stdout.expected | 10 ++++++ .../permutation.essence | 0 .../permutation.param | 0 .../permutation2.param | 0 .../0001_given_permutation_given_int/run.sh | 3 ++ .../stdout.expected | 0 .../permutation.essence | 0 .../permutation.param | 0 .../0002_given_permutation_letting_int/run.sh | 3 ++ .../stdout.expected | 0 .../permutation.essence | 0 .../permutation.param | 0 .../0003_given_permutation_letting_int/run.sh | 3 ++ .../stdout.expected | 0 .../permutation.essence | 0 .../permutation.param | 0 .../permutation2.essence | 0 .../0004_given_permutation_find_int/run.sh | 3 ++ .../stdout.expected | 0 .../permutation.essence | 0 .../permutation.param | 0 .../permutation2.param | 0 .../0005_find_permutation_given_ints/run.sh | 3 ++ .../stdout.expected | 0 .../permutation.essence | 0 .../permutation.param | 0 .../permutation2.param | 0 .../0006_letting_permutation_given_int/run.sh | 3 ++ .../stdout.expected | 0 .../permutation.essence | 14 ++++++++ .../0007_find_permutation_find_ints/run.sh | 3 ++ .../stdout.expected | 10 ++++++ .../permutation.essence | 14 ++++++++ .../run.sh | 3 ++ .../stdout.expected | 11 ++++++ 70 files changed, 328 insertions(+) create mode 100644 tests/custom/permutations/03_generators/enum/0004_find_permutation_in_generator/permutation.essence create mode 100755 tests/custom/permutations/03_generators/enum/0004_find_permutation_in_generator/run.sh create mode 100644 tests/custom/permutations/03_generators/enum/0004_find_permutation_in_generator/stdout.expected create mode 100644 tests/custom/permutations/03_generators/enum/minimaler_bug_example/permutation.essence create mode 100755 tests/custom/permutations/03_generators/enum/minimaler_bug_example/run.sh create mode 100644 tests/custom/permutations/04_image/enum/0001_given_permutation_given_enum/permutation.essence create mode 100644 tests/custom/permutations/04_image/enum/0001_given_permutation_given_enum/permutation.param create mode 100644 tests/custom/permutations/04_image/enum/0001_given_permutation_given_enum/permutation2.param rename tests/custom/permutations/04_image/{0001_given_permutation_given_int => enum/0001_given_permutation_given_enum}/run.sh (100%) create mode 100644 tests/custom/permutations/04_image/enum/0001_given_permutation_given_enum/stdout.expected create mode 100644 tests/custom/permutations/04_image/enum/0002_given_permutation_letting_enum/permutation.essence create mode 100644 tests/custom/permutations/04_image/enum/0002_given_permutation_letting_enum/permutation.param rename tests/custom/permutations/04_image/{0002_given_permutation_letting_int => enum/0002_given_permutation_letting_enum}/run.sh (100%) create mode 100644 tests/custom/permutations/04_image/enum/0002_given_permutation_letting_enum/stdout.expected create mode 100644 tests/custom/permutations/04_image/enum/0003_given_permutation_letting_enum/permutation.essence create mode 100644 tests/custom/permutations/04_image/enum/0003_given_permutation_letting_enum/permutation.param rename tests/custom/permutations/04_image/{0003_given_permutation_letting_int => enum/0003_given_permutation_letting_enum}/run.sh (100%) create mode 100644 tests/custom/permutations/04_image/enum/0003_given_permutation_letting_enum/stdout.expected create mode 100644 tests/custom/permutations/04_image/enum/0004_given_permutation_find_enum/permutation.essence create mode 100644 tests/custom/permutations/04_image/enum/0004_given_permutation_find_enum/permutation.param create mode 100644 tests/custom/permutations/04_image/enum/0004_given_permutation_find_enum/permutation2.essence rename tests/custom/permutations/04_image/{0004_given_permutation_find_int => enum/0004_given_permutation_find_enum}/run.sh (100%) create mode 100644 tests/custom/permutations/04_image/enum/0004_given_permutation_find_enum/stdout.expected create mode 100644 tests/custom/permutations/04_image/enum/0005_find_permutation_given_enums/permutation.essence create mode 100644 tests/custom/permutations/04_image/enum/0005_find_permutation_given_enums/permutation.param create mode 100644 tests/custom/permutations/04_image/enum/0005_find_permutation_given_enums/permutation2.param rename tests/custom/permutations/04_image/{0005_find_permutation_given_ints => enum/0005_find_permutation_given_enums}/run.sh (100%) create mode 100644 tests/custom/permutations/04_image/enum/0005_find_permutation_given_enums/stdout.expected create mode 100644 tests/custom/permutations/04_image/enum/0006_letting_permutation_given_enum/permutation.essence create mode 100644 tests/custom/permutations/04_image/enum/0006_letting_permutation_given_enum/permutation.param create mode 100644 tests/custom/permutations/04_image/enum/0006_letting_permutation_given_enum/permutation2.param rename tests/custom/permutations/04_image/{0006_letting_permutation_given_int => enum/0006_letting_permutation_given_enum}/run.sh (100%) create mode 100644 tests/custom/permutations/04_image/enum/0006_letting_permutation_given_enum/stdout.expected create mode 100644 tests/custom/permutations/04_image/enum/0007_find_permutation_find_enums/permutation.essence create mode 100755 tests/custom/permutations/04_image/enum/0007_find_permutation_find_enums/run.sh create mode 100644 tests/custom/permutations/04_image/enum/0007_find_permutation_find_enums/stdout.expected rename tests/custom/permutations/04_image/{ => int}/0001_given_permutation_given_int/permutation.essence (100%) rename tests/custom/permutations/04_image/{ => int}/0001_given_permutation_given_int/permutation.param (100%) rename tests/custom/permutations/04_image/{ => int}/0001_given_permutation_given_int/permutation2.param (100%) create mode 100755 tests/custom/permutations/04_image/int/0001_given_permutation_given_int/run.sh rename tests/custom/permutations/04_image/{ => int}/0001_given_permutation_given_int/stdout.expected (100%) rename tests/custom/permutations/04_image/{ => int}/0002_given_permutation_letting_int/permutation.essence (100%) rename tests/custom/permutations/04_image/{ => int}/0002_given_permutation_letting_int/permutation.param (100%) create mode 100755 tests/custom/permutations/04_image/int/0002_given_permutation_letting_int/run.sh rename tests/custom/permutations/04_image/{ => int}/0002_given_permutation_letting_int/stdout.expected (100%) rename tests/custom/permutations/04_image/{ => int}/0003_given_permutation_letting_int/permutation.essence (100%) rename tests/custom/permutations/04_image/{ => int}/0003_given_permutation_letting_int/permutation.param (100%) create mode 100755 tests/custom/permutations/04_image/int/0003_given_permutation_letting_int/run.sh rename tests/custom/permutations/04_image/{ => int}/0003_given_permutation_letting_int/stdout.expected (100%) rename tests/custom/permutations/04_image/{ => int}/0004_given_permutation_find_int/permutation.essence (100%) rename tests/custom/permutations/04_image/{ => int}/0004_given_permutation_find_int/permutation.param (100%) rename tests/custom/permutations/04_image/{ => int}/0004_given_permutation_find_int/permutation2.essence (100%) create mode 100755 tests/custom/permutations/04_image/int/0004_given_permutation_find_int/run.sh rename tests/custom/permutations/04_image/{ => int}/0004_given_permutation_find_int/stdout.expected (100%) rename tests/custom/permutations/04_image/{ => int}/0005_find_permutation_given_ints/permutation.essence (100%) rename tests/custom/permutations/04_image/{ => int}/0005_find_permutation_given_ints/permutation.param (100%) rename tests/custom/permutations/04_image/{ => int}/0005_find_permutation_given_ints/permutation2.param (100%) create mode 100755 tests/custom/permutations/04_image/int/0005_find_permutation_given_ints/run.sh rename tests/custom/permutations/04_image/{ => int}/0005_find_permutation_given_ints/stdout.expected (100%) rename tests/custom/permutations/04_image/{ => int}/0006_letting_permutation_given_int/permutation.essence (100%) rename tests/custom/permutations/04_image/{ => int}/0006_letting_permutation_given_int/permutation.param (100%) rename tests/custom/permutations/04_image/{ => int}/0006_letting_permutation_given_int/permutation2.param (100%) create mode 100755 tests/custom/permutations/04_image/int/0006_letting_permutation_given_int/run.sh rename tests/custom/permutations/04_image/{ => int}/0006_letting_permutation_given_int/stdout.expected (100%) create mode 100644 tests/custom/permutations/04_image/int/0007_find_permutation_find_ints/permutation.essence create mode 100755 tests/custom/permutations/04_image/int/0007_find_permutation_find_ints/run.sh create mode 100644 tests/custom/permutations/04_image/int/0007_find_permutation_find_ints/stdout.expected create mode 100644 tests/custom/permutations/04_image/unnamed/0007_find_permutation_find_unnameds/permutation.essence create mode 100755 tests/custom/permutations/04_image/unnamed/0007_find_permutation_find_unnameds/run.sh create mode 100644 tests/custom/permutations/04_image/unnamed/0007_find_permutation_find_unnameds/stdout.expected diff --git a/tests/custom/permutations/03_generators/enum/0004_find_permutation_in_generator/permutation.essence b/tests/custom/permutations/03_generators/enum/0004_find_permutation_in_generator/permutation.essence new file mode 100644 index 0000000000..80c1a9b4e3 --- /dev/null +++ b/tests/custom/permutations/03_generators/enum/0004_find_permutation_in_generator/permutation.essence @@ -0,0 +1,10 @@ +letting n be new type enum {E1,E2,E3,E4} +find p : permutation (size 3) of n + + +such that + and([l != r | (l,r) <- p]) + + + + diff --git a/tests/custom/permutations/03_generators/enum/0004_find_permutation_in_generator/run.sh b/tests/custom/permutations/03_generators/enum/0004_find_permutation_in_generator/run.sh new file mode 100755 index 0000000000..de361d4354 --- /dev/null +++ b/tests/custom/permutations/03_generators/enum/0004_find_permutation_in_generator/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence --number-of-solutions=40 +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/03_generators/enum/0004_find_permutation_in_generator/stdout.expected b/tests/custom/permutations/03_generators/enum/0004_find_permutation_in_generator/stdout.expected new file mode 100644 index 0000000000..290f204bac --- /dev/null +++ b/tests/custom/permutations/03_generators/enum/0004_find_permutation_in_generator/stdout.expected @@ -0,0 +1,36 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Copying solution to: permutation-000001.solution +Copying solution to: permutation-000002.solution +Copying solution to: permutation-000003.solution +Copying solution to: permutation-000004.solution +Copying solution to: permutation-000005.solution +Copying solution to: permutation-000006.solution +Copying solution to: permutation-000007.solution +Copying solution to: permutation-000008.solution +language Essence 1.3 + +letting p be permutation((E2, E3, E4)) +language Essence 1.3 + +letting p be permutation((E2, E4, E3)) +language Essence 1.3 + +letting p be permutation((E1, E2, E3)) +language Essence 1.3 + +letting p be permutation((E1, E2, E4)) +language Essence 1.3 + +letting p be permutation((E1, E3, E2)) +language Essence 1.3 + +letting p be permutation((E1, E3, E4)) +language Essence 1.3 + +letting p be permutation((E1, E4, E2)) +language Essence 1.3 + +letting p be permutation((E1, E4, E3)) diff --git a/tests/custom/permutations/03_generators/enum/minimaler_bug_example/permutation.essence b/tests/custom/permutations/03_generators/enum/minimaler_bug_example/permutation.essence new file mode 100644 index 0000000000..fcacda0a92 --- /dev/null +++ b/tests/custom/permutations/03_generators/enum/minimaler_bug_example/permutation.essence @@ -0,0 +1,16 @@ +letting n be new type enum {E1,E2,E3,E4} + +$ We don't need a permutation to reach this bug +$letting p be permutation((E1,E3,E4)) +$ A tuple of enums is sufficient +letting i be (E1,E2) + +find s : matrix indexed by [int(1..3)] of (n,n) + + +such that i in s +$ and([e in s | e <- p]) + + + + diff --git a/tests/custom/permutations/03_generators/enum/minimaler_bug_example/run.sh b/tests/custom/permutations/03_generators/enum/minimaler_bug_example/run.sh new file mode 100755 index 0000000000..b4899d6266 --- /dev/null +++ b/tests/custom/permutations/03_generators/enum/minimaler_bug_example/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/04_image/enum/0001_given_permutation_given_enum/permutation.essence b/tests/custom/permutations/04_image/enum/0001_given_permutation_given_enum/permutation.essence new file mode 100644 index 0000000000..d72ee5d644 --- /dev/null +++ b/tests/custom/permutations/04_image/enum/0001_given_permutation_given_enum/permutation.essence @@ -0,0 +1,13 @@ +letting n be new type enum {E0, E1, E2, E3, E4, E5, E6} + +given i : n + +given p : permutation of n + +find j : n + +such that j = image(p, i) + + + + diff --git a/tests/custom/permutations/04_image/enum/0001_given_permutation_given_enum/permutation.param b/tests/custom/permutations/04_image/enum/0001_given_permutation_given_enum/permutation.param new file mode 100644 index 0000000000..b09ac9d45d --- /dev/null +++ b/tests/custom/permutations/04_image/enum/0001_given_permutation_given_enum/permutation.param @@ -0,0 +1,2 @@ +letting p be permutation((E1,E3,E4)) +letting i be E1 diff --git a/tests/custom/permutations/04_image/enum/0001_given_permutation_given_enum/permutation2.param b/tests/custom/permutations/04_image/enum/0001_given_permutation_given_enum/permutation2.param new file mode 100644 index 0000000000..c02623b95d --- /dev/null +++ b/tests/custom/permutations/04_image/enum/0001_given_permutation_given_enum/permutation2.param @@ -0,0 +1,2 @@ +letting p be permutation((E1,E3,E4)) +letting i be E6 diff --git a/tests/custom/permutations/04_image/0001_given_permutation_given_int/run.sh b/tests/custom/permutations/04_image/enum/0001_given_permutation_given_enum/run.sh similarity index 100% rename from tests/custom/permutations/04_image/0001_given_permutation_given_int/run.sh rename to tests/custom/permutations/04_image/enum/0001_given_permutation_given_enum/run.sh diff --git a/tests/custom/permutations/04_image/enum/0001_given_permutation_given_enum/stdout.expected b/tests/custom/permutations/04_image/enum/0001_given_permutation_given_enum/stdout.expected new file mode 100644 index 0000000000..41fd1f1fbe --- /dev/null +++ b/tests/custom/permutations/04_image/enum/0001_given_permutation_given_enum/stdout.expected @@ -0,0 +1,13 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime permutation.param +Savile Row: model000001.eprime permutation2.param +Copying solution to: permutation-permutation.solution +Copying solution to: permutation-permutation2.solution +language Essence 1.3 + +letting j be E3 +language Essence 1.3 + +letting j be E6 diff --git a/tests/custom/permutations/04_image/enum/0002_given_permutation_letting_enum/permutation.essence b/tests/custom/permutations/04_image/enum/0002_given_permutation_letting_enum/permutation.essence new file mode 100644 index 0000000000..61a292a552 --- /dev/null +++ b/tests/custom/permutations/04_image/enum/0002_given_permutation_letting_enum/permutation.essence @@ -0,0 +1,12 @@ +letting n be new type enum {E0,E1,E2,E3,E4,E5,E6} +letting i be E1 + +given p : permutation of n + +find j : n + +such that j = image(p, i) + + + + diff --git a/tests/custom/permutations/04_image/enum/0002_given_permutation_letting_enum/permutation.param b/tests/custom/permutations/04_image/enum/0002_given_permutation_letting_enum/permutation.param new file mode 100644 index 0000000000..19349bb872 --- /dev/null +++ b/tests/custom/permutations/04_image/enum/0002_given_permutation_letting_enum/permutation.param @@ -0,0 +1 @@ +letting p be permutation((E1,E3,E4)) diff --git a/tests/custom/permutations/04_image/0002_given_permutation_letting_int/run.sh b/tests/custom/permutations/04_image/enum/0002_given_permutation_letting_enum/run.sh similarity index 100% rename from tests/custom/permutations/04_image/0002_given_permutation_letting_int/run.sh rename to tests/custom/permutations/04_image/enum/0002_given_permutation_letting_enum/run.sh diff --git a/tests/custom/permutations/04_image/enum/0002_given_permutation_letting_enum/stdout.expected b/tests/custom/permutations/04_image/enum/0002_given_permutation_letting_enum/stdout.expected new file mode 100644 index 0000000000..f512b33cb4 --- /dev/null +++ b/tests/custom/permutations/04_image/enum/0002_given_permutation_letting_enum/stdout.expected @@ -0,0 +1,8 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime permutation.param +Copying solution to: permutation-permutation.solution +language Essence 1.3 + +letting j be E3 diff --git a/tests/custom/permutations/04_image/enum/0003_given_permutation_letting_enum/permutation.essence b/tests/custom/permutations/04_image/enum/0003_given_permutation_letting_enum/permutation.essence new file mode 100644 index 0000000000..a136a2c21d --- /dev/null +++ b/tests/custom/permutations/04_image/enum/0003_given_permutation_letting_enum/permutation.essence @@ -0,0 +1,12 @@ +letting n be new type enum {E0,E1,E2,E3,E4,E5,E6} +letting i be E6 + +given p : permutation of n + +find j : n + +such that j = image(p, i) + + + + diff --git a/tests/custom/permutations/04_image/enum/0003_given_permutation_letting_enum/permutation.param b/tests/custom/permutations/04_image/enum/0003_given_permutation_letting_enum/permutation.param new file mode 100644 index 0000000000..19349bb872 --- /dev/null +++ b/tests/custom/permutations/04_image/enum/0003_given_permutation_letting_enum/permutation.param @@ -0,0 +1 @@ +letting p be permutation((E1,E3,E4)) diff --git a/tests/custom/permutations/04_image/0003_given_permutation_letting_int/run.sh b/tests/custom/permutations/04_image/enum/0003_given_permutation_letting_enum/run.sh similarity index 100% rename from tests/custom/permutations/04_image/0003_given_permutation_letting_int/run.sh rename to tests/custom/permutations/04_image/enum/0003_given_permutation_letting_enum/run.sh diff --git a/tests/custom/permutations/04_image/enum/0003_given_permutation_letting_enum/stdout.expected b/tests/custom/permutations/04_image/enum/0003_given_permutation_letting_enum/stdout.expected new file mode 100644 index 0000000000..fa4fe849ea --- /dev/null +++ b/tests/custom/permutations/04_image/enum/0003_given_permutation_letting_enum/stdout.expected @@ -0,0 +1,8 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime permutation.param +Copying solution to: permutation-permutation.solution +language Essence 1.3 + +letting j be E6 diff --git a/tests/custom/permutations/04_image/enum/0004_given_permutation_find_enum/permutation.essence b/tests/custom/permutations/04_image/enum/0004_given_permutation_find_enum/permutation.essence new file mode 100644 index 0000000000..97fce44295 --- /dev/null +++ b/tests/custom/permutations/04_image/enum/0004_given_permutation_find_enum/permutation.essence @@ -0,0 +1,13 @@ +letting n be new type enum {E0,E1,E2,E3,E4,E5,E6} + +find i : n + +given p : permutation of n + +given j : n + +such that j = image(p, i) + + + + diff --git a/tests/custom/permutations/04_image/enum/0004_given_permutation_find_enum/permutation.param b/tests/custom/permutations/04_image/enum/0004_given_permutation_find_enum/permutation.param new file mode 100644 index 0000000000..b4965c6a6e --- /dev/null +++ b/tests/custom/permutations/04_image/enum/0004_given_permutation_find_enum/permutation.param @@ -0,0 +1,2 @@ +letting p be permutation((E1,E3,E4)) +letting j be E3 diff --git a/tests/custom/permutations/04_image/enum/0004_given_permutation_find_enum/permutation2.essence b/tests/custom/permutations/04_image/enum/0004_given_permutation_find_enum/permutation2.essence new file mode 100644 index 0000000000..cd3e42be10 --- /dev/null +++ b/tests/custom/permutations/04_image/enum/0004_given_permutation_find_enum/permutation2.essence @@ -0,0 +1,2 @@ +letting p be permutation((E1,E3,E4)) +letting j be E6 diff --git a/tests/custom/permutations/04_image/0004_given_permutation_find_int/run.sh b/tests/custom/permutations/04_image/enum/0004_given_permutation_find_enum/run.sh similarity index 100% rename from tests/custom/permutations/04_image/0004_given_permutation_find_int/run.sh rename to tests/custom/permutations/04_image/enum/0004_given_permutation_find_enum/run.sh diff --git a/tests/custom/permutations/04_image/enum/0004_given_permutation_find_enum/stdout.expected b/tests/custom/permutations/04_image/enum/0004_given_permutation_find_enum/stdout.expected new file mode 100644 index 0000000000..75ee4f23cb --- /dev/null +++ b/tests/custom/permutations/04_image/enum/0004_given_permutation_find_enum/stdout.expected @@ -0,0 +1,13 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime permutation2.essence +Savile Row: model000001.eprime permutation.param +Copying solution to: permutation-permutation2.solution +Copying solution to: permutation-permutation.solution +language Essence 1.3 + +letting i be E1 +language Essence 1.3 + +letting i be E6 diff --git a/tests/custom/permutations/04_image/enum/0005_find_permutation_given_enums/permutation.essence b/tests/custom/permutations/04_image/enum/0005_find_permutation_given_enums/permutation.essence new file mode 100644 index 0000000000..4eacc18605 --- /dev/null +++ b/tests/custom/permutations/04_image/enum/0005_find_permutation_given_enums/permutation.essence @@ -0,0 +1,14 @@ +letting n be new type enum {E0,E1,E2,E3,E4,E5,E6} + +given i : n + +find p : permutation of n + +given j : n + +such that + j = image(p, i) /\ |p| = 3 + + + + diff --git a/tests/custom/permutations/04_image/enum/0005_find_permutation_given_enums/permutation.param b/tests/custom/permutations/04_image/enum/0005_find_permutation_given_enums/permutation.param new file mode 100644 index 0000000000..4298bddeda --- /dev/null +++ b/tests/custom/permutations/04_image/enum/0005_find_permutation_given_enums/permutation.param @@ -0,0 +1,2 @@ +letting i be E4 +letting j be E3 diff --git a/tests/custom/permutations/04_image/enum/0005_find_permutation_given_enums/permutation2.param b/tests/custom/permutations/04_image/enum/0005_find_permutation_given_enums/permutation2.param new file mode 100644 index 0000000000..ad96fe5ec5 --- /dev/null +++ b/tests/custom/permutations/04_image/enum/0005_find_permutation_given_enums/permutation2.param @@ -0,0 +1,2 @@ +letting i be E3 +letting j be E3 diff --git a/tests/custom/permutations/04_image/0005_find_permutation_given_ints/run.sh b/tests/custom/permutations/04_image/enum/0005_find_permutation_given_enums/run.sh similarity index 100% rename from tests/custom/permutations/04_image/0005_find_permutation_given_ints/run.sh rename to tests/custom/permutations/04_image/enum/0005_find_permutation_given_enums/run.sh diff --git a/tests/custom/permutations/04_image/enum/0005_find_permutation_given_enums/stdout.expected b/tests/custom/permutations/04_image/enum/0005_find_permutation_given_enums/stdout.expected new file mode 100644 index 0000000000..8b5ff8e97e --- /dev/null +++ b/tests/custom/permutations/04_image/enum/0005_find_permutation_given_enums/stdout.expected @@ -0,0 +1,13 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime permutation.param +Savile Row: model000001.eprime permutation2.param +Copying solution to: permutation-permutation.solution +Copying solution to: permutation-permutation2.solution +language Essence 1.3 + +letting p be permutation((E3, E5, E4)) +language Essence 1.3 + +letting p be permutation((E4, E5, E6)) diff --git a/tests/custom/permutations/04_image/enum/0006_letting_permutation_given_enum/permutation.essence b/tests/custom/permutations/04_image/enum/0006_letting_permutation_given_enum/permutation.essence new file mode 100644 index 0000000000..b6f45bdb6d --- /dev/null +++ b/tests/custom/permutations/04_image/enum/0006_letting_permutation_given_enum/permutation.essence @@ -0,0 +1,12 @@ +letting n be new type enum {E0,E1,E2,E3,E4,E5,E6} +given i : n +letting p be permutation((E1,E3,E4)) + + +find j : n + +such that j = image(p, i) + + + + diff --git a/tests/custom/permutations/04_image/enum/0006_letting_permutation_given_enum/permutation.param b/tests/custom/permutations/04_image/enum/0006_letting_permutation_given_enum/permutation.param new file mode 100644 index 0000000000..78d957a607 --- /dev/null +++ b/tests/custom/permutations/04_image/enum/0006_letting_permutation_given_enum/permutation.param @@ -0,0 +1 @@ +letting i be E1 diff --git a/tests/custom/permutations/04_image/enum/0006_letting_permutation_given_enum/permutation2.param b/tests/custom/permutations/04_image/enum/0006_letting_permutation_given_enum/permutation2.param new file mode 100644 index 0000000000..4a531ef986 --- /dev/null +++ b/tests/custom/permutations/04_image/enum/0006_letting_permutation_given_enum/permutation2.param @@ -0,0 +1 @@ +letting i be E6 diff --git a/tests/custom/permutations/04_image/0006_letting_permutation_given_int/run.sh b/tests/custom/permutations/04_image/enum/0006_letting_permutation_given_enum/run.sh similarity index 100% rename from tests/custom/permutations/04_image/0006_letting_permutation_given_int/run.sh rename to tests/custom/permutations/04_image/enum/0006_letting_permutation_given_enum/run.sh diff --git a/tests/custom/permutations/04_image/enum/0006_letting_permutation_given_enum/stdout.expected b/tests/custom/permutations/04_image/enum/0006_letting_permutation_given_enum/stdout.expected new file mode 100644 index 0000000000..41fd1f1fbe --- /dev/null +++ b/tests/custom/permutations/04_image/enum/0006_letting_permutation_given_enum/stdout.expected @@ -0,0 +1,13 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime permutation.param +Savile Row: model000001.eprime permutation2.param +Copying solution to: permutation-permutation.solution +Copying solution to: permutation-permutation2.solution +language Essence 1.3 + +letting j be E3 +language Essence 1.3 + +letting j be E6 diff --git a/tests/custom/permutations/04_image/enum/0007_find_permutation_find_enums/permutation.essence b/tests/custom/permutations/04_image/enum/0007_find_permutation_find_enums/permutation.essence new file mode 100644 index 0000000000..c994d8042b --- /dev/null +++ b/tests/custom/permutations/04_image/enum/0007_find_permutation_find_enums/permutation.essence @@ -0,0 +1,14 @@ +letting n be new type enum {E0,E1,E2,E3,E4} + +find i : n + +find p : permutation of n + +find j : n + +such that + j = image(p, i) /\ |p| = 3 + + + + diff --git a/tests/custom/permutations/04_image/enum/0007_find_permutation_find_enums/run.sh b/tests/custom/permutations/04_image/enum/0007_find_permutation_find_enums/run.sh new file mode 100755 index 0000000000..b4899d6266 --- /dev/null +++ b/tests/custom/permutations/04_image/enum/0007_find_permutation_find_enums/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/04_image/enum/0007_find_permutation_find_enums/stdout.expected b/tests/custom/permutations/04_image/enum/0007_find_permutation_find_enums/stdout.expected new file mode 100644 index 0000000000..3531be6272 --- /dev/null +++ b/tests/custom/permutations/04_image/enum/0007_find_permutation_find_enums/stdout.expected @@ -0,0 +1,10 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Copying solution to: permutation.solution +language Essence 1.3 + +letting i be E0 +letting j be E0 +letting p be permutation((E2, E3, E4)) diff --git a/tests/custom/permutations/04_image/0001_given_permutation_given_int/permutation.essence b/tests/custom/permutations/04_image/int/0001_given_permutation_given_int/permutation.essence similarity index 100% rename from tests/custom/permutations/04_image/0001_given_permutation_given_int/permutation.essence rename to tests/custom/permutations/04_image/int/0001_given_permutation_given_int/permutation.essence diff --git a/tests/custom/permutations/04_image/0001_given_permutation_given_int/permutation.param b/tests/custom/permutations/04_image/int/0001_given_permutation_given_int/permutation.param similarity index 100% rename from tests/custom/permutations/04_image/0001_given_permutation_given_int/permutation.param rename to tests/custom/permutations/04_image/int/0001_given_permutation_given_int/permutation.param diff --git a/tests/custom/permutations/04_image/0001_given_permutation_given_int/permutation2.param b/tests/custom/permutations/04_image/int/0001_given_permutation_given_int/permutation2.param similarity index 100% rename from tests/custom/permutations/04_image/0001_given_permutation_given_int/permutation2.param rename to tests/custom/permutations/04_image/int/0001_given_permutation_given_int/permutation2.param diff --git a/tests/custom/permutations/04_image/int/0001_given_permutation_given_int/run.sh b/tests/custom/permutations/04_image/int/0001_given_permutation_given_int/run.sh new file mode 100755 index 0000000000..9dc67e67f5 --- /dev/null +++ b/tests/custom/permutations/04_image/int/0001_given_permutation_given_int/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence *.param +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/04_image/0001_given_permutation_given_int/stdout.expected b/tests/custom/permutations/04_image/int/0001_given_permutation_given_int/stdout.expected similarity index 100% rename from tests/custom/permutations/04_image/0001_given_permutation_given_int/stdout.expected rename to tests/custom/permutations/04_image/int/0001_given_permutation_given_int/stdout.expected diff --git a/tests/custom/permutations/04_image/0002_given_permutation_letting_int/permutation.essence b/tests/custom/permutations/04_image/int/0002_given_permutation_letting_int/permutation.essence similarity index 100% rename from tests/custom/permutations/04_image/0002_given_permutation_letting_int/permutation.essence rename to tests/custom/permutations/04_image/int/0002_given_permutation_letting_int/permutation.essence diff --git a/tests/custom/permutations/04_image/0002_given_permutation_letting_int/permutation.param b/tests/custom/permutations/04_image/int/0002_given_permutation_letting_int/permutation.param similarity index 100% rename from tests/custom/permutations/04_image/0002_given_permutation_letting_int/permutation.param rename to tests/custom/permutations/04_image/int/0002_given_permutation_letting_int/permutation.param diff --git a/tests/custom/permutations/04_image/int/0002_given_permutation_letting_int/run.sh b/tests/custom/permutations/04_image/int/0002_given_permutation_letting_int/run.sh new file mode 100755 index 0000000000..9dc67e67f5 --- /dev/null +++ b/tests/custom/permutations/04_image/int/0002_given_permutation_letting_int/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence *.param +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/04_image/0002_given_permutation_letting_int/stdout.expected b/tests/custom/permutations/04_image/int/0002_given_permutation_letting_int/stdout.expected similarity index 100% rename from tests/custom/permutations/04_image/0002_given_permutation_letting_int/stdout.expected rename to tests/custom/permutations/04_image/int/0002_given_permutation_letting_int/stdout.expected diff --git a/tests/custom/permutations/04_image/0003_given_permutation_letting_int/permutation.essence b/tests/custom/permutations/04_image/int/0003_given_permutation_letting_int/permutation.essence similarity index 100% rename from tests/custom/permutations/04_image/0003_given_permutation_letting_int/permutation.essence rename to tests/custom/permutations/04_image/int/0003_given_permutation_letting_int/permutation.essence diff --git a/tests/custom/permutations/04_image/0003_given_permutation_letting_int/permutation.param b/tests/custom/permutations/04_image/int/0003_given_permutation_letting_int/permutation.param similarity index 100% rename from tests/custom/permutations/04_image/0003_given_permutation_letting_int/permutation.param rename to tests/custom/permutations/04_image/int/0003_given_permutation_letting_int/permutation.param diff --git a/tests/custom/permutations/04_image/int/0003_given_permutation_letting_int/run.sh b/tests/custom/permutations/04_image/int/0003_given_permutation_letting_int/run.sh new file mode 100755 index 0000000000..9dc67e67f5 --- /dev/null +++ b/tests/custom/permutations/04_image/int/0003_given_permutation_letting_int/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence *.param +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/04_image/0003_given_permutation_letting_int/stdout.expected b/tests/custom/permutations/04_image/int/0003_given_permutation_letting_int/stdout.expected similarity index 100% rename from tests/custom/permutations/04_image/0003_given_permutation_letting_int/stdout.expected rename to tests/custom/permutations/04_image/int/0003_given_permutation_letting_int/stdout.expected diff --git a/tests/custom/permutations/04_image/0004_given_permutation_find_int/permutation.essence b/tests/custom/permutations/04_image/int/0004_given_permutation_find_int/permutation.essence similarity index 100% rename from tests/custom/permutations/04_image/0004_given_permutation_find_int/permutation.essence rename to tests/custom/permutations/04_image/int/0004_given_permutation_find_int/permutation.essence diff --git a/tests/custom/permutations/04_image/0004_given_permutation_find_int/permutation.param b/tests/custom/permutations/04_image/int/0004_given_permutation_find_int/permutation.param similarity index 100% rename from tests/custom/permutations/04_image/0004_given_permutation_find_int/permutation.param rename to tests/custom/permutations/04_image/int/0004_given_permutation_find_int/permutation.param diff --git a/tests/custom/permutations/04_image/0004_given_permutation_find_int/permutation2.essence b/tests/custom/permutations/04_image/int/0004_given_permutation_find_int/permutation2.essence similarity index 100% rename from tests/custom/permutations/04_image/0004_given_permutation_find_int/permutation2.essence rename to tests/custom/permutations/04_image/int/0004_given_permutation_find_int/permutation2.essence diff --git a/tests/custom/permutations/04_image/int/0004_given_permutation_find_int/run.sh b/tests/custom/permutations/04_image/int/0004_given_permutation_find_int/run.sh new file mode 100755 index 0000000000..9dc67e67f5 --- /dev/null +++ b/tests/custom/permutations/04_image/int/0004_given_permutation_find_int/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence *.param +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/04_image/0004_given_permutation_find_int/stdout.expected b/tests/custom/permutations/04_image/int/0004_given_permutation_find_int/stdout.expected similarity index 100% rename from tests/custom/permutations/04_image/0004_given_permutation_find_int/stdout.expected rename to tests/custom/permutations/04_image/int/0004_given_permutation_find_int/stdout.expected diff --git a/tests/custom/permutations/04_image/0005_find_permutation_given_ints/permutation.essence b/tests/custom/permutations/04_image/int/0005_find_permutation_given_ints/permutation.essence similarity index 100% rename from tests/custom/permutations/04_image/0005_find_permutation_given_ints/permutation.essence rename to tests/custom/permutations/04_image/int/0005_find_permutation_given_ints/permutation.essence diff --git a/tests/custom/permutations/04_image/0005_find_permutation_given_ints/permutation.param b/tests/custom/permutations/04_image/int/0005_find_permutation_given_ints/permutation.param similarity index 100% rename from tests/custom/permutations/04_image/0005_find_permutation_given_ints/permutation.param rename to tests/custom/permutations/04_image/int/0005_find_permutation_given_ints/permutation.param diff --git a/tests/custom/permutations/04_image/0005_find_permutation_given_ints/permutation2.param b/tests/custom/permutations/04_image/int/0005_find_permutation_given_ints/permutation2.param similarity index 100% rename from tests/custom/permutations/04_image/0005_find_permutation_given_ints/permutation2.param rename to tests/custom/permutations/04_image/int/0005_find_permutation_given_ints/permutation2.param diff --git a/tests/custom/permutations/04_image/int/0005_find_permutation_given_ints/run.sh b/tests/custom/permutations/04_image/int/0005_find_permutation_given_ints/run.sh new file mode 100755 index 0000000000..9dc67e67f5 --- /dev/null +++ b/tests/custom/permutations/04_image/int/0005_find_permutation_given_ints/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence *.param +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/04_image/0005_find_permutation_given_ints/stdout.expected b/tests/custom/permutations/04_image/int/0005_find_permutation_given_ints/stdout.expected similarity index 100% rename from tests/custom/permutations/04_image/0005_find_permutation_given_ints/stdout.expected rename to tests/custom/permutations/04_image/int/0005_find_permutation_given_ints/stdout.expected diff --git a/tests/custom/permutations/04_image/0006_letting_permutation_given_int/permutation.essence b/tests/custom/permutations/04_image/int/0006_letting_permutation_given_int/permutation.essence similarity index 100% rename from tests/custom/permutations/04_image/0006_letting_permutation_given_int/permutation.essence rename to tests/custom/permutations/04_image/int/0006_letting_permutation_given_int/permutation.essence diff --git a/tests/custom/permutations/04_image/0006_letting_permutation_given_int/permutation.param b/tests/custom/permutations/04_image/int/0006_letting_permutation_given_int/permutation.param similarity index 100% rename from tests/custom/permutations/04_image/0006_letting_permutation_given_int/permutation.param rename to tests/custom/permutations/04_image/int/0006_letting_permutation_given_int/permutation.param diff --git a/tests/custom/permutations/04_image/0006_letting_permutation_given_int/permutation2.param b/tests/custom/permutations/04_image/int/0006_letting_permutation_given_int/permutation2.param similarity index 100% rename from tests/custom/permutations/04_image/0006_letting_permutation_given_int/permutation2.param rename to tests/custom/permutations/04_image/int/0006_letting_permutation_given_int/permutation2.param diff --git a/tests/custom/permutations/04_image/int/0006_letting_permutation_given_int/run.sh b/tests/custom/permutations/04_image/int/0006_letting_permutation_given_int/run.sh new file mode 100755 index 0000000000..9dc67e67f5 --- /dev/null +++ b/tests/custom/permutations/04_image/int/0006_letting_permutation_given_int/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence *.param +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/04_image/0006_letting_permutation_given_int/stdout.expected b/tests/custom/permutations/04_image/int/0006_letting_permutation_given_int/stdout.expected similarity index 100% rename from tests/custom/permutations/04_image/0006_letting_permutation_given_int/stdout.expected rename to tests/custom/permutations/04_image/int/0006_letting_permutation_given_int/stdout.expected diff --git a/tests/custom/permutations/04_image/int/0007_find_permutation_find_ints/permutation.essence b/tests/custom/permutations/04_image/int/0007_find_permutation_find_ints/permutation.essence new file mode 100644 index 0000000000..08f32ca98a --- /dev/null +++ b/tests/custom/permutations/04_image/int/0007_find_permutation_find_ints/permutation.essence @@ -0,0 +1,14 @@ +letting n be domain int(1..5) + +find i : n + +find p : permutation of n + +find j : n + +such that + j = image(p, i) /\ |p| = 3 + + + + diff --git a/tests/custom/permutations/04_image/int/0007_find_permutation_find_ints/run.sh b/tests/custom/permutations/04_image/int/0007_find_permutation_find_ints/run.sh new file mode 100755 index 0000000000..b4899d6266 --- /dev/null +++ b/tests/custom/permutations/04_image/int/0007_find_permutation_find_ints/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/04_image/int/0007_find_permutation_find_ints/stdout.expected b/tests/custom/permutations/04_image/int/0007_find_permutation_find_ints/stdout.expected new file mode 100644 index 0000000000..236f65e8da --- /dev/null +++ b/tests/custom/permutations/04_image/int/0007_find_permutation_find_ints/stdout.expected @@ -0,0 +1,10 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Copying solution to: permutation.solution +language Essence 1.3 + +letting i be 1 +letting j be 1 +letting p be permutation((3, 4, 5)) diff --git a/tests/custom/permutations/04_image/unnamed/0007_find_permutation_find_unnameds/permutation.essence b/tests/custom/permutations/04_image/unnamed/0007_find_permutation_find_unnameds/permutation.essence new file mode 100644 index 0000000000..95bff24946 --- /dev/null +++ b/tests/custom/permutations/04_image/unnamed/0007_find_permutation_find_unnameds/permutation.essence @@ -0,0 +1,14 @@ +letting n be new type of size 7 + +find i : n + +find p : permutation of n + +find j : n + +such that + j = image(p, i) /\ |p| = 3 + + + + diff --git a/tests/custom/permutations/04_image/unnamed/0007_find_permutation_find_unnameds/run.sh b/tests/custom/permutations/04_image/unnamed/0007_find_permutation_find_unnameds/run.sh new file mode 100755 index 0000000000..b4899d6266 --- /dev/null +++ b/tests/custom/permutations/04_image/unnamed/0007_find_permutation_find_unnameds/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/04_image/unnamed/0007_find_permutation_find_unnameds/stdout.expected b/tests/custom/permutations/04_image/unnamed/0007_find_permutation_find_unnameds/stdout.expected new file mode 100644 index 0000000000..3f0b9a4848 --- /dev/null +++ b/tests/custom/permutations/04_image/unnamed/0007_find_permutation_find_unnameds/stdout.expected @@ -0,0 +1,11 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Copying solution to: permutation.solution +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_1 +letting j be n_1 +letting p be permutation((n_5, n_6, n_7)) From 4dc8787dfae338979c2670b32103667e016d9f87 Mon Sep 17 00:00:00 2001 From: Fraser Dunlop Date: Mon, 10 Dec 2018 13:09:12 +0000 Subject: [PATCH 048/229] More tests --- src/Conjure/Language/Expression/Op/Product.hs | 12 +- src/Conjure/Language/Expression/Op/Succ.hs | 1 - .../deprecated_permutations_basic/.DS_Store | Bin 6148 -> 0 bytes .../permutation.essence | 9 - .../permutation.essence | 7 - .../permutation.param | 1 - .../permutation.essence | 7 - .../permutation.param | 1 - .../stderr.expected | 10 - .../stdout.expected | 4 - .../permutation.essence | 7 - .../permutation.param | 1 - .../permutation.essence | 11 - .../permutation.param | 1 - .../permutation.essence | 11 - .../permutation.param | 1 - .../stdout.expected | 8 - .../permutation.essence | 11 - .../permutation.param | 1 - .../stdout.expected | 8 - .../permutation.essence | 14 - .../permutation.param | 2 - .../stdout.expected | 8 - .../permutation.essence | 14 - .../permutation.param | 3 - .../run.sh | 3 - .../stdout.expected | 8 - .../permutation.essence | 14 - .../permutation.param | 3 - .../run.sh | 3 - .../stdout.expected | 8 - .../permutation.essence | 8 - .../stdout.expected | 9 - .../permutation.essence | 8 - .../run.sh | 3 - .../stdout.expected | 9 - .../permutation.essence | 10 - .../run.sh | 3 - .../stdout.expected | 8 - .../permutation.essence | 7 - .../run.sh | 3 - .../permutation.essence | 10 - .../run.sh | 3 - .../permutation.essence | 9 - .../run.sh | 3 - .../stdout.expected | 12 - .../permutation.essence | 8 - .../run.sh | 3 - .../stdout.expected | 34 - .../permutation.essence | 6 - .../run.sh | 3 - .../stdout.expected | 28 - .../permutation.essence | 7 - .../run.sh | 3 - .../stdout.expected | 268 - .../permutation.essence | 6 - .../run.sh | 3 - .../stdout.expected | 1004 - .../permutation.essence | 13 - .../permutation.param | 2 - .../run.sh | 3 - .../stdout.expected | 8 - .../permutation.essence | 13 - .../permutation.param | 2 - .../run.sh | 3 - .../stdout.expected | 104 - .../permutation.essence | 12 - .../permutation.param | 1 - .../run.sh | 3 - .../stdout.expected | 24 - .../permutation.essence | 12 - .../permutation.param | 1 - .../run.sh | 3 - .../stdout.expected | 9 - .../permutation.essence | 16 - .../permutation.param | 2 - .../run.sh | 3 - .../stdout.expected | 124 - .../permutation.essence | 16 - .../permutation.param | 1 - .../run.sh | 3 - .../stdout.expected | 104 - .../permutation.essence | 12 - .../run.sh | 3 - .../stdout.expected | 29 - .../permutation.essence | 13 - .../run.sh | 3 - .../stdout.expected | 14 - .../log | 24365 ---------------- .../log-lite | 7863 ----- .../permutation.essence | 13 - .../run.sh | 3 - .../permutation.essence | 8 - .../permutation.param | 1 - .../run.sh | 3 - .../permutation.essence | 5 - .../permutation.param | 1 - .../run.sh | 3 - .../permutation.essence | 9 - .../permutation.param | 1 - .../run.sh | 3 - .../permutation.essence | 11 - .../permutation.param | 1 - .../run.sh | 3 - .../stdout.expected | 284 - .../permutation.essence | 6 - .../permutation.param | 1 - .../0034_image_of_empty_permutation/run.sh | 3 - .../permutation.essence | 10 - .../permutation.param | 1 - .../stdout.expected | 28 - .../permutation.essence | 19 - .../stdout.expected | 114 - .../permutation.essence | 12 - .../stdout.expected | 64 - .../permutation.essence | 11 - .../run.sh | 3 - .../stdout.expected | 64 - .../permutation.essence | 8 - .../run.sh | 3 - .../permutation.essence | 6 - .../run.sh | 3 - .../stdout.expected | 14 - .../permutation.essence | 10 - .../run.sh | 3 - .../permutation.essence | 8 - .../run.sh | 3 - .../permutation.essence | 6 - .../run.sh | 3 - .../deprecated_permutations_basic/runthese.sh | 1 - .../enum/0004/permutation.essence | 10 + .../02_cardinality/enum/0004}/run.sh | 0 .../02_cardinality/enum/0004}/stdout.expected | 3 +- .../0001_given_permutations_in_param/run.sh | 3 - .../0002_given_permutations_in_param/run.sh | 3 - .../0003_given_equal_letting/run.sh | 3 - .../permutation.param | 1 - .../0004_letting_equal_given/run.sh | 3 - .../permutation.essence | 12 + .../permutation.param | 2 + .../0001_given_permutations_in_param}/run.sh | 0 .../stdout.expected | 0 .../permutation.essence | 12 + .../permutation.param | 2 + .../0002_given_permutations_in_param}/run.sh | 0 .../stdout.expected | 0 .../permutation.essence | 12 + .../permutation.param | 1 + .../enum/0003_given_equal_letting}/run.sh | 0 .../0003_given_equal_letting/stdout.expected | 0 .../permutation.essence | 12 + .../permutation.param | 1 + .../enum/0004_letting_equal_given}/run.sh | 0 .../0004_letting_equal_given/stdout.expected | 0 .../0005_find_eq_find/permutation.essence | 10 + .../enum/0005_find_eq_find}/run.sh | 0 .../enum/0005_find_eq_find/stdout.expected | 54 + .../permutation.essence | 0 .../permutation.param | 0 .../0001_given_permutations_in_param}/run.sh | 0 .../stdout.expected | 1 + .../permutation.essence | 0 .../permutation.param | 0 .../0002_given_permutations_in_param}/run.sh | 0 .../stdout.expected | 2 +- .../permutation.essence | 0 .../permutation.param | 0 .../int/0003_given_equal_letting}/run.sh | 0 .../0003_given_equal_letting}/stdout.expected | 1 + .../permutation.essence | 0 .../permutation.param | 0 .../int/0004_letting_equal_given}/run.sh | 0 .../0004_letting_equal_given}/stdout.expected | 1 + .../int/0005_find_eq_find/permutation.essence | 8 + .../05_equality/int/0005_find_eq_find}/run.sh | 0 .../int/0005_find_eq_find}/stdout.expected | 30 +- .../0005_find_eq_find/permutation.essence | 10 + .../unnamed/0005_find_eq_find}/run.sh | 0 .../unnamed/0005_find_eq_find/stdout.expected | 64 + 179 files changed, 242 insertions(+), 35226 deletions(-) delete mode 100644 tests/custom/deprecated_permutations_basic/.DS_Store delete mode 100644 tests/custom/deprecated_permutations_basic/0001_given_permutation_in_param/permutation.essence delete mode 100644 tests/custom/deprecated_permutations_basic/0002_given_permutation_in_param/permutation.essence delete mode 100644 tests/custom/deprecated_permutations_basic/0002_given_permutation_in_param/permutation.param delete mode 100644 tests/custom/deprecated_permutations_basic/0003_given_permutation_in_param_2_cycle/permutation.essence delete mode 100644 tests/custom/deprecated_permutations_basic/0003_given_permutation_in_param_2_cycle/permutation.param delete mode 100644 tests/custom/deprecated_permutations_basic/0003_given_permutation_in_param_2_cycle/stderr.expected delete mode 100644 tests/custom/deprecated_permutations_basic/0003_given_permutation_in_param_2_cycle/stdout.expected delete mode 100644 tests/custom/deprecated_permutations_basic/0004_given_permutation_in_param_2_cycle/permutation.essence delete mode 100644 tests/custom/deprecated_permutations_basic/0004_given_permutation_in_param_2_cycle/permutation.param delete mode 100644 tests/custom/deprecated_permutations_basic/0005_find_int_image_under_given_permutation/permutation.essence delete mode 100644 tests/custom/deprecated_permutations_basic/0005_find_int_image_under_given_permutation/permutation.param delete mode 100644 tests/custom/deprecated_permutations_basic/0006_find_int_image_under_given_permutation/permutation.essence delete mode 100644 tests/custom/deprecated_permutations_basic/0006_find_int_image_under_given_permutation/permutation.param delete mode 100644 tests/custom/deprecated_permutations_basic/0006_find_int_image_under_given_permutation/stdout.expected delete mode 100644 tests/custom/deprecated_permutations_basic/0007_find_int_image_under_given_permutation/permutation.essence delete mode 100644 tests/custom/deprecated_permutations_basic/0007_find_int_image_under_given_permutation/permutation.param delete mode 100644 tests/custom/deprecated_permutations_basic/0007_find_int_image_under_given_permutation/stdout.expected delete mode 100644 tests/custom/deprecated_permutations_basic/0008_find_int_image_under_two_composed_given_permutations/permutation.essence delete mode 100644 tests/custom/deprecated_permutations_basic/0008_find_int_image_under_two_composed_given_permutations/permutation.param delete mode 100644 tests/custom/deprecated_permutations_basic/0008_find_int_image_under_two_composed_given_permutations/stdout.expected delete mode 100644 tests/custom/deprecated_permutations_basic/0009_find_int_image_under_three_composed_given_permutations/permutation.essence delete mode 100644 tests/custom/deprecated_permutations_basic/0009_find_int_image_under_three_composed_given_permutations/permutation.param delete mode 100755 tests/custom/deprecated_permutations_basic/0009_find_int_image_under_three_composed_given_permutations/run.sh delete mode 100644 tests/custom/deprecated_permutations_basic/0009_find_int_image_under_three_composed_given_permutations/stdout.expected delete mode 100644 tests/custom/deprecated_permutations_basic/0010_find_int_image_under_three_composed_given_permutations/permutation.essence delete mode 100644 tests/custom/deprecated_permutations_basic/0010_find_int_image_under_three_composed_given_permutations/permutation.param delete mode 100755 tests/custom/deprecated_permutations_basic/0010_find_int_image_under_three_composed_given_permutations/run.sh delete mode 100644 tests/custom/deprecated_permutations_basic/0010_find_int_image_under_three_composed_given_permutations/stdout.expected delete mode 100644 tests/custom/deprecated_permutations_basic/0011_find_int_and_permutation_such_that_int_image_equals_const/permutation.essence delete mode 100644 tests/custom/deprecated_permutations_basic/0011_find_int_and_permutation_such_that_int_image_equals_const/stdout.expected delete mode 100644 tests/custom/deprecated_permutations_basic/0012_find_int_and_permutation_such_that_int_image_equals_const/permutation.essence delete mode 100755 tests/custom/deprecated_permutations_basic/0012_find_int_and_permutation_such_that_int_image_equals_const/run.sh delete mode 100644 tests/custom/deprecated_permutations_basic/0012_find_int_and_permutation_such_that_int_image_equals_const/stdout.expected delete mode 100644 tests/custom/deprecated_permutations_basic/0013_find_permutation_such_that_image_of_matrix1_equals_matrix2/permutation.essence delete mode 100755 tests/custom/deprecated_permutations_basic/0013_find_permutation_such_that_image_of_matrix1_equals_matrix2/run.sh delete mode 100644 tests/custom/deprecated_permutations_basic/0013_find_permutation_such_that_image_of_matrix1_equals_matrix2/stdout.expected delete mode 100644 tests/custom/deprecated_permutations_basic/0014_find_matrix_such_that_swapping_any_index_pairs_becomes_lex_greater/permutation.essence delete mode 100755 tests/custom/deprecated_permutations_basic/0014_find_matrix_such_that_swapping_any_index_pairs_becomes_lex_greater/run.sh delete mode 100644 tests/custom/deprecated_permutations_basic/0015_find_set_of_permuted_elements_of_matrix/permutation.essence delete mode 100755 tests/custom/deprecated_permutations_basic/0015_find_set_of_permuted_elements_of_matrix/run.sh delete mode 100644 tests/custom/deprecated_permutations_basic/0016_find_permutation_such_that_image_is_identity_for_given_matrix/permutation.essence delete mode 100755 tests/custom/deprecated_permutations_basic/0016_find_permutation_such_that_image_is_identity_for_given_matrix/run.sh delete mode 100644 tests/custom/deprecated_permutations_basic/0016_find_permutation_such_that_image_is_identity_for_given_matrix/stdout.expected delete mode 100644 tests/custom/deprecated_permutations_basic/0017_find_two_permutations_with_overlapping_domains_and_same_image_over_domain_union/permutation.essence delete mode 100755 tests/custom/deprecated_permutations_basic/0017_find_two_permutations_with_overlapping_domains_and_same_image_over_domain_union/run.sh delete mode 100644 tests/custom/deprecated_permutations_basic/0017_find_two_permutations_with_overlapping_domains_and_same_image_over_domain_union/stdout.expected delete mode 100644 tests/custom/deprecated_permutations_basic/0018_find_matrix_lex_less_than_under_any_swap/permutation.essence delete mode 100755 tests/custom/deprecated_permutations_basic/0018_find_matrix_lex_less_than_under_any_swap/run.sh delete mode 100644 tests/custom/deprecated_permutations_basic/0018_find_matrix_lex_less_than_under_any_swap/stdout.expected delete mode 100644 tests/custom/deprecated_permutations_basic/0019_find_set_of_permutation_tuples_using_comprehension/permutation.essence delete mode 100755 tests/custom/deprecated_permutations_basic/0019_find_set_of_permutation_tuples_using_comprehension/run.sh delete mode 100644 tests/custom/deprecated_permutations_basic/0019_find_set_of_permutation_tuples_using_comprehension/stdout.expected delete mode 100644 tests/custom/deprecated_permutations_basic/0020_find_permutation_inverse_using_comprehension/permutation.essence delete mode 100755 tests/custom/deprecated_permutations_basic/0020_find_permutation_inverse_using_comprehension/run.sh delete mode 100644 tests/custom/deprecated_permutations_basic/0020_find_permutation_inverse_using_comprehension/stdout.expected delete mode 100644 tests/custom/deprecated_permutations_basic/0021_image_of_int_under_composition_of_two_given_permutations/permutation.essence delete mode 100644 tests/custom/deprecated_permutations_basic/0021_image_of_int_under_composition_of_two_given_permutations/permutation.param delete mode 100755 tests/custom/deprecated_permutations_basic/0021_image_of_int_under_composition_of_two_given_permutations/run.sh delete mode 100644 tests/custom/deprecated_permutations_basic/0021_image_of_int_under_composition_of_two_given_permutations/stdout.expected delete mode 100644 tests/custom/deprecated_permutations_basic/0022_find_matrices_of_enum_x_y_such_that_y_lexless_than_x_under_any_index_swap/permutation.essence delete mode 100644 tests/custom/deprecated_permutations_basic/0022_find_matrices_of_enum_x_y_such_that_y_lexless_than_x_under_any_index_swap/permutation.param delete mode 100755 tests/custom/deprecated_permutations_basic/0022_find_matrices_of_enum_x_y_such_that_y_lexless_than_x_under_any_index_swap/run.sh delete mode 100644 tests/custom/deprecated_permutations_basic/0022_find_matrices_of_enum_x_y_such_that_y_lexless_than_x_under_any_index_swap/stdout.expected delete mode 100644 tests/custom/deprecated_permutations_basic/0023_find_triples_x_y_such_that_y_lex_less_x_under_any_swap/permutation.essence delete mode 100644 tests/custom/deprecated_permutations_basic/0023_find_triples_x_y_such_that_y_lex_less_x_under_any_swap/permutation.param delete mode 100755 tests/custom/deprecated_permutations_basic/0023_find_triples_x_y_such_that_y_lex_less_x_under_any_swap/run.sh delete mode 100644 tests/custom/deprecated_permutations_basic/0023_find_triples_x_y_such_that_y_lex_less_x_under_any_swap/stdout.expected delete mode 100644 tests/custom/deprecated_permutations_basic/0024_find_sets_x_y_such_that_y_lexless_x_under_any_swap/permutation.essence delete mode 100644 tests/custom/deprecated_permutations_basic/0024_find_sets_x_y_such_that_y_lexless_x_under_any_swap/permutation.param delete mode 100755 tests/custom/deprecated_permutations_basic/0024_find_sets_x_y_such_that_y_lexless_x_under_any_swap/run.sh delete mode 100644 tests/custom/deprecated_permutations_basic/0024_find_sets_x_y_such_that_y_lexless_x_under_any_swap/stdout.expected delete mode 100644 tests/custom/deprecated_permutations_basic/0025_find_permutation_and_matrices_x_y_such_that_image_x_eq_y/permutation.essence delete mode 100644 tests/custom/deprecated_permutations_basic/0025_find_permutation_and_matrices_x_y_such_that_image_x_eq_y/permutation.param delete mode 100755 tests/custom/deprecated_permutations_basic/0025_find_permutation_and_matrices_x_y_such_that_image_x_eq_y/run.sh delete mode 100644 tests/custom/deprecated_permutations_basic/0025_find_permutation_and_matrices_x_y_such_that_image_x_eq_y/stdout.expected delete mode 100644 tests/custom/deprecated_permutations_basic/0026_find_matrices_of_enums_x_y_such_that_y_image_x_under_p/permutation.essence delete mode 100644 tests/custom/deprecated_permutations_basic/0026_find_matrices_of_enums_x_y_such_that_y_image_x_under_p/permutation.param delete mode 100755 tests/custom/deprecated_permutations_basic/0026_find_matrices_of_enums_x_y_such_that_y_image_x_under_p/run.sh delete mode 100644 tests/custom/deprecated_permutations_basic/0026_find_matrices_of_enums_x_y_such_that_y_image_x_under_p/stdout.expected delete mode 100644 tests/custom/deprecated_permutations_basic/0027_find_sets_of_enum_x_y_such_that_y_image_x_under_p/permutation.essence delete mode 100755 tests/custom/deprecated_permutations_basic/0027_find_sets_of_enum_x_y_such_that_y_image_x_under_p/run.sh delete mode 100644 tests/custom/deprecated_permutations_basic/0027_find_sets_of_enum_x_y_such_that_y_image_x_under_p/stdout.expected delete mode 100644 tests/custom/deprecated_permutations_basic/0028_find_sets_of_enum_x_y_such_that_y_image_x_under_p/permutation.essence delete mode 100755 tests/custom/deprecated_permutations_basic/0028_find_sets_of_enum_x_y_such_that_y_image_x_under_p/run.sh delete mode 100644 tests/custom/deprecated_permutations_basic/0028_find_sets_of_enum_x_y_such_that_y_image_x_under_p/stdout.expected delete mode 100644 tests/custom/deprecated_permutations_basic/0029_find_relations_x_y_such_that_y_image_x_under_p/log delete mode 100644 tests/custom/deprecated_permutations_basic/0029_find_relations_x_y_such_that_y_image_x_under_p/log-lite delete mode 100644 tests/custom/deprecated_permutations_basic/0029_find_relations_x_y_such_that_y_image_x_under_p/permutation.essence delete mode 100755 tests/custom/deprecated_permutations_basic/0029_find_relations_x_y_such_that_y_image_x_under_p/run.sh delete mode 100644 tests/custom/deprecated_permutations_basic/0030_find_permutation_equal_given_permutation/permutation.essence delete mode 100644 tests/custom/deprecated_permutations_basic/0030_find_permutation_equal_given_permutation/permutation.param delete mode 100755 tests/custom/deprecated_permutations_basic/0030_find_permutation_equal_given_permutation/run.sh delete mode 100644 tests/custom/deprecated_permutations_basic/0031_find_matrix_lexless_indices_swapped_in_comprehension/permutation.essence delete mode 100644 tests/custom/deprecated_permutations_basic/0031_find_matrix_lexless_indices_swapped_in_comprehension/permutation.param delete mode 100755 tests/custom/deprecated_permutations_basic/0031_find_matrix_lexless_indices_swapped_in_comprehension/run.sh delete mode 100644 tests/custom/deprecated_permutations_basic/0032_find_sets_of_ints_such_that_tuple_of_sets_lexless_any_int_swapped_tuple/permutation.essence delete mode 100644 tests/custom/deprecated_permutations_basic/0032_find_sets_of_ints_such_that_tuple_of_sets_lexless_any_int_swapped_tuple/permutation.param delete mode 100755 tests/custom/deprecated_permutations_basic/0032_find_sets_of_ints_such_that_tuple_of_sets_lexless_any_int_swapped_tuple/run.sh delete mode 100644 tests/custom/deprecated_permutations_basic/0033_find_matrixes_of_enum_such_that_tuple_of_matrices_lexless_any_int_swapped_tuple/permutation.essence delete mode 100644 tests/custom/deprecated_permutations_basic/0033_find_matrixes_of_enum_such_that_tuple_of_matrices_lexless_any_int_swapped_tuple/permutation.param delete mode 100755 tests/custom/deprecated_permutations_basic/0033_find_matrixes_of_enum_such_that_tuple_of_matrices_lexless_any_int_swapped_tuple/run.sh delete mode 100644 tests/custom/deprecated_permutations_basic/0033_find_matrixes_of_enum_such_that_tuple_of_matrices_lexless_any_int_swapped_tuple/stdout.expected delete mode 100644 tests/custom/deprecated_permutations_basic/0034_image_of_empty_permutation/permutation.essence delete mode 100644 tests/custom/deprecated_permutations_basic/0034_image_of_empty_permutation/permutation.param delete mode 100755 tests/custom/deprecated_permutations_basic/0034_image_of_empty_permutation/run.sh delete mode 100644 tests/custom/deprecated_permutations_basic/0035_permutation_of_enum_is_identity_for_integers/permutation.essence delete mode 100644 tests/custom/deprecated_permutations_basic/0035_permutation_of_enum_is_identity_for_integers/permutation.param delete mode 100644 tests/custom/deprecated_permutations_basic/0035_permutation_of_enum_is_identity_for_integers/stdout.expected delete mode 100644 tests/custom/deprecated_permutations_basic/0036_big_test_of_enums_in_matrices/permutation.essence delete mode 100644 tests/custom/deprecated_permutations_basic/0036_big_test_of_enums_in_matrices/stdout.expected delete mode 100644 tests/custom/deprecated_permutations_basic/0037_matrices_of_enums_indexed_by_enums/permutation.essence delete mode 100644 tests/custom/deprecated_permutations_basic/0037_matrices_of_enums_indexed_by_enums/stdout.expected delete mode 100644 tests/custom/deprecated_permutations_basic/0038_matricies_of_tuples_of_enums_indexed_by_enums/permutation.essence delete mode 100755 tests/custom/deprecated_permutations_basic/0038_matricies_of_tuples_of_enums_indexed_by_enums/run.sh delete mode 100644 tests/custom/deprecated_permutations_basic/0038_matricies_of_tuples_of_enums_indexed_by_enums/stdout.expected delete mode 100644 tests/custom/deprecated_permutations_basic/0039_toSet_on_given_permutation_of_enum/permutation.essence delete mode 100755 tests/custom/deprecated_permutations_basic/0039_toSet_on_given_permutation_of_enum/run.sh delete mode 100644 tests/custom/deprecated_permutations_basic/0040_toSet_on_given_permutation_of_int/permutation.essence delete mode 100755 tests/custom/deprecated_permutations_basic/0040_toSet_on_given_permutation_of_int/run.sh delete mode 100644 tests/custom/deprecated_permutations_basic/0040_toSet_on_given_permutation_of_int/stdout.expected delete mode 100644 tests/custom/deprecated_permutations_basic/0041_toSet_on_found_permutation_of_enum/permutation.essence delete mode 100755 tests/custom/deprecated_permutations_basic/0041_toSet_on_found_permutation_of_enum/run.sh delete mode 100644 tests/custom/deprecated_permutations_basic/0042_toSet_on_found_permutation_of_int/permutation.essence delete mode 100755 tests/custom/deprecated_permutations_basic/0042_toSet_on_found_permutation_of_int/run.sh delete mode 100644 tests/custom/deprecated_permutations_basic/0043_inverse_on_given_permutation_of_int/permutation.essence delete mode 100755 tests/custom/deprecated_permutations_basic/0043_inverse_on_given_permutation_of_int/run.sh delete mode 100644 tests/custom/deprecated_permutations_basic/runthese.sh create mode 100644 tests/custom/permutations/02_cardinality/enum/0004/permutation.essence rename tests/custom/{deprecated_permutations_basic/0011_find_int_and_permutation_such_that_int_image_equals_const => permutations/02_cardinality/enum/0004}/run.sh (100%) rename tests/custom/{deprecated_permutations_basic/0015_find_set_of_permuted_elements_of_matrix => permutations/02_cardinality/enum/0004}/stdout.expected (77%) delete mode 100755 tests/custom/permutations/05_equality/0001_given_permutations_in_param/run.sh delete mode 100755 tests/custom/permutations/05_equality/0002_given_permutations_in_param/run.sh delete mode 100755 tests/custom/permutations/05_equality/0003_given_equal_letting/run.sh delete mode 100644 tests/custom/permutations/05_equality/0004_letting_equal_given/permutation.param delete mode 100755 tests/custom/permutations/05_equality/0004_letting_equal_given/run.sh create mode 100644 tests/custom/permutations/05_equality/enum/0001_given_permutations_in_param/permutation.essence create mode 100644 tests/custom/permutations/05_equality/enum/0001_given_permutations_in_param/permutation.param rename tests/custom/{deprecated_permutations_basic/0001_given_permutation_in_param => permutations/05_equality/enum/0001_given_permutations_in_param}/run.sh (100%) rename tests/custom/permutations/05_equality/{ => enum}/0001_given_permutations_in_param/stdout.expected (100%) create mode 100644 tests/custom/permutations/05_equality/enum/0002_given_permutations_in_param/permutation.essence create mode 100644 tests/custom/permutations/05_equality/enum/0002_given_permutations_in_param/permutation.param rename tests/custom/{deprecated_permutations_basic/0002_given_permutation_in_param => permutations/05_equality/enum/0002_given_permutations_in_param}/run.sh (100%) rename tests/custom/permutations/05_equality/{ => enum}/0002_given_permutations_in_param/stdout.expected (100%) create mode 100644 tests/custom/permutations/05_equality/enum/0003_given_equal_letting/permutation.essence create mode 100644 tests/custom/permutations/05_equality/enum/0003_given_equal_letting/permutation.param rename tests/custom/{deprecated_permutations_basic/0003_given_permutation_in_param_2_cycle => permutations/05_equality/enum/0003_given_equal_letting}/run.sh (100%) rename tests/custom/permutations/05_equality/{ => enum}/0003_given_equal_letting/stdout.expected (100%) create mode 100644 tests/custom/permutations/05_equality/enum/0004_letting_equal_given/permutation.essence create mode 100644 tests/custom/permutations/05_equality/enum/0004_letting_equal_given/permutation.param rename tests/custom/{deprecated_permutations_basic/0004_given_permutation_in_param_2_cycle => permutations/05_equality/enum/0004_letting_equal_given}/run.sh (100%) rename tests/custom/permutations/05_equality/{ => enum}/0004_letting_equal_given/stdout.expected (100%) create mode 100644 tests/custom/permutations/05_equality/enum/0005_find_eq_find/permutation.essence rename tests/custom/{deprecated_permutations_basic/0035_permutation_of_enum_is_identity_for_integers => permutations/05_equality/enum/0005_find_eq_find}/run.sh (100%) create mode 100644 tests/custom/permutations/05_equality/enum/0005_find_eq_find/stdout.expected rename tests/custom/permutations/05_equality/{ => int}/0001_given_permutations_in_param/permutation.essence (100%) rename tests/custom/permutations/05_equality/{ => int}/0001_given_permutations_in_param/permutation.param (100%) rename tests/custom/{deprecated_permutations_basic/0005_find_int_image_under_given_permutation => permutations/05_equality/int/0001_given_permutations_in_param}/run.sh (100%) rename tests/custom/{deprecated_permutations_basic/0002_given_permutation_in_param => permutations/05_equality/int/0001_given_permutations_in_param}/stdout.expected (92%) rename tests/custom/permutations/05_equality/{ => int}/0002_given_permutations_in_param/permutation.essence (100%) rename tests/custom/permutations/05_equality/{ => int}/0002_given_permutations_in_param/permutation.param (100%) rename tests/custom/{deprecated_permutations_basic/0006_find_int_image_under_given_permutation => permutations/05_equality/int/0002_given_permutations_in_param}/run.sh (100%) rename tests/custom/{deprecated_permutations_basic/0005_find_int_image_under_given_permutation => permutations/05_equality/int/0002_given_permutations_in_param}/stdout.expected (92%) rename tests/custom/permutations/05_equality/{ => int}/0003_given_equal_letting/permutation.essence (100%) rename tests/custom/{deprecated_permutations_basic/0001_given_permutation_in_param => permutations/05_equality/int/0003_given_equal_letting}/permutation.param (100%) rename tests/custom/{deprecated_permutations_basic/0007_find_int_image_under_given_permutation => permutations/05_equality/int/0003_given_equal_letting}/run.sh (100%) rename tests/custom/{deprecated_permutations_basic/0001_given_permutation_in_param => permutations/05_equality/int/0003_given_equal_letting}/stdout.expected (92%) rename tests/custom/permutations/05_equality/{ => int}/0004_letting_equal_given/permutation.essence (100%) rename tests/custom/permutations/05_equality/{0003_given_equal_letting => int/0004_letting_equal_given}/permutation.param (100%) rename tests/custom/{deprecated_permutations_basic/0008_find_int_image_under_two_composed_given_permutations => permutations/05_equality/int/0004_letting_equal_given}/run.sh (100%) rename tests/custom/{deprecated_permutations_basic/0004_given_permutation_in_param_2_cycle => permutations/05_equality/int/0004_letting_equal_given}/stdout.expected (92%) create mode 100644 tests/custom/permutations/05_equality/int/0005_find_eq_find/permutation.essence rename tests/custom/{deprecated_permutations_basic/0036_big_test_of_enums_in_matrices => permutations/05_equality/int/0005_find_eq_find}/run.sh (100%) rename tests/custom/{deprecated_permutations_basic/0014_find_matrix_such_that_swapping_any_index_pairs_becomes_lex_greater => permutations/05_equality/int/0005_find_eq_find}/stdout.expected (54%) create mode 100644 tests/custom/permutations/05_equality/unnamed/0005_find_eq_find/permutation.essence rename tests/custom/{deprecated_permutations_basic/0037_matrices_of_enums_indexed_by_enums => permutations/05_equality/unnamed/0005_find_eq_find}/run.sh (100%) create mode 100644 tests/custom/permutations/05_equality/unnamed/0005_find_eq_find/stdout.expected diff --git a/src/Conjure/Language/Expression/Op/Product.hs b/src/Conjure/Language/Expression/Op/Product.hs index 53219b4fa2..0392b5d703 100644 --- a/src/Conjure/Language/Expression/Op/Product.hs +++ b/src/Conjure/Language/Expression/Op/Product.hs @@ -47,13 +47,13 @@ instance EvaluateOp OpProduct where | Just xs <- listOut x , any isUndef xs = return $ mkUndef (TypeInt AnyTag) $ "Has undefined children:" <+> pretty p - evaluateOp (OpProduct x) = ConstantInt NoTag . product <$> intsOut "OpProduct" x - - evaluateOp p@(OpProduct x) - | Just xs <- listOut x - , any isUndef xs = return $ mkUndef (TypeInt NoTag) $ "Has undefined children:" <+> pretty p - evaluateOp (OpProduct x) = ConstantInt NoTag . product <$> intsOut "OpProduct" x + evaluateOp (OpProduct x) = ConstantInt AnyTag . product <$> intsOut "OpProduct" x +-- evaluateOp p@(OpProduct x) +-- | Just xs <- listOut x +-- , any isUndef xs = return $ mkUndef (TypeInt NoTag) $ "Has undefined children:" <+> pretty p +-- evaluateOp (OpProduct x) = ConstantInt NoTag . product <$> intsOut "OpProduct" x +-- instance (OpProduct x :< x) => SimplifyOp OpProduct x where simplifyOp (OpProduct x) diff --git a/src/Conjure/Language/Expression/Op/Succ.hs b/src/Conjure/Language/Expression/Op/Succ.hs index 354d9d85cf..b7324188eb 100644 --- a/src/Conjure/Language/Expression/Op/Succ.hs +++ b/src/Conjure/Language/Expression/Op/Succ.hs @@ -37,7 +37,6 @@ instance EvaluateOp OpSucc where evaluateOp (OpSucc (ConstantInt (TagEnum t) x)) = return (ConstantInt (TagEnum t) (succ x)) evaluateOp op = na $ "evaluateOp{OpSucc}" <+> pretty (show op) - evaluateOp op = na $ "evaluateOp{OpSucc}" <+> pretty (show op) instance SimplifyOp OpSucc x where simplifyOp _ = na "simplifyOp{OpSucc}" diff --git a/tests/custom/deprecated_permutations_basic/.DS_Store b/tests/custom/deprecated_permutations_basic/.DS_Store deleted file mode 100644 index 0f7ba840a9442d2bf7141c57606c1abd9cdea677..0000000000000000000000000000000000000000 GIT binary patch literal 0 HcmV?d00001 literal 6148 zcmeHKyH3MU3_XSpl~_75-cR5$u|-w+f_?xXT1usoqO?Jw@ zb7X`fUP|;*i4jA*obeKQRbc1n<&YRYB%UlWp@==5=NC(dRE}wrfn=c1z^S_v?f m <=lex [m[image(permutation((i,j)),k)] | k : int(1..9)] diff --git a/tests/custom/deprecated_permutations_basic/0014_find_matrix_such_that_swapping_any_index_pairs_becomes_lex_greater/run.sh b/tests/custom/deprecated_permutations_basic/0014_find_matrix_such_that_swapping_any_index_pairs_becomes_lex_greater/run.sh deleted file mode 100755 index bb7cfec8d9..0000000000 --- a/tests/custom/deprecated_permutations_basic/0014_find_matrix_such_that_swapping_any_index_pairs_becomes_lex_greater/run.sh +++ /dev/null @@ -1,3 +0,0 @@ -conjure solve *.essence --number-of-solutions=25 -cat conjure-output/*.solution -rm -rf conjure-output *.solution diff --git a/tests/custom/deprecated_permutations_basic/0015_find_set_of_permuted_elements_of_matrix/permutation.essence b/tests/custom/deprecated_permutations_basic/0015_find_set_of_permuted_elements_of_matrix/permutation.essence deleted file mode 100644 index 88f10307d8..0000000000 --- a/tests/custom/deprecated_permutations_basic/0015_find_set_of_permuted_elements_of_matrix/permutation.essence +++ /dev/null @@ -1,10 +0,0 @@ - -letting p be permutation((1,5,4),(7,12,20)) - -letting j be [20,3,4,7] - -find k : set of int(1..30) - -such that - forAll i in j . - image(p, i) in k diff --git a/tests/custom/deprecated_permutations_basic/0015_find_set_of_permuted_elements_of_matrix/run.sh b/tests/custom/deprecated_permutations_basic/0015_find_set_of_permuted_elements_of_matrix/run.sh deleted file mode 100755 index b4899d6266..0000000000 --- a/tests/custom/deprecated_permutations_basic/0015_find_set_of_permuted_elements_of_matrix/run.sh +++ /dev/null @@ -1,3 +0,0 @@ -conjure solve *.essence -cat conjure-output/*.solution -rm -rf conjure-output *.solution diff --git a/tests/custom/deprecated_permutations_basic/0016_find_permutation_such_that_image_is_identity_for_given_matrix/permutation.essence b/tests/custom/deprecated_permutations_basic/0016_find_permutation_such_that_image_is_identity_for_given_matrix/permutation.essence deleted file mode 100644 index 7dab320548..0000000000 --- a/tests/custom/deprecated_permutations_basic/0016_find_permutation_such_that_image_is_identity_for_given_matrix/permutation.essence +++ /dev/null @@ -1,9 +0,0 @@ - -find p : permutation of int(3..7) - -letting j be [20,3,4,7,2,15,12,5] - -such that - forAll i : int(1..4) . - image(p,j[i]) = j[i] - diff --git a/tests/custom/deprecated_permutations_basic/0016_find_permutation_such_that_image_is_identity_for_given_matrix/run.sh b/tests/custom/deprecated_permutations_basic/0016_find_permutation_such_that_image_is_identity_for_given_matrix/run.sh deleted file mode 100755 index de361d4354..0000000000 --- a/tests/custom/deprecated_permutations_basic/0016_find_permutation_such_that_image_is_identity_for_given_matrix/run.sh +++ /dev/null @@ -1,3 +0,0 @@ -conjure solve *.essence --number-of-solutions=40 -cat conjure-output/*.solution -rm -rf conjure-output *.solution diff --git a/tests/custom/deprecated_permutations_basic/0016_find_permutation_such_that_image_is_identity_for_given_matrix/stdout.expected b/tests/custom/deprecated_permutations_basic/0016_find_permutation_such_that_image_is_identity_for_given_matrix/stdout.expected deleted file mode 100644 index 19bfe22fc9..0000000000 --- a/tests/custom/deprecated_permutations_basic/0016_find_permutation_such_that_image_is_identity_for_given_matrix/stdout.expected +++ /dev/null @@ -1,12 +0,0 @@ -Generating models for permutation.essence -Generated models: model000001.eprime -Saved under: conjure-output -Savile Row: model000001.eprime -Copying solution to: permutation-000001.solution -Copying solution to: permutation-000002.solution -language Essence 1.3 - -letting p be permutation() -language Essence 1.3 - -letting p be permutation((5, 6)) diff --git a/tests/custom/deprecated_permutations_basic/0017_find_two_permutations_with_overlapping_domains_and_same_image_over_domain_union/permutation.essence b/tests/custom/deprecated_permutations_basic/0017_find_two_permutations_with_overlapping_domains_and_same_image_over_domain_union/permutation.essence deleted file mode 100644 index 45f9c2ee03..0000000000 --- a/tests/custom/deprecated_permutations_basic/0017_find_two_permutations_with_overlapping_domains_and_same_image_over_domain_union/permutation.essence +++ /dev/null @@ -1,8 +0,0 @@ - -find p : permutation of int(1..5) -find q : permutation of int(3..7) - -such that - forAll i : int(1..7) . - image(p,i) = image(q,i) - diff --git a/tests/custom/deprecated_permutations_basic/0017_find_two_permutations_with_overlapping_domains_and_same_image_over_domain_union/run.sh b/tests/custom/deprecated_permutations_basic/0017_find_two_permutations_with_overlapping_domains_and_same_image_over_domain_union/run.sh deleted file mode 100755 index de361d4354..0000000000 --- a/tests/custom/deprecated_permutations_basic/0017_find_two_permutations_with_overlapping_domains_and_same_image_over_domain_union/run.sh +++ /dev/null @@ -1,3 +0,0 @@ -conjure solve *.essence --number-of-solutions=40 -cat conjure-output/*.solution -rm -rf conjure-output *.solution diff --git a/tests/custom/deprecated_permutations_basic/0017_find_two_permutations_with_overlapping_domains_and_same_image_over_domain_union/stdout.expected b/tests/custom/deprecated_permutations_basic/0017_find_two_permutations_with_overlapping_domains_and_same_image_over_domain_union/stdout.expected deleted file mode 100644 index 2bc692b21d..0000000000 --- a/tests/custom/deprecated_permutations_basic/0017_find_two_permutations_with_overlapping_domains_and_same_image_over_domain_union/stdout.expected +++ /dev/null @@ -1,34 +0,0 @@ -Generating models for permutation.essence -Generated models: model000001.eprime -Saved under: conjure-output -Savile Row: model000001.eprime -Copying solution to: permutation-000001.solution -Copying solution to: permutation-000002.solution -Copying solution to: permutation-000003.solution -Copying solution to: permutation-000004.solution -Copying solution to: permutation-000005.solution -Copying solution to: permutation-000006.solution -language Essence 1.3 - -letting p be permutation() -letting q be permutation() -language Essence 1.3 - -letting p be permutation((4, 5)) -letting q be permutation((4, 5)) -language Essence 1.3 - -letting p be permutation((3, 4)) -letting q be permutation((3, 4)) -language Essence 1.3 - -letting p be permutation((3, 4, 5)) -letting q be permutation((3, 4, 5)) -language Essence 1.3 - -letting p be permutation((3, 5, 4)) -letting q be permutation((3, 5, 4)) -language Essence 1.3 - -letting p be permutation((3, 5)) -letting q be permutation((3, 5)) diff --git a/tests/custom/deprecated_permutations_basic/0018_find_matrix_lex_less_than_under_any_swap/permutation.essence b/tests/custom/deprecated_permutations_basic/0018_find_matrix_lex_less_than_under_any_swap/permutation.essence deleted file mode 100644 index 362d8df9cd..0000000000 --- a/tests/custom/deprecated_permutations_basic/0018_find_matrix_lex_less_than_under_any_swap/permutation.essence +++ /dev/null @@ -1,6 +0,0 @@ - -find m : matrix indexed by [int(1..5)] of int(0..1) - -such that - forAll i, j : int(1..5) . - i != j -> m <=lex [m[image(permutation((i,j)),k)] | k : int(1..5)] diff --git a/tests/custom/deprecated_permutations_basic/0018_find_matrix_lex_less_than_under_any_swap/run.sh b/tests/custom/deprecated_permutations_basic/0018_find_matrix_lex_less_than_under_any_swap/run.sh deleted file mode 100755 index a440de2e64..0000000000 --- a/tests/custom/deprecated_permutations_basic/0018_find_matrix_lex_less_than_under_any_swap/run.sh +++ /dev/null @@ -1,3 +0,0 @@ -conjure solve *.essence --number-of-solutions=20 -cat conjure-output/*.solution -rm -rf conjure-output *.solution diff --git a/tests/custom/deprecated_permutations_basic/0018_find_matrix_lex_less_than_under_any_swap/stdout.expected b/tests/custom/deprecated_permutations_basic/0018_find_matrix_lex_less_than_under_any_swap/stdout.expected deleted file mode 100644 index cd7357680f..0000000000 --- a/tests/custom/deprecated_permutations_basic/0018_find_matrix_lex_less_than_under_any_swap/stdout.expected +++ /dev/null @@ -1,28 +0,0 @@ -Generating models for permutation.essence -Generated models: model000001.eprime -Saved under: conjure-output -Savile Row: model000001.eprime -Copying solution to: permutation-000001.solution -Copying solution to: permutation-000002.solution -Copying solution to: permutation-000003.solution -Copying solution to: permutation-000004.solution -Copying solution to: permutation-000005.solution -Copying solution to: permutation-000006.solution -language Essence 1.3 - -letting m be [0, 0, 0, 0, 0; int(1..5)] -language Essence 1.3 - -letting m be [0, 0, 0, 0, 1; int(1..5)] -language Essence 1.3 - -letting m be [0, 0, 0, 1, 1; int(1..5)] -language Essence 1.3 - -letting m be [0, 0, 1, 1, 1; int(1..5)] -language Essence 1.3 - -letting m be [0, 1, 1, 1, 1; int(1..5)] -language Essence 1.3 - -letting m be [1, 1, 1, 1, 1; int(1..5)] diff --git a/tests/custom/deprecated_permutations_basic/0019_find_set_of_permutation_tuples_using_comprehension/permutation.essence b/tests/custom/deprecated_permutations_basic/0019_find_set_of_permutation_tuples_using_comprehension/permutation.essence deleted file mode 100644 index 85f4d0ce52..0000000000 --- a/tests/custom/deprecated_permutations_basic/0019_find_set_of_permutation_tuples_using_comprehension/permutation.essence +++ /dev/null @@ -1,7 +0,0 @@ - -find p : permutation of int(1..4) -find s : set of (int(1..4), int(1..4)) - -such that - and([ x in s | x <- p]) - /\ and([ image(p, a) = b | (a,b) <- s]) diff --git a/tests/custom/deprecated_permutations_basic/0019_find_set_of_permutation_tuples_using_comprehension/run.sh b/tests/custom/deprecated_permutations_basic/0019_find_set_of_permutation_tuples_using_comprehension/run.sh deleted file mode 100755 index 0ab098f9b5..0000000000 --- a/tests/custom/deprecated_permutations_basic/0019_find_set_of_permutation_tuples_using_comprehension/run.sh +++ /dev/null @@ -1,3 +0,0 @@ -conjure solve *.essence --number-of-solutions=200 -cat conjure-output/*.solution -rm -rf conjure-output *.solution diff --git a/tests/custom/deprecated_permutations_basic/0019_find_set_of_permutation_tuples_using_comprehension/stdout.expected b/tests/custom/deprecated_permutations_basic/0019_find_set_of_permutation_tuples_using_comprehension/stdout.expected deleted file mode 100644 index cf39893719..0000000000 --- a/tests/custom/deprecated_permutations_basic/0019_find_set_of_permutation_tuples_using_comprehension/stdout.expected +++ /dev/null @@ -1,268 +0,0 @@ -Generating models for permutation.essence -Generated models: model000001.eprime -Saved under: conjure-output -Savile Row: model000001.eprime -Copying solution to: permutation-000001.solution -Copying solution to: permutation-000002.solution -Copying solution to: permutation-000003.solution -Copying solution to: permutation-000004.solution -Copying solution to: permutation-000005.solution -Copying solution to: permutation-000006.solution -Copying solution to: permutation-000007.solution -Copying solution to: permutation-000008.solution -Copying solution to: permutation-000009.solution -Copying solution to: permutation-000010.solution -Copying solution to: permutation-000011.solution -Copying solution to: permutation-000012.solution -Copying solution to: permutation-000013.solution -Copying solution to: permutation-000014.solution -Copying solution to: permutation-000015.solution -Copying solution to: permutation-000016.solution -Copying solution to: permutation-000017.solution -Copying solution to: permutation-000018.solution -Copying solution to: permutation-000019.solution -Copying solution to: permutation-000020.solution -Copying solution to: permutation-000021.solution -Copying solution to: permutation-000022.solution -Copying solution to: permutation-000023.solution -Copying solution to: permutation-000024.solution -language Essence 1.3 - -letting p be permutation() -letting s be {(1, 1), (2, 2), (3, 3), (4, 4)} -$ Visualisation for s -$ 1 1 -$ 2 2 -$ 3 3 -$ 4 4 - -language Essence 1.3 - -letting p be permutation((3, 4)) -letting s be {(1, 1), (2, 2), (3, 4), (4, 3)} -$ Visualisation for s -$ 1 1 -$ 2 2 -$ 3 4 -$ 4 3 - -language Essence 1.3 - -letting p be permutation((2, 3)) -letting s be {(1, 1), (2, 3), (3, 2), (4, 4)} -$ Visualisation for s -$ 1 1 -$ 2 3 -$ 3 2 -$ 4 4 - -language Essence 1.3 - -letting p be permutation((2, 3, 4)) -letting s be {(1, 1), (2, 3), (3, 4), (4, 2)} -$ Visualisation for s -$ 1 1 -$ 2 3 -$ 3 4 -$ 4 2 - -language Essence 1.3 - -letting p be permutation((2, 4, 3)) -letting s be {(1, 1), (2, 4), (3, 2), (4, 3)} -$ Visualisation for s -$ 1 1 -$ 2 4 -$ 3 2 -$ 4 3 - -language Essence 1.3 - -letting p be permutation((2, 4)) -letting s be {(1, 1), (2, 4), (3, 3), (4, 2)} -$ Visualisation for s -$ 1 1 -$ 2 4 -$ 3 3 -$ 4 2 - -language Essence 1.3 - -letting p be permutation((1, 2)) -letting s be {(1, 2), (2, 1), (3, 3), (4, 4)} -$ Visualisation for s -$ 1 2 -$ 2 1 -$ 3 3 -$ 4 4 - -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4)) -letting s be {(1, 2), (2, 1), (3, 4), (4, 3)} -$ Visualisation for s -$ 1 2 -$ 2 1 -$ 3 4 -$ 4 3 - -language Essence 1.3 - -letting p be permutation((1, 2, 3)) -letting s be {(1, 2), (2, 3), (3, 1), (4, 4)} -$ Visualisation for s -$ 1 2 -$ 2 3 -$ 3 1 -$ 4 4 - -language Essence 1.3 - -letting p be permutation((1, 2, 3, 4)) -letting s be {(1, 2), (2, 3), (3, 4), (4, 1)} -$ Visualisation for s -$ 1 2 -$ 2 3 -$ 3 4 -$ 4 1 - -language Essence 1.3 - -letting p be permutation((1, 2, 4, 3)) -letting s be {(1, 2), (2, 4), (3, 1), (4, 3)} -$ Visualisation for s -$ 1 2 -$ 2 4 -$ 3 1 -$ 4 3 - -language Essence 1.3 - -letting p be permutation((1, 2, 4)) -letting s be {(1, 2), (2, 4), (3, 3), (4, 1)} -$ Visualisation for s -$ 1 2 -$ 2 4 -$ 3 3 -$ 4 1 - -language Essence 1.3 - -letting p be permutation((1, 3, 2)) -letting s be {(1, 3), (2, 1), (3, 2), (4, 4)} -$ Visualisation for s -$ 1 3 -$ 2 1 -$ 3 2 -$ 4 4 - -language Essence 1.3 - -letting p be permutation((1, 3, 4, 2)) -letting s be {(1, 3), (2, 1), (3, 4), (4, 2)} -$ Visualisation for s -$ 1 3 -$ 2 1 -$ 3 4 -$ 4 2 - -language Essence 1.3 - -letting p be permutation((1, 3)) -letting s be {(1, 3), (2, 2), (3, 1), (4, 4)} -$ Visualisation for s -$ 1 3 -$ 2 2 -$ 3 1 -$ 4 4 - -language Essence 1.3 - -letting p be permutation((1, 3, 4)) -letting s be {(1, 3), (2, 2), (3, 4), (4, 1)} -$ Visualisation for s -$ 1 3 -$ 2 2 -$ 3 4 -$ 4 1 - -language Essence 1.3 - -letting p be permutation((1, 3), (2, 4)) -letting s be {(1, 3), (2, 4), (3, 1), (4, 2)} -$ Visualisation for s -$ 1 3 -$ 2 4 -$ 3 1 -$ 4 2 - -language Essence 1.3 - -letting p be permutation((1, 3, 2, 4)) -letting s be {(1, 3), (2, 4), (3, 2), (4, 1)} -$ Visualisation for s -$ 1 3 -$ 2 4 -$ 3 2 -$ 4 1 - -language Essence 1.3 - -letting p be permutation((1, 4, 3, 2)) -letting s be {(1, 4), (2, 1), (3, 2), (4, 3)} -$ Visualisation for s -$ 1 4 -$ 2 1 -$ 3 2 -$ 4 3 - -language Essence 1.3 - -letting p be permutation((1, 4, 2)) -letting s be {(1, 4), (2, 1), (3, 3), (4, 2)} -$ Visualisation for s -$ 1 4 -$ 2 1 -$ 3 3 -$ 4 2 - -language Essence 1.3 - -letting p be permutation((1, 4, 3)) -letting s be {(1, 4), (2, 2), (3, 1), (4, 3)} -$ Visualisation for s -$ 1 4 -$ 2 2 -$ 3 1 -$ 4 3 - -language Essence 1.3 - -letting p be permutation((1, 4)) -letting s be {(1, 4), (2, 2), (3, 3), (4, 1)} -$ Visualisation for s -$ 1 4 -$ 2 2 -$ 3 3 -$ 4 1 - -language Essence 1.3 - -letting p be permutation((1, 4, 2, 3)) -letting s be {(1, 4), (2, 3), (3, 1), (4, 2)} -$ Visualisation for s -$ 1 4 -$ 2 3 -$ 3 1 -$ 4 2 - -language Essence 1.3 - -letting p be permutation((1, 4), (2, 3)) -letting s be {(1, 4), (2, 3), (3, 2), (4, 1)} -$ Visualisation for s -$ 1 4 -$ 2 3 -$ 3 2 -$ 4 1 - diff --git a/tests/custom/deprecated_permutations_basic/0020_find_permutation_inverse_using_comprehension/permutation.essence b/tests/custom/deprecated_permutations_basic/0020_find_permutation_inverse_using_comprehension/permutation.essence deleted file mode 100644 index 5da5e765ba..0000000000 --- a/tests/custom/deprecated_permutations_basic/0020_find_permutation_inverse_using_comprehension/permutation.essence +++ /dev/null @@ -1,6 +0,0 @@ - -find p : permutation (size 10) of int(1..10) -find q : permutation (size 10) of int(1..10) - -such that - and([ image(p, b) = a | (a,b) <- q]) diff --git a/tests/custom/deprecated_permutations_basic/0020_find_permutation_inverse_using_comprehension/run.sh b/tests/custom/deprecated_permutations_basic/0020_find_permutation_inverse_using_comprehension/run.sh deleted file mode 100755 index 0ab098f9b5..0000000000 --- a/tests/custom/deprecated_permutations_basic/0020_find_permutation_inverse_using_comprehension/run.sh +++ /dev/null @@ -1,3 +0,0 @@ -conjure solve *.essence --number-of-solutions=200 -cat conjure-output/*.solution -rm -rf conjure-output *.solution diff --git a/tests/custom/deprecated_permutations_basic/0020_find_permutation_inverse_using_comprehension/stdout.expected b/tests/custom/deprecated_permutations_basic/0020_find_permutation_inverse_using_comprehension/stdout.expected deleted file mode 100644 index eb4493e3a5..0000000000 --- a/tests/custom/deprecated_permutations_basic/0020_find_permutation_inverse_using_comprehension/stdout.expected +++ /dev/null @@ -1,1004 +0,0 @@ -Generating models for permutation.essence -Generated models: model000001.eprime -Saved under: conjure-output -Savile Row: model000001.eprime -Copying solution to: permutation-000001.solution -Copying solution to: permutation-000002.solution -Copying solution to: permutation-000003.solution -Copying solution to: permutation-000004.solution -Copying solution to: permutation-000005.solution -Copying solution to: permutation-000006.solution -Copying solution to: permutation-000007.solution -Copying solution to: permutation-000008.solution -Copying solution to: permutation-000009.solution -Copying solution to: permutation-000010.solution -Copying solution to: permutation-000011.solution -Copying solution to: permutation-000012.solution -Copying solution to: permutation-000013.solution -Copying solution to: permutation-000014.solution -Copying solution to: permutation-000015.solution -Copying solution to: permutation-000016.solution -Copying solution to: permutation-000017.solution -Copying solution to: permutation-000018.solution -Copying solution to: permutation-000019.solution -Copying solution to: permutation-000020.solution -Copying solution to: permutation-000021.solution -Copying solution to: permutation-000022.solution -Copying solution to: permutation-000023.solution -Copying solution to: permutation-000024.solution -Copying solution to: permutation-000025.solution -Copying solution to: permutation-000026.solution -Copying solution to: permutation-000027.solution -Copying solution to: permutation-000028.solution -Copying solution to: permutation-000029.solution -Copying solution to: permutation-000030.solution -Copying solution to: permutation-000031.solution -Copying solution to: permutation-000032.solution -Copying solution to: permutation-000033.solution -Copying solution to: permutation-000034.solution -Copying solution to: permutation-000035.solution -Copying solution to: permutation-000036.solution -Copying solution to: permutation-000037.solution -Copying solution to: permutation-000038.solution -Copying solution to: permutation-000039.solution -Copying solution to: permutation-000040.solution -Copying solution to: permutation-000041.solution -Copying solution to: permutation-000042.solution -Copying solution to: permutation-000043.solution -Copying solution to: permutation-000044.solution -Copying solution to: permutation-000045.solution -Copying solution to: permutation-000046.solution -Copying solution to: permutation-000047.solution -Copying solution to: permutation-000048.solution -Copying solution to: permutation-000049.solution -Copying solution to: permutation-000050.solution -Copying solution to: permutation-000051.solution -Copying solution to: permutation-000052.solution -Copying solution to: permutation-000053.solution -Copying solution to: permutation-000054.solution -Copying solution to: permutation-000055.solution -Copying solution to: permutation-000056.solution -Copying solution to: permutation-000057.solution -Copying solution to: permutation-000058.solution -Copying solution to: permutation-000059.solution -Copying solution to: permutation-000060.solution -Copying solution to: permutation-000061.solution -Copying solution to: permutation-000062.solution -Copying solution to: permutation-000063.solution -Copying solution to: permutation-000064.solution -Copying solution to: permutation-000065.solution -Copying solution to: permutation-000066.solution -Copying solution to: permutation-000067.solution -Copying solution to: permutation-000068.solution -Copying solution to: permutation-000069.solution -Copying solution to: permutation-000070.solution -Copying solution to: permutation-000071.solution -Copying solution to: permutation-000072.solution -Copying solution to: permutation-000073.solution -Copying solution to: permutation-000074.solution -Copying solution to: permutation-000075.solution -Copying solution to: permutation-000076.solution -Copying solution to: permutation-000077.solution -Copying solution to: permutation-000078.solution -Copying solution to: permutation-000079.solution -Copying solution to: permutation-000080.solution -Copying solution to: permutation-000081.solution -Copying solution to: permutation-000082.solution -Copying solution to: permutation-000083.solution -Copying solution to: permutation-000084.solution -Copying solution to: permutation-000085.solution -Copying solution to: permutation-000086.solution -Copying solution to: permutation-000087.solution -Copying solution to: permutation-000088.solution -Copying solution to: permutation-000089.solution -Copying solution to: permutation-000090.solution -Copying solution to: permutation-000091.solution -Copying solution to: permutation-000092.solution -Copying solution to: permutation-000093.solution -Copying solution to: permutation-000094.solution -Copying solution to: permutation-000095.solution -Copying solution to: permutation-000096.solution -Copying solution to: permutation-000097.solution -Copying solution to: permutation-000098.solution -Copying solution to: permutation-000099.solution -Copying solution to: permutation-000100.solution -Copying solution to: permutation-000101.solution -Copying solution to: permutation-000102.solution -Copying solution to: permutation-000103.solution -Copying solution to: permutation-000104.solution -Copying solution to: permutation-000105.solution -Copying solution to: permutation-000106.solution -Copying solution to: permutation-000107.solution -Copying solution to: permutation-000108.solution -Copying solution to: permutation-000109.solution -Copying solution to: permutation-000110.solution -Copying solution to: permutation-000111.solution -Copying solution to: permutation-000112.solution -Copying solution to: permutation-000113.solution -Copying solution to: permutation-000114.solution -Copying solution to: permutation-000115.solution -Copying solution to: permutation-000116.solution -Copying solution to: permutation-000117.solution -Copying solution to: permutation-000118.solution -Copying solution to: permutation-000119.solution -Copying solution to: permutation-000120.solution -Copying solution to: permutation-000121.solution -Copying solution to: permutation-000122.solution -Copying solution to: permutation-000123.solution -Copying solution to: permutation-000124.solution -Copying solution to: permutation-000125.solution -Copying solution to: permutation-000126.solution -Copying solution to: permutation-000127.solution -Copying solution to: permutation-000128.solution -Copying solution to: permutation-000129.solution -Copying solution to: permutation-000130.solution -Copying solution to: permutation-000131.solution -Copying solution to: permutation-000132.solution -Copying solution to: permutation-000133.solution -Copying solution to: permutation-000134.solution -Copying solution to: permutation-000135.solution -Copying solution to: permutation-000136.solution -Copying solution to: permutation-000137.solution -Copying solution to: permutation-000138.solution -Copying solution to: permutation-000139.solution -Copying solution to: permutation-000140.solution -Copying solution to: permutation-000141.solution -Copying solution to: permutation-000142.solution -Copying solution to: permutation-000143.solution -Copying solution to: permutation-000144.solution -Copying solution to: permutation-000145.solution -Copying solution to: permutation-000146.solution -Copying solution to: permutation-000147.solution -Copying solution to: permutation-000148.solution -Copying solution to: permutation-000149.solution -Copying solution to: permutation-000150.solution -Copying solution to: permutation-000151.solution -Copying solution to: permutation-000152.solution -Copying solution to: permutation-000153.solution -Copying solution to: permutation-000154.solution -Copying solution to: permutation-000155.solution -Copying solution to: permutation-000156.solution -Copying solution to: permutation-000157.solution -Copying solution to: permutation-000158.solution -Copying solution to: permutation-000159.solution -Copying solution to: permutation-000160.solution -Copying solution to: permutation-000161.solution -Copying solution to: permutation-000162.solution -Copying solution to: permutation-000163.solution -Copying solution to: permutation-000164.solution -Copying solution to: permutation-000165.solution -Copying solution to: permutation-000166.solution -Copying solution to: permutation-000167.solution -Copying solution to: permutation-000168.solution -Copying solution to: permutation-000169.solution -Copying solution to: permutation-000170.solution -Copying solution to: permutation-000171.solution -Copying solution to: permutation-000172.solution -Copying solution to: permutation-000173.solution -Copying solution to: permutation-000174.solution -Copying solution to: permutation-000175.solution -Copying solution to: permutation-000176.solution -Copying solution to: permutation-000177.solution -Copying solution to: permutation-000178.solution -Copying solution to: permutation-000179.solution -Copying solution to: permutation-000180.solution -Copying solution to: permutation-000181.solution -Copying solution to: permutation-000182.solution -Copying solution to: permutation-000183.solution -Copying solution to: permutation-000184.solution -Copying solution to: permutation-000185.solution -Copying solution to: permutation-000186.solution -Copying solution to: permutation-000187.solution -Copying solution to: permutation-000188.solution -Copying solution to: permutation-000189.solution -Copying solution to: permutation-000190.solution -Copying solution to: permutation-000191.solution -Copying solution to: permutation-000192.solution -Copying solution to: permutation-000193.solution -Copying solution to: permutation-000194.solution -Copying solution to: permutation-000195.solution -Copying solution to: permutation-000196.solution -Copying solution to: permutation-000197.solution -Copying solution to: permutation-000198.solution -Copying solution to: permutation-000199.solution -Copying solution to: permutation-000200.solution -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 6), (7, 8), (9, 10)) -letting q be permutation((1, 2), (3, 4), (5, 6), (7, 8), (9, 10)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 6), (7, 8, 9, 10)) -letting q be permutation((1, 2), (3, 4), (5, 6), (7, 10, 9, 8)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 6), (7, 8, 10, 9)) -letting q be permutation((1, 2), (3, 4), (5, 6), (7, 9, 10, 8)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 6), (7, 9, 10, 8)) -letting q be permutation((1, 2), (3, 4), (5, 6), (7, 8, 10, 9)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 6), (7, 9), (8, 10)) -letting q be permutation((1, 2), (3, 4), (5, 6), (7, 9), (8, 10)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 6), (7, 9, 8, 10)) -letting q be permutation((1, 2), (3, 4), (5, 6), (7, 10, 8, 9)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 6), (7, 10, 9, 8)) -letting q be permutation((1, 2), (3, 4), (5, 6), (7, 8, 9, 10)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 6), (7, 10, 8, 9)) -letting q be permutation((1, 2), (3, 4), (5, 6), (7, 9, 8, 10)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 6), (7, 10), (8, 9)) -letting q be permutation((1, 2), (3, 4), (5, 6), (7, 10), (8, 9)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 6, 7), (8, 9, 10)) -letting q be permutation((1, 2), (3, 4), (5, 7, 6), (8, 10, 9)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 6, 7), (8, 10, 9)) -letting q be permutation((1, 2), (3, 4), (5, 7, 6), (8, 9, 10)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 6, 7, 8), (9, 10)) -letting q be permutation((1, 2), (3, 4), (5, 8, 7, 6), (9, 10)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 6, 7, 8, 9, 10)) -letting q be permutation((1, 2), (3, 4), (5, 10, 9, 8, 7, 6)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 6, 7, 8, 10, 9)) -letting q be permutation((1, 2), (3, 4), (5, 9, 10, 8, 7, 6)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 6, 7, 9, 10, 8)) -letting q be permutation((1, 2), (3, 4), (5, 8, 10, 9, 7, 6)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 6, 7, 9), (8, 10)) -letting q be permutation((1, 2), (3, 4), (5, 9, 7, 6), (8, 10)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 6, 7, 9, 8, 10)) -letting q be permutation((1, 2), (3, 4), (5, 10, 8, 9, 7, 6)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 6, 7, 10, 9, 8)) -letting q be permutation((1, 2), (3, 4), (5, 8, 9, 10, 7, 6)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 6, 7, 10, 8, 9)) -letting q be permutation((1, 2), (3, 4), (5, 9, 8, 10, 7, 6)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 6, 7, 10), (8, 9)) -letting q be permutation((1, 2), (3, 4), (5, 10, 7, 6), (8, 9)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 6, 8, 7), (9, 10)) -letting q be permutation((1, 2), (3, 4), (5, 7, 8, 6), (9, 10)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 6, 8, 9, 10, 7)) -letting q be permutation((1, 2), (3, 4), (5, 7, 10, 9, 8, 6)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 6, 8, 10, 9, 7)) -letting q be permutation((1, 2), (3, 4), (5, 7, 9, 10, 8, 6)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 6, 8), (7, 9, 10)) -letting q be permutation((1, 2), (3, 4), (5, 8, 6), (7, 10, 9)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 6, 8, 7, 9, 10)) -letting q be permutation((1, 2), (3, 4), (5, 10, 9, 7, 8, 6)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 6, 8, 10, 7, 9)) -letting q be permutation((1, 2), (3, 4), (5, 9, 7, 10, 8, 6)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 6, 8, 10), (7, 9)) -letting q be permutation((1, 2), (3, 4), (5, 10, 8, 6), (7, 9)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 6, 8), (7, 10, 9)) -letting q be permutation((1, 2), (3, 4), (5, 8, 6), (7, 9, 10)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 6, 8, 7, 10, 9)) -letting q be permutation((1, 2), (3, 4), (5, 9, 10, 7, 8, 6)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 6, 8, 9), (7, 10)) -letting q be permutation((1, 2), (3, 4), (5, 9, 8, 6), (7, 10)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 6, 8, 9, 7, 10)) -letting q be permutation((1, 2), (3, 4), (5, 10, 7, 9, 8, 6)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 6, 9, 10, 8, 7)) -letting q be permutation((1, 2), (3, 4), (5, 7, 8, 10, 9, 6)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 6, 9, 7), (8, 10)) -letting q be permutation((1, 2), (3, 4), (5, 7, 9, 6), (8, 10)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 6, 9, 8, 10, 7)) -letting q be permutation((1, 2), (3, 4), (5, 7, 10, 8, 9, 6)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 6, 9, 10, 7, 8)) -letting q be permutation((1, 2), (3, 4), (5, 8, 7, 10, 9, 6)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 6, 9, 10), (7, 8)) -letting q be permutation((1, 2), (3, 4), (5, 10, 9, 6), (7, 8)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 6, 9), (7, 8, 10)) -letting q be permutation((1, 2), (3, 4), (5, 9, 6), (7, 10, 8)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 6, 9, 7, 8, 10)) -letting q be permutation((1, 2), (3, 4), (5, 10, 8, 7, 9, 6)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 6, 9, 7, 10, 8)) -letting q be permutation((1, 2), (3, 4), (5, 8, 10, 7, 9, 6)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 6, 9, 8), (7, 10)) -letting q be permutation((1, 2), (3, 4), (5, 8, 9, 6), (7, 10)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 6, 9), (7, 10, 8)) -letting q be permutation((1, 2), (3, 4), (5, 9, 6), (7, 8, 10)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 6, 9, 8, 7, 10)) -letting q be permutation((1, 2), (3, 4), (5, 10, 7, 8, 9, 6)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 6, 10, 9, 8, 7)) -letting q be permutation((1, 2), (3, 4), (5, 7, 8, 9, 10, 6)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 6, 10, 8, 9, 7)) -letting q be permutation((1, 2), (3, 4), (5, 7, 9, 8, 10, 6)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 6, 10, 7), (8, 9)) -letting q be permutation((1, 2), (3, 4), (5, 7, 10, 6), (8, 9)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 6, 10, 9, 7, 8)) -letting q be permutation((1, 2), (3, 4), (5, 8, 7, 9, 10, 6)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 6, 10, 9), (7, 8)) -letting q be permutation((1, 2), (3, 4), (5, 9, 10, 6), (7, 8)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 6, 10, 7, 8, 9)) -letting q be permutation((1, 2), (3, 4), (5, 9, 8, 7, 10, 6)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 6, 10), (7, 8, 9)) -letting q be permutation((1, 2), (3, 4), (5, 10, 6), (7, 9, 8)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 6, 10, 8), (7, 9)) -letting q be permutation((1, 2), (3, 4), (5, 8, 10, 6), (7, 9)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 6, 10, 7, 9, 8)) -letting q be permutation((1, 2), (3, 4), (5, 8, 9, 7, 10, 6)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 6, 10, 8, 7, 9)) -letting q be permutation((1, 2), (3, 4), (5, 9, 7, 8, 10, 6)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 6, 10), (7, 9, 8)) -letting q be permutation((1, 2), (3, 4), (5, 10, 6), (7, 8, 9)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 7, 6), (8, 9, 10)) -letting q be permutation((1, 2), (3, 4), (5, 6, 7), (8, 10, 9)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 7, 6), (8, 10, 9)) -letting q be permutation((1, 2), (3, 4), (5, 6, 7), (8, 9, 10)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 7, 8, 6), (9, 10)) -letting q be permutation((1, 2), (3, 4), (5, 6, 8, 7), (9, 10)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 7, 8, 9, 10, 6)) -letting q be permutation((1, 2), (3, 4), (5, 6, 10, 9, 8, 7)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 7, 8, 10, 9, 6)) -letting q be permutation((1, 2), (3, 4), (5, 6, 9, 10, 8, 7)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 7, 9, 10, 8, 6)) -letting q be permutation((1, 2), (3, 4), (5, 6, 8, 10, 9, 7)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 7, 9, 6), (8, 10)) -letting q be permutation((1, 2), (3, 4), (5, 6, 9, 7), (8, 10)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 7, 9, 8, 10, 6)) -letting q be permutation((1, 2), (3, 4), (5, 6, 10, 8, 9, 7)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 7, 10, 9, 8, 6)) -letting q be permutation((1, 2), (3, 4), (5, 6, 8, 9, 10, 7)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 7, 10, 8, 9, 6)) -letting q be permutation((1, 2), (3, 4), (5, 6, 9, 8, 10, 7)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 7, 10, 6), (8, 9)) -letting q be permutation((1, 2), (3, 4), (5, 6, 10, 7), (8, 9)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 7), (6, 8), (9, 10)) -letting q be permutation((1, 2), (3, 4), (5, 7), (6, 8), (9, 10)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 7), (6, 8, 9, 10)) -letting q be permutation((1, 2), (3, 4), (5, 7), (6, 10, 9, 8)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 7), (6, 8, 10, 9)) -letting q be permutation((1, 2), (3, 4), (5, 7), (6, 9, 10, 8)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 7, 6, 8), (9, 10)) -letting q be permutation((1, 2), (3, 4), (5, 8, 6, 7), (9, 10)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 7, 6, 8, 9, 10)) -letting q be permutation((1, 2), (3, 4), (5, 10, 9, 8, 6, 7)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 7, 6, 8, 10, 9)) -letting q be permutation((1, 2), (3, 4), (5, 9, 10, 8, 6, 7)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 7, 9, 10, 6, 8)) -letting q be permutation((1, 2), (3, 4), (5, 8, 6, 10, 9, 7)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 7, 9, 10), (6, 8)) -letting q be permutation((1, 2), (3, 4), (5, 10, 9, 7), (6, 8)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 7, 9), (6, 8, 10)) -letting q be permutation((1, 2), (3, 4), (5, 9, 7), (6, 10, 8)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 7, 9, 6, 8, 10)) -letting q be permutation((1, 2), (3, 4), (5, 10, 8, 6, 9, 7)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 7, 10, 9, 6, 8)) -letting q be permutation((1, 2), (3, 4), (5, 8, 6, 9, 10, 7)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 7, 10, 9), (6, 8)) -letting q be permutation((1, 2), (3, 4), (5, 9, 10, 7), (6, 8)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 7, 10, 6, 8, 9)) -letting q be permutation((1, 2), (3, 4), (5, 9, 8, 6, 10, 7)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 7, 10), (6, 8, 9)) -letting q be permutation((1, 2), (3, 4), (5, 10, 7), (6, 9, 8)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 7), (6, 9, 10, 8)) -letting q be permutation((1, 2), (3, 4), (5, 7), (6, 8, 10, 9)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 7), (6, 9), (8, 10)) -letting q be permutation((1, 2), (3, 4), (5, 7), (6, 9), (8, 10)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 7), (6, 9, 8, 10)) -letting q be permutation((1, 2), (3, 4), (5, 7), (6, 10, 8, 9)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 7, 6, 9, 10, 8)) -letting q be permutation((1, 2), (3, 4), (5, 8, 10, 9, 6, 7)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 7, 6, 9), (8, 10)) -letting q be permutation((1, 2), (3, 4), (5, 9, 6, 7), (8, 10)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 7, 6, 9, 8, 10)) -letting q be permutation((1, 2), (3, 4), (5, 10, 8, 9, 6, 7)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 7, 8), (6, 9, 10)) -letting q be permutation((1, 2), (3, 4), (5, 8, 7), (6, 10, 9)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 7, 8, 6, 9, 10)) -letting q be permutation((1, 2), (3, 4), (5, 10, 9, 6, 8, 7)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 7, 8, 10, 6, 9)) -letting q be permutation((1, 2), (3, 4), (5, 9, 6, 10, 8, 7)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 7, 8, 10), (6, 9)) -letting q be permutation((1, 2), (3, 4), (5, 10, 8, 7), (6, 9)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 7, 10, 8), (6, 9)) -letting q be permutation((1, 2), (3, 4), (5, 8, 10, 7), (6, 9)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 7, 10, 6, 9, 8)) -letting q be permutation((1, 2), (3, 4), (5, 8, 9, 6, 10, 7)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 7, 10, 8, 6, 9)) -letting q be permutation((1, 2), (3, 4), (5, 9, 6, 8, 10, 7)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 7, 10), (6, 9, 8)) -letting q be permutation((1, 2), (3, 4), (5, 10, 7), (6, 8, 9)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 7), (6, 10, 9, 8)) -letting q be permutation((1, 2), (3, 4), (5, 7), (6, 8, 9, 10)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 7), (6, 10, 8, 9)) -letting q be permutation((1, 2), (3, 4), (5, 7), (6, 9, 8, 10)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 7), (6, 10), (8, 9)) -letting q be permutation((1, 2), (3, 4), (5, 7), (6, 10), (8, 9)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 7, 6, 10, 9, 8)) -letting q be permutation((1, 2), (3, 4), (5, 8, 9, 10, 6, 7)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 7, 6, 10, 8, 9)) -letting q be permutation((1, 2), (3, 4), (5, 9, 8, 10, 6, 7)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 7, 6, 10), (8, 9)) -letting q be permutation((1, 2), (3, 4), (5, 10, 6, 7), (8, 9)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 7, 8), (6, 10, 9)) -letting q be permutation((1, 2), (3, 4), (5, 8, 7), (6, 9, 10)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 7, 8, 6, 10, 9)) -letting q be permutation((1, 2), (3, 4), (5, 9, 10, 6, 8, 7)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 7, 8, 9), (6, 10)) -letting q be permutation((1, 2), (3, 4), (5, 9, 8, 7), (6, 10)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 7, 8, 9, 6, 10)) -letting q be permutation((1, 2), (3, 4), (5, 10, 6, 9, 8, 7)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 7, 9, 6, 10, 8)) -letting q be permutation((1, 2), (3, 4), (5, 8, 10, 6, 9, 7)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 7, 9, 8), (6, 10)) -letting q be permutation((1, 2), (3, 4), (5, 8, 9, 7), (6, 10)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 7, 9), (6, 10, 8)) -letting q be permutation((1, 2), (3, 4), (5, 9, 7), (6, 8, 10)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 7, 9, 8, 6, 10)) -letting q be permutation((1, 2), (3, 4), (5, 10, 6, 8, 9, 7)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 8, 7, 6), (9, 10)) -letting q be permutation((1, 2), (3, 4), (5, 6, 7, 8), (9, 10)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 8, 9, 10, 7, 6)) -letting q be permutation((1, 2), (3, 4), (5, 6, 7, 10, 9, 8)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 8, 10, 9, 7, 6)) -letting q be permutation((1, 2), (3, 4), (5, 6, 7, 9, 10, 8)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 8, 6), (7, 9, 10)) -letting q be permutation((1, 2), (3, 4), (5, 6, 8), (7, 10, 9)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 8, 7, 9, 10, 6)) -letting q be permutation((1, 2), (3, 4), (5, 6, 10, 9, 7, 8)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 8, 10, 7, 9, 6)) -letting q be permutation((1, 2), (3, 4), (5, 6, 9, 7, 10, 8)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 8, 10, 6), (7, 9)) -letting q be permutation((1, 2), (3, 4), (5, 6, 10, 8), (7, 9)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 8, 6), (7, 10, 9)) -letting q be permutation((1, 2), (3, 4), (5, 6, 8), (7, 9, 10)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 8, 7, 10, 9, 6)) -letting q be permutation((1, 2), (3, 4), (5, 6, 9, 10, 7, 8)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 8, 9, 6), (7, 10)) -letting q be permutation((1, 2), (3, 4), (5, 6, 9, 8), (7, 10)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 8, 9, 7, 10, 6)) -letting q be permutation((1, 2), (3, 4), (5, 6, 10, 7, 9, 8)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 8, 6, 7), (9, 10)) -letting q be permutation((1, 2), (3, 4), (5, 7, 6, 8), (9, 10)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 8, 9, 10, 6, 7)) -letting q be permutation((1, 2), (3, 4), (5, 7, 6, 10, 9, 8)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 8, 10, 9, 6, 7)) -letting q be permutation((1, 2), (3, 4), (5, 7, 6, 9, 10, 8)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 8), (6, 7), (9, 10)) -letting q be permutation((1, 2), (3, 4), (5, 8), (6, 7), (9, 10)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 8, 9, 10), (6, 7)) -letting q be permutation((1, 2), (3, 4), (5, 10, 9, 8), (6, 7)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 8, 10, 9), (6, 7)) -letting q be permutation((1, 2), (3, 4), (5, 9, 10, 8), (6, 7)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 8), (6, 7, 9, 10)) -letting q be permutation((1, 2), (3, 4), (5, 8), (6, 10, 9, 7)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 8, 6, 7, 9, 10)) -letting q be permutation((1, 2), (3, 4), (5, 10, 9, 7, 6, 8)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 8, 10, 6, 7, 9)) -letting q be permutation((1, 2), (3, 4), (5, 9, 7, 6, 10, 8)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 8, 10), (6, 7, 9)) -letting q be permutation((1, 2), (3, 4), (5, 10, 8), (6, 9, 7)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 8), (6, 7, 10, 9)) -letting q be permutation((1, 2), (3, 4), (5, 8), (6, 9, 10, 7)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 8, 6, 7, 10, 9)) -letting q be permutation((1, 2), (3, 4), (5, 9, 10, 7, 6, 8)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 8, 9), (6, 7, 10)) -letting q be permutation((1, 2), (3, 4), (5, 9, 8), (6, 10, 7)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 8, 9, 6, 7, 10)) -letting q be permutation((1, 2), (3, 4), (5, 10, 7, 6, 9, 8)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 8, 6, 9, 10, 7)) -letting q be permutation((1, 2), (3, 4), (5, 7, 10, 9, 6, 8)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 8, 7), (6, 9, 10)) -letting q be permutation((1, 2), (3, 4), (5, 7, 8), (6, 10, 9)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 8, 10, 7), (6, 9)) -letting q be permutation((1, 2), (3, 4), (5, 7, 10, 8), (6, 9)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 8, 10, 6, 9, 7)) -letting q be permutation((1, 2), (3, 4), (5, 7, 9, 6, 10, 8)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 8), (6, 9, 10, 7)) -letting q be permutation((1, 2), (3, 4), (5, 8), (6, 7, 10, 9)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 8, 7, 6, 9, 10)) -letting q be permutation((1, 2), (3, 4), (5, 10, 9, 6, 7, 8)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 8, 10, 7, 6, 9)) -letting q be permutation((1, 2), (3, 4), (5, 9, 6, 7, 10, 8)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 8, 10), (6, 9, 7)) -letting q be permutation((1, 2), (3, 4), (5, 10, 8), (6, 7, 9)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 8), (6, 9), (7, 10)) -letting q be permutation((1, 2), (3, 4), (5, 8), (6, 9), (7, 10)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 8), (6, 9, 7, 10)) -letting q be permutation((1, 2), (3, 4), (5, 8), (6, 10, 7, 9)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 8, 6, 9), (7, 10)) -letting q be permutation((1, 2), (3, 4), (5, 9, 6, 8), (7, 10)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 8, 6, 9, 7, 10)) -letting q be permutation((1, 2), (3, 4), (5, 10, 7, 9, 6, 8)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 8, 7, 10, 6, 9)) -letting q be permutation((1, 2), (3, 4), (5, 9, 6, 10, 7, 8)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 8, 7, 10), (6, 9)) -letting q be permutation((1, 2), (3, 4), (5, 10, 7, 8), (6, 9)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 8, 6, 10, 9, 7)) -letting q be permutation((1, 2), (3, 4), (5, 7, 9, 10, 6, 8)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 8, 7), (6, 10, 9)) -letting q be permutation((1, 2), (3, 4), (5, 7, 8), (6, 9, 10)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 8, 9, 6, 10, 7)) -letting q be permutation((1, 2), (3, 4), (5, 7, 10, 6, 9, 8)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 8, 9, 7), (6, 10)) -letting q be permutation((1, 2), (3, 4), (5, 7, 9, 8), (6, 10)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 8), (6, 10, 9, 7)) -letting q be permutation((1, 2), (3, 4), (5, 8), (6, 7, 9, 10)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 8, 7, 6, 10, 9)) -letting q be permutation((1, 2), (3, 4), (5, 9, 10, 6, 7, 8)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 8, 9), (6, 10, 7)) -letting q be permutation((1, 2), (3, 4), (5, 9, 8), (6, 7, 10)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 8, 9, 7, 6, 10)) -letting q be permutation((1, 2), (3, 4), (5, 10, 6, 7, 9, 8)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 8), (6, 10, 7, 9)) -letting q be permutation((1, 2), (3, 4), (5, 8), (6, 9, 7, 10)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 8), (6, 10), (7, 9)) -letting q be permutation((1, 2), (3, 4), (5, 8), (6, 10), (7, 9)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 8, 6, 10, 7, 9)) -letting q be permutation((1, 2), (3, 4), (5, 9, 7, 10, 6, 8)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 8, 6, 10), (7, 9)) -letting q be permutation((1, 2), (3, 4), (5, 10, 6, 8), (7, 9)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 8, 7, 9), (6, 10)) -letting q be permutation((1, 2), (3, 4), (5, 9, 7, 8), (6, 10)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 8, 7, 9, 6, 10)) -letting q be permutation((1, 2), (3, 4), (5, 10, 6, 9, 7, 8)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 9, 10, 8, 7, 6)) -letting q be permutation((1, 2), (3, 4), (5, 6, 7, 8, 10, 9)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 9, 7, 6), (8, 10)) -letting q be permutation((1, 2), (3, 4), (5, 6, 7, 9), (8, 10)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 9, 8, 10, 7, 6)) -letting q be permutation((1, 2), (3, 4), (5, 6, 7, 10, 8, 9)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 9, 10, 7, 8, 6)) -letting q be permutation((1, 2), (3, 4), (5, 6, 8, 7, 10, 9)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 9, 10, 6), (7, 8)) -letting q be permutation((1, 2), (3, 4), (5, 6, 10, 9), (7, 8)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 9, 6), (7, 8, 10)) -letting q be permutation((1, 2), (3, 4), (5, 6, 9), (7, 10, 8)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 9, 7, 8, 10, 6)) -letting q be permutation((1, 2), (3, 4), (5, 6, 10, 8, 7, 9)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 9, 7, 10, 8, 6)) -letting q be permutation((1, 2), (3, 4), (5, 6, 8, 10, 7, 9)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 9, 8, 6), (7, 10)) -letting q be permutation((1, 2), (3, 4), (5, 6, 8, 9), (7, 10)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 9, 6), (7, 10, 8)) -letting q be permutation((1, 2), (3, 4), (5, 6, 9), (7, 8, 10)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 9, 8, 7, 10, 6)) -letting q be permutation((1, 2), (3, 4), (5, 6, 10, 7, 8, 9)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 9, 10, 8, 6, 7)) -letting q be permutation((1, 2), (3, 4), (5, 7, 6, 8, 10, 9)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 9, 6, 7), (8, 10)) -letting q be permutation((1, 2), (3, 4), (5, 7, 6, 9), (8, 10)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 9, 8, 10, 6, 7)) -letting q be permutation((1, 2), (3, 4), (5, 7, 6, 10, 8, 9)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 9, 10, 8), (6, 7)) -letting q be permutation((1, 2), (3, 4), (5, 8, 10, 9), (6, 7)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 9), (6, 7), (8, 10)) -letting q be permutation((1, 2), (3, 4), (5, 9), (6, 7), (8, 10)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 9, 8, 10), (6, 7)) -letting q be permutation((1, 2), (3, 4), (5, 10, 8, 9), (6, 7)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 9, 10, 6, 7, 8)) -letting q be permutation((1, 2), (3, 4), (5, 8, 7, 6, 10, 9)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 9, 10), (6, 7, 8)) -letting q be permutation((1, 2), (3, 4), (5, 10, 9), (6, 8, 7)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 9), (6, 7, 8, 10)) -letting q be permutation((1, 2), (3, 4), (5, 9), (6, 10, 8, 7)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 9, 6, 7, 8, 10)) -letting q be permutation((1, 2), (3, 4), (5, 10, 8, 7, 6, 9)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 9, 6, 7, 10, 8)) -letting q be permutation((1, 2), (3, 4), (5, 8, 10, 7, 6, 9)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 9, 8), (6, 7, 10)) -letting q be permutation((1, 2), (3, 4), (5, 8, 9), (6, 10, 7)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 9), (6, 7, 10, 8)) -letting q be permutation((1, 2), (3, 4), (5, 9), (6, 8, 10, 7)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 9, 8, 6, 7, 10)) -letting q be permutation((1, 2), (3, 4), (5, 10, 7, 6, 8, 9)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 9, 10, 7), (6, 8)) -letting q be permutation((1, 2), (3, 4), (5, 7, 10, 9), (6, 8)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 9, 10, 6, 8, 7)) -letting q be permutation((1, 2), (3, 4), (5, 7, 8, 6, 10, 9)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 9, 6, 8, 10, 7)) -letting q be permutation((1, 2), (3, 4), (5, 7, 10, 8, 6, 9)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 9, 7), (6, 8, 10)) -letting q be permutation((1, 2), (3, 4), (5, 7, 9), (6, 10, 8)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 9, 10, 7, 6, 8)) -letting q be permutation((1, 2), (3, 4), (5, 8, 6, 7, 10, 9)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 9, 10), (6, 8, 7)) -letting q be permutation((1, 2), (3, 4), (5, 10, 9), (6, 7, 8)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 9), (6, 8, 10, 7)) -letting q be permutation((1, 2), (3, 4), (5, 9), (6, 7, 10, 8)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 9, 7, 6, 8, 10)) -letting q be permutation((1, 2), (3, 4), (5, 10, 8, 6, 7, 9)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 9, 6, 8), (7, 10)) -letting q be permutation((1, 2), (3, 4), (5, 8, 6, 9), (7, 10)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 9, 7, 10, 6, 8)) -letting q be permutation((1, 2), (3, 4), (5, 8, 6, 10, 7, 9)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 9), (6, 8), (7, 10)) -letting q be permutation((1, 2), (3, 4), (5, 9), (6, 8), (7, 10)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 9, 7, 10), (6, 8)) -letting q be permutation((1, 2), (3, 4), (5, 10, 7, 9), (6, 8)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 9), (6, 8, 7, 10)) -letting q be permutation((1, 2), (3, 4), (5, 9), (6, 10, 7, 8)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 9, 6, 8, 7, 10)) -letting q be permutation((1, 2), (3, 4), (5, 10, 7, 8, 6, 9)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 9, 7), (6, 10, 8)) -letting q be permutation((1, 2), (3, 4), (5, 7, 9), (6, 8, 10)) -language Essence 1.3 - -letting p be permutation((1, 2), (3, 4), (5, 9, 8, 6, 10, 7)) -letting q be permutation((1, 2), (3, 4), (5, 7, 10, 6, 8, 9)) diff --git a/tests/custom/deprecated_permutations_basic/0021_image_of_int_under_composition_of_two_given_permutations/permutation.essence b/tests/custom/deprecated_permutations_basic/0021_image_of_int_under_composition_of_two_given_permutations/permutation.essence deleted file mode 100644 index c9605b6589..0000000000 --- a/tests/custom/deprecated_permutations_basic/0021_image_of_int_under_composition_of_two_given_permutations/permutation.essence +++ /dev/null @@ -1,13 +0,0 @@ - -letting n be 4 -letting m be 8 - -given p : permutation of int(1..n) - -given q : permutation of int(n..m) - -letting j be 20 - -find i : int(1..30) - -such that image(compose(q,p),i) = j diff --git a/tests/custom/deprecated_permutations_basic/0021_image_of_int_under_composition_of_two_given_permutations/permutation.param b/tests/custom/deprecated_permutations_basic/0021_image_of_int_under_composition_of_two_given_permutations/permutation.param deleted file mode 100644 index 6888afc4ca..0000000000 --- a/tests/custom/deprecated_permutations_basic/0021_image_of_int_under_composition_of_two_given_permutations/permutation.param +++ /dev/null @@ -1,2 +0,0 @@ -letting p be permutation((1,3),(4,2)) -letting q be permutation((4,7),(5,8)) diff --git a/tests/custom/deprecated_permutations_basic/0021_image_of_int_under_composition_of_two_given_permutations/run.sh b/tests/custom/deprecated_permutations_basic/0021_image_of_int_under_composition_of_two_given_permutations/run.sh deleted file mode 100755 index 9dc67e67f5..0000000000 --- a/tests/custom/deprecated_permutations_basic/0021_image_of_int_under_composition_of_two_given_permutations/run.sh +++ /dev/null @@ -1,3 +0,0 @@ -conjure solve *.essence *.param -cat conjure-output/*.solution -rm -rf conjure-output *.solution diff --git a/tests/custom/deprecated_permutations_basic/0021_image_of_int_under_composition_of_two_given_permutations/stdout.expected b/tests/custom/deprecated_permutations_basic/0021_image_of_int_under_composition_of_two_given_permutations/stdout.expected deleted file mode 100644 index 497335e5d7..0000000000 --- a/tests/custom/deprecated_permutations_basic/0021_image_of_int_under_composition_of_two_given_permutations/stdout.expected +++ /dev/null @@ -1,8 +0,0 @@ -Generating models for permutation.essence -Generated models: model000001.eprime -Saved under: conjure-output -Savile Row: model000001.eprime permutation.param -Copying solution to: permutation-permutation.solution -language Essence 1.3 - -letting i be 20 diff --git a/tests/custom/deprecated_permutations_basic/0022_find_matrices_of_enum_x_y_such_that_y_lexless_than_x_under_any_index_swap/permutation.essence b/tests/custom/deprecated_permutations_basic/0022_find_matrices_of_enum_x_y_such_that_y_lexless_than_x_under_any_index_swap/permutation.essence deleted file mode 100644 index b8879b7d12..0000000000 --- a/tests/custom/deprecated_permutations_basic/0022_find_matrices_of_enum_x_y_such_that_y_lexless_than_x_under_any_index_swap/permutation.essence +++ /dev/null @@ -1,13 +0,0 @@ - -given n : int -letting MYTYPE be new type enum {THING1, THING2, THING3, THING4, THING5} - - -find x : matrix indexed by [int(1..n)] of MYTYPE - -find y : matrix indexed by [int(1..n)] of MYTYPE - - -such that - forAll i, j : int(1..n) . - i != j -> y .<= image(permutation((i,j)), x) diff --git a/tests/custom/deprecated_permutations_basic/0022_find_matrices_of_enum_x_y_such_that_y_lexless_than_x_under_any_index_swap/permutation.param b/tests/custom/deprecated_permutations_basic/0022_find_matrices_of_enum_x_y_such_that_y_lexless_than_x_under_any_index_swap/permutation.param deleted file mode 100644 index 6ea3a6e608..0000000000 --- a/tests/custom/deprecated_permutations_basic/0022_find_matrices_of_enum_x_y_such_that_y_lexless_than_x_under_any_index_swap/permutation.param +++ /dev/null @@ -1,2 +0,0 @@ -letting n be 5 - diff --git a/tests/custom/deprecated_permutations_basic/0022_find_matrices_of_enum_x_y_such_that_y_lexless_than_x_under_any_index_swap/run.sh b/tests/custom/deprecated_permutations_basic/0022_find_matrices_of_enum_x_y_such_that_y_lexless_than_x_under_any_index_swap/run.sh deleted file mode 100755 index 98ec8c2243..0000000000 --- a/tests/custom/deprecated_permutations_basic/0022_find_matrices_of_enum_x_y_such_that_y_lexless_than_x_under_any_index_swap/run.sh +++ /dev/null @@ -1,3 +0,0 @@ -conjure solve *.essence *.param --number-of-solutions=20 -cat conjure-output/*.solution -rm -rf conjure-output *.solution diff --git a/tests/custom/deprecated_permutations_basic/0022_find_matrices_of_enum_x_y_such_that_y_lexless_than_x_under_any_index_swap/stdout.expected b/tests/custom/deprecated_permutations_basic/0022_find_matrices_of_enum_x_y_such_that_y_lexless_than_x_under_any_index_swap/stdout.expected deleted file mode 100644 index d2bbe0f9e1..0000000000 --- a/tests/custom/deprecated_permutations_basic/0022_find_matrices_of_enum_x_y_such_that_y_lexless_than_x_under_any_index_swap/stdout.expected +++ /dev/null @@ -1,104 +0,0 @@ -Generating models for permutation.essence -Generated models: model000001.eprime -Saved under: conjure-output -Savile Row: model000001.eprime permutation.param -Copying solution to: permutation-permutation-000001.solution -Copying solution to: permutation-permutation-000002.solution -Copying solution to: permutation-permutation-000003.solution -Copying solution to: permutation-permutation-000004.solution -Copying solution to: permutation-permutation-000005.solution -Copying solution to: permutation-permutation-000006.solution -Copying solution to: permutation-permutation-000007.solution -Copying solution to: permutation-permutation-000008.solution -Copying solution to: permutation-permutation-000009.solution -Copying solution to: permutation-permutation-000010.solution -Copying solution to: permutation-permutation-000011.solution -Copying solution to: permutation-permutation-000012.solution -Copying solution to: permutation-permutation-000013.solution -Copying solution to: permutation-permutation-000014.solution -Copying solution to: permutation-permutation-000015.solution -Copying solution to: permutation-permutation-000016.solution -Copying solution to: permutation-permutation-000017.solution -Copying solution to: permutation-permutation-000018.solution -Copying solution to: permutation-permutation-000019.solution -Copying solution to: permutation-permutation-000020.solution -language Essence 1.3 - -letting x be [THING1, THING1, THING1, THING1, THING1; int(1..5)] -letting y be [THING1, THING1, THING1, THING1, THING1; int(1..5)] -language Essence 1.3 - -letting x be [THING1, THING1, THING1, THING1, THING2; int(1..5)] -letting y be [THING1, THING1, THING1, THING1, THING1; int(1..5)] -language Essence 1.3 - -letting x be [THING1, THING1, THING1, THING1, THING2; int(1..5)] -letting y be [THING1, THING1, THING1, THING1, THING2; int(1..5)] -language Essence 1.3 - -letting x be [THING1, THING1, THING1, THING1, THING3; int(1..5)] -letting y be [THING1, THING1, THING1, THING1, THING1; int(1..5)] -language Essence 1.3 - -letting x be [THING1, THING1, THING1, THING1, THING3; int(1..5)] -letting y be [THING1, THING1, THING1, THING1, THING2; int(1..5)] -language Essence 1.3 - -letting x be [THING1, THING1, THING1, THING1, THING3; int(1..5)] -letting y be [THING1, THING1, THING1, THING1, THING3; int(1..5)] -language Essence 1.3 - -letting x be [THING1, THING1, THING1, THING1, THING4; int(1..5)] -letting y be [THING1, THING1, THING1, THING1, THING1; int(1..5)] -language Essence 1.3 - -letting x be [THING1, THING1, THING1, THING1, THING4; int(1..5)] -letting y be [THING1, THING1, THING1, THING1, THING2; int(1..5)] -language Essence 1.3 - -letting x be [THING1, THING1, THING1, THING1, THING4; int(1..5)] -letting y be [THING1, THING1, THING1, THING1, THING3; int(1..5)] -language Essence 1.3 - -letting x be [THING1, THING1, THING1, THING1, THING4; int(1..5)] -letting y be [THING1, THING1, THING1, THING1, THING4; int(1..5)] -language Essence 1.3 - -letting x be [THING1, THING1, THING1, THING1, THING5; int(1..5)] -letting y be [THING1, THING1, THING1, THING1, THING1; int(1..5)] -language Essence 1.3 - -letting x be [THING1, THING1, THING1, THING1, THING5; int(1..5)] -letting y be [THING1, THING1, THING1, THING1, THING2; int(1..5)] -language Essence 1.3 - -letting x be [THING1, THING1, THING1, THING1, THING5; int(1..5)] -letting y be [THING1, THING1, THING1, THING1, THING3; int(1..5)] -language Essence 1.3 - -letting x be [THING1, THING1, THING1, THING1, THING5; int(1..5)] -letting y be [THING1, THING1, THING1, THING1, THING4; int(1..5)] -language Essence 1.3 - -letting x be [THING1, THING1, THING1, THING1, THING5; int(1..5)] -letting y be [THING1, THING1, THING1, THING1, THING5; int(1..5)] -language Essence 1.3 - -letting x be [THING1, THING1, THING1, THING2, THING1; int(1..5)] -letting y be [THING1, THING1, THING1, THING1, THING1; int(1..5)] -language Essence 1.3 - -letting x be [THING1, THING1, THING1, THING2, THING1; int(1..5)] -letting y be [THING1, THING1, THING1, THING1, THING2; int(1..5)] -language Essence 1.3 - -letting x be [THING1, THING1, THING1, THING2, THING2; int(1..5)] -letting y be [THING1, THING1, THING1, THING1, THING1; int(1..5)] -language Essence 1.3 - -letting x be [THING1, THING1, THING1, THING2, THING2; int(1..5)] -letting y be [THING1, THING1, THING1, THING1, THING2; int(1..5)] -language Essence 1.3 - -letting x be [THING1, THING1, THING1, THING2, THING2; int(1..5)] -letting y be [THING1, THING1, THING1, THING1, THING3; int(1..5)] diff --git a/tests/custom/deprecated_permutations_basic/0023_find_triples_x_y_such_that_y_lex_less_x_under_any_swap/permutation.essence b/tests/custom/deprecated_permutations_basic/0023_find_triples_x_y_such_that_y_lex_less_x_under_any_swap/permutation.essence deleted file mode 100644 index 8959658bf4..0000000000 --- a/tests/custom/deprecated_permutations_basic/0023_find_triples_x_y_such_that_y_lex_less_x_under_any_swap/permutation.essence +++ /dev/null @@ -1,12 +0,0 @@ - -given n : int - -find x : (int(1..n), int(1..n), int(1..n)) - -find y : (int(1..n), int(1..n), int(1..n)) - - - -such that - forAll i, j : int(1..n) . - i != j -> y .<= image(permutation((i,j)), x) diff --git a/tests/custom/deprecated_permutations_basic/0023_find_triples_x_y_such_that_y_lex_less_x_under_any_swap/permutation.param b/tests/custom/deprecated_permutations_basic/0023_find_triples_x_y_such_that_y_lex_less_x_under_any_swap/permutation.param deleted file mode 100644 index f1b89d4a65..0000000000 --- a/tests/custom/deprecated_permutations_basic/0023_find_triples_x_y_such_that_y_lex_less_x_under_any_swap/permutation.param +++ /dev/null @@ -1 +0,0 @@ -letting n be 4 diff --git a/tests/custom/deprecated_permutations_basic/0023_find_triples_x_y_such_that_y_lex_less_x_under_any_swap/run.sh b/tests/custom/deprecated_permutations_basic/0023_find_triples_x_y_such_that_y_lex_less_x_under_any_swap/run.sh deleted file mode 100755 index 81aa56049c..0000000000 --- a/tests/custom/deprecated_permutations_basic/0023_find_triples_x_y_such_that_y_lex_less_x_under_any_swap/run.sh +++ /dev/null @@ -1,3 +0,0 @@ -conjure solve *.essence *.param --number-of-solutions=4 -cat conjure-output/*.solution -rm -rf conjure-output *.solution diff --git a/tests/custom/deprecated_permutations_basic/0023_find_triples_x_y_such_that_y_lex_less_x_under_any_swap/stdout.expected b/tests/custom/deprecated_permutations_basic/0023_find_triples_x_y_such_that_y_lex_less_x_under_any_swap/stdout.expected deleted file mode 100644 index 58bb53cf5f..0000000000 --- a/tests/custom/deprecated_permutations_basic/0023_find_triples_x_y_such_that_y_lex_less_x_under_any_swap/stdout.expected +++ /dev/null @@ -1,24 +0,0 @@ -Generating models for permutation.essence -Generated models: model000001.eprime -Saved under: conjure-output -Savile Row: model000001.eprime permutation.param -Copying solution to: permutation-permutation-000001.solution -Copying solution to: permutation-permutation-000002.solution -Copying solution to: permutation-permutation-000003.solution -Copying solution to: permutation-permutation-000004.solution -language Essence 1.3 - -letting x be (1, 1, 1) -letting y be (1, 1, 1) -language Essence 1.3 - -letting x be (1, 1, 2) -letting y be (1, 1, 1) -language Essence 1.3 - -letting x be (1, 1, 2) -letting y be (1, 1, 2) -language Essence 1.3 - -letting x be (1, 1, 3) -letting y be (1, 1, 1) diff --git a/tests/custom/deprecated_permutations_basic/0024_find_sets_x_y_such_that_y_lexless_x_under_any_swap/permutation.essence b/tests/custom/deprecated_permutations_basic/0024_find_sets_x_y_such_that_y_lexless_x_under_any_swap/permutation.essence deleted file mode 100644 index d38c30508f..0000000000 --- a/tests/custom/deprecated_permutations_basic/0024_find_sets_x_y_such_that_y_lexless_x_under_any_swap/permutation.essence +++ /dev/null @@ -1,12 +0,0 @@ - -given n : int - -find x : set (size n) of int(1..n) - -find y : set (size n) of int(1..n) - - - -such that - forAll i, j : int(1..n) . - i != j -> y .<= image(permutation((i,j)), x) diff --git a/tests/custom/deprecated_permutations_basic/0024_find_sets_x_y_such_that_y_lexless_x_under_any_swap/permutation.param b/tests/custom/deprecated_permutations_basic/0024_find_sets_x_y_such_that_y_lexless_x_under_any_swap/permutation.param deleted file mode 100644 index f1b89d4a65..0000000000 --- a/tests/custom/deprecated_permutations_basic/0024_find_sets_x_y_such_that_y_lexless_x_under_any_swap/permutation.param +++ /dev/null @@ -1 +0,0 @@ -letting n be 4 diff --git a/tests/custom/deprecated_permutations_basic/0024_find_sets_x_y_such_that_y_lexless_x_under_any_swap/run.sh b/tests/custom/deprecated_permutations_basic/0024_find_sets_x_y_such_that_y_lexless_x_under_any_swap/run.sh deleted file mode 100755 index 98ec8c2243..0000000000 --- a/tests/custom/deprecated_permutations_basic/0024_find_sets_x_y_such_that_y_lexless_x_under_any_swap/run.sh +++ /dev/null @@ -1,3 +0,0 @@ -conjure solve *.essence *.param --number-of-solutions=20 -cat conjure-output/*.solution -rm -rf conjure-output *.solution diff --git a/tests/custom/deprecated_permutations_basic/0024_find_sets_x_y_such_that_y_lexless_x_under_any_swap/stdout.expected b/tests/custom/deprecated_permutations_basic/0024_find_sets_x_y_such_that_y_lexless_x_under_any_swap/stdout.expected deleted file mode 100644 index 443cd04178..0000000000 --- a/tests/custom/deprecated_permutations_basic/0024_find_sets_x_y_such_that_y_lexless_x_under_any_swap/stdout.expected +++ /dev/null @@ -1,9 +0,0 @@ -Generating models for permutation.essence -Generated models: model000001.eprime -Saved under: conjure-output -Savile Row: model000001.eprime permutation.param -Copying solution to: permutation-permutation.solution -language Essence 1.3 - -letting x be {1, 2, 3, 4} -letting y be {1, 2, 3, 4} diff --git a/tests/custom/deprecated_permutations_basic/0025_find_permutation_and_matrices_x_y_such_that_image_x_eq_y/permutation.essence b/tests/custom/deprecated_permutations_basic/0025_find_permutation_and_matrices_x_y_such_that_image_x_eq_y/permutation.essence deleted file mode 100644 index f93fac900c..0000000000 --- a/tests/custom/deprecated_permutations_basic/0025_find_permutation_and_matrices_x_y_such_that_image_x_eq_y/permutation.essence +++ /dev/null @@ -1,16 +0,0 @@ - -given n : int -given m : int - -find p : permutation of int(1..n) - -find x : matrix indexed by [int((n+1)..m)] of int(1..n) - -find y : matrix indexed by [int((n+1)..m)] of int(1..n) - - -such that - y = image(p,x) - /\ allDiff(y) - /\ x != y - diff --git a/tests/custom/deprecated_permutations_basic/0025_find_permutation_and_matrices_x_y_such_that_image_x_eq_y/permutation.param b/tests/custom/deprecated_permutations_basic/0025_find_permutation_and_matrices_x_y_such_that_image_x_eq_y/permutation.param deleted file mode 100644 index 581936cf9d..0000000000 --- a/tests/custom/deprecated_permutations_basic/0025_find_permutation_and_matrices_x_y_such_that_image_x_eq_y/permutation.param +++ /dev/null @@ -1,2 +0,0 @@ -letting n be 3 -letting m be 6 diff --git a/tests/custom/deprecated_permutations_basic/0025_find_permutation_and_matrices_x_y_such_that_image_x_eq_y/run.sh b/tests/custom/deprecated_permutations_basic/0025_find_permutation_and_matrices_x_y_such_that_image_x_eq_y/run.sh deleted file mode 100755 index 98ec8c2243..0000000000 --- a/tests/custom/deprecated_permutations_basic/0025_find_permutation_and_matrices_x_y_such_that_image_x_eq_y/run.sh +++ /dev/null @@ -1,3 +0,0 @@ -conjure solve *.essence *.param --number-of-solutions=20 -cat conjure-output/*.solution -rm -rf conjure-output *.solution diff --git a/tests/custom/deprecated_permutations_basic/0025_find_permutation_and_matrices_x_y_such_that_image_x_eq_y/stdout.expected b/tests/custom/deprecated_permutations_basic/0025_find_permutation_and_matrices_x_y_such_that_image_x_eq_y/stdout.expected deleted file mode 100644 index 75a4205281..0000000000 --- a/tests/custom/deprecated_permutations_basic/0025_find_permutation_and_matrices_x_y_such_that_image_x_eq_y/stdout.expected +++ /dev/null @@ -1,124 +0,0 @@ -Generating models for permutation.essence -Generated models: model000001.eprime -Saved under: conjure-output -Savile Row: model000001.eprime permutation.param -Copying solution to: permutation-permutation-000001.solution -Copying solution to: permutation-permutation-000002.solution -Copying solution to: permutation-permutation-000003.solution -Copying solution to: permutation-permutation-000004.solution -Copying solution to: permutation-permutation-000005.solution -Copying solution to: permutation-permutation-000006.solution -Copying solution to: permutation-permutation-000007.solution -Copying solution to: permutation-permutation-000008.solution -Copying solution to: permutation-permutation-000009.solution -Copying solution to: permutation-permutation-000010.solution -Copying solution to: permutation-permutation-000011.solution -Copying solution to: permutation-permutation-000012.solution -Copying solution to: permutation-permutation-000013.solution -Copying solution to: permutation-permutation-000014.solution -Copying solution to: permutation-permutation-000015.solution -Copying solution to: permutation-permutation-000016.solution -Copying solution to: permutation-permutation-000017.solution -Copying solution to: permutation-permutation-000018.solution -Copying solution to: permutation-permutation-000019.solution -Copying solution to: permutation-permutation-000020.solution -language Essence 1.3 - -letting p be permutation((2, 3)) -letting x be [1, 2, 3; int(4..6)] -letting y be [1, 3, 2; int(4..6)] -language Essence 1.3 - -letting p be permutation((2, 3)) -letting x be [1, 3, 2; int(4..6)] -letting y be [1, 2, 3; int(4..6)] -language Essence 1.3 - -letting p be permutation((2, 3)) -letting x be [2, 1, 3; int(4..6)] -letting y be [3, 1, 2; int(4..6)] -language Essence 1.3 - -letting p be permutation((2, 3)) -letting x be [2, 3, 1; int(4..6)] -letting y be [3, 2, 1; int(4..6)] -language Essence 1.3 - -letting p be permutation((2, 3)) -letting x be [3, 1, 2; int(4..6)] -letting y be [2, 1, 3; int(4..6)] -language Essence 1.3 - -letting p be permutation((2, 3)) -letting x be [3, 2, 1; int(4..6)] -letting y be [2, 3, 1; int(4..6)] -language Essence 1.3 - -letting p be permutation((1, 2)) -letting x be [1, 2, 3; int(4..6)] -letting y be [2, 1, 3; int(4..6)] -language Essence 1.3 - -letting p be permutation((1, 2)) -letting x be [1, 3, 2; int(4..6)] -letting y be [2, 3, 1; int(4..6)] -language Essence 1.3 - -letting p be permutation((1, 2)) -letting x be [2, 1, 3; int(4..6)] -letting y be [1, 2, 3; int(4..6)] -language Essence 1.3 - -letting p be permutation((1, 2)) -letting x be [2, 3, 1; int(4..6)] -letting y be [1, 3, 2; int(4..6)] -language Essence 1.3 - -letting p be permutation((1, 2)) -letting x be [3, 1, 2; int(4..6)] -letting y be [3, 2, 1; int(4..6)] -language Essence 1.3 - -letting p be permutation((1, 2)) -letting x be [3, 2, 1; int(4..6)] -letting y be [3, 1, 2; int(4..6)] -language Essence 1.3 - -letting p be permutation((1, 2, 3)) -letting x be [1, 2, 3; int(4..6)] -letting y be [2, 3, 1; int(4..6)] -language Essence 1.3 - -letting p be permutation((1, 2, 3)) -letting x be [1, 3, 2; int(4..6)] -letting y be [2, 1, 3; int(4..6)] -language Essence 1.3 - -letting p be permutation((1, 2, 3)) -letting x be [2, 1, 3; int(4..6)] -letting y be [3, 2, 1; int(4..6)] -language Essence 1.3 - -letting p be permutation((1, 2, 3)) -letting x be [2, 3, 1; int(4..6)] -letting y be [3, 1, 2; int(4..6)] -language Essence 1.3 - -letting p be permutation((1, 2, 3)) -letting x be [3, 1, 2; int(4..6)] -letting y be [1, 2, 3; int(4..6)] -language Essence 1.3 - -letting p be permutation((1, 2, 3)) -letting x be [3, 2, 1; int(4..6)] -letting y be [1, 3, 2; int(4..6)] -language Essence 1.3 - -letting p be permutation((1, 3, 2)) -letting x be [1, 2, 3; int(4..6)] -letting y be [3, 1, 2; int(4..6)] -language Essence 1.3 - -letting p be permutation((1, 3, 2)) -letting x be [1, 3, 2; int(4..6)] -letting y be [3, 2, 1; int(4..6)] diff --git a/tests/custom/deprecated_permutations_basic/0026_find_matrices_of_enums_x_y_such_that_y_image_x_under_p/permutation.essence b/tests/custom/deprecated_permutations_basic/0026_find_matrices_of_enums_x_y_such_that_y_image_x_under_p/permutation.essence deleted file mode 100644 index 937da2aaad..0000000000 --- a/tests/custom/deprecated_permutations_basic/0026_find_matrices_of_enums_x_y_such_that_y_image_x_under_p/permutation.essence +++ /dev/null @@ -1,16 +0,0 @@ - -given n : int - -letting MYTYPE be new type enum {THING1, THING2, THING3, THING4, THING5} - -letting p be permutation ((3,4)) - -find x : matrix indexed by [int(1..n)] of MYTYPE - -find y : matrix indexed by [int(1..n)] of MYTYPE - - -such that - y = image(p,x) - /\ allDiff(y) - /\ allDiff(x) diff --git a/tests/custom/deprecated_permutations_basic/0026_find_matrices_of_enums_x_y_such_that_y_image_x_under_p/permutation.param b/tests/custom/deprecated_permutations_basic/0026_find_matrices_of_enums_x_y_such_that_y_image_x_under_p/permutation.param deleted file mode 100644 index 36d2429361..0000000000 --- a/tests/custom/deprecated_permutations_basic/0026_find_matrices_of_enums_x_y_such_that_y_image_x_under_p/permutation.param +++ /dev/null @@ -1 +0,0 @@ -letting n be 5 diff --git a/tests/custom/deprecated_permutations_basic/0026_find_matrices_of_enums_x_y_such_that_y_image_x_under_p/run.sh b/tests/custom/deprecated_permutations_basic/0026_find_matrices_of_enums_x_y_such_that_y_image_x_under_p/run.sh deleted file mode 100755 index 98ec8c2243..0000000000 --- a/tests/custom/deprecated_permutations_basic/0026_find_matrices_of_enums_x_y_such_that_y_image_x_under_p/run.sh +++ /dev/null @@ -1,3 +0,0 @@ -conjure solve *.essence *.param --number-of-solutions=20 -cat conjure-output/*.solution -rm -rf conjure-output *.solution diff --git a/tests/custom/deprecated_permutations_basic/0026_find_matrices_of_enums_x_y_such_that_y_image_x_under_p/stdout.expected b/tests/custom/deprecated_permutations_basic/0026_find_matrices_of_enums_x_y_such_that_y_image_x_under_p/stdout.expected deleted file mode 100644 index 40dfd2cbff..0000000000 --- a/tests/custom/deprecated_permutations_basic/0026_find_matrices_of_enums_x_y_such_that_y_image_x_under_p/stdout.expected +++ /dev/null @@ -1,104 +0,0 @@ -Generating models for permutation.essence -Generated models: model000001.eprime -Saved under: conjure-output -Savile Row: model000001.eprime permutation.param -Copying solution to: permutation-permutation-000001.solution -Copying solution to: permutation-permutation-000002.solution -Copying solution to: permutation-permutation-000003.solution -Copying solution to: permutation-permutation-000004.solution -Copying solution to: permutation-permutation-000005.solution -Copying solution to: permutation-permutation-000006.solution -Copying solution to: permutation-permutation-000007.solution -Copying solution to: permutation-permutation-000008.solution -Copying solution to: permutation-permutation-000009.solution -Copying solution to: permutation-permutation-000010.solution -Copying solution to: permutation-permutation-000011.solution -Copying solution to: permutation-permutation-000012.solution -Copying solution to: permutation-permutation-000013.solution -Copying solution to: permutation-permutation-000014.solution -Copying solution to: permutation-permutation-000015.solution -Copying solution to: permutation-permutation-000016.solution -Copying solution to: permutation-permutation-000017.solution -Copying solution to: permutation-permutation-000018.solution -Copying solution to: permutation-permutation-000019.solution -Copying solution to: permutation-permutation-000020.solution -language Essence 1.3 - -letting x be [THING1, THING2, THING3, THING4, THING5; int(1..5)] -letting y be [THING1, THING2, THING4, THING3, THING5; int(1..5)] -language Essence 1.3 - -letting x be [THING1, THING2, THING3, THING5, THING4; int(1..5)] -letting y be [THING1, THING2, THING5, THING3, THING4; int(1..5)] -language Essence 1.3 - -letting x be [THING1, THING2, THING4, THING3, THING5; int(1..5)] -letting y be [THING1, THING2, THING3, THING4, THING5; int(1..5)] -language Essence 1.3 - -letting x be [THING1, THING2, THING4, THING5, THING3; int(1..5)] -letting y be [THING1, THING2, THING5, THING4, THING3; int(1..5)] -language Essence 1.3 - -letting x be [THING1, THING2, THING5, THING3, THING4; int(1..5)] -letting y be [THING1, THING2, THING3, THING5, THING4; int(1..5)] -language Essence 1.3 - -letting x be [THING1, THING2, THING5, THING4, THING3; int(1..5)] -letting y be [THING1, THING2, THING4, THING5, THING3; int(1..5)] -language Essence 1.3 - -letting x be [THING1, THING3, THING2, THING4, THING5; int(1..5)] -letting y be [THING1, THING3, THING4, THING2, THING5; int(1..5)] -language Essence 1.3 - -letting x be [THING1, THING3, THING2, THING5, THING4; int(1..5)] -letting y be [THING1, THING3, THING5, THING2, THING4; int(1..5)] -language Essence 1.3 - -letting x be [THING1, THING3, THING4, THING2, THING5; int(1..5)] -letting y be [THING1, THING3, THING2, THING4, THING5; int(1..5)] -language Essence 1.3 - -letting x be [THING1, THING3, THING4, THING5, THING2; int(1..5)] -letting y be [THING1, THING3, THING5, THING4, THING2; int(1..5)] -language Essence 1.3 - -letting x be [THING1, THING3, THING5, THING2, THING4; int(1..5)] -letting y be [THING1, THING3, THING2, THING5, THING4; int(1..5)] -language Essence 1.3 - -letting x be [THING1, THING3, THING5, THING4, THING2; int(1..5)] -letting y be [THING1, THING3, THING4, THING5, THING2; int(1..5)] -language Essence 1.3 - -letting x be [THING1, THING4, THING2, THING3, THING5; int(1..5)] -letting y be [THING1, THING4, THING3, THING2, THING5; int(1..5)] -language Essence 1.3 - -letting x be [THING1, THING4, THING2, THING5, THING3; int(1..5)] -letting y be [THING1, THING4, THING5, THING2, THING3; int(1..5)] -language Essence 1.3 - -letting x be [THING1, THING4, THING3, THING2, THING5; int(1..5)] -letting y be [THING1, THING4, THING2, THING3, THING5; int(1..5)] -language Essence 1.3 - -letting x be [THING1, THING4, THING3, THING5, THING2; int(1..5)] -letting y be [THING1, THING4, THING5, THING3, THING2; int(1..5)] -language Essence 1.3 - -letting x be [THING1, THING4, THING5, THING2, THING3; int(1..5)] -letting y be [THING1, THING4, THING2, THING5, THING3; int(1..5)] -language Essence 1.3 - -letting x be [THING1, THING4, THING5, THING3, THING2; int(1..5)] -letting y be [THING1, THING4, THING3, THING5, THING2; int(1..5)] -language Essence 1.3 - -letting x be [THING1, THING5, THING2, THING3, THING4; int(1..5)] -letting y be [THING1, THING5, THING3, THING2, THING4; int(1..5)] -language Essence 1.3 - -letting x be [THING1, THING5, THING2, THING4, THING3; int(1..5)] -letting y be [THING1, THING5, THING4, THING2, THING3; int(1..5)] diff --git a/tests/custom/deprecated_permutations_basic/0027_find_sets_of_enum_x_y_such_that_y_image_x_under_p/permutation.essence b/tests/custom/deprecated_permutations_basic/0027_find_sets_of_enum_x_y_such_that_y_image_x_under_p/permutation.essence deleted file mode 100644 index e33b3b35c6..0000000000 --- a/tests/custom/deprecated_permutations_basic/0027_find_sets_of_enum_x_y_such_that_y_image_x_under_p/permutation.essence +++ /dev/null @@ -1,12 +0,0 @@ -letting MYTYPE be new type enum {THING1, THING2, THING3, THING4, THING5} - -letting p be permutation ((3,4)) - -find x : set (size 4) of MYTYPE - -find y : set (size 4) of MYTYPE - - -such that - y = image(p,x) - diff --git a/tests/custom/deprecated_permutations_basic/0027_find_sets_of_enum_x_y_such_that_y_image_x_under_p/run.sh b/tests/custom/deprecated_permutations_basic/0027_find_sets_of_enum_x_y_such_that_y_image_x_under_p/run.sh deleted file mode 100755 index a440de2e64..0000000000 --- a/tests/custom/deprecated_permutations_basic/0027_find_sets_of_enum_x_y_such_that_y_image_x_under_p/run.sh +++ /dev/null @@ -1,3 +0,0 @@ -conjure solve *.essence --number-of-solutions=20 -cat conjure-output/*.solution -rm -rf conjure-output *.solution diff --git a/tests/custom/deprecated_permutations_basic/0027_find_sets_of_enum_x_y_such_that_y_image_x_under_p/stdout.expected b/tests/custom/deprecated_permutations_basic/0027_find_sets_of_enum_x_y_such_that_y_image_x_under_p/stdout.expected deleted file mode 100644 index b7d1e6e137..0000000000 --- a/tests/custom/deprecated_permutations_basic/0027_find_sets_of_enum_x_y_such_that_y_image_x_under_p/stdout.expected +++ /dev/null @@ -1,29 +0,0 @@ -Generating models for permutation.essence -Generated models: model000001.eprime -Saved under: conjure-output -Savile Row: model000001.eprime -Copying solution to: permutation-000001.solution -Copying solution to: permutation-000002.solution -Copying solution to: permutation-000003.solution -Copying solution to: permutation-000004.solution -Copying solution to: permutation-000005.solution -language Essence 1.3 - -letting x be {THING2, THING3, THING4, THING5} -letting y be {THING2, THING3, THING4, THING5} -language Essence 1.3 - -letting x be {THING1, THING3, THING4, THING5} -letting y be {THING1, THING3, THING4, THING5} -language Essence 1.3 - -letting x be {THING1, THING2, THING4, THING5} -letting y be {THING1, THING2, THING4, THING5} -language Essence 1.3 - -letting x be {THING1, THING2, THING3, THING5} -letting y be {THING1, THING2, THING3, THING5} -language Essence 1.3 - -letting x be {THING1, THING2, THING3, THING4} -letting y be {THING1, THING2, THING3, THING4} diff --git a/tests/custom/deprecated_permutations_basic/0028_find_sets_of_enum_x_y_such_that_y_image_x_under_p/permutation.essence b/tests/custom/deprecated_permutations_basic/0028_find_sets_of_enum_x_y_such_that_y_image_x_under_p/permutation.essence deleted file mode 100644 index d009652492..0000000000 --- a/tests/custom/deprecated_permutations_basic/0028_find_sets_of_enum_x_y_such_that_y_image_x_under_p/permutation.essence +++ /dev/null @@ -1,13 +0,0 @@ -letting MYTYPE be new type enum {THING1, THING2, THING3, THING4, THING5} - -letting p be permutation ((THING3,THING4)) - -find x : set (size 4) of MYTYPE - -find y : set (size 4) of MYTYPE - - -such that - y = image(p,x) - /\ y != x - diff --git a/tests/custom/deprecated_permutations_basic/0028_find_sets_of_enum_x_y_such_that_y_image_x_under_p/run.sh b/tests/custom/deprecated_permutations_basic/0028_find_sets_of_enum_x_y_such_that_y_image_x_under_p/run.sh deleted file mode 100755 index a440de2e64..0000000000 --- a/tests/custom/deprecated_permutations_basic/0028_find_sets_of_enum_x_y_such_that_y_image_x_under_p/run.sh +++ /dev/null @@ -1,3 +0,0 @@ -conjure solve *.essence --number-of-solutions=20 -cat conjure-output/*.solution -rm -rf conjure-output *.solution diff --git a/tests/custom/deprecated_permutations_basic/0028_find_sets_of_enum_x_y_such_that_y_image_x_under_p/stdout.expected b/tests/custom/deprecated_permutations_basic/0028_find_sets_of_enum_x_y_such_that_y_image_x_under_p/stdout.expected deleted file mode 100644 index 77d313faaa..0000000000 --- a/tests/custom/deprecated_permutations_basic/0028_find_sets_of_enum_x_y_such_that_y_image_x_under_p/stdout.expected +++ /dev/null @@ -1,14 +0,0 @@ -Generating models for permutation.essence -Generated models: model000001.eprime -Saved under: conjure-output -Savile Row: model000001.eprime -Copying solution to: permutation-000001.solution -Copying solution to: permutation-000002.solution -language Essence 1.3 - -letting x be {THING1, THING2, THING4, THING5} -letting y be {THING1, THING2, THING3, THING5} -language Essence 1.3 - -letting x be {THING1, THING2, THING3, THING5} -letting y be {THING1, THING2, THING4, THING5} diff --git a/tests/custom/deprecated_permutations_basic/0029_find_relations_x_y_such_that_y_image_x_under_p/log b/tests/custom/deprecated_permutations_basic/0029_find_relations_x_y_such_that_y_image_x_under_p/log deleted file mode 100644 index 69b0598ff1..0000000000 --- a/tests/custom/deprecated_permutations_basic/0029_find_relations_x_y_such_that_y_image_x_under_p/log +++ /dev/null @@ -1,24365 +0,0 @@ -Command line options: Modelling {essence = "permutation.essence", outputDirectory = "conjure-output", numberingStart = 1, smartFilenames = False, responses = "", logLevel = LogDebug, verboseTrail = False, rewritesTrail = False, logRuleFails = False, logRuleSuccesses = False, logRuleAttempts = False, logChoices = False, strategyQ = "f", strategyA = "ai", representations = Nothing, representationsFinds = Nothing, representationsGivens = Nothing, representationsAuxiliaries = Nothing, representationsQuantifieds = Nothing, representationsCuts = Nothing, channelling = True, representationLevels = True, seed = Nothing, limitModels = Nothing, limitTime = Nothing, savedChoices = Nothing, outputFormat = Plain, lineWidth = 120} -[input] - language Essence 1.3 - - letting MYTYPE be new type enum {THING1, THING2, THING3, THING4, THING5} - letting p be permutation((THING3, THING4)) - find x: relation (size 4) of (MYTYPE * MYTYPE) - find y: relation (size 4) of (MYTYPE * MYTYPE) - such that y = image(p, x) - -[removeUnnamedsFromModel] - language Essence 1.3 - - letting MYTYPE be new type enum {THING1, THING2, THING3, THING4, THING5} - letting p be permutation((THING3, THING4)) - find x: relation (size 4) of (MYTYPE * MYTYPE) - find y: relation (size 4) of (MYTYPE * MYTYPE) - such that y = image(p, x) - -Recording enumGivens: -[removeEnumsFromModel] - language Essence 1.3 - - letting MYTYPE be domain int(1..5) - letting p be permutation((3, 4)) - find x: relation (size 4) of (MYTYPE * MYTYPE) - find y: relation (size 4) of (MYTYPE * MYTYPE) - such that y = image(p, x) - -[resolveNames] - language Essence 1.3 - - letting MYTYPE be domain int(1..5) - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that y = image(p, x) - -[typeCheckModel] - language Essence 1.3 - - letting MYTYPE be domain int(1..5) - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that y = image(p, x) - -[categoryChecking] - language Essence 1.3 - - letting MYTYPE be domain int(1..5) - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that y = image(p, x) - -[sanityChecks] - language Essence 1.3 - - letting MYTYPE be domain int(1..5) - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that y = image(p, x) - -[typeCheckModel] - language Essence 1.3 - - letting MYTYPE be domain int(1..5) - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that y = image(p, x) - -[input] - language Essence 1.3 - - letting MYTYPE be new type enum {THING1, THING2, THING3, THING4, THING5} - letting p be permutation((THING3, THING4)) - find x: relation (size 4) of (MYTYPE * MYTYPE) - find y: relation (size 4) of (MYTYPE * MYTYPE) - such that y = image(p, x) - -[addSearchOrder] - language Essence 1.3 - - letting MYTYPE be new type enum {THING1, THING2, THING3, THING4, THING5} - letting p be permutation((THING3, THING4)) - find x: relation (size 4) of (MYTYPE * MYTYPE) - find y: relation (size 4) of (MYTYPE * MYTYPE) - such that y = image(p, x) - branching on [x, y] - -[attributeAsConstraints] - language Essence 1.3 - - letting MYTYPE be new type enum {THING1, THING2, THING3, THING4, THING5} - letting p be permutation((THING3, THING4)) - find x: relation (size 4) of (MYTYPE * MYTYPE) - find y: relation (size 4) of (MYTYPE * MYTYPE) - such that y = image(p, x) - branching on [x, y] - -[inferAttributes] - language Essence 1.3 - - letting MYTYPE be new type enum {THING1, THING2, THING3, THING4, THING5} - letting p be permutation((THING3, THING4)) - find x: relation (size 4) of (MYTYPE * MYTYPE) - find y: relation (size 4) of (MYTYPE * MYTYPE) - such that y = image(p, x) - branching on [x, y] - -[inlineLettingDomainsForDecls] - language Essence 1.3 - - letting MYTYPE be new type enum {THING1, THING2, THING3, THING4, THING5} - letting p be permutation((THING3, THING4)) - find x: relation (size 4) of (MYTYPE * MYTYPE) - find y: relation (size 4) of (MYTYPE * MYTYPE) - such that y = image(p, x) - branching on [x, y] - -[lettingsForComplexInDoms] - language Essence 1.3 - - letting MYTYPE be new type enum {THING1, THING2, THING3, THING4, THING5} - letting p be permutation((THING3, THING4)) - find x: relation (size 4) of (MYTYPE * MYTYPE) - find y: relation (size 4) of (MYTYPE * MYTYPE) - such that y = image(p, x) - branching on [x, y] - -[distinctQuantifiedVars] - language Essence 1.3 - - letting MYTYPE be new type enum {THING1, THING2, THING3, THING4, THING5} - letting p be permutation((THING3, THING4)) - find x: relation (size 4) of (MYTYPE * MYTYPE) - find y: relation (size 4) of (MYTYPE * MYTYPE) - such that y = image(p, x) - branching on [x, y] - -[initInfo] - language Essence 1.3 - - letting MYTYPE be new type enum {THING1, THING2, THING3, THING4, THING5} - letting p be permutation((THING3, THING4)) - find x: relation (size 4) of (MYTYPE * MYTYPE) - find y: relation (size 4) of (MYTYPE * MYTYPE) - such that y = image(p, x) - branching on [x, y] - -[removeUnnamedsFromModel] - language Essence 1.3 - - letting MYTYPE be new type enum {THING1, THING2, THING3, THING4, THING5} - letting p be permutation((THING3, THING4)) - find x: relation (size 4) of (MYTYPE * MYTYPE) - find y: relation (size 4) of (MYTYPE * MYTYPE) - such that y = image(p, x) - branching on [x, y] - -Recording enumGivens: -[removeEnumsFromModel] - language Essence 1.3 - - letting MYTYPE be domain int(1..5) - letting p be permutation((3, 4)) - find x: relation (size 4) of (MYTYPE * MYTYPE) - find y: relation (size 4) of (MYTYPE * MYTYPE) - such that y = image(p, x) - branching on [x, y] - -[finiteGivens] - language Essence 1.3 - - letting MYTYPE be domain int(1..5) - letting p be permutation((3, 4)) - find x: relation (size 4) of (MYTYPE * MYTYPE) - find y: relation (size 4) of (MYTYPE * MYTYPE) - such that y = image(p, x) - branching on [x, y] - -[resolveNames] - language Essence 1.3 - - letting MYTYPE be domain int(1..5) - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that y = image(p, x) - branching on [x, y] - -[initInfo_Lettings] - language Essence 1.3 - - letting MYTYPE be domain int(1..5) - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that y = image(p, x) - branching on [x, y] - -[removeDomainLettings] - language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that y = image(p, x) - branching on [x, y] - -[typeCheckModel] - language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that y = image(p, x) - branching on [x, y] - -[categoryChecking] - language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that y = image(p, x) - branching on [x, y] - -[sanityChecks] - language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that y = image(p, x) - branching on [x, y] - -[dealWithCuts] - language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that y = image(p, x) - branching on [x, y] - such that - -[removeExtraSlices] - language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that y = image(p, x) - branching on [x, y] - such that - -[addTrueConstraints] - language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that y = image(p, x) - branching on [x, y] - such that - such that - true(x), - true(y) - -Contains 0 parameters (0 abstract) - 2 decision variables (2 abstract) -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that y = image(p, x) - branching on [x, y] - such that - such that - true(x), - true(y) - -Picking the first option: Question 1: permutation((3, 4)) -Picking the only option: Answer 1: full-evaluate: Full evaluator - permutation((3, 4)) -storedChoice: -permutation((3, 4)) -604127175528974338 -AnsweredRule {qHole_ = -604127175528974338, qAscendants_ = fromList [], aRuleName_ = "full-evaluate"} -LF: {"AnsweredRule":{"aRuleName_":"full-evaluate","qAscendants_":[],"qHole_":-604127175528974338}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that y = image(p, x) - branching on [x, y] - such that - such that - true(x), - true(y) - -Picking the first option: Question 1: p - Context #1: image(p, x) - Context #2: y = image(p, x) -Picking the only option: Answer 1: full-evaluate: Full evaluator - permutation((3, 4)) -storedChoice: -p -7234408895829330219 -AnsweredRule {qHole_ = -7234408895829330219, qAscendants_ = fromList [-7340749217212310711,-5834110796085551311], aRuleName_ = "full-evaluate"} -LF: {"AnsweredRule":{"aRuleName_":"full-evaluate","qAscendants_":[-7340749217212310711,-5834110796085551311],"qHole_":-7234408895829330219}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that y = image(permutation((3, 4)), x) - branching on [x, y] - such that - such that - true(x), - true(y) - -Picking the first option: Question 1: x - Context #1: image(permutation((3, 4)), x) - Context #2: y = image(permutation((3, 4)), x) -Picking the only option: Answer 1: choose-repr: Choosing representation for x: - relation {RelationAsMatrix} (size 4) of (int(1..5) * int(1..5)) - x -storedChoice: -x -7234408895963551171 -AnsweredReprStored {qHole_ = -7234408895963551171, qAscendants_ = fromList [-7111069252946253414,-6043361806322913446], aDomStored_ = "relation {RelationAsMatrix} (size 4) of (int(1..5) * int(1..5))", aRuleName_ = "choose-repr"} -LF: {"AnsweredReprStored":{"aDomStored_":"relation {RelationAsMatrix} (size 4) of (int(1..5) * int(1..5))","aRuleName_":"choose-repr","qAscendants_":[-7111069252946253414,-6043361806322913446],"qHole_":-7234408895963551171}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that y = image(permutation((3, 4)), x) - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - -Picking the first option: Question 1: y - Context #1: y = image(permutation((3, 4)), x) -Picking the only option: Answer 1: choose-repr: Choosing representation for y: - relation {RelationAsMatrix} (size 4) of (int(1..5) * int(1..5)) - y -storedChoice: -y -7234408895946773554 -AnsweredReprStored {qHole_ = -7234408895946773554, qAscendants_ = fromList [-7111069252946253414], aDomStored_ = "relation {RelationAsMatrix} (size 4) of (int(1..5) * int(1..5))", aRuleName_ = "choose-repr"} -LF: {"AnsweredReprStored":{"aDomStored_":"relation {RelationAsMatrix} (size 4) of (int(1..5) * int(1..5))","aRuleName_":"choose-repr","qAscendants_":[-7111069252946253414],"qHole_":-7234408895946773554}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that y = image(permutation((3, 4)), x) - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: x - Context #1: true(x) -Picking the only option: Answer 1: choose-repr: Choosing representation for x: - relation {RelationAsMatrix} (size 4) of (int(1..5) * int(1..5)) - x -storedChoice: -x -7234408895963551171 -AnsweredReprStored {qHole_ = -7234408895963551171, qAscendants_ = fromList [-1508832156878423928], aDomStored_ = "relation {RelationAsMatrix} (size 4) of (int(1..5) * int(1..5))", aRuleName_ = "choose-repr"} -LF: {"AnsweredReprStored":{"aDomStored_":"relation {RelationAsMatrix} (size 4) of (int(1..5) * int(1..5))","aRuleName_":"choose-repr","qAscendants_":[-1508832156878423928],"qHole_":-7234408895963551171}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that y = image(permutation((3, 4)), x) - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: y - Context #1: true(y) -Picking the only option: Answer 1: choose-repr: Choosing representation for y: - relation {RelationAsMatrix} (size 4) of (int(1..5) * int(1..5)) - y -storedChoice: -y -7234408895946773554 -AnsweredReprStored {qHole_ = -7234408895946773554, qAscendants_ = fromList [-1508550667338902379], aDomStored_ = "relation {RelationAsMatrix} (size 4) of (int(1..5) * int(1..5))", aRuleName_ = "choose-repr"} -LF: {"AnsweredReprStored":{"aDomStored_":"relation {RelationAsMatrix} (size 4) of (int(1..5) * int(1..5))","aRuleName_":"choose-repr","qAscendants_":[-1508550667338902379],"qHole_":-7234408895946773554}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that y = image(permutation((3, 4)), x) - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: [sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)] - Context #1: sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - Context #2: 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) -Picking the only option: Answer 1: choose-repr-for-comprehension: Choosing representation for quantified variable q1 (with type: int) - [sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)] -storedChoice: -[sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)] 6263396600925448594 -AnsweredRule {qHole_ = 6263396600925448594, qAscendants_ = fromList [5049395136776340146,5865511705196666561], aRuleName_ = "choose-repr-for-comprehension"} -LF: {"AnsweredRule":{"aRuleName_":"choose-repr-for-comprehension","qAscendants_":[5049395136776340146,5865511705196666561],"qHole_":6263396600925448594}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that y = image(permutation((3, 4)), x) - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: [toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)] - Context #1: sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) - Context #2: [sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)] - Context #3: sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - Context #4: 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) -Picking the only option: Answer 1: choose-repr-for-comprehension: Choosing representation for quantified variable q2 (with type: int) - [toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)] -storedChoice: -[toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)] 7855671108991671235 -AnsweredRule {qHole_ = 7855671108991671235, qAscendants_ = fromList [5049395136776340146,5865511705196666561,6263396600925448594,7085372780514568240], aRuleName_ = "choose-repr-for-comprehension"} -LF: {"AnsweredRule":{"aRuleName_":"choose-repr-for-comprehension","qAscendants_":[5049395136776340146,5865511705196666561,6263396600925448594,7085372780514568240],"qHole_":7855671108991671235}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that y = image(permutation((3, 4)), x) - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: [sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)] - Context #1: sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - Context #2: 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) -Picking the only option: Answer 1: choose-repr-for-comprehension: Choosing representation for quantified variable q3 (with type: int) - [sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)] -storedChoice: -[sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)] -3620919297952344383 -AnsweredRule {qHole_ = -3620919297952344383, qAscendants_ = fromList [-5513655157779400708,7219712989341858895], aRuleName_ = "choose-repr-for-comprehension"} -LF: {"AnsweredRule":{"aRuleName_":"choose-repr-for-comprehension","qAscendants_":[-5513655157779400708,7219712989341858895],"qHole_":-3620919297952344383}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that y = image(permutation((3, 4)), x) - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: [toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)] - Context #1: sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) - Context #2: [sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)] - Context #3: sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - Context #4: 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) -Picking the only option: Answer 1: choose-repr-for-comprehension: Choosing representation for quantified variable q4 (with type: int) - [toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)] -storedChoice: -[toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)] -2356590267706027710 -AnsweredRule {qHole_ = -2356590267706027710, qAscendants_ = fromList [-5513655157779400708,-3620919297952344383,7219712989341858895,8125267169441206107], aRuleName_ = "choose-repr-for-comprehension"} -LF: {"AnsweredRule":{"aRuleName_":"choose-repr-for-comprehension","qAscendants_":[-5513655157779400708,-3620919297952344383,7219712989341858895,8125267169441206107],"qHole_":-2356590267706027710}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that y = image(permutation((3, 4)), x) - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: image(permutation((3, 4)), x) - Context #1: y = image(permutation((3, 4)), x) -Picking the only option: Answer 1: relation-image: Horizontal rule for image relation in comprehension - { conjure_aux1 - @ find conjure_aux1: relation (size 4) of (int(1..5) * int(1..5)) - such that |x| = |conjure_aux1| /\ and([image(permutation((3, 4)), q5) in conjure_aux1 | q5 <- x]) - } -storedChoice: -image(permutation((3, 4)), x) -6043361806322913446 -AnsweredRule {qHole_ = -6043361806322913446, qAscendants_ = fromList [-7111069252946253414], aRuleName_ = "relation-image"} -LF: {"AnsweredRule":{"aRuleName_":"relation-image","qAscendants_":[-7111069252946253414],"qHole_":-6043361806322913446}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1: relation (size 4) of (int(1..5) * int(1..5)) - such that |x| = |conjure_aux1| /\ and([image(permutation((3, 4)), q5) in conjure_aux1 | q5 <- x]) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: { conjure_aux1 - @ find conjure_aux1: relation (size 4) of (int(1..5) * int(1..5)) - such that |x| = |conjure_aux1| /\ and([image(permutation((3, 4)), q5) in conjure_aux1 | q5 <- x]) - } - Context #1: y = - { conjure_aux1 - @ find conjure_aux1: relation (size 4) of (int(1..5) * int(1..5)) - such that |x| = |conjure_aux1| /\ and([image(permutation((3, 4)), q5) in conjure_aux1 | q5 <- x]) - } -Picking the only option: Answer 1: choose-repr-for-locals: Choosing representation for local variable conjure_aux1 - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that |x| = |conjure_aux1| /\ and([image(permutation((3, 4)), q5) in conjure_aux1 | q5 <- x]) - } -storedChoice: -{ conjure_aux1 -@ find conjure_aux1: relation (size 4) of (int(1..5) * int(1..5)) - such that |x| = |conjure_aux1| /\ and([image(permutation((3, 4)), q5) in conjure_aux1 | q5 <- x]) -} 1714623876200418132 -AnsweredRule {qHole_ = 1714623876200418132, qAscendants_ = fromList [5536329259437519582], aRuleName_ = "choose-repr-for-locals"} -LF: {"AnsweredRule":{"aRuleName_":"choose-repr-for-locals","qAscendants_":[5536329259437519582],"qHole_":1714623876200418132}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that |x| = |conjure_aux1| /\ and([image(permutation((3, 4)), q5) in conjure_aux1 | q5 <- x]) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: [sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)] - Context #1: sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - Context #2: 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - Context #3: { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that |x| = |conjure_aux1| /\ and([image(permutation((3, 4)), q5) in conjure_aux1 | q5 <- x]) - } - Context #4: y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that |x| = |conjure_aux1| /\ and([image(permutation((3, 4)), q5) in conjure_aux1 | q5 <- x]) - } -Picking the only option: Answer 1: choose-repr-for-comprehension: Choosing representation for quantified variable q6 (with type: int) - [sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)] -storedChoice: -[sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)] -878601234175159627 -AnsweredRule {qHole_ = -878601234175159627, qAscendants_ = fromList [-5775367836057753714,-1245214478984509661,79132428954328345,1049837485042621691], aRuleName_ = "choose-repr-for-comprehension"} -LF: {"AnsweredRule":{"aRuleName_":"choose-repr-for-comprehension","qAscendants_":[-5775367836057753714,-1245214478984509661,79132428954328345,1049837485042621691],"qHole_":-878601234175159627}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that |x| = |conjure_aux1| /\ and([image(permutation((3, 4)), q5) in conjure_aux1 | q5 <- x]) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: [toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)] - Context #1: sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) - Context #2: [sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)] - Context #3: sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - Context #4: 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - Context #5: { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that |x| = |conjure_aux1| /\ and([image(permutation((3, 4)), q5) in conjure_aux1 | q5 <- x]) - } - Context #6: y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that |x| = |conjure_aux1| /\ and([image(permutation((3, 4)), q5) in conjure_aux1 | q5 <- x]) - } -Picking the only option: Answer 1: choose-repr-for-comprehension: Choosing representation for quantified variable q7 (with type: int) - [toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)] -storedChoice: -[toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)] 2379582110528111197 -AnsweredRule {qHole_ = 2379582110528111197, qAscendants_ = fromList [-5775367836057753714,-1245214478984509661,-878601234175159627,79132428954328345,1049837485042621691,4483484998279672051], aRuleName_ = "choose-repr-for-comprehension"} -LF: {"AnsweredRule":{"aRuleName_":"choose-repr-for-comprehension","qAscendants_":[-5775367836057753714,-1245214478984509661,-878601234175159627,79132428954328345,1049837485042621691,4483484998279672051],"qHole_":2379582110528111197}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that |x| = |conjure_aux1| /\ and([image(permutation((3, 4)), q5) in conjure_aux1 | q5 <- x]) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: [image(permutation((3, 4)), q5) in conjure_aux1 | q5 <- x] - Context #1: and([image(permutation((3, 4)), q5) in conjure_aux1 | q5 <- x]) - Context #2: [|x| = |conjure_aux1|, and([image(permutation((3, 4)), q5) in conjure_aux1 | q5 <- x]); int(1..2)] - Context #3: |x| = |conjure_aux1| /\ and([image(permutation((3, 4)), q5) in conjure_aux1 | q5 <- x]) - Context #4: { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that |x| = |conjure_aux1| /\ and([image(permutation((3, 4)), q5) in conjure_aux1 | q5 <- x]) - } - Context #5: y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that |x| = |conjure_aux1| /\ and([image(permutation((3, 4)), q5) in conjure_aux1 | q5 <- x]) - } -Picking the only option: Answer 1: relation-map_in_expr{RelationAsMatrix}: Vertical rule for map_in_expr for relation domains, RelationAsMatrix representation. - [image(permutation((3, 4)), (q8[1], q8[2])) in conjure_aux1 | q8 : (int(1..5), int(1..5)), x_RelationAsMatrix[q8[1], q8[2]]] -storedChoice: -[image(permutation((3, 4)), q5) in conjure_aux1 | q5 <- x] 2569794631160861273 -AnsweredRule {qHole_ = 2569794631160861273, qAscendants_ = fromList [-4776664362067532454,-1245214478984509661,-1036657270873470960,79132428954328345,5830139973578569810], aRuleName_ = "relation-map_in_expr{RelationAsMatrix}"} -LF: {"AnsweredRule":{"aRuleName_":"relation-map_in_expr{RelationAsMatrix}","qAscendants_":[-4776664362067532454,-1245214478984509661,-1036657270873470960,79132428954328345,5830139973578569810],"qHole_":2569794631160861273}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([image(permutation((3, 4)), (q8[1], q8[2])) in conjure_aux1 | q8 : (int(1..5), int(1..5)), x_RelationAsMatrix[q8[1], q8[2]]]) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: [image(permutation((3, 4)), (q8[1], q8[2])) in conjure_aux1 - | q8 : (int(1..5), int(1..5)), x_RelationAsMatrix[q8[1], q8[2]]] - Context #1: and([image(permutation((3, 4)), (q8[1], q8[2])) in conjure_aux1 - | q8 : (int(1..5), int(1..5)), x_RelationAsMatrix[q8[1], q8[2]]]) - Context #2: [|x| = |conjure_aux1|, - and([image(permutation((3, 4)), (q8[1], q8[2])) in conjure_aux1 | q8 : (int(1..5), int(1..5)), x_RelationAsMatrix[q8[1], q8[2]]]); - int(1..2)] - Context #3: |x| = |conjure_aux1| /\ - and([image(permutation((3, 4)), (q8[1], q8[2])) in conjure_aux1 | q8 : (int(1..5), int(1..5)), x_RelationAsMatrix[q8[1], q8[2]]]) - Context #4: { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([image(permutation((3, 4)), (q8[1], q8[2])) in conjure_aux1 | q8 : (int(1..5), int(1..5)), x_RelationAsMatrix[q8[1], q8[2]]]) - } - Context #5: y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([image(permutation((3, 4)), (q8[1], q8[2])) in conjure_aux1 | q8 : (int(1..5), int(1..5)), x_RelationAsMatrix[q8[1], q8[2]]]) - } -Picking the only option: Answer 1: choose-repr-for-comprehension: Choosing representation for quantified variable q8 (with type: (int, - int)) - [image(permutation((3, 4)), (q8[1], q8[2])) in conjure_aux1 | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]] -storedChoice: -[image(permutation((3, 4)), (q8[1], q8[2])) in conjure_aux1 - | q8 : (int(1..5), int(1..5)), x_RelationAsMatrix[q8[1], q8[2]]] -6121410142271556240 -AnsweredRule {qHole_ = -6121410142271556240, qAscendants_ = fromList [-8542780548609610841,-2372866271326699518,-688805377682383984,1829424135801856670,4203509818187934421], aRuleName_ = "choose-repr-for-comprehension"} -LF: {"AnsweredRule":{"aRuleName_":"choose-repr-for-comprehension","qAscendants_":[-8542780548609610841,-2372866271326699518,-688805377682383984,1829424135801856670,4203509818187934421],"qHole_":-6121410142271556240}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([image(permutation((3, 4)), (q8[1], q8[2])) in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: image(permutation((3, 4)), (q8[1], q8[2])) - Context #1: image(permutation((3, 4)), (q8[1], q8[2])) in conjure_aux1 - Context #2: [image(permutation((3, 4)), (q8[1], q8[2])) in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]] - Context #3: and([image(permutation((3, 4)), (q8[1], q8[2])) in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - Context #4: [|x| = |conjure_aux1|, - and([image(permutation((3, 4)), (q8[1], q8[2])) in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]); - int(1..2)] - Context #5: |x| = |conjure_aux1| /\ - and([image(permutation((3, 4)), (q8[1], q8[2])) in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - Context #6: { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([image(permutation((3, 4)), (q8[1], q8[2])) in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - Context #7: y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([image(permutation((3, 4)), (q8[1], q8[2])) in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } -Picking the only option: Answer 1: tuple-image: Horizontal rule for image tuple in comprehension - { conjure_aux2 - @ find conjure_aux2: (int(1..5), int(1..5)) - such that conjure_aux2[1] = image(permutation((3, 4)), (q8[1], q8[2])[1]) - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } -storedChoice: -image(permutation((3, 4)), (q8[1], q8[2])) 7641797427128728383 -AnsweredRule {qHole_ = 7641797427128728383, qAscendants_ = fromList [-6118234929664435696,-1399392580596120430,-1387706708486858898,-1208703870972871253,-742133995496027829,4437220630107512706,5070918677941821273], aRuleName_ = "tuple-image"} -LF: {"AnsweredRule":{"aRuleName_":"tuple-image","qAscendants_":[-6118234929664435696,-1399392580596120430,-1387706708486858898,-1208703870972871253,-742133995496027829,4437220630107512706,5070918677941821273],"qHole_":7641797427128728383}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2: (int(1..5), int(1..5)) - such that conjure_aux2[1] = image(permutation((3, 4)), (q8[1], q8[2])[1]) - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: { conjure_aux2 - @ find conjure_aux2: (int(1..5), int(1..5)) - such that conjure_aux2[1] = image(permutation((3, 4)), (q8[1], q8[2])[1]) - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - Context #1: { conjure_aux2 - @ find conjure_aux2: (int(1..5), int(1..5)) - such that conjure_aux2[1] = image(permutation((3, 4)), (q8[1], q8[2])[1]) - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - Context #2: [{ conjure_aux2 - @ find conjure_aux2: (int(1..5), int(1..5)) - such that conjure_aux2[1] = image(permutation((3, 4)), (q8[1], q8[2])[1]) - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]] - Context #3: and([{ conjure_aux2 - @ find conjure_aux2: (int(1..5), int(1..5)) - such that conjure_aux2[1] = image(permutation((3, 4)), (q8[1], q8[2])[1]) - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - Context #4: [|x| = |conjure_aux1|, - and([{ conjure_aux2 - @ find conjure_aux2: (int(1..5), int(1..5)) - such that conjure_aux2[1] = image(permutation((3, 4)), (q8[1], q8[2])[1]) - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]); - int(1..2)] - Context #5: |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2: (int(1..5), int(1..5)) - such that conjure_aux2[1] = image(permutation((3, 4)), (q8[1], q8[2])[1]) - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - Context #6: { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2: (int(1..5), int(1..5)) - such that conjure_aux2[1] = image(permutation((3, 4)), (q8[1], q8[2])[1]) - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - Context #7: y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2: (int(1..5), int(1..5)) - such that conjure_aux2[1] = image(permutation((3, 4)), (q8[1], q8[2])[1]) - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } -Picking the only option: Answer 1: choose-repr-for-locals: Choosing representation for local variable conjure_aux2 - { conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that conjure_aux2[1] = image(permutation((3, 4)), (q8[1], q8[2])[1]) - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } -storedChoice: -{ conjure_aux2 -@ find conjure_aux2: (int(1..5), int(1..5)) - such that conjure_aux2[1] = image(permutation((3, 4)), (q8[1], q8[2])[1]) - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) -} 7832450608952021018 -AnsweredRule {qHole_ = 7832450608952021018, qAscendants_ = fromList [-4717314876217502109,-4294582922489450379,1651264905194084305,2977457561748621690,4087019737558016944,5019534480518702783,6820345709468359473], aRuleName_ = "choose-repr-for-locals"} -LF: {"AnsweredRule":{"aRuleName_":"choose-repr-for-locals","qAscendants_":[-4717314876217502109,-4294582922489450379,1651264905194084305,2977457561748621690,4087019737558016944,5019534480518702783,6820345709468359473],"qHole_":7832450608952021018}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that conjure_aux2[1] = image(permutation((3, 4)), (q8[1], q8[2])[1]) - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: conjure_aux2[1] - Context #1: conjure_aux2[1] = image(permutation((3, 4)), (q8[1], q8[2])[1]) - Context #2: { conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that conjure_aux2[1] = image(permutation((3, 4)), (q8[1], q8[2])[1]) - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - Context #3: { conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that conjure_aux2[1] = image(permutation((3, 4)), (q8[1], q8[2])[1]) - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - Context #4: [{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that conjure_aux2[1] = image(permutation((3, 4)), (q8[1], q8[2])[1]) - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]] - Context #5: and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that conjure_aux2[1] = image(permutation((3, 4)), (q8[1], q8[2])[1]) - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - Context #6: [|x| = |conjure_aux1|, - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that conjure_aux2[1] = image(permutation((3, 4)), (q8[1], q8[2])[1]) - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]); - int(1..2)] - Context #7: |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that conjure_aux2[1] = image(permutation((3, 4)), (q8[1], q8[2])[1]) - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - Context #8: { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that conjure_aux2[1] = image(permutation((3, 4)), (q8[1], q8[2])[1]) - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - Context #9: y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that conjure_aux2[1] = image(permutation((3, 4)), (q8[1], q8[2])[1]) - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } -Picking the only option: Answer 1: tuple-index: Tuple indexing on: conjure_aux2[1] - conjure_aux2_1 -storedChoice: -conjure_aux2[1] 2042848205583864547 -AnsweredRule {qHole_ = 2042848205583864547, qAscendants_ = fromList [-7836606021998938252,-4083899676628141502,-3337431591692655861,-1871379374487492755,31163859450310923,347176683161250196,1078578095348213584,3723112517704369347,8818185052449544140], aRuleName_ = "tuple-index"} -LF: {"AnsweredRule":{"aRuleName_":"tuple-index","qAscendants_":[-7836606021998938252,-4083899676628141502,-3337431591692655861,-1871379374487492755,31163859450310923,347176683161250196,1078578095348213584,3723112517704369347,8818185052449544140],"qHole_":2042848205583864547}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that conjure_aux2_1 = image(permutation((3, 4)), (q8[1], q8[2])[1]) - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: (q8[1], q8[2])[1] - Context #1: image(permutation((3, 4)), (q8[1], q8[2])[1]) - Context #2: conjure_aux2_1 = image(permutation((3, 4)), (q8[1], q8[2])[1]) - Context #3: { conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that conjure_aux2_1 = image(permutation((3, 4)), (q8[1], q8[2])[1]) - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - Context #4: { conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that conjure_aux2_1 = image(permutation((3, 4)), (q8[1], q8[2])[1]) - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - Context #5: [{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that conjure_aux2_1 = image(permutation((3, 4)), (q8[1], q8[2])[1]) - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]] - Context #6: and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that conjure_aux2_1 = image(permutation((3, 4)), (q8[1], q8[2])[1]) - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - Context #7: [|x| = |conjure_aux1|, - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that conjure_aux2_1 = image(permutation((3, 4)), (q8[1], q8[2])[1]) - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]); - int(1..2)] - Context #8: |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that conjure_aux2_1 = image(permutation((3, 4)), (q8[1], q8[2])[1]) - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - Context #9: { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that conjure_aux2_1 = image(permutation((3, 4)), (q8[1], q8[2])[1]) - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - Context #10: y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that conjure_aux2_1 = image(permutation((3, 4)), (q8[1], q8[2])[1]) - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } -Picking the only option: Answer 1: tuple-index: Tuple indexing on: (q8[1], q8[2])[1] - q8[1] -storedChoice: -(q8[1], q8[2])[1] -5501922928837560372 -AnsweredRule {qHole_ = -5501922928837560372, qAscendants_ = fromList [-8079003502337880871,-5992757738829033069,-4052786222025792276,-4045994663639704708,-1887930543228865818,2614825847120268012,2969550575619082812,4897364746913734457,7503648025096004321,8070588202073729915], aRuleName_ = "tuple-index"} -LF: {"AnsweredRule":{"aRuleName_":"tuple-index","qAscendants_":[-8079003502337880871,-5992757738829033069,-4052786222025792276,-4045994663639704708,-1887930543228865818,2614825847120268012,2969550575619082812,4897364746913734457,7503648025096004321,8070588202073729915],"qHole_":-5501922928837560372}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that conjure_aux2_1 = image(permutation((3, 4)), q8[1]) - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: q8[1] - Context #1: image(permutation((3, 4)), q8[1]) - Context #2: conjure_aux2_1 = image(permutation((3, 4)), q8[1]) - Context #3: { conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that conjure_aux2_1 = image(permutation((3, 4)), q8[1]) - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - Context #4: { conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that conjure_aux2_1 = image(permutation((3, 4)), q8[1]) - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - Context #5: [{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that conjure_aux2_1 = image(permutation((3, 4)), q8[1]) - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]] - Context #6: and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that conjure_aux2_1 = image(permutation((3, 4)), q8[1]) - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - Context #7: [|x| = |conjure_aux1|, - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that conjure_aux2_1 = image(permutation((3, 4)), q8[1]) - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]); - int(1..2)] - Context #8: |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that conjure_aux2_1 = image(permutation((3, 4)), q8[1]) - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - Context #9: { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that conjure_aux2_1 = image(permutation((3, 4)), q8[1]) - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - Context #10: y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that conjure_aux2_1 = image(permutation((3, 4)), q8[1]) - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } -Picking the only option: Answer 1: tuple-index: Tuple indexing on: q8[1] - q8_1 -storedChoice: -q8[1] 6051865069970393497 -AnsweredRule {qHole_ = 6051865069970393497, qAscendants_ = fromList [-6240564754428641774,-3828924106000349868,-2497616537930163555,-2455337427536589680,-1546470019878997061,409221243111017286,1096079797629796883,1353067250173028676,4249511820642706384,6954638962073438443], aRuleName_ = "tuple-index"} -LF: {"AnsweredRule":{"aRuleName_":"tuple-index","qAscendants_":[-6240564754428641774,-3828924106000349868,-2497616537930163555,-2455337427536589680,-1546470019878997061,409221243111017286,1096079797629796883,1353067250173028676,4249511820642706384,6954638962073438443],"qHole_":6051865069970393497}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that conjure_aux2_1 = image(permutation((3, 4)), q8_1) - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: image(permutation((3, 4)), q8_1) - Context #1: conjure_aux2_1 = image(permutation((3, 4)), q8_1) - Context #2: { conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that conjure_aux2_1 = image(permutation((3, 4)), q8_1) - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - Context #3: { conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that conjure_aux2_1 = image(permutation((3, 4)), q8_1) - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - Context #4: [{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that conjure_aux2_1 = image(permutation((3, 4)), q8_1) - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]] - Context #5: and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that conjure_aux2_1 = image(permutation((3, 4)), q8_1) - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - Context #6: [|x| = |conjure_aux1|, - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that conjure_aux2_1 = image(permutation((3, 4)), q8_1) - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]); - int(1..2)] - Context #7: |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that conjure_aux2_1 = image(permutation((3, 4)), q8_1) - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - Context #8: { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that conjure_aux2_1 = image(permutation((3, 4)), q8_1) - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - Context #9: y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that conjure_aux2_1 = image(permutation((3, 4)), q8_1) - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } -Picking the only option: Answer 1: permutation-image-literal{AsFunction}: Horizontal rule for permutation literal application to a single value (image), AsFunction representation - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and([q9 = q8_1 <-> conjure_aux3 = q10 | (q9, q10) <- [(3, 4), (4, 3); int(1..2)]]) /\ - (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) - } -storedChoice: -image(permutation((3, 4)), q8_1) -6565377216106402436 -AnsweredRule {qHole_ = -6565377216106402436, qAscendants_ = fromList [-8683446058401842621,-8501667396727033866,-6589174251984098358,-5196229448616722462,-2562107481961042620,-1290778481550223845,5400239128163960843,7319032080622836357,8711639898256895276], aRuleName_ = "permutation-image-literal{AsFunction}"} -LF: {"AnsweredRule":{"aRuleName_":"permutation-image-literal{AsFunction}","qAscendants_":[-8683446058401842621,-8501667396727033866,-6589174251984098358,-5196229448616722462,-2562107481961042620,-1290778481550223845,5400239128163960843,7319032080622836357,8711639898256895276],"qHole_":-6565377216106402436}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and([q9 = q8_1 <-> conjure_aux3 = q10 | (q9, q10) <- [(3, 4), (4, 3); int(1..2)]]) /\ - (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: [(3, 4), (4, 3); int(1..2)] - Context #1: [q9 = q8_1 <-> conjure_aux3 = q10 | (q9, q10) <- [(3, 4), (4, 3); int(1..2)]] - Context #2: and([q9 = q8_1 <-> conjure_aux3 = q10 | (q9, q10) <- [(3, 4), (4, 3); int(1..2)]]) - Context #3: [and([q9 = q8_1 <-> conjure_aux3 = q10 | (q9, q10) <- [(3, 4), (4, 3); int(1..2)]]), - !or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1; - int(1..2)] - Context #4: and([q9 = q8_1 <-> conjure_aux3 = q10 | (q9, q10) <- [(3, 4), (4, 3); int(1..2)]]) /\ - (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) - Context #5: { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and([q9 = q8_1 <-> conjure_aux3 = q10 | (q9, q10) <- [(3, 4), (4, 3); int(1..2)]]) /\ - (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) - } - Context #6: conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and([q9 = q8_1 <-> conjure_aux3 = q10 | (q9, q10) <- [(3, 4), (4, 3); int(1..2)]]) /\ - (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) - } - Context #7: { conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and([q9 = q8_1 <-> conjure_aux3 = q10 | (q9, q10) <- [(3, 4), (4, 3); int(1..2)]]) /\ - (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - Context #8: { conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and([q9 = q8_1 <-> conjure_aux3 = q10 | (q9, q10) <- [(3, 4), (4, 3); int(1..2)]]) /\ - (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - Context #9: [{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and([q9 = q8_1 <-> conjure_aux3 = q10 | (q9, q10) <- [(3, 4), (4, 3); int(1..2)]]) /\ - (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]] - Context #10: and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and([q9 = q8_1 <-> conjure_aux3 = q10 | (q9, q10) <- [(3, 4), (4, 3); int(1..2)]]) /\ - (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - Context #11: [|x| = |conjure_aux1|, - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and([q9 = q8_1 <-> conjure_aux3 = q10 | (q9, q10) <- [(3, 4), (4, 3); int(1..2)]]) /\ - (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]); - int(1..2)] - Context #12: |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and([q9 = q8_1 <-> conjure_aux3 = q10 | (q9, q10) <- [(3, 4), (4, 3); int(1..2)]]) /\ - (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - Context #13: { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and([q9 = q8_1 <-> conjure_aux3 = q10 | (q9, q10) <- [(3, 4), (4, 3); int(1..2)]]) /\ - (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - Context #14: y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and([q9 = q8_1 <-> conjure_aux3 = q10 | (q9, q10) <- [(3, 4), (4, 3); int(1..2)]]) /\ - (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } -Picking the only option: Answer 1: full-evaluate: Full evaluator - [(3, 4), (4, 3); int(1..2)] -storedChoice: -[(3, 4), (4, 3); int(1..2)] 6597397470067790033 -AnsweredRule {qHole_ = 6597397470067790033, qAscendants_ = fromList [-8621354921797967448,-6160248818055544346,-6049820697610812758,-4894284809815571873,-4858508204008314707,-4635274203177452231,-1665058964617223774,996353907888938120,1107585814561782716,1593343993162845666,1994644797538381771,2641311773319376803,3730217346423440641,5862930277568425410], aRuleName_ = "full-evaluate"} -LF: {"AnsweredRule":{"aRuleName_":"full-evaluate","qAscendants_":[-8621354921797967448,-6160248818055544346,-6049820697610812758,-4894284809815571873,-4858508204008314707,-4635274203177452231,-1665058964617223774,996353907888938120,1107585814561782716,1593343993162845666,1994644797538381771,2641311773319376803,3730217346423440641,5862930277568425410],"qHole_":6597397470067790033}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and([q9 = q8_1 <-> conjure_aux3 = q10 | (q9, q10) <- [(3, 4), (4, 3); int(1..2)]]) /\ - (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: [q9 = q8_1 <-> conjure_aux3 = q10 | (q9, q10) <- [(3, 4), (4, 3); int(1..2)]] - Context #1: and([q9 = q8_1 <-> conjure_aux3 = q10 | (q9, q10) <- [(3, 4), (4, 3); int(1..2)]]) - Context #2: [and([q9 = q8_1 <-> conjure_aux3 = q10 | (q9, q10) <- [(3, 4), (4, 3); int(1..2)]]), - !or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1; - int(1..2)] - Context #3: and([q9 = q8_1 <-> conjure_aux3 = q10 | (q9, q10) <- [(3, 4), (4, 3); int(1..2)]]) /\ - (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) - Context #4: { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and([q9 = q8_1 <-> conjure_aux3 = q10 | (q9, q10) <- [(3, 4), (4, 3); int(1..2)]]) /\ - (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) - } - Context #5: conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and([q9 = q8_1 <-> conjure_aux3 = q10 | (q9, q10) <- [(3, 4), (4, 3); int(1..2)]]) /\ - (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) - } - Context #6: { conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and([q9 = q8_1 <-> conjure_aux3 = q10 | (q9, q10) <- [(3, 4), (4, 3); int(1..2)]]) /\ - (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - Context #7: { conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and([q9 = q8_1 <-> conjure_aux3 = q10 | (q9, q10) <- [(3, 4), (4, 3); int(1..2)]]) /\ - (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - Context #8: [{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and([q9 = q8_1 <-> conjure_aux3 = q10 | (q9, q10) <- [(3, 4), (4, 3); int(1..2)]]) /\ - (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]] - Context #9: and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and([q9 = q8_1 <-> conjure_aux3 = q10 | (q9, q10) <- [(3, 4), (4, 3); int(1..2)]]) /\ - (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - Context #10: [|x| = |conjure_aux1|, - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and([q9 = q8_1 <-> conjure_aux3 = q10 | (q9, q10) <- [(3, 4), (4, 3); int(1..2)]]) /\ - (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]); - int(1..2)] - Context #11: |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and([q9 = q8_1 <-> conjure_aux3 = q10 | (q9, q10) <- [(3, 4), (4, 3); int(1..2)]]) /\ - (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - Context #12: { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and([q9 = q8_1 <-> conjure_aux3 = q10 | (q9, q10) <- [(3, 4), (4, 3); int(1..2)]]) /\ - (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - Context #13: y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and([q9 = q8_1 <-> conjure_aux3 = q10 | (q9, q10) <- [(3, 4), (4, 3); int(1..2)]]) /\ - (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } -Picking the only option: Answer 1: complex-pattern: complex pattern on tuple patterns - [q13[1] = q8_1 <-> conjure_aux3 = q13[2] | q13 <- [(3, 4), (4, 3); int(1..2)]] -storedChoice: -[q9 = q8_1 <-> conjure_aux3 = q10 | (q9, q10) <- [(3, 4), (4, 3); int(1..2)]] 996353907888938120 -AnsweredRule {qHole_ = 996353907888938120, qAscendants_ = fromList [-8621354921797967448,-6160248818055544346,-6049820697610812758,-4894284809815571873,-4858508204008314707,-4635274203177452231,-1665058964617223774,1107585814561782716,1593343993162845666,1994644797538381771,2641311773319376803,3730217346423440641,5862930277568425410], aRuleName_ = "complex-pattern"} -LF: {"AnsweredRule":{"aRuleName_":"complex-pattern","qAscendants_":[-8621354921797967448,-6160248818055544346,-6049820697610812758,-4894284809815571873,-4858508204008314707,-4635274203177452231,-1665058964617223774,1107585814561782716,1593343993162845666,1994644797538381771,2641311773319376803,3730217346423440641,5862930277568425410],"qHole_":996353907888938120}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and([q13[1] = q8_1 <-> conjure_aux3 = q13[2] | q13 <- [(3, 4), (4, 3); int(1..2)]]) /\ - (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: [q13[1] = q8_1 <-> conjure_aux3 = q13[2] | q13 <- [(3, 4), (4, 3); int(1..2)]] - Context #1: and([q13[1] = q8_1 <-> conjure_aux3 = q13[2] | q13 <- [(3, 4), (4, 3); int(1..2)]]) - Context #2: [and([q13[1] = q8_1 <-> conjure_aux3 = q13[2] | q13 <- [(3, 4), (4, 3); int(1..2)]]), - !or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1; - int(1..2)] - Context #3: and([q13[1] = q8_1 <-> conjure_aux3 = q13[2] | q13 <- [(3, 4), (4, 3); int(1..2)]]) /\ - (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) - Context #4: { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and([q13[1] = q8_1 <-> conjure_aux3 = q13[2] | q13 <- [(3, 4), (4, 3); int(1..2)]]) /\ - (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) - } - Context #5: conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and([q13[1] = q8_1 <-> conjure_aux3 = q13[2] | q13 <- [(3, 4), (4, 3); int(1..2)]]) /\ - (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) - } - Context #6: { conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and([q13[1] = q8_1 <-> conjure_aux3 = q13[2] | q13 <- [(3, 4), (4, 3); int(1..2)]]) /\ - (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - Context #7: { conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and([q13[1] = q8_1 <-> conjure_aux3 = q13[2] | q13 <- [(3, 4), (4, 3); int(1..2)]]) /\ - (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - Context #8: [{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and([q13[1] = q8_1 <-> conjure_aux3 = q13[2] | q13 <- [(3, 4), (4, 3); int(1..2)]]) /\ - (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]] - Context #9: and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and([q13[1] = q8_1 <-> conjure_aux3 = q13[2] | q13 <- [(3, 4), (4, 3); int(1..2)]]) /\ - (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - Context #10: [|x| = |conjure_aux1|, - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and([q13[1] = q8_1 <-> conjure_aux3 = q13[2] | q13 <- [(3, 4), (4, 3); int(1..2)]]) /\ - (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]); - int(1..2)] - Context #11: |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and([q13[1] = q8_1 <-> conjure_aux3 = q13[2] | q13 <- [(3, 4), (4, 3); int(1..2)]]) /\ - (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - Context #12: { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and([q13[1] = q8_1 <-> conjure_aux3 = q13[2] | q13 <- [(3, 4), (4, 3); int(1..2)]]) /\ - (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - Context #13: y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and([q13[1] = q8_1 <-> conjure_aux3 = q13[2] | q13 <- [(3, 4), (4, 3); int(1..2)]]) /\ - (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } -Picking the only option: Answer 1: matrix-comprehension-literal: Vertical rule for matrix-comprehension on matrix literal - flatten(1, - [[q13[1] = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (3, 4)], - [q13[1] = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (4, 3)]; - int(1..2)]) -storedChoice: -[q13[1] = q8_1 <-> conjure_aux3 = q13[2] | q13 <- [(3, 4), (4, 3); int(1..2)]] 3456861798216985162 -AnsweredRule {qHole_ = 3456861798216985162, qAscendants_ = fromList [-8808315865059383030,-8227483119145124211,-7793095449913038876,-5679502255425066053,-3572216896086163269,-3021143752573374113,-2561056581393168238,-842750970546105960,3371366859945964624,5522715912807809257,6264069036653869010,7196566142350255202,8156173651558168583], aRuleName_ = "matrix-comprehension-literal"} -LF: {"AnsweredRule":{"aRuleName_":"matrix-comprehension-literal","qAscendants_":[-8808315865059383030,-8227483119145124211,-7793095449913038876,-5679502255425066053,-3572216896086163269,-3021143752573374113,-2561056581393168238,-842750970546105960,3371366859945964624,5522715912807809257,6264069036653869010,7196566142350255202,8156173651558168583],"qHole_":3456861798216985162}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, - [[q13[1] = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (3, 4)], - [q13[1] = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (4, 3)]; - int(1..2)])) - /\ (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: q13[1] - Context #1: q13[1] = q8_1 - Context #2: q13[1] = q8_1 <-> conjure_aux3 = q13[2] - Context #3: [q13[1] = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (3, 4)] - Context #4: [[q13[1] = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (3, 4)], - [q13[1] = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (4, 3)]; - int(1..2)] - Context #5: flatten(1, - [[q13[1] = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (3, 4)], - [q13[1] = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (4, 3)]; - int(1..2)]) - Context #6: and(flatten(1, - [[q13[1] = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (3, 4)], - [q13[1] = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (4, 3)]; - int(1..2)])) - Context #7: [and(flatten(1, - [[q13[1] = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (3, 4)], - [q13[1] = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (4, 3)]; - int(1..2)])), - !or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1; - int(1..2)] - Context #8: and(flatten(1, - [[q13[1] = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (3, 4)], - [q13[1] = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (4, 3)]; - int(1..2)])) - /\ (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) - Context #9: { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, - [[q13[1] = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (3, 4)], - [q13[1] = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (4, 3)]; - int(1..2)])) - /\ (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) - } - Context #10: conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, - [[q13[1] = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (3, 4)], - [q13[1] = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (4, 3)]; - int(1..2)])) - /\ (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) - } - Context #11: { conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, - [[q13[1] = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (3, 4)], - [q13[1] = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (4, 3)]; - int(1..2)])) - /\ (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - Context #12: { conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, - [[q13[1] = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (3, 4)], - [q13[1] = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (4, 3)]; - int(1..2)])) - /\ (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - Context #13: [{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, - [[q13[1] = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (3, 4)], - [q13[1] = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (4, 3)]; - int(1..2)])) - /\ (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]] - Context #14: and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, - [[q13[1] = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (3, 4)], - [q13[1] = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (4, 3)]; - int(1..2)])) - /\ (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - Context #15: [|x| = |conjure_aux1|, - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, - [[q13[1] = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (3, 4)], - [q13[1] = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (4, 3)]; - int(1..2)])) - /\ (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]); - int(1..2)] - Context #16: |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, - [[q13[1] = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (3, 4)], - [q13[1] = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (4, 3)]; - int(1..2)])) - /\ (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - Context #17: { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, - [[q13[1] = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (3, 4)], - [q13[1] = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (4, 3)]; - int(1..2)])) - /\ (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - Context #18: y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, - [[q13[1] = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (3, 4)], - [q13[1] = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (4, 3)]; - int(1..2)])) - /\ (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } -Picking the only option: Answer 1: full-evaluate: Full evaluator - 3 -storedChoice: -q13[1] -1254902052079317740 -AnsweredRule {qHole_ = -1254902052079317740, qAscendants_ = fromList [-7844826506044189197,-6543998516580374433,-5468160839539146108,-4646329838907093569,-4421494240673914403,-4030269164244882685,-3696611495810109143,-3345198454859526376,-2923685885462842550,-2579765278873905792,-2489053689031557395,-2037117675633093401,-1199749775392010500,-1159821892128975232,-61377228416248265,964892601978301791,3910121320990104243,4511388692183383834], aRuleName_ = "full-evaluate"} -LF: {"AnsweredRule":{"aRuleName_":"full-evaluate","qAscendants_":[-7844826506044189197,-6543998516580374433,-5468160839539146108,-4646329838907093569,-4421494240673914403,-4030269164244882685,-3696611495810109143,-3345198454859526376,-2923685885462842550,-2579765278873905792,-2489053689031557395,-2037117675633093401,-1199749775392010500,-1159821892128975232,-61377228416248265,964892601978301791,3910121320990104243,4511388692183383834],"qHole_":-1254902052079317740}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, - [[3 = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (3, 4)], [q13[1] = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (4, 3)]; - int(1..2)])) - /\ (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: q13[2] - Context #1: conjure_aux3 = q13[2] - Context #2: 3 = q8_1 <-> conjure_aux3 = q13[2] - Context #3: [3 = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (3, 4)] - Context #4: [[3 = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (3, 4)], - [q13[1] = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (4, 3)]; - int(1..2)] - Context #5: flatten(1, - [[3 = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (3, 4)], [q13[1] = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (4, 3)]; - int(1..2)]) - Context #6: and(flatten(1, - [[3 = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (3, 4)], [q13[1] = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (4, 3)]; - int(1..2)])) - Context #7: [and(flatten(1, - [[3 = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (3, 4)], [q13[1] = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (4, 3)]; - int(1..2)])), - !or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1; - int(1..2)] - Context #8: and(flatten(1, - [[3 = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (3, 4)], [q13[1] = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (4, 3)]; - int(1..2)])) - /\ (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) - Context #9: { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, - [[3 = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (3, 4)], [q13[1] = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (4, 3)]; - int(1..2)])) - /\ (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) - } - Context #10: conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, - [[3 = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (3, 4)], [q13[1] = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (4, 3)]; - int(1..2)])) - /\ (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) - } - Context #11: { conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, - [[3 = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (3, 4)], [q13[1] = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (4, 3)]; - int(1..2)])) - /\ (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - Context #12: { conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, - [[3 = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (3, 4)], [q13[1] = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (4, 3)]; - int(1..2)])) - /\ (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - Context #13: [{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, - [[3 = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (3, 4)], [q13[1] = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (4, 3)]; - int(1..2)])) - /\ (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]] - Context #14: and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, - [[3 = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (3, 4)], - [q13[1] = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (4, 3)]; - int(1..2)])) - /\ (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - Context #15: [|x| = |conjure_aux1|, - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, - [[3 = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (3, 4)], - [q13[1] = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (4, 3)]; - int(1..2)])) - /\ (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]); - int(1..2)] - Context #16: |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, - [[3 = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (3, 4)], - [q13[1] = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (4, 3)]; - int(1..2)])) - /\ (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - Context #17: { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, - [[3 = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (3, 4)], - [q13[1] = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (4, 3)]; - int(1..2)])) - /\ (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - Context #18: y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, - [[3 = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (3, 4)], - [q13[1] = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (4, 3)]; - int(1..2)])) - /\ (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } -Picking the only option: Answer 1: full-evaluate: Full evaluator - 4 -storedChoice: -q13[2] -1254620565291325713 -AnsweredRule {qHole_ = -1254620565291325713, qAscendants_ = fromList [-8360775170969626109,-8218634654132870929,-7641638248746524641,-4934801957947094136,-4254522952928052133,-4092969587983186253,-3780104048260027650,-2622265047463603714,-848316662104045049,563172654367211215,1222024046659559696,4078666449752848978,4662787952378127984,5249190568318080416,5574891365015849631,7061285353711906011,7866305697050141526,9112935851435552216], aRuleName_ = "full-evaluate"} -LF: {"AnsweredRule":{"aRuleName_":"full-evaluate","qAscendants_":[-8360775170969626109,-8218634654132870929,-7641638248746524641,-4934801957947094136,-4254522952928052133,-4092969587983186253,-3780104048260027650,-2622265047463603714,-848316662104045049,563172654367211215,1222024046659559696,4078666449752848978,4662787952378127984,5249190568318080416,5574891365015849631,7061285353711906011,7866305697050141526,9112935851435552216],"qHole_":-1254620565291325713}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, - [[3 = q8_1 <-> conjure_aux3 = 4 | letting q13 be (3, 4)], [q13[1] = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (4, 3)]; - int(1..2)])) - /\ (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: q13[1] - Context #1: q13[1] = q8_1 - Context #2: q13[1] = q8_1 <-> conjure_aux3 = q13[2] - Context #3: [q13[1] = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (4, 3)] - Context #4: [[3 = q8_1 <-> conjure_aux3 = 4 | letting q13 be (3, 4)], - [q13[1] = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (4, 3)]; - int(1..2)] - Context #5: flatten(1, - [[3 = q8_1 <-> conjure_aux3 = 4 | letting q13 be (3, 4)], [q13[1] = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (4, 3)]; - int(1..2)]) - Context #6: and(flatten(1, - [[3 = q8_1 <-> conjure_aux3 = 4 | letting q13 be (3, 4)], [q13[1] = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (4, 3)]; - int(1..2)])) - Context #7: [and(flatten(1, - [[3 = q8_1 <-> conjure_aux3 = 4 | letting q13 be (3, 4)], [q13[1] = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (4, 3)]; - int(1..2)])), - !or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1; - int(1..2)] - Context #8: and(flatten(1, - [[3 = q8_1 <-> conjure_aux3 = 4 | letting q13 be (3, 4)], [q13[1] = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (4, 3)]; - int(1..2)])) - /\ (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) - Context #9: { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, - [[3 = q8_1 <-> conjure_aux3 = 4 | letting q13 be (3, 4)], [q13[1] = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (4, 3)]; - int(1..2)])) - /\ (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) - } - Context #10: conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, - [[3 = q8_1 <-> conjure_aux3 = 4 | letting q13 be (3, 4)], [q13[1] = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (4, 3)]; - int(1..2)])) - /\ (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) - } - Context #11: { conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, - [[3 = q8_1 <-> conjure_aux3 = 4 | letting q13 be (3, 4)], [q13[1] = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (4, 3)]; - int(1..2)])) - /\ (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - Context #12: { conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, - [[3 = q8_1 <-> conjure_aux3 = 4 | letting q13 be (3, 4)], [q13[1] = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (4, 3)]; - int(1..2)])) - /\ (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - Context #13: [{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, - [[3 = q8_1 <-> conjure_aux3 = 4 | letting q13 be (3, 4)], [q13[1] = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (4, 3)]; - int(1..2)])) - /\ (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]] - Context #14: and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, - [[3 = q8_1 <-> conjure_aux3 = 4 | letting q13 be (3, 4)], [q13[1] = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (4, 3)]; - int(1..2)])) - /\ (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - Context #15: [|x| = |conjure_aux1|, - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, - [[3 = q8_1 <-> conjure_aux3 = 4 | letting q13 be (3, 4)], [q13[1] = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (4, 3)]; - int(1..2)])) - /\ (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]); - int(1..2)] - Context #16: |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, - [[3 = q8_1 <-> conjure_aux3 = 4 | letting q13 be (3, 4)], [q13[1] = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (4, 3)]; - int(1..2)])) - /\ (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - Context #17: { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, - [[3 = q8_1 <-> conjure_aux3 = 4 | letting q13 be (3, 4)], - [q13[1] = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (4, 3)]; - int(1..2)])) - /\ (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - Context #18: y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, - [[3 = q8_1 <-> conjure_aux3 = 4 | letting q13 be (3, 4)], - [q13[1] = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (4, 3)]; - int(1..2)])) - /\ (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } -Picking the only option: Answer 1: full-evaluate: Full evaluator - 4 -storedChoice: -q13[1] -1254902052079317740 -AnsweredRule {qHole_ = -1254902052079317740, qAscendants_ = fromList [-8638629789947627417,-7681680422406975063,-7045052392114671596,-5468160839539146108,-5360000098558189830,-5130716656066417701,-3536433963763386607,-3341254942655847808,-1332675206370029612,-61377228416248265,518672155518189655,1368815305078223764,1506712726218393853,2813413964084179331,4256368997522955231,6094767248156078778,6822727452915095676,7566490689068664978], aRuleName_ = "full-evaluate"} -LF: {"AnsweredRule":{"aRuleName_":"full-evaluate","qAscendants_":[-8638629789947627417,-7681680422406975063,-7045052392114671596,-5468160839539146108,-5360000098558189830,-5130716656066417701,-3536433963763386607,-3341254942655847808,-1332675206370029612,-61377228416248265,518672155518189655,1368815305078223764,1506712726218393853,2813413964084179331,4256368997522955231,6094767248156078778,6822727452915095676,7566490689068664978],"qHole_":-1254902052079317740}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, - [[3 = q8_1 <-> conjure_aux3 = 4 | letting q13 be (3, 4)], [4 = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (4, 3)]; int(1..2)])) - /\ (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: q13[2] - Context #1: conjure_aux3 = q13[2] - Context #2: 4 = q8_1 <-> conjure_aux3 = q13[2] - Context #3: [4 = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (4, 3)] - Context #4: [[3 = q8_1 <-> conjure_aux3 = 4 | letting q13 be (3, 4)], [4 = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (4, 3)]; - int(1..2)] - Context #5: flatten(1, - [[3 = q8_1 <-> conjure_aux3 = 4 | letting q13 be (3, 4)], [4 = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (4, 3)]; int(1..2)]) - Context #6: and(flatten(1, - [[3 = q8_1 <-> conjure_aux3 = 4 | letting q13 be (3, 4)], [4 = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (4, 3)]; int(1..2)])) - Context #7: [and(flatten(1, - [[3 = q8_1 <-> conjure_aux3 = 4 | letting q13 be (3, 4)], [4 = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (4, 3)]; int(1..2)])), - !or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1; - int(1..2)] - Context #8: and(flatten(1, - [[3 = q8_1 <-> conjure_aux3 = 4 | letting q13 be (3, 4)], [4 = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (4, 3)]; int(1..2)])) - /\ (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) - Context #9: { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, - [[3 = q8_1 <-> conjure_aux3 = 4 | letting q13 be (3, 4)], [4 = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (4, 3)]; int(1..2)])) - /\ (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) - } - Context #10: conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, - [[3 = q8_1 <-> conjure_aux3 = 4 | letting q13 be (3, 4)], [4 = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (4, 3)]; int(1..2)])) - /\ (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) - } - Context #11: { conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, - [[3 = q8_1 <-> conjure_aux3 = 4 | letting q13 be (3, 4)], [4 = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (4, 3)]; int(1..2)])) - /\ (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - Context #12: { conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, - [[3 = q8_1 <-> conjure_aux3 = 4 | letting q13 be (3, 4)], [4 = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (4, 3)]; int(1..2)])) - /\ (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - Context #13: [{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, - [[3 = q8_1 <-> conjure_aux3 = 4 | letting q13 be (3, 4)], [4 = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (4, 3)]; int(1..2)])) - /\ (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]] - Context #14: and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, - [[3 = q8_1 <-> conjure_aux3 = 4 | letting q13 be (3, 4)], [4 = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (4, 3)]; - int(1..2)])) - /\ (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - Context #15: [|x| = |conjure_aux1|, - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, - [[3 = q8_1 <-> conjure_aux3 = 4 | letting q13 be (3, 4)], [4 = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (4, 3)]; - int(1..2)])) - /\ (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]); - int(1..2)] - Context #16: |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, - [[3 = q8_1 <-> conjure_aux3 = 4 | letting q13 be (3, 4)], [4 = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (4, 3)]; - int(1..2)])) - /\ (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - Context #17: { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, - [[3 = q8_1 <-> conjure_aux3 = 4 | letting q13 be (3, 4)], [4 = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (4, 3)]; - int(1..2)])) - /\ (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - Context #18: y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, - [[3 = q8_1 <-> conjure_aux3 = 4 | letting q13 be (3, 4)], [4 = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (4, 3)]; - int(1..2)])) - /\ (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } -Picking the only option: Answer 1: full-evaluate: Full evaluator - 3 -storedChoice: -q13[2] -1254620565291325713 -AnsweredRule {qHole_ = -1254620565291325713, qAscendants_ = fromList [-8870698451967212431,-8218634654132870929,-8157916199347819983,-6958532007910279584,-4735583185965836928,-3733766703817256233,-1365219118307736560,-1326414908464043218,-756643065960997164,-238771092705033653,525451447959791552,2934402913780861128,4090216973995379955,4246953395184334158,4325482688218662469,4385767247150328058,4926105801959606859,4926669858781506740], aRuleName_ = "full-evaluate"} -LF: {"AnsweredRule":{"aRuleName_":"full-evaluate","qAscendants_":[-8870698451967212431,-8218634654132870929,-8157916199347819983,-6958532007910279584,-4735583185965836928,-3733766703817256233,-1365219118307736560,-1326414908464043218,-756643065960997164,-238771092705033653,525451447959791552,2934402913780861128,4090216973995379955,4246953395184334158,4325482688218662469,4385767247150328058,4926105801959606859,4926669858781506740],"qHole_":-1254620565291325713}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, - [[3 = q8_1 <-> conjure_aux3 = 4 | letting q13 be (3, 4)], [4 = q8_1 <-> conjure_aux3 = 3 | letting q13 be (4, 3)]; int(1..2)])) - /\ (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: [4 = q8_1 <-> conjure_aux3 = 3 | letting q13 be (4, 3)] - Context #1: [[3 = q8_1 <-> conjure_aux3 = 4 | letting q13 be (3, 4)], [4 = q8_1 <-> conjure_aux3 = 3 | letting q13 be (4, 3)]; - int(1..2)] - Context #2: flatten(1, - [[3 = q8_1 <-> conjure_aux3 = 4 | letting q13 be (3, 4)], [4 = q8_1 <-> conjure_aux3 = 3 | letting q13 be (4, 3)]; int(1..2)]) - Context #3: and(flatten(1, - [[3 = q8_1 <-> conjure_aux3 = 4 | letting q13 be (3, 4)], [4 = q8_1 <-> conjure_aux3 = 3 | letting q13 be (4, 3)]; int(1..2)])) - Context #4: [and(flatten(1, - [[3 = q8_1 <-> conjure_aux3 = 4 | letting q13 be (3, 4)], [4 = q8_1 <-> conjure_aux3 = 3 | letting q13 be (4, 3)]; int(1..2)])), - !or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1; - int(1..2)] - Context #5: and(flatten(1, - [[3 = q8_1 <-> conjure_aux3 = 4 | letting q13 be (3, 4)], [4 = q8_1 <-> conjure_aux3 = 3 | letting q13 be (4, 3)]; int(1..2)])) - /\ (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) - Context #6: { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, - [[3 = q8_1 <-> conjure_aux3 = 4 | letting q13 be (3, 4)], [4 = q8_1 <-> conjure_aux3 = 3 | letting q13 be (4, 3)]; int(1..2)])) - /\ (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) - } - Context #7: conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, - [[3 = q8_1 <-> conjure_aux3 = 4 | letting q13 be (3, 4)], [4 = q8_1 <-> conjure_aux3 = 3 | letting q13 be (4, 3)]; int(1..2)])) - /\ (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) - } - Context #8: { conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, - [[3 = q8_1 <-> conjure_aux3 = 4 | letting q13 be (3, 4)], [4 = q8_1 <-> conjure_aux3 = 3 | letting q13 be (4, 3)]; int(1..2)])) - /\ (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - Context #9: { conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, - [[3 = q8_1 <-> conjure_aux3 = 4 | letting q13 be (3, 4)], [4 = q8_1 <-> conjure_aux3 = 3 | letting q13 be (4, 3)]; int(1..2)])) - /\ (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - Context #10: [{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, - [[3 = q8_1 <-> conjure_aux3 = 4 | letting q13 be (3, 4)], [4 = q8_1 <-> conjure_aux3 = 3 | letting q13 be (4, 3)]; int(1..2)])) - /\ (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]] - Context #11: and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, - [[3 = q8_1 <-> conjure_aux3 = 4 | letting q13 be (3, 4)], [4 = q8_1 <-> conjure_aux3 = 3 | letting q13 be (4, 3)]; int(1..2)])) - /\ (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - Context #12: [|x| = |conjure_aux1|, - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, - [[3 = q8_1 <-> conjure_aux3 = 4 | letting q13 be (3, 4)], [4 = q8_1 <-> conjure_aux3 = 3 | letting q13 be (4, 3)]; int(1..2)])) - /\ (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]); - int(1..2)] - Context #13: |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, - [[3 = q8_1 <-> conjure_aux3 = 4 | letting q13 be (3, 4)], [4 = q8_1 <-> conjure_aux3 = 3 | letting q13 be (4, 3)]; int(1..2)])) - /\ (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - Context #14: { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, - [[3 = q8_1 <-> conjure_aux3 = 4 | letting q13 be (3, 4)], [4 = q8_1 <-> conjure_aux3 = 3 | letting q13 be (4, 3)]; - int(1..2)])) - /\ (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - Context #15: y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, - [[3 = q8_1 <-> conjure_aux3 = 4 | letting q13 be (3, 4)], [4 = q8_1 <-> conjure_aux3 = 3 | letting q13 be (4, 3)]; - int(1..2)])) - /\ (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } -Picking the only option: Answer 1: generators-first: Inlining comprehension lettings. - [4 = q8_1 <-> conjure_aux3 = 3 |] -storedChoice: -[4 = q8_1 <-> conjure_aux3 = 3 | letting q13 be (4, 3)] 7815870421468516721 -AnsweredRule {qHole_ = 7815870421468516721, qAscendants_ = fromList [-7319924227898755161,-6204074559855855953,-5721547888581640964,-4667135429861035401,-3119038628659086386,-2914873009721382719,-275708737112837829,358797451837378,588328580564008008,1171576539747863800,3860402082075414220,5255108035061878259,7534557817041195235,8046872103256922185,9076826399099772257], aRuleName_ = "generators-first"} -LF: {"AnsweredRule":{"aRuleName_":"generators-first","qAscendants_":[-7319924227898755161,-6204074559855855953,-5721547888581640964,-4667135429861035401,-3119038628659086386,-2914873009721382719,-275708737112837829,358797451837378,588328580564008008,1171576539747863800,3860402082075414220,5255108035061878259,7534557817041195235,8046872103256922185,9076826399099772257],"qHole_":7815870421468516721}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4 | letting q13 be (3, 4)], [4 = q8_1 <-> conjure_aux3 = 3 |]; int(1..2)])) /\ - (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: [4 = q8_1 <-> conjure_aux3 = 3 |] - Context #1: [[3 = q8_1 <-> conjure_aux3 = 4 | letting q13 be (3, 4)], [4 = q8_1 <-> conjure_aux3 = 3 |]; int(1..2)] - Context #2: flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4 | letting q13 be (3, 4)], [4 = q8_1 <-> conjure_aux3 = 3 |]; int(1..2)]) - Context #3: and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4 | letting q13 be (3, 4)], [4 = q8_1 <-> conjure_aux3 = 3 |]; int(1..2)])) - Context #4: [and(flatten(1, - [[3 = q8_1 <-> conjure_aux3 = 4 | letting q13 be (3, 4)], [4 = q8_1 <-> conjure_aux3 = 3 |]; int(1..2)])), - !or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1; - int(1..2)] - Context #5: and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4 | letting q13 be (3, 4)], [4 = q8_1 <-> conjure_aux3 = 3 |]; int(1..2)])) - /\ (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) - Context #6: { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4 | letting q13 be (3, 4)], [4 = q8_1 <-> conjure_aux3 = 3 |]; int(1..2)])) /\ - (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) - } - Context #7: conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4 | letting q13 be (3, 4)], [4 = q8_1 <-> conjure_aux3 = 3 |]; int(1..2)])) /\ - (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) - } - Context #8: { conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4 | letting q13 be (3, 4)], [4 = q8_1 <-> conjure_aux3 = 3 |]; int(1..2)])) /\ - (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - Context #9: { conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4 | letting q13 be (3, 4)], [4 = q8_1 <-> conjure_aux3 = 3 |]; int(1..2)])) /\ - (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - Context #10: [{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4 | letting q13 be (3, 4)], [4 = q8_1 <-> conjure_aux3 = 3 |]; int(1..2)])) /\ - (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]] - Context #11: and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4 | letting q13 be (3, 4)], [4 = q8_1 <-> conjure_aux3 = 3 |]; int(1..2)])) /\ - (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - Context #12: [|x| = |conjure_aux1|, - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4 | letting q13 be (3, 4)], [4 = q8_1 <-> conjure_aux3 = 3 |]; int(1..2)])) /\ - (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]); - int(1..2)] - Context #13: |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4 | letting q13 be (3, 4)], [4 = q8_1 <-> conjure_aux3 = 3 |]; int(1..2)])) /\ - (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - Context #14: { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4 | letting q13 be (3, 4)], [4 = q8_1 <-> conjure_aux3 = 3 |]; int(1..2)])) /\ - (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - Context #15: y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4 | letting q13 be (3, 4)], [4 = q8_1 <-> conjure_aux3 = 3 |]; int(1..2)])) /\ - (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } -Picking the only option: Answer 1: generators-first: Empty generators. - [4 = q8_1 <-> conjure_aux3 = 3; int(1)] -storedChoice: -[4 = q8_1 <-> conjure_aux3 = 3 |] 2538271587388693524 -AnsweredRule {qHole_ = 2538271587388693524, qAscendants_ = fromList [-8521000068701228812,-8466935177678778299,-8378067175040646304,-7795155064905057512,-7398425908569645990,-5020343327513684658,-1331085484917687815,-382563719840663416,1239306329275872739,3167048961433864186,4591749041469508459,5482352134908236922,5648481728193344963,6702522234416193183,8765316459520566910], aRuleName_ = "generators-first"} -LF: {"AnsweredRule":{"aRuleName_":"generators-first","qAscendants_":[-8521000068701228812,-8466935177678778299,-8378067175040646304,-7795155064905057512,-7398425908569645990,-5020343327513684658,-1331085484917687815,-382563719840663416,1239306329275872739,3167048961433864186,4591749041469508459,5482352134908236922,5648481728193344963,6702522234416193183,8765316459520566910],"qHole_":2538271587388693524}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4 | letting q13 be (3, 4)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: [3 = q8_1 <-> conjure_aux3 = 4 | letting q13 be (3, 4)] - Context #1: [[3 = q8_1 <-> conjure_aux3 = 4 | letting q13 be (3, 4)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)] - Context #2: flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4 | letting q13 be (3, 4)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)]) - Context #3: and(flatten(1, - [[3 = q8_1 <-> conjure_aux3 = 4 | letting q13 be (3, 4)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) - Context #4: [and(flatten(1, - [[3 = q8_1 <-> conjure_aux3 = 4 | letting q13 be (3, 4)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])), - !or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1; - int(1..2)] - Context #5: and(flatten(1, - [[3 = q8_1 <-> conjure_aux3 = 4 | letting q13 be (3, 4)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) - /\ (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) - Context #6: { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4 | letting q13 be (3, 4)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) - } - Context #7: conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4 | letting q13 be (3, 4)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) - } - Context #8: { conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4 | letting q13 be (3, 4)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - Context #9: { conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4 | letting q13 be (3, 4)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - Context #10: [{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4 | letting q13 be (3, 4)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]] - Context #11: and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4 | letting q13 be (3, 4)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - Context #12: [|x| = |conjure_aux1|, - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4 | letting q13 be (3, 4)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]); - int(1..2)] - Context #13: |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4 | letting q13 be (3, 4)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - Context #14: { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4 | letting q13 be (3, 4)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - Context #15: y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4 | letting q13 be (3, 4)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } -Picking the only option: Answer 1: generators-first: Inlining comprehension lettings. - [3 = q8_1 <-> conjure_aux3 = 4 |] -storedChoice: -[3 = q8_1 <-> conjure_aux3 = 4 | letting q13 be (3, 4)] 1317873634227795931 -AnsweredRule {qHole_ = 1317873634227795931, qAscendants_ = fromList [-6229747794032826968,-5833692553090476381,-4830840744837226265,-4695719515395703877,-1447797878088113254,-1026424407203100673,-114180086101386755,1230900640119672810,2384858822123183656,2641682090906853361,4932647657883680462,5503876696275907482,5561643139389034608,8062918047402720448,8618709991360516938], aRuleName_ = "generators-first"} -LF: {"AnsweredRule":{"aRuleName_":"generators-first","qAscendants_":[-6229747794032826968,-5833692553090476381,-4830840744837226265,-4695719515395703877,-1447797878088113254,-1026424407203100673,-114180086101386755,1230900640119672810,2384858822123183656,2641682090906853361,4932647657883680462,5503876696275907482,5561643139389034608,8062918047402720448,8618709991360516938],"qHole_":1317873634227795931}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4 |], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: [3 = q8_1 <-> conjure_aux3 = 4 |] - Context #1: [[3 = q8_1 <-> conjure_aux3 = 4 |], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)] - Context #2: flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4 |], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)]) - Context #3: and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4 |], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) - Context #4: [and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4 |], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])), - !or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1; - int(1..2)] - Context #5: and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4 |], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) - Context #6: { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4 |], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) - } - Context #7: conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4 |], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) - } - Context #8: { conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4 |], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - Context #9: { conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4 |], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - Context #10: [{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4 |], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]] - Context #11: and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4 |], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - Context #12: [|x| = |conjure_aux1|, - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4 |], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]); - int(1..2)] - Context #13: |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4 |], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - Context #14: { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4 |], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - Context #15: y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4 |], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } -Picking the only option: Answer 1: generators-first: Empty generators. - [3 = q8_1 <-> conjure_aux3 = 4; int(1)] -storedChoice: -[3 = q8_1 <-> conjure_aux3 = 4 |] 7527005283398106432 -AnsweredRule {qHole_ = 7527005283398106432, qAscendants_ = fromList [-5151808191572404398,-4353286235323785771,-4339955062448219396,-4142041909263092979,-3736320932349712947,-3440388200198466301,-2029225889893250969,-1817262023712192284,-116834249900757749,483550512093615086,1497957860809309721,2283573903554163553,3854374349353612498,7382215623493355130,8339321953980948829], aRuleName_ = "generators-first"} -LF: {"AnsweredRule":{"aRuleName_":"generators-first","qAscendants_":[-5151808191572404398,-4353286235323785771,-4339955062448219396,-4142041909263092979,-3736320932349712947,-3440388200198466301,-2029225889893250969,-1817262023712192284,-116834249900757749,483550512093615086,1497957860809309721,2283573903554163553,3854374349353612498,7382215623493355130,8339321953980948829],"qHole_":7527005283398106432}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: [(3, 4), (4, 3); int(1..2)] - Context #1: [q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]] - Context #2: or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) - Context #3: !or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) - Context #4: !or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1 - Context #5: [and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])), - !or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1; - int(1..2)] - Context #6: and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) - Context #7: { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) - } - Context #8: conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) - } - Context #9: { conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - Context #10: { conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - Context #11: [{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]] - Context #12: and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - Context #13: [|x| = |conjure_aux1|, - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]); - int(1..2)] - Context #14: |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - Context #15: { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - Context #16: y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } -Picking the only option: Answer 1: full-evaluate: Full evaluator - [(3, 4), (4, 3); int(1..2)] -storedChoice: -[(3, 4), (4, 3); int(1..2)] 6597397470067790033 -AnsweredRule {qHole_ = 6597397470067790033, qAscendants_ = fromList [-9213624152780173787,-5982135693274236766,-5396430067534345835,-2363572399258163690,-2255081376624876153,-320252043164433323,1280603170430058832,2648872121679578871,4076507060053755550,5033554600497872881,6390584767367481427,6475772422542545541,6480002864764397731,6871118355510909196,7049518756068236715,8591929121087659168], aRuleName_ = "full-evaluate"} -LF: {"AnsweredRule":{"aRuleName_":"full-evaluate","qAscendants_":[-9213624152780173787,-5982135693274236766,-5396430067534345835,-2363572399258163690,-2255081376624876153,-320252043164433323,1280603170430058832,2648872121679578871,4076507060053755550,5033554600497872881,6390584767367481427,6475772422542545541,6480002864764397731,6871118355510909196,7049518756068236715,8591929121087659168],"qHole_":6597397470067790033}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: [q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]] - Context #1: or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) - Context #2: !or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) - Context #3: !or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1 - Context #4: [and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])), - !or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1; - int(1..2)] - Context #5: and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) - Context #6: { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) - } - Context #7: conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) - } - Context #8: { conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - Context #9: { conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - Context #10: [{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]] - Context #11: and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - Context #12: [|x| = |conjure_aux1|, - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]); - int(1..2)] - Context #13: |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - Context #14: { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - Context #15: y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } -Picking the only option: Answer 1: complex-pattern: complex pattern on tuple patterns - [q14[1] = conjure_aux3 | q14 <- [(3, 4), (4, 3); int(1..2)]] -storedChoice: -[q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]] 5033554600497872881 -AnsweredRule {qHole_ = 5033554600497872881, qAscendants_ = fromList [-9213624152780173787,-5982135693274236766,-5396430067534345835,-2363572399258163690,-2255081376624876153,-320252043164433323,1280603170430058832,2648872121679578871,4076507060053755550,6390584767367481427,6475772422542545541,6480002864764397731,6871118355510909196,7049518756068236715,8591929121087659168], aRuleName_ = "complex-pattern"} -LF: {"AnsweredRule":{"aRuleName_":"complex-pattern","qAscendants_":[-9213624152780173787,-5982135693274236766,-5396430067534345835,-2363572399258163690,-2255081376624876153,-320252043164433323,1280603170430058832,2648872121679578871,4076507060053755550,6390584767367481427,6475772422542545541,6480002864764397731,6871118355510909196,7049518756068236715,8591929121087659168],"qHole_":5033554600497872881}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!or([q14[1] = conjure_aux3 | q14 <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: [q14[1] = conjure_aux3 | q14 <- [(3, 4), (4, 3); int(1..2)]] - Context #1: or([q14[1] = conjure_aux3 | q14 <- [(3, 4), (4, 3); int(1..2)]]) - Context #2: !or([q14[1] = conjure_aux3 | q14 <- [(3, 4), (4, 3); int(1..2)]]) - Context #3: !or([q14[1] = conjure_aux3 | q14 <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1 - Context #4: [and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])), - !or([q14[1] = conjure_aux3 | q14 <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1; - int(1..2)] - Context #5: and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!or([q14[1] = conjure_aux3 | q14 <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) - Context #6: { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!or([q14[1] = conjure_aux3 | q14 <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) - } - Context #7: conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!or([q14[1] = conjure_aux3 | q14 <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) - } - Context #8: { conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!or([q14[1] = conjure_aux3 | q14 <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - Context #9: { conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!or([q14[1] = conjure_aux3 | q14 <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - Context #10: [{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!or([q14[1] = conjure_aux3 | q14 <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]] - Context #11: and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!or([q14[1] = conjure_aux3 | q14 <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - Context #12: [|x| = |conjure_aux1|, - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!or([q14[1] = conjure_aux3 | q14 <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]); - int(1..2)] - Context #13: |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!or([q14[1] = conjure_aux3 | q14 <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - Context #14: { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!or([q14[1] = conjure_aux3 | q14 <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - Context #15: y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!or([q14[1] = conjure_aux3 | q14 <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } -Picking the only option: Answer 1: matrix-comprehension-literal: Vertical rule for matrix-comprehension on matrix literal - flatten(1, [[q14[1] = conjure_aux3 | letting q14 be (3, 4)], [q14[1] = conjure_aux3 | letting q14 be (4, 3)]; int(1..2)]) -storedChoice: -[q14[1] = conjure_aux3 | q14 <- [(3, 4), (4, 3); int(1..2)]] 8665374887955696009 -AnsweredRule {qHole_ = 8665374887955696009, qAscendants_ = fromList [-8790838049079552472,-7586671731712078955,-7257845330645731074,-6187411109644722069,-5035649525051787097,-4935714982215491801,-4790057621145645718,-2980197002499358476,-1690854938850194471,-619668906698634467,1003810935162304708,3378856114517929630,5359983985600686059,5489110086534554143,8428096257079881520], aRuleName_ = "matrix-comprehension-literal"} -LF: {"AnsweredRule":{"aRuleName_":"matrix-comprehension-literal","qAscendants_":[-8790838049079552472,-7586671731712078955,-7257845330645731074,-6187411109644722069,-5035649525051787097,-4935714982215491801,-4790057621145645718,-2980197002499358476,-1690854938850194471,-619668906698634467,1003810935162304708,3378856114517929630,5359983985600686059,5489110086534554143,8428096257079881520],"qHole_":8665374887955696009}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!or(flatten(1, [[q14[1] = conjure_aux3 | letting q14 be (3, 4)], [q14[1] = conjure_aux3 | letting q14 be (4, 3)]; int(1..2)])) <-> - conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: q14[1] - Context #1: q14[1] = conjure_aux3 - Context #2: [q14[1] = conjure_aux3 | letting q14 be (3, 4)] - Context #3: [[q14[1] = conjure_aux3 | letting q14 be (3, 4)], [q14[1] = conjure_aux3 | letting q14 be (4, 3)]; int(1..2)] - Context #4: flatten(1, [[q14[1] = conjure_aux3 | letting q14 be (3, 4)], [q14[1] = conjure_aux3 | letting q14 be (4, 3)]; int(1..2)]) - Context #5: or(flatten(1, - [[q14[1] = conjure_aux3 | letting q14 be (3, 4)], [q14[1] = conjure_aux3 | letting q14 be (4, 3)]; int(1..2)])) - Context #6: !or(flatten(1, - [[q14[1] = conjure_aux3 | letting q14 be (3, 4)], [q14[1] = conjure_aux3 | letting q14 be (4, 3)]; int(1..2)])) - Context #7: !or(flatten(1, - [[q14[1] = conjure_aux3 | letting q14 be (3, 4)], [q14[1] = conjure_aux3 | letting q14 be (4, 3)]; int(1..2)])) - <-> conjure_aux3 = q8_1 - Context #8: [and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])), - !or(flatten(1, [[q14[1] = conjure_aux3 | letting q14 be (3, 4)], [q14[1] = conjure_aux3 | letting q14 be (4, 3)]; int(1..2)])) <-> - conjure_aux3 = q8_1; - int(1..2)] - Context #9: and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!or(flatten(1, [[q14[1] = conjure_aux3 | letting q14 be (3, 4)], [q14[1] = conjure_aux3 | letting q14 be (4, 3)]; int(1..2)])) <-> - conjure_aux3 = q8_1) - Context #10: { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!or(flatten(1, [[q14[1] = conjure_aux3 | letting q14 be (3, 4)], [q14[1] = conjure_aux3 | letting q14 be (4, 3)]; int(1..2)])) <-> - conjure_aux3 = q8_1) - } - Context #11: conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!or(flatten(1, [[q14[1] = conjure_aux3 | letting q14 be (3, 4)], [q14[1] = conjure_aux3 | letting q14 be (4, 3)]; int(1..2)])) <-> - conjure_aux3 = q8_1) - } - Context #12: { conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!or(flatten(1, [[q14[1] = conjure_aux3 | letting q14 be (3, 4)], [q14[1] = conjure_aux3 | letting q14 be (4, 3)]; int(1..2)])) <-> - conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - Context #13: { conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!or(flatten(1, [[q14[1] = conjure_aux3 | letting q14 be (3, 4)], [q14[1] = conjure_aux3 | letting q14 be (4, 3)]; int(1..2)])) <-> - conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - Context #14: [{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!or(flatten(1, [[q14[1] = conjure_aux3 | letting q14 be (3, 4)], [q14[1] = conjure_aux3 | letting q14 be (4, 3)]; int(1..2)])) <-> - conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]] - Context #15: and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!or(flatten(1, [[q14[1] = conjure_aux3 | letting q14 be (3, 4)], [q14[1] = conjure_aux3 | letting q14 be (4, 3)]; int(1..2)])) <-> - conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - Context #16: [|x| = |conjure_aux1|, - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!or(flatten(1, [[q14[1] = conjure_aux3 | letting q14 be (3, 4)], [q14[1] = conjure_aux3 | letting q14 be (4, 3)]; int(1..2)])) <-> - conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]); - int(1..2)] - Context #17: |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!or(flatten(1, [[q14[1] = conjure_aux3 | letting q14 be (3, 4)], [q14[1] = conjure_aux3 | letting q14 be (4, 3)]; int(1..2)])) <-> - conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - Context #18: { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!or(flatten(1, [[q14[1] = conjure_aux3 | letting q14 be (3, 4)], [q14[1] = conjure_aux3 | letting q14 be (4, 3)]; int(1..2)])) <-> - conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - Context #19: y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!or(flatten(1, [[q14[1] = conjure_aux3 | letting q14 be (3, 4)], [q14[1] = conjure_aux3 | letting q14 be (4, 3)]; int(1..2)])) <-> - conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } -Picking the only option: Answer 1: full-evaluate: Full evaluator - 3 -storedChoice: -q14[1] -883253742927518753 -AnsweredRule {qHole_ = -883253742927518753, qAscendants_ = fromList [-9176123018977089417,-9101977553270866225,-9093406545418508012,-9026590884990837132,-7266038392684934735,-7030617368587845027,-6315177474832767189,-6185538668149951971,-5045957588695750237,-2422194591007956529,-2140558072442299093,-1323860184563866252,370104820105510026,1657237947942821584,1725179241386393490,3615940558330371386,6441285251735452902,7836445554474639282,8733492850970682893], aRuleName_ = "full-evaluate"} -LF: {"AnsweredRule":{"aRuleName_":"full-evaluate","qAscendants_":[-9176123018977089417,-9101977553270866225,-9093406545418508012,-9026590884990837132,-7266038392684934735,-7030617368587845027,-6315177474832767189,-6185538668149951971,-5045957588695750237,-2422194591007956529,-2140558072442299093,-1323860184563866252,370104820105510026,1657237947942821584,1725179241386393490,3615940558330371386,6441285251735452902,7836445554474639282,8733492850970682893],"qHole_":-883253742927518753}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!or(flatten(1, [[3 = conjure_aux3 | letting q14 be (3, 4)], [q14[1] = conjure_aux3 | letting q14 be (4, 3)]; int(1..2)])) <-> - conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: q14[1] - Context #1: q14[1] = conjure_aux3 - Context #2: [q14[1] = conjure_aux3 | letting q14 be (4, 3)] - Context #3: [[3 = conjure_aux3 | letting q14 be (3, 4)], [q14[1] = conjure_aux3 | letting q14 be (4, 3)]; int(1..2)] - Context #4: flatten(1, [[3 = conjure_aux3 | letting q14 be (3, 4)], [q14[1] = conjure_aux3 | letting q14 be (4, 3)]; int(1..2)]) - Context #5: or(flatten(1, [[3 = conjure_aux3 | letting q14 be (3, 4)], [q14[1] = conjure_aux3 | letting q14 be (4, 3)]; int(1..2)])) - Context #6: !or(flatten(1, [[3 = conjure_aux3 | letting q14 be (3, 4)], [q14[1] = conjure_aux3 | letting q14 be (4, 3)]; int(1..2)])) - Context #7: !or(flatten(1, [[3 = conjure_aux3 | letting q14 be (3, 4)], [q14[1] = conjure_aux3 | letting q14 be (4, 3)]; int(1..2)])) - <-> conjure_aux3 = q8_1 - Context #8: [and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])), - !or(flatten(1, [[3 = conjure_aux3 | letting q14 be (3, 4)], [q14[1] = conjure_aux3 | letting q14 be (4, 3)]; int(1..2)])) <-> - conjure_aux3 = q8_1; - int(1..2)] - Context #9: and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!or(flatten(1, [[3 = conjure_aux3 | letting q14 be (3, 4)], [q14[1] = conjure_aux3 | letting q14 be (4, 3)]; int(1..2)])) <-> - conjure_aux3 = q8_1) - Context #10: { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!or(flatten(1, [[3 = conjure_aux3 | letting q14 be (3, 4)], [q14[1] = conjure_aux3 | letting q14 be (4, 3)]; int(1..2)])) <-> - conjure_aux3 = q8_1) - } - Context #11: conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!or(flatten(1, [[3 = conjure_aux3 | letting q14 be (3, 4)], [q14[1] = conjure_aux3 | letting q14 be (4, 3)]; int(1..2)])) <-> - conjure_aux3 = q8_1) - } - Context #12: { conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!or(flatten(1, [[3 = conjure_aux3 | letting q14 be (3, 4)], [q14[1] = conjure_aux3 | letting q14 be (4, 3)]; int(1..2)])) <-> - conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - Context #13: { conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!or(flatten(1, [[3 = conjure_aux3 | letting q14 be (3, 4)], [q14[1] = conjure_aux3 | letting q14 be (4, 3)]; int(1..2)])) <-> - conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - Context #14: [{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!or(flatten(1, [[3 = conjure_aux3 | letting q14 be (3, 4)], [q14[1] = conjure_aux3 | letting q14 be (4, 3)]; int(1..2)])) <-> - conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]] - Context #15: and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!or(flatten(1, [[3 = conjure_aux3 | letting q14 be (3, 4)], [q14[1] = conjure_aux3 | letting q14 be (4, 3)]; int(1..2)])) <-> - conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - Context #16: [|x| = |conjure_aux1|, - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!or(flatten(1, [[3 = conjure_aux3 | letting q14 be (3, 4)], [q14[1] = conjure_aux3 | letting q14 be (4, 3)]; int(1..2)])) <-> - conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]); - int(1..2)] - Context #17: |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!or(flatten(1, [[3 = conjure_aux3 | letting q14 be (3, 4)], [q14[1] = conjure_aux3 | letting q14 be (4, 3)]; int(1..2)])) <-> - conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - Context #18: { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!or(flatten(1, [[3 = conjure_aux3 | letting q14 be (3, 4)], [q14[1] = conjure_aux3 | letting q14 be (4, 3)]; int(1..2)])) <-> - conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - Context #19: y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!or(flatten(1, [[3 = conjure_aux3 | letting q14 be (3, 4)], [q14[1] = conjure_aux3 | letting q14 be (4, 3)]; int(1..2)])) <-> - conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } -Picking the only option: Answer 1: full-evaluate: Full evaluator - 4 -storedChoice: -q14[1] -883253742927518753 -AnsweredRule {qHole_ = -883253742927518753, qAscendants_ = fromList [-8969758503132111487,-6784916903301812310,-4362502606594339694,-2424885897194395863,-2417099766119933872,-661357570700780995,659540462714969701,741299023684531871,841316382876489834,1080971480076294633,2455636718555289611,4781036327687591913,6314971418857005121,6957705147325524125,7520484523970872436,7814781884486080266,8472710336593287104,8733492850970682893,9124601515932951508], aRuleName_ = "full-evaluate"} -LF: {"AnsweredRule":{"aRuleName_":"full-evaluate","qAscendants_":[-8969758503132111487,-6784916903301812310,-4362502606594339694,-2424885897194395863,-2417099766119933872,-661357570700780995,659540462714969701,741299023684531871,841316382876489834,1080971480076294633,2455636718555289611,4781036327687591913,6314971418857005121,6957705147325524125,7520484523970872436,7814781884486080266,8472710336593287104,8733492850970682893,9124601515932951508],"qHole_":-883253742927518753}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!or(flatten(1, [[3 = conjure_aux3 | letting q14 be (3, 4)], [4 = conjure_aux3 | letting q14 be (4, 3)]; int(1..2)])) <-> - conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: [4 = conjure_aux3 | letting q14 be (4, 3)] - Context #1: [[3 = conjure_aux3 | letting q14 be (3, 4)], [4 = conjure_aux3 | letting q14 be (4, 3)]; int(1..2)] - Context #2: flatten(1, [[3 = conjure_aux3 | letting q14 be (3, 4)], [4 = conjure_aux3 | letting q14 be (4, 3)]; int(1..2)]) - Context #3: or(flatten(1, [[3 = conjure_aux3 | letting q14 be (3, 4)], [4 = conjure_aux3 | letting q14 be (4, 3)]; int(1..2)])) - Context #4: !or(flatten(1, [[3 = conjure_aux3 | letting q14 be (3, 4)], [4 = conjure_aux3 | letting q14 be (4, 3)]; int(1..2)])) - Context #5: !or(flatten(1, [[3 = conjure_aux3 | letting q14 be (3, 4)], [4 = conjure_aux3 | letting q14 be (4, 3)]; int(1..2)])) <-> - conjure_aux3 = q8_1 - Context #6: [and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])), - !or(flatten(1, [[3 = conjure_aux3 | letting q14 be (3, 4)], [4 = conjure_aux3 | letting q14 be (4, 3)]; int(1..2)])) <-> - conjure_aux3 = q8_1; - int(1..2)] - Context #7: and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!or(flatten(1, [[3 = conjure_aux3 | letting q14 be (3, 4)], [4 = conjure_aux3 | letting q14 be (4, 3)]; int(1..2)])) <-> - conjure_aux3 = q8_1) - Context #8: { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!or(flatten(1, [[3 = conjure_aux3 | letting q14 be (3, 4)], [4 = conjure_aux3 | letting q14 be (4, 3)]; int(1..2)])) <-> - conjure_aux3 = q8_1) - } - Context #9: conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!or(flatten(1, [[3 = conjure_aux3 | letting q14 be (3, 4)], [4 = conjure_aux3 | letting q14 be (4, 3)]; int(1..2)])) <-> - conjure_aux3 = q8_1) - } - Context #10: { conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!or(flatten(1, [[3 = conjure_aux3 | letting q14 be (3, 4)], [4 = conjure_aux3 | letting q14 be (4, 3)]; int(1..2)])) <-> - conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - Context #11: { conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!or(flatten(1, [[3 = conjure_aux3 | letting q14 be (3, 4)], [4 = conjure_aux3 | letting q14 be (4, 3)]; int(1..2)])) <-> - conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - Context #12: [{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!or(flatten(1, [[3 = conjure_aux3 | letting q14 be (3, 4)], [4 = conjure_aux3 | letting q14 be (4, 3)]; int(1..2)])) <-> - conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]] - Context #13: and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!or(flatten(1, [[3 = conjure_aux3 | letting q14 be (3, 4)], [4 = conjure_aux3 | letting q14 be (4, 3)]; int(1..2)])) <-> - conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - Context #14: [|x| = |conjure_aux1|, - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!or(flatten(1, [[3 = conjure_aux3 | letting q14 be (3, 4)], [4 = conjure_aux3 | letting q14 be (4, 3)]; int(1..2)])) <-> - conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]); - int(1..2)] - Context #15: |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!or(flatten(1, [[3 = conjure_aux3 | letting q14 be (3, 4)], [4 = conjure_aux3 | letting q14 be (4, 3)]; int(1..2)])) <-> - conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - Context #16: { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!or(flatten(1, [[3 = conjure_aux3 | letting q14 be (3, 4)], [4 = conjure_aux3 | letting q14 be (4, 3)]; int(1..2)])) <-> - conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - Context #17: y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!or(flatten(1, [[3 = conjure_aux3 | letting q14 be (3, 4)], [4 = conjure_aux3 | letting q14 be (4, 3)]; int(1..2)])) <-> - conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } -Picking the only option: Answer 1: generators-first: Inlining comprehension lettings. - [4 = conjure_aux3 |] -storedChoice: -[4 = conjure_aux3 | letting q14 be (4, 3)] 5094133043100232579 -AnsweredRule {qHole_ = 5094133043100232579, qAscendants_ = fromList [-8909122354700020440,-7460733051808423716,-5113575940370069634,-3275789614875181527,-1485928817419295239,-1453326525258547920,-1190111094765899527,-425934852058965166,-227269000323710205,1017324948146570036,2402920626236815200,4379418785875775437,5239709721973149055,5447511985754467121,6138327529543829831,6983653976480365703,7190718169255452642], aRuleName_ = "generators-first"} -LF: {"AnsweredRule":{"aRuleName_":"generators-first","qAscendants_":[-8909122354700020440,-7460733051808423716,-5113575940370069634,-3275789614875181527,-1485928817419295239,-1453326525258547920,-1190111094765899527,-425934852058965166,-227269000323710205,1017324948146570036,2402920626236815200,4379418785875775437,5239709721973149055,5447511985754467121,6138327529543829831,6983653976480365703,7190718169255452642],"qHole_":5094133043100232579}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!or(flatten(1, [[3 = conjure_aux3 | letting q14 be (3, 4)], [4 = conjure_aux3 |]; int(1..2)])) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: [4 = conjure_aux3 |] - Context #1: [[3 = conjure_aux3 | letting q14 be (3, 4)], [4 = conjure_aux3 |]; int(1..2)] - Context #2: flatten(1, [[3 = conjure_aux3 | letting q14 be (3, 4)], [4 = conjure_aux3 |]; int(1..2)]) - Context #3: or(flatten(1, [[3 = conjure_aux3 | letting q14 be (3, 4)], [4 = conjure_aux3 |]; int(1..2)])) - Context #4: !or(flatten(1, [[3 = conjure_aux3 | letting q14 be (3, 4)], [4 = conjure_aux3 |]; int(1..2)])) - Context #5: !or(flatten(1, [[3 = conjure_aux3 | letting q14 be (3, 4)], [4 = conjure_aux3 |]; int(1..2)])) <-> conjure_aux3 = q8_1 - Context #6: [and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])), - !or(flatten(1, [[3 = conjure_aux3 | letting q14 be (3, 4)], [4 = conjure_aux3 |]; int(1..2)])) <-> conjure_aux3 = q8_1; - int(1..2)] - Context #7: and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!or(flatten(1, [[3 = conjure_aux3 | letting q14 be (3, 4)], [4 = conjure_aux3 |]; int(1..2)])) <-> conjure_aux3 = q8_1) - Context #8: { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!or(flatten(1, [[3 = conjure_aux3 | letting q14 be (3, 4)], [4 = conjure_aux3 |]; int(1..2)])) <-> conjure_aux3 = q8_1) - } - Context #9: conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!or(flatten(1, [[3 = conjure_aux3 | letting q14 be (3, 4)], [4 = conjure_aux3 |]; int(1..2)])) <-> conjure_aux3 = q8_1) - } - Context #10: { conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!or(flatten(1, [[3 = conjure_aux3 | letting q14 be (3, 4)], [4 = conjure_aux3 |]; int(1..2)])) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - Context #11: { conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!or(flatten(1, [[3 = conjure_aux3 | letting q14 be (3, 4)], [4 = conjure_aux3 |]; int(1..2)])) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - Context #12: [{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!or(flatten(1, [[3 = conjure_aux3 | letting q14 be (3, 4)], [4 = conjure_aux3 |]; int(1..2)])) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]] - Context #13: and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!or(flatten(1, [[3 = conjure_aux3 | letting q14 be (3, 4)], [4 = conjure_aux3 |]; int(1..2)])) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - Context #14: [|x| = |conjure_aux1|, - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!or(flatten(1, [[3 = conjure_aux3 | letting q14 be (3, 4)], [4 = conjure_aux3 |]; int(1..2)])) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]); - int(1..2)] - Context #15: |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!or(flatten(1, [[3 = conjure_aux3 | letting q14 be (3, 4)], [4 = conjure_aux3 |]; int(1..2)])) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - Context #16: { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!or(flatten(1, [[3 = conjure_aux3 | letting q14 be (3, 4)], [4 = conjure_aux3 |]; int(1..2)])) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - Context #17: y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!or(flatten(1, [[3 = conjure_aux3 | letting q14 be (3, 4)], [4 = conjure_aux3 |]; int(1..2)])) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } -Picking the only option: Answer 1: generators-first: Empty generators. - [4 = conjure_aux3; int(1)] -storedChoice: -[4 = conjure_aux3 |] 6112956542716486877 -AnsweredRule {qHole_ = 6112956542716486877, qAscendants_ = fromList [-9207305118438100391,-6369735332026353512,-5991924291783106431,-5776209435213632803,-3830978856990678993,-3641847297966420112,-338462998493300906,2767710529868660813,4005580531872772405,4397758740249101114,4804584669642102451,5890086814982925863,6459294084780550343,6686373777934096773,7031238571308724387,7962655793307038867,8888369891598567800], aRuleName_ = "generators-first"} -LF: {"AnsweredRule":{"aRuleName_":"generators-first","qAscendants_":[-9207305118438100391,-6369735332026353512,-5991924291783106431,-5776209435213632803,-3830978856990678993,-3641847297966420112,-338462998493300906,2767710529868660813,4005580531872772405,4397758740249101114,4804584669642102451,5890086814982925863,6459294084780550343,6686373777934096773,7031238571308724387,7962655793307038867,8888369891598567800],"qHole_":6112956542716486877}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!or(flatten(1, [[3 = conjure_aux3 | letting q14 be (3, 4)], [4 = conjure_aux3; int(1)]; int(1..2)])) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: [3 = conjure_aux3 | letting q14 be (3, 4)] - Context #1: [[3 = conjure_aux3 | letting q14 be (3, 4)], [4 = conjure_aux3; int(1)]; int(1..2)] - Context #2: flatten(1, [[3 = conjure_aux3 | letting q14 be (3, 4)], [4 = conjure_aux3; int(1)]; int(1..2)]) - Context #3: or(flatten(1, [[3 = conjure_aux3 | letting q14 be (3, 4)], [4 = conjure_aux3; int(1)]; int(1..2)])) - Context #4: !or(flatten(1, [[3 = conjure_aux3 | letting q14 be (3, 4)], [4 = conjure_aux3; int(1)]; int(1..2)])) - Context #5: !or(flatten(1, [[3 = conjure_aux3 | letting q14 be (3, 4)], [4 = conjure_aux3; int(1)]; int(1..2)])) <-> - conjure_aux3 = q8_1 - Context #6: [and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])), - !or(flatten(1, [[3 = conjure_aux3 | letting q14 be (3, 4)], [4 = conjure_aux3; int(1)]; int(1..2)])) <-> conjure_aux3 = q8_1; - int(1..2)] - Context #7: and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!or(flatten(1, [[3 = conjure_aux3 | letting q14 be (3, 4)], [4 = conjure_aux3; int(1)]; int(1..2)])) <-> conjure_aux3 = q8_1) - Context #8: { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!or(flatten(1, [[3 = conjure_aux3 | letting q14 be (3, 4)], [4 = conjure_aux3; int(1)]; int(1..2)])) <-> conjure_aux3 = q8_1) - } - Context #9: conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!or(flatten(1, [[3 = conjure_aux3 | letting q14 be (3, 4)], [4 = conjure_aux3; int(1)]; int(1..2)])) <-> conjure_aux3 = q8_1) - } - Context #10: { conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!or(flatten(1, [[3 = conjure_aux3 | letting q14 be (3, 4)], [4 = conjure_aux3; int(1)]; int(1..2)])) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - Context #11: { conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!or(flatten(1, [[3 = conjure_aux3 | letting q14 be (3, 4)], [4 = conjure_aux3; int(1)]; int(1..2)])) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - Context #12: [{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!or(flatten(1, [[3 = conjure_aux3 | letting q14 be (3, 4)], [4 = conjure_aux3; int(1)]; int(1..2)])) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]] - Context #13: and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!or(flatten(1, [[3 = conjure_aux3 | letting q14 be (3, 4)], [4 = conjure_aux3; int(1)]; int(1..2)])) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - Context #14: [|x| = |conjure_aux1|, - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!or(flatten(1, [[3 = conjure_aux3 | letting q14 be (3, 4)], [4 = conjure_aux3; int(1)]; int(1..2)])) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]); - int(1..2)] - Context #15: |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!or(flatten(1, [[3 = conjure_aux3 | letting q14 be (3, 4)], [4 = conjure_aux3; int(1)]; int(1..2)])) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - Context #16: { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!or(flatten(1, [[3 = conjure_aux3 | letting q14 be (3, 4)], [4 = conjure_aux3; int(1)]; int(1..2)])) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - Context #17: y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!or(flatten(1, [[3 = conjure_aux3 | letting q14 be (3, 4)], [4 = conjure_aux3; int(1)]; int(1..2)])) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } -Picking the only option: Answer 1: generators-first: Inlining comprehension lettings. - [3 = conjure_aux3 |] -storedChoice: -[3 = conjure_aux3 | letting q14 be (3, 4)] 4832497823804752928 -AnsweredRule {qHole_ = 4832497823804752928, qAscendants_ = fromList [-6677145406315480965,-5384732204964843677,-3071059650417301550,-2603160466482895011,-2221619722341004417,-1557091775694725768,-1403621344696630627,711266062685662619,1333581340284470498,1611305677733360901,2753561903646462793,3866947117330481491,5332477917871449756,5559142600358984796,6001232326845461178,7602738452352881434,8088691831228319750], aRuleName_ = "generators-first"} -LF: {"AnsweredRule":{"aRuleName_":"generators-first","qAscendants_":[-6677145406315480965,-5384732204964843677,-3071059650417301550,-2603160466482895011,-2221619722341004417,-1557091775694725768,-1403621344696630627,711266062685662619,1333581340284470498,1611305677733360901,2753561903646462793,3866947117330481491,5332477917871449756,5559142600358984796,6001232326845461178,7602738452352881434,8088691831228319750],"qHole_":4832497823804752928}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!or(flatten(1, [[3 = conjure_aux3 |], [4 = conjure_aux3; int(1)]; int(1..2)])) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: [3 = conjure_aux3 |] - Context #1: [[3 = conjure_aux3 |], [4 = conjure_aux3; int(1)]; int(1..2)] - Context #2: flatten(1, [[3 = conjure_aux3 |], [4 = conjure_aux3; int(1)]; int(1..2)]) - Context #3: or(flatten(1, [[3 = conjure_aux3 |], [4 = conjure_aux3; int(1)]; int(1..2)])) - Context #4: !or(flatten(1, [[3 = conjure_aux3 |], [4 = conjure_aux3; int(1)]; int(1..2)])) - Context #5: !or(flatten(1, [[3 = conjure_aux3 |], [4 = conjure_aux3; int(1)]; int(1..2)])) <-> conjure_aux3 = q8_1 - Context #6: [and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])), - !or(flatten(1, [[3 = conjure_aux3 |], [4 = conjure_aux3; int(1)]; int(1..2)])) <-> conjure_aux3 = q8_1; - int(1..2)] - Context #7: and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!or(flatten(1, [[3 = conjure_aux3 |], [4 = conjure_aux3; int(1)]; int(1..2)])) <-> conjure_aux3 = q8_1) - Context #8: { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!or(flatten(1, [[3 = conjure_aux3 |], [4 = conjure_aux3; int(1)]; int(1..2)])) <-> conjure_aux3 = q8_1) - } - Context #9: conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!or(flatten(1, [[3 = conjure_aux3 |], [4 = conjure_aux3; int(1)]; int(1..2)])) <-> conjure_aux3 = q8_1) - } - Context #10: { conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!or(flatten(1, [[3 = conjure_aux3 |], [4 = conjure_aux3; int(1)]; int(1..2)])) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - Context #11: { conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!or(flatten(1, [[3 = conjure_aux3 |], [4 = conjure_aux3; int(1)]; int(1..2)])) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - Context #12: [{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!or(flatten(1, [[3 = conjure_aux3 |], [4 = conjure_aux3; int(1)]; int(1..2)])) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]] - Context #13: and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!or(flatten(1, [[3 = conjure_aux3 |], [4 = conjure_aux3; int(1)]; int(1..2)])) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - Context #14: [|x| = |conjure_aux1|, - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!or(flatten(1, [[3 = conjure_aux3 |], [4 = conjure_aux3; int(1)]; int(1..2)])) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]); - int(1..2)] - Context #15: |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!or(flatten(1, [[3 = conjure_aux3 |], [4 = conjure_aux3; int(1)]; int(1..2)])) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - Context #16: { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!or(flatten(1, [[3 = conjure_aux3 |], [4 = conjure_aux3; int(1)]; int(1..2)])) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - Context #17: y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!or(flatten(1, [[3 = conjure_aux3 |], [4 = conjure_aux3; int(1)]; int(1..2)])) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } -Picking the only option: Answer 1: generators-first: Empty generators. - [3 = conjure_aux3; int(1)] -storedChoice: -[3 = conjure_aux3 |] -185461686146028532 -AnsweredRule {qHole_ = -185461686146028532, qAscendants_ = fromList [-8289289739114023416,-8221845150149788696,-8019537499083765163,-7053954318911112143,-6092536859292112896,-4070943207855695476,-4028159753280221929,-3732495125634815821,-3238009362727088795,-282387919327309193,1775857482582255809,1882693949567706262,2362052944268224547,4832344585872237142,7445111209011732230,7705507659096261482,8654062028269091919], aRuleName_ = "generators-first"} -LF: {"AnsweredRule":{"aRuleName_":"generators-first","qAscendants_":[-8289289739114023416,-8221845150149788696,-8019537499083765163,-7053954318911112143,-6092536859292112896,-4070943207855695476,-4028159753280221929,-3732495125634815821,-3238009362727088795,-282387919327309193,1775857482582255809,1882693949567706262,2362052944268224547,4832344585872237142,7445111209011732230,7705507659096261482,8654062028269091919],"qHole_":-185461686146028532}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!or(flatten(1, [[3 = conjure_aux3; int(1)], [4 = conjure_aux3; int(1)]; int(1..2)])) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: or(flatten(1, [[3 = conjure_aux3; int(1)], [4 = conjure_aux3; int(1)]; int(1..2)])) - Context #1: !or(flatten(1, [[3 = conjure_aux3; int(1)], [4 = conjure_aux3; int(1)]; int(1..2)])) - Context #2: !or(flatten(1, [[3 = conjure_aux3; int(1)], [4 = conjure_aux3; int(1)]; int(1..2)])) <-> conjure_aux3 = q8_1 - Context #3: [and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])), - !or(flatten(1, [[3 = conjure_aux3; int(1)], [4 = conjure_aux3; int(1)]; int(1..2)])) <-> conjure_aux3 = q8_1; - int(1..2)] - Context #4: and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!or(flatten(1, [[3 = conjure_aux3; int(1)], [4 = conjure_aux3; int(1)]; int(1..2)])) <-> conjure_aux3 = q8_1) - Context #5: { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!or(flatten(1, [[3 = conjure_aux3; int(1)], [4 = conjure_aux3; int(1)]; int(1..2)])) <-> conjure_aux3 = q8_1) - } - Context #6: conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!or(flatten(1, [[3 = conjure_aux3; int(1)], [4 = conjure_aux3; int(1)]; int(1..2)])) <-> conjure_aux3 = q8_1) - } - Context #7: { conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!or(flatten(1, [[3 = conjure_aux3; int(1)], [4 = conjure_aux3; int(1)]; int(1..2)])) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - Context #8: { conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!or(flatten(1, [[3 = conjure_aux3; int(1)], [4 = conjure_aux3; int(1)]; int(1..2)])) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - Context #9: [{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!or(flatten(1, [[3 = conjure_aux3; int(1)], [4 = conjure_aux3; int(1)]; int(1..2)])) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]] - Context #10: and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!or(flatten(1, [[3 = conjure_aux3; int(1)], [4 = conjure_aux3; int(1)]; int(1..2)])) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - Context #11: [|x| = |conjure_aux1|, - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!or(flatten(1, [[3 = conjure_aux3; int(1)], [4 = conjure_aux3; int(1)]; int(1..2)])) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]); - int(1..2)] - Context #12: |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!or(flatten(1, [[3 = conjure_aux3; int(1)], [4 = conjure_aux3; int(1)]; int(1..2)])) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - Context #13: { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!or(flatten(1, [[3 = conjure_aux3; int(1)], [4 = conjure_aux3; int(1)]; int(1..2)])) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - Context #14: y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!or(flatten(1, [[3 = conjure_aux3; int(1)], [4 = conjure_aux3; int(1)]; int(1..2)])) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } -Picking the only option: Answer 1: quantifier-shift3: Shifting quantifier inwards - or([3 = conjure_aux3; int(1)]) \/ or([4 = conjure_aux3; int(1)]) -storedChoice: -or(flatten(1, [[3 = conjure_aux3; int(1)], [4 = conjure_aux3; int(1)]; int(1..2)])) 6206761561595236625 -AnsweredRule {qHole_ = 6206761561595236625, qAscendants_ = fromList [-9091665958233421775,-8534800408556100581,-8389275971974927944,-7928483109077342673,-7581357772290646644,-7037234840397785533,-6263532840176792370,-5427006571018076668,-4431680199820092864,-4076541738995400933,-1064366526874994538,5387747797148225385,6292098423078440671,8420337927154511626], aRuleName_ = "quantifier-shift3"} -LF: {"AnsweredRule":{"aRuleName_":"quantifier-shift3","qAscendants_":[-9091665958233421775,-8534800408556100581,-8389275971974927944,-7928483109077342673,-7581357772290646644,-7037234840397785533,-6263532840176792370,-5427006571018076668,-4431680199820092864,-4076541738995400933,-1064366526874994538,5387747797148225385,6292098423078440671,8420337927154511626],"qHole_":6206761561595236625}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!(or([3 = conjure_aux3; int(1)]) \/ or([4 = conjure_aux3; int(1)])) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: or([3 = conjure_aux3; int(1)]) - Context #1: [or([3 = conjure_aux3; int(1)]), or([4 = conjure_aux3; int(1)]); int(1..2)] - Context #2: or([3 = conjure_aux3; int(1)]) \/ or([4 = conjure_aux3; int(1)]) - Context #3: !(or([3 = conjure_aux3; int(1)]) \/ or([4 = conjure_aux3; int(1)])) - Context #4: !(or([3 = conjure_aux3; int(1)]) \/ or([4 = conjure_aux3; int(1)])) <-> conjure_aux3 = q8_1 - Context #5: [and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])), - !(or([3 = conjure_aux3; int(1)]) \/ or([4 = conjure_aux3; int(1)])) <-> conjure_aux3 = q8_1; - int(1..2)] - Context #6: and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!(or([3 = conjure_aux3; int(1)]) \/ or([4 = conjure_aux3; int(1)])) <-> conjure_aux3 = q8_1) - Context #7: { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!(or([3 = conjure_aux3; int(1)]) \/ or([4 = conjure_aux3; int(1)])) <-> conjure_aux3 = q8_1) - } - Context #8: conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!(or([3 = conjure_aux3; int(1)]) \/ or([4 = conjure_aux3; int(1)])) <-> conjure_aux3 = q8_1) - } - Context #9: { conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!(or([3 = conjure_aux3; int(1)]) \/ or([4 = conjure_aux3; int(1)])) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - Context #10: { conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!(or([3 = conjure_aux3; int(1)]) \/ or([4 = conjure_aux3; int(1)])) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - Context #11: [{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!(or([3 = conjure_aux3; int(1)]) \/ or([4 = conjure_aux3; int(1)])) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]] - Context #12: and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!(or([3 = conjure_aux3; int(1)]) \/ or([4 = conjure_aux3; int(1)])) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - Context #13: [|x| = |conjure_aux1|, - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!(or([3 = conjure_aux3; int(1)]) \/ or([4 = conjure_aux3; int(1)])) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]); - int(1..2)] - Context #14: |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!(or([3 = conjure_aux3; int(1)]) \/ or([4 = conjure_aux3; int(1)])) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - Context #15: { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!(or([3 = conjure_aux3; int(1)]) \/ or([4 = conjure_aux3; int(1)])) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - Context #16: y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!(or([3 = conjure_aux3; int(1)]) \/ or([4 = conjure_aux3; int(1)])) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } -Picking the only option: Answer 1: matrix-comprehension-singleton: Removing quantifier of a single item - 3 = conjure_aux3 -storedChoice: -or([3 = conjure_aux3; int(1)]) -3434962391173132894 -AnsweredRule {qHole_ = -3434962391173132894, qAscendants_ = fromList [-7235853985473547952,-6866498255018164123,-4960622746477117042,-4585543795134183636,-4105761649660625353,-3524766623875920799,-2347278582408429201,-1565913897093032045,-636316196669785718,259925545372009536,2634241883209911323,4718505660743647939,6517008955702082360,6653106233829268540,7728404530962223160,8536818627412251687], aRuleName_ = "matrix-comprehension-singleton"} -LF: {"AnsweredRule":{"aRuleName_":"matrix-comprehension-singleton","qAscendants_":[-7235853985473547952,-6866498255018164123,-4960622746477117042,-4585543795134183636,-4105761649660625353,-3524766623875920799,-2347278582408429201,-1565913897093032045,-636316196669785718,259925545372009536,2634241883209911323,4718505660743647939,6517008955702082360,6653106233829268540,7728404530962223160,8536818627412251687],"qHole_":-3434962391173132894}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!(3 = conjure_aux3 \/ or([4 = conjure_aux3; int(1)])) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: or([4 = conjure_aux3; int(1)]) - Context #1: [3 = conjure_aux3, or([4 = conjure_aux3; int(1)]); int(1..2)] - Context #2: 3 = conjure_aux3 \/ or([4 = conjure_aux3; int(1)]) - Context #3: !(3 = conjure_aux3 \/ or([4 = conjure_aux3; int(1)])) - Context #4: !(3 = conjure_aux3 \/ or([4 = conjure_aux3; int(1)])) <-> conjure_aux3 = q8_1 - Context #5: [and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])), - !(3 = conjure_aux3 \/ or([4 = conjure_aux3; int(1)])) <-> conjure_aux3 = q8_1; - int(1..2)] - Context #6: and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!(3 = conjure_aux3 \/ or([4 = conjure_aux3; int(1)])) <-> conjure_aux3 = q8_1) - Context #7: { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!(3 = conjure_aux3 \/ or([4 = conjure_aux3; int(1)])) <-> conjure_aux3 = q8_1) - } - Context #8: conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!(3 = conjure_aux3 \/ or([4 = conjure_aux3; int(1)])) <-> conjure_aux3 = q8_1) - } - Context #9: { conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!(3 = conjure_aux3 \/ or([4 = conjure_aux3; int(1)])) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - Context #10: { conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!(3 = conjure_aux3 \/ or([4 = conjure_aux3; int(1)])) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - Context #11: [{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!(3 = conjure_aux3 \/ or([4 = conjure_aux3; int(1)])) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]] - Context #12: and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!(3 = conjure_aux3 \/ or([4 = conjure_aux3; int(1)])) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - Context #13: [|x| = |conjure_aux1|, - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!(3 = conjure_aux3 \/ or([4 = conjure_aux3; int(1)])) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]); - int(1..2)] - Context #14: |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!(3 = conjure_aux3 \/ or([4 = conjure_aux3; int(1)])) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - Context #15: { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!(3 = conjure_aux3 \/ or([4 = conjure_aux3; int(1)])) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - Context #16: y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!(3 = conjure_aux3 \/ or([4 = conjure_aux3; int(1)])) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } -Picking the only option: Answer 1: matrix-comprehension-singleton: Removing quantifier of a single item - 4 = conjure_aux3 -storedChoice: -or([4 = conjure_aux3; int(1)]) 8578967638246734293 -AnsweredRule {qHole_ = 8578967638246734293, qAscendants_ = fromList [-7767892036023956761,-6284781492183215029,-1727905482554729427,-1356654288157906426,2281150997448020466,2372014189263015226,2446665452257606178,2838934993441470606,4742034938664987168,4756703484454204779,6116173103300050025,6542907600674666418,7911556895678534380,8081136239962017343,8569698893899834293,8949973037119072966], aRuleName_ = "matrix-comprehension-singleton"} -LF: {"AnsweredRule":{"aRuleName_":"matrix-comprehension-singleton","qAscendants_":[-7767892036023956761,-6284781492183215029,-1727905482554729427,-1356654288157906426,2281150997448020466,2372014189263015226,2446665452257606178,2838934993441470606,4742034938664987168,4756703484454204779,6116173103300050025,6542907600674666418,7911556895678534380,8081136239962017343,8569698893899834293,8949973037119072966],"qHole_":8578967638246734293}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: and(flatten(1, - [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) - Context #1: [and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])), - !(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1; - int(1..2)] - Context #2: and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - Context #3: { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - Context #4: conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - Context #5: { conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - Context #6: { conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - Context #7: [{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]] - Context #8: and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - Context #9: [|x| = |conjure_aux1|, - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]); - int(1..2)] - Context #10: |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - Context #11: { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - Context #12: y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } -Picking the only option: Answer 1: quantifier-shift3: Shifting quantifier inwards - and([3 = q8_1 <-> conjure_aux3 = 4; int(1)]) /\ and([4 = q8_1 <-> conjure_aux3 = 3; int(1)]) -storedChoice: -and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) -2199657802844878530 -AnsweredRule {qHole_ = -2199657802844878530, qAscendants_ = fromList [-8444650881280502798,-8271565969096831831,-6564446395948378541,-3553121516791984732,-3091505528568185300,-28537057046234944,2611036720111951620,3048392108732098635,4941408088135413888,6187348870363663871,6391218772456415880,9128754183040712545], aRuleName_ = "quantifier-shift3"} -LF: {"AnsweredRule":{"aRuleName_":"quantifier-shift3","qAscendants_":[-8444650881280502798,-8271565969096831831,-6564446395948378541,-3553121516791984732,-3091505528568185300,-28537057046234944,2611036720111951620,3048392108732098635,4941408088135413888,6187348870363663871,6391218772456415880,9128754183040712545],"qHole_":-2199657802844878530}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and([3 = q8_1 <-> conjure_aux3 = 4; int(1)]) /\ and([4 = q8_1 <-> conjure_aux3 = 3; int(1)]) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: and([3 = q8_1 <-> conjure_aux3 = 4; int(1)]) - Context #1: [and([3 = q8_1 <-> conjure_aux3 = 4; int(1)]), and([4 = q8_1 <-> conjure_aux3 = 3; int(1)]); int(1..2)] - Context #2: and([3 = q8_1 <-> conjure_aux3 = 4; int(1)]) /\ and([4 = q8_1 <-> conjure_aux3 = 3; int(1)]) - Context #3: [and([3 = q8_1 <-> conjure_aux3 = 4; int(1)]) /\ and([4 = q8_1 <-> conjure_aux3 = 3; int(1)]), - !(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1; - int(1..2)] - Context #4: and([3 = q8_1 <-> conjure_aux3 = 4; int(1)]) /\ and([4 = q8_1 <-> conjure_aux3 = 3; int(1)]) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - Context #5: { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and([3 = q8_1 <-> conjure_aux3 = 4; int(1)]) /\ and([4 = q8_1 <-> conjure_aux3 = 3; int(1)]) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - Context #6: conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and([3 = q8_1 <-> conjure_aux3 = 4; int(1)]) /\ and([4 = q8_1 <-> conjure_aux3 = 3; int(1)]) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - Context #7: { conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and([3 = q8_1 <-> conjure_aux3 = 4; int(1)]) /\ and([4 = q8_1 <-> conjure_aux3 = 3; int(1)]) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - Context #8: { conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and([3 = q8_1 <-> conjure_aux3 = 4; int(1)]) /\ and([4 = q8_1 <-> conjure_aux3 = 3; int(1)]) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - Context #9: [{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and([3 = q8_1 <-> conjure_aux3 = 4; int(1)]) /\ and([4 = q8_1 <-> conjure_aux3 = 3; int(1)]) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]] - Context #10: and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and([3 = q8_1 <-> conjure_aux3 = 4; int(1)]) /\ and([4 = q8_1 <-> conjure_aux3 = 3; int(1)]) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - Context #11: [|x| = |conjure_aux1|, - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and([3 = q8_1 <-> conjure_aux3 = 4; int(1)]) /\ and([4 = q8_1 <-> conjure_aux3 = 3; int(1)]) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]); - int(1..2)] - Context #12: |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and([3 = q8_1 <-> conjure_aux3 = 4; int(1)]) /\ and([4 = q8_1 <-> conjure_aux3 = 3; int(1)]) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - Context #13: { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and([3 = q8_1 <-> conjure_aux3 = 4; int(1)]) /\ and([4 = q8_1 <-> conjure_aux3 = 3; int(1)]) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - Context #14: y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and([3 = q8_1 <-> conjure_aux3 = 4; int(1)]) /\ and([4 = q8_1 <-> conjure_aux3 = 3; int(1)]) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } -Picking the only option: Answer 1: matrix-comprehension-singleton: Removing quantifier of a single item - 3 = q8_1 <-> conjure_aux3 = 4 -storedChoice: -and([3 = q8_1 <-> conjure_aux3 = 4; int(1)]) -82084885825755383 -AnsweredRule {qHole_ = -82084885825755383, qAscendants_ = fromList [-7910416632419113217,-6789993106391976797,-6474394686920849630,-4532119084740741428,-4148488185654761721,-3872345874892611968,-3008944008775182264,-2299093800387471961,-1551233151285274759,-649051754905350518,1456233810038530873,2986022555450137983,3688733153117744851,8953876927154124061], aRuleName_ = "matrix-comprehension-singleton"} -LF: {"AnsweredRule":{"aRuleName_":"matrix-comprehension-singleton","qAscendants_":[-7910416632419113217,-6789993106391976797,-6474394686920849630,-4532119084740741428,-4148488185654761721,-3872345874892611968,-3008944008775182264,-2299093800387471961,-1551233151285274759,-649051754905350518,1456233810038530873,2986022555450137983,3688733153117744851,8953876927154124061],"qHole_":-82084885825755383}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ and([4 = q8_1 <-> conjure_aux3 = 3; int(1)]) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: and([4 = q8_1 <-> conjure_aux3 = 3; int(1)]) - Context #1: [3 = q8_1 <-> conjure_aux3 = 4, and([4 = q8_1 <-> conjure_aux3 = 3; int(1)]); int(1..2)] - Context #2: (3 = q8_1 <-> conjure_aux3 = 4) /\ and([4 = q8_1 <-> conjure_aux3 = 3; int(1)]) - Context #3: [(3 = q8_1 <-> conjure_aux3 = 4) /\ and([4 = q8_1 <-> conjure_aux3 = 3; int(1)]), - !(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1; - int(1..2)] - Context #4: (3 = q8_1 <-> conjure_aux3 = 4) /\ and([4 = q8_1 <-> conjure_aux3 = 3; int(1)]) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - Context #5: { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ and([4 = q8_1 <-> conjure_aux3 = 3; int(1)]) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - Context #6: conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ and([4 = q8_1 <-> conjure_aux3 = 3; int(1)]) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - Context #7: { conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ and([4 = q8_1 <-> conjure_aux3 = 3; int(1)]) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - Context #8: { conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ and([4 = q8_1 <-> conjure_aux3 = 3; int(1)]) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - Context #9: [{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ and([4 = q8_1 <-> conjure_aux3 = 3; int(1)]) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]] - Context #10: and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ and([4 = q8_1 <-> conjure_aux3 = 3; int(1)]) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - Context #11: [|x| = |conjure_aux1|, - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ and([4 = q8_1 <-> conjure_aux3 = 3; int(1)]) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]); - int(1..2)] - Context #12: |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ and([4 = q8_1 <-> conjure_aux3 = 3; int(1)]) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - Context #13: { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ and([4 = q8_1 <-> conjure_aux3 = 3; int(1)]) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - Context #14: y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ and([4 = q8_1 <-> conjure_aux3 = 3; int(1)]) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } -Picking the only option: Answer 1: matrix-comprehension-singleton: Removing quantifier of a single item - 4 = q8_1 <-> conjure_aux3 = 3 -storedChoice: -and([4 = q8_1 <-> conjure_aux3 = 3; int(1)]) 4451202942487357861 -AnsweredRule {qHole_ = 4451202942487357861, qAscendants_ = fromList [-7368630815449645005,-4752206960723048197,-2804301512506126649,-1530922004872999299,-236411210949206668,204928372325319241,2335949798361580872,2698852189043337488,3049593885211881070,3728149952134739241,4353487588625663382,5225198894548896615,5925873450508265460,6881890190583065447], aRuleName_ = "matrix-comprehension-singleton"} -LF: {"AnsweredRule":{"aRuleName_":"matrix-comprehension-singleton","qAscendants_":[-7368630815449645005,-4752206960723048197,-2804301512506126649,-1530922004872999299,-236411210949206668,204928372325319241,2335949798361580872,2698852189043337488,3049593885211881070,3728149952134739241,4353487588625663382,5225198894548896615,5925873450508265460,6881890190583065447],"qHole_":4451202942487357861}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - Context #1: conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - Context #2: { conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - Context #3: { conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - Context #4: [{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]] - Context #5: and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - Context #6: [|x| = |conjure_aux1|, - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]); - int(1..2)] - Context #7: |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - Context #8: { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - Context #9: y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } -Picking the only option: Answer 1: choose-repr-for-locals: Choosing representation for local variable conjure_aux3 - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } -storedChoice: -{ conjure_aux3 -@ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) -} -3398171252428132748 -AnsweredRule {qHole_ = -3398171252428132748, qAscendants_ = fromList [-4801520196462386255,-3106386946478834998,-1836288510476607810,-1423400445383478062,1875892051782461076,3043802995379454474,7974629594191079167,8285823029631020243,8636179585519730549], aRuleName_ = "choose-repr-for-locals"} -LF: {"AnsweredRule":{"aRuleName_":"choose-repr-for-locals","qAscendants_":[-4801520196462386255,-3106386946478834998,-1836288510476607810,-1423400445383478062,1875892051782461076,3043802995379454474,7974629594191079167,8285823029631020243,8636179585519730549],"qHole_":-3398171252428132748}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - Context #1: { conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - Context #2: { conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - Context #3: [{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]] - Context #4: and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - Context #5: [|x| = |conjure_aux1|, - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]); - int(1..2)] - Context #6: |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - Context #7: { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - Context #8: y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } -Picking the only option: Answer 1: bubble-up-LiftVars: Bubbling up auxiliary variables. - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } -storedChoice: -conjure_aux2_1 = -{ conjure_aux3 -@ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) -} 7974629594191079167 -AnsweredRule {qHole_ = 7974629594191079167, qAscendants_ = fromList [-4801520196462386255,-3106386946478834998,-1836288510476607810,-1423400445383478062,1875892051782461076,3043802995379454474,8285823029631020243,8636179585519730549], aRuleName_ = "bubble-up-LiftVars"} -LF: {"AnsweredRule":{"aRuleName_":"bubble-up-LiftVars","qAscendants_":[-4801520196462386255,-3106386946478834998,-1836288510476607810,-1423400445383478062,1875892051782461076,3043802995379454474,8285823029631020243,8636179585519730549],"qHole_":7974629594191079167}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: conjure_aux2[2] - Context #1: conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - Context #2: { conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - Context #3: { conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - Context #4: [{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]] - Context #5: and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - Context #6: [|x| = |conjure_aux1|, - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]); - int(1..2)] - Context #7: |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - Context #8: { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - Context #9: y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } -Picking the only option: Answer 1: tuple-index: Tuple indexing on: conjure_aux2[2] - conjure_aux2_2 -storedChoice: -conjure_aux2[2] 2042003740924818024 -AnsweredRule {qHole_ = 2042003740924818024, qAscendants_ = fromList [-7047224780753215240,-3882919266147774615,-2299063140006189613,681365846263239803,6336625794965795994,6485140089845002516,7009155380893464902,7082442116022567493,8239398540167710302], aRuleName_ = "tuple-index"} -LF: {"AnsweredRule":{"aRuleName_":"tuple-index","qAscendants_":[-7047224780753215240,-3882919266147774615,-2299063140006189613,681365846263239803,6336625794965795994,6485140089845002516,7009155380893464902,7082442116022567493,8239398540167710302],"qHole_":2042003740924818024}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2_2 = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: (q8[1], q8[2])[2] - Context #1: image(permutation((3, 4)), (q8[1], q8[2])[2]) - Context #2: conjure_aux2_2 = image(permutation((3, 4)), (q8[1], q8[2])[2]) - Context #3: { conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2_2 = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - Context #4: { conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2_2 = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - Context #5: [{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2_2 = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]] - Context #6: and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2_2 = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - Context #7: [|x| = |conjure_aux1|, - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2_2 = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]); - int(1..2)] - Context #8: |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2_2 = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - Context #9: { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2_2 = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - Context #10: y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2_2 = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } -Picking the only option: Answer 1: tuple-index: Tuple indexing on: (q8[1], q8[2])[2] - q8[2] -storedChoice: -(q8[1], q8[2])[2] -5502204419920622825 -AnsweredRule {qHole_ = -5502204419920622825, qAscendants_ = fromList [-8588231375425367299,-8510895911811768656,-8426633625849827304,-8207238726412672978,-5936144574452389035,-2652871536273271001,-1630485539153521150,-1126023409437003920,6016260006111454055,8400731779430988570], aRuleName_ = "tuple-index"} -LF: {"AnsweredRule":{"aRuleName_":"tuple-index","qAscendants_":[-8588231375425367299,-8510895911811768656,-8426633625849827304,-8207238726412672978,-5936144574452389035,-2652871536273271001,-1630485539153521150,-1126023409437003920,6016260006111454055,8400731779430988570],"qHole_":-5502204419920622825}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2_2 = image(permutation((3, 4)), q8[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: q8[2] - Context #1: image(permutation((3, 4)), q8[2]) - Context #2: conjure_aux2_2 = image(permutation((3, 4)), q8[2]) - Context #3: { conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2_2 = image(permutation((3, 4)), q8[2]) - } - Context #4: { conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2_2 = image(permutation((3, 4)), q8[2]) - } - in conjure_aux1 - Context #5: [{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2_2 = image(permutation((3, 4)), q8[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]] - Context #6: and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2_2 = image(permutation((3, 4)), q8[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - Context #7: [|x| = |conjure_aux1|, - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2_2 = image(permutation((3, 4)), q8[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]); - int(1..2)] - Context #8: |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2_2 = image(permutation((3, 4)), q8[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - Context #9: { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2_2 = image(permutation((3, 4)), q8[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - Context #10: y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2_2 = image(permutation((3, 4)), q8[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } -Picking the only option: Answer 1: tuple-index: Tuple indexing on: q8[2] - q8_2 -storedChoice: -q8[2] 6051020602090044114 -AnsweredRule {qHole_ = 6051020602090044114, qAscendants_ = fromList [-8305205627063512429,-4351892905554585329,-3978385945799741575,-2899802451648727176,-2610387685810348227,-2009358436958284574,-1222951737421888386,-579623331933497389,4724832166697728323,7712861814088489767], aRuleName_ = "tuple-index"} -LF: {"AnsweredRule":{"aRuleName_":"tuple-index","qAscendants_":[-8305205627063512429,-4351892905554585329,-3978385945799741575,-2899802451648727176,-2610387685810348227,-2009358436958284574,-1222951737421888386,-579623331933497389,4724832166697728323,7712861814088489767],"qHole_":6051020602090044114}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2_2 = image(permutation((3, 4)), q8_2) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: image(permutation((3, 4)), q8_2) - Context #1: conjure_aux2_2 = image(permutation((3, 4)), q8_2) - Context #2: { conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2_2 = image(permutation((3, 4)), q8_2) - } - Context #3: { conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2_2 = image(permutation((3, 4)), q8_2) - } - in conjure_aux1 - Context #4: [{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2_2 = image(permutation((3, 4)), q8_2) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]] - Context #5: and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2_2 = image(permutation((3, 4)), q8_2) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - Context #6: [|x| = |conjure_aux1|, - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2_2 = image(permutation((3, 4)), q8_2) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]); - int(1..2)] - Context #7: |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2_2 = image(permutation((3, 4)), q8_2) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - Context #8: { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2_2 = image(permutation((3, 4)), q8_2) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - Context #9: y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2_2 = image(permutation((3, 4)), q8_2) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } -Picking the only option: Answer 1: permutation-image-literal{AsFunction}: Horizontal rule for permutation literal application to a single value (image), AsFunction representation - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and([q15 = q8_2 <-> conjure_aux4 = q16 | (q15, q16) <- [(3, 4), (4, 3); int(1..2)]]) /\ - (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) - } -storedChoice: -image(permutation((3, 4)), q8_2) -6566221682376100457 -AnsweredRule {qHole_ = -6566221682376100457, qAscendants_ = fromList [-7375621483096556180,-6476209656930651827,-6169031786475517693,-4051333596644929202,-1139526513744825718,614654197146956279,4282607200389588721,4519547606898719585,5902970686666028765], aRuleName_ = "permutation-image-literal{AsFunction}"} -LF: {"AnsweredRule":{"aRuleName_":"permutation-image-literal{AsFunction}","qAscendants_":[-7375621483096556180,-6476209656930651827,-6169031786475517693,-4051333596644929202,-1139526513744825718,614654197146956279,4282607200389588721,4519547606898719585,5902970686666028765],"qHole_":-6566221682376100457}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and([q15 = q8_2 <-> conjure_aux4 = q16 | (q15, q16) <- [(3, 4), (4, 3); int(1..2)]]) /\ - (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: [(3, 4), (4, 3); int(1..2)] - Context #1: [q15 = q8_2 <-> conjure_aux4 = q16 | (q15, q16) <- [(3, 4), (4, 3); int(1..2)]] - Context #2: and([q15 = q8_2 <-> conjure_aux4 = q16 | (q15, q16) <- [(3, 4), (4, 3); int(1..2)]]) - Context #3: [and([q15 = q8_2 <-> conjure_aux4 = q16 | (q15, q16) <- [(3, 4), (4, 3); int(1..2)]]), - !or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2; - int(1..2)] - Context #4: and([q15 = q8_2 <-> conjure_aux4 = q16 | (q15, q16) <- [(3, 4), (4, 3); int(1..2)]]) /\ - (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) - Context #5: { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and([q15 = q8_2 <-> conjure_aux4 = q16 | (q15, q16) <- [(3, 4), (4, 3); int(1..2)]]) /\ - (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) - } - Context #6: conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and([q15 = q8_2 <-> conjure_aux4 = q16 | (q15, q16) <- [(3, 4), (4, 3); int(1..2)]]) /\ - (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) - } - Context #7: { conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and([q15 = q8_2 <-> conjure_aux4 = q16 | (q15, q16) <- [(3, 4), (4, 3); int(1..2)]]) /\ - (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) - } - } - Context #8: { conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and([q15 = q8_2 <-> conjure_aux4 = q16 | (q15, q16) <- [(3, 4), (4, 3); int(1..2)]]) /\ - (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - Context #9: [{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and([q15 = q8_2 <-> conjure_aux4 = q16 | (q15, q16) <- [(3, 4), (4, 3); int(1..2)]]) /\ - (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]] - Context #10: and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and([q15 = q8_2 <-> conjure_aux4 = q16 | (q15, q16) <- [(3, 4), (4, 3); int(1..2)]]) /\ - (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - Context #11: [|x| = |conjure_aux1|, - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and([q15 = q8_2 <-> conjure_aux4 = q16 | (q15, q16) <- [(3, 4), (4, 3); int(1..2)]]) /\ - (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]); - int(1..2)] - Context #12: |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and([q15 = q8_2 <-> conjure_aux4 = q16 | (q15, q16) <- [(3, 4), (4, 3); int(1..2)]]) /\ - (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - Context #13: { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and([q15 = q8_2 <-> conjure_aux4 = q16 | (q15, q16) <- [(3, 4), (4, 3); int(1..2)]]) /\ - (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - Context #14: y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and([q15 = q8_2 <-> conjure_aux4 = q16 | (q15, q16) <- [(3, 4), (4, 3); int(1..2)]]) /\ - (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } -Picking the only option: Answer 1: full-evaluate: Full evaluator - [(3, 4), (4, 3); int(1..2)] -storedChoice: -[(3, 4), (4, 3); int(1..2)] 6597397470067790033 -AnsweredRule {qHole_ = 6597397470067790033, qAscendants_ = fromList [-8545307407731927617,-8177498968743831179,-5742947888929994190,-4442383996991551152,396642913451874760,889145374549031649,902104300452840084,1328695702543446488,2152276483370682723,4084473456285295179,4905601367831877360,6850337191508996871,7001603146156804613,8689879020318308638], aRuleName_ = "full-evaluate"} -LF: {"AnsweredRule":{"aRuleName_":"full-evaluate","qAscendants_":[-8545307407731927617,-8177498968743831179,-5742947888929994190,-4442383996991551152,396642913451874760,889145374549031649,902104300452840084,1328695702543446488,2152276483370682723,4084473456285295179,4905601367831877360,6850337191508996871,7001603146156804613,8689879020318308638],"qHole_":6597397470067790033}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and([q15 = q8_2 <-> conjure_aux4 = q16 | (q15, q16) <- [(3, 4), (4, 3); int(1..2)]]) /\ - (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: [q15 = q8_2 <-> conjure_aux4 = q16 | (q15, q16) <- [(3, 4), (4, 3); int(1..2)]] - Context #1: and([q15 = q8_2 <-> conjure_aux4 = q16 | (q15, q16) <- [(3, 4), (4, 3); int(1..2)]]) - Context #2: [and([q15 = q8_2 <-> conjure_aux4 = q16 | (q15, q16) <- [(3, 4), (4, 3); int(1..2)]]), - !or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2; - int(1..2)] - Context #3: and([q15 = q8_2 <-> conjure_aux4 = q16 | (q15, q16) <- [(3, 4), (4, 3); int(1..2)]]) /\ - (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) - Context #4: { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and([q15 = q8_2 <-> conjure_aux4 = q16 | (q15, q16) <- [(3, 4), (4, 3); int(1..2)]]) /\ - (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) - } - Context #5: conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and([q15 = q8_2 <-> conjure_aux4 = q16 | (q15, q16) <- [(3, 4), (4, 3); int(1..2)]]) /\ - (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) - } - Context #6: { conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and([q15 = q8_2 <-> conjure_aux4 = q16 | (q15, q16) <- [(3, 4), (4, 3); int(1..2)]]) /\ - (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) - } - } - Context #7: { conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and([q15 = q8_2 <-> conjure_aux4 = q16 | (q15, q16) <- [(3, 4), (4, 3); int(1..2)]]) /\ - (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - Context #8: [{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and([q15 = q8_2 <-> conjure_aux4 = q16 | (q15, q16) <- [(3, 4), (4, 3); int(1..2)]]) /\ - (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]] - Context #9: and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and([q15 = q8_2 <-> conjure_aux4 = q16 | (q15, q16) <- [(3, 4), (4, 3); int(1..2)]]) /\ - (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - Context #10: [|x| = |conjure_aux1|, - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and([q15 = q8_2 <-> conjure_aux4 = q16 | (q15, q16) <- [(3, 4), (4, 3); int(1..2)]]) /\ - (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]); - int(1..2)] - Context #11: |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and([q15 = q8_2 <-> conjure_aux4 = q16 | (q15, q16) <- [(3, 4), (4, 3); int(1..2)]]) /\ - (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - Context #12: { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and([q15 = q8_2 <-> conjure_aux4 = q16 | (q15, q16) <- [(3, 4), (4, 3); int(1..2)]]) /\ - (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - Context #13: y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and([q15 = q8_2 <-> conjure_aux4 = q16 | (q15, q16) <- [(3, 4), (4, 3); int(1..2)]]) /\ - (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } -Picking the only option: Answer 1: complex-pattern: complex pattern on tuple patterns - [q19[1] = q8_2 <-> conjure_aux4 = q19[2] | q19 <- [(3, 4), (4, 3); int(1..2)]] -storedChoice: -[q15 = q8_2 <-> conjure_aux4 = q16 | (q15, q16) <- [(3, 4), (4, 3); int(1..2)]] 1328695702543446488 -AnsweredRule {qHole_ = 1328695702543446488, qAscendants_ = fromList [-8545307407731927617,-8177498968743831179,-5742947888929994190,-4442383996991551152,396642913451874760,889145374549031649,902104300452840084,2152276483370682723,4084473456285295179,4905601367831877360,6850337191508996871,7001603146156804613,8689879020318308638], aRuleName_ = "complex-pattern"} -LF: {"AnsweredRule":{"aRuleName_":"complex-pattern","qAscendants_":[-8545307407731927617,-8177498968743831179,-5742947888929994190,-4442383996991551152,396642913451874760,889145374549031649,902104300452840084,2152276483370682723,4084473456285295179,4905601367831877360,6850337191508996871,7001603146156804613,8689879020318308638],"qHole_":1328695702543446488}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and([q19[1] = q8_2 <-> conjure_aux4 = q19[2] | q19 <- [(3, 4), (4, 3); int(1..2)]]) /\ - (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: [q19[1] = q8_2 <-> conjure_aux4 = q19[2] | q19 <- [(3, 4), (4, 3); int(1..2)]] - Context #1: and([q19[1] = q8_2 <-> conjure_aux4 = q19[2] | q19 <- [(3, 4), (4, 3); int(1..2)]]) - Context #2: [and([q19[1] = q8_2 <-> conjure_aux4 = q19[2] | q19 <- [(3, 4), (4, 3); int(1..2)]]), - !or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2; - int(1..2)] - Context #3: and([q19[1] = q8_2 <-> conjure_aux4 = q19[2] | q19 <- [(3, 4), (4, 3); int(1..2)]]) /\ - (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) - Context #4: { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and([q19[1] = q8_2 <-> conjure_aux4 = q19[2] | q19 <- [(3, 4), (4, 3); int(1..2)]]) /\ - (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) - } - Context #5: conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and([q19[1] = q8_2 <-> conjure_aux4 = q19[2] | q19 <- [(3, 4), (4, 3); int(1..2)]]) /\ - (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) - } - Context #6: { conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and([q19[1] = q8_2 <-> conjure_aux4 = q19[2] | q19 <- [(3, 4), (4, 3); int(1..2)]]) /\ - (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) - } - } - Context #7: { conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and([q19[1] = q8_2 <-> conjure_aux4 = q19[2] | q19 <- [(3, 4), (4, 3); int(1..2)]]) /\ - (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - Context #8: [{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and([q19[1] = q8_2 <-> conjure_aux4 = q19[2] | q19 <- [(3, 4), (4, 3); int(1..2)]]) /\ - (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]] - Context #9: and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and([q19[1] = q8_2 <-> conjure_aux4 = q19[2] | q19 <- [(3, 4), (4, 3); int(1..2)]]) /\ - (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - Context #10: [|x| = |conjure_aux1|, - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and([q19[1] = q8_2 <-> conjure_aux4 = q19[2] | q19 <- [(3, 4), (4, 3); int(1..2)]]) /\ - (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]); - int(1..2)] - Context #11: |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and([q19[1] = q8_2 <-> conjure_aux4 = q19[2] | q19 <- [(3, 4), (4, 3); int(1..2)]]) /\ - (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - Context #12: { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and([q19[1] = q8_2 <-> conjure_aux4 = q19[2] | q19 <- [(3, 4), (4, 3); int(1..2)]]) /\ - (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - Context #13: y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and([q19[1] = q8_2 <-> conjure_aux4 = q19[2] | q19 <- [(3, 4), (4, 3); int(1..2)]]) /\ - (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } -Picking the only option: Answer 1: matrix-comprehension-literal: Vertical rule for matrix-comprehension on matrix literal - flatten(1, - [[q19[1] = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (3, 4)], - [q19[1] = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (4, 3)]; - int(1..2)]) -storedChoice: -[q19[1] = q8_2 <-> conjure_aux4 = q19[2] | q19 <- [(3, 4), (4, 3); int(1..2)]] 2193708270475412974 -AnsweredRule {qHole_ = 2193708270475412974, qAscendants_ = fromList [-6135273235547916413,-3511824826747542530,-2817684250930868121,-1400917739936160745,-1319813811263441476,-481597523330641054,222999019742587203,2503474596382683671,4309903314606971320,7082348445248550107,7474061097534958542,8348619552204205832,9141480563237676781], aRuleName_ = "matrix-comprehension-literal"} -LF: {"AnsweredRule":{"aRuleName_":"matrix-comprehension-literal","qAscendants_":[-6135273235547916413,-3511824826747542530,-2817684250930868121,-1400917739936160745,-1319813811263441476,-481597523330641054,222999019742587203,2503474596382683671,4309903314606971320,7082348445248550107,7474061097534958542,8348619552204205832,9141480563237676781],"qHole_":2193708270475412974}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, - [[q19[1] = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (3, 4)], - [q19[1] = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (4, 3)]; - int(1..2)])) - /\ (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: q19[1] - Context #1: q19[1] = q8_2 - Context #2: q19[1] = q8_2 <-> conjure_aux4 = q19[2] - Context #3: [q19[1] = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (3, 4)] - Context #4: [[q19[1] = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (3, 4)], - [q19[1] = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (4, 3)]; - int(1..2)] - Context #5: flatten(1, - [[q19[1] = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (3, 4)], - [q19[1] = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (4, 3)]; - int(1..2)]) - Context #6: and(flatten(1, - [[q19[1] = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (3, 4)], - [q19[1] = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (4, 3)]; - int(1..2)])) - Context #7: [and(flatten(1, - [[q19[1] = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (3, 4)], - [q19[1] = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (4, 3)]; - int(1..2)])), - !or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2; - int(1..2)] - Context #8: and(flatten(1, - [[q19[1] = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (3, 4)], - [q19[1] = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (4, 3)]; - int(1..2)])) - /\ (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) - Context #9: { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, - [[q19[1] = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (3, 4)], - [q19[1] = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (4, 3)]; - int(1..2)])) - /\ (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) - } - Context #10: conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, - [[q19[1] = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (3, 4)], - [q19[1] = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (4, 3)]; - int(1..2)])) - /\ (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) - } - Context #11: { conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, - [[q19[1] = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (3, 4)], - [q19[1] = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (4, 3)]; - int(1..2)])) - /\ (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) - } - } - Context #12: { conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, - [[q19[1] = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (3, 4)], - [q19[1] = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (4, 3)]; - int(1..2)])) - /\ (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - Context #13: [{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, - [[q19[1] = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (3, 4)], - [q19[1] = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (4, 3)]; - int(1..2)])) - /\ (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]] - Context #14: and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, - [[q19[1] = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (3, 4)], - [q19[1] = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (4, 3)]; - int(1..2)])) - /\ (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - Context #15: [|x| = |conjure_aux1|, - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, - [[q19[1] = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (3, 4)], - [q19[1] = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (4, 3)]; - int(1..2)])) - /\ (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]); - int(1..2)] - Context #16: |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, - [[q19[1] = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (3, 4)], - [q19[1] = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (4, 3)]; - int(1..2)])) - /\ (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - Context #17: { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, - [[q19[1] = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (3, 4)], - [q19[1] = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (4, 3)]; - int(1..2)])) - /\ (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - Context #18: y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, - [[q19[1] = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (3, 4)], - [q19[1] = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (4, 3)]; - int(1..2)])) - /\ (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } -Picking the only option: Answer 1: full-evaluate: Full evaluator - 3 -storedChoice: -q19[1] 6191924817638487798 -AnsweredRule {qHole_ = 6191924817638487798, qAscendants_ = fromList [-7807298629892727492,-7342314879418443169,-6863795700888677384,-4312957023244042045,-4187455163410375661,-3675178923764728484,-2875109432163106677,-562821977670977521,-430646313158070946,645934730965016486,1213611367040462212,1245826829098445208,2464444564009404876,4591515159436918289,5954646064348546905,6209885551316441807,7780749284175319389,8140212805021622098], aRuleName_ = "full-evaluate"} -LF: {"AnsweredRule":{"aRuleName_":"full-evaluate","qAscendants_":[-7807298629892727492,-7342314879418443169,-6863795700888677384,-4312957023244042045,-4187455163410375661,-3675178923764728484,-2875109432163106677,-562821977670977521,-430646313158070946,645934730965016486,1213611367040462212,1245826829098445208,2464444564009404876,4591515159436918289,5954646064348546905,6209885551316441807,7780749284175319389,8140212805021622098],"qHole_":6191924817638487798}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, - [[3 = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (3, 4)], [q19[1] = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (4, 3)]; - int(1..2)])) - /\ (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: q19[2] - Context #1: conjure_aux4 = q19[2] - Context #2: 3 = q8_2 <-> conjure_aux4 = q19[2] - Context #3: [3 = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (3, 4)] - Context #4: [[3 = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (3, 4)], - [q19[1] = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (4, 3)]; - int(1..2)] - Context #5: flatten(1, - [[3 = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (3, 4)], [q19[1] = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (4, 3)]; - int(1..2)]) - Context #6: and(flatten(1, - [[3 = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (3, 4)], [q19[1] = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (4, 3)]; - int(1..2)])) - Context #7: [and(flatten(1, - [[3 = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (3, 4)], [q19[1] = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (4, 3)]; - int(1..2)])), - !or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2; - int(1..2)] - Context #8: and(flatten(1, - [[3 = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (3, 4)], [q19[1] = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (4, 3)]; - int(1..2)])) - /\ (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) - Context #9: { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, - [[3 = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (3, 4)], [q19[1] = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (4, 3)]; - int(1..2)])) - /\ (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) - } - Context #10: conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, - [[3 = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (3, 4)], [q19[1] = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (4, 3)]; - int(1..2)])) - /\ (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) - } - Context #11: { conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, - [[3 = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (3, 4)], [q19[1] = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (4, 3)]; - int(1..2)])) - /\ (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) - } - } - Context #12: { conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, - [[3 = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (3, 4)], [q19[1] = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (4, 3)]; - int(1..2)])) - /\ (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - Context #13: [{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, - [[3 = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (3, 4)], [q19[1] = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (4, 3)]; - int(1..2)])) - /\ (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]] - Context #14: and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, - [[3 = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (3, 4)], - [q19[1] = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (4, 3)]; - int(1..2)])) - /\ (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - Context #15: [|x| = |conjure_aux1|, - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, - [[3 = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (3, 4)], - [q19[1] = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (4, 3)]; - int(1..2)])) - /\ (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]); - int(1..2)] - Context #16: |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, - [[3 = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (3, 4)], - [q19[1] = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (4, 3)]; - int(1..2)])) - /\ (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - Context #17: { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, - [[3 = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (3, 4)], - [q19[1] = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (4, 3)]; - int(1..2)])) - /\ (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - Context #18: y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, - [[3 = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (3, 4)], - [q19[1] = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (4, 3)]; - int(1..2)])) - /\ (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } -Picking the only option: Answer 1: full-evaluate: Full evaluator - 4 -storedChoice: -q19[2] 6191080349758138413 -AnsweredRule {qHole_ = 6191080349758138413, qAscendants_ = fromList [-6520176996801677506,-5843168008449148354,-5683324553460351353,-4951129330098074556,-4643211621054911287,-3822866046842193137,-3751755282991126720,-2857878400374217220,-1860910263859276895,-1737565941370477352,1050126061434755877,2341740140041990923,2502411580506467583,2525054445025194025,3419152102230274364,7279809536600806905,8523948582780839689,8905640568803089599], aRuleName_ = "full-evaluate"} -LF: {"AnsweredRule":{"aRuleName_":"full-evaluate","qAscendants_":[-6520176996801677506,-5843168008449148354,-5683324553460351353,-4951129330098074556,-4643211621054911287,-3822866046842193137,-3751755282991126720,-2857878400374217220,-1860910263859276895,-1737565941370477352,1050126061434755877,2341740140041990923,2502411580506467583,2525054445025194025,3419152102230274364,7279809536600806905,8523948582780839689,8905640568803089599],"qHole_":6191080349758138413}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, - [[3 = q8_2 <-> conjure_aux4 = 4 | letting q19 be (3, 4)], [q19[1] = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (4, 3)]; - int(1..2)])) - /\ (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: q19[1] - Context #1: q19[1] = q8_2 - Context #2: q19[1] = q8_2 <-> conjure_aux4 = q19[2] - Context #3: [q19[1] = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (4, 3)] - Context #4: [[3 = q8_2 <-> conjure_aux4 = 4 | letting q19 be (3, 4)], - [q19[1] = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (4, 3)]; - int(1..2)] - Context #5: flatten(1, - [[3 = q8_2 <-> conjure_aux4 = 4 | letting q19 be (3, 4)], [q19[1] = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (4, 3)]; - int(1..2)]) - Context #6: and(flatten(1, - [[3 = q8_2 <-> conjure_aux4 = 4 | letting q19 be (3, 4)], [q19[1] = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (4, 3)]; - int(1..2)])) - Context #7: [and(flatten(1, - [[3 = q8_2 <-> conjure_aux4 = 4 | letting q19 be (3, 4)], [q19[1] = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (4, 3)]; - int(1..2)])), - !or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2; - int(1..2)] - Context #8: and(flatten(1, - [[3 = q8_2 <-> conjure_aux4 = 4 | letting q19 be (3, 4)], [q19[1] = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (4, 3)]; - int(1..2)])) - /\ (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) - Context #9: { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, - [[3 = q8_2 <-> conjure_aux4 = 4 | letting q19 be (3, 4)], [q19[1] = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (4, 3)]; - int(1..2)])) - /\ (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) - } - Context #10: conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, - [[3 = q8_2 <-> conjure_aux4 = 4 | letting q19 be (3, 4)], [q19[1] = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (4, 3)]; - int(1..2)])) - /\ (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) - } - Context #11: { conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, - [[3 = q8_2 <-> conjure_aux4 = 4 | letting q19 be (3, 4)], [q19[1] = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (4, 3)]; - int(1..2)])) - /\ (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) - } - } - Context #12: { conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, - [[3 = q8_2 <-> conjure_aux4 = 4 | letting q19 be (3, 4)], [q19[1] = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (4, 3)]; - int(1..2)])) - /\ (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - Context #13: [{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, - [[3 = q8_2 <-> conjure_aux4 = 4 | letting q19 be (3, 4)], [q19[1] = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (4, 3)]; - int(1..2)])) - /\ (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]] - Context #14: and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, - [[3 = q8_2 <-> conjure_aux4 = 4 | letting q19 be (3, 4)], [q19[1] = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (4, 3)]; - int(1..2)])) - /\ (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - Context #15: [|x| = |conjure_aux1|, - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, - [[3 = q8_2 <-> conjure_aux4 = 4 | letting q19 be (3, 4)], [q19[1] = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (4, 3)]; - int(1..2)])) - /\ (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]); - int(1..2)] - Context #16: |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, - [[3 = q8_2 <-> conjure_aux4 = 4 | letting q19 be (3, 4)], [q19[1] = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (4, 3)]; - int(1..2)])) - /\ (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - Context #17: { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, - [[3 = q8_2 <-> conjure_aux4 = 4 | letting q19 be (3, 4)], - [q19[1] = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (4, 3)]; - int(1..2)])) - /\ (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - Context #18: y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, - [[3 = q8_2 <-> conjure_aux4 = 4 | letting q19 be (3, 4)], - [q19[1] = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (4, 3)]; - int(1..2)])) - /\ (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } -Picking the only option: Answer 1: full-evaluate: Full evaluator - 4 -storedChoice: -q19[1] 6191924817638487798 -AnsweredRule {qHole_ = 6191924817638487798, qAscendants_ = fromList [-8623968074095065085,-7329444732361257248,-4918646323490343107,-3863503547689138135,-3675178923764728484,-3569961048242171061,-3144694525976125140,-3142709837274542140,-3025737286103464396,-2863059074413010081,-2845931958765307537,-1992102340549551315,-1320176390405360702,-727033692116714751,-430646313158070946,4099404035470031281,7496678802752551639,8353918602880186919], aRuleName_ = "full-evaluate"} -LF: {"AnsweredRule":{"aRuleName_":"full-evaluate","qAscendants_":[-8623968074095065085,-7329444732361257248,-4918646323490343107,-3863503547689138135,-3675178923764728484,-3569961048242171061,-3144694525976125140,-3142709837274542140,-3025737286103464396,-2863059074413010081,-2845931958765307537,-1992102340549551315,-1320176390405360702,-727033692116714751,-430646313158070946,4099404035470031281,7496678802752551639,8353918602880186919],"qHole_":6191924817638487798}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, - [[3 = q8_2 <-> conjure_aux4 = 4 | letting q19 be (3, 4)], [4 = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (4, 3)]; int(1..2)])) - /\ (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: q19[2] - Context #1: conjure_aux4 = q19[2] - Context #2: 4 = q8_2 <-> conjure_aux4 = q19[2] - Context #3: [4 = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (4, 3)] - Context #4: [[3 = q8_2 <-> conjure_aux4 = 4 | letting q19 be (3, 4)], [4 = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (4, 3)]; - int(1..2)] - Context #5: flatten(1, - [[3 = q8_2 <-> conjure_aux4 = 4 | letting q19 be (3, 4)], [4 = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (4, 3)]; int(1..2)]) - Context #6: and(flatten(1, - [[3 = q8_2 <-> conjure_aux4 = 4 | letting q19 be (3, 4)], [4 = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (4, 3)]; int(1..2)])) - Context #7: [and(flatten(1, - [[3 = q8_2 <-> conjure_aux4 = 4 | letting q19 be (3, 4)], [4 = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (4, 3)]; int(1..2)])), - !or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2; - int(1..2)] - Context #8: and(flatten(1, - [[3 = q8_2 <-> conjure_aux4 = 4 | letting q19 be (3, 4)], [4 = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (4, 3)]; int(1..2)])) - /\ (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) - Context #9: { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, - [[3 = q8_2 <-> conjure_aux4 = 4 | letting q19 be (3, 4)], [4 = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (4, 3)]; int(1..2)])) - /\ (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) - } - Context #10: conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, - [[3 = q8_2 <-> conjure_aux4 = 4 | letting q19 be (3, 4)], [4 = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (4, 3)]; int(1..2)])) - /\ (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) - } - Context #11: { conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, - [[3 = q8_2 <-> conjure_aux4 = 4 | letting q19 be (3, 4)], [4 = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (4, 3)]; int(1..2)])) - /\ (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) - } - } - Context #12: { conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, - [[3 = q8_2 <-> conjure_aux4 = 4 | letting q19 be (3, 4)], [4 = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (4, 3)]; int(1..2)])) - /\ (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - Context #13: [{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, - [[3 = q8_2 <-> conjure_aux4 = 4 | letting q19 be (3, 4)], [4 = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (4, 3)]; int(1..2)])) - /\ (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]] - Context #14: and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, - [[3 = q8_2 <-> conjure_aux4 = 4 | letting q19 be (3, 4)], [4 = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (4, 3)]; - int(1..2)])) - /\ (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - Context #15: [|x| = |conjure_aux1|, - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, - [[3 = q8_2 <-> conjure_aux4 = 4 | letting q19 be (3, 4)], [4 = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (4, 3)]; - int(1..2)])) - /\ (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]); - int(1..2)] - Context #16: |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, - [[3 = q8_2 <-> conjure_aux4 = 4 | letting q19 be (3, 4)], [4 = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (4, 3)]; - int(1..2)])) - /\ (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - Context #17: { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, - [[3 = q8_2 <-> conjure_aux4 = 4 | letting q19 be (3, 4)], [4 = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (4, 3)]; - int(1..2)])) - /\ (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - Context #18: y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, - [[3 = q8_2 <-> conjure_aux4 = 4 | letting q19 be (3, 4)], [4 = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (4, 3)]; - int(1..2)])) - /\ (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } -Picking the only option: Answer 1: full-evaluate: Full evaluator - 3 -storedChoice: -q19[2] 6191080349758138413 -AnsweredRule {qHole_ = 6191080349758138413, qAscendants_ = fromList [-8757640153264855213,-8246403386320852045,-7634455432471374117,-6807206396586148212,-6520176996801677506,-3765915116603809328,-3206961831370542574,-2880744773295792633,10288890695967554,1236510066935204208,2127338015569558053,2891526256517846499,4193370254288787506,4672949733519819188,4775978928665173836,5268252065626460890,7614915012244226995,8901849277253604507], aRuleName_ = "full-evaluate"} -LF: {"AnsweredRule":{"aRuleName_":"full-evaluate","qAscendants_":[-8757640153264855213,-8246403386320852045,-7634455432471374117,-6807206396586148212,-6520176996801677506,-3765915116603809328,-3206961831370542574,-2880744773295792633,10288890695967554,1236510066935204208,2127338015569558053,2891526256517846499,4193370254288787506,4672949733519819188,4775978928665173836,5268252065626460890,7614915012244226995,8901849277253604507],"qHole_":6191080349758138413}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, - [[3 = q8_2 <-> conjure_aux4 = 4 | letting q19 be (3, 4)], [4 = q8_2 <-> conjure_aux4 = 3 | letting q19 be (4, 3)]; int(1..2)])) - /\ (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: [4 = q8_2 <-> conjure_aux4 = 3 | letting q19 be (4, 3)] - Context #1: [[3 = q8_2 <-> conjure_aux4 = 4 | letting q19 be (3, 4)], [4 = q8_2 <-> conjure_aux4 = 3 | letting q19 be (4, 3)]; - int(1..2)] - Context #2: flatten(1, - [[3 = q8_2 <-> conjure_aux4 = 4 | letting q19 be (3, 4)], [4 = q8_2 <-> conjure_aux4 = 3 | letting q19 be (4, 3)]; int(1..2)]) - Context #3: and(flatten(1, - [[3 = q8_2 <-> conjure_aux4 = 4 | letting q19 be (3, 4)], [4 = q8_2 <-> conjure_aux4 = 3 | letting q19 be (4, 3)]; int(1..2)])) - Context #4: [and(flatten(1, - [[3 = q8_2 <-> conjure_aux4 = 4 | letting q19 be (3, 4)], [4 = q8_2 <-> conjure_aux4 = 3 | letting q19 be (4, 3)]; int(1..2)])), - !or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2; - int(1..2)] - Context #5: and(flatten(1, - [[3 = q8_2 <-> conjure_aux4 = 4 | letting q19 be (3, 4)], [4 = q8_2 <-> conjure_aux4 = 3 | letting q19 be (4, 3)]; int(1..2)])) - /\ (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) - Context #6: { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, - [[3 = q8_2 <-> conjure_aux4 = 4 | letting q19 be (3, 4)], [4 = q8_2 <-> conjure_aux4 = 3 | letting q19 be (4, 3)]; int(1..2)])) - /\ (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) - } - Context #7: conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, - [[3 = q8_2 <-> conjure_aux4 = 4 | letting q19 be (3, 4)], [4 = q8_2 <-> conjure_aux4 = 3 | letting q19 be (4, 3)]; int(1..2)])) - /\ (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) - } - Context #8: { conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, - [[3 = q8_2 <-> conjure_aux4 = 4 | letting q19 be (3, 4)], [4 = q8_2 <-> conjure_aux4 = 3 | letting q19 be (4, 3)]; int(1..2)])) - /\ (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) - } - } - Context #9: { conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, - [[3 = q8_2 <-> conjure_aux4 = 4 | letting q19 be (3, 4)], [4 = q8_2 <-> conjure_aux4 = 3 | letting q19 be (4, 3)]; int(1..2)])) - /\ (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - Context #10: [{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, - [[3 = q8_2 <-> conjure_aux4 = 4 | letting q19 be (3, 4)], [4 = q8_2 <-> conjure_aux4 = 3 | letting q19 be (4, 3)]; int(1..2)])) - /\ (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]] - Context #11: and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, - [[3 = q8_2 <-> conjure_aux4 = 4 | letting q19 be (3, 4)], [4 = q8_2 <-> conjure_aux4 = 3 | letting q19 be (4, 3)]; int(1..2)])) - /\ (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - Context #12: [|x| = |conjure_aux1|, - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, - [[3 = q8_2 <-> conjure_aux4 = 4 | letting q19 be (3, 4)], [4 = q8_2 <-> conjure_aux4 = 3 | letting q19 be (4, 3)]; int(1..2)])) - /\ (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]); - int(1..2)] - Context #13: |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, - [[3 = q8_2 <-> conjure_aux4 = 4 | letting q19 be (3, 4)], [4 = q8_2 <-> conjure_aux4 = 3 | letting q19 be (4, 3)]; int(1..2)])) - /\ (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - Context #14: { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, - [[3 = q8_2 <-> conjure_aux4 = 4 | letting q19 be (3, 4)], [4 = q8_2 <-> conjure_aux4 = 3 | letting q19 be (4, 3)]; - int(1..2)])) - /\ (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - Context #15: y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, - [[3 = q8_2 <-> conjure_aux4 = 4 | letting q19 be (3, 4)], [4 = q8_2 <-> conjure_aux4 = 3 | letting q19 be (4, 3)]; - int(1..2)])) - /\ (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } -Picking the only option: Answer 1: generators-first: Inlining comprehension lettings. - [4 = q8_2 <-> conjure_aux4 = 3 |] -storedChoice: -[4 = q8_2 <-> conjure_aux4 = 3 | letting q19 be (4, 3)] 1588099557195084353 -AnsweredRule {qHole_ = 1588099557195084353, qAscendants_ = fromList [-8793688442874950149,-7572881584565844112,-7548342805617471592,-4348732945489509501,-2395694351007614565,88957386040583823,374422725277413608,1323284114810179273,2396707417125615551,2821870942280363336,4471571311804301542,5264705085330663748,5735937483858420141,6159114761266478893,6376856799016601882], aRuleName_ = "generators-first"} -LF: {"AnsweredRule":{"aRuleName_":"generators-first","qAscendants_":[-8793688442874950149,-7572881584565844112,-7548342805617471592,-4348732945489509501,-2395694351007614565,88957386040583823,374422725277413608,1323284114810179273,2396707417125615551,2821870942280363336,4471571311804301542,5264705085330663748,5735937483858420141,6159114761266478893,6376856799016601882],"qHole_":1588099557195084353}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4 | letting q19 be (3, 4)], [4 = q8_2 <-> conjure_aux4 = 3 |]; int(1..2)])) /\ - (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: [4 = q8_2 <-> conjure_aux4 = 3 |] - Context #1: [[3 = q8_2 <-> conjure_aux4 = 4 | letting q19 be (3, 4)], [4 = q8_2 <-> conjure_aux4 = 3 |]; int(1..2)] - Context #2: flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4 | letting q19 be (3, 4)], [4 = q8_2 <-> conjure_aux4 = 3 |]; int(1..2)]) - Context #3: and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4 | letting q19 be (3, 4)], [4 = q8_2 <-> conjure_aux4 = 3 |]; int(1..2)])) - Context #4: [and(flatten(1, - [[3 = q8_2 <-> conjure_aux4 = 4 | letting q19 be (3, 4)], [4 = q8_2 <-> conjure_aux4 = 3 |]; int(1..2)])), - !or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2; - int(1..2)] - Context #5: and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4 | letting q19 be (3, 4)], [4 = q8_2 <-> conjure_aux4 = 3 |]; int(1..2)])) - /\ (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) - Context #6: { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4 | letting q19 be (3, 4)], [4 = q8_2 <-> conjure_aux4 = 3 |]; int(1..2)])) /\ - (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) - } - Context #7: conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4 | letting q19 be (3, 4)], [4 = q8_2 <-> conjure_aux4 = 3 |]; int(1..2)])) /\ - (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) - } - Context #8: { conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4 | letting q19 be (3, 4)], [4 = q8_2 <-> conjure_aux4 = 3 |]; int(1..2)])) /\ - (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) - } - } - Context #9: { conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4 | letting q19 be (3, 4)], [4 = q8_2 <-> conjure_aux4 = 3 |]; int(1..2)])) /\ - (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - Context #10: [{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4 | letting q19 be (3, 4)], [4 = q8_2 <-> conjure_aux4 = 3 |]; int(1..2)])) /\ - (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]] - Context #11: and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4 | letting q19 be (3, 4)], [4 = q8_2 <-> conjure_aux4 = 3 |]; int(1..2)])) /\ - (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - Context #12: [|x| = |conjure_aux1|, - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4 | letting q19 be (3, 4)], [4 = q8_2 <-> conjure_aux4 = 3 |]; int(1..2)])) /\ - (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]); - int(1..2)] - Context #13: |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4 | letting q19 be (3, 4)], [4 = q8_2 <-> conjure_aux4 = 3 |]; int(1..2)])) /\ - (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - Context #14: { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4 | letting q19 be (3, 4)], [4 = q8_2 <-> conjure_aux4 = 3 |]; int(1..2)])) /\ - (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - Context #15: y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4 | letting q19 be (3, 4)], [4 = q8_2 <-> conjure_aux4 = 3 |]; int(1..2)])) /\ - (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } -Picking the only option: Answer 1: generators-first: Empty generators. - [4 = q8_2 <-> conjure_aux4 = 3; int(1)] -storedChoice: -[4 = q8_2 <-> conjure_aux4 = 3 |] 5497036040823098170 -AnsweredRule {qHole_ = 5497036040823098170, qAscendants_ = fromList [-8392241438280449004,-7601484554155610431,-6546222595955103458,-5296722524234462815,-2359991535599832467,-1063257280645700723,-17895501989558244,635280768506310618,1960340259087120798,3697301678543081257,4285418689022343979,6976383550303671088,8132222765465596941,8451535935592013102,8523836484272235728], aRuleName_ = "generators-first"} -LF: {"AnsweredRule":{"aRuleName_":"generators-first","qAscendants_":[-8392241438280449004,-7601484554155610431,-6546222595955103458,-5296722524234462815,-2359991535599832467,-1063257280645700723,-17895501989558244,635280768506310618,1960340259087120798,3697301678543081257,4285418689022343979,6976383550303671088,8132222765465596941,8451535935592013102,8523836484272235728],"qHole_":5497036040823098170}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4 | letting q19 be (3, 4)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: [3 = q8_2 <-> conjure_aux4 = 4 | letting q19 be (3, 4)] - Context #1: [[3 = q8_2 <-> conjure_aux4 = 4 | letting q19 be (3, 4)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)] - Context #2: flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4 | letting q19 be (3, 4)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)]) - Context #3: and(flatten(1, - [[3 = q8_2 <-> conjure_aux4 = 4 | letting q19 be (3, 4)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) - Context #4: [and(flatten(1, - [[3 = q8_2 <-> conjure_aux4 = 4 | letting q19 be (3, 4)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])), - !or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2; - int(1..2)] - Context #5: and(flatten(1, - [[3 = q8_2 <-> conjure_aux4 = 4 | letting q19 be (3, 4)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) - /\ (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) - Context #6: { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4 | letting q19 be (3, 4)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) - } - Context #7: conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4 | letting q19 be (3, 4)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) - } - Context #8: { conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4 | letting q19 be (3, 4)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) - } - } - Context #9: { conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4 | letting q19 be (3, 4)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - Context #10: [{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4 | letting q19 be (3, 4)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]] - Context #11: and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4 | letting q19 be (3, 4)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - Context #12: [|x| = |conjure_aux1|, - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4 | letting q19 be (3, 4)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]); - int(1..2)] - Context #13: |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4 | letting q19 be (3, 4)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - Context #14: { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4 | letting q19 be (3, 4)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - Context #15: y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4 | letting q19 be (3, 4)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } -Picking the only option: Answer 1: generators-first: Inlining comprehension lettings. - [3 = q8_2 <-> conjure_aux4 = 4 |] -storedChoice: -[3 = q8_2 <-> conjure_aux4 = 4 | letting q19 be (3, 4)] 4563840366785778455 -AnsweredRule {qHole_ = 4563840366785778455, qAscendants_ = fromList [-8318635854976707433,-5946611935025738568,-5571483100812435886,-5359593091160120138,-5038848917712120091,-4505559122101590956,-4490512703364564363,-3882495187869643600,1795022445773124374,2052386823818313881,3017254667178360325,5004474385002050470,5786646087302900637,8288841898596402765,8964004080555796084], aRuleName_ = "generators-first"} -LF: {"AnsweredRule":{"aRuleName_":"generators-first","qAscendants_":[-8318635854976707433,-5946611935025738568,-5571483100812435886,-5359593091160120138,-5038848917712120091,-4505559122101590956,-4490512703364564363,-3882495187869643600,1795022445773124374,2052386823818313881,3017254667178360325,5004474385002050470,5786646087302900637,8288841898596402765,8964004080555796084],"qHole_":4563840366785778455}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4 |], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: [3 = q8_2 <-> conjure_aux4 = 4 |] - Context #1: [[3 = q8_2 <-> conjure_aux4 = 4 |], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)] - Context #2: flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4 |], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)]) - Context #3: and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4 |], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) - Context #4: [and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4 |], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])), - !or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2; - int(1..2)] - Context #5: and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4 |], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) - Context #6: { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4 |], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) - } - Context #7: conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4 |], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) - } - Context #8: { conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4 |], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) - } - } - Context #9: { conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4 |], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - Context #10: [{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4 |], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]] - Context #11: and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4 |], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - Context #12: [|x| = |conjure_aux1|, - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4 |], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]); - int(1..2)] - Context #13: |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4 |], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - Context #14: { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4 |], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - Context #15: y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4 |], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } -Picking the only option: Answer 1: generators-first: Empty generators. - [3 = q8_2 <-> conjure_aux4 = 4; int(1)] -storedChoice: -[3 = q8_2 <-> conjure_aux4 = 4 |] -4963556797043179790 -AnsweredRule {qHole_ = -4963556797043179790, qAscendants_ = fromList [-8774772560597070458,-8569754725622420077,-7014391000977899535,-5142692957413181259,-4041649316716467790,-3712748679124722967,-622761194274709583,-434728569439334546,1040357877965562186,2786263529603136423,3452832737484532816,4830299290996501437,5939727597018131278,7229121740432553148,8127256833064397799], aRuleName_ = "generators-first"} -LF: {"AnsweredRule":{"aRuleName_":"generators-first","qAscendants_":[-8774772560597070458,-8569754725622420077,-7014391000977899535,-5142692957413181259,-4041649316716467790,-3712748679124722967,-622761194274709583,-434728569439334546,1040357877965562186,2786263529603136423,3452832737484532816,4830299290996501437,5939727597018131278,7229121740432553148,8127256833064397799],"qHole_":-4963556797043179790}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: [(3, 4), (4, 3); int(1..2)] - Context #1: [q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]] - Context #2: or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) - Context #3: !or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) - Context #4: !or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2 - Context #5: [and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])), - !or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2; - int(1..2)] - Context #6: and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) - Context #7: { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) - } - Context #8: conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) - } - Context #9: { conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) - } - } - Context #10: { conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - Context #11: [{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]] - Context #12: and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - Context #13: [|x| = |conjure_aux1|, - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]); - int(1..2)] - Context #14: |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - Context #15: { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - Context #16: y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } -Picking the only option: Answer 1: full-evaluate: Full evaluator - [(3, 4), (4, 3); int(1..2)] -storedChoice: -[(3, 4), (4, 3); int(1..2)] 6597397470067790033 -AnsweredRule {qHole_ = 6597397470067790033, qAscendants_ = fromList [-8633754808918514186,-8188184727507762196,-5677541651570710819,-4916174755379616322,-4850199604535152020,-3462648503323623219,-2367628624258445968,-2307855029918049024,1883982971068606087,1912870777007720445,2809445194379708718,3667006364909395131,3677477140697149393,7256127331114215867,8364657527657792986,9047491038558976704], aRuleName_ = "full-evaluate"} -LF: {"AnsweredRule":{"aRuleName_":"full-evaluate","qAscendants_":[-8633754808918514186,-8188184727507762196,-5677541651570710819,-4916174755379616322,-4850199604535152020,-3462648503323623219,-2367628624258445968,-2307855029918049024,1883982971068606087,1912870777007720445,2809445194379708718,3667006364909395131,3677477140697149393,7256127331114215867,8364657527657792986,9047491038558976704],"qHole_":6597397470067790033}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: [q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]] - Context #1: or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) - Context #2: !or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) - Context #3: !or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2 - Context #4: [and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])), - !or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2; - int(1..2)] - Context #5: and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) - Context #6: { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) - } - Context #7: conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) - } - Context #8: { conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) - } - } - Context #9: { conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - Context #10: [{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]] - Context #11: and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - Context #12: [|x| = |conjure_aux1|, - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]); - int(1..2)] - Context #13: |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - Context #14: { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - Context #15: y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } -Picking the only option: Answer 1: complex-pattern: complex pattern on tuple patterns - [q20[1] = conjure_aux4 | q20 <- [(3, 4), (4, 3); int(1..2)]] -storedChoice: -[q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]] -4850199604535152020 -AnsweredRule {qHole_ = -4850199604535152020, qAscendants_ = fromList [-8633754808918514186,-8188184727507762196,-5677541651570710819,-4916174755379616322,-3462648503323623219,-2367628624258445968,-2307855029918049024,1883982971068606087,1912870777007720445,2809445194379708718,3667006364909395131,3677477140697149393,7256127331114215867,8364657527657792986,9047491038558976704], aRuleName_ = "complex-pattern"} -LF: {"AnsweredRule":{"aRuleName_":"complex-pattern","qAscendants_":[-8633754808918514186,-8188184727507762196,-5677541651570710819,-4916174755379616322,-3462648503323623219,-2367628624258445968,-2307855029918049024,1883982971068606087,1912870777007720445,2809445194379708718,3667006364909395131,3677477140697149393,7256127331114215867,8364657527657792986,9047491038558976704],"qHole_":-4850199604535152020}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!or([q20[1] = conjure_aux4 | q20 <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: [q20[1] = conjure_aux4 | q20 <- [(3, 4), (4, 3); int(1..2)]] - Context #1: or([q20[1] = conjure_aux4 | q20 <- [(3, 4), (4, 3); int(1..2)]]) - Context #2: !or([q20[1] = conjure_aux4 | q20 <- [(3, 4), (4, 3); int(1..2)]]) - Context #3: !or([q20[1] = conjure_aux4 | q20 <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2 - Context #4: [and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])), - !or([q20[1] = conjure_aux4 | q20 <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2; - int(1..2)] - Context #5: and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!or([q20[1] = conjure_aux4 | q20 <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) - Context #6: { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!or([q20[1] = conjure_aux4 | q20 <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) - } - Context #7: conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!or([q20[1] = conjure_aux4 | q20 <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) - } - Context #8: { conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!or([q20[1] = conjure_aux4 | q20 <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) - } - } - Context #9: { conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!or([q20[1] = conjure_aux4 | q20 <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - Context #10: [{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!or([q20[1] = conjure_aux4 | q20 <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]] - Context #11: and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!or([q20[1] = conjure_aux4 | q20 <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - Context #12: [|x| = |conjure_aux1|, - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!or([q20[1] = conjure_aux4 | q20 <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]); - int(1..2)] - Context #13: |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!or([q20[1] = conjure_aux4 | q20 <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - Context #14: { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!or([q20[1] = conjure_aux4 | q20 <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - Context #15: y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!or([q20[1] = conjure_aux4 | q20 <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } -Picking the only option: Answer 1: matrix-comprehension-literal: Vertical rule for matrix-comprehension on matrix literal - flatten(1, [[q20[1] = conjure_aux4 | letting q20 be (3, 4)], [q20[1] = conjure_aux4 | letting q20 be (4, 3)]; int(1..2)]) -storedChoice: -[q20[1] = conjure_aux4 | q20 <- [(3, 4), (4, 3); int(1..2)]] -7042519532359788232 -AnsweredRule {qHole_ = -7042519532359788232, qAscendants_ = fromList [-8908244575740954826,-5683928670681234592,-5283973279755061591,-3518626964796470528,-1965680338567566419,-1619218070244699183,-1290540526775639182,-1001280480543716507,-920250991117702438,-37243485035014411,3109960451075183399,3577717700431629359,4854879008546753238,5736831950861882173,7673200081862847690], aRuleName_ = "matrix-comprehension-literal"} -LF: {"AnsweredRule":{"aRuleName_":"matrix-comprehension-literal","qAscendants_":[-8908244575740954826,-5683928670681234592,-5283973279755061591,-3518626964796470528,-1965680338567566419,-1619218070244699183,-1290540526775639182,-1001280480543716507,-920250991117702438,-37243485035014411,3109960451075183399,3577717700431629359,4854879008546753238,5736831950861882173,7673200081862847690],"qHole_":-7042519532359788232}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!or(flatten(1, [[q20[1] = conjure_aux4 | letting q20 be (3, 4)], [q20[1] = conjure_aux4 | letting q20 be (4, 3)]; int(1..2)])) <-> - conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: q20[1] - Context #1: q20[1] = conjure_aux4 - Context #2: [q20[1] = conjure_aux4 | letting q20 be (3, 4)] - Context #3: [[q20[1] = conjure_aux4 | letting q20 be (3, 4)], [q20[1] = conjure_aux4 | letting q20 be (4, 3)]; int(1..2)] - Context #4: flatten(1, [[q20[1] = conjure_aux4 | letting q20 be (3, 4)], [q20[1] = conjure_aux4 | letting q20 be (4, 3)]; int(1..2)]) - Context #5: or(flatten(1, - [[q20[1] = conjure_aux4 | letting q20 be (3, 4)], [q20[1] = conjure_aux4 | letting q20 be (4, 3)]; int(1..2)])) - Context #6: !or(flatten(1, - [[q20[1] = conjure_aux4 | letting q20 be (3, 4)], [q20[1] = conjure_aux4 | letting q20 be (4, 3)]; int(1..2)])) - Context #7: !or(flatten(1, - [[q20[1] = conjure_aux4 | letting q20 be (3, 4)], [q20[1] = conjure_aux4 | letting q20 be (4, 3)]; int(1..2)])) - <-> conjure_aux4 = q8_2 - Context #8: [and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])), - !or(flatten(1, [[q20[1] = conjure_aux4 | letting q20 be (3, 4)], [q20[1] = conjure_aux4 | letting q20 be (4, 3)]; int(1..2)])) <-> - conjure_aux4 = q8_2; - int(1..2)] - Context #9: and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!or(flatten(1, [[q20[1] = conjure_aux4 | letting q20 be (3, 4)], [q20[1] = conjure_aux4 | letting q20 be (4, 3)]; int(1..2)])) <-> - conjure_aux4 = q8_2) - Context #10: { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!or(flatten(1, [[q20[1] = conjure_aux4 | letting q20 be (3, 4)], [q20[1] = conjure_aux4 | letting q20 be (4, 3)]; int(1..2)])) <-> - conjure_aux4 = q8_2) - } - Context #11: conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!or(flatten(1, [[q20[1] = conjure_aux4 | letting q20 be (3, 4)], [q20[1] = conjure_aux4 | letting q20 be (4, 3)]; int(1..2)])) <-> - conjure_aux4 = q8_2) - } - Context #12: { conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!or(flatten(1, [[q20[1] = conjure_aux4 | letting q20 be (3, 4)], [q20[1] = conjure_aux4 | letting q20 be (4, 3)]; int(1..2)])) <-> - conjure_aux4 = q8_2) - } - } - Context #13: { conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!or(flatten(1, [[q20[1] = conjure_aux4 | letting q20 be (3, 4)], [q20[1] = conjure_aux4 | letting q20 be (4, 3)]; int(1..2)])) <-> - conjure_aux4 = q8_2) - } - } - in conjure_aux1 - Context #14: [{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!or(flatten(1, [[q20[1] = conjure_aux4 | letting q20 be (3, 4)], [q20[1] = conjure_aux4 | letting q20 be (4, 3)]; int(1..2)])) <-> - conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]] - Context #15: and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!or(flatten(1, [[q20[1] = conjure_aux4 | letting q20 be (3, 4)], [q20[1] = conjure_aux4 | letting q20 be (4, 3)]; int(1..2)])) <-> - conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - Context #16: [|x| = |conjure_aux1|, - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!or(flatten(1, [[q20[1] = conjure_aux4 | letting q20 be (3, 4)], [q20[1] = conjure_aux4 | letting q20 be (4, 3)]; int(1..2)])) <-> - conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]); - int(1..2)] - Context #17: |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!or(flatten(1, [[q20[1] = conjure_aux4 | letting q20 be (3, 4)], [q20[1] = conjure_aux4 | letting q20 be (4, 3)]; int(1..2)])) <-> - conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - Context #18: { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!or(flatten(1, [[q20[1] = conjure_aux4 | letting q20 be (3, 4)], [q20[1] = conjure_aux4 | letting q20 be (4, 3)]; int(1..2)])) <-> - conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - Context #19: y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!or(flatten(1, [[q20[1] = conjure_aux4 | letting q20 be (3, 4)], [q20[1] = conjure_aux4 | letting q20 be (4, 3)]; int(1..2)])) <-> - conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } -Picking the only option: Answer 1: full-evaluate: Full evaluator - 3 -storedChoice: -q20[1] -5066820997822192518 -AnsweredRule {qHole_ = -5066820997822192518, qAscendants_ = fromList [-8114810939578997179,-5955986499643421728,-5766477344136638660,-3619457499884836706,-3596989804158315723,-3512526206489503481,-2484614995521209041,-1748033148869835596,-58454364784882596,76873978234325305,2489610439802360191,3564003602712422871,3732529855370416098,3884465148016108231,4296494138735898078,4399359040184583027,4639251469994992570,7395797297508748841,7886700597594415296], aRuleName_ = "full-evaluate"} -LF: {"AnsweredRule":{"aRuleName_":"full-evaluate","qAscendants_":[-8114810939578997179,-5955986499643421728,-5766477344136638660,-3619457499884836706,-3596989804158315723,-3512526206489503481,-2484614995521209041,-1748033148869835596,-58454364784882596,76873978234325305,2489610439802360191,3564003602712422871,3732529855370416098,3884465148016108231,4296494138735898078,4399359040184583027,4639251469994992570,7395797297508748841,7886700597594415296],"qHole_":-5066820997822192518}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!or(flatten(1, [[3 = conjure_aux4 | letting q20 be (3, 4)], [q20[1] = conjure_aux4 | letting q20 be (4, 3)]; int(1..2)])) <-> - conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: q20[1] - Context #1: q20[1] = conjure_aux4 - Context #2: [q20[1] = conjure_aux4 | letting q20 be (4, 3)] - Context #3: [[3 = conjure_aux4 | letting q20 be (3, 4)], [q20[1] = conjure_aux4 | letting q20 be (4, 3)]; int(1..2)] - Context #4: flatten(1, [[3 = conjure_aux4 | letting q20 be (3, 4)], [q20[1] = conjure_aux4 | letting q20 be (4, 3)]; int(1..2)]) - Context #5: or(flatten(1, [[3 = conjure_aux4 | letting q20 be (3, 4)], [q20[1] = conjure_aux4 | letting q20 be (4, 3)]; int(1..2)])) - Context #6: !or(flatten(1, [[3 = conjure_aux4 | letting q20 be (3, 4)], [q20[1] = conjure_aux4 | letting q20 be (4, 3)]; int(1..2)])) - Context #7: !or(flatten(1, [[3 = conjure_aux4 | letting q20 be (3, 4)], [q20[1] = conjure_aux4 | letting q20 be (4, 3)]; int(1..2)])) - <-> conjure_aux4 = q8_2 - Context #8: [and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])), - !or(flatten(1, [[3 = conjure_aux4 | letting q20 be (3, 4)], [q20[1] = conjure_aux4 | letting q20 be (4, 3)]; int(1..2)])) <-> - conjure_aux4 = q8_2; - int(1..2)] - Context #9: and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!or(flatten(1, [[3 = conjure_aux4 | letting q20 be (3, 4)], [q20[1] = conjure_aux4 | letting q20 be (4, 3)]; int(1..2)])) <-> - conjure_aux4 = q8_2) - Context #10: { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!or(flatten(1, [[3 = conjure_aux4 | letting q20 be (3, 4)], [q20[1] = conjure_aux4 | letting q20 be (4, 3)]; int(1..2)])) <-> - conjure_aux4 = q8_2) - } - Context #11: conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!or(flatten(1, [[3 = conjure_aux4 | letting q20 be (3, 4)], [q20[1] = conjure_aux4 | letting q20 be (4, 3)]; int(1..2)])) <-> - conjure_aux4 = q8_2) - } - Context #12: { conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!or(flatten(1, [[3 = conjure_aux4 | letting q20 be (3, 4)], [q20[1] = conjure_aux4 | letting q20 be (4, 3)]; int(1..2)])) <-> - conjure_aux4 = q8_2) - } - } - Context #13: { conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!or(flatten(1, [[3 = conjure_aux4 | letting q20 be (3, 4)], [q20[1] = conjure_aux4 | letting q20 be (4, 3)]; int(1..2)])) <-> - conjure_aux4 = q8_2) - } - } - in conjure_aux1 - Context #14: [{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!or(flatten(1, [[3 = conjure_aux4 | letting q20 be (3, 4)], [q20[1] = conjure_aux4 | letting q20 be (4, 3)]; int(1..2)])) <-> - conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]] - Context #15: and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!or(flatten(1, [[3 = conjure_aux4 | letting q20 be (3, 4)], [q20[1] = conjure_aux4 | letting q20 be (4, 3)]; int(1..2)])) <-> - conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - Context #16: [|x| = |conjure_aux1|, - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!or(flatten(1, [[3 = conjure_aux4 | letting q20 be (3, 4)], [q20[1] = conjure_aux4 | letting q20 be (4, 3)]; int(1..2)])) <-> - conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]); - int(1..2)] - Context #17: |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!or(flatten(1, [[3 = conjure_aux4 | letting q20 be (3, 4)], [q20[1] = conjure_aux4 | letting q20 be (4, 3)]; int(1..2)])) <-> - conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - Context #18: { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!or(flatten(1, [[3 = conjure_aux4 | letting q20 be (3, 4)], [q20[1] = conjure_aux4 | letting q20 be (4, 3)]; int(1..2)])) <-> - conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - Context #19: y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!or(flatten(1, [[3 = conjure_aux4 | letting q20 be (3, 4)], [q20[1] = conjure_aux4 | letting q20 be (4, 3)]; int(1..2)])) <-> - conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } -Picking the only option: Answer 1: full-evaluate: Full evaluator - 4 -storedChoice: -q20[1] -5066820997822192518 -AnsweredRule {qHole_ = -5066820997822192518, qAscendants_ = fromList [-8725074021340919078,-8574349549577316045,-7990711773149197775,-7723660686298995374,-6875295913338400819,-5695102429637848602,-5273340809049818279,-3512526206489503481,-2862537938983036678,-2765562469061820724,-807453819412548209,-307031570223611599,37627954002053673,516678838692838411,3479854824023329968,6753745594226090750,8107007183604066764,8502378019651797201,9046378511697116254], aRuleName_ = "full-evaluate"} -LF: {"AnsweredRule":{"aRuleName_":"full-evaluate","qAscendants_":[-8725074021340919078,-8574349549577316045,-7990711773149197775,-7723660686298995374,-6875295913338400819,-5695102429637848602,-5273340809049818279,-3512526206489503481,-2862537938983036678,-2765562469061820724,-807453819412548209,-307031570223611599,37627954002053673,516678838692838411,3479854824023329968,6753745594226090750,8107007183604066764,8502378019651797201,9046378511697116254],"qHole_":-5066820997822192518}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!or(flatten(1, [[3 = conjure_aux4 | letting q20 be (3, 4)], [4 = conjure_aux4 | letting q20 be (4, 3)]; int(1..2)])) <-> - conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: [4 = conjure_aux4 | letting q20 be (4, 3)] - Context #1: [[3 = conjure_aux4 | letting q20 be (3, 4)], [4 = conjure_aux4 | letting q20 be (4, 3)]; int(1..2)] - Context #2: flatten(1, [[3 = conjure_aux4 | letting q20 be (3, 4)], [4 = conjure_aux4 | letting q20 be (4, 3)]; int(1..2)]) - Context #3: or(flatten(1, [[3 = conjure_aux4 | letting q20 be (3, 4)], [4 = conjure_aux4 | letting q20 be (4, 3)]; int(1..2)])) - Context #4: !or(flatten(1, [[3 = conjure_aux4 | letting q20 be (3, 4)], [4 = conjure_aux4 | letting q20 be (4, 3)]; int(1..2)])) - Context #5: !or(flatten(1, [[3 = conjure_aux4 | letting q20 be (3, 4)], [4 = conjure_aux4 | letting q20 be (4, 3)]; int(1..2)])) <-> - conjure_aux4 = q8_2 - Context #6: [and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])), - !or(flatten(1, [[3 = conjure_aux4 | letting q20 be (3, 4)], [4 = conjure_aux4 | letting q20 be (4, 3)]; int(1..2)])) <-> - conjure_aux4 = q8_2; - int(1..2)] - Context #7: and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!or(flatten(1, [[3 = conjure_aux4 | letting q20 be (3, 4)], [4 = conjure_aux4 | letting q20 be (4, 3)]; int(1..2)])) <-> - conjure_aux4 = q8_2) - Context #8: { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!or(flatten(1, [[3 = conjure_aux4 | letting q20 be (3, 4)], [4 = conjure_aux4 | letting q20 be (4, 3)]; int(1..2)])) <-> - conjure_aux4 = q8_2) - } - Context #9: conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!or(flatten(1, [[3 = conjure_aux4 | letting q20 be (3, 4)], [4 = conjure_aux4 | letting q20 be (4, 3)]; int(1..2)])) <-> - conjure_aux4 = q8_2) - } - Context #10: { conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!or(flatten(1, [[3 = conjure_aux4 | letting q20 be (3, 4)], [4 = conjure_aux4 | letting q20 be (4, 3)]; int(1..2)])) <-> - conjure_aux4 = q8_2) - } - } - Context #11: { conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!or(flatten(1, [[3 = conjure_aux4 | letting q20 be (3, 4)], [4 = conjure_aux4 | letting q20 be (4, 3)]; int(1..2)])) <-> - conjure_aux4 = q8_2) - } - } - in conjure_aux1 - Context #12: [{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!or(flatten(1, [[3 = conjure_aux4 | letting q20 be (3, 4)], [4 = conjure_aux4 | letting q20 be (4, 3)]; int(1..2)])) <-> - conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]] - Context #13: and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!or(flatten(1, [[3 = conjure_aux4 | letting q20 be (3, 4)], [4 = conjure_aux4 | letting q20 be (4, 3)]; int(1..2)])) <-> - conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - Context #14: [|x| = |conjure_aux1|, - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!or(flatten(1, [[3 = conjure_aux4 | letting q20 be (3, 4)], [4 = conjure_aux4 | letting q20 be (4, 3)]; int(1..2)])) <-> - conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]); - int(1..2)] - Context #15: |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!or(flatten(1, [[3 = conjure_aux4 | letting q20 be (3, 4)], [4 = conjure_aux4 | letting q20 be (4, 3)]; int(1..2)])) <-> - conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - Context #16: { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!or(flatten(1, [[3 = conjure_aux4 | letting q20 be (3, 4)], [4 = conjure_aux4 | letting q20 be (4, 3)]; int(1..2)])) <-> - conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - Context #17: y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!or(flatten(1, [[3 = conjure_aux4 | letting q20 be (3, 4)], [4 = conjure_aux4 | letting q20 be (4, 3)]; int(1..2)])) <-> - conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } -Picking the only option: Answer 1: generators-first: Inlining comprehension lettings. - [4 = conjure_aux4 |] -storedChoice: -[4 = conjure_aux4 | letting q20 be (4, 3)] -4659269292751863231 -AnsweredRule {qHole_ = -4659269292751863231, qAscendants_ = fromList [-8139107762275405780,-6067050360933011415,-4668927100952759839,-2832336555945972970,-2685263499350289956,-712998101401819851,-662867422474666417,-634413128047463436,1314890692039055455,1461492958057141352,1536420920342600247,1612507314243025908,6104410666907258834,6818646762744932078,7002085677101186921,7870098581639353518,8074964079189467219], aRuleName_ = "generators-first"} -LF: {"AnsweredRule":{"aRuleName_":"generators-first","qAscendants_":[-8139107762275405780,-6067050360933011415,-4668927100952759839,-2832336555945972970,-2685263499350289956,-712998101401819851,-662867422474666417,-634413128047463436,1314890692039055455,1461492958057141352,1536420920342600247,1612507314243025908,6104410666907258834,6818646762744932078,7002085677101186921,7870098581639353518,8074964079189467219],"qHole_":-4659269292751863231}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!or(flatten(1, [[3 = conjure_aux4 | letting q20 be (3, 4)], [4 = conjure_aux4 |]; int(1..2)])) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: [4 = conjure_aux4 |] - Context #1: [[3 = conjure_aux4 | letting q20 be (3, 4)], [4 = conjure_aux4 |]; int(1..2)] - Context #2: flatten(1, [[3 = conjure_aux4 | letting q20 be (3, 4)], [4 = conjure_aux4 |]; int(1..2)]) - Context #3: or(flatten(1, [[3 = conjure_aux4 | letting q20 be (3, 4)], [4 = conjure_aux4 |]; int(1..2)])) - Context #4: !or(flatten(1, [[3 = conjure_aux4 | letting q20 be (3, 4)], [4 = conjure_aux4 |]; int(1..2)])) - Context #5: !or(flatten(1, [[3 = conjure_aux4 | letting q20 be (3, 4)], [4 = conjure_aux4 |]; int(1..2)])) <-> conjure_aux4 = q8_2 - Context #6: [and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])), - !or(flatten(1, [[3 = conjure_aux4 | letting q20 be (3, 4)], [4 = conjure_aux4 |]; int(1..2)])) <-> conjure_aux4 = q8_2; - int(1..2)] - Context #7: and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!or(flatten(1, [[3 = conjure_aux4 | letting q20 be (3, 4)], [4 = conjure_aux4 |]; int(1..2)])) <-> conjure_aux4 = q8_2) - Context #8: { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!or(flatten(1, [[3 = conjure_aux4 | letting q20 be (3, 4)], [4 = conjure_aux4 |]; int(1..2)])) <-> conjure_aux4 = q8_2) - } - Context #9: conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!or(flatten(1, [[3 = conjure_aux4 | letting q20 be (3, 4)], [4 = conjure_aux4 |]; int(1..2)])) <-> conjure_aux4 = q8_2) - } - Context #10: { conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!or(flatten(1, [[3 = conjure_aux4 | letting q20 be (3, 4)], [4 = conjure_aux4 |]; int(1..2)])) <-> conjure_aux4 = q8_2) - } - } - Context #11: { conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!or(flatten(1, [[3 = conjure_aux4 | letting q20 be (3, 4)], [4 = conjure_aux4 |]; int(1..2)])) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - Context #12: [{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!or(flatten(1, [[3 = conjure_aux4 | letting q20 be (3, 4)], [4 = conjure_aux4 |]; int(1..2)])) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]] - Context #13: and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!or(flatten(1, [[3 = conjure_aux4 | letting q20 be (3, 4)], [4 = conjure_aux4 |]; int(1..2)])) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - Context #14: [|x| = |conjure_aux1|, - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!or(flatten(1, [[3 = conjure_aux4 | letting q20 be (3, 4)], [4 = conjure_aux4 |]; int(1..2)])) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]); - int(1..2)] - Context #15: |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!or(flatten(1, [[3 = conjure_aux4 | letting q20 be (3, 4)], [4 = conjure_aux4 |]; int(1..2)])) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - Context #16: { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!or(flatten(1, [[3 = conjure_aux4 | letting q20 be (3, 4)], [4 = conjure_aux4 |]; int(1..2)])) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - Context #17: y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!or(flatten(1, [[3 = conjure_aux4 | letting q20 be (3, 4)], [4 = conjure_aux4 |]; int(1..2)])) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } -Picking the only option: Answer 1: generators-first: Empty generators. - [4 = conjure_aux4; int(1)] -storedChoice: -[4 = conjure_aux4 |] 3103944569848083730 -AnsweredRule {qHole_ = 3103944569848083730, qAscendants_ = fromList [-6499292278244277577,-5447382347614094034,-3901800536920366688,-3381517728243229044,-2903466984087021575,-1629155788585143592,-595707724612505928,-531462185798445081,-436711175201990026,-305874969643107400,713364048257302949,3760728491479375708,4192007196113212495,5520591029544627590,7106210168219555744,7226177407162985748,8785470622724542357], aRuleName_ = "generators-first"} -LF: {"AnsweredRule":{"aRuleName_":"generators-first","qAscendants_":[-6499292278244277577,-5447382347614094034,-3901800536920366688,-3381517728243229044,-2903466984087021575,-1629155788585143592,-595707724612505928,-531462185798445081,-436711175201990026,-305874969643107400,713364048257302949,3760728491479375708,4192007196113212495,5520591029544627590,7106210168219555744,7226177407162985748,8785470622724542357],"qHole_":3103944569848083730}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!or(flatten(1, [[3 = conjure_aux4 | letting q20 be (3, 4)], [4 = conjure_aux4; int(1)]; int(1..2)])) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: [3 = conjure_aux4 | letting q20 be (3, 4)] - Context #1: [[3 = conjure_aux4 | letting q20 be (3, 4)], [4 = conjure_aux4; int(1)]; int(1..2)] - Context #2: flatten(1, [[3 = conjure_aux4 | letting q20 be (3, 4)], [4 = conjure_aux4; int(1)]; int(1..2)]) - Context #3: or(flatten(1, [[3 = conjure_aux4 | letting q20 be (3, 4)], [4 = conjure_aux4; int(1)]; int(1..2)])) - Context #4: !or(flatten(1, [[3 = conjure_aux4 | letting q20 be (3, 4)], [4 = conjure_aux4; int(1)]; int(1..2)])) - Context #5: !or(flatten(1, [[3 = conjure_aux4 | letting q20 be (3, 4)], [4 = conjure_aux4; int(1)]; int(1..2)])) <-> - conjure_aux4 = q8_2 - Context #6: [and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])), - !or(flatten(1, [[3 = conjure_aux4 | letting q20 be (3, 4)], [4 = conjure_aux4; int(1)]; int(1..2)])) <-> conjure_aux4 = q8_2; - int(1..2)] - Context #7: and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!or(flatten(1, [[3 = conjure_aux4 | letting q20 be (3, 4)], [4 = conjure_aux4; int(1)]; int(1..2)])) <-> conjure_aux4 = q8_2) - Context #8: { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!or(flatten(1, [[3 = conjure_aux4 | letting q20 be (3, 4)], [4 = conjure_aux4; int(1)]; int(1..2)])) <-> conjure_aux4 = q8_2) - } - Context #9: conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!or(flatten(1, [[3 = conjure_aux4 | letting q20 be (3, 4)], [4 = conjure_aux4; int(1)]; int(1..2)])) <-> conjure_aux4 = q8_2) - } - Context #10: { conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!or(flatten(1, [[3 = conjure_aux4 | letting q20 be (3, 4)], [4 = conjure_aux4; int(1)]; int(1..2)])) <-> conjure_aux4 = q8_2) - } - } - Context #11: { conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!or(flatten(1, [[3 = conjure_aux4 | letting q20 be (3, 4)], [4 = conjure_aux4; int(1)]; int(1..2)])) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - Context #12: [{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!or(flatten(1, [[3 = conjure_aux4 | letting q20 be (3, 4)], [4 = conjure_aux4; int(1)]; int(1..2)])) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]] - Context #13: and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!or(flatten(1, [[3 = conjure_aux4 | letting q20 be (3, 4)], [4 = conjure_aux4; int(1)]; int(1..2)])) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - Context #14: [|x| = |conjure_aux1|, - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!or(flatten(1, [[3 = conjure_aux4 | letting q20 be (3, 4)], [4 = conjure_aux4; int(1)]; int(1..2)])) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]); - int(1..2)] - Context #15: |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!or(flatten(1, [[3 = conjure_aux4 | letting q20 be (3, 4)], [4 = conjure_aux4; int(1)]; int(1..2)])) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - Context #16: { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!or(flatten(1, [[3 = conjure_aux4 | letting q20 be (3, 4)], [4 = conjure_aux4; int(1)]; int(1..2)])) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - Context #17: y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!or(flatten(1, [[3 = conjure_aux4 | letting q20 be (3, 4)], [4 = conjure_aux4; int(1)]; int(1..2)])) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } -Picking the only option: Answer 1: generators-first: Inlining comprehension lettings. - [3 = conjure_aux4 |] -storedChoice: -[3 = conjure_aux4 | letting q20 be (3, 4)] -6255934535417186594 -AnsweredRule {qHole_ = -6255934535417186594, qAscendants_ = fromList [-7136276057455168685,-7072459974569890512,-6196259248273364037,-5834210587143255228,-2665342865711637679,-1906879012656170539,-1522455433242873900,752122676500601510,1351313430292206143,2164743633705935677,2917302706197316348,3522536415221397176,3844998889588585321,5240671478404014136,7264763306810372171,7563078030555210243,8716248641960869542], aRuleName_ = "generators-first"} -LF: {"AnsweredRule":{"aRuleName_":"generators-first","qAscendants_":[-7136276057455168685,-7072459974569890512,-6196259248273364037,-5834210587143255228,-2665342865711637679,-1906879012656170539,-1522455433242873900,752122676500601510,1351313430292206143,2164743633705935677,2917302706197316348,3522536415221397176,3844998889588585321,5240671478404014136,7264763306810372171,7563078030555210243,8716248641960869542],"qHole_":-6255934535417186594}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!or(flatten(1, [[3 = conjure_aux4 |], [4 = conjure_aux4; int(1)]; int(1..2)])) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: [3 = conjure_aux4 |] - Context #1: [[3 = conjure_aux4 |], [4 = conjure_aux4; int(1)]; int(1..2)] - Context #2: flatten(1, [[3 = conjure_aux4 |], [4 = conjure_aux4; int(1)]; int(1..2)]) - Context #3: or(flatten(1, [[3 = conjure_aux4 |], [4 = conjure_aux4; int(1)]; int(1..2)])) - Context #4: !or(flatten(1, [[3 = conjure_aux4 |], [4 = conjure_aux4; int(1)]; int(1..2)])) - Context #5: !or(flatten(1, [[3 = conjure_aux4 |], [4 = conjure_aux4; int(1)]; int(1..2)])) <-> conjure_aux4 = q8_2 - Context #6: [and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])), - !or(flatten(1, [[3 = conjure_aux4 |], [4 = conjure_aux4; int(1)]; int(1..2)])) <-> conjure_aux4 = q8_2; - int(1..2)] - Context #7: and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!or(flatten(1, [[3 = conjure_aux4 |], [4 = conjure_aux4; int(1)]; int(1..2)])) <-> conjure_aux4 = q8_2) - Context #8: { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!or(flatten(1, [[3 = conjure_aux4 |], [4 = conjure_aux4; int(1)]; int(1..2)])) <-> conjure_aux4 = q8_2) - } - Context #9: conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!or(flatten(1, [[3 = conjure_aux4 |], [4 = conjure_aux4; int(1)]; int(1..2)])) <-> conjure_aux4 = q8_2) - } - Context #10: { conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!or(flatten(1, [[3 = conjure_aux4 |], [4 = conjure_aux4; int(1)]; int(1..2)])) <-> conjure_aux4 = q8_2) - } - } - Context #11: { conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!or(flatten(1, [[3 = conjure_aux4 |], [4 = conjure_aux4; int(1)]; int(1..2)])) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - Context #12: [{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!or(flatten(1, [[3 = conjure_aux4 |], [4 = conjure_aux4; int(1)]; int(1..2)])) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]] - Context #13: and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!or(flatten(1, [[3 = conjure_aux4 |], [4 = conjure_aux4; int(1)]; int(1..2)])) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - Context #14: [|x| = |conjure_aux1|, - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!or(flatten(1, [[3 = conjure_aux4 |], [4 = conjure_aux4; int(1)]; int(1..2)])) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]); - int(1..2)] - Context #15: |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!or(flatten(1, [[3 = conjure_aux4 |], [4 = conjure_aux4; int(1)]; int(1..2)])) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - Context #16: { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!or(flatten(1, [[3 = conjure_aux4 |], [4 = conjure_aux4; int(1)]; int(1..2)])) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - Context #17: y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!or(flatten(1, [[3 = conjure_aux4 |], [4 = conjure_aux4; int(1)]; int(1..2)])) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } -Picking the only option: Answer 1: generators-first: Empty generators. - [3 = conjure_aux4; int(1)] -storedChoice: -[3 = conjure_aux4 |] -2658614992963116405 -AnsweredRule {qHole_ = -2658614992963116405, qAscendants_ = fromList [-8200797483737906583,-7142891394430515063,-5048865527690557400,-3204141723258765628,-2755421715163082104,-2150417528239571907,-427238415401958863,345854652969155162,444587743724873706,1433275916120849547,2082716253070264500,3621608353720498501,3817394469011428558,4338626750910725978,6129719379140106144,6899422834286368127,8748622476088678609], aRuleName_ = "generators-first"} -LF: {"AnsweredRule":{"aRuleName_":"generators-first","qAscendants_":[-8200797483737906583,-7142891394430515063,-5048865527690557400,-3204141723258765628,-2755421715163082104,-2150417528239571907,-427238415401958863,345854652969155162,444587743724873706,1433275916120849547,2082716253070264500,3621608353720498501,3817394469011428558,4338626750910725978,6129719379140106144,6899422834286368127,8748622476088678609],"qHole_":-2658614992963116405}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!or(flatten(1, [[3 = conjure_aux4; int(1)], [4 = conjure_aux4; int(1)]; int(1..2)])) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: or(flatten(1, [[3 = conjure_aux4; int(1)], [4 = conjure_aux4; int(1)]; int(1..2)])) - Context #1: !or(flatten(1, [[3 = conjure_aux4; int(1)], [4 = conjure_aux4; int(1)]; int(1..2)])) - Context #2: !or(flatten(1, [[3 = conjure_aux4; int(1)], [4 = conjure_aux4; int(1)]; int(1..2)])) <-> conjure_aux4 = q8_2 - Context #3: [and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])), - !or(flatten(1, [[3 = conjure_aux4; int(1)], [4 = conjure_aux4; int(1)]; int(1..2)])) <-> conjure_aux4 = q8_2; - int(1..2)] - Context #4: and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!or(flatten(1, [[3 = conjure_aux4; int(1)], [4 = conjure_aux4; int(1)]; int(1..2)])) <-> conjure_aux4 = q8_2) - Context #5: { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!or(flatten(1, [[3 = conjure_aux4; int(1)], [4 = conjure_aux4; int(1)]; int(1..2)])) <-> conjure_aux4 = q8_2) - } - Context #6: conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!or(flatten(1, [[3 = conjure_aux4; int(1)], [4 = conjure_aux4; int(1)]; int(1..2)])) <-> conjure_aux4 = q8_2) - } - Context #7: { conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!or(flatten(1, [[3 = conjure_aux4; int(1)], [4 = conjure_aux4; int(1)]; int(1..2)])) <-> conjure_aux4 = q8_2) - } - } - Context #8: { conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!or(flatten(1, [[3 = conjure_aux4; int(1)], [4 = conjure_aux4; int(1)]; int(1..2)])) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - Context #9: [{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!or(flatten(1, [[3 = conjure_aux4; int(1)], [4 = conjure_aux4; int(1)]; int(1..2)])) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]] - Context #10: and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!or(flatten(1, [[3 = conjure_aux4; int(1)], [4 = conjure_aux4; int(1)]; int(1..2)])) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - Context #11: [|x| = |conjure_aux1|, - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!or(flatten(1, [[3 = conjure_aux4; int(1)], [4 = conjure_aux4; int(1)]; int(1..2)])) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]); - int(1..2)] - Context #12: |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!or(flatten(1, [[3 = conjure_aux4; int(1)], [4 = conjure_aux4; int(1)]; int(1..2)])) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - Context #13: { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!or(flatten(1, [[3 = conjure_aux4; int(1)], [4 = conjure_aux4; int(1)]; int(1..2)])) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - Context #14: y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!or(flatten(1, [[3 = conjure_aux4; int(1)], [4 = conjure_aux4; int(1)]; int(1..2)])) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } -Picking the only option: Answer 1: quantifier-shift3: Shifting quantifier inwards - or([3 = conjure_aux4; int(1)]) \/ or([4 = conjure_aux4; int(1)]) -storedChoice: -or(flatten(1, [[3 = conjure_aux4; int(1)], [4 = conjure_aux4; int(1)]; int(1..2)])) 1792302133485940861 -AnsweredRule {qHole_ = 1792302133485940861, qAscendants_ = fromList [-9215156694345218491,-7884159941367425225,-4061787575651201278,-2348548688413524686,-1616656984063374174,1019247903219888070,1202444192825383566,2448039896892401119,2522006493315280277,2872569756943491545,3292387117872397760,5871641527667180654,6531511286127386564,8891172200144465433], aRuleName_ = "quantifier-shift3"} -LF: {"AnsweredRule":{"aRuleName_":"quantifier-shift3","qAscendants_":[-9215156694345218491,-7884159941367425225,-4061787575651201278,-2348548688413524686,-1616656984063374174,1019247903219888070,1202444192825383566,2448039896892401119,2522006493315280277,2872569756943491545,3292387117872397760,5871641527667180654,6531511286127386564,8891172200144465433],"qHole_":1792302133485940861}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!(or([3 = conjure_aux4; int(1)]) \/ or([4 = conjure_aux4; int(1)])) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: or([3 = conjure_aux4; int(1)]) - Context #1: [or([3 = conjure_aux4; int(1)]), or([4 = conjure_aux4; int(1)]); int(1..2)] - Context #2: or([3 = conjure_aux4; int(1)]) \/ or([4 = conjure_aux4; int(1)]) - Context #3: !(or([3 = conjure_aux4; int(1)]) \/ or([4 = conjure_aux4; int(1)])) - Context #4: !(or([3 = conjure_aux4; int(1)]) \/ or([4 = conjure_aux4; int(1)])) <-> conjure_aux4 = q8_2 - Context #5: [and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])), - !(or([3 = conjure_aux4; int(1)]) \/ or([4 = conjure_aux4; int(1)])) <-> conjure_aux4 = q8_2; - int(1..2)] - Context #6: and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!(or([3 = conjure_aux4; int(1)]) \/ or([4 = conjure_aux4; int(1)])) <-> conjure_aux4 = q8_2) - Context #7: { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!(or([3 = conjure_aux4; int(1)]) \/ or([4 = conjure_aux4; int(1)])) <-> conjure_aux4 = q8_2) - } - Context #8: conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!(or([3 = conjure_aux4; int(1)]) \/ or([4 = conjure_aux4; int(1)])) <-> conjure_aux4 = q8_2) - } - Context #9: { conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!(or([3 = conjure_aux4; int(1)]) \/ or([4 = conjure_aux4; int(1)])) <-> conjure_aux4 = q8_2) - } - } - Context #10: { conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!(or([3 = conjure_aux4; int(1)]) \/ or([4 = conjure_aux4; int(1)])) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - Context #11: [{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!(or([3 = conjure_aux4; int(1)]) \/ or([4 = conjure_aux4; int(1)])) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]] - Context #12: and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!(or([3 = conjure_aux4; int(1)]) \/ or([4 = conjure_aux4; int(1)])) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - Context #13: [|x| = |conjure_aux1|, - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!(or([3 = conjure_aux4; int(1)]) \/ or([4 = conjure_aux4; int(1)])) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]); - int(1..2)] - Context #14: |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!(or([3 = conjure_aux4; int(1)]) \/ or([4 = conjure_aux4; int(1)])) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - Context #15: { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!(or([3 = conjure_aux4; int(1)]) \/ or([4 = conjure_aux4; int(1)])) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - Context #16: y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!(or([3 = conjure_aux4; int(1)]) \/ or([4 = conjure_aux4; int(1)])) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } -Picking the only option: Answer 1: matrix-comprehension-singleton: Removing quantifier of a single item - 3 = conjure_aux4 -storedChoice: -or([3 = conjure_aux4; int(1)]) -2238338300082489653 -AnsweredRule {qHole_ = -2238338300082489653, qAscendants_ = fromList [-9135090969161870748,-7040580929681195434,-5844866756595959210,-5200489563969105483,-5135428809631204876,-4567662440315024812,-2637178807861984772,-1043830869774709897,117930584853289771,1197239461988022471,4464393825362555947,5063705836807996732,5078493517063792951,6402729242588877157,6830536617247247401,7925032212346973439], aRuleName_ = "matrix-comprehension-singleton"} -LF: {"AnsweredRule":{"aRuleName_":"matrix-comprehension-singleton","qAscendants_":[-9135090969161870748,-7040580929681195434,-5844866756595959210,-5200489563969105483,-5135428809631204876,-4567662440315024812,-2637178807861984772,-1043830869774709897,117930584853289771,1197239461988022471,4464393825362555947,5063705836807996732,5078493517063792951,6402729242588877157,6830536617247247401,7925032212346973439],"qHole_":-2238338300082489653}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!(3 = conjure_aux4 \/ or([4 = conjure_aux4; int(1)])) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: or([4 = conjure_aux4; int(1)]) - Context #1: [3 = conjure_aux4, or([4 = conjure_aux4; int(1)]); int(1..2)] - Context #2: 3 = conjure_aux4 \/ or([4 = conjure_aux4; int(1)]) - Context #3: !(3 = conjure_aux4 \/ or([4 = conjure_aux4; int(1)])) - Context #4: !(3 = conjure_aux4 \/ or([4 = conjure_aux4; int(1)])) <-> conjure_aux4 = q8_2 - Context #5: [and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])), - !(3 = conjure_aux4 \/ or([4 = conjure_aux4; int(1)])) <-> conjure_aux4 = q8_2; - int(1..2)] - Context #6: and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!(3 = conjure_aux4 \/ or([4 = conjure_aux4; int(1)])) <-> conjure_aux4 = q8_2) - Context #7: { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!(3 = conjure_aux4 \/ or([4 = conjure_aux4; int(1)])) <-> conjure_aux4 = q8_2) - } - Context #8: conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!(3 = conjure_aux4 \/ or([4 = conjure_aux4; int(1)])) <-> conjure_aux4 = q8_2) - } - Context #9: { conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!(3 = conjure_aux4 \/ or([4 = conjure_aux4; int(1)])) <-> conjure_aux4 = q8_2) - } - } - Context #10: { conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!(3 = conjure_aux4 \/ or([4 = conjure_aux4; int(1)])) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - Context #11: [{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!(3 = conjure_aux4 \/ or([4 = conjure_aux4; int(1)])) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]] - Context #12: and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!(3 = conjure_aux4 \/ or([4 = conjure_aux4; int(1)])) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - Context #13: [|x| = |conjure_aux1|, - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!(3 = conjure_aux4 \/ or([4 = conjure_aux4; int(1)])) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]); - int(1..2)] - Context #14: |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!(3 = conjure_aux4 \/ or([4 = conjure_aux4; int(1)])) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - Context #15: { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!(3 = conjure_aux4 \/ or([4 = conjure_aux4; int(1)])) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - Context #16: y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!(3 = conjure_aux4 \/ or([4 = conjure_aux4; int(1)])) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } -Picking the only option: Answer 1: matrix-comprehension-singleton: Removing quantifier of a single item - 4 = conjure_aux4 -storedChoice: -or([4 = conjure_aux4; int(1)]) 6931996324238769216 -AnsweredRule {qHole_ = 6931996324238769216, qAscendants_ = fromList [-8301199506799591941,-7558092101252853604,-6067998700973920226,-5155701249953128914,-4576047313272360415,-4347126985617275804,-2751859814401093547,137469789217709822,144729713112841205,2146657550292868874,3729312864595267230,4118600647582069537,4766806173317946186,4942755527663293565,6086894017411589008,8428538202899570704], aRuleName_ = "matrix-comprehension-singleton"} -LF: {"AnsweredRule":{"aRuleName_":"matrix-comprehension-singleton","qAscendants_":[-8301199506799591941,-7558092101252853604,-6067998700973920226,-5155701249953128914,-4576047313272360415,-4347126985617275804,-2751859814401093547,137469789217709822,144729713112841205,2146657550292868874,3729312864595267230,4118600647582069537,4766806173317946186,4942755527663293565,6086894017411589008,8428538202899570704],"qHole_":6931996324238769216}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: and(flatten(1, - [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) - Context #1: [and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])), - !(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2; - int(1..2)] - Context #2: and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) - Context #3: { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) - } - Context #4: conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) - } - Context #5: { conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) - } - } - Context #6: { conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - Context #7: [{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]] - Context #8: and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - Context #9: [|x| = |conjure_aux1|, - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]); - int(1..2)] - Context #10: |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - Context #11: { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - Context #12: y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } -Picking the only option: Answer 1: quantifier-shift3: Shifting quantifier inwards - and([3 = q8_2 <-> conjure_aux4 = 4; int(1)]) /\ and([4 = q8_2 <-> conjure_aux4 = 3; int(1)]) -storedChoice: -and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) 6498896587051443094 -AnsweredRule {qHole_ = 6498896587051443094, qAscendants_ = fromList [-9122266668816456873,-8763687680398485956,-6768148177044187855,-5775912378426088215,-3542921895788471154,-2263838003336096906,-202295424977994982,851884620329916301,5528267415991175666,6533818616419587005,7566808087161406219,8046934030769361906], aRuleName_ = "quantifier-shift3"} -LF: {"AnsweredRule":{"aRuleName_":"quantifier-shift3","qAscendants_":[-9122266668816456873,-8763687680398485956,-6768148177044187855,-5775912378426088215,-3542921895788471154,-2263838003336096906,-202295424977994982,851884620329916301,5528267415991175666,6533818616419587005,7566808087161406219,8046934030769361906],"qHole_":6498896587051443094}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and([3 = q8_2 <-> conjure_aux4 = 4; int(1)]) /\ and([4 = q8_2 <-> conjure_aux4 = 3; int(1)]) /\ - (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: and([3 = q8_2 <-> conjure_aux4 = 4; int(1)]) - Context #1: [and([3 = q8_2 <-> conjure_aux4 = 4; int(1)]), and([4 = q8_2 <-> conjure_aux4 = 3; int(1)]); int(1..2)] - Context #2: and([3 = q8_2 <-> conjure_aux4 = 4; int(1)]) /\ and([4 = q8_2 <-> conjure_aux4 = 3; int(1)]) - Context #3: [and([3 = q8_2 <-> conjure_aux4 = 4; int(1)]) /\ and([4 = q8_2 <-> conjure_aux4 = 3; int(1)]), - !(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2; - int(1..2)] - Context #4: and([3 = q8_2 <-> conjure_aux4 = 4; int(1)]) /\ and([4 = q8_2 <-> conjure_aux4 = 3; int(1)]) /\ - (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) - Context #5: { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and([3 = q8_2 <-> conjure_aux4 = 4; int(1)]) /\ and([4 = q8_2 <-> conjure_aux4 = 3; int(1)]) /\ - (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) - } - Context #6: conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and([3 = q8_2 <-> conjure_aux4 = 4; int(1)]) /\ and([4 = q8_2 <-> conjure_aux4 = 3; int(1)]) /\ - (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) - } - Context #7: { conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and([3 = q8_2 <-> conjure_aux4 = 4; int(1)]) /\ and([4 = q8_2 <-> conjure_aux4 = 3; int(1)]) /\ - (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) - } - } - Context #8: { conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and([3 = q8_2 <-> conjure_aux4 = 4; int(1)]) /\ and([4 = q8_2 <-> conjure_aux4 = 3; int(1)]) /\ - (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - Context #9: [{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and([3 = q8_2 <-> conjure_aux4 = 4; int(1)]) /\ and([4 = q8_2 <-> conjure_aux4 = 3; int(1)]) /\ - (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]] - Context #10: and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and([3 = q8_2 <-> conjure_aux4 = 4; int(1)]) /\ and([4 = q8_2 <-> conjure_aux4 = 3; int(1)]) /\ - (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - Context #11: [|x| = |conjure_aux1|, - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and([3 = q8_2 <-> conjure_aux4 = 4; int(1)]) /\ and([4 = q8_2 <-> conjure_aux4 = 3; int(1)]) /\ - (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]); - int(1..2)] - Context #12: |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and([3 = q8_2 <-> conjure_aux4 = 4; int(1)]) /\ and([4 = q8_2 <-> conjure_aux4 = 3; int(1)]) /\ - (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - Context #13: { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and([3 = q8_2 <-> conjure_aux4 = 4; int(1)]) /\ and([4 = q8_2 <-> conjure_aux4 = 3; int(1)]) /\ - (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - Context #14: y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and([3 = q8_2 <-> conjure_aux4 = 4; int(1)]) /\ and([4 = q8_2 <-> conjure_aux4 = 3; int(1)]) /\ - (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } -Picking the only option: Answer 1: matrix-comprehension-singleton: Removing quantifier of a single item - 3 = q8_2 <-> conjure_aux4 = 4 -storedChoice: -and([3 = q8_2 <-> conjure_aux4 = 4; int(1)]) 4625414366441981983 -AnsweredRule {qHole_ = 4625414366441981983, qAscendants_ = fromList [-5032104045245797729,-4260367211447941052,-3800321491279460974,-3527728036515378511,-3186771756499085870,-2663126455000061452,-2397177437658285933,-953818733459672679,51316433765895449,382670796215945555,1275044521375561569,2333080611421701721,2485864324914475150,5509053191108998898], aRuleName_ = "matrix-comprehension-singleton"} -LF: {"AnsweredRule":{"aRuleName_":"matrix-comprehension-singleton","qAscendants_":[-5032104045245797729,-4260367211447941052,-3800321491279460974,-3527728036515378511,-3186771756499085870,-2663126455000061452,-2397177437658285933,-953818733459672679,51316433765895449,382670796215945555,1275044521375561569,2333080611421701721,2485864324914475150,5509053191108998898],"qHole_":4625414366441981983}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - (3 = q8_2 <-> conjure_aux4 = 4) /\ and([4 = q8_2 <-> conjure_aux4 = 3; int(1)]) /\ - (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: and([4 = q8_2 <-> conjure_aux4 = 3; int(1)]) - Context #1: [3 = q8_2 <-> conjure_aux4 = 4, and([4 = q8_2 <-> conjure_aux4 = 3; int(1)]); int(1..2)] - Context #2: (3 = q8_2 <-> conjure_aux4 = 4) /\ and([4 = q8_2 <-> conjure_aux4 = 3; int(1)]) - Context #3: [(3 = q8_2 <-> conjure_aux4 = 4) /\ and([4 = q8_2 <-> conjure_aux4 = 3; int(1)]), - !(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2; - int(1..2)] - Context #4: (3 = q8_2 <-> conjure_aux4 = 4) /\ and([4 = q8_2 <-> conjure_aux4 = 3; int(1)]) /\ - (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) - Context #5: { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - (3 = q8_2 <-> conjure_aux4 = 4) /\ and([4 = q8_2 <-> conjure_aux4 = 3; int(1)]) /\ - (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) - } - Context #6: conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - (3 = q8_2 <-> conjure_aux4 = 4) /\ and([4 = q8_2 <-> conjure_aux4 = 3; int(1)]) /\ - (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) - } - Context #7: { conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - (3 = q8_2 <-> conjure_aux4 = 4) /\ and([4 = q8_2 <-> conjure_aux4 = 3; int(1)]) /\ - (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) - } - } - Context #8: { conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - (3 = q8_2 <-> conjure_aux4 = 4) /\ and([4 = q8_2 <-> conjure_aux4 = 3; int(1)]) /\ - (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - Context #9: [{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - (3 = q8_2 <-> conjure_aux4 = 4) /\ and([4 = q8_2 <-> conjure_aux4 = 3; int(1)]) /\ - (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]] - Context #10: and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - (3 = q8_2 <-> conjure_aux4 = 4) /\ and([4 = q8_2 <-> conjure_aux4 = 3; int(1)]) /\ - (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - Context #11: [|x| = |conjure_aux1|, - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - (3 = q8_2 <-> conjure_aux4 = 4) /\ and([4 = q8_2 <-> conjure_aux4 = 3; int(1)]) /\ - (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]); - int(1..2)] - Context #12: |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - (3 = q8_2 <-> conjure_aux4 = 4) /\ and([4 = q8_2 <-> conjure_aux4 = 3; int(1)]) /\ - (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - Context #13: { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - (3 = q8_2 <-> conjure_aux4 = 4) /\ and([4 = q8_2 <-> conjure_aux4 = 3; int(1)]) /\ - (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - Context #14: y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - (3 = q8_2 <-> conjure_aux4 = 4) /\ and([4 = q8_2 <-> conjure_aux4 = 3; int(1)]) /\ - (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } -Picking the only option: Answer 1: matrix-comprehension-singleton: Removing quantifier of a single item - 4 = q8_2 <-> conjure_aux4 = 3 -storedChoice: -and([4 = q8_2 <-> conjure_aux4 = 3; int(1)]) -8650590815054601249 -AnsweredRule {qHole_ = -8650590815054601249, qAscendants_ = fromList [-7526881736718068312,-7405557604309373817,-7201686808491642883,-6330762734028692340,-5804239247306276412,-5043128294307900798,-4578161512601023984,-2463121278901514889,303127519297990446,594877140964359361,1533543948414682137,4243960396898301951,6573830124911821771,7997158881778982126], aRuleName_ = "matrix-comprehension-singleton"} -LF: {"AnsweredRule":{"aRuleName_":"matrix-comprehension-singleton","qAscendants_":[-7526881736718068312,-7405557604309373817,-7201686808491642883,-6330762734028692340,-5804239247306276412,-5043128294307900798,-4578161512601023984,-2463121278901514889,303127519297990446,594877140964359361,1533543948414682137,4243960396898301951,6573830124911821771,7997158881778982126],"qHole_":-8650590815054601249}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ - (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ - (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) - } - Context #1: conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ - (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) - } - Context #2: { conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ - (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) - } - } - Context #3: { conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ - (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - Context #4: [{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ - (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]] - Context #5: and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ - (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - Context #6: [|x| = |conjure_aux1|, - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ - (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]); - int(1..2)] - Context #7: |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ - (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - Context #8: { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ - (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - Context #9: y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ - (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } -Picking the only option: Answer 1: choose-repr-for-locals: Choosing representation for local variable conjure_aux4 - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ - (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) - } -storedChoice: -{ conjure_aux4 -@ find conjure_aux4: int(1..5) - such that - (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ - (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) -} -5523540219623150802 -AnsweredRule {qHole_ = -5523540219623150802, qAscendants_ = fromList [-8941059882607301911,-4338998493244249628,-2962415465773075069,-2259331243426380901,-565469044512126150,-60812526271457966,2469584683440447504,4682955345466050776,5578803032032481190], aRuleName_ = "choose-repr-for-locals"} -LF: {"AnsweredRule":{"aRuleName_":"choose-repr-for-locals","qAscendants_":[-8941059882607301911,-4338998493244249628,-2962415465773075069,-2259331243426380901,-565469044512126150,-60812526271457966,2469584683440447504,4682955345466050776,5578803032032481190],"qHole_":-5523540219623150802}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ - (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ - (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) - } - Context #1: { conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ - (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) - } - } - Context #2: { conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ - (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - Context #3: [{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ - (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]] - Context #4: and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ - (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - Context #5: [|x| = |conjure_aux1|, - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ - (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]); - int(1..2)] - Context #6: |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ - (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - Context #7: { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ - (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - Context #8: y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ - (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } -Picking the only option: Answer 1: bubble-up-LiftVars: Bubbling up auxiliary variables. - { conjure_aux2_2 = conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ - (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) - } -storedChoice: -conjure_aux2_2 = -{ conjure_aux4 -@ find conjure_aux4: int(1..5) - such that - (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ - (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) -} 4682955345466050776 -AnsweredRule {qHole_ = 4682955345466050776, qAscendants_ = fromList [-8941059882607301911,-4338998493244249628,-2962415465773075069,-2259331243426380901,-565469044512126150,-60812526271457966,2469584683440447504,5578803032032481190], aRuleName_ = "bubble-up-LiftVars"} -LF: {"AnsweredRule":{"aRuleName_":"bubble-up-LiftVars","qAscendants_":[-8941059882607301911,-4338998493244249628,-2962415465773075069,-2259331243426380901,-565469044512126150,-60812526271457966,2469584683440447504,5578803032032481190],"qHole_":4682955345466050776}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - { conjure_aux2_2 = conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ - (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: { conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - { conjure_aux2_2 = conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ - (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - Context #1: [{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - { conjure_aux2_2 = conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ - (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]] - Context #2: and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - { conjure_aux2_2 = conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ - (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - Context #3: [|x| = |conjure_aux1|, - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - { conjure_aux2_2 = conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ - (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]); - int(1..2)] - Context #4: |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - { conjure_aux2_2 = conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ - (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - Context #5: { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - { conjure_aux2_2 = conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ - (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - Context #6: y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - { conjure_aux2_2 = conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ - (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } -Picking the only option: Answer 1: bubble-up-LiftVars: Bubbling up auxiliary variables. - { conjure_aux2 in conjure_aux1 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - { conjure_aux2_2 = conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ - (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) - } - } -storedChoice: -{ conjure_aux2 -@ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - { conjure_aux2_2 = conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ - (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) - } -} -in conjure_aux1 -8498631454693468162 -AnsweredRule {qHole_ = -8498631454693468162, qAscendants_ = fromList [-8906484870153215238,-5210480414835359833,-1572320097158340186,7262859821198064716,7664399396112355801,9199488081424848815], aRuleName_ = "bubble-up-LiftVars"} -LF: {"AnsweredRule":{"aRuleName_":"bubble-up-LiftVars","qAscendants_":[-8906484870153215238,-5210480414835359833,-1572320097158340186,7262859821198064716,7664399396112355801,9199488081424848815],"qHole_":-8498631454693468162}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 in conjure_aux1 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - { conjure_aux2_2 = conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ - (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) - } - } | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: q8[1] - Context #1: x_RelationAsMatrix[q8[1]] - Context #2: x_RelationAsMatrix[q8[1], q8[2]] - Context #3: [{ conjure_aux2 in conjure_aux1 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - { conjure_aux2_2 = conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ - (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) - } - } | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]] - Context #4: and([{ conjure_aux2 in conjure_aux1 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - { conjure_aux2_2 = conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ - (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) - } - } | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - Context #5: [|x| = |conjure_aux1|, - and([{ conjure_aux2 in conjure_aux1 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - { conjure_aux2_2 = conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ - (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) - } - } | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]); - int(1..2)] - Context #6: |x| = |conjure_aux1| /\ - and([{ conjure_aux2 in conjure_aux1 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - { conjure_aux2_2 = conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ - (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) - } - } | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - Context #7: { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 in conjure_aux1 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - { conjure_aux2_2 = conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ - (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) - } - } | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - Context #8: y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 in conjure_aux1 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - { conjure_aux2_2 = conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ - (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) - } - } | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } -Picking the only option: Answer 1: tuple-index: Tuple indexing on: q8[1] - q8_1 -storedChoice: -q8[1] 6051865069970393497 -AnsweredRule {qHole_ = 6051865069970393497, qAscendants_ = fromList [-8640702807944529160,-7554917160340714381,-7282620252070677492,-4679672213039578282,-3902820972913913543,-1648680758926951321,-323488035431343639,4558015980602682727], aRuleName_ = "tuple-index"} -LF: {"AnsweredRule":{"aRuleName_":"tuple-index","qAscendants_":[-8640702807944529160,-7554917160340714381,-7282620252070677492,-4679672213039578282,-3902820972913913543,-1648680758926951321,-323488035431343639,4558015980602682727],"qHole_":6051865069970393497}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 in conjure_aux1 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - { conjure_aux2_2 = conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ - (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) - } - } | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8[2]]]) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: q8[2] - Context #1: x_RelationAsMatrix[q8_1, q8[2]] - Context #2: [{ conjure_aux2 in conjure_aux1 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - { conjure_aux2_2 = conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ - (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) - } - } | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8[2]]] - Context #3: and([{ conjure_aux2 in conjure_aux1 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - { conjure_aux2_2 = conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ - (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) - } - } | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8[2]]]) - Context #4: [|x| = |conjure_aux1|, - and([{ conjure_aux2 in conjure_aux1 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - { conjure_aux2_2 = conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ - (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) - } - } | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8[2]]]); - int(1..2)] - Context #5: |x| = |conjure_aux1| /\ - and([{ conjure_aux2 in conjure_aux1 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - { conjure_aux2_2 = conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ - (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) - } - } | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8[2]]]) - Context #6: { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 in conjure_aux1 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - { conjure_aux2_2 = conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ - (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) - } - } | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8[2]]]) - } - Context #7: y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 in conjure_aux1 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - { conjure_aux2_2 = conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ - (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) - } - } | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8[2]]]) - } -Picking the only option: Answer 1: tuple-index: Tuple indexing on: q8[2] - q8_2 -storedChoice: -q8[2] 6051020602090044114 -AnsweredRule {qHole_ = 6051020602090044114, qAscendants_ = fromList [-1657839898828256711,-1442033437105002979,-382389179101208790,2791764908100697416,2932884812988402663,3044000407645637671,4978224969731597410], aRuleName_ = "tuple-index"} -LF: {"AnsweredRule":{"aRuleName_":"tuple-index","qAscendants_":[-1657839898828256711,-1442033437105002979,-382389179101208790,2791764908100697416,2932884812988402663,3044000407645637671,4978224969731597410],"qHole_":6051020602090044114}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 in conjure_aux1 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - { conjure_aux2_2 = conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ - (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) - } - } | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]]) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: [{ conjure_aux2 in conjure_aux1 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - { conjure_aux2_2 = conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ - (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) - } - } | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] - Context #1: and([{ conjure_aux2 in conjure_aux1 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - { conjure_aux2_2 = conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ - (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) - } - } | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]]) - Context #2: [|x| = |conjure_aux1|, - and([{ conjure_aux2 in conjure_aux1 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - { conjure_aux2_2 = conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ - (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) - } - } | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]]); - int(1..2)] - Context #3: |x| = |conjure_aux1| /\ - and([{ conjure_aux2 in conjure_aux1 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - { conjure_aux2_2 = conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ - (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) - } - } | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]]) - Context #4: { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 in conjure_aux1 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - { conjure_aux2_2 = conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ - (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) - } - } | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]]) - } - Context #5: y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 in conjure_aux1 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - { conjure_aux2_2 = conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ - (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) - } - } | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]]) - } -Picking the only option: Answer 1: bubble-up-LiftVars: Bubbling up auxiliary variables through a comprehension. - { [conjure_aux2 in conjure_aux1 | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([{ conjure_aux2_1[q8_1, q8_2] = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } | q8_1 : int(1..5), q8_2 : int(1..5)]), - and([{ conjure_aux2_2[q8_1, q8_2] = conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ - (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) - } | q8_1 : int(1..5), q8_2 : int(1..5)]) - } -storedChoice: -[{ conjure_aux2 in conjure_aux1 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - { conjure_aux2_2 = conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ - (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) - } - } | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] 4632560015221358179 -AnsweredRule {qHole_ = 4632560015221358179, qAscendants_ = fromList [-7796146364068057171,-6981365833241776808,-5029665938164178889,-3928434564447926958,-2893776785872977312], aRuleName_ = "bubble-up-LiftVars"} -LF: {"AnsweredRule":{"aRuleName_":"bubble-up-LiftVars","qAscendants_":[-7796146364068057171,-6981365833241776808,-5029665938164178889,-3928434564447926958,-2893776785872977312],"qHole_":4632560015221358179}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and({ [conjure_aux2 in conjure_aux1 | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([{ conjure_aux2_1[q8_1, q8_2] = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } | q8_1 : int(1..5), q8_2 : int(1..5)]), - and([{ conjure_aux2_2[q8_1, q8_2] = conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ - (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) - } | q8_1 : int(1..5), q8_2 : int(1..5)]) - }) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: { [conjure_aux2 in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([{ conjure_aux2_1[q8_1, q8_2] = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } | q8_1 : int(1..5), q8_2 : int(1..5)]), - and([{ conjure_aux2_2[q8_1, q8_2] = conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ - (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) - } | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - Context #1: and({ [conjure_aux2 in conjure_aux1 | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([{ conjure_aux2_1[q8_1, q8_2] = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } | q8_1 : int(1..5), q8_2 : int(1..5)]), - and([{ conjure_aux2_2[q8_1, q8_2] = conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ - (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) - } | q8_1 : int(1..5), q8_2 : int(1..5)]) - }) - Context #2: [|x| = |conjure_aux1|, - and({ [conjure_aux2 in conjure_aux1 | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([{ conjure_aux2_1[q8_1, q8_2] = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } | q8_1 : int(1..5), q8_2 : int(1..5)]), - and([{ conjure_aux2_2[q8_1, q8_2] = conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ - (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) - } | q8_1 : int(1..5), q8_2 : int(1..5)]) - }); - int(1..2)] - Context #3: |x| = |conjure_aux1| /\ - and({ [conjure_aux2 in conjure_aux1 | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([{ conjure_aux2_1[q8_1, q8_2] = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } | q8_1 : int(1..5), q8_2 : int(1..5)]), - and([{ conjure_aux2_2[q8_1, q8_2] = conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ - (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) - } | q8_1 : int(1..5), q8_2 : int(1..5)]) - }) - Context #4: { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and({ [conjure_aux2 in conjure_aux1 | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([{ conjure_aux2_1[q8_1, q8_2] = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } | q8_1 : int(1..5), q8_2 : int(1..5)]), - and([{ conjure_aux2_2[q8_1, q8_2] = conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ - (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) - } | q8_1 : int(1..5), q8_2 : int(1..5)]) - }) - } - Context #5: y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and({ [conjure_aux2 in conjure_aux1 | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([{ conjure_aux2_1[q8_1, q8_2] = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } | q8_1 : int(1..5), q8_2 : int(1..5)]), - and([{ conjure_aux2_2[q8_1, q8_2] = conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ - (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) - } | q8_1 : int(1..5), q8_2 : int(1..5)]) - }) - } -Picking the only option: Answer 1: choose-repr-for-locals: Choosing representation for local variable conjure_aux2_1 - { [conjure_aux2 in conjure_aux1 | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([{ conjure_aux2_1[q8_1, q8_2] = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } | q8_1 : int(1..5), q8_2 : int(1..5)]), - and([{ conjure_aux2_2[q8_1, q8_2] = conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ - (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) - } | q8_1 : int(1..5), q8_2 : int(1..5)]) - } -storedChoice: -{ [conjure_aux2 in conjure_aux1 | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] -@ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([{ conjure_aux2_1[q8_1, q8_2] = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } | q8_1 : int(1..5), q8_2 : int(1..5)]), - and([{ conjure_aux2_2[q8_1, q8_2] = conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ - (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) - } | q8_1 : int(1..5), q8_2 : int(1..5)]) -} 5183357163976320088 -AnsweredRule {qHole_ = 5183357163976320088, qAscendants_ = fromList [-5465830923914696498,-4063366109563536561,-2043995450352341839,378335084364868291,1311484366701431644], aRuleName_ = "choose-repr-for-locals"} -LF: {"AnsweredRule":{"aRuleName_":"choose-repr-for-locals","qAscendants_":[-5465830923914696498,-4063366109563536561,-2043995450352341839,378335084364868291,1311484366701431644],"qHole_":5183357163976320088}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and({ [conjure_aux2 in conjure_aux1 | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([{ conjure_aux2_1[q8_1, q8_2] = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } | q8_1 : int(1..5), q8_2 : int(1..5)]), - and([{ conjure_aux2_2[q8_1, q8_2] = conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ - (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) - } | q8_1 : int(1..5), q8_2 : int(1..5)]) - }) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: [{ conjure_aux2_1[q8_1, q8_2] = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } | q8_1 : int(1..5), q8_2 : int(1..5)] - Context #1: and([{ conjure_aux2_1[q8_1, q8_2] = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } | q8_1 : int(1..5), q8_2 : int(1..5)]) - Context #2: { [conjure_aux2 in conjure_aux1 | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([{ conjure_aux2_1[q8_1, q8_2] = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } | q8_1 : int(1..5), q8_2 : int(1..5)]), - and([{ conjure_aux2_2[q8_1, q8_2] = conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ - (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) - } | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - Context #3: and({ [conjure_aux2 in conjure_aux1 | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([{ conjure_aux2_1[q8_1, q8_2] = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } | q8_1 : int(1..5), q8_2 : int(1..5)]), - and([{ conjure_aux2_2[q8_1, q8_2] = conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ - (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) - } | q8_1 : int(1..5), q8_2 : int(1..5)]) - }) - Context #4: [|x| = |conjure_aux1|, - and({ [conjure_aux2 in conjure_aux1 | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([{ conjure_aux2_1[q8_1, q8_2] = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } | q8_1 : int(1..5), q8_2 : int(1..5)]), - and([{ conjure_aux2_2[q8_1, q8_2] = conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ - (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) - } | q8_1 : int(1..5), q8_2 : int(1..5)]) - }); - int(1..2)] - Context #5: |x| = |conjure_aux1| /\ - and({ [conjure_aux2 in conjure_aux1 | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([{ conjure_aux2_1[q8_1, q8_2] = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } | q8_1 : int(1..5), q8_2 : int(1..5)]), - and([{ conjure_aux2_2[q8_1, q8_2] = conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ - (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) - } | q8_1 : int(1..5), q8_2 : int(1..5)]) - }) - Context #6: { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and({ [conjure_aux2 in conjure_aux1 | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([{ conjure_aux2_1[q8_1, q8_2] = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } | q8_1 : int(1..5), q8_2 : int(1..5)]), - and([{ conjure_aux2_2[q8_1, q8_2] = conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ - (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) - } | q8_1 : int(1..5), q8_2 : int(1..5)]) - }) - } - Context #7: y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and({ [conjure_aux2 in conjure_aux1 | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([{ conjure_aux2_1[q8_1, q8_2] = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } | q8_1 : int(1..5), q8_2 : int(1..5)]), - and([{ conjure_aux2_2[q8_1, q8_2] = conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ - (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) - } | q8_1 : int(1..5), q8_2 : int(1..5)]) - }) - } -Picking the only option: Answer 1: bubble-up-LiftVars: Bubbling up auxiliary variables through a comprehension. - { [conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)] - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } -storedChoice: -[{ conjure_aux2_1[q8_1, q8_2] = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } | q8_1 : int(1..5), q8_2 : int(1..5)] -2066028230956466058 -AnsweredRule {qHole_ = -2066028230956466058, qAscendants_ = fromList [-8778252753919104373,-5465830923914696498,-4063366109563536561,-2043995450352341839,378335084364868291,1311484366701431644,5183357163976320088], aRuleName_ = "bubble-up-LiftVars"} -LF: {"AnsweredRule":{"aRuleName_":"bubble-up-LiftVars","qAscendants_":[-8778252753919104373,-5465830923914696498,-4063366109563536561,-2043995450352341839,378335084364868291,1311484366701431644,5183357163976320088],"qHole_":-2066028230956466058}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and({ [conjure_aux2 in conjure_aux1 | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and({ [conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)] - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }), - and([{ conjure_aux2_2[q8_1, q8_2] = conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ - (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) - } | q8_1 : int(1..5), q8_2 : int(1..5)]) - }) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: { [conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)] - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - Context #1: and({ [conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)] - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }) - Context #2: { [conjure_aux2 in conjure_aux1 | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and({ [conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)] - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }), - and([{ conjure_aux2_2[q8_1, q8_2] = conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ - (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) - } | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - Context #3: and({ [conjure_aux2 in conjure_aux1 | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and({ [conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)] - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }), - and([{ conjure_aux2_2[q8_1, q8_2] = conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ - (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) - } | q8_1 : int(1..5), q8_2 : int(1..5)]) - }) - Context #4: [|x| = |conjure_aux1|, - and({ [conjure_aux2 in conjure_aux1 | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and({ [conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)] - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }), - and([{ conjure_aux2_2[q8_1, q8_2] = conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ - (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) - } | q8_1 : int(1..5), q8_2 : int(1..5)]) - }); - int(1..2)] - Context #5: |x| = |conjure_aux1| /\ - and({ [conjure_aux2 in conjure_aux1 | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and({ [conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)] - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }), - and([{ conjure_aux2_2[q8_1, q8_2] = conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ - (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) - } | q8_1 : int(1..5), q8_2 : int(1..5)]) - }) - Context #6: { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and({ [conjure_aux2 in conjure_aux1 | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and({ [conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)] - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }), - and([{ conjure_aux2_2[q8_1, q8_2] = conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ - (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) - } | q8_1 : int(1..5), q8_2 : int(1..5)]) - }) - } - Context #7: y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and({ [conjure_aux2 in conjure_aux1 | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and({ [conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)] - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }), - and([{ conjure_aux2_2[q8_1, q8_2] = conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ - (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) - } | q8_1 : int(1..5), q8_2 : int(1..5)]) - }) - } -Picking the only option: Answer 1: choose-repr-for-locals: Choosing representation for local variable conjure_aux3 - { [conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)] - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } -storedChoice: -{ [conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)] -@ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) -} -2683400798428888576 -AnsweredRule {qHole_ = -2683400798428888576, qAscendants_ = fromList [-7630765854898757381,-5152289056460337438,-4378029185233493510,-2193789157648306228,-780484605375639491,4611290103392876019,8129436120778745950], aRuleName_ = "choose-repr-for-locals"} -LF: {"AnsweredRule":{"aRuleName_":"choose-repr-for-locals","qAscendants_":[-7630765854898757381,-5152289056460337438,-4378029185233493510,-2193789157648306228,-780484605375639491,4611290103392876019,8129436120778745950],"qHole_":-2683400798428888576}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and({ [conjure_aux2 in conjure_aux1 | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and({ [conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)] - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }), - and([{ conjure_aux2_2[q8_1, q8_2] = conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ - (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) - } | q8_1 : int(1..5), q8_2 : int(1..5)]) - }) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: and({ [conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] - | q8_1 : int(1..5), q8_2 : int(1..5)] - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }) - Context #1: { [conjure_aux2 in conjure_aux1 | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and({ [conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)] - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }), - and([{ conjure_aux2_2[q8_1, q8_2] = conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ - (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) - } | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - Context #2: and({ [conjure_aux2 in conjure_aux1 | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and({ [conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)] - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }), - and([{ conjure_aux2_2[q8_1, q8_2] = conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ - (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) - } | q8_1 : int(1..5), q8_2 : int(1..5)]) - }) - Context #3: [|x| = |conjure_aux1|, - and({ [conjure_aux2 in conjure_aux1 | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and({ [conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)] - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }), - and([{ conjure_aux2_2[q8_1, q8_2] = conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ - (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) - } | q8_1 : int(1..5), q8_2 : int(1..5)]) - }); - int(1..2)] - Context #4: |x| = |conjure_aux1| /\ - and({ [conjure_aux2 in conjure_aux1 | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and({ [conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)] - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }), - and([{ conjure_aux2_2[q8_1, q8_2] = conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ - (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) - } | q8_1 : int(1..5), q8_2 : int(1..5)]) - }) - Context #5: { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and({ [conjure_aux2 in conjure_aux1 | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and({ [conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)] - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }), - and([{ conjure_aux2_2[q8_1, q8_2] = conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ - (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) - } | q8_1 : int(1..5), q8_2 : int(1..5)]) - }) - } - Context #6: y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and({ [conjure_aux2 in conjure_aux1 | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and({ [conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)] - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }), - and([{ conjure_aux2_2[q8_1, q8_2] = conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ - (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) - } | q8_1 : int(1..5), q8_2 : int(1..5)]) - }) - } -Picking the only option: Answer 1: bubble-up-LiftVars: Bubbling up auxiliary variables. - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } -storedChoice: -and({ [conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)] - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }) -7630765854898757381 -AnsweredRule {qHole_ = -7630765854898757381, qAscendants_ = fromList [-5152289056460337438,-4378029185233493510,-2193789157648306228,-780484605375639491,4611290103392876019,8129436120778745950], aRuleName_ = "bubble-up-LiftVars"} -LF: {"AnsweredRule":{"aRuleName_":"bubble-up-LiftVars","qAscendants_":[-5152289056460337438,-4378029185233493510,-2193789157648306228,-780484605375639491,4611290103392876019,8129436120778745950],"qHole_":-7630765854898757381}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and({ [conjure_aux2 in conjure_aux1 | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - and([{ conjure_aux2_2[q8_1, q8_2] = conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ - (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) - } | q8_1 : int(1..5), q8_2 : int(1..5)]) - }) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: [{ conjure_aux2_2[q8_1, q8_2] = conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ - (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) - } | q8_1 : int(1..5), q8_2 : int(1..5)] - Context #1: and([{ conjure_aux2_2[q8_1, q8_2] = conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ - (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) - } | q8_1 : int(1..5), q8_2 : int(1..5)]) - Context #2: { [conjure_aux2 in conjure_aux1 | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - and([{ conjure_aux2_2[q8_1, q8_2] = conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ - (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) - } | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - Context #3: and({ [conjure_aux2 in conjure_aux1 | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - and([{ conjure_aux2_2[q8_1, q8_2] = conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ - (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) - } | q8_1 : int(1..5), q8_2 : int(1..5)]) - }) - Context #4: [|x| = |conjure_aux1|, - and({ [conjure_aux2 in conjure_aux1 | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - and([{ conjure_aux2_2[q8_1, q8_2] = conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ - (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) - } | q8_1 : int(1..5), q8_2 : int(1..5)]) - }); - int(1..2)] - Context #5: |x| = |conjure_aux1| /\ - and({ [conjure_aux2 in conjure_aux1 | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - and([{ conjure_aux2_2[q8_1, q8_2] = conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ - (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) - } | q8_1 : int(1..5), q8_2 : int(1..5)]) - }) - Context #6: { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and({ [conjure_aux2 in conjure_aux1 | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - and([{ conjure_aux2_2[q8_1, q8_2] = conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ - (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) - } | q8_1 : int(1..5), q8_2 : int(1..5)]) - }) - } - Context #7: y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and({ [conjure_aux2 in conjure_aux1 | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - and([{ conjure_aux2_2[q8_1, q8_2] = conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ - (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) - } | q8_1 : int(1..5), q8_2 : int(1..5)]) - }) - } -Picking the only option: Answer 1: bubble-up-LiftVars: Bubbling up auxiliary variables through a comprehension. - { [conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)] - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } -storedChoice: -[{ conjure_aux2_2[q8_1, q8_2] = conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ - (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) - } | q8_1 : int(1..5), q8_2 : int(1..5)] 4586595665260781575 -AnsweredRule {qHole_ = 4586595665260781575, qAscendants_ = fromList [-5189262863924670079,-4576870578376860616,-3657040581488238581,667350004362937900,5588145911994567168,7042957946885141470,7965291691177128164], aRuleName_ = "bubble-up-LiftVars"} -LF: {"AnsweredRule":{"aRuleName_":"bubble-up-LiftVars","qAscendants_":[-5189262863924670079,-4576870578376860616,-3657040581488238581,667350004362937900,5588145911994567168,7042957946885141470,7965291691177128164],"qHole_":4586595665260781575}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and({ [conjure_aux2 in conjure_aux1 | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - and({ [conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)] - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }) - }) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: { [conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)] - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - Context #1: and({ [conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)] - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }) - Context #2: { [conjure_aux2 in conjure_aux1 | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - and({ [conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)] - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }) - } - Context #3: and({ [conjure_aux2 in conjure_aux1 | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - and({ [conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)] - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }) - }) - Context #4: [|x| = |conjure_aux1|, - and({ [conjure_aux2 in conjure_aux1 | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - and({ [conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)] - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }) - }); - int(1..2)] - Context #5: |x| = |conjure_aux1| /\ - and({ [conjure_aux2 in conjure_aux1 | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - and({ [conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)] - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }) - }) - Context #6: { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and({ [conjure_aux2 in conjure_aux1 | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - and({ [conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)] - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }) - }) - } - Context #7: y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and({ [conjure_aux2 in conjure_aux1 | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - and({ [conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)] - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }) - }) - } -Picking the only option: Answer 1: choose-repr-for-locals: Choosing representation for local variable conjure_aux4 - { [conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)] - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } -storedChoice: -{ [conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)] -@ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) -} -1434005429531325525 -AnsweredRule {qHole_ = -1434005429531325525, qAscendants_ = fromList [-7860778431127922714,-4340120710083553155,-3276746255609047616,-2418004144569851915,-329464522225361142,8566682329173394842,8971959176905079767], aRuleName_ = "choose-repr-for-locals"} -LF: {"AnsweredRule":{"aRuleName_":"choose-repr-for-locals","qAscendants_":[-7860778431127922714,-4340120710083553155,-3276746255609047616,-2418004144569851915,-329464522225361142,8566682329173394842,8971959176905079767],"qHole_":-1434005429531325525}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and({ [conjure_aux2 in conjure_aux1 | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - and({ [conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)] - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }) - }) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: and({ [conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] - | q8_1 : int(1..5), q8_2 : int(1..5)] - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }) - Context #1: { [conjure_aux2 in conjure_aux1 | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - and({ [conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)] - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }) - } - Context #2: and({ [conjure_aux2 in conjure_aux1 | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - and({ [conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)] - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }) - }) - Context #3: [|x| = |conjure_aux1|, - and({ [conjure_aux2 in conjure_aux1 | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - and({ [conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)] - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }) - }); - int(1..2)] - Context #4: |x| = |conjure_aux1| /\ - and({ [conjure_aux2 in conjure_aux1 | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - and({ [conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)] - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }) - }) - Context #5: { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and({ [conjure_aux2 in conjure_aux1 | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - and({ [conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)] - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }) - }) - } - Context #6: y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and({ [conjure_aux2 in conjure_aux1 | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - and({ [conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)] - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }) - }) - } -Picking the only option: Answer 1: bubble-up-LiftVars: Bubbling up auxiliary variables. - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } -storedChoice: -and({ [conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)] - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }) -329464522225361142 -AnsweredRule {qHole_ = -329464522225361142, qAscendants_ = fromList [-7860778431127922714,-4340120710083553155,-3276746255609047616,-2418004144569851915,8566682329173394842,8971959176905079767], aRuleName_ = "bubble-up-LiftVars"} -LF: {"AnsweredRule":{"aRuleName_":"bubble-up-LiftVars","qAscendants_":[-7860778431127922714,-4340120710083553155,-3276746255609047616,-2418004144569851915,8566682329173394842,8971959176905079767],"qHole_":-329464522225361142}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and({ [conjure_aux2 in conjure_aux1 | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - }) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: conjure_aux2 in conjure_aux1 - Context #1: [conjure_aux2 in conjure_aux1 | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] - Context #2: { [conjure_aux2 in conjure_aux1 | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - } - Context #3: and({ [conjure_aux2 in conjure_aux1 | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - }) - Context #4: [|x| = |conjure_aux1|, - and({ [conjure_aux2 in conjure_aux1 | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - }); - int(1..2)] - Context #5: |x| = |conjure_aux1| /\ - and({ [conjure_aux2 in conjure_aux1 | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - }) - Context #6: { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and({ [conjure_aux2 in conjure_aux1 | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - }) - } - Context #7: y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and({ [conjure_aux2 in conjure_aux1 | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - }) - } -Picking the only option: Answer 1: relation-in: relation membership to existential quantification - or([q27 = conjure_aux2 | q27 <- toSet(conjure_aux1)]) -storedChoice: -conjure_aux2 in conjure_aux1 7266634060293924720 -AnsweredRule {qHole_ = 7266634060293924720, qAscendants_ = fromList [-7266324578771459181,-6713121642540228318,-5826297241095436731,-5526349309453330732,1756707357159771390,2149626909839152329,4938058042264599181], aRuleName_ = "relation-in"} -LF: {"AnsweredRule":{"aRuleName_":"relation-in","qAscendants_":[-7266324578771459181,-6713121642540228318,-5826297241095436731,-5526349309453330732,1756707357159771390,2149626909839152329,4938058042264599181],"qHole_":7266634060293924720}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and({ [or([q27 = conjure_aux2 | q27 <- toSet(conjure_aux1)]) | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - }) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: [q27 = conjure_aux2 | q27 <- toSet(conjure_aux1)] - Context #1: or([q27 = conjure_aux2 | q27 <- toSet(conjure_aux1)]) - Context #2: [or([q27 = conjure_aux2 | q27 <- toSet(conjure_aux1)]) - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] - Context #3: { [or([q27 = conjure_aux2 | q27 <- toSet(conjure_aux1)]) - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - } - Context #4: and({ [or([q27 = conjure_aux2 | q27 <- toSet(conjure_aux1)]) - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - }) - Context #5: [|x| = |conjure_aux1|, - and({ [or([q27 = conjure_aux2 | q27 <- toSet(conjure_aux1)]) | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - }); - int(1..2)] - Context #6: |x| = |conjure_aux1| /\ - and({ [or([q27 = conjure_aux2 | q27 <- toSet(conjure_aux1)]) | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - }) - Context #7: { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and({ [or([q27 = conjure_aux2 | q27 <- toSet(conjure_aux1)]) | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - }) - } - Context #8: y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and({ [or([q27 = conjure_aux2 | q27 <- toSet(conjure_aux1)]) | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - }) - } -Picking the only option: Answer 1: relation-map_in_expr{RelationAsMatrix}: Vertical rule for map_in_expr for relation domains, RelationAsMatrix representation. - [(q28[1], q28[2]) = conjure_aux2 | q28 : (int(1..5), int(1..5)), conjure_aux1_RelationAsMatrix[q28[1], q28[2]]] -storedChoice: -[q27 = conjure_aux2 | q27 <- toSet(conjure_aux1)] -3470261408387399930 -AnsweredRule {qHole_ = -3470261408387399930, qAscendants_ = fromList [-8536113027950480792,-7330204231396072871,-4786623393387445427,-4223003553667075844,4116516722814445548,4281838781863596501,6175095517354461663,6559035824535384582], aRuleName_ = "relation-map_in_expr{RelationAsMatrix}"} -LF: {"AnsweredRule":{"aRuleName_":"relation-map_in_expr{RelationAsMatrix}","qAscendants_":[-8536113027950480792,-7330204231396072871,-4786623393387445427,-4223003553667075844,4116516722814445548,4281838781863596501,6175095517354461663,6559035824535384582],"qHole_":-3470261408387399930}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and({ [or([(q28[1], q28[2]) = conjure_aux2 | q28 : (int(1..5), int(1..5)), conjure_aux1_RelationAsMatrix[q28[1], q28[2]]]) - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - }) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: [(q28[1], q28[2]) = conjure_aux2 - | q28 : (int(1..5), int(1..5)), conjure_aux1_RelationAsMatrix[q28[1], q28[2]]] - Context #1: or([(q28[1], q28[2]) = conjure_aux2 | q28 : (int(1..5), int(1..5)), conjure_aux1_RelationAsMatrix[q28[1], q28[2]]]) - Context #2: [or([(q28[1], q28[2]) = conjure_aux2 | q28 : (int(1..5), int(1..5)), conjure_aux1_RelationAsMatrix[q28[1], q28[2]]]) - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] - Context #3: { [or([(q28[1], q28[2]) = conjure_aux2 | q28 : (int(1..5), int(1..5)), conjure_aux1_RelationAsMatrix[q28[1], q28[2]]]) - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - } - Context #4: and({ [or([(q28[1], q28[2]) = conjure_aux2 - | q28 : (int(1..5), int(1..5)), conjure_aux1_RelationAsMatrix[q28[1], q28[2]]]) - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - }) - Context #5: [|x| = |conjure_aux1|, - and({ [or([(q28[1], q28[2]) = conjure_aux2 | q28 : (int(1..5), int(1..5)), conjure_aux1_RelationAsMatrix[q28[1], q28[2]]]) - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - }); - int(1..2)] - Context #6: |x| = |conjure_aux1| /\ - and({ [or([(q28[1], q28[2]) = conjure_aux2 | q28 : (int(1..5), int(1..5)), conjure_aux1_RelationAsMatrix[q28[1], q28[2]]]) - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - }) - Context #7: { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and({ [or([(q28[1], q28[2]) = conjure_aux2 | q28 : (int(1..5), int(1..5)), conjure_aux1_RelationAsMatrix[q28[1], q28[2]]]) - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - }) - } - Context #8: y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and({ [or([(q28[1], q28[2]) = conjure_aux2 | q28 : (int(1..5), int(1..5)), conjure_aux1_RelationAsMatrix[q28[1], q28[2]]]) - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - }) - } -Picking the only option: Answer 1: choose-repr-for-comprehension: Choosing representation for quantified variable q28 (with type: (int, - int)) - [(q28[1], q28[2]) = conjure_aux2 | q28_1 : int(1..5), q28_2 : int(1..5), conjure_aux1_RelationAsMatrix[q28[1], q28[2]]] -storedChoice: -[(q28[1], q28[2]) = conjure_aux2 | q28 : (int(1..5), int(1..5)), conjure_aux1_RelationAsMatrix[q28[1], q28[2]]] 4348009411125732066 -AnsweredRule {qHole_ = 4348009411125732066, qAscendants_ = fromList [-6592612559904363413,-6472871177545322172,-6453293890463000807,-2235240472846537890,3259852529283772574,4455209103885624492,6352194885377054835,8420829954716127361], aRuleName_ = "choose-repr-for-comprehension"} -LF: {"AnsweredRule":{"aRuleName_":"choose-repr-for-comprehension","qAscendants_":[-6592612559904363413,-6472871177545322172,-6453293890463000807,-2235240472846537890,3259852529283772574,4455209103885624492,6352194885377054835,8420829954716127361],"qHole_":4348009411125732066}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and({ [or([(q28[1], q28[2]) = conjure_aux2 | q28_1 : int(1..5), q28_2 : int(1..5), conjure_aux1_RelationAsMatrix[q28[1], q28[2]]]) - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - }) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: (q28[1], q28[2]) = conjure_aux2 - Context #1: [(q28[1], q28[2]) = conjure_aux2 | q28_1 : int(1..5), q28_2 : int(1..5), conjure_aux1_RelationAsMatrix[q28[1], q28[2]]] - Context #2: or([(q28[1], q28[2]) = conjure_aux2 - | q28_1 : int(1..5), q28_2 : int(1..5), conjure_aux1_RelationAsMatrix[q28[1], q28[2]]]) - Context #3: [or([(q28[1], q28[2]) = conjure_aux2 - | q28_1 : int(1..5), q28_2 : int(1..5), conjure_aux1_RelationAsMatrix[q28[1], q28[2]]]) - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] - Context #4: { [or([(q28[1], q28[2]) = conjure_aux2 - | q28_1 : int(1..5), q28_2 : int(1..5), conjure_aux1_RelationAsMatrix[q28[1], q28[2]]]) - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - } - Context #5: and({ [or([(q28[1], q28[2]) = conjure_aux2 - | q28_1 : int(1..5), q28_2 : int(1..5), conjure_aux1_RelationAsMatrix[q28[1], q28[2]]]) - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - }) - Context #6: [|x| = |conjure_aux1|, - and({ [or([(q28[1], q28[2]) = conjure_aux2 | q28_1 : int(1..5), q28_2 : int(1..5), conjure_aux1_RelationAsMatrix[q28[1], q28[2]]]) - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - }); - int(1..2)] - Context #7: |x| = |conjure_aux1| /\ - and({ [or([(q28[1], q28[2]) = conjure_aux2 | q28_1 : int(1..5), q28_2 : int(1..5), conjure_aux1_RelationAsMatrix[q28[1], q28[2]]]) - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - }) - Context #8: { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and({ [or([(q28[1], q28[2]) = conjure_aux2 | q28_1 : int(1..5), q28_2 : int(1..5), conjure_aux1_RelationAsMatrix[q28[1], q28[2]]]) - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - }) - } - Context #9: y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and({ [or([(q28[1], q28[2]) = conjure_aux2 | q28_1 : int(1..5), q28_2 : int(1..5), conjure_aux1_RelationAsMatrix[q28[1], q28[2]]]) - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - }) - } -Picking the only option: Answer 1: tuple-eq: Horizontal rule for tuple equality - q28[1] = conjure_aux2_1 /\ q28[2] = conjure_aux2_2 -storedChoice: -(q28[1], q28[2]) = conjure_aux2 -4124337097652933443 -AnsweredRule {qHole_ = -4124337097652933443, qAscendants_ = fromList [-6634517003356473421,-4157154907530130258,-932339049260687039,4056979115757602560,5419805607560390341,5700344114265930133,8275228852675492835,8651388538213571462,8952456806918978808], aRuleName_ = "tuple-eq"} -LF: {"AnsweredRule":{"aRuleName_":"tuple-eq","qAscendants_":[-6634517003356473421,-4157154907530130258,-932339049260687039,4056979115757602560,5419805607560390341,5700344114265930133,8275228852675492835,8651388538213571462,8952456806918978808],"qHole_":-4124337097652933443}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and({ [or([q28[1] = conjure_aux2_1 /\ q28[2] = conjure_aux2_2 - | q28_1 : int(1..5), q28_2 : int(1..5), conjure_aux1_RelationAsMatrix[q28[1], q28[2]]]) - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - }) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: q28[1] - Context #1: q28[1] = conjure_aux2_1 - Context #2: [q28[1] = conjure_aux2_1, q28[2] = conjure_aux2_2; int(1..2)] - Context #3: q28[1] = conjure_aux2_1 /\ q28[2] = conjure_aux2_2 - Context #4: [q28[1] = conjure_aux2_1 /\ q28[2] = conjure_aux2_2 - | q28_1 : int(1..5), q28_2 : int(1..5), conjure_aux1_RelationAsMatrix[q28[1], q28[2]]] - Context #5: or([q28[1] = conjure_aux2_1 /\ q28[2] = conjure_aux2_2 - | q28_1 : int(1..5), q28_2 : int(1..5), conjure_aux1_RelationAsMatrix[q28[1], q28[2]]]) - Context #6: [or([q28[1] = conjure_aux2_1 /\ q28[2] = conjure_aux2_2 - | q28_1 : int(1..5), q28_2 : int(1..5), conjure_aux1_RelationAsMatrix[q28[1], q28[2]]]) - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] - Context #7: { [or([q28[1] = conjure_aux2_1 /\ q28[2] = conjure_aux2_2 - | q28_1 : int(1..5), q28_2 : int(1..5), conjure_aux1_RelationAsMatrix[q28[1], q28[2]]]) - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - } - Context #8: and({ [or([q28[1] = conjure_aux2_1 /\ q28[2] = conjure_aux2_2 - | q28_1 : int(1..5), q28_2 : int(1..5), conjure_aux1_RelationAsMatrix[q28[1], q28[2]]]) - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - }) - Context #9: [|x| = |conjure_aux1|, - and({ [or([q28[1] = conjure_aux2_1 /\ q28[2] = conjure_aux2_2 - | q28_1 : int(1..5), q28_2 : int(1..5), conjure_aux1_RelationAsMatrix[q28[1], q28[2]]]) - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - }); - int(1..2)] - Context #10: |x| = |conjure_aux1| /\ - and({ [or([q28[1] = conjure_aux2_1 /\ q28[2] = conjure_aux2_2 - | q28_1 : int(1..5), q28_2 : int(1..5), conjure_aux1_RelationAsMatrix[q28[1], q28[2]]]) - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - }) - Context #11: { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and({ [or([q28[1] = conjure_aux2_1 /\ q28[2] = conjure_aux2_2 - | q28_1 : int(1..5), q28_2 : int(1..5), conjure_aux1_RelationAsMatrix[q28[1], q28[2]]]) - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - }) - } - Context #12: y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and({ [or([q28[1] = conjure_aux2_1 /\ q28[2] = conjure_aux2_2 - | q28_1 : int(1..5), q28_2 : int(1..5), conjure_aux1_RelationAsMatrix[q28[1], q28[2]]]) - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - }) - } -Picking the only option: Answer 1: tuple-index: Tuple indexing on: q28[1] - q28_1 -storedChoice: -q28[1] 8787010607011614834 -AnsweredRule {qHole_ = 8787010607011614834, qAscendants_ = fromList [-8956326597613561383,-6532059540256123763,-6109385609926416455,-3678896154897738560,-419523469793567323,-407169135612228618,2034669589965157861,4997220444967745554,6148375269450574671,6513082934840114429,8747477145020099131,8922317001415918920], aRuleName_ = "tuple-index"} -LF: {"AnsweredRule":{"aRuleName_":"tuple-index","qAscendants_":[-8956326597613561383,-6532059540256123763,-6109385609926416455,-3678896154897738560,-419523469793567323,-407169135612228618,2034669589965157861,4997220444967745554,6148375269450574671,6513082934840114429,8747477145020099131,8922317001415918920],"qHole_":8787010607011614834}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and({ [or([q28_1 = conjure_aux2_1 /\ q28[2] = conjure_aux2_2 - | q28_1 : int(1..5), q28_2 : int(1..5), conjure_aux1_RelationAsMatrix[q28[1], q28[2]]]) - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - }) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: q28[2] - Context #1: q28[2] = conjure_aux2_2 - Context #2: [q28_1 = conjure_aux2_1, q28[2] = conjure_aux2_2; int(1..2)] - Context #3: q28_1 = conjure_aux2_1 /\ q28[2] = conjure_aux2_2 - Context #4: [q28_1 = conjure_aux2_1 /\ q28[2] = conjure_aux2_2 - | q28_1 : int(1..5), q28_2 : int(1..5), conjure_aux1_RelationAsMatrix[q28[1], q28[2]]] - Context #5: or([q28_1 = conjure_aux2_1 /\ q28[2] = conjure_aux2_2 - | q28_1 : int(1..5), q28_2 : int(1..5), conjure_aux1_RelationAsMatrix[q28[1], q28[2]]]) - Context #6: [or([q28_1 = conjure_aux2_1 /\ q28[2] = conjure_aux2_2 - | q28_1 : int(1..5), q28_2 : int(1..5), conjure_aux1_RelationAsMatrix[q28[1], q28[2]]]) - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] - Context #7: { [or([q28_1 = conjure_aux2_1 /\ q28[2] = conjure_aux2_2 - | q28_1 : int(1..5), q28_2 : int(1..5), conjure_aux1_RelationAsMatrix[q28[1], q28[2]]]) - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - } - Context #8: and({ [or([q28_1 = conjure_aux2_1 /\ q28[2] = conjure_aux2_2 - | q28_1 : int(1..5), q28_2 : int(1..5), conjure_aux1_RelationAsMatrix[q28[1], q28[2]]]) - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - }) - Context #9: [|x| = |conjure_aux1|, - and({ [or([q28_1 = conjure_aux2_1 /\ q28[2] = conjure_aux2_2 - | q28_1 : int(1..5), q28_2 : int(1..5), conjure_aux1_RelationAsMatrix[q28[1], q28[2]]]) - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - }); - int(1..2)] - Context #10: |x| = |conjure_aux1| /\ - and({ [or([q28_1 = conjure_aux2_1 /\ q28[2] = conjure_aux2_2 - | q28_1 : int(1..5), q28_2 : int(1..5), conjure_aux1_RelationAsMatrix[q28[1], q28[2]]]) - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - }) - Context #11: { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and({ [or([q28_1 = conjure_aux2_1 /\ q28[2] = conjure_aux2_2 - | q28_1 : int(1..5), q28_2 : int(1..5), conjure_aux1_RelationAsMatrix[q28[1], q28[2]]]) - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - }) - } - Context #12: y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and({ [or([q28_1 = conjure_aux2_1 /\ q28[2] = conjure_aux2_2 - | q28_1 : int(1..5), q28_2 : int(1..5), conjure_aux1_RelationAsMatrix[q28[1], q28[2]]]) - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - }) - } -Picking the only option: Answer 1: tuple-index: Tuple indexing on: q28[2] - q28_2 -storedChoice: -q28[2] 8786166143426335913 -AnsweredRule {qHole_ = 8786166143426335913, qAscendants_ = fromList [-7531325615783388500,-6124769537006831453,-2577262930135244673,-590286472771932315,-83534367005148570,715122028962684739,1709615173437954783,5607005680561137835,7486385006046341809,7705725891024727552,8323234866884020390,8780789924434106151], aRuleName_ = "tuple-index"} -LF: {"AnsweredRule":{"aRuleName_":"tuple-index","qAscendants_":[-7531325615783388500,-6124769537006831453,-2577262930135244673,-590286472771932315,-83534367005148570,715122028962684739,1709615173437954783,5607005680561137835,7486385006046341809,7705725891024727552,8323234866884020390,8780789924434106151],"qHole_":8786166143426335913}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and({ [or([q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2 - | q28_1 : int(1..5), q28_2 : int(1..5), conjure_aux1_RelationAsMatrix[q28[1], q28[2]]]) - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - }) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: q28[1] - Context #1: conjure_aux1_RelationAsMatrix[q28[1]] - Context #2: conjure_aux1_RelationAsMatrix[q28[1], q28[2]] - Context #3: [q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2 - | q28_1 : int(1..5), q28_2 : int(1..5), conjure_aux1_RelationAsMatrix[q28[1], q28[2]]] - Context #4: or([q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2 - | q28_1 : int(1..5), q28_2 : int(1..5), conjure_aux1_RelationAsMatrix[q28[1], q28[2]]]) - Context #5: [or([q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2 - | q28_1 : int(1..5), q28_2 : int(1..5), conjure_aux1_RelationAsMatrix[q28[1], q28[2]]]) - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] - Context #6: { [or([q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2 - | q28_1 : int(1..5), q28_2 : int(1..5), conjure_aux1_RelationAsMatrix[q28[1], q28[2]]]) - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - } - Context #7: and({ [or([q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2 - | q28_1 : int(1..5), q28_2 : int(1..5), conjure_aux1_RelationAsMatrix[q28[1], q28[2]]]) - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - }) - Context #8: [|x| = |conjure_aux1|, - and({ [or([q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2 - | q28_1 : int(1..5), q28_2 : int(1..5), conjure_aux1_RelationAsMatrix[q28[1], q28[2]]]) - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - }); - int(1..2)] - Context #9: |x| = |conjure_aux1| /\ - and({ [or([q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2 - | q28_1 : int(1..5), q28_2 : int(1..5), conjure_aux1_RelationAsMatrix[q28[1], q28[2]]]) - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - }) - Context #10: { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and({ [or([q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2 - | q28_1 : int(1..5), q28_2 : int(1..5), conjure_aux1_RelationAsMatrix[q28[1], q28[2]]]) - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - }) - } - Context #11: y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and({ [or([q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2 - | q28_1 : int(1..5), q28_2 : int(1..5), conjure_aux1_RelationAsMatrix[q28[1], q28[2]]]) - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - }) - } -Picking the only option: Answer 1: tuple-index: Tuple indexing on: q28[1] - q28_1 -storedChoice: -q28[1] 8787010607011614834 -AnsweredRule {qHole_ = 8787010607011614834, qAscendants_ = fromList [-6233761776568569553,-6207878452900388515,-3381866216268371578,-560496032557153780,-80631966925160875,1067854355870431415,1108013619790213016,4161317878060049142,4647826867886404607,5228020545282852391,8646369751965333728], aRuleName_ = "tuple-index"} -LF: {"AnsweredRule":{"aRuleName_":"tuple-index","qAscendants_":[-6233761776568569553,-6207878452900388515,-3381866216268371578,-560496032557153780,-80631966925160875,1067854355870431415,1108013619790213016,4161317878060049142,4647826867886404607,5228020545282852391,8646369751965333728],"qHole_":8787010607011614834}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and({ [or([q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2 - | q28_1 : int(1..5), q28_2 : int(1..5), conjure_aux1_RelationAsMatrix[q28_1, q28[2]]]) - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - }) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: q28[2] - Context #1: conjure_aux1_RelationAsMatrix[q28_1, q28[2]] - Context #2: [q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2 - | q28_1 : int(1..5), q28_2 : int(1..5), conjure_aux1_RelationAsMatrix[q28_1, q28[2]]] - Context #3: or([q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2 - | q28_1 : int(1..5), q28_2 : int(1..5), conjure_aux1_RelationAsMatrix[q28_1, q28[2]]]) - Context #4: [or([q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2 - | q28_1 : int(1..5), q28_2 : int(1..5), conjure_aux1_RelationAsMatrix[q28_1, q28[2]]]) - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] - Context #5: { [or([q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2 - | q28_1 : int(1..5), q28_2 : int(1..5), conjure_aux1_RelationAsMatrix[q28_1, q28[2]]]) - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - } - Context #6: and({ [or([q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2 - | q28_1 : int(1..5), q28_2 : int(1..5), conjure_aux1_RelationAsMatrix[q28_1, q28[2]]]) - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - }) - Context #7: [|x| = |conjure_aux1|, - and({ [or([q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2 - | q28_1 : int(1..5), q28_2 : int(1..5), conjure_aux1_RelationAsMatrix[q28_1, q28[2]]]) - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - }); - int(1..2)] - Context #8: |x| = |conjure_aux1| /\ - and({ [or([q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2 - | q28_1 : int(1..5), q28_2 : int(1..5), conjure_aux1_RelationAsMatrix[q28_1, q28[2]]]) - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - }) - Context #9: { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and({ [or([q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2 - | q28_1 : int(1..5), q28_2 : int(1..5), conjure_aux1_RelationAsMatrix[q28_1, q28[2]]]) - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - }) - } - Context #10: y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and({ [or([q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2 - | q28_1 : int(1..5), q28_2 : int(1..5), conjure_aux1_RelationAsMatrix[q28_1, q28[2]]]) - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - }) - } -Picking the only option: Answer 1: tuple-index: Tuple indexing on: q28[2] - q28_2 -storedChoice: -q28[2] 8786166143426335913 -AnsweredRule {qHole_ = 8786166143426335913, qAscendants_ = fromList [-8932183048783716768,-6021176910053718006,-1484921959836170832,-1243263695470418987,-307241860641088143,5123914162100475129,6415834318102058907,6682610423178443283,7959220516069049554,8895625464985590456], aRuleName_ = "tuple-index"} -LF: {"AnsweredRule":{"aRuleName_":"tuple-index","qAscendants_":[-8932183048783716768,-6021176910053718006,-1484921959836170832,-1243263695470418987,-307241860641088143,5123914162100475129,6415834318102058907,6682610423178443283,7959220516069049554,8895625464985590456],"qHole_":8786166143426335913}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and({ [or([q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2 - | q28_1 : int(1..5), q28_2 : int(1..5), conjure_aux1_RelationAsMatrix[q28_1, q28_2]]) - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - }) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: [q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2 - | q28_1 : int(1..5), q28_2 : int(1..5), conjure_aux1_RelationAsMatrix[q28_1, q28_2]] - Context #1: or([q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2 - | q28_1 : int(1..5), q28_2 : int(1..5), conjure_aux1_RelationAsMatrix[q28_1, q28_2]]) - Context #2: [or([q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2 - | q28_1 : int(1..5), q28_2 : int(1..5), conjure_aux1_RelationAsMatrix[q28_1, q28_2]]) - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] - Context #3: { [or([q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2 - | q28_1 : int(1..5), q28_2 : int(1..5), conjure_aux1_RelationAsMatrix[q28_1, q28_2]]) - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - } - Context #4: and({ [or([q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2 - | q28_1 : int(1..5), q28_2 : int(1..5), conjure_aux1_RelationAsMatrix[q28_1, q28_2]]) - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - }) - Context #5: [|x| = |conjure_aux1|, - and({ [or([q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2 - | q28_1 : int(1..5), q28_2 : int(1..5), conjure_aux1_RelationAsMatrix[q28_1, q28_2]]) - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - }); - int(1..2)] - Context #6: |x| = |conjure_aux1| /\ - and({ [or([q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2 - | q28_1 : int(1..5), q28_2 : int(1..5), conjure_aux1_RelationAsMatrix[q28_1, q28_2]]) - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - }) - Context #7: { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and({ [or([q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2 - | q28_1 : int(1..5), q28_2 : int(1..5), conjure_aux1_RelationAsMatrix[q28_1, q28_2]]) - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - }) - } - Context #8: y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and({ [or([q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2 - | q28_1 : int(1..5), q28_2 : int(1..5), conjure_aux1_RelationAsMatrix[q28_1, q28_2]]) - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - }) - } -Picking the only option: Answer 1: inline-conditions: Inlining conditions, inside or - [conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)] -storedChoice: -[q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2 - | q28_1 : int(1..5), q28_2 : int(1..5), conjure_aux1_RelationAsMatrix[q28_1, q28_2]] -9107354217279316955 -AnsweredRule {qHole_ = -9107354217279316955, qAscendants_ = fromList [-7614046741660552896,-7556360939789777851,-6910364700408604777,-6183630476596424374,-2673910102480230275,7059218223957164648,8407785490318688805,8504193122766115214], aRuleName_ = "inline-conditions"} -LF: {"AnsweredRule":{"aRuleName_":"inline-conditions","qAscendants_":[-7614046741660552896,-7556360939789777851,-6910364700408604777,-6183630476596424374,-2673910102480230275,7059218223957164648,8407785490318688805,8504193122766115214],"qHole_":-9107354217279316955}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and({ [or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - }) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: and({ [or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ - (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - }) - Context #1: [|x| = |conjure_aux1|, - and({ [or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - }); - int(1..2)] - Context #2: |x| = |conjure_aux1| /\ - and({ [or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - }) - Context #3: { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and({ [or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - }) - } - Context #4: y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and({ [or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - }) - } -Picking the only option: Answer 1: bubble-up-LiftVars: Bubbling up auxiliary variables. - { and([or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]]) - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - } -storedChoice: -and({ [or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - }) 7825224301270217826 -AnsweredRule {qHole_ = 7825224301270217826, qAscendants_ = fromList [-7337214924393354854,-6793331199204698657,4098536301578040545,4694401685199555588], aRuleName_ = "bubble-up-LiftVars"} -LF: {"AnsweredRule":{"aRuleName_":"bubble-up-LiftVars","qAscendants_":[-7337214924393354854,-6793331199204698657,4098536301578040545,4694401685199555588],"qHole_":7825224301270217826}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - { and([or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]]) - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - } - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: [or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ - (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] - Context #1: and([or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]]) - Context #2: { and([or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]]) - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - } - Context #3: [|x| = |conjure_aux1|, - { and([or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]]) - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - }; int(1..2)] - Context #4: |x| = |conjure_aux1| /\ - { and([or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]]) - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - } - Context #5: { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - { and([or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]]) - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - } - } - Context #6: y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - { and([or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]]) - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - } - } -Picking the only option: Answer 1: inline-conditions: Inlining conditions, inside and - [x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)] -storedChoice: -[or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] -7818394351581759390 -AnsweredRule {qHole_ = -7818394351581759390, qAscendants_ = fromList [-8854367752148363141,868987242372315934,1952008385480716564,2094581585082781447,3197112935473569797,5197989222011368608], aRuleName_ = "inline-conditions"} -LF: {"AnsweredRule":{"aRuleName_":"inline-conditions","qAscendants_":[-8854367752148363141,868987242372315934,1952008385480716564,2094581585082781447,3197112935473569797,5197989222011368608],"qHole_":-7818394351581759390}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - { and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - } - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: [|x| = |conjure_aux1|, - { and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - }; int(1..2)] - Context #1: |x| = |conjure_aux1| /\ - { and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - } - Context #2: { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - { and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - } - } - Context #3: y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - { and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - } - } -Picking the only option: Answer 1: bubble-up-LiftVars: Bubbling up auxiliary variables. - { [|x| = |conjure_aux1|, - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]); - int(1..2)] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - } -storedChoice: -[|x| = |conjure_aux1|, - { and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - }; int(1..2)] 8700659888572119213 -AnsweredRule {qHole_ = 8700659888572119213, qAscendants_ = fromList [1085907639859271742,5213477129051060331,8301951387372896488], aRuleName_ = "bubble-up-LiftVars"} -LF: {"AnsweredRule":{"aRuleName_":"bubble-up-LiftVars","qAscendants_":[1085907639859271742,5213477129051060331,8301951387372896488],"qHole_":8700659888572119213}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - and({ [|x| = |conjure_aux1|, - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]); - int(1..2)] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - }) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: |x| - Context #1: |x| = |conjure_aux1| - Context #2: [|x| = |conjure_aux1|, - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]); - int(1..2)] - Context #3: { [|x| = |conjure_aux1|, - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]); - int(1..2)] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - } - Context #4: and({ [|x| = |conjure_aux1|, - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]); - int(1..2)] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - }) - Context #5: { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - and({ [|x| = |conjure_aux1|, - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]); - int(1..2)] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - }) - } - Context #6: y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - and({ [|x| = |conjure_aux1|, - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]); - int(1..2)] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - }) - } -Picking the only option: Answer 1: relation-cardinality: Relation cardinality - |toSet(x)| -storedChoice: -|x| -1852370716973049233 -AnsweredRule {qHole_ = -1852370716973049233, qAscendants_ = fromList [-8274899275771564111,-7189265364834618222,-4195293662753593531,-2250203036499850017,4837893138970417558,5156053544824672407], aRuleName_ = "relation-cardinality"} -LF: {"AnsweredRule":{"aRuleName_":"relation-cardinality","qAscendants_":[-8274899275771564111,-7189265364834618222,-4195293662753593531,-2250203036499850017,4837893138970417558,5156053544824672407],"qHole_":-1852370716973049233}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - and({ [|toSet(x)| = |conjure_aux1|, - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]); - int(1..2)] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - }) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: |toSet(x)| - Context #1: |toSet(x)| = |conjure_aux1| - Context #2: [|toSet(x)| = |conjure_aux1|, - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]); - int(1..2)] - Context #3: { [|toSet(x)| = |conjure_aux1|, - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]); - int(1..2)] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - } - Context #4: and({ [|toSet(x)| = |conjure_aux1|, - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]); - int(1..2)] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - }) - Context #5: { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - and({ [|toSet(x)| = |conjure_aux1|, - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]); - int(1..2)] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - }) - } - Context #6: y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - and({ [|toSet(x)| = |conjure_aux1|, - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]); - int(1..2)] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - }) - } -Picking the only option: Answer 1: set-card: Horizontal rule for set cardinality. - sum([1 | q29 <- toSet(x)]) -storedChoice: -|toSet(x)| 1897988597909520616 -AnsweredRule {qHole_ = 1897988597909520616, qAscendants_ = fromList [-6188688663705288789,-5846429895491118400,361855989135376679,6530150935582701688,7219968226893579546,7779309324238844246], aRuleName_ = "set-card"} -LF: {"AnsweredRule":{"aRuleName_":"set-card","qAscendants_":[-6188688663705288789,-5846429895491118400,361855989135376679,6530150935582701688,7219968226893579546,7779309324238844246],"qHole_":1897988597909520616}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - and({ [sum([1 | q29 <- toSet(x)]) = |conjure_aux1|, - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]); - int(1..2)] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - }) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: [1 | q29 <- toSet(x)] - Context #1: sum([1 | q29 <- toSet(x)]) - Context #2: sum([1 | q29 <- toSet(x)]) = |conjure_aux1| - Context #3: [sum([1 | q29 <- toSet(x)]) = |conjure_aux1|, - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]); - int(1..2)] - Context #4: { [sum([1 | q29 <- toSet(x)]) = |conjure_aux1|, - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]); - int(1..2)] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - } - Context #5: and({ [sum([1 | q29 <- toSet(x)]) = |conjure_aux1|, - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]); - int(1..2)] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - }) - Context #6: { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - and({ [sum([1 | q29 <- toSet(x)]) = |conjure_aux1|, - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]); - int(1..2)] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - }) - } - Context #7: y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - and({ [sum([1 | q29 <- toSet(x)]) = |conjure_aux1|, - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]); - int(1..2)] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - }) - } -Picking the only option: Answer 1: relation-map_in_expr{RelationAsMatrix}: Vertical rule for map_in_expr for relation domains, RelationAsMatrix representation. - [1 | q30 : (int(1..5), int(1..5)), x_RelationAsMatrix[q30[1], q30[2]]] -storedChoice: -[1 | q29 <- toSet(x)] 7483192753320191769 -AnsweredRule {qHole_ = 7483192753320191769, qAscendants_ = fromList [-7918094600437589284,-6091097458145320110,-4725927117271772380,-3818842550960350061,-801403655548510881,4177802111281067004,8691639764190092042], aRuleName_ = "relation-map_in_expr{RelationAsMatrix}"} -LF: {"AnsweredRule":{"aRuleName_":"relation-map_in_expr{RelationAsMatrix}","qAscendants_":[-7918094600437589284,-6091097458145320110,-4725927117271772380,-3818842550960350061,-801403655548510881,4177802111281067004,8691639764190092042],"qHole_":7483192753320191769}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - and({ [sum([1 | q30 : (int(1..5), int(1..5)), x_RelationAsMatrix[q30[1], q30[2]]]) = |conjure_aux1|, - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]); - int(1..2)] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - }) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: [1 | q30 : (int(1..5), int(1..5)), x_RelationAsMatrix[q30[1], q30[2]]] - Context #1: sum([1 | q30 : (int(1..5), int(1..5)), x_RelationAsMatrix[q30[1], q30[2]]]) - Context #2: sum([1 | q30 : (int(1..5), int(1..5)), x_RelationAsMatrix[q30[1], q30[2]]]) = |conjure_aux1| - Context #3: [sum([1 | q30 : (int(1..5), int(1..5)), x_RelationAsMatrix[q30[1], q30[2]]]) = |conjure_aux1|, - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]); - int(1..2)] - Context #4: { [sum([1 | q30 : (int(1..5), int(1..5)), x_RelationAsMatrix[q30[1], q30[2]]]) = |conjure_aux1|, - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]); - int(1..2)] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - } - Context #5: and({ [sum([1 | q30 : (int(1..5), int(1..5)), x_RelationAsMatrix[q30[1], q30[2]]]) = |conjure_aux1|, - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]); - int(1..2)] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - }) - Context #6: { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - and({ [sum([1 | q30 : (int(1..5), int(1..5)), x_RelationAsMatrix[q30[1], q30[2]]]) = |conjure_aux1|, - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]); - int(1..2)] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - }) - } - Context #7: y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - and({ [sum([1 | q30 : (int(1..5), int(1..5)), x_RelationAsMatrix[q30[1], q30[2]]]) = |conjure_aux1|, - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]); - int(1..2)] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - }) - } -Picking the only option: Answer 1: choose-repr-for-comprehension: Choosing representation for quantified variable q30 (with type: (int, - int)) - [1 | q30_1 : int(1..5), q30_2 : int(1..5), x_RelationAsMatrix[q30[1], q30[2]]] -storedChoice: -[1 | q30 : (int(1..5), int(1..5)), x_RelationAsMatrix[q30[1], q30[2]]] -2219318056453463832 -AnsweredRule {qHole_ = -2219318056453463832, qAscendants_ = fromList [-7631595452381029825,-6332648069028765836,-5599362277318624933,-1170492770147107149,188905738781826972,1046361987104095667,9181513732839926293], aRuleName_ = "choose-repr-for-comprehension"} -LF: {"AnsweredRule":{"aRuleName_":"choose-repr-for-comprehension","qAscendants_":[-7631595452381029825,-6332648069028765836,-5599362277318624933,-1170492770147107149,188905738781826972,1046361987104095667,9181513732839926293],"qHole_":-2219318056453463832}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - and({ [sum([1 | q30_1 : int(1..5), q30_2 : int(1..5), x_RelationAsMatrix[q30[1], q30[2]]]) = |conjure_aux1|, - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]); - int(1..2)] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - }) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: q30[1] - Context #1: x_RelationAsMatrix[q30[1]] - Context #2: x_RelationAsMatrix[q30[1], q30[2]] - Context #3: [1 | q30_1 : int(1..5), q30_2 : int(1..5), x_RelationAsMatrix[q30[1], q30[2]]] - Context #4: sum([1 | q30_1 : int(1..5), q30_2 : int(1..5), x_RelationAsMatrix[q30[1], q30[2]]]) - Context #5: sum([1 | q30_1 : int(1..5), q30_2 : int(1..5), x_RelationAsMatrix[q30[1], q30[2]]]) = |conjure_aux1| - Context #6: [sum([1 | q30_1 : int(1..5), q30_2 : int(1..5), x_RelationAsMatrix[q30[1], q30[2]]]) = |conjure_aux1|, - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]); - int(1..2)] - Context #7: { [sum([1 | q30_1 : int(1..5), q30_2 : int(1..5), x_RelationAsMatrix[q30[1], q30[2]]]) = |conjure_aux1|, - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]); - int(1..2)] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - } - Context #8: and({ [sum([1 | q30_1 : int(1..5), q30_2 : int(1..5), x_RelationAsMatrix[q30[1], q30[2]]]) = |conjure_aux1|, - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]); - int(1..2)] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - }) - Context #9: { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - and({ [sum([1 | q30_1 : int(1..5), q30_2 : int(1..5), x_RelationAsMatrix[q30[1], q30[2]]]) = |conjure_aux1|, - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]); - int(1..2)] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - }) - } - Context #10: y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - and({ [sum([1 | q30_1 : int(1..5), q30_2 : int(1..5), x_RelationAsMatrix[q30[1], q30[2]]]) = |conjure_aux1|, - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]); - int(1..2)] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - }) - } -Picking the only option: Answer 1: tuple-index: Tuple indexing on: q30[1] - q30_1 -storedChoice: -q30[1] 8985411351629801837 -AnsweredRule {qHole_ = 8985411351629801837, qAscendants_ = fromList [-7287907811082918289,-3433749237930268197,-1514549063082826885,-254808116082235497,1395102958002486929,3724900484480857440,3763839719817425200,3764103551892886579,7098469255683427931,8809290278576126972], aRuleName_ = "tuple-index"} -LF: {"AnsweredRule":{"aRuleName_":"tuple-index","qAscendants_":[-7287907811082918289,-3433749237930268197,-1514549063082826885,-254808116082235497,1395102958002486929,3724900484480857440,3763839719817425200,3764103551892886579,7098469255683427931,8809290278576126972],"qHole_":8985411351629801837}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - and({ [sum([1 | q30_1 : int(1..5), q30_2 : int(1..5), x_RelationAsMatrix[q30_1, q30[2]]]) = |conjure_aux1|, - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]); - int(1..2)] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - }) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: q30[2] - Context #1: x_RelationAsMatrix[q30_1, q30[2]] - Context #2: [1 | q30_1 : int(1..5), q30_2 : int(1..5), x_RelationAsMatrix[q30_1, q30[2]]] - Context #3: sum([1 | q30_1 : int(1..5), q30_2 : int(1..5), x_RelationAsMatrix[q30_1, q30[2]]]) - Context #4: sum([1 | q30_1 : int(1..5), q30_2 : int(1..5), x_RelationAsMatrix[q30_1, q30[2]]]) = |conjure_aux1| - Context #5: [sum([1 | q30_1 : int(1..5), q30_2 : int(1..5), x_RelationAsMatrix[q30_1, q30[2]]]) = |conjure_aux1|, - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]); - int(1..2)] - Context #6: { [sum([1 | q30_1 : int(1..5), q30_2 : int(1..5), x_RelationAsMatrix[q30_1, q30[2]]]) = |conjure_aux1|, - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]); - int(1..2)] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - } - Context #7: and({ [sum([1 | q30_1 : int(1..5), q30_2 : int(1..5), x_RelationAsMatrix[q30_1, q30[2]]]) = |conjure_aux1|, - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]); - int(1..2)] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - }) - Context #8: { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - and({ [sum([1 | q30_1 : int(1..5), q30_2 : int(1..5), x_RelationAsMatrix[q30_1, q30[2]]]) = |conjure_aux1|, - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]); - int(1..2)] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - }) - } - Context #9: y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - and({ [sum([1 | q30_1 : int(1..5), q30_2 : int(1..5), x_RelationAsMatrix[q30_1, q30[2]]]) = |conjure_aux1|, - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]); - int(1..2)] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - }) - } -Picking the only option: Answer 1: tuple-index: Tuple indexing on: q30[2] - q30_2 -storedChoice: -q30[2] 8986255815215080758 -AnsweredRule {qHole_ = 8986255815215080758, qAscendants_ = fromList [-1904605123138931514,-1605383351683875510,-1500814072571245463,-1159370656118278861,-345152881798089093,3653718321561964858,5560045049720260591,6001294353827372355,7845034033468093823], aRuleName_ = "tuple-index"} -LF: {"AnsweredRule":{"aRuleName_":"tuple-index","qAscendants_":[-1904605123138931514,-1605383351683875510,-1500814072571245463,-1159370656118278861,-345152881798089093,3653718321561964858,5560045049720260591,6001294353827372355,7845034033468093823],"qHole_":8986255815215080758}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - and({ [sum([1 | q30_1 : int(1..5), q30_2 : int(1..5), x_RelationAsMatrix[q30_1, q30_2]]) = |conjure_aux1|, - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]); - int(1..2)] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - }) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: [1 | q30_1 : int(1..5), q30_2 : int(1..5), x_RelationAsMatrix[q30_1, q30_2]] - Context #1: sum([1 | q30_1 : int(1..5), q30_2 : int(1..5), x_RelationAsMatrix[q30_1, q30_2]]) - Context #2: sum([1 | q30_1 : int(1..5), q30_2 : int(1..5), x_RelationAsMatrix[q30_1, q30_2]]) = |conjure_aux1| - Context #3: [sum([1 | q30_1 : int(1..5), q30_2 : int(1..5), x_RelationAsMatrix[q30_1, q30_2]]) = |conjure_aux1|, - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]); - int(1..2)] - Context #4: { [sum([1 | q30_1 : int(1..5), q30_2 : int(1..5), x_RelationAsMatrix[q30_1, q30_2]]) = |conjure_aux1|, - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]); - int(1..2)] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - } - Context #5: and({ [sum([1 | q30_1 : int(1..5), q30_2 : int(1..5), x_RelationAsMatrix[q30_1, q30_2]]) = |conjure_aux1|, - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]); - int(1..2)] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - }) - Context #6: { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - and({ [sum([1 | q30_1 : int(1..5), q30_2 : int(1..5), x_RelationAsMatrix[q30_1, q30_2]]) = |conjure_aux1|, - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]); - int(1..2)] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - }) - } - Context #7: y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - and({ [sum([1 | q30_1 : int(1..5), q30_2 : int(1..5), x_RelationAsMatrix[q30_1, q30_2]]) = |conjure_aux1|, - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]); - int(1..2)] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - }) - } -Picking the only option: Answer 1: inline-conditions: Inlining conditions, inside sum - [toInt(x_RelationAsMatrix[q30_1, q30_2]) * catchUndef(1, 0) | q30_1 : int(1..5), q30_2 : int(1..5)] -storedChoice: -[1 | q30_1 : int(1..5), q30_2 : int(1..5), x_RelationAsMatrix[q30_1, q30_2]] 6730778895089912004 -AnsweredRule {qHole_ = 6730778895089912004, qAscendants_ = fromList [-5543455485138138697,-1367499344277324489,-577770218778700729,3965135726409895025,4154476703970574900,4424005630299656964,8591791291160167043], aRuleName_ = "inline-conditions"} -LF: {"AnsweredRule":{"aRuleName_":"inline-conditions","qAscendants_":[-5543455485138138697,-1367499344277324489,-577770218778700729,3965135726409895025,4154476703970574900,4424005630299656964,8591791291160167043],"qHole_":6730778895089912004}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - and({ [sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) * catchUndef(1, 0) | q30_1 : int(1..5), q30_2 : int(1..5)]) = |conjure_aux1|, - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]); - int(1..2)] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - }) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: catchUndef(1, 0) - Context #1: [toInt(x_RelationAsMatrix[q30_1, q30_2]), catchUndef(1, 0); int(1..2)] - Context #2: toInt(x_RelationAsMatrix[q30_1, q30_2]) * catchUndef(1, 0) - Context #3: [toInt(x_RelationAsMatrix[q30_1, q30_2]) * catchUndef(1, 0) | q30_1 : int(1..5), q30_2 : int(1..5)] - Context #4: sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) * catchUndef(1, 0) | q30_1 : int(1..5), q30_2 : int(1..5)]) - Context #5: sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) * catchUndef(1, 0) | q30_1 : int(1..5), q30_2 : int(1..5)]) = |conjure_aux1| - Context #6: [sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) * catchUndef(1, 0) | q30_1 : int(1..5), q30_2 : int(1..5)]) = - |conjure_aux1|, - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]); - int(1..2)] - Context #7: { [sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) * catchUndef(1, 0) | q30_1 : int(1..5), q30_2 : int(1..5)]) = - |conjure_aux1|, - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]); - int(1..2)] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - } - Context #8: and({ [sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) * catchUndef(1, 0) | q30_1 : int(1..5), q30_2 : int(1..5)]) = - |conjure_aux1|, - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]); - int(1..2)] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - }) - Context #9: { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - and({ [sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) * catchUndef(1, 0) | q30_1 : int(1..5), q30_2 : int(1..5)]) = |conjure_aux1|, - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]); - int(1..2)] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - }) - } - Context #10: y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - and({ [sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) * catchUndef(1, 0) | q30_1 : int(1..5), q30_2 : int(1..5)]) = |conjure_aux1|, - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]); - int(1..2)] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - }) - } -Picking the only option: Answer 1: full-evaluate: Full evaluator - 1 -storedChoice: -catchUndef(1, 0) -4103543015608659681 -AnsweredRule {qHole_ = -4103543015608659681, qAscendants_ = fromList [-6246651641675555191,-4991494778996523170,-4841212563091249093,-3913142375130629094,-3482484897580979170,-192545505272530247,4617164660703414243,7663465281870587155,7888233777833351600,8484251082711739255], aRuleName_ = "full-evaluate"} -LF: {"AnsweredRule":{"aRuleName_":"full-evaluate","qAscendants_":[-6246651641675555191,-4991494778996523170,-4841212563091249093,-3913142375130629094,-3482484897580979170,-192545505272530247,4617164660703414243,7663465281870587155,7888233777833351600,8484251082711739255],"qHole_":-4103543015608659681}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - and({ [sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) * 1 | q30_1 : int(1..5), q30_2 : int(1..5)]) = |conjure_aux1|, - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]); - int(1..2)] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - }) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: toInt(x_RelationAsMatrix[q30_1, q30_2]) * 1 - Context #1: [toInt(x_RelationAsMatrix[q30_1, q30_2]) * 1 | q30_1 : int(1..5), q30_2 : int(1..5)] - Context #2: sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) * 1 | q30_1 : int(1..5), q30_2 : int(1..5)]) - Context #3: sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) * 1 | q30_1 : int(1..5), q30_2 : int(1..5)]) = |conjure_aux1| - Context #4: [sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) * 1 | q30_1 : int(1..5), q30_2 : int(1..5)]) = |conjure_aux1|, - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]); - int(1..2)] - Context #5: { [sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) * 1 | q30_1 : int(1..5), q30_2 : int(1..5)]) = |conjure_aux1|, - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]); - int(1..2)] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - } - Context #6: and({ [sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) * 1 | q30_1 : int(1..5), q30_2 : int(1..5)]) = |conjure_aux1|, - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]); - int(1..2)] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - }) - Context #7: { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - and({ [sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) * 1 | q30_1 : int(1..5), q30_2 : int(1..5)]) = |conjure_aux1|, - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]); - int(1..2)] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - }) - } - Context #8: y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - and({ [sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) * 1 | q30_1 : int(1..5), q30_2 : int(1..5)]) = |conjure_aux1|, - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]); - int(1..2)] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - }) - } -Picking the only option: Answer 1: partial-evaluate: Partial evaluator - product([toInt(x_RelationAsMatrix[q30_1, q30_2]); int(1)]) -storedChoice: -toInt(x_RelationAsMatrix[q30_1, q30_2]) * 1 -1687514346990485250 -AnsweredRule {qHole_ = -1687514346990485250, qAscendants_ = fromList [-8383279591293107624,-5870374077749082103,-5035592936147091491,-3450507034164856240,-3171744958437112094,-148321104615195040,923428228047877070,2221664695150773241], aRuleName_ = "partial-evaluate"} -LF: {"AnsweredRule":{"aRuleName_":"partial-evaluate","qAscendants_":[-8383279591293107624,-5870374077749082103,-5035592936147091491,-3450507034164856240,-3171744958437112094,-148321104615195040,923428228047877070,2221664695150773241],"qHole_":-1687514346990485250}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - and({ [sum([product([toInt(x_RelationAsMatrix[q30_1, q30_2]); int(1)]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = |conjure_aux1|, - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]); - int(1..2)] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - }) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: product([toInt(x_RelationAsMatrix[q30_1, q30_2]); int(1)]) - Context #1: [product([toInt(x_RelationAsMatrix[q30_1, q30_2]); int(1)]) | q30_1 : int(1..5), q30_2 : int(1..5)] - Context #2: sum([product([toInt(x_RelationAsMatrix[q30_1, q30_2]); int(1)]) | q30_1 : int(1..5), q30_2 : int(1..5)]) - Context #3: sum([product([toInt(x_RelationAsMatrix[q30_1, q30_2]); int(1)]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = |conjure_aux1| - Context #4: [sum([product([toInt(x_RelationAsMatrix[q30_1, q30_2]); int(1)]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = - |conjure_aux1|, - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]); - int(1..2)] - Context #5: { [sum([product([toInt(x_RelationAsMatrix[q30_1, q30_2]); int(1)]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = - |conjure_aux1|, - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]); - int(1..2)] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - } - Context #6: and({ [sum([product([toInt(x_RelationAsMatrix[q30_1, q30_2]); int(1)]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = - |conjure_aux1|, - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]); - int(1..2)] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - }) - Context #7: { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - and({ [sum([product([toInt(x_RelationAsMatrix[q30_1, q30_2]); int(1)]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = |conjure_aux1|, - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]); - int(1..2)] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - }) - } - Context #8: y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - and({ [sum([product([toInt(x_RelationAsMatrix[q30_1, q30_2]); int(1)]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = |conjure_aux1|, - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]); - int(1..2)] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - }) - } -Picking the only option: Answer 1: matrix-comprehension-singleton: Removing quantifier of a single item - toInt(x_RelationAsMatrix[q30_1, q30_2]) -storedChoice: -product([toInt(x_RelationAsMatrix[q30_1, q30_2]); int(1)]) -601225972055529548 -AnsweredRule {qHole_ = -601225972055529548, qAscendants_ = fromList [-7799870564036439127,-7432780384698737696,-6354763341195320334,-5508479272970515476,-2004497734168533005,1354218247559476283,3284517275149475981,4357080134642246606], aRuleName_ = "matrix-comprehension-singleton"} -LF: {"AnsweredRule":{"aRuleName_":"matrix-comprehension-singleton","qAscendants_":[-7799870564036439127,-7432780384698737696,-6354763341195320334,-5508479272970515476,-2004497734168533005,1354218247559476283,3284517275149475981,4357080134642246606],"qHole_":-601225972055529548}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - and({ [sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = |conjure_aux1|, - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]); - int(1..2)] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - }) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: |conjure_aux1| - Context #1: sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = |conjure_aux1| - Context #2: [sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = |conjure_aux1|, - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]); - int(1..2)] - Context #3: { [sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = |conjure_aux1|, - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]); - int(1..2)] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - } - Context #4: and({ [sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = |conjure_aux1|, - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]); - int(1..2)] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - }) - Context #5: { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - and({ [sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = |conjure_aux1|, - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]); - int(1..2)] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - }) - } - Context #6: y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - and({ [sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = |conjure_aux1|, - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]); - int(1..2)] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - }) - } -Picking the only option: Answer 1: relation-cardinality: Relation cardinality - |toSet(conjure_aux1)| -storedChoice: -|conjure_aux1| 547691173299348338 -AnsweredRule {qHole_ = 547691173299348338, qAscendants_ = fromList [-7326096647933004975,-3638343112521383479,-2681179249513342582,-1433468233918517477,416753721122881089,6250330639306929770], aRuleName_ = "relation-cardinality"} -LF: {"AnsweredRule":{"aRuleName_":"relation-cardinality","qAscendants_":[-7326096647933004975,-3638343112521383479,-2681179249513342582,-1433468233918517477,416753721122881089,6250330639306929770],"qHole_":547691173299348338}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - and({ [sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = |toSet(conjure_aux1)|, - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]); - int(1..2)] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - }) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: |toSet(conjure_aux1)| - Context #1: sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = |toSet(conjure_aux1)| - Context #2: [sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = |toSet(conjure_aux1)|, - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]); - int(1..2)] - Context #3: { [sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = |toSet(conjure_aux1)|, - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]); - int(1..2)] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - } - Context #4: and({ [sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = |toSet(conjure_aux1)|, - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]); - int(1..2)] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - }) - Context #5: { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - and({ [sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = |toSet(conjure_aux1)|, - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]); - int(1..2)] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - }) - } - Context #6: y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - and({ [sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = |toSet(conjure_aux1)|, - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]); - int(1..2)] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - }) - } -Picking the only option: Answer 1: set-card: Horizontal rule for set cardinality. - sum([1 | q31 <- toSet(conjure_aux1)]) -storedChoice: -|toSet(conjure_aux1)| -1999756309500896427 -AnsweredRule {qHole_ = -1999756309500896427, qAscendants_ = fromList [-7320026331482846196,-1560614952215100976,3610191966919989235,3922795876024111867,4652593413741964988,8460019197720106806], aRuleName_ = "set-card"} -LF: {"AnsweredRule":{"aRuleName_":"set-card","qAscendants_":[-7320026331482846196,-1560614952215100976,3610191966919989235,3922795876024111867,4652593413741964988,8460019197720106806],"qHole_":-1999756309500896427}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - and({ [sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = sum([1 | q31 <- toSet(conjure_aux1)]), - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]); - int(1..2)] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - }) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: [1 | q31 <- toSet(conjure_aux1)] - Context #1: sum([1 | q31 <- toSet(conjure_aux1)]) - Context #2: sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = - sum([1 | q31 <- toSet(conjure_aux1)]) - Context #3: [sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = - sum([1 | q31 <- toSet(conjure_aux1)]), - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]); - int(1..2)] - Context #4: { [sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = - sum([1 | q31 <- toSet(conjure_aux1)]), - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]); - int(1..2)] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - } - Context #5: and({ [sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = - sum([1 | q31 <- toSet(conjure_aux1)]), - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]); - int(1..2)] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - }) - Context #6: { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - and({ [sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = sum([1 | q31 <- toSet(conjure_aux1)]), - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]); - int(1..2)] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - }) - } - Context #7: y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - and({ [sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = sum([1 | q31 <- toSet(conjure_aux1)]), - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]); - int(1..2)] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - }) - } -Picking the only option: Answer 1: relation-map_in_expr{RelationAsMatrix}: Vertical rule for map_in_expr for relation domains, RelationAsMatrix representation. - [1 | q32 : (int(1..5), int(1..5)), conjure_aux1_RelationAsMatrix[q32[1], q32[2]]] -storedChoice: -[1 | q31 <- toSet(conjure_aux1)] 4978495210772817269 -AnsweredRule {qHole_ = 4978495210772817269, qAscendants_ = fromList [-7947851092910419335,-4272160902177458760,-654328132560036401,4133420425219294144,6369167416454940534,6390095031407007755,7113998651427981501], aRuleName_ = "relation-map_in_expr{RelationAsMatrix}"} -LF: {"AnsweredRule":{"aRuleName_":"relation-map_in_expr{RelationAsMatrix}","qAscendants_":[-7947851092910419335,-4272160902177458760,-654328132560036401,4133420425219294144,6369167416454940534,6390095031407007755,7113998651427981501],"qHole_":4978495210772817269}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - and({ [sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = - sum([1 | q32 : (int(1..5), int(1..5)), conjure_aux1_RelationAsMatrix[q32[1], q32[2]]]), - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]); - int(1..2)] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - }) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: [1 | q32 : (int(1..5), int(1..5)), conjure_aux1_RelationAsMatrix[q32[1], q32[2]]] - Context #1: sum([1 | q32 : (int(1..5), int(1..5)), conjure_aux1_RelationAsMatrix[q32[1], q32[2]]]) - Context #2: sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = - sum([1 | q32 : (int(1..5), int(1..5)), conjure_aux1_RelationAsMatrix[q32[1], q32[2]]]) - Context #3: [sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = - sum([1 | q32 : (int(1..5), int(1..5)), conjure_aux1_RelationAsMatrix[q32[1], q32[2]]]), - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]); - int(1..2)] - Context #4: { [sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = - sum([1 | q32 : (int(1..5), int(1..5)), conjure_aux1_RelationAsMatrix[q32[1], q32[2]]]), - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]); - int(1..2)] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - } - Context #5: and({ [sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = - sum([1 | q32 : (int(1..5), int(1..5)), conjure_aux1_RelationAsMatrix[q32[1], q32[2]]]), - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]); - int(1..2)] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - }) - Context #6: { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - and({ [sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = - sum([1 | q32 : (int(1..5), int(1..5)), conjure_aux1_RelationAsMatrix[q32[1], q32[2]]]), - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]); - int(1..2)] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - }) - } - Context #7: y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - and({ [sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = - sum([1 | q32 : (int(1..5), int(1..5)), conjure_aux1_RelationAsMatrix[q32[1], q32[2]]]), - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]); - int(1..2)] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - }) - } -Picking the only option: Answer 1: choose-repr-for-comprehension: Choosing representation for quantified variable q32 (with type: (int, - int)) - [1 | q32_1 : int(1..5), q32_2 : int(1..5), conjure_aux1_RelationAsMatrix[q32[1], q32[2]]] -storedChoice: -[1 | q32 : (int(1..5), int(1..5)), conjure_aux1_RelationAsMatrix[q32[1], q32[2]]] 3282965607985773269 -AnsweredRule {qHole_ = 3282965607985773269, qAscendants_ = fromList [-7122899784982260955,-5889198071192861072,-531055723096273851,147713573061616732,2477913925342540157,3767703974941705567,9091983968002426702], aRuleName_ = "choose-repr-for-comprehension"} -LF: {"AnsweredRule":{"aRuleName_":"choose-repr-for-comprehension","qAscendants_":[-7122899784982260955,-5889198071192861072,-531055723096273851,147713573061616732,2477913925342540157,3767703974941705567,9091983968002426702],"qHole_":3282965607985773269}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - and({ [sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = - sum([1 | q32_1 : int(1..5), q32_2 : int(1..5), conjure_aux1_RelationAsMatrix[q32[1], q32[2]]]), - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]); - int(1..2)] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - }) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: q32[1] - Context #1: conjure_aux1_RelationAsMatrix[q32[1]] - Context #2: conjure_aux1_RelationAsMatrix[q32[1], q32[2]] - Context #3: [1 | q32_1 : int(1..5), q32_2 : int(1..5), conjure_aux1_RelationAsMatrix[q32[1], q32[2]]] - Context #4: sum([1 | q32_1 : int(1..5), q32_2 : int(1..5), conjure_aux1_RelationAsMatrix[q32[1], q32[2]]]) - Context #5: sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = - sum([1 | q32_1 : int(1..5), q32_2 : int(1..5), conjure_aux1_RelationAsMatrix[q32[1], q32[2]]]) - Context #6: [sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = - sum([1 | q32_1 : int(1..5), q32_2 : int(1..5), conjure_aux1_RelationAsMatrix[q32[1], q32[2]]]), - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]); - int(1..2)] - Context #7: { [sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = - sum([1 | q32_1 : int(1..5), q32_2 : int(1..5), conjure_aux1_RelationAsMatrix[q32[1], q32[2]]]), - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]); - int(1..2)] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - } - Context #8: and({ [sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = - sum([1 | q32_1 : int(1..5), q32_2 : int(1..5), conjure_aux1_RelationAsMatrix[q32[1], q32[2]]]), - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]); - int(1..2)] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - }) - Context #9: { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - and({ [sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = - sum([1 | q32_1 : int(1..5), q32_2 : int(1..5), conjure_aux1_RelationAsMatrix[q32[1], q32[2]]]), - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]); - int(1..2)] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - }) - } - Context #10: y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - and({ [sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = - sum([1 | q32_1 : int(1..5), q32_2 : int(1..5), conjure_aux1_RelationAsMatrix[q32[1], q32[2]]]), - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]); - int(1..2)] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - }) - } -Picking the only option: Answer 1: tuple-index: Tuple indexing on: q32[1] - q32_1 -storedChoice: -q32[1] 4038868374035555703 -AnsweredRule {qHole_ = 4038868374035555703, qAscendants_ = fromList [-8553658543572221773,-6138711856874023512,-4335853381078465244,-2646146961819662754,-2343456358494450273,-1664802311461525085,-1649342081664357811,3161695419280017087,3741265834386353390,8703630850884516346], aRuleName_ = "tuple-index"} -LF: {"AnsweredRule":{"aRuleName_":"tuple-index","qAscendants_":[-8553658543572221773,-6138711856874023512,-4335853381078465244,-2646146961819662754,-2343456358494450273,-1664802311461525085,-1649342081664357811,3161695419280017087,3741265834386353390,8703630850884516346],"qHole_":4038868374035555703}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - and({ [sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = - sum([1 | q32_1 : int(1..5), q32_2 : int(1..5), conjure_aux1_RelationAsMatrix[q32_1, q32[2]]]), - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]); - int(1..2)] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - }) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: q32[2] - Context #1: conjure_aux1_RelationAsMatrix[q32_1, q32[2]] - Context #2: [1 | q32_1 : int(1..5), q32_2 : int(1..5), conjure_aux1_RelationAsMatrix[q32_1, q32[2]]] - Context #3: sum([1 | q32_1 : int(1..5), q32_2 : int(1..5), conjure_aux1_RelationAsMatrix[q32_1, q32[2]]]) - Context #4: sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = - sum([1 | q32_1 : int(1..5), q32_2 : int(1..5), conjure_aux1_RelationAsMatrix[q32_1, q32[2]]]) - Context #5: [sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = - sum([1 | q32_1 : int(1..5), q32_2 : int(1..5), conjure_aux1_RelationAsMatrix[q32_1, q32[2]]]), - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]); - int(1..2)] - Context #6: { [sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = - sum([1 | q32_1 : int(1..5), q32_2 : int(1..5), conjure_aux1_RelationAsMatrix[q32_1, q32[2]]]), - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]); - int(1..2)] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - } - Context #7: and({ [sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = - sum([1 | q32_1 : int(1..5), q32_2 : int(1..5), conjure_aux1_RelationAsMatrix[q32_1, q32[2]]]), - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]); - int(1..2)] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - }) - Context #8: { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - and({ [sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = - sum([1 | q32_1 : int(1..5), q32_2 : int(1..5), conjure_aux1_RelationAsMatrix[q32_1, q32[2]]]), - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]); - int(1..2)] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - }) - } - Context #9: y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - and({ [sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = - sum([1 | q32_1 : int(1..5), q32_2 : int(1..5), conjure_aux1_RelationAsMatrix[q32_1, q32[2]]]), - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]); - int(1..2)] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - }) - } -Picking the only option: Answer 1: tuple-index: Tuple indexing on: q32[2] - q32_2 -storedChoice: -q32[2] 4038586886173796060 -AnsweredRule {qHole_ = 4038586886173796060, qAscendants_ = fromList [58246981470148902,365936135746281162,897915292494521279,2148255109439096362,2599338170801596327,4347596293011070033,8156974448309241515,8375135551163386670,8976994852842826417], aRuleName_ = "tuple-index"} -LF: {"AnsweredRule":{"aRuleName_":"tuple-index","qAscendants_":[58246981470148902,365936135746281162,897915292494521279,2148255109439096362,2599338170801596327,4347596293011070033,8156974448309241515,8375135551163386670,8976994852842826417],"qHole_":4038586886173796060}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - and({ [sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = - sum([1 | q32_1 : int(1..5), q32_2 : int(1..5), conjure_aux1_RelationAsMatrix[q32_1, q32_2]]), - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]); - int(1..2)] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - }) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: [1 | q32_1 : int(1..5), q32_2 : int(1..5), conjure_aux1_RelationAsMatrix[q32_1, q32_2]] - Context #1: sum([1 | q32_1 : int(1..5), q32_2 : int(1..5), conjure_aux1_RelationAsMatrix[q32_1, q32_2]]) - Context #2: sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = - sum([1 | q32_1 : int(1..5), q32_2 : int(1..5), conjure_aux1_RelationAsMatrix[q32_1, q32_2]]) - Context #3: [sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = - sum([1 | q32_1 : int(1..5), q32_2 : int(1..5), conjure_aux1_RelationAsMatrix[q32_1, q32_2]]), - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]); - int(1..2)] - Context #4: { [sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = - sum([1 | q32_1 : int(1..5), q32_2 : int(1..5), conjure_aux1_RelationAsMatrix[q32_1, q32_2]]), - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]); - int(1..2)] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - } - Context #5: and({ [sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = - sum([1 | q32_1 : int(1..5), q32_2 : int(1..5), conjure_aux1_RelationAsMatrix[q32_1, q32_2]]), - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]); - int(1..2)] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - }) - Context #6: { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - and({ [sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = - sum([1 | q32_1 : int(1..5), q32_2 : int(1..5), conjure_aux1_RelationAsMatrix[q32_1, q32_2]]), - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]); - int(1..2)] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - }) - } - Context #7: y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - and({ [sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = - sum([1 | q32_1 : int(1..5), q32_2 : int(1..5), conjure_aux1_RelationAsMatrix[q32_1, q32_2]]), - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]); - int(1..2)] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - }) - } -Picking the only option: Answer 1: inline-conditions: Inlining conditions, inside sum - [toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) * catchUndef(1, 0) | q32_1 : int(1..5), q32_2 : int(1..5)] -storedChoice: -[1 | q32_1 : int(1..5), q32_2 : int(1..5), conjure_aux1_RelationAsMatrix[q32_1, q32_2]] -5719405584779695493 -AnsweredRule {qHole_ = -5719405584779695493, qAscendants_ = fromList [-9027745215861162370,-8099216132366058965,-5857000228242749317,-5553782237459419472,4623787234387693138,7124000196337888585,8079567542521963183], aRuleName_ = "inline-conditions"} -LF: {"AnsweredRule":{"aRuleName_":"inline-conditions","qAscendants_":[-9027745215861162370,-8099216132366058965,-5857000228242749317,-5553782237459419472,4623787234387693138,7124000196337888585,8079567542521963183],"qHole_":-5719405584779695493}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - and({ [sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = - sum([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) * catchUndef(1, 0) | q32_1 : int(1..5), q32_2 : int(1..5)]), - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]); - int(1..2)] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - }) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: catchUndef(1, 0) - Context #1: [toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]), catchUndef(1, 0); int(1..2)] - Context #2: toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) * catchUndef(1, 0) - Context #3: [toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) * catchUndef(1, 0) | q32_1 : int(1..5), q32_2 : int(1..5)] - Context #4: sum([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) * catchUndef(1, 0) | q32_1 : int(1..5), q32_2 : int(1..5)]) - Context #5: sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = - sum([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) * catchUndef(1, 0) | q32_1 : int(1..5), q32_2 : int(1..5)]) - Context #6: [sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = - sum([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) * catchUndef(1, 0) | q32_1 : int(1..5), q32_2 : int(1..5)]), - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]); - int(1..2)] - Context #7: { [sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = - sum([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) * catchUndef(1, 0) | q32_1 : int(1..5), q32_2 : int(1..5)]), - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]); - int(1..2)] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - } - Context #8: and({ [sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = - sum([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) * catchUndef(1, 0) | q32_1 : int(1..5), q32_2 : int(1..5)]), - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]); - int(1..2)] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - }) - Context #9: { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - and({ [sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = - sum([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) * catchUndef(1, 0) | q32_1 : int(1..5), q32_2 : int(1..5)]), - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]); - int(1..2)] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - }) - } - Context #10: y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - and({ [sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = - sum([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) * catchUndef(1, 0) | q32_1 : int(1..5), q32_2 : int(1..5)]), - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]); - int(1..2)] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - }) - } -Picking the only option: Answer 1: full-evaluate: Full evaluator - 1 -storedChoice: -catchUndef(1, 0) -4103543015608659681 -AnsweredRule {qHole_ = -4103543015608659681, qAscendants_ = fromList [-8969688714663757079,-8620054688580705850,-7803342152587091485,-6406402188841036454,-3137912990386087120,-2245754891843782432,-893701506107809144,-421079377584717971,4859060653783625533,9081980220064719370], aRuleName_ = "full-evaluate"} -LF: {"AnsweredRule":{"aRuleName_":"full-evaluate","qAscendants_":[-8969688714663757079,-8620054688580705850,-7803342152587091485,-6406402188841036454,-3137912990386087120,-2245754891843782432,-893701506107809144,-421079377584717971,4859060653783625533,9081980220064719370],"qHole_":-4103543015608659681}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - and({ [sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = - sum([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) * 1 | q32_1 : int(1..5), q32_2 : int(1..5)]), - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]); - int(1..2)] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - }) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) * 1 - Context #1: [toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) * 1 | q32_1 : int(1..5), q32_2 : int(1..5)] - Context #2: sum([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) * 1 | q32_1 : int(1..5), q32_2 : int(1..5)]) - Context #3: sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = - sum([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) * 1 | q32_1 : int(1..5), q32_2 : int(1..5)]) - Context #4: [sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = - sum([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) * 1 | q32_1 : int(1..5), q32_2 : int(1..5)]), - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]); - int(1..2)] - Context #5: { [sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = - sum([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) * 1 | q32_1 : int(1..5), q32_2 : int(1..5)]), - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]); - int(1..2)] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - } - Context #6: and({ [sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = - sum([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) * 1 | q32_1 : int(1..5), q32_2 : int(1..5)]), - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]); - int(1..2)] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - }) - Context #7: { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - and({ [sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = - sum([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) * 1 | q32_1 : int(1..5), q32_2 : int(1..5)]), - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]); - int(1..2)] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - }) - } - Context #8: y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - and({ [sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = - sum([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) * 1 | q32_1 : int(1..5), q32_2 : int(1..5)]), - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]); - int(1..2)] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - }) - } -Picking the only option: Answer 1: partial-evaluate: Partial evaluator - product([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]); int(1)]) -storedChoice: -toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) * 1 -4682469706785037945 -AnsweredRule {qHole_ = -4682469706785037945, qAscendants_ = fromList [-9179050654683062954,-8797033748133430528,-8329454991333631126,-5647606918064816013,-3380861767487578940,6010365049512866508,6747419370843152779,7119833088853932687], aRuleName_ = "partial-evaluate"} -LF: {"AnsweredRule":{"aRuleName_":"partial-evaluate","qAscendants_":[-9179050654683062954,-8797033748133430528,-8329454991333631126,-5647606918064816013,-3380861767487578940,6010365049512866508,6747419370843152779,7119833088853932687],"qHole_":-4682469706785037945}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - and({ [sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = - sum([product([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]); int(1)]) | q32_1 : int(1..5), q32_2 : int(1..5)]), - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]); - int(1..2)] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - }) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: product([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]); int(1)]) - Context #1: [product([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]); int(1)]) | q32_1 : int(1..5), q32_2 : int(1..5)] - Context #2: sum([product([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]); int(1)]) | q32_1 : int(1..5), q32_2 : int(1..5)]) - Context #3: sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = - sum([product([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]); int(1)]) | q32_1 : int(1..5), q32_2 : int(1..5)]) - Context #4: [sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = - sum([product([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]); int(1)]) | q32_1 : int(1..5), q32_2 : int(1..5)]), - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]); - int(1..2)] - Context #5: { [sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = - sum([product([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]); int(1)]) | q32_1 : int(1..5), q32_2 : int(1..5)]), - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]); - int(1..2)] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - } - Context #6: and({ [sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = - sum([product([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]); int(1)]) | q32_1 : int(1..5), q32_2 : int(1..5)]), - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]); - int(1..2)] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - }) - Context #7: { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - and({ [sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = - sum([product([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]); int(1)]) | q32_1 : int(1..5), q32_2 : int(1..5)]), - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]); - int(1..2)] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - }) - } - Context #8: y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - and({ [sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = - sum([product([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]); int(1)]) | q32_1 : int(1..5), q32_2 : int(1..5)]), - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]); - int(1..2)] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - }) - } -Picking the only option: Answer 1: matrix-comprehension-singleton: Removing quantifier of a single item - toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) -storedChoice: -product([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]); int(1)]) -3618757702268377732 -AnsweredRule {qHole_ = -3618757702268377732, qAscendants_ = fromList [-3180788541249390624,-1419697389512850335,2051112281511221751,3011082682326874338,4702464191332467431,4730858055169822202,6821954100224183740,8108702534288021537], aRuleName_ = "matrix-comprehension-singleton"} -LF: {"AnsweredRule":{"aRuleName_":"matrix-comprehension-singleton","qAscendants_":[-3180788541249390624,-1419697389512850335,2051112281511221751,3011082682326874338,4702464191332467431,4730858055169822202,6821954100224183740,8108702534288021537],"qHole_":-3618757702268377732}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - and({ [sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = - sum([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) | q32_1 : int(1..5), q32_2 : int(1..5)]), - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]); - int(1..2)] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - }) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: and({ [sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = - sum([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) | q32_1 : int(1..5), q32_2 : int(1..5)]), - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]); - int(1..2)] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - }) - Context #1: { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - and({ [sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = - sum([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) | q32_1 : int(1..5), q32_2 : int(1..5)]), - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]); - int(1..2)] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - }) - } - Context #2: y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - and({ [sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = - sum([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) | q32_1 : int(1..5), q32_2 : int(1..5)]), - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]); - int(1..2)] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - }) - } -Picking the only option: Answer 1: bubble-up-LiftVars: Bubbling up auxiliary variables. - { sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = - sum([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) | q32_1 : int(1..5), q32_2 : int(1..5)]) - /\ - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - } -storedChoice: -and({ [sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = - sum([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) | q32_1 : int(1..5), q32_2 : int(1..5)]), - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]); - int(1..2)] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - }) -4558336889735046944 -AnsweredRule {qHole_ = -4558336889735046944, qAscendants_ = fromList [-3486949521822083211,2980043443155673363], aRuleName_ = "bubble-up-LiftVars"} -LF: {"AnsweredRule":{"aRuleName_":"bubble-up-LiftVars","qAscendants_":[-3486949521822083211,2980043443155673363],"qHole_":-4558336889735046944}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - { sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = - sum([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) | q32_1 : int(1..5), q32_2 : int(1..5)]) - /\ - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - } - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - { sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = - sum([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) | q32_1 : int(1..5), q32_2 : int(1..5)]) - /\ - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - } - } -Picking the only option: Answer 1: bubble-up-LiftVars: Bubbling up auxiliary variables. - { y = conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - { sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = - sum([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) | q32_1 : int(1..5), q32_2 : int(1..5)]) - /\ - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - } - } -storedChoice: -y = -{ conjure_aux1 -@ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - { sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = - sum([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) | q32_1 : int(1..5), q32_2 : int(1..5)]) - /\ - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - } -} 8908675996089062110 -AnsweredRule {qHole_ = 8908675996089062110, qAscendants_ = fromList [], aRuleName_ = "bubble-up-LiftVars"} -LF: {"AnsweredRule":{"aRuleName_":"bubble-up-LiftVars","qAscendants_":[],"qHole_":8908675996089062110}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - { y = conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - { sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = - sum([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) | q32_1 : int(1..5), q32_2 : int(1..5)]) - /\ - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - } - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: y = conjure_aux1 - Context #1: { y = conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - { sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = - sum([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) | q32_1 : int(1..5), q32_2 : int(1..5)]) - /\ - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - } - } -Picking the only option: Answer 1: identical-domain-eq: Generic vertical rule for identical-domain equality - and([y_RelationAsMatrix = conjure_aux1_RelationAsMatrix; int(1)]) -storedChoice: -y = conjure_aux1 3717099060101766216 -AnsweredRule {qHole_ = 3717099060101766216, qAscendants_ = fromList [2671848414499686108], aRuleName_ = "identical-domain-eq"} -LF: {"AnsweredRule":{"aRuleName_":"identical-domain-eq","qAscendants_":[2671848414499686108],"qHole_":3717099060101766216}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - { and([y_RelationAsMatrix = conjure_aux1_RelationAsMatrix; int(1)]) - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - { sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = - sum([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) | q32_1 : int(1..5), q32_2 : int(1..5)]) - /\ - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - } - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: y_RelationAsMatrix = conjure_aux1_RelationAsMatrix - Context #1: [y_RelationAsMatrix = conjure_aux1_RelationAsMatrix; int(1)] - Context #2: and([y_RelationAsMatrix = conjure_aux1_RelationAsMatrix; int(1)]) - Context #3: { and([y_RelationAsMatrix = conjure_aux1_RelationAsMatrix; int(1)]) - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - { sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = - sum([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) | q32_1 : int(1..5), q32_2 : int(1..5)]) - /\ - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - } - } -Picking the only option: Answer 1: matrix-eq: Horizontal rule for matrix = - and([y_RelationAsMatrix[q33] = conjure_aux1_RelationAsMatrix[q33] | q33 : int(1..5)]) -storedChoice: -y_RelationAsMatrix = conjure_aux1_RelationAsMatrix 847538541028825252 -AnsweredRule {qHole_ = 847538541028825252, qAscendants_ = fromList [-7545604584042643741,-3140704007737949652,8589500105863926587], aRuleName_ = "matrix-eq"} -LF: {"AnsweredRule":{"aRuleName_":"matrix-eq","qAscendants_":[-7545604584042643741,-3140704007737949652,8589500105863926587],"qHole_":847538541028825252}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - { and([and([y_RelationAsMatrix[q33] = conjure_aux1_RelationAsMatrix[q33] | q33 : int(1..5)]); int(1)]) - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - { sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = - sum([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) | q32_1 : int(1..5), q32_2 : int(1..5)]) - /\ - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - } - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: [y_RelationAsMatrix[q33] = conjure_aux1_RelationAsMatrix[q33] | q33 : int(1..5)] - Context #1: and([y_RelationAsMatrix[q33] = conjure_aux1_RelationAsMatrix[q33] | q33 : int(1..5)]) - Context #2: [and([y_RelationAsMatrix[q33] = conjure_aux1_RelationAsMatrix[q33] | q33 : int(1..5)]); int(1)] - Context #3: and([and([y_RelationAsMatrix[q33] = conjure_aux1_RelationAsMatrix[q33] | q33 : int(1..5)]); int(1)]) - Context #4: { and([and([y_RelationAsMatrix[q33] = conjure_aux1_RelationAsMatrix[q33] | q33 : int(1..5)]); int(1)]) - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - { sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = - sum([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) | q32_1 : int(1..5), q32_2 : int(1..5)]) - /\ - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - } - } -Picking the only option: Answer 1: choose-repr-for-comprehension: Choosing representation for quantified variable q33 (with type: int) - [y_RelationAsMatrix[q33] = conjure_aux1_RelationAsMatrix[q33] | q33 : int(1..5)] -storedChoice: -[y_RelationAsMatrix[q33] = conjure_aux1_RelationAsMatrix[q33] | q33 : int(1..5)] 45103260545151270 -AnsweredRule {qHole_ = 45103260545151270, qAscendants_ = fromList [-5973861858959396663,-4660253290178341140,-3962474706459959320,-1163992588452778161], aRuleName_ = "choose-repr-for-comprehension"} -LF: {"AnsweredRule":{"aRuleName_":"choose-repr-for-comprehension","qAscendants_":[-5973861858959396663,-4660253290178341140,-3962474706459959320,-1163992588452778161],"qHole_":45103260545151270}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - { and([and([y_RelationAsMatrix[q33] = conjure_aux1_RelationAsMatrix[q33] | q33 : int(1..5)]); int(1)]) - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - { sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = - sum([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) | q32_1 : int(1..5), q32_2 : int(1..5)]) - /\ - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - } - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: y_RelationAsMatrix[q33] = conjure_aux1_RelationAsMatrix[q33] - Context #1: [y_RelationAsMatrix[q33] = conjure_aux1_RelationAsMatrix[q33] | q33 : int(1..5)] - Context #2: and([y_RelationAsMatrix[q33] = conjure_aux1_RelationAsMatrix[q33] | q33 : int(1..5)]) - Context #3: [and([y_RelationAsMatrix[q33] = conjure_aux1_RelationAsMatrix[q33] | q33 : int(1..5)]); int(1)] - Context #4: and([and([y_RelationAsMatrix[q33] = conjure_aux1_RelationAsMatrix[q33] | q33 : int(1..5)]); int(1)]) - Context #5: { and([and([y_RelationAsMatrix[q33] = conjure_aux1_RelationAsMatrix[q33] | q33 : int(1..5)]); int(1)]) - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - { sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = - sum([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) | q32_1 : int(1..5), q32_2 : int(1..5)]) - /\ - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - } - } -Picking the only option: Answer 1: matrix-eq: Horizontal rule for matrix = - and([y_RelationAsMatrix[q33, q35] = conjure_aux1_RelationAsMatrix[q33, q35] | q35 : int(1..5)]) -storedChoice: -y_RelationAsMatrix[q33] = conjure_aux1_RelationAsMatrix[q33] 971298532972344754 -AnsweredRule {qHole_ = 971298532972344754, qAscendants_ = fromList [-5973861858959396663,-4660253290178341140,-3962474706459959320,-1163992588452778161,45103260545151270], aRuleName_ = "matrix-eq"} -LF: {"AnsweredRule":{"aRuleName_":"matrix-eq","qAscendants_":[-5973861858959396663,-4660253290178341140,-3962474706459959320,-1163992588452778161,45103260545151270],"qHole_":971298532972344754}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - { and([and([and([y_RelationAsMatrix[q33, q35] = conjure_aux1_RelationAsMatrix[q33, q35] | q35 : int(1..5)]) | q33 : int(1..5)]); - int(1)]) - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - { sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = - sum([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) | q32_1 : int(1..5), q32_2 : int(1..5)]) - /\ - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - } - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: [y_RelationAsMatrix[q33, q35] = conjure_aux1_RelationAsMatrix[q33, q35] | q35 : int(1..5)] - Context #1: and([y_RelationAsMatrix[q33, q35] = conjure_aux1_RelationAsMatrix[q33, q35] | q35 : int(1..5)]) - Context #2: [and([y_RelationAsMatrix[q33, q35] = conjure_aux1_RelationAsMatrix[q33, q35] | q35 : int(1..5)]) | q33 : int(1..5)] - Context #3: and([and([y_RelationAsMatrix[q33, q35] = conjure_aux1_RelationAsMatrix[q33, q35] | q35 : int(1..5)]) | q33 : int(1..5)]) - Context #4: [and([and([y_RelationAsMatrix[q33, q35] = conjure_aux1_RelationAsMatrix[q33, q35] | q35 : int(1..5)]) - | q33 : int(1..5)]); - int(1)] - Context #5: and([and([and([y_RelationAsMatrix[q33, q35] = conjure_aux1_RelationAsMatrix[q33, q35] | q35 : int(1..5)]) - | q33 : int(1..5)]); - int(1)]) - Context #6: { and([and([and([y_RelationAsMatrix[q33, q35] = conjure_aux1_RelationAsMatrix[q33, q35] | q35 : int(1..5)]) - | q33 : int(1..5)]); - int(1)]) - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - { sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = - sum([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) | q32_1 : int(1..5), q32_2 : int(1..5)]) - /\ - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - } - } -Picking the only option: Answer 1: choose-repr-for-comprehension: Choosing representation for quantified variable q35 (with type: int) - [y_RelationAsMatrix[q33, q35] = conjure_aux1_RelationAsMatrix[q33, q35] | q35 : int(1..5)] -storedChoice: -[y_RelationAsMatrix[q33, q35] = conjure_aux1_RelationAsMatrix[q33, q35] | q35 : int(1..5)] -1275491152285478671 -AnsweredRule {qHole_ = -1275491152285478671, qAscendants_ = fromList [-9124538447972763747,1151872964749555522,2218928338283019637,3574995822047355118,8452562685486794942,8526913528687567140], aRuleName_ = "choose-repr-for-comprehension"} -LF: {"AnsweredRule":{"aRuleName_":"choose-repr-for-comprehension","qAscendants_":[-9124538447972763747,1151872964749555522,2218928338283019637,3574995822047355118,8452562685486794942,8526913528687567140],"qHole_":-1275491152285478671}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - { and([and([and([y_RelationAsMatrix[q33, q35] = conjure_aux1_RelationAsMatrix[q33, q35] | q35 : int(1..5)]) | q33 : int(1..5)]); - int(1)]) - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - { sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = - sum([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) | q32_1 : int(1..5), q32_2 : int(1..5)]) - /\ - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - } - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: and([and([and([y_RelationAsMatrix[q33, q35] = conjure_aux1_RelationAsMatrix[q33, q35] - | q35 : int(1..5)]) - | q33 : int(1..5)]); - int(1)]) - Context #1: { and([and([and([y_RelationAsMatrix[q33, q35] = conjure_aux1_RelationAsMatrix[q33, q35] | q35 : int(1..5)]) - | q33 : int(1..5)]); - int(1)]) - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - { sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = - sum([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) | q32_1 : int(1..5), q32_2 : int(1..5)]) - /\ - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - } - } -Picking the only option: Answer 1: matrix-comprehension-singleton: Removing quantifier of a single item - and([and([y_RelationAsMatrix[q33, q35] = conjure_aux1_RelationAsMatrix[q33, q35] | q35 : int(1..5)]) | q33 : int(1..5)]) -storedChoice: -and([and([and([y_RelationAsMatrix[q33, q35] = conjure_aux1_RelationAsMatrix[q33, q35] | q35 : int(1..5)]) | q33 : int(1..5)]); - int(1)]) 3574995822047355118 -AnsweredRule {qHole_ = 3574995822047355118, qAscendants_ = fromList [1151872964749555522], aRuleName_ = "matrix-comprehension-singleton"} -LF: {"AnsweredRule":{"aRuleName_":"matrix-comprehension-singleton","qAscendants_":[1151872964749555522],"qHole_":3574995822047355118}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - { and([and([y_RelationAsMatrix[q33, q35] = conjure_aux1_RelationAsMatrix[q33, q35] | q35 : int(1..5)]) | q33 : int(1..5)]) - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - { sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = - sum([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) | q32_1 : int(1..5), q32_2 : int(1..5)]) - /\ - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - } - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: true(x) -Picking the only option: Answer 1: true-is-noop: Remove the argument from true. - true -storedChoice: -true(x) -1508832156878423928 -AnsweredRule {qHole_ = -1508832156878423928, qAscendants_ = fromList [], aRuleName_ = "true-is-noop"} -LF: {"AnsweredRule":{"aRuleName_":"true-is-noop","qAscendants_":[],"qHole_":-1508832156878423928}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - { and([and([y_RelationAsMatrix[q33, q35] = conjure_aux1_RelationAsMatrix[q33, q35] | q35 : int(1..5)]) | q33 : int(1..5)]) - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - { sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = - sum([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) | q32_1 : int(1..5), q32_2 : int(1..5)]) - /\ - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - } - } - branching on [x, y] - such that - such that - true, - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: true(y) -Picking the only option: Answer 1: true-is-noop: Remove the argument from true. - true -storedChoice: -true(y) -1508550667338902379 -AnsweredRule {qHole_ = -1508550667338902379, qAscendants_ = fromList [], aRuleName_ = "true-is-noop"} -LF: {"AnsweredRule":{"aRuleName_":"true-is-noop","qAscendants_":[],"qHole_":-1508550667338902379}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - { and([and([y_RelationAsMatrix[q33, q35] = conjure_aux1_RelationAsMatrix[q33, q35] | q35 : int(1..5)]) | q33 : int(1..5)]) - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - { sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = - sum([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) | q32_1 : int(1..5), q32_2 : int(1..5)]) - /\ - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - } - } - branching on [x, y] - such that - such that - true, - true - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -[epilogue] - language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - { and([and([y_RelationAsMatrix[q33, q35] = conjure_aux1_RelationAsMatrix[q33, q35] | q35 : int(1..5)]) | q33 : int(1..5)]) - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - { sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = - sum([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) | q32_1 : int(1..5), q32_2 : int(1..5)]) - /\ - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - } - } - branching on [x, y] - such that - such that - true, - true - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -[dropTagForSR] - language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - { and([and([y_RelationAsMatrix[q33, q35] = conjure_aux1_RelationAsMatrix[q33, q35] | q35 : int(1..5)]) | q33 : int(1..5)]) - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - { sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = - sum([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) | q32_1 : int(1..5), q32_2 : int(1..5)]) - /\ - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - } - } - branching on [x, y] - such that - such that - true, - true - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -[updateDeclarations] - language Essence 1.3 - - find x_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - find y_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that - { and([and([y_RelationAsMatrix[q33, q35] = conjure_aux1_RelationAsMatrix[q33, q35] | q35 : int(1..5)]) | q33 : int(1..5)]) - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - { sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = - sum([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) | q32_1 : int(1..5), q32_2 : int(1..5)]) - /\ - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - } - } - branching on [x_RelationAsMatrix, y_RelationAsMatrix] - such that - such that - true, - true - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -[inlineDecVarLettings] - language Essence 1.3 - - find x_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - find y_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that - { and([and([y_RelationAsMatrix[q33, q35] = conjure_aux1_RelationAsMatrix[q33, q35] | q35 : int(1..5)]) | q33 : int(1..5)]) - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - { sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = - sum([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) | q32_1 : int(1..5), q32_2 : int(1..5)]) - /\ - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - } - } - branching on [x_RelationAsMatrix, y_RelationAsMatrix] - such that - such that - true, - true - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -[topLevelBubbles] - language Essence 1.3 - - find x_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - find y_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - such that and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - such that and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - such that - sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = - sum([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) | q32_1 : int(1..5), q32_2 : int(1..5)]) - /\ - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - such that and([and([y_RelationAsMatrix[q33, q35] = conjure_aux1_RelationAsMatrix[q33, q35] | q35 : int(1..5)]) | q33 : int(1..5)]) - branching on [x_RelationAsMatrix, y_RelationAsMatrix] - such that true - such that true - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -[checkIfAllRefined] - language Essence 1.3 - - find x_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - find y_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - such that and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - such that and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - such that - sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = - sum([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) | q32_1 : int(1..5), q32_2 : int(1..5)]) - /\ - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - such that and([and([y_RelationAsMatrix[q33, q35] = conjure_aux1_RelationAsMatrix[q33, q35] | q35 : int(1..5)]) | q33 : int(1..5)]) - branching on [x_RelationAsMatrix, y_RelationAsMatrix] - such that true - such that true - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -[checkIfHasUndefined] - language Essence 1.3 - - find x_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - find y_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - such that and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - such that and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - such that - sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = - sum([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) | q32_1 : int(1..5), q32_2 : int(1..5)]) - /\ - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - such that and([and([y_RelationAsMatrix[q33, q35] = conjure_aux1_RelationAsMatrix[q33, q35] | q35 : int(1..5)]) | q33 : int(1..5)]) - branching on [x_RelationAsMatrix, y_RelationAsMatrix] - such that true - such that true - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -[sliceThemMatrices] - language Essence 1.3 - - find x_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - find y_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - such that and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - such that and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - such that - sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = - sum([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) | q32_1 : int(1..5), q32_2 : int(1..5)]) - /\ - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - such that and([and([y_RelationAsMatrix[q33, q35] = conjure_aux1_RelationAsMatrix[q33, q35] | q35 : int(1..5)]) | q33 : int(1..5)]) - branching on [x_RelationAsMatrix, y_RelationAsMatrix] - such that true - such that true - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -[emptyMatrixLiterals] - language Essence 1.3 - - find x_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - find y_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - such that and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - such that and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - such that - sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = - sum([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) | q32_1 : int(1..5), q32_2 : int(1..5)]) - /\ - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - such that and([and([y_RelationAsMatrix[q33, q35] = conjure_aux1_RelationAsMatrix[q33, q35] | q35 : int(1..5)]) | q33 : int(1..5)]) - branching on [x_RelationAsMatrix, y_RelationAsMatrix] - such that true - such that true - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -[reverseTrails] - language Essence 1.3 - - find x_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - find y_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - such that and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - such that and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - such that - sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = - sum([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) | q32_1 : int(1..5), q32_2 : int(1..5)]) - /\ - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - such that and([and([y_RelationAsMatrix[q33, q35] = conjure_aux1_RelationAsMatrix[q33, q35] | q35 : int(1..5)]) | q33 : int(1..5)]) - branching on [x_RelationAsMatrix, y_RelationAsMatrix] - such that true - such that true - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -[oneSuchThat] - language Essence 1.3 - - find x_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - find y_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - branching on [x_RelationAsMatrix, y_RelationAsMatrix] - such that - 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]), - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]), - and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]), - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]), - and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]), - sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = - sum([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) | q32_1 : int(1..5), q32_2 : int(1..5)]), - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]), - and([and([y_RelationAsMatrix[q33, q35] = conjure_aux1_RelationAsMatrix[q33, q35] | q35 : int(1..5)]) | q33 : int(1..5)]), - 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]), - 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -[languageEprime] - language ESSENCE' 1.0 - - find x_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - find y_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - branching on [x_RelationAsMatrix, y_RelationAsMatrix] - such that - 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]), - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]), - and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]), - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]), - and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]), - sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = - sum([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) | q32_1 : int(1..5), q32_2 : int(1..5)]), - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]), - and([and([y_RelationAsMatrix[q33, q35] = conjure_aux1_RelationAsMatrix[q33, q35] | q35 : int(1..5)]) | q33 : int(1..5)]), - 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]), - 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - diff --git a/tests/custom/deprecated_permutations_basic/0029_find_relations_x_y_such_that_y_image_x_under_p/log-lite b/tests/custom/deprecated_permutations_basic/0029_find_relations_x_y_such_that_y_image_x_under_p/log-lite deleted file mode 100644 index d9c9edd24e..0000000000 --- a/tests/custom/deprecated_permutations_basic/0029_find_relations_x_y_such_that_y_image_x_under_p/log-lite +++ /dev/null @@ -1,7863 +0,0 @@ -Command line options: Modelling {essence = "permutation.essence", outputDirectory = "conjure-output", numberingStart = 1, smartFilenames = False, responses = "", logLevel = LogDebug, verboseTrail = False, rewritesTrail = False, logRuleFails = False, logRuleSuccesses = False, logRuleAttempts = False, logChoices = False, strategyQ = "f", strategyA = "ai", representations = Nothing, representationsFinds = Nothing, representationsGivens = Nothing, representationsAuxiliaries = Nothing, representationsQuantifieds = Nothing, representationsCuts = Nothing, channelling = True, representationLevels = True, seed = Nothing, limitModels = Nothing, limitTime = Nothing, savedChoices = Nothing, outputFormat = Plain, lineWidth = 120} -[input] - language Essence 1.3 - - letting MYTYPE be new type enum {THING1, THING2, THING3, THING4, THING5} - letting p be permutation((THING3, THING4)) - find x: relation (size 4) of (MYTYPE * MYTYPE) - find y: relation (size 4) of (MYTYPE * MYTYPE) - such that y = image(p, x) - -[removeUnnamedsFromModel] - language Essence 1.3 - - letting MYTYPE be new type enum {THING1, THING2, THING3, THING4, THING5} - letting p be permutation((THING3, THING4)) - find x: relation (size 4) of (MYTYPE * MYTYPE) - find y: relation (size 4) of (MYTYPE * MYTYPE) - such that y = image(p, x) - -Recording enumGivens: -[removeEnumsFromModel] - language Essence 1.3 - - letting MYTYPE be domain int(1..5) - letting p be permutation((3, 4)) - find x: relation (size 4) of (MYTYPE * MYTYPE) - find y: relation (size 4) of (MYTYPE * MYTYPE) - such that y = image(p, x) - -[resolveNames] - language Essence 1.3 - - letting MYTYPE be domain int(1..5) - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that y = image(p, x) - -[typeCheckModel] - language Essence 1.3 - - letting MYTYPE be domain int(1..5) - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that y = image(p, x) - -[categoryChecking] - language Essence 1.3 - - letting MYTYPE be domain int(1..5) - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that y = image(p, x) - -[sanityChecks] - language Essence 1.3 - - letting MYTYPE be domain int(1..5) - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that y = image(p, x) - -[typeCheckModel] - language Essence 1.3 - - letting MYTYPE be domain int(1..5) - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that y = image(p, x) - -[input] - language Essence 1.3 - - letting MYTYPE be new type enum {THING1, THING2, THING3, THING4, THING5} - letting p be permutation((THING3, THING4)) - find x: relation (size 4) of (MYTYPE * MYTYPE) - find y: relation (size 4) of (MYTYPE * MYTYPE) - such that y = image(p, x) - -[addSearchOrder] - language Essence 1.3 - - letting MYTYPE be new type enum {THING1, THING2, THING3, THING4, THING5} - letting p be permutation((THING3, THING4)) - find x: relation (size 4) of (MYTYPE * MYTYPE) - find y: relation (size 4) of (MYTYPE * MYTYPE) - such that y = image(p, x) - branching on [x, y] - -[attributeAsConstraints] - language Essence 1.3 - - letting MYTYPE be new type enum {THING1, THING2, THING3, THING4, THING5} - letting p be permutation((THING3, THING4)) - find x: relation (size 4) of (MYTYPE * MYTYPE) - find y: relation (size 4) of (MYTYPE * MYTYPE) - such that y = image(p, x) - branching on [x, y] - -[inferAttributes] - language Essence 1.3 - - letting MYTYPE be new type enum {THING1, THING2, THING3, THING4, THING5} - letting p be permutation((THING3, THING4)) - find x: relation (size 4) of (MYTYPE * MYTYPE) - find y: relation (size 4) of (MYTYPE * MYTYPE) - such that y = image(p, x) - branching on [x, y] - -[inlineLettingDomainsForDecls] - language Essence 1.3 - - letting MYTYPE be new type enum {THING1, THING2, THING3, THING4, THING5} - letting p be permutation((THING3, THING4)) - find x: relation (size 4) of (MYTYPE * MYTYPE) - find y: relation (size 4) of (MYTYPE * MYTYPE) - such that y = image(p, x) - branching on [x, y] - -[lettingsForComplexInDoms] - language Essence 1.3 - - letting MYTYPE be new type enum {THING1, THING2, THING3, THING4, THING5} - letting p be permutation((THING3, THING4)) - find x: relation (size 4) of (MYTYPE * MYTYPE) - find y: relation (size 4) of (MYTYPE * MYTYPE) - such that y = image(p, x) - branching on [x, y] - -[distinctQuantifiedVars] - language Essence 1.3 - - letting MYTYPE be new type enum {THING1, THING2, THING3, THING4, THING5} - letting p be permutation((THING3, THING4)) - find x: relation (size 4) of (MYTYPE * MYTYPE) - find y: relation (size 4) of (MYTYPE * MYTYPE) - such that y = image(p, x) - branching on [x, y] - -[initInfo] - language Essence 1.3 - - letting MYTYPE be new type enum {THING1, THING2, THING3, THING4, THING5} - letting p be permutation((THING3, THING4)) - find x: relation (size 4) of (MYTYPE * MYTYPE) - find y: relation (size 4) of (MYTYPE * MYTYPE) - such that y = image(p, x) - branching on [x, y] - -[removeUnnamedsFromModel] - language Essence 1.3 - - letting MYTYPE be new type enum {THING1, THING2, THING3, THING4, THING5} - letting p be permutation((THING3, THING4)) - find x: relation (size 4) of (MYTYPE * MYTYPE) - find y: relation (size 4) of (MYTYPE * MYTYPE) - such that y = image(p, x) - branching on [x, y] - -Recording enumGivens: -[removeEnumsFromModel] - language Essence 1.3 - - letting MYTYPE be domain int(1..5) - letting p be permutation((3, 4)) - find x: relation (size 4) of (MYTYPE * MYTYPE) - find y: relation (size 4) of (MYTYPE * MYTYPE) - such that y = image(p, x) - branching on [x, y] - -[finiteGivens] - language Essence 1.3 - - letting MYTYPE be domain int(1..5) - letting p be permutation((3, 4)) - find x: relation (size 4) of (MYTYPE * MYTYPE) - find y: relation (size 4) of (MYTYPE * MYTYPE) - such that y = image(p, x) - branching on [x, y] - -[resolveNames] - language Essence 1.3 - - letting MYTYPE be domain int(1..5) - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that y = image(p, x) - branching on [x, y] - -[initInfo_Lettings] - language Essence 1.3 - - letting MYTYPE be domain int(1..5) - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that y = image(p, x) - branching on [x, y] - -[removeDomainLettings] - language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that y = image(p, x) - branching on [x, y] - -[typeCheckModel] - language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that y = image(p, x) - branching on [x, y] - -[categoryChecking] - language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that y = image(p, x) - branching on [x, y] - -[sanityChecks] - language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that y = image(p, x) - branching on [x, y] - -[dealWithCuts] - language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that y = image(p, x) - branching on [x, y] - such that - -[removeExtraSlices] - language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that y = image(p, x) - branching on [x, y] - such that - -[addTrueConstraints] - language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that y = image(p, x) - branching on [x, y] - such that - such that - true(x), - true(y) - -Contains 0 parameters (0 abstract) - 2 decision variables (2 abstract) -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that y = image(p, x) - branching on [x, y] - such that - such that - true(x), - true(y) - -Picking the first option: Question 1: permutation((3, 4)) -Picking the only option: Answer 1: full-evaluate: Full evaluator - permutation((3, 4)) -storedChoice: -permutation((3, 4)) -604127175528974338 -AnsweredRule {qHole_ = -604127175528974338, qAscendants_ = fromList [], aRuleName_ = "full-evaluate"} -LF: {"AnsweredRule":{"aRuleName_":"full-evaluate","qAscendants_":[],"qHole_":-604127175528974338}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that y = image(p, x) - branching on [x, y] - such that - such that - true(x), - true(y) - -Picking the first option: Question 1: p - Context #1: image(p, x) -Picking the only option: Answer 1: full-evaluate: Full evaluator - permutation((3, 4)) -storedChoice: -p -7234408895829330219 -AnsweredRule {qHole_ = -7234408895829330219, qAscendants_ = fromList [-7340749217212310711,-5834110796085551311], aRuleName_ = "full-evaluate"} -LF: {"AnsweredRule":{"aRuleName_":"full-evaluate","qAscendants_":[-7340749217212310711,-5834110796085551311],"qHole_":-7234408895829330219}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that y = image(permutation((3, 4)), x) - branching on [x, y] - such that - such that - true(x), - true(y) - -Picking the first option: Question 1: x - Context #1: image(permutation((3, 4)), x) -Picking the only option: Answer 1: choose-repr: Choosing representation for x: - relation {RelationAsMatrix} (size 4) of (int(1..5) * int(1..5)) - x -storedChoice: -x -7234408895963551171 -AnsweredReprStored {qHole_ = -7234408895963551171, qAscendants_ = fromList [-7111069252946253414,-6043361806322913446], aDomStored_ = "relation {RelationAsMatrix} (size 4) of (int(1..5) * int(1..5))", aRuleName_ = "choose-repr"} -LF: {"AnsweredReprStored":{"aDomStored_":"relation {RelationAsMatrix} (size 4) of (int(1..5) * int(1..5))","aRuleName_":"choose-repr","qAscendants_":[-7111069252946253414,-6043361806322913446],"qHole_":-7234408895963551171}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that y = image(permutation((3, 4)), x) - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - -Picking the first option: Question 1: y - Context #1: y = image(permutation((3, 4)), x) -Picking the only option: Answer 1: choose-repr: Choosing representation for y: - relation {RelationAsMatrix} (size 4) of (int(1..5) * int(1..5)) - y -storedChoice: -y -7234408895946773554 -AnsweredReprStored {qHole_ = -7234408895946773554, qAscendants_ = fromList [-7111069252946253414], aDomStored_ = "relation {RelationAsMatrix} (size 4) of (int(1..5) * int(1..5))", aRuleName_ = "choose-repr"} -LF: {"AnsweredReprStored":{"aDomStored_":"relation {RelationAsMatrix} (size 4) of (int(1..5) * int(1..5))","aRuleName_":"choose-repr","qAscendants_":[-7111069252946253414],"qHole_":-7234408895946773554}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that y = image(permutation((3, 4)), x) - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: x - Context #1: true(x) -Picking the only option: Answer 1: choose-repr: Choosing representation for x: - relation {RelationAsMatrix} (size 4) of (int(1..5) * int(1..5)) - x -storedChoice: -x -7234408895963551171 -AnsweredReprStored {qHole_ = -7234408895963551171, qAscendants_ = fromList [-1508832156878423928], aDomStored_ = "relation {RelationAsMatrix} (size 4) of (int(1..5) * int(1..5))", aRuleName_ = "choose-repr"} -LF: {"AnsweredReprStored":{"aDomStored_":"relation {RelationAsMatrix} (size 4) of (int(1..5) * int(1..5))","aRuleName_":"choose-repr","qAscendants_":[-1508832156878423928],"qHole_":-7234408895963551171}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that y = image(permutation((3, 4)), x) - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: y - Context #1: true(y) -Picking the only option: Answer 1: choose-repr: Choosing representation for y: - relation {RelationAsMatrix} (size 4) of (int(1..5) * int(1..5)) - y -storedChoice: -y -7234408895946773554 -AnsweredReprStored {qHole_ = -7234408895946773554, qAscendants_ = fromList [-1508550667338902379], aDomStored_ = "relation {RelationAsMatrix} (size 4) of (int(1..5) * int(1..5))", aRuleName_ = "choose-repr"} -LF: {"AnsweredReprStored":{"aDomStored_":"relation {RelationAsMatrix} (size 4) of (int(1..5) * int(1..5))","aRuleName_":"choose-repr","qAscendants_":[-1508550667338902379],"qHole_":-7234408895946773554}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that y = image(permutation((3, 4)), x) - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: [sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)] - Context #1: sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) -Picking the only option: Answer 1: choose-repr-for-comprehension: Choosing representation for quantified variable q1 (with type: int) - [sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)] -storedChoice: -[sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)] 6263396600925448594 -AnsweredRule {qHole_ = 6263396600925448594, qAscendants_ = fromList [5049395136776340146,5865511705196666561], aRuleName_ = "choose-repr-for-comprehension"} -LF: {"AnsweredRule":{"aRuleName_":"choose-repr-for-comprehension","qAscendants_":[5049395136776340146,5865511705196666561],"qHole_":6263396600925448594}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that y = image(permutation((3, 4)), x) - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: [toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)] - Context #1: sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) -Picking the only option: Answer 1: choose-repr-for-comprehension: Choosing representation for quantified variable q2 (with type: int) - [toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)] -storedChoice: -[toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)] 7855671108991671235 -AnsweredRule {qHole_ = 7855671108991671235, qAscendants_ = fromList [5049395136776340146,5865511705196666561,6263396600925448594,7085372780514568240], aRuleName_ = "choose-repr-for-comprehension"} -LF: {"AnsweredRule":{"aRuleName_":"choose-repr-for-comprehension","qAscendants_":[5049395136776340146,5865511705196666561,6263396600925448594,7085372780514568240],"qHole_":7855671108991671235}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that y = image(permutation((3, 4)), x) - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: [sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)] - Context #1: sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) -Picking the only option: Answer 1: choose-repr-for-comprehension: Choosing representation for quantified variable q3 (with type: int) - [sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)] -storedChoice: -[sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)] -3620919297952344383 -AnsweredRule {qHole_ = -3620919297952344383, qAscendants_ = fromList [-5513655157779400708,7219712989341858895], aRuleName_ = "choose-repr-for-comprehension"} -LF: {"AnsweredRule":{"aRuleName_":"choose-repr-for-comprehension","qAscendants_":[-5513655157779400708,7219712989341858895],"qHole_":-3620919297952344383}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that y = image(permutation((3, 4)), x) - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: [toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)] - Context #1: sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) -Picking the only option: Answer 1: choose-repr-for-comprehension: Choosing representation for quantified variable q4 (with type: int) - [toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)] -storedChoice: -[toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)] -2356590267706027710 -AnsweredRule {qHole_ = -2356590267706027710, qAscendants_ = fromList [-5513655157779400708,-3620919297952344383,7219712989341858895,8125267169441206107], aRuleName_ = "choose-repr-for-comprehension"} -LF: {"AnsweredRule":{"aRuleName_":"choose-repr-for-comprehension","qAscendants_":[-5513655157779400708,-3620919297952344383,7219712989341858895,8125267169441206107],"qHole_":-2356590267706027710}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that y = image(permutation((3, 4)), x) - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: image(permutation((3, 4)), x) - Context #1: y = image(permutation((3, 4)), x) -Picking the only option: Answer 1: relation-image: Horizontal rule for image relation in comprehension - { conjure_aux1 - @ find conjure_aux1: relation (size 4) of (int(1..5) * int(1..5)) - such that |x| = |conjure_aux1| /\ and([image(permutation((3, 4)), q5) in conjure_aux1 | q5 <- x]) - } -storedChoice: -image(permutation((3, 4)), x) -6043361806322913446 -AnsweredRule {qHole_ = -6043361806322913446, qAscendants_ = fromList [-7111069252946253414], aRuleName_ = "relation-image"} -LF: {"AnsweredRule":{"aRuleName_":"relation-image","qAscendants_":[-7111069252946253414],"qHole_":-6043361806322913446}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1: relation (size 4) of (int(1..5) * int(1..5)) - such that |x| = |conjure_aux1| /\ and([image(permutation((3, 4)), q5) in conjure_aux1 | q5 <- x]) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: { conjure_aux1 - @ find conjure_aux1: relation (size 4) of (int(1..5) * int(1..5)) - such that |x| = |conjure_aux1| /\ and([image(permutation((3, 4)), q5) in conjure_aux1 | q5 <- x]) - } - Context #1: y = - { conjure_aux1 - @ find conjure_aux1: relation (size 4) of (int(1..5) * int(1..5)) - such that |x| = |conjure_aux1| /\ and([image(permutation((3, 4)), q5) in conjure_aux1 | q5 <- x]) - } -Picking the only option: Answer 1: choose-repr-for-locals: Choosing representation for local variable conjure_aux1 - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that |x| = |conjure_aux1| /\ and([image(permutation((3, 4)), q5) in conjure_aux1 | q5 <- x]) - } -storedChoice: -{ conjure_aux1 -@ find conjure_aux1: relation (size 4) of (int(1..5) * int(1..5)) - such that |x| = |conjure_aux1| /\ and([image(permutation((3, 4)), q5) in conjure_aux1 | q5 <- x]) -} 1714623876200418132 -AnsweredRule {qHole_ = 1714623876200418132, qAscendants_ = fromList [5536329259437519582], aRuleName_ = "choose-repr-for-locals"} -LF: {"AnsweredRule":{"aRuleName_":"choose-repr-for-locals","qAscendants_":[5536329259437519582],"qHole_":1714623876200418132}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that |x| = |conjure_aux1| /\ and([image(permutation((3, 4)), q5) in conjure_aux1 | q5 <- x]) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: [sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)] - Context #1: sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) -Picking the only option: Answer 1: choose-repr-for-comprehension: Choosing representation for quantified variable q6 (with type: int) - [sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)] -storedChoice: -[sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)] -878601234175159627 -AnsweredRule {qHole_ = -878601234175159627, qAscendants_ = fromList [-5775367836057753714,-1245214478984509661,79132428954328345,1049837485042621691], aRuleName_ = "choose-repr-for-comprehension"} -LF: {"AnsweredRule":{"aRuleName_":"choose-repr-for-comprehension","qAscendants_":[-5775367836057753714,-1245214478984509661,79132428954328345,1049837485042621691],"qHole_":-878601234175159627}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that |x| = |conjure_aux1| /\ and([image(permutation((3, 4)), q5) in conjure_aux1 | q5 <- x]) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: [toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)] - Context #1: sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) -Picking the only option: Answer 1: choose-repr-for-comprehension: Choosing representation for quantified variable q7 (with type: int) - [toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)] -storedChoice: -[toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)] 2379582110528111197 -AnsweredRule {qHole_ = 2379582110528111197, qAscendants_ = fromList [-5775367836057753714,-1245214478984509661,-878601234175159627,79132428954328345,1049837485042621691,4483484998279672051], aRuleName_ = "choose-repr-for-comprehension"} -LF: {"AnsweredRule":{"aRuleName_":"choose-repr-for-comprehension","qAscendants_":[-5775367836057753714,-1245214478984509661,-878601234175159627,79132428954328345,1049837485042621691,4483484998279672051],"qHole_":2379582110528111197}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that |x| = |conjure_aux1| /\ and([image(permutation((3, 4)), q5) in conjure_aux1 | q5 <- x]) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: [image(permutation((3, 4)), q5) in conjure_aux1 | q5 <- x] - Context #1: and([image(permutation((3, 4)), q5) in conjure_aux1 | q5 <- x]) -Picking the only option: Answer 1: relation-map_in_expr{RelationAsMatrix}: Vertical rule for map_in_expr for relation domains, RelationAsMatrix representation. - [image(permutation((3, 4)), (q8[1], q8[2])) in conjure_aux1 | q8 : (int(1..5), int(1..5)), x_RelationAsMatrix[q8[1], q8[2]]] -storedChoice: -[image(permutation((3, 4)), q5) in conjure_aux1 | q5 <- x] 2569794631160861273 -AnsweredRule {qHole_ = 2569794631160861273, qAscendants_ = fromList [-4776664362067532454,-1245214478984509661,-1036657270873470960,79132428954328345,5830139973578569810], aRuleName_ = "relation-map_in_expr{RelationAsMatrix}"} -LF: {"AnsweredRule":{"aRuleName_":"relation-map_in_expr{RelationAsMatrix}","qAscendants_":[-4776664362067532454,-1245214478984509661,-1036657270873470960,79132428954328345,5830139973578569810],"qHole_":2569794631160861273}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([image(permutation((3, 4)), (q8[1], q8[2])) in conjure_aux1 | q8 : (int(1..5), int(1..5)), x_RelationAsMatrix[q8[1], q8[2]]]) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: [image(permutation((3, 4)), (q8[1], q8[2])) in conjure_aux1 - | q8 : (int(1..5), int(1..5)), x_RelationAsMatrix[q8[1], q8[2]]] - Context #1: and([image(permutation((3, 4)), (q8[1], q8[2])) in conjure_aux1 - | q8 : (int(1..5), int(1..5)), x_RelationAsMatrix[q8[1], q8[2]]]) -Picking the only option: Answer 1: choose-repr-for-comprehension: Choosing representation for quantified variable q8 (with type: (int, - int)) - [image(permutation((3, 4)), (q8[1], q8[2])) in conjure_aux1 | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]] -storedChoice: -[image(permutation((3, 4)), (q8[1], q8[2])) in conjure_aux1 - | q8 : (int(1..5), int(1..5)), x_RelationAsMatrix[q8[1], q8[2]]] -6121410142271556240 -AnsweredRule {qHole_ = -6121410142271556240, qAscendants_ = fromList [-8542780548609610841,-2372866271326699518,-688805377682383984,1829424135801856670,4203509818187934421], aRuleName_ = "choose-repr-for-comprehension"} -LF: {"AnsweredRule":{"aRuleName_":"choose-repr-for-comprehension","qAscendants_":[-8542780548609610841,-2372866271326699518,-688805377682383984,1829424135801856670,4203509818187934421],"qHole_":-6121410142271556240}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([image(permutation((3, 4)), (q8[1], q8[2])) in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: image(permutation((3, 4)), (q8[1], q8[2])) - Context #1: image(permutation((3, 4)), (q8[1], q8[2])) in conjure_aux1 -Picking the only option: Answer 1: tuple-image: Horizontal rule for image tuple in comprehension - { conjure_aux2 - @ find conjure_aux2: (int(1..5), int(1..5)) - such that conjure_aux2[1] = image(permutation((3, 4)), (q8[1], q8[2])[1]) - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } -storedChoice: -image(permutation((3, 4)), (q8[1], q8[2])) 7641797427128728383 -AnsweredRule {qHole_ = 7641797427128728383, qAscendants_ = fromList [-6118234929664435696,-1399392580596120430,-1387706708486858898,-1208703870972871253,-742133995496027829,4437220630107512706,5070918677941821273], aRuleName_ = "tuple-image"} -LF: {"AnsweredRule":{"aRuleName_":"tuple-image","qAscendants_":[-6118234929664435696,-1399392580596120430,-1387706708486858898,-1208703870972871253,-742133995496027829,4437220630107512706,5070918677941821273],"qHole_":7641797427128728383}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2: (int(1..5), int(1..5)) - such that conjure_aux2[1] = image(permutation((3, 4)), (q8[1], q8[2])[1]) - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: { conjure_aux2 - @ find conjure_aux2: (int(1..5), int(1..5)) - such that conjure_aux2[1] = image(permutation((3, 4)), (q8[1], q8[2])[1]) - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - Context #1: { conjure_aux2 - @ find conjure_aux2: (int(1..5), int(1..5)) - such that conjure_aux2[1] = image(permutation((3, 4)), (q8[1], q8[2])[1]) - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 -Picking the only option: Answer 1: choose-repr-for-locals: Choosing representation for local variable conjure_aux2 - { conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that conjure_aux2[1] = image(permutation((3, 4)), (q8[1], q8[2])[1]) - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } -storedChoice: -{ conjure_aux2 -@ find conjure_aux2: (int(1..5), int(1..5)) - such that conjure_aux2[1] = image(permutation((3, 4)), (q8[1], q8[2])[1]) - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) -} 7832450608952021018 -AnsweredRule {qHole_ = 7832450608952021018, qAscendants_ = fromList [-4717314876217502109,-4294582922489450379,1651264905194084305,2977457561748621690,4087019737558016944,5019534480518702783,6820345709468359473], aRuleName_ = "choose-repr-for-locals"} -LF: {"AnsweredRule":{"aRuleName_":"choose-repr-for-locals","qAscendants_":[-4717314876217502109,-4294582922489450379,1651264905194084305,2977457561748621690,4087019737558016944,5019534480518702783,6820345709468359473],"qHole_":7832450608952021018}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that conjure_aux2[1] = image(permutation((3, 4)), (q8[1], q8[2])[1]) - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: conjure_aux2[1] - Context #1: conjure_aux2[1] = image(permutation((3, 4)), (q8[1], q8[2])[1]) -Picking the only option: Answer 1: tuple-index: Tuple indexing on: conjure_aux2[1] - conjure_aux2_1 -storedChoice: -conjure_aux2[1] 2042848205583864547 -AnsweredRule {qHole_ = 2042848205583864547, qAscendants_ = fromList [-7836606021998938252,-4083899676628141502,-3337431591692655861,-1871379374487492755,31163859450310923,347176683161250196,1078578095348213584,3723112517704369347,8818185052449544140], aRuleName_ = "tuple-index"} -LF: {"AnsweredRule":{"aRuleName_":"tuple-index","qAscendants_":[-7836606021998938252,-4083899676628141502,-3337431591692655861,-1871379374487492755,31163859450310923,347176683161250196,1078578095348213584,3723112517704369347,8818185052449544140],"qHole_":2042848205583864547}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that conjure_aux2_1 = image(permutation((3, 4)), (q8[1], q8[2])[1]) - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: (q8[1], q8[2])[1] - Context #1: image(permutation((3, 4)), (q8[1], q8[2])[1]) -Picking the only option: Answer 1: tuple-index: Tuple indexing on: (q8[1], q8[2])[1] - q8[1] -storedChoice: -(q8[1], q8[2])[1] -5501922928837560372 -AnsweredRule {qHole_ = -5501922928837560372, qAscendants_ = fromList [-8079003502337880871,-5992757738829033069,-4052786222025792276,-4045994663639704708,-1887930543228865818,2614825847120268012,2969550575619082812,4897364746913734457,7503648025096004321,8070588202073729915], aRuleName_ = "tuple-index"} -LF: {"AnsweredRule":{"aRuleName_":"tuple-index","qAscendants_":[-8079003502337880871,-5992757738829033069,-4052786222025792276,-4045994663639704708,-1887930543228865818,2614825847120268012,2969550575619082812,4897364746913734457,7503648025096004321,8070588202073729915],"qHole_":-5501922928837560372}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that conjure_aux2_1 = image(permutation((3, 4)), q8[1]) - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: q8[1] - Context #1: image(permutation((3, 4)), q8[1]) -Picking the only option: Answer 1: tuple-index: Tuple indexing on: q8[1] - q8_1 -storedChoice: -q8[1] 6051865069970393497 -AnsweredRule {qHole_ = 6051865069970393497, qAscendants_ = fromList [-6240564754428641774,-3828924106000349868,-2497616537930163555,-2455337427536589680,-1546470019878997061,409221243111017286,1096079797629796883,1353067250173028676,4249511820642706384,6954638962073438443], aRuleName_ = "tuple-index"} -LF: {"AnsweredRule":{"aRuleName_":"tuple-index","qAscendants_":[-6240564754428641774,-3828924106000349868,-2497616537930163555,-2455337427536589680,-1546470019878997061,409221243111017286,1096079797629796883,1353067250173028676,4249511820642706384,6954638962073438443],"qHole_":6051865069970393497}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that conjure_aux2_1 = image(permutation((3, 4)), q8_1) - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: image(permutation((3, 4)), q8_1) - Context #1: conjure_aux2_1 = image(permutation((3, 4)), q8_1) -Picking the only option: Answer 1: permutation-image-literal{AsFunction}: Horizontal rule for permutation literal application to a single value (image), AsFunction representation - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and([q9 = q8_1 <-> conjure_aux3 = q10 | (q9, q10) <- [(3, 4), (4, 3); int(1..2)]]) /\ - (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) - } -storedChoice: -image(permutation((3, 4)), q8_1) -6565377216106402436 -AnsweredRule {qHole_ = -6565377216106402436, qAscendants_ = fromList [-8683446058401842621,-8501667396727033866,-6589174251984098358,-5196229448616722462,-2562107481961042620,-1290778481550223845,5400239128163960843,7319032080622836357,8711639898256895276], aRuleName_ = "permutation-image-literal{AsFunction}"} -LF: {"AnsweredRule":{"aRuleName_":"permutation-image-literal{AsFunction}","qAscendants_":[-8683446058401842621,-8501667396727033866,-6589174251984098358,-5196229448616722462,-2562107481961042620,-1290778481550223845,5400239128163960843,7319032080622836357,8711639898256895276],"qHole_":-6565377216106402436}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and([q9 = q8_1 <-> conjure_aux3 = q10 | (q9, q10) <- [(3, 4), (4, 3); int(1..2)]]) /\ - (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: [(3, 4), (4, 3); int(1..2)] - Context #1: [q9 = q8_1 <-> conjure_aux3 = q10 | (q9, q10) <- [(3, 4), (4, 3); int(1..2)]] -Picking the only option: Answer 1: full-evaluate: Full evaluator - [(3, 4), (4, 3); int(1..2)] -storedChoice: -[(3, 4), (4, 3); int(1..2)] 6597397470067790033 -AnsweredRule {qHole_ = 6597397470067790033, qAscendants_ = fromList [-8621354921797967448,-6160248818055544346,-6049820697610812758,-4894284809815571873,-4858508204008314707,-4635274203177452231,-1665058964617223774,996353907888938120,1107585814561782716,1593343993162845666,1994644797538381771,2641311773319376803,3730217346423440641,5862930277568425410], aRuleName_ = "full-evaluate"} -LF: {"AnsweredRule":{"aRuleName_":"full-evaluate","qAscendants_":[-8621354921797967448,-6160248818055544346,-6049820697610812758,-4894284809815571873,-4858508204008314707,-4635274203177452231,-1665058964617223774,996353907888938120,1107585814561782716,1593343993162845666,1994644797538381771,2641311773319376803,3730217346423440641,5862930277568425410],"qHole_":6597397470067790033}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and([q9 = q8_1 <-> conjure_aux3 = q10 | (q9, q10) <- [(3, 4), (4, 3); int(1..2)]]) /\ - (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: [q9 = q8_1 <-> conjure_aux3 = q10 | (q9, q10) <- [(3, 4), (4, 3); int(1..2)]] - Context #1: and([q9 = q8_1 <-> conjure_aux3 = q10 | (q9, q10) <- [(3, 4), (4, 3); int(1..2)]]) -Picking the only option: Answer 1: complex-pattern: complex pattern on tuple patterns - [q13[1] = q8_1 <-> conjure_aux3 = q13[2] | q13 <- [(3, 4), (4, 3); int(1..2)]] -storedChoice: -[q9 = q8_1 <-> conjure_aux3 = q10 | (q9, q10) <- [(3, 4), (4, 3); int(1..2)]] 996353907888938120 -AnsweredRule {qHole_ = 996353907888938120, qAscendants_ = fromList [-8621354921797967448,-6160248818055544346,-6049820697610812758,-4894284809815571873,-4858508204008314707,-4635274203177452231,-1665058964617223774,1107585814561782716,1593343993162845666,1994644797538381771,2641311773319376803,3730217346423440641,5862930277568425410], aRuleName_ = "complex-pattern"} -LF: {"AnsweredRule":{"aRuleName_":"complex-pattern","qAscendants_":[-8621354921797967448,-6160248818055544346,-6049820697610812758,-4894284809815571873,-4858508204008314707,-4635274203177452231,-1665058964617223774,1107585814561782716,1593343993162845666,1994644797538381771,2641311773319376803,3730217346423440641,5862930277568425410],"qHole_":996353907888938120}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and([q13[1] = q8_1 <-> conjure_aux3 = q13[2] | q13 <- [(3, 4), (4, 3); int(1..2)]]) /\ - (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: [q13[1] = q8_1 <-> conjure_aux3 = q13[2] | q13 <- [(3, 4), (4, 3); int(1..2)]] - Context #1: and([q13[1] = q8_1 <-> conjure_aux3 = q13[2] | q13 <- [(3, 4), (4, 3); int(1..2)]]) -Picking the only option: Answer 1: matrix-comprehension-literal: Vertical rule for matrix-comprehension on matrix literal - flatten(1, - [[q13[1] = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (3, 4)], - [q13[1] = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (4, 3)]; - int(1..2)]) -storedChoice: -[q13[1] = q8_1 <-> conjure_aux3 = q13[2] | q13 <- [(3, 4), (4, 3); int(1..2)]] 3456861798216985162 -AnsweredRule {qHole_ = 3456861798216985162, qAscendants_ = fromList [-8808315865059383030,-8227483119145124211,-7793095449913038876,-5679502255425066053,-3572216896086163269,-3021143752573374113,-2561056581393168238,-842750970546105960,3371366859945964624,5522715912807809257,6264069036653869010,7196566142350255202,8156173651558168583], aRuleName_ = "matrix-comprehension-literal"} -LF: {"AnsweredRule":{"aRuleName_":"matrix-comprehension-literal","qAscendants_":[-8808315865059383030,-8227483119145124211,-7793095449913038876,-5679502255425066053,-3572216896086163269,-3021143752573374113,-2561056581393168238,-842750970546105960,3371366859945964624,5522715912807809257,6264069036653869010,7196566142350255202,8156173651558168583],"qHole_":3456861798216985162}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, - [[q13[1] = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (3, 4)], - [q13[1] = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (4, 3)]; - int(1..2)])) - /\ (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: q13[1] - Context #1: q13[1] = q8_1 -Picking the only option: Answer 1: full-evaluate: Full evaluator - 3 -storedChoice: -q13[1] -1254902052079317740 -AnsweredRule {qHole_ = -1254902052079317740, qAscendants_ = fromList [-7844826506044189197,-6543998516580374433,-5468160839539146108,-4646329838907093569,-4421494240673914403,-4030269164244882685,-3696611495810109143,-3345198454859526376,-2923685885462842550,-2579765278873905792,-2489053689031557395,-2037117675633093401,-1199749775392010500,-1159821892128975232,-61377228416248265,964892601978301791,3910121320990104243,4511388692183383834], aRuleName_ = "full-evaluate"} -LF: {"AnsweredRule":{"aRuleName_":"full-evaluate","qAscendants_":[-7844826506044189197,-6543998516580374433,-5468160839539146108,-4646329838907093569,-4421494240673914403,-4030269164244882685,-3696611495810109143,-3345198454859526376,-2923685885462842550,-2579765278873905792,-2489053689031557395,-2037117675633093401,-1199749775392010500,-1159821892128975232,-61377228416248265,964892601978301791,3910121320990104243,4511388692183383834],"qHole_":-1254902052079317740}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, - [[3 = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (3, 4)], [q13[1] = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (4, 3)]; - int(1..2)])) - /\ (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: q13[2] - Context #1: conjure_aux3 = q13[2] -Picking the only option: Answer 1: full-evaluate: Full evaluator - 4 -storedChoice: -q13[2] -1254620565291325713 -AnsweredRule {qHole_ = -1254620565291325713, qAscendants_ = fromList [-8360775170969626109,-8218634654132870929,-7641638248746524641,-4934801957947094136,-4254522952928052133,-4092969587983186253,-3780104048260027650,-2622265047463603714,-848316662104045049,563172654367211215,1222024046659559696,4078666449752848978,4662787952378127984,5249190568318080416,5574891365015849631,7061285353711906011,7866305697050141526,9112935851435552216], aRuleName_ = "full-evaluate"} -LF: {"AnsweredRule":{"aRuleName_":"full-evaluate","qAscendants_":[-8360775170969626109,-8218634654132870929,-7641638248746524641,-4934801957947094136,-4254522952928052133,-4092969587983186253,-3780104048260027650,-2622265047463603714,-848316662104045049,563172654367211215,1222024046659559696,4078666449752848978,4662787952378127984,5249190568318080416,5574891365015849631,7061285353711906011,7866305697050141526,9112935851435552216],"qHole_":-1254620565291325713}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, - [[3 = q8_1 <-> conjure_aux3 = 4 | letting q13 be (3, 4)], [q13[1] = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (4, 3)]; - int(1..2)])) - /\ (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: q13[1] - Context #1: q13[1] = q8_1 -Picking the only option: Answer 1: full-evaluate: Full evaluator - 4 -storedChoice: -q13[1] -1254902052079317740 -AnsweredRule {qHole_ = -1254902052079317740, qAscendants_ = fromList [-8638629789947627417,-7681680422406975063,-7045052392114671596,-5468160839539146108,-5360000098558189830,-5130716656066417701,-3536433963763386607,-3341254942655847808,-1332675206370029612,-61377228416248265,518672155518189655,1368815305078223764,1506712726218393853,2813413964084179331,4256368997522955231,6094767248156078778,6822727452915095676,7566490689068664978], aRuleName_ = "full-evaluate"} -LF: {"AnsweredRule":{"aRuleName_":"full-evaluate","qAscendants_":[-8638629789947627417,-7681680422406975063,-7045052392114671596,-5468160839539146108,-5360000098558189830,-5130716656066417701,-3536433963763386607,-3341254942655847808,-1332675206370029612,-61377228416248265,518672155518189655,1368815305078223764,1506712726218393853,2813413964084179331,4256368997522955231,6094767248156078778,6822727452915095676,7566490689068664978],"qHole_":-1254902052079317740}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, - [[3 = q8_1 <-> conjure_aux3 = 4 | letting q13 be (3, 4)], [4 = q8_1 <-> conjure_aux3 = q13[2] | letting q13 be (4, 3)]; int(1..2)])) - /\ (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: q13[2] - Context #1: conjure_aux3 = q13[2] -Picking the only option: Answer 1: full-evaluate: Full evaluator - 3 -storedChoice: -q13[2] -1254620565291325713 -AnsweredRule {qHole_ = -1254620565291325713, qAscendants_ = fromList [-8870698451967212431,-8218634654132870929,-8157916199347819983,-6958532007910279584,-4735583185965836928,-3733766703817256233,-1365219118307736560,-1326414908464043218,-756643065960997164,-238771092705033653,525451447959791552,2934402913780861128,4090216973995379955,4246953395184334158,4325482688218662469,4385767247150328058,4926105801959606859,4926669858781506740], aRuleName_ = "full-evaluate"} -LF: {"AnsweredRule":{"aRuleName_":"full-evaluate","qAscendants_":[-8870698451967212431,-8218634654132870929,-8157916199347819983,-6958532007910279584,-4735583185965836928,-3733766703817256233,-1365219118307736560,-1326414908464043218,-756643065960997164,-238771092705033653,525451447959791552,2934402913780861128,4090216973995379955,4246953395184334158,4325482688218662469,4385767247150328058,4926105801959606859,4926669858781506740],"qHole_":-1254620565291325713}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, - [[3 = q8_1 <-> conjure_aux3 = 4 | letting q13 be (3, 4)], [4 = q8_1 <-> conjure_aux3 = 3 | letting q13 be (4, 3)]; int(1..2)])) - /\ (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: [4 = q8_1 <-> conjure_aux3 = 3 | letting q13 be (4, 3)] - Context #1: [[3 = q8_1 <-> conjure_aux3 = 4 | letting q13 be (3, 4)], [4 = q8_1 <-> conjure_aux3 = 3 | letting q13 be (4, 3)]; - int(1..2)] -Picking the only option: Answer 1: generators-first: Inlining comprehension lettings. - [4 = q8_1 <-> conjure_aux3 = 3 |] -storedChoice: -[4 = q8_1 <-> conjure_aux3 = 3 | letting q13 be (4, 3)] 7815870421468516721 -AnsweredRule {qHole_ = 7815870421468516721, qAscendants_ = fromList [-7319924227898755161,-6204074559855855953,-5721547888581640964,-4667135429861035401,-3119038628659086386,-2914873009721382719,-275708737112837829,358797451837378,588328580564008008,1171576539747863800,3860402082075414220,5255108035061878259,7534557817041195235,8046872103256922185,9076826399099772257], aRuleName_ = "generators-first"} -LF: {"AnsweredRule":{"aRuleName_":"generators-first","qAscendants_":[-7319924227898755161,-6204074559855855953,-5721547888581640964,-4667135429861035401,-3119038628659086386,-2914873009721382719,-275708737112837829,358797451837378,588328580564008008,1171576539747863800,3860402082075414220,5255108035061878259,7534557817041195235,8046872103256922185,9076826399099772257],"qHole_":7815870421468516721}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4 | letting q13 be (3, 4)], [4 = q8_1 <-> conjure_aux3 = 3 |]; int(1..2)])) /\ - (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: [4 = q8_1 <-> conjure_aux3 = 3 |] - Context #1: [[3 = q8_1 <-> conjure_aux3 = 4 | letting q13 be (3, 4)], [4 = q8_1 <-> conjure_aux3 = 3 |]; int(1..2)] -Picking the only option: Answer 1: generators-first: Empty generators. - [4 = q8_1 <-> conjure_aux3 = 3; int(1)] -storedChoice: -[4 = q8_1 <-> conjure_aux3 = 3 |] 2538271587388693524 -AnsweredRule {qHole_ = 2538271587388693524, qAscendants_ = fromList [-8521000068701228812,-8466935177678778299,-8378067175040646304,-7795155064905057512,-7398425908569645990,-5020343327513684658,-1331085484917687815,-382563719840663416,1239306329275872739,3167048961433864186,4591749041469508459,5482352134908236922,5648481728193344963,6702522234416193183,8765316459520566910], aRuleName_ = "generators-first"} -LF: {"AnsweredRule":{"aRuleName_":"generators-first","qAscendants_":[-8521000068701228812,-8466935177678778299,-8378067175040646304,-7795155064905057512,-7398425908569645990,-5020343327513684658,-1331085484917687815,-382563719840663416,1239306329275872739,3167048961433864186,4591749041469508459,5482352134908236922,5648481728193344963,6702522234416193183,8765316459520566910],"qHole_":2538271587388693524}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4 | letting q13 be (3, 4)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: [3 = q8_1 <-> conjure_aux3 = 4 | letting q13 be (3, 4)] - Context #1: [[3 = q8_1 <-> conjure_aux3 = 4 | letting q13 be (3, 4)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)] -Picking the only option: Answer 1: generators-first: Inlining comprehension lettings. - [3 = q8_1 <-> conjure_aux3 = 4 |] -storedChoice: -[3 = q8_1 <-> conjure_aux3 = 4 | letting q13 be (3, 4)] 1317873634227795931 -AnsweredRule {qHole_ = 1317873634227795931, qAscendants_ = fromList [-6229747794032826968,-5833692553090476381,-4830840744837226265,-4695719515395703877,-1447797878088113254,-1026424407203100673,-114180086101386755,1230900640119672810,2384858822123183656,2641682090906853361,4932647657883680462,5503876696275907482,5561643139389034608,8062918047402720448,8618709991360516938], aRuleName_ = "generators-first"} -LF: {"AnsweredRule":{"aRuleName_":"generators-first","qAscendants_":[-6229747794032826968,-5833692553090476381,-4830840744837226265,-4695719515395703877,-1447797878088113254,-1026424407203100673,-114180086101386755,1230900640119672810,2384858822123183656,2641682090906853361,4932647657883680462,5503876696275907482,5561643139389034608,8062918047402720448,8618709991360516938],"qHole_":1317873634227795931}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4 |], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: [3 = q8_1 <-> conjure_aux3 = 4 |] - Context #1: [[3 = q8_1 <-> conjure_aux3 = 4 |], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)] -Picking the only option: Answer 1: generators-first: Empty generators. - [3 = q8_1 <-> conjure_aux3 = 4; int(1)] -storedChoice: -[3 = q8_1 <-> conjure_aux3 = 4 |] 7527005283398106432 -AnsweredRule {qHole_ = 7527005283398106432, qAscendants_ = fromList [-5151808191572404398,-4353286235323785771,-4339955062448219396,-4142041909263092979,-3736320932349712947,-3440388200198466301,-2029225889893250969,-1817262023712192284,-116834249900757749,483550512093615086,1497957860809309721,2283573903554163553,3854374349353612498,7382215623493355130,8339321953980948829], aRuleName_ = "generators-first"} -LF: {"AnsweredRule":{"aRuleName_":"generators-first","qAscendants_":[-5151808191572404398,-4353286235323785771,-4339955062448219396,-4142041909263092979,-3736320932349712947,-3440388200198466301,-2029225889893250969,-1817262023712192284,-116834249900757749,483550512093615086,1497957860809309721,2283573903554163553,3854374349353612498,7382215623493355130,8339321953980948829],"qHole_":7527005283398106432}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: [(3, 4), (4, 3); int(1..2)] - Context #1: [q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]] -Picking the only option: Answer 1: full-evaluate: Full evaluator - [(3, 4), (4, 3); int(1..2)] -storedChoice: -[(3, 4), (4, 3); int(1..2)] 6597397470067790033 -AnsweredRule {qHole_ = 6597397470067790033, qAscendants_ = fromList [-9213624152780173787,-5982135693274236766,-5396430067534345835,-2363572399258163690,-2255081376624876153,-320252043164433323,1280603170430058832,2648872121679578871,4076507060053755550,5033554600497872881,6390584767367481427,6475772422542545541,6480002864764397731,6871118355510909196,7049518756068236715,8591929121087659168], aRuleName_ = "full-evaluate"} -LF: {"AnsweredRule":{"aRuleName_":"full-evaluate","qAscendants_":[-9213624152780173787,-5982135693274236766,-5396430067534345835,-2363572399258163690,-2255081376624876153,-320252043164433323,1280603170430058832,2648872121679578871,4076507060053755550,5033554600497872881,6390584767367481427,6475772422542545541,6480002864764397731,6871118355510909196,7049518756068236715,8591929121087659168],"qHole_":6597397470067790033}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: [q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]] - Context #1: or([q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]]) -Picking the only option: Answer 1: complex-pattern: complex pattern on tuple patterns - [q14[1] = conjure_aux3 | q14 <- [(3, 4), (4, 3); int(1..2)]] -storedChoice: -[q11 = conjure_aux3 | (q11, q12) <- [(3, 4), (4, 3); int(1..2)]] 5033554600497872881 -AnsweredRule {qHole_ = 5033554600497872881, qAscendants_ = fromList [-9213624152780173787,-5982135693274236766,-5396430067534345835,-2363572399258163690,-2255081376624876153,-320252043164433323,1280603170430058832,2648872121679578871,4076507060053755550,6390584767367481427,6475772422542545541,6480002864764397731,6871118355510909196,7049518756068236715,8591929121087659168], aRuleName_ = "complex-pattern"} -LF: {"AnsweredRule":{"aRuleName_":"complex-pattern","qAscendants_":[-9213624152780173787,-5982135693274236766,-5396430067534345835,-2363572399258163690,-2255081376624876153,-320252043164433323,1280603170430058832,2648872121679578871,4076507060053755550,6390584767367481427,6475772422542545541,6480002864764397731,6871118355510909196,7049518756068236715,8591929121087659168],"qHole_":5033554600497872881}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!or([q14[1] = conjure_aux3 | q14 <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: [q14[1] = conjure_aux3 | q14 <- [(3, 4), (4, 3); int(1..2)]] - Context #1: or([q14[1] = conjure_aux3 | q14 <- [(3, 4), (4, 3); int(1..2)]]) -Picking the only option: Answer 1: matrix-comprehension-literal: Vertical rule for matrix-comprehension on matrix literal - flatten(1, [[q14[1] = conjure_aux3 | letting q14 be (3, 4)], [q14[1] = conjure_aux3 | letting q14 be (4, 3)]; int(1..2)]) -storedChoice: -[q14[1] = conjure_aux3 | q14 <- [(3, 4), (4, 3); int(1..2)]] 8665374887955696009 -AnsweredRule {qHole_ = 8665374887955696009, qAscendants_ = fromList [-8790838049079552472,-7586671731712078955,-7257845330645731074,-6187411109644722069,-5035649525051787097,-4935714982215491801,-4790057621145645718,-2980197002499358476,-1690854938850194471,-619668906698634467,1003810935162304708,3378856114517929630,5359983985600686059,5489110086534554143,8428096257079881520], aRuleName_ = "matrix-comprehension-literal"} -LF: {"AnsweredRule":{"aRuleName_":"matrix-comprehension-literal","qAscendants_":[-8790838049079552472,-7586671731712078955,-7257845330645731074,-6187411109644722069,-5035649525051787097,-4935714982215491801,-4790057621145645718,-2980197002499358476,-1690854938850194471,-619668906698634467,1003810935162304708,3378856114517929630,5359983985600686059,5489110086534554143,8428096257079881520],"qHole_":8665374887955696009}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!or(flatten(1, [[q14[1] = conjure_aux3 | letting q14 be (3, 4)], [q14[1] = conjure_aux3 | letting q14 be (4, 3)]; int(1..2)])) <-> - conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: q14[1] - Context #1: q14[1] = conjure_aux3 -Picking the only option: Answer 1: full-evaluate: Full evaluator - 3 -storedChoice: -q14[1] -883253742927518753 -AnsweredRule {qHole_ = -883253742927518753, qAscendants_ = fromList [-9176123018977089417,-9101977553270866225,-9093406545418508012,-9026590884990837132,-7266038392684934735,-7030617368587845027,-6315177474832767189,-6185538668149951971,-5045957588695750237,-2422194591007956529,-2140558072442299093,-1323860184563866252,370104820105510026,1657237947942821584,1725179241386393490,3615940558330371386,6441285251735452902,7836445554474639282,8733492850970682893], aRuleName_ = "full-evaluate"} -LF: {"AnsweredRule":{"aRuleName_":"full-evaluate","qAscendants_":[-9176123018977089417,-9101977553270866225,-9093406545418508012,-9026590884990837132,-7266038392684934735,-7030617368587845027,-6315177474832767189,-6185538668149951971,-5045957588695750237,-2422194591007956529,-2140558072442299093,-1323860184563866252,370104820105510026,1657237947942821584,1725179241386393490,3615940558330371386,6441285251735452902,7836445554474639282,8733492850970682893],"qHole_":-883253742927518753}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!or(flatten(1, [[3 = conjure_aux3 | letting q14 be (3, 4)], [q14[1] = conjure_aux3 | letting q14 be (4, 3)]; int(1..2)])) <-> - conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: q14[1] - Context #1: q14[1] = conjure_aux3 -Picking the only option: Answer 1: full-evaluate: Full evaluator - 4 -storedChoice: -q14[1] -883253742927518753 -AnsweredRule {qHole_ = -883253742927518753, qAscendants_ = fromList [-8969758503132111487,-6784916903301812310,-4362502606594339694,-2424885897194395863,-2417099766119933872,-661357570700780995,659540462714969701,741299023684531871,841316382876489834,1080971480076294633,2455636718555289611,4781036327687591913,6314971418857005121,6957705147325524125,7520484523970872436,7814781884486080266,8472710336593287104,8733492850970682893,9124601515932951508], aRuleName_ = "full-evaluate"} -LF: {"AnsweredRule":{"aRuleName_":"full-evaluate","qAscendants_":[-8969758503132111487,-6784916903301812310,-4362502606594339694,-2424885897194395863,-2417099766119933872,-661357570700780995,659540462714969701,741299023684531871,841316382876489834,1080971480076294633,2455636718555289611,4781036327687591913,6314971418857005121,6957705147325524125,7520484523970872436,7814781884486080266,8472710336593287104,8733492850970682893,9124601515932951508],"qHole_":-883253742927518753}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!or(flatten(1, [[3 = conjure_aux3 | letting q14 be (3, 4)], [4 = conjure_aux3 | letting q14 be (4, 3)]; int(1..2)])) <-> - conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: [4 = conjure_aux3 | letting q14 be (4, 3)] - Context #1: [[3 = conjure_aux3 | letting q14 be (3, 4)], [4 = conjure_aux3 | letting q14 be (4, 3)]; int(1..2)] -Picking the only option: Answer 1: generators-first: Inlining comprehension lettings. - [4 = conjure_aux3 |] -storedChoice: -[4 = conjure_aux3 | letting q14 be (4, 3)] 5094133043100232579 -AnsweredRule {qHole_ = 5094133043100232579, qAscendants_ = fromList [-8909122354700020440,-7460733051808423716,-5113575940370069634,-3275789614875181527,-1485928817419295239,-1453326525258547920,-1190111094765899527,-425934852058965166,-227269000323710205,1017324948146570036,2402920626236815200,4379418785875775437,5239709721973149055,5447511985754467121,6138327529543829831,6983653976480365703,7190718169255452642], aRuleName_ = "generators-first"} -LF: {"AnsweredRule":{"aRuleName_":"generators-first","qAscendants_":[-8909122354700020440,-7460733051808423716,-5113575940370069634,-3275789614875181527,-1485928817419295239,-1453326525258547920,-1190111094765899527,-425934852058965166,-227269000323710205,1017324948146570036,2402920626236815200,4379418785875775437,5239709721973149055,5447511985754467121,6138327529543829831,6983653976480365703,7190718169255452642],"qHole_":5094133043100232579}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!or(flatten(1, [[3 = conjure_aux3 | letting q14 be (3, 4)], [4 = conjure_aux3 |]; int(1..2)])) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: [4 = conjure_aux3 |] - Context #1: [[3 = conjure_aux3 | letting q14 be (3, 4)], [4 = conjure_aux3 |]; int(1..2)] -Picking the only option: Answer 1: generators-first: Empty generators. - [4 = conjure_aux3; int(1)] -storedChoice: -[4 = conjure_aux3 |] 6112956542716486877 -AnsweredRule {qHole_ = 6112956542716486877, qAscendants_ = fromList [-9207305118438100391,-6369735332026353512,-5991924291783106431,-5776209435213632803,-3830978856990678993,-3641847297966420112,-338462998493300906,2767710529868660813,4005580531872772405,4397758740249101114,4804584669642102451,5890086814982925863,6459294084780550343,6686373777934096773,7031238571308724387,7962655793307038867,8888369891598567800], aRuleName_ = "generators-first"} -LF: {"AnsweredRule":{"aRuleName_":"generators-first","qAscendants_":[-9207305118438100391,-6369735332026353512,-5991924291783106431,-5776209435213632803,-3830978856990678993,-3641847297966420112,-338462998493300906,2767710529868660813,4005580531872772405,4397758740249101114,4804584669642102451,5890086814982925863,6459294084780550343,6686373777934096773,7031238571308724387,7962655793307038867,8888369891598567800],"qHole_":6112956542716486877}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!or(flatten(1, [[3 = conjure_aux3 | letting q14 be (3, 4)], [4 = conjure_aux3; int(1)]; int(1..2)])) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: [3 = conjure_aux3 | letting q14 be (3, 4)] - Context #1: [[3 = conjure_aux3 | letting q14 be (3, 4)], [4 = conjure_aux3; int(1)]; int(1..2)] -Picking the only option: Answer 1: generators-first: Inlining comprehension lettings. - [3 = conjure_aux3 |] -storedChoice: -[3 = conjure_aux3 | letting q14 be (3, 4)] 4832497823804752928 -AnsweredRule {qHole_ = 4832497823804752928, qAscendants_ = fromList [-6677145406315480965,-5384732204964843677,-3071059650417301550,-2603160466482895011,-2221619722341004417,-1557091775694725768,-1403621344696630627,711266062685662619,1333581340284470498,1611305677733360901,2753561903646462793,3866947117330481491,5332477917871449756,5559142600358984796,6001232326845461178,7602738452352881434,8088691831228319750], aRuleName_ = "generators-first"} -LF: {"AnsweredRule":{"aRuleName_":"generators-first","qAscendants_":[-6677145406315480965,-5384732204964843677,-3071059650417301550,-2603160466482895011,-2221619722341004417,-1557091775694725768,-1403621344696630627,711266062685662619,1333581340284470498,1611305677733360901,2753561903646462793,3866947117330481491,5332477917871449756,5559142600358984796,6001232326845461178,7602738452352881434,8088691831228319750],"qHole_":4832497823804752928}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!or(flatten(1, [[3 = conjure_aux3 |], [4 = conjure_aux3; int(1)]; int(1..2)])) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: [3 = conjure_aux3 |] - Context #1: [[3 = conjure_aux3 |], [4 = conjure_aux3; int(1)]; int(1..2)] -Picking the only option: Answer 1: generators-first: Empty generators. - [3 = conjure_aux3; int(1)] -storedChoice: -[3 = conjure_aux3 |] -185461686146028532 -AnsweredRule {qHole_ = -185461686146028532, qAscendants_ = fromList [-8289289739114023416,-8221845150149788696,-8019537499083765163,-7053954318911112143,-6092536859292112896,-4070943207855695476,-4028159753280221929,-3732495125634815821,-3238009362727088795,-282387919327309193,1775857482582255809,1882693949567706262,2362052944268224547,4832344585872237142,7445111209011732230,7705507659096261482,8654062028269091919], aRuleName_ = "generators-first"} -LF: {"AnsweredRule":{"aRuleName_":"generators-first","qAscendants_":[-8289289739114023416,-8221845150149788696,-8019537499083765163,-7053954318911112143,-6092536859292112896,-4070943207855695476,-4028159753280221929,-3732495125634815821,-3238009362727088795,-282387919327309193,1775857482582255809,1882693949567706262,2362052944268224547,4832344585872237142,7445111209011732230,7705507659096261482,8654062028269091919],"qHole_":-185461686146028532}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!or(flatten(1, [[3 = conjure_aux3; int(1)], [4 = conjure_aux3; int(1)]; int(1..2)])) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: or(flatten(1, [[3 = conjure_aux3; int(1)], [4 = conjure_aux3; int(1)]; int(1..2)])) - Context #1: !or(flatten(1, [[3 = conjure_aux3; int(1)], [4 = conjure_aux3; int(1)]; int(1..2)])) -Picking the only option: Answer 1: quantifier-shift3: Shifting quantifier inwards - or([3 = conjure_aux3; int(1)]) \/ or([4 = conjure_aux3; int(1)]) -storedChoice: -or(flatten(1, [[3 = conjure_aux3; int(1)], [4 = conjure_aux3; int(1)]; int(1..2)])) 6206761561595236625 -AnsweredRule {qHole_ = 6206761561595236625, qAscendants_ = fromList [-9091665958233421775,-8534800408556100581,-8389275971974927944,-7928483109077342673,-7581357772290646644,-7037234840397785533,-6263532840176792370,-5427006571018076668,-4431680199820092864,-4076541738995400933,-1064366526874994538,5387747797148225385,6292098423078440671,8420337927154511626], aRuleName_ = "quantifier-shift3"} -LF: {"AnsweredRule":{"aRuleName_":"quantifier-shift3","qAscendants_":[-9091665958233421775,-8534800408556100581,-8389275971974927944,-7928483109077342673,-7581357772290646644,-7037234840397785533,-6263532840176792370,-5427006571018076668,-4431680199820092864,-4076541738995400933,-1064366526874994538,5387747797148225385,6292098423078440671,8420337927154511626],"qHole_":6206761561595236625}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!(or([3 = conjure_aux3; int(1)]) \/ or([4 = conjure_aux3; int(1)])) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: or([3 = conjure_aux3; int(1)]) - Context #1: [or([3 = conjure_aux3; int(1)]), or([4 = conjure_aux3; int(1)]); int(1..2)] -Picking the only option: Answer 1: matrix-comprehension-singleton: Removing quantifier of a single item - 3 = conjure_aux3 -storedChoice: -or([3 = conjure_aux3; int(1)]) -3434962391173132894 -AnsweredRule {qHole_ = -3434962391173132894, qAscendants_ = fromList [-7235853985473547952,-6866498255018164123,-4960622746477117042,-4585543795134183636,-4105761649660625353,-3524766623875920799,-2347278582408429201,-1565913897093032045,-636316196669785718,259925545372009536,2634241883209911323,4718505660743647939,6517008955702082360,6653106233829268540,7728404530962223160,8536818627412251687], aRuleName_ = "matrix-comprehension-singleton"} -LF: {"AnsweredRule":{"aRuleName_":"matrix-comprehension-singleton","qAscendants_":[-7235853985473547952,-6866498255018164123,-4960622746477117042,-4585543795134183636,-4105761649660625353,-3524766623875920799,-2347278582408429201,-1565913897093032045,-636316196669785718,259925545372009536,2634241883209911323,4718505660743647939,6517008955702082360,6653106233829268540,7728404530962223160,8536818627412251687],"qHole_":-3434962391173132894}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!(3 = conjure_aux3 \/ or([4 = conjure_aux3; int(1)])) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: or([4 = conjure_aux3; int(1)]) - Context #1: [3 = conjure_aux3, or([4 = conjure_aux3; int(1)]); int(1..2)] -Picking the only option: Answer 1: matrix-comprehension-singleton: Removing quantifier of a single item - 4 = conjure_aux3 -storedChoice: -or([4 = conjure_aux3; int(1)]) 8578967638246734293 -AnsweredRule {qHole_ = 8578967638246734293, qAscendants_ = fromList [-7767892036023956761,-6284781492183215029,-1727905482554729427,-1356654288157906426,2281150997448020466,2372014189263015226,2446665452257606178,2838934993441470606,4742034938664987168,4756703484454204779,6116173103300050025,6542907600674666418,7911556895678534380,8081136239962017343,8569698893899834293,8949973037119072966], aRuleName_ = "matrix-comprehension-singleton"} -LF: {"AnsweredRule":{"aRuleName_":"matrix-comprehension-singleton","qAscendants_":[-7767892036023956761,-6284781492183215029,-1727905482554729427,-1356654288157906426,2281150997448020466,2372014189263015226,2446665452257606178,2838934993441470606,4742034938664987168,4756703484454204779,6116173103300050025,6542907600674666418,7911556895678534380,8081136239962017343,8569698893899834293,8949973037119072966],"qHole_":8578967638246734293}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: and(flatten(1, - [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) - Context #1: [and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])), - !(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1; - int(1..2)] -Picking the only option: Answer 1: quantifier-shift3: Shifting quantifier inwards - and([3 = q8_1 <-> conjure_aux3 = 4; int(1)]) /\ and([4 = q8_1 <-> conjure_aux3 = 3; int(1)]) -storedChoice: -and(flatten(1, [[3 = q8_1 <-> conjure_aux3 = 4; int(1)], [4 = q8_1 <-> conjure_aux3 = 3; int(1)]; int(1..2)])) -2199657802844878530 -AnsweredRule {qHole_ = -2199657802844878530, qAscendants_ = fromList [-8444650881280502798,-8271565969096831831,-6564446395948378541,-3553121516791984732,-3091505528568185300,-28537057046234944,2611036720111951620,3048392108732098635,4941408088135413888,6187348870363663871,6391218772456415880,9128754183040712545], aRuleName_ = "quantifier-shift3"} -LF: {"AnsweredRule":{"aRuleName_":"quantifier-shift3","qAscendants_":[-8444650881280502798,-8271565969096831831,-6564446395948378541,-3553121516791984732,-3091505528568185300,-28537057046234944,2611036720111951620,3048392108732098635,4941408088135413888,6187348870363663871,6391218772456415880,9128754183040712545],"qHole_":-2199657802844878530}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - and([3 = q8_1 <-> conjure_aux3 = 4; int(1)]) /\ and([4 = q8_1 <-> conjure_aux3 = 3; int(1)]) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: and([3 = q8_1 <-> conjure_aux3 = 4; int(1)]) - Context #1: [and([3 = q8_1 <-> conjure_aux3 = 4; int(1)]), and([4 = q8_1 <-> conjure_aux3 = 3; int(1)]); int(1..2)] -Picking the only option: Answer 1: matrix-comprehension-singleton: Removing quantifier of a single item - 3 = q8_1 <-> conjure_aux3 = 4 -storedChoice: -and([3 = q8_1 <-> conjure_aux3 = 4; int(1)]) -82084885825755383 -AnsweredRule {qHole_ = -82084885825755383, qAscendants_ = fromList [-7910416632419113217,-6789993106391976797,-6474394686920849630,-4532119084740741428,-4148488185654761721,-3872345874892611968,-3008944008775182264,-2299093800387471961,-1551233151285274759,-649051754905350518,1456233810038530873,2986022555450137983,3688733153117744851,8953876927154124061], aRuleName_ = "matrix-comprehension-singleton"} -LF: {"AnsweredRule":{"aRuleName_":"matrix-comprehension-singleton","qAscendants_":[-7910416632419113217,-6789993106391976797,-6474394686920849630,-4532119084740741428,-4148488185654761721,-3872345874892611968,-3008944008775182264,-2299093800387471961,-1551233151285274759,-649051754905350518,1456233810038530873,2986022555450137983,3688733153117744851,8953876927154124061],"qHole_":-82084885825755383}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ and([4 = q8_1 <-> conjure_aux3 = 3; int(1)]) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: and([4 = q8_1 <-> conjure_aux3 = 3; int(1)]) - Context #1: [3 = q8_1 <-> conjure_aux3 = 4, and([4 = q8_1 <-> conjure_aux3 = 3; int(1)]); int(1..2)] -Picking the only option: Answer 1: matrix-comprehension-singleton: Removing quantifier of a single item - 4 = q8_1 <-> conjure_aux3 = 3 -storedChoice: -and([4 = q8_1 <-> conjure_aux3 = 3; int(1)]) 4451202942487357861 -AnsweredRule {qHole_ = 4451202942487357861, qAscendants_ = fromList [-7368630815449645005,-4752206960723048197,-2804301512506126649,-1530922004872999299,-236411210949206668,204928372325319241,2335949798361580872,2698852189043337488,3049593885211881070,3728149952134739241,4353487588625663382,5225198894548896615,5925873450508265460,6881890190583065447], aRuleName_ = "matrix-comprehension-singleton"} -LF: {"AnsweredRule":{"aRuleName_":"matrix-comprehension-singleton","qAscendants_":[-7368630815449645005,-4752206960723048197,-2804301512506126649,-1530922004872999299,-236411210949206668,204928372325319241,2335949798361580872,2698852189043337488,3049593885211881070,3728149952134739241,4353487588625663382,5225198894548896615,5925873450508265460,6881890190583065447],"qHole_":4451202942487357861}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - Context #1: conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } -Picking the only option: Answer 1: choose-repr-for-locals: Choosing representation for local variable conjure_aux3 - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } -storedChoice: -{ conjure_aux3 -@ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) -} -3398171252428132748 -AnsweredRule {qHole_ = -3398171252428132748, qAscendants_ = fromList [-4801520196462386255,-3106386946478834998,-1836288510476607810,-1423400445383478062,1875892051782461076,3043802995379454474,7974629594191079167,8285823029631020243,8636179585519730549], aRuleName_ = "choose-repr-for-locals"} -LF: {"AnsweredRule":{"aRuleName_":"choose-repr-for-locals","qAscendants_":[-4801520196462386255,-3106386946478834998,-1836288510476607810,-1423400445383478062,1875892051782461076,3043802995379454474,7974629594191079167,8285823029631020243,8636179585519730549],"qHole_":-3398171252428132748}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - Context #1: { conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - conjure_aux2_1 = - { conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } -Picking the only option: Answer 1: bubble-up-LiftVars: Bubbling up auxiliary variables. - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } -storedChoice: -conjure_aux2_1 = -{ conjure_aux3 -@ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) -} 7974629594191079167 -AnsweredRule {qHole_ = 7974629594191079167, qAscendants_ = fromList [-4801520196462386255,-3106386946478834998,-1836288510476607810,-1423400445383478062,1875892051782461076,3043802995379454474,8285823029631020243,8636179585519730549], aRuleName_ = "bubble-up-LiftVars"} -LF: {"AnsweredRule":{"aRuleName_":"bubble-up-LiftVars","qAscendants_":[-4801520196462386255,-3106386946478834998,-1836288510476607810,-1423400445383478062,1875892051782461076,3043802995379454474,8285823029631020243,8636179585519730549],"qHole_":7974629594191079167}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: conjure_aux2[2] - Context #1: conjure_aux2[2] = image(permutation((3, 4)), (q8[1], q8[2])[2]) -Picking the only option: Answer 1: tuple-index: Tuple indexing on: conjure_aux2[2] - conjure_aux2_2 -storedChoice: -conjure_aux2[2] 2042003740924818024 -AnsweredRule {qHole_ = 2042003740924818024, qAscendants_ = fromList [-7047224780753215240,-3882919266147774615,-2299063140006189613,681365846263239803,6336625794965795994,6485140089845002516,7009155380893464902,7082442116022567493,8239398540167710302], aRuleName_ = "tuple-index"} -LF: {"AnsweredRule":{"aRuleName_":"tuple-index","qAscendants_":[-7047224780753215240,-3882919266147774615,-2299063140006189613,681365846263239803,6336625794965795994,6485140089845002516,7009155380893464902,7082442116022567493,8239398540167710302],"qHole_":2042003740924818024}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2_2 = image(permutation((3, 4)), (q8[1], q8[2])[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: (q8[1], q8[2])[2] - Context #1: image(permutation((3, 4)), (q8[1], q8[2])[2]) -Picking the only option: Answer 1: tuple-index: Tuple indexing on: (q8[1], q8[2])[2] - q8[2] -storedChoice: -(q8[1], q8[2])[2] -5502204419920622825 -AnsweredRule {qHole_ = -5502204419920622825, qAscendants_ = fromList [-8588231375425367299,-8510895911811768656,-8426633625849827304,-8207238726412672978,-5936144574452389035,-2652871536273271001,-1630485539153521150,-1126023409437003920,6016260006111454055,8400731779430988570], aRuleName_ = "tuple-index"} -LF: {"AnsweredRule":{"aRuleName_":"tuple-index","qAscendants_":[-8588231375425367299,-8510895911811768656,-8426633625849827304,-8207238726412672978,-5936144574452389035,-2652871536273271001,-1630485539153521150,-1126023409437003920,6016260006111454055,8400731779430988570],"qHole_":-5502204419920622825}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2_2 = image(permutation((3, 4)), q8[2]) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: q8[2] - Context #1: image(permutation((3, 4)), q8[2]) -Picking the only option: Answer 1: tuple-index: Tuple indexing on: q8[2] - q8_2 -storedChoice: -q8[2] 6051020602090044114 -AnsweredRule {qHole_ = 6051020602090044114, qAscendants_ = fromList [-8305205627063512429,-4351892905554585329,-3978385945799741575,-2899802451648727176,-2610387685810348227,-2009358436958284574,-1222951737421888386,-579623331933497389,4724832166697728323,7712861814088489767], aRuleName_ = "tuple-index"} -LF: {"AnsweredRule":{"aRuleName_":"tuple-index","qAscendants_":[-8305205627063512429,-4351892905554585329,-3978385945799741575,-2899802451648727176,-2610387685810348227,-2009358436958284574,-1222951737421888386,-579623331933497389,4724832166697728323,7712861814088489767],"qHole_":6051020602090044114}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that conjure_aux2_2 = image(permutation((3, 4)), q8_2) - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: image(permutation((3, 4)), q8_2) - Context #1: conjure_aux2_2 = image(permutation((3, 4)), q8_2) -Picking the only option: Answer 1: permutation-image-literal{AsFunction}: Horizontal rule for permutation literal application to a single value (image), AsFunction representation - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and([q15 = q8_2 <-> conjure_aux4 = q16 | (q15, q16) <- [(3, 4), (4, 3); int(1..2)]]) /\ - (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) - } -storedChoice: -image(permutation((3, 4)), q8_2) -6566221682376100457 -AnsweredRule {qHole_ = -6566221682376100457, qAscendants_ = fromList [-7375621483096556180,-6476209656930651827,-6169031786475517693,-4051333596644929202,-1139526513744825718,614654197146956279,4282607200389588721,4519547606898719585,5902970686666028765], aRuleName_ = "permutation-image-literal{AsFunction}"} -LF: {"AnsweredRule":{"aRuleName_":"permutation-image-literal{AsFunction}","qAscendants_":[-7375621483096556180,-6476209656930651827,-6169031786475517693,-4051333596644929202,-1139526513744825718,614654197146956279,4282607200389588721,4519547606898719585,5902970686666028765],"qHole_":-6566221682376100457}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and([q15 = q8_2 <-> conjure_aux4 = q16 | (q15, q16) <- [(3, 4), (4, 3); int(1..2)]]) /\ - (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: [(3, 4), (4, 3); int(1..2)] - Context #1: [q15 = q8_2 <-> conjure_aux4 = q16 | (q15, q16) <- [(3, 4), (4, 3); int(1..2)]] -Picking the only option: Answer 1: full-evaluate: Full evaluator - [(3, 4), (4, 3); int(1..2)] -storedChoice: -[(3, 4), (4, 3); int(1..2)] 6597397470067790033 -AnsweredRule {qHole_ = 6597397470067790033, qAscendants_ = fromList [-8545307407731927617,-8177498968743831179,-5742947888929994190,-4442383996991551152,396642913451874760,889145374549031649,902104300452840084,1328695702543446488,2152276483370682723,4084473456285295179,4905601367831877360,6850337191508996871,7001603146156804613,8689879020318308638], aRuleName_ = "full-evaluate"} -LF: {"AnsweredRule":{"aRuleName_":"full-evaluate","qAscendants_":[-8545307407731927617,-8177498968743831179,-5742947888929994190,-4442383996991551152,396642913451874760,889145374549031649,902104300452840084,1328695702543446488,2152276483370682723,4084473456285295179,4905601367831877360,6850337191508996871,7001603146156804613,8689879020318308638],"qHole_":6597397470067790033}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and([q15 = q8_2 <-> conjure_aux4 = q16 | (q15, q16) <- [(3, 4), (4, 3); int(1..2)]]) /\ - (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: [q15 = q8_2 <-> conjure_aux4 = q16 | (q15, q16) <- [(3, 4), (4, 3); int(1..2)]] - Context #1: and([q15 = q8_2 <-> conjure_aux4 = q16 | (q15, q16) <- [(3, 4), (4, 3); int(1..2)]]) -Picking the only option: Answer 1: complex-pattern: complex pattern on tuple patterns - [q19[1] = q8_2 <-> conjure_aux4 = q19[2] | q19 <- [(3, 4), (4, 3); int(1..2)]] -storedChoice: -[q15 = q8_2 <-> conjure_aux4 = q16 | (q15, q16) <- [(3, 4), (4, 3); int(1..2)]] 1328695702543446488 -AnsweredRule {qHole_ = 1328695702543446488, qAscendants_ = fromList [-8545307407731927617,-8177498968743831179,-5742947888929994190,-4442383996991551152,396642913451874760,889145374549031649,902104300452840084,2152276483370682723,4084473456285295179,4905601367831877360,6850337191508996871,7001603146156804613,8689879020318308638], aRuleName_ = "complex-pattern"} -LF: {"AnsweredRule":{"aRuleName_":"complex-pattern","qAscendants_":[-8545307407731927617,-8177498968743831179,-5742947888929994190,-4442383996991551152,396642913451874760,889145374549031649,902104300452840084,2152276483370682723,4084473456285295179,4905601367831877360,6850337191508996871,7001603146156804613,8689879020318308638],"qHole_":1328695702543446488}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and([q19[1] = q8_2 <-> conjure_aux4 = q19[2] | q19 <- [(3, 4), (4, 3); int(1..2)]]) /\ - (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: [q19[1] = q8_2 <-> conjure_aux4 = q19[2] | q19 <- [(3, 4), (4, 3); int(1..2)]] - Context #1: and([q19[1] = q8_2 <-> conjure_aux4 = q19[2] | q19 <- [(3, 4), (4, 3); int(1..2)]]) -Picking the only option: Answer 1: matrix-comprehension-literal: Vertical rule for matrix-comprehension on matrix literal - flatten(1, - [[q19[1] = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (3, 4)], - [q19[1] = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (4, 3)]; - int(1..2)]) -storedChoice: -[q19[1] = q8_2 <-> conjure_aux4 = q19[2] | q19 <- [(3, 4), (4, 3); int(1..2)]] 2193708270475412974 -AnsweredRule {qHole_ = 2193708270475412974, qAscendants_ = fromList [-6135273235547916413,-3511824826747542530,-2817684250930868121,-1400917739936160745,-1319813811263441476,-481597523330641054,222999019742587203,2503474596382683671,4309903314606971320,7082348445248550107,7474061097534958542,8348619552204205832,9141480563237676781], aRuleName_ = "matrix-comprehension-literal"} -LF: {"AnsweredRule":{"aRuleName_":"matrix-comprehension-literal","qAscendants_":[-6135273235547916413,-3511824826747542530,-2817684250930868121,-1400917739936160745,-1319813811263441476,-481597523330641054,222999019742587203,2503474596382683671,4309903314606971320,7082348445248550107,7474061097534958542,8348619552204205832,9141480563237676781],"qHole_":2193708270475412974}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, - [[q19[1] = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (3, 4)], - [q19[1] = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (4, 3)]; - int(1..2)])) - /\ (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: q19[1] - Context #1: q19[1] = q8_2 -Picking the only option: Answer 1: full-evaluate: Full evaluator - 3 -storedChoice: -q19[1] 6191924817638487798 -AnsweredRule {qHole_ = 6191924817638487798, qAscendants_ = fromList [-7807298629892727492,-7342314879418443169,-6863795700888677384,-4312957023244042045,-4187455163410375661,-3675178923764728484,-2875109432163106677,-562821977670977521,-430646313158070946,645934730965016486,1213611367040462212,1245826829098445208,2464444564009404876,4591515159436918289,5954646064348546905,6209885551316441807,7780749284175319389,8140212805021622098], aRuleName_ = "full-evaluate"} -LF: {"AnsweredRule":{"aRuleName_":"full-evaluate","qAscendants_":[-7807298629892727492,-7342314879418443169,-6863795700888677384,-4312957023244042045,-4187455163410375661,-3675178923764728484,-2875109432163106677,-562821977670977521,-430646313158070946,645934730965016486,1213611367040462212,1245826829098445208,2464444564009404876,4591515159436918289,5954646064348546905,6209885551316441807,7780749284175319389,8140212805021622098],"qHole_":6191924817638487798}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, - [[3 = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (3, 4)], [q19[1] = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (4, 3)]; - int(1..2)])) - /\ (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: q19[2] - Context #1: conjure_aux4 = q19[2] -Picking the only option: Answer 1: full-evaluate: Full evaluator - 4 -storedChoice: -q19[2] 6191080349758138413 -AnsweredRule {qHole_ = 6191080349758138413, qAscendants_ = fromList [-6520176996801677506,-5843168008449148354,-5683324553460351353,-4951129330098074556,-4643211621054911287,-3822866046842193137,-3751755282991126720,-2857878400374217220,-1860910263859276895,-1737565941370477352,1050126061434755877,2341740140041990923,2502411580506467583,2525054445025194025,3419152102230274364,7279809536600806905,8523948582780839689,8905640568803089599], aRuleName_ = "full-evaluate"} -LF: {"AnsweredRule":{"aRuleName_":"full-evaluate","qAscendants_":[-6520176996801677506,-5843168008449148354,-5683324553460351353,-4951129330098074556,-4643211621054911287,-3822866046842193137,-3751755282991126720,-2857878400374217220,-1860910263859276895,-1737565941370477352,1050126061434755877,2341740140041990923,2502411580506467583,2525054445025194025,3419152102230274364,7279809536600806905,8523948582780839689,8905640568803089599],"qHole_":6191080349758138413}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, - [[3 = q8_2 <-> conjure_aux4 = 4 | letting q19 be (3, 4)], [q19[1] = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (4, 3)]; - int(1..2)])) - /\ (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: q19[1] - Context #1: q19[1] = q8_2 -Picking the only option: Answer 1: full-evaluate: Full evaluator - 4 -storedChoice: -q19[1] 6191924817638487798 -AnsweredRule {qHole_ = 6191924817638487798, qAscendants_ = fromList [-8623968074095065085,-7329444732361257248,-4918646323490343107,-3863503547689138135,-3675178923764728484,-3569961048242171061,-3144694525976125140,-3142709837274542140,-3025737286103464396,-2863059074413010081,-2845931958765307537,-1992102340549551315,-1320176390405360702,-727033692116714751,-430646313158070946,4099404035470031281,7496678802752551639,8353918602880186919], aRuleName_ = "full-evaluate"} -LF: {"AnsweredRule":{"aRuleName_":"full-evaluate","qAscendants_":[-8623968074095065085,-7329444732361257248,-4918646323490343107,-3863503547689138135,-3675178923764728484,-3569961048242171061,-3144694525976125140,-3142709837274542140,-3025737286103464396,-2863059074413010081,-2845931958765307537,-1992102340549551315,-1320176390405360702,-727033692116714751,-430646313158070946,4099404035470031281,7496678802752551639,8353918602880186919],"qHole_":6191924817638487798}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, - [[3 = q8_2 <-> conjure_aux4 = 4 | letting q19 be (3, 4)], [4 = q8_2 <-> conjure_aux4 = q19[2] | letting q19 be (4, 3)]; int(1..2)])) - /\ (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: q19[2] - Context #1: conjure_aux4 = q19[2] -Picking the only option: Answer 1: full-evaluate: Full evaluator - 3 -storedChoice: -q19[2] 6191080349758138413 -AnsweredRule {qHole_ = 6191080349758138413, qAscendants_ = fromList [-8757640153264855213,-8246403386320852045,-7634455432471374117,-6807206396586148212,-6520176996801677506,-3765915116603809328,-3206961831370542574,-2880744773295792633,10288890695967554,1236510066935204208,2127338015569558053,2891526256517846499,4193370254288787506,4672949733519819188,4775978928665173836,5268252065626460890,7614915012244226995,8901849277253604507], aRuleName_ = "full-evaluate"} -LF: {"AnsweredRule":{"aRuleName_":"full-evaluate","qAscendants_":[-8757640153264855213,-8246403386320852045,-7634455432471374117,-6807206396586148212,-6520176996801677506,-3765915116603809328,-3206961831370542574,-2880744773295792633,10288890695967554,1236510066935204208,2127338015569558053,2891526256517846499,4193370254288787506,4672949733519819188,4775978928665173836,5268252065626460890,7614915012244226995,8901849277253604507],"qHole_":6191080349758138413}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, - [[3 = q8_2 <-> conjure_aux4 = 4 | letting q19 be (3, 4)], [4 = q8_2 <-> conjure_aux4 = 3 | letting q19 be (4, 3)]; int(1..2)])) - /\ (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: [4 = q8_2 <-> conjure_aux4 = 3 | letting q19 be (4, 3)] - Context #1: [[3 = q8_2 <-> conjure_aux4 = 4 | letting q19 be (3, 4)], [4 = q8_2 <-> conjure_aux4 = 3 | letting q19 be (4, 3)]; - int(1..2)] -Picking the only option: Answer 1: generators-first: Inlining comprehension lettings. - [4 = q8_2 <-> conjure_aux4 = 3 |] -storedChoice: -[4 = q8_2 <-> conjure_aux4 = 3 | letting q19 be (4, 3)] 1588099557195084353 -AnsweredRule {qHole_ = 1588099557195084353, qAscendants_ = fromList [-8793688442874950149,-7572881584565844112,-7548342805617471592,-4348732945489509501,-2395694351007614565,88957386040583823,374422725277413608,1323284114810179273,2396707417125615551,2821870942280363336,4471571311804301542,5264705085330663748,5735937483858420141,6159114761266478893,6376856799016601882], aRuleName_ = "generators-first"} -LF: {"AnsweredRule":{"aRuleName_":"generators-first","qAscendants_":[-8793688442874950149,-7572881584565844112,-7548342805617471592,-4348732945489509501,-2395694351007614565,88957386040583823,374422725277413608,1323284114810179273,2396707417125615551,2821870942280363336,4471571311804301542,5264705085330663748,5735937483858420141,6159114761266478893,6376856799016601882],"qHole_":1588099557195084353}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4 | letting q19 be (3, 4)], [4 = q8_2 <-> conjure_aux4 = 3 |]; int(1..2)])) /\ - (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: [4 = q8_2 <-> conjure_aux4 = 3 |] - Context #1: [[3 = q8_2 <-> conjure_aux4 = 4 | letting q19 be (3, 4)], [4 = q8_2 <-> conjure_aux4 = 3 |]; int(1..2)] -Picking the only option: Answer 1: generators-first: Empty generators. - [4 = q8_2 <-> conjure_aux4 = 3; int(1)] -storedChoice: -[4 = q8_2 <-> conjure_aux4 = 3 |] 5497036040823098170 -AnsweredRule {qHole_ = 5497036040823098170, qAscendants_ = fromList [-8392241438280449004,-7601484554155610431,-6546222595955103458,-5296722524234462815,-2359991535599832467,-1063257280645700723,-17895501989558244,635280768506310618,1960340259087120798,3697301678543081257,4285418689022343979,6976383550303671088,8132222765465596941,8451535935592013102,8523836484272235728], aRuleName_ = "generators-first"} -LF: {"AnsweredRule":{"aRuleName_":"generators-first","qAscendants_":[-8392241438280449004,-7601484554155610431,-6546222595955103458,-5296722524234462815,-2359991535599832467,-1063257280645700723,-17895501989558244,635280768506310618,1960340259087120798,3697301678543081257,4285418689022343979,6976383550303671088,8132222765465596941,8451535935592013102,8523836484272235728],"qHole_":5497036040823098170}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4 | letting q19 be (3, 4)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: [3 = q8_2 <-> conjure_aux4 = 4 | letting q19 be (3, 4)] - Context #1: [[3 = q8_2 <-> conjure_aux4 = 4 | letting q19 be (3, 4)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)] -Picking the only option: Answer 1: generators-first: Inlining comprehension lettings. - [3 = q8_2 <-> conjure_aux4 = 4 |] -storedChoice: -[3 = q8_2 <-> conjure_aux4 = 4 | letting q19 be (3, 4)] 4563840366785778455 -AnsweredRule {qHole_ = 4563840366785778455, qAscendants_ = fromList [-8318635854976707433,-5946611935025738568,-5571483100812435886,-5359593091160120138,-5038848917712120091,-4505559122101590956,-4490512703364564363,-3882495187869643600,1795022445773124374,2052386823818313881,3017254667178360325,5004474385002050470,5786646087302900637,8288841898596402765,8964004080555796084], aRuleName_ = "generators-first"} -LF: {"AnsweredRule":{"aRuleName_":"generators-first","qAscendants_":[-8318635854976707433,-5946611935025738568,-5571483100812435886,-5359593091160120138,-5038848917712120091,-4505559122101590956,-4490512703364564363,-3882495187869643600,1795022445773124374,2052386823818313881,3017254667178360325,5004474385002050470,5786646087302900637,8288841898596402765,8964004080555796084],"qHole_":4563840366785778455}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4 |], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: [3 = q8_2 <-> conjure_aux4 = 4 |] - Context #1: [[3 = q8_2 <-> conjure_aux4 = 4 |], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)] -Picking the only option: Answer 1: generators-first: Empty generators. - [3 = q8_2 <-> conjure_aux4 = 4; int(1)] -storedChoice: -[3 = q8_2 <-> conjure_aux4 = 4 |] -4963556797043179790 -AnsweredRule {qHole_ = -4963556797043179790, qAscendants_ = fromList [-8774772560597070458,-8569754725622420077,-7014391000977899535,-5142692957413181259,-4041649316716467790,-3712748679124722967,-622761194274709583,-434728569439334546,1040357877965562186,2786263529603136423,3452832737484532816,4830299290996501437,5939727597018131278,7229121740432553148,8127256833064397799], aRuleName_ = "generators-first"} -LF: {"AnsweredRule":{"aRuleName_":"generators-first","qAscendants_":[-8774772560597070458,-8569754725622420077,-7014391000977899535,-5142692957413181259,-4041649316716467790,-3712748679124722967,-622761194274709583,-434728569439334546,1040357877965562186,2786263529603136423,3452832737484532816,4830299290996501437,5939727597018131278,7229121740432553148,8127256833064397799],"qHole_":-4963556797043179790}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: [(3, 4), (4, 3); int(1..2)] - Context #1: [q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]] -Picking the only option: Answer 1: full-evaluate: Full evaluator - [(3, 4), (4, 3); int(1..2)] -storedChoice: -[(3, 4), (4, 3); int(1..2)] 6597397470067790033 -AnsweredRule {qHole_ = 6597397470067790033, qAscendants_ = fromList [-8633754808918514186,-8188184727507762196,-5677541651570710819,-4916174755379616322,-4850199604535152020,-3462648503323623219,-2367628624258445968,-2307855029918049024,1883982971068606087,1912870777007720445,2809445194379708718,3667006364909395131,3677477140697149393,7256127331114215867,8364657527657792986,9047491038558976704], aRuleName_ = "full-evaluate"} -LF: {"AnsweredRule":{"aRuleName_":"full-evaluate","qAscendants_":[-8633754808918514186,-8188184727507762196,-5677541651570710819,-4916174755379616322,-4850199604535152020,-3462648503323623219,-2367628624258445968,-2307855029918049024,1883982971068606087,1912870777007720445,2809445194379708718,3667006364909395131,3677477140697149393,7256127331114215867,8364657527657792986,9047491038558976704],"qHole_":6597397470067790033}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: [q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]] - Context #1: or([q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]]) -Picking the only option: Answer 1: complex-pattern: complex pattern on tuple patterns - [q20[1] = conjure_aux4 | q20 <- [(3, 4), (4, 3); int(1..2)]] -storedChoice: -[q17 = conjure_aux4 | (q17, q18) <- [(3, 4), (4, 3); int(1..2)]] -4850199604535152020 -AnsweredRule {qHole_ = -4850199604535152020, qAscendants_ = fromList [-8633754808918514186,-8188184727507762196,-5677541651570710819,-4916174755379616322,-3462648503323623219,-2367628624258445968,-2307855029918049024,1883982971068606087,1912870777007720445,2809445194379708718,3667006364909395131,3677477140697149393,7256127331114215867,8364657527657792986,9047491038558976704], aRuleName_ = "complex-pattern"} -LF: {"AnsweredRule":{"aRuleName_":"complex-pattern","qAscendants_":[-8633754808918514186,-8188184727507762196,-5677541651570710819,-4916174755379616322,-3462648503323623219,-2367628624258445968,-2307855029918049024,1883982971068606087,1912870777007720445,2809445194379708718,3667006364909395131,3677477140697149393,7256127331114215867,8364657527657792986,9047491038558976704],"qHole_":-4850199604535152020}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!or([q20[1] = conjure_aux4 | q20 <- [(3, 4), (4, 3); int(1..2)]]) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: [q20[1] = conjure_aux4 | q20 <- [(3, 4), (4, 3); int(1..2)]] - Context #1: or([q20[1] = conjure_aux4 | q20 <- [(3, 4), (4, 3); int(1..2)]]) -Picking the only option: Answer 1: matrix-comprehension-literal: Vertical rule for matrix-comprehension on matrix literal - flatten(1, [[q20[1] = conjure_aux4 | letting q20 be (3, 4)], [q20[1] = conjure_aux4 | letting q20 be (4, 3)]; int(1..2)]) -storedChoice: -[q20[1] = conjure_aux4 | q20 <- [(3, 4), (4, 3); int(1..2)]] -7042519532359788232 -AnsweredRule {qHole_ = -7042519532359788232, qAscendants_ = fromList [-8908244575740954826,-5683928670681234592,-5283973279755061591,-3518626964796470528,-1965680338567566419,-1619218070244699183,-1290540526775639182,-1001280480543716507,-920250991117702438,-37243485035014411,3109960451075183399,3577717700431629359,4854879008546753238,5736831950861882173,7673200081862847690], aRuleName_ = "matrix-comprehension-literal"} -LF: {"AnsweredRule":{"aRuleName_":"matrix-comprehension-literal","qAscendants_":[-8908244575740954826,-5683928670681234592,-5283973279755061591,-3518626964796470528,-1965680338567566419,-1619218070244699183,-1290540526775639182,-1001280480543716507,-920250991117702438,-37243485035014411,3109960451075183399,3577717700431629359,4854879008546753238,5736831950861882173,7673200081862847690],"qHole_":-7042519532359788232}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!or(flatten(1, [[q20[1] = conjure_aux4 | letting q20 be (3, 4)], [q20[1] = conjure_aux4 | letting q20 be (4, 3)]; int(1..2)])) <-> - conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: q20[1] - Context #1: q20[1] = conjure_aux4 -Picking the only option: Answer 1: full-evaluate: Full evaluator - 3 -storedChoice: -q20[1] -5066820997822192518 -AnsweredRule {qHole_ = -5066820997822192518, qAscendants_ = fromList [-8114810939578997179,-5955986499643421728,-5766477344136638660,-3619457499884836706,-3596989804158315723,-3512526206489503481,-2484614995521209041,-1748033148869835596,-58454364784882596,76873978234325305,2489610439802360191,3564003602712422871,3732529855370416098,3884465148016108231,4296494138735898078,4399359040184583027,4639251469994992570,7395797297508748841,7886700597594415296], aRuleName_ = "full-evaluate"} -LF: {"AnsweredRule":{"aRuleName_":"full-evaluate","qAscendants_":[-8114810939578997179,-5955986499643421728,-5766477344136638660,-3619457499884836706,-3596989804158315723,-3512526206489503481,-2484614995521209041,-1748033148869835596,-58454364784882596,76873978234325305,2489610439802360191,3564003602712422871,3732529855370416098,3884465148016108231,4296494138735898078,4399359040184583027,4639251469994992570,7395797297508748841,7886700597594415296],"qHole_":-5066820997822192518}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!or(flatten(1, [[3 = conjure_aux4 | letting q20 be (3, 4)], [q20[1] = conjure_aux4 | letting q20 be (4, 3)]; int(1..2)])) <-> - conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: q20[1] - Context #1: q20[1] = conjure_aux4 -Picking the only option: Answer 1: full-evaluate: Full evaluator - 4 -storedChoice: -q20[1] -5066820997822192518 -AnsweredRule {qHole_ = -5066820997822192518, qAscendants_ = fromList [-8725074021340919078,-8574349549577316045,-7990711773149197775,-7723660686298995374,-6875295913338400819,-5695102429637848602,-5273340809049818279,-3512526206489503481,-2862537938983036678,-2765562469061820724,-807453819412548209,-307031570223611599,37627954002053673,516678838692838411,3479854824023329968,6753745594226090750,8107007183604066764,8502378019651797201,9046378511697116254], aRuleName_ = "full-evaluate"} -LF: {"AnsweredRule":{"aRuleName_":"full-evaluate","qAscendants_":[-8725074021340919078,-8574349549577316045,-7990711773149197775,-7723660686298995374,-6875295913338400819,-5695102429637848602,-5273340809049818279,-3512526206489503481,-2862537938983036678,-2765562469061820724,-807453819412548209,-307031570223611599,37627954002053673,516678838692838411,3479854824023329968,6753745594226090750,8107007183604066764,8502378019651797201,9046378511697116254],"qHole_":-5066820997822192518}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!or(flatten(1, [[3 = conjure_aux4 | letting q20 be (3, 4)], [4 = conjure_aux4 | letting q20 be (4, 3)]; int(1..2)])) <-> - conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: [4 = conjure_aux4 | letting q20 be (4, 3)] - Context #1: [[3 = conjure_aux4 | letting q20 be (3, 4)], [4 = conjure_aux4 | letting q20 be (4, 3)]; int(1..2)] -Picking the only option: Answer 1: generators-first: Inlining comprehension lettings. - [4 = conjure_aux4 |] -storedChoice: -[4 = conjure_aux4 | letting q20 be (4, 3)] -4659269292751863231 -AnsweredRule {qHole_ = -4659269292751863231, qAscendants_ = fromList [-8139107762275405780,-6067050360933011415,-4668927100952759839,-2832336555945972970,-2685263499350289956,-712998101401819851,-662867422474666417,-634413128047463436,1314890692039055455,1461492958057141352,1536420920342600247,1612507314243025908,6104410666907258834,6818646762744932078,7002085677101186921,7870098581639353518,8074964079189467219], aRuleName_ = "generators-first"} -LF: {"AnsweredRule":{"aRuleName_":"generators-first","qAscendants_":[-8139107762275405780,-6067050360933011415,-4668927100952759839,-2832336555945972970,-2685263499350289956,-712998101401819851,-662867422474666417,-634413128047463436,1314890692039055455,1461492958057141352,1536420920342600247,1612507314243025908,6104410666907258834,6818646762744932078,7002085677101186921,7870098581639353518,8074964079189467219],"qHole_":-4659269292751863231}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!or(flatten(1, [[3 = conjure_aux4 | letting q20 be (3, 4)], [4 = conjure_aux4 |]; int(1..2)])) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: [4 = conjure_aux4 |] - Context #1: [[3 = conjure_aux4 | letting q20 be (3, 4)], [4 = conjure_aux4 |]; int(1..2)] -Picking the only option: Answer 1: generators-first: Empty generators. - [4 = conjure_aux4; int(1)] -storedChoice: -[4 = conjure_aux4 |] 3103944569848083730 -AnsweredRule {qHole_ = 3103944569848083730, qAscendants_ = fromList [-6499292278244277577,-5447382347614094034,-3901800536920366688,-3381517728243229044,-2903466984087021575,-1629155788585143592,-595707724612505928,-531462185798445081,-436711175201990026,-305874969643107400,713364048257302949,3760728491479375708,4192007196113212495,5520591029544627590,7106210168219555744,7226177407162985748,8785470622724542357], aRuleName_ = "generators-first"} -LF: {"AnsweredRule":{"aRuleName_":"generators-first","qAscendants_":[-6499292278244277577,-5447382347614094034,-3901800536920366688,-3381517728243229044,-2903466984087021575,-1629155788585143592,-595707724612505928,-531462185798445081,-436711175201990026,-305874969643107400,713364048257302949,3760728491479375708,4192007196113212495,5520591029544627590,7106210168219555744,7226177407162985748,8785470622724542357],"qHole_":3103944569848083730}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!or(flatten(1, [[3 = conjure_aux4 | letting q20 be (3, 4)], [4 = conjure_aux4; int(1)]; int(1..2)])) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: [3 = conjure_aux4 | letting q20 be (3, 4)] - Context #1: [[3 = conjure_aux4 | letting q20 be (3, 4)], [4 = conjure_aux4; int(1)]; int(1..2)] -Picking the only option: Answer 1: generators-first: Inlining comprehension lettings. - [3 = conjure_aux4 |] -storedChoice: -[3 = conjure_aux4 | letting q20 be (3, 4)] -6255934535417186594 -AnsweredRule {qHole_ = -6255934535417186594, qAscendants_ = fromList [-7136276057455168685,-7072459974569890512,-6196259248273364037,-5834210587143255228,-2665342865711637679,-1906879012656170539,-1522455433242873900,752122676500601510,1351313430292206143,2164743633705935677,2917302706197316348,3522536415221397176,3844998889588585321,5240671478404014136,7264763306810372171,7563078030555210243,8716248641960869542], aRuleName_ = "generators-first"} -LF: {"AnsweredRule":{"aRuleName_":"generators-first","qAscendants_":[-7136276057455168685,-7072459974569890512,-6196259248273364037,-5834210587143255228,-2665342865711637679,-1906879012656170539,-1522455433242873900,752122676500601510,1351313430292206143,2164743633705935677,2917302706197316348,3522536415221397176,3844998889588585321,5240671478404014136,7264763306810372171,7563078030555210243,8716248641960869542],"qHole_":-6255934535417186594}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!or(flatten(1, [[3 = conjure_aux4 |], [4 = conjure_aux4; int(1)]; int(1..2)])) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: [3 = conjure_aux4 |] - Context #1: [[3 = conjure_aux4 |], [4 = conjure_aux4; int(1)]; int(1..2)] -Picking the only option: Answer 1: generators-first: Empty generators. - [3 = conjure_aux4; int(1)] -storedChoice: -[3 = conjure_aux4 |] -2658614992963116405 -AnsweredRule {qHole_ = -2658614992963116405, qAscendants_ = fromList [-8200797483737906583,-7142891394430515063,-5048865527690557400,-3204141723258765628,-2755421715163082104,-2150417528239571907,-427238415401958863,345854652969155162,444587743724873706,1433275916120849547,2082716253070264500,3621608353720498501,3817394469011428558,4338626750910725978,6129719379140106144,6899422834286368127,8748622476088678609], aRuleName_ = "generators-first"} -LF: {"AnsweredRule":{"aRuleName_":"generators-first","qAscendants_":[-8200797483737906583,-7142891394430515063,-5048865527690557400,-3204141723258765628,-2755421715163082104,-2150417528239571907,-427238415401958863,345854652969155162,444587743724873706,1433275916120849547,2082716253070264500,3621608353720498501,3817394469011428558,4338626750910725978,6129719379140106144,6899422834286368127,8748622476088678609],"qHole_":-2658614992963116405}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!or(flatten(1, [[3 = conjure_aux4; int(1)], [4 = conjure_aux4; int(1)]; int(1..2)])) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: or(flatten(1, [[3 = conjure_aux4; int(1)], [4 = conjure_aux4; int(1)]; int(1..2)])) - Context #1: !or(flatten(1, [[3 = conjure_aux4; int(1)], [4 = conjure_aux4; int(1)]; int(1..2)])) -Picking the only option: Answer 1: quantifier-shift3: Shifting quantifier inwards - or([3 = conjure_aux4; int(1)]) \/ or([4 = conjure_aux4; int(1)]) -storedChoice: -or(flatten(1, [[3 = conjure_aux4; int(1)], [4 = conjure_aux4; int(1)]; int(1..2)])) 1792302133485940861 -AnsweredRule {qHole_ = 1792302133485940861, qAscendants_ = fromList [-9215156694345218491,-7884159941367425225,-4061787575651201278,-2348548688413524686,-1616656984063374174,1019247903219888070,1202444192825383566,2448039896892401119,2522006493315280277,2872569756943491545,3292387117872397760,5871641527667180654,6531511286127386564,8891172200144465433], aRuleName_ = "quantifier-shift3"} -LF: {"AnsweredRule":{"aRuleName_":"quantifier-shift3","qAscendants_":[-9215156694345218491,-7884159941367425225,-4061787575651201278,-2348548688413524686,-1616656984063374174,1019247903219888070,1202444192825383566,2448039896892401119,2522006493315280277,2872569756943491545,3292387117872397760,5871641527667180654,6531511286127386564,8891172200144465433],"qHole_":1792302133485940861}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!(or([3 = conjure_aux4; int(1)]) \/ or([4 = conjure_aux4; int(1)])) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: or([3 = conjure_aux4; int(1)]) - Context #1: [or([3 = conjure_aux4; int(1)]), or([4 = conjure_aux4; int(1)]); int(1..2)] -Picking the only option: Answer 1: matrix-comprehension-singleton: Removing quantifier of a single item - 3 = conjure_aux4 -storedChoice: -or([3 = conjure_aux4; int(1)]) -2238338300082489653 -AnsweredRule {qHole_ = -2238338300082489653, qAscendants_ = fromList [-9135090969161870748,-7040580929681195434,-5844866756595959210,-5200489563969105483,-5135428809631204876,-4567662440315024812,-2637178807861984772,-1043830869774709897,117930584853289771,1197239461988022471,4464393825362555947,5063705836807996732,5078493517063792951,6402729242588877157,6830536617247247401,7925032212346973439], aRuleName_ = "matrix-comprehension-singleton"} -LF: {"AnsweredRule":{"aRuleName_":"matrix-comprehension-singleton","qAscendants_":[-9135090969161870748,-7040580929681195434,-5844866756595959210,-5200489563969105483,-5135428809631204876,-4567662440315024812,-2637178807861984772,-1043830869774709897,117930584853289771,1197239461988022471,4464393825362555947,5063705836807996732,5078493517063792951,6402729242588877157,6830536617247247401,7925032212346973439],"qHole_":-2238338300082489653}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!(3 = conjure_aux4 \/ or([4 = conjure_aux4; int(1)])) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: or([4 = conjure_aux4; int(1)]) - Context #1: [3 = conjure_aux4, or([4 = conjure_aux4; int(1)]); int(1..2)] -Picking the only option: Answer 1: matrix-comprehension-singleton: Removing quantifier of a single item - 4 = conjure_aux4 -storedChoice: -or([4 = conjure_aux4; int(1)]) 6931996324238769216 -AnsweredRule {qHole_ = 6931996324238769216, qAscendants_ = fromList [-8301199506799591941,-7558092101252853604,-6067998700973920226,-5155701249953128914,-4576047313272360415,-4347126985617275804,-2751859814401093547,137469789217709822,144729713112841205,2146657550292868874,3729312864595267230,4118600647582069537,4766806173317946186,4942755527663293565,6086894017411589008,8428538202899570704], aRuleName_ = "matrix-comprehension-singleton"} -LF: {"AnsweredRule":{"aRuleName_":"matrix-comprehension-singleton","qAscendants_":[-8301199506799591941,-7558092101252853604,-6067998700973920226,-5155701249953128914,-4576047313272360415,-4347126985617275804,-2751859814401093547,137469789217709822,144729713112841205,2146657550292868874,3729312864595267230,4118600647582069537,4766806173317946186,4942755527663293565,6086894017411589008,8428538202899570704],"qHole_":6931996324238769216}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) /\ - (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: and(flatten(1, - [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) - Context #1: [and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])), - !(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2; - int(1..2)] -Picking the only option: Answer 1: quantifier-shift3: Shifting quantifier inwards - and([3 = q8_2 <-> conjure_aux4 = 4; int(1)]) /\ and([4 = q8_2 <-> conjure_aux4 = 3; int(1)]) -storedChoice: -and(flatten(1, [[3 = q8_2 <-> conjure_aux4 = 4; int(1)], [4 = q8_2 <-> conjure_aux4 = 3; int(1)]; int(1..2)])) 6498896587051443094 -AnsweredRule {qHole_ = 6498896587051443094, qAscendants_ = fromList [-9122266668816456873,-8763687680398485956,-6768148177044187855,-5775912378426088215,-3542921895788471154,-2263838003336096906,-202295424977994982,851884620329916301,5528267415991175666,6533818616419587005,7566808087161406219,8046934030769361906], aRuleName_ = "quantifier-shift3"} -LF: {"AnsweredRule":{"aRuleName_":"quantifier-shift3","qAscendants_":[-9122266668816456873,-8763687680398485956,-6768148177044187855,-5775912378426088215,-3542921895788471154,-2263838003336096906,-202295424977994982,851884620329916301,5528267415991175666,6533818616419587005,7566808087161406219,8046934030769361906],"qHole_":6498896587051443094}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - and([3 = q8_2 <-> conjure_aux4 = 4; int(1)]) /\ and([4 = q8_2 <-> conjure_aux4 = 3; int(1)]) /\ - (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: and([3 = q8_2 <-> conjure_aux4 = 4; int(1)]) - Context #1: [and([3 = q8_2 <-> conjure_aux4 = 4; int(1)]), and([4 = q8_2 <-> conjure_aux4 = 3; int(1)]); int(1..2)] -Picking the only option: Answer 1: matrix-comprehension-singleton: Removing quantifier of a single item - 3 = q8_2 <-> conjure_aux4 = 4 -storedChoice: -and([3 = q8_2 <-> conjure_aux4 = 4; int(1)]) 4625414366441981983 -AnsweredRule {qHole_ = 4625414366441981983, qAscendants_ = fromList [-5032104045245797729,-4260367211447941052,-3800321491279460974,-3527728036515378511,-3186771756499085870,-2663126455000061452,-2397177437658285933,-953818733459672679,51316433765895449,382670796215945555,1275044521375561569,2333080611421701721,2485864324914475150,5509053191108998898], aRuleName_ = "matrix-comprehension-singleton"} -LF: {"AnsweredRule":{"aRuleName_":"matrix-comprehension-singleton","qAscendants_":[-5032104045245797729,-4260367211447941052,-3800321491279460974,-3527728036515378511,-3186771756499085870,-2663126455000061452,-2397177437658285933,-953818733459672679,51316433765895449,382670796215945555,1275044521375561569,2333080611421701721,2485864324914475150,5509053191108998898],"qHole_":4625414366441981983}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - (3 = q8_2 <-> conjure_aux4 = 4) /\ and([4 = q8_2 <-> conjure_aux4 = 3; int(1)]) /\ - (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: and([4 = q8_2 <-> conjure_aux4 = 3; int(1)]) - Context #1: [3 = q8_2 <-> conjure_aux4 = 4, and([4 = q8_2 <-> conjure_aux4 = 3; int(1)]); int(1..2)] -Picking the only option: Answer 1: matrix-comprehension-singleton: Removing quantifier of a single item - 4 = q8_2 <-> conjure_aux4 = 3 -storedChoice: -and([4 = q8_2 <-> conjure_aux4 = 3; int(1)]) -8650590815054601249 -AnsweredRule {qHole_ = -8650590815054601249, qAscendants_ = fromList [-7526881736718068312,-7405557604309373817,-7201686808491642883,-6330762734028692340,-5804239247306276412,-5043128294307900798,-4578161512601023984,-2463121278901514889,303127519297990446,594877140964359361,1533543948414682137,4243960396898301951,6573830124911821771,7997158881778982126], aRuleName_ = "matrix-comprehension-singleton"} -LF: {"AnsweredRule":{"aRuleName_":"matrix-comprehension-singleton","qAscendants_":[-7526881736718068312,-7405557604309373817,-7201686808491642883,-6330762734028692340,-5804239247306276412,-5043128294307900798,-4578161512601023984,-2463121278901514889,303127519297990446,594877140964359361,1533543948414682137,4243960396898301951,6573830124911821771,7997158881778982126],"qHole_":-8650590815054601249}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ - (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ - (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) - } - Context #1: conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ - (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) - } -Picking the only option: Answer 1: choose-repr-for-locals: Choosing representation for local variable conjure_aux4 - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ - (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) - } -storedChoice: -{ conjure_aux4 -@ find conjure_aux4: int(1..5) - such that - (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ - (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) -} -5523540219623150802 -AnsweredRule {qHole_ = -5523540219623150802, qAscendants_ = fromList [-8941059882607301911,-4338998493244249628,-2962415465773075069,-2259331243426380901,-565469044512126150,-60812526271457966,2469584683440447504,4682955345466050776,5578803032032481190], aRuleName_ = "choose-repr-for-locals"} -LF: {"AnsweredRule":{"aRuleName_":"choose-repr-for-locals","qAscendants_":[-8941059882607301911,-4338998493244249628,-2962415465773075069,-2259331243426380901,-565469044512126150,-60812526271457966,2469584683440447504,4682955345466050776,5578803032032481190],"qHole_":-5523540219623150802}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ - (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ - (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) - } - Context #1: { conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - conjure_aux2_2 = - { conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ - (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) - } - } -Picking the only option: Answer 1: bubble-up-LiftVars: Bubbling up auxiliary variables. - { conjure_aux2_2 = conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ - (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) - } -storedChoice: -conjure_aux2_2 = -{ conjure_aux4 -@ find conjure_aux4: int(1..5) - such that - (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ - (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) -} 4682955345466050776 -AnsweredRule {qHole_ = 4682955345466050776, qAscendants_ = fromList [-8941059882607301911,-4338998493244249628,-2962415465773075069,-2259331243426380901,-565469044512126150,-60812526271457966,2469584683440447504,5578803032032481190], aRuleName_ = "bubble-up-LiftVars"} -LF: {"AnsweredRule":{"aRuleName_":"bubble-up-LiftVars","qAscendants_":[-8941059882607301911,-4338998493244249628,-2962415465773075069,-2259331243426380901,-565469044512126150,-60812526271457966,2469584683440447504,5578803032032481190],"qHole_":4682955345466050776}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - { conjure_aux2_2 = conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ - (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: { conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - { conjure_aux2_2 = conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ - (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - Context #1: [{ conjure_aux2 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - { conjure_aux2_2 = conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ - (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) - } - } - in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]] -Picking the only option: Answer 1: bubble-up-LiftVars: Bubbling up auxiliary variables. - { conjure_aux2 in conjure_aux1 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - { conjure_aux2_2 = conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ - (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) - } - } -storedChoice: -{ conjure_aux2 -@ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - { conjure_aux2_2 = conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ - (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) - } -} -in conjure_aux1 -8498631454693468162 -AnsweredRule {qHole_ = -8498631454693468162, qAscendants_ = fromList [-8906484870153215238,-5210480414835359833,-1572320097158340186,7262859821198064716,7664399396112355801,9199488081424848815], aRuleName_ = "bubble-up-LiftVars"} -LF: {"AnsweredRule":{"aRuleName_":"bubble-up-LiftVars","qAscendants_":[-8906484870153215238,-5210480414835359833,-1572320097158340186,7262859821198064716,7664399396112355801,9199488081424848815],"qHole_":-8498631454693468162}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 in conjure_aux1 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - { conjure_aux2_2 = conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ - (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) - } - } | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8[1], q8[2]]]) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: q8[1] - Context #1: x_RelationAsMatrix[q8[1]] -Picking the only option: Answer 1: tuple-index: Tuple indexing on: q8[1] - q8_1 -storedChoice: -q8[1] 6051865069970393497 -AnsweredRule {qHole_ = 6051865069970393497, qAscendants_ = fromList [-8640702807944529160,-7554917160340714381,-7282620252070677492,-4679672213039578282,-3902820972913913543,-1648680758926951321,-323488035431343639,4558015980602682727], aRuleName_ = "tuple-index"} -LF: {"AnsweredRule":{"aRuleName_":"tuple-index","qAscendants_":[-8640702807944529160,-7554917160340714381,-7282620252070677492,-4679672213039578282,-3902820972913913543,-1648680758926951321,-323488035431343639,4558015980602682727],"qHole_":6051865069970393497}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 in conjure_aux1 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - { conjure_aux2_2 = conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ - (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) - } - } | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8[2]]]) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: q8[2] - Context #1: x_RelationAsMatrix[q8_1, q8[2]] -Picking the only option: Answer 1: tuple-index: Tuple indexing on: q8[2] - q8_2 -storedChoice: -q8[2] 6051020602090044114 -AnsweredRule {qHole_ = 6051020602090044114, qAscendants_ = fromList [-1657839898828256711,-1442033437105002979,-382389179101208790,2791764908100697416,2932884812988402663,3044000407645637671,4978224969731597410], aRuleName_ = "tuple-index"} -LF: {"AnsweredRule":{"aRuleName_":"tuple-index","qAscendants_":[-1657839898828256711,-1442033437105002979,-382389179101208790,2791764908100697416,2932884812988402663,3044000407645637671,4978224969731597410],"qHole_":6051020602090044114}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and([{ conjure_aux2 in conjure_aux1 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - { conjure_aux2_2 = conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ - (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) - } - } | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]]) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: [{ conjure_aux2 in conjure_aux1 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - { conjure_aux2_2 = conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ - (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) - } - } | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] - Context #1: and([{ conjure_aux2 in conjure_aux1 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - { conjure_aux2_2 = conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ - (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) - } - } | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]]) -Picking the only option: Answer 1: bubble-up-LiftVars: Bubbling up auxiliary variables through a comprehension. - { [conjure_aux2 in conjure_aux1 | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([{ conjure_aux2_1[q8_1, q8_2] = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } | q8_1 : int(1..5), q8_2 : int(1..5)]), - and([{ conjure_aux2_2[q8_1, q8_2] = conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ - (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) - } | q8_1 : int(1..5), q8_2 : int(1..5)]) - } -storedChoice: -[{ conjure_aux2 in conjure_aux1 - @ find conjure_aux2_1: int(1..5) - find conjure_aux2_2: int(1..5) - such that - { conjure_aux2_1 = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } - such that - { conjure_aux2_2 = conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ - (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) - } - } | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] 4632560015221358179 -AnsweredRule {qHole_ = 4632560015221358179, qAscendants_ = fromList [-7796146364068057171,-6981365833241776808,-5029665938164178889,-3928434564447926958,-2893776785872977312], aRuleName_ = "bubble-up-LiftVars"} -LF: {"AnsweredRule":{"aRuleName_":"bubble-up-LiftVars","qAscendants_":[-7796146364068057171,-6981365833241776808,-5029665938164178889,-3928434564447926958,-2893776785872977312],"qHole_":4632560015221358179}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and({ [conjure_aux2 in conjure_aux1 | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([{ conjure_aux2_1[q8_1, q8_2] = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } | q8_1 : int(1..5), q8_2 : int(1..5)]), - and([{ conjure_aux2_2[q8_1, q8_2] = conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ - (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) - } | q8_1 : int(1..5), q8_2 : int(1..5)]) - }) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: { [conjure_aux2 in conjure_aux1 - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([{ conjure_aux2_1[q8_1, q8_2] = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } | q8_1 : int(1..5), q8_2 : int(1..5)]), - and([{ conjure_aux2_2[q8_1, q8_2] = conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ - (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) - } | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - Context #1: and({ [conjure_aux2 in conjure_aux1 | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([{ conjure_aux2_1[q8_1, q8_2] = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } | q8_1 : int(1..5), q8_2 : int(1..5)]), - and([{ conjure_aux2_2[q8_1, q8_2] = conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ - (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) - } | q8_1 : int(1..5), q8_2 : int(1..5)]) - }) -Picking the only option: Answer 1: choose-repr-for-locals: Choosing representation for local variable conjure_aux2_1 - { [conjure_aux2 in conjure_aux1 | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([{ conjure_aux2_1[q8_1, q8_2] = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } | q8_1 : int(1..5), q8_2 : int(1..5)]), - and([{ conjure_aux2_2[q8_1, q8_2] = conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ - (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) - } | q8_1 : int(1..5), q8_2 : int(1..5)]) - } -storedChoice: -{ [conjure_aux2 in conjure_aux1 | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] -@ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([{ conjure_aux2_1[q8_1, q8_2] = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } | q8_1 : int(1..5), q8_2 : int(1..5)]), - and([{ conjure_aux2_2[q8_1, q8_2] = conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ - (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) - } | q8_1 : int(1..5), q8_2 : int(1..5)]) -} 5183357163976320088 -AnsweredRule {qHole_ = 5183357163976320088, qAscendants_ = fromList [-5465830923914696498,-4063366109563536561,-2043995450352341839,378335084364868291,1311484366701431644], aRuleName_ = "choose-repr-for-locals"} -LF: {"AnsweredRule":{"aRuleName_":"choose-repr-for-locals","qAscendants_":[-5465830923914696498,-4063366109563536561,-2043995450352341839,378335084364868291,1311484366701431644],"qHole_":5183357163976320088}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and({ [conjure_aux2 in conjure_aux1 | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([{ conjure_aux2_1[q8_1, q8_2] = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } | q8_1 : int(1..5), q8_2 : int(1..5)]), - and([{ conjure_aux2_2[q8_1, q8_2] = conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ - (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) - } | q8_1 : int(1..5), q8_2 : int(1..5)]) - }) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: [{ conjure_aux2_1[q8_1, q8_2] = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } | q8_1 : int(1..5), q8_2 : int(1..5)] - Context #1: and([{ conjure_aux2_1[q8_1, q8_2] = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } | q8_1 : int(1..5), q8_2 : int(1..5)]) -Picking the only option: Answer 1: bubble-up-LiftVars: Bubbling up auxiliary variables through a comprehension. - { [conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)] - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } -storedChoice: -[{ conjure_aux2_1[q8_1, q8_2] = conjure_aux3 - @ find conjure_aux3: int(1..5) - such that - (3 = q8_1 <-> conjure_aux3 = 4) /\ (4 = q8_1 <-> conjure_aux3 = 3) /\ - (!(3 = conjure_aux3 \/ 4 = conjure_aux3) <-> conjure_aux3 = q8_1) - } | q8_1 : int(1..5), q8_2 : int(1..5)] -2066028230956466058 -AnsweredRule {qHole_ = -2066028230956466058, qAscendants_ = fromList [-8778252753919104373,-5465830923914696498,-4063366109563536561,-2043995450352341839,378335084364868291,1311484366701431644,5183357163976320088], aRuleName_ = "bubble-up-LiftVars"} -LF: {"AnsweredRule":{"aRuleName_":"bubble-up-LiftVars","qAscendants_":[-8778252753919104373,-5465830923914696498,-4063366109563536561,-2043995450352341839,378335084364868291,1311484366701431644,5183357163976320088],"qHole_":-2066028230956466058}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and({ [conjure_aux2 in conjure_aux1 | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and({ [conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)] - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }), - and([{ conjure_aux2_2[q8_1, q8_2] = conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ - (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) - } | q8_1 : int(1..5), q8_2 : int(1..5)]) - }) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: { [conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)] - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - Context #1: and({ [conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)] - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }) -Picking the only option: Answer 1: choose-repr-for-locals: Choosing representation for local variable conjure_aux3 - { [conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)] - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } -storedChoice: -{ [conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)] -@ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) -} -2683400798428888576 -AnsweredRule {qHole_ = -2683400798428888576, qAscendants_ = fromList [-7630765854898757381,-5152289056460337438,-4378029185233493510,-2193789157648306228,-780484605375639491,4611290103392876019,8129436120778745950], aRuleName_ = "choose-repr-for-locals"} -LF: {"AnsweredRule":{"aRuleName_":"choose-repr-for-locals","qAscendants_":[-7630765854898757381,-5152289056460337438,-4378029185233493510,-2193789157648306228,-780484605375639491,4611290103392876019,8129436120778745950],"qHole_":-2683400798428888576}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and({ [conjure_aux2 in conjure_aux1 | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and({ [conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)] - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }), - and([{ conjure_aux2_2[q8_1, q8_2] = conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ - (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) - } | q8_1 : int(1..5), q8_2 : int(1..5)]) - }) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: and({ [conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] - | q8_1 : int(1..5), q8_2 : int(1..5)] - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }) - Context #1: { [conjure_aux2 in conjure_aux1 | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and({ [conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)] - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }), - and([{ conjure_aux2_2[q8_1, q8_2] = conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ - (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) - } | q8_1 : int(1..5), q8_2 : int(1..5)]) - } -Picking the only option: Answer 1: bubble-up-LiftVars: Bubbling up auxiliary variables. - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } -storedChoice: -and({ [conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)] - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }) -7630765854898757381 -AnsweredRule {qHole_ = -7630765854898757381, qAscendants_ = fromList [-5152289056460337438,-4378029185233493510,-2193789157648306228,-780484605375639491,4611290103392876019,8129436120778745950], aRuleName_ = "bubble-up-LiftVars"} -LF: {"AnsweredRule":{"aRuleName_":"bubble-up-LiftVars","qAscendants_":[-5152289056460337438,-4378029185233493510,-2193789157648306228,-780484605375639491,4611290103392876019,8129436120778745950],"qHole_":-7630765854898757381}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and({ [conjure_aux2 in conjure_aux1 | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - and([{ conjure_aux2_2[q8_1, q8_2] = conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ - (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) - } | q8_1 : int(1..5), q8_2 : int(1..5)]) - }) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: [{ conjure_aux2_2[q8_1, q8_2] = conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ - (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) - } | q8_1 : int(1..5), q8_2 : int(1..5)] - Context #1: and([{ conjure_aux2_2[q8_1, q8_2] = conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ - (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) - } | q8_1 : int(1..5), q8_2 : int(1..5)]) -Picking the only option: Answer 1: bubble-up-LiftVars: Bubbling up auxiliary variables through a comprehension. - { [conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)] - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } -storedChoice: -[{ conjure_aux2_2[q8_1, q8_2] = conjure_aux4 - @ find conjure_aux4: int(1..5) - such that - (3 = q8_2 <-> conjure_aux4 = 4) /\ (4 = q8_2 <-> conjure_aux4 = 3) /\ - (!(3 = conjure_aux4 \/ 4 = conjure_aux4) <-> conjure_aux4 = q8_2) - } | q8_1 : int(1..5), q8_2 : int(1..5)] 4586595665260781575 -AnsweredRule {qHole_ = 4586595665260781575, qAscendants_ = fromList [-5189262863924670079,-4576870578376860616,-3657040581488238581,667350004362937900,5588145911994567168,7042957946885141470,7965291691177128164], aRuleName_ = "bubble-up-LiftVars"} -LF: {"AnsweredRule":{"aRuleName_":"bubble-up-LiftVars","qAscendants_":[-5189262863924670079,-4576870578376860616,-3657040581488238581,667350004362937900,5588145911994567168,7042957946885141470,7965291691177128164],"qHole_":4586595665260781575}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and({ [conjure_aux2 in conjure_aux1 | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - and({ [conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)] - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }) - }) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: { [conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)] - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - Context #1: and({ [conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)] - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }) -Picking the only option: Answer 1: choose-repr-for-locals: Choosing representation for local variable conjure_aux4 - { [conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)] - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } -storedChoice: -{ [conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)] -@ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) -} -1434005429531325525 -AnsweredRule {qHole_ = -1434005429531325525, qAscendants_ = fromList [-7860778431127922714,-4340120710083553155,-3276746255609047616,-2418004144569851915,-329464522225361142,8566682329173394842,8971959176905079767], aRuleName_ = "choose-repr-for-locals"} -LF: {"AnsweredRule":{"aRuleName_":"choose-repr-for-locals","qAscendants_":[-7860778431127922714,-4340120710083553155,-3276746255609047616,-2418004144569851915,-329464522225361142,8566682329173394842,8971959176905079767],"qHole_":-1434005429531325525}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and({ [conjure_aux2 in conjure_aux1 | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - and({ [conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)] - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }) - }) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: and({ [conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] - | q8_1 : int(1..5), q8_2 : int(1..5)] - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }) - Context #1: { [conjure_aux2 in conjure_aux1 | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - and({ [conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)] - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }) - } -Picking the only option: Answer 1: bubble-up-LiftVars: Bubbling up auxiliary variables. - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } -storedChoice: -and({ [conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)] - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }) -329464522225361142 -AnsweredRule {qHole_ = -329464522225361142, qAscendants_ = fromList [-7860778431127922714,-4340120710083553155,-3276746255609047616,-2418004144569851915,8566682329173394842,8971959176905079767], aRuleName_ = "bubble-up-LiftVars"} -LF: {"AnsweredRule":{"aRuleName_":"bubble-up-LiftVars","qAscendants_":[-7860778431127922714,-4340120710083553155,-3276746255609047616,-2418004144569851915,8566682329173394842,8971959176905079767],"qHole_":-329464522225361142}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and({ [conjure_aux2 in conjure_aux1 | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - }) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: conjure_aux2 in conjure_aux1 - Context #1: [conjure_aux2 in conjure_aux1 | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] -Picking the only option: Answer 1: relation-in: relation membership to existential quantification - or([q27 = conjure_aux2 | q27 <- toSet(conjure_aux1)]) -storedChoice: -conjure_aux2 in conjure_aux1 7266634060293924720 -AnsweredRule {qHole_ = 7266634060293924720, qAscendants_ = fromList [-7266324578771459181,-6713121642540228318,-5826297241095436731,-5526349309453330732,1756707357159771390,2149626909839152329,4938058042264599181], aRuleName_ = "relation-in"} -LF: {"AnsweredRule":{"aRuleName_":"relation-in","qAscendants_":[-7266324578771459181,-6713121642540228318,-5826297241095436731,-5526349309453330732,1756707357159771390,2149626909839152329,4938058042264599181],"qHole_":7266634060293924720}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and({ [or([q27 = conjure_aux2 | q27 <- toSet(conjure_aux1)]) | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - }) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: [q27 = conjure_aux2 | q27 <- toSet(conjure_aux1)] - Context #1: or([q27 = conjure_aux2 | q27 <- toSet(conjure_aux1)]) -Picking the only option: Answer 1: relation-map_in_expr{RelationAsMatrix}: Vertical rule for map_in_expr for relation domains, RelationAsMatrix representation. - [(q28[1], q28[2]) = conjure_aux2 | q28 : (int(1..5), int(1..5)), conjure_aux1_RelationAsMatrix[q28[1], q28[2]]] -storedChoice: -[q27 = conjure_aux2 | q27 <- toSet(conjure_aux1)] -3470261408387399930 -AnsweredRule {qHole_ = -3470261408387399930, qAscendants_ = fromList [-8536113027950480792,-7330204231396072871,-4786623393387445427,-4223003553667075844,4116516722814445548,4281838781863596501,6175095517354461663,6559035824535384582], aRuleName_ = "relation-map_in_expr{RelationAsMatrix}"} -LF: {"AnsweredRule":{"aRuleName_":"relation-map_in_expr{RelationAsMatrix}","qAscendants_":[-8536113027950480792,-7330204231396072871,-4786623393387445427,-4223003553667075844,4116516722814445548,4281838781863596501,6175095517354461663,6559035824535384582],"qHole_":-3470261408387399930}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and({ [or([(q28[1], q28[2]) = conjure_aux2 | q28 : (int(1..5), int(1..5)), conjure_aux1_RelationAsMatrix[q28[1], q28[2]]]) - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - }) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: [(q28[1], q28[2]) = conjure_aux2 - | q28 : (int(1..5), int(1..5)), conjure_aux1_RelationAsMatrix[q28[1], q28[2]]] - Context #1: or([(q28[1], q28[2]) = conjure_aux2 | q28 : (int(1..5), int(1..5)), conjure_aux1_RelationAsMatrix[q28[1], q28[2]]]) -Picking the only option: Answer 1: choose-repr-for-comprehension: Choosing representation for quantified variable q28 (with type: (int, - int)) - [(q28[1], q28[2]) = conjure_aux2 | q28_1 : int(1..5), q28_2 : int(1..5), conjure_aux1_RelationAsMatrix[q28[1], q28[2]]] -storedChoice: -[(q28[1], q28[2]) = conjure_aux2 | q28 : (int(1..5), int(1..5)), conjure_aux1_RelationAsMatrix[q28[1], q28[2]]] 4348009411125732066 -AnsweredRule {qHole_ = 4348009411125732066, qAscendants_ = fromList [-6592612559904363413,-6472871177545322172,-6453293890463000807,-2235240472846537890,3259852529283772574,4455209103885624492,6352194885377054835,8420829954716127361], aRuleName_ = "choose-repr-for-comprehension"} -LF: {"AnsweredRule":{"aRuleName_":"choose-repr-for-comprehension","qAscendants_":[-6592612559904363413,-6472871177545322172,-6453293890463000807,-2235240472846537890,3259852529283772574,4455209103885624492,6352194885377054835,8420829954716127361],"qHole_":4348009411125732066}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and({ [or([(q28[1], q28[2]) = conjure_aux2 | q28_1 : int(1..5), q28_2 : int(1..5), conjure_aux1_RelationAsMatrix[q28[1], q28[2]]]) - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - }) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: (q28[1], q28[2]) = conjure_aux2 - Context #1: [(q28[1], q28[2]) = conjure_aux2 | q28_1 : int(1..5), q28_2 : int(1..5), conjure_aux1_RelationAsMatrix[q28[1], q28[2]]] -Picking the only option: Answer 1: tuple-eq: Horizontal rule for tuple equality - q28[1] = conjure_aux2_1 /\ q28[2] = conjure_aux2_2 -storedChoice: -(q28[1], q28[2]) = conjure_aux2 -4124337097652933443 -AnsweredRule {qHole_ = -4124337097652933443, qAscendants_ = fromList [-6634517003356473421,-4157154907530130258,-932339049260687039,4056979115757602560,5419805607560390341,5700344114265930133,8275228852675492835,8651388538213571462,8952456806918978808], aRuleName_ = "tuple-eq"} -LF: {"AnsweredRule":{"aRuleName_":"tuple-eq","qAscendants_":[-6634517003356473421,-4157154907530130258,-932339049260687039,4056979115757602560,5419805607560390341,5700344114265930133,8275228852675492835,8651388538213571462,8952456806918978808],"qHole_":-4124337097652933443}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and({ [or([q28[1] = conjure_aux2_1 /\ q28[2] = conjure_aux2_2 - | q28_1 : int(1..5), q28_2 : int(1..5), conjure_aux1_RelationAsMatrix[q28[1], q28[2]]]) - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - }) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: q28[1] - Context #1: q28[1] = conjure_aux2_1 -Picking the only option: Answer 1: tuple-index: Tuple indexing on: q28[1] - q28_1 -storedChoice: -q28[1] 8787010607011614834 -AnsweredRule {qHole_ = 8787010607011614834, qAscendants_ = fromList [-8956326597613561383,-6532059540256123763,-6109385609926416455,-3678896154897738560,-419523469793567323,-407169135612228618,2034669589965157861,4997220444967745554,6148375269450574671,6513082934840114429,8747477145020099131,8922317001415918920], aRuleName_ = "tuple-index"} -LF: {"AnsweredRule":{"aRuleName_":"tuple-index","qAscendants_":[-8956326597613561383,-6532059540256123763,-6109385609926416455,-3678896154897738560,-419523469793567323,-407169135612228618,2034669589965157861,4997220444967745554,6148375269450574671,6513082934840114429,8747477145020099131,8922317001415918920],"qHole_":8787010607011614834}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and({ [or([q28_1 = conjure_aux2_1 /\ q28[2] = conjure_aux2_2 - | q28_1 : int(1..5), q28_2 : int(1..5), conjure_aux1_RelationAsMatrix[q28[1], q28[2]]]) - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - }) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: q28[2] - Context #1: q28[2] = conjure_aux2_2 -Picking the only option: Answer 1: tuple-index: Tuple indexing on: q28[2] - q28_2 -storedChoice: -q28[2] 8786166143426335913 -AnsweredRule {qHole_ = 8786166143426335913, qAscendants_ = fromList [-7531325615783388500,-6124769537006831453,-2577262930135244673,-590286472771932315,-83534367005148570,715122028962684739,1709615173437954783,5607005680561137835,7486385006046341809,7705725891024727552,8323234866884020390,8780789924434106151], aRuleName_ = "tuple-index"} -LF: {"AnsweredRule":{"aRuleName_":"tuple-index","qAscendants_":[-7531325615783388500,-6124769537006831453,-2577262930135244673,-590286472771932315,-83534367005148570,715122028962684739,1709615173437954783,5607005680561137835,7486385006046341809,7705725891024727552,8323234866884020390,8780789924434106151],"qHole_":8786166143426335913}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and({ [or([q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2 - | q28_1 : int(1..5), q28_2 : int(1..5), conjure_aux1_RelationAsMatrix[q28[1], q28[2]]]) - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - }) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: q28[1] - Context #1: conjure_aux1_RelationAsMatrix[q28[1]] -Picking the only option: Answer 1: tuple-index: Tuple indexing on: q28[1] - q28_1 -storedChoice: -q28[1] 8787010607011614834 -AnsweredRule {qHole_ = 8787010607011614834, qAscendants_ = fromList [-6233761776568569553,-6207878452900388515,-3381866216268371578,-560496032557153780,-80631966925160875,1067854355870431415,1108013619790213016,4161317878060049142,4647826867886404607,5228020545282852391,8646369751965333728], aRuleName_ = "tuple-index"} -LF: {"AnsweredRule":{"aRuleName_":"tuple-index","qAscendants_":[-6233761776568569553,-6207878452900388515,-3381866216268371578,-560496032557153780,-80631966925160875,1067854355870431415,1108013619790213016,4161317878060049142,4647826867886404607,5228020545282852391,8646369751965333728],"qHole_":8787010607011614834}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and({ [or([q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2 - | q28_1 : int(1..5), q28_2 : int(1..5), conjure_aux1_RelationAsMatrix[q28_1, q28[2]]]) - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - }) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: q28[2] - Context #1: conjure_aux1_RelationAsMatrix[q28_1, q28[2]] -Picking the only option: Answer 1: tuple-index: Tuple indexing on: q28[2] - q28_2 -storedChoice: -q28[2] 8786166143426335913 -AnsweredRule {qHole_ = 8786166143426335913, qAscendants_ = fromList [-8932183048783716768,-6021176910053718006,-1484921959836170832,-1243263695470418987,-307241860641088143,5123914162100475129,6415834318102058907,6682610423178443283,7959220516069049554,8895625464985590456], aRuleName_ = "tuple-index"} -LF: {"AnsweredRule":{"aRuleName_":"tuple-index","qAscendants_":[-8932183048783716768,-6021176910053718006,-1484921959836170832,-1243263695470418987,-307241860641088143,5123914162100475129,6415834318102058907,6682610423178443283,7959220516069049554,8895625464985590456],"qHole_":8786166143426335913}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and({ [or([q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2 - | q28_1 : int(1..5), q28_2 : int(1..5), conjure_aux1_RelationAsMatrix[q28_1, q28_2]]) - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - }) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: [q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2 - | q28_1 : int(1..5), q28_2 : int(1..5), conjure_aux1_RelationAsMatrix[q28_1, q28_2]] - Context #1: or([q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2 - | q28_1 : int(1..5), q28_2 : int(1..5), conjure_aux1_RelationAsMatrix[q28_1, q28_2]]) -Picking the only option: Answer 1: inline-conditions: Inlining conditions, inside or - [conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)] -storedChoice: -[q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2 - | q28_1 : int(1..5), q28_2 : int(1..5), conjure_aux1_RelationAsMatrix[q28_1, q28_2]] -9107354217279316955 -AnsweredRule {qHole_ = -9107354217279316955, qAscendants_ = fromList [-7614046741660552896,-7556360939789777851,-6910364700408604777,-6183630476596424374,-2673910102480230275,7059218223957164648,8407785490318688805,8504193122766115214], aRuleName_ = "inline-conditions"} -LF: {"AnsweredRule":{"aRuleName_":"inline-conditions","qAscendants_":[-7614046741660552896,-7556360939789777851,-6910364700408604777,-6183630476596424374,-2673910102480230275,7059218223957164648,8407785490318688805,8504193122766115214],"qHole_":-9107354217279316955}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - and({ [or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - }) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: and({ [or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ - (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - }) - Context #1: [|x| = |conjure_aux1|, - and({ [or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - }); - int(1..2)] -Picking the only option: Answer 1: bubble-up-LiftVars: Bubbling up auxiliary variables. - { and([or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]]) - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - } -storedChoice: -and({ [or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - }) 7825224301270217826 -AnsweredRule {qHole_ = 7825224301270217826, qAscendants_ = fromList [-7337214924393354854,-6793331199204698657,4098536301578040545,4694401685199555588], aRuleName_ = "bubble-up-LiftVars"} -LF: {"AnsweredRule":{"aRuleName_":"bubble-up-LiftVars","qAscendants_":[-7337214924393354854,-6793331199204698657,4098536301578040545,4694401685199555588],"qHole_":7825224301270217826}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - { and([or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]]) - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - } - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: [or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ - (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] - Context #1: and([or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]]) -Picking the only option: Answer 1: inline-conditions: Inlining conditions, inside and - [x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)] -storedChoice: -[or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5), x_RelationAsMatrix[q8_1, q8_2]] -7818394351581759390 -AnsweredRule {qHole_ = -7818394351581759390, qAscendants_ = fromList [-8854367752148363141,868987242372315934,1952008385480716564,2094581585082781447,3197112935473569797,5197989222011368608], aRuleName_ = "inline-conditions"} -LF: {"AnsweredRule":{"aRuleName_":"inline-conditions","qAscendants_":[-8854367752148363141,868987242372315934,1952008385480716564,2094581585082781447,3197112935473569797,5197989222011368608],"qHole_":-7818394351581759390}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - |x| = |conjure_aux1| /\ - { and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - } - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: [|x| = |conjure_aux1|, - { and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - }; int(1..2)] - Context #1: |x| = |conjure_aux1| /\ - { and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - } -Picking the only option: Answer 1: bubble-up-LiftVars: Bubbling up auxiliary variables. - { [|x| = |conjure_aux1|, - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]); - int(1..2)] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - } -storedChoice: -[|x| = |conjure_aux1|, - { and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - }; int(1..2)] 8700659888572119213 -AnsweredRule {qHole_ = 8700659888572119213, qAscendants_ = fromList [1085907639859271742,5213477129051060331,8301951387372896488], aRuleName_ = "bubble-up-LiftVars"} -LF: {"AnsweredRule":{"aRuleName_":"bubble-up-LiftVars","qAscendants_":[1085907639859271742,5213477129051060331,8301951387372896488],"qHole_":8700659888572119213}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - and({ [|x| = |conjure_aux1|, - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]); - int(1..2)] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - }) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: |x| - Context #1: |x| = |conjure_aux1| -Picking the only option: Answer 1: relation-cardinality: Relation cardinality - |toSet(x)| -storedChoice: -|x| -1852370716973049233 -AnsweredRule {qHole_ = -1852370716973049233, qAscendants_ = fromList [-8274899275771564111,-7189265364834618222,-4195293662753593531,-2250203036499850017,4837893138970417558,5156053544824672407], aRuleName_ = "relation-cardinality"} -LF: {"AnsweredRule":{"aRuleName_":"relation-cardinality","qAscendants_":[-8274899275771564111,-7189265364834618222,-4195293662753593531,-2250203036499850017,4837893138970417558,5156053544824672407],"qHole_":-1852370716973049233}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - and({ [|toSet(x)| = |conjure_aux1|, - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]); - int(1..2)] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - }) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: |toSet(x)| - Context #1: |toSet(x)| = |conjure_aux1| -Picking the only option: Answer 1: set-card: Horizontal rule for set cardinality. - sum([1 | q29 <- toSet(x)]) -storedChoice: -|toSet(x)| 1897988597909520616 -AnsweredRule {qHole_ = 1897988597909520616, qAscendants_ = fromList [-6188688663705288789,-5846429895491118400,361855989135376679,6530150935582701688,7219968226893579546,7779309324238844246], aRuleName_ = "set-card"} -LF: {"AnsweredRule":{"aRuleName_":"set-card","qAscendants_":[-6188688663705288789,-5846429895491118400,361855989135376679,6530150935582701688,7219968226893579546,7779309324238844246],"qHole_":1897988597909520616}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - and({ [sum([1 | q29 <- toSet(x)]) = |conjure_aux1|, - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]); - int(1..2)] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - }) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: [1 | q29 <- toSet(x)] - Context #1: sum([1 | q29 <- toSet(x)]) -Picking the only option: Answer 1: relation-map_in_expr{RelationAsMatrix}: Vertical rule for map_in_expr for relation domains, RelationAsMatrix representation. - [1 | q30 : (int(1..5), int(1..5)), x_RelationAsMatrix[q30[1], q30[2]]] -storedChoice: -[1 | q29 <- toSet(x)] 7483192753320191769 -AnsweredRule {qHole_ = 7483192753320191769, qAscendants_ = fromList [-7918094600437589284,-6091097458145320110,-4725927117271772380,-3818842550960350061,-801403655548510881,4177802111281067004,8691639764190092042], aRuleName_ = "relation-map_in_expr{RelationAsMatrix}"} -LF: {"AnsweredRule":{"aRuleName_":"relation-map_in_expr{RelationAsMatrix}","qAscendants_":[-7918094600437589284,-6091097458145320110,-4725927117271772380,-3818842550960350061,-801403655548510881,4177802111281067004,8691639764190092042],"qHole_":7483192753320191769}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - and({ [sum([1 | q30 : (int(1..5), int(1..5)), x_RelationAsMatrix[q30[1], q30[2]]]) = |conjure_aux1|, - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]); - int(1..2)] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - }) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: [1 | q30 : (int(1..5), int(1..5)), x_RelationAsMatrix[q30[1], q30[2]]] - Context #1: sum([1 | q30 : (int(1..5), int(1..5)), x_RelationAsMatrix[q30[1], q30[2]]]) -Picking the only option: Answer 1: choose-repr-for-comprehension: Choosing representation for quantified variable q30 (with type: (int, - int)) - [1 | q30_1 : int(1..5), q30_2 : int(1..5), x_RelationAsMatrix[q30[1], q30[2]]] -storedChoice: -[1 | q30 : (int(1..5), int(1..5)), x_RelationAsMatrix[q30[1], q30[2]]] -2219318056453463832 -AnsweredRule {qHole_ = -2219318056453463832, qAscendants_ = fromList [-7631595452381029825,-6332648069028765836,-5599362277318624933,-1170492770147107149,188905738781826972,1046361987104095667,9181513732839926293], aRuleName_ = "choose-repr-for-comprehension"} -LF: {"AnsweredRule":{"aRuleName_":"choose-repr-for-comprehension","qAscendants_":[-7631595452381029825,-6332648069028765836,-5599362277318624933,-1170492770147107149,188905738781826972,1046361987104095667,9181513732839926293],"qHole_":-2219318056453463832}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - and({ [sum([1 | q30_1 : int(1..5), q30_2 : int(1..5), x_RelationAsMatrix[q30[1], q30[2]]]) = |conjure_aux1|, - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]); - int(1..2)] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - }) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: q30[1] - Context #1: x_RelationAsMatrix[q30[1]] -Picking the only option: Answer 1: tuple-index: Tuple indexing on: q30[1] - q30_1 -storedChoice: -q30[1] 8985411351629801837 -AnsweredRule {qHole_ = 8985411351629801837, qAscendants_ = fromList [-7287907811082918289,-3433749237930268197,-1514549063082826885,-254808116082235497,1395102958002486929,3724900484480857440,3763839719817425200,3764103551892886579,7098469255683427931,8809290278576126972], aRuleName_ = "tuple-index"} -LF: {"AnsweredRule":{"aRuleName_":"tuple-index","qAscendants_":[-7287907811082918289,-3433749237930268197,-1514549063082826885,-254808116082235497,1395102958002486929,3724900484480857440,3763839719817425200,3764103551892886579,7098469255683427931,8809290278576126972],"qHole_":8985411351629801837}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - and({ [sum([1 | q30_1 : int(1..5), q30_2 : int(1..5), x_RelationAsMatrix[q30_1, q30[2]]]) = |conjure_aux1|, - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]); - int(1..2)] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - }) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: q30[2] - Context #1: x_RelationAsMatrix[q30_1, q30[2]] -Picking the only option: Answer 1: tuple-index: Tuple indexing on: q30[2] - q30_2 -storedChoice: -q30[2] 8986255815215080758 -AnsweredRule {qHole_ = 8986255815215080758, qAscendants_ = fromList [-1904605123138931514,-1605383351683875510,-1500814072571245463,-1159370656118278861,-345152881798089093,3653718321561964858,5560045049720260591,6001294353827372355,7845034033468093823], aRuleName_ = "tuple-index"} -LF: {"AnsweredRule":{"aRuleName_":"tuple-index","qAscendants_":[-1904605123138931514,-1605383351683875510,-1500814072571245463,-1159370656118278861,-345152881798089093,3653718321561964858,5560045049720260591,6001294353827372355,7845034033468093823],"qHole_":8986255815215080758}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - and({ [sum([1 | q30_1 : int(1..5), q30_2 : int(1..5), x_RelationAsMatrix[q30_1, q30_2]]) = |conjure_aux1|, - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]); - int(1..2)] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - }) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: [1 | q30_1 : int(1..5), q30_2 : int(1..5), x_RelationAsMatrix[q30_1, q30_2]] - Context #1: sum([1 | q30_1 : int(1..5), q30_2 : int(1..5), x_RelationAsMatrix[q30_1, q30_2]]) -Picking the only option: Answer 1: inline-conditions: Inlining conditions, inside sum - [toInt(x_RelationAsMatrix[q30_1, q30_2]) * catchUndef(1, 0) | q30_1 : int(1..5), q30_2 : int(1..5)] -storedChoice: -[1 | q30_1 : int(1..5), q30_2 : int(1..5), x_RelationAsMatrix[q30_1, q30_2]] 6730778895089912004 -AnsweredRule {qHole_ = 6730778895089912004, qAscendants_ = fromList [-5543455485138138697,-1367499344277324489,-577770218778700729,3965135726409895025,4154476703970574900,4424005630299656964,8591791291160167043], aRuleName_ = "inline-conditions"} -LF: {"AnsweredRule":{"aRuleName_":"inline-conditions","qAscendants_":[-5543455485138138697,-1367499344277324489,-577770218778700729,3965135726409895025,4154476703970574900,4424005630299656964,8591791291160167043],"qHole_":6730778895089912004}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - and({ [sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) * catchUndef(1, 0) | q30_1 : int(1..5), q30_2 : int(1..5)]) = |conjure_aux1|, - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]); - int(1..2)] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - }) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: catchUndef(1, 0) - Context #1: [toInt(x_RelationAsMatrix[q30_1, q30_2]), catchUndef(1, 0); int(1..2)] -Picking the only option: Answer 1: full-evaluate: Full evaluator - 1 -storedChoice: -catchUndef(1, 0) -4103543015608659681 -AnsweredRule {qHole_ = -4103543015608659681, qAscendants_ = fromList [-6246651641675555191,-4991494778996523170,-4841212563091249093,-3913142375130629094,-3482484897580979170,-192545505272530247,4617164660703414243,7663465281870587155,7888233777833351600,8484251082711739255], aRuleName_ = "full-evaluate"} -LF: {"AnsweredRule":{"aRuleName_":"full-evaluate","qAscendants_":[-6246651641675555191,-4991494778996523170,-4841212563091249093,-3913142375130629094,-3482484897580979170,-192545505272530247,4617164660703414243,7663465281870587155,7888233777833351600,8484251082711739255],"qHole_":-4103543015608659681}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - and({ [sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) * 1 | q30_1 : int(1..5), q30_2 : int(1..5)]) = |conjure_aux1|, - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]); - int(1..2)] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - }) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: toInt(x_RelationAsMatrix[q30_1, q30_2]) * 1 - Context #1: [toInt(x_RelationAsMatrix[q30_1, q30_2]) * 1 | q30_1 : int(1..5), q30_2 : int(1..5)] -Picking the only option: Answer 1: partial-evaluate: Partial evaluator - product([toInt(x_RelationAsMatrix[q30_1, q30_2]); int(1)]) -storedChoice: -toInt(x_RelationAsMatrix[q30_1, q30_2]) * 1 -1687514346990485250 -AnsweredRule {qHole_ = -1687514346990485250, qAscendants_ = fromList [-8383279591293107624,-5870374077749082103,-5035592936147091491,-3450507034164856240,-3171744958437112094,-148321104615195040,923428228047877070,2221664695150773241], aRuleName_ = "partial-evaluate"} -LF: {"AnsweredRule":{"aRuleName_":"partial-evaluate","qAscendants_":[-8383279591293107624,-5870374077749082103,-5035592936147091491,-3450507034164856240,-3171744958437112094,-148321104615195040,923428228047877070,2221664695150773241],"qHole_":-1687514346990485250}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - and({ [sum([product([toInt(x_RelationAsMatrix[q30_1, q30_2]); int(1)]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = |conjure_aux1|, - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]); - int(1..2)] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - }) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: product([toInt(x_RelationAsMatrix[q30_1, q30_2]); int(1)]) - Context #1: [product([toInt(x_RelationAsMatrix[q30_1, q30_2]); int(1)]) | q30_1 : int(1..5), q30_2 : int(1..5)] -Picking the only option: Answer 1: matrix-comprehension-singleton: Removing quantifier of a single item - toInt(x_RelationAsMatrix[q30_1, q30_2]) -storedChoice: -product([toInt(x_RelationAsMatrix[q30_1, q30_2]); int(1)]) -601225972055529548 -AnsweredRule {qHole_ = -601225972055529548, qAscendants_ = fromList [-7799870564036439127,-7432780384698737696,-6354763341195320334,-5508479272970515476,-2004497734168533005,1354218247559476283,3284517275149475981,4357080134642246606], aRuleName_ = "matrix-comprehension-singleton"} -LF: {"AnsweredRule":{"aRuleName_":"matrix-comprehension-singleton","qAscendants_":[-7799870564036439127,-7432780384698737696,-6354763341195320334,-5508479272970515476,-2004497734168533005,1354218247559476283,3284517275149475981,4357080134642246606],"qHole_":-601225972055529548}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - and({ [sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = |conjure_aux1|, - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]); - int(1..2)] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - }) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: |conjure_aux1| - Context #1: sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = |conjure_aux1| -Picking the only option: Answer 1: relation-cardinality: Relation cardinality - |toSet(conjure_aux1)| -storedChoice: -|conjure_aux1| 547691173299348338 -AnsweredRule {qHole_ = 547691173299348338, qAscendants_ = fromList [-7326096647933004975,-3638343112521383479,-2681179249513342582,-1433468233918517477,416753721122881089,6250330639306929770], aRuleName_ = "relation-cardinality"} -LF: {"AnsweredRule":{"aRuleName_":"relation-cardinality","qAscendants_":[-7326096647933004975,-3638343112521383479,-2681179249513342582,-1433468233918517477,416753721122881089,6250330639306929770],"qHole_":547691173299348338}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - and({ [sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = |toSet(conjure_aux1)|, - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]); - int(1..2)] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - }) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: |toSet(conjure_aux1)| - Context #1: sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = |toSet(conjure_aux1)| -Picking the only option: Answer 1: set-card: Horizontal rule for set cardinality. - sum([1 | q31 <- toSet(conjure_aux1)]) -storedChoice: -|toSet(conjure_aux1)| -1999756309500896427 -AnsweredRule {qHole_ = -1999756309500896427, qAscendants_ = fromList [-7320026331482846196,-1560614952215100976,3610191966919989235,3922795876024111867,4652593413741964988,8460019197720106806], aRuleName_ = "set-card"} -LF: {"AnsweredRule":{"aRuleName_":"set-card","qAscendants_":[-7320026331482846196,-1560614952215100976,3610191966919989235,3922795876024111867,4652593413741964988,8460019197720106806],"qHole_":-1999756309500896427}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - and({ [sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = sum([1 | q31 <- toSet(conjure_aux1)]), - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]); - int(1..2)] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - }) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: [1 | q31 <- toSet(conjure_aux1)] - Context #1: sum([1 | q31 <- toSet(conjure_aux1)]) -Picking the only option: Answer 1: relation-map_in_expr{RelationAsMatrix}: Vertical rule for map_in_expr for relation domains, RelationAsMatrix representation. - [1 | q32 : (int(1..5), int(1..5)), conjure_aux1_RelationAsMatrix[q32[1], q32[2]]] -storedChoice: -[1 | q31 <- toSet(conjure_aux1)] 4978495210772817269 -AnsweredRule {qHole_ = 4978495210772817269, qAscendants_ = fromList [-7947851092910419335,-4272160902177458760,-654328132560036401,4133420425219294144,6369167416454940534,6390095031407007755,7113998651427981501], aRuleName_ = "relation-map_in_expr{RelationAsMatrix}"} -LF: {"AnsweredRule":{"aRuleName_":"relation-map_in_expr{RelationAsMatrix}","qAscendants_":[-7947851092910419335,-4272160902177458760,-654328132560036401,4133420425219294144,6369167416454940534,6390095031407007755,7113998651427981501],"qHole_":4978495210772817269}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - and({ [sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = - sum([1 | q32 : (int(1..5), int(1..5)), conjure_aux1_RelationAsMatrix[q32[1], q32[2]]]), - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]); - int(1..2)] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - }) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: [1 | q32 : (int(1..5), int(1..5)), conjure_aux1_RelationAsMatrix[q32[1], q32[2]]] - Context #1: sum([1 | q32 : (int(1..5), int(1..5)), conjure_aux1_RelationAsMatrix[q32[1], q32[2]]]) -Picking the only option: Answer 1: choose-repr-for-comprehension: Choosing representation for quantified variable q32 (with type: (int, - int)) - [1 | q32_1 : int(1..5), q32_2 : int(1..5), conjure_aux1_RelationAsMatrix[q32[1], q32[2]]] -storedChoice: -[1 | q32 : (int(1..5), int(1..5)), conjure_aux1_RelationAsMatrix[q32[1], q32[2]]] 3282965607985773269 -AnsweredRule {qHole_ = 3282965607985773269, qAscendants_ = fromList [-7122899784982260955,-5889198071192861072,-531055723096273851,147713573061616732,2477913925342540157,3767703974941705567,9091983968002426702], aRuleName_ = "choose-repr-for-comprehension"} -LF: {"AnsweredRule":{"aRuleName_":"choose-repr-for-comprehension","qAscendants_":[-7122899784982260955,-5889198071192861072,-531055723096273851,147713573061616732,2477913925342540157,3767703974941705567,9091983968002426702],"qHole_":3282965607985773269}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - and({ [sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = - sum([1 | q32_1 : int(1..5), q32_2 : int(1..5), conjure_aux1_RelationAsMatrix[q32[1], q32[2]]]), - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]); - int(1..2)] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - }) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: q32[1] - Context #1: conjure_aux1_RelationAsMatrix[q32[1]] -Picking the only option: Answer 1: tuple-index: Tuple indexing on: q32[1] - q32_1 -storedChoice: -q32[1] 4038868374035555703 -AnsweredRule {qHole_ = 4038868374035555703, qAscendants_ = fromList [-8553658543572221773,-6138711856874023512,-4335853381078465244,-2646146961819662754,-2343456358494450273,-1664802311461525085,-1649342081664357811,3161695419280017087,3741265834386353390,8703630850884516346], aRuleName_ = "tuple-index"} -LF: {"AnsweredRule":{"aRuleName_":"tuple-index","qAscendants_":[-8553658543572221773,-6138711856874023512,-4335853381078465244,-2646146961819662754,-2343456358494450273,-1664802311461525085,-1649342081664357811,3161695419280017087,3741265834386353390,8703630850884516346],"qHole_":4038868374035555703}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - and({ [sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = - sum([1 | q32_1 : int(1..5), q32_2 : int(1..5), conjure_aux1_RelationAsMatrix[q32_1, q32[2]]]), - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]); - int(1..2)] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - }) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: q32[2] - Context #1: conjure_aux1_RelationAsMatrix[q32_1, q32[2]] -Picking the only option: Answer 1: tuple-index: Tuple indexing on: q32[2] - q32_2 -storedChoice: -q32[2] 4038586886173796060 -AnsweredRule {qHole_ = 4038586886173796060, qAscendants_ = fromList [58246981470148902,365936135746281162,897915292494521279,2148255109439096362,2599338170801596327,4347596293011070033,8156974448309241515,8375135551163386670,8976994852842826417], aRuleName_ = "tuple-index"} -LF: {"AnsweredRule":{"aRuleName_":"tuple-index","qAscendants_":[58246981470148902,365936135746281162,897915292494521279,2148255109439096362,2599338170801596327,4347596293011070033,8156974448309241515,8375135551163386670,8976994852842826417],"qHole_":4038586886173796060}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - and({ [sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = - sum([1 | q32_1 : int(1..5), q32_2 : int(1..5), conjure_aux1_RelationAsMatrix[q32_1, q32_2]]), - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]); - int(1..2)] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - }) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: [1 | q32_1 : int(1..5), q32_2 : int(1..5), conjure_aux1_RelationAsMatrix[q32_1, q32_2]] - Context #1: sum([1 | q32_1 : int(1..5), q32_2 : int(1..5), conjure_aux1_RelationAsMatrix[q32_1, q32_2]]) -Picking the only option: Answer 1: inline-conditions: Inlining conditions, inside sum - [toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) * catchUndef(1, 0) | q32_1 : int(1..5), q32_2 : int(1..5)] -storedChoice: -[1 | q32_1 : int(1..5), q32_2 : int(1..5), conjure_aux1_RelationAsMatrix[q32_1, q32_2]] -5719405584779695493 -AnsweredRule {qHole_ = -5719405584779695493, qAscendants_ = fromList [-9027745215861162370,-8099216132366058965,-5857000228242749317,-5553782237459419472,4623787234387693138,7124000196337888585,8079567542521963183], aRuleName_ = "inline-conditions"} -LF: {"AnsweredRule":{"aRuleName_":"inline-conditions","qAscendants_":[-9027745215861162370,-8099216132366058965,-5857000228242749317,-5553782237459419472,4623787234387693138,7124000196337888585,8079567542521963183],"qHole_":-5719405584779695493}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - and({ [sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = - sum([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) * catchUndef(1, 0) | q32_1 : int(1..5), q32_2 : int(1..5)]), - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]); - int(1..2)] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - }) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: catchUndef(1, 0) - Context #1: [toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]), catchUndef(1, 0); int(1..2)] -Picking the only option: Answer 1: full-evaluate: Full evaluator - 1 -storedChoice: -catchUndef(1, 0) -4103543015608659681 -AnsweredRule {qHole_ = -4103543015608659681, qAscendants_ = fromList [-8969688714663757079,-8620054688580705850,-7803342152587091485,-6406402188841036454,-3137912990386087120,-2245754891843782432,-893701506107809144,-421079377584717971,4859060653783625533,9081980220064719370], aRuleName_ = "full-evaluate"} -LF: {"AnsweredRule":{"aRuleName_":"full-evaluate","qAscendants_":[-8969688714663757079,-8620054688580705850,-7803342152587091485,-6406402188841036454,-3137912990386087120,-2245754891843782432,-893701506107809144,-421079377584717971,4859060653783625533,9081980220064719370],"qHole_":-4103543015608659681}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - and({ [sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = - sum([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) * 1 | q32_1 : int(1..5), q32_2 : int(1..5)]), - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]); - int(1..2)] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - }) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) * 1 - Context #1: [toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) * 1 | q32_1 : int(1..5), q32_2 : int(1..5)] -Picking the only option: Answer 1: partial-evaluate: Partial evaluator - product([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]); int(1)]) -storedChoice: -toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) * 1 -4682469706785037945 -AnsweredRule {qHole_ = -4682469706785037945, qAscendants_ = fromList [-9179050654683062954,-8797033748133430528,-8329454991333631126,-5647606918064816013,-3380861767487578940,6010365049512866508,6747419370843152779,7119833088853932687], aRuleName_ = "partial-evaluate"} -LF: {"AnsweredRule":{"aRuleName_":"partial-evaluate","qAscendants_":[-9179050654683062954,-8797033748133430528,-8329454991333631126,-5647606918064816013,-3380861767487578940,6010365049512866508,6747419370843152779,7119833088853932687],"qHole_":-4682469706785037945}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - and({ [sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = - sum([product([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]); int(1)]) | q32_1 : int(1..5), q32_2 : int(1..5)]), - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]); - int(1..2)] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - }) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: product([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]); int(1)]) - Context #1: [product([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]); int(1)]) | q32_1 : int(1..5), q32_2 : int(1..5)] -Picking the only option: Answer 1: matrix-comprehension-singleton: Removing quantifier of a single item - toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) -storedChoice: -product([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]); int(1)]) -3618757702268377732 -AnsweredRule {qHole_ = -3618757702268377732, qAscendants_ = fromList [-3180788541249390624,-1419697389512850335,2051112281511221751,3011082682326874338,4702464191332467431,4730858055169822202,6821954100224183740,8108702534288021537], aRuleName_ = "matrix-comprehension-singleton"} -LF: {"AnsweredRule":{"aRuleName_":"matrix-comprehension-singleton","qAscendants_":[-3180788541249390624,-1419697389512850335,2051112281511221751,3011082682326874338,4702464191332467431,4730858055169822202,6821954100224183740,8108702534288021537],"qHole_":-3618757702268377732}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - and({ [sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = - sum([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) | q32_1 : int(1..5), q32_2 : int(1..5)]), - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]); - int(1..2)] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - }) - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: and({ [sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = - sum([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) | q32_1 : int(1..5), q32_2 : int(1..5)]), - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]); - int(1..2)] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - }) - Context #1: { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - and({ [sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = - sum([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) | q32_1 : int(1..5), q32_2 : int(1..5)]), - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]); - int(1..2)] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - }) - } -Picking the only option: Answer 1: bubble-up-LiftVars: Bubbling up auxiliary variables. - { sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = - sum([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) | q32_1 : int(1..5), q32_2 : int(1..5)]) - /\ - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - } -storedChoice: -and({ [sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = - sum([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) | q32_1 : int(1..5), q32_2 : int(1..5)]), - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]); - int(1..2)] - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - }) -4558336889735046944 -AnsweredRule {qHole_ = -4558336889735046944, qAscendants_ = fromList [-3486949521822083211,2980043443155673363], aRuleName_ = "bubble-up-LiftVars"} -LF: {"AnsweredRule":{"aRuleName_":"bubble-up-LiftVars","qAscendants_":[-3486949521822083211,2980043443155673363],"qHole_":-4558336889735046944}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - { sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = - sum([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) | q32_1 : int(1..5), q32_2 : int(1..5)]) - /\ - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - } - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: y = - { conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - { sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = - sum([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) | q32_1 : int(1..5), q32_2 : int(1..5)]) - /\ - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - } - } -Picking the only option: Answer 1: bubble-up-LiftVars: Bubbling up auxiliary variables. - { y = conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - { sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = - sum([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) | q32_1 : int(1..5), q32_2 : int(1..5)]) - /\ - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - } - } -storedChoice: -y = -{ conjure_aux1 -@ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - { sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = - sum([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) | q32_1 : int(1..5), q32_2 : int(1..5)]) - /\ - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - } -} 8908675996089062110 -AnsweredRule {qHole_ = 8908675996089062110, qAscendants_ = fromList [], aRuleName_ = "bubble-up-LiftVars"} -LF: {"AnsweredRule":{"aRuleName_":"bubble-up-LiftVars","qAscendants_":[],"qHole_":8908675996089062110}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - { y = conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - { sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = - sum([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) | q32_1 : int(1..5), q32_2 : int(1..5)]) - /\ - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - } - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: y = conjure_aux1 - Context #1: { y = conjure_aux1 - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - { sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = - sum([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) | q32_1 : int(1..5), q32_2 : int(1..5)]) - /\ - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - } - } -Picking the only option: Answer 1: identical-domain-eq: Generic vertical rule for identical-domain equality - and([y_RelationAsMatrix = conjure_aux1_RelationAsMatrix; int(1)]) -storedChoice: -y = conjure_aux1 3717099060101766216 -AnsweredRule {qHole_ = 3717099060101766216, qAscendants_ = fromList [2671848414499686108], aRuleName_ = "identical-domain-eq"} -LF: {"AnsweredRule":{"aRuleName_":"identical-domain-eq","qAscendants_":[2671848414499686108],"qHole_":3717099060101766216}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - { and([y_RelationAsMatrix = conjure_aux1_RelationAsMatrix; int(1)]) - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - { sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = - sum([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) | q32_1 : int(1..5), q32_2 : int(1..5)]) - /\ - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - } - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: y_RelationAsMatrix = conjure_aux1_RelationAsMatrix - Context #1: [y_RelationAsMatrix = conjure_aux1_RelationAsMatrix; int(1)] -Picking the only option: Answer 1: matrix-eq: Horizontal rule for matrix = - and([y_RelationAsMatrix[q33] = conjure_aux1_RelationAsMatrix[q33] | q33 : int(1..5)]) -storedChoice: -y_RelationAsMatrix = conjure_aux1_RelationAsMatrix 847538541028825252 -AnsweredRule {qHole_ = 847538541028825252, qAscendants_ = fromList [-7545604584042643741,-3140704007737949652,8589500105863926587], aRuleName_ = "matrix-eq"} -LF: {"AnsweredRule":{"aRuleName_":"matrix-eq","qAscendants_":[-7545604584042643741,-3140704007737949652,8589500105863926587],"qHole_":847538541028825252}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - { and([and([y_RelationAsMatrix[q33] = conjure_aux1_RelationAsMatrix[q33] | q33 : int(1..5)]); int(1)]) - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - { sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = - sum([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) | q32_1 : int(1..5), q32_2 : int(1..5)]) - /\ - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - } - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: [y_RelationAsMatrix[q33] = conjure_aux1_RelationAsMatrix[q33] | q33 : int(1..5)] - Context #1: and([y_RelationAsMatrix[q33] = conjure_aux1_RelationAsMatrix[q33] | q33 : int(1..5)]) -Picking the only option: Answer 1: choose-repr-for-comprehension: Choosing representation for quantified variable q33 (with type: int) - [y_RelationAsMatrix[q33] = conjure_aux1_RelationAsMatrix[q33] | q33 : int(1..5)] -storedChoice: -[y_RelationAsMatrix[q33] = conjure_aux1_RelationAsMatrix[q33] | q33 : int(1..5)] 45103260545151270 -AnsweredRule {qHole_ = 45103260545151270, qAscendants_ = fromList [-5973861858959396663,-4660253290178341140,-3962474706459959320,-1163992588452778161], aRuleName_ = "choose-repr-for-comprehension"} -LF: {"AnsweredRule":{"aRuleName_":"choose-repr-for-comprehension","qAscendants_":[-5973861858959396663,-4660253290178341140,-3962474706459959320,-1163992588452778161],"qHole_":45103260545151270}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - { and([and([y_RelationAsMatrix[q33] = conjure_aux1_RelationAsMatrix[q33] | q33 : int(1..5)]); int(1)]) - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - { sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = - sum([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) | q32_1 : int(1..5), q32_2 : int(1..5)]) - /\ - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - } - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: y_RelationAsMatrix[q33] = conjure_aux1_RelationAsMatrix[q33] - Context #1: [y_RelationAsMatrix[q33] = conjure_aux1_RelationAsMatrix[q33] | q33 : int(1..5)] -Picking the only option: Answer 1: matrix-eq: Horizontal rule for matrix = - and([y_RelationAsMatrix[q33, q35] = conjure_aux1_RelationAsMatrix[q33, q35] | q35 : int(1..5)]) -storedChoice: -y_RelationAsMatrix[q33] = conjure_aux1_RelationAsMatrix[q33] 971298532972344754 -AnsweredRule {qHole_ = 971298532972344754, qAscendants_ = fromList [-5973861858959396663,-4660253290178341140,-3962474706459959320,-1163992588452778161,45103260545151270], aRuleName_ = "matrix-eq"} -LF: {"AnsweredRule":{"aRuleName_":"matrix-eq","qAscendants_":[-5973861858959396663,-4660253290178341140,-3962474706459959320,-1163992588452778161,45103260545151270],"qHole_":971298532972344754}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - { and([and([and([y_RelationAsMatrix[q33, q35] = conjure_aux1_RelationAsMatrix[q33, q35] | q35 : int(1..5)]) | q33 : int(1..5)]); - int(1)]) - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - { sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = - sum([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) | q32_1 : int(1..5), q32_2 : int(1..5)]) - /\ - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - } - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: [y_RelationAsMatrix[q33, q35] = conjure_aux1_RelationAsMatrix[q33, q35] | q35 : int(1..5)] - Context #1: and([y_RelationAsMatrix[q33, q35] = conjure_aux1_RelationAsMatrix[q33, q35] | q35 : int(1..5)]) -Picking the only option: Answer 1: choose-repr-for-comprehension: Choosing representation for quantified variable q35 (with type: int) - [y_RelationAsMatrix[q33, q35] = conjure_aux1_RelationAsMatrix[q33, q35] | q35 : int(1..5)] -storedChoice: -[y_RelationAsMatrix[q33, q35] = conjure_aux1_RelationAsMatrix[q33, q35] | q35 : int(1..5)] -1275491152285478671 -AnsweredRule {qHole_ = -1275491152285478671, qAscendants_ = fromList [-9124538447972763747,1151872964749555522,2218928338283019637,3574995822047355118,8452562685486794942,8526913528687567140], aRuleName_ = "choose-repr-for-comprehension"} -LF: {"AnsweredRule":{"aRuleName_":"choose-repr-for-comprehension","qAscendants_":[-9124538447972763747,1151872964749555522,2218928338283019637,3574995822047355118,8452562685486794942,8526913528687567140],"qHole_":-1275491152285478671}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - { and([and([and([y_RelationAsMatrix[q33, q35] = conjure_aux1_RelationAsMatrix[q33, q35] | q35 : int(1..5)]) | q33 : int(1..5)]); - int(1)]) - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - { sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = - sum([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) | q32_1 : int(1..5), q32_2 : int(1..5)]) - /\ - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - } - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: and([and([and([y_RelationAsMatrix[q33, q35] = conjure_aux1_RelationAsMatrix[q33, q35] - | q35 : int(1..5)]) - | q33 : int(1..5)]); - int(1)]) - Context #1: { and([and([and([y_RelationAsMatrix[q33, q35] = conjure_aux1_RelationAsMatrix[q33, q35] | q35 : int(1..5)]) - | q33 : int(1..5)]); - int(1)]) - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - { sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = - sum([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) | q32_1 : int(1..5), q32_2 : int(1..5)]) - /\ - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - } - } -Picking the only option: Answer 1: matrix-comprehension-singleton: Removing quantifier of a single item - and([and([y_RelationAsMatrix[q33, q35] = conjure_aux1_RelationAsMatrix[q33, q35] | q35 : int(1..5)]) | q33 : int(1..5)]) -storedChoice: -and([and([and([y_RelationAsMatrix[q33, q35] = conjure_aux1_RelationAsMatrix[q33, q35] | q35 : int(1..5)]) | q33 : int(1..5)]); - int(1)]) 3574995822047355118 -AnsweredRule {qHole_ = 3574995822047355118, qAscendants_ = fromList [1151872964749555522], aRuleName_ = "matrix-comprehension-singleton"} -LF: {"AnsweredRule":{"aRuleName_":"matrix-comprehension-singleton","qAscendants_":[1151872964749555522],"qHole_":3574995822047355118}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - { and([and([y_RelationAsMatrix[q33, q35] = conjure_aux1_RelationAsMatrix[q33, q35] | q35 : int(1..5)]) | q33 : int(1..5)]) - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - { sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = - sum([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) | q32_1 : int(1..5), q32_2 : int(1..5)]) - /\ - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - } - } - branching on [x, y] - such that - such that - true(x), - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: true(x) -Picking the only option: Answer 1: true-is-noop: Remove the argument from true. - true -storedChoice: -true(x) -1508832156878423928 -AnsweredRule {qHole_ = -1508832156878423928, qAscendants_ = fromList [], aRuleName_ = "true-is-noop"} -LF: {"AnsweredRule":{"aRuleName_":"true-is-noop","qAscendants_":[],"qHole_":-1508832156878423928}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - { and([and([y_RelationAsMatrix[q33, q35] = conjure_aux1_RelationAsMatrix[q33, q35] | q35 : int(1..5)]) | q33 : int(1..5)]) - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - { sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = - sum([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) | q32_1 : int(1..5), q32_2 : int(1..5)]) - /\ - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - } - } - branching on [x, y] - such that - such that - true, - true(y) - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -Picking the first option: Question 1: true(y) -Picking the only option: Answer 1: true-is-noop: Remove the argument from true. - true -storedChoice: -true(y) -1508550667338902379 -AnsweredRule {qHole_ = -1508550667338902379, qAscendants_ = fromList [], aRuleName_ = "true-is-noop"} -LF: {"AnsweredRule":{"aRuleName_":"true-is-noop","qAscendants_":[],"qHole_":-1508550667338902379}} END: -[loopy] language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - { and([and([y_RelationAsMatrix[q33, q35] = conjure_aux1_RelationAsMatrix[q33, q35] | q35 : int(1..5)]) | q33 : int(1..5)]) - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - { sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = - sum([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) | q32_1 : int(1..5), q32_2 : int(1..5)]) - /\ - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - } - } - branching on [x, y] - such that - such that - true, - true - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -[epilogue] - language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - { and([and([y_RelationAsMatrix[q33, q35] = conjure_aux1_RelationAsMatrix[q33, q35] | q35 : int(1..5)]) | q33 : int(1..5)]) - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - { sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = - sum([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) | q32_1 : int(1..5), q32_2 : int(1..5)]) - /\ - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - } - } - branching on [x, y] - such that - such that - true, - true - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -[dropTagForSR] - language Essence 1.3 - - letting p be permutation((3, 4)) - find x: relation (size 4) of (int(1..5) * int(1..5)) - find y: relation (size 4) of (int(1..5) * int(1..5)) - such that - { and([and([y_RelationAsMatrix[q33, q35] = conjure_aux1_RelationAsMatrix[q33, q35] | q35 : int(1..5)]) | q33 : int(1..5)]) - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - { sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = - sum([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) | q32_1 : int(1..5), q32_2 : int(1..5)]) - /\ - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - } - } - branching on [x, y] - such that - such that - true, - true - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -[updateDeclarations] - language Essence 1.3 - - find x_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - find y_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that - { and([and([y_RelationAsMatrix[q33, q35] = conjure_aux1_RelationAsMatrix[q33, q35] | q35 : int(1..5)]) | q33 : int(1..5)]) - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - { sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = - sum([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) | q32_1 : int(1..5), q32_2 : int(1..5)]) - /\ - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - } - } - branching on [x_RelationAsMatrix, y_RelationAsMatrix] - such that - such that - true, - true - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -[inlineDecVarLettings] - language Essence 1.3 - - find x_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - find y_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that - { and([and([y_RelationAsMatrix[q33, q35] = conjure_aux1_RelationAsMatrix[q33, q35] | q35 : int(1..5)]) | q33 : int(1..5)]) - @ find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - such that - { sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = - sum([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) | q32_1 : int(1..5), q32_2 : int(1..5)]) - /\ - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - { and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - }, - { and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - @ find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - } - } - } - branching on [x_RelationAsMatrix, y_RelationAsMatrix] - such that - such that - true, - true - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -[topLevelBubbles] - language Essence 1.3 - - find x_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - find y_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - such that and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - such that and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - such that - sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = - sum([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) | q32_1 : int(1..5), q32_2 : int(1..5)]) - /\ - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - such that and([and([y_RelationAsMatrix[q33, q35] = conjure_aux1_RelationAsMatrix[q33, q35] | q35 : int(1..5)]) | q33 : int(1..5)]) - branching on [x_RelationAsMatrix, y_RelationAsMatrix] - such that true - such that true - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -[checkIfAllRefined] - language Essence 1.3 - - find x_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - find y_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - such that and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - such that and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - such that - sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = - sum([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) | q32_1 : int(1..5), q32_2 : int(1..5)]) - /\ - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - such that and([and([y_RelationAsMatrix[q33, q35] = conjure_aux1_RelationAsMatrix[q33, q35] | q35 : int(1..5)]) | q33 : int(1..5)]) - branching on [x_RelationAsMatrix, y_RelationAsMatrix] - such that true - such that true - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -[checkIfHasUndefined] - language Essence 1.3 - - find x_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - find y_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - such that and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - such that and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - such that - sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = - sum([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) | q32_1 : int(1..5), q32_2 : int(1..5)]) - /\ - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - such that and([and([y_RelationAsMatrix[q33, q35] = conjure_aux1_RelationAsMatrix[q33, q35] | q35 : int(1..5)]) | q33 : int(1..5)]) - branching on [x_RelationAsMatrix, y_RelationAsMatrix] - such that true - such that true - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -[sliceThemMatrices] - language Essence 1.3 - - find x_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - find y_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - such that and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - such that and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - such that - sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = - sum([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) | q32_1 : int(1..5), q32_2 : int(1..5)]) - /\ - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - such that and([and([y_RelationAsMatrix[q33, q35] = conjure_aux1_RelationAsMatrix[q33, q35] | q35 : int(1..5)]) | q33 : int(1..5)]) - branching on [x_RelationAsMatrix, y_RelationAsMatrix] - such that true - such that true - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -[emptyMatrixLiterals] - language Essence 1.3 - - find x_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - find y_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - such that and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - such that and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - such that - sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = - sum([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) | q32_1 : int(1..5), q32_2 : int(1..5)]) - /\ - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - such that and([and([y_RelationAsMatrix[q33, q35] = conjure_aux1_RelationAsMatrix[q33, q35] | q35 : int(1..5)]) | q33 : int(1..5)]) - branching on [x_RelationAsMatrix, y_RelationAsMatrix] - such that true - such that true - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -[reverseTrails] - language Essence 1.3 - - find x_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - find y_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - such that 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]) - find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - such that and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - such that - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - such that and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]) - such that - sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = - sum([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) | q32_1 : int(1..5), q32_2 : int(1..5)]) - /\ - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]) - such that and([and([y_RelationAsMatrix[q33, q35] = conjure_aux1_RelationAsMatrix[q33, q35] | q35 : int(1..5)]) | q33 : int(1..5)]) - branching on [x_RelationAsMatrix, y_RelationAsMatrix] - such that true - such that true - such that 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]) - such that 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -[oneSuchThat] - language Essence 1.3 - - find x_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - find y_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - branching on [x_RelationAsMatrix, y_RelationAsMatrix] - such that - 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]), - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]), - and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]), - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]), - and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]), - sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = - sum([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) | q32_1 : int(1..5), q32_2 : int(1..5)]), - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]), - and([and([y_RelationAsMatrix[q33, q35] = conjure_aux1_RelationAsMatrix[q33, q35] | q35 : int(1..5)]) | q33 : int(1..5)]), - 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]), - 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - -[languageEprime] - language ESSENCE' 1.0 - - find x_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - find y_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - find conjure_aux1_RelationAsMatrix: matrix indexed by [int(1..5), int(1..5)] of bool - find conjure_aux2_1: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux2_2: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux3: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - find conjure_aux4: matrix indexed by [int(1..5), int(1..5)] of int(1..5) - branching on [x_RelationAsMatrix, y_RelationAsMatrix] - such that - 4 = sum([sum([toInt(conjure_aux1_RelationAsMatrix[q6, q7]) | q7 : int(1..5)]) | q6 : int(1..5)]), - and([(3 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 4) /\ (4 = q8_1 <-> conjure_aux3[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux3[q8_1, q8_2] \/ 4 = conjure_aux3[q8_1, q8_2]) <-> conjure_aux3[q8_1, q8_2] = q8_1) - | q8_1 : int(1..5), q8_2 : int(1..5)]), - and([conjure_aux2_1[q8_1, q8_2] = conjure_aux3[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]), - and([(3 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 4) /\ (4 = q8_2 <-> conjure_aux4[q8_1, q8_2] = 3) /\ - (!(3 = conjure_aux4[q8_1, q8_2] \/ 4 = conjure_aux4[q8_1, q8_2]) <-> conjure_aux4[q8_1, q8_2] = q8_2) - | q8_1 : int(1..5), q8_2 : int(1..5)]), - and([conjure_aux2_2[q8_1, q8_2] = conjure_aux4[q8_1, q8_2] | q8_1 : int(1..5), q8_2 : int(1..5)]), - sum([toInt(x_RelationAsMatrix[q30_1, q30_2]) | q30_1 : int(1..5), q30_2 : int(1..5)]) = - sum([toInt(conjure_aux1_RelationAsMatrix[q32_1, q32_2]) | q32_1 : int(1..5), q32_2 : int(1..5)]), - and([x_RelationAsMatrix[q8_1, q8_2] -> - or([conjure_aux1_RelationAsMatrix[q28_1, q28_2] /\ (q28_1 = conjure_aux2_1 /\ q28_2 = conjure_aux2_2) - | q28_1 : int(1..5), q28_2 : int(1..5)]) - | q8_1 : int(1..5), q8_2 : int(1..5)]), - and([and([y_RelationAsMatrix[q33, q35] = conjure_aux1_RelationAsMatrix[q33, q35] | q35 : int(1..5)]) | q33 : int(1..5)]), - 4 = sum([sum([toInt(x_RelationAsMatrix[q1, q2]) | q2 : int(1..5)]) | q1 : int(1..5)]), - 4 = sum([sum([toInt(y_RelationAsMatrix[q3, q4]) | q4 : int(1..5)]) | q3 : int(1..5)]) - diff --git a/tests/custom/deprecated_permutations_basic/0029_find_relations_x_y_such_that_y_image_x_under_p/permutation.essence b/tests/custom/deprecated_permutations_basic/0029_find_relations_x_y_such_that_y_image_x_under_p/permutation.essence deleted file mode 100644 index 25233ab564..0000000000 --- a/tests/custom/deprecated_permutations_basic/0029_find_relations_x_y_such_that_y_image_x_under_p/permutation.essence +++ /dev/null @@ -1,13 +0,0 @@ -letting MYTYPE be new type enum {THING1, THING2, THING3, THING4, THING5} - -letting p be permutation ((THING3,THING4)) - -find x : relation (size 4) of (MYTYPE*MYTYPE) - -find y : relation (size 4) of (MYTYPE*MYTYPE) - - -such that - y = image(p,x) -$ /\ y != x - diff --git a/tests/custom/deprecated_permutations_basic/0029_find_relations_x_y_such_that_y_image_x_under_p/run.sh b/tests/custom/deprecated_permutations_basic/0029_find_relations_x_y_such_that_y_image_x_under_p/run.sh deleted file mode 100755 index a440de2e64..0000000000 --- a/tests/custom/deprecated_permutations_basic/0029_find_relations_x_y_such_that_y_image_x_under_p/run.sh +++ /dev/null @@ -1,3 +0,0 @@ -conjure solve *.essence --number-of-solutions=20 -cat conjure-output/*.solution -rm -rf conjure-output *.solution diff --git a/tests/custom/deprecated_permutations_basic/0030_find_permutation_equal_given_permutation/permutation.essence b/tests/custom/deprecated_permutations_basic/0030_find_permutation_equal_given_permutation/permutation.essence deleted file mode 100644 index 15c38c1a52..0000000000 --- a/tests/custom/deprecated_permutations_basic/0030_find_permutation_equal_given_permutation/permutation.essence +++ /dev/null @@ -1,8 +0,0 @@ -letting n be 4 - -given p : permutation of int(1..n) - -find s : permutation of int(1..n) - -such that - p = s diff --git a/tests/custom/deprecated_permutations_basic/0030_find_permutation_equal_given_permutation/permutation.param b/tests/custom/deprecated_permutations_basic/0030_find_permutation_equal_given_permutation/permutation.param deleted file mode 100644 index 220d828501..0000000000 --- a/tests/custom/deprecated_permutations_basic/0030_find_permutation_equal_given_permutation/permutation.param +++ /dev/null @@ -1 +0,0 @@ -letting p be permutation((1,2)) diff --git a/tests/custom/deprecated_permutations_basic/0030_find_permutation_equal_given_permutation/run.sh b/tests/custom/deprecated_permutations_basic/0030_find_permutation_equal_given_permutation/run.sh deleted file mode 100755 index 98ec8c2243..0000000000 --- a/tests/custom/deprecated_permutations_basic/0030_find_permutation_equal_given_permutation/run.sh +++ /dev/null @@ -1,3 +0,0 @@ -conjure solve *.essence *.param --number-of-solutions=20 -cat conjure-output/*.solution -rm -rf conjure-output *.solution diff --git a/tests/custom/deprecated_permutations_basic/0031_find_matrix_lexless_indices_swapped_in_comprehension/permutation.essence b/tests/custom/deprecated_permutations_basic/0031_find_matrix_lexless_indices_swapped_in_comprehension/permutation.essence deleted file mode 100644 index ae70851ae4..0000000000 --- a/tests/custom/deprecated_permutations_basic/0031_find_matrix_lexless_indices_swapped_in_comprehension/permutation.essence +++ /dev/null @@ -1,5 +0,0 @@ -find m : matrix indexed by [int(1..9)] of set of int(1) - -such that - forAll i, j : int(1..9) . - i != j -> m <=lex [m[image(permutation((i,j)),k)] | k : int(1..9)] diff --git a/tests/custom/deprecated_permutations_basic/0031_find_matrix_lexless_indices_swapped_in_comprehension/permutation.param b/tests/custom/deprecated_permutations_basic/0031_find_matrix_lexless_indices_swapped_in_comprehension/permutation.param deleted file mode 100644 index 220d828501..0000000000 --- a/tests/custom/deprecated_permutations_basic/0031_find_matrix_lexless_indices_swapped_in_comprehension/permutation.param +++ /dev/null @@ -1 +0,0 @@ -letting p be permutation((1,2)) diff --git a/tests/custom/deprecated_permutations_basic/0031_find_matrix_lexless_indices_swapped_in_comprehension/run.sh b/tests/custom/deprecated_permutations_basic/0031_find_matrix_lexless_indices_swapped_in_comprehension/run.sh deleted file mode 100755 index a440de2e64..0000000000 --- a/tests/custom/deprecated_permutations_basic/0031_find_matrix_lexless_indices_swapped_in_comprehension/run.sh +++ /dev/null @@ -1,3 +0,0 @@ -conjure solve *.essence --number-of-solutions=20 -cat conjure-output/*.solution -rm -rf conjure-output *.solution diff --git a/tests/custom/deprecated_permutations_basic/0032_find_sets_of_ints_such_that_tuple_of_sets_lexless_any_int_swapped_tuple/permutation.essence b/tests/custom/deprecated_permutations_basic/0032_find_sets_of_ints_such_that_tuple_of_sets_lexless_any_int_swapped_tuple/permutation.essence deleted file mode 100644 index 3cef85e612..0000000000 --- a/tests/custom/deprecated_permutations_basic/0032_find_sets_of_ints_such_that_tuple_of_sets_lexless_any_int_swapped_tuple/permutation.essence +++ /dev/null @@ -1,9 +0,0 @@ -given n : int - -find x : set of int(1..n) - -find y : set of int(1..n) - -such that - forAll i, j : int(1..n) . - i != j -> (x,y) .<= image(permutation((i,j)), (x,y)) diff --git a/tests/custom/deprecated_permutations_basic/0032_find_sets_of_ints_such_that_tuple_of_sets_lexless_any_int_swapped_tuple/permutation.param b/tests/custom/deprecated_permutations_basic/0032_find_sets_of_ints_such_that_tuple_of_sets_lexless_any_int_swapped_tuple/permutation.param deleted file mode 100644 index 3c551dae32..0000000000 --- a/tests/custom/deprecated_permutations_basic/0032_find_sets_of_ints_such_that_tuple_of_sets_lexless_any_int_swapped_tuple/permutation.param +++ /dev/null @@ -1 +0,0 @@ -letting n be 3 diff --git a/tests/custom/deprecated_permutations_basic/0032_find_sets_of_ints_such_that_tuple_of_sets_lexless_any_int_swapped_tuple/run.sh b/tests/custom/deprecated_permutations_basic/0032_find_sets_of_ints_such_that_tuple_of_sets_lexless_any_int_swapped_tuple/run.sh deleted file mode 100755 index 98ec8c2243..0000000000 --- a/tests/custom/deprecated_permutations_basic/0032_find_sets_of_ints_such_that_tuple_of_sets_lexless_any_int_swapped_tuple/run.sh +++ /dev/null @@ -1,3 +0,0 @@ -conjure solve *.essence *.param --number-of-solutions=20 -cat conjure-output/*.solution -rm -rf conjure-output *.solution diff --git a/tests/custom/deprecated_permutations_basic/0033_find_matrixes_of_enum_such_that_tuple_of_matrices_lexless_any_int_swapped_tuple/permutation.essence b/tests/custom/deprecated_permutations_basic/0033_find_matrixes_of_enum_such_that_tuple_of_matrices_lexless_any_int_swapped_tuple/permutation.essence deleted file mode 100644 index e47950062d..0000000000 --- a/tests/custom/deprecated_permutations_basic/0033_find_matrixes_of_enum_such_that_tuple_of_matrices_lexless_any_int_swapped_tuple/permutation.essence +++ /dev/null @@ -1,11 +0,0 @@ -given n : int - -letting MYTYPE be new type enum {THING1, THING2} - -find x : matrix indexed by [int(1..n)] of MYTYPE - -find y : matrix indexed by [int(1..n)] of MYTYPE - -such that - forAll i, j : int(1..n) . - i != j -> tuple(x,y) .<= image(permutation((i,j)),tuple(x,y)) diff --git a/tests/custom/deprecated_permutations_basic/0033_find_matrixes_of_enum_such_that_tuple_of_matrices_lexless_any_int_swapped_tuple/permutation.param b/tests/custom/deprecated_permutations_basic/0033_find_matrixes_of_enum_such_that_tuple_of_matrices_lexless_any_int_swapped_tuple/permutation.param deleted file mode 100644 index 05cd66931a..0000000000 --- a/tests/custom/deprecated_permutations_basic/0033_find_matrixes_of_enum_such_that_tuple_of_matrices_lexless_any_int_swapped_tuple/permutation.param +++ /dev/null @@ -1 +0,0 @@ -letting n be 5 diff --git a/tests/custom/deprecated_permutations_basic/0033_find_matrixes_of_enum_such_that_tuple_of_matrices_lexless_any_int_swapped_tuple/run.sh b/tests/custom/deprecated_permutations_basic/0033_find_matrixes_of_enum_such_that_tuple_of_matrices_lexless_any_int_swapped_tuple/run.sh deleted file mode 100755 index 1f1c63f942..0000000000 --- a/tests/custom/deprecated_permutations_basic/0033_find_matrixes_of_enum_such_that_tuple_of_matrices_lexless_any_int_swapped_tuple/run.sh +++ /dev/null @@ -1,3 +0,0 @@ -conjure solve *.essence *.param --number-of-solutions=60 -cat conjure-output/*.solution -rm -rf conjure-output *.solution diff --git a/tests/custom/deprecated_permutations_basic/0033_find_matrixes_of_enum_such_that_tuple_of_matrices_lexless_any_int_swapped_tuple/stdout.expected b/tests/custom/deprecated_permutations_basic/0033_find_matrixes_of_enum_such_that_tuple_of_matrices_lexless_any_int_swapped_tuple/stdout.expected deleted file mode 100644 index 6f8d4866b7..0000000000 --- a/tests/custom/deprecated_permutations_basic/0033_find_matrixes_of_enum_such_that_tuple_of_matrices_lexless_any_int_swapped_tuple/stdout.expected +++ /dev/null @@ -1,284 +0,0 @@ -Generating models for permutation.essence -Generated models: model000001.eprime -Saved under: conjure-output -Savile Row: model000001.eprime permutation.param -Copying solution to: permutation-permutation-000001.solution -Copying solution to: permutation-permutation-000002.solution -Copying solution to: permutation-permutation-000003.solution -Copying solution to: permutation-permutation-000004.solution -Copying solution to: permutation-permutation-000005.solution -Copying solution to: permutation-permutation-000006.solution -Copying solution to: permutation-permutation-000007.solution -Copying solution to: permutation-permutation-000008.solution -Copying solution to: permutation-permutation-000009.solution -Copying solution to: permutation-permutation-000010.solution -Copying solution to: permutation-permutation-000011.solution -Copying solution to: permutation-permutation-000012.solution -Copying solution to: permutation-permutation-000013.solution -Copying solution to: permutation-permutation-000014.solution -Copying solution to: permutation-permutation-000015.solution -Copying solution to: permutation-permutation-000016.solution -Copying solution to: permutation-permutation-000017.solution -Copying solution to: permutation-permutation-000018.solution -Copying solution to: permutation-permutation-000019.solution -Copying solution to: permutation-permutation-000020.solution -Copying solution to: permutation-permutation-000021.solution -Copying solution to: permutation-permutation-000022.solution -Copying solution to: permutation-permutation-000023.solution -Copying solution to: permutation-permutation-000024.solution -Copying solution to: permutation-permutation-000025.solution -Copying solution to: permutation-permutation-000026.solution -Copying solution to: permutation-permutation-000027.solution -Copying solution to: permutation-permutation-000028.solution -Copying solution to: permutation-permutation-000029.solution -Copying solution to: permutation-permutation-000030.solution -Copying solution to: permutation-permutation-000031.solution -Copying solution to: permutation-permutation-000032.solution -Copying solution to: permutation-permutation-000033.solution -Copying solution to: permutation-permutation-000034.solution -Copying solution to: permutation-permutation-000035.solution -Copying solution to: permutation-permutation-000036.solution -Copying solution to: permutation-permutation-000037.solution -Copying solution to: permutation-permutation-000038.solution -Copying solution to: permutation-permutation-000039.solution -Copying solution to: permutation-permutation-000040.solution -Copying solution to: permutation-permutation-000041.solution -Copying solution to: permutation-permutation-000042.solution -Copying solution to: permutation-permutation-000043.solution -Copying solution to: permutation-permutation-000044.solution -Copying solution to: permutation-permutation-000045.solution -Copying solution to: permutation-permutation-000046.solution -Copying solution to: permutation-permutation-000047.solution -Copying solution to: permutation-permutation-000048.solution -Copying solution to: permutation-permutation-000049.solution -Copying solution to: permutation-permutation-000050.solution -Copying solution to: permutation-permutation-000051.solution -Copying solution to: permutation-permutation-000052.solution -Copying solution to: permutation-permutation-000053.solution -Copying solution to: permutation-permutation-000054.solution -Copying solution to: permutation-permutation-000055.solution -Copying solution to: permutation-permutation-000056.solution -language Essence 1.3 - -letting x be [THING1, THING1, THING1, THING1, THING1; int(1..5)] -letting y be [THING1, THING1, THING1, THING1, THING1; int(1..5)] -language Essence 1.3 - -letting x be [THING1, THING1, THING1, THING1, THING1; int(1..5)] -letting y be [THING1, THING1, THING1, THING1, THING2; int(1..5)] -language Essence 1.3 - -letting x be [THING1, THING1, THING1, THING1, THING1; int(1..5)] -letting y be [THING1, THING1, THING1, THING2, THING2; int(1..5)] -language Essence 1.3 - -letting x be [THING1, THING1, THING1, THING1, THING1; int(1..5)] -letting y be [THING1, THING1, THING2, THING2, THING2; int(1..5)] -language Essence 1.3 - -letting x be [THING1, THING1, THING1, THING1, THING1; int(1..5)] -letting y be [THING1, THING2, THING2, THING2, THING2; int(1..5)] -language Essence 1.3 - -letting x be [THING1, THING1, THING1, THING1, THING1; int(1..5)] -letting y be [THING2, THING2, THING2, THING2, THING2; int(1..5)] -language Essence 1.3 - -letting x be [THING1, THING1, THING1, THING1, THING2; int(1..5)] -letting y be [THING1, THING1, THING1, THING1, THING1; int(1..5)] -language Essence 1.3 - -letting x be [THING1, THING1, THING1, THING1, THING2; int(1..5)] -letting y be [THING1, THING1, THING1, THING1, THING2; int(1..5)] -language Essence 1.3 - -letting x be [THING1, THING1, THING1, THING1, THING2; int(1..5)] -letting y be [THING1, THING1, THING1, THING2, THING1; int(1..5)] -language Essence 1.3 - -letting x be [THING1, THING1, THING1, THING1, THING2; int(1..5)] -letting y be [THING1, THING1, THING1, THING2, THING2; int(1..5)] -language Essence 1.3 - -letting x be [THING1, THING1, THING1, THING1, THING2; int(1..5)] -letting y be [THING1, THING1, THING2, THING2, THING1; int(1..5)] -language Essence 1.3 - -letting x be [THING1, THING1, THING1, THING1, THING2; int(1..5)] -letting y be [THING1, THING1, THING2, THING2, THING2; int(1..5)] -language Essence 1.3 - -letting x be [THING1, THING1, THING1, THING1, THING2; int(1..5)] -letting y be [THING1, THING2, THING2, THING2, THING1; int(1..5)] -language Essence 1.3 - -letting x be [THING1, THING1, THING1, THING1, THING2; int(1..5)] -letting y be [THING1, THING2, THING2, THING2, THING2; int(1..5)] -language Essence 1.3 - -letting x be [THING1, THING1, THING1, THING1, THING2; int(1..5)] -letting y be [THING2, THING2, THING2, THING2, THING1; int(1..5)] -language Essence 1.3 - -letting x be [THING1, THING1, THING1, THING1, THING2; int(1..5)] -letting y be [THING2, THING2, THING2, THING2, THING2; int(1..5)] -language Essence 1.3 - -letting x be [THING1, THING1, THING1, THING2, THING2; int(1..5)] -letting y be [THING1, THING1, THING1, THING1, THING1; int(1..5)] -language Essence 1.3 - -letting x be [THING1, THING1, THING1, THING2, THING2; int(1..5)] -letting y be [THING1, THING1, THING1, THING1, THING2; int(1..5)] -language Essence 1.3 - -letting x be [THING1, THING1, THING1, THING2, THING2; int(1..5)] -letting y be [THING1, THING1, THING1, THING2, THING2; int(1..5)] -language Essence 1.3 - -letting x be [THING1, THING1, THING1, THING2, THING2; int(1..5)] -letting y be [THING1, THING1, THING2, THING1, THING1; int(1..5)] -language Essence 1.3 - -letting x be [THING1, THING1, THING1, THING2, THING2; int(1..5)] -letting y be [THING1, THING1, THING2, THING1, THING2; int(1..5)] -language Essence 1.3 - -letting x be [THING1, THING1, THING1, THING2, THING2; int(1..5)] -letting y be [THING1, THING1, THING2, THING2, THING2; int(1..5)] -language Essence 1.3 - -letting x be [THING1, THING1, THING1, THING2, THING2; int(1..5)] -letting y be [THING1, THING2, THING2, THING1, THING1; int(1..5)] -language Essence 1.3 - -letting x be [THING1, THING1, THING1, THING2, THING2; int(1..5)] -letting y be [THING1, THING2, THING2, THING1, THING2; int(1..5)] -language Essence 1.3 - -letting x be [THING1, THING1, THING1, THING2, THING2; int(1..5)] -letting y be [THING1, THING2, THING2, THING2, THING2; int(1..5)] -language Essence 1.3 - -letting x be [THING1, THING1, THING1, THING2, THING2; int(1..5)] -letting y be [THING2, THING2, THING2, THING1, THING1; int(1..5)] -language Essence 1.3 - -letting x be [THING1, THING1, THING1, THING2, THING2; int(1..5)] -letting y be [THING2, THING2, THING2, THING1, THING2; int(1..5)] -language Essence 1.3 - -letting x be [THING1, THING1, THING1, THING2, THING2; int(1..5)] -letting y be [THING2, THING2, THING2, THING2, THING2; int(1..5)] -language Essence 1.3 - -letting x be [THING1, THING1, THING2, THING2, THING2; int(1..5)] -letting y be [THING1, THING1, THING1, THING1, THING1; int(1..5)] -language Essence 1.3 - -letting x be [THING1, THING1, THING2, THING2, THING2; int(1..5)] -letting y be [THING1, THING1, THING1, THING1, THING2; int(1..5)] -language Essence 1.3 - -letting x be [THING1, THING1, THING2, THING2, THING2; int(1..5)] -letting y be [THING1, THING1, THING1, THING2, THING2; int(1..5)] -language Essence 1.3 - -letting x be [THING1, THING1, THING2, THING2, THING2; int(1..5)] -letting y be [THING1, THING1, THING2, THING2, THING2; int(1..5)] -language Essence 1.3 - -letting x be [THING1, THING1, THING2, THING2, THING2; int(1..5)] -letting y be [THING1, THING2, THING1, THING1, THING1; int(1..5)] -language Essence 1.3 - -letting x be [THING1, THING1, THING2, THING2, THING2; int(1..5)] -letting y be [THING1, THING2, THING1, THING1, THING2; int(1..5)] -language Essence 1.3 - -letting x be [THING1, THING1, THING2, THING2, THING2; int(1..5)] -letting y be [THING1, THING2, THING1, THING2, THING2; int(1..5)] -language Essence 1.3 - -letting x be [THING1, THING1, THING2, THING2, THING2; int(1..5)] -letting y be [THING1, THING2, THING2, THING2, THING2; int(1..5)] -language Essence 1.3 - -letting x be [THING1, THING1, THING2, THING2, THING2; int(1..5)] -letting y be [THING2, THING2, THING1, THING1, THING1; int(1..5)] -language Essence 1.3 - -letting x be [THING1, THING1, THING2, THING2, THING2; int(1..5)] -letting y be [THING2, THING2, THING1, THING1, THING2; int(1..5)] -language Essence 1.3 - -letting x be [THING1, THING1, THING2, THING2, THING2; int(1..5)] -letting y be [THING2, THING2, THING1, THING2, THING2; int(1..5)] -language Essence 1.3 - -letting x be [THING1, THING1, THING2, THING2, THING2; int(1..5)] -letting y be [THING2, THING2, THING2, THING2, THING2; int(1..5)] -language Essence 1.3 - -letting x be [THING1, THING2, THING2, THING2, THING2; int(1..5)] -letting y be [THING1, THING1, THING1, THING1, THING1; int(1..5)] -language Essence 1.3 - -letting x be [THING1, THING2, THING2, THING2, THING2; int(1..5)] -letting y be [THING1, THING1, THING1, THING1, THING2; int(1..5)] -language Essence 1.3 - -letting x be [THING1, THING2, THING2, THING2, THING2; int(1..5)] -letting y be [THING1, THING1, THING1, THING2, THING2; int(1..5)] -language Essence 1.3 - -letting x be [THING1, THING2, THING2, THING2, THING2; int(1..5)] -letting y be [THING1, THING1, THING2, THING2, THING2; int(1..5)] -language Essence 1.3 - -letting x be [THING1, THING2, THING2, THING2, THING2; int(1..5)] -letting y be [THING1, THING2, THING2, THING2, THING2; int(1..5)] -language Essence 1.3 - -letting x be [THING1, THING2, THING2, THING2, THING2; int(1..5)] -letting y be [THING2, THING1, THING1, THING1, THING1; int(1..5)] -language Essence 1.3 - -letting x be [THING1, THING2, THING2, THING2, THING2; int(1..5)] -letting y be [THING2, THING1, THING1, THING1, THING2; int(1..5)] -language Essence 1.3 - -letting x be [THING1, THING2, THING2, THING2, THING2; int(1..5)] -letting y be [THING2, THING1, THING1, THING2, THING2; int(1..5)] -language Essence 1.3 - -letting x be [THING1, THING2, THING2, THING2, THING2; int(1..5)] -letting y be [THING2, THING1, THING2, THING2, THING2; int(1..5)] -language Essence 1.3 - -letting x be [THING1, THING2, THING2, THING2, THING2; int(1..5)] -letting y be [THING2, THING2, THING2, THING2, THING2; int(1..5)] -language Essence 1.3 - -letting x be [THING2, THING2, THING2, THING2, THING2; int(1..5)] -letting y be [THING1, THING1, THING1, THING1, THING1; int(1..5)] -language Essence 1.3 - -letting x be [THING2, THING2, THING2, THING2, THING2; int(1..5)] -letting y be [THING1, THING1, THING1, THING1, THING2; int(1..5)] -language Essence 1.3 - -letting x be [THING2, THING2, THING2, THING2, THING2; int(1..5)] -letting y be [THING1, THING1, THING1, THING2, THING2; int(1..5)] -language Essence 1.3 - -letting x be [THING2, THING2, THING2, THING2, THING2; int(1..5)] -letting y be [THING1, THING1, THING2, THING2, THING2; int(1..5)] -language Essence 1.3 - -letting x be [THING2, THING2, THING2, THING2, THING2; int(1..5)] -letting y be [THING1, THING2, THING2, THING2, THING2; int(1..5)] -language Essence 1.3 - -letting x be [THING2, THING2, THING2, THING2, THING2; int(1..5)] -letting y be [THING2, THING2, THING2, THING2, THING2; int(1..5)] diff --git a/tests/custom/deprecated_permutations_basic/0034_image_of_empty_permutation/permutation.essence b/tests/custom/deprecated_permutations_basic/0034_image_of_empty_permutation/permutation.essence deleted file mode 100644 index c9d1fe6895..0000000000 --- a/tests/custom/deprecated_permutations_basic/0034_image_of_empty_permutation/permutation.essence +++ /dev/null @@ -1,6 +0,0 @@ -given n : int - -find j : int(0..100) - -such that - n = image(permutation(()),j) diff --git a/tests/custom/deprecated_permutations_basic/0034_image_of_empty_permutation/permutation.param b/tests/custom/deprecated_permutations_basic/0034_image_of_empty_permutation/permutation.param deleted file mode 100644 index 05cd66931a..0000000000 --- a/tests/custom/deprecated_permutations_basic/0034_image_of_empty_permutation/permutation.param +++ /dev/null @@ -1 +0,0 @@ -letting n be 5 diff --git a/tests/custom/deprecated_permutations_basic/0034_image_of_empty_permutation/run.sh b/tests/custom/deprecated_permutations_basic/0034_image_of_empty_permutation/run.sh deleted file mode 100755 index 1f1c63f942..0000000000 --- a/tests/custom/deprecated_permutations_basic/0034_image_of_empty_permutation/run.sh +++ /dev/null @@ -1,3 +0,0 @@ -conjure solve *.essence *.param --number-of-solutions=60 -cat conjure-output/*.solution -rm -rf conjure-output *.solution diff --git a/tests/custom/deprecated_permutations_basic/0035_permutation_of_enum_is_identity_for_integers/permutation.essence b/tests/custom/deprecated_permutations_basic/0035_permutation_of_enum_is_identity_for_integers/permutation.essence deleted file mode 100644 index feff622574..0000000000 --- a/tests/custom/deprecated_permutations_basic/0035_permutation_of_enum_is_identity_for_integers/permutation.essence +++ /dev/null @@ -1,10 +0,0 @@ -letting e be new type enum {E1, E2, E3, E4} - -find s : permutation of e - -such that - image(s, E1)= E2, - forAll i : int(-10..10) . - image(s, i) = i - - diff --git a/tests/custom/deprecated_permutations_basic/0035_permutation_of_enum_is_identity_for_integers/permutation.param b/tests/custom/deprecated_permutations_basic/0035_permutation_of_enum_is_identity_for_integers/permutation.param deleted file mode 100644 index 05cd66931a..0000000000 --- a/tests/custom/deprecated_permutations_basic/0035_permutation_of_enum_is_identity_for_integers/permutation.param +++ /dev/null @@ -1 +0,0 @@ -letting n be 5 diff --git a/tests/custom/deprecated_permutations_basic/0035_permutation_of_enum_is_identity_for_integers/stdout.expected b/tests/custom/deprecated_permutations_basic/0035_permutation_of_enum_is_identity_for_integers/stdout.expected deleted file mode 100644 index 22c4c0a298..0000000000 --- a/tests/custom/deprecated_permutations_basic/0035_permutation_of_enum_is_identity_for_integers/stdout.expected +++ /dev/null @@ -1,28 +0,0 @@ -Generating models for permutation.essence -Generated models: model000001.eprime -Saved under: conjure-output -Savile Row: model000001.eprime -Copying solution to: permutation-000001.solution -Copying solution to: permutation-000002.solution -Copying solution to: permutation-000003.solution -Copying solution to: permutation-000004.solution -Copying solution to: permutation-000005.solution -Copying solution to: permutation-000006.solution -language Essence 1.3 - -letting s be permutation((E1, E2)) -language Essence 1.3 - -letting s be permutation((E1, E2), (E3, E4)) -language Essence 1.3 - -letting s be permutation((E1, E2, E3)) -language Essence 1.3 - -letting s be permutation((E1, E2, E3, E4)) -language Essence 1.3 - -letting s be permutation((E1, E2, E4, E3)) -language Essence 1.3 - -letting s be permutation((E1, E2, E4)) diff --git a/tests/custom/deprecated_permutations_basic/0036_big_test_of_enums_in_matrices/permutation.essence b/tests/custom/deprecated_permutations_basic/0036_big_test_of_enums_in_matrices/permutation.essence deleted file mode 100644 index db47699eb5..0000000000 --- a/tests/custom/deprecated_permutations_basic/0036_big_test_of_enums_in_matrices/permutation.essence +++ /dev/null @@ -1,19 +0,0 @@ -letting e be new type enum {E1, E2, E3, E4} - -find s,t: permutation of e -find m1 : matrix indexed by [e] of int(1..4) -find m2 : matrix indexed by [e] of int(1..4) -find n1 : matrix indexed by [int(1..2)] of e -find n2 : matrix indexed by [int(1..2)] of e -find x1 : matrix indexed by [e] of e -find x2 : matrix indexed by [e] of e - -such that - image(s, m1) = m2 - , image(s, n1) = n2 - , image(s, x1) = x2 - , forAll i : e . - image(s, i) != i - , allDiff(m1), allDiff(n1), allDiff(x1) - , x1[E1]=E3 - diff --git a/tests/custom/deprecated_permutations_basic/0036_big_test_of_enums_in_matrices/stdout.expected b/tests/custom/deprecated_permutations_basic/0036_big_test_of_enums_in_matrices/stdout.expected deleted file mode 100644 index fe2f448795..0000000000 --- a/tests/custom/deprecated_permutations_basic/0036_big_test_of_enums_in_matrices/stdout.expected +++ /dev/null @@ -1,114 +0,0 @@ -Generating models for permutation.essence -Generated models: model000001.eprime -Saved under: conjure-output -Savile Row: model000001.eprime -Copying solution to: permutation-000001.solution -Copying solution to: permutation-000002.solution -Copying solution to: permutation-000003.solution -Copying solution to: permutation-000004.solution -Copying solution to: permutation-000005.solution -Copying solution to: permutation-000006.solution -Copying solution to: permutation-000007.solution -Copying solution to: permutation-000008.solution -Copying solution to: permutation-000009.solution -Copying solution to: permutation-000010.solution -language Essence 1.3 - -letting m1 be [1, 2, 3, 4; int(1..4)] -letting m2 be [2, 1, 4, 3; int(1..4)] -letting n1 be [E1, E2; int(1..2)] -letting n2 be [E2, E1; int(1..2)] -letting s be permutation((E1, E2), (E3, E4)) -letting t be permutation() -letting x1 be [E3, E1, E2, E4; int(1..4)] -letting x2 be [E2, E4, E3, E1; int(1..4)] -language Essence 1.3 - -letting m1 be [1, 2, 3, 4; int(1..4)] -letting m2 be [2, 1, 4, 3; int(1..4)] -letting n1 be [E1, E2; int(1..2)] -letting n2 be [E2, E1; int(1..2)] -letting s be permutation((E1, E2), (E3, E4)) -letting t be permutation() -letting x1 be [E3, E1, E4, E2; int(1..4)] -letting x2 be [E2, E4, E1, E3; int(1..4)] -language Essence 1.3 - -letting m1 be [1, 2, 3, 4; int(1..4)] -letting m2 be [2, 1, 4, 3; int(1..4)] -letting n1 be [E1, E2; int(1..2)] -letting n2 be [E2, E1; int(1..2)] -letting s be permutation((E1, E2), (E3, E4)) -letting t be permutation() -letting x1 be [E3, E2, E1, E4; int(1..4)] -letting x2 be [E1, E4, E3, E2; int(1..4)] -language Essence 1.3 - -letting m1 be [1, 2, 3, 4; int(1..4)] -letting m2 be [2, 1, 4, 3; int(1..4)] -letting n1 be [E1, E2; int(1..2)] -letting n2 be [E2, E1; int(1..2)] -letting s be permutation((E1, E2), (E3, E4)) -letting t be permutation() -letting x1 be [E3, E2, E4, E1; int(1..4)] -letting x2 be [E1, E4, E2, E3; int(1..4)] -language Essence 1.3 - -letting m1 be [1, 2, 3, 4; int(1..4)] -letting m2 be [2, 1, 4, 3; int(1..4)] -letting n1 be [E1, E2; int(1..2)] -letting n2 be [E2, E1; int(1..2)] -letting s be permutation((E1, E2), (E3, E4)) -letting t be permutation() -letting x1 be [E3, E4, E1, E2; int(1..4)] -letting x2 be [E3, E4, E1, E2; int(1..4)] -language Essence 1.3 - -letting m1 be [1, 2, 3, 4; int(1..4)] -letting m2 be [2, 1, 4, 3; int(1..4)] -letting n1 be [E1, E2; int(1..2)] -letting n2 be [E2, E1; int(1..2)] -letting s be permutation((E1, E2), (E3, E4)) -letting t be permutation() -letting x1 be [E3, E4, E2, E1; int(1..4)] -letting x2 be [E3, E4, E2, E1; int(1..4)] -language Essence 1.3 - -letting m1 be [1, 2, 3, 4; int(1..4)] -letting m2 be [2, 1, 4, 3; int(1..4)] -letting n1 be [E1, E3; int(1..2)] -letting n2 be [E2, E4; int(1..2)] -letting s be permutation((E1, E2), (E3, E4)) -letting t be permutation() -letting x1 be [E3, E1, E2, E4; int(1..4)] -letting x2 be [E2, E4, E3, E1; int(1..4)] -language Essence 1.3 - -letting m1 be [1, 2, 3, 4; int(1..4)] -letting m2 be [2, 1, 4, 3; int(1..4)] -letting n1 be [E1, E3; int(1..2)] -letting n2 be [E2, E4; int(1..2)] -letting s be permutation((E1, E2), (E3, E4)) -letting t be permutation() -letting x1 be [E3, E1, E4, E2; int(1..4)] -letting x2 be [E2, E4, E1, E3; int(1..4)] -language Essence 1.3 - -letting m1 be [1, 2, 3, 4; int(1..4)] -letting m2 be [2, 1, 4, 3; int(1..4)] -letting n1 be [E1, E3; int(1..2)] -letting n2 be [E2, E4; int(1..2)] -letting s be permutation((E1, E2), (E3, E4)) -letting t be permutation() -letting x1 be [E3, E2, E1, E4; int(1..4)] -letting x2 be [E1, E4, E3, E2; int(1..4)] -language Essence 1.3 - -letting m1 be [1, 2, 3, 4; int(1..4)] -letting m2 be [2, 1, 4, 3; int(1..4)] -letting n1 be [E1, E3; int(1..2)] -letting n2 be [E2, E4; int(1..2)] -letting s be permutation((E1, E2), (E3, E4)) -letting t be permutation() -letting x1 be [E3, E2, E4, E1; int(1..4)] -letting x2 be [E1, E4, E2, E3; int(1..4)] diff --git a/tests/custom/deprecated_permutations_basic/0037_matrices_of_enums_indexed_by_enums/permutation.essence b/tests/custom/deprecated_permutations_basic/0037_matrices_of_enums_indexed_by_enums/permutation.essence deleted file mode 100644 index 0620281665..0000000000 --- a/tests/custom/deprecated_permutations_basic/0037_matrices_of_enums_indexed_by_enums/permutation.essence +++ /dev/null @@ -1,12 +0,0 @@ -letting e be new type enum {E1, E2, E3, E4} - -find s: permutation of e -find x1 : matrix indexed by [e] of e -find x2 : matrix indexed by [e] of e - -such that - forAll i : e . - image(s,i) != i - , image(s, x1) = x2 - , x1 != x2 - diff --git a/tests/custom/deprecated_permutations_basic/0037_matrices_of_enums_indexed_by_enums/stdout.expected b/tests/custom/deprecated_permutations_basic/0037_matrices_of_enums_indexed_by_enums/stdout.expected deleted file mode 100644 index e9a6a9a1e9..0000000000 --- a/tests/custom/deprecated_permutations_basic/0037_matrices_of_enums_indexed_by_enums/stdout.expected +++ /dev/null @@ -1,64 +0,0 @@ -Generating models for permutation.essence -Generated models: model000001.eprime -Saved under: conjure-output -Savile Row: model000001.eprime -Copying solution to: permutation-000001.solution -Copying solution to: permutation-000002.solution -Copying solution to: permutation-000003.solution -Copying solution to: permutation-000004.solution -Copying solution to: permutation-000005.solution -Copying solution to: permutation-000006.solution -Copying solution to: permutation-000007.solution -Copying solution to: permutation-000008.solution -Copying solution to: permutation-000009.solution -Copying solution to: permutation-000010.solution -language Essence 1.3 - -letting s be permutation((E1, E2), (E3, E4)) -letting x1 be [E1, E1, E1, E1; int(1..4)] -letting x2 be [E2, E2, E2, E2; int(1..4)] -language Essence 1.3 - -letting s be permutation((E1, E2), (E3, E4)) -letting x1 be [E1, E1, E1, E2; int(1..4)] -letting x2 be [E2, E2, E1, E2; int(1..4)] -language Essence 1.3 - -letting s be permutation((E1, E2), (E3, E4)) -letting x1 be [E1, E1, E1, E3; int(1..4)] -letting x2 be [E2, E2, E4, E2; int(1..4)] -language Essence 1.3 - -letting s be permutation((E1, E2), (E3, E4)) -letting x1 be [E1, E1, E1, E4; int(1..4)] -letting x2 be [E2, E2, E3, E2; int(1..4)] -language Essence 1.3 - -letting s be permutation((E1, E2), (E3, E4)) -letting x1 be [E1, E1, E2, E1; int(1..4)] -letting x2 be [E2, E2, E2, E1; int(1..4)] -language Essence 1.3 - -letting s be permutation((E1, E2), (E3, E4)) -letting x1 be [E1, E1, E2, E2; int(1..4)] -letting x2 be [E2, E2, E1, E1; int(1..4)] -language Essence 1.3 - -letting s be permutation((E1, E2), (E3, E4)) -letting x1 be [E1, E1, E2, E3; int(1..4)] -letting x2 be [E2, E2, E4, E1; int(1..4)] -language Essence 1.3 - -letting s be permutation((E1, E2), (E3, E4)) -letting x1 be [E1, E1, E2, E4; int(1..4)] -letting x2 be [E2, E2, E3, E1; int(1..4)] -language Essence 1.3 - -letting s be permutation((E1, E2), (E3, E4)) -letting x1 be [E1, E1, E3, E1; int(1..4)] -letting x2 be [E2, E2, E2, E4; int(1..4)] -language Essence 1.3 - -letting s be permutation((E1, E2), (E3, E4)) -letting x1 be [E1, E1, E3, E2; int(1..4)] -letting x2 be [E2, E2, E1, E4; int(1..4)] diff --git a/tests/custom/deprecated_permutations_basic/0038_matricies_of_tuples_of_enums_indexed_by_enums/permutation.essence b/tests/custom/deprecated_permutations_basic/0038_matricies_of_tuples_of_enums_indexed_by_enums/permutation.essence deleted file mode 100644 index 63626dab1d..0000000000 --- a/tests/custom/deprecated_permutations_basic/0038_matricies_of_tuples_of_enums_indexed_by_enums/permutation.essence +++ /dev/null @@ -1,11 +0,0 @@ -letting e be new type enum {E1, E2, E3, E4} - -find s: permutation of e -find x1 : matrix indexed by [e] of (e,e) -find x2 : matrix indexed by [e] of (e,e) - -such that - forAll i : e . - image(s,i) != i - , image(s, x1) = x2 - , x1 != x2 diff --git a/tests/custom/deprecated_permutations_basic/0038_matricies_of_tuples_of_enums_indexed_by_enums/run.sh b/tests/custom/deprecated_permutations_basic/0038_matricies_of_tuples_of_enums_indexed_by_enums/run.sh deleted file mode 100755 index 3c60e3f90e..0000000000 --- a/tests/custom/deprecated_permutations_basic/0038_matricies_of_tuples_of_enums_indexed_by_enums/run.sh +++ /dev/null @@ -1,3 +0,0 @@ -conjure solve *.essence --number-of-solutions=10 -cat conjure-output/*.solution -rm -rf conjure-output *.solution diff --git a/tests/custom/deprecated_permutations_basic/0038_matricies_of_tuples_of_enums_indexed_by_enums/stdout.expected b/tests/custom/deprecated_permutations_basic/0038_matricies_of_tuples_of_enums_indexed_by_enums/stdout.expected deleted file mode 100644 index e9a6a9a1e9..0000000000 --- a/tests/custom/deprecated_permutations_basic/0038_matricies_of_tuples_of_enums_indexed_by_enums/stdout.expected +++ /dev/null @@ -1,64 +0,0 @@ -Generating models for permutation.essence -Generated models: model000001.eprime -Saved under: conjure-output -Savile Row: model000001.eprime -Copying solution to: permutation-000001.solution -Copying solution to: permutation-000002.solution -Copying solution to: permutation-000003.solution -Copying solution to: permutation-000004.solution -Copying solution to: permutation-000005.solution -Copying solution to: permutation-000006.solution -Copying solution to: permutation-000007.solution -Copying solution to: permutation-000008.solution -Copying solution to: permutation-000009.solution -Copying solution to: permutation-000010.solution -language Essence 1.3 - -letting s be permutation((E1, E2), (E3, E4)) -letting x1 be [E1, E1, E1, E1; int(1..4)] -letting x2 be [E2, E2, E2, E2; int(1..4)] -language Essence 1.3 - -letting s be permutation((E1, E2), (E3, E4)) -letting x1 be [E1, E1, E1, E2; int(1..4)] -letting x2 be [E2, E2, E1, E2; int(1..4)] -language Essence 1.3 - -letting s be permutation((E1, E2), (E3, E4)) -letting x1 be [E1, E1, E1, E3; int(1..4)] -letting x2 be [E2, E2, E4, E2; int(1..4)] -language Essence 1.3 - -letting s be permutation((E1, E2), (E3, E4)) -letting x1 be [E1, E1, E1, E4; int(1..4)] -letting x2 be [E2, E2, E3, E2; int(1..4)] -language Essence 1.3 - -letting s be permutation((E1, E2), (E3, E4)) -letting x1 be [E1, E1, E2, E1; int(1..4)] -letting x2 be [E2, E2, E2, E1; int(1..4)] -language Essence 1.3 - -letting s be permutation((E1, E2), (E3, E4)) -letting x1 be [E1, E1, E2, E2; int(1..4)] -letting x2 be [E2, E2, E1, E1; int(1..4)] -language Essence 1.3 - -letting s be permutation((E1, E2), (E3, E4)) -letting x1 be [E1, E1, E2, E3; int(1..4)] -letting x2 be [E2, E2, E4, E1; int(1..4)] -language Essence 1.3 - -letting s be permutation((E1, E2), (E3, E4)) -letting x1 be [E1, E1, E2, E4; int(1..4)] -letting x2 be [E2, E2, E3, E1; int(1..4)] -language Essence 1.3 - -letting s be permutation((E1, E2), (E3, E4)) -letting x1 be [E1, E1, E3, E1; int(1..4)] -letting x2 be [E2, E2, E2, E4; int(1..4)] -language Essence 1.3 - -letting s be permutation((E1, E2), (E3, E4)) -letting x1 be [E1, E1, E3, E2; int(1..4)] -letting x2 be [E2, E2, E1, E4; int(1..4)] diff --git a/tests/custom/deprecated_permutations_basic/0039_toSet_on_given_permutation_of_enum/permutation.essence b/tests/custom/deprecated_permutations_basic/0039_toSet_on_given_permutation_of_enum/permutation.essence deleted file mode 100644 index 17f1905d9d..0000000000 --- a/tests/custom/deprecated_permutations_basic/0039_toSet_on_given_permutation_of_enum/permutation.essence +++ /dev/null @@ -1,8 +0,0 @@ -letting e be new type enum {E1, E2, E3, E4} - -letting p be permutation((E1,E2),(E3,E4)) - -find s : set of (e,e) - -such that s = toSet(p) - diff --git a/tests/custom/deprecated_permutations_basic/0039_toSet_on_given_permutation_of_enum/run.sh b/tests/custom/deprecated_permutations_basic/0039_toSet_on_given_permutation_of_enum/run.sh deleted file mode 100755 index 3c60e3f90e..0000000000 --- a/tests/custom/deprecated_permutations_basic/0039_toSet_on_given_permutation_of_enum/run.sh +++ /dev/null @@ -1,3 +0,0 @@ -conjure solve *.essence --number-of-solutions=10 -cat conjure-output/*.solution -rm -rf conjure-output *.solution diff --git a/tests/custom/deprecated_permutations_basic/0040_toSet_on_given_permutation_of_int/permutation.essence b/tests/custom/deprecated_permutations_basic/0040_toSet_on_given_permutation_of_int/permutation.essence deleted file mode 100644 index c50cd03727..0000000000 --- a/tests/custom/deprecated_permutations_basic/0040_toSet_on_given_permutation_of_int/permutation.essence +++ /dev/null @@ -1,6 +0,0 @@ -letting p be permutation((1,2),(3,4)) - -find s : set of (int(1..4),int(1..4)) - -such that s = toSet(p) - diff --git a/tests/custom/deprecated_permutations_basic/0040_toSet_on_given_permutation_of_int/run.sh b/tests/custom/deprecated_permutations_basic/0040_toSet_on_given_permutation_of_int/run.sh deleted file mode 100755 index 3c60e3f90e..0000000000 --- a/tests/custom/deprecated_permutations_basic/0040_toSet_on_given_permutation_of_int/run.sh +++ /dev/null @@ -1,3 +0,0 @@ -conjure solve *.essence --number-of-solutions=10 -cat conjure-output/*.solution -rm -rf conjure-output *.solution diff --git a/tests/custom/deprecated_permutations_basic/0040_toSet_on_given_permutation_of_int/stdout.expected b/tests/custom/deprecated_permutations_basic/0040_toSet_on_given_permutation_of_int/stdout.expected deleted file mode 100644 index 7dd7245819..0000000000 --- a/tests/custom/deprecated_permutations_basic/0040_toSet_on_given_permutation_of_int/stdout.expected +++ /dev/null @@ -1,14 +0,0 @@ -Generating models for permutation.essence -Generated models: model000001.eprime -Saved under: conjure-output -Savile Row: model000001.eprime -Copying solution to: permutation.solution -language Essence 1.3 - -letting s be {(1, 2), (2, 1), (3, 4), (4, 3)} -$ Visualisation for s -$ 1 2 -$ 2 1 -$ 3 4 -$ 4 3 - diff --git a/tests/custom/deprecated_permutations_basic/0041_toSet_on_found_permutation_of_enum/permutation.essence b/tests/custom/deprecated_permutations_basic/0041_toSet_on_found_permutation_of_enum/permutation.essence deleted file mode 100644 index a987081ebf..0000000000 --- a/tests/custom/deprecated_permutations_basic/0041_toSet_on_found_permutation_of_enum/permutation.essence +++ /dev/null @@ -1,10 +0,0 @@ -letting e be new type enum {E1,E2,E3,E4} - -find p : permutation of e - -find s : set of (e,e) - -such that - s = toSet(p) - /\ |s| = 3 - diff --git a/tests/custom/deprecated_permutations_basic/0041_toSet_on_found_permutation_of_enum/run.sh b/tests/custom/deprecated_permutations_basic/0041_toSet_on_found_permutation_of_enum/run.sh deleted file mode 100755 index 3c60e3f90e..0000000000 --- a/tests/custom/deprecated_permutations_basic/0041_toSet_on_found_permutation_of_enum/run.sh +++ /dev/null @@ -1,3 +0,0 @@ -conjure solve *.essence --number-of-solutions=10 -cat conjure-output/*.solution -rm -rf conjure-output *.solution diff --git a/tests/custom/deprecated_permutations_basic/0042_toSet_on_found_permutation_of_int/permutation.essence b/tests/custom/deprecated_permutations_basic/0042_toSet_on_found_permutation_of_int/permutation.essence deleted file mode 100644 index 5a0edceeef..0000000000 --- a/tests/custom/deprecated_permutations_basic/0042_toSet_on_found_permutation_of_int/permutation.essence +++ /dev/null @@ -1,8 +0,0 @@ -find p : permutation of int(1..4) - -find s : set of (int(1..4),int(1..4)) - -such that - s = toSet(p) - /\ |s| = 3 - diff --git a/tests/custom/deprecated_permutations_basic/0042_toSet_on_found_permutation_of_int/run.sh b/tests/custom/deprecated_permutations_basic/0042_toSet_on_found_permutation_of_int/run.sh deleted file mode 100755 index 3c60e3f90e..0000000000 --- a/tests/custom/deprecated_permutations_basic/0042_toSet_on_found_permutation_of_int/run.sh +++ /dev/null @@ -1,3 +0,0 @@ -conjure solve *.essence --number-of-solutions=10 -cat conjure-output/*.solution -rm -rf conjure-output *.solution diff --git a/tests/custom/deprecated_permutations_basic/0043_inverse_on_given_permutation_of_int/permutation.essence b/tests/custom/deprecated_permutations_basic/0043_inverse_on_given_permutation_of_int/permutation.essence deleted file mode 100644 index 15af8b6379..0000000000 --- a/tests/custom/deprecated_permutations_basic/0043_inverse_on_given_permutation_of_int/permutation.essence +++ /dev/null @@ -1,6 +0,0 @@ -letting p be permutation ((1,2),(3,4)) - -find q : permutation of int(1..4) - -such that inverse(p,q) - diff --git a/tests/custom/deprecated_permutations_basic/0043_inverse_on_given_permutation_of_int/run.sh b/tests/custom/deprecated_permutations_basic/0043_inverse_on_given_permutation_of_int/run.sh deleted file mode 100755 index 3c60e3f90e..0000000000 --- a/tests/custom/deprecated_permutations_basic/0043_inverse_on_given_permutation_of_int/run.sh +++ /dev/null @@ -1,3 +0,0 @@ -conjure solve *.essence --number-of-solutions=10 -cat conjure-output/*.solution -rm -rf conjure-output *.solution diff --git a/tests/custom/deprecated_permutations_basic/runthese.sh b/tests/custom/deprecated_permutations_basic/runthese.sh deleted file mode 100644 index 042718136a..0000000000 --- a/tests/custom/deprecated_permutations_basic/runthese.sh +++ /dev/null @@ -1 +0,0 @@ -stack test --test-arguments "-p custom.permutations.basic" diff --git a/tests/custom/permutations/02_cardinality/enum/0004/permutation.essence b/tests/custom/permutations/02_cardinality/enum/0004/permutation.essence new file mode 100644 index 0000000000..be6ffeff36 --- /dev/null +++ b/tests/custom/permutations/02_cardinality/enum/0004/permutation.essence @@ -0,0 +1,10 @@ +letting n be new type enum {E1,E2,E3,E4,E5,E6} + +find p : permutation of n + +such that + |toSet([i | i <- p])| = |p| + + + + diff --git a/tests/custom/deprecated_permutations_basic/0011_find_int_and_permutation_such_that_int_image_equals_const/run.sh b/tests/custom/permutations/02_cardinality/enum/0004/run.sh similarity index 100% rename from tests/custom/deprecated_permutations_basic/0011_find_int_and_permutation_such_that_int_image_equals_const/run.sh rename to tests/custom/permutations/02_cardinality/enum/0004/run.sh diff --git a/tests/custom/deprecated_permutations_basic/0015_find_set_of_permuted_elements_of_matrix/stdout.expected b/tests/custom/permutations/02_cardinality/enum/0004/stdout.expected similarity index 77% rename from tests/custom/deprecated_permutations_basic/0015_find_set_of_permuted_elements_of_matrix/stdout.expected rename to tests/custom/permutations/02_cardinality/enum/0004/stdout.expected index 899694ba25..4e026e23dd 100644 --- a/tests/custom/deprecated_permutations_basic/0015_find_set_of_permuted_elements_of_matrix/stdout.expected +++ b/tests/custom/permutations/02_cardinality/enum/0004/stdout.expected @@ -5,4 +5,5 @@ Savile Row: model000001.eprime Copying solution to: permutation.solution language Essence 1.3 -letting k be {1, 3, 7, 12} +letting i be 4 +letting p be permutation((E3, E4), (E5, E6)) diff --git a/tests/custom/permutations/05_equality/0001_given_permutations_in_param/run.sh b/tests/custom/permutations/05_equality/0001_given_permutations_in_param/run.sh deleted file mode 100755 index 9dc67e67f5..0000000000 --- a/tests/custom/permutations/05_equality/0001_given_permutations_in_param/run.sh +++ /dev/null @@ -1,3 +0,0 @@ -conjure solve *.essence *.param -cat conjure-output/*.solution -rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/05_equality/0002_given_permutations_in_param/run.sh b/tests/custom/permutations/05_equality/0002_given_permutations_in_param/run.sh deleted file mode 100755 index 9dc67e67f5..0000000000 --- a/tests/custom/permutations/05_equality/0002_given_permutations_in_param/run.sh +++ /dev/null @@ -1,3 +0,0 @@ -conjure solve *.essence *.param -cat conjure-output/*.solution -rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/05_equality/0003_given_equal_letting/run.sh b/tests/custom/permutations/05_equality/0003_given_equal_letting/run.sh deleted file mode 100755 index 9dc67e67f5..0000000000 --- a/tests/custom/permutations/05_equality/0003_given_equal_letting/run.sh +++ /dev/null @@ -1,3 +0,0 @@ -conjure solve *.essence *.param -cat conjure-output/*.solution -rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/05_equality/0004_letting_equal_given/permutation.param b/tests/custom/permutations/05_equality/0004_letting_equal_given/permutation.param deleted file mode 100644 index 8a8c516801..0000000000 --- a/tests/custom/permutations/05_equality/0004_letting_equal_given/permutation.param +++ /dev/null @@ -1 +0,0 @@ -letting p be permutation((1,3,4)) diff --git a/tests/custom/permutations/05_equality/0004_letting_equal_given/run.sh b/tests/custom/permutations/05_equality/0004_letting_equal_given/run.sh deleted file mode 100755 index 9dc67e67f5..0000000000 --- a/tests/custom/permutations/05_equality/0004_letting_equal_given/run.sh +++ /dev/null @@ -1,3 +0,0 @@ -conjure solve *.essence *.param -cat conjure-output/*.solution -rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/05_equality/enum/0001_given_permutations_in_param/permutation.essence b/tests/custom/permutations/05_equality/enum/0001_given_permutations_in_param/permutation.essence new file mode 100644 index 0000000000..1d734d0227 --- /dev/null +++ b/tests/custom/permutations/05_equality/enum/0001_given_permutations_in_param/permutation.essence @@ -0,0 +1,12 @@ +letting n be new type enum {E1,E2,E3,E4} + +given p : permutation of n +given q : permutation of n + +find b : bool + +such that b = (p = q) + + + + diff --git a/tests/custom/permutations/05_equality/enum/0001_given_permutations_in_param/permutation.param b/tests/custom/permutations/05_equality/enum/0001_given_permutations_in_param/permutation.param new file mode 100644 index 0000000000..d15978a724 --- /dev/null +++ b/tests/custom/permutations/05_equality/enum/0001_given_permutations_in_param/permutation.param @@ -0,0 +1,2 @@ +letting p be permutation((E1,E3,E4)) +letting q be permutation((E1,E3,E4)) diff --git a/tests/custom/deprecated_permutations_basic/0001_given_permutation_in_param/run.sh b/tests/custom/permutations/05_equality/enum/0001_given_permutations_in_param/run.sh similarity index 100% rename from tests/custom/deprecated_permutations_basic/0001_given_permutation_in_param/run.sh rename to tests/custom/permutations/05_equality/enum/0001_given_permutations_in_param/run.sh diff --git a/tests/custom/permutations/05_equality/0001_given_permutations_in_param/stdout.expected b/tests/custom/permutations/05_equality/enum/0001_given_permutations_in_param/stdout.expected similarity index 100% rename from tests/custom/permutations/05_equality/0001_given_permutations_in_param/stdout.expected rename to tests/custom/permutations/05_equality/enum/0001_given_permutations_in_param/stdout.expected diff --git a/tests/custom/permutations/05_equality/enum/0002_given_permutations_in_param/permutation.essence b/tests/custom/permutations/05_equality/enum/0002_given_permutations_in_param/permutation.essence new file mode 100644 index 0000000000..f50a7f5ec1 --- /dev/null +++ b/tests/custom/permutations/05_equality/enum/0002_given_permutations_in_param/permutation.essence @@ -0,0 +1,12 @@ +letting n be new type enum {E1,E2,E3,E4} + +given p : permutation of n +given q : permutation of n + +find b : bool + +such that b = (p = q) + + + + diff --git a/tests/custom/permutations/05_equality/enum/0002_given_permutations_in_param/permutation.param b/tests/custom/permutations/05_equality/enum/0002_given_permutations_in_param/permutation.param new file mode 100644 index 0000000000..9fe9e7a421 --- /dev/null +++ b/tests/custom/permutations/05_equality/enum/0002_given_permutations_in_param/permutation.param @@ -0,0 +1,2 @@ +letting p be permutation((E1,E3,E4)) +letting q be permutation((E1,E2,E4)) diff --git a/tests/custom/deprecated_permutations_basic/0002_given_permutation_in_param/run.sh b/tests/custom/permutations/05_equality/enum/0002_given_permutations_in_param/run.sh similarity index 100% rename from tests/custom/deprecated_permutations_basic/0002_given_permutation_in_param/run.sh rename to tests/custom/permutations/05_equality/enum/0002_given_permutations_in_param/run.sh diff --git a/tests/custom/permutations/05_equality/0002_given_permutations_in_param/stdout.expected b/tests/custom/permutations/05_equality/enum/0002_given_permutations_in_param/stdout.expected similarity index 100% rename from tests/custom/permutations/05_equality/0002_given_permutations_in_param/stdout.expected rename to tests/custom/permutations/05_equality/enum/0002_given_permutations_in_param/stdout.expected diff --git a/tests/custom/permutations/05_equality/enum/0003_given_equal_letting/permutation.essence b/tests/custom/permutations/05_equality/enum/0003_given_equal_letting/permutation.essence new file mode 100644 index 0000000000..70fee7073d --- /dev/null +++ b/tests/custom/permutations/05_equality/enum/0003_given_equal_letting/permutation.essence @@ -0,0 +1,12 @@ +letting n be new type enum {E1,E2,E3,E4} + +given p : permutation of n +letting q be permutation((E1,E2,E4)) + +find b : bool + +such that b = (p = q) + + + + diff --git a/tests/custom/permutations/05_equality/enum/0003_given_equal_letting/permutation.param b/tests/custom/permutations/05_equality/enum/0003_given_equal_letting/permutation.param new file mode 100644 index 0000000000..19349bb872 --- /dev/null +++ b/tests/custom/permutations/05_equality/enum/0003_given_equal_letting/permutation.param @@ -0,0 +1 @@ +letting p be permutation((E1,E3,E4)) diff --git a/tests/custom/deprecated_permutations_basic/0003_given_permutation_in_param_2_cycle/run.sh b/tests/custom/permutations/05_equality/enum/0003_given_equal_letting/run.sh similarity index 100% rename from tests/custom/deprecated_permutations_basic/0003_given_permutation_in_param_2_cycle/run.sh rename to tests/custom/permutations/05_equality/enum/0003_given_equal_letting/run.sh diff --git a/tests/custom/permutations/05_equality/0003_given_equal_letting/stdout.expected b/tests/custom/permutations/05_equality/enum/0003_given_equal_letting/stdout.expected similarity index 100% rename from tests/custom/permutations/05_equality/0003_given_equal_letting/stdout.expected rename to tests/custom/permutations/05_equality/enum/0003_given_equal_letting/stdout.expected diff --git a/tests/custom/permutations/05_equality/enum/0004_letting_equal_given/permutation.essence b/tests/custom/permutations/05_equality/enum/0004_letting_equal_given/permutation.essence new file mode 100644 index 0000000000..ec7bacb28f --- /dev/null +++ b/tests/custom/permutations/05_equality/enum/0004_letting_equal_given/permutation.essence @@ -0,0 +1,12 @@ +letting n be new type enum {E1,E2,E3,E4} + +given p : permutation of n +letting q be permutation((E1,E2,E4)) + +find b : bool + +such that b = (q = p) + + + + diff --git a/tests/custom/permutations/05_equality/enum/0004_letting_equal_given/permutation.param b/tests/custom/permutations/05_equality/enum/0004_letting_equal_given/permutation.param new file mode 100644 index 0000000000..19349bb872 --- /dev/null +++ b/tests/custom/permutations/05_equality/enum/0004_letting_equal_given/permutation.param @@ -0,0 +1 @@ +letting p be permutation((E1,E3,E4)) diff --git a/tests/custom/deprecated_permutations_basic/0004_given_permutation_in_param_2_cycle/run.sh b/tests/custom/permutations/05_equality/enum/0004_letting_equal_given/run.sh similarity index 100% rename from tests/custom/deprecated_permutations_basic/0004_given_permutation_in_param_2_cycle/run.sh rename to tests/custom/permutations/05_equality/enum/0004_letting_equal_given/run.sh diff --git a/tests/custom/permutations/05_equality/0004_letting_equal_given/stdout.expected b/tests/custom/permutations/05_equality/enum/0004_letting_equal_given/stdout.expected similarity index 100% rename from tests/custom/permutations/05_equality/0004_letting_equal_given/stdout.expected rename to tests/custom/permutations/05_equality/enum/0004_letting_equal_given/stdout.expected diff --git a/tests/custom/permutations/05_equality/enum/0005_find_eq_find/permutation.essence b/tests/custom/permutations/05_equality/enum/0005_find_eq_find/permutation.essence new file mode 100644 index 0000000000..55b8c1f1e4 --- /dev/null +++ b/tests/custom/permutations/05_equality/enum/0005_find_eq_find/permutation.essence @@ -0,0 +1,10 @@ +letting n be new type enum {E1,E2,E3,E4} + +find p : permutation of n +find q : permutation of n + +such that q = p + + + + diff --git a/tests/custom/deprecated_permutations_basic/0035_permutation_of_enum_is_identity_for_integers/run.sh b/tests/custom/permutations/05_equality/enum/0005_find_eq_find/run.sh similarity index 100% rename from tests/custom/deprecated_permutations_basic/0035_permutation_of_enum_is_identity_for_integers/run.sh rename to tests/custom/permutations/05_equality/enum/0005_find_eq_find/run.sh diff --git a/tests/custom/permutations/05_equality/enum/0005_find_eq_find/stdout.expected b/tests/custom/permutations/05_equality/enum/0005_find_eq_find/stdout.expected new file mode 100644 index 0000000000..16efae085b --- /dev/null +++ b/tests/custom/permutations/05_equality/enum/0005_find_eq_find/stdout.expected @@ -0,0 +1,54 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Copying solution to: permutation-000001.solution +Copying solution to: permutation-000002.solution +Copying solution to: permutation-000003.solution +Copying solution to: permutation-000004.solution +Copying solution to: permutation-000005.solution +Copying solution to: permutation-000006.solution +Copying solution to: permutation-000007.solution +Copying solution to: permutation-000008.solution +Copying solution to: permutation-000009.solution +Copying solution to: permutation-000010.solution +language Essence 1.3 + +letting p be permutation() +letting q be permutation() +language Essence 1.3 + +letting p be permutation((E3, E4)) +letting q be permutation((E3, E4)) +language Essence 1.3 + +letting p be permutation((E2, E3)) +letting q be permutation((E2, E3)) +language Essence 1.3 + +letting p be permutation((E2, E3, E4)) +letting q be permutation((E2, E3, E4)) +language Essence 1.3 + +letting p be permutation((E2, E4, E3)) +letting q be permutation((E2, E4, E3)) +language Essence 1.3 + +letting p be permutation((E2, E4)) +letting q be permutation((E2, E4)) +language Essence 1.3 + +letting p be permutation((E1, E2)) +letting q be permutation((E1, E2)) +language Essence 1.3 + +letting p be permutation((E1, E2), (E3, E4)) +letting q be permutation((E1, E2), (E3, E4)) +language Essence 1.3 + +letting p be permutation((E1, E2, E3)) +letting q be permutation((E1, E2, E3)) +language Essence 1.3 + +letting p be permutation((E1, E2, E3, E4)) +letting q be permutation((E1, E2, E3, E4)) diff --git a/tests/custom/permutations/05_equality/0001_given_permutations_in_param/permutation.essence b/tests/custom/permutations/05_equality/int/0001_given_permutations_in_param/permutation.essence similarity index 100% rename from tests/custom/permutations/05_equality/0001_given_permutations_in_param/permutation.essence rename to tests/custom/permutations/05_equality/int/0001_given_permutations_in_param/permutation.essence diff --git a/tests/custom/permutations/05_equality/0001_given_permutations_in_param/permutation.param b/tests/custom/permutations/05_equality/int/0001_given_permutations_in_param/permutation.param similarity index 100% rename from tests/custom/permutations/05_equality/0001_given_permutations_in_param/permutation.param rename to tests/custom/permutations/05_equality/int/0001_given_permutations_in_param/permutation.param diff --git a/tests/custom/deprecated_permutations_basic/0005_find_int_image_under_given_permutation/run.sh b/tests/custom/permutations/05_equality/int/0001_given_permutations_in_param/run.sh similarity index 100% rename from tests/custom/deprecated_permutations_basic/0005_find_int_image_under_given_permutation/run.sh rename to tests/custom/permutations/05_equality/int/0001_given_permutations_in_param/run.sh diff --git a/tests/custom/deprecated_permutations_basic/0002_given_permutation_in_param/stdout.expected b/tests/custom/permutations/05_equality/int/0001_given_permutations_in_param/stdout.expected similarity index 92% rename from tests/custom/deprecated_permutations_basic/0002_given_permutation_in_param/stdout.expected rename to tests/custom/permutations/05_equality/int/0001_given_permutations_in_param/stdout.expected index 1d9c5a0937..901f2ae574 100644 --- a/tests/custom/deprecated_permutations_basic/0002_given_permutation_in_param/stdout.expected +++ b/tests/custom/permutations/05_equality/int/0001_given_permutations_in_param/stdout.expected @@ -5,3 +5,4 @@ Savile Row: model000001.eprime permutation.param Copying solution to: permutation-permutation.solution language Essence 1.3 +letting b be true diff --git a/tests/custom/permutations/05_equality/0002_given_permutations_in_param/permutation.essence b/tests/custom/permutations/05_equality/int/0002_given_permutations_in_param/permutation.essence similarity index 100% rename from tests/custom/permutations/05_equality/0002_given_permutations_in_param/permutation.essence rename to tests/custom/permutations/05_equality/int/0002_given_permutations_in_param/permutation.essence diff --git a/tests/custom/permutations/05_equality/0002_given_permutations_in_param/permutation.param b/tests/custom/permutations/05_equality/int/0002_given_permutations_in_param/permutation.param similarity index 100% rename from tests/custom/permutations/05_equality/0002_given_permutations_in_param/permutation.param rename to tests/custom/permutations/05_equality/int/0002_given_permutations_in_param/permutation.param diff --git a/tests/custom/deprecated_permutations_basic/0006_find_int_image_under_given_permutation/run.sh b/tests/custom/permutations/05_equality/int/0002_given_permutations_in_param/run.sh similarity index 100% rename from tests/custom/deprecated_permutations_basic/0006_find_int_image_under_given_permutation/run.sh rename to tests/custom/permutations/05_equality/int/0002_given_permutations_in_param/run.sh diff --git a/tests/custom/deprecated_permutations_basic/0005_find_int_image_under_given_permutation/stdout.expected b/tests/custom/permutations/05_equality/int/0002_given_permutations_in_param/stdout.expected similarity index 92% rename from tests/custom/deprecated_permutations_basic/0005_find_int_image_under_given_permutation/stdout.expected rename to tests/custom/permutations/05_equality/int/0002_given_permutations_in_param/stdout.expected index 826dd27a43..1cc90d46bc 100644 --- a/tests/custom/deprecated_permutations_basic/0005_find_int_image_under_given_permutation/stdout.expected +++ b/tests/custom/permutations/05_equality/int/0002_given_permutations_in_param/stdout.expected @@ -5,4 +5,4 @@ Savile Row: model000001.eprime permutation.param Copying solution to: permutation-permutation.solution language Essence 1.3 -letting i be 0 +letting b be false diff --git a/tests/custom/permutations/05_equality/0003_given_equal_letting/permutation.essence b/tests/custom/permutations/05_equality/int/0003_given_equal_letting/permutation.essence similarity index 100% rename from tests/custom/permutations/05_equality/0003_given_equal_letting/permutation.essence rename to tests/custom/permutations/05_equality/int/0003_given_equal_letting/permutation.essence diff --git a/tests/custom/deprecated_permutations_basic/0001_given_permutation_in_param/permutation.param b/tests/custom/permutations/05_equality/int/0003_given_equal_letting/permutation.param similarity index 100% rename from tests/custom/deprecated_permutations_basic/0001_given_permutation_in_param/permutation.param rename to tests/custom/permutations/05_equality/int/0003_given_equal_letting/permutation.param diff --git a/tests/custom/deprecated_permutations_basic/0007_find_int_image_under_given_permutation/run.sh b/tests/custom/permutations/05_equality/int/0003_given_equal_letting/run.sh similarity index 100% rename from tests/custom/deprecated_permutations_basic/0007_find_int_image_under_given_permutation/run.sh rename to tests/custom/permutations/05_equality/int/0003_given_equal_letting/run.sh diff --git a/tests/custom/deprecated_permutations_basic/0001_given_permutation_in_param/stdout.expected b/tests/custom/permutations/05_equality/int/0003_given_equal_letting/stdout.expected similarity index 92% rename from tests/custom/deprecated_permutations_basic/0001_given_permutation_in_param/stdout.expected rename to tests/custom/permutations/05_equality/int/0003_given_equal_letting/stdout.expected index 1d9c5a0937..1cc90d46bc 100644 --- a/tests/custom/deprecated_permutations_basic/0001_given_permutation_in_param/stdout.expected +++ b/tests/custom/permutations/05_equality/int/0003_given_equal_letting/stdout.expected @@ -5,3 +5,4 @@ Savile Row: model000001.eprime permutation.param Copying solution to: permutation-permutation.solution language Essence 1.3 +letting b be false diff --git a/tests/custom/permutations/05_equality/0004_letting_equal_given/permutation.essence b/tests/custom/permutations/05_equality/int/0004_letting_equal_given/permutation.essence similarity index 100% rename from tests/custom/permutations/05_equality/0004_letting_equal_given/permutation.essence rename to tests/custom/permutations/05_equality/int/0004_letting_equal_given/permutation.essence diff --git a/tests/custom/permutations/05_equality/0003_given_equal_letting/permutation.param b/tests/custom/permutations/05_equality/int/0004_letting_equal_given/permutation.param similarity index 100% rename from tests/custom/permutations/05_equality/0003_given_equal_letting/permutation.param rename to tests/custom/permutations/05_equality/int/0004_letting_equal_given/permutation.param diff --git a/tests/custom/deprecated_permutations_basic/0008_find_int_image_under_two_composed_given_permutations/run.sh b/tests/custom/permutations/05_equality/int/0004_letting_equal_given/run.sh similarity index 100% rename from tests/custom/deprecated_permutations_basic/0008_find_int_image_under_two_composed_given_permutations/run.sh rename to tests/custom/permutations/05_equality/int/0004_letting_equal_given/run.sh diff --git a/tests/custom/deprecated_permutations_basic/0004_given_permutation_in_param_2_cycle/stdout.expected b/tests/custom/permutations/05_equality/int/0004_letting_equal_given/stdout.expected similarity index 92% rename from tests/custom/deprecated_permutations_basic/0004_given_permutation_in_param_2_cycle/stdout.expected rename to tests/custom/permutations/05_equality/int/0004_letting_equal_given/stdout.expected index 1d9c5a0937..1cc90d46bc 100644 --- a/tests/custom/deprecated_permutations_basic/0004_given_permutation_in_param_2_cycle/stdout.expected +++ b/tests/custom/permutations/05_equality/int/0004_letting_equal_given/stdout.expected @@ -5,3 +5,4 @@ Savile Row: model000001.eprime permutation.param Copying solution to: permutation-permutation.solution language Essence 1.3 +letting b be false diff --git a/tests/custom/permutations/05_equality/int/0005_find_eq_find/permutation.essence b/tests/custom/permutations/05_equality/int/0005_find_eq_find/permutation.essence new file mode 100644 index 0000000000..cd79b60584 --- /dev/null +++ b/tests/custom/permutations/05_equality/int/0005_find_eq_find/permutation.essence @@ -0,0 +1,8 @@ +find p : permutation of int(1..4) +find q : permutation of int(1..4) + +such that q = p + + + + diff --git a/tests/custom/deprecated_permutations_basic/0036_big_test_of_enums_in_matrices/run.sh b/tests/custom/permutations/05_equality/int/0005_find_eq_find/run.sh similarity index 100% rename from tests/custom/deprecated_permutations_basic/0036_big_test_of_enums_in_matrices/run.sh rename to tests/custom/permutations/05_equality/int/0005_find_eq_find/run.sh diff --git a/tests/custom/deprecated_permutations_basic/0014_find_matrix_such_that_swapping_any_index_pairs_becomes_lex_greater/stdout.expected b/tests/custom/permutations/05_equality/int/0005_find_eq_find/stdout.expected similarity index 54% rename from tests/custom/deprecated_permutations_basic/0014_find_matrix_such_that_swapping_any_index_pairs_becomes_lex_greater/stdout.expected rename to tests/custom/permutations/05_equality/int/0005_find_eq_find/stdout.expected index f0d0665e21..f8eaaf4a36 100644 --- a/tests/custom/deprecated_permutations_basic/0014_find_matrix_such_that_swapping_any_index_pairs_becomes_lex_greater/stdout.expected +++ b/tests/custom/permutations/05_equality/int/0005_find_eq_find/stdout.expected @@ -14,31 +14,41 @@ Copying solution to: permutation-000009.solution Copying solution to: permutation-000010.solution language Essence 1.3 -letting m be [0, 0, 0, 0, 0, 0, 0, 0, 0; int(1..9)] +letting p be permutation() +letting q be permutation() language Essence 1.3 -letting m be [0, 0, 0, 0, 0, 0, 0, 0, 1; int(1..9)] +letting p be permutation((3, 4)) +letting q be permutation((3, 4)) language Essence 1.3 -letting m be [0, 0, 0, 0, 0, 0, 0, 1, 1; int(1..9)] +letting p be permutation((2, 3)) +letting q be permutation((2, 3)) language Essence 1.3 -letting m be [0, 0, 0, 0, 0, 0, 1, 1, 1; int(1..9)] +letting p be permutation((2, 3, 4)) +letting q be permutation((2, 3, 4)) language Essence 1.3 -letting m be [0, 0, 0, 0, 0, 1, 1, 1, 1; int(1..9)] +letting p be permutation((2, 4, 3)) +letting q be permutation((2, 4, 3)) language Essence 1.3 -letting m be [0, 0, 0, 0, 1, 1, 1, 1, 1; int(1..9)] +letting p be permutation((2, 4)) +letting q be permutation((2, 4)) language Essence 1.3 -letting m be [0, 0, 0, 1, 1, 1, 1, 1, 1; int(1..9)] +letting p be permutation((1, 2)) +letting q be permutation((1, 2)) language Essence 1.3 -letting m be [0, 0, 1, 1, 1, 1, 1, 1, 1; int(1..9)] +letting p be permutation((1, 2), (3, 4)) +letting q be permutation((1, 2), (3, 4)) language Essence 1.3 -letting m be [0, 1, 1, 1, 1, 1, 1, 1, 1; int(1..9)] +letting p be permutation((1, 2, 3)) +letting q be permutation((1, 2, 3)) language Essence 1.3 -letting m be [1, 1, 1, 1, 1, 1, 1, 1, 1; int(1..9)] +letting p be permutation((1, 2, 3, 4)) +letting q be permutation((1, 2, 3, 4)) diff --git a/tests/custom/permutations/05_equality/unnamed/0005_find_eq_find/permutation.essence b/tests/custom/permutations/05_equality/unnamed/0005_find_eq_find/permutation.essence new file mode 100644 index 0000000000..00112283a9 --- /dev/null +++ b/tests/custom/permutations/05_equality/unnamed/0005_find_eq_find/permutation.essence @@ -0,0 +1,10 @@ +letting n be new type of size 4 + +find p : permutation of n +find q : permutation of n + +such that q = p + + + + diff --git a/tests/custom/deprecated_permutations_basic/0037_matrices_of_enums_indexed_by_enums/run.sh b/tests/custom/permutations/05_equality/unnamed/0005_find_eq_find/run.sh similarity index 100% rename from tests/custom/deprecated_permutations_basic/0037_matrices_of_enums_indexed_by_enums/run.sh rename to tests/custom/permutations/05_equality/unnamed/0005_find_eq_find/run.sh diff --git a/tests/custom/permutations/05_equality/unnamed/0005_find_eq_find/stdout.expected b/tests/custom/permutations/05_equality/unnamed/0005_find_eq_find/stdout.expected new file mode 100644 index 0000000000..6446ec12f7 --- /dev/null +++ b/tests/custom/permutations/05_equality/unnamed/0005_find_eq_find/stdout.expected @@ -0,0 +1,64 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Copying solution to: permutation-000001.solution +Copying solution to: permutation-000002.solution +Copying solution to: permutation-000003.solution +Copying solution to: permutation-000004.solution +Copying solution to: permutation-000005.solution +Copying solution to: permutation-000006.solution +Copying solution to: permutation-000007.solution +Copying solution to: permutation-000008.solution +Copying solution to: permutation-000009.solution +Copying solution to: permutation-000010.solution +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation() +letting q be permutation() +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_3, n_4)) +letting q be permutation((n_3, n_4)) +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_2, n_3)) +letting q be permutation((n_2, n_3)) +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_2, n_3, n_4)) +letting q be permutation((n_2, n_3, n_4)) +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_2, n_4, n_3)) +letting q be permutation((n_2, n_4, n_3)) +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_2, n_4)) +letting q be permutation((n_2, n_4)) +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_1, n_2)) +letting q be permutation((n_1, n_2)) +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_1, n_2), (n_3, n_4)) +letting q be permutation((n_1, n_2), (n_3, n_4)) +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_1, n_2, n_3)) +letting q be permutation((n_1, n_2, n_3)) +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_1, n_2, n_3, n_4)) +letting q be permutation((n_1, n_2, n_3, n_4)) From 86de63ce84289d16d3ff296237959705a92a9b82 Mon Sep 17 00:00:00 2001 From: Fraser Dunlop Date: Tue, 11 Dec 2018 13:40:50 +0000 Subject: [PATCH 049/229] Inverse tests --- src/Conjure/Rules/Horizontal/Permutation.hs | 38 +++++------ src/Conjure/UI/Model.hs | 3 +- .../permutation.essence | 9 +++ .../permutation.param | 2 + .../permutation2.param | 2 + .../0001_given_permutations_in_param/run.sh | 3 + .../stdout.expected | 13 ++++ .../permutation.essence | 9 +++ .../permutation.param | 2 + .../permutation2.param | 2 + .../0002_given_permutations_in_param/run.sh | 3 + .../stdout.expected | 13 ++++ .../permutation.essence | 9 +++ .../permutation.param | 1 + .../permutation2.essence | 1 + .../enum/0003_given_equal_letting/run.sh | 3 + .../0003_given_equal_letting/stdout.expected | 13 ++++ .../permutation.essence | 9 +++ .../permutation.param | 1 + .../permutation2.param | 1 + .../enum/0004_letting_equal_given/run.sh | 3 + .../0004_letting_equal_given/stdout.expected | 13 ++++ .../0005_find_eq_find/permutation.essence | 5 ++ .../06_inverse/enum/0005_find_eq_find/run.sh | 3 + .../enum/0005_find_eq_find/stdout.expected | 54 ++++++++++++++++ .../permutation.essence | 9 +++ .../permutation.param | 2 + .../0001_given_permutations_in_param/run.sh | 3 + .../stdout.expected | 8 +++ .../permutation.essence | 9 +++ .../permutation.param | 2 + .../0002_given_permutations_in_param/run.sh | 3 + .../stdout.expected | 8 +++ .../permutation.essence | 9 +++ .../permutation.param | 1 + .../int/0003_given_equal_letting/run.sh | 3 + .../0003_given_equal_letting/stdout.expected | 8 +++ .../permutation.essence | 9 +++ .../permutation.param | 1 + .../permutation2.param | 1 + .../int/0004_letting_equal_given/run.sh | 3 + .../0004_letting_equal_given/stdout.expected | 13 ++++ .../int/0005_find_eq_find/permutation.essence | 4 ++ .../06_inverse/int/0005_find_eq_find/run.sh | 3 + .../int/0005_find_eq_find/stdout.expected | 54 ++++++++++++++++ .../permutations/06_inverse/runthese.sh | 2 + .../permutation.essence | 8 +++ .../unnamed/0005_find_inverse_find/run.sh | 3 + .../0005_find_inverse_find/stdout.expected | 64 +++++++++++++++++++ tests/custom/permutations/README.md | 2 + 50 files changed, 427 insertions(+), 20 deletions(-) create mode 100644 tests/custom/permutations/06_inverse/enum/0001_given_permutations_in_param/permutation.essence create mode 100644 tests/custom/permutations/06_inverse/enum/0001_given_permutations_in_param/permutation.param create mode 100644 tests/custom/permutations/06_inverse/enum/0001_given_permutations_in_param/permutation2.param create mode 100755 tests/custom/permutations/06_inverse/enum/0001_given_permutations_in_param/run.sh create mode 100644 tests/custom/permutations/06_inverse/enum/0001_given_permutations_in_param/stdout.expected create mode 100644 tests/custom/permutations/06_inverse/enum/0002_given_permutations_in_param/permutation.essence create mode 100644 tests/custom/permutations/06_inverse/enum/0002_given_permutations_in_param/permutation.param create mode 100644 tests/custom/permutations/06_inverse/enum/0002_given_permutations_in_param/permutation2.param create mode 100755 tests/custom/permutations/06_inverse/enum/0002_given_permutations_in_param/run.sh create mode 100644 tests/custom/permutations/06_inverse/enum/0002_given_permutations_in_param/stdout.expected create mode 100644 tests/custom/permutations/06_inverse/enum/0003_given_equal_letting/permutation.essence create mode 100644 tests/custom/permutations/06_inverse/enum/0003_given_equal_letting/permutation.param create mode 100644 tests/custom/permutations/06_inverse/enum/0003_given_equal_letting/permutation2.essence create mode 100755 tests/custom/permutations/06_inverse/enum/0003_given_equal_letting/run.sh create mode 100644 tests/custom/permutations/06_inverse/enum/0003_given_equal_letting/stdout.expected create mode 100644 tests/custom/permutations/06_inverse/enum/0004_letting_equal_given/permutation.essence create mode 100644 tests/custom/permutations/06_inverse/enum/0004_letting_equal_given/permutation.param create mode 100644 tests/custom/permutations/06_inverse/enum/0004_letting_equal_given/permutation2.param create mode 100755 tests/custom/permutations/06_inverse/enum/0004_letting_equal_given/run.sh create mode 100644 tests/custom/permutations/06_inverse/enum/0004_letting_equal_given/stdout.expected create mode 100644 tests/custom/permutations/06_inverse/enum/0005_find_eq_find/permutation.essence create mode 100755 tests/custom/permutations/06_inverse/enum/0005_find_eq_find/run.sh create mode 100644 tests/custom/permutations/06_inverse/enum/0005_find_eq_find/stdout.expected create mode 100644 tests/custom/permutations/06_inverse/int/0001_given_permutations_in_param/permutation.essence create mode 100644 tests/custom/permutations/06_inverse/int/0001_given_permutations_in_param/permutation.param create mode 100755 tests/custom/permutations/06_inverse/int/0001_given_permutations_in_param/run.sh create mode 100644 tests/custom/permutations/06_inverse/int/0001_given_permutations_in_param/stdout.expected create mode 100644 tests/custom/permutations/06_inverse/int/0002_given_permutations_in_param/permutation.essence create mode 100644 tests/custom/permutations/06_inverse/int/0002_given_permutations_in_param/permutation.param create mode 100755 tests/custom/permutations/06_inverse/int/0002_given_permutations_in_param/run.sh create mode 100644 tests/custom/permutations/06_inverse/int/0002_given_permutations_in_param/stdout.expected create mode 100644 tests/custom/permutations/06_inverse/int/0003_given_equal_letting/permutation.essence create mode 100644 tests/custom/permutations/06_inverse/int/0003_given_equal_letting/permutation.param create mode 100755 tests/custom/permutations/06_inverse/int/0003_given_equal_letting/run.sh create mode 100644 tests/custom/permutations/06_inverse/int/0003_given_equal_letting/stdout.expected create mode 100644 tests/custom/permutations/06_inverse/int/0004_letting_equal_given/permutation.essence create mode 100644 tests/custom/permutations/06_inverse/int/0004_letting_equal_given/permutation.param create mode 100644 tests/custom/permutations/06_inverse/int/0004_letting_equal_given/permutation2.param create mode 100755 tests/custom/permutations/06_inverse/int/0004_letting_equal_given/run.sh create mode 100644 tests/custom/permutations/06_inverse/int/0004_letting_equal_given/stdout.expected create mode 100644 tests/custom/permutations/06_inverse/int/0005_find_eq_find/permutation.essence create mode 100755 tests/custom/permutations/06_inverse/int/0005_find_eq_find/run.sh create mode 100644 tests/custom/permutations/06_inverse/int/0005_find_eq_find/stdout.expected create mode 100644 tests/custom/permutations/06_inverse/runthese.sh create mode 100644 tests/custom/permutations/06_inverse/unnamed/0005_find_inverse_find/permutation.essence create mode 100755 tests/custom/permutations/06_inverse/unnamed/0005_find_inverse_find/run.sh create mode 100644 tests/custom/permutations/06_inverse/unnamed/0005_find_inverse_find/stdout.expected diff --git a/src/Conjure/Rules/Horizontal/Permutation.hs b/src/Conjure/Rules/Horizontal/Permutation.hs index d5edbe930e..04e13b986b 100644 --- a/src/Conjure/Rules/Horizontal/Permutation.hs +++ b/src/Conjure/Rules/Horizontal/Permutation.hs @@ -131,6 +131,25 @@ rule_In = "permutation-in" `namedRule` theRule where return [essence| exists &iPat in &s . &i = &x |] ) +rule_Permutation_Inverse :: Rule +rule_Permutation_Inverse = "permutation-inverse" `namedRule` theRule where + theRule [essence| inverse(&p1, &p2)|] = do + case p1 of WithLocals{} -> na "bubble-delay" ; _ -> return () + case p2 of WithLocals{} -> na "bubble-delay" ; _ -> return () + TypePermutation{} <- typeOf p1 + TypePermutation{} <- typeOf p2 + return + ( "Vertical rule for permutation-inverse" + , do + (iPat, i) <- quantifiedVar + return [essence| + (forAll &iPat in &p1 . image(&p2,&i[2]) = &i[1]) + /\ + (forAll &iPat in &p2 . image(&p1,&i[2]) = &i[1]) + |] + ) + theRule _ = na "rule_Permutation_Inverse" + @@ -210,23 +229,4 @@ rule_In = "permutation-in" `namedRule` theRule where -- theRule _ = na "rule_Compose" -- -- ---rule_Permutation_Inverse :: Rule ---rule_Permutation_Inverse = "permutation-inverse{AsFunction}" `namedRule` theRule where --- theRule [essence| inverse(&p1, &p2)|] = do --- case p1 of WithLocals{} -> na "bubble-delay" ; _ -> return () --- case p2 of WithLocals{} -> na "bubble-delay" ; _ -> return () --- TypePermutation{} <- typeOf p1 --- TypePermutation{} <- typeOf p2 --- return --- ( "Vertical rule for permutation-inverse, AsFunction representation" --- , do --- (iPat, i) <- quantifiedVar --- return [essence| --- (forAll &iPat in &p1 . image(&p2,&i[2]) = &i[1]) --- /\ --- (forAll &iPat in &p2 . image(&p1,&i[2]) = &i[1]) --- |] --- ) --- theRule _ = na "rule_Permutation_Equality" - diff --git a/src/Conjure/UI/Model.hs b/src/Conjure/UI/Model.hs index 7c69ef4edd..1744140828 100644 --- a/src/Conjure/UI/Model.hs +++ b/src/Conjure/UI/Model.hs @@ -1210,8 +1210,9 @@ horizontalRules = , Horizontal.Permutation.rule_Permute_Comprehension_Tuples_Literal , Horizontal.Permutation.rule_Image_Literal , Horizontal.Permutation.rule_In + , Horizontal.Permutation.rule_Permutation_Inverse -- , Horizontal.Permutation.rule_Image_Literal_Comprehension --- , Horizontal.Permutation.rule_Permutation_Inverse + -- , Horizontal.Permutation.rule_Compose diff --git a/tests/custom/permutations/06_inverse/enum/0001_given_permutations_in_param/permutation.essence b/tests/custom/permutations/06_inverse/enum/0001_given_permutations_in_param/permutation.essence new file mode 100644 index 0000000000..7ccfbd21e6 --- /dev/null +++ b/tests/custom/permutations/06_inverse/enum/0001_given_permutations_in_param/permutation.essence @@ -0,0 +1,9 @@ +letting n be new type enum {E1,E2,E3,E4} + +given p : permutation of n +given q : permutation of n + +find b : bool + +such that b = inverse(p,q) + diff --git a/tests/custom/permutations/06_inverse/enum/0001_given_permutations_in_param/permutation.param b/tests/custom/permutations/06_inverse/enum/0001_given_permutations_in_param/permutation.param new file mode 100644 index 0000000000..d15978a724 --- /dev/null +++ b/tests/custom/permutations/06_inverse/enum/0001_given_permutations_in_param/permutation.param @@ -0,0 +1,2 @@ +letting p be permutation((E1,E3,E4)) +letting q be permutation((E1,E3,E4)) diff --git a/tests/custom/permutations/06_inverse/enum/0001_given_permutations_in_param/permutation2.param b/tests/custom/permutations/06_inverse/enum/0001_given_permutations_in_param/permutation2.param new file mode 100644 index 0000000000..d357e2323a --- /dev/null +++ b/tests/custom/permutations/06_inverse/enum/0001_given_permutations_in_param/permutation2.param @@ -0,0 +1,2 @@ +letting p be permutation((E1,E4,E3)) +letting q be permutation((E1,E3,E4)) diff --git a/tests/custom/permutations/06_inverse/enum/0001_given_permutations_in_param/run.sh b/tests/custom/permutations/06_inverse/enum/0001_given_permutations_in_param/run.sh new file mode 100755 index 0000000000..9dc67e67f5 --- /dev/null +++ b/tests/custom/permutations/06_inverse/enum/0001_given_permutations_in_param/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence *.param +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/06_inverse/enum/0001_given_permutations_in_param/stdout.expected b/tests/custom/permutations/06_inverse/enum/0001_given_permutations_in_param/stdout.expected new file mode 100644 index 0000000000..8ca07a3941 --- /dev/null +++ b/tests/custom/permutations/06_inverse/enum/0001_given_permutations_in_param/stdout.expected @@ -0,0 +1,13 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime permutation.param +Savile Row: model000001.eprime permutation2.param +Copying solution to: permutation-permutation.solution +Copying solution to: permutation-permutation2.solution +language Essence 1.3 + +letting b be false +language Essence 1.3 + +letting b be true diff --git a/tests/custom/permutations/06_inverse/enum/0002_given_permutations_in_param/permutation.essence b/tests/custom/permutations/06_inverse/enum/0002_given_permutations_in_param/permutation.essence new file mode 100644 index 0000000000..64f3b737de --- /dev/null +++ b/tests/custom/permutations/06_inverse/enum/0002_given_permutations_in_param/permutation.essence @@ -0,0 +1,9 @@ +letting n be new type enum {E1,E2,E3,E4} + +given p : permutation of n +given q : permutation of n + +find b : bool + +such that b = inverse(p,q) + diff --git a/tests/custom/permutations/06_inverse/enum/0002_given_permutations_in_param/permutation.param b/tests/custom/permutations/06_inverse/enum/0002_given_permutations_in_param/permutation.param new file mode 100644 index 0000000000..9fe9e7a421 --- /dev/null +++ b/tests/custom/permutations/06_inverse/enum/0002_given_permutations_in_param/permutation.param @@ -0,0 +1,2 @@ +letting p be permutation((E1,E3,E4)) +letting q be permutation((E1,E2,E4)) diff --git a/tests/custom/permutations/06_inverse/enum/0002_given_permutations_in_param/permutation2.param b/tests/custom/permutations/06_inverse/enum/0002_given_permutations_in_param/permutation2.param new file mode 100644 index 0000000000..5b94ce626d --- /dev/null +++ b/tests/custom/permutations/06_inverse/enum/0002_given_permutations_in_param/permutation2.param @@ -0,0 +1,2 @@ +letting p be permutation((E1,E4,E2)) +letting q be permutation((E1,E2,E4)) diff --git a/tests/custom/permutations/06_inverse/enum/0002_given_permutations_in_param/run.sh b/tests/custom/permutations/06_inverse/enum/0002_given_permutations_in_param/run.sh new file mode 100755 index 0000000000..9dc67e67f5 --- /dev/null +++ b/tests/custom/permutations/06_inverse/enum/0002_given_permutations_in_param/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence *.param +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/06_inverse/enum/0002_given_permutations_in_param/stdout.expected b/tests/custom/permutations/06_inverse/enum/0002_given_permutations_in_param/stdout.expected new file mode 100644 index 0000000000..8ca07a3941 --- /dev/null +++ b/tests/custom/permutations/06_inverse/enum/0002_given_permutations_in_param/stdout.expected @@ -0,0 +1,13 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime permutation.param +Savile Row: model000001.eprime permutation2.param +Copying solution to: permutation-permutation.solution +Copying solution to: permutation-permutation2.solution +language Essence 1.3 + +letting b be false +language Essence 1.3 + +letting b be true diff --git a/tests/custom/permutations/06_inverse/enum/0003_given_equal_letting/permutation.essence b/tests/custom/permutations/06_inverse/enum/0003_given_equal_letting/permutation.essence new file mode 100644 index 0000000000..0ffbd5a5be --- /dev/null +++ b/tests/custom/permutations/06_inverse/enum/0003_given_equal_letting/permutation.essence @@ -0,0 +1,9 @@ +letting n be new type enum {E1,E2,E3,E4} + +given p : permutation of n +letting q be permutation((E1,E2,E4)) + +find b : bool + +such that b = inverse(p,q) + diff --git a/tests/custom/permutations/06_inverse/enum/0003_given_equal_letting/permutation.param b/tests/custom/permutations/06_inverse/enum/0003_given_equal_letting/permutation.param new file mode 100644 index 0000000000..19349bb872 --- /dev/null +++ b/tests/custom/permutations/06_inverse/enum/0003_given_equal_letting/permutation.param @@ -0,0 +1 @@ +letting p be permutation((E1,E3,E4)) diff --git a/tests/custom/permutations/06_inverse/enum/0003_given_equal_letting/permutation2.essence b/tests/custom/permutations/06_inverse/enum/0003_given_equal_letting/permutation2.essence new file mode 100644 index 0000000000..6ff41cc29d --- /dev/null +++ b/tests/custom/permutations/06_inverse/enum/0003_given_equal_letting/permutation2.essence @@ -0,0 +1 @@ +letting p be permutation((E1,E4,E2)) diff --git a/tests/custom/permutations/06_inverse/enum/0003_given_equal_letting/run.sh b/tests/custom/permutations/06_inverse/enum/0003_given_equal_letting/run.sh new file mode 100755 index 0000000000..9dc67e67f5 --- /dev/null +++ b/tests/custom/permutations/06_inverse/enum/0003_given_equal_letting/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence *.param +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/06_inverse/enum/0003_given_equal_letting/stdout.expected b/tests/custom/permutations/06_inverse/enum/0003_given_equal_letting/stdout.expected new file mode 100644 index 0000000000..f8cb0c5eb2 --- /dev/null +++ b/tests/custom/permutations/06_inverse/enum/0003_given_equal_letting/stdout.expected @@ -0,0 +1,13 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime permutation2.essence +Savile Row: model000001.eprime permutation.param +Copying solution to: permutation-permutation2.solution +Copying solution to: permutation-permutation.solution +language Essence 1.3 + +letting b be false +language Essence 1.3 + +letting b be true diff --git a/tests/custom/permutations/06_inverse/enum/0004_letting_equal_given/permutation.essence b/tests/custom/permutations/06_inverse/enum/0004_letting_equal_given/permutation.essence new file mode 100644 index 0000000000..c2c2efa328 --- /dev/null +++ b/tests/custom/permutations/06_inverse/enum/0004_letting_equal_given/permutation.essence @@ -0,0 +1,9 @@ +letting n be new type enum {E1,E2,E3,E4} + +given p : permutation of n +letting q be permutation((E1,E2,E4)) + +find b : bool + +such that b = inverse(p,q) + diff --git a/tests/custom/permutations/06_inverse/enum/0004_letting_equal_given/permutation.param b/tests/custom/permutations/06_inverse/enum/0004_letting_equal_given/permutation.param new file mode 100644 index 0000000000..19349bb872 --- /dev/null +++ b/tests/custom/permutations/06_inverse/enum/0004_letting_equal_given/permutation.param @@ -0,0 +1 @@ +letting p be permutation((E1,E3,E4)) diff --git a/tests/custom/permutations/06_inverse/enum/0004_letting_equal_given/permutation2.param b/tests/custom/permutations/06_inverse/enum/0004_letting_equal_given/permutation2.param new file mode 100644 index 0000000000..6ff41cc29d --- /dev/null +++ b/tests/custom/permutations/06_inverse/enum/0004_letting_equal_given/permutation2.param @@ -0,0 +1 @@ +letting p be permutation((E1,E4,E2)) diff --git a/tests/custom/permutations/06_inverse/enum/0004_letting_equal_given/run.sh b/tests/custom/permutations/06_inverse/enum/0004_letting_equal_given/run.sh new file mode 100755 index 0000000000..9dc67e67f5 --- /dev/null +++ b/tests/custom/permutations/06_inverse/enum/0004_letting_equal_given/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence *.param +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/06_inverse/enum/0004_letting_equal_given/stdout.expected b/tests/custom/permutations/06_inverse/enum/0004_letting_equal_given/stdout.expected new file mode 100644 index 0000000000..8ca07a3941 --- /dev/null +++ b/tests/custom/permutations/06_inverse/enum/0004_letting_equal_given/stdout.expected @@ -0,0 +1,13 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime permutation.param +Savile Row: model000001.eprime permutation2.param +Copying solution to: permutation-permutation.solution +Copying solution to: permutation-permutation2.solution +language Essence 1.3 + +letting b be false +language Essence 1.3 + +letting b be true diff --git a/tests/custom/permutations/06_inverse/enum/0005_find_eq_find/permutation.essence b/tests/custom/permutations/06_inverse/enum/0005_find_eq_find/permutation.essence new file mode 100644 index 0000000000..5935904bc6 --- /dev/null +++ b/tests/custom/permutations/06_inverse/enum/0005_find_eq_find/permutation.essence @@ -0,0 +1,5 @@ +letting n be new type enum {E1,E2,E3,E4} +find p : permutation of n +find q : permutation of n + +such that inverse(p,q) diff --git a/tests/custom/permutations/06_inverse/enum/0005_find_eq_find/run.sh b/tests/custom/permutations/06_inverse/enum/0005_find_eq_find/run.sh new file mode 100755 index 0000000000..3c60e3f90e --- /dev/null +++ b/tests/custom/permutations/06_inverse/enum/0005_find_eq_find/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence --number-of-solutions=10 +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/06_inverse/enum/0005_find_eq_find/stdout.expected b/tests/custom/permutations/06_inverse/enum/0005_find_eq_find/stdout.expected new file mode 100644 index 0000000000..f18ecd5016 --- /dev/null +++ b/tests/custom/permutations/06_inverse/enum/0005_find_eq_find/stdout.expected @@ -0,0 +1,54 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Copying solution to: permutation-000001.solution +Copying solution to: permutation-000002.solution +Copying solution to: permutation-000003.solution +Copying solution to: permutation-000004.solution +Copying solution to: permutation-000005.solution +Copying solution to: permutation-000006.solution +Copying solution to: permutation-000007.solution +Copying solution to: permutation-000008.solution +Copying solution to: permutation-000009.solution +Copying solution to: permutation-000010.solution +language Essence 1.3 + +letting p be permutation() +letting q be permutation() +language Essence 1.3 + +letting p be permutation((E3, E4)) +letting q be permutation((E3, E4)) +language Essence 1.3 + +letting p be permutation((E2, E3)) +letting q be permutation((E2, E3)) +language Essence 1.3 + +letting p be permutation((E2, E3, E4)) +letting q be permutation((E2, E4, E3)) +language Essence 1.3 + +letting p be permutation((E2, E4, E3)) +letting q be permutation((E2, E3, E4)) +language Essence 1.3 + +letting p be permutation((E2, E4)) +letting q be permutation((E2, E4)) +language Essence 1.3 + +letting p be permutation((E1, E2)) +letting q be permutation((E1, E2)) +language Essence 1.3 + +letting p be permutation((E1, E2), (E3, E4)) +letting q be permutation((E1, E2), (E3, E4)) +language Essence 1.3 + +letting p be permutation((E1, E2, E3)) +letting q be permutation((E1, E3, E2)) +language Essence 1.3 + +letting p be permutation((E1, E2, E3, E4)) +letting q be permutation((E1, E4, E3, E2)) diff --git a/tests/custom/permutations/06_inverse/int/0001_given_permutations_in_param/permutation.essence b/tests/custom/permutations/06_inverse/int/0001_given_permutations_in_param/permutation.essence new file mode 100644 index 0000000000..c3ad2db985 --- /dev/null +++ b/tests/custom/permutations/06_inverse/int/0001_given_permutations_in_param/permutation.essence @@ -0,0 +1,9 @@ +letting n be 4 + +given p : permutation of int(1..n) +given q : permutation of int(1..n) + +find b : bool + +such that b = inverse(p,q) + diff --git a/tests/custom/permutations/06_inverse/int/0001_given_permutations_in_param/permutation.param b/tests/custom/permutations/06_inverse/int/0001_given_permutations_in_param/permutation.param new file mode 100644 index 0000000000..98b582712a --- /dev/null +++ b/tests/custom/permutations/06_inverse/int/0001_given_permutations_in_param/permutation.param @@ -0,0 +1,2 @@ +letting p be permutation((1,3,4)) +letting q be permutation((1,3,4)) diff --git a/tests/custom/permutations/06_inverse/int/0001_given_permutations_in_param/run.sh b/tests/custom/permutations/06_inverse/int/0001_given_permutations_in_param/run.sh new file mode 100755 index 0000000000..9dc67e67f5 --- /dev/null +++ b/tests/custom/permutations/06_inverse/int/0001_given_permutations_in_param/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence *.param +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/06_inverse/int/0001_given_permutations_in_param/stdout.expected b/tests/custom/permutations/06_inverse/int/0001_given_permutations_in_param/stdout.expected new file mode 100644 index 0000000000..1cc90d46bc --- /dev/null +++ b/tests/custom/permutations/06_inverse/int/0001_given_permutations_in_param/stdout.expected @@ -0,0 +1,8 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime permutation.param +Copying solution to: permutation-permutation.solution +language Essence 1.3 + +letting b be false diff --git a/tests/custom/permutations/06_inverse/int/0002_given_permutations_in_param/permutation.essence b/tests/custom/permutations/06_inverse/int/0002_given_permutations_in_param/permutation.essence new file mode 100644 index 0000000000..c3ad2db985 --- /dev/null +++ b/tests/custom/permutations/06_inverse/int/0002_given_permutations_in_param/permutation.essence @@ -0,0 +1,9 @@ +letting n be 4 + +given p : permutation of int(1..n) +given q : permutation of int(1..n) + +find b : bool + +such that b = inverse(p,q) + diff --git a/tests/custom/permutations/06_inverse/int/0002_given_permutations_in_param/permutation.param b/tests/custom/permutations/06_inverse/int/0002_given_permutations_in_param/permutation.param new file mode 100644 index 0000000000..a58ae460a2 --- /dev/null +++ b/tests/custom/permutations/06_inverse/int/0002_given_permutations_in_param/permutation.param @@ -0,0 +1,2 @@ +letting p be permutation((1,3,4)) +letting q be permutation((1,2,4)) diff --git a/tests/custom/permutations/06_inverse/int/0002_given_permutations_in_param/run.sh b/tests/custom/permutations/06_inverse/int/0002_given_permutations_in_param/run.sh new file mode 100755 index 0000000000..9dc67e67f5 --- /dev/null +++ b/tests/custom/permutations/06_inverse/int/0002_given_permutations_in_param/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence *.param +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/06_inverse/int/0002_given_permutations_in_param/stdout.expected b/tests/custom/permutations/06_inverse/int/0002_given_permutations_in_param/stdout.expected new file mode 100644 index 0000000000..1cc90d46bc --- /dev/null +++ b/tests/custom/permutations/06_inverse/int/0002_given_permutations_in_param/stdout.expected @@ -0,0 +1,8 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime permutation.param +Copying solution to: permutation-permutation.solution +language Essence 1.3 + +letting b be false diff --git a/tests/custom/permutations/06_inverse/int/0003_given_equal_letting/permutation.essence b/tests/custom/permutations/06_inverse/int/0003_given_equal_letting/permutation.essence new file mode 100644 index 0000000000..a2c68d1e7c --- /dev/null +++ b/tests/custom/permutations/06_inverse/int/0003_given_equal_letting/permutation.essence @@ -0,0 +1,9 @@ +letting n be 4 + +given p : permutation of int(1..n) +letting q be permutation((1,2,4)) + +find b : bool + +such that b = inverse(p,q) + diff --git a/tests/custom/permutations/06_inverse/int/0003_given_equal_letting/permutation.param b/tests/custom/permutations/06_inverse/int/0003_given_equal_letting/permutation.param new file mode 100644 index 0000000000..8a8c516801 --- /dev/null +++ b/tests/custom/permutations/06_inverse/int/0003_given_equal_letting/permutation.param @@ -0,0 +1 @@ +letting p be permutation((1,3,4)) diff --git a/tests/custom/permutations/06_inverse/int/0003_given_equal_letting/run.sh b/tests/custom/permutations/06_inverse/int/0003_given_equal_letting/run.sh new file mode 100755 index 0000000000..9dc67e67f5 --- /dev/null +++ b/tests/custom/permutations/06_inverse/int/0003_given_equal_letting/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence *.param +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/06_inverse/int/0003_given_equal_letting/stdout.expected b/tests/custom/permutations/06_inverse/int/0003_given_equal_letting/stdout.expected new file mode 100644 index 0000000000..1cc90d46bc --- /dev/null +++ b/tests/custom/permutations/06_inverse/int/0003_given_equal_letting/stdout.expected @@ -0,0 +1,8 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime permutation.param +Copying solution to: permutation-permutation.solution +language Essence 1.3 + +letting b be false diff --git a/tests/custom/permutations/06_inverse/int/0004_letting_equal_given/permutation.essence b/tests/custom/permutations/06_inverse/int/0004_letting_equal_given/permutation.essence new file mode 100644 index 0000000000..4c40218347 --- /dev/null +++ b/tests/custom/permutations/06_inverse/int/0004_letting_equal_given/permutation.essence @@ -0,0 +1,9 @@ +letting n be 4 + +given p : permutation of int(1..n) +letting q be permutation((1,2,4)) + +find b : bool + +such that b = inverse(p,q) + diff --git a/tests/custom/permutations/06_inverse/int/0004_letting_equal_given/permutation.param b/tests/custom/permutations/06_inverse/int/0004_letting_equal_given/permutation.param new file mode 100644 index 0000000000..8a8c516801 --- /dev/null +++ b/tests/custom/permutations/06_inverse/int/0004_letting_equal_given/permutation.param @@ -0,0 +1 @@ +letting p be permutation((1,3,4)) diff --git a/tests/custom/permutations/06_inverse/int/0004_letting_equal_given/permutation2.param b/tests/custom/permutations/06_inverse/int/0004_letting_equal_given/permutation2.param new file mode 100644 index 0000000000..6348d16d1d --- /dev/null +++ b/tests/custom/permutations/06_inverse/int/0004_letting_equal_given/permutation2.param @@ -0,0 +1 @@ +letting p be permutation((1,4,2)) diff --git a/tests/custom/permutations/06_inverse/int/0004_letting_equal_given/run.sh b/tests/custom/permutations/06_inverse/int/0004_letting_equal_given/run.sh new file mode 100755 index 0000000000..9dc67e67f5 --- /dev/null +++ b/tests/custom/permutations/06_inverse/int/0004_letting_equal_given/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence *.param +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/06_inverse/int/0004_letting_equal_given/stdout.expected b/tests/custom/permutations/06_inverse/int/0004_letting_equal_given/stdout.expected new file mode 100644 index 0000000000..8ca07a3941 --- /dev/null +++ b/tests/custom/permutations/06_inverse/int/0004_letting_equal_given/stdout.expected @@ -0,0 +1,13 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime permutation.param +Savile Row: model000001.eprime permutation2.param +Copying solution to: permutation-permutation.solution +Copying solution to: permutation-permutation2.solution +language Essence 1.3 + +letting b be false +language Essence 1.3 + +letting b be true diff --git a/tests/custom/permutations/06_inverse/int/0005_find_eq_find/permutation.essence b/tests/custom/permutations/06_inverse/int/0005_find_eq_find/permutation.essence new file mode 100644 index 0000000000..31fede5d60 --- /dev/null +++ b/tests/custom/permutations/06_inverse/int/0005_find_eq_find/permutation.essence @@ -0,0 +1,4 @@ +find p : permutation of int(1..4) +find q : permutation of int(1..4) + +such that inverse(p,q) diff --git a/tests/custom/permutations/06_inverse/int/0005_find_eq_find/run.sh b/tests/custom/permutations/06_inverse/int/0005_find_eq_find/run.sh new file mode 100755 index 0000000000..3c60e3f90e --- /dev/null +++ b/tests/custom/permutations/06_inverse/int/0005_find_eq_find/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence --number-of-solutions=10 +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/06_inverse/int/0005_find_eq_find/stdout.expected b/tests/custom/permutations/06_inverse/int/0005_find_eq_find/stdout.expected new file mode 100644 index 0000000000..a1b5092b13 --- /dev/null +++ b/tests/custom/permutations/06_inverse/int/0005_find_eq_find/stdout.expected @@ -0,0 +1,54 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Copying solution to: permutation-000001.solution +Copying solution to: permutation-000002.solution +Copying solution to: permutation-000003.solution +Copying solution to: permutation-000004.solution +Copying solution to: permutation-000005.solution +Copying solution to: permutation-000006.solution +Copying solution to: permutation-000007.solution +Copying solution to: permutation-000008.solution +Copying solution to: permutation-000009.solution +Copying solution to: permutation-000010.solution +language Essence 1.3 + +letting p be permutation() +letting q be permutation() +language Essence 1.3 + +letting p be permutation((3, 4)) +letting q be permutation((3, 4)) +language Essence 1.3 + +letting p be permutation((2, 3)) +letting q be permutation((2, 3)) +language Essence 1.3 + +letting p be permutation((2, 3, 4)) +letting q be permutation((2, 4, 3)) +language Essence 1.3 + +letting p be permutation((2, 4, 3)) +letting q be permutation((2, 3, 4)) +language Essence 1.3 + +letting p be permutation((2, 4)) +letting q be permutation((2, 4)) +language Essence 1.3 + +letting p be permutation((1, 2)) +letting q be permutation((1, 2)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4)) +letting q be permutation((1, 2), (3, 4)) +language Essence 1.3 + +letting p be permutation((1, 2, 3)) +letting q be permutation((1, 3, 2)) +language Essence 1.3 + +letting p be permutation((1, 2, 3, 4)) +letting q be permutation((1, 4, 3, 2)) diff --git a/tests/custom/permutations/06_inverse/runthese.sh b/tests/custom/permutations/06_inverse/runthese.sh new file mode 100644 index 0000000000..7a109bc890 --- /dev/null +++ b/tests/custom/permutations/06_inverse/runthese.sh @@ -0,0 +1,2 @@ +stack install +stack test --test-arguments "-p custom.permutations.06_inverse" diff --git a/tests/custom/permutations/06_inverse/unnamed/0005_find_inverse_find/permutation.essence b/tests/custom/permutations/06_inverse/unnamed/0005_find_inverse_find/permutation.essence new file mode 100644 index 0000000000..1f8e689b2e --- /dev/null +++ b/tests/custom/permutations/06_inverse/unnamed/0005_find_inverse_find/permutation.essence @@ -0,0 +1,8 @@ +letting n be new type of size 4 + +find p : permutation of n +find q : permutation of n + +such that inverse(q, p) + + diff --git a/tests/custom/permutations/06_inverse/unnamed/0005_find_inverse_find/run.sh b/tests/custom/permutations/06_inverse/unnamed/0005_find_inverse_find/run.sh new file mode 100755 index 0000000000..3c60e3f90e --- /dev/null +++ b/tests/custom/permutations/06_inverse/unnamed/0005_find_inverse_find/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence --number-of-solutions=10 +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/06_inverse/unnamed/0005_find_inverse_find/stdout.expected b/tests/custom/permutations/06_inverse/unnamed/0005_find_inverse_find/stdout.expected new file mode 100644 index 0000000000..453e3e80ef --- /dev/null +++ b/tests/custom/permutations/06_inverse/unnamed/0005_find_inverse_find/stdout.expected @@ -0,0 +1,64 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Copying solution to: permutation-000001.solution +Copying solution to: permutation-000002.solution +Copying solution to: permutation-000003.solution +Copying solution to: permutation-000004.solution +Copying solution to: permutation-000005.solution +Copying solution to: permutation-000006.solution +Copying solution to: permutation-000007.solution +Copying solution to: permutation-000008.solution +Copying solution to: permutation-000009.solution +Copying solution to: permutation-000010.solution +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation() +letting q be permutation() +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_3, n_4)) +letting q be permutation((n_3, n_4)) +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_2, n_3)) +letting q be permutation((n_2, n_3)) +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_2, n_3, n_4)) +letting q be permutation((n_2, n_4, n_3)) +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_2, n_4, n_3)) +letting q be permutation((n_2, n_3, n_4)) +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_2, n_4)) +letting q be permutation((n_2, n_4)) +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_1, n_2)) +letting q be permutation((n_1, n_2)) +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_1, n_2), (n_3, n_4)) +letting q be permutation((n_1, n_2), (n_3, n_4)) +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_1, n_2, n_3)) +letting q be permutation((n_1, n_3, n_2)) +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_1, n_2, n_3, n_4)) +letting q be permutation((n_1, n_4, n_3, n_2)) diff --git a/tests/custom/permutations/README.md b/tests/custom/permutations/README.md index 13da9b61f9..02a1ad3d54 100644 --- a/tests/custom/permutations/README.md +++ b/tests/custom/permutations/README.md @@ -26,3 +26,5 @@ Tests permutations in generator of a comprehension Tests equality on permutations - basic equality for find, letting, given - tests [|p| = i | p <- sp] where sp is a set of permutations + +## 06 inverse From d3cdd0a990a6b970b99158a8e1406f48fc9b9686 Mon Sep 17 00:00:00 2001 From: Fraser Dunlop Date: Tue, 11 Dec 2018 21:25:47 +0000 Subject: [PATCH 050/229] compose tests --- src/Conjure/Rules/Horizontal/Permutation.hs | 36 +++++---- src/Conjure/UI/Model.hs | 3 +- .../permutation.essence | 11 +++ .../permutation.param | 4 + .../permutation2.essence | 4 + .../permutation3.essence | 4 + .../0001_given_permutations_in_param/run.sh | 3 + .../stdout.expected | 18 +++++ .../permutation.essence | 11 +++ .../0002_given_and_letting/permutation.param | 3 + .../enum/0002_given_and_letting/run.sh | 3 + .../0002_given_and_letting/stdout.expected | 8 ++ .../0003_letting_and_find/permutation.essence | 9 +++ .../0003_letting_and_find/permutation.param | 2 + .../0003_letting_and_find/permutation2.param | 2 + .../enum/0003_letting_and_find/run.sh | 3 + .../0003_letting_and_find/stdout.expected | 13 ++++ .../0004_find_and_find/permutation.essence | 7 ++ .../enum/0004_find_and_find/permutation.param | 2 + .../07_compose/enum/0004_find_and_find/run.sh | 3 + .../enum/0004_find_and_find/stdout.expected | 54 ++++++++++++++ .../permutation.essence | 11 +++ .../permutation.param | 4 + .../permutation2.essence | 4 + .../permutation3.essence | 4 + .../0001_given_permutations_in_param/run.sh | 3 + .../stdout.expected | 18 +++++ .../permutation.essence | 11 +++ .../0002_given_and_letting/permutation.param | 3 + .../int/0002_given_and_letting/run.sh | 3 + .../0002_given_and_letting/stdout.expected | 8 ++ .../0003_letting_and_find/permutation.essence | 9 +++ .../0003_letting_and_find/permutation.param | 2 + .../0003_letting_and_find/permutation2.param | 2 + .../int/0003_letting_and_find/run.sh | 3 + .../int/0003_letting_and_find/stdout.expected | 13 ++++ .../0004_find_and_find/permutation.essence | 6 ++ .../int/0004_find_and_find/permutation.param | 2 + .../07_compose/int/0004_find_and_find/run.sh | 3 + .../int/0004_find_and_find/stdout.expected | 54 ++++++++++++++ .../permutations/07_compose/runthese.sh | 2 + .../0004_find_and_find/permutation.essence | 9 +++ .../unnamed/0004_find_and_find/run.sh | 3 + .../0004_find_and_find/stdout.expected | 74 +++++++++++++++++++ tests/custom/permutations/README.md | 4 + 45 files changed, 437 insertions(+), 21 deletions(-) create mode 100644 tests/custom/permutations/07_compose/enum/0001_given_permutations_in_param/permutation.essence create mode 100644 tests/custom/permutations/07_compose/enum/0001_given_permutations_in_param/permutation.param create mode 100644 tests/custom/permutations/07_compose/enum/0001_given_permutations_in_param/permutation2.essence create mode 100644 tests/custom/permutations/07_compose/enum/0001_given_permutations_in_param/permutation3.essence create mode 100755 tests/custom/permutations/07_compose/enum/0001_given_permutations_in_param/run.sh create mode 100644 tests/custom/permutations/07_compose/enum/0001_given_permutations_in_param/stdout.expected create mode 100644 tests/custom/permutations/07_compose/enum/0002_given_and_letting/permutation.essence create mode 100644 tests/custom/permutations/07_compose/enum/0002_given_and_letting/permutation.param create mode 100755 tests/custom/permutations/07_compose/enum/0002_given_and_letting/run.sh create mode 100644 tests/custom/permutations/07_compose/enum/0002_given_and_letting/stdout.expected create mode 100644 tests/custom/permutations/07_compose/enum/0003_letting_and_find/permutation.essence create mode 100644 tests/custom/permutations/07_compose/enum/0003_letting_and_find/permutation.param create mode 100644 tests/custom/permutations/07_compose/enum/0003_letting_and_find/permutation2.param create mode 100755 tests/custom/permutations/07_compose/enum/0003_letting_and_find/run.sh create mode 100644 tests/custom/permutations/07_compose/enum/0003_letting_and_find/stdout.expected create mode 100644 tests/custom/permutations/07_compose/enum/0004_find_and_find/permutation.essence create mode 100644 tests/custom/permutations/07_compose/enum/0004_find_and_find/permutation.param create mode 100755 tests/custom/permutations/07_compose/enum/0004_find_and_find/run.sh create mode 100644 tests/custom/permutations/07_compose/enum/0004_find_and_find/stdout.expected create mode 100644 tests/custom/permutations/07_compose/int/0001_given_permutations_in_param/permutation.essence create mode 100644 tests/custom/permutations/07_compose/int/0001_given_permutations_in_param/permutation.param create mode 100644 tests/custom/permutations/07_compose/int/0001_given_permutations_in_param/permutation2.essence create mode 100644 tests/custom/permutations/07_compose/int/0001_given_permutations_in_param/permutation3.essence create mode 100755 tests/custom/permutations/07_compose/int/0001_given_permutations_in_param/run.sh create mode 100644 tests/custom/permutations/07_compose/int/0001_given_permutations_in_param/stdout.expected create mode 100644 tests/custom/permutations/07_compose/int/0002_given_and_letting/permutation.essence create mode 100644 tests/custom/permutations/07_compose/int/0002_given_and_letting/permutation.param create mode 100755 tests/custom/permutations/07_compose/int/0002_given_and_letting/run.sh create mode 100644 tests/custom/permutations/07_compose/int/0002_given_and_letting/stdout.expected create mode 100644 tests/custom/permutations/07_compose/int/0003_letting_and_find/permutation.essence create mode 100644 tests/custom/permutations/07_compose/int/0003_letting_and_find/permutation.param create mode 100644 tests/custom/permutations/07_compose/int/0003_letting_and_find/permutation2.param create mode 100755 tests/custom/permutations/07_compose/int/0003_letting_and_find/run.sh create mode 100644 tests/custom/permutations/07_compose/int/0003_letting_and_find/stdout.expected create mode 100644 tests/custom/permutations/07_compose/int/0004_find_and_find/permutation.essence create mode 100644 tests/custom/permutations/07_compose/int/0004_find_and_find/permutation.param create mode 100755 tests/custom/permutations/07_compose/int/0004_find_and_find/run.sh create mode 100644 tests/custom/permutations/07_compose/int/0004_find_and_find/stdout.expected create mode 100644 tests/custom/permutations/07_compose/runthese.sh create mode 100644 tests/custom/permutations/07_compose/unnamed/0004_find_and_find/permutation.essence create mode 100755 tests/custom/permutations/07_compose/unnamed/0004_find_and_find/run.sh create mode 100644 tests/custom/permutations/07_compose/unnamed/0004_find_and_find/stdout.expected diff --git a/src/Conjure/Rules/Horizontal/Permutation.hs b/src/Conjure/Rules/Horizontal/Permutation.hs index 04e13b986b..805d6395ed 100644 --- a/src/Conjure/Rules/Horizontal/Permutation.hs +++ b/src/Conjure/Rules/Horizontal/Permutation.hs @@ -150,6 +150,23 @@ rule_Permutation_Inverse = "permutation-inverse" `namedRule` theRule where ) theRule _ = na "rule_Permutation_Inverse" +rule_Compose :: Rule +rule_Compose = "permutation-compose" `namedRule` theRule where + theRule [essence| image(compose(&g, &h),&i) |] = do + TypePermutation innerG <- typeOf g + TypePermutation innerH <- typeOf g + typeI <- typeOf i + if typesUnify [innerG, innerH, typeI] + then return + ( "Horizontal rule for permutation composition" + , do + return [essence| image(&g, image(&h,&i)) |] + ) + else na "rule_Compose" + theRule _ = na "rule_Compose" + + + @@ -211,22 +228,3 @@ rule_Permutation_Inverse = "permutation-inverse" `namedRule` theRule where -- theRule _ = na "rule_Image_Literal" -- --- --- ---rule_Compose :: Rule ---rule_Compose = "permutation-compose{rule_Compose}" `namedRule` theRule where --- theRule [essence| image(compose(&g, &h),&i) |] = do --- TypePermutation innerG <- typeOf g --- TypePermutation innerH <- typeOf g --- typeI <- typeOf i --- if typesUnify [innerG, innerH, typeI] --- then return --- ( "Horizontal rule for permutation composition/application" --- , do --- return [essence| image(&g, image(&h,&i)) |] --- ) --- else na "rule_Compose" --- theRule _ = na "rule_Compose" --- --- - diff --git a/src/Conjure/UI/Model.hs b/src/Conjure/UI/Model.hs index 1744140828..3cfd5f3785 100644 --- a/src/Conjure/UI/Model.hs +++ b/src/Conjure/UI/Model.hs @@ -1211,11 +1211,10 @@ horizontalRules = , Horizontal.Permutation.rule_Image_Literal , Horizontal.Permutation.rule_In , Horizontal.Permutation.rule_Permutation_Inverse + , Horizontal.Permutation.rule_Compose -- , Horizontal.Permutation.rule_Image_Literal_Comprehension --- , Horizontal.Permutation.rule_Compose - , Horizontal.Set.rule_Comprehension_Literal , Horizontal.Set.rule_Eq diff --git a/tests/custom/permutations/07_compose/enum/0001_given_permutations_in_param/permutation.essence b/tests/custom/permutations/07_compose/enum/0001_given_permutations_in_param/permutation.essence new file mode 100644 index 0000000000..6b6821cba0 --- /dev/null +++ b/tests/custom/permutations/07_compose/enum/0001_given_permutations_in_param/permutation.essence @@ -0,0 +1,11 @@ +letting n be new type enum {E0,E1,E2,E3,E4} + +given p : permutation of n +given q : permutation of n +given i : n +given j : n + +find b : bool + +such that b = (j = image(compose(p,q),i)) + diff --git a/tests/custom/permutations/07_compose/enum/0001_given_permutations_in_param/permutation.param b/tests/custom/permutations/07_compose/enum/0001_given_permutations_in_param/permutation.param new file mode 100644 index 0000000000..2da4095c9a --- /dev/null +++ b/tests/custom/permutations/07_compose/enum/0001_given_permutations_in_param/permutation.param @@ -0,0 +1,4 @@ +letting p be permutation((E1,E3,E4)) +letting q be permutation((E1,E3,E4)) +letting i be E0 +letting j be E0 diff --git a/tests/custom/permutations/07_compose/enum/0001_given_permutations_in_param/permutation2.essence b/tests/custom/permutations/07_compose/enum/0001_given_permutations_in_param/permutation2.essence new file mode 100644 index 0000000000..c0d49009c5 --- /dev/null +++ b/tests/custom/permutations/07_compose/enum/0001_given_permutations_in_param/permutation2.essence @@ -0,0 +1,4 @@ +letting p be permutation((E1,E3,E4)) +letting q be permutation((E1,E3,E4)) +letting i be E1 +letting j be E4 diff --git a/tests/custom/permutations/07_compose/enum/0001_given_permutations_in_param/permutation3.essence b/tests/custom/permutations/07_compose/enum/0001_given_permutations_in_param/permutation3.essence new file mode 100644 index 0000000000..13bb57fa19 --- /dev/null +++ b/tests/custom/permutations/07_compose/enum/0001_given_permutations_in_param/permutation3.essence @@ -0,0 +1,4 @@ +letting p be permutation((E1,E3,E4)) +letting q be permutation((E1,E3,E4)) +letting i be E3 +letting j be E1 diff --git a/tests/custom/permutations/07_compose/enum/0001_given_permutations_in_param/run.sh b/tests/custom/permutations/07_compose/enum/0001_given_permutations_in_param/run.sh new file mode 100755 index 0000000000..9dc67e67f5 --- /dev/null +++ b/tests/custom/permutations/07_compose/enum/0001_given_permutations_in_param/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence *.param +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/07_compose/enum/0001_given_permutations_in_param/stdout.expected b/tests/custom/permutations/07_compose/enum/0001_given_permutations_in_param/stdout.expected new file mode 100644 index 0000000000..5034947736 --- /dev/null +++ b/tests/custom/permutations/07_compose/enum/0001_given_permutations_in_param/stdout.expected @@ -0,0 +1,18 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime permutation2.essence +Savile Row: model000001.eprime permutation3.essence +Savile Row: model000001.eprime permutation.param +Copying solution to: permutation-permutation2.solution +Copying solution to: permutation-permutation3.solution +Copying solution to: permutation-permutation.solution +language Essence 1.3 + +letting b be true +language Essence 1.3 + +letting b be true +language Essence 1.3 + +letting b be true diff --git a/tests/custom/permutations/07_compose/enum/0002_given_and_letting/permutation.essence b/tests/custom/permutations/07_compose/enum/0002_given_and_letting/permutation.essence new file mode 100644 index 0000000000..ab4b5a746c --- /dev/null +++ b/tests/custom/permutations/07_compose/enum/0002_given_and_letting/permutation.essence @@ -0,0 +1,11 @@ +letting n be new type enum {E1,E2,E3,E4} + +given p : permutation of n +letting q be permutation((E1,E2,E4)) +given i : n +given j : n + +find b : bool + +such that b = (j = image(compose(p,q),i)) + diff --git a/tests/custom/permutations/07_compose/enum/0002_given_and_letting/permutation.param b/tests/custom/permutations/07_compose/enum/0002_given_and_letting/permutation.param new file mode 100644 index 0000000000..4ce832b07e --- /dev/null +++ b/tests/custom/permutations/07_compose/enum/0002_given_and_letting/permutation.param @@ -0,0 +1,3 @@ +letting p be permutation((E1,E3,E4)) +letting i be E1 +letting j be E2 diff --git a/tests/custom/permutations/07_compose/enum/0002_given_and_letting/run.sh b/tests/custom/permutations/07_compose/enum/0002_given_and_letting/run.sh new file mode 100755 index 0000000000..9dc67e67f5 --- /dev/null +++ b/tests/custom/permutations/07_compose/enum/0002_given_and_letting/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence *.param +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/07_compose/enum/0002_given_and_letting/stdout.expected b/tests/custom/permutations/07_compose/enum/0002_given_and_letting/stdout.expected new file mode 100644 index 0000000000..901f2ae574 --- /dev/null +++ b/tests/custom/permutations/07_compose/enum/0002_given_and_letting/stdout.expected @@ -0,0 +1,8 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime permutation.param +Copying solution to: permutation-permutation.solution +language Essence 1.3 + +letting b be true diff --git a/tests/custom/permutations/07_compose/enum/0003_letting_and_find/permutation.essence b/tests/custom/permutations/07_compose/enum/0003_letting_and_find/permutation.essence new file mode 100644 index 0000000000..04fefffea8 --- /dev/null +++ b/tests/custom/permutations/07_compose/enum/0003_letting_and_find/permutation.essence @@ -0,0 +1,9 @@ +letting n be new type enum {E1,E2,E3,E4} + +find p : permutation of n +letting q be permutation((E1,E2,E4)) +given i : n +given j : n + +such that j = image(compose(p,q),i) + diff --git a/tests/custom/permutations/07_compose/enum/0003_letting_and_find/permutation.param b/tests/custom/permutations/07_compose/enum/0003_letting_and_find/permutation.param new file mode 100644 index 0000000000..d2b7d221ac --- /dev/null +++ b/tests/custom/permutations/07_compose/enum/0003_letting_and_find/permutation.param @@ -0,0 +1,2 @@ +letting i be E1 +letting j be E4 diff --git a/tests/custom/permutations/07_compose/enum/0003_letting_and_find/permutation2.param b/tests/custom/permutations/07_compose/enum/0003_letting_and_find/permutation2.param new file mode 100644 index 0000000000..3f9f500e5a --- /dev/null +++ b/tests/custom/permutations/07_compose/enum/0003_letting_and_find/permutation2.param @@ -0,0 +1,2 @@ +letting i be E3 +letting j be E2 diff --git a/tests/custom/permutations/07_compose/enum/0003_letting_and_find/run.sh b/tests/custom/permutations/07_compose/enum/0003_letting_and_find/run.sh new file mode 100755 index 0000000000..9dc67e67f5 --- /dev/null +++ b/tests/custom/permutations/07_compose/enum/0003_letting_and_find/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence *.param +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/07_compose/enum/0003_letting_and_find/stdout.expected b/tests/custom/permutations/07_compose/enum/0003_letting_and_find/stdout.expected new file mode 100644 index 0000000000..5c93b5fa44 --- /dev/null +++ b/tests/custom/permutations/07_compose/enum/0003_letting_and_find/stdout.expected @@ -0,0 +1,13 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime permutation.param +Savile Row: model000001.eprime permutation2.param +Copying solution to: permutation-permutation.solution +Copying solution to: permutation-permutation2.solution +language Essence 1.3 + +letting p be permutation((E2, E4, E3)) +language Essence 1.3 + +letting p be permutation((E2, E3)) diff --git a/tests/custom/permutations/07_compose/enum/0004_find_and_find/permutation.essence b/tests/custom/permutations/07_compose/enum/0004_find_and_find/permutation.essence new file mode 100644 index 0000000000..cd573b1dc5 --- /dev/null +++ b/tests/custom/permutations/07_compose/enum/0004_find_and_find/permutation.essence @@ -0,0 +1,7 @@ +letting n be new type enum {E1,E2,E3,E4} +find p : permutation of n +find q : permutation of n +given i : n +given j : n + +such that j = image(compose(p,q),i) diff --git a/tests/custom/permutations/07_compose/enum/0004_find_and_find/permutation.param b/tests/custom/permutations/07_compose/enum/0004_find_and_find/permutation.param new file mode 100644 index 0000000000..e5ffa00501 --- /dev/null +++ b/tests/custom/permutations/07_compose/enum/0004_find_and_find/permutation.param @@ -0,0 +1,2 @@ +letting i be E4 +letting j be E2 diff --git a/tests/custom/permutations/07_compose/enum/0004_find_and_find/run.sh b/tests/custom/permutations/07_compose/enum/0004_find_and_find/run.sh new file mode 100755 index 0000000000..1c9e6bbde4 --- /dev/null +++ b/tests/custom/permutations/07_compose/enum/0004_find_and_find/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence *.param --number-of-solutions=10 +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/07_compose/enum/0004_find_and_find/stdout.expected b/tests/custom/permutations/07_compose/enum/0004_find_and_find/stdout.expected new file mode 100644 index 0000000000..01b2419221 --- /dev/null +++ b/tests/custom/permutations/07_compose/enum/0004_find_and_find/stdout.expected @@ -0,0 +1,54 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime permutation.param +Copying solution to: permutation-permutation-000001.solution +Copying solution to: permutation-permutation-000002.solution +Copying solution to: permutation-permutation-000003.solution +Copying solution to: permutation-permutation-000004.solution +Copying solution to: permutation-permutation-000005.solution +Copying solution to: permutation-permutation-000006.solution +Copying solution to: permutation-permutation-000007.solution +Copying solution to: permutation-permutation-000008.solution +Copying solution to: permutation-permutation-000009.solution +Copying solution to: permutation-permutation-000010.solution +language Essence 1.3 + +letting p be permutation() +letting q be permutation((E2, E3, E4)) +language Essence 1.3 + +letting p be permutation() +letting q be permutation((E2, E4)) +language Essence 1.3 + +letting p be permutation() +letting q be permutation((E1, E3, E4, E2)) +language Essence 1.3 + +letting p be permutation() +letting q be permutation((E1, E3), (E2, E4)) +language Essence 1.3 + +letting p be permutation() +letting q be permutation((E1, E4, E2)) +language Essence 1.3 + +letting p be permutation() +letting q be permutation((E1, E4, E2, E3)) +language Essence 1.3 + +letting p be permutation((E3, E4)) +letting q be permutation((E2, E3, E4)) +language Essence 1.3 + +letting p be permutation((E3, E4)) +letting q be permutation((E2, E4)) +language Essence 1.3 + +letting p be permutation((E3, E4)) +letting q be permutation((E1, E3, E4, E2)) +language Essence 1.3 + +letting p be permutation((E3, E4)) +letting q be permutation((E1, E3), (E2, E4)) diff --git a/tests/custom/permutations/07_compose/int/0001_given_permutations_in_param/permutation.essence b/tests/custom/permutations/07_compose/int/0001_given_permutations_in_param/permutation.essence new file mode 100644 index 0000000000..6e5bb967bd --- /dev/null +++ b/tests/custom/permutations/07_compose/int/0001_given_permutations_in_param/permutation.essence @@ -0,0 +1,11 @@ +letting n be 4 + +given p : permutation of int(1..n) +given q : permutation of int(1..n) +given i : int(0..5) +given j : int(0..5) + +find b : bool + +such that b = (j = image(compose(p,q),i)) + diff --git a/tests/custom/permutations/07_compose/int/0001_given_permutations_in_param/permutation.param b/tests/custom/permutations/07_compose/int/0001_given_permutations_in_param/permutation.param new file mode 100644 index 0000000000..83dbc0bb11 --- /dev/null +++ b/tests/custom/permutations/07_compose/int/0001_given_permutations_in_param/permutation.param @@ -0,0 +1,4 @@ +letting p be permutation((1,3,4)) +letting q be permutation((1,3,4)) +letting i be 0 +letting j be 0 diff --git a/tests/custom/permutations/07_compose/int/0001_given_permutations_in_param/permutation2.essence b/tests/custom/permutations/07_compose/int/0001_given_permutations_in_param/permutation2.essence new file mode 100644 index 0000000000..1501ce9836 --- /dev/null +++ b/tests/custom/permutations/07_compose/int/0001_given_permutations_in_param/permutation2.essence @@ -0,0 +1,4 @@ +letting p be permutation((1,3,4)) +letting q be permutation((1,3,4)) +letting i be 1 +letting j be 4 diff --git a/tests/custom/permutations/07_compose/int/0001_given_permutations_in_param/permutation3.essence b/tests/custom/permutations/07_compose/int/0001_given_permutations_in_param/permutation3.essence new file mode 100644 index 0000000000..43631bd64d --- /dev/null +++ b/tests/custom/permutations/07_compose/int/0001_given_permutations_in_param/permutation3.essence @@ -0,0 +1,4 @@ +letting p be permutation((1,3,4)) +letting q be permutation((1,3,4)) +letting i be 3 +letting j be 1 diff --git a/tests/custom/permutations/07_compose/int/0001_given_permutations_in_param/run.sh b/tests/custom/permutations/07_compose/int/0001_given_permutations_in_param/run.sh new file mode 100755 index 0000000000..9dc67e67f5 --- /dev/null +++ b/tests/custom/permutations/07_compose/int/0001_given_permutations_in_param/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence *.param +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/07_compose/int/0001_given_permutations_in_param/stdout.expected b/tests/custom/permutations/07_compose/int/0001_given_permutations_in_param/stdout.expected new file mode 100644 index 0000000000..5034947736 --- /dev/null +++ b/tests/custom/permutations/07_compose/int/0001_given_permutations_in_param/stdout.expected @@ -0,0 +1,18 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime permutation2.essence +Savile Row: model000001.eprime permutation3.essence +Savile Row: model000001.eprime permutation.param +Copying solution to: permutation-permutation2.solution +Copying solution to: permutation-permutation3.solution +Copying solution to: permutation-permutation.solution +language Essence 1.3 + +letting b be true +language Essence 1.3 + +letting b be true +language Essence 1.3 + +letting b be true diff --git a/tests/custom/permutations/07_compose/int/0002_given_and_letting/permutation.essence b/tests/custom/permutations/07_compose/int/0002_given_and_letting/permutation.essence new file mode 100644 index 0000000000..e8b28e580b --- /dev/null +++ b/tests/custom/permutations/07_compose/int/0002_given_and_letting/permutation.essence @@ -0,0 +1,11 @@ +letting n be 4 + +given p : permutation of int(1..n) +letting q be permutation((1,2,4)) +given i : int(0..5) +given j : int(0..5) + +find b : bool + +such that b = (j = image(compose(p,q),i)) + diff --git a/tests/custom/permutations/07_compose/int/0002_given_and_letting/permutation.param b/tests/custom/permutations/07_compose/int/0002_given_and_letting/permutation.param new file mode 100644 index 0000000000..5ad6d6df98 --- /dev/null +++ b/tests/custom/permutations/07_compose/int/0002_given_and_letting/permutation.param @@ -0,0 +1,3 @@ +letting p be permutation((1,3,4)) +letting i be 1 +letting j be 2 diff --git a/tests/custom/permutations/07_compose/int/0002_given_and_letting/run.sh b/tests/custom/permutations/07_compose/int/0002_given_and_letting/run.sh new file mode 100755 index 0000000000..9dc67e67f5 --- /dev/null +++ b/tests/custom/permutations/07_compose/int/0002_given_and_letting/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence *.param +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/07_compose/int/0002_given_and_letting/stdout.expected b/tests/custom/permutations/07_compose/int/0002_given_and_letting/stdout.expected new file mode 100644 index 0000000000..901f2ae574 --- /dev/null +++ b/tests/custom/permutations/07_compose/int/0002_given_and_letting/stdout.expected @@ -0,0 +1,8 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime permutation.param +Copying solution to: permutation-permutation.solution +language Essence 1.3 + +letting b be true diff --git a/tests/custom/permutations/07_compose/int/0003_letting_and_find/permutation.essence b/tests/custom/permutations/07_compose/int/0003_letting_and_find/permutation.essence new file mode 100644 index 0000000000..0abee49ad1 --- /dev/null +++ b/tests/custom/permutations/07_compose/int/0003_letting_and_find/permutation.essence @@ -0,0 +1,9 @@ +letting n be 4 + +find p : permutation of int(1..n) +letting q be permutation((1,2,4)) +given i : int(0..5) +given j : int(0..5) + +such that j = image(compose(p,q),i) + diff --git a/tests/custom/permutations/07_compose/int/0003_letting_and_find/permutation.param b/tests/custom/permutations/07_compose/int/0003_letting_and_find/permutation.param new file mode 100644 index 0000000000..dd1fe9cadb --- /dev/null +++ b/tests/custom/permutations/07_compose/int/0003_letting_and_find/permutation.param @@ -0,0 +1,2 @@ +letting i be 1 +letting j be 4 diff --git a/tests/custom/permutations/07_compose/int/0003_letting_and_find/permutation2.param b/tests/custom/permutations/07_compose/int/0003_letting_and_find/permutation2.param new file mode 100644 index 0000000000..a3611e4834 --- /dev/null +++ b/tests/custom/permutations/07_compose/int/0003_letting_and_find/permutation2.param @@ -0,0 +1,2 @@ +letting i be 3 +letting j be 2 diff --git a/tests/custom/permutations/07_compose/int/0003_letting_and_find/run.sh b/tests/custom/permutations/07_compose/int/0003_letting_and_find/run.sh new file mode 100755 index 0000000000..9dc67e67f5 --- /dev/null +++ b/tests/custom/permutations/07_compose/int/0003_letting_and_find/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence *.param +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/07_compose/int/0003_letting_and_find/stdout.expected b/tests/custom/permutations/07_compose/int/0003_letting_and_find/stdout.expected new file mode 100644 index 0000000000..2d74f851e9 --- /dev/null +++ b/tests/custom/permutations/07_compose/int/0003_letting_and_find/stdout.expected @@ -0,0 +1,13 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime permutation.param +Savile Row: model000001.eprime permutation2.param +Copying solution to: permutation-permutation.solution +Copying solution to: permutation-permutation2.solution +language Essence 1.3 + +letting p be permutation((2, 4, 3)) +language Essence 1.3 + +letting p be permutation((2, 3)) diff --git a/tests/custom/permutations/07_compose/int/0004_find_and_find/permutation.essence b/tests/custom/permutations/07_compose/int/0004_find_and_find/permutation.essence new file mode 100644 index 0000000000..e1a334ecc7 --- /dev/null +++ b/tests/custom/permutations/07_compose/int/0004_find_and_find/permutation.essence @@ -0,0 +1,6 @@ +find p : permutation of int(1..4) +find q : permutation of int(1..4) +given i : int(0..5) +given j : int(0..5) + +such that j = image(compose(p,q),i) diff --git a/tests/custom/permutations/07_compose/int/0004_find_and_find/permutation.param b/tests/custom/permutations/07_compose/int/0004_find_and_find/permutation.param new file mode 100644 index 0000000000..c1239958c9 --- /dev/null +++ b/tests/custom/permutations/07_compose/int/0004_find_and_find/permutation.param @@ -0,0 +1,2 @@ +letting i be 4 +letting j be 2 diff --git a/tests/custom/permutations/07_compose/int/0004_find_and_find/run.sh b/tests/custom/permutations/07_compose/int/0004_find_and_find/run.sh new file mode 100755 index 0000000000..1c9e6bbde4 --- /dev/null +++ b/tests/custom/permutations/07_compose/int/0004_find_and_find/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence *.param --number-of-solutions=10 +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/07_compose/int/0004_find_and_find/stdout.expected b/tests/custom/permutations/07_compose/int/0004_find_and_find/stdout.expected new file mode 100644 index 0000000000..313f185cec --- /dev/null +++ b/tests/custom/permutations/07_compose/int/0004_find_and_find/stdout.expected @@ -0,0 +1,54 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime permutation.param +Copying solution to: permutation-permutation-000001.solution +Copying solution to: permutation-permutation-000002.solution +Copying solution to: permutation-permutation-000003.solution +Copying solution to: permutation-permutation-000004.solution +Copying solution to: permutation-permutation-000005.solution +Copying solution to: permutation-permutation-000006.solution +Copying solution to: permutation-permutation-000007.solution +Copying solution to: permutation-permutation-000008.solution +Copying solution to: permutation-permutation-000009.solution +Copying solution to: permutation-permutation-000010.solution +language Essence 1.3 + +letting p be permutation() +letting q be permutation((2, 3, 4)) +language Essence 1.3 + +letting p be permutation() +letting q be permutation((2, 4)) +language Essence 1.3 + +letting p be permutation() +letting q be permutation((1, 3, 4, 2)) +language Essence 1.3 + +letting p be permutation() +letting q be permutation((1, 3), (2, 4)) +language Essence 1.3 + +letting p be permutation() +letting q be permutation((1, 4, 2)) +language Essence 1.3 + +letting p be permutation() +letting q be permutation((1, 4, 2, 3)) +language Essence 1.3 + +letting p be permutation((3, 4)) +letting q be permutation((2, 3, 4)) +language Essence 1.3 + +letting p be permutation((3, 4)) +letting q be permutation((2, 4)) +language Essence 1.3 + +letting p be permutation((3, 4)) +letting q be permutation((1, 3, 4, 2)) +language Essence 1.3 + +letting p be permutation((3, 4)) +letting q be permutation((1, 3), (2, 4)) diff --git a/tests/custom/permutations/07_compose/runthese.sh b/tests/custom/permutations/07_compose/runthese.sh new file mode 100644 index 0000000000..db7212b076 --- /dev/null +++ b/tests/custom/permutations/07_compose/runthese.sh @@ -0,0 +1,2 @@ +stack install +stack test --test-arguments "-p custom.permutations.07_compose" diff --git a/tests/custom/permutations/07_compose/unnamed/0004_find_and_find/permutation.essence b/tests/custom/permutations/07_compose/unnamed/0004_find_and_find/permutation.essence new file mode 100644 index 0000000000..3a5095a6e2 --- /dev/null +++ b/tests/custom/permutations/07_compose/unnamed/0004_find_and_find/permutation.essence @@ -0,0 +1,9 @@ +letting n be new type of size 4 +find p : permutation of n +find q : permutation of n +find i : n + +such that + i = image(compose(p,q),i) + /\ |p| = 4 + /\ |q| = 3 diff --git a/tests/custom/permutations/07_compose/unnamed/0004_find_and_find/run.sh b/tests/custom/permutations/07_compose/unnamed/0004_find_and_find/run.sh new file mode 100755 index 0000000000..3c60e3f90e --- /dev/null +++ b/tests/custom/permutations/07_compose/unnamed/0004_find_and_find/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence --number-of-solutions=10 +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/07_compose/unnamed/0004_find_and_find/stdout.expected b/tests/custom/permutations/07_compose/unnamed/0004_find_and_find/stdout.expected new file mode 100644 index 0000000000..ba284f1627 --- /dev/null +++ b/tests/custom/permutations/07_compose/unnamed/0004_find_and_find/stdout.expected @@ -0,0 +1,74 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Copying solution to: permutation-000001.solution +Copying solution to: permutation-000002.solution +Copying solution to: permutation-000003.solution +Copying solution to: permutation-000004.solution +Copying solution to: permutation-000005.solution +Copying solution to: permutation-000006.solution +Copying solution to: permutation-000007.solution +Copying solution to: permutation-000008.solution +Copying solution to: permutation-000009.solution +Copying solution to: permutation-000010.solution +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting i be n_3 +letting p be permutation((n_1, n_2), (n_3, n_4)) +letting q be permutation((n_2, n_3, n_4)) +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting i be n_4 +letting p be permutation((n_1, n_2), (n_3, n_4)) +letting q be permutation((n_2, n_4, n_3)) +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting i be n_1 +letting p be permutation((n_1, n_2), (n_3, n_4)) +letting q be permutation((n_1, n_2, n_3)) +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting i be n_1 +letting p be permutation((n_1, n_2), (n_3, n_4)) +letting q be permutation((n_1, n_2, n_4)) +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting i be n_2 +letting p be permutation((n_1, n_2), (n_3, n_4)) +letting q be permutation((n_1, n_3, n_2)) +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting i be n_3 +letting p be permutation((n_1, n_2), (n_3, n_4)) +letting q be permutation((n_1, n_3, n_4)) +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting i be n_2 +letting p be permutation((n_1, n_2), (n_3, n_4)) +letting q be permutation((n_1, n_4, n_2)) +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting i be n_4 +letting p be permutation((n_1, n_2), (n_3, n_4)) +letting q be permutation((n_1, n_4, n_3)) +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting i be n_3 +letting p be permutation((n_1, n_2, n_3, n_4)) +letting q be permutation((n_2, n_4, n_3)) +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting i be n_4 +letting p be permutation((n_1, n_2, n_3, n_4)) +letting q be permutation((n_2, n_4, n_3)) diff --git a/tests/custom/permutations/README.md b/tests/custom/permutations/README.md index 02a1ad3d54..85ecf77b0f 100644 --- a/tests/custom/permutations/README.md +++ b/tests/custom/permutations/README.md @@ -28,3 +28,7 @@ Tests equality on permutations - tests [|p| = i | p <- sp] where sp is a set of permutations ## 06 inverse +Testing inverse in minimal contexts + +## 07 Compose +Testing composition in minimal contexts From 9f63de6a2c25bb873dde5bcb16789fb47567db7c Mon Sep 17 00:00:00 2001 From: Fraser Dunlop Date: Wed, 12 Dec 2018 11:09:10 +0000 Subject: [PATCH 051/229] Inequality in comprehension tests --- .../0006_in_comprehension/permutation.essence | 7 + .../enum/0006_in_comprehension/run.sh | 3 + .../0006_in_comprehension/stdout.expected | 124 +++++++++++++++ .../0006_in_comprehension/permutation.essence | 6 + .../int/0006_in_comprehension/run.sh | 3 + .../int/0006_in_comprehension/stdout.expected | 124 +++++++++++++++ .../0006_in_comprehension/permutation.essence | 7 + .../unnamed/0006_in_comprehension/run.sh | 3 + .../0006_in_comprehension/stdout.expected | 148 ++++++++++++++++++ 9 files changed, 425 insertions(+) create mode 100644 tests/custom/permutations/05_equality/enum/0006_in_comprehension/permutation.essence create mode 100755 tests/custom/permutations/05_equality/enum/0006_in_comprehension/run.sh create mode 100644 tests/custom/permutations/05_equality/enum/0006_in_comprehension/stdout.expected create mode 100644 tests/custom/permutations/05_equality/int/0006_in_comprehension/permutation.essence create mode 100755 tests/custom/permutations/05_equality/int/0006_in_comprehension/run.sh create mode 100644 tests/custom/permutations/05_equality/int/0006_in_comprehension/stdout.expected create mode 100644 tests/custom/permutations/05_equality/unnamed/0006_in_comprehension/permutation.essence create mode 100755 tests/custom/permutations/05_equality/unnamed/0006_in_comprehension/run.sh create mode 100644 tests/custom/permutations/05_equality/unnamed/0006_in_comprehension/stdout.expected diff --git a/tests/custom/permutations/05_equality/enum/0006_in_comprehension/permutation.essence b/tests/custom/permutations/05_equality/enum/0006_in_comprehension/permutation.essence new file mode 100644 index 0000000000..673ee7f52d --- /dev/null +++ b/tests/custom/permutations/05_equality/enum/0006_in_comprehension/permutation.essence @@ -0,0 +1,7 @@ +letting n be new type enum {E1,E2,E3,E4} +find p : permutation (size 4) of n +find q : permutation (size 4) of n + +such that + [pt != qt | pt <- p, qt <- q] + diff --git a/tests/custom/permutations/05_equality/enum/0006_in_comprehension/run.sh b/tests/custom/permutations/05_equality/enum/0006_in_comprehension/run.sh new file mode 100755 index 0000000000..de361d4354 --- /dev/null +++ b/tests/custom/permutations/05_equality/enum/0006_in_comprehension/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence --number-of-solutions=40 +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/05_equality/enum/0006_in_comprehension/stdout.expected b/tests/custom/permutations/05_equality/enum/0006_in_comprehension/stdout.expected new file mode 100644 index 0000000000..61af88efe6 --- /dev/null +++ b/tests/custom/permutations/05_equality/enum/0006_in_comprehension/stdout.expected @@ -0,0 +1,124 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Copying solution to: permutation-000001.solution +Copying solution to: permutation-000002.solution +Copying solution to: permutation-000003.solution +Copying solution to: permutation-000004.solution +Copying solution to: permutation-000005.solution +Copying solution to: permutation-000006.solution +Copying solution to: permutation-000007.solution +Copying solution to: permutation-000008.solution +Copying solution to: permutation-000009.solution +Copying solution to: permutation-000010.solution +Copying solution to: permutation-000011.solution +Copying solution to: permutation-000012.solution +Copying solution to: permutation-000013.solution +Copying solution to: permutation-000014.solution +Copying solution to: permutation-000015.solution +Copying solution to: permutation-000016.solution +Copying solution to: permutation-000017.solution +Copying solution to: permutation-000018.solution +Copying solution to: permutation-000019.solution +Copying solution to: permutation-000020.solution +Copying solution to: permutation-000021.solution +Copying solution to: permutation-000022.solution +Copying solution to: permutation-000023.solution +Copying solution to: permutation-000024.solution +language Essence 1.3 + +letting p be permutation((E1, E2), (E3, E4)) +letting q be permutation((E1, E3), (E2, E4)) +language Essence 1.3 + +letting p be permutation((E1, E2), (E3, E4)) +letting q be permutation((E1, E3, E2, E4)) +language Essence 1.3 + +letting p be permutation((E1, E2), (E3, E4)) +letting q be permutation((E1, E4, E2, E3)) +language Essence 1.3 + +letting p be permutation((E1, E2), (E3, E4)) +letting q be permutation((E1, E4), (E2, E3)) +language Essence 1.3 + +letting p be permutation((E1, E2, E3, E4)) +letting q be permutation((E1, E3), (E2, E4)) +language Essence 1.3 + +letting p be permutation((E1, E2, E3, E4)) +letting q be permutation((E1, E4, E3, E2)) +language Essence 1.3 + +letting p be permutation((E1, E2, E4, E3)) +letting q be permutation((E1, E3, E4, E2)) +language Essence 1.3 + +letting p be permutation((E1, E2, E4, E3)) +letting q be permutation((E1, E4), (E2, E3)) +language Essence 1.3 + +letting p be permutation((E1, E3, E4, E2)) +letting q be permutation((E1, E2, E4, E3)) +language Essence 1.3 + +letting p be permutation((E1, E3, E4, E2)) +letting q be permutation((E1, E4), (E2, E3)) +language Essence 1.3 + +letting p be permutation((E1, E3), (E2, E4)) +letting q be permutation((E1, E2), (E3, E4)) +language Essence 1.3 + +letting p be permutation((E1, E3), (E2, E4)) +letting q be permutation((E1, E2, E3, E4)) +language Essence 1.3 + +letting p be permutation((E1, E3), (E2, E4)) +letting q be permutation((E1, E4, E3, E2)) +language Essence 1.3 + +letting p be permutation((E1, E3), (E2, E4)) +letting q be permutation((E1, E4), (E2, E3)) +language Essence 1.3 + +letting p be permutation((E1, E3, E2, E4)) +letting q be permutation((E1, E2), (E3, E4)) +language Essence 1.3 + +letting p be permutation((E1, E3, E2, E4)) +letting q be permutation((E1, E4, E2, E3)) +language Essence 1.3 + +letting p be permutation((E1, E4, E3, E2)) +letting q be permutation((E1, E2, E3, E4)) +language Essence 1.3 + +letting p be permutation((E1, E4, E3, E2)) +letting q be permutation((E1, E3), (E2, E4)) +language Essence 1.3 + +letting p be permutation((E1, E4, E2, E3)) +letting q be permutation((E1, E2), (E3, E4)) +language Essence 1.3 + +letting p be permutation((E1, E4, E2, E3)) +letting q be permutation((E1, E3, E2, E4)) +language Essence 1.3 + +letting p be permutation((E1, E4), (E2, E3)) +letting q be permutation((E1, E2), (E3, E4)) +language Essence 1.3 + +letting p be permutation((E1, E4), (E2, E3)) +letting q be permutation((E1, E2, E4, E3)) +language Essence 1.3 + +letting p be permutation((E1, E4), (E2, E3)) +letting q be permutation((E1, E3, E4, E2)) +language Essence 1.3 + +letting p be permutation((E1, E4), (E2, E3)) +letting q be permutation((E1, E3), (E2, E4)) diff --git a/tests/custom/permutations/05_equality/int/0006_in_comprehension/permutation.essence b/tests/custom/permutations/05_equality/int/0006_in_comprehension/permutation.essence new file mode 100644 index 0000000000..a3aac36aaa --- /dev/null +++ b/tests/custom/permutations/05_equality/int/0006_in_comprehension/permutation.essence @@ -0,0 +1,6 @@ +find p : permutation (size 4) of int(1..4) +find q : permutation (size 4) of int(1..4) + +such that + [pt != qt | pt <- p, qt <- q] + diff --git a/tests/custom/permutations/05_equality/int/0006_in_comprehension/run.sh b/tests/custom/permutations/05_equality/int/0006_in_comprehension/run.sh new file mode 100755 index 0000000000..de361d4354 --- /dev/null +++ b/tests/custom/permutations/05_equality/int/0006_in_comprehension/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence --number-of-solutions=40 +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/05_equality/int/0006_in_comprehension/stdout.expected b/tests/custom/permutations/05_equality/int/0006_in_comprehension/stdout.expected new file mode 100644 index 0000000000..351d543e1e --- /dev/null +++ b/tests/custom/permutations/05_equality/int/0006_in_comprehension/stdout.expected @@ -0,0 +1,124 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Copying solution to: permutation-000001.solution +Copying solution to: permutation-000002.solution +Copying solution to: permutation-000003.solution +Copying solution to: permutation-000004.solution +Copying solution to: permutation-000005.solution +Copying solution to: permutation-000006.solution +Copying solution to: permutation-000007.solution +Copying solution to: permutation-000008.solution +Copying solution to: permutation-000009.solution +Copying solution to: permutation-000010.solution +Copying solution to: permutation-000011.solution +Copying solution to: permutation-000012.solution +Copying solution to: permutation-000013.solution +Copying solution to: permutation-000014.solution +Copying solution to: permutation-000015.solution +Copying solution to: permutation-000016.solution +Copying solution to: permutation-000017.solution +Copying solution to: permutation-000018.solution +Copying solution to: permutation-000019.solution +Copying solution to: permutation-000020.solution +Copying solution to: permutation-000021.solution +Copying solution to: permutation-000022.solution +Copying solution to: permutation-000023.solution +Copying solution to: permutation-000024.solution +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4)) +letting q be permutation((1, 3), (2, 4)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4)) +letting q be permutation((1, 3, 2, 4)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4)) +letting q be permutation((1, 4, 2, 3)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4)) +letting q be permutation((1, 4), (2, 3)) +language Essence 1.3 + +letting p be permutation((1, 2, 3, 4)) +letting q be permutation((1, 3), (2, 4)) +language Essence 1.3 + +letting p be permutation((1, 2, 3, 4)) +letting q be permutation((1, 4, 3, 2)) +language Essence 1.3 + +letting p be permutation((1, 2, 4, 3)) +letting q be permutation((1, 3, 4, 2)) +language Essence 1.3 + +letting p be permutation((1, 2, 4, 3)) +letting q be permutation((1, 4), (2, 3)) +language Essence 1.3 + +letting p be permutation((1, 3, 4, 2)) +letting q be permutation((1, 2, 4, 3)) +language Essence 1.3 + +letting p be permutation((1, 3, 4, 2)) +letting q be permutation((1, 4), (2, 3)) +language Essence 1.3 + +letting p be permutation((1, 3), (2, 4)) +letting q be permutation((1, 2), (3, 4)) +language Essence 1.3 + +letting p be permutation((1, 3), (2, 4)) +letting q be permutation((1, 2, 3, 4)) +language Essence 1.3 + +letting p be permutation((1, 3), (2, 4)) +letting q be permutation((1, 4, 3, 2)) +language Essence 1.3 + +letting p be permutation((1, 3), (2, 4)) +letting q be permutation((1, 4), (2, 3)) +language Essence 1.3 + +letting p be permutation((1, 3, 2, 4)) +letting q be permutation((1, 2), (3, 4)) +language Essence 1.3 + +letting p be permutation((1, 3, 2, 4)) +letting q be permutation((1, 4, 2, 3)) +language Essence 1.3 + +letting p be permutation((1, 4, 3, 2)) +letting q be permutation((1, 2, 3, 4)) +language Essence 1.3 + +letting p be permutation((1, 4, 3, 2)) +letting q be permutation((1, 3), (2, 4)) +language Essence 1.3 + +letting p be permutation((1, 4, 2, 3)) +letting q be permutation((1, 2), (3, 4)) +language Essence 1.3 + +letting p be permutation((1, 4, 2, 3)) +letting q be permutation((1, 3, 2, 4)) +language Essence 1.3 + +letting p be permutation((1, 4), (2, 3)) +letting q be permutation((1, 2), (3, 4)) +language Essence 1.3 + +letting p be permutation((1, 4), (2, 3)) +letting q be permutation((1, 2, 4, 3)) +language Essence 1.3 + +letting p be permutation((1, 4), (2, 3)) +letting q be permutation((1, 3, 4, 2)) +language Essence 1.3 + +letting p be permutation((1, 4), (2, 3)) +letting q be permutation((1, 3), (2, 4)) diff --git a/tests/custom/permutations/05_equality/unnamed/0006_in_comprehension/permutation.essence b/tests/custom/permutations/05_equality/unnamed/0006_in_comprehension/permutation.essence new file mode 100644 index 0000000000..96c13569f4 --- /dev/null +++ b/tests/custom/permutations/05_equality/unnamed/0006_in_comprehension/permutation.essence @@ -0,0 +1,7 @@ +letting n be new type of size 4 +find p : permutation (size 4) of n +find q : permutation (size 4) of n + +such that + [pt != qt | pt <- p, qt <- q] + diff --git a/tests/custom/permutations/05_equality/unnamed/0006_in_comprehension/run.sh b/tests/custom/permutations/05_equality/unnamed/0006_in_comprehension/run.sh new file mode 100755 index 0000000000..de361d4354 --- /dev/null +++ b/tests/custom/permutations/05_equality/unnamed/0006_in_comprehension/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence --number-of-solutions=40 +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/05_equality/unnamed/0006_in_comprehension/stdout.expected b/tests/custom/permutations/05_equality/unnamed/0006_in_comprehension/stdout.expected new file mode 100644 index 0000000000..d02cb834ce --- /dev/null +++ b/tests/custom/permutations/05_equality/unnamed/0006_in_comprehension/stdout.expected @@ -0,0 +1,148 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Copying solution to: permutation-000001.solution +Copying solution to: permutation-000002.solution +Copying solution to: permutation-000003.solution +Copying solution to: permutation-000004.solution +Copying solution to: permutation-000005.solution +Copying solution to: permutation-000006.solution +Copying solution to: permutation-000007.solution +Copying solution to: permutation-000008.solution +Copying solution to: permutation-000009.solution +Copying solution to: permutation-000010.solution +Copying solution to: permutation-000011.solution +Copying solution to: permutation-000012.solution +Copying solution to: permutation-000013.solution +Copying solution to: permutation-000014.solution +Copying solution to: permutation-000015.solution +Copying solution to: permutation-000016.solution +Copying solution to: permutation-000017.solution +Copying solution to: permutation-000018.solution +Copying solution to: permutation-000019.solution +Copying solution to: permutation-000020.solution +Copying solution to: permutation-000021.solution +Copying solution to: permutation-000022.solution +Copying solution to: permutation-000023.solution +Copying solution to: permutation-000024.solution +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_1, n_2), (n_3, n_4)) +letting q be permutation((n_1, n_3), (n_2, n_4)) +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_1, n_2), (n_3, n_4)) +letting q be permutation((n_1, n_3, n_2, n_4)) +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_1, n_2), (n_3, n_4)) +letting q be permutation((n_1, n_4, n_2, n_3)) +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_1, n_2), (n_3, n_4)) +letting q be permutation((n_1, n_4), (n_2, n_3)) +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_1, n_2, n_3, n_4)) +letting q be permutation((n_1, n_3), (n_2, n_4)) +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_1, n_2, n_3, n_4)) +letting q be permutation((n_1, n_4, n_3, n_2)) +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_1, n_2, n_4, n_3)) +letting q be permutation((n_1, n_3, n_4, n_2)) +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_1, n_2, n_4, n_3)) +letting q be permutation((n_1, n_4), (n_2, n_3)) +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_1, n_3, n_4, n_2)) +letting q be permutation((n_1, n_2, n_4, n_3)) +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_1, n_3, n_4, n_2)) +letting q be permutation((n_1, n_4), (n_2, n_3)) +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_1, n_3), (n_2, n_4)) +letting q be permutation((n_1, n_2), (n_3, n_4)) +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_1, n_3), (n_2, n_4)) +letting q be permutation((n_1, n_2, n_3, n_4)) +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_1, n_3), (n_2, n_4)) +letting q be permutation((n_1, n_4, n_3, n_2)) +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_1, n_3), (n_2, n_4)) +letting q be permutation((n_1, n_4), (n_2, n_3)) +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_1, n_3, n_2, n_4)) +letting q be permutation((n_1, n_2), (n_3, n_4)) +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_1, n_3, n_2, n_4)) +letting q be permutation((n_1, n_4, n_2, n_3)) +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_1, n_4, n_3, n_2)) +letting q be permutation((n_1, n_2, n_3, n_4)) +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_1, n_4, n_3, n_2)) +letting q be permutation((n_1, n_3), (n_2, n_4)) +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_1, n_4, n_2, n_3)) +letting q be permutation((n_1, n_2), (n_3, n_4)) +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_1, n_4, n_2, n_3)) +letting q be permutation((n_1, n_3, n_2, n_4)) +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_1, n_4), (n_2, n_3)) +letting q be permutation((n_1, n_2), (n_3, n_4)) +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_1, n_4), (n_2, n_3)) +letting q be permutation((n_1, n_2, n_4, n_3)) +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_1, n_4), (n_2, n_3)) +letting q be permutation((n_1, n_3, n_4, n_2)) +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_1, n_4), (n_2, n_3)) +letting q be permutation((n_1, n_3), (n_2, n_4)) From 5def9b00d85d1255b2381b48d1da234892bab940 Mon Sep 17 00:00:00 2001 From: Fraser Dunlop Date: Thu, 13 Dec 2018 14:01:54 +0000 Subject: [PATCH 052/229] Set of tuples bug fix --- .../Set/ExplicitVarSizeWithDummy.hs | 2 +- .../Set/ExplicitVarSizeWithFlags.hs | 2 +- .../Set/ExplicitVarSizeWithMarker.hs | 2 +- .../enum/0004/permutation.essence | 10 --------- .../02_cardinality/enum/0004/run.sh | 3 --- .../stdout.expected | 13 +++++++++++ .../stdout.expected | 8 +++++-- .../permutations/03_generators/enum/BUGS.md | 22 ------------------- .../minimal_bug_example/permutation.essence | 16 -------------- .../enum/minimal_bug_example/run.sh | 3 --- .../minimaler_bug_example/permutation.essence | 16 -------------- .../enum/minimaler_bug_example/run.sh | 3 --- 12 files changed, 22 insertions(+), 78 deletions(-) delete mode 100644 tests/custom/permutations/02_cardinality/enum/0004/permutation.essence delete mode 100755 tests/custom/permutations/02_cardinality/enum/0004/run.sh create mode 100644 tests/custom/permutations/03_generators/enum/0001_given_permutation_in_generator/stdout.expected rename tests/custom/permutations/{02_cardinality/enum/0004 => 03_generators/enum/0002_letting_permutation_in_generator}/stdout.expected (68%) delete mode 100644 tests/custom/permutations/03_generators/enum/BUGS.md delete mode 100644 tests/custom/permutations/03_generators/enum/minimal_bug_example/permutation.essence delete mode 100755 tests/custom/permutations/03_generators/enum/minimal_bug_example/run.sh delete mode 100644 tests/custom/permutations/03_generators/enum/minimaler_bug_example/permutation.essence delete mode 100755 tests/custom/permutations/03_generators/enum/minimaler_bug_example/run.sh diff --git a/src/Conjure/Representations/Set/ExplicitVarSizeWithDummy.hs b/src/Conjure/Representations/Set/ExplicitVarSizeWithDummy.hs index 2dfafd4f7c..52be9d78f8 100644 --- a/src/Conjure/Representations/Set/ExplicitVarSizeWithDummy.hs +++ b/src/Conjure/Representations/Set/ExplicitVarSizeWithDummy.hs @@ -29,7 +29,7 @@ setExplicitVarSizeWithDummy = Representation chck downD structuralCons downC up getMaxSize attrs innerDomain = case attrs of SizeAttr_MaxSize x -> return x SizeAttr_MinMaxSize _ x -> return x - _ -> domainSizeOf innerDomain + _ -> reTag AnyTag <$> domainSizeOf innerDomain calcDummyDomain :: Pretty r => Domain r Expression -> Domain r Expression calcDummyDomain (DomainInt t [RangeBounded lb ub]) = diff --git a/src/Conjure/Representations/Set/ExplicitVarSizeWithFlags.hs b/src/Conjure/Representations/Set/ExplicitVarSizeWithFlags.hs index 8af6057c9f..e4be807030 100644 --- a/src/Conjure/Representations/Set/ExplicitVarSizeWithFlags.hs +++ b/src/Conjure/Representations/Set/ExplicitVarSizeWithFlags.hs @@ -29,7 +29,7 @@ setExplicitVarSizeWithFlags = Representation chck downD structuralCons downC up getMaxSize attrs innerDomain = case attrs of SizeAttr_MaxSize x -> return x SizeAttr_MinMaxSize _ x -> return x - _ -> domainSizeOf innerDomain + _ -> reTag AnyTag <$> domainSizeOf innerDomain downD :: TypeOf_DownD m diff --git a/src/Conjure/Representations/Set/ExplicitVarSizeWithMarker.hs b/src/Conjure/Representations/Set/ExplicitVarSizeWithMarker.hs index 7f0982b8bc..077854e3af 100644 --- a/src/Conjure/Representations/Set/ExplicitVarSizeWithMarker.hs +++ b/src/Conjure/Representations/Set/ExplicitVarSizeWithMarker.hs @@ -28,7 +28,7 @@ setExplicitVarSizeWithMarker = Representation chck downD structuralCons downC up getMaxSize attrs innerDomain = case attrs of SizeAttr_MaxSize x -> return x SizeAttr_MinMaxSize _ x -> return x - _ -> domainSizeOf innerDomain + _ -> reTag AnyTag <$> domainSizeOf innerDomain downD :: TypeOf_DownD m downD (name, domain@(DomainSet _ (SetAttr attrs) innerDomain)) = do diff --git a/tests/custom/permutations/02_cardinality/enum/0004/permutation.essence b/tests/custom/permutations/02_cardinality/enum/0004/permutation.essence deleted file mode 100644 index be6ffeff36..0000000000 --- a/tests/custom/permutations/02_cardinality/enum/0004/permutation.essence +++ /dev/null @@ -1,10 +0,0 @@ -letting n be new type enum {E1,E2,E3,E4,E5,E6} - -find p : permutation of n - -such that - |toSet([i | i <- p])| = |p| - - - - diff --git a/tests/custom/permutations/02_cardinality/enum/0004/run.sh b/tests/custom/permutations/02_cardinality/enum/0004/run.sh deleted file mode 100755 index b4899d6266..0000000000 --- a/tests/custom/permutations/02_cardinality/enum/0004/run.sh +++ /dev/null @@ -1,3 +0,0 @@ -conjure solve *.essence -cat conjure-output/*.solution -rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/03_generators/enum/0001_given_permutation_in_generator/stdout.expected b/tests/custom/permutations/03_generators/enum/0001_given_permutation_in_generator/stdout.expected new file mode 100644 index 0000000000..3002dbbb0f --- /dev/null +++ b/tests/custom/permutations/03_generators/enum/0001_given_permutation_in_generator/stdout.expected @@ -0,0 +1,13 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime permutation.param +Copying solution to: permutation-permutation.solution +language Essence 1.3 + +letting s be {(E1, E3), (E3, E4), (E4, E1)} +$ Visualisation for s +$ E1 E3 +$ E3 E4 +$ E4 E1 + diff --git a/tests/custom/permutations/02_cardinality/enum/0004/stdout.expected b/tests/custom/permutations/03_generators/enum/0002_letting_permutation_in_generator/stdout.expected similarity index 68% rename from tests/custom/permutations/02_cardinality/enum/0004/stdout.expected rename to tests/custom/permutations/03_generators/enum/0002_letting_permutation_in_generator/stdout.expected index 4e026e23dd..cdf044d2a7 100644 --- a/tests/custom/permutations/02_cardinality/enum/0004/stdout.expected +++ b/tests/custom/permutations/03_generators/enum/0002_letting_permutation_in_generator/stdout.expected @@ -5,5 +5,9 @@ Savile Row: model000001.eprime Copying solution to: permutation.solution language Essence 1.3 -letting i be 4 -letting p be permutation((E3, E4), (E5, E6)) +letting s be {(E1, E3), (E3, E4), (E4, E1)} +$ Visualisation for s +$ E1 E3 +$ E3 E4 +$ E4 E1 + diff --git a/tests/custom/permutations/03_generators/enum/BUGS.md b/tests/custom/permutations/03_generators/enum/BUGS.md deleted file mode 100644 index 9417909c38..0000000000 --- a/tests/custom/permutations/03_generators/enum/BUGS.md +++ /dev/null @@ -1,22 +0,0 @@ -There appears to be a bug in refinement -- 0001 -- 0002 -are affected -These examples both work with ints instead of enums - -A minimal bug example is in this folder - the problem is sets of tuples of enums - -$minimal bug example - letting n be new type enum {E1,E2,E3,E4} - letting i be (E1,E2) - find s : set of (n,n) - such that i in s - - -IO Error -Type error in 4 * 4 - The argument has type: matrix indexed by [int] of int - -CallStack (from HasCallStack): - error, called at src/Conjure/Bug.hs:21:15 in conjure-cp-2.2.0-4cfnInyB42NJSP2i6f0krZ:Conjure.Bug - bug, called at src/Conjure/Bug.hs:47:16 in conjure-cp-2.2.0-4cfnInyB42NJSP2i6f0krZ:Conjure.Bug diff --git a/tests/custom/permutations/03_generators/enum/minimal_bug_example/permutation.essence b/tests/custom/permutations/03_generators/enum/minimal_bug_example/permutation.essence deleted file mode 100644 index 9040ee25a7..0000000000 --- a/tests/custom/permutations/03_generators/enum/minimal_bug_example/permutation.essence +++ /dev/null @@ -1,16 +0,0 @@ -letting n be new type enum {E1,E2,E3,E4} - -$ We don't need a permutation to reach this bug -$letting p be permutation((E1,E3,E4)) -$ A tuple of enums is sufficient -letting i be (E1,E2) - -find s : set of (n,n) - - -such that i in s -$ and([e in s | e <- p]) - - - - diff --git a/tests/custom/permutations/03_generators/enum/minimal_bug_example/run.sh b/tests/custom/permutations/03_generators/enum/minimal_bug_example/run.sh deleted file mode 100755 index b4899d6266..0000000000 --- a/tests/custom/permutations/03_generators/enum/minimal_bug_example/run.sh +++ /dev/null @@ -1,3 +0,0 @@ -conjure solve *.essence -cat conjure-output/*.solution -rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/03_generators/enum/minimaler_bug_example/permutation.essence b/tests/custom/permutations/03_generators/enum/minimaler_bug_example/permutation.essence deleted file mode 100644 index fcacda0a92..0000000000 --- a/tests/custom/permutations/03_generators/enum/minimaler_bug_example/permutation.essence +++ /dev/null @@ -1,16 +0,0 @@ -letting n be new type enum {E1,E2,E3,E4} - -$ We don't need a permutation to reach this bug -$letting p be permutation((E1,E3,E4)) -$ A tuple of enums is sufficient -letting i be (E1,E2) - -find s : matrix indexed by [int(1..3)] of (n,n) - - -such that i in s -$ and([e in s | e <- p]) - - - - diff --git a/tests/custom/permutations/03_generators/enum/minimaler_bug_example/run.sh b/tests/custom/permutations/03_generators/enum/minimaler_bug_example/run.sh deleted file mode 100755 index b4899d6266..0000000000 --- a/tests/custom/permutations/03_generators/enum/minimaler_bug_example/run.sh +++ /dev/null @@ -1,3 +0,0 @@ -conjure solve *.essence -cat conjure-output/*.solution -rm -rf conjure-output *.solution From 50ce3d48d7ddd8dc998ed96999359d37210de631 Mon Sep 17 00:00:00 2001 From: Fraser Dunlop Date: Thu, 13 Dec 2018 16:05:49 +0000 Subject: [PATCH 053/229] Fixed merge --- src/Conjure/Language/ParserC.hs | 14 +++++--------- src/Conjure/Rules/Horizontal/Permutation.hs | 6 +++++- 2 files changed, 10 insertions(+), 10 deletions(-) diff --git a/src/Conjure/Language/ParserC.hs b/src/Conjure/Language/ParserC.hs index 9b3df4c889..ddd24d0454 100644 --- a/src/Conjure/Language/ParserC.hs +++ b/src/Conjure/Language/ParserC.hs @@ -242,20 +242,16 @@ parseDomainWithRepr = pDomainAtom x <- parsePartitionAttr lexeme L_from y <- parseDomainWithRepr -<<<<<<< HEAD - return $ DomainPartition r x y + return $ DomainPartition NoRepresentation x y pPermutation = do lexeme L_permutation - r <- parseRepr +-- r <- parseRepr x <- parsePermutationAttr lexeme L_of -- $ trace (textToString $ representationToShortText r) L_of y <- parseDomainWithRepr - return $ DomainPermutation r x y -||||||| merged common ancestors - return $ DomainPartition r x y -======= - return $ DomainPartition NoRepresentation x y ->>>>>>> set-of-tuple-of-enum-bug + return $ DomainPermutation NoRepresentation x y + + parseAttributes :: Parser (DomainAttributes Expression) parseAttributes = do diff --git a/src/Conjure/Rules/Horizontal/Permutation.hs b/src/Conjure/Rules/Horizontal/Permutation.hs index 805d6395ed..177dd84323 100644 --- a/src/Conjure/Rules/Horizontal/Permutation.hs +++ b/src/Conjure/Rules/Horizontal/Permutation.hs @@ -167,7 +167,11 @@ rule_Compose = "permutation-compose" `namedRule` theRule where - +--TODO image over Essence Types +-- +--e.g. + -- + -- [essence| [ - | t <- image(p, rel)] |] refines to [essence| [ - | t' <- rel, let t = image(p, t') ] |] -- From a05f014ab42bfa92aa53825408acca836ade8266 Mon Sep 17 00:00:00 2001 From: Fraser Dunlop Date: Mon, 17 Dec 2018 13:25:05 +0000 Subject: [PATCH 054/229] compose broken after image extended to work over sets --- src/Conjure/Language/Expression/Op/Defined.hs | 9 +- src/Conjure/Language/Type.hs | 31 +++- src/Conjure/Rules/Horizontal/Permutation.hs | 174 +++++++++++++----- src/Conjure/Rules/Vertical/Permutation.hs | 24 ++- src/Conjure/UI/Model.hs | 4 +- .../permutation.essence | 11 ++ .../0002_letting_and_given/permutation.param | 3 + .../int/0002_letting_and_given/run.sh | 3 + .../0002_letting_and_given/stdout.expected | 8 + .../permutation.essence | 10 + .../permutation.param | 2 + .../0001_given_permutation_letting_set/run.sh | 3 + .../stdout.expected | 8 + .../permutation.essence | 11 ++ .../permutation.param | 1 + .../0002_given_permutation_find_sets/run.sh | 3 + .../stdout.expected | 54 ++++++ .../permutation.essence | 11 ++ .../0003_letting_permutation_find_sets/run.sh | 3 + .../stdout.expected | 54 ++++++ .../permutations/08_image_set/runthese.sh | 2 + 21 files changed, 359 insertions(+), 70 deletions(-) create mode 100644 tests/custom/permutations/07_compose/int/0002_letting_and_given/permutation.essence create mode 100644 tests/custom/permutations/07_compose/int/0002_letting_and_given/permutation.param create mode 100755 tests/custom/permutations/07_compose/int/0002_letting_and_given/run.sh create mode 100644 tests/custom/permutations/07_compose/int/0002_letting_and_given/stdout.expected create mode 100644 tests/custom/permutations/08_image_set/int/0001_given_permutation_letting_set/permutation.essence create mode 100644 tests/custom/permutations/08_image_set/int/0001_given_permutation_letting_set/permutation.param create mode 100755 tests/custom/permutations/08_image_set/int/0001_given_permutation_letting_set/run.sh create mode 100644 tests/custom/permutations/08_image_set/int/0001_given_permutation_letting_set/stdout.expected create mode 100644 tests/custom/permutations/08_image_set/int/0002_given_permutation_find_sets/permutation.essence create mode 100644 tests/custom/permutations/08_image_set/int/0002_given_permutation_find_sets/permutation.param create mode 100755 tests/custom/permutations/08_image_set/int/0002_given_permutation_find_sets/run.sh create mode 100644 tests/custom/permutations/08_image_set/int/0002_given_permutation_find_sets/stdout.expected create mode 100644 tests/custom/permutations/08_image_set/int/0003_letting_permutation_find_sets/permutation.essence create mode 100755 tests/custom/permutations/08_image_set/int/0003_letting_permutation_find_sets/run.sh create mode 100644 tests/custom/permutations/08_image_set/int/0003_letting_permutation_find_sets/stdout.expected create mode 100644 tests/custom/permutations/08_image_set/runthese.sh diff --git a/src/Conjure/Language/Expression/Op/Defined.hs b/src/Conjure/Language/Expression/Op/Defined.hs index 96d2d668aa..6e96559f02 100644 --- a/src/Conjure/Language/Expression/Op/Defined.hs +++ b/src/Conjure/Language/Expression/Op/Defined.hs @@ -22,9 +22,10 @@ instance (Pretty x, TypeOf x) => TypeOf (OpDefined x) where typeOf p@(OpDefined x) = do ty <- typeOf x case ty of - TypeFunction a _ -> return (TypeSet a) - TypeSequence _ -> return (TypeSet (TypeInt NoTag)) - _ -> raiseTypeError p + TypeFunction a _ -> return (TypeSet a) +-- TypePermutation a -> return (TypeSet a) + TypeSequence _ -> return (TypeSet (TypeInt NoTag)) + _ -> raiseTypeError p instance EvaluateOp OpDefined where evaluateOp p | any isUndef (childrenBi p) = do @@ -32,6 +33,8 @@ instance EvaluateOp OpDefined where return $ mkUndef ty $ "Has undefined children:" <+> pretty p evaluateOp (OpDefined (viewConstantFunction -> Just xs)) = return $ ConstantAbstract $ AbsLitSet $ sortNub $ map fst xs +--TODO +-- evaluateOp (OpDefined (viewConstantPermutation -> evaluateOp op = na $ "evaluateOp{OpDefined}:" <++> pretty (show op) instance SimplifyOp OpDefined x where diff --git a/src/Conjure/Language/Type.hs b/src/Conjure/Language/Type.hs index ea6fbc2c75..bba66830cf 100644 --- a/src/Conjure/Language/Type.hs +++ b/src/Conjure/Language/Type.hs @@ -11,6 +11,8 @@ module Conjure.Language.Type , innerTypeOf , isPrimitiveType , typeCanIndexMatrix + , containsTypeComprehendable + , containsTypeIncomprehendable , containsType ) where @@ -227,10 +229,31 @@ typeCanIndexMatrix TypeEnum{} = True typeCanIndexMatrix _ = False -containsType :: Type -> Type -> Bool -containsType container containee = +-- | Types must not unify && type can be a generator in a comprehension +containsTypeComprehendable :: Type -> Type -> Bool +containsTypeComprehendable container containee = if typesUnify [container, containee] - then True + then False else case innerTypeOf container of Nothing -> False - Just so -> containsType so containee + Just so -> unifiesOrContains so containee + +-- | Types do not unify && type cannot be a generator in a comprehension +containsTypeIncomprehendable :: Type -> Type -> Bool +containsTypeIncomprehendable (TypeTuple ts) t = + any id ((\x -> unifiesOrContains x t) <$> ts) +containsTypeIncomprehendable (TypeRecord ts) t = + any id ((\x -> unifiesOrContains (snd x) t) <$> ts) +containsTypeIncomprehendable (TypeVariant ts) t = + any id ((\x -> unifiesOrContains (snd x) t) <$> ts) +containsTypeIncomprehendable _ _ = False + + +containsType :: Type -> Type -> Bool +containsType container containee = + (containsTypeComprehendable container containee) + || (containsTypeIncomprehendable container containee) + +unifiesOrContains :: Type -> Type -> Bool +unifiesOrContains container containee = + typesUnify [container, containee] || containsType container containee diff --git a/src/Conjure/Rules/Horizontal/Permutation.hs b/src/Conjure/Rules/Horizontal/Permutation.hs index 177dd84323..0ac4b250cc 100644 --- a/src/Conjure/Rules/Horizontal/Permutation.hs +++ b/src/Conjure/Rules/Horizontal/Permutation.hs @@ -63,54 +63,78 @@ rule_Permute_Comprehension_Tuples_Literal = "permutation-comprehension-tuples{As ) theRule _ = na "rule_Comprehension_Tuples_Literal" +--rule_Image_Literal' :: Rule +--rule_Image_Literal' = "permutation-image-literal" `namedRule` theRule where +-- theRule [essence| image(&p, &i) |] = do +-- (TypePermutation inner, elems) <- match permutationLiteral p +-- DomainPermutation _ _ innerP <- domainOf p +-- let f' = toFunction <$> fromCycles elems +-- case f' of +-- Left er -> fail $ "Permutation literal invalid." <++> stringToDoc (show er) +-- Right f -> do +-- let outLiteral = make matrixLiteral +-- (TypeMatrix (TypeInt AnyTag) (TypeTuple [inner,inner])) innerP +-- [ AbstractLiteral (AbsLitTuple [de +-- ,f de]) +-- | de <- join elems +-- ] +-- typeI <- typeOf i +-- if typesUnify [inner, typeI] +-- then do +-- innerD <- domainOf i +-- return +-- ( "Horizontal rule for permutation literal application to a single value (image), AsFunction representation" +-- , do +-- (hName, h) <- auxiliaryVar +-- (fPat, f) <- quantifiedVar +-- (tPat, t) <- quantifiedVar +-- (gPat, g) <- quantifiedVar +-- (ePat, _) <- quantifiedVar +-- return $ WithLocals +-- [essence| &h |] +-- (AuxiliaryVars +-- [ Declaration (FindOrGiven LocalFind hName innerD) +-- , SuchThat +-- [ [essence| +-- (forAll (&fPat, &tPat) in &outLiteral . &f = &i <-> &h = &t) +-- /\ (!(exists (&gPat, &ePat) in &outLiteral . &g = &h) <-> &h = &i) +-- |] +-- ] +-- ] +-- ) +-- ) +-- else if typeI `containsType` inner +-- then na "rule_Image_Literal" +-- else return ( "Horizontal rule for permutation application to a type the permutation doesn't care about" +-- , do +-- return [essence| &i |] +-- ) +-- theRule _ = na "rule_Image_Literal" + + rule_Image_Literal :: Rule rule_Image_Literal = "permutation-image-literal" `namedRule` theRule where theRule [essence| image(&p, &i) |] = do - (TypePermutation inner, elems) <- match permutationLiteral p - DomainPermutation _ _ innerP <- domainOf p + (TypePermutation inner, elems) <- match permutationLiteral p let f' = toFunction <$> fromCycles elems case f' of Left er -> fail $ "Permutation literal invalid." <++> stringToDoc (show er) Right f -> do - let outLiteral = make matrixLiteral - (TypeMatrix (TypeInt AnyTag) (TypeTuple [inner,inner])) innerP - [ AbstractLiteral (AbsLitTuple [de - ,f de]) - | de <- join elems - ] typeI <- typeOf i - if typeI `containsType` inner + if typesUnify [inner, typeI] then do - if typesUnify [inner, typeI] - then do - innerD <- domainOf i - return - ( "Horizontal rule for permutation literal application to a single value (image), AsFunction representation" - , do - (hName, h) <- auxiliaryVar - (fPat, f) <- quantifiedVar - (tPat, t) <- quantifiedVar - (gPat, g) <- quantifiedVar - (ePat, _) <- quantifiedVar - return $ WithLocals - [essence| &h |] - (AuxiliaryVars - [ Declaration (FindOrGiven LocalFind hName innerD) - , SuchThat - [ [essence| - (forAll (&fPat, &tPat) in &outLiteral . &f = &i <-> &h = &t) - /\ (!(exists (&gPat, &ePat) in &outLiteral . &g = &h) <-> &h = &i) - |] - ] - ] - ) - ) - else na "rule_Permute_Literal" - else return - ( "Horizontal rule for permutation application to a type the permutation doesn't care about" - , do - return [essence| &i |] - ) + let outLiteral = make functionLiteral (TypeFunction inner inner) [ (de,f de) | de <- join elems ] + return + ( "Horizontal rule for permutation literal application to a single value (image), AsFunction representation" + , do + return $ reTag AnyTag [essence| [&i, catchUndef(image(&outLiteral,&i),0)][toInt(&i in defined(&outLiteral))+1] |] + ) + else if typeI `containsType` inner + then na "rule_Image_Literal" + else return ( "Horizontal rule for permutation application to a type the permutation doesn't care about" + , do + return [essence| &i |] + ) theRule _ = na "rule_Image_Literal" @@ -150,28 +174,80 @@ rule_Permutation_Inverse = "permutation-inverse" `namedRule` theRule where ) theRule _ = na "rule_Permutation_Inverse" -rule_Compose :: Rule -rule_Compose = "permutation-compose" `namedRule` theRule where +rule_Compose_Image :: Rule +rule_Compose_Image = "permutation-compose-image" `namedRule` theRule where theRule [essence| image(compose(&g, &h),&i) |] = do + case match permutationLiteral h of + Nothing -> return () + Just _ -> na "rule_Compose_Image" TypePermutation innerG <- typeOf g TypePermutation innerH <- typeOf g typeI <- typeOf i if typesUnify [innerG, innerH, typeI] then return - ( "Horizontal rule for permutation composition" + ( "Horizontal rule for image of permutation composition" , do return [essence| image(&g, image(&h,&i)) |] ) - else na "rule_Compose" - theRule _ = na "rule_Compose" + else na "rule_Compose_Image" + theRule _ = na "rule_Compose_Image" +--rule_Compose :: Rule +--rule_Compose = "permutation-compose" `namedRule` theRule where +-- theRule [essence| compose(&g,&h) |] = do +-- TypePermutation innerG <- typeOf g +-- TypePermutation innerH <- typeOf h +-- (DomainPermutation _ _ dg) <- domainOf g +-- (DomainPermutation _ _ dh) <- domainOf h +-- if typesUnify [innerG, innerH] +-- then do +-- du <- domainUnion dg dh +-- return ( "Horizontal rule for permutation composition" +-- , do +-- +-- (lPat, l) <- quantifiedVar +-- (rPat, r) <- quantifiedVar +-- (pName, p) <- auxiliaryVar +-- return $ WithLocals +-- [essence| &p |] +-- ( AuxiliaryVars +-- [ Declaration (FindOrGiven LocalFind pName du) +-- , SuchThat +-- [ [essence| +-- and([image(&p,&l[1]) = image(&g, image(&h,&l[1])) | &lPat <- &g]) +-- /\ and([image(&p,&r[1]) = image(&g, image(&h,&r[1])) | &rPat <- &h]) +-- |] +-- ] +-- ] +-- ) +-- ) +-- else na "rule_Compose" +-- theRule _ = na "rule_Compose" +rule_Image_Comprehendable :: Rule +rule_Image_Comprehendable = "comprehendable-image" `namedRule` theRule where + theRule (Comprehension body gensOrConds) = do + (gocBefore, (pat, perm, y), gocAfter) <- matchFirst gensOrConds $ \ goc -> case goc of + Generator (GenInExpr (Single pat) [essence| image(&perm, &y) |]) -> return (pat, perm, y) + _ -> na "rule_Image_Comprehendable" + ty <- typeOf y + (TypePermutation inn) <- typeOf perm + if (not $ typesUnify [ty, inn]) && (ty `containsTypeComprehendable` inn) + then do + return + ( "Horizontal rule for image of comprehendable under permutation" + , do + (dPat, d) <- quantifiedVar + return (Comprehension body $ + gocBefore + ++ [Generator (GenInExpr dPat [essence| &y |])] + ++ ((ComprehensionLetting pat [essence| image(&perm, &d) |] ):gocAfter) + ) + + ) + else na "rule_Image_Comprehendable" + theRule _ = na "rule_Image_Comprehendable" ---TODO image over Essence Types --- ---e.g. - -- - -- [essence| [ - | t <- image(p, rel)] |] refines to [essence| [ - | t' <- rel, let t = image(p, t') ] |] -- diff --git a/src/Conjure/Rules/Vertical/Permutation.hs b/src/Conjure/Rules/Vertical/Permutation.hs index 09bf9ec5e6..3578cac23f 100644 --- a/src/Conjure/Rules/Vertical/Permutation.hs +++ b/src/Conjure/Rules/Vertical/Permutation.hs @@ -55,21 +55,19 @@ rule_Image = "permutation-image{AsFunction}" `namedRule` theRule where case match permutationLiteral p of Nothing -> do typeI <- typeOf i - if typeI `containsType` inner + if typesUnify [inner, typeI] then do [f] <- downX1 p - if typesUnify [inner, typeI] - then return - ( "Vertical rule for permutation application to a single value" - , do - return [essence| [&i, catchUndef(image(&f,&i),0)][toInt(&i in defined(&f))+1] |] - ) - else na "rule_Image" - else return - ( "Vertical rule for permutation application to a type the permutation doesn't care about" - , do - return [essence| &i |] - ) + return ( "Vertical rule for permutation application to a single value" + , do + return [essence| [&i, catchUndef(image(&f,&i),0)][toInt(&i in defined(&f))+1] |] + ) + else if typeI `containsType` inner + then na "rule_Image" + else return ( "Vertical rule for permutation application to a type the permutation doesn't care about" + , do + return [essence| &i |] + ) _ -> na "rule_Image" theRule _ = na "rule_Image" diff --git a/src/Conjure/UI/Model.hs b/src/Conjure/UI/Model.hs index 2881c79d2e..62918fdb08 100644 --- a/src/Conjure/UI/Model.hs +++ b/src/Conjure/UI/Model.hs @@ -1212,10 +1212,12 @@ horizontalRules = [ Horizontal.Permutation.rule_Cardinality_Literal , Horizontal.Permutation.rule_Equality , Horizontal.Permutation.rule_Permute_Comprehension_Tuples_Literal + , Horizontal.Permutation.rule_Compose_Image +-- , Horizontal.Permutation.rule_Compose , Horizontal.Permutation.rule_Image_Literal , Horizontal.Permutation.rule_In , Horizontal.Permutation.rule_Permutation_Inverse - , Horizontal.Permutation.rule_Compose + , Horizontal.Permutation.rule_Image_Comprehendable -- , Horizontal.Permutation.rule_Image_Literal_Comprehension diff --git a/tests/custom/permutations/07_compose/int/0002_letting_and_given/permutation.essence b/tests/custom/permutations/07_compose/int/0002_letting_and_given/permutation.essence new file mode 100644 index 0000000000..c4755c7ed0 --- /dev/null +++ b/tests/custom/permutations/07_compose/int/0002_letting_and_given/permutation.essence @@ -0,0 +1,11 @@ +letting n be 4 + +given p : permutation of int(1..n) +letting q be permutation((1,2,4)) +given i : int(0..5) +given j : int(0..5) + +find b : bool + +such that b = (j = image(compose(q,p),i)) + diff --git a/tests/custom/permutations/07_compose/int/0002_letting_and_given/permutation.param b/tests/custom/permutations/07_compose/int/0002_letting_and_given/permutation.param new file mode 100644 index 0000000000..5ad6d6df98 --- /dev/null +++ b/tests/custom/permutations/07_compose/int/0002_letting_and_given/permutation.param @@ -0,0 +1,3 @@ +letting p be permutation((1,3,4)) +letting i be 1 +letting j be 2 diff --git a/tests/custom/permutations/07_compose/int/0002_letting_and_given/run.sh b/tests/custom/permutations/07_compose/int/0002_letting_and_given/run.sh new file mode 100755 index 0000000000..9dc67e67f5 --- /dev/null +++ b/tests/custom/permutations/07_compose/int/0002_letting_and_given/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence *.param +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/07_compose/int/0002_letting_and_given/stdout.expected b/tests/custom/permutations/07_compose/int/0002_letting_and_given/stdout.expected new file mode 100644 index 0000000000..1cc90d46bc --- /dev/null +++ b/tests/custom/permutations/07_compose/int/0002_letting_and_given/stdout.expected @@ -0,0 +1,8 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime permutation.param +Copying solution to: permutation-permutation.solution +language Essence 1.3 + +letting b be false diff --git a/tests/custom/permutations/08_image_set/int/0001_given_permutation_letting_set/permutation.essence b/tests/custom/permutations/08_image_set/int/0001_given_permutation_letting_set/permutation.essence new file mode 100644 index 0000000000..d503098c60 --- /dev/null +++ b/tests/custom/permutations/08_image_set/int/0001_given_permutation_letting_set/permutation.essence @@ -0,0 +1,10 @@ +letting n be 4 + +given p : permutation of int(1..n) +given s : set of int(1..n) + +find sn : set of int(1..n) + + +such that sn = image(p,s) + diff --git a/tests/custom/permutations/08_image_set/int/0001_given_permutation_letting_set/permutation.param b/tests/custom/permutations/08_image_set/int/0001_given_permutation_letting_set/permutation.param new file mode 100644 index 0000000000..ca0e445536 --- /dev/null +++ b/tests/custom/permutations/08_image_set/int/0001_given_permutation_letting_set/permutation.param @@ -0,0 +1,2 @@ +letting p be permutation((1,3,4)) +letting s be {1,2} diff --git a/tests/custom/permutations/08_image_set/int/0001_given_permutation_letting_set/run.sh b/tests/custom/permutations/08_image_set/int/0001_given_permutation_letting_set/run.sh new file mode 100755 index 0000000000..9dc67e67f5 --- /dev/null +++ b/tests/custom/permutations/08_image_set/int/0001_given_permutation_letting_set/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence *.param +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/08_image_set/int/0001_given_permutation_letting_set/stdout.expected b/tests/custom/permutations/08_image_set/int/0001_given_permutation_letting_set/stdout.expected new file mode 100644 index 0000000000..3d0b07b4fc --- /dev/null +++ b/tests/custom/permutations/08_image_set/int/0001_given_permutation_letting_set/stdout.expected @@ -0,0 +1,8 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime permutation.param +Copying solution to: permutation-permutation.solution +language Essence 1.3 + +letting sn be {2, 3} diff --git a/tests/custom/permutations/08_image_set/int/0002_given_permutation_find_sets/permutation.essence b/tests/custom/permutations/08_image_set/int/0002_given_permutation_find_sets/permutation.essence new file mode 100644 index 0000000000..421b59bd2a --- /dev/null +++ b/tests/custom/permutations/08_image_set/int/0002_given_permutation_find_sets/permutation.essence @@ -0,0 +1,11 @@ +letting n be 4 + +given p : permutation of int(1..n) + +find s : set of int(1..n) + +find sn : set of int(1..n) + + +such that sn = image(p,s) + diff --git a/tests/custom/permutations/08_image_set/int/0002_given_permutation_find_sets/permutation.param b/tests/custom/permutations/08_image_set/int/0002_given_permutation_find_sets/permutation.param new file mode 100644 index 0000000000..8a8c516801 --- /dev/null +++ b/tests/custom/permutations/08_image_set/int/0002_given_permutation_find_sets/permutation.param @@ -0,0 +1 @@ +letting p be permutation((1,3,4)) diff --git a/tests/custom/permutations/08_image_set/int/0002_given_permutation_find_sets/run.sh b/tests/custom/permutations/08_image_set/int/0002_given_permutation_find_sets/run.sh new file mode 100755 index 0000000000..aab5d44c6e --- /dev/null +++ b/tests/custom/permutations/08_image_set/int/0002_given_permutation_find_sets/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence *.param --number-of-solutions=10 +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/08_image_set/int/0002_given_permutation_find_sets/stdout.expected b/tests/custom/permutations/08_image_set/int/0002_given_permutation_find_sets/stdout.expected new file mode 100644 index 0000000000..e408f884c6 --- /dev/null +++ b/tests/custom/permutations/08_image_set/int/0002_given_permutation_find_sets/stdout.expected @@ -0,0 +1,54 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime permutation.param +Copying solution to: permutation-permutation-000001.solution +Copying solution to: permutation-permutation-000002.solution +Copying solution to: permutation-permutation-000003.solution +Copying solution to: permutation-permutation-000004.solution +Copying solution to: permutation-permutation-000005.solution +Copying solution to: permutation-permutation-000006.solution +Copying solution to: permutation-permutation-000007.solution +Copying solution to: permutation-permutation-000008.solution +Copying solution to: permutation-permutation-000009.solution +Copying solution to: permutation-permutation-000010.solution +language Essence 1.3 + +letting s be {} +letting sn be {} +language Essence 1.3 + +letting s be {4} +letting sn be {1} +language Essence 1.3 + +letting s be {3} +letting sn be {4} +language Essence 1.3 + +letting s be {3, 4} +letting sn be {1, 4} +language Essence 1.3 + +letting s be {2} +letting sn be {2} +language Essence 1.3 + +letting s be {2, 4} +letting sn be {1, 2} +language Essence 1.3 + +letting s be {2, 3} +letting sn be {2, 4} +language Essence 1.3 + +letting s be {2, 3, 4} +letting sn be {1, 2, 4} +language Essence 1.3 + +letting s be {1} +letting sn be {3} +language Essence 1.3 + +letting s be {1, 4} +letting sn be {1, 3} diff --git a/tests/custom/permutations/08_image_set/int/0003_letting_permutation_find_sets/permutation.essence b/tests/custom/permutations/08_image_set/int/0003_letting_permutation_find_sets/permutation.essence new file mode 100644 index 0000000000..0badd860c7 --- /dev/null +++ b/tests/custom/permutations/08_image_set/int/0003_letting_permutation_find_sets/permutation.essence @@ -0,0 +1,11 @@ +letting n be 4 + +letting p be permutation((1,3,4)) + +find s : set of int(1..n) + +find sn : set of int(1..n) + + +such that sn = image(p,s) + diff --git a/tests/custom/permutations/08_image_set/int/0003_letting_permutation_find_sets/run.sh b/tests/custom/permutations/08_image_set/int/0003_letting_permutation_find_sets/run.sh new file mode 100755 index 0000000000..03373df6cb --- /dev/null +++ b/tests/custom/permutations/08_image_set/int/0003_letting_permutation_find_sets/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence --number-of-solutions=10 +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/08_image_set/int/0003_letting_permutation_find_sets/stdout.expected b/tests/custom/permutations/08_image_set/int/0003_letting_permutation_find_sets/stdout.expected new file mode 100644 index 0000000000..e436325718 --- /dev/null +++ b/tests/custom/permutations/08_image_set/int/0003_letting_permutation_find_sets/stdout.expected @@ -0,0 +1,54 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Copying solution to: permutation-000001.solution +Copying solution to: permutation-000002.solution +Copying solution to: permutation-000003.solution +Copying solution to: permutation-000004.solution +Copying solution to: permutation-000005.solution +Copying solution to: permutation-000006.solution +Copying solution to: permutation-000007.solution +Copying solution to: permutation-000008.solution +Copying solution to: permutation-000009.solution +Copying solution to: permutation-000010.solution +language Essence 1.3 + +letting s be {} +letting sn be {} +language Essence 1.3 + +letting s be {4} +letting sn be {1} +language Essence 1.3 + +letting s be {3} +letting sn be {4} +language Essence 1.3 + +letting s be {3, 4} +letting sn be {1, 4} +language Essence 1.3 + +letting s be {2} +letting sn be {2} +language Essence 1.3 + +letting s be {2, 4} +letting sn be {1, 2} +language Essence 1.3 + +letting s be {2, 3} +letting sn be {2, 4} +language Essence 1.3 + +letting s be {2, 3, 4} +letting sn be {1, 2, 4} +language Essence 1.3 + +letting s be {1} +letting sn be {3} +language Essence 1.3 + +letting s be {1, 4} +letting sn be {1, 3} diff --git a/tests/custom/permutations/08_image_set/runthese.sh b/tests/custom/permutations/08_image_set/runthese.sh new file mode 100644 index 0000000000..3e9eeed3ec --- /dev/null +++ b/tests/custom/permutations/08_image_set/runthese.sh @@ -0,0 +1,2 @@ +stack install +stack test --test-arguments "-p custom.permutations.08_image_set" From 362fd247b44f35fed0ae92f9fa4f9ebf830b6f6b Mon Sep 17 00:00:00 2001 From: Fraser Dunlop Date: Mon, 17 Dec 2018 16:18:12 +0000 Subject: [PATCH 055/229] compose rule that finds new permutation is fix --- src/Conjure/Compute/DomainUnion.hs | 10 + src/Conjure/Rules/Horizontal/Permutation.hs | 191 ++++++++++++-------- src/Conjure/UI/Model.hs | 4 +- 3 files changed, 125 insertions(+), 80 deletions(-) diff --git a/src/Conjure/Compute/DomainUnion.hs b/src/Conjure/Compute/DomainUnion.hs index 229605943c..40a865f95c 100644 --- a/src/Conjure/Compute/DomainUnion.hs +++ b/src/Conjure/Compute/DomainUnion.hs @@ -69,6 +69,8 @@ instance = DomainRelation def <$> domainUnion xA yA <*> zipWithM domainUnion xs ys domainUnion (DomainPartition _ xA x) (DomainPartition _ yA y) = DomainPartition def <$> domainUnion xA yA <*> domainUnion x y + domainUnion (DomainPermutation _ xA x) (DomainPermutation _ yA y) + = DomainPermutation def <$> domainUnion xA yA <*> domainUnion x y domainUnion d1 d2 = bug $ vcat ["Domain.domainUnion", pretty d1, pretty d2] @@ -79,6 +81,14 @@ instance ) => DomainUnion (SetAttr x) where domainUnion (SetAttr a) (SetAttr b) = SetAttr <$> domainUnion a b +instance + ( ExpressionLike x + , Op x :< x + , Pretty x + ) => DomainUnion (PermutationAttr x) where + domainUnion (PermutationAttr a) (PermutationAttr b) = PermutationAttr <$> domainUnion a b + + instance ( ExpressionLike x diff --git a/src/Conjure/Rules/Horizontal/Permutation.hs b/src/Conjure/Rules/Horizontal/Permutation.hs index 0ac4b250cc..ea259a1a29 100644 --- a/src/Conjure/Rules/Horizontal/Permutation.hs +++ b/src/Conjure/Rules/Horizontal/Permutation.hs @@ -63,53 +63,53 @@ rule_Permute_Comprehension_Tuples_Literal = "permutation-comprehension-tuples{As ) theRule _ = na "rule_Comprehension_Tuples_Literal" ---rule_Image_Literal' :: Rule ---rule_Image_Literal' = "permutation-image-literal" `namedRule` theRule where --- theRule [essence| image(&p, &i) |] = do --- (TypePermutation inner, elems) <- match permutationLiteral p --- DomainPermutation _ _ innerP <- domainOf p --- let f' = toFunction <$> fromCycles elems --- case f' of --- Left er -> fail $ "Permutation literal invalid." <++> stringToDoc (show er) --- Right f -> do --- let outLiteral = make matrixLiteral --- (TypeMatrix (TypeInt AnyTag) (TypeTuple [inner,inner])) innerP --- [ AbstractLiteral (AbsLitTuple [de --- ,f de]) --- | de <- join elems --- ] --- typeI <- typeOf i --- if typesUnify [inner, typeI] --- then do --- innerD <- domainOf i --- return --- ( "Horizontal rule for permutation literal application to a single value (image), AsFunction representation" --- , do --- (hName, h) <- auxiliaryVar --- (fPat, f) <- quantifiedVar --- (tPat, t) <- quantifiedVar --- (gPat, g) <- quantifiedVar --- (ePat, _) <- quantifiedVar --- return $ WithLocals --- [essence| &h |] --- (AuxiliaryVars --- [ Declaration (FindOrGiven LocalFind hName innerD) --- , SuchThat --- [ [essence| --- (forAll (&fPat, &tPat) in &outLiteral . &f = &i <-> &h = &t) --- /\ (!(exists (&gPat, &ePat) in &outLiteral . &g = &h) <-> &h = &i) --- |] --- ] --- ] --- ) --- ) --- else if typeI `containsType` inner --- then na "rule_Image_Literal" --- else return ( "Horizontal rule for permutation application to a type the permutation doesn't care about" --- , do --- return [essence| &i |] --- ) --- theRule _ = na "rule_Image_Literal" +rule_Image_Literal_Find :: Rule +rule_Image_Literal_Find = "permutation-image-literal" `namedRule` theRule where + theRule [essence| image(&p, &i) |] = do + (TypePermutation inner, elems) <- match permutationLiteral p + DomainPermutation _ _ innerP <- domainOf p + let f' = toFunction <$> fromCycles elems + case f' of + Left er -> fail $ "Permutation literal invalid." <++> stringToDoc (show er) + Right f -> do + let outLiteral = make matrixLiteral + (TypeMatrix (TypeInt AnyTag) (TypeTuple [inner,inner])) innerP + [ AbstractLiteral (AbsLitTuple [de + ,f de]) + | de <- join elems + ] + typeI <- typeOf i + if typesUnify [inner, typeI] + then do + innerD <- domainOf i + return + ( "Horizontal rule for permutation literal application to a single value (image), AsFunction representation" + , do + (hName, h) <- auxiliaryVar + (fPat, f) <- quantifiedVar + (tPat, t) <- quantifiedVar + (gPat, g) <- quantifiedVar + (ePat, _) <- quantifiedVar + return $ WithLocals + [essence| &h |] + (AuxiliaryVars + [ Declaration (FindOrGiven LocalFind hName innerD) + , SuchThat + [ [essence| + (forAll (&fPat, &tPat) in &outLiteral . &f = &i <-> &h = &t) + /\ (!(exists (&gPat, &ePat) in &outLiteral . &g = &h) <-> &h = &i) + |] + ] + ] + ) + ) + else if typeI `containsType` inner + then na "rule_Image_Literal" + else return ( "Horizontal rule for permutation application to a type the permutation doesn't care about" + , do + return [essence| &i |] + ) + theRule _ = na "rule_Image_Literal" rule_Image_Literal :: Rule @@ -137,6 +137,39 @@ rule_Image_Literal = "permutation-image-literal" `namedRule` theRule where ) theRule _ = na "rule_Image_Literal" +rule_Image_Literal_Comprehension :: Rule +rule_Image_Literal_Comprehension = "permutation-image-literal-comprehension" `namedRule` theRule where + theRule (Comprehension body gensOrConds) = do + (gocBefore, (pat, p, i), gocAfter) <- matchFirst gensOrConds $ \ goc -> case goc of + Generator (GenInExpr pat [essence| image(&p, &i) |]) -> return (pat, p, i) + _ -> na "rule_Image_Literal_Comprehension" + (TypePermutation inner, elems) <- match permutationLiteral p + let f' = toFunction <$> fromCycles elems + case f' of + Left er -> fail $ "Permutation literal invalid." <++> stringToDoc (show er) + Right f -> do + typeI <- typeOf i + if typesUnify [inner, typeI] + then do + let outLiteral = make functionLiteral (TypeFunction inner inner) [ (de,f de) | de <- join elems ] + return + ( "Horizontal rule for permutation literal application to a single value (image), AsFunction representation" + , do + return $ Comprehension body $ gocBefore + ++ [ Generator (GenInExpr pat (reTag AnyTag [essence| [&i, catchUndef(image(&outLiteral,&i),0)][toInt(&i in defined(&outLiteral))+1] |])) + ] ++ gocAfter + ) + else if typeI `containsType` inner + then na "rule_Image_Literal_Comprehension" + else return ( "Horizontal rule for permutation application to a type the permutation doesn't care about" + , do + return $ Comprehension body $ gocBefore + ++ [ Generator (GenInExpr pat [essence| &i |]) ] + ++ gocAfter + ) + theRule _ = na "rule_Image_Literal_Comprehension" + + rule_In :: Rule rule_In = "permutation-in" `namedRule` theRule where @@ -178,7 +211,7 @@ rule_Compose_Image :: Rule rule_Compose_Image = "permutation-compose-image" `namedRule` theRule where theRule [essence| image(compose(&g, &h),&i) |] = do case match permutationLiteral h of - Nothing -> return () + Nothing -> return () -- This rule + rule_Image_Literal makes SR explode Just _ -> na "rule_Compose_Image" TypePermutation innerG <- typeOf g TypePermutation innerH <- typeOf g @@ -192,37 +225,37 @@ rule_Compose_Image = "permutation-compose-image" `namedRule` theRule where else na "rule_Compose_Image" theRule _ = na "rule_Compose_Image" ---rule_Compose :: Rule ---rule_Compose = "permutation-compose" `namedRule` theRule where --- theRule [essence| compose(&g,&h) |] = do --- TypePermutation innerG <- typeOf g --- TypePermutation innerH <- typeOf h --- (DomainPermutation _ _ dg) <- domainOf g --- (DomainPermutation _ _ dh) <- domainOf h --- if typesUnify [innerG, innerH] --- then do --- du <- domainUnion dg dh --- return ( "Horizontal rule for permutation composition" --- , do --- --- (lPat, l) <- quantifiedVar --- (rPat, r) <- quantifiedVar --- (pName, p) <- auxiliaryVar --- return $ WithLocals --- [essence| &p |] --- ( AuxiliaryVars --- [ Declaration (FindOrGiven LocalFind pName du) --- , SuchThat --- [ [essence| --- and([image(&p,&l[1]) = image(&g, image(&h,&l[1])) | &lPat <- &g]) --- /\ and([image(&p,&r[1]) = image(&g, image(&h,&r[1])) | &rPat <- &h]) --- |] --- ] --- ] --- ) --- ) --- else na "rule_Compose" --- theRule _ = na "rule_Compose" +rule_Compose :: Rule +rule_Compose = "permutation-compose" `namedRule` theRule where + theRule [essence| compose(&g,&h) |] = do + TypePermutation innerG <- typeOf g + TypePermutation innerH <- typeOf h + dg <- domainOf g + dh <- domainOf h + if typesUnify [innerG, innerH] + then do + du <- domainUnion dg dh + return ( "Horizontal rule for permutation composition" + , do + + (lPat, l) <- quantifiedVar + (rPat, r) <- quantifiedVar + (pName, p) <- auxiliaryVar + return $ WithLocals + [essence| &p |] + ( AuxiliaryVars + [ Declaration (FindOrGiven LocalFind pName du) + , SuchThat +--TODO this rule is not correct as it is not restrictive enough +--rewrite with defined to constrain size of found permutation + [ [essence| and([image(&p,&l[1]) = image(&g, image(&h,&l[1])) | &lPat <- &g]) /\ and([image(&p,&r[1]) = image(&g, image(&h,&r[1])) | &rPat <- &h]) + |] + ] + ] + ) + ) + else na "rule_Compose" + theRule _ = na "rule_Compose" rule_Image_Comprehendable :: Rule rule_Image_Comprehendable = "comprehendable-image" `namedRule` theRule where diff --git a/src/Conjure/UI/Model.hs b/src/Conjure/UI/Model.hs index 62918fdb08..90323fdf13 100644 --- a/src/Conjure/UI/Model.hs +++ b/src/Conjure/UI/Model.hs @@ -1213,8 +1213,10 @@ horizontalRules = , Horizontal.Permutation.rule_Equality , Horizontal.Permutation.rule_Permute_Comprehension_Tuples_Literal , Horizontal.Permutation.rule_Compose_Image --- , Horizontal.Permutation.rule_Compose + , Horizontal.Permutation.rule_Compose , Horizontal.Permutation.rule_Image_Literal +-- , Horizontal.Permutation.rule_Image_Literal_Comprehension +-- , Horizontal.Permutation.rule_Image_Literal_Find , Horizontal.Permutation.rule_In , Horizontal.Permutation.rule_Permutation_Inverse , Horizontal.Permutation.rule_Image_Comprehendable From 53f8f78cfe63c150e572e44ae626d414332d50be Mon Sep 17 00:00:00 2001 From: Fraser Dunlop Date: Tue, 18 Dec 2018 11:36:20 +0000 Subject: [PATCH 056/229] change to cardinality def + defined --- .../0001_given_permutation_in_param/stdout.expected | 2 +- .../enum/0003_find_permutation/stdout.expected | 2 +- .../0001_given_permutation_in_param/stdout.expected | 2 +- .../int/0003_find_permutation/stdout.expected | 2 +- tests/custom/permutations/02_cardinality/runthese.sh | 3 +-- .../unnamed/0003_find_permutation/stdout.expected | 2 +- .../permutation.essence | 2 +- .../permutation.essence | 2 +- .../permutation.essence | 2 +- .../permutation.essence | 2 +- tests/custom/permutations/04_image/runthese.sh | 3 +-- .../permutation.essence | 2 +- .../int/0005_find_composition/permutation.essence | 9 +++++++++ .../07_compose/int/0005_find_composition/run.sh | 3 +++ .../int/0005_find_composition/stdout.expected | 12 ++++++++++++ .../int/0006_find_composition/permutation.essence | 9 +++++++++ .../07_compose/int/0006_find_composition/run.sh | 3 +++ .../int/0006_find_composition/stdout.expected | 8 ++++++++ tests/custom/permutations/07_compose/runthese.sh | 3 +-- .../unnamed/0004_find_and_find/permutation.essence | 4 ++-- .../int/0001_letting_permutation/permutation.essence | 10 ++++++++++ .../int/0001_letting_permutation/permutation.param | 1 + .../09_defined/int/0001_letting_permutation/run.sh | 3 +++ .../int/0001_letting_permutation/stdout.expected | 8 ++++++++ .../int/0002_letting_permutation/permutation.essence | 10 ++++++++++ .../int/0002_letting_permutation/permutation.param | 1 + .../09_defined/int/0002_letting_permutation/run.sh | 3 +++ .../int/0002_letting_permutation/stdout.expected | 8 ++++++++ .../int/0003_given_permutation/permutation.essence | 10 ++++++++++ .../int/0003_given_permutation/permutation.param | 2 ++ .../09_defined/int/0003_given_permutation/run.sh | 3 +++ .../int/0003_given_permutation/stdout.expected | 8 ++++++++ .../int/0004_given_permutation/permutation.essence | 7 +++++++ .../int/0004_given_permutation/permutation.param | 2 ++ .../09_defined/int/0004_given_permutation/run.sh | 3 +++ .../int/0004_given_permutation/stdout.expected | 8 ++++++++ tests/custom/permutations/09_defined/runthese.sh | 1 + tests/custom/permutations/runthese.sh | 3 +-- 38 files changed, 148 insertions(+), 20 deletions(-) create mode 100644 tests/custom/permutations/07_compose/int/0005_find_composition/permutation.essence create mode 100755 tests/custom/permutations/07_compose/int/0005_find_composition/run.sh create mode 100644 tests/custom/permutations/07_compose/int/0005_find_composition/stdout.expected create mode 100644 tests/custom/permutations/07_compose/int/0006_find_composition/permutation.essence create mode 100755 tests/custom/permutations/07_compose/int/0006_find_composition/run.sh create mode 100644 tests/custom/permutations/07_compose/int/0006_find_composition/stdout.expected create mode 100644 tests/custom/permutations/09_defined/int/0001_letting_permutation/permutation.essence create mode 100644 tests/custom/permutations/09_defined/int/0001_letting_permutation/permutation.param create mode 100755 tests/custom/permutations/09_defined/int/0001_letting_permutation/run.sh create mode 100644 tests/custom/permutations/09_defined/int/0001_letting_permutation/stdout.expected create mode 100644 tests/custom/permutations/09_defined/int/0002_letting_permutation/permutation.essence create mode 100644 tests/custom/permutations/09_defined/int/0002_letting_permutation/permutation.param create mode 100755 tests/custom/permutations/09_defined/int/0002_letting_permutation/run.sh create mode 100644 tests/custom/permutations/09_defined/int/0002_letting_permutation/stdout.expected create mode 100644 tests/custom/permutations/09_defined/int/0003_given_permutation/permutation.essence create mode 100644 tests/custom/permutations/09_defined/int/0003_given_permutation/permutation.param create mode 100755 tests/custom/permutations/09_defined/int/0003_given_permutation/run.sh create mode 100644 tests/custom/permutations/09_defined/int/0003_given_permutation/stdout.expected create mode 100644 tests/custom/permutations/09_defined/int/0004_given_permutation/permutation.essence create mode 100644 tests/custom/permutations/09_defined/int/0004_given_permutation/permutation.param create mode 100755 tests/custom/permutations/09_defined/int/0004_given_permutation/run.sh create mode 100644 tests/custom/permutations/09_defined/int/0004_given_permutation/stdout.expected create mode 100644 tests/custom/permutations/09_defined/runthese.sh diff --git a/tests/custom/permutations/02_cardinality/enum/0001_given_permutation_in_param/stdout.expected b/tests/custom/permutations/02_cardinality/enum/0001_given_permutation_in_param/stdout.expected index d20985577b..0165072a84 100644 --- a/tests/custom/permutations/02_cardinality/enum/0001_given_permutation_in_param/stdout.expected +++ b/tests/custom/permutations/02_cardinality/enum/0001_given_permutation_in_param/stdout.expected @@ -5,4 +5,4 @@ Savile Row: model000001.eprime permutation.param Copying solution to: permutation-permutation.solution language Essence 1.3 -letting i be 3 +letting i be 4 diff --git a/tests/custom/permutations/02_cardinality/enum/0003_find_permutation/stdout.expected b/tests/custom/permutations/02_cardinality/enum/0003_find_permutation/stdout.expected index 4e026e23dd..68ac740d13 100644 --- a/tests/custom/permutations/02_cardinality/enum/0003_find_permutation/stdout.expected +++ b/tests/custom/permutations/02_cardinality/enum/0003_find_permutation/stdout.expected @@ -5,5 +5,5 @@ Savile Row: model000001.eprime Copying solution to: permutation.solution language Essence 1.3 -letting i be 4 +letting i be 6 letting p be permutation((E3, E4), (E5, E6)) diff --git a/tests/custom/permutations/02_cardinality/int/0001_given_permutation_in_param/stdout.expected b/tests/custom/permutations/02_cardinality/int/0001_given_permutation_in_param/stdout.expected index d20985577b..0165072a84 100644 --- a/tests/custom/permutations/02_cardinality/int/0001_given_permutation_in_param/stdout.expected +++ b/tests/custom/permutations/02_cardinality/int/0001_given_permutation_in_param/stdout.expected @@ -5,4 +5,4 @@ Savile Row: model000001.eprime permutation.param Copying solution to: permutation-permutation.solution language Essence 1.3 -letting i be 3 +letting i be 4 diff --git a/tests/custom/permutations/02_cardinality/int/0003_find_permutation/stdout.expected b/tests/custom/permutations/02_cardinality/int/0003_find_permutation/stdout.expected index 8030f81a88..adb884d68a 100644 --- a/tests/custom/permutations/02_cardinality/int/0003_find_permutation/stdout.expected +++ b/tests/custom/permutations/02_cardinality/int/0003_find_permutation/stdout.expected @@ -5,5 +5,5 @@ Savile Row: model000001.eprime Copying solution to: permutation.solution language Essence 1.3 -letting i be 4 +letting i be 6 letting p be permutation((3, 4), (5, 6)) diff --git a/tests/custom/permutations/02_cardinality/runthese.sh b/tests/custom/permutations/02_cardinality/runthese.sh index c39242ca37..d087e47838 100644 --- a/tests/custom/permutations/02_cardinality/runthese.sh +++ b/tests/custom/permutations/02_cardinality/runthese.sh @@ -1,2 +1 @@ -stack install -stack test --test-arguments "-p custom.permutations.02_cardinality" +stack build --copy-bins --test --test-arguments "-p custom.permutations.02_cardinality" diff --git a/tests/custom/permutations/02_cardinality/unnamed/0003_find_permutation/stdout.expected b/tests/custom/permutations/02_cardinality/unnamed/0003_find_permutation/stdout.expected index 08c17fa62d..f14be02e29 100644 --- a/tests/custom/permutations/02_cardinality/unnamed/0003_find_permutation/stdout.expected +++ b/tests/custom/permutations/02_cardinality/unnamed/0003_find_permutation/stdout.expected @@ -6,5 +6,5 @@ Copying solution to: permutation.solution language Essence 1.3 letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6} -letting i be 4 +letting i be 6 letting p be permutation((n_3, n_4), (n_5, n_6)) diff --git a/tests/custom/permutations/04_image/enum/0005_find_permutation_given_enums/permutation.essence b/tests/custom/permutations/04_image/enum/0005_find_permutation_given_enums/permutation.essence index 4eacc18605..04775d022f 100644 --- a/tests/custom/permutations/04_image/enum/0005_find_permutation_given_enums/permutation.essence +++ b/tests/custom/permutations/04_image/enum/0005_find_permutation_given_enums/permutation.essence @@ -7,7 +7,7 @@ find p : permutation of n given j : n such that - j = image(p, i) /\ |p| = 3 + j = image(p, i) /\ sum([toInt(l!=r)|(l,r)<-p]) = 3 diff --git a/tests/custom/permutations/04_image/enum/0007_find_permutation_find_enums/permutation.essence b/tests/custom/permutations/04_image/enum/0007_find_permutation_find_enums/permutation.essence index c994d8042b..530076abc4 100644 --- a/tests/custom/permutations/04_image/enum/0007_find_permutation_find_enums/permutation.essence +++ b/tests/custom/permutations/04_image/enum/0007_find_permutation_find_enums/permutation.essence @@ -7,7 +7,7 @@ find p : permutation of n find j : n such that - j = image(p, i) /\ |p| = 3 + j = image(p, i) /\ sum([toInt(l!=r)|(l,r)<-p]) = 3 diff --git a/tests/custom/permutations/04_image/int/0005_find_permutation_given_ints/permutation.essence b/tests/custom/permutations/04_image/int/0005_find_permutation_given_ints/permutation.essence index 4cd6172d9d..fb725c1838 100644 --- a/tests/custom/permutations/04_image/int/0005_find_permutation_given_ints/permutation.essence +++ b/tests/custom/permutations/04_image/int/0005_find_permutation_given_ints/permutation.essence @@ -5,7 +5,7 @@ find p : permutation of int(1..4) given j : int(0..10) such that - j = image(p, i) /\ |p| = 3 + j = image(p, i) /\ sum([toInt(l!=r)|(l,r)<-p])= 3 diff --git a/tests/custom/permutations/04_image/int/0007_find_permutation_find_ints/permutation.essence b/tests/custom/permutations/04_image/int/0007_find_permutation_find_ints/permutation.essence index 08f32ca98a..a4e00cabe0 100644 --- a/tests/custom/permutations/04_image/int/0007_find_permutation_find_ints/permutation.essence +++ b/tests/custom/permutations/04_image/int/0007_find_permutation_find_ints/permutation.essence @@ -7,7 +7,7 @@ find p : permutation of n find j : n such that - j = image(p, i) /\ |p| = 3 + j = image(p, i) /\ sum([toInt(l!=r)|(l,r)<-p]) = 3 diff --git a/tests/custom/permutations/04_image/runthese.sh b/tests/custom/permutations/04_image/runthese.sh index 0ca42228a0..42c6fb5f7b 100644 --- a/tests/custom/permutations/04_image/runthese.sh +++ b/tests/custom/permutations/04_image/runthese.sh @@ -1,2 +1 @@ -stack install -stack test --test-arguments "-p custom.permutations.04_image" +stack build --copy-bins --test --test-arguments "-p custom.permutations.04_image" diff --git a/tests/custom/permutations/04_image/unnamed/0007_find_permutation_find_unnameds/permutation.essence b/tests/custom/permutations/04_image/unnamed/0007_find_permutation_find_unnameds/permutation.essence index 95bff24946..62aca160b0 100644 --- a/tests/custom/permutations/04_image/unnamed/0007_find_permutation_find_unnameds/permutation.essence +++ b/tests/custom/permutations/04_image/unnamed/0007_find_permutation_find_unnameds/permutation.essence @@ -7,7 +7,7 @@ find p : permutation of n find j : n such that - j = image(p, i) /\ |p| = 3 + j = image(p, i) /\ sum([toInt(l!=r)|(l,r)<-p]) = 3 diff --git a/tests/custom/permutations/07_compose/int/0005_find_composition/permutation.essence b/tests/custom/permutations/07_compose/int/0005_find_composition/permutation.essence new file mode 100644 index 0000000000..e8a926c524 --- /dev/null +++ b/tests/custom/permutations/07_compose/int/0005_find_composition/permutation.essence @@ -0,0 +1,9 @@ +letting n be 4 + +letting p be permutation((3,4)) +letting q be permutation((1,2)) + +find c : permutation of int(1..n) + +such that c = compose(p,q) + diff --git a/tests/custom/permutations/07_compose/int/0005_find_composition/run.sh b/tests/custom/permutations/07_compose/int/0005_find_composition/run.sh new file mode 100755 index 0000000000..3c60e3f90e --- /dev/null +++ b/tests/custom/permutations/07_compose/int/0005_find_composition/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence --number-of-solutions=10 +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/07_compose/int/0005_find_composition/stdout.expected b/tests/custom/permutations/07_compose/int/0005_find_composition/stdout.expected new file mode 100644 index 0000000000..c308909413 --- /dev/null +++ b/tests/custom/permutations/07_compose/int/0005_find_composition/stdout.expected @@ -0,0 +1,12 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Copying solution to: permutation-000001.solution +Copying solution to: permutation-000002.solution +language Essence 1.3 + +letting c be permutation((1, 2)) +language Essence 1.3 + +letting c be permutation((1, 2), (3, 4)) diff --git a/tests/custom/permutations/07_compose/int/0006_find_composition/permutation.essence b/tests/custom/permutations/07_compose/int/0006_find_composition/permutation.essence new file mode 100644 index 0000000000..542b021aab --- /dev/null +++ b/tests/custom/permutations/07_compose/int/0006_find_composition/permutation.essence @@ -0,0 +1,9 @@ +letting n be 4 + +letting p be permutation((3,4)) +letting q be permutation((1,2,3)) + +find c : permutation of int(1..n) + +such that c = compose(p,q) + diff --git a/tests/custom/permutations/07_compose/int/0006_find_composition/run.sh b/tests/custom/permutations/07_compose/int/0006_find_composition/run.sh new file mode 100755 index 0000000000..3c60e3f90e --- /dev/null +++ b/tests/custom/permutations/07_compose/int/0006_find_composition/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence --number-of-solutions=10 +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/07_compose/int/0006_find_composition/stdout.expected b/tests/custom/permutations/07_compose/int/0006_find_composition/stdout.expected new file mode 100644 index 0000000000..44eece037a --- /dev/null +++ b/tests/custom/permutations/07_compose/int/0006_find_composition/stdout.expected @@ -0,0 +1,8 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Copying solution to: permutation.solution +language Essence 1.3 + +letting c be permutation((1, 2, 4)) diff --git a/tests/custom/permutations/07_compose/runthese.sh b/tests/custom/permutations/07_compose/runthese.sh index db7212b076..9537d9e1f4 100644 --- a/tests/custom/permutations/07_compose/runthese.sh +++ b/tests/custom/permutations/07_compose/runthese.sh @@ -1,2 +1 @@ -stack install -stack test --test-arguments "-p custom.permutations.07_compose" +stack build --copy-bins --test --test-arguments "-p custom.permutations.07_compose" diff --git a/tests/custom/permutations/07_compose/unnamed/0004_find_and_find/permutation.essence b/tests/custom/permutations/07_compose/unnamed/0004_find_and_find/permutation.essence index 3a5095a6e2..e412d8a573 100644 --- a/tests/custom/permutations/07_compose/unnamed/0004_find_and_find/permutation.essence +++ b/tests/custom/permutations/07_compose/unnamed/0004_find_and_find/permutation.essence @@ -5,5 +5,5 @@ find i : n such that i = image(compose(p,q),i) - /\ |p| = 4 - /\ |q| = 3 + /\ sum([toInt(l != r) | (l,r) <- p]) = 4 + /\ sum([toInt(l != r) | (l,r) <- q]) = 3 diff --git a/tests/custom/permutations/09_defined/int/0001_letting_permutation/permutation.essence b/tests/custom/permutations/09_defined/int/0001_letting_permutation/permutation.essence new file mode 100644 index 0000000000..e0eda0ff07 --- /dev/null +++ b/tests/custom/permutations/09_defined/int/0001_letting_permutation/permutation.essence @@ -0,0 +1,10 @@ +letting n be 4 + +letting p be permutation((1,3,4)) +given s : set of int(1..n) + +find b : bool + + +such that b = (s = defined(p)) + diff --git a/tests/custom/permutations/09_defined/int/0001_letting_permutation/permutation.param b/tests/custom/permutations/09_defined/int/0001_letting_permutation/permutation.param new file mode 100644 index 0000000000..e5a4debfc2 --- /dev/null +++ b/tests/custom/permutations/09_defined/int/0001_letting_permutation/permutation.param @@ -0,0 +1 @@ +letting s be {1,3,4} diff --git a/tests/custom/permutations/09_defined/int/0001_letting_permutation/run.sh b/tests/custom/permutations/09_defined/int/0001_letting_permutation/run.sh new file mode 100755 index 0000000000..9dc67e67f5 --- /dev/null +++ b/tests/custom/permutations/09_defined/int/0001_letting_permutation/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence *.param +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/09_defined/int/0001_letting_permutation/stdout.expected b/tests/custom/permutations/09_defined/int/0001_letting_permutation/stdout.expected new file mode 100644 index 0000000000..901f2ae574 --- /dev/null +++ b/tests/custom/permutations/09_defined/int/0001_letting_permutation/stdout.expected @@ -0,0 +1,8 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime permutation.param +Copying solution to: permutation-permutation.solution +language Essence 1.3 + +letting b be true diff --git a/tests/custom/permutations/09_defined/int/0002_letting_permutation/permutation.essence b/tests/custom/permutations/09_defined/int/0002_letting_permutation/permutation.essence new file mode 100644 index 0000000000..4d132bbc47 --- /dev/null +++ b/tests/custom/permutations/09_defined/int/0002_letting_permutation/permutation.essence @@ -0,0 +1,10 @@ +letting n be 4 + +letting p be permutation((1,2,4)) +given s : set of int(1..n) + +find b : bool + + +such that b = (s = defined(p)) + diff --git a/tests/custom/permutations/09_defined/int/0002_letting_permutation/permutation.param b/tests/custom/permutations/09_defined/int/0002_letting_permutation/permutation.param new file mode 100644 index 0000000000..e5a4debfc2 --- /dev/null +++ b/tests/custom/permutations/09_defined/int/0002_letting_permutation/permutation.param @@ -0,0 +1 @@ +letting s be {1,3,4} diff --git a/tests/custom/permutations/09_defined/int/0002_letting_permutation/run.sh b/tests/custom/permutations/09_defined/int/0002_letting_permutation/run.sh new file mode 100755 index 0000000000..9dc67e67f5 --- /dev/null +++ b/tests/custom/permutations/09_defined/int/0002_letting_permutation/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence *.param +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/09_defined/int/0002_letting_permutation/stdout.expected b/tests/custom/permutations/09_defined/int/0002_letting_permutation/stdout.expected new file mode 100644 index 0000000000..1cc90d46bc --- /dev/null +++ b/tests/custom/permutations/09_defined/int/0002_letting_permutation/stdout.expected @@ -0,0 +1,8 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime permutation.param +Copying solution to: permutation-permutation.solution +language Essence 1.3 + +letting b be false diff --git a/tests/custom/permutations/09_defined/int/0003_given_permutation/permutation.essence b/tests/custom/permutations/09_defined/int/0003_given_permutation/permutation.essence new file mode 100644 index 0000000000..ca2b07ea28 --- /dev/null +++ b/tests/custom/permutations/09_defined/int/0003_given_permutation/permutation.essence @@ -0,0 +1,10 @@ +letting n be 4 + +given p : permutation of int(1..n) +given s : set of int(1..n) + +find b : bool + + +such that b = (s = defined(p)) + diff --git a/tests/custom/permutations/09_defined/int/0003_given_permutation/permutation.param b/tests/custom/permutations/09_defined/int/0003_given_permutation/permutation.param new file mode 100644 index 0000000000..7826515575 --- /dev/null +++ b/tests/custom/permutations/09_defined/int/0003_given_permutation/permutation.param @@ -0,0 +1,2 @@ +letting p be permutation((1,3,4)) +letting s be {1,2,3,4} diff --git a/tests/custom/permutations/09_defined/int/0003_given_permutation/run.sh b/tests/custom/permutations/09_defined/int/0003_given_permutation/run.sh new file mode 100755 index 0000000000..9dc67e67f5 --- /dev/null +++ b/tests/custom/permutations/09_defined/int/0003_given_permutation/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence *.param +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/09_defined/int/0003_given_permutation/stdout.expected b/tests/custom/permutations/09_defined/int/0003_given_permutation/stdout.expected new file mode 100644 index 0000000000..901f2ae574 --- /dev/null +++ b/tests/custom/permutations/09_defined/int/0003_given_permutation/stdout.expected @@ -0,0 +1,8 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime permutation.param +Copying solution to: permutation-permutation.solution +language Essence 1.3 + +letting b be true diff --git a/tests/custom/permutations/09_defined/int/0004_given_permutation/permutation.essence b/tests/custom/permutations/09_defined/int/0004_given_permutation/permutation.essence new file mode 100644 index 0000000000..4dcc710f7b --- /dev/null +++ b/tests/custom/permutations/09_defined/int/0004_given_permutation/permutation.essence @@ -0,0 +1,7 @@ +letting n be 4 + +given p : permutation of int(1..n) +find s : set of int(1..n) + +such that s = defined(p) + diff --git a/tests/custom/permutations/09_defined/int/0004_given_permutation/permutation.param b/tests/custom/permutations/09_defined/int/0004_given_permutation/permutation.param new file mode 100644 index 0000000000..38c4159c22 --- /dev/null +++ b/tests/custom/permutations/09_defined/int/0004_given_permutation/permutation.param @@ -0,0 +1,2 @@ +letting p be permutation((1,3,4)) + diff --git a/tests/custom/permutations/09_defined/int/0004_given_permutation/run.sh b/tests/custom/permutations/09_defined/int/0004_given_permutation/run.sh new file mode 100755 index 0000000000..9dc67e67f5 --- /dev/null +++ b/tests/custom/permutations/09_defined/int/0004_given_permutation/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence *.param +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/09_defined/int/0004_given_permutation/stdout.expected b/tests/custom/permutations/09_defined/int/0004_given_permutation/stdout.expected new file mode 100644 index 0000000000..43cefee272 --- /dev/null +++ b/tests/custom/permutations/09_defined/int/0004_given_permutation/stdout.expected @@ -0,0 +1,8 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime permutation.param +Copying solution to: permutation-permutation.solution +language Essence 1.3 + +letting s be {1, 2, 3, 4} diff --git a/tests/custom/permutations/09_defined/runthese.sh b/tests/custom/permutations/09_defined/runthese.sh new file mode 100644 index 0000000000..ed2756d059 --- /dev/null +++ b/tests/custom/permutations/09_defined/runthese.sh @@ -0,0 +1 @@ +stack build --copy-bins --test --test-arguments "-p custom.permutations.09_defined" diff --git a/tests/custom/permutations/runthese.sh b/tests/custom/permutations/runthese.sh index e2d0c6b574..179fecc442 100644 --- a/tests/custom/permutations/runthese.sh +++ b/tests/custom/permutations/runthese.sh @@ -1,2 +1 @@ -stack install -stack test --test-arguments "-p custom.permutations" +stack build --copy-bins --test --test-arguments "-p custom.permutations" From 8c22609b0198eebe501928ce925021b967806d12 Mon Sep 17 00:00:00 2001 From: Fraser Dunlop Date: Tue, 18 Dec 2018 11:39:16 +0000 Subject: [PATCH 057/229] card def change + defined + some fixes --- src/Conjure/Language/Expression/Op/Defined.hs | 6 +++--- .../Function/Function1DPartial.hs | 8 ++++++-- src/Conjure/Rules/Horizontal/Permutation.hs | 13 ++++++++----- src/Conjure/Rules/Vertical/Permutation.hs | 19 ++++++++++++++++--- src/Conjure/UI/Model.hs | 1 + 5 files changed, 34 insertions(+), 13 deletions(-) diff --git a/src/Conjure/Language/Expression/Op/Defined.hs b/src/Conjure/Language/Expression/Op/Defined.hs index 6e96559f02..6dc1ad6820 100644 --- a/src/Conjure/Language/Expression/Op/Defined.hs +++ b/src/Conjure/Language/Expression/Op/Defined.hs @@ -23,7 +23,7 @@ instance (Pretty x, TypeOf x) => TypeOf (OpDefined x) where ty <- typeOf x case ty of TypeFunction a _ -> return (TypeSet a) --- TypePermutation a -> return (TypeSet a) + TypePermutation a -> return (TypeSet a) TypeSequence _ -> return (TypeSet (TypeInt NoTag)) _ -> raiseTypeError p @@ -33,8 +33,8 @@ instance EvaluateOp OpDefined where return $ mkUndef ty $ "Has undefined children:" <+> pretty p evaluateOp (OpDefined (viewConstantFunction -> Just xs)) = return $ ConstantAbstract $ AbsLitSet $ sortNub $ map fst xs ---TODO --- evaluateOp (OpDefined (viewConstantPermutation -> + evaluateOp (OpDefined (viewConstantPermutation -> Just xss)) = + return $ ConstantAbstract $ AbsLitSet $ join xss evaluateOp op = na $ "evaluateOp{OpDefined}:" <++> pretty (show op) instance SimplifyOp OpDefined x where diff --git a/src/Conjure/Representations/Function/Function1DPartial.hs b/src/Conjure/Representations/Function/Function1DPartial.hs index 1ff5d90a8a..de617db906 100644 --- a/src/Conjure/Representations/Function/Function1DPartial.hs +++ b/src/Conjure/Representations/Function/Function1DPartial.hs @@ -160,8 +160,12 @@ function1DPartial = Representation chck downD structuralCons downC up valsOut ) ] - downC _ = na "{downC} Function1DPartial" - + downC (name, domain, constant) = na $ vcat [ "{downC} Function1DPartial" + , "name:" <+> pretty name + , "domain:" <+> pretty domain + , "constant:" <+> pretty constant + ] + up :: TypeOf_Up m up ctxt (name, domain@(DomainFunction Function_1DPartial (FunctionAttr _ PartialityAttr_Partial _) diff --git a/src/Conjure/Rules/Horizontal/Permutation.hs b/src/Conjure/Rules/Horizontal/Permutation.hs index ea259a1a29..a45a8c09ef 100644 --- a/src/Conjure/Rules/Horizontal/Permutation.hs +++ b/src/Conjure/Rules/Horizontal/Permutation.hs @@ -225,6 +225,10 @@ rule_Compose_Image = "permutation-compose-image" `namedRule` theRule where else na "rule_Compose_Image" theRule _ = na "rule_Compose_Image" + +-- This isn't great but handles the literal case rule_Compose_Image fails on +-- TODO would be nice to be able to compose permutations without having to +-- introduce auxiliary variables - this is a slow way to go rule_Compose :: Rule rule_Compose = "permutation-compose" `namedRule` theRule where theRule [essence| compose(&g,&h) |] = do @@ -239,16 +243,15 @@ rule_Compose = "permutation-compose" `namedRule` theRule where , do (lPat, l) <- quantifiedVar - (rPat, r) <- quantifiedVar (pName, p) <- auxiliaryVar return $ WithLocals [essence| &p |] ( AuxiliaryVars - [ Declaration (FindOrGiven LocalFind pName du) + [ reTag AnyTag (Declaration (FindOrGiven LocalFind pName du)) , SuchThat ---TODO this rule is not correct as it is not restrictive enough ---rewrite with defined to constrain size of found permutation - [ [essence| and([image(&p,&l[1]) = image(&g, image(&h,&l[1])) | &lPat <- &g]) /\ and([image(&p,&r[1]) = image(&g, image(&h,&r[1])) | &rPat <- &h]) + [ [essence| + forAll &lPat in (defined(&g) union defined(&h)) . + image(&p,&l) = image(&g,image(&h,&l)) |] ] ] diff --git a/src/Conjure/Rules/Vertical/Permutation.hs b/src/Conjure/Rules/Vertical/Permutation.hs index 3578cac23f..f2d85f0f49 100644 --- a/src/Conjure/Rules/Vertical/Permutation.hs +++ b/src/Conjure/Rules/Vertical/Permutation.hs @@ -17,11 +17,24 @@ rule_Cardinality = "permutation-cardinality" `namedRule` theRule where ( "Vertical rule for permutation cardinality, AsFunction representation." , do (iPat, i) <- quantifiedVarOverDomain (forgetRepr innerDom) - return [essence| - sum([ toInt(&i != image(&fun, &i)) | &iPat : &innerDom ]) - |] + return $ reTag AnyTag $ [essence| |&fun| |] ) +rule_Defined :: Rule +rule_Defined = "permutation-defined" `namedRule` theRule where + theRule p = do + p <- match opDefined p + TypePermutation{} <- typeOf p + Permutation_AsFunction <- representationOf p + DomainPermutation _ _ innerDom <- domainOf p + [fun] <- downX1 p + return + ( "Vertical rule for permutation defined, AsFunction representation." + , do + return [essence| defined(&fun) |] + ) + + rule_Permute_Comprehension_Tuples :: Rule rule_Permute_Comprehension_Tuples = "permutation-comprehension-tuples{AsFunction}" `namedRule` theRule where diff --git a/src/Conjure/UI/Model.hs b/src/Conjure/UI/Model.hs index 90323fdf13..593844c11e 100644 --- a/src/Conjure/UI/Model.hs +++ b/src/Conjure/UI/Model.hs @@ -1090,6 +1090,7 @@ verticalRules = [ Vertical.Permutation.rule_Image -- , Vertical.Permutation.rule_Permute_Comprehension , Vertical.Permutation.rule_Cardinality + , Vertical.Permutation.rule_Defined , Vertical.Permutation.rule_Permute_Comprehension_Tuples -- , Vertical.Permutation.rule_Permutation_Equality -- , Vertical.Permutation.rule_Permutation_Equality_Comprehension From 5d2248b0c5fe20a78648183cb90125e4e7d4dfaf Mon Sep 17 00:00:00 2001 From: Fraser Dunlop Date: Wed, 19 Dec 2018 15:33:54 +0000 Subject: [PATCH 058/229] incomprehendable image + more tests --- src/Conjure/Language/Type.hs | 12 +-- src/Conjure/Rules/Horizontal/Permutation.hs | 91 ++++++------------- src/Conjure/UI/Model.hs | 1 + .../permutation.essence | 10 ++ .../permutation.param | 2 + .../0001_given_permutation_letting_set/run.sh | 3 + .../stdout.expected | 8 ++ .../permutation.essence | 11 +++ .../permutation.param | 1 + .../0002_given_permutation_find_sets/run.sh | 3 + .../stdout.expected | 54 +++++++++++ .../permutation.essence | 11 +++ .../0003_letting_permutation_find_sets/run.sh | 3 + .../stdout.expected | 54 +++++++++++ .../permutation.essence | 11 +++ .../0004_find_permutation_find_sets/run.sh | 3 + .../stdout.expected | 64 +++++++++++++ .../permutation.essence | 11 +++ .../permutation.param | 1 + .../run.sh | 3 + .../stdout.expected | 44 +++++++++ .../permutation.essence | 11 +++ .../0004_find_permutation_find_sets/run.sh | 3 + .../stdout.expected | 64 +++++++++++++ .../permutation.essence | 11 +++ .../permutation.param | 1 + .../run.sh | 3 + .../stdout.expected | 44 +++++++++ .../permutation.essence | 11 +++ .../0004_find_permutation_find_sets/run.sh | 3 + .../stdout.expected | 74 +++++++++++++++ .../permutation.essence | 10 ++ .../permutation.param | 1 + .../enum/0001_letting_permutation/run.sh | 3 + .../0001_letting_permutation/stdout.expected | 8 ++ .../permutation.essence | 10 ++ .../permutation.param | 1 + .../enum/0002_letting_permutation/run.sh | 3 + .../0002_letting_permutation/stdout.expected | 8 ++ .../permutation.essence | 10 ++ .../0003_given_permutation/permutation.param | 2 + .../enum/0003_given_permutation/run.sh | 3 + .../0003_given_permutation/stdout.expected | 8 ++ .../permutation.essence | 7 ++ .../0004_given_permutation/permutation.param | 2 + .../enum/0004_given_permutation/run.sh | 3 + .../0004_given_permutation/stdout.expected | 8 ++ .../0005_find_permutation/permutation.essence | 7 ++ .../enum/0005_find_permutation/run.sh | 3 + .../0005_find_permutation/stdout.expected | 9 ++ .../0005_find_permutation/permutation.essence | 7 ++ .../int/0005_find_permutation/run.sh | 3 + .../int/0005_find_permutation/stdout.expected | 9 ++ .../0005_find_permutation/permutation.essence | 7 ++ .../unnamed/0005_find_permutation/run.sh | 3 + .../0005_find_permutation/stdout.expected | 10 ++ .../permutation.essence | 9 ++ .../permutation.param | 1 + .../run.sh | 3 + .../stdout.expected | 8 ++ .../permutation.essence | 9 ++ .../permutation.param | 1 + .../run.sh | 3 + .../stdout.expected | 8 ++ .../permutation.essence | 10 ++ .../permutation.param | 2 + .../run.sh | 3 + .../stdout.expected | 8 ++ .../permutation.essence | 10 ++ .../permutation.param | 1 + .../run.sh | 3 + .../stdout.expected | 54 +++++++++++ .../permutation.essence | 9 ++ .../run.sh | 3 + .../stdout.expected | 64 +++++++++++++ .../permutation.essence | 8 ++ .../permutation.param | 1 + .../run.sh | 3 + .../stdout.expected | 8 ++ .../permutation.essence | 8 ++ .../permutation.param | 1 + .../run.sh | 3 + .../stdout.expected | 8 ++ .../permutation.essence | 10 ++ .../permutation.param | 2 + .../run.sh | 3 + .../stdout.expected | 8 ++ .../permutation.essence | 10 ++ .../permutation.param | 1 + .../run.sh | 3 + .../stdout.expected | 54 +++++++++++ .../permutation.essence | 10 ++ .../run.sh | 3 + .../stdout.expected | 64 +++++++++++++ .../permutations/10_image_tuple/runthese.sh | 1 + .../permutation.essence | 9 ++ .../run.sh | 3 + .../stdout.expected | 74 +++++++++++++++ .../permutation.essence | 11 +++ .../permutation.param | 2 + .../0001_given_permutation_letting_set/run.sh | 3 + .../stdout.expected | 12 +++ .../11_image_relation/runthese.sh | 2 + 103 files changed, 1238 insertions(+), 67 deletions(-) create mode 100644 tests/custom/permutations/08_image_set/enum/0001_given_permutation_letting_set/permutation.essence create mode 100644 tests/custom/permutations/08_image_set/enum/0001_given_permutation_letting_set/permutation.param create mode 100755 tests/custom/permutations/08_image_set/enum/0001_given_permutation_letting_set/run.sh create mode 100644 tests/custom/permutations/08_image_set/enum/0001_given_permutation_letting_set/stdout.expected create mode 100644 tests/custom/permutations/08_image_set/enum/0002_given_permutation_find_sets/permutation.essence create mode 100644 tests/custom/permutations/08_image_set/enum/0002_given_permutation_find_sets/permutation.param create mode 100755 tests/custom/permutations/08_image_set/enum/0002_given_permutation_find_sets/run.sh create mode 100644 tests/custom/permutations/08_image_set/enum/0002_given_permutation_find_sets/stdout.expected create mode 100644 tests/custom/permutations/08_image_set/enum/0003_letting_permutation_find_sets/permutation.essence create mode 100755 tests/custom/permutations/08_image_set/enum/0003_letting_permutation_find_sets/run.sh create mode 100644 tests/custom/permutations/08_image_set/enum/0003_letting_permutation_find_sets/stdout.expected create mode 100644 tests/custom/permutations/08_image_set/enum/0004_find_permutation_find_sets/permutation.essence create mode 100755 tests/custom/permutations/08_image_set/enum/0004_find_permutation_find_sets/run.sh create mode 100644 tests/custom/permutations/08_image_set/enum/0004_find_permutation_find_sets/stdout.expected create mode 100644 tests/custom/permutations/08_image_set/enum/0005_find_permutation_given_set_find_set/permutation.essence create mode 100644 tests/custom/permutations/08_image_set/enum/0005_find_permutation_given_set_find_set/permutation.param create mode 100755 tests/custom/permutations/08_image_set/enum/0005_find_permutation_given_set_find_set/run.sh create mode 100644 tests/custom/permutations/08_image_set/enum/0005_find_permutation_given_set_find_set/stdout.expected create mode 100644 tests/custom/permutations/08_image_set/int/0004_find_permutation_find_sets/permutation.essence create mode 100755 tests/custom/permutations/08_image_set/int/0004_find_permutation_find_sets/run.sh create mode 100644 tests/custom/permutations/08_image_set/int/0004_find_permutation_find_sets/stdout.expected create mode 100644 tests/custom/permutations/08_image_set/int/0005_find_permutation_given_set_find_set/permutation.essence create mode 100644 tests/custom/permutations/08_image_set/int/0005_find_permutation_given_set_find_set/permutation.param create mode 100755 tests/custom/permutations/08_image_set/int/0005_find_permutation_given_set_find_set/run.sh create mode 100644 tests/custom/permutations/08_image_set/int/0005_find_permutation_given_set_find_set/stdout.expected create mode 100644 tests/custom/permutations/08_image_set/unnamed/0004_find_permutation_find_sets/permutation.essence create mode 100755 tests/custom/permutations/08_image_set/unnamed/0004_find_permutation_find_sets/run.sh create mode 100644 tests/custom/permutations/08_image_set/unnamed/0004_find_permutation_find_sets/stdout.expected create mode 100644 tests/custom/permutations/09_defined/enum/0001_letting_permutation/permutation.essence create mode 100644 tests/custom/permutations/09_defined/enum/0001_letting_permutation/permutation.param create mode 100755 tests/custom/permutations/09_defined/enum/0001_letting_permutation/run.sh create mode 100644 tests/custom/permutations/09_defined/enum/0001_letting_permutation/stdout.expected create mode 100644 tests/custom/permutations/09_defined/enum/0002_letting_permutation/permutation.essence create mode 100644 tests/custom/permutations/09_defined/enum/0002_letting_permutation/permutation.param create mode 100755 tests/custom/permutations/09_defined/enum/0002_letting_permutation/run.sh create mode 100644 tests/custom/permutations/09_defined/enum/0002_letting_permutation/stdout.expected create mode 100644 tests/custom/permutations/09_defined/enum/0003_given_permutation/permutation.essence create mode 100644 tests/custom/permutations/09_defined/enum/0003_given_permutation/permutation.param create mode 100755 tests/custom/permutations/09_defined/enum/0003_given_permutation/run.sh create mode 100644 tests/custom/permutations/09_defined/enum/0003_given_permutation/stdout.expected create mode 100644 tests/custom/permutations/09_defined/enum/0004_given_permutation/permutation.essence create mode 100644 tests/custom/permutations/09_defined/enum/0004_given_permutation/permutation.param create mode 100755 tests/custom/permutations/09_defined/enum/0004_given_permutation/run.sh create mode 100644 tests/custom/permutations/09_defined/enum/0004_given_permutation/stdout.expected create mode 100644 tests/custom/permutations/09_defined/enum/0005_find_permutation/permutation.essence create mode 100755 tests/custom/permutations/09_defined/enum/0005_find_permutation/run.sh create mode 100644 tests/custom/permutations/09_defined/enum/0005_find_permutation/stdout.expected create mode 100644 tests/custom/permutations/09_defined/int/0005_find_permutation/permutation.essence create mode 100755 tests/custom/permutations/09_defined/int/0005_find_permutation/run.sh create mode 100644 tests/custom/permutations/09_defined/int/0005_find_permutation/stdout.expected create mode 100644 tests/custom/permutations/09_defined/unnamed/0005_find_permutation/permutation.essence create mode 100755 tests/custom/permutations/09_defined/unnamed/0005_find_permutation/run.sh create mode 100644 tests/custom/permutations/09_defined/unnamed/0005_find_permutation/stdout.expected create mode 100644 tests/custom/permutations/10_image_tuple/enum/0001_letting_permutation_given_tuple_find_tuple/permutation.essence create mode 100644 tests/custom/permutations/10_image_tuple/enum/0001_letting_permutation_given_tuple_find_tuple/permutation.param create mode 100755 tests/custom/permutations/10_image_tuple/enum/0001_letting_permutation_given_tuple_find_tuple/run.sh create mode 100644 tests/custom/permutations/10_image_tuple/enum/0001_letting_permutation_given_tuple_find_tuple/stdout.expected create mode 100644 tests/custom/permutations/10_image_tuple/enum/0002_letting_permutation_given_tuple_find_tuple/permutation.essence create mode 100644 tests/custom/permutations/10_image_tuple/enum/0002_letting_permutation_given_tuple_find_tuple/permutation.param create mode 100755 tests/custom/permutations/10_image_tuple/enum/0002_letting_permutation_given_tuple_find_tuple/run.sh create mode 100644 tests/custom/permutations/10_image_tuple/enum/0002_letting_permutation_given_tuple_find_tuple/stdout.expected create mode 100644 tests/custom/permutations/10_image_tuple/enum/0003_given_permutation_given_tuple_find_tuple/permutation.essence create mode 100644 tests/custom/permutations/10_image_tuple/enum/0003_given_permutation_given_tuple_find_tuple/permutation.param create mode 100755 tests/custom/permutations/10_image_tuple/enum/0003_given_permutation_given_tuple_find_tuple/run.sh create mode 100644 tests/custom/permutations/10_image_tuple/enum/0003_given_permutation_given_tuple_find_tuple/stdout.expected create mode 100644 tests/custom/permutations/10_image_tuple/enum/0004_given_permutation_find_tuple_find_tuple/permutation.essence create mode 100644 tests/custom/permutations/10_image_tuple/enum/0004_given_permutation_find_tuple_find_tuple/permutation.param create mode 100755 tests/custom/permutations/10_image_tuple/enum/0004_given_permutation_find_tuple_find_tuple/run.sh create mode 100644 tests/custom/permutations/10_image_tuple/enum/0004_given_permutation_find_tuple_find_tuple/stdout.expected create mode 100644 tests/custom/permutations/10_image_tuple/enum/0005_find_permutation_find_tuple_find_tuple/permutation.essence create mode 100755 tests/custom/permutations/10_image_tuple/enum/0005_find_permutation_find_tuple_find_tuple/run.sh create mode 100644 tests/custom/permutations/10_image_tuple/enum/0005_find_permutation_find_tuple_find_tuple/stdout.expected create mode 100644 tests/custom/permutations/10_image_tuple/int/0001_letting_permutation_given_tuple_find_tuple/permutation.essence create mode 100644 tests/custom/permutations/10_image_tuple/int/0001_letting_permutation_given_tuple_find_tuple/permutation.param create mode 100755 tests/custom/permutations/10_image_tuple/int/0001_letting_permutation_given_tuple_find_tuple/run.sh create mode 100644 tests/custom/permutations/10_image_tuple/int/0001_letting_permutation_given_tuple_find_tuple/stdout.expected create mode 100644 tests/custom/permutations/10_image_tuple/int/0002_letting_permutation_given_tuple_find_tuple/permutation.essence create mode 100644 tests/custom/permutations/10_image_tuple/int/0002_letting_permutation_given_tuple_find_tuple/permutation.param create mode 100755 tests/custom/permutations/10_image_tuple/int/0002_letting_permutation_given_tuple_find_tuple/run.sh create mode 100644 tests/custom/permutations/10_image_tuple/int/0002_letting_permutation_given_tuple_find_tuple/stdout.expected create mode 100644 tests/custom/permutations/10_image_tuple/int/0003_given_permutation_given_tuple_find_tuple/permutation.essence create mode 100644 tests/custom/permutations/10_image_tuple/int/0003_given_permutation_given_tuple_find_tuple/permutation.param create mode 100755 tests/custom/permutations/10_image_tuple/int/0003_given_permutation_given_tuple_find_tuple/run.sh create mode 100644 tests/custom/permutations/10_image_tuple/int/0003_given_permutation_given_tuple_find_tuple/stdout.expected create mode 100644 tests/custom/permutations/10_image_tuple/int/0004_given_permutation_find_tuple_find_tuple/permutation.essence create mode 100644 tests/custom/permutations/10_image_tuple/int/0004_given_permutation_find_tuple_find_tuple/permutation.param create mode 100755 tests/custom/permutations/10_image_tuple/int/0004_given_permutation_find_tuple_find_tuple/run.sh create mode 100644 tests/custom/permutations/10_image_tuple/int/0004_given_permutation_find_tuple_find_tuple/stdout.expected create mode 100644 tests/custom/permutations/10_image_tuple/int/0005_find_permutation_find_tuple_find_tuple/permutation.essence create mode 100755 tests/custom/permutations/10_image_tuple/int/0005_find_permutation_find_tuple_find_tuple/run.sh create mode 100644 tests/custom/permutations/10_image_tuple/int/0005_find_permutation_find_tuple_find_tuple/stdout.expected create mode 100644 tests/custom/permutations/10_image_tuple/runthese.sh create mode 100644 tests/custom/permutations/10_image_tuple/unnamed/0005_find_permutation_find_tuple_find_tuple/permutation.essence create mode 100755 tests/custom/permutations/10_image_tuple/unnamed/0005_find_permutation_find_tuple_find_tuple/run.sh create mode 100644 tests/custom/permutations/10_image_tuple/unnamed/0005_find_permutation_find_tuple_find_tuple/stdout.expected create mode 100644 tests/custom/permutations/11_image_relation/int/0001_given_permutation_letting_set/permutation.essence create mode 100644 tests/custom/permutations/11_image_relation/int/0001_given_permutation_letting_set/permutation.param create mode 100755 tests/custom/permutations/11_image_relation/int/0001_given_permutation_letting_set/run.sh create mode 100644 tests/custom/permutations/11_image_relation/int/0001_given_permutation_letting_set/stdout.expected create mode 100644 tests/custom/permutations/11_image_relation/runthese.sh diff --git a/src/Conjure/Language/Type.hs b/src/Conjure/Language/Type.hs index bba66830cf..5c31be8a18 100644 --- a/src/Conjure/Language/Type.hs +++ b/src/Conjure/Language/Type.hs @@ -240,12 +240,12 @@ containsTypeComprehendable container containee = -- | Types do not unify && type cannot be a generator in a comprehension containsTypeIncomprehendable :: Type -> Type -> Bool -containsTypeIncomprehendable (TypeTuple ts) t = - any id ((\x -> unifiesOrContains x t) <$> ts) -containsTypeIncomprehendable (TypeRecord ts) t = - any id ((\x -> unifiesOrContains (snd x) t) <$> ts) -containsTypeIncomprehendable (TypeVariant ts) t = - any id ((\x -> unifiesOrContains (snd x) t) <$> ts) +containsTypeIncomprehendable ot@(TypeTuple ts) t = + (not $ typesUnify [ot, t]) && (any id ((\x -> unifiesOrContains x t) <$> ts)) +containsTypeIncomprehendable ot@(TypeRecord ts) t = + (not $ typesUnify [ot, t]) && (any id ((\x -> unifiesOrContains (snd x) t) <$> ts)) +containsTypeIncomprehendable ot@(TypeVariant ts) t = + (not $ typesUnify [ot, t]) && (any id ((\x -> unifiesOrContains (snd x) t) <$> ts)) containsTypeIncomprehendable _ _ = False diff --git a/src/Conjure/Rules/Horizontal/Permutation.hs b/src/Conjure/Rules/Horizontal/Permutation.hs index a45a8c09ef..8d56f33b8b 100644 --- a/src/Conjure/Rules/Horizontal/Permutation.hs +++ b/src/Conjure/Rules/Horizontal/Permutation.hs @@ -2,6 +2,7 @@ module Conjure.Rules.Horizontal.Permutation where import Conjure.Rules.Import import Data.Permutation (size, fromCycles, toFunction) +import Conjure.Bug rule_Cardinality_Literal :: Rule @@ -246,7 +247,8 @@ rule_Compose = "permutation-compose" `namedRule` theRule where (pName, p) <- auxiliaryVar return $ WithLocals [essence| &p |] - ( AuxiliaryVars + ( AuxiliaryVars --TODO this reTag seems dangerous + -- does it break image of nested type object? [ reTag AnyTag (Declaration (FindOrGiven LocalFind pName du)) , SuchThat [ [essence| @@ -263,12 +265,13 @@ rule_Compose = "permutation-compose" `namedRule` theRule where rule_Image_Comprehendable :: Rule rule_Image_Comprehendable = "comprehendable-image" `namedRule` theRule where theRule (Comprehension body gensOrConds) = do - (gocBefore, (pat, perm, y), gocAfter) <- matchFirst gensOrConds $ \ goc -> case goc of - Generator (GenInExpr (Single pat) [essence| image(&perm, &y) |]) -> return (pat, perm, y) + (gocBefore, (pat, x), gocAfter) <- matchFirst gensOrConds $ \ goc -> case goc of + Generator (GenInExpr (Single pat) expr) -> return (pat, matchDefs [opToSet, opToMSet] expr) _ -> na "rule_Image_Comprehendable" + (perm, y) <- match opImage x ty <- typeOf y (TypePermutation inn) <- typeOf perm - if (not $ typesUnify [ty, inn]) && (ty `containsTypeComprehendable` inn) + if ty `containsTypeComprehendable` inn then do return ( "Horizontal rule for image of comprehendable under permutation" @@ -285,62 +288,28 @@ rule_Image_Comprehendable = "comprehendable-image" `namedRule` theRule where theRule _ = na "rule_Image_Comprehendable" +rule_Image_Incomprehendable :: Rule +rule_Image_Incomprehendable = "comprehendable-image" `namedRule` theRule where + theRule [essence| image(&p, &i) |] = do + (TypePermutation inn) <- typeOf p + ti <- typeOf i + if ti `containsTypeIncomprehendable` inn + then case ti of + (TypeTuple tint) -> do + let tupleIndexImage indx = let indexexpr = Constant (ConstantInt AnyTag indx) + in [essence| image(&p, &i[&indexexpr]) |] + tupleExpression = AbstractLiteral $ AbsLitTuple + $ (tupleIndexImage <$> [1..(fromIntegral $ length tint)]) + return + ( "Horizontal rule for image of incomprehendable under permutation" + , return tupleExpression + ) + (TypeRecord _) -> + bug "rule_Image_Incomprehendable not implemented for Record" + (TypeVariant _) -> + bug "rule_Image_Incomprehendable not implemented for Variant" + _ -> bug "rule_Image_Incomprehendable this is a bug" + else na "rule_Image_Comprehendable" + theRule _ = na "rule_Image_Comprehendable" --- ---rule_Image_Literal_Comprehension :: Rule ---rule_Image_Literal_Comprehension = "permutation-image-literal-comprehension{AsFunction}" `namedRule` theRule where --- theRule (Comprehension body gensOrConds) = do --- (gocBefore, (pat, p, i), gocAfter) <- matchFirst gensOrConds $ \ goc -> case goc of --- Generator (GenInExpr pat [essence| image(&p, &i) |]) -> return (pat, p, i) --- _ -> na "rule_Comprehension" --- case i of WithLocals{} -> na "bubble-delay" ; _ -> return () --- (TypePermutation inner, elems) <- match permutationLiteral p --- typeI <- typeOf i --- if typeI `containsType` inner --- then do --- if typesUnify [inner, typeI] --- then do --- innerD <- domainOf i --- let prmTup pt = take (length pt) $ zip (cycle pt) (drop 1 $ cycle pt) --- permTups = join $ prmTup <$> elems --- let outLiteral = make matrixLiteral --- (TypeMatrix (TypeInt NoTag) (TypeTuple [inner,inner])) --- (DomainInt NoTag [RangeBounded 1 (fromInt (genericLength permTups))]) --- [ AbstractLiteral (AbsLitTuple [a,b]) --- | (a,b) <- permTups --- ] --- return --- ( "Horizontal rule for permutation literal application to a single value (image), AsFunction representation" --- , do --- (hName, h) <- auxiliaryVar --- (fPat, f) <- quantifiedVar --- (tPat, t) <- quantifiedVar --- (gPat, g) <- quantifiedVar --- (ePat, _) <- quantifiedVar --- return $ WithLocals --- (Comprehension body $ gocBefore --- ++ [Generator (GenInExpr pat --- [essence| &h |])] --- ++ gocAfter) --- (AuxiliaryVars --- [ Declaration (FindOrGiven LocalFind hName innerD) --- , SuchThat --- [ [essence| --- (forAll (&fPat, &tPat) in &outLiteral . &f = &i <-> &h = &t) --- /\ (!(exists (&gPat, &ePat) in &outLiteral . &g = &h) <-> &h = &i) --- |] --- ] --- ] --- ) --- ) --- else na "rule_Image_Literal" --- else return --- ( "Horizontal rule for permutation application to a type the permutation doesn't care about" --- , return --- (Comprehension body $ gocBefore --- ++ [Generator (GenInExpr pat [essence| &i |])] --- ++ gocAfter) --- ) --- theRule _ = na "rule_Image_Literal" --- diff --git a/src/Conjure/UI/Model.hs b/src/Conjure/UI/Model.hs index 593844c11e..92264b3b50 100644 --- a/src/Conjure/UI/Model.hs +++ b/src/Conjure/UI/Model.hs @@ -1221,6 +1221,7 @@ horizontalRules = , Horizontal.Permutation.rule_In , Horizontal.Permutation.rule_Permutation_Inverse , Horizontal.Permutation.rule_Image_Comprehendable + , Horizontal.Permutation.rule_Image_Incomprehendable -- , Horizontal.Permutation.rule_Image_Literal_Comprehension diff --git a/tests/custom/permutations/08_image_set/enum/0001_given_permutation_letting_set/permutation.essence b/tests/custom/permutations/08_image_set/enum/0001_given_permutation_letting_set/permutation.essence new file mode 100644 index 0000000000..16bdf6013e --- /dev/null +++ b/tests/custom/permutations/08_image_set/enum/0001_given_permutation_letting_set/permutation.essence @@ -0,0 +1,10 @@ +letting n be new type enum {E1,E2,E3,E4} + +given p : permutation of n +given s : set of n + +find sn : set of n + + +such that sn = image(p,s) + diff --git a/tests/custom/permutations/08_image_set/enum/0001_given_permutation_letting_set/permutation.param b/tests/custom/permutations/08_image_set/enum/0001_given_permutation_letting_set/permutation.param new file mode 100644 index 0000000000..65d08e8247 --- /dev/null +++ b/tests/custom/permutations/08_image_set/enum/0001_given_permutation_letting_set/permutation.param @@ -0,0 +1,2 @@ +letting p be permutation((E1,E3,E4)) +letting s be {E1,E2} diff --git a/tests/custom/permutations/08_image_set/enum/0001_given_permutation_letting_set/run.sh b/tests/custom/permutations/08_image_set/enum/0001_given_permutation_letting_set/run.sh new file mode 100755 index 0000000000..9dc67e67f5 --- /dev/null +++ b/tests/custom/permutations/08_image_set/enum/0001_given_permutation_letting_set/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence *.param +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/08_image_set/enum/0001_given_permutation_letting_set/stdout.expected b/tests/custom/permutations/08_image_set/enum/0001_given_permutation_letting_set/stdout.expected new file mode 100644 index 0000000000..c19e017a09 --- /dev/null +++ b/tests/custom/permutations/08_image_set/enum/0001_given_permutation_letting_set/stdout.expected @@ -0,0 +1,8 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime permutation.param +Copying solution to: permutation-permutation.solution +language Essence 1.3 + +letting sn be {E2, E3} diff --git a/tests/custom/permutations/08_image_set/enum/0002_given_permutation_find_sets/permutation.essence b/tests/custom/permutations/08_image_set/enum/0002_given_permutation_find_sets/permutation.essence new file mode 100644 index 0000000000..bb435e5de5 --- /dev/null +++ b/tests/custom/permutations/08_image_set/enum/0002_given_permutation_find_sets/permutation.essence @@ -0,0 +1,11 @@ +letting n be new type enum {E1,E2,E3,E4} + +given p : permutation of n + +find s : set of n + +find sn : set of n + + +such that sn = image(p,s) + diff --git a/tests/custom/permutations/08_image_set/enum/0002_given_permutation_find_sets/permutation.param b/tests/custom/permutations/08_image_set/enum/0002_given_permutation_find_sets/permutation.param new file mode 100644 index 0000000000..19349bb872 --- /dev/null +++ b/tests/custom/permutations/08_image_set/enum/0002_given_permutation_find_sets/permutation.param @@ -0,0 +1 @@ +letting p be permutation((E1,E3,E4)) diff --git a/tests/custom/permutations/08_image_set/enum/0002_given_permutation_find_sets/run.sh b/tests/custom/permutations/08_image_set/enum/0002_given_permutation_find_sets/run.sh new file mode 100755 index 0000000000..aab5d44c6e --- /dev/null +++ b/tests/custom/permutations/08_image_set/enum/0002_given_permutation_find_sets/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence *.param --number-of-solutions=10 +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/08_image_set/enum/0002_given_permutation_find_sets/stdout.expected b/tests/custom/permutations/08_image_set/enum/0002_given_permutation_find_sets/stdout.expected new file mode 100644 index 0000000000..f8250f03d3 --- /dev/null +++ b/tests/custom/permutations/08_image_set/enum/0002_given_permutation_find_sets/stdout.expected @@ -0,0 +1,54 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime permutation.param +Copying solution to: permutation-permutation-000001.solution +Copying solution to: permutation-permutation-000002.solution +Copying solution to: permutation-permutation-000003.solution +Copying solution to: permutation-permutation-000004.solution +Copying solution to: permutation-permutation-000005.solution +Copying solution to: permutation-permutation-000006.solution +Copying solution to: permutation-permutation-000007.solution +Copying solution to: permutation-permutation-000008.solution +Copying solution to: permutation-permutation-000009.solution +Copying solution to: permutation-permutation-000010.solution +language Essence 1.3 + +letting s be {} +letting sn be {} +language Essence 1.3 + +letting s be {E4} +letting sn be {E1} +language Essence 1.3 + +letting s be {E3} +letting sn be {E4} +language Essence 1.3 + +letting s be {E3, E4} +letting sn be {E1, E4} +language Essence 1.3 + +letting s be {E2} +letting sn be {E2} +language Essence 1.3 + +letting s be {E2, E4} +letting sn be {E1, E2} +language Essence 1.3 + +letting s be {E2, E3} +letting sn be {E2, E4} +language Essence 1.3 + +letting s be {E2, E3, E4} +letting sn be {E1, E2, E4} +language Essence 1.3 + +letting s be {E1} +letting sn be {E3} +language Essence 1.3 + +letting s be {E1, E4} +letting sn be {E1, E3} diff --git a/tests/custom/permutations/08_image_set/enum/0003_letting_permutation_find_sets/permutation.essence b/tests/custom/permutations/08_image_set/enum/0003_letting_permutation_find_sets/permutation.essence new file mode 100644 index 0000000000..9a3fcb1eff --- /dev/null +++ b/tests/custom/permutations/08_image_set/enum/0003_letting_permutation_find_sets/permutation.essence @@ -0,0 +1,11 @@ +letting n be new type enum {E1,E2,E3,E4} + +letting p be permutation((E1,E3,E4)) + +find s : set of n + +find sn : set of n + + +such that sn = image(p,s) + diff --git a/tests/custom/permutations/08_image_set/enum/0003_letting_permutation_find_sets/run.sh b/tests/custom/permutations/08_image_set/enum/0003_letting_permutation_find_sets/run.sh new file mode 100755 index 0000000000..03373df6cb --- /dev/null +++ b/tests/custom/permutations/08_image_set/enum/0003_letting_permutation_find_sets/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence --number-of-solutions=10 +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/08_image_set/enum/0003_letting_permutation_find_sets/stdout.expected b/tests/custom/permutations/08_image_set/enum/0003_letting_permutation_find_sets/stdout.expected new file mode 100644 index 0000000000..a0ba996c55 --- /dev/null +++ b/tests/custom/permutations/08_image_set/enum/0003_letting_permutation_find_sets/stdout.expected @@ -0,0 +1,54 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Copying solution to: permutation-000001.solution +Copying solution to: permutation-000002.solution +Copying solution to: permutation-000003.solution +Copying solution to: permutation-000004.solution +Copying solution to: permutation-000005.solution +Copying solution to: permutation-000006.solution +Copying solution to: permutation-000007.solution +Copying solution to: permutation-000008.solution +Copying solution to: permutation-000009.solution +Copying solution to: permutation-000010.solution +language Essence 1.3 + +letting s be {} +letting sn be {} +language Essence 1.3 + +letting s be {E4} +letting sn be {E1} +language Essence 1.3 + +letting s be {E3} +letting sn be {E4} +language Essence 1.3 + +letting s be {E3, E4} +letting sn be {E1, E4} +language Essence 1.3 + +letting s be {E2} +letting sn be {E2} +language Essence 1.3 + +letting s be {E2, E4} +letting sn be {E1, E2} +language Essence 1.3 + +letting s be {E2, E3} +letting sn be {E2, E4} +language Essence 1.3 + +letting s be {E2, E3, E4} +letting sn be {E1, E2, E4} +language Essence 1.3 + +letting s be {E1} +letting sn be {E3} +language Essence 1.3 + +letting s be {E1, E4} +letting sn be {E1, E3} diff --git a/tests/custom/permutations/08_image_set/enum/0004_find_permutation_find_sets/permutation.essence b/tests/custom/permutations/08_image_set/enum/0004_find_permutation_find_sets/permutation.essence new file mode 100644 index 0000000000..7f494c25f4 --- /dev/null +++ b/tests/custom/permutations/08_image_set/enum/0004_find_permutation_find_sets/permutation.essence @@ -0,0 +1,11 @@ +letting n be new type enum {E1,E2,E3,E4} + +find p : permutation of n + +find s : set of n + +find sn : set of n + + +such that sn = image(p,s) /\ (3 = sum([ toInt(l != r) | (l, r) <- p])) + diff --git a/tests/custom/permutations/08_image_set/enum/0004_find_permutation_find_sets/run.sh b/tests/custom/permutations/08_image_set/enum/0004_find_permutation_find_sets/run.sh new file mode 100755 index 0000000000..03373df6cb --- /dev/null +++ b/tests/custom/permutations/08_image_set/enum/0004_find_permutation_find_sets/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence --number-of-solutions=10 +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/08_image_set/enum/0004_find_permutation_find_sets/stdout.expected b/tests/custom/permutations/08_image_set/enum/0004_find_permutation_find_sets/stdout.expected new file mode 100644 index 0000000000..e0dee52381 --- /dev/null +++ b/tests/custom/permutations/08_image_set/enum/0004_find_permutation_find_sets/stdout.expected @@ -0,0 +1,64 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Copying solution to: permutation-000001.solution +Copying solution to: permutation-000002.solution +Copying solution to: permutation-000003.solution +Copying solution to: permutation-000004.solution +Copying solution to: permutation-000005.solution +Copying solution to: permutation-000006.solution +Copying solution to: permutation-000007.solution +Copying solution to: permutation-000008.solution +Copying solution to: permutation-000009.solution +Copying solution to: permutation-000010.solution +language Essence 1.3 + +letting p be permutation((E2, E3, E4)) +letting s be {} +letting sn be {} +language Essence 1.3 + +letting p be permutation((E2, E3, E4)) +letting s be {E4} +letting sn be {E2} +language Essence 1.3 + +letting p be permutation((E2, E3, E4)) +letting s be {E3} +letting sn be {E4} +language Essence 1.3 + +letting p be permutation((E2, E3, E4)) +letting s be {E3, E4} +letting sn be {E2, E4} +language Essence 1.3 + +letting p be permutation((E2, E3, E4)) +letting s be {E2} +letting sn be {E3} +language Essence 1.3 + +letting p be permutation((E2, E3, E4)) +letting s be {E2, E4} +letting sn be {E2, E3} +language Essence 1.3 + +letting p be permutation((E2, E3, E4)) +letting s be {E2, E3} +letting sn be {E3, E4} +language Essence 1.3 + +letting p be permutation((E2, E3, E4)) +letting s be {E2, E3, E4} +letting sn be {E2, E3, E4} +language Essence 1.3 + +letting p be permutation((E2, E3, E4)) +letting s be {E1} +letting sn be {E1} +language Essence 1.3 + +letting p be permutation((E2, E3, E4)) +letting s be {E1, E4} +letting sn be {E1, E2} diff --git a/tests/custom/permutations/08_image_set/enum/0005_find_permutation_given_set_find_set/permutation.essence b/tests/custom/permutations/08_image_set/enum/0005_find_permutation_given_set_find_set/permutation.essence new file mode 100644 index 0000000000..1d550e041f --- /dev/null +++ b/tests/custom/permutations/08_image_set/enum/0005_find_permutation_given_set_find_set/permutation.essence @@ -0,0 +1,11 @@ +letting n be new type enum {E1,E2,E3,E4} + +find p : permutation of n + +given s : set of n + +find sn : set of n + + +such that sn = image(p,s) /\ (3 = sum([ toInt(l != r) | (l, r) <- p])) + diff --git a/tests/custom/permutations/08_image_set/enum/0005_find_permutation_given_set_find_set/permutation.param b/tests/custom/permutations/08_image_set/enum/0005_find_permutation_given_set_find_set/permutation.param new file mode 100644 index 0000000000..fa2940160b --- /dev/null +++ b/tests/custom/permutations/08_image_set/enum/0005_find_permutation_given_set_find_set/permutation.param @@ -0,0 +1 @@ +letting s be {E1,E2,E3} diff --git a/tests/custom/permutations/08_image_set/enum/0005_find_permutation_given_set_find_set/run.sh b/tests/custom/permutations/08_image_set/enum/0005_find_permutation_given_set_find_set/run.sh new file mode 100755 index 0000000000..aab5d44c6e --- /dev/null +++ b/tests/custom/permutations/08_image_set/enum/0005_find_permutation_given_set_find_set/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence *.param --number-of-solutions=10 +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/08_image_set/enum/0005_find_permutation_given_set_find_set/stdout.expected b/tests/custom/permutations/08_image_set/enum/0005_find_permutation_given_set_find_set/stdout.expected new file mode 100644 index 0000000000..dcbaec3952 --- /dev/null +++ b/tests/custom/permutations/08_image_set/enum/0005_find_permutation_given_set_find_set/stdout.expected @@ -0,0 +1,44 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime permutation.param +Copying solution to: permutation-permutation-000001.solution +Copying solution to: permutation-permutation-000002.solution +Copying solution to: permutation-permutation-000003.solution +Copying solution to: permutation-permutation-000004.solution +Copying solution to: permutation-permutation-000005.solution +Copying solution to: permutation-permutation-000006.solution +Copying solution to: permutation-permutation-000007.solution +Copying solution to: permutation-permutation-000008.solution +language Essence 1.3 + +letting p be permutation((E2, E3, E4)) +letting sn be {E1, E3, E4} +language Essence 1.3 + +letting p be permutation((E2, E4, E3)) +letting sn be {E1, E2, E4} +language Essence 1.3 + +letting p be permutation((E1, E2, E3)) +letting sn be {E1, E2, E3} +language Essence 1.3 + +letting p be permutation((E1, E2, E4)) +letting sn be {E2, E3, E4} +language Essence 1.3 + +letting p be permutation((E1, E3, E2)) +letting sn be {E1, E2, E3} +language Essence 1.3 + +letting p be permutation((E1, E3, E4)) +letting sn be {E2, E3, E4} +language Essence 1.3 + +letting p be permutation((E1, E4, E2)) +letting sn be {E1, E3, E4} +language Essence 1.3 + +letting p be permutation((E1, E4, E3)) +letting sn be {E1, E2, E4} diff --git a/tests/custom/permutations/08_image_set/int/0004_find_permutation_find_sets/permutation.essence b/tests/custom/permutations/08_image_set/int/0004_find_permutation_find_sets/permutation.essence new file mode 100644 index 0000000000..c281ffe0c7 --- /dev/null +++ b/tests/custom/permutations/08_image_set/int/0004_find_permutation_find_sets/permutation.essence @@ -0,0 +1,11 @@ +letting n be 4 + +find p : permutation of int(1..4) + +find s : set of int(1..n) + +find sn : set of int(1..n) + + +such that sn = image(p,s) /\ (3 = sum([ toInt(l != r) | (l, r) <- p])) + diff --git a/tests/custom/permutations/08_image_set/int/0004_find_permutation_find_sets/run.sh b/tests/custom/permutations/08_image_set/int/0004_find_permutation_find_sets/run.sh new file mode 100755 index 0000000000..03373df6cb --- /dev/null +++ b/tests/custom/permutations/08_image_set/int/0004_find_permutation_find_sets/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence --number-of-solutions=10 +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/08_image_set/int/0004_find_permutation_find_sets/stdout.expected b/tests/custom/permutations/08_image_set/int/0004_find_permutation_find_sets/stdout.expected new file mode 100644 index 0000000000..42291b8573 --- /dev/null +++ b/tests/custom/permutations/08_image_set/int/0004_find_permutation_find_sets/stdout.expected @@ -0,0 +1,64 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Copying solution to: permutation-000001.solution +Copying solution to: permutation-000002.solution +Copying solution to: permutation-000003.solution +Copying solution to: permutation-000004.solution +Copying solution to: permutation-000005.solution +Copying solution to: permutation-000006.solution +Copying solution to: permutation-000007.solution +Copying solution to: permutation-000008.solution +Copying solution to: permutation-000009.solution +Copying solution to: permutation-000010.solution +language Essence 1.3 + +letting p be permutation((2, 3, 4)) +letting s be {} +letting sn be {} +language Essence 1.3 + +letting p be permutation((2, 3, 4)) +letting s be {4} +letting sn be {2} +language Essence 1.3 + +letting p be permutation((2, 3, 4)) +letting s be {3} +letting sn be {4} +language Essence 1.3 + +letting p be permutation((2, 3, 4)) +letting s be {3, 4} +letting sn be {2, 4} +language Essence 1.3 + +letting p be permutation((2, 3, 4)) +letting s be {2} +letting sn be {3} +language Essence 1.3 + +letting p be permutation((2, 3, 4)) +letting s be {2, 4} +letting sn be {2, 3} +language Essence 1.3 + +letting p be permutation((2, 3, 4)) +letting s be {2, 3} +letting sn be {3, 4} +language Essence 1.3 + +letting p be permutation((2, 3, 4)) +letting s be {2, 3, 4} +letting sn be {2, 3, 4} +language Essence 1.3 + +letting p be permutation((2, 3, 4)) +letting s be {1} +letting sn be {1} +language Essence 1.3 + +letting p be permutation((2, 3, 4)) +letting s be {1, 4} +letting sn be {1, 2} diff --git a/tests/custom/permutations/08_image_set/int/0005_find_permutation_given_set_find_set/permutation.essence b/tests/custom/permutations/08_image_set/int/0005_find_permutation_given_set_find_set/permutation.essence new file mode 100644 index 0000000000..bc2e8b55e4 --- /dev/null +++ b/tests/custom/permutations/08_image_set/int/0005_find_permutation_given_set_find_set/permutation.essence @@ -0,0 +1,11 @@ +letting n be 4 + +find p : permutation of int(1..4) + +given s : set of int(1..n) + +find sn : set of int(1..n) + + +such that sn = image(p,s) /\ (3 = sum([ toInt(l != r) | (l, r) <- p])) + diff --git a/tests/custom/permutations/08_image_set/int/0005_find_permutation_given_set_find_set/permutation.param b/tests/custom/permutations/08_image_set/int/0005_find_permutation_given_set_find_set/permutation.param new file mode 100644 index 0000000000..1aa7e6126c --- /dev/null +++ b/tests/custom/permutations/08_image_set/int/0005_find_permutation_given_set_find_set/permutation.param @@ -0,0 +1 @@ +letting s be {1,2,3} diff --git a/tests/custom/permutations/08_image_set/int/0005_find_permutation_given_set_find_set/run.sh b/tests/custom/permutations/08_image_set/int/0005_find_permutation_given_set_find_set/run.sh new file mode 100755 index 0000000000..aab5d44c6e --- /dev/null +++ b/tests/custom/permutations/08_image_set/int/0005_find_permutation_given_set_find_set/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence *.param --number-of-solutions=10 +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/08_image_set/int/0005_find_permutation_given_set_find_set/stdout.expected b/tests/custom/permutations/08_image_set/int/0005_find_permutation_given_set_find_set/stdout.expected new file mode 100644 index 0000000000..a76cb5cf7f --- /dev/null +++ b/tests/custom/permutations/08_image_set/int/0005_find_permutation_given_set_find_set/stdout.expected @@ -0,0 +1,44 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime permutation.param +Copying solution to: permutation-permutation-000001.solution +Copying solution to: permutation-permutation-000002.solution +Copying solution to: permutation-permutation-000003.solution +Copying solution to: permutation-permutation-000004.solution +Copying solution to: permutation-permutation-000005.solution +Copying solution to: permutation-permutation-000006.solution +Copying solution to: permutation-permutation-000007.solution +Copying solution to: permutation-permutation-000008.solution +language Essence 1.3 + +letting p be permutation((2, 3, 4)) +letting sn be {1, 3, 4} +language Essence 1.3 + +letting p be permutation((2, 4, 3)) +letting sn be {1, 2, 4} +language Essence 1.3 + +letting p be permutation((1, 2, 3)) +letting sn be {1, 2, 3} +language Essence 1.3 + +letting p be permutation((1, 2, 4)) +letting sn be {2, 3, 4} +language Essence 1.3 + +letting p be permutation((1, 3, 2)) +letting sn be {1, 2, 3} +language Essence 1.3 + +letting p be permutation((1, 3, 4)) +letting sn be {2, 3, 4} +language Essence 1.3 + +letting p be permutation((1, 4, 2)) +letting sn be {1, 3, 4} +language Essence 1.3 + +letting p be permutation((1, 4, 3)) +letting sn be {1, 2, 4} diff --git a/tests/custom/permutations/08_image_set/unnamed/0004_find_permutation_find_sets/permutation.essence b/tests/custom/permutations/08_image_set/unnamed/0004_find_permutation_find_sets/permutation.essence new file mode 100644 index 0000000000..4405140cad --- /dev/null +++ b/tests/custom/permutations/08_image_set/unnamed/0004_find_permutation_find_sets/permutation.essence @@ -0,0 +1,11 @@ +letting n be new type of size 4 + +find p : permutation of n + +find s : set of n + +find sn : set of n + + +such that sn = image(p,s) /\ (3 = sum([ toInt(l != r) | (l, r) <- p])) + diff --git a/tests/custom/permutations/08_image_set/unnamed/0004_find_permutation_find_sets/run.sh b/tests/custom/permutations/08_image_set/unnamed/0004_find_permutation_find_sets/run.sh new file mode 100755 index 0000000000..03373df6cb --- /dev/null +++ b/tests/custom/permutations/08_image_set/unnamed/0004_find_permutation_find_sets/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence --number-of-solutions=10 +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/08_image_set/unnamed/0004_find_permutation_find_sets/stdout.expected b/tests/custom/permutations/08_image_set/unnamed/0004_find_permutation_find_sets/stdout.expected new file mode 100644 index 0000000000..412c71035c --- /dev/null +++ b/tests/custom/permutations/08_image_set/unnamed/0004_find_permutation_find_sets/stdout.expected @@ -0,0 +1,74 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Copying solution to: permutation-000001.solution +Copying solution to: permutation-000002.solution +Copying solution to: permutation-000003.solution +Copying solution to: permutation-000004.solution +Copying solution to: permutation-000005.solution +Copying solution to: permutation-000006.solution +Copying solution to: permutation-000007.solution +Copying solution to: permutation-000008.solution +Copying solution to: permutation-000009.solution +Copying solution to: permutation-000010.solution +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_2, n_3, n_4)) +letting s be {} +letting sn be {} +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_2, n_3, n_4)) +letting s be {n_4} +letting sn be {n_2} +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_2, n_3, n_4)) +letting s be {n_3} +letting sn be {n_4} +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_2, n_3, n_4)) +letting s be {n_3, n_4} +letting sn be {n_2, n_4} +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_2, n_3, n_4)) +letting s be {n_2} +letting sn be {n_3} +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_2, n_3, n_4)) +letting s be {n_2, n_4} +letting sn be {n_2, n_3} +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_2, n_3, n_4)) +letting s be {n_2, n_3} +letting sn be {n_3, n_4} +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_2, n_3, n_4)) +letting s be {n_2, n_3, n_4} +letting sn be {n_2, n_3, n_4} +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_2, n_3, n_4)) +letting s be {n_1} +letting sn be {n_1} +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_2, n_3, n_4)) +letting s be {n_1, n_4} +letting sn be {n_1, n_2} diff --git a/tests/custom/permutations/09_defined/enum/0001_letting_permutation/permutation.essence b/tests/custom/permutations/09_defined/enum/0001_letting_permutation/permutation.essence new file mode 100644 index 0000000000..827feeaeb2 --- /dev/null +++ b/tests/custom/permutations/09_defined/enum/0001_letting_permutation/permutation.essence @@ -0,0 +1,10 @@ +letting n be new type enum {E1,E2,E3,E4} + +letting p be permutation((E1,E3,E4)) +given s : set of n + +find b : bool + + +such that b = (s = defined(p)) + diff --git a/tests/custom/permutations/09_defined/enum/0001_letting_permutation/permutation.param b/tests/custom/permutations/09_defined/enum/0001_letting_permutation/permutation.param new file mode 100644 index 0000000000..081a6f056f --- /dev/null +++ b/tests/custom/permutations/09_defined/enum/0001_letting_permutation/permutation.param @@ -0,0 +1 @@ +letting s be {E1,E3,E4} diff --git a/tests/custom/permutations/09_defined/enum/0001_letting_permutation/run.sh b/tests/custom/permutations/09_defined/enum/0001_letting_permutation/run.sh new file mode 100755 index 0000000000..9dc67e67f5 --- /dev/null +++ b/tests/custom/permutations/09_defined/enum/0001_letting_permutation/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence *.param +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/09_defined/enum/0001_letting_permutation/stdout.expected b/tests/custom/permutations/09_defined/enum/0001_letting_permutation/stdout.expected new file mode 100644 index 0000000000..901f2ae574 --- /dev/null +++ b/tests/custom/permutations/09_defined/enum/0001_letting_permutation/stdout.expected @@ -0,0 +1,8 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime permutation.param +Copying solution to: permutation-permutation.solution +language Essence 1.3 + +letting b be true diff --git a/tests/custom/permutations/09_defined/enum/0002_letting_permutation/permutation.essence b/tests/custom/permutations/09_defined/enum/0002_letting_permutation/permutation.essence new file mode 100644 index 0000000000..6578fe1715 --- /dev/null +++ b/tests/custom/permutations/09_defined/enum/0002_letting_permutation/permutation.essence @@ -0,0 +1,10 @@ +letting n be new type enum {E1,E2,E3,E4} + +letting p be permutation((E1,E2,E4)) +given s : set of n + +find b : bool + + +such that b = (s = defined(p)) + diff --git a/tests/custom/permutations/09_defined/enum/0002_letting_permutation/permutation.param b/tests/custom/permutations/09_defined/enum/0002_letting_permutation/permutation.param new file mode 100644 index 0000000000..081a6f056f --- /dev/null +++ b/tests/custom/permutations/09_defined/enum/0002_letting_permutation/permutation.param @@ -0,0 +1 @@ +letting s be {E1,E3,E4} diff --git a/tests/custom/permutations/09_defined/enum/0002_letting_permutation/run.sh b/tests/custom/permutations/09_defined/enum/0002_letting_permutation/run.sh new file mode 100755 index 0000000000..9dc67e67f5 --- /dev/null +++ b/tests/custom/permutations/09_defined/enum/0002_letting_permutation/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence *.param +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/09_defined/enum/0002_letting_permutation/stdout.expected b/tests/custom/permutations/09_defined/enum/0002_letting_permutation/stdout.expected new file mode 100644 index 0000000000..1cc90d46bc --- /dev/null +++ b/tests/custom/permutations/09_defined/enum/0002_letting_permutation/stdout.expected @@ -0,0 +1,8 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime permutation.param +Copying solution to: permutation-permutation.solution +language Essence 1.3 + +letting b be false diff --git a/tests/custom/permutations/09_defined/enum/0003_given_permutation/permutation.essence b/tests/custom/permutations/09_defined/enum/0003_given_permutation/permutation.essence new file mode 100644 index 0000000000..97d3678969 --- /dev/null +++ b/tests/custom/permutations/09_defined/enum/0003_given_permutation/permutation.essence @@ -0,0 +1,10 @@ +letting n be new type enum {E1,E2,E3,E4} + +given p : permutation of n +given s : set of n + +find b : bool + + +such that b = (s = defined(p)) + diff --git a/tests/custom/permutations/09_defined/enum/0003_given_permutation/permutation.param b/tests/custom/permutations/09_defined/enum/0003_given_permutation/permutation.param new file mode 100644 index 0000000000..157810fb04 --- /dev/null +++ b/tests/custom/permutations/09_defined/enum/0003_given_permutation/permutation.param @@ -0,0 +1,2 @@ +letting p be permutation((E1,E3,E4)) +letting s be {E1,E2,E3,E4} diff --git a/tests/custom/permutations/09_defined/enum/0003_given_permutation/run.sh b/tests/custom/permutations/09_defined/enum/0003_given_permutation/run.sh new file mode 100755 index 0000000000..9dc67e67f5 --- /dev/null +++ b/tests/custom/permutations/09_defined/enum/0003_given_permutation/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence *.param +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/09_defined/enum/0003_given_permutation/stdout.expected b/tests/custom/permutations/09_defined/enum/0003_given_permutation/stdout.expected new file mode 100644 index 0000000000..901f2ae574 --- /dev/null +++ b/tests/custom/permutations/09_defined/enum/0003_given_permutation/stdout.expected @@ -0,0 +1,8 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime permutation.param +Copying solution to: permutation-permutation.solution +language Essence 1.3 + +letting b be true diff --git a/tests/custom/permutations/09_defined/enum/0004_given_permutation/permutation.essence b/tests/custom/permutations/09_defined/enum/0004_given_permutation/permutation.essence new file mode 100644 index 0000000000..bb2ac5fd1b --- /dev/null +++ b/tests/custom/permutations/09_defined/enum/0004_given_permutation/permutation.essence @@ -0,0 +1,7 @@ +letting n be new type enum {E1,E2,E3,E4} + +given p : permutation of n +find s : set of n + +such that s = defined(p) + diff --git a/tests/custom/permutations/09_defined/enum/0004_given_permutation/permutation.param b/tests/custom/permutations/09_defined/enum/0004_given_permutation/permutation.param new file mode 100644 index 0000000000..595ea14168 --- /dev/null +++ b/tests/custom/permutations/09_defined/enum/0004_given_permutation/permutation.param @@ -0,0 +1,2 @@ +letting p be permutation((E1,E3,E4)) + diff --git a/tests/custom/permutations/09_defined/enum/0004_given_permutation/run.sh b/tests/custom/permutations/09_defined/enum/0004_given_permutation/run.sh new file mode 100755 index 0000000000..9dc67e67f5 --- /dev/null +++ b/tests/custom/permutations/09_defined/enum/0004_given_permutation/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence *.param +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/09_defined/enum/0004_given_permutation/stdout.expected b/tests/custom/permutations/09_defined/enum/0004_given_permutation/stdout.expected new file mode 100644 index 0000000000..64aacd0ddd --- /dev/null +++ b/tests/custom/permutations/09_defined/enum/0004_given_permutation/stdout.expected @@ -0,0 +1,8 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime permutation.param +Copying solution to: permutation-permutation.solution +language Essence 1.3 + +letting s be {E1, E2, E3, E4} diff --git a/tests/custom/permutations/09_defined/enum/0005_find_permutation/permutation.essence b/tests/custom/permutations/09_defined/enum/0005_find_permutation/permutation.essence new file mode 100644 index 0000000000..854ec685da --- /dev/null +++ b/tests/custom/permutations/09_defined/enum/0005_find_permutation/permutation.essence @@ -0,0 +1,7 @@ +letting n be new type enum {E1,E2,E3,E4} + +find p : permutation of n +find s : set of n + +such that s = defined(p) + diff --git a/tests/custom/permutations/09_defined/enum/0005_find_permutation/run.sh b/tests/custom/permutations/09_defined/enum/0005_find_permutation/run.sh new file mode 100755 index 0000000000..b4899d6266 --- /dev/null +++ b/tests/custom/permutations/09_defined/enum/0005_find_permutation/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/09_defined/enum/0005_find_permutation/stdout.expected b/tests/custom/permutations/09_defined/enum/0005_find_permutation/stdout.expected new file mode 100644 index 0000000000..7f88621554 --- /dev/null +++ b/tests/custom/permutations/09_defined/enum/0005_find_permutation/stdout.expected @@ -0,0 +1,9 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Copying solution to: permutation.solution +language Essence 1.3 + +letting p be permutation() +letting s be {E1, E2, E3, E4} diff --git a/tests/custom/permutations/09_defined/int/0005_find_permutation/permutation.essence b/tests/custom/permutations/09_defined/int/0005_find_permutation/permutation.essence new file mode 100644 index 0000000000..bfbc47112b --- /dev/null +++ b/tests/custom/permutations/09_defined/int/0005_find_permutation/permutation.essence @@ -0,0 +1,7 @@ +letting n be 4 + +find p : permutation of int(1..n) +find s : set of int(1..n) + +such that s = defined(p) + diff --git a/tests/custom/permutations/09_defined/int/0005_find_permutation/run.sh b/tests/custom/permutations/09_defined/int/0005_find_permutation/run.sh new file mode 100755 index 0000000000..b4899d6266 --- /dev/null +++ b/tests/custom/permutations/09_defined/int/0005_find_permutation/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/09_defined/int/0005_find_permutation/stdout.expected b/tests/custom/permutations/09_defined/int/0005_find_permutation/stdout.expected new file mode 100644 index 0000000000..ddece56758 --- /dev/null +++ b/tests/custom/permutations/09_defined/int/0005_find_permutation/stdout.expected @@ -0,0 +1,9 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Copying solution to: permutation.solution +language Essence 1.3 + +letting p be permutation() +letting s be {1, 2, 3, 4} diff --git a/tests/custom/permutations/09_defined/unnamed/0005_find_permutation/permutation.essence b/tests/custom/permutations/09_defined/unnamed/0005_find_permutation/permutation.essence new file mode 100644 index 0000000000..a9249cccef --- /dev/null +++ b/tests/custom/permutations/09_defined/unnamed/0005_find_permutation/permutation.essence @@ -0,0 +1,7 @@ +letting n be new type of size 4 + +find p : permutation of n +find s : set of n + +such that s = defined(p) + diff --git a/tests/custom/permutations/09_defined/unnamed/0005_find_permutation/run.sh b/tests/custom/permutations/09_defined/unnamed/0005_find_permutation/run.sh new file mode 100755 index 0000000000..b4899d6266 --- /dev/null +++ b/tests/custom/permutations/09_defined/unnamed/0005_find_permutation/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/09_defined/unnamed/0005_find_permutation/stdout.expected b/tests/custom/permutations/09_defined/unnamed/0005_find_permutation/stdout.expected new file mode 100644 index 0000000000..ab113b5a06 --- /dev/null +++ b/tests/custom/permutations/09_defined/unnamed/0005_find_permutation/stdout.expected @@ -0,0 +1,10 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Copying solution to: permutation.solution +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation() +letting s be {n_1, n_2, n_3, n_4} diff --git a/tests/custom/permutations/10_image_tuple/enum/0001_letting_permutation_given_tuple_find_tuple/permutation.essence b/tests/custom/permutations/10_image_tuple/enum/0001_letting_permutation_given_tuple_find_tuple/permutation.essence new file mode 100644 index 0000000000..f64f66cc18 --- /dev/null +++ b/tests/custom/permutations/10_image_tuple/enum/0001_letting_permutation_given_tuple_find_tuple/permutation.essence @@ -0,0 +1,9 @@ +letting n be new type enum {E1,E2,E3,E4,E5} + +letting p be permutation((E1,E3,E4)) +given t : (n,n,n) +find q : (n,n,n) + + +such that q = image(p,t) + diff --git a/tests/custom/permutations/10_image_tuple/enum/0001_letting_permutation_given_tuple_find_tuple/permutation.param b/tests/custom/permutations/10_image_tuple/enum/0001_letting_permutation_given_tuple_find_tuple/permutation.param new file mode 100644 index 0000000000..14bc67fb9c --- /dev/null +++ b/tests/custom/permutations/10_image_tuple/enum/0001_letting_permutation_given_tuple_find_tuple/permutation.param @@ -0,0 +1 @@ +letting t be (E1,E4,E5) diff --git a/tests/custom/permutations/10_image_tuple/enum/0001_letting_permutation_given_tuple_find_tuple/run.sh b/tests/custom/permutations/10_image_tuple/enum/0001_letting_permutation_given_tuple_find_tuple/run.sh new file mode 100755 index 0000000000..9dc67e67f5 --- /dev/null +++ b/tests/custom/permutations/10_image_tuple/enum/0001_letting_permutation_given_tuple_find_tuple/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence *.param +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/10_image_tuple/enum/0001_letting_permutation_given_tuple_find_tuple/stdout.expected b/tests/custom/permutations/10_image_tuple/enum/0001_letting_permutation_given_tuple_find_tuple/stdout.expected new file mode 100644 index 0000000000..d069522cd4 --- /dev/null +++ b/tests/custom/permutations/10_image_tuple/enum/0001_letting_permutation_given_tuple_find_tuple/stdout.expected @@ -0,0 +1,8 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime permutation.param +Copying solution to: permutation-permutation.solution +language Essence 1.3 + +letting q be (E3, E1, E5) diff --git a/tests/custom/permutations/10_image_tuple/enum/0002_letting_permutation_given_tuple_find_tuple/permutation.essence b/tests/custom/permutations/10_image_tuple/enum/0002_letting_permutation_given_tuple_find_tuple/permutation.essence new file mode 100644 index 0000000000..cd8ec560a8 --- /dev/null +++ b/tests/custom/permutations/10_image_tuple/enum/0002_letting_permutation_given_tuple_find_tuple/permutation.essence @@ -0,0 +1,9 @@ +letting n be new type enum {E1,E2,E3,E4,E5} + +letting p be permutation((E1,E3,E4)) +given t : (n,n,n,n) +find q : (n,n,n,n) + + +such that q = image(p,t) + diff --git a/tests/custom/permutations/10_image_tuple/enum/0002_letting_permutation_given_tuple_find_tuple/permutation.param b/tests/custom/permutations/10_image_tuple/enum/0002_letting_permutation_given_tuple_find_tuple/permutation.param new file mode 100644 index 0000000000..0a001f546c --- /dev/null +++ b/tests/custom/permutations/10_image_tuple/enum/0002_letting_permutation_given_tuple_find_tuple/permutation.param @@ -0,0 +1 @@ +letting t be (E1,E4,E5,E2) diff --git a/tests/custom/permutations/10_image_tuple/enum/0002_letting_permutation_given_tuple_find_tuple/run.sh b/tests/custom/permutations/10_image_tuple/enum/0002_letting_permutation_given_tuple_find_tuple/run.sh new file mode 100755 index 0000000000..9dc67e67f5 --- /dev/null +++ b/tests/custom/permutations/10_image_tuple/enum/0002_letting_permutation_given_tuple_find_tuple/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence *.param +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/10_image_tuple/enum/0002_letting_permutation_given_tuple_find_tuple/stdout.expected b/tests/custom/permutations/10_image_tuple/enum/0002_letting_permutation_given_tuple_find_tuple/stdout.expected new file mode 100644 index 0000000000..087a53e1a2 --- /dev/null +++ b/tests/custom/permutations/10_image_tuple/enum/0002_letting_permutation_given_tuple_find_tuple/stdout.expected @@ -0,0 +1,8 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime permutation.param +Copying solution to: permutation-permutation.solution +language Essence 1.3 + +letting q be (E3, E1, E5, E2) diff --git a/tests/custom/permutations/10_image_tuple/enum/0003_given_permutation_given_tuple_find_tuple/permutation.essence b/tests/custom/permutations/10_image_tuple/enum/0003_given_permutation_given_tuple_find_tuple/permutation.essence new file mode 100644 index 0000000000..5877cf2311 --- /dev/null +++ b/tests/custom/permutations/10_image_tuple/enum/0003_given_permutation_given_tuple_find_tuple/permutation.essence @@ -0,0 +1,10 @@ +letting n be new type enum {E1,E2,E3,E4,E5} + +given p : permutation of n +given t : (n,n,n) +find q : (n,n,n) + + + +such that q = image(p, t) + diff --git a/tests/custom/permutations/10_image_tuple/enum/0003_given_permutation_given_tuple_find_tuple/permutation.param b/tests/custom/permutations/10_image_tuple/enum/0003_given_permutation_given_tuple_find_tuple/permutation.param new file mode 100644 index 0000000000..dcc5370ef5 --- /dev/null +++ b/tests/custom/permutations/10_image_tuple/enum/0003_given_permutation_given_tuple_find_tuple/permutation.param @@ -0,0 +1,2 @@ +letting p be permutation((E1,E3,E4)) +letting t be (E1,E4,E5) diff --git a/tests/custom/permutations/10_image_tuple/enum/0003_given_permutation_given_tuple_find_tuple/run.sh b/tests/custom/permutations/10_image_tuple/enum/0003_given_permutation_given_tuple_find_tuple/run.sh new file mode 100755 index 0000000000..9dc67e67f5 --- /dev/null +++ b/tests/custom/permutations/10_image_tuple/enum/0003_given_permutation_given_tuple_find_tuple/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence *.param +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/10_image_tuple/enum/0003_given_permutation_given_tuple_find_tuple/stdout.expected b/tests/custom/permutations/10_image_tuple/enum/0003_given_permutation_given_tuple_find_tuple/stdout.expected new file mode 100644 index 0000000000..d069522cd4 --- /dev/null +++ b/tests/custom/permutations/10_image_tuple/enum/0003_given_permutation_given_tuple_find_tuple/stdout.expected @@ -0,0 +1,8 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime permutation.param +Copying solution to: permutation-permutation.solution +language Essence 1.3 + +letting q be (E3, E1, E5) diff --git a/tests/custom/permutations/10_image_tuple/enum/0004_given_permutation_find_tuple_find_tuple/permutation.essence b/tests/custom/permutations/10_image_tuple/enum/0004_given_permutation_find_tuple_find_tuple/permutation.essence new file mode 100644 index 0000000000..0b5ba8f9f6 --- /dev/null +++ b/tests/custom/permutations/10_image_tuple/enum/0004_given_permutation_find_tuple_find_tuple/permutation.essence @@ -0,0 +1,10 @@ +letting n be new type enum {E1,E2,E3,E4,E5} + +given p : permutation of n +find t : (n,n,n) +find q : (n,n,n) + + + +such that q = image(p, t) + diff --git a/tests/custom/permutations/10_image_tuple/enum/0004_given_permutation_find_tuple_find_tuple/permutation.param b/tests/custom/permutations/10_image_tuple/enum/0004_given_permutation_find_tuple_find_tuple/permutation.param new file mode 100644 index 0000000000..19349bb872 --- /dev/null +++ b/tests/custom/permutations/10_image_tuple/enum/0004_given_permutation_find_tuple_find_tuple/permutation.param @@ -0,0 +1 @@ +letting p be permutation((E1,E3,E4)) diff --git a/tests/custom/permutations/10_image_tuple/enum/0004_given_permutation_find_tuple_find_tuple/run.sh b/tests/custom/permutations/10_image_tuple/enum/0004_given_permutation_find_tuple_find_tuple/run.sh new file mode 100755 index 0000000000..aab5d44c6e --- /dev/null +++ b/tests/custom/permutations/10_image_tuple/enum/0004_given_permutation_find_tuple_find_tuple/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence *.param --number-of-solutions=10 +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/10_image_tuple/enum/0004_given_permutation_find_tuple_find_tuple/stdout.expected b/tests/custom/permutations/10_image_tuple/enum/0004_given_permutation_find_tuple_find_tuple/stdout.expected new file mode 100644 index 0000000000..e0cbb59c9f --- /dev/null +++ b/tests/custom/permutations/10_image_tuple/enum/0004_given_permutation_find_tuple_find_tuple/stdout.expected @@ -0,0 +1,54 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime permutation.param +Copying solution to: permutation-permutation-000001.solution +Copying solution to: permutation-permutation-000002.solution +Copying solution to: permutation-permutation-000003.solution +Copying solution to: permutation-permutation-000004.solution +Copying solution to: permutation-permutation-000005.solution +Copying solution to: permutation-permutation-000006.solution +Copying solution to: permutation-permutation-000007.solution +Copying solution to: permutation-permutation-000008.solution +Copying solution to: permutation-permutation-000009.solution +Copying solution to: permutation-permutation-000010.solution +language Essence 1.3 + +letting q be (E3, E3, E3) +letting t be (E1, E1, E1) +language Essence 1.3 + +letting q be (E3, E3, E2) +letting t be (E1, E1, E2) +language Essence 1.3 + +letting q be (E3, E3, E4) +letting t be (E1, E1, E3) +language Essence 1.3 + +letting q be (E3, E3, E1) +letting t be (E1, E1, E4) +language Essence 1.3 + +letting q be (E3, E3, E5) +letting t be (E1, E1, E5) +language Essence 1.3 + +letting q be (E3, E2, E3) +letting t be (E1, E2, E1) +language Essence 1.3 + +letting q be (E3, E2, E2) +letting t be (E1, E2, E2) +language Essence 1.3 + +letting q be (E3, E2, E4) +letting t be (E1, E2, E3) +language Essence 1.3 + +letting q be (E3, E2, E1) +letting t be (E1, E2, E4) +language Essence 1.3 + +letting q be (E3, E2, E5) +letting t be (E1, E2, E5) diff --git a/tests/custom/permutations/10_image_tuple/enum/0005_find_permutation_find_tuple_find_tuple/permutation.essence b/tests/custom/permutations/10_image_tuple/enum/0005_find_permutation_find_tuple_find_tuple/permutation.essence new file mode 100644 index 0000000000..29011a21a1 --- /dev/null +++ b/tests/custom/permutations/10_image_tuple/enum/0005_find_permutation_find_tuple_find_tuple/permutation.essence @@ -0,0 +1,9 @@ +letting n be new type enum {E1,E2,E3,E4,E5} + +find p : permutation of n +find t : (n,n,n) +find q : (n,n,n) + + +such that (q = image(p, t)) /\ (4 = sum([toInt(l != r) | (l,r) <- p])) + diff --git a/tests/custom/permutations/10_image_tuple/enum/0005_find_permutation_find_tuple_find_tuple/run.sh b/tests/custom/permutations/10_image_tuple/enum/0005_find_permutation_find_tuple_find_tuple/run.sh new file mode 100755 index 0000000000..03373df6cb --- /dev/null +++ b/tests/custom/permutations/10_image_tuple/enum/0005_find_permutation_find_tuple_find_tuple/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence --number-of-solutions=10 +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/10_image_tuple/enum/0005_find_permutation_find_tuple_find_tuple/stdout.expected b/tests/custom/permutations/10_image_tuple/enum/0005_find_permutation_find_tuple_find_tuple/stdout.expected new file mode 100644 index 0000000000..9540e6c30c --- /dev/null +++ b/tests/custom/permutations/10_image_tuple/enum/0005_find_permutation_find_tuple_find_tuple/stdout.expected @@ -0,0 +1,64 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Copying solution to: permutation-000001.solution +Copying solution to: permutation-000002.solution +Copying solution to: permutation-000003.solution +Copying solution to: permutation-000004.solution +Copying solution to: permutation-000005.solution +Copying solution to: permutation-000006.solution +Copying solution to: permutation-000007.solution +Copying solution to: permutation-000008.solution +Copying solution to: permutation-000009.solution +Copying solution to: permutation-000010.solution +language Essence 1.3 + +letting p be permutation((E2, E3), (E4, E5)) +letting q be (E1, E1, E1) +letting t be (E1, E1, E1) +language Essence 1.3 + +letting p be permutation((E2, E3), (E4, E5)) +letting q be (E1, E1, E3) +letting t be (E1, E1, E2) +language Essence 1.3 + +letting p be permutation((E2, E3), (E4, E5)) +letting q be (E1, E1, E2) +letting t be (E1, E1, E3) +language Essence 1.3 + +letting p be permutation((E2, E3), (E4, E5)) +letting q be (E1, E1, E5) +letting t be (E1, E1, E4) +language Essence 1.3 + +letting p be permutation((E2, E3), (E4, E5)) +letting q be (E1, E1, E4) +letting t be (E1, E1, E5) +language Essence 1.3 + +letting p be permutation((E2, E3), (E4, E5)) +letting q be (E1, E3, E1) +letting t be (E1, E2, E1) +language Essence 1.3 + +letting p be permutation((E2, E3), (E4, E5)) +letting q be (E1, E3, E3) +letting t be (E1, E2, E2) +language Essence 1.3 + +letting p be permutation((E2, E3), (E4, E5)) +letting q be (E1, E3, E2) +letting t be (E1, E2, E3) +language Essence 1.3 + +letting p be permutation((E2, E3), (E4, E5)) +letting q be (E1, E3, E5) +letting t be (E1, E2, E4) +language Essence 1.3 + +letting p be permutation((E2, E3), (E4, E5)) +letting q be (E1, E3, E4) +letting t be (E1, E2, E5) diff --git a/tests/custom/permutations/10_image_tuple/int/0001_letting_permutation_given_tuple_find_tuple/permutation.essence b/tests/custom/permutations/10_image_tuple/int/0001_letting_permutation_given_tuple_find_tuple/permutation.essence new file mode 100644 index 0000000000..8ff47ec02b --- /dev/null +++ b/tests/custom/permutations/10_image_tuple/int/0001_letting_permutation_given_tuple_find_tuple/permutation.essence @@ -0,0 +1,8 @@ +letting n be 5 + +letting p be permutation((1,3,4)) +given t : (int(1..5), int(1..5), int(1..5)) +find q : (int(1..5), int(1..5), int(1..5)) + +such that q = image(p,t) + diff --git a/tests/custom/permutations/10_image_tuple/int/0001_letting_permutation_given_tuple_find_tuple/permutation.param b/tests/custom/permutations/10_image_tuple/int/0001_letting_permutation_given_tuple_find_tuple/permutation.param new file mode 100644 index 0000000000..8498727582 --- /dev/null +++ b/tests/custom/permutations/10_image_tuple/int/0001_letting_permutation_given_tuple_find_tuple/permutation.param @@ -0,0 +1 @@ +letting t be (1,4,5) diff --git a/tests/custom/permutations/10_image_tuple/int/0001_letting_permutation_given_tuple_find_tuple/run.sh b/tests/custom/permutations/10_image_tuple/int/0001_letting_permutation_given_tuple_find_tuple/run.sh new file mode 100755 index 0000000000..9dc67e67f5 --- /dev/null +++ b/tests/custom/permutations/10_image_tuple/int/0001_letting_permutation_given_tuple_find_tuple/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence *.param +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/10_image_tuple/int/0001_letting_permutation_given_tuple_find_tuple/stdout.expected b/tests/custom/permutations/10_image_tuple/int/0001_letting_permutation_given_tuple_find_tuple/stdout.expected new file mode 100644 index 0000000000..719e5b7b9c --- /dev/null +++ b/tests/custom/permutations/10_image_tuple/int/0001_letting_permutation_given_tuple_find_tuple/stdout.expected @@ -0,0 +1,8 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime permutation.param +Copying solution to: permutation-permutation.solution +language Essence 1.3 + +letting q be (3, 1, 5) diff --git a/tests/custom/permutations/10_image_tuple/int/0002_letting_permutation_given_tuple_find_tuple/permutation.essence b/tests/custom/permutations/10_image_tuple/int/0002_letting_permutation_given_tuple_find_tuple/permutation.essence new file mode 100644 index 0000000000..dbdc925827 --- /dev/null +++ b/tests/custom/permutations/10_image_tuple/int/0002_letting_permutation_given_tuple_find_tuple/permutation.essence @@ -0,0 +1,8 @@ +letting n be 5 + +letting p be permutation((1,3,4)) +given t : (int(1..5), int(1..5), int(1..5), int(1..5)) +find q : (int(1..5), int(1..5), int(1..5), int(1..5)) + +such that q = image(p,t) + diff --git a/tests/custom/permutations/10_image_tuple/int/0002_letting_permutation_given_tuple_find_tuple/permutation.param b/tests/custom/permutations/10_image_tuple/int/0002_letting_permutation_given_tuple_find_tuple/permutation.param new file mode 100644 index 0000000000..49565e6780 --- /dev/null +++ b/tests/custom/permutations/10_image_tuple/int/0002_letting_permutation_given_tuple_find_tuple/permutation.param @@ -0,0 +1 @@ +letting t be (1,4,5,2) diff --git a/tests/custom/permutations/10_image_tuple/int/0002_letting_permutation_given_tuple_find_tuple/run.sh b/tests/custom/permutations/10_image_tuple/int/0002_letting_permutation_given_tuple_find_tuple/run.sh new file mode 100755 index 0000000000..9dc67e67f5 --- /dev/null +++ b/tests/custom/permutations/10_image_tuple/int/0002_letting_permutation_given_tuple_find_tuple/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence *.param +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/10_image_tuple/int/0002_letting_permutation_given_tuple_find_tuple/stdout.expected b/tests/custom/permutations/10_image_tuple/int/0002_letting_permutation_given_tuple_find_tuple/stdout.expected new file mode 100644 index 0000000000..f0593a67be --- /dev/null +++ b/tests/custom/permutations/10_image_tuple/int/0002_letting_permutation_given_tuple_find_tuple/stdout.expected @@ -0,0 +1,8 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime permutation.param +Copying solution to: permutation-permutation.solution +language Essence 1.3 + +letting q be (3, 1, 5, 2) diff --git a/tests/custom/permutations/10_image_tuple/int/0003_given_permutation_given_tuple_find_tuple/permutation.essence b/tests/custom/permutations/10_image_tuple/int/0003_given_permutation_given_tuple_find_tuple/permutation.essence new file mode 100644 index 0000000000..ed4d8c10a4 --- /dev/null +++ b/tests/custom/permutations/10_image_tuple/int/0003_given_permutation_given_tuple_find_tuple/permutation.essence @@ -0,0 +1,10 @@ +letting n be 5 + +given p : permutation of int(1..n) +given t : (int(1..n), int(1..n), int(1..n)) +find q : (int(1..n), int(1..n), int(1..n)) + + + +such that q = image(p, t) + diff --git a/tests/custom/permutations/10_image_tuple/int/0003_given_permutation_given_tuple_find_tuple/permutation.param b/tests/custom/permutations/10_image_tuple/int/0003_given_permutation_given_tuple_find_tuple/permutation.param new file mode 100644 index 0000000000..110f00ec0d --- /dev/null +++ b/tests/custom/permutations/10_image_tuple/int/0003_given_permutation_given_tuple_find_tuple/permutation.param @@ -0,0 +1,2 @@ +letting p be permutation((1,3,4)) +letting t be (1,4,5) diff --git a/tests/custom/permutations/10_image_tuple/int/0003_given_permutation_given_tuple_find_tuple/run.sh b/tests/custom/permutations/10_image_tuple/int/0003_given_permutation_given_tuple_find_tuple/run.sh new file mode 100755 index 0000000000..9dc67e67f5 --- /dev/null +++ b/tests/custom/permutations/10_image_tuple/int/0003_given_permutation_given_tuple_find_tuple/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence *.param +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/10_image_tuple/int/0003_given_permutation_given_tuple_find_tuple/stdout.expected b/tests/custom/permutations/10_image_tuple/int/0003_given_permutation_given_tuple_find_tuple/stdout.expected new file mode 100644 index 0000000000..719e5b7b9c --- /dev/null +++ b/tests/custom/permutations/10_image_tuple/int/0003_given_permutation_given_tuple_find_tuple/stdout.expected @@ -0,0 +1,8 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime permutation.param +Copying solution to: permutation-permutation.solution +language Essence 1.3 + +letting q be (3, 1, 5) diff --git a/tests/custom/permutations/10_image_tuple/int/0004_given_permutation_find_tuple_find_tuple/permutation.essence b/tests/custom/permutations/10_image_tuple/int/0004_given_permutation_find_tuple_find_tuple/permutation.essence new file mode 100644 index 0000000000..688cb2c963 --- /dev/null +++ b/tests/custom/permutations/10_image_tuple/int/0004_given_permutation_find_tuple_find_tuple/permutation.essence @@ -0,0 +1,10 @@ +letting n be 5 + +given p : permutation of int(1..n) +find t : (int(1..n), int(1..n), int(1..n)) +find q : (int(1..n), int(1..n), int(1..n)) + + + +such that q = image(p, t) + diff --git a/tests/custom/permutations/10_image_tuple/int/0004_given_permutation_find_tuple_find_tuple/permutation.param b/tests/custom/permutations/10_image_tuple/int/0004_given_permutation_find_tuple_find_tuple/permutation.param new file mode 100644 index 0000000000..8a8c516801 --- /dev/null +++ b/tests/custom/permutations/10_image_tuple/int/0004_given_permutation_find_tuple_find_tuple/permutation.param @@ -0,0 +1 @@ +letting p be permutation((1,3,4)) diff --git a/tests/custom/permutations/10_image_tuple/int/0004_given_permutation_find_tuple_find_tuple/run.sh b/tests/custom/permutations/10_image_tuple/int/0004_given_permutation_find_tuple_find_tuple/run.sh new file mode 100755 index 0000000000..aab5d44c6e --- /dev/null +++ b/tests/custom/permutations/10_image_tuple/int/0004_given_permutation_find_tuple_find_tuple/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence *.param --number-of-solutions=10 +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/10_image_tuple/int/0004_given_permutation_find_tuple_find_tuple/stdout.expected b/tests/custom/permutations/10_image_tuple/int/0004_given_permutation_find_tuple_find_tuple/stdout.expected new file mode 100644 index 0000000000..88540848fd --- /dev/null +++ b/tests/custom/permutations/10_image_tuple/int/0004_given_permutation_find_tuple_find_tuple/stdout.expected @@ -0,0 +1,54 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime permutation.param +Copying solution to: permutation-permutation-000001.solution +Copying solution to: permutation-permutation-000002.solution +Copying solution to: permutation-permutation-000003.solution +Copying solution to: permutation-permutation-000004.solution +Copying solution to: permutation-permutation-000005.solution +Copying solution to: permutation-permutation-000006.solution +Copying solution to: permutation-permutation-000007.solution +Copying solution to: permutation-permutation-000008.solution +Copying solution to: permutation-permutation-000009.solution +Copying solution to: permutation-permutation-000010.solution +language Essence 1.3 + +letting q be (3, 3, 3) +letting t be (1, 1, 1) +language Essence 1.3 + +letting q be (3, 3, 2) +letting t be (1, 1, 2) +language Essence 1.3 + +letting q be (3, 3, 4) +letting t be (1, 1, 3) +language Essence 1.3 + +letting q be (3, 3, 1) +letting t be (1, 1, 4) +language Essence 1.3 + +letting q be (3, 3, 5) +letting t be (1, 1, 5) +language Essence 1.3 + +letting q be (3, 2, 3) +letting t be (1, 2, 1) +language Essence 1.3 + +letting q be (3, 2, 2) +letting t be (1, 2, 2) +language Essence 1.3 + +letting q be (3, 2, 4) +letting t be (1, 2, 3) +language Essence 1.3 + +letting q be (3, 2, 1) +letting t be (1, 2, 4) +language Essence 1.3 + +letting q be (3, 2, 5) +letting t be (1, 2, 5) diff --git a/tests/custom/permutations/10_image_tuple/int/0005_find_permutation_find_tuple_find_tuple/permutation.essence b/tests/custom/permutations/10_image_tuple/int/0005_find_permutation_find_tuple_find_tuple/permutation.essence new file mode 100644 index 0000000000..e06c7ffc0d --- /dev/null +++ b/tests/custom/permutations/10_image_tuple/int/0005_find_permutation_find_tuple_find_tuple/permutation.essence @@ -0,0 +1,10 @@ +letting n be 5 + +find p : permutation of int(1..n) +find t : (int(1..n), int(1..n), int(1..n)) +find q : (int(1..n), int(1..n), int(1..n)) + + + +such that (q = image(p, t)) /\ (4 = sum([toInt(l != r) | (l,r) <- p])) + diff --git a/tests/custom/permutations/10_image_tuple/int/0005_find_permutation_find_tuple_find_tuple/run.sh b/tests/custom/permutations/10_image_tuple/int/0005_find_permutation_find_tuple_find_tuple/run.sh new file mode 100755 index 0000000000..03373df6cb --- /dev/null +++ b/tests/custom/permutations/10_image_tuple/int/0005_find_permutation_find_tuple_find_tuple/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence --number-of-solutions=10 +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/10_image_tuple/int/0005_find_permutation_find_tuple_find_tuple/stdout.expected b/tests/custom/permutations/10_image_tuple/int/0005_find_permutation_find_tuple_find_tuple/stdout.expected new file mode 100644 index 0000000000..4413c9de83 --- /dev/null +++ b/tests/custom/permutations/10_image_tuple/int/0005_find_permutation_find_tuple_find_tuple/stdout.expected @@ -0,0 +1,64 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Copying solution to: permutation-000001.solution +Copying solution to: permutation-000002.solution +Copying solution to: permutation-000003.solution +Copying solution to: permutation-000004.solution +Copying solution to: permutation-000005.solution +Copying solution to: permutation-000006.solution +Copying solution to: permutation-000007.solution +Copying solution to: permutation-000008.solution +Copying solution to: permutation-000009.solution +Copying solution to: permutation-000010.solution +language Essence 1.3 + +letting p be permutation((2, 3), (4, 5)) +letting q be (1, 1, 1) +letting t be (1, 1, 1) +language Essence 1.3 + +letting p be permutation((2, 3), (4, 5)) +letting q be (1, 1, 3) +letting t be (1, 1, 2) +language Essence 1.3 + +letting p be permutation((2, 3), (4, 5)) +letting q be (1, 1, 2) +letting t be (1, 1, 3) +language Essence 1.3 + +letting p be permutation((2, 3), (4, 5)) +letting q be (1, 1, 5) +letting t be (1, 1, 4) +language Essence 1.3 + +letting p be permutation((2, 3), (4, 5)) +letting q be (1, 1, 4) +letting t be (1, 1, 5) +language Essence 1.3 + +letting p be permutation((2, 3), (4, 5)) +letting q be (1, 3, 1) +letting t be (1, 2, 1) +language Essence 1.3 + +letting p be permutation((2, 3), (4, 5)) +letting q be (1, 3, 3) +letting t be (1, 2, 2) +language Essence 1.3 + +letting p be permutation((2, 3), (4, 5)) +letting q be (1, 3, 2) +letting t be (1, 2, 3) +language Essence 1.3 + +letting p be permutation((2, 3), (4, 5)) +letting q be (1, 3, 5) +letting t be (1, 2, 4) +language Essence 1.3 + +letting p be permutation((2, 3), (4, 5)) +letting q be (1, 3, 4) +letting t be (1, 2, 5) diff --git a/tests/custom/permutations/10_image_tuple/runthese.sh b/tests/custom/permutations/10_image_tuple/runthese.sh new file mode 100644 index 0000000000..47ef7cdc6b --- /dev/null +++ b/tests/custom/permutations/10_image_tuple/runthese.sh @@ -0,0 +1 @@ +stack build --copy-bins --test --test-arguments "-p custom.permutations.10_image_tuple" diff --git a/tests/custom/permutations/10_image_tuple/unnamed/0005_find_permutation_find_tuple_find_tuple/permutation.essence b/tests/custom/permutations/10_image_tuple/unnamed/0005_find_permutation_find_tuple_find_tuple/permutation.essence new file mode 100644 index 0000000000..dade0a1bf6 --- /dev/null +++ b/tests/custom/permutations/10_image_tuple/unnamed/0005_find_permutation_find_tuple_find_tuple/permutation.essence @@ -0,0 +1,9 @@ +letting n be new type of size 5 + +find p : permutation of n +find t : (n,n,n) +find q : (n,n,n) + + +such that (q = image(p, t)) /\ (4 = sum([toInt(l != r) | (l,r) <- p])) + diff --git a/tests/custom/permutations/10_image_tuple/unnamed/0005_find_permutation_find_tuple_find_tuple/run.sh b/tests/custom/permutations/10_image_tuple/unnamed/0005_find_permutation_find_tuple_find_tuple/run.sh new file mode 100755 index 0000000000..03373df6cb --- /dev/null +++ b/tests/custom/permutations/10_image_tuple/unnamed/0005_find_permutation_find_tuple_find_tuple/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence --number-of-solutions=10 +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/10_image_tuple/unnamed/0005_find_permutation_find_tuple_find_tuple/stdout.expected b/tests/custom/permutations/10_image_tuple/unnamed/0005_find_permutation_find_tuple_find_tuple/stdout.expected new file mode 100644 index 0000000000..8ed90d7f24 --- /dev/null +++ b/tests/custom/permutations/10_image_tuple/unnamed/0005_find_permutation_find_tuple_find_tuple/stdout.expected @@ -0,0 +1,74 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Copying solution to: permutation-000001.solution +Copying solution to: permutation-000002.solution +Copying solution to: permutation-000003.solution +Copying solution to: permutation-000004.solution +Copying solution to: permutation-000005.solution +Copying solution to: permutation-000006.solution +Copying solution to: permutation-000007.solution +Copying solution to: permutation-000008.solution +Copying solution to: permutation-000009.solution +Copying solution to: permutation-000010.solution +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5} +letting p be permutation((n_2, n_3), (n_4, n_5)) +letting q be (n_1, n_1, n_1) +letting t be (n_1, n_1, n_1) +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5} +letting p be permutation((n_2, n_3), (n_4, n_5)) +letting q be (n_1, n_1, n_3) +letting t be (n_1, n_1, n_2) +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5} +letting p be permutation((n_2, n_3), (n_4, n_5)) +letting q be (n_1, n_1, n_2) +letting t be (n_1, n_1, n_3) +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5} +letting p be permutation((n_2, n_3), (n_4, n_5)) +letting q be (n_1, n_1, n_5) +letting t be (n_1, n_1, n_4) +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5} +letting p be permutation((n_2, n_3), (n_4, n_5)) +letting q be (n_1, n_1, n_4) +letting t be (n_1, n_1, n_5) +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5} +letting p be permutation((n_2, n_3), (n_4, n_5)) +letting q be (n_1, n_3, n_1) +letting t be (n_1, n_2, n_1) +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5} +letting p be permutation((n_2, n_3), (n_4, n_5)) +letting q be (n_1, n_3, n_3) +letting t be (n_1, n_2, n_2) +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5} +letting p be permutation((n_2, n_3), (n_4, n_5)) +letting q be (n_1, n_3, n_2) +letting t be (n_1, n_2, n_3) +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5} +letting p be permutation((n_2, n_3), (n_4, n_5)) +letting q be (n_1, n_3, n_5) +letting t be (n_1, n_2, n_4) +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5} +letting p be permutation((n_2, n_3), (n_4, n_5)) +letting q be (n_1, n_3, n_4) +letting t be (n_1, n_2, n_5) diff --git a/tests/custom/permutations/11_image_relation/int/0001_given_permutation_letting_set/permutation.essence b/tests/custom/permutations/11_image_relation/int/0001_given_permutation_letting_set/permutation.essence new file mode 100644 index 0000000000..8245be0083 --- /dev/null +++ b/tests/custom/permutations/11_image_relation/int/0001_given_permutation_letting_set/permutation.essence @@ -0,0 +1,11 @@ +letting n be 4 + +given p : permutation of int(1..n) +given s : relation of (int(1..n) * int(1..n)) + +find sn : relation of (int(1..n) * int(1..n)) + + + +such that sn = image(p,s) + diff --git a/tests/custom/permutations/11_image_relation/int/0001_given_permutation_letting_set/permutation.param b/tests/custom/permutations/11_image_relation/int/0001_given_permutation_letting_set/permutation.param new file mode 100644 index 0000000000..a3e9ac8b2f --- /dev/null +++ b/tests/custom/permutations/11_image_relation/int/0001_given_permutation_letting_set/permutation.param @@ -0,0 +1,2 @@ +letting p be permutation((1,3,4)) +letting s be relation((1,2),(3,4)) diff --git a/tests/custom/permutations/11_image_relation/int/0001_given_permutation_letting_set/run.sh b/tests/custom/permutations/11_image_relation/int/0001_given_permutation_letting_set/run.sh new file mode 100755 index 0000000000..9dc67e67f5 --- /dev/null +++ b/tests/custom/permutations/11_image_relation/int/0001_given_permutation_letting_set/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence *.param +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/11_image_relation/int/0001_given_permutation_letting_set/stdout.expected b/tests/custom/permutations/11_image_relation/int/0001_given_permutation_letting_set/stdout.expected new file mode 100644 index 0000000000..672239ad4e --- /dev/null +++ b/tests/custom/permutations/11_image_relation/int/0001_given_permutation_letting_set/stdout.expected @@ -0,0 +1,12 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime permutation.param +Copying solution to: permutation-permutation.solution +language Essence 1.3 + +letting sn be relation((3, 2), (4, 1)) +$ Visualisation for sn +$ 3 2 +$ 4 1 + diff --git a/tests/custom/permutations/11_image_relation/runthese.sh b/tests/custom/permutations/11_image_relation/runthese.sh new file mode 100644 index 0000000000..1622b0171a --- /dev/null +++ b/tests/custom/permutations/11_image_relation/runthese.sh @@ -0,0 +1,2 @@ +stack install +stack test --test-arguments "-p custom.permutations.11_image_relation" From b8f40915515d2965d29e8227178e11fffc51e40e Mon Sep 17 00:00:00 2001 From: Fraser Dunlop Date: Wed, 19 Dec 2018 23:08:21 +0000 Subject: [PATCH 059/229] relation + list tests --- src/Conjure/Language/Expression/Op/Image.hs | 22 +++++++----- src/Conjure/Rules/Horizontal/Function.hs | 2 +- src/Conjure/Rules/Horizontal/Permutation.hs | 9 +++-- .../permutation.essence | 11 ++++++ .../permutation.param | 2 ++ .../run.sh | 0 .../stdout.expected | 12 +++++++ .../permutation.essence | 11 ++++++ .../permutation.param | 1 + .../run.sh | 3 ++ .../stdout.expected | 12 +++++++ .../permutation.essence | 10 ++++++ .../permutation.param | 1 + .../run.sh | 3 ++ .../stdout.expected | 13 +++++++ .../permutation.essence | 10 ++++++ .../run.sh | 3 ++ .../stdout.expected | 22 ++++++++++++ .../permutation.essence | 0 .../permutation.param | 0 .../run.sh | 3 ++ .../stdout.expected | 0 .../permutation.essence | 11 ++++++ .../permutation.param | 1 + .../run.sh | 3 ++ .../stdout.expected | 12 +++++++ .../permutation.essence | 10 ++++++ .../permutation.param | 1 + .../run.sh | 3 ++ .../stdout.expected | 13 +++++++ .../permutation.essence | 10 ++++++ .../run.sh | 3 ++ .../stdout.expected | 22 ++++++++++++ .../permutation.essence | 10 ++++++ .../run.sh | 3 ++ .../stdout.expected | 23 +++++++++++++ .../permutation.essence | 8 +++++ .../0010_given_permutation/permutation.param | 2 ++ .../enum/0010_given_permutation/run.sh | 3 ++ .../0010_given_permutation/stdout.expected | 8 +++++ .../permutation.essence | 7 ++++ .../enum/0020_letting_permutation/run.sh | 3 ++ .../0020_letting_permutation/stdout.expected | 8 +++++ .../0030_find_permutation/permutation.essence | 7 ++++ .../enum/0030_find_permutation/run.sh | 3 ++ .../0030_find_permutation/stdout.expected | 9 +++++ .../permutation.essence | 8 +++++ .../0010_given_permutation/permutation.param | 2 ++ .../int/0010_given_permutation/run.sh | 3 ++ .../0010_given_permutation/stdout.expected | 8 +++++ .../permutation.essence | 7 ++++ .../int/0020_letting_permutation/run.sh | 3 ++ .../0020_letting_permutation/stdout.expected | 8 +++++ .../0030_find_permutation/permutation.essence | 6 ++++ .../int/0030_find_permutation/run.sh | 3 ++ .../int/0030_find_permutation/stdout.expected | 8 +++++ .../permutations/12_image_list/runthese.sh | 1 + .../0030_find_permutation/permutation.essence | 8 +++++ .../unnamed/0030_find_permutation/run.sh | 3 ++ .../0030_find_permutation/stdout.expected | 11 ++++++ tests/custom/permutations/README.md | 34 ------------------- 61 files changed, 398 insertions(+), 48 deletions(-) create mode 100644 tests/custom/permutations/11_image_relation/enum/0010_given_permutation_letting_relation/permutation.essence create mode 100644 tests/custom/permutations/11_image_relation/enum/0010_given_permutation_letting_relation/permutation.param rename tests/custom/permutations/11_image_relation/{int/0001_given_permutation_letting_set => enum/0010_given_permutation_letting_relation}/run.sh (100%) create mode 100644 tests/custom/permutations/11_image_relation/enum/0010_given_permutation_letting_relation/stdout.expected create mode 100644 tests/custom/permutations/11_image_relation/enum/0020_letting_permutation_letting_relation/permutation.essence create mode 100644 tests/custom/permutations/11_image_relation/enum/0020_letting_permutation_letting_relation/permutation.param create mode 100755 tests/custom/permutations/11_image_relation/enum/0020_letting_permutation_letting_relation/run.sh create mode 100644 tests/custom/permutations/11_image_relation/enum/0020_letting_permutation_letting_relation/stdout.expected create mode 100644 tests/custom/permutations/11_image_relation/enum/0030_find_permutation_given_relation/permutation.essence create mode 100644 tests/custom/permutations/11_image_relation/enum/0030_find_permutation_given_relation/permutation.param create mode 100755 tests/custom/permutations/11_image_relation/enum/0030_find_permutation_given_relation/run.sh create mode 100644 tests/custom/permutations/11_image_relation/enum/0030_find_permutation_given_relation/stdout.expected create mode 100644 tests/custom/permutations/11_image_relation/enum/0040_find_permutation_find_relation/permutation.essence create mode 100755 tests/custom/permutations/11_image_relation/enum/0040_find_permutation_find_relation/run.sh create mode 100644 tests/custom/permutations/11_image_relation/enum/0040_find_permutation_find_relation/stdout.expected rename tests/custom/permutations/11_image_relation/int/{0001_given_permutation_letting_set => 0010_given_permutation_letting_relation}/permutation.essence (100%) rename tests/custom/permutations/11_image_relation/int/{0001_given_permutation_letting_set => 0010_given_permutation_letting_relation}/permutation.param (100%) create mode 100755 tests/custom/permutations/11_image_relation/int/0010_given_permutation_letting_relation/run.sh rename tests/custom/permutations/11_image_relation/int/{0001_given_permutation_letting_set => 0010_given_permutation_letting_relation}/stdout.expected (100%) create mode 100644 tests/custom/permutations/11_image_relation/int/0020_letting_permutation_letting_relation/permutation.essence create mode 100644 tests/custom/permutations/11_image_relation/int/0020_letting_permutation_letting_relation/permutation.param create mode 100755 tests/custom/permutations/11_image_relation/int/0020_letting_permutation_letting_relation/run.sh create mode 100644 tests/custom/permutations/11_image_relation/int/0020_letting_permutation_letting_relation/stdout.expected create mode 100644 tests/custom/permutations/11_image_relation/int/0030_find_permutation_given_relation/permutation.essence create mode 100644 tests/custom/permutations/11_image_relation/int/0030_find_permutation_given_relation/permutation.param create mode 100755 tests/custom/permutations/11_image_relation/int/0030_find_permutation_given_relation/run.sh create mode 100644 tests/custom/permutations/11_image_relation/int/0030_find_permutation_given_relation/stdout.expected create mode 100644 tests/custom/permutations/11_image_relation/int/0040_find_permutation_find_relation/permutation.essence create mode 100755 tests/custom/permutations/11_image_relation/int/0040_find_permutation_find_relation/run.sh create mode 100644 tests/custom/permutations/11_image_relation/int/0040_find_permutation_find_relation/stdout.expected create mode 100644 tests/custom/permutations/11_image_relation/unnamed/0040_find_permutation_find_relation/permutation.essence create mode 100755 tests/custom/permutations/11_image_relation/unnamed/0040_find_permutation_find_relation/run.sh create mode 100644 tests/custom/permutations/11_image_relation/unnamed/0040_find_permutation_find_relation/stdout.expected create mode 100644 tests/custom/permutations/12_image_list/enum/0010_given_permutation/permutation.essence create mode 100644 tests/custom/permutations/12_image_list/enum/0010_given_permutation/permutation.param create mode 100755 tests/custom/permutations/12_image_list/enum/0010_given_permutation/run.sh create mode 100644 tests/custom/permutations/12_image_list/enum/0010_given_permutation/stdout.expected create mode 100644 tests/custom/permutations/12_image_list/enum/0020_letting_permutation/permutation.essence create mode 100755 tests/custom/permutations/12_image_list/enum/0020_letting_permutation/run.sh create mode 100644 tests/custom/permutations/12_image_list/enum/0020_letting_permutation/stdout.expected create mode 100644 tests/custom/permutations/12_image_list/enum/0030_find_permutation/permutation.essence create mode 100755 tests/custom/permutations/12_image_list/enum/0030_find_permutation/run.sh create mode 100644 tests/custom/permutations/12_image_list/enum/0030_find_permutation/stdout.expected create mode 100644 tests/custom/permutations/12_image_list/int/0010_given_permutation/permutation.essence create mode 100644 tests/custom/permutations/12_image_list/int/0010_given_permutation/permutation.param create mode 100755 tests/custom/permutations/12_image_list/int/0010_given_permutation/run.sh create mode 100644 tests/custom/permutations/12_image_list/int/0010_given_permutation/stdout.expected create mode 100644 tests/custom/permutations/12_image_list/int/0020_letting_permutation/permutation.essence create mode 100755 tests/custom/permutations/12_image_list/int/0020_letting_permutation/run.sh create mode 100644 tests/custom/permutations/12_image_list/int/0020_letting_permutation/stdout.expected create mode 100644 tests/custom/permutations/12_image_list/int/0030_find_permutation/permutation.essence create mode 100755 tests/custom/permutations/12_image_list/int/0030_find_permutation/run.sh create mode 100644 tests/custom/permutations/12_image_list/int/0030_find_permutation/stdout.expected create mode 100644 tests/custom/permutations/12_image_list/runthese.sh create mode 100644 tests/custom/permutations/12_image_list/unnamed/0030_find_permutation/permutation.essence create mode 100755 tests/custom/permutations/12_image_list/unnamed/0030_find_permutation/run.sh create mode 100644 tests/custom/permutations/12_image_list/unnamed/0030_find_permutation/stdout.expected delete mode 100644 tests/custom/permutations/README.md diff --git a/src/Conjure/Language/Expression/Op/Image.hs b/src/Conjure/Language/Expression/Op/Image.hs index 70e5ac2c7e..517c2ea740 100644 --- a/src/Conjure/Language/Expression/Op/Image.hs +++ b/src/Conjure/Language/Expression/Op/Image.hs @@ -71,14 +71,20 @@ instance EvaluateOp OpImage where [ "Sequence is multiply defined at this point:" <+> pretty a , "Sequence value:" <+> pretty f ] - evaluateOp op@(OpImage (viewConstantPermutation -> Just xss) i) = do - case filter (i `elem`) xss of - [] -> return i - [h] -> do - case length $ filter (== i) h of - 1 -> return $ head $ drop 1 $ dropWhile (/= i) $ cycle h - _ -> bug "evaluateOp{OpImage} element in cycle of permutationmore than once" - _ -> bug "evaluateOp{OpPermute} element in more than one cycle of permutation" + evaluateOp op@(OpImage p@(viewConstantPermutation -> Just xss) i) = do + (TypePermutation ip) <- typeOf p + ti <- typeOf i + if typesUnify [ti, ip] + then case filter (i `elem`) xss of + [] -> return i + [h] -> do + case length $ filter (== i) h of + 1 -> return $ head $ drop 1 $ dropWhile (/= i) $ cycle h + _ -> bug "evaluateOp{OpImage} element in cycle of permutationmore than once" + _ -> bug "evaluateOp{OpPermute} element in more than one cycle of permutation" + else if ti `containsType` ip + then na "refinement required to evaluate image of permutation" + else return i evaluateOp op = na $ "evaluateOp{OpImage}:" <++> pretty (show op) instance SimplifyOp OpImage x where diff --git a/src/Conjure/Rules/Horizontal/Function.hs b/src/Conjure/Rules/Horizontal/Function.hs index 126a5a74c4..84a0b11866 100644 --- a/src/Conjure/Rules/Horizontal/Function.hs +++ b/src/Conjure/Rules/Horizontal/Function.hs @@ -567,7 +567,7 @@ rule_Image_Int = "function-image-int" `namedRule` theRule where ( "Function image, int." , do (iPat, i) <- quantifiedVar - let val = make opSum $ Comprehension [essence| &i[2] |] + let val = make opSum $ reTag AnyTag $ Comprehension [essence| &i[2] |] [ Generator (GenInExpr iPat func) , Condition [essence| &i[1] = &arg |] ] diff --git a/src/Conjure/Rules/Horizontal/Permutation.hs b/src/Conjure/Rules/Horizontal/Permutation.hs index 8d56f33b8b..0d7fc1b61e 100644 --- a/src/Conjure/Rules/Horizontal/Permutation.hs +++ b/src/Conjure/Rules/Horizontal/Permutation.hs @@ -128,7 +128,7 @@ rule_Image_Literal = "permutation-image-literal" `namedRule` theRule where return ( "Horizontal rule for permutation literal application to a single value (image), AsFunction representation" , do - return $ reTag AnyTag [essence| [&i, catchUndef(image(&outLiteral,&i),0)][toInt(&i in defined(&outLiteral))+1] |] + return [essence| [&i, catchUndef(image(&outLiteral,&i),0)][toInt(&i in defined(&outLiteral))+1] |] ) else if typeI `containsType` inner then na "rule_Image_Literal" @@ -157,7 +157,7 @@ rule_Image_Literal_Comprehension = "permutation-image-literal-comprehension" `na ( "Horizontal rule for permutation literal application to a single value (image), AsFunction representation" , do return $ Comprehension body $ gocBefore - ++ [ Generator (GenInExpr pat (reTag AnyTag [essence| [&i, catchUndef(image(&outLiteral,&i),0)][toInt(&i in defined(&outLiteral))+1] |])) + ++ [ Generator (GenInExpr pat [essence| [&i, catchUndef(image(&outLiteral,&i),0)][toInt(&i in defined(&outLiteral))+1] |]) ] ++ gocAfter ) else if typeI `containsType` inner @@ -247,9 +247,8 @@ rule_Compose = "permutation-compose" `namedRule` theRule where (pName, p) <- auxiliaryVar return $ WithLocals [essence| &p |] - ( AuxiliaryVars --TODO this reTag seems dangerous - -- does it break image of nested type object? - [ reTag AnyTag (Declaration (FindOrGiven LocalFind pName du)) + ( AuxiliaryVars + [ (Declaration (FindOrGiven LocalFind pName du)) , SuchThat [ [essence| forAll &lPat in (defined(&g) union defined(&h)) . diff --git a/tests/custom/permutations/11_image_relation/enum/0010_given_permutation_letting_relation/permutation.essence b/tests/custom/permutations/11_image_relation/enum/0010_given_permutation_letting_relation/permutation.essence new file mode 100644 index 0000000000..5ccea8a6b8 --- /dev/null +++ b/tests/custom/permutations/11_image_relation/enum/0010_given_permutation_letting_relation/permutation.essence @@ -0,0 +1,11 @@ +letting n be new type enum {E1,E2,E3,E4} + +given p : permutation of n +given s : relation of (n * n) + +find sn : relation of (n * n) + + + +such that sn = image(p,s) + diff --git a/tests/custom/permutations/11_image_relation/enum/0010_given_permutation_letting_relation/permutation.param b/tests/custom/permutations/11_image_relation/enum/0010_given_permutation_letting_relation/permutation.param new file mode 100644 index 0000000000..ef1f1be2c6 --- /dev/null +++ b/tests/custom/permutations/11_image_relation/enum/0010_given_permutation_letting_relation/permutation.param @@ -0,0 +1,2 @@ +letting p be permutation((E1,E3,E4)) +letting s be relation((E1,E2),(E3,E4)) diff --git a/tests/custom/permutations/11_image_relation/int/0001_given_permutation_letting_set/run.sh b/tests/custom/permutations/11_image_relation/enum/0010_given_permutation_letting_relation/run.sh similarity index 100% rename from tests/custom/permutations/11_image_relation/int/0001_given_permutation_letting_set/run.sh rename to tests/custom/permutations/11_image_relation/enum/0010_given_permutation_letting_relation/run.sh diff --git a/tests/custom/permutations/11_image_relation/enum/0010_given_permutation_letting_relation/stdout.expected b/tests/custom/permutations/11_image_relation/enum/0010_given_permutation_letting_relation/stdout.expected new file mode 100644 index 0000000000..0958f891d2 --- /dev/null +++ b/tests/custom/permutations/11_image_relation/enum/0010_given_permutation_letting_relation/stdout.expected @@ -0,0 +1,12 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime permutation.param +Copying solution to: permutation-permutation.solution +language Essence 1.3 + +letting sn be relation((E3, E2), (E4, E1)) +$ Visualisation for sn +$ E3 E2 +$ E4 E1 + diff --git a/tests/custom/permutations/11_image_relation/enum/0020_letting_permutation_letting_relation/permutation.essence b/tests/custom/permutations/11_image_relation/enum/0020_letting_permutation_letting_relation/permutation.essence new file mode 100644 index 0000000000..02e9f6473d --- /dev/null +++ b/tests/custom/permutations/11_image_relation/enum/0020_letting_permutation_letting_relation/permutation.essence @@ -0,0 +1,11 @@ +letting n be new type enum {E1,E2,E3,E4} + +letting p be permutation((E1,E3,E4)) +given s : relation of (n * n) + +find sn : relation of (n * n) + + + +such that sn = image(p,s) + diff --git a/tests/custom/permutations/11_image_relation/enum/0020_letting_permutation_letting_relation/permutation.param b/tests/custom/permutations/11_image_relation/enum/0020_letting_permutation_letting_relation/permutation.param new file mode 100644 index 0000000000..13c0afcb0a --- /dev/null +++ b/tests/custom/permutations/11_image_relation/enum/0020_letting_permutation_letting_relation/permutation.param @@ -0,0 +1 @@ +letting s be relation((E1,E2),(E3,E4)) diff --git a/tests/custom/permutations/11_image_relation/enum/0020_letting_permutation_letting_relation/run.sh b/tests/custom/permutations/11_image_relation/enum/0020_letting_permutation_letting_relation/run.sh new file mode 100755 index 0000000000..9dc67e67f5 --- /dev/null +++ b/tests/custom/permutations/11_image_relation/enum/0020_letting_permutation_letting_relation/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence *.param +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/11_image_relation/enum/0020_letting_permutation_letting_relation/stdout.expected b/tests/custom/permutations/11_image_relation/enum/0020_letting_permutation_letting_relation/stdout.expected new file mode 100644 index 0000000000..0958f891d2 --- /dev/null +++ b/tests/custom/permutations/11_image_relation/enum/0020_letting_permutation_letting_relation/stdout.expected @@ -0,0 +1,12 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime permutation.param +Copying solution to: permutation-permutation.solution +language Essence 1.3 + +letting sn be relation((E3, E2), (E4, E1)) +$ Visualisation for sn +$ E3 E2 +$ E4 E1 + diff --git a/tests/custom/permutations/11_image_relation/enum/0030_find_permutation_given_relation/permutation.essence b/tests/custom/permutations/11_image_relation/enum/0030_find_permutation_given_relation/permutation.essence new file mode 100644 index 0000000000..3e30e185cb --- /dev/null +++ b/tests/custom/permutations/11_image_relation/enum/0030_find_permutation_given_relation/permutation.essence @@ -0,0 +1,10 @@ +letting n be new type enum {E1,E2,E3,E4} + +find p : permutation of n +given s : relation of (n * n) + +find sn : relation of (n * n) + + + +such that sn = image(p,s) /\ (3 = sum([ toInt(l!=r) | (l,r) <- p])) diff --git a/tests/custom/permutations/11_image_relation/enum/0030_find_permutation_given_relation/permutation.param b/tests/custom/permutations/11_image_relation/enum/0030_find_permutation_given_relation/permutation.param new file mode 100644 index 0000000000..13c0afcb0a --- /dev/null +++ b/tests/custom/permutations/11_image_relation/enum/0030_find_permutation_given_relation/permutation.param @@ -0,0 +1 @@ +letting s be relation((E1,E2),(E3,E4)) diff --git a/tests/custom/permutations/11_image_relation/enum/0030_find_permutation_given_relation/run.sh b/tests/custom/permutations/11_image_relation/enum/0030_find_permutation_given_relation/run.sh new file mode 100755 index 0000000000..9dc67e67f5 --- /dev/null +++ b/tests/custom/permutations/11_image_relation/enum/0030_find_permutation_given_relation/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence *.param +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/11_image_relation/enum/0030_find_permutation_given_relation/stdout.expected b/tests/custom/permutations/11_image_relation/enum/0030_find_permutation_given_relation/stdout.expected new file mode 100644 index 0000000000..6274febb02 --- /dev/null +++ b/tests/custom/permutations/11_image_relation/enum/0030_find_permutation_given_relation/stdout.expected @@ -0,0 +1,13 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime permutation.param +Copying solution to: permutation-permutation.solution +language Essence 1.3 + +letting p be permutation((E2, E3, E4)) +letting sn be relation((E1, E3), (E4, E2)) +$ Visualisation for sn +$ E1 E3 +$ E4 E2 + diff --git a/tests/custom/permutations/11_image_relation/enum/0040_find_permutation_find_relation/permutation.essence b/tests/custom/permutations/11_image_relation/enum/0040_find_permutation_find_relation/permutation.essence new file mode 100644 index 0000000000..3c7b761179 --- /dev/null +++ b/tests/custom/permutations/11_image_relation/enum/0040_find_permutation_find_relation/permutation.essence @@ -0,0 +1,10 @@ +letting n be new type enum {E1,E2,E3,E4} + +find p : permutation of n +find s : relation of (n * n) + +find sn : relation of (n * n) + + + +such that sn = image(p,s) /\ (3 = sum([ toInt(l!=r) | (l,r) <- p]) /\ |s| = 4) diff --git a/tests/custom/permutations/11_image_relation/enum/0040_find_permutation_find_relation/run.sh b/tests/custom/permutations/11_image_relation/enum/0040_find_permutation_find_relation/run.sh new file mode 100755 index 0000000000..b4899d6266 --- /dev/null +++ b/tests/custom/permutations/11_image_relation/enum/0040_find_permutation_find_relation/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/11_image_relation/enum/0040_find_permutation_find_relation/stdout.expected b/tests/custom/permutations/11_image_relation/enum/0040_find_permutation_find_relation/stdout.expected new file mode 100644 index 0000000000..f7f0905d56 --- /dev/null +++ b/tests/custom/permutations/11_image_relation/enum/0040_find_permutation_find_relation/stdout.expected @@ -0,0 +1,22 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Copying solution to: permutation.solution +language Essence 1.3 + +letting p be permutation((E2, E3, E4)) +letting s be relation((E4, E1), (E4, E2), (E4, E3), (E4, E4)) +$ Visualisation for s +$ E4 E1 +$ E4 E2 +$ E4 E3 +$ E4 E4 + +letting sn be relation((E2, E1), (E2, E2), (E2, E3), (E2, E4)) +$ Visualisation for sn +$ E2 E1 +$ E2 E2 +$ E2 E3 +$ E2 E4 + diff --git a/tests/custom/permutations/11_image_relation/int/0001_given_permutation_letting_set/permutation.essence b/tests/custom/permutations/11_image_relation/int/0010_given_permutation_letting_relation/permutation.essence similarity index 100% rename from tests/custom/permutations/11_image_relation/int/0001_given_permutation_letting_set/permutation.essence rename to tests/custom/permutations/11_image_relation/int/0010_given_permutation_letting_relation/permutation.essence diff --git a/tests/custom/permutations/11_image_relation/int/0001_given_permutation_letting_set/permutation.param b/tests/custom/permutations/11_image_relation/int/0010_given_permutation_letting_relation/permutation.param similarity index 100% rename from tests/custom/permutations/11_image_relation/int/0001_given_permutation_letting_set/permutation.param rename to tests/custom/permutations/11_image_relation/int/0010_given_permutation_letting_relation/permutation.param diff --git a/tests/custom/permutations/11_image_relation/int/0010_given_permutation_letting_relation/run.sh b/tests/custom/permutations/11_image_relation/int/0010_given_permutation_letting_relation/run.sh new file mode 100755 index 0000000000..9dc67e67f5 --- /dev/null +++ b/tests/custom/permutations/11_image_relation/int/0010_given_permutation_letting_relation/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence *.param +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/11_image_relation/int/0001_given_permutation_letting_set/stdout.expected b/tests/custom/permutations/11_image_relation/int/0010_given_permutation_letting_relation/stdout.expected similarity index 100% rename from tests/custom/permutations/11_image_relation/int/0001_given_permutation_letting_set/stdout.expected rename to tests/custom/permutations/11_image_relation/int/0010_given_permutation_letting_relation/stdout.expected diff --git a/tests/custom/permutations/11_image_relation/int/0020_letting_permutation_letting_relation/permutation.essence b/tests/custom/permutations/11_image_relation/int/0020_letting_permutation_letting_relation/permutation.essence new file mode 100644 index 0000000000..b013d8138c --- /dev/null +++ b/tests/custom/permutations/11_image_relation/int/0020_letting_permutation_letting_relation/permutation.essence @@ -0,0 +1,11 @@ +letting n be 4 + +letting p be permutation((1,3,4)) +given s : relation of (int(1..n) * int(1..n)) + +find sn : relation of (int(1..n) * int(1..n)) + + + +such that sn = image(p,s) + diff --git a/tests/custom/permutations/11_image_relation/int/0020_letting_permutation_letting_relation/permutation.param b/tests/custom/permutations/11_image_relation/int/0020_letting_permutation_letting_relation/permutation.param new file mode 100644 index 0000000000..77cfcdb492 --- /dev/null +++ b/tests/custom/permutations/11_image_relation/int/0020_letting_permutation_letting_relation/permutation.param @@ -0,0 +1 @@ +letting s be relation((1,2),(3,4)) diff --git a/tests/custom/permutations/11_image_relation/int/0020_letting_permutation_letting_relation/run.sh b/tests/custom/permutations/11_image_relation/int/0020_letting_permutation_letting_relation/run.sh new file mode 100755 index 0000000000..9dc67e67f5 --- /dev/null +++ b/tests/custom/permutations/11_image_relation/int/0020_letting_permutation_letting_relation/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence *.param +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/11_image_relation/int/0020_letting_permutation_letting_relation/stdout.expected b/tests/custom/permutations/11_image_relation/int/0020_letting_permutation_letting_relation/stdout.expected new file mode 100644 index 0000000000..672239ad4e --- /dev/null +++ b/tests/custom/permutations/11_image_relation/int/0020_letting_permutation_letting_relation/stdout.expected @@ -0,0 +1,12 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime permutation.param +Copying solution to: permutation-permutation.solution +language Essence 1.3 + +letting sn be relation((3, 2), (4, 1)) +$ Visualisation for sn +$ 3 2 +$ 4 1 + diff --git a/tests/custom/permutations/11_image_relation/int/0030_find_permutation_given_relation/permutation.essence b/tests/custom/permutations/11_image_relation/int/0030_find_permutation_given_relation/permutation.essence new file mode 100644 index 0000000000..0e05c005db --- /dev/null +++ b/tests/custom/permutations/11_image_relation/int/0030_find_permutation_given_relation/permutation.essence @@ -0,0 +1,10 @@ +letting n be 4 + +find p : permutation of int(1..n) +given s : relation of (int(1..n) * int(1..n)) + +find sn : relation of (int(1..n) * int(1..n)) + + + +such that sn = image(p,s) /\ (3 = sum([ toInt(l!=r) | (l,r) <- p])) diff --git a/tests/custom/permutations/11_image_relation/int/0030_find_permutation_given_relation/permutation.param b/tests/custom/permutations/11_image_relation/int/0030_find_permutation_given_relation/permutation.param new file mode 100644 index 0000000000..77cfcdb492 --- /dev/null +++ b/tests/custom/permutations/11_image_relation/int/0030_find_permutation_given_relation/permutation.param @@ -0,0 +1 @@ +letting s be relation((1,2),(3,4)) diff --git a/tests/custom/permutations/11_image_relation/int/0030_find_permutation_given_relation/run.sh b/tests/custom/permutations/11_image_relation/int/0030_find_permutation_given_relation/run.sh new file mode 100755 index 0000000000..9dc67e67f5 --- /dev/null +++ b/tests/custom/permutations/11_image_relation/int/0030_find_permutation_given_relation/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence *.param +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/11_image_relation/int/0030_find_permutation_given_relation/stdout.expected b/tests/custom/permutations/11_image_relation/int/0030_find_permutation_given_relation/stdout.expected new file mode 100644 index 0000000000..ba78bdf1b6 --- /dev/null +++ b/tests/custom/permutations/11_image_relation/int/0030_find_permutation_given_relation/stdout.expected @@ -0,0 +1,13 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime permutation.param +Copying solution to: permutation-permutation.solution +language Essence 1.3 + +letting p be permutation((2, 3, 4)) +letting sn be relation((1, 3), (4, 2)) +$ Visualisation for sn +$ 1 3 +$ 4 2 + diff --git a/tests/custom/permutations/11_image_relation/int/0040_find_permutation_find_relation/permutation.essence b/tests/custom/permutations/11_image_relation/int/0040_find_permutation_find_relation/permutation.essence new file mode 100644 index 0000000000..ef68f9ff7a --- /dev/null +++ b/tests/custom/permutations/11_image_relation/int/0040_find_permutation_find_relation/permutation.essence @@ -0,0 +1,10 @@ +letting n be 4 + +find p : permutation of int(1..n) +find s : relation of (int(1..n) * int(1..n)) + +find sn : relation of (int(1..n) * int(1..n)) + + + +such that sn = image(p,s) /\ (3 = sum([ toInt(l!=r) | (l,r) <- p]) /\ |s| = 4) diff --git a/tests/custom/permutations/11_image_relation/int/0040_find_permutation_find_relation/run.sh b/tests/custom/permutations/11_image_relation/int/0040_find_permutation_find_relation/run.sh new file mode 100755 index 0000000000..b4899d6266 --- /dev/null +++ b/tests/custom/permutations/11_image_relation/int/0040_find_permutation_find_relation/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/11_image_relation/int/0040_find_permutation_find_relation/stdout.expected b/tests/custom/permutations/11_image_relation/int/0040_find_permutation_find_relation/stdout.expected new file mode 100644 index 0000000000..4b7742790e --- /dev/null +++ b/tests/custom/permutations/11_image_relation/int/0040_find_permutation_find_relation/stdout.expected @@ -0,0 +1,22 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Copying solution to: permutation.solution +language Essence 1.3 + +letting p be permutation((2, 3, 4)) +letting s be relation((4, 1), (4, 2), (4, 3), (4, 4)) +$ Visualisation for s +$ 4 1 +$ 4 2 +$ 4 3 +$ 4 4 + +letting sn be relation((2, 1), (2, 2), (2, 3), (2, 4)) +$ Visualisation for sn +$ 2 1 +$ 2 2 +$ 2 3 +$ 2 4 + diff --git a/tests/custom/permutations/11_image_relation/unnamed/0040_find_permutation_find_relation/permutation.essence b/tests/custom/permutations/11_image_relation/unnamed/0040_find_permutation_find_relation/permutation.essence new file mode 100644 index 0000000000..f8cf709877 --- /dev/null +++ b/tests/custom/permutations/11_image_relation/unnamed/0040_find_permutation_find_relation/permutation.essence @@ -0,0 +1,10 @@ +letting n be new type of size 4 + +find p : permutation of n +find s : relation of (n * n) + +find sn : relation of (n * n) + + + +such that sn = image(p,s) /\ (3 = sum([ toInt(l!=r) | (l,r) <- p]) /\ |s| = 4) diff --git a/tests/custom/permutations/11_image_relation/unnamed/0040_find_permutation_find_relation/run.sh b/tests/custom/permutations/11_image_relation/unnamed/0040_find_permutation_find_relation/run.sh new file mode 100755 index 0000000000..b4899d6266 --- /dev/null +++ b/tests/custom/permutations/11_image_relation/unnamed/0040_find_permutation_find_relation/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/11_image_relation/unnamed/0040_find_permutation_find_relation/stdout.expected b/tests/custom/permutations/11_image_relation/unnamed/0040_find_permutation_find_relation/stdout.expected new file mode 100644 index 0000000000..8096cfe173 --- /dev/null +++ b/tests/custom/permutations/11_image_relation/unnamed/0040_find_permutation_find_relation/stdout.expected @@ -0,0 +1,23 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Copying solution to: permutation.solution +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_2, n_3, n_4)) +letting s be relation((n_4, n_1), (n_4, n_2), (n_4, n_3), (n_4, n_4)) +$ Visualisation for s +$ n_4 n_1 +$ n_4 n_2 +$ n_4 n_3 +$ n_4 n_4 + +letting sn be relation((n_2, n_1), (n_2, n_2), (n_2, n_3), (n_2, n_4)) +$ Visualisation for sn +$ n_2 n_1 +$ n_2 n_2 +$ n_2 n_3 +$ n_2 n_4 + diff --git a/tests/custom/permutations/12_image_list/enum/0010_given_permutation/permutation.essence b/tests/custom/permutations/12_image_list/enum/0010_given_permutation/permutation.essence new file mode 100644 index 0000000000..2fc7eb726b --- /dev/null +++ b/tests/custom/permutations/12_image_list/enum/0010_given_permutation/permutation.essence @@ -0,0 +1,8 @@ +letting n be new type enum {E1,E2,E3,E4} + +given p : permutation of n + +find b : n + +such that and([ i = b | i <- image(p,[E4,E4,E4,E4])]) + diff --git a/tests/custom/permutations/12_image_list/enum/0010_given_permutation/permutation.param b/tests/custom/permutations/12_image_list/enum/0010_given_permutation/permutation.param new file mode 100644 index 0000000000..595ea14168 --- /dev/null +++ b/tests/custom/permutations/12_image_list/enum/0010_given_permutation/permutation.param @@ -0,0 +1,2 @@ +letting p be permutation((E1,E3,E4)) + diff --git a/tests/custom/permutations/12_image_list/enum/0010_given_permutation/run.sh b/tests/custom/permutations/12_image_list/enum/0010_given_permutation/run.sh new file mode 100755 index 0000000000..9dc67e67f5 --- /dev/null +++ b/tests/custom/permutations/12_image_list/enum/0010_given_permutation/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence *.param +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/12_image_list/enum/0010_given_permutation/stdout.expected b/tests/custom/permutations/12_image_list/enum/0010_given_permutation/stdout.expected new file mode 100644 index 0000000000..506b046403 --- /dev/null +++ b/tests/custom/permutations/12_image_list/enum/0010_given_permutation/stdout.expected @@ -0,0 +1,8 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime permutation.param +Copying solution to: permutation-permutation.solution +language Essence 1.3 + +letting b be E1 diff --git a/tests/custom/permutations/12_image_list/enum/0020_letting_permutation/permutation.essence b/tests/custom/permutations/12_image_list/enum/0020_letting_permutation/permutation.essence new file mode 100644 index 0000000000..ad1e442938 --- /dev/null +++ b/tests/custom/permutations/12_image_list/enum/0020_letting_permutation/permutation.essence @@ -0,0 +1,7 @@ +letting n be new type enum {E1,E2,E3,E4} + +letting p be permutation((E1,E3,E4)) +find b : n + +such that and([i = b | i <- image(p, [E4,E4,E4,E4])]) + diff --git a/tests/custom/permutations/12_image_list/enum/0020_letting_permutation/run.sh b/tests/custom/permutations/12_image_list/enum/0020_letting_permutation/run.sh new file mode 100755 index 0000000000..b4899d6266 --- /dev/null +++ b/tests/custom/permutations/12_image_list/enum/0020_letting_permutation/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/12_image_list/enum/0020_letting_permutation/stdout.expected b/tests/custom/permutations/12_image_list/enum/0020_letting_permutation/stdout.expected new file mode 100644 index 0000000000..7e742d02ef --- /dev/null +++ b/tests/custom/permutations/12_image_list/enum/0020_letting_permutation/stdout.expected @@ -0,0 +1,8 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Copying solution to: permutation.solution +language Essence 1.3 + +letting b be E1 diff --git a/tests/custom/permutations/12_image_list/enum/0030_find_permutation/permutation.essence b/tests/custom/permutations/12_image_list/enum/0030_find_permutation/permutation.essence new file mode 100644 index 0000000000..f2003d2684 --- /dev/null +++ b/tests/custom/permutations/12_image_list/enum/0030_find_permutation/permutation.essence @@ -0,0 +1,7 @@ +letting n be new type enum {E1,E2,E3,E4} + +find p : permutation of n +find b : n + +such that and([i = b | i <- image(p, [E4,E4,E4,E4])]) /\ b != E4 + diff --git a/tests/custom/permutations/12_image_list/enum/0030_find_permutation/run.sh b/tests/custom/permutations/12_image_list/enum/0030_find_permutation/run.sh new file mode 100755 index 0000000000..b4899d6266 --- /dev/null +++ b/tests/custom/permutations/12_image_list/enum/0030_find_permutation/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/12_image_list/enum/0030_find_permutation/stdout.expected b/tests/custom/permutations/12_image_list/enum/0030_find_permutation/stdout.expected new file mode 100644 index 0000000000..b8d3197660 --- /dev/null +++ b/tests/custom/permutations/12_image_list/enum/0030_find_permutation/stdout.expected @@ -0,0 +1,9 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Copying solution to: permutation.solution +language Essence 1.3 + +letting b be E3 +letting p be permutation((E3, E4)) diff --git a/tests/custom/permutations/12_image_list/int/0010_given_permutation/permutation.essence b/tests/custom/permutations/12_image_list/int/0010_given_permutation/permutation.essence new file mode 100644 index 0000000000..603a3a6d80 --- /dev/null +++ b/tests/custom/permutations/12_image_list/int/0010_given_permutation/permutation.essence @@ -0,0 +1,8 @@ +letting n be 4 + +given p : permutation of int(1..n) + +find b : int(1..50) + +such that b = sum([ i | i <- image(p,[4,4,4,4])]) + diff --git a/tests/custom/permutations/12_image_list/int/0010_given_permutation/permutation.param b/tests/custom/permutations/12_image_list/int/0010_given_permutation/permutation.param new file mode 100644 index 0000000000..38c4159c22 --- /dev/null +++ b/tests/custom/permutations/12_image_list/int/0010_given_permutation/permutation.param @@ -0,0 +1,2 @@ +letting p be permutation((1,3,4)) + diff --git a/tests/custom/permutations/12_image_list/int/0010_given_permutation/run.sh b/tests/custom/permutations/12_image_list/int/0010_given_permutation/run.sh new file mode 100755 index 0000000000..9dc67e67f5 --- /dev/null +++ b/tests/custom/permutations/12_image_list/int/0010_given_permutation/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence *.param +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/12_image_list/int/0010_given_permutation/stdout.expected b/tests/custom/permutations/12_image_list/int/0010_given_permutation/stdout.expected new file mode 100644 index 0000000000..b149f7b32e --- /dev/null +++ b/tests/custom/permutations/12_image_list/int/0010_given_permutation/stdout.expected @@ -0,0 +1,8 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime permutation.param +Copying solution to: permutation-permutation.solution +language Essence 1.3 + +letting b be 4 diff --git a/tests/custom/permutations/12_image_list/int/0020_letting_permutation/permutation.essence b/tests/custom/permutations/12_image_list/int/0020_letting_permutation/permutation.essence new file mode 100644 index 0000000000..7ccc16aff8 --- /dev/null +++ b/tests/custom/permutations/12_image_list/int/0020_letting_permutation/permutation.essence @@ -0,0 +1,7 @@ +letting n be 4 + +letting p be permutation((1,3,4)) +find b : int(1..50) + +such that b = sum([i | i <- image(p, [4,4,4,4])]) + diff --git a/tests/custom/permutations/12_image_list/int/0020_letting_permutation/run.sh b/tests/custom/permutations/12_image_list/int/0020_letting_permutation/run.sh new file mode 100755 index 0000000000..b4899d6266 --- /dev/null +++ b/tests/custom/permutations/12_image_list/int/0020_letting_permutation/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/12_image_list/int/0020_letting_permutation/stdout.expected b/tests/custom/permutations/12_image_list/int/0020_letting_permutation/stdout.expected new file mode 100644 index 0000000000..12a21c3a0e --- /dev/null +++ b/tests/custom/permutations/12_image_list/int/0020_letting_permutation/stdout.expected @@ -0,0 +1,8 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Copying solution to: permutation.solution +language Essence 1.3 + +letting b be 4 diff --git a/tests/custom/permutations/12_image_list/int/0030_find_permutation/permutation.essence b/tests/custom/permutations/12_image_list/int/0030_find_permutation/permutation.essence new file mode 100644 index 0000000000..50bd7450a8 --- /dev/null +++ b/tests/custom/permutations/12_image_list/int/0030_find_permutation/permutation.essence @@ -0,0 +1,6 @@ +letting n be 4 + +find p : permutation of int(1..4) + +such that 4 = sum([i | i <- image(p, [4,4,4,4])]) + diff --git a/tests/custom/permutations/12_image_list/int/0030_find_permutation/run.sh b/tests/custom/permutations/12_image_list/int/0030_find_permutation/run.sh new file mode 100755 index 0000000000..b4899d6266 --- /dev/null +++ b/tests/custom/permutations/12_image_list/int/0030_find_permutation/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/12_image_list/int/0030_find_permutation/stdout.expected b/tests/custom/permutations/12_image_list/int/0030_find_permutation/stdout.expected new file mode 100644 index 0000000000..1fc3c0fa55 --- /dev/null +++ b/tests/custom/permutations/12_image_list/int/0030_find_permutation/stdout.expected @@ -0,0 +1,8 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Copying solution to: permutation.solution +language Essence 1.3 + +letting p be permutation((1, 2, 3, 4)) diff --git a/tests/custom/permutations/12_image_list/runthese.sh b/tests/custom/permutations/12_image_list/runthese.sh new file mode 100644 index 0000000000..3a0e2a9392 --- /dev/null +++ b/tests/custom/permutations/12_image_list/runthese.sh @@ -0,0 +1 @@ +stack build --copy-bins --test --test-arguments "-p custom.permutations.12_image_list" diff --git a/tests/custom/permutations/12_image_list/unnamed/0030_find_permutation/permutation.essence b/tests/custom/permutations/12_image_list/unnamed/0030_find_permutation/permutation.essence new file mode 100644 index 0000000000..b3570ccf42 --- /dev/null +++ b/tests/custom/permutations/12_image_list/unnamed/0030_find_permutation/permutation.essence @@ -0,0 +1,8 @@ +letting n be new type of size 4 + +find p : permutation of n +find b : n +find c : n + +such that and([i = b | i <- image(p, [c,c,c,c])]) /\ b != c + diff --git a/tests/custom/permutations/12_image_list/unnamed/0030_find_permutation/run.sh b/tests/custom/permutations/12_image_list/unnamed/0030_find_permutation/run.sh new file mode 100755 index 0000000000..b4899d6266 --- /dev/null +++ b/tests/custom/permutations/12_image_list/unnamed/0030_find_permutation/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/12_image_list/unnamed/0030_find_permutation/stdout.expected b/tests/custom/permutations/12_image_list/unnamed/0030_find_permutation/stdout.expected new file mode 100644 index 0000000000..dd091051e6 --- /dev/null +++ b/tests/custom/permutations/12_image_list/unnamed/0030_find_permutation/stdout.expected @@ -0,0 +1,11 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Copying solution to: permutation.solution +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting b be n_3 +letting c be n_4 +letting p be permutation((n_3, n_4)) diff --git a/tests/custom/permutations/README.md b/tests/custom/permutations/README.md deleted file mode 100644 index 85ecf77b0f..0000000000 --- a/tests/custom/permutations/README.md +++ /dev/null @@ -1,34 +0,0 @@ -# Permutations spec -Organized by level - each level adding functionality -At the moment a permutation's inner type is restricted -to types that can index a matrix i.e. int, enum, unnamed types - -## 01 representation -Tests permutation behaviour that should work with no rewrite rules. -- permutations must parse correctly in model and parameter files -- the size attribute must constrain the size of the permutation -- enumeration tests for finding permutations -- TODO add tests for enums, unnameds - -## 02 cardinality -Test that we can get the number of permuted elements by |p| -- basic cardinality for find, letting, given -- TODO add tests for enums, unnameds - -## 03 generators -Tests permutations in generator of a comprehension -- TODO add tests for enums, unnameds - -## 04 image of value of inner type under permutation -- TODO add tests for enums & unnameds - -## 05 equality -Tests equality on permutations -- basic equality for find, letting, given -- tests [|p| = i | p <- sp] where sp is a set of permutations - -## 06 inverse -Testing inverse in minimal contexts - -## 07 Compose -Testing composition in minimal contexts From 39412bd942849626feabcc242428fb372d7d4160 Mon Sep 17 00:00:00 2001 From: Fraser Dunlop Date: Thu, 20 Dec 2018 12:34:32 +0000 Subject: [PATCH 060/229] sequence tests --- src/Conjure/Rules/Horizontal/Permutation.hs | 152 +++---- src/Conjure/Rules/Horizontal/Sequence.hs | 2 +- src/Conjure/Rules/Vertical/Permutation.hs | 375 +----------------- src/Conjure/UI/Model.hs | 19 +- .../01_representation/runthese.sh | 2 +- .../stdout.expected | 2 +- .../0003_find_permutation/stdout.expected | 2 +- .../stdout.expected | 2 +- .../int/0003_find_permutation/stdout.expected | 2 +- .../0003_find_permutation/stdout.expected | 2 +- .../permutations/03_generators/runthese.sh | 3 +- .../permutations/05_equality/runthese.sh | 3 +- .../permutations/06_inverse/runthese.sh | 3 +- .../permutations/08_image_set/runthese.sh | 3 +- .../11_image_relation/runthese.sh | 3 +- .../permutation.essence | 8 + .../0010_given_permutation/permutation.param | 2 + .../enum/0010_given_permutation/run.sh | 3 + .../0010_given_permutation/stdout.expected | 8 + .../permutation.essence | 8 + .../enum/0020_letting_permutation/run.sh | 3 + .../0020_letting_permutation/stdout.expected | 8 + .../0030_find_permutation/permutation.essence | 8 + .../enum/0030_find_permutation/run.sh | 3 + .../0030_find_permutation/stdout.expected | 8 + .../permutation.essence | 8 + .../0010_given_permutation/permutation.param | 2 + .../int/0010_given_permutation/run.sh | 3 + .../0010_given_permutation/stdout.expected | 8 + .../permutation.essence | 8 + .../int/0020_letting_permutation/run.sh | 3 + .../0020_letting_permutation/stdout.expected | 8 + .../0030_find_permutation/permutation.essence | 8 + .../int/0030_find_permutation/run.sh | 3 + .../int/0030_find_permutation/stdout.expected | 8 + .../13_image_function/runthese.sh | 1 + .../0030_find_permutation/permutation.essence | 9 + .../unnamed/0030_find_permutation/run.sh | 3 + .../0030_find_permutation/stdout.expected | 11 + .../permutation.essence | 8 + .../0010_given_permutation/permutation.param | 2 + .../enum/0010_given_permutation/run.sh | 3 + .../0010_given_permutation/stdout.expected | 8 + .../permutation.essence | 8 + .../enum/0020_letting_permutation/run.sh | 3 + .../0020_letting_permutation/stdout.expected | 8 + .../0030_find_permutation/permutation.essence | 8 + .../enum/0030_find_permutation/run.sh | 3 + .../0030_find_permutation/stdout.expected | 8 + .../permutation.essence | 8 + .../0010_given_permutation/permutation.param | 2 + .../int/0010_given_permutation/run.sh | 3 + .../0010_given_permutation/stdout.expected | 8 + .../permutation.essence | 8 + .../int/0020_letting_permutation/run.sh | 3 + .../0020_letting_permutation/stdout.expected | 8 + .../0030_find_permutation/permutation.essence | 8 + .../int/0030_find_permutation/run.sh | 3 + .../int/0030_find_permutation/stdout.expected | 8 + .../14_image_sequence/runthese.sh | 1 + .../0030_find_permutation/permutation.essence | 8 + .../unnamed/0030_find_permutation/run.sh | 3 + .../0030_find_permutation/stdout.expected | 11 + 63 files changed, 369 insertions(+), 489 deletions(-) create mode 100644 tests/custom/permutations/13_image_function/enum/0010_given_permutation/permutation.essence create mode 100644 tests/custom/permutations/13_image_function/enum/0010_given_permutation/permutation.param create mode 100755 tests/custom/permutations/13_image_function/enum/0010_given_permutation/run.sh create mode 100644 tests/custom/permutations/13_image_function/enum/0010_given_permutation/stdout.expected create mode 100644 tests/custom/permutations/13_image_function/enum/0020_letting_permutation/permutation.essence create mode 100755 tests/custom/permutations/13_image_function/enum/0020_letting_permutation/run.sh create mode 100644 tests/custom/permutations/13_image_function/enum/0020_letting_permutation/stdout.expected create mode 100644 tests/custom/permutations/13_image_function/enum/0030_find_permutation/permutation.essence create mode 100755 tests/custom/permutations/13_image_function/enum/0030_find_permutation/run.sh create mode 100644 tests/custom/permutations/13_image_function/enum/0030_find_permutation/stdout.expected create mode 100644 tests/custom/permutations/13_image_function/int/0010_given_permutation/permutation.essence create mode 100644 tests/custom/permutations/13_image_function/int/0010_given_permutation/permutation.param create mode 100755 tests/custom/permutations/13_image_function/int/0010_given_permutation/run.sh create mode 100644 tests/custom/permutations/13_image_function/int/0010_given_permutation/stdout.expected create mode 100644 tests/custom/permutations/13_image_function/int/0020_letting_permutation/permutation.essence create mode 100755 tests/custom/permutations/13_image_function/int/0020_letting_permutation/run.sh create mode 100644 tests/custom/permutations/13_image_function/int/0020_letting_permutation/stdout.expected create mode 100644 tests/custom/permutations/13_image_function/int/0030_find_permutation/permutation.essence create mode 100755 tests/custom/permutations/13_image_function/int/0030_find_permutation/run.sh create mode 100644 tests/custom/permutations/13_image_function/int/0030_find_permutation/stdout.expected create mode 100644 tests/custom/permutations/13_image_function/runthese.sh create mode 100644 tests/custom/permutations/13_image_function/unnamed/0030_find_permutation/permutation.essence create mode 100755 tests/custom/permutations/13_image_function/unnamed/0030_find_permutation/run.sh create mode 100644 tests/custom/permutations/13_image_function/unnamed/0030_find_permutation/stdout.expected create mode 100644 tests/custom/permutations/14_image_sequence/enum/0010_given_permutation/permutation.essence create mode 100644 tests/custom/permutations/14_image_sequence/enum/0010_given_permutation/permutation.param create mode 100755 tests/custom/permutations/14_image_sequence/enum/0010_given_permutation/run.sh create mode 100644 tests/custom/permutations/14_image_sequence/enum/0010_given_permutation/stdout.expected create mode 100644 tests/custom/permutations/14_image_sequence/enum/0020_letting_permutation/permutation.essence create mode 100755 tests/custom/permutations/14_image_sequence/enum/0020_letting_permutation/run.sh create mode 100644 tests/custom/permutations/14_image_sequence/enum/0020_letting_permutation/stdout.expected create mode 100644 tests/custom/permutations/14_image_sequence/enum/0030_find_permutation/permutation.essence create mode 100755 tests/custom/permutations/14_image_sequence/enum/0030_find_permutation/run.sh create mode 100644 tests/custom/permutations/14_image_sequence/enum/0030_find_permutation/stdout.expected create mode 100644 tests/custom/permutations/14_image_sequence/int/0010_given_permutation/permutation.essence create mode 100644 tests/custom/permutations/14_image_sequence/int/0010_given_permutation/permutation.param create mode 100755 tests/custom/permutations/14_image_sequence/int/0010_given_permutation/run.sh create mode 100644 tests/custom/permutations/14_image_sequence/int/0010_given_permutation/stdout.expected create mode 100644 tests/custom/permutations/14_image_sequence/int/0020_letting_permutation/permutation.essence create mode 100755 tests/custom/permutations/14_image_sequence/int/0020_letting_permutation/run.sh create mode 100644 tests/custom/permutations/14_image_sequence/int/0020_letting_permutation/stdout.expected create mode 100644 tests/custom/permutations/14_image_sequence/int/0030_find_permutation/permutation.essence create mode 100755 tests/custom/permutations/14_image_sequence/int/0030_find_permutation/run.sh create mode 100644 tests/custom/permutations/14_image_sequence/int/0030_find_permutation/stdout.expected create mode 100644 tests/custom/permutations/14_image_sequence/runthese.sh create mode 100644 tests/custom/permutations/14_image_sequence/unnamed/0030_find_permutation/permutation.essence create mode 100755 tests/custom/permutations/14_image_sequence/unnamed/0030_find_permutation/run.sh create mode 100644 tests/custom/permutations/14_image_sequence/unnamed/0030_find_permutation/stdout.expected diff --git a/src/Conjure/Rules/Horizontal/Permutation.hs b/src/Conjure/Rules/Horizontal/Permutation.hs index 0d7fc1b61e..2884feebe2 100644 --- a/src/Conjure/Rules/Horizontal/Permutation.hs +++ b/src/Conjure/Rules/Horizontal/Permutation.hs @@ -2,7 +2,6 @@ module Conjure.Rules.Horizontal.Permutation where import Conjure.Rules.Import import Data.Permutation (size, fromCycles, toFunction) -import Conjure.Bug rule_Cardinality_Literal :: Rule @@ -35,12 +34,12 @@ rule_Equality = "permutation-equality" `namedRule` theRule where ) -rule_Permute_Comprehension_Tuples_Literal :: Rule -rule_Permute_Comprehension_Tuples_Literal = "permutation-comprehension-tuples{AsFunction}" `namedRule` theRule where +rule_Comprehension :: Rule +rule_Comprehension = "permutation-comprehension" `namedRule` theRule where theRule (Comprehension body gensOrConds) = do (gocBefore, (pat, perm), gocAfter) <- matchFirst gensOrConds $ \ goc -> case goc of Generator (GenInExpr pat [essence| &perm |] ) -> return (pat, perm) - _ -> na "rule_Comprehension_Tuples_Literal" + _ -> na "rule_Comprehension" (TypePermutation inner, elems) <- match permutationLiteral perm DomainPermutation _ _ innerD <- domainOf perm let f' = toFunction <$> fromCycles elems @@ -54,7 +53,7 @@ rule_Permute_Comprehension_Tuples_Literal = "permutation-comprehension-tuples{As | de <- join elems ] return - ( "Vertical rule for permutation-comprehension-tuples-literal" + ( "Vertical rule for permutation-comprehension" , do return $ Comprehension body $ gocBefore @@ -62,56 +61,7 @@ rule_Permute_Comprehension_Tuples_Literal = "permutation-comprehension-tuples{As ] ++ gocAfter ) - theRule _ = na "rule_Comprehension_Tuples_Literal" - -rule_Image_Literal_Find :: Rule -rule_Image_Literal_Find = "permutation-image-literal" `namedRule` theRule where - theRule [essence| image(&p, &i) |] = do - (TypePermutation inner, elems) <- match permutationLiteral p - DomainPermutation _ _ innerP <- domainOf p - let f' = toFunction <$> fromCycles elems - case f' of - Left er -> fail $ "Permutation literal invalid." <++> stringToDoc (show er) - Right f -> do - let outLiteral = make matrixLiteral - (TypeMatrix (TypeInt AnyTag) (TypeTuple [inner,inner])) innerP - [ AbstractLiteral (AbsLitTuple [de - ,f de]) - | de <- join elems - ] - typeI <- typeOf i - if typesUnify [inner, typeI] - then do - innerD <- domainOf i - return - ( "Horizontal rule for permutation literal application to a single value (image), AsFunction representation" - , do - (hName, h) <- auxiliaryVar - (fPat, f) <- quantifiedVar - (tPat, t) <- quantifiedVar - (gPat, g) <- quantifiedVar - (ePat, _) <- quantifiedVar - return $ WithLocals - [essence| &h |] - (AuxiliaryVars - [ Declaration (FindOrGiven LocalFind hName innerD) - , SuchThat - [ [essence| - (forAll (&fPat, &tPat) in &outLiteral . &f = &i <-> &h = &t) - /\ (!(exists (&gPat, &ePat) in &outLiteral . &g = &h) <-> &h = &i) - |] - ] - ] - ) - ) - else if typeI `containsType` inner - then na "rule_Image_Literal" - else return ( "Horizontal rule for permutation application to a type the permutation doesn't care about" - , do - return [essence| &i |] - ) - theRule _ = na "rule_Image_Literal" - + theRule _ = na "rule_Comprehension" rule_Image_Literal :: Rule rule_Image_Literal = "permutation-image-literal" `namedRule` theRule where @@ -138,39 +88,6 @@ rule_Image_Literal = "permutation-image-literal" `namedRule` theRule where ) theRule _ = na "rule_Image_Literal" -rule_Image_Literal_Comprehension :: Rule -rule_Image_Literal_Comprehension = "permutation-image-literal-comprehension" `namedRule` theRule where - theRule (Comprehension body gensOrConds) = do - (gocBefore, (pat, p, i), gocAfter) <- matchFirst gensOrConds $ \ goc -> case goc of - Generator (GenInExpr pat [essence| image(&p, &i) |]) -> return (pat, p, i) - _ -> na "rule_Image_Literal_Comprehension" - (TypePermutation inner, elems) <- match permutationLiteral p - let f' = toFunction <$> fromCycles elems - case f' of - Left er -> fail $ "Permutation literal invalid." <++> stringToDoc (show er) - Right f -> do - typeI <- typeOf i - if typesUnify [inner, typeI] - then do - let outLiteral = make functionLiteral (TypeFunction inner inner) [ (de,f de) | de <- join elems ] - return - ( "Horizontal rule for permutation literal application to a single value (image), AsFunction representation" - , do - return $ Comprehension body $ gocBefore - ++ [ Generator (GenInExpr pat [essence| [&i, catchUndef(image(&outLiteral,&i),0)][toInt(&i in defined(&outLiteral))+1] |]) - ] ++ gocAfter - ) - else if typeI `containsType` inner - then na "rule_Image_Literal_Comprehension" - else return ( "Horizontal rule for permutation application to a type the permutation doesn't care about" - , do - return $ Comprehension body $ gocBefore - ++ [ Generator (GenInExpr pat [essence| &i |]) ] - ++ gocAfter - ) - theRule _ = na "rule_Image_Literal_Comprehension" - - rule_In :: Rule rule_In = "permutation-in" `namedRule` theRule where @@ -212,7 +129,7 @@ rule_Compose_Image :: Rule rule_Compose_Image = "permutation-compose-image" `namedRule` theRule where theRule [essence| image(compose(&g, &h),&i) |] = do case match permutationLiteral h of - Nothing -> return () -- This rule + rule_Image_Literal makes SR explode + Nothing -> return () --SR error when h is literal, fall back to rule_Compose Just _ -> na "rule_Compose_Image" TypePermutation innerG <- typeOf g TypePermutation innerH <- typeOf g @@ -227,9 +144,6 @@ rule_Compose_Image = "permutation-compose-image" `namedRule` theRule where theRule _ = na "rule_Compose_Image" --- This isn't great but handles the literal case rule_Compose_Image fails on --- TODO would be nice to be able to compose permutations without having to --- introduce auxiliary variables - this is a slow way to go rule_Compose :: Rule rule_Compose = "permutation-compose" `namedRule` theRule where theRule [essence| compose(&g,&h) |] = do @@ -269,6 +183,7 @@ rule_Image_Comprehendable = "comprehendable-image" `namedRule` theRule where _ -> na "rule_Image_Comprehendable" (perm, y) <- match opImage x ty <- typeOf y + case ty of TypeSequence{} -> na "sequence is a special case" ; _ -> return () (TypePermutation inn) <- typeOf perm if ty `containsTypeComprehendable` inn then do @@ -286,6 +201,59 @@ rule_Image_Comprehendable = "comprehendable-image" `namedRule` theRule where else na "rule_Image_Comprehendable" theRule _ = na "rule_Image_Comprehendable" +rule_Image_Sequence :: Rule +rule_Image_Sequence = "image-sequence" `namedRule` theRule where + theRule (Comprehension body gensOrConds) = do + (gocBefore, (pat, x), gocAfter) <- matchFirst gensOrConds $ \ goc -> case goc of + Generator (GenInExpr (Single pat) expr) -> return (pat, matchDefs [opToSet, opToMSet] expr) + _ -> na "rule_Image_Sequence" + (perm, y) <- match opImage x + ty <- typeOf y + case ty of TypeSequence{} -> return () ; _ -> na "only applies to sequences" + (TypePermutation inn) <- typeOf perm + if ty `containsTypeComprehendable` inn + then do + return + ( "Horizontal rule for image of sequence under permutation" + , do + (dPat, d) <- quantifiedVar + return (Comprehension body $ + gocBefore + ++ [Generator (GenInExpr dPat [essence| &y |])] + ++ ((ComprehensionLetting pat [essence| (&d[1],image(&perm, &d[2])) |] ):gocAfter) + ) + + ) + else na "rule_Image_Sequence" + theRule _ = na "rule_Image_Sequence" + + +rule_Image_Sequence_Defined :: Rule +rule_Image_Sequence_Defined = "image-sequence-defined" `namedRule` theRule where + theRule (Comprehension body gensOrConds) = do + (gocBefore, (pat, x), gocAfter) <- matchFirst gensOrConds $ \ goc -> case goc of + Generator (GenInExpr pat@Single{} expr) -> return (pat, matchDefs [opToSet, opToMSet] expr) + _ -> na "rule_Image_Sequence_Defined" + defi <- match opDefined x + (perm, y) <- match opImage defi + ty <- typeOf y + case ty of TypeSequence{} -> return () ; _ -> na "only applies to sequences" + (TypePermutation inn) <- typeOf perm + if ty `containsTypeComprehendable` inn + then do + return + ( "Horizontal rule for image of sequence defined under permutation" + , do + return (Comprehension body $ + gocBefore + ++ [Generator (GenInExpr pat [essence| defined(&y) |])] + ++ gocAfter + ) + ) + else na "rule_Image_Sequence_Defined" + theRule _ = na "rule_Image_Sequence_Defined" + + rule_Image_Incomprehendable :: Rule rule_Image_Incomprehendable = "comprehendable-image" `namedRule` theRule where diff --git a/src/Conjure/Rules/Horizontal/Sequence.hs b/src/Conjure/Rules/Horizontal/Sequence.hs index 512f7d1880..c90c334b1c 100644 --- a/src/Conjure/Rules/Horizontal/Sequence.hs +++ b/src/Conjure/Rules/Horizontal/Sequence.hs @@ -457,7 +457,7 @@ rule_Image_Int = "sequence-image-int" `namedRule` theRule where ( "Sequence image, int." , do (iPat, i) <- quantifiedVar - let val = make opSum $ Comprehension [essence| &i[2] |] + let val = make opSum $ reTag AnyTag $ Comprehension [essence| &i[2] |] [ Generator (GenInExpr iPat func) , Condition [essence| &i[1] = &arg |] ] diff --git a/src/Conjure/Rules/Vertical/Permutation.hs b/src/Conjure/Rules/Vertical/Permutation.hs index f2d85f0f49..6a5e6bb031 100644 --- a/src/Conjure/Rules/Vertical/Permutation.hs +++ b/src/Conjure/Rules/Vertical/Permutation.hs @@ -1,14 +1,11 @@ {-# LANGUAGE QuasiQuotes #-} - module Conjure.Rules.Vertical.Permutation where - import Conjure.Rules.Import -import Conjure.Rules.Vertical.Matrix (flattenIfNeeded) rule_Cardinality :: Rule rule_Cardinality = "permutation-cardinality" `namedRule` theRule where - theRule p = do - p <- match opTwoBars p + theRule po = do + p <- match opTwoBars po TypePermutation{} <- typeOf p Permutation_AsFunction <- representationOf p DomainPermutation _ _ innerDom <- domainOf p @@ -17,16 +14,17 @@ rule_Cardinality = "permutation-cardinality" `namedRule` theRule where ( "Vertical rule for permutation cardinality, AsFunction representation." , do (iPat, i) <- quantifiedVarOverDomain (forgetRepr innerDom) - return $ reTag AnyTag $ [essence| |&fun| |] + return $ reTag AnyTag $ [essence| + sum([ toInt(&i != image(&fun, &i)) | &iPat : &innerDom ]) + |] ) rule_Defined :: Rule rule_Defined = "permutation-defined" `namedRule` theRule where - theRule p = do - p <- match opDefined p + theRule po = do + p <- match opDefined po TypePermutation{} <- typeOf p Permutation_AsFunction <- representationOf p - DomainPermutation _ _ innerDom <- domainOf p [fun] <- downX1 p return ( "Vertical rule for permutation defined, AsFunction representation." @@ -36,8 +34,8 @@ rule_Defined = "permutation-defined" `namedRule` theRule where -rule_Permute_Comprehension_Tuples :: Rule -rule_Permute_Comprehension_Tuples = "permutation-comprehension-tuples{AsFunction}" `namedRule` theRule where +rule_Comprehension :: Rule +rule_Comprehension = "permutation-comprehension-tuples{AsFunction}" `namedRule` theRule where theRule (Comprehension body gensOrConds) = do (gocBefore, (pat, perm), gocAfter) <- matchFirst gensOrConds $ \ goc -> case goc of Generator (GenInExpr pat [essence| &perm |] ) -> return (pat, perm) @@ -46,7 +44,7 @@ rule_Permute_Comprehension_Tuples = "permutation-comprehension-tuples{AsFunction Permutation_AsFunction <- representationOf perm [f] <- downX1 perm return - ( "Vertical rule for permutation-comprehension-tuples, AsFunction representation" + ( "Vertical rule for permutation-comprehension" , do (lPat, l) <- quantifiedVar (rPat, r) <- quantifiedVar @@ -86,356 +84,3 @@ rule_Image = "permutation-image{AsFunction}" `namedRule` theRule where --- --- ---rule_Permutation_Inverse :: Rule ---rule_Permutation_Inverse = "permutation-inverse{AsFunction}" `namedRule` theRule where --- theRule [essence| inverse(&p1, &p2)|] = do --- TypePermutation{} <- typeOf p1 --- Permutation_AsFunction <- representationOf p1 --- TypePermutation{} <- typeOf p2 --- Permutation_AsFunction <- representationOf p2 --- [f1] <- downX1 p2 --- [f2] <- downX1 p2 --- return --- ( "Vertical rule for permutation-inverse, AsFunction representation" --- , return [essence| inverse(&f1, &f2) |] --- ) --- theRule _ = na "rule_Permutation_Equality" --- --- ---rule_Permutation_Inverse_Comprehension :: Rule ---rule_Permutation_Inverse_Comprehension = "permutation-inverse-comprehension{AsFunction}" `namedRule` theRule where --- theRule (Comprehension body gensOrConds) = do --- (gocBefore, (pat, p1, p2), gocAfter) <- matchFirst gensOrConds $ \ goc -> case goc of --- Generator (GenInExpr pat [essence| inverse(&p1, &p2)|] ) -> return (pat, p1, p2) --- _ -> na "rule_Inverse_Comprehension" --- TypePermutation{} <- typeOf p1 --- Permutation_AsFunction <- representationOf p1 --- TypePermutation{} <- typeOf p2 --- Permutation_AsFunction <- representationOf p2 --- [f1] <- downX1 p2 --- [f2] <- downX1 p2 --- return --- ( "Vertical rule for permutation-inverse-comprehension, AsFunction representation" --- , do --- return $ Comprehension body --- $ gocBefore --- ++ [ Generator (GenInExpr pat [essence| inverse(&f1, &f2) |]) --- ] --- ++ gocAfter --- ) --- theRule _ = na "rule_Permutation_Inverse_Comprehension" --- --- --- ---rule_Permutation_Equality :: Rule ---rule_Permutation_Equality = "permutation-equality{AsFunction}" `namedRule` theRule where --- theRule [essence| &p1 = &p2|] = do --- TypePermutation{} <- typeOf p1 --- Permutation_AsFunction <- representationOf p1 --- TypePermutation{} <- typeOf p2 --- Permutation_AsFunction <- representationOf p2 --- [f1] <- downX1 p2 --- [f2] <- downX1 p2 --- return --- ( "Vertical rule for permutation-equality, AsFunction representation" --- , return [essence| &f1 = &f2 |] --- ) --- theRule _ = na "rule_Permutation_Equality" --- --- ---rule_Permutation_Equality_Comprehension :: Rule ---rule_Permutation_Equality_Comprehension = "permutation-equality-comprehension{AsFunction}" `namedRule` theRule where --- theRule (Comprehension body gensOrConds) = do --- (gocBefore, (pat, p1, p2), gocAfter) <- matchFirst gensOrConds $ \ goc -> case goc of --- Generator (GenInExpr pat [essence| &p1 = &p2|] ) -> return (pat, p1, p2) --- _ -> na "rule_Comprehension" --- TypePermutation{} <- typeOf p1 --- Permutation_AsFunction <- representationOf p1 --- TypePermutation{} <- typeOf p2 --- Permutation_AsFunction <- representationOf p2 --- [f1] <- downX1 p2 --- [f2] <- downX1 p2 --- return --- ( "Vertical rule for permutation-equality-comprehension, AsFunction representation" --- , do --- return $ Comprehension body --- $ gocBefore --- ++ [ Generator (GenInExpr pat [essence| &f1 = &f2 |]) --- ] --- ++ gocAfter --- ) --- theRule _ = na "rule_Permutation_Equality_Comprehension" - --- ---rule_Permute_Comprehension :: Rule ---rule_Permute_Comprehension = "permutation-image{AsFunction}" `namedRule` theRule where --- theRule (Comprehension body gensOrConds) = do --- (gocBefore, (pat, p, i), gocAfter) <- matchFirst gensOrConds $ \ goc -> case goc of --- Generator (GenInExpr pat [essence| image(&p, &i) |]) -> return (pat, p, i) --- _ -> na "rule_Comprehension" --- --- TypePermutation inner <- typeOf p --- typeI <- typeOf i --- if typeI `containsType` inner --- then do --- [f] <- downX1 p --- if typesUnify [inner, typeI] --- then return --- ( "Vertical rule for permutation application to a single value" --- , return --- (Comprehension body $ gocBefore --- ++ [Generator (GenInExpr pat --- [essence| [&i, catchUndef(image(&f,&i),0)][toInt(&i in defined(&f))+1] |])] --- ++ gocAfter) --- ) --- else na "rule_Permute" --- else return --- ( "Vertical rule for permutation application to a type the permutation doesn't care about" --- , return --- (Comprehension body $ gocBefore --- ++ [Generator (GenInExpr pat [essence| &i |])] --- ++ gocAfter) --- ) --- theRule _ = na "rule_Permute" --- ---rule_Matrix_Permute :: Rule ---rule_Matrix_Permute = "matrix-image" `namedRule` theRule where --- theRule [essence| image(&perm, &y) |] = do --- ty@(TypeMatrix _ _) <- typeOf y --- (TypePermutation inn) <- typeOf perm --- if not $ typesUnify [ty, inn] --- then do --- unless (isPrimitiveType ty) $ fail ("not a primitive type:" <+> pretty ty) --- y' <- flattenIfNeeded y --- dm@(DomainMatrix dyindex _) <- domainOf y' --- return --- ( "Horizontal rule for image matrix" --- , do --- (dPat, d) <- quantifiedVar --- (pyName, py) <- auxiliaryVar --- return $ WithLocals --- [essence| &py |] --- (AuxiliaryVars --- [ Declaration (FindOrGiven LocalFind pyName dm) --- , SuchThat --- [ [essence| --- forAll &dPat : &dyindex . --- &py[image(&perm,&d)] = image(&perm,&y'[&d]) --- |] --- ] --- ] --- ) --- ) --- else na "rule_Matrix_Permute" --- theRule _ = na "rule_Matrix_Permute" --- ---rule_Matrix_Permute_Comprehension :: Rule ---rule_Matrix_Permute_Comprehension = "matrix-image-comprehension" `namedRule` theRule where --- theRule (Comprehension body gensOrConds) = do --- (gocBefore, (pat, perm, y), gocAfter) <- matchFirst gensOrConds $ \ goc -> case goc of --- Generator (GenInExpr pat [essence| image(&perm, &y) |]) -> return (pat, perm, y) --- _ -> na "rule_Matrix_Permute" --- ty@(TypeMatrix _ _) <- typeOf y --- (TypePermutation inn) <- typeOf perm --- if not $ typesUnify [ty, inn] --- then do --- unless (isPrimitiveType ty) $ fail ("not a primitive type:" <+> pretty ty) --- y' <- flattenIfNeeded y --- dm@(DomainMatrix dyindex _) <- domainOf y' --- return --- ( "Horizontal rule for image matrix in comprehension" --- , do --- (dPat, d) <- quantifiedVar --- (pyName, py) <- auxiliaryVar --- return $ WithLocals --- (Comprehension body $ gocBefore --- ++ [Generator (GenInExpr pat [essence| &py |])] --- ++ gocAfter) --- (AuxiliaryVars --- [ Declaration (FindOrGiven LocalFind pyName dm) --- , SuchThat --- [ [essence| --- forAll &dPat : &dyindex . --- &py[image(&perm,&d)] = image(&perm,&y'[&d]) --- |] --- ] --- ] --- ) --- ) --- else na "rule_Matrix_Permute_Comprehension" --- theRule _ = na "rule_Matrix_Permute_Comprehension" --- ---rule_Set_Permute :: Rule ---rule_Set_Permute = "set-image" `namedRule` theRule where --- theRule (Comprehension body gensOrConds) = do --- (gocBefore, (pat, perm, y), gocAfter) <- matchFirst gensOrConds $ \ goc -> case goc of --- Generator (GenInExpr pat [essence| image(&perm, &y) |]) -> return (pat, perm, y) --- _ -> na "rule_Set_Permute" --- ts@(TypeSet _) <- typeOf y --- (TypePermutation inn) <- typeOf perm --- if not $ typesUnify [ts, inn] --- then do --- ds <- domainOf y --- return --- ( "Horizontal rule for image set" --- , do --- (dPat, d) <- quantifiedVar --- (pyName, py) <- auxiliaryVar --- return $ WithLocals --- (Comprehension body $ gocBefore --- ++ [Generator (GenInExpr pat [essence| &py |])] --- ++ gocAfter) --- (AuxiliaryVars --- [ Declaration (FindOrGiven LocalFind pyName ds) --- , SuchThat --- [ [essence| --- |&y| = |&py| --- /\ forAll &dPat in &y . --- image(&perm, &d) in &py --- |] --- ] --- ] --- ) --- ) --- else na "rule_Set_Permute" --- theRule _ = na "rule_Set_Permute" --- --- ---rule_Relation_Permute :: Rule ---rule_Relation_Permute = "relation-image" `namedRule` theRule where --- theRule [essence| image(&perm, &y) |] = do --- case y of WithLocals{} -> na "bubble-delay" ; _ -> return () --- ts@(TypeRelation _) <- typeOf y --- (TypePermutation inn) <- typeOf perm --- if not $ typesUnify [ts, inn] --- then do --- ds <- domainOf y --- return --- ( "Horizontal rule for image relation in comprehension" --- , do --- (dPat, d) <- quantifiedVar --- (pyName, py) <- auxiliaryVar --- return $ WithLocals --- [essence| &py |] --- (AuxiliaryVars --- [ Declaration (FindOrGiven LocalFind pyName ds) --- , SuchThat --- [ [essence| --- |&y| = |&py| --- /\ and([image(&perm, &d) in &py | &dPat <- &y]) --- --- |] --- ] --- ] --- ) --- ) --- else na "rule_Relation_Permute" --- theRule _ = na "rule_Relation_Permute" --- ---rule_Relation_Permute_Comprehension :: Rule ---rule_Relation_Permute_Comprehension = "relation-image-comprehension" `namedRule` theRule where --- theRule (Comprehension body gensOrConds) = do --- (gocBefore, (pat, perm, y), gocAfter) <- matchFirst gensOrConds $ \ goc -> case goc of --- Generator (GenInExpr pat [essence| image(&perm, &y) |]) -> return (pat, perm, y) --- _ -> na "rule_Relation_Permute_Comprehension" --- case y of WithLocals{} -> na "bubble-delay" ; _ -> return () --- ts@(TypeRelation _) <- typeOf y --- (TypePermutation inn) <- typeOf perm --- if not $ typesUnify [ts, inn] --- then do --- ds <- domainOf y --- return --- ( "Horizontal rule for image relation in comprehension" --- , do --- (dPat, d) <- quantifiedVar --- (pyName, py) <- auxiliaryVar --- return $ WithLocals --- (Comprehension body $ gocBefore --- ++ [Generator (GenInExpr pat [essence| &py |])] --- ++ gocAfter) --- (AuxiliaryVars --- [ Declaration (FindOrGiven LocalFind pyName ds) --- , SuchThat --- [ [essence| --- |&y| = |&py| --- /\ and([image(&perm, &d) in &py | &dPat <- &y]) --- |] --- ] --- ] --- ) --- ) --- else na "rule_Relation_Permute_Comprehension" --- theRule _ = na "rule_Relation_Permute_Comprehension" --- --- ---rule_Tuple_Permute :: Rule ---rule_Tuple_Permute = "tuple-image" `namedRule` theRule where --- theRule [essence| image(&perm, &y) |] = do --- case y of WithLocals{} -> na "bubble-delay" ; _ -> return () --- ty' <- typeOf y ----- traceM $ "rule_Tuple_Permute: " ++ show ty' --- ty@(TypeTuple it) <- typeOf y --- (TypePermutation inn) <- typeOf perm --- if not $ typesUnify [ty, inn] --- then do ----- traceM $ "rule_Tuple_Permute: applying" --- dm <- domainOf y --- return --- ( "Horizontal rule for image tuple in comprehension" --- , do --- (pyName, py) <- auxiliaryVar --- return $ WithLocals --- [essence| &py |] --- (AuxiliaryVars $ --- [ Declaration (FindOrGiven LocalFind pyName dm)] --- ++ ((\x -> let d = Constant $ ConstantInt NoTag x --- in SuchThat [[essence| &py[&d] = image(&perm,&y[&d]) |] ]) --- <$> [1..(genericLength it)]) --- --- --- ) --- ) --- else na "rule_Tuple_Permute" --- theRule _ = na "rule_Tuple_Permute" --- ---rule_Tuple_Permute_Comprehension :: Rule ---rule_Tuple_Permute_Comprehension = "tuple-image-comprehension" `namedRule` theRule where --- theRule (Comprehension body gensOrConds) = do --- (gocBefore, (pat, perm, y), gocAfter) <- matchFirst gensOrConds $ \ goc -> case goc of --- Generator (GenInExpr pat [essence| image(&perm, &y) |]) -> return (pat, perm, y) --- _ -> na "rule_Tuple_Permute" --- case y of WithLocals{} -> na "bubble-delay" ; _ -> return () --- ty' <- typeOf y ----- traceM $ "rule_Tuple_Permute_Comprehension: " ++ show ty' --- ty@(TypeTuple it) <- typeOf y --- (TypePermutation inn) <- typeOf perm --- if not $ typesUnify [ty, inn] --- then do ----- traceM $ "rule_Tuple_Permute_Comprehension: applying" --- dm <- domainOf y --- return --- ( "Horizontal rule for image tuple in comprehension" --- , do --- (pyName, py) <- auxiliaryVar --- return $ WithLocals --- (Comprehension body $ gocBefore --- ++ [Generator (GenInExpr pat [essence| &py |])] --- ++ gocAfter) --- (AuxiliaryVars $ --- [ Declaration (FindOrGiven LocalFind pyName dm)] --- ++ ((\x -> let d = Constant $ ConstantInt NoTag x --- in SuchThat [[essence| &py[&d] = image(&perm,&y[&d]) |] ]) --- <$> [1..(genericLength it)]) --- ) --- ) --- else na "rule_Tuple_Permute_Comprehension" --- theRule _ = na "rule_Tuple_Permute_Comprehension" --- - - ---rule_Function_Permute :: Rule ---rule_Partition_Permute :: Rule ---rule_MSet_Permute :: Rule ---rule_Sequence_Permute :: Rule diff --git a/src/Conjure/UI/Model.hs b/src/Conjure/UI/Model.hs index 92264b3b50..c421f002cc 100644 --- a/src/Conjure/UI/Model.hs +++ b/src/Conjure/UI/Model.hs @@ -1088,19 +1088,9 @@ paramRules = verticalRules :: [Rule] verticalRules = [ Vertical.Permutation.rule_Image --- , Vertical.Permutation.rule_Permute_Comprehension , Vertical.Permutation.rule_Cardinality , Vertical.Permutation.rule_Defined - , Vertical.Permutation.rule_Permute_Comprehension_Tuples --- , Vertical.Permutation.rule_Permutation_Equality --- , Vertical.Permutation.rule_Permutation_Equality_Comprehension --- , Vertical.Permutation.rule_Relation_Permute --- , Vertical.Permutation.rule_Relation_Permute_Comprehension --- , Vertical.Permutation.rule_Set_Permute --- , Vertical.Permutation.rule_Tuple_Permute --- , Vertical.Permutation.rule_Tuple_Permute_Comprehension --- , Vertical.Permutation.rule_Matrix_Permute --- , Vertical.Permutation.rule_Matrix_Permute_Comprehension + , Vertical.Permutation.rule_Comprehension , Vertical.Tuple.rule_Tuple_Eq , Vertical.Tuple.rule_Tuple_Neq @@ -1212,17 +1202,16 @@ horizontalRules :: [Rule] horizontalRules = [ Horizontal.Permutation.rule_Cardinality_Literal , Horizontal.Permutation.rule_Equality - , Horizontal.Permutation.rule_Permute_Comprehension_Tuples_Literal + , Horizontal.Permutation.rule_Comprehension , Horizontal.Permutation.rule_Compose_Image , Horizontal.Permutation.rule_Compose , Horizontal.Permutation.rule_Image_Literal --- , Horizontal.Permutation.rule_Image_Literal_Comprehension --- , Horizontal.Permutation.rule_Image_Literal_Find + , Horizontal.Permutation.rule_Image_Sequence + , Horizontal.Permutation.rule_Image_Sequence_Defined , Horizontal.Permutation.rule_In , Horizontal.Permutation.rule_Permutation_Inverse , Horizontal.Permutation.rule_Image_Comprehendable , Horizontal.Permutation.rule_Image_Incomprehendable --- , Horizontal.Permutation.rule_Image_Literal_Comprehension diff --git a/tests/custom/permutations/01_representation/runthese.sh b/tests/custom/permutations/01_representation/runthese.sh index 4682c19d59..1cc0572a12 100644 --- a/tests/custom/permutations/01_representation/runthese.sh +++ b/tests/custom/permutations/01_representation/runthese.sh @@ -1 +1 @@ -stack test --test-arguments "-p custom.permutations.01_representation" +stack build --copy-bins --test --test-arguments "-p custom.permutations.01_representation" diff --git a/tests/custom/permutations/02_cardinality/enum/0001_given_permutation_in_param/stdout.expected b/tests/custom/permutations/02_cardinality/enum/0001_given_permutation_in_param/stdout.expected index 0165072a84..d20985577b 100644 --- a/tests/custom/permutations/02_cardinality/enum/0001_given_permutation_in_param/stdout.expected +++ b/tests/custom/permutations/02_cardinality/enum/0001_given_permutation_in_param/stdout.expected @@ -5,4 +5,4 @@ Savile Row: model000001.eprime permutation.param Copying solution to: permutation-permutation.solution language Essence 1.3 -letting i be 4 +letting i be 3 diff --git a/tests/custom/permutations/02_cardinality/enum/0003_find_permutation/stdout.expected b/tests/custom/permutations/02_cardinality/enum/0003_find_permutation/stdout.expected index 68ac740d13..4e026e23dd 100644 --- a/tests/custom/permutations/02_cardinality/enum/0003_find_permutation/stdout.expected +++ b/tests/custom/permutations/02_cardinality/enum/0003_find_permutation/stdout.expected @@ -5,5 +5,5 @@ Savile Row: model000001.eprime Copying solution to: permutation.solution language Essence 1.3 -letting i be 6 +letting i be 4 letting p be permutation((E3, E4), (E5, E6)) diff --git a/tests/custom/permutations/02_cardinality/int/0001_given_permutation_in_param/stdout.expected b/tests/custom/permutations/02_cardinality/int/0001_given_permutation_in_param/stdout.expected index 0165072a84..d20985577b 100644 --- a/tests/custom/permutations/02_cardinality/int/0001_given_permutation_in_param/stdout.expected +++ b/tests/custom/permutations/02_cardinality/int/0001_given_permutation_in_param/stdout.expected @@ -5,4 +5,4 @@ Savile Row: model000001.eprime permutation.param Copying solution to: permutation-permutation.solution language Essence 1.3 -letting i be 4 +letting i be 3 diff --git a/tests/custom/permutations/02_cardinality/int/0003_find_permutation/stdout.expected b/tests/custom/permutations/02_cardinality/int/0003_find_permutation/stdout.expected index adb884d68a..8030f81a88 100644 --- a/tests/custom/permutations/02_cardinality/int/0003_find_permutation/stdout.expected +++ b/tests/custom/permutations/02_cardinality/int/0003_find_permutation/stdout.expected @@ -5,5 +5,5 @@ Savile Row: model000001.eprime Copying solution to: permutation.solution language Essence 1.3 -letting i be 6 +letting i be 4 letting p be permutation((3, 4), (5, 6)) diff --git a/tests/custom/permutations/02_cardinality/unnamed/0003_find_permutation/stdout.expected b/tests/custom/permutations/02_cardinality/unnamed/0003_find_permutation/stdout.expected index f14be02e29..08c17fa62d 100644 --- a/tests/custom/permutations/02_cardinality/unnamed/0003_find_permutation/stdout.expected +++ b/tests/custom/permutations/02_cardinality/unnamed/0003_find_permutation/stdout.expected @@ -6,5 +6,5 @@ Copying solution to: permutation.solution language Essence 1.3 letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6} -letting i be 6 +letting i be 4 letting p be permutation((n_3, n_4), (n_5, n_6)) diff --git a/tests/custom/permutations/03_generators/runthese.sh b/tests/custom/permutations/03_generators/runthese.sh index 3e52ea37a4..953e3eacd0 100644 --- a/tests/custom/permutations/03_generators/runthese.sh +++ b/tests/custom/permutations/03_generators/runthese.sh @@ -1,2 +1 @@ -stack install -stack test --test-arguments "-p custom.permutations.03_generators" +stack build --copy-bins --test --test-arguments "-p custom.permutations.03_generators" diff --git a/tests/custom/permutations/05_equality/runthese.sh b/tests/custom/permutations/05_equality/runthese.sh index fe88c0e1a7..1c9834ccee 100644 --- a/tests/custom/permutations/05_equality/runthese.sh +++ b/tests/custom/permutations/05_equality/runthese.sh @@ -1,2 +1 @@ -stack install -stack test --test-arguments "-p custom.permutations.05_equality" +stack build --copy-bins --test --test-arguments "-p custom.permutations.05_equality" diff --git a/tests/custom/permutations/06_inverse/runthese.sh b/tests/custom/permutations/06_inverse/runthese.sh index 7a109bc890..1048702814 100644 --- a/tests/custom/permutations/06_inverse/runthese.sh +++ b/tests/custom/permutations/06_inverse/runthese.sh @@ -1,2 +1 @@ -stack install -stack test --test-arguments "-p custom.permutations.06_inverse" +stack build --copy-bins --test --test-arguments "-p custom.permutations.06_inverse" diff --git a/tests/custom/permutations/08_image_set/runthese.sh b/tests/custom/permutations/08_image_set/runthese.sh index 3e9eeed3ec..ca3f96bc20 100644 --- a/tests/custom/permutations/08_image_set/runthese.sh +++ b/tests/custom/permutations/08_image_set/runthese.sh @@ -1,2 +1 @@ -stack install -stack test --test-arguments "-p custom.permutations.08_image_set" +stack build --copy-bins --test --test-arguments "-p custom.permutations.08_image_set" diff --git a/tests/custom/permutations/11_image_relation/runthese.sh b/tests/custom/permutations/11_image_relation/runthese.sh index 1622b0171a..26a4fa606f 100644 --- a/tests/custom/permutations/11_image_relation/runthese.sh +++ b/tests/custom/permutations/11_image_relation/runthese.sh @@ -1,2 +1 @@ -stack install -stack test --test-arguments "-p custom.permutations.11_image_relation" +stack build --copy-bins --test --test-arguments "-p custom.permutations.11_image_relation" diff --git a/tests/custom/permutations/13_image_function/enum/0010_given_permutation/permutation.essence b/tests/custom/permutations/13_image_function/enum/0010_given_permutation/permutation.essence new file mode 100644 index 0000000000..c0e5a90e9d --- /dev/null +++ b/tests/custom/permutations/13_image_function/enum/0010_given_permutation/permutation.essence @@ -0,0 +1,8 @@ +letting n be new type enum {E1,E2,E3,E4} + +given p : permutation of n +letting f be function(E1-->E2, E2-->E3) +find g : function n --> n + +such that g = image(p,f) + diff --git a/tests/custom/permutations/13_image_function/enum/0010_given_permutation/permutation.param b/tests/custom/permutations/13_image_function/enum/0010_given_permutation/permutation.param new file mode 100644 index 0000000000..c7d9c37d25 --- /dev/null +++ b/tests/custom/permutations/13_image_function/enum/0010_given_permutation/permutation.param @@ -0,0 +1,2 @@ +letting p be permutation((E2,E4)) + diff --git a/tests/custom/permutations/13_image_function/enum/0010_given_permutation/run.sh b/tests/custom/permutations/13_image_function/enum/0010_given_permutation/run.sh new file mode 100755 index 0000000000..9dc67e67f5 --- /dev/null +++ b/tests/custom/permutations/13_image_function/enum/0010_given_permutation/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence *.param +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/13_image_function/enum/0010_given_permutation/stdout.expected b/tests/custom/permutations/13_image_function/enum/0010_given_permutation/stdout.expected new file mode 100644 index 0000000000..a37bad006e --- /dev/null +++ b/tests/custom/permutations/13_image_function/enum/0010_given_permutation/stdout.expected @@ -0,0 +1,8 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime permutation.param +Copying solution to: permutation-permutation.solution +language Essence 1.3 + +letting g be function(E1 --> E4, E4 --> E3) diff --git a/tests/custom/permutations/13_image_function/enum/0020_letting_permutation/permutation.essence b/tests/custom/permutations/13_image_function/enum/0020_letting_permutation/permutation.essence new file mode 100644 index 0000000000..f92e6054c6 --- /dev/null +++ b/tests/custom/permutations/13_image_function/enum/0020_letting_permutation/permutation.essence @@ -0,0 +1,8 @@ +letting n be new type enum {E1,E2,E3,E4} + +letting p be permutation((E2,E3)) +letting f be function(E1-->E2, E2-->E4) +find g : function n --> n + +such that g = image(p,f) + diff --git a/tests/custom/permutations/13_image_function/enum/0020_letting_permutation/run.sh b/tests/custom/permutations/13_image_function/enum/0020_letting_permutation/run.sh new file mode 100755 index 0000000000..b4899d6266 --- /dev/null +++ b/tests/custom/permutations/13_image_function/enum/0020_letting_permutation/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/13_image_function/enum/0020_letting_permutation/stdout.expected b/tests/custom/permutations/13_image_function/enum/0020_letting_permutation/stdout.expected new file mode 100644 index 0000000000..9910fdd1d7 --- /dev/null +++ b/tests/custom/permutations/13_image_function/enum/0020_letting_permutation/stdout.expected @@ -0,0 +1,8 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Copying solution to: permutation.solution +language Essence 1.3 + +letting g be function(E1 --> E3, E3 --> E4) diff --git a/tests/custom/permutations/13_image_function/enum/0030_find_permutation/permutation.essence b/tests/custom/permutations/13_image_function/enum/0030_find_permutation/permutation.essence new file mode 100644 index 0000000000..7e7c9c3dc6 --- /dev/null +++ b/tests/custom/permutations/13_image_function/enum/0030_find_permutation/permutation.essence @@ -0,0 +1,8 @@ +letting n be new type enum {E1,E2,E3,E4} + +find p : permutation of n +letting f be function(E1-->E2,E2-->E4) +letting g be function(E1-->E3,E3-->E4) + +such that g = image(p,f) + diff --git a/tests/custom/permutations/13_image_function/enum/0030_find_permutation/run.sh b/tests/custom/permutations/13_image_function/enum/0030_find_permutation/run.sh new file mode 100755 index 0000000000..b4899d6266 --- /dev/null +++ b/tests/custom/permutations/13_image_function/enum/0030_find_permutation/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/13_image_function/enum/0030_find_permutation/stdout.expected b/tests/custom/permutations/13_image_function/enum/0030_find_permutation/stdout.expected new file mode 100644 index 0000000000..066eb575ff --- /dev/null +++ b/tests/custom/permutations/13_image_function/enum/0030_find_permutation/stdout.expected @@ -0,0 +1,8 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Copying solution to: permutation.solution +language Essence 1.3 + +letting p be permutation((E2, E3)) diff --git a/tests/custom/permutations/13_image_function/int/0010_given_permutation/permutation.essence b/tests/custom/permutations/13_image_function/int/0010_given_permutation/permutation.essence new file mode 100644 index 0000000000..a89c13ead8 --- /dev/null +++ b/tests/custom/permutations/13_image_function/int/0010_given_permutation/permutation.essence @@ -0,0 +1,8 @@ +letting n be 4 + +given p : permutation of int(1..n) +letting f be function(1-->2, 2-->3) +find g : function int(1..4) --> int(1..4) + +such that g = image(p,f) + diff --git a/tests/custom/permutations/13_image_function/int/0010_given_permutation/permutation.param b/tests/custom/permutations/13_image_function/int/0010_given_permutation/permutation.param new file mode 100644 index 0000000000..179de93e68 --- /dev/null +++ b/tests/custom/permutations/13_image_function/int/0010_given_permutation/permutation.param @@ -0,0 +1,2 @@ +letting p be permutation((2,4)) + diff --git a/tests/custom/permutations/13_image_function/int/0010_given_permutation/run.sh b/tests/custom/permutations/13_image_function/int/0010_given_permutation/run.sh new file mode 100755 index 0000000000..9dc67e67f5 --- /dev/null +++ b/tests/custom/permutations/13_image_function/int/0010_given_permutation/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence *.param +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/13_image_function/int/0010_given_permutation/stdout.expected b/tests/custom/permutations/13_image_function/int/0010_given_permutation/stdout.expected new file mode 100644 index 0000000000..07cf3d6c18 --- /dev/null +++ b/tests/custom/permutations/13_image_function/int/0010_given_permutation/stdout.expected @@ -0,0 +1,8 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime permutation.param +Copying solution to: permutation-permutation.solution +language Essence 1.3 + +letting g be function(1 --> 4, 4 --> 3) diff --git a/tests/custom/permutations/13_image_function/int/0020_letting_permutation/permutation.essence b/tests/custom/permutations/13_image_function/int/0020_letting_permutation/permutation.essence new file mode 100644 index 0000000000..7c72c3dfa6 --- /dev/null +++ b/tests/custom/permutations/13_image_function/int/0020_letting_permutation/permutation.essence @@ -0,0 +1,8 @@ +letting n be 4 + +letting p be permutation((2,3)) +letting f be function(1-->2, 2-->4) +find g : function int(1..4) --> int(1..4) + +such that g = image(p,f) + diff --git a/tests/custom/permutations/13_image_function/int/0020_letting_permutation/run.sh b/tests/custom/permutations/13_image_function/int/0020_letting_permutation/run.sh new file mode 100755 index 0000000000..b4899d6266 --- /dev/null +++ b/tests/custom/permutations/13_image_function/int/0020_letting_permutation/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/13_image_function/int/0020_letting_permutation/stdout.expected b/tests/custom/permutations/13_image_function/int/0020_letting_permutation/stdout.expected new file mode 100644 index 0000000000..400f44ca55 --- /dev/null +++ b/tests/custom/permutations/13_image_function/int/0020_letting_permutation/stdout.expected @@ -0,0 +1,8 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Copying solution to: permutation.solution +language Essence 1.3 + +letting g be function(1 --> 3, 3 --> 4) diff --git a/tests/custom/permutations/13_image_function/int/0030_find_permutation/permutation.essence b/tests/custom/permutations/13_image_function/int/0030_find_permutation/permutation.essence new file mode 100644 index 0000000000..67e8890930 --- /dev/null +++ b/tests/custom/permutations/13_image_function/int/0030_find_permutation/permutation.essence @@ -0,0 +1,8 @@ +letting n be 4 + +find p : permutation of int(1..4) +letting f be function(1-->2,2-->4) +letting g be function(1-->3,3-->4) + +such that g = image(p,f) + diff --git a/tests/custom/permutations/13_image_function/int/0030_find_permutation/run.sh b/tests/custom/permutations/13_image_function/int/0030_find_permutation/run.sh new file mode 100755 index 0000000000..b4899d6266 --- /dev/null +++ b/tests/custom/permutations/13_image_function/int/0030_find_permutation/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/13_image_function/int/0030_find_permutation/stdout.expected b/tests/custom/permutations/13_image_function/int/0030_find_permutation/stdout.expected new file mode 100644 index 0000000000..4e07c3be70 --- /dev/null +++ b/tests/custom/permutations/13_image_function/int/0030_find_permutation/stdout.expected @@ -0,0 +1,8 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Copying solution to: permutation.solution +language Essence 1.3 + +letting p be permutation((2, 3)) diff --git a/tests/custom/permutations/13_image_function/runthese.sh b/tests/custom/permutations/13_image_function/runthese.sh new file mode 100644 index 0000000000..ac3509a9ce --- /dev/null +++ b/tests/custom/permutations/13_image_function/runthese.sh @@ -0,0 +1 @@ +stack build --copy-bins --test --test-arguments "-p custom.permutations.13_image_function" diff --git a/tests/custom/permutations/13_image_function/unnamed/0030_find_permutation/permutation.essence b/tests/custom/permutations/13_image_function/unnamed/0030_find_permutation/permutation.essence new file mode 100644 index 0000000000..adf1db82c6 --- /dev/null +++ b/tests/custom/permutations/13_image_function/unnamed/0030_find_permutation/permutation.essence @@ -0,0 +1,9 @@ +letting n be new type of size 4 + +find p : permutation of n +find f : function n --> n +find g : function n --> n + + +such that g = image(p,f) /\ |p| > 0 /\ |f| > 0 + diff --git a/tests/custom/permutations/13_image_function/unnamed/0030_find_permutation/run.sh b/tests/custom/permutations/13_image_function/unnamed/0030_find_permutation/run.sh new file mode 100755 index 0000000000..b4899d6266 --- /dev/null +++ b/tests/custom/permutations/13_image_function/unnamed/0030_find_permutation/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/13_image_function/unnamed/0030_find_permutation/stdout.expected b/tests/custom/permutations/13_image_function/unnamed/0030_find_permutation/stdout.expected new file mode 100644 index 0000000000..8631753f0f --- /dev/null +++ b/tests/custom/permutations/13_image_function/unnamed/0030_find_permutation/stdout.expected @@ -0,0 +1,11 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Copying solution to: permutation.solution +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting f be function(n_4 --> n_1) +letting g be function(n_3 --> n_1) +letting p be permutation((n_3, n_4)) diff --git a/tests/custom/permutations/14_image_sequence/enum/0010_given_permutation/permutation.essence b/tests/custom/permutations/14_image_sequence/enum/0010_given_permutation/permutation.essence new file mode 100644 index 0000000000..a48b6809f9 --- /dev/null +++ b/tests/custom/permutations/14_image_sequence/enum/0010_given_permutation/permutation.essence @@ -0,0 +1,8 @@ +letting n be new type enum {E1,E2,E3,E4} + +given p : permutation of n +letting f be sequence(E1,E2,E3,E4) +find g : sequence (size 4) of n + +such that g = image(p,f) + diff --git a/tests/custom/permutations/14_image_sequence/enum/0010_given_permutation/permutation.param b/tests/custom/permutations/14_image_sequence/enum/0010_given_permutation/permutation.param new file mode 100644 index 0000000000..c7d9c37d25 --- /dev/null +++ b/tests/custom/permutations/14_image_sequence/enum/0010_given_permutation/permutation.param @@ -0,0 +1,2 @@ +letting p be permutation((E2,E4)) + diff --git a/tests/custom/permutations/14_image_sequence/enum/0010_given_permutation/run.sh b/tests/custom/permutations/14_image_sequence/enum/0010_given_permutation/run.sh new file mode 100755 index 0000000000..9dc67e67f5 --- /dev/null +++ b/tests/custom/permutations/14_image_sequence/enum/0010_given_permutation/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence *.param +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/14_image_sequence/enum/0010_given_permutation/stdout.expected b/tests/custom/permutations/14_image_sequence/enum/0010_given_permutation/stdout.expected new file mode 100644 index 0000000000..5793310569 --- /dev/null +++ b/tests/custom/permutations/14_image_sequence/enum/0010_given_permutation/stdout.expected @@ -0,0 +1,8 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime permutation.param +Copying solution to: permutation-permutation.solution +language Essence 1.3 + +letting g be sequence(E1, E4, E3, E2) diff --git a/tests/custom/permutations/14_image_sequence/enum/0020_letting_permutation/permutation.essence b/tests/custom/permutations/14_image_sequence/enum/0020_letting_permutation/permutation.essence new file mode 100644 index 0000000000..446537c410 --- /dev/null +++ b/tests/custom/permutations/14_image_sequence/enum/0020_letting_permutation/permutation.essence @@ -0,0 +1,8 @@ +letting n be new type enum {E1,E2,E3,E4} + +letting p be permutation((E2,E3)) +letting f be sequence(E1,E2,E3,E4) +find g : sequence (size 4) of n + +such that g = image(p,f) + diff --git a/tests/custom/permutations/14_image_sequence/enum/0020_letting_permutation/run.sh b/tests/custom/permutations/14_image_sequence/enum/0020_letting_permutation/run.sh new file mode 100755 index 0000000000..b4899d6266 --- /dev/null +++ b/tests/custom/permutations/14_image_sequence/enum/0020_letting_permutation/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/14_image_sequence/enum/0020_letting_permutation/stdout.expected b/tests/custom/permutations/14_image_sequence/enum/0020_letting_permutation/stdout.expected new file mode 100644 index 0000000000..e4b9bb364e --- /dev/null +++ b/tests/custom/permutations/14_image_sequence/enum/0020_letting_permutation/stdout.expected @@ -0,0 +1,8 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Copying solution to: permutation.solution +language Essence 1.3 + +letting g be sequence(E1, E3, E2, E4) diff --git a/tests/custom/permutations/14_image_sequence/enum/0030_find_permutation/permutation.essence b/tests/custom/permutations/14_image_sequence/enum/0030_find_permutation/permutation.essence new file mode 100644 index 0000000000..2861b8d4a5 --- /dev/null +++ b/tests/custom/permutations/14_image_sequence/enum/0030_find_permutation/permutation.essence @@ -0,0 +1,8 @@ +letting n be new type enum {E1,E2,E3,E4} + +find p : permutation of n +letting f be sequence(E1,E2,E3,E4) +letting g be sequence (E4,E3,E2,E1) + +such that g = image(p,f) + diff --git a/tests/custom/permutations/14_image_sequence/enum/0030_find_permutation/run.sh b/tests/custom/permutations/14_image_sequence/enum/0030_find_permutation/run.sh new file mode 100755 index 0000000000..b4899d6266 --- /dev/null +++ b/tests/custom/permutations/14_image_sequence/enum/0030_find_permutation/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/14_image_sequence/enum/0030_find_permutation/stdout.expected b/tests/custom/permutations/14_image_sequence/enum/0030_find_permutation/stdout.expected new file mode 100644 index 0000000000..75c9c50761 --- /dev/null +++ b/tests/custom/permutations/14_image_sequence/enum/0030_find_permutation/stdout.expected @@ -0,0 +1,8 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Copying solution to: permutation.solution +language Essence 1.3 + +letting p be permutation((E1, E4), (E2, E3)) diff --git a/tests/custom/permutations/14_image_sequence/int/0010_given_permutation/permutation.essence b/tests/custom/permutations/14_image_sequence/int/0010_given_permutation/permutation.essence new file mode 100644 index 0000000000..d313a62827 --- /dev/null +++ b/tests/custom/permutations/14_image_sequence/int/0010_given_permutation/permutation.essence @@ -0,0 +1,8 @@ +letting n be 4 + +given p : permutation of int(1..n) +letting f be sequence(1,2,3,4) +find g : sequence (size 4) of int(1..4) + +such that g = image(p,f) + diff --git a/tests/custom/permutations/14_image_sequence/int/0010_given_permutation/permutation.param b/tests/custom/permutations/14_image_sequence/int/0010_given_permutation/permutation.param new file mode 100644 index 0000000000..179de93e68 --- /dev/null +++ b/tests/custom/permutations/14_image_sequence/int/0010_given_permutation/permutation.param @@ -0,0 +1,2 @@ +letting p be permutation((2,4)) + diff --git a/tests/custom/permutations/14_image_sequence/int/0010_given_permutation/run.sh b/tests/custom/permutations/14_image_sequence/int/0010_given_permutation/run.sh new file mode 100755 index 0000000000..9dc67e67f5 --- /dev/null +++ b/tests/custom/permutations/14_image_sequence/int/0010_given_permutation/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence *.param +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/14_image_sequence/int/0010_given_permutation/stdout.expected b/tests/custom/permutations/14_image_sequence/int/0010_given_permutation/stdout.expected new file mode 100644 index 0000000000..57d6d03ae4 --- /dev/null +++ b/tests/custom/permutations/14_image_sequence/int/0010_given_permutation/stdout.expected @@ -0,0 +1,8 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime permutation.param +Copying solution to: permutation-permutation.solution +language Essence 1.3 + +letting g be sequence(1, 4, 3, 2) diff --git a/tests/custom/permutations/14_image_sequence/int/0020_letting_permutation/permutation.essence b/tests/custom/permutations/14_image_sequence/int/0020_letting_permutation/permutation.essence new file mode 100644 index 0000000000..1dce97d86d --- /dev/null +++ b/tests/custom/permutations/14_image_sequence/int/0020_letting_permutation/permutation.essence @@ -0,0 +1,8 @@ +letting n be 4 + +letting p be permutation((2,3)) +letting f be sequence(1,2,3,4) +find g : sequence (size 4) of int(1..4) + +such that g = image(p,f) + diff --git a/tests/custom/permutations/14_image_sequence/int/0020_letting_permutation/run.sh b/tests/custom/permutations/14_image_sequence/int/0020_letting_permutation/run.sh new file mode 100755 index 0000000000..b4899d6266 --- /dev/null +++ b/tests/custom/permutations/14_image_sequence/int/0020_letting_permutation/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/14_image_sequence/int/0020_letting_permutation/stdout.expected b/tests/custom/permutations/14_image_sequence/int/0020_letting_permutation/stdout.expected new file mode 100644 index 0000000000..d93cbb4075 --- /dev/null +++ b/tests/custom/permutations/14_image_sequence/int/0020_letting_permutation/stdout.expected @@ -0,0 +1,8 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Copying solution to: permutation.solution +language Essence 1.3 + +letting g be sequence(1, 3, 2, 4) diff --git a/tests/custom/permutations/14_image_sequence/int/0030_find_permutation/permutation.essence b/tests/custom/permutations/14_image_sequence/int/0030_find_permutation/permutation.essence new file mode 100644 index 0000000000..419cd05ff9 --- /dev/null +++ b/tests/custom/permutations/14_image_sequence/int/0030_find_permutation/permutation.essence @@ -0,0 +1,8 @@ +letting n be 4 + +find p : permutation of int(1..4) +letting f be sequence(1,2,3,4) +letting g be sequence (4,3,2,1) + +such that g = image(p,f) + diff --git a/tests/custom/permutations/14_image_sequence/int/0030_find_permutation/run.sh b/tests/custom/permutations/14_image_sequence/int/0030_find_permutation/run.sh new file mode 100755 index 0000000000..b4899d6266 --- /dev/null +++ b/tests/custom/permutations/14_image_sequence/int/0030_find_permutation/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/14_image_sequence/int/0030_find_permutation/stdout.expected b/tests/custom/permutations/14_image_sequence/int/0030_find_permutation/stdout.expected new file mode 100644 index 0000000000..df2d4d38af --- /dev/null +++ b/tests/custom/permutations/14_image_sequence/int/0030_find_permutation/stdout.expected @@ -0,0 +1,8 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Copying solution to: permutation.solution +language Essence 1.3 + +letting p be permutation((1, 4), (2, 3)) diff --git a/tests/custom/permutations/14_image_sequence/runthese.sh b/tests/custom/permutations/14_image_sequence/runthese.sh new file mode 100644 index 0000000000..f4ba4c79fb --- /dev/null +++ b/tests/custom/permutations/14_image_sequence/runthese.sh @@ -0,0 +1 @@ +stack build --copy-bins --test --test-arguments "-p custom.permutations.14_image_sequence" diff --git a/tests/custom/permutations/14_image_sequence/unnamed/0030_find_permutation/permutation.essence b/tests/custom/permutations/14_image_sequence/unnamed/0030_find_permutation/permutation.essence new file mode 100644 index 0000000000..a6e601898b --- /dev/null +++ b/tests/custom/permutations/14_image_sequence/unnamed/0030_find_permutation/permutation.essence @@ -0,0 +1,8 @@ +letting n be new type of size 4 + +find p : permutation of n +find f : sequence (size 4) of n +find g : sequence (size 4) of n + +such that g = image(p,f) /\ f != g + diff --git a/tests/custom/permutations/14_image_sequence/unnamed/0030_find_permutation/run.sh b/tests/custom/permutations/14_image_sequence/unnamed/0030_find_permutation/run.sh new file mode 100755 index 0000000000..b4899d6266 --- /dev/null +++ b/tests/custom/permutations/14_image_sequence/unnamed/0030_find_permutation/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/14_image_sequence/unnamed/0030_find_permutation/stdout.expected b/tests/custom/permutations/14_image_sequence/unnamed/0030_find_permutation/stdout.expected new file mode 100644 index 0000000000..87cc818944 --- /dev/null +++ b/tests/custom/permutations/14_image_sequence/unnamed/0030_find_permutation/stdout.expected @@ -0,0 +1,11 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Copying solution to: permutation.solution +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting f be sequence(n_1, n_1, n_1, n_3) +letting g be sequence(n_1, n_1, n_1, n_4) +letting p be permutation((n_3, n_4)) From fcbf42127e9076e5517cacba68f91c5e19e6adb9 Mon Sep 17 00:00:00 2001 From: Fraser Dunlop Date: Fri, 21 Dec 2018 15:33:48 +0000 Subject: [PATCH 061/229] mset tests --- .../permutation.essence | 10 +++ .../permutation.param | 2 + .../run.sh | 3 + .../stdout.expected | 8 ++ .../permutation.essence | 11 +++ .../permutation.param | 1 + .../0020_given_permutation_find_msets/run.sh | 3 + .../stdout.expected | 54 ++++++++++++++ .../permutation.essence | 11 +++ .../run.sh | 3 + .../stdout.expected | 54 ++++++++++++++ .../permutation.essence | 11 +++ .../0040_find_permutation_find_msets/run.sh | 3 + .../stdout.expected | 64 ++++++++++++++++ .../permutation.essence | 11 +++ .../permutation.param | 1 + .../run.sh | 3 + .../stdout.expected | 44 +++++++++++ .../permutation.essence | 10 +++ .../permutation.param | 2 + .../run.sh | 3 + .../stdout.expected | 8 ++ .../permutation.essence | 11 +++ .../permutation.param | 1 + .../0020_given_permutation_find_msets/run.sh | 3 + .../stdout.expected | 54 ++++++++++++++ .../permutation.essence | 11 +++ .../run.sh | 3 + .../stdout.expected | 54 ++++++++++++++ .../permutation.essence | 11 +++ .../0040_find_permutation_find_msets/run.sh | 3 + .../stdout.expected | 64 ++++++++++++++++ .../permutation.essence | 11 +++ .../permutation.param | 1 + .../run.sh | 3 + .../stdout.expected | 44 +++++++++++ .../permutations/15_image_mset/runthese.sh | 1 + .../permutation.essence | 11 +++ .../0004_find_permutation_find_sets/run.sh | 3 + .../stdout.expected | 74 +++++++++++++++++++ 40 files changed, 683 insertions(+) create mode 100644 tests/custom/permutations/15_image_mset/enum/0010_given_permutation_letting_mset/permutation.essence create mode 100644 tests/custom/permutations/15_image_mset/enum/0010_given_permutation_letting_mset/permutation.param create mode 100755 tests/custom/permutations/15_image_mset/enum/0010_given_permutation_letting_mset/run.sh create mode 100644 tests/custom/permutations/15_image_mset/enum/0010_given_permutation_letting_mset/stdout.expected create mode 100644 tests/custom/permutations/15_image_mset/enum/0020_given_permutation_find_msets/permutation.essence create mode 100644 tests/custom/permutations/15_image_mset/enum/0020_given_permutation_find_msets/permutation.param create mode 100755 tests/custom/permutations/15_image_mset/enum/0020_given_permutation_find_msets/run.sh create mode 100644 tests/custom/permutations/15_image_mset/enum/0020_given_permutation_find_msets/stdout.expected create mode 100644 tests/custom/permutations/15_image_mset/enum/0030_letting_permutation_find_msets/permutation.essence create mode 100755 tests/custom/permutations/15_image_mset/enum/0030_letting_permutation_find_msets/run.sh create mode 100644 tests/custom/permutations/15_image_mset/enum/0030_letting_permutation_find_msets/stdout.expected create mode 100644 tests/custom/permutations/15_image_mset/enum/0040_find_permutation_find_msets/permutation.essence create mode 100755 tests/custom/permutations/15_image_mset/enum/0040_find_permutation_find_msets/run.sh create mode 100644 tests/custom/permutations/15_image_mset/enum/0040_find_permutation_find_msets/stdout.expected create mode 100644 tests/custom/permutations/15_image_mset/enum/0050_find_permutation_given_mset_find_mset/permutation.essence create mode 100644 tests/custom/permutations/15_image_mset/enum/0050_find_permutation_given_mset_find_mset/permutation.param create mode 100755 tests/custom/permutations/15_image_mset/enum/0050_find_permutation_given_mset_find_mset/run.sh create mode 100644 tests/custom/permutations/15_image_mset/enum/0050_find_permutation_given_mset_find_mset/stdout.expected create mode 100644 tests/custom/permutations/15_image_mset/int/0010_given_permutation_letting_mset/permutation.essence create mode 100644 tests/custom/permutations/15_image_mset/int/0010_given_permutation_letting_mset/permutation.param create mode 100755 tests/custom/permutations/15_image_mset/int/0010_given_permutation_letting_mset/run.sh create mode 100644 tests/custom/permutations/15_image_mset/int/0010_given_permutation_letting_mset/stdout.expected create mode 100644 tests/custom/permutations/15_image_mset/int/0020_given_permutation_find_msets/permutation.essence create mode 100644 tests/custom/permutations/15_image_mset/int/0020_given_permutation_find_msets/permutation.param create mode 100755 tests/custom/permutations/15_image_mset/int/0020_given_permutation_find_msets/run.sh create mode 100644 tests/custom/permutations/15_image_mset/int/0020_given_permutation_find_msets/stdout.expected create mode 100644 tests/custom/permutations/15_image_mset/int/0030_letting_permutation_find_msets/permutation.essence create mode 100755 tests/custom/permutations/15_image_mset/int/0030_letting_permutation_find_msets/run.sh create mode 100644 tests/custom/permutations/15_image_mset/int/0030_letting_permutation_find_msets/stdout.expected create mode 100644 tests/custom/permutations/15_image_mset/int/0040_find_permutation_find_msets/permutation.essence create mode 100755 tests/custom/permutations/15_image_mset/int/0040_find_permutation_find_msets/run.sh create mode 100644 tests/custom/permutations/15_image_mset/int/0040_find_permutation_find_msets/stdout.expected create mode 100644 tests/custom/permutations/15_image_mset/int/0050_find_permutation_given_mset_find_mset/permutation.essence create mode 100644 tests/custom/permutations/15_image_mset/int/0050_find_permutation_given_mset_find_mset/permutation.param create mode 100755 tests/custom/permutations/15_image_mset/int/0050_find_permutation_given_mset_find_mset/run.sh create mode 100644 tests/custom/permutations/15_image_mset/int/0050_find_permutation_given_mset_find_mset/stdout.expected create mode 100644 tests/custom/permutations/15_image_mset/runthese.sh create mode 100644 tests/custom/permutations/15_image_mset/unnamed/0004_find_permutation_find_sets/permutation.essence create mode 100755 tests/custom/permutations/15_image_mset/unnamed/0004_find_permutation_find_sets/run.sh create mode 100644 tests/custom/permutations/15_image_mset/unnamed/0004_find_permutation_find_sets/stdout.expected diff --git a/tests/custom/permutations/15_image_mset/enum/0010_given_permutation_letting_mset/permutation.essence b/tests/custom/permutations/15_image_mset/enum/0010_given_permutation_letting_mset/permutation.essence new file mode 100644 index 0000000000..4ed5ea678e --- /dev/null +++ b/tests/custom/permutations/15_image_mset/enum/0010_given_permutation_letting_mset/permutation.essence @@ -0,0 +1,10 @@ +letting n be new type enum {E1,E2,E3,E4} + +given p : permutation of n +given s : mset (size 3) of n + +find sn : mset (size 3) of n + + +such that sn = image(p,s) + diff --git a/tests/custom/permutations/15_image_mset/enum/0010_given_permutation_letting_mset/permutation.param b/tests/custom/permutations/15_image_mset/enum/0010_given_permutation_letting_mset/permutation.param new file mode 100644 index 0000000000..32b99e8a6c --- /dev/null +++ b/tests/custom/permutations/15_image_mset/enum/0010_given_permutation_letting_mset/permutation.param @@ -0,0 +1,2 @@ +letting p be permutation((E1,E3,E4)) +letting s be mset(E1,E2,E2) diff --git a/tests/custom/permutations/15_image_mset/enum/0010_given_permutation_letting_mset/run.sh b/tests/custom/permutations/15_image_mset/enum/0010_given_permutation_letting_mset/run.sh new file mode 100755 index 0000000000..9dc67e67f5 --- /dev/null +++ b/tests/custom/permutations/15_image_mset/enum/0010_given_permutation_letting_mset/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence *.param +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/15_image_mset/enum/0010_given_permutation_letting_mset/stdout.expected b/tests/custom/permutations/15_image_mset/enum/0010_given_permutation_letting_mset/stdout.expected new file mode 100644 index 0000000000..7d29cdcc0b --- /dev/null +++ b/tests/custom/permutations/15_image_mset/enum/0010_given_permutation_letting_mset/stdout.expected @@ -0,0 +1,8 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime permutation.param +Copying solution to: permutation-permutation.solution +language Essence 1.3 + +letting sn be mset(E2, E2, E3) diff --git a/tests/custom/permutations/15_image_mset/enum/0020_given_permutation_find_msets/permutation.essence b/tests/custom/permutations/15_image_mset/enum/0020_given_permutation_find_msets/permutation.essence new file mode 100644 index 0000000000..a3dedca402 --- /dev/null +++ b/tests/custom/permutations/15_image_mset/enum/0020_given_permutation_find_msets/permutation.essence @@ -0,0 +1,11 @@ +letting n be new type enum {E1,E2,E3,E4} + +given p : permutation of n + +find s : mset (maxSize 3) of n + +find sn : mset (maxSize 3) of n + + +such that sn = image(p,s) + diff --git a/tests/custom/permutations/15_image_mset/enum/0020_given_permutation_find_msets/permutation.param b/tests/custom/permutations/15_image_mset/enum/0020_given_permutation_find_msets/permutation.param new file mode 100644 index 0000000000..19349bb872 --- /dev/null +++ b/tests/custom/permutations/15_image_mset/enum/0020_given_permutation_find_msets/permutation.param @@ -0,0 +1 @@ +letting p be permutation((E1,E3,E4)) diff --git a/tests/custom/permutations/15_image_mset/enum/0020_given_permutation_find_msets/run.sh b/tests/custom/permutations/15_image_mset/enum/0020_given_permutation_find_msets/run.sh new file mode 100755 index 0000000000..aab5d44c6e --- /dev/null +++ b/tests/custom/permutations/15_image_mset/enum/0020_given_permutation_find_msets/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence *.param --number-of-solutions=10 +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/15_image_mset/enum/0020_given_permutation_find_msets/stdout.expected b/tests/custom/permutations/15_image_mset/enum/0020_given_permutation_find_msets/stdout.expected new file mode 100644 index 0000000000..94ae70cf3d --- /dev/null +++ b/tests/custom/permutations/15_image_mset/enum/0020_given_permutation_find_msets/stdout.expected @@ -0,0 +1,54 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime permutation.param +Copying solution to: permutation-permutation-000001.solution +Copying solution to: permutation-permutation-000002.solution +Copying solution to: permutation-permutation-000003.solution +Copying solution to: permutation-permutation-000004.solution +Copying solution to: permutation-permutation-000005.solution +Copying solution to: permutation-permutation-000006.solution +Copying solution to: permutation-permutation-000007.solution +Copying solution to: permutation-permutation-000008.solution +Copying solution to: permutation-permutation-000009.solution +Copying solution to: permutation-permutation-000010.solution +language Essence 1.3 + +letting s be mset() +letting sn be mset() +language Essence 1.3 + +letting s be mset(E1) +letting sn be mset(E3) +language Essence 1.3 + +letting s be mset(E2) +letting sn be mset(E2) +language Essence 1.3 + +letting s be mset(E3) +letting sn be mset(E4) +language Essence 1.3 + +letting s be mset(E4) +letting sn be mset(E1) +language Essence 1.3 + +letting s be mset(E1, E2) +letting sn be mset(E2, E3) +language Essence 1.3 + +letting s be mset(E1, E3) +letting sn be mset(E3, E4) +language Essence 1.3 + +letting s be mset(E1, E4) +letting sn be mset(E1, E3) +language Essence 1.3 + +letting s be mset(E2, E3) +letting sn be mset(E2, E4) +language Essence 1.3 + +letting s be mset(E2, E4) +letting sn be mset(E1, E2) diff --git a/tests/custom/permutations/15_image_mset/enum/0030_letting_permutation_find_msets/permutation.essence b/tests/custom/permutations/15_image_mset/enum/0030_letting_permutation_find_msets/permutation.essence new file mode 100644 index 0000000000..c9f6d9f4d4 --- /dev/null +++ b/tests/custom/permutations/15_image_mset/enum/0030_letting_permutation_find_msets/permutation.essence @@ -0,0 +1,11 @@ +letting n be new type enum {E1,E2,E3,E4} + +letting p be permutation((E1,E3,E4)) + +find s : mset (maxSize 3) of n + +find sn : mset (maxSize 3) of n + + +such that sn = image(p,s) + diff --git a/tests/custom/permutations/15_image_mset/enum/0030_letting_permutation_find_msets/run.sh b/tests/custom/permutations/15_image_mset/enum/0030_letting_permutation_find_msets/run.sh new file mode 100755 index 0000000000..03373df6cb --- /dev/null +++ b/tests/custom/permutations/15_image_mset/enum/0030_letting_permutation_find_msets/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence --number-of-solutions=10 +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/15_image_mset/enum/0030_letting_permutation_find_msets/stdout.expected b/tests/custom/permutations/15_image_mset/enum/0030_letting_permutation_find_msets/stdout.expected new file mode 100644 index 0000000000..269d8404f3 --- /dev/null +++ b/tests/custom/permutations/15_image_mset/enum/0030_letting_permutation_find_msets/stdout.expected @@ -0,0 +1,54 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Copying solution to: permutation-000001.solution +Copying solution to: permutation-000002.solution +Copying solution to: permutation-000003.solution +Copying solution to: permutation-000004.solution +Copying solution to: permutation-000005.solution +Copying solution to: permutation-000006.solution +Copying solution to: permutation-000007.solution +Copying solution to: permutation-000008.solution +Copying solution to: permutation-000009.solution +Copying solution to: permutation-000010.solution +language Essence 1.3 + +letting s be mset() +letting sn be mset() +language Essence 1.3 + +letting s be mset(E1) +letting sn be mset(E3) +language Essence 1.3 + +letting s be mset(E2) +letting sn be mset(E2) +language Essence 1.3 + +letting s be mset(E3) +letting sn be mset(E4) +language Essence 1.3 + +letting s be mset(E4) +letting sn be mset(E1) +language Essence 1.3 + +letting s be mset(E1, E2) +letting sn be mset(E2, E3) +language Essence 1.3 + +letting s be mset(E1, E3) +letting sn be mset(E3, E4) +language Essence 1.3 + +letting s be mset(E1, E4) +letting sn be mset(E1, E3) +language Essence 1.3 + +letting s be mset(E2, E3) +letting sn be mset(E2, E4) +language Essence 1.3 + +letting s be mset(E2, E4) +letting sn be mset(E1, E2) diff --git a/tests/custom/permutations/15_image_mset/enum/0040_find_permutation_find_msets/permutation.essence b/tests/custom/permutations/15_image_mset/enum/0040_find_permutation_find_msets/permutation.essence new file mode 100644 index 0000000000..7b9ce98cbf --- /dev/null +++ b/tests/custom/permutations/15_image_mset/enum/0040_find_permutation_find_msets/permutation.essence @@ -0,0 +1,11 @@ +letting n be new type enum {E1,E2,E3,E4} + +find p : permutation of n + +find s : mset (size 6) of n + +find sn : mset (size 6) of n + + +such that sn = image(p,s) /\ (3 = sum([ toInt(l != r) | (l, r) <- p])) + diff --git a/tests/custom/permutations/15_image_mset/enum/0040_find_permutation_find_msets/run.sh b/tests/custom/permutations/15_image_mset/enum/0040_find_permutation_find_msets/run.sh new file mode 100755 index 0000000000..03373df6cb --- /dev/null +++ b/tests/custom/permutations/15_image_mset/enum/0040_find_permutation_find_msets/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence --number-of-solutions=10 +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/15_image_mset/enum/0040_find_permutation_find_msets/stdout.expected b/tests/custom/permutations/15_image_mset/enum/0040_find_permutation_find_msets/stdout.expected new file mode 100644 index 0000000000..5c6f660314 --- /dev/null +++ b/tests/custom/permutations/15_image_mset/enum/0040_find_permutation_find_msets/stdout.expected @@ -0,0 +1,64 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Copying solution to: permutation-000001.solution +Copying solution to: permutation-000002.solution +Copying solution to: permutation-000003.solution +Copying solution to: permutation-000004.solution +Copying solution to: permutation-000005.solution +Copying solution to: permutation-000006.solution +Copying solution to: permutation-000007.solution +Copying solution to: permutation-000008.solution +Copying solution to: permutation-000009.solution +Copying solution to: permutation-000010.solution +language Essence 1.3 + +letting p be permutation((E2, E3, E4)) +letting s be mset(E1, E2, E3, E4, E4, E4) +letting sn be mset(E1, E2, E2, E2, E3, E4) +language Essence 1.3 + +letting p be permutation((E2, E3, E4)) +letting s be mset(E1, E2, E3, E3, E4, E4) +letting sn be mset(E1, E2, E2, E3, E4, E4) +language Essence 1.3 + +letting p be permutation((E2, E3, E4)) +letting s be mset(E1, E2, E3, E3, E3, E4) +letting sn be mset(E1, E2, E3, E4, E4, E4) +language Essence 1.3 + +letting p be permutation((E2, E3, E4)) +letting s be mset(E1, E2, E3, E3, E3, E3) +letting sn be mset(E1, E3, E4, E4, E4, E4) +language Essence 1.3 + +letting p be permutation((E2, E3, E4)) +letting s be mset(E1, E2, E4, E4, E4, E4) +letting sn be mset(E1, E2, E2, E2, E2, E3) +language Essence 1.3 + +letting p be permutation((E2, E3, E4)) +letting s be mset(E1, E3, E4, E4, E4, E4) +letting sn be mset(E1, E2, E2, E2, E2, E4) +language Essence 1.3 + +letting p be permutation((E2, E3, E4)) +letting s be mset(E2, E3, E4, E4, E4, E4) +letting sn be mset(E2, E2, E2, E2, E3, E4) +language Essence 1.3 + +letting p be permutation((E2, E3, E4)) +letting s be mset(E1, E2, E2, E3, E4, E4) +letting sn be mset(E1, E2, E2, E3, E3, E4) +language Essence 1.3 + +letting p be permutation((E2, E3, E4)) +letting s be mset(E1, E2, E2, E3, E3, E4) +letting sn be mset(E1, E2, E3, E3, E4, E4) +language Essence 1.3 + +letting p be permutation((E2, E3, E4)) +letting s be mset(E1, E2, E2, E3, E3, E3) +letting sn be mset(E1, E3, E3, E4, E4, E4) diff --git a/tests/custom/permutations/15_image_mset/enum/0050_find_permutation_given_mset_find_mset/permutation.essence b/tests/custom/permutations/15_image_mset/enum/0050_find_permutation_given_mset_find_mset/permutation.essence new file mode 100644 index 0000000000..682a284254 --- /dev/null +++ b/tests/custom/permutations/15_image_mset/enum/0050_find_permutation_given_mset_find_mset/permutation.essence @@ -0,0 +1,11 @@ +letting n be new type enum {E1,E2,E3,E4} + +find p : permutation of n + +given s : mset of n + +find sn : mset (maxSize 5) of n + + +such that sn = image(p,s) /\ (3 = sum([ toInt(l != r) | (l, r) <- p])) + diff --git a/tests/custom/permutations/15_image_mset/enum/0050_find_permutation_given_mset_find_mset/permutation.param b/tests/custom/permutations/15_image_mset/enum/0050_find_permutation_given_mset_find_mset/permutation.param new file mode 100644 index 0000000000..c863766fa2 --- /dev/null +++ b/tests/custom/permutations/15_image_mset/enum/0050_find_permutation_given_mset_find_mset/permutation.param @@ -0,0 +1 @@ +letting s be mset(E1,E2,E3) diff --git a/tests/custom/permutations/15_image_mset/enum/0050_find_permutation_given_mset_find_mset/run.sh b/tests/custom/permutations/15_image_mset/enum/0050_find_permutation_given_mset_find_mset/run.sh new file mode 100755 index 0000000000..aab5d44c6e --- /dev/null +++ b/tests/custom/permutations/15_image_mset/enum/0050_find_permutation_given_mset_find_mset/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence *.param --number-of-solutions=10 +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/15_image_mset/enum/0050_find_permutation_given_mset_find_mset/stdout.expected b/tests/custom/permutations/15_image_mset/enum/0050_find_permutation_given_mset_find_mset/stdout.expected new file mode 100644 index 0000000000..14465059ff --- /dev/null +++ b/tests/custom/permutations/15_image_mset/enum/0050_find_permutation_given_mset_find_mset/stdout.expected @@ -0,0 +1,44 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime permutation.param +Copying solution to: permutation-permutation-000001.solution +Copying solution to: permutation-permutation-000002.solution +Copying solution to: permutation-permutation-000003.solution +Copying solution to: permutation-permutation-000004.solution +Copying solution to: permutation-permutation-000005.solution +Copying solution to: permutation-permutation-000006.solution +Copying solution to: permutation-permutation-000007.solution +Copying solution to: permutation-permutation-000008.solution +language Essence 1.3 + +letting p be permutation((E2, E3, E4)) +letting sn be mset(E1, E3, E4) +language Essence 1.3 + +letting p be permutation((E2, E4, E3)) +letting sn be mset(E1, E2, E4) +language Essence 1.3 + +letting p be permutation((E1, E2, E3)) +letting sn be mset(E1, E2, E3) +language Essence 1.3 + +letting p be permutation((E1, E2, E4)) +letting sn be mset(E2, E3, E4) +language Essence 1.3 + +letting p be permutation((E1, E3, E2)) +letting sn be mset(E1, E2, E3) +language Essence 1.3 + +letting p be permutation((E1, E3, E4)) +letting sn be mset(E2, E3, E4) +language Essence 1.3 + +letting p be permutation((E1, E4, E2)) +letting sn be mset(E1, E3, E4) +language Essence 1.3 + +letting p be permutation((E1, E4, E3)) +letting sn be mset(E1, E2, E4) diff --git a/tests/custom/permutations/15_image_mset/int/0010_given_permutation_letting_mset/permutation.essence b/tests/custom/permutations/15_image_mset/int/0010_given_permutation_letting_mset/permutation.essence new file mode 100644 index 0000000000..f39709e521 --- /dev/null +++ b/tests/custom/permutations/15_image_mset/int/0010_given_permutation_letting_mset/permutation.essence @@ -0,0 +1,10 @@ +letting n be 4 + +given p : permutation of int(1..n) +given s : mset (size 4) of int(1..n) + +find sn : mset (size 4) of int(1..n) + + +such that sn = image(p,s) + diff --git a/tests/custom/permutations/15_image_mset/int/0010_given_permutation_letting_mset/permutation.param b/tests/custom/permutations/15_image_mset/int/0010_given_permutation_letting_mset/permutation.param new file mode 100644 index 0000000000..06bc926f80 --- /dev/null +++ b/tests/custom/permutations/15_image_mset/int/0010_given_permutation_letting_mset/permutation.param @@ -0,0 +1,2 @@ +letting p be permutation((1,3,4)) +letting s be mset(1,1,2,2) diff --git a/tests/custom/permutations/15_image_mset/int/0010_given_permutation_letting_mset/run.sh b/tests/custom/permutations/15_image_mset/int/0010_given_permutation_letting_mset/run.sh new file mode 100755 index 0000000000..9dc67e67f5 --- /dev/null +++ b/tests/custom/permutations/15_image_mset/int/0010_given_permutation_letting_mset/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence *.param +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/15_image_mset/int/0010_given_permutation_letting_mset/stdout.expected b/tests/custom/permutations/15_image_mset/int/0010_given_permutation_letting_mset/stdout.expected new file mode 100644 index 0000000000..116746b7a3 --- /dev/null +++ b/tests/custom/permutations/15_image_mset/int/0010_given_permutation_letting_mset/stdout.expected @@ -0,0 +1,8 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime permutation.param +Copying solution to: permutation-permutation.solution +language Essence 1.3 + +letting sn be mset(2, 2, 3, 3) diff --git a/tests/custom/permutations/15_image_mset/int/0020_given_permutation_find_msets/permutation.essence b/tests/custom/permutations/15_image_mset/int/0020_given_permutation_find_msets/permutation.essence new file mode 100644 index 0000000000..512a928f0f --- /dev/null +++ b/tests/custom/permutations/15_image_mset/int/0020_given_permutation_find_msets/permutation.essence @@ -0,0 +1,11 @@ +letting n be 4 + +given p : permutation of int(1..n) + +find s : mset (size 4) of int(1..n) + +find sn : mset (size 4) of int(1..n) + + +such that sn = image(p,s) + diff --git a/tests/custom/permutations/15_image_mset/int/0020_given_permutation_find_msets/permutation.param b/tests/custom/permutations/15_image_mset/int/0020_given_permutation_find_msets/permutation.param new file mode 100644 index 0000000000..8a8c516801 --- /dev/null +++ b/tests/custom/permutations/15_image_mset/int/0020_given_permutation_find_msets/permutation.param @@ -0,0 +1 @@ +letting p be permutation((1,3,4)) diff --git a/tests/custom/permutations/15_image_mset/int/0020_given_permutation_find_msets/run.sh b/tests/custom/permutations/15_image_mset/int/0020_given_permutation_find_msets/run.sh new file mode 100755 index 0000000000..aab5d44c6e --- /dev/null +++ b/tests/custom/permutations/15_image_mset/int/0020_given_permutation_find_msets/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence *.param --number-of-solutions=10 +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/15_image_mset/int/0020_given_permutation_find_msets/stdout.expected b/tests/custom/permutations/15_image_mset/int/0020_given_permutation_find_msets/stdout.expected new file mode 100644 index 0000000000..f6d27c0865 --- /dev/null +++ b/tests/custom/permutations/15_image_mset/int/0020_given_permutation_find_msets/stdout.expected @@ -0,0 +1,54 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime permutation.param +Copying solution to: permutation-permutation-000001.solution +Copying solution to: permutation-permutation-000002.solution +Copying solution to: permutation-permutation-000003.solution +Copying solution to: permutation-permutation-000004.solution +Copying solution to: permutation-permutation-000005.solution +Copying solution to: permutation-permutation-000006.solution +Copying solution to: permutation-permutation-000007.solution +Copying solution to: permutation-permutation-000008.solution +Copying solution to: permutation-permutation-000009.solution +Copying solution to: permutation-permutation-000010.solution +language Essence 1.3 + +letting s be mset(1, 2, 3, 4) +letting sn be mset(1, 2, 3, 4) +language Essence 1.3 + +letting s be mset(1, 2, 3, 3) +letting sn be mset(2, 3, 4, 4) +language Essence 1.3 + +letting s be mset(1, 2, 4, 4) +letting sn be mset(1, 1, 2, 3) +language Essence 1.3 + +letting s be mset(1, 3, 4, 4) +letting sn be mset(1, 1, 3, 4) +language Essence 1.3 + +letting s be mset(2, 3, 4, 4) +letting sn be mset(1, 1, 2, 4) +language Essence 1.3 + +letting s be mset(1, 2, 2, 3) +letting sn be mset(2, 2, 3, 4) +language Essence 1.3 + +letting s be mset(1, 2, 2, 4) +letting sn be mset(1, 2, 2, 3) +language Essence 1.3 + +letting s be mset(1, 3, 3, 4) +letting sn be mset(1, 3, 4, 4) +language Essence 1.3 + +letting s be mset(2, 3, 3, 4) +letting sn be mset(1, 2, 4, 4) +language Essence 1.3 + +letting s be mset(1, 2, 2, 2) +letting sn be mset(2, 2, 2, 3) diff --git a/tests/custom/permutations/15_image_mset/int/0030_letting_permutation_find_msets/permutation.essence b/tests/custom/permutations/15_image_mset/int/0030_letting_permutation_find_msets/permutation.essence new file mode 100644 index 0000000000..d69b86aa03 --- /dev/null +++ b/tests/custom/permutations/15_image_mset/int/0030_letting_permutation_find_msets/permutation.essence @@ -0,0 +1,11 @@ +letting n be 4 + +letting p be permutation((1,3,4)) + +find s : mset (size 4) of int(1..n) + +find sn : mset (size 4) of int(1..n) + + +such that sn = image(p,s) + diff --git a/tests/custom/permutations/15_image_mset/int/0030_letting_permutation_find_msets/run.sh b/tests/custom/permutations/15_image_mset/int/0030_letting_permutation_find_msets/run.sh new file mode 100755 index 0000000000..03373df6cb --- /dev/null +++ b/tests/custom/permutations/15_image_mset/int/0030_letting_permutation_find_msets/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence --number-of-solutions=10 +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/15_image_mset/int/0030_letting_permutation_find_msets/stdout.expected b/tests/custom/permutations/15_image_mset/int/0030_letting_permutation_find_msets/stdout.expected new file mode 100644 index 0000000000..87171190e1 --- /dev/null +++ b/tests/custom/permutations/15_image_mset/int/0030_letting_permutation_find_msets/stdout.expected @@ -0,0 +1,54 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Copying solution to: permutation-000001.solution +Copying solution to: permutation-000002.solution +Copying solution to: permutation-000003.solution +Copying solution to: permutation-000004.solution +Copying solution to: permutation-000005.solution +Copying solution to: permutation-000006.solution +Copying solution to: permutation-000007.solution +Copying solution to: permutation-000008.solution +Copying solution to: permutation-000009.solution +Copying solution to: permutation-000010.solution +language Essence 1.3 + +letting s be mset(1, 2, 3, 4) +letting sn be mset(1, 2, 3, 4) +language Essence 1.3 + +letting s be mset(1, 2, 3, 3) +letting sn be mset(2, 3, 4, 4) +language Essence 1.3 + +letting s be mset(1, 2, 4, 4) +letting sn be mset(1, 1, 2, 3) +language Essence 1.3 + +letting s be mset(1, 3, 4, 4) +letting sn be mset(1, 1, 3, 4) +language Essence 1.3 + +letting s be mset(2, 3, 4, 4) +letting sn be mset(1, 1, 2, 4) +language Essence 1.3 + +letting s be mset(1, 2, 2, 3) +letting sn be mset(2, 2, 3, 4) +language Essence 1.3 + +letting s be mset(1, 2, 2, 4) +letting sn be mset(1, 2, 2, 3) +language Essence 1.3 + +letting s be mset(1, 3, 3, 4) +letting sn be mset(1, 3, 4, 4) +language Essence 1.3 + +letting s be mset(2, 3, 3, 4) +letting sn be mset(1, 2, 4, 4) +language Essence 1.3 + +letting s be mset(1, 2, 2, 2) +letting sn be mset(2, 2, 2, 3) diff --git a/tests/custom/permutations/15_image_mset/int/0040_find_permutation_find_msets/permutation.essence b/tests/custom/permutations/15_image_mset/int/0040_find_permutation_find_msets/permutation.essence new file mode 100644 index 0000000000..930c052961 --- /dev/null +++ b/tests/custom/permutations/15_image_mset/int/0040_find_permutation_find_msets/permutation.essence @@ -0,0 +1,11 @@ +letting n be 4 + +find p : permutation of int(1..4) + +find s : mset (size 4) of int(1..n) + +find sn : mset (size 4) of int(1..n) + + +such that sn = image(p,s) /\ 3 = |p| + diff --git a/tests/custom/permutations/15_image_mset/int/0040_find_permutation_find_msets/run.sh b/tests/custom/permutations/15_image_mset/int/0040_find_permutation_find_msets/run.sh new file mode 100755 index 0000000000..03373df6cb --- /dev/null +++ b/tests/custom/permutations/15_image_mset/int/0040_find_permutation_find_msets/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence --number-of-solutions=10 +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/15_image_mset/int/0040_find_permutation_find_msets/stdout.expected b/tests/custom/permutations/15_image_mset/int/0040_find_permutation_find_msets/stdout.expected new file mode 100644 index 0000000000..c68ae1dd2d --- /dev/null +++ b/tests/custom/permutations/15_image_mset/int/0040_find_permutation_find_msets/stdout.expected @@ -0,0 +1,64 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Copying solution to: permutation-000001.solution +Copying solution to: permutation-000002.solution +Copying solution to: permutation-000003.solution +Copying solution to: permutation-000004.solution +Copying solution to: permutation-000005.solution +Copying solution to: permutation-000006.solution +Copying solution to: permutation-000007.solution +Copying solution to: permutation-000008.solution +Copying solution to: permutation-000009.solution +Copying solution to: permutation-000010.solution +language Essence 1.3 + +letting p be permutation((2, 3, 4)) +letting s be mset(1, 2, 3, 4) +letting sn be mset(1, 2, 3, 4) +language Essence 1.3 + +letting p be permutation((2, 3, 4)) +letting s be mset(1, 2, 3, 3) +letting sn be mset(1, 3, 4, 4) +language Essence 1.3 + +letting p be permutation((2, 3, 4)) +letting s be mset(1, 2, 4, 4) +letting sn be mset(1, 2, 2, 3) +language Essence 1.3 + +letting p be permutation((2, 3, 4)) +letting s be mset(1, 3, 4, 4) +letting sn be mset(1, 2, 2, 4) +language Essence 1.3 + +letting p be permutation((2, 3, 4)) +letting s be mset(2, 3, 4, 4) +letting sn be mset(2, 2, 3, 4) +language Essence 1.3 + +letting p be permutation((2, 3, 4)) +letting s be mset(1, 2, 2, 3) +letting sn be mset(1, 3, 3, 4) +language Essence 1.3 + +letting p be permutation((2, 3, 4)) +letting s be mset(1, 2, 2, 4) +letting sn be mset(1, 2, 3, 3) +language Essence 1.3 + +letting p be permutation((2, 3, 4)) +letting s be mset(1, 3, 3, 4) +letting sn be mset(1, 2, 4, 4) +language Essence 1.3 + +letting p be permutation((2, 3, 4)) +letting s be mset(2, 3, 3, 4) +letting sn be mset(2, 3, 4, 4) +language Essence 1.3 + +letting p be permutation((2, 3, 4)) +letting s be mset(1, 2, 2, 2) +letting sn be mset(1, 3, 3, 3) diff --git a/tests/custom/permutations/15_image_mset/int/0050_find_permutation_given_mset_find_mset/permutation.essence b/tests/custom/permutations/15_image_mset/int/0050_find_permutation_given_mset_find_mset/permutation.essence new file mode 100644 index 0000000000..58d3abf762 --- /dev/null +++ b/tests/custom/permutations/15_image_mset/int/0050_find_permutation_given_mset_find_mset/permutation.essence @@ -0,0 +1,11 @@ +letting n be 4 + +find p : permutation of int(1..4) + +given s : mset (size 3) of int(1..n) + +find sn : mset (size 3) of int(1..n) + + +such that sn = image(p,s) /\ (3 = sum([ toInt(l != r) | (l, r) <- p])) + diff --git a/tests/custom/permutations/15_image_mset/int/0050_find_permutation_given_mset_find_mset/permutation.param b/tests/custom/permutations/15_image_mset/int/0050_find_permutation_given_mset_find_mset/permutation.param new file mode 100644 index 0000000000..b6b3f18fa6 --- /dev/null +++ b/tests/custom/permutations/15_image_mset/int/0050_find_permutation_given_mset_find_mset/permutation.param @@ -0,0 +1 @@ +letting s be mset(1,2,3) diff --git a/tests/custom/permutations/15_image_mset/int/0050_find_permutation_given_mset_find_mset/run.sh b/tests/custom/permutations/15_image_mset/int/0050_find_permutation_given_mset_find_mset/run.sh new file mode 100755 index 0000000000..aab5d44c6e --- /dev/null +++ b/tests/custom/permutations/15_image_mset/int/0050_find_permutation_given_mset_find_mset/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence *.param --number-of-solutions=10 +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/15_image_mset/int/0050_find_permutation_given_mset_find_mset/stdout.expected b/tests/custom/permutations/15_image_mset/int/0050_find_permutation_given_mset_find_mset/stdout.expected new file mode 100644 index 0000000000..3419c537e4 --- /dev/null +++ b/tests/custom/permutations/15_image_mset/int/0050_find_permutation_given_mset_find_mset/stdout.expected @@ -0,0 +1,44 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime permutation.param +Copying solution to: permutation-permutation-000001.solution +Copying solution to: permutation-permutation-000002.solution +Copying solution to: permutation-permutation-000003.solution +Copying solution to: permutation-permutation-000004.solution +Copying solution to: permutation-permutation-000005.solution +Copying solution to: permutation-permutation-000006.solution +Copying solution to: permutation-permutation-000007.solution +Copying solution to: permutation-permutation-000008.solution +language Essence 1.3 + +letting p be permutation((2, 3, 4)) +letting sn be mset(1, 3, 4) +language Essence 1.3 + +letting p be permutation((2, 4, 3)) +letting sn be mset(1, 2, 4) +language Essence 1.3 + +letting p be permutation((1, 2, 3)) +letting sn be mset(1, 2, 3) +language Essence 1.3 + +letting p be permutation((1, 2, 4)) +letting sn be mset(2, 3, 4) +language Essence 1.3 + +letting p be permutation((1, 3, 2)) +letting sn be mset(1, 2, 3) +language Essence 1.3 + +letting p be permutation((1, 3, 4)) +letting sn be mset(2, 3, 4) +language Essence 1.3 + +letting p be permutation((1, 4, 2)) +letting sn be mset(1, 3, 4) +language Essence 1.3 + +letting p be permutation((1, 4, 3)) +letting sn be mset(1, 2, 4) diff --git a/tests/custom/permutations/15_image_mset/runthese.sh b/tests/custom/permutations/15_image_mset/runthese.sh new file mode 100644 index 0000000000..a816234e2e --- /dev/null +++ b/tests/custom/permutations/15_image_mset/runthese.sh @@ -0,0 +1 @@ +stack build --copy-bins --test --test-arguments "-p custom.permutations.15_image_mset" diff --git a/tests/custom/permutations/15_image_mset/unnamed/0004_find_permutation_find_sets/permutation.essence b/tests/custom/permutations/15_image_mset/unnamed/0004_find_permutation_find_sets/permutation.essence new file mode 100644 index 0000000000..afba9a0bae --- /dev/null +++ b/tests/custom/permutations/15_image_mset/unnamed/0004_find_permutation_find_sets/permutation.essence @@ -0,0 +1,11 @@ +letting n be new type of size 4 + +find p : permutation of n + +find s : mset (size 4) of n + +find sn : mset (size 4) of n + + +such that sn = image(p,s) /\ (3 = sum([ toInt(l != r) | (l, r) <- p])) + diff --git a/tests/custom/permutations/15_image_mset/unnamed/0004_find_permutation_find_sets/run.sh b/tests/custom/permutations/15_image_mset/unnamed/0004_find_permutation_find_sets/run.sh new file mode 100755 index 0000000000..03373df6cb --- /dev/null +++ b/tests/custom/permutations/15_image_mset/unnamed/0004_find_permutation_find_sets/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence --number-of-solutions=10 +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/15_image_mset/unnamed/0004_find_permutation_find_sets/stdout.expected b/tests/custom/permutations/15_image_mset/unnamed/0004_find_permutation_find_sets/stdout.expected new file mode 100644 index 0000000000..1309113e68 --- /dev/null +++ b/tests/custom/permutations/15_image_mset/unnamed/0004_find_permutation_find_sets/stdout.expected @@ -0,0 +1,74 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Copying solution to: permutation-000001.solution +Copying solution to: permutation-000002.solution +Copying solution to: permutation-000003.solution +Copying solution to: permutation-000004.solution +Copying solution to: permutation-000005.solution +Copying solution to: permutation-000006.solution +Copying solution to: permutation-000007.solution +Copying solution to: permutation-000008.solution +Copying solution to: permutation-000009.solution +Copying solution to: permutation-000010.solution +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_2, n_3, n_4)) +letting s be mset(n_1, n_2, n_3, n_4) +letting sn be mset(n_1, n_2, n_3, n_4) +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_2, n_3, n_4)) +letting s be mset(n_1, n_2, n_3, n_3) +letting sn be mset(n_1, n_3, n_4, n_4) +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_2, n_3, n_4)) +letting s be mset(n_1, n_2, n_4, n_4) +letting sn be mset(n_1, n_2, n_2, n_3) +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_2, n_3, n_4)) +letting s be mset(n_1, n_3, n_4, n_4) +letting sn be mset(n_1, n_2, n_2, n_4) +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_2, n_3, n_4)) +letting s be mset(n_2, n_3, n_4, n_4) +letting sn be mset(n_2, n_2, n_3, n_4) +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_2, n_3, n_4)) +letting s be mset(n_1, n_2, n_2, n_3) +letting sn be mset(n_1, n_3, n_3, n_4) +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_2, n_3, n_4)) +letting s be mset(n_1, n_2, n_2, n_4) +letting sn be mset(n_1, n_2, n_3, n_3) +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_2, n_3, n_4)) +letting s be mset(n_1, n_3, n_3, n_4) +letting sn be mset(n_1, n_2, n_4, n_4) +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_2, n_3, n_4)) +letting s be mset(n_2, n_3, n_3, n_4) +letting sn be mset(n_2, n_3, n_4, n_4) +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_2, n_3, n_4)) +letting s be mset(n_1, n_2, n_2, n_2) +letting sn be mset(n_1, n_3, n_3, n_3) From 5272e300e66e230b376facc05b29779a38d21d8b Mon Sep 17 00:00:00 2001 From: Fraser Dunlop Date: Sat, 5 Jan 2019 13:55:31 +0000 Subject: [PATCH 062/229] Added image of permutation tests + fixed compose + eq bugs --- src/Conjure/Language/Expression/Op/Compose.hs | 25 +++---- src/Conjure/Rules/Horizontal/Permutation.hs | 9 +-- src/Conjure/Rules/Vertical/Permutation.hs | 2 +- .../permutation.essence | 4 + .../int/0007_letting_equal_letting/run.sh | 3 + .../stdout.expected | 8 ++ .../permutations/05_equality/int/new.essence | 4 + .../int/0005_find_composition/stdout.expected | 6 +- .../int/0006_find_composition/stdout.expected | 2 +- .../permutation.essence | 0 .../run.sh | 0 .../stdout.expected | 0 .../permutation.essence | 9 +++ .../permutation.param | 2 + .../run.sh | 3 + .../stdout.expected | 8 ++ .../permutation.essence | 11 +++ .../permutation.param | 1 + .../run.sh | 3 + .../stdout.expected | 54 ++++++++++++++ .../permutation.essence | 11 +++ .../run.sh | 3 + .../stdout.expected | 54 ++++++++++++++ .../permutation.essence | 11 +++ .../run.sh | 3 + .../stdout.expected | 64 ++++++++++++++++ .../permutation.essence | 11 +++ .../permutation.param | 1 + .../run.sh | 3 + .../stdout.expected | 54 ++++++++++++++ .../permutation.essence | 10 +++ .../permutation.param | 2 + .../run.sh | 3 + .../stdout.expected | 8 ++ .../permutation.essence | 11 +++ .../permutation.param | 1 + .../run.sh | 3 + .../stdout.expected | 54 ++++++++++++++ .../permutation.essence | 11 +++ .../run.sh | 3 + .../stdout.expected | 54 ++++++++++++++ .../permutation.essence | 11 +++ .../run.sh | 3 + .../stdout.expected | 64 ++++++++++++++++ .../permutation.essence | 11 +++ .../permutation.param | 1 + .../run.sh | 3 + .../stdout.expected | 54 ++++++++++++++ .../16_image_permutation/runthese.sh | 1 + .../permutation.essence | 11 +++ .../run.sh | 3 + .../stdout.expected | 74 +++++++++++++++++++ 52 files changed, 737 insertions(+), 28 deletions(-) create mode 100644 tests/custom/permutations/05_equality/int/0007_letting_equal_letting/permutation.essence create mode 100755 tests/custom/permutations/05_equality/int/0007_letting_equal_letting/run.sh create mode 100644 tests/custom/permutations/05_equality/int/0007_letting_equal_letting/stdout.expected create mode 100644 tests/custom/permutations/05_equality/int/new.essence rename tests/custom/permutations/15_image_mset/unnamed/{0004_find_permutation_find_sets => 0004_find_permutation_find_msets}/permutation.essence (100%) rename tests/custom/permutations/15_image_mset/unnamed/{0004_find_permutation_find_sets => 0004_find_permutation_find_msets}/run.sh (100%) rename tests/custom/permutations/15_image_mset/unnamed/{0004_find_permutation_find_sets => 0004_find_permutation_find_msets}/stdout.expected (100%) create mode 100644 tests/custom/permutations/16_image_permutation/enum/0010_given_permutation_letting_permutation/permutation.essence create mode 100644 tests/custom/permutations/16_image_permutation/enum/0010_given_permutation_letting_permutation/permutation.param create mode 100755 tests/custom/permutations/16_image_permutation/enum/0010_given_permutation_letting_permutation/run.sh create mode 100644 tests/custom/permutations/16_image_permutation/enum/0010_given_permutation_letting_permutation/stdout.expected create mode 100644 tests/custom/permutations/16_image_permutation/enum/0020_given_permutation_find_permutations/permutation.essence create mode 100644 tests/custom/permutations/16_image_permutation/enum/0020_given_permutation_find_permutations/permutation.param create mode 100755 tests/custom/permutations/16_image_permutation/enum/0020_given_permutation_find_permutations/run.sh create mode 100644 tests/custom/permutations/16_image_permutation/enum/0020_given_permutation_find_permutations/stdout.expected create mode 100644 tests/custom/permutations/16_image_permutation/enum/0030_letting_permutation_find_permutations/permutation.essence create mode 100755 tests/custom/permutations/16_image_permutation/enum/0030_letting_permutation_find_permutations/run.sh create mode 100644 tests/custom/permutations/16_image_permutation/enum/0030_letting_permutation_find_permutations/stdout.expected create mode 100644 tests/custom/permutations/16_image_permutation/enum/0040_find_permutation_find_permutations/permutation.essence create mode 100755 tests/custom/permutations/16_image_permutation/enum/0040_find_permutation_find_permutations/run.sh create mode 100644 tests/custom/permutations/16_image_permutation/enum/0040_find_permutation_find_permutations/stdout.expected create mode 100644 tests/custom/permutations/16_image_permutation/enum/0050_find_permutation_given_permutation_find_permutation/permutation.essence create mode 100644 tests/custom/permutations/16_image_permutation/enum/0050_find_permutation_given_permutation_find_permutation/permutation.param create mode 100755 tests/custom/permutations/16_image_permutation/enum/0050_find_permutation_given_permutation_find_permutation/run.sh create mode 100644 tests/custom/permutations/16_image_permutation/enum/0050_find_permutation_given_permutation_find_permutation/stdout.expected create mode 100644 tests/custom/permutations/16_image_permutation/int/0010_given_permutation_letting_permutation/permutation.essence create mode 100644 tests/custom/permutations/16_image_permutation/int/0010_given_permutation_letting_permutation/permutation.param create mode 100755 tests/custom/permutations/16_image_permutation/int/0010_given_permutation_letting_permutation/run.sh create mode 100644 tests/custom/permutations/16_image_permutation/int/0010_given_permutation_letting_permutation/stdout.expected create mode 100644 tests/custom/permutations/16_image_permutation/int/0020_given_permutation_find_permutations/permutation.essence create mode 100644 tests/custom/permutations/16_image_permutation/int/0020_given_permutation_find_permutations/permutation.param create mode 100755 tests/custom/permutations/16_image_permutation/int/0020_given_permutation_find_permutations/run.sh create mode 100644 tests/custom/permutations/16_image_permutation/int/0020_given_permutation_find_permutations/stdout.expected create mode 100644 tests/custom/permutations/16_image_permutation/int/0030_letting_permutation_find_permutations/permutation.essence create mode 100755 tests/custom/permutations/16_image_permutation/int/0030_letting_permutation_find_permutations/run.sh create mode 100644 tests/custom/permutations/16_image_permutation/int/0030_letting_permutation_find_permutations/stdout.expected create mode 100644 tests/custom/permutations/16_image_permutation/int/0040_find_permutation_find_permutations/permutation.essence create mode 100755 tests/custom/permutations/16_image_permutation/int/0040_find_permutation_find_permutations/run.sh create mode 100644 tests/custom/permutations/16_image_permutation/int/0040_find_permutation_find_permutations/stdout.expected create mode 100644 tests/custom/permutations/16_image_permutation/int/0050_find_permutation_given_permutation_find_permutation/permutation.essence create mode 100644 tests/custom/permutations/16_image_permutation/int/0050_find_permutation_given_permutation_find_permutation/permutation.param create mode 100755 tests/custom/permutations/16_image_permutation/int/0050_find_permutation_given_permutation_find_permutation/run.sh create mode 100644 tests/custom/permutations/16_image_permutation/int/0050_find_permutation_given_permutation_find_permutation/stdout.expected create mode 100644 tests/custom/permutations/16_image_permutation/runthese.sh create mode 100644 tests/custom/permutations/16_image_permutation/unnamed/0004_find_permutation_find_permutations/permutation.essence create mode 100755 tests/custom/permutations/16_image_permutation/unnamed/0004_find_permutation_find_permutations/run.sh create mode 100644 tests/custom/permutations/16_image_permutation/unnamed/0004_find_permutation_find_permutations/stdout.expected diff --git a/src/Conjure/Language/Expression/Op/Compose.hs b/src/Conjure/Language/Expression/Op/Compose.hs index 37e63fc82e..36d249da41 100644 --- a/src/Conjure/Language/Expression/Op/Compose.hs +++ b/src/Conjure/Language/Expression/Op/Compose.hs @@ -4,13 +4,15 @@ module Conjure.Language.Expression.Op.Compose where import Conjure.Prelude import Conjure.Language.Expression.Op.Internal.Common -import Conjure.Bug import qualified Data.Aeson as JSON -- aeson import qualified Data.HashMap.Strict as M -- unordered-containers import qualified Data.Vector as V -- vector -import Data.List (cycle) +import Data.Permutation + +import qualified Data.Semigroup as SG + data OpCompose x = OpCompose x x deriving (Eq, Ord, Show, Data, Functor, Traversable, Foldable, Typeable, Generic) @@ -32,18 +34,13 @@ instance (TypeOf x, Pretty x) => TypeOf (OpCompose x) where _ -> raiseTypeError inp instance EvaluateOp OpCompose where - evaluateOp op@(OpCompose g@(viewConstantPermutation -> Just gss) - h@(viewConstantPermutation -> Just hss)) = do - gt <- typeOf g - ht <- typeOf h - case (gt, ht) of - (TypePermutation (TypeInt _), TypePermutation (TypeInt _)) -> - let appI xss i = case filter (i `elem`) xss of - [] -> return i - [k] -> return $ head $ drop 1 $ dropWhile (/= i) $ cycle k - _ -> bug "evaluateOp{OpCompose} element should only be in one cycle of permutation" - in ConstantAbstract . AbsLitPermutation <$> (mapM (mapM (appI gss)) hss) - _ -> na $ "evaluateOp{OpCompose} only defined for Ints right now:" <++> pretty (show op) + evaluateOp (OpCompose (viewConstantPermutation -> Just gss) + (viewConstantPermutation -> Just hss)) = do + case (fromCycles gss, fromCycles hss) of + (Right g, Right h) -> + return $ ConstantAbstract $ AbsLitPermutation $ toCycles $ g SG.<> h + (Left e, _) -> fail $ "evaluateOp{OpCompose}" <++> pretty (show e) + (_, Left e) -> fail $ "evaluateOp{OpCompose}" <++> pretty (show e) evaluateOp op = na $ "evaluateOp{OpCompose}:" <++> pretty (show op) instance SimplifyOp OpCompose x where diff --git a/src/Conjure/Rules/Horizontal/Permutation.hs b/src/Conjure/Rules/Horizontal/Permutation.hs index 2884feebe2..65b80e234f 100644 --- a/src/Conjure/Rules/Horizontal/Permutation.hs +++ b/src/Conjure/Rules/Horizontal/Permutation.hs @@ -25,12 +25,7 @@ rule_Equality = "permutation-equality" `namedRule` theRule where TypePermutation{} <- typeOf p TypePermutation{} <- typeOf q return ( "Horizontal rule for permutation equality" - , do - (rPat, r) <- quantifiedVar - (lPat, l) <- quantifiedVar - return [essence| and([ 1 = sum([ toInt(&r = &l) - | &lPat <- &p]) - | &rPat <- &q]) |] + , return [essence| toSet(&p) = toSet(&q) |] ) @@ -38,7 +33,7 @@ rule_Comprehension :: Rule rule_Comprehension = "permutation-comprehension" `namedRule` theRule where theRule (Comprehension body gensOrConds) = do (gocBefore, (pat, perm), gocAfter) <- matchFirst gensOrConds $ \ goc -> case goc of - Generator (GenInExpr pat [essence| &perm |] ) -> return (pat, perm) + Generator (GenInExpr pat expr) -> return (pat, matchDefs [opToSet] expr) _ -> na "rule_Comprehension" (TypePermutation inner, elems) <- match permutationLiteral perm DomainPermutation _ _ innerD <- domainOf perm diff --git a/src/Conjure/Rules/Vertical/Permutation.hs b/src/Conjure/Rules/Vertical/Permutation.hs index 6a5e6bb031..b6c1df7ccb 100644 --- a/src/Conjure/Rules/Vertical/Permutation.hs +++ b/src/Conjure/Rules/Vertical/Permutation.hs @@ -38,7 +38,7 @@ rule_Comprehension :: Rule rule_Comprehension = "permutation-comprehension-tuples{AsFunction}" `namedRule` theRule where theRule (Comprehension body gensOrConds) = do (gocBefore, (pat, perm), gocAfter) <- matchFirst gensOrConds $ \ goc -> case goc of - Generator (GenInExpr pat [essence| &perm |] ) -> return (pat, perm) + Generator (GenInExpr pat expr) -> return (pat, matchDefs [opToSet] expr) _ -> na "rule_Comprehension" TypePermutation{} <- typeOf perm Permutation_AsFunction <- representationOf perm diff --git a/tests/custom/permutations/05_equality/int/0007_letting_equal_letting/permutation.essence b/tests/custom/permutations/05_equality/int/0007_letting_equal_letting/permutation.essence new file mode 100644 index 0000000000..77fdcef849 --- /dev/null +++ b/tests/custom/permutations/05_equality/int/0007_letting_equal_letting/permutation.essence @@ -0,0 +1,4 @@ +letting s be permutation((3, 4)) +letting sn be permutation((1, 4), (2, 3)) +find b : bool +such that b = (s = sn) diff --git a/tests/custom/permutations/05_equality/int/0007_letting_equal_letting/run.sh b/tests/custom/permutations/05_equality/int/0007_letting_equal_letting/run.sh new file mode 100755 index 0000000000..b4899d6266 --- /dev/null +++ b/tests/custom/permutations/05_equality/int/0007_letting_equal_letting/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/05_equality/int/0007_letting_equal_letting/stdout.expected b/tests/custom/permutations/05_equality/int/0007_letting_equal_letting/stdout.expected new file mode 100644 index 0000000000..587753f3d2 --- /dev/null +++ b/tests/custom/permutations/05_equality/int/0007_letting_equal_letting/stdout.expected @@ -0,0 +1,8 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Copying solution to: permutation.solution +language Essence 1.3 + +letting b be false diff --git a/tests/custom/permutations/05_equality/int/new.essence b/tests/custom/permutations/05_equality/int/new.essence new file mode 100644 index 0000000000..77fdcef849 --- /dev/null +++ b/tests/custom/permutations/05_equality/int/new.essence @@ -0,0 +1,4 @@ +letting s be permutation((3, 4)) +letting sn be permutation((1, 4), (2, 3)) +find b : bool +such that b = (s = sn) diff --git a/tests/custom/permutations/07_compose/int/0005_find_composition/stdout.expected b/tests/custom/permutations/07_compose/int/0005_find_composition/stdout.expected index c308909413..d041d90c1a 100644 --- a/tests/custom/permutations/07_compose/int/0005_find_composition/stdout.expected +++ b/tests/custom/permutations/07_compose/int/0005_find_composition/stdout.expected @@ -2,11 +2,7 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output Savile Row: model000001.eprime -Copying solution to: permutation-000001.solution -Copying solution to: permutation-000002.solution -language Essence 1.3 - -letting c be permutation((1, 2)) +Copying solution to: permutation.solution language Essence 1.3 letting c be permutation((1, 2), (3, 4)) diff --git a/tests/custom/permutations/07_compose/int/0006_find_composition/stdout.expected b/tests/custom/permutations/07_compose/int/0006_find_composition/stdout.expected index 44eece037a..496da0634a 100644 --- a/tests/custom/permutations/07_compose/int/0006_find_composition/stdout.expected +++ b/tests/custom/permutations/07_compose/int/0006_find_composition/stdout.expected @@ -5,4 +5,4 @@ Savile Row: model000001.eprime Copying solution to: permutation.solution language Essence 1.3 -letting c be permutation((1, 2, 4)) +letting c be permutation((1, 2, 4, 3)) diff --git a/tests/custom/permutations/15_image_mset/unnamed/0004_find_permutation_find_sets/permutation.essence b/tests/custom/permutations/15_image_mset/unnamed/0004_find_permutation_find_msets/permutation.essence similarity index 100% rename from tests/custom/permutations/15_image_mset/unnamed/0004_find_permutation_find_sets/permutation.essence rename to tests/custom/permutations/15_image_mset/unnamed/0004_find_permutation_find_msets/permutation.essence diff --git a/tests/custom/permutations/15_image_mset/unnamed/0004_find_permutation_find_sets/run.sh b/tests/custom/permutations/15_image_mset/unnamed/0004_find_permutation_find_msets/run.sh similarity index 100% rename from tests/custom/permutations/15_image_mset/unnamed/0004_find_permutation_find_sets/run.sh rename to tests/custom/permutations/15_image_mset/unnamed/0004_find_permutation_find_msets/run.sh diff --git a/tests/custom/permutations/15_image_mset/unnamed/0004_find_permutation_find_sets/stdout.expected b/tests/custom/permutations/15_image_mset/unnamed/0004_find_permutation_find_msets/stdout.expected similarity index 100% rename from tests/custom/permutations/15_image_mset/unnamed/0004_find_permutation_find_sets/stdout.expected rename to tests/custom/permutations/15_image_mset/unnamed/0004_find_permutation_find_msets/stdout.expected diff --git a/tests/custom/permutations/16_image_permutation/enum/0010_given_permutation_letting_permutation/permutation.essence b/tests/custom/permutations/16_image_permutation/enum/0010_given_permutation_letting_permutation/permutation.essence new file mode 100644 index 0000000000..a3081ab099 --- /dev/null +++ b/tests/custom/permutations/16_image_permutation/enum/0010_given_permutation_letting_permutation/permutation.essence @@ -0,0 +1,9 @@ +letting n be new type enum {E1,E2,E3,E4} + +given p : permutation of n +given s : permutation of n +find sn : permutation of n + + +such that sn = image(p,s) + diff --git a/tests/custom/permutations/16_image_permutation/enum/0010_given_permutation_letting_permutation/permutation.param b/tests/custom/permutations/16_image_permutation/enum/0010_given_permutation_letting_permutation/permutation.param new file mode 100644 index 0000000000..83ff642a8c --- /dev/null +++ b/tests/custom/permutations/16_image_permutation/enum/0010_given_permutation_letting_permutation/permutation.param @@ -0,0 +1,2 @@ +letting p be permutation((E1,E3)) +letting s be permutation((E1,E2),(E3,E4)) diff --git a/tests/custom/permutations/16_image_permutation/enum/0010_given_permutation_letting_permutation/run.sh b/tests/custom/permutations/16_image_permutation/enum/0010_given_permutation_letting_permutation/run.sh new file mode 100755 index 0000000000..9dc67e67f5 --- /dev/null +++ b/tests/custom/permutations/16_image_permutation/enum/0010_given_permutation_letting_permutation/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence *.param +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/16_image_permutation/enum/0010_given_permutation_letting_permutation/stdout.expected b/tests/custom/permutations/16_image_permutation/enum/0010_given_permutation_letting_permutation/stdout.expected new file mode 100644 index 0000000000..1ae9c33dae --- /dev/null +++ b/tests/custom/permutations/16_image_permutation/enum/0010_given_permutation_letting_permutation/stdout.expected @@ -0,0 +1,8 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime permutation.param +Copying solution to: permutation-permutation.solution +language Essence 1.3 + +letting sn be permutation((E1, E4), (E2, E3)) diff --git a/tests/custom/permutations/16_image_permutation/enum/0020_given_permutation_find_permutations/permutation.essence b/tests/custom/permutations/16_image_permutation/enum/0020_given_permutation_find_permutations/permutation.essence new file mode 100644 index 0000000000..48bac35241 --- /dev/null +++ b/tests/custom/permutations/16_image_permutation/enum/0020_given_permutation_find_permutations/permutation.essence @@ -0,0 +1,11 @@ +letting n be new type enum {E1,E2,E3,E4} + +given p : permutation of n + +find s : permutation of n + +find sn : permutation of n + + +such that sn = image(p,s) /\ sn != s /\ |s| > 0 + diff --git a/tests/custom/permutations/16_image_permutation/enum/0020_given_permutation_find_permutations/permutation.param b/tests/custom/permutations/16_image_permutation/enum/0020_given_permutation_find_permutations/permutation.param new file mode 100644 index 0000000000..19349bb872 --- /dev/null +++ b/tests/custom/permutations/16_image_permutation/enum/0020_given_permutation_find_permutations/permutation.param @@ -0,0 +1 @@ +letting p be permutation((E1,E3,E4)) diff --git a/tests/custom/permutations/16_image_permutation/enum/0020_given_permutation_find_permutations/run.sh b/tests/custom/permutations/16_image_permutation/enum/0020_given_permutation_find_permutations/run.sh new file mode 100755 index 0000000000..aab5d44c6e --- /dev/null +++ b/tests/custom/permutations/16_image_permutation/enum/0020_given_permutation_find_permutations/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence *.param --number-of-solutions=10 +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/16_image_permutation/enum/0020_given_permutation_find_permutations/stdout.expected b/tests/custom/permutations/16_image_permutation/enum/0020_given_permutation_find_permutations/stdout.expected new file mode 100644 index 0000000000..bf0321c3a7 --- /dev/null +++ b/tests/custom/permutations/16_image_permutation/enum/0020_given_permutation_find_permutations/stdout.expected @@ -0,0 +1,54 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime permutation.param +Copying solution to: permutation-permutation-000001.solution +Copying solution to: permutation-permutation-000002.solution +Copying solution to: permutation-permutation-000003.solution +Copying solution to: permutation-permutation-000004.solution +Copying solution to: permutation-permutation-000005.solution +Copying solution to: permutation-permutation-000006.solution +Copying solution to: permutation-permutation-000007.solution +Copying solution to: permutation-permutation-000008.solution +Copying solution to: permutation-permutation-000009.solution +Copying solution to: permutation-permutation-000010.solution +language Essence 1.3 + +letting s be permutation((E3, E4)) +letting sn be permutation((E1, E4)) +language Essence 1.3 + +letting s be permutation((E2, E3)) +letting sn be permutation((E2, E4)) +language Essence 1.3 + +letting s be permutation((E2, E3, E4)) +letting sn be permutation((E1, E2, E4)) +language Essence 1.3 + +letting s be permutation((E2, E4, E3)) +letting sn be permutation((E1, E4, E2)) +language Essence 1.3 + +letting s be permutation((E2, E4)) +letting sn be permutation((E1, E2)) +language Essence 1.3 + +letting s be permutation((E1, E2)) +letting sn be permutation((E2, E3)) +language Essence 1.3 + +letting s be permutation((E1, E2), (E3, E4)) +letting sn be permutation((E1, E4), (E2, E3)) +language Essence 1.3 + +letting s be permutation((E1, E2, E3)) +letting sn be permutation((E2, E4, E3)) +language Essence 1.3 + +letting s be permutation((E1, E2, E3, E4)) +letting sn be permutation((E1, E3, E2, E4)) +language Essence 1.3 + +letting s be permutation((E1, E2, E4, E3)) +letting sn be permutation((E1, E4, E3, E2)) diff --git a/tests/custom/permutations/16_image_permutation/enum/0030_letting_permutation_find_permutations/permutation.essence b/tests/custom/permutations/16_image_permutation/enum/0030_letting_permutation_find_permutations/permutation.essence new file mode 100644 index 0000000000..f91391eafd --- /dev/null +++ b/tests/custom/permutations/16_image_permutation/enum/0030_letting_permutation_find_permutations/permutation.essence @@ -0,0 +1,11 @@ +letting n be new type enum {E1,E2,E3,E4} + +letting p be permutation((E1,E3,E4)) + +find s : permutation of n + +find sn : permutation of n + + +such that sn = image(p,s) + diff --git a/tests/custom/permutations/16_image_permutation/enum/0030_letting_permutation_find_permutations/run.sh b/tests/custom/permutations/16_image_permutation/enum/0030_letting_permutation_find_permutations/run.sh new file mode 100755 index 0000000000..03373df6cb --- /dev/null +++ b/tests/custom/permutations/16_image_permutation/enum/0030_letting_permutation_find_permutations/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence --number-of-solutions=10 +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/16_image_permutation/enum/0030_letting_permutation_find_permutations/stdout.expected b/tests/custom/permutations/16_image_permutation/enum/0030_letting_permutation_find_permutations/stdout.expected new file mode 100644 index 0000000000..2058ad9727 --- /dev/null +++ b/tests/custom/permutations/16_image_permutation/enum/0030_letting_permutation_find_permutations/stdout.expected @@ -0,0 +1,54 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Copying solution to: permutation-000001.solution +Copying solution to: permutation-000002.solution +Copying solution to: permutation-000003.solution +Copying solution to: permutation-000004.solution +Copying solution to: permutation-000005.solution +Copying solution to: permutation-000006.solution +Copying solution to: permutation-000007.solution +Copying solution to: permutation-000008.solution +Copying solution to: permutation-000009.solution +Copying solution to: permutation-000010.solution +language Essence 1.3 + +letting s be permutation() +letting sn be permutation() +language Essence 1.3 + +letting s be permutation((E3, E4)) +letting sn be permutation((E1, E4)) +language Essence 1.3 + +letting s be permutation((E2, E3)) +letting sn be permutation((E2, E4)) +language Essence 1.3 + +letting s be permutation((E2, E3, E4)) +letting sn be permutation((E1, E2, E4)) +language Essence 1.3 + +letting s be permutation((E2, E4, E3)) +letting sn be permutation((E1, E4, E2)) +language Essence 1.3 + +letting s be permutation((E2, E4)) +letting sn be permutation((E1, E2)) +language Essence 1.3 + +letting s be permutation((E1, E2)) +letting sn be permutation((E2, E3)) +language Essence 1.3 + +letting s be permutation((E1, E2), (E3, E4)) +letting sn be permutation((E1, E4), (E2, E3)) +language Essence 1.3 + +letting s be permutation((E1, E2, E3)) +letting sn be permutation((E2, E4, E3)) +language Essence 1.3 + +letting s be permutation((E1, E2, E3, E4)) +letting sn be permutation((E1, E3, E2, E4)) diff --git a/tests/custom/permutations/16_image_permutation/enum/0040_find_permutation_find_permutations/permutation.essence b/tests/custom/permutations/16_image_permutation/enum/0040_find_permutation_find_permutations/permutation.essence new file mode 100644 index 0000000000..0541d6385b --- /dev/null +++ b/tests/custom/permutations/16_image_permutation/enum/0040_find_permutation_find_permutations/permutation.essence @@ -0,0 +1,11 @@ +letting n be new type enum {E1,E2,E3,E4} + +find p : permutation of n + +find s : permutation of n + +find sn : permutation of n + + +such that sn = image(p,s) /\ 3 = |p| + diff --git a/tests/custom/permutations/16_image_permutation/enum/0040_find_permutation_find_permutations/run.sh b/tests/custom/permutations/16_image_permutation/enum/0040_find_permutation_find_permutations/run.sh new file mode 100755 index 0000000000..03373df6cb --- /dev/null +++ b/tests/custom/permutations/16_image_permutation/enum/0040_find_permutation_find_permutations/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence --number-of-solutions=10 +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/16_image_permutation/enum/0040_find_permutation_find_permutations/stdout.expected b/tests/custom/permutations/16_image_permutation/enum/0040_find_permutation_find_permutations/stdout.expected new file mode 100644 index 0000000000..b738675525 --- /dev/null +++ b/tests/custom/permutations/16_image_permutation/enum/0040_find_permutation_find_permutations/stdout.expected @@ -0,0 +1,64 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Copying solution to: permutation-000001.solution +Copying solution to: permutation-000002.solution +Copying solution to: permutation-000003.solution +Copying solution to: permutation-000004.solution +Copying solution to: permutation-000005.solution +Copying solution to: permutation-000006.solution +Copying solution to: permutation-000007.solution +Copying solution to: permutation-000008.solution +Copying solution to: permutation-000009.solution +Copying solution to: permutation-000010.solution +language Essence 1.3 + +letting p be permutation((E2, E3, E4)) +letting s be permutation() +letting sn be permutation() +language Essence 1.3 + +letting p be permutation((E2, E3, E4)) +letting s be permutation((E3, E4)) +letting sn be permutation((E2, E4)) +language Essence 1.3 + +letting p be permutation((E2, E3, E4)) +letting s be permutation((E2, E3)) +letting sn be permutation((E3, E4)) +language Essence 1.3 + +letting p be permutation((E2, E3, E4)) +letting s be permutation((E2, E3, E4)) +letting sn be permutation((E2, E3, E4)) +language Essence 1.3 + +letting p be permutation((E2, E3, E4)) +letting s be permutation((E2, E4, E3)) +letting sn be permutation((E2, E4, E3)) +language Essence 1.3 + +letting p be permutation((E2, E3, E4)) +letting s be permutation((E2, E4)) +letting sn be permutation((E2, E3)) +language Essence 1.3 + +letting p be permutation((E2, E3, E4)) +letting s be permutation((E1, E2)) +letting sn be permutation((E1, E3)) +language Essence 1.3 + +letting p be permutation((E2, E3, E4)) +letting s be permutation((E1, E2), (E3, E4)) +letting sn be permutation((E1, E3), (E2, E4)) +language Essence 1.3 + +letting p be permutation((E2, E3, E4)) +letting s be permutation((E1, E2, E3)) +letting sn be permutation((E1, E3, E4)) +language Essence 1.3 + +letting p be permutation((E2, E3, E4)) +letting s be permutation((E1, E2, E3, E4)) +letting sn be permutation((E1, E3, E4, E2)) diff --git a/tests/custom/permutations/16_image_permutation/enum/0050_find_permutation_given_permutation_find_permutation/permutation.essence b/tests/custom/permutations/16_image_permutation/enum/0050_find_permutation_given_permutation_find_permutation/permutation.essence new file mode 100644 index 0000000000..29240f3a0c --- /dev/null +++ b/tests/custom/permutations/16_image_permutation/enum/0050_find_permutation_given_permutation_find_permutation/permutation.essence @@ -0,0 +1,11 @@ +letting n be new type enum {E1,E2,E3,E4} + +find p : permutation of n + +given s : permutation of n + +find sn : permutation of n + + +such that sn = image(p,s) + diff --git a/tests/custom/permutations/16_image_permutation/enum/0050_find_permutation_given_permutation_find_permutation/permutation.param b/tests/custom/permutations/16_image_permutation/enum/0050_find_permutation_given_permutation_find_permutation/permutation.param new file mode 100644 index 0000000000..6782187f3d --- /dev/null +++ b/tests/custom/permutations/16_image_permutation/enum/0050_find_permutation_given_permutation_find_permutation/permutation.param @@ -0,0 +1 @@ +letting s be permutation((E1,E2,E3)) diff --git a/tests/custom/permutations/16_image_permutation/enum/0050_find_permutation_given_permutation_find_permutation/run.sh b/tests/custom/permutations/16_image_permutation/enum/0050_find_permutation_given_permutation_find_permutation/run.sh new file mode 100755 index 0000000000..aab5d44c6e --- /dev/null +++ b/tests/custom/permutations/16_image_permutation/enum/0050_find_permutation_given_permutation_find_permutation/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence *.param --number-of-solutions=10 +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/16_image_permutation/enum/0050_find_permutation_given_permutation_find_permutation/stdout.expected b/tests/custom/permutations/16_image_permutation/enum/0050_find_permutation_given_permutation_find_permutation/stdout.expected new file mode 100644 index 0000000000..dfa9602299 --- /dev/null +++ b/tests/custom/permutations/16_image_permutation/enum/0050_find_permutation_given_permutation_find_permutation/stdout.expected @@ -0,0 +1,54 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime permutation.param +Copying solution to: permutation-permutation-000001.solution +Copying solution to: permutation-permutation-000002.solution +Copying solution to: permutation-permutation-000003.solution +Copying solution to: permutation-permutation-000004.solution +Copying solution to: permutation-permutation-000005.solution +Copying solution to: permutation-permutation-000006.solution +Copying solution to: permutation-permutation-000007.solution +Copying solution to: permutation-permutation-000008.solution +Copying solution to: permutation-permutation-000009.solution +Copying solution to: permutation-permutation-000010.solution +language Essence 1.3 + +letting p be permutation() +letting sn be permutation((E1, E2, E3)) +language Essence 1.3 + +letting p be permutation((E3, E4)) +letting sn be permutation((E1, E2, E4)) +language Essence 1.3 + +letting p be permutation((E2, E3)) +letting sn be permutation((E1, E3, E2)) +language Essence 1.3 + +letting p be permutation((E2, E3, E4)) +letting sn be permutation((E1, E3, E4)) +language Essence 1.3 + +letting p be permutation((E2, E4, E3)) +letting sn be permutation((E1, E4, E2)) +language Essence 1.3 + +letting p be permutation((E2, E4)) +letting sn be permutation((E1, E4, E3)) +language Essence 1.3 + +letting p be permutation((E1, E2)) +letting sn be permutation((E1, E3, E2)) +language Essence 1.3 + +letting p be permutation((E1, E2), (E3, E4)) +letting sn be permutation((E1, E4, E2)) +language Essence 1.3 + +letting p be permutation((E1, E2, E3)) +letting sn be permutation((E1, E2, E3)) +language Essence 1.3 + +letting p be permutation((E1, E2, E3, E4)) +letting sn be permutation((E2, E3, E4)) diff --git a/tests/custom/permutations/16_image_permutation/int/0010_given_permutation_letting_permutation/permutation.essence b/tests/custom/permutations/16_image_permutation/int/0010_given_permutation_letting_permutation/permutation.essence new file mode 100644 index 0000000000..ebd5b402fc --- /dev/null +++ b/tests/custom/permutations/16_image_permutation/int/0010_given_permutation_letting_permutation/permutation.essence @@ -0,0 +1,10 @@ +letting n be 4 + +given p : permutation of int(1..n) +given s : permutation of int(1..n) + +find sn : permutation of int(1..n) + + +such that sn = image(p,s) + diff --git a/tests/custom/permutations/16_image_permutation/int/0010_given_permutation_letting_permutation/permutation.param b/tests/custom/permutations/16_image_permutation/int/0010_given_permutation_letting_permutation/permutation.param new file mode 100644 index 0000000000..09f6f5d15b --- /dev/null +++ b/tests/custom/permutations/16_image_permutation/int/0010_given_permutation_letting_permutation/permutation.param @@ -0,0 +1,2 @@ +letting p be permutation((1,3)) +letting s be permutation((1,2),(3,4)) diff --git a/tests/custom/permutations/16_image_permutation/int/0010_given_permutation_letting_permutation/run.sh b/tests/custom/permutations/16_image_permutation/int/0010_given_permutation_letting_permutation/run.sh new file mode 100755 index 0000000000..9dc67e67f5 --- /dev/null +++ b/tests/custom/permutations/16_image_permutation/int/0010_given_permutation_letting_permutation/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence *.param +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/16_image_permutation/int/0010_given_permutation_letting_permutation/stdout.expected b/tests/custom/permutations/16_image_permutation/int/0010_given_permutation_letting_permutation/stdout.expected new file mode 100644 index 0000000000..c56184dc94 --- /dev/null +++ b/tests/custom/permutations/16_image_permutation/int/0010_given_permutation_letting_permutation/stdout.expected @@ -0,0 +1,8 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime permutation.param +Copying solution to: permutation-permutation.solution +language Essence 1.3 + +letting sn be permutation((1, 4), (2, 3)) diff --git a/tests/custom/permutations/16_image_permutation/int/0020_given_permutation_find_permutations/permutation.essence b/tests/custom/permutations/16_image_permutation/int/0020_given_permutation_find_permutations/permutation.essence new file mode 100644 index 0000000000..c29d51a9dd --- /dev/null +++ b/tests/custom/permutations/16_image_permutation/int/0020_given_permutation_find_permutations/permutation.essence @@ -0,0 +1,11 @@ +letting n be 4 + +given p : permutation of int(1..n) + +find s : permutation of int(1..n) + +find sn : permutation of int(1..n) + + +such that sn = image(p,s) /\ sn != s /\ |s| > 0 + diff --git a/tests/custom/permutations/16_image_permutation/int/0020_given_permutation_find_permutations/permutation.param b/tests/custom/permutations/16_image_permutation/int/0020_given_permutation_find_permutations/permutation.param new file mode 100644 index 0000000000..8a8c516801 --- /dev/null +++ b/tests/custom/permutations/16_image_permutation/int/0020_given_permutation_find_permutations/permutation.param @@ -0,0 +1 @@ +letting p be permutation((1,3,4)) diff --git a/tests/custom/permutations/16_image_permutation/int/0020_given_permutation_find_permutations/run.sh b/tests/custom/permutations/16_image_permutation/int/0020_given_permutation_find_permutations/run.sh new file mode 100755 index 0000000000..aab5d44c6e --- /dev/null +++ b/tests/custom/permutations/16_image_permutation/int/0020_given_permutation_find_permutations/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence *.param --number-of-solutions=10 +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/16_image_permutation/int/0020_given_permutation_find_permutations/stdout.expected b/tests/custom/permutations/16_image_permutation/int/0020_given_permutation_find_permutations/stdout.expected new file mode 100644 index 0000000000..4a4c1a1fe9 --- /dev/null +++ b/tests/custom/permutations/16_image_permutation/int/0020_given_permutation_find_permutations/stdout.expected @@ -0,0 +1,54 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime permutation.param +Copying solution to: permutation-permutation-000001.solution +Copying solution to: permutation-permutation-000002.solution +Copying solution to: permutation-permutation-000003.solution +Copying solution to: permutation-permutation-000004.solution +Copying solution to: permutation-permutation-000005.solution +Copying solution to: permutation-permutation-000006.solution +Copying solution to: permutation-permutation-000007.solution +Copying solution to: permutation-permutation-000008.solution +Copying solution to: permutation-permutation-000009.solution +Copying solution to: permutation-permutation-000010.solution +language Essence 1.3 + +letting s be permutation((3, 4)) +letting sn be permutation((1, 4)) +language Essence 1.3 + +letting s be permutation((2, 3)) +letting sn be permutation((2, 4)) +language Essence 1.3 + +letting s be permutation((2, 3, 4)) +letting sn be permutation((1, 2, 4)) +language Essence 1.3 + +letting s be permutation((2, 4, 3)) +letting sn be permutation((1, 4, 2)) +language Essence 1.3 + +letting s be permutation((2, 4)) +letting sn be permutation((1, 2)) +language Essence 1.3 + +letting s be permutation((1, 2)) +letting sn be permutation((2, 3)) +language Essence 1.3 + +letting s be permutation((1, 2), (3, 4)) +letting sn be permutation((1, 4), (2, 3)) +language Essence 1.3 + +letting s be permutation((1, 2, 3)) +letting sn be permutation((2, 4, 3)) +language Essence 1.3 + +letting s be permutation((1, 2, 3, 4)) +letting sn be permutation((1, 3, 2, 4)) +language Essence 1.3 + +letting s be permutation((1, 2, 4, 3)) +letting sn be permutation((1, 4, 3, 2)) diff --git a/tests/custom/permutations/16_image_permutation/int/0030_letting_permutation_find_permutations/permutation.essence b/tests/custom/permutations/16_image_permutation/int/0030_letting_permutation_find_permutations/permutation.essence new file mode 100644 index 0000000000..db27179e9c --- /dev/null +++ b/tests/custom/permutations/16_image_permutation/int/0030_letting_permutation_find_permutations/permutation.essence @@ -0,0 +1,11 @@ +letting n be 4 + +letting p be permutation((1,3,4)) + +find s : permutation of int(1..n) + +find sn : permutation of int(1..n) + + +such that sn = image(p,s) + diff --git a/tests/custom/permutations/16_image_permutation/int/0030_letting_permutation_find_permutations/run.sh b/tests/custom/permutations/16_image_permutation/int/0030_letting_permutation_find_permutations/run.sh new file mode 100755 index 0000000000..03373df6cb --- /dev/null +++ b/tests/custom/permutations/16_image_permutation/int/0030_letting_permutation_find_permutations/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence --number-of-solutions=10 +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/16_image_permutation/int/0030_letting_permutation_find_permutations/stdout.expected b/tests/custom/permutations/16_image_permutation/int/0030_letting_permutation_find_permutations/stdout.expected new file mode 100644 index 0000000000..640c74ecb2 --- /dev/null +++ b/tests/custom/permutations/16_image_permutation/int/0030_letting_permutation_find_permutations/stdout.expected @@ -0,0 +1,54 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Copying solution to: permutation-000001.solution +Copying solution to: permutation-000002.solution +Copying solution to: permutation-000003.solution +Copying solution to: permutation-000004.solution +Copying solution to: permutation-000005.solution +Copying solution to: permutation-000006.solution +Copying solution to: permutation-000007.solution +Copying solution to: permutation-000008.solution +Copying solution to: permutation-000009.solution +Copying solution to: permutation-000010.solution +language Essence 1.3 + +letting s be permutation() +letting sn be permutation() +language Essence 1.3 + +letting s be permutation((3, 4)) +letting sn be permutation((1, 4)) +language Essence 1.3 + +letting s be permutation((2, 3)) +letting sn be permutation((2, 4)) +language Essence 1.3 + +letting s be permutation((2, 3, 4)) +letting sn be permutation((1, 2, 4)) +language Essence 1.3 + +letting s be permutation((2, 4, 3)) +letting sn be permutation((1, 4, 2)) +language Essence 1.3 + +letting s be permutation((2, 4)) +letting sn be permutation((1, 2)) +language Essence 1.3 + +letting s be permutation((1, 2)) +letting sn be permutation((2, 3)) +language Essence 1.3 + +letting s be permutation((1, 2), (3, 4)) +letting sn be permutation((1, 4), (2, 3)) +language Essence 1.3 + +letting s be permutation((1, 2, 3)) +letting sn be permutation((2, 4, 3)) +language Essence 1.3 + +letting s be permutation((1, 2, 3, 4)) +letting sn be permutation((1, 3, 2, 4)) diff --git a/tests/custom/permutations/16_image_permutation/int/0040_find_permutation_find_permutations/permutation.essence b/tests/custom/permutations/16_image_permutation/int/0040_find_permutation_find_permutations/permutation.essence new file mode 100644 index 0000000000..15ea636aef --- /dev/null +++ b/tests/custom/permutations/16_image_permutation/int/0040_find_permutation_find_permutations/permutation.essence @@ -0,0 +1,11 @@ +letting n be 4 + +find p : permutation of int(1..4) + +find s : permutation of int(1..n) + +find sn : permutation of int(1..n) + + +such that sn = image(p,s) /\ 3 = |p| + diff --git a/tests/custom/permutations/16_image_permutation/int/0040_find_permutation_find_permutations/run.sh b/tests/custom/permutations/16_image_permutation/int/0040_find_permutation_find_permutations/run.sh new file mode 100755 index 0000000000..03373df6cb --- /dev/null +++ b/tests/custom/permutations/16_image_permutation/int/0040_find_permutation_find_permutations/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence --number-of-solutions=10 +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/16_image_permutation/int/0040_find_permutation_find_permutations/stdout.expected b/tests/custom/permutations/16_image_permutation/int/0040_find_permutation_find_permutations/stdout.expected new file mode 100644 index 0000000000..820e928dce --- /dev/null +++ b/tests/custom/permutations/16_image_permutation/int/0040_find_permutation_find_permutations/stdout.expected @@ -0,0 +1,64 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Copying solution to: permutation-000001.solution +Copying solution to: permutation-000002.solution +Copying solution to: permutation-000003.solution +Copying solution to: permutation-000004.solution +Copying solution to: permutation-000005.solution +Copying solution to: permutation-000006.solution +Copying solution to: permutation-000007.solution +Copying solution to: permutation-000008.solution +Copying solution to: permutation-000009.solution +Copying solution to: permutation-000010.solution +language Essence 1.3 + +letting p be permutation((2, 3, 4)) +letting s be permutation() +letting sn be permutation() +language Essence 1.3 + +letting p be permutation((2, 3, 4)) +letting s be permutation((3, 4)) +letting sn be permutation((2, 4)) +language Essence 1.3 + +letting p be permutation((2, 3, 4)) +letting s be permutation((2, 3)) +letting sn be permutation((3, 4)) +language Essence 1.3 + +letting p be permutation((2, 3, 4)) +letting s be permutation((2, 3, 4)) +letting sn be permutation((2, 3, 4)) +language Essence 1.3 + +letting p be permutation((2, 3, 4)) +letting s be permutation((2, 4, 3)) +letting sn be permutation((2, 4, 3)) +language Essence 1.3 + +letting p be permutation((2, 3, 4)) +letting s be permutation((2, 4)) +letting sn be permutation((2, 3)) +language Essence 1.3 + +letting p be permutation((2, 3, 4)) +letting s be permutation((1, 2)) +letting sn be permutation((1, 3)) +language Essence 1.3 + +letting p be permutation((2, 3, 4)) +letting s be permutation((1, 2), (3, 4)) +letting sn be permutation((1, 3), (2, 4)) +language Essence 1.3 + +letting p be permutation((2, 3, 4)) +letting s be permutation((1, 2, 3)) +letting sn be permutation((1, 3, 4)) +language Essence 1.3 + +letting p be permutation((2, 3, 4)) +letting s be permutation((1, 2, 3, 4)) +letting sn be permutation((1, 3, 4, 2)) diff --git a/tests/custom/permutations/16_image_permutation/int/0050_find_permutation_given_permutation_find_permutation/permutation.essence b/tests/custom/permutations/16_image_permutation/int/0050_find_permutation_given_permutation_find_permutation/permutation.essence new file mode 100644 index 0000000000..df9daf9b35 --- /dev/null +++ b/tests/custom/permutations/16_image_permutation/int/0050_find_permutation_given_permutation_find_permutation/permutation.essence @@ -0,0 +1,11 @@ +letting n be 4 + +find p : permutation of int(1..4) + +given s : permutation of int(1..n) + +find sn : permutation of int(1..n) + + +such that sn = image(p,s) + diff --git a/tests/custom/permutations/16_image_permutation/int/0050_find_permutation_given_permutation_find_permutation/permutation.param b/tests/custom/permutations/16_image_permutation/int/0050_find_permutation_given_permutation_find_permutation/permutation.param new file mode 100644 index 0000000000..e129fce6db --- /dev/null +++ b/tests/custom/permutations/16_image_permutation/int/0050_find_permutation_given_permutation_find_permutation/permutation.param @@ -0,0 +1 @@ +letting s be permutation((1,2,3)) diff --git a/tests/custom/permutations/16_image_permutation/int/0050_find_permutation_given_permutation_find_permutation/run.sh b/tests/custom/permutations/16_image_permutation/int/0050_find_permutation_given_permutation_find_permutation/run.sh new file mode 100755 index 0000000000..aab5d44c6e --- /dev/null +++ b/tests/custom/permutations/16_image_permutation/int/0050_find_permutation_given_permutation_find_permutation/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence *.param --number-of-solutions=10 +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/16_image_permutation/int/0050_find_permutation_given_permutation_find_permutation/stdout.expected b/tests/custom/permutations/16_image_permutation/int/0050_find_permutation_given_permutation_find_permutation/stdout.expected new file mode 100644 index 0000000000..c03dbfd631 --- /dev/null +++ b/tests/custom/permutations/16_image_permutation/int/0050_find_permutation_given_permutation_find_permutation/stdout.expected @@ -0,0 +1,54 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime permutation.param +Copying solution to: permutation-permutation-000001.solution +Copying solution to: permutation-permutation-000002.solution +Copying solution to: permutation-permutation-000003.solution +Copying solution to: permutation-permutation-000004.solution +Copying solution to: permutation-permutation-000005.solution +Copying solution to: permutation-permutation-000006.solution +Copying solution to: permutation-permutation-000007.solution +Copying solution to: permutation-permutation-000008.solution +Copying solution to: permutation-permutation-000009.solution +Copying solution to: permutation-permutation-000010.solution +language Essence 1.3 + +letting p be permutation() +letting sn be permutation((1, 2, 3)) +language Essence 1.3 + +letting p be permutation((3, 4)) +letting sn be permutation((1, 2, 4)) +language Essence 1.3 + +letting p be permutation((2, 3)) +letting sn be permutation((1, 3, 2)) +language Essence 1.3 + +letting p be permutation((2, 3, 4)) +letting sn be permutation((1, 3, 4)) +language Essence 1.3 + +letting p be permutation((2, 4, 3)) +letting sn be permutation((1, 4, 2)) +language Essence 1.3 + +letting p be permutation((2, 4)) +letting sn be permutation((1, 4, 3)) +language Essence 1.3 + +letting p be permutation((1, 2)) +letting sn be permutation((1, 3, 2)) +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4)) +letting sn be permutation((1, 4, 2)) +language Essence 1.3 + +letting p be permutation((1, 2, 3)) +letting sn be permutation((1, 2, 3)) +language Essence 1.3 + +letting p be permutation((1, 2, 3, 4)) +letting sn be permutation((2, 3, 4)) diff --git a/tests/custom/permutations/16_image_permutation/runthese.sh b/tests/custom/permutations/16_image_permutation/runthese.sh new file mode 100644 index 0000000000..2c9f64b312 --- /dev/null +++ b/tests/custom/permutations/16_image_permutation/runthese.sh @@ -0,0 +1 @@ +stack build --copy-bins --test --test-arguments "-p custom.permutations.16_image_permutation" diff --git a/tests/custom/permutations/16_image_permutation/unnamed/0004_find_permutation_find_permutations/permutation.essence b/tests/custom/permutations/16_image_permutation/unnamed/0004_find_permutation_find_permutations/permutation.essence new file mode 100644 index 0000000000..41ef1b0e1c --- /dev/null +++ b/tests/custom/permutations/16_image_permutation/unnamed/0004_find_permutation_find_permutations/permutation.essence @@ -0,0 +1,11 @@ +letting n be new type of size 4 + +find p : permutation of n + +find s : permutation of n + +find sn : permutation of n + + +such that sn = image(p,s) /\ |p| > 0 + diff --git a/tests/custom/permutations/16_image_permutation/unnamed/0004_find_permutation_find_permutations/run.sh b/tests/custom/permutations/16_image_permutation/unnamed/0004_find_permutation_find_permutations/run.sh new file mode 100755 index 0000000000..03373df6cb --- /dev/null +++ b/tests/custom/permutations/16_image_permutation/unnamed/0004_find_permutation_find_permutations/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence --number-of-solutions=10 +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/16_image_permutation/unnamed/0004_find_permutation_find_permutations/stdout.expected b/tests/custom/permutations/16_image_permutation/unnamed/0004_find_permutation_find_permutations/stdout.expected new file mode 100644 index 0000000000..7426c7dd7b --- /dev/null +++ b/tests/custom/permutations/16_image_permutation/unnamed/0004_find_permutation_find_permutations/stdout.expected @@ -0,0 +1,74 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Copying solution to: permutation-000001.solution +Copying solution to: permutation-000002.solution +Copying solution to: permutation-000003.solution +Copying solution to: permutation-000004.solution +Copying solution to: permutation-000005.solution +Copying solution to: permutation-000006.solution +Copying solution to: permutation-000007.solution +Copying solution to: permutation-000008.solution +Copying solution to: permutation-000009.solution +Copying solution to: permutation-000010.solution +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_3, n_4)) +letting s be permutation() +letting sn be permutation() +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_3, n_4)) +letting s be permutation((n_3, n_4)) +letting sn be permutation((n_3, n_4)) +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_3, n_4)) +letting s be permutation((n_2, n_3)) +letting sn be permutation((n_2, n_4)) +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_3, n_4)) +letting s be permutation((n_2, n_3, n_4)) +letting sn be permutation((n_2, n_4, n_3)) +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_3, n_4)) +letting s be permutation((n_2, n_4, n_3)) +letting sn be permutation((n_2, n_3, n_4)) +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_3, n_4)) +letting s be permutation((n_2, n_4)) +letting sn be permutation((n_2, n_3)) +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_3, n_4)) +letting s be permutation((n_1, n_2)) +letting sn be permutation((n_1, n_2)) +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_3, n_4)) +letting s be permutation((n_1, n_2), (n_3, n_4)) +letting sn be permutation((n_1, n_2), (n_3, n_4)) +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_3, n_4)) +letting s be permutation((n_1, n_2, n_3)) +letting sn be permutation((n_1, n_2, n_4)) +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_3, n_4)) +letting s be permutation((n_1, n_2, n_3, n_4)) +letting sn be permutation((n_1, n_2, n_4, n_3)) From 4a73448235067e5c26fa08f3b9cff40913aacc00 Mon Sep 17 00:00:00 2001 From: Fraser Dunlop Date: Tue, 8 Jan 2019 11:13:46 +0000 Subject: [PATCH 063/229] partition tests - partition bug discovered --- src/Conjure/Rules/Horizontal/Permutation.hs | 31 ++++ src/Conjure/UI/Model.hs | 1 + .../permutations/17_image_partition/BUGS.md | 1 + .../permutation.essence | 4 + .../permutation.param | 1 + .../0010_given_partition_of_enum_BUG/run.sh | 3 + .../stdout.expected | 12 ++ .../permutation.essence | 3 + .../0020_find_partition_of_enum_BUG/run.sh | 3 + .../permutation.essence | 10 ++ .../permutation.param | 2 + .../run.sh | 3 + .../stdout.expected | 12 ++ .../permutation.essence | 11 ++ .../permutation.param | 1 + .../run.sh | 3 + .../stdout.expected | 142 +++++++++++++++++ .../permutation.essence | 11 ++ .../run.sh | 3 + .../stdout.expected | 136 ++++++++++++++++ .../permutation.essence | 11 ++ .../run.sh | 3 + .../stdout.expected | 146 ++++++++++++++++++ .../permutation.essence | 11 ++ .../permutation.param | 1 + .../run.sh | 3 + .../stdout.expected | 94 +++++++++++ .../17_image_partition/runthese.sh | 1 + .../permutation.essence | 4 + .../0010_find_partition_of_unnamed_BUG/run.sh | 3 + .../permutation.essence | 9 ++ .../permutation.param | 2 + .../run.sh | 3 + .../stdout.expected | 12 ++ .../permutations/18_image_matrix/runthese.sh | 1 + 35 files changed, 697 insertions(+) create mode 100644 tests/custom/permutations/17_image_partition/BUGS.md create mode 100644 tests/custom/permutations/17_image_partition/enum/0010_given_partition_of_enum_BUG/permutation.essence create mode 100644 tests/custom/permutations/17_image_partition/enum/0010_given_partition_of_enum_BUG/permutation.param create mode 100755 tests/custom/permutations/17_image_partition/enum/0010_given_partition_of_enum_BUG/run.sh create mode 100644 tests/custom/permutations/17_image_partition/enum/0010_given_partition_of_enum_BUG/stdout.expected create mode 100644 tests/custom/permutations/17_image_partition/enum/0020_find_partition_of_enum_BUG/permutation.essence create mode 100755 tests/custom/permutations/17_image_partition/enum/0020_find_partition_of_enum_BUG/run.sh create mode 100644 tests/custom/permutations/17_image_partition/int/0010_given_permutation_partition_find_partition/permutation.essence create mode 100644 tests/custom/permutations/17_image_partition/int/0010_given_permutation_partition_find_partition/permutation.param create mode 100755 tests/custom/permutations/17_image_partition/int/0010_given_permutation_partition_find_partition/run.sh create mode 100644 tests/custom/permutations/17_image_partition/int/0010_given_permutation_partition_find_partition/stdout.expected create mode 100644 tests/custom/permutations/17_image_partition/int/0020_given_permutation_find_partitions/permutation.essence create mode 100644 tests/custom/permutations/17_image_partition/int/0020_given_permutation_find_partitions/permutation.param create mode 100755 tests/custom/permutations/17_image_partition/int/0020_given_permutation_find_partitions/run.sh create mode 100644 tests/custom/permutations/17_image_partition/int/0020_given_permutation_find_partitions/stdout.expected create mode 100644 tests/custom/permutations/17_image_partition/int/0030_letting_permutation_find_partitions/permutation.essence create mode 100755 tests/custom/permutations/17_image_partition/int/0030_letting_permutation_find_partitions/run.sh create mode 100644 tests/custom/permutations/17_image_partition/int/0030_letting_permutation_find_partitions/stdout.expected create mode 100644 tests/custom/permutations/17_image_partition/int/0040_find_permutation_find_partitions/permutation.essence create mode 100755 tests/custom/permutations/17_image_partition/int/0040_find_permutation_find_partitions/run.sh create mode 100644 tests/custom/permutations/17_image_partition/int/0040_find_permutation_find_partitions/stdout.expected create mode 100644 tests/custom/permutations/17_image_partition/int/0050_find_permutation_given_partition_find_partition/permutation.essence create mode 100644 tests/custom/permutations/17_image_partition/int/0050_find_permutation_given_partition_find_partition/permutation.param create mode 100755 tests/custom/permutations/17_image_partition/int/0050_find_permutation_given_partition_find_partition/run.sh create mode 100644 tests/custom/permutations/17_image_partition/int/0050_find_permutation_given_partition_find_partition/stdout.expected create mode 100644 tests/custom/permutations/17_image_partition/runthese.sh create mode 100644 tests/custom/permutations/17_image_partition/unnamed/0010_find_partition_of_unnamed_BUG/permutation.essence create mode 100755 tests/custom/permutations/17_image_partition/unnamed/0010_find_partition_of_unnamed_BUG/run.sh create mode 100644 tests/custom/permutations/18_image_matrix/int/0010_given_permutation_matrix_find_matrix/permutation.essence create mode 100644 tests/custom/permutations/18_image_matrix/int/0010_given_permutation_matrix_find_matrix/permutation.param create mode 100755 tests/custom/permutations/18_image_matrix/int/0010_given_permutation_matrix_find_matrix/run.sh create mode 100644 tests/custom/permutations/18_image_matrix/int/0010_given_permutation_matrix_find_matrix/stdout.expected create mode 100644 tests/custom/permutations/18_image_matrix/runthese.sh diff --git a/src/Conjure/Rules/Horizontal/Permutation.hs b/src/Conjure/Rules/Horizontal/Permutation.hs index 65b80e234f..661b3479bb 100644 --- a/src/Conjure/Rules/Horizontal/Permutation.hs +++ b/src/Conjure/Rules/Horizontal/Permutation.hs @@ -179,6 +179,7 @@ rule_Image_Comprehendable = "comprehendable-image" `namedRule` theRule where (perm, y) <- match opImage x ty <- typeOf y case ty of TypeSequence{} -> na "sequence is a special case" ; _ -> return () + case ty of TypePartition{} -> na "partition is a special case" ; _ -> return () (TypePermutation inn) <- typeOf perm if ty `containsTypeComprehendable` inn then do @@ -249,6 +250,36 @@ rule_Image_Sequence_Defined = "image-sequence-defined" `namedRule` theRule where theRule _ = na "rule_Image_Sequence_Defined" +rule_Image_Partition :: Rule +rule_Image_Partition = "image-partition" `namedRule` theRule where + theRule (Comprehension body gensOrConds) = do + (gocBefore, (pat, x), gocAfter) <- matchFirst gensOrConds $ \ goc -> case goc of + Generator (GenInExpr (Single pat) expr) -> return (pat, expr) + _ -> na "rule_Image_Partition" + z <- match opParts x + (perm, y) <- match opImage z + ty <- typeOf y + case ty of TypePartition{} -> return () ; _ -> na "only applies to partitions" + (TypePermutation inn) <- typeOf perm + if ty `containsTypeComprehendable` inn + then do + return + ( "Horizontal rule for image of partition under permutation" + , do + (dPat, d) <- quantifiedVar + return (Comprehension body $ + gocBefore + ++ [Generator (GenInExpr dPat [essence| parts(&y) |])] + ++ ((ComprehensionLetting pat [essence| image(&perm, &d) |] ):gocAfter) + ) + + ) + else na "rule_Image_Partition" + theRule _ = na "rule_Image_Partition" + + + + rule_Image_Incomprehendable :: Rule rule_Image_Incomprehendable = "comprehendable-image" `namedRule` theRule where diff --git a/src/Conjure/UI/Model.hs b/src/Conjure/UI/Model.hs index c421f002cc..c76e8d5c42 100644 --- a/src/Conjure/UI/Model.hs +++ b/src/Conjure/UI/Model.hs @@ -1206,6 +1206,7 @@ horizontalRules = , Horizontal.Permutation.rule_Compose_Image , Horizontal.Permutation.rule_Compose , Horizontal.Permutation.rule_Image_Literal + , Horizontal.Permutation.rule_Image_Partition , Horizontal.Permutation.rule_Image_Sequence , Horizontal.Permutation.rule_Image_Sequence_Defined , Horizontal.Permutation.rule_In diff --git a/tests/custom/permutations/17_image_partition/BUGS.md b/tests/custom/permutations/17_image_partition/BUGS.md new file mode 100644 index 0000000000..0dbfbf8547 --- /dev/null +++ b/tests/custom/permutations/17_image_partition/BUGS.md @@ -0,0 +1 @@ +It is not currently possible to construct a permutation of unnamed or enum. diff --git a/tests/custom/permutations/17_image_partition/enum/0010_given_partition_of_enum_BUG/permutation.essence b/tests/custom/permutations/17_image_partition/enum/0010_given_partition_of_enum_BUG/permutation.essence new file mode 100644 index 0000000000..500eee541c --- /dev/null +++ b/tests/custom/permutations/17_image_partition/enum/0010_given_partition_of_enum_BUG/permutation.essence @@ -0,0 +1,4 @@ +letting n be new type enum {E1,E2,E3,E4} + +given s : partition from n + diff --git a/tests/custom/permutations/17_image_partition/enum/0010_given_partition_of_enum_BUG/permutation.param b/tests/custom/permutations/17_image_partition/enum/0010_given_partition_of_enum_BUG/permutation.param new file mode 100644 index 0000000000..0b4c3cb3a0 --- /dev/null +++ b/tests/custom/permutations/17_image_partition/enum/0010_given_partition_of_enum_BUG/permutation.param @@ -0,0 +1 @@ +letting s be partition({E1,E2},{E3,E4}) diff --git a/tests/custom/permutations/17_image_partition/enum/0010_given_partition_of_enum_BUG/run.sh b/tests/custom/permutations/17_image_partition/enum/0010_given_partition_of_enum_BUG/run.sh new file mode 100755 index 0000000000..9dc67e67f5 --- /dev/null +++ b/tests/custom/permutations/17_image_partition/enum/0010_given_partition_of_enum_BUG/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence *.param +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/17_image_partition/enum/0010_given_partition_of_enum_BUG/stdout.expected b/tests/custom/permutations/17_image_partition/enum/0010_given_partition_of_enum_BUG/stdout.expected new file mode 100644 index 0000000000..75fa929da5 --- /dev/null +++ b/tests/custom/permutations/17_image_partition/enum/0010_given_partition_of_enum_BUG/stdout.expected @@ -0,0 +1,12 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime permutation.param +Copying solution to: permutation-permutation.solution +language Essence 1.3 + +letting sn be partition({1, 4}, {2, 3}) +$ Visualisation for sn +$ 1 4 +$ 2 3 + diff --git a/tests/custom/permutations/17_image_partition/enum/0020_find_partition_of_enum_BUG/permutation.essence b/tests/custom/permutations/17_image_partition/enum/0020_find_partition_of_enum_BUG/permutation.essence new file mode 100644 index 0000000000..030692165f --- /dev/null +++ b/tests/custom/permutations/17_image_partition/enum/0020_find_partition_of_enum_BUG/permutation.essence @@ -0,0 +1,3 @@ +letting n be new type enum {E1,E2,E3,E4} + +find sn : partition from n diff --git a/tests/custom/permutations/17_image_partition/enum/0020_find_partition_of_enum_BUG/run.sh b/tests/custom/permutations/17_image_partition/enum/0020_find_partition_of_enum_BUG/run.sh new file mode 100755 index 0000000000..b4899d6266 --- /dev/null +++ b/tests/custom/permutations/17_image_partition/enum/0020_find_partition_of_enum_BUG/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/17_image_partition/int/0010_given_permutation_partition_find_partition/permutation.essence b/tests/custom/permutations/17_image_partition/int/0010_given_permutation_partition_find_partition/permutation.essence new file mode 100644 index 0000000000..655db58eee --- /dev/null +++ b/tests/custom/permutations/17_image_partition/int/0010_given_permutation_partition_find_partition/permutation.essence @@ -0,0 +1,10 @@ +letting n be 4 + +given p : permutation of int(1..n) +given s : partition from int(1..n) + +find sn : partition from int(1..n) + + +such that sn = image(p,s) + diff --git a/tests/custom/permutations/17_image_partition/int/0010_given_permutation_partition_find_partition/permutation.param b/tests/custom/permutations/17_image_partition/int/0010_given_permutation_partition_find_partition/permutation.param new file mode 100644 index 0000000000..f328a92c6a --- /dev/null +++ b/tests/custom/permutations/17_image_partition/int/0010_given_permutation_partition_find_partition/permutation.param @@ -0,0 +1,2 @@ +letting p be permutation((1,3)) +letting s be partition({1,2},{3,4}) diff --git a/tests/custom/permutations/17_image_partition/int/0010_given_permutation_partition_find_partition/run.sh b/tests/custom/permutations/17_image_partition/int/0010_given_permutation_partition_find_partition/run.sh new file mode 100755 index 0000000000..9dc67e67f5 --- /dev/null +++ b/tests/custom/permutations/17_image_partition/int/0010_given_permutation_partition_find_partition/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence *.param +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/17_image_partition/int/0010_given_permutation_partition_find_partition/stdout.expected b/tests/custom/permutations/17_image_partition/int/0010_given_permutation_partition_find_partition/stdout.expected new file mode 100644 index 0000000000..75fa929da5 --- /dev/null +++ b/tests/custom/permutations/17_image_partition/int/0010_given_permutation_partition_find_partition/stdout.expected @@ -0,0 +1,12 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime permutation.param +Copying solution to: permutation-permutation.solution +language Essence 1.3 + +letting sn be partition({1, 4}, {2, 3}) +$ Visualisation for sn +$ 1 4 +$ 2 3 + diff --git a/tests/custom/permutations/17_image_partition/int/0020_given_permutation_find_partitions/permutation.essence b/tests/custom/permutations/17_image_partition/int/0020_given_permutation_find_partitions/permutation.essence new file mode 100644 index 0000000000..0dae580e91 --- /dev/null +++ b/tests/custom/permutations/17_image_partition/int/0020_given_permutation_find_partitions/permutation.essence @@ -0,0 +1,11 @@ +letting n be 4 + +given p : permutation of int(1..n) + +find s : partition from int(1..n) + +find sn : partition from int(1..n) + + +such that sn = image(p,s) /\ sn != s /\ |s| > 0 + diff --git a/tests/custom/permutations/17_image_partition/int/0020_given_permutation_find_partitions/permutation.param b/tests/custom/permutations/17_image_partition/int/0020_given_permutation_find_partitions/permutation.param new file mode 100644 index 0000000000..8a8c516801 --- /dev/null +++ b/tests/custom/permutations/17_image_partition/int/0020_given_permutation_find_partitions/permutation.param @@ -0,0 +1 @@ +letting p be permutation((1,3,4)) diff --git a/tests/custom/permutations/17_image_partition/int/0020_given_permutation_find_partitions/run.sh b/tests/custom/permutations/17_image_partition/int/0020_given_permutation_find_partitions/run.sh new file mode 100755 index 0000000000..aab5d44c6e --- /dev/null +++ b/tests/custom/permutations/17_image_partition/int/0020_given_permutation_find_partitions/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence *.param --number-of-solutions=10 +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/17_image_partition/int/0020_given_permutation_find_partitions/stdout.expected b/tests/custom/permutations/17_image_partition/int/0020_given_permutation_find_partitions/stdout.expected new file mode 100644 index 0000000000..703b05e795 --- /dev/null +++ b/tests/custom/permutations/17_image_partition/int/0020_given_permutation_find_partitions/stdout.expected @@ -0,0 +1,142 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime permutation.param +Copying solution to: permutation-permutation-000001.solution +Copying solution to: permutation-permutation-000002.solution +Copying solution to: permutation-permutation-000003.solution +Copying solution to: permutation-permutation-000004.solution +Copying solution to: permutation-permutation-000005.solution +Copying solution to: permutation-permutation-000006.solution +Copying solution to: permutation-permutation-000007.solution +Copying solution to: permutation-permutation-000008.solution +Copying solution to: permutation-permutation-000009.solution +Copying solution to: permutation-permutation-000010.solution +language Essence 1.3 + +letting s be partition({1, 2, 3}, {4}) +$ Visualisation for s +$ 1 2 3 +$ 4 + +letting sn be partition({1}, {2, 3, 4}) +$ Visualisation for sn +$ 1 +$ 2 3 4 + +language Essence 1.3 + +letting s be partition({1, 2, 4}, {3}) +$ Visualisation for s +$ 1 2 4 +$ 3 + +letting sn be partition({1, 2, 3}, {4}) +$ Visualisation for sn +$ 1 2 3 +$ 4 + +language Essence 1.3 + +letting s be partition({1, 2}, {3, 4}) +$ Visualisation for s +$ 1 2 +$ 3 4 + +letting sn be partition({1, 4}, {2, 3}) +$ Visualisation for sn +$ 1 4 +$ 2 3 + +language Essence 1.3 + +letting s be partition({1, 3}, {2, 4}) +$ Visualisation for s +$ 1 3 +$ 2 4 + +letting sn be partition({1, 2}, {3, 4}) +$ Visualisation for sn +$ 1 2 +$ 3 4 + +language Essence 1.3 + +letting s be partition({1, 4}, {2, 3}) +$ Visualisation for s +$ 1 4 +$ 2 3 + +letting sn be partition({1, 3}, {2, 4}) +$ Visualisation for sn +$ 1 3 +$ 2 4 + +language Essence 1.3 + +letting s be partition({1}, {2, 3, 4}) +$ Visualisation for s +$ 1 +$ 2 3 4 + +letting sn be partition({1, 2, 4}, {3}) +$ Visualisation for sn +$ 1 2 4 +$ 3 + +language Essence 1.3 + +letting s be partition({1, 2}, {3}, {4}) +$ Visualisation for s +$ 1 2 +$ 3 +$ 4 + +letting sn be partition({1}, {2, 3}, {4}) +$ Visualisation for sn +$ 1 +$ 2 3 +$ 4 + +language Essence 1.3 + +letting s be partition({1, 3}, {2}, {4}) +$ Visualisation for s +$ 1 3 +$ 2 +$ 4 + +letting sn be partition({1}, {2}, {3, 4}) +$ Visualisation for sn +$ 1 +$ 2 +$ 3 4 + +language Essence 1.3 + +letting s be partition({1}, {2, 3}, {4}) +$ Visualisation for s +$ 1 +$ 2 3 +$ 4 + +letting sn be partition({1}, {2, 4}, {3}) +$ Visualisation for sn +$ 1 +$ 2 4 +$ 3 + +language Essence 1.3 + +letting s be partition({1, 4}, {2}, {3}) +$ Visualisation for s +$ 1 4 +$ 2 +$ 3 + +letting sn be partition({1, 3}, {2}, {4}) +$ Visualisation for sn +$ 1 3 +$ 2 +$ 4 + diff --git a/tests/custom/permutations/17_image_partition/int/0030_letting_permutation_find_partitions/permutation.essence b/tests/custom/permutations/17_image_partition/int/0030_letting_permutation_find_partitions/permutation.essence new file mode 100644 index 0000000000..bc3c7c232a --- /dev/null +++ b/tests/custom/permutations/17_image_partition/int/0030_letting_permutation_find_partitions/permutation.essence @@ -0,0 +1,11 @@ +letting n be 4 + +letting p be permutation((1,3,4)) + +find s : partition from int(1..n) + +find sn : partition from int(1..n) + + +such that sn = image(p,s) + diff --git a/tests/custom/permutations/17_image_partition/int/0030_letting_permutation_find_partitions/run.sh b/tests/custom/permutations/17_image_partition/int/0030_letting_permutation_find_partitions/run.sh new file mode 100755 index 0000000000..03373df6cb --- /dev/null +++ b/tests/custom/permutations/17_image_partition/int/0030_letting_permutation_find_partitions/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence --number-of-solutions=10 +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/17_image_partition/int/0030_letting_permutation_find_partitions/stdout.expected b/tests/custom/permutations/17_image_partition/int/0030_letting_permutation_find_partitions/stdout.expected new file mode 100644 index 0000000000..2884fa5c2b --- /dev/null +++ b/tests/custom/permutations/17_image_partition/int/0030_letting_permutation_find_partitions/stdout.expected @@ -0,0 +1,136 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Copying solution to: permutation-000001.solution +Copying solution to: permutation-000002.solution +Copying solution to: permutation-000003.solution +Copying solution to: permutation-000004.solution +Copying solution to: permutation-000005.solution +Copying solution to: permutation-000006.solution +Copying solution to: permutation-000007.solution +Copying solution to: permutation-000008.solution +Copying solution to: permutation-000009.solution +Copying solution to: permutation-000010.solution +language Essence 1.3 + +letting s be partition({1, 2, 3, 4}) +$ Visualisation for s +$ 1 2 3 4 + +letting sn be partition({1, 2, 3, 4}) +$ Visualisation for sn +$ 1 2 3 4 + +language Essence 1.3 + +letting s be partition({1, 2, 3}, {4}) +$ Visualisation for s +$ 1 2 3 +$ 4 + +letting sn be partition({1}, {2, 3, 4}) +$ Visualisation for sn +$ 1 +$ 2 3 4 + +language Essence 1.3 + +letting s be partition({1, 2, 4}, {3}) +$ Visualisation for s +$ 1 2 4 +$ 3 + +letting sn be partition({1, 2, 3}, {4}) +$ Visualisation for sn +$ 1 2 3 +$ 4 + +language Essence 1.3 + +letting s be partition({1, 2}, {3, 4}) +$ Visualisation for s +$ 1 2 +$ 3 4 + +letting sn be partition({1, 4}, {2, 3}) +$ Visualisation for sn +$ 1 4 +$ 2 3 + +language Essence 1.3 + +letting s be partition({1, 3, 4}, {2}) +$ Visualisation for s +$ 1 3 4 +$ 2 + +letting sn be partition({1, 3, 4}, {2}) +$ Visualisation for sn +$ 1 3 4 +$ 2 + +language Essence 1.3 + +letting s be partition({1, 3}, {2, 4}) +$ Visualisation for s +$ 1 3 +$ 2 4 + +letting sn be partition({1, 2}, {3, 4}) +$ Visualisation for sn +$ 1 2 +$ 3 4 + +language Essence 1.3 + +letting s be partition({1, 4}, {2, 3}) +$ Visualisation for s +$ 1 4 +$ 2 3 + +letting sn be partition({1, 3}, {2, 4}) +$ Visualisation for sn +$ 1 3 +$ 2 4 + +language Essence 1.3 + +letting s be partition({1}, {2, 3, 4}) +$ Visualisation for s +$ 1 +$ 2 3 4 + +letting sn be partition({1, 2, 4}, {3}) +$ Visualisation for sn +$ 1 2 4 +$ 3 + +language Essence 1.3 + +letting s be partition({1, 2}, {3}, {4}) +$ Visualisation for s +$ 1 2 +$ 3 +$ 4 + +letting sn be partition({1}, {2, 3}, {4}) +$ Visualisation for sn +$ 1 +$ 2 3 +$ 4 + +language Essence 1.3 + +letting s be partition({1, 3}, {2}, {4}) +$ Visualisation for s +$ 1 3 +$ 2 +$ 4 + +letting sn be partition({1}, {2}, {3, 4}) +$ Visualisation for sn +$ 1 +$ 2 +$ 3 4 + diff --git a/tests/custom/permutations/17_image_partition/int/0040_find_permutation_find_partitions/permutation.essence b/tests/custom/permutations/17_image_partition/int/0040_find_permutation_find_partitions/permutation.essence new file mode 100644 index 0000000000..947d6ec00f --- /dev/null +++ b/tests/custom/permutations/17_image_partition/int/0040_find_permutation_find_partitions/permutation.essence @@ -0,0 +1,11 @@ +letting n be 4 + +find p : permutation of int(1..4) + +find s : partition from int(1..n) + +find sn : partition from int(1..n) + + +such that sn = image(p,s) /\ 3 = |p| + diff --git a/tests/custom/permutations/17_image_partition/int/0040_find_permutation_find_partitions/run.sh b/tests/custom/permutations/17_image_partition/int/0040_find_permutation_find_partitions/run.sh new file mode 100755 index 0000000000..03373df6cb --- /dev/null +++ b/tests/custom/permutations/17_image_partition/int/0040_find_permutation_find_partitions/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence --number-of-solutions=10 +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/17_image_partition/int/0040_find_permutation_find_partitions/stdout.expected b/tests/custom/permutations/17_image_partition/int/0040_find_permutation_find_partitions/stdout.expected new file mode 100644 index 0000000000..c64f85dd97 --- /dev/null +++ b/tests/custom/permutations/17_image_partition/int/0040_find_permutation_find_partitions/stdout.expected @@ -0,0 +1,146 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Copying solution to: permutation-000001.solution +Copying solution to: permutation-000002.solution +Copying solution to: permutation-000003.solution +Copying solution to: permutation-000004.solution +Copying solution to: permutation-000005.solution +Copying solution to: permutation-000006.solution +Copying solution to: permutation-000007.solution +Copying solution to: permutation-000008.solution +Copying solution to: permutation-000009.solution +Copying solution to: permutation-000010.solution +language Essence 1.3 + +letting p be permutation((2, 3, 4)) +letting s be partition({1, 2, 3, 4}) +$ Visualisation for s +$ 1 2 3 4 + +letting sn be partition({1, 2, 3, 4}) +$ Visualisation for sn +$ 1 2 3 4 + +language Essence 1.3 + +letting p be permutation((2, 3, 4)) +letting s be partition({1, 2, 3}, {4}) +$ Visualisation for s +$ 1 2 3 +$ 4 + +letting sn be partition({1, 3, 4}, {2}) +$ Visualisation for sn +$ 1 3 4 +$ 2 + +language Essence 1.3 + +letting p be permutation((2, 3, 4)) +letting s be partition({1, 2, 4}, {3}) +$ Visualisation for s +$ 1 2 4 +$ 3 + +letting sn be partition({1, 2, 3}, {4}) +$ Visualisation for sn +$ 1 2 3 +$ 4 + +language Essence 1.3 + +letting p be permutation((2, 3, 4)) +letting s be partition({1, 2}, {3, 4}) +$ Visualisation for s +$ 1 2 +$ 3 4 + +letting sn be partition({1, 3}, {2, 4}) +$ Visualisation for sn +$ 1 3 +$ 2 4 + +language Essence 1.3 + +letting p be permutation((2, 3, 4)) +letting s be partition({1, 3, 4}, {2}) +$ Visualisation for s +$ 1 3 4 +$ 2 + +letting sn be partition({1, 2, 4}, {3}) +$ Visualisation for sn +$ 1 2 4 +$ 3 + +language Essence 1.3 + +letting p be permutation((2, 3, 4)) +letting s be partition({1, 3}, {2, 4}) +$ Visualisation for s +$ 1 3 +$ 2 4 + +letting sn be partition({1, 4}, {2, 3}) +$ Visualisation for sn +$ 1 4 +$ 2 3 + +language Essence 1.3 + +letting p be permutation((2, 3, 4)) +letting s be partition({1, 4}, {2, 3}) +$ Visualisation for s +$ 1 4 +$ 2 3 + +letting sn be partition({1, 2}, {3, 4}) +$ Visualisation for sn +$ 1 2 +$ 3 4 + +language Essence 1.3 + +letting p be permutation((2, 3, 4)) +letting s be partition({1}, {2, 3, 4}) +$ Visualisation for s +$ 1 +$ 2 3 4 + +letting sn be partition({1}, {2, 3, 4}) +$ Visualisation for sn +$ 1 +$ 2 3 4 + +language Essence 1.3 + +letting p be permutation((2, 3, 4)) +letting s be partition({1, 2}, {3}, {4}) +$ Visualisation for s +$ 1 2 +$ 3 +$ 4 + +letting sn be partition({1, 3}, {2}, {4}) +$ Visualisation for sn +$ 1 3 +$ 2 +$ 4 + +language Essence 1.3 + +letting p be permutation((2, 3, 4)) +letting s be partition({1, 3}, {2}, {4}) +$ Visualisation for s +$ 1 3 +$ 2 +$ 4 + +letting sn be partition({1, 4}, {2}, {3}) +$ Visualisation for sn +$ 1 4 +$ 2 +$ 3 + diff --git a/tests/custom/permutations/17_image_partition/int/0050_find_permutation_given_partition_find_partition/permutation.essence b/tests/custom/permutations/17_image_partition/int/0050_find_permutation_given_partition_find_partition/permutation.essence new file mode 100644 index 0000000000..5e04cbe8ed --- /dev/null +++ b/tests/custom/permutations/17_image_partition/int/0050_find_permutation_given_partition_find_partition/permutation.essence @@ -0,0 +1,11 @@ +letting n be 4 + +find p : permutation of int(1..4) + +given s : partition from int(1..n) + +find sn : partition from int(1..n) + + +such that sn = image(p,s) + diff --git a/tests/custom/permutations/17_image_partition/int/0050_find_permutation_given_partition_find_partition/permutation.param b/tests/custom/permutations/17_image_partition/int/0050_find_permutation_given_partition_find_partition/permutation.param new file mode 100644 index 0000000000..e5c7b2aa77 --- /dev/null +++ b/tests/custom/permutations/17_image_partition/int/0050_find_permutation_given_partition_find_partition/permutation.param @@ -0,0 +1 @@ +letting s be partition({1,2},{3,4}) diff --git a/tests/custom/permutations/17_image_partition/int/0050_find_permutation_given_partition_find_partition/run.sh b/tests/custom/permutations/17_image_partition/int/0050_find_permutation_given_partition_find_partition/run.sh new file mode 100755 index 0000000000..aab5d44c6e --- /dev/null +++ b/tests/custom/permutations/17_image_partition/int/0050_find_permutation_given_partition_find_partition/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence *.param --number-of-solutions=10 +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/17_image_partition/int/0050_find_permutation_given_partition_find_partition/stdout.expected b/tests/custom/permutations/17_image_partition/int/0050_find_permutation_given_partition_find_partition/stdout.expected new file mode 100644 index 0000000000..7eb68a2281 --- /dev/null +++ b/tests/custom/permutations/17_image_partition/int/0050_find_permutation_given_partition_find_partition/stdout.expected @@ -0,0 +1,94 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime permutation.param +Copying solution to: permutation-permutation-000001.solution +Copying solution to: permutation-permutation-000002.solution +Copying solution to: permutation-permutation-000003.solution +Copying solution to: permutation-permutation-000004.solution +Copying solution to: permutation-permutation-000005.solution +Copying solution to: permutation-permutation-000006.solution +Copying solution to: permutation-permutation-000007.solution +Copying solution to: permutation-permutation-000008.solution +Copying solution to: permutation-permutation-000009.solution +Copying solution to: permutation-permutation-000010.solution +language Essence 1.3 + +letting p be permutation() +letting sn be partition({1, 2}, {3, 4}) +$ Visualisation for sn +$ 1 2 +$ 3 4 + +language Essence 1.3 + +letting p be permutation((3, 4)) +letting sn be partition({1, 2}, {3, 4}) +$ Visualisation for sn +$ 1 2 +$ 3 4 + +language Essence 1.3 + +letting p be permutation((2, 3)) +letting sn be partition({1, 3}, {2, 4}) +$ Visualisation for sn +$ 1 3 +$ 2 4 + +language Essence 1.3 + +letting p be permutation((2, 3, 4)) +letting sn be partition({1, 3}, {2, 4}) +$ Visualisation for sn +$ 1 3 +$ 2 4 + +language Essence 1.3 + +letting p be permutation((2, 4, 3)) +letting sn be partition({1, 4}, {2, 3}) +$ Visualisation for sn +$ 1 4 +$ 2 3 + +language Essence 1.3 + +letting p be permutation((2, 4)) +letting sn be partition({1, 4}, {2, 3}) +$ Visualisation for sn +$ 1 4 +$ 2 3 + +language Essence 1.3 + +letting p be permutation((1, 2)) +letting sn be partition({1, 2}, {3, 4}) +$ Visualisation for sn +$ 1 2 +$ 3 4 + +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4)) +letting sn be partition({1, 2}, {3, 4}) +$ Visualisation for sn +$ 1 2 +$ 3 4 + +language Essence 1.3 + +letting p be permutation((1, 2, 3)) +letting sn be partition({1, 4}, {2, 3}) +$ Visualisation for sn +$ 1 4 +$ 2 3 + +language Essence 1.3 + +letting p be permutation((1, 2, 3, 4)) +letting sn be partition({1, 4}, {2, 3}) +$ Visualisation for sn +$ 1 4 +$ 2 3 + diff --git a/tests/custom/permutations/17_image_partition/runthese.sh b/tests/custom/permutations/17_image_partition/runthese.sh new file mode 100644 index 0000000000..f7d9c58994 --- /dev/null +++ b/tests/custom/permutations/17_image_partition/runthese.sh @@ -0,0 +1 @@ +stack build --copy-bins --test --test-arguments "-p custom.permutations.17_image_partition" diff --git a/tests/custom/permutations/17_image_partition/unnamed/0010_find_partition_of_unnamed_BUG/permutation.essence b/tests/custom/permutations/17_image_partition/unnamed/0010_find_partition_of_unnamed_BUG/permutation.essence new file mode 100644 index 0000000000..eb8f38f09b --- /dev/null +++ b/tests/custom/permutations/17_image_partition/unnamed/0010_find_partition_of_unnamed_BUG/permutation.essence @@ -0,0 +1,4 @@ +letting n be new type of size 4 + +find sn : partition from n + diff --git a/tests/custom/permutations/17_image_partition/unnamed/0010_find_partition_of_unnamed_BUG/run.sh b/tests/custom/permutations/17_image_partition/unnamed/0010_find_partition_of_unnamed_BUG/run.sh new file mode 100755 index 0000000000..03373df6cb --- /dev/null +++ b/tests/custom/permutations/17_image_partition/unnamed/0010_find_partition_of_unnamed_BUG/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence --number-of-solutions=10 +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/18_image_matrix/int/0010_given_permutation_matrix_find_matrix/permutation.essence b/tests/custom/permutations/18_image_matrix/int/0010_given_permutation_matrix_find_matrix/permutation.essence new file mode 100644 index 0000000000..483c20a1b1 --- /dev/null +++ b/tests/custom/permutations/18_image_matrix/int/0010_given_permutation_matrix_find_matrix/permutation.essence @@ -0,0 +1,9 @@ +letting n be 4 + +given p : permutation of int(1..n) +given s : matrix indexed by [int(1..4)] of int(1..4) +find sn : matrix indexed by [int(1..4)] of int(1..4) + + +such that sn = image(p,s) + diff --git a/tests/custom/permutations/18_image_matrix/int/0010_given_permutation_matrix_find_matrix/permutation.param b/tests/custom/permutations/18_image_matrix/int/0010_given_permutation_matrix_find_matrix/permutation.param new file mode 100644 index 0000000000..598202acca --- /dev/null +++ b/tests/custom/permutations/18_image_matrix/int/0010_given_permutation_matrix_find_matrix/permutation.param @@ -0,0 +1,2 @@ +letting p be permutation((1,3)) +letting s be [1,2,3,4] diff --git a/tests/custom/permutations/18_image_matrix/int/0010_given_permutation_matrix_find_matrix/run.sh b/tests/custom/permutations/18_image_matrix/int/0010_given_permutation_matrix_find_matrix/run.sh new file mode 100755 index 0000000000..9dc67e67f5 --- /dev/null +++ b/tests/custom/permutations/18_image_matrix/int/0010_given_permutation_matrix_find_matrix/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence *.param +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/18_image_matrix/int/0010_given_permutation_matrix_find_matrix/stdout.expected b/tests/custom/permutations/18_image_matrix/int/0010_given_permutation_matrix_find_matrix/stdout.expected new file mode 100644 index 0000000000..75fa929da5 --- /dev/null +++ b/tests/custom/permutations/18_image_matrix/int/0010_given_permutation_matrix_find_matrix/stdout.expected @@ -0,0 +1,12 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime permutation.param +Copying solution to: permutation-permutation.solution +language Essence 1.3 + +letting sn be partition({1, 4}, {2, 3}) +$ Visualisation for sn +$ 1 4 +$ 2 3 + diff --git a/tests/custom/permutations/18_image_matrix/runthese.sh b/tests/custom/permutations/18_image_matrix/runthese.sh new file mode 100644 index 0000000000..fbd0b51ebd --- /dev/null +++ b/tests/custom/permutations/18_image_matrix/runthese.sh @@ -0,0 +1 @@ +stack build --copy-bins --test --test-arguments "-p custom.permutations.18_image_matrix" From e81c4e8d579e8fcc431d42c1f41e74b7b3be136f Mon Sep 17 00:00:00 2001 From: Fraser Dunlop Date: Thu, 10 Jan 2019 13:51:07 +0000 Subject: [PATCH 064/229] Fixed image of literal bug that was crashing SR --- src/Conjure/Compute/DomainOf.hs | 3 +- src/Conjure/Rules/Horizontal/Permutation.hs | 59 +++++++++++++++-- src/Conjure/Rules/Vertical/Permutation.hs | 66 +++++++++++++++++++ src/Conjure/UI/Model.hs | 4 +- .../permutation.essence | 7 ++ .../permutation.param | 1 + .../run.sh | 0 .../stdout.expected | 6 +- .../permutation.essence | 9 --- .../permutation.essence | 9 +++ .../permutation.param | 2 +- .../run.sh | 3 + .../stdout.expected | 8 +++ .../permutation.essence | 9 +++ .../permutation.param | 1 + .../run.sh | 3 + .../stdout.expected | 8 +++ 17 files changed, 176 insertions(+), 22 deletions(-) create mode 100644 tests/custom/permutations/18_image_matrix/int/0010_find_permutation_indexing_given_matrix/permutation.essence create mode 100644 tests/custom/permutations/18_image_matrix/int/0010_find_permutation_indexing_given_matrix/permutation.param rename tests/custom/permutations/18_image_matrix/int/{0010_given_permutation_matrix_find_matrix => 0010_find_permutation_indexing_given_matrix}/run.sh (100%) rename tests/custom/permutations/18_image_matrix/int/{0010_given_permutation_matrix_find_matrix => 0010_find_permutation_indexing_given_matrix}/stdout.expected (75%) delete mode 100644 tests/custom/permutations/18_image_matrix/int/0010_given_permutation_matrix_find_matrix/permutation.essence create mode 100644 tests/custom/permutations/18_image_matrix/int/0020_given_permutation_and_matrix_find_matrix/permutation.essence rename tests/custom/permutations/18_image_matrix/int/{0010_given_permutation_matrix_find_matrix => 0020_given_permutation_and_matrix_find_matrix}/permutation.param (57%) create mode 100755 tests/custom/permutations/18_image_matrix/int/0020_given_permutation_and_matrix_find_matrix/run.sh create mode 100644 tests/custom/permutations/18_image_matrix/int/0020_given_permutation_and_matrix_find_matrix/stdout.expected create mode 100644 tests/custom/permutations/18_image_matrix/int/0030_letting_permutation_given_matrix_find_matrix/permutation.essence create mode 100644 tests/custom/permutations/18_image_matrix/int/0030_letting_permutation_given_matrix_find_matrix/permutation.param create mode 100755 tests/custom/permutations/18_image_matrix/int/0030_letting_permutation_given_matrix_find_matrix/run.sh create mode 100644 tests/custom/permutations/18_image_matrix/int/0030_letting_permutation_given_matrix_find_matrix/stdout.expected diff --git a/src/Conjure/Compute/DomainOf.hs b/src/Conjure/Compute/DomainOf.hs index a28062bb4e..a76c0dc8e1 100644 --- a/src/Conjure/Compute/DomainOf.hs +++ b/src/Conjure/Compute/DomainOf.hs @@ -379,8 +379,9 @@ instance (Pretty x, TypeOf x) => DomainOf (OpHist x) where instance DomainOf (OpIff x) where domainOf _ = return DomainBool -instance (Pretty x, TypeOf x) => DomainOf (OpImage x) where +instance (Pretty x, TypeOf x, DomainOf x) => DomainOf (OpImage x) where domainOf op = mkDomainAny ("OpImage:" <++> pretty op) <$> typeOf op + indexDomainsOf (OpImage _ x) = indexDomainsOf x instance (Pretty x, TypeOf x) => DomainOf (OpImageSet x) where domainOf op = mkDomainAny ("OpImageSet:" <++> pretty op) <$> typeOf op diff --git a/src/Conjure/Rules/Horizontal/Permutation.hs b/src/Conjure/Rules/Horizontal/Permutation.hs index 661b3479bb..8d4d0e96c0 100644 --- a/src/Conjure/Rules/Horizontal/Permutation.hs +++ b/src/Conjure/Rules/Horizontal/Permutation.hs @@ -69,11 +69,14 @@ rule_Image_Literal = "permutation-image-literal" `namedRule` theRule where typeI <- typeOf i if typesUnify [inner, typeI] then do - let outLiteral = make functionLiteral (TypeFunction inner inner) [ (de,f de) | de <- join elems ] + let srtdel = sortBy compare (join elems) + domIndx = reTag AnyTag $ mkDomainInt (RangeSingle <$> srtdel) + matLit = make matrixLiteral (TypeMatrix (TypeInt AnyTag) inner) domIndx ( f <$> srtdel) return ( "Horizontal rule for permutation literal application to a single value (image), AsFunction representation" , do - return [essence| [&i, catchUndef(image(&outLiteral,&i),0)][toInt(&i in defined(&outLiteral))+1] |] + return [essence| [&i, catchUndef(&matLit[&i],0)][toInt(&i in toSet(&matLit))+1] |] + ) else if typeI `containsType` inner then na "rule_Image_Literal" @@ -123,9 +126,9 @@ rule_Permutation_Inverse = "permutation-inverse" `namedRule` theRule where rule_Compose_Image :: Rule rule_Compose_Image = "permutation-compose-image" `namedRule` theRule where theRule [essence| image(compose(&g, &h),&i) |] = do - case match permutationLiteral h of - Nothing -> return () --SR error when h is literal, fall back to rule_Compose - Just _ -> na "rule_Compose_Image" +-- case match permutationLiteral h of +-- Nothing -> return () --SR error when h is literal, fall back to rule_Compose +-- Just _ -> na "rule_Compose_Image" TypePermutation innerG <- typeOf g TypePermutation innerH <- typeOf g typeI <- typeOf i @@ -197,6 +200,7 @@ rule_Image_Comprehendable = "comprehendable-image" `namedRule` theRule where else na "rule_Image_Comprehendable" theRule _ = na "rule_Image_Comprehendable" + rule_Image_Sequence :: Rule rule_Image_Sequence = "image-sequence" `namedRule` theRule where theRule (Comprehension body gensOrConds) = do @@ -305,4 +309,49 @@ rule_Image_Incomprehendable = "comprehendable-image" `namedRule` theRule where else na "rule_Image_Comprehendable" theRule _ = na "rule_Image_Comprehendable" +---------------------------------------------------------------------------------- + +rule_Image_Matrix_Indexing :: Rule +rule_Image_Matrix_Indexing = "image-matrix-indexing" `namedRule` theRule where + theRule p = do + (matexp, indexer) <- match opIndexing p + (perm, mat) <- match opImage matexp + ty <- typeOf mat + case ty of TypeMatrix{} -> return () ; _ -> na "only applies to matrices" + (TypePermutation inn) <- typeOf perm + if ty `containsTypeComprehendable` inn + then do + return + ( "Horizontal rule for image of matrix under permutation" + , return $ [essence| image(&perm, &mat[image(&perm, &indexer)]) |] ) + else na "rule_Image_Matrix_Indexing" + + +rule_Image_Matrix_Indexing_Comprehension :: Rule +rule_Image_Matrix_Indexing_Comprehension = "image-matrix-indexing-comprehension" `namedRule` theRule where + theRule (Comprehension body gensOrConds) = do + (gocBefore, (pat, x), gocAfter) <- matchFirst gensOrConds $ \ goc -> case goc of + Generator (GenInExpr (Single pat) expr) -> return (pat, matchDefs [opToSet, opToMSet] expr) + _ -> na "rule_Image_Matrix_Indexing_Comprehension" + (matexp, indexer) <- match opIndexing x + (perm, mat) <- match opImage matexp + ty <- typeOf mat + case ty of TypeMatrix{} -> return () ; _ -> na "only applies to matrices" + (TypePermutation inn) <- typeOf perm + if ty `containsTypeComprehendable` inn + then do + return + ( "Horizontal rule for image of matrix under permutation" + , do + (dPat, d) <- quantifiedVar + return (Comprehension body $ + gocBefore + ++ [Generator (GenInExpr dPat [essence| &mat[image(&perm, &indexer)] |])] + ++ [ComprehensionLetting pat [essence| image(&perm, &d) |]] + ++ gocAfter) + ) + else na "rule_Image_Matrix_Indexing_Comprehension" + + theRule _ = na "rule_Image_Matrix_Indexing_Comprehension" + diff --git a/src/Conjure/Rules/Vertical/Permutation.hs b/src/Conjure/Rules/Vertical/Permutation.hs index b6c1df7ccb..c95080320d 100644 --- a/src/Conjure/Rules/Vertical/Permutation.hs +++ b/src/Conjure/Rules/Vertical/Permutation.hs @@ -1,6 +1,7 @@ {-# LANGUAGE QuasiQuotes #-} module Conjure.Rules.Vertical.Permutation where import Conjure.Rules.Import +import Conjure.Rules.Vertical.Matrix (flattenIfNeeded) rule_Cardinality :: Rule rule_Cardinality = "permutation-cardinality" `namedRule` theRule where @@ -83,4 +84,69 @@ rule_Image = "permutation-image{AsFunction}" `namedRule` theRule where theRule _ = na "rule_Image" +rule_Matrix_Image :: Rule +rule_Matrix_Image = "matrix-image" `namedRule` theRule where + theRule [essence| image(&perm, &y) |] = do + ty@(TypeMatrix _ _) <- typeOf y + (TypePermutation inn) <- typeOf perm + if ty `containsTypeComprehendable` inn + then do + y' <- flattenIfNeeded y + dm@(DomainMatrix dyindex _) <- domainOf y' + return + ( "Horizontal rule for image matrix" + , do + (dPat, d) <- quantifiedVar + (pyName, py) <- auxiliaryVar + return $ WithLocals + [essence| &py |] + (AuxiliaryVars + [ Declaration (FindOrGiven LocalFind pyName dm) + , SuchThat + [ [essence| + forAll &dPat : &dyindex . + &py[image(&perm,&d)] = image(&perm,&y'[&d]) + |] + ] + ] + ) + ) + else na "rule_Matrix_Image" + theRule _ = na "rule_Matrix_Image" + +rule_Matrix_Image_Comprehension :: Rule +rule_Matrix_Image_Comprehension = "matrix-image-comprehension" `namedRule` theRule where + theRule (Comprehension body gensOrConds) = do + (gocBefore, (pat, perm, y), gocAfter) <- matchFirst gensOrConds $ \ goc -> case goc of + Generator (GenInExpr pat [essence| image(&perm, &y) |]) -> return (pat, perm, y) + _ -> na "rule_Matrix_Image" + ty@(TypeMatrix _ _) <- typeOf y + (TypePermutation inn) <- typeOf perm + if not $ typesUnify [ty, inn] + then do + unless (isPrimitiveType ty) $ fail ("not a primitive type:" <+> pretty ty) + y' <- flattenIfNeeded y + dm@(DomainMatrix dyindex _) <- domainOf y' + return + ( "Horizontal rule for image matrix in comprehension" + , do + (dPat, d) <- quantifiedVar + (pyName, py) <- auxiliaryVar + return $ WithLocals + (Comprehension body $ gocBefore + ++ [Generator (GenInExpr pat [essence| &py |])] + ++ gocAfter) + (AuxiliaryVars + [ Declaration (FindOrGiven LocalFind pyName dm) + , SuchThat + [ [essence| + forAll &dPat : &dyindex . + &py[image(&perm,&d)] = image(&perm,&y'[&d]) + |] + ] + ] + ) + ) + else na "rule_Matrix_Image_Comprehension" + theRule _ = na "rule_Matrix_Image_Comprehension" diff --git a/src/Conjure/UI/Model.hs b/src/Conjure/UI/Model.hs index c76e8d5c42..17dbdd8edb 100644 --- a/src/Conjure/UI/Model.hs +++ b/src/Conjure/UI/Model.hs @@ -1204,8 +1204,10 @@ horizontalRules = , Horizontal.Permutation.rule_Equality , Horizontal.Permutation.rule_Comprehension , Horizontal.Permutation.rule_Compose_Image - , Horizontal.Permutation.rule_Compose +-- , Horizontal.Permutation.rule_Compose , Horizontal.Permutation.rule_Image_Literal + , Horizontal.Permutation.rule_Image_Matrix_Indexing + , Horizontal.Permutation.rule_Image_Matrix_Indexing_Comprehension , Horizontal.Permutation.rule_Image_Partition , Horizontal.Permutation.rule_Image_Sequence , Horizontal.Permutation.rule_Image_Sequence_Defined diff --git a/tests/custom/permutations/18_image_matrix/int/0010_find_permutation_indexing_given_matrix/permutation.essence b/tests/custom/permutations/18_image_matrix/int/0010_find_permutation_indexing_given_matrix/permutation.essence new file mode 100644 index 0000000000..c91bce7e79 --- /dev/null +++ b/tests/custom/permutations/18_image_matrix/int/0010_find_permutation_indexing_given_matrix/permutation.essence @@ -0,0 +1,7 @@ +letting n be 4 + +find p : permutation of int(1..n) +given s : matrix indexed by [int(1..4)] of int(5..8) + +such that 8 = image(p,s)[2] + diff --git a/tests/custom/permutations/18_image_matrix/int/0010_find_permutation_indexing_given_matrix/permutation.param b/tests/custom/permutations/18_image_matrix/int/0010_find_permutation_indexing_given_matrix/permutation.param new file mode 100644 index 0000000000..4f040eeac8 --- /dev/null +++ b/tests/custom/permutations/18_image_matrix/int/0010_find_permutation_indexing_given_matrix/permutation.param @@ -0,0 +1 @@ +letting s be [5,6,7,8] diff --git a/tests/custom/permutations/18_image_matrix/int/0010_given_permutation_matrix_find_matrix/run.sh b/tests/custom/permutations/18_image_matrix/int/0010_find_permutation_indexing_given_matrix/run.sh similarity index 100% rename from tests/custom/permutations/18_image_matrix/int/0010_given_permutation_matrix_find_matrix/run.sh rename to tests/custom/permutations/18_image_matrix/int/0010_find_permutation_indexing_given_matrix/run.sh diff --git a/tests/custom/permutations/18_image_matrix/int/0010_given_permutation_matrix_find_matrix/stdout.expected b/tests/custom/permutations/18_image_matrix/int/0010_find_permutation_indexing_given_matrix/stdout.expected similarity index 75% rename from tests/custom/permutations/18_image_matrix/int/0010_given_permutation_matrix_find_matrix/stdout.expected rename to tests/custom/permutations/18_image_matrix/int/0010_find_permutation_indexing_given_matrix/stdout.expected index 75fa929da5..0a2c68038b 100644 --- a/tests/custom/permutations/18_image_matrix/int/0010_given_permutation_matrix_find_matrix/stdout.expected +++ b/tests/custom/permutations/18_image_matrix/int/0010_find_permutation_indexing_given_matrix/stdout.expected @@ -5,8 +5,4 @@ Savile Row: model000001.eprime permutation.param Copying solution to: permutation-permutation.solution language Essence 1.3 -letting sn be partition({1, 4}, {2, 3}) -$ Visualisation for sn -$ 1 4 -$ 2 3 - +letting p be permutation((2, 4, 3)) diff --git a/tests/custom/permutations/18_image_matrix/int/0010_given_permutation_matrix_find_matrix/permutation.essence b/tests/custom/permutations/18_image_matrix/int/0010_given_permutation_matrix_find_matrix/permutation.essence deleted file mode 100644 index 483c20a1b1..0000000000 --- a/tests/custom/permutations/18_image_matrix/int/0010_given_permutation_matrix_find_matrix/permutation.essence +++ /dev/null @@ -1,9 +0,0 @@ -letting n be 4 - -given p : permutation of int(1..n) -given s : matrix indexed by [int(1..4)] of int(1..4) -find sn : matrix indexed by [int(1..4)] of int(1..4) - - -such that sn = image(p,s) - diff --git a/tests/custom/permutations/18_image_matrix/int/0020_given_permutation_and_matrix_find_matrix/permutation.essence b/tests/custom/permutations/18_image_matrix/int/0020_given_permutation_and_matrix_find_matrix/permutation.essence new file mode 100644 index 0000000000..fcf2b326c7 --- /dev/null +++ b/tests/custom/permutations/18_image_matrix/int/0020_given_permutation_and_matrix_find_matrix/permutation.essence @@ -0,0 +1,9 @@ +letting n be 4 + +given p : permutation of int(1..n) +given s : matrix indexed by [int(1..4)] of int(5..8) +find sn : matrix indexed by [int(1..4)] of int(5..8) + + +such that sn = image(p,s) + diff --git a/tests/custom/permutations/18_image_matrix/int/0010_given_permutation_matrix_find_matrix/permutation.param b/tests/custom/permutations/18_image_matrix/int/0020_given_permutation_and_matrix_find_matrix/permutation.param similarity index 57% rename from tests/custom/permutations/18_image_matrix/int/0010_given_permutation_matrix_find_matrix/permutation.param rename to tests/custom/permutations/18_image_matrix/int/0020_given_permutation_and_matrix_find_matrix/permutation.param index 598202acca..3ff703ccd0 100644 --- a/tests/custom/permutations/18_image_matrix/int/0010_given_permutation_matrix_find_matrix/permutation.param +++ b/tests/custom/permutations/18_image_matrix/int/0020_given_permutation_and_matrix_find_matrix/permutation.param @@ -1,2 +1,2 @@ letting p be permutation((1,3)) -letting s be [1,2,3,4] +letting s be [5,6,7,8] diff --git a/tests/custom/permutations/18_image_matrix/int/0020_given_permutation_and_matrix_find_matrix/run.sh b/tests/custom/permutations/18_image_matrix/int/0020_given_permutation_and_matrix_find_matrix/run.sh new file mode 100755 index 0000000000..9dc67e67f5 --- /dev/null +++ b/tests/custom/permutations/18_image_matrix/int/0020_given_permutation_and_matrix_find_matrix/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence *.param +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/18_image_matrix/int/0020_given_permutation_and_matrix_find_matrix/stdout.expected b/tests/custom/permutations/18_image_matrix/int/0020_given_permutation_and_matrix_find_matrix/stdout.expected new file mode 100644 index 0000000000..448a5ef974 --- /dev/null +++ b/tests/custom/permutations/18_image_matrix/int/0020_given_permutation_and_matrix_find_matrix/stdout.expected @@ -0,0 +1,8 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime permutation.param +Copying solution to: permutation-permutation.solution +language Essence 1.3 + +letting sn be [7, 6, 5, 8; int(1..4)] diff --git a/tests/custom/permutations/18_image_matrix/int/0030_letting_permutation_given_matrix_find_matrix/permutation.essence b/tests/custom/permutations/18_image_matrix/int/0030_letting_permutation_given_matrix_find_matrix/permutation.essence new file mode 100644 index 0000000000..f4b9b4f76f --- /dev/null +++ b/tests/custom/permutations/18_image_matrix/int/0030_letting_permutation_given_matrix_find_matrix/permutation.essence @@ -0,0 +1,9 @@ +letting n be 4 + +letting p be permutation((1,3)) +given s : matrix indexed by [int(1..4)] of int(5..8) +find sn : matrix indexed by [int(1..4)] of int(5..8) + + +such that sn = image(p,s) + diff --git a/tests/custom/permutations/18_image_matrix/int/0030_letting_permutation_given_matrix_find_matrix/permutation.param b/tests/custom/permutations/18_image_matrix/int/0030_letting_permutation_given_matrix_find_matrix/permutation.param new file mode 100644 index 0000000000..4f040eeac8 --- /dev/null +++ b/tests/custom/permutations/18_image_matrix/int/0030_letting_permutation_given_matrix_find_matrix/permutation.param @@ -0,0 +1 @@ +letting s be [5,6,7,8] diff --git a/tests/custom/permutations/18_image_matrix/int/0030_letting_permutation_given_matrix_find_matrix/run.sh b/tests/custom/permutations/18_image_matrix/int/0030_letting_permutation_given_matrix_find_matrix/run.sh new file mode 100755 index 0000000000..9dc67e67f5 --- /dev/null +++ b/tests/custom/permutations/18_image_matrix/int/0030_letting_permutation_given_matrix_find_matrix/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence *.param +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/18_image_matrix/int/0030_letting_permutation_given_matrix_find_matrix/stdout.expected b/tests/custom/permutations/18_image_matrix/int/0030_letting_permutation_given_matrix_find_matrix/stdout.expected new file mode 100644 index 0000000000..448a5ef974 --- /dev/null +++ b/tests/custom/permutations/18_image_matrix/int/0030_letting_permutation_given_matrix_find_matrix/stdout.expected @@ -0,0 +1,8 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime permutation.param +Copying solution to: permutation-permutation.solution +language Essence 1.3 + +letting sn be [7, 6, 5, 8; int(1..4)] From f2abde262c16e6ea969291240566ef69662df623 Mon Sep 17 00:00:00 2001 From: Fraser Dunlop Date: Thu, 10 Jan 2019 15:23:36 +0000 Subject: [PATCH 065/229] Matrix test --- src/Conjure/Rules/Horizontal/Permutation.hs | 36 ------------------- .../permutation.essence | 7 ++++ .../run.sh | 3 ++ .../stdout.expected | 8 +++++ 4 files changed, 18 insertions(+), 36 deletions(-) create mode 100644 tests/custom/permutations/18_image_matrix/int/0015_find_permutation_indexing_given_matrix/permutation.essence create mode 100755 tests/custom/permutations/18_image_matrix/int/0015_find_permutation_indexing_given_matrix/run.sh create mode 100644 tests/custom/permutations/18_image_matrix/int/0015_find_permutation_indexing_given_matrix/stdout.expected diff --git a/src/Conjure/Rules/Horizontal/Permutation.hs b/src/Conjure/Rules/Horizontal/Permutation.hs index 8d4d0e96c0..31ebc006b9 100644 --- a/src/Conjure/Rules/Horizontal/Permutation.hs +++ b/src/Conjure/Rules/Horizontal/Permutation.hs @@ -107,8 +107,6 @@ rule_In = "permutation-in" `namedRule` theRule where rule_Permutation_Inverse :: Rule rule_Permutation_Inverse = "permutation-inverse" `namedRule` theRule where theRule [essence| inverse(&p1, &p2)|] = do - case p1 of WithLocals{} -> na "bubble-delay" ; _ -> return () - case p2 of WithLocals{} -> na "bubble-delay" ; _ -> return () TypePermutation{} <- typeOf p1 TypePermutation{} <- typeOf p2 return @@ -126,9 +124,6 @@ rule_Permutation_Inverse = "permutation-inverse" `namedRule` theRule where rule_Compose_Image :: Rule rule_Compose_Image = "permutation-compose-image" `namedRule` theRule where theRule [essence| image(compose(&g, &h),&i) |] = do --- case match permutationLiteral h of --- Nothing -> return () --SR error when h is literal, fall back to rule_Compose --- Just _ -> na "rule_Compose_Image" TypePermutation innerG <- typeOf g TypePermutation innerH <- typeOf g typeI <- typeOf i @@ -142,37 +137,6 @@ rule_Compose_Image = "permutation-compose-image" `namedRule` theRule where theRule _ = na "rule_Compose_Image" -rule_Compose :: Rule -rule_Compose = "permutation-compose" `namedRule` theRule where - theRule [essence| compose(&g,&h) |] = do - TypePermutation innerG <- typeOf g - TypePermutation innerH <- typeOf h - dg <- domainOf g - dh <- domainOf h - if typesUnify [innerG, innerH] - then do - du <- domainUnion dg dh - return ( "Horizontal rule for permutation composition" - , do - - (lPat, l) <- quantifiedVar - (pName, p) <- auxiliaryVar - return $ WithLocals - [essence| &p |] - ( AuxiliaryVars - [ (Declaration (FindOrGiven LocalFind pName du)) - , SuchThat - [ [essence| - forAll &lPat in (defined(&g) union defined(&h)) . - image(&p,&l) = image(&g,image(&h,&l)) - |] - ] - ] - ) - ) - else na "rule_Compose" - theRule _ = na "rule_Compose" - rule_Image_Comprehendable :: Rule rule_Image_Comprehendable = "comprehendable-image" `namedRule` theRule where theRule (Comprehension body gensOrConds) = do diff --git a/tests/custom/permutations/18_image_matrix/int/0015_find_permutation_indexing_given_matrix/permutation.essence b/tests/custom/permutations/18_image_matrix/int/0015_find_permutation_indexing_given_matrix/permutation.essence new file mode 100644 index 0000000000..de2e14a788 --- /dev/null +++ b/tests/custom/permutations/18_image_matrix/int/0015_find_permutation_indexing_given_matrix/permutation.essence @@ -0,0 +1,7 @@ +letting n be 4 + +find p : permutation of int(1..n) +letting s be [5,6,7,8] + +such that 8 = image(p,s)[2] + diff --git a/tests/custom/permutations/18_image_matrix/int/0015_find_permutation_indexing_given_matrix/run.sh b/tests/custom/permutations/18_image_matrix/int/0015_find_permutation_indexing_given_matrix/run.sh new file mode 100755 index 0000000000..b4899d6266 --- /dev/null +++ b/tests/custom/permutations/18_image_matrix/int/0015_find_permutation_indexing_given_matrix/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/18_image_matrix/int/0015_find_permutation_indexing_given_matrix/stdout.expected b/tests/custom/permutations/18_image_matrix/int/0015_find_permutation_indexing_given_matrix/stdout.expected new file mode 100644 index 0000000000..0a2c68038b --- /dev/null +++ b/tests/custom/permutations/18_image_matrix/int/0015_find_permutation_indexing_given_matrix/stdout.expected @@ -0,0 +1,8 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime permutation.param +Copying solution to: permutation-permutation.solution +language Essence 1.3 + +letting p be permutation((2, 4, 3)) From 04ada6f5bf424335ced313c1e4093ee98dd1de7a Mon Sep 17 00:00:00 2001 From: Fraser Dunlop Date: Fri, 1 Feb 2019 15:29:35 +0000 Subject: [PATCH 066/229] Counting sets of permutations now possible --- src/Conjure/Rules/DontCare.hs | 25 ++++++++++++++----- src/Conjure/Rules/Vertical/Permutation.hs | 15 +++++++++++ src/Conjure/UI/Model.hs | 3 +++ .../permutation.essence | 4 +++ .../0010_set_of_permutations/run.sh | 3 +++ .../0010_set_of_permutations/stdout.expected | 10 ++++++++ .../permutations/20_counting/runthese.sh | 1 + 7 files changed, 55 insertions(+), 6 deletions(-) create mode 100644 tests/custom/permutations/20_counting/0010_set_of_permutations/permutation.essence create mode 100755 tests/custom/permutations/20_counting/0010_set_of_permutations/run.sh create mode 100644 tests/custom/permutations/20_counting/0010_set_of_permutations/stdout.expected create mode 100644 tests/custom/permutations/20_counting/runthese.sh diff --git a/src/Conjure/Rules/DontCare.hs b/src/Conjure/Rules/DontCare.hs index 9542c680c4..b4810450cd 100644 --- a/src/Conjure/Rules/DontCare.hs +++ b/src/Conjure/Rules/DontCare.hs @@ -88,6 +88,19 @@ rule_Matrix = "dontCare-matrix" `namedRule` theRule where return [essence| forAll &iPat : &index . dontCare(&x[&i]) |] ) +rule_Permutation :: Rule +rule_Permutation = "dontCare-permutation" `namedRule` theRule where + theRule p = do + x <- match opDontCare p + DomainPermutation _ _ inner <- domainOf x + return + ( "dontCare handling for permutation" + , do + (iPat, i) <- quantifiedVar + return [essence| forAll &iPat : &inner . image(&x,&i) = &i |] + ) + + rule_Abstract :: Rule rule_Abstract = "dontCare-abstract" `namedRule` theRule where @@ -95,12 +108,12 @@ rule_Abstract = "dontCare-abstract" `namedRule` theRule where x <- match opDontCare p ty <- typeOf x case ty of - TypeSet {} -> return () - TypeMSet {} -> return () - TypeSequence {} -> return () - TypeFunction {} -> return () - TypeRelation {} -> return () - TypePartition{} -> return () + TypeSet {} -> return () + TypeMSet {} -> return () + TypeSequence {} -> return () + TypeFunction {} -> return () + TypeRelation {} -> return () + TypePartition{} -> return () _ -> na "not a known abstract domain" hasRepresentation x xs <- downX1 x diff --git a/src/Conjure/Rules/Vertical/Permutation.hs b/src/Conjure/Rules/Vertical/Permutation.hs index dff4556d6e..3689fa9a55 100644 --- a/src/Conjure/Rules/Vertical/Permutation.hs +++ b/src/Conjure/Rules/Vertical/Permutation.hs @@ -84,6 +84,21 @@ rule_Image = "permutation-image{AsFunction}" `namedRule` theRule where theRule _ = na "rule_Image" +rule_Permutation_DotLt :: Rule +rule_Permutation_DotLt = "permuation-dotlt" `namedRule` theRule where + theRule [essence| &lhs .< &rhs |] = do + TypePermutation _ <- typeOf lhs + TypePermutation _ <- typeOf rhs + [fl] <- downX1 lhs + [fr] <- downX1 rhs + return + ( "Vertical rule for permutation dot less." + , return [essence| &fl .< &fr |] + ) + theRule _ = na "rule_Permutation_DotLt" + + + rule_Matrix_Image :: Rule rule_Matrix_Image = "matrix-image" `namedRule` theRule where theRule [essence| image(&perm, &y) |] = do diff --git a/src/Conjure/UI/Model.hs b/src/Conjure/UI/Model.hs index 95c6eedd23..bc012e0168 100644 --- a/src/Conjure/UI/Model.hs +++ b/src/Conjure/UI/Model.hs @@ -1151,6 +1151,8 @@ verticalRules = , Vertical.Permutation.rule_Cardinality , Vertical.Permutation.rule_Defined , Vertical.Permutation.rule_Comprehension + , Vertical.Permutation.rule_Permutation_DotLt + , Vertical.Tuple.rule_Tuple_Eq , Vertical.Tuple.rule_Tuple_Neq @@ -1419,6 +1421,7 @@ otherRules = , DontCare.rule_Tuple , DontCare.rule_Record , DontCare.rule_Variant + , DontCare.rule_Permutation , DontCare.rule_Matrix , DontCare.rule_Abstract ] diff --git a/tests/custom/permutations/20_counting/0010_set_of_permutations/permutation.essence b/tests/custom/permutations/20_counting/0010_set_of_permutations/permutation.essence new file mode 100644 index 0000000000..fa4c3992f1 --- /dev/null +++ b/tests/custom/permutations/20_counting/0010_set_of_permutations/permutation.essence @@ -0,0 +1,4 @@ +find s : set of permutation of int(1..3) + +maximising |s| + diff --git a/tests/custom/permutations/20_counting/0010_set_of_permutations/run.sh b/tests/custom/permutations/20_counting/0010_set_of_permutations/run.sh new file mode 100755 index 0000000000..a1691af90c --- /dev/null +++ b/tests/custom/permutations/20_counting/0010_set_of_permutations/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/20_counting/0010_set_of_permutations/stdout.expected b/tests/custom/permutations/20_counting/0010_set_of_permutations/stdout.expected new file mode 100644 index 0000000000..3b1723c783 --- /dev/null +++ b/tests/custom/permutations/20_counting/0010_set_of_permutations/stdout.expected @@ -0,0 +1,10 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Copying solution to: permutation.solution +language Essence 1.3 + +letting s be + {permutation(), permutation((1, 2)), permutation((1, 2, 3)), permutation((1, 3)), permutation((1, 3, 2)), + permutation((2, 3))} diff --git a/tests/custom/permutations/20_counting/runthese.sh b/tests/custom/permutations/20_counting/runthese.sh new file mode 100644 index 0000000000..c09b909f62 --- /dev/null +++ b/tests/custom/permutations/20_counting/runthese.sh @@ -0,0 +1 @@ +stack build --copy-bins --test --test-arguments "-p custom.permutations.20_counting" From 2ebd819e479680eeec1d6e4c4f93107c8b1207e4 Mon Sep 17 00:00:00 2001 From: Fraser Dunlop Date: Fri, 8 Feb 2019 12:49:50 +0000 Subject: [PATCH 067/229] counting + superpermutation tests --- src/Conjure/Rules/Horizontal/Permutation.hs | 14 +++++++++++ src/Conjure/UI/Model.hs | 1 + .../stderr.expected | 25 +++++++++++++++++++ .../stdout.expected | 8 ------ .../stderr.expected | 7 ++++++ .../stdout.expected | 4 +++ .../permutation.essence | 0 .../run.sh | 0 .../stdout.expected | 0 .../permutation.essence | 4 +++ .../0020_set_of_permutations_size_4/run.sh | 3 +++ .../stdout.expected | 12 +++++++++ .../0010_size_3/permutation.essence | 13 ++++++++++ .../0010_size_3/permutation.param | 6 +++++ .../21_superpermutations/0010_size_3/run.sh | 3 +++ .../0010_size_3/stdout.expected | 19 ++++++++++++++ .../0020_size_3/permutation.essence | 8 ++++++ .../0020_size_3/permutation.param | 5 ++++ .../21_superpermutations/0020_size_3/run.sh | 3 +++ .../0020_size_3/stdout.expected | 8 ++++++ .../21_superpermutations/runthese.sh | 1 + 21 files changed, 136 insertions(+), 8 deletions(-) create mode 100644 tests/custom/permutations/17_image_partition/enum/0010_given_partition_of_enum_BUG/stderr.expected create mode 100644 tests/custom/permutations/17_image_partition/enum/0020_find_partition_of_enum_BUG/stderr.expected create mode 100644 tests/custom/permutations/17_image_partition/enum/0020_find_partition_of_enum_BUG/stdout.expected rename tests/custom/permutations/20_counting/{0010_set_of_permutations => 0010_set_of_permutations_size_3}/permutation.essence (100%) rename tests/custom/permutations/20_counting/{0010_set_of_permutations => 0010_set_of_permutations_size_3}/run.sh (100%) rename tests/custom/permutations/20_counting/{0010_set_of_permutations => 0010_set_of_permutations_size_3}/stdout.expected (100%) create mode 100644 tests/custom/permutations/20_counting/0020_set_of_permutations_size_4/permutation.essence create mode 100755 tests/custom/permutations/20_counting/0020_set_of_permutations_size_4/run.sh create mode 100644 tests/custom/permutations/20_counting/0020_set_of_permutations_size_4/stdout.expected create mode 100644 tests/custom/permutations/21_superpermutations/0010_size_3/permutation.essence create mode 100644 tests/custom/permutations/21_superpermutations/0010_size_3/permutation.param create mode 100755 tests/custom/permutations/21_superpermutations/0010_size_3/run.sh create mode 100644 tests/custom/permutations/21_superpermutations/0010_size_3/stdout.expected create mode 100644 tests/custom/permutations/21_superpermutations/0020_size_3/permutation.essence create mode 100644 tests/custom/permutations/21_superpermutations/0020_size_3/permutation.param create mode 100755 tests/custom/permutations/21_superpermutations/0020_size_3/run.sh create mode 100644 tests/custom/permutations/21_superpermutations/0020_size_3/stdout.expected create mode 100644 tests/custom/permutations/21_superpermutations/runthese.sh diff --git a/src/Conjure/Rules/Horizontal/Permutation.hs b/src/Conjure/Rules/Horizontal/Permutation.hs index 80e7741f55..b2463681fe 100644 --- a/src/Conjure/Rules/Horizontal/Permutation.hs +++ b/src/Conjure/Rules/Horizontal/Permutation.hs @@ -164,6 +164,20 @@ rule_Image_Comprehendable = "comprehendable-image" `namedRule` theRule where else na "rule_Image_Comprehendable" theRule _ = na "rule_Image_Comprehendable" +rule_Image_Sequence_Literal :: Rule +rule_Image_Sequence_Literal = "image-permutation-sequence-literal" `namedRule` theRule where + theRule expr = do + (perm,seq) <- match opImage expr + (TypeSequence t, elems) <- match sequenceLiteral seq + (TypePermutation inn) <- typeOf perm + let outLiteral = AbstractLiteral $ AbsLitSequence [ [essence| image(&perm,&e) |] | e <- elems ] + return + ( "Comprehension on permutation image of sequence literals" + , return [essence| &outLiteral |] + ) + theRule _ = na "rule_Image_Sequence_Literal" + + rule_Image_Sequence :: Rule rule_Image_Sequence = "image-sequence" `namedRule` theRule where diff --git a/src/Conjure/UI/Model.hs b/src/Conjure/UI/Model.hs index bc012e0168..ea25f6a85e 100644 --- a/src/Conjure/UI/Model.hs +++ b/src/Conjure/UI/Model.hs @@ -1268,6 +1268,7 @@ horizontalRules = , Horizontal.Permutation.rule_Comprehension , Horizontal.Permutation.rule_Compose_Image , Horizontal.Permutation.rule_Image_Matrix_Indexing + , Horizontal.Permutation.rule_Image_Sequence_Literal -- , Horizontal.Permutation.rule_Image_Matrix_Indexing_Comprehension -- , Horizontal.Permutation.rule_Compose , Horizontal.Permutation.rule_Image_Literal diff --git a/tests/custom/permutations/17_image_partition/enum/0010_given_partition_of_enum_BUG/stderr.expected b/tests/custom/permutations/17_image_partition/enum/0010_given_partition_of_enum_BUG/stderr.expected new file mode 100644 index 0000000000..76cbe64a84 --- /dev/null +++ b/tests/custom/permutations/17_image_partition/enum/0010_given_partition_of_enum_BUG/stderr.expected @@ -0,0 +1,25 @@ +conjure: +Ran commands: + +Exception: This should never happen, sorry! + +However, it did happen, so it must be a bug. Please report it to us! + +Conjure is actively maintained, we will get back to you as soon as possible. +You can help us by providing a minimal failing example. + +Also include the repository version for this build: f2abde262 (2019-01-10 15:23:36 +0000) + +Issue tracker: http://github.com/conjure-cp/conjure/issues + + +IO Error +No value for: n_EnumSize +Bindings in context: + s: partition({1, 2}, {3, 4}) + n: `int(1..4)` + +CallStack (from HasCallStack): + error, called at src/Conjure/Bug.hs:21:15 in conjure-cp-2.2.0-4cfnInyB42NJSP2i6f0krZ:Conjure.Bug + bug, called at src/Conjure/Bug.hs:47:16 in conjure-cp-2.2.0-4cfnInyB42NJSP2i6f0krZ:Conjure.Bug +cat: conjure-output/*.solution: No such file or directory diff --git a/tests/custom/permutations/17_image_partition/enum/0010_given_partition_of_enum_BUG/stdout.expected b/tests/custom/permutations/17_image_partition/enum/0010_given_partition_of_enum_BUG/stdout.expected index 75fa929da5..a1634e8c4c 100644 --- a/tests/custom/permutations/17_image_partition/enum/0010_given_partition_of_enum_BUG/stdout.expected +++ b/tests/custom/permutations/17_image_partition/enum/0010_given_partition_of_enum_BUG/stdout.expected @@ -2,11 +2,3 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output Savile Row: model000001.eprime permutation.param -Copying solution to: permutation-permutation.solution -language Essence 1.3 - -letting sn be partition({1, 4}, {2, 3}) -$ Visualisation for sn -$ 1 4 -$ 2 3 - diff --git a/tests/custom/permutations/17_image_partition/enum/0020_find_partition_of_enum_BUG/stderr.expected b/tests/custom/permutations/17_image_partition/enum/0020_find_partition_of_enum_BUG/stderr.expected new file mode 100644 index 0000000000..3365ae2ca0 --- /dev/null +++ b/tests/custom/permutations/17_image_partition/enum/0020_find_partition_of_enum_BUG/stderr.expected @@ -0,0 +1,7 @@ +Error: + Savile Row stdout: ERROR: Identifier not defined: n_EnumSize + + Savile Row stderr: ERROR: Failed type checking:find sn_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker: int(0..n_EnumSize) + + Savile Row exit-code: 1 +cat: conjure-output/*.solution: No such file or directory diff --git a/tests/custom/permutations/17_image_partition/enum/0020_find_partition_of_enum_BUG/stdout.expected b/tests/custom/permutations/17_image_partition/enum/0020_find_partition_of_enum_BUG/stdout.expected new file mode 100644 index 0000000000..c557beda73 --- /dev/null +++ b/tests/custom/permutations/17_image_partition/enum/0020_find_partition_of_enum_BUG/stdout.expected @@ -0,0 +1,4 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime diff --git a/tests/custom/permutations/20_counting/0010_set_of_permutations/permutation.essence b/tests/custom/permutations/20_counting/0010_set_of_permutations_size_3/permutation.essence similarity index 100% rename from tests/custom/permutations/20_counting/0010_set_of_permutations/permutation.essence rename to tests/custom/permutations/20_counting/0010_set_of_permutations_size_3/permutation.essence diff --git a/tests/custom/permutations/20_counting/0010_set_of_permutations/run.sh b/tests/custom/permutations/20_counting/0010_set_of_permutations_size_3/run.sh similarity index 100% rename from tests/custom/permutations/20_counting/0010_set_of_permutations/run.sh rename to tests/custom/permutations/20_counting/0010_set_of_permutations_size_3/run.sh diff --git a/tests/custom/permutations/20_counting/0010_set_of_permutations/stdout.expected b/tests/custom/permutations/20_counting/0010_set_of_permutations_size_3/stdout.expected similarity index 100% rename from tests/custom/permutations/20_counting/0010_set_of_permutations/stdout.expected rename to tests/custom/permutations/20_counting/0010_set_of_permutations_size_3/stdout.expected diff --git a/tests/custom/permutations/20_counting/0020_set_of_permutations_size_4/permutation.essence b/tests/custom/permutations/20_counting/0020_set_of_permutations_size_4/permutation.essence new file mode 100644 index 0000000000..2644118b13 --- /dev/null +++ b/tests/custom/permutations/20_counting/0020_set_of_permutations_size_4/permutation.essence @@ -0,0 +1,4 @@ +find s : set of permutation of int(1..4) + +maximising |s| + diff --git a/tests/custom/permutations/20_counting/0020_set_of_permutations_size_4/run.sh b/tests/custom/permutations/20_counting/0020_set_of_permutations_size_4/run.sh new file mode 100755 index 0000000000..a1691af90c --- /dev/null +++ b/tests/custom/permutations/20_counting/0020_set_of_permutations_size_4/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/20_counting/0020_set_of_permutations_size_4/stdout.expected b/tests/custom/permutations/20_counting/0020_set_of_permutations_size_4/stdout.expected new file mode 100644 index 0000000000..6faf256466 --- /dev/null +++ b/tests/custom/permutations/20_counting/0020_set_of_permutations_size_4/stdout.expected @@ -0,0 +1,12 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Copying solution to: permutation.solution +language Essence 1.3 + +letting s be + {permutation(), permutation((1, 2)), permutation((1, 2), (3, 4)), permutation((1, 2, 3)), + permutation((1, 2, 3, 4)), permutation((1, 2, 4)), permutation((1, 2, 4, 3)), permutation((1, 3)), + permutation((1, 3, 2)), permutation((1, 3, 4)), permutation((1, 3, 4, 2)), permutation((2, 3)), + permutation((2, 3, 4)), permutation((2, 4)), permutation((2, 4, 3)), permutation((3, 4))} diff --git a/tests/custom/permutations/21_superpermutations/0010_size_3/permutation.essence b/tests/custom/permutations/21_superpermutations/0010_size_3/permutation.essence new file mode 100644 index 0000000000..7aecd27844 --- /dev/null +++ b/tests/custom/permutations/21_superpermutations/0010_size_3/permutation.essence @@ -0,0 +1,13 @@ +given s : set of permutation of int(1..3) +given q : sequence (size 3) of int(1..3) + +find qs : set of sequence (size 3) of int(1..3) +such that |qs| = |s| /\ and([ image(p,q) in qs | p <- s]) + +find superperm : sequence (maxSize 100) of int(1..3) + +such that + and([ z substring superperm | z <- qs ]) + +minimising |superperm| + diff --git a/tests/custom/permutations/21_superpermutations/0010_size_3/permutation.param b/tests/custom/permutations/21_superpermutations/0010_size_3/permutation.param new file mode 100644 index 0000000000..991fa7b6e4 --- /dev/null +++ b/tests/custom/permutations/21_superpermutations/0010_size_3/permutation.param @@ -0,0 +1,6 @@ + +letting s be + {permutation(), permutation((1, 2)), permutation((1, 2, 3)), permutation((1, 3)), permutation((1, 3, 2)), + permutation((2, 3))} + +letting q be sequence(1,2,3) diff --git a/tests/custom/permutations/21_superpermutations/0010_size_3/run.sh b/tests/custom/permutations/21_superpermutations/0010_size_3/run.sh new file mode 100755 index 0000000000..4194275f38 --- /dev/null +++ b/tests/custom/permutations/21_superpermutations/0010_size_3/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence *.param +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/21_superpermutations/0010_size_3/stdout.expected b/tests/custom/permutations/21_superpermutations/0010_size_3/stdout.expected new file mode 100644 index 0000000000..9d8a5471bf --- /dev/null +++ b/tests/custom/permutations/21_superpermutations/0010_size_3/stdout.expected @@ -0,0 +1,19 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime permutation.param +Copying solution to: permutation-permutation.solution +language Essence 1.3 + +letting qs be + {sequence(1, 2, 3), sequence(1, 3, 2), sequence(2, 1, 3), sequence(2, 3, 1), sequence(3, 1, 2), + sequence(3, 2, 1)} +$ Visualisation for qs +$ 1 2 3 +$ 1 3 2 +$ 2 1 3 +$ 2 3 1 +$ 3 1 2 +$ 3 2 1 + +letting superperm be sequence(1, 2, 3, 1, 2, 1, 3, 2, 1) diff --git a/tests/custom/permutations/21_superpermutations/0020_size_3/permutation.essence b/tests/custom/permutations/21_superpermutations/0020_size_3/permutation.essence new file mode 100644 index 0000000000..c08d28953f --- /dev/null +++ b/tests/custom/permutations/21_superpermutations/0020_size_3/permutation.essence @@ -0,0 +1,8 @@ +given s : set of permutation of int(1..3) +find superperm : sequence (maxSize 100) of int(1..3) + +such that + and([ image(z,sequence(1,2,3)) substring superperm | z <- s ]) + +minimising |superperm| + diff --git a/tests/custom/permutations/21_superpermutations/0020_size_3/permutation.param b/tests/custom/permutations/21_superpermutations/0020_size_3/permutation.param new file mode 100644 index 0000000000..f6697b1251 --- /dev/null +++ b/tests/custom/permutations/21_superpermutations/0020_size_3/permutation.param @@ -0,0 +1,5 @@ + +letting s be + {permutation(), permutation((1, 2)), permutation((1, 2, 3)), permutation((1, 3)), permutation((1, 3, 2)), + permutation((2, 3))} + diff --git a/tests/custom/permutations/21_superpermutations/0020_size_3/run.sh b/tests/custom/permutations/21_superpermutations/0020_size_3/run.sh new file mode 100755 index 0000000000..4194275f38 --- /dev/null +++ b/tests/custom/permutations/21_superpermutations/0020_size_3/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence *.param +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/21_superpermutations/0020_size_3/stdout.expected b/tests/custom/permutations/21_superpermutations/0020_size_3/stdout.expected new file mode 100644 index 0000000000..6d17d75323 --- /dev/null +++ b/tests/custom/permutations/21_superpermutations/0020_size_3/stdout.expected @@ -0,0 +1,8 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime permutation.param +Copying solution to: permutation-permutation.solution +language Essence 1.3 + +letting superperm be sequence(1, 2, 3, 1, 2, 1, 3, 2, 1) diff --git a/tests/custom/permutations/21_superpermutations/runthese.sh b/tests/custom/permutations/21_superpermutations/runthese.sh new file mode 100644 index 0000000000..515dc85742 --- /dev/null +++ b/tests/custom/permutations/21_superpermutations/runthese.sh @@ -0,0 +1 @@ +stack build --copy-bins --test --test-arguments "-p custom.permutations.21_superpermutations" From 1802f5e8283d0984e74046b6f87ffaf7a43f17e0 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?O=CC=88zgu=CC=88r=20Akgu=CC=88n?= Date: Mon, 18 Feb 2019 10:04:59 +0000 Subject: [PATCH 068/229] post merge cleanup --- src/Conjure/Representations/Permutation.hs | 10 +++++++--- src/Conjure/Rules/Horizontal/Permutation.hs | 1 - src/Conjure/Rules/Vertical/Permutation.hs | 5 ++--- 3 files changed, 9 insertions(+), 7 deletions(-) diff --git a/src/Conjure/Representations/Permutation.hs b/src/Conjure/Representations/Permutation.hs index 9b741092ad..c0095b3ca0 100644 --- a/src/Conjure/Representations/Permutation.hs +++ b/src/Conjure/Representations/Permutation.hs @@ -20,7 +20,7 @@ permutationAsFunction :: forall m . (MonadFail m, NameGen m, EnumerateDomain m) => (forall x . DispatchFunction m x) -> Representation m -permutationAsFunction dispatch = Representation chck downD structuralCons downC up +permutationAsFunction dispatch = Representation chck downD structuralCons downC up symmetryOrdering where chck :: TypeOf_ReprCheck m chck f (DomainPermutation _ s innerDomain) @@ -129,5 +129,9 @@ permutationAsFunction dispatch = Representation chck downD structuralCons downC , "domain:" <+> pretty domain ] - - + symmetryOrdering :: TypeOf_SymmetryOrdering m + symmetryOrdering innerSO downX1 inp domain = do + [x] <- downX1 inp + Just [(_, xDomain)] <- downD ("SO", domain) + soValues <- innerSO downX1 x xDomain + return soValues diff --git a/src/Conjure/Rules/Horizontal/Permutation.hs b/src/Conjure/Rules/Horizontal/Permutation.hs index 80e7741f55..be3fcf2931 100644 --- a/src/Conjure/Rules/Horizontal/Permutation.hs +++ b/src/Conjure/Rules/Horizontal/Permutation.hs @@ -283,7 +283,6 @@ rule_Image_Matrix_Indexing = "image-matrix-indexing" `namedRule` theRule where ty <- typeOf mat case ty of TypeMatrix{} -> return () ; _ -> na "only applies to matrices" (TypePermutation inn) <- typeOf perm - ti <- typeOf indexer if let ?typeCheckerMode = StronglyTyped in ty `containsType` inn then do return diff --git a/src/Conjure/Rules/Vertical/Permutation.hs b/src/Conjure/Rules/Vertical/Permutation.hs index 3689fa9a55..71e752e6f0 100644 --- a/src/Conjure/Rules/Vertical/Permutation.hs +++ b/src/Conjure/Rules/Vertical/Permutation.hs @@ -1,7 +1,6 @@ {-# LANGUAGE QuasiQuotes #-} module Conjure.Rules.Vertical.Permutation where import Conjure.Rules.Import -import Conjure.Rules.Vertical.Matrix (flattenIfNeeded) rule_Cardinality :: Rule rule_Cardinality = "permutation-cardinality" `namedRule` theRule where @@ -106,7 +105,7 @@ rule_Matrix_Image = "matrix-image" `namedRule` theRule where (TypePermutation inn) <- typeOf perm if let ?typeCheckerMode = StronglyTyped in ty `containsTypeComprehendable` inn then do - y' <- flattenIfNeeded y + let y' = flattenIfNeeded (matrixNumDims ty) y dm@(DomainMatrix dyindex _) <- domainOf y' return ( "Horizontal rule for image matrix" @@ -140,7 +139,7 @@ rule_Matrix_Image_Comprehension = "matrix-image-comprehension" `namedRule` theRu if let ?typeCheckerMode = StronglyTyped in not $ typesUnify [ty, inn] then do unless (isPrimitiveType ty) $ fail ("not a primitive type:" <+> pretty ty) - y' <- flattenIfNeeded y + let y' = flattenIfNeeded (matrixNumDims ty) y dm@(DomainMatrix dyindex _) <- domainOf y' return ( "Horizontal rule for image matrix in comprehension" From 387102ca1a0fdee1a9784a434e475a3c9efa3f11 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?O=CC=88zgu=CC=88r=20Akgu=CC=88n?= Date: Mon, 18 Feb 2019 20:24:02 +0000 Subject: [PATCH 069/229] Handle ordering operators between comprehensions --- src/Conjure/Language/Expression/Op/Image.hs | 2 +- src/Conjure/Representations.hs | 6 +-- src/Conjure/UI/Model.hs | 34 ++++++++--------- .../permutations/21_set_comprehension/run.sh | 5 +++ .../set_comprehension.essence | 4 ++ .../21_set_comprehension/stdout.expected | 38 +++++++++++++++++++ 6 files changed, 68 insertions(+), 21 deletions(-) create mode 100755 tests/custom/permutations/21_set_comprehension/run.sh create mode 100644 tests/custom/permutations/21_set_comprehension/set_comprehension.essence create mode 100644 tests/custom/permutations/21_set_comprehension/stdout.expected diff --git a/src/Conjure/Language/Expression/Op/Image.hs b/src/Conjure/Language/Expression/Op/Image.hs index 4d78429b6d..cd4564860b 100644 --- a/src/Conjure/Language/Expression/Op/Image.hs +++ b/src/Conjure/Language/Expression/Op/Image.hs @@ -71,7 +71,7 @@ instance EvaluateOp OpImage where [ "Sequence is multiply defined at this point:" <+> pretty a , "Sequence value:" <+> pretty f ] - evaluateOp op@(OpImage p@(viewConstantPermutation -> Just xss) i) = do + evaluateOp (OpImage p@(viewConstantPermutation -> Just xss) i) = do (TypePermutation ip) <- typeOf p ti <- typeOf i if typesUnify [ti, ip] diff --git a/src/Conjure/Representations.hs b/src/Conjure/Representations.hs index c5e4f4ff32..54d2b70c1c 100644 --- a/src/Conjure/Representations.hs +++ b/src/Conjure/Representations.hs @@ -158,9 +158,9 @@ symmetryOrdering inp = DomainMatrix _ domainInner -> symmetryOrderingDispatch downX1 inp domainInner _ -> bug ("symmetryOrdering, not DomainMatrix:" <++> pretty (show op)) _ -> bug ("symmetryOrdering, no OpIndexing:" <++> pretty (show op)) - -- Comprehension body stmts -> do - -- xs <- downX1 body - -- return [Comprehension x stmts | x <- xs] + Comprehension body stmts -> do + xs <- symmetryOrdering body + return $ make opFlatten $ Comprehension xs stmts -- x@WithLocals{} -> bug ("downX1:" <++> pretty (show x)) _ -> bug ("symmetryOrdering:" <++> pretty (show inp)) diff --git a/src/Conjure/UI/Model.hs b/src/Conjure/UI/Model.hs index 5a8f2cf16e..0328c0e68d 100644 --- a/src/Conjure/UI/Model.hs +++ b/src/Conjure/UI/Model.hs @@ -2094,26 +2094,26 @@ rule_InlineConditions = Rule "inline-conditions" theRule where -- when found, return the skipping operator for the quantifier -- if none exists, do not apply the rule. -- (or maybe we should call bug right ahead, it can't be anything else.) - queryQ z0 = - case Zipper.up z0 of - Nothing -> na "rule_InlineConditions (meh-1)" - Just z -> do - let h = hole z - case ( match opAnd h, match opOr h, match opSum h - , match opMin h, match opMax h, match opOrdering h ) of - (Just{}, _, _, _, _, _) -> return ("and", opAndSkip) - (_, Just{}, _, _, _, _) -> return ("or" , opOrSkip ) - (_, _, Just{}, _, _, _) -> return ("sum", opSumSkip) - (_, _, _, Just{}, _, _) -> na "rule_InlineConditions (min)" - (_, _, _, _, Just{}, _) -> na "rule_InlineConditions (max)" - (_, _, _, _, _, Just{}) -> return ("ordering", opSumSkip) - _ -> na "rule_InlineConditions (meh-2)" - -- case Zipper.up z of - -- Nothing -> na "queryQ" - -- Just u -> queryQ u + queryQ z0 = case Zipper.up z0 of + Nothing -> na "rule_InlineConditions (top)" + Just z -> queryQ_handleLevel z (hole z) + + queryQ_handleLevel z h + | Just{} <- match opAnd h = return ("and", opAndSkip) + | Just{} <- match opOr h = return ("or" , opOrSkip ) + | Just{} <- match opSum h = return ("sum", opSumSkip) + | Just{} <- match opMin h = na "rule_InlineConditions (min)" + | Just{} <- match opMax h = na "rule_InlineConditions (max)" + | Just{} <- match opOrdering h = return ("ordering", opSumSkip) + | Comprehension{} <- h = queryQ z + | Just{} <- match opFlatten h = queryQ z + | otherwise = na "rule_InlineConditions (stop)" opAndSkip b x = [essence| &b -> &x |] opOrSkip b x = [essence| &b /\ &x |] + + opSumSkip b [essence| flatten(&x)|] = make opFlatten (opSumSkip b x) + opSumSkip b (Comprehension body gocs) = Comprehension (opSumSkip b body) gocs opSumSkip b x = [essence| toInt(&b) * catchUndef(&x, 0) |] diff --git a/tests/custom/permutations/21_set_comprehension/run.sh b/tests/custom/permutations/21_set_comprehension/run.sh new file mode 100755 index 0000000000..66b39490c4 --- /dev/null +++ b/tests/custom/permutations/21_set_comprehension/run.sh @@ -0,0 +1,5 @@ +rm -rf conjure-output +conjure solve set_comprehension.essence --copy-solutions=no +cat conjure-output/*.eprime | grep -v '\$' +cat conjure-output/*.solution +rm -rf conjure-output \ No newline at end of file diff --git a/tests/custom/permutations/21_set_comprehension/set_comprehension.essence b/tests/custom/permutations/21_set_comprehension/set_comprehension.essence new file mode 100644 index 0000000000..72947ffaa9 --- /dev/null +++ b/tests/custom/permutations/21_set_comprehension/set_comprehension.essence @@ -0,0 +1,4 @@ +find s : set (minSize 2) of set (minSize 2) of int(1..3) +letting p be permutation((1,2,3)) +such that + [i | i <- s] .<= [i | i <- s] \ No newline at end of file diff --git a/tests/custom/permutations/21_set_comprehension/stdout.expected b/tests/custom/permutations/21_set_comprehension/stdout.expected new file mode 100644 index 0000000000..3446d90c20 --- /dev/null +++ b/tests/custom/permutations/21_set_comprehension/stdout.expected @@ -0,0 +1,38 @@ +Generating models for set_comprehension.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +language ESSENCE' 1.0 + +find s_ExplicitVarSizeWithMarkerR2_Marker: int(0..8) +find s_ExplicitVarSizeWithMarkerR2_Values_Occurrence: matrix indexed by [int(1..8), int(1..3)] of bool +branching on [s_ExplicitVarSizeWithMarkerR2_Marker, s_ExplicitVarSizeWithMarkerR2_Values_Occurrence] +such that + flatten([[toInt(q8 <= s_ExplicitVarSizeWithMarkerR2_Marker) * + catchUndef(-toInt(s_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q8, q10]), 0) + | q10 : int(1..3)] + | q8 : int(1..8)]) + <=lex + flatten([[toInt(q9 <= s_ExplicitVarSizeWithMarkerR2_Marker) * + catchUndef(-toInt(s_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q9, q11]), 0) + | q11 : int(1..3)] + | q9 : int(1..8)]), + and([q1 + 1 <= s_ExplicitVarSizeWithMarkerR2_Marker -> + [-toInt(s_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q1, q5]) | q5 : int(1..3)] s_ExplicitVarSizeWithMarkerR2_Marker -> + and([s_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q2, q7] = false | q7 : int(1..3)]) + | q2 : int(1..8)]), + 2 <= s_ExplicitVarSizeWithMarkerR2_Marker, + and([q3 <= s_ExplicitVarSizeWithMarkerR2_Marker -> + 2 <= sum([toInt(s_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q3, q4]) | q4 : int(1..3)]) + | q3 : int(1..8)]) + +language Essence 1.3 + +letting s be {{1, 3}, {2, 3}} +$ Visualisation for s +$ 1 3 +$ 2 3 + From c7bc58faf013c8e05d02aa0dad5a623df365aa29 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?O=CC=88zgu=CC=88r=20Akgu=CC=88n?= Date: Mon, 18 Feb 2019 20:30:57 +0000 Subject: [PATCH 070/229] Support p(x) syntax for permutation application --- src/Conjure/Language/Lenses.hs | 7 ++++--- 1 file changed, 4 insertions(+), 3 deletions(-) diff --git a/src/Conjure/Language/Lenses.hs b/src/Conjure/Language/Lenses.hs index 7c1d6733d8..97a555c7e4 100644 --- a/src/Conjure/Language/Lenses.hs +++ b/src/Conjure/Language/Lenses.hs @@ -1531,9 +1531,10 @@ fixRelationProj= transformBi f case match opRelationProj p of Just (func, [Just arg]) -> case typeOf func of - Just TypeFunction{} -> make opImage func arg - Just TypeSequence{} -> make opImage func arg - _ -> p + Just TypeFunction{} -> make opImage func arg + Just TypeSequence{} -> make opImage func arg + Just TypePermutation{} -> make opImage func arg + _ -> p _ -> p From 4a9d4ca08f29d362ce9461af55c711b2a9c76180 Mon Sep 17 00:00:00 2001 From: Fraser Dunlop Date: Tue, 26 Feb 2019 14:02:10 +0000 Subject: [PATCH 071/229] changed tests to pass with new ordering --- .../stdout.expected | 90 +++++------ .../stdout.expected | 102 ++++++------- .../stdout.expected | 104 ++++++------- .../stdout.expected | 140 +++++++++--------- 4 files changed, 218 insertions(+), 218 deletions(-) diff --git a/tests/custom/permutations/17_image_partition/int/0020_given_permutation_find_partitions/stdout.expected b/tests/custom/permutations/17_image_partition/int/0020_given_permutation_find_partitions/stdout.expected index 703b05e795..cdb26da296 100644 --- a/tests/custom/permutations/17_image_partition/int/0020_given_permutation_find_partitions/stdout.expected +++ b/tests/custom/permutations/17_image_partition/int/0020_given_permutation_find_partitions/stdout.expected @@ -14,40 +14,28 @@ Copying solution to: permutation-permutation-000009.solution Copying solution to: permutation-permutation-000010.solution language Essence 1.3 -letting s be partition({1, 2, 3}, {4}) +letting s be partition({1}, {2, 3, 4}) $ Visualisation for s -$ 1 2 3 -$ 4 - -letting sn be partition({1}, {2, 3, 4}) -$ Visualisation for sn $ 1 $ 2 3 4 -language Essence 1.3 - -letting s be partition({1, 2, 4}, {3}) -$ Visualisation for s +letting sn be partition({1, 2, 4}, {3}) +$ Visualisation for sn $ 1 2 4 $ 3 -letting sn be partition({1, 2, 3}, {4}) -$ Visualisation for sn -$ 1 2 3 -$ 4 - language Essence 1.3 -letting s be partition({1, 2}, {3, 4}) +letting s be partition({1, 4}, {2, 3}) $ Visualisation for s -$ 1 2 -$ 3 4 - -letting sn be partition({1, 4}, {2, 3}) -$ Visualisation for sn $ 1 4 $ 2 3 +letting sn be partition({1, 3}, {2, 4}) +$ Visualisation for sn +$ 1 3 +$ 2 4 + language Essence 1.3 letting s be partition({1, 3}, {2, 4}) @@ -62,55 +50,67 @@ $ 3 4 language Essence 1.3 -letting s be partition({1, 4}, {2, 3}) +letting s be partition({1, 2}, {3, 4}) $ Visualisation for s -$ 1 4 -$ 2 3 +$ 1 2 +$ 3 4 -letting sn be partition({1, 3}, {2, 4}) +letting sn be partition({1, 4}, {2, 3}) $ Visualisation for sn -$ 1 3 -$ 2 4 +$ 1 4 +$ 2 3 language Essence 1.3 -letting s be partition({1}, {2, 3, 4}) +letting s be partition({1, 2, 4}, {3}) $ Visualisation for s -$ 1 -$ 2 3 4 - -letting sn be partition({1, 2, 4}, {3}) -$ Visualisation for sn $ 1 2 4 $ 3 +letting sn be partition({1, 2, 3}, {4}) +$ Visualisation for sn +$ 1 2 3 +$ 4 + language Essence 1.3 -letting s be partition({1, 2}, {3}, {4}) +letting s be partition({1, 2, 3}, {4}) $ Visualisation for s -$ 1 2 -$ 3 +$ 1 2 3 $ 4 -letting sn be partition({1}, {2, 3}, {4}) +letting sn be partition({1}, {2, 3, 4}) $ Visualisation for sn $ 1 -$ 2 3 -$ 4 +$ 2 3 4 language Essence 1.3 -letting s be partition({1, 3}, {2}, {4}) +letting s be partition({1}, {2}, {3, 4}) $ Visualisation for s -$ 1 3 +$ 1 $ 2 -$ 4 +$ 3 4 -letting sn be partition({1}, {2}, {3, 4}) +letting sn be partition({1, 4}, {2}, {3}) $ Visualisation for sn -$ 1 +$ 1 4 $ 2 -$ 3 4 +$ 3 + +language Essence 1.3 + +letting s be partition({1}, {2, 4}, {3}) +$ Visualisation for s +$ 1 +$ 2 4 +$ 3 + +letting sn be partition({1, 2}, {3}, {4}) +$ Visualisation for sn +$ 1 2 +$ 3 +$ 4 language Essence 1.3 diff --git a/tests/custom/permutations/17_image_partition/int/0030_letting_permutation_find_partitions/stdout.expected b/tests/custom/permutations/17_image_partition/int/0030_letting_permutation_find_partitions/stdout.expected index 2884fa5c2b..0a5cc47ad3 100644 --- a/tests/custom/permutations/17_image_partition/int/0030_letting_permutation_find_partitions/stdout.expected +++ b/tests/custom/permutations/17_image_partition/int/0030_letting_permutation_find_partitions/stdout.expected @@ -24,39 +24,39 @@ $ 1 2 3 4 language Essence 1.3 -letting s be partition({1, 2, 3}, {4}) +letting s be partition({1}, {2, 3, 4}) $ Visualisation for s -$ 1 2 3 -$ 4 - -letting sn be partition({1}, {2, 3, 4}) -$ Visualisation for sn $ 1 $ 2 3 4 +letting sn be partition({1, 2, 4}, {3}) +$ Visualisation for sn +$ 1 2 4 +$ 3 + language Essence 1.3 -letting s be partition({1, 2, 4}, {3}) +letting s be partition({1, 4}, {2, 3}) $ Visualisation for s -$ 1 2 4 -$ 3 +$ 1 4 +$ 2 3 -letting sn be partition({1, 2, 3}, {4}) +letting sn be partition({1, 3}, {2, 4}) $ Visualisation for sn -$ 1 2 3 -$ 4 +$ 1 3 +$ 2 4 language Essence 1.3 -letting s be partition({1, 2}, {3, 4}) +letting s be partition({1, 3}, {2, 4}) $ Visualisation for s -$ 1 2 -$ 3 4 +$ 1 3 +$ 2 4 -letting sn be partition({1, 4}, {2, 3}) +letting sn be partition({1, 2}, {3, 4}) $ Visualisation for sn -$ 1 4 -$ 2 3 +$ 1 2 +$ 3 4 language Essence 1.3 @@ -72,65 +72,65 @@ $ 2 language Essence 1.3 -letting s be partition({1, 3}, {2, 4}) +letting s be partition({1, 2}, {3, 4}) $ Visualisation for s -$ 1 3 -$ 2 4 - -letting sn be partition({1, 2}, {3, 4}) -$ Visualisation for sn $ 1 2 $ 3 4 -language Essence 1.3 - -letting s be partition({1, 4}, {2, 3}) -$ Visualisation for s +letting sn be partition({1, 4}, {2, 3}) +$ Visualisation for sn $ 1 4 $ 2 3 -letting sn be partition({1, 3}, {2, 4}) -$ Visualisation for sn -$ 1 3 -$ 2 4 - language Essence 1.3 -letting s be partition({1}, {2, 3, 4}) +letting s be partition({1, 2, 4}, {3}) $ Visualisation for s -$ 1 -$ 2 3 4 - -letting sn be partition({1, 2, 4}, {3}) -$ Visualisation for sn $ 1 2 4 $ 3 +letting sn be partition({1, 2, 3}, {4}) +$ Visualisation for sn +$ 1 2 3 +$ 4 + language Essence 1.3 -letting s be partition({1, 2}, {3}, {4}) +letting s be partition({1, 2, 3}, {4}) $ Visualisation for s -$ 1 2 -$ 3 +$ 1 2 3 $ 4 -letting sn be partition({1}, {2, 3}, {4}) +letting sn be partition({1}, {2, 3, 4}) $ Visualisation for sn $ 1 -$ 2 3 -$ 4 +$ 2 3 4 language Essence 1.3 -letting s be partition({1, 3}, {2}, {4}) +letting s be partition({1}, {2}, {3, 4}) $ Visualisation for s -$ 1 3 +$ 1 $ 2 -$ 4 +$ 3 4 -letting sn be partition({1}, {2}, {3, 4}) +letting sn be partition({1, 4}, {2}, {3}) $ Visualisation for sn -$ 1 +$ 1 4 $ 2 -$ 3 4 +$ 3 + +language Essence 1.3 + +letting s be partition({1}, {2, 4}, {3}) +$ Visualisation for s +$ 1 +$ 2 4 +$ 3 + +letting sn be partition({1, 2}, {3}, {4}) +$ Visualisation for sn +$ 1 2 +$ 3 +$ 4 diff --git a/tests/custom/permutations/17_image_partition/int/0040_find_permutation_find_partitions/stdout.expected b/tests/custom/permutations/17_image_partition/int/0040_find_permutation_find_partitions/stdout.expected index c64f85dd97..f4b377f97d 100644 --- a/tests/custom/permutations/17_image_partition/int/0040_find_permutation_find_partitions/stdout.expected +++ b/tests/custom/permutations/17_image_partition/int/0040_find_permutation_find_partitions/stdout.expected @@ -26,42 +26,42 @@ $ 1 2 3 4 language Essence 1.3 letting p be permutation((2, 3, 4)) -letting s be partition({1, 2, 3}, {4}) +letting s be partition({1}, {2, 3, 4}) $ Visualisation for s -$ 1 2 3 -$ 4 +$ 1 +$ 2 3 4 -letting sn be partition({1, 3, 4}, {2}) +letting sn be partition({1}, {2, 3, 4}) $ Visualisation for sn -$ 1 3 4 -$ 2 +$ 1 +$ 2 3 4 language Essence 1.3 letting p be permutation((2, 3, 4)) -letting s be partition({1, 2, 4}, {3}) +letting s be partition({1, 4}, {2, 3}) $ Visualisation for s -$ 1 2 4 -$ 3 +$ 1 4 +$ 2 3 -letting sn be partition({1, 2, 3}, {4}) +letting sn be partition({1, 2}, {3, 4}) $ Visualisation for sn -$ 1 2 3 -$ 4 +$ 1 2 +$ 3 4 language Essence 1.3 letting p be permutation((2, 3, 4)) -letting s be partition({1, 2}, {3, 4}) +letting s be partition({1, 3}, {2, 4}) $ Visualisation for s -$ 1 2 -$ 3 4 - -letting sn be partition({1, 3}, {2, 4}) -$ Visualisation for sn $ 1 3 $ 2 4 +letting sn be partition({1, 4}, {2, 3}) +$ Visualisation for sn +$ 1 4 +$ 2 3 + language Essence 1.3 letting p be permutation((2, 3, 4)) @@ -78,69 +78,69 @@ $ 3 language Essence 1.3 letting p be permutation((2, 3, 4)) -letting s be partition({1, 3}, {2, 4}) +letting s be partition({1, 2}, {3, 4}) $ Visualisation for s -$ 1 3 -$ 2 4 +$ 1 2 +$ 3 4 -letting sn be partition({1, 4}, {2, 3}) +letting sn be partition({1, 3}, {2, 4}) $ Visualisation for sn -$ 1 4 -$ 2 3 +$ 1 3 +$ 2 4 language Essence 1.3 letting p be permutation((2, 3, 4)) -letting s be partition({1, 4}, {2, 3}) +letting s be partition({1, 2, 4}, {3}) $ Visualisation for s -$ 1 4 -$ 2 3 +$ 1 2 4 +$ 3 -letting sn be partition({1, 2}, {3, 4}) +letting sn be partition({1, 2, 3}, {4}) $ Visualisation for sn -$ 1 2 -$ 3 4 +$ 1 2 3 +$ 4 language Essence 1.3 letting p be permutation((2, 3, 4)) -letting s be partition({1}, {2, 3, 4}) +letting s be partition({1, 2, 3}, {4}) $ Visualisation for s -$ 1 -$ 2 3 4 +$ 1 2 3 +$ 4 -letting sn be partition({1}, {2, 3, 4}) +letting sn be partition({1, 3, 4}, {2}) $ Visualisation for sn -$ 1 -$ 2 3 4 +$ 1 3 4 +$ 2 language Essence 1.3 letting p be permutation((2, 3, 4)) -letting s be partition({1, 2}, {3}, {4}) +letting s be partition({1}, {2}, {3, 4}) $ Visualisation for s -$ 1 2 -$ 3 -$ 4 +$ 1 +$ 2 +$ 3 4 -letting sn be partition({1, 3}, {2}, {4}) +letting sn be partition({1}, {2, 4}, {3}) $ Visualisation for sn -$ 1 3 -$ 2 -$ 4 +$ 1 +$ 2 4 +$ 3 language Essence 1.3 letting p be permutation((2, 3, 4)) -letting s be partition({1, 3}, {2}, {4}) +letting s be partition({1}, {2, 4}, {3}) $ Visualisation for s -$ 1 3 -$ 2 -$ 4 +$ 1 +$ 2 4 +$ 3 -letting sn be partition({1, 4}, {2}, {3}) +letting sn be partition({1}, {2, 3}, {4}) $ Visualisation for sn -$ 1 4 -$ 2 -$ 3 +$ 1 +$ 2 3 +$ 4 diff --git a/tests/custom/permutations/17_image_partition/unnamed/0010_find_partition_of_unnamed/stdout.expected b/tests/custom/permutations/17_image_partition/unnamed/0010_find_partition_of_unnamed/stdout.expected index b90c57db38..76423dba25 100644 --- a/tests/custom/permutations/17_image_partition/unnamed/0010_find_partition_of_unnamed/stdout.expected +++ b/tests/custom/permutations/17_image_partition/unnamed/0010_find_partition_of_unnamed/stdout.expected @@ -15,140 +15,140 @@ Copying solution to: permutation-000010.solution language Essence 1.3 letting n be new type enum {n_1, n_2, n_3, n_4} -letting a be partition({n_1, n_2, n_3}, {n_4}) +letting a be partition({n_1}, {n_2, n_3, n_4}) $ Visualisation for a -$ n_1 n_2 n_3 -$ n_4 - -letting b be partition({n_1, n_2, n_4}, {n_3}) -$ Visualisation for b -$ n_1 n_2 n_4 -$ n_3 - -letting p be permutation((n_2, n_4, n_3)) -language Essence 1.3 - -letting n be new type enum {n_1, n_2, n_3, n_4} -letting a be partition({n_1, n_2, n_3}, {n_4}) -$ Visualisation for a -$ n_1 n_2 n_3 -$ n_4 - -letting b be partition({n_1, n_2, n_4}, {n_3}) -$ Visualisation for b -$ n_1 n_2 n_4 -$ n_3 - -letting p be permutation((n_1, n_4, n_3)) -language Essence 1.3 - -letting n be new type enum {n_1, n_2, n_3, n_4} -letting a be partition({n_1, n_2, n_3}, {n_4}) -$ Visualisation for a -$ n_1 n_2 n_3 -$ n_4 +$ n_1 +$ n_2 n_3 n_4 letting b be partition({n_1, n_3, n_4}, {n_2}) $ Visualisation for b $ n_1 n_3 n_4 $ n_2 -letting p be permutation((n_2, n_3, n_4)) +letting p be permutation((n_1, n_2, n_3)) language Essence 1.3 letting n be new type enum {n_1, n_2, n_3, n_4} -letting a be partition({n_1, n_2, n_3}, {n_4}) +letting a be partition({n_1}, {n_2, n_3, n_4}) $ Visualisation for a -$ n_1 n_2 n_3 -$ n_4 +$ n_1 +$ n_2 n_3 n_4 letting b be partition({n_1, n_3, n_4}, {n_2}) $ Visualisation for b $ n_1 n_3 n_4 $ n_2 -letting p be permutation((n_1, n_4, n_2)) +letting p be permutation((n_1, n_2, n_4)) language Essence 1.3 letting n be new type enum {n_1, n_2, n_3, n_4} -letting a be partition({n_1, n_2, n_3}, {n_4}) +letting a be partition({n_1}, {n_2, n_3, n_4}) $ Visualisation for a -$ n_1 n_2 n_3 -$ n_4 - -letting b be partition({n_1}, {n_2, n_3, n_4}) -$ Visualisation for b $ n_1 $ n_2 n_3 n_4 -letting p be permutation((n_1, n_2, n_4)) +letting b be partition({n_1, n_2, n_4}, {n_3}) +$ Visualisation for b +$ n_1 n_2 n_4 +$ n_3 + +letting p be permutation((n_1, n_3, n_2)) language Essence 1.3 letting n be new type enum {n_1, n_2, n_3, n_4} -letting a be partition({n_1, n_2, n_3}, {n_4}) +letting a be partition({n_1}, {n_2, n_3, n_4}) $ Visualisation for a -$ n_1 n_2 n_3 -$ n_4 - -letting b be partition({n_1}, {n_2, n_3, n_4}) -$ Visualisation for b $ n_1 $ n_2 n_3 n_4 +letting b be partition({n_1, n_2, n_4}, {n_3}) +$ Visualisation for b +$ n_1 n_2 n_4 +$ n_3 + letting p be permutation((n_1, n_3, n_4)) language Essence 1.3 letting n be new type enum {n_1, n_2, n_3, n_4} -letting a be partition({n_1, n_2, n_4}, {n_3}) +letting a be partition({n_1}, {n_2, n_3, n_4}) $ Visualisation for a -$ n_1 n_2 n_4 -$ n_3 +$ n_1 +$ n_2 n_3 n_4 letting b be partition({n_1, n_2, n_3}, {n_4}) $ Visualisation for b $ n_1 n_2 n_3 $ n_4 -letting p be permutation((n_2, n_3, n_4)) +letting p be permutation((n_1, n_4, n_2)) language Essence 1.3 letting n be new type enum {n_1, n_2, n_3, n_4} -letting a be partition({n_1, n_2, n_4}, {n_3}) +letting a be partition({n_1}, {n_2, n_3, n_4}) $ Visualisation for a -$ n_1 n_2 n_4 -$ n_3 +$ n_1 +$ n_2 n_3 n_4 letting b be partition({n_1, n_2, n_3}, {n_4}) $ Visualisation for b $ n_1 n_2 n_3 $ n_4 -letting p be permutation((n_1, n_3, n_4)) +letting p be permutation((n_1, n_4, n_3)) language Essence 1.3 letting n be new type enum {n_1, n_2, n_3, n_4} -letting a be partition({n_1, n_2, n_4}, {n_3}) +letting a be partition({n_1, n_4}, {n_2, n_3}) $ Visualisation for a -$ n_1 n_2 n_4 -$ n_3 +$ n_1 n_4 +$ n_2 n_3 -letting b be partition({n_1, n_3, n_4}, {n_2}) +letting b be partition({n_1, n_3}, {n_2, n_4}) $ Visualisation for b -$ n_1 n_3 n_4 -$ n_2 +$ n_1 n_3 +$ n_2 n_4 letting p be permutation((n_2, n_4, n_3)) language Essence 1.3 letting n be new type enum {n_1, n_2, n_3, n_4} -letting a be partition({n_1, n_2, n_4}, {n_3}) +letting a be partition({n_1, n_4}, {n_2, n_3}) $ Visualisation for a -$ n_1 n_2 n_4 -$ n_3 +$ n_1 n_4 +$ n_2 n_3 -letting b be partition({n_1, n_3, n_4}, {n_2}) +letting b be partition({n_1, n_3}, {n_2, n_4}) $ Visualisation for b -$ n_1 n_3 n_4 -$ n_2 +$ n_1 n_3 +$ n_2 n_4 -letting p be permutation((n_1, n_3, n_2)) +letting p be permutation((n_1, n_2, n_3)) +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting a be partition({n_1, n_4}, {n_2, n_3}) +$ Visualisation for a +$ n_1 n_4 +$ n_2 n_3 + +letting b be partition({n_1, n_3}, {n_2, n_4}) +$ Visualisation for b +$ n_1 n_3 +$ n_2 n_4 + +letting p be permutation((n_1, n_3, n_4)) +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting a be partition({n_1, n_4}, {n_2, n_3}) +$ Visualisation for a +$ n_1 n_4 +$ n_2 n_3 + +letting b be partition({n_1, n_3}, {n_2, n_4}) +$ Visualisation for b +$ n_1 n_3 +$ n_2 n_4 + +letting p be permutation((n_1, n_4, n_2)) From 3e7e1a7abc5c4990f4ee385116cda55ded5dbd80 Mon Sep 17 00:00:00 2001 From: Fraser Dunlop Date: Fri, 22 Mar 2019 12:53:39 +0000 Subject: [PATCH 072/229] Tagged Int syntax and tests --- etc/build/gen_Operator.hs | 1 + .../Language/Expression/Op/AllDiffExcept.hs | 1 + src/Conjure/Language/Expression/Op/Div.hs | 7 +- .../Language/Expression/Op/Factorial.hs | 1 + src/Conjure/Language/Expression/Op/Geq.hs | 1 + .../Language/Expression/Op/Internal/Common.hs | 30 + src/Conjure/Language/Expression/Op/Leq.hs | 1 + src/Conjure/Language/Expression/Op/Lt.hs | 1 + src/Conjure/Language/Expression/Op/Max.hs | 2 + src/Conjure/Language/Expression/Op/Min.hs | 2 + src/Conjure/Language/Expression/Op/Minus.hs | 1 + src/Conjure/Language/Expression/Op/Negate.hs | 1 + src/Conjure/Language/Expression/Op/Pred.hs | 1 + src/Conjure/Language/Expression/Op/Product.hs | 1 + src/Conjure/Language/Expression/Op/Succ.hs | 1 + src/Conjure/Language/Expression/Op/Sum.hs | 1 + src/Conjure/Language/Lexer.hs | 3 +- src/Conjure/Language/Parser.hs | 20 +- src/Conjure/Language/ParserC.hs | 20 +- src/Conjure/Language/Type.hs | 6 +- tests/custom/issues/119/1/stdout.expected | 48 - tests/custom/issues/119/2/stdout.expected | 38 - tests/custom/issues/370/01/stdout.expected | 20 - tests/custom/issues/370/03/stdout.expected | 11 - tests/custom/issues/388/2/stdout.expected | 125 -- .../stderr.expected | 6 +- .../0001_permute_untagged/permutation.essence | 5 + .../int/0001_permute_untagged/run.sh | 3 + .../int/0001_permute_untagged/stdout.expected | 9 + .../0002_permute_tagged/permutation.essence | 5 + .../int/0002_permute_tagged/run.sh | 3 + .../int/0002_permute_tagged/stdout.expected | 9 + .../permutation.essence | 6 + .../permutation.param | 1 + .../int/0003_tagged_lits_in_param/run.sh | 3 + .../0003_tagged_lits_in_param/stdout.expected | 9 + .../0001_same_tags_works/permutation.essence | 5 + .../int/div/0001_same_tags_works/run.sh | 3 + .../div/0001_same_tags_works/stdout.expected | 9 + .../permutation.essence | 5 + .../int/div/0002_diff_tags_prohibited/run.sh | 3 + .../0002_diff_tags_prohibited/stderr.expected | 6 + .../0002_diff_tags_prohibited/stdout.expected | 1 + .../permutation.essence | 4 + .../int/div/0003_const_tagged_works/run.sh | 3 + .../0003_const_tagged_works/stdout.expected | 8 + .../0004_enum_doesnt_work/permutation.essence | 5 + .../int/div/0004_enum_doesnt_work/run.sh | 3 + .../div/0004_enum_doesnt_work/stderr.expected | 6 + .../div/0004_enum_doesnt_work/stdout.expected | 1 + .../permutation.essence | 4 + .../0002_diff_tags_prohibited/run.sh | 3 + .../0002_diff_tags_prohibited/stderr.expected | 10 + .../0002_diff_tags_prohibited/stdout.expected | 1 + .../permutation.essence | 4 + .../factorial/0003_const_tagged_works/run.sh | 3 + .../0003_const_tagged_works/stdout.expected | 8 + .../permutation.essence | 6 + .../int/geq/0002_diff_tags_prohibited/run.sh | 3 + .../0002_diff_tags_prohibited/stderr.expected | 10 + .../0002_diff_tags_prohibited/stdout.expected | 1 + .../permutation.essence | 5 + .../int/geq/0003_const_tagged_works/run.sh | 3 + .../0003_const_tagged_works/stdout.expected | 9 + .../permutation.essence | 6 + .../int/leq/0002_diff_tags_prohibited/run.sh | 3 + .../0002_diff_tags_prohibited/stderr.expected | 10 + .../0002_diff_tags_prohibited/stdout.expected | 1 + .../permutation.essence | 5 + .../int/leq/0003_const_tagged_works/run.sh | 3 + .../0003_const_tagged_works/stdout.expected | 9 + .../permutation.essence | 6 + .../int/lt/0002_diff_tags_prohibited/run.sh | 3 + .../0002_diff_tags_prohibited/stderr.expected | 10 + .../0002_diff_tags_prohibited/stdout.expected | 1 + .../permutation.essence | 5 + .../int/lt/0003_const_tagged_works/run.sh | 3 + .../0003_const_tagged_works/stdout.expected | 9 + .../0001_same_tags_work/permutation.essence | 5 + .../int/max/0001_same_tags_work/run.sh | 3 + .../max/0001_same_tags_work/stdout.expected | 9 + .../permutation.essence | 5 + .../int/max/0002_diff_tags_prohibited/run.sh | 3 + .../0002_diff_tags_prohibited/stderr.expected | 10 + .../0002_diff_tags_prohibited/stdout.expected | 1 + .../permutation.essence | 5 + .../int/max/0003_const_tagged_works/run.sh | 3 + .../0003_const_tagged_works/stdout.expected | 8 + .../0001_same_tags_work/permutation.essence | 5 + .../int/min/0001_same_tags_work/run.sh | 3 + .../min/0001_same_tags_work/stdout.expected | 9 + .../permutation.essence | 5 + .../int/min/0002_diff_tags_prohibited/run.sh | 3 + .../0002_diff_tags_prohibited/stderr.expected | 10 + .../0002_diff_tags_prohibited/stdout.expected | 1 + .../permutation.essence | 5 + .../int/min/0003_const_tagged_works/run.sh | 3 + .../0003_const_tagged_works/stdout.expected | 8 + .../0001_same_tags_works/permutation.essence | 5 + .../int/minus/0001_same_tags_works/run.sh | 3 + .../0001_same_tags_works/stdout.expected | 9 + .../permutation.essence | 5 + .../minus/0002_diff_tags_prohibited/run.sh | 3 + .../0002_diff_tags_prohibited/stderr.expected | 10 + .../0002_diff_tags_prohibited/stdout.expected | 1 + .../permutation.essence | 4 + .../int/minus/0003_const_tagged_works/run.sh | 3 + .../0003_const_tagged_works/stdout.expected | 8 + .../0001_same_tags_works/permutation.essence | 5 + .../int/mod/0001_same_tags_works/run.sh | 3 + .../mod/0001_same_tags_works/stdout.expected | 9 + .../permutation.essence | 5 + .../int/mod/0002_diff_tags_prohibited/run.sh | 3 + .../0002_diff_tags_prohibited/stderr.expected | 6 + .../0002_diff_tags_prohibited/stdout.expected | 1 + .../permutation.essence | 4 + .../int/mod/0003_const_tagged_works/run.sh | 3 + .../0003_const_tagged_works/stdout.expected | 8 + .../0001_same_tags_works/permutation.essence | 5 + .../int/neg/0001_same_tags_works/run.sh | 3 + .../neg/0001_same_tags_works/stdout.expected | 9 + .../permutation.essence | 5 + .../int/neg/0002_diff_tags_prohibited/run.sh | 3 + .../0002_diff_tags_prohibited/stderr.expected | 10 + .../0002_diff_tags_prohibited/stdout.expected | 1 + .../permutation.essence | 4 + .../int/neg/0003_const_tagged_works/run.sh | 3 + .../0003_const_tagged_works/stdout.expected | 8 + .../permutation.essence | 6 + .../int/pred/0002_diff_tags_prohibited/run.sh | 3 + .../0002_diff_tags_prohibited/stderr.expected | 10 + .../0002_diff_tags_prohibited/stdout.expected | 1 + .../permutation.essence | 5 + .../int/pred/0003_const_tagged_works/run.sh | 3 + .../0003_const_tagged_works/stdout.expected | 9 + .../0001_same_tags_works/permutation.essence | 5 + .../int/prod/0001_same_tags_works/run.sh | 3 + .../prod/0001_same_tags_works/stdout.expected | 9 + .../permutation.essence | 5 + .../int/prod/0002_diff_tags_prohibited/run.sh | 3 + .../0002_diff_tags_prohibited/stderr.expected | 7 + .../0002_diff_tags_prohibited/stdout.expected | 1 + .../permutation.essence | 4 + .../int/prod/0003_const_tagged_works/run.sh | 3 + .../0003_const_tagged_works/stdout.expected | 8 + .../permutation.essence | 6 + .../int/succ/0002_diff_tags_prohibited/run.sh | 3 + .../0002_diff_tags_prohibited/stderr.expected | 10 + .../0002_diff_tags_prohibited/stdout.expected | 1 + .../permutation.essence | 5 + .../int/succ/0003_const_tagged_works/run.sh | 3 + .../0003_const_tagged_works/stdout.expected | 9 + .../0001_same_tags_works/permutation.essence | 5 + .../int/sum/0001_same_tags_works/run.sh | 3 + .../sum/0001_same_tags_works/stdout.expected | 9 + .../permutation.essence | 5 + .../int/sum/0002_diff_tags_prohibited/run.sh | 3 + .../0002_diff_tags_prohibited/stderr.expected | 7 + .../0002_diff_tags_prohibited/stdout.expected | 1 + .../permutation.essence | 4 + .../int/sum/0003_const_tagged_works/run.sh | 3 + .../0003_const_tagged_works/stdout.expected | 8 + .../permutations/22_tagged_ints/runthese.sh | 1 + .../model_1_1-solution000001.solution | 3 - .../model_1_1-solution000002.solution | 6 - .../model_1_1-solution000003.solution | 6 - .../model_1_1-solution000004.solution | 6 - .../model_1_1-solution000005.solution | 7 - .../model_1_1-solution000006.solution | 7 - .../model_1_1-solution000007.solution | 7 - .../model_1_1-solution000008.solution | 7 - .../model_1_1-solution000009.solution | 7 - .../model_1_1-solution000010.solution | 7 - .../model_1_1-solution000011.solution | 8 - .../model_1_1-solution000012.solution | 8 - .../model_1_1-solution000013.solution | 8 - .../model_1_1-solution000014.solution | 8 - .../model_1_1-solution000015.solution | 9 - .../autogen/gen02/expected/model_1_1.eprime | 46 - .../model_1_2-solution000001.solution | 3 - .../model_1_2-solution000002.solution | 6 - .../model_1_2-solution000003.solution | 6 - .../model_1_2-solution000004.solution | 6 - .../model_1_2-solution000005.solution | 7 - .../model_1_2-solution000006.solution | 7 - .../model_1_2-solution000007.solution | 7 - .../model_1_2-solution000008.solution | 7 - .../model_1_2-solution000009.solution | 7 - .../model_1_2-solution000010.solution | 7 - .../model_1_2-solution000011.solution | 8 - .../model_1_2-solution000012.solution | 8 - .../model_1_2-solution000013.solution | 8 - .../model_1_2-solution000014.solution | 8 - .../model_1_2-solution000015.solution | 9 - .../autogen/gen02/expected/model_1_2.eprime | 125 -- .../model_1_3-solution000001.solution | 3 - .../model_1_3-solution000002.solution | 6 - .../model_1_3-solution000003.solution | 6 - .../model_1_3-solution000004.solution | 6 - .../model_1_3-solution000005.solution | 7 - .../model_1_3-solution000006.solution | 7 - .../model_1_3-solution000007.solution | 7 - .../model_1_3-solution000008.solution | 7 - .../model_1_3-solution000009.solution | 7 - .../model_1_3-solution000010.solution | 7 - .../model_1_3-solution000011.solution | 8 - .../model_1_3-solution000012.solution | 8 - .../model_1_3-solution000013.solution | 8 - .../model_1_3-solution000014.solution | 8 - .../model_1_3-solution000015.solution | 9 - .../autogen/gen02/expected/model_1_3.eprime | 103 -- .../model_1_4-solution000001.solution | 3 - .../model_1_4-solution000002.solution | 6 - .../model_1_4-solution000003.solution | 6 - .../model_1_4-solution000004.solution | 6 - .../model_1_4-solution000005.solution | 7 - .../model_1_4-solution000006.solution | 7 - .../model_1_4-solution000007.solution | 7 - .../model_1_4-solution000008.solution | 7 - .../model_1_4-solution000009.solution | 7 - .../model_1_4-solution000010.solution | 7 - .../model_1_4-solution000011.solution | 8 - .../model_1_4-solution000012.solution | 8 - .../model_1_4-solution000013.solution | 8 - .../model_1_4-solution000014.solution | 8 - .../model_1_4-solution000015.solution | 9 - .../autogen/gen02/expected/model_1_4.eprime | 126 -- .../model_2_1-solution000001.solution | 3 - .../model_2_1-solution000002.solution | 6 - .../model_2_1-solution000003.solution | 6 - .../model_2_1-solution000004.solution | 6 - .../model_2_1-solution000005.solution | 7 - .../model_2_1-solution000006.solution | 7 - .../model_2_1-solution000007.solution | 7 - .../model_2_1-solution000008.solution | 7 - .../model_2_1-solution000009.solution | 7 - .../model_2_1-solution000010.solution | 7 - .../model_2_1-solution000011.solution | 8 - .../model_2_1-solution000012.solution | 8 - .../model_2_1-solution000013.solution | 8 - .../model_2_1-solution000014.solution | 8 - .../model_2_1-solution000015.solution | 9 - .../autogen/gen02/expected/model_2_1.eprime | 123 -- .../model_2_2-solution000001.solution | 3 - .../model_2_2-solution000002.solution | 6 - .../model_2_2-solution000003.solution | 6 - .../model_2_2-solution000004.solution | 6 - .../model_2_2-solution000005.solution | 7 - .../model_2_2-solution000006.solution | 7 - .../model_2_2-solution000007.solution | 7 - .../model_2_2-solution000008.solution | 7 - .../model_2_2-solution000009.solution | 7 - .../model_2_2-solution000010.solution | 7 - .../model_2_2-solution000011.solution | 8 - .../model_2_2-solution000012.solution | 8 - .../model_2_2-solution000013.solution | 8 - .../model_2_2-solution000014.solution | 8 - .../model_2_2-solution000015.solution | 9 - .../autogen/gen02/expected/model_2_2.eprime | 53 - .../model_2_3-solution000001.solution | 3 - .../model_2_3-solution000002.solution | 6 - .../model_2_3-solution000003.solution | 6 - .../model_2_3-solution000004.solution | 6 - .../model_2_3-solution000005.solution | 7 - .../model_2_3-solution000006.solution | 7 - .../model_2_3-solution000007.solution | 7 - .../model_2_3-solution000008.solution | 7 - .../model_2_3-solution000009.solution | 7 - .../model_2_3-solution000010.solution | 7 - .../model_2_3-solution000011.solution | 8 - .../model_2_3-solution000012.solution | 8 - .../model_2_3-solution000013.solution | 8 - .../model_2_3-solution000014.solution | 8 - .../model_2_3-solution000015.solution | 9 - .../autogen/gen02/expected/model_2_3.eprime | 124 -- .../model_2_4-solution000001.solution | 3 - .../model_2_4-solution000002.solution | 6 - .../model_2_4-solution000003.solution | 6 - .../model_2_4-solution000004.solution | 6 - .../model_2_4-solution000005.solution | 7 - .../model_2_4-solution000006.solution | 7 - .../model_2_4-solution000007.solution | 7 - .../model_2_4-solution000008.solution | 7 - .../model_2_4-solution000009.solution | 7 - .../model_2_4-solution000010.solution | 7 - .../model_2_4-solution000011.solution | 8 - .../model_2_4-solution000012.solution | 8 - .../model_2_4-solution000013.solution | 8 - .../model_2_4-solution000014.solution | 8 - .../model_2_4-solution000015.solution | 9 - .../autogen/gen02/expected/model_2_4.eprime | 121 -- .../model_3_1-solution000001.solution | 3 - .../model_3_1-solution000002.solution | 6 - .../model_3_1-solution000003.solution | 6 - .../model_3_1-solution000004.solution | 6 - .../model_3_1-solution000005.solution | 7 - .../model_3_1-solution000006.solution | 7 - .../model_3_1-solution000007.solution | 7 - .../model_3_1-solution000008.solution | 7 - .../model_3_1-solution000009.solution | 7 - .../model_3_1-solution000010.solution | 7 - .../model_3_1-solution000011.solution | 8 - .../model_3_1-solution000012.solution | 8 - .../model_3_1-solution000013.solution | 8 - .../model_3_1-solution000014.solution | 8 - .../model_3_1-solution000015.solution | 9 - .../autogen/gen02/expected/model_3_1.eprime | 102 -- .../model_3_2-solution000001.solution | 3 - .../model_3_2-solution000002.solution | 6 - .../model_3_2-solution000003.solution | 6 - .../model_3_2-solution000004.solution | 6 - .../model_3_2-solution000005.solution | 7 - .../model_3_2-solution000006.solution | 7 - .../model_3_2-solution000007.solution | 7 - .../model_3_2-solution000008.solution | 7 - .../model_3_2-solution000009.solution | 7 - .../model_3_2-solution000010.solution | 7 - .../model_3_2-solution000011.solution | 8 - .../model_3_2-solution000012.solution | 8 - .../model_3_2-solution000013.solution | 8 - .../model_3_2-solution000014.solution | 8 - .../model_3_2-solution000015.solution | 9 - .../autogen/gen02/expected/model_3_2.eprime | 125 -- .../model_3_3-solution000001.solution | 3 - .../model_3_3-solution000002.solution | 6 - .../model_3_3-solution000003.solution | 6 - .../model_3_3-solution000004.solution | 6 - .../model_3_3-solution000005.solution | 7 - .../model_3_3-solution000006.solution | 7 - .../model_3_3-solution000007.solution | 7 - .../model_3_3-solution000008.solution | 7 - .../model_3_3-solution000009.solution | 7 - .../model_3_3-solution000010.solution | 7 - .../model_3_3-solution000011.solution | 8 - .../model_3_3-solution000012.solution | 8 - .../model_3_3-solution000013.solution | 8 - .../model_3_3-solution000014.solution | 8 - .../model_3_3-solution000015.solution | 9 - .../autogen/gen02/expected/model_3_3.eprime | 46 - .../model_3_4-solution000001.solution | 3 - .../model_3_4-solution000002.solution | 6 - .../model_3_4-solution000003.solution | 6 - .../model_3_4-solution000004.solution | 6 - .../model_3_4-solution000005.solution | 7 - .../model_3_4-solution000006.solution | 7 - .../model_3_4-solution000007.solution | 7 - .../model_3_4-solution000008.solution | 7 - .../model_3_4-solution000009.solution | 7 - .../model_3_4-solution000010.solution | 7 - .../model_3_4-solution000011.solution | 8 - .../model_3_4-solution000012.solution | 8 - .../model_3_4-solution000013.solution | 8 - .../model_3_4-solution000014.solution | 8 - .../model_3_4-solution000015.solution | 9 - .../autogen/gen02/expected/model_3_4.eprime | 126 -- .../model_4_1-solution000001.solution | 3 - .../model_4_1-solution000002.solution | 6 - .../model_4_1-solution000003.solution | 6 - .../model_4_1-solution000004.solution | 6 - .../model_4_1-solution000005.solution | 7 - .../model_4_1-solution000006.solution | 7 - .../model_4_1-solution000007.solution | 7 - .../model_4_1-solution000008.solution | 7 - .../model_4_1-solution000009.solution | 7 - .../model_4_1-solution000010.solution | 7 - .../model_4_1-solution000011.solution | 8 - .../model_4_1-solution000012.solution | 8 - .../model_4_1-solution000013.solution | 8 - .../model_4_1-solution000014.solution | 8 - .../model_4_1-solution000015.solution | 9 - .../autogen/gen02/expected/model_4_1.eprime | 122 -- .../model_4_2-solution000001.solution | 3 - .../model_4_2-solution000002.solution | 6 - .../model_4_2-solution000003.solution | 6 - .../model_4_2-solution000004.solution | 6 - .../model_4_2-solution000005.solution | 7 - .../model_4_2-solution000006.solution | 7 - .../model_4_2-solution000007.solution | 7 - .../model_4_2-solution000008.solution | 7 - .../model_4_2-solution000009.solution | 7 - .../model_4_2-solution000010.solution | 7 - .../model_4_2-solution000011.solution | 8 - .../model_4_2-solution000012.solution | 8 - .../model_4_2-solution000013.solution | 8 - .../model_4_2-solution000014.solution | 8 - .../model_4_2-solution000015.solution | 9 - .../autogen/gen02/expected/model_4_2.eprime | 119 -- .../model_4_3-solution000001.solution | 3 - .../model_4_3-solution000002.solution | 6 - .../model_4_3-solution000003.solution | 6 - .../model_4_3-solution000004.solution | 6 - .../model_4_3-solution000005.solution | 7 - .../model_4_3-solution000006.solution | 7 - .../model_4_3-solution000007.solution | 7 - .../model_4_3-solution000008.solution | 7 - .../model_4_3-solution000009.solution | 7 - .../model_4_3-solution000010.solution | 7 - .../model_4_3-solution000011.solution | 8 - .../model_4_3-solution000012.solution | 8 - .../model_4_3-solution000013.solution | 8 - .../model_4_3-solution000014.solution | 8 - .../model_4_3-solution000015.solution | 9 - .../autogen/gen02/expected/model_4_3.eprime | 123 -- .../model_4_4-solution000001.solution | 3 - .../model_4_4-solution000002.solution | 6 - .../model_4_4-solution000003.solution | 6 - .../model_4_4-solution000004.solution | 6 - .../model_4_4-solution000005.solution | 7 - .../model_4_4-solution000006.solution | 7 - .../model_4_4-solution000007.solution | 7 - .../model_4_4-solution000008.solution | 7 - .../model_4_4-solution000009.solution | 7 - .../model_4_4-solution000010.solution | 7 - .../model_4_4-solution000011.solution | 8 - .../model_4_4-solution000012.solution | 8 - .../model_4_4-solution000013.solution | 8 - .../model_4_4-solution000014.solution | 8 - .../model_4_4-solution000015.solution | 9 - .../autogen/gen02/expected/model_4_4.eprime | 52 - .../expected/model-solution000001.solution | 3 - .../expected/model-solution000002.solution | 3 - .../expected/model-solution000003.solution | 3 - .../expected/model-solution000004.solution | 3 - .../autogen/gen10/expected/model.eprime | 9 - .../expected/model_1-solution000001.solution | 6 - .../expected/model_1-solution000002.solution | 7 - .../autogen/gen14_1/expected/model_1.eprime | 104 -- .../expected/model_2-solution000001.solution | 6 - .../expected/model_2-solution000002.solution | 7 - .../autogen/gen14_1/expected/model_2.eprime | 176 --- .../expected/model_3-solution000001.solution | 6 - .../expected/model_3-solution000002.solution | 7 - .../autogen/gen14_1/expected/model_3.eprime | 224 --- .../expected/model_4-solution000001.solution | 6 - .../expected/model_4-solution000002.solution | 7 - .../autogen/gen14_1/expected/model_4.eprime | 97 -- .../expected/model_1-solution000001.solution | 6 - .../expected/model_1-solution000002.solution | 7 - .../autogen/gen14_2/expected/model_1.eprime | 38 - .../expected/model_2-solution000001.solution | 6 - .../expected/model_2-solution000002.solution | 7 - .../autogen/gen14_2/expected/model_2.eprime | 58 - .../expected/model_3-solution000001.solution | 6 - .../expected/model_3-solution000002.solution | 7 - .../autogen/gen14_2/expected/model_3.eprime | 69 - .../expected/model_4-solution000001.solution | 6 - .../expected/model_4-solution000002.solution | 7 - .../autogen/gen14_2/expected/model_4.eprime | 34 - .../autogen/gen32/expected/model_1_1_1.eprime | 9 - .../autogen/gen32/expected/model_1_1_2.eprime | 19 - .../autogen/gen32/expected/model_1_1_3.eprime | 22 - .../autogen/gen32/expected/model_1_1_4.eprime | 23 - .../autogen/gen32/expected/model_1_2_1.eprime | 23 - .../autogen/gen32/expected/model_1_2_2.eprime | 23 - .../autogen/gen32/expected/model_1_2_3.eprime | 48 - .../autogen/gen32/expected/model_1_2_4.eprime | 49 - .../autogen/gen32/expected/model_1_3_1.eprime | 27 - .../autogen/gen32/expected/model_1_3_2.eprime | 49 - .../autogen/gen32/expected/model_1_3_3.eprime | 27 - .../autogen/gen32/expected/model_1_3_4.eprime | 53 - .../autogen/gen32/expected/model_1_4_1.eprime | 28 - .../autogen/gen32/expected/model_1_4_2.eprime | 50 - .../autogen/gen32/expected/model_1_4_3.eprime | 53 - .../autogen/gen32/expected/model_1_4_4.eprime | 28 - .../autogen/gen32/expected/model_2_1_1.eprime | 23 - .../autogen/gen32/expected/model_2_1_2.eprime | 23 - .../autogen/gen32/expected/model_2_1_3.eprime | 48 - .../autogen/gen32/expected/model_2_1_4.eprime | 49 - .../autogen/gen32/expected/model_2_2_1.eprime | 28 - .../autogen/gen32/expected/model_2_2_2.eprime | 22 - .../autogen/gen32/expected/model_2_2_3.eprime | 40 - .../autogen/gen32/expected/model_2_2_4.eprime | 40 - .../autogen/gen32/expected/model_2_3_1.eprime | 53 - .../autogen/gen32/expected/model_2_3_2.eprime | 40 - .../autogen/gen32/expected/model_2_3_3.eprime | 40 - .../autogen/gen32/expected/model_2_3_4.eprime | 69 - .../autogen/gen32/expected/model_2_4_1.eprime | 54 - .../autogen/gen32/expected/model_2_4_2.eprime | 40 - .../autogen/gen32/expected/model_2_4_3.eprime | 69 - .../autogen/gen32/expected/model_2_4_4.eprime | 40 - .../autogen/gen32/expected/model_3_1_1.eprime | 27 - .../autogen/gen32/expected/model_3_1_2.eprime | 49 - .../autogen/gen32/expected/model_3_1_3.eprime | 27 - .../autogen/gen32/expected/model_3_1_4.eprime | 53 - .../autogen/gen32/expected/model_3_2_1.eprime | 53 - .../autogen/gen32/expected/model_3_2_2.eprime | 40 - .../autogen/gen32/expected/model_3_2_3.eprime | 40 - .../autogen/gen32/expected/model_3_2_4.eprime | 69 - .../autogen/gen32/expected/model_3_3_1.eprime | 31 - .../autogen/gen32/expected/model_3_3_2.eprime | 40 - .../autogen/gen32/expected/model_3_3_3.eprime | 24 - .../autogen/gen32/expected/model_3_3_4.eprime | 44 - .../autogen/gen32/expected/model_3_4_1.eprime | 57 - .../autogen/gen32/expected/model_3_4_2.eprime | 69 - .../autogen/gen32/expected/model_3_4_3.eprime | 44 - .../autogen/gen32/expected/model_3_4_4.eprime | 44 - .../autogen/gen32/expected/model_4_1_1.eprime | 28 - .../autogen/gen32/expected/model_4_1_2.eprime | 50 - .../autogen/gen32/expected/model_4_1_3.eprime | 53 - .../autogen/gen32/expected/model_4_1_4.eprime | 28 - .../autogen/gen32/expected/model_4_2_1.eprime | 54 - .../autogen/gen32/expected/model_4_2_2.eprime | 40 - .../autogen/gen32/expected/model_4_2_3.eprime | 69 - .../autogen/gen32/expected/model_4_2_4.eprime | 40 - .../autogen/gen32/expected/model_4_3_1.eprime | 57 - .../autogen/gen32/expected/model_4_3_2.eprime | 69 - .../autogen/gen32/expected/model_4_3_3.eprime | 44 - .../autogen/gen32/expected/model_4_3_4.eprime | 44 - .../autogen/gen32/expected/model_4_4_1.eprime | 32 - .../autogen/gen32/expected/model_4_4_2.eprime | 40 - .../autogen/gen32/expected/model_4_4_3.eprime | 44 - .../autogen/gen32/expected/model_4_4_4.eprime | 25 - .../expected/model_1-solution000001.solution | 3 - .../autogen/gen36/expected/model_1.eprime | 88 -- .../expected/model_2-solution000001.solution | 3 - .../autogen/gen36/expected/model_2.eprime | 43 - .../expected/model_3-solution000001.solution | 3 - .../autogen/gen36/expected/model_3.eprime | 100 -- .../expected/model_4-solution000001.solution | 3 - .../autogen/gen36/expected/model_4.eprime | 87 -- .../expected/model_5-solution000001.solution | 3 - .../autogen/gen36/expected/model_5.eprime | 42 - .../expected/model_6-solution000001.solution | 3 - .../autogen/gen36/expected/model_6.eprime | 101 -- .../expected/model-solution000001.solution | 5 - .../expected/model-solution000002.solution | 5 - .../expected/model-solution000003.solution | 5 - .../expected/model-solution000004.solution | 5 - .../comprehension_04_2/expected/model.eprime | 26 - .../model_1_1_1-solution000001.solution | 4 - .../model_1_1_1-solution000002.solution | 4 - .../model_1_1_1-solution000003.solution | 4 - .../model_1_1_1-solution000004.solution | 4 - .../model_1_1_1-solution000005.solution | 4 - .../model_1_1_1-solution000006.solution | 4 - .../model_1_1_1-solution000007.solution | 4 - .../expected/model_1_1_1.eprime | 25 - .../model_1_1_2-solution000001.solution | 4 - .../model_1_1_2-solution000002.solution | 4 - .../model_1_1_2-solution000003.solution | 4 - .../model_1_1_2-solution000004.solution | 4 - .../model_1_1_2-solution000005.solution | 4 - .../model_1_1_2-solution000006.solution | 4 - .../model_1_1_2-solution000007.solution | 4 - .../expected/model_1_1_2.eprime | 33 - .../model_1_1_3-solution000001.solution | 4 - .../model_1_1_3-solution000002.solution | 4 - .../model_1_1_3-solution000003.solution | 4 - .../model_1_1_3-solution000004.solution | 4 - .../model_1_1_3-solution000005.solution | 4 - .../model_1_1_3-solution000006.solution | 4 - .../model_1_1_3-solution000007.solution | 4 - .../expected/model_1_1_3.eprime | 36 - .../model_1_1_4-solution000001.solution | 4 - .../model_1_1_4-solution000002.solution | 4 - .../model_1_1_4-solution000003.solution | 4 - .../model_1_1_4-solution000004.solution | 4 - .../model_1_1_4-solution000005.solution | 4 - .../model_1_1_4-solution000006.solution | 4 - .../model_1_1_4-solution000007.solution | 4 - .../expected/model_1_1_4.eprime | 36 - .../model_1_2_1-solution000001.solution | 4 - .../model_1_2_1-solution000002.solution | 4 - .../model_1_2_1-solution000003.solution | 4 - .../model_1_2_1-solution000004.solution | 4 - .../model_1_2_1-solution000005.solution | 4 - .../model_1_2_1-solution000006.solution | 4 - .../model_1_2_1-solution000007.solution | 4 - .../expected/model_1_2_1.eprime | 68 - .../model_1_2_2-solution000001.solution | 4 - .../model_1_2_2-solution000002.solution | 4 - .../model_1_2_2-solution000003.solution | 4 - .../model_1_2_2-solution000004.solution | 4 - .../model_1_2_2-solution000005.solution | 4 - .../model_1_2_2-solution000006.solution | 4 - .../model_1_2_2-solution000007.solution | 4 - .../expected/model_1_2_2.eprime | 68 - .../model_1_2_3-solution000001.solution | 4 - .../model_1_2_3-solution000002.solution | 4 - .../model_1_2_3-solution000003.solution | 4 - .../model_1_2_3-solution000004.solution | 4 - .../model_1_2_3-solution000005.solution | 4 - .../model_1_2_3-solution000006.solution | 4 - .../model_1_2_3-solution000007.solution | 4 - .../expected/model_1_2_3.eprime | 92 -- .../model_1_2_4-solution000001.solution | 4 - .../model_1_2_4-solution000002.solution | 4 - .../model_1_2_4-solution000003.solution | 4 - .../model_1_2_4-solution000004.solution | 4 - .../model_1_2_4-solution000005.solution | 4 - .../model_1_2_4-solution000006.solution | 4 - .../model_1_2_4-solution000007.solution | 4 - .../expected/model_1_2_4.eprime | 92 -- .../model_1_3_1-solution000001.solution | 4 - .../model_1_3_1-solution000002.solution | 4 - .../model_1_3_1-solution000003.solution | 4 - .../model_1_3_1-solution000004.solution | 4 - .../model_1_3_1-solution000005.solution | 4 - .../model_1_3_1-solution000006.solution | 4 - .../model_1_3_1-solution000007.solution | 4 - .../expected/model_1_3_1.eprime | 74 - .../model_1_3_2-solution000001.solution | 4 - .../model_1_3_2-solution000002.solution | 4 - .../model_1_3_2-solution000003.solution | 4 - .../model_1_3_2-solution000004.solution | 4 - .../model_1_3_2-solution000005.solution | 4 - .../model_1_3_2-solution000006.solution | 4 - .../model_1_3_2-solution000007.solution | 4 - .../expected/model_1_3_2.eprime | 94 -- .../model_1_3_3-solution000001.solution | 4 - .../model_1_3_3-solution000002.solution | 4 - .../model_1_3_3-solution000003.solution | 4 - .../model_1_3_3-solution000004.solution | 4 - .../model_1_3_3-solution000005.solution | 4 - .../model_1_3_3-solution000006.solution | 4 - .../model_1_3_3-solution000007.solution | 4 - .../expected/model_1_3_3.eprime | 74 - .../model_1_3_4-solution000001.solution | 4 - .../model_1_3_4-solution000002.solution | 4 - .../model_1_3_4-solution000003.solution | 4 - .../model_1_3_4-solution000004.solution | 4 - .../model_1_3_4-solution000005.solution | 4 - .../model_1_3_4-solution000006.solution | 4 - .../model_1_3_4-solution000007.solution | 4 - .../expected/model_1_3_4.eprime | 99 -- .../model_1_4_1-solution000001.solution | 4 - .../model_1_4_1-solution000002.solution | 4 - .../model_1_4_1-solution000003.solution | 4 - .../model_1_4_1-solution000004.solution | 4 - .../model_1_4_1-solution000005.solution | 4 - .../model_1_4_1-solution000006.solution | 4 - .../model_1_4_1-solution000007.solution | 4 - .../expected/model_1_4_1.eprime | 71 - .../model_1_4_2-solution000001.solution | 4 - .../model_1_4_2-solution000002.solution | 4 - .../model_1_4_2-solution000003.solution | 4 - .../model_1_4_2-solution000004.solution | 4 - .../model_1_4_2-solution000005.solution | 4 - .../model_1_4_2-solution000006.solution | 4 - .../model_1_4_2-solution000007.solution | 4 - .../expected/model_1_4_2.eprime | 90 -- .../model_1_4_3-solution000001.solution | 4 - .../model_1_4_3-solution000002.solution | 4 - .../model_1_4_3-solution000003.solution | 4 - .../model_1_4_3-solution000004.solution | 4 - .../model_1_4_3-solution000005.solution | 4 - .../model_1_4_3-solution000006.solution | 4 - .../model_1_4_3-solution000007.solution | 4 - .../expected/model_1_4_3.eprime | 95 -- .../model_1_4_4-solution000001.solution | 4 - .../model_1_4_4-solution000002.solution | 4 - .../model_1_4_4-solution000003.solution | 4 - .../model_1_4_4-solution000004.solution | 4 - .../model_1_4_4-solution000005.solution | 4 - .../model_1_4_4-solution000006.solution | 4 - .../model_1_4_4-solution000007.solution | 4 - .../expected/model_1_4_4.eprime | 71 - .../model_2_1_1-solution000001.solution | 4 - .../model_2_1_1-solution000002.solution | 4 - .../model_2_1_1-solution000003.solution | 4 - .../model_2_1_1-solution000004.solution | 4 - .../model_2_1_1-solution000005.solution | 4 - .../model_2_1_1-solution000006.solution | 4 - .../model_2_1_1-solution000007.solution | 4 - .../expected/model_2_1_1.eprime | 68 - .../model_2_1_2-solution000001.solution | 4 - .../model_2_1_2-solution000002.solution | 4 - .../model_2_1_2-solution000003.solution | 4 - .../model_2_1_2-solution000004.solution | 4 - .../model_2_1_2-solution000005.solution | 4 - .../model_2_1_2-solution000006.solution | 4 - .../model_2_1_2-solution000007.solution | 4 - .../expected/model_2_1_2.eprime | 68 - .../model_2_1_3-solution000001.solution | 4 - .../model_2_1_3-solution000002.solution | 4 - .../model_2_1_3-solution000003.solution | 4 - .../model_2_1_3-solution000004.solution | 4 - .../model_2_1_3-solution000005.solution | 4 - .../model_2_1_3-solution000006.solution | 4 - .../model_2_1_3-solution000007.solution | 4 - .../expected/model_2_1_3.eprime | 92 -- .../model_2_1_4-solution000001.solution | 4 - .../model_2_1_4-solution000002.solution | 4 - .../model_2_1_4-solution000003.solution | 4 - .../model_2_1_4-solution000004.solution | 4 - .../model_2_1_4-solution000005.solution | 4 - .../model_2_1_4-solution000006.solution | 4 - .../model_2_1_4-solution000007.solution | 4 - .../expected/model_2_1_4.eprime | 91 -- .../model_2_2_1-solution000001.solution | 4 - .../model_2_2_1-solution000002.solution | 4 - .../model_2_2_1-solution000003.solution | 4 - .../model_2_2_1-solution000004.solution | 4 - .../model_2_2_1-solution000005.solution | 4 - .../model_2_2_1-solution000006.solution | 4 - .../model_2_2_1-solution000007.solution | 4 - .../expected/model_2_2_1.eprime | 82 -- .../model_2_2_2-solution000001.solution | 4 - .../model_2_2_2-solution000002.solution | 4 - .../model_2_2_2-solution000003.solution | 4 - .../model_2_2_2-solution000004.solution | 4 - .../model_2_2_2-solution000005.solution | 4 - .../model_2_2_2-solution000006.solution | 4 - .../model_2_2_2-solution000007.solution | 4 - .../expected/model_2_2_2.eprime | 77 -- .../model_2_2_3-solution000001.solution | 4 - .../model_2_2_3-solution000002.solution | 4 - .../model_2_2_3-solution000003.solution | 4 - .../model_2_2_3-solution000004.solution | 4 - .../model_2_2_3-solution000005.solution | 4 - .../model_2_2_3-solution000006.solution | 4 - .../model_2_2_3-solution000007.solution | 4 - .../expected/model_2_2_3.eprime | 93 -- .../model_2_2_4-solution000001.solution | 4 - .../model_2_2_4-solution000002.solution | 4 - .../model_2_2_4-solution000003.solution | 4 - .../model_2_2_4-solution000004.solution | 4 - .../model_2_2_4-solution000005.solution | 4 - .../model_2_2_4-solution000006.solution | 4 - .../model_2_2_4-solution000007.solution | 4 - .../expected/model_2_2_4.eprime | 94 -- .../model_2_3_1-solution000001.solution | 4 - .../model_2_3_1-solution000002.solution | 4 - .../model_2_3_1-solution000003.solution | 4 - .../model_2_3_1-solution000004.solution | 4 - .../model_2_3_1-solution000005.solution | 4 - .../model_2_3_1-solution000006.solution | 4 - .../model_2_3_1-solution000007.solution | 4 - .../expected/model_2_3_1.eprime | 106 -- .../model_2_3_2-solution000001.solution | 4 - .../model_2_3_2-solution000002.solution | 4 - .../model_2_3_2-solution000003.solution | 4 - .../model_2_3_2-solution000004.solution | 4 - .../model_2_3_2-solution000005.solution | 4 - .../model_2_3_2-solution000006.solution | 4 - .../model_2_3_2-solution000007.solution | 4 - .../expected/model_2_3_2.eprime | 93 -- .../model_2_3_3-solution000001.solution | 4 - .../model_2_3_3-solution000002.solution | 4 - .../model_2_3_3-solution000003.solution | 4 - .../model_2_3_3-solution000004.solution | 4 - .../model_2_3_3-solution000005.solution | 4 - .../model_2_3_3-solution000006.solution | 4 - .../model_2_3_3-solution000007.solution | 4 - .../expected/model_2_3_3.eprime | 93 -- .../model_2_3_4-solution000001.solution | 4 - .../model_2_3_4-solution000002.solution | 4 - .../model_2_3_4-solution000003.solution | 4 - .../model_2_3_4-solution000004.solution | 4 - .../model_2_3_4-solution000005.solution | 4 - .../model_2_3_4-solution000006.solution | 4 - .../model_2_3_4-solution000007.solution | 4 - .../expected/model_2_3_4.eprime | 123 -- .../model_2_4_1-solution000001.solution | 4 - .../model_2_4_1-solution000002.solution | 4 - .../model_2_4_1-solution000003.solution | 4 - .../model_2_4_1-solution000004.solution | 4 - .../model_2_4_1-solution000005.solution | 4 - .../model_2_4_1-solution000006.solution | 4 - .../model_2_4_1-solution000007.solution | 4 - .../expected/model_2_4_1.eprime | 105 -- .../model_2_4_2-solution000001.solution | 4 - .../model_2_4_2-solution000002.solution | 4 - .../model_2_4_2-solution000003.solution | 4 - .../model_2_4_2-solution000004.solution | 4 - .../model_2_4_2-solution000005.solution | 4 - .../model_2_4_2-solution000006.solution | 4 - .../model_2_4_2-solution000007.solution | 4 - .../expected/model_2_4_2.eprime | 94 -- .../model_2_4_3-solution000001.solution | 4 - .../model_2_4_3-solution000002.solution | 4 - .../model_2_4_3-solution000003.solution | 4 - .../model_2_4_3-solution000004.solution | 4 - .../model_2_4_3-solution000005.solution | 4 - .../model_2_4_3-solution000006.solution | 4 - .../model_2_4_3-solution000007.solution | 4 - .../expected/model_2_4_3.eprime | 122 -- .../model_2_4_4-solution000001.solution | 4 - .../model_2_4_4-solution000002.solution | 4 - .../model_2_4_4-solution000003.solution | 4 - .../model_2_4_4-solution000004.solution | 4 - .../model_2_4_4-solution000005.solution | 4 - .../model_2_4_4-solution000006.solution | 4 - .../model_2_4_4-solution000007.solution | 4 - .../expected/model_2_4_4.eprime | 94 -- .../model_3_1_1-solution000001.solution | 4 - .../model_3_1_1-solution000002.solution | 4 - .../model_3_1_1-solution000003.solution | 4 - .../model_3_1_1-solution000004.solution | 4 - .../model_3_1_1-solution000005.solution | 4 - .../model_3_1_1-solution000006.solution | 4 - .../model_3_1_1-solution000007.solution | 4 - .../expected/model_3_1_1.eprime | 75 - .../model_3_1_2-solution000001.solution | 4 - .../model_3_1_2-solution000002.solution | 4 - .../model_3_1_2-solution000003.solution | 4 - .../model_3_1_2-solution000004.solution | 4 - .../model_3_1_2-solution000005.solution | 4 - .../model_3_1_2-solution000006.solution | 4 - .../model_3_1_2-solution000007.solution | 4 - .../expected/model_3_1_2.eprime | 95 -- .../model_3_1_3-solution000001.solution | 4 - .../model_3_1_3-solution000002.solution | 4 - .../model_3_1_3-solution000003.solution | 4 - .../model_3_1_3-solution000004.solution | 4 - .../model_3_1_3-solution000005.solution | 4 - .../model_3_1_3-solution000006.solution | 4 - .../model_3_1_3-solution000007.solution | 4 - .../expected/model_3_1_3.eprime | 75 - .../model_3_1_4-solution000001.solution | 4 - .../model_3_1_4-solution000002.solution | 4 - .../model_3_1_4-solution000003.solution | 4 - .../model_3_1_4-solution000004.solution | 4 - .../model_3_1_4-solution000005.solution | 4 - .../model_3_1_4-solution000006.solution | 4 - .../model_3_1_4-solution000007.solution | 4 - .../expected/model_3_1_4.eprime | 99 -- .../model_3_2_1-solution000001.solution | 4 - .../model_3_2_1-solution000002.solution | 4 - .../model_3_2_1-solution000003.solution | 4 - .../model_3_2_1-solution000004.solution | 4 - .../model_3_2_1-solution000005.solution | 4 - .../model_3_2_1-solution000006.solution | 4 - .../model_3_2_1-solution000007.solution | 4 - .../expected/model_3_2_1.eprime | 106 -- .../model_3_2_2-solution000001.solution | 4 - .../model_3_2_2-solution000002.solution | 4 - .../model_3_2_2-solution000003.solution | 4 - .../model_3_2_2-solution000004.solution | 4 - .../model_3_2_2-solution000005.solution | 4 - .../model_3_2_2-solution000006.solution | 4 - .../model_3_2_2-solution000007.solution | 4 - .../expected/model_3_2_2.eprime | 93 -- .../model_3_2_3-solution000001.solution | 4 - .../model_3_2_3-solution000002.solution | 4 - .../model_3_2_3-solution000003.solution | 4 - .../model_3_2_3-solution000004.solution | 4 - .../model_3_2_3-solution000005.solution | 4 - .../model_3_2_3-solution000006.solution | 4 - .../model_3_2_3-solution000007.solution | 4 - .../expected/model_3_2_3.eprime | 93 -- .../model_3_2_4-solution000001.solution | 4 - .../model_3_2_4-solution000002.solution | 4 - .../model_3_2_4-solution000003.solution | 4 - .../model_3_2_4-solution000004.solution | 4 - .../model_3_2_4-solution000005.solution | 4 - .../model_3_2_4-solution000006.solution | 4 - .../model_3_2_4-solution000007.solution | 4 - .../expected/model_3_2_4.eprime | 123 -- .../model_3_3_1-solution000001.solution | 4 - .../model_3_3_1-solution000002.solution | 4 - .../model_3_3_1-solution000003.solution | 4 - .../model_3_3_1-solution000004.solution | 4 - .../model_3_3_1-solution000005.solution | 4 - .../model_3_3_1-solution000006.solution | 4 - .../model_3_3_1-solution000007.solution | 4 - .../expected/model_3_3_1.eprime | 86 -- .../model_3_3_2-solution000001.solution | 4 - .../model_3_3_2-solution000002.solution | 4 - .../model_3_3_2-solution000003.solution | 4 - .../model_3_3_2-solution000004.solution | 4 - .../model_3_3_2-solution000005.solution | 4 - .../model_3_3_2-solution000006.solution | 4 - .../model_3_3_2-solution000007.solution | 4 - .../expected/model_3_3_2.eprime | 93 -- .../model_3_3_3-solution000001.solution | 4 - .../model_3_3_3-solution000002.solution | 4 - .../model_3_3_3-solution000003.solution | 4 - .../model_3_3_3-solution000004.solution | 4 - .../model_3_3_3-solution000005.solution | 4 - .../model_3_3_3-solution000006.solution | 4 - .../model_3_3_3-solution000007.solution | 4 - .../expected/model_3_3_3.eprime | 79 -- .../model_3_3_4-solution000001.solution | 4 - .../model_3_3_4-solution000002.solution | 4 - .../model_3_3_4-solution000003.solution | 4 - .../model_3_3_4-solution000004.solution | 4 - .../model_3_3_4-solution000005.solution | 4 - .../model_3_3_4-solution000006.solution | 4 - .../model_3_3_4-solution000007.solution | 4 - .../expected/model_3_3_4.eprime | 98 -- .../model_3_4_1-solution000001.solution | 4 - .../model_3_4_1-solution000002.solution | 4 - .../model_3_4_1-solution000003.solution | 4 - .../model_3_4_1-solution000004.solution | 4 - .../model_3_4_1-solution000005.solution | 4 - .../model_3_4_1-solution000006.solution | 4 - .../model_3_4_1-solution000007.solution | 4 - .../expected/model_3_4_1.eprime | 110 -- .../model_3_4_2-solution000001.solution | 4 - .../model_3_4_2-solution000002.solution | 4 - .../model_3_4_2-solution000003.solution | 4 - .../model_3_4_2-solution000004.solution | 4 - .../model_3_4_2-solution000005.solution | 4 - .../model_3_4_2-solution000006.solution | 4 - .../model_3_4_2-solution000007.solution | 4 - .../expected/model_3_4_2.eprime | 122 -- .../model_3_4_3-solution000001.solution | 4 - .../model_3_4_3-solution000002.solution | 4 - .../model_3_4_3-solution000003.solution | 4 - .../model_3_4_3-solution000004.solution | 4 - .../model_3_4_3-solution000005.solution | 4 - .../model_3_4_3-solution000006.solution | 4 - .../model_3_4_3-solution000007.solution | 4 - .../expected/model_3_4_3.eprime | 98 -- .../model_3_4_4-solution000001.solution | 4 - .../model_3_4_4-solution000002.solution | 4 - .../model_3_4_4-solution000003.solution | 4 - .../model_3_4_4-solution000004.solution | 4 - .../model_3_4_4-solution000005.solution | 4 - .../model_3_4_4-solution000006.solution | 4 - .../model_3_4_4-solution000007.solution | 4 - .../expected/model_3_4_4.eprime | 98 -- .../model_4_1_1-solution000001.solution | 4 - .../model_4_1_1-solution000002.solution | 4 - .../model_4_1_1-solution000003.solution | 4 - .../model_4_1_1-solution000004.solution | 4 - .../model_4_1_1-solution000005.solution | 4 - .../model_4_1_1-solution000006.solution | 4 - .../model_4_1_1-solution000007.solution | 4 - .../expected/model_4_1_1.eprime | 72 - .../model_4_1_2-solution000001.solution | 4 - .../model_4_1_2-solution000002.solution | 4 - .../model_4_1_2-solution000003.solution | 4 - .../model_4_1_2-solution000004.solution | 4 - .../model_4_1_2-solution000005.solution | 4 - .../model_4_1_2-solution000006.solution | 4 - .../model_4_1_2-solution000007.solution | 4 - .../expected/model_4_1_2.eprime | 91 -- .../model_4_1_3-solution000001.solution | 4 - .../model_4_1_3-solution000002.solution | 4 - .../model_4_1_3-solution000003.solution | 4 - .../model_4_1_3-solution000004.solution | 4 - .../model_4_1_3-solution000005.solution | 4 - .../model_4_1_3-solution000006.solution | 4 - .../model_4_1_3-solution000007.solution | 4 - .../expected/model_4_1_3.eprime | 96 -- .../model_4_1_4-solution000001.solution | 4 - .../model_4_1_4-solution000002.solution | 4 - .../model_4_1_4-solution000003.solution | 4 - .../model_4_1_4-solution000004.solution | 4 - .../model_4_1_4-solution000005.solution | 4 - .../model_4_1_4-solution000006.solution | 4 - .../model_4_1_4-solution000007.solution | 4 - .../expected/model_4_1_4.eprime | 72 - .../model_4_2_1-solution000001.solution | 4 - .../model_4_2_1-solution000002.solution | 4 - .../model_4_2_1-solution000003.solution | 4 - .../model_4_2_1-solution000004.solution | 4 - .../model_4_2_1-solution000005.solution | 4 - .../model_4_2_1-solution000006.solution | 4 - .../model_4_2_1-solution000007.solution | 4 - .../expected/model_4_2_1.eprime | 105 -- .../model_4_2_2-solution000001.solution | 4 - .../model_4_2_2-solution000002.solution | 4 - .../model_4_2_2-solution000003.solution | 4 - .../model_4_2_2-solution000004.solution | 4 - .../model_4_2_2-solution000005.solution | 4 - .../model_4_2_2-solution000006.solution | 4 - .../model_4_2_2-solution000007.solution | 4 - .../expected/model_4_2_2.eprime | 94 -- .../model_4_2_3-solution000001.solution | 4 - .../model_4_2_3-solution000002.solution | 4 - .../model_4_2_3-solution000003.solution | 4 - .../model_4_2_3-solution000004.solution | 4 - .../model_4_2_3-solution000005.solution | 4 - .../model_4_2_3-solution000006.solution | 4 - .../model_4_2_3-solution000007.solution | 4 - .../expected/model_4_2_3.eprime | 122 -- .../model_4_2_4-solution000001.solution | 4 - .../model_4_2_4-solution000002.solution | 4 - .../model_4_2_4-solution000003.solution | 4 - .../model_4_2_4-solution000004.solution | 4 - .../model_4_2_4-solution000005.solution | 4 - .../model_4_2_4-solution000006.solution | 4 - .../model_4_2_4-solution000007.solution | 4 - .../expected/model_4_2_4.eprime | 94 -- .../model_4_3_1-solution000001.solution | 4 - .../model_4_3_1-solution000002.solution | 4 - .../model_4_3_1-solution000003.solution | 4 - .../model_4_3_1-solution000004.solution | 4 - .../model_4_3_1-solution000005.solution | 4 - .../model_4_3_1-solution000006.solution | 4 - .../model_4_3_1-solution000007.solution | 4 - .../expected/model_4_3_1.eprime | 110 -- .../model_4_3_2-solution000001.solution | 4 - .../model_4_3_2-solution000002.solution | 4 - .../model_4_3_2-solution000003.solution | 4 - .../model_4_3_2-solution000004.solution | 4 - .../model_4_3_2-solution000005.solution | 4 - .../model_4_3_2-solution000006.solution | 4 - .../model_4_3_2-solution000007.solution | 4 - .../expected/model_4_3_2.eprime | 122 -- .../model_4_3_3-solution000001.solution | 4 - .../model_4_3_3-solution000002.solution | 4 - .../model_4_3_3-solution000003.solution | 4 - .../model_4_3_3-solution000004.solution | 4 - .../model_4_3_3-solution000005.solution | 4 - .../model_4_3_3-solution000006.solution | 4 - .../model_4_3_3-solution000007.solution | 4 - .../expected/model_4_3_3.eprime | 98 -- .../model_4_3_4-solution000001.solution | 4 - .../model_4_3_4-solution000002.solution | 4 - .../model_4_3_4-solution000003.solution | 4 - .../model_4_3_4-solution000004.solution | 4 - .../model_4_3_4-solution000005.solution | 4 - .../model_4_3_4-solution000006.solution | 4 - .../model_4_3_4-solution000007.solution | 4 - .../expected/model_4_3_4.eprime | 98 -- .../model_4_4_1-solution000001.solution | 4 - .../model_4_4_1-solution000002.solution | 4 - .../model_4_4_1-solution000003.solution | 4 - .../model_4_4_1-solution000004.solution | 4 - .../model_4_4_1-solution000005.solution | 4 - .../model_4_4_1-solution000006.solution | 4 - .../model_4_4_1-solution000007.solution | 4 - .../expected/model_4_4_1.eprime | 86 -- .../model_4_4_2-solution000001.solution | 4 - .../model_4_4_2-solution000002.solution | 4 - .../model_4_4_2-solution000003.solution | 4 - .../model_4_4_2-solution000004.solution | 4 - .../model_4_4_2-solution000005.solution | 4 - .../model_4_4_2-solution000006.solution | 4 - .../model_4_4_2-solution000007.solution | 4 - .../expected/model_4_4_2.eprime | 94 -- .../model_4_4_3-solution000001.solution | 4 - .../model_4_4_3-solution000002.solution | 4 - .../model_4_4_3-solution000003.solution | 4 - .../model_4_4_3-solution000004.solution | 4 - .../model_4_4_3-solution000005.solution | 4 - .../model_4_4_3-solution000006.solution | 4 - .../model_4_4_3-solution000007.solution | 4 - .../expected/model_4_4_3.eprime | 98 -- .../model_4_4_4-solution000001.solution | 4 - .../model_4_4_4-solution000002.solution | 4 - .../model_4_4_4-solution000003.solution | 4 - .../model_4_4_4-solution000004.solution | 4 - .../model_4_4_4-solution000005.solution | 4 - .../model_4_4_4-solution000006.solution | 4 - .../model_4_4_4-solution000007.solution | 4 - .../expected/model_4_4_4.eprime | 80 -- .../model_1_1_1-solution000001.solution | 3 - .../model_1_1_1-solution000002.solution | 3 - .../model_1_1_1-solution000003.solution | 3 - .../model_1_1_1-solution000004.solution | 3 - .../model_1_1_1-solution000005.solution | 3 - .../model_1_1_1-solution000006.solution | 3 - .../model_1_1_1-solution000007.solution | 3 - .../model_1_1_1-solution000008.solution | 3 - .../cut_01_on/expected/model_1_1_1.eprime | 10 - .../model_1_1_2-solution000001.solution | 3 - .../model_1_1_2-solution000002.solution | 3 - .../model_1_1_2-solution000003.solution | 3 - .../model_1_1_2-solution000004.solution | 3 - .../model_1_1_2-solution000005.solution | 3 - .../model_1_1_2-solution000006.solution | 3 - .../model_1_1_2-solution000007.solution | 3 - .../model_1_1_2-solution000008.solution | 3 - .../cut_01_on/expected/model_1_1_2.eprime | 18 - .../model_1_1_3-solution000001.solution | 3 - .../model_1_1_3-solution000002.solution | 3 - .../model_1_1_3-solution000003.solution | 3 - .../model_1_1_3-solution000004.solution | 3 - .../model_1_1_3-solution000005.solution | 3 - .../model_1_1_3-solution000006.solution | 3 - .../model_1_1_3-solution000007.solution | 3 - .../model_1_1_3-solution000008.solution | 3 - .../cut_01_on/expected/model_1_1_3.eprime | 21 - .../model_1_1_4-solution000001.solution | 3 - .../model_1_1_4-solution000002.solution | 3 - .../model_1_1_4-solution000003.solution | 3 - .../model_1_1_4-solution000004.solution | 3 - .../model_1_1_4-solution000005.solution | 3 - .../model_1_1_4-solution000006.solution | 3 - .../model_1_1_4-solution000007.solution | 3 - .../model_1_1_4-solution000008.solution | 3 - .../cut_01_on/expected/model_1_1_4.eprime | 21 - .../model_1_2_1-solution000001.solution | 3 - .../model_1_2_1-solution000002.solution | 3 - .../model_1_2_1-solution000003.solution | 3 - .../model_1_2_1-solution000004.solution | 3 - .../model_1_2_1-solution000005.solution | 3 - .../model_1_2_1-solution000006.solution | 3 - .../model_1_2_1-solution000007.solution | 3 - .../model_1_2_1-solution000008.solution | 3 - .../cut_01_on/expected/model_1_2_1.eprime | 18 - .../model_1_2_2-solution000001.solution | 3 - .../model_1_2_2-solution000002.solution | 3 - .../model_1_2_2-solution000003.solution | 3 - .../model_1_2_2-solution000004.solution | 3 - .../model_1_2_2-solution000005.solution | 3 - .../model_1_2_2-solution000006.solution | 3 - .../model_1_2_2-solution000007.solution | 3 - .../model_1_2_2-solution000008.solution | 3 - .../cut_01_on/expected/model_1_2_2.eprime | 18 - .../model_1_2_3-solution000001.solution | 3 - .../model_1_2_3-solution000002.solution | 3 - .../model_1_2_3-solution000003.solution | 3 - .../model_1_2_3-solution000004.solution | 3 - .../model_1_2_3-solution000005.solution | 3 - .../model_1_2_3-solution000006.solution | 3 - .../model_1_2_3-solution000007.solution | 3 - .../model_1_2_3-solution000008.solution | 3 - .../cut_01_on/expected/model_1_2_3.eprime | 42 - .../model_1_2_4-solution000001.solution | 3 - .../model_1_2_4-solution000002.solution | 3 - .../model_1_2_4-solution000003.solution | 3 - .../model_1_2_4-solution000004.solution | 3 - .../model_1_2_4-solution000005.solution | 3 - .../model_1_2_4-solution000006.solution | 3 - .../model_1_2_4-solution000007.solution | 3 - .../model_1_2_4-solution000008.solution | 3 - .../cut_01_on/expected/model_1_2_4.eprime | 43 - .../model_1_3_1-solution000001.solution | 3 - .../model_1_3_1-solution000002.solution | 3 - .../model_1_3_1-solution000003.solution | 3 - .../model_1_3_1-solution000004.solution | 3 - .../model_1_3_1-solution000005.solution | 3 - .../model_1_3_1-solution000006.solution | 3 - .../model_1_3_1-solution000007.solution | 3 - .../model_1_3_1-solution000008.solution | 3 - .../cut_01_on/expected/model_1_3_1.eprime | 22 - .../model_1_3_2-solution000001.solution | 3 - .../model_1_3_2-solution000002.solution | 3 - .../model_1_3_2-solution000003.solution | 3 - .../model_1_3_2-solution000004.solution | 3 - .../model_1_3_2-solution000005.solution | 3 - .../model_1_3_2-solution000006.solution | 3 - .../model_1_3_2-solution000007.solution | 3 - .../model_1_3_2-solution000008.solution | 3 - .../cut_01_on/expected/model_1_3_2.eprime | 42 - .../model_1_3_3-solution000001.solution | 3 - .../model_1_3_3-solution000002.solution | 3 - .../model_1_3_3-solution000003.solution | 3 - .../model_1_3_3-solution000004.solution | 3 - .../model_1_3_3-solution000005.solution | 3 - .../model_1_3_3-solution000006.solution | 3 - .../model_1_3_3-solution000007.solution | 3 - .../model_1_3_3-solution000008.solution | 3 - .../cut_01_on/expected/model_1_3_3.eprime | 22 - .../model_1_3_4-solution000001.solution | 3 - .../model_1_3_4-solution000002.solution | 3 - .../model_1_3_4-solution000003.solution | 3 - .../model_1_3_4-solution000004.solution | 3 - .../model_1_3_4-solution000005.solution | 3 - .../model_1_3_4-solution000006.solution | 3 - .../model_1_3_4-solution000007.solution | 3 - .../model_1_3_4-solution000008.solution | 3 - .../cut_01_on/expected/model_1_3_4.eprime | 47 - .../model_1_4_1-solution000001.solution | 3 - .../model_1_4_1-solution000002.solution | 3 - .../model_1_4_1-solution000003.solution | 3 - .../model_1_4_1-solution000004.solution | 3 - .../model_1_4_1-solution000005.solution | 3 - .../model_1_4_1-solution000006.solution | 3 - .../model_1_4_1-solution000007.solution | 3 - .../model_1_4_1-solution000008.solution | 3 - .../cut_01_on/expected/model_1_4_1.eprime | 22 - .../model_1_4_2-solution000001.solution | 3 - .../model_1_4_2-solution000002.solution | 3 - .../model_1_4_2-solution000003.solution | 3 - .../model_1_4_2-solution000004.solution | 3 - .../model_1_4_2-solution000005.solution | 3 - .../model_1_4_2-solution000006.solution | 3 - .../model_1_4_2-solution000007.solution | 3 - .../model_1_4_2-solution000008.solution | 3 - .../cut_01_on/expected/model_1_4_2.eprime | 42 - .../model_1_4_3-solution000001.solution | 3 - .../model_1_4_3-solution000002.solution | 3 - .../model_1_4_3-solution000003.solution | 3 - .../model_1_4_3-solution000004.solution | 3 - .../model_1_4_3-solution000005.solution | 3 - .../model_1_4_3-solution000006.solution | 3 - .../model_1_4_3-solution000007.solution | 3 - .../model_1_4_3-solution000008.solution | 3 - .../cut_01_on/expected/model_1_4_3.eprime | 46 - .../model_1_4_4-solution000001.solution | 3 - .../model_1_4_4-solution000002.solution | 3 - .../model_1_4_4-solution000003.solution | 3 - .../model_1_4_4-solution000004.solution | 3 - .../model_1_4_4-solution000005.solution | 3 - .../model_1_4_4-solution000006.solution | 3 - .../model_1_4_4-solution000007.solution | 3 - .../model_1_4_4-solution000008.solution | 3 - .../cut_01_on/expected/model_1_4_4.eprime | 22 - .../model_2_1_1-solution000001.solution | 3 - .../model_2_1_1-solution000002.solution | 3 - .../model_2_1_1-solution000003.solution | 3 - .../model_2_1_1-solution000004.solution | 3 - .../model_2_1_1-solution000005.solution | 3 - .../model_2_1_1-solution000006.solution | 3 - .../model_2_1_1-solution000007.solution | 3 - .../model_2_1_1-solution000008.solution | 3 - .../cut_01_on/expected/model_2_1_1.eprime | 20 - .../model_2_1_2-solution000001.solution | 3 - .../model_2_1_2-solution000002.solution | 3 - .../model_2_1_2-solution000003.solution | 3 - .../model_2_1_2-solution000004.solution | 3 - .../model_2_1_2-solution000005.solution | 3 - .../model_2_1_2-solution000006.solution | 3 - .../model_2_1_2-solution000007.solution | 3 - .../model_2_1_2-solution000008.solution | 3 - .../cut_01_on/expected/model_2_1_2.eprime | 20 - .../model_2_1_3-solution000001.solution | 3 - .../model_2_1_3-solution000002.solution | 3 - .../model_2_1_3-solution000003.solution | 3 - .../model_2_1_3-solution000004.solution | 3 - .../model_2_1_3-solution000005.solution | 3 - .../model_2_1_3-solution000006.solution | 3 - .../model_2_1_3-solution000007.solution | 3 - .../model_2_1_3-solution000008.solution | 3 - .../cut_01_on/expected/model_2_1_3.eprime | 44 - .../model_2_1_4-solution000001.solution | 3 - .../model_2_1_4-solution000002.solution | 3 - .../model_2_1_4-solution000003.solution | 3 - .../model_2_1_4-solution000004.solution | 3 - .../model_2_1_4-solution000005.solution | 3 - .../model_2_1_4-solution000006.solution | 3 - .../model_2_1_4-solution000007.solution | 3 - .../model_2_1_4-solution000008.solution | 3 - .../cut_01_on/expected/model_2_1_4.eprime | 44 - .../model_2_2_1-solution000001.solution | 3 - .../model_2_2_1-solution000002.solution | 3 - .../model_2_2_1-solution000003.solution | 3 - .../model_2_2_1-solution000004.solution | 3 - .../model_2_2_1-solution000005.solution | 3 - .../model_2_2_1-solution000006.solution | 3 - .../model_2_2_1-solution000007.solution | 3 - .../model_2_2_1-solution000008.solution | 3 - .../cut_01_on/expected/model_2_2_1.eprime | 20 - .../model_2_2_2-solution000001.solution | 3 - .../model_2_2_2-solution000002.solution | 3 - .../model_2_2_2-solution000003.solution | 3 - .../model_2_2_2-solution000004.solution | 3 - .../model_2_2_2-solution000005.solution | 3 - .../model_2_2_2-solution000006.solution | 3 - .../model_2_2_2-solution000007.solution | 3 - .../model_2_2_2-solution000008.solution | 3 - .../cut_01_on/expected/model_2_2_2.eprime | 15 - .../model_2_2_3-solution000001.solution | 3 - .../model_2_2_3-solution000002.solution | 3 - .../model_2_2_3-solution000003.solution | 3 - .../model_2_2_3-solution000004.solution | 3 - .../model_2_2_3-solution000005.solution | 3 - .../model_2_2_3-solution000006.solution | 3 - .../model_2_2_3-solution000007.solution | 3 - .../model_2_2_3-solution000008.solution | 3 - .../cut_01_on/expected/model_2_2_3.eprime | 32 - .../model_2_2_4-solution000001.solution | 3 - .../model_2_2_4-solution000002.solution | 3 - .../model_2_2_4-solution000003.solution | 3 - .../model_2_2_4-solution000004.solution | 3 - .../model_2_2_4-solution000005.solution | 3 - .../model_2_2_4-solution000006.solution | 3 - .../model_2_2_4-solution000007.solution | 3 - .../model_2_2_4-solution000008.solution | 3 - .../cut_01_on/expected/model_2_2_4.eprime | 33 - .../model_2_3_1-solution000001.solution | 3 - .../model_2_3_1-solution000002.solution | 3 - .../model_2_3_1-solution000003.solution | 3 - .../model_2_3_1-solution000004.solution | 3 - .../model_2_3_1-solution000005.solution | 3 - .../model_2_3_1-solution000006.solution | 3 - .../model_2_3_1-solution000007.solution | 3 - .../model_2_3_1-solution000008.solution | 3 - .../cut_01_on/expected/model_2_3_1.eprime | 45 - .../model_2_3_2-solution000001.solution | 3 - .../model_2_3_2-solution000002.solution | 3 - .../model_2_3_2-solution000003.solution | 3 - .../model_2_3_2-solution000004.solution | 3 - .../model_2_3_2-solution000005.solution | 3 - .../model_2_3_2-solution000006.solution | 3 - .../model_2_3_2-solution000007.solution | 3 - .../model_2_3_2-solution000008.solution | 3 - .../cut_01_on/expected/model_2_3_2.eprime | 33 - .../model_2_3_3-solution000001.solution | 3 - .../model_2_3_3-solution000002.solution | 3 - .../model_2_3_3-solution000003.solution | 3 - .../model_2_3_3-solution000004.solution | 3 - .../model_2_3_3-solution000005.solution | 3 - .../model_2_3_3-solution000006.solution | 3 - .../model_2_3_3-solution000007.solution | 3 - .../model_2_3_3-solution000008.solution | 3 - .../cut_01_on/expected/model_2_3_3.eprime | 33 - .../model_2_3_4-solution000001.solution | 3 - .../model_2_3_4-solution000002.solution | 3 - .../model_2_3_4-solution000003.solution | 3 - .../model_2_3_4-solution000004.solution | 3 - .../model_2_3_4-solution000005.solution | 3 - .../model_2_3_4-solution000006.solution | 3 - .../model_2_3_4-solution000007.solution | 3 - .../model_2_3_4-solution000008.solution | 3 - .../cut_01_on/expected/model_2_3_4.eprime | 62 - .../model_2_4_1-solution000001.solution | 3 - .../model_2_4_1-solution000002.solution | 3 - .../model_2_4_1-solution000003.solution | 3 - .../model_2_4_1-solution000004.solution | 3 - .../model_2_4_1-solution000005.solution | 3 - .../model_2_4_1-solution000006.solution | 3 - .../model_2_4_1-solution000007.solution | 3 - .../model_2_4_1-solution000008.solution | 3 - .../cut_01_on/expected/model_2_4_1.eprime | 45 - .../model_2_4_2-solution000001.solution | 3 - .../model_2_4_2-solution000002.solution | 3 - .../model_2_4_2-solution000003.solution | 3 - .../model_2_4_2-solution000004.solution | 3 - .../model_2_4_2-solution000005.solution | 3 - .../model_2_4_2-solution000006.solution | 3 - .../model_2_4_2-solution000007.solution | 3 - .../model_2_4_2-solution000008.solution | 3 - .../cut_01_on/expected/model_2_4_2.eprime | 34 - .../model_2_4_3-solution000001.solution | 3 - .../model_2_4_3-solution000002.solution | 3 - .../model_2_4_3-solution000003.solution | 3 - .../model_2_4_3-solution000004.solution | 3 - .../model_2_4_3-solution000005.solution | 3 - .../model_2_4_3-solution000006.solution | 3 - .../model_2_4_3-solution000007.solution | 3 - .../model_2_4_3-solution000008.solution | 3 - .../cut_01_on/expected/model_2_4_3.eprime | 61 - .../model_2_4_4-solution000001.solution | 3 - .../model_2_4_4-solution000002.solution | 3 - .../model_2_4_4-solution000003.solution | 3 - .../model_2_4_4-solution000004.solution | 3 - .../model_2_4_4-solution000005.solution | 3 - .../model_2_4_4-solution000006.solution | 3 - .../model_2_4_4-solution000007.solution | 3 - .../model_2_4_4-solution000008.solution | 3 - .../cut_01_on/expected/model_2_4_4.eprime | 34 - .../model_3_1_1-solution000001.solution | 3 - .../model_3_1_1-solution000002.solution | 3 - .../model_3_1_1-solution000003.solution | 3 - .../model_3_1_1-solution000004.solution | 3 - .../model_3_1_1-solution000005.solution | 3 - .../model_3_1_1-solution000006.solution | 3 - .../model_3_1_1-solution000007.solution | 3 - .../model_3_1_1-solution000008.solution | 3 - .../cut_01_on/expected/model_3_1_1.eprime | 23 - .../model_3_1_2-solution000001.solution | 3 - .../model_3_1_2-solution000002.solution | 3 - .../model_3_1_2-solution000003.solution | 3 - .../model_3_1_2-solution000004.solution | 3 - .../model_3_1_2-solution000005.solution | 3 - .../model_3_1_2-solution000006.solution | 3 - .../model_3_1_2-solution000007.solution | 3 - .../model_3_1_2-solution000008.solution | 3 - .../cut_01_on/expected/model_3_1_2.eprime | 44 - .../model_3_1_3-solution000001.solution | 3 - .../model_3_1_3-solution000002.solution | 3 - .../model_3_1_3-solution000003.solution | 3 - .../model_3_1_3-solution000004.solution | 3 - .../model_3_1_3-solution000005.solution | 3 - .../model_3_1_3-solution000006.solution | 3 - .../model_3_1_3-solution000007.solution | 3 - .../model_3_1_3-solution000008.solution | 3 - .../cut_01_on/expected/model_3_1_3.eprime | 23 - .../model_3_1_4-solution000001.solution | 3 - .../model_3_1_4-solution000002.solution | 3 - .../model_3_1_4-solution000003.solution | 3 - .../model_3_1_4-solution000004.solution | 3 - .../model_3_1_4-solution000005.solution | 3 - .../model_3_1_4-solution000006.solution | 3 - .../model_3_1_4-solution000007.solution | 3 - .../model_3_1_4-solution000008.solution | 3 - .../cut_01_on/expected/model_3_1_4.eprime | 48 - .../model_3_2_1-solution000001.solution | 3 - .../model_3_2_1-solution000002.solution | 3 - .../model_3_2_1-solution000003.solution | 3 - .../model_3_2_1-solution000004.solution | 3 - .../model_3_2_1-solution000005.solution | 3 - .../model_3_2_1-solution000006.solution | 3 - .../model_3_2_1-solution000007.solution | 3 - .../model_3_2_1-solution000008.solution | 3 - .../cut_01_on/expected/model_3_2_1.eprime | 44 - .../model_3_2_2-solution000001.solution | 3 - .../model_3_2_2-solution000002.solution | 3 - .../model_3_2_2-solution000003.solution | 3 - .../model_3_2_2-solution000004.solution | 3 - .../model_3_2_2-solution000005.solution | 3 - .../model_3_2_2-solution000006.solution | 3 - .../model_3_2_2-solution000007.solution | 3 - .../model_3_2_2-solution000008.solution | 3 - .../cut_01_on/expected/model_3_2_2.eprime | 32 - .../model_3_2_3-solution000001.solution | 3 - .../model_3_2_3-solution000002.solution | 3 - .../model_3_2_3-solution000003.solution | 3 - .../model_3_2_3-solution000004.solution | 3 - .../model_3_2_3-solution000005.solution | 3 - .../model_3_2_3-solution000006.solution | 3 - .../model_3_2_3-solution000007.solution | 3 - .../model_3_2_3-solution000008.solution | 3 - .../cut_01_on/expected/model_3_2_3.eprime | 32 - .../model_3_2_4-solution000001.solution | 3 - .../model_3_2_4-solution000002.solution | 3 - .../model_3_2_4-solution000003.solution | 3 - .../model_3_2_4-solution000004.solution | 3 - .../model_3_2_4-solution000005.solution | 3 - .../model_3_2_4-solution000006.solution | 3 - .../model_3_2_4-solution000007.solution | 3 - .../model_3_2_4-solution000008.solution | 3 - .../cut_01_on/expected/model_3_2_4.eprime | 61 - .../model_3_3_1-solution000001.solution | 3 - .../model_3_3_1-solution000002.solution | 3 - .../model_3_3_1-solution000003.solution | 3 - .../model_3_3_1-solution000004.solution | 3 - .../model_3_3_1-solution000005.solution | 3 - .../model_3_3_1-solution000006.solution | 3 - .../model_3_3_1-solution000007.solution | 3 - .../model_3_3_1-solution000008.solution | 3 - .../cut_01_on/expected/model_3_3_1.eprime | 25 - .../model_3_3_2-solution000001.solution | 3 - .../model_3_3_2-solution000002.solution | 3 - .../model_3_3_2-solution000003.solution | 3 - .../model_3_3_2-solution000004.solution | 3 - .../model_3_3_2-solution000005.solution | 3 - .../model_3_3_2-solution000006.solution | 3 - .../model_3_3_2-solution000007.solution | 3 - .../model_3_3_2-solution000008.solution | 3 - .../cut_01_on/expected/model_3_3_2.eprime | 33 - .../model_3_3_3-solution000001.solution | 3 - .../model_3_3_3-solution000002.solution | 3 - .../model_3_3_3-solution000003.solution | 3 - .../model_3_3_3-solution000004.solution | 3 - .../model_3_3_3-solution000005.solution | 3 - .../model_3_3_3-solution000006.solution | 3 - .../model_3_3_3-solution000007.solution | 3 - .../model_3_3_3-solution000008.solution | 3 - .../cut_01_on/expected/model_3_3_3.eprime | 18 - .../model_3_3_4-solution000001.solution | 3 - .../model_3_3_4-solution000002.solution | 3 - .../model_3_3_4-solution000003.solution | 3 - .../model_3_3_4-solution000004.solution | 3 - .../model_3_3_4-solution000005.solution | 3 - .../model_3_3_4-solution000006.solution | 3 - .../model_3_3_4-solution000007.solution | 3 - .../model_3_3_4-solution000008.solution | 3 - .../cut_01_on/expected/model_3_3_4.eprime | 37 - .../model_3_4_1-solution000001.solution | 3 - .../model_3_4_1-solution000002.solution | 3 - .../model_3_4_1-solution000003.solution | 3 - .../model_3_4_1-solution000004.solution | 3 - .../model_3_4_1-solution000005.solution | 3 - .../model_3_4_1-solution000006.solution | 3 - .../model_3_4_1-solution000007.solution | 3 - .../model_3_4_1-solution000008.solution | 3 - .../cut_01_on/expected/model_3_4_1.eprime | 49 - .../model_3_4_2-solution000001.solution | 3 - .../model_3_4_2-solution000002.solution | 3 - .../model_3_4_2-solution000003.solution | 3 - .../model_3_4_2-solution000004.solution | 3 - .../model_3_4_2-solution000005.solution | 3 - .../model_3_4_2-solution000006.solution | 3 - .../model_3_4_2-solution000007.solution | 3 - .../model_3_4_2-solution000008.solution | 3 - .../cut_01_on/expected/model_3_4_2.eprime | 61 - .../model_3_4_3-solution000001.solution | 3 - .../model_3_4_3-solution000002.solution | 3 - .../model_3_4_3-solution000003.solution | 3 - .../model_3_4_3-solution000004.solution | 3 - .../model_3_4_3-solution000005.solution | 3 - .../model_3_4_3-solution000006.solution | 3 - .../model_3_4_3-solution000007.solution | 3 - .../model_3_4_3-solution000008.solution | 3 - .../cut_01_on/expected/model_3_4_3.eprime | 37 - .../model_3_4_4-solution000001.solution | 3 - .../model_3_4_4-solution000002.solution | 3 - .../model_3_4_4-solution000003.solution | 3 - .../model_3_4_4-solution000004.solution | 3 - .../model_3_4_4-solution000005.solution | 3 - .../model_3_4_4-solution000006.solution | 3 - .../model_3_4_4-solution000007.solution | 3 - .../model_3_4_4-solution000008.solution | 3 - .../cut_01_on/expected/model_3_4_4.eprime | 37 - .../model_4_1_1-solution000001.solution | 3 - .../model_4_1_1-solution000002.solution | 3 - .../model_4_1_1-solution000003.solution | 3 - .../model_4_1_1-solution000004.solution | 3 - .../model_4_1_1-solution000005.solution | 3 - .../model_4_1_1-solution000006.solution | 3 - .../model_4_1_1-solution000007.solution | 3 - .../model_4_1_1-solution000008.solution | 3 - .../cut_01_on/expected/model_4_1_1.eprime | 24 - .../model_4_1_2-solution000001.solution | 3 - .../model_4_1_2-solution000002.solution | 3 - .../model_4_1_2-solution000003.solution | 3 - .../model_4_1_2-solution000004.solution | 3 - .../model_4_1_2-solution000005.solution | 3 - .../model_4_1_2-solution000006.solution | 3 - .../model_4_1_2-solution000007.solution | 3 - .../model_4_1_2-solution000008.solution | 3 - .../cut_01_on/expected/model_4_1_2.eprime | 44 - .../model_4_1_3-solution000001.solution | 3 - .../model_4_1_3-solution000002.solution | 3 - .../model_4_1_3-solution000003.solution | 3 - .../model_4_1_3-solution000004.solution | 3 - .../model_4_1_3-solution000005.solution | 3 - .../model_4_1_3-solution000006.solution | 3 - .../model_4_1_3-solution000007.solution | 3 - .../model_4_1_3-solution000008.solution | 3 - .../cut_01_on/expected/model_4_1_3.eprime | 48 - .../model_4_1_4-solution000001.solution | 3 - .../model_4_1_4-solution000002.solution | 3 - .../model_4_1_4-solution000003.solution | 3 - .../model_4_1_4-solution000004.solution | 3 - .../model_4_1_4-solution000005.solution | 3 - .../model_4_1_4-solution000006.solution | 3 - .../model_4_1_4-solution000007.solution | 3 - .../model_4_1_4-solution000008.solution | 3 - .../cut_01_on/expected/model_4_1_4.eprime | 24 - .../model_4_2_1-solution000001.solution | 3 - .../model_4_2_1-solution000002.solution | 3 - .../model_4_2_1-solution000003.solution | 3 - .../model_4_2_1-solution000004.solution | 3 - .../model_4_2_1-solution000005.solution | 3 - .../model_4_2_1-solution000006.solution | 3 - .../model_4_2_1-solution000007.solution | 3 - .../model_4_2_1-solution000008.solution | 3 - .../cut_01_on/expected/model_4_2_1.eprime | 44 - .../model_4_2_2-solution000001.solution | 3 - .../model_4_2_2-solution000002.solution | 3 - .../model_4_2_2-solution000003.solution | 3 - .../model_4_2_2-solution000004.solution | 3 - .../model_4_2_2-solution000005.solution | 3 - .../model_4_2_2-solution000006.solution | 3 - .../model_4_2_2-solution000007.solution | 3 - .../model_4_2_2-solution000008.solution | 3 - .../cut_01_on/expected/model_4_2_2.eprime | 33 - .../model_4_2_3-solution000001.solution | 3 - .../model_4_2_3-solution000002.solution | 3 - .../model_4_2_3-solution000003.solution | 3 - .../model_4_2_3-solution000004.solution | 3 - .../model_4_2_3-solution000005.solution | 3 - .../model_4_2_3-solution000006.solution | 3 - .../model_4_2_3-solution000007.solution | 3 - .../model_4_2_3-solution000008.solution | 3 - .../cut_01_on/expected/model_4_2_3.eprime | 60 - .../model_4_2_4-solution000001.solution | 3 - .../model_4_2_4-solution000002.solution | 3 - .../model_4_2_4-solution000003.solution | 3 - .../model_4_2_4-solution000004.solution | 3 - .../model_4_2_4-solution000005.solution | 3 - .../model_4_2_4-solution000006.solution | 3 - .../model_4_2_4-solution000007.solution | 3 - .../model_4_2_4-solution000008.solution | 3 - .../cut_01_on/expected/model_4_2_4.eprime | 33 - .../model_4_3_1-solution000001.solution | 3 - .../model_4_3_1-solution000002.solution | 3 - .../model_4_3_1-solution000003.solution | 3 - .../model_4_3_1-solution000004.solution | 3 - .../model_4_3_1-solution000005.solution | 3 - .../model_4_3_1-solution000006.solution | 3 - .../model_4_3_1-solution000007.solution | 3 - .../model_4_3_1-solution000008.solution | 3 - .../cut_01_on/expected/model_4_3_1.eprime | 49 - .../model_4_3_2-solution000001.solution | 3 - .../model_4_3_2-solution000002.solution | 3 - .../model_4_3_2-solution000003.solution | 3 - .../model_4_3_2-solution000004.solution | 3 - .../model_4_3_2-solution000005.solution | 3 - .../model_4_3_2-solution000006.solution | 3 - .../model_4_3_2-solution000007.solution | 3 - .../model_4_3_2-solution000008.solution | 3 - .../cut_01_on/expected/model_4_3_2.eprime | 61 - .../model_4_3_3-solution000001.solution | 3 - .../model_4_3_3-solution000002.solution | 3 - .../model_4_3_3-solution000003.solution | 3 - .../model_4_3_3-solution000004.solution | 3 - .../model_4_3_3-solution000005.solution | 3 - .../model_4_3_3-solution000006.solution | 3 - .../model_4_3_3-solution000007.solution | 3 - .../model_4_3_3-solution000008.solution | 3 - .../cut_01_on/expected/model_4_3_3.eprime | 37 - .../model_4_3_4-solution000001.solution | 3 - .../model_4_3_4-solution000002.solution | 3 - .../model_4_3_4-solution000003.solution | 3 - .../model_4_3_4-solution000004.solution | 3 - .../model_4_3_4-solution000005.solution | 3 - .../model_4_3_4-solution000006.solution | 3 - .../model_4_3_4-solution000007.solution | 3 - .../model_4_3_4-solution000008.solution | 3 - .../cut_01_on/expected/model_4_3_4.eprime | 37 - .../model_4_4_1-solution000001.solution | 3 - .../model_4_4_1-solution000002.solution | 3 - .../model_4_4_1-solution000003.solution | 3 - .../model_4_4_1-solution000004.solution | 3 - .../model_4_4_1-solution000005.solution | 3 - .../model_4_4_1-solution000006.solution | 3 - .../model_4_4_1-solution000007.solution | 3 - .../model_4_4_1-solution000008.solution | 3 - .../cut_01_on/expected/model_4_4_1.eprime | 25 - .../model_4_4_2-solution000001.solution | 3 - .../model_4_4_2-solution000002.solution | 3 - .../model_4_4_2-solution000003.solution | 3 - .../model_4_4_2-solution000004.solution | 3 - .../model_4_4_2-solution000005.solution | 3 - .../model_4_4_2-solution000006.solution | 3 - .../model_4_4_2-solution000007.solution | 3 - .../model_4_4_2-solution000008.solution | 3 - .../cut_01_on/expected/model_4_4_2.eprime | 34 - .../model_4_4_3-solution000001.solution | 3 - .../model_4_4_3-solution000002.solution | 3 - .../model_4_4_3-solution000003.solution | 3 - .../model_4_4_3-solution000004.solution | 3 - .../model_4_4_3-solution000005.solution | 3 - .../model_4_4_3-solution000006.solution | 3 - .../model_4_4_3-solution000007.solution | 3 - .../model_4_4_3-solution000008.solution | 3 - .../cut_01_on/expected/model_4_4_3.eprime | 37 - .../model_4_4_4-solution000001.solution | 3 - .../model_4_4_4-solution000002.solution | 3 - .../model_4_4_4-solution000003.solution | 3 - .../model_4_4_4-solution000004.solution | 3 - .../model_4_4_4-solution000005.solution | 3 - .../model_4_4_4-solution000006.solution | 3 - .../model_4_4_4-solution000007.solution | 3 - .../model_4_4_4-solution000008.solution | 3 - .../cut_01_on/expected/model_4_4_4.eprime | 19 - .../expected/model-p1-solution000001.solution | 12 - .../expected/model-p1-solution000002.solution | 12 - .../expected/model-p1-solution000003.solution | 12 - .../expected/model-p1-solution000004.solution | 12 - .../expected/model-p1-solution000005.solution | 12 - .../expected/model-p1-solution000006.solution | 12 - .../expected/model-p1-solution000007.solution | 12 - .../expected/model-p1-solution000008.solution | 12 - .../expected/model-p1-solution000009.solution | 12 - .../expected/model-p1.eprime-param | 3 - .../enum_functions/expected/model.eprime | 122 -- .../expected/model_1-solution000001.solution | 3 - .../expected/model_1-solution000002.solution | 3 - .../expected/model_1-solution000003.solution | 3 - .../expected/model_1-solution000004.solution | 3 - .../expected/model_1-solution000005.solution | 3 - .../expected/model_1-solution000006.solution | 3 - .../expected/model_1.eprime | 174 --- .../expected/model_2-solution000001.solution | 3 - .../expected/model_2-solution000002.solution | 3 - .../expected/model_2-solution000003.solution | 3 - .../expected/model_2-solution000004.solution | 3 - .../expected/model_2-solution000005.solution | 3 - .../expected/model_2-solution000006.solution | 3 - .../expected/model_2.eprime | 196 --- .../model_1_1-solution000001.solution | 4 - .../model_1_1-solution000002.solution | 4 - .../model_1_1-solution000003.solution | 4 - .../expected/model_1_1.eprime | 15 - .../model_1_2-solution000001.solution | 4 - .../model_1_2-solution000002.solution | 4 - .../model_1_2-solution000003.solution | 4 - .../expected/model_1_2.eprime | 24 - .../model_1_3-solution000001.solution | 4 - .../model_1_3-solution000002.solution | 4 - .../model_1_3-solution000003.solution | 4 - .../expected/model_1_3.eprime | 30 - .../model_1_4-solution000001.solution | 4 - .../model_1_4-solution000002.solution | 4 - .../model_1_4-solution000003.solution | 4 - .../expected/model_1_4.eprime | 30 - .../model_2_1-solution000001.solution | 4 - .../model_2_1-solution000002.solution | 4 - .../model_2_1-solution000003.solution | 4 - .../expected/model_2_1.eprime | 28 - .../model_2_2-solution000001.solution | 4 - .../model_2_2-solution000002.solution | 4 - .../model_2_2-solution000003.solution | 4 - .../expected/model_2_2.eprime | 23 - .../model_2_3-solution000001.solution | 4 - .../model_2_3-solution000002.solution | 4 - .../model_2_3-solution000003.solution | 4 - .../expected/model_2_3.eprime | 41 - .../model_2_4-solution000001.solution | 4 - .../model_2_4-solution000002.solution | 4 - .../model_2_4-solution000003.solution | 4 - .../expected/model_2_4.eprime | 42 - .../model_3_1-solution000001.solution | 4 - .../model_3_1-solution000002.solution | 4 - .../model_3_1-solution000003.solution | 4 - .../expected/model_3_1.eprime | 35 - .../model_3_2-solution000001.solution | 4 - .../model_3_2-solution000002.solution | 4 - .../model_3_2-solution000003.solution | 4 - .../expected/model_3_2.eprime | 42 - .../model_3_3-solution000001.solution | 4 - .../model_3_3-solution000002.solution | 4 - .../model_3_3-solution000003.solution | 4 - .../expected/model_3_3.eprime | 28 - .../model_3_4-solution000001.solution | 4 - .../model_3_4-solution000002.solution | 4 - .../model_3_4-solution000003.solution | 4 - .../expected/model_3_4.eprime | 45 - .../model_4_1-solution000001.solution | 4 - .../model_4_1-solution000002.solution | 4 - .../model_4_1-solution000003.solution | 4 - .../expected/model_4_1.eprime | 35 - .../model_4_2-solution000001.solution | 4 - .../model_4_2-solution000002.solution | 4 - .../model_4_2-solution000003.solution | 4 - .../expected/model_4_2.eprime | 43 - .../model_4_3-solution000001.solution | 4 - .../model_4_3-solution000002.solution | 4 - .../model_4_3-solution000003.solution | 4 - .../expected/model_4_3.eprime | 45 - .../model_4_4-solution000001.solution | 4 - .../model_4_4-solution000002.solution | 4 - .../model_4_4-solution000003.solution | 4 - .../expected/model_4_4.eprime | 29 - .../expected/model-solution000001.solution | 3 - .../expected/model-solution000002.solution | 3 - .../expected/model-solution000003.solution | 3 - .../expected/model-solution000004.solution | 3 - .../expected/model-solution000005.solution | 3 - .../expected/model-solution000006.solution | 3 - .../expected/model-solution000007.solution | 3 - .../expected/model-solution000008.solution | 3 - .../expected/model-solution000009.solution | 3 - .../expected/model-solution000010.solution | 3 - .../expected/model-solution000011.solution | 3 - .../expected/model-solution000012.solution | 3 - .../function_range/expected/model.eprime | 12 - .../model_1_1-solution000001.solution | 3 - .../model_1_1-solution000002.solution | 7 - .../model_1_1-solution000003.solution | 7 - .../model_1_1-solution000004.solution | 7 - .../expected/model_1_1.eprime | 6 - .../model_1_2-solution000001.solution | 7 - .../model_1_2-solution000002.solution | 7 - .../model_1_2-solution000003.solution | 7 - .../model_1_2-solution000004.solution | 3 - .../expected/model_1_2.eprime | 22 - .../model_1_3-solution000001.solution | 3 - .../model_1_3-solution000002.solution | 7 - .../model_1_3-solution000003.solution | 7 - .../model_1_3-solution000004.solution | 7 - .../expected/model_1_3.eprime | 25 - .../model_1_4-solution000001.solution | 3 - .../model_1_4-solution000002.solution | 7 - .../model_1_4-solution000003.solution | 7 - .../model_1_4-solution000004.solution | 7 - .../expected/model_1_4.eprime | 27 - .../model_2_1-solution000001.solution | 3 - .../model_2_1-solution000002.solution | 7 - .../model_2_1-solution000003.solution | 7 - .../model_2_1-solution000004.solution | 7 - .../expected/model_2_1.eprime | 23 - .../model_2_2-solution000001.solution | 7 - .../model_2_2-solution000002.solution | 7 - .../model_2_2-solution000003.solution | 7 - .../model_2_2-solution000004.solution | 3 - .../expected/model_2_2.eprime | 14 - .../model_2_3-solution000001.solution | 3 - .../model_2_3-solution000002.solution | 7 - .../model_2_3-solution000003.solution | 7 - .../model_2_3-solution000004.solution | 7 - .../expected/model_2_3.eprime | 35 - .../model_2_4-solution000001.solution | 3 - .../model_2_4-solution000002.solution | 7 - .../model_2_4-solution000003.solution | 7 - .../model_2_4-solution000004.solution | 7 - .../expected/model_2_4.eprime | 38 - .../model_3_1-solution000001.solution | 3 - .../model_3_1-solution000002.solution | 7 - .../model_3_1-solution000003.solution | 7 - .../model_3_1-solution000004.solution | 7 - .../expected/model_3_1.eprime | 26 - .../model_3_2-solution000001.solution | 7 - .../model_3_2-solution000002.solution | 7 - .../model_3_2-solution000003.solution | 7 - .../model_3_2-solution000004.solution | 3 - .../expected/model_3_2.eprime | 35 - .../model_3_3-solution000001.solution | 3 - .../model_3_3-solution000002.solution | 7 - .../model_3_3-solution000003.solution | 7 - .../model_3_3-solution000004.solution | 7 - .../expected/model_3_3.eprime | 16 - .../model_3_4-solution000001.solution | 3 - .../model_3_4-solution000002.solution | 7 - .../model_3_4-solution000003.solution | 7 - .../model_3_4-solution000004.solution | 7 - .../expected/model_3_4.eprime | 42 - .../model_4_1-solution000001.solution | 3 - .../model_4_1-solution000002.solution | 7 - .../model_4_1-solution000003.solution | 7 - .../model_4_1-solution000004.solution | 7 - .../expected/model_4_1.eprime | 28 - .../model_4_2-solution000001.solution | 7 - .../model_4_2-solution000002.solution | 7 - .../model_4_2-solution000003.solution | 7 - .../model_4_2-solution000004.solution | 3 - .../expected/model_4_2.eprime | 38 - .../model_4_3-solution000001.solution | 3 - .../model_4_3-solution000002.solution | 7 - .../model_4_3-solution000003.solution | 7 - .../model_4_3-solution000004.solution | 7 - .../expected/model_4_3.eprime | 42 - .../model_4_4-solution000001.solution | 3 - .../model_4_4-solution000002.solution | 7 - .../model_4_4-solution000003.solution | 7 - .../model_4_4-solution000004.solution | 7 - .../expected/model_4_4.eprime | 19 - .../model_1_1-solution000001.solution | 13 - .../expected/model_1_1.eprime | 8 - .../model_1_2-solution000001.solution | 13 - .../expected/model_1_2.eprime | 30 - .../model_1_3-solution000001.solution | 13 - .../expected/model_1_3.eprime | 31 - .../model_1_4-solution000001.solution | 13 - .../expected/model_1_4.eprime | 37 - .../model_2_1-solution000001.solution | 13 - .../expected/model_2_1.eprime | 31 - .../model_2_2-solution000001.solution | 13 - .../expected/model_2_2.eprime | 19 - .../model_2_3-solution000001.solution | 13 - .../expected/model_2_3.eprime | 45 - .../model_2_4-solution000001.solution | 13 - .../expected/model_2_4.eprime | 50 - .../model_3_1-solution000001.solution | 13 - .../expected/model_3_1.eprime | 32 - .../model_3_2-solution000001.solution | 13 - .../expected/model_3_2.eprime | 44 - .../model_3_3-solution000001.solution | 13 - .../expected/model_3_3.eprime | 19 - .../model_3_4-solution000001.solution | 13 - .../expected/model_3_4.eprime | 54 - .../model_4_1-solution000001.solution | 13 - .../expected/model_4_1.eprime | 38 - .../model_4_2-solution000001.solution | 13 - .../expected/model_4_2.eprime | 50 - .../model_4_3-solution000001.solution | 13 - .../expected/model_4_3.eprime | 55 - .../model_4_4-solution000001.solution | 13 - .../expected/model_4_4.eprime | 25 - .../model_1_1_1_1-solution000001.solution | 4 - .../expected/model_1_1_1_1.eprime | 11 - .../model_1_1_1_2-solution000001.solution | 4 - .../expected/model_1_1_1_2.eprime | 14 - .../model_1_1_2_1-solution000001.solution | 4 - .../expected/model_1_1_2_1.eprime | 14 - .../model_1_1_2_2-solution000001.solution | 4 - .../expected/model_1_1_2_2.eprime | 17 - .../model_1_2_1_1-solution000001.solution | 4 - .../expected/model_1_2_1_1.eprime | 14 - .../model_1_2_1_2-solution000001.solution | 4 - .../expected/model_1_2_1_2.eprime | 10 - .../model_1_2_2_1-solution000001.solution | 4 - .../expected/model_1_2_2_1.eprime | 17 - .../model_1_2_2_2-solution000001.solution | 4 - .../expected/model_1_2_2_2.eprime | 13 - .../model_2_1_1_1-solution000001.solution | 4 - .../expected/model_2_1_1_1.eprime | 14 - .../model_2_1_1_2-solution000001.solution | 4 - .../expected/model_2_1_1_2.eprime | 17 - .../model_2_1_2_1-solution000001.solution | 4 - .../expected/model_2_1_2_1.eprime | 10 - .../model_2_1_2_2-solution000001.solution | 4 - .../expected/model_2_1_2_2.eprime | 13 - .../model_2_2_1_1-solution000001.solution | 4 - .../expected/model_2_2_1_1.eprime | 17 - .../model_2_2_1_2-solution000001.solution | 4 - .../expected/model_2_2_1_2.eprime | 13 - .../model_2_2_2_1-solution000001.solution | 4 - .../expected/model_2_2_2_1.eprime | 13 - .../model_2_2_2_2-solution000001.solution | 4 - .../expected/model_2_2_2_2.eprime | 9 - .../model_1_1_1_1-solution000001.solution | 4 - .../expected/model_1_1_1_1.eprime | 11 - .../model_1_1_1_2-solution000001.solution | 4 - .../expected/model_1_1_1_2.eprime | 14 - .../model_1_1_2_1-solution000001.solution | 4 - .../expected/model_1_1_2_1.eprime | 14 - .../model_1_1_2_2-solution000001.solution | 4 - .../expected/model_1_1_2_2.eprime | 17 - .../model_1_2_1_1-solution000001.solution | 4 - .../expected/model_1_2_1_1.eprime | 14 - .../model_1_2_1_2-solution000001.solution | 4 - .../expected/model_1_2_1_2.eprime | 10 - .../model_1_2_2_1-solution000001.solution | 4 - .../expected/model_1_2_2_1.eprime | 17 - .../model_1_2_2_2-solution000001.solution | 4 - .../expected/model_1_2_2_2.eprime | 13 - .../model_2_1_1_1-solution000001.solution | 4 - .../expected/model_2_1_1_1.eprime | 14 - .../model_2_1_1_2-solution000001.solution | 4 - .../expected/model_2_1_1_2.eprime | 17 - .../model_2_1_2_1-solution000001.solution | 4 - .../expected/model_2_1_2_1.eprime | 10 - .../model_2_1_2_2-solution000001.solution | 4 - .../expected/model_2_1_2_2.eprime | 13 - .../model_2_2_1_1-solution000001.solution | 4 - .../expected/model_2_2_1_1.eprime | 17 - .../model_2_2_1_2-solution000001.solution | 4 - .../expected/model_2_2_1_2.eprime | 13 - .../model_2_2_2_1-solution000001.solution | 4 - .../expected/model_2_2_2_1.eprime | 13 - .../model_2_2_2_2-solution000001.solution | 4 - .../expected/model_2_2_2_2.eprime | 9 - .../model_1_1-param1-solution000001.solution | 3 - .../expected/model_1_1-param1.eprime-param | 5 - .../model_1_1-param4-solution000001.solution | 3 - .../expected/model_1_1-param4.eprime-param | 5 - .../model_1_1-param7-solution000001.solution | 3 - .../expected/model_1_1-param7.eprime-param | 5 - .../mset01_param/expected/model_1_1.eprime | 31 - .../model_1_2-param1-solution000001.solution | 3 - .../expected/model_1_2-param1.eprime-param | 5 - .../model_1_2-param4-solution000001.solution | 3 - .../expected/model_1_2-param4.eprime-param | 5 - .../model_1_2-param7-solution000001.solution | 3 - .../expected/model_1_2-param7.eprime-param | 5 - .../mset01_param/expected/model_1_2.eprime | 64 - .../model_1_3-param1-solution000001.solution | 3 - .../expected/model_1_3-param1.eprime-param | 5 - .../model_1_3-param4-solution000001.solution | 3 - .../expected/model_1_3-param4.eprime-param | 5 - .../model_1_3-param7-solution000001.solution | 3 - .../expected/model_1_3-param7.eprime-param | 5 - .../mset01_param/expected/model_1_3.eprime | 44 - .../model_2_1-param1-solution000001.solution | 3 - .../expected/model_2_1-param1.eprime-param | 5 - .../model_2_1-param4-solution000001.solution | 3 - .../expected/model_2_1-param4.eprime-param | 5 - .../model_2_1-param7-solution000001.solution | 3 - .../expected/model_2_1-param7.eprime-param | 5 - .../mset01_param/expected/model_2_1.eprime | 64 - .../model_2_2-param1-solution000001.solution | 3 - .../expected/model_2_2-param1.eprime-param | 5 - .../model_2_2-param4-solution000001.solution | 3 - .../expected/model_2_2-param4.eprime-param | 5 - .../model_2_2-param7-solution000001.solution | 3 - .../expected/model_2_2-param7.eprime-param | 5 - .../mset01_param/expected/model_2_2.eprime | 37 - .../model_2_3-param1-solution000001.solution | 3 - .../expected/model_2_3-param1.eprime-param | 5 - .../model_2_3-param4-solution000001.solution | 3 - .../expected/model_2_3-param4.eprime-param | 5 - .../model_2_3-param7-solution000001.solution | 3 - .../expected/model_2_3-param7.eprime-param | 5 - .../mset01_param/expected/model_2_3.eprime | 51 - .../model_3_1-param1-solution000001.solution | 3 - .../expected/model_3_1-param1.eprime-param | 5 - .../model_3_1-param4-solution000001.solution | 3 - .../expected/model_3_1-param4.eprime-param | 5 - .../model_3_1-param7-solution000001.solution | 3 - .../expected/model_3_1-param7.eprime-param | 5 - .../mset01_param/expected/model_3_1.eprime | 36 - .../model_3_2-param1-solution000001.solution | 3 - .../expected/model_3_2-param1.eprime-param | 5 - .../model_3_2-param4-solution000001.solution | 3 - .../expected/model_3_2-param4.eprime-param | 5 - .../model_3_2-param7-solution000001.solution | 3 - .../expected/model_3_2-param7.eprime-param | 5 - .../mset01_param/expected/model_3_2.eprime | 43 - .../model_3_3-param1-solution000001.solution | 3 - .../expected/model_3_3-param1.eprime-param | 5 - .../model_3_3-param4-solution000001.solution | 3 - .../expected/model_3_3-param4.eprime-param | 5 - .../model_3_3-param7-solution000001.solution | 3 - .../expected/model_3_3-param7.eprime-param | 5 - .../mset01_param/expected/model_3_3.eprime | 18 - .../model_1_1-solution000001.solution | 4 - .../model_1_1-solution000002.solution | 4 - .../name-reuse/expected/model_1_1.eprime | 13 - .../model_1_2-solution000001.solution | 4 - .../model_1_2-solution000002.solution | 4 - .../name-reuse/expected/model_1_2.eprime | 22 - .../model_1_3-solution000001.solution | 4 - .../model_1_3-solution000002.solution | 4 - .../name-reuse/expected/model_1_3.eprime | 25 - .../model_1_4-solution000001.solution | 4 - .../model_1_4-solution000002.solution | 4 - .../name-reuse/expected/model_1_4.eprime | 25 - .../model_2_1-solution000001.solution | 4 - .../model_2_1-solution000002.solution | 4 - .../name-reuse/expected/model_2_1.eprime | 22 - .../model_2_2-solution000001.solution | 4 - .../model_2_2-solution000002.solution | 4 - .../name-reuse/expected/model_2_2.eprime | 17 - .../model_2_3-solution000001.solution | 4 - .../model_2_3-solution000002.solution | 4 - .../name-reuse/expected/model_2_3.eprime | 34 - .../model_2_4-solution000001.solution | 4 - .../model_2_4-solution000002.solution | 4 - .../name-reuse/expected/model_2_4.eprime | 35 - .../model_3_1-solution000001.solution | 4 - .../model_3_1-solution000002.solution | 4 - .../name-reuse/expected/model_3_1.eprime | 27 - .../model_3_2-solution000001.solution | 4 - .../model_3_2-solution000002.solution | 4 - .../name-reuse/expected/model_3_2.eprime | 36 - .../model_3_3-solution000001.solution | 4 - .../model_3_3-solution000002.solution | 4 - .../name-reuse/expected/model_3_3.eprime | 21 - .../model_3_4-solution000001.solution | 4 - .../model_3_4-solution000002.solution | 4 - .../name-reuse/expected/model_3_4.eprime | 40 - .../model_4_1-solution000001.solution | 4 - .../model_4_1-solution000002.solution | 4 - .../name-reuse/expected/model_4_1.eprime | 28 - .../model_4_2-solution000001.solution | 4 - .../model_4_2-solution000002.solution | 4 - .../name-reuse/expected/model_4_2.eprime | 37 - .../model_4_3-solution000001.solution | 4 - .../model_4_3-solution000002.solution | 4 - .../name-reuse/expected/model_4_3.eprime | 40 - .../model_4_4-solution000001.solution | 4 - .../model_4_4-solution000002.solution | 4 - .../name-reuse/expected/model_4_4.eprime | 21 - .../expected/model_1-solution000001.solution | 7 - .../partition_05_1/expected/model_1.eprime | 48 - .../expected/model_2-solution000001.solution | 7 - .../partition_05_1/expected/model_2.eprime | 83 -- .../expected/model_3-solution000001.solution | 7 - .../partition_05_1/expected/model_3.eprime | 90 -- .../expected/model_4-solution000001.solution | 7 - .../partition_05_1/expected/model_4.eprime | 40 - .../expected/model_1-solution000001.solution | 7 - .../partition_05_2/expected/model_1.eprime | 78 -- .../expected/model_2-solution000001.solution | 7 - .../partition_05_2/expected/model_2.eprime | 116 -- .../expected/model_3-solution000001.solution | 7 - .../partition_05_2/expected/model_3.eprime | 123 -- .../expected/model_4-solution000001.solution | 7 - .../partition_05_2/expected/model_4.eprime | 61 - .../model_1_1-solution000001.solution | 7 - .../model_1_1-solution000002.solution | 7 - .../model_1_1-solution000003.solution | 7 - .../partition_06/expected/model_1_1.eprime | 37 - .../model_1_2-solution000001.solution | 7 - .../model_1_2-solution000002.solution | 7 - .../model_1_2-solution000003.solution | 7 - .../partition_06/expected/model_1_2.eprime | 116 -- .../model_1_3-solution000001.solution | 7 - .../model_1_3-solution000002.solution | 7 - .../model_1_3-solution000003.solution | 7 - .../partition_06/expected/model_1_3.eprime | 130 -- .../model_1_4-solution000001.solution | 7 - .../model_1_4-solution000002.solution | 7 - .../model_1_4-solution000003.solution | 7 - .../partition_06/expected/model_1_4.eprime | 85 -- .../model_2_1-solution000001.solution | 7 - .../model_2_1-solution000002.solution | 7 - .../model_2_1-solution000003.solution | 7 - .../partition_06/expected/model_2_1.eprime | 117 -- .../model_2_2-solution000001.solution | 7 - .../model_2_2-solution000002.solution | 7 - .../model_2_2-solution000003.solution | 7 - .../partition_06/expected/model_2_2.eprime | 60 - .../model_2_3-solution000001.solution | 7 - .../model_2_3-solution000002.solution | 7 - .../model_2_3-solution000003.solution | 7 - .../partition_06/expected/model_2_3.eprime | 157 --- .../model_2_4-solution000001.solution | 7 - .../model_2_4-solution000002.solution | 7 - .../model_2_4-solution000003.solution | 7 - .../partition_06/expected/model_2_4.eprime | 116 -- .../model_3_1-solution000001.solution | 7 - .../model_3_1-solution000002.solution | 7 - .../model_3_1-solution000003.solution | 7 - .../partition_06/expected/model_3_1.eprime | 130 -- .../model_3_2-solution000001.solution | 7 - .../model_3_2-solution000002.solution | 7 - .../model_3_2-solution000003.solution | 7 - .../partition_06/expected/model_3_2.eprime | 156 --- .../model_3_3-solution000001.solution | 7 - .../model_3_3-solution000002.solution | 7 - .../model_3_3-solution000003.solution | 7 - .../partition_06/expected/model_3_3.eprime | 69 - .../model_3_4-solution000001.solution | 7 - .../model_3_4-solution000002.solution | 7 - .../model_3_4-solution000003.solution | 7 - .../partition_06/expected/model_3_4.eprime | 129 -- .../model_4_1-solution000001.solution | 7 - .../model_4_1-solution000002.solution | 7 - .../model_4_1-solution000003.solution | 7 - .../partition_06/expected/model_4_1.eprime | 82 -- .../model_4_2-solution000001.solution | 7 - .../model_4_2-solution000002.solution | 7 - .../model_4_2-solution000003.solution | 7 - .../partition_06/expected/model_4_2.eprime | 112 -- .../model_4_3-solution000001.solution | 7 - .../model_4_3-solution000002.solution | 7 - .../model_4_3-solution000003.solution | 7 - .../partition_06/expected/model_4_3.eprime | 127 -- .../model_4_4-solution000001.solution | 7 - .../model_4_4-solution000002.solution | 7 - .../model_4_4-solution000003.solution | 7 - .../partition_06/expected/model_4_4.eprime | 32 - .../model_1_1-p-solution000001.solution | 3 - .../model_1_1-p-solution000002.solution | 3 - .../model_1_1-p-solution000003.solution | 3 - .../model_1_1-p-solution000004.solution | 3 - .../model_1_1-p-solution000005.solution | 3 - .../model_1_1-p-solution000006.solution | 3 - .../expected/model_1_1-p.eprime-param | 5 - .../expected/model_1_1.eprime | 20 - .../model_1_2-p-solution000001.solution | 3 - .../model_1_2-p-solution000002.solution | 3 - .../model_1_2-p-solution000003.solution | 3 - .../model_1_2-p-solution000004.solution | 3 - .../model_1_2-p-solution000005.solution | 3 - .../model_1_2-p-solution000006.solution | 3 - .../expected/model_1_2-p.eprime-param | 5 - .../expected/model_1_2.eprime | 32 - .../model_1_3-p-solution000001.solution | 3 - .../model_1_3-p-solution000002.solution | 3 - .../model_1_3-p-solution000003.solution | 3 - .../model_1_3-p-solution000004.solution | 3 - .../model_1_3-p-solution000005.solution | 3 - .../model_1_3-p-solution000006.solution | 3 - .../expected/model_1_3-p.eprime-param | 5 - .../expected/model_1_3.eprime | 34 - .../model_1_4-p-solution000001.solution | 3 - .../model_1_4-p-solution000002.solution | 3 - .../model_1_4-p-solution000003.solution | 3 - .../model_1_4-p-solution000004.solution | 3 - .../model_1_4-p-solution000005.solution | 3 - .../model_1_4-p-solution000006.solution | 3 - .../expected/model_1_4-p.eprime-param | 5 - .../expected/model_1_4.eprime | 36 - .../model_2_1-p-solution000001.solution | 3 - .../model_2_1-p-solution000002.solution | 3 - .../model_2_1-p-solution000003.solution | 3 - .../model_2_1-p-solution000004.solution | 3 - .../model_2_1-p-solution000005.solution | 3 - .../model_2_1-p-solution000006.solution | 3 - .../expected/model_2_1-p.eprime-param | 5 - .../expected/model_2_1.eprime | 33 - .../model_2_2-p-solution000001.solution | 3 - .../model_2_2-p-solution000002.solution | 3 - .../model_2_2-p-solution000003.solution | 3 - .../model_2_2-p-solution000004.solution | 3 - .../model_2_2-p-solution000005.solution | 3 - .../model_2_2-p-solution000006.solution | 3 - .../expected/model_2_2-p.eprime-param | 5 - .../expected/model_2_2.eprime | 26 - .../model_2_3-p-solution000001.solution | 3 - .../model_2_3-p-solution000002.solution | 3 - .../model_2_3-p-solution000003.solution | 3 - .../model_2_3-p-solution000004.solution | 3 - .../model_2_3-p-solution000005.solution | 3 - .../model_2_3-p-solution000006.solution | 3 - .../expected/model_2_3-p.eprime-param | 5 - .../expected/model_2_3.eprime | 44 - .../model_2_4-p-solution000001.solution | 3 - .../model_2_4-p-solution000002.solution | 3 - .../model_2_4-p-solution000003.solution | 3 - .../model_2_4-p-solution000004.solution | 3 - .../model_2_4-p-solution000005.solution | 3 - .../model_2_4-p-solution000006.solution | 3 - .../expected/model_2_4-p.eprime-param | 5 - .../expected/model_2_4.eprime | 46 - .../model_3_1-p-solution000001.solution | 3 - .../model_3_1-p-solution000002.solution | 3 - .../model_3_1-p-solution000003.solution | 3 - .../model_3_1-p-solution000004.solution | 3 - .../model_3_1-p-solution000005.solution | 3 - .../model_3_1-p-solution000006.solution | 3 - .../expected/model_3_1-p.eprime-param | 5 - .../expected/model_3_1.eprime | 36 - .../model_3_2-p-solution000001.solution | 3 - .../model_3_2-p-solution000002.solution | 3 - .../model_3_2-p-solution000003.solution | 3 - .../model_3_2-p-solution000004.solution | 3 - .../model_3_2-p-solution000005.solution | 3 - .../model_3_2-p-solution000006.solution | 3 - .../expected/model_3_2-p.eprime-param | 5 - .../expected/model_3_2.eprime | 44 - .../model_3_3-p-solution000001.solution | 3 - .../model_3_3-p-solution000002.solution | 3 - .../model_3_3-p-solution000003.solution | 3 - .../model_3_3-p-solution000004.solution | 3 - .../model_3_3-p-solution000005.solution | 3 - .../model_3_3-p-solution000006.solution | 3 - .../expected/model_3_3-p.eprime-param | 5 - .../expected/model_3_3.eprime | 28 - .../model_3_4-p-solution000001.solution | 3 - .../model_3_4-p-solution000002.solution | 3 - .../model_3_4-p-solution000003.solution | 3 - .../model_3_4-p-solution000004.solution | 3 - .../model_3_4-p-solution000005.solution | 3 - .../model_3_4-p-solution000006.solution | 3 - .../expected/model_3_4-p.eprime-param | 5 - .../expected/model_3_4.eprime | 50 - .../model_4_1-p-solution000001.solution | 3 - .../model_4_1-p-solution000002.solution | 3 - .../model_4_1-p-solution000003.solution | 3 - .../model_4_1-p-solution000004.solution | 3 - .../model_4_1-p-solution000005.solution | 3 - .../model_4_1-p-solution000006.solution | 3 - .../expected/model_4_1-p.eprime-param | 5 - .../expected/model_4_1.eprime | 38 - .../model_4_2-p-solution000001.solution | 3 - .../model_4_2-p-solution000002.solution | 3 - .../model_4_2-p-solution000003.solution | 3 - .../model_4_2-p-solution000004.solution | 3 - .../model_4_2-p-solution000005.solution | 3 - .../model_4_2-p-solution000006.solution | 3 - .../expected/model_4_2-p.eprime-param | 5 - .../expected/model_4_2.eprime | 46 - .../model_4_3-p-solution000001.solution | 3 - .../model_4_3-p-solution000002.solution | 3 - .../model_4_3-p-solution000003.solution | 3 - .../model_4_3-p-solution000004.solution | 3 - .../model_4_3-p-solution000005.solution | 3 - .../model_4_3-p-solution000006.solution | 3 - .../expected/model_4_3-p.eprime-param | 5 - .../expected/model_4_3.eprime | 50 - .../model_4_4-p-solution000001.solution | 3 - .../model_4_4-p-solution000002.solution | 3 - .../model_4_4-p-solution000003.solution | 3 - .../model_4_4-p-solution000004.solution | 3 - .../model_4_4-p-solution000005.solution | 3 - .../model_4_4-p-solution000006.solution | 3 - .../expected/model_4_4-p.eprime-param | 5 - .../expected/model_4_4.eprime | 30 - .../model_1_1-solution000001.solution | 3 - .../expected/model_1_1.eprime | 8 - .../model_1_2-solution000001.solution | 3 - .../expected/model_1_2.eprime | 17 - .../model_1_3-solution000001.solution | 3 - .../expected/model_1_3.eprime | 20 - .../model_1_4-solution000001.solution | 3 - .../expected/model_1_4.eprime | 20 - .../model_2_1-solution000001.solution | 3 - .../expected/model_2_1.eprime | 19 - .../model_2_2-solution000001.solution | 3 - .../expected/model_2_2.eprime | 13 - .../model_2_3-solution000001.solution | 3 - .../expected/model_2_3.eprime | 30 - .../model_2_4-solution000001.solution | 3 - .../expected/model_2_4.eprime | 31 - .../model_3_1-solution000001.solution | 3 - .../expected/model_3_1.eprime | 22 - .../model_3_2-solution000001.solution | 3 - .../expected/model_3_2.eprime | 30 - .../model_3_3-solution000001.solution | 3 - .../expected/model_3_3.eprime | 15 - .../model_3_4-solution000001.solution | 3 - .../expected/model_3_4.eprime | 35 - .../model_4_1-solution000001.solution | 3 - .../expected/model_4_1.eprime | 23 - .../model_4_2-solution000001.solution | 3 - .../expected/model_4_2.eprime | 31 - .../model_4_3-solution000001.solution | 3 - .../expected/model_4_3.eprime | 35 - .../model_4_4-solution000001.solution | 3 - .../expected/model_4_4.eprime | 16 - .../model_1_1-param4-solution000001.solution | 3 - .../expected/model_1_1-param4.eprime-param | 11 - .../expected/model_1_1.eprime | 70 - .../model_1_2-param4-solution000001.solution | 3 - .../expected/model_1_2-param4.eprime-param | 11 - .../expected/model_1_2.eprime | 152 -- .../model_1_3-param4-solution000001.solution | 3 - .../expected/model_1_3-param4.eprime-param | 11 - .../expected/model_1_3.eprime | 178 --- .../model_1_4-param4-solution000001.solution | 3 - .../expected/model_1_4-param4.eprime-param | 11 - .../expected/model_1_4.eprime | 184 --- .../model_2_1-param4-solution000001.solution | 3 - .../expected/model_2_1-param4.eprime-param | 11 - .../expected/model_2_1.eprime | 164 --- .../model_2_2-param4-solution000001.solution | 3 - .../expected/model_2_2-param4.eprime-param | 11 - .../expected/model_2_2.eprime | 91 -- .../model_2_3-param4-solution000001.solution | 3 - .../expected/model_2_3-param4.eprime-param | 11 - .../expected/model_2_3.eprime | 206 --- .../model_2_4-param4-solution000001.solution | 3 - .../expected/model_2_4-param4.eprime-param | 11 - .../expected/model_2_4.eprime | 211 --- .../model_3_1-param4-solution000001.solution | 3 - .../expected/model_3_1-param4.eprime-param | 11 - .../expected/model_3_1.eprime | 198 --- .../model_3_2-param4-solution000001.solution | 3 - .../expected/model_3_2-param4.eprime-param | 11 - .../expected/model_3_2.eprime | 213 --- .../model_3_3-param4-solution000001.solution | 3 - .../expected/model_3_3-param4.eprime-param | 11 - .../expected/model_3_3.eprime | 115 -- .../model_3_4-param4-solution000001.solution | 3 - .../expected/model_3_4-param4.eprime-param | 11 - .../expected/model_3_4.eprime | 247 ---- .../model_4_1-param4-solution000001.solution | 3 - .../expected/model_4_1-param4.eprime-param | 11 - .../expected/model_4_1.eprime | 202 --- .../model_4_2-param4-solution000001.solution | 3 - .../expected/model_4_2-param4.eprime-param | 11 - .../expected/model_4_2.eprime | 217 --- .../model_4_3-param4-solution000001.solution | 3 - .../expected/model_4_3-param4.eprime-param | 11 - .../expected/model_4_3.eprime | 246 ---- .../model_4_4-param4-solution000001.solution | 3 - .../expected/model_4_4-param4.eprime-param | 11 - .../expected/model_4_4.eprime | 121 -- .../model_1_1-solution000001.solution | 3 - .../model_1_1-solution000002.solution | 3 - .../basic/set03/expected/model_1_1.eprime | 8 - .../model_1_2-solution000001.solution | 3 - .../model_1_2-solution000002.solution | 3 - .../basic/set03/expected/model_1_2.eprime | 16 - .../model_1_3-solution000001.solution | 3 - .../model_1_3-solution000002.solution | 3 - .../basic/set03/expected/model_1_3.eprime | 19 - .../model_1_4-solution000001.solution | 3 - .../model_1_4-solution000002.solution | 3 - .../basic/set03/expected/model_1_4.eprime | 18 - .../model_2_1-solution000001.solution | 3 - .../model_2_1-solution000002.solution | 3 - .../basic/set03/expected/model_2_1.eprime | 16 - .../model_2_2-solution000001.solution | 3 - .../model_2_2-solution000002.solution | 3 - .../basic/set03/expected/model_2_2.eprime | 10 - .../model_2_3-solution000001.solution | 3 - .../model_2_3-solution000002.solution | 3 - .../basic/set03/expected/model_2_3.eprime | 26 - .../model_2_4-solution000001.solution | 3 - .../model_2_4-solution000002.solution | 3 - .../basic/set03/expected/model_2_4.eprime | 26 - .../model_3_1-solution000001.solution | 3 - .../model_3_1-solution000002.solution | 3 - .../basic/set03/expected/model_3_1.eprime | 19 - .../model_3_2-solution000001.solution | 3 - .../model_3_2-solution000002.solution | 3 - .../basic/set03/expected/model_3_2.eprime | 26 - .../model_3_3-solution000001.solution | 3 - .../model_3_3-solution000002.solution | 3 - .../basic/set03/expected/model_3_3.eprime | 12 - .../model_3_4-solution000001.solution | 3 - .../model_3_4-solution000002.solution | 3 - .../basic/set03/expected/model_3_4.eprime | 30 - .../model_4_1-solution000001.solution | 3 - .../model_4_1-solution000002.solution | 3 - .../basic/set03/expected/model_4_1.eprime | 19 - .../model_4_2-solution000001.solution | 3 - .../model_4_2-solution000002.solution | 3 - .../basic/set03/expected/model_4_2.eprime | 26 - .../model_4_3-solution000001.solution | 3 - .../model_4_3-solution000002.solution | 3 - .../basic/set03/expected/model_4_3.eprime | 30 - .../model_4_4-solution000001.solution | 3 - .../model_4_4-solution000002.solution | 3 - .../basic/set03/expected/model_4_4.eprime | 12 - .../model_1_1_1-solution000001.solution | 3 - .../model_1_1_1-solution000002.solution | 3 - .../basic/set04/expected/model_1_1_1.eprime | 9 - .../model_1_1_2-solution000001.solution | 3 - .../model_1_1_2-solution000002.solution | 3 - .../basic/set04/expected/model_1_1_2.eprime | 18 - .../model_1_1_3-solution000001.solution | 3 - .../model_1_1_3-solution000002.solution | 3 - .../basic/set04/expected/model_1_1_3.eprime | 21 - .../model_1_1_4-solution000001.solution | 3 - .../model_1_1_4-solution000002.solution | 3 - .../basic/set04/expected/model_1_1_4.eprime | 21 - .../model_1_2_1-solution000001.solution | 3 - .../model_1_2_1-solution000002.solution | 3 - .../basic/set04/expected/model_1_2_1.eprime | 18 - .../model_1_2_2-solution000001.solution | 3 - .../model_1_2_2-solution000002.solution | 3 - .../basic/set04/expected/model_1_2_2.eprime | 18 - .../model_1_2_3-solution000001.solution | 3 - .../model_1_2_3-solution000002.solution | 3 - .../basic/set04/expected/model_1_2_3.eprime | 42 - .../model_1_2_4-solution000001.solution | 3 - .../model_1_2_4-solution000002.solution | 3 - .../basic/set04/expected/model_1_2_4.eprime | 43 - .../model_1_3_1-solution000001.solution | 3 - .../model_1_3_1-solution000002.solution | 3 - .../basic/set04/expected/model_1_3_1.eprime | 21 - .../model_1_3_2-solution000001.solution | 3 - .../model_1_3_2-solution000002.solution | 3 - .../basic/set04/expected/model_1_3_2.eprime | 41 - .../model_1_3_3-solution000001.solution | 3 - .../model_1_3_3-solution000002.solution | 3 - .../basic/set04/expected/model_1_3_3.eprime | 21 - .../model_1_3_4-solution000001.solution | 3 - .../model_1_3_4-solution000002.solution | 3 - .../basic/set04/expected/model_1_3_4.eprime | 47 - .../model_1_4_1-solution000001.solution | 3 - .../model_1_4_1-solution000002.solution | 3 - .../basic/set04/expected/model_1_4_1.eprime | 21 - .../model_1_4_2-solution000001.solution | 3 - .../model_1_4_2-solution000002.solution | 3 - .../basic/set04/expected/model_1_4_2.eprime | 41 - .../model_1_4_3-solution000001.solution | 3 - .../model_1_4_3-solution000002.solution | 3 - .../basic/set04/expected/model_1_4_3.eprime | 46 - .../model_1_4_4-solution000001.solution | 3 - .../model_1_4_4-solution000002.solution | 3 - .../basic/set04/expected/model_1_4_4.eprime | 21 - .../model_2_1_1-solution000001.solution | 3 - .../model_2_1_1-solution000002.solution | 3 - .../basic/set04/expected/model_2_1_1.eprime | 18 - .../model_2_1_2-solution000001.solution | 3 - .../model_2_1_2-solution000002.solution | 3 - .../basic/set04/expected/model_2_1_2.eprime | 18 - .../model_2_1_3-solution000001.solution | 3 - .../model_2_1_3-solution000002.solution | 3 - .../basic/set04/expected/model_2_1_3.eprime | 42 - .../model_2_1_4-solution000001.solution | 3 - .../model_2_1_4-solution000002.solution | 3 - .../basic/set04/expected/model_2_1_4.eprime | 42 - .../model_2_2_1-solution000001.solution | 3 - .../model_2_2_1-solution000002.solution | 3 - .../basic/set04/expected/model_2_2_1.eprime | 18 - .../model_2_2_2-solution000001.solution | 3 - .../model_2_2_2-solution000002.solution | 3 - .../basic/set04/expected/model_2_2_2.eprime | 12 - .../model_2_2_3-solution000001.solution | 3 - .../model_2_2_3-solution000002.solution | 3 - .../basic/set04/expected/model_2_2_3.eprime | 29 - .../model_2_2_4-solution000001.solution | 3 - .../model_2_2_4-solution000002.solution | 3 - .../basic/set04/expected/model_2_2_4.eprime | 30 - .../model_2_3_1-solution000001.solution | 3 - .../model_2_3_1-solution000002.solution | 3 - .../basic/set04/expected/model_2_3_1.eprime | 42 - .../model_2_3_2-solution000001.solution | 3 - .../model_2_3_2-solution000002.solution | 3 - .../basic/set04/expected/model_2_3_2.eprime | 29 - .../model_2_3_3-solution000001.solution | 3 - .../model_2_3_3-solution000002.solution | 3 - .../basic/set04/expected/model_2_3_3.eprime | 29 - .../model_2_3_4-solution000001.solution | 3 - .../model_2_3_4-solution000002.solution | 3 - .../basic/set04/expected/model_2_3_4.eprime | 60 - .../model_2_4_1-solution000001.solution | 3 - .../model_2_4_1-solution000002.solution | 3 - .../basic/set04/expected/model_2_4_1.eprime | 42 - .../model_2_4_2-solution000001.solution | 3 - .../model_2_4_2-solution000002.solution | 3 - .../basic/set04/expected/model_2_4_2.eprime | 30 - .../model_2_4_3-solution000001.solution | 3 - .../model_2_4_3-solution000002.solution | 3 - .../basic/set04/expected/model_2_4_3.eprime | 59 - .../model_2_4_4-solution000001.solution | 3 - .../model_2_4_4-solution000002.solution | 3 - .../basic/set04/expected/model_2_4_4.eprime | 30 - .../model_3_1_1-solution000001.solution | 3 - .../model_3_1_1-solution000002.solution | 3 - .../basic/set04/expected/model_3_1_1.eprime | 21 - .../model_3_1_2-solution000001.solution | 3 - .../model_3_1_2-solution000002.solution | 3 - .../basic/set04/expected/model_3_1_2.eprime | 42 - .../model_3_1_3-solution000001.solution | 3 - .../model_3_1_3-solution000002.solution | 3 - .../basic/set04/expected/model_3_1_3.eprime | 21 - .../model_3_1_4-solution000001.solution | 3 - .../model_3_1_4-solution000002.solution | 3 - .../basic/set04/expected/model_3_1_4.eprime | 47 - .../model_3_2_1-solution000001.solution | 3 - .../model_3_2_1-solution000002.solution | 3 - .../basic/set04/expected/model_3_2_1.eprime | 42 - .../model_3_2_2-solution000001.solution | 3 - .../model_3_2_2-solution000002.solution | 3 - .../basic/set04/expected/model_3_2_2.eprime | 29 - .../model_3_2_3-solution000001.solution | 3 - .../model_3_2_3-solution000002.solution | 3 - .../basic/set04/expected/model_3_2_3.eprime | 29 - .../model_3_2_4-solution000001.solution | 3 - .../model_3_2_4-solution000002.solution | 3 - .../basic/set04/expected/model_3_2_4.eprime | 60 - .../model_3_3_1-solution000001.solution | 3 - .../model_3_3_1-solution000002.solution | 3 - .../basic/set04/expected/model_3_3_1.eprime | 21 - .../model_3_3_2-solution000001.solution | 3 - .../model_3_3_2-solution000002.solution | 3 - .../basic/set04/expected/model_3_3_2.eprime | 29 - .../model_3_3_3-solution000001.solution | 3 - .../model_3_3_3-solution000002.solution | 3 - .../basic/set04/expected/model_3_3_3.eprime | 14 - .../model_3_3_4-solution000001.solution | 3 - .../model_3_3_4-solution000002.solution | 3 - .../basic/set04/expected/model_3_3_4.eprime | 34 - .../model_3_4_1-solution000001.solution | 3 - .../model_3_4_1-solution000002.solution | 3 - .../basic/set04/expected/model_3_4_1.eprime | 47 - .../model_3_4_2-solution000001.solution | 3 - .../model_3_4_2-solution000002.solution | 3 - .../basic/set04/expected/model_3_4_2.eprime | 59 - .../model_3_4_3-solution000001.solution | 3 - .../model_3_4_3-solution000002.solution | 3 - .../basic/set04/expected/model_3_4_3.eprime | 34 - .../model_3_4_4-solution000001.solution | 3 - .../model_3_4_4-solution000002.solution | 3 - .../basic/set04/expected/model_3_4_4.eprime | 34 - .../model_4_1_1-solution000001.solution | 3 - .../model_4_1_1-solution000002.solution | 3 - .../basic/set04/expected/model_4_1_1.eprime | 22 - .../model_4_1_2-solution000001.solution | 3 - .../model_4_1_2-solution000002.solution | 3 - .../basic/set04/expected/model_4_1_2.eprime | 42 - .../model_4_1_3-solution000001.solution | 3 - .../model_4_1_3-solution000002.solution | 3 - .../basic/set04/expected/model_4_1_3.eprime | 47 - .../model_4_1_4-solution000001.solution | 3 - .../model_4_1_4-solution000002.solution | 3 - .../basic/set04/expected/model_4_1_4.eprime | 22 - .../model_4_2_1-solution000001.solution | 3 - .../model_4_2_1-solution000002.solution | 3 - .../basic/set04/expected/model_4_2_1.eprime | 42 - .../model_4_2_2-solution000001.solution | 3 - .../model_4_2_2-solution000002.solution | 3 - .../basic/set04/expected/model_4_2_2.eprime | 30 - .../model_4_2_3-solution000001.solution | 3 - .../model_4_2_3-solution000002.solution | 3 - .../basic/set04/expected/model_4_2_3.eprime | 59 - .../model_4_2_4-solution000001.solution | 3 - .../model_4_2_4-solution000002.solution | 3 - .../basic/set04/expected/model_4_2_4.eprime | 30 - .../model_4_3_1-solution000001.solution | 3 - .../model_4_3_1-solution000002.solution | 3 - .../basic/set04/expected/model_4_3_1.eprime | 47 - .../model_4_3_2-solution000001.solution | 3 - .../model_4_3_2-solution000002.solution | 3 - .../basic/set04/expected/model_4_3_2.eprime | 59 - .../model_4_3_3-solution000001.solution | 3 - .../model_4_3_3-solution000002.solution | 3 - .../basic/set04/expected/model_4_3_3.eprime | 34 - .../model_4_3_4-solution000001.solution | 3 - .../model_4_3_4-solution000002.solution | 3 - .../basic/set04/expected/model_4_3_4.eprime | 34 - .../model_4_4_1-solution000001.solution | 3 - .../model_4_4_1-solution000002.solution | 3 - .../basic/set04/expected/model_4_4_1.eprime | 22 - .../model_4_4_2-solution000001.solution | 3 - .../model_4_4_2-solution000002.solution | 3 - .../basic/set04/expected/model_4_4_2.eprime | 30 - .../model_4_4_3-solution000001.solution | 3 - .../model_4_4_3-solution000002.solution | 3 - .../basic/set04/expected/model_4_4_3.eprime | 34 - .../model_4_4_4-solution000001.solution | 3 - .../model_4_4_4-solution000002.solution | 3 - .../basic/set04/expected/model_4_4_4.eprime | 15 - .../model_1_1_1-solution000001.solution | 3 - .../model_1_1_1-solution000002.solution | 3 - .../model_1_1_1-solution000003.solution | 3 - .../basic/set05/expected/model_1_1_1.eprime | 9 - .../model_1_1_2-solution000001.solution | 3 - .../model_1_1_2-solution000002.solution | 3 - .../model_1_1_2-solution000003.solution | 3 - .../basic/set05/expected/model_1_1_2.eprime | 18 - .../model_1_1_3-solution000001.solution | 3 - .../model_1_1_3-solution000002.solution | 3 - .../model_1_1_3-solution000003.solution | 3 - .../basic/set05/expected/model_1_1_3.eprime | 21 - .../model_1_1_4-solution000001.solution | 3 - .../model_1_1_4-solution000002.solution | 3 - .../model_1_1_4-solution000003.solution | 3 - .../basic/set05/expected/model_1_1_4.eprime | 21 - .../model_1_2_1-solution000001.solution | 3 - .../model_1_2_1-solution000002.solution | 3 - .../model_1_2_1-solution000003.solution | 3 - .../basic/set05/expected/model_1_2_1.eprime | 18 - .../model_1_2_2-solution000001.solution | 3 - .../model_1_2_2-solution000002.solution | 3 - .../model_1_2_2-solution000003.solution | 3 - .../basic/set05/expected/model_1_2_2.eprime | 18 - .../model_1_2_3-solution000001.solution | 3 - .../model_1_2_3-solution000002.solution | 3 - .../model_1_2_3-solution000003.solution | 3 - .../basic/set05/expected/model_1_2_3.eprime | 42 - .../model_1_2_4-solution000001.solution | 3 - .../model_1_2_4-solution000002.solution | 3 - .../model_1_2_4-solution000003.solution | 3 - .../basic/set05/expected/model_1_2_4.eprime | 43 - .../model_1_3_1-solution000001.solution | 3 - .../model_1_3_1-solution000002.solution | 3 - .../model_1_3_1-solution000003.solution | 3 - .../basic/set05/expected/model_1_3_1.eprime | 21 - .../model_1_3_2-solution000001.solution | 3 - .../model_1_3_2-solution000002.solution | 3 - .../model_1_3_2-solution000003.solution | 3 - .../basic/set05/expected/model_1_3_2.eprime | 41 - .../model_1_3_3-solution000001.solution | 3 - .../model_1_3_3-solution000002.solution | 3 - .../model_1_3_3-solution000003.solution | 3 - .../basic/set05/expected/model_1_3_3.eprime | 21 - .../model_1_3_4-solution000001.solution | 3 - .../model_1_3_4-solution000002.solution | 3 - .../model_1_3_4-solution000003.solution | 3 - .../basic/set05/expected/model_1_3_4.eprime | 47 - .../model_1_4_1-solution000001.solution | 3 - .../model_1_4_1-solution000002.solution | 3 - .../model_1_4_1-solution000003.solution | 3 - .../basic/set05/expected/model_1_4_1.eprime | 21 - .../model_1_4_2-solution000001.solution | 3 - .../model_1_4_2-solution000002.solution | 3 - .../model_1_4_2-solution000003.solution | 3 - .../basic/set05/expected/model_1_4_2.eprime | 41 - .../model_1_4_3-solution000001.solution | 3 - .../model_1_4_3-solution000002.solution | 3 - .../model_1_4_3-solution000003.solution | 3 - .../basic/set05/expected/model_1_4_3.eprime | 46 - .../model_1_4_4-solution000001.solution | 3 - .../model_1_4_4-solution000002.solution | 3 - .../model_1_4_4-solution000003.solution | 3 - .../basic/set05/expected/model_1_4_4.eprime | 21 - .../model_2_1_1-solution000001.solution | 3 - .../model_2_1_1-solution000002.solution | 3 - .../model_2_1_1-solution000003.solution | 3 - .../basic/set05/expected/model_2_1_1.eprime | 18 - .../model_2_1_2-solution000001.solution | 3 - .../model_2_1_2-solution000002.solution | 3 - .../model_2_1_2-solution000003.solution | 3 - .../basic/set05/expected/model_2_1_2.eprime | 18 - .../model_2_1_3-solution000001.solution | 3 - .../model_2_1_3-solution000002.solution | 3 - .../model_2_1_3-solution000003.solution | 3 - .../basic/set05/expected/model_2_1_3.eprime | 42 - .../model_2_1_4-solution000001.solution | 3 - .../model_2_1_4-solution000002.solution | 3 - .../model_2_1_4-solution000003.solution | 3 - .../basic/set05/expected/model_2_1_4.eprime | 42 - .../model_2_2_1-solution000001.solution | 3 - .../model_2_2_1-solution000002.solution | 3 - .../model_2_2_1-solution000003.solution | 3 - .../basic/set05/expected/model_2_2_1.eprime | 18 - .../model_2_2_2-solution000001.solution | 3 - .../model_2_2_2-solution000002.solution | 3 - .../model_2_2_2-solution000003.solution | 3 - .../basic/set05/expected/model_2_2_2.eprime | 12 - .../model_2_2_3-solution000001.solution | 3 - .../model_2_2_3-solution000002.solution | 3 - .../model_2_2_3-solution000003.solution | 3 - .../basic/set05/expected/model_2_2_3.eprime | 29 - .../model_2_2_4-solution000001.solution | 3 - .../model_2_2_4-solution000002.solution | 3 - .../model_2_2_4-solution000003.solution | 3 - .../basic/set05/expected/model_2_2_4.eprime | 30 - .../model_2_3_1-solution000001.solution | 3 - .../model_2_3_1-solution000002.solution | 3 - .../model_2_3_1-solution000003.solution | 3 - .../basic/set05/expected/model_2_3_1.eprime | 42 - .../model_2_3_2-solution000001.solution | 3 - .../model_2_3_2-solution000002.solution | 3 - .../model_2_3_2-solution000003.solution | 3 - .../basic/set05/expected/model_2_3_2.eprime | 29 - .../model_2_3_3-solution000001.solution | 3 - .../model_2_3_3-solution000002.solution | 3 - .../model_2_3_3-solution000003.solution | 3 - .../basic/set05/expected/model_2_3_3.eprime | 29 - .../model_2_3_4-solution000001.solution | 3 - .../model_2_3_4-solution000002.solution | 3 - .../model_2_3_4-solution000003.solution | 3 - .../basic/set05/expected/model_2_3_4.eprime | 60 - .../model_2_4_1-solution000001.solution | 3 - .../model_2_4_1-solution000002.solution | 3 - .../model_2_4_1-solution000003.solution | 3 - .../basic/set05/expected/model_2_4_1.eprime | 42 - .../model_2_4_2-solution000001.solution | 3 - .../model_2_4_2-solution000002.solution | 3 - .../model_2_4_2-solution000003.solution | 3 - .../basic/set05/expected/model_2_4_2.eprime | 30 - .../model_2_4_3-solution000001.solution | 3 - .../model_2_4_3-solution000002.solution | 3 - .../model_2_4_3-solution000003.solution | 3 - .../basic/set05/expected/model_2_4_3.eprime | 59 - .../model_2_4_4-solution000001.solution | 3 - .../model_2_4_4-solution000002.solution | 3 - .../model_2_4_4-solution000003.solution | 3 - .../basic/set05/expected/model_2_4_4.eprime | 30 - .../model_3_1_1-solution000001.solution | 3 - .../model_3_1_1-solution000002.solution | 3 - .../model_3_1_1-solution000003.solution | 3 - .../basic/set05/expected/model_3_1_1.eprime | 21 - .../model_3_1_2-solution000001.solution | 3 - .../model_3_1_2-solution000002.solution | 3 - .../model_3_1_2-solution000003.solution | 3 - .../basic/set05/expected/model_3_1_2.eprime | 42 - .../model_3_1_3-solution000001.solution | 3 - .../model_3_1_3-solution000002.solution | 3 - .../model_3_1_3-solution000003.solution | 3 - .../basic/set05/expected/model_3_1_3.eprime | 21 - .../model_3_1_4-solution000001.solution | 3 - .../model_3_1_4-solution000002.solution | 3 - .../model_3_1_4-solution000003.solution | 3 - .../basic/set05/expected/model_3_1_4.eprime | 47 - .../model_3_2_1-solution000001.solution | 3 - .../model_3_2_1-solution000002.solution | 3 - .../model_3_2_1-solution000003.solution | 3 - .../basic/set05/expected/model_3_2_1.eprime | 42 - .../model_3_2_2-solution000001.solution | 3 - .../model_3_2_2-solution000002.solution | 3 - .../model_3_2_2-solution000003.solution | 3 - .../basic/set05/expected/model_3_2_2.eprime | 29 - .../model_3_2_3-solution000001.solution | 3 - .../model_3_2_3-solution000002.solution | 3 - .../model_3_2_3-solution000003.solution | 3 - .../basic/set05/expected/model_3_2_3.eprime | 29 - .../model_3_2_4-solution000001.solution | 3 - .../model_3_2_4-solution000002.solution | 3 - .../model_3_2_4-solution000003.solution | 3 - .../basic/set05/expected/model_3_2_4.eprime | 60 - .../model_3_3_1-solution000001.solution | 3 - .../model_3_3_1-solution000002.solution | 3 - .../model_3_3_1-solution000003.solution | 3 - .../basic/set05/expected/model_3_3_1.eprime | 21 - .../model_3_3_2-solution000001.solution | 3 - .../model_3_3_2-solution000002.solution | 3 - .../model_3_3_2-solution000003.solution | 3 - .../basic/set05/expected/model_3_3_2.eprime | 29 - .../model_3_3_3-solution000001.solution | 3 - .../model_3_3_3-solution000002.solution | 3 - .../model_3_3_3-solution000003.solution | 3 - .../basic/set05/expected/model_3_3_3.eprime | 14 - .../model_3_3_4-solution000001.solution | 3 - .../model_3_3_4-solution000002.solution | 3 - .../model_3_3_4-solution000003.solution | 3 - .../basic/set05/expected/model_3_3_4.eprime | 34 - .../model_3_4_1-solution000001.solution | 3 - .../model_3_4_1-solution000002.solution | 3 - .../model_3_4_1-solution000003.solution | 3 - .../basic/set05/expected/model_3_4_1.eprime | 47 - .../model_3_4_2-solution000001.solution | 3 - .../model_3_4_2-solution000002.solution | 3 - .../model_3_4_2-solution000003.solution | 3 - .../basic/set05/expected/model_3_4_2.eprime | 59 - .../model_3_4_3-solution000001.solution | 3 - .../model_3_4_3-solution000002.solution | 3 - .../model_3_4_3-solution000003.solution | 3 - .../basic/set05/expected/model_3_4_3.eprime | 34 - .../model_3_4_4-solution000001.solution | 3 - .../model_3_4_4-solution000002.solution | 3 - .../model_3_4_4-solution000003.solution | 3 - .../basic/set05/expected/model_3_4_4.eprime | 34 - .../model_4_1_1-solution000001.solution | 3 - .../model_4_1_1-solution000002.solution | 3 - .../model_4_1_1-solution000003.solution | 3 - .../basic/set05/expected/model_4_1_1.eprime | 22 - .../model_4_1_2-solution000001.solution | 3 - .../model_4_1_2-solution000002.solution | 3 - .../model_4_1_2-solution000003.solution | 3 - .../basic/set05/expected/model_4_1_2.eprime | 42 - .../model_4_1_3-solution000001.solution | 3 - .../model_4_1_3-solution000002.solution | 3 - .../model_4_1_3-solution000003.solution | 3 - .../basic/set05/expected/model_4_1_3.eprime | 47 - .../model_4_1_4-solution000001.solution | 3 - .../model_4_1_4-solution000002.solution | 3 - .../model_4_1_4-solution000003.solution | 3 - .../basic/set05/expected/model_4_1_4.eprime | 22 - .../model_4_2_1-solution000001.solution | 3 - .../model_4_2_1-solution000002.solution | 3 - .../model_4_2_1-solution000003.solution | 3 - .../basic/set05/expected/model_4_2_1.eprime | 42 - .../model_4_2_2-solution000001.solution | 3 - .../model_4_2_2-solution000002.solution | 3 - .../model_4_2_2-solution000003.solution | 3 - .../basic/set05/expected/model_4_2_2.eprime | 30 - .../model_4_2_3-solution000001.solution | 3 - .../model_4_2_3-solution000002.solution | 3 - .../model_4_2_3-solution000003.solution | 3 - .../basic/set05/expected/model_4_2_3.eprime | 59 - .../model_4_2_4-solution000001.solution | 3 - .../model_4_2_4-solution000002.solution | 3 - .../model_4_2_4-solution000003.solution | 3 - .../basic/set05/expected/model_4_2_4.eprime | 30 - .../model_4_3_1-solution000001.solution | 3 - .../model_4_3_1-solution000002.solution | 3 - .../model_4_3_1-solution000003.solution | 3 - .../basic/set05/expected/model_4_3_1.eprime | 47 - .../model_4_3_2-solution000001.solution | 3 - .../model_4_3_2-solution000002.solution | 3 - .../model_4_3_2-solution000003.solution | 3 - .../basic/set05/expected/model_4_3_2.eprime | 59 - .../model_4_3_3-solution000001.solution | 3 - .../model_4_3_3-solution000002.solution | 3 - .../model_4_3_3-solution000003.solution | 3 - .../basic/set05/expected/model_4_3_3.eprime | 34 - .../model_4_3_4-solution000001.solution | 3 - .../model_4_3_4-solution000002.solution | 3 - .../model_4_3_4-solution000003.solution | 3 - .../basic/set05/expected/model_4_3_4.eprime | 34 - .../model_4_4_1-solution000001.solution | 3 - .../model_4_4_1-solution000002.solution | 3 - .../model_4_4_1-solution000003.solution | 3 - .../basic/set05/expected/model_4_4_1.eprime | 22 - .../model_4_4_2-solution000001.solution | 3 - .../model_4_4_2-solution000002.solution | 3 - .../model_4_4_2-solution000003.solution | 3 - .../basic/set05/expected/model_4_4_2.eprime | 30 - .../model_4_4_3-solution000001.solution | 3 - .../model_4_4_3-solution000002.solution | 3 - .../model_4_4_3-solution000003.solution | 3 - .../basic/set05/expected/model_4_4_3.eprime | 34 - .../model_4_4_4-solution000001.solution | 3 - .../model_4_4_4-solution000002.solution | 3 - .../model_4_4_4-solution000003.solution | 3 - .../basic/set05/expected/model_4_4_4.eprime | 15 - .../model_1_1_1_1-solution000001.solution | 3 - .../model_1_1_1_1-solution000002.solution | 3 - .../basic/set06/expected/model_1_1_1_1.eprime | 10 - .../model_1_1_1_2-solution000001.solution | 3 - .../model_1_1_1_2-solution000002.solution | 3 - .../basic/set06/expected/model_1_1_1_2.eprime | 19 - .../model_1_1_1_3-solution000001.solution | 3 - .../model_1_1_1_3-solution000002.solution | 3 - .../basic/set06/expected/model_1_1_1_3.eprime | 22 - .../model_1_1_1_4-solution000001.solution | 3 - .../model_1_1_1_4-solution000002.solution | 3 - .../basic/set06/expected/model_1_1_1_4.eprime | 22 - .../model_1_1_2_1-solution000001.solution | 3 - .../model_1_1_2_1-solution000002.solution | 3 - .../basic/set06/expected/model_1_1_2_1.eprime | 19 - .../model_1_1_2_2-solution000001.solution | 3 - .../model_1_1_2_2-solution000002.solution | 3 - .../basic/set06/expected/model_1_1_2_2.eprime | 19 - .../model_1_1_2_3-solution000001.solution | 3 - .../model_1_1_2_3-solution000002.solution | 3 - .../basic/set06/expected/model_1_1_2_3.eprime | 43 - .../model_1_1_2_4-solution000001.solution | 3 - .../model_1_1_2_4-solution000002.solution | 3 - .../basic/set06/expected/model_1_1_2_4.eprime | 44 - .../model_1_1_3_1-solution000001.solution | 3 - .../model_1_1_3_1-solution000002.solution | 3 - .../basic/set06/expected/model_1_1_3_1.eprime | 22 - .../model_1_1_3_2-solution000001.solution | 3 - .../model_1_1_3_2-solution000002.solution | 3 - .../basic/set06/expected/model_1_1_3_2.eprime | 42 - .../model_1_1_3_3-solution000001.solution | 3 - .../model_1_1_3_3-solution000002.solution | 3 - .../basic/set06/expected/model_1_1_3_3.eprime | 22 - .../model_1_1_3_4-solution000001.solution | 3 - .../model_1_1_3_4-solution000002.solution | 3 - .../basic/set06/expected/model_1_1_3_4.eprime | 48 - .../model_1_1_4_1-solution000001.solution | 3 - .../model_1_1_4_1-solution000002.solution | 3 - .../basic/set06/expected/model_1_1_4_1.eprime | 22 - .../model_1_1_4_2-solution000001.solution | 3 - .../model_1_1_4_2-solution000002.solution | 3 - .../basic/set06/expected/model_1_1_4_2.eprime | 42 - .../model_1_1_4_3-solution000001.solution | 3 - .../model_1_1_4_3-solution000002.solution | 3 - .../basic/set06/expected/model_1_1_4_3.eprime | 47 - .../model_1_1_4_4-solution000001.solution | 3 - .../model_1_1_4_4-solution000002.solution | 3 - .../basic/set06/expected/model_1_1_4_4.eprime | 22 - .../model_1_2_1_1-solution000001.solution | 3 - .../model_1_2_1_1-solution000002.solution | 3 - .../basic/set06/expected/model_1_2_1_1.eprime | 19 - .../model_1_2_1_2-solution000001.solution | 3 - .../model_1_2_1_2-solution000002.solution | 3 - .../basic/set06/expected/model_1_2_1_2.eprime | 19 - .../model_1_2_1_3-solution000001.solution | 3 - .../model_1_2_1_3-solution000002.solution | 3 - .../basic/set06/expected/model_1_2_1_3.eprime | 43 - .../model_1_2_1_4-solution000001.solution | 3 - .../model_1_2_1_4-solution000002.solution | 3 - .../basic/set06/expected/model_1_2_1_4.eprime | 44 - .../model_1_2_2_1-solution000001.solution | 3 - .../model_1_2_2_1-solution000002.solution | 3 - .../basic/set06/expected/model_1_2_2_1.eprime | 19 - .../model_1_2_2_2-solution000001.solution | 3 - .../model_1_2_2_2-solution000002.solution | 3 - .../basic/set06/expected/model_1_2_2_2.eprime | 19 - .../model_1_2_2_3-solution000001.solution | 3 - .../model_1_2_2_3-solution000002.solution | 3 - .../basic/set06/expected/model_1_2_2_3.eprime | 43 - .../model_1_2_2_4-solution000001.solution | 3 - .../model_1_2_2_4-solution000002.solution | 3 - .../basic/set06/expected/model_1_2_2_4.eprime | 44 - .../model_1_2_3_1-solution000001.solution | 3 - .../model_1_2_3_1-solution000002.solution | 3 - .../basic/set06/expected/model_1_2_3_1.eprime | 43 - .../model_1_2_3_2-solution000001.solution | 3 - .../model_1_2_3_2-solution000002.solution | 3 - .../basic/set06/expected/model_1_2_3_2.eprime | 43 - .../model_1_2_3_3-solution000001.solution | 3 - .../model_1_2_3_3-solution000002.solution | 3 - .../basic/set06/expected/model_1_2_3_3.eprime | 43 - .../model_1_2_3_4-solution000001.solution | 3 - .../model_1_2_3_4-solution000002.solution | 3 - .../basic/set06/expected/model_1_2_3_4.eprime | 78 -- .../model_1_2_4_1-solution000001.solution | 3 - .../model_1_2_4_1-solution000002.solution | 3 - .../basic/set06/expected/model_1_2_4_1.eprime | 44 - .../model_1_2_4_2-solution000001.solution | 3 - .../model_1_2_4_2-solution000002.solution | 3 - .../basic/set06/expected/model_1_2_4_2.eprime | 44 - .../model_1_2_4_3-solution000001.solution | 3 - .../model_1_2_4_3-solution000002.solution | 3 - .../basic/set06/expected/model_1_2_4_3.eprime | 78 -- .../model_1_2_4_4-solution000001.solution | 3 - .../model_1_2_4_4-solution000002.solution | 3 - .../basic/set06/expected/model_1_2_4_4.eprime | 44 - .../model_1_3_1_1-solution000001.solution | 3 - .../model_1_3_1_1-solution000002.solution | 3 - .../basic/set06/expected/model_1_3_1_1.eprime | 22 - .../model_1_3_1_2-solution000001.solution | 3 - .../model_1_3_1_2-solution000002.solution | 3 - .../basic/set06/expected/model_1_3_1_2.eprime | 42 - .../model_1_3_1_3-solution000001.solution | 3 - .../model_1_3_1_3-solution000002.solution | 3 - .../basic/set06/expected/model_1_3_1_3.eprime | 22 - .../model_1_3_1_4-solution000001.solution | 3 - .../model_1_3_1_4-solution000002.solution | 3 - .../basic/set06/expected/model_1_3_1_4.eprime | 48 - .../model_1_3_2_1-solution000001.solution | 3 - .../model_1_3_2_1-solution000002.solution | 3 - .../basic/set06/expected/model_1_3_2_1.eprime | 42 - .../model_1_3_2_2-solution000001.solution | 3 - .../model_1_3_2_2-solution000002.solution | 3 - .../basic/set06/expected/model_1_3_2_2.eprime | 42 - .../model_1_3_2_3-solution000001.solution | 3 - .../model_1_3_2_3-solution000002.solution | 3 - .../basic/set06/expected/model_1_3_2_3.eprime | 42 - .../model_1_3_2_4-solution000001.solution | 3 - .../model_1_3_2_4-solution000002.solution | 3 - .../basic/set06/expected/model_1_3_2_4.eprime | 77 -- .../model_1_3_3_1-solution000001.solution | 3 - .../model_1_3_3_1-solution000002.solution | 3 - .../basic/set06/expected/model_1_3_3_1.eprime | 22 - .../model_1_3_3_2-solution000001.solution | 3 - .../model_1_3_3_2-solution000002.solution | 3 - .../basic/set06/expected/model_1_3_3_2.eprime | 42 - .../model_1_3_3_3-solution000001.solution | 3 - .../model_1_3_3_3-solution000002.solution | 3 - .../basic/set06/expected/model_1_3_3_3.eprime | 22 - .../model_1_3_3_4-solution000001.solution | 3 - .../model_1_3_3_4-solution000002.solution | 3 - .../basic/set06/expected/model_1_3_3_4.eprime | 48 - .../model_1_3_4_1-solution000001.solution | 3 - .../model_1_3_4_1-solution000002.solution | 3 - .../basic/set06/expected/model_1_3_4_1.eprime | 48 - .../model_1_3_4_2-solution000001.solution | 3 - .../model_1_3_4_2-solution000002.solution | 3 - .../basic/set06/expected/model_1_3_4_2.eprime | 77 -- .../model_1_3_4_3-solution000001.solution | 3 - .../model_1_3_4_3-solution000002.solution | 3 - .../basic/set06/expected/model_1_3_4_3.eprime | 48 - .../model_1_3_4_4-solution000001.solution | 3 - .../model_1_3_4_4-solution000002.solution | 3 - .../basic/set06/expected/model_1_3_4_4.eprime | 48 - .../model_1_4_1_1-solution000001.solution | 3 - .../model_1_4_1_1-solution000002.solution | 3 - .../basic/set06/expected/model_1_4_1_1.eprime | 22 - .../model_1_4_1_2-solution000001.solution | 3 - .../model_1_4_1_2-solution000002.solution | 3 - .../basic/set06/expected/model_1_4_1_2.eprime | 42 - .../model_1_4_1_3-solution000001.solution | 3 - .../model_1_4_1_3-solution000002.solution | 3 - .../basic/set06/expected/model_1_4_1_3.eprime | 47 - .../model_1_4_1_4-solution000001.solution | 3 - .../model_1_4_1_4-solution000002.solution | 3 - .../basic/set06/expected/model_1_4_1_4.eprime | 22 - .../model_1_4_2_1-solution000001.solution | 3 - .../model_1_4_2_1-solution000002.solution | 3 - .../basic/set06/expected/model_1_4_2_1.eprime | 42 - .../model_1_4_2_2-solution000001.solution | 3 - .../model_1_4_2_2-solution000002.solution | 3 - .../basic/set06/expected/model_1_4_2_2.eprime | 42 - .../model_1_4_2_3-solution000001.solution | 3 - .../model_1_4_2_3-solution000002.solution | 3 - .../basic/set06/expected/model_1_4_2_3.eprime | 76 - .../model_1_4_2_4-solution000001.solution | 3 - .../model_1_4_2_4-solution000002.solution | 3 - .../basic/set06/expected/model_1_4_2_4.eprime | 42 - .../model_1_4_3_1-solution000001.solution | 3 - .../model_1_4_3_1-solution000002.solution | 3 - .../basic/set06/expected/model_1_4_3_1.eprime | 47 - .../model_1_4_3_2-solution000001.solution | 3 - .../model_1_4_3_2-solution000002.solution | 3 - .../basic/set06/expected/model_1_4_3_2.eprime | 76 - .../model_1_4_3_3-solution000001.solution | 3 - .../model_1_4_3_3-solution000002.solution | 3 - .../basic/set06/expected/model_1_4_3_3.eprime | 47 - .../model_1_4_3_4-solution000001.solution | 3 - .../model_1_4_3_4-solution000002.solution | 3 - .../basic/set06/expected/model_1_4_3_4.eprime | 47 - .../model_1_4_4_1-solution000001.solution | 3 - .../model_1_4_4_1-solution000002.solution | 3 - .../basic/set06/expected/model_1_4_4_1.eprime | 22 - .../model_1_4_4_2-solution000001.solution | 3 - .../model_1_4_4_2-solution000002.solution | 3 - .../basic/set06/expected/model_1_4_4_2.eprime | 42 - .../model_1_4_4_3-solution000001.solution | 3 - .../model_1_4_4_3-solution000002.solution | 3 - .../basic/set06/expected/model_1_4_4_3.eprime | 47 - .../model_1_4_4_4-solution000001.solution | 3 - .../model_1_4_4_4-solution000002.solution | 3 - .../basic/set06/expected/model_1_4_4_4.eprime | 22 - .../model_2_1_1_1-solution000001.solution | 3 - .../model_2_1_1_1-solution000002.solution | 3 - .../basic/set06/expected/model_2_1_1_1.eprime | 19 - .../model_2_1_1_2-solution000001.solution | 3 - .../model_2_1_1_2-solution000002.solution | 3 - .../basic/set06/expected/model_2_1_1_2.eprime | 19 - .../model_2_1_1_3-solution000001.solution | 3 - .../model_2_1_1_3-solution000002.solution | 3 - .../basic/set06/expected/model_2_1_1_3.eprime | 43 - .../model_2_1_1_4-solution000001.solution | 3 - .../model_2_1_1_4-solution000002.solution | 3 - .../basic/set06/expected/model_2_1_1_4.eprime | 43 - .../model_2_1_2_1-solution000001.solution | 3 - .../model_2_1_2_1-solution000002.solution | 3 - .../basic/set06/expected/model_2_1_2_1.eprime | 19 - .../model_2_1_2_2-solution000001.solution | 3 - .../model_2_1_2_2-solution000002.solution | 3 - .../basic/set06/expected/model_2_1_2_2.eprime | 19 - .../model_2_1_2_3-solution000001.solution | 3 - .../model_2_1_2_3-solution000002.solution | 3 - .../basic/set06/expected/model_2_1_2_3.eprime | 43 - .../model_2_1_2_4-solution000001.solution | 3 - .../model_2_1_2_4-solution000002.solution | 3 - .../basic/set06/expected/model_2_1_2_4.eprime | 43 - .../model_2_1_3_1-solution000001.solution | 3 - .../model_2_1_3_1-solution000002.solution | 3 - .../basic/set06/expected/model_2_1_3_1.eprime | 43 - .../model_2_1_3_2-solution000001.solution | 3 - .../model_2_1_3_2-solution000002.solution | 3 - .../basic/set06/expected/model_2_1_3_2.eprime | 43 - .../model_2_1_3_3-solution000001.solution | 3 - .../model_2_1_3_3-solution000002.solution | 3 - .../basic/set06/expected/model_2_1_3_3.eprime | 43 - .../model_2_1_3_4-solution000001.solution | 3 - .../model_2_1_3_4-solution000002.solution | 3 - .../basic/set06/expected/model_2_1_3_4.eprime | 78 -- .../model_2_1_4_1-solution000001.solution | 3 - .../model_2_1_4_1-solution000002.solution | 3 - .../basic/set06/expected/model_2_1_4_1.eprime | 43 - .../model_2_1_4_2-solution000001.solution | 3 - .../model_2_1_4_2-solution000002.solution | 3 - .../basic/set06/expected/model_2_1_4_2.eprime | 43 - .../model_2_1_4_3-solution000001.solution | 3 - .../model_2_1_4_3-solution000002.solution | 3 - .../basic/set06/expected/model_2_1_4_3.eprime | 77 -- .../model_2_1_4_4-solution000001.solution | 3 - .../model_2_1_4_4-solution000002.solution | 3 - .../basic/set06/expected/model_2_1_4_4.eprime | 43 - .../model_2_2_1_1-solution000001.solution | 3 - .../model_2_2_1_1-solution000002.solution | 3 - .../basic/set06/expected/model_2_2_1_1.eprime | 19 - .../model_2_2_1_2-solution000001.solution | 3 - .../model_2_2_1_2-solution000002.solution | 3 - .../basic/set06/expected/model_2_2_1_2.eprime | 19 - .../model_2_2_1_3-solution000001.solution | 3 - .../model_2_2_1_3-solution000002.solution | 3 - .../basic/set06/expected/model_2_2_1_3.eprime | 43 - .../model_2_2_1_4-solution000001.solution | 3 - .../model_2_2_1_4-solution000002.solution | 3 - .../basic/set06/expected/model_2_2_1_4.eprime | 43 - .../model_2_2_2_1-solution000001.solution | 3 - .../model_2_2_2_1-solution000002.solution | 3 - .../basic/set06/expected/model_2_2_2_1.eprime | 19 - .../model_2_2_2_2-solution000001.solution | 3 - .../model_2_2_2_2-solution000002.solution | 3 - .../basic/set06/expected/model_2_2_2_2.eprime | 13 - .../model_2_2_2_3-solution000001.solution | 3 - .../model_2_2_2_3-solution000002.solution | 3 - .../basic/set06/expected/model_2_2_2_3.eprime | 30 - .../model_2_2_2_4-solution000001.solution | 3 - .../model_2_2_2_4-solution000002.solution | 3 - .../basic/set06/expected/model_2_2_2_4.eprime | 31 - .../model_2_2_3_1-solution000001.solution | 3 - .../model_2_2_3_1-solution000002.solution | 3 - .../basic/set06/expected/model_2_2_3_1.eprime | 43 - .../model_2_2_3_2-solution000001.solution | 3 - .../model_2_2_3_2-solution000002.solution | 3 - .../basic/set06/expected/model_2_2_3_2.eprime | 30 - .../model_2_2_3_3-solution000001.solution | 3 - .../model_2_2_3_3-solution000002.solution | 3 - .../basic/set06/expected/model_2_2_3_3.eprime | 30 - .../model_2_2_3_4-solution000001.solution | 3 - .../model_2_2_3_4-solution000002.solution | 3 - .../basic/set06/expected/model_2_2_3_4.eprime | 61 - .../model_2_2_4_1-solution000001.solution | 3 - .../model_2_2_4_1-solution000002.solution | 3 - .../basic/set06/expected/model_2_2_4_1.eprime | 43 - .../model_2_2_4_2-solution000001.solution | 3 - .../model_2_2_4_2-solution000002.solution | 3 - .../basic/set06/expected/model_2_2_4_2.eprime | 31 - .../model_2_2_4_3-solution000001.solution | 3 - .../model_2_2_4_3-solution000002.solution | 3 - .../basic/set06/expected/model_2_2_4_3.eprime | 60 - .../model_2_2_4_4-solution000001.solution | 3 - .../model_2_2_4_4-solution000002.solution | 3 - .../basic/set06/expected/model_2_2_4_4.eprime | 31 - .../model_2_3_1_1-solution000001.solution | 3 - .../model_2_3_1_1-solution000002.solution | 3 - .../basic/set06/expected/model_2_3_1_1.eprime | 43 - .../model_2_3_1_2-solution000001.solution | 3 - .../model_2_3_1_2-solution000002.solution | 3 - .../basic/set06/expected/model_2_3_1_2.eprime | 43 - .../model_2_3_1_3-solution000001.solution | 3 - .../model_2_3_1_3-solution000002.solution | 3 - .../basic/set06/expected/model_2_3_1_3.eprime | 43 - .../model_2_3_1_4-solution000001.solution | 3 - .../model_2_3_1_4-solution000002.solution | 3 - .../basic/set06/expected/model_2_3_1_4.eprime | 78 -- .../model_2_3_2_1-solution000001.solution | 3 - .../model_2_3_2_1-solution000002.solution | 3 - .../basic/set06/expected/model_2_3_2_1.eprime | 43 - .../model_2_3_2_2-solution000001.solution | 3 - .../model_2_3_2_2-solution000002.solution | 3 - .../basic/set06/expected/model_2_3_2_2.eprime | 30 - .../model_2_3_2_3-solution000001.solution | 3 - .../model_2_3_2_3-solution000002.solution | 3 - .../basic/set06/expected/model_2_3_2_3.eprime | 30 - .../model_2_3_2_4-solution000001.solution | 3 - .../model_2_3_2_4-solution000002.solution | 3 - .../basic/set06/expected/model_2_3_2_4.eprime | 61 - .../model_2_3_3_1-solution000001.solution | 3 - .../model_2_3_3_1-solution000002.solution | 3 - .../basic/set06/expected/model_2_3_3_1.eprime | 43 - .../model_2_3_3_2-solution000001.solution | 3 - .../model_2_3_3_2-solution000002.solution | 3 - .../basic/set06/expected/model_2_3_3_2.eprime | 30 - .../model_2_3_3_3-solution000001.solution | 3 - .../model_2_3_3_3-solution000002.solution | 3 - .../basic/set06/expected/model_2_3_3_3.eprime | 30 - .../model_2_3_3_4-solution000001.solution | 3 - .../model_2_3_3_4-solution000002.solution | 3 - .../basic/set06/expected/model_2_3_3_4.eprime | 61 - .../model_2_3_4_1-solution000001.solution | 3 - .../model_2_3_4_1-solution000002.solution | 3 - .../basic/set06/expected/model_2_3_4_1.eprime | 78 -- .../model_2_3_4_2-solution000001.solution | 3 - .../model_2_3_4_2-solution000002.solution | 3 - .../basic/set06/expected/model_2_3_4_2.eprime | 61 - .../model_2_3_4_3-solution000001.solution | 3 - .../model_2_3_4_3-solution000002.solution | 3 - .../basic/set06/expected/model_2_3_4_3.eprime | 61 - .../model_2_3_4_4-solution000001.solution | 3 - .../model_2_3_4_4-solution000002.solution | 3 - .../basic/set06/expected/model_2_3_4_4.eprime | 61 - .../model_2_4_1_1-solution000001.solution | 3 - .../model_2_4_1_1-solution000002.solution | 3 - .../basic/set06/expected/model_2_4_1_1.eprime | 43 - .../model_2_4_1_2-solution000001.solution | 3 - .../model_2_4_1_2-solution000002.solution | 3 - .../basic/set06/expected/model_2_4_1_2.eprime | 43 - .../model_2_4_1_3-solution000001.solution | 3 - .../model_2_4_1_3-solution000002.solution | 3 - .../basic/set06/expected/model_2_4_1_3.eprime | 77 -- .../model_2_4_1_4-solution000001.solution | 3 - .../model_2_4_1_4-solution000002.solution | 3 - .../basic/set06/expected/model_2_4_1_4.eprime | 43 - .../model_2_4_2_1-solution000001.solution | 3 - .../model_2_4_2_1-solution000002.solution | 3 - .../basic/set06/expected/model_2_4_2_1.eprime | 43 - .../model_2_4_2_2-solution000001.solution | 3 - .../model_2_4_2_2-solution000002.solution | 3 - .../basic/set06/expected/model_2_4_2_2.eprime | 31 - .../model_2_4_2_3-solution000001.solution | 3 - .../model_2_4_2_3-solution000002.solution | 3 - .../basic/set06/expected/model_2_4_2_3.eprime | 60 - .../model_2_4_2_4-solution000001.solution | 3 - .../model_2_4_2_4-solution000002.solution | 3 - .../basic/set06/expected/model_2_4_2_4.eprime | 31 - .../model_2_4_3_1-solution000001.solution | 3 - .../model_2_4_3_1-solution000002.solution | 3 - .../basic/set06/expected/model_2_4_3_1.eprime | 77 -- .../model_2_4_3_2-solution000001.solution | 3 - .../model_2_4_3_2-solution000002.solution | 3 - .../basic/set06/expected/model_2_4_3_2.eprime | 60 - .../model_2_4_3_3-solution000001.solution | 3 - .../model_2_4_3_3-solution000002.solution | 3 - .../basic/set06/expected/model_2_4_3_3.eprime | 60 - .../model_2_4_3_4-solution000001.solution | 3 - .../model_2_4_3_4-solution000002.solution | 3 - .../basic/set06/expected/model_2_4_3_4.eprime | 60 - .../model_2_4_4_1-solution000001.solution | 3 - .../model_2_4_4_1-solution000002.solution | 3 - .../basic/set06/expected/model_2_4_4_1.eprime | 43 - .../model_2_4_4_2-solution000001.solution | 3 - .../model_2_4_4_2-solution000002.solution | 3 - .../basic/set06/expected/model_2_4_4_2.eprime | 31 - .../model_2_4_4_3-solution000001.solution | 3 - .../model_2_4_4_3-solution000002.solution | 3 - .../basic/set06/expected/model_2_4_4_3.eprime | 60 - .../model_2_4_4_4-solution000001.solution | 3 - .../model_2_4_4_4-solution000002.solution | 3 - .../basic/set06/expected/model_2_4_4_4.eprime | 31 - .../model_3_1_1_1-solution000001.solution | 3 - .../model_3_1_1_1-solution000002.solution | 3 - .../basic/set06/expected/model_3_1_1_1.eprime | 22 - .../model_3_1_1_2-solution000001.solution | 3 - .../model_3_1_1_2-solution000002.solution | 3 - .../basic/set06/expected/model_3_1_1_2.eprime | 43 - .../model_3_1_1_3-solution000001.solution | 3 - .../model_3_1_1_3-solution000002.solution | 3 - .../basic/set06/expected/model_3_1_1_3.eprime | 22 - .../model_3_1_1_4-solution000001.solution | 3 - .../model_3_1_1_4-solution000002.solution | 3 - .../basic/set06/expected/model_3_1_1_4.eprime | 48 - .../model_3_1_2_1-solution000001.solution | 3 - .../model_3_1_2_1-solution000002.solution | 3 - .../basic/set06/expected/model_3_1_2_1.eprime | 43 - .../model_3_1_2_2-solution000001.solution | 3 - .../model_3_1_2_2-solution000002.solution | 3 - .../basic/set06/expected/model_3_1_2_2.eprime | 43 - .../model_3_1_2_3-solution000001.solution | 3 - .../model_3_1_2_3-solution000002.solution | 3 - .../basic/set06/expected/model_3_1_2_3.eprime | 43 - .../model_3_1_2_4-solution000001.solution | 3 - .../model_3_1_2_4-solution000002.solution | 3 - .../basic/set06/expected/model_3_1_2_4.eprime | 78 -- .../model_3_1_3_1-solution000001.solution | 3 - .../model_3_1_3_1-solution000002.solution | 3 - .../basic/set06/expected/model_3_1_3_1.eprime | 22 - .../model_3_1_3_2-solution000001.solution | 3 - .../model_3_1_3_2-solution000002.solution | 3 - .../basic/set06/expected/model_3_1_3_2.eprime | 43 - .../model_3_1_3_3-solution000001.solution | 3 - .../model_3_1_3_3-solution000002.solution | 3 - .../basic/set06/expected/model_3_1_3_3.eprime | 22 - .../model_3_1_3_4-solution000001.solution | 3 - .../model_3_1_3_4-solution000002.solution | 3 - .../basic/set06/expected/model_3_1_3_4.eprime | 48 - .../model_3_1_4_1-solution000001.solution | 3 - .../model_3_1_4_1-solution000002.solution | 3 - .../basic/set06/expected/model_3_1_4_1.eprime | 48 - .../model_3_1_4_2-solution000001.solution | 3 - .../model_3_1_4_2-solution000002.solution | 3 - .../basic/set06/expected/model_3_1_4_2.eprime | 77 -- .../model_3_1_4_3-solution000001.solution | 3 - .../model_3_1_4_3-solution000002.solution | 3 - .../basic/set06/expected/model_3_1_4_3.eprime | 48 - .../model_3_1_4_4-solution000001.solution | 3 - .../model_3_1_4_4-solution000002.solution | 3 - .../basic/set06/expected/model_3_1_4_4.eprime | 48 - .../model_3_2_1_1-solution000001.solution | 3 - .../model_3_2_1_1-solution000002.solution | 3 - .../basic/set06/expected/model_3_2_1_1.eprime | 43 - .../model_3_2_1_2-solution000001.solution | 3 - .../model_3_2_1_2-solution000002.solution | 3 - .../basic/set06/expected/model_3_2_1_2.eprime | 43 - .../model_3_2_1_3-solution000001.solution | 3 - .../model_3_2_1_3-solution000002.solution | 3 - .../basic/set06/expected/model_3_2_1_3.eprime | 43 - .../model_3_2_1_4-solution000001.solution | 3 - .../model_3_2_1_4-solution000002.solution | 3 - .../basic/set06/expected/model_3_2_1_4.eprime | 78 -- .../model_3_2_2_1-solution000001.solution | 3 - .../model_3_2_2_1-solution000002.solution | 3 - .../basic/set06/expected/model_3_2_2_1.eprime | 43 - .../model_3_2_2_2-solution000001.solution | 3 - .../model_3_2_2_2-solution000002.solution | 3 - .../basic/set06/expected/model_3_2_2_2.eprime | 30 - .../model_3_2_2_3-solution000001.solution | 3 - .../model_3_2_2_3-solution000002.solution | 3 - .../basic/set06/expected/model_3_2_2_3.eprime | 30 - .../model_3_2_2_4-solution000001.solution | 3 - .../model_3_2_2_4-solution000002.solution | 3 - .../basic/set06/expected/model_3_2_2_4.eprime | 61 - .../model_3_2_3_1-solution000001.solution | 3 - .../model_3_2_3_1-solution000002.solution | 3 - .../basic/set06/expected/model_3_2_3_1.eprime | 43 - .../model_3_2_3_2-solution000001.solution | 3 - .../model_3_2_3_2-solution000002.solution | 3 - .../basic/set06/expected/model_3_2_3_2.eprime | 30 - .../model_3_2_3_3-solution000001.solution | 3 - .../model_3_2_3_3-solution000002.solution | 3 - .../basic/set06/expected/model_3_2_3_3.eprime | 30 - .../model_3_2_3_4-solution000001.solution | 3 - .../model_3_2_3_4-solution000002.solution | 3 - .../basic/set06/expected/model_3_2_3_4.eprime | 61 - .../model_3_2_4_1-solution000001.solution | 3 - .../model_3_2_4_1-solution000002.solution | 3 - .../basic/set06/expected/model_3_2_4_1.eprime | 78 -- .../model_3_2_4_2-solution000001.solution | 3 - .../model_3_2_4_2-solution000002.solution | 3 - .../basic/set06/expected/model_3_2_4_2.eprime | 61 - .../model_3_2_4_3-solution000001.solution | 3 - .../model_3_2_4_3-solution000002.solution | 3 - .../basic/set06/expected/model_3_2_4_3.eprime | 61 - .../model_3_2_4_4-solution000001.solution | 3 - .../model_3_2_4_4-solution000002.solution | 3 - .../basic/set06/expected/model_3_2_4_4.eprime | 61 - .../model_3_3_1_1-solution000001.solution | 3 - .../model_3_3_1_1-solution000002.solution | 3 - .../basic/set06/expected/model_3_3_1_1.eprime | 22 - .../model_3_3_1_2-solution000001.solution | 3 - .../model_3_3_1_2-solution000002.solution | 3 - .../basic/set06/expected/model_3_3_1_2.eprime | 43 - .../model_3_3_1_3-solution000001.solution | 3 - .../model_3_3_1_3-solution000002.solution | 3 - .../basic/set06/expected/model_3_3_1_3.eprime | 22 - .../model_3_3_1_4-solution000001.solution | 3 - .../model_3_3_1_4-solution000002.solution | 3 - .../basic/set06/expected/model_3_3_1_4.eprime | 48 - .../model_3_3_2_1-solution000001.solution | 3 - .../model_3_3_2_1-solution000002.solution | 3 - .../basic/set06/expected/model_3_3_2_1.eprime | 43 - .../model_3_3_2_2-solution000001.solution | 3 - .../model_3_3_2_2-solution000002.solution | 3 - .../basic/set06/expected/model_3_3_2_2.eprime | 30 - .../model_3_3_2_3-solution000001.solution | 3 - .../model_3_3_2_3-solution000002.solution | 3 - .../basic/set06/expected/model_3_3_2_3.eprime | 30 - .../model_3_3_2_4-solution000001.solution | 3 - .../model_3_3_2_4-solution000002.solution | 3 - .../basic/set06/expected/model_3_3_2_4.eprime | 61 - .../model_3_3_3_1-solution000001.solution | 3 - .../model_3_3_3_1-solution000002.solution | 3 - .../basic/set06/expected/model_3_3_3_1.eprime | 22 - .../model_3_3_3_2-solution000001.solution | 3 - .../model_3_3_3_2-solution000002.solution | 3 - .../basic/set06/expected/model_3_3_3_2.eprime | 30 - .../model_3_3_3_3-solution000001.solution | 3 - .../model_3_3_3_3-solution000002.solution | 3 - .../basic/set06/expected/model_3_3_3_3.eprime | 15 - .../model_3_3_3_4-solution000001.solution | 3 - .../model_3_3_3_4-solution000002.solution | 3 - .../basic/set06/expected/model_3_3_3_4.eprime | 35 - .../model_3_3_4_1-solution000001.solution | 3 - .../model_3_3_4_1-solution000002.solution | 3 - .../basic/set06/expected/model_3_3_4_1.eprime | 48 - .../model_3_3_4_2-solution000001.solution | 3 - .../model_3_3_4_2-solution000002.solution | 3 - .../basic/set06/expected/model_3_3_4_2.eprime | 60 - .../model_3_3_4_3-solution000001.solution | 3 - .../model_3_3_4_3-solution000002.solution | 3 - .../basic/set06/expected/model_3_3_4_3.eprime | 35 - .../model_3_3_4_4-solution000001.solution | 3 - .../model_3_3_4_4-solution000002.solution | 3 - .../basic/set06/expected/model_3_3_4_4.eprime | 35 - .../model_3_4_1_1-solution000001.solution | 3 - .../model_3_4_1_1-solution000002.solution | 3 - .../basic/set06/expected/model_3_4_1_1.eprime | 48 - .../model_3_4_1_2-solution000001.solution | 3 - .../model_3_4_1_2-solution000002.solution | 3 - .../basic/set06/expected/model_3_4_1_2.eprime | 77 -- .../model_3_4_1_3-solution000001.solution | 3 - .../model_3_4_1_3-solution000002.solution | 3 - .../basic/set06/expected/model_3_4_1_3.eprime | 48 - .../model_3_4_1_4-solution000001.solution | 3 - .../model_3_4_1_4-solution000002.solution | 3 - .../basic/set06/expected/model_3_4_1_4.eprime | 48 - .../model_3_4_2_1-solution000001.solution | 3 - .../model_3_4_2_1-solution000002.solution | 3 - .../basic/set06/expected/model_3_4_2_1.eprime | 77 -- .../model_3_4_2_2-solution000001.solution | 3 - .../model_3_4_2_2-solution000002.solution | 3 - .../basic/set06/expected/model_3_4_2_2.eprime | 60 - .../model_3_4_2_3-solution000001.solution | 3 - .../model_3_4_2_3-solution000002.solution | 3 - .../basic/set06/expected/model_3_4_2_3.eprime | 60 - .../model_3_4_2_4-solution000001.solution | 3 - .../model_3_4_2_4-solution000002.solution | 3 - .../basic/set06/expected/model_3_4_2_4.eprime | 60 - .../model_3_4_3_1-solution000001.solution | 3 - .../model_3_4_3_1-solution000002.solution | 3 - .../basic/set06/expected/model_3_4_3_1.eprime | 48 - .../model_3_4_3_2-solution000001.solution | 3 - .../model_3_4_3_2-solution000002.solution | 3 - .../basic/set06/expected/model_3_4_3_2.eprime | 60 - .../model_3_4_3_3-solution000001.solution | 3 - .../model_3_4_3_3-solution000002.solution | 3 - .../basic/set06/expected/model_3_4_3_3.eprime | 35 - .../model_3_4_3_4-solution000001.solution | 3 - .../model_3_4_3_4-solution000002.solution | 3 - .../basic/set06/expected/model_3_4_3_4.eprime | 35 - .../model_3_4_4_1-solution000001.solution | 3 - .../model_3_4_4_1-solution000002.solution | 3 - .../basic/set06/expected/model_3_4_4_1.eprime | 48 - .../model_3_4_4_2-solution000001.solution | 3 - .../model_3_4_4_2-solution000002.solution | 3 - .../basic/set06/expected/model_3_4_4_2.eprime | 60 - .../model_3_4_4_3-solution000001.solution | 3 - .../model_3_4_4_3-solution000002.solution | 3 - .../basic/set06/expected/model_3_4_4_3.eprime | 35 - .../model_3_4_4_4-solution000001.solution | 3 - .../model_3_4_4_4-solution000002.solution | 3 - .../basic/set06/expected/model_3_4_4_4.eprime | 35 - .../model_4_1_1_1-solution000001.solution | 3 - .../model_4_1_1_1-solution000002.solution | 3 - .../basic/set06/expected/model_4_1_1_1.eprime | 23 - .../model_4_1_1_2-solution000001.solution | 3 - .../model_4_1_1_2-solution000002.solution | 3 - .../basic/set06/expected/model_4_1_1_2.eprime | 43 - .../model_4_1_1_3-solution000001.solution | 3 - .../model_4_1_1_3-solution000002.solution | 3 - .../basic/set06/expected/model_4_1_1_3.eprime | 48 - .../model_4_1_1_4-solution000001.solution | 3 - .../model_4_1_1_4-solution000002.solution | 3 - .../basic/set06/expected/model_4_1_1_4.eprime | 23 - .../model_4_1_2_1-solution000001.solution | 3 - .../model_4_1_2_1-solution000002.solution | 3 - .../basic/set06/expected/model_4_1_2_1.eprime | 43 - .../model_4_1_2_2-solution000001.solution | 3 - .../model_4_1_2_2-solution000002.solution | 3 - .../basic/set06/expected/model_4_1_2_2.eprime | 43 - .../model_4_1_2_3-solution000001.solution | 3 - .../model_4_1_2_3-solution000002.solution | 3 - .../basic/set06/expected/model_4_1_2_3.eprime | 77 -- .../model_4_1_2_4-solution000001.solution | 3 - .../model_4_1_2_4-solution000002.solution | 3 - .../basic/set06/expected/model_4_1_2_4.eprime | 43 - .../model_4_1_3_1-solution000001.solution | 3 - .../model_4_1_3_1-solution000002.solution | 3 - .../basic/set06/expected/model_4_1_3_1.eprime | 48 - .../model_4_1_3_2-solution000001.solution | 3 - .../model_4_1_3_2-solution000002.solution | 3 - .../basic/set06/expected/model_4_1_3_2.eprime | 77 -- .../model_4_1_3_3-solution000001.solution | 3 - .../model_4_1_3_3-solution000002.solution | 3 - .../basic/set06/expected/model_4_1_3_3.eprime | 48 - .../model_4_1_3_4-solution000001.solution | 3 - .../model_4_1_3_4-solution000002.solution | 3 - .../basic/set06/expected/model_4_1_3_4.eprime | 48 - .../model_4_1_4_1-solution000001.solution | 3 - .../model_4_1_4_1-solution000002.solution | 3 - .../basic/set06/expected/model_4_1_4_1.eprime | 23 - .../model_4_1_4_2-solution000001.solution | 3 - .../model_4_1_4_2-solution000002.solution | 3 - .../basic/set06/expected/model_4_1_4_2.eprime | 43 - .../model_4_1_4_3-solution000001.solution | 3 - .../model_4_1_4_3-solution000002.solution | 3 - .../basic/set06/expected/model_4_1_4_3.eprime | 48 - .../model_4_1_4_4-solution000001.solution | 3 - .../model_4_1_4_4-solution000002.solution | 3 - .../basic/set06/expected/model_4_1_4_4.eprime | 23 - .../model_4_2_1_1-solution000001.solution | 3 - .../model_4_2_1_1-solution000002.solution | 3 - .../basic/set06/expected/model_4_2_1_1.eprime | 43 - .../model_4_2_1_2-solution000001.solution | 3 - .../model_4_2_1_2-solution000002.solution | 3 - .../basic/set06/expected/model_4_2_1_2.eprime | 43 - .../model_4_2_1_3-solution000001.solution | 3 - .../model_4_2_1_3-solution000002.solution | 3 - .../basic/set06/expected/model_4_2_1_3.eprime | 77 -- .../model_4_2_1_4-solution000001.solution | 3 - .../model_4_2_1_4-solution000002.solution | 3 - .../basic/set06/expected/model_4_2_1_4.eprime | 43 - .../model_4_2_2_1-solution000001.solution | 3 - .../model_4_2_2_1-solution000002.solution | 3 - .../basic/set06/expected/model_4_2_2_1.eprime | 43 - .../model_4_2_2_2-solution000001.solution | 3 - .../model_4_2_2_2-solution000002.solution | 3 - .../basic/set06/expected/model_4_2_2_2.eprime | 31 - .../model_4_2_2_3-solution000001.solution | 3 - .../model_4_2_2_3-solution000002.solution | 3 - .../basic/set06/expected/model_4_2_2_3.eprime | 60 - .../model_4_2_2_4-solution000001.solution | 3 - .../model_4_2_2_4-solution000002.solution | 3 - .../basic/set06/expected/model_4_2_2_4.eprime | 31 - .../model_4_2_3_1-solution000001.solution | 3 - .../model_4_2_3_1-solution000002.solution | 3 - .../basic/set06/expected/model_4_2_3_1.eprime | 77 -- .../model_4_2_3_2-solution000001.solution | 3 - .../model_4_2_3_2-solution000002.solution | 3 - .../basic/set06/expected/model_4_2_3_2.eprime | 60 - .../model_4_2_3_3-solution000001.solution | 3 - .../model_4_2_3_3-solution000002.solution | 3 - .../basic/set06/expected/model_4_2_3_3.eprime | 60 - .../model_4_2_3_4-solution000001.solution | 3 - .../model_4_2_3_4-solution000002.solution | 3 - .../basic/set06/expected/model_4_2_3_4.eprime | 60 - .../model_4_2_4_1-solution000001.solution | 3 - .../model_4_2_4_1-solution000002.solution | 3 - .../basic/set06/expected/model_4_2_4_1.eprime | 43 - .../model_4_2_4_2-solution000001.solution | 3 - .../model_4_2_4_2-solution000002.solution | 3 - .../basic/set06/expected/model_4_2_4_2.eprime | 31 - .../model_4_2_4_3-solution000001.solution | 3 - .../model_4_2_4_3-solution000002.solution | 3 - .../basic/set06/expected/model_4_2_4_3.eprime | 60 - .../model_4_2_4_4-solution000001.solution | 3 - .../model_4_2_4_4-solution000002.solution | 3 - .../basic/set06/expected/model_4_2_4_4.eprime | 31 - .../model_4_3_1_1-solution000001.solution | 3 - .../model_4_3_1_1-solution000002.solution | 3 - .../basic/set06/expected/model_4_3_1_1.eprime | 48 - .../model_4_3_1_2-solution000001.solution | 3 - .../model_4_3_1_2-solution000002.solution | 3 - .../basic/set06/expected/model_4_3_1_2.eprime | 77 -- .../model_4_3_1_3-solution000001.solution | 3 - .../model_4_3_1_3-solution000002.solution | 3 - .../basic/set06/expected/model_4_3_1_3.eprime | 48 - .../model_4_3_1_4-solution000001.solution | 3 - .../model_4_3_1_4-solution000002.solution | 3 - .../basic/set06/expected/model_4_3_1_4.eprime | 48 - .../model_4_3_2_1-solution000001.solution | 3 - .../model_4_3_2_1-solution000002.solution | 3 - .../basic/set06/expected/model_4_3_2_1.eprime | 77 -- .../model_4_3_2_2-solution000001.solution | 3 - .../model_4_3_2_2-solution000002.solution | 3 - .../basic/set06/expected/model_4_3_2_2.eprime | 60 - .../model_4_3_2_3-solution000001.solution | 3 - .../model_4_3_2_3-solution000002.solution | 3 - .../basic/set06/expected/model_4_3_2_3.eprime | 60 - .../model_4_3_2_4-solution000001.solution | 3 - .../model_4_3_2_4-solution000002.solution | 3 - .../basic/set06/expected/model_4_3_2_4.eprime | 60 - .../model_4_3_3_1-solution000001.solution | 3 - .../model_4_3_3_1-solution000002.solution | 3 - .../basic/set06/expected/model_4_3_3_1.eprime | 48 - .../model_4_3_3_2-solution000001.solution | 3 - .../model_4_3_3_2-solution000002.solution | 3 - .../basic/set06/expected/model_4_3_3_2.eprime | 60 - .../model_4_3_3_3-solution000001.solution | 3 - .../model_4_3_3_3-solution000002.solution | 3 - .../basic/set06/expected/model_4_3_3_3.eprime | 35 - .../model_4_3_3_4-solution000001.solution | 3 - .../model_4_3_3_4-solution000002.solution | 3 - .../basic/set06/expected/model_4_3_3_4.eprime | 35 - .../model_4_3_4_1-solution000001.solution | 3 - .../model_4_3_4_1-solution000002.solution | 3 - .../basic/set06/expected/model_4_3_4_1.eprime | 48 - .../model_4_3_4_2-solution000001.solution | 3 - .../model_4_3_4_2-solution000002.solution | 3 - .../basic/set06/expected/model_4_3_4_2.eprime | 60 - .../model_4_3_4_3-solution000001.solution | 3 - .../model_4_3_4_3-solution000002.solution | 3 - .../basic/set06/expected/model_4_3_4_3.eprime | 35 - .../model_4_3_4_4-solution000001.solution | 3 - .../model_4_3_4_4-solution000002.solution | 3 - .../basic/set06/expected/model_4_3_4_4.eprime | 35 - .../model_4_4_1_1-solution000001.solution | 3 - .../model_4_4_1_1-solution000002.solution | 3 - .../basic/set06/expected/model_4_4_1_1.eprime | 23 - .../model_4_4_1_2-solution000001.solution | 3 - .../model_4_4_1_2-solution000002.solution | 3 - .../basic/set06/expected/model_4_4_1_2.eprime | 43 - .../model_4_4_1_3-solution000001.solution | 3 - .../model_4_4_1_3-solution000002.solution | 3 - .../basic/set06/expected/model_4_4_1_3.eprime | 48 - .../model_4_4_1_4-solution000001.solution | 3 - .../model_4_4_1_4-solution000002.solution | 3 - .../basic/set06/expected/model_4_4_1_4.eprime | 23 - .../model_4_4_2_1-solution000001.solution | 3 - .../model_4_4_2_1-solution000002.solution | 3 - .../basic/set06/expected/model_4_4_2_1.eprime | 43 - .../model_4_4_2_2-solution000001.solution | 3 - .../model_4_4_2_2-solution000002.solution | 3 - .../basic/set06/expected/model_4_4_2_2.eprime | 31 - .../model_4_4_2_3-solution000001.solution | 3 - .../model_4_4_2_3-solution000002.solution | 3 - .../basic/set06/expected/model_4_4_2_3.eprime | 60 - .../model_4_4_2_4-solution000001.solution | 3 - .../model_4_4_2_4-solution000002.solution | 3 - .../basic/set06/expected/model_4_4_2_4.eprime | 31 - .../model_4_4_3_1-solution000001.solution | 3 - .../model_4_4_3_1-solution000002.solution | 3 - .../basic/set06/expected/model_4_4_3_1.eprime | 48 - .../model_4_4_3_2-solution000001.solution | 3 - .../model_4_4_3_2-solution000002.solution | 3 - .../basic/set06/expected/model_4_4_3_2.eprime | 60 - .../model_4_4_3_3-solution000001.solution | 3 - .../model_4_4_3_3-solution000002.solution | 3 - .../basic/set06/expected/model_4_4_3_3.eprime | 35 - .../model_4_4_3_4-solution000001.solution | 3 - .../model_4_4_3_4-solution000002.solution | 3 - .../basic/set06/expected/model_4_4_3_4.eprime | 35 - .../model_4_4_4_1-solution000001.solution | 3 - .../model_4_4_4_1-solution000002.solution | 3 - .../basic/set06/expected/model_4_4_4_1.eprime | 23 - .../model_4_4_4_2-solution000001.solution | 3 - .../model_4_4_4_2-solution000002.solution | 3 - .../basic/set06/expected/model_4_4_4_2.eprime | 31 - .../model_4_4_4_3-solution000001.solution | 3 - .../model_4_4_4_3-solution000002.solution | 3 - .../basic/set06/expected/model_4_4_4_3.eprime | 35 - .../model_4_4_4_4-solution000001.solution | 3 - .../model_4_4_4_4-solution000002.solution | 3 - .../basic/set06/expected/model_4_4_4_4.eprime | 16 - .../model_1_1_1-solution000001.solution | 3 - .../basic/set07/expected/model_1_1_1.eprime | 6 - .../model_1_1_2-solution000001.solution | 3 - .../basic/set07/expected/model_1_1_2.eprime | 15 - .../model_1_1_3-solution000001.solution | 3 - .../basic/set07/expected/model_1_1_3.eprime | 18 - .../model_1_1_4-solution000001.solution | 3 - .../basic/set07/expected/model_1_1_4.eprime | 18 - .../model_1_2_1-solution000001.solution | 3 - .../basic/set07/expected/model_1_2_1.eprime | 17 - .../model_1_2_2-solution000001.solution | 3 - .../basic/set07/expected/model_1_2_2.eprime | 17 - .../model_1_2_3-solution000001.solution | 3 - .../basic/set07/expected/model_1_2_3.eprime | 40 - .../model_1_2_4-solution000001.solution | 3 - .../basic/set07/expected/model_1_2_4.eprime | 41 - .../model_1_3_1-solution000001.solution | 3 - .../basic/set07/expected/model_1_3_1.eprime | 21 - .../model_1_3_2-solution000001.solution | 3 - .../basic/set07/expected/model_1_3_2.eprime | 40 - .../model_1_3_3-solution000001.solution | 3 - .../basic/set07/expected/model_1_3_3.eprime | 21 - .../model_1_3_4-solution000001.solution | 3 - .../basic/set07/expected/model_1_3_4.eprime | 46 - .../model_1_4_1-solution000001.solution | 3 - .../basic/set07/expected/model_1_4_1.eprime | 21 - .../model_1_4_2-solution000001.solution | 3 - .../basic/set07/expected/model_1_4_2.eprime | 40 - .../model_1_4_3-solution000001.solution | 3 - .../basic/set07/expected/model_1_4_3.eprime | 45 - .../model_1_4_4-solution000001.solution | 3 - .../basic/set07/expected/model_1_4_4.eprime | 21 - .../model_2_1_1-solution000001.solution | 3 - .../basic/set07/expected/model_2_1_1.eprime | 17 - .../model_2_1_2-solution000001.solution | 3 - .../basic/set07/expected/model_2_1_2.eprime | 17 - .../model_2_1_3-solution000001.solution | 3 - .../basic/set07/expected/model_2_1_3.eprime | 40 - .../model_2_1_4-solution000001.solution | 3 - .../basic/set07/expected/model_2_1_4.eprime | 40 - .../model_2_2_1-solution000001.solution | 3 - .../basic/set07/expected/model_2_2_1.eprime | 17 - .../model_2_2_2-solution000001.solution | 3 - .../basic/set07/expected/model_2_2_2.eprime | 12 - .../model_2_2_3-solution000001.solution | 3 - .../basic/set07/expected/model_2_2_3.eprime | 28 - .../model_2_2_4-solution000001.solution | 3 - .../basic/set07/expected/model_2_2_4.eprime | 29 - .../model_2_3_1-solution000001.solution | 3 - .../basic/set07/expected/model_2_3_1.eprime | 41 - .../model_2_3_2-solution000001.solution | 3 - .../basic/set07/expected/model_2_3_2.eprime | 29 - .../model_2_3_3-solution000001.solution | 3 - .../basic/set07/expected/model_2_3_3.eprime | 29 - .../model_2_3_4-solution000001.solution | 3 - .../basic/set07/expected/model_2_3_4.eprime | 59 - .../model_2_4_1-solution000001.solution | 3 - .../basic/set07/expected/model_2_4_1.eprime | 41 - .../model_2_4_2-solution000001.solution | 3 - .../basic/set07/expected/model_2_4_2.eprime | 30 - .../model_2_4_3-solution000001.solution | 3 - .../basic/set07/expected/model_2_4_3.eprime | 58 - .../model_2_4_4-solution000001.solution | 3 - .../basic/set07/expected/model_2_4_4.eprime | 30 - .../model_3_1_1-solution000001.solution | 3 - .../basic/set07/expected/model_3_1_1.eprime | 22 - .../model_3_1_2-solution000001.solution | 3 - .../basic/set07/expected/model_3_1_2.eprime | 41 - .../model_3_1_3-solution000001.solution | 3 - .../basic/set07/expected/model_3_1_3.eprime | 22 - .../model_3_1_4-solution000001.solution | 3 - .../basic/set07/expected/model_3_1_4.eprime | 46 - .../model_3_2_1-solution000001.solution | 3 - .../basic/set07/expected/model_3_2_1.eprime | 41 - .../model_3_2_2-solution000001.solution | 3 - .../basic/set07/expected/model_3_2_2.eprime | 29 - .../model_3_2_3-solution000001.solution | 3 - .../basic/set07/expected/model_3_2_3.eprime | 29 - .../model_3_2_4-solution000001.solution | 3 - .../basic/set07/expected/model_3_2_4.eprime | 59 - .../model_3_3_1-solution000001.solution | 3 - .../basic/set07/expected/model_3_3_1.eprime | 24 - .../model_3_3_2-solution000001.solution | 3 - .../basic/set07/expected/model_3_3_2.eprime | 31 - .../model_3_3_3-solution000001.solution | 3 - .../basic/set07/expected/model_3_3_3.eprime | 17 - .../model_3_3_4-solution000001.solution | 3 - .../basic/set07/expected/model_3_3_4.eprime | 36 - .../model_3_4_1-solution000001.solution | 3 - .../basic/set07/expected/model_3_4_1.eprime | 48 - .../model_3_4_2-solution000001.solution | 3 - .../basic/set07/expected/model_3_4_2.eprime | 60 - .../model_3_4_3-solution000001.solution | 3 - .../basic/set07/expected/model_3_4_3.eprime | 36 - .../model_3_4_4-solution000001.solution | 3 - .../basic/set07/expected/model_3_4_4.eprime | 36 - .../model_4_1_1-solution000001.solution | 3 - .../basic/set07/expected/model_4_1_1.eprime | 21 - .../model_4_1_2-solution000001.solution | 3 - .../basic/set07/expected/model_4_1_2.eprime | 40 - .../model_4_1_3-solution000001.solution | 3 - .../basic/set07/expected/model_4_1_3.eprime | 45 - .../model_4_1_4-solution000001.solution | 3 - .../basic/set07/expected/model_4_1_4.eprime | 21 - .../model_4_2_1-solution000001.solution | 3 - .../basic/set07/expected/model_4_2_1.eprime | 40 - .../model_4_2_2-solution000001.solution | 3 - .../basic/set07/expected/model_4_2_2.eprime | 29 - .../model_4_2_3-solution000001.solution | 3 - .../basic/set07/expected/model_4_2_3.eprime | 57 - .../model_4_2_4-solution000001.solution | 3 - .../basic/set07/expected/model_4_2_4.eprime | 29 - .../model_4_3_1-solution000001.solution | 3 - .../basic/set07/expected/model_4_3_1.eprime | 47 - .../model_4_3_2-solution000001.solution | 3 - .../basic/set07/expected/model_4_3_2.eprime | 59 - .../model_4_3_3-solution000001.solution | 3 - .../basic/set07/expected/model_4_3_3.eprime | 35 - .../model_4_3_4-solution000001.solution | 3 - .../basic/set07/expected/model_4_3_4.eprime | 35 - .../model_4_4_1-solution000001.solution | 3 - .../basic/set07/expected/model_4_4_1.eprime | 23 - .../model_4_4_2-solution000001.solution | 3 - .../basic/set07/expected/model_4_4_2.eprime | 31 - .../model_4_4_3-solution000001.solution | 3 - .../basic/set07/expected/model_4_4_3.eprime | 35 - .../model_4_4_4-solution000001.solution | 3 - .../basic/set07/expected/model_4_4_4.eprime | 15 - .../model_1_1-solution000001.solution | 7 - .../basic/set08/expected/model_1_1.eprime | 25 - .../model_1_2-solution000001.solution | 7 - .../basic/set08/expected/model_1_2.eprime | 54 - .../model_2_1-solution000001.solution | 7 - .../basic/set08/expected/model_2_1.eprime | 54 - .../model_2_2-solution000001.solution | 7 - .../basic/set08/expected/model_2_2.eprime | 25 - .../model_1_1_1_1-solution000001.solution | 4 - .../model_1_1_1_1-solution000002.solution | 4 - .../basic/set09/expected/model_1_1_1_1.eprime | 10 - .../model_1_1_1_2-solution000001.solution | 4 - .../model_1_1_1_2-solution000002.solution | 4 - .../basic/set09/expected/model_1_1_1_2.eprime | 19 - .../model_1_1_1_3-solution000001.solution | 4 - .../model_1_1_1_3-solution000002.solution | 4 - .../basic/set09/expected/model_1_1_1_3.eprime | 23 - .../model_1_1_1_4-solution000001.solution | 4 - .../model_1_1_1_4-solution000002.solution | 4 - .../basic/set09/expected/model_1_1_1_4.eprime | 22 - .../model_1_1_2_1-solution000001.solution | 4 - .../model_1_1_2_1-solution000002.solution | 4 - .../basic/set09/expected/model_1_1_2_1.eprime | 19 - .../model_1_1_2_2-solution000001.solution | 4 - .../model_1_1_2_2-solution000002.solution | 4 - .../basic/set09/expected/model_1_1_2_2.eprime | 28 - .../model_1_1_2_3-solution000001.solution | 4 - .../model_1_1_2_3-solution000002.solution | 4 - .../basic/set09/expected/model_1_1_2_3.eprime | 34 - .../model_1_1_2_4-solution000001.solution | 4 - .../model_1_1_2_4-solution000002.solution | 4 - .../basic/set09/expected/model_1_1_2_4.eprime | 35 - .../model_1_1_3_1-solution000001.solution | 4 - .../model_1_1_3_1-solution000002.solution | 4 - .../basic/set09/expected/model_1_1_3_1.eprime | 23 - .../model_1_1_3_2-solution000001.solution | 4 - .../model_1_1_3_2-solution000002.solution | 4 - .../basic/set09/expected/model_1_1_3_2.eprime | 34 - .../model_1_1_3_3-solution000001.solution | 4 - .../model_1_1_3_3-solution000002.solution | 4 - .../basic/set09/expected/model_1_1_3_3.eprime | 38 - .../model_1_1_3_4-solution000001.solution | 4 - .../model_1_1_3_4-solution000002.solution | 4 - .../basic/set09/expected/model_1_1_3_4.eprime | 39 - .../model_1_1_4_1-solution000001.solution | 4 - .../model_1_1_4_1-solution000002.solution | 4 - .../basic/set09/expected/model_1_1_4_1.eprime | 22 - .../model_1_1_4_2-solution000001.solution | 4 - .../model_1_1_4_2-solution000002.solution | 4 - .../basic/set09/expected/model_1_1_4_2.eprime | 33 - .../model_1_1_4_3-solution000001.solution | 4 - .../model_1_1_4_3-solution000002.solution | 4 - .../basic/set09/expected/model_1_1_4_3.eprime | 37 - .../model_1_1_4_4-solution000001.solution | 4 - .../model_1_1_4_4-solution000002.solution | 4 - .../basic/set09/expected/model_1_1_4_4.eprime | 38 - .../model_1_2_1_1-solution000001.solution | 4 - .../model_1_2_1_1-solution000002.solution | 4 - .../basic/set09/expected/model_1_2_1_1.eprime | 20 - .../model_1_2_1_2-solution000001.solution | 4 - .../model_1_2_1_2-solution000002.solution | 4 - .../basic/set09/expected/model_1_2_1_2.eprime | 14 - .../model_1_2_1_3-solution000001.solution | 4 - .../model_1_2_1_3-solution000002.solution | 4 - .../basic/set09/expected/model_1_2_1_3.eprime | 32 - .../model_1_2_1_4-solution000001.solution | 4 - .../model_1_2_1_4-solution000002.solution | 4 - .../basic/set09/expected/model_1_2_1_4.eprime | 33 - .../model_1_2_2_1-solution000001.solution | 4 - .../model_1_2_2_1-solution000002.solution | 4 - .../basic/set09/expected/model_1_2_2_1.eprime | 29 - .../model_1_2_2_2-solution000001.solution | 4 - .../model_1_2_2_2-solution000002.solution | 4 - .../basic/set09/expected/model_1_2_2_2.eprime | 23 - .../model_1_2_2_3-solution000001.solution | 4 - .../model_1_2_2_3-solution000002.solution | 4 - .../basic/set09/expected/model_1_2_2_3.eprime | 42 - .../model_1_2_2_4-solution000001.solution | 4 - .../model_1_2_2_4-solution000002.solution | 4 - .../basic/set09/expected/model_1_2_2_4.eprime | 44 - .../model_1_2_3_1-solution000001.solution | 4 - .../model_1_2_3_1-solution000002.solution | 4 - .../basic/set09/expected/model_1_2_3_1.eprime | 35 - .../model_1_2_3_2-solution000001.solution | 4 - .../model_1_2_3_2-solution000002.solution | 4 - .../basic/set09/expected/model_1_2_3_2.eprime | 28 - .../model_1_2_3_3-solution000001.solution | 4 - .../model_1_2_3_3-solution000002.solution | 4 - .../basic/set09/expected/model_1_2_3_3.eprime | 46 - .../model_1_2_3_4-solution000001.solution | 4 - .../model_1_2_3_4-solution000002.solution | 4 - .../basic/set09/expected/model_1_2_3_4.eprime | 48 - .../model_1_2_4_1-solution000001.solution | 4 - .../model_1_2_4_1-solution000002.solution | 4 - .../basic/set09/expected/model_1_2_4_1.eprime | 35 - .../model_1_2_4_2-solution000001.solution | 4 - .../model_1_2_4_2-solution000002.solution | 4 - .../basic/set09/expected/model_1_2_4_2.eprime | 28 - .../model_1_2_4_3-solution000001.solution | 4 - .../model_1_2_4_3-solution000002.solution | 4 - .../basic/set09/expected/model_1_2_4_3.eprime | 46 - .../model_1_2_4_4-solution000001.solution | 4 - .../model_1_2_4_4-solution000002.solution | 4 - .../basic/set09/expected/model_1_2_4_4.eprime | 48 - .../model_1_3_1_1-solution000001.solution | 4 - .../model_1_3_1_1-solution000002.solution | 4 - .../basic/set09/expected/model_1_3_1_1.eprime | 23 - .../model_1_3_1_2-solution000001.solution | 4 - .../model_1_3_1_2-solution000002.solution | 4 - .../basic/set09/expected/model_1_3_1_2.eprime | 32 - .../model_1_3_1_3-solution000001.solution | 4 - .../model_1_3_1_3-solution000002.solution | 4 - .../basic/set09/expected/model_1_3_1_3.eprime | 16 - .../model_1_3_1_4-solution000001.solution | 4 - .../model_1_3_1_4-solution000002.solution | 4 - .../basic/set09/expected/model_1_3_1_4.eprime | 36 - .../model_1_3_2_1-solution000001.solution | 4 - .../model_1_3_2_1-solution000002.solution | 4 - .../basic/set09/expected/model_1_3_2_1.eprime | 35 - .../model_1_3_2_2-solution000001.solution | 4 - .../model_1_3_2_2-solution000002.solution | 4 - .../basic/set09/expected/model_1_3_2_2.eprime | 42 - .../model_1_3_2_3-solution000001.solution | 4 - .../model_1_3_2_3-solution000002.solution | 4 - .../basic/set09/expected/model_1_3_2_3.eprime | 26 - .../model_1_3_2_4-solution000001.solution | 4 - .../model_1_3_2_4-solution000002.solution | 4 - .../basic/set09/expected/model_1_3_2_4.eprime | 46 - .../model_1_3_3_1-solution000001.solution | 4 - .../model_1_3_3_1-solution000002.solution | 4 - .../basic/set09/expected/model_1_3_3_1.eprime | 39 - .../model_1_3_3_2-solution000001.solution | 4 - .../model_1_3_3_2-solution000002.solution | 4 - .../basic/set09/expected/model_1_3_3_2.eprime | 46 - .../model_1_3_3_3-solution000001.solution | 4 - .../model_1_3_3_3-solution000002.solution | 4 - .../basic/set09/expected/model_1_3_3_3.eprime | 31 - .../model_1_3_3_4-solution000001.solution | 4 - .../model_1_3_3_4-solution000002.solution | 4 - .../basic/set09/expected/model_1_3_3_4.eprime | 51 - .../model_1_3_4_1-solution000001.solution | 4 - .../model_1_3_4_1-solution000002.solution | 4 - .../basic/set09/expected/model_1_3_4_1.eprime | 39 - .../model_1_3_4_2-solution000001.solution | 4 - .../model_1_3_4_2-solution000002.solution | 4 - .../basic/set09/expected/model_1_3_4_2.eprime | 46 - .../model_1_3_4_3-solution000001.solution | 4 - .../model_1_3_4_3-solution000002.solution | 4 - .../basic/set09/expected/model_1_3_4_3.eprime | 31 - .../model_1_3_4_4-solution000001.solution | 4 - .../model_1_3_4_4-solution000002.solution | 4 - .../basic/set09/expected/model_1_3_4_4.eprime | 51 - .../model_1_4_1_1-solution000001.solution | 4 - .../model_1_4_1_1-solution000002.solution | 4 - .../basic/set09/expected/model_1_4_1_1.eprime | 24 - .../model_1_4_1_2-solution000001.solution | 4 - .../model_1_4_1_2-solution000002.solution | 4 - .../basic/set09/expected/model_1_4_1_2.eprime | 33 - .../model_1_4_1_3-solution000001.solution | 4 - .../model_1_4_1_3-solution000002.solution | 4 - .../basic/set09/expected/model_1_4_1_3.eprime | 36 - .../model_1_4_1_4-solution000001.solution | 4 - .../model_1_4_1_4-solution000002.solution | 4 - .../basic/set09/expected/model_1_4_1_4.eprime | 17 - .../model_1_4_2_1-solution000001.solution | 4 - .../model_1_4_2_1-solution000002.solution | 4 - .../basic/set09/expected/model_1_4_2_1.eprime | 35 - .../model_1_4_2_2-solution000001.solution | 4 - .../model_1_4_2_2-solution000002.solution | 4 - .../basic/set09/expected/model_1_4_2_2.eprime | 43 - .../model_1_4_2_3-solution000001.solution | 4 - .../model_1_4_2_3-solution000002.solution | 4 - .../basic/set09/expected/model_1_4_2_3.eprime | 45 - .../model_1_4_2_4-solution000001.solution | 4 - .../model_1_4_2_4-solution000002.solution | 4 - .../basic/set09/expected/model_1_4_2_4.eprime | 27 - .../model_1_4_3_1-solution000001.solution | 4 - .../model_1_4_3_1-solution000002.solution | 4 - .../basic/set09/expected/model_1_4_3_1.eprime | 39 - .../model_1_4_3_2-solution000001.solution | 4 - .../model_1_4_3_2-solution000002.solution | 4 - .../basic/set09/expected/model_1_4_3_2.eprime | 47 - .../model_1_4_3_3-solution000001.solution | 4 - .../model_1_4_3_3-solution000002.solution | 4 - .../basic/set09/expected/model_1_4_3_3.eprime | 50 - .../model_1_4_3_4-solution000001.solution | 4 - .../model_1_4_3_4-solution000002.solution | 4 - .../basic/set09/expected/model_1_4_3_4.eprime | 32 - .../model_1_4_4_1-solution000001.solution | 4 - .../model_1_4_4_1-solution000002.solution | 4 - .../basic/set09/expected/model_1_4_4_1.eprime | 39 - .../model_1_4_4_2-solution000001.solution | 4 - .../model_1_4_4_2-solution000002.solution | 4 - .../basic/set09/expected/model_1_4_4_2.eprime | 47 - .../model_1_4_4_3-solution000001.solution | 4 - .../model_1_4_4_3-solution000002.solution | 4 - .../basic/set09/expected/model_1_4_4_3.eprime | 50 - .../model_1_4_4_4-solution000001.solution | 4 - .../model_1_4_4_4-solution000002.solution | 4 - .../basic/set09/expected/model_1_4_4_4.eprime | 32 - .../model_2_1_1_1-solution000001.solution | 4 - .../model_2_1_1_1-solution000002.solution | 4 - .../basic/set09/expected/model_2_1_1_1.eprime | 20 - .../model_2_1_1_2-solution000001.solution | 4 - .../model_2_1_1_2-solution000002.solution | 4 - .../basic/set09/expected/model_2_1_1_2.eprime | 29 - .../model_2_1_1_3-solution000001.solution | 4 - .../model_2_1_1_3-solution000002.solution | 4 - .../basic/set09/expected/model_2_1_1_3.eprime | 35 - .../model_2_1_1_4-solution000001.solution | 4 - .../model_2_1_1_4-solution000002.solution | 4 - .../basic/set09/expected/model_2_1_1_4.eprime | 35 - .../model_2_1_2_1-solution000001.solution | 4 - .../model_2_1_2_1-solution000002.solution | 4 - .../basic/set09/expected/model_2_1_2_1.eprime | 14 - .../model_2_1_2_2-solution000001.solution | 4 - .../model_2_1_2_2-solution000002.solution | 4 - .../basic/set09/expected/model_2_1_2_2.eprime | 23 - .../model_2_1_2_3-solution000001.solution | 4 - .../model_2_1_2_3-solution000002.solution | 4 - .../basic/set09/expected/model_2_1_2_3.eprime | 28 - .../model_2_1_2_4-solution000001.solution | 4 - .../model_2_1_2_4-solution000002.solution | 4 - .../basic/set09/expected/model_2_1_2_4.eprime | 28 - .../model_2_1_3_1-solution000001.solution | 4 - .../model_2_1_3_1-solution000002.solution | 4 - .../basic/set09/expected/model_2_1_3_1.eprime | 32 - .../model_2_1_3_2-solution000001.solution | 4 - .../model_2_1_3_2-solution000002.solution | 4 - .../basic/set09/expected/model_2_1_3_2.eprime | 42 - .../model_2_1_3_3-solution000001.solution | 4 - .../model_2_1_3_3-solution000002.solution | 4 - .../basic/set09/expected/model_2_1_3_3.eprime | 46 - .../model_2_1_3_4-solution000001.solution | 4 - .../model_2_1_3_4-solution000002.solution | 4 - .../basic/set09/expected/model_2_1_3_4.eprime | 47 - .../model_2_1_4_1-solution000001.solution | 4 - .../model_2_1_4_1-solution000002.solution | 4 - .../basic/set09/expected/model_2_1_4_1.eprime | 33 - .../model_2_1_4_2-solution000001.solution | 4 - .../model_2_1_4_2-solution000002.solution | 4 - .../basic/set09/expected/model_2_1_4_2.eprime | 43 - .../model_2_1_4_3-solution000001.solution | 4 - .../model_2_1_4_3-solution000002.solution | 4 - .../basic/set09/expected/model_2_1_4_3.eprime | 47 - .../model_2_1_4_4-solution000001.solution | 4 - .../model_2_1_4_4-solution000002.solution | 4 - .../basic/set09/expected/model_2_1_4_4.eprime | 48 - .../model_2_2_1_1-solution000001.solution | 4 - .../model_2_2_1_1-solution000002.solution | 4 - .../basic/set09/expected/model_2_2_1_1.eprime | 30 - .../model_2_2_1_2-solution000001.solution | 4 - .../model_2_2_1_2-solution000002.solution | 4 - .../basic/set09/expected/model_2_2_1_2.eprime | 24 - .../model_2_2_1_3-solution000001.solution | 4 - .../model_2_2_1_3-solution000002.solution | 4 - .../basic/set09/expected/model_2_2_1_3.eprime | 43 - .../model_2_2_1_4-solution000001.solution | 4 - .../model_2_2_1_4-solution000002.solution | 4 - .../basic/set09/expected/model_2_2_1_4.eprime | 45 - .../model_2_2_2_1-solution000001.solution | 4 - .../model_2_2_2_1-solution000002.solution | 4 - .../basic/set09/expected/model_2_2_2_1.eprime | 24 - .../model_2_2_2_2-solution000001.solution | 4 - .../model_2_2_2_2-solution000002.solution | 4 - .../basic/set09/expected/model_2_2_2_2.eprime | 18 - .../model_2_2_2_3-solution000001.solution | 4 - .../model_2_2_2_3-solution000002.solution | 4 - .../basic/set09/expected/model_2_2_2_3.eprime | 37 - .../model_2_2_2_4-solution000001.solution | 4 - .../model_2_2_2_4-solution000002.solution | 4 - .../basic/set09/expected/model_2_2_2_4.eprime | 39 - .../model_2_2_3_1-solution000001.solution | 4 - .../model_2_2_3_1-solution000002.solution | 4 - .../basic/set09/expected/model_2_2_3_1.eprime | 43 - .../model_2_2_3_2-solution000001.solution | 4 - .../model_2_2_3_2-solution000002.solution | 4 - .../basic/set09/expected/model_2_2_3_2.eprime | 37 - .../model_2_2_3_3-solution000001.solution | 4 - .../model_2_2_3_3-solution000002.solution | 4 - .../basic/set09/expected/model_2_2_3_3.eprime | 54 - .../model_2_2_3_4-solution000001.solution | 4 - .../model_2_2_3_4-solution000002.solution | 4 - .../basic/set09/expected/model_2_2_3_4.eprime | 56 - .../model_2_2_4_1-solution000001.solution | 4 - .../model_2_2_4_1-solution000002.solution | 4 - .../basic/set09/expected/model_2_2_4_1.eprime | 45 - .../model_2_2_4_2-solution000001.solution | 4 - .../model_2_2_4_2-solution000002.solution | 4 - .../basic/set09/expected/model_2_2_4_2.eprime | 39 - .../model_2_2_4_3-solution000001.solution | 4 - .../model_2_2_4_3-solution000002.solution | 4 - .../basic/set09/expected/model_2_2_4_3.eprime | 56 - .../model_2_2_4_4-solution000001.solution | 4 - .../model_2_2_4_4-solution000002.solution | 4 - .../basic/set09/expected/model_2_2_4_4.eprime | 58 - .../model_2_3_1_1-solution000001.solution | 4 - .../model_2_3_1_1-solution000002.solution | 4 - .../basic/set09/expected/model_2_3_1_1.eprime | 36 - .../model_2_3_1_2-solution000001.solution | 4 - .../model_2_3_1_2-solution000002.solution | 4 - .../basic/set09/expected/model_2_3_1_2.eprime | 43 - .../model_2_3_1_3-solution000001.solution | 4 - .../model_2_3_1_3-solution000002.solution | 4 - .../basic/set09/expected/model_2_3_1_3.eprime | 27 - .../model_2_3_1_4-solution000001.solution | 4 - .../model_2_3_1_4-solution000002.solution | 4 - .../basic/set09/expected/model_2_3_1_4.eprime | 47 - .../model_2_3_2_1-solution000001.solution | 4 - .../model_2_3_2_1-solution000002.solution | 4 - .../basic/set09/expected/model_2_3_2_1.eprime | 29 - .../model_2_3_2_2-solution000001.solution | 4 - .../model_2_3_2_2-solution000002.solution | 4 - .../basic/set09/expected/model_2_3_2_2.eprime | 37 - .../model_2_3_2_3-solution000001.solution | 4 - .../model_2_3_2_3-solution000002.solution | 4 - .../basic/set09/expected/model_2_3_2_3.eprime | 20 - .../model_2_3_2_4-solution000001.solution | 4 - .../model_2_3_2_4-solution000002.solution | 4 - .../basic/set09/expected/model_2_3_2_4.eprime | 40 - .../model_2_3_3_1-solution000001.solution | 4 - .../model_2_3_3_1-solution000002.solution | 4 - .../basic/set09/expected/model_2_3_3_1.eprime | 47 - .../model_2_3_3_2-solution000001.solution | 4 - .../model_2_3_3_2-solution000002.solution | 4 - .../basic/set09/expected/model_2_3_3_2.eprime | 54 - .../model_2_3_3_3-solution000001.solution | 4 - .../model_2_3_3_3-solution000002.solution | 4 - .../basic/set09/expected/model_2_3_3_3.eprime | 39 - .../model_2_3_3_4-solution000001.solution | 4 - .../model_2_3_3_4-solution000002.solution | 4 - .../basic/set09/expected/model_2_3_3_4.eprime | 59 - .../model_2_3_4_1-solution000001.solution | 4 - .../model_2_3_4_1-solution000002.solution | 4 - .../basic/set09/expected/model_2_3_4_1.eprime | 48 - .../model_2_3_4_2-solution000001.solution | 4 - .../model_2_3_4_2-solution000002.solution | 4 - .../basic/set09/expected/model_2_3_4_2.eprime | 55 - .../model_2_3_4_3-solution000001.solution | 4 - .../model_2_3_4_3-solution000002.solution | 4 - .../basic/set09/expected/model_2_3_4_3.eprime | 40 - .../model_2_3_4_4-solution000001.solution | 4 - .../model_2_3_4_4-solution000002.solution | 4 - .../basic/set09/expected/model_2_3_4_4.eprime | 60 - .../model_2_4_1_1-solution000001.solution | 4 - .../model_2_4_1_1-solution000002.solution | 4 - .../basic/set09/expected/model_2_4_1_1.eprime | 36 - .../model_2_4_1_2-solution000001.solution | 4 - .../model_2_4_1_2-solution000002.solution | 4 - .../basic/set09/expected/model_2_4_1_2.eprime | 44 - .../model_2_4_1_3-solution000001.solution | 4 - .../model_2_4_1_3-solution000002.solution | 4 - .../basic/set09/expected/model_2_4_1_3.eprime | 46 - .../model_2_4_1_4-solution000001.solution | 4 - .../model_2_4_1_4-solution000002.solution | 4 - .../basic/set09/expected/model_2_4_1_4.eprime | 28 - .../model_2_4_2_1-solution000001.solution | 4 - .../model_2_4_2_1-solution000002.solution | 4 - .../basic/set09/expected/model_2_4_2_1.eprime | 29 - .../model_2_4_2_2-solution000001.solution | 4 - .../model_2_4_2_2-solution000002.solution | 4 - .../basic/set09/expected/model_2_4_2_2.eprime | 38 - .../model_2_4_2_3-solution000001.solution | 4 - .../model_2_4_2_3-solution000002.solution | 4 - .../basic/set09/expected/model_2_4_2_3.eprime | 40 - .../model_2_4_2_4-solution000001.solution | 4 - .../model_2_4_2_4-solution000002.solution | 4 - .../basic/set09/expected/model_2_4_2_4.eprime | 21 - .../model_2_4_3_1-solution000001.solution | 4 - .../model_2_4_3_1-solution000002.solution | 4 - .../basic/set09/expected/model_2_4_3_1.eprime | 47 - .../model_2_4_3_2-solution000001.solution | 4 - .../model_2_4_3_2-solution000002.solution | 4 - .../basic/set09/expected/model_2_4_3_2.eprime | 55 - .../model_2_4_3_3-solution000001.solution | 4 - .../model_2_4_3_3-solution000002.solution | 4 - .../basic/set09/expected/model_2_4_3_3.eprime | 58 - .../model_2_4_3_4-solution000001.solution | 4 - .../model_2_4_3_4-solution000002.solution | 4 - .../basic/set09/expected/model_2_4_3_4.eprime | 40 - .../model_2_4_4_1-solution000001.solution | 4 - .../model_2_4_4_1-solution000002.solution | 4 - .../basic/set09/expected/model_2_4_4_1.eprime | 49 - .../model_2_4_4_2-solution000001.solution | 4 - .../model_2_4_4_2-solution000002.solution | 4 - .../basic/set09/expected/model_2_4_4_2.eprime | 57 - .../model_2_4_4_3-solution000001.solution | 4 - .../model_2_4_4_3-solution000002.solution | 4 - .../basic/set09/expected/model_2_4_4_3.eprime | 60 - .../model_2_4_4_4-solution000001.solution | 4 - .../model_2_4_4_4-solution000002.solution | 4 - .../basic/set09/expected/model_2_4_4_4.eprime | 42 - .../model_3_1_1_1-solution000001.solution | 4 - .../model_3_1_1_1-solution000002.solution | 4 - .../basic/set09/expected/model_3_1_1_1.eprime | 23 - .../model_3_1_1_2-solution000001.solution | 4 - .../model_3_1_1_2-solution000002.solution | 4 - .../basic/set09/expected/model_3_1_1_2.eprime | 35 - .../model_3_1_1_3-solution000001.solution | 4 - .../model_3_1_1_3-solution000002.solution | 4 - .../basic/set09/expected/model_3_1_1_3.eprime | 39 - .../model_3_1_1_4-solution000001.solution | 4 - .../model_3_1_1_4-solution000002.solution | 4 - .../basic/set09/expected/model_3_1_1_4.eprime | 39 - .../model_3_1_2_1-solution000001.solution | 4 - .../model_3_1_2_1-solution000002.solution | 4 - .../basic/set09/expected/model_3_1_2_1.eprime | 32 - .../model_3_1_2_2-solution000001.solution | 4 - .../model_3_1_2_2-solution000002.solution | 4 - .../basic/set09/expected/model_3_1_2_2.eprime | 42 - .../model_3_1_2_3-solution000001.solution | 4 - .../model_3_1_2_3-solution000002.solution | 4 - .../basic/set09/expected/model_3_1_2_3.eprime | 46 - .../model_3_1_2_4-solution000001.solution | 4 - .../model_3_1_2_4-solution000002.solution | 4 - .../basic/set09/expected/model_3_1_2_4.eprime | 47 - .../model_3_1_3_1-solution000001.solution | 4 - .../model_3_1_3_1-solution000002.solution | 4 - .../basic/set09/expected/model_3_1_3_1.eprime | 16 - .../model_3_1_3_2-solution000001.solution | 4 - .../model_3_1_3_2-solution000002.solution | 4 - .../basic/set09/expected/model_3_1_3_2.eprime | 26 - .../model_3_1_3_3-solution000001.solution | 4 - .../model_3_1_3_3-solution000002.solution | 4 - .../basic/set09/expected/model_3_1_3_3.eprime | 31 - .../model_3_1_3_4-solution000001.solution | 4 - .../model_3_1_3_4-solution000002.solution | 4 - .../basic/set09/expected/model_3_1_3_4.eprime | 31 - .../model_3_1_4_1-solution000001.solution | 4 - .../model_3_1_4_1-solution000002.solution | 4 - .../basic/set09/expected/model_3_1_4_1.eprime | 36 - .../model_3_1_4_2-solution000001.solution | 4 - .../model_3_1_4_2-solution000002.solution | 4 - .../basic/set09/expected/model_3_1_4_2.eprime | 45 - .../model_3_1_4_3-solution000001.solution | 4 - .../model_3_1_4_3-solution000002.solution | 4 - .../basic/set09/expected/model_3_1_4_3.eprime | 50 - .../model_3_1_4_4-solution000001.solution | 4 - .../model_3_1_4_4-solution000002.solution | 4 - .../basic/set09/expected/model_3_1_4_4.eprime | 51 - .../model_3_2_1_1-solution000001.solution | 4 - .../model_3_2_1_1-solution000002.solution | 4 - .../basic/set09/expected/model_3_2_1_1.eprime | 36 - .../model_3_2_1_2-solution000001.solution | 4 - .../model_3_2_1_2-solution000002.solution | 4 - .../basic/set09/expected/model_3_2_1_2.eprime | 29 - .../model_3_2_1_3-solution000001.solution | 4 - .../model_3_2_1_3-solution000002.solution | 4 - .../basic/set09/expected/model_3_2_1_3.eprime | 47 - .../model_3_2_1_4-solution000001.solution | 4 - .../model_3_2_1_4-solution000002.solution | 4 - .../basic/set09/expected/model_3_2_1_4.eprime | 49 - .../model_3_2_2_1-solution000001.solution | 4 - .../model_3_2_2_1-solution000002.solution | 4 - .../basic/set09/expected/model_3_2_2_1.eprime | 43 - .../model_3_2_2_2-solution000001.solution | 4 - .../model_3_2_2_2-solution000002.solution | 4 - .../basic/set09/expected/model_3_2_2_2.eprime | 37 - .../model_3_2_2_3-solution000001.solution | 4 - .../model_3_2_2_3-solution000002.solution | 4 - .../basic/set09/expected/model_3_2_2_3.eprime | 54 - .../model_3_2_2_4-solution000001.solution | 4 - .../model_3_2_2_4-solution000002.solution | 4 - .../basic/set09/expected/model_3_2_2_4.eprime | 56 - .../model_3_2_3_1-solution000001.solution | 4 - .../model_3_2_3_1-solution000002.solution | 4 - .../basic/set09/expected/model_3_2_3_1.eprime | 27 - .../model_3_2_3_2-solution000001.solution | 4 - .../model_3_2_3_2-solution000002.solution | 4 - .../basic/set09/expected/model_3_2_3_2.eprime | 20 - .../model_3_2_3_3-solution000001.solution | 4 - .../model_3_2_3_3-solution000002.solution | 4 - .../basic/set09/expected/model_3_2_3_3.eprime | 39 - .../model_3_2_3_4-solution000001.solution | 4 - .../model_3_2_3_4-solution000002.solution | 4 - .../basic/set09/expected/model_3_2_3_4.eprime | 40 - .../model_3_2_4_1-solution000001.solution | 4 - .../model_3_2_4_1-solution000002.solution | 4 - .../basic/set09/expected/model_3_2_4_1.eprime | 46 - .../model_3_2_4_2-solution000001.solution | 4 - .../model_3_2_4_2-solution000002.solution | 4 - .../basic/set09/expected/model_3_2_4_2.eprime | 40 - .../model_3_2_4_3-solution000001.solution | 4 - .../model_3_2_4_3-solution000002.solution | 4 - .../basic/set09/expected/model_3_2_4_3.eprime | 58 - .../model_3_2_4_4-solution000001.solution | 4 - .../model_3_2_4_4-solution000002.solution | 4 - .../basic/set09/expected/model_3_2_4_4.eprime | 60 - .../model_3_3_1_1-solution000001.solution | 4 - .../model_3_3_1_1-solution000002.solution | 4 - .../basic/set09/expected/model_3_3_1_1.eprime | 40 - .../model_3_3_1_2-solution000001.solution | 4 - .../model_3_3_1_2-solution000002.solution | 4 - .../basic/set09/expected/model_3_3_1_2.eprime | 47 - .../model_3_3_1_3-solution000001.solution | 4 - .../model_3_3_1_3-solution000002.solution | 4 - .../basic/set09/expected/model_3_3_1_3.eprime | 32 - .../model_3_3_1_4-solution000001.solution | 4 - .../model_3_3_1_4-solution000002.solution | 4 - .../basic/set09/expected/model_3_3_1_4.eprime | 51 - .../model_3_3_2_1-solution000001.solution | 4 - .../model_3_3_2_1-solution000002.solution | 4 - .../basic/set09/expected/model_3_3_2_1.eprime | 47 - .../model_3_3_2_2-solution000001.solution | 4 - .../model_3_3_2_2-solution000002.solution | 4 - .../basic/set09/expected/model_3_3_2_2.eprime | 54 - .../model_3_3_2_3-solution000001.solution | 4 - .../model_3_3_2_3-solution000002.solution | 4 - .../basic/set09/expected/model_3_3_2_3.eprime | 39 - .../model_3_3_2_4-solution000001.solution | 4 - .../model_3_3_2_4-solution000002.solution | 4 - .../basic/set09/expected/model_3_3_2_4.eprime | 59 - .../model_3_3_3_1-solution000001.solution | 4 - .../model_3_3_3_1-solution000002.solution | 4 - .../basic/set09/expected/model_3_3_3_1.eprime | 32 - .../model_3_3_3_2-solution000001.solution | 4 - .../model_3_3_3_2-solution000002.solution | 4 - .../basic/set09/expected/model_3_3_3_2.eprime | 39 - .../model_3_3_3_3-solution000001.solution | 4 - .../model_3_3_3_3-solution000002.solution | 4 - .../basic/set09/expected/model_3_3_3_3.eprime | 24 - .../model_3_3_3_4-solution000001.solution | 4 - .../model_3_3_3_4-solution000002.solution | 4 - .../basic/set09/expected/model_3_3_3_4.eprime | 42 - .../model_3_3_4_1-solution000001.solution | 4 - .../model_3_3_4_1-solution000002.solution | 4 - .../basic/set09/expected/model_3_3_4_1.eprime | 51 - .../model_3_3_4_2-solution000001.solution | 4 - .../model_3_3_4_2-solution000002.solution | 4 - .../basic/set09/expected/model_3_3_4_2.eprime | 58 - .../model_3_3_4_3-solution000001.solution | 4 - .../model_3_3_4_3-solution000002.solution | 4 - .../basic/set09/expected/model_3_3_4_3.eprime | 42 - .../model_3_3_4_4-solution000001.solution | 4 - .../model_3_3_4_4-solution000002.solution | 4 - .../basic/set09/expected/model_3_3_4_4.eprime | 62 - .../model_3_4_1_1-solution000001.solution | 4 - .../model_3_4_1_1-solution000002.solution | 4 - .../basic/set09/expected/model_3_4_1_1.eprime | 40 - .../model_3_4_1_2-solution000001.solution | 4 - .../model_3_4_1_2-solution000002.solution | 4 - .../basic/set09/expected/model_3_4_1_2.eprime | 48 - .../model_3_4_1_3-solution000001.solution | 4 - .../model_3_4_1_3-solution000002.solution | 4 - .../basic/set09/expected/model_3_4_1_3.eprime | 51 - .../model_3_4_1_4-solution000001.solution | 4 - .../model_3_4_1_4-solution000002.solution | 4 - .../basic/set09/expected/model_3_4_1_4.eprime | 33 - .../model_3_4_2_1-solution000001.solution | 4 - .../model_3_4_2_1-solution000002.solution | 4 - .../basic/set09/expected/model_3_4_2_1.eprime | 47 - .../model_3_4_2_2-solution000001.solution | 4 - .../model_3_4_2_2-solution000002.solution | 4 - .../basic/set09/expected/model_3_4_2_2.eprime | 55 - .../model_3_4_2_3-solution000001.solution | 4 - .../model_3_4_2_3-solution000002.solution | 4 - .../basic/set09/expected/model_3_4_2_3.eprime | 58 - .../model_3_4_2_4-solution000001.solution | 4 - .../model_3_4_2_4-solution000002.solution | 4 - .../basic/set09/expected/model_3_4_2_4.eprime | 40 - .../model_3_4_3_1-solution000001.solution | 4 - .../model_3_4_3_1-solution000002.solution | 4 - .../basic/set09/expected/model_3_4_3_1.eprime | 32 - .../model_3_4_3_2-solution000001.solution | 4 - .../model_3_4_3_2-solution000002.solution | 4 - .../basic/set09/expected/model_3_4_3_2.eprime | 40 - .../model_3_4_3_3-solution000001.solution | 4 - .../model_3_4_3_3-solution000002.solution | 4 - .../basic/set09/expected/model_3_4_3_3.eprime | 42 - .../model_3_4_3_4-solution000001.solution | 4 - .../model_3_4_3_4-solution000002.solution | 4 - .../basic/set09/expected/model_3_4_3_4.eprime | 25 - .../model_3_4_4_1-solution000001.solution | 4 - .../model_3_4_4_1-solution000002.solution | 4 - .../basic/set09/expected/model_3_4_4_1.eprime | 52 - .../model_3_4_4_2-solution000001.solution | 4 - .../model_3_4_4_2-solution000002.solution | 4 - .../basic/set09/expected/model_3_4_4_2.eprime | 60 - .../model_3_4_4_3-solution000001.solution | 4 - .../model_3_4_4_3-solution000002.solution | 4 - .../basic/set09/expected/model_3_4_4_3.eprime | 62 - .../model_3_4_4_4-solution000001.solution | 4 - .../model_3_4_4_4-solution000002.solution | 4 - .../basic/set09/expected/model_3_4_4_4.eprime | 44 - .../model_4_1_1_1-solution000001.solution | 4 - .../model_4_1_1_1-solution000002.solution | 4 - .../basic/set09/expected/model_4_1_1_1.eprime | 24 - .../model_4_1_1_2-solution000001.solution | 4 - .../model_4_1_1_2-solution000002.solution | 4 - .../basic/set09/expected/model_4_1_1_2.eprime | 35 - .../model_4_1_1_3-solution000001.solution | 4 - .../model_4_1_1_3-solution000002.solution | 4 - .../basic/set09/expected/model_4_1_1_3.eprime | 39 - .../model_4_1_1_4-solution000001.solution | 4 - .../model_4_1_1_4-solution000002.solution | 4 - .../basic/set09/expected/model_4_1_1_4.eprime | 39 - .../model_4_1_2_1-solution000001.solution | 4 - .../model_4_1_2_1-solution000002.solution | 4 - .../basic/set09/expected/model_4_1_2_1.eprime | 33 - .../model_4_1_2_2-solution000001.solution | 4 - .../model_4_1_2_2-solution000002.solution | 4 - .../basic/set09/expected/model_4_1_2_2.eprime | 43 - .../model_4_1_2_3-solution000001.solution | 4 - .../model_4_1_2_3-solution000002.solution | 4 - .../basic/set09/expected/model_4_1_2_3.eprime | 47 - .../model_4_1_2_4-solution000001.solution | 4 - .../model_4_1_2_4-solution000002.solution | 4 - .../basic/set09/expected/model_4_1_2_4.eprime | 48 - .../model_4_1_3_1-solution000001.solution | 4 - .../model_4_1_3_1-solution000002.solution | 4 - .../basic/set09/expected/model_4_1_3_1.eprime | 36 - .../model_4_1_3_2-solution000001.solution | 4 - .../model_4_1_3_2-solution000002.solution | 4 - .../basic/set09/expected/model_4_1_3_2.eprime | 45 - .../model_4_1_3_3-solution000001.solution | 4 - .../model_4_1_3_3-solution000002.solution | 4 - .../basic/set09/expected/model_4_1_3_3.eprime | 50 - .../model_4_1_3_4-solution000001.solution | 4 - .../model_4_1_3_4-solution000002.solution | 4 - .../basic/set09/expected/model_4_1_3_4.eprime | 51 - .../model_4_1_4_1-solution000001.solution | 4 - .../model_4_1_4_1-solution000002.solution | 4 - .../basic/set09/expected/model_4_1_4_1.eprime | 17 - .../model_4_1_4_2-solution000001.solution | 4 - .../model_4_1_4_2-solution000002.solution | 4 - .../basic/set09/expected/model_4_1_4_2.eprime | 27 - .../model_4_1_4_3-solution000001.solution | 4 - .../model_4_1_4_3-solution000002.solution | 4 - .../basic/set09/expected/model_4_1_4_3.eprime | 32 - .../model_4_1_4_4-solution000001.solution | 4 - .../model_4_1_4_4-solution000002.solution | 4 - .../basic/set09/expected/model_4_1_4_4.eprime | 32 - .../model_4_2_1_1-solution000001.solution | 4 - .../model_4_2_1_1-solution000002.solution | 4 - .../basic/set09/expected/model_4_2_1_1.eprime | 36 - .../model_4_2_1_2-solution000001.solution | 4 - .../model_4_2_1_2-solution000002.solution | 4 - .../basic/set09/expected/model_4_2_1_2.eprime | 29 - .../model_4_2_1_3-solution000001.solution | 4 - .../model_4_2_1_3-solution000002.solution | 4 - .../basic/set09/expected/model_4_2_1_3.eprime | 47 - .../model_4_2_1_4-solution000001.solution | 4 - .../model_4_2_1_4-solution000002.solution | 4 - .../basic/set09/expected/model_4_2_1_4.eprime | 49 - .../model_4_2_2_1-solution000001.solution | 4 - .../model_4_2_2_1-solution000002.solution | 4 - .../basic/set09/expected/model_4_2_2_1.eprime | 44 - .../model_4_2_2_2-solution000001.solution | 4 - .../model_4_2_2_2-solution000002.solution | 4 - .../basic/set09/expected/model_4_2_2_2.eprime | 38 - .../model_4_2_2_3-solution000001.solution | 4 - .../model_4_2_2_3-solution000002.solution | 4 - .../basic/set09/expected/model_4_2_2_3.eprime | 55 - .../model_4_2_2_4-solution000001.solution | 4 - .../model_4_2_2_4-solution000002.solution | 4 - .../basic/set09/expected/model_4_2_2_4.eprime | 57 - .../model_4_2_3_1-solution000001.solution | 4 - .../model_4_2_3_1-solution000002.solution | 4 - .../basic/set09/expected/model_4_2_3_1.eprime | 46 - .../model_4_2_3_2-solution000001.solution | 4 - .../model_4_2_3_2-solution000002.solution | 4 - .../basic/set09/expected/model_4_2_3_2.eprime | 40 - .../model_4_2_3_3-solution000001.solution | 4 - .../model_4_2_3_3-solution000002.solution | 4 - .../basic/set09/expected/model_4_2_3_3.eprime | 58 - .../model_4_2_3_4-solution000001.solution | 4 - .../model_4_2_3_4-solution000002.solution | 4 - .../basic/set09/expected/model_4_2_3_4.eprime | 60 - .../model_4_2_4_1-solution000001.solution | 4 - .../model_4_2_4_1-solution000002.solution | 4 - .../basic/set09/expected/model_4_2_4_1.eprime | 28 - .../model_4_2_4_2-solution000001.solution | 4 - .../model_4_2_4_2-solution000002.solution | 4 - .../basic/set09/expected/model_4_2_4_2.eprime | 21 - .../model_4_2_4_3-solution000001.solution | 4 - .../model_4_2_4_3-solution000002.solution | 4 - .../basic/set09/expected/model_4_2_4_3.eprime | 40 - .../model_4_2_4_4-solution000001.solution | 4 - .../model_4_2_4_4-solution000002.solution | 4 - .../basic/set09/expected/model_4_2_4_4.eprime | 42 - .../model_4_3_1_1-solution000001.solution | 4 - .../model_4_3_1_1-solution000002.solution | 4 - .../basic/set09/expected/model_4_3_1_1.eprime | 40 - .../model_4_3_1_2-solution000001.solution | 4 - .../model_4_3_1_2-solution000002.solution | 4 - .../basic/set09/expected/model_4_3_1_2.eprime | 47 - .../model_4_3_1_3-solution000001.solution | 4 - .../model_4_3_1_3-solution000002.solution | 4 - .../basic/set09/expected/model_4_3_1_3.eprime | 32 - .../model_4_3_1_4-solution000001.solution | 4 - .../model_4_3_1_4-solution000002.solution | 4 - .../basic/set09/expected/model_4_3_1_4.eprime | 52 - .../model_4_3_2_1-solution000001.solution | 4 - .../model_4_3_2_1-solution000002.solution | 4 - .../basic/set09/expected/model_4_3_2_1.eprime | 48 - .../model_4_3_2_2-solution000001.solution | 4 - .../model_4_3_2_2-solution000002.solution | 4 - .../basic/set09/expected/model_4_3_2_2.eprime | 55 - .../model_4_3_2_3-solution000001.solution | 4 - .../model_4_3_2_3-solution000002.solution | 4 - .../basic/set09/expected/model_4_3_2_3.eprime | 40 - .../model_4_3_2_4-solution000001.solution | 4 - .../model_4_3_2_4-solution000002.solution | 4 - .../basic/set09/expected/model_4_3_2_4.eprime | 60 - .../model_4_3_3_1-solution000001.solution | 4 - .../model_4_3_3_1-solution000002.solution | 4 - .../basic/set09/expected/model_4_3_3_1.eprime | 51 - .../model_4_3_3_2-solution000001.solution | 4 - .../model_4_3_3_2-solution000002.solution | 4 - .../basic/set09/expected/model_4_3_3_2.eprime | 58 - .../model_4_3_3_3-solution000001.solution | 4 - .../model_4_3_3_3-solution000002.solution | 4 - .../basic/set09/expected/model_4_3_3_3.eprime | 42 - .../model_4_3_3_4-solution000001.solution | 4 - .../model_4_3_3_4-solution000002.solution | 4 - .../basic/set09/expected/model_4_3_3_4.eprime | 62 - .../model_4_3_4_1-solution000001.solution | 4 - .../model_4_3_4_1-solution000002.solution | 4 - .../basic/set09/expected/model_4_3_4_1.eprime | 33 - .../model_4_3_4_2-solution000001.solution | 4 - .../model_4_3_4_2-solution000002.solution | 4 - .../basic/set09/expected/model_4_3_4_2.eprime | 40 - .../model_4_3_4_3-solution000001.solution | 4 - .../model_4_3_4_3-solution000002.solution | 4 - .../basic/set09/expected/model_4_3_4_3.eprime | 25 - .../model_4_3_4_4-solution000001.solution | 4 - .../model_4_3_4_4-solution000002.solution | 4 - .../basic/set09/expected/model_4_3_4_4.eprime | 44 - .../model_4_4_1_1-solution000001.solution | 4 - .../model_4_4_1_1-solution000002.solution | 4 - .../basic/set09/expected/model_4_4_1_1.eprime | 40 - .../model_4_4_1_2-solution000001.solution | 4 - .../model_4_4_1_2-solution000002.solution | 4 - .../basic/set09/expected/model_4_4_1_2.eprime | 48 - .../model_4_4_1_3-solution000001.solution | 4 - .../model_4_4_1_3-solution000002.solution | 4 - .../basic/set09/expected/model_4_4_1_3.eprime | 51 - .../model_4_4_1_4-solution000001.solution | 4 - .../model_4_4_1_4-solution000002.solution | 4 - .../basic/set09/expected/model_4_4_1_4.eprime | 33 - .../model_4_4_2_1-solution000001.solution | 4 - .../model_4_4_2_1-solution000002.solution | 4 - .../basic/set09/expected/model_4_4_2_1.eprime | 48 - .../model_4_4_2_2-solution000001.solution | 4 - .../model_4_4_2_2-solution000002.solution | 4 - .../basic/set09/expected/model_4_4_2_2.eprime | 56 - .../model_4_4_2_3-solution000001.solution | 4 - .../model_4_4_2_3-solution000002.solution | 4 - .../basic/set09/expected/model_4_4_2_3.eprime | 59 - .../model_4_4_2_4-solution000001.solution | 4 - .../model_4_4_2_4-solution000002.solution | 4 - .../basic/set09/expected/model_4_4_2_4.eprime | 41 - .../model_4_4_3_1-solution000001.solution | 4 - .../model_4_4_3_1-solution000002.solution | 4 - .../basic/set09/expected/model_4_4_3_1.eprime | 51 - .../model_4_4_3_2-solution000001.solution | 4 - .../model_4_4_3_2-solution000002.solution | 4 - .../basic/set09/expected/model_4_4_3_2.eprime | 59 - .../model_4_4_3_3-solution000001.solution | 4 - .../model_4_4_3_3-solution000002.solution | 4 - .../basic/set09/expected/model_4_4_3_3.eprime | 61 - .../model_4_4_3_4-solution000001.solution | 4 - .../model_4_4_3_4-solution000002.solution | 4 - .../basic/set09/expected/model_4_4_3_4.eprime | 43 - .../model_4_4_4_1-solution000001.solution | 4 - .../model_4_4_4_1-solution000002.solution | 4 - .../basic/set09/expected/model_4_4_4_1.eprime | 33 - .../model_4_4_4_2-solution000001.solution | 4 - .../model_4_4_4_2-solution000002.solution | 4 - .../basic/set09/expected/model_4_4_4_2.eprime | 41 - .../model_4_4_4_3-solution000001.solution | 4 - .../model_4_4_4_3-solution000002.solution | 4 - .../basic/set09/expected/model_4_4_4_3.eprime | 43 - .../model_4_4_4_4-solution000001.solution | 4 - .../model_4_4_4_4-solution000002.solution | 4 - .../basic/set09/expected/model_4_4_4_4.eprime | 26 - .../expected/model_1-solution000001.solution | 3 - .../expected/model_1-solution000002.solution | 3 - .../expected/model_1-solution000003.solution | 6 - .../expected/model_1-solution000004.solution | 6 - .../expected/model_1-solution000005.solution | 6 - .../expected/model_1-solution000006.solution | 7 - .../expected/model_1-solution000007.solution | 7 - .../expected/model_1-solution000008.solution | 7 - .../expected/model_1-solution000009.solution | 7 - .../expected/model_1-solution000010.solution | 7 - .../expected/model_1-solution000011.solution | 7 - .../expected/model_1-solution000012.solution | 8 - .../expected/model_1-solution000013.solution | 8 - .../expected/model_1-solution000014.solution | 8 - .../expected/model_1-solution000015.solution | 8 - .../expected/model_1-solution000016.solution | 9 - .../basic/setOfSet01/expected/model_1.eprime | 14 - .../expected/model_2-solution000001.solution | 3 - .../expected/model_2-solution000002.solution | 6 - .../expected/model_2-solution000003.solution | 6 - .../expected/model_2-solution000004.solution | 6 - .../expected/model_2-solution000005.solution | 3 - .../expected/model_2-solution000006.solution | 7 - .../expected/model_2-solution000007.solution | 7 - .../expected/model_2-solution000008.solution | 7 - .../expected/model_2-solution000009.solution | 7 - .../expected/model_2-solution000010.solution | 7 - .../expected/model_2-solution000011.solution | 7 - .../expected/model_2-solution000012.solution | 8 - .../expected/model_2-solution000013.solution | 8 - .../expected/model_2-solution000014.solution | 8 - .../expected/model_2-solution000015.solution | 8 - .../expected/model_2-solution000016.solution | 9 - .../basic/setOfSet01/expected/model_2.eprime | 24 - .../expected/model_3-solution000001.solution | 3 - .../expected/model_3-solution000002.solution | 3 - .../expected/model_3-solution000003.solution | 6 - .../expected/model_3-solution000004.solution | 6 - .../expected/model_3-solution000005.solution | 6 - .../expected/model_3-solution000006.solution | 7 - .../expected/model_3-solution000007.solution | 7 - .../expected/model_3-solution000008.solution | 7 - .../expected/model_3-solution000009.solution | 7 - .../expected/model_3-solution000010.solution | 7 - .../expected/model_3-solution000011.solution | 7 - .../expected/model_3-solution000012.solution | 8 - .../expected/model_3-solution000013.solution | 8 - .../expected/model_3-solution000014.solution | 8 - .../expected/model_3-solution000015.solution | 8 - .../expected/model_3-solution000016.solution | 9 - .../basic/setOfSet01/expected/model_3.eprime | 36 - .../expected/model_4-solution000001.solution | 3 - .../expected/model_4-solution000002.solution | 3 - .../expected/model_4-solution000003.solution | 6 - .../expected/model_4-solution000004.solution | 6 - .../expected/model_4-solution000005.solution | 6 - .../expected/model_4-solution000006.solution | 7 - .../expected/model_4-solution000007.solution | 7 - .../expected/model_4-solution000008.solution | 7 - .../expected/model_4-solution000009.solution | 7 - .../expected/model_4-solution000010.solution | 7 - .../expected/model_4-solution000011.solution | 7 - .../expected/model_4-solution000012.solution | 8 - .../expected/model_4-solution000013.solution | 8 - .../expected/model_4-solution000014.solution | 8 - .../expected/model_4-solution000015.solution | 8 - .../expected/model_4-solution000016.solution | 9 - .../basic/setOfSet01/expected/model_4.eprime | 43 - .../expected/model_5-solution000001.solution | 3 - .../expected/model_5-solution000002.solution | 3 - .../expected/model_5-solution000003.solution | 6 - .../expected/model_5-solution000004.solution | 6 - .../expected/model_5-solution000005.solution | 6 - .../expected/model_5-solution000006.solution | 7 - .../expected/model_5-solution000007.solution | 7 - .../expected/model_5-solution000008.solution | 7 - .../expected/model_5-solution000009.solution | 7 - .../expected/model_5-solution000010.solution | 7 - .../expected/model_5-solution000011.solution | 7 - .../expected/model_5-solution000012.solution | 8 - .../expected/model_5-solution000013.solution | 8 - .../expected/model_5-solution000014.solution | 8 - .../expected/model_5-solution000015.solution | 8 - .../expected/model_5-solution000016.solution | 9 - .../basic/setOfSet01/expected/model_5.eprime | 15 - .../expected/model_6-solution000001.solution | 3 - .../expected/model_6-solution000002.solution | 6 - .../expected/model_6-solution000003.solution | 6 - .../expected/model_6-solution000004.solution | 6 - .../expected/model_6-solution000005.solution | 3 - .../expected/model_6-solution000006.solution | 7 - .../expected/model_6-solution000007.solution | 7 - .../expected/model_6-solution000008.solution | 7 - .../expected/model_6-solution000009.solution | 7 - .../expected/model_6-solution000010.solution | 7 - .../expected/model_6-solution000011.solution | 7 - .../expected/model_6-solution000012.solution | 8 - .../expected/model_6-solution000013.solution | 8 - .../expected/model_6-solution000014.solution | 8 - .../expected/model_6-solution000015.solution | 8 - .../expected/model_6-solution000016.solution | 9 - .../basic/setOfSet01/expected/model_6.eprime | 24 - .../expected/model_7-solution000001.solution | 3 - .../expected/model_7-solution000002.solution | 3 - .../expected/model_7-solution000003.solution | 6 - .../expected/model_7-solution000004.solution | 6 - .../expected/model_7-solution000005.solution | 6 - .../expected/model_7-solution000006.solution | 7 - .../expected/model_7-solution000007.solution | 7 - .../expected/model_7-solution000008.solution | 7 - .../expected/model_7-solution000009.solution | 7 - .../expected/model_7-solution000010.solution | 7 - .../expected/model_7-solution000011.solution | 7 - .../expected/model_7-solution000012.solution | 8 - .../expected/model_7-solution000013.solution | 8 - .../expected/model_7-solution000014.solution | 8 - .../expected/model_7-solution000015.solution | 8 - .../expected/model_7-solution000016.solution | 9 - .../basic/setOfSet01/expected/model_7.eprime | 37 - .../expected/model_8-solution000001.solution | 3 - .../expected/model_8-solution000002.solution | 3 - .../expected/model_8-solution000003.solution | 6 - .../expected/model_8-solution000004.solution | 6 - .../expected/model_8-solution000005.solution | 6 - .../expected/model_8-solution000006.solution | 7 - .../expected/model_8-solution000007.solution | 7 - .../expected/model_8-solution000008.solution | 7 - .../expected/model_8-solution000009.solution | 7 - .../expected/model_8-solution000010.solution | 7 - .../expected/model_8-solution000011.solution | 7 - .../expected/model_8-solution000012.solution | 8 - .../expected/model_8-solution000013.solution | 8 - .../expected/model_8-solution000014.solution | 8 - .../expected/model_8-solution000015.solution | 8 - .../expected/model_8-solution000016.solution | 9 - .../basic/setOfSet01/expected/model_8.eprime | 44 - .../model_1_1-solution000001.solution | 7 - .../model_1_1-solution000002.solution | 7 - .../model_1_1-solution000003.solution | 7 - .../setOfSet02/expected/model_1_1.eprime | 12 - .../model_1_2-solution000001.solution | 7 - .../model_1_2-solution000002.solution | 7 - .../model_1_2-solution000003.solution | 7 - .../setOfSet02/expected/model_1_2.eprime | 27 - .../model_2_1-solution000001.solution | 7 - .../model_2_1-solution000002.solution | 7 - .../model_2_1-solution000003.solution | 7 - .../setOfSet02/expected/model_2_1.eprime | 33 - .../model_2_2-solution000001.solution | 7 - .../model_2_2-solution000002.solution | 7 - .../model_2_2-solution000003.solution | 7 - .../setOfSet02/expected/model_2_2.eprime | 19 - .../model_1_1_1-solution000001.solution | 7 - .../model_1_1_1-solution000002.solution | 7 - .../model_1_1_1-solution000003.solution | 7 - .../model_1_1_1-solution000004.solution | 7 - .../model_1_1_1-solution000005.solution | 7 - .../model_1_1_1-solution000006.solution | 7 - .../setOfSet04/expected/model_1_1_1.eprime | 9 - .../model_1_1_2-solution000001.solution | 7 - .../model_1_1_2-solution000002.solution | 7 - .../model_1_1_2-solution000003.solution | 7 - .../model_1_1_2-solution000004.solution | 7 - .../model_1_1_2-solution000005.solution | 7 - .../model_1_1_2-solution000006.solution | 7 - .../setOfSet04/expected/model_1_1_2.eprime | 42 - .../model_1_1_3-solution000001.solution | 7 - .../model_1_1_3-solution000002.solution | 7 - .../model_1_1_3-solution000003.solution | 7 - .../model_1_1_3-solution000004.solution | 7 - .../model_1_1_3-solution000005.solution | 7 - .../model_1_1_3-solution000006.solution | 7 - .../setOfSet04/expected/model_1_1_3.eprime | 52 - .../model_1_1_4-solution000001.solution | 7 - .../model_1_1_4-solution000002.solution | 7 - .../model_1_1_4-solution000003.solution | 7 - .../model_1_1_4-solution000004.solution | 7 - .../model_1_1_4-solution000005.solution | 7 - .../model_1_1_4-solution000006.solution | 7 - .../setOfSet04/expected/model_1_1_4.eprime | 57 - .../model_1_2_1-solution000001.solution | 7 - .../model_1_2_1-solution000002.solution | 7 - .../model_1_2_1-solution000003.solution | 7 - .../model_1_2_1-solution000004.solution | 7 - .../model_1_2_1-solution000005.solution | 7 - .../model_1_2_1-solution000006.solution | 7 - .../setOfSet04/expected/model_1_2_1.eprime | 42 - .../model_1_2_2-solution000001.solution | 7 - .../model_1_2_2-solution000002.solution | 7 - .../model_1_2_2-solution000003.solution | 7 - .../model_1_2_2-solution000004.solution | 7 - .../model_1_2_2-solution000005.solution | 7 - .../model_1_2_2-solution000006.solution | 7 - .../setOfSet04/expected/model_1_2_2.eprime | 42 - .../model_1_2_3-solution000001.solution | 7 - .../model_1_2_3-solution000002.solution | 7 - .../model_1_2_3-solution000003.solution | 7 - .../model_1_2_3-solution000004.solution | 7 - .../model_1_2_3-solution000005.solution | 7 - .../model_1_2_3-solution000006.solution | 7 - .../setOfSet04/expected/model_1_2_3.eprime | 115 -- .../model_1_2_4-solution000001.solution | 7 - .../model_1_2_4-solution000002.solution | 7 - .../model_1_2_4-solution000003.solution | 7 - .../model_1_2_4-solution000004.solution | 7 - .../model_1_2_4-solution000005.solution | 7 - .../model_1_2_4-solution000006.solution | 7 - .../setOfSet04/expected/model_1_2_4.eprime | 121 -- .../model_1_3_1-solution000001.solution | 7 - .../model_1_3_1-solution000002.solution | 7 - .../model_1_3_1-solution000003.solution | 7 - .../model_1_3_1-solution000004.solution | 7 - .../model_1_3_1-solution000005.solution | 7 - .../model_1_3_1-solution000006.solution | 7 - .../setOfSet04/expected/model_1_3_1.eprime | 52 - .../model_1_3_2-solution000001.solution | 7 - .../model_1_3_2-solution000002.solution | 7 - .../model_1_3_2-solution000003.solution | 7 - .../model_1_3_2-solution000004.solution | 7 - .../model_1_3_2-solution000005.solution | 7 - .../model_1_3_2-solution000006.solution | 7 - .../setOfSet04/expected/model_1_3_2.eprime | 116 -- .../model_1_3_3-solution000001.solution | 7 - .../model_1_3_3-solution000002.solution | 7 - .../model_1_3_3-solution000003.solution | 7 - .../model_1_3_3-solution000004.solution | 7 - .../model_1_3_3-solution000005.solution | 7 - .../model_1_3_3-solution000006.solution | 7 - .../setOfSet04/expected/model_1_3_3.eprime | 52 - .../model_1_3_4-solution000001.solution | 7 - .../model_1_3_4-solution000002.solution | 7 - .../model_1_3_4-solution000003.solution | 7 - .../model_1_3_4-solution000004.solution | 7 - .../model_1_3_4-solution000005.solution | 7 - .../model_1_3_4-solution000006.solution | 7 - .../setOfSet04/expected/model_1_3_4.eprime | 129 -- .../model_1_4_1-solution000001.solution | 7 - .../model_1_4_1-solution000002.solution | 7 - .../model_1_4_1-solution000003.solution | 7 - .../model_1_4_1-solution000004.solution | 7 - .../model_1_4_1-solution000005.solution | 7 - .../model_1_4_1-solution000006.solution | 7 - .../setOfSet04/expected/model_1_4_1.eprime | 57 - .../model_1_4_2-solution000001.solution | 7 - .../model_1_4_2-solution000002.solution | 7 - .../model_1_4_2-solution000003.solution | 7 - .../model_1_4_2-solution000004.solution | 7 - .../model_1_4_2-solution000005.solution | 7 - .../model_1_4_2-solution000006.solution | 7 - .../setOfSet04/expected/model_1_4_2.eprime | 122 -- .../model_1_4_3-solution000001.solution | 7 - .../model_1_4_3-solution000002.solution | 7 - .../model_1_4_3-solution000003.solution | 7 - .../model_1_4_3-solution000004.solution | 7 - .../model_1_4_3-solution000005.solution | 7 - .../model_1_4_3-solution000006.solution | 7 - .../setOfSet04/expected/model_1_4_3.eprime | 129 -- .../model_1_4_4-solution000001.solution | 7 - .../model_1_4_4-solution000002.solution | 7 - .../model_1_4_4-solution000003.solution | 7 - .../model_1_4_4-solution000004.solution | 7 - .../model_1_4_4-solution000005.solution | 7 - .../model_1_4_4-solution000006.solution | 7 - .../setOfSet04/expected/model_1_4_4.eprime | 57 - .../model_2_1_1-solution000001.solution | 7 - .../model_2_1_1-solution000002.solution | 7 - .../model_2_1_1-solution000003.solution | 7 - .../model_2_1_1-solution000004.solution | 7 - .../model_2_1_1-solution000005.solution | 7 - .../model_2_1_1-solution000006.solution | 7 - .../setOfSet04/expected/model_2_1_1.eprime | 42 - .../model_2_1_2-solution000001.solution | 7 - .../model_2_1_2-solution000002.solution | 7 - .../model_2_1_2-solution000003.solution | 7 - .../model_2_1_2-solution000004.solution | 7 - .../model_2_1_2-solution000005.solution | 7 - .../model_2_1_2-solution000006.solution | 7 - .../setOfSet04/expected/model_2_1_2.eprime | 42 - .../model_2_1_3-solution000001.solution | 7 - .../model_2_1_3-solution000002.solution | 7 - .../model_2_1_3-solution000003.solution | 7 - .../model_2_1_3-solution000004.solution | 7 - .../model_2_1_3-solution000005.solution | 7 - .../model_2_1_3-solution000006.solution | 7 - .../setOfSet04/expected/model_2_1_3.eprime | 115 -- .../model_2_1_4-solution000001.solution | 7 - .../model_2_1_4-solution000002.solution | 7 - .../model_2_1_4-solution000003.solution | 7 - .../model_2_1_4-solution000004.solution | 7 - .../model_2_1_4-solution000005.solution | 7 - .../model_2_1_4-solution000006.solution | 7 - .../setOfSet04/expected/model_2_1_4.eprime | 121 -- .../model_2_2_1-solution000001.solution | 7 - .../model_2_2_1-solution000002.solution | 7 - .../model_2_2_1-solution000003.solution | 7 - .../model_2_2_1-solution000004.solution | 7 - .../model_2_2_1-solution000005.solution | 7 - .../model_2_2_1-solution000006.solution | 7 - .../setOfSet04/expected/model_2_2_1.eprime | 42 - .../model_2_2_2-solution000001.solution | 7 - .../model_2_2_2-solution000002.solution | 7 - .../model_2_2_2-solution000003.solution | 7 - .../model_2_2_2-solution000004.solution | 7 - .../model_2_2_2-solution000005.solution | 7 - .../model_2_2_2-solution000006.solution | 7 - .../setOfSet04/expected/model_2_2_2.eprime | 16 - .../model_2_2_3-solution000001.solution | 7 - .../model_2_2_3-solution000002.solution | 7 - .../model_2_2_3-solution000003.solution | 7 - .../model_2_2_3-solution000004.solution | 7 - .../model_2_2_3-solution000005.solution | 7 - .../model_2_2_3-solution000006.solution | 7 - .../setOfSet04/expected/model_2_2_3.eprime | 67 - .../model_2_2_4-solution000001.solution | 7 - .../model_2_2_4-solution000002.solution | 7 - .../model_2_2_4-solution000003.solution | 7 - .../model_2_2_4-solution000004.solution | 7 - .../model_2_2_4-solution000005.solution | 7 - .../model_2_2_4-solution000006.solution | 7 - .../setOfSet04/expected/model_2_2_4.eprime | 73 - .../model_2_3_1-solution000001.solution | 7 - .../model_2_3_1-solution000002.solution | 7 - .../model_2_3_1-solution000003.solution | 7 - .../model_2_3_1-solution000004.solution | 7 - .../model_2_3_1-solution000005.solution | 7 - .../model_2_3_1-solution000006.solution | 7 - .../setOfSet04/expected/model_2_3_1.eprime | 115 -- .../model_2_3_2-solution000001.solution | 7 - .../model_2_3_2-solution000002.solution | 7 - .../model_2_3_2-solution000003.solution | 7 - .../model_2_3_2-solution000004.solution | 7 - .../model_2_3_2-solution000005.solution | 7 - .../model_2_3_2-solution000006.solution | 7 - .../setOfSet04/expected/model_2_3_2.eprime | 67 - .../model_2_3_3-solution000001.solution | 7 - .../model_2_3_3-solution000002.solution | 7 - .../model_2_3_3-solution000003.solution | 7 - .../model_2_3_3-solution000004.solution | 7 - .../model_2_3_3-solution000005.solution | 7 - .../model_2_3_3-solution000006.solution | 7 - .../setOfSet04/expected/model_2_3_3.eprime | 67 - .../model_2_3_4-solution000001.solution | 7 - .../model_2_3_4-solution000002.solution | 7 - .../model_2_3_4-solution000003.solution | 7 - .../model_2_3_4-solution000004.solution | 7 - .../model_2_3_4-solution000005.solution | 7 - .../model_2_3_4-solution000006.solution | 7 - .../setOfSet04/expected/model_2_3_4.eprime | 153 -- .../model_2_4_1-solution000001.solution | 7 - .../model_2_4_1-solution000002.solution | 7 - .../model_2_4_1-solution000003.solution | 7 - .../model_2_4_1-solution000004.solution | 7 - .../model_2_4_1-solution000005.solution | 7 - .../model_2_4_1-solution000006.solution | 7 - .../setOfSet04/expected/model_2_4_1.eprime | 121 -- .../model_2_4_2-solution000001.solution | 7 - .../model_2_4_2-solution000002.solution | 7 - .../model_2_4_2-solution000003.solution | 7 - .../model_2_4_2-solution000004.solution | 7 - .../model_2_4_2-solution000005.solution | 7 - .../model_2_4_2-solution000006.solution | 7 - .../setOfSet04/expected/model_2_4_2.eprime | 73 - .../model_2_4_3-solution000001.solution | 7 - .../model_2_4_3-solution000002.solution | 7 - .../model_2_4_3-solution000003.solution | 7 - .../model_2_4_3-solution000004.solution | 7 - .../model_2_4_3-solution000005.solution | 7 - .../model_2_4_3-solution000006.solution | 7 - .../setOfSet04/expected/model_2_4_3.eprime | 153 -- .../model_2_4_4-solution000001.solution | 7 - .../model_2_4_4-solution000002.solution | 7 - .../model_2_4_4-solution000003.solution | 7 - .../model_2_4_4-solution000004.solution | 7 - .../model_2_4_4-solution000005.solution | 7 - .../model_2_4_4-solution000006.solution | 7 - .../setOfSet04/expected/model_2_4_4.eprime | 73 - .../model_3_1_1-solution000001.solution | 7 - .../model_3_1_1-solution000002.solution | 7 - .../model_3_1_1-solution000003.solution | 7 - .../model_3_1_1-solution000004.solution | 7 - .../model_3_1_1-solution000005.solution | 7 - .../model_3_1_1-solution000006.solution | 7 - .../setOfSet04/expected/model_3_1_1.eprime | 52 - .../model_3_1_2-solution000001.solution | 7 - .../model_3_1_2-solution000002.solution | 7 - .../model_3_1_2-solution000003.solution | 7 - .../model_3_1_2-solution000004.solution | 7 - .../model_3_1_2-solution000005.solution | 7 - .../model_3_1_2-solution000006.solution | 7 - .../setOfSet04/expected/model_3_1_2.eprime | 116 -- .../model_3_1_3-solution000001.solution | 7 - .../model_3_1_3-solution000002.solution | 7 - .../model_3_1_3-solution000003.solution | 7 - .../model_3_1_3-solution000004.solution | 7 - .../model_3_1_3-solution000005.solution | 7 - .../model_3_1_3-solution000006.solution | 7 - .../setOfSet04/expected/model_3_1_3.eprime | 52 - .../model_3_1_4-solution000001.solution | 7 - .../model_3_1_4-solution000002.solution | 7 - .../model_3_1_4-solution000003.solution | 7 - .../model_3_1_4-solution000004.solution | 7 - .../model_3_1_4-solution000005.solution | 7 - .../model_3_1_4-solution000006.solution | 7 - .../setOfSet04/expected/model_3_1_4.eprime | 130 -- .../model_3_2_1-solution000001.solution | 7 - .../model_3_2_1-solution000002.solution | 7 - .../model_3_2_1-solution000003.solution | 7 - .../model_3_2_1-solution000004.solution | 7 - .../model_3_2_1-solution000005.solution | 7 - .../model_3_2_1-solution000006.solution | 7 - .../setOfSet04/expected/model_3_2_1.eprime | 116 -- .../model_3_2_2-solution000001.solution | 7 - .../model_3_2_2-solution000002.solution | 7 - .../model_3_2_2-solution000003.solution | 7 - .../model_3_2_2-solution000004.solution | 7 - .../model_3_2_2-solution000005.solution | 7 - .../model_3_2_2-solution000006.solution | 7 - .../setOfSet04/expected/model_3_2_2.eprime | 68 - .../model_3_2_3-solution000001.solution | 7 - .../model_3_2_3-solution000002.solution | 7 - .../model_3_2_3-solution000003.solution | 7 - .../model_3_2_3-solution000004.solution | 7 - .../model_3_2_3-solution000005.solution | 7 - .../model_3_2_3-solution000006.solution | 7 - .../setOfSet04/expected/model_3_2_3.eprime | 68 - .../model_3_2_4-solution000001.solution | 7 - .../model_3_2_4-solution000002.solution | 7 - .../model_3_2_4-solution000003.solution | 7 - .../model_3_2_4-solution000004.solution | 7 - .../model_3_2_4-solution000005.solution | 7 - .../model_3_2_4-solution000006.solution | 7 - .../setOfSet04/expected/model_3_2_4.eprime | 154 --- .../model_3_3_1-solution000001.solution | 7 - .../model_3_3_1-solution000002.solution | 7 - .../model_3_3_1-solution000003.solution | 7 - .../model_3_3_1-solution000004.solution | 7 - .../model_3_3_1-solution000005.solution | 7 - .../model_3_3_1-solution000006.solution | 7 - .../setOfSet04/expected/model_3_3_1.eprime | 52 - .../model_3_3_2-solution000001.solution | 7 - .../model_3_3_2-solution000002.solution | 7 - .../model_3_3_2-solution000003.solution | 7 - .../model_3_3_2-solution000004.solution | 7 - .../model_3_3_2-solution000005.solution | 7 - .../model_3_3_2-solution000006.solution | 7 - .../setOfSet04/expected/model_3_3_2.eprime | 68 - .../model_3_3_3-solution000001.solution | 7 - .../model_3_3_3-solution000002.solution | 7 - .../model_3_3_3-solution000003.solution | 7 - .../model_3_3_3-solution000004.solution | 7 - .../model_3_3_3-solution000005.solution | 7 - .../model_3_3_3-solution000006.solution | 7 - .../setOfSet04/expected/model_3_3_3.eprime | 24 - .../model_3_3_4-solution000001.solution | 7 - .../model_3_3_4-solution000002.solution | 7 - .../model_3_3_4-solution000003.solution | 7 - .../model_3_3_4-solution000004.solution | 7 - .../model_3_3_4-solution000005.solution | 7 - .../model_3_3_4-solution000006.solution | 7 - .../setOfSet04/expected/model_3_3_4.eprime | 81 -- .../model_3_4_1-solution000001.solution | 7 - .../model_3_4_1-solution000002.solution | 7 - .../model_3_4_1-solution000003.solution | 7 - .../model_3_4_1-solution000004.solution | 7 - .../model_3_4_1-solution000005.solution | 7 - .../model_3_4_1-solution000006.solution | 7 - .../setOfSet04/expected/model_3_4_1.eprime | 130 -- .../model_3_4_2-solution000001.solution | 7 - .../model_3_4_2-solution000002.solution | 7 - .../model_3_4_2-solution000003.solution | 7 - .../model_3_4_2-solution000004.solution | 7 - .../model_3_4_2-solution000005.solution | 7 - .../model_3_4_2-solution000006.solution | 7 - .../setOfSet04/expected/model_3_4_2.eprime | 154 --- .../model_3_4_3-solution000001.solution | 7 - .../model_3_4_3-solution000002.solution | 7 - .../model_3_4_3-solution000003.solution | 7 - .../model_3_4_3-solution000004.solution | 7 - .../model_3_4_3-solution000005.solution | 7 - .../model_3_4_3-solution000006.solution | 7 - .../setOfSet04/expected/model_3_4_3.eprime | 81 -- .../model_3_4_4-solution000001.solution | 7 - .../model_3_4_4-solution000002.solution | 7 - .../model_3_4_4-solution000003.solution | 7 - .../model_3_4_4-solution000004.solution | 7 - .../model_3_4_4-solution000005.solution | 7 - .../model_3_4_4-solution000006.solution | 7 - .../setOfSet04/expected/model_3_4_4.eprime | 81 -- .../model_4_1_1-solution000001.solution | 7 - .../model_4_1_1-solution000002.solution | 7 - .../model_4_1_1-solution000003.solution | 7 - .../model_4_1_1-solution000004.solution | 7 - .../model_4_1_1-solution000005.solution | 7 - .../model_4_1_1-solution000006.solution | 7 - .../setOfSet04/expected/model_4_1_1.eprime | 57 - .../model_4_1_2-solution000001.solution | 7 - .../model_4_1_2-solution000002.solution | 7 - .../model_4_1_2-solution000003.solution | 7 - .../model_4_1_2-solution000004.solution | 7 - .../model_4_1_2-solution000005.solution | 7 - .../model_4_1_2-solution000006.solution | 7 - .../setOfSet04/expected/model_4_1_2.eprime | 122 -- .../model_4_1_3-solution000001.solution | 7 - .../model_4_1_3-solution000002.solution | 7 - .../model_4_1_3-solution000003.solution | 7 - .../model_4_1_3-solution000004.solution | 7 - .../model_4_1_3-solution000005.solution | 7 - .../model_4_1_3-solution000006.solution | 7 - .../setOfSet04/expected/model_4_1_3.eprime | 129 -- .../model_4_1_4-solution000001.solution | 7 - .../model_4_1_4-solution000002.solution | 7 - .../model_4_1_4-solution000003.solution | 7 - .../model_4_1_4-solution000004.solution | 7 - .../model_4_1_4-solution000005.solution | 7 - .../model_4_1_4-solution000006.solution | 7 - .../setOfSet04/expected/model_4_1_4.eprime | 57 - .../model_4_2_1-solution000001.solution | 7 - .../model_4_2_1-solution000002.solution | 7 - .../model_4_2_1-solution000003.solution | 7 - .../model_4_2_1-solution000004.solution | 7 - .../model_4_2_1-solution000005.solution | 7 - .../model_4_2_1-solution000006.solution | 7 - .../setOfSet04/expected/model_4_2_1.eprime | 122 -- .../model_4_2_2-solution000001.solution | 7 - .../model_4_2_2-solution000002.solution | 7 - .../model_4_2_2-solution000003.solution | 7 - .../model_4_2_2-solution000004.solution | 7 - .../model_4_2_2-solution000005.solution | 7 - .../model_4_2_2-solution000006.solution | 7 - .../setOfSet04/expected/model_4_2_2.eprime | 74 - .../model_4_2_3-solution000001.solution | 7 - .../model_4_2_3-solution000002.solution | 7 - .../model_4_2_3-solution000003.solution | 7 - .../model_4_2_3-solution000004.solution | 7 - .../model_4_2_3-solution000005.solution | 7 - .../model_4_2_3-solution000006.solution | 7 - .../setOfSet04/expected/model_4_2_3.eprime | 154 --- .../model_4_2_4-solution000001.solution | 7 - .../model_4_2_4-solution000002.solution | 7 - .../model_4_2_4-solution000003.solution | 7 - .../model_4_2_4-solution000004.solution | 7 - .../model_4_2_4-solution000005.solution | 7 - .../model_4_2_4-solution000006.solution | 7 - .../setOfSet04/expected/model_4_2_4.eprime | 74 - .../model_4_3_1-solution000001.solution | 7 - .../model_4_3_1-solution000002.solution | 7 - .../model_4_3_1-solution000003.solution | 7 - .../model_4_3_1-solution000004.solution | 7 - .../model_4_3_1-solution000005.solution | 7 - .../model_4_3_1-solution000006.solution | 7 - .../setOfSet04/expected/model_4_3_1.eprime | 129 -- .../model_4_3_2-solution000001.solution | 7 - .../model_4_3_2-solution000002.solution | 7 - .../model_4_3_2-solution000003.solution | 7 - .../model_4_3_2-solution000004.solution | 7 - .../model_4_3_2-solution000005.solution | 7 - .../model_4_3_2-solution000006.solution | 7 - .../setOfSet04/expected/model_4_3_2.eprime | 154 --- .../model_4_3_3-solution000001.solution | 7 - .../model_4_3_3-solution000002.solution | 7 - .../model_4_3_3-solution000003.solution | 7 - .../model_4_3_3-solution000004.solution | 7 - .../model_4_3_3-solution000005.solution | 7 - .../model_4_3_3-solution000006.solution | 7 - .../setOfSet04/expected/model_4_3_3.eprime | 81 -- .../model_4_3_4-solution000001.solution | 7 - .../model_4_3_4-solution000002.solution | 7 - .../model_4_3_4-solution000003.solution | 7 - .../model_4_3_4-solution000004.solution | 7 - .../model_4_3_4-solution000005.solution | 7 - .../model_4_3_4-solution000006.solution | 7 - .../setOfSet04/expected/model_4_3_4.eprime | 81 -- .../model_4_4_1-solution000001.solution | 7 - .../model_4_4_1-solution000002.solution | 7 - .../model_4_4_1-solution000003.solution | 7 - .../model_4_4_1-solution000004.solution | 7 - .../model_4_4_1-solution000005.solution | 7 - .../model_4_4_1-solution000006.solution | 7 - .../setOfSet04/expected/model_4_4_1.eprime | 57 - .../model_4_4_2-solution000001.solution | 7 - .../model_4_4_2-solution000002.solution | 7 - .../model_4_4_2-solution000003.solution | 7 - .../model_4_4_2-solution000004.solution | 7 - .../model_4_4_2-solution000005.solution | 7 - .../model_4_4_2-solution000006.solution | 7 - .../setOfSet04/expected/model_4_4_2.eprime | 74 - .../model_4_4_3-solution000001.solution | 7 - .../model_4_4_3-solution000002.solution | 7 - .../model_4_4_3-solution000003.solution | 7 - .../model_4_4_3-solution000004.solution | 7 - .../model_4_4_3-solution000005.solution | 7 - .../model_4_4_3-solution000006.solution | 7 - .../setOfSet04/expected/model_4_4_3.eprime | 81 -- .../model_4_4_4-solution000001.solution | 7 - .../model_4_4_4-solution000002.solution | 7 - .../model_4_4_4-solution000003.solution | 7 - .../model_4_4_4-solution000004.solution | 7 - .../model_4_4_4-solution000005.solution | 7 - .../model_4_4_4-solution000006.solution | 7 - .../setOfSet04/expected/model_4_4_4.eprime | 30 - .../model_1_1_1-solution000001.solution | 3 - .../model_1_1_1-solution000002.solution | 3 - .../set_card_00/expected/model_1_1_1.eprime | 6 - .../model_1_1_2-solution000001.solution | 3 - .../model_1_1_2-solution000002.solution | 3 - .../set_card_00/expected/model_1_1_2.eprime | 14 - .../model_1_1_3-solution000001.solution | 3 - .../model_1_1_3-solution000002.solution | 3 - .../set_card_00/expected/model_1_1_3.eprime | 17 - .../model_1_1_4-solution000001.solution | 3 - .../model_1_1_4-solution000002.solution | 3 - .../set_card_00/expected/model_1_1_4.eprime | 16 - .../model_1_2_1-solution000001.solution | 3 - .../model_1_2_1-solution000002.solution | 3 - .../set_card_00/expected/model_1_2_1.eprime | 16 - .../model_1_2_2-solution000001.solution | 3 - .../model_1_2_2-solution000002.solution | 3 - .../set_card_00/expected/model_1_2_2.eprime | 16 - .../model_1_2_3-solution000001.solution | 3 - .../model_1_2_3-solution000002.solution | 3 - .../set_card_00/expected/model_1_2_3.eprime | 38 - .../model_1_2_4-solution000001.solution | 3 - .../model_1_2_4-solution000002.solution | 3 - .../set_card_00/expected/model_1_2_4.eprime | 38 - .../model_1_3_1-solution000001.solution | 3 - .../model_1_3_1-solution000002.solution | 3 - .../set_card_00/expected/model_1_3_1.eprime | 19 - .../model_1_3_2-solution000001.solution | 3 - .../model_1_3_2-solution000002.solution | 3 - .../set_card_00/expected/model_1_3_2.eprime | 37 - .../model_1_3_3-solution000001.solution | 3 - .../model_1_3_3-solution000002.solution | 3 - .../set_card_00/expected/model_1_3_3.eprime | 19 - .../model_1_3_4-solution000001.solution | 3 - .../model_1_3_4-solution000002.solution | 3 - .../set_card_00/expected/model_1_3_4.eprime | 42 - .../model_1_4_1-solution000001.solution | 3 - .../model_1_4_1-solution000002.solution | 3 - .../set_card_00/expected/model_1_4_1.eprime | 18 - .../model_1_4_2-solution000001.solution | 3 - .../model_1_4_2-solution000002.solution | 3 - .../set_card_00/expected/model_1_4_2.eprime | 36 - .../model_1_4_3-solution000001.solution | 3 - .../model_1_4_3-solution000002.solution | 3 - .../set_card_00/expected/model_1_4_3.eprime | 41 - .../model_1_4_4-solution000001.solution | 3 - .../model_1_4_4-solution000002.solution | 3 - .../set_card_00/expected/model_1_4_4.eprime | 18 - .../model_2_1_1-solution000001.solution | 3 - .../model_2_1_1-solution000002.solution | 3 - .../set_card_00/expected/model_2_1_1.eprime | 14 - .../model_2_1_2-solution000001.solution | 3 - .../model_2_1_2-solution000002.solution | 3 - .../set_card_00/expected/model_2_1_2.eprime | 14 - .../model_2_1_3-solution000001.solution | 3 - .../model_2_1_3-solution000002.solution | 3 - .../set_card_00/expected/model_2_1_3.eprime | 36 - .../model_2_1_4-solution000001.solution | 3 - .../model_2_1_4-solution000002.solution | 3 - .../set_card_00/expected/model_2_1_4.eprime | 35 - .../model_2_2_1-solution000001.solution | 3 - .../model_2_2_1-solution000002.solution | 3 - .../set_card_00/expected/model_2_2_1.eprime | 16 - .../model_2_2_2-solution000001.solution | 3 - .../model_2_2_2-solution000002.solution | 3 - .../set_card_00/expected/model_2_2_2.eprime | 11 - .../model_2_2_3-solution000001.solution | 3 - .../model_2_2_3-solution000002.solution | 3 - .../set_card_00/expected/model_2_2_3.eprime | 26 - .../model_2_2_4-solution000001.solution | 3 - .../model_2_2_4-solution000002.solution | 3 - .../set_card_00/expected/model_2_2_4.eprime | 26 - .../model_2_3_1-solution000001.solution | 3 - .../model_2_3_1-solution000002.solution | 3 - .../set_card_00/expected/model_2_3_1.eprime | 38 - .../model_2_3_2-solution000001.solution | 3 - .../model_2_3_2-solution000002.solution | 3 - .../set_card_00/expected/model_2_3_2.eprime | 26 - .../model_2_3_3-solution000001.solution | 3 - .../model_2_3_3-solution000002.solution | 3 - .../set_card_00/expected/model_2_3_3.eprime | 26 - .../model_2_3_4-solution000001.solution | 3 - .../model_2_3_4-solution000002.solution | 3 - .../set_card_00/expected/model_2_3_4.eprime | 54 - .../model_2_4_1-solution000001.solution | 3 - .../model_2_4_1-solution000002.solution | 3 - .../set_card_00/expected/model_2_4_1.eprime | 37 - .../model_2_4_2-solution000001.solution | 3 - .../model_2_4_2-solution000002.solution | 3 - .../set_card_00/expected/model_2_4_2.eprime | 26 - .../model_2_4_3-solution000001.solution | 3 - .../model_2_4_3-solution000002.solution | 3 - .../set_card_00/expected/model_2_4_3.eprime | 53 - .../model_2_4_4-solution000001.solution | 3 - .../model_2_4_4-solution000002.solution | 3 - .../set_card_00/expected/model_2_4_4.eprime | 26 - .../model_3_1_1-solution000001.solution | 3 - .../model_3_1_1-solution000002.solution | 3 - .../set_card_00/expected/model_3_1_1.eprime | 17 - .../model_3_1_2-solution000001.solution | 3 - .../model_3_1_2-solution000002.solution | 3 - .../set_card_00/expected/model_3_1_2.eprime | 36 - .../model_3_1_3-solution000001.solution | 3 - .../model_3_1_3-solution000002.solution | 3 - .../set_card_00/expected/model_3_1_3.eprime | 17 - .../model_3_1_4-solution000001.solution | 3 - .../model_3_1_4-solution000002.solution | 3 - .../set_card_00/expected/model_3_1_4.eprime | 40 - .../model_3_2_1-solution000001.solution | 3 - .../model_3_2_1-solution000002.solution | 3 - .../set_card_00/expected/model_3_2_1.eprime | 37 - .../model_3_2_2-solution000001.solution | 3 - .../model_3_2_2-solution000002.solution | 3 - .../set_card_00/expected/model_3_2_2.eprime | 25 - .../model_3_2_3-solution000001.solution | 3 - .../model_3_2_3-solution000002.solution | 3 - .../set_card_00/expected/model_3_2_3.eprime | 25 - .../model_3_2_4-solution000001.solution | 3 - .../model_3_2_4-solution000002.solution | 3 - .../set_card_00/expected/model_3_2_4.eprime | 53 - .../model_3_3_1-solution000001.solution | 3 - .../model_3_3_1-solution000002.solution | 3 - .../set_card_00/expected/model_3_3_1.eprime | 19 - .../model_3_3_2-solution000001.solution | 3 - .../model_3_3_2-solution000002.solution | 3 - .../set_card_00/expected/model_3_3_2.eprime | 26 - .../model_3_3_3-solution000001.solution | 3 - .../model_3_3_3-solution000002.solution | 3 - .../set_card_00/expected/model_3_3_3.eprime | 13 - .../model_3_3_4-solution000001.solution | 3 - .../model_3_3_4-solution000002.solution | 3 - .../set_card_00/expected/model_3_3_4.eprime | 30 - .../model_3_4_1-solution000001.solution | 3 - .../model_3_4_1-solution000002.solution | 3 - .../set_card_00/expected/model_3_4_1.eprime | 42 - .../model_3_4_2-solution000001.solution | 3 - .../model_3_4_2-solution000002.solution | 3 - .../set_card_00/expected/model_3_4_2.eprime | 53 - .../model_3_4_3-solution000001.solution | 3 - .../model_3_4_3-solution000002.solution | 3 - .../set_card_00/expected/model_3_4_3.eprime | 30 - .../model_3_4_4-solution000001.solution | 3 - .../model_3_4_4-solution000002.solution | 3 - .../set_card_00/expected/model_3_4_4.eprime | 30 - .../model_4_1_1-solution000001.solution | 3 - .../model_4_1_1-solution000002.solution | 3 - .../set_card_00/expected/model_4_1_1.eprime | 17 - .../model_4_1_2-solution000001.solution | 3 - .../model_4_1_2-solution000002.solution | 3 - .../set_card_00/expected/model_4_1_2.eprime | 35 - .../model_4_1_3-solution000001.solution | 3 - .../model_4_1_3-solution000002.solution | 3 - .../set_card_00/expected/model_4_1_3.eprime | 40 - .../model_4_1_4-solution000001.solution | 3 - .../model_4_1_4-solution000002.solution | 3 - .../set_card_00/expected/model_4_1_4.eprime | 17 - .../model_4_2_1-solution000001.solution | 3 - .../model_4_2_1-solution000002.solution | 3 - .../set_card_00/expected/model_4_2_1.eprime | 37 - .../model_4_2_2-solution000001.solution | 3 - .../model_4_2_2-solution000002.solution | 3 - .../set_card_00/expected/model_4_2_2.eprime | 26 - .../model_4_2_3-solution000001.solution | 3 - .../model_4_2_3-solution000002.solution | 3 - .../set_card_00/expected/model_4_2_3.eprime | 53 - .../model_4_2_4-solution000001.solution | 3 - .../model_4_2_4-solution000002.solution | 3 - .../set_card_00/expected/model_4_2_4.eprime | 26 - .../model_4_3_1-solution000001.solution | 3 - .../model_4_3_1-solution000002.solution | 3 - .../set_card_00/expected/model_4_3_1.eprime | 42 - .../model_4_3_2-solution000001.solution | 3 - .../model_4_3_2-solution000002.solution | 3 - .../set_card_00/expected/model_4_3_2.eprime | 53 - .../model_4_3_3-solution000001.solution | 3 - .../model_4_3_3-solution000002.solution | 3 - .../set_card_00/expected/model_4_3_3.eprime | 30 - .../model_4_3_4-solution000001.solution | 3 - .../model_4_3_4-solution000002.solution | 3 - .../set_card_00/expected/model_4_3_4.eprime | 30 - .../model_4_4_1-solution000001.solution | 3 - .../model_4_4_1-solution000002.solution | 3 - .../set_card_00/expected/model_4_4_1.eprime | 19 - .../model_4_4_2-solution000001.solution | 3 - .../model_4_4_2-solution000002.solution | 3 - .../set_card_00/expected/model_4_4_2.eprime | 26 - .../model_4_4_3-solution000001.solution | 3 - .../model_4_4_3-solution000002.solution | 3 - .../set_card_00/expected/model_4_4_3.eprime | 30 - .../model_4_4_4-solution000001.solution | 3 - .../model_4_4_4-solution000002.solution | 3 - .../set_card_00/expected/model_4_4_4.eprime | 13 - .../model_1_1_1_1_1-solution000001.solution | 4 - .../model_1_1_1_1_1-solution000002.solution | 4 - .../model_1_1_1_1_1-solution000003.solution | 4 - .../model_1_1_1_1_1-solution000004.solution | 4 - .../model_1_1_1_1_1-solution000005.solution | 4 - .../model_1_1_1_1_1-solution000006.solution | 4 - .../model_1_1_1_1_1-solution000007.solution | 4 - .../model_1_1_1_1_1-solution000008.solution | 4 - .../model_1_1_1_1_1-solution000009.solution | 4 - .../model_1_1_1_1_1-solution000010.solution | 4 - .../model_1_1_1_1_1-solution000011.solution | 4 - .../model_1_1_1_1_1-solution000012.solution | 4 - .../expected/model_1_1_1_1_1.eprime | 34 - .../model_1_1_1_1_2-solution000001.solution | 4 - .../model_1_1_1_1_2-solution000002.solution | 4 - .../model_1_1_1_1_2-solution000003.solution | 4 - .../model_1_1_1_1_2-solution000004.solution | 4 - .../model_1_1_1_1_2-solution000005.solution | 4 - .../model_1_1_1_1_2-solution000006.solution | 4 - .../model_1_1_1_1_2-solution000007.solution | 4 - .../model_1_1_1_1_2-solution000008.solution | 4 - .../model_1_1_1_1_2-solution000009.solution | 4 - .../model_1_1_1_1_2-solution000010.solution | 4 - .../model_1_1_1_1_2-solution000011.solution | 4 - .../model_1_1_1_1_2-solution000012.solution | 4 - .../expected/model_1_1_1_1_2.eprime | 38 - .../model_1_1_1_2_1-solution000001.solution | 4 - .../model_1_1_1_2_1-solution000002.solution | 4 - .../model_1_1_1_2_1-solution000003.solution | 4 - .../model_1_1_1_2_1-solution000004.solution | 4 - .../model_1_1_1_2_1-solution000005.solution | 4 - .../model_1_1_1_2_1-solution000006.solution | 4 - .../model_1_1_1_2_1-solution000007.solution | 4 - .../model_1_1_1_2_1-solution000008.solution | 4 - .../model_1_1_1_2_1-solution000009.solution | 4 - .../model_1_1_1_2_1-solution000010.solution | 4 - .../model_1_1_1_2_1-solution000011.solution | 4 - .../model_1_1_1_2_1-solution000012.solution | 4 - .../expected/model_1_1_1_2_1.eprime | 33 - .../model_1_1_1_2_2-solution000001.solution | 4 - .../model_1_1_1_2_2-solution000002.solution | 4 - .../model_1_1_1_2_2-solution000003.solution | 4 - .../model_1_1_1_2_2-solution000004.solution | 4 - .../model_1_1_1_2_2-solution000005.solution | 4 - .../model_1_1_1_2_2-solution000006.solution | 4 - .../model_1_1_1_2_2-solution000007.solution | 4 - .../model_1_1_1_2_2-solution000008.solution | 4 - .../model_1_1_1_2_2-solution000009.solution | 4 - .../model_1_1_1_2_2-solution000010.solution | 4 - .../model_1_1_1_2_2-solution000011.solution | 4 - .../model_1_1_1_2_2-solution000012.solution | 4 - .../expected/model_1_1_1_2_2.eprime | 33 - .../model_1_1_2_1_1-solution000001.solution | 4 - .../model_1_1_2_1_1-solution000002.solution | 4 - .../model_1_1_2_1_1-solution000003.solution | 4 - .../model_1_1_2_1_1-solution000004.solution | 4 - .../model_1_1_2_1_1-solution000005.solution | 4 - .../model_1_1_2_1_1-solution000006.solution | 4 - .../model_1_1_2_1_1-solution000007.solution | 4 - .../model_1_1_2_1_1-solution000008.solution | 4 - .../model_1_1_2_1_1-solution000009.solution | 4 - .../model_1_1_2_1_1-solution000010.solution | 4 - .../model_1_1_2_1_1-solution000011.solution | 4 - .../model_1_1_2_1_1-solution000012.solution | 4 - .../expected/model_1_1_2_1_1.eprime | 35 - .../model_1_1_2_1_2-solution000001.solution | 4 - .../model_1_1_2_1_2-solution000002.solution | 4 - .../model_1_1_2_1_2-solution000003.solution | 4 - .../model_1_1_2_1_2-solution000004.solution | 4 - .../model_1_1_2_1_2-solution000005.solution | 4 - .../model_1_1_2_1_2-solution000006.solution | 4 - .../model_1_1_2_1_2-solution000007.solution | 4 - .../model_1_1_2_1_2-solution000008.solution | 4 - .../model_1_1_2_1_2-solution000009.solution | 4 - .../model_1_1_2_1_2-solution000010.solution | 4 - .../model_1_1_2_1_2-solution000011.solution | 4 - .../model_1_1_2_1_2-solution000012.solution | 4 - .../expected/model_1_1_2_1_2.eprime | 35 - .../model_1_1_2_2_1-solution000001.solution | 4 - .../model_1_1_2_2_1-solution000002.solution | 4 - .../model_1_1_2_2_1-solution000003.solution | 4 - .../model_1_1_2_2_1-solution000004.solution | 4 - .../model_1_1_2_2_1-solution000005.solution | 4 - .../model_1_1_2_2_1-solution000006.solution | 4 - .../model_1_1_2_2_1-solution000007.solution | 4 - .../model_1_1_2_2_1-solution000008.solution | 4 - .../model_1_1_2_2_1-solution000009.solution | 4 - .../model_1_1_2_2_1-solution000010.solution | 4 - .../model_1_1_2_2_1-solution000011.solution | 4 - .../model_1_1_2_2_1-solution000012.solution | 4 - .../expected/model_1_1_2_2_1.eprime | 30 - .../model_1_1_2_2_2-solution000001.solution | 4 - .../model_1_1_2_2_2-solution000002.solution | 4 - .../model_1_1_2_2_2-solution000003.solution | 4 - .../model_1_1_2_2_2-solution000004.solution | 4 - .../model_1_1_2_2_2-solution000005.solution | 4 - .../model_1_1_2_2_2-solution000006.solution | 4 - .../model_1_1_2_2_2-solution000007.solution | 4 - .../model_1_1_2_2_2-solution000008.solution | 4 - .../model_1_1_2_2_2-solution000009.solution | 4 - .../model_1_1_2_2_2-solution000010.solution | 4 - .../model_1_1_2_2_2-solution000011.solution | 4 - .../model_1_1_2_2_2-solution000012.solution | 4 - .../expected/model_1_1_2_2_2.eprime | 30 - .../model_1_2_1_1_1-solution000001.solution | 4 - .../model_1_2_1_1_1-solution000002.solution | 4 - .../model_1_2_1_1_1-solution000003.solution | 4 - .../model_1_2_1_1_1-solution000004.solution | 4 - .../model_1_2_1_1_1-solution000005.solution | 4 - .../model_1_2_1_1_1-solution000006.solution | 4 - .../model_1_2_1_1_1-solution000007.solution | 4 - .../model_1_2_1_1_1-solution000008.solution | 4 - .../model_1_2_1_1_1-solution000009.solution | 4 - .../model_1_2_1_1_1-solution000010.solution | 4 - .../model_1_2_1_1_1-solution000011.solution | 4 - .../model_1_2_1_1_1-solution000012.solution | 4 - .../expected/model_1_2_1_1_1.eprime | 24 - .../model_1_2_1_1_2-solution000001.solution | 4 - .../model_1_2_1_1_2-solution000002.solution | 4 - .../model_1_2_1_1_2-solution000003.solution | 4 - .../model_1_2_1_1_2-solution000004.solution | 4 - .../model_1_2_1_1_2-solution000005.solution | 4 - .../model_1_2_1_1_2-solution000006.solution | 4 - .../model_1_2_1_1_2-solution000007.solution | 4 - .../model_1_2_1_1_2-solution000008.solution | 4 - .../model_1_2_1_1_2-solution000009.solution | 4 - .../model_1_2_1_1_2-solution000010.solution | 4 - .../model_1_2_1_1_2-solution000011.solution | 4 - .../model_1_2_1_1_2-solution000012.solution | 4 - .../expected/model_1_2_1_1_2.eprime | 24 - .../model_1_2_1_2_1-solution000001.solution | 4 - .../model_1_2_1_2_1-solution000002.solution | 4 - .../model_1_2_1_2_1-solution000003.solution | 4 - .../model_1_2_1_2_1-solution000004.solution | 4 - .../model_1_2_1_2_1-solution000005.solution | 4 - .../model_1_2_1_2_1-solution000006.solution | 4 - .../model_1_2_1_2_1-solution000007.solution | 4 - .../model_1_2_1_2_1-solution000008.solution | 4 - .../model_1_2_1_2_1-solution000009.solution | 4 - .../model_1_2_1_2_1-solution000010.solution | 4 - .../model_1_2_1_2_1-solution000011.solution | 4 - .../model_1_2_1_2_1-solution000012.solution | 4 - .../expected/model_1_2_1_2_1.eprime | 19 - .../model_1_2_1_2_2-solution000001.solution | 4 - .../model_1_2_1_2_2-solution000002.solution | 4 - .../model_1_2_1_2_2-solution000003.solution | 4 - .../model_1_2_1_2_2-solution000004.solution | 4 - .../model_1_2_1_2_2-solution000005.solution | 4 - .../model_1_2_1_2_2-solution000006.solution | 4 - .../model_1_2_1_2_2-solution000007.solution | 4 - .../model_1_2_1_2_2-solution000008.solution | 4 - .../model_1_2_1_2_2-solution000009.solution | 4 - .../model_1_2_1_2_2-solution000010.solution | 4 - .../model_1_2_1_2_2-solution000011.solution | 4 - .../model_1_2_1_2_2-solution000012.solution | 4 - .../expected/model_1_2_1_2_2.eprime | 19 - .../model_1_2_2_1_1-solution000001.solution | 4 - .../model_1_2_2_1_1-solution000002.solution | 4 - .../model_1_2_2_1_1-solution000003.solution | 4 - .../model_1_2_2_1_1-solution000004.solution | 4 - .../model_1_2_2_1_1-solution000005.solution | 4 - .../model_1_2_2_1_1-solution000006.solution | 4 - .../model_1_2_2_1_1-solution000007.solution | 4 - .../model_1_2_2_1_1-solution000008.solution | 4 - .../model_1_2_2_1_1-solution000009.solution | 4 - .../model_1_2_2_1_1-solution000010.solution | 4 - .../model_1_2_2_1_1-solution000011.solution | 4 - .../model_1_2_2_1_1-solution000012.solution | 4 - .../expected/model_1_2_2_1_1.eprime | 23 - .../model_1_2_2_1_2-solution000001.solution | 4 - .../model_1_2_2_1_2-solution000002.solution | 4 - .../model_1_2_2_1_2-solution000003.solution | 4 - .../model_1_2_2_1_2-solution000004.solution | 4 - .../model_1_2_2_1_2-solution000005.solution | 4 - .../model_1_2_2_1_2-solution000006.solution | 4 - .../model_1_2_2_1_2-solution000007.solution | 4 - .../model_1_2_2_1_2-solution000008.solution | 4 - .../model_1_2_2_1_2-solution000009.solution | 4 - .../model_1_2_2_1_2-solution000010.solution | 4 - .../model_1_2_2_1_2-solution000011.solution | 4 - .../model_1_2_2_1_2-solution000012.solution | 4 - .../expected/model_1_2_2_1_2.eprime | 23 - .../model_1_2_2_2_1-solution000001.solution | 4 - .../model_1_2_2_2_1-solution000002.solution | 4 - .../model_1_2_2_2_1-solution000003.solution | 4 - .../model_1_2_2_2_1-solution000004.solution | 4 - .../model_1_2_2_2_1-solution000005.solution | 4 - .../model_1_2_2_2_1-solution000006.solution | 4 - .../model_1_2_2_2_1-solution000007.solution | 4 - .../model_1_2_2_2_1-solution000008.solution | 4 - .../model_1_2_2_2_1-solution000009.solution | 4 - .../model_1_2_2_2_1-solution000010.solution | 4 - .../model_1_2_2_2_1-solution000011.solution | 4 - .../model_1_2_2_2_1-solution000012.solution | 4 - .../expected/model_1_2_2_2_1.eprime | 18 - .../model_1_2_2_2_2-solution000001.solution | 4 - .../model_1_2_2_2_2-solution000002.solution | 4 - .../model_1_2_2_2_2-solution000003.solution | 4 - .../model_1_2_2_2_2-solution000004.solution | 4 - .../model_1_2_2_2_2-solution000005.solution | 4 - .../model_1_2_2_2_2-solution000006.solution | 4 - .../model_1_2_2_2_2-solution000007.solution | 4 - .../model_1_2_2_2_2-solution000008.solution | 4 - .../model_1_2_2_2_2-solution000009.solution | 4 - .../model_1_2_2_2_2-solution000010.solution | 4 - .../model_1_2_2_2_2-solution000011.solution | 4 - .../model_1_2_2_2_2-solution000012.solution | 4 - .../expected/model_1_2_2_2_2.eprime | 18 - .../model_2_1_1_1_1-solution000001.solution | 4 - .../model_2_1_1_1_1-solution000002.solution | 4 - .../model_2_1_1_1_1-solution000003.solution | 4 - .../model_2_1_1_1_1-solution000004.solution | 4 - .../model_2_1_1_1_1-solution000005.solution | 4 - .../model_2_1_1_1_1-solution000006.solution | 4 - .../model_2_1_1_1_1-solution000007.solution | 4 - .../model_2_1_1_1_1-solution000008.solution | 4 - .../model_2_1_1_1_1-solution000009.solution | 4 - .../model_2_1_1_1_1-solution000010.solution | 4 - .../model_2_1_1_1_1-solution000011.solution | 4 - .../model_2_1_1_1_1-solution000012.solution | 4 - .../expected/model_2_1_1_1_1.eprime | 39 - .../model_2_1_1_1_2-solution000001.solution | 4 - .../model_2_1_1_1_2-solution000002.solution | 4 - .../model_2_1_1_1_2-solution000003.solution | 4 - .../model_2_1_1_1_2-solution000004.solution | 4 - .../model_2_1_1_1_2-solution000005.solution | 4 - .../model_2_1_1_1_2-solution000006.solution | 4 - .../model_2_1_1_1_2-solution000007.solution | 4 - .../model_2_1_1_1_2-solution000008.solution | 4 - .../model_2_1_1_1_2-solution000009.solution | 4 - .../model_2_1_1_1_2-solution000010.solution | 4 - .../model_2_1_1_1_2-solution000011.solution | 4 - .../model_2_1_1_1_2-solution000012.solution | 4 - .../expected/model_2_1_1_1_2.eprime | 39 - .../model_2_1_1_2_1-solution000001.solution | 4 - .../model_2_1_1_2_1-solution000002.solution | 4 - .../model_2_1_1_2_1-solution000003.solution | 4 - .../model_2_1_1_2_1-solution000004.solution | 4 - .../model_2_1_1_2_1-solution000005.solution | 4 - .../model_2_1_1_2_1-solution000006.solution | 4 - .../model_2_1_1_2_1-solution000007.solution | 4 - .../model_2_1_1_2_1-solution000008.solution | 4 - .../model_2_1_1_2_1-solution000009.solution | 4 - .../model_2_1_1_2_1-solution000010.solution | 4 - .../model_2_1_1_2_1-solution000011.solution | 4 - .../model_2_1_1_2_1-solution000012.solution | 4 - .../expected/model_2_1_1_2_1.eprime | 34 - .../model_2_1_1_2_2-solution000001.solution | 4 - .../model_2_1_1_2_2-solution000002.solution | 4 - .../model_2_1_1_2_2-solution000003.solution | 4 - .../model_2_1_1_2_2-solution000004.solution | 4 - .../model_2_1_1_2_2-solution000005.solution | 4 - .../model_2_1_1_2_2-solution000006.solution | 4 - .../model_2_1_1_2_2-solution000007.solution | 4 - .../model_2_1_1_2_2-solution000008.solution | 4 - .../model_2_1_1_2_2-solution000009.solution | 4 - .../model_2_1_1_2_2-solution000010.solution | 4 - .../model_2_1_1_2_2-solution000011.solution | 4 - .../model_2_1_1_2_2-solution000012.solution | 4 - .../expected/model_2_1_1_2_2.eprime | 34 - .../model_2_1_2_1_1-solution000001.solution | 4 - .../model_2_1_2_1_1-solution000002.solution | 4 - .../model_2_1_2_1_1-solution000003.solution | 4 - .../model_2_1_2_1_1-solution000004.solution | 4 - .../model_2_1_2_1_1-solution000005.solution | 4 - .../model_2_1_2_1_1-solution000006.solution | 4 - .../model_2_1_2_1_1-solution000007.solution | 4 - .../model_2_1_2_1_1-solution000008.solution | 4 - .../model_2_1_2_1_1-solution000009.solution | 4 - .../model_2_1_2_1_1-solution000010.solution | 4 - .../model_2_1_2_1_1-solution000011.solution | 4 - .../model_2_1_2_1_1-solution000012.solution | 4 - .../expected/model_2_1_2_1_1.eprime | 36 - .../model_2_1_2_1_2-solution000001.solution | 4 - .../model_2_1_2_1_2-solution000002.solution | 4 - .../model_2_1_2_1_2-solution000003.solution | 4 - .../model_2_1_2_1_2-solution000004.solution | 4 - .../model_2_1_2_1_2-solution000005.solution | 4 - .../model_2_1_2_1_2-solution000006.solution | 4 - .../model_2_1_2_1_2-solution000007.solution | 4 - .../model_2_1_2_1_2-solution000008.solution | 4 - .../model_2_1_2_1_2-solution000009.solution | 4 - .../model_2_1_2_1_2-solution000010.solution | 4 - .../model_2_1_2_1_2-solution000011.solution | 4 - .../model_2_1_2_1_2-solution000012.solution | 4 - .../expected/model_2_1_2_1_2.eprime | 36 - .../model_2_1_2_2_1-solution000001.solution | 4 - .../model_2_1_2_2_1-solution000002.solution | 4 - .../model_2_1_2_2_1-solution000003.solution | 4 - .../model_2_1_2_2_1-solution000004.solution | 4 - .../model_2_1_2_2_1-solution000005.solution | 4 - .../model_2_1_2_2_1-solution000006.solution | 4 - .../model_2_1_2_2_1-solution000007.solution | 4 - .../model_2_1_2_2_1-solution000008.solution | 4 - .../model_2_1_2_2_1-solution000009.solution | 4 - .../model_2_1_2_2_1-solution000010.solution | 4 - .../model_2_1_2_2_1-solution000011.solution | 4 - .../model_2_1_2_2_1-solution000012.solution | 4 - .../expected/model_2_1_2_2_1.eprime | 31 - .../model_2_1_2_2_2-solution000001.solution | 4 - .../model_2_1_2_2_2-solution000002.solution | 4 - .../model_2_1_2_2_2-solution000003.solution | 4 - .../model_2_1_2_2_2-solution000004.solution | 4 - .../model_2_1_2_2_2-solution000005.solution | 4 - .../model_2_1_2_2_2-solution000006.solution | 4 - .../model_2_1_2_2_2-solution000007.solution | 4 - .../model_2_1_2_2_2-solution000008.solution | 4 - .../model_2_1_2_2_2-solution000009.solution | 4 - .../model_2_1_2_2_2-solution000010.solution | 4 - .../model_2_1_2_2_2-solution000011.solution | 4 - .../model_2_1_2_2_2-solution000012.solution | 4 - .../expected/model_2_1_2_2_2.eprime | 31 - .../model_2_2_1_1_1-solution000001.solution | 4 - .../model_2_2_1_1_1-solution000002.solution | 4 - .../model_2_2_1_1_1-solution000003.solution | 4 - .../model_2_2_1_1_1-solution000004.solution | 4 - .../model_2_2_1_1_1-solution000005.solution | 4 - .../model_2_2_1_1_1-solution000006.solution | 4 - .../model_2_2_1_1_1-solution000007.solution | 4 - .../model_2_2_1_1_1-solution000008.solution | 4 - .../model_2_2_1_1_1-solution000009.solution | 4 - .../model_2_2_1_1_1-solution000010.solution | 4 - .../model_2_2_1_1_1-solution000011.solution | 4 - .../model_2_2_1_1_1-solution000012.solution | 4 - .../expected/model_2_2_1_1_1.eprime | 25 - .../model_2_2_1_1_2-solution000001.solution | 4 - .../model_2_2_1_1_2-solution000002.solution | 4 - .../model_2_2_1_1_2-solution000003.solution | 4 - .../model_2_2_1_1_2-solution000004.solution | 4 - .../model_2_2_1_1_2-solution000005.solution | 4 - .../model_2_2_1_1_2-solution000006.solution | 4 - .../model_2_2_1_1_2-solution000007.solution | 4 - .../model_2_2_1_1_2-solution000008.solution | 4 - .../model_2_2_1_1_2-solution000009.solution | 4 - .../model_2_2_1_1_2-solution000010.solution | 4 - .../model_2_2_1_1_2-solution000011.solution | 4 - .../model_2_2_1_1_2-solution000012.solution | 4 - .../expected/model_2_2_1_1_2.eprime | 25 - .../model_2_2_1_2_1-solution000001.solution | 4 - .../model_2_2_1_2_1-solution000002.solution | 4 - .../model_2_2_1_2_1-solution000003.solution | 4 - .../model_2_2_1_2_1-solution000004.solution | 4 - .../model_2_2_1_2_1-solution000005.solution | 4 - .../model_2_2_1_2_1-solution000006.solution | 4 - .../model_2_2_1_2_1-solution000007.solution | 4 - .../model_2_2_1_2_1-solution000008.solution | 4 - .../model_2_2_1_2_1-solution000009.solution | 4 - .../model_2_2_1_2_1-solution000010.solution | 4 - .../model_2_2_1_2_1-solution000011.solution | 4 - .../model_2_2_1_2_1-solution000012.solution | 4 - .../expected/model_2_2_1_2_1.eprime | 20 - .../model_2_2_1_2_2-solution000001.solution | 4 - .../model_2_2_1_2_2-solution000002.solution | 4 - .../model_2_2_1_2_2-solution000003.solution | 4 - .../model_2_2_1_2_2-solution000004.solution | 4 - .../model_2_2_1_2_2-solution000005.solution | 4 - .../model_2_2_1_2_2-solution000006.solution | 4 - .../model_2_2_1_2_2-solution000007.solution | 4 - .../model_2_2_1_2_2-solution000008.solution | 4 - .../model_2_2_1_2_2-solution000009.solution | 4 - .../model_2_2_1_2_2-solution000010.solution | 4 - .../model_2_2_1_2_2-solution000011.solution | 4 - .../model_2_2_1_2_2-solution000012.solution | 4 - .../expected/model_2_2_1_2_2.eprime | 20 - .../model_2_2_2_1_1-solution000001.solution | 4 - .../model_2_2_2_1_1-solution000002.solution | 4 - .../model_2_2_2_1_1-solution000003.solution | 4 - .../model_2_2_2_1_1-solution000004.solution | 4 - .../model_2_2_2_1_1-solution000005.solution | 4 - .../model_2_2_2_1_1-solution000006.solution | 4 - .../model_2_2_2_1_1-solution000007.solution | 4 - .../model_2_2_2_1_1-solution000008.solution | 4 - .../model_2_2_2_1_1-solution000009.solution | 4 - .../model_2_2_2_1_1-solution000010.solution | 4 - .../model_2_2_2_1_1-solution000011.solution | 4 - .../model_2_2_2_1_1-solution000012.solution | 4 - .../expected/model_2_2_2_1_1.eprime | 24 - .../model_2_2_2_1_2-solution000001.solution | 4 - .../model_2_2_2_1_2-solution000002.solution | 4 - .../model_2_2_2_1_2-solution000003.solution | 4 - .../model_2_2_2_1_2-solution000004.solution | 4 - .../model_2_2_2_1_2-solution000005.solution | 4 - .../model_2_2_2_1_2-solution000006.solution | 4 - .../model_2_2_2_1_2-solution000007.solution | 4 - .../model_2_2_2_1_2-solution000008.solution | 4 - .../model_2_2_2_1_2-solution000009.solution | 4 - .../model_2_2_2_1_2-solution000010.solution | 4 - .../model_2_2_2_1_2-solution000011.solution | 4 - .../model_2_2_2_1_2-solution000012.solution | 4 - .../expected/model_2_2_2_1_2.eprime | 24 - .../model_2_2_2_2_1-solution000001.solution | 4 - .../model_2_2_2_2_1-solution000002.solution | 4 - .../model_2_2_2_2_1-solution000003.solution | 4 - .../model_2_2_2_2_1-solution000004.solution | 4 - .../model_2_2_2_2_1-solution000005.solution | 4 - .../model_2_2_2_2_1-solution000006.solution | 4 - .../model_2_2_2_2_1-solution000007.solution | 4 - .../model_2_2_2_2_1-solution000008.solution | 4 - .../model_2_2_2_2_1-solution000009.solution | 4 - .../model_2_2_2_2_1-solution000010.solution | 4 - .../model_2_2_2_2_1-solution000011.solution | 4 - .../model_2_2_2_2_1-solution000012.solution | 4 - .../expected/model_2_2_2_2_1.eprime | 19 - .../model_2_2_2_2_2-solution000001.solution | 4 - .../model_2_2_2_2_2-solution000002.solution | 4 - .../model_2_2_2_2_2-solution000003.solution | 4 - .../model_2_2_2_2_2-solution000004.solution | 4 - .../model_2_2_2_2_2-solution000005.solution | 4 - .../model_2_2_2_2_2-solution000006.solution | 4 - .../model_2_2_2_2_2-solution000007.solution | 4 - .../model_2_2_2_2_2-solution000008.solution | 4 - .../model_2_2_2_2_2-solution000009.solution | 4 - .../model_2_2_2_2_2-solution000010.solution | 4 - .../model_2_2_2_2_2-solution000011.solution | 4 - .../model_2_2_2_2_2-solution000012.solution | 4 - .../expected/model_2_2_2_2_2.eprime | 15 - .../model_1_1_1_1-solution000001.solution | 4 - .../model_1_1_1_1-solution000002.solution | 4 - .../model_1_1_1_1-solution000003.solution | 4 - .../typed01/expected/model_1_1_1_1.eprime | 7 - .../model_1_1_1_2-solution000001.solution | 4 - .../model_1_1_1_2-solution000002.solution | 4 - .../model_1_1_1_2-solution000003.solution | 4 - .../typed01/expected/model_1_1_1_2.eprime | 11 - .../model_1_1_1_3-solution000001.solution | 4 - .../model_1_1_1_3-solution000002.solution | 4 - .../model_1_1_1_3-solution000003.solution | 4 - .../typed01/expected/model_1_1_1_3.eprime | 13 - .../model_1_1_1_4-solution000001.solution | 4 - .../model_1_1_1_4-solution000002.solution | 4 - .../model_1_1_1_4-solution000003.solution | 4 - .../typed01/expected/model_1_1_1_4.eprime | 13 - .../model_1_1_2_1-solution000001.solution | 4 - .../model_1_1_2_1-solution000002.solution | 4 - .../model_1_1_2_1-solution000003.solution | 4 - .../typed01/expected/model_1_1_2_1.eprime | 11 - .../model_1_1_2_2-solution000001.solution | 4 - .../model_1_1_2_2-solution000002.solution | 4 - .../model_1_1_2_2-solution000003.solution | 4 - .../typed01/expected/model_1_1_2_2.eprime | 14 - .../model_1_1_2_3-solution000001.solution | 4 - .../model_1_1_2_3-solution000002.solution | 4 - .../model_1_1_2_3-solution000003.solution | 4 - .../typed01/expected/model_1_1_2_3.eprime | 18 - .../model_1_1_2_4-solution000001.solution | 4 - .../model_1_1_2_4-solution000002.solution | 4 - .../model_1_1_2_4-solution000003.solution | 4 - .../typed01/expected/model_1_1_2_4.eprime | 18 - .../model_1_1_3_1-solution000001.solution | 4 - .../model_1_1_3_1-solution000002.solution | 4 - .../model_1_1_3_1-solution000003.solution | 4 - .../typed01/expected/model_1_1_3_1.eprime | 13 - .../model_1_1_3_2-solution000001.solution | 4 - .../model_1_1_3_2-solution000002.solution | 4 - .../model_1_1_3_2-solution000003.solution | 4 - .../typed01/expected/model_1_1_3_2.eprime | 18 - .../model_1_1_3_3-solution000001.solution | 4 - .../model_1_1_3_3-solution000002.solution | 4 - .../model_1_1_3_3-solution000003.solution | 4 - .../typed01/expected/model_1_1_3_3.eprime | 20 - .../model_1_1_3_4-solution000001.solution | 4 - .../model_1_1_3_4-solution000002.solution | 4 - .../model_1_1_3_4-solution000003.solution | 4 - .../typed01/expected/model_1_1_3_4.eprime | 20 - .../model_1_1_4_1-solution000001.solution | 4 - .../model_1_1_4_1-solution000002.solution | 4 - .../model_1_1_4_1-solution000003.solution | 4 - .../typed01/expected/model_1_1_4_1.eprime | 13 - .../model_1_1_4_2-solution000001.solution | 4 - .../model_1_1_4_2-solution000002.solution | 4 - .../model_1_1_4_2-solution000003.solution | 4 - .../typed01/expected/model_1_1_4_2.eprime | 18 - .../model_1_1_4_3-solution000001.solution | 4 - .../model_1_1_4_3-solution000002.solution | 4 - .../model_1_1_4_3-solution000003.solution | 4 - .../typed01/expected/model_1_1_4_3.eprime | 20 - .../model_1_1_4_4-solution000001.solution | 4 - .../model_1_1_4_4-solution000002.solution | 4 - .../model_1_1_4_4-solution000003.solution | 4 - .../typed01/expected/model_1_1_4_4.eprime | 20 - .../model_1_2_1_1-solution000001.solution | 4 - .../model_1_2_1_1-solution000002.solution | 4 - .../model_1_2_1_1-solution000003.solution | 4 - .../typed01/expected/model_1_2_1_1.eprime | 11 - .../model_1_2_1_2-solution000001.solution | 4 - .../model_1_2_1_2-solution000002.solution | 4 - .../model_1_2_1_2-solution000003.solution | 4 - .../typed01/expected/model_1_2_1_2.eprime | 7 - .../model_1_2_1_3-solution000001.solution | 4 - .../model_1_2_1_3-solution000002.solution | 4 - .../model_1_2_1_3-solution000003.solution | 4 - .../typed01/expected/model_1_2_1_3.eprime | 16 - .../model_1_2_1_4-solution000001.solution | 4 - .../model_1_2_1_4-solution000002.solution | 4 - .../model_1_2_1_4-solution000003.solution | 4 - .../typed01/expected/model_1_2_1_4.eprime | 16 - .../model_1_2_2_1-solution000001.solution | 4 - .../model_1_2_2_1-solution000002.solution | 4 - .../model_1_2_2_1-solution000003.solution | 4 - .../typed01/expected/model_1_2_2_1.eprime | 14 - .../model_1_2_2_2-solution000001.solution | 4 - .../model_1_2_2_2-solution000002.solution | 4 - .../model_1_2_2_2-solution000003.solution | 4 - .../typed01/expected/model_1_2_2_2.eprime | 11 - .../model_1_2_2_3-solution000001.solution | 4 - .../model_1_2_2_3-solution000002.solution | 4 - .../model_1_2_2_3-solution000003.solution | 4 - .../typed01/expected/model_1_2_2_3.eprime | 20 - .../model_1_2_2_4-solution000001.solution | 4 - .../model_1_2_2_4-solution000002.solution | 4 - .../model_1_2_2_4-solution000003.solution | 4 - .../typed01/expected/model_1_2_2_4.eprime | 20 - .../model_1_2_3_1-solution000001.solution | 4 - .../model_1_2_3_1-solution000002.solution | 4 - .../model_1_2_3_1-solution000003.solution | 4 - .../typed01/expected/model_1_2_3_1.eprime | 18 - .../model_1_2_3_2-solution000001.solution | 4 - .../model_1_2_3_2-solution000002.solution | 4 - .../model_1_2_3_2-solution000003.solution | 4 - .../typed01/expected/model_1_2_3_2.eprime | 14 - .../model_1_2_3_3-solution000001.solution | 4 - .../model_1_2_3_3-solution000002.solution | 4 - .../model_1_2_3_3-solution000003.solution | 4 - .../typed01/expected/model_1_2_3_3.eprime | 22 - .../model_1_2_3_4-solution000001.solution | 4 - .../model_1_2_3_4-solution000002.solution | 4 - .../model_1_2_3_4-solution000003.solution | 4 - .../typed01/expected/model_1_2_3_4.eprime | 22 - .../model_1_2_4_1-solution000001.solution | 4 - .../model_1_2_4_1-solution000002.solution | 4 - .../model_1_2_4_1-solution000003.solution | 4 - .../typed01/expected/model_1_2_4_1.eprime | 18 - .../model_1_2_4_2-solution000001.solution | 4 - .../model_1_2_4_2-solution000002.solution | 4 - .../model_1_2_4_2-solution000003.solution | 4 - .../typed01/expected/model_1_2_4_2.eprime | 14 - .../model_1_2_4_3-solution000001.solution | 4 - .../model_1_2_4_3-solution000002.solution | 4 - .../model_1_2_4_3-solution000003.solution | 4 - .../typed01/expected/model_1_2_4_3.eprime | 22 - .../model_1_2_4_4-solution000001.solution | 4 - .../model_1_2_4_4-solution000002.solution | 4 - .../model_1_2_4_4-solution000003.solution | 4 - .../typed01/expected/model_1_2_4_4.eprime | 22 - .../model_1_3_1_1-solution000001.solution | 4 - .../model_1_3_1_1-solution000002.solution | 4 - .../model_1_3_1_1-solution000003.solution | 4 - .../typed01/expected/model_1_3_1_1.eprime | 13 - .../model_1_3_1_2-solution000001.solution | 4 - .../model_1_3_1_2-solution000002.solution | 4 - .../model_1_3_1_2-solution000003.solution | 4 - .../typed01/expected/model_1_3_1_2.eprime | 16 - .../model_1_3_1_3-solution000001.solution | 4 - .../model_1_3_1_3-solution000002.solution | 4 - .../model_1_3_1_3-solution000003.solution | 4 - .../typed01/expected/model_1_3_1_3.eprime | 10 - .../model_1_3_1_4-solution000001.solution | 4 - .../model_1_3_1_4-solution000002.solution | 4 - .../model_1_3_1_4-solution000003.solution | 4 - .../typed01/expected/model_1_3_1_4.eprime | 20 - .../model_1_3_2_1-solution000001.solution | 4 - .../model_1_3_2_1-solution000002.solution | 4 - .../model_1_3_2_1-solution000003.solution | 4 - .../typed01/expected/model_1_3_2_1.eprime | 18 - .../model_1_3_2_2-solution000001.solution | 4 - .../model_1_3_2_2-solution000002.solution | 4 - .../model_1_3_2_2-solution000003.solution | 4 - .../typed01/expected/model_1_3_2_2.eprime | 20 - .../model_1_3_2_3-solution000001.solution | 4 - .../model_1_3_2_3-solution000002.solution | 4 - .../model_1_3_2_3-solution000003.solution | 4 - .../typed01/expected/model_1_3_2_3.eprime | 14 - .../model_1_3_2_4-solution000001.solution | 4 - .../model_1_3_2_4-solution000002.solution | 4 - .../model_1_3_2_4-solution000003.solution | 4 - .../typed01/expected/model_1_3_2_4.eprime | 23 - .../model_1_3_3_1-solution000001.solution | 4 - .../model_1_3_3_1-solution000002.solution | 4 - .../model_1_3_3_1-solution000003.solution | 4 - .../typed01/expected/model_1_3_3_1.eprime | 20 - .../model_1_3_3_2-solution000001.solution | 4 - .../model_1_3_3_2-solution000002.solution | 4 - .../model_1_3_3_2-solution000003.solution | 4 - .../typed01/expected/model_1_3_3_2.eprime | 22 - .../model_1_3_3_3-solution000001.solution | 4 - .../model_1_3_3_3-solution000002.solution | 4 - .../model_1_3_3_3-solution000003.solution | 4 - .../typed01/expected/model_1_3_3_3.eprime | 17 - .../model_1_3_3_4-solution000001.solution | 4 - .../model_1_3_3_4-solution000002.solution | 4 - .../model_1_3_3_4-solution000003.solution | 4 - .../typed01/expected/model_1_3_3_4.eprime | 26 - .../model_1_3_4_1-solution000001.solution | 4 - .../model_1_3_4_1-solution000002.solution | 4 - .../model_1_3_4_1-solution000003.solution | 4 - .../typed01/expected/model_1_3_4_1.eprime | 20 - .../model_1_3_4_2-solution000001.solution | 4 - .../model_1_3_4_2-solution000002.solution | 4 - .../model_1_3_4_2-solution000003.solution | 4 - .../typed01/expected/model_1_3_4_2.eprime | 22 - .../model_1_3_4_3-solution000001.solution | 4 - .../model_1_3_4_3-solution000002.solution | 4 - .../model_1_3_4_3-solution000003.solution | 4 - .../typed01/expected/model_1_3_4_3.eprime | 17 - .../model_1_3_4_4-solution000001.solution | 4 - .../model_1_3_4_4-solution000002.solution | 4 - .../model_1_3_4_4-solution000003.solution | 4 - .../typed01/expected/model_1_3_4_4.eprime | 26 - .../model_1_4_1_1-solution000001.solution | 4 - .../model_1_4_1_1-solution000002.solution | 4 - .../model_1_4_1_1-solution000003.solution | 4 - .../typed01/expected/model_1_4_1_1.eprime | 13 - .../model_1_4_1_2-solution000001.solution | 4 - .../model_1_4_1_2-solution000002.solution | 4 - .../model_1_4_1_2-solution000003.solution | 4 - .../typed01/expected/model_1_4_1_2.eprime | 16 - .../model_1_4_1_3-solution000001.solution | 4 - .../model_1_4_1_3-solution000002.solution | 4 - .../model_1_4_1_3-solution000003.solution | 4 - .../typed01/expected/model_1_4_1_3.eprime | 20 - .../model_1_4_1_4-solution000001.solution | 4 - .../model_1_4_1_4-solution000002.solution | 4 - .../model_1_4_1_4-solution000003.solution | 4 - .../typed01/expected/model_1_4_1_4.eprime | 10 - .../model_1_4_2_1-solution000001.solution | 4 - .../model_1_4_2_1-solution000002.solution | 4 - .../model_1_4_2_1-solution000003.solution | 4 - .../typed01/expected/model_1_4_2_1.eprime | 18 - .../model_1_4_2_2-solution000001.solution | 4 - .../model_1_4_2_2-solution000002.solution | 4 - .../model_1_4_2_2-solution000003.solution | 4 - .../typed01/expected/model_1_4_2_2.eprime | 20 - .../model_1_4_2_3-solution000001.solution | 4 - .../model_1_4_2_3-solution000002.solution | 4 - .../model_1_4_2_3-solution000003.solution | 4 - .../typed01/expected/model_1_4_2_3.eprime | 23 - .../model_1_4_2_4-solution000001.solution | 4 - .../model_1_4_2_4-solution000002.solution | 4 - .../model_1_4_2_4-solution000003.solution | 4 - .../typed01/expected/model_1_4_2_4.eprime | 14 - .../model_1_4_3_1-solution000001.solution | 4 - .../model_1_4_3_1-solution000002.solution | 4 - .../model_1_4_3_1-solution000003.solution | 4 - .../typed01/expected/model_1_4_3_1.eprime | 20 - .../model_1_4_3_2-solution000001.solution | 4 - .../model_1_4_3_2-solution000002.solution | 4 - .../model_1_4_3_2-solution000003.solution | 4 - .../typed01/expected/model_1_4_3_2.eprime | 22 - .../model_1_4_3_3-solution000001.solution | 4 - .../model_1_4_3_3-solution000002.solution | 4 - .../model_1_4_3_3-solution000003.solution | 4 - .../typed01/expected/model_1_4_3_3.eprime | 26 - .../model_1_4_3_4-solution000001.solution | 4 - .../model_1_4_3_4-solution000002.solution | 4 - .../model_1_4_3_4-solution000003.solution | 4 - .../typed01/expected/model_1_4_3_4.eprime | 17 - .../model_1_4_4_1-solution000001.solution | 4 - .../model_1_4_4_1-solution000002.solution | 4 - .../model_1_4_4_1-solution000003.solution | 4 - .../typed01/expected/model_1_4_4_1.eprime | 20 - .../model_1_4_4_2-solution000001.solution | 4 - .../model_1_4_4_2-solution000002.solution | 4 - .../model_1_4_4_2-solution000003.solution | 4 - .../typed01/expected/model_1_4_4_2.eprime | 22 - .../model_1_4_4_3-solution000001.solution | 4 - .../model_1_4_4_3-solution000002.solution | 4 - .../model_1_4_4_3-solution000003.solution | 4 - .../typed01/expected/model_1_4_4_3.eprime | 26 - .../model_1_4_4_4-solution000001.solution | 4 - .../model_1_4_4_4-solution000002.solution | 4 - .../model_1_4_4_4-solution000003.solution | 4 - .../typed01/expected/model_1_4_4_4.eprime | 17 - .../model_2_1_1_1-solution000001.solution | 4 - .../model_2_1_1_1-solution000002.solution | 4 - .../model_2_1_1_1-solution000003.solution | 4 - .../typed01/expected/model_2_1_1_1.eprime | 11 - .../model_2_1_1_2-solution000001.solution | 4 - .../model_2_1_1_2-solution000002.solution | 4 - .../model_2_1_1_2-solution000003.solution | 4 - .../typed01/expected/model_2_1_1_2.eprime | 14 - .../model_2_1_1_3-solution000001.solution | 4 - .../model_2_1_1_3-solution000002.solution | 4 - .../model_2_1_1_3-solution000003.solution | 4 - .../typed01/expected/model_2_1_1_3.eprime | 18 - .../model_2_1_1_4-solution000001.solution | 4 - .../model_2_1_1_4-solution000002.solution | 4 - .../model_2_1_1_4-solution000003.solution | 4 - .../typed01/expected/model_2_1_1_4.eprime | 18 - .../model_2_1_2_1-solution000001.solution | 4 - .../model_2_1_2_1-solution000002.solution | 4 - .../model_2_1_2_1-solution000003.solution | 4 - .../typed01/expected/model_2_1_2_1.eprime | 7 - .../model_2_1_2_2-solution000001.solution | 4 - .../model_2_1_2_2-solution000002.solution | 4 - .../model_2_1_2_2-solution000003.solution | 4 - .../typed01/expected/model_2_1_2_2.eprime | 11 - .../model_2_1_2_3-solution000001.solution | 4 - .../model_2_1_2_3-solution000002.solution | 4 - .../model_2_1_2_3-solution000003.solution | 4 - .../typed01/expected/model_2_1_2_3.eprime | 14 - .../model_2_1_2_4-solution000001.solution | 4 - .../model_2_1_2_4-solution000002.solution | 4 - .../model_2_1_2_4-solution000003.solution | 4 - .../typed01/expected/model_2_1_2_4.eprime | 14 - .../model_2_1_3_1-solution000001.solution | 4 - .../model_2_1_3_1-solution000002.solution | 4 - .../model_2_1_3_1-solution000003.solution | 4 - .../typed01/expected/model_2_1_3_1.eprime | 16 - .../model_2_1_3_2-solution000001.solution | 4 - .../model_2_1_3_2-solution000002.solution | 4 - .../model_2_1_3_2-solution000003.solution | 4 - .../typed01/expected/model_2_1_3_2.eprime | 20 - .../model_2_1_3_3-solution000001.solution | 4 - .../model_2_1_3_3-solution000002.solution | 4 - .../model_2_1_3_3-solution000003.solution | 4 - .../typed01/expected/model_2_1_3_3.eprime | 22 - .../model_2_1_3_4-solution000001.solution | 4 - .../model_2_1_3_4-solution000002.solution | 4 - .../model_2_1_3_4-solution000003.solution | 4 - .../typed01/expected/model_2_1_3_4.eprime | 22 - .../model_2_1_4_1-solution000001.solution | 4 - .../model_2_1_4_1-solution000002.solution | 4 - .../model_2_1_4_1-solution000003.solution | 4 - .../typed01/expected/model_2_1_4_1.eprime | 16 - .../model_2_1_4_2-solution000001.solution | 4 - .../model_2_1_4_2-solution000002.solution | 4 - .../model_2_1_4_2-solution000003.solution | 4 - .../typed01/expected/model_2_1_4_2.eprime | 20 - .../model_2_1_4_3-solution000001.solution | 4 - .../model_2_1_4_3-solution000002.solution | 4 - .../model_2_1_4_3-solution000003.solution | 4 - .../typed01/expected/model_2_1_4_3.eprime | 22 - .../model_2_1_4_4-solution000001.solution | 4 - .../model_2_1_4_4-solution000002.solution | 4 - .../model_2_1_4_4-solution000003.solution | 4 - .../typed01/expected/model_2_1_4_4.eprime | 22 - .../model_2_2_1_1-solution000001.solution | 4 - .../model_2_2_1_1-solution000002.solution | 4 - .../model_2_2_1_1-solution000003.solution | 4 - .../typed01/expected/model_2_2_1_1.eprime | 16 - .../model_2_2_1_2-solution000001.solution | 4 - .../model_2_2_1_2-solution000002.solution | 4 - .../model_2_2_1_2-solution000003.solution | 4 - .../typed01/expected/model_2_2_1_2.eprime | 13 - .../model_2_2_1_3-solution000001.solution | 4 - .../model_2_2_1_3-solution000002.solution | 4 - .../model_2_2_1_3-solution000003.solution | 4 - .../typed01/expected/model_2_2_1_3.eprime | 22 - .../model_2_2_1_4-solution000001.solution | 4 - .../model_2_2_1_4-solution000002.solution | 4 - .../model_2_2_1_4-solution000003.solution | 4 - .../typed01/expected/model_2_2_1_4.eprime | 22 - .../model_2_2_2_1-solution000001.solution | 4 - .../model_2_2_2_1-solution000002.solution | 4 - .../model_2_2_2_1-solution000003.solution | 4 - .../typed01/expected/model_2_2_2_1.eprime | 13 - .../model_2_2_2_2-solution000001.solution | 4 - .../model_2_2_2_2-solution000002.solution | 4 - .../model_2_2_2_2-solution000003.solution | 4 - .../typed01/expected/model_2_2_2_2.eprime | 10 - .../model_2_2_2_3-solution000001.solution | 4 - .../model_2_2_2_3-solution000002.solution | 4 - .../model_2_2_2_3-solution000003.solution | 4 - .../typed01/expected/model_2_2_2_3.eprime | 19 - .../model_2_2_2_4-solution000001.solution | 4 - .../model_2_2_2_4-solution000002.solution | 4 - .../model_2_2_2_4-solution000003.solution | 4 - .../typed01/expected/model_2_2_2_4.eprime | 19 - .../model_2_2_3_1-solution000001.solution | 4 - .../model_2_2_3_1-solution000002.solution | 4 - .../model_2_2_3_1-solution000003.solution | 4 - .../typed01/expected/model_2_2_3_1.eprime | 22 - .../model_2_2_3_2-solution000001.solution | 4 - .../model_2_2_3_2-solution000002.solution | 4 - .../model_2_2_3_2-solution000003.solution | 4 - .../typed01/expected/model_2_2_3_2.eprime | 19 - .../model_2_2_3_3-solution000001.solution | 4 - .../model_2_2_3_3-solution000002.solution | 4 - .../model_2_2_3_3-solution000003.solution | 4 - .../typed01/expected/model_2_2_3_3.eprime | 26 - .../model_2_2_3_4-solution000001.solution | 4 - .../model_2_2_3_4-solution000002.solution | 4 - .../model_2_2_3_4-solution000003.solution | 4 - .../typed01/expected/model_2_2_3_4.eprime | 26 - .../model_2_2_4_1-solution000001.solution | 4 - .../model_2_2_4_1-solution000002.solution | 4 - .../model_2_2_4_1-solution000003.solution | 4 - .../typed01/expected/model_2_2_4_1.eprime | 22 - .../model_2_2_4_2-solution000001.solution | 4 - .../model_2_2_4_2-solution000002.solution | 4 - .../model_2_2_4_2-solution000003.solution | 4 - .../typed01/expected/model_2_2_4_2.eprime | 19 - .../model_2_2_4_3-solution000001.solution | 4 - .../model_2_2_4_3-solution000002.solution | 4 - .../model_2_2_4_3-solution000003.solution | 4 - .../typed01/expected/model_2_2_4_3.eprime | 26 - .../model_2_2_4_4-solution000001.solution | 4 - .../model_2_2_4_4-solution000002.solution | 4 - .../model_2_2_4_4-solution000003.solution | 4 - .../typed01/expected/model_2_2_4_4.eprime | 26 - .../model_2_3_1_1-solution000001.solution | 4 - .../model_2_3_1_1-solution000002.solution | 4 - .../model_2_3_1_1-solution000003.solution | 4 - .../typed01/expected/model_2_3_1_1.eprime | 20 - .../model_2_3_1_2-solution000001.solution | 4 - .../model_2_3_1_2-solution000002.solution | 4 - .../model_2_3_1_2-solution000003.solution | 4 - .../typed01/expected/model_2_3_1_2.eprime | 22 - .../model_2_3_1_3-solution000001.solution | 4 - .../model_2_3_1_3-solution000002.solution | 4 - .../model_2_3_1_3-solution000003.solution | 4 - .../typed01/expected/model_2_3_1_3.eprime | 16 - .../model_2_3_1_4-solution000001.solution | 4 - .../model_2_3_1_4-solution000002.solution | 4 - .../model_2_3_1_4-solution000003.solution | 4 - .../typed01/expected/model_2_3_1_4.eprime | 25 - .../model_2_3_2_1-solution000001.solution | 4 - .../model_2_3_2_1-solution000002.solution | 4 - .../model_2_3_2_1-solution000003.solution | 4 - .../typed01/expected/model_2_3_2_1.eprime | 16 - .../model_2_3_2_2-solution000001.solution | 4 - .../model_2_3_2_2-solution000002.solution | 4 - .../model_2_3_2_2-solution000003.solution | 4 - .../typed01/expected/model_2_3_2_2.eprime | 19 - .../model_2_3_2_3-solution000001.solution | 4 - .../model_2_3_2_3-solution000002.solution | 4 - .../model_2_3_2_3-solution000003.solution | 4 - .../typed01/expected/model_2_3_2_3.eprime | 12 - .../model_2_3_2_4-solution000001.solution | 4 - .../model_2_3_2_4-solution000002.solution | 4 - .../model_2_3_2_4-solution000003.solution | 4 - .../typed01/expected/model_2_3_2_4.eprime | 22 - .../model_2_3_3_1-solution000001.solution | 4 - .../model_2_3_3_1-solution000002.solution | 4 - .../model_2_3_3_1-solution000003.solution | 4 - .../typed01/expected/model_2_3_3_1.eprime | 24 - .../model_2_3_3_2-solution000001.solution | 4 - .../model_2_3_3_2-solution000002.solution | 4 - .../model_2_3_3_2-solution000003.solution | 4 - .../typed01/expected/model_2_3_3_2.eprime | 26 - .../model_2_3_3_3-solution000001.solution | 4 - .../model_2_3_3_3-solution000002.solution | 4 - .../model_2_3_3_3-solution000003.solution | 4 - .../typed01/expected/model_2_3_3_3.eprime | 21 - .../model_2_3_3_4-solution000001.solution | 4 - .../model_2_3_3_4-solution000002.solution | 4 - .../model_2_3_3_4-solution000003.solution | 4 - .../typed01/expected/model_2_3_3_4.eprime | 30 - .../model_2_3_4_1-solution000001.solution | 4 - .../model_2_3_4_1-solution000002.solution | 4 - .../model_2_3_4_1-solution000003.solution | 4 - .../typed01/expected/model_2_3_4_1.eprime | 24 - .../model_2_3_4_2-solution000001.solution | 4 - .../model_2_3_4_2-solution000002.solution | 4 - .../model_2_3_4_2-solution000003.solution | 4 - .../typed01/expected/model_2_3_4_2.eprime | 26 - .../model_2_3_4_3-solution000001.solution | 4 - .../model_2_3_4_3-solution000002.solution | 4 - .../model_2_3_4_3-solution000003.solution | 4 - .../typed01/expected/model_2_3_4_3.eprime | 21 - .../model_2_3_4_4-solution000001.solution | 4 - .../model_2_3_4_4-solution000002.solution | 4 - .../model_2_3_4_4-solution000003.solution | 4 - .../typed01/expected/model_2_3_4_4.eprime | 30 - .../model_2_4_1_1-solution000001.solution | 4 - .../model_2_4_1_1-solution000002.solution | 4 - .../model_2_4_1_1-solution000003.solution | 4 - .../typed01/expected/model_2_4_1_1.eprime | 20 - .../model_2_4_1_2-solution000001.solution | 4 - .../model_2_4_1_2-solution000002.solution | 4 - .../model_2_4_1_2-solution000003.solution | 4 - .../typed01/expected/model_2_4_1_2.eprime | 22 - .../model_2_4_1_3-solution000001.solution | 4 - .../model_2_4_1_3-solution000002.solution | 4 - .../model_2_4_1_3-solution000003.solution | 4 - .../typed01/expected/model_2_4_1_3.eprime | 25 - .../model_2_4_1_4-solution000001.solution | 4 - .../model_2_4_1_4-solution000002.solution | 4 - .../model_2_4_1_4-solution000003.solution | 4 - .../typed01/expected/model_2_4_1_4.eprime | 16 - .../model_2_4_2_1-solution000001.solution | 4 - .../model_2_4_2_1-solution000002.solution | 4 - .../model_2_4_2_1-solution000003.solution | 4 - .../typed01/expected/model_2_4_2_1.eprime | 16 - .../model_2_4_2_2-solution000001.solution | 4 - .../model_2_4_2_2-solution000002.solution | 4 - .../model_2_4_2_2-solution000003.solution | 4 - .../typed01/expected/model_2_4_2_2.eprime | 19 - .../model_2_4_2_3-solution000001.solution | 4 - .../model_2_4_2_3-solution000002.solution | 4 - .../model_2_4_2_3-solution000003.solution | 4 - .../typed01/expected/model_2_4_2_3.eprime | 22 - .../model_2_4_2_4-solution000001.solution | 4 - .../model_2_4_2_4-solution000002.solution | 4 - .../model_2_4_2_4-solution000003.solution | 4 - .../typed01/expected/model_2_4_2_4.eprime | 12 - .../model_2_4_3_1-solution000001.solution | 4 - .../model_2_4_3_1-solution000002.solution | 4 - .../model_2_4_3_1-solution000003.solution | 4 - .../typed01/expected/model_2_4_3_1.eprime | 24 - .../model_2_4_3_2-solution000001.solution | 4 - .../model_2_4_3_2-solution000002.solution | 4 - .../model_2_4_3_2-solution000003.solution | 4 - .../typed01/expected/model_2_4_3_2.eprime | 26 - .../model_2_4_3_3-solution000001.solution | 4 - .../model_2_4_3_3-solution000002.solution | 4 - .../model_2_4_3_3-solution000003.solution | 4 - .../typed01/expected/model_2_4_3_3.eprime | 30 - .../model_2_4_3_4-solution000001.solution | 4 - .../model_2_4_3_4-solution000002.solution | 4 - .../model_2_4_3_4-solution000003.solution | 4 - .../typed01/expected/model_2_4_3_4.eprime | 21 - .../model_2_4_4_1-solution000001.solution | 4 - .../model_2_4_4_1-solution000002.solution | 4 - .../model_2_4_4_1-solution000003.solution | 4 - .../typed01/expected/model_2_4_4_1.eprime | 24 - .../model_2_4_4_2-solution000001.solution | 4 - .../model_2_4_4_2-solution000002.solution | 4 - .../model_2_4_4_2-solution000003.solution | 4 - .../typed01/expected/model_2_4_4_2.eprime | 26 - .../model_2_4_4_3-solution000001.solution | 4 - .../model_2_4_4_3-solution000002.solution | 4 - .../model_2_4_4_3-solution000003.solution | 4 - .../typed01/expected/model_2_4_4_3.eprime | 30 - .../model_2_4_4_4-solution000001.solution | 4 - .../model_2_4_4_4-solution000002.solution | 4 - .../model_2_4_4_4-solution000003.solution | 4 - .../typed01/expected/model_2_4_4_4.eprime | 21 - .../model_3_1_1_1-solution000001.solution | 4 - .../model_3_1_1_1-solution000002.solution | 4 - .../model_3_1_1_1-solution000003.solution | 4 - .../typed01/expected/model_3_1_1_1.eprime | 13 - .../model_3_1_1_2-solution000001.solution | 4 - .../model_3_1_1_2-solution000002.solution | 4 - .../model_3_1_1_2-solution000003.solution | 4 - .../typed01/expected/model_3_1_1_2.eprime | 18 - .../model_3_1_1_3-solution000001.solution | 4 - .../model_3_1_1_3-solution000002.solution | 4 - .../model_3_1_1_3-solution000003.solution | 4 - .../typed01/expected/model_3_1_1_3.eprime | 20 - .../model_3_1_1_4-solution000001.solution | 4 - .../model_3_1_1_4-solution000002.solution | 4 - .../model_3_1_1_4-solution000003.solution | 4 - .../typed01/expected/model_3_1_1_4.eprime | 20 - .../model_3_1_2_1-solution000001.solution | 4 - .../model_3_1_2_1-solution000002.solution | 4 - .../model_3_1_2_1-solution000003.solution | 4 - .../typed01/expected/model_3_1_2_1.eprime | 16 - .../model_3_1_2_2-solution000001.solution | 4 - .../model_3_1_2_2-solution000002.solution | 4 - .../model_3_1_2_2-solution000003.solution | 4 - .../typed01/expected/model_3_1_2_2.eprime | 20 - .../model_3_1_2_3-solution000001.solution | 4 - .../model_3_1_2_3-solution000002.solution | 4 - .../model_3_1_2_3-solution000003.solution | 4 - .../typed01/expected/model_3_1_2_3.eprime | 22 - .../model_3_1_2_4-solution000001.solution | 4 - .../model_3_1_2_4-solution000002.solution | 4 - .../model_3_1_2_4-solution000003.solution | 4 - .../typed01/expected/model_3_1_2_4.eprime | 22 - .../model_3_1_3_1-solution000001.solution | 4 - .../model_3_1_3_1-solution000002.solution | 4 - .../model_3_1_3_1-solution000003.solution | 4 - .../typed01/expected/model_3_1_3_1.eprime | 10 - .../model_3_1_3_2-solution000001.solution | 4 - .../model_3_1_3_2-solution000002.solution | 4 - .../model_3_1_3_2-solution000003.solution | 4 - .../typed01/expected/model_3_1_3_2.eprime | 14 - .../model_3_1_3_3-solution000001.solution | 4 - .../model_3_1_3_3-solution000002.solution | 4 - .../model_3_1_3_3-solution000003.solution | 4 - .../typed01/expected/model_3_1_3_3.eprime | 17 - .../model_3_1_3_4-solution000001.solution | 4 - .../model_3_1_3_4-solution000002.solution | 4 - .../model_3_1_3_4-solution000003.solution | 4 - .../typed01/expected/model_3_1_3_4.eprime | 17 - .../model_3_1_4_1-solution000001.solution | 4 - .../model_3_1_4_1-solution000002.solution | 4 - .../model_3_1_4_1-solution000003.solution | 4 - .../typed01/expected/model_3_1_4_1.eprime | 20 - .../model_3_1_4_2-solution000001.solution | 4 - .../model_3_1_4_2-solution000002.solution | 4 - .../model_3_1_4_2-solution000003.solution | 4 - .../typed01/expected/model_3_1_4_2.eprime | 23 - .../model_3_1_4_3-solution000001.solution | 4 - .../model_3_1_4_3-solution000002.solution | 4 - .../model_3_1_4_3-solution000003.solution | 4 - .../typed01/expected/model_3_1_4_3.eprime | 26 - .../model_3_1_4_4-solution000001.solution | 4 - .../model_3_1_4_4-solution000002.solution | 4 - .../model_3_1_4_4-solution000003.solution | 4 - .../typed01/expected/model_3_1_4_4.eprime | 26 - .../model_3_2_1_1-solution000001.solution | 4 - .../model_3_2_1_1-solution000002.solution | 4 - .../model_3_2_1_1-solution000003.solution | 4 - .../typed01/expected/model_3_2_1_1.eprime | 20 - .../model_3_2_1_2-solution000001.solution | 4 - .../model_3_2_1_2-solution000002.solution | 4 - .../model_3_2_1_2-solution000003.solution | 4 - .../typed01/expected/model_3_2_1_2.eprime | 16 - .../model_3_2_1_3-solution000001.solution | 4 - .../model_3_2_1_3-solution000002.solution | 4 - .../model_3_2_1_3-solution000003.solution | 4 - .../typed01/expected/model_3_2_1_3.eprime | 24 - .../model_3_2_1_4-solution000001.solution | 4 - .../model_3_2_1_4-solution000002.solution | 4 - .../model_3_2_1_4-solution000003.solution | 4 - .../typed01/expected/model_3_2_1_4.eprime | 24 - .../model_3_2_2_1-solution000001.solution | 4 - .../model_3_2_2_1-solution000002.solution | 4 - .../model_3_2_2_1-solution000003.solution | 4 - .../typed01/expected/model_3_2_2_1.eprime | 22 - .../model_3_2_2_2-solution000001.solution | 4 - .../model_3_2_2_2-solution000002.solution | 4 - .../model_3_2_2_2-solution000003.solution | 4 - .../typed01/expected/model_3_2_2_2.eprime | 19 - .../model_3_2_2_3-solution000001.solution | 4 - .../model_3_2_2_3-solution000002.solution | 4 - .../model_3_2_2_3-solution000003.solution | 4 - .../typed01/expected/model_3_2_2_3.eprime | 26 - .../model_3_2_2_4-solution000001.solution | 4 - .../model_3_2_2_4-solution000002.solution | 4 - .../model_3_2_2_4-solution000003.solution | 4 - .../typed01/expected/model_3_2_2_4.eprime | 26 - .../model_3_2_3_1-solution000001.solution | 4 - .../model_3_2_3_1-solution000002.solution | 4 - .../model_3_2_3_1-solution000003.solution | 4 - .../typed01/expected/model_3_2_3_1.eprime | 16 - .../model_3_2_3_2-solution000001.solution | 4 - .../model_3_2_3_2-solution000002.solution | 4 - .../model_3_2_3_2-solution000003.solution | 4 - .../typed01/expected/model_3_2_3_2.eprime | 12 - .../model_3_2_3_3-solution000001.solution | 4 - .../model_3_2_3_3-solution000002.solution | 4 - .../model_3_2_3_3-solution000003.solution | 4 - .../typed01/expected/model_3_2_3_3.eprime | 21 - .../model_3_2_3_4-solution000001.solution | 4 - .../model_3_2_3_4-solution000002.solution | 4 - .../model_3_2_3_4-solution000003.solution | 4 - .../typed01/expected/model_3_2_3_4.eprime | 21 - .../model_3_2_4_1-solution000001.solution | 4 - .../model_3_2_4_1-solution000002.solution | 4 - .../model_3_2_4_1-solution000003.solution | 4 - .../typed01/expected/model_3_2_4_1.eprime | 25 - .../model_3_2_4_2-solution000001.solution | 4 - .../model_3_2_4_2-solution000002.solution | 4 - .../model_3_2_4_2-solution000003.solution | 4 - .../typed01/expected/model_3_2_4_2.eprime | 22 - .../model_3_2_4_3-solution000001.solution | 4 - .../model_3_2_4_3-solution000002.solution | 4 - .../model_3_2_4_3-solution000003.solution | 4 - .../typed01/expected/model_3_2_4_3.eprime | 30 - .../model_3_2_4_4-solution000001.solution | 4 - .../model_3_2_4_4-solution000002.solution | 4 - .../model_3_2_4_4-solution000003.solution | 4 - .../typed01/expected/model_3_2_4_4.eprime | 30 - .../model_3_3_1_1-solution000001.solution | 4 - .../model_3_3_1_1-solution000002.solution | 4 - .../model_3_3_1_1-solution000003.solution | 4 - .../typed01/expected/model_3_3_1_1.eprime | 23 - .../model_3_3_1_2-solution000001.solution | 4 - .../model_3_3_1_2-solution000002.solution | 4 - .../model_3_3_1_2-solution000003.solution | 4 - .../typed01/expected/model_3_3_1_2.eprime | 25 - .../model_3_3_1_3-solution000001.solution | 4 - .../model_3_3_1_3-solution000002.solution | 4 - .../model_3_3_1_3-solution000003.solution | 4 - .../typed01/expected/model_3_3_1_3.eprime | 20 - .../model_3_3_1_4-solution000001.solution | 4 - .../model_3_3_1_4-solution000002.solution | 4 - .../model_3_3_1_4-solution000003.solution | 4 - .../typed01/expected/model_3_3_1_4.eprime | 29 - .../model_3_3_2_1-solution000001.solution | 4 - .../model_3_3_2_1-solution000002.solution | 4 - .../model_3_3_2_1-solution000003.solution | 4 - .../typed01/expected/model_3_3_2_1.eprime | 25 - .../model_3_3_2_2-solution000001.solution | 4 - .../model_3_3_2_2-solution000002.solution | 4 - .../model_3_3_2_2-solution000003.solution | 4 - .../typed01/expected/model_3_3_2_2.eprime | 27 - .../model_3_3_2_3-solution000001.solution | 4 - .../model_3_3_2_3-solution000002.solution | 4 - .../model_3_3_2_3-solution000003.solution | 4 - .../typed01/expected/model_3_3_2_3.eprime | 22 - .../model_3_3_2_4-solution000001.solution | 4 - .../model_3_3_2_4-solution000002.solution | 4 - .../model_3_3_2_4-solution000003.solution | 4 - .../typed01/expected/model_3_3_2_4.eprime | 31 - .../model_3_3_3_1-solution000001.solution | 4 - .../model_3_3_3_1-solution000002.solution | 4 - .../model_3_3_3_1-solution000003.solution | 4 - .../typed01/expected/model_3_3_3_1.eprime | 20 - .../model_3_3_3_2-solution000001.solution | 4 - .../model_3_3_3_2-solution000002.solution | 4 - .../model_3_3_3_2-solution000003.solution | 4 - .../typed01/expected/model_3_3_3_2.eprime | 22 - .../model_3_3_3_3-solution000001.solution | 4 - .../model_3_3_3_3-solution000002.solution | 4 - .../model_3_3_3_3-solution000003.solution | 4 - .../typed01/expected/model_3_3_3_3.eprime | 17 - .../model_3_3_3_4-solution000001.solution | 4 - .../model_3_3_3_4-solution000002.solution | 4 - .../model_3_3_3_4-solution000003.solution | 4 - .../typed01/expected/model_3_3_3_4.eprime | 25 - .../model_3_3_4_1-solution000001.solution | 4 - .../model_3_3_4_1-solution000002.solution | 4 - .../model_3_3_4_1-solution000003.solution | 4 - .../typed01/expected/model_3_3_4_1.eprime | 29 - .../model_3_3_4_2-solution000001.solution | 4 - .../model_3_3_4_2-solution000002.solution | 4 - .../model_3_3_4_2-solution000003.solution | 4 - .../typed01/expected/model_3_3_4_2.eprime | 31 - .../model_3_3_4_3-solution000001.solution | 4 - .../model_3_3_4_3-solution000002.solution | 4 - .../model_3_3_4_3-solution000003.solution | 4 - .../typed01/expected/model_3_3_4_3.eprime | 25 - .../model_3_3_4_4-solution000001.solution | 4 - .../model_3_3_4_4-solution000002.solution | 4 - .../model_3_3_4_4-solution000003.solution | 4 - .../typed01/expected/model_3_3_4_4.eprime | 34 - .../model_3_4_1_1-solution000001.solution | 4 - .../model_3_4_1_1-solution000002.solution | 4 - .../model_3_4_1_1-solution000003.solution | 4 - .../typed01/expected/model_3_4_1_1.eprime | 23 - .../model_3_4_1_2-solution000001.solution | 4 - .../model_3_4_1_2-solution000002.solution | 4 - .../model_3_4_1_2-solution000003.solution | 4 - .../typed01/expected/model_3_4_1_2.eprime | 25 - .../model_3_4_1_3-solution000001.solution | 4 - .../model_3_4_1_3-solution000002.solution | 4 - .../model_3_4_1_3-solution000003.solution | 4 - .../typed01/expected/model_3_4_1_3.eprime | 29 - .../model_3_4_1_4-solution000001.solution | 4 - .../model_3_4_1_4-solution000002.solution | 4 - .../model_3_4_1_4-solution000003.solution | 4 - .../typed01/expected/model_3_4_1_4.eprime | 20 - .../model_3_4_2_1-solution000001.solution | 4 - .../model_3_4_2_1-solution000002.solution | 4 - .../model_3_4_2_1-solution000003.solution | 4 - .../typed01/expected/model_3_4_2_1.eprime | 25 - .../model_3_4_2_2-solution000001.solution | 4 - .../model_3_4_2_2-solution000002.solution | 4 - .../model_3_4_2_2-solution000003.solution | 4 - .../typed01/expected/model_3_4_2_2.eprime | 27 - .../model_3_4_2_3-solution000001.solution | 4 - .../model_3_4_2_3-solution000002.solution | 4 - .../model_3_4_2_3-solution000003.solution | 4 - .../typed01/expected/model_3_4_2_3.eprime | 31 - .../model_3_4_2_4-solution000001.solution | 4 - .../model_3_4_2_4-solution000002.solution | 4 - .../model_3_4_2_4-solution000003.solution | 4 - .../typed01/expected/model_3_4_2_4.eprime | 22 - .../model_3_4_3_1-solution000001.solution | 4 - .../model_3_4_3_1-solution000002.solution | 4 - .../model_3_4_3_1-solution000003.solution | 4 - .../typed01/expected/model_3_4_3_1.eprime | 20 - .../model_3_4_3_2-solution000001.solution | 4 - .../model_3_4_3_2-solution000002.solution | 4 - .../model_3_4_3_2-solution000003.solution | 4 - .../typed01/expected/model_3_4_3_2.eprime | 22 - .../model_3_4_3_3-solution000001.solution | 4 - .../model_3_4_3_3-solution000002.solution | 4 - .../model_3_4_3_3-solution000003.solution | 4 - .../typed01/expected/model_3_4_3_3.eprime | 25 - .../model_3_4_3_4-solution000001.solution | 4 - .../model_3_4_3_4-solution000002.solution | 4 - .../model_3_4_3_4-solution000003.solution | 4 - .../typed01/expected/model_3_4_3_4.eprime | 17 - .../model_3_4_4_1-solution000001.solution | 4 - .../model_3_4_4_1-solution000002.solution | 4 - .../model_3_4_4_1-solution000003.solution | 4 - .../typed01/expected/model_3_4_4_1.eprime | 29 - .../model_3_4_4_2-solution000001.solution | 4 - .../model_3_4_4_2-solution000002.solution | 4 - .../model_3_4_4_2-solution000003.solution | 4 - .../typed01/expected/model_3_4_4_2.eprime | 31 - .../model_3_4_4_3-solution000001.solution | 4 - .../model_3_4_4_3-solution000002.solution | 4 - .../model_3_4_4_3-solution000003.solution | 4 - .../typed01/expected/model_3_4_4_3.eprime | 34 - .../model_3_4_4_4-solution000001.solution | 4 - .../model_3_4_4_4-solution000002.solution | 4 - .../model_3_4_4_4-solution000003.solution | 4 - .../typed01/expected/model_3_4_4_4.eprime | 25 - .../model_4_1_1_1-solution000001.solution | 4 - .../model_4_1_1_1-solution000002.solution | 4 - .../model_4_1_1_1-solution000003.solution | 4 - .../typed01/expected/model_4_1_1_1.eprime | 13 - .../model_4_1_1_2-solution000001.solution | 4 - .../model_4_1_1_2-solution000002.solution | 4 - .../model_4_1_1_2-solution000003.solution | 4 - .../typed01/expected/model_4_1_1_2.eprime | 18 - .../model_4_1_1_3-solution000001.solution | 4 - .../model_4_1_1_3-solution000002.solution | 4 - .../model_4_1_1_3-solution000003.solution | 4 - .../typed01/expected/model_4_1_1_3.eprime | 20 - .../model_4_1_1_4-solution000001.solution | 4 - .../model_4_1_1_4-solution000002.solution | 4 - .../model_4_1_1_4-solution000003.solution | 4 - .../typed01/expected/model_4_1_1_4.eprime | 20 - .../model_4_1_2_1-solution000001.solution | 4 - .../model_4_1_2_1-solution000002.solution | 4 - .../model_4_1_2_1-solution000003.solution | 4 - .../typed01/expected/model_4_1_2_1.eprime | 16 - .../model_4_1_2_2-solution000001.solution | 4 - .../model_4_1_2_2-solution000002.solution | 4 - .../model_4_1_2_2-solution000003.solution | 4 - .../typed01/expected/model_4_1_2_2.eprime | 20 - .../model_4_1_2_3-solution000001.solution | 4 - .../model_4_1_2_3-solution000002.solution | 4 - .../model_4_1_2_3-solution000003.solution | 4 - .../typed01/expected/model_4_1_2_3.eprime | 22 - .../model_4_1_2_4-solution000001.solution | 4 - .../model_4_1_2_4-solution000002.solution | 4 - .../model_4_1_2_4-solution000003.solution | 4 - .../typed01/expected/model_4_1_2_4.eprime | 22 - .../model_4_1_3_1-solution000001.solution | 4 - .../model_4_1_3_1-solution000002.solution | 4 - .../model_4_1_3_1-solution000003.solution | 4 - .../typed01/expected/model_4_1_3_1.eprime | 20 - .../model_4_1_3_2-solution000001.solution | 4 - .../model_4_1_3_2-solution000002.solution | 4 - .../model_4_1_3_2-solution000003.solution | 4 - .../typed01/expected/model_4_1_3_2.eprime | 23 - .../model_4_1_3_3-solution000001.solution | 4 - .../model_4_1_3_3-solution000002.solution | 4 - .../model_4_1_3_3-solution000003.solution | 4 - .../typed01/expected/model_4_1_3_3.eprime | 26 - .../model_4_1_3_4-solution000001.solution | 4 - .../model_4_1_3_4-solution000002.solution | 4 - .../model_4_1_3_4-solution000003.solution | 4 - .../typed01/expected/model_4_1_3_4.eprime | 26 - .../model_4_1_4_1-solution000001.solution | 4 - .../model_4_1_4_1-solution000002.solution | 4 - .../model_4_1_4_1-solution000003.solution | 4 - .../typed01/expected/model_4_1_4_1.eprime | 10 - .../model_4_1_4_2-solution000001.solution | 4 - .../model_4_1_4_2-solution000002.solution | 4 - .../model_4_1_4_2-solution000003.solution | 4 - .../typed01/expected/model_4_1_4_2.eprime | 14 - .../model_4_1_4_3-solution000001.solution | 4 - .../model_4_1_4_3-solution000002.solution | 4 - .../model_4_1_4_3-solution000003.solution | 4 - .../typed01/expected/model_4_1_4_3.eprime | 17 - .../model_4_1_4_4-solution000001.solution | 4 - .../model_4_1_4_4-solution000002.solution | 4 - .../model_4_1_4_4-solution000003.solution | 4 - .../typed01/expected/model_4_1_4_4.eprime | 17 - .../model_4_2_1_1-solution000001.solution | 4 - .../model_4_2_1_1-solution000002.solution | 4 - .../model_4_2_1_1-solution000003.solution | 4 - .../typed01/expected/model_4_2_1_1.eprime | 20 - .../model_4_2_1_2-solution000001.solution | 4 - .../model_4_2_1_2-solution000002.solution | 4 - .../model_4_2_1_2-solution000003.solution | 4 - .../typed01/expected/model_4_2_1_2.eprime | 16 - .../model_4_2_1_3-solution000001.solution | 4 - .../model_4_2_1_3-solution000002.solution | 4 - .../model_4_2_1_3-solution000003.solution | 4 - .../typed01/expected/model_4_2_1_3.eprime | 24 - .../model_4_2_1_4-solution000001.solution | 4 - .../model_4_2_1_4-solution000002.solution | 4 - .../model_4_2_1_4-solution000003.solution | 4 - .../typed01/expected/model_4_2_1_4.eprime | 24 - .../model_4_2_2_1-solution000001.solution | 4 - .../model_4_2_2_1-solution000002.solution | 4 - .../model_4_2_2_1-solution000003.solution | 4 - .../typed01/expected/model_4_2_2_1.eprime | 22 - .../model_4_2_2_2-solution000001.solution | 4 - .../model_4_2_2_2-solution000002.solution | 4 - .../model_4_2_2_2-solution000003.solution | 4 - .../typed01/expected/model_4_2_2_2.eprime | 19 - .../model_4_2_2_3-solution000001.solution | 4 - .../model_4_2_2_3-solution000002.solution | 4 - .../model_4_2_2_3-solution000003.solution | 4 - .../typed01/expected/model_4_2_2_3.eprime | 26 - .../model_4_2_2_4-solution000001.solution | 4 - .../model_4_2_2_4-solution000002.solution | 4 - .../model_4_2_2_4-solution000003.solution | 4 - .../typed01/expected/model_4_2_2_4.eprime | 26 - .../model_4_2_3_1-solution000001.solution | 4 - .../model_4_2_3_1-solution000002.solution | 4 - .../model_4_2_3_1-solution000003.solution | 4 - .../typed01/expected/model_4_2_3_1.eprime | 25 - .../model_4_2_3_2-solution000001.solution | 4 - .../model_4_2_3_2-solution000002.solution | 4 - .../model_4_2_3_2-solution000003.solution | 4 - .../typed01/expected/model_4_2_3_2.eprime | 22 - .../model_4_2_3_3-solution000001.solution | 4 - .../model_4_2_3_3-solution000002.solution | 4 - .../model_4_2_3_3-solution000003.solution | 4 - .../typed01/expected/model_4_2_3_3.eprime | 30 - .../model_4_2_3_4-solution000001.solution | 4 - .../model_4_2_3_4-solution000002.solution | 4 - .../model_4_2_3_4-solution000003.solution | 4 - .../typed01/expected/model_4_2_3_4.eprime | 30 - .../model_4_2_4_1-solution000001.solution | 4 - .../model_4_2_4_1-solution000002.solution | 4 - .../model_4_2_4_1-solution000003.solution | 4 - .../typed01/expected/model_4_2_4_1.eprime | 16 - .../model_4_2_4_2-solution000001.solution | 4 - .../model_4_2_4_2-solution000002.solution | 4 - .../model_4_2_4_2-solution000003.solution | 4 - .../typed01/expected/model_4_2_4_2.eprime | 12 - .../model_4_2_4_3-solution000001.solution | 4 - .../model_4_2_4_3-solution000002.solution | 4 - .../model_4_2_4_3-solution000003.solution | 4 - .../typed01/expected/model_4_2_4_3.eprime | 21 - .../model_4_2_4_4-solution000001.solution | 4 - .../model_4_2_4_4-solution000002.solution | 4 - .../model_4_2_4_4-solution000003.solution | 4 - .../typed01/expected/model_4_2_4_4.eprime | 21 - .../model_4_3_1_1-solution000001.solution | 4 - .../model_4_3_1_1-solution000002.solution | 4 - .../model_4_3_1_1-solution000003.solution | 4 - .../typed01/expected/model_4_3_1_1.eprime | 23 - .../model_4_3_1_2-solution000001.solution | 4 - .../model_4_3_1_2-solution000002.solution | 4 - .../model_4_3_1_2-solution000003.solution | 4 - .../typed01/expected/model_4_3_1_2.eprime | 25 - .../model_4_3_1_3-solution000001.solution | 4 - .../model_4_3_1_3-solution000002.solution | 4 - .../model_4_3_1_3-solution000003.solution | 4 - .../typed01/expected/model_4_3_1_3.eprime | 20 - .../model_4_3_1_4-solution000001.solution | 4 - .../model_4_3_1_4-solution000002.solution | 4 - .../model_4_3_1_4-solution000003.solution | 4 - .../typed01/expected/model_4_3_1_4.eprime | 29 - .../model_4_3_2_1-solution000001.solution | 4 - .../model_4_3_2_1-solution000002.solution | 4 - .../model_4_3_2_1-solution000003.solution | 4 - .../typed01/expected/model_4_3_2_1.eprime | 25 - .../model_4_3_2_2-solution000001.solution | 4 - .../model_4_3_2_2-solution000002.solution | 4 - .../model_4_3_2_2-solution000003.solution | 4 - .../typed01/expected/model_4_3_2_2.eprime | 27 - .../model_4_3_2_3-solution000001.solution | 4 - .../model_4_3_2_3-solution000002.solution | 4 - .../model_4_3_2_3-solution000003.solution | 4 - .../typed01/expected/model_4_3_2_3.eprime | 22 - .../model_4_3_2_4-solution000001.solution | 4 - .../model_4_3_2_4-solution000002.solution | 4 - .../model_4_3_2_4-solution000003.solution | 4 - .../typed01/expected/model_4_3_2_4.eprime | 31 - .../model_4_3_3_1-solution000001.solution | 4 - .../model_4_3_3_1-solution000002.solution | 4 - .../model_4_3_3_1-solution000003.solution | 4 - .../typed01/expected/model_4_3_3_1.eprime | 29 - .../model_4_3_3_2-solution000001.solution | 4 - .../model_4_3_3_2-solution000002.solution | 4 - .../model_4_3_3_2-solution000003.solution | 4 - .../typed01/expected/model_4_3_3_2.eprime | 31 - .../model_4_3_3_3-solution000001.solution | 4 - .../model_4_3_3_3-solution000002.solution | 4 - .../model_4_3_3_3-solution000003.solution | 4 - .../typed01/expected/model_4_3_3_3.eprime | 25 - .../model_4_3_3_4-solution000001.solution | 4 - .../model_4_3_3_4-solution000002.solution | 4 - .../model_4_3_3_4-solution000003.solution | 4 - .../typed01/expected/model_4_3_3_4.eprime | 34 - .../model_4_3_4_1-solution000001.solution | 4 - .../model_4_3_4_1-solution000002.solution | 4 - .../model_4_3_4_1-solution000003.solution | 4 - .../typed01/expected/model_4_3_4_1.eprime | 20 - .../model_4_3_4_2-solution000001.solution | 4 - .../model_4_3_4_2-solution000002.solution | 4 - .../model_4_3_4_2-solution000003.solution | 4 - .../typed01/expected/model_4_3_4_2.eprime | 22 - .../model_4_3_4_3-solution000001.solution | 4 - .../model_4_3_4_3-solution000002.solution | 4 - .../model_4_3_4_3-solution000003.solution | 4 - .../typed01/expected/model_4_3_4_3.eprime | 17 - .../model_4_3_4_4-solution000001.solution | 4 - .../model_4_3_4_4-solution000002.solution | 4 - .../model_4_3_4_4-solution000003.solution | 4 - .../typed01/expected/model_4_3_4_4.eprime | 25 - .../model_4_4_1_1-solution000001.solution | 4 - .../model_4_4_1_1-solution000002.solution | 4 - .../model_4_4_1_1-solution000003.solution | 4 - .../typed01/expected/model_4_4_1_1.eprime | 22 - .../model_4_4_1_2-solution000001.solution | 4 - .../model_4_4_1_2-solution000002.solution | 4 - .../model_4_4_1_2-solution000003.solution | 4 - .../typed01/expected/model_4_4_1_2.eprime | 24 - .../model_4_4_1_3-solution000001.solution | 4 - .../model_4_4_1_3-solution000002.solution | 4 - .../model_4_4_1_3-solution000003.solution | 4 - .../typed01/expected/model_4_4_1_3.eprime | 28 - .../model_4_4_1_4-solution000001.solution | 4 - .../model_4_4_1_4-solution000002.solution | 4 - .../model_4_4_1_4-solution000003.solution | 4 - .../typed01/expected/model_4_4_1_4.eprime | 19 - .../model_4_4_2_1-solution000001.solution | 4 - .../model_4_4_2_1-solution000002.solution | 4 - .../model_4_4_2_1-solution000003.solution | 4 - .../typed01/expected/model_4_4_2_1.eprime | 24 - .../model_4_4_2_2-solution000001.solution | 4 - .../model_4_4_2_2-solution000002.solution | 4 - .../model_4_4_2_2-solution000003.solution | 4 - .../typed01/expected/model_4_4_2_2.eprime | 26 - .../model_4_4_2_3-solution000001.solution | 4 - .../model_4_4_2_3-solution000002.solution | 4 - .../model_4_4_2_3-solution000003.solution | 4 - .../typed01/expected/model_4_4_2_3.eprime | 30 - .../model_4_4_2_4-solution000001.solution | 4 - .../model_4_4_2_4-solution000002.solution | 4 - .../model_4_4_2_4-solution000003.solution | 4 - .../typed01/expected/model_4_4_2_4.eprime | 21 - .../model_4_4_3_1-solution000001.solution | 4 - .../model_4_4_3_1-solution000002.solution | 4 - .../model_4_4_3_1-solution000003.solution | 4 - .../typed01/expected/model_4_4_3_1.eprime | 28 - .../model_4_4_3_2-solution000001.solution | 4 - .../model_4_4_3_2-solution000002.solution | 4 - .../model_4_4_3_2-solution000003.solution | 4 - .../typed01/expected/model_4_4_3_2.eprime | 30 - .../model_4_4_3_3-solution000001.solution | 4 - .../model_4_4_3_3-solution000002.solution | 4 - .../model_4_4_3_3-solution000003.solution | 4 - .../typed01/expected/model_4_4_3_3.eprime | 33 - .../model_4_4_3_4-solution000001.solution | 4 - .../model_4_4_3_4-solution000002.solution | 4 - .../model_4_4_3_4-solution000003.solution | 4 - .../typed01/expected/model_4_4_3_4.eprime | 24 - .../model_4_4_4_1-solution000001.solution | 4 - .../model_4_4_4_1-solution000002.solution | 4 - .../model_4_4_4_1-solution000003.solution | 4 - .../typed01/expected/model_4_4_4_1.eprime | 19 - .../model_4_4_4_2-solution000001.solution | 4 - .../model_4_4_4_2-solution000002.solution | 4 - .../model_4_4_4_2-solution000003.solution | 4 - .../typed01/expected/model_4_4_4_2.eprime | 21 - .../model_4_4_4_3-solution000001.solution | 4 - .../model_4_4_4_3-solution000002.solution | 4 - .../model_4_4_4_3-solution000003.solution | 4 - .../typed01/expected/model_4_4_4_3.eprime | 24 - .../model_4_4_4_4-solution000001.solution | 4 - .../model_4_4_4_4-solution000002.solution | 4 - .../model_4_4_4_4-solution000003.solution | 4 - .../typed01/expected/model_4_4_4_4.eprime | 16 - .../expected/model-solution000001.solution | 28 - .../issues/102/expected/model.eprime | 88 -- .../model_1_1-solution000001.solution | 6 - .../issues/166/expected/model_1_1.eprime | 46 - .../model_1_2-solution000001.solution | 6 - .../issues/166/expected/model_1_2.eprime | 83 -- .../model_1_3-solution000001.solution | 6 - .../issues/166/expected/model_1_3.eprime | 88 -- .../model_1_4-solution000001.solution | 6 - .../issues/166/expected/model_1_4.eprime | 92 -- .../model_2_1-solution000001.solution | 6 - .../issues/166/expected/model_2_1.eprime | 139 -- .../model_2_2-solution000001.solution | 6 - .../issues/166/expected/model_2_2.eprime | 111 -- .../model_2_3-solution000001.solution | 6 - .../issues/166/expected/model_2_3.eprime | 159 --- .../model_2_4-solution000001.solution | 6 - .../issues/166/expected/model_2_4.eprime | 163 --- .../model_3_1-solution000001.solution | 6 - .../issues/166/expected/model_3_1.eprime | 148 -- .../model_3_2-solution000001.solution | 6 - .../issues/166/expected/model_3_2.eprime | 166 --- .../model_3_3-solution000001.solution | 6 - .../issues/166/expected/model_3_3.eprime | 118 -- .../model_3_4-solution000001.solution | 6 - .../issues/166/expected/model_3_4.eprime | 173 --- .../model_4_1-solution000001.solution | 6 - .../issues/166/expected/model_4_1.eprime | 154 --- .../model_4_2-solution000001.solution | 6 - .../issues/166/expected/model_4_2.eprime | 169 --- .../model_4_3-solution000001.solution | 6 - .../issues/166/expected/model_4_3.eprime | 172 --- .../model_4_4-solution000001.solution | 6 - .../issues/166/expected/model_4_4.eprime | 121 -- .../model_1_1-1-solution000001.solution | 3 - .../212/expected/model_1_1-1.eprime-param | 6 - .../issues/212/expected/model_1_1.eprime | 14 - .../model_1_2-1-solution000001.solution | 3 - .../212/expected/model_1_2-1.eprime-param | 6 - .../issues/212/expected/model_1_2.eprime | 23 - .../model_1_3-1-solution000001.solution | 3 - .../212/expected/model_1_3-1.eprime-param | 6 - .../issues/212/expected/model_1_3.eprime | 26 - .../model_1_4-1-solution000001.solution | 3 - .../212/expected/model_1_4-1.eprime-param | 6 - .../issues/212/expected/model_1_4.eprime | 26 - .../model_2_1-1-solution000001.solution | 3 - .../212/expected/model_2_1-1.eprime-param | 6 - .../issues/212/expected/model_2_1.eprime | 25 - .../model_2_2-1-solution000001.solution | 3 - .../212/expected/model_2_2-1.eprime-param | 6 - .../issues/212/expected/model_2_2.eprime | 20 - .../model_2_3-1-solution000001.solution | 3 - .../212/expected/model_2_3-1.eprime-param | 6 - .../issues/212/expected/model_2_3.eprime | 36 - .../model_2_4-1-solution000001.solution | 3 - .../212/expected/model_2_4-1.eprime-param | 6 - .../issues/212/expected/model_2_4.eprime | 37 - .../model_3_1-1-solution000001.solution | 3 - .../212/expected/model_3_1-1.eprime-param | 6 - .../issues/212/expected/model_3_1.eprime | 29 - .../model_3_2-1-solution000001.solution | 3 - .../212/expected/model_3_2-1.eprime-param | 6 - .../issues/212/expected/model_3_2.eprime | 36 - .../model_3_3-1-solution000001.solution | 3 - .../212/expected/model_3_3-1.eprime-param | 6 - .../issues/212/expected/model_3_3.eprime | 22 - .../model_3_4-1-solution000001.solution | 3 - .../212/expected/model_3_4-1.eprime-param | 6 - .../issues/212/expected/model_3_4.eprime | 41 - .../model_4_1-1-solution000001.solution | 3 - .../212/expected/model_4_1-1.eprime-param | 6 - .../issues/212/expected/model_4_1.eprime | 29 - .../model_4_2-1-solution000001.solution | 3 - .../212/expected/model_4_2-1.eprime-param | 6 - .../issues/212/expected/model_4_2.eprime | 37 - .../model_4_3-1-solution000001.solution | 3 - .../212/expected/model_4_3-1.eprime-param | 6 - .../issues/212/expected/model_4_3.eprime | 41 - .../model_4_4-1-solution000001.solution | 3 - .../212/expected/model_4_4-1.eprime-param | 6 - .../issues/212/expected/model_4_4.eprime | 23 - .../model_1_1-p1-solution000001.solution | 6 - .../model_1_1-p1-solution000002.solution | 7 - .../model_1_1-p1-solution000003.solution | 7 - .../model_1_1-p1-solution000004.solution | 7 - .../model_1_1-p1-solution000005.solution | 7 - .../model_1_1-p1-solution000006.solution | 7 - .../model_1_1-p1-solution000007.solution | 7 - .../model_1_1-p1-solution000008.solution | 7 - .../286/expected/model_1_1-p1.eprime-param | 3 - .../issues/286/expected/model_1_1.eprime | 43 - .../model_1_2-p1-solution000001.solution | 6 - .../model_1_2-p1-solution000002.solution | 7 - .../model_1_2-p1-solution000003.solution | 7 - .../model_1_2-p1-solution000004.solution | 7 - .../model_1_2-p1-solution000005.solution | 7 - .../model_1_2-p1-solution000006.solution | 7 - .../model_1_2-p1-solution000007.solution | 7 - .../model_1_2-p1-solution000008.solution | 7 - .../286/expected/model_1_2-p1.eprime-param | 3 - .../issues/286/expected/model_1_2.eprime | 122 -- .../model_1_3-p1-solution000001.solution | 6 - .../model_1_3-p1-solution000002.solution | 7 - .../model_1_3-p1-solution000003.solution | 7 - .../model_1_3-p1-solution000004.solution | 7 - .../model_1_3-p1-solution000005.solution | 7 - .../model_1_3-p1-solution000006.solution | 7 - .../model_1_3-p1-solution000007.solution | 7 - .../model_1_3-p1-solution000008.solution | 7 - .../286/expected/model_1_3-p1.eprime-param | 3 - .../issues/286/expected/model_1_3.eprime | 136 -- .../model_1_4-p1-solution000001.solution | 6 - .../model_1_4-p1-solution000002.solution | 7 - .../model_1_4-p1-solution000003.solution | 7 - .../model_1_4-p1-solution000004.solution | 7 - .../model_1_4-p1-solution000005.solution | 7 - .../model_1_4-p1-solution000006.solution | 7 - .../model_1_4-p1-solution000007.solution | 7 - .../model_1_4-p1-solution000008.solution | 7 - .../286/expected/model_1_4-p1.eprime-param | 3 - .../issues/286/expected/model_1_4.eprime | 91 -- .../model_2_1-p1-solution000001.solution | 6 - .../model_2_1-p1-solution000002.solution | 7 - .../model_2_1-p1-solution000003.solution | 7 - .../model_2_1-p1-solution000004.solution | 7 - .../model_2_1-p1-solution000005.solution | 7 - .../model_2_1-p1-solution000006.solution | 7 - .../model_2_1-p1-solution000007.solution | 7 - .../model_2_1-p1-solution000008.solution | 7 - .../286/expected/model_2_1-p1.eprime-param | 3 - .../issues/286/expected/model_2_1.eprime | 122 -- .../model_2_2-p1-solution000001.solution | 6 - .../model_2_2-p1-solution000002.solution | 7 - .../model_2_2-p1-solution000003.solution | 7 - .../model_2_2-p1-solution000004.solution | 7 - .../model_2_2-p1-solution000005.solution | 7 - .../model_2_2-p1-solution000006.solution | 7 - .../model_2_2-p1-solution000007.solution | 7 - .../model_2_2-p1-solution000008.solution | 7 - .../286/expected/model_2_2-p1.eprime-param | 3 - .../issues/286/expected/model_2_2.eprime | 65 - .../model_2_3-p1-solution000001.solution | 6 - .../model_2_3-p1-solution000002.solution | 7 - .../model_2_3-p1-solution000003.solution | 7 - .../model_2_3-p1-solution000004.solution | 7 - .../model_2_3-p1-solution000005.solution | 7 - .../model_2_3-p1-solution000006.solution | 7 - .../model_2_3-p1-solution000007.solution | 7 - .../model_2_3-p1-solution000008.solution | 7 - .../286/expected/model_2_3-p1.eprime-param | 3 - .../issues/286/expected/model_2_3.eprime | 164 --- .../model_2_4-p1-solution000001.solution | 6 - .../model_2_4-p1-solution000002.solution | 7 - .../model_2_4-p1-solution000003.solution | 7 - .../model_2_4-p1-solution000004.solution | 7 - .../model_2_4-p1-solution000005.solution | 7 - .../model_2_4-p1-solution000006.solution | 7 - .../model_2_4-p1-solution000007.solution | 7 - .../model_2_4-p1-solution000008.solution | 7 - .../286/expected/model_2_4-p1.eprime-param | 3 - .../issues/286/expected/model_2_4.eprime | 121 -- .../model_3_1-p1-solution000001.solution | 6 - .../model_3_1-p1-solution000002.solution | 7 - .../model_3_1-p1-solution000003.solution | 7 - .../model_3_1-p1-solution000004.solution | 7 - .../model_3_1-p1-solution000005.solution | 7 - .../model_3_1-p1-solution000006.solution | 7 - .../model_3_1-p1-solution000007.solution | 7 - .../model_3_1-p1-solution000008.solution | 7 - .../286/expected/model_3_1-p1.eprime-param | 3 - .../issues/286/expected/model_3_1.eprime | 136 -- .../model_3_2-p1-solution000001.solution | 6 - .../model_3_2-p1-solution000002.solution | 7 - .../model_3_2-p1-solution000003.solution | 7 - .../model_3_2-p1-solution000004.solution | 7 - .../model_3_2-p1-solution000005.solution | 7 - .../model_3_2-p1-solution000006.solution | 7 - .../model_3_2-p1-solution000007.solution | 7 - .../model_3_2-p1-solution000008.solution | 7 - .../286/expected/model_3_2-p1.eprime-param | 3 - .../issues/286/expected/model_3_2.eprime | 164 --- .../model_3_3-p1-solution000001.solution | 6 - .../model_3_3-p1-solution000002.solution | 7 - .../model_3_3-p1-solution000003.solution | 7 - .../model_3_3-p1-solution000004.solution | 7 - .../model_3_3-p1-solution000005.solution | 7 - .../model_3_3-p1-solution000006.solution | 7 - .../model_3_3-p1-solution000007.solution | 7 - .../model_3_3-p1-solution000008.solution | 7 - .../286/expected/model_3_3-p1.eprime-param | 3 - .../issues/286/expected/model_3_3.eprime | 75 - .../model_3_4-p1-solution000001.solution | 6 - .../model_3_4-p1-solution000002.solution | 7 - .../model_3_4-p1-solution000003.solution | 7 - .../model_3_4-p1-solution000004.solution | 7 - .../model_3_4-p1-solution000005.solution | 7 - .../model_3_4-p1-solution000006.solution | 7 - .../model_3_4-p1-solution000007.solution | 7 - .../model_3_4-p1-solution000008.solution | 7 - .../286/expected/model_3_4-p1.eprime-param | 3 - .../issues/286/expected/model_3_4.eprime | 135 -- .../model_4_1-p1-solution000001.solution | 6 - .../model_4_1-p1-solution000002.solution | 7 - .../model_4_1-p1-solution000003.solution | 7 - .../model_4_1-p1-solution000004.solution | 7 - .../model_4_1-p1-solution000005.solution | 7 - .../model_4_1-p1-solution000006.solution | 7 - .../model_4_1-p1-solution000007.solution | 7 - .../model_4_1-p1-solution000008.solution | 7 - .../286/expected/model_4_1-p1.eprime-param | 3 - .../issues/286/expected/model_4_1.eprime | 88 -- .../model_4_2-p1-solution000001.solution | 6 - .../model_4_2-p1-solution000002.solution | 7 - .../model_4_2-p1-solution000003.solution | 7 - .../model_4_2-p1-solution000004.solution | 7 - .../model_4_2-p1-solution000005.solution | 7 - .../model_4_2-p1-solution000006.solution | 7 - .../model_4_2-p1-solution000007.solution | 7 - .../model_4_2-p1-solution000008.solution | 7 - .../286/expected/model_4_2-p1.eprime-param | 3 - .../issues/286/expected/model_4_2.eprime | 118 -- .../model_4_3-p1-solution000001.solution | 6 - .../model_4_3-p1-solution000002.solution | 7 - .../model_4_3-p1-solution000003.solution | 7 - .../model_4_3-p1-solution000004.solution | 7 - .../model_4_3-p1-solution000005.solution | 7 - .../model_4_3-p1-solution000006.solution | 7 - .../model_4_3-p1-solution000007.solution | 7 - .../model_4_3-p1-solution000008.solution | 7 - .../286/expected/model_4_3-p1.eprime-param | 3 - .../issues/286/expected/model_4_3.eprime | 133 -- .../model_4_4-p1-solution000001.solution | 6 - .../model_4_4-p1-solution000002.solution | 7 - .../model_4_4-p1-solution000003.solution | 7 - .../model_4_4-p1-solution000004.solution | 7 - .../model_4_4-p1-solution000005.solution | 7 - .../model_4_4-p1-solution000006.solution | 7 - .../model_4_4-p1-solution000007.solution | 7 - .../model_4_4-p1-solution000008.solution | 7 - .../286/expected/model_4_4-p1.eprime-param | 3 - .../issues/286/expected/model_4_4.eprime | 38 - .../expected/model-cyc1.eprime-param | 6 - .../expected/model-cyc2.eprime-param | 6 - .../model-non-solution000001.solution | 3 - .../expected/model-non.eprime-param | 6 - .../cyclic_graph/expected/model.eprime | 39 - .../model-inst-solution000001.solution | 182 --- .../expected/model-inst.eprime-param | 98 -- .../gchq_2016/expected/model.eprime | 127 -- .../model_1_1_1-p1-solution000001.solution | 3 - .../expected/model_1_1_1-p1.eprime-param | 7 - .../model_1_1_1-p2-solution000001.solution | 3 - .../model_1_1_1-p2-solution000002.solution | 3 - .../expected/model_1_1_1-p2.eprime-param | 7 - .../subsetSum/expected/model_1_1_1.eprime | 27 - .../model_1_1_2-p1-solution000001.solution | 3 - .../expected/model_1_1_2-p1.eprime-param | 7 - .../model_1_1_2-p2-solution000001.solution | 3 - .../model_1_1_2-p2-solution000002.solution | 3 - .../expected/model_1_1_2-p2.eprime-param | 7 - .../subsetSum/expected/model_1_1_2.eprime | 49 - .../model_1_2_1-p1-solution000001.solution | 3 - .../expected/model_1_2_1-p1.eprime-param | 7 - .../model_1_2_1-p2-solution000001.solution | 3 - .../model_1_2_1-p2-solution000002.solution | 3 - .../expected/model_1_2_1-p2.eprime-param | 7 - .../subsetSum/expected/model_1_2_1.eprime | 49 - .../model_1_2_2-p1-solution000001.solution | 3 - .../expected/model_1_2_2-p1.eprime-param | 7 - .../model_1_2_2-p2-solution000001.solution | 3 - .../model_1_2_2-p2-solution000002.solution | 3 - .../expected/model_1_2_2-p2.eprime-param | 7 - .../subsetSum/expected/model_1_2_2.eprime | 49 - .../model_2_1_1-p1-solution000001.solution | 3 - .../expected/model_2_1_1-p1.eprime-param | 7 - .../model_2_1_1-p2-solution000001.solution | 3 - .../model_2_1_1-p2-solution000002.solution | 3 - .../expected/model_2_1_1-p2.eprime-param | 7 - .../subsetSum/expected/model_2_1_1.eprime | 49 - .../model_2_1_2-p1-solution000001.solution | 3 - .../expected/model_2_1_2-p1.eprime-param | 7 - .../model_2_1_2-p2-solution000001.solution | 3 - .../model_2_1_2-p2-solution000002.solution | 3 - .../expected/model_2_1_2-p2.eprime-param | 7 - .../subsetSum/expected/model_2_1_2.eprime | 49 - .../model_2_2_1-p1-solution000001.solution | 3 - .../expected/model_2_2_1-p1.eprime-param | 7 - .../model_2_2_1-p2-solution000001.solution | 3 - .../model_2_2_1-p2-solution000002.solution | 3 - .../expected/model_2_2_1-p2.eprime-param | 7 - .../subsetSum/expected/model_2_2_1.eprime | 49 - .../model_2_2_2-p1-solution000001.solution | 3 - .../expected/model_2_2_2-p1.eprime-param | 7 - .../model_2_2_2-p2-solution000001.solution | 3 - .../model_2_2_2-p2-solution000002.solution | 3 - .../expected/model_2_2_2-p2.eprime-param | 7 - .../subsetSum/expected/model_2_2_2.eprime | 28 - .../expected/model-solution000001.solution | 4 - .../expected/model-solution000002.solution | 4 - .../expected/model-solution000003.solution | 4 - .../expected/model-solution000004.solution | 4 - .../expected/model-solution000005.solution | 4 - .../expected/model-solution000006.solution | 4 - .../expected/model-solution000007.solution | 4 - .../expected/model-solution000008.solution | 4 - .../expected/model-solution000009.solution | 4 - .../expected/model-solution000010.solution | 4 - .../expected/model-solution000011.solution | 4 - .../expected/model-solution000012.solution | 4 - .../expected/model-solution000013.solution | 4 - .../expected/model-solution000014.solution | 4 - .../expected/model-solution000015.solution | 4 - .../expected/model-solution000016.solution | 4 - .../expected/model-solution000017.solution | 4 - .../expected/model-solution000018.solution | 4 - .../expected/model-solution000019.solution | 4 - .../expected/model-solution000020.solution | 4 - .../expected/model-solution000021.solution | 4 - .../expected/model-solution000022.solution | 4 - .../expected/model-solution000023.solution | 4 - .../expected/model-solution000024.solution | 4 - .../expected/model-solution000025.solution | 4 - .../expected/model-solution000026.solution | 4 - .../expected/model-solution000027.solution | 4 - .../expected/model-solution000028.solution | 4 - .../expected/model-solution000029.solution | 4 - .../expected/model-solution000030.solution | 4 - .../expected/model-solution000031.solution | 4 - .../expected/model-solution000032.solution | 4 - .../expected/model-solution000033.solution | 4 - .../expected/model-solution000034.solution | 4 - .../expected/model-solution000035.solution | 4 - .../expected/model-solution000036.solution | 4 - .../expected/model.eprime | 91 -- .../model_1_1_1_1-solution000001.solution | 4 - .../model_1_1_1_1-solution000002.solution | 4 - .../model_1_1_1_1-solution000003.solution | 4 - .../model_1_1_1_1-solution000004.solution | 4 - .../model_1_1_1_1-solution000005.solution | 4 - .../model_1_1_1_1-solution000006.solution | 4 - .../expected/model_1_1_1_1.eprime | 96 -- .../model_1_1_1_2-solution000001.solution | 4 - .../model_1_1_1_2-solution000002.solution | 4 - .../model_1_1_1_2-solution000003.solution | 4 - .../model_1_1_1_2-solution000004.solution | 4 - .../model_1_1_1_2-solution000005.solution | 4 - .../model_1_1_1_2-solution000006.solution | 4 - .../expected/model_1_1_1_2.eprime | 116 -- .../model_1_1_1_3-solution000001.solution | 4 - .../model_1_1_1_3-solution000002.solution | 4 - .../model_1_1_1_3-solution000003.solution | 4 - .../model_1_1_1_3-solution000004.solution | 4 - .../model_1_1_1_3-solution000005.solution | 4 - .../model_1_1_1_3-solution000006.solution | 4 - .../expected/model_1_1_1_3.eprime | 110 -- .../model_1_1_2_1-solution000001.solution | 4 - .../model_1_1_2_1-solution000002.solution | 4 - .../model_1_1_2_1-solution000003.solution | 4 - .../model_1_1_2_1-solution000004.solution | 4 - .../model_1_1_2_1-solution000005.solution | 4 - .../model_1_1_2_1-solution000006.solution | 4 - .../expected/model_1_1_2_1.eprime | 116 -- .../model_1_1_2_2-solution000001.solution | 4 - .../model_1_1_2_2-solution000002.solution | 4 - .../model_1_1_2_2-solution000003.solution | 4 - .../model_1_1_2_2-solution000004.solution | 4 - .../model_1_1_2_2-solution000005.solution | 4 - .../model_1_1_2_2-solution000006.solution | 4 - .../expected/model_1_1_2_2.eprime | 136 -- .../model_1_1_2_3-solution000001.solution | 4 - .../model_1_1_2_3-solution000002.solution | 4 - .../model_1_1_2_3-solution000003.solution | 4 - .../model_1_1_2_3-solution000004.solution | 4 - .../model_1_1_2_3-solution000005.solution | 4 - .../model_1_1_2_3-solution000006.solution | 4 - .../expected/model_1_1_2_3.eprime | 129 -- .../model_1_1_3_1-solution000001.solution | 4 - .../model_1_1_3_1-solution000002.solution | 4 - .../model_1_1_3_1-solution000003.solution | 4 - .../model_1_1_3_1-solution000004.solution | 4 - .../model_1_1_3_1-solution000005.solution | 4 - .../model_1_1_3_1-solution000006.solution | 4 - .../expected/model_1_1_3_1.eprime | 110 -- .../model_1_1_3_2-solution000001.solution | 4 - .../model_1_1_3_2-solution000002.solution | 4 - .../model_1_1_3_2-solution000003.solution | 4 - .../model_1_1_3_2-solution000004.solution | 4 - .../model_1_1_3_2-solution000005.solution | 4 - .../model_1_1_3_2-solution000006.solution | 4 - .../expected/model_1_1_3_2.eprime | 129 -- .../model_1_1_3_3-solution000001.solution | 4 - .../model_1_1_3_3-solution000002.solution | 4 - .../model_1_1_3_3-solution000003.solution | 4 - .../model_1_1_3_3-solution000004.solution | 4 - .../model_1_1_3_3-solution000005.solution | 4 - .../model_1_1_3_3-solution000006.solution | 4 - .../expected/model_1_1_3_3.eprime | 123 -- .../model_1_2_1_1-solution000001.solution | 4 - .../model_1_2_1_1-solution000002.solution | 4 - .../model_1_2_1_1-solution000003.solution | 4 - .../model_1_2_1_1-solution000004.solution | 4 - .../model_1_2_1_1-solution000005.solution | 4 - .../model_1_2_1_1-solution000006.solution | 4 - .../expected/model_1_2_1_1.eprime | 106 -- .../model_1_2_1_2-solution000001.solution | 4 - .../model_1_2_1_2-solution000002.solution | 4 - .../model_1_2_1_2-solution000003.solution | 4 - .../model_1_2_1_2-solution000004.solution | 4 - .../model_1_2_1_2-solution000005.solution | 4 - .../model_1_2_1_2-solution000006.solution | 4 - .../expected/model_1_2_1_2.eprime | 84 -- .../model_1_2_1_3-solution000001.solution | 4 - .../model_1_2_1_3-solution000002.solution | 4 - .../model_1_2_1_3-solution000003.solution | 4 - .../model_1_2_1_3-solution000004.solution | 4 - .../model_1_2_1_3-solution000005.solution | 4 - .../model_1_2_1_3-solution000006.solution | 4 - .../expected/model_1_2_1_3.eprime | 93 -- .../model_1_2_2_1-solution000001.solution | 4 - .../model_1_2_2_1-solution000002.solution | 4 - .../model_1_2_2_1-solution000003.solution | 4 - .../model_1_2_2_1-solution000004.solution | 4 - .../model_1_2_2_1-solution000005.solution | 4 - .../model_1_2_2_1-solution000006.solution | 4 - .../expected/model_1_2_2_1.eprime | 126 -- .../model_1_2_2_2-solution000001.solution | 4 - .../model_1_2_2_2-solution000002.solution | 4 - .../model_1_2_2_2-solution000003.solution | 4 - .../model_1_2_2_2-solution000004.solution | 4 - .../model_1_2_2_2-solution000005.solution | 4 - .../model_1_2_2_2-solution000006.solution | 4 - .../expected/model_1_2_2_2.eprime | 103 -- .../model_1_2_2_3-solution000001.solution | 4 - .../model_1_2_2_3-solution000002.solution | 4 - .../model_1_2_2_3-solution000003.solution | 4 - .../model_1_2_2_3-solution000004.solution | 4 - .../model_1_2_2_3-solution000005.solution | 4 - .../model_1_2_2_3-solution000006.solution | 4 - .../expected/model_1_2_2_3.eprime | 112 -- .../model_1_2_3_1-solution000001.solution | 4 - .../model_1_2_3_1-solution000002.solution | 4 - .../model_1_2_3_1-solution000003.solution | 4 - .../model_1_2_3_1-solution000004.solution | 4 - .../model_1_2_3_1-solution000005.solution | 4 - .../model_1_2_3_1-solution000006.solution | 4 - .../expected/model_1_2_3_1.eprime | 119 -- .../model_1_2_3_2-solution000001.solution | 4 - .../model_1_2_3_2-solution000002.solution | 4 - .../model_1_2_3_2-solution000003.solution | 4 - .../model_1_2_3_2-solution000004.solution | 4 - .../model_1_2_3_2-solution000005.solution | 4 - .../model_1_2_3_2-solution000006.solution | 4 - .../expected/model_1_2_3_2.eprime | 97 -- .../model_1_2_3_3-solution000001.solution | 4 - .../model_1_2_3_3-solution000002.solution | 4 - .../model_1_2_3_3-solution000003.solution | 4 - .../model_1_2_3_3-solution000004.solution | 4 - .../model_1_2_3_3-solution000005.solution | 4 - .../model_1_2_3_3-solution000006.solution | 4 - .../expected/model_1_2_3_3.eprime | 106 -- .../model_1_3_1_1-solution000001.solution | 4 - .../model_1_3_1_1-solution000002.solution | 4 - .../model_1_3_1_1-solution000003.solution | 4 - .../model_1_3_1_1-solution000004.solution | 4 - .../model_1_3_1_1-solution000005.solution | 4 - .../model_1_3_1_1-solution000006.solution | 4 - .../expected/model_1_3_1_1.eprime | 80 -- .../model_1_3_1_2-solution000001.solution | 4 - .../model_1_3_1_2-solution000002.solution | 4 - .../model_1_3_1_2-solution000003.solution | 4 - .../model_1_3_1_2-solution000004.solution | 4 - .../model_1_3_1_2-solution000005.solution | 4 - .../model_1_3_1_2-solution000006.solution | 4 - .../expected/model_1_3_1_2.eprime | 72 - .../model_1_3_1_3-solution000001.solution | 4 - .../model_1_3_1_3-solution000002.solution | 4 - .../model_1_3_1_3-solution000003.solution | 4 - .../model_1_3_1_3-solution000004.solution | 4 - .../model_1_3_1_3-solution000005.solution | 4 - .../model_1_3_1_3-solution000006.solution | 4 - .../expected/model_1_3_1_3.eprime | 60 - .../model_1_3_2_1-solution000001.solution | 4 - .../model_1_3_2_1-solution000002.solution | 4 - .../model_1_3_2_1-solution000003.solution | 4 - .../model_1_3_2_1-solution000004.solution | 4 - .../model_1_3_2_1-solution000005.solution | 4 - .../model_1_3_2_1-solution000006.solution | 4 - .../expected/model_1_3_2_1.eprime | 98 -- .../model_1_3_2_2-solution000001.solution | 4 - .../model_1_3_2_2-solution000002.solution | 4 - .../model_1_3_2_2-solution000003.solution | 4 - .../model_1_3_2_2-solution000004.solution | 4 - .../model_1_3_2_2-solution000005.solution | 4 - .../model_1_3_2_2-solution000006.solution | 4 - .../expected/model_1_3_2_2.eprime | 91 -- .../model_1_3_2_3-solution000001.solution | 4 - .../model_1_3_2_3-solution000002.solution | 4 - .../model_1_3_2_3-solution000003.solution | 4 - .../model_1_3_2_3-solution000004.solution | 4 - .../model_1_3_2_3-solution000005.solution | 4 - .../model_1_3_2_3-solution000006.solution | 4 - .../expected/model_1_3_2_3.eprime | 80 -- .../model_1_3_3_1-solution000001.solution | 4 - .../model_1_3_3_1-solution000002.solution | 4 - .../model_1_3_3_1-solution000003.solution | 4 - .../model_1_3_3_1-solution000004.solution | 4 - .../model_1_3_3_1-solution000005.solution | 4 - .../model_1_3_3_1-solution000006.solution | 4 - .../expected/model_1_3_3_1.eprime | 93 -- .../model_1_3_3_2-solution000001.solution | 4 - .../model_1_3_3_2-solution000002.solution | 4 - .../model_1_3_3_2-solution000003.solution | 4 - .../model_1_3_3_2-solution000004.solution | 4 - .../model_1_3_3_2-solution000005.solution | 4 - .../model_1_3_3_2-solution000006.solution | 4 - .../expected/model_1_3_3_2.eprime | 85 -- .../model_1_3_3_3-solution000001.solution | 4 - .../model_1_3_3_3-solution000002.solution | 4 - .../model_1_3_3_3-solution000003.solution | 4 - .../model_1_3_3_3-solution000004.solution | 4 - .../model_1_3_3_3-solution000005.solution | 4 - .../model_1_3_3_3-solution000006.solution | 4 - .../expected/model_1_3_3_3.eprime | 73 - .../model_2_1_1_1-solution000001.solution | 4 - .../model_2_1_1_1-solution000002.solution | 4 - .../model_2_1_1_1-solution000003.solution | 4 - .../model_2_1_1_1-solution000004.solution | 4 - .../model_2_1_1_1-solution000005.solution | 4 - .../model_2_1_1_1-solution000006.solution | 4 - .../expected/model_2_1_1_1.eprime | 103 -- .../model_2_1_1_2-solution000001.solution | 4 - .../model_2_1_1_2-solution000002.solution | 4 - .../model_2_1_1_2-solution000003.solution | 4 - .../model_2_1_1_2-solution000004.solution | 4 - .../model_2_1_1_2-solution000005.solution | 4 - .../model_2_1_1_2-solution000006.solution | 4 - .../expected/model_2_1_1_2.eprime | 123 -- .../model_2_1_1_3-solution000001.solution | 4 - .../model_2_1_1_3-solution000002.solution | 4 - .../model_2_1_1_3-solution000003.solution | 4 - .../model_2_1_1_3-solution000004.solution | 4 - .../model_2_1_1_3-solution000005.solution | 4 - .../model_2_1_1_3-solution000006.solution | 4 - .../expected/model_2_1_1_3.eprime | 116 -- .../model_2_1_2_1-solution000001.solution | 4 - .../model_2_1_2_1-solution000002.solution | 4 - .../model_2_1_2_1-solution000003.solution | 4 - .../model_2_1_2_1-solution000004.solution | 4 - .../model_2_1_2_1-solution000005.solution | 4 - .../model_2_1_2_1-solution000006.solution | 4 - .../expected/model_2_1_2_1.eprime | 81 -- .../model_2_1_2_2-solution000001.solution | 4 - .../model_2_1_2_2-solution000002.solution | 4 - .../model_2_1_2_2-solution000003.solution | 4 - .../model_2_1_2_2-solution000004.solution | 4 - .../model_2_1_2_2-solution000005.solution | 4 - .../model_2_1_2_2-solution000006.solution | 4 - .../expected/model_2_1_2_2.eprime | 100 -- .../model_2_1_2_3-solution000001.solution | 4 - .../model_2_1_2_3-solution000002.solution | 4 - .../model_2_1_2_3-solution000003.solution | 4 - .../model_2_1_2_3-solution000004.solution | 4 - .../model_2_1_2_3-solution000005.solution | 4 - .../model_2_1_2_3-solution000006.solution | 4 - .../expected/model_2_1_2_3.eprime | 94 -- .../model_2_1_3_1-solution000001.solution | 4 - .../model_2_1_3_1-solution000002.solution | 4 - .../model_2_1_3_1-solution000003.solution | 4 - .../model_2_1_3_1-solution000004.solution | 4 - .../model_2_1_3_1-solution000005.solution | 4 - .../model_2_1_3_1-solution000006.solution | 4 - .../expected/model_2_1_3_1.eprime | 90 -- .../model_2_1_3_2-solution000001.solution | 4 - .../model_2_1_3_2-solution000002.solution | 4 - .../model_2_1_3_2-solution000003.solution | 4 - .../model_2_1_3_2-solution000004.solution | 4 - .../model_2_1_3_2-solution000005.solution | 4 - .../model_2_1_3_2-solution000006.solution | 4 - .../expected/model_2_1_3_2.eprime | 109 -- .../model_2_1_3_3-solution000001.solution | 4 - .../model_2_1_3_3-solution000002.solution | 4 - .../model_2_1_3_3-solution000003.solution | 4 - .../model_2_1_3_3-solution000004.solution | 4 - .../model_2_1_3_3-solution000005.solution | 4 - .../model_2_1_3_3-solution000006.solution | 4 - .../expected/model_2_1_3_3.eprime | 103 -- .../model_2_2_1_1-solution000001.solution | 4 - .../model_2_2_1_1-solution000002.solution | 4 - .../model_2_2_1_1-solution000003.solution | 4 - .../model_2_2_1_1-solution000004.solution | 4 - .../model_2_2_1_1-solution000005.solution | 4 - .../model_2_2_1_1-solution000006.solution | 4 - .../expected/model_2_2_1_1.eprime | 111 -- .../model_2_2_1_2-solution000001.solution | 4 - .../model_2_2_1_2-solution000002.solution | 4 - .../model_2_2_1_2-solution000003.solution | 4 - .../model_2_2_1_2-solution000004.solution | 4 - .../model_2_2_1_2-solution000005.solution | 4 - .../model_2_2_1_2-solution000006.solution | 4 - .../expected/model_2_2_1_2.eprime | 88 -- .../model_2_2_1_3-solution000001.solution | 4 - .../model_2_2_1_3-solution000002.solution | 4 - .../model_2_2_1_3-solution000003.solution | 4 - .../model_2_2_1_3-solution000004.solution | 4 - .../model_2_2_1_3-solution000005.solution | 4 - .../model_2_2_1_3-solution000006.solution | 4 - .../expected/model_2_2_1_3.eprime | 97 -- .../model_2_2_2_1-solution000001.solution | 4 - .../model_2_2_2_1-solution000002.solution | 4 - .../model_2_2_2_1-solution000003.solution | 4 - .../model_2_2_2_1-solution000004.solution | 4 - .../model_2_2_2_1-solution000005.solution | 4 - .../model_2_2_2_1-solution000006.solution | 4 - .../expected/model_2_2_2_1.eprime | 88 -- .../model_2_2_2_2-solution000001.solution | 4 - .../model_2_2_2_2-solution000002.solution | 4 - .../model_2_2_2_2-solution000003.solution | 4 - .../model_2_2_2_2-solution000004.solution | 4 - .../model_2_2_2_2-solution000005.solution | 4 - .../model_2_2_2_2-solution000006.solution | 4 - .../expected/model_2_2_2_2.eprime | 66 - .../model_2_2_2_3-solution000001.solution | 4 - .../model_2_2_2_3-solution000002.solution | 4 - .../model_2_2_2_3-solution000003.solution | 4 - .../model_2_2_2_3-solution000004.solution | 4 - .../model_2_2_2_3-solution000005.solution | 4 - .../model_2_2_2_3-solution000006.solution | 4 - .../expected/model_2_2_2_3.eprime | 75 - .../model_2_2_3_1-solution000001.solution | 4 - .../model_2_2_3_1-solution000002.solution | 4 - .../model_2_2_3_1-solution000003.solution | 4 - .../model_2_2_3_1-solution000004.solution | 4 - .../model_2_2_3_1-solution000005.solution | 4 - .../model_2_2_3_1-solution000006.solution | 4 - .../expected/model_2_2_3_1.eprime | 97 -- .../model_2_2_3_2-solution000001.solution | 4 - .../model_2_2_3_2-solution000002.solution | 4 - .../model_2_2_3_2-solution000003.solution | 4 - .../model_2_2_3_2-solution000004.solution | 4 - .../model_2_2_3_2-solution000005.solution | 4 - .../model_2_2_3_2-solution000006.solution | 4 - .../expected/model_2_2_3_2.eprime | 75 - .../model_2_2_3_3-solution000001.solution | 4 - .../model_2_2_3_3-solution000002.solution | 4 - .../model_2_2_3_3-solution000003.solution | 4 - .../model_2_2_3_3-solution000004.solution | 4 - .../model_2_2_3_3-solution000005.solution | 4 - .../model_2_2_3_3-solution000006.solution | 4 - .../expected/model_2_2_3_3.eprime | 84 -- .../model_2_3_1_1-solution000001.solution | 4 - .../model_2_3_1_1-solution000002.solution | 4 - .../model_2_3_1_1-solution000003.solution | 4 - .../model_2_3_1_1-solution000004.solution | 4 - .../model_2_3_1_1-solution000005.solution | 4 - .../model_2_3_1_1-solution000006.solution | 4 - .../expected/model_2_3_1_1.eprime | 83 -- .../model_2_3_1_2-solution000001.solution | 4 - .../model_2_3_1_2-solution000002.solution | 4 - .../model_2_3_1_2-solution000003.solution | 4 - .../model_2_3_1_2-solution000004.solution | 4 - .../model_2_3_1_2-solution000005.solution | 4 - .../model_2_3_1_2-solution000006.solution | 4 - .../expected/model_2_3_1_2.eprime | 76 - .../model_2_3_1_3-solution000001.solution | 4 - .../model_2_3_1_3-solution000002.solution | 4 - .../model_2_3_1_3-solution000003.solution | 4 - .../model_2_3_1_3-solution000004.solution | 4 - .../model_2_3_1_3-solution000005.solution | 4 - .../model_2_3_1_3-solution000006.solution | 4 - .../expected/model_2_3_1_3.eprime | 65 - .../model_2_3_2_1-solution000001.solution | 4 - .../model_2_3_2_1-solution000002.solution | 4 - .../model_2_3_2_1-solution000003.solution | 4 - .../model_2_3_2_1-solution000004.solution | 4 - .../model_2_3_2_1-solution000005.solution | 4 - .../model_2_3_2_1-solution000006.solution | 4 - .../expected/model_2_3_2_1.eprime | 61 - .../model_2_3_2_2-solution000001.solution | 4 - .../model_2_3_2_2-solution000002.solution | 4 - .../model_2_3_2_2-solution000003.solution | 4 - .../model_2_3_2_2-solution000004.solution | 4 - .../model_2_3_2_2-solution000005.solution | 4 - .../model_2_3_2_2-solution000006.solution | 4 - .../expected/model_2_3_2_2.eprime | 53 - .../model_2_3_2_3-solution000001.solution | 4 - .../model_2_3_2_3-solution000002.solution | 4 - .../model_2_3_2_3-solution000003.solution | 4 - .../model_2_3_2_3-solution000004.solution | 4 - .../model_2_3_2_3-solution000005.solution | 4 - .../model_2_3_2_3-solution000006.solution | 4 - .../expected/model_2_3_2_3.eprime | 41 - .../model_2_3_3_1-solution000001.solution | 4 - .../model_2_3_3_1-solution000002.solution | 4 - .../model_2_3_3_1-solution000003.solution | 4 - .../model_2_3_3_1-solution000004.solution | 4 - .../model_2_3_3_1-solution000005.solution | 4 - .../model_2_3_3_1-solution000006.solution | 4 - .../expected/model_2_3_3_1.eprime | 70 - .../model_2_3_3_2-solution000001.solution | 4 - .../model_2_3_3_2-solution000002.solution | 4 - .../model_2_3_3_2-solution000003.solution | 4 - .../model_2_3_3_2-solution000004.solution | 4 - .../model_2_3_3_2-solution000005.solution | 4 - .../model_2_3_3_2-solution000006.solution | 4 - .../expected/model_2_3_3_2.eprime | 62 - .../model_2_3_3_3-solution000001.solution | 4 - .../model_2_3_3_3-solution000002.solution | 4 - .../model_2_3_3_3-solution000003.solution | 4 - .../model_2_3_3_3-solution000004.solution | 4 - .../model_2_3_3_3-solution000005.solution | 4 - .../model_2_3_3_3-solution000006.solution | 4 - .../expected/model_2_3_3_3.eprime | 50 - .../model_3_1_1_1-solution000001.solution | 4 - .../model_3_1_1_1-solution000002.solution | 4 - .../model_3_1_1_1-solution000003.solution | 4 - .../model_3_1_1_1-solution000004.solution | 4 - .../model_3_1_1_1-solution000005.solution | 4 - .../model_3_1_1_1-solution000006.solution | 4 - .../expected/model_3_1_1_1.eprime | 83 -- .../model_3_1_1_2-solution000001.solution | 4 - .../model_3_1_1_2-solution000002.solution | 4 - .../model_3_1_1_2-solution000003.solution | 4 - .../model_3_1_1_2-solution000004.solution | 4 - .../model_3_1_1_2-solution000005.solution | 4 - .../model_3_1_1_2-solution000006.solution | 4 - .../expected/model_3_1_1_2.eprime | 102 -- .../model_3_1_1_3-solution000001.solution | 4 - .../model_3_1_1_3-solution000002.solution | 4 - .../model_3_1_1_3-solution000003.solution | 4 - .../model_3_1_1_3-solution000004.solution | 4 - .../model_3_1_1_3-solution000005.solution | 4 - .../model_3_1_1_3-solution000006.solution | 4 - .../expected/model_3_1_1_3.eprime | 96 -- .../model_3_1_2_1-solution000001.solution | 4 - .../model_3_1_2_1-solution000002.solution | 4 - .../model_3_1_2_1-solution000003.solution | 4 - .../model_3_1_2_1-solution000004.solution | 4 - .../model_3_1_2_1-solution000005.solution | 4 - .../model_3_1_2_1-solution000006.solution | 4 - .../expected/model_3_1_2_1.eprime | 75 - .../model_3_1_2_2-solution000001.solution | 4 - .../model_3_1_2_2-solution000002.solution | 4 - .../model_3_1_2_2-solution000003.solution | 4 - .../model_3_1_2_2-solution000004.solution | 4 - .../model_3_1_2_2-solution000005.solution | 4 - .../model_3_1_2_2-solution000006.solution | 4 - .../expected/model_3_1_2_2.eprime | 94 -- .../model_3_1_2_3-solution000001.solution | 4 - .../model_3_1_2_3-solution000002.solution | 4 - .../model_3_1_2_3-solution000003.solution | 4 - .../model_3_1_2_3-solution000004.solution | 4 - .../model_3_1_2_3-solution000005.solution | 4 - .../model_3_1_2_3-solution000006.solution | 4 - .../expected/model_3_1_2_3.eprime | 88 -- .../model_3_1_3_1-solution000001.solution | 4 - .../model_3_1_3_1-solution000002.solution | 4 - .../model_3_1_3_1-solution000003.solution | 4 - .../model_3_1_3_1-solution000004.solution | 4 - .../model_3_1_3_1-solution000005.solution | 4 - .../model_3_1_3_1-solution000006.solution | 4 - .../expected/model_3_1_3_1.eprime | 63 - .../model_3_1_3_2-solution000001.solution | 4 - .../model_3_1_3_2-solution000002.solution | 4 - .../model_3_1_3_2-solution000003.solution | 4 - .../model_3_1_3_2-solution000004.solution | 4 - .../model_3_1_3_2-solution000005.solution | 4 - .../model_3_1_3_2-solution000006.solution | 4 - .../expected/model_3_1_3_2.eprime | 83 -- .../model_3_1_3_3-solution000001.solution | 4 - .../model_3_1_3_3-solution000002.solution | 4 - .../model_3_1_3_3-solution000003.solution | 4 - .../model_3_1_3_3-solution000004.solution | 4 - .../model_3_1_3_3-solution000005.solution | 4 - .../model_3_1_3_3-solution000006.solution | 4 - .../expected/model_3_1_3_3.eprime | 76 - .../model_3_2_1_1-solution000001.solution | 4 - .../model_3_2_1_1-solution000002.solution | 4 - .../model_3_2_1_1-solution000003.solution | 4 - .../model_3_2_1_1-solution000004.solution | 4 - .../model_3_2_1_1-solution000005.solution | 4 - .../model_3_2_1_1-solution000006.solution | 4 - .../expected/model_3_2_1_1.eprime | 86 -- .../model_3_2_1_2-solution000001.solution | 4 - .../model_3_2_1_2-solution000002.solution | 4 - .../model_3_2_1_2-solution000003.solution | 4 - .../model_3_2_1_2-solution000004.solution | 4 - .../model_3_2_1_2-solution000005.solution | 4 - .../model_3_2_1_2-solution000006.solution | 4 - .../expected/model_3_2_1_2.eprime | 64 - .../model_3_2_1_3-solution000001.solution | 4 - .../model_3_2_1_3-solution000002.solution | 4 - .../model_3_2_1_3-solution000003.solution | 4 - .../model_3_2_1_3-solution000004.solution | 4 - .../model_3_2_1_3-solution000005.solution | 4 - .../model_3_2_1_3-solution000006.solution | 4 - .../expected/model_3_2_1_3.eprime | 73 - .../model_3_2_2_1-solution000001.solution | 4 - .../model_3_2_2_1-solution000002.solution | 4 - .../model_3_2_2_1-solution000003.solution | 4 - .../model_3_2_2_1-solution000004.solution | 4 - .../model_3_2_2_1-solution000005.solution | 4 - .../model_3_2_2_1-solution000006.solution | 4 - .../expected/model_3_2_2_1.eprime | 78 -- .../model_3_2_2_2-solution000001.solution | 4 - .../model_3_2_2_2-solution000002.solution | 4 - .../model_3_2_2_2-solution000003.solution | 4 - .../model_3_2_2_2-solution000004.solution | 4 - .../model_3_2_2_2-solution000005.solution | 4 - .../model_3_2_2_2-solution000006.solution | 4 - .../expected/model_3_2_2_2.eprime | 56 - .../model_3_2_2_3-solution000001.solution | 4 - .../model_3_2_2_3-solution000002.solution | 4 - .../model_3_2_2_3-solution000003.solution | 4 - .../model_3_2_2_3-solution000004.solution | 4 - .../model_3_2_2_3-solution000005.solution | 4 - .../model_3_2_2_3-solution000006.solution | 4 - .../expected/model_3_2_2_3.eprime | 65 - .../model_3_2_3_1-solution000001.solution | 4 - .../model_3_2_3_1-solution000002.solution | 4 - .../model_3_2_3_1-solution000003.solution | 4 - .../model_3_2_3_1-solution000004.solution | 4 - .../model_3_2_3_1-solution000005.solution | 4 - .../model_3_2_3_1-solution000006.solution | 4 - .../expected/model_3_2_3_1.eprime | 68 - .../model_3_2_3_2-solution000001.solution | 4 - .../model_3_2_3_2-solution000002.solution | 4 - .../model_3_2_3_2-solution000003.solution | 4 - .../model_3_2_3_2-solution000004.solution | 4 - .../model_3_2_3_2-solution000005.solution | 4 - .../model_3_2_3_2-solution000006.solution | 4 - .../expected/model_3_2_3_2.eprime | 44 - .../model_3_2_3_3-solution000001.solution | 4 - .../model_3_2_3_3-solution000002.solution | 4 - .../model_3_2_3_3-solution000003.solution | 4 - .../model_3_2_3_3-solution000004.solution | 4 - .../model_3_2_3_3-solution000005.solution | 4 - .../model_3_2_3_3-solution000006.solution | 4 - .../expected/model_3_2_3_3.eprime | 53 - .../model_3_3_1_1-solution000001.solution | 4 - .../model_3_3_1_1-solution000002.solution | 4 - .../model_3_3_1_1-solution000003.solution | 4 - .../model_3_3_1_1-solution000004.solution | 4 - .../model_3_3_1_1-solution000005.solution | 4 - .../model_3_3_1_1-solution000006.solution | 4 - .../expected/model_3_3_1_1.eprime | 62 - .../model_3_3_1_2-solution000001.solution | 4 - .../model_3_3_1_2-solution000002.solution | 4 - .../model_3_3_1_2-solution000003.solution | 4 - .../model_3_3_1_2-solution000004.solution | 4 - .../model_3_3_1_2-solution000005.solution | 4 - .../model_3_3_1_2-solution000006.solution | 4 - .../expected/model_3_3_1_2.eprime | 55 - .../model_3_3_1_3-solution000001.solution | 4 - .../model_3_3_1_3-solution000002.solution | 4 - .../model_3_3_1_3-solution000003.solution | 4 - .../model_3_3_1_3-solution000004.solution | 4 - .../model_3_3_1_3-solution000005.solution | 4 - .../model_3_3_1_3-solution000006.solution | 4 - .../expected/model_3_3_1_3.eprime | 42 - .../model_3_3_2_1-solution000001.solution | 4 - .../model_3_3_2_1-solution000002.solution | 4 - .../model_3_3_2_1-solution000003.solution | 4 - .../model_3_3_2_1-solution000004.solution | 4 - .../model_3_3_2_1-solution000005.solution | 4 - .../model_3_3_2_1-solution000006.solution | 4 - .../expected/model_3_3_2_1.eprime | 54 - .../model_3_3_2_2-solution000001.solution | 4 - .../model_3_3_2_2-solution000002.solution | 4 - .../model_3_3_2_2-solution000003.solution | 4 - .../model_3_3_2_2-solution000004.solution | 4 - .../model_3_3_2_2-solution000005.solution | 4 - .../model_3_3_2_2-solution000006.solution | 4 - .../expected/model_3_3_2_2.eprime | 47 - .../model_3_3_2_3-solution000001.solution | 4 - .../model_3_3_2_3-solution000002.solution | 4 - .../model_3_3_2_3-solution000003.solution | 4 - .../model_3_3_2_3-solution000004.solution | 4 - .../model_3_3_2_3-solution000005.solution | 4 - .../model_3_3_2_3-solution000006.solution | 4 - .../expected/model_3_3_2_3.eprime | 34 - .../model_3_3_3_1-solution000001.solution | 4 - .../model_3_3_3_1-solution000002.solution | 4 - .../model_3_3_3_1-solution000003.solution | 4 - .../model_3_3_3_1-solution000004.solution | 4 - .../model_3_3_3_1-solution000005.solution | 4 - .../model_3_3_3_1-solution000006.solution | 4 - .../expected/model_3_3_3_1.eprime | 42 - .../model_3_3_3_2-solution000001.solution | 4 - .../model_3_3_3_2-solution000002.solution | 4 - .../model_3_3_3_2-solution000003.solution | 4 - .../model_3_3_3_2-solution000004.solution | 4 - .../model_3_3_3_2-solution000005.solution | 4 - .../model_3_3_3_2-solution000006.solution | 4 - .../expected/model_3_3_3_2.eprime | 34 - .../model_3_3_3_3-solution000001.solution | 4 - .../model_3_3_3_3-solution000002.solution | 4 - .../model_3_3_3_3-solution000003.solution | 4 - .../model_3_3_3_3-solution000004.solution | 4 - .../model_3_3_3_3-solution000005.solution | 4 - .../model_3_3_3_3-solution000006.solution | 4 - .../expected/model_3_3_3_3.eprime | 24 - .../model_1_1-solution000001.solution | 11 - .../expected/model_1_1.eprime | 324 ----- .../model_1_2-solution000001.solution | 11 - .../expected/model_1_2.eprime | 787 ----------- .../model_1_3-solution000001.solution | 11 - .../expected/model_1_3.eprime | 858 ------------ .../model_1_4-solution000001.solution | 11 - .../expected/model_1_4.eprime | 382 ----- .../model_2_1-solution000001.solution | 11 - .../expected/model_2_1.eprime | 761 ---------- .../model_2_2-solution000001.solution | 11 - .../expected/model_2_2.eprime | 949 ------------- .../model_2_3-solution000001.solution | 11 - .../expected/model_2_3.eprime | 1210 ---------------- .../model_2_4-solution000001.solution | 11 - .../expected/model_2_4.eprime | 809 ----------- .../model_3_1-solution000001.solution | 11 - .../expected/model_3_1.eprime | 854 ------------ .../model_3_2-solution000001.solution | 11 - .../expected/model_3_2.eprime | 1230 ----------------- .../model_3_3-solution000001.solution | 11 - .../expected/model_3_3.eprime | 1131 --------------- .../model_3_4-solution000001.solution | 11 - .../expected/model_3_4.eprime | 908 ------------ .../model_4_1-solution000001.solution | 11 - .../expected/model_4_1.eprime | 373 ----- .../model_4_2-solution000001.solution | 11 - .../expected/model_4_2.eprime | 827 ----------- .../model_4_3-solution000001.solution | 11 - .../expected/model_4_3.eprime | 903 ------------ .../model_4_4-solution000001.solution | 11 - .../expected/model_4_4.eprime | 394 ------ .../expected/model-solution000001.solution | 7 - .../expected/model-solution000002.solution | 7 - .../expected/model-solution000003.solution | 8 - .../expected/model-solution000004.solution | 7 - .../expected/model-solution000005.solution | 8 - .../expected/model-solution000006.solution | 8 - .../expected/model-solution000007.solution | 9 - .../expected/model-solution000008.solution | 7 - .../expected/model-solution000009.solution | 8 - .../expected/model-solution000010.solution | 8 - .../expected/model-solution000011.solution | 9 - .../expected/model-solution000012.solution | 8 - .../expected/model-solution000013.solution | 9 - .../expected/model-solution000014.solution | 9 - .../expected/model-solution000015.solution | 10 - .../expected/model-solution000016.solution | 10 - .../expected/model-solution000017.solution | 11 - .../expected/model-solution000018.solution | 10 - .../expected/model-solution000019.solution | 11 - .../expected/model-solution000020.solution | 11 - .../expected/model-solution000021.solution | 12 - .../expected/model-solution000022.solution | 10 - .../expected/model-solution000023.solution | 11 - .../expected/model-solution000024.solution | 11 - .../expected/model-solution000025.solution | 12 - .../expected/model-solution000026.solution | 11 - .../expected/model-solution000027.solution | 12 - .../expected/model-solution000028.solution | 12 - .../expected/model-solution000029.solution | 13 - .../expected/model-solution000030.solution | 11 - .../expected/model-solution000031.solution | 10 - .../expected/model-solution000032.solution | 11 - .../expected/model-solution000033.solution | 11 - .../expected/model-solution000034.solution | 12 - .../expected/model-solution000035.solution | 10 - .../expected/model-solution000036.solution | 11 - .../expected/model-solution000037.solution | 11 - .../expected/model-solution000038.solution | 12 - .../expected/model-solution000039.solution | 11 - .../expected/model-solution000040.solution | 12 - .../expected/model-solution000041.solution | 12 - .../expected/model-solution000042.solution | 13 - .../expected/model-solution000043.solution | 11 - .../expected/model-solution000044.solution | 12 - .../expected/model-solution000045.solution | 12 - .../expected/model-solution000046.solution | 13 - .../expected/model-solution000047.solution | 11 - .../expected/model-solution000048.solution | 12 - .../expected/model-solution000049.solution | 12 - .../expected/model-solution000050.solution | 13 - .../expected/model-solution000051.solution | 12 - .../expected/model-solution000052.solution | 13 - .../expected/model-solution000053.solution | 13 - .../expected/model-solution000054.solution | 14 - .../expected/model-solution000055.solution | 11 - .../expected/model-solution000056.solution | 11 - .../expected/model-solution000057.solution | 12 - .../expected/model-solution000058.solution | 10 - .../expected/model-solution000059.solution | 11 - .../expected/model-solution000060.solution | 11 - .../expected/model-solution000061.solution | 12 - .../expected/model-solution000062.solution | 11 - .../expected/model-solution000063.solution | 12 - .../expected/model-solution000064.solution | 12 - .../expected/model-solution000065.solution | 13 - .../expected/model-solution000066.solution | 12 - .../expected/model-solution000067.solution | 13 - .../expected/model-solution000068.solution | 11 - .../expected/model-solution000069.solution | 12 - .../expected/model-solution000070.solution | 12 - .../expected/model-solution000071.solution | 13 - .../expected/model-solution000072.solution | 12 - .../expected/model-solution000073.solution | 13 - .../expected/model-solution000074.solution | 13 - .../expected/model-solution000075.solution | 14 - .../expected/model-solution000076.solution | 13 - .../expected/model-solution000077.solution | 11 - .../expected/model-solution000078.solution | 12 - .../expected/model-solution000079.solution | 12 - .../expected/model-solution000080.solution | 13 - .../expected/model-solution000081.solution | 12 - .../expected/model-solution000082.solution | 13 - .../expected/model-solution000083.solution | 13 - .../expected/model-solution000084.solution | 14 - .../expected/model-solution000085.solution | 12 - .../expected/model-solution000086.solution | 13 - .../expected/model-solution000087.solution | 13 - .../expected/model-solution000088.solution | 14 - .../expected/model-solution000089.solution | 13 - .../expected/model-solution000090.solution | 14 - .../expected/model-solution000091.solution | 14 - .../expected/model-solution000092.solution | 15 - .../expected/model-solution000093.solution | 11 - .../expected/model-solution000094.solution | 11 - .../expected/model-solution000095.solution | 12 - .../expected/model-solution000096.solution | 11 - .../expected/model-solution000097.solution | 12 - .../expected/model-solution000098.solution | 12 - .../expected/model-solution000099.solution | 13 - .../expected/model-solution000100.solution | 12 - .../expected/model-solution000101.solution | 13 - .../expected/model-solution000102.solution | 12 - .../expected/model-solution000103.solution | 13 - .../expected/model-solution000104.solution | 13 - .../expected/model-solution000105.solution | 14 - .../expected/model-solution000106.solution | 13 - .../expected/model-solution000107.solution | 12 - .../expected/model-solution000108.solution | 13 - .../expected/model-solution000109.solution | 13 - .../expected/model-solution000110.solution | 14 - .../expected/model-solution000111.solution | 13 - .../expected/model-solution000112.solution | 14 - .../expected/model-solution000113.solution | 14 - .../expected/model-solution000114.solution | 15 - .../expected/model-solution000115.solution | 13 - .../expected/model-solution000116.solution | 13 - .../expected/model-solution000117.solution | 14 - .../expected/model-solution000118.solution | 14 - .../expected/model-solution000119.solution | 15 - .../expected/model-solution000120.solution | 15 - .../expected/model.eprime | 62 - .../model_1_1_1_1-solution000001.solution | 4 - .../model_1_1_1_1-solution000002.solution | 4 - .../model_1_1_1_1-solution000003.solution | 4 - .../model_1_1_1_1-solution000004.solution | 4 - .../model_1_1_1_1-solution000005.solution | 4 - .../model_1_1_1_1-solution000006.solution | 4 - .../expected/model_1_1_1_1.eprime | 24 - .../model_1_1_1_2-solution000001.solution | 4 - .../model_1_1_1_2-solution000002.solution | 4 - .../model_1_1_1_2-solution000003.solution | 4 - .../model_1_1_1_2-solution000004.solution | 4 - .../model_1_1_1_2-solution000005.solution | 4 - .../model_1_1_1_2-solution000006.solution | 4 - .../expected/model_1_1_1_2.eprime | 30 - .../model_1_1_2_1-solution000001.solution | 4 - .../model_1_1_2_1-solution000002.solution | 4 - .../model_1_1_2_1-solution000003.solution | 4 - .../model_1_1_2_1-solution000004.solution | 4 - .../model_1_1_2_1-solution000005.solution | 4 - .../model_1_1_2_1-solution000006.solution | 4 - .../expected/model_1_1_2_1.eprime | 30 - .../model_1_1_2_2-solution000001.solution | 4 - .../model_1_1_2_2-solution000002.solution | 4 - .../model_1_1_2_2-solution000003.solution | 4 - .../model_1_1_2_2-solution000004.solution | 4 - .../model_1_1_2_2-solution000005.solution | 4 - .../model_1_1_2_2-solution000006.solution | 4 - .../expected/model_1_1_2_2.eprime | 34 - .../model_1_2_1_1-solution000001.solution | 4 - .../model_1_2_1_1-solution000002.solution | 4 - .../model_1_2_1_1-solution000003.solution | 4 - .../model_1_2_1_1-solution000004.solution | 4 - .../model_1_2_1_1-solution000005.solution | 4 - .../model_1_2_1_1-solution000006.solution | 4 - .../expected/model_1_2_1_1.eprime | 34 - .../model_1_2_1_2-solution000001.solution | 4 - .../model_1_2_1_2-solution000002.solution | 4 - .../model_1_2_1_2-solution000003.solution | 4 - .../model_1_2_1_2-solution000004.solution | 4 - .../model_1_2_1_2-solution000005.solution | 4 - .../model_1_2_1_2-solution000006.solution | 4 - .../expected/model_1_2_1_2.eprime | 29 - .../model_1_2_2_1-solution000001.solution | 4 - .../model_1_2_2_1-solution000002.solution | 4 - .../model_1_2_2_1-solution000003.solution | 4 - .../model_1_2_2_1-solution000004.solution | 4 - .../model_1_2_2_1-solution000005.solution | 4 - .../model_1_2_2_1-solution000006.solution | 4 - .../expected/model_1_2_2_1.eprime | 38 - .../model_1_2_2_2-solution000001.solution | 4 - .../model_1_2_2_2-solution000002.solution | 4 - .../model_1_2_2_2-solution000003.solution | 4 - .../model_1_2_2_2-solution000004.solution | 4 - .../model_1_2_2_2-solution000005.solution | 4 - .../model_1_2_2_2-solution000006.solution | 4 - .../expected/model_1_2_2_2.eprime | 34 - .../model_2_1_1_1-solution000001.solution | 4 - .../model_2_1_1_1-solution000002.solution | 4 - .../model_2_1_1_1-solution000003.solution | 4 - .../model_2_1_1_1-solution000004.solution | 4 - .../model_2_1_1_1-solution000005.solution | 4 - .../model_2_1_1_1-solution000006.solution | 4 - .../expected/model_2_1_1_1.eprime | 33 - .../model_2_1_1_2-solution000001.solution | 4 - .../model_2_1_1_2-solution000002.solution | 4 - .../model_2_1_1_2-solution000003.solution | 4 - .../model_2_1_1_2-solution000004.solution | 4 - .../model_2_1_1_2-solution000005.solution | 4 - .../model_2_1_1_2-solution000006.solution | 4 - .../expected/model_2_1_1_2.eprime | 37 - .../model_2_1_2_1-solution000001.solution | 4 - .../model_2_1_2_1-solution000002.solution | 4 - .../model_2_1_2_1-solution000003.solution | 4 - .../model_2_1_2_1-solution000004.solution | 4 - .../model_2_1_2_1-solution000005.solution | 4 - .../model_2_1_2_1-solution000006.solution | 4 - .../expected/model_2_1_2_1.eprime | 29 - .../model_2_1_2_2-solution000001.solution | 4 - .../model_2_1_2_2-solution000002.solution | 4 - .../model_2_1_2_2-solution000003.solution | 4 - .../model_2_1_2_2-solution000004.solution | 4 - .../model_2_1_2_2-solution000005.solution | 4 - .../model_2_1_2_2-solution000006.solution | 4 - .../expected/model_2_1_2_2.eprime | 33 - .../model_2_2_1_1-solution000001.solution | 4 - .../model_2_2_1_1-solution000002.solution | 4 - .../model_2_2_1_1-solution000003.solution | 4 - .../model_2_2_1_1-solution000004.solution | 4 - .../model_2_2_1_1-solution000005.solution | 4 - .../model_2_2_1_1-solution000006.solution | 4 - .../expected/model_2_2_1_1.eprime | 45 - .../model_2_2_1_2-solution000001.solution | 4 - .../model_2_2_1_2-solution000002.solution | 4 - .../model_2_2_1_2-solution000003.solution | 4 - .../model_2_2_1_2-solution000004.solution | 4 - .../model_2_2_1_2-solution000005.solution | 4 - .../model_2_2_1_2-solution000006.solution | 4 - .../expected/model_2_2_1_2.eprime | 41 - .../model_2_2_2_1-solution000001.solution | 4 - .../model_2_2_2_1-solution000002.solution | 4 - .../model_2_2_2_1-solution000003.solution | 4 - .../model_2_2_2_1-solution000004.solution | 4 - .../model_2_2_2_1-solution000005.solution | 4 - .../model_2_2_2_1-solution000006.solution | 4 - .../expected/model_2_2_2_1.eprime | 41 - .../model_2_2_2_2-solution000001.solution | 4 - .../model_2_2_2_2-solution000002.solution | 4 - .../model_2_2_2_2-solution000003.solution | 4 - .../model_2_2_2_2-solution000004.solution | 4 - .../model_2_2_2_2-solution000005.solution | 4 - .../model_2_2_2_2-solution000006.solution | 4 - .../expected/model_2_2_2_2.eprime | 37 - 7861 files changed, 781 insertions(+), 116991 deletions(-) delete mode 100644 tests/custom/issues/119/1/stdout.expected delete mode 100644 tests/custom/issues/119/2/stdout.expected delete mode 100644 tests/custom/issues/370/01/stdout.expected delete mode 100644 tests/custom/issues/370/03/stdout.expected delete mode 100644 tests/custom/issues/388/2/stdout.expected create mode 100644 tests/custom/permutations/22_tagged_ints/int/0001_permute_untagged/permutation.essence create mode 100755 tests/custom/permutations/22_tagged_ints/int/0001_permute_untagged/run.sh create mode 100644 tests/custom/permutations/22_tagged_ints/int/0001_permute_untagged/stdout.expected create mode 100644 tests/custom/permutations/22_tagged_ints/int/0002_permute_tagged/permutation.essence create mode 100755 tests/custom/permutations/22_tagged_ints/int/0002_permute_tagged/run.sh create mode 100644 tests/custom/permutations/22_tagged_ints/int/0002_permute_tagged/stdout.expected create mode 100644 tests/custom/permutations/22_tagged_ints/int/0003_tagged_lits_in_param/permutation.essence create mode 100644 tests/custom/permutations/22_tagged_ints/int/0003_tagged_lits_in_param/permutation.param create mode 100755 tests/custom/permutations/22_tagged_ints/int/0003_tagged_lits_in_param/run.sh create mode 100644 tests/custom/permutations/22_tagged_ints/int/0003_tagged_lits_in_param/stdout.expected create mode 100644 tests/custom/permutations/22_tagged_ints/int/div/0001_same_tags_works/permutation.essence create mode 100755 tests/custom/permutations/22_tagged_ints/int/div/0001_same_tags_works/run.sh create mode 100644 tests/custom/permutations/22_tagged_ints/int/div/0001_same_tags_works/stdout.expected create mode 100644 tests/custom/permutations/22_tagged_ints/int/div/0002_diff_tags_prohibited/permutation.essence create mode 100755 tests/custom/permutations/22_tagged_ints/int/div/0002_diff_tags_prohibited/run.sh create mode 100644 tests/custom/permutations/22_tagged_ints/int/div/0002_diff_tags_prohibited/stderr.expected create mode 100644 tests/custom/permutations/22_tagged_ints/int/div/0002_diff_tags_prohibited/stdout.expected create mode 100644 tests/custom/permutations/22_tagged_ints/int/div/0003_const_tagged_works/permutation.essence create mode 100755 tests/custom/permutations/22_tagged_ints/int/div/0003_const_tagged_works/run.sh create mode 100644 tests/custom/permutations/22_tagged_ints/int/div/0003_const_tagged_works/stdout.expected create mode 100644 tests/custom/permutations/22_tagged_ints/int/div/0004_enum_doesnt_work/permutation.essence create mode 100755 tests/custom/permutations/22_tagged_ints/int/div/0004_enum_doesnt_work/run.sh create mode 100644 tests/custom/permutations/22_tagged_ints/int/div/0004_enum_doesnt_work/stderr.expected create mode 100644 tests/custom/permutations/22_tagged_ints/int/div/0004_enum_doesnt_work/stdout.expected create mode 100644 tests/custom/permutations/22_tagged_ints/int/factorial/0002_diff_tags_prohibited/permutation.essence create mode 100755 tests/custom/permutations/22_tagged_ints/int/factorial/0002_diff_tags_prohibited/run.sh create mode 100644 tests/custom/permutations/22_tagged_ints/int/factorial/0002_diff_tags_prohibited/stderr.expected create mode 100644 tests/custom/permutations/22_tagged_ints/int/factorial/0002_diff_tags_prohibited/stdout.expected create mode 100644 tests/custom/permutations/22_tagged_ints/int/factorial/0003_const_tagged_works/permutation.essence create mode 100755 tests/custom/permutations/22_tagged_ints/int/factorial/0003_const_tagged_works/run.sh create mode 100644 tests/custom/permutations/22_tagged_ints/int/factorial/0003_const_tagged_works/stdout.expected create mode 100644 tests/custom/permutations/22_tagged_ints/int/geq/0002_diff_tags_prohibited/permutation.essence create mode 100755 tests/custom/permutations/22_tagged_ints/int/geq/0002_diff_tags_prohibited/run.sh create mode 100644 tests/custom/permutations/22_tagged_ints/int/geq/0002_diff_tags_prohibited/stderr.expected create mode 100644 tests/custom/permutations/22_tagged_ints/int/geq/0002_diff_tags_prohibited/stdout.expected create mode 100644 tests/custom/permutations/22_tagged_ints/int/geq/0003_const_tagged_works/permutation.essence create mode 100755 tests/custom/permutations/22_tagged_ints/int/geq/0003_const_tagged_works/run.sh create mode 100644 tests/custom/permutations/22_tagged_ints/int/geq/0003_const_tagged_works/stdout.expected create mode 100644 tests/custom/permutations/22_tagged_ints/int/leq/0002_diff_tags_prohibited/permutation.essence create mode 100755 tests/custom/permutations/22_tagged_ints/int/leq/0002_diff_tags_prohibited/run.sh create mode 100644 tests/custom/permutations/22_tagged_ints/int/leq/0002_diff_tags_prohibited/stderr.expected create mode 100644 tests/custom/permutations/22_tagged_ints/int/leq/0002_diff_tags_prohibited/stdout.expected create mode 100644 tests/custom/permutations/22_tagged_ints/int/leq/0003_const_tagged_works/permutation.essence create mode 100755 tests/custom/permutations/22_tagged_ints/int/leq/0003_const_tagged_works/run.sh create mode 100644 tests/custom/permutations/22_tagged_ints/int/leq/0003_const_tagged_works/stdout.expected create mode 100644 tests/custom/permutations/22_tagged_ints/int/lt/0002_diff_tags_prohibited/permutation.essence create mode 100755 tests/custom/permutations/22_tagged_ints/int/lt/0002_diff_tags_prohibited/run.sh create mode 100644 tests/custom/permutations/22_tagged_ints/int/lt/0002_diff_tags_prohibited/stderr.expected create mode 100644 tests/custom/permutations/22_tagged_ints/int/lt/0002_diff_tags_prohibited/stdout.expected create mode 100644 tests/custom/permutations/22_tagged_ints/int/lt/0003_const_tagged_works/permutation.essence create mode 100755 tests/custom/permutations/22_tagged_ints/int/lt/0003_const_tagged_works/run.sh create mode 100644 tests/custom/permutations/22_tagged_ints/int/lt/0003_const_tagged_works/stdout.expected create mode 100644 tests/custom/permutations/22_tagged_ints/int/max/0001_same_tags_work/permutation.essence create mode 100755 tests/custom/permutations/22_tagged_ints/int/max/0001_same_tags_work/run.sh create mode 100644 tests/custom/permutations/22_tagged_ints/int/max/0001_same_tags_work/stdout.expected create mode 100644 tests/custom/permutations/22_tagged_ints/int/max/0002_diff_tags_prohibited/permutation.essence create mode 100755 tests/custom/permutations/22_tagged_ints/int/max/0002_diff_tags_prohibited/run.sh create mode 100644 tests/custom/permutations/22_tagged_ints/int/max/0002_diff_tags_prohibited/stderr.expected create mode 100644 tests/custom/permutations/22_tagged_ints/int/max/0002_diff_tags_prohibited/stdout.expected create mode 100644 tests/custom/permutations/22_tagged_ints/int/max/0003_const_tagged_works/permutation.essence create mode 100755 tests/custom/permutations/22_tagged_ints/int/max/0003_const_tagged_works/run.sh create mode 100644 tests/custom/permutations/22_tagged_ints/int/max/0003_const_tagged_works/stdout.expected create mode 100644 tests/custom/permutations/22_tagged_ints/int/min/0001_same_tags_work/permutation.essence create mode 100755 tests/custom/permutations/22_tagged_ints/int/min/0001_same_tags_work/run.sh create mode 100644 tests/custom/permutations/22_tagged_ints/int/min/0001_same_tags_work/stdout.expected create mode 100644 tests/custom/permutations/22_tagged_ints/int/min/0002_diff_tags_prohibited/permutation.essence create mode 100755 tests/custom/permutations/22_tagged_ints/int/min/0002_diff_tags_prohibited/run.sh create mode 100644 tests/custom/permutations/22_tagged_ints/int/min/0002_diff_tags_prohibited/stderr.expected create mode 100644 tests/custom/permutations/22_tagged_ints/int/min/0002_diff_tags_prohibited/stdout.expected create mode 100644 tests/custom/permutations/22_tagged_ints/int/min/0003_const_tagged_works/permutation.essence create mode 100755 tests/custom/permutations/22_tagged_ints/int/min/0003_const_tagged_works/run.sh create mode 100644 tests/custom/permutations/22_tagged_ints/int/min/0003_const_tagged_works/stdout.expected create mode 100644 tests/custom/permutations/22_tagged_ints/int/minus/0001_same_tags_works/permutation.essence create mode 100755 tests/custom/permutations/22_tagged_ints/int/minus/0001_same_tags_works/run.sh create mode 100644 tests/custom/permutations/22_tagged_ints/int/minus/0001_same_tags_works/stdout.expected create mode 100644 tests/custom/permutations/22_tagged_ints/int/minus/0002_diff_tags_prohibited/permutation.essence create mode 100755 tests/custom/permutations/22_tagged_ints/int/minus/0002_diff_tags_prohibited/run.sh create mode 100644 tests/custom/permutations/22_tagged_ints/int/minus/0002_diff_tags_prohibited/stderr.expected create mode 100644 tests/custom/permutations/22_tagged_ints/int/minus/0002_diff_tags_prohibited/stdout.expected create mode 100644 tests/custom/permutations/22_tagged_ints/int/minus/0003_const_tagged_works/permutation.essence create mode 100755 tests/custom/permutations/22_tagged_ints/int/minus/0003_const_tagged_works/run.sh create mode 100644 tests/custom/permutations/22_tagged_ints/int/minus/0003_const_tagged_works/stdout.expected create mode 100644 tests/custom/permutations/22_tagged_ints/int/mod/0001_same_tags_works/permutation.essence create mode 100755 tests/custom/permutations/22_tagged_ints/int/mod/0001_same_tags_works/run.sh create mode 100644 tests/custom/permutations/22_tagged_ints/int/mod/0001_same_tags_works/stdout.expected create mode 100644 tests/custom/permutations/22_tagged_ints/int/mod/0002_diff_tags_prohibited/permutation.essence create mode 100755 tests/custom/permutations/22_tagged_ints/int/mod/0002_diff_tags_prohibited/run.sh create mode 100644 tests/custom/permutations/22_tagged_ints/int/mod/0002_diff_tags_prohibited/stderr.expected create mode 100644 tests/custom/permutations/22_tagged_ints/int/mod/0002_diff_tags_prohibited/stdout.expected create mode 100644 tests/custom/permutations/22_tagged_ints/int/mod/0003_const_tagged_works/permutation.essence create mode 100755 tests/custom/permutations/22_tagged_ints/int/mod/0003_const_tagged_works/run.sh create mode 100644 tests/custom/permutations/22_tagged_ints/int/mod/0003_const_tagged_works/stdout.expected create mode 100644 tests/custom/permutations/22_tagged_ints/int/neg/0001_same_tags_works/permutation.essence create mode 100755 tests/custom/permutations/22_tagged_ints/int/neg/0001_same_tags_works/run.sh create mode 100644 tests/custom/permutations/22_tagged_ints/int/neg/0001_same_tags_works/stdout.expected create mode 100644 tests/custom/permutations/22_tagged_ints/int/neg/0002_diff_tags_prohibited/permutation.essence create mode 100755 tests/custom/permutations/22_tagged_ints/int/neg/0002_diff_tags_prohibited/run.sh create mode 100644 tests/custom/permutations/22_tagged_ints/int/neg/0002_diff_tags_prohibited/stderr.expected create mode 100644 tests/custom/permutations/22_tagged_ints/int/neg/0002_diff_tags_prohibited/stdout.expected create mode 100644 tests/custom/permutations/22_tagged_ints/int/neg/0003_const_tagged_works/permutation.essence create mode 100755 tests/custom/permutations/22_tagged_ints/int/neg/0003_const_tagged_works/run.sh create mode 100644 tests/custom/permutations/22_tagged_ints/int/neg/0003_const_tagged_works/stdout.expected create mode 100644 tests/custom/permutations/22_tagged_ints/int/pred/0002_diff_tags_prohibited/permutation.essence create mode 100755 tests/custom/permutations/22_tagged_ints/int/pred/0002_diff_tags_prohibited/run.sh create mode 100644 tests/custom/permutations/22_tagged_ints/int/pred/0002_diff_tags_prohibited/stderr.expected create mode 100644 tests/custom/permutations/22_tagged_ints/int/pred/0002_diff_tags_prohibited/stdout.expected create mode 100644 tests/custom/permutations/22_tagged_ints/int/pred/0003_const_tagged_works/permutation.essence create mode 100755 tests/custom/permutations/22_tagged_ints/int/pred/0003_const_tagged_works/run.sh create mode 100644 tests/custom/permutations/22_tagged_ints/int/pred/0003_const_tagged_works/stdout.expected create mode 100644 tests/custom/permutations/22_tagged_ints/int/prod/0001_same_tags_works/permutation.essence create mode 100755 tests/custom/permutations/22_tagged_ints/int/prod/0001_same_tags_works/run.sh create mode 100644 tests/custom/permutations/22_tagged_ints/int/prod/0001_same_tags_works/stdout.expected create mode 100644 tests/custom/permutations/22_tagged_ints/int/prod/0002_diff_tags_prohibited/permutation.essence create mode 100755 tests/custom/permutations/22_tagged_ints/int/prod/0002_diff_tags_prohibited/run.sh create mode 100644 tests/custom/permutations/22_tagged_ints/int/prod/0002_diff_tags_prohibited/stderr.expected create mode 100644 tests/custom/permutations/22_tagged_ints/int/prod/0002_diff_tags_prohibited/stdout.expected create mode 100644 tests/custom/permutations/22_tagged_ints/int/prod/0003_const_tagged_works/permutation.essence create mode 100755 tests/custom/permutations/22_tagged_ints/int/prod/0003_const_tagged_works/run.sh create mode 100644 tests/custom/permutations/22_tagged_ints/int/prod/0003_const_tagged_works/stdout.expected create mode 100644 tests/custom/permutations/22_tagged_ints/int/succ/0002_diff_tags_prohibited/permutation.essence create mode 100755 tests/custom/permutations/22_tagged_ints/int/succ/0002_diff_tags_prohibited/run.sh create mode 100644 tests/custom/permutations/22_tagged_ints/int/succ/0002_diff_tags_prohibited/stderr.expected create mode 100644 tests/custom/permutations/22_tagged_ints/int/succ/0002_diff_tags_prohibited/stdout.expected create mode 100644 tests/custom/permutations/22_tagged_ints/int/succ/0003_const_tagged_works/permutation.essence create mode 100755 tests/custom/permutations/22_tagged_ints/int/succ/0003_const_tagged_works/run.sh create mode 100644 tests/custom/permutations/22_tagged_ints/int/succ/0003_const_tagged_works/stdout.expected create mode 100644 tests/custom/permutations/22_tagged_ints/int/sum/0001_same_tags_works/permutation.essence create mode 100755 tests/custom/permutations/22_tagged_ints/int/sum/0001_same_tags_works/run.sh create mode 100644 tests/custom/permutations/22_tagged_ints/int/sum/0001_same_tags_works/stdout.expected create mode 100644 tests/custom/permutations/22_tagged_ints/int/sum/0002_diff_tags_prohibited/permutation.essence create mode 100755 tests/custom/permutations/22_tagged_ints/int/sum/0002_diff_tags_prohibited/run.sh create mode 100644 tests/custom/permutations/22_tagged_ints/int/sum/0002_diff_tags_prohibited/stderr.expected create mode 100644 tests/custom/permutations/22_tagged_ints/int/sum/0002_diff_tags_prohibited/stdout.expected create mode 100644 tests/custom/permutations/22_tagged_ints/int/sum/0003_const_tagged_works/permutation.essence create mode 100755 tests/custom/permutations/22_tagged_ints/int/sum/0003_const_tagged_works/run.sh create mode 100644 tests/custom/permutations/22_tagged_ints/int/sum/0003_const_tagged_works/stdout.expected create mode 100644 tests/custom/permutations/22_tagged_ints/runthese.sh delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_1_1-solution000001.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_1_1-solution000002.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_1_1-solution000003.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_1_1-solution000004.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_1_1-solution000005.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_1_1-solution000006.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_1_1-solution000007.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_1_1-solution000008.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_1_1-solution000009.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_1_1-solution000010.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_1_1-solution000011.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_1_1-solution000012.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_1_1-solution000013.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_1_1-solution000014.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_1_1-solution000015.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_1_1.eprime delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_1_2-solution000001.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_1_2-solution000002.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_1_2-solution000003.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_1_2-solution000004.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_1_2-solution000005.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_1_2-solution000006.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_1_2-solution000007.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_1_2-solution000008.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_1_2-solution000009.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_1_2-solution000010.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_1_2-solution000011.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_1_2-solution000012.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_1_2-solution000013.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_1_2-solution000014.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_1_2-solution000015.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_1_2.eprime delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_1_3-solution000001.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_1_3-solution000002.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_1_3-solution000003.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_1_3-solution000004.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_1_3-solution000005.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_1_3-solution000006.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_1_3-solution000007.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_1_3-solution000008.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_1_3-solution000009.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_1_3-solution000010.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_1_3-solution000011.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_1_3-solution000012.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_1_3-solution000013.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_1_3-solution000014.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_1_3-solution000015.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_1_3.eprime delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_1_4-solution000001.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_1_4-solution000002.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_1_4-solution000003.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_1_4-solution000004.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_1_4-solution000005.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_1_4-solution000006.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_1_4-solution000007.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_1_4-solution000008.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_1_4-solution000009.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_1_4-solution000010.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_1_4-solution000011.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_1_4-solution000012.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_1_4-solution000013.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_1_4-solution000014.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_1_4-solution000015.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_1_4.eprime delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_2_1-solution000001.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_2_1-solution000002.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_2_1-solution000003.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_2_1-solution000004.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_2_1-solution000005.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_2_1-solution000006.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_2_1-solution000007.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_2_1-solution000008.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_2_1-solution000009.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_2_1-solution000010.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_2_1-solution000011.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_2_1-solution000012.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_2_1-solution000013.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_2_1-solution000014.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_2_1-solution000015.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_2_1.eprime delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_2_2-solution000001.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_2_2-solution000002.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_2_2-solution000003.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_2_2-solution000004.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_2_2-solution000005.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_2_2-solution000006.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_2_2-solution000007.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_2_2-solution000008.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_2_2-solution000009.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_2_2-solution000010.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_2_2-solution000011.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_2_2-solution000012.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_2_2-solution000013.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_2_2-solution000014.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_2_2-solution000015.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_2_2.eprime delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_2_3-solution000001.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_2_3-solution000002.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_2_3-solution000003.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_2_3-solution000004.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_2_3-solution000005.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_2_3-solution000006.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_2_3-solution000007.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_2_3-solution000008.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_2_3-solution000009.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_2_3-solution000010.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_2_3-solution000011.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_2_3-solution000012.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_2_3-solution000013.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_2_3-solution000014.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_2_3-solution000015.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_2_3.eprime delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_2_4-solution000001.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_2_4-solution000002.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_2_4-solution000003.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_2_4-solution000004.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_2_4-solution000005.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_2_4-solution000006.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_2_4-solution000007.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_2_4-solution000008.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_2_4-solution000009.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_2_4-solution000010.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_2_4-solution000011.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_2_4-solution000012.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_2_4-solution000013.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_2_4-solution000014.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_2_4-solution000015.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_2_4.eprime delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_3_1-solution000001.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_3_1-solution000002.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_3_1-solution000003.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_3_1-solution000004.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_3_1-solution000005.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_3_1-solution000006.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_3_1-solution000007.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_3_1-solution000008.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_3_1-solution000009.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_3_1-solution000010.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_3_1-solution000011.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_3_1-solution000012.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_3_1-solution000013.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_3_1-solution000014.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_3_1-solution000015.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_3_1.eprime delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_3_2-solution000001.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_3_2-solution000002.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_3_2-solution000003.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_3_2-solution000004.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_3_2-solution000005.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_3_2-solution000006.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_3_2-solution000007.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_3_2-solution000008.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_3_2-solution000009.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_3_2-solution000010.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_3_2-solution000011.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_3_2-solution000012.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_3_2-solution000013.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_3_2-solution000014.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_3_2-solution000015.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_3_2.eprime delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_3_3-solution000001.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_3_3-solution000002.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_3_3-solution000003.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_3_3-solution000004.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_3_3-solution000005.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_3_3-solution000006.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_3_3-solution000007.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_3_3-solution000008.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_3_3-solution000009.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_3_3-solution000010.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_3_3-solution000011.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_3_3-solution000012.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_3_3-solution000013.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_3_3-solution000014.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_3_3-solution000015.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_3_3.eprime delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_3_4-solution000001.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_3_4-solution000002.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_3_4-solution000003.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_3_4-solution000004.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_3_4-solution000005.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_3_4-solution000006.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_3_4-solution000007.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_3_4-solution000008.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_3_4-solution000009.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_3_4-solution000010.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_3_4-solution000011.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_3_4-solution000012.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_3_4-solution000013.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_3_4-solution000014.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_3_4-solution000015.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_3_4.eprime delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_4_1-solution000001.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_4_1-solution000002.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_4_1-solution000003.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_4_1-solution000004.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_4_1-solution000005.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_4_1-solution000006.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_4_1-solution000007.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_4_1-solution000008.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_4_1-solution000009.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_4_1-solution000010.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_4_1-solution000011.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_4_1-solution000012.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_4_1-solution000013.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_4_1-solution000014.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_4_1-solution000015.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_4_1.eprime delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_4_2-solution000001.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_4_2-solution000002.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_4_2-solution000003.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_4_2-solution000004.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_4_2-solution000005.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_4_2-solution000006.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_4_2-solution000007.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_4_2-solution000008.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_4_2-solution000009.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_4_2-solution000010.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_4_2-solution000011.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_4_2-solution000012.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_4_2-solution000013.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_4_2-solution000014.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_4_2-solution000015.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_4_2.eprime delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_4_3-solution000001.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_4_3-solution000002.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_4_3-solution000003.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_4_3-solution000004.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_4_3-solution000005.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_4_3-solution000006.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_4_3-solution000007.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_4_3-solution000008.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_4_3-solution000009.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_4_3-solution000010.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_4_3-solution000011.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_4_3-solution000012.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_4_3-solution000013.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_4_3-solution000014.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_4_3-solution000015.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_4_3.eprime delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_4_4-solution000001.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_4_4-solution000002.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_4_4-solution000003.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_4_4-solution000004.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_4_4-solution000005.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_4_4-solution000006.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_4_4-solution000007.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_4_4-solution000008.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_4_4-solution000009.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_4_4-solution000010.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_4_4-solution000011.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_4_4-solution000012.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_4_4-solution000013.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_4_4-solution000014.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_4_4-solution000015.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_4_4.eprime delete mode 100644 tests/exhaustive/autogen/gen10/expected/model-solution000001.solution delete mode 100644 tests/exhaustive/autogen/gen10/expected/model-solution000002.solution delete mode 100644 tests/exhaustive/autogen/gen10/expected/model-solution000003.solution delete mode 100644 tests/exhaustive/autogen/gen10/expected/model-solution000004.solution delete mode 100644 tests/exhaustive/autogen/gen10/expected/model.eprime delete mode 100644 tests/exhaustive/autogen/gen14_1/expected/model_1-solution000001.solution delete mode 100644 tests/exhaustive/autogen/gen14_1/expected/model_1-solution000002.solution delete mode 100644 tests/exhaustive/autogen/gen14_1/expected/model_1.eprime delete mode 100644 tests/exhaustive/autogen/gen14_1/expected/model_2-solution000001.solution delete mode 100644 tests/exhaustive/autogen/gen14_1/expected/model_2-solution000002.solution delete mode 100644 tests/exhaustive/autogen/gen14_1/expected/model_2.eprime delete mode 100644 tests/exhaustive/autogen/gen14_1/expected/model_3-solution000001.solution delete mode 100644 tests/exhaustive/autogen/gen14_1/expected/model_3-solution000002.solution delete mode 100644 tests/exhaustive/autogen/gen14_1/expected/model_3.eprime delete mode 100644 tests/exhaustive/autogen/gen14_1/expected/model_4-solution000001.solution delete mode 100644 tests/exhaustive/autogen/gen14_1/expected/model_4-solution000002.solution delete mode 100644 tests/exhaustive/autogen/gen14_1/expected/model_4.eprime delete mode 100644 tests/exhaustive/autogen/gen14_2/expected/model_1-solution000001.solution delete mode 100644 tests/exhaustive/autogen/gen14_2/expected/model_1-solution000002.solution delete mode 100644 tests/exhaustive/autogen/gen14_2/expected/model_1.eprime delete mode 100644 tests/exhaustive/autogen/gen14_2/expected/model_2-solution000001.solution delete mode 100644 tests/exhaustive/autogen/gen14_2/expected/model_2-solution000002.solution delete mode 100644 tests/exhaustive/autogen/gen14_2/expected/model_2.eprime delete mode 100644 tests/exhaustive/autogen/gen14_2/expected/model_3-solution000001.solution delete mode 100644 tests/exhaustive/autogen/gen14_2/expected/model_3-solution000002.solution delete mode 100644 tests/exhaustive/autogen/gen14_2/expected/model_3.eprime delete mode 100644 tests/exhaustive/autogen/gen14_2/expected/model_4-solution000001.solution delete mode 100644 tests/exhaustive/autogen/gen14_2/expected/model_4-solution000002.solution delete mode 100644 tests/exhaustive/autogen/gen14_2/expected/model_4.eprime delete mode 100644 tests/exhaustive/autogen/gen32/expected/model_1_1_1.eprime delete mode 100644 tests/exhaustive/autogen/gen32/expected/model_1_1_2.eprime delete mode 100644 tests/exhaustive/autogen/gen32/expected/model_1_1_3.eprime delete mode 100644 tests/exhaustive/autogen/gen32/expected/model_1_1_4.eprime delete mode 100644 tests/exhaustive/autogen/gen32/expected/model_1_2_1.eprime delete mode 100644 tests/exhaustive/autogen/gen32/expected/model_1_2_2.eprime delete mode 100644 tests/exhaustive/autogen/gen32/expected/model_1_2_3.eprime delete mode 100644 tests/exhaustive/autogen/gen32/expected/model_1_2_4.eprime delete mode 100644 tests/exhaustive/autogen/gen32/expected/model_1_3_1.eprime delete mode 100644 tests/exhaustive/autogen/gen32/expected/model_1_3_2.eprime delete mode 100644 tests/exhaustive/autogen/gen32/expected/model_1_3_3.eprime delete mode 100644 tests/exhaustive/autogen/gen32/expected/model_1_3_4.eprime delete mode 100644 tests/exhaustive/autogen/gen32/expected/model_1_4_1.eprime delete mode 100644 tests/exhaustive/autogen/gen32/expected/model_1_4_2.eprime delete mode 100644 tests/exhaustive/autogen/gen32/expected/model_1_4_3.eprime delete mode 100644 tests/exhaustive/autogen/gen32/expected/model_1_4_4.eprime delete mode 100644 tests/exhaustive/autogen/gen32/expected/model_2_1_1.eprime delete mode 100644 tests/exhaustive/autogen/gen32/expected/model_2_1_2.eprime delete mode 100644 tests/exhaustive/autogen/gen32/expected/model_2_1_3.eprime delete mode 100644 tests/exhaustive/autogen/gen32/expected/model_2_1_4.eprime delete mode 100644 tests/exhaustive/autogen/gen32/expected/model_2_2_1.eprime delete mode 100644 tests/exhaustive/autogen/gen32/expected/model_2_2_2.eprime delete mode 100644 tests/exhaustive/autogen/gen32/expected/model_2_2_3.eprime delete mode 100644 tests/exhaustive/autogen/gen32/expected/model_2_2_4.eprime delete mode 100644 tests/exhaustive/autogen/gen32/expected/model_2_3_1.eprime delete mode 100644 tests/exhaustive/autogen/gen32/expected/model_2_3_2.eprime delete mode 100644 tests/exhaustive/autogen/gen32/expected/model_2_3_3.eprime delete mode 100644 tests/exhaustive/autogen/gen32/expected/model_2_3_4.eprime delete mode 100644 tests/exhaustive/autogen/gen32/expected/model_2_4_1.eprime delete mode 100644 tests/exhaustive/autogen/gen32/expected/model_2_4_2.eprime delete mode 100644 tests/exhaustive/autogen/gen32/expected/model_2_4_3.eprime delete mode 100644 tests/exhaustive/autogen/gen32/expected/model_2_4_4.eprime delete mode 100644 tests/exhaustive/autogen/gen32/expected/model_3_1_1.eprime delete mode 100644 tests/exhaustive/autogen/gen32/expected/model_3_1_2.eprime delete mode 100644 tests/exhaustive/autogen/gen32/expected/model_3_1_3.eprime delete mode 100644 tests/exhaustive/autogen/gen32/expected/model_3_1_4.eprime delete mode 100644 tests/exhaustive/autogen/gen32/expected/model_3_2_1.eprime delete mode 100644 tests/exhaustive/autogen/gen32/expected/model_3_2_2.eprime delete mode 100644 tests/exhaustive/autogen/gen32/expected/model_3_2_3.eprime delete mode 100644 tests/exhaustive/autogen/gen32/expected/model_3_2_4.eprime delete mode 100644 tests/exhaustive/autogen/gen32/expected/model_3_3_1.eprime delete mode 100644 tests/exhaustive/autogen/gen32/expected/model_3_3_2.eprime delete mode 100644 tests/exhaustive/autogen/gen32/expected/model_3_3_3.eprime delete mode 100644 tests/exhaustive/autogen/gen32/expected/model_3_3_4.eprime delete mode 100644 tests/exhaustive/autogen/gen32/expected/model_3_4_1.eprime delete mode 100644 tests/exhaustive/autogen/gen32/expected/model_3_4_2.eprime delete mode 100644 tests/exhaustive/autogen/gen32/expected/model_3_4_3.eprime delete mode 100644 tests/exhaustive/autogen/gen32/expected/model_3_4_4.eprime delete mode 100644 tests/exhaustive/autogen/gen32/expected/model_4_1_1.eprime delete mode 100644 tests/exhaustive/autogen/gen32/expected/model_4_1_2.eprime delete mode 100644 tests/exhaustive/autogen/gen32/expected/model_4_1_3.eprime delete mode 100644 tests/exhaustive/autogen/gen32/expected/model_4_1_4.eprime delete mode 100644 tests/exhaustive/autogen/gen32/expected/model_4_2_1.eprime delete mode 100644 tests/exhaustive/autogen/gen32/expected/model_4_2_2.eprime delete mode 100644 tests/exhaustive/autogen/gen32/expected/model_4_2_3.eprime delete mode 100644 tests/exhaustive/autogen/gen32/expected/model_4_2_4.eprime delete mode 100644 tests/exhaustive/autogen/gen32/expected/model_4_3_1.eprime delete mode 100644 tests/exhaustive/autogen/gen32/expected/model_4_3_2.eprime delete mode 100644 tests/exhaustive/autogen/gen32/expected/model_4_3_3.eprime delete mode 100644 tests/exhaustive/autogen/gen32/expected/model_4_3_4.eprime delete mode 100644 tests/exhaustive/autogen/gen32/expected/model_4_4_1.eprime delete mode 100644 tests/exhaustive/autogen/gen32/expected/model_4_4_2.eprime delete mode 100644 tests/exhaustive/autogen/gen32/expected/model_4_4_3.eprime delete mode 100644 tests/exhaustive/autogen/gen32/expected/model_4_4_4.eprime delete mode 100644 tests/exhaustive/autogen/gen36/expected/model_1-solution000001.solution delete mode 100644 tests/exhaustive/autogen/gen36/expected/model_1.eprime delete mode 100644 tests/exhaustive/autogen/gen36/expected/model_2-solution000001.solution delete mode 100644 tests/exhaustive/autogen/gen36/expected/model_2.eprime delete mode 100644 tests/exhaustive/autogen/gen36/expected/model_3-solution000001.solution delete mode 100644 tests/exhaustive/autogen/gen36/expected/model_3.eprime delete mode 100644 tests/exhaustive/autogen/gen36/expected/model_4-solution000001.solution delete mode 100644 tests/exhaustive/autogen/gen36/expected/model_4.eprime delete mode 100644 tests/exhaustive/autogen/gen36/expected/model_5-solution000001.solution delete mode 100644 tests/exhaustive/autogen/gen36/expected/model_5.eprime delete mode 100644 tests/exhaustive/autogen/gen36/expected/model_6-solution000001.solution delete mode 100644 tests/exhaustive/autogen/gen36/expected/model_6.eprime delete mode 100644 tests/exhaustive/basic/comprehension_04_2/expected/model-solution000001.solution delete mode 100644 tests/exhaustive/basic/comprehension_04_2/expected/model-solution000002.solution delete mode 100644 tests/exhaustive/basic/comprehension_04_2/expected/model-solution000003.solution delete mode 100644 tests/exhaustive/basic/comprehension_04_2/expected/model-solution000004.solution delete mode 100644 tests/exhaustive/basic/comprehension_04_2/expected/model.eprime delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_1_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_1_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_1_1-solution000003.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_1_1-solution000004.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_1_1-solution000005.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_1_1-solution000006.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_1_1-solution000007.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_1_1.eprime delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_1_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_1_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_1_2-solution000003.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_1_2-solution000004.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_1_2-solution000005.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_1_2-solution000006.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_1_2-solution000007.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_1_2.eprime delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_1_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_1_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_1_3-solution000003.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_1_3-solution000004.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_1_3-solution000005.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_1_3-solution000006.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_1_3-solution000007.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_1_3.eprime delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_1_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_1_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_1_4-solution000003.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_1_4-solution000004.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_1_4-solution000005.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_1_4-solution000006.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_1_4-solution000007.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_1_4.eprime delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_2_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_2_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_2_1-solution000003.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_2_1-solution000004.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_2_1-solution000005.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_2_1-solution000006.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_2_1-solution000007.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_2_1.eprime delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_2_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_2_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_2_2-solution000003.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_2_2-solution000004.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_2_2-solution000005.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_2_2-solution000006.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_2_2-solution000007.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_2_2.eprime delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_2_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_2_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_2_3-solution000003.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_2_3-solution000004.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_2_3-solution000005.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_2_3-solution000006.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_2_3-solution000007.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_2_3.eprime delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_2_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_2_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_2_4-solution000003.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_2_4-solution000004.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_2_4-solution000005.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_2_4-solution000006.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_2_4-solution000007.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_2_4.eprime delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_3_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_3_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_3_1-solution000003.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_3_1-solution000004.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_3_1-solution000005.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_3_1-solution000006.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_3_1-solution000007.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_3_1.eprime delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_3_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_3_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_3_2-solution000003.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_3_2-solution000004.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_3_2-solution000005.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_3_2-solution000006.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_3_2-solution000007.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_3_2.eprime delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_3_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_3_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_3_3-solution000003.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_3_3-solution000004.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_3_3-solution000005.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_3_3-solution000006.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_3_3-solution000007.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_3_3.eprime delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_3_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_3_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_3_4-solution000003.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_3_4-solution000004.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_3_4-solution000005.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_3_4-solution000006.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_3_4-solution000007.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_3_4.eprime delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_4_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_4_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_4_1-solution000003.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_4_1-solution000004.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_4_1-solution000005.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_4_1-solution000006.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_4_1-solution000007.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_4_1.eprime delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_4_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_4_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_4_2-solution000003.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_4_2-solution000004.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_4_2-solution000005.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_4_2-solution000006.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_4_2-solution000007.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_4_2.eprime delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_4_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_4_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_4_3-solution000003.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_4_3-solution000004.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_4_3-solution000005.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_4_3-solution000006.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_4_3-solution000007.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_4_3.eprime delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_4_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_4_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_4_4-solution000003.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_4_4-solution000004.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_4_4-solution000005.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_4_4-solution000006.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_4_4-solution000007.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_4_4.eprime delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_1_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_1_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_1_1-solution000003.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_1_1-solution000004.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_1_1-solution000005.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_1_1-solution000006.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_1_1-solution000007.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_1_1.eprime delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_1_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_1_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_1_2-solution000003.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_1_2-solution000004.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_1_2-solution000005.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_1_2-solution000006.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_1_2-solution000007.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_1_2.eprime delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_1_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_1_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_1_3-solution000003.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_1_3-solution000004.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_1_3-solution000005.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_1_3-solution000006.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_1_3-solution000007.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_1_3.eprime delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_1_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_1_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_1_4-solution000003.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_1_4-solution000004.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_1_4-solution000005.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_1_4-solution000006.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_1_4-solution000007.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_1_4.eprime delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_2_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_2_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_2_1-solution000003.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_2_1-solution000004.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_2_1-solution000005.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_2_1-solution000006.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_2_1-solution000007.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_2_1.eprime delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_2_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_2_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_2_2-solution000003.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_2_2-solution000004.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_2_2-solution000005.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_2_2-solution000006.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_2_2-solution000007.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_2_2.eprime delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_2_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_2_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_2_3-solution000003.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_2_3-solution000004.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_2_3-solution000005.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_2_3-solution000006.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_2_3-solution000007.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_2_3.eprime delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_2_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_2_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_2_4-solution000003.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_2_4-solution000004.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_2_4-solution000005.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_2_4-solution000006.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_2_4-solution000007.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_2_4.eprime delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_3_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_3_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_3_1-solution000003.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_3_1-solution000004.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_3_1-solution000005.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_3_1-solution000006.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_3_1-solution000007.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_3_1.eprime delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_3_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_3_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_3_2-solution000003.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_3_2-solution000004.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_3_2-solution000005.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_3_2-solution000006.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_3_2-solution000007.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_3_2.eprime delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_3_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_3_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_3_3-solution000003.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_3_3-solution000004.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_3_3-solution000005.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_3_3-solution000006.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_3_3-solution000007.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_3_3.eprime delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_3_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_3_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_3_4-solution000003.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_3_4-solution000004.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_3_4-solution000005.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_3_4-solution000006.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_3_4-solution000007.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_3_4.eprime delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_4_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_4_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_4_1-solution000003.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_4_1-solution000004.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_4_1-solution000005.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_4_1-solution000006.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_4_1-solution000007.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_4_1.eprime delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_4_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_4_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_4_2-solution000003.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_4_2-solution000004.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_4_2-solution000005.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_4_2-solution000006.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_4_2-solution000007.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_4_2.eprime delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_4_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_4_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_4_3-solution000003.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_4_3-solution000004.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_4_3-solution000005.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_4_3-solution000006.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_4_3-solution000007.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_4_3.eprime delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_4_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_4_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_4_4-solution000003.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_4_4-solution000004.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_4_4-solution000005.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_4_4-solution000006.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_4_4-solution000007.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_4_4.eprime delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_1_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_1_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_1_1-solution000003.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_1_1-solution000004.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_1_1-solution000005.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_1_1-solution000006.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_1_1-solution000007.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_1_1.eprime delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_1_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_1_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_1_2-solution000003.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_1_2-solution000004.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_1_2-solution000005.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_1_2-solution000006.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_1_2-solution000007.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_1_2.eprime delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_1_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_1_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_1_3-solution000003.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_1_3-solution000004.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_1_3-solution000005.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_1_3-solution000006.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_1_3-solution000007.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_1_3.eprime delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_1_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_1_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_1_4-solution000003.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_1_4-solution000004.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_1_4-solution000005.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_1_4-solution000006.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_1_4-solution000007.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_1_4.eprime delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_2_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_2_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_2_1-solution000003.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_2_1-solution000004.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_2_1-solution000005.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_2_1-solution000006.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_2_1-solution000007.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_2_1.eprime delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_2_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_2_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_2_2-solution000003.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_2_2-solution000004.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_2_2-solution000005.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_2_2-solution000006.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_2_2-solution000007.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_2_2.eprime delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_2_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_2_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_2_3-solution000003.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_2_3-solution000004.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_2_3-solution000005.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_2_3-solution000006.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_2_3-solution000007.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_2_3.eprime delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_2_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_2_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_2_4-solution000003.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_2_4-solution000004.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_2_4-solution000005.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_2_4-solution000006.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_2_4-solution000007.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_2_4.eprime delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_3_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_3_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_3_1-solution000003.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_3_1-solution000004.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_3_1-solution000005.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_3_1-solution000006.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_3_1-solution000007.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_3_1.eprime delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_3_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_3_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_3_2-solution000003.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_3_2-solution000004.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_3_2-solution000005.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_3_2-solution000006.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_3_2-solution000007.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_3_2.eprime delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_3_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_3_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_3_3-solution000003.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_3_3-solution000004.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_3_3-solution000005.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_3_3-solution000006.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_3_3-solution000007.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_3_3.eprime delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_3_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_3_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_3_4-solution000003.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_3_4-solution000004.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_3_4-solution000005.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_3_4-solution000006.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_3_4-solution000007.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_3_4.eprime delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_4_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_4_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_4_1-solution000003.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_4_1-solution000004.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_4_1-solution000005.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_4_1-solution000006.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_4_1-solution000007.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_4_1.eprime delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_4_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_4_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_4_2-solution000003.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_4_2-solution000004.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_4_2-solution000005.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_4_2-solution000006.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_4_2-solution000007.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_4_2.eprime delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_4_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_4_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_4_3-solution000003.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_4_3-solution000004.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_4_3-solution000005.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_4_3-solution000006.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_4_3-solution000007.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_4_3.eprime delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_4_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_4_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_4_4-solution000003.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_4_4-solution000004.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_4_4-solution000005.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_4_4-solution000006.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_4_4-solution000007.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_4_4.eprime delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_1_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_1_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_1_1-solution000003.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_1_1-solution000004.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_1_1-solution000005.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_1_1-solution000006.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_1_1-solution000007.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_1_1.eprime delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_1_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_1_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_1_2-solution000003.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_1_2-solution000004.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_1_2-solution000005.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_1_2-solution000006.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_1_2-solution000007.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_1_2.eprime delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_1_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_1_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_1_3-solution000003.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_1_3-solution000004.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_1_3-solution000005.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_1_3-solution000006.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_1_3-solution000007.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_1_3.eprime delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_1_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_1_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_1_4-solution000003.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_1_4-solution000004.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_1_4-solution000005.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_1_4-solution000006.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_1_4-solution000007.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_1_4.eprime delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_2_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_2_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_2_1-solution000003.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_2_1-solution000004.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_2_1-solution000005.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_2_1-solution000006.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_2_1-solution000007.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_2_1.eprime delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_2_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_2_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_2_2-solution000003.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_2_2-solution000004.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_2_2-solution000005.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_2_2-solution000006.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_2_2-solution000007.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_2_2.eprime delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_2_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_2_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_2_3-solution000003.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_2_3-solution000004.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_2_3-solution000005.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_2_3-solution000006.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_2_3-solution000007.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_2_3.eprime delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_2_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_2_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_2_4-solution000003.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_2_4-solution000004.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_2_4-solution000005.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_2_4-solution000006.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_2_4-solution000007.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_2_4.eprime delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_3_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_3_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_3_1-solution000003.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_3_1-solution000004.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_3_1-solution000005.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_3_1-solution000006.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_3_1-solution000007.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_3_1.eprime delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_3_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_3_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_3_2-solution000003.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_3_2-solution000004.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_3_2-solution000005.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_3_2-solution000006.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_3_2-solution000007.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_3_2.eprime delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_3_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_3_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_3_3-solution000003.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_3_3-solution000004.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_3_3-solution000005.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_3_3-solution000006.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_3_3-solution000007.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_3_3.eprime delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_3_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_3_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_3_4-solution000003.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_3_4-solution000004.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_3_4-solution000005.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_3_4-solution000006.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_3_4-solution000007.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_3_4.eprime delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_4_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_4_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_4_1-solution000003.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_4_1-solution000004.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_4_1-solution000005.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_4_1-solution000006.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_4_1-solution000007.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_4_1.eprime delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_4_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_4_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_4_2-solution000003.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_4_2-solution000004.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_4_2-solution000005.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_4_2-solution000006.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_4_2-solution000007.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_4_2.eprime delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_4_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_4_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_4_3-solution000003.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_4_3-solution000004.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_4_3-solution000005.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_4_3-solution000006.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_4_3-solution000007.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_4_3.eprime delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_4_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_4_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_4_4-solution000003.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_4_4-solution000004.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_4_4-solution000005.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_4_4-solution000006.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_4_4-solution000007.solution delete mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_4_4.eprime delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_1_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_1_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_1_1-solution000003.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_1_1-solution000004.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_1_1-solution000005.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_1_1-solution000006.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_1_1-solution000007.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_1_1-solution000008.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_1_1.eprime delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_1_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_1_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_1_2-solution000003.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_1_2-solution000004.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_1_2-solution000005.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_1_2-solution000006.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_1_2-solution000007.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_1_2-solution000008.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_1_2.eprime delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_1_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_1_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_1_3-solution000003.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_1_3-solution000004.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_1_3-solution000005.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_1_3-solution000006.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_1_3-solution000007.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_1_3-solution000008.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_1_3.eprime delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_1_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_1_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_1_4-solution000003.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_1_4-solution000004.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_1_4-solution000005.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_1_4-solution000006.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_1_4-solution000007.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_1_4-solution000008.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_1_4.eprime delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_2_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_2_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_2_1-solution000003.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_2_1-solution000004.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_2_1-solution000005.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_2_1-solution000006.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_2_1-solution000007.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_2_1-solution000008.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_2_1.eprime delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_2_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_2_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_2_2-solution000003.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_2_2-solution000004.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_2_2-solution000005.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_2_2-solution000006.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_2_2-solution000007.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_2_2-solution000008.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_2_2.eprime delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_2_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_2_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_2_3-solution000003.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_2_3-solution000004.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_2_3-solution000005.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_2_3-solution000006.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_2_3-solution000007.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_2_3-solution000008.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_2_3.eprime delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_2_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_2_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_2_4-solution000003.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_2_4-solution000004.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_2_4-solution000005.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_2_4-solution000006.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_2_4-solution000007.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_2_4-solution000008.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_2_4.eprime delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_3_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_3_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_3_1-solution000003.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_3_1-solution000004.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_3_1-solution000005.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_3_1-solution000006.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_3_1-solution000007.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_3_1-solution000008.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_3_1.eprime delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_3_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_3_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_3_2-solution000003.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_3_2-solution000004.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_3_2-solution000005.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_3_2-solution000006.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_3_2-solution000007.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_3_2-solution000008.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_3_2.eprime delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_3_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_3_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_3_3-solution000003.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_3_3-solution000004.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_3_3-solution000005.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_3_3-solution000006.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_3_3-solution000007.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_3_3-solution000008.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_3_3.eprime delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_3_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_3_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_3_4-solution000003.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_3_4-solution000004.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_3_4-solution000005.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_3_4-solution000006.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_3_4-solution000007.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_3_4-solution000008.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_3_4.eprime delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_4_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_4_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_4_1-solution000003.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_4_1-solution000004.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_4_1-solution000005.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_4_1-solution000006.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_4_1-solution000007.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_4_1-solution000008.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_4_1.eprime delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_4_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_4_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_4_2-solution000003.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_4_2-solution000004.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_4_2-solution000005.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_4_2-solution000006.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_4_2-solution000007.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_4_2-solution000008.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_4_2.eprime delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_4_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_4_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_4_3-solution000003.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_4_3-solution000004.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_4_3-solution000005.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_4_3-solution000006.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_4_3-solution000007.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_4_3-solution000008.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_4_3.eprime delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_4_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_4_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_4_4-solution000003.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_4_4-solution000004.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_4_4-solution000005.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_4_4-solution000006.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_4_4-solution000007.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_4_4-solution000008.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_4_4.eprime delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_1_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_1_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_1_1-solution000003.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_1_1-solution000004.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_1_1-solution000005.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_1_1-solution000006.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_1_1-solution000007.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_1_1-solution000008.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_1_1.eprime delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_1_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_1_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_1_2-solution000003.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_1_2-solution000004.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_1_2-solution000005.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_1_2-solution000006.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_1_2-solution000007.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_1_2-solution000008.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_1_2.eprime delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_1_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_1_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_1_3-solution000003.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_1_3-solution000004.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_1_3-solution000005.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_1_3-solution000006.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_1_3-solution000007.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_1_3-solution000008.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_1_3.eprime delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_1_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_1_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_1_4-solution000003.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_1_4-solution000004.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_1_4-solution000005.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_1_4-solution000006.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_1_4-solution000007.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_1_4-solution000008.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_1_4.eprime delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_2_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_2_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_2_1-solution000003.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_2_1-solution000004.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_2_1-solution000005.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_2_1-solution000006.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_2_1-solution000007.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_2_1-solution000008.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_2_1.eprime delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_2_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_2_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_2_2-solution000003.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_2_2-solution000004.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_2_2-solution000005.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_2_2-solution000006.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_2_2-solution000007.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_2_2-solution000008.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_2_2.eprime delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_2_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_2_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_2_3-solution000003.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_2_3-solution000004.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_2_3-solution000005.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_2_3-solution000006.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_2_3-solution000007.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_2_3-solution000008.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_2_3.eprime delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_2_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_2_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_2_4-solution000003.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_2_4-solution000004.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_2_4-solution000005.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_2_4-solution000006.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_2_4-solution000007.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_2_4-solution000008.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_2_4.eprime delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_3_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_3_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_3_1-solution000003.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_3_1-solution000004.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_3_1-solution000005.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_3_1-solution000006.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_3_1-solution000007.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_3_1-solution000008.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_3_1.eprime delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_3_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_3_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_3_2-solution000003.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_3_2-solution000004.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_3_2-solution000005.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_3_2-solution000006.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_3_2-solution000007.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_3_2-solution000008.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_3_2.eprime delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_3_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_3_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_3_3-solution000003.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_3_3-solution000004.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_3_3-solution000005.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_3_3-solution000006.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_3_3-solution000007.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_3_3-solution000008.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_3_3.eprime delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_3_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_3_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_3_4-solution000003.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_3_4-solution000004.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_3_4-solution000005.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_3_4-solution000006.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_3_4-solution000007.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_3_4-solution000008.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_3_4.eprime delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_4_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_4_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_4_1-solution000003.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_4_1-solution000004.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_4_1-solution000005.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_4_1-solution000006.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_4_1-solution000007.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_4_1-solution000008.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_4_1.eprime delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_4_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_4_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_4_2-solution000003.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_4_2-solution000004.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_4_2-solution000005.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_4_2-solution000006.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_4_2-solution000007.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_4_2-solution000008.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_4_2.eprime delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_4_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_4_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_4_3-solution000003.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_4_3-solution000004.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_4_3-solution000005.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_4_3-solution000006.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_4_3-solution000007.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_4_3-solution000008.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_4_3.eprime delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_4_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_4_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_4_4-solution000003.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_4_4-solution000004.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_4_4-solution000005.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_4_4-solution000006.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_4_4-solution000007.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_4_4-solution000008.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_4_4.eprime delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_1_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_1_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_1_1-solution000003.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_1_1-solution000004.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_1_1-solution000005.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_1_1-solution000006.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_1_1-solution000007.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_1_1-solution000008.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_1_1.eprime delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_1_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_1_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_1_2-solution000003.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_1_2-solution000004.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_1_2-solution000005.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_1_2-solution000006.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_1_2-solution000007.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_1_2-solution000008.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_1_2.eprime delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_1_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_1_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_1_3-solution000003.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_1_3-solution000004.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_1_3-solution000005.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_1_3-solution000006.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_1_3-solution000007.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_1_3-solution000008.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_1_3.eprime delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_1_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_1_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_1_4-solution000003.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_1_4-solution000004.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_1_4-solution000005.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_1_4-solution000006.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_1_4-solution000007.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_1_4-solution000008.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_1_4.eprime delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_2_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_2_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_2_1-solution000003.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_2_1-solution000004.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_2_1-solution000005.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_2_1-solution000006.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_2_1-solution000007.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_2_1-solution000008.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_2_1.eprime delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_2_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_2_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_2_2-solution000003.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_2_2-solution000004.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_2_2-solution000005.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_2_2-solution000006.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_2_2-solution000007.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_2_2-solution000008.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_2_2.eprime delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_2_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_2_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_2_3-solution000003.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_2_3-solution000004.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_2_3-solution000005.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_2_3-solution000006.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_2_3-solution000007.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_2_3-solution000008.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_2_3.eprime delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_2_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_2_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_2_4-solution000003.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_2_4-solution000004.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_2_4-solution000005.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_2_4-solution000006.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_2_4-solution000007.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_2_4-solution000008.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_2_4.eprime delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_3_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_3_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_3_1-solution000003.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_3_1-solution000004.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_3_1-solution000005.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_3_1-solution000006.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_3_1-solution000007.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_3_1-solution000008.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_3_1.eprime delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_3_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_3_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_3_2-solution000003.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_3_2-solution000004.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_3_2-solution000005.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_3_2-solution000006.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_3_2-solution000007.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_3_2-solution000008.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_3_2.eprime delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_3_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_3_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_3_3-solution000003.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_3_3-solution000004.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_3_3-solution000005.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_3_3-solution000006.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_3_3-solution000007.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_3_3-solution000008.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_3_3.eprime delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_3_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_3_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_3_4-solution000003.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_3_4-solution000004.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_3_4-solution000005.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_3_4-solution000006.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_3_4-solution000007.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_3_4-solution000008.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_3_4.eprime delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_4_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_4_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_4_1-solution000003.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_4_1-solution000004.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_4_1-solution000005.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_4_1-solution000006.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_4_1-solution000007.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_4_1-solution000008.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_4_1.eprime delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_4_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_4_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_4_2-solution000003.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_4_2-solution000004.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_4_2-solution000005.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_4_2-solution000006.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_4_2-solution000007.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_4_2-solution000008.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_4_2.eprime delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_4_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_4_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_4_3-solution000003.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_4_3-solution000004.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_4_3-solution000005.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_4_3-solution000006.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_4_3-solution000007.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_4_3-solution000008.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_4_3.eprime delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_4_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_4_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_4_4-solution000003.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_4_4-solution000004.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_4_4-solution000005.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_4_4-solution000006.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_4_4-solution000007.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_4_4-solution000008.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_4_4.eprime delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_1_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_1_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_1_1-solution000003.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_1_1-solution000004.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_1_1-solution000005.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_1_1-solution000006.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_1_1-solution000007.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_1_1-solution000008.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_1_1.eprime delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_1_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_1_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_1_2-solution000003.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_1_2-solution000004.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_1_2-solution000005.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_1_2-solution000006.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_1_2-solution000007.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_1_2-solution000008.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_1_2.eprime delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_1_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_1_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_1_3-solution000003.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_1_3-solution000004.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_1_3-solution000005.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_1_3-solution000006.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_1_3-solution000007.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_1_3-solution000008.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_1_3.eprime delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_1_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_1_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_1_4-solution000003.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_1_4-solution000004.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_1_4-solution000005.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_1_4-solution000006.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_1_4-solution000007.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_1_4-solution000008.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_1_4.eprime delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_2_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_2_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_2_1-solution000003.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_2_1-solution000004.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_2_1-solution000005.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_2_1-solution000006.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_2_1-solution000007.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_2_1-solution000008.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_2_1.eprime delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_2_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_2_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_2_2-solution000003.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_2_2-solution000004.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_2_2-solution000005.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_2_2-solution000006.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_2_2-solution000007.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_2_2-solution000008.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_2_2.eprime delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_2_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_2_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_2_3-solution000003.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_2_3-solution000004.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_2_3-solution000005.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_2_3-solution000006.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_2_3-solution000007.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_2_3-solution000008.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_2_3.eprime delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_2_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_2_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_2_4-solution000003.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_2_4-solution000004.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_2_4-solution000005.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_2_4-solution000006.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_2_4-solution000007.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_2_4-solution000008.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_2_4.eprime delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_3_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_3_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_3_1-solution000003.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_3_1-solution000004.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_3_1-solution000005.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_3_1-solution000006.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_3_1-solution000007.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_3_1-solution000008.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_3_1.eprime delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_3_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_3_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_3_2-solution000003.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_3_2-solution000004.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_3_2-solution000005.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_3_2-solution000006.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_3_2-solution000007.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_3_2-solution000008.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_3_2.eprime delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_3_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_3_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_3_3-solution000003.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_3_3-solution000004.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_3_3-solution000005.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_3_3-solution000006.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_3_3-solution000007.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_3_3-solution000008.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_3_3.eprime delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_3_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_3_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_3_4-solution000003.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_3_4-solution000004.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_3_4-solution000005.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_3_4-solution000006.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_3_4-solution000007.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_3_4-solution000008.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_3_4.eprime delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_4_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_4_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_4_1-solution000003.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_4_1-solution000004.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_4_1-solution000005.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_4_1-solution000006.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_4_1-solution000007.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_4_1-solution000008.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_4_1.eprime delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_4_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_4_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_4_2-solution000003.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_4_2-solution000004.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_4_2-solution000005.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_4_2-solution000006.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_4_2-solution000007.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_4_2-solution000008.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_4_2.eprime delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_4_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_4_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_4_3-solution000003.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_4_3-solution000004.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_4_3-solution000005.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_4_3-solution000006.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_4_3-solution000007.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_4_3-solution000008.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_4_3.eprime delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_4_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_4_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_4_4-solution000003.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_4_4-solution000004.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_4_4-solution000005.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_4_4-solution000006.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_4_4-solution000007.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_4_4-solution000008.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_4_4.eprime delete mode 100644 tests/exhaustive/basic/enum_functions/expected/model-p1-solution000001.solution delete mode 100644 tests/exhaustive/basic/enum_functions/expected/model-p1-solution000002.solution delete mode 100644 tests/exhaustive/basic/enum_functions/expected/model-p1-solution000003.solution delete mode 100644 tests/exhaustive/basic/enum_functions/expected/model-p1-solution000004.solution delete mode 100644 tests/exhaustive/basic/enum_functions/expected/model-p1-solution000005.solution delete mode 100644 tests/exhaustive/basic/enum_functions/expected/model-p1-solution000006.solution delete mode 100644 tests/exhaustive/basic/enum_functions/expected/model-p1-solution000007.solution delete mode 100644 tests/exhaustive/basic/enum_functions/expected/model-p1-solution000008.solution delete mode 100644 tests/exhaustive/basic/enum_functions/expected/model-p1-solution000009.solution delete mode 100644 tests/exhaustive/basic/enum_functions/expected/model-p1.eprime-param delete mode 100644 tests/exhaustive/basic/enum_functions/expected/model.eprime delete mode 100644 tests/exhaustive/basic/function_complex_01/expected/model_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/function_complex_01/expected/model_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/function_complex_01/expected/model_1-solution000003.solution delete mode 100644 tests/exhaustive/basic/function_complex_01/expected/model_1-solution000004.solution delete mode 100644 tests/exhaustive/basic/function_complex_01/expected/model_1-solution000005.solution delete mode 100644 tests/exhaustive/basic/function_complex_01/expected/model_1-solution000006.solution delete mode 100644 tests/exhaustive/basic/function_complex_01/expected/model_1.eprime delete mode 100644 tests/exhaustive/basic/function_complex_01/expected/model_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/function_complex_01/expected/model_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/function_complex_01/expected/model_2-solution000003.solution delete mode 100644 tests/exhaustive/basic/function_complex_01/expected/model_2-solution000004.solution delete mode 100644 tests/exhaustive/basic/function_complex_01/expected/model_2-solution000005.solution delete mode 100644 tests/exhaustive/basic/function_complex_01/expected/model_2-solution000006.solution delete mode 100644 tests/exhaustive/basic/function_complex_01/expected/model_2.eprime delete mode 100644 tests/exhaustive/basic/function_imageSet01/expected/model_1_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/function_imageSet01/expected/model_1_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/function_imageSet01/expected/model_1_1-solution000003.solution delete mode 100644 tests/exhaustive/basic/function_imageSet01/expected/model_1_1.eprime delete mode 100644 tests/exhaustive/basic/function_imageSet01/expected/model_1_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/function_imageSet01/expected/model_1_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/function_imageSet01/expected/model_1_2-solution000003.solution delete mode 100644 tests/exhaustive/basic/function_imageSet01/expected/model_1_2.eprime delete mode 100644 tests/exhaustive/basic/function_imageSet01/expected/model_1_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/function_imageSet01/expected/model_1_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/function_imageSet01/expected/model_1_3-solution000003.solution delete mode 100644 tests/exhaustive/basic/function_imageSet01/expected/model_1_3.eprime delete mode 100644 tests/exhaustive/basic/function_imageSet01/expected/model_1_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/function_imageSet01/expected/model_1_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/function_imageSet01/expected/model_1_4-solution000003.solution delete mode 100644 tests/exhaustive/basic/function_imageSet01/expected/model_1_4.eprime delete mode 100644 tests/exhaustive/basic/function_imageSet01/expected/model_2_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/function_imageSet01/expected/model_2_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/function_imageSet01/expected/model_2_1-solution000003.solution delete mode 100644 tests/exhaustive/basic/function_imageSet01/expected/model_2_1.eprime delete mode 100644 tests/exhaustive/basic/function_imageSet01/expected/model_2_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/function_imageSet01/expected/model_2_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/function_imageSet01/expected/model_2_2-solution000003.solution delete mode 100644 tests/exhaustive/basic/function_imageSet01/expected/model_2_2.eprime delete mode 100644 tests/exhaustive/basic/function_imageSet01/expected/model_2_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/function_imageSet01/expected/model_2_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/function_imageSet01/expected/model_2_3-solution000003.solution delete mode 100644 tests/exhaustive/basic/function_imageSet01/expected/model_2_3.eprime delete mode 100644 tests/exhaustive/basic/function_imageSet01/expected/model_2_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/function_imageSet01/expected/model_2_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/function_imageSet01/expected/model_2_4-solution000003.solution delete mode 100644 tests/exhaustive/basic/function_imageSet01/expected/model_2_4.eprime delete mode 100644 tests/exhaustive/basic/function_imageSet01/expected/model_3_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/function_imageSet01/expected/model_3_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/function_imageSet01/expected/model_3_1-solution000003.solution delete mode 100644 tests/exhaustive/basic/function_imageSet01/expected/model_3_1.eprime delete mode 100644 tests/exhaustive/basic/function_imageSet01/expected/model_3_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/function_imageSet01/expected/model_3_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/function_imageSet01/expected/model_3_2-solution000003.solution delete mode 100644 tests/exhaustive/basic/function_imageSet01/expected/model_3_2.eprime delete mode 100644 tests/exhaustive/basic/function_imageSet01/expected/model_3_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/function_imageSet01/expected/model_3_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/function_imageSet01/expected/model_3_3-solution000003.solution delete mode 100644 tests/exhaustive/basic/function_imageSet01/expected/model_3_3.eprime delete mode 100644 tests/exhaustive/basic/function_imageSet01/expected/model_3_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/function_imageSet01/expected/model_3_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/function_imageSet01/expected/model_3_4-solution000003.solution delete mode 100644 tests/exhaustive/basic/function_imageSet01/expected/model_3_4.eprime delete mode 100644 tests/exhaustive/basic/function_imageSet01/expected/model_4_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/function_imageSet01/expected/model_4_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/function_imageSet01/expected/model_4_1-solution000003.solution delete mode 100644 tests/exhaustive/basic/function_imageSet01/expected/model_4_1.eprime delete mode 100644 tests/exhaustive/basic/function_imageSet01/expected/model_4_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/function_imageSet01/expected/model_4_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/function_imageSet01/expected/model_4_2-solution000003.solution delete mode 100644 tests/exhaustive/basic/function_imageSet01/expected/model_4_2.eprime delete mode 100644 tests/exhaustive/basic/function_imageSet01/expected/model_4_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/function_imageSet01/expected/model_4_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/function_imageSet01/expected/model_4_3-solution000003.solution delete mode 100644 tests/exhaustive/basic/function_imageSet01/expected/model_4_3.eprime delete mode 100644 tests/exhaustive/basic/function_imageSet01/expected/model_4_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/function_imageSet01/expected/model_4_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/function_imageSet01/expected/model_4_4-solution000003.solution delete mode 100644 tests/exhaustive/basic/function_imageSet01/expected/model_4_4.eprime delete mode 100644 tests/exhaustive/basic/function_range/expected/model-solution000001.solution delete mode 100644 tests/exhaustive/basic/function_range/expected/model-solution000002.solution delete mode 100644 tests/exhaustive/basic/function_range/expected/model-solution000003.solution delete mode 100644 tests/exhaustive/basic/function_range/expected/model-solution000004.solution delete mode 100644 tests/exhaustive/basic/function_range/expected/model-solution000005.solution delete mode 100644 tests/exhaustive/basic/function_range/expected/model-solution000006.solution delete mode 100644 tests/exhaustive/basic/function_range/expected/model-solution000007.solution delete mode 100644 tests/exhaustive/basic/function_range/expected/model-solution000008.solution delete mode 100644 tests/exhaustive/basic/function_range/expected/model-solution000009.solution delete mode 100644 tests/exhaustive/basic/function_range/expected/model-solution000010.solution delete mode 100644 tests/exhaustive/basic/function_range/expected/model-solution000011.solution delete mode 100644 tests/exhaustive/basic/function_range/expected/model-solution000012.solution delete mode 100644 tests/exhaustive/basic/function_range/expected/model.eprime delete mode 100644 tests/exhaustive/basic/matrix_of_set_02/expected/model_1_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/matrix_of_set_02/expected/model_1_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/matrix_of_set_02/expected/model_1_1-solution000003.solution delete mode 100644 tests/exhaustive/basic/matrix_of_set_02/expected/model_1_1-solution000004.solution delete mode 100644 tests/exhaustive/basic/matrix_of_set_02/expected/model_1_1.eprime delete mode 100644 tests/exhaustive/basic/matrix_of_set_02/expected/model_1_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/matrix_of_set_02/expected/model_1_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/matrix_of_set_02/expected/model_1_2-solution000003.solution delete mode 100644 tests/exhaustive/basic/matrix_of_set_02/expected/model_1_2-solution000004.solution delete mode 100644 tests/exhaustive/basic/matrix_of_set_02/expected/model_1_2.eprime delete mode 100644 tests/exhaustive/basic/matrix_of_set_02/expected/model_1_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/matrix_of_set_02/expected/model_1_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/matrix_of_set_02/expected/model_1_3-solution000003.solution delete mode 100644 tests/exhaustive/basic/matrix_of_set_02/expected/model_1_3-solution000004.solution delete mode 100644 tests/exhaustive/basic/matrix_of_set_02/expected/model_1_3.eprime delete mode 100644 tests/exhaustive/basic/matrix_of_set_02/expected/model_1_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/matrix_of_set_02/expected/model_1_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/matrix_of_set_02/expected/model_1_4-solution000003.solution delete mode 100644 tests/exhaustive/basic/matrix_of_set_02/expected/model_1_4-solution000004.solution delete mode 100644 tests/exhaustive/basic/matrix_of_set_02/expected/model_1_4.eprime delete mode 100644 tests/exhaustive/basic/matrix_of_set_02/expected/model_2_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/matrix_of_set_02/expected/model_2_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/matrix_of_set_02/expected/model_2_1-solution000003.solution delete mode 100644 tests/exhaustive/basic/matrix_of_set_02/expected/model_2_1-solution000004.solution delete mode 100644 tests/exhaustive/basic/matrix_of_set_02/expected/model_2_1.eprime delete mode 100644 tests/exhaustive/basic/matrix_of_set_02/expected/model_2_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/matrix_of_set_02/expected/model_2_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/matrix_of_set_02/expected/model_2_2-solution000003.solution delete mode 100644 tests/exhaustive/basic/matrix_of_set_02/expected/model_2_2-solution000004.solution delete mode 100644 tests/exhaustive/basic/matrix_of_set_02/expected/model_2_2.eprime delete mode 100644 tests/exhaustive/basic/matrix_of_set_02/expected/model_2_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/matrix_of_set_02/expected/model_2_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/matrix_of_set_02/expected/model_2_3-solution000003.solution delete mode 100644 tests/exhaustive/basic/matrix_of_set_02/expected/model_2_3-solution000004.solution delete mode 100644 tests/exhaustive/basic/matrix_of_set_02/expected/model_2_3.eprime delete mode 100644 tests/exhaustive/basic/matrix_of_set_02/expected/model_2_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/matrix_of_set_02/expected/model_2_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/matrix_of_set_02/expected/model_2_4-solution000003.solution delete mode 100644 tests/exhaustive/basic/matrix_of_set_02/expected/model_2_4-solution000004.solution delete mode 100644 tests/exhaustive/basic/matrix_of_set_02/expected/model_2_4.eprime delete mode 100644 tests/exhaustive/basic/matrix_of_set_02/expected/model_3_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/matrix_of_set_02/expected/model_3_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/matrix_of_set_02/expected/model_3_1-solution000003.solution delete mode 100644 tests/exhaustive/basic/matrix_of_set_02/expected/model_3_1-solution000004.solution delete mode 100644 tests/exhaustive/basic/matrix_of_set_02/expected/model_3_1.eprime delete mode 100644 tests/exhaustive/basic/matrix_of_set_02/expected/model_3_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/matrix_of_set_02/expected/model_3_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/matrix_of_set_02/expected/model_3_2-solution000003.solution delete mode 100644 tests/exhaustive/basic/matrix_of_set_02/expected/model_3_2-solution000004.solution delete mode 100644 tests/exhaustive/basic/matrix_of_set_02/expected/model_3_2.eprime delete mode 100644 tests/exhaustive/basic/matrix_of_set_02/expected/model_3_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/matrix_of_set_02/expected/model_3_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/matrix_of_set_02/expected/model_3_3-solution000003.solution delete mode 100644 tests/exhaustive/basic/matrix_of_set_02/expected/model_3_3-solution000004.solution delete mode 100644 tests/exhaustive/basic/matrix_of_set_02/expected/model_3_3.eprime delete mode 100644 tests/exhaustive/basic/matrix_of_set_02/expected/model_3_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/matrix_of_set_02/expected/model_3_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/matrix_of_set_02/expected/model_3_4-solution000003.solution delete mode 100644 tests/exhaustive/basic/matrix_of_set_02/expected/model_3_4-solution000004.solution delete mode 100644 tests/exhaustive/basic/matrix_of_set_02/expected/model_3_4.eprime delete mode 100644 tests/exhaustive/basic/matrix_of_set_02/expected/model_4_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/matrix_of_set_02/expected/model_4_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/matrix_of_set_02/expected/model_4_1-solution000003.solution delete mode 100644 tests/exhaustive/basic/matrix_of_set_02/expected/model_4_1-solution000004.solution delete mode 100644 tests/exhaustive/basic/matrix_of_set_02/expected/model_4_1.eprime delete mode 100644 tests/exhaustive/basic/matrix_of_set_02/expected/model_4_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/matrix_of_set_02/expected/model_4_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/matrix_of_set_02/expected/model_4_2-solution000003.solution delete mode 100644 tests/exhaustive/basic/matrix_of_set_02/expected/model_4_2-solution000004.solution delete mode 100644 tests/exhaustive/basic/matrix_of_set_02/expected/model_4_2.eprime delete mode 100644 tests/exhaustive/basic/matrix_of_set_02/expected/model_4_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/matrix_of_set_02/expected/model_4_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/matrix_of_set_02/expected/model_4_3-solution000003.solution delete mode 100644 tests/exhaustive/basic/matrix_of_set_02/expected/model_4_3-solution000004.solution delete mode 100644 tests/exhaustive/basic/matrix_of_set_02/expected/model_4_3.eprime delete mode 100644 tests/exhaustive/basic/matrix_of_set_02/expected/model_4_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/matrix_of_set_02/expected/model_4_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/matrix_of_set_02/expected/model_4_4-solution000003.solution delete mode 100644 tests/exhaustive/basic/matrix_of_set_02/expected/model_4_4-solution000004.solution delete mode 100644 tests/exhaustive/basic/matrix_of_set_02/expected/model_4_4.eprime delete mode 100644 tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_1_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_1_1.eprime delete mode 100644 tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_1_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_1_2.eprime delete mode 100644 tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_1_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_1_3.eprime delete mode 100644 tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_1_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_1_4.eprime delete mode 100644 tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_2_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_2_1.eprime delete mode 100644 tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_2_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_2_2.eprime delete mode 100644 tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_2_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_2_3.eprime delete mode 100644 tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_2_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_2_4.eprime delete mode 100644 tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_3_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_3_1.eprime delete mode 100644 tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_3_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_3_2.eprime delete mode 100644 tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_3_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_3_3.eprime delete mode 100644 tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_3_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_3_4.eprime delete mode 100644 tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_4_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_4_1.eprime delete mode 100644 tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_4_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_4_2.eprime delete mode 100644 tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_4_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_4_3.eprime delete mode 100644 tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_4_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_4_4.eprime delete mode 100644 tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_1_1_1_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_1_1_1_1.eprime delete mode 100644 tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_1_1_1_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_1_1_1_2.eprime delete mode 100644 tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_1_1_2_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_1_1_2_1.eprime delete mode 100644 tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_1_1_2_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_1_1_2_2.eprime delete mode 100644 tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_1_2_1_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_1_2_1_1.eprime delete mode 100644 tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_1_2_1_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_1_2_1_2.eprime delete mode 100644 tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_1_2_2_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_1_2_2_1.eprime delete mode 100644 tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_1_2_2_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_1_2_2_2.eprime delete mode 100644 tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_2_1_1_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_2_1_1_1.eprime delete mode 100644 tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_2_1_1_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_2_1_1_2.eprime delete mode 100644 tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_2_1_2_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_2_1_2_1.eprime delete mode 100644 tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_2_1_2_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_2_1_2_2.eprime delete mode 100644 tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_2_2_1_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_2_2_1_1.eprime delete mode 100644 tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_2_2_1_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_2_2_1_2.eprime delete mode 100644 tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_2_2_2_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_2_2_2_1.eprime delete mode 100644 tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_2_2_2_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_2_2_2_2.eprime delete mode 100644 tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_1_1_1_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_1_1_1_1.eprime delete mode 100644 tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_1_1_1_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_1_1_1_2.eprime delete mode 100644 tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_1_1_2_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_1_1_2_1.eprime delete mode 100644 tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_1_1_2_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_1_1_2_2.eprime delete mode 100644 tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_1_2_1_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_1_2_1_1.eprime delete mode 100644 tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_1_2_1_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_1_2_1_2.eprime delete mode 100644 tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_1_2_2_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_1_2_2_1.eprime delete mode 100644 tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_1_2_2_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_1_2_2_2.eprime delete mode 100644 tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_2_1_1_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_2_1_1_1.eprime delete mode 100644 tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_2_1_1_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_2_1_1_2.eprime delete mode 100644 tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_2_1_2_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_2_1_2_1.eprime delete mode 100644 tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_2_1_2_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_2_1_2_2.eprime delete mode 100644 tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_2_2_1_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_2_2_1_1.eprime delete mode 100644 tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_2_2_1_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_2_2_1_2.eprime delete mode 100644 tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_2_2_2_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_2_2_2_1.eprime delete mode 100644 tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_2_2_2_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_2_2_2_2.eprime delete mode 100644 tests/exhaustive/basic/mset01_param/expected/model_1_1-param1-solution000001.solution delete mode 100644 tests/exhaustive/basic/mset01_param/expected/model_1_1-param1.eprime-param delete mode 100644 tests/exhaustive/basic/mset01_param/expected/model_1_1-param4-solution000001.solution delete mode 100644 tests/exhaustive/basic/mset01_param/expected/model_1_1-param4.eprime-param delete mode 100644 tests/exhaustive/basic/mset01_param/expected/model_1_1-param7-solution000001.solution delete mode 100644 tests/exhaustive/basic/mset01_param/expected/model_1_1-param7.eprime-param delete mode 100644 tests/exhaustive/basic/mset01_param/expected/model_1_1.eprime delete mode 100644 tests/exhaustive/basic/mset01_param/expected/model_1_2-param1-solution000001.solution delete mode 100644 tests/exhaustive/basic/mset01_param/expected/model_1_2-param1.eprime-param delete mode 100644 tests/exhaustive/basic/mset01_param/expected/model_1_2-param4-solution000001.solution delete mode 100644 tests/exhaustive/basic/mset01_param/expected/model_1_2-param4.eprime-param delete mode 100644 tests/exhaustive/basic/mset01_param/expected/model_1_2-param7-solution000001.solution delete mode 100644 tests/exhaustive/basic/mset01_param/expected/model_1_2-param7.eprime-param delete mode 100644 tests/exhaustive/basic/mset01_param/expected/model_1_2.eprime delete mode 100644 tests/exhaustive/basic/mset01_param/expected/model_1_3-param1-solution000001.solution delete mode 100644 tests/exhaustive/basic/mset01_param/expected/model_1_3-param1.eprime-param delete mode 100644 tests/exhaustive/basic/mset01_param/expected/model_1_3-param4-solution000001.solution delete mode 100644 tests/exhaustive/basic/mset01_param/expected/model_1_3-param4.eprime-param delete mode 100644 tests/exhaustive/basic/mset01_param/expected/model_1_3-param7-solution000001.solution delete mode 100644 tests/exhaustive/basic/mset01_param/expected/model_1_3-param7.eprime-param delete mode 100644 tests/exhaustive/basic/mset01_param/expected/model_1_3.eprime delete mode 100644 tests/exhaustive/basic/mset01_param/expected/model_2_1-param1-solution000001.solution delete mode 100644 tests/exhaustive/basic/mset01_param/expected/model_2_1-param1.eprime-param delete mode 100644 tests/exhaustive/basic/mset01_param/expected/model_2_1-param4-solution000001.solution delete mode 100644 tests/exhaustive/basic/mset01_param/expected/model_2_1-param4.eprime-param delete mode 100644 tests/exhaustive/basic/mset01_param/expected/model_2_1-param7-solution000001.solution delete mode 100644 tests/exhaustive/basic/mset01_param/expected/model_2_1-param7.eprime-param delete mode 100644 tests/exhaustive/basic/mset01_param/expected/model_2_1.eprime delete mode 100644 tests/exhaustive/basic/mset01_param/expected/model_2_2-param1-solution000001.solution delete mode 100644 tests/exhaustive/basic/mset01_param/expected/model_2_2-param1.eprime-param delete mode 100644 tests/exhaustive/basic/mset01_param/expected/model_2_2-param4-solution000001.solution delete mode 100644 tests/exhaustive/basic/mset01_param/expected/model_2_2-param4.eprime-param delete mode 100644 tests/exhaustive/basic/mset01_param/expected/model_2_2-param7-solution000001.solution delete mode 100644 tests/exhaustive/basic/mset01_param/expected/model_2_2-param7.eprime-param delete mode 100644 tests/exhaustive/basic/mset01_param/expected/model_2_2.eprime delete mode 100644 tests/exhaustive/basic/mset01_param/expected/model_2_3-param1-solution000001.solution delete mode 100644 tests/exhaustive/basic/mset01_param/expected/model_2_3-param1.eprime-param delete mode 100644 tests/exhaustive/basic/mset01_param/expected/model_2_3-param4-solution000001.solution delete mode 100644 tests/exhaustive/basic/mset01_param/expected/model_2_3-param4.eprime-param delete mode 100644 tests/exhaustive/basic/mset01_param/expected/model_2_3-param7-solution000001.solution delete mode 100644 tests/exhaustive/basic/mset01_param/expected/model_2_3-param7.eprime-param delete mode 100644 tests/exhaustive/basic/mset01_param/expected/model_2_3.eprime delete mode 100644 tests/exhaustive/basic/mset01_param/expected/model_3_1-param1-solution000001.solution delete mode 100644 tests/exhaustive/basic/mset01_param/expected/model_3_1-param1.eprime-param delete mode 100644 tests/exhaustive/basic/mset01_param/expected/model_3_1-param4-solution000001.solution delete mode 100644 tests/exhaustive/basic/mset01_param/expected/model_3_1-param4.eprime-param delete mode 100644 tests/exhaustive/basic/mset01_param/expected/model_3_1-param7-solution000001.solution delete mode 100644 tests/exhaustive/basic/mset01_param/expected/model_3_1-param7.eprime-param delete mode 100644 tests/exhaustive/basic/mset01_param/expected/model_3_1.eprime delete mode 100644 tests/exhaustive/basic/mset01_param/expected/model_3_2-param1-solution000001.solution delete mode 100644 tests/exhaustive/basic/mset01_param/expected/model_3_2-param1.eprime-param delete mode 100644 tests/exhaustive/basic/mset01_param/expected/model_3_2-param4-solution000001.solution delete mode 100644 tests/exhaustive/basic/mset01_param/expected/model_3_2-param4.eprime-param delete mode 100644 tests/exhaustive/basic/mset01_param/expected/model_3_2-param7-solution000001.solution delete mode 100644 tests/exhaustive/basic/mset01_param/expected/model_3_2-param7.eprime-param delete mode 100644 tests/exhaustive/basic/mset01_param/expected/model_3_2.eprime delete mode 100644 tests/exhaustive/basic/mset01_param/expected/model_3_3-param1-solution000001.solution delete mode 100644 tests/exhaustive/basic/mset01_param/expected/model_3_3-param1.eprime-param delete mode 100644 tests/exhaustive/basic/mset01_param/expected/model_3_3-param4-solution000001.solution delete mode 100644 tests/exhaustive/basic/mset01_param/expected/model_3_3-param4.eprime-param delete mode 100644 tests/exhaustive/basic/mset01_param/expected/model_3_3-param7-solution000001.solution delete mode 100644 tests/exhaustive/basic/mset01_param/expected/model_3_3-param7.eprime-param delete mode 100644 tests/exhaustive/basic/mset01_param/expected/model_3_3.eprime delete mode 100644 tests/exhaustive/basic/name-reuse/expected/model_1_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/name-reuse/expected/model_1_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/name-reuse/expected/model_1_1.eprime delete mode 100644 tests/exhaustive/basic/name-reuse/expected/model_1_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/name-reuse/expected/model_1_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/name-reuse/expected/model_1_2.eprime delete mode 100644 tests/exhaustive/basic/name-reuse/expected/model_1_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/name-reuse/expected/model_1_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/name-reuse/expected/model_1_3.eprime delete mode 100644 tests/exhaustive/basic/name-reuse/expected/model_1_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/name-reuse/expected/model_1_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/name-reuse/expected/model_1_4.eprime delete mode 100644 tests/exhaustive/basic/name-reuse/expected/model_2_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/name-reuse/expected/model_2_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/name-reuse/expected/model_2_1.eprime delete mode 100644 tests/exhaustive/basic/name-reuse/expected/model_2_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/name-reuse/expected/model_2_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/name-reuse/expected/model_2_2.eprime delete mode 100644 tests/exhaustive/basic/name-reuse/expected/model_2_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/name-reuse/expected/model_2_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/name-reuse/expected/model_2_3.eprime delete mode 100644 tests/exhaustive/basic/name-reuse/expected/model_2_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/name-reuse/expected/model_2_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/name-reuse/expected/model_2_4.eprime delete mode 100644 tests/exhaustive/basic/name-reuse/expected/model_3_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/name-reuse/expected/model_3_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/name-reuse/expected/model_3_1.eprime delete mode 100644 tests/exhaustive/basic/name-reuse/expected/model_3_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/name-reuse/expected/model_3_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/name-reuse/expected/model_3_2.eprime delete mode 100644 tests/exhaustive/basic/name-reuse/expected/model_3_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/name-reuse/expected/model_3_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/name-reuse/expected/model_3_3.eprime delete mode 100644 tests/exhaustive/basic/name-reuse/expected/model_3_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/name-reuse/expected/model_3_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/name-reuse/expected/model_3_4.eprime delete mode 100644 tests/exhaustive/basic/name-reuse/expected/model_4_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/name-reuse/expected/model_4_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/name-reuse/expected/model_4_1.eprime delete mode 100644 tests/exhaustive/basic/name-reuse/expected/model_4_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/name-reuse/expected/model_4_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/name-reuse/expected/model_4_2.eprime delete mode 100644 tests/exhaustive/basic/name-reuse/expected/model_4_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/name-reuse/expected/model_4_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/name-reuse/expected/model_4_3.eprime delete mode 100644 tests/exhaustive/basic/name-reuse/expected/model_4_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/name-reuse/expected/model_4_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/name-reuse/expected/model_4_4.eprime delete mode 100644 tests/exhaustive/basic/partition_05_1/expected/model_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/partition_05_1/expected/model_1.eprime delete mode 100644 tests/exhaustive/basic/partition_05_1/expected/model_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/partition_05_1/expected/model_2.eprime delete mode 100644 tests/exhaustive/basic/partition_05_1/expected/model_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/partition_05_1/expected/model_3.eprime delete mode 100644 tests/exhaustive/basic/partition_05_1/expected/model_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/partition_05_1/expected/model_4.eprime delete mode 100644 tests/exhaustive/basic/partition_05_2/expected/model_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/partition_05_2/expected/model_1.eprime delete mode 100644 tests/exhaustive/basic/partition_05_2/expected/model_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/partition_05_2/expected/model_2.eprime delete mode 100644 tests/exhaustive/basic/partition_05_2/expected/model_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/partition_05_2/expected/model_3.eprime delete mode 100644 tests/exhaustive/basic/partition_05_2/expected/model_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/partition_05_2/expected/model_4.eprime delete mode 100644 tests/exhaustive/basic/partition_06/expected/model_1_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/partition_06/expected/model_1_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/partition_06/expected/model_1_1-solution000003.solution delete mode 100644 tests/exhaustive/basic/partition_06/expected/model_1_1.eprime delete mode 100644 tests/exhaustive/basic/partition_06/expected/model_1_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/partition_06/expected/model_1_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/partition_06/expected/model_1_2-solution000003.solution delete mode 100644 tests/exhaustive/basic/partition_06/expected/model_1_2.eprime delete mode 100644 tests/exhaustive/basic/partition_06/expected/model_1_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/partition_06/expected/model_1_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/partition_06/expected/model_1_3-solution000003.solution delete mode 100644 tests/exhaustive/basic/partition_06/expected/model_1_3.eprime delete mode 100644 tests/exhaustive/basic/partition_06/expected/model_1_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/partition_06/expected/model_1_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/partition_06/expected/model_1_4-solution000003.solution delete mode 100644 tests/exhaustive/basic/partition_06/expected/model_1_4.eprime delete mode 100644 tests/exhaustive/basic/partition_06/expected/model_2_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/partition_06/expected/model_2_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/partition_06/expected/model_2_1-solution000003.solution delete mode 100644 tests/exhaustive/basic/partition_06/expected/model_2_1.eprime delete mode 100644 tests/exhaustive/basic/partition_06/expected/model_2_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/partition_06/expected/model_2_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/partition_06/expected/model_2_2-solution000003.solution delete mode 100644 tests/exhaustive/basic/partition_06/expected/model_2_2.eprime delete mode 100644 tests/exhaustive/basic/partition_06/expected/model_2_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/partition_06/expected/model_2_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/partition_06/expected/model_2_3-solution000003.solution delete mode 100644 tests/exhaustive/basic/partition_06/expected/model_2_3.eprime delete mode 100644 tests/exhaustive/basic/partition_06/expected/model_2_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/partition_06/expected/model_2_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/partition_06/expected/model_2_4-solution000003.solution delete mode 100644 tests/exhaustive/basic/partition_06/expected/model_2_4.eprime delete mode 100644 tests/exhaustive/basic/partition_06/expected/model_3_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/partition_06/expected/model_3_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/partition_06/expected/model_3_1-solution000003.solution delete mode 100644 tests/exhaustive/basic/partition_06/expected/model_3_1.eprime delete mode 100644 tests/exhaustive/basic/partition_06/expected/model_3_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/partition_06/expected/model_3_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/partition_06/expected/model_3_2-solution000003.solution delete mode 100644 tests/exhaustive/basic/partition_06/expected/model_3_2.eprime delete mode 100644 tests/exhaustive/basic/partition_06/expected/model_3_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/partition_06/expected/model_3_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/partition_06/expected/model_3_3-solution000003.solution delete mode 100644 tests/exhaustive/basic/partition_06/expected/model_3_3.eprime delete mode 100644 tests/exhaustive/basic/partition_06/expected/model_3_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/partition_06/expected/model_3_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/partition_06/expected/model_3_4-solution000003.solution delete mode 100644 tests/exhaustive/basic/partition_06/expected/model_3_4.eprime delete mode 100644 tests/exhaustive/basic/partition_06/expected/model_4_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/partition_06/expected/model_4_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/partition_06/expected/model_4_1-solution000003.solution delete mode 100644 tests/exhaustive/basic/partition_06/expected/model_4_1.eprime delete mode 100644 tests/exhaustive/basic/partition_06/expected/model_4_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/partition_06/expected/model_4_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/partition_06/expected/model_4_2-solution000003.solution delete mode 100644 tests/exhaustive/basic/partition_06/expected/model_4_2.eprime delete mode 100644 tests/exhaustive/basic/partition_06/expected/model_4_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/partition_06/expected/model_4_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/partition_06/expected/model_4_3-solution000003.solution delete mode 100644 tests/exhaustive/basic/partition_06/expected/model_4_3.eprime delete mode 100644 tests/exhaustive/basic/partition_06/expected/model_4_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/partition_06/expected/model_4_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/partition_06/expected/model_4_4-solution000003.solution delete mode 100644 tests/exhaustive/basic/partition_06/expected/model_4_4.eprime delete mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_1-p-solution000001.solution delete mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_1-p-solution000002.solution delete mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_1-p-solution000003.solution delete mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_1-p-solution000004.solution delete mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_1-p-solution000005.solution delete mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_1-p-solution000006.solution delete mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_1-p.eprime-param delete mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_1.eprime delete mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_2-p-solution000001.solution delete mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_2-p-solution000002.solution delete mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_2-p-solution000003.solution delete mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_2-p-solution000004.solution delete mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_2-p-solution000005.solution delete mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_2-p-solution000006.solution delete mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_2-p.eprime-param delete mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_2.eprime delete mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_3-p-solution000001.solution delete mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_3-p-solution000002.solution delete mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_3-p-solution000003.solution delete mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_3-p-solution000004.solution delete mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_3-p-solution000005.solution delete mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_3-p-solution000006.solution delete mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_3-p.eprime-param delete mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_3.eprime delete mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_4-p-solution000001.solution delete mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_4-p-solution000002.solution delete mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_4-p-solution000003.solution delete mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_4-p-solution000004.solution delete mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_4-p-solution000005.solution delete mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_4-p-solution000006.solution delete mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_4-p.eprime-param delete mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_4.eprime delete mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_1-p-solution000001.solution delete mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_1-p-solution000002.solution delete mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_1-p-solution000003.solution delete mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_1-p-solution000004.solution delete mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_1-p-solution000005.solution delete mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_1-p-solution000006.solution delete mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_1-p.eprime-param delete mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_1.eprime delete mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_2-p-solution000001.solution delete mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_2-p-solution000002.solution delete mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_2-p-solution000003.solution delete mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_2-p-solution000004.solution delete mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_2-p-solution000005.solution delete mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_2-p-solution000006.solution delete mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_2-p.eprime-param delete mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_2.eprime delete mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_3-p-solution000001.solution delete mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_3-p-solution000002.solution delete mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_3-p-solution000003.solution delete mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_3-p-solution000004.solution delete mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_3-p-solution000005.solution delete mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_3-p-solution000006.solution delete mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_3-p.eprime-param delete mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_3.eprime delete mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_4-p-solution000001.solution delete mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_4-p-solution000002.solution delete mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_4-p-solution000003.solution delete mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_4-p-solution000004.solution delete mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_4-p-solution000005.solution delete mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_4-p-solution000006.solution delete mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_4-p.eprime-param delete mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_4.eprime delete mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_1-p-solution000001.solution delete mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_1-p-solution000002.solution delete mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_1-p-solution000003.solution delete mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_1-p-solution000004.solution delete mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_1-p-solution000005.solution delete mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_1-p-solution000006.solution delete mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_1-p.eprime-param delete mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_1.eprime delete mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_2-p-solution000001.solution delete mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_2-p-solution000002.solution delete mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_2-p-solution000003.solution delete mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_2-p-solution000004.solution delete mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_2-p-solution000005.solution delete mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_2-p-solution000006.solution delete mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_2-p.eprime-param delete mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_2.eprime delete mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_3-p-solution000001.solution delete mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_3-p-solution000002.solution delete mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_3-p-solution000003.solution delete mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_3-p-solution000004.solution delete mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_3-p-solution000005.solution delete mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_3-p-solution000006.solution delete mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_3-p.eprime-param delete mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_3.eprime delete mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_4-p-solution000001.solution delete mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_4-p-solution000002.solution delete mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_4-p-solution000003.solution delete mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_4-p-solution000004.solution delete mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_4-p-solution000005.solution delete mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_4-p-solution000006.solution delete mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_4-p.eprime-param delete mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_4.eprime delete mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_1-p-solution000001.solution delete mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_1-p-solution000002.solution delete mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_1-p-solution000003.solution delete mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_1-p-solution000004.solution delete mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_1-p-solution000005.solution delete mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_1-p-solution000006.solution delete mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_1-p.eprime-param delete mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_1.eprime delete mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_2-p-solution000001.solution delete mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_2-p-solution000002.solution delete mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_2-p-solution000003.solution delete mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_2-p-solution000004.solution delete mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_2-p-solution000005.solution delete mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_2-p-solution000006.solution delete mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_2-p.eprime-param delete mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_2.eprime delete mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_3-p-solution000001.solution delete mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_3-p-solution000002.solution delete mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_3-p-solution000003.solution delete mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_3-p-solution000004.solution delete mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_3-p-solution000005.solution delete mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_3-p-solution000006.solution delete mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_3-p.eprime-param delete mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_3.eprime delete mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_4-p-solution000001.solution delete mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_4-p-solution000002.solution delete mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_4-p-solution000003.solution delete mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_4-p-solution000004.solution delete mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_4-p-solution000005.solution delete mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_4-p-solution000006.solution delete mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_4-p.eprime-param delete mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_4.eprime delete mode 100644 tests/exhaustive/basic/powerSetComprehensionPat/expected/model_1_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/powerSetComprehensionPat/expected/model_1_1.eprime delete mode 100644 tests/exhaustive/basic/powerSetComprehensionPat/expected/model_1_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/powerSetComprehensionPat/expected/model_1_2.eprime delete mode 100644 tests/exhaustive/basic/powerSetComprehensionPat/expected/model_1_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/powerSetComprehensionPat/expected/model_1_3.eprime delete mode 100644 tests/exhaustive/basic/powerSetComprehensionPat/expected/model_1_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/powerSetComprehensionPat/expected/model_1_4.eprime delete mode 100644 tests/exhaustive/basic/powerSetComprehensionPat/expected/model_2_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/powerSetComprehensionPat/expected/model_2_1.eprime delete mode 100644 tests/exhaustive/basic/powerSetComprehensionPat/expected/model_2_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/powerSetComprehensionPat/expected/model_2_2.eprime delete mode 100644 tests/exhaustive/basic/powerSetComprehensionPat/expected/model_2_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/powerSetComprehensionPat/expected/model_2_3.eprime delete mode 100644 tests/exhaustive/basic/powerSetComprehensionPat/expected/model_2_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/powerSetComprehensionPat/expected/model_2_4.eprime delete mode 100644 tests/exhaustive/basic/powerSetComprehensionPat/expected/model_3_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/powerSetComprehensionPat/expected/model_3_1.eprime delete mode 100644 tests/exhaustive/basic/powerSetComprehensionPat/expected/model_3_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/powerSetComprehensionPat/expected/model_3_2.eprime delete mode 100644 tests/exhaustive/basic/powerSetComprehensionPat/expected/model_3_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/powerSetComprehensionPat/expected/model_3_3.eprime delete mode 100644 tests/exhaustive/basic/powerSetComprehensionPat/expected/model_3_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/powerSetComprehensionPat/expected/model_3_4.eprime delete mode 100644 tests/exhaustive/basic/powerSetComprehensionPat/expected/model_4_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/powerSetComprehensionPat/expected/model_4_1.eprime delete mode 100644 tests/exhaustive/basic/powerSetComprehensionPat/expected/model_4_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/powerSetComprehensionPat/expected/model_4_2.eprime delete mode 100644 tests/exhaustive/basic/powerSetComprehensionPat/expected/model_4_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/powerSetComprehensionPat/expected/model_4_3.eprime delete mode 100644 tests/exhaustive/basic/powerSetComprehensionPat/expected/model_4_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/powerSetComprehensionPat/expected/model_4_4.eprime delete mode 100644 tests/exhaustive/basic/relation04_param/expected/model_1_1-param4-solution000001.solution delete mode 100644 tests/exhaustive/basic/relation04_param/expected/model_1_1-param4.eprime-param delete mode 100644 tests/exhaustive/basic/relation04_param/expected/model_1_1.eprime delete mode 100644 tests/exhaustive/basic/relation04_param/expected/model_1_2-param4-solution000001.solution delete mode 100644 tests/exhaustive/basic/relation04_param/expected/model_1_2-param4.eprime-param delete mode 100644 tests/exhaustive/basic/relation04_param/expected/model_1_2.eprime delete mode 100644 tests/exhaustive/basic/relation04_param/expected/model_1_3-param4-solution000001.solution delete mode 100644 tests/exhaustive/basic/relation04_param/expected/model_1_3-param4.eprime-param delete mode 100644 tests/exhaustive/basic/relation04_param/expected/model_1_3.eprime delete mode 100644 tests/exhaustive/basic/relation04_param/expected/model_1_4-param4-solution000001.solution delete mode 100644 tests/exhaustive/basic/relation04_param/expected/model_1_4-param4.eprime-param delete mode 100644 tests/exhaustive/basic/relation04_param/expected/model_1_4.eprime delete mode 100644 tests/exhaustive/basic/relation04_param/expected/model_2_1-param4-solution000001.solution delete mode 100644 tests/exhaustive/basic/relation04_param/expected/model_2_1-param4.eprime-param delete mode 100644 tests/exhaustive/basic/relation04_param/expected/model_2_1.eprime delete mode 100644 tests/exhaustive/basic/relation04_param/expected/model_2_2-param4-solution000001.solution delete mode 100644 tests/exhaustive/basic/relation04_param/expected/model_2_2-param4.eprime-param delete mode 100644 tests/exhaustive/basic/relation04_param/expected/model_2_2.eprime delete mode 100644 tests/exhaustive/basic/relation04_param/expected/model_2_3-param4-solution000001.solution delete mode 100644 tests/exhaustive/basic/relation04_param/expected/model_2_3-param4.eprime-param delete mode 100644 tests/exhaustive/basic/relation04_param/expected/model_2_3.eprime delete mode 100644 tests/exhaustive/basic/relation04_param/expected/model_2_4-param4-solution000001.solution delete mode 100644 tests/exhaustive/basic/relation04_param/expected/model_2_4-param4.eprime-param delete mode 100644 tests/exhaustive/basic/relation04_param/expected/model_2_4.eprime delete mode 100644 tests/exhaustive/basic/relation04_param/expected/model_3_1-param4-solution000001.solution delete mode 100644 tests/exhaustive/basic/relation04_param/expected/model_3_1-param4.eprime-param delete mode 100644 tests/exhaustive/basic/relation04_param/expected/model_3_1.eprime delete mode 100644 tests/exhaustive/basic/relation04_param/expected/model_3_2-param4-solution000001.solution delete mode 100644 tests/exhaustive/basic/relation04_param/expected/model_3_2-param4.eprime-param delete mode 100644 tests/exhaustive/basic/relation04_param/expected/model_3_2.eprime delete mode 100644 tests/exhaustive/basic/relation04_param/expected/model_3_3-param4-solution000001.solution delete mode 100644 tests/exhaustive/basic/relation04_param/expected/model_3_3-param4.eprime-param delete mode 100644 tests/exhaustive/basic/relation04_param/expected/model_3_3.eprime delete mode 100644 tests/exhaustive/basic/relation04_param/expected/model_3_4-param4-solution000001.solution delete mode 100644 tests/exhaustive/basic/relation04_param/expected/model_3_4-param4.eprime-param delete mode 100644 tests/exhaustive/basic/relation04_param/expected/model_3_4.eprime delete mode 100644 tests/exhaustive/basic/relation04_param/expected/model_4_1-param4-solution000001.solution delete mode 100644 tests/exhaustive/basic/relation04_param/expected/model_4_1-param4.eprime-param delete mode 100644 tests/exhaustive/basic/relation04_param/expected/model_4_1.eprime delete mode 100644 tests/exhaustive/basic/relation04_param/expected/model_4_2-param4-solution000001.solution delete mode 100644 tests/exhaustive/basic/relation04_param/expected/model_4_2-param4.eprime-param delete mode 100644 tests/exhaustive/basic/relation04_param/expected/model_4_2.eprime delete mode 100644 tests/exhaustive/basic/relation04_param/expected/model_4_3-param4-solution000001.solution delete mode 100644 tests/exhaustive/basic/relation04_param/expected/model_4_3-param4.eprime-param delete mode 100644 tests/exhaustive/basic/relation04_param/expected/model_4_3.eprime delete mode 100644 tests/exhaustive/basic/relation04_param/expected/model_4_4-param4-solution000001.solution delete mode 100644 tests/exhaustive/basic/relation04_param/expected/model_4_4-param4.eprime-param delete mode 100644 tests/exhaustive/basic/relation04_param/expected/model_4_4.eprime delete mode 100644 tests/exhaustive/basic/set03/expected/model_1_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set03/expected/model_1_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/set03/expected/model_1_1.eprime delete mode 100644 tests/exhaustive/basic/set03/expected/model_1_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set03/expected/model_1_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/set03/expected/model_1_2.eprime delete mode 100644 tests/exhaustive/basic/set03/expected/model_1_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set03/expected/model_1_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/set03/expected/model_1_3.eprime delete mode 100644 tests/exhaustive/basic/set03/expected/model_1_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set03/expected/model_1_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/set03/expected/model_1_4.eprime delete mode 100644 tests/exhaustive/basic/set03/expected/model_2_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set03/expected/model_2_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/set03/expected/model_2_1.eprime delete mode 100644 tests/exhaustive/basic/set03/expected/model_2_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set03/expected/model_2_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/set03/expected/model_2_2.eprime delete mode 100644 tests/exhaustive/basic/set03/expected/model_2_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set03/expected/model_2_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/set03/expected/model_2_3.eprime delete mode 100644 tests/exhaustive/basic/set03/expected/model_2_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set03/expected/model_2_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/set03/expected/model_2_4.eprime delete mode 100644 tests/exhaustive/basic/set03/expected/model_3_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set03/expected/model_3_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/set03/expected/model_3_1.eprime delete mode 100644 tests/exhaustive/basic/set03/expected/model_3_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set03/expected/model_3_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/set03/expected/model_3_2.eprime delete mode 100644 tests/exhaustive/basic/set03/expected/model_3_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set03/expected/model_3_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/set03/expected/model_3_3.eprime delete mode 100644 tests/exhaustive/basic/set03/expected/model_3_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set03/expected/model_3_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/set03/expected/model_3_4.eprime delete mode 100644 tests/exhaustive/basic/set03/expected/model_4_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set03/expected/model_4_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/set03/expected/model_4_1.eprime delete mode 100644 tests/exhaustive/basic/set03/expected/model_4_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set03/expected/model_4_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/set03/expected/model_4_2.eprime delete mode 100644 tests/exhaustive/basic/set03/expected/model_4_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set03/expected/model_4_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/set03/expected/model_4_3.eprime delete mode 100644 tests/exhaustive/basic/set03/expected/model_4_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set03/expected/model_4_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/set03/expected/model_4_4.eprime delete mode 100644 tests/exhaustive/basic/set04/expected/model_1_1_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set04/expected/model_1_1_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/set04/expected/model_1_1_1.eprime delete mode 100644 tests/exhaustive/basic/set04/expected/model_1_1_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set04/expected/model_1_1_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/set04/expected/model_1_1_2.eprime delete mode 100644 tests/exhaustive/basic/set04/expected/model_1_1_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set04/expected/model_1_1_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/set04/expected/model_1_1_3.eprime delete mode 100644 tests/exhaustive/basic/set04/expected/model_1_1_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set04/expected/model_1_1_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/set04/expected/model_1_1_4.eprime delete mode 100644 tests/exhaustive/basic/set04/expected/model_1_2_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set04/expected/model_1_2_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/set04/expected/model_1_2_1.eprime delete mode 100644 tests/exhaustive/basic/set04/expected/model_1_2_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set04/expected/model_1_2_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/set04/expected/model_1_2_2.eprime delete mode 100644 tests/exhaustive/basic/set04/expected/model_1_2_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set04/expected/model_1_2_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/set04/expected/model_1_2_3.eprime delete mode 100644 tests/exhaustive/basic/set04/expected/model_1_2_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set04/expected/model_1_2_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/set04/expected/model_1_2_4.eprime delete mode 100644 tests/exhaustive/basic/set04/expected/model_1_3_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set04/expected/model_1_3_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/set04/expected/model_1_3_1.eprime delete mode 100644 tests/exhaustive/basic/set04/expected/model_1_3_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set04/expected/model_1_3_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/set04/expected/model_1_3_2.eprime delete mode 100644 tests/exhaustive/basic/set04/expected/model_1_3_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set04/expected/model_1_3_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/set04/expected/model_1_3_3.eprime delete mode 100644 tests/exhaustive/basic/set04/expected/model_1_3_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set04/expected/model_1_3_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/set04/expected/model_1_3_4.eprime delete mode 100644 tests/exhaustive/basic/set04/expected/model_1_4_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set04/expected/model_1_4_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/set04/expected/model_1_4_1.eprime delete mode 100644 tests/exhaustive/basic/set04/expected/model_1_4_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set04/expected/model_1_4_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/set04/expected/model_1_4_2.eprime delete mode 100644 tests/exhaustive/basic/set04/expected/model_1_4_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set04/expected/model_1_4_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/set04/expected/model_1_4_3.eprime delete mode 100644 tests/exhaustive/basic/set04/expected/model_1_4_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set04/expected/model_1_4_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/set04/expected/model_1_4_4.eprime delete mode 100644 tests/exhaustive/basic/set04/expected/model_2_1_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set04/expected/model_2_1_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/set04/expected/model_2_1_1.eprime delete mode 100644 tests/exhaustive/basic/set04/expected/model_2_1_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set04/expected/model_2_1_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/set04/expected/model_2_1_2.eprime delete mode 100644 tests/exhaustive/basic/set04/expected/model_2_1_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set04/expected/model_2_1_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/set04/expected/model_2_1_3.eprime delete mode 100644 tests/exhaustive/basic/set04/expected/model_2_1_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set04/expected/model_2_1_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/set04/expected/model_2_1_4.eprime delete mode 100644 tests/exhaustive/basic/set04/expected/model_2_2_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set04/expected/model_2_2_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/set04/expected/model_2_2_1.eprime delete mode 100644 tests/exhaustive/basic/set04/expected/model_2_2_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set04/expected/model_2_2_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/set04/expected/model_2_2_2.eprime delete mode 100644 tests/exhaustive/basic/set04/expected/model_2_2_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set04/expected/model_2_2_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/set04/expected/model_2_2_3.eprime delete mode 100644 tests/exhaustive/basic/set04/expected/model_2_2_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set04/expected/model_2_2_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/set04/expected/model_2_2_4.eprime delete mode 100644 tests/exhaustive/basic/set04/expected/model_2_3_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set04/expected/model_2_3_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/set04/expected/model_2_3_1.eprime delete mode 100644 tests/exhaustive/basic/set04/expected/model_2_3_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set04/expected/model_2_3_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/set04/expected/model_2_3_2.eprime delete mode 100644 tests/exhaustive/basic/set04/expected/model_2_3_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set04/expected/model_2_3_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/set04/expected/model_2_3_3.eprime delete mode 100644 tests/exhaustive/basic/set04/expected/model_2_3_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set04/expected/model_2_3_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/set04/expected/model_2_3_4.eprime delete mode 100644 tests/exhaustive/basic/set04/expected/model_2_4_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set04/expected/model_2_4_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/set04/expected/model_2_4_1.eprime delete mode 100644 tests/exhaustive/basic/set04/expected/model_2_4_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set04/expected/model_2_4_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/set04/expected/model_2_4_2.eprime delete mode 100644 tests/exhaustive/basic/set04/expected/model_2_4_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set04/expected/model_2_4_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/set04/expected/model_2_4_3.eprime delete mode 100644 tests/exhaustive/basic/set04/expected/model_2_4_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set04/expected/model_2_4_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/set04/expected/model_2_4_4.eprime delete mode 100644 tests/exhaustive/basic/set04/expected/model_3_1_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set04/expected/model_3_1_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/set04/expected/model_3_1_1.eprime delete mode 100644 tests/exhaustive/basic/set04/expected/model_3_1_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set04/expected/model_3_1_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/set04/expected/model_3_1_2.eprime delete mode 100644 tests/exhaustive/basic/set04/expected/model_3_1_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set04/expected/model_3_1_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/set04/expected/model_3_1_3.eprime delete mode 100644 tests/exhaustive/basic/set04/expected/model_3_1_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set04/expected/model_3_1_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/set04/expected/model_3_1_4.eprime delete mode 100644 tests/exhaustive/basic/set04/expected/model_3_2_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set04/expected/model_3_2_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/set04/expected/model_3_2_1.eprime delete mode 100644 tests/exhaustive/basic/set04/expected/model_3_2_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set04/expected/model_3_2_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/set04/expected/model_3_2_2.eprime delete mode 100644 tests/exhaustive/basic/set04/expected/model_3_2_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set04/expected/model_3_2_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/set04/expected/model_3_2_3.eprime delete mode 100644 tests/exhaustive/basic/set04/expected/model_3_2_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set04/expected/model_3_2_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/set04/expected/model_3_2_4.eprime delete mode 100644 tests/exhaustive/basic/set04/expected/model_3_3_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set04/expected/model_3_3_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/set04/expected/model_3_3_1.eprime delete mode 100644 tests/exhaustive/basic/set04/expected/model_3_3_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set04/expected/model_3_3_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/set04/expected/model_3_3_2.eprime delete mode 100644 tests/exhaustive/basic/set04/expected/model_3_3_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set04/expected/model_3_3_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/set04/expected/model_3_3_3.eprime delete mode 100644 tests/exhaustive/basic/set04/expected/model_3_3_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set04/expected/model_3_3_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/set04/expected/model_3_3_4.eprime delete mode 100644 tests/exhaustive/basic/set04/expected/model_3_4_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set04/expected/model_3_4_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/set04/expected/model_3_4_1.eprime delete mode 100644 tests/exhaustive/basic/set04/expected/model_3_4_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set04/expected/model_3_4_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/set04/expected/model_3_4_2.eprime delete mode 100644 tests/exhaustive/basic/set04/expected/model_3_4_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set04/expected/model_3_4_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/set04/expected/model_3_4_3.eprime delete mode 100644 tests/exhaustive/basic/set04/expected/model_3_4_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set04/expected/model_3_4_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/set04/expected/model_3_4_4.eprime delete mode 100644 tests/exhaustive/basic/set04/expected/model_4_1_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set04/expected/model_4_1_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/set04/expected/model_4_1_1.eprime delete mode 100644 tests/exhaustive/basic/set04/expected/model_4_1_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set04/expected/model_4_1_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/set04/expected/model_4_1_2.eprime delete mode 100644 tests/exhaustive/basic/set04/expected/model_4_1_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set04/expected/model_4_1_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/set04/expected/model_4_1_3.eprime delete mode 100644 tests/exhaustive/basic/set04/expected/model_4_1_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set04/expected/model_4_1_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/set04/expected/model_4_1_4.eprime delete mode 100644 tests/exhaustive/basic/set04/expected/model_4_2_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set04/expected/model_4_2_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/set04/expected/model_4_2_1.eprime delete mode 100644 tests/exhaustive/basic/set04/expected/model_4_2_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set04/expected/model_4_2_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/set04/expected/model_4_2_2.eprime delete mode 100644 tests/exhaustive/basic/set04/expected/model_4_2_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set04/expected/model_4_2_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/set04/expected/model_4_2_3.eprime delete mode 100644 tests/exhaustive/basic/set04/expected/model_4_2_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set04/expected/model_4_2_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/set04/expected/model_4_2_4.eprime delete mode 100644 tests/exhaustive/basic/set04/expected/model_4_3_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set04/expected/model_4_3_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/set04/expected/model_4_3_1.eprime delete mode 100644 tests/exhaustive/basic/set04/expected/model_4_3_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set04/expected/model_4_3_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/set04/expected/model_4_3_2.eprime delete mode 100644 tests/exhaustive/basic/set04/expected/model_4_3_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set04/expected/model_4_3_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/set04/expected/model_4_3_3.eprime delete mode 100644 tests/exhaustive/basic/set04/expected/model_4_3_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set04/expected/model_4_3_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/set04/expected/model_4_3_4.eprime delete mode 100644 tests/exhaustive/basic/set04/expected/model_4_4_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set04/expected/model_4_4_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/set04/expected/model_4_4_1.eprime delete mode 100644 tests/exhaustive/basic/set04/expected/model_4_4_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set04/expected/model_4_4_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/set04/expected/model_4_4_2.eprime delete mode 100644 tests/exhaustive/basic/set04/expected/model_4_4_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set04/expected/model_4_4_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/set04/expected/model_4_4_3.eprime delete mode 100644 tests/exhaustive/basic/set04/expected/model_4_4_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set04/expected/model_4_4_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/set04/expected/model_4_4_4.eprime delete mode 100644 tests/exhaustive/basic/set05/expected/model_1_1_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_1_1_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_1_1_1-solution000003.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_1_1_1.eprime delete mode 100644 tests/exhaustive/basic/set05/expected/model_1_1_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_1_1_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_1_1_2-solution000003.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_1_1_2.eprime delete mode 100644 tests/exhaustive/basic/set05/expected/model_1_1_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_1_1_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_1_1_3-solution000003.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_1_1_3.eprime delete mode 100644 tests/exhaustive/basic/set05/expected/model_1_1_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_1_1_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_1_1_4-solution000003.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_1_1_4.eprime delete mode 100644 tests/exhaustive/basic/set05/expected/model_1_2_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_1_2_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_1_2_1-solution000003.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_1_2_1.eprime delete mode 100644 tests/exhaustive/basic/set05/expected/model_1_2_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_1_2_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_1_2_2-solution000003.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_1_2_2.eprime delete mode 100644 tests/exhaustive/basic/set05/expected/model_1_2_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_1_2_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_1_2_3-solution000003.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_1_2_3.eprime delete mode 100644 tests/exhaustive/basic/set05/expected/model_1_2_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_1_2_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_1_2_4-solution000003.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_1_2_4.eprime delete mode 100644 tests/exhaustive/basic/set05/expected/model_1_3_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_1_3_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_1_3_1-solution000003.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_1_3_1.eprime delete mode 100644 tests/exhaustive/basic/set05/expected/model_1_3_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_1_3_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_1_3_2-solution000003.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_1_3_2.eprime delete mode 100644 tests/exhaustive/basic/set05/expected/model_1_3_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_1_3_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_1_3_3-solution000003.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_1_3_3.eprime delete mode 100644 tests/exhaustive/basic/set05/expected/model_1_3_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_1_3_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_1_3_4-solution000003.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_1_3_4.eprime delete mode 100644 tests/exhaustive/basic/set05/expected/model_1_4_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_1_4_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_1_4_1-solution000003.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_1_4_1.eprime delete mode 100644 tests/exhaustive/basic/set05/expected/model_1_4_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_1_4_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_1_4_2-solution000003.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_1_4_2.eprime delete mode 100644 tests/exhaustive/basic/set05/expected/model_1_4_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_1_4_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_1_4_3-solution000003.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_1_4_3.eprime delete mode 100644 tests/exhaustive/basic/set05/expected/model_1_4_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_1_4_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_1_4_4-solution000003.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_1_4_4.eprime delete mode 100644 tests/exhaustive/basic/set05/expected/model_2_1_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_2_1_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_2_1_1-solution000003.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_2_1_1.eprime delete mode 100644 tests/exhaustive/basic/set05/expected/model_2_1_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_2_1_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_2_1_2-solution000003.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_2_1_2.eprime delete mode 100644 tests/exhaustive/basic/set05/expected/model_2_1_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_2_1_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_2_1_3-solution000003.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_2_1_3.eprime delete mode 100644 tests/exhaustive/basic/set05/expected/model_2_1_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_2_1_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_2_1_4-solution000003.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_2_1_4.eprime delete mode 100644 tests/exhaustive/basic/set05/expected/model_2_2_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_2_2_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_2_2_1-solution000003.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_2_2_1.eprime delete mode 100644 tests/exhaustive/basic/set05/expected/model_2_2_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_2_2_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_2_2_2-solution000003.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_2_2_2.eprime delete mode 100644 tests/exhaustive/basic/set05/expected/model_2_2_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_2_2_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_2_2_3-solution000003.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_2_2_3.eprime delete mode 100644 tests/exhaustive/basic/set05/expected/model_2_2_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_2_2_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_2_2_4-solution000003.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_2_2_4.eprime delete mode 100644 tests/exhaustive/basic/set05/expected/model_2_3_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_2_3_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_2_3_1-solution000003.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_2_3_1.eprime delete mode 100644 tests/exhaustive/basic/set05/expected/model_2_3_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_2_3_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_2_3_2-solution000003.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_2_3_2.eprime delete mode 100644 tests/exhaustive/basic/set05/expected/model_2_3_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_2_3_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_2_3_3-solution000003.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_2_3_3.eprime delete mode 100644 tests/exhaustive/basic/set05/expected/model_2_3_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_2_3_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_2_3_4-solution000003.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_2_3_4.eprime delete mode 100644 tests/exhaustive/basic/set05/expected/model_2_4_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_2_4_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_2_4_1-solution000003.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_2_4_1.eprime delete mode 100644 tests/exhaustive/basic/set05/expected/model_2_4_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_2_4_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_2_4_2-solution000003.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_2_4_2.eprime delete mode 100644 tests/exhaustive/basic/set05/expected/model_2_4_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_2_4_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_2_4_3-solution000003.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_2_4_3.eprime delete mode 100644 tests/exhaustive/basic/set05/expected/model_2_4_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_2_4_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_2_4_4-solution000003.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_2_4_4.eprime delete mode 100644 tests/exhaustive/basic/set05/expected/model_3_1_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_3_1_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_3_1_1-solution000003.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_3_1_1.eprime delete mode 100644 tests/exhaustive/basic/set05/expected/model_3_1_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_3_1_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_3_1_2-solution000003.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_3_1_2.eprime delete mode 100644 tests/exhaustive/basic/set05/expected/model_3_1_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_3_1_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_3_1_3-solution000003.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_3_1_3.eprime delete mode 100644 tests/exhaustive/basic/set05/expected/model_3_1_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_3_1_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_3_1_4-solution000003.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_3_1_4.eprime delete mode 100644 tests/exhaustive/basic/set05/expected/model_3_2_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_3_2_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_3_2_1-solution000003.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_3_2_1.eprime delete mode 100644 tests/exhaustive/basic/set05/expected/model_3_2_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_3_2_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_3_2_2-solution000003.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_3_2_2.eprime delete mode 100644 tests/exhaustive/basic/set05/expected/model_3_2_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_3_2_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_3_2_3-solution000003.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_3_2_3.eprime delete mode 100644 tests/exhaustive/basic/set05/expected/model_3_2_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_3_2_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_3_2_4-solution000003.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_3_2_4.eprime delete mode 100644 tests/exhaustive/basic/set05/expected/model_3_3_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_3_3_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_3_3_1-solution000003.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_3_3_1.eprime delete mode 100644 tests/exhaustive/basic/set05/expected/model_3_3_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_3_3_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_3_3_2-solution000003.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_3_3_2.eprime delete mode 100644 tests/exhaustive/basic/set05/expected/model_3_3_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_3_3_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_3_3_3-solution000003.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_3_3_3.eprime delete mode 100644 tests/exhaustive/basic/set05/expected/model_3_3_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_3_3_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_3_3_4-solution000003.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_3_3_4.eprime delete mode 100644 tests/exhaustive/basic/set05/expected/model_3_4_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_3_4_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_3_4_1-solution000003.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_3_4_1.eprime delete mode 100644 tests/exhaustive/basic/set05/expected/model_3_4_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_3_4_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_3_4_2-solution000003.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_3_4_2.eprime delete mode 100644 tests/exhaustive/basic/set05/expected/model_3_4_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_3_4_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_3_4_3-solution000003.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_3_4_3.eprime delete mode 100644 tests/exhaustive/basic/set05/expected/model_3_4_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_3_4_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_3_4_4-solution000003.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_3_4_4.eprime delete mode 100644 tests/exhaustive/basic/set05/expected/model_4_1_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_4_1_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_4_1_1-solution000003.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_4_1_1.eprime delete mode 100644 tests/exhaustive/basic/set05/expected/model_4_1_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_4_1_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_4_1_2-solution000003.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_4_1_2.eprime delete mode 100644 tests/exhaustive/basic/set05/expected/model_4_1_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_4_1_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_4_1_3-solution000003.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_4_1_3.eprime delete mode 100644 tests/exhaustive/basic/set05/expected/model_4_1_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_4_1_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_4_1_4-solution000003.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_4_1_4.eprime delete mode 100644 tests/exhaustive/basic/set05/expected/model_4_2_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_4_2_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_4_2_1-solution000003.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_4_2_1.eprime delete mode 100644 tests/exhaustive/basic/set05/expected/model_4_2_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_4_2_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_4_2_2-solution000003.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_4_2_2.eprime delete mode 100644 tests/exhaustive/basic/set05/expected/model_4_2_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_4_2_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_4_2_3-solution000003.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_4_2_3.eprime delete mode 100644 tests/exhaustive/basic/set05/expected/model_4_2_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_4_2_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_4_2_4-solution000003.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_4_2_4.eprime delete mode 100644 tests/exhaustive/basic/set05/expected/model_4_3_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_4_3_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_4_3_1-solution000003.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_4_3_1.eprime delete mode 100644 tests/exhaustive/basic/set05/expected/model_4_3_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_4_3_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_4_3_2-solution000003.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_4_3_2.eprime delete mode 100644 tests/exhaustive/basic/set05/expected/model_4_3_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_4_3_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_4_3_3-solution000003.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_4_3_3.eprime delete mode 100644 tests/exhaustive/basic/set05/expected/model_4_3_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_4_3_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_4_3_4-solution000003.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_4_3_4.eprime delete mode 100644 tests/exhaustive/basic/set05/expected/model_4_4_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_4_4_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_4_4_1-solution000003.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_4_4_1.eprime delete mode 100644 tests/exhaustive/basic/set05/expected/model_4_4_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_4_4_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_4_4_2-solution000003.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_4_4_2.eprime delete mode 100644 tests/exhaustive/basic/set05/expected/model_4_4_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_4_4_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_4_4_3-solution000003.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_4_4_3.eprime delete mode 100644 tests/exhaustive/basic/set05/expected/model_4_4_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_4_4_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_4_4_4-solution000003.solution delete mode 100644 tests/exhaustive/basic/set05/expected/model_4_4_4.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_1_1_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_1_1_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_1_1_1.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_1_1_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_1_1_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_1_1_2.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_1_1_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_1_1_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_1_1_3.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_1_1_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_1_1_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_1_1_4.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_1_2_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_1_2_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_1_2_1.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_1_2_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_1_2_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_1_2_2.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_1_2_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_1_2_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_1_2_3.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_1_2_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_1_2_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_1_2_4.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_1_3_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_1_3_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_1_3_1.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_1_3_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_1_3_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_1_3_2.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_1_3_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_1_3_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_1_3_3.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_1_3_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_1_3_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_1_3_4.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_1_4_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_1_4_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_1_4_1.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_1_4_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_1_4_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_1_4_2.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_1_4_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_1_4_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_1_4_3.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_1_4_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_1_4_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_1_4_4.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_2_1_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_2_1_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_2_1_1.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_2_1_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_2_1_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_2_1_2.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_2_1_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_2_1_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_2_1_3.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_2_1_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_2_1_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_2_1_4.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_2_2_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_2_2_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_2_2_1.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_2_2_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_2_2_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_2_2_2.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_2_2_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_2_2_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_2_2_3.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_2_2_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_2_2_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_2_2_4.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_2_3_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_2_3_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_2_3_1.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_2_3_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_2_3_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_2_3_2.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_2_3_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_2_3_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_2_3_3.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_2_3_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_2_3_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_2_3_4.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_2_4_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_2_4_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_2_4_1.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_2_4_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_2_4_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_2_4_2.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_2_4_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_2_4_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_2_4_3.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_2_4_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_2_4_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_2_4_4.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_3_1_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_3_1_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_3_1_1.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_3_1_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_3_1_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_3_1_2.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_3_1_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_3_1_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_3_1_3.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_3_1_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_3_1_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_3_1_4.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_3_2_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_3_2_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_3_2_1.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_3_2_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_3_2_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_3_2_2.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_3_2_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_3_2_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_3_2_3.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_3_2_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_3_2_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_3_2_4.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_3_3_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_3_3_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_3_3_1.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_3_3_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_3_3_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_3_3_2.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_3_3_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_3_3_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_3_3_3.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_3_3_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_3_3_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_3_3_4.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_3_4_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_3_4_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_3_4_1.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_3_4_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_3_4_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_3_4_2.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_3_4_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_3_4_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_3_4_3.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_3_4_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_3_4_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_3_4_4.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_4_1_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_4_1_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_4_1_1.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_4_1_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_4_1_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_4_1_2.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_4_1_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_4_1_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_4_1_3.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_4_1_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_4_1_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_4_1_4.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_4_2_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_4_2_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_4_2_1.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_4_2_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_4_2_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_4_2_2.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_4_2_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_4_2_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_4_2_3.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_4_2_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_4_2_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_4_2_4.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_4_3_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_4_3_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_4_3_1.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_4_3_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_4_3_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_4_3_2.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_4_3_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_4_3_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_4_3_3.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_4_3_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_4_3_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_4_3_4.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_4_4_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_4_4_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_4_4_1.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_4_4_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_4_4_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_4_4_2.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_4_4_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_4_4_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_4_4_3.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_4_4_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_4_4_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_1_4_4_4.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_1_1_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_1_1_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_1_1_1.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_1_1_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_1_1_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_1_1_2.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_1_1_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_1_1_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_1_1_3.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_1_1_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_1_1_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_1_1_4.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_1_2_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_1_2_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_1_2_1.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_1_2_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_1_2_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_1_2_2.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_1_2_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_1_2_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_1_2_3.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_1_2_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_1_2_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_1_2_4.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_1_3_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_1_3_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_1_3_1.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_1_3_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_1_3_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_1_3_2.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_1_3_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_1_3_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_1_3_3.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_1_3_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_1_3_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_1_3_4.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_1_4_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_1_4_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_1_4_1.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_1_4_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_1_4_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_1_4_2.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_1_4_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_1_4_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_1_4_3.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_1_4_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_1_4_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_1_4_4.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_2_1_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_2_1_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_2_1_1.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_2_1_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_2_1_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_2_1_2.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_2_1_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_2_1_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_2_1_3.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_2_1_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_2_1_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_2_1_4.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_2_2_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_2_2_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_2_2_1.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_2_2_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_2_2_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_2_2_2.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_2_2_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_2_2_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_2_2_3.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_2_2_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_2_2_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_2_2_4.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_2_3_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_2_3_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_2_3_1.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_2_3_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_2_3_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_2_3_2.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_2_3_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_2_3_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_2_3_3.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_2_3_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_2_3_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_2_3_4.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_2_4_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_2_4_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_2_4_1.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_2_4_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_2_4_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_2_4_2.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_2_4_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_2_4_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_2_4_3.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_2_4_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_2_4_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_2_4_4.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_3_1_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_3_1_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_3_1_1.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_3_1_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_3_1_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_3_1_2.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_3_1_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_3_1_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_3_1_3.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_3_1_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_3_1_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_3_1_4.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_3_2_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_3_2_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_3_2_1.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_3_2_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_3_2_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_3_2_2.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_3_2_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_3_2_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_3_2_3.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_3_2_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_3_2_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_3_2_4.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_3_3_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_3_3_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_3_3_1.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_3_3_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_3_3_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_3_3_2.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_3_3_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_3_3_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_3_3_3.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_3_3_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_3_3_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_3_3_4.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_3_4_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_3_4_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_3_4_1.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_3_4_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_3_4_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_3_4_2.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_3_4_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_3_4_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_3_4_3.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_3_4_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_3_4_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_3_4_4.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_4_1_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_4_1_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_4_1_1.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_4_1_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_4_1_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_4_1_2.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_4_1_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_4_1_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_4_1_3.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_4_1_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_4_1_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_4_1_4.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_4_2_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_4_2_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_4_2_1.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_4_2_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_4_2_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_4_2_2.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_4_2_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_4_2_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_4_2_3.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_4_2_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_4_2_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_4_2_4.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_4_3_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_4_3_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_4_3_1.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_4_3_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_4_3_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_4_3_2.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_4_3_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_4_3_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_4_3_3.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_4_3_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_4_3_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_4_3_4.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_4_4_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_4_4_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_4_4_1.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_4_4_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_4_4_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_4_4_2.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_4_4_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_4_4_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_4_4_3.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_4_4_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_4_4_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_2_4_4_4.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_1_1_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_1_1_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_1_1_1.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_1_1_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_1_1_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_1_1_2.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_1_1_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_1_1_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_1_1_3.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_1_1_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_1_1_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_1_1_4.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_1_2_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_1_2_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_1_2_1.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_1_2_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_1_2_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_1_2_2.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_1_2_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_1_2_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_1_2_3.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_1_2_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_1_2_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_1_2_4.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_1_3_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_1_3_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_1_3_1.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_1_3_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_1_3_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_1_3_2.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_1_3_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_1_3_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_1_3_3.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_1_3_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_1_3_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_1_3_4.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_1_4_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_1_4_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_1_4_1.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_1_4_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_1_4_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_1_4_2.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_1_4_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_1_4_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_1_4_3.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_1_4_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_1_4_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_1_4_4.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_2_1_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_2_1_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_2_1_1.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_2_1_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_2_1_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_2_1_2.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_2_1_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_2_1_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_2_1_3.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_2_1_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_2_1_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_2_1_4.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_2_2_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_2_2_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_2_2_1.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_2_2_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_2_2_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_2_2_2.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_2_2_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_2_2_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_2_2_3.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_2_2_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_2_2_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_2_2_4.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_2_3_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_2_3_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_2_3_1.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_2_3_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_2_3_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_2_3_2.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_2_3_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_2_3_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_2_3_3.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_2_3_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_2_3_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_2_3_4.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_2_4_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_2_4_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_2_4_1.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_2_4_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_2_4_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_2_4_2.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_2_4_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_2_4_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_2_4_3.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_2_4_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_2_4_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_2_4_4.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_3_1_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_3_1_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_3_1_1.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_3_1_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_3_1_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_3_1_2.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_3_1_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_3_1_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_3_1_3.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_3_1_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_3_1_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_3_1_4.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_3_2_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_3_2_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_3_2_1.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_3_2_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_3_2_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_3_2_2.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_3_2_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_3_2_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_3_2_3.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_3_2_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_3_2_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_3_2_4.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_3_3_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_3_3_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_3_3_1.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_3_3_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_3_3_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_3_3_2.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_3_3_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_3_3_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_3_3_3.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_3_3_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_3_3_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_3_3_4.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_3_4_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_3_4_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_3_4_1.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_3_4_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_3_4_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_3_4_2.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_3_4_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_3_4_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_3_4_3.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_3_4_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_3_4_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_3_4_4.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_4_1_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_4_1_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_4_1_1.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_4_1_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_4_1_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_4_1_2.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_4_1_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_4_1_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_4_1_3.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_4_1_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_4_1_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_4_1_4.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_4_2_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_4_2_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_4_2_1.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_4_2_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_4_2_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_4_2_2.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_4_2_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_4_2_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_4_2_3.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_4_2_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_4_2_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_4_2_4.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_4_3_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_4_3_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_4_3_1.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_4_3_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_4_3_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_4_3_2.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_4_3_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_4_3_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_4_3_3.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_4_3_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_4_3_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_4_3_4.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_4_4_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_4_4_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_4_4_1.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_4_4_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_4_4_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_4_4_2.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_4_4_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_4_4_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_4_4_3.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_4_4_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_4_4_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_3_4_4_4.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_1_1_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_1_1_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_1_1_1.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_1_1_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_1_1_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_1_1_2.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_1_1_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_1_1_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_1_1_3.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_1_1_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_1_1_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_1_1_4.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_1_2_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_1_2_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_1_2_1.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_1_2_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_1_2_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_1_2_2.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_1_2_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_1_2_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_1_2_3.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_1_2_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_1_2_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_1_2_4.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_1_3_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_1_3_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_1_3_1.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_1_3_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_1_3_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_1_3_2.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_1_3_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_1_3_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_1_3_3.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_1_3_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_1_3_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_1_3_4.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_1_4_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_1_4_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_1_4_1.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_1_4_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_1_4_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_1_4_2.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_1_4_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_1_4_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_1_4_3.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_1_4_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_1_4_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_1_4_4.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_2_1_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_2_1_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_2_1_1.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_2_1_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_2_1_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_2_1_2.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_2_1_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_2_1_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_2_1_3.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_2_1_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_2_1_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_2_1_4.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_2_2_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_2_2_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_2_2_1.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_2_2_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_2_2_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_2_2_2.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_2_2_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_2_2_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_2_2_3.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_2_2_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_2_2_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_2_2_4.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_2_3_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_2_3_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_2_3_1.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_2_3_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_2_3_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_2_3_2.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_2_3_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_2_3_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_2_3_3.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_2_3_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_2_3_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_2_3_4.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_2_4_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_2_4_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_2_4_1.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_2_4_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_2_4_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_2_4_2.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_2_4_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_2_4_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_2_4_3.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_2_4_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_2_4_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_2_4_4.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_3_1_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_3_1_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_3_1_1.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_3_1_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_3_1_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_3_1_2.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_3_1_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_3_1_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_3_1_3.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_3_1_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_3_1_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_3_1_4.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_3_2_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_3_2_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_3_2_1.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_3_2_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_3_2_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_3_2_2.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_3_2_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_3_2_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_3_2_3.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_3_2_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_3_2_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_3_2_4.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_3_3_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_3_3_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_3_3_1.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_3_3_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_3_3_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_3_3_2.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_3_3_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_3_3_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_3_3_3.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_3_3_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_3_3_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_3_3_4.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_3_4_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_3_4_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_3_4_1.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_3_4_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_3_4_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_3_4_2.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_3_4_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_3_4_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_3_4_3.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_3_4_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_3_4_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_3_4_4.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_4_1_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_4_1_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_4_1_1.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_4_1_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_4_1_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_4_1_2.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_4_1_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_4_1_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_4_1_3.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_4_1_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_4_1_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_4_1_4.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_4_2_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_4_2_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_4_2_1.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_4_2_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_4_2_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_4_2_2.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_4_2_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_4_2_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_4_2_3.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_4_2_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_4_2_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_4_2_4.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_4_3_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_4_3_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_4_3_1.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_4_3_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_4_3_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_4_3_2.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_4_3_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_4_3_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_4_3_3.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_4_3_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_4_3_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_4_3_4.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_4_4_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_4_4_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_4_4_1.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_4_4_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_4_4_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_4_4_2.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_4_4_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_4_4_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_4_4_3.eprime delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_4_4_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_4_4_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/set06/expected/model_4_4_4_4.eprime delete mode 100644 tests/exhaustive/basic/set07/expected/model_1_1_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set07/expected/model_1_1_1.eprime delete mode 100644 tests/exhaustive/basic/set07/expected/model_1_1_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set07/expected/model_1_1_2.eprime delete mode 100644 tests/exhaustive/basic/set07/expected/model_1_1_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set07/expected/model_1_1_3.eprime delete mode 100644 tests/exhaustive/basic/set07/expected/model_1_1_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set07/expected/model_1_1_4.eprime delete mode 100644 tests/exhaustive/basic/set07/expected/model_1_2_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set07/expected/model_1_2_1.eprime delete mode 100644 tests/exhaustive/basic/set07/expected/model_1_2_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set07/expected/model_1_2_2.eprime delete mode 100644 tests/exhaustive/basic/set07/expected/model_1_2_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set07/expected/model_1_2_3.eprime delete mode 100644 tests/exhaustive/basic/set07/expected/model_1_2_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set07/expected/model_1_2_4.eprime delete mode 100644 tests/exhaustive/basic/set07/expected/model_1_3_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set07/expected/model_1_3_1.eprime delete mode 100644 tests/exhaustive/basic/set07/expected/model_1_3_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set07/expected/model_1_3_2.eprime delete mode 100644 tests/exhaustive/basic/set07/expected/model_1_3_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set07/expected/model_1_3_3.eprime delete mode 100644 tests/exhaustive/basic/set07/expected/model_1_3_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set07/expected/model_1_3_4.eprime delete mode 100644 tests/exhaustive/basic/set07/expected/model_1_4_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set07/expected/model_1_4_1.eprime delete mode 100644 tests/exhaustive/basic/set07/expected/model_1_4_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set07/expected/model_1_4_2.eprime delete mode 100644 tests/exhaustive/basic/set07/expected/model_1_4_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set07/expected/model_1_4_3.eprime delete mode 100644 tests/exhaustive/basic/set07/expected/model_1_4_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set07/expected/model_1_4_4.eprime delete mode 100644 tests/exhaustive/basic/set07/expected/model_2_1_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set07/expected/model_2_1_1.eprime delete mode 100644 tests/exhaustive/basic/set07/expected/model_2_1_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set07/expected/model_2_1_2.eprime delete mode 100644 tests/exhaustive/basic/set07/expected/model_2_1_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set07/expected/model_2_1_3.eprime delete mode 100644 tests/exhaustive/basic/set07/expected/model_2_1_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set07/expected/model_2_1_4.eprime delete mode 100644 tests/exhaustive/basic/set07/expected/model_2_2_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set07/expected/model_2_2_1.eprime delete mode 100644 tests/exhaustive/basic/set07/expected/model_2_2_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set07/expected/model_2_2_2.eprime delete mode 100644 tests/exhaustive/basic/set07/expected/model_2_2_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set07/expected/model_2_2_3.eprime delete mode 100644 tests/exhaustive/basic/set07/expected/model_2_2_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set07/expected/model_2_2_4.eprime delete mode 100644 tests/exhaustive/basic/set07/expected/model_2_3_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set07/expected/model_2_3_1.eprime delete mode 100644 tests/exhaustive/basic/set07/expected/model_2_3_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set07/expected/model_2_3_2.eprime delete mode 100644 tests/exhaustive/basic/set07/expected/model_2_3_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set07/expected/model_2_3_3.eprime delete mode 100644 tests/exhaustive/basic/set07/expected/model_2_3_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set07/expected/model_2_3_4.eprime delete mode 100644 tests/exhaustive/basic/set07/expected/model_2_4_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set07/expected/model_2_4_1.eprime delete mode 100644 tests/exhaustive/basic/set07/expected/model_2_4_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set07/expected/model_2_4_2.eprime delete mode 100644 tests/exhaustive/basic/set07/expected/model_2_4_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set07/expected/model_2_4_3.eprime delete mode 100644 tests/exhaustive/basic/set07/expected/model_2_4_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set07/expected/model_2_4_4.eprime delete mode 100644 tests/exhaustive/basic/set07/expected/model_3_1_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set07/expected/model_3_1_1.eprime delete mode 100644 tests/exhaustive/basic/set07/expected/model_3_1_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set07/expected/model_3_1_2.eprime delete mode 100644 tests/exhaustive/basic/set07/expected/model_3_1_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set07/expected/model_3_1_3.eprime delete mode 100644 tests/exhaustive/basic/set07/expected/model_3_1_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set07/expected/model_3_1_4.eprime delete mode 100644 tests/exhaustive/basic/set07/expected/model_3_2_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set07/expected/model_3_2_1.eprime delete mode 100644 tests/exhaustive/basic/set07/expected/model_3_2_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set07/expected/model_3_2_2.eprime delete mode 100644 tests/exhaustive/basic/set07/expected/model_3_2_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set07/expected/model_3_2_3.eprime delete mode 100644 tests/exhaustive/basic/set07/expected/model_3_2_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set07/expected/model_3_2_4.eprime delete mode 100644 tests/exhaustive/basic/set07/expected/model_3_3_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set07/expected/model_3_3_1.eprime delete mode 100644 tests/exhaustive/basic/set07/expected/model_3_3_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set07/expected/model_3_3_2.eprime delete mode 100644 tests/exhaustive/basic/set07/expected/model_3_3_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set07/expected/model_3_3_3.eprime delete mode 100644 tests/exhaustive/basic/set07/expected/model_3_3_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set07/expected/model_3_3_4.eprime delete mode 100644 tests/exhaustive/basic/set07/expected/model_3_4_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set07/expected/model_3_4_1.eprime delete mode 100644 tests/exhaustive/basic/set07/expected/model_3_4_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set07/expected/model_3_4_2.eprime delete mode 100644 tests/exhaustive/basic/set07/expected/model_3_4_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set07/expected/model_3_4_3.eprime delete mode 100644 tests/exhaustive/basic/set07/expected/model_3_4_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set07/expected/model_3_4_4.eprime delete mode 100644 tests/exhaustive/basic/set07/expected/model_4_1_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set07/expected/model_4_1_1.eprime delete mode 100644 tests/exhaustive/basic/set07/expected/model_4_1_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set07/expected/model_4_1_2.eprime delete mode 100644 tests/exhaustive/basic/set07/expected/model_4_1_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set07/expected/model_4_1_3.eprime delete mode 100644 tests/exhaustive/basic/set07/expected/model_4_1_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set07/expected/model_4_1_4.eprime delete mode 100644 tests/exhaustive/basic/set07/expected/model_4_2_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set07/expected/model_4_2_1.eprime delete mode 100644 tests/exhaustive/basic/set07/expected/model_4_2_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set07/expected/model_4_2_2.eprime delete mode 100644 tests/exhaustive/basic/set07/expected/model_4_2_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set07/expected/model_4_2_3.eprime delete mode 100644 tests/exhaustive/basic/set07/expected/model_4_2_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set07/expected/model_4_2_4.eprime delete mode 100644 tests/exhaustive/basic/set07/expected/model_4_3_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set07/expected/model_4_3_1.eprime delete mode 100644 tests/exhaustive/basic/set07/expected/model_4_3_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set07/expected/model_4_3_2.eprime delete mode 100644 tests/exhaustive/basic/set07/expected/model_4_3_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set07/expected/model_4_3_3.eprime delete mode 100644 tests/exhaustive/basic/set07/expected/model_4_3_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set07/expected/model_4_3_4.eprime delete mode 100644 tests/exhaustive/basic/set07/expected/model_4_4_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set07/expected/model_4_4_1.eprime delete mode 100644 tests/exhaustive/basic/set07/expected/model_4_4_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set07/expected/model_4_4_2.eprime delete mode 100644 tests/exhaustive/basic/set07/expected/model_4_4_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set07/expected/model_4_4_3.eprime delete mode 100644 tests/exhaustive/basic/set07/expected/model_4_4_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set07/expected/model_4_4_4.eprime delete mode 100644 tests/exhaustive/basic/set08/expected/model_1_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set08/expected/model_1_1.eprime delete mode 100644 tests/exhaustive/basic/set08/expected/model_1_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set08/expected/model_1_2.eprime delete mode 100644 tests/exhaustive/basic/set08/expected/model_2_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set08/expected/model_2_1.eprime delete mode 100644 tests/exhaustive/basic/set08/expected/model_2_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set08/expected/model_2_2.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_1_1_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_1_1_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_1_1_1.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_1_1_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_1_1_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_1_1_2.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_1_1_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_1_1_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_1_1_3.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_1_1_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_1_1_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_1_1_4.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_1_2_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_1_2_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_1_2_1.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_1_2_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_1_2_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_1_2_2.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_1_2_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_1_2_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_1_2_3.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_1_2_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_1_2_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_1_2_4.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_1_3_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_1_3_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_1_3_1.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_1_3_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_1_3_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_1_3_2.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_1_3_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_1_3_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_1_3_3.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_1_3_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_1_3_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_1_3_4.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_1_4_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_1_4_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_1_4_1.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_1_4_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_1_4_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_1_4_2.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_1_4_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_1_4_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_1_4_3.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_1_4_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_1_4_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_1_4_4.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_2_1_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_2_1_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_2_1_1.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_2_1_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_2_1_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_2_1_2.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_2_1_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_2_1_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_2_1_3.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_2_1_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_2_1_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_2_1_4.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_2_2_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_2_2_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_2_2_1.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_2_2_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_2_2_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_2_2_2.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_2_2_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_2_2_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_2_2_3.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_2_2_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_2_2_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_2_2_4.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_2_3_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_2_3_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_2_3_1.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_2_3_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_2_3_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_2_3_2.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_2_3_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_2_3_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_2_3_3.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_2_3_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_2_3_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_2_3_4.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_2_4_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_2_4_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_2_4_1.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_2_4_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_2_4_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_2_4_2.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_2_4_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_2_4_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_2_4_3.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_2_4_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_2_4_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_2_4_4.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_3_1_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_3_1_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_3_1_1.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_3_1_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_3_1_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_3_1_2.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_3_1_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_3_1_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_3_1_3.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_3_1_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_3_1_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_3_1_4.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_3_2_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_3_2_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_3_2_1.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_3_2_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_3_2_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_3_2_2.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_3_2_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_3_2_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_3_2_3.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_3_2_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_3_2_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_3_2_4.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_3_3_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_3_3_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_3_3_1.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_3_3_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_3_3_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_3_3_2.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_3_3_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_3_3_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_3_3_3.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_3_3_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_3_3_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_3_3_4.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_3_4_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_3_4_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_3_4_1.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_3_4_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_3_4_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_3_4_2.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_3_4_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_3_4_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_3_4_3.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_3_4_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_3_4_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_3_4_4.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_4_1_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_4_1_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_4_1_1.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_4_1_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_4_1_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_4_1_2.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_4_1_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_4_1_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_4_1_3.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_4_1_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_4_1_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_4_1_4.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_4_2_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_4_2_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_4_2_1.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_4_2_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_4_2_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_4_2_2.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_4_2_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_4_2_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_4_2_3.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_4_2_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_4_2_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_4_2_4.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_4_3_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_4_3_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_4_3_1.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_4_3_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_4_3_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_4_3_2.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_4_3_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_4_3_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_4_3_3.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_4_3_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_4_3_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_4_3_4.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_4_4_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_4_4_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_4_4_1.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_4_4_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_4_4_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_4_4_2.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_4_4_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_4_4_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_4_4_3.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_4_4_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_4_4_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_1_4_4_4.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_1_1_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_1_1_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_1_1_1.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_1_1_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_1_1_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_1_1_2.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_1_1_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_1_1_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_1_1_3.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_1_1_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_1_1_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_1_1_4.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_1_2_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_1_2_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_1_2_1.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_1_2_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_1_2_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_1_2_2.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_1_2_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_1_2_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_1_2_3.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_1_2_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_1_2_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_1_2_4.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_1_3_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_1_3_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_1_3_1.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_1_3_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_1_3_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_1_3_2.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_1_3_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_1_3_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_1_3_3.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_1_3_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_1_3_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_1_3_4.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_1_4_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_1_4_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_1_4_1.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_1_4_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_1_4_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_1_4_2.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_1_4_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_1_4_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_1_4_3.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_1_4_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_1_4_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_1_4_4.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_2_1_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_2_1_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_2_1_1.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_2_1_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_2_1_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_2_1_2.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_2_1_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_2_1_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_2_1_3.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_2_1_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_2_1_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_2_1_4.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_2_2_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_2_2_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_2_2_1.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_2_2_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_2_2_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_2_2_2.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_2_2_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_2_2_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_2_2_3.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_2_2_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_2_2_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_2_2_4.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_2_3_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_2_3_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_2_3_1.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_2_3_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_2_3_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_2_3_2.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_2_3_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_2_3_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_2_3_3.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_2_3_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_2_3_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_2_3_4.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_2_4_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_2_4_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_2_4_1.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_2_4_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_2_4_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_2_4_2.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_2_4_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_2_4_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_2_4_3.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_2_4_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_2_4_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_2_4_4.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_3_1_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_3_1_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_3_1_1.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_3_1_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_3_1_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_3_1_2.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_3_1_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_3_1_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_3_1_3.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_3_1_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_3_1_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_3_1_4.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_3_2_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_3_2_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_3_2_1.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_3_2_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_3_2_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_3_2_2.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_3_2_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_3_2_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_3_2_3.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_3_2_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_3_2_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_3_2_4.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_3_3_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_3_3_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_3_3_1.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_3_3_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_3_3_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_3_3_2.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_3_3_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_3_3_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_3_3_3.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_3_3_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_3_3_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_3_3_4.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_3_4_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_3_4_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_3_4_1.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_3_4_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_3_4_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_3_4_2.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_3_4_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_3_4_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_3_4_3.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_3_4_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_3_4_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_3_4_4.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_4_1_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_4_1_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_4_1_1.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_4_1_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_4_1_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_4_1_2.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_4_1_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_4_1_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_4_1_3.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_4_1_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_4_1_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_4_1_4.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_4_2_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_4_2_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_4_2_1.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_4_2_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_4_2_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_4_2_2.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_4_2_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_4_2_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_4_2_3.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_4_2_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_4_2_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_4_2_4.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_4_3_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_4_3_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_4_3_1.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_4_3_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_4_3_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_4_3_2.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_4_3_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_4_3_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_4_3_3.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_4_3_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_4_3_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_4_3_4.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_4_4_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_4_4_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_4_4_1.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_4_4_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_4_4_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_4_4_2.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_4_4_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_4_4_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_4_4_3.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_4_4_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_4_4_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_2_4_4_4.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_1_1_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_1_1_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_1_1_1.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_1_1_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_1_1_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_1_1_2.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_1_1_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_1_1_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_1_1_3.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_1_1_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_1_1_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_1_1_4.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_1_2_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_1_2_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_1_2_1.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_1_2_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_1_2_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_1_2_2.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_1_2_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_1_2_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_1_2_3.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_1_2_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_1_2_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_1_2_4.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_1_3_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_1_3_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_1_3_1.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_1_3_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_1_3_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_1_3_2.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_1_3_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_1_3_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_1_3_3.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_1_3_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_1_3_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_1_3_4.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_1_4_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_1_4_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_1_4_1.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_1_4_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_1_4_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_1_4_2.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_1_4_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_1_4_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_1_4_3.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_1_4_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_1_4_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_1_4_4.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_2_1_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_2_1_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_2_1_1.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_2_1_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_2_1_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_2_1_2.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_2_1_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_2_1_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_2_1_3.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_2_1_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_2_1_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_2_1_4.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_2_2_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_2_2_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_2_2_1.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_2_2_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_2_2_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_2_2_2.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_2_2_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_2_2_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_2_2_3.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_2_2_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_2_2_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_2_2_4.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_2_3_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_2_3_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_2_3_1.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_2_3_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_2_3_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_2_3_2.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_2_3_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_2_3_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_2_3_3.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_2_3_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_2_3_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_2_3_4.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_2_4_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_2_4_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_2_4_1.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_2_4_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_2_4_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_2_4_2.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_2_4_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_2_4_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_2_4_3.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_2_4_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_2_4_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_2_4_4.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_3_1_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_3_1_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_3_1_1.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_3_1_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_3_1_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_3_1_2.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_3_1_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_3_1_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_3_1_3.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_3_1_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_3_1_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_3_1_4.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_3_2_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_3_2_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_3_2_1.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_3_2_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_3_2_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_3_2_2.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_3_2_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_3_2_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_3_2_3.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_3_2_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_3_2_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_3_2_4.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_3_3_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_3_3_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_3_3_1.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_3_3_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_3_3_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_3_3_2.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_3_3_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_3_3_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_3_3_3.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_3_3_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_3_3_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_3_3_4.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_3_4_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_3_4_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_3_4_1.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_3_4_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_3_4_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_3_4_2.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_3_4_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_3_4_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_3_4_3.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_3_4_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_3_4_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_3_4_4.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_4_1_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_4_1_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_4_1_1.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_4_1_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_4_1_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_4_1_2.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_4_1_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_4_1_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_4_1_3.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_4_1_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_4_1_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_4_1_4.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_4_2_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_4_2_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_4_2_1.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_4_2_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_4_2_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_4_2_2.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_4_2_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_4_2_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_4_2_3.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_4_2_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_4_2_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_4_2_4.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_4_3_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_4_3_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_4_3_1.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_4_3_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_4_3_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_4_3_2.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_4_3_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_4_3_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_4_3_3.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_4_3_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_4_3_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_4_3_4.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_4_4_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_4_4_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_4_4_1.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_4_4_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_4_4_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_4_4_2.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_4_4_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_4_4_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_4_4_3.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_4_4_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_4_4_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_3_4_4_4.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_1_1_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_1_1_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_1_1_1.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_1_1_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_1_1_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_1_1_2.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_1_1_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_1_1_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_1_1_3.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_1_1_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_1_1_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_1_1_4.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_1_2_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_1_2_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_1_2_1.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_1_2_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_1_2_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_1_2_2.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_1_2_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_1_2_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_1_2_3.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_1_2_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_1_2_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_1_2_4.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_1_3_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_1_3_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_1_3_1.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_1_3_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_1_3_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_1_3_2.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_1_3_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_1_3_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_1_3_3.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_1_3_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_1_3_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_1_3_4.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_1_4_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_1_4_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_1_4_1.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_1_4_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_1_4_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_1_4_2.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_1_4_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_1_4_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_1_4_3.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_1_4_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_1_4_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_1_4_4.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_2_1_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_2_1_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_2_1_1.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_2_1_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_2_1_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_2_1_2.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_2_1_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_2_1_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_2_1_3.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_2_1_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_2_1_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_2_1_4.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_2_2_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_2_2_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_2_2_1.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_2_2_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_2_2_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_2_2_2.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_2_2_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_2_2_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_2_2_3.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_2_2_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_2_2_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_2_2_4.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_2_3_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_2_3_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_2_3_1.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_2_3_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_2_3_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_2_3_2.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_2_3_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_2_3_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_2_3_3.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_2_3_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_2_3_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_2_3_4.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_2_4_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_2_4_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_2_4_1.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_2_4_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_2_4_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_2_4_2.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_2_4_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_2_4_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_2_4_3.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_2_4_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_2_4_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_2_4_4.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_3_1_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_3_1_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_3_1_1.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_3_1_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_3_1_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_3_1_2.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_3_1_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_3_1_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_3_1_3.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_3_1_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_3_1_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_3_1_4.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_3_2_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_3_2_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_3_2_1.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_3_2_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_3_2_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_3_2_2.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_3_2_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_3_2_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_3_2_3.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_3_2_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_3_2_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_3_2_4.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_3_3_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_3_3_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_3_3_1.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_3_3_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_3_3_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_3_3_2.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_3_3_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_3_3_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_3_3_3.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_3_3_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_3_3_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_3_3_4.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_3_4_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_3_4_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_3_4_1.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_3_4_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_3_4_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_3_4_2.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_3_4_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_3_4_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_3_4_3.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_3_4_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_3_4_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_3_4_4.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_4_1_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_4_1_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_4_1_1.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_4_1_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_4_1_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_4_1_2.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_4_1_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_4_1_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_4_1_3.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_4_1_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_4_1_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_4_1_4.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_4_2_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_4_2_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_4_2_1.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_4_2_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_4_2_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_4_2_2.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_4_2_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_4_2_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_4_2_3.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_4_2_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_4_2_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_4_2_4.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_4_3_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_4_3_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_4_3_1.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_4_3_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_4_3_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_4_3_2.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_4_3_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_4_3_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_4_3_3.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_4_3_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_4_3_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_4_3_4.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_4_4_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_4_4_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_4_4_1.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_4_4_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_4_4_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_4_4_2.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_4_4_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_4_4_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_4_4_3.eprime delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_4_4_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_4_4_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/set09/expected/model_4_4_4_4.eprime delete mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_1-solution000003.solution delete mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_1-solution000004.solution delete mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_1-solution000005.solution delete mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_1-solution000006.solution delete mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_1-solution000007.solution delete mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_1-solution000008.solution delete mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_1-solution000009.solution delete mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_1-solution000010.solution delete mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_1-solution000011.solution delete mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_1-solution000012.solution delete mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_1-solution000013.solution delete mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_1-solution000014.solution delete mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_1-solution000015.solution delete mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_1-solution000016.solution delete mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_1.eprime delete mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_2-solution000003.solution delete mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_2-solution000004.solution delete mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_2-solution000005.solution delete mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_2-solution000006.solution delete mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_2-solution000007.solution delete mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_2-solution000008.solution delete mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_2-solution000009.solution delete mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_2-solution000010.solution delete mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_2-solution000011.solution delete mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_2-solution000012.solution delete mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_2-solution000013.solution delete mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_2-solution000014.solution delete mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_2-solution000015.solution delete mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_2-solution000016.solution delete mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_2.eprime delete mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_3-solution000003.solution delete mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_3-solution000004.solution delete mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_3-solution000005.solution delete mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_3-solution000006.solution delete mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_3-solution000007.solution delete mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_3-solution000008.solution delete mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_3-solution000009.solution delete mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_3-solution000010.solution delete mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_3-solution000011.solution delete mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_3-solution000012.solution delete mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_3-solution000013.solution delete mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_3-solution000014.solution delete mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_3-solution000015.solution delete mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_3-solution000016.solution delete mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_3.eprime delete mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_4-solution000003.solution delete mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_4-solution000004.solution delete mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_4-solution000005.solution delete mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_4-solution000006.solution delete mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_4-solution000007.solution delete mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_4-solution000008.solution delete mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_4-solution000009.solution delete mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_4-solution000010.solution delete mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_4-solution000011.solution delete mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_4-solution000012.solution delete mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_4-solution000013.solution delete mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_4-solution000014.solution delete mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_4-solution000015.solution delete mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_4-solution000016.solution delete mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_4.eprime delete mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_5-solution000001.solution delete mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_5-solution000002.solution delete mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_5-solution000003.solution delete mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_5-solution000004.solution delete mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_5-solution000005.solution delete mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_5-solution000006.solution delete mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_5-solution000007.solution delete mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_5-solution000008.solution delete mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_5-solution000009.solution delete mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_5-solution000010.solution delete mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_5-solution000011.solution delete mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_5-solution000012.solution delete mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_5-solution000013.solution delete mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_5-solution000014.solution delete mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_5-solution000015.solution delete mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_5-solution000016.solution delete mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_5.eprime delete mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_6-solution000001.solution delete mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_6-solution000002.solution delete mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_6-solution000003.solution delete mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_6-solution000004.solution delete mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_6-solution000005.solution delete mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_6-solution000006.solution delete mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_6-solution000007.solution delete mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_6-solution000008.solution delete mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_6-solution000009.solution delete mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_6-solution000010.solution delete mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_6-solution000011.solution delete mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_6-solution000012.solution delete mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_6-solution000013.solution delete mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_6-solution000014.solution delete mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_6-solution000015.solution delete mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_6-solution000016.solution delete mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_6.eprime delete mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_7-solution000001.solution delete mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_7-solution000002.solution delete mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_7-solution000003.solution delete mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_7-solution000004.solution delete mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_7-solution000005.solution delete mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_7-solution000006.solution delete mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_7-solution000007.solution delete mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_7-solution000008.solution delete mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_7-solution000009.solution delete mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_7-solution000010.solution delete mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_7-solution000011.solution delete mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_7-solution000012.solution delete mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_7-solution000013.solution delete mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_7-solution000014.solution delete mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_7-solution000015.solution delete mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_7-solution000016.solution delete mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_7.eprime delete mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_8-solution000001.solution delete mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_8-solution000002.solution delete mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_8-solution000003.solution delete mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_8-solution000004.solution delete mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_8-solution000005.solution delete mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_8-solution000006.solution delete mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_8-solution000007.solution delete mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_8-solution000008.solution delete mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_8-solution000009.solution delete mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_8-solution000010.solution delete mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_8-solution000011.solution delete mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_8-solution000012.solution delete mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_8-solution000013.solution delete mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_8-solution000014.solution delete mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_8-solution000015.solution delete mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_8-solution000016.solution delete mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_8.eprime delete mode 100644 tests/exhaustive/basic/setOfSet02/expected/model_1_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/setOfSet02/expected/model_1_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/setOfSet02/expected/model_1_1-solution000003.solution delete mode 100644 tests/exhaustive/basic/setOfSet02/expected/model_1_1.eprime delete mode 100644 tests/exhaustive/basic/setOfSet02/expected/model_1_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/setOfSet02/expected/model_1_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/setOfSet02/expected/model_1_2-solution000003.solution delete mode 100644 tests/exhaustive/basic/setOfSet02/expected/model_1_2.eprime delete mode 100644 tests/exhaustive/basic/setOfSet02/expected/model_2_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/setOfSet02/expected/model_2_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/setOfSet02/expected/model_2_1-solution000003.solution delete mode 100644 tests/exhaustive/basic/setOfSet02/expected/model_2_1.eprime delete mode 100644 tests/exhaustive/basic/setOfSet02/expected/model_2_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/setOfSet02/expected/model_2_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/setOfSet02/expected/model_2_2-solution000003.solution delete mode 100644 tests/exhaustive/basic/setOfSet02/expected/model_2_2.eprime delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_1_1_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_1_1_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_1_1_1-solution000003.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_1_1_1-solution000004.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_1_1_1-solution000005.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_1_1_1-solution000006.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_1_1_1.eprime delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_1_1_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_1_1_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_1_1_2-solution000003.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_1_1_2-solution000004.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_1_1_2-solution000005.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_1_1_2-solution000006.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_1_1_2.eprime delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_1_1_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_1_1_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_1_1_3-solution000003.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_1_1_3-solution000004.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_1_1_3-solution000005.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_1_1_3-solution000006.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_1_1_3.eprime delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_1_1_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_1_1_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_1_1_4-solution000003.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_1_1_4-solution000004.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_1_1_4-solution000005.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_1_1_4-solution000006.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_1_1_4.eprime delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_1_2_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_1_2_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_1_2_1-solution000003.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_1_2_1-solution000004.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_1_2_1-solution000005.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_1_2_1-solution000006.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_1_2_1.eprime delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_1_2_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_1_2_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_1_2_2-solution000003.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_1_2_2-solution000004.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_1_2_2-solution000005.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_1_2_2-solution000006.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_1_2_2.eprime delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_1_2_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_1_2_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_1_2_3-solution000003.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_1_2_3-solution000004.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_1_2_3-solution000005.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_1_2_3-solution000006.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_1_2_3.eprime delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_1_2_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_1_2_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_1_2_4-solution000003.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_1_2_4-solution000004.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_1_2_4-solution000005.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_1_2_4-solution000006.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_1_2_4.eprime delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_1_3_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_1_3_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_1_3_1-solution000003.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_1_3_1-solution000004.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_1_3_1-solution000005.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_1_3_1-solution000006.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_1_3_1.eprime delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_1_3_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_1_3_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_1_3_2-solution000003.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_1_3_2-solution000004.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_1_3_2-solution000005.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_1_3_2-solution000006.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_1_3_2.eprime delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_1_3_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_1_3_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_1_3_3-solution000003.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_1_3_3-solution000004.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_1_3_3-solution000005.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_1_3_3-solution000006.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_1_3_3.eprime delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_1_3_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_1_3_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_1_3_4-solution000003.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_1_3_4-solution000004.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_1_3_4-solution000005.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_1_3_4-solution000006.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_1_3_4.eprime delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_1_4_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_1_4_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_1_4_1-solution000003.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_1_4_1-solution000004.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_1_4_1-solution000005.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_1_4_1-solution000006.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_1_4_1.eprime delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_1_4_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_1_4_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_1_4_2-solution000003.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_1_4_2-solution000004.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_1_4_2-solution000005.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_1_4_2-solution000006.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_1_4_2.eprime delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_1_4_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_1_4_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_1_4_3-solution000003.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_1_4_3-solution000004.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_1_4_3-solution000005.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_1_4_3-solution000006.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_1_4_3.eprime delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_1_4_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_1_4_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_1_4_4-solution000003.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_1_4_4-solution000004.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_1_4_4-solution000005.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_1_4_4-solution000006.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_1_4_4.eprime delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_2_1_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_2_1_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_2_1_1-solution000003.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_2_1_1-solution000004.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_2_1_1-solution000005.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_2_1_1-solution000006.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_2_1_1.eprime delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_2_1_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_2_1_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_2_1_2-solution000003.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_2_1_2-solution000004.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_2_1_2-solution000005.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_2_1_2-solution000006.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_2_1_2.eprime delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_2_1_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_2_1_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_2_1_3-solution000003.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_2_1_3-solution000004.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_2_1_3-solution000005.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_2_1_3-solution000006.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_2_1_3.eprime delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_2_1_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_2_1_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_2_1_4-solution000003.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_2_1_4-solution000004.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_2_1_4-solution000005.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_2_1_4-solution000006.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_2_1_4.eprime delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_2_2_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_2_2_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_2_2_1-solution000003.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_2_2_1-solution000004.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_2_2_1-solution000005.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_2_2_1-solution000006.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_2_2_1.eprime delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_2_2_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_2_2_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_2_2_2-solution000003.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_2_2_2-solution000004.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_2_2_2-solution000005.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_2_2_2-solution000006.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_2_2_2.eprime delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_2_2_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_2_2_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_2_2_3-solution000003.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_2_2_3-solution000004.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_2_2_3-solution000005.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_2_2_3-solution000006.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_2_2_3.eprime delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_2_2_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_2_2_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_2_2_4-solution000003.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_2_2_4-solution000004.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_2_2_4-solution000005.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_2_2_4-solution000006.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_2_2_4.eprime delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_2_3_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_2_3_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_2_3_1-solution000003.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_2_3_1-solution000004.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_2_3_1-solution000005.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_2_3_1-solution000006.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_2_3_1.eprime delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_2_3_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_2_3_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_2_3_2-solution000003.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_2_3_2-solution000004.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_2_3_2-solution000005.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_2_3_2-solution000006.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_2_3_2.eprime delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_2_3_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_2_3_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_2_3_3-solution000003.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_2_3_3-solution000004.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_2_3_3-solution000005.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_2_3_3-solution000006.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_2_3_3.eprime delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_2_3_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_2_3_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_2_3_4-solution000003.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_2_3_4-solution000004.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_2_3_4-solution000005.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_2_3_4-solution000006.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_2_3_4.eprime delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_2_4_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_2_4_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_2_4_1-solution000003.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_2_4_1-solution000004.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_2_4_1-solution000005.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_2_4_1-solution000006.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_2_4_1.eprime delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_2_4_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_2_4_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_2_4_2-solution000003.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_2_4_2-solution000004.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_2_4_2-solution000005.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_2_4_2-solution000006.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_2_4_2.eprime delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_2_4_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_2_4_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_2_4_3-solution000003.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_2_4_3-solution000004.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_2_4_3-solution000005.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_2_4_3-solution000006.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_2_4_3.eprime delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_2_4_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_2_4_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_2_4_4-solution000003.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_2_4_4-solution000004.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_2_4_4-solution000005.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_2_4_4-solution000006.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_2_4_4.eprime delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_3_1_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_3_1_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_3_1_1-solution000003.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_3_1_1-solution000004.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_3_1_1-solution000005.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_3_1_1-solution000006.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_3_1_1.eprime delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_3_1_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_3_1_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_3_1_2-solution000003.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_3_1_2-solution000004.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_3_1_2-solution000005.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_3_1_2-solution000006.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_3_1_2.eprime delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_3_1_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_3_1_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_3_1_3-solution000003.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_3_1_3-solution000004.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_3_1_3-solution000005.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_3_1_3-solution000006.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_3_1_3.eprime delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_3_1_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_3_1_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_3_1_4-solution000003.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_3_1_4-solution000004.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_3_1_4-solution000005.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_3_1_4-solution000006.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_3_1_4.eprime delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_3_2_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_3_2_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_3_2_1-solution000003.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_3_2_1-solution000004.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_3_2_1-solution000005.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_3_2_1-solution000006.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_3_2_1.eprime delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_3_2_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_3_2_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_3_2_2-solution000003.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_3_2_2-solution000004.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_3_2_2-solution000005.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_3_2_2-solution000006.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_3_2_2.eprime delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_3_2_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_3_2_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_3_2_3-solution000003.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_3_2_3-solution000004.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_3_2_3-solution000005.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_3_2_3-solution000006.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_3_2_3.eprime delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_3_2_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_3_2_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_3_2_4-solution000003.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_3_2_4-solution000004.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_3_2_4-solution000005.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_3_2_4-solution000006.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_3_2_4.eprime delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_3_3_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_3_3_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_3_3_1-solution000003.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_3_3_1-solution000004.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_3_3_1-solution000005.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_3_3_1-solution000006.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_3_3_1.eprime delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_3_3_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_3_3_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_3_3_2-solution000003.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_3_3_2-solution000004.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_3_3_2-solution000005.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_3_3_2-solution000006.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_3_3_2.eprime delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_3_3_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_3_3_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_3_3_3-solution000003.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_3_3_3-solution000004.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_3_3_3-solution000005.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_3_3_3-solution000006.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_3_3_3.eprime delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_3_3_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_3_3_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_3_3_4-solution000003.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_3_3_4-solution000004.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_3_3_4-solution000005.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_3_3_4-solution000006.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_3_3_4.eprime delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_3_4_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_3_4_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_3_4_1-solution000003.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_3_4_1-solution000004.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_3_4_1-solution000005.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_3_4_1-solution000006.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_3_4_1.eprime delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_3_4_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_3_4_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_3_4_2-solution000003.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_3_4_2-solution000004.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_3_4_2-solution000005.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_3_4_2-solution000006.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_3_4_2.eprime delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_3_4_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_3_4_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_3_4_3-solution000003.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_3_4_3-solution000004.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_3_4_3-solution000005.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_3_4_3-solution000006.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_3_4_3.eprime delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_3_4_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_3_4_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_3_4_4-solution000003.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_3_4_4-solution000004.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_3_4_4-solution000005.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_3_4_4-solution000006.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_3_4_4.eprime delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_4_1_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_4_1_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_4_1_1-solution000003.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_4_1_1-solution000004.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_4_1_1-solution000005.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_4_1_1-solution000006.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_4_1_1.eprime delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_4_1_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_4_1_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_4_1_2-solution000003.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_4_1_2-solution000004.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_4_1_2-solution000005.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_4_1_2-solution000006.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_4_1_2.eprime delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_4_1_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_4_1_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_4_1_3-solution000003.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_4_1_3-solution000004.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_4_1_3-solution000005.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_4_1_3-solution000006.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_4_1_3.eprime delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_4_1_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_4_1_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_4_1_4-solution000003.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_4_1_4-solution000004.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_4_1_4-solution000005.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_4_1_4-solution000006.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_4_1_4.eprime delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_4_2_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_4_2_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_4_2_1-solution000003.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_4_2_1-solution000004.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_4_2_1-solution000005.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_4_2_1-solution000006.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_4_2_1.eprime delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_4_2_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_4_2_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_4_2_2-solution000003.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_4_2_2-solution000004.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_4_2_2-solution000005.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_4_2_2-solution000006.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_4_2_2.eprime delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_4_2_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_4_2_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_4_2_3-solution000003.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_4_2_3-solution000004.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_4_2_3-solution000005.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_4_2_3-solution000006.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_4_2_3.eprime delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_4_2_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_4_2_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_4_2_4-solution000003.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_4_2_4-solution000004.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_4_2_4-solution000005.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_4_2_4-solution000006.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_4_2_4.eprime delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_4_3_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_4_3_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_4_3_1-solution000003.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_4_3_1-solution000004.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_4_3_1-solution000005.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_4_3_1-solution000006.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_4_3_1.eprime delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_4_3_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_4_3_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_4_3_2-solution000003.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_4_3_2-solution000004.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_4_3_2-solution000005.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_4_3_2-solution000006.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_4_3_2.eprime delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_4_3_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_4_3_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_4_3_3-solution000003.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_4_3_3-solution000004.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_4_3_3-solution000005.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_4_3_3-solution000006.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_4_3_3.eprime delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_4_3_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_4_3_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_4_3_4-solution000003.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_4_3_4-solution000004.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_4_3_4-solution000005.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_4_3_4-solution000006.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_4_3_4.eprime delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_4_4_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_4_4_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_4_4_1-solution000003.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_4_4_1-solution000004.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_4_4_1-solution000005.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_4_4_1-solution000006.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_4_4_1.eprime delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_4_4_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_4_4_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_4_4_2-solution000003.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_4_4_2-solution000004.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_4_4_2-solution000005.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_4_4_2-solution000006.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_4_4_2.eprime delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_4_4_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_4_4_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_4_4_3-solution000003.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_4_4_3-solution000004.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_4_4_3-solution000005.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_4_4_3-solution000006.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_4_4_3.eprime delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_4_4_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_4_4_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_4_4_4-solution000003.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_4_4_4-solution000004.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_4_4_4-solution000005.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_4_4_4-solution000006.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_4_4_4.eprime delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_1_1_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_1_1_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_1_1_1.eprime delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_1_1_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_1_1_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_1_1_2.eprime delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_1_1_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_1_1_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_1_1_3.eprime delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_1_1_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_1_1_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_1_1_4.eprime delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_1_2_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_1_2_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_1_2_1.eprime delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_1_2_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_1_2_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_1_2_2.eprime delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_1_2_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_1_2_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_1_2_3.eprime delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_1_2_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_1_2_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_1_2_4.eprime delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_1_3_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_1_3_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_1_3_1.eprime delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_1_3_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_1_3_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_1_3_2.eprime delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_1_3_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_1_3_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_1_3_3.eprime delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_1_3_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_1_3_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_1_3_4.eprime delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_1_4_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_1_4_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_1_4_1.eprime delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_1_4_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_1_4_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_1_4_2.eprime delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_1_4_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_1_4_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_1_4_3.eprime delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_1_4_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_1_4_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_1_4_4.eprime delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_2_1_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_2_1_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_2_1_1.eprime delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_2_1_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_2_1_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_2_1_2.eprime delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_2_1_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_2_1_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_2_1_3.eprime delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_2_1_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_2_1_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_2_1_4.eprime delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_2_2_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_2_2_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_2_2_1.eprime delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_2_2_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_2_2_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_2_2_2.eprime delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_2_2_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_2_2_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_2_2_3.eprime delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_2_2_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_2_2_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_2_2_4.eprime delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_2_3_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_2_3_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_2_3_1.eprime delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_2_3_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_2_3_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_2_3_2.eprime delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_2_3_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_2_3_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_2_3_3.eprime delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_2_3_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_2_3_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_2_3_4.eprime delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_2_4_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_2_4_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_2_4_1.eprime delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_2_4_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_2_4_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_2_4_2.eprime delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_2_4_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_2_4_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_2_4_3.eprime delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_2_4_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_2_4_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_2_4_4.eprime delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_3_1_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_3_1_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_3_1_1.eprime delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_3_1_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_3_1_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_3_1_2.eprime delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_3_1_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_3_1_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_3_1_3.eprime delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_3_1_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_3_1_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_3_1_4.eprime delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_3_2_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_3_2_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_3_2_1.eprime delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_3_2_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_3_2_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_3_2_2.eprime delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_3_2_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_3_2_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_3_2_3.eprime delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_3_2_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_3_2_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_3_2_4.eprime delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_3_3_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_3_3_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_3_3_1.eprime delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_3_3_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_3_3_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_3_3_2.eprime delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_3_3_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_3_3_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_3_3_3.eprime delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_3_3_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_3_3_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_3_3_4.eprime delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_3_4_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_3_4_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_3_4_1.eprime delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_3_4_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_3_4_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_3_4_2.eprime delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_3_4_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_3_4_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_3_4_3.eprime delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_3_4_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_3_4_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_3_4_4.eprime delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_4_1_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_4_1_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_4_1_1.eprime delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_4_1_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_4_1_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_4_1_2.eprime delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_4_1_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_4_1_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_4_1_3.eprime delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_4_1_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_4_1_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_4_1_4.eprime delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_4_2_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_4_2_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_4_2_1.eprime delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_4_2_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_4_2_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_4_2_2.eprime delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_4_2_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_4_2_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_4_2_3.eprime delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_4_2_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_4_2_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_4_2_4.eprime delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_4_3_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_4_3_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_4_3_1.eprime delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_4_3_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_4_3_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_4_3_2.eprime delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_4_3_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_4_3_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_4_3_3.eprime delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_4_3_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_4_3_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_4_3_4.eprime delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_4_4_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_4_4_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_4_4_1.eprime delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_4_4_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_4_4_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_4_4_2.eprime delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_4_4_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_4_4_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_4_4_3.eprime delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_4_4_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_4_4_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/set_card_00/expected/model_4_4_4.eprime delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_1_1_1_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_1_1_1_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_1_1_1_1-solution000003.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_1_1_1_1-solution000004.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_1_1_1_1-solution000005.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_1_1_1_1-solution000006.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_1_1_1_1-solution000007.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_1_1_1_1-solution000008.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_1_1_1_1-solution000009.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_1_1_1_1-solution000010.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_1_1_1_1-solution000011.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_1_1_1_1-solution000012.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_1_1_1_1.eprime delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_1_1_1_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_1_1_1_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_1_1_1_2-solution000003.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_1_1_1_2-solution000004.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_1_1_1_2-solution000005.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_1_1_1_2-solution000006.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_1_1_1_2-solution000007.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_1_1_1_2-solution000008.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_1_1_1_2-solution000009.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_1_1_1_2-solution000010.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_1_1_1_2-solution000011.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_1_1_1_2-solution000012.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_1_1_1_2.eprime delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_1_1_2_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_1_1_2_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_1_1_2_1-solution000003.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_1_1_2_1-solution000004.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_1_1_2_1-solution000005.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_1_1_2_1-solution000006.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_1_1_2_1-solution000007.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_1_1_2_1-solution000008.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_1_1_2_1-solution000009.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_1_1_2_1-solution000010.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_1_1_2_1-solution000011.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_1_1_2_1-solution000012.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_1_1_2_1.eprime delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_1_1_2_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_1_1_2_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_1_1_2_2-solution000003.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_1_1_2_2-solution000004.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_1_1_2_2-solution000005.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_1_1_2_2-solution000006.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_1_1_2_2-solution000007.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_1_1_2_2-solution000008.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_1_1_2_2-solution000009.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_1_1_2_2-solution000010.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_1_1_2_2-solution000011.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_1_1_2_2-solution000012.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_1_1_2_2.eprime delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_1_2_1_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_1_2_1_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_1_2_1_1-solution000003.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_1_2_1_1-solution000004.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_1_2_1_1-solution000005.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_1_2_1_1-solution000006.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_1_2_1_1-solution000007.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_1_2_1_1-solution000008.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_1_2_1_1-solution000009.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_1_2_1_1-solution000010.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_1_2_1_1-solution000011.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_1_2_1_1-solution000012.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_1_2_1_1.eprime delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_1_2_1_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_1_2_1_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_1_2_1_2-solution000003.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_1_2_1_2-solution000004.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_1_2_1_2-solution000005.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_1_2_1_2-solution000006.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_1_2_1_2-solution000007.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_1_2_1_2-solution000008.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_1_2_1_2-solution000009.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_1_2_1_2-solution000010.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_1_2_1_2-solution000011.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_1_2_1_2-solution000012.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_1_2_1_2.eprime delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_1_2_2_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_1_2_2_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_1_2_2_1-solution000003.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_1_2_2_1-solution000004.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_1_2_2_1-solution000005.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_1_2_2_1-solution000006.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_1_2_2_1-solution000007.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_1_2_2_1-solution000008.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_1_2_2_1-solution000009.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_1_2_2_1-solution000010.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_1_2_2_1-solution000011.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_1_2_2_1-solution000012.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_1_2_2_1.eprime delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_1_2_2_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_1_2_2_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_1_2_2_2-solution000003.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_1_2_2_2-solution000004.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_1_2_2_2-solution000005.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_1_2_2_2-solution000006.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_1_2_2_2-solution000007.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_1_2_2_2-solution000008.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_1_2_2_2-solution000009.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_1_2_2_2-solution000010.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_1_2_2_2-solution000011.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_1_2_2_2-solution000012.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_1_2_2_2.eprime delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_2_1_1_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_2_1_1_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_2_1_1_1-solution000003.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_2_1_1_1-solution000004.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_2_1_1_1-solution000005.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_2_1_1_1-solution000006.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_2_1_1_1-solution000007.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_2_1_1_1-solution000008.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_2_1_1_1-solution000009.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_2_1_1_1-solution000010.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_2_1_1_1-solution000011.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_2_1_1_1-solution000012.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_2_1_1_1.eprime delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_2_1_1_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_2_1_1_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_2_1_1_2-solution000003.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_2_1_1_2-solution000004.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_2_1_1_2-solution000005.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_2_1_1_2-solution000006.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_2_1_1_2-solution000007.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_2_1_1_2-solution000008.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_2_1_1_2-solution000009.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_2_1_1_2-solution000010.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_2_1_1_2-solution000011.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_2_1_1_2-solution000012.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_2_1_1_2.eprime delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_2_1_2_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_2_1_2_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_2_1_2_1-solution000003.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_2_1_2_1-solution000004.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_2_1_2_1-solution000005.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_2_1_2_1-solution000006.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_2_1_2_1-solution000007.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_2_1_2_1-solution000008.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_2_1_2_1-solution000009.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_2_1_2_1-solution000010.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_2_1_2_1-solution000011.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_2_1_2_1-solution000012.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_2_1_2_1.eprime delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_2_1_2_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_2_1_2_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_2_1_2_2-solution000003.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_2_1_2_2-solution000004.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_2_1_2_2-solution000005.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_2_1_2_2-solution000006.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_2_1_2_2-solution000007.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_2_1_2_2-solution000008.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_2_1_2_2-solution000009.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_2_1_2_2-solution000010.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_2_1_2_2-solution000011.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_2_1_2_2-solution000012.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_2_1_2_2.eprime delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_2_2_1_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_2_2_1_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_2_2_1_1-solution000003.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_2_2_1_1-solution000004.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_2_2_1_1-solution000005.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_2_2_1_1-solution000006.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_2_2_1_1-solution000007.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_2_2_1_1-solution000008.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_2_2_1_1-solution000009.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_2_2_1_1-solution000010.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_2_2_1_1-solution000011.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_2_2_1_1-solution000012.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_2_2_1_1.eprime delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_2_2_1_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_2_2_1_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_2_2_1_2-solution000003.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_2_2_1_2-solution000004.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_2_2_1_2-solution000005.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_2_2_1_2-solution000006.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_2_2_1_2-solution000007.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_2_2_1_2-solution000008.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_2_2_1_2-solution000009.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_2_2_1_2-solution000010.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_2_2_1_2-solution000011.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_2_2_1_2-solution000012.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_2_2_1_2.eprime delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_2_2_2_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_2_2_2_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_2_2_2_1-solution000003.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_2_2_2_1-solution000004.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_2_2_2_1-solution000005.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_2_2_2_1-solution000006.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_2_2_2_1-solution000007.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_2_2_2_1-solution000008.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_2_2_2_1-solution000009.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_2_2_2_1-solution000010.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_2_2_2_1-solution000011.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_2_2_2_1-solution000012.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_2_2_2_1.eprime delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_2_2_2_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_2_2_2_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_2_2_2_2-solution000003.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_2_2_2_2-solution000004.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_2_2_2_2-solution000005.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_2_2_2_2-solution000006.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_2_2_2_2-solution000007.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_2_2_2_2-solution000008.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_2_2_2_2-solution000009.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_2_2_2_2-solution000010.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_2_2_2_2-solution000011.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_2_2_2_2-solution000012.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_1_2_2_2_2.eprime delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_1_1_1_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_1_1_1_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_1_1_1_1-solution000003.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_1_1_1_1-solution000004.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_1_1_1_1-solution000005.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_1_1_1_1-solution000006.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_1_1_1_1-solution000007.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_1_1_1_1-solution000008.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_1_1_1_1-solution000009.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_1_1_1_1-solution000010.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_1_1_1_1-solution000011.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_1_1_1_1-solution000012.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_1_1_1_1.eprime delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_1_1_1_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_1_1_1_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_1_1_1_2-solution000003.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_1_1_1_2-solution000004.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_1_1_1_2-solution000005.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_1_1_1_2-solution000006.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_1_1_1_2-solution000007.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_1_1_1_2-solution000008.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_1_1_1_2-solution000009.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_1_1_1_2-solution000010.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_1_1_1_2-solution000011.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_1_1_1_2-solution000012.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_1_1_1_2.eprime delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_1_1_2_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_1_1_2_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_1_1_2_1-solution000003.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_1_1_2_1-solution000004.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_1_1_2_1-solution000005.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_1_1_2_1-solution000006.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_1_1_2_1-solution000007.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_1_1_2_1-solution000008.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_1_1_2_1-solution000009.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_1_1_2_1-solution000010.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_1_1_2_1-solution000011.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_1_1_2_1-solution000012.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_1_1_2_1.eprime delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_1_1_2_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_1_1_2_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_1_1_2_2-solution000003.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_1_1_2_2-solution000004.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_1_1_2_2-solution000005.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_1_1_2_2-solution000006.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_1_1_2_2-solution000007.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_1_1_2_2-solution000008.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_1_1_2_2-solution000009.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_1_1_2_2-solution000010.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_1_1_2_2-solution000011.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_1_1_2_2-solution000012.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_1_1_2_2.eprime delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_1_2_1_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_1_2_1_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_1_2_1_1-solution000003.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_1_2_1_1-solution000004.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_1_2_1_1-solution000005.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_1_2_1_1-solution000006.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_1_2_1_1-solution000007.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_1_2_1_1-solution000008.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_1_2_1_1-solution000009.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_1_2_1_1-solution000010.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_1_2_1_1-solution000011.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_1_2_1_1-solution000012.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_1_2_1_1.eprime delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_1_2_1_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_1_2_1_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_1_2_1_2-solution000003.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_1_2_1_2-solution000004.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_1_2_1_2-solution000005.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_1_2_1_2-solution000006.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_1_2_1_2-solution000007.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_1_2_1_2-solution000008.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_1_2_1_2-solution000009.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_1_2_1_2-solution000010.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_1_2_1_2-solution000011.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_1_2_1_2-solution000012.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_1_2_1_2.eprime delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_1_2_2_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_1_2_2_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_1_2_2_1-solution000003.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_1_2_2_1-solution000004.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_1_2_2_1-solution000005.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_1_2_2_1-solution000006.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_1_2_2_1-solution000007.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_1_2_2_1-solution000008.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_1_2_2_1-solution000009.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_1_2_2_1-solution000010.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_1_2_2_1-solution000011.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_1_2_2_1-solution000012.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_1_2_2_1.eprime delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_1_2_2_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_1_2_2_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_1_2_2_2-solution000003.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_1_2_2_2-solution000004.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_1_2_2_2-solution000005.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_1_2_2_2-solution000006.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_1_2_2_2-solution000007.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_1_2_2_2-solution000008.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_1_2_2_2-solution000009.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_1_2_2_2-solution000010.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_1_2_2_2-solution000011.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_1_2_2_2-solution000012.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_1_2_2_2.eprime delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_2_1_1_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_2_1_1_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_2_1_1_1-solution000003.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_2_1_1_1-solution000004.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_2_1_1_1-solution000005.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_2_1_1_1-solution000006.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_2_1_1_1-solution000007.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_2_1_1_1-solution000008.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_2_1_1_1-solution000009.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_2_1_1_1-solution000010.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_2_1_1_1-solution000011.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_2_1_1_1-solution000012.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_2_1_1_1.eprime delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_2_1_1_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_2_1_1_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_2_1_1_2-solution000003.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_2_1_1_2-solution000004.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_2_1_1_2-solution000005.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_2_1_1_2-solution000006.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_2_1_1_2-solution000007.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_2_1_1_2-solution000008.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_2_1_1_2-solution000009.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_2_1_1_2-solution000010.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_2_1_1_2-solution000011.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_2_1_1_2-solution000012.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_2_1_1_2.eprime delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_2_1_2_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_2_1_2_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_2_1_2_1-solution000003.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_2_1_2_1-solution000004.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_2_1_2_1-solution000005.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_2_1_2_1-solution000006.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_2_1_2_1-solution000007.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_2_1_2_1-solution000008.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_2_1_2_1-solution000009.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_2_1_2_1-solution000010.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_2_1_2_1-solution000011.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_2_1_2_1-solution000012.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_2_1_2_1.eprime delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_2_1_2_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_2_1_2_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_2_1_2_2-solution000003.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_2_1_2_2-solution000004.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_2_1_2_2-solution000005.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_2_1_2_2-solution000006.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_2_1_2_2-solution000007.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_2_1_2_2-solution000008.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_2_1_2_2-solution000009.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_2_1_2_2-solution000010.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_2_1_2_2-solution000011.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_2_1_2_2-solution000012.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_2_1_2_2.eprime delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_2_2_1_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_2_2_1_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_2_2_1_1-solution000003.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_2_2_1_1-solution000004.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_2_2_1_1-solution000005.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_2_2_1_1-solution000006.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_2_2_1_1-solution000007.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_2_2_1_1-solution000008.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_2_2_1_1-solution000009.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_2_2_1_1-solution000010.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_2_2_1_1-solution000011.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_2_2_1_1-solution000012.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_2_2_1_1.eprime delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_2_2_1_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_2_2_1_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_2_2_1_2-solution000003.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_2_2_1_2-solution000004.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_2_2_1_2-solution000005.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_2_2_1_2-solution000006.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_2_2_1_2-solution000007.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_2_2_1_2-solution000008.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_2_2_1_2-solution000009.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_2_2_1_2-solution000010.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_2_2_1_2-solution000011.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_2_2_1_2-solution000012.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_2_2_1_2.eprime delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_2_2_2_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_2_2_2_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_2_2_2_1-solution000003.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_2_2_2_1-solution000004.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_2_2_2_1-solution000005.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_2_2_2_1-solution000006.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_2_2_2_1-solution000007.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_2_2_2_1-solution000008.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_2_2_2_1-solution000009.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_2_2_2_1-solution000010.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_2_2_2_1-solution000011.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_2_2_2_1-solution000012.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_2_2_2_1.eprime delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_2_2_2_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_2_2_2_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_2_2_2_2-solution000003.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_2_2_2_2-solution000004.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_2_2_2_2-solution000005.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_2_2_2_2-solution000006.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_2_2_2_2-solution000007.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_2_2_2_2-solution000008.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_2_2_2_2-solution000009.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_2_2_2_2-solution000010.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_2_2_2_2-solution000011.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_2_2_2_2-solution000012.solution delete mode 100644 tests/exhaustive/basic/streamline01/expected/model_2_2_2_2_2.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_1_1_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_1_1_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_1_1_1-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_1_1_1.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_1_1_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_1_1_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_1_1_2-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_1_1_2.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_1_1_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_1_1_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_1_1_3-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_1_1_3.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_1_1_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_1_1_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_1_1_4-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_1_1_4.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_1_2_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_1_2_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_1_2_1-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_1_2_1.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_1_2_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_1_2_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_1_2_2-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_1_2_2.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_1_2_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_1_2_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_1_2_3-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_1_2_3.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_1_2_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_1_2_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_1_2_4-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_1_2_4.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_1_3_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_1_3_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_1_3_1-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_1_3_1.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_1_3_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_1_3_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_1_3_2-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_1_3_2.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_1_3_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_1_3_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_1_3_3-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_1_3_3.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_1_3_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_1_3_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_1_3_4-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_1_3_4.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_1_4_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_1_4_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_1_4_1-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_1_4_1.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_1_4_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_1_4_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_1_4_2-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_1_4_2.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_1_4_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_1_4_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_1_4_3-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_1_4_3.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_1_4_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_1_4_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_1_4_4-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_1_4_4.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_2_1_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_2_1_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_2_1_1-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_2_1_1.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_2_1_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_2_1_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_2_1_2-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_2_1_2.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_2_1_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_2_1_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_2_1_3-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_2_1_3.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_2_1_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_2_1_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_2_1_4-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_2_1_4.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_2_2_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_2_2_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_2_2_1-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_2_2_1.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_2_2_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_2_2_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_2_2_2-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_2_2_2.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_2_2_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_2_2_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_2_2_3-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_2_2_3.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_2_2_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_2_2_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_2_2_4-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_2_2_4.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_2_3_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_2_3_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_2_3_1-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_2_3_1.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_2_3_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_2_3_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_2_3_2-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_2_3_2.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_2_3_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_2_3_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_2_3_3-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_2_3_3.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_2_3_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_2_3_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_2_3_4-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_2_3_4.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_2_4_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_2_4_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_2_4_1-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_2_4_1.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_2_4_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_2_4_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_2_4_2-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_2_4_2.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_2_4_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_2_4_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_2_4_3-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_2_4_3.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_2_4_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_2_4_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_2_4_4-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_2_4_4.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_3_1_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_3_1_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_3_1_1-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_3_1_1.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_3_1_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_3_1_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_3_1_2-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_3_1_2.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_3_1_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_3_1_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_3_1_3-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_3_1_3.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_3_1_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_3_1_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_3_1_4-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_3_1_4.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_3_2_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_3_2_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_3_2_1-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_3_2_1.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_3_2_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_3_2_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_3_2_2-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_3_2_2.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_3_2_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_3_2_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_3_2_3-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_3_2_3.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_3_2_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_3_2_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_3_2_4-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_3_2_4.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_3_3_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_3_3_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_3_3_1-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_3_3_1.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_3_3_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_3_3_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_3_3_2-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_3_3_2.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_3_3_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_3_3_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_3_3_3-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_3_3_3.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_3_3_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_3_3_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_3_3_4-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_3_3_4.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_3_4_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_3_4_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_3_4_1-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_3_4_1.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_3_4_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_3_4_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_3_4_2-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_3_4_2.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_3_4_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_3_4_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_3_4_3-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_3_4_3.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_3_4_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_3_4_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_3_4_4-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_3_4_4.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_4_1_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_4_1_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_4_1_1-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_4_1_1.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_4_1_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_4_1_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_4_1_2-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_4_1_2.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_4_1_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_4_1_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_4_1_3-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_4_1_3.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_4_1_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_4_1_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_4_1_4-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_4_1_4.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_4_2_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_4_2_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_4_2_1-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_4_2_1.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_4_2_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_4_2_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_4_2_2-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_4_2_2.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_4_2_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_4_2_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_4_2_3-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_4_2_3.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_4_2_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_4_2_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_4_2_4-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_4_2_4.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_4_3_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_4_3_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_4_3_1-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_4_3_1.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_4_3_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_4_3_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_4_3_2-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_4_3_2.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_4_3_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_4_3_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_4_3_3-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_4_3_3.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_4_3_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_4_3_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_4_3_4-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_4_3_4.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_4_4_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_4_4_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_4_4_1-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_4_4_1.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_4_4_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_4_4_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_4_4_2-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_4_4_2.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_4_4_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_4_4_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_4_4_3-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_4_4_3.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_4_4_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_4_4_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_4_4_4-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_1_4_4_4.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_1_1_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_1_1_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_1_1_1-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_1_1_1.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_1_1_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_1_1_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_1_1_2-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_1_1_2.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_1_1_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_1_1_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_1_1_3-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_1_1_3.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_1_1_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_1_1_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_1_1_4-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_1_1_4.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_1_2_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_1_2_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_1_2_1-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_1_2_1.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_1_2_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_1_2_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_1_2_2-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_1_2_2.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_1_2_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_1_2_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_1_2_3-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_1_2_3.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_1_2_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_1_2_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_1_2_4-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_1_2_4.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_1_3_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_1_3_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_1_3_1-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_1_3_1.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_1_3_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_1_3_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_1_3_2-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_1_3_2.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_1_3_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_1_3_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_1_3_3-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_1_3_3.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_1_3_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_1_3_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_1_3_4-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_1_3_4.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_1_4_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_1_4_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_1_4_1-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_1_4_1.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_1_4_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_1_4_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_1_4_2-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_1_4_2.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_1_4_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_1_4_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_1_4_3-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_1_4_3.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_1_4_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_1_4_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_1_4_4-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_1_4_4.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_2_1_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_2_1_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_2_1_1-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_2_1_1.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_2_1_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_2_1_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_2_1_2-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_2_1_2.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_2_1_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_2_1_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_2_1_3-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_2_1_3.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_2_1_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_2_1_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_2_1_4-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_2_1_4.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_2_2_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_2_2_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_2_2_1-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_2_2_1.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_2_2_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_2_2_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_2_2_2-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_2_2_2.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_2_2_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_2_2_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_2_2_3-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_2_2_3.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_2_2_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_2_2_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_2_2_4-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_2_2_4.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_2_3_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_2_3_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_2_3_1-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_2_3_1.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_2_3_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_2_3_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_2_3_2-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_2_3_2.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_2_3_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_2_3_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_2_3_3-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_2_3_3.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_2_3_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_2_3_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_2_3_4-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_2_3_4.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_2_4_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_2_4_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_2_4_1-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_2_4_1.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_2_4_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_2_4_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_2_4_2-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_2_4_2.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_2_4_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_2_4_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_2_4_3-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_2_4_3.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_2_4_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_2_4_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_2_4_4-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_2_4_4.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_3_1_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_3_1_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_3_1_1-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_3_1_1.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_3_1_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_3_1_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_3_1_2-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_3_1_2.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_3_1_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_3_1_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_3_1_3-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_3_1_3.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_3_1_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_3_1_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_3_1_4-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_3_1_4.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_3_2_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_3_2_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_3_2_1-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_3_2_1.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_3_2_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_3_2_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_3_2_2-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_3_2_2.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_3_2_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_3_2_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_3_2_3-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_3_2_3.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_3_2_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_3_2_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_3_2_4-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_3_2_4.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_3_3_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_3_3_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_3_3_1-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_3_3_1.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_3_3_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_3_3_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_3_3_2-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_3_3_2.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_3_3_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_3_3_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_3_3_3-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_3_3_3.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_3_3_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_3_3_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_3_3_4-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_3_3_4.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_3_4_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_3_4_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_3_4_1-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_3_4_1.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_3_4_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_3_4_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_3_4_2-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_3_4_2.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_3_4_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_3_4_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_3_4_3-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_3_4_3.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_3_4_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_3_4_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_3_4_4-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_3_4_4.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_4_1_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_4_1_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_4_1_1-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_4_1_1.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_4_1_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_4_1_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_4_1_2-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_4_1_2.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_4_1_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_4_1_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_4_1_3-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_4_1_3.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_4_1_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_4_1_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_4_1_4-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_4_1_4.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_4_2_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_4_2_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_4_2_1-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_4_2_1.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_4_2_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_4_2_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_4_2_2-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_4_2_2.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_4_2_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_4_2_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_4_2_3-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_4_2_3.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_4_2_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_4_2_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_4_2_4-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_4_2_4.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_4_3_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_4_3_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_4_3_1-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_4_3_1.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_4_3_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_4_3_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_4_3_2-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_4_3_2.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_4_3_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_4_3_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_4_3_3-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_4_3_3.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_4_3_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_4_3_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_4_3_4-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_4_3_4.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_4_4_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_4_4_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_4_4_1-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_4_4_1.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_4_4_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_4_4_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_4_4_2-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_4_4_2.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_4_4_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_4_4_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_4_4_3-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_4_4_3.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_4_4_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_4_4_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_4_4_4-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_2_4_4_4.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_1_1_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_1_1_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_1_1_1-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_1_1_1.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_1_1_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_1_1_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_1_1_2-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_1_1_2.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_1_1_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_1_1_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_1_1_3-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_1_1_3.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_1_1_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_1_1_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_1_1_4-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_1_1_4.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_1_2_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_1_2_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_1_2_1-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_1_2_1.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_1_2_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_1_2_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_1_2_2-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_1_2_2.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_1_2_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_1_2_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_1_2_3-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_1_2_3.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_1_2_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_1_2_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_1_2_4-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_1_2_4.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_1_3_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_1_3_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_1_3_1-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_1_3_1.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_1_3_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_1_3_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_1_3_2-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_1_3_2.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_1_3_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_1_3_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_1_3_3-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_1_3_3.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_1_3_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_1_3_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_1_3_4-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_1_3_4.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_1_4_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_1_4_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_1_4_1-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_1_4_1.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_1_4_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_1_4_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_1_4_2-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_1_4_2.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_1_4_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_1_4_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_1_4_3-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_1_4_3.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_1_4_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_1_4_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_1_4_4-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_1_4_4.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_2_1_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_2_1_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_2_1_1-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_2_1_1.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_2_1_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_2_1_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_2_1_2-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_2_1_2.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_2_1_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_2_1_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_2_1_3-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_2_1_3.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_2_1_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_2_1_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_2_1_4-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_2_1_4.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_2_2_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_2_2_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_2_2_1-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_2_2_1.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_2_2_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_2_2_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_2_2_2-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_2_2_2.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_2_2_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_2_2_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_2_2_3-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_2_2_3.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_2_2_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_2_2_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_2_2_4-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_2_2_4.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_2_3_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_2_3_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_2_3_1-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_2_3_1.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_2_3_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_2_3_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_2_3_2-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_2_3_2.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_2_3_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_2_3_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_2_3_3-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_2_3_3.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_2_3_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_2_3_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_2_3_4-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_2_3_4.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_2_4_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_2_4_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_2_4_1-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_2_4_1.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_2_4_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_2_4_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_2_4_2-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_2_4_2.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_2_4_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_2_4_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_2_4_3-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_2_4_3.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_2_4_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_2_4_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_2_4_4-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_2_4_4.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_3_1_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_3_1_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_3_1_1-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_3_1_1.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_3_1_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_3_1_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_3_1_2-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_3_1_2.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_3_1_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_3_1_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_3_1_3-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_3_1_3.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_3_1_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_3_1_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_3_1_4-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_3_1_4.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_3_2_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_3_2_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_3_2_1-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_3_2_1.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_3_2_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_3_2_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_3_2_2-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_3_2_2.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_3_2_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_3_2_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_3_2_3-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_3_2_3.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_3_2_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_3_2_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_3_2_4-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_3_2_4.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_3_3_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_3_3_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_3_3_1-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_3_3_1.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_3_3_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_3_3_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_3_3_2-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_3_3_2.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_3_3_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_3_3_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_3_3_3-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_3_3_3.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_3_3_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_3_3_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_3_3_4-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_3_3_4.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_3_4_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_3_4_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_3_4_1-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_3_4_1.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_3_4_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_3_4_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_3_4_2-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_3_4_2.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_3_4_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_3_4_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_3_4_3-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_3_4_3.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_3_4_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_3_4_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_3_4_4-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_3_4_4.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_4_1_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_4_1_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_4_1_1-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_4_1_1.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_4_1_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_4_1_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_4_1_2-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_4_1_2.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_4_1_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_4_1_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_4_1_3-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_4_1_3.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_4_1_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_4_1_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_4_1_4-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_4_1_4.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_4_2_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_4_2_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_4_2_1-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_4_2_1.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_4_2_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_4_2_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_4_2_2-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_4_2_2.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_4_2_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_4_2_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_4_2_3-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_4_2_3.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_4_2_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_4_2_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_4_2_4-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_4_2_4.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_4_3_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_4_3_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_4_3_1-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_4_3_1.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_4_3_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_4_3_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_4_3_2-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_4_3_2.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_4_3_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_4_3_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_4_3_3-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_4_3_3.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_4_3_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_4_3_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_4_3_4-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_4_3_4.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_4_4_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_4_4_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_4_4_1-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_4_4_1.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_4_4_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_4_4_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_4_4_2-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_4_4_2.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_4_4_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_4_4_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_4_4_3-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_4_4_3.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_4_4_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_4_4_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_4_4_4-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_3_4_4_4.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_1_1_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_1_1_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_1_1_1-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_1_1_1.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_1_1_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_1_1_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_1_1_2-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_1_1_2.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_1_1_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_1_1_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_1_1_3-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_1_1_3.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_1_1_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_1_1_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_1_1_4-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_1_1_4.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_1_2_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_1_2_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_1_2_1-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_1_2_1.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_1_2_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_1_2_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_1_2_2-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_1_2_2.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_1_2_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_1_2_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_1_2_3-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_1_2_3.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_1_2_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_1_2_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_1_2_4-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_1_2_4.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_1_3_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_1_3_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_1_3_1-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_1_3_1.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_1_3_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_1_3_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_1_3_2-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_1_3_2.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_1_3_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_1_3_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_1_3_3-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_1_3_3.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_1_3_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_1_3_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_1_3_4-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_1_3_4.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_1_4_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_1_4_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_1_4_1-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_1_4_1.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_1_4_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_1_4_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_1_4_2-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_1_4_2.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_1_4_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_1_4_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_1_4_3-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_1_4_3.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_1_4_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_1_4_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_1_4_4-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_1_4_4.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_2_1_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_2_1_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_2_1_1-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_2_1_1.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_2_1_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_2_1_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_2_1_2-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_2_1_2.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_2_1_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_2_1_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_2_1_3-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_2_1_3.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_2_1_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_2_1_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_2_1_4-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_2_1_4.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_2_2_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_2_2_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_2_2_1-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_2_2_1.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_2_2_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_2_2_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_2_2_2-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_2_2_2.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_2_2_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_2_2_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_2_2_3-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_2_2_3.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_2_2_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_2_2_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_2_2_4-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_2_2_4.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_2_3_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_2_3_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_2_3_1-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_2_3_1.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_2_3_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_2_3_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_2_3_2-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_2_3_2.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_2_3_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_2_3_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_2_3_3-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_2_3_3.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_2_3_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_2_3_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_2_3_4-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_2_3_4.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_2_4_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_2_4_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_2_4_1-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_2_4_1.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_2_4_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_2_4_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_2_4_2-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_2_4_2.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_2_4_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_2_4_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_2_4_3-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_2_4_3.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_2_4_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_2_4_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_2_4_4-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_2_4_4.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_3_1_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_3_1_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_3_1_1-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_3_1_1.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_3_1_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_3_1_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_3_1_2-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_3_1_2.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_3_1_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_3_1_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_3_1_3-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_3_1_3.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_3_1_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_3_1_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_3_1_4-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_3_1_4.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_3_2_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_3_2_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_3_2_1-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_3_2_1.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_3_2_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_3_2_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_3_2_2-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_3_2_2.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_3_2_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_3_2_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_3_2_3-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_3_2_3.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_3_2_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_3_2_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_3_2_4-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_3_2_4.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_3_3_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_3_3_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_3_3_1-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_3_3_1.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_3_3_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_3_3_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_3_3_2-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_3_3_2.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_3_3_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_3_3_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_3_3_3-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_3_3_3.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_3_3_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_3_3_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_3_3_4-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_3_3_4.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_3_4_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_3_4_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_3_4_1-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_3_4_1.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_3_4_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_3_4_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_3_4_2-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_3_4_2.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_3_4_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_3_4_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_3_4_3-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_3_4_3.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_3_4_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_3_4_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_3_4_4-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_3_4_4.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_4_1_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_4_1_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_4_1_1-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_4_1_1.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_4_1_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_4_1_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_4_1_2-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_4_1_2.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_4_1_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_4_1_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_4_1_3-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_4_1_3.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_4_1_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_4_1_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_4_1_4-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_4_1_4.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_4_2_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_4_2_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_4_2_1-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_4_2_1.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_4_2_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_4_2_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_4_2_2-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_4_2_2.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_4_2_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_4_2_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_4_2_3-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_4_2_3.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_4_2_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_4_2_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_4_2_4-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_4_2_4.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_4_3_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_4_3_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_4_3_1-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_4_3_1.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_4_3_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_4_3_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_4_3_2-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_4_3_2.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_4_3_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_4_3_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_4_3_3-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_4_3_3.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_4_3_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_4_3_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_4_3_4-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_4_3_4.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_4_4_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_4_4_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_4_4_1-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_4_4_1.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_4_4_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_4_4_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_4_4_2-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_4_4_2.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_4_4_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_4_4_3-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_4_4_3-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_4_4_3.eprime delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_4_4_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_4_4_4-solution000002.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_4_4_4-solution000003.solution delete mode 100644 tests/exhaustive/basic/typed01/expected/model_4_4_4_4.eprime delete mode 100644 tests/exhaustive/issues/102/expected/model-solution000001.solution delete mode 100644 tests/exhaustive/issues/102/expected/model.eprime delete mode 100644 tests/exhaustive/issues/166/expected/model_1_1-solution000001.solution delete mode 100644 tests/exhaustive/issues/166/expected/model_1_1.eprime delete mode 100644 tests/exhaustive/issues/166/expected/model_1_2-solution000001.solution delete mode 100644 tests/exhaustive/issues/166/expected/model_1_2.eprime delete mode 100644 tests/exhaustive/issues/166/expected/model_1_3-solution000001.solution delete mode 100644 tests/exhaustive/issues/166/expected/model_1_3.eprime delete mode 100644 tests/exhaustive/issues/166/expected/model_1_4-solution000001.solution delete mode 100644 tests/exhaustive/issues/166/expected/model_1_4.eprime delete mode 100644 tests/exhaustive/issues/166/expected/model_2_1-solution000001.solution delete mode 100644 tests/exhaustive/issues/166/expected/model_2_1.eprime delete mode 100644 tests/exhaustive/issues/166/expected/model_2_2-solution000001.solution delete mode 100644 tests/exhaustive/issues/166/expected/model_2_2.eprime delete mode 100644 tests/exhaustive/issues/166/expected/model_2_3-solution000001.solution delete mode 100644 tests/exhaustive/issues/166/expected/model_2_3.eprime delete mode 100644 tests/exhaustive/issues/166/expected/model_2_4-solution000001.solution delete mode 100644 tests/exhaustive/issues/166/expected/model_2_4.eprime delete mode 100644 tests/exhaustive/issues/166/expected/model_3_1-solution000001.solution delete mode 100644 tests/exhaustive/issues/166/expected/model_3_1.eprime delete mode 100644 tests/exhaustive/issues/166/expected/model_3_2-solution000001.solution delete mode 100644 tests/exhaustive/issues/166/expected/model_3_2.eprime delete mode 100644 tests/exhaustive/issues/166/expected/model_3_3-solution000001.solution delete mode 100644 tests/exhaustive/issues/166/expected/model_3_3.eprime delete mode 100644 tests/exhaustive/issues/166/expected/model_3_4-solution000001.solution delete mode 100644 tests/exhaustive/issues/166/expected/model_3_4.eprime delete mode 100644 tests/exhaustive/issues/166/expected/model_4_1-solution000001.solution delete mode 100644 tests/exhaustive/issues/166/expected/model_4_1.eprime delete mode 100644 tests/exhaustive/issues/166/expected/model_4_2-solution000001.solution delete mode 100644 tests/exhaustive/issues/166/expected/model_4_2.eprime delete mode 100644 tests/exhaustive/issues/166/expected/model_4_3-solution000001.solution delete mode 100644 tests/exhaustive/issues/166/expected/model_4_3.eprime delete mode 100644 tests/exhaustive/issues/166/expected/model_4_4-solution000001.solution delete mode 100644 tests/exhaustive/issues/166/expected/model_4_4.eprime delete mode 100644 tests/exhaustive/issues/212/expected/model_1_1-1-solution000001.solution delete mode 100644 tests/exhaustive/issues/212/expected/model_1_1-1.eprime-param delete mode 100644 tests/exhaustive/issues/212/expected/model_1_1.eprime delete mode 100644 tests/exhaustive/issues/212/expected/model_1_2-1-solution000001.solution delete mode 100644 tests/exhaustive/issues/212/expected/model_1_2-1.eprime-param delete mode 100644 tests/exhaustive/issues/212/expected/model_1_2.eprime delete mode 100644 tests/exhaustive/issues/212/expected/model_1_3-1-solution000001.solution delete mode 100644 tests/exhaustive/issues/212/expected/model_1_3-1.eprime-param delete mode 100644 tests/exhaustive/issues/212/expected/model_1_3.eprime delete mode 100644 tests/exhaustive/issues/212/expected/model_1_4-1-solution000001.solution delete mode 100644 tests/exhaustive/issues/212/expected/model_1_4-1.eprime-param delete mode 100644 tests/exhaustive/issues/212/expected/model_1_4.eprime delete mode 100644 tests/exhaustive/issues/212/expected/model_2_1-1-solution000001.solution delete mode 100644 tests/exhaustive/issues/212/expected/model_2_1-1.eprime-param delete mode 100644 tests/exhaustive/issues/212/expected/model_2_1.eprime delete mode 100644 tests/exhaustive/issues/212/expected/model_2_2-1-solution000001.solution delete mode 100644 tests/exhaustive/issues/212/expected/model_2_2-1.eprime-param delete mode 100644 tests/exhaustive/issues/212/expected/model_2_2.eprime delete mode 100644 tests/exhaustive/issues/212/expected/model_2_3-1-solution000001.solution delete mode 100644 tests/exhaustive/issues/212/expected/model_2_3-1.eprime-param delete mode 100644 tests/exhaustive/issues/212/expected/model_2_3.eprime delete mode 100644 tests/exhaustive/issues/212/expected/model_2_4-1-solution000001.solution delete mode 100644 tests/exhaustive/issues/212/expected/model_2_4-1.eprime-param delete mode 100644 tests/exhaustive/issues/212/expected/model_2_4.eprime delete mode 100644 tests/exhaustive/issues/212/expected/model_3_1-1-solution000001.solution delete mode 100644 tests/exhaustive/issues/212/expected/model_3_1-1.eprime-param delete mode 100644 tests/exhaustive/issues/212/expected/model_3_1.eprime delete mode 100644 tests/exhaustive/issues/212/expected/model_3_2-1-solution000001.solution delete mode 100644 tests/exhaustive/issues/212/expected/model_3_2-1.eprime-param delete mode 100644 tests/exhaustive/issues/212/expected/model_3_2.eprime delete mode 100644 tests/exhaustive/issues/212/expected/model_3_3-1-solution000001.solution delete mode 100644 tests/exhaustive/issues/212/expected/model_3_3-1.eprime-param delete mode 100644 tests/exhaustive/issues/212/expected/model_3_3.eprime delete mode 100644 tests/exhaustive/issues/212/expected/model_3_4-1-solution000001.solution delete mode 100644 tests/exhaustive/issues/212/expected/model_3_4-1.eprime-param delete mode 100644 tests/exhaustive/issues/212/expected/model_3_4.eprime delete mode 100644 tests/exhaustive/issues/212/expected/model_4_1-1-solution000001.solution delete mode 100644 tests/exhaustive/issues/212/expected/model_4_1-1.eprime-param delete mode 100644 tests/exhaustive/issues/212/expected/model_4_1.eprime delete mode 100644 tests/exhaustive/issues/212/expected/model_4_2-1-solution000001.solution delete mode 100644 tests/exhaustive/issues/212/expected/model_4_2-1.eprime-param delete mode 100644 tests/exhaustive/issues/212/expected/model_4_2.eprime delete mode 100644 tests/exhaustive/issues/212/expected/model_4_3-1-solution000001.solution delete mode 100644 tests/exhaustive/issues/212/expected/model_4_3-1.eprime-param delete mode 100644 tests/exhaustive/issues/212/expected/model_4_3.eprime delete mode 100644 tests/exhaustive/issues/212/expected/model_4_4-1-solution000001.solution delete mode 100644 tests/exhaustive/issues/212/expected/model_4_4-1.eprime-param delete mode 100644 tests/exhaustive/issues/212/expected/model_4_4.eprime delete mode 100644 tests/exhaustive/issues/286/expected/model_1_1-p1-solution000001.solution delete mode 100644 tests/exhaustive/issues/286/expected/model_1_1-p1-solution000002.solution delete mode 100644 tests/exhaustive/issues/286/expected/model_1_1-p1-solution000003.solution delete mode 100644 tests/exhaustive/issues/286/expected/model_1_1-p1-solution000004.solution delete mode 100644 tests/exhaustive/issues/286/expected/model_1_1-p1-solution000005.solution delete mode 100644 tests/exhaustive/issues/286/expected/model_1_1-p1-solution000006.solution delete mode 100644 tests/exhaustive/issues/286/expected/model_1_1-p1-solution000007.solution delete mode 100644 tests/exhaustive/issues/286/expected/model_1_1-p1-solution000008.solution delete mode 100644 tests/exhaustive/issues/286/expected/model_1_1-p1.eprime-param delete mode 100644 tests/exhaustive/issues/286/expected/model_1_1.eprime delete mode 100644 tests/exhaustive/issues/286/expected/model_1_2-p1-solution000001.solution delete mode 100644 tests/exhaustive/issues/286/expected/model_1_2-p1-solution000002.solution delete mode 100644 tests/exhaustive/issues/286/expected/model_1_2-p1-solution000003.solution delete mode 100644 tests/exhaustive/issues/286/expected/model_1_2-p1-solution000004.solution delete mode 100644 tests/exhaustive/issues/286/expected/model_1_2-p1-solution000005.solution delete mode 100644 tests/exhaustive/issues/286/expected/model_1_2-p1-solution000006.solution delete mode 100644 tests/exhaustive/issues/286/expected/model_1_2-p1-solution000007.solution delete mode 100644 tests/exhaustive/issues/286/expected/model_1_2-p1-solution000008.solution delete mode 100644 tests/exhaustive/issues/286/expected/model_1_2-p1.eprime-param delete mode 100644 tests/exhaustive/issues/286/expected/model_1_2.eprime delete mode 100644 tests/exhaustive/issues/286/expected/model_1_3-p1-solution000001.solution delete mode 100644 tests/exhaustive/issues/286/expected/model_1_3-p1-solution000002.solution delete mode 100644 tests/exhaustive/issues/286/expected/model_1_3-p1-solution000003.solution delete mode 100644 tests/exhaustive/issues/286/expected/model_1_3-p1-solution000004.solution delete mode 100644 tests/exhaustive/issues/286/expected/model_1_3-p1-solution000005.solution delete mode 100644 tests/exhaustive/issues/286/expected/model_1_3-p1-solution000006.solution delete mode 100644 tests/exhaustive/issues/286/expected/model_1_3-p1-solution000007.solution delete mode 100644 tests/exhaustive/issues/286/expected/model_1_3-p1-solution000008.solution delete mode 100644 tests/exhaustive/issues/286/expected/model_1_3-p1.eprime-param delete mode 100644 tests/exhaustive/issues/286/expected/model_1_3.eprime delete mode 100644 tests/exhaustive/issues/286/expected/model_1_4-p1-solution000001.solution delete mode 100644 tests/exhaustive/issues/286/expected/model_1_4-p1-solution000002.solution delete mode 100644 tests/exhaustive/issues/286/expected/model_1_4-p1-solution000003.solution delete mode 100644 tests/exhaustive/issues/286/expected/model_1_4-p1-solution000004.solution delete mode 100644 tests/exhaustive/issues/286/expected/model_1_4-p1-solution000005.solution delete mode 100644 tests/exhaustive/issues/286/expected/model_1_4-p1-solution000006.solution delete mode 100644 tests/exhaustive/issues/286/expected/model_1_4-p1-solution000007.solution delete mode 100644 tests/exhaustive/issues/286/expected/model_1_4-p1-solution000008.solution delete mode 100644 tests/exhaustive/issues/286/expected/model_1_4-p1.eprime-param delete mode 100644 tests/exhaustive/issues/286/expected/model_1_4.eprime delete mode 100644 tests/exhaustive/issues/286/expected/model_2_1-p1-solution000001.solution delete mode 100644 tests/exhaustive/issues/286/expected/model_2_1-p1-solution000002.solution delete mode 100644 tests/exhaustive/issues/286/expected/model_2_1-p1-solution000003.solution delete mode 100644 tests/exhaustive/issues/286/expected/model_2_1-p1-solution000004.solution delete mode 100644 tests/exhaustive/issues/286/expected/model_2_1-p1-solution000005.solution delete mode 100644 tests/exhaustive/issues/286/expected/model_2_1-p1-solution000006.solution delete mode 100644 tests/exhaustive/issues/286/expected/model_2_1-p1-solution000007.solution delete mode 100644 tests/exhaustive/issues/286/expected/model_2_1-p1-solution000008.solution delete mode 100644 tests/exhaustive/issues/286/expected/model_2_1-p1.eprime-param delete mode 100644 tests/exhaustive/issues/286/expected/model_2_1.eprime delete mode 100644 tests/exhaustive/issues/286/expected/model_2_2-p1-solution000001.solution delete mode 100644 tests/exhaustive/issues/286/expected/model_2_2-p1-solution000002.solution delete mode 100644 tests/exhaustive/issues/286/expected/model_2_2-p1-solution000003.solution delete mode 100644 tests/exhaustive/issues/286/expected/model_2_2-p1-solution000004.solution delete mode 100644 tests/exhaustive/issues/286/expected/model_2_2-p1-solution000005.solution delete mode 100644 tests/exhaustive/issues/286/expected/model_2_2-p1-solution000006.solution delete mode 100644 tests/exhaustive/issues/286/expected/model_2_2-p1-solution000007.solution delete mode 100644 tests/exhaustive/issues/286/expected/model_2_2-p1-solution000008.solution delete mode 100644 tests/exhaustive/issues/286/expected/model_2_2-p1.eprime-param delete mode 100644 tests/exhaustive/issues/286/expected/model_2_2.eprime delete mode 100644 tests/exhaustive/issues/286/expected/model_2_3-p1-solution000001.solution delete mode 100644 tests/exhaustive/issues/286/expected/model_2_3-p1-solution000002.solution delete mode 100644 tests/exhaustive/issues/286/expected/model_2_3-p1-solution000003.solution delete mode 100644 tests/exhaustive/issues/286/expected/model_2_3-p1-solution000004.solution delete mode 100644 tests/exhaustive/issues/286/expected/model_2_3-p1-solution000005.solution delete mode 100644 tests/exhaustive/issues/286/expected/model_2_3-p1-solution000006.solution delete mode 100644 tests/exhaustive/issues/286/expected/model_2_3-p1-solution000007.solution delete mode 100644 tests/exhaustive/issues/286/expected/model_2_3-p1-solution000008.solution delete mode 100644 tests/exhaustive/issues/286/expected/model_2_3-p1.eprime-param delete mode 100644 tests/exhaustive/issues/286/expected/model_2_3.eprime delete mode 100644 tests/exhaustive/issues/286/expected/model_2_4-p1-solution000001.solution delete mode 100644 tests/exhaustive/issues/286/expected/model_2_4-p1-solution000002.solution delete mode 100644 tests/exhaustive/issues/286/expected/model_2_4-p1-solution000003.solution delete mode 100644 tests/exhaustive/issues/286/expected/model_2_4-p1-solution000004.solution delete mode 100644 tests/exhaustive/issues/286/expected/model_2_4-p1-solution000005.solution delete mode 100644 tests/exhaustive/issues/286/expected/model_2_4-p1-solution000006.solution delete mode 100644 tests/exhaustive/issues/286/expected/model_2_4-p1-solution000007.solution delete mode 100644 tests/exhaustive/issues/286/expected/model_2_4-p1-solution000008.solution delete mode 100644 tests/exhaustive/issues/286/expected/model_2_4-p1.eprime-param delete mode 100644 tests/exhaustive/issues/286/expected/model_2_4.eprime delete mode 100644 tests/exhaustive/issues/286/expected/model_3_1-p1-solution000001.solution delete mode 100644 tests/exhaustive/issues/286/expected/model_3_1-p1-solution000002.solution delete mode 100644 tests/exhaustive/issues/286/expected/model_3_1-p1-solution000003.solution delete mode 100644 tests/exhaustive/issues/286/expected/model_3_1-p1-solution000004.solution delete mode 100644 tests/exhaustive/issues/286/expected/model_3_1-p1-solution000005.solution delete mode 100644 tests/exhaustive/issues/286/expected/model_3_1-p1-solution000006.solution delete mode 100644 tests/exhaustive/issues/286/expected/model_3_1-p1-solution000007.solution delete mode 100644 tests/exhaustive/issues/286/expected/model_3_1-p1-solution000008.solution delete mode 100644 tests/exhaustive/issues/286/expected/model_3_1-p1.eprime-param delete mode 100644 tests/exhaustive/issues/286/expected/model_3_1.eprime delete mode 100644 tests/exhaustive/issues/286/expected/model_3_2-p1-solution000001.solution delete mode 100644 tests/exhaustive/issues/286/expected/model_3_2-p1-solution000002.solution delete mode 100644 tests/exhaustive/issues/286/expected/model_3_2-p1-solution000003.solution delete mode 100644 tests/exhaustive/issues/286/expected/model_3_2-p1-solution000004.solution delete mode 100644 tests/exhaustive/issues/286/expected/model_3_2-p1-solution000005.solution delete mode 100644 tests/exhaustive/issues/286/expected/model_3_2-p1-solution000006.solution delete mode 100644 tests/exhaustive/issues/286/expected/model_3_2-p1-solution000007.solution delete mode 100644 tests/exhaustive/issues/286/expected/model_3_2-p1-solution000008.solution delete mode 100644 tests/exhaustive/issues/286/expected/model_3_2-p1.eprime-param delete mode 100644 tests/exhaustive/issues/286/expected/model_3_2.eprime delete mode 100644 tests/exhaustive/issues/286/expected/model_3_3-p1-solution000001.solution delete mode 100644 tests/exhaustive/issues/286/expected/model_3_3-p1-solution000002.solution delete mode 100644 tests/exhaustive/issues/286/expected/model_3_3-p1-solution000003.solution delete mode 100644 tests/exhaustive/issues/286/expected/model_3_3-p1-solution000004.solution delete mode 100644 tests/exhaustive/issues/286/expected/model_3_3-p1-solution000005.solution delete mode 100644 tests/exhaustive/issues/286/expected/model_3_3-p1-solution000006.solution delete mode 100644 tests/exhaustive/issues/286/expected/model_3_3-p1-solution000007.solution delete mode 100644 tests/exhaustive/issues/286/expected/model_3_3-p1-solution000008.solution delete mode 100644 tests/exhaustive/issues/286/expected/model_3_3-p1.eprime-param delete mode 100644 tests/exhaustive/issues/286/expected/model_3_3.eprime delete mode 100644 tests/exhaustive/issues/286/expected/model_3_4-p1-solution000001.solution delete mode 100644 tests/exhaustive/issues/286/expected/model_3_4-p1-solution000002.solution delete mode 100644 tests/exhaustive/issues/286/expected/model_3_4-p1-solution000003.solution delete mode 100644 tests/exhaustive/issues/286/expected/model_3_4-p1-solution000004.solution delete mode 100644 tests/exhaustive/issues/286/expected/model_3_4-p1-solution000005.solution delete mode 100644 tests/exhaustive/issues/286/expected/model_3_4-p1-solution000006.solution delete mode 100644 tests/exhaustive/issues/286/expected/model_3_4-p1-solution000007.solution delete mode 100644 tests/exhaustive/issues/286/expected/model_3_4-p1-solution000008.solution delete mode 100644 tests/exhaustive/issues/286/expected/model_3_4-p1.eprime-param delete mode 100644 tests/exhaustive/issues/286/expected/model_3_4.eprime delete mode 100644 tests/exhaustive/issues/286/expected/model_4_1-p1-solution000001.solution delete mode 100644 tests/exhaustive/issues/286/expected/model_4_1-p1-solution000002.solution delete mode 100644 tests/exhaustive/issues/286/expected/model_4_1-p1-solution000003.solution delete mode 100644 tests/exhaustive/issues/286/expected/model_4_1-p1-solution000004.solution delete mode 100644 tests/exhaustive/issues/286/expected/model_4_1-p1-solution000005.solution delete mode 100644 tests/exhaustive/issues/286/expected/model_4_1-p1-solution000006.solution delete mode 100644 tests/exhaustive/issues/286/expected/model_4_1-p1-solution000007.solution delete mode 100644 tests/exhaustive/issues/286/expected/model_4_1-p1-solution000008.solution delete mode 100644 tests/exhaustive/issues/286/expected/model_4_1-p1.eprime-param delete mode 100644 tests/exhaustive/issues/286/expected/model_4_1.eprime delete mode 100644 tests/exhaustive/issues/286/expected/model_4_2-p1-solution000001.solution delete mode 100644 tests/exhaustive/issues/286/expected/model_4_2-p1-solution000002.solution delete mode 100644 tests/exhaustive/issues/286/expected/model_4_2-p1-solution000003.solution delete mode 100644 tests/exhaustive/issues/286/expected/model_4_2-p1-solution000004.solution delete mode 100644 tests/exhaustive/issues/286/expected/model_4_2-p1-solution000005.solution delete mode 100644 tests/exhaustive/issues/286/expected/model_4_2-p1-solution000006.solution delete mode 100644 tests/exhaustive/issues/286/expected/model_4_2-p1-solution000007.solution delete mode 100644 tests/exhaustive/issues/286/expected/model_4_2-p1-solution000008.solution delete mode 100644 tests/exhaustive/issues/286/expected/model_4_2-p1.eprime-param delete mode 100644 tests/exhaustive/issues/286/expected/model_4_2.eprime delete mode 100644 tests/exhaustive/issues/286/expected/model_4_3-p1-solution000001.solution delete mode 100644 tests/exhaustive/issues/286/expected/model_4_3-p1-solution000002.solution delete mode 100644 tests/exhaustive/issues/286/expected/model_4_3-p1-solution000003.solution delete mode 100644 tests/exhaustive/issues/286/expected/model_4_3-p1-solution000004.solution delete mode 100644 tests/exhaustive/issues/286/expected/model_4_3-p1-solution000005.solution delete mode 100644 tests/exhaustive/issues/286/expected/model_4_3-p1-solution000006.solution delete mode 100644 tests/exhaustive/issues/286/expected/model_4_3-p1-solution000007.solution delete mode 100644 tests/exhaustive/issues/286/expected/model_4_3-p1-solution000008.solution delete mode 100644 tests/exhaustive/issues/286/expected/model_4_3-p1.eprime-param delete mode 100644 tests/exhaustive/issues/286/expected/model_4_3.eprime delete mode 100644 tests/exhaustive/issues/286/expected/model_4_4-p1-solution000001.solution delete mode 100644 tests/exhaustive/issues/286/expected/model_4_4-p1-solution000002.solution delete mode 100644 tests/exhaustive/issues/286/expected/model_4_4-p1-solution000003.solution delete mode 100644 tests/exhaustive/issues/286/expected/model_4_4-p1-solution000004.solution delete mode 100644 tests/exhaustive/issues/286/expected/model_4_4-p1-solution000005.solution delete mode 100644 tests/exhaustive/issues/286/expected/model_4_4-p1-solution000006.solution delete mode 100644 tests/exhaustive/issues/286/expected/model_4_4-p1-solution000007.solution delete mode 100644 tests/exhaustive/issues/286/expected/model_4_4-p1-solution000008.solution delete mode 100644 tests/exhaustive/issues/286/expected/model_4_4-p1.eprime-param delete mode 100644 tests/exhaustive/issues/286/expected/model_4_4.eprime delete mode 100644 tests/exhaustive/mildly_interesting/cyclic_graph/expected/model-cyc1.eprime-param delete mode 100644 tests/exhaustive/mildly_interesting/cyclic_graph/expected/model-cyc2.eprime-param delete mode 100644 tests/exhaustive/mildly_interesting/cyclic_graph/expected/model-non-solution000001.solution delete mode 100644 tests/exhaustive/mildly_interesting/cyclic_graph/expected/model-non.eprime-param delete mode 100644 tests/exhaustive/mildly_interesting/cyclic_graph/expected/model.eprime delete mode 100644 tests/exhaustive/mildly_interesting/gchq_2016/expected/model-inst-solution000001.solution delete mode 100644 tests/exhaustive/mildly_interesting/gchq_2016/expected/model-inst.eprime-param delete mode 100644 tests/exhaustive/mildly_interesting/gchq_2016/expected/model.eprime delete mode 100644 tests/exhaustive/mildly_interesting/subsetSum/expected/model_1_1_1-p1-solution000001.solution delete mode 100644 tests/exhaustive/mildly_interesting/subsetSum/expected/model_1_1_1-p1.eprime-param delete mode 100644 tests/exhaustive/mildly_interesting/subsetSum/expected/model_1_1_1-p2-solution000001.solution delete mode 100644 tests/exhaustive/mildly_interesting/subsetSum/expected/model_1_1_1-p2-solution000002.solution delete mode 100644 tests/exhaustive/mildly_interesting/subsetSum/expected/model_1_1_1-p2.eprime-param delete mode 100644 tests/exhaustive/mildly_interesting/subsetSum/expected/model_1_1_1.eprime delete mode 100644 tests/exhaustive/mildly_interesting/subsetSum/expected/model_1_1_2-p1-solution000001.solution delete mode 100644 tests/exhaustive/mildly_interesting/subsetSum/expected/model_1_1_2-p1.eprime-param delete mode 100644 tests/exhaustive/mildly_interesting/subsetSum/expected/model_1_1_2-p2-solution000001.solution delete mode 100644 tests/exhaustive/mildly_interesting/subsetSum/expected/model_1_1_2-p2-solution000002.solution delete mode 100644 tests/exhaustive/mildly_interesting/subsetSum/expected/model_1_1_2-p2.eprime-param delete mode 100644 tests/exhaustive/mildly_interesting/subsetSum/expected/model_1_1_2.eprime delete mode 100644 tests/exhaustive/mildly_interesting/subsetSum/expected/model_1_2_1-p1-solution000001.solution delete mode 100644 tests/exhaustive/mildly_interesting/subsetSum/expected/model_1_2_1-p1.eprime-param delete mode 100644 tests/exhaustive/mildly_interesting/subsetSum/expected/model_1_2_1-p2-solution000001.solution delete mode 100644 tests/exhaustive/mildly_interesting/subsetSum/expected/model_1_2_1-p2-solution000002.solution delete mode 100644 tests/exhaustive/mildly_interesting/subsetSum/expected/model_1_2_1-p2.eprime-param delete mode 100644 tests/exhaustive/mildly_interesting/subsetSum/expected/model_1_2_1.eprime delete mode 100644 tests/exhaustive/mildly_interesting/subsetSum/expected/model_1_2_2-p1-solution000001.solution delete mode 100644 tests/exhaustive/mildly_interesting/subsetSum/expected/model_1_2_2-p1.eprime-param delete mode 100644 tests/exhaustive/mildly_interesting/subsetSum/expected/model_1_2_2-p2-solution000001.solution delete mode 100644 tests/exhaustive/mildly_interesting/subsetSum/expected/model_1_2_2-p2-solution000002.solution delete mode 100644 tests/exhaustive/mildly_interesting/subsetSum/expected/model_1_2_2-p2.eprime-param delete mode 100644 tests/exhaustive/mildly_interesting/subsetSum/expected/model_1_2_2.eprime delete mode 100644 tests/exhaustive/mildly_interesting/subsetSum/expected/model_2_1_1-p1-solution000001.solution delete mode 100644 tests/exhaustive/mildly_interesting/subsetSum/expected/model_2_1_1-p1.eprime-param delete mode 100644 tests/exhaustive/mildly_interesting/subsetSum/expected/model_2_1_1-p2-solution000001.solution delete mode 100644 tests/exhaustive/mildly_interesting/subsetSum/expected/model_2_1_1-p2-solution000002.solution delete mode 100644 tests/exhaustive/mildly_interesting/subsetSum/expected/model_2_1_1-p2.eprime-param delete mode 100644 tests/exhaustive/mildly_interesting/subsetSum/expected/model_2_1_1.eprime delete mode 100644 tests/exhaustive/mildly_interesting/subsetSum/expected/model_2_1_2-p1-solution000001.solution delete mode 100644 tests/exhaustive/mildly_interesting/subsetSum/expected/model_2_1_2-p1.eprime-param delete mode 100644 tests/exhaustive/mildly_interesting/subsetSum/expected/model_2_1_2-p2-solution000001.solution delete mode 100644 tests/exhaustive/mildly_interesting/subsetSum/expected/model_2_1_2-p2-solution000002.solution delete mode 100644 tests/exhaustive/mildly_interesting/subsetSum/expected/model_2_1_2-p2.eprime-param delete mode 100644 tests/exhaustive/mildly_interesting/subsetSum/expected/model_2_1_2.eprime delete mode 100644 tests/exhaustive/mildly_interesting/subsetSum/expected/model_2_2_1-p1-solution000001.solution delete mode 100644 tests/exhaustive/mildly_interesting/subsetSum/expected/model_2_2_1-p1.eprime-param delete mode 100644 tests/exhaustive/mildly_interesting/subsetSum/expected/model_2_2_1-p2-solution000001.solution delete mode 100644 tests/exhaustive/mildly_interesting/subsetSum/expected/model_2_2_1-p2-solution000002.solution delete mode 100644 tests/exhaustive/mildly_interesting/subsetSum/expected/model_2_2_1-p2.eprime-param delete mode 100644 tests/exhaustive/mildly_interesting/subsetSum/expected/model_2_2_1.eprime delete mode 100644 tests/exhaustive/mildly_interesting/subsetSum/expected/model_2_2_2-p1-solution000001.solution delete mode 100644 tests/exhaustive/mildly_interesting/subsetSum/expected/model_2_2_2-p1.eprime-param delete mode 100644 tests/exhaustive/mildly_interesting/subsetSum/expected/model_2_2_2-p2-solution000001.solution delete mode 100644 tests/exhaustive/mildly_interesting/subsetSum/expected/model_2_2_2-p2-solution000002.solution delete mode 100644 tests/exhaustive/mildly_interesting/subsetSum/expected/model_2_2_2-p2.eprime-param delete mode 100644 tests/exhaustive/mildly_interesting/subsetSum/expected/model_2_2_2.eprime delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000001.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000002.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000003.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000004.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000005.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000006.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000007.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000008.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000009.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000010.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000011.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000012.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000013.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000014.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000015.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000016.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000017.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000018.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000019.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000020.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000021.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000022.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000023.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000024.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000025.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000026.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000027.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000028.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000029.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000030.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000031.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000032.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000033.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000034.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000035.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000036.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model.eprime delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_1_1-solution000001.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_1_1-solution000002.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_1_1-solution000003.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_1_1-solution000004.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_1_1-solution000005.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_1_1-solution000006.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_1_1.eprime delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_1_2-solution000001.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_1_2-solution000002.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_1_2-solution000003.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_1_2-solution000004.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_1_2-solution000005.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_1_2-solution000006.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_1_2.eprime delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_1_3-solution000001.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_1_3-solution000002.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_1_3-solution000003.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_1_3-solution000004.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_1_3-solution000005.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_1_3-solution000006.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_1_3.eprime delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_2_1-solution000001.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_2_1-solution000002.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_2_1-solution000003.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_2_1-solution000004.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_2_1-solution000005.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_2_1-solution000006.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_2_1.eprime delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_2_2-solution000001.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_2_2-solution000002.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_2_2-solution000003.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_2_2-solution000004.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_2_2-solution000005.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_2_2-solution000006.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_2_2.eprime delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_2_3-solution000001.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_2_3-solution000002.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_2_3-solution000003.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_2_3-solution000004.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_2_3-solution000005.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_2_3-solution000006.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_2_3.eprime delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_3_1-solution000001.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_3_1-solution000002.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_3_1-solution000003.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_3_1-solution000004.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_3_1-solution000005.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_3_1-solution000006.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_3_1.eprime delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_3_2-solution000001.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_3_2-solution000002.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_3_2-solution000003.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_3_2-solution000004.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_3_2-solution000005.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_3_2-solution000006.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_3_2.eprime delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_3_3-solution000001.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_3_3-solution000002.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_3_3-solution000003.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_3_3-solution000004.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_3_3-solution000005.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_3_3-solution000006.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_3_3.eprime delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_1_1-solution000001.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_1_1-solution000002.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_1_1-solution000003.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_1_1-solution000004.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_1_1-solution000005.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_1_1-solution000006.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_1_1.eprime delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_1_2-solution000001.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_1_2-solution000002.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_1_2-solution000003.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_1_2-solution000004.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_1_2-solution000005.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_1_2-solution000006.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_1_2.eprime delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_1_3-solution000001.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_1_3-solution000002.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_1_3-solution000003.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_1_3-solution000004.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_1_3-solution000005.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_1_3-solution000006.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_1_3.eprime delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_2_1-solution000001.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_2_1-solution000002.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_2_1-solution000003.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_2_1-solution000004.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_2_1-solution000005.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_2_1-solution000006.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_2_1.eprime delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_2_2-solution000001.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_2_2-solution000002.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_2_2-solution000003.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_2_2-solution000004.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_2_2-solution000005.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_2_2-solution000006.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_2_2.eprime delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_2_3-solution000001.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_2_3-solution000002.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_2_3-solution000003.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_2_3-solution000004.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_2_3-solution000005.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_2_3-solution000006.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_2_3.eprime delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_3_1-solution000001.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_3_1-solution000002.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_3_1-solution000003.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_3_1-solution000004.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_3_1-solution000005.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_3_1-solution000006.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_3_1.eprime delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_3_2-solution000001.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_3_2-solution000002.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_3_2-solution000003.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_3_2-solution000004.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_3_2-solution000005.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_3_2-solution000006.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_3_2.eprime delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_3_3-solution000001.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_3_3-solution000002.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_3_3-solution000003.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_3_3-solution000004.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_3_3-solution000005.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_3_3-solution000006.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_3_3.eprime delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_1_1-solution000001.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_1_1-solution000002.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_1_1-solution000003.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_1_1-solution000004.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_1_1-solution000005.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_1_1-solution000006.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_1_1.eprime delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_1_2-solution000001.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_1_2-solution000002.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_1_2-solution000003.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_1_2-solution000004.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_1_2-solution000005.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_1_2-solution000006.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_1_2.eprime delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_1_3-solution000001.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_1_3-solution000002.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_1_3-solution000003.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_1_3-solution000004.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_1_3-solution000005.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_1_3-solution000006.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_1_3.eprime delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_2_1-solution000001.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_2_1-solution000002.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_2_1-solution000003.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_2_1-solution000004.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_2_1-solution000005.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_2_1-solution000006.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_2_1.eprime delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_2_2-solution000001.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_2_2-solution000002.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_2_2-solution000003.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_2_2-solution000004.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_2_2-solution000005.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_2_2-solution000006.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_2_2.eprime delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_2_3-solution000001.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_2_3-solution000002.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_2_3-solution000003.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_2_3-solution000004.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_2_3-solution000005.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_2_3-solution000006.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_2_3.eprime delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_3_1-solution000001.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_3_1-solution000002.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_3_1-solution000003.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_3_1-solution000004.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_3_1-solution000005.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_3_1-solution000006.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_3_1.eprime delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_3_2-solution000001.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_3_2-solution000002.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_3_2-solution000003.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_3_2-solution000004.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_3_2-solution000005.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_3_2-solution000006.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_3_2.eprime delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_3_3-solution000001.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_3_3-solution000002.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_3_3-solution000003.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_3_3-solution000004.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_3_3-solution000005.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_3_3-solution000006.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_3_3.eprime delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_1_1-solution000001.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_1_1-solution000002.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_1_1-solution000003.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_1_1-solution000004.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_1_1-solution000005.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_1_1-solution000006.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_1_1.eprime delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_1_2-solution000001.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_1_2-solution000002.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_1_2-solution000003.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_1_2-solution000004.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_1_2-solution000005.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_1_2-solution000006.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_1_2.eprime delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_1_3-solution000001.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_1_3-solution000002.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_1_3-solution000003.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_1_3-solution000004.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_1_3-solution000005.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_1_3-solution000006.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_1_3.eprime delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_2_1-solution000001.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_2_1-solution000002.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_2_1-solution000003.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_2_1-solution000004.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_2_1-solution000005.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_2_1-solution000006.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_2_1.eprime delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_2_2-solution000001.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_2_2-solution000002.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_2_2-solution000003.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_2_2-solution000004.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_2_2-solution000005.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_2_2-solution000006.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_2_2.eprime delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_2_3-solution000001.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_2_3-solution000002.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_2_3-solution000003.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_2_3-solution000004.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_2_3-solution000005.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_2_3-solution000006.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_2_3.eprime delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_3_1-solution000001.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_3_1-solution000002.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_3_1-solution000003.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_3_1-solution000004.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_3_1-solution000005.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_3_1-solution000006.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_3_1.eprime delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_3_2-solution000001.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_3_2-solution000002.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_3_2-solution000003.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_3_2-solution000004.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_3_2-solution000005.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_3_2-solution000006.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_3_2.eprime delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_3_3-solution000001.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_3_3-solution000002.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_3_3-solution000003.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_3_3-solution000004.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_3_3-solution000005.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_3_3-solution000006.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_3_3.eprime delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_1_1-solution000001.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_1_1-solution000002.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_1_1-solution000003.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_1_1-solution000004.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_1_1-solution000005.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_1_1-solution000006.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_1_1.eprime delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_1_2-solution000001.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_1_2-solution000002.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_1_2-solution000003.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_1_2-solution000004.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_1_2-solution000005.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_1_2-solution000006.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_1_2.eprime delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_1_3-solution000001.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_1_3-solution000002.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_1_3-solution000003.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_1_3-solution000004.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_1_3-solution000005.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_1_3-solution000006.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_1_3.eprime delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_2_1-solution000001.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_2_1-solution000002.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_2_1-solution000003.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_2_1-solution000004.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_2_1-solution000005.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_2_1-solution000006.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_2_1.eprime delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_2_2-solution000001.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_2_2-solution000002.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_2_2-solution000003.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_2_2-solution000004.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_2_2-solution000005.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_2_2-solution000006.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_2_2.eprime delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_2_3-solution000001.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_2_3-solution000002.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_2_3-solution000003.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_2_3-solution000004.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_2_3-solution000005.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_2_3-solution000006.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_2_3.eprime delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_3_1-solution000001.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_3_1-solution000002.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_3_1-solution000003.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_3_1-solution000004.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_3_1-solution000005.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_3_1-solution000006.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_3_1.eprime delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_3_2-solution000001.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_3_2-solution000002.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_3_2-solution000003.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_3_2-solution000004.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_3_2-solution000005.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_3_2-solution000006.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_3_2.eprime delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_3_3-solution000001.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_3_3-solution000002.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_3_3-solution000003.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_3_3-solution000004.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_3_3-solution000005.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_3_3-solution000006.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_3_3.eprime delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_1_1-solution000001.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_1_1-solution000002.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_1_1-solution000003.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_1_1-solution000004.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_1_1-solution000005.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_1_1-solution000006.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_1_1.eprime delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_1_2-solution000001.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_1_2-solution000002.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_1_2-solution000003.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_1_2-solution000004.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_1_2-solution000005.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_1_2-solution000006.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_1_2.eprime delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_1_3-solution000001.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_1_3-solution000002.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_1_3-solution000003.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_1_3-solution000004.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_1_3-solution000005.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_1_3-solution000006.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_1_3.eprime delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_2_1-solution000001.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_2_1-solution000002.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_2_1-solution000003.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_2_1-solution000004.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_2_1-solution000005.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_2_1-solution000006.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_2_1.eprime delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_2_2-solution000001.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_2_2-solution000002.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_2_2-solution000003.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_2_2-solution000004.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_2_2-solution000005.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_2_2-solution000006.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_2_2.eprime delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_2_3-solution000001.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_2_3-solution000002.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_2_3-solution000003.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_2_3-solution000004.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_2_3-solution000005.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_2_3-solution000006.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_2_3.eprime delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_3_1-solution000001.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_3_1-solution000002.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_3_1-solution000003.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_3_1-solution000004.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_3_1-solution000005.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_3_1-solution000006.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_3_1.eprime delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_3_2-solution000001.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_3_2-solution000002.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_3_2-solution000003.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_3_2-solution000004.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_3_2-solution000005.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_3_2-solution000006.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_3_2.eprime delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_3_3-solution000001.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_3_3-solution000002.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_3_3-solution000003.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_3_3-solution000004.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_3_3-solution000005.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_3_3-solution000006.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_3_3.eprime delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_1_1-solution000001.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_1_1-solution000002.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_1_1-solution000003.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_1_1-solution000004.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_1_1-solution000005.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_1_1-solution000006.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_1_1.eprime delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_1_2-solution000001.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_1_2-solution000002.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_1_2-solution000003.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_1_2-solution000004.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_1_2-solution000005.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_1_2-solution000006.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_1_2.eprime delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_1_3-solution000001.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_1_3-solution000002.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_1_3-solution000003.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_1_3-solution000004.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_1_3-solution000005.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_1_3-solution000006.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_1_3.eprime delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_2_1-solution000001.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_2_1-solution000002.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_2_1-solution000003.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_2_1-solution000004.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_2_1-solution000005.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_2_1-solution000006.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_2_1.eprime delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_2_2-solution000001.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_2_2-solution000002.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_2_2-solution000003.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_2_2-solution000004.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_2_2-solution000005.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_2_2-solution000006.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_2_2.eprime delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_2_3-solution000001.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_2_3-solution000002.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_2_3-solution000003.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_2_3-solution000004.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_2_3-solution000005.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_2_3-solution000006.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_2_3.eprime delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_3_1-solution000001.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_3_1-solution000002.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_3_1-solution000003.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_3_1-solution000004.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_3_1-solution000005.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_3_1-solution000006.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_3_1.eprime delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_3_2-solution000001.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_3_2-solution000002.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_3_2-solution000003.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_3_2-solution000004.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_3_2-solution000005.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_3_2-solution000006.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_3_2.eprime delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_3_3-solution000001.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_3_3-solution000002.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_3_3-solution000003.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_3_3-solution000004.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_3_3-solution000005.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_3_3-solution000006.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_3_3.eprime delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_1_1-solution000001.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_1_1-solution000002.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_1_1-solution000003.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_1_1-solution000004.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_1_1-solution000005.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_1_1-solution000006.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_1_1.eprime delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_1_2-solution000001.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_1_2-solution000002.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_1_2-solution000003.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_1_2-solution000004.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_1_2-solution000005.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_1_2-solution000006.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_1_2.eprime delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_1_3-solution000001.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_1_3-solution000002.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_1_3-solution000003.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_1_3-solution000004.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_1_3-solution000005.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_1_3-solution000006.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_1_3.eprime delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_2_1-solution000001.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_2_1-solution000002.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_2_1-solution000003.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_2_1-solution000004.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_2_1-solution000005.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_2_1-solution000006.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_2_1.eprime delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_2_2-solution000001.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_2_2-solution000002.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_2_2-solution000003.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_2_2-solution000004.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_2_2-solution000005.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_2_2-solution000006.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_2_2.eprime delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_2_3-solution000001.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_2_3-solution000002.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_2_3-solution000003.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_2_3-solution000004.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_2_3-solution000005.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_2_3-solution000006.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_2_3.eprime delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_3_1-solution000001.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_3_1-solution000002.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_3_1-solution000003.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_3_1-solution000004.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_3_1-solution000005.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_3_1-solution000006.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_3_1.eprime delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_3_2-solution000001.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_3_2-solution000002.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_3_2-solution000003.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_3_2-solution000004.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_3_2-solution000005.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_3_2-solution000006.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_3_2.eprime delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_3_3-solution000001.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_3_3-solution000002.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_3_3-solution000003.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_3_3-solution000004.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_3_3-solution000005.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_3_3-solution000006.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_3_3.eprime delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_1_1-solution000001.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_1_1-solution000002.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_1_1-solution000003.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_1_1-solution000004.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_1_1-solution000005.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_1_1-solution000006.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_1_1.eprime delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_1_2-solution000001.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_1_2-solution000002.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_1_2-solution000003.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_1_2-solution000004.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_1_2-solution000005.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_1_2-solution000006.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_1_2.eprime delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_1_3-solution000001.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_1_3-solution000002.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_1_3-solution000003.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_1_3-solution000004.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_1_3-solution000005.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_1_3-solution000006.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_1_3.eprime delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_2_1-solution000001.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_2_1-solution000002.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_2_1-solution000003.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_2_1-solution000004.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_2_1-solution000005.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_2_1-solution000006.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_2_1.eprime delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_2_2-solution000001.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_2_2-solution000002.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_2_2-solution000003.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_2_2-solution000004.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_2_2-solution000005.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_2_2-solution000006.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_2_2.eprime delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_2_3-solution000001.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_2_3-solution000002.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_2_3-solution000003.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_2_3-solution000004.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_2_3-solution000005.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_2_3-solution000006.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_2_3.eprime delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_3_1-solution000001.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_3_1-solution000002.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_3_1-solution000003.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_3_1-solution000004.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_3_1-solution000005.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_3_1-solution000006.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_3_1.eprime delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_3_2-solution000001.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_3_2-solution000002.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_3_2-solution000003.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_3_2-solution000004.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_3_2-solution000005.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_3_2-solution000006.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_3_2.eprime delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_3_3-solution000001.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_3_3-solution000002.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_3_3-solution000003.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_3_3-solution000004.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_3_3-solution000005.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_3_3-solution000006.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_3_3.eprime delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_1_1-solution000001.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_1_1.eprime delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_1_2-solution000001.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_1_2.eprime delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_1_3-solution000001.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_1_3.eprime delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_1_4-solution000001.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_1_4.eprime delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_2_1-solution000001.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_2_1.eprime delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_2_2-solution000001.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_2_2.eprime delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_2_3-solution000001.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_2_3.eprime delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_2_4-solution000001.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_2_4.eprime delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_3_1-solution000001.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_3_1.eprime delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_3_2-solution000001.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_3_2.eprime delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_3_3-solution000001.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_3_3.eprime delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_3_4-solution000001.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_3_4.eprime delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_4_1-solution000001.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_4_1.eprime delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_4_2-solution000001.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_4_2.eprime delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_4_3-solution000001.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_4_3.eprime delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_4_4-solution000001.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_4_4.eprime delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000001.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000002.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000003.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000004.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000005.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000006.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000007.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000008.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000009.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000010.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000011.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000012.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000013.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000014.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000015.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000016.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000017.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000018.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000019.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000020.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000021.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000022.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000023.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000024.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000025.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000026.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000027.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000028.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000029.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000030.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000031.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000032.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000033.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000034.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000035.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000036.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000037.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000038.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000039.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000040.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000041.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000042.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000043.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000044.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000045.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000046.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000047.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000048.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000049.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000050.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000051.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000052.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000053.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000054.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000055.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000056.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000057.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000058.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000059.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000060.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000061.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000062.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000063.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000064.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000065.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000066.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000067.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000068.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000069.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000070.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000071.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000072.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000073.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000074.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000075.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000076.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000077.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000078.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000079.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000080.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000081.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000082.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000083.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000084.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000085.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000086.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000087.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000088.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000089.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000090.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000091.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000092.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000093.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000094.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000095.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000096.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000097.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000098.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000099.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000100.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000101.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000102.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000103.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000104.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000105.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000106.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000107.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000108.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000109.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000110.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000111.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000112.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000113.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000114.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000115.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000116.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000117.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000118.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000119.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000120.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model.eprime delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_1_1_1-solution000001.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_1_1_1-solution000002.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_1_1_1-solution000003.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_1_1_1-solution000004.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_1_1_1-solution000005.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_1_1_1-solution000006.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_1_1_1.eprime delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_1_1_2-solution000001.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_1_1_2-solution000002.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_1_1_2-solution000003.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_1_1_2-solution000004.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_1_1_2-solution000005.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_1_1_2-solution000006.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_1_1_2.eprime delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_1_2_1-solution000001.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_1_2_1-solution000002.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_1_2_1-solution000003.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_1_2_1-solution000004.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_1_2_1-solution000005.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_1_2_1-solution000006.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_1_2_1.eprime delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_1_2_2-solution000001.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_1_2_2-solution000002.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_1_2_2-solution000003.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_1_2_2-solution000004.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_1_2_2-solution000005.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_1_2_2-solution000006.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_1_2_2.eprime delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_2_1_1-solution000001.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_2_1_1-solution000002.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_2_1_1-solution000003.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_2_1_1-solution000004.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_2_1_1-solution000005.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_2_1_1-solution000006.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_2_1_1.eprime delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_2_1_2-solution000001.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_2_1_2-solution000002.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_2_1_2-solution000003.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_2_1_2-solution000004.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_2_1_2-solution000005.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_2_1_2-solution000006.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_2_1_2.eprime delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_2_2_1-solution000001.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_2_2_1-solution000002.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_2_2_1-solution000003.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_2_2_1-solution000004.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_2_2_1-solution000005.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_2_2_1-solution000006.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_2_2_1.eprime delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_2_2_2-solution000001.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_2_2_2-solution000002.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_2_2_2-solution000003.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_2_2_2-solution000004.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_2_2_2-solution000005.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_2_2_2-solution000006.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_2_2_2.eprime delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_1_1_1-solution000001.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_1_1_1-solution000002.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_1_1_1-solution000003.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_1_1_1-solution000004.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_1_1_1-solution000005.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_1_1_1-solution000006.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_1_1_1.eprime delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_1_1_2-solution000001.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_1_1_2-solution000002.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_1_1_2-solution000003.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_1_1_2-solution000004.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_1_1_2-solution000005.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_1_1_2-solution000006.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_1_1_2.eprime delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_1_2_1-solution000001.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_1_2_1-solution000002.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_1_2_1-solution000003.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_1_2_1-solution000004.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_1_2_1-solution000005.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_1_2_1-solution000006.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_1_2_1.eprime delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_1_2_2-solution000001.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_1_2_2-solution000002.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_1_2_2-solution000003.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_1_2_2-solution000004.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_1_2_2-solution000005.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_1_2_2-solution000006.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_1_2_2.eprime delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_2_1_1-solution000001.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_2_1_1-solution000002.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_2_1_1-solution000003.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_2_1_1-solution000004.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_2_1_1-solution000005.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_2_1_1-solution000006.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_2_1_1.eprime delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_2_1_2-solution000001.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_2_1_2-solution000002.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_2_1_2-solution000003.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_2_1_2-solution000004.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_2_1_2-solution000005.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_2_1_2-solution000006.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_2_1_2.eprime delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_2_2_1-solution000001.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_2_2_1-solution000002.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_2_2_1-solution000003.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_2_2_1-solution000004.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_2_2_1-solution000005.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_2_2_1-solution000006.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_2_2_1.eprime delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_2_2_2-solution000001.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_2_2_2-solution000002.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_2_2_2-solution000003.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_2_2_2-solution000004.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_2_2_2-solution000005.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_2_2_2-solution000006.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_2_2_2.eprime diff --git a/etc/build/gen_Operator.hs b/etc/build/gen_Operator.hs index 82f937f318..b675c68956 100644 --- a/etc/build/gen_Operator.hs +++ b/etc/build/gen_Operator.hs @@ -66,6 +66,7 @@ main = do , [ "" , "instance ( Pretty x" + , " , Data x" , " , ExpressionLike x" , " , ReferenceContainer x" , " , TypeOf x" diff --git a/src/Conjure/Language/Expression/Op/AllDiffExcept.hs b/src/Conjure/Language/Expression/Op/AllDiffExcept.hs index 995099bc19..aa2e73b0d3 100644 --- a/src/Conjure/Language/Expression/Op/AllDiffExcept.hs +++ b/src/Conjure/Language/Expression/Op/AllDiffExcept.hs @@ -24,6 +24,7 @@ instance (TypeOf x, Pretty x) => TypeOf (OpAllDiffExcept x) where tyN <- typeOf n case tyN of TypeInt TagInt -> return () + TypeInt TaggedInt{} -> return () TypeInt (TagEnum _) -> return () _ -> raiseTypeError p case tyX of diff --git a/src/Conjure/Language/Expression/Op/Div.hs b/src/Conjure/Language/Expression/Op/Div.hs index a718409d1d..2754519f3a 100644 --- a/src/Conjure/Language/Expression/Op/Div.hs +++ b/src/Conjure/Language/Expression/Op/Div.hs @@ -21,8 +21,11 @@ instance FromJSON x => FromJSON (OpDiv x) where parseJSON = genericParseJSON j instance BinaryOperator (OpDiv x) where opLexeme _ = L_Div -instance (TypeOf x, Pretty x) => TypeOf (OpDiv x) where - typeOf p@(OpDiv a b) = intToIntToInt p a b +instance (TypeOf x, Pretty x, Data x) => TypeOf (OpDiv x) where + typeOf p@(OpDiv a b) = + if ?typeCheckerMode == RelaxedIntegerTags + then intToIntToInt p a b + else intToIntToIntStrict p a b instance EvaluateOp OpDiv where evaluateOp p | any isUndef (childrenBi p) = diff --git a/src/Conjure/Language/Expression/Op/Factorial.hs b/src/Conjure/Language/Expression/Op/Factorial.hs index 63c5696198..70c91e13d3 100644 --- a/src/Conjure/Language/Expression/Op/Factorial.hs +++ b/src/Conjure/Language/Expression/Op/Factorial.hs @@ -23,6 +23,7 @@ instance (TypeOf x, Pretty x) => TypeOf (OpFactorial x) where TypeInt t <- typeOf a case t of TagInt -> return () + TaggedInt _ -> return () _ -> raiseTypeError p return (TypeInt t) diff --git a/src/Conjure/Language/Expression/Op/Geq.hs b/src/Conjure/Language/Expression/Op/Geq.hs index 8beb72960a..006d49a052 100644 --- a/src/Conjure/Language/Expression/Op/Geq.hs +++ b/src/Conjure/Language/Expression/Op/Geq.hs @@ -26,6 +26,7 @@ instance (TypeOf x, Pretty x) => TypeOf (OpGeq x) where TypeBool -> True TypeInt{} | ?typeCheckerMode == RelaxedIntegerTags -> True TypeInt TagInt -> True + TypeInt TaggedInt{} -> True TypeInt TagEnum{} -> True _ -> False diff --git a/src/Conjure/Language/Expression/Op/Internal/Common.hs b/src/Conjure/Language/Expression/Op/Internal/Common.hs index 53780b6dfe..792bb471dd 100644 --- a/src/Conjure/Language/Expression/Op/Internal/Common.hs +++ b/src/Conjure/Language/Expression/Op/Internal/Common.hs @@ -16,6 +16,7 @@ module Conjure.Language.Expression.Op.Internal.Common , intToInt , intToIntToInt + , intToIntToIntStrict , boolToBoolToBool , sameToSameToBool , sameToSameToSame @@ -113,6 +114,35 @@ intToIntToInt p a b = do , "Second argument expected to be an int, but it is:" <++> pretty tyb ] +intToIntToIntStrict :: (MonadFail m, TypeOf a, Pretty p, ?typeCheckerMode :: TypeCheckerMode) => p -> a -> a -> m Type +intToIntToIntStrict p a b = do + tya <- typeOf a + tyb <- typeOf b + case (tya, tyb) of + (TypeInt TagInt, TypeInt TagInt) -> + if typeUnify tya tyb + then return $ mostDefined [tya, tyb] + else fail $ vcat + [ "When type checking:" <+> pretty p + , "Types do not unify:" <++> pretty tya + ] + (TypeInt TaggedInt{}, TypeInt TaggedInt{}) -> + if typeUnify tya tyb + then return $ mostDefined [tya, tyb] + else fail $ vcat + [ "When type checking:" <+> pretty p + , "Types do not unify:" <++> pretty tya + ] + (_, TypeInt{}) -> fail $ vcat + [ "When type checking:" <+> pretty p + , "First argument expected to be an int, but it is:" <++> pretty tya + ] + _ -> fail $ vcat + [ "When type checking:" <+> pretty p + , "Second argument expected to be an int, but it is:" <++> pretty tyb + ] + + boolToBoolToBool :: (MonadFail m, TypeOf a, Pretty p, ?typeCheckerMode :: TypeCheckerMode) => p -> a -> a -> m Type boolToBoolToBool p a b = do diff --git a/src/Conjure/Language/Expression/Op/Leq.hs b/src/Conjure/Language/Expression/Op/Leq.hs index 8cfaf371f3..2d805ca8ce 100644 --- a/src/Conjure/Language/Expression/Op/Leq.hs +++ b/src/Conjure/Language/Expression/Op/Leq.hs @@ -26,6 +26,7 @@ instance (TypeOf x, Pretty x) => TypeOf (OpLeq x) where TypeBool -> True TypeInt{} | ?typeCheckerMode == RelaxedIntegerTags -> True TypeInt TagInt -> True + TypeInt TaggedInt{} -> True TypeInt TagEnum{} -> True _ -> False diff --git a/src/Conjure/Language/Expression/Op/Lt.hs b/src/Conjure/Language/Expression/Op/Lt.hs index 7cf26bbd4b..adfb9f3c65 100644 --- a/src/Conjure/Language/Expression/Op/Lt.hs +++ b/src/Conjure/Language/Expression/Op/Lt.hs @@ -26,6 +26,7 @@ instance (TypeOf x, Pretty x) => TypeOf (OpLt x) where TypeBool -> True TypeInt{} | ?typeCheckerMode == RelaxedIntegerTags -> True TypeInt TagInt -> True + TypeInt TaggedInt{} -> True TypeInt TagEnum{} -> True _ -> False diff --git a/src/Conjure/Language/Expression/Op/Max.hs b/src/Conjure/Language/Expression/Op/Max.hs index fe7e575e00..f816efdfd8 100644 --- a/src/Conjure/Language/Expression/Op/Max.hs +++ b/src/Conjure/Language/Expression/Op/Max.hs @@ -26,6 +26,7 @@ instance ( TypeOf x, Pretty x ty <- typeOf dom case ty of TypeInt TagInt -> return ty + TypeInt TaggedInt{} -> return ty TypeInt (TagEnum _) -> return ty TypeEnum{} -> return ty _ -> raiseTypeError $ vcat [ pretty p @@ -43,6 +44,7 @@ instance ( TypeOf x, Pretty x ] case tyInner of TypeInt TagInt -> return () + TypeInt TaggedInt{} -> return () TypeInt (TagEnum _) -> return () _ -> raiseTypeError $ vcat [ pretty p , "Unexpected type inside max:" <+> pretty ty diff --git a/src/Conjure/Language/Expression/Op/Min.hs b/src/Conjure/Language/Expression/Op/Min.hs index 3420b3c220..fa9c81a5bc 100644 --- a/src/Conjure/Language/Expression/Op/Min.hs +++ b/src/Conjure/Language/Expression/Op/Min.hs @@ -26,6 +26,7 @@ instance ( TypeOf x, Pretty x ty <- typeOf dom case ty of TypeInt TagInt -> return ty + TypeInt TaggedInt{} -> return ty TypeInt (TagEnum _) -> return ty TypeEnum{} -> return ty _ -> raiseTypeError $ vcat [ pretty p @@ -43,6 +44,7 @@ instance ( TypeOf x, Pretty x ] case tyInner of TypeInt TagInt -> return () + TypeInt TaggedInt{} -> return () TypeInt (TagEnum _) -> return () _ -> raiseTypeError $ vcat [ pretty p , "Unexpected type inside min:" <+> pretty ty diff --git a/src/Conjure/Language/Expression/Op/Minus.hs b/src/Conjure/Language/Expression/Op/Minus.hs index c80e510bf2..71342200fd 100644 --- a/src/Conjure/Language/Expression/Op/Minus.hs +++ b/src/Conjure/Language/Expression/Op/Minus.hs @@ -30,6 +30,7 @@ instance (TypeOf x, Pretty x) => TypeOf (OpMinus x) where ] (\ ty -> case (?typeCheckerMode, ty) of (StronglyTyped, TypeInt TagInt) -> True + (StronglyTyped, TypeInt TaggedInt{}) -> True (RelaxedIntegerTags, TypeInt{}) -> True _ -> False ) diff --git a/src/Conjure/Language/Expression/Op/Negate.hs b/src/Conjure/Language/Expression/Op/Negate.hs index dd34b2a4ad..b85025a64e 100644 --- a/src/Conjure/Language/Expression/Op/Negate.hs +++ b/src/Conjure/Language/Expression/Op/Negate.hs @@ -23,6 +23,7 @@ instance (TypeOf x, Pretty x) => TypeOf (OpNegate x) where TypeInt t <- typeOf a case t of TagInt -> return () + TaggedInt{} -> return () _ -> raiseTypeError p return (TypeInt t) diff --git a/src/Conjure/Language/Expression/Op/Pred.hs b/src/Conjure/Language/Expression/Op/Pred.hs index 0e7300cc0c..9e5e436187 100644 --- a/src/Conjure/Language/Expression/Op/Pred.hs +++ b/src/Conjure/Language/Expression/Op/Pred.hs @@ -24,6 +24,7 @@ instance (TypeOf x, Pretty x) => TypeOf (OpPred x) where case ty of TypeBool{} -> return ty TypeInt TagInt -> return ty + TypeInt TaggedInt{} -> return ty TypeInt (TagEnum _) -> return ty TypeEnum{} -> return ty _ -> raiseTypeError p diff --git a/src/Conjure/Language/Expression/Op/Product.hs b/src/Conjure/Language/Expression/Op/Product.hs index 12f01234d1..98d0d9c39d 100644 --- a/src/Conjure/Language/Expression/Op/Product.hs +++ b/src/Conjure/Language/Expression/Op/Product.hs @@ -33,6 +33,7 @@ instance (TypeOf x, Pretty x, ExpressionLike x) => TypeOf (OpProduct x) where case innerTy of TypeInt t | ?typeCheckerMode == RelaxedIntegerTags -> return (TypeInt t) TypeInt TagInt -> return (TypeInt TagInt) + TypeInt t@(TaggedInt _) -> return $ TypeInt t _ -> raiseTypeError $ vcat [ pretty p , "The argument has type:" <+> pretty ty ] diff --git a/src/Conjure/Language/Expression/Op/Succ.hs b/src/Conjure/Language/Expression/Op/Succ.hs index d8c7c9535d..7c69624118 100644 --- a/src/Conjure/Language/Expression/Op/Succ.hs +++ b/src/Conjure/Language/Expression/Op/Succ.hs @@ -24,6 +24,7 @@ instance (TypeOf x, Pretty x) => TypeOf (OpSucc x) where case ty of TypeBool{} -> return ty TypeInt TagInt -> return ty + TypeInt TaggedInt{} -> return ty TypeInt (TagEnum _) -> return ty TypeEnum{} -> return ty _ -> raiseTypeError p diff --git a/src/Conjure/Language/Expression/Op/Sum.hs b/src/Conjure/Language/Expression/Op/Sum.hs index 9aa5db18d7..4b23f9ad79 100644 --- a/src/Conjure/Language/Expression/Op/Sum.hs +++ b/src/Conjure/Language/Expression/Op/Sum.hs @@ -33,6 +33,7 @@ instance (TypeOf x, Pretty x, ExpressionLike x) => TypeOf (OpSum x) where case innerTy of TypeInt t | ?typeCheckerMode == RelaxedIntegerTags -> return (TypeInt t) TypeInt TagInt -> return (TypeInt TagInt) + TypeInt t@(TaggedInt _) -> return (TypeInt t) _ -> raiseTypeError $ vcat [ pretty p , "The argument has type:" <+> pretty ty ] diff --git a/src/Conjure/Language/Lexer.hs b/src/Conjure/Language/Lexer.hs index d78fad5886..2afbc7f315 100644 --- a/src/Conjure/Language/Lexer.hs +++ b/src/Conjure/Language/Lexer.hs @@ -266,6 +266,7 @@ data Lexeme | L_pred | L_succ + | L_tagged deriving (Eq, Ord, Show, Generic) instance Hashable Lexeme @@ -478,7 +479,7 @@ lexemes = sortBy (flip (comparing (T.length . fst))) $ map swap , ( L_pred, "pred" ) , ( L_succ, "succ" ) - + , ( L_tagged, "tagged" ) ] runLexer :: MonadFail m => T.Text -> m [LexemePos] diff --git a/src/Conjure/Language/Parser.hs b/src/Conjure/Language/Parser.hs index 3db13ffdfc..4bfb155390 100644 --- a/src/Conjure/Language/Parser.hs +++ b/src/Conjure/Language/Parser.hs @@ -243,7 +243,7 @@ parseDomainWithRepr = pDomainAtom where pDomainAtom = msum - [ pBool, try pIntFromExpr, pInt, try pEnum, try pReference + [ pBool, try pIntFromExpr, try pIntTagged, pInt, try pEnum, try pReference , pMatrix, try pTupleWithout, pTupleWith , pRecord, pVariant , pSet @@ -281,6 +281,7 @@ parseDomainWithRepr = pDomainAtom x <- parens parseExpr case (let ?typeCheckerMode = StronglyTyped in typeOf x) of Just (TypeInt TagInt) -> return $ DomainInt TagInt [RangeSingle x] + Just (TypeInt t@(TaggedInt _)) -> return $ DomainInt t [RangeSingle x] _ -> return $ DomainIntE x pInt = do @@ -289,6 +290,15 @@ parseDomainWithRepr = pDomainAtom let xs = fromMaybe [] mxs return $ DomainInt TagInt xs + pIntTagged = do + lexeme L_int + lexeme L_Colon + t <- identifierText + mxs <- optional $ parens $ commaSeparated0 $ parseRange parseExpr + let xs = fromMaybe [] mxs + return $ DomainInt (TaggedInt t) xs + + pReference = do r <- identifierText return $ DomainReference (Name r) Nothing @@ -901,6 +911,7 @@ parseAbstractPattern = label "pattern" $ msum parseLiteral :: Parser Expression parseLiteral = label "value" $ msum [ Constant <$> pBool + , Constant <$> try pIntTagged , Constant <$> pInt , mkAbstractLiteral <$> pMatrix , mkAbstractLiteral <$> pTupleWith @@ -932,6 +943,13 @@ parseLiteral = label "value" $ msum pInt = ConstantInt TagInt . fromInteger <$> integer + pIntTagged = do + i <- integer + lexeme L_Colon + t <- identifierText + return $ ConstantInt (TaggedInt t) $ fromInteger i + + pMatrix = do lexeme L_OpenBracket xs <- commaSeparated0 parseExpr diff --git a/src/Conjure/Language/ParserC.hs b/src/Conjure/Language/ParserC.hs index 9aff06b4ff..9124844256 100644 --- a/src/Conjure/Language/ParserC.hs +++ b/src/Conjure/Language/ParserC.hs @@ -116,7 +116,7 @@ parseDomainWithRepr = pDomainAtom where pDomainAtom = msum - [ pBool, try pIntFromExpr, pInt, try pEnum, try pReference + [ pBool, try pIntFromExpr, try pIntTagged, pInt, try pEnum, try pReference , pMatrix, try pTupleWithout, pTupleWith , pRecord, pVariant , pSet @@ -148,6 +148,15 @@ parseDomainWithRepr = pDomainAtom let xs = fromMaybe [] mxs return $ DomainInt TagInt xs + pIntTagged = do + lexeme L_int + lexeme L_Colon + t <- identifierText + mxs <- optional $ parens $ commaSeparated0 $ parseRange parseExpr + let xs = fromMaybe [] mxs + return $ DomainInt (TaggedInt t) xs + + pReference = do r <- identifierText return $ DomainReference (Name r) Nothing @@ -548,7 +557,7 @@ parseLiteral = label "value" (do p <- pCore ; p) pCore = satisfyL $ \case L_false -> Just $ return $ Constant $ ConstantBool False L_true -> Just $ return $ Constant $ ConstantBool True - LIntLiteral i -> Just $ return $ Constant $ ConstantInt TagInt (fromInteger i) + LIntLiteral i -> Just $ msum [try (pIntTagged i), pInt i] L_OpenBracket -> Just pMatrix L_tuple -> Just pTupleWith L_OpenParen -> Just pTupleWithout @@ -567,6 +576,13 @@ parseLiteral = label "value" (do p <- pCore ; p) return (negate res) _ -> Nothing + pInt i = return $ Constant $ ConstantInt TagInt $ fromInteger i + + pIntTagged i = do + lexeme L_Colon + t <- identifierText + return $ Constant $ ConstantInt (TaggedInt t) $ fromInteger i + pMatrix = mkAbstractLiteral <$> do -- lexeme L_OpenBracket xs <- commaSeparated0 parseExpr diff --git a/src/Conjure/Language/Type.hs b/src/Conjure/Language/Type.hs index 0f4a1cf77b..b516645b7a 100644 --- a/src/Conjure/Language/Type.hs +++ b/src/Conjure/Language/Type.hs @@ -52,7 +52,10 @@ instance FromJSON Type where parseJSON = genericParseJSON jsonOptions instance Pretty Type where pretty TypeAny = "?" pretty TypeBool = "bool" - pretty TypeInt{} = "int" + pretty (TypeInt TagInt ) = "int" + pretty (TypeInt (TaggedInt t) ) = stringToDoc ("int:" ++ textToString t) + pretty (TypeInt (TagEnum t) ) = stringToDoc ("enum:" ++ textToString t) + pretty (TypeInt (TagUnnamed t)) = stringToDoc ("unnamed:" ++ textToString t) pretty (TypeEnum nm ) = pretty nm pretty (TypeUnnamed nm) = pretty nm pretty (TypeTuple xs) = (if length xs <= 1 then "tuple" else prEmpty) @@ -79,6 +82,7 @@ instance Pretty Type where data IntTag = TagInt -- was an integer in the input + | TaggedInt Text -- was an integer in the input with user specified tag | TagEnum Text -- was an enum in the input | TagUnnamed Text -- was an unnamed in the input deriving (Eq, Ord, Show, Data, Typeable, Generic) diff --git a/tests/custom/issues/119/1/stdout.expected b/tests/custom/issues/119/1/stdout.expected deleted file mode 100644 index b2205ad7a5..0000000000 --- a/tests/custom/issues/119/1/stdout.expected +++ /dev/null @@ -1,48 +0,0 @@ -Generating models for _old_issues_118_smaller.essence -Generated models: model_1.eprime, model_2.eprime, model_3.eprime, model_4.eprime -Saved under: conjure-output -Savile Row: model_1.eprime -Savile Row: model_2.eprime -Savile Row: model_3.eprime -Savile Row: model_4.eprime -Validating solution: conjure-output/model_1-solution000001.solution -Validating solution: conjure-output/model_2-solution000001.solution -Validating solution: conjure-output/model_3-solution000001.solution -Validating solution: conjure-output/model_4-solution000001.solution ----- -language Essence 1.3 - -letting p be partition({1}, {2}, {3}) -$ Visualisation for p -$ 1 -$ 2 -$ 3 - -language Essence 1.3 - -letting p be partition({1}, {2}, {3}) -$ Visualisation for p -$ 1 -$ 2 -$ 3 - -language Essence 1.3 - -letting p be partition({1}, {2}, {3}) -$ Visualisation for p -$ 1 -$ 2 -$ 3 - -language Essence 1.3 - -letting p be partition({1}, {2}, {3}) -$ Visualisation for p -$ 1 -$ 2 -$ 3 - ----- - -language Essence 1.3 -letting p be partition({1}, {2}, {3}) diff --git a/tests/custom/issues/119/2/stdout.expected b/tests/custom/issues/119/2/stdout.expected deleted file mode 100644 index 0a249bfa25..0000000000 --- a/tests/custom/issues/119/2/stdout.expected +++ /dev/null @@ -1,38 +0,0 @@ -Generating models for _old_issues_118_smaller2.essence -Generated models: model_1.eprime, model_2.eprime, model_3.eprime -Saved under: conjure-output -Savile Row: model_1.eprime -Savile Row: model_2.eprime -Savile Row: model_3.eprime -Validating solution: conjure-output/model_1-solution000001.solution -Validating solution: conjure-output/model_2-solution000001.solution -Validating solution: conjure-output/model_3-solution000001.solution ----- -language Essence 1.3 - -letting p be partition({1}, {2}, {3}) -$ Visualisation for p -$ 1 -$ 2 -$ 3 - -language Essence 1.3 - -letting p be partition({1}, {2}, {3}) -$ Visualisation for p -$ 1 -$ 2 -$ 3 - -language Essence 1.3 - -letting p be partition({1}, {2}, {3}) -$ Visualisation for p -$ 1 -$ 2 -$ 3 - ----- - -language Essence 1.3 -letting p be partition({1}, {2}, {3}) diff --git a/tests/custom/issues/370/01/stdout.expected b/tests/custom/issues/370/01/stdout.expected deleted file mode 100644 index 20a2ba4464..0000000000 --- a/tests/custom/issues/370/01/stdout.expected +++ /dev/null @@ -1,20 +0,0 @@ -Generating models for 370.essence -Generated models: model_1.eprime, model_2.eprime, model_3.eprime, model_4.eprime, model_5.eprime, model_6.eprime, - model_7.eprime, model_8.eprime -Saved under: conjure-output -Savile Row: model_1.eprime -Savile Row: model_2.eprime -Savile Row: model_3.eprime -Savile Row: model_4.eprime -Savile Row: model_5.eprime -Savile Row: model_6.eprime -Savile Row: model_7.eprime -Savile Row: model_8.eprime -Validating solution: conjure-output/model_1-solution000001.solution -Validating solution: conjure-output/model_2-solution000001.solution -Validating solution: conjure-output/model_3-solution000001.solution -Validating solution: conjure-output/model_4-solution000001.solution -Validating solution: conjure-output/model_5-solution000001.solution -Validating solution: conjure-output/model_6-solution000001.solution -Validating solution: conjure-output/model_7-solution000001.solution -Validating solution: conjure-output/model_8-solution000001.solution diff --git a/tests/custom/issues/370/03/stdout.expected b/tests/custom/issues/370/03/stdout.expected deleted file mode 100644 index ccb1bcd82c..0000000000 --- a/tests/custom/issues/370/03/stdout.expected +++ /dev/null @@ -1,11 +0,0 @@ -Generating models for 370.essence -Generated models: model_1.eprime, model_2.eprime, model_3.eprime, model_4.eprime -Saved under: conjure-output -Savile Row: model_1.eprime -Savile Row: model_2.eprime -Savile Row: model_3.eprime -Savile Row: model_4.eprime -Validating solution: conjure-output/model_1-solution000001.solution -Validating solution: conjure-output/model_2-solution000001.solution -Validating solution: conjure-output/model_3-solution000001.solution -Validating solution: conjure-output/model_4-solution000001.solution diff --git a/tests/custom/issues/388/2/stdout.expected b/tests/custom/issues/388/2/stdout.expected deleted file mode 100644 index 6e21cf60c3..0000000000 --- a/tests/custom/issues/388/2/stdout.expected +++ /dev/null @@ -1,125 +0,0 @@ -Generating models for 388-2.essence -Generated models: model_1_1.eprime, model_1_2.eprime, model_1_3.eprime, model_1_4.eprime, model_2_1.eprime, - model_2_2.eprime, model_2_3.eprime, model_2_4.eprime, model_3_1.eprime, model_3_2.eprime, - model_3_3.eprime, model_3_4.eprime, model_4_1.eprime, model_4_2.eprime, model_4_3.eprime, - model_4_4.eprime -Saved under: conjure-output -Savile Row: model_1_1.eprime -Savile Row: model_1_2.eprime -Savile Row: model_1_3.eprime -Savile Row: model_1_4.eprime -Savile Row: model_2_1.eprime -Savile Row: model_2_2.eprime -Savile Row: model_2_3.eprime -Savile Row: model_2_4.eprime -Savile Row: model_3_1.eprime -Savile Row: model_3_2.eprime -Savile Row: model_3_3.eprime -Savile Row: model_3_4.eprime -Savile Row: model_4_1.eprime -Savile Row: model_4_2.eprime -Savile Row: model_4_3.eprime -Savile Row: model_4_4.eprime -Validating solution: conjure-output/model_1_1-solution000001.solution -Validating solution: conjure-output/model_1_2-solution000001.solution -Validating solution: conjure-output/model_1_3-solution000001.solution -Validating solution: conjure-output/model_1_4-solution000001.solution -Validating solution: conjure-output/model_2_1-solution000001.solution -Validating solution: conjure-output/model_2_2-solution000001.solution -Validating solution: conjure-output/model_2_3-solution000001.solution -Validating solution: conjure-output/model_2_4-solution000001.solution -Validating solution: conjure-output/model_3_1-solution000001.solution -Validating solution: conjure-output/model_3_2-solution000001.solution -Validating solution: conjure-output/model_3_3-solution000001.solution -Validating solution: conjure-output/model_3_4-solution000001.solution -Validating solution: conjure-output/model_4_1-solution000001.solution -Validating solution: conjure-output/model_4_2-solution000001.solution -Validating solution: conjure-output/model_4_3-solution000001.solution -Validating solution: conjure-output/model_4_4-solution000001.solution ----- -language Essence 1.3 - -letting C be {1, 2, 3} -letting X be [2, 3, 1, 2, 3, 1, 2, 3, 1, 2; int(1..10)] -letting c be 3 -language Essence 1.3 - -letting C be {1, 2, 3} -letting X be [2, 3, 1, 2, 3, 1, 2, 3, 1, 2; int(1..10)] -letting c be 3 -language Essence 1.3 - -letting C be {1, 2, 3} -letting X be [2, 3, 1, 2, 3, 1, 2, 3, 1, 2; int(1..10)] -letting c be 3 -language Essence 1.3 - -letting C be {1, 2, 3} -letting X be [2, 3, 1, 2, 3, 1, 2, 3, 1, 2; int(1..10)] -letting c be 3 -language Essence 1.3 - -letting C be {1, 2, 3} -letting X be [2, 3, 1, 2, 3, 1, 2, 3, 1, 2; int(1..10)] -letting c be 3 -language Essence 1.3 - -letting C be {1, 2, 3} -letting X be [2, 3, 1, 2, 3, 1, 2, 3, 1, 2; int(1..10)] -letting c be 3 -language Essence 1.3 - -letting C be {1, 2, 3} -letting X be [2, 3, 1, 2, 3, 1, 2, 3, 1, 2; int(1..10)] -letting c be 3 -language Essence 1.3 - -letting C be {1, 2, 3} -letting X be [2, 3, 1, 2, 3, 1, 2, 3, 1, 2; int(1..10)] -letting c be 3 -language Essence 1.3 - -letting C be {1, 2, 3} -letting X be [2, 3, 1, 2, 3, 1, 2, 3, 1, 2; int(1..10)] -letting c be 3 -language Essence 1.3 - -letting C be {1, 2, 3} -letting X be [2, 3, 1, 2, 3, 1, 2, 3, 1, 2; int(1..10)] -letting c be 3 -language Essence 1.3 - -letting C be {1, 2, 3} -letting X be [2, 3, 1, 2, 3, 1, 2, 3, 1, 2; int(1..10)] -letting c be 3 -language Essence 1.3 - -letting C be {1, 2, 3} -letting X be [2, 3, 1, 2, 3, 1, 2, 3, 1, 2; int(1..10)] -letting c be 3 -language Essence 1.3 - -letting C be {1, 2, 3} -letting X be [2, 3, 1, 2, 3, 1, 2, 3, 1, 2; int(1..10)] -letting c be 3 -language Essence 1.3 - -letting C be {1, 2, 3} -letting X be [2, 3, 1, 2, 3, 1, 2, 3, 1, 2; int(1..10)] -letting c be 3 -language Essence 1.3 - -letting C be {1, 2, 3} -letting X be [2, 3, 1, 2, 3, 1, 2, 3, 1, 2; int(1..10)] -letting c be 3 -language Essence 1.3 - -letting C be {1, 2, 3} -letting X be [2, 3, 1, 2, 3, 1, 2, 3, 1, 2; int(1..10)] -letting c be 3 ----- - -language Essence 1.3 -letting C be {1, 2, 3} -letting X be [2, 3, 1, 2, 3, 1, 2, 3, 1, 2; int(1..10)] -letting c be 3 diff --git a/tests/custom/permutations/17_image_partition/enum/0010_given_partition_of_enum_BUG/stderr.expected b/tests/custom/permutations/17_image_partition/enum/0010_given_partition_of_enum_BUG/stderr.expected index 76cbe64a84..8d9e3b4c34 100644 --- a/tests/custom/permutations/17_image_partition/enum/0010_given_partition_of_enum_BUG/stderr.expected +++ b/tests/custom/permutations/17_image_partition/enum/0010_given_partition_of_enum_BUG/stderr.expected @@ -8,7 +8,7 @@ However, it did happen, so it must be a bug. Please report it to us! Conjure is actively maintained, we will get back to you as soon as possible. You can help us by providing a minimal failing example. -Also include the repository version for this build: f2abde262 (2019-01-10 15:23:36 +0000) +Also include the repository version for this build: 4a9d4ca08 (2019-02-26 14:02:10 +0000) Issue tracker: http://github.com/conjure-cp/conjure/issues @@ -20,6 +20,6 @@ Bindings in context: n: `int(1..4)` CallStack (from HasCallStack): - error, called at src/Conjure/Bug.hs:21:15 in conjure-cp-2.2.0-4cfnInyB42NJSP2i6f0krZ:Conjure.Bug - bug, called at src/Conjure/Bug.hs:47:16 in conjure-cp-2.2.0-4cfnInyB42NJSP2i6f0krZ:Conjure.Bug + error, called at src/Conjure/Bug.hs:21:15 in conjure-cp-2.2.0-71NFmy1yFuTKzqIQD5mEC7:Conjure.Bug + bug, called at src/Conjure/Bug.hs:47:16 in conjure-cp-2.2.0-71NFmy1yFuTKzqIQD5mEC7:Conjure.Bug cat: conjure-output/*.solution: No such file or directory diff --git a/tests/custom/permutations/22_tagged_ints/int/0001_permute_untagged/permutation.essence b/tests/custom/permutations/22_tagged_ints/int/0001_permute_untagged/permutation.essence new file mode 100644 index 0000000000..1ce852f79e --- /dev/null +++ b/tests/custom/permutations/22_tagged_ints/int/0001_permute_untagged/permutation.essence @@ -0,0 +1,5 @@ +find t : (int:A(1..6), int(1..6)) +find x : (int:A(1..6), int(1..6)) +such that x = image(permutation((1,2,3,4,5,6)),t) + + diff --git a/tests/custom/permutations/22_tagged_ints/int/0001_permute_untagged/run.sh b/tests/custom/permutations/22_tagged_ints/int/0001_permute_untagged/run.sh new file mode 100755 index 0000000000..b4899d6266 --- /dev/null +++ b/tests/custom/permutations/22_tagged_ints/int/0001_permute_untagged/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/22_tagged_ints/int/0001_permute_untagged/stdout.expected b/tests/custom/permutations/22_tagged_ints/int/0001_permute_untagged/stdout.expected new file mode 100644 index 0000000000..d8e77ec23e --- /dev/null +++ b/tests/custom/permutations/22_tagged_ints/int/0001_permute_untagged/stdout.expected @@ -0,0 +1,9 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Copying solution to: permutation.solution +language Essence 1.3 + +letting t be (1, 1) +letting x be (1, 2) diff --git a/tests/custom/permutations/22_tagged_ints/int/0002_permute_tagged/permutation.essence b/tests/custom/permutations/22_tagged_ints/int/0002_permute_tagged/permutation.essence new file mode 100644 index 0000000000..86b76d4f2d --- /dev/null +++ b/tests/custom/permutations/22_tagged_ints/int/0002_permute_tagged/permutation.essence @@ -0,0 +1,5 @@ +find t : (int:A(1..6), int(1..6)) +find x : (int:A(1..6), int(1..6)) +such that x = image(permutation((1:A,2:A,3:A,4:A,5:A,6:A)),t) + + diff --git a/tests/custom/permutations/22_tagged_ints/int/0002_permute_tagged/run.sh b/tests/custom/permutations/22_tagged_ints/int/0002_permute_tagged/run.sh new file mode 100755 index 0000000000..b4899d6266 --- /dev/null +++ b/tests/custom/permutations/22_tagged_ints/int/0002_permute_tagged/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/22_tagged_ints/int/0002_permute_tagged/stdout.expected b/tests/custom/permutations/22_tagged_ints/int/0002_permute_tagged/stdout.expected new file mode 100644 index 0000000000..4aa68baef7 --- /dev/null +++ b/tests/custom/permutations/22_tagged_ints/int/0002_permute_tagged/stdout.expected @@ -0,0 +1,9 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Copying solution to: permutation.solution +language Essence 1.3 + +letting t be (1, 1) +letting x be (2, 1) diff --git a/tests/custom/permutations/22_tagged_ints/int/0003_tagged_lits_in_param/permutation.essence b/tests/custom/permutations/22_tagged_ints/int/0003_tagged_lits_in_param/permutation.essence new file mode 100644 index 0000000000..6910c5ae6a --- /dev/null +++ b/tests/custom/permutations/22_tagged_ints/int/0003_tagged_lits_in_param/permutation.essence @@ -0,0 +1,6 @@ +find t : (int:A(1..6), int(1..6)) +find x : (int:A(1..6), int(1..6)) +given p : permutation of int:A(1..6) +such that x = image(p,t) + + diff --git a/tests/custom/permutations/22_tagged_ints/int/0003_tagged_lits_in_param/permutation.param b/tests/custom/permutations/22_tagged_ints/int/0003_tagged_lits_in_param/permutation.param new file mode 100644 index 0000000000..8b43dcc6c8 --- /dev/null +++ b/tests/custom/permutations/22_tagged_ints/int/0003_tagged_lits_in_param/permutation.param @@ -0,0 +1 @@ +letting p be permutation((1:A,2:A,3:A,4:A,5:A,6:A)) diff --git a/tests/custom/permutations/22_tagged_ints/int/0003_tagged_lits_in_param/run.sh b/tests/custom/permutations/22_tagged_ints/int/0003_tagged_lits_in_param/run.sh new file mode 100755 index 0000000000..9dc67e67f5 --- /dev/null +++ b/tests/custom/permutations/22_tagged_ints/int/0003_tagged_lits_in_param/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence *.param +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/22_tagged_ints/int/0003_tagged_lits_in_param/stdout.expected b/tests/custom/permutations/22_tagged_ints/int/0003_tagged_lits_in_param/stdout.expected new file mode 100644 index 0000000000..b4bc08fe98 --- /dev/null +++ b/tests/custom/permutations/22_tagged_ints/int/0003_tagged_lits_in_param/stdout.expected @@ -0,0 +1,9 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime permutation.param +Copying solution to: permutation-permutation.solution +language Essence 1.3 + +letting t be (1, 1) +letting x be (2, 1) diff --git a/tests/custom/permutations/22_tagged_ints/int/div/0001_same_tags_works/permutation.essence b/tests/custom/permutations/22_tagged_ints/int/div/0001_same_tags_works/permutation.essence new file mode 100644 index 0000000000..9418f406f9 --- /dev/null +++ b/tests/custom/permutations/22_tagged_ints/int/div/0001_same_tags_works/permutation.essence @@ -0,0 +1,5 @@ +find t : int:A(1..6) +find x : int:A(1..6) +such that x = t / 3:A + + diff --git a/tests/custom/permutations/22_tagged_ints/int/div/0001_same_tags_works/run.sh b/tests/custom/permutations/22_tagged_ints/int/div/0001_same_tags_works/run.sh new file mode 100755 index 0000000000..b4899d6266 --- /dev/null +++ b/tests/custom/permutations/22_tagged_ints/int/div/0001_same_tags_works/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/22_tagged_ints/int/div/0001_same_tags_works/stdout.expected b/tests/custom/permutations/22_tagged_ints/int/div/0001_same_tags_works/stdout.expected new file mode 100644 index 0000000000..4805b4c772 --- /dev/null +++ b/tests/custom/permutations/22_tagged_ints/int/div/0001_same_tags_works/stdout.expected @@ -0,0 +1,9 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Copying solution to: permutation.solution +language Essence 1.3 + +letting t be 3 +letting x be 1 diff --git a/tests/custom/permutations/22_tagged_ints/int/div/0002_diff_tags_prohibited/permutation.essence b/tests/custom/permutations/22_tagged_ints/int/div/0002_diff_tags_prohibited/permutation.essence new file mode 100644 index 0000000000..e3611ef6eb --- /dev/null +++ b/tests/custom/permutations/22_tagged_ints/int/div/0002_diff_tags_prohibited/permutation.essence @@ -0,0 +1,5 @@ +find t : int:A(1..6) +find x : int:A(1..6) +such that x = t / 3 + + diff --git a/tests/custom/permutations/22_tagged_ints/int/div/0002_diff_tags_prohibited/run.sh b/tests/custom/permutations/22_tagged_ints/int/div/0002_diff_tags_prohibited/run.sh new file mode 100755 index 0000000000..b4899d6266 --- /dev/null +++ b/tests/custom/permutations/22_tagged_ints/int/div/0002_diff_tags_prohibited/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/22_tagged_ints/int/div/0002_diff_tags_prohibited/stderr.expected b/tests/custom/permutations/22_tagged_ints/int/div/0002_diff_tags_prohibited/stderr.expected new file mode 100644 index 0000000000..fc43d15c41 --- /dev/null +++ b/tests/custom/permutations/22_tagged_ints/int/div/0002_diff_tags_prohibited/stderr.expected @@ -0,0 +1,6 @@ +Error: + In a 'such that' statement: x = t / 3 + Error: + When type checking: t / 3 + First argument expected to be an int, but it is: int:A +cat: conjure-output/*.solution: No such file or directory diff --git a/tests/custom/permutations/22_tagged_ints/int/div/0002_diff_tags_prohibited/stdout.expected b/tests/custom/permutations/22_tagged_ints/int/div/0002_diff_tags_prohibited/stdout.expected new file mode 100644 index 0000000000..d10ebe7b59 --- /dev/null +++ b/tests/custom/permutations/22_tagged_ints/int/div/0002_diff_tags_prohibited/stdout.expected @@ -0,0 +1 @@ +Generating models for permutation.essence diff --git a/tests/custom/permutations/22_tagged_ints/int/div/0003_const_tagged_works/permutation.essence b/tests/custom/permutations/22_tagged_ints/int/div/0003_const_tagged_works/permutation.essence new file mode 100644 index 0000000000..7fe43cd276 --- /dev/null +++ b/tests/custom/permutations/22_tagged_ints/int/div/0003_const_tagged_works/permutation.essence @@ -0,0 +1,4 @@ +find x : int:A(1..6) +such that x = 6:A / 3:A + + diff --git a/tests/custom/permutations/22_tagged_ints/int/div/0003_const_tagged_works/run.sh b/tests/custom/permutations/22_tagged_ints/int/div/0003_const_tagged_works/run.sh new file mode 100755 index 0000000000..b4899d6266 --- /dev/null +++ b/tests/custom/permutations/22_tagged_ints/int/div/0003_const_tagged_works/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/22_tagged_ints/int/div/0003_const_tagged_works/stdout.expected b/tests/custom/permutations/22_tagged_ints/int/div/0003_const_tagged_works/stdout.expected new file mode 100644 index 0000000000..ce08534589 --- /dev/null +++ b/tests/custom/permutations/22_tagged_ints/int/div/0003_const_tagged_works/stdout.expected @@ -0,0 +1,8 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Copying solution to: permutation.solution +language Essence 1.3 + +letting x be 2 diff --git a/tests/custom/permutations/22_tagged_ints/int/div/0004_enum_doesnt_work/permutation.essence b/tests/custom/permutations/22_tagged_ints/int/div/0004_enum_doesnt_work/permutation.essence new file mode 100644 index 0000000000..6a235469c4 --- /dev/null +++ b/tests/custom/permutations/22_tagged_ints/int/div/0004_enum_doesnt_work/permutation.essence @@ -0,0 +1,5 @@ +letting X be new type enum {e1,e2,e3,e4,e5,e6} +find x : X +such that x = e6 / e3 + + diff --git a/tests/custom/permutations/22_tagged_ints/int/div/0004_enum_doesnt_work/run.sh b/tests/custom/permutations/22_tagged_ints/int/div/0004_enum_doesnt_work/run.sh new file mode 100755 index 0000000000..b4899d6266 --- /dev/null +++ b/tests/custom/permutations/22_tagged_ints/int/div/0004_enum_doesnt_work/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/22_tagged_ints/int/div/0004_enum_doesnt_work/stderr.expected b/tests/custom/permutations/22_tagged_ints/int/div/0004_enum_doesnt_work/stderr.expected new file mode 100644 index 0000000000..f8961b84bf --- /dev/null +++ b/tests/custom/permutations/22_tagged_ints/int/div/0004_enum_doesnt_work/stderr.expected @@ -0,0 +1,6 @@ +Error: + In a 'such that' statement: x = 6 / 3 + Error: + When type checking: 6 / 3 + First argument expected to be an int, but it is: enum:X +cat: conjure-output/*.solution: No such file or directory diff --git a/tests/custom/permutations/22_tagged_ints/int/div/0004_enum_doesnt_work/stdout.expected b/tests/custom/permutations/22_tagged_ints/int/div/0004_enum_doesnt_work/stdout.expected new file mode 100644 index 0000000000..d10ebe7b59 --- /dev/null +++ b/tests/custom/permutations/22_tagged_ints/int/div/0004_enum_doesnt_work/stdout.expected @@ -0,0 +1 @@ +Generating models for permutation.essence diff --git a/tests/custom/permutations/22_tagged_ints/int/factorial/0002_diff_tags_prohibited/permutation.essence b/tests/custom/permutations/22_tagged_ints/int/factorial/0002_diff_tags_prohibited/permutation.essence new file mode 100644 index 0000000000..7c1b5fcc1c --- /dev/null +++ b/tests/custom/permutations/22_tagged_ints/int/factorial/0002_diff_tags_prohibited/permutation.essence @@ -0,0 +1,4 @@ +find x : int:A(1..6) +such that x! = 6 + + diff --git a/tests/custom/permutations/22_tagged_ints/int/factorial/0002_diff_tags_prohibited/run.sh b/tests/custom/permutations/22_tagged_ints/int/factorial/0002_diff_tags_prohibited/run.sh new file mode 100755 index 0000000000..b4899d6266 --- /dev/null +++ b/tests/custom/permutations/22_tagged_ints/int/factorial/0002_diff_tags_prohibited/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/22_tagged_ints/int/factorial/0002_diff_tags_prohibited/stderr.expected b/tests/custom/permutations/22_tagged_ints/int/factorial/0002_diff_tags_prohibited/stderr.expected new file mode 100644 index 0000000000..4a3b1708e3 --- /dev/null +++ b/tests/custom/permutations/22_tagged_ints/int/factorial/0002_diff_tags_prohibited/stderr.expected @@ -0,0 +1,10 @@ +Error: + In a 'such that' statement: factorial(x) = 6 + Error: + When type checking: factorial(x) = 6 + Cannot unify the types of the following. + lhs : factorial(x) + type of lhs: int:A + rhs : 6 + type of rhs: int +cat: conjure-output/*.solution: No such file or directory diff --git a/tests/custom/permutations/22_tagged_ints/int/factorial/0002_diff_tags_prohibited/stdout.expected b/tests/custom/permutations/22_tagged_ints/int/factorial/0002_diff_tags_prohibited/stdout.expected new file mode 100644 index 0000000000..d10ebe7b59 --- /dev/null +++ b/tests/custom/permutations/22_tagged_ints/int/factorial/0002_diff_tags_prohibited/stdout.expected @@ -0,0 +1 @@ +Generating models for permutation.essence diff --git a/tests/custom/permutations/22_tagged_ints/int/factorial/0003_const_tagged_works/permutation.essence b/tests/custom/permutations/22_tagged_ints/int/factorial/0003_const_tagged_works/permutation.essence new file mode 100644 index 0000000000..ca63321a1f --- /dev/null +++ b/tests/custom/permutations/22_tagged_ints/int/factorial/0003_const_tagged_works/permutation.essence @@ -0,0 +1,4 @@ +find x : int:A(1..6) +such that x = (3:A)! + + diff --git a/tests/custom/permutations/22_tagged_ints/int/factorial/0003_const_tagged_works/run.sh b/tests/custom/permutations/22_tagged_ints/int/factorial/0003_const_tagged_works/run.sh new file mode 100755 index 0000000000..b4899d6266 --- /dev/null +++ b/tests/custom/permutations/22_tagged_ints/int/factorial/0003_const_tagged_works/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/22_tagged_ints/int/factorial/0003_const_tagged_works/stdout.expected b/tests/custom/permutations/22_tagged_ints/int/factorial/0003_const_tagged_works/stdout.expected new file mode 100644 index 0000000000..79e05ead18 --- /dev/null +++ b/tests/custom/permutations/22_tagged_ints/int/factorial/0003_const_tagged_works/stdout.expected @@ -0,0 +1,8 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Copying solution to: permutation.solution +language Essence 1.3 + +letting x be 6 diff --git a/tests/custom/permutations/22_tagged_ints/int/geq/0002_diff_tags_prohibited/permutation.essence b/tests/custom/permutations/22_tagged_ints/int/geq/0002_diff_tags_prohibited/permutation.essence new file mode 100644 index 0000000000..0f2d9a40e1 --- /dev/null +++ b/tests/custom/permutations/22_tagged_ints/int/geq/0002_diff_tags_prohibited/permutation.essence @@ -0,0 +1,6 @@ +find x : int:A(1..6) +find y : int(1..6) + +such that x >= y + + diff --git a/tests/custom/permutations/22_tagged_ints/int/geq/0002_diff_tags_prohibited/run.sh b/tests/custom/permutations/22_tagged_ints/int/geq/0002_diff_tags_prohibited/run.sh new file mode 100755 index 0000000000..b4899d6266 --- /dev/null +++ b/tests/custom/permutations/22_tagged_ints/int/geq/0002_diff_tags_prohibited/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/22_tagged_ints/int/geq/0002_diff_tags_prohibited/stderr.expected b/tests/custom/permutations/22_tagged_ints/int/geq/0002_diff_tags_prohibited/stderr.expected new file mode 100644 index 0000000000..b3184742df --- /dev/null +++ b/tests/custom/permutations/22_tagged_ints/int/geq/0002_diff_tags_prohibited/stderr.expected @@ -0,0 +1,10 @@ +Error: + In a 'such that' statement: x >= y + Error: + When type checking: x >= y + Cannot unify the types of the following. + lhs : x + type of lhs: int:A + rhs : y + type of rhs: int +cat: conjure-output/*.solution: No such file or directory diff --git a/tests/custom/permutations/22_tagged_ints/int/geq/0002_diff_tags_prohibited/stdout.expected b/tests/custom/permutations/22_tagged_ints/int/geq/0002_diff_tags_prohibited/stdout.expected new file mode 100644 index 0000000000..d10ebe7b59 --- /dev/null +++ b/tests/custom/permutations/22_tagged_ints/int/geq/0002_diff_tags_prohibited/stdout.expected @@ -0,0 +1 @@ +Generating models for permutation.essence diff --git a/tests/custom/permutations/22_tagged_ints/int/geq/0003_const_tagged_works/permutation.essence b/tests/custom/permutations/22_tagged_ints/int/geq/0003_const_tagged_works/permutation.essence new file mode 100644 index 0000000000..23b62a29d8 --- /dev/null +++ b/tests/custom/permutations/22_tagged_ints/int/geq/0003_const_tagged_works/permutation.essence @@ -0,0 +1,5 @@ +find x : int:A(1..6) +find y : int:A(1..6) +such that x >= y + + diff --git a/tests/custom/permutations/22_tagged_ints/int/geq/0003_const_tagged_works/run.sh b/tests/custom/permutations/22_tagged_ints/int/geq/0003_const_tagged_works/run.sh new file mode 100755 index 0000000000..b4899d6266 --- /dev/null +++ b/tests/custom/permutations/22_tagged_ints/int/geq/0003_const_tagged_works/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/22_tagged_ints/int/geq/0003_const_tagged_works/stdout.expected b/tests/custom/permutations/22_tagged_ints/int/geq/0003_const_tagged_works/stdout.expected new file mode 100644 index 0000000000..25665ca6ca --- /dev/null +++ b/tests/custom/permutations/22_tagged_ints/int/geq/0003_const_tagged_works/stdout.expected @@ -0,0 +1,9 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Copying solution to: permutation.solution +language Essence 1.3 + +letting x be 1 +letting y be 1 diff --git a/tests/custom/permutations/22_tagged_ints/int/leq/0002_diff_tags_prohibited/permutation.essence b/tests/custom/permutations/22_tagged_ints/int/leq/0002_diff_tags_prohibited/permutation.essence new file mode 100644 index 0000000000..1aaa9a4d35 --- /dev/null +++ b/tests/custom/permutations/22_tagged_ints/int/leq/0002_diff_tags_prohibited/permutation.essence @@ -0,0 +1,6 @@ +find x : int:A(1..6) +find y : int(1..6) + +such that x <= y + + diff --git a/tests/custom/permutations/22_tagged_ints/int/leq/0002_diff_tags_prohibited/run.sh b/tests/custom/permutations/22_tagged_ints/int/leq/0002_diff_tags_prohibited/run.sh new file mode 100755 index 0000000000..b4899d6266 --- /dev/null +++ b/tests/custom/permutations/22_tagged_ints/int/leq/0002_diff_tags_prohibited/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/22_tagged_ints/int/leq/0002_diff_tags_prohibited/stderr.expected b/tests/custom/permutations/22_tagged_ints/int/leq/0002_diff_tags_prohibited/stderr.expected new file mode 100644 index 0000000000..6121d59c4e --- /dev/null +++ b/tests/custom/permutations/22_tagged_ints/int/leq/0002_diff_tags_prohibited/stderr.expected @@ -0,0 +1,10 @@ +Error: + In a 'such that' statement: x <= y + Error: + When type checking: x <= y + Cannot unify the types of the following. + lhs : x + type of lhs: int:A + rhs : y + type of rhs: int +cat: conjure-output/*.solution: No such file or directory diff --git a/tests/custom/permutations/22_tagged_ints/int/leq/0002_diff_tags_prohibited/stdout.expected b/tests/custom/permutations/22_tagged_ints/int/leq/0002_diff_tags_prohibited/stdout.expected new file mode 100644 index 0000000000..d10ebe7b59 --- /dev/null +++ b/tests/custom/permutations/22_tagged_ints/int/leq/0002_diff_tags_prohibited/stdout.expected @@ -0,0 +1 @@ +Generating models for permutation.essence diff --git a/tests/custom/permutations/22_tagged_ints/int/leq/0003_const_tagged_works/permutation.essence b/tests/custom/permutations/22_tagged_ints/int/leq/0003_const_tagged_works/permutation.essence new file mode 100644 index 0000000000..6950fcf208 --- /dev/null +++ b/tests/custom/permutations/22_tagged_ints/int/leq/0003_const_tagged_works/permutation.essence @@ -0,0 +1,5 @@ +find x : int:A(1..6) +find y : int:A(1..6) +such that x <= y + + diff --git a/tests/custom/permutations/22_tagged_ints/int/leq/0003_const_tagged_works/run.sh b/tests/custom/permutations/22_tagged_ints/int/leq/0003_const_tagged_works/run.sh new file mode 100755 index 0000000000..b4899d6266 --- /dev/null +++ b/tests/custom/permutations/22_tagged_ints/int/leq/0003_const_tagged_works/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/22_tagged_ints/int/leq/0003_const_tagged_works/stdout.expected b/tests/custom/permutations/22_tagged_ints/int/leq/0003_const_tagged_works/stdout.expected new file mode 100644 index 0000000000..25665ca6ca --- /dev/null +++ b/tests/custom/permutations/22_tagged_ints/int/leq/0003_const_tagged_works/stdout.expected @@ -0,0 +1,9 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Copying solution to: permutation.solution +language Essence 1.3 + +letting x be 1 +letting y be 1 diff --git a/tests/custom/permutations/22_tagged_ints/int/lt/0002_diff_tags_prohibited/permutation.essence b/tests/custom/permutations/22_tagged_ints/int/lt/0002_diff_tags_prohibited/permutation.essence new file mode 100644 index 0000000000..1c76db51f7 --- /dev/null +++ b/tests/custom/permutations/22_tagged_ints/int/lt/0002_diff_tags_prohibited/permutation.essence @@ -0,0 +1,6 @@ +find x : int:A(1..6) +find y : int(1..6) + +such that x < y + + diff --git a/tests/custom/permutations/22_tagged_ints/int/lt/0002_diff_tags_prohibited/run.sh b/tests/custom/permutations/22_tagged_ints/int/lt/0002_diff_tags_prohibited/run.sh new file mode 100755 index 0000000000..b4899d6266 --- /dev/null +++ b/tests/custom/permutations/22_tagged_ints/int/lt/0002_diff_tags_prohibited/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/22_tagged_ints/int/lt/0002_diff_tags_prohibited/stderr.expected b/tests/custom/permutations/22_tagged_ints/int/lt/0002_diff_tags_prohibited/stderr.expected new file mode 100644 index 0000000000..03a66a1533 --- /dev/null +++ b/tests/custom/permutations/22_tagged_ints/int/lt/0002_diff_tags_prohibited/stderr.expected @@ -0,0 +1,10 @@ +Error: + In a 'such that' statement: x < y + Error: + When type checking: x < y + Cannot unify the types of the following. + lhs : x + type of lhs: int:A + rhs : y + type of rhs: int +cat: conjure-output/*.solution: No such file or directory diff --git a/tests/custom/permutations/22_tagged_ints/int/lt/0002_diff_tags_prohibited/stdout.expected b/tests/custom/permutations/22_tagged_ints/int/lt/0002_diff_tags_prohibited/stdout.expected new file mode 100644 index 0000000000..d10ebe7b59 --- /dev/null +++ b/tests/custom/permutations/22_tagged_ints/int/lt/0002_diff_tags_prohibited/stdout.expected @@ -0,0 +1 @@ +Generating models for permutation.essence diff --git a/tests/custom/permutations/22_tagged_ints/int/lt/0003_const_tagged_works/permutation.essence b/tests/custom/permutations/22_tagged_ints/int/lt/0003_const_tagged_works/permutation.essence new file mode 100644 index 0000000000..9639e763a8 --- /dev/null +++ b/tests/custom/permutations/22_tagged_ints/int/lt/0003_const_tagged_works/permutation.essence @@ -0,0 +1,5 @@ +find x : int:A(1..6) +find y : int:A(1..6) +such that x < y + + diff --git a/tests/custom/permutations/22_tagged_ints/int/lt/0003_const_tagged_works/run.sh b/tests/custom/permutations/22_tagged_ints/int/lt/0003_const_tagged_works/run.sh new file mode 100755 index 0000000000..b4899d6266 --- /dev/null +++ b/tests/custom/permutations/22_tagged_ints/int/lt/0003_const_tagged_works/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/22_tagged_ints/int/lt/0003_const_tagged_works/stdout.expected b/tests/custom/permutations/22_tagged_ints/int/lt/0003_const_tagged_works/stdout.expected new file mode 100644 index 0000000000..b241021976 --- /dev/null +++ b/tests/custom/permutations/22_tagged_ints/int/lt/0003_const_tagged_works/stdout.expected @@ -0,0 +1,9 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Copying solution to: permutation.solution +language Essence 1.3 + +letting x be 1 +letting y be 2 diff --git a/tests/custom/permutations/22_tagged_ints/int/max/0001_same_tags_work/permutation.essence b/tests/custom/permutations/22_tagged_ints/int/max/0001_same_tags_work/permutation.essence new file mode 100644 index 0000000000..e78f3eedbc --- /dev/null +++ b/tests/custom/permutations/22_tagged_ints/int/max/0001_same_tags_work/permutation.essence @@ -0,0 +1,5 @@ +find t : set of int:A(1..6) +find x : int:A(2..4) +such that x = max(t) + + diff --git a/tests/custom/permutations/22_tagged_ints/int/max/0001_same_tags_work/run.sh b/tests/custom/permutations/22_tagged_ints/int/max/0001_same_tags_work/run.sh new file mode 100755 index 0000000000..b4899d6266 --- /dev/null +++ b/tests/custom/permutations/22_tagged_ints/int/max/0001_same_tags_work/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/22_tagged_ints/int/max/0001_same_tags_work/stdout.expected b/tests/custom/permutations/22_tagged_ints/int/max/0001_same_tags_work/stdout.expected new file mode 100644 index 0000000000..bf44838b4f --- /dev/null +++ b/tests/custom/permutations/22_tagged_ints/int/max/0001_same_tags_work/stdout.expected @@ -0,0 +1,9 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Copying solution to: permutation.solution +language Essence 1.3 + +letting t be {4} +letting x be 4 diff --git a/tests/custom/permutations/22_tagged_ints/int/max/0002_diff_tags_prohibited/permutation.essence b/tests/custom/permutations/22_tagged_ints/int/max/0002_diff_tags_prohibited/permutation.essence new file mode 100644 index 0000000000..eb1704e28a --- /dev/null +++ b/tests/custom/permutations/22_tagged_ints/int/max/0002_diff_tags_prohibited/permutation.essence @@ -0,0 +1,5 @@ +find t : set of int:A(1..6) +find x : int(2..4) +such that x = max(t) + + diff --git a/tests/custom/permutations/22_tagged_ints/int/max/0002_diff_tags_prohibited/run.sh b/tests/custom/permutations/22_tagged_ints/int/max/0002_diff_tags_prohibited/run.sh new file mode 100755 index 0000000000..b4899d6266 --- /dev/null +++ b/tests/custom/permutations/22_tagged_ints/int/max/0002_diff_tags_prohibited/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/22_tagged_ints/int/max/0002_diff_tags_prohibited/stderr.expected b/tests/custom/permutations/22_tagged_ints/int/max/0002_diff_tags_prohibited/stderr.expected new file mode 100644 index 0000000000..249ac355e6 --- /dev/null +++ b/tests/custom/permutations/22_tagged_ints/int/max/0002_diff_tags_prohibited/stderr.expected @@ -0,0 +1,10 @@ +Error: + In a 'such that' statement: x = max(t) + Error: + When type checking: x = max(t) + Cannot unify the types of the following. + lhs : x + type of lhs: int + rhs : max(t) + type of rhs: int:A +cat: conjure-output/*.solution: No such file or directory diff --git a/tests/custom/permutations/22_tagged_ints/int/max/0002_diff_tags_prohibited/stdout.expected b/tests/custom/permutations/22_tagged_ints/int/max/0002_diff_tags_prohibited/stdout.expected new file mode 100644 index 0000000000..d10ebe7b59 --- /dev/null +++ b/tests/custom/permutations/22_tagged_ints/int/max/0002_diff_tags_prohibited/stdout.expected @@ -0,0 +1 @@ +Generating models for permutation.essence diff --git a/tests/custom/permutations/22_tagged_ints/int/max/0003_const_tagged_works/permutation.essence b/tests/custom/permutations/22_tagged_ints/int/max/0003_const_tagged_works/permutation.essence new file mode 100644 index 0000000000..4fca4ecb97 --- /dev/null +++ b/tests/custom/permutations/22_tagged_ints/int/max/0003_const_tagged_works/permutation.essence @@ -0,0 +1,5 @@ +find t : set of int:A(1..6) + +such that 3:A = max(t) + + diff --git a/tests/custom/permutations/22_tagged_ints/int/max/0003_const_tagged_works/run.sh b/tests/custom/permutations/22_tagged_ints/int/max/0003_const_tagged_works/run.sh new file mode 100755 index 0000000000..b4899d6266 --- /dev/null +++ b/tests/custom/permutations/22_tagged_ints/int/max/0003_const_tagged_works/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/22_tagged_ints/int/max/0003_const_tagged_works/stdout.expected b/tests/custom/permutations/22_tagged_ints/int/max/0003_const_tagged_works/stdout.expected new file mode 100644 index 0000000000..df7b739bcd --- /dev/null +++ b/tests/custom/permutations/22_tagged_ints/int/max/0003_const_tagged_works/stdout.expected @@ -0,0 +1,8 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Copying solution to: permutation.solution +language Essence 1.3 + +letting t be {3} diff --git a/tests/custom/permutations/22_tagged_ints/int/min/0001_same_tags_work/permutation.essence b/tests/custom/permutations/22_tagged_ints/int/min/0001_same_tags_work/permutation.essence new file mode 100644 index 0000000000..15b6dfd5a2 --- /dev/null +++ b/tests/custom/permutations/22_tagged_ints/int/min/0001_same_tags_work/permutation.essence @@ -0,0 +1,5 @@ +find t : set of int:A(1..6) +find x : int:A(2..4) +such that x = min(t) + + diff --git a/tests/custom/permutations/22_tagged_ints/int/min/0001_same_tags_work/run.sh b/tests/custom/permutations/22_tagged_ints/int/min/0001_same_tags_work/run.sh new file mode 100755 index 0000000000..b4899d6266 --- /dev/null +++ b/tests/custom/permutations/22_tagged_ints/int/min/0001_same_tags_work/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/22_tagged_ints/int/min/0001_same_tags_work/stdout.expected b/tests/custom/permutations/22_tagged_ints/int/min/0001_same_tags_work/stdout.expected new file mode 100644 index 0000000000..bf44838b4f --- /dev/null +++ b/tests/custom/permutations/22_tagged_ints/int/min/0001_same_tags_work/stdout.expected @@ -0,0 +1,9 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Copying solution to: permutation.solution +language Essence 1.3 + +letting t be {4} +letting x be 4 diff --git a/tests/custom/permutations/22_tagged_ints/int/min/0002_diff_tags_prohibited/permutation.essence b/tests/custom/permutations/22_tagged_ints/int/min/0002_diff_tags_prohibited/permutation.essence new file mode 100644 index 0000000000..f4ec790a15 --- /dev/null +++ b/tests/custom/permutations/22_tagged_ints/int/min/0002_diff_tags_prohibited/permutation.essence @@ -0,0 +1,5 @@ +find t : set of int:A(1..6) +find x : int(2..4) +such that x = min(t) + + diff --git a/tests/custom/permutations/22_tagged_ints/int/min/0002_diff_tags_prohibited/run.sh b/tests/custom/permutations/22_tagged_ints/int/min/0002_diff_tags_prohibited/run.sh new file mode 100755 index 0000000000..b4899d6266 --- /dev/null +++ b/tests/custom/permutations/22_tagged_ints/int/min/0002_diff_tags_prohibited/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/22_tagged_ints/int/min/0002_diff_tags_prohibited/stderr.expected b/tests/custom/permutations/22_tagged_ints/int/min/0002_diff_tags_prohibited/stderr.expected new file mode 100644 index 0000000000..0be983c55d --- /dev/null +++ b/tests/custom/permutations/22_tagged_ints/int/min/0002_diff_tags_prohibited/stderr.expected @@ -0,0 +1,10 @@ +Error: + In a 'such that' statement: x = min(t) + Error: + When type checking: x = min(t) + Cannot unify the types of the following. + lhs : x + type of lhs: int + rhs : min(t) + type of rhs: int:A +cat: conjure-output/*.solution: No such file or directory diff --git a/tests/custom/permutations/22_tagged_ints/int/min/0002_diff_tags_prohibited/stdout.expected b/tests/custom/permutations/22_tagged_ints/int/min/0002_diff_tags_prohibited/stdout.expected new file mode 100644 index 0000000000..d10ebe7b59 --- /dev/null +++ b/tests/custom/permutations/22_tagged_ints/int/min/0002_diff_tags_prohibited/stdout.expected @@ -0,0 +1 @@ +Generating models for permutation.essence diff --git a/tests/custom/permutations/22_tagged_ints/int/min/0003_const_tagged_works/permutation.essence b/tests/custom/permutations/22_tagged_ints/int/min/0003_const_tagged_works/permutation.essence new file mode 100644 index 0000000000..2a05fb9ec0 --- /dev/null +++ b/tests/custom/permutations/22_tagged_ints/int/min/0003_const_tagged_works/permutation.essence @@ -0,0 +1,5 @@ +find t : set of int:A(1..6) + +such that 3:A = min(t) + + diff --git a/tests/custom/permutations/22_tagged_ints/int/min/0003_const_tagged_works/run.sh b/tests/custom/permutations/22_tagged_ints/int/min/0003_const_tagged_works/run.sh new file mode 100755 index 0000000000..b4899d6266 --- /dev/null +++ b/tests/custom/permutations/22_tagged_ints/int/min/0003_const_tagged_works/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/22_tagged_ints/int/min/0003_const_tagged_works/stdout.expected b/tests/custom/permutations/22_tagged_ints/int/min/0003_const_tagged_works/stdout.expected new file mode 100644 index 0000000000..df7b739bcd --- /dev/null +++ b/tests/custom/permutations/22_tagged_ints/int/min/0003_const_tagged_works/stdout.expected @@ -0,0 +1,8 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Copying solution to: permutation.solution +language Essence 1.3 + +letting t be {3} diff --git a/tests/custom/permutations/22_tagged_ints/int/minus/0001_same_tags_works/permutation.essence b/tests/custom/permutations/22_tagged_ints/int/minus/0001_same_tags_works/permutation.essence new file mode 100644 index 0000000000..672589ee10 --- /dev/null +++ b/tests/custom/permutations/22_tagged_ints/int/minus/0001_same_tags_works/permutation.essence @@ -0,0 +1,5 @@ +find t : int:A(1..6) +find x : int:A(1..6) +such that x = t - 4:A + + diff --git a/tests/custom/permutations/22_tagged_ints/int/minus/0001_same_tags_works/run.sh b/tests/custom/permutations/22_tagged_ints/int/minus/0001_same_tags_works/run.sh new file mode 100755 index 0000000000..b4899d6266 --- /dev/null +++ b/tests/custom/permutations/22_tagged_ints/int/minus/0001_same_tags_works/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/22_tagged_ints/int/minus/0001_same_tags_works/stdout.expected b/tests/custom/permutations/22_tagged_ints/int/minus/0001_same_tags_works/stdout.expected new file mode 100644 index 0000000000..592ae071db --- /dev/null +++ b/tests/custom/permutations/22_tagged_ints/int/minus/0001_same_tags_works/stdout.expected @@ -0,0 +1,9 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Copying solution to: permutation.solution +language Essence 1.3 + +letting t be 5 +letting x be 1 diff --git a/tests/custom/permutations/22_tagged_ints/int/minus/0002_diff_tags_prohibited/permutation.essence b/tests/custom/permutations/22_tagged_ints/int/minus/0002_diff_tags_prohibited/permutation.essence new file mode 100644 index 0000000000..3f9f59c620 --- /dev/null +++ b/tests/custom/permutations/22_tagged_ints/int/minus/0002_diff_tags_prohibited/permutation.essence @@ -0,0 +1,5 @@ +find t : int:A(1..6) +find x : int:A(1..6) +such that x = t - 4 + + diff --git a/tests/custom/permutations/22_tagged_ints/int/minus/0002_diff_tags_prohibited/run.sh b/tests/custom/permutations/22_tagged_ints/int/minus/0002_diff_tags_prohibited/run.sh new file mode 100755 index 0000000000..b4899d6266 --- /dev/null +++ b/tests/custom/permutations/22_tagged_ints/int/minus/0002_diff_tags_prohibited/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/22_tagged_ints/int/minus/0002_diff_tags_prohibited/stderr.expected b/tests/custom/permutations/22_tagged_ints/int/minus/0002_diff_tags_prohibited/stderr.expected new file mode 100644 index 0000000000..df5d28699f --- /dev/null +++ b/tests/custom/permutations/22_tagged_ints/int/minus/0002_diff_tags_prohibited/stderr.expected @@ -0,0 +1,10 @@ +Error: + In a 'such that' statement: x = t - 4 + Error: + When type checking: t - 4 + Cannot unify the types of the following. + lhs : t + type of lhs: int:A + rhs : 4 + type of rhs: int +cat: conjure-output/*.solution: No such file or directory diff --git a/tests/custom/permutations/22_tagged_ints/int/minus/0002_diff_tags_prohibited/stdout.expected b/tests/custom/permutations/22_tagged_ints/int/minus/0002_diff_tags_prohibited/stdout.expected new file mode 100644 index 0000000000..d10ebe7b59 --- /dev/null +++ b/tests/custom/permutations/22_tagged_ints/int/minus/0002_diff_tags_prohibited/stdout.expected @@ -0,0 +1 @@ +Generating models for permutation.essence diff --git a/tests/custom/permutations/22_tagged_ints/int/minus/0003_const_tagged_works/permutation.essence b/tests/custom/permutations/22_tagged_ints/int/minus/0003_const_tagged_works/permutation.essence new file mode 100644 index 0000000000..57e2255d86 --- /dev/null +++ b/tests/custom/permutations/22_tagged_ints/int/minus/0003_const_tagged_works/permutation.essence @@ -0,0 +1,4 @@ +find x : int:A(1..6) +such that x = 6:A - 4:A + + diff --git a/tests/custom/permutations/22_tagged_ints/int/minus/0003_const_tagged_works/run.sh b/tests/custom/permutations/22_tagged_ints/int/minus/0003_const_tagged_works/run.sh new file mode 100755 index 0000000000..b4899d6266 --- /dev/null +++ b/tests/custom/permutations/22_tagged_ints/int/minus/0003_const_tagged_works/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/22_tagged_ints/int/minus/0003_const_tagged_works/stdout.expected b/tests/custom/permutations/22_tagged_ints/int/minus/0003_const_tagged_works/stdout.expected new file mode 100644 index 0000000000..ce08534589 --- /dev/null +++ b/tests/custom/permutations/22_tagged_ints/int/minus/0003_const_tagged_works/stdout.expected @@ -0,0 +1,8 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Copying solution to: permutation.solution +language Essence 1.3 + +letting x be 2 diff --git a/tests/custom/permutations/22_tagged_ints/int/mod/0001_same_tags_works/permutation.essence b/tests/custom/permutations/22_tagged_ints/int/mod/0001_same_tags_works/permutation.essence new file mode 100644 index 0000000000..aa8f87ed20 --- /dev/null +++ b/tests/custom/permutations/22_tagged_ints/int/mod/0001_same_tags_works/permutation.essence @@ -0,0 +1,5 @@ +find t : int:A(1..6) +find x : int:A(1..6) +such that x = t%4:A + + diff --git a/tests/custom/permutations/22_tagged_ints/int/mod/0001_same_tags_works/run.sh b/tests/custom/permutations/22_tagged_ints/int/mod/0001_same_tags_works/run.sh new file mode 100755 index 0000000000..b4899d6266 --- /dev/null +++ b/tests/custom/permutations/22_tagged_ints/int/mod/0001_same_tags_works/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/22_tagged_ints/int/mod/0001_same_tags_works/stdout.expected b/tests/custom/permutations/22_tagged_ints/int/mod/0001_same_tags_works/stdout.expected new file mode 100644 index 0000000000..bbc23f8d00 --- /dev/null +++ b/tests/custom/permutations/22_tagged_ints/int/mod/0001_same_tags_works/stdout.expected @@ -0,0 +1,9 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Copying solution to: permutation.solution +language Essence 1.3 + +letting t be 1 +letting x be 1 diff --git a/tests/custom/permutations/22_tagged_ints/int/mod/0002_diff_tags_prohibited/permutation.essence b/tests/custom/permutations/22_tagged_ints/int/mod/0002_diff_tags_prohibited/permutation.essence new file mode 100644 index 0000000000..4f930c919d --- /dev/null +++ b/tests/custom/permutations/22_tagged_ints/int/mod/0002_diff_tags_prohibited/permutation.essence @@ -0,0 +1,5 @@ +find t : int:A(1..6) +find x : int:A(1..6) +such that x = t%4 + + diff --git a/tests/custom/permutations/22_tagged_ints/int/mod/0002_diff_tags_prohibited/run.sh b/tests/custom/permutations/22_tagged_ints/int/mod/0002_diff_tags_prohibited/run.sh new file mode 100755 index 0000000000..b4899d6266 --- /dev/null +++ b/tests/custom/permutations/22_tagged_ints/int/mod/0002_diff_tags_prohibited/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/22_tagged_ints/int/mod/0002_diff_tags_prohibited/stderr.expected b/tests/custom/permutations/22_tagged_ints/int/mod/0002_diff_tags_prohibited/stderr.expected new file mode 100644 index 0000000000..453d0f71f2 --- /dev/null +++ b/tests/custom/permutations/22_tagged_ints/int/mod/0002_diff_tags_prohibited/stderr.expected @@ -0,0 +1,6 @@ +Error: + In a 'such that' statement: x = t % 4 + Error: + When type checking: t % 4 + Types do not unify: int:A +cat: conjure-output/*.solution: No such file or directory diff --git a/tests/custom/permutations/22_tagged_ints/int/mod/0002_diff_tags_prohibited/stdout.expected b/tests/custom/permutations/22_tagged_ints/int/mod/0002_diff_tags_prohibited/stdout.expected new file mode 100644 index 0000000000..d10ebe7b59 --- /dev/null +++ b/tests/custom/permutations/22_tagged_ints/int/mod/0002_diff_tags_prohibited/stdout.expected @@ -0,0 +1 @@ +Generating models for permutation.essence diff --git a/tests/custom/permutations/22_tagged_ints/int/mod/0003_const_tagged_works/permutation.essence b/tests/custom/permutations/22_tagged_ints/int/mod/0003_const_tagged_works/permutation.essence new file mode 100644 index 0000000000..e8e597556d --- /dev/null +++ b/tests/custom/permutations/22_tagged_ints/int/mod/0003_const_tagged_works/permutation.essence @@ -0,0 +1,4 @@ +find x : int:A(1..6) +such that x = 2:A%4:A + + diff --git a/tests/custom/permutations/22_tagged_ints/int/mod/0003_const_tagged_works/run.sh b/tests/custom/permutations/22_tagged_ints/int/mod/0003_const_tagged_works/run.sh new file mode 100755 index 0000000000..b4899d6266 --- /dev/null +++ b/tests/custom/permutations/22_tagged_ints/int/mod/0003_const_tagged_works/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/22_tagged_ints/int/mod/0003_const_tagged_works/stdout.expected b/tests/custom/permutations/22_tagged_ints/int/mod/0003_const_tagged_works/stdout.expected new file mode 100644 index 0000000000..ce08534589 --- /dev/null +++ b/tests/custom/permutations/22_tagged_ints/int/mod/0003_const_tagged_works/stdout.expected @@ -0,0 +1,8 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Copying solution to: permutation.solution +language Essence 1.3 + +letting x be 2 diff --git a/tests/custom/permutations/22_tagged_ints/int/neg/0001_same_tags_works/permutation.essence b/tests/custom/permutations/22_tagged_ints/int/neg/0001_same_tags_works/permutation.essence new file mode 100644 index 0000000000..db85b36169 --- /dev/null +++ b/tests/custom/permutations/22_tagged_ints/int/neg/0001_same_tags_works/permutation.essence @@ -0,0 +1,5 @@ +find t : int:A(-6..6) +find x : int:A(-6..6) +such that x = -t + + diff --git a/tests/custom/permutations/22_tagged_ints/int/neg/0001_same_tags_works/run.sh b/tests/custom/permutations/22_tagged_ints/int/neg/0001_same_tags_works/run.sh new file mode 100755 index 0000000000..b4899d6266 --- /dev/null +++ b/tests/custom/permutations/22_tagged_ints/int/neg/0001_same_tags_works/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/22_tagged_ints/int/neg/0001_same_tags_works/stdout.expected b/tests/custom/permutations/22_tagged_ints/int/neg/0001_same_tags_works/stdout.expected new file mode 100644 index 0000000000..2239389f44 --- /dev/null +++ b/tests/custom/permutations/22_tagged_ints/int/neg/0001_same_tags_works/stdout.expected @@ -0,0 +1,9 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Copying solution to: permutation.solution +language Essence 1.3 + +letting t be -6 +letting x be 6 diff --git a/tests/custom/permutations/22_tagged_ints/int/neg/0002_diff_tags_prohibited/permutation.essence b/tests/custom/permutations/22_tagged_ints/int/neg/0002_diff_tags_prohibited/permutation.essence new file mode 100644 index 0000000000..eabd834673 --- /dev/null +++ b/tests/custom/permutations/22_tagged_ints/int/neg/0002_diff_tags_prohibited/permutation.essence @@ -0,0 +1,5 @@ +find t : int:A(-6..6) +find x : int(-6..6) +such that x = -t + + diff --git a/tests/custom/permutations/22_tagged_ints/int/neg/0002_diff_tags_prohibited/run.sh b/tests/custom/permutations/22_tagged_ints/int/neg/0002_diff_tags_prohibited/run.sh new file mode 100755 index 0000000000..b4899d6266 --- /dev/null +++ b/tests/custom/permutations/22_tagged_ints/int/neg/0002_diff_tags_prohibited/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/22_tagged_ints/int/neg/0002_diff_tags_prohibited/stderr.expected b/tests/custom/permutations/22_tagged_ints/int/neg/0002_diff_tags_prohibited/stderr.expected new file mode 100644 index 0000000000..2ba6915ac8 --- /dev/null +++ b/tests/custom/permutations/22_tagged_ints/int/neg/0002_diff_tags_prohibited/stderr.expected @@ -0,0 +1,10 @@ +Error: + In a 'such that' statement: x = -t + Error: + When type checking: x = -t + Cannot unify the types of the following. + lhs : x + type of lhs: int + rhs : -t + type of rhs: int:A +cat: conjure-output/*.solution: No such file or directory diff --git a/tests/custom/permutations/22_tagged_ints/int/neg/0002_diff_tags_prohibited/stdout.expected b/tests/custom/permutations/22_tagged_ints/int/neg/0002_diff_tags_prohibited/stdout.expected new file mode 100644 index 0000000000..d10ebe7b59 --- /dev/null +++ b/tests/custom/permutations/22_tagged_ints/int/neg/0002_diff_tags_prohibited/stdout.expected @@ -0,0 +1 @@ +Generating models for permutation.essence diff --git a/tests/custom/permutations/22_tagged_ints/int/neg/0003_const_tagged_works/permutation.essence b/tests/custom/permutations/22_tagged_ints/int/neg/0003_const_tagged_works/permutation.essence new file mode 100644 index 0000000000..da4b7c7f99 --- /dev/null +++ b/tests/custom/permutations/22_tagged_ints/int/neg/0003_const_tagged_works/permutation.essence @@ -0,0 +1,4 @@ +find x : int:A(-6..6) +such that x = -2:A + + diff --git a/tests/custom/permutations/22_tagged_ints/int/neg/0003_const_tagged_works/run.sh b/tests/custom/permutations/22_tagged_ints/int/neg/0003_const_tagged_works/run.sh new file mode 100755 index 0000000000..b4899d6266 --- /dev/null +++ b/tests/custom/permutations/22_tagged_ints/int/neg/0003_const_tagged_works/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/22_tagged_ints/int/neg/0003_const_tagged_works/stdout.expected b/tests/custom/permutations/22_tagged_ints/int/neg/0003_const_tagged_works/stdout.expected new file mode 100644 index 0000000000..3484829aca --- /dev/null +++ b/tests/custom/permutations/22_tagged_ints/int/neg/0003_const_tagged_works/stdout.expected @@ -0,0 +1,8 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Copying solution to: permutation.solution +language Essence 1.3 + +letting x be -2 diff --git a/tests/custom/permutations/22_tagged_ints/int/pred/0002_diff_tags_prohibited/permutation.essence b/tests/custom/permutations/22_tagged_ints/int/pred/0002_diff_tags_prohibited/permutation.essence new file mode 100644 index 0000000000..7c3746a24c --- /dev/null +++ b/tests/custom/permutations/22_tagged_ints/int/pred/0002_diff_tags_prohibited/permutation.essence @@ -0,0 +1,6 @@ +find x : int:A(1..6) +find y : int(1..6) + +such that x = pred(y) + + diff --git a/tests/custom/permutations/22_tagged_ints/int/pred/0002_diff_tags_prohibited/run.sh b/tests/custom/permutations/22_tagged_ints/int/pred/0002_diff_tags_prohibited/run.sh new file mode 100755 index 0000000000..b4899d6266 --- /dev/null +++ b/tests/custom/permutations/22_tagged_ints/int/pred/0002_diff_tags_prohibited/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/22_tagged_ints/int/pred/0002_diff_tags_prohibited/stderr.expected b/tests/custom/permutations/22_tagged_ints/int/pred/0002_diff_tags_prohibited/stderr.expected new file mode 100644 index 0000000000..d862c7c880 --- /dev/null +++ b/tests/custom/permutations/22_tagged_ints/int/pred/0002_diff_tags_prohibited/stderr.expected @@ -0,0 +1,10 @@ +Error: + In a 'such that' statement: x = pred(y) + Error: + When type checking: x = pred(y) + Cannot unify the types of the following. + lhs : x + type of lhs: int:A + rhs : pred(y) + type of rhs: int +cat: conjure-output/*.solution: No such file or directory diff --git a/tests/custom/permutations/22_tagged_ints/int/pred/0002_diff_tags_prohibited/stdout.expected b/tests/custom/permutations/22_tagged_ints/int/pred/0002_diff_tags_prohibited/stdout.expected new file mode 100644 index 0000000000..d10ebe7b59 --- /dev/null +++ b/tests/custom/permutations/22_tagged_ints/int/pred/0002_diff_tags_prohibited/stdout.expected @@ -0,0 +1 @@ +Generating models for permutation.essence diff --git a/tests/custom/permutations/22_tagged_ints/int/pred/0003_const_tagged_works/permutation.essence b/tests/custom/permutations/22_tagged_ints/int/pred/0003_const_tagged_works/permutation.essence new file mode 100644 index 0000000000..1661e2ebea --- /dev/null +++ b/tests/custom/permutations/22_tagged_ints/int/pred/0003_const_tagged_works/permutation.essence @@ -0,0 +1,5 @@ +find x : int:A(1..6) +find y : int:A(1..6) +such that x = pred(y) + + diff --git a/tests/custom/permutations/22_tagged_ints/int/pred/0003_const_tagged_works/run.sh b/tests/custom/permutations/22_tagged_ints/int/pred/0003_const_tagged_works/run.sh new file mode 100755 index 0000000000..b4899d6266 --- /dev/null +++ b/tests/custom/permutations/22_tagged_ints/int/pred/0003_const_tagged_works/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/22_tagged_ints/int/pred/0003_const_tagged_works/stdout.expected b/tests/custom/permutations/22_tagged_ints/int/pred/0003_const_tagged_works/stdout.expected new file mode 100644 index 0000000000..b241021976 --- /dev/null +++ b/tests/custom/permutations/22_tagged_ints/int/pred/0003_const_tagged_works/stdout.expected @@ -0,0 +1,9 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Copying solution to: permutation.solution +language Essence 1.3 + +letting x be 1 +letting y be 2 diff --git a/tests/custom/permutations/22_tagged_ints/int/prod/0001_same_tags_works/permutation.essence b/tests/custom/permutations/22_tagged_ints/int/prod/0001_same_tags_works/permutation.essence new file mode 100644 index 0000000000..44c42e4874 --- /dev/null +++ b/tests/custom/permutations/22_tagged_ints/int/prod/0001_same_tags_works/permutation.essence @@ -0,0 +1,5 @@ +find t : int:A(1..6) +find x : int:A(1..6) +such that x = t * 3:A + + diff --git a/tests/custom/permutations/22_tagged_ints/int/prod/0001_same_tags_works/run.sh b/tests/custom/permutations/22_tagged_ints/int/prod/0001_same_tags_works/run.sh new file mode 100755 index 0000000000..b4899d6266 --- /dev/null +++ b/tests/custom/permutations/22_tagged_ints/int/prod/0001_same_tags_works/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/22_tagged_ints/int/prod/0001_same_tags_works/stdout.expected b/tests/custom/permutations/22_tagged_ints/int/prod/0001_same_tags_works/stdout.expected new file mode 100644 index 0000000000..eee4b0542b --- /dev/null +++ b/tests/custom/permutations/22_tagged_ints/int/prod/0001_same_tags_works/stdout.expected @@ -0,0 +1,9 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Copying solution to: permutation.solution +language Essence 1.3 + +letting t be 1 +letting x be 3 diff --git a/tests/custom/permutations/22_tagged_ints/int/prod/0002_diff_tags_prohibited/permutation.essence b/tests/custom/permutations/22_tagged_ints/int/prod/0002_diff_tags_prohibited/permutation.essence new file mode 100644 index 0000000000..c3889c09f7 --- /dev/null +++ b/tests/custom/permutations/22_tagged_ints/int/prod/0002_diff_tags_prohibited/permutation.essence @@ -0,0 +1,5 @@ +find t : int:A(1..6) +find x : int:A(1..6) +such that x = t * 3 + + diff --git a/tests/custom/permutations/22_tagged_ints/int/prod/0002_diff_tags_prohibited/run.sh b/tests/custom/permutations/22_tagged_ints/int/prod/0002_diff_tags_prohibited/run.sh new file mode 100755 index 0000000000..b4899d6266 --- /dev/null +++ b/tests/custom/permutations/22_tagged_ints/int/prod/0002_diff_tags_prohibited/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/22_tagged_ints/int/prod/0002_diff_tags_prohibited/stderr.expected b/tests/custom/permutations/22_tagged_ints/int/prod/0002_diff_tags_prohibited/stderr.expected new file mode 100644 index 0000000000..a7dce442b8 --- /dev/null +++ b/tests/custom/permutations/22_tagged_ints/int/prod/0002_diff_tags_prohibited/stderr.expected @@ -0,0 +1,7 @@ +Error: + In a 'such that' statement: x = t * 3 + Error: + Not uniformly typed: [t, 3; int(1..2)] + Involved types are: int:A + int +cat: conjure-output/*.solution: No such file or directory diff --git a/tests/custom/permutations/22_tagged_ints/int/prod/0002_diff_tags_prohibited/stdout.expected b/tests/custom/permutations/22_tagged_ints/int/prod/0002_diff_tags_prohibited/stdout.expected new file mode 100644 index 0000000000..d10ebe7b59 --- /dev/null +++ b/tests/custom/permutations/22_tagged_ints/int/prod/0002_diff_tags_prohibited/stdout.expected @@ -0,0 +1 @@ +Generating models for permutation.essence diff --git a/tests/custom/permutations/22_tagged_ints/int/prod/0003_const_tagged_works/permutation.essence b/tests/custom/permutations/22_tagged_ints/int/prod/0003_const_tagged_works/permutation.essence new file mode 100644 index 0000000000..e4eac350a5 --- /dev/null +++ b/tests/custom/permutations/22_tagged_ints/int/prod/0003_const_tagged_works/permutation.essence @@ -0,0 +1,4 @@ +find x : int:A(1..6) +such that x = 2:A * 3:A + + diff --git a/tests/custom/permutations/22_tagged_ints/int/prod/0003_const_tagged_works/run.sh b/tests/custom/permutations/22_tagged_ints/int/prod/0003_const_tagged_works/run.sh new file mode 100755 index 0000000000..b4899d6266 --- /dev/null +++ b/tests/custom/permutations/22_tagged_ints/int/prod/0003_const_tagged_works/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/22_tagged_ints/int/prod/0003_const_tagged_works/stdout.expected b/tests/custom/permutations/22_tagged_ints/int/prod/0003_const_tagged_works/stdout.expected new file mode 100644 index 0000000000..79e05ead18 --- /dev/null +++ b/tests/custom/permutations/22_tagged_ints/int/prod/0003_const_tagged_works/stdout.expected @@ -0,0 +1,8 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Copying solution to: permutation.solution +language Essence 1.3 + +letting x be 6 diff --git a/tests/custom/permutations/22_tagged_ints/int/succ/0002_diff_tags_prohibited/permutation.essence b/tests/custom/permutations/22_tagged_ints/int/succ/0002_diff_tags_prohibited/permutation.essence new file mode 100644 index 0000000000..1e8280733f --- /dev/null +++ b/tests/custom/permutations/22_tagged_ints/int/succ/0002_diff_tags_prohibited/permutation.essence @@ -0,0 +1,6 @@ +find x : int:A(1..6) +find y : int(1..6) + +such that x = succ(y) + + diff --git a/tests/custom/permutations/22_tagged_ints/int/succ/0002_diff_tags_prohibited/run.sh b/tests/custom/permutations/22_tagged_ints/int/succ/0002_diff_tags_prohibited/run.sh new file mode 100755 index 0000000000..b4899d6266 --- /dev/null +++ b/tests/custom/permutations/22_tagged_ints/int/succ/0002_diff_tags_prohibited/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/22_tagged_ints/int/succ/0002_diff_tags_prohibited/stderr.expected b/tests/custom/permutations/22_tagged_ints/int/succ/0002_diff_tags_prohibited/stderr.expected new file mode 100644 index 0000000000..80c98c80b8 --- /dev/null +++ b/tests/custom/permutations/22_tagged_ints/int/succ/0002_diff_tags_prohibited/stderr.expected @@ -0,0 +1,10 @@ +Error: + In a 'such that' statement: x = succ(y) + Error: + When type checking: x = succ(y) + Cannot unify the types of the following. + lhs : x + type of lhs: int:A + rhs : succ(y) + type of rhs: int +cat: conjure-output/*.solution: No such file or directory diff --git a/tests/custom/permutations/22_tagged_ints/int/succ/0002_diff_tags_prohibited/stdout.expected b/tests/custom/permutations/22_tagged_ints/int/succ/0002_diff_tags_prohibited/stdout.expected new file mode 100644 index 0000000000..d10ebe7b59 --- /dev/null +++ b/tests/custom/permutations/22_tagged_ints/int/succ/0002_diff_tags_prohibited/stdout.expected @@ -0,0 +1 @@ +Generating models for permutation.essence diff --git a/tests/custom/permutations/22_tagged_ints/int/succ/0003_const_tagged_works/permutation.essence b/tests/custom/permutations/22_tagged_ints/int/succ/0003_const_tagged_works/permutation.essence new file mode 100644 index 0000000000..92ae5936fc --- /dev/null +++ b/tests/custom/permutations/22_tagged_ints/int/succ/0003_const_tagged_works/permutation.essence @@ -0,0 +1,5 @@ +find x : int:A(1..6) +find y : int:A(1..6) +such that x = succ(y) + + diff --git a/tests/custom/permutations/22_tagged_ints/int/succ/0003_const_tagged_works/run.sh b/tests/custom/permutations/22_tagged_ints/int/succ/0003_const_tagged_works/run.sh new file mode 100755 index 0000000000..b4899d6266 --- /dev/null +++ b/tests/custom/permutations/22_tagged_ints/int/succ/0003_const_tagged_works/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/22_tagged_ints/int/succ/0003_const_tagged_works/stdout.expected b/tests/custom/permutations/22_tagged_ints/int/succ/0003_const_tagged_works/stdout.expected new file mode 100644 index 0000000000..746139963a --- /dev/null +++ b/tests/custom/permutations/22_tagged_ints/int/succ/0003_const_tagged_works/stdout.expected @@ -0,0 +1,9 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Copying solution to: permutation.solution +language Essence 1.3 + +letting x be 2 +letting y be 1 diff --git a/tests/custom/permutations/22_tagged_ints/int/sum/0001_same_tags_works/permutation.essence b/tests/custom/permutations/22_tagged_ints/int/sum/0001_same_tags_works/permutation.essence new file mode 100644 index 0000000000..7f7d3cfc30 --- /dev/null +++ b/tests/custom/permutations/22_tagged_ints/int/sum/0001_same_tags_works/permutation.essence @@ -0,0 +1,5 @@ +find t : int:A(1..6) +find x : int:A(1..6) +such that x = t + 4:A + + diff --git a/tests/custom/permutations/22_tagged_ints/int/sum/0001_same_tags_works/run.sh b/tests/custom/permutations/22_tagged_ints/int/sum/0001_same_tags_works/run.sh new file mode 100755 index 0000000000..b4899d6266 --- /dev/null +++ b/tests/custom/permutations/22_tagged_ints/int/sum/0001_same_tags_works/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/22_tagged_ints/int/sum/0001_same_tags_works/stdout.expected b/tests/custom/permutations/22_tagged_ints/int/sum/0001_same_tags_works/stdout.expected new file mode 100644 index 0000000000..4bdc225570 --- /dev/null +++ b/tests/custom/permutations/22_tagged_ints/int/sum/0001_same_tags_works/stdout.expected @@ -0,0 +1,9 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Copying solution to: permutation.solution +language Essence 1.3 + +letting t be 1 +letting x be 5 diff --git a/tests/custom/permutations/22_tagged_ints/int/sum/0002_diff_tags_prohibited/permutation.essence b/tests/custom/permutations/22_tagged_ints/int/sum/0002_diff_tags_prohibited/permutation.essence new file mode 100644 index 0000000000..3baa87095e --- /dev/null +++ b/tests/custom/permutations/22_tagged_ints/int/sum/0002_diff_tags_prohibited/permutation.essence @@ -0,0 +1,5 @@ +find t : int:A(1..6) +find x : int:A(1..6) +such that x = t + 4 + + diff --git a/tests/custom/permutations/22_tagged_ints/int/sum/0002_diff_tags_prohibited/run.sh b/tests/custom/permutations/22_tagged_ints/int/sum/0002_diff_tags_prohibited/run.sh new file mode 100755 index 0000000000..b4899d6266 --- /dev/null +++ b/tests/custom/permutations/22_tagged_ints/int/sum/0002_diff_tags_prohibited/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/22_tagged_ints/int/sum/0002_diff_tags_prohibited/stderr.expected b/tests/custom/permutations/22_tagged_ints/int/sum/0002_diff_tags_prohibited/stderr.expected new file mode 100644 index 0000000000..a8243dfa8c --- /dev/null +++ b/tests/custom/permutations/22_tagged_ints/int/sum/0002_diff_tags_prohibited/stderr.expected @@ -0,0 +1,7 @@ +Error: + In a 'such that' statement: x = t + 4 + Error: + Not uniformly typed: [t, 4; int(1..2)] + Involved types are: int:A + int +cat: conjure-output/*.solution: No such file or directory diff --git a/tests/custom/permutations/22_tagged_ints/int/sum/0002_diff_tags_prohibited/stdout.expected b/tests/custom/permutations/22_tagged_ints/int/sum/0002_diff_tags_prohibited/stdout.expected new file mode 100644 index 0000000000..d10ebe7b59 --- /dev/null +++ b/tests/custom/permutations/22_tagged_ints/int/sum/0002_diff_tags_prohibited/stdout.expected @@ -0,0 +1 @@ +Generating models for permutation.essence diff --git a/tests/custom/permutations/22_tagged_ints/int/sum/0003_const_tagged_works/permutation.essence b/tests/custom/permutations/22_tagged_ints/int/sum/0003_const_tagged_works/permutation.essence new file mode 100644 index 0000000000..2c0667c5b1 --- /dev/null +++ b/tests/custom/permutations/22_tagged_ints/int/sum/0003_const_tagged_works/permutation.essence @@ -0,0 +1,4 @@ +find x : int:A(1..6) +such that x = 2:A + 4:A + + diff --git a/tests/custom/permutations/22_tagged_ints/int/sum/0003_const_tagged_works/run.sh b/tests/custom/permutations/22_tagged_ints/int/sum/0003_const_tagged_works/run.sh new file mode 100755 index 0000000000..b4899d6266 --- /dev/null +++ b/tests/custom/permutations/22_tagged_ints/int/sum/0003_const_tagged_works/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/22_tagged_ints/int/sum/0003_const_tagged_works/stdout.expected b/tests/custom/permutations/22_tagged_ints/int/sum/0003_const_tagged_works/stdout.expected new file mode 100644 index 0000000000..79e05ead18 --- /dev/null +++ b/tests/custom/permutations/22_tagged_ints/int/sum/0003_const_tagged_works/stdout.expected @@ -0,0 +1,8 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Copying solution to: permutation.solution +language Essence 1.3 + +letting x be 6 diff --git a/tests/custom/permutations/22_tagged_ints/runthese.sh b/tests/custom/permutations/22_tagged_ints/runthese.sh new file mode 100644 index 0000000000..388ae0e9f2 --- /dev/null +++ b/tests/custom/permutations/22_tagged_ints/runthese.sh @@ -0,0 +1 @@ +stack build --copy-bins --test --test-arguments "-p custom.permutations.22_tagged_ints" diff --git a/tests/exhaustive/autogen/gen02/expected/model_1_1-solution000001.solution b/tests/exhaustive/autogen/gen02/expected/model_1_1-solution000001.solution deleted file mode 100644 index 19d999ca82..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_1_1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting var2 be {{}} diff --git a/tests/exhaustive/autogen/gen02/expected/model_1_1-solution000002.solution b/tests/exhaustive/autogen/gen02/expected/model_1_1-solution000002.solution deleted file mode 100644 index 937293310f..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_1_1-solution000002.solution +++ /dev/null @@ -1,6 +0,0 @@ -language Essence 1.3 - -letting var2 be {{false}} -$ Visualisation for var2 -$ _ - diff --git a/tests/exhaustive/autogen/gen02/expected/model_1_1-solution000003.solution b/tests/exhaustive/autogen/gen02/expected/model_1_1-solution000003.solution deleted file mode 100644 index 5a187652fa..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_1_1-solution000003.solution +++ /dev/null @@ -1,6 +0,0 @@ -language Essence 1.3 - -letting var2 be {{true}} -$ Visualisation for var2 -$ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_1_1-solution000004.solution b/tests/exhaustive/autogen/gen02/expected/model_1_1-solution000004.solution deleted file mode 100644 index 0678d41bf8..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_1_1-solution000004.solution +++ /dev/null @@ -1,6 +0,0 @@ -language Essence 1.3 - -letting var2 be {{false, true}} -$ Visualisation for var2 -$ _ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_1_1-solution000005.solution b/tests/exhaustive/autogen/gen02/expected/model_1_1-solution000005.solution deleted file mode 100644 index 73f1bfe1ac..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_1_1-solution000005.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting var2 be {{}, {false}} -$ Visualisation for var2 -$ -$ _ - diff --git a/tests/exhaustive/autogen/gen02/expected/model_1_1-solution000006.solution b/tests/exhaustive/autogen/gen02/expected/model_1_1-solution000006.solution deleted file mode 100644 index d4c4a238b9..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_1_1-solution000006.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting var2 be {{}, {true}} -$ Visualisation for var2 -$ -$ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_1_1-solution000007.solution b/tests/exhaustive/autogen/gen02/expected/model_1_1-solution000007.solution deleted file mode 100644 index 9c15a8e4e1..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_1_1-solution000007.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting var2 be {{}, {false, true}} -$ Visualisation for var2 -$ -$ _ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_1_1-solution000008.solution b/tests/exhaustive/autogen/gen02/expected/model_1_1-solution000008.solution deleted file mode 100644 index 2b6a8959da..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_1_1-solution000008.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting var2 be {{false}, {true}} -$ Visualisation for var2 -$ _ -$ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_1_1-solution000009.solution b/tests/exhaustive/autogen/gen02/expected/model_1_1-solution000009.solution deleted file mode 100644 index b2e98e56a6..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_1_1-solution000009.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting var2 be {{false}, {false, true}} -$ Visualisation for var2 -$ _ -$ _ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_1_1-solution000010.solution b/tests/exhaustive/autogen/gen02/expected/model_1_1-solution000010.solution deleted file mode 100644 index 4fc309134f..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_1_1-solution000010.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting var2 be {{false, true}, {true}} -$ Visualisation for var2 -$ _ T -$ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_1_1-solution000011.solution b/tests/exhaustive/autogen/gen02/expected/model_1_1-solution000011.solution deleted file mode 100644 index 70d0f91f38..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_1_1-solution000011.solution +++ /dev/null @@ -1,8 +0,0 @@ -language Essence 1.3 - -letting var2 be {{}, {false}, {true}} -$ Visualisation for var2 -$ -$ _ -$ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_1_1-solution000012.solution b/tests/exhaustive/autogen/gen02/expected/model_1_1-solution000012.solution deleted file mode 100644 index ebc3fe4182..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_1_1-solution000012.solution +++ /dev/null @@ -1,8 +0,0 @@ -language Essence 1.3 - -letting var2 be {{}, {false}, {false, true}} -$ Visualisation for var2 -$ -$ _ -$ _ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_1_1-solution000013.solution b/tests/exhaustive/autogen/gen02/expected/model_1_1-solution000013.solution deleted file mode 100644 index fa4340a533..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_1_1-solution000013.solution +++ /dev/null @@ -1,8 +0,0 @@ -language Essence 1.3 - -letting var2 be {{}, {false, true}, {true}} -$ Visualisation for var2 -$ -$ _ T -$ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_1_1-solution000014.solution b/tests/exhaustive/autogen/gen02/expected/model_1_1-solution000014.solution deleted file mode 100644 index 371f28aab7..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_1_1-solution000014.solution +++ /dev/null @@ -1,8 +0,0 @@ -language Essence 1.3 - -letting var2 be {{false}, {false, true}, {true}} -$ Visualisation for var2 -$ _ -$ _ T -$ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_1_1-solution000015.solution b/tests/exhaustive/autogen/gen02/expected/model_1_1-solution000015.solution deleted file mode 100644 index 35cfa328e8..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_1_1-solution000015.solution +++ /dev/null @@ -1,9 +0,0 @@ -language Essence 1.3 - -letting var2 be {{}, {false}, {false, true}, {true}} -$ Visualisation for var2 -$ -$ _ -$ _ T -$ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_1_1.eprime b/tests/exhaustive/autogen/gen02/expected/model_1_1.eprime deleted file mode 100644 index 977c249a3f..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_1_1.eprime +++ /dev/null @@ -1,46 +0,0 @@ -language ESSENCE' 1.0 - -find var2_ExplicitVarSizeWithMarkerR5_Marker: int(0..4) -find var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker: - matrix indexed by [int(1..4)] of int(0..2) -find var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values: - matrix indexed by [int(1..4), int(1..2)] of bool -branching on - [var2_ExplicitVarSizeWithMarkerR5_Marker, var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker, - var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values] -such that - or([q11 <= var2_ExplicitVarSizeWithMarkerR5_Marker /\ - sum([toInt(q12 <= var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q11]) - | q12 : int(1..2)]) - >= -7 - | q11 : int(1..4)]), - and([q2 + 1 <= var2_ExplicitVarSizeWithMarkerR5_Marker -> - flatten([[var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q2]; int(1)], - flatten([[-toInt(var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q2, q8]); - int(1)] - | q8 : int(1..2)]); - int(1..2)]) - var2_ExplicitVarSizeWithMarkerR5_Marker -> - var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q3] = 0 /\ - and([var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q3, q10] = false - | q10 : int(1..2)]) - | q3 : int(1..4)]), - and([q4 <= var2_ExplicitVarSizeWithMarkerR5_Marker -> - (2 <= var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q4] -> - -toInt(var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q4, 1]) < - -toInt(var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q4, 2])) - | q4 : int(1..4)]), - and([q4 <= var2_ExplicitVarSizeWithMarkerR5_Marker -> - and([q6 > var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q4] -> - var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q4, q6] = false - | q6 : int(1..2)]) - | q4 : int(1..4)]) - diff --git a/tests/exhaustive/autogen/gen02/expected/model_1_2-solution000001.solution b/tests/exhaustive/autogen/gen02/expected/model_1_2-solution000001.solution deleted file mode 100644 index 19d999ca82..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_1_2-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting var2 be {{}} diff --git a/tests/exhaustive/autogen/gen02/expected/model_1_2-solution000002.solution b/tests/exhaustive/autogen/gen02/expected/model_1_2-solution000002.solution deleted file mode 100644 index 937293310f..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_1_2-solution000002.solution +++ /dev/null @@ -1,6 +0,0 @@ -language Essence 1.3 - -letting var2 be {{false}} -$ Visualisation for var2 -$ _ - diff --git a/tests/exhaustive/autogen/gen02/expected/model_1_2-solution000003.solution b/tests/exhaustive/autogen/gen02/expected/model_1_2-solution000003.solution deleted file mode 100644 index 5a187652fa..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_1_2-solution000003.solution +++ /dev/null @@ -1,6 +0,0 @@ -language Essence 1.3 - -letting var2 be {{true}} -$ Visualisation for var2 -$ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_1_2-solution000004.solution b/tests/exhaustive/autogen/gen02/expected/model_1_2-solution000004.solution deleted file mode 100644 index 0678d41bf8..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_1_2-solution000004.solution +++ /dev/null @@ -1,6 +0,0 @@ -language Essence 1.3 - -letting var2 be {{false, true}} -$ Visualisation for var2 -$ _ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_1_2-solution000005.solution b/tests/exhaustive/autogen/gen02/expected/model_1_2-solution000005.solution deleted file mode 100644 index 73f1bfe1ac..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_1_2-solution000005.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting var2 be {{}, {false}} -$ Visualisation for var2 -$ -$ _ - diff --git a/tests/exhaustive/autogen/gen02/expected/model_1_2-solution000006.solution b/tests/exhaustive/autogen/gen02/expected/model_1_2-solution000006.solution deleted file mode 100644 index d4c4a238b9..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_1_2-solution000006.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting var2 be {{}, {true}} -$ Visualisation for var2 -$ -$ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_1_2-solution000007.solution b/tests/exhaustive/autogen/gen02/expected/model_1_2-solution000007.solution deleted file mode 100644 index 2b6a8959da..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_1_2-solution000007.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting var2 be {{false}, {true}} -$ Visualisation for var2 -$ _ -$ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_1_2-solution000008.solution b/tests/exhaustive/autogen/gen02/expected/model_1_2-solution000008.solution deleted file mode 100644 index 9c15a8e4e1..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_1_2-solution000008.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting var2 be {{}, {false, true}} -$ Visualisation for var2 -$ -$ _ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_1_2-solution000009.solution b/tests/exhaustive/autogen/gen02/expected/model_1_2-solution000009.solution deleted file mode 100644 index b2e98e56a6..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_1_2-solution000009.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting var2 be {{false}, {false, true}} -$ Visualisation for var2 -$ _ -$ _ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_1_2-solution000010.solution b/tests/exhaustive/autogen/gen02/expected/model_1_2-solution000010.solution deleted file mode 100644 index 4fc309134f..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_1_2-solution000010.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting var2 be {{false, true}, {true}} -$ Visualisation for var2 -$ _ T -$ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_1_2-solution000011.solution b/tests/exhaustive/autogen/gen02/expected/model_1_2-solution000011.solution deleted file mode 100644 index 70d0f91f38..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_1_2-solution000011.solution +++ /dev/null @@ -1,8 +0,0 @@ -language Essence 1.3 - -letting var2 be {{}, {false}, {true}} -$ Visualisation for var2 -$ -$ _ -$ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_1_2-solution000012.solution b/tests/exhaustive/autogen/gen02/expected/model_1_2-solution000012.solution deleted file mode 100644 index ebc3fe4182..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_1_2-solution000012.solution +++ /dev/null @@ -1,8 +0,0 @@ -language Essence 1.3 - -letting var2 be {{}, {false}, {false, true}} -$ Visualisation for var2 -$ -$ _ -$ _ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_1_2-solution000013.solution b/tests/exhaustive/autogen/gen02/expected/model_1_2-solution000013.solution deleted file mode 100644 index fa4340a533..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_1_2-solution000013.solution +++ /dev/null @@ -1,8 +0,0 @@ -language Essence 1.3 - -letting var2 be {{}, {false, true}, {true}} -$ Visualisation for var2 -$ -$ _ T -$ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_1_2-solution000014.solution b/tests/exhaustive/autogen/gen02/expected/model_1_2-solution000014.solution deleted file mode 100644 index 371f28aab7..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_1_2-solution000014.solution +++ /dev/null @@ -1,8 +0,0 @@ -language Essence 1.3 - -letting var2 be {{false}, {false, true}, {true}} -$ Visualisation for var2 -$ _ -$ _ T -$ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_1_2-solution000015.solution b/tests/exhaustive/autogen/gen02/expected/model_1_2-solution000015.solution deleted file mode 100644 index 35cfa328e8..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_1_2-solution000015.solution +++ /dev/null @@ -1,9 +0,0 @@ -language Essence 1.3 - -letting var2 be {{}, {false}, {false, true}, {true}} -$ Visualisation for var2 -$ -$ _ -$ _ T -$ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_1_2.eprime b/tests/exhaustive/autogen/gen02/expected/model_1_2.eprime deleted file mode 100644 index 482331f544..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_1_2.eprime +++ /dev/null @@ -1,125 +0,0 @@ -language ESSENCE' 1.0 - -find var2_ExplicitVarSizeWithMarkerR5_Marker: int(0..4) -find var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker: - matrix indexed by [int(1..4)] of int(0..2) -find var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values: - matrix indexed by [int(1..4), int(1..2)] of bool -find var2_ExplicitVarSizeWithMarkerR4_Marker: int(0..4) -find var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Flags: - matrix indexed by [int(1..4), int(1..2)] of bool -find var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Values: - matrix indexed by [int(1..4), int(1..2)] of bool -branching on - [var2_ExplicitVarSizeWithMarkerR4_Marker, var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Flags, - var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Values, var2_ExplicitVarSizeWithMarkerR5_Marker, - var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker, - var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values] -such that - or([q47 <= var2_ExplicitVarSizeWithMarkerR5_Marker /\ - sum([toInt(q48 <= var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q47]) - | q48 : int(1..2)]) - >= -7 - | q47 : int(1..4)]), - and([q2 + 1 <= var2_ExplicitVarSizeWithMarkerR5_Marker -> - flatten([[var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q2]; int(1)], - flatten([[-toInt(var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q2, q8]); - int(1)] - | q8 : int(1..2)]); - int(1..2)]) - var2_ExplicitVarSizeWithMarkerR5_Marker -> - var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q3] = 0 /\ - and([var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q3, q10] = false - | q10 : int(1..2)]) - | q3 : int(1..4)]), - and([q4 <= var2_ExplicitVarSizeWithMarkerR5_Marker -> - (2 <= var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q4] -> - -toInt(var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q4, 1]) < - -toInt(var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q4, 2])) - | q4 : int(1..4)]), - and([q4 <= var2_ExplicitVarSizeWithMarkerR5_Marker -> - and([q6 > var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q4] -> - var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q4, q6] = false - | q6 : int(1..2)]) - | q4 : int(1..4)]), - and([q11 + 1 <= var2_ExplicitVarSizeWithMarkerR4_Marker -> - flatten([flatten([[-toInt(var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Flags[q11, q19]); - int(1)], - [-toInt(var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Values[q11, q19]); - int(1)]; - int(1..2)]) - | q19 : int(1..2)]) - var2_ExplicitVarSizeWithMarkerR4_Marker -> - and([var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Flags[q12, q21] = false - | q21 : int(1..2)]) - /\ - and([var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Values[q12, q22] = false - | q22 : int(1..2)]) - | q12 : int(1..4)]), - and([q13 <= var2_ExplicitVarSizeWithMarkerR4_Marker -> - (var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Flags[q13, 2] -> - -toInt(var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Values[q13, 1]) < - -toInt(var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Values[q13, 2])) - | q13 : int(1..4)]), - and([q13 <= var2_ExplicitVarSizeWithMarkerR4_Marker -> - and([var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Flags[q13, q15] = false -> - var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Values[q13, q15] = false - | q15 : int(1..2)]) - | q13 : int(1..4)]), - and([q13 <= var2_ExplicitVarSizeWithMarkerR4_Marker -> - (var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Flags[q13, 2] -> - var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Flags[q13, 1]) - | q13 : int(1..4)]), - and([q24 <= var2_ExplicitVarSizeWithMarkerR4_Marker -> - or([q26 <= var2_ExplicitVarSizeWithMarkerR5_Marker /\ - (and([q28 <= var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q26] -> - or([var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Flags[q24, q30] /\ - var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Values[q24, q30] = - var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q26, q28] - | q30 : int(1..2)]) - | q28 : int(1..2)]) - /\ - and([var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Flags[q24, q32] -> - or([q34 <= var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q26] /\ - var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q26, q34] = - var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Values[q24, q32] - | q34 : int(1..2)]) - | q32 : int(1..2)])) - | q26 : int(1..4)]) - | q24 : int(1..4)]), - and([q36 <= var2_ExplicitVarSizeWithMarkerR5_Marker -> - or([q38 <= var2_ExplicitVarSizeWithMarkerR4_Marker /\ - (and([var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Flags[q38, q40] -> - or([q42 <= var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q36] /\ - var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q36, q42] = - var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Values[q38, q40] - | q42 : int(1..2)]) - | q40 : int(1..2)]) - /\ - and([q44 <= var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q36] -> - or([var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Flags[q38, q46] /\ - var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Values[q38, q46] = - var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q36, q44] - | q46 : int(1..2)]) - | q44 : int(1..2)])) - | q38 : int(1..4)]) - | q36 : int(1..4)]) - diff --git a/tests/exhaustive/autogen/gen02/expected/model_1_3-solution000001.solution b/tests/exhaustive/autogen/gen02/expected/model_1_3-solution000001.solution deleted file mode 100644 index 19d999ca82..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_1_3-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting var2 be {{}} diff --git a/tests/exhaustive/autogen/gen02/expected/model_1_3-solution000002.solution b/tests/exhaustive/autogen/gen02/expected/model_1_3-solution000002.solution deleted file mode 100644 index 937293310f..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_1_3-solution000002.solution +++ /dev/null @@ -1,6 +0,0 @@ -language Essence 1.3 - -letting var2 be {{false}} -$ Visualisation for var2 -$ _ - diff --git a/tests/exhaustive/autogen/gen02/expected/model_1_3-solution000003.solution b/tests/exhaustive/autogen/gen02/expected/model_1_3-solution000003.solution deleted file mode 100644 index 5a187652fa..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_1_3-solution000003.solution +++ /dev/null @@ -1,6 +0,0 @@ -language Essence 1.3 - -letting var2 be {{true}} -$ Visualisation for var2 -$ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_1_3-solution000004.solution b/tests/exhaustive/autogen/gen02/expected/model_1_3-solution000004.solution deleted file mode 100644 index 0678d41bf8..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_1_3-solution000004.solution +++ /dev/null @@ -1,6 +0,0 @@ -language Essence 1.3 - -letting var2 be {{false, true}} -$ Visualisation for var2 -$ _ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_1_3-solution000005.solution b/tests/exhaustive/autogen/gen02/expected/model_1_3-solution000005.solution deleted file mode 100644 index 73f1bfe1ac..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_1_3-solution000005.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting var2 be {{}, {false}} -$ Visualisation for var2 -$ -$ _ - diff --git a/tests/exhaustive/autogen/gen02/expected/model_1_3-solution000006.solution b/tests/exhaustive/autogen/gen02/expected/model_1_3-solution000006.solution deleted file mode 100644 index d4c4a238b9..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_1_3-solution000006.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting var2 be {{}, {true}} -$ Visualisation for var2 -$ -$ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_1_3-solution000007.solution b/tests/exhaustive/autogen/gen02/expected/model_1_3-solution000007.solution deleted file mode 100644 index 9c15a8e4e1..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_1_3-solution000007.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting var2 be {{}, {false, true}} -$ Visualisation for var2 -$ -$ _ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_1_3-solution000008.solution b/tests/exhaustive/autogen/gen02/expected/model_1_3-solution000008.solution deleted file mode 100644 index 2b6a8959da..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_1_3-solution000008.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting var2 be {{false}, {true}} -$ Visualisation for var2 -$ _ -$ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_1_3-solution000009.solution b/tests/exhaustive/autogen/gen02/expected/model_1_3-solution000009.solution deleted file mode 100644 index b2e98e56a6..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_1_3-solution000009.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting var2 be {{false}, {false, true}} -$ Visualisation for var2 -$ _ -$ _ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_1_3-solution000010.solution b/tests/exhaustive/autogen/gen02/expected/model_1_3-solution000010.solution deleted file mode 100644 index 4fc309134f..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_1_3-solution000010.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting var2 be {{false, true}, {true}} -$ Visualisation for var2 -$ _ T -$ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_1_3-solution000011.solution b/tests/exhaustive/autogen/gen02/expected/model_1_3-solution000011.solution deleted file mode 100644 index 70d0f91f38..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_1_3-solution000011.solution +++ /dev/null @@ -1,8 +0,0 @@ -language Essence 1.3 - -letting var2 be {{}, {false}, {true}} -$ Visualisation for var2 -$ -$ _ -$ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_1_3-solution000012.solution b/tests/exhaustive/autogen/gen02/expected/model_1_3-solution000012.solution deleted file mode 100644 index ebc3fe4182..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_1_3-solution000012.solution +++ /dev/null @@ -1,8 +0,0 @@ -language Essence 1.3 - -letting var2 be {{}, {false}, {false, true}} -$ Visualisation for var2 -$ -$ _ -$ _ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_1_3-solution000013.solution b/tests/exhaustive/autogen/gen02/expected/model_1_3-solution000013.solution deleted file mode 100644 index fa4340a533..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_1_3-solution000013.solution +++ /dev/null @@ -1,8 +0,0 @@ -language Essence 1.3 - -letting var2 be {{}, {false, true}, {true}} -$ Visualisation for var2 -$ -$ _ T -$ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_1_3-solution000014.solution b/tests/exhaustive/autogen/gen02/expected/model_1_3-solution000014.solution deleted file mode 100644 index 371f28aab7..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_1_3-solution000014.solution +++ /dev/null @@ -1,8 +0,0 @@ -language Essence 1.3 - -letting var2 be {{false}, {false, true}, {true}} -$ Visualisation for var2 -$ _ -$ _ T -$ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_1_3-solution000015.solution b/tests/exhaustive/autogen/gen02/expected/model_1_3-solution000015.solution deleted file mode 100644 index 35cfa328e8..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_1_3-solution000015.solution +++ /dev/null @@ -1,9 +0,0 @@ -language Essence 1.3 - -letting var2 be {{}, {false}, {false, true}, {true}} -$ Visualisation for var2 -$ -$ _ -$ _ T -$ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_1_3.eprime b/tests/exhaustive/autogen/gen02/expected/model_1_3.eprime deleted file mode 100644 index 67fce63a26..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_1_3.eprime +++ /dev/null @@ -1,103 +0,0 @@ -language ESSENCE' 1.0 - -find var2_ExplicitVarSizeWithMarkerR5_Marker: int(0..4) -find var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker: - matrix indexed by [int(1..4)] of int(0..2) -find var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values: - matrix indexed by [int(1..4), int(1..2)] of bool -find var2_ExplicitVarSizeWithFlagsR5_Flags: matrix indexed by [int(1..4)] of bool -find var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Marker: matrix indexed by [int(1..4)] of int(0..2) -find var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Values: - matrix indexed by [int(1..4), int(1..2)] of bool -branching on - [var2_ExplicitVarSizeWithFlagsR5_Flags, var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Marker, - var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Values, var2_ExplicitVarSizeWithMarkerR5_Marker, - var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker, - var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values] -such that - or([q34 <= var2_ExplicitVarSizeWithMarkerR5_Marker /\ - sum([toInt(q35 <= var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q34]) - | q35 : int(1..2)]) - >= -7 - | q34 : int(1..4)]), - and([q2 + 1 <= var2_ExplicitVarSizeWithMarkerR5_Marker -> - flatten([[var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q2]; int(1)], - flatten([[-toInt(var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q2, q8]); - int(1)] - | q8 : int(1..2)]); - int(1..2)]) - var2_ExplicitVarSizeWithMarkerR5_Marker -> - var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q3] = 0 /\ - and([var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q3, q10] = false - | q10 : int(1..2)]) - | q3 : int(1..4)]), - and([q4 <= var2_ExplicitVarSizeWithMarkerR5_Marker -> - (2 <= var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q4] -> - -toInt(var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q4, 1]) < - -toInt(var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q4, 2])) - | q4 : int(1..4)]), - and([q4 <= var2_ExplicitVarSizeWithMarkerR5_Marker -> - and([q6 > var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q4] -> - var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q4, q6] = false - | q6 : int(1..2)]) - | q4 : int(1..4)]), - and([var2_ExplicitVarSizeWithFlagsR5_Flags[q11 + 1] -> - flatten([[var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Marker[q11]; int(1)], - flatten([[-toInt(var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Values[q11, q19]); - int(1)] - | q19 : int(1..2)]); - int(1..2)]) - - var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Marker[q12] = 0 /\ - and([var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Values[q12, q21] = false - | q21 : int(1..2)]) - | q12 : int(1..4)]), - and([var2_ExplicitVarSizeWithFlagsR5_Flags[q13 + 1] -> var2_ExplicitVarSizeWithFlagsR5_Flags[q13] - | q13 : int(1..3)]), - and([var2_ExplicitVarSizeWithFlagsR5_Flags[q15] -> - (2 <= var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Marker[q15] -> - -toInt(var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Values[q15, 1]) < - -toInt(var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Values[q15, 2])) - | q15 : int(1..4)]), - and([var2_ExplicitVarSizeWithFlagsR5_Flags[q15] -> - and([q17 > var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Marker[q15] -> - var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Values[q15, q17] = false - | q17 : int(1..2)]) - | q15 : int(1..4)]), - and([var2_ExplicitVarSizeWithFlagsR5_Flags[q23] -> - or([q25 <= var2_ExplicitVarSizeWithMarkerR5_Marker /\ - (var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q25] = - var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Marker[q23] - /\ - and([var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q25, q26] = - var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Values[q23, q26] - | q26 : int(1..2)])) - | q25 : int(1..4)]) - | q23 : int(1..4)]), - and([q29 <= var2_ExplicitVarSizeWithMarkerR5_Marker -> - or([var2_ExplicitVarSizeWithFlagsR5_Flags[q31] /\ - (var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Marker[q31] = - var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q29] - /\ - and([var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Values[q31, q32] = - var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q29, q32] - | q32 : int(1..2)])) - | q31 : int(1..4)]) - | q29 : int(1..4)]) - diff --git a/tests/exhaustive/autogen/gen02/expected/model_1_4-solution000001.solution b/tests/exhaustive/autogen/gen02/expected/model_1_4-solution000001.solution deleted file mode 100644 index 19d999ca82..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_1_4-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting var2 be {{}} diff --git a/tests/exhaustive/autogen/gen02/expected/model_1_4-solution000002.solution b/tests/exhaustive/autogen/gen02/expected/model_1_4-solution000002.solution deleted file mode 100644 index 937293310f..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_1_4-solution000002.solution +++ /dev/null @@ -1,6 +0,0 @@ -language Essence 1.3 - -letting var2 be {{false}} -$ Visualisation for var2 -$ _ - diff --git a/tests/exhaustive/autogen/gen02/expected/model_1_4-solution000003.solution b/tests/exhaustive/autogen/gen02/expected/model_1_4-solution000003.solution deleted file mode 100644 index 5a187652fa..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_1_4-solution000003.solution +++ /dev/null @@ -1,6 +0,0 @@ -language Essence 1.3 - -letting var2 be {{true}} -$ Visualisation for var2 -$ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_1_4-solution000004.solution b/tests/exhaustive/autogen/gen02/expected/model_1_4-solution000004.solution deleted file mode 100644 index 0678d41bf8..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_1_4-solution000004.solution +++ /dev/null @@ -1,6 +0,0 @@ -language Essence 1.3 - -letting var2 be {{false, true}} -$ Visualisation for var2 -$ _ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_1_4-solution000005.solution b/tests/exhaustive/autogen/gen02/expected/model_1_4-solution000005.solution deleted file mode 100644 index 73f1bfe1ac..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_1_4-solution000005.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting var2 be {{}, {false}} -$ Visualisation for var2 -$ -$ _ - diff --git a/tests/exhaustive/autogen/gen02/expected/model_1_4-solution000006.solution b/tests/exhaustive/autogen/gen02/expected/model_1_4-solution000006.solution deleted file mode 100644 index d4c4a238b9..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_1_4-solution000006.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting var2 be {{}, {true}} -$ Visualisation for var2 -$ -$ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_1_4-solution000007.solution b/tests/exhaustive/autogen/gen02/expected/model_1_4-solution000007.solution deleted file mode 100644 index 2b6a8959da..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_1_4-solution000007.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting var2 be {{false}, {true}} -$ Visualisation for var2 -$ _ -$ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_1_4-solution000008.solution b/tests/exhaustive/autogen/gen02/expected/model_1_4-solution000008.solution deleted file mode 100644 index 9c15a8e4e1..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_1_4-solution000008.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting var2 be {{}, {false, true}} -$ Visualisation for var2 -$ -$ _ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_1_4-solution000009.solution b/tests/exhaustive/autogen/gen02/expected/model_1_4-solution000009.solution deleted file mode 100644 index b2e98e56a6..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_1_4-solution000009.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting var2 be {{false}, {false, true}} -$ Visualisation for var2 -$ _ -$ _ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_1_4-solution000010.solution b/tests/exhaustive/autogen/gen02/expected/model_1_4-solution000010.solution deleted file mode 100644 index 4fc309134f..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_1_4-solution000010.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting var2 be {{false, true}, {true}} -$ Visualisation for var2 -$ _ T -$ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_1_4-solution000011.solution b/tests/exhaustive/autogen/gen02/expected/model_1_4-solution000011.solution deleted file mode 100644 index 70d0f91f38..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_1_4-solution000011.solution +++ /dev/null @@ -1,8 +0,0 @@ -language Essence 1.3 - -letting var2 be {{}, {false}, {true}} -$ Visualisation for var2 -$ -$ _ -$ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_1_4-solution000012.solution b/tests/exhaustive/autogen/gen02/expected/model_1_4-solution000012.solution deleted file mode 100644 index ebc3fe4182..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_1_4-solution000012.solution +++ /dev/null @@ -1,8 +0,0 @@ -language Essence 1.3 - -letting var2 be {{}, {false}, {false, true}} -$ Visualisation for var2 -$ -$ _ -$ _ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_1_4-solution000013.solution b/tests/exhaustive/autogen/gen02/expected/model_1_4-solution000013.solution deleted file mode 100644 index fa4340a533..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_1_4-solution000013.solution +++ /dev/null @@ -1,8 +0,0 @@ -language Essence 1.3 - -letting var2 be {{}, {false, true}, {true}} -$ Visualisation for var2 -$ -$ _ T -$ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_1_4-solution000014.solution b/tests/exhaustive/autogen/gen02/expected/model_1_4-solution000014.solution deleted file mode 100644 index 371f28aab7..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_1_4-solution000014.solution +++ /dev/null @@ -1,8 +0,0 @@ -language Essence 1.3 - -letting var2 be {{false}, {false, true}, {true}} -$ Visualisation for var2 -$ _ -$ _ T -$ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_1_4-solution000015.solution b/tests/exhaustive/autogen/gen02/expected/model_1_4-solution000015.solution deleted file mode 100644 index 35cfa328e8..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_1_4-solution000015.solution +++ /dev/null @@ -1,9 +0,0 @@ -language Essence 1.3 - -letting var2 be {{}, {false}, {false, true}, {true}} -$ Visualisation for var2 -$ -$ _ -$ _ T -$ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_1_4.eprime b/tests/exhaustive/autogen/gen02/expected/model_1_4.eprime deleted file mode 100644 index 09604083ba..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_1_4.eprime +++ /dev/null @@ -1,126 +0,0 @@ -language ESSENCE' 1.0 - -find var2_ExplicitVarSizeWithMarkerR5_Marker: int(0..4) -find var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker: - matrix indexed by [int(1..4)] of int(0..2) -find var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values: - matrix indexed by [int(1..4), int(1..2)] of bool -find var2_ExplicitVarSizeWithFlagsR4_Flags: matrix indexed by [int(1..4)] of bool -find var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Flags: - matrix indexed by [int(1..4), int(1..2)] of bool -find var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Values: - matrix indexed by [int(1..4), int(1..2)] of bool -branching on - [var2_ExplicitVarSizeWithFlagsR4_Flags, var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Flags, - var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Values, var2_ExplicitVarSizeWithMarkerR5_Marker, - var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker, - var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values] -such that - or([q49 <= var2_ExplicitVarSizeWithMarkerR5_Marker /\ - sum([toInt(q50 <= var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q49]) - | q50 : int(1..2)]) - >= -7 - | q49 : int(1..4)]), - and([q2 + 1 <= var2_ExplicitVarSizeWithMarkerR5_Marker -> - flatten([[var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q2]; int(1)], - flatten([[-toInt(var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q2, q8]); - int(1)] - | q8 : int(1..2)]); - int(1..2)]) - var2_ExplicitVarSizeWithMarkerR5_Marker -> - var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q3] = 0 /\ - and([var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q3, q10] = false - | q10 : int(1..2)]) - | q3 : int(1..4)]), - and([q4 <= var2_ExplicitVarSizeWithMarkerR5_Marker -> - (2 <= var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q4] -> - -toInt(var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q4, 1]) < - -toInt(var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q4, 2])) - | q4 : int(1..4)]), - and([q4 <= var2_ExplicitVarSizeWithMarkerR5_Marker -> - and([q6 > var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q4] -> - var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q4, q6] = false - | q6 : int(1..2)]) - | q4 : int(1..4)]), - and([var2_ExplicitVarSizeWithFlagsR4_Flags[q11 + 1] -> - flatten([flatten([[-toInt(var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Flags[q11, q21]); - int(1)], - [-toInt(var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Values[q11, q21]); - int(1)]; - int(1..2)]) - | q21 : int(1..2)]) - - and([var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Flags[q12, q23] = false - | q23 : int(1..2)]) - /\ - and([var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Values[q12, q24] = false - | q24 : int(1..2)]) - | q12 : int(1..4)]), - and([var2_ExplicitVarSizeWithFlagsR4_Flags[q13 + 1] -> var2_ExplicitVarSizeWithFlagsR4_Flags[q13] - | q13 : int(1..3)]), - and([var2_ExplicitVarSizeWithFlagsR4_Flags[q15] -> - (var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Flags[q15, 2] -> - -toInt(var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Values[q15, 1]) < - -toInt(var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Values[q15, 2])) - | q15 : int(1..4)]), - and([var2_ExplicitVarSizeWithFlagsR4_Flags[q15] -> - and([var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Flags[q15, q17] = false -> - var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Values[q15, q17] = false - | q17 : int(1..2)]) - | q15 : int(1..4)]), - and([var2_ExplicitVarSizeWithFlagsR4_Flags[q15] -> - (var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Flags[q15, 2] -> - var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Flags[q15, 1]) - | q15 : int(1..4)]), - and([var2_ExplicitVarSizeWithFlagsR4_Flags[q26] -> - or([q28 <= var2_ExplicitVarSizeWithMarkerR5_Marker /\ - (and([q30 <= var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q28] -> - or([var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Flags[q26, q32] /\ - var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Values[q26, q32] = - var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q28, q30] - | q32 : int(1..2)]) - | q30 : int(1..2)]) - /\ - and([var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Flags[q26, q34] -> - or([q36 <= var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q28] /\ - var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q28, q36] = - var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Values[q26, q34] - | q36 : int(1..2)]) - | q34 : int(1..2)])) - | q28 : int(1..4)]) - | q26 : int(1..4)]), - and([q38 <= var2_ExplicitVarSizeWithMarkerR5_Marker -> - or([var2_ExplicitVarSizeWithFlagsR4_Flags[q40] /\ - (and([var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Flags[q40, q42] -> - or([q44 <= var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q38] /\ - var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q38, q44] = - var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Values[q40, q42] - | q44 : int(1..2)]) - | q42 : int(1..2)]) - /\ - and([q46 <= var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q38] -> - or([var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Flags[q40, q48] /\ - var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Values[q40, q48] = - var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q38, q46] - | q48 : int(1..2)]) - | q46 : int(1..2)])) - | q40 : int(1..4)]) - | q38 : int(1..4)]) - diff --git a/tests/exhaustive/autogen/gen02/expected/model_2_1-solution000001.solution b/tests/exhaustive/autogen/gen02/expected/model_2_1-solution000001.solution deleted file mode 100644 index 19d999ca82..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_2_1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting var2 be {{}} diff --git a/tests/exhaustive/autogen/gen02/expected/model_2_1-solution000002.solution b/tests/exhaustive/autogen/gen02/expected/model_2_1-solution000002.solution deleted file mode 100644 index 937293310f..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_2_1-solution000002.solution +++ /dev/null @@ -1,6 +0,0 @@ -language Essence 1.3 - -letting var2 be {{false}} -$ Visualisation for var2 -$ _ - diff --git a/tests/exhaustive/autogen/gen02/expected/model_2_1-solution000003.solution b/tests/exhaustive/autogen/gen02/expected/model_2_1-solution000003.solution deleted file mode 100644 index 5a187652fa..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_2_1-solution000003.solution +++ /dev/null @@ -1,6 +0,0 @@ -language Essence 1.3 - -letting var2 be {{true}} -$ Visualisation for var2 -$ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_2_1-solution000004.solution b/tests/exhaustive/autogen/gen02/expected/model_2_1-solution000004.solution deleted file mode 100644 index 0678d41bf8..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_2_1-solution000004.solution +++ /dev/null @@ -1,6 +0,0 @@ -language Essence 1.3 - -letting var2 be {{false, true}} -$ Visualisation for var2 -$ _ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_2_1-solution000005.solution b/tests/exhaustive/autogen/gen02/expected/model_2_1-solution000005.solution deleted file mode 100644 index 73f1bfe1ac..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_2_1-solution000005.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting var2 be {{}, {false}} -$ Visualisation for var2 -$ -$ _ - diff --git a/tests/exhaustive/autogen/gen02/expected/model_2_1-solution000006.solution b/tests/exhaustive/autogen/gen02/expected/model_2_1-solution000006.solution deleted file mode 100644 index d4c4a238b9..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_2_1-solution000006.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting var2 be {{}, {true}} -$ Visualisation for var2 -$ -$ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_2_1-solution000007.solution b/tests/exhaustive/autogen/gen02/expected/model_2_1-solution000007.solution deleted file mode 100644 index 9c15a8e4e1..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_2_1-solution000007.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting var2 be {{}, {false, true}} -$ Visualisation for var2 -$ -$ _ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_2_1-solution000008.solution b/tests/exhaustive/autogen/gen02/expected/model_2_1-solution000008.solution deleted file mode 100644 index 2b6a8959da..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_2_1-solution000008.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting var2 be {{false}, {true}} -$ Visualisation for var2 -$ _ -$ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_2_1-solution000009.solution b/tests/exhaustive/autogen/gen02/expected/model_2_1-solution000009.solution deleted file mode 100644 index b2e98e56a6..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_2_1-solution000009.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting var2 be {{false}, {false, true}} -$ Visualisation for var2 -$ _ -$ _ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_2_1-solution000010.solution b/tests/exhaustive/autogen/gen02/expected/model_2_1-solution000010.solution deleted file mode 100644 index 4fc309134f..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_2_1-solution000010.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting var2 be {{false, true}, {true}} -$ Visualisation for var2 -$ _ T -$ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_2_1-solution000011.solution b/tests/exhaustive/autogen/gen02/expected/model_2_1-solution000011.solution deleted file mode 100644 index 70d0f91f38..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_2_1-solution000011.solution +++ /dev/null @@ -1,8 +0,0 @@ -language Essence 1.3 - -letting var2 be {{}, {false}, {true}} -$ Visualisation for var2 -$ -$ _ -$ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_2_1-solution000012.solution b/tests/exhaustive/autogen/gen02/expected/model_2_1-solution000012.solution deleted file mode 100644 index ebc3fe4182..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_2_1-solution000012.solution +++ /dev/null @@ -1,8 +0,0 @@ -language Essence 1.3 - -letting var2 be {{}, {false}, {false, true}} -$ Visualisation for var2 -$ -$ _ -$ _ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_2_1-solution000013.solution b/tests/exhaustive/autogen/gen02/expected/model_2_1-solution000013.solution deleted file mode 100644 index fa4340a533..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_2_1-solution000013.solution +++ /dev/null @@ -1,8 +0,0 @@ -language Essence 1.3 - -letting var2 be {{}, {false, true}, {true}} -$ Visualisation for var2 -$ -$ _ T -$ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_2_1-solution000014.solution b/tests/exhaustive/autogen/gen02/expected/model_2_1-solution000014.solution deleted file mode 100644 index 371f28aab7..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_2_1-solution000014.solution +++ /dev/null @@ -1,8 +0,0 @@ -language Essence 1.3 - -letting var2 be {{false}, {false, true}, {true}} -$ Visualisation for var2 -$ _ -$ _ T -$ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_2_1-solution000015.solution b/tests/exhaustive/autogen/gen02/expected/model_2_1-solution000015.solution deleted file mode 100644 index 35cfa328e8..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_2_1-solution000015.solution +++ /dev/null @@ -1,9 +0,0 @@ -language Essence 1.3 - -letting var2 be {{}, {false}, {false, true}, {true}} -$ Visualisation for var2 -$ -$ _ -$ _ T -$ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_2_1.eprime b/tests/exhaustive/autogen/gen02/expected/model_2_1.eprime deleted file mode 100644 index 39316b414d..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_2_1.eprime +++ /dev/null @@ -1,123 +0,0 @@ -language ESSENCE' 1.0 - -find var2_ExplicitVarSizeWithMarkerR4_Marker: int(0..4) -find var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Flags: - matrix indexed by [int(1..4), int(1..2)] of bool -find var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Values: - matrix indexed by [int(1..4), int(1..2)] of bool -find var2_ExplicitVarSizeWithMarkerR5_Marker: int(0..4) -find var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker: - matrix indexed by [int(1..4)] of int(0..2) -find var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values: - matrix indexed by [int(1..4), int(1..2)] of bool -branching on - [var2_ExplicitVarSizeWithMarkerR5_Marker, var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker, - var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values, var2_ExplicitVarSizeWithMarkerR4_Marker, - var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Flags, - var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Values] -such that - or([q47 <= var2_ExplicitVarSizeWithMarkerR4_Marker /\ - sum([toInt(var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Flags[q47, q48]) | q48 : int(1..2)]) - >= -7 - | q47 : int(1..4)]), - and([q2 + 1 <= var2_ExplicitVarSizeWithMarkerR4_Marker -> - flatten([flatten([[-toInt(var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Flags[q2, q10]); - int(1)], - [-toInt(var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Values[q2, q10]); - int(1)]; - int(1..2)]) - | q10 : int(1..2)]) - var2_ExplicitVarSizeWithMarkerR4_Marker -> - and([var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Flags[q3, q12] = false - | q12 : int(1..2)]) - /\ - and([var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Values[q3, q13] = false - | q13 : int(1..2)]) - | q3 : int(1..4)]), - and([q4 <= var2_ExplicitVarSizeWithMarkerR4_Marker -> - (var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Flags[q4, 2] -> - -toInt(var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Values[q4, 1]) < - -toInt(var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Values[q4, 2])) - | q4 : int(1..4)]), - and([q4 <= var2_ExplicitVarSizeWithMarkerR4_Marker -> - and([var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Flags[q4, q6] = false -> - var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Values[q4, q6] = false - | q6 : int(1..2)]) - | q4 : int(1..4)]), - and([q4 <= var2_ExplicitVarSizeWithMarkerR4_Marker -> - (var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Flags[q4, 2] -> - var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Flags[q4, 1]) - | q4 : int(1..4)]), - and([q14 + 1 <= var2_ExplicitVarSizeWithMarkerR5_Marker -> - flatten([[var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q14]; int(1)], - flatten([[-toInt(var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q14, q20]); - int(1)] - | q20 : int(1..2)]); - int(1..2)]) - var2_ExplicitVarSizeWithMarkerR5_Marker -> - var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q15] = 0 /\ - and([var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q15, q22] = false - | q22 : int(1..2)]) - | q15 : int(1..4)]), - and([q16 <= var2_ExplicitVarSizeWithMarkerR5_Marker -> - (2 <= var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q16] -> - -toInt(var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q16, 1]) < - -toInt(var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q16, 2])) - | q16 : int(1..4)]), - and([q16 <= var2_ExplicitVarSizeWithMarkerR5_Marker -> - and([q18 > var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q16] -> - var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q16, q18] = false - | q18 : int(1..2)]) - | q16 : int(1..4)]), - and([q24 <= var2_ExplicitVarSizeWithMarkerR5_Marker -> - or([q26 <= var2_ExplicitVarSizeWithMarkerR4_Marker /\ - (and([var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Flags[q26, q28] -> - or([q30 <= var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q24] /\ - var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q24, q30] = - var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Values[q26, q28] - | q30 : int(1..2)]) - | q28 : int(1..2)]) - /\ - and([q32 <= var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q24] -> - or([var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Flags[q26, q34] /\ - var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Values[q26, q34] = - var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q24, q32] - | q34 : int(1..2)]) - | q32 : int(1..2)])) - | q26 : int(1..4)]) - | q24 : int(1..4)]), - and([q36 <= var2_ExplicitVarSizeWithMarkerR4_Marker -> - or([q38 <= var2_ExplicitVarSizeWithMarkerR5_Marker /\ - (and([q40 <= var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q38] -> - or([var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Flags[q36, q42] /\ - var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Values[q36, q42] = - var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q38, q40] - | q42 : int(1..2)]) - | q40 : int(1..2)]) - /\ - and([var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Flags[q36, q44] -> - or([q46 <= var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q38] /\ - var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q38, q46] = - var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Values[q36, q44] - | q46 : int(1..2)]) - | q44 : int(1..2)])) - | q38 : int(1..4)]) - | q36 : int(1..4)]) - diff --git a/tests/exhaustive/autogen/gen02/expected/model_2_2-solution000001.solution b/tests/exhaustive/autogen/gen02/expected/model_2_2-solution000001.solution deleted file mode 100644 index 19d999ca82..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_2_2-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting var2 be {{}} diff --git a/tests/exhaustive/autogen/gen02/expected/model_2_2-solution000002.solution b/tests/exhaustive/autogen/gen02/expected/model_2_2-solution000002.solution deleted file mode 100644 index 937293310f..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_2_2-solution000002.solution +++ /dev/null @@ -1,6 +0,0 @@ -language Essence 1.3 - -letting var2 be {{false}} -$ Visualisation for var2 -$ _ - diff --git a/tests/exhaustive/autogen/gen02/expected/model_2_2-solution000003.solution b/tests/exhaustive/autogen/gen02/expected/model_2_2-solution000003.solution deleted file mode 100644 index 5a187652fa..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_2_2-solution000003.solution +++ /dev/null @@ -1,6 +0,0 @@ -language Essence 1.3 - -letting var2 be {{true}} -$ Visualisation for var2 -$ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_2_2-solution000004.solution b/tests/exhaustive/autogen/gen02/expected/model_2_2-solution000004.solution deleted file mode 100644 index 0678d41bf8..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_2_2-solution000004.solution +++ /dev/null @@ -1,6 +0,0 @@ -language Essence 1.3 - -letting var2 be {{false, true}} -$ Visualisation for var2 -$ _ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_2_2-solution000005.solution b/tests/exhaustive/autogen/gen02/expected/model_2_2-solution000005.solution deleted file mode 100644 index 73f1bfe1ac..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_2_2-solution000005.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting var2 be {{}, {false}} -$ Visualisation for var2 -$ -$ _ - diff --git a/tests/exhaustive/autogen/gen02/expected/model_2_2-solution000006.solution b/tests/exhaustive/autogen/gen02/expected/model_2_2-solution000006.solution deleted file mode 100644 index d4c4a238b9..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_2_2-solution000006.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting var2 be {{}, {true}} -$ Visualisation for var2 -$ -$ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_2_2-solution000007.solution b/tests/exhaustive/autogen/gen02/expected/model_2_2-solution000007.solution deleted file mode 100644 index 2b6a8959da..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_2_2-solution000007.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting var2 be {{false}, {true}} -$ Visualisation for var2 -$ _ -$ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_2_2-solution000008.solution b/tests/exhaustive/autogen/gen02/expected/model_2_2-solution000008.solution deleted file mode 100644 index 9c15a8e4e1..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_2_2-solution000008.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting var2 be {{}, {false, true}} -$ Visualisation for var2 -$ -$ _ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_2_2-solution000009.solution b/tests/exhaustive/autogen/gen02/expected/model_2_2-solution000009.solution deleted file mode 100644 index b2e98e56a6..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_2_2-solution000009.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting var2 be {{false}, {false, true}} -$ Visualisation for var2 -$ _ -$ _ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_2_2-solution000010.solution b/tests/exhaustive/autogen/gen02/expected/model_2_2-solution000010.solution deleted file mode 100644 index 4fc309134f..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_2_2-solution000010.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting var2 be {{false, true}, {true}} -$ Visualisation for var2 -$ _ T -$ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_2_2-solution000011.solution b/tests/exhaustive/autogen/gen02/expected/model_2_2-solution000011.solution deleted file mode 100644 index 70d0f91f38..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_2_2-solution000011.solution +++ /dev/null @@ -1,8 +0,0 @@ -language Essence 1.3 - -letting var2 be {{}, {false}, {true}} -$ Visualisation for var2 -$ -$ _ -$ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_2_2-solution000012.solution b/tests/exhaustive/autogen/gen02/expected/model_2_2-solution000012.solution deleted file mode 100644 index ebc3fe4182..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_2_2-solution000012.solution +++ /dev/null @@ -1,8 +0,0 @@ -language Essence 1.3 - -letting var2 be {{}, {false}, {false, true}} -$ Visualisation for var2 -$ -$ _ -$ _ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_2_2-solution000013.solution b/tests/exhaustive/autogen/gen02/expected/model_2_2-solution000013.solution deleted file mode 100644 index fa4340a533..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_2_2-solution000013.solution +++ /dev/null @@ -1,8 +0,0 @@ -language Essence 1.3 - -letting var2 be {{}, {false, true}, {true}} -$ Visualisation for var2 -$ -$ _ T -$ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_2_2-solution000014.solution b/tests/exhaustive/autogen/gen02/expected/model_2_2-solution000014.solution deleted file mode 100644 index 371f28aab7..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_2_2-solution000014.solution +++ /dev/null @@ -1,8 +0,0 @@ -language Essence 1.3 - -letting var2 be {{false}, {false, true}, {true}} -$ Visualisation for var2 -$ _ -$ _ T -$ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_2_2-solution000015.solution b/tests/exhaustive/autogen/gen02/expected/model_2_2-solution000015.solution deleted file mode 100644 index 35cfa328e8..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_2_2-solution000015.solution +++ /dev/null @@ -1,9 +0,0 @@ -language Essence 1.3 - -letting var2 be {{}, {false}, {false, true}, {true}} -$ Visualisation for var2 -$ -$ _ -$ _ T -$ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_2_2.eprime b/tests/exhaustive/autogen/gen02/expected/model_2_2.eprime deleted file mode 100644 index c1cfaf2da7..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_2_2.eprime +++ /dev/null @@ -1,53 +0,0 @@ -language ESSENCE' 1.0 - -find var2_ExplicitVarSizeWithMarkerR4_Marker: int(0..4) -find var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Flags: - matrix indexed by [int(1..4), int(1..2)] of bool -find var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Values: - matrix indexed by [int(1..4), int(1..2)] of bool -branching on - [var2_ExplicitVarSizeWithMarkerR4_Marker, var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Flags, - var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Values] -such that - or([q14 <= var2_ExplicitVarSizeWithMarkerR4_Marker /\ - sum([toInt(var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Flags[q14, q15]) | q15 : int(1..2)]) - >= -7 - | q14 : int(1..4)]), - and([q2 + 1 <= var2_ExplicitVarSizeWithMarkerR4_Marker -> - flatten([flatten([[-toInt(var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Flags[q2, q10]); - int(1)], - [-toInt(var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Values[q2, q10]); - int(1)]; - int(1..2)]) - | q10 : int(1..2)]) - var2_ExplicitVarSizeWithMarkerR4_Marker -> - and([var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Flags[q3, q12] = false - | q12 : int(1..2)]) - /\ - and([var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Values[q3, q13] = false - | q13 : int(1..2)]) - | q3 : int(1..4)]), - and([q4 <= var2_ExplicitVarSizeWithMarkerR4_Marker -> - (var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Flags[q4, 2] -> - -toInt(var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Values[q4, 1]) < - -toInt(var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Values[q4, 2])) - | q4 : int(1..4)]), - and([q4 <= var2_ExplicitVarSizeWithMarkerR4_Marker -> - and([var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Flags[q4, q6] = false -> - var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Values[q4, q6] = false - | q6 : int(1..2)]) - | q4 : int(1..4)]), - and([q4 <= var2_ExplicitVarSizeWithMarkerR4_Marker -> - (var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Flags[q4, 2] -> - var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Flags[q4, 1]) - | q4 : int(1..4)]) - diff --git a/tests/exhaustive/autogen/gen02/expected/model_2_3-solution000001.solution b/tests/exhaustive/autogen/gen02/expected/model_2_3-solution000001.solution deleted file mode 100644 index 19d999ca82..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_2_3-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting var2 be {{}} diff --git a/tests/exhaustive/autogen/gen02/expected/model_2_3-solution000002.solution b/tests/exhaustive/autogen/gen02/expected/model_2_3-solution000002.solution deleted file mode 100644 index 937293310f..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_2_3-solution000002.solution +++ /dev/null @@ -1,6 +0,0 @@ -language Essence 1.3 - -letting var2 be {{false}} -$ Visualisation for var2 -$ _ - diff --git a/tests/exhaustive/autogen/gen02/expected/model_2_3-solution000003.solution b/tests/exhaustive/autogen/gen02/expected/model_2_3-solution000003.solution deleted file mode 100644 index 5a187652fa..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_2_3-solution000003.solution +++ /dev/null @@ -1,6 +0,0 @@ -language Essence 1.3 - -letting var2 be {{true}} -$ Visualisation for var2 -$ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_2_3-solution000004.solution b/tests/exhaustive/autogen/gen02/expected/model_2_3-solution000004.solution deleted file mode 100644 index 0678d41bf8..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_2_3-solution000004.solution +++ /dev/null @@ -1,6 +0,0 @@ -language Essence 1.3 - -letting var2 be {{false, true}} -$ Visualisation for var2 -$ _ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_2_3-solution000005.solution b/tests/exhaustive/autogen/gen02/expected/model_2_3-solution000005.solution deleted file mode 100644 index 73f1bfe1ac..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_2_3-solution000005.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting var2 be {{}, {false}} -$ Visualisation for var2 -$ -$ _ - diff --git a/tests/exhaustive/autogen/gen02/expected/model_2_3-solution000006.solution b/tests/exhaustive/autogen/gen02/expected/model_2_3-solution000006.solution deleted file mode 100644 index d4c4a238b9..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_2_3-solution000006.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting var2 be {{}, {true}} -$ Visualisation for var2 -$ -$ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_2_3-solution000007.solution b/tests/exhaustive/autogen/gen02/expected/model_2_3-solution000007.solution deleted file mode 100644 index 9c15a8e4e1..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_2_3-solution000007.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting var2 be {{}, {false, true}} -$ Visualisation for var2 -$ -$ _ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_2_3-solution000008.solution b/tests/exhaustive/autogen/gen02/expected/model_2_3-solution000008.solution deleted file mode 100644 index 2b6a8959da..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_2_3-solution000008.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting var2 be {{false}, {true}} -$ Visualisation for var2 -$ _ -$ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_2_3-solution000009.solution b/tests/exhaustive/autogen/gen02/expected/model_2_3-solution000009.solution deleted file mode 100644 index b2e98e56a6..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_2_3-solution000009.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting var2 be {{false}, {false, true}} -$ Visualisation for var2 -$ _ -$ _ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_2_3-solution000010.solution b/tests/exhaustive/autogen/gen02/expected/model_2_3-solution000010.solution deleted file mode 100644 index 4fc309134f..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_2_3-solution000010.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting var2 be {{false, true}, {true}} -$ Visualisation for var2 -$ _ T -$ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_2_3-solution000011.solution b/tests/exhaustive/autogen/gen02/expected/model_2_3-solution000011.solution deleted file mode 100644 index 70d0f91f38..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_2_3-solution000011.solution +++ /dev/null @@ -1,8 +0,0 @@ -language Essence 1.3 - -letting var2 be {{}, {false}, {true}} -$ Visualisation for var2 -$ -$ _ -$ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_2_3-solution000012.solution b/tests/exhaustive/autogen/gen02/expected/model_2_3-solution000012.solution deleted file mode 100644 index ebc3fe4182..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_2_3-solution000012.solution +++ /dev/null @@ -1,8 +0,0 @@ -language Essence 1.3 - -letting var2 be {{}, {false}, {false, true}} -$ Visualisation for var2 -$ -$ _ -$ _ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_2_3-solution000013.solution b/tests/exhaustive/autogen/gen02/expected/model_2_3-solution000013.solution deleted file mode 100644 index fa4340a533..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_2_3-solution000013.solution +++ /dev/null @@ -1,8 +0,0 @@ -language Essence 1.3 - -letting var2 be {{}, {false, true}, {true}} -$ Visualisation for var2 -$ -$ _ T -$ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_2_3-solution000014.solution b/tests/exhaustive/autogen/gen02/expected/model_2_3-solution000014.solution deleted file mode 100644 index 371f28aab7..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_2_3-solution000014.solution +++ /dev/null @@ -1,8 +0,0 @@ -language Essence 1.3 - -letting var2 be {{false}, {false, true}, {true}} -$ Visualisation for var2 -$ _ -$ _ T -$ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_2_3-solution000015.solution b/tests/exhaustive/autogen/gen02/expected/model_2_3-solution000015.solution deleted file mode 100644 index 35cfa328e8..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_2_3-solution000015.solution +++ /dev/null @@ -1,9 +0,0 @@ -language Essence 1.3 - -letting var2 be {{}, {false}, {false, true}, {true}} -$ Visualisation for var2 -$ -$ _ -$ _ T -$ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_2_3.eprime b/tests/exhaustive/autogen/gen02/expected/model_2_3.eprime deleted file mode 100644 index 930f9649d5..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_2_3.eprime +++ /dev/null @@ -1,124 +0,0 @@ -language ESSENCE' 1.0 - -find var2_ExplicitVarSizeWithMarkerR4_Marker: int(0..4) -find var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Flags: - matrix indexed by [int(1..4), int(1..2)] of bool -find var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Values: - matrix indexed by [int(1..4), int(1..2)] of bool -find var2_ExplicitVarSizeWithFlagsR5_Flags: matrix indexed by [int(1..4)] of bool -find var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Marker: matrix indexed by [int(1..4)] of int(0..2) -find var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Values: - matrix indexed by [int(1..4), int(1..2)] of bool -branching on - [var2_ExplicitVarSizeWithFlagsR5_Flags, var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Marker, - var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Values, var2_ExplicitVarSizeWithMarkerR4_Marker, - var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Flags, - var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Values] -such that - or([q49 <= var2_ExplicitVarSizeWithMarkerR4_Marker /\ - sum([toInt(var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Flags[q49, q50]) | q50 : int(1..2)]) - >= -7 - | q49 : int(1..4)]), - and([q2 + 1 <= var2_ExplicitVarSizeWithMarkerR4_Marker -> - flatten([flatten([[-toInt(var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Flags[q2, q10]); - int(1)], - [-toInt(var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Values[q2, q10]); - int(1)]; - int(1..2)]) - | q10 : int(1..2)]) - var2_ExplicitVarSizeWithMarkerR4_Marker -> - and([var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Flags[q3, q12] = false - | q12 : int(1..2)]) - /\ - and([var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Values[q3, q13] = false - | q13 : int(1..2)]) - | q3 : int(1..4)]), - and([q4 <= var2_ExplicitVarSizeWithMarkerR4_Marker -> - (var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Flags[q4, 2] -> - -toInt(var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Values[q4, 1]) < - -toInt(var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Values[q4, 2])) - | q4 : int(1..4)]), - and([q4 <= var2_ExplicitVarSizeWithMarkerR4_Marker -> - and([var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Flags[q4, q6] = false -> - var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Values[q4, q6] = false - | q6 : int(1..2)]) - | q4 : int(1..4)]), - and([q4 <= var2_ExplicitVarSizeWithMarkerR4_Marker -> - (var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Flags[q4, 2] -> - var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Flags[q4, 1]) - | q4 : int(1..4)]), - and([var2_ExplicitVarSizeWithFlagsR5_Flags[q14 + 1] -> - flatten([[var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Marker[q14]; int(1)], - flatten([[-toInt(var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Values[q14, q22]); - int(1)] - | q22 : int(1..2)]); - int(1..2)]) - - var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Marker[q15] = 0 /\ - and([var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Values[q15, q24] = false - | q24 : int(1..2)]) - | q15 : int(1..4)]), - and([var2_ExplicitVarSizeWithFlagsR5_Flags[q16 + 1] -> var2_ExplicitVarSizeWithFlagsR5_Flags[q16] - | q16 : int(1..3)]), - and([var2_ExplicitVarSizeWithFlagsR5_Flags[q18] -> - (2 <= var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Marker[q18] -> - -toInt(var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Values[q18, 1]) < - -toInt(var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Values[q18, 2])) - | q18 : int(1..4)]), - and([var2_ExplicitVarSizeWithFlagsR5_Flags[q18] -> - and([q20 > var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Marker[q18] -> - var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Values[q18, q20] = false - | q20 : int(1..2)]) - | q18 : int(1..4)]), - and([var2_ExplicitVarSizeWithFlagsR5_Flags[q26] -> - or([q28 <= var2_ExplicitVarSizeWithMarkerR4_Marker /\ - (and([var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Flags[q28, q30] -> - or([q32 <= var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Marker[q26] /\ - var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Values[q26, q32] = - var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Values[q28, q30] - | q32 : int(1..2)]) - | q30 : int(1..2)]) - /\ - and([q34 <= var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Marker[q26] -> - or([var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Flags[q28, q36] /\ - var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Values[q28, q36] = - var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Values[q26, q34] - | q36 : int(1..2)]) - | q34 : int(1..2)])) - | q28 : int(1..4)]) - | q26 : int(1..4)]), - and([q38 <= var2_ExplicitVarSizeWithMarkerR4_Marker -> - or([var2_ExplicitVarSizeWithFlagsR5_Flags[q40] /\ - (and([q42 <= var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Marker[q40] -> - or([var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Flags[q38, q44] /\ - var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Values[q38, q44] = - var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Values[q40, q42] - | q44 : int(1..2)]) - | q42 : int(1..2)]) - /\ - and([var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Flags[q38, q46] -> - or([q48 <= var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Marker[q40] /\ - var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Values[q40, q48] = - var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Values[q38, q46] - | q48 : int(1..2)]) - | q46 : int(1..2)])) - | q40 : int(1..4)]) - | q38 : int(1..4)]) - diff --git a/tests/exhaustive/autogen/gen02/expected/model_2_4-solution000001.solution b/tests/exhaustive/autogen/gen02/expected/model_2_4-solution000001.solution deleted file mode 100644 index 19d999ca82..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_2_4-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting var2 be {{}} diff --git a/tests/exhaustive/autogen/gen02/expected/model_2_4-solution000002.solution b/tests/exhaustive/autogen/gen02/expected/model_2_4-solution000002.solution deleted file mode 100644 index 937293310f..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_2_4-solution000002.solution +++ /dev/null @@ -1,6 +0,0 @@ -language Essence 1.3 - -letting var2 be {{false}} -$ Visualisation for var2 -$ _ - diff --git a/tests/exhaustive/autogen/gen02/expected/model_2_4-solution000003.solution b/tests/exhaustive/autogen/gen02/expected/model_2_4-solution000003.solution deleted file mode 100644 index 5a187652fa..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_2_4-solution000003.solution +++ /dev/null @@ -1,6 +0,0 @@ -language Essence 1.3 - -letting var2 be {{true}} -$ Visualisation for var2 -$ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_2_4-solution000004.solution b/tests/exhaustive/autogen/gen02/expected/model_2_4-solution000004.solution deleted file mode 100644 index 0678d41bf8..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_2_4-solution000004.solution +++ /dev/null @@ -1,6 +0,0 @@ -language Essence 1.3 - -letting var2 be {{false, true}} -$ Visualisation for var2 -$ _ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_2_4-solution000005.solution b/tests/exhaustive/autogen/gen02/expected/model_2_4-solution000005.solution deleted file mode 100644 index 73f1bfe1ac..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_2_4-solution000005.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting var2 be {{}, {false}} -$ Visualisation for var2 -$ -$ _ - diff --git a/tests/exhaustive/autogen/gen02/expected/model_2_4-solution000006.solution b/tests/exhaustive/autogen/gen02/expected/model_2_4-solution000006.solution deleted file mode 100644 index d4c4a238b9..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_2_4-solution000006.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting var2 be {{}, {true}} -$ Visualisation for var2 -$ -$ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_2_4-solution000007.solution b/tests/exhaustive/autogen/gen02/expected/model_2_4-solution000007.solution deleted file mode 100644 index 2b6a8959da..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_2_4-solution000007.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting var2 be {{false}, {true}} -$ Visualisation for var2 -$ _ -$ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_2_4-solution000008.solution b/tests/exhaustive/autogen/gen02/expected/model_2_4-solution000008.solution deleted file mode 100644 index 9c15a8e4e1..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_2_4-solution000008.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting var2 be {{}, {false, true}} -$ Visualisation for var2 -$ -$ _ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_2_4-solution000009.solution b/tests/exhaustive/autogen/gen02/expected/model_2_4-solution000009.solution deleted file mode 100644 index b2e98e56a6..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_2_4-solution000009.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting var2 be {{false}, {false, true}} -$ Visualisation for var2 -$ _ -$ _ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_2_4-solution000010.solution b/tests/exhaustive/autogen/gen02/expected/model_2_4-solution000010.solution deleted file mode 100644 index 4fc309134f..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_2_4-solution000010.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting var2 be {{false, true}, {true}} -$ Visualisation for var2 -$ _ T -$ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_2_4-solution000011.solution b/tests/exhaustive/autogen/gen02/expected/model_2_4-solution000011.solution deleted file mode 100644 index 70d0f91f38..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_2_4-solution000011.solution +++ /dev/null @@ -1,8 +0,0 @@ -language Essence 1.3 - -letting var2 be {{}, {false}, {true}} -$ Visualisation for var2 -$ -$ _ -$ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_2_4-solution000012.solution b/tests/exhaustive/autogen/gen02/expected/model_2_4-solution000012.solution deleted file mode 100644 index ebc3fe4182..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_2_4-solution000012.solution +++ /dev/null @@ -1,8 +0,0 @@ -language Essence 1.3 - -letting var2 be {{}, {false}, {false, true}} -$ Visualisation for var2 -$ -$ _ -$ _ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_2_4-solution000013.solution b/tests/exhaustive/autogen/gen02/expected/model_2_4-solution000013.solution deleted file mode 100644 index fa4340a533..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_2_4-solution000013.solution +++ /dev/null @@ -1,8 +0,0 @@ -language Essence 1.3 - -letting var2 be {{}, {false, true}, {true}} -$ Visualisation for var2 -$ -$ _ T -$ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_2_4-solution000014.solution b/tests/exhaustive/autogen/gen02/expected/model_2_4-solution000014.solution deleted file mode 100644 index 371f28aab7..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_2_4-solution000014.solution +++ /dev/null @@ -1,8 +0,0 @@ -language Essence 1.3 - -letting var2 be {{false}, {false, true}, {true}} -$ Visualisation for var2 -$ _ -$ _ T -$ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_2_4-solution000015.solution b/tests/exhaustive/autogen/gen02/expected/model_2_4-solution000015.solution deleted file mode 100644 index 35cfa328e8..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_2_4-solution000015.solution +++ /dev/null @@ -1,9 +0,0 @@ -language Essence 1.3 - -letting var2 be {{}, {false}, {false, true}, {true}} -$ Visualisation for var2 -$ -$ _ -$ _ T -$ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_2_4.eprime b/tests/exhaustive/autogen/gen02/expected/model_2_4.eprime deleted file mode 100644 index 1c6891d59e..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_2_4.eprime +++ /dev/null @@ -1,121 +0,0 @@ -language ESSENCE' 1.0 - -find var2_ExplicitVarSizeWithMarkerR4_Marker: int(0..4) -find var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Flags: - matrix indexed by [int(1..4), int(1..2)] of bool -find var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Values: - matrix indexed by [int(1..4), int(1..2)] of bool -find var2_ExplicitVarSizeWithFlagsR4_Flags: matrix indexed by [int(1..4)] of bool -find var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Flags: - matrix indexed by [int(1..4), int(1..2)] of bool -find var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Values: - matrix indexed by [int(1..4), int(1..2)] of bool -branching on - [var2_ExplicitVarSizeWithFlagsR4_Flags, var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Flags, - var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Values, var2_ExplicitVarSizeWithMarkerR4_Marker, - var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Flags, - var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Values] -such that - or([q44 <= var2_ExplicitVarSizeWithMarkerR4_Marker /\ - sum([toInt(var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Flags[q44, q45]) | q45 : int(1..2)]) - >= -7 - | q44 : int(1..4)]), - and([q2 + 1 <= var2_ExplicitVarSizeWithMarkerR4_Marker -> - flatten([flatten([[-toInt(var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Flags[q2, q10]); - int(1)], - [-toInt(var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Values[q2, q10]); - int(1)]; - int(1..2)]) - | q10 : int(1..2)]) - var2_ExplicitVarSizeWithMarkerR4_Marker -> - and([var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Flags[q3, q12] = false - | q12 : int(1..2)]) - /\ - and([var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Values[q3, q13] = false - | q13 : int(1..2)]) - | q3 : int(1..4)]), - and([q4 <= var2_ExplicitVarSizeWithMarkerR4_Marker -> - (var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Flags[q4, 2] -> - -toInt(var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Values[q4, 1]) < - -toInt(var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Values[q4, 2])) - | q4 : int(1..4)]), - and([q4 <= var2_ExplicitVarSizeWithMarkerR4_Marker -> - and([var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Flags[q4, q6] = false -> - var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Values[q4, q6] = false - | q6 : int(1..2)]) - | q4 : int(1..4)]), - and([q4 <= var2_ExplicitVarSizeWithMarkerR4_Marker -> - (var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Flags[q4, 2] -> - var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Flags[q4, 1]) - | q4 : int(1..4)]), - and([var2_ExplicitVarSizeWithFlagsR4_Flags[q14 + 1] -> - flatten([flatten([[-toInt(var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Flags[q14, q24]); - int(1)], - [-toInt(var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Values[q14, q24]); - int(1)]; - int(1..2)]) - | q24 : int(1..2)]) - - and([var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Flags[q15, q26] = false - | q26 : int(1..2)]) - /\ - and([var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Values[q15, q27] = false - | q27 : int(1..2)]) - | q15 : int(1..4)]), - and([var2_ExplicitVarSizeWithFlagsR4_Flags[q16 + 1] -> var2_ExplicitVarSizeWithFlagsR4_Flags[q16] - | q16 : int(1..3)]), - and([var2_ExplicitVarSizeWithFlagsR4_Flags[q18] -> - (var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Flags[q18, 2] -> - -toInt(var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Values[q18, 1]) < - -toInt(var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Values[q18, 2])) - | q18 : int(1..4)]), - and([var2_ExplicitVarSizeWithFlagsR4_Flags[q18] -> - and([var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Flags[q18, q20] = false -> - var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Values[q18, q20] = false - | q20 : int(1..2)]) - | q18 : int(1..4)]), - and([var2_ExplicitVarSizeWithFlagsR4_Flags[q18] -> - (var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Flags[q18, 2] -> - var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Flags[q18, 1]) - | q18 : int(1..4)]), - and([var2_ExplicitVarSizeWithFlagsR4_Flags[q29] -> - or([q31 <= var2_ExplicitVarSizeWithMarkerR4_Marker /\ - (and([var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Flags[q31, q32] = - var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Flags[q29, q32] - | q32 : int(1..2)]) - /\ - and([var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Values[q31, q34] = - var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Values[q29, q34] - | q34 : int(1..2)])) - | q31 : int(1..4)]) - | q29 : int(1..4)]), - and([q37 <= var2_ExplicitVarSizeWithMarkerR4_Marker -> - or([var2_ExplicitVarSizeWithFlagsR4_Flags[q39] /\ - (and([var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Flags[q39, q40] = - var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Flags[q37, q40] - | q40 : int(1..2)]) - /\ - and([var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Values[q39, q42] = - var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Values[q37, q42] - | q42 : int(1..2)])) - | q39 : int(1..4)]) - | q37 : int(1..4)]) - diff --git a/tests/exhaustive/autogen/gen02/expected/model_3_1-solution000001.solution b/tests/exhaustive/autogen/gen02/expected/model_3_1-solution000001.solution deleted file mode 100644 index 19d999ca82..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_3_1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting var2 be {{}} diff --git a/tests/exhaustive/autogen/gen02/expected/model_3_1-solution000002.solution b/tests/exhaustive/autogen/gen02/expected/model_3_1-solution000002.solution deleted file mode 100644 index 937293310f..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_3_1-solution000002.solution +++ /dev/null @@ -1,6 +0,0 @@ -language Essence 1.3 - -letting var2 be {{false}} -$ Visualisation for var2 -$ _ - diff --git a/tests/exhaustive/autogen/gen02/expected/model_3_1-solution000003.solution b/tests/exhaustive/autogen/gen02/expected/model_3_1-solution000003.solution deleted file mode 100644 index 5a187652fa..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_3_1-solution000003.solution +++ /dev/null @@ -1,6 +0,0 @@ -language Essence 1.3 - -letting var2 be {{true}} -$ Visualisation for var2 -$ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_3_1-solution000004.solution b/tests/exhaustive/autogen/gen02/expected/model_3_1-solution000004.solution deleted file mode 100644 index 0678d41bf8..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_3_1-solution000004.solution +++ /dev/null @@ -1,6 +0,0 @@ -language Essence 1.3 - -letting var2 be {{false, true}} -$ Visualisation for var2 -$ _ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_3_1-solution000005.solution b/tests/exhaustive/autogen/gen02/expected/model_3_1-solution000005.solution deleted file mode 100644 index 73f1bfe1ac..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_3_1-solution000005.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting var2 be {{}, {false}} -$ Visualisation for var2 -$ -$ _ - diff --git a/tests/exhaustive/autogen/gen02/expected/model_3_1-solution000006.solution b/tests/exhaustive/autogen/gen02/expected/model_3_1-solution000006.solution deleted file mode 100644 index d4c4a238b9..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_3_1-solution000006.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting var2 be {{}, {true}} -$ Visualisation for var2 -$ -$ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_3_1-solution000007.solution b/tests/exhaustive/autogen/gen02/expected/model_3_1-solution000007.solution deleted file mode 100644 index 9c15a8e4e1..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_3_1-solution000007.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting var2 be {{}, {false, true}} -$ Visualisation for var2 -$ -$ _ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_3_1-solution000008.solution b/tests/exhaustive/autogen/gen02/expected/model_3_1-solution000008.solution deleted file mode 100644 index 2b6a8959da..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_3_1-solution000008.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting var2 be {{false}, {true}} -$ Visualisation for var2 -$ _ -$ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_3_1-solution000009.solution b/tests/exhaustive/autogen/gen02/expected/model_3_1-solution000009.solution deleted file mode 100644 index b2e98e56a6..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_3_1-solution000009.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting var2 be {{false}, {false, true}} -$ Visualisation for var2 -$ _ -$ _ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_3_1-solution000010.solution b/tests/exhaustive/autogen/gen02/expected/model_3_1-solution000010.solution deleted file mode 100644 index 4fc309134f..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_3_1-solution000010.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting var2 be {{false, true}, {true}} -$ Visualisation for var2 -$ _ T -$ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_3_1-solution000011.solution b/tests/exhaustive/autogen/gen02/expected/model_3_1-solution000011.solution deleted file mode 100644 index 70d0f91f38..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_3_1-solution000011.solution +++ /dev/null @@ -1,8 +0,0 @@ -language Essence 1.3 - -letting var2 be {{}, {false}, {true}} -$ Visualisation for var2 -$ -$ _ -$ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_3_1-solution000012.solution b/tests/exhaustive/autogen/gen02/expected/model_3_1-solution000012.solution deleted file mode 100644 index ebc3fe4182..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_3_1-solution000012.solution +++ /dev/null @@ -1,8 +0,0 @@ -language Essence 1.3 - -letting var2 be {{}, {false}, {false, true}} -$ Visualisation for var2 -$ -$ _ -$ _ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_3_1-solution000013.solution b/tests/exhaustive/autogen/gen02/expected/model_3_1-solution000013.solution deleted file mode 100644 index fa4340a533..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_3_1-solution000013.solution +++ /dev/null @@ -1,8 +0,0 @@ -language Essence 1.3 - -letting var2 be {{}, {false, true}, {true}} -$ Visualisation for var2 -$ -$ _ T -$ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_3_1-solution000014.solution b/tests/exhaustive/autogen/gen02/expected/model_3_1-solution000014.solution deleted file mode 100644 index 371f28aab7..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_3_1-solution000014.solution +++ /dev/null @@ -1,8 +0,0 @@ -language Essence 1.3 - -letting var2 be {{false}, {false, true}, {true}} -$ Visualisation for var2 -$ _ -$ _ T -$ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_3_1-solution000015.solution b/tests/exhaustive/autogen/gen02/expected/model_3_1-solution000015.solution deleted file mode 100644 index 35cfa328e8..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_3_1-solution000015.solution +++ /dev/null @@ -1,9 +0,0 @@ -language Essence 1.3 - -letting var2 be {{}, {false}, {false, true}, {true}} -$ Visualisation for var2 -$ -$ _ -$ _ T -$ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_3_1.eprime b/tests/exhaustive/autogen/gen02/expected/model_3_1.eprime deleted file mode 100644 index 4f08c77fd7..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_3_1.eprime +++ /dev/null @@ -1,102 +0,0 @@ -language ESSENCE' 1.0 - -find var2_ExplicitVarSizeWithFlagsR5_Flags: matrix indexed by [int(1..4)] of bool -find var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Marker: matrix indexed by [int(1..4)] of int(0..2) -find var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Values: - matrix indexed by [int(1..4), int(1..2)] of bool -find var2_ExplicitVarSizeWithMarkerR5_Marker: int(0..4) -find var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker: - matrix indexed by [int(1..4)] of int(0..2) -find var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values: - matrix indexed by [int(1..4), int(1..2)] of bool -branching on - [var2_ExplicitVarSizeWithMarkerR5_Marker, var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker, - var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values, var2_ExplicitVarSizeWithFlagsR5_Flags, - var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Marker, - var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Values] -such that - or([var2_ExplicitVarSizeWithFlagsR5_Flags[q34] /\ - sum([toInt(q35 <= var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Marker[q34]) - | q35 : int(1..2)]) - >= -7 - | q34 : int(1..4)]), - and([var2_ExplicitVarSizeWithFlagsR5_Flags[q2 + 1] -> - flatten([[var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Marker[q2]; int(1)], - flatten([[-toInt(var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Values[q2, q10]); - int(1)] - | q10 : int(1..2)]); - int(1..2)]) - - var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Marker[q3] = 0 /\ - and([var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Values[q3, q12] = false - | q12 : int(1..2)]) - | q3 : int(1..4)]), - and([var2_ExplicitVarSizeWithFlagsR5_Flags[q4 + 1] -> var2_ExplicitVarSizeWithFlagsR5_Flags[q4] | q4 : int(1..3)]), - and([var2_ExplicitVarSizeWithFlagsR5_Flags[q6] -> - (2 <= var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Marker[q6] -> - -toInt(var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Values[q6, 1]) < - -toInt(var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Values[q6, 2])) - | q6 : int(1..4)]), - and([var2_ExplicitVarSizeWithFlagsR5_Flags[q6] -> - and([q8 > var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Marker[q6] -> - var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Values[q6, q8] = false - | q8 : int(1..2)]) - | q6 : int(1..4)]), - and([q13 + 1 <= var2_ExplicitVarSizeWithMarkerR5_Marker -> - flatten([[var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q13]; int(1)], - flatten([[-toInt(var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q13, q19]); - int(1)] - | q19 : int(1..2)]); - int(1..2)]) - var2_ExplicitVarSizeWithMarkerR5_Marker -> - var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q14] = 0 /\ - and([var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q14, q21] = false - | q21 : int(1..2)]) - | q14 : int(1..4)]), - and([q15 <= var2_ExplicitVarSizeWithMarkerR5_Marker -> - (2 <= var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q15] -> - -toInt(var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q15, 1]) < - -toInt(var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q15, 2])) - | q15 : int(1..4)]), - and([q15 <= var2_ExplicitVarSizeWithMarkerR5_Marker -> - and([q17 > var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q15] -> - var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q15, q17] = false - | q17 : int(1..2)]) - | q15 : int(1..4)]), - and([q23 <= var2_ExplicitVarSizeWithMarkerR5_Marker -> - or([var2_ExplicitVarSizeWithFlagsR5_Flags[q25] /\ - (var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Marker[q25] = - var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q23] - /\ - and([var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Values[q25, q26] = - var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q23, q26] - | q26 : int(1..2)])) - | q25 : int(1..4)]) - | q23 : int(1..4)]), - and([var2_ExplicitVarSizeWithFlagsR5_Flags[q29] -> - or([q31 <= var2_ExplicitVarSizeWithMarkerR5_Marker /\ - (var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q31] = - var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Marker[q29] - /\ - and([var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q31, q32] = - var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Values[q29, q32] - | q32 : int(1..2)])) - | q31 : int(1..4)]) - | q29 : int(1..4)]) - diff --git a/tests/exhaustive/autogen/gen02/expected/model_3_2-solution000001.solution b/tests/exhaustive/autogen/gen02/expected/model_3_2-solution000001.solution deleted file mode 100644 index 19d999ca82..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_3_2-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting var2 be {{}} diff --git a/tests/exhaustive/autogen/gen02/expected/model_3_2-solution000002.solution b/tests/exhaustive/autogen/gen02/expected/model_3_2-solution000002.solution deleted file mode 100644 index 937293310f..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_3_2-solution000002.solution +++ /dev/null @@ -1,6 +0,0 @@ -language Essence 1.3 - -letting var2 be {{false}} -$ Visualisation for var2 -$ _ - diff --git a/tests/exhaustive/autogen/gen02/expected/model_3_2-solution000003.solution b/tests/exhaustive/autogen/gen02/expected/model_3_2-solution000003.solution deleted file mode 100644 index 5a187652fa..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_3_2-solution000003.solution +++ /dev/null @@ -1,6 +0,0 @@ -language Essence 1.3 - -letting var2 be {{true}} -$ Visualisation for var2 -$ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_3_2-solution000004.solution b/tests/exhaustive/autogen/gen02/expected/model_3_2-solution000004.solution deleted file mode 100644 index 0678d41bf8..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_3_2-solution000004.solution +++ /dev/null @@ -1,6 +0,0 @@ -language Essence 1.3 - -letting var2 be {{false, true}} -$ Visualisation for var2 -$ _ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_3_2-solution000005.solution b/tests/exhaustive/autogen/gen02/expected/model_3_2-solution000005.solution deleted file mode 100644 index 73f1bfe1ac..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_3_2-solution000005.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting var2 be {{}, {false}} -$ Visualisation for var2 -$ -$ _ - diff --git a/tests/exhaustive/autogen/gen02/expected/model_3_2-solution000006.solution b/tests/exhaustive/autogen/gen02/expected/model_3_2-solution000006.solution deleted file mode 100644 index d4c4a238b9..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_3_2-solution000006.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting var2 be {{}, {true}} -$ Visualisation for var2 -$ -$ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_3_2-solution000007.solution b/tests/exhaustive/autogen/gen02/expected/model_3_2-solution000007.solution deleted file mode 100644 index 2b6a8959da..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_3_2-solution000007.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting var2 be {{false}, {true}} -$ Visualisation for var2 -$ _ -$ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_3_2-solution000008.solution b/tests/exhaustive/autogen/gen02/expected/model_3_2-solution000008.solution deleted file mode 100644 index 9c15a8e4e1..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_3_2-solution000008.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting var2 be {{}, {false, true}} -$ Visualisation for var2 -$ -$ _ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_3_2-solution000009.solution b/tests/exhaustive/autogen/gen02/expected/model_3_2-solution000009.solution deleted file mode 100644 index b2e98e56a6..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_3_2-solution000009.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting var2 be {{false}, {false, true}} -$ Visualisation for var2 -$ _ -$ _ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_3_2-solution000010.solution b/tests/exhaustive/autogen/gen02/expected/model_3_2-solution000010.solution deleted file mode 100644 index 4fc309134f..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_3_2-solution000010.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting var2 be {{false, true}, {true}} -$ Visualisation for var2 -$ _ T -$ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_3_2-solution000011.solution b/tests/exhaustive/autogen/gen02/expected/model_3_2-solution000011.solution deleted file mode 100644 index 70d0f91f38..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_3_2-solution000011.solution +++ /dev/null @@ -1,8 +0,0 @@ -language Essence 1.3 - -letting var2 be {{}, {false}, {true}} -$ Visualisation for var2 -$ -$ _ -$ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_3_2-solution000012.solution b/tests/exhaustive/autogen/gen02/expected/model_3_2-solution000012.solution deleted file mode 100644 index ebc3fe4182..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_3_2-solution000012.solution +++ /dev/null @@ -1,8 +0,0 @@ -language Essence 1.3 - -letting var2 be {{}, {false}, {false, true}} -$ Visualisation for var2 -$ -$ _ -$ _ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_3_2-solution000013.solution b/tests/exhaustive/autogen/gen02/expected/model_3_2-solution000013.solution deleted file mode 100644 index fa4340a533..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_3_2-solution000013.solution +++ /dev/null @@ -1,8 +0,0 @@ -language Essence 1.3 - -letting var2 be {{}, {false, true}, {true}} -$ Visualisation for var2 -$ -$ _ T -$ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_3_2-solution000014.solution b/tests/exhaustive/autogen/gen02/expected/model_3_2-solution000014.solution deleted file mode 100644 index 371f28aab7..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_3_2-solution000014.solution +++ /dev/null @@ -1,8 +0,0 @@ -language Essence 1.3 - -letting var2 be {{false}, {false, true}, {true}} -$ Visualisation for var2 -$ _ -$ _ T -$ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_3_2-solution000015.solution b/tests/exhaustive/autogen/gen02/expected/model_3_2-solution000015.solution deleted file mode 100644 index 35cfa328e8..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_3_2-solution000015.solution +++ /dev/null @@ -1,9 +0,0 @@ -language Essence 1.3 - -letting var2 be {{}, {false}, {false, true}, {true}} -$ Visualisation for var2 -$ -$ _ -$ _ T -$ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_3_2.eprime b/tests/exhaustive/autogen/gen02/expected/model_3_2.eprime deleted file mode 100644 index 862e124028..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_3_2.eprime +++ /dev/null @@ -1,125 +0,0 @@ -language ESSENCE' 1.0 - -find var2_ExplicitVarSizeWithFlagsR5_Flags: matrix indexed by [int(1..4)] of bool -find var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Marker: matrix indexed by [int(1..4)] of int(0..2) -find var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Values: - matrix indexed by [int(1..4), int(1..2)] of bool -find var2_ExplicitVarSizeWithMarkerR4_Marker: int(0..4) -find var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Flags: - matrix indexed by [int(1..4), int(1..2)] of bool -find var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Values: - matrix indexed by [int(1..4), int(1..2)] of bool -branching on - [var2_ExplicitVarSizeWithMarkerR4_Marker, var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Flags, - var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Values, var2_ExplicitVarSizeWithFlagsR5_Flags, - var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Marker, - var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Values] -such that - or([var2_ExplicitVarSizeWithFlagsR5_Flags[q49] /\ - sum([toInt(q50 <= var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Marker[q49]) - | q50 : int(1..2)]) - >= -7 - | q49 : int(1..4)]), - and([var2_ExplicitVarSizeWithFlagsR5_Flags[q2 + 1] -> - flatten([[var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Marker[q2]; int(1)], - flatten([[-toInt(var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Values[q2, q10]); - int(1)] - | q10 : int(1..2)]); - int(1..2)]) - - var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Marker[q3] = 0 /\ - and([var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Values[q3, q12] = false - | q12 : int(1..2)]) - | q3 : int(1..4)]), - and([var2_ExplicitVarSizeWithFlagsR5_Flags[q4 + 1] -> var2_ExplicitVarSizeWithFlagsR5_Flags[q4] | q4 : int(1..3)]), - and([var2_ExplicitVarSizeWithFlagsR5_Flags[q6] -> - (2 <= var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Marker[q6] -> - -toInt(var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Values[q6, 1]) < - -toInt(var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Values[q6, 2])) - | q6 : int(1..4)]), - and([var2_ExplicitVarSizeWithFlagsR5_Flags[q6] -> - and([q8 > var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Marker[q6] -> - var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Values[q6, q8] = false - | q8 : int(1..2)]) - | q6 : int(1..4)]), - and([q13 + 1 <= var2_ExplicitVarSizeWithMarkerR4_Marker -> - flatten([flatten([[-toInt(var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Flags[q13, q21]); - int(1)], - [-toInt(var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Values[q13, q21]); - int(1)]; - int(1..2)]) - | q21 : int(1..2)]) - var2_ExplicitVarSizeWithMarkerR4_Marker -> - and([var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Flags[q14, q23] = false - | q23 : int(1..2)]) - /\ - and([var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Values[q14, q24] = false - | q24 : int(1..2)]) - | q14 : int(1..4)]), - and([q15 <= var2_ExplicitVarSizeWithMarkerR4_Marker -> - (var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Flags[q15, 2] -> - -toInt(var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Values[q15, 1]) < - -toInt(var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Values[q15, 2])) - | q15 : int(1..4)]), - and([q15 <= var2_ExplicitVarSizeWithMarkerR4_Marker -> - and([var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Flags[q15, q17] = false -> - var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Values[q15, q17] = false - | q17 : int(1..2)]) - | q15 : int(1..4)]), - and([q15 <= var2_ExplicitVarSizeWithMarkerR4_Marker -> - (var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Flags[q15, 2] -> - var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Flags[q15, 1]) - | q15 : int(1..4)]), - and([q26 <= var2_ExplicitVarSizeWithMarkerR4_Marker -> - or([var2_ExplicitVarSizeWithFlagsR5_Flags[q28] /\ - (and([q30 <= var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Marker[q28] -> - or([var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Flags[q26, q32] /\ - var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Values[q26, q32] = - var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Values[q28, q30] - | q32 : int(1..2)]) - | q30 : int(1..2)]) - /\ - and([var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Flags[q26, q34] -> - or([q36 <= var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Marker[q28] /\ - var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Values[q28, q36] = - var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Values[q26, q34] - | q36 : int(1..2)]) - | q34 : int(1..2)])) - | q28 : int(1..4)]) - | q26 : int(1..4)]), - and([var2_ExplicitVarSizeWithFlagsR5_Flags[q38] -> - or([q40 <= var2_ExplicitVarSizeWithMarkerR4_Marker /\ - (and([var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Flags[q40, q42] -> - or([q44 <= var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Marker[q38] /\ - var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Values[q38, q44] = - var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Values[q40, q42] - | q44 : int(1..2)]) - | q42 : int(1..2)]) - /\ - and([q46 <= var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Marker[q38] -> - or([var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Flags[q40, q48] /\ - var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Values[q40, q48] = - var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Values[q38, q46] - | q48 : int(1..2)]) - | q46 : int(1..2)])) - | q40 : int(1..4)]) - | q38 : int(1..4)]) - diff --git a/tests/exhaustive/autogen/gen02/expected/model_3_3-solution000001.solution b/tests/exhaustive/autogen/gen02/expected/model_3_3-solution000001.solution deleted file mode 100644 index 19d999ca82..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_3_3-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting var2 be {{}} diff --git a/tests/exhaustive/autogen/gen02/expected/model_3_3-solution000002.solution b/tests/exhaustive/autogen/gen02/expected/model_3_3-solution000002.solution deleted file mode 100644 index 937293310f..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_3_3-solution000002.solution +++ /dev/null @@ -1,6 +0,0 @@ -language Essence 1.3 - -letting var2 be {{false}} -$ Visualisation for var2 -$ _ - diff --git a/tests/exhaustive/autogen/gen02/expected/model_3_3-solution000003.solution b/tests/exhaustive/autogen/gen02/expected/model_3_3-solution000003.solution deleted file mode 100644 index 5a187652fa..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_3_3-solution000003.solution +++ /dev/null @@ -1,6 +0,0 @@ -language Essence 1.3 - -letting var2 be {{true}} -$ Visualisation for var2 -$ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_3_3-solution000004.solution b/tests/exhaustive/autogen/gen02/expected/model_3_3-solution000004.solution deleted file mode 100644 index 0678d41bf8..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_3_3-solution000004.solution +++ /dev/null @@ -1,6 +0,0 @@ -language Essence 1.3 - -letting var2 be {{false, true}} -$ Visualisation for var2 -$ _ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_3_3-solution000005.solution b/tests/exhaustive/autogen/gen02/expected/model_3_3-solution000005.solution deleted file mode 100644 index 73f1bfe1ac..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_3_3-solution000005.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting var2 be {{}, {false}} -$ Visualisation for var2 -$ -$ _ - diff --git a/tests/exhaustive/autogen/gen02/expected/model_3_3-solution000006.solution b/tests/exhaustive/autogen/gen02/expected/model_3_3-solution000006.solution deleted file mode 100644 index d4c4a238b9..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_3_3-solution000006.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting var2 be {{}, {true}} -$ Visualisation for var2 -$ -$ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_3_3-solution000007.solution b/tests/exhaustive/autogen/gen02/expected/model_3_3-solution000007.solution deleted file mode 100644 index 9c15a8e4e1..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_3_3-solution000007.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting var2 be {{}, {false, true}} -$ Visualisation for var2 -$ -$ _ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_3_3-solution000008.solution b/tests/exhaustive/autogen/gen02/expected/model_3_3-solution000008.solution deleted file mode 100644 index 2b6a8959da..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_3_3-solution000008.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting var2 be {{false}, {true}} -$ Visualisation for var2 -$ _ -$ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_3_3-solution000009.solution b/tests/exhaustive/autogen/gen02/expected/model_3_3-solution000009.solution deleted file mode 100644 index b2e98e56a6..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_3_3-solution000009.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting var2 be {{false}, {false, true}} -$ Visualisation for var2 -$ _ -$ _ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_3_3-solution000010.solution b/tests/exhaustive/autogen/gen02/expected/model_3_3-solution000010.solution deleted file mode 100644 index 4fc309134f..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_3_3-solution000010.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting var2 be {{false, true}, {true}} -$ Visualisation for var2 -$ _ T -$ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_3_3-solution000011.solution b/tests/exhaustive/autogen/gen02/expected/model_3_3-solution000011.solution deleted file mode 100644 index 70d0f91f38..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_3_3-solution000011.solution +++ /dev/null @@ -1,8 +0,0 @@ -language Essence 1.3 - -letting var2 be {{}, {false}, {true}} -$ Visualisation for var2 -$ -$ _ -$ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_3_3-solution000012.solution b/tests/exhaustive/autogen/gen02/expected/model_3_3-solution000012.solution deleted file mode 100644 index ebc3fe4182..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_3_3-solution000012.solution +++ /dev/null @@ -1,8 +0,0 @@ -language Essence 1.3 - -letting var2 be {{}, {false}, {false, true}} -$ Visualisation for var2 -$ -$ _ -$ _ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_3_3-solution000013.solution b/tests/exhaustive/autogen/gen02/expected/model_3_3-solution000013.solution deleted file mode 100644 index fa4340a533..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_3_3-solution000013.solution +++ /dev/null @@ -1,8 +0,0 @@ -language Essence 1.3 - -letting var2 be {{}, {false, true}, {true}} -$ Visualisation for var2 -$ -$ _ T -$ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_3_3-solution000014.solution b/tests/exhaustive/autogen/gen02/expected/model_3_3-solution000014.solution deleted file mode 100644 index 371f28aab7..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_3_3-solution000014.solution +++ /dev/null @@ -1,8 +0,0 @@ -language Essence 1.3 - -letting var2 be {{false}, {false, true}, {true}} -$ Visualisation for var2 -$ _ -$ _ T -$ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_3_3-solution000015.solution b/tests/exhaustive/autogen/gen02/expected/model_3_3-solution000015.solution deleted file mode 100644 index 35cfa328e8..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_3_3-solution000015.solution +++ /dev/null @@ -1,9 +0,0 @@ -language Essence 1.3 - -letting var2 be {{}, {false}, {false, true}, {true}} -$ Visualisation for var2 -$ -$ _ -$ _ T -$ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_3_3.eprime b/tests/exhaustive/autogen/gen02/expected/model_3_3.eprime deleted file mode 100644 index 84b872dd38..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_3_3.eprime +++ /dev/null @@ -1,46 +0,0 @@ -language ESSENCE' 1.0 - -find var2_ExplicitVarSizeWithFlagsR5_Flags: matrix indexed by [int(1..4)] of bool -find var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Marker: matrix indexed by [int(1..4)] of int(0..2) -find var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Values: - matrix indexed by [int(1..4), int(1..2)] of bool -branching on - [var2_ExplicitVarSizeWithFlagsR5_Flags, var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Marker, - var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Values] -such that - or([var2_ExplicitVarSizeWithFlagsR5_Flags[q13] /\ - sum([toInt(q14 <= var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Marker[q13]) - | q14 : int(1..2)]) - >= -7 - | q13 : int(1..4)]), - and([var2_ExplicitVarSizeWithFlagsR5_Flags[q2 + 1] -> - flatten([[var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Marker[q2]; int(1)], - flatten([[-toInt(var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Values[q2, q10]); - int(1)] - | q10 : int(1..2)]); - int(1..2)]) - - var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Marker[q3] = 0 /\ - and([var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Values[q3, q12] = false - | q12 : int(1..2)]) - | q3 : int(1..4)]), - and([var2_ExplicitVarSizeWithFlagsR5_Flags[q4 + 1] -> var2_ExplicitVarSizeWithFlagsR5_Flags[q4] | q4 : int(1..3)]), - and([var2_ExplicitVarSizeWithFlagsR5_Flags[q6] -> - (2 <= var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Marker[q6] -> - -toInt(var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Values[q6, 1]) < - -toInt(var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Values[q6, 2])) - | q6 : int(1..4)]), - and([var2_ExplicitVarSizeWithFlagsR5_Flags[q6] -> - and([q8 > var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Marker[q6] -> - var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Values[q6, q8] = false - | q8 : int(1..2)]) - | q6 : int(1..4)]) - diff --git a/tests/exhaustive/autogen/gen02/expected/model_3_4-solution000001.solution b/tests/exhaustive/autogen/gen02/expected/model_3_4-solution000001.solution deleted file mode 100644 index 19d999ca82..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_3_4-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting var2 be {{}} diff --git a/tests/exhaustive/autogen/gen02/expected/model_3_4-solution000002.solution b/tests/exhaustive/autogen/gen02/expected/model_3_4-solution000002.solution deleted file mode 100644 index 937293310f..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_3_4-solution000002.solution +++ /dev/null @@ -1,6 +0,0 @@ -language Essence 1.3 - -letting var2 be {{false}} -$ Visualisation for var2 -$ _ - diff --git a/tests/exhaustive/autogen/gen02/expected/model_3_4-solution000003.solution b/tests/exhaustive/autogen/gen02/expected/model_3_4-solution000003.solution deleted file mode 100644 index 5a187652fa..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_3_4-solution000003.solution +++ /dev/null @@ -1,6 +0,0 @@ -language Essence 1.3 - -letting var2 be {{true}} -$ Visualisation for var2 -$ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_3_4-solution000004.solution b/tests/exhaustive/autogen/gen02/expected/model_3_4-solution000004.solution deleted file mode 100644 index 0678d41bf8..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_3_4-solution000004.solution +++ /dev/null @@ -1,6 +0,0 @@ -language Essence 1.3 - -letting var2 be {{false, true}} -$ Visualisation for var2 -$ _ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_3_4-solution000005.solution b/tests/exhaustive/autogen/gen02/expected/model_3_4-solution000005.solution deleted file mode 100644 index 73f1bfe1ac..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_3_4-solution000005.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting var2 be {{}, {false}} -$ Visualisation for var2 -$ -$ _ - diff --git a/tests/exhaustive/autogen/gen02/expected/model_3_4-solution000006.solution b/tests/exhaustive/autogen/gen02/expected/model_3_4-solution000006.solution deleted file mode 100644 index d4c4a238b9..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_3_4-solution000006.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting var2 be {{}, {true}} -$ Visualisation for var2 -$ -$ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_3_4-solution000007.solution b/tests/exhaustive/autogen/gen02/expected/model_3_4-solution000007.solution deleted file mode 100644 index 2b6a8959da..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_3_4-solution000007.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting var2 be {{false}, {true}} -$ Visualisation for var2 -$ _ -$ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_3_4-solution000008.solution b/tests/exhaustive/autogen/gen02/expected/model_3_4-solution000008.solution deleted file mode 100644 index 9c15a8e4e1..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_3_4-solution000008.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting var2 be {{}, {false, true}} -$ Visualisation for var2 -$ -$ _ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_3_4-solution000009.solution b/tests/exhaustive/autogen/gen02/expected/model_3_4-solution000009.solution deleted file mode 100644 index b2e98e56a6..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_3_4-solution000009.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting var2 be {{false}, {false, true}} -$ Visualisation for var2 -$ _ -$ _ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_3_4-solution000010.solution b/tests/exhaustive/autogen/gen02/expected/model_3_4-solution000010.solution deleted file mode 100644 index 4fc309134f..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_3_4-solution000010.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting var2 be {{false, true}, {true}} -$ Visualisation for var2 -$ _ T -$ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_3_4-solution000011.solution b/tests/exhaustive/autogen/gen02/expected/model_3_4-solution000011.solution deleted file mode 100644 index 70d0f91f38..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_3_4-solution000011.solution +++ /dev/null @@ -1,8 +0,0 @@ -language Essence 1.3 - -letting var2 be {{}, {false}, {true}} -$ Visualisation for var2 -$ -$ _ -$ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_3_4-solution000012.solution b/tests/exhaustive/autogen/gen02/expected/model_3_4-solution000012.solution deleted file mode 100644 index ebc3fe4182..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_3_4-solution000012.solution +++ /dev/null @@ -1,8 +0,0 @@ -language Essence 1.3 - -letting var2 be {{}, {false}, {false, true}} -$ Visualisation for var2 -$ -$ _ -$ _ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_3_4-solution000013.solution b/tests/exhaustive/autogen/gen02/expected/model_3_4-solution000013.solution deleted file mode 100644 index fa4340a533..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_3_4-solution000013.solution +++ /dev/null @@ -1,8 +0,0 @@ -language Essence 1.3 - -letting var2 be {{}, {false, true}, {true}} -$ Visualisation for var2 -$ -$ _ T -$ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_3_4-solution000014.solution b/tests/exhaustive/autogen/gen02/expected/model_3_4-solution000014.solution deleted file mode 100644 index 371f28aab7..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_3_4-solution000014.solution +++ /dev/null @@ -1,8 +0,0 @@ -language Essence 1.3 - -letting var2 be {{false}, {false, true}, {true}} -$ Visualisation for var2 -$ _ -$ _ T -$ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_3_4-solution000015.solution b/tests/exhaustive/autogen/gen02/expected/model_3_4-solution000015.solution deleted file mode 100644 index 35cfa328e8..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_3_4-solution000015.solution +++ /dev/null @@ -1,9 +0,0 @@ -language Essence 1.3 - -letting var2 be {{}, {false}, {false, true}, {true}} -$ Visualisation for var2 -$ -$ _ -$ _ T -$ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_3_4.eprime b/tests/exhaustive/autogen/gen02/expected/model_3_4.eprime deleted file mode 100644 index 4cd49f885e..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_3_4.eprime +++ /dev/null @@ -1,126 +0,0 @@ -language ESSENCE' 1.0 - -find var2_ExplicitVarSizeWithFlagsR5_Flags: matrix indexed by [int(1..4)] of bool -find var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Marker: matrix indexed by [int(1..4)] of int(0..2) -find var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Values: - matrix indexed by [int(1..4), int(1..2)] of bool -find var2_ExplicitVarSizeWithFlagsR4_Flags: matrix indexed by [int(1..4)] of bool -find var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Flags: - matrix indexed by [int(1..4), int(1..2)] of bool -find var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Values: - matrix indexed by [int(1..4), int(1..2)] of bool -branching on - [var2_ExplicitVarSizeWithFlagsR4_Flags, var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Flags, - var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Values, var2_ExplicitVarSizeWithFlagsR5_Flags, - var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Marker, - var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Values] -such that - or([var2_ExplicitVarSizeWithFlagsR5_Flags[q51] /\ - sum([toInt(q52 <= var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Marker[q51]) - | q52 : int(1..2)]) - >= -7 - | q51 : int(1..4)]), - and([var2_ExplicitVarSizeWithFlagsR5_Flags[q2 + 1] -> - flatten([[var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Marker[q2]; int(1)], - flatten([[-toInt(var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Values[q2, q10]); - int(1)] - | q10 : int(1..2)]); - int(1..2)]) - - var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Marker[q3] = 0 /\ - and([var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Values[q3, q12] = false - | q12 : int(1..2)]) - | q3 : int(1..4)]), - and([var2_ExplicitVarSizeWithFlagsR5_Flags[q4 + 1] -> var2_ExplicitVarSizeWithFlagsR5_Flags[q4] | q4 : int(1..3)]), - and([var2_ExplicitVarSizeWithFlagsR5_Flags[q6] -> - (2 <= var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Marker[q6] -> - -toInt(var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Values[q6, 1]) < - -toInt(var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Values[q6, 2])) - | q6 : int(1..4)]), - and([var2_ExplicitVarSizeWithFlagsR5_Flags[q6] -> - and([q8 > var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Marker[q6] -> - var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Values[q6, q8] = false - | q8 : int(1..2)]) - | q6 : int(1..4)]), - and([var2_ExplicitVarSizeWithFlagsR4_Flags[q13 + 1] -> - flatten([flatten([[-toInt(var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Flags[q13, q23]); - int(1)], - [-toInt(var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Values[q13, q23]); - int(1)]; - int(1..2)]) - | q23 : int(1..2)]) - - and([var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Flags[q14, q25] = false - | q25 : int(1..2)]) - /\ - and([var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Values[q14, q26] = false - | q26 : int(1..2)]) - | q14 : int(1..4)]), - and([var2_ExplicitVarSizeWithFlagsR4_Flags[q15 + 1] -> var2_ExplicitVarSizeWithFlagsR4_Flags[q15] - | q15 : int(1..3)]), - and([var2_ExplicitVarSizeWithFlagsR4_Flags[q17] -> - (var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Flags[q17, 2] -> - -toInt(var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Values[q17, 1]) < - -toInt(var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Values[q17, 2])) - | q17 : int(1..4)]), - and([var2_ExplicitVarSizeWithFlagsR4_Flags[q17] -> - and([var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Flags[q17, q19] = false -> - var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Values[q17, q19] = false - | q19 : int(1..2)]) - | q17 : int(1..4)]), - and([var2_ExplicitVarSizeWithFlagsR4_Flags[q17] -> - (var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Flags[q17, 2] -> - var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Flags[q17, 1]) - | q17 : int(1..4)]), - and([var2_ExplicitVarSizeWithFlagsR4_Flags[q28] -> - or([var2_ExplicitVarSizeWithFlagsR5_Flags[q30] /\ - (and([q32 <= var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Marker[q30] -> - or([var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Flags[q28, q34] /\ - var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Values[q28, q34] = - var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Values[q30, q32] - | q34 : int(1..2)]) - | q32 : int(1..2)]) - /\ - and([var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Flags[q28, q36] -> - or([q38 <= var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Marker[q30] /\ - var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Values[q30, q38] = - var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Values[q28, q36] - | q38 : int(1..2)]) - | q36 : int(1..2)])) - | q30 : int(1..4)]) - | q28 : int(1..4)]), - and([var2_ExplicitVarSizeWithFlagsR5_Flags[q40] -> - or([var2_ExplicitVarSizeWithFlagsR4_Flags[q42] /\ - (and([var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Flags[q42, q44] -> - or([q46 <= var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Marker[q40] /\ - var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Values[q40, q46] = - var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Values[q42, q44] - | q46 : int(1..2)]) - | q44 : int(1..2)]) - /\ - and([q48 <= var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Marker[q40] -> - or([var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Flags[q42, q50] /\ - var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Values[q42, q50] = - var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Values[q40, q48] - | q50 : int(1..2)]) - | q48 : int(1..2)])) - | q42 : int(1..4)]) - | q40 : int(1..4)]) - diff --git a/tests/exhaustive/autogen/gen02/expected/model_4_1-solution000001.solution b/tests/exhaustive/autogen/gen02/expected/model_4_1-solution000001.solution deleted file mode 100644 index 19d999ca82..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_4_1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting var2 be {{}} diff --git a/tests/exhaustive/autogen/gen02/expected/model_4_1-solution000002.solution b/tests/exhaustive/autogen/gen02/expected/model_4_1-solution000002.solution deleted file mode 100644 index 937293310f..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_4_1-solution000002.solution +++ /dev/null @@ -1,6 +0,0 @@ -language Essence 1.3 - -letting var2 be {{false}} -$ Visualisation for var2 -$ _ - diff --git a/tests/exhaustive/autogen/gen02/expected/model_4_1-solution000003.solution b/tests/exhaustive/autogen/gen02/expected/model_4_1-solution000003.solution deleted file mode 100644 index 5a187652fa..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_4_1-solution000003.solution +++ /dev/null @@ -1,6 +0,0 @@ -language Essence 1.3 - -letting var2 be {{true}} -$ Visualisation for var2 -$ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_4_1-solution000004.solution b/tests/exhaustive/autogen/gen02/expected/model_4_1-solution000004.solution deleted file mode 100644 index 0678d41bf8..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_4_1-solution000004.solution +++ /dev/null @@ -1,6 +0,0 @@ -language Essence 1.3 - -letting var2 be {{false, true}} -$ Visualisation for var2 -$ _ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_4_1-solution000005.solution b/tests/exhaustive/autogen/gen02/expected/model_4_1-solution000005.solution deleted file mode 100644 index 73f1bfe1ac..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_4_1-solution000005.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting var2 be {{}, {false}} -$ Visualisation for var2 -$ -$ _ - diff --git a/tests/exhaustive/autogen/gen02/expected/model_4_1-solution000006.solution b/tests/exhaustive/autogen/gen02/expected/model_4_1-solution000006.solution deleted file mode 100644 index d4c4a238b9..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_4_1-solution000006.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting var2 be {{}, {true}} -$ Visualisation for var2 -$ -$ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_4_1-solution000007.solution b/tests/exhaustive/autogen/gen02/expected/model_4_1-solution000007.solution deleted file mode 100644 index 9c15a8e4e1..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_4_1-solution000007.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting var2 be {{}, {false, true}} -$ Visualisation for var2 -$ -$ _ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_4_1-solution000008.solution b/tests/exhaustive/autogen/gen02/expected/model_4_1-solution000008.solution deleted file mode 100644 index 2b6a8959da..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_4_1-solution000008.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting var2 be {{false}, {true}} -$ Visualisation for var2 -$ _ -$ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_4_1-solution000009.solution b/tests/exhaustive/autogen/gen02/expected/model_4_1-solution000009.solution deleted file mode 100644 index b2e98e56a6..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_4_1-solution000009.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting var2 be {{false}, {false, true}} -$ Visualisation for var2 -$ _ -$ _ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_4_1-solution000010.solution b/tests/exhaustive/autogen/gen02/expected/model_4_1-solution000010.solution deleted file mode 100644 index 4fc309134f..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_4_1-solution000010.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting var2 be {{false, true}, {true}} -$ Visualisation for var2 -$ _ T -$ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_4_1-solution000011.solution b/tests/exhaustive/autogen/gen02/expected/model_4_1-solution000011.solution deleted file mode 100644 index 70d0f91f38..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_4_1-solution000011.solution +++ /dev/null @@ -1,8 +0,0 @@ -language Essence 1.3 - -letting var2 be {{}, {false}, {true}} -$ Visualisation for var2 -$ -$ _ -$ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_4_1-solution000012.solution b/tests/exhaustive/autogen/gen02/expected/model_4_1-solution000012.solution deleted file mode 100644 index ebc3fe4182..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_4_1-solution000012.solution +++ /dev/null @@ -1,8 +0,0 @@ -language Essence 1.3 - -letting var2 be {{}, {false}, {false, true}} -$ Visualisation for var2 -$ -$ _ -$ _ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_4_1-solution000013.solution b/tests/exhaustive/autogen/gen02/expected/model_4_1-solution000013.solution deleted file mode 100644 index fa4340a533..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_4_1-solution000013.solution +++ /dev/null @@ -1,8 +0,0 @@ -language Essence 1.3 - -letting var2 be {{}, {false, true}, {true}} -$ Visualisation for var2 -$ -$ _ T -$ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_4_1-solution000014.solution b/tests/exhaustive/autogen/gen02/expected/model_4_1-solution000014.solution deleted file mode 100644 index 371f28aab7..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_4_1-solution000014.solution +++ /dev/null @@ -1,8 +0,0 @@ -language Essence 1.3 - -letting var2 be {{false}, {false, true}, {true}} -$ Visualisation for var2 -$ _ -$ _ T -$ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_4_1-solution000015.solution b/tests/exhaustive/autogen/gen02/expected/model_4_1-solution000015.solution deleted file mode 100644 index 35cfa328e8..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_4_1-solution000015.solution +++ /dev/null @@ -1,9 +0,0 @@ -language Essence 1.3 - -letting var2 be {{}, {false}, {false, true}, {true}} -$ Visualisation for var2 -$ -$ _ -$ _ T -$ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_4_1.eprime b/tests/exhaustive/autogen/gen02/expected/model_4_1.eprime deleted file mode 100644 index bf3de42864..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_4_1.eprime +++ /dev/null @@ -1,122 +0,0 @@ -language ESSENCE' 1.0 - -find var2_ExplicitVarSizeWithFlagsR4_Flags: matrix indexed by [int(1..4)] of bool -find var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Flags: - matrix indexed by [int(1..4), int(1..2)] of bool -find var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Values: - matrix indexed by [int(1..4), int(1..2)] of bool -find var2_ExplicitVarSizeWithMarkerR5_Marker: int(0..4) -find var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker: - matrix indexed by [int(1..4)] of int(0..2) -find var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values: - matrix indexed by [int(1..4), int(1..2)] of bool -branching on - [var2_ExplicitVarSizeWithMarkerR5_Marker, var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker, - var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values, var2_ExplicitVarSizeWithFlagsR4_Flags, - var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Flags, - var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Values] -such that - or([var2_ExplicitVarSizeWithFlagsR4_Flags[q49] /\ - sum([toInt(var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Flags[q49, q50]) | q50 : int(1..2)]) - >= -7 - | q49 : int(1..4)]), - and([var2_ExplicitVarSizeWithFlagsR4_Flags[q2 + 1] -> - flatten([flatten([[-toInt(var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Flags[q2, q12]); - int(1)], - [-toInt(var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Values[q2, q12]); - int(1)]; - int(1..2)]) - | q12 : int(1..2)]) - - and([var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Flags[q3, q14] = false | q14 : int(1..2)]) - /\ - and([var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Values[q3, q15] = false - | q15 : int(1..2)]) - | q3 : int(1..4)]), - and([var2_ExplicitVarSizeWithFlagsR4_Flags[q4 + 1] -> var2_ExplicitVarSizeWithFlagsR4_Flags[q4] | q4 : int(1..3)]), - and([var2_ExplicitVarSizeWithFlagsR4_Flags[q6] -> - (var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Flags[q6, 2] -> - -toInt(var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Values[q6, 1]) < - -toInt(var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Values[q6, 2])) - | q6 : int(1..4)]), - and([var2_ExplicitVarSizeWithFlagsR4_Flags[q6] -> - and([var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Flags[q6, q8] = false -> - var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Values[q6, q8] = false - | q8 : int(1..2)]) - | q6 : int(1..4)]), - and([var2_ExplicitVarSizeWithFlagsR4_Flags[q6] -> - (var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Flags[q6, 2] -> - var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Flags[q6, 1]) - | q6 : int(1..4)]), - and([q16 + 1 <= var2_ExplicitVarSizeWithMarkerR5_Marker -> - flatten([[var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q16]; int(1)], - flatten([[-toInt(var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q16, q22]); - int(1)] - | q22 : int(1..2)]); - int(1..2)]) - var2_ExplicitVarSizeWithMarkerR5_Marker -> - var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q17] = 0 /\ - and([var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q17, q24] = false - | q24 : int(1..2)]) - | q17 : int(1..4)]), - and([q18 <= var2_ExplicitVarSizeWithMarkerR5_Marker -> - (2 <= var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q18] -> - -toInt(var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q18, 1]) < - -toInt(var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q18, 2])) - | q18 : int(1..4)]), - and([q18 <= var2_ExplicitVarSizeWithMarkerR5_Marker -> - and([q20 > var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q18] -> - var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q18, q20] = false - | q20 : int(1..2)]) - | q18 : int(1..4)]), - and([q26 <= var2_ExplicitVarSizeWithMarkerR5_Marker -> - or([var2_ExplicitVarSizeWithFlagsR4_Flags[q28] /\ - (and([var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Flags[q28, q30] -> - or([q32 <= var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q26] /\ - var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q26, q32] = - var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Values[q28, q30] - | q32 : int(1..2)]) - | q30 : int(1..2)]) - /\ - and([q34 <= var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q26] -> - or([var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Flags[q28, q36] /\ - var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Values[q28, q36] = - var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q26, q34] - | q36 : int(1..2)]) - | q34 : int(1..2)])) - | q28 : int(1..4)]) - | q26 : int(1..4)]), - and([var2_ExplicitVarSizeWithFlagsR4_Flags[q38] -> - or([q40 <= var2_ExplicitVarSizeWithMarkerR5_Marker /\ - (and([q42 <= var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q40] -> - or([var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Flags[q38, q44] /\ - var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Values[q38, q44] = - var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q40, q42] - | q44 : int(1..2)]) - | q42 : int(1..2)]) - /\ - and([var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Flags[q38, q46] -> - or([q48 <= var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q40] /\ - var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q40, q48] = - var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Values[q38, q46] - | q48 : int(1..2)]) - | q46 : int(1..2)])) - | q40 : int(1..4)]) - | q38 : int(1..4)]) - diff --git a/tests/exhaustive/autogen/gen02/expected/model_4_2-solution000001.solution b/tests/exhaustive/autogen/gen02/expected/model_4_2-solution000001.solution deleted file mode 100644 index 19d999ca82..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_4_2-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting var2 be {{}} diff --git a/tests/exhaustive/autogen/gen02/expected/model_4_2-solution000002.solution b/tests/exhaustive/autogen/gen02/expected/model_4_2-solution000002.solution deleted file mode 100644 index 937293310f..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_4_2-solution000002.solution +++ /dev/null @@ -1,6 +0,0 @@ -language Essence 1.3 - -letting var2 be {{false}} -$ Visualisation for var2 -$ _ - diff --git a/tests/exhaustive/autogen/gen02/expected/model_4_2-solution000003.solution b/tests/exhaustive/autogen/gen02/expected/model_4_2-solution000003.solution deleted file mode 100644 index 5a187652fa..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_4_2-solution000003.solution +++ /dev/null @@ -1,6 +0,0 @@ -language Essence 1.3 - -letting var2 be {{true}} -$ Visualisation for var2 -$ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_4_2-solution000004.solution b/tests/exhaustive/autogen/gen02/expected/model_4_2-solution000004.solution deleted file mode 100644 index 0678d41bf8..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_4_2-solution000004.solution +++ /dev/null @@ -1,6 +0,0 @@ -language Essence 1.3 - -letting var2 be {{false, true}} -$ Visualisation for var2 -$ _ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_4_2-solution000005.solution b/tests/exhaustive/autogen/gen02/expected/model_4_2-solution000005.solution deleted file mode 100644 index 73f1bfe1ac..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_4_2-solution000005.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting var2 be {{}, {false}} -$ Visualisation for var2 -$ -$ _ - diff --git a/tests/exhaustive/autogen/gen02/expected/model_4_2-solution000006.solution b/tests/exhaustive/autogen/gen02/expected/model_4_2-solution000006.solution deleted file mode 100644 index d4c4a238b9..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_4_2-solution000006.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting var2 be {{}, {true}} -$ Visualisation for var2 -$ -$ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_4_2-solution000007.solution b/tests/exhaustive/autogen/gen02/expected/model_4_2-solution000007.solution deleted file mode 100644 index 2b6a8959da..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_4_2-solution000007.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting var2 be {{false}, {true}} -$ Visualisation for var2 -$ _ -$ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_4_2-solution000008.solution b/tests/exhaustive/autogen/gen02/expected/model_4_2-solution000008.solution deleted file mode 100644 index 9c15a8e4e1..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_4_2-solution000008.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting var2 be {{}, {false, true}} -$ Visualisation for var2 -$ -$ _ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_4_2-solution000009.solution b/tests/exhaustive/autogen/gen02/expected/model_4_2-solution000009.solution deleted file mode 100644 index b2e98e56a6..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_4_2-solution000009.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting var2 be {{false}, {false, true}} -$ Visualisation for var2 -$ _ -$ _ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_4_2-solution000010.solution b/tests/exhaustive/autogen/gen02/expected/model_4_2-solution000010.solution deleted file mode 100644 index 4fc309134f..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_4_2-solution000010.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting var2 be {{false, true}, {true}} -$ Visualisation for var2 -$ _ T -$ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_4_2-solution000011.solution b/tests/exhaustive/autogen/gen02/expected/model_4_2-solution000011.solution deleted file mode 100644 index 70d0f91f38..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_4_2-solution000011.solution +++ /dev/null @@ -1,8 +0,0 @@ -language Essence 1.3 - -letting var2 be {{}, {false}, {true}} -$ Visualisation for var2 -$ -$ _ -$ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_4_2-solution000012.solution b/tests/exhaustive/autogen/gen02/expected/model_4_2-solution000012.solution deleted file mode 100644 index ebc3fe4182..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_4_2-solution000012.solution +++ /dev/null @@ -1,8 +0,0 @@ -language Essence 1.3 - -letting var2 be {{}, {false}, {false, true}} -$ Visualisation for var2 -$ -$ _ -$ _ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_4_2-solution000013.solution b/tests/exhaustive/autogen/gen02/expected/model_4_2-solution000013.solution deleted file mode 100644 index fa4340a533..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_4_2-solution000013.solution +++ /dev/null @@ -1,8 +0,0 @@ -language Essence 1.3 - -letting var2 be {{}, {false, true}, {true}} -$ Visualisation for var2 -$ -$ _ T -$ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_4_2-solution000014.solution b/tests/exhaustive/autogen/gen02/expected/model_4_2-solution000014.solution deleted file mode 100644 index 371f28aab7..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_4_2-solution000014.solution +++ /dev/null @@ -1,8 +0,0 @@ -language Essence 1.3 - -letting var2 be {{false}, {false, true}, {true}} -$ Visualisation for var2 -$ _ -$ _ T -$ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_4_2-solution000015.solution b/tests/exhaustive/autogen/gen02/expected/model_4_2-solution000015.solution deleted file mode 100644 index 35cfa328e8..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_4_2-solution000015.solution +++ /dev/null @@ -1,9 +0,0 @@ -language Essence 1.3 - -letting var2 be {{}, {false}, {false, true}, {true}} -$ Visualisation for var2 -$ -$ _ -$ _ T -$ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_4_2.eprime b/tests/exhaustive/autogen/gen02/expected/model_4_2.eprime deleted file mode 100644 index c50ffb2189..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_4_2.eprime +++ /dev/null @@ -1,119 +0,0 @@ -language ESSENCE' 1.0 - -find var2_ExplicitVarSizeWithFlagsR4_Flags: matrix indexed by [int(1..4)] of bool -find var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Flags: - matrix indexed by [int(1..4), int(1..2)] of bool -find var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Values: - matrix indexed by [int(1..4), int(1..2)] of bool -find var2_ExplicitVarSizeWithMarkerR4_Marker: int(0..4) -find var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Flags: - matrix indexed by [int(1..4), int(1..2)] of bool -find var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Values: - matrix indexed by [int(1..4), int(1..2)] of bool -branching on - [var2_ExplicitVarSizeWithMarkerR4_Marker, var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Flags, - var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Values, var2_ExplicitVarSizeWithFlagsR4_Flags, - var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Flags, - var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Values] -such that - or([var2_ExplicitVarSizeWithFlagsR4_Flags[q44] /\ - sum([toInt(var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Flags[q44, q45]) | q45 : int(1..2)]) - >= -7 - | q44 : int(1..4)]), - and([var2_ExplicitVarSizeWithFlagsR4_Flags[q2 + 1] -> - flatten([flatten([[-toInt(var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Flags[q2, q12]); - int(1)], - [-toInt(var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Values[q2, q12]); - int(1)]; - int(1..2)]) - | q12 : int(1..2)]) - - and([var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Flags[q3, q14] = false | q14 : int(1..2)]) - /\ - and([var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Values[q3, q15] = false - | q15 : int(1..2)]) - | q3 : int(1..4)]), - and([var2_ExplicitVarSizeWithFlagsR4_Flags[q4 + 1] -> var2_ExplicitVarSizeWithFlagsR4_Flags[q4] | q4 : int(1..3)]), - and([var2_ExplicitVarSizeWithFlagsR4_Flags[q6] -> - (var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Flags[q6, 2] -> - -toInt(var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Values[q6, 1]) < - -toInt(var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Values[q6, 2])) - | q6 : int(1..4)]), - and([var2_ExplicitVarSizeWithFlagsR4_Flags[q6] -> - and([var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Flags[q6, q8] = false -> - var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Values[q6, q8] = false - | q8 : int(1..2)]) - | q6 : int(1..4)]), - and([var2_ExplicitVarSizeWithFlagsR4_Flags[q6] -> - (var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Flags[q6, 2] -> - var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Flags[q6, 1]) - | q6 : int(1..4)]), - and([q16 + 1 <= var2_ExplicitVarSizeWithMarkerR4_Marker -> - flatten([flatten([[-toInt(var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Flags[q16, q24]); - int(1)], - [-toInt(var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Values[q16, q24]); - int(1)]; - int(1..2)]) - | q24 : int(1..2)]) - var2_ExplicitVarSizeWithMarkerR4_Marker -> - and([var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Flags[q17, q26] = false - | q26 : int(1..2)]) - /\ - and([var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Values[q17, q27] = false - | q27 : int(1..2)]) - | q17 : int(1..4)]), - and([q18 <= var2_ExplicitVarSizeWithMarkerR4_Marker -> - (var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Flags[q18, 2] -> - -toInt(var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Values[q18, 1]) < - -toInt(var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Values[q18, 2])) - | q18 : int(1..4)]), - and([q18 <= var2_ExplicitVarSizeWithMarkerR4_Marker -> - and([var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Flags[q18, q20] = false -> - var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Values[q18, q20] = false - | q20 : int(1..2)]) - | q18 : int(1..4)]), - and([q18 <= var2_ExplicitVarSizeWithMarkerR4_Marker -> - (var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Flags[q18, 2] -> - var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Flags[q18, 1]) - | q18 : int(1..4)]), - and([q29 <= var2_ExplicitVarSizeWithMarkerR4_Marker -> - or([var2_ExplicitVarSizeWithFlagsR4_Flags[q31] /\ - (and([var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Flags[q31, q32] = - var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Flags[q29, q32] - | q32 : int(1..2)]) - /\ - and([var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Values[q31, q34] = - var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Values[q29, q34] - | q34 : int(1..2)])) - | q31 : int(1..4)]) - | q29 : int(1..4)]), - and([var2_ExplicitVarSizeWithFlagsR4_Flags[q37] -> - or([q39 <= var2_ExplicitVarSizeWithMarkerR4_Marker /\ - (and([var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Flags[q39, q40] = - var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Flags[q37, q40] - | q40 : int(1..2)]) - /\ - and([var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Values[q39, q42] = - var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Values[q37, q42] - | q42 : int(1..2)])) - | q39 : int(1..4)]) - | q37 : int(1..4)]) - diff --git a/tests/exhaustive/autogen/gen02/expected/model_4_3-solution000001.solution b/tests/exhaustive/autogen/gen02/expected/model_4_3-solution000001.solution deleted file mode 100644 index 19d999ca82..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_4_3-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting var2 be {{}} diff --git a/tests/exhaustive/autogen/gen02/expected/model_4_3-solution000002.solution b/tests/exhaustive/autogen/gen02/expected/model_4_3-solution000002.solution deleted file mode 100644 index 937293310f..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_4_3-solution000002.solution +++ /dev/null @@ -1,6 +0,0 @@ -language Essence 1.3 - -letting var2 be {{false}} -$ Visualisation for var2 -$ _ - diff --git a/tests/exhaustive/autogen/gen02/expected/model_4_3-solution000003.solution b/tests/exhaustive/autogen/gen02/expected/model_4_3-solution000003.solution deleted file mode 100644 index 5a187652fa..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_4_3-solution000003.solution +++ /dev/null @@ -1,6 +0,0 @@ -language Essence 1.3 - -letting var2 be {{true}} -$ Visualisation for var2 -$ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_4_3-solution000004.solution b/tests/exhaustive/autogen/gen02/expected/model_4_3-solution000004.solution deleted file mode 100644 index 0678d41bf8..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_4_3-solution000004.solution +++ /dev/null @@ -1,6 +0,0 @@ -language Essence 1.3 - -letting var2 be {{false, true}} -$ Visualisation for var2 -$ _ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_4_3-solution000005.solution b/tests/exhaustive/autogen/gen02/expected/model_4_3-solution000005.solution deleted file mode 100644 index 73f1bfe1ac..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_4_3-solution000005.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting var2 be {{}, {false}} -$ Visualisation for var2 -$ -$ _ - diff --git a/tests/exhaustive/autogen/gen02/expected/model_4_3-solution000006.solution b/tests/exhaustive/autogen/gen02/expected/model_4_3-solution000006.solution deleted file mode 100644 index d4c4a238b9..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_4_3-solution000006.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting var2 be {{}, {true}} -$ Visualisation for var2 -$ -$ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_4_3-solution000007.solution b/tests/exhaustive/autogen/gen02/expected/model_4_3-solution000007.solution deleted file mode 100644 index 9c15a8e4e1..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_4_3-solution000007.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting var2 be {{}, {false, true}} -$ Visualisation for var2 -$ -$ _ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_4_3-solution000008.solution b/tests/exhaustive/autogen/gen02/expected/model_4_3-solution000008.solution deleted file mode 100644 index 2b6a8959da..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_4_3-solution000008.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting var2 be {{false}, {true}} -$ Visualisation for var2 -$ _ -$ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_4_3-solution000009.solution b/tests/exhaustive/autogen/gen02/expected/model_4_3-solution000009.solution deleted file mode 100644 index b2e98e56a6..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_4_3-solution000009.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting var2 be {{false}, {false, true}} -$ Visualisation for var2 -$ _ -$ _ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_4_3-solution000010.solution b/tests/exhaustive/autogen/gen02/expected/model_4_3-solution000010.solution deleted file mode 100644 index 4fc309134f..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_4_3-solution000010.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting var2 be {{false, true}, {true}} -$ Visualisation for var2 -$ _ T -$ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_4_3-solution000011.solution b/tests/exhaustive/autogen/gen02/expected/model_4_3-solution000011.solution deleted file mode 100644 index 70d0f91f38..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_4_3-solution000011.solution +++ /dev/null @@ -1,8 +0,0 @@ -language Essence 1.3 - -letting var2 be {{}, {false}, {true}} -$ Visualisation for var2 -$ -$ _ -$ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_4_3-solution000012.solution b/tests/exhaustive/autogen/gen02/expected/model_4_3-solution000012.solution deleted file mode 100644 index ebc3fe4182..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_4_3-solution000012.solution +++ /dev/null @@ -1,8 +0,0 @@ -language Essence 1.3 - -letting var2 be {{}, {false}, {false, true}} -$ Visualisation for var2 -$ -$ _ -$ _ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_4_3-solution000013.solution b/tests/exhaustive/autogen/gen02/expected/model_4_3-solution000013.solution deleted file mode 100644 index fa4340a533..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_4_3-solution000013.solution +++ /dev/null @@ -1,8 +0,0 @@ -language Essence 1.3 - -letting var2 be {{}, {false, true}, {true}} -$ Visualisation for var2 -$ -$ _ T -$ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_4_3-solution000014.solution b/tests/exhaustive/autogen/gen02/expected/model_4_3-solution000014.solution deleted file mode 100644 index 371f28aab7..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_4_3-solution000014.solution +++ /dev/null @@ -1,8 +0,0 @@ -language Essence 1.3 - -letting var2 be {{false}, {false, true}, {true}} -$ Visualisation for var2 -$ _ -$ _ T -$ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_4_3-solution000015.solution b/tests/exhaustive/autogen/gen02/expected/model_4_3-solution000015.solution deleted file mode 100644 index 35cfa328e8..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_4_3-solution000015.solution +++ /dev/null @@ -1,9 +0,0 @@ -language Essence 1.3 - -letting var2 be {{}, {false}, {false, true}, {true}} -$ Visualisation for var2 -$ -$ _ -$ _ T -$ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_4_3.eprime b/tests/exhaustive/autogen/gen02/expected/model_4_3.eprime deleted file mode 100644 index 93cd681dfb..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_4_3.eprime +++ /dev/null @@ -1,123 +0,0 @@ -language ESSENCE' 1.0 - -find var2_ExplicitVarSizeWithFlagsR4_Flags: matrix indexed by [int(1..4)] of bool -find var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Flags: - matrix indexed by [int(1..4), int(1..2)] of bool -find var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Values: - matrix indexed by [int(1..4), int(1..2)] of bool -find var2_ExplicitVarSizeWithFlagsR5_Flags: matrix indexed by [int(1..4)] of bool -find var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Marker: matrix indexed by [int(1..4)] of int(0..2) -find var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Values: - matrix indexed by [int(1..4), int(1..2)] of bool -branching on - [var2_ExplicitVarSizeWithFlagsR5_Flags, var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Marker, - var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Values, var2_ExplicitVarSizeWithFlagsR4_Flags, - var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Flags, - var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Values] -such that - or([var2_ExplicitVarSizeWithFlagsR4_Flags[q51] /\ - sum([toInt(var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Flags[q51, q52]) | q52 : int(1..2)]) - >= -7 - | q51 : int(1..4)]), - and([var2_ExplicitVarSizeWithFlagsR4_Flags[q2 + 1] -> - flatten([flatten([[-toInt(var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Flags[q2, q12]); - int(1)], - [-toInt(var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Values[q2, q12]); - int(1)]; - int(1..2)]) - | q12 : int(1..2)]) - - and([var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Flags[q3, q14] = false | q14 : int(1..2)]) - /\ - and([var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Values[q3, q15] = false - | q15 : int(1..2)]) - | q3 : int(1..4)]), - and([var2_ExplicitVarSizeWithFlagsR4_Flags[q4 + 1] -> var2_ExplicitVarSizeWithFlagsR4_Flags[q4] | q4 : int(1..3)]), - and([var2_ExplicitVarSizeWithFlagsR4_Flags[q6] -> - (var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Flags[q6, 2] -> - -toInt(var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Values[q6, 1]) < - -toInt(var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Values[q6, 2])) - | q6 : int(1..4)]), - and([var2_ExplicitVarSizeWithFlagsR4_Flags[q6] -> - and([var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Flags[q6, q8] = false -> - var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Values[q6, q8] = false - | q8 : int(1..2)]) - | q6 : int(1..4)]), - and([var2_ExplicitVarSizeWithFlagsR4_Flags[q6] -> - (var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Flags[q6, 2] -> - var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Flags[q6, 1]) - | q6 : int(1..4)]), - and([var2_ExplicitVarSizeWithFlagsR5_Flags[q16 + 1] -> - flatten([[var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Marker[q16]; int(1)], - flatten([[-toInt(var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Values[q16, q24]); - int(1)] - | q24 : int(1..2)]); - int(1..2)]) - - var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Marker[q17] = 0 /\ - and([var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Values[q17, q26] = false - | q26 : int(1..2)]) - | q17 : int(1..4)]), - and([var2_ExplicitVarSizeWithFlagsR5_Flags[q18 + 1] -> var2_ExplicitVarSizeWithFlagsR5_Flags[q18] - | q18 : int(1..3)]), - and([var2_ExplicitVarSizeWithFlagsR5_Flags[q20] -> - (2 <= var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Marker[q20] -> - -toInt(var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Values[q20, 1]) < - -toInt(var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Values[q20, 2])) - | q20 : int(1..4)]), - and([var2_ExplicitVarSizeWithFlagsR5_Flags[q20] -> - and([q22 > var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Marker[q20] -> - var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Values[q20, q22] = false - | q22 : int(1..2)]) - | q20 : int(1..4)]), - and([var2_ExplicitVarSizeWithFlagsR5_Flags[q28] -> - or([var2_ExplicitVarSizeWithFlagsR4_Flags[q30] /\ - (and([var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Flags[q30, q32] -> - or([q34 <= var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Marker[q28] /\ - var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Values[q28, q34] = - var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Values[q30, q32] - | q34 : int(1..2)]) - | q32 : int(1..2)]) - /\ - and([q36 <= var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Marker[q28] -> - or([var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Flags[q30, q38] /\ - var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Values[q30, q38] = - var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Values[q28, q36] - | q38 : int(1..2)]) - | q36 : int(1..2)])) - | q30 : int(1..4)]) - | q28 : int(1..4)]), - and([var2_ExplicitVarSizeWithFlagsR4_Flags[q40] -> - or([var2_ExplicitVarSizeWithFlagsR5_Flags[q42] /\ - (and([q44 <= var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Marker[q42] -> - or([var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Flags[q40, q46] /\ - var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Values[q40, q46] = - var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Values[q42, q44] - | q46 : int(1..2)]) - | q44 : int(1..2)]) - /\ - and([var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Flags[q40, q48] -> - or([q50 <= var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Marker[q42] /\ - var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Values[q42, q50] = - var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Values[q40, q48] - | q50 : int(1..2)]) - | q48 : int(1..2)])) - | q42 : int(1..4)]) - | q40 : int(1..4)]) - diff --git a/tests/exhaustive/autogen/gen02/expected/model_4_4-solution000001.solution b/tests/exhaustive/autogen/gen02/expected/model_4_4-solution000001.solution deleted file mode 100644 index 19d999ca82..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_4_4-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting var2 be {{}} diff --git a/tests/exhaustive/autogen/gen02/expected/model_4_4-solution000002.solution b/tests/exhaustive/autogen/gen02/expected/model_4_4-solution000002.solution deleted file mode 100644 index 937293310f..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_4_4-solution000002.solution +++ /dev/null @@ -1,6 +0,0 @@ -language Essence 1.3 - -letting var2 be {{false}} -$ Visualisation for var2 -$ _ - diff --git a/tests/exhaustive/autogen/gen02/expected/model_4_4-solution000003.solution b/tests/exhaustive/autogen/gen02/expected/model_4_4-solution000003.solution deleted file mode 100644 index 5a187652fa..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_4_4-solution000003.solution +++ /dev/null @@ -1,6 +0,0 @@ -language Essence 1.3 - -letting var2 be {{true}} -$ Visualisation for var2 -$ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_4_4-solution000004.solution b/tests/exhaustive/autogen/gen02/expected/model_4_4-solution000004.solution deleted file mode 100644 index 0678d41bf8..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_4_4-solution000004.solution +++ /dev/null @@ -1,6 +0,0 @@ -language Essence 1.3 - -letting var2 be {{false, true}} -$ Visualisation for var2 -$ _ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_4_4-solution000005.solution b/tests/exhaustive/autogen/gen02/expected/model_4_4-solution000005.solution deleted file mode 100644 index 73f1bfe1ac..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_4_4-solution000005.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting var2 be {{}, {false}} -$ Visualisation for var2 -$ -$ _ - diff --git a/tests/exhaustive/autogen/gen02/expected/model_4_4-solution000006.solution b/tests/exhaustive/autogen/gen02/expected/model_4_4-solution000006.solution deleted file mode 100644 index d4c4a238b9..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_4_4-solution000006.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting var2 be {{}, {true}} -$ Visualisation for var2 -$ -$ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_4_4-solution000007.solution b/tests/exhaustive/autogen/gen02/expected/model_4_4-solution000007.solution deleted file mode 100644 index 2b6a8959da..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_4_4-solution000007.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting var2 be {{false}, {true}} -$ Visualisation for var2 -$ _ -$ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_4_4-solution000008.solution b/tests/exhaustive/autogen/gen02/expected/model_4_4-solution000008.solution deleted file mode 100644 index 9c15a8e4e1..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_4_4-solution000008.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting var2 be {{}, {false, true}} -$ Visualisation for var2 -$ -$ _ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_4_4-solution000009.solution b/tests/exhaustive/autogen/gen02/expected/model_4_4-solution000009.solution deleted file mode 100644 index b2e98e56a6..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_4_4-solution000009.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting var2 be {{false}, {false, true}} -$ Visualisation for var2 -$ _ -$ _ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_4_4-solution000010.solution b/tests/exhaustive/autogen/gen02/expected/model_4_4-solution000010.solution deleted file mode 100644 index 4fc309134f..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_4_4-solution000010.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting var2 be {{false, true}, {true}} -$ Visualisation for var2 -$ _ T -$ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_4_4-solution000011.solution b/tests/exhaustive/autogen/gen02/expected/model_4_4-solution000011.solution deleted file mode 100644 index 70d0f91f38..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_4_4-solution000011.solution +++ /dev/null @@ -1,8 +0,0 @@ -language Essence 1.3 - -letting var2 be {{}, {false}, {true}} -$ Visualisation for var2 -$ -$ _ -$ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_4_4-solution000012.solution b/tests/exhaustive/autogen/gen02/expected/model_4_4-solution000012.solution deleted file mode 100644 index ebc3fe4182..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_4_4-solution000012.solution +++ /dev/null @@ -1,8 +0,0 @@ -language Essence 1.3 - -letting var2 be {{}, {false}, {false, true}} -$ Visualisation for var2 -$ -$ _ -$ _ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_4_4-solution000013.solution b/tests/exhaustive/autogen/gen02/expected/model_4_4-solution000013.solution deleted file mode 100644 index fa4340a533..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_4_4-solution000013.solution +++ /dev/null @@ -1,8 +0,0 @@ -language Essence 1.3 - -letting var2 be {{}, {false, true}, {true}} -$ Visualisation for var2 -$ -$ _ T -$ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_4_4-solution000014.solution b/tests/exhaustive/autogen/gen02/expected/model_4_4-solution000014.solution deleted file mode 100644 index 371f28aab7..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_4_4-solution000014.solution +++ /dev/null @@ -1,8 +0,0 @@ -language Essence 1.3 - -letting var2 be {{false}, {false, true}, {true}} -$ Visualisation for var2 -$ _ -$ _ T -$ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_4_4-solution000015.solution b/tests/exhaustive/autogen/gen02/expected/model_4_4-solution000015.solution deleted file mode 100644 index 35cfa328e8..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_4_4-solution000015.solution +++ /dev/null @@ -1,9 +0,0 @@ -language Essence 1.3 - -letting var2 be {{}, {false}, {false, true}, {true}} -$ Visualisation for var2 -$ -$ _ -$ _ T -$ T - diff --git a/tests/exhaustive/autogen/gen02/expected/model_4_4.eprime b/tests/exhaustive/autogen/gen02/expected/model_4_4.eprime deleted file mode 100644 index e694258b7c..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_4_4.eprime +++ /dev/null @@ -1,52 +0,0 @@ -language ESSENCE' 1.0 - -find var2_ExplicitVarSizeWithFlagsR4_Flags: matrix indexed by [int(1..4)] of bool -find var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Flags: - matrix indexed by [int(1..4), int(1..2)] of bool -find var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Values: - matrix indexed by [int(1..4), int(1..2)] of bool -branching on - [var2_ExplicitVarSizeWithFlagsR4_Flags, var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Flags, - var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Values] -such that - or([var2_ExplicitVarSizeWithFlagsR4_Flags[q16] /\ - sum([toInt(var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Flags[q16, q17]) | q17 : int(1..2)]) - >= -7 - | q16 : int(1..4)]), - and([var2_ExplicitVarSizeWithFlagsR4_Flags[q2 + 1] -> - flatten([flatten([[-toInt(var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Flags[q2, q12]); - int(1)], - [-toInt(var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Values[q2, q12]); - int(1)]; - int(1..2)]) - | q12 : int(1..2)]) - - and([var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Flags[q3, q14] = false | q14 : int(1..2)]) - /\ - and([var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Values[q3, q15] = false - | q15 : int(1..2)]) - | q3 : int(1..4)]), - and([var2_ExplicitVarSizeWithFlagsR4_Flags[q4 + 1] -> var2_ExplicitVarSizeWithFlagsR4_Flags[q4] | q4 : int(1..3)]), - and([var2_ExplicitVarSizeWithFlagsR4_Flags[q6] -> - (var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Flags[q6, 2] -> - -toInt(var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Values[q6, 1]) < - -toInt(var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Values[q6, 2])) - | q6 : int(1..4)]), - and([var2_ExplicitVarSizeWithFlagsR4_Flags[q6] -> - and([var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Flags[q6, q8] = false -> - var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Values[q6, q8] = false - | q8 : int(1..2)]) - | q6 : int(1..4)]), - and([var2_ExplicitVarSizeWithFlagsR4_Flags[q6] -> - (var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Flags[q6, 2] -> - var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Flags[q6, 1]) - | q6 : int(1..4)]) - diff --git a/tests/exhaustive/autogen/gen10/expected/model-solution000001.solution b/tests/exhaustive/autogen/gen10/expected/model-solution000001.solution deleted file mode 100644 index d1b79e6028..0000000000 --- a/tests/exhaustive/autogen/gen10/expected/model-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting var3 be function() diff --git a/tests/exhaustive/autogen/gen10/expected/model-solution000002.solution b/tests/exhaustive/autogen/gen10/expected/model-solution000002.solution deleted file mode 100644 index 5d0756d312..0000000000 --- a/tests/exhaustive/autogen/gen10/expected/model-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting var3 be function(2 --> -4) diff --git a/tests/exhaustive/autogen/gen10/expected/model-solution000003.solution b/tests/exhaustive/autogen/gen10/expected/model-solution000003.solution deleted file mode 100644 index a1b25629fb..0000000000 --- a/tests/exhaustive/autogen/gen10/expected/model-solution000003.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting var3 be function(2 --> -3) diff --git a/tests/exhaustive/autogen/gen10/expected/model-solution000004.solution b/tests/exhaustive/autogen/gen10/expected/model-solution000004.solution deleted file mode 100644 index 8c056c5c54..0000000000 --- a/tests/exhaustive/autogen/gen10/expected/model-solution000004.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting var3 be function(2 --> -2) diff --git a/tests/exhaustive/autogen/gen10/expected/model.eprime b/tests/exhaustive/autogen/gen10/expected/model.eprime deleted file mode 100644 index d50899e1fd..0000000000 --- a/tests/exhaustive/autogen/gen10/expected/model.eprime +++ /dev/null @@ -1,9 +0,0 @@ -language ESSENCE' 1.0 - -letting let1 be -4 -letting let2 be -2 -find var3_Function1DPartial_Flags: matrix indexed by [int(2, 2)] of bool -find var3_Function1DPartial_Values: matrix indexed by [int(2, 2)] of int(-4..-2) -branching on [var3_Function1DPartial_Flags, var3_Function1DPartial_Values] -such that and([var3_Function1DPartial_Flags[q1] = false -> var3_Function1DPartial_Values[q1] = -4 | q1 : int(2, 2)]) - diff --git a/tests/exhaustive/autogen/gen14_1/expected/model_1-solution000001.solution b/tests/exhaustive/autogen/gen14_1/expected/model_1-solution000001.solution deleted file mode 100644 index dc001498cc..0000000000 --- a/tests/exhaustive/autogen/gen14_1/expected/model_1-solution000001.solution +++ /dev/null @@ -1,6 +0,0 @@ -language Essence 1.3 - -letting var1 be partition({1, 2}) -$ Visualisation for var1 -$ 1 2 - diff --git a/tests/exhaustive/autogen/gen14_1/expected/model_1-solution000002.solution b/tests/exhaustive/autogen/gen14_1/expected/model_1-solution000002.solution deleted file mode 100644 index d53bf91bd1..0000000000 --- a/tests/exhaustive/autogen/gen14_1/expected/model_1-solution000002.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting var1 be partition({1}, {2}) -$ Visualisation for var1 -$ 1 -$ 2 - diff --git a/tests/exhaustive/autogen/gen14_1/expected/model_1.eprime b/tests/exhaustive/autogen/gen14_1/expected/model_1.eprime deleted file mode 100644 index 7edd61cd65..0000000000 --- a/tests/exhaustive/autogen/gen14_1/expected/model_1.eprime +++ /dev/null @@ -1,104 +0,0 @@ -language ESSENCE' 1.0 - -find var1_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker: int(0..2) -find var1_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence: matrix indexed by [int(1..2), int(1..2)] of bool -branching on - [var1_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker, - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence] -such that - !(and([q52 <= var1_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> - or([q56 <= var1_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ - (and([var1_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q56, q45] -> - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q52, q45] - | q45 : int(1..2)]) - /\ - and([var1_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q52, q46] -> - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q56, q46] - | q46 : int(1..2)])) - | q56 : int(1..2)]) - | q52 : int(1..2)]) - /\ - and([q58 <= var1_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> - or([q54 <= var1_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ - (and([var1_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q54, q49] -> - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q58, q49] - | q49 : int(1..2)]) - /\ - and([var1_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q58, q50] -> - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q54, q50] - | q50 : int(1..2)])) - | q54 : int(1..2)]) - | q58 : int(1..2)])) - \/ - !(and([q38 <= var1_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q38, 1] /\ - and([var1_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q38, q26] -> 1 = q26 - | q26 : int(1..2)]) - | q38 : int(1..2)]) - /\ - or([q40 <= var1_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ - (and([var1_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q40, q32] -> 1 = q32 - | q32 : int(1..2)]) - /\ var1_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q40, 1]) - | q40 : int(1..2)])) - \/ - !(and([q87 <= var1_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> - or([q91 <= var1_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ - (and([var1_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q91, q80] -> - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q87, q80] - | q80 : int(1..2)]) - /\ - and([var1_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q87, q81] -> - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q91, q81] - | q81 : int(1..2)])) - | q91 : int(1..2)]) - | q87 : int(1..2)]) - /\ - and([q93 <= var1_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> - or([q89 <= var1_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ - (and([var1_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q89, q84] -> - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q93, q84] - | q84 : int(1..2)]) - /\ - and([var1_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q93, q85] -> - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q89, q85] - | q85 : int(1..2)])) - | q89 : int(1..2)]) - | q93 : int(1..2)]) - \/ - or([q95 <= var1_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ - (and([var1_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q95, q65] -> 1 = q65 - | q65 : int(1..2)]) - /\ var1_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q95, 1]) - | q95 : int(1..2)]) - /\ - and([q97 <= var1_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q97, 1] /\ - and([var1_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q97, q75] -> 1 = q75 - | q75 : int(1..2)]) - | q97 : int(1..2)])), - and([1 = - sum([toInt(q14 <= var1_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q14, q1]) - | q14 : int(1..2)]) - | q1 : int(1..2)]), - and([q15 <= var1_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> - sum([toInt(var1_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q15, q16]) | q16 : int(1..2)]) >= - 1 | q15 : int(1..2)]), - 2 <= var1_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> - [-toInt(var1_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[1, q9]) | q9 : int(1..2)] var1_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> - and([var1_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q5, q11] = false | q11 : int(1..2)]) - | q5 : int(1..2)]), - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker <= 2, - and([q6 <= var1_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> - sum([toInt(var1_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q6, q7]) | q7 : int(1..2)]) <= 2 - | q6 : int(1..2)]), - 2 = - sum([toInt(q12 <= var1_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker) * - catchUndef(sum([toInt(var1_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q12, q13]) - | q13 : int(1..2)]), - 0) - | q12 : int(1..2)]) - diff --git a/tests/exhaustive/autogen/gen14_1/expected/model_2-solution000001.solution b/tests/exhaustive/autogen/gen14_1/expected/model_2-solution000001.solution deleted file mode 100644 index dc001498cc..0000000000 --- a/tests/exhaustive/autogen/gen14_1/expected/model_2-solution000001.solution +++ /dev/null @@ -1,6 +0,0 @@ -language Essence 1.3 - -letting var1 be partition({1, 2}) -$ Visualisation for var1 -$ 1 2 - diff --git a/tests/exhaustive/autogen/gen14_1/expected/model_2-solution000002.solution b/tests/exhaustive/autogen/gen14_1/expected/model_2-solution000002.solution deleted file mode 100644 index d53bf91bd1..0000000000 --- a/tests/exhaustive/autogen/gen14_1/expected/model_2-solution000002.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting var1 be partition({1}, {2}) -$ Visualisation for var1 -$ 1 -$ 2 - diff --git a/tests/exhaustive/autogen/gen14_1/expected/model_2.eprime b/tests/exhaustive/autogen/gen14_1/expected/model_2.eprime deleted file mode 100644 index 3480e2f5b6..0000000000 --- a/tests/exhaustive/autogen/gen14_1/expected/model_2.eprime +++ /dev/null @@ -1,176 +0,0 @@ -language ESSENCE' 1.0 - -find var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker: int(0..2) -find var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy: - matrix indexed by [int(1..2), int(1..2)] of int(1..3) -branching on - [var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker, - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy] -such that - !(and([q64 <= var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - or([q74 <= var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ - (and([var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q74, q75] != 3 -> - or([var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q64, q67] != 3 - /\ - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q64, q67] = - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q74, q75] - | q67 : int(1..2)]) - | q75 : int(1..2)]) - /\ - and([var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q64, q65] != 3 -> - or([var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q74, q77] != 3 - /\ - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q74, q77] = - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q64, q65] - | q77 : int(1..2)]) - | q65 : int(1..2)])) - | q74 : int(1..2)]) - | q64 : int(1..2)]) - /\ - and([q79 <= var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - or([q69 <= var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ - (and([var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q69, q70] != 3 -> - or([var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q79, q82] != 3 - /\ - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q79, q82] = - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q69, q70] - | q82 : int(1..2)]) - | q70 : int(1..2)]) - /\ - and([var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q79, q80] != 3 -> - or([var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q69, q72] != 3 - /\ - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q69, q72] = - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q79, q80] - | q72 : int(1..2)]) - | q80 : int(1..2)])) - | q69 : int(1..2)]) - | q79 : int(1..2)])) - \/ - !(and([q44 <= var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - or([var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q44, q47] != 3 /\ - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q44, q47] = 1 - | q47 : int(1..2)]) - /\ - and([var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q44, q45] != 3 -> - 1 = var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q44, q45] - | q45 : int(1..2)]) - | q44 : int(1..2)]) - /\ - or([q49 <= var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ - (and([var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q49, q50] != 3 -> - 1 = var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q49, q50] - | q50 : int(1..2)]) - /\ - or([var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q49, q52] != 3 /\ - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q49, q52] = 1 - | q52 : int(1..2)])) - | q49 : int(1..2)])) - \/ - !(and([q111 <= var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - or([q121 <= var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ - (and([var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q121, q122] != 3 -> - or([var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q111, q114] != - 3 - /\ - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q111, q114] = - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q121, q122] - | q114 : int(1..2)]) - | q122 : int(1..2)]) - /\ - and([var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q111, q112] != 3 -> - or([var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q121, q124] != - 3 - /\ - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q121, q124] = - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q111, q112] - | q124 : int(1..2)]) - | q112 : int(1..2)])) - | q121 : int(1..2)]) - | q111 : int(1..2)]) - /\ - and([q126 <= var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - or([q116 <= var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ - (and([var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q116, q117] != 3 -> - or([var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q126, q129] != - 3 - /\ - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q126, q129] = - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q116, q117] - | q129 : int(1..2)]) - | q117 : int(1..2)]) - /\ - and([var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q126, q127] != 3 -> - or([var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q116, q119] != - 3 - /\ - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q116, q119] = - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q126, q127] - | q119 : int(1..2)]) - | q127 : int(1..2)])) - | q116 : int(1..2)]) - | q126 : int(1..2)]) - \/ - or([q131 <= var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ - (and([var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q131, q132] != 3 -> - 1 = var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q131, q132] - | q132 : int(1..2)]) - /\ - or([var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q131, q134] != 3 /\ - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q131, q134] = 1 - | q134 : int(1..2)])) - | q131 : int(1..2)]) - /\ - and([q136 <= var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - or([var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q136, q139] != 3 /\ - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q136, q139] = 1 - | q139 : int(1..2)]) - /\ - and([var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q136, q137] != 3 -> - 1 = var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q136, q137] - | q137 : int(1..2)]) - | q136 : int(1..2)])), - alldifferent_except([toInt(q18 <= var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q18, q19] - != 3) - * - catchUndef(var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q18, q19], - 0) - | q18 : int(1..2), q19 : int(1..2)], - 0), - and([q20 <= var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - sum([toInt(var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q20, q22] != 3) - | q22 : int(1..2)]) - >= 1 - | q20 : int(1..2)]), - 2 <= var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - [var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[1, q12] | q12 : int(1..2)] var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - and([var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q5, q17] = 1 - | q17 : int(1..2)]) - | q5 : int(1..2)]), - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker <= 2, - and([q6 <= var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q6, 1] < - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q6, 2] - \/ var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q6, 1] = 3 - | q6 : int(1..2)]), - and([q6 <= var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - (var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q6, 1] = 3 -> - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q6, 2] = 3) - | q6 : int(1..2)]), - and([q6 <= var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - sum([toInt(var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q6, q9] != 3) - | q9 : int(1..2)]) - <= 2 - | q6 : int(1..2)]), - 2 = - sum([toInt(q14 <= var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker) * - catchUndef(sum([toInt(var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q14, q16] - != 3) - | q16 : int(1..2)]), - 0) - | q14 : int(1..2)]) - diff --git a/tests/exhaustive/autogen/gen14_1/expected/model_3-solution000001.solution b/tests/exhaustive/autogen/gen14_1/expected/model_3-solution000001.solution deleted file mode 100644 index dc001498cc..0000000000 --- a/tests/exhaustive/autogen/gen14_1/expected/model_3-solution000001.solution +++ /dev/null @@ -1,6 +0,0 @@ -language Essence 1.3 - -letting var1 be partition({1, 2}) -$ Visualisation for var1 -$ 1 2 - diff --git a/tests/exhaustive/autogen/gen14_1/expected/model_3-solution000002.solution b/tests/exhaustive/autogen/gen14_1/expected/model_3-solution000002.solution deleted file mode 100644 index d53bf91bd1..0000000000 --- a/tests/exhaustive/autogen/gen14_1/expected/model_3-solution000002.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting var1 be partition({1}, {2}) -$ Visualisation for var1 -$ 1 -$ 2 - diff --git a/tests/exhaustive/autogen/gen14_1/expected/model_3.eprime b/tests/exhaustive/autogen/gen14_1/expected/model_3.eprime deleted file mode 100644 index 3cb5d6bf40..0000000000 --- a/tests/exhaustive/autogen/gen14_1/expected/model_3.eprime +++ /dev/null @@ -1,224 +0,0 @@ -language ESSENCE' 1.0 - -find var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker: int(0..2) -find var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker: - matrix indexed by [int(1..2)] of int(0..2) -find var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values: - matrix indexed by [int(1..2), int(1..2)] of int(1..2) -branching on - [var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker, - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker, - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values] -such that - !(and([q59 <= var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - or([q69 <= var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - (and([q70 <= var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q69] - -> - or([q62 <= - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q59] - /\ - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q59, q62] - = - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q69, q70] - | q62 : int(1..2)]) - | q70 : int(1..2)]) - /\ - and([q60 <= var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q59] - -> - or([q72 <= - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q69] - /\ - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q69, q72] - = - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q59, q60] - | q72 : int(1..2)]) - | q60 : int(1..2)])) - | q69 : int(1..2)]) - | q59 : int(1..2)]) - /\ - and([q74 <= var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - or([q64 <= var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - (and([q65 <= var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q64] - -> - or([q77 <= - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q74] - /\ - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q74, q77] - = - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q64, q65] - | q77 : int(1..2)]) - | q65 : int(1..2)]) - /\ - and([q75 <= var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q74] - -> - or([q67 <= - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q64] - /\ - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q64, q67] - = - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q74, q75] - | q67 : int(1..2)]) - | q75 : int(1..2)])) - | q64 : int(1..2)]) - | q74 : int(1..2)])) - \/ - !(and([q39 <= var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - or([q42 <= var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q39] /\ - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q39, q42] = 1 - | q42 : int(1..2)]) - /\ - and([q40 <= var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q39] -> - 1 = var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q39, q40] - | q40 : int(1..2)]) - | q39 : int(1..2)]) - /\ - or([q44 <= var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - (and([q45 <= var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q44] -> - 1 = var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q44, q45] - | q45 : int(1..2)]) - /\ - or([q47 <= var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q44] /\ - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q44, q47] = 1 - | q47 : int(1..2)])) - | q44 : int(1..2)])) - \/ - !(and([q106 <= var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - or([q116 <= var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - (and([q117 <= - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q116] - -> - or([q109 <= - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q106] - /\ - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q106, q109] - = - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q116, q117] - | q109 : int(1..2)]) - | q117 : int(1..2)]) - /\ - and([q107 <= - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q106] - -> - or([q119 <= - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q116] - /\ - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q116, q119] - = - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q106, q107] - | q119 : int(1..2)]) - | q107 : int(1..2)])) - | q116 : int(1..2)]) - | q106 : int(1..2)]) - /\ - and([q121 <= var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - or([q111 <= var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - (and([q112 <= - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q111] - -> - or([q124 <= - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q121] - /\ - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q121, q124] - = - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q111, q112] - | q124 : int(1..2)]) - | q112 : int(1..2)]) - /\ - and([q122 <= - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q121] - -> - or([q114 <= - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q111] - /\ - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q111, q114] - = - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q121, q122] - | q114 : int(1..2)]) - | q122 : int(1..2)])) - | q111 : int(1..2)]) - | q121 : int(1..2)]) - \/ - or([q126 <= var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - (and([q127 <= var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q126] -> - 1 = var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q126, q127] - | q127 : int(1..2)]) - /\ - or([q129 <= var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q126] /\ - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q126, q129] = 1 - | q129 : int(1..2)])) - | q126 : int(1..2)]) - /\ - and([q131 <= var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - or([q134 <= var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q131] /\ - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q131, q134] = 1 - | q134 : int(1..2)]) - /\ - and([q132 <= var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q131] -> - 1 = var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q131, q132] - | q132 : int(1..2)]) - | q131 : int(1..2)])), - alldifferent_except([toInt(q15 <= var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - q16 <= - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q15]) - * - catchUndef(var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q15, q16], - 0) - | q15 : int(1..2), q16 : int(1..2)], - 0), - and([q17 <= var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q17] >= 1 - | q17 : int(1..2)]), - 2 <= var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - flatten([[var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[1]; int(1)], - flatten([[var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[1, q11]; - int(1)] - | q11 : int(1..2)]); - int(1..2)]) - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q5] = 0 /\ - and([var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q5, q14] = 1 - | q14 : int(1..2)]) - | q5 : int(1..2)]), - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker <= 2, - and([q6 <= var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - (2 <= var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q6] -> - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q6, 1] < - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q6, 2]) - | q6 : int(1..2)]), - and([q6 <= var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - and([q8 > var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q6] -> - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q6, q8] = 1 - | q8 : int(1..2)]) - | q6 : int(1..2)]), - and([q6 <= var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q6] <= 2 - | q6 : int(1..2)]), - 2 = - sum([toInt(q13 <= var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker) * - catchUndef(var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q13], 0) - | q13 : int(1..2)]) - diff --git a/tests/exhaustive/autogen/gen14_1/expected/model_4-solution000001.solution b/tests/exhaustive/autogen/gen14_1/expected/model_4-solution000001.solution deleted file mode 100644 index dc001498cc..0000000000 --- a/tests/exhaustive/autogen/gen14_1/expected/model_4-solution000001.solution +++ /dev/null @@ -1,6 +0,0 @@ -language Essence 1.3 - -letting var1 be partition({1, 2}) -$ Visualisation for var1 -$ 1 2 - diff --git a/tests/exhaustive/autogen/gen14_1/expected/model_4-solution000002.solution b/tests/exhaustive/autogen/gen14_1/expected/model_4-solution000002.solution deleted file mode 100644 index d53bf91bd1..0000000000 --- a/tests/exhaustive/autogen/gen14_1/expected/model_4-solution000002.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting var1 be partition({1}, {2}) -$ Visualisation for var1 -$ 1 -$ 2 - diff --git a/tests/exhaustive/autogen/gen14_1/expected/model_4.eprime b/tests/exhaustive/autogen/gen14_1/expected/model_4.eprime deleted file mode 100644 index f21cfb8002..0000000000 --- a/tests/exhaustive/autogen/gen14_1/expected/model_4.eprime +++ /dev/null @@ -1,97 +0,0 @@ -language ESSENCE' 1.0 - -find var1_PartitionOccurrence_NumParts: int(1..2) -find var1_PartitionOccurrence_WhichPart: matrix indexed by [int(1..2)] of int(1..2) -find var1_PartitionOccurrence_PartSizes: matrix indexed by [int(1..2)] of int(0..2) -find var1_PartitionOccurrence_FirstIndex: matrix indexed by [int(1..2)] of int(1..2) -branching on - [var1_PartitionOccurrence_NumParts, var1_PartitionOccurrence_WhichPart, var1_PartitionOccurrence_PartSizes, - var1_PartitionOccurrence_FirstIndex] -such that - !(and([q51 <= var1_PartitionOccurrence_NumParts -> - or([q61 <= var1_PartitionOccurrence_NumParts /\ - (and([var1_PartitionOccurrence_WhichPart[q63] = q61 -> - or([var1_PartitionOccurrence_WhichPart[q54] = q51 /\ q54 = q63 | q54 : int(1..2)]) - | q63 : int(1..2)]) - /\ - and([var1_PartitionOccurrence_WhichPart[q55] = q51 -> - or([var1_PartitionOccurrence_WhichPart[q65] = q61 /\ q65 = q55 | q65 : int(1..2)]) - | q55 : int(1..2)])) - | q61 : int(1..2)]) - | q51 : int(1..2)]) - /\ - and([q66 <= var1_PartitionOccurrence_NumParts -> - or([q56 <= var1_PartitionOccurrence_NumParts /\ - (and([var1_PartitionOccurrence_WhichPart[q58] = q56 -> - or([var1_PartitionOccurrence_WhichPart[q69] = q66 /\ q69 = q58 | q69 : int(1..2)]) - | q58 : int(1..2)]) - /\ - and([var1_PartitionOccurrence_WhichPart[q70] = q66 -> - or([var1_PartitionOccurrence_WhichPart[q60] = q56 /\ q60 = q70 | q60 : int(1..2)]) - | q70 : int(1..2)])) - | q56 : int(1..2)]) - | q66 : int(1..2)])) - \/ - !(and([q31 <= var1_PartitionOccurrence_NumParts -> - or([var1_PartitionOccurrence_WhichPart[q35] = q31 /\ q35 = 1 | q35 : int(1..2)]) /\ - and([var1_PartitionOccurrence_WhichPart[q33] = q31 -> 1 = q33 | q33 : int(1..2)]) - | q31 : int(1..2)]) - /\ - or([q36 <= var1_PartitionOccurrence_NumParts /\ - (and([var1_PartitionOccurrence_WhichPart[q38] = q36 -> 1 = q38 | q38 : int(1..2)]) /\ - or([var1_PartitionOccurrence_WhichPart[q40] = q36 /\ q40 = 1 | q40 : int(1..2)])) - | q36 : int(1..2)])) - \/ - !(and([q98 <= var1_PartitionOccurrence_NumParts -> - or([q108 <= var1_PartitionOccurrence_NumParts /\ - (and([var1_PartitionOccurrence_WhichPart[q110] = q108 -> - or([var1_PartitionOccurrence_WhichPart[q101] = q98 /\ q101 = q110 | q101 : int(1..2)]) - | q110 : int(1..2)]) - /\ - and([var1_PartitionOccurrence_WhichPart[q102] = q98 -> - or([var1_PartitionOccurrence_WhichPart[q112] = q108 /\ q112 = q102 | q112 : int(1..2)]) - | q102 : int(1..2)])) - | q108 : int(1..2)]) - | q98 : int(1..2)]) - /\ - and([q113 <= var1_PartitionOccurrence_NumParts -> - or([q103 <= var1_PartitionOccurrence_NumParts /\ - (and([var1_PartitionOccurrence_WhichPart[q105] = q103 -> - or([var1_PartitionOccurrence_WhichPart[q116] = q113 /\ q116 = q105 | q116 : int(1..2)]) - | q105 : int(1..2)]) - /\ - and([var1_PartitionOccurrence_WhichPart[q117] = q113 -> - or([var1_PartitionOccurrence_WhichPart[q107] = q103 /\ q107 = q117 | q107 : int(1..2)]) - | q117 : int(1..2)])) - | q103 : int(1..2)]) - | q113 : int(1..2)]) - \/ - or([q118 <= var1_PartitionOccurrence_NumParts /\ - (and([var1_PartitionOccurrence_WhichPart[q120] = q118 -> 1 = q120 | q120 : int(1..2)]) /\ - or([var1_PartitionOccurrence_WhichPart[q122] = q118 /\ q122 = 1 | q122 : int(1..2)])) - | q118 : int(1..2)]) - /\ - and([q123 <= var1_PartitionOccurrence_NumParts -> - or([var1_PartitionOccurrence_WhichPart[q127] = q123 /\ q127 = 1 | q127 : int(1..2)]) /\ - and([var1_PartitionOccurrence_WhichPart[q125] = q123 -> 1 = q125 | q125 : int(1..2)]) - | q123 : int(1..2)])), - and([q1 <= var1_PartitionOccurrence_NumParts -> var1_PartitionOccurrence_PartSizes[q1] <= 2 | q1 : int(1..2)]), - and([q1 > var1_PartitionOccurrence_NumParts -> var1_PartitionOccurrence_PartSizes[q1] = 0 | q1 : int(1..2)]), - var1_PartitionOccurrence_NumParts <= 2, - var1_PartitionOccurrence_NumParts = max([var1_PartitionOccurrence_WhichPart[q4] | q4 : int(1..2)]), - and([var1_PartitionOccurrence_PartSizes[q5] = - sum([toInt(var1_PartitionOccurrence_WhichPart[q6] = q5) | q6 : int(1..2)]) - | q5 : int(1..2)]), - and([q7 <= var1_PartitionOccurrence_NumParts -> - and([var1_PartitionOccurrence_WhichPart[q8] = q7 -> var1_PartitionOccurrence_FirstIndex[q7] <= q8 - | q8 : int(1..2)]) - | q7 : int(1..2)]), - and([q7 <= var1_PartitionOccurrence_NumParts -> - or([var1_PartitionOccurrence_WhichPart[q8] = q7 /\ var1_PartitionOccurrence_FirstIndex[q7] = q8 - | q8 : int(1..2)]) - | q7 : int(1..2)]), - and([q7 > var1_PartitionOccurrence_NumParts -> var1_PartitionOccurrence_FirstIndex[q7] = 1 | q7 : int(1..2)]), - and([q9 <= var1_PartitionOccurrence_NumParts /\ q10 <= var1_PartitionOccurrence_NumParts -> - (q9 < q10 <-> var1_PartitionOccurrence_FirstIndex[q9] < var1_PartitionOccurrence_FirstIndex[q10]) - | q9 : int(1..2), q10 : int(1..2)]) - diff --git a/tests/exhaustive/autogen/gen14_2/expected/model_1-solution000001.solution b/tests/exhaustive/autogen/gen14_2/expected/model_1-solution000001.solution deleted file mode 100644 index dc001498cc..0000000000 --- a/tests/exhaustive/autogen/gen14_2/expected/model_1-solution000001.solution +++ /dev/null @@ -1,6 +0,0 @@ -language Essence 1.3 - -letting var1 be partition({1, 2}) -$ Visualisation for var1 -$ 1 2 - diff --git a/tests/exhaustive/autogen/gen14_2/expected/model_1-solution000002.solution b/tests/exhaustive/autogen/gen14_2/expected/model_1-solution000002.solution deleted file mode 100644 index d53bf91bd1..0000000000 --- a/tests/exhaustive/autogen/gen14_2/expected/model_1-solution000002.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting var1 be partition({1}, {2}) -$ Visualisation for var1 -$ 1 -$ 2 - diff --git a/tests/exhaustive/autogen/gen14_2/expected/model_1.eprime b/tests/exhaustive/autogen/gen14_2/expected/model_1.eprime deleted file mode 100644 index 1f3c94bad0..0000000000 --- a/tests/exhaustive/autogen/gen14_2/expected/model_1.eprime +++ /dev/null @@ -1,38 +0,0 @@ -language ESSENCE' 1.0 - -find var1_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker: int(0..2) -find var1_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence: matrix indexed by [int(1..2), int(1..2)] of bool -branching on - [var1_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker, - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence] -such that - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker = var1_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker, - and([and([var1_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q17, q19] = - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q17, q19] - | q19 : int(1..2)]) - | q17 : int(1..2)]), - and([1 = - sum([toInt(q14 <= var1_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q14, q1]) - | q14 : int(1..2)]) - | q1 : int(1..2)]), - and([q15 <= var1_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> - sum([toInt(var1_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q15, q16]) | q16 : int(1..2)]) >= - 1 | q15 : int(1..2)]), - 2 <= var1_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> - [-toInt(var1_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[1, q9]) | q9 : int(1..2)] var1_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> - and([var1_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q5, q11] = false | q11 : int(1..2)]) - | q5 : int(1..2)]), - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker <= 2, - and([q6 <= var1_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> - sum([toInt(var1_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q6, q7]) | q7 : int(1..2)]) <= 2 - | q6 : int(1..2)]), - 2 = - sum([toInt(q12 <= var1_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker) * - catchUndef(sum([toInt(var1_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q12, q13]) - | q13 : int(1..2)]), - 0) - | q12 : int(1..2)]) - diff --git a/tests/exhaustive/autogen/gen14_2/expected/model_2-solution000001.solution b/tests/exhaustive/autogen/gen14_2/expected/model_2-solution000001.solution deleted file mode 100644 index dc001498cc..0000000000 --- a/tests/exhaustive/autogen/gen14_2/expected/model_2-solution000001.solution +++ /dev/null @@ -1,6 +0,0 @@ -language Essence 1.3 - -letting var1 be partition({1, 2}) -$ Visualisation for var1 -$ 1 2 - diff --git a/tests/exhaustive/autogen/gen14_2/expected/model_2-solution000002.solution b/tests/exhaustive/autogen/gen14_2/expected/model_2-solution000002.solution deleted file mode 100644 index d53bf91bd1..0000000000 --- a/tests/exhaustive/autogen/gen14_2/expected/model_2-solution000002.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting var1 be partition({1}, {2}) -$ Visualisation for var1 -$ 1 -$ 2 - diff --git a/tests/exhaustive/autogen/gen14_2/expected/model_2.eprime b/tests/exhaustive/autogen/gen14_2/expected/model_2.eprime deleted file mode 100644 index 0da1c335c9..0000000000 --- a/tests/exhaustive/autogen/gen14_2/expected/model_2.eprime +++ /dev/null @@ -1,58 +0,0 @@ -language ESSENCE' 1.0 - -find var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker: int(0..2) -find var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy: - matrix indexed by [int(1..2), int(1..2)] of int(1..3) -branching on - [var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker, - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy] -such that - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker = var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker, - and([and([var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q18, q20] = - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q18, q20] - | q20 : int(1..2)]) - | q18 : int(1..2)]), - alldifferent_except([toInt(q22 <= var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q22, q23] - != 3) - * - catchUndef(var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q22, q23], - 0) - | q22 : int(1..2), q23 : int(1..2)], - 0), - and([q24 <= var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - sum([toInt(var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q24, q26] != 3) - | q26 : int(1..2)]) - >= 1 - | q24 : int(1..2)]), - 2 <= var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - [var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[1, q12] | q12 : int(1..2)] var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - and([var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q5, q17] = 1 - | q17 : int(1..2)]) - | q5 : int(1..2)]), - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker <= 2, - and([q6 <= var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q6, 1] < - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q6, 2] - \/ var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q6, 1] = 3 - | q6 : int(1..2)]), - and([q6 <= var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - (var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q6, 1] = 3 -> - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q6, 2] = 3) - | q6 : int(1..2)]), - and([q6 <= var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - sum([toInt(var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q6, q9] != 3) - | q9 : int(1..2)]) - <= 2 - | q6 : int(1..2)]), - 2 = - sum([toInt(q14 <= var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker) * - catchUndef(sum([toInt(var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q14, q16] - != 3) - | q16 : int(1..2)]), - 0) - | q14 : int(1..2)]) - diff --git a/tests/exhaustive/autogen/gen14_2/expected/model_3-solution000001.solution b/tests/exhaustive/autogen/gen14_2/expected/model_3-solution000001.solution deleted file mode 100644 index dc001498cc..0000000000 --- a/tests/exhaustive/autogen/gen14_2/expected/model_3-solution000001.solution +++ /dev/null @@ -1,6 +0,0 @@ -language Essence 1.3 - -letting var1 be partition({1, 2}) -$ Visualisation for var1 -$ 1 2 - diff --git a/tests/exhaustive/autogen/gen14_2/expected/model_3-solution000002.solution b/tests/exhaustive/autogen/gen14_2/expected/model_3-solution000002.solution deleted file mode 100644 index d53bf91bd1..0000000000 --- a/tests/exhaustive/autogen/gen14_2/expected/model_3-solution000002.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting var1 be partition({1}, {2}) -$ Visualisation for var1 -$ 1 -$ 2 - diff --git a/tests/exhaustive/autogen/gen14_2/expected/model_3.eprime b/tests/exhaustive/autogen/gen14_2/expected/model_3.eprime deleted file mode 100644 index 6b660f9eca..0000000000 --- a/tests/exhaustive/autogen/gen14_2/expected/model_3.eprime +++ /dev/null @@ -1,69 +0,0 @@ -language ESSENCE' 1.0 - -find var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker: int(0..2) -find var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker: - matrix indexed by [int(1..2)] of int(0..2) -find var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values: - matrix indexed by [int(1..2), int(1..2)] of int(1..2) -branching on - [var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker, - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker, - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values] -such that - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker = var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker, - and([var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q15] = - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q15] - | q15 : int(1..2)]), - and([and([var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q17, q19] = - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q17, q19] - | q19 : int(1..2)]) - | q17 : int(1..2)]), - alldifferent_except([toInt(q21 <= var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - q22 <= - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q21]) - * - catchUndef(var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q21, q22], - 0) - | q21 : int(1..2), q22 : int(1..2)], - 0), - and([q23 <= var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q23] >= 1 - | q23 : int(1..2)]), - 2 <= var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - flatten([[var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[1]; int(1)], - flatten([[var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[1, q11]; - int(1)] - | q11 : int(1..2)]); - int(1..2)]) - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q5] = 0 /\ - and([var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q5, q14] = 1 - | q14 : int(1..2)]) - | q5 : int(1..2)]), - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker <= 2, - and([q6 <= var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - (2 <= var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q6] -> - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q6, 1] < - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q6, 2]) - | q6 : int(1..2)]), - and([q6 <= var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - and([q8 > var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q6] -> - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q6, q8] = 1 - | q8 : int(1..2)]) - | q6 : int(1..2)]), - and([q6 <= var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q6] <= 2 - | q6 : int(1..2)]), - 2 = - sum([toInt(q13 <= var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker) * - catchUndef(var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q13], 0) - | q13 : int(1..2)]) - diff --git a/tests/exhaustive/autogen/gen14_2/expected/model_4-solution000001.solution b/tests/exhaustive/autogen/gen14_2/expected/model_4-solution000001.solution deleted file mode 100644 index dc001498cc..0000000000 --- a/tests/exhaustive/autogen/gen14_2/expected/model_4-solution000001.solution +++ /dev/null @@ -1,6 +0,0 @@ -language Essence 1.3 - -letting var1 be partition({1, 2}) -$ Visualisation for var1 -$ 1 2 - diff --git a/tests/exhaustive/autogen/gen14_2/expected/model_4-solution000002.solution b/tests/exhaustive/autogen/gen14_2/expected/model_4-solution000002.solution deleted file mode 100644 index d53bf91bd1..0000000000 --- a/tests/exhaustive/autogen/gen14_2/expected/model_4-solution000002.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting var1 be partition({1}, {2}) -$ Visualisation for var1 -$ 1 -$ 2 - diff --git a/tests/exhaustive/autogen/gen14_2/expected/model_4.eprime b/tests/exhaustive/autogen/gen14_2/expected/model_4.eprime deleted file mode 100644 index dadf615aea..0000000000 --- a/tests/exhaustive/autogen/gen14_2/expected/model_4.eprime +++ /dev/null @@ -1,34 +0,0 @@ -language ESSENCE' 1.0 - -find var1_PartitionOccurrence_NumParts: int(1..2) -find var1_PartitionOccurrence_WhichPart: matrix indexed by [int(1..2)] of int(1..2) -find var1_PartitionOccurrence_PartSizes: matrix indexed by [int(1..2)] of int(0..2) -find var1_PartitionOccurrence_FirstIndex: matrix indexed by [int(1..2)] of int(1..2) -branching on - [var1_PartitionOccurrence_NumParts, var1_PartitionOccurrence_WhichPart, var1_PartitionOccurrence_PartSizes, - var1_PartitionOccurrence_FirstIndex] -such that - var1_PartitionOccurrence_NumParts = var1_PartitionOccurrence_NumParts, - and([var1_PartitionOccurrence_WhichPart[q11] = var1_PartitionOccurrence_WhichPart[q11] | q11 : int(1..2)]), - and([var1_PartitionOccurrence_PartSizes[q13] = var1_PartitionOccurrence_PartSizes[q13] | q13 : int(1..2)]), - and([var1_PartitionOccurrence_FirstIndex[q15] = var1_PartitionOccurrence_FirstIndex[q15] | q15 : int(1..2)]), - and([q1 <= var1_PartitionOccurrence_NumParts -> var1_PartitionOccurrence_PartSizes[q1] <= 2 | q1 : int(1..2)]), - and([q1 > var1_PartitionOccurrence_NumParts -> var1_PartitionOccurrence_PartSizes[q1] = 0 | q1 : int(1..2)]), - var1_PartitionOccurrence_NumParts <= 2, - var1_PartitionOccurrence_NumParts = max([var1_PartitionOccurrence_WhichPart[q4] | q4 : int(1..2)]), - and([var1_PartitionOccurrence_PartSizes[q5] = - sum([toInt(var1_PartitionOccurrence_WhichPart[q6] = q5) | q6 : int(1..2)]) - | q5 : int(1..2)]), - and([q7 <= var1_PartitionOccurrence_NumParts -> - and([var1_PartitionOccurrence_WhichPart[q8] = q7 -> var1_PartitionOccurrence_FirstIndex[q7] <= q8 - | q8 : int(1..2)]) - | q7 : int(1..2)]), - and([q7 <= var1_PartitionOccurrence_NumParts -> - or([var1_PartitionOccurrence_WhichPart[q8] = q7 /\ var1_PartitionOccurrence_FirstIndex[q7] = q8 - | q8 : int(1..2)]) - | q7 : int(1..2)]), - and([q7 > var1_PartitionOccurrence_NumParts -> var1_PartitionOccurrence_FirstIndex[q7] = 1 | q7 : int(1..2)]), - and([q9 <= var1_PartitionOccurrence_NumParts /\ q10 <= var1_PartitionOccurrence_NumParts -> - (q9 < q10 <-> var1_PartitionOccurrence_FirstIndex[q9] < var1_PartitionOccurrence_FirstIndex[q10]) - | q9 : int(1..2), q10 : int(1..2)]) - diff --git a/tests/exhaustive/autogen/gen32/expected/model_1_1_1.eprime b/tests/exhaustive/autogen/gen32/expected/model_1_1_1.eprime deleted file mode 100644 index 2e44586da2..0000000000 --- a/tests/exhaustive/autogen/gen32/expected/model_1_1_1.eprime +++ /dev/null @@ -1,9 +0,0 @@ -language ESSENCE' 1.0 - -letting let1 be -4 -find var2_Occurrence: matrix indexed by [int(-4..5, 2)] of bool -branching on [var2_Occurrence] -such that - or([var2_Occurrence[q2] /\ !var2_Occurrence[q2] | q2 : int(-4..5, 2)]) \/ - or([var2_Occurrence[q2] /\ !var2_Occurrence[q2] | q2 : int(-4..5, 2)]) - diff --git a/tests/exhaustive/autogen/gen32/expected/model_1_1_2.eprime b/tests/exhaustive/autogen/gen32/expected/model_1_1_2.eprime deleted file mode 100644 index 5d9dfb9509..0000000000 --- a/tests/exhaustive/autogen/gen32/expected/model_1_1_2.eprime +++ /dev/null @@ -1,19 +0,0 @@ -language ESSENCE' 1.0 - -letting let1 be -4 -find var2_Occurrence: matrix indexed by [int(-4..5, 2)] of bool -find var2_ExplicitVarSizeWithDummy: matrix indexed by [int(1..11)] of int(-4..5, 2, 6) -branching on [var2_ExplicitVarSizeWithDummy, var2_Occurrence] -such that - or([var2_Occurrence[q11] /\ !var2_Occurrence[q11] | q11 : int(-4..5, 2)]) \/ - or([var2_Occurrence[q11] /\ !var2_Occurrence[q11] | q11 : int(-4..5, 2)]), - and([var2_ExplicitVarSizeWithDummy[q2] < var2_ExplicitVarSizeWithDummy[q2 + 1] \/ - var2_ExplicitVarSizeWithDummy[q2] = 6 - | q2 : int(1..10)]), - and([var2_ExplicitVarSizeWithDummy[q3] = 6 -> var2_ExplicitVarSizeWithDummy[q3 + 1] = 6 | q3 : int(1..10)]), - and([var2_ExplicitVarSizeWithDummy[q7] != 6 -> var2_Occurrence[var2_ExplicitVarSizeWithDummy[q7]] - | q7 : int(1..11)]), - and([var2_Occurrence[q8] -> - or([var2_ExplicitVarSizeWithDummy[q10] != 6 /\ var2_ExplicitVarSizeWithDummy[q10] = q8 | q10 : int(1..11)]) - | q8 : int(-4..5, 2)]) - diff --git a/tests/exhaustive/autogen/gen32/expected/model_1_1_3.eprime b/tests/exhaustive/autogen/gen32/expected/model_1_1_3.eprime deleted file mode 100644 index b7f0533fd6..0000000000 --- a/tests/exhaustive/autogen/gen32/expected/model_1_1_3.eprime +++ /dev/null @@ -1,22 +0,0 @@ -language ESSENCE' 1.0 - -letting let1 be -4 -find var2_Occurrence: matrix indexed by [int(-4..5, 2)] of bool -find var2_ExplicitVarSizeWithMarker_Marker: int(0..11) -find var2_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..11)] of int(-4..5, 2) -branching on [var2_ExplicitVarSizeWithMarker_Marker, var2_ExplicitVarSizeWithMarker_Values, var2_Occurrence] -such that - or([var2_Occurrence[q10] /\ !var2_Occurrence[q10] | q10 : int(-4..5, 2)]) \/ - or([var2_Occurrence[q10] /\ !var2_Occurrence[q10] | q10 : int(-4..5, 2)]), - and([q2 + 1 <= var2_ExplicitVarSizeWithMarker_Marker -> - var2_ExplicitVarSizeWithMarker_Values[q2] < var2_ExplicitVarSizeWithMarker_Values[q2 + 1] - | q2 : int(1..10)]), - and([q3 > var2_ExplicitVarSizeWithMarker_Marker -> var2_ExplicitVarSizeWithMarker_Values[q3] = -4 - | q3 : int(1..11)]), - and([q6 <= var2_ExplicitVarSizeWithMarker_Marker -> var2_Occurrence[var2_ExplicitVarSizeWithMarker_Values[q6]] - | q6 : int(1..11)]), - and([var2_Occurrence[q7] -> - or([q9 <= var2_ExplicitVarSizeWithMarker_Marker /\ var2_ExplicitVarSizeWithMarker_Values[q9] = q7 - | q9 : int(1..11)]) - | q7 : int(-4..5, 2)]) - diff --git a/tests/exhaustive/autogen/gen32/expected/model_1_1_4.eprime b/tests/exhaustive/autogen/gen32/expected/model_1_1_4.eprime deleted file mode 100644 index bd003c9167..0000000000 --- a/tests/exhaustive/autogen/gen32/expected/model_1_1_4.eprime +++ /dev/null @@ -1,23 +0,0 @@ -language ESSENCE' 1.0 - -letting let1 be -4 -find var2_Occurrence: matrix indexed by [int(-4..5, 2)] of bool -find var2_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..11)] of bool -find var2_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..11)] of int(-4..5, 2) -branching on [var2_ExplicitVarSizeWithFlags_Flags, var2_ExplicitVarSizeWithFlags_Values, var2_Occurrence] -such that - or([var2_Occurrence[q12] /\ !var2_Occurrence[q12] | q12 : int(-4..5, 2)]) \/ - or([var2_Occurrence[q12] /\ !var2_Occurrence[q12] | q12 : int(-4..5, 2)]), - and([var2_ExplicitVarSizeWithFlags_Flags[q2 + 1] -> - var2_ExplicitVarSizeWithFlags_Values[q2] < var2_ExplicitVarSizeWithFlags_Values[q2 + 1] - | q2 : int(1..10)]), - and([var2_ExplicitVarSizeWithFlags_Flags[q3] = false -> var2_ExplicitVarSizeWithFlags_Values[q3] = -4 - | q3 : int(1..11)]), - and([var2_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> var2_ExplicitVarSizeWithFlags_Flags[q4] | q4 : int(1..10)]), - and([var2_ExplicitVarSizeWithFlags_Flags[q8] -> var2_Occurrence[var2_ExplicitVarSizeWithFlags_Values[q8]] - | q8 : int(1..11)]), - and([var2_Occurrence[q9] -> - or([var2_ExplicitVarSizeWithFlags_Flags[q11] /\ var2_ExplicitVarSizeWithFlags_Values[q11] = q9 - | q11 : int(1..11)]) - | q9 : int(-4..5, 2)]) - diff --git a/tests/exhaustive/autogen/gen32/expected/model_1_2_1.eprime b/tests/exhaustive/autogen/gen32/expected/model_1_2_1.eprime deleted file mode 100644 index 7ba618afa0..0000000000 --- a/tests/exhaustive/autogen/gen32/expected/model_1_2_1.eprime +++ /dev/null @@ -1,23 +0,0 @@ -language ESSENCE' 1.0 - -letting let1 be -4 -find var2_Occurrence: matrix indexed by [int(-4..5, 2)] of bool -find var2_ExplicitVarSizeWithDummy: matrix indexed by [int(1..11)] of int(-4..5, 2, 6) -branching on [var2_ExplicitVarSizeWithDummy, var2_Occurrence] -such that - or([var2_Occurrence[q11] /\ - !or([var2_ExplicitVarSizeWithDummy[q13] != 6 /\ var2_ExplicitVarSizeWithDummy[q13] = q11 | q13 : int(1..11)]) - | q11 : int(-4..5, 2)]) - \/ - or([var2_ExplicitVarSizeWithDummy[q14] != 6 /\ !var2_Occurrence[var2_ExplicitVarSizeWithDummy[q14]] - | q14 : int(1..11)]), - and([var2_ExplicitVarSizeWithDummy[q2] < var2_ExplicitVarSizeWithDummy[q2 + 1] \/ - var2_ExplicitVarSizeWithDummy[q2] = 6 - | q2 : int(1..10)]), - and([var2_ExplicitVarSizeWithDummy[q3] = 6 -> var2_ExplicitVarSizeWithDummy[q3 + 1] = 6 | q3 : int(1..10)]), - and([var2_ExplicitVarSizeWithDummy[q7] != 6 -> var2_Occurrence[var2_ExplicitVarSizeWithDummy[q7]] - | q7 : int(1..11)]), - and([var2_Occurrence[q8] -> - or([var2_ExplicitVarSizeWithDummy[q10] != 6 /\ var2_ExplicitVarSizeWithDummy[q10] = q8 | q10 : int(1..11)]) - | q8 : int(-4..5, 2)]) - diff --git a/tests/exhaustive/autogen/gen32/expected/model_1_2_2.eprime b/tests/exhaustive/autogen/gen32/expected/model_1_2_2.eprime deleted file mode 100644 index 7ba618afa0..0000000000 --- a/tests/exhaustive/autogen/gen32/expected/model_1_2_2.eprime +++ /dev/null @@ -1,23 +0,0 @@ -language ESSENCE' 1.0 - -letting let1 be -4 -find var2_Occurrence: matrix indexed by [int(-4..5, 2)] of bool -find var2_ExplicitVarSizeWithDummy: matrix indexed by [int(1..11)] of int(-4..5, 2, 6) -branching on [var2_ExplicitVarSizeWithDummy, var2_Occurrence] -such that - or([var2_Occurrence[q11] /\ - !or([var2_ExplicitVarSizeWithDummy[q13] != 6 /\ var2_ExplicitVarSizeWithDummy[q13] = q11 | q13 : int(1..11)]) - | q11 : int(-4..5, 2)]) - \/ - or([var2_ExplicitVarSizeWithDummy[q14] != 6 /\ !var2_Occurrence[var2_ExplicitVarSizeWithDummy[q14]] - | q14 : int(1..11)]), - and([var2_ExplicitVarSizeWithDummy[q2] < var2_ExplicitVarSizeWithDummy[q2 + 1] \/ - var2_ExplicitVarSizeWithDummy[q2] = 6 - | q2 : int(1..10)]), - and([var2_ExplicitVarSizeWithDummy[q3] = 6 -> var2_ExplicitVarSizeWithDummy[q3 + 1] = 6 | q3 : int(1..10)]), - and([var2_ExplicitVarSizeWithDummy[q7] != 6 -> var2_Occurrence[var2_ExplicitVarSizeWithDummy[q7]] - | q7 : int(1..11)]), - and([var2_Occurrence[q8] -> - or([var2_ExplicitVarSizeWithDummy[q10] != 6 /\ var2_ExplicitVarSizeWithDummy[q10] = q8 | q10 : int(1..11)]) - | q8 : int(-4..5, 2)]) - diff --git a/tests/exhaustive/autogen/gen32/expected/model_1_2_3.eprime b/tests/exhaustive/autogen/gen32/expected/model_1_2_3.eprime deleted file mode 100644 index 9722a2c244..0000000000 --- a/tests/exhaustive/autogen/gen32/expected/model_1_2_3.eprime +++ /dev/null @@ -1,48 +0,0 @@ -language ESSENCE' 1.0 - -letting let1 be -4 -find var2_Occurrence: matrix indexed by [int(-4..5, 2)] of bool -find var2_ExplicitVarSizeWithDummy: matrix indexed by [int(1..11)] of int(-4..5, 2, 6) -find var2_ExplicitVarSizeWithMarker_Marker: int(0..11) -find var2_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..11)] of int(-4..5, 2) -branching on - [var2_ExplicitVarSizeWithMarker_Marker, var2_ExplicitVarSizeWithMarker_Values, var2_Occurrence, - var2_ExplicitVarSizeWithDummy] -such that - or([var2_Occurrence[q27] /\ - !or([var2_ExplicitVarSizeWithDummy[q29] != 6 /\ var2_ExplicitVarSizeWithDummy[q29] = q27 | q29 : int(1..11)]) - | q27 : int(-4..5, 2)]) - \/ - or([var2_ExplicitVarSizeWithDummy[q30] != 6 /\ !var2_Occurrence[var2_ExplicitVarSizeWithDummy[q30]] - | q30 : int(1..11)]), - and([var2_ExplicitVarSizeWithDummy[q2] < var2_ExplicitVarSizeWithDummy[q2 + 1] \/ - var2_ExplicitVarSizeWithDummy[q2] = 6 - | q2 : int(1..10)]), - and([var2_ExplicitVarSizeWithDummy[q3] = 6 -> var2_ExplicitVarSizeWithDummy[q3 + 1] = 6 | q3 : int(1..10)]), - and([var2_ExplicitVarSizeWithDummy[q7] != 6 -> var2_Occurrence[var2_ExplicitVarSizeWithDummy[q7]] - | q7 : int(1..11)]), - and([var2_Occurrence[q8] -> - or([var2_ExplicitVarSizeWithDummy[q10] != 6 /\ var2_ExplicitVarSizeWithDummy[q10] = q8 | q10 : int(1..11)]) - | q8 : int(-4..5, 2)]), - and([q11 + 1 <= var2_ExplicitVarSizeWithMarker_Marker -> - var2_ExplicitVarSizeWithMarker_Values[q11] < var2_ExplicitVarSizeWithMarker_Values[q11 + 1] - | q11 : int(1..10)]), - and([q12 > var2_ExplicitVarSizeWithMarker_Marker -> var2_ExplicitVarSizeWithMarker_Values[q12] = -4 - | q12 : int(1..11)]), - and([q15 <= var2_ExplicitVarSizeWithMarker_Marker -> var2_Occurrence[var2_ExplicitVarSizeWithMarker_Values[q15]] - | q15 : int(1..11)]), - and([var2_Occurrence[q16] -> - or([q18 <= var2_ExplicitVarSizeWithMarker_Marker /\ var2_ExplicitVarSizeWithMarker_Values[q18] = q16 - | q18 : int(1..11)]) - | q16 : int(-4..5, 2)]), - and([q20 <= var2_ExplicitVarSizeWithMarker_Marker -> - or([var2_ExplicitVarSizeWithDummy[q22] != 6 /\ - var2_ExplicitVarSizeWithDummy[q22] = var2_ExplicitVarSizeWithMarker_Values[q20] - | q22 : int(1..11)]) - | q20 : int(1..11)]), - and([var2_ExplicitVarSizeWithDummy[q24] != 6 -> - or([q26 <= var2_ExplicitVarSizeWithMarker_Marker /\ - var2_ExplicitVarSizeWithMarker_Values[q26] = var2_ExplicitVarSizeWithDummy[q24] - | q26 : int(1..11)]) - | q24 : int(1..11)]) - diff --git a/tests/exhaustive/autogen/gen32/expected/model_1_2_4.eprime b/tests/exhaustive/autogen/gen32/expected/model_1_2_4.eprime deleted file mode 100644 index 8ea95c72c3..0000000000 --- a/tests/exhaustive/autogen/gen32/expected/model_1_2_4.eprime +++ /dev/null @@ -1,49 +0,0 @@ -language ESSENCE' 1.0 - -letting let1 be -4 -find var2_Occurrence: matrix indexed by [int(-4..5, 2)] of bool -find var2_ExplicitVarSizeWithDummy: matrix indexed by [int(1..11)] of int(-4..5, 2, 6) -find var2_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..11)] of bool -find var2_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..11)] of int(-4..5, 2) -branching on - [var2_ExplicitVarSizeWithFlags_Flags, var2_ExplicitVarSizeWithFlags_Values, var2_Occurrence, - var2_ExplicitVarSizeWithDummy] -such that - or([var2_Occurrence[q29] /\ - !or([var2_ExplicitVarSizeWithDummy[q31] != 6 /\ var2_ExplicitVarSizeWithDummy[q31] = q29 | q31 : int(1..11)]) - | q29 : int(-4..5, 2)]) - \/ - or([var2_ExplicitVarSizeWithDummy[q32] != 6 /\ !var2_Occurrence[var2_ExplicitVarSizeWithDummy[q32]] - | q32 : int(1..11)]), - and([var2_ExplicitVarSizeWithDummy[q2] < var2_ExplicitVarSizeWithDummy[q2 + 1] \/ - var2_ExplicitVarSizeWithDummy[q2] = 6 - | q2 : int(1..10)]), - and([var2_ExplicitVarSizeWithDummy[q3] = 6 -> var2_ExplicitVarSizeWithDummy[q3 + 1] = 6 | q3 : int(1..10)]), - and([var2_ExplicitVarSizeWithDummy[q7] != 6 -> var2_Occurrence[var2_ExplicitVarSizeWithDummy[q7]] - | q7 : int(1..11)]), - and([var2_Occurrence[q8] -> - or([var2_ExplicitVarSizeWithDummy[q10] != 6 /\ var2_ExplicitVarSizeWithDummy[q10] = q8 | q10 : int(1..11)]) - | q8 : int(-4..5, 2)]), - and([var2_ExplicitVarSizeWithFlags_Flags[q11 + 1] -> - var2_ExplicitVarSizeWithFlags_Values[q11] < var2_ExplicitVarSizeWithFlags_Values[q11 + 1] - | q11 : int(1..10)]), - and([var2_ExplicitVarSizeWithFlags_Flags[q12] = false -> var2_ExplicitVarSizeWithFlags_Values[q12] = -4 - | q12 : int(1..11)]), - and([var2_ExplicitVarSizeWithFlags_Flags[q13 + 1] -> var2_ExplicitVarSizeWithFlags_Flags[q13] | q13 : int(1..10)]), - and([var2_ExplicitVarSizeWithFlags_Flags[q17] -> var2_Occurrence[var2_ExplicitVarSizeWithFlags_Values[q17]] - | q17 : int(1..11)]), - and([var2_Occurrence[q18] -> - or([var2_ExplicitVarSizeWithFlags_Flags[q20] /\ var2_ExplicitVarSizeWithFlags_Values[q20] = q18 - | q20 : int(1..11)]) - | q18 : int(-4..5, 2)]), - and([var2_ExplicitVarSizeWithFlags_Flags[q22] -> - or([var2_ExplicitVarSizeWithDummy[q24] != 6 /\ - var2_ExplicitVarSizeWithDummy[q24] = var2_ExplicitVarSizeWithFlags_Values[q22] - | q24 : int(1..11)]) - | q22 : int(1..11)]), - and([var2_ExplicitVarSizeWithDummy[q26] != 6 -> - or([var2_ExplicitVarSizeWithFlags_Flags[q28] /\ - var2_ExplicitVarSizeWithFlags_Values[q28] = var2_ExplicitVarSizeWithDummy[q26] - | q28 : int(1..11)]) - | q26 : int(1..11)]) - diff --git a/tests/exhaustive/autogen/gen32/expected/model_1_3_1.eprime b/tests/exhaustive/autogen/gen32/expected/model_1_3_1.eprime deleted file mode 100644 index f4bcfbc82e..0000000000 --- a/tests/exhaustive/autogen/gen32/expected/model_1_3_1.eprime +++ /dev/null @@ -1,27 +0,0 @@ -language ESSENCE' 1.0 - -letting let1 be -4 -find var2_Occurrence: matrix indexed by [int(-4..5, 2)] of bool -find var2_ExplicitVarSizeWithMarker_Marker: int(0..11) -find var2_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..11)] of int(-4..5, 2) -branching on [var2_ExplicitVarSizeWithMarker_Marker, var2_ExplicitVarSizeWithMarker_Values, var2_Occurrence] -such that - or([var2_Occurrence[q10] /\ - !or([q12 <= var2_ExplicitVarSizeWithMarker_Marker /\ var2_ExplicitVarSizeWithMarker_Values[q12] = q10 - | q12 : int(1..11)]) - | q10 : int(-4..5, 2)]) - \/ - or([q13 <= var2_ExplicitVarSizeWithMarker_Marker /\ !var2_Occurrence[var2_ExplicitVarSizeWithMarker_Values[q13]] - | q13 : int(1..11)]), - and([q2 + 1 <= var2_ExplicitVarSizeWithMarker_Marker -> - var2_ExplicitVarSizeWithMarker_Values[q2] < var2_ExplicitVarSizeWithMarker_Values[q2 + 1] - | q2 : int(1..10)]), - and([q3 > var2_ExplicitVarSizeWithMarker_Marker -> var2_ExplicitVarSizeWithMarker_Values[q3] = -4 - | q3 : int(1..11)]), - and([q6 <= var2_ExplicitVarSizeWithMarker_Marker -> var2_Occurrence[var2_ExplicitVarSizeWithMarker_Values[q6]] - | q6 : int(1..11)]), - and([var2_Occurrence[q7] -> - or([q9 <= var2_ExplicitVarSizeWithMarker_Marker /\ var2_ExplicitVarSizeWithMarker_Values[q9] = q7 - | q9 : int(1..11)]) - | q7 : int(-4..5, 2)]) - diff --git a/tests/exhaustive/autogen/gen32/expected/model_1_3_2.eprime b/tests/exhaustive/autogen/gen32/expected/model_1_3_2.eprime deleted file mode 100644 index 8612434ed5..0000000000 --- a/tests/exhaustive/autogen/gen32/expected/model_1_3_2.eprime +++ /dev/null @@ -1,49 +0,0 @@ -language ESSENCE' 1.0 - -letting let1 be -4 -find var2_Occurrence: matrix indexed by [int(-4..5, 2)] of bool -find var2_ExplicitVarSizeWithMarker_Marker: int(0..11) -find var2_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..11)] of int(-4..5, 2) -find var2_ExplicitVarSizeWithDummy: matrix indexed by [int(1..11)] of int(-4..5, 2, 6) -branching on - [var2_ExplicitVarSizeWithDummy, var2_Occurrence, var2_ExplicitVarSizeWithMarker_Marker, - var2_ExplicitVarSizeWithMarker_Values] -such that - or([var2_Occurrence[q27] /\ - !or([q29 <= var2_ExplicitVarSizeWithMarker_Marker /\ var2_ExplicitVarSizeWithMarker_Values[q29] = q27 - | q29 : int(1..11)]) - | q27 : int(-4..5, 2)]) - \/ - or([q30 <= var2_ExplicitVarSizeWithMarker_Marker /\ !var2_Occurrence[var2_ExplicitVarSizeWithMarker_Values[q30]] - | q30 : int(1..11)]), - and([q2 + 1 <= var2_ExplicitVarSizeWithMarker_Marker -> - var2_ExplicitVarSizeWithMarker_Values[q2] < var2_ExplicitVarSizeWithMarker_Values[q2 + 1] - | q2 : int(1..10)]), - and([q3 > var2_ExplicitVarSizeWithMarker_Marker -> var2_ExplicitVarSizeWithMarker_Values[q3] = -4 - | q3 : int(1..11)]), - and([q6 <= var2_ExplicitVarSizeWithMarker_Marker -> var2_Occurrence[var2_ExplicitVarSizeWithMarker_Values[q6]] - | q6 : int(1..11)]), - and([var2_Occurrence[q7] -> - or([q9 <= var2_ExplicitVarSizeWithMarker_Marker /\ var2_ExplicitVarSizeWithMarker_Values[q9] = q7 - | q9 : int(1..11)]) - | q7 : int(-4..5, 2)]), - and([var2_ExplicitVarSizeWithDummy[q10] < var2_ExplicitVarSizeWithDummy[q10 + 1] \/ - var2_ExplicitVarSizeWithDummy[q10] = 6 - | q10 : int(1..10)]), - and([var2_ExplicitVarSizeWithDummy[q11] = 6 -> var2_ExplicitVarSizeWithDummy[q11 + 1] = 6 | q11 : int(1..10)]), - and([var2_ExplicitVarSizeWithDummy[q15] != 6 -> var2_Occurrence[var2_ExplicitVarSizeWithDummy[q15]] - | q15 : int(1..11)]), - and([var2_Occurrence[q16] -> - or([var2_ExplicitVarSizeWithDummy[q18] != 6 /\ var2_ExplicitVarSizeWithDummy[q18] = q16 | q18 : int(1..11)]) - | q16 : int(-4..5, 2)]), - and([var2_ExplicitVarSizeWithDummy[q20] != 6 -> - or([q22 <= var2_ExplicitVarSizeWithMarker_Marker /\ - var2_ExplicitVarSizeWithMarker_Values[q22] = var2_ExplicitVarSizeWithDummy[q20] - | q22 : int(1..11)]) - | q20 : int(1..11)]), - and([q24 <= var2_ExplicitVarSizeWithMarker_Marker -> - or([var2_ExplicitVarSizeWithDummy[q26] != 6 /\ - var2_ExplicitVarSizeWithDummy[q26] = var2_ExplicitVarSizeWithMarker_Values[q24] - | q26 : int(1..11)]) - | q24 : int(1..11)]) - diff --git a/tests/exhaustive/autogen/gen32/expected/model_1_3_3.eprime b/tests/exhaustive/autogen/gen32/expected/model_1_3_3.eprime deleted file mode 100644 index f4bcfbc82e..0000000000 --- a/tests/exhaustive/autogen/gen32/expected/model_1_3_3.eprime +++ /dev/null @@ -1,27 +0,0 @@ -language ESSENCE' 1.0 - -letting let1 be -4 -find var2_Occurrence: matrix indexed by [int(-4..5, 2)] of bool -find var2_ExplicitVarSizeWithMarker_Marker: int(0..11) -find var2_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..11)] of int(-4..5, 2) -branching on [var2_ExplicitVarSizeWithMarker_Marker, var2_ExplicitVarSizeWithMarker_Values, var2_Occurrence] -such that - or([var2_Occurrence[q10] /\ - !or([q12 <= var2_ExplicitVarSizeWithMarker_Marker /\ var2_ExplicitVarSizeWithMarker_Values[q12] = q10 - | q12 : int(1..11)]) - | q10 : int(-4..5, 2)]) - \/ - or([q13 <= var2_ExplicitVarSizeWithMarker_Marker /\ !var2_Occurrence[var2_ExplicitVarSizeWithMarker_Values[q13]] - | q13 : int(1..11)]), - and([q2 + 1 <= var2_ExplicitVarSizeWithMarker_Marker -> - var2_ExplicitVarSizeWithMarker_Values[q2] < var2_ExplicitVarSizeWithMarker_Values[q2 + 1] - | q2 : int(1..10)]), - and([q3 > var2_ExplicitVarSizeWithMarker_Marker -> var2_ExplicitVarSizeWithMarker_Values[q3] = -4 - | q3 : int(1..11)]), - and([q6 <= var2_ExplicitVarSizeWithMarker_Marker -> var2_Occurrence[var2_ExplicitVarSizeWithMarker_Values[q6]] - | q6 : int(1..11)]), - and([var2_Occurrence[q7] -> - or([q9 <= var2_ExplicitVarSizeWithMarker_Marker /\ var2_ExplicitVarSizeWithMarker_Values[q9] = q7 - | q9 : int(1..11)]) - | q7 : int(-4..5, 2)]) - diff --git a/tests/exhaustive/autogen/gen32/expected/model_1_3_4.eprime b/tests/exhaustive/autogen/gen32/expected/model_1_3_4.eprime deleted file mode 100644 index ef83393629..0000000000 --- a/tests/exhaustive/autogen/gen32/expected/model_1_3_4.eprime +++ /dev/null @@ -1,53 +0,0 @@ -language ESSENCE' 1.0 - -letting let1 be -4 -find var2_Occurrence: matrix indexed by [int(-4..5, 2)] of bool -find var2_ExplicitVarSizeWithMarker_Marker: int(0..11) -find var2_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..11)] of int(-4..5, 2) -find var2_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..11)] of bool -find var2_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..11)] of int(-4..5, 2) -branching on - [var2_ExplicitVarSizeWithFlags_Flags, var2_ExplicitVarSizeWithFlags_Values, var2_Occurrence, - var2_ExplicitVarSizeWithMarker_Marker, var2_ExplicitVarSizeWithMarker_Values] -such that - or([var2_Occurrence[q28] /\ - !or([q30 <= var2_ExplicitVarSizeWithMarker_Marker /\ var2_ExplicitVarSizeWithMarker_Values[q30] = q28 - | q30 : int(1..11)]) - | q28 : int(-4..5, 2)]) - \/ - or([q31 <= var2_ExplicitVarSizeWithMarker_Marker /\ !var2_Occurrence[var2_ExplicitVarSizeWithMarker_Values[q31]] - | q31 : int(1..11)]), - and([q2 + 1 <= var2_ExplicitVarSizeWithMarker_Marker -> - var2_ExplicitVarSizeWithMarker_Values[q2] < var2_ExplicitVarSizeWithMarker_Values[q2 + 1] - | q2 : int(1..10)]), - and([q3 > var2_ExplicitVarSizeWithMarker_Marker -> var2_ExplicitVarSizeWithMarker_Values[q3] = -4 - | q3 : int(1..11)]), - and([q6 <= var2_ExplicitVarSizeWithMarker_Marker -> var2_Occurrence[var2_ExplicitVarSizeWithMarker_Values[q6]] - | q6 : int(1..11)]), - and([var2_Occurrence[q7] -> - or([q9 <= var2_ExplicitVarSizeWithMarker_Marker /\ var2_ExplicitVarSizeWithMarker_Values[q9] = q7 - | q9 : int(1..11)]) - | q7 : int(-4..5, 2)]), - and([var2_ExplicitVarSizeWithFlags_Flags[q10 + 1] -> - var2_ExplicitVarSizeWithFlags_Values[q10] < var2_ExplicitVarSizeWithFlags_Values[q10 + 1] - | q10 : int(1..10)]), - and([var2_ExplicitVarSizeWithFlags_Flags[q11] = false -> var2_ExplicitVarSizeWithFlags_Values[q11] = -4 - | q11 : int(1..11)]), - and([var2_ExplicitVarSizeWithFlags_Flags[q12 + 1] -> var2_ExplicitVarSizeWithFlags_Flags[q12] | q12 : int(1..10)]), - and([var2_ExplicitVarSizeWithFlags_Flags[q16] -> var2_Occurrence[var2_ExplicitVarSizeWithFlags_Values[q16]] - | q16 : int(1..11)]), - and([var2_Occurrence[q17] -> - or([var2_ExplicitVarSizeWithFlags_Flags[q19] /\ var2_ExplicitVarSizeWithFlags_Values[q19] = q17 - | q19 : int(1..11)]) - | q17 : int(-4..5, 2)]), - and([var2_ExplicitVarSizeWithFlags_Flags[q21] -> - or([q23 <= var2_ExplicitVarSizeWithMarker_Marker /\ - var2_ExplicitVarSizeWithMarker_Values[q23] = var2_ExplicitVarSizeWithFlags_Values[q21] - | q23 : int(1..11)]) - | q21 : int(1..11)]), - and([q25 <= var2_ExplicitVarSizeWithMarker_Marker -> - or([var2_ExplicitVarSizeWithFlags_Flags[q27] /\ - var2_ExplicitVarSizeWithFlags_Values[q27] = var2_ExplicitVarSizeWithMarker_Values[q25] - | q27 : int(1..11)]) - | q25 : int(1..11)]) - diff --git a/tests/exhaustive/autogen/gen32/expected/model_1_4_1.eprime b/tests/exhaustive/autogen/gen32/expected/model_1_4_1.eprime deleted file mode 100644 index ac3a2f9711..0000000000 --- a/tests/exhaustive/autogen/gen32/expected/model_1_4_1.eprime +++ /dev/null @@ -1,28 +0,0 @@ -language ESSENCE' 1.0 - -letting let1 be -4 -find var2_Occurrence: matrix indexed by [int(-4..5, 2)] of bool -find var2_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..11)] of bool -find var2_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..11)] of int(-4..5, 2) -branching on [var2_ExplicitVarSizeWithFlags_Flags, var2_ExplicitVarSizeWithFlags_Values, var2_Occurrence] -such that - or([var2_Occurrence[q12] /\ - !or([var2_ExplicitVarSizeWithFlags_Flags[q14] /\ var2_ExplicitVarSizeWithFlags_Values[q14] = q12 - | q14 : int(1..11)]) - | q12 : int(-4..5, 2)]) - \/ - or([var2_ExplicitVarSizeWithFlags_Flags[q15] /\ !var2_Occurrence[var2_ExplicitVarSizeWithFlags_Values[q15]] - | q15 : int(1..11)]), - and([var2_ExplicitVarSizeWithFlags_Flags[q2 + 1] -> - var2_ExplicitVarSizeWithFlags_Values[q2] < var2_ExplicitVarSizeWithFlags_Values[q2 + 1] - | q2 : int(1..10)]), - and([var2_ExplicitVarSizeWithFlags_Flags[q3] = false -> var2_ExplicitVarSizeWithFlags_Values[q3] = -4 - | q3 : int(1..11)]), - and([var2_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> var2_ExplicitVarSizeWithFlags_Flags[q4] | q4 : int(1..10)]), - and([var2_ExplicitVarSizeWithFlags_Flags[q8] -> var2_Occurrence[var2_ExplicitVarSizeWithFlags_Values[q8]] - | q8 : int(1..11)]), - and([var2_Occurrence[q9] -> - or([var2_ExplicitVarSizeWithFlags_Flags[q11] /\ var2_ExplicitVarSizeWithFlags_Values[q11] = q9 - | q11 : int(1..11)]) - | q9 : int(-4..5, 2)]) - diff --git a/tests/exhaustive/autogen/gen32/expected/model_1_4_2.eprime b/tests/exhaustive/autogen/gen32/expected/model_1_4_2.eprime deleted file mode 100644 index ff6e8bf8e4..0000000000 --- a/tests/exhaustive/autogen/gen32/expected/model_1_4_2.eprime +++ /dev/null @@ -1,50 +0,0 @@ -language ESSENCE' 1.0 - -letting let1 be -4 -find var2_Occurrence: matrix indexed by [int(-4..5, 2)] of bool -find var2_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..11)] of bool -find var2_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..11)] of int(-4..5, 2) -find var2_ExplicitVarSizeWithDummy: matrix indexed by [int(1..11)] of int(-4..5, 2, 6) -branching on - [var2_ExplicitVarSizeWithDummy, var2_Occurrence, var2_ExplicitVarSizeWithFlags_Flags, - var2_ExplicitVarSizeWithFlags_Values] -such that - or([var2_Occurrence[q29] /\ - !or([var2_ExplicitVarSizeWithFlags_Flags[q31] /\ var2_ExplicitVarSizeWithFlags_Values[q31] = q29 - | q31 : int(1..11)]) - | q29 : int(-4..5, 2)]) - \/ - or([var2_ExplicitVarSizeWithFlags_Flags[q32] /\ !var2_Occurrence[var2_ExplicitVarSizeWithFlags_Values[q32]] - | q32 : int(1..11)]), - and([var2_ExplicitVarSizeWithFlags_Flags[q2 + 1] -> - var2_ExplicitVarSizeWithFlags_Values[q2] < var2_ExplicitVarSizeWithFlags_Values[q2 + 1] - | q2 : int(1..10)]), - and([var2_ExplicitVarSizeWithFlags_Flags[q3] = false -> var2_ExplicitVarSizeWithFlags_Values[q3] = -4 - | q3 : int(1..11)]), - and([var2_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> var2_ExplicitVarSizeWithFlags_Flags[q4] | q4 : int(1..10)]), - and([var2_ExplicitVarSizeWithFlags_Flags[q8] -> var2_Occurrence[var2_ExplicitVarSizeWithFlags_Values[q8]] - | q8 : int(1..11)]), - and([var2_Occurrence[q9] -> - or([var2_ExplicitVarSizeWithFlags_Flags[q11] /\ var2_ExplicitVarSizeWithFlags_Values[q11] = q9 - | q11 : int(1..11)]) - | q9 : int(-4..5, 2)]), - and([var2_ExplicitVarSizeWithDummy[q12] < var2_ExplicitVarSizeWithDummy[q12 + 1] \/ - var2_ExplicitVarSizeWithDummy[q12] = 6 - | q12 : int(1..10)]), - and([var2_ExplicitVarSizeWithDummy[q13] = 6 -> var2_ExplicitVarSizeWithDummy[q13 + 1] = 6 | q13 : int(1..10)]), - and([var2_ExplicitVarSizeWithDummy[q17] != 6 -> var2_Occurrence[var2_ExplicitVarSizeWithDummy[q17]] - | q17 : int(1..11)]), - and([var2_Occurrence[q18] -> - or([var2_ExplicitVarSizeWithDummy[q20] != 6 /\ var2_ExplicitVarSizeWithDummy[q20] = q18 | q20 : int(1..11)]) - | q18 : int(-4..5, 2)]), - and([var2_ExplicitVarSizeWithDummy[q22] != 6 -> - or([var2_ExplicitVarSizeWithFlags_Flags[q24] /\ - var2_ExplicitVarSizeWithFlags_Values[q24] = var2_ExplicitVarSizeWithDummy[q22] - | q24 : int(1..11)]) - | q22 : int(1..11)]), - and([var2_ExplicitVarSizeWithFlags_Flags[q26] -> - or([var2_ExplicitVarSizeWithDummy[q28] != 6 /\ - var2_ExplicitVarSizeWithDummy[q28] = var2_ExplicitVarSizeWithFlags_Values[q26] - | q28 : int(1..11)]) - | q26 : int(1..11)]) - diff --git a/tests/exhaustive/autogen/gen32/expected/model_1_4_3.eprime b/tests/exhaustive/autogen/gen32/expected/model_1_4_3.eprime deleted file mode 100644 index 74db93bcc4..0000000000 --- a/tests/exhaustive/autogen/gen32/expected/model_1_4_3.eprime +++ /dev/null @@ -1,53 +0,0 @@ -language ESSENCE' 1.0 - -letting let1 be -4 -find var2_Occurrence: matrix indexed by [int(-4..5, 2)] of bool -find var2_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..11)] of bool -find var2_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..11)] of int(-4..5, 2) -find var2_ExplicitVarSizeWithMarker_Marker: int(0..11) -find var2_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..11)] of int(-4..5, 2) -branching on - [var2_ExplicitVarSizeWithMarker_Marker, var2_ExplicitVarSizeWithMarker_Values, var2_Occurrence, - var2_ExplicitVarSizeWithFlags_Flags, var2_ExplicitVarSizeWithFlags_Values] -such that - or([var2_Occurrence[q28] /\ - !or([var2_ExplicitVarSizeWithFlags_Flags[q30] /\ var2_ExplicitVarSizeWithFlags_Values[q30] = q28 - | q30 : int(1..11)]) - | q28 : int(-4..5, 2)]) - \/ - or([var2_ExplicitVarSizeWithFlags_Flags[q31] /\ !var2_Occurrence[var2_ExplicitVarSizeWithFlags_Values[q31]] - | q31 : int(1..11)]), - and([var2_ExplicitVarSizeWithFlags_Flags[q2 + 1] -> - var2_ExplicitVarSizeWithFlags_Values[q2] < var2_ExplicitVarSizeWithFlags_Values[q2 + 1] - | q2 : int(1..10)]), - and([var2_ExplicitVarSizeWithFlags_Flags[q3] = false -> var2_ExplicitVarSizeWithFlags_Values[q3] = -4 - | q3 : int(1..11)]), - and([var2_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> var2_ExplicitVarSizeWithFlags_Flags[q4] | q4 : int(1..10)]), - and([var2_ExplicitVarSizeWithFlags_Flags[q8] -> var2_Occurrence[var2_ExplicitVarSizeWithFlags_Values[q8]] - | q8 : int(1..11)]), - and([var2_Occurrence[q9] -> - or([var2_ExplicitVarSizeWithFlags_Flags[q11] /\ var2_ExplicitVarSizeWithFlags_Values[q11] = q9 - | q11 : int(1..11)]) - | q9 : int(-4..5, 2)]), - and([q12 + 1 <= var2_ExplicitVarSizeWithMarker_Marker -> - var2_ExplicitVarSizeWithMarker_Values[q12] < var2_ExplicitVarSizeWithMarker_Values[q12 + 1] - | q12 : int(1..10)]), - and([q13 > var2_ExplicitVarSizeWithMarker_Marker -> var2_ExplicitVarSizeWithMarker_Values[q13] = -4 - | q13 : int(1..11)]), - and([q16 <= var2_ExplicitVarSizeWithMarker_Marker -> var2_Occurrence[var2_ExplicitVarSizeWithMarker_Values[q16]] - | q16 : int(1..11)]), - and([var2_Occurrence[q17] -> - or([q19 <= var2_ExplicitVarSizeWithMarker_Marker /\ var2_ExplicitVarSizeWithMarker_Values[q19] = q17 - | q19 : int(1..11)]) - | q17 : int(-4..5, 2)]), - and([q21 <= var2_ExplicitVarSizeWithMarker_Marker -> - or([var2_ExplicitVarSizeWithFlags_Flags[q23] /\ - var2_ExplicitVarSizeWithFlags_Values[q23] = var2_ExplicitVarSizeWithMarker_Values[q21] - | q23 : int(1..11)]) - | q21 : int(1..11)]), - and([var2_ExplicitVarSizeWithFlags_Flags[q25] -> - or([q27 <= var2_ExplicitVarSizeWithMarker_Marker /\ - var2_ExplicitVarSizeWithMarker_Values[q27] = var2_ExplicitVarSizeWithFlags_Values[q25] - | q27 : int(1..11)]) - | q25 : int(1..11)]) - diff --git a/tests/exhaustive/autogen/gen32/expected/model_1_4_4.eprime b/tests/exhaustive/autogen/gen32/expected/model_1_4_4.eprime deleted file mode 100644 index ac3a2f9711..0000000000 --- a/tests/exhaustive/autogen/gen32/expected/model_1_4_4.eprime +++ /dev/null @@ -1,28 +0,0 @@ -language ESSENCE' 1.0 - -letting let1 be -4 -find var2_Occurrence: matrix indexed by [int(-4..5, 2)] of bool -find var2_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..11)] of bool -find var2_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..11)] of int(-4..5, 2) -branching on [var2_ExplicitVarSizeWithFlags_Flags, var2_ExplicitVarSizeWithFlags_Values, var2_Occurrence] -such that - or([var2_Occurrence[q12] /\ - !or([var2_ExplicitVarSizeWithFlags_Flags[q14] /\ var2_ExplicitVarSizeWithFlags_Values[q14] = q12 - | q14 : int(1..11)]) - | q12 : int(-4..5, 2)]) - \/ - or([var2_ExplicitVarSizeWithFlags_Flags[q15] /\ !var2_Occurrence[var2_ExplicitVarSizeWithFlags_Values[q15]] - | q15 : int(1..11)]), - and([var2_ExplicitVarSizeWithFlags_Flags[q2 + 1] -> - var2_ExplicitVarSizeWithFlags_Values[q2] < var2_ExplicitVarSizeWithFlags_Values[q2 + 1] - | q2 : int(1..10)]), - and([var2_ExplicitVarSizeWithFlags_Flags[q3] = false -> var2_ExplicitVarSizeWithFlags_Values[q3] = -4 - | q3 : int(1..11)]), - and([var2_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> var2_ExplicitVarSizeWithFlags_Flags[q4] | q4 : int(1..10)]), - and([var2_ExplicitVarSizeWithFlags_Flags[q8] -> var2_Occurrence[var2_ExplicitVarSizeWithFlags_Values[q8]] - | q8 : int(1..11)]), - and([var2_Occurrence[q9] -> - or([var2_ExplicitVarSizeWithFlags_Flags[q11] /\ var2_ExplicitVarSizeWithFlags_Values[q11] = q9 - | q11 : int(1..11)]) - | q9 : int(-4..5, 2)]) - diff --git a/tests/exhaustive/autogen/gen32/expected/model_2_1_1.eprime b/tests/exhaustive/autogen/gen32/expected/model_2_1_1.eprime deleted file mode 100644 index cc87135b8c..0000000000 --- a/tests/exhaustive/autogen/gen32/expected/model_2_1_1.eprime +++ /dev/null @@ -1,23 +0,0 @@ -language ESSENCE' 1.0 - -letting let1 be -4 -find var2_ExplicitVarSizeWithDummy: matrix indexed by [int(1..11)] of int(-4..5, 2, 6) -find var2_Occurrence: matrix indexed by [int(-4..5, 2)] of bool -branching on [var2_Occurrence, var2_ExplicitVarSizeWithDummy] -such that - or([var2_ExplicitVarSizeWithDummy[q7] != 6 /\ !var2_Occurrence[var2_ExplicitVarSizeWithDummy[q7]] - | q7 : int(1..11)]) - \/ - or([var2_Occurrence[q6] /\ - !or([var2_ExplicitVarSizeWithDummy[q9] != 6 /\ var2_ExplicitVarSizeWithDummy[q9] = q6 | q9 : int(1..11)]) - | q6 : int(-4..5, 2)]), - and([var2_ExplicitVarSizeWithDummy[q1] < var2_ExplicitVarSizeWithDummy[q1 + 1] \/ - var2_ExplicitVarSizeWithDummy[q1] = 6 - | q1 : int(1..10)]), - and([var2_ExplicitVarSizeWithDummy[q2] = 6 -> var2_ExplicitVarSizeWithDummy[q2 + 1] = 6 | q2 : int(1..10)]), - and([var2_Occurrence[q10] -> - or([var2_ExplicitVarSizeWithDummy[q12] != 6 /\ var2_ExplicitVarSizeWithDummy[q12] = q10 | q12 : int(1..11)]) - | q10 : int(-4..5, 2)]), - and([var2_ExplicitVarSizeWithDummy[q14] != 6 -> var2_Occurrence[var2_ExplicitVarSizeWithDummy[q14]] - | q14 : int(1..11)]) - diff --git a/tests/exhaustive/autogen/gen32/expected/model_2_1_2.eprime b/tests/exhaustive/autogen/gen32/expected/model_2_1_2.eprime deleted file mode 100644 index cc87135b8c..0000000000 --- a/tests/exhaustive/autogen/gen32/expected/model_2_1_2.eprime +++ /dev/null @@ -1,23 +0,0 @@ -language ESSENCE' 1.0 - -letting let1 be -4 -find var2_ExplicitVarSizeWithDummy: matrix indexed by [int(1..11)] of int(-4..5, 2, 6) -find var2_Occurrence: matrix indexed by [int(-4..5, 2)] of bool -branching on [var2_Occurrence, var2_ExplicitVarSizeWithDummy] -such that - or([var2_ExplicitVarSizeWithDummy[q7] != 6 /\ !var2_Occurrence[var2_ExplicitVarSizeWithDummy[q7]] - | q7 : int(1..11)]) - \/ - or([var2_Occurrence[q6] /\ - !or([var2_ExplicitVarSizeWithDummy[q9] != 6 /\ var2_ExplicitVarSizeWithDummy[q9] = q6 | q9 : int(1..11)]) - | q6 : int(-4..5, 2)]), - and([var2_ExplicitVarSizeWithDummy[q1] < var2_ExplicitVarSizeWithDummy[q1 + 1] \/ - var2_ExplicitVarSizeWithDummy[q1] = 6 - | q1 : int(1..10)]), - and([var2_ExplicitVarSizeWithDummy[q2] = 6 -> var2_ExplicitVarSizeWithDummy[q2 + 1] = 6 | q2 : int(1..10)]), - and([var2_Occurrence[q10] -> - or([var2_ExplicitVarSizeWithDummy[q12] != 6 /\ var2_ExplicitVarSizeWithDummy[q12] = q10 | q12 : int(1..11)]) - | q10 : int(-4..5, 2)]), - and([var2_ExplicitVarSizeWithDummy[q14] != 6 -> var2_Occurrence[var2_ExplicitVarSizeWithDummy[q14]] - | q14 : int(1..11)]) - diff --git a/tests/exhaustive/autogen/gen32/expected/model_2_1_3.eprime b/tests/exhaustive/autogen/gen32/expected/model_2_1_3.eprime deleted file mode 100644 index ff7949c852..0000000000 --- a/tests/exhaustive/autogen/gen32/expected/model_2_1_3.eprime +++ /dev/null @@ -1,48 +0,0 @@ -language ESSENCE' 1.0 - -letting let1 be -4 -find var2_ExplicitVarSizeWithDummy: matrix indexed by [int(1..11)] of int(-4..5, 2, 6) -find var2_Occurrence: matrix indexed by [int(-4..5, 2)] of bool -find var2_ExplicitVarSizeWithMarker_Marker: int(0..11) -find var2_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..11)] of int(-4..5, 2) -branching on - [var2_ExplicitVarSizeWithMarker_Marker, var2_ExplicitVarSizeWithMarker_Values, var2_ExplicitVarSizeWithDummy, - var2_Occurrence] -such that - or([var2_ExplicitVarSizeWithDummy[q23] != 6 /\ !var2_Occurrence[var2_ExplicitVarSizeWithDummy[q23]] - | q23 : int(1..11)]) - \/ - or([var2_Occurrence[q22] /\ - !or([var2_ExplicitVarSizeWithDummy[q25] != 6 /\ var2_ExplicitVarSizeWithDummy[q25] = q22 | q25 : int(1..11)]) - | q22 : int(-4..5, 2)]), - and([var2_ExplicitVarSizeWithDummy[q1] < var2_ExplicitVarSizeWithDummy[q1 + 1] \/ - var2_ExplicitVarSizeWithDummy[q1] = 6 - | q1 : int(1..10)]), - and([var2_ExplicitVarSizeWithDummy[q2] = 6 -> var2_ExplicitVarSizeWithDummy[q2 + 1] = 6 | q2 : int(1..10)]), - and([var2_Occurrence[q26] -> - or([var2_ExplicitVarSizeWithDummy[q28] != 6 /\ var2_ExplicitVarSizeWithDummy[q28] = q26 | q28 : int(1..11)]) - | q26 : int(-4..5, 2)]), - and([var2_ExplicitVarSizeWithDummy[q30] != 6 -> var2_Occurrence[var2_ExplicitVarSizeWithDummy[q30]] - | q30 : int(1..11)]), - and([q6 + 1 <= var2_ExplicitVarSizeWithMarker_Marker -> - var2_ExplicitVarSizeWithMarker_Values[q6] < var2_ExplicitVarSizeWithMarker_Values[q6 + 1] - | q6 : int(1..10)]), - and([q7 > var2_ExplicitVarSizeWithMarker_Marker -> var2_ExplicitVarSizeWithMarker_Values[q7] = -4 - | q7 : int(1..11)]), - and([q10 <= var2_ExplicitVarSizeWithMarker_Marker -> - or([var2_ExplicitVarSizeWithDummy[q12] != 6 /\ - var2_ExplicitVarSizeWithDummy[q12] = var2_ExplicitVarSizeWithMarker_Values[q10] - | q12 : int(1..11)]) - | q10 : int(1..11)]), - and([var2_ExplicitVarSizeWithDummy[q14] != 6 -> - or([q16 <= var2_ExplicitVarSizeWithMarker_Marker /\ - var2_ExplicitVarSizeWithMarker_Values[q16] = var2_ExplicitVarSizeWithDummy[q14] - | q16 : int(1..11)]) - | q14 : int(1..11)]), - and([q18 <= var2_ExplicitVarSizeWithMarker_Marker -> var2_Occurrence[var2_ExplicitVarSizeWithMarker_Values[q18]] - | q18 : int(1..11)]), - and([var2_Occurrence[q19] -> - or([q21 <= var2_ExplicitVarSizeWithMarker_Marker /\ var2_ExplicitVarSizeWithMarker_Values[q21] = q19 - | q21 : int(1..11)]) - | q19 : int(-4..5, 2)]) - diff --git a/tests/exhaustive/autogen/gen32/expected/model_2_1_4.eprime b/tests/exhaustive/autogen/gen32/expected/model_2_1_4.eprime deleted file mode 100644 index 39bbf550cc..0000000000 --- a/tests/exhaustive/autogen/gen32/expected/model_2_1_4.eprime +++ /dev/null @@ -1,49 +0,0 @@ -language ESSENCE' 1.0 - -letting let1 be -4 -find var2_ExplicitVarSizeWithDummy: matrix indexed by [int(1..11)] of int(-4..5, 2, 6) -find var2_Occurrence: matrix indexed by [int(-4..5, 2)] of bool -find var2_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..11)] of bool -find var2_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..11)] of int(-4..5, 2) -branching on - [var2_ExplicitVarSizeWithFlags_Flags, var2_ExplicitVarSizeWithFlags_Values, var2_ExplicitVarSizeWithDummy, - var2_Occurrence] -such that - or([var2_ExplicitVarSizeWithDummy[q25] != 6 /\ !var2_Occurrence[var2_ExplicitVarSizeWithDummy[q25]] - | q25 : int(1..11)]) - \/ - or([var2_Occurrence[q24] /\ - !or([var2_ExplicitVarSizeWithDummy[q27] != 6 /\ var2_ExplicitVarSizeWithDummy[q27] = q24 | q27 : int(1..11)]) - | q24 : int(-4..5, 2)]), - and([var2_ExplicitVarSizeWithDummy[q1] < var2_ExplicitVarSizeWithDummy[q1 + 1] \/ - var2_ExplicitVarSizeWithDummy[q1] = 6 - | q1 : int(1..10)]), - and([var2_ExplicitVarSizeWithDummy[q2] = 6 -> var2_ExplicitVarSizeWithDummy[q2 + 1] = 6 | q2 : int(1..10)]), - and([var2_Occurrence[q28] -> - or([var2_ExplicitVarSizeWithDummy[q30] != 6 /\ var2_ExplicitVarSizeWithDummy[q30] = q28 | q30 : int(1..11)]) - | q28 : int(-4..5, 2)]), - and([var2_ExplicitVarSizeWithDummy[q32] != 6 -> var2_Occurrence[var2_ExplicitVarSizeWithDummy[q32]] - | q32 : int(1..11)]), - and([var2_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> - var2_ExplicitVarSizeWithFlags_Values[q6] < var2_ExplicitVarSizeWithFlags_Values[q6 + 1] - | q6 : int(1..10)]), - and([var2_ExplicitVarSizeWithFlags_Flags[q7] = false -> var2_ExplicitVarSizeWithFlags_Values[q7] = -4 - | q7 : int(1..11)]), - and([var2_ExplicitVarSizeWithFlags_Flags[q8 + 1] -> var2_ExplicitVarSizeWithFlags_Flags[q8] | q8 : int(1..10)]), - and([var2_ExplicitVarSizeWithFlags_Flags[q12] -> - or([var2_ExplicitVarSizeWithDummy[q14] != 6 /\ - var2_ExplicitVarSizeWithDummy[q14] = var2_ExplicitVarSizeWithFlags_Values[q12] - | q14 : int(1..11)]) - | q12 : int(1..11)]), - and([var2_ExplicitVarSizeWithDummy[q16] != 6 -> - or([var2_ExplicitVarSizeWithFlags_Flags[q18] /\ - var2_ExplicitVarSizeWithFlags_Values[q18] = var2_ExplicitVarSizeWithDummy[q16] - | q18 : int(1..11)]) - | q16 : int(1..11)]), - and([var2_ExplicitVarSizeWithFlags_Flags[q20] -> var2_Occurrence[var2_ExplicitVarSizeWithFlags_Values[q20]] - | q20 : int(1..11)]), - and([var2_Occurrence[q21] -> - or([var2_ExplicitVarSizeWithFlags_Flags[q23] /\ var2_ExplicitVarSizeWithFlags_Values[q23] = q21 - | q23 : int(1..11)]) - | q21 : int(-4..5, 2)]) - diff --git a/tests/exhaustive/autogen/gen32/expected/model_2_2_1.eprime b/tests/exhaustive/autogen/gen32/expected/model_2_2_1.eprime deleted file mode 100644 index c131688486..0000000000 --- a/tests/exhaustive/autogen/gen32/expected/model_2_2_1.eprime +++ /dev/null @@ -1,28 +0,0 @@ -language ESSENCE' 1.0 - -letting let1 be -4 -find var2_ExplicitVarSizeWithDummy: matrix indexed by [int(1..11)] of int(-4..5, 2, 6) -find var2_Occurrence: matrix indexed by [int(-4..5, 2)] of bool -branching on [var2_Occurrence, var2_ExplicitVarSizeWithDummy] -such that - or([var2_ExplicitVarSizeWithDummy[q7] != 6 /\ - !or([var2_ExplicitVarSizeWithDummy[q9] != 6 /\ - var2_ExplicitVarSizeWithDummy[q9] = var2_ExplicitVarSizeWithDummy[q7] - | q9 : int(1..11)]) - | q7 : int(1..11)]) - \/ - or([var2_ExplicitVarSizeWithDummy[q10] != 6 /\ - !or([var2_ExplicitVarSizeWithDummy[q12] != 6 /\ - var2_ExplicitVarSizeWithDummy[q12] = var2_ExplicitVarSizeWithDummy[q10] - | q12 : int(1..11)]) - | q10 : int(1..11)]), - and([var2_ExplicitVarSizeWithDummy[q1] < var2_ExplicitVarSizeWithDummy[q1 + 1] \/ - var2_ExplicitVarSizeWithDummy[q1] = 6 - | q1 : int(1..10)]), - and([var2_ExplicitVarSizeWithDummy[q2] = 6 -> var2_ExplicitVarSizeWithDummy[q2 + 1] = 6 | q2 : int(1..10)]), - and([var2_Occurrence[q13] -> - or([var2_ExplicitVarSizeWithDummy[q15] != 6 /\ var2_ExplicitVarSizeWithDummy[q15] = q13 | q15 : int(1..11)]) - | q13 : int(-4..5, 2)]), - and([var2_ExplicitVarSizeWithDummy[q17] != 6 -> var2_Occurrence[var2_ExplicitVarSizeWithDummy[q17]] - | q17 : int(1..11)]) - diff --git a/tests/exhaustive/autogen/gen32/expected/model_2_2_2.eprime b/tests/exhaustive/autogen/gen32/expected/model_2_2_2.eprime deleted file mode 100644 index c724673a10..0000000000 --- a/tests/exhaustive/autogen/gen32/expected/model_2_2_2.eprime +++ /dev/null @@ -1,22 +0,0 @@ -language ESSENCE' 1.0 - -letting let1 be -4 -find var2_ExplicitVarSizeWithDummy: matrix indexed by [int(1..11)] of int(-4..5, 2, 6) -branching on [var2_ExplicitVarSizeWithDummy] -such that - or([var2_ExplicitVarSizeWithDummy[q6] != 6 /\ - !or([var2_ExplicitVarSizeWithDummy[q8] != 6 /\ - var2_ExplicitVarSizeWithDummy[q8] = var2_ExplicitVarSizeWithDummy[q6] - | q8 : int(1..11)]) - | q6 : int(1..11)]) - \/ - or([var2_ExplicitVarSizeWithDummy[q9] != 6 /\ - !or([var2_ExplicitVarSizeWithDummy[q11] != 6 /\ - var2_ExplicitVarSizeWithDummy[q11] = var2_ExplicitVarSizeWithDummy[q9] - | q11 : int(1..11)]) - | q9 : int(1..11)]), - and([var2_ExplicitVarSizeWithDummy[q1] < var2_ExplicitVarSizeWithDummy[q1 + 1] \/ - var2_ExplicitVarSizeWithDummy[q1] = 6 - | q1 : int(1..10)]), - and([var2_ExplicitVarSizeWithDummy[q2] = 6 -> var2_ExplicitVarSizeWithDummy[q2 + 1] = 6 | q2 : int(1..10)]) - diff --git a/tests/exhaustive/autogen/gen32/expected/model_2_2_3.eprime b/tests/exhaustive/autogen/gen32/expected/model_2_2_3.eprime deleted file mode 100644 index a4c92861d6..0000000000 --- a/tests/exhaustive/autogen/gen32/expected/model_2_2_3.eprime +++ /dev/null @@ -1,40 +0,0 @@ -language ESSENCE' 1.0 - -letting let1 be -4 -find var2_ExplicitVarSizeWithDummy: matrix indexed by [int(1..11)] of int(-4..5, 2, 6) -find var2_ExplicitVarSizeWithMarker_Marker: int(0..11) -find var2_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..11)] of int(-4..5, 2) -branching on - [var2_ExplicitVarSizeWithMarker_Marker, var2_ExplicitVarSizeWithMarker_Values, var2_ExplicitVarSizeWithDummy] -such that - or([var2_ExplicitVarSizeWithDummy[q17] != 6 /\ - !or([var2_ExplicitVarSizeWithDummy[q19] != 6 /\ - var2_ExplicitVarSizeWithDummy[q19] = var2_ExplicitVarSizeWithDummy[q17] - | q19 : int(1..11)]) - | q17 : int(1..11)]) - \/ - or([var2_ExplicitVarSizeWithDummy[q20] != 6 /\ - !or([var2_ExplicitVarSizeWithDummy[q22] != 6 /\ - var2_ExplicitVarSizeWithDummy[q22] = var2_ExplicitVarSizeWithDummy[q20] - | q22 : int(1..11)]) - | q20 : int(1..11)]), - and([var2_ExplicitVarSizeWithDummy[q1] < var2_ExplicitVarSizeWithDummy[q1 + 1] \/ - var2_ExplicitVarSizeWithDummy[q1] = 6 - | q1 : int(1..10)]), - and([var2_ExplicitVarSizeWithDummy[q2] = 6 -> var2_ExplicitVarSizeWithDummy[q2 + 1] = 6 | q2 : int(1..10)]), - and([q5 + 1 <= var2_ExplicitVarSizeWithMarker_Marker -> - var2_ExplicitVarSizeWithMarker_Values[q5] < var2_ExplicitVarSizeWithMarker_Values[q5 + 1] - | q5 : int(1..10)]), - and([q6 > var2_ExplicitVarSizeWithMarker_Marker -> var2_ExplicitVarSizeWithMarker_Values[q6] = -4 - | q6 : int(1..11)]), - and([q9 <= var2_ExplicitVarSizeWithMarker_Marker -> - or([var2_ExplicitVarSizeWithDummy[q11] != 6 /\ - var2_ExplicitVarSizeWithDummy[q11] = var2_ExplicitVarSizeWithMarker_Values[q9] - | q11 : int(1..11)]) - | q9 : int(1..11)]), - and([var2_ExplicitVarSizeWithDummy[q13] != 6 -> - or([q15 <= var2_ExplicitVarSizeWithMarker_Marker /\ - var2_ExplicitVarSizeWithMarker_Values[q15] = var2_ExplicitVarSizeWithDummy[q13] - | q15 : int(1..11)]) - | q13 : int(1..11)]) - diff --git a/tests/exhaustive/autogen/gen32/expected/model_2_2_4.eprime b/tests/exhaustive/autogen/gen32/expected/model_2_2_4.eprime deleted file mode 100644 index 4b33c5a6af..0000000000 --- a/tests/exhaustive/autogen/gen32/expected/model_2_2_4.eprime +++ /dev/null @@ -1,40 +0,0 @@ -language ESSENCE' 1.0 - -letting let1 be -4 -find var2_ExplicitVarSizeWithDummy: matrix indexed by [int(1..11)] of int(-4..5, 2, 6) -find var2_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..11)] of bool -find var2_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..11)] of int(-4..5, 2) -branching on [var2_ExplicitVarSizeWithFlags_Flags, var2_ExplicitVarSizeWithFlags_Values, var2_ExplicitVarSizeWithDummy] -such that - or([var2_ExplicitVarSizeWithDummy[q19] != 6 /\ - !or([var2_ExplicitVarSizeWithDummy[q21] != 6 /\ - var2_ExplicitVarSizeWithDummy[q21] = var2_ExplicitVarSizeWithDummy[q19] - | q21 : int(1..11)]) - | q19 : int(1..11)]) - \/ - or([var2_ExplicitVarSizeWithDummy[q22] != 6 /\ - !or([var2_ExplicitVarSizeWithDummy[q24] != 6 /\ - var2_ExplicitVarSizeWithDummy[q24] = var2_ExplicitVarSizeWithDummy[q22] - | q24 : int(1..11)]) - | q22 : int(1..11)]), - and([var2_ExplicitVarSizeWithDummy[q1] < var2_ExplicitVarSizeWithDummy[q1 + 1] \/ - var2_ExplicitVarSizeWithDummy[q1] = 6 - | q1 : int(1..10)]), - and([var2_ExplicitVarSizeWithDummy[q2] = 6 -> var2_ExplicitVarSizeWithDummy[q2 + 1] = 6 | q2 : int(1..10)]), - and([var2_ExplicitVarSizeWithFlags_Flags[q5 + 1] -> - var2_ExplicitVarSizeWithFlags_Values[q5] < var2_ExplicitVarSizeWithFlags_Values[q5 + 1] - | q5 : int(1..10)]), - and([var2_ExplicitVarSizeWithFlags_Flags[q6] = false -> var2_ExplicitVarSizeWithFlags_Values[q6] = -4 - | q6 : int(1..11)]), - and([var2_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> var2_ExplicitVarSizeWithFlags_Flags[q7] | q7 : int(1..10)]), - and([var2_ExplicitVarSizeWithFlags_Flags[q11] -> - or([var2_ExplicitVarSizeWithDummy[q13] != 6 /\ - var2_ExplicitVarSizeWithDummy[q13] = var2_ExplicitVarSizeWithFlags_Values[q11] - | q13 : int(1..11)]) - | q11 : int(1..11)]), - and([var2_ExplicitVarSizeWithDummy[q15] != 6 -> - or([var2_ExplicitVarSizeWithFlags_Flags[q17] /\ - var2_ExplicitVarSizeWithFlags_Values[q17] = var2_ExplicitVarSizeWithDummy[q15] - | q17 : int(1..11)]) - | q15 : int(1..11)]) - diff --git a/tests/exhaustive/autogen/gen32/expected/model_2_3_1.eprime b/tests/exhaustive/autogen/gen32/expected/model_2_3_1.eprime deleted file mode 100644 index 9e87cee675..0000000000 --- a/tests/exhaustive/autogen/gen32/expected/model_2_3_1.eprime +++ /dev/null @@ -1,53 +0,0 @@ -language ESSENCE' 1.0 - -letting let1 be -4 -find var2_ExplicitVarSizeWithDummy: matrix indexed by [int(1..11)] of int(-4..5, 2, 6) -find var2_ExplicitVarSizeWithMarker_Marker: int(0..11) -find var2_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..11)] of int(-4..5, 2) -find var2_Occurrence: matrix indexed by [int(-4..5, 2)] of bool -branching on - [var2_Occurrence, var2_ExplicitVarSizeWithDummy, var2_ExplicitVarSizeWithMarker_Marker, - var2_ExplicitVarSizeWithMarker_Values] -such that - or([var2_ExplicitVarSizeWithDummy[q18] != 6 /\ - !or([q20 <= var2_ExplicitVarSizeWithMarker_Marker /\ - var2_ExplicitVarSizeWithMarker_Values[q20] = var2_ExplicitVarSizeWithDummy[q18] - | q20 : int(1..11)]) - | q18 : int(1..11)]) - \/ - or([q21 <= var2_ExplicitVarSizeWithMarker_Marker /\ - !or([var2_ExplicitVarSizeWithDummy[q23] != 6 /\ - var2_ExplicitVarSizeWithDummy[q23] = var2_ExplicitVarSizeWithMarker_Values[q21] - | q23 : int(1..11)]) - | q21 : int(1..11)]), - and([var2_ExplicitVarSizeWithDummy[q1] < var2_ExplicitVarSizeWithDummy[q1 + 1] \/ - var2_ExplicitVarSizeWithDummy[q1] = 6 - | q1 : int(1..10)]), - and([var2_ExplicitVarSizeWithDummy[q2] = 6 -> var2_ExplicitVarSizeWithDummy[q2 + 1] = 6 | q2 : int(1..10)]), - and([q5 + 1 <= var2_ExplicitVarSizeWithMarker_Marker -> - var2_ExplicitVarSizeWithMarker_Values[q5] < var2_ExplicitVarSizeWithMarker_Values[q5 + 1] - | q5 : int(1..10)]), - and([q6 > var2_ExplicitVarSizeWithMarker_Marker -> var2_ExplicitVarSizeWithMarker_Values[q6] = -4 - | q6 : int(1..11)]), - and([q9 <= var2_ExplicitVarSizeWithMarker_Marker -> - or([var2_ExplicitVarSizeWithDummy[q11] != 6 /\ - var2_ExplicitVarSizeWithDummy[q11] = var2_ExplicitVarSizeWithMarker_Values[q9] - | q11 : int(1..11)]) - | q9 : int(1..11)]), - and([var2_ExplicitVarSizeWithDummy[q13] != 6 -> - or([q15 <= var2_ExplicitVarSizeWithMarker_Marker /\ - var2_ExplicitVarSizeWithMarker_Values[q15] = var2_ExplicitVarSizeWithDummy[q13] - | q15 : int(1..11)]) - | q13 : int(1..11)]), - and([var2_Occurrence[q24] -> - or([var2_ExplicitVarSizeWithDummy[q26] != 6 /\ var2_ExplicitVarSizeWithDummy[q26] = q24 | q26 : int(1..11)]) - | q24 : int(-4..5, 2)]), - and([var2_ExplicitVarSizeWithDummy[q28] != 6 -> var2_Occurrence[var2_ExplicitVarSizeWithDummy[q28]] - | q28 : int(1..11)]), - and([var2_Occurrence[q29] -> - or([q31 <= var2_ExplicitVarSizeWithMarker_Marker /\ var2_ExplicitVarSizeWithMarker_Values[q31] = q29 - | q31 : int(1..11)]) - | q29 : int(-4..5, 2)]), - and([q33 <= var2_ExplicitVarSizeWithMarker_Marker -> var2_Occurrence[var2_ExplicitVarSizeWithMarker_Values[q33]] - | q33 : int(1..11)]) - diff --git a/tests/exhaustive/autogen/gen32/expected/model_2_3_2.eprime b/tests/exhaustive/autogen/gen32/expected/model_2_3_2.eprime deleted file mode 100644 index 9aea3cfc02..0000000000 --- a/tests/exhaustive/autogen/gen32/expected/model_2_3_2.eprime +++ /dev/null @@ -1,40 +0,0 @@ -language ESSENCE' 1.0 - -letting let1 be -4 -find var2_ExplicitVarSizeWithDummy: matrix indexed by [int(1..11)] of int(-4..5, 2, 6) -find var2_ExplicitVarSizeWithMarker_Marker: int(0..11) -find var2_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..11)] of int(-4..5, 2) -branching on - [var2_ExplicitVarSizeWithMarker_Marker, var2_ExplicitVarSizeWithMarker_Values, var2_ExplicitVarSizeWithDummy] -such that - or([var2_ExplicitVarSizeWithDummy[q17] != 6 /\ - !or([q19 <= var2_ExplicitVarSizeWithMarker_Marker /\ - var2_ExplicitVarSizeWithMarker_Values[q19] = var2_ExplicitVarSizeWithDummy[q17] - | q19 : int(1..11)]) - | q17 : int(1..11)]) - \/ - or([q20 <= var2_ExplicitVarSizeWithMarker_Marker /\ - !or([var2_ExplicitVarSizeWithDummy[q22] != 6 /\ - var2_ExplicitVarSizeWithDummy[q22] = var2_ExplicitVarSizeWithMarker_Values[q20] - | q22 : int(1..11)]) - | q20 : int(1..11)]), - and([var2_ExplicitVarSizeWithDummy[q1] < var2_ExplicitVarSizeWithDummy[q1 + 1] \/ - var2_ExplicitVarSizeWithDummy[q1] = 6 - | q1 : int(1..10)]), - and([var2_ExplicitVarSizeWithDummy[q2] = 6 -> var2_ExplicitVarSizeWithDummy[q2 + 1] = 6 | q2 : int(1..10)]), - and([q5 + 1 <= var2_ExplicitVarSizeWithMarker_Marker -> - var2_ExplicitVarSizeWithMarker_Values[q5] < var2_ExplicitVarSizeWithMarker_Values[q5 + 1] - | q5 : int(1..10)]), - and([q6 > var2_ExplicitVarSizeWithMarker_Marker -> var2_ExplicitVarSizeWithMarker_Values[q6] = -4 - | q6 : int(1..11)]), - and([q9 <= var2_ExplicitVarSizeWithMarker_Marker -> - or([var2_ExplicitVarSizeWithDummy[q11] != 6 /\ - var2_ExplicitVarSizeWithDummy[q11] = var2_ExplicitVarSizeWithMarker_Values[q9] - | q11 : int(1..11)]) - | q9 : int(1..11)]), - and([var2_ExplicitVarSizeWithDummy[q13] != 6 -> - or([q15 <= var2_ExplicitVarSizeWithMarker_Marker /\ - var2_ExplicitVarSizeWithMarker_Values[q15] = var2_ExplicitVarSizeWithDummy[q13] - | q15 : int(1..11)]) - | q13 : int(1..11)]) - diff --git a/tests/exhaustive/autogen/gen32/expected/model_2_3_3.eprime b/tests/exhaustive/autogen/gen32/expected/model_2_3_3.eprime deleted file mode 100644 index 9aea3cfc02..0000000000 --- a/tests/exhaustive/autogen/gen32/expected/model_2_3_3.eprime +++ /dev/null @@ -1,40 +0,0 @@ -language ESSENCE' 1.0 - -letting let1 be -4 -find var2_ExplicitVarSizeWithDummy: matrix indexed by [int(1..11)] of int(-4..5, 2, 6) -find var2_ExplicitVarSizeWithMarker_Marker: int(0..11) -find var2_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..11)] of int(-4..5, 2) -branching on - [var2_ExplicitVarSizeWithMarker_Marker, var2_ExplicitVarSizeWithMarker_Values, var2_ExplicitVarSizeWithDummy] -such that - or([var2_ExplicitVarSizeWithDummy[q17] != 6 /\ - !or([q19 <= var2_ExplicitVarSizeWithMarker_Marker /\ - var2_ExplicitVarSizeWithMarker_Values[q19] = var2_ExplicitVarSizeWithDummy[q17] - | q19 : int(1..11)]) - | q17 : int(1..11)]) - \/ - or([q20 <= var2_ExplicitVarSizeWithMarker_Marker /\ - !or([var2_ExplicitVarSizeWithDummy[q22] != 6 /\ - var2_ExplicitVarSizeWithDummy[q22] = var2_ExplicitVarSizeWithMarker_Values[q20] - | q22 : int(1..11)]) - | q20 : int(1..11)]), - and([var2_ExplicitVarSizeWithDummy[q1] < var2_ExplicitVarSizeWithDummy[q1 + 1] \/ - var2_ExplicitVarSizeWithDummy[q1] = 6 - | q1 : int(1..10)]), - and([var2_ExplicitVarSizeWithDummy[q2] = 6 -> var2_ExplicitVarSizeWithDummy[q2 + 1] = 6 | q2 : int(1..10)]), - and([q5 + 1 <= var2_ExplicitVarSizeWithMarker_Marker -> - var2_ExplicitVarSizeWithMarker_Values[q5] < var2_ExplicitVarSizeWithMarker_Values[q5 + 1] - | q5 : int(1..10)]), - and([q6 > var2_ExplicitVarSizeWithMarker_Marker -> var2_ExplicitVarSizeWithMarker_Values[q6] = -4 - | q6 : int(1..11)]), - and([q9 <= var2_ExplicitVarSizeWithMarker_Marker -> - or([var2_ExplicitVarSizeWithDummy[q11] != 6 /\ - var2_ExplicitVarSizeWithDummy[q11] = var2_ExplicitVarSizeWithMarker_Values[q9] - | q11 : int(1..11)]) - | q9 : int(1..11)]), - and([var2_ExplicitVarSizeWithDummy[q13] != 6 -> - or([q15 <= var2_ExplicitVarSizeWithMarker_Marker /\ - var2_ExplicitVarSizeWithMarker_Values[q15] = var2_ExplicitVarSizeWithDummy[q13] - | q15 : int(1..11)]) - | q13 : int(1..11)]) - diff --git a/tests/exhaustive/autogen/gen32/expected/model_2_3_4.eprime b/tests/exhaustive/autogen/gen32/expected/model_2_3_4.eprime deleted file mode 100644 index 8caf045469..0000000000 --- a/tests/exhaustive/autogen/gen32/expected/model_2_3_4.eprime +++ /dev/null @@ -1,69 +0,0 @@ -language ESSENCE' 1.0 - -letting let1 be -4 -find var2_ExplicitVarSizeWithDummy: matrix indexed by [int(1..11)] of int(-4..5, 2, 6) -find var2_ExplicitVarSizeWithMarker_Marker: int(0..11) -find var2_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..11)] of int(-4..5, 2) -find var2_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..11)] of bool -find var2_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..11)] of int(-4..5, 2) -branching on - [var2_ExplicitVarSizeWithFlags_Flags, var2_ExplicitVarSizeWithFlags_Values, var2_ExplicitVarSizeWithDummy, - var2_ExplicitVarSizeWithMarker_Marker, var2_ExplicitVarSizeWithMarker_Values] -such that - or([var2_ExplicitVarSizeWithDummy[q38] != 6 /\ - !or([q40 <= var2_ExplicitVarSizeWithMarker_Marker /\ - var2_ExplicitVarSizeWithMarker_Values[q40] = var2_ExplicitVarSizeWithDummy[q38] - | q40 : int(1..11)]) - | q38 : int(1..11)]) - \/ - or([q41 <= var2_ExplicitVarSizeWithMarker_Marker /\ - !or([var2_ExplicitVarSizeWithDummy[q43] != 6 /\ - var2_ExplicitVarSizeWithDummy[q43] = var2_ExplicitVarSizeWithMarker_Values[q41] - | q43 : int(1..11)]) - | q41 : int(1..11)]), - and([var2_ExplicitVarSizeWithDummy[q1] < var2_ExplicitVarSizeWithDummy[q1 + 1] \/ - var2_ExplicitVarSizeWithDummy[q1] = 6 - | q1 : int(1..10)]), - and([var2_ExplicitVarSizeWithDummy[q2] = 6 -> var2_ExplicitVarSizeWithDummy[q2 + 1] = 6 | q2 : int(1..10)]), - and([q5 + 1 <= var2_ExplicitVarSizeWithMarker_Marker -> - var2_ExplicitVarSizeWithMarker_Values[q5] < var2_ExplicitVarSizeWithMarker_Values[q5 + 1] - | q5 : int(1..10)]), - and([q6 > var2_ExplicitVarSizeWithMarker_Marker -> var2_ExplicitVarSizeWithMarker_Values[q6] = -4 - | q6 : int(1..11)]), - and([q9 <= var2_ExplicitVarSizeWithMarker_Marker -> - or([var2_ExplicitVarSizeWithDummy[q11] != 6 /\ - var2_ExplicitVarSizeWithDummy[q11] = var2_ExplicitVarSizeWithMarker_Values[q9] - | q11 : int(1..11)]) - | q9 : int(1..11)]), - and([var2_ExplicitVarSizeWithDummy[q13] != 6 -> - or([q15 <= var2_ExplicitVarSizeWithMarker_Marker /\ - var2_ExplicitVarSizeWithMarker_Values[q15] = var2_ExplicitVarSizeWithDummy[q13] - | q15 : int(1..11)]) - | q13 : int(1..11)]), - and([var2_ExplicitVarSizeWithFlags_Flags[q16 + 1] -> - var2_ExplicitVarSizeWithFlags_Values[q16] < var2_ExplicitVarSizeWithFlags_Values[q16 + 1] - | q16 : int(1..10)]), - and([var2_ExplicitVarSizeWithFlags_Flags[q17] = false -> var2_ExplicitVarSizeWithFlags_Values[q17] = -4 - | q17 : int(1..11)]), - and([var2_ExplicitVarSizeWithFlags_Flags[q18 + 1] -> var2_ExplicitVarSizeWithFlags_Flags[q18] | q18 : int(1..10)]), - and([var2_ExplicitVarSizeWithFlags_Flags[q22] -> - or([var2_ExplicitVarSizeWithDummy[q24] != 6 /\ - var2_ExplicitVarSizeWithDummy[q24] = var2_ExplicitVarSizeWithFlags_Values[q22] - | q24 : int(1..11)]) - | q22 : int(1..11)]), - and([var2_ExplicitVarSizeWithDummy[q26] != 6 -> - or([var2_ExplicitVarSizeWithFlags_Flags[q28] /\ - var2_ExplicitVarSizeWithFlags_Values[q28] = var2_ExplicitVarSizeWithDummy[q26] - | q28 : int(1..11)]) - | q26 : int(1..11)]), - and([var2_ExplicitVarSizeWithFlags_Flags[q30] -> - or([q32 <= var2_ExplicitVarSizeWithMarker_Marker /\ - var2_ExplicitVarSizeWithMarker_Values[q32] = var2_ExplicitVarSizeWithFlags_Values[q30] - | q32 : int(1..11)]) - | q30 : int(1..11)]), - and([q34 <= var2_ExplicitVarSizeWithMarker_Marker -> - or([var2_ExplicitVarSizeWithFlags_Flags[q36] /\ - var2_ExplicitVarSizeWithFlags_Values[q36] = var2_ExplicitVarSizeWithMarker_Values[q34] - | q36 : int(1..11)]) - | q34 : int(1..11)]) - diff --git a/tests/exhaustive/autogen/gen32/expected/model_2_4_1.eprime b/tests/exhaustive/autogen/gen32/expected/model_2_4_1.eprime deleted file mode 100644 index e1fcf174dd..0000000000 --- a/tests/exhaustive/autogen/gen32/expected/model_2_4_1.eprime +++ /dev/null @@ -1,54 +0,0 @@ -language ESSENCE' 1.0 - -letting let1 be -4 -find var2_ExplicitVarSizeWithDummy: matrix indexed by [int(1..11)] of int(-4..5, 2, 6) -find var2_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..11)] of bool -find var2_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..11)] of int(-4..5, 2) -find var2_Occurrence: matrix indexed by [int(-4..5, 2)] of bool -branching on - [var2_Occurrence, var2_ExplicitVarSizeWithDummy, var2_ExplicitVarSizeWithFlags_Flags, - var2_ExplicitVarSizeWithFlags_Values] -such that - or([var2_ExplicitVarSizeWithDummy[q20] != 6 /\ - !or([var2_ExplicitVarSizeWithFlags_Flags[q22] /\ - var2_ExplicitVarSizeWithFlags_Values[q22] = var2_ExplicitVarSizeWithDummy[q20] - | q22 : int(1..11)]) - | q20 : int(1..11)]) - \/ - or([var2_ExplicitVarSizeWithFlags_Flags[q23] /\ - !or([var2_ExplicitVarSizeWithDummy[q25] != 6 /\ - var2_ExplicitVarSizeWithDummy[q25] = var2_ExplicitVarSizeWithFlags_Values[q23] - | q25 : int(1..11)]) - | q23 : int(1..11)]), - and([var2_ExplicitVarSizeWithDummy[q1] < var2_ExplicitVarSizeWithDummy[q1 + 1] \/ - var2_ExplicitVarSizeWithDummy[q1] = 6 - | q1 : int(1..10)]), - and([var2_ExplicitVarSizeWithDummy[q2] = 6 -> var2_ExplicitVarSizeWithDummy[q2 + 1] = 6 | q2 : int(1..10)]), - and([var2_ExplicitVarSizeWithFlags_Flags[q5 + 1] -> - var2_ExplicitVarSizeWithFlags_Values[q5] < var2_ExplicitVarSizeWithFlags_Values[q5 + 1] - | q5 : int(1..10)]), - and([var2_ExplicitVarSizeWithFlags_Flags[q6] = false -> var2_ExplicitVarSizeWithFlags_Values[q6] = -4 - | q6 : int(1..11)]), - and([var2_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> var2_ExplicitVarSizeWithFlags_Flags[q7] | q7 : int(1..10)]), - and([var2_ExplicitVarSizeWithFlags_Flags[q11] -> - or([var2_ExplicitVarSizeWithDummy[q13] != 6 /\ - var2_ExplicitVarSizeWithDummy[q13] = var2_ExplicitVarSizeWithFlags_Values[q11] - | q13 : int(1..11)]) - | q11 : int(1..11)]), - and([var2_ExplicitVarSizeWithDummy[q15] != 6 -> - or([var2_ExplicitVarSizeWithFlags_Flags[q17] /\ - var2_ExplicitVarSizeWithFlags_Values[q17] = var2_ExplicitVarSizeWithDummy[q15] - | q17 : int(1..11)]) - | q15 : int(1..11)]), - and([var2_Occurrence[q26] -> - or([var2_ExplicitVarSizeWithDummy[q28] != 6 /\ var2_ExplicitVarSizeWithDummy[q28] = q26 | q28 : int(1..11)]) - | q26 : int(-4..5, 2)]), - and([var2_ExplicitVarSizeWithDummy[q30] != 6 -> var2_Occurrence[var2_ExplicitVarSizeWithDummy[q30]] - | q30 : int(1..11)]), - and([var2_Occurrence[q31] -> - or([var2_ExplicitVarSizeWithFlags_Flags[q33] /\ var2_ExplicitVarSizeWithFlags_Values[q33] = q31 - | q33 : int(1..11)]) - | q31 : int(-4..5, 2)]), - and([var2_ExplicitVarSizeWithFlags_Flags[q35] -> var2_Occurrence[var2_ExplicitVarSizeWithFlags_Values[q35]] - | q35 : int(1..11)]) - diff --git a/tests/exhaustive/autogen/gen32/expected/model_2_4_2.eprime b/tests/exhaustive/autogen/gen32/expected/model_2_4_2.eprime deleted file mode 100644 index d3c3ed6086..0000000000 --- a/tests/exhaustive/autogen/gen32/expected/model_2_4_2.eprime +++ /dev/null @@ -1,40 +0,0 @@ -language ESSENCE' 1.0 - -letting let1 be -4 -find var2_ExplicitVarSizeWithDummy: matrix indexed by [int(1..11)] of int(-4..5, 2, 6) -find var2_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..11)] of bool -find var2_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..11)] of int(-4..5, 2) -branching on [var2_ExplicitVarSizeWithFlags_Flags, var2_ExplicitVarSizeWithFlags_Values, var2_ExplicitVarSizeWithDummy] -such that - or([var2_ExplicitVarSizeWithDummy[q19] != 6 /\ - !or([var2_ExplicitVarSizeWithFlags_Flags[q21] /\ - var2_ExplicitVarSizeWithFlags_Values[q21] = var2_ExplicitVarSizeWithDummy[q19] - | q21 : int(1..11)]) - | q19 : int(1..11)]) - \/ - or([var2_ExplicitVarSizeWithFlags_Flags[q22] /\ - !or([var2_ExplicitVarSizeWithDummy[q24] != 6 /\ - var2_ExplicitVarSizeWithDummy[q24] = var2_ExplicitVarSizeWithFlags_Values[q22] - | q24 : int(1..11)]) - | q22 : int(1..11)]), - and([var2_ExplicitVarSizeWithDummy[q1] < var2_ExplicitVarSizeWithDummy[q1 + 1] \/ - var2_ExplicitVarSizeWithDummy[q1] = 6 - | q1 : int(1..10)]), - and([var2_ExplicitVarSizeWithDummy[q2] = 6 -> var2_ExplicitVarSizeWithDummy[q2 + 1] = 6 | q2 : int(1..10)]), - and([var2_ExplicitVarSizeWithFlags_Flags[q5 + 1] -> - var2_ExplicitVarSizeWithFlags_Values[q5] < var2_ExplicitVarSizeWithFlags_Values[q5 + 1] - | q5 : int(1..10)]), - and([var2_ExplicitVarSizeWithFlags_Flags[q6] = false -> var2_ExplicitVarSizeWithFlags_Values[q6] = -4 - | q6 : int(1..11)]), - and([var2_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> var2_ExplicitVarSizeWithFlags_Flags[q7] | q7 : int(1..10)]), - and([var2_ExplicitVarSizeWithFlags_Flags[q11] -> - or([var2_ExplicitVarSizeWithDummy[q13] != 6 /\ - var2_ExplicitVarSizeWithDummy[q13] = var2_ExplicitVarSizeWithFlags_Values[q11] - | q13 : int(1..11)]) - | q11 : int(1..11)]), - and([var2_ExplicitVarSizeWithDummy[q15] != 6 -> - or([var2_ExplicitVarSizeWithFlags_Flags[q17] /\ - var2_ExplicitVarSizeWithFlags_Values[q17] = var2_ExplicitVarSizeWithDummy[q15] - | q17 : int(1..11)]) - | q15 : int(1..11)]) - diff --git a/tests/exhaustive/autogen/gen32/expected/model_2_4_3.eprime b/tests/exhaustive/autogen/gen32/expected/model_2_4_3.eprime deleted file mode 100644 index 298bb93993..0000000000 --- a/tests/exhaustive/autogen/gen32/expected/model_2_4_3.eprime +++ /dev/null @@ -1,69 +0,0 @@ -language ESSENCE' 1.0 - -letting let1 be -4 -find var2_ExplicitVarSizeWithDummy: matrix indexed by [int(1..11)] of int(-4..5, 2, 6) -find var2_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..11)] of bool -find var2_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..11)] of int(-4..5, 2) -find var2_ExplicitVarSizeWithMarker_Marker: int(0..11) -find var2_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..11)] of int(-4..5, 2) -branching on - [var2_ExplicitVarSizeWithMarker_Marker, var2_ExplicitVarSizeWithMarker_Values, var2_ExplicitVarSizeWithDummy, - var2_ExplicitVarSizeWithFlags_Flags, var2_ExplicitVarSizeWithFlags_Values] -such that - or([var2_ExplicitVarSizeWithDummy[q38] != 6 /\ - !or([var2_ExplicitVarSizeWithFlags_Flags[q40] /\ - var2_ExplicitVarSizeWithFlags_Values[q40] = var2_ExplicitVarSizeWithDummy[q38] - | q40 : int(1..11)]) - | q38 : int(1..11)]) - \/ - or([var2_ExplicitVarSizeWithFlags_Flags[q41] /\ - !or([var2_ExplicitVarSizeWithDummy[q43] != 6 /\ - var2_ExplicitVarSizeWithDummy[q43] = var2_ExplicitVarSizeWithFlags_Values[q41] - | q43 : int(1..11)]) - | q41 : int(1..11)]), - and([var2_ExplicitVarSizeWithDummy[q1] < var2_ExplicitVarSizeWithDummy[q1 + 1] \/ - var2_ExplicitVarSizeWithDummy[q1] = 6 - | q1 : int(1..10)]), - and([var2_ExplicitVarSizeWithDummy[q2] = 6 -> var2_ExplicitVarSizeWithDummy[q2 + 1] = 6 | q2 : int(1..10)]), - and([var2_ExplicitVarSizeWithFlags_Flags[q5 + 1] -> - var2_ExplicitVarSizeWithFlags_Values[q5] < var2_ExplicitVarSizeWithFlags_Values[q5 + 1] - | q5 : int(1..10)]), - and([var2_ExplicitVarSizeWithFlags_Flags[q6] = false -> var2_ExplicitVarSizeWithFlags_Values[q6] = -4 - | q6 : int(1..11)]), - and([var2_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> var2_ExplicitVarSizeWithFlags_Flags[q7] | q7 : int(1..10)]), - and([var2_ExplicitVarSizeWithFlags_Flags[q11] -> - or([var2_ExplicitVarSizeWithDummy[q13] != 6 /\ - var2_ExplicitVarSizeWithDummy[q13] = var2_ExplicitVarSizeWithFlags_Values[q11] - | q13 : int(1..11)]) - | q11 : int(1..11)]), - and([var2_ExplicitVarSizeWithDummy[q15] != 6 -> - or([var2_ExplicitVarSizeWithFlags_Flags[q17] /\ - var2_ExplicitVarSizeWithFlags_Values[q17] = var2_ExplicitVarSizeWithDummy[q15] - | q17 : int(1..11)]) - | q15 : int(1..11)]), - and([q18 + 1 <= var2_ExplicitVarSizeWithMarker_Marker -> - var2_ExplicitVarSizeWithMarker_Values[q18] < var2_ExplicitVarSizeWithMarker_Values[q18 + 1] - | q18 : int(1..10)]), - and([q19 > var2_ExplicitVarSizeWithMarker_Marker -> var2_ExplicitVarSizeWithMarker_Values[q19] = -4 - | q19 : int(1..11)]), - and([q22 <= var2_ExplicitVarSizeWithMarker_Marker -> - or([var2_ExplicitVarSizeWithDummy[q24] != 6 /\ - var2_ExplicitVarSizeWithDummy[q24] = var2_ExplicitVarSizeWithMarker_Values[q22] - | q24 : int(1..11)]) - | q22 : int(1..11)]), - and([var2_ExplicitVarSizeWithDummy[q26] != 6 -> - or([q28 <= var2_ExplicitVarSizeWithMarker_Marker /\ - var2_ExplicitVarSizeWithMarker_Values[q28] = var2_ExplicitVarSizeWithDummy[q26] - | q28 : int(1..11)]) - | q26 : int(1..11)]), - and([q30 <= var2_ExplicitVarSizeWithMarker_Marker -> - or([var2_ExplicitVarSizeWithFlags_Flags[q32] /\ - var2_ExplicitVarSizeWithFlags_Values[q32] = var2_ExplicitVarSizeWithMarker_Values[q30] - | q32 : int(1..11)]) - | q30 : int(1..11)]), - and([var2_ExplicitVarSizeWithFlags_Flags[q34] -> - or([q36 <= var2_ExplicitVarSizeWithMarker_Marker /\ - var2_ExplicitVarSizeWithMarker_Values[q36] = var2_ExplicitVarSizeWithFlags_Values[q34] - | q36 : int(1..11)]) - | q34 : int(1..11)]) - diff --git a/tests/exhaustive/autogen/gen32/expected/model_2_4_4.eprime b/tests/exhaustive/autogen/gen32/expected/model_2_4_4.eprime deleted file mode 100644 index d3c3ed6086..0000000000 --- a/tests/exhaustive/autogen/gen32/expected/model_2_4_4.eprime +++ /dev/null @@ -1,40 +0,0 @@ -language ESSENCE' 1.0 - -letting let1 be -4 -find var2_ExplicitVarSizeWithDummy: matrix indexed by [int(1..11)] of int(-4..5, 2, 6) -find var2_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..11)] of bool -find var2_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..11)] of int(-4..5, 2) -branching on [var2_ExplicitVarSizeWithFlags_Flags, var2_ExplicitVarSizeWithFlags_Values, var2_ExplicitVarSizeWithDummy] -such that - or([var2_ExplicitVarSizeWithDummy[q19] != 6 /\ - !or([var2_ExplicitVarSizeWithFlags_Flags[q21] /\ - var2_ExplicitVarSizeWithFlags_Values[q21] = var2_ExplicitVarSizeWithDummy[q19] - | q21 : int(1..11)]) - | q19 : int(1..11)]) - \/ - or([var2_ExplicitVarSizeWithFlags_Flags[q22] /\ - !or([var2_ExplicitVarSizeWithDummy[q24] != 6 /\ - var2_ExplicitVarSizeWithDummy[q24] = var2_ExplicitVarSizeWithFlags_Values[q22] - | q24 : int(1..11)]) - | q22 : int(1..11)]), - and([var2_ExplicitVarSizeWithDummy[q1] < var2_ExplicitVarSizeWithDummy[q1 + 1] \/ - var2_ExplicitVarSizeWithDummy[q1] = 6 - | q1 : int(1..10)]), - and([var2_ExplicitVarSizeWithDummy[q2] = 6 -> var2_ExplicitVarSizeWithDummy[q2 + 1] = 6 | q2 : int(1..10)]), - and([var2_ExplicitVarSizeWithFlags_Flags[q5 + 1] -> - var2_ExplicitVarSizeWithFlags_Values[q5] < var2_ExplicitVarSizeWithFlags_Values[q5 + 1] - | q5 : int(1..10)]), - and([var2_ExplicitVarSizeWithFlags_Flags[q6] = false -> var2_ExplicitVarSizeWithFlags_Values[q6] = -4 - | q6 : int(1..11)]), - and([var2_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> var2_ExplicitVarSizeWithFlags_Flags[q7] | q7 : int(1..10)]), - and([var2_ExplicitVarSizeWithFlags_Flags[q11] -> - or([var2_ExplicitVarSizeWithDummy[q13] != 6 /\ - var2_ExplicitVarSizeWithDummy[q13] = var2_ExplicitVarSizeWithFlags_Values[q11] - | q13 : int(1..11)]) - | q11 : int(1..11)]), - and([var2_ExplicitVarSizeWithDummy[q15] != 6 -> - or([var2_ExplicitVarSizeWithFlags_Flags[q17] /\ - var2_ExplicitVarSizeWithFlags_Values[q17] = var2_ExplicitVarSizeWithDummy[q15] - | q17 : int(1..11)]) - | q15 : int(1..11)]) - diff --git a/tests/exhaustive/autogen/gen32/expected/model_3_1_1.eprime b/tests/exhaustive/autogen/gen32/expected/model_3_1_1.eprime deleted file mode 100644 index c841bbbe9f..0000000000 --- a/tests/exhaustive/autogen/gen32/expected/model_3_1_1.eprime +++ /dev/null @@ -1,27 +0,0 @@ -language ESSENCE' 1.0 - -letting let1 be -4 -find var2_ExplicitVarSizeWithMarker_Marker: int(0..11) -find var2_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..11)] of int(-4..5, 2) -find var2_Occurrence: matrix indexed by [int(-4..5, 2)] of bool -branching on [var2_Occurrence, var2_ExplicitVarSizeWithMarker_Marker, var2_ExplicitVarSizeWithMarker_Values] -such that - or([q6 <= var2_ExplicitVarSizeWithMarker_Marker /\ !var2_Occurrence[var2_ExplicitVarSizeWithMarker_Values[q6]] - | q6 : int(1..11)]) - \/ - or([var2_Occurrence[q5] /\ - !or([q8 <= var2_ExplicitVarSizeWithMarker_Marker /\ var2_ExplicitVarSizeWithMarker_Values[q8] = q5 - | q8 : int(1..11)]) - | q5 : int(-4..5, 2)]), - and([q1 + 1 <= var2_ExplicitVarSizeWithMarker_Marker -> - var2_ExplicitVarSizeWithMarker_Values[q1] < var2_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..10)]), - and([q2 > var2_ExplicitVarSizeWithMarker_Marker -> var2_ExplicitVarSizeWithMarker_Values[q2] = -4 - | q2 : int(1..11)]), - and([var2_Occurrence[q9] -> - or([q11 <= var2_ExplicitVarSizeWithMarker_Marker /\ var2_ExplicitVarSizeWithMarker_Values[q11] = q9 - | q11 : int(1..11)]) - | q9 : int(-4..5, 2)]), - and([q13 <= var2_ExplicitVarSizeWithMarker_Marker -> var2_Occurrence[var2_ExplicitVarSizeWithMarker_Values[q13]] - | q13 : int(1..11)]) - diff --git a/tests/exhaustive/autogen/gen32/expected/model_3_1_2.eprime b/tests/exhaustive/autogen/gen32/expected/model_3_1_2.eprime deleted file mode 100644 index 7e7b9ddfa6..0000000000 --- a/tests/exhaustive/autogen/gen32/expected/model_3_1_2.eprime +++ /dev/null @@ -1,49 +0,0 @@ -language ESSENCE' 1.0 - -letting let1 be -4 -find var2_ExplicitVarSizeWithMarker_Marker: int(0..11) -find var2_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..11)] of int(-4..5, 2) -find var2_Occurrence: matrix indexed by [int(-4..5, 2)] of bool -find var2_ExplicitVarSizeWithDummy: matrix indexed by [int(1..11)] of int(-4..5, 2, 6) -branching on - [var2_ExplicitVarSizeWithDummy, var2_ExplicitVarSizeWithMarker_Marker, var2_ExplicitVarSizeWithMarker_Values, - var2_Occurrence] -such that - or([q23 <= var2_ExplicitVarSizeWithMarker_Marker /\ !var2_Occurrence[var2_ExplicitVarSizeWithMarker_Values[q23]] - | q23 : int(1..11)]) - \/ - or([var2_Occurrence[q22] /\ - !or([q25 <= var2_ExplicitVarSizeWithMarker_Marker /\ var2_ExplicitVarSizeWithMarker_Values[q25] = q22 - | q25 : int(1..11)]) - | q22 : int(-4..5, 2)]), - and([q1 + 1 <= var2_ExplicitVarSizeWithMarker_Marker -> - var2_ExplicitVarSizeWithMarker_Values[q1] < var2_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..10)]), - and([q2 > var2_ExplicitVarSizeWithMarker_Marker -> var2_ExplicitVarSizeWithMarker_Values[q2] = -4 - | q2 : int(1..11)]), - and([var2_Occurrence[q26] -> - or([q28 <= var2_ExplicitVarSizeWithMarker_Marker /\ var2_ExplicitVarSizeWithMarker_Values[q28] = q26 - | q28 : int(1..11)]) - | q26 : int(-4..5, 2)]), - and([q30 <= var2_ExplicitVarSizeWithMarker_Marker -> var2_Occurrence[var2_ExplicitVarSizeWithMarker_Values[q30]] - | q30 : int(1..11)]), - and([var2_ExplicitVarSizeWithDummy[q5] < var2_ExplicitVarSizeWithDummy[q5 + 1] \/ - var2_ExplicitVarSizeWithDummy[q5] = 6 - | q5 : int(1..10)]), - and([var2_ExplicitVarSizeWithDummy[q6] = 6 -> var2_ExplicitVarSizeWithDummy[q6 + 1] = 6 | q6 : int(1..10)]), - and([var2_ExplicitVarSizeWithDummy[q10] != 6 -> - or([q12 <= var2_ExplicitVarSizeWithMarker_Marker /\ - var2_ExplicitVarSizeWithMarker_Values[q12] = var2_ExplicitVarSizeWithDummy[q10] - | q12 : int(1..11)]) - | q10 : int(1..11)]), - and([q14 <= var2_ExplicitVarSizeWithMarker_Marker -> - or([var2_ExplicitVarSizeWithDummy[q16] != 6 /\ - var2_ExplicitVarSizeWithDummy[q16] = var2_ExplicitVarSizeWithMarker_Values[q14] - | q16 : int(1..11)]) - | q14 : int(1..11)]), - and([var2_ExplicitVarSizeWithDummy[q18] != 6 -> var2_Occurrence[var2_ExplicitVarSizeWithDummy[q18]] - | q18 : int(1..11)]), - and([var2_Occurrence[q19] -> - or([var2_ExplicitVarSizeWithDummy[q21] != 6 /\ var2_ExplicitVarSizeWithDummy[q21] = q19 | q21 : int(1..11)]) - | q19 : int(-4..5, 2)]) - diff --git a/tests/exhaustive/autogen/gen32/expected/model_3_1_3.eprime b/tests/exhaustive/autogen/gen32/expected/model_3_1_3.eprime deleted file mode 100644 index c841bbbe9f..0000000000 --- a/tests/exhaustive/autogen/gen32/expected/model_3_1_3.eprime +++ /dev/null @@ -1,27 +0,0 @@ -language ESSENCE' 1.0 - -letting let1 be -4 -find var2_ExplicitVarSizeWithMarker_Marker: int(0..11) -find var2_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..11)] of int(-4..5, 2) -find var2_Occurrence: matrix indexed by [int(-4..5, 2)] of bool -branching on [var2_Occurrence, var2_ExplicitVarSizeWithMarker_Marker, var2_ExplicitVarSizeWithMarker_Values] -such that - or([q6 <= var2_ExplicitVarSizeWithMarker_Marker /\ !var2_Occurrence[var2_ExplicitVarSizeWithMarker_Values[q6]] - | q6 : int(1..11)]) - \/ - or([var2_Occurrence[q5] /\ - !or([q8 <= var2_ExplicitVarSizeWithMarker_Marker /\ var2_ExplicitVarSizeWithMarker_Values[q8] = q5 - | q8 : int(1..11)]) - | q5 : int(-4..5, 2)]), - and([q1 + 1 <= var2_ExplicitVarSizeWithMarker_Marker -> - var2_ExplicitVarSizeWithMarker_Values[q1] < var2_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..10)]), - and([q2 > var2_ExplicitVarSizeWithMarker_Marker -> var2_ExplicitVarSizeWithMarker_Values[q2] = -4 - | q2 : int(1..11)]), - and([var2_Occurrence[q9] -> - or([q11 <= var2_ExplicitVarSizeWithMarker_Marker /\ var2_ExplicitVarSizeWithMarker_Values[q11] = q9 - | q11 : int(1..11)]) - | q9 : int(-4..5, 2)]), - and([q13 <= var2_ExplicitVarSizeWithMarker_Marker -> var2_Occurrence[var2_ExplicitVarSizeWithMarker_Values[q13]] - | q13 : int(1..11)]) - diff --git a/tests/exhaustive/autogen/gen32/expected/model_3_1_4.eprime b/tests/exhaustive/autogen/gen32/expected/model_3_1_4.eprime deleted file mode 100644 index a2676c1f31..0000000000 --- a/tests/exhaustive/autogen/gen32/expected/model_3_1_4.eprime +++ /dev/null @@ -1,53 +0,0 @@ -language ESSENCE' 1.0 - -letting let1 be -4 -find var2_ExplicitVarSizeWithMarker_Marker: int(0..11) -find var2_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..11)] of int(-4..5, 2) -find var2_Occurrence: matrix indexed by [int(-4..5, 2)] of bool -find var2_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..11)] of bool -find var2_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..11)] of int(-4..5, 2) -branching on - [var2_ExplicitVarSizeWithFlags_Flags, var2_ExplicitVarSizeWithFlags_Values, var2_ExplicitVarSizeWithMarker_Marker, - var2_ExplicitVarSizeWithMarker_Values, var2_Occurrence] -such that - or([q24 <= var2_ExplicitVarSizeWithMarker_Marker /\ !var2_Occurrence[var2_ExplicitVarSizeWithMarker_Values[q24]] - | q24 : int(1..11)]) - \/ - or([var2_Occurrence[q23] /\ - !or([q26 <= var2_ExplicitVarSizeWithMarker_Marker /\ var2_ExplicitVarSizeWithMarker_Values[q26] = q23 - | q26 : int(1..11)]) - | q23 : int(-4..5, 2)]), - and([q1 + 1 <= var2_ExplicitVarSizeWithMarker_Marker -> - var2_ExplicitVarSizeWithMarker_Values[q1] < var2_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..10)]), - and([q2 > var2_ExplicitVarSizeWithMarker_Marker -> var2_ExplicitVarSizeWithMarker_Values[q2] = -4 - | q2 : int(1..11)]), - and([var2_Occurrence[q27] -> - or([q29 <= var2_ExplicitVarSizeWithMarker_Marker /\ var2_ExplicitVarSizeWithMarker_Values[q29] = q27 - | q29 : int(1..11)]) - | q27 : int(-4..5, 2)]), - and([q31 <= var2_ExplicitVarSizeWithMarker_Marker -> var2_Occurrence[var2_ExplicitVarSizeWithMarker_Values[q31]] - | q31 : int(1..11)]), - and([var2_ExplicitVarSizeWithFlags_Flags[q5 + 1] -> - var2_ExplicitVarSizeWithFlags_Values[q5] < var2_ExplicitVarSizeWithFlags_Values[q5 + 1] - | q5 : int(1..10)]), - and([var2_ExplicitVarSizeWithFlags_Flags[q6] = false -> var2_ExplicitVarSizeWithFlags_Values[q6] = -4 - | q6 : int(1..11)]), - and([var2_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> var2_ExplicitVarSizeWithFlags_Flags[q7] | q7 : int(1..10)]), - and([var2_ExplicitVarSizeWithFlags_Flags[q11] -> - or([q13 <= var2_ExplicitVarSizeWithMarker_Marker /\ - var2_ExplicitVarSizeWithMarker_Values[q13] = var2_ExplicitVarSizeWithFlags_Values[q11] - | q13 : int(1..11)]) - | q11 : int(1..11)]), - and([q15 <= var2_ExplicitVarSizeWithMarker_Marker -> - or([var2_ExplicitVarSizeWithFlags_Flags[q17] /\ - var2_ExplicitVarSizeWithFlags_Values[q17] = var2_ExplicitVarSizeWithMarker_Values[q15] - | q17 : int(1..11)]) - | q15 : int(1..11)]), - and([var2_ExplicitVarSizeWithFlags_Flags[q19] -> var2_Occurrence[var2_ExplicitVarSizeWithFlags_Values[q19]] - | q19 : int(1..11)]), - and([var2_Occurrence[q20] -> - or([var2_ExplicitVarSizeWithFlags_Flags[q22] /\ var2_ExplicitVarSizeWithFlags_Values[q22] = q20 - | q22 : int(1..11)]) - | q20 : int(-4..5, 2)]) - diff --git a/tests/exhaustive/autogen/gen32/expected/model_3_2_1.eprime b/tests/exhaustive/autogen/gen32/expected/model_3_2_1.eprime deleted file mode 100644 index 86dbab6810..0000000000 --- a/tests/exhaustive/autogen/gen32/expected/model_3_2_1.eprime +++ /dev/null @@ -1,53 +0,0 @@ -language ESSENCE' 1.0 - -letting let1 be -4 -find var2_ExplicitVarSizeWithMarker_Marker: int(0..11) -find var2_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..11)] of int(-4..5, 2) -find var2_ExplicitVarSizeWithDummy: matrix indexed by [int(1..11)] of int(-4..5, 2, 6) -find var2_Occurrence: matrix indexed by [int(-4..5, 2)] of bool -branching on - [var2_Occurrence, var2_ExplicitVarSizeWithMarker_Marker, var2_ExplicitVarSizeWithMarker_Values, - var2_ExplicitVarSizeWithDummy] -such that - or([q18 <= var2_ExplicitVarSizeWithMarker_Marker /\ - !or([var2_ExplicitVarSizeWithDummy[q20] != 6 /\ - var2_ExplicitVarSizeWithDummy[q20] = var2_ExplicitVarSizeWithMarker_Values[q18] - | q20 : int(1..11)]) - | q18 : int(1..11)]) - \/ - or([var2_ExplicitVarSizeWithDummy[q21] != 6 /\ - !or([q23 <= var2_ExplicitVarSizeWithMarker_Marker /\ - var2_ExplicitVarSizeWithMarker_Values[q23] = var2_ExplicitVarSizeWithDummy[q21] - | q23 : int(1..11)]) - | q21 : int(1..11)]), - and([q1 + 1 <= var2_ExplicitVarSizeWithMarker_Marker -> - var2_ExplicitVarSizeWithMarker_Values[q1] < var2_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..10)]), - and([q2 > var2_ExplicitVarSizeWithMarker_Marker -> var2_ExplicitVarSizeWithMarker_Values[q2] = -4 - | q2 : int(1..11)]), - and([var2_ExplicitVarSizeWithDummy[q4] < var2_ExplicitVarSizeWithDummy[q4 + 1] \/ - var2_ExplicitVarSizeWithDummy[q4] = 6 - | q4 : int(1..10)]), - and([var2_ExplicitVarSizeWithDummy[q5] = 6 -> var2_ExplicitVarSizeWithDummy[q5 + 1] = 6 | q5 : int(1..10)]), - and([var2_ExplicitVarSizeWithDummy[q9] != 6 -> - or([q11 <= var2_ExplicitVarSizeWithMarker_Marker /\ - var2_ExplicitVarSizeWithMarker_Values[q11] = var2_ExplicitVarSizeWithDummy[q9] - | q11 : int(1..11)]) - | q9 : int(1..11)]), - and([q13 <= var2_ExplicitVarSizeWithMarker_Marker -> - or([var2_ExplicitVarSizeWithDummy[q15] != 6 /\ - var2_ExplicitVarSizeWithDummy[q15] = var2_ExplicitVarSizeWithMarker_Values[q13] - | q15 : int(1..11)]) - | q13 : int(1..11)]), - and([var2_Occurrence[q24] -> - or([q26 <= var2_ExplicitVarSizeWithMarker_Marker /\ var2_ExplicitVarSizeWithMarker_Values[q26] = q24 - | q26 : int(1..11)]) - | q24 : int(-4..5, 2)]), - and([q28 <= var2_ExplicitVarSizeWithMarker_Marker -> var2_Occurrence[var2_ExplicitVarSizeWithMarker_Values[q28]] - | q28 : int(1..11)]), - and([var2_Occurrence[q29] -> - or([var2_ExplicitVarSizeWithDummy[q31] != 6 /\ var2_ExplicitVarSizeWithDummy[q31] = q29 | q31 : int(1..11)]) - | q29 : int(-4..5, 2)]), - and([var2_ExplicitVarSizeWithDummy[q33] != 6 -> var2_Occurrence[var2_ExplicitVarSizeWithDummy[q33]] - | q33 : int(1..11)]) - diff --git a/tests/exhaustive/autogen/gen32/expected/model_3_2_2.eprime b/tests/exhaustive/autogen/gen32/expected/model_3_2_2.eprime deleted file mode 100644 index c9a6281665..0000000000 --- a/tests/exhaustive/autogen/gen32/expected/model_3_2_2.eprime +++ /dev/null @@ -1,40 +0,0 @@ -language ESSENCE' 1.0 - -letting let1 be -4 -find var2_ExplicitVarSizeWithMarker_Marker: int(0..11) -find var2_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..11)] of int(-4..5, 2) -find var2_ExplicitVarSizeWithDummy: matrix indexed by [int(1..11)] of int(-4..5, 2, 6) -branching on - [var2_ExplicitVarSizeWithDummy, var2_ExplicitVarSizeWithMarker_Marker, var2_ExplicitVarSizeWithMarker_Values] -such that - or([q17 <= var2_ExplicitVarSizeWithMarker_Marker /\ - !or([var2_ExplicitVarSizeWithDummy[q19] != 6 /\ - var2_ExplicitVarSizeWithDummy[q19] = var2_ExplicitVarSizeWithMarker_Values[q17] - | q19 : int(1..11)]) - | q17 : int(1..11)]) - \/ - or([var2_ExplicitVarSizeWithDummy[q20] != 6 /\ - !or([q22 <= var2_ExplicitVarSizeWithMarker_Marker /\ - var2_ExplicitVarSizeWithMarker_Values[q22] = var2_ExplicitVarSizeWithDummy[q20] - | q22 : int(1..11)]) - | q20 : int(1..11)]), - and([q1 + 1 <= var2_ExplicitVarSizeWithMarker_Marker -> - var2_ExplicitVarSizeWithMarker_Values[q1] < var2_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..10)]), - and([q2 > var2_ExplicitVarSizeWithMarker_Marker -> var2_ExplicitVarSizeWithMarker_Values[q2] = -4 - | q2 : int(1..11)]), - and([var2_ExplicitVarSizeWithDummy[q4] < var2_ExplicitVarSizeWithDummy[q4 + 1] \/ - var2_ExplicitVarSizeWithDummy[q4] = 6 - | q4 : int(1..10)]), - and([var2_ExplicitVarSizeWithDummy[q5] = 6 -> var2_ExplicitVarSizeWithDummy[q5 + 1] = 6 | q5 : int(1..10)]), - and([var2_ExplicitVarSizeWithDummy[q9] != 6 -> - or([q11 <= var2_ExplicitVarSizeWithMarker_Marker /\ - var2_ExplicitVarSizeWithMarker_Values[q11] = var2_ExplicitVarSizeWithDummy[q9] - | q11 : int(1..11)]) - | q9 : int(1..11)]), - and([q13 <= var2_ExplicitVarSizeWithMarker_Marker -> - or([var2_ExplicitVarSizeWithDummy[q15] != 6 /\ - var2_ExplicitVarSizeWithDummy[q15] = var2_ExplicitVarSizeWithMarker_Values[q13] - | q15 : int(1..11)]) - | q13 : int(1..11)]) - diff --git a/tests/exhaustive/autogen/gen32/expected/model_3_2_3.eprime b/tests/exhaustive/autogen/gen32/expected/model_3_2_3.eprime deleted file mode 100644 index c9a6281665..0000000000 --- a/tests/exhaustive/autogen/gen32/expected/model_3_2_3.eprime +++ /dev/null @@ -1,40 +0,0 @@ -language ESSENCE' 1.0 - -letting let1 be -4 -find var2_ExplicitVarSizeWithMarker_Marker: int(0..11) -find var2_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..11)] of int(-4..5, 2) -find var2_ExplicitVarSizeWithDummy: matrix indexed by [int(1..11)] of int(-4..5, 2, 6) -branching on - [var2_ExplicitVarSizeWithDummy, var2_ExplicitVarSizeWithMarker_Marker, var2_ExplicitVarSizeWithMarker_Values] -such that - or([q17 <= var2_ExplicitVarSizeWithMarker_Marker /\ - !or([var2_ExplicitVarSizeWithDummy[q19] != 6 /\ - var2_ExplicitVarSizeWithDummy[q19] = var2_ExplicitVarSizeWithMarker_Values[q17] - | q19 : int(1..11)]) - | q17 : int(1..11)]) - \/ - or([var2_ExplicitVarSizeWithDummy[q20] != 6 /\ - !or([q22 <= var2_ExplicitVarSizeWithMarker_Marker /\ - var2_ExplicitVarSizeWithMarker_Values[q22] = var2_ExplicitVarSizeWithDummy[q20] - | q22 : int(1..11)]) - | q20 : int(1..11)]), - and([q1 + 1 <= var2_ExplicitVarSizeWithMarker_Marker -> - var2_ExplicitVarSizeWithMarker_Values[q1] < var2_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..10)]), - and([q2 > var2_ExplicitVarSizeWithMarker_Marker -> var2_ExplicitVarSizeWithMarker_Values[q2] = -4 - | q2 : int(1..11)]), - and([var2_ExplicitVarSizeWithDummy[q4] < var2_ExplicitVarSizeWithDummy[q4 + 1] \/ - var2_ExplicitVarSizeWithDummy[q4] = 6 - | q4 : int(1..10)]), - and([var2_ExplicitVarSizeWithDummy[q5] = 6 -> var2_ExplicitVarSizeWithDummy[q5 + 1] = 6 | q5 : int(1..10)]), - and([var2_ExplicitVarSizeWithDummy[q9] != 6 -> - or([q11 <= var2_ExplicitVarSizeWithMarker_Marker /\ - var2_ExplicitVarSizeWithMarker_Values[q11] = var2_ExplicitVarSizeWithDummy[q9] - | q11 : int(1..11)]) - | q9 : int(1..11)]), - and([q13 <= var2_ExplicitVarSizeWithMarker_Marker -> - or([var2_ExplicitVarSizeWithDummy[q15] != 6 /\ - var2_ExplicitVarSizeWithDummy[q15] = var2_ExplicitVarSizeWithMarker_Values[q13] - | q15 : int(1..11)]) - | q13 : int(1..11)]) - diff --git a/tests/exhaustive/autogen/gen32/expected/model_3_2_4.eprime b/tests/exhaustive/autogen/gen32/expected/model_3_2_4.eprime deleted file mode 100644 index 0a6285920a..0000000000 --- a/tests/exhaustive/autogen/gen32/expected/model_3_2_4.eprime +++ /dev/null @@ -1,69 +0,0 @@ -language ESSENCE' 1.0 - -letting let1 be -4 -find var2_ExplicitVarSizeWithMarker_Marker: int(0..11) -find var2_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..11)] of int(-4..5, 2) -find var2_ExplicitVarSizeWithDummy: matrix indexed by [int(1..11)] of int(-4..5, 2, 6) -find var2_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..11)] of bool -find var2_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..11)] of int(-4..5, 2) -branching on - [var2_ExplicitVarSizeWithFlags_Flags, var2_ExplicitVarSizeWithFlags_Values, var2_ExplicitVarSizeWithMarker_Marker, - var2_ExplicitVarSizeWithMarker_Values, var2_ExplicitVarSizeWithDummy] -such that - or([q38 <= var2_ExplicitVarSizeWithMarker_Marker /\ - !or([var2_ExplicitVarSizeWithDummy[q40] != 6 /\ - var2_ExplicitVarSizeWithDummy[q40] = var2_ExplicitVarSizeWithMarker_Values[q38] - | q40 : int(1..11)]) - | q38 : int(1..11)]) - \/ - or([var2_ExplicitVarSizeWithDummy[q41] != 6 /\ - !or([q43 <= var2_ExplicitVarSizeWithMarker_Marker /\ - var2_ExplicitVarSizeWithMarker_Values[q43] = var2_ExplicitVarSizeWithDummy[q41] - | q43 : int(1..11)]) - | q41 : int(1..11)]), - and([q1 + 1 <= var2_ExplicitVarSizeWithMarker_Marker -> - var2_ExplicitVarSizeWithMarker_Values[q1] < var2_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..10)]), - and([q2 > var2_ExplicitVarSizeWithMarker_Marker -> var2_ExplicitVarSizeWithMarker_Values[q2] = -4 - | q2 : int(1..11)]), - and([var2_ExplicitVarSizeWithDummy[q4] < var2_ExplicitVarSizeWithDummy[q4 + 1] \/ - var2_ExplicitVarSizeWithDummy[q4] = 6 - | q4 : int(1..10)]), - and([var2_ExplicitVarSizeWithDummy[q5] = 6 -> var2_ExplicitVarSizeWithDummy[q5 + 1] = 6 | q5 : int(1..10)]), - and([var2_ExplicitVarSizeWithDummy[q9] != 6 -> - or([q11 <= var2_ExplicitVarSizeWithMarker_Marker /\ - var2_ExplicitVarSizeWithMarker_Values[q11] = var2_ExplicitVarSizeWithDummy[q9] - | q11 : int(1..11)]) - | q9 : int(1..11)]), - and([q13 <= var2_ExplicitVarSizeWithMarker_Marker -> - or([var2_ExplicitVarSizeWithDummy[q15] != 6 /\ - var2_ExplicitVarSizeWithDummy[q15] = var2_ExplicitVarSizeWithMarker_Values[q13] - | q15 : int(1..11)]) - | q13 : int(1..11)]), - and([var2_ExplicitVarSizeWithFlags_Flags[q16 + 1] -> - var2_ExplicitVarSizeWithFlags_Values[q16] < var2_ExplicitVarSizeWithFlags_Values[q16 + 1] - | q16 : int(1..10)]), - and([var2_ExplicitVarSizeWithFlags_Flags[q17] = false -> var2_ExplicitVarSizeWithFlags_Values[q17] = -4 - | q17 : int(1..11)]), - and([var2_ExplicitVarSizeWithFlags_Flags[q18 + 1] -> var2_ExplicitVarSizeWithFlags_Flags[q18] | q18 : int(1..10)]), - and([var2_ExplicitVarSizeWithFlags_Flags[q22] -> - or([q24 <= var2_ExplicitVarSizeWithMarker_Marker /\ - var2_ExplicitVarSizeWithMarker_Values[q24] = var2_ExplicitVarSizeWithFlags_Values[q22] - | q24 : int(1..11)]) - | q22 : int(1..11)]), - and([q26 <= var2_ExplicitVarSizeWithMarker_Marker -> - or([var2_ExplicitVarSizeWithFlags_Flags[q28] /\ - var2_ExplicitVarSizeWithFlags_Values[q28] = var2_ExplicitVarSizeWithMarker_Values[q26] - | q28 : int(1..11)]) - | q26 : int(1..11)]), - and([var2_ExplicitVarSizeWithFlags_Flags[q30] -> - or([var2_ExplicitVarSizeWithDummy[q32] != 6 /\ - var2_ExplicitVarSizeWithDummy[q32] = var2_ExplicitVarSizeWithFlags_Values[q30] - | q32 : int(1..11)]) - | q30 : int(1..11)]), - and([var2_ExplicitVarSizeWithDummy[q34] != 6 -> - or([var2_ExplicitVarSizeWithFlags_Flags[q36] /\ - var2_ExplicitVarSizeWithFlags_Values[q36] = var2_ExplicitVarSizeWithDummy[q34] - | q36 : int(1..11)]) - | q34 : int(1..11)]) - diff --git a/tests/exhaustive/autogen/gen32/expected/model_3_3_1.eprime b/tests/exhaustive/autogen/gen32/expected/model_3_3_1.eprime deleted file mode 100644 index da12cb2407..0000000000 --- a/tests/exhaustive/autogen/gen32/expected/model_3_3_1.eprime +++ /dev/null @@ -1,31 +0,0 @@ -language ESSENCE' 1.0 - -letting let1 be -4 -find var2_ExplicitVarSizeWithMarker_Marker: int(0..11) -find var2_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..11)] of int(-4..5, 2) -find var2_Occurrence: matrix indexed by [int(-4..5, 2)] of bool -branching on [var2_Occurrence, var2_ExplicitVarSizeWithMarker_Marker, var2_ExplicitVarSizeWithMarker_Values] -such that - or([q6 <= var2_ExplicitVarSizeWithMarker_Marker /\ - !or([q8 <= var2_ExplicitVarSizeWithMarker_Marker /\ - var2_ExplicitVarSizeWithMarker_Values[q8] = var2_ExplicitVarSizeWithMarker_Values[q6] - | q8 : int(1..11)]) - | q6 : int(1..11)]) - \/ - or([q9 <= var2_ExplicitVarSizeWithMarker_Marker /\ - !or([q11 <= var2_ExplicitVarSizeWithMarker_Marker /\ - var2_ExplicitVarSizeWithMarker_Values[q11] = var2_ExplicitVarSizeWithMarker_Values[q9] - | q11 : int(1..11)]) - | q9 : int(1..11)]), - and([q1 + 1 <= var2_ExplicitVarSizeWithMarker_Marker -> - var2_ExplicitVarSizeWithMarker_Values[q1] < var2_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..10)]), - and([q2 > var2_ExplicitVarSizeWithMarker_Marker -> var2_ExplicitVarSizeWithMarker_Values[q2] = -4 - | q2 : int(1..11)]), - and([var2_Occurrence[q12] -> - or([q14 <= var2_ExplicitVarSizeWithMarker_Marker /\ var2_ExplicitVarSizeWithMarker_Values[q14] = q12 - | q14 : int(1..11)]) - | q12 : int(-4..5, 2)]), - and([q16 <= var2_ExplicitVarSizeWithMarker_Marker -> var2_Occurrence[var2_ExplicitVarSizeWithMarker_Values[q16]] - | q16 : int(1..11)]) - diff --git a/tests/exhaustive/autogen/gen32/expected/model_3_3_2.eprime b/tests/exhaustive/autogen/gen32/expected/model_3_3_2.eprime deleted file mode 100644 index 4b5f1c3017..0000000000 --- a/tests/exhaustive/autogen/gen32/expected/model_3_3_2.eprime +++ /dev/null @@ -1,40 +0,0 @@ -language ESSENCE' 1.0 - -letting let1 be -4 -find var2_ExplicitVarSizeWithMarker_Marker: int(0..11) -find var2_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..11)] of int(-4..5, 2) -find var2_ExplicitVarSizeWithDummy: matrix indexed by [int(1..11)] of int(-4..5, 2, 6) -branching on - [var2_ExplicitVarSizeWithDummy, var2_ExplicitVarSizeWithMarker_Marker, var2_ExplicitVarSizeWithMarker_Values] -such that - or([q17 <= var2_ExplicitVarSizeWithMarker_Marker /\ - !or([q19 <= var2_ExplicitVarSizeWithMarker_Marker /\ - var2_ExplicitVarSizeWithMarker_Values[q19] = var2_ExplicitVarSizeWithMarker_Values[q17] - | q19 : int(1..11)]) - | q17 : int(1..11)]) - \/ - or([q20 <= var2_ExplicitVarSizeWithMarker_Marker /\ - !or([q22 <= var2_ExplicitVarSizeWithMarker_Marker /\ - var2_ExplicitVarSizeWithMarker_Values[q22] = var2_ExplicitVarSizeWithMarker_Values[q20] - | q22 : int(1..11)]) - | q20 : int(1..11)]), - and([q1 + 1 <= var2_ExplicitVarSizeWithMarker_Marker -> - var2_ExplicitVarSizeWithMarker_Values[q1] < var2_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..10)]), - and([q2 > var2_ExplicitVarSizeWithMarker_Marker -> var2_ExplicitVarSizeWithMarker_Values[q2] = -4 - | q2 : int(1..11)]), - and([var2_ExplicitVarSizeWithDummy[q4] < var2_ExplicitVarSizeWithDummy[q4 + 1] \/ - var2_ExplicitVarSizeWithDummy[q4] = 6 - | q4 : int(1..10)]), - and([var2_ExplicitVarSizeWithDummy[q5] = 6 -> var2_ExplicitVarSizeWithDummy[q5 + 1] = 6 | q5 : int(1..10)]), - and([var2_ExplicitVarSizeWithDummy[q9] != 6 -> - or([q11 <= var2_ExplicitVarSizeWithMarker_Marker /\ - var2_ExplicitVarSizeWithMarker_Values[q11] = var2_ExplicitVarSizeWithDummy[q9] - | q11 : int(1..11)]) - | q9 : int(1..11)]), - and([q13 <= var2_ExplicitVarSizeWithMarker_Marker -> - or([var2_ExplicitVarSizeWithDummy[q15] != 6 /\ - var2_ExplicitVarSizeWithDummy[q15] = var2_ExplicitVarSizeWithMarker_Values[q13] - | q15 : int(1..11)]) - | q13 : int(1..11)]) - diff --git a/tests/exhaustive/autogen/gen32/expected/model_3_3_3.eprime b/tests/exhaustive/autogen/gen32/expected/model_3_3_3.eprime deleted file mode 100644 index d30539480c..0000000000 --- a/tests/exhaustive/autogen/gen32/expected/model_3_3_3.eprime +++ /dev/null @@ -1,24 +0,0 @@ -language ESSENCE' 1.0 - -letting let1 be -4 -find var2_ExplicitVarSizeWithMarker_Marker: int(0..11) -find var2_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..11)] of int(-4..5, 2) -branching on [var2_ExplicitVarSizeWithMarker_Marker, var2_ExplicitVarSizeWithMarker_Values] -such that - or([q5 <= var2_ExplicitVarSizeWithMarker_Marker /\ - !or([q7 <= var2_ExplicitVarSizeWithMarker_Marker /\ - var2_ExplicitVarSizeWithMarker_Values[q7] = var2_ExplicitVarSizeWithMarker_Values[q5] - | q7 : int(1..11)]) - | q5 : int(1..11)]) - \/ - or([q8 <= var2_ExplicitVarSizeWithMarker_Marker /\ - !or([q10 <= var2_ExplicitVarSizeWithMarker_Marker /\ - var2_ExplicitVarSizeWithMarker_Values[q10] = var2_ExplicitVarSizeWithMarker_Values[q8] - | q10 : int(1..11)]) - | q8 : int(1..11)]), - and([q1 + 1 <= var2_ExplicitVarSizeWithMarker_Marker -> - var2_ExplicitVarSizeWithMarker_Values[q1] < var2_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..10)]), - and([q2 > var2_ExplicitVarSizeWithMarker_Marker -> var2_ExplicitVarSizeWithMarker_Values[q2] = -4 - | q2 : int(1..11)]) - diff --git a/tests/exhaustive/autogen/gen32/expected/model_3_3_4.eprime b/tests/exhaustive/autogen/gen32/expected/model_3_3_4.eprime deleted file mode 100644 index 9cb3e7b96b..0000000000 --- a/tests/exhaustive/autogen/gen32/expected/model_3_3_4.eprime +++ /dev/null @@ -1,44 +0,0 @@ -language ESSENCE' 1.0 - -letting let1 be -4 -find var2_ExplicitVarSizeWithMarker_Marker: int(0..11) -find var2_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..11)] of int(-4..5, 2) -find var2_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..11)] of bool -find var2_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..11)] of int(-4..5, 2) -branching on - [var2_ExplicitVarSizeWithFlags_Flags, var2_ExplicitVarSizeWithFlags_Values, var2_ExplicitVarSizeWithMarker_Marker, - var2_ExplicitVarSizeWithMarker_Values] -such that - or([q18 <= var2_ExplicitVarSizeWithMarker_Marker /\ - !or([q20 <= var2_ExplicitVarSizeWithMarker_Marker /\ - var2_ExplicitVarSizeWithMarker_Values[q20] = var2_ExplicitVarSizeWithMarker_Values[q18] - | q20 : int(1..11)]) - | q18 : int(1..11)]) - \/ - or([q21 <= var2_ExplicitVarSizeWithMarker_Marker /\ - !or([q23 <= var2_ExplicitVarSizeWithMarker_Marker /\ - var2_ExplicitVarSizeWithMarker_Values[q23] = var2_ExplicitVarSizeWithMarker_Values[q21] - | q23 : int(1..11)]) - | q21 : int(1..11)]), - and([q1 + 1 <= var2_ExplicitVarSizeWithMarker_Marker -> - var2_ExplicitVarSizeWithMarker_Values[q1] < var2_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..10)]), - and([q2 > var2_ExplicitVarSizeWithMarker_Marker -> var2_ExplicitVarSizeWithMarker_Values[q2] = -4 - | q2 : int(1..11)]), - and([var2_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> - var2_ExplicitVarSizeWithFlags_Values[q4] < var2_ExplicitVarSizeWithFlags_Values[q4 + 1] - | q4 : int(1..10)]), - and([var2_ExplicitVarSizeWithFlags_Flags[q5] = false -> var2_ExplicitVarSizeWithFlags_Values[q5] = -4 - | q5 : int(1..11)]), - and([var2_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> var2_ExplicitVarSizeWithFlags_Flags[q6] | q6 : int(1..10)]), - and([var2_ExplicitVarSizeWithFlags_Flags[q10] -> - or([q12 <= var2_ExplicitVarSizeWithMarker_Marker /\ - var2_ExplicitVarSizeWithMarker_Values[q12] = var2_ExplicitVarSizeWithFlags_Values[q10] - | q12 : int(1..11)]) - | q10 : int(1..11)]), - and([q14 <= var2_ExplicitVarSizeWithMarker_Marker -> - or([var2_ExplicitVarSizeWithFlags_Flags[q16] /\ - var2_ExplicitVarSizeWithFlags_Values[q16] = var2_ExplicitVarSizeWithMarker_Values[q14] - | q16 : int(1..11)]) - | q14 : int(1..11)]) - diff --git a/tests/exhaustive/autogen/gen32/expected/model_3_4_1.eprime b/tests/exhaustive/autogen/gen32/expected/model_3_4_1.eprime deleted file mode 100644 index 4ec1f855f0..0000000000 --- a/tests/exhaustive/autogen/gen32/expected/model_3_4_1.eprime +++ /dev/null @@ -1,57 +0,0 @@ -language ESSENCE' 1.0 - -letting let1 be -4 -find var2_ExplicitVarSizeWithMarker_Marker: int(0..11) -find var2_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..11)] of int(-4..5, 2) -find var2_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..11)] of bool -find var2_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..11)] of int(-4..5, 2) -find var2_Occurrence: matrix indexed by [int(-4..5, 2)] of bool -branching on - [var2_Occurrence, var2_ExplicitVarSizeWithMarker_Marker, var2_ExplicitVarSizeWithMarker_Values, - var2_ExplicitVarSizeWithFlags_Flags, var2_ExplicitVarSizeWithFlags_Values] -such that - or([q19 <= var2_ExplicitVarSizeWithMarker_Marker /\ - !or([var2_ExplicitVarSizeWithFlags_Flags[q21] /\ - var2_ExplicitVarSizeWithFlags_Values[q21] = var2_ExplicitVarSizeWithMarker_Values[q19] - | q21 : int(1..11)]) - | q19 : int(1..11)]) - \/ - or([var2_ExplicitVarSizeWithFlags_Flags[q22] /\ - !or([q24 <= var2_ExplicitVarSizeWithMarker_Marker /\ - var2_ExplicitVarSizeWithMarker_Values[q24] = var2_ExplicitVarSizeWithFlags_Values[q22] - | q24 : int(1..11)]) - | q22 : int(1..11)]), - and([q1 + 1 <= var2_ExplicitVarSizeWithMarker_Marker -> - var2_ExplicitVarSizeWithMarker_Values[q1] < var2_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..10)]), - and([q2 > var2_ExplicitVarSizeWithMarker_Marker -> var2_ExplicitVarSizeWithMarker_Values[q2] = -4 - | q2 : int(1..11)]), - and([var2_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> - var2_ExplicitVarSizeWithFlags_Values[q4] < var2_ExplicitVarSizeWithFlags_Values[q4 + 1] - | q4 : int(1..10)]), - and([var2_ExplicitVarSizeWithFlags_Flags[q5] = false -> var2_ExplicitVarSizeWithFlags_Values[q5] = -4 - | q5 : int(1..11)]), - and([var2_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> var2_ExplicitVarSizeWithFlags_Flags[q6] | q6 : int(1..10)]), - and([var2_ExplicitVarSizeWithFlags_Flags[q10] -> - or([q12 <= var2_ExplicitVarSizeWithMarker_Marker /\ - var2_ExplicitVarSizeWithMarker_Values[q12] = var2_ExplicitVarSizeWithFlags_Values[q10] - | q12 : int(1..11)]) - | q10 : int(1..11)]), - and([q14 <= var2_ExplicitVarSizeWithMarker_Marker -> - or([var2_ExplicitVarSizeWithFlags_Flags[q16] /\ - var2_ExplicitVarSizeWithFlags_Values[q16] = var2_ExplicitVarSizeWithMarker_Values[q14] - | q16 : int(1..11)]) - | q14 : int(1..11)]), - and([var2_Occurrence[q25] -> - or([q27 <= var2_ExplicitVarSizeWithMarker_Marker /\ var2_ExplicitVarSizeWithMarker_Values[q27] = q25 - | q27 : int(1..11)]) - | q25 : int(-4..5, 2)]), - and([q29 <= var2_ExplicitVarSizeWithMarker_Marker -> var2_Occurrence[var2_ExplicitVarSizeWithMarker_Values[q29]] - | q29 : int(1..11)]), - and([var2_Occurrence[q30] -> - or([var2_ExplicitVarSizeWithFlags_Flags[q32] /\ var2_ExplicitVarSizeWithFlags_Values[q32] = q30 - | q32 : int(1..11)]) - | q30 : int(-4..5, 2)]), - and([var2_ExplicitVarSizeWithFlags_Flags[q34] -> var2_Occurrence[var2_ExplicitVarSizeWithFlags_Values[q34]] - | q34 : int(1..11)]) - diff --git a/tests/exhaustive/autogen/gen32/expected/model_3_4_2.eprime b/tests/exhaustive/autogen/gen32/expected/model_3_4_2.eprime deleted file mode 100644 index df59cf3084..0000000000 --- a/tests/exhaustive/autogen/gen32/expected/model_3_4_2.eprime +++ /dev/null @@ -1,69 +0,0 @@ -language ESSENCE' 1.0 - -letting let1 be -4 -find var2_ExplicitVarSizeWithMarker_Marker: int(0..11) -find var2_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..11)] of int(-4..5, 2) -find var2_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..11)] of bool -find var2_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..11)] of int(-4..5, 2) -find var2_ExplicitVarSizeWithDummy: matrix indexed by [int(1..11)] of int(-4..5, 2, 6) -branching on - [var2_ExplicitVarSizeWithDummy, var2_ExplicitVarSizeWithMarker_Marker, var2_ExplicitVarSizeWithMarker_Values, - var2_ExplicitVarSizeWithFlags_Flags, var2_ExplicitVarSizeWithFlags_Values] -such that - or([q38 <= var2_ExplicitVarSizeWithMarker_Marker /\ - !or([var2_ExplicitVarSizeWithFlags_Flags[q40] /\ - var2_ExplicitVarSizeWithFlags_Values[q40] = var2_ExplicitVarSizeWithMarker_Values[q38] - | q40 : int(1..11)]) - | q38 : int(1..11)]) - \/ - or([var2_ExplicitVarSizeWithFlags_Flags[q41] /\ - !or([q43 <= var2_ExplicitVarSizeWithMarker_Marker /\ - var2_ExplicitVarSizeWithMarker_Values[q43] = var2_ExplicitVarSizeWithFlags_Values[q41] - | q43 : int(1..11)]) - | q41 : int(1..11)]), - and([q1 + 1 <= var2_ExplicitVarSizeWithMarker_Marker -> - var2_ExplicitVarSizeWithMarker_Values[q1] < var2_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..10)]), - and([q2 > var2_ExplicitVarSizeWithMarker_Marker -> var2_ExplicitVarSizeWithMarker_Values[q2] = -4 - | q2 : int(1..11)]), - and([var2_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> - var2_ExplicitVarSizeWithFlags_Values[q4] < var2_ExplicitVarSizeWithFlags_Values[q4 + 1] - | q4 : int(1..10)]), - and([var2_ExplicitVarSizeWithFlags_Flags[q5] = false -> var2_ExplicitVarSizeWithFlags_Values[q5] = -4 - | q5 : int(1..11)]), - and([var2_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> var2_ExplicitVarSizeWithFlags_Flags[q6] | q6 : int(1..10)]), - and([var2_ExplicitVarSizeWithFlags_Flags[q10] -> - or([q12 <= var2_ExplicitVarSizeWithMarker_Marker /\ - var2_ExplicitVarSizeWithMarker_Values[q12] = var2_ExplicitVarSizeWithFlags_Values[q10] - | q12 : int(1..11)]) - | q10 : int(1..11)]), - and([q14 <= var2_ExplicitVarSizeWithMarker_Marker -> - or([var2_ExplicitVarSizeWithFlags_Flags[q16] /\ - var2_ExplicitVarSizeWithFlags_Values[q16] = var2_ExplicitVarSizeWithMarker_Values[q14] - | q16 : int(1..11)]) - | q14 : int(1..11)]), - and([var2_ExplicitVarSizeWithDummy[q17] < var2_ExplicitVarSizeWithDummy[q17 + 1] \/ - var2_ExplicitVarSizeWithDummy[q17] = 6 - | q17 : int(1..10)]), - and([var2_ExplicitVarSizeWithDummy[q18] = 6 -> var2_ExplicitVarSizeWithDummy[q18 + 1] = 6 | q18 : int(1..10)]), - and([var2_ExplicitVarSizeWithDummy[q22] != 6 -> - or([q24 <= var2_ExplicitVarSizeWithMarker_Marker /\ - var2_ExplicitVarSizeWithMarker_Values[q24] = var2_ExplicitVarSizeWithDummy[q22] - | q24 : int(1..11)]) - | q22 : int(1..11)]), - and([q26 <= var2_ExplicitVarSizeWithMarker_Marker -> - or([var2_ExplicitVarSizeWithDummy[q28] != 6 /\ - var2_ExplicitVarSizeWithDummy[q28] = var2_ExplicitVarSizeWithMarker_Values[q26] - | q28 : int(1..11)]) - | q26 : int(1..11)]), - and([var2_ExplicitVarSizeWithDummy[q30] != 6 -> - or([var2_ExplicitVarSizeWithFlags_Flags[q32] /\ - var2_ExplicitVarSizeWithFlags_Values[q32] = var2_ExplicitVarSizeWithDummy[q30] - | q32 : int(1..11)]) - | q30 : int(1..11)]), - and([var2_ExplicitVarSizeWithFlags_Flags[q34] -> - or([var2_ExplicitVarSizeWithDummy[q36] != 6 /\ - var2_ExplicitVarSizeWithDummy[q36] = var2_ExplicitVarSizeWithFlags_Values[q34] - | q36 : int(1..11)]) - | q34 : int(1..11)]) - diff --git a/tests/exhaustive/autogen/gen32/expected/model_3_4_3.eprime b/tests/exhaustive/autogen/gen32/expected/model_3_4_3.eprime deleted file mode 100644 index 4785a0c0ec..0000000000 --- a/tests/exhaustive/autogen/gen32/expected/model_3_4_3.eprime +++ /dev/null @@ -1,44 +0,0 @@ -language ESSENCE' 1.0 - -letting let1 be -4 -find var2_ExplicitVarSizeWithMarker_Marker: int(0..11) -find var2_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..11)] of int(-4..5, 2) -find var2_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..11)] of bool -find var2_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..11)] of int(-4..5, 2) -branching on - [var2_ExplicitVarSizeWithFlags_Flags, var2_ExplicitVarSizeWithFlags_Values, var2_ExplicitVarSizeWithMarker_Marker, - var2_ExplicitVarSizeWithMarker_Values] -such that - or([q18 <= var2_ExplicitVarSizeWithMarker_Marker /\ - !or([var2_ExplicitVarSizeWithFlags_Flags[q20] /\ - var2_ExplicitVarSizeWithFlags_Values[q20] = var2_ExplicitVarSizeWithMarker_Values[q18] - | q20 : int(1..11)]) - | q18 : int(1..11)]) - \/ - or([var2_ExplicitVarSizeWithFlags_Flags[q21] /\ - !or([q23 <= var2_ExplicitVarSizeWithMarker_Marker /\ - var2_ExplicitVarSizeWithMarker_Values[q23] = var2_ExplicitVarSizeWithFlags_Values[q21] - | q23 : int(1..11)]) - | q21 : int(1..11)]), - and([q1 + 1 <= var2_ExplicitVarSizeWithMarker_Marker -> - var2_ExplicitVarSizeWithMarker_Values[q1] < var2_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..10)]), - and([q2 > var2_ExplicitVarSizeWithMarker_Marker -> var2_ExplicitVarSizeWithMarker_Values[q2] = -4 - | q2 : int(1..11)]), - and([var2_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> - var2_ExplicitVarSizeWithFlags_Values[q4] < var2_ExplicitVarSizeWithFlags_Values[q4 + 1] - | q4 : int(1..10)]), - and([var2_ExplicitVarSizeWithFlags_Flags[q5] = false -> var2_ExplicitVarSizeWithFlags_Values[q5] = -4 - | q5 : int(1..11)]), - and([var2_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> var2_ExplicitVarSizeWithFlags_Flags[q6] | q6 : int(1..10)]), - and([var2_ExplicitVarSizeWithFlags_Flags[q10] -> - or([q12 <= var2_ExplicitVarSizeWithMarker_Marker /\ - var2_ExplicitVarSizeWithMarker_Values[q12] = var2_ExplicitVarSizeWithFlags_Values[q10] - | q12 : int(1..11)]) - | q10 : int(1..11)]), - and([q14 <= var2_ExplicitVarSizeWithMarker_Marker -> - or([var2_ExplicitVarSizeWithFlags_Flags[q16] /\ - var2_ExplicitVarSizeWithFlags_Values[q16] = var2_ExplicitVarSizeWithMarker_Values[q14] - | q16 : int(1..11)]) - | q14 : int(1..11)]) - diff --git a/tests/exhaustive/autogen/gen32/expected/model_3_4_4.eprime b/tests/exhaustive/autogen/gen32/expected/model_3_4_4.eprime deleted file mode 100644 index 4785a0c0ec..0000000000 --- a/tests/exhaustive/autogen/gen32/expected/model_3_4_4.eprime +++ /dev/null @@ -1,44 +0,0 @@ -language ESSENCE' 1.0 - -letting let1 be -4 -find var2_ExplicitVarSizeWithMarker_Marker: int(0..11) -find var2_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..11)] of int(-4..5, 2) -find var2_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..11)] of bool -find var2_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..11)] of int(-4..5, 2) -branching on - [var2_ExplicitVarSizeWithFlags_Flags, var2_ExplicitVarSizeWithFlags_Values, var2_ExplicitVarSizeWithMarker_Marker, - var2_ExplicitVarSizeWithMarker_Values] -such that - or([q18 <= var2_ExplicitVarSizeWithMarker_Marker /\ - !or([var2_ExplicitVarSizeWithFlags_Flags[q20] /\ - var2_ExplicitVarSizeWithFlags_Values[q20] = var2_ExplicitVarSizeWithMarker_Values[q18] - | q20 : int(1..11)]) - | q18 : int(1..11)]) - \/ - or([var2_ExplicitVarSizeWithFlags_Flags[q21] /\ - !or([q23 <= var2_ExplicitVarSizeWithMarker_Marker /\ - var2_ExplicitVarSizeWithMarker_Values[q23] = var2_ExplicitVarSizeWithFlags_Values[q21] - | q23 : int(1..11)]) - | q21 : int(1..11)]), - and([q1 + 1 <= var2_ExplicitVarSizeWithMarker_Marker -> - var2_ExplicitVarSizeWithMarker_Values[q1] < var2_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..10)]), - and([q2 > var2_ExplicitVarSizeWithMarker_Marker -> var2_ExplicitVarSizeWithMarker_Values[q2] = -4 - | q2 : int(1..11)]), - and([var2_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> - var2_ExplicitVarSizeWithFlags_Values[q4] < var2_ExplicitVarSizeWithFlags_Values[q4 + 1] - | q4 : int(1..10)]), - and([var2_ExplicitVarSizeWithFlags_Flags[q5] = false -> var2_ExplicitVarSizeWithFlags_Values[q5] = -4 - | q5 : int(1..11)]), - and([var2_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> var2_ExplicitVarSizeWithFlags_Flags[q6] | q6 : int(1..10)]), - and([var2_ExplicitVarSizeWithFlags_Flags[q10] -> - or([q12 <= var2_ExplicitVarSizeWithMarker_Marker /\ - var2_ExplicitVarSizeWithMarker_Values[q12] = var2_ExplicitVarSizeWithFlags_Values[q10] - | q12 : int(1..11)]) - | q10 : int(1..11)]), - and([q14 <= var2_ExplicitVarSizeWithMarker_Marker -> - or([var2_ExplicitVarSizeWithFlags_Flags[q16] /\ - var2_ExplicitVarSizeWithFlags_Values[q16] = var2_ExplicitVarSizeWithMarker_Values[q14] - | q16 : int(1..11)]) - | q14 : int(1..11)]) - diff --git a/tests/exhaustive/autogen/gen32/expected/model_4_1_1.eprime b/tests/exhaustive/autogen/gen32/expected/model_4_1_1.eprime deleted file mode 100644 index 5c6854637e..0000000000 --- a/tests/exhaustive/autogen/gen32/expected/model_4_1_1.eprime +++ /dev/null @@ -1,28 +0,0 @@ -language ESSENCE' 1.0 - -letting let1 be -4 -find var2_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..11)] of bool -find var2_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..11)] of int(-4..5, 2) -find var2_Occurrence: matrix indexed by [int(-4..5, 2)] of bool -branching on [var2_Occurrence, var2_ExplicitVarSizeWithFlags_Flags, var2_ExplicitVarSizeWithFlags_Values] -such that - or([var2_ExplicitVarSizeWithFlags_Flags[q8] /\ !var2_Occurrence[var2_ExplicitVarSizeWithFlags_Values[q8]] - | q8 : int(1..11)]) - \/ - or([var2_Occurrence[q7] /\ - !or([var2_ExplicitVarSizeWithFlags_Flags[q10] /\ var2_ExplicitVarSizeWithFlags_Values[q10] = q7 - | q10 : int(1..11)]) - | q7 : int(-4..5, 2)]), - and([var2_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - var2_ExplicitVarSizeWithFlags_Values[q1] < var2_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..10)]), - and([var2_ExplicitVarSizeWithFlags_Flags[q2] = false -> var2_ExplicitVarSizeWithFlags_Values[q2] = -4 - | q2 : int(1..11)]), - and([var2_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> var2_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..10)]), - and([var2_Occurrence[q11] -> - or([var2_ExplicitVarSizeWithFlags_Flags[q13] /\ var2_ExplicitVarSizeWithFlags_Values[q13] = q11 - | q13 : int(1..11)]) - | q11 : int(-4..5, 2)]), - and([var2_ExplicitVarSizeWithFlags_Flags[q15] -> var2_Occurrence[var2_ExplicitVarSizeWithFlags_Values[q15]] - | q15 : int(1..11)]) - diff --git a/tests/exhaustive/autogen/gen32/expected/model_4_1_2.eprime b/tests/exhaustive/autogen/gen32/expected/model_4_1_2.eprime deleted file mode 100644 index 0f8965d6c5..0000000000 --- a/tests/exhaustive/autogen/gen32/expected/model_4_1_2.eprime +++ /dev/null @@ -1,50 +0,0 @@ -language ESSENCE' 1.0 - -letting let1 be -4 -find var2_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..11)] of bool -find var2_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..11)] of int(-4..5, 2) -find var2_Occurrence: matrix indexed by [int(-4..5, 2)] of bool -find var2_ExplicitVarSizeWithDummy: matrix indexed by [int(1..11)] of int(-4..5, 2, 6) -branching on - [var2_ExplicitVarSizeWithDummy, var2_ExplicitVarSizeWithFlags_Flags, var2_ExplicitVarSizeWithFlags_Values, - var2_Occurrence] -such that - or([var2_ExplicitVarSizeWithFlags_Flags[q25] /\ !var2_Occurrence[var2_ExplicitVarSizeWithFlags_Values[q25]] - | q25 : int(1..11)]) - \/ - or([var2_Occurrence[q24] /\ - !or([var2_ExplicitVarSizeWithFlags_Flags[q27] /\ var2_ExplicitVarSizeWithFlags_Values[q27] = q24 - | q27 : int(1..11)]) - | q24 : int(-4..5, 2)]), - and([var2_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - var2_ExplicitVarSizeWithFlags_Values[q1] < var2_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..10)]), - and([var2_ExplicitVarSizeWithFlags_Flags[q2] = false -> var2_ExplicitVarSizeWithFlags_Values[q2] = -4 - | q2 : int(1..11)]), - and([var2_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> var2_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..10)]), - and([var2_Occurrence[q28] -> - or([var2_ExplicitVarSizeWithFlags_Flags[q30] /\ var2_ExplicitVarSizeWithFlags_Values[q30] = q28 - | q30 : int(1..11)]) - | q28 : int(-4..5, 2)]), - and([var2_ExplicitVarSizeWithFlags_Flags[q32] -> var2_Occurrence[var2_ExplicitVarSizeWithFlags_Values[q32]] - | q32 : int(1..11)]), - and([var2_ExplicitVarSizeWithDummy[q7] < var2_ExplicitVarSizeWithDummy[q7 + 1] \/ - var2_ExplicitVarSizeWithDummy[q7] = 6 - | q7 : int(1..10)]), - and([var2_ExplicitVarSizeWithDummy[q8] = 6 -> var2_ExplicitVarSizeWithDummy[q8 + 1] = 6 | q8 : int(1..10)]), - and([var2_ExplicitVarSizeWithDummy[q12] != 6 -> - or([var2_ExplicitVarSizeWithFlags_Flags[q14] /\ - var2_ExplicitVarSizeWithFlags_Values[q14] = var2_ExplicitVarSizeWithDummy[q12] - | q14 : int(1..11)]) - | q12 : int(1..11)]), - and([var2_ExplicitVarSizeWithFlags_Flags[q16] -> - or([var2_ExplicitVarSizeWithDummy[q18] != 6 /\ - var2_ExplicitVarSizeWithDummy[q18] = var2_ExplicitVarSizeWithFlags_Values[q16] - | q18 : int(1..11)]) - | q16 : int(1..11)]), - and([var2_ExplicitVarSizeWithDummy[q20] != 6 -> var2_Occurrence[var2_ExplicitVarSizeWithDummy[q20]] - | q20 : int(1..11)]), - and([var2_Occurrence[q21] -> - or([var2_ExplicitVarSizeWithDummy[q23] != 6 /\ var2_ExplicitVarSizeWithDummy[q23] = q21 | q23 : int(1..11)]) - | q21 : int(-4..5, 2)]) - diff --git a/tests/exhaustive/autogen/gen32/expected/model_4_1_3.eprime b/tests/exhaustive/autogen/gen32/expected/model_4_1_3.eprime deleted file mode 100644 index 6fff70a69f..0000000000 --- a/tests/exhaustive/autogen/gen32/expected/model_4_1_3.eprime +++ /dev/null @@ -1,53 +0,0 @@ -language ESSENCE' 1.0 - -letting let1 be -4 -find var2_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..11)] of bool -find var2_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..11)] of int(-4..5, 2) -find var2_Occurrence: matrix indexed by [int(-4..5, 2)] of bool -find var2_ExplicitVarSizeWithMarker_Marker: int(0..11) -find var2_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..11)] of int(-4..5, 2) -branching on - [var2_ExplicitVarSizeWithMarker_Marker, var2_ExplicitVarSizeWithMarker_Values, var2_ExplicitVarSizeWithFlags_Flags, - var2_ExplicitVarSizeWithFlags_Values, var2_Occurrence] -such that - or([var2_ExplicitVarSizeWithFlags_Flags[q24] /\ !var2_Occurrence[var2_ExplicitVarSizeWithFlags_Values[q24]] - | q24 : int(1..11)]) - \/ - or([var2_Occurrence[q23] /\ - !or([var2_ExplicitVarSizeWithFlags_Flags[q26] /\ var2_ExplicitVarSizeWithFlags_Values[q26] = q23 - | q26 : int(1..11)]) - | q23 : int(-4..5, 2)]), - and([var2_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - var2_ExplicitVarSizeWithFlags_Values[q1] < var2_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..10)]), - and([var2_ExplicitVarSizeWithFlags_Flags[q2] = false -> var2_ExplicitVarSizeWithFlags_Values[q2] = -4 - | q2 : int(1..11)]), - and([var2_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> var2_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..10)]), - and([var2_Occurrence[q27] -> - or([var2_ExplicitVarSizeWithFlags_Flags[q29] /\ var2_ExplicitVarSizeWithFlags_Values[q29] = q27 - | q29 : int(1..11)]) - | q27 : int(-4..5, 2)]), - and([var2_ExplicitVarSizeWithFlags_Flags[q31] -> var2_Occurrence[var2_ExplicitVarSizeWithFlags_Values[q31]] - | q31 : int(1..11)]), - and([q7 + 1 <= var2_ExplicitVarSizeWithMarker_Marker -> - var2_ExplicitVarSizeWithMarker_Values[q7] < var2_ExplicitVarSizeWithMarker_Values[q7 + 1] - | q7 : int(1..10)]), - and([q8 > var2_ExplicitVarSizeWithMarker_Marker -> var2_ExplicitVarSizeWithMarker_Values[q8] = -4 - | q8 : int(1..11)]), - and([q11 <= var2_ExplicitVarSizeWithMarker_Marker -> - or([var2_ExplicitVarSizeWithFlags_Flags[q13] /\ - var2_ExplicitVarSizeWithFlags_Values[q13] = var2_ExplicitVarSizeWithMarker_Values[q11] - | q13 : int(1..11)]) - | q11 : int(1..11)]), - and([var2_ExplicitVarSizeWithFlags_Flags[q15] -> - or([q17 <= var2_ExplicitVarSizeWithMarker_Marker /\ - var2_ExplicitVarSizeWithMarker_Values[q17] = var2_ExplicitVarSizeWithFlags_Values[q15] - | q17 : int(1..11)]) - | q15 : int(1..11)]), - and([q19 <= var2_ExplicitVarSizeWithMarker_Marker -> var2_Occurrence[var2_ExplicitVarSizeWithMarker_Values[q19]] - | q19 : int(1..11)]), - and([var2_Occurrence[q20] -> - or([q22 <= var2_ExplicitVarSizeWithMarker_Marker /\ var2_ExplicitVarSizeWithMarker_Values[q22] = q20 - | q22 : int(1..11)]) - | q20 : int(-4..5, 2)]) - diff --git a/tests/exhaustive/autogen/gen32/expected/model_4_1_4.eprime b/tests/exhaustive/autogen/gen32/expected/model_4_1_4.eprime deleted file mode 100644 index 5c6854637e..0000000000 --- a/tests/exhaustive/autogen/gen32/expected/model_4_1_4.eprime +++ /dev/null @@ -1,28 +0,0 @@ -language ESSENCE' 1.0 - -letting let1 be -4 -find var2_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..11)] of bool -find var2_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..11)] of int(-4..5, 2) -find var2_Occurrence: matrix indexed by [int(-4..5, 2)] of bool -branching on [var2_Occurrence, var2_ExplicitVarSizeWithFlags_Flags, var2_ExplicitVarSizeWithFlags_Values] -such that - or([var2_ExplicitVarSizeWithFlags_Flags[q8] /\ !var2_Occurrence[var2_ExplicitVarSizeWithFlags_Values[q8]] - | q8 : int(1..11)]) - \/ - or([var2_Occurrence[q7] /\ - !or([var2_ExplicitVarSizeWithFlags_Flags[q10] /\ var2_ExplicitVarSizeWithFlags_Values[q10] = q7 - | q10 : int(1..11)]) - | q7 : int(-4..5, 2)]), - and([var2_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - var2_ExplicitVarSizeWithFlags_Values[q1] < var2_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..10)]), - and([var2_ExplicitVarSizeWithFlags_Flags[q2] = false -> var2_ExplicitVarSizeWithFlags_Values[q2] = -4 - | q2 : int(1..11)]), - and([var2_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> var2_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..10)]), - and([var2_Occurrence[q11] -> - or([var2_ExplicitVarSizeWithFlags_Flags[q13] /\ var2_ExplicitVarSizeWithFlags_Values[q13] = q11 - | q13 : int(1..11)]) - | q11 : int(-4..5, 2)]), - and([var2_ExplicitVarSizeWithFlags_Flags[q15] -> var2_Occurrence[var2_ExplicitVarSizeWithFlags_Values[q15]] - | q15 : int(1..11)]) - diff --git a/tests/exhaustive/autogen/gen32/expected/model_4_2_1.eprime b/tests/exhaustive/autogen/gen32/expected/model_4_2_1.eprime deleted file mode 100644 index b7b3b2ad4a..0000000000 --- a/tests/exhaustive/autogen/gen32/expected/model_4_2_1.eprime +++ /dev/null @@ -1,54 +0,0 @@ -language ESSENCE' 1.0 - -letting let1 be -4 -find var2_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..11)] of bool -find var2_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..11)] of int(-4..5, 2) -find var2_ExplicitVarSizeWithDummy: matrix indexed by [int(1..11)] of int(-4..5, 2, 6) -find var2_Occurrence: matrix indexed by [int(-4..5, 2)] of bool -branching on - [var2_Occurrence, var2_ExplicitVarSizeWithFlags_Flags, var2_ExplicitVarSizeWithFlags_Values, - var2_ExplicitVarSizeWithDummy] -such that - or([var2_ExplicitVarSizeWithFlags_Flags[q20] /\ - !or([var2_ExplicitVarSizeWithDummy[q22] != 6 /\ - var2_ExplicitVarSizeWithDummy[q22] = var2_ExplicitVarSizeWithFlags_Values[q20] - | q22 : int(1..11)]) - | q20 : int(1..11)]) - \/ - or([var2_ExplicitVarSizeWithDummy[q23] != 6 /\ - !or([var2_ExplicitVarSizeWithFlags_Flags[q25] /\ - var2_ExplicitVarSizeWithFlags_Values[q25] = var2_ExplicitVarSizeWithDummy[q23] - | q25 : int(1..11)]) - | q23 : int(1..11)]), - and([var2_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - var2_ExplicitVarSizeWithFlags_Values[q1] < var2_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..10)]), - and([var2_ExplicitVarSizeWithFlags_Flags[q2] = false -> var2_ExplicitVarSizeWithFlags_Values[q2] = -4 - | q2 : int(1..11)]), - and([var2_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> var2_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..10)]), - and([var2_ExplicitVarSizeWithDummy[q6] < var2_ExplicitVarSizeWithDummy[q6 + 1] \/ - var2_ExplicitVarSizeWithDummy[q6] = 6 - | q6 : int(1..10)]), - and([var2_ExplicitVarSizeWithDummy[q7] = 6 -> var2_ExplicitVarSizeWithDummy[q7 + 1] = 6 | q7 : int(1..10)]), - and([var2_ExplicitVarSizeWithDummy[q11] != 6 -> - or([var2_ExplicitVarSizeWithFlags_Flags[q13] /\ - var2_ExplicitVarSizeWithFlags_Values[q13] = var2_ExplicitVarSizeWithDummy[q11] - | q13 : int(1..11)]) - | q11 : int(1..11)]), - and([var2_ExplicitVarSizeWithFlags_Flags[q15] -> - or([var2_ExplicitVarSizeWithDummy[q17] != 6 /\ - var2_ExplicitVarSizeWithDummy[q17] = var2_ExplicitVarSizeWithFlags_Values[q15] - | q17 : int(1..11)]) - | q15 : int(1..11)]), - and([var2_Occurrence[q26] -> - or([var2_ExplicitVarSizeWithFlags_Flags[q28] /\ var2_ExplicitVarSizeWithFlags_Values[q28] = q26 - | q28 : int(1..11)]) - | q26 : int(-4..5, 2)]), - and([var2_ExplicitVarSizeWithFlags_Flags[q30] -> var2_Occurrence[var2_ExplicitVarSizeWithFlags_Values[q30]] - | q30 : int(1..11)]), - and([var2_Occurrence[q31] -> - or([var2_ExplicitVarSizeWithDummy[q33] != 6 /\ var2_ExplicitVarSizeWithDummy[q33] = q31 | q33 : int(1..11)]) - | q31 : int(-4..5, 2)]), - and([var2_ExplicitVarSizeWithDummy[q35] != 6 -> var2_Occurrence[var2_ExplicitVarSizeWithDummy[q35]] - | q35 : int(1..11)]) - diff --git a/tests/exhaustive/autogen/gen32/expected/model_4_2_2.eprime b/tests/exhaustive/autogen/gen32/expected/model_4_2_2.eprime deleted file mode 100644 index 9a094995de..0000000000 --- a/tests/exhaustive/autogen/gen32/expected/model_4_2_2.eprime +++ /dev/null @@ -1,40 +0,0 @@ -language ESSENCE' 1.0 - -letting let1 be -4 -find var2_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..11)] of bool -find var2_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..11)] of int(-4..5, 2) -find var2_ExplicitVarSizeWithDummy: matrix indexed by [int(1..11)] of int(-4..5, 2, 6) -branching on [var2_ExplicitVarSizeWithDummy, var2_ExplicitVarSizeWithFlags_Flags, var2_ExplicitVarSizeWithFlags_Values] -such that - or([var2_ExplicitVarSizeWithFlags_Flags[q19] /\ - !or([var2_ExplicitVarSizeWithDummy[q21] != 6 /\ - var2_ExplicitVarSizeWithDummy[q21] = var2_ExplicitVarSizeWithFlags_Values[q19] - | q21 : int(1..11)]) - | q19 : int(1..11)]) - \/ - or([var2_ExplicitVarSizeWithDummy[q22] != 6 /\ - !or([var2_ExplicitVarSizeWithFlags_Flags[q24] /\ - var2_ExplicitVarSizeWithFlags_Values[q24] = var2_ExplicitVarSizeWithDummy[q22] - | q24 : int(1..11)]) - | q22 : int(1..11)]), - and([var2_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - var2_ExplicitVarSizeWithFlags_Values[q1] < var2_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..10)]), - and([var2_ExplicitVarSizeWithFlags_Flags[q2] = false -> var2_ExplicitVarSizeWithFlags_Values[q2] = -4 - | q2 : int(1..11)]), - and([var2_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> var2_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..10)]), - and([var2_ExplicitVarSizeWithDummy[q6] < var2_ExplicitVarSizeWithDummy[q6 + 1] \/ - var2_ExplicitVarSizeWithDummy[q6] = 6 - | q6 : int(1..10)]), - and([var2_ExplicitVarSizeWithDummy[q7] = 6 -> var2_ExplicitVarSizeWithDummy[q7 + 1] = 6 | q7 : int(1..10)]), - and([var2_ExplicitVarSizeWithDummy[q11] != 6 -> - or([var2_ExplicitVarSizeWithFlags_Flags[q13] /\ - var2_ExplicitVarSizeWithFlags_Values[q13] = var2_ExplicitVarSizeWithDummy[q11] - | q13 : int(1..11)]) - | q11 : int(1..11)]), - and([var2_ExplicitVarSizeWithFlags_Flags[q15] -> - or([var2_ExplicitVarSizeWithDummy[q17] != 6 /\ - var2_ExplicitVarSizeWithDummy[q17] = var2_ExplicitVarSizeWithFlags_Values[q15] - | q17 : int(1..11)]) - | q15 : int(1..11)]) - diff --git a/tests/exhaustive/autogen/gen32/expected/model_4_2_3.eprime b/tests/exhaustive/autogen/gen32/expected/model_4_2_3.eprime deleted file mode 100644 index ff001560cb..0000000000 --- a/tests/exhaustive/autogen/gen32/expected/model_4_2_3.eprime +++ /dev/null @@ -1,69 +0,0 @@ -language ESSENCE' 1.0 - -letting let1 be -4 -find var2_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..11)] of bool -find var2_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..11)] of int(-4..5, 2) -find var2_ExplicitVarSizeWithDummy: matrix indexed by [int(1..11)] of int(-4..5, 2, 6) -find var2_ExplicitVarSizeWithMarker_Marker: int(0..11) -find var2_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..11)] of int(-4..5, 2) -branching on - [var2_ExplicitVarSizeWithMarker_Marker, var2_ExplicitVarSizeWithMarker_Values, var2_ExplicitVarSizeWithFlags_Flags, - var2_ExplicitVarSizeWithFlags_Values, var2_ExplicitVarSizeWithDummy] -such that - or([var2_ExplicitVarSizeWithFlags_Flags[q38] /\ - !or([var2_ExplicitVarSizeWithDummy[q40] != 6 /\ - var2_ExplicitVarSizeWithDummy[q40] = var2_ExplicitVarSizeWithFlags_Values[q38] - | q40 : int(1..11)]) - | q38 : int(1..11)]) - \/ - or([var2_ExplicitVarSizeWithDummy[q41] != 6 /\ - !or([var2_ExplicitVarSizeWithFlags_Flags[q43] /\ - var2_ExplicitVarSizeWithFlags_Values[q43] = var2_ExplicitVarSizeWithDummy[q41] - | q43 : int(1..11)]) - | q41 : int(1..11)]), - and([var2_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - var2_ExplicitVarSizeWithFlags_Values[q1] < var2_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..10)]), - and([var2_ExplicitVarSizeWithFlags_Flags[q2] = false -> var2_ExplicitVarSizeWithFlags_Values[q2] = -4 - | q2 : int(1..11)]), - and([var2_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> var2_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..10)]), - and([var2_ExplicitVarSizeWithDummy[q6] < var2_ExplicitVarSizeWithDummy[q6 + 1] \/ - var2_ExplicitVarSizeWithDummy[q6] = 6 - | q6 : int(1..10)]), - and([var2_ExplicitVarSizeWithDummy[q7] = 6 -> var2_ExplicitVarSizeWithDummy[q7 + 1] = 6 | q7 : int(1..10)]), - and([var2_ExplicitVarSizeWithDummy[q11] != 6 -> - or([var2_ExplicitVarSizeWithFlags_Flags[q13] /\ - var2_ExplicitVarSizeWithFlags_Values[q13] = var2_ExplicitVarSizeWithDummy[q11] - | q13 : int(1..11)]) - | q11 : int(1..11)]), - and([var2_ExplicitVarSizeWithFlags_Flags[q15] -> - or([var2_ExplicitVarSizeWithDummy[q17] != 6 /\ - var2_ExplicitVarSizeWithDummy[q17] = var2_ExplicitVarSizeWithFlags_Values[q15] - | q17 : int(1..11)]) - | q15 : int(1..11)]), - and([q18 + 1 <= var2_ExplicitVarSizeWithMarker_Marker -> - var2_ExplicitVarSizeWithMarker_Values[q18] < var2_ExplicitVarSizeWithMarker_Values[q18 + 1] - | q18 : int(1..10)]), - and([q19 > var2_ExplicitVarSizeWithMarker_Marker -> var2_ExplicitVarSizeWithMarker_Values[q19] = -4 - | q19 : int(1..11)]), - and([q22 <= var2_ExplicitVarSizeWithMarker_Marker -> - or([var2_ExplicitVarSizeWithFlags_Flags[q24] /\ - var2_ExplicitVarSizeWithFlags_Values[q24] = var2_ExplicitVarSizeWithMarker_Values[q22] - | q24 : int(1..11)]) - | q22 : int(1..11)]), - and([var2_ExplicitVarSizeWithFlags_Flags[q26] -> - or([q28 <= var2_ExplicitVarSizeWithMarker_Marker /\ - var2_ExplicitVarSizeWithMarker_Values[q28] = var2_ExplicitVarSizeWithFlags_Values[q26] - | q28 : int(1..11)]) - | q26 : int(1..11)]), - and([q30 <= var2_ExplicitVarSizeWithMarker_Marker -> - or([var2_ExplicitVarSizeWithDummy[q32] != 6 /\ - var2_ExplicitVarSizeWithDummy[q32] = var2_ExplicitVarSizeWithMarker_Values[q30] - | q32 : int(1..11)]) - | q30 : int(1..11)]), - and([var2_ExplicitVarSizeWithDummy[q34] != 6 -> - or([q36 <= var2_ExplicitVarSizeWithMarker_Marker /\ - var2_ExplicitVarSizeWithMarker_Values[q36] = var2_ExplicitVarSizeWithDummy[q34] - | q36 : int(1..11)]) - | q34 : int(1..11)]) - diff --git a/tests/exhaustive/autogen/gen32/expected/model_4_2_4.eprime b/tests/exhaustive/autogen/gen32/expected/model_4_2_4.eprime deleted file mode 100644 index 9a094995de..0000000000 --- a/tests/exhaustive/autogen/gen32/expected/model_4_2_4.eprime +++ /dev/null @@ -1,40 +0,0 @@ -language ESSENCE' 1.0 - -letting let1 be -4 -find var2_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..11)] of bool -find var2_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..11)] of int(-4..5, 2) -find var2_ExplicitVarSizeWithDummy: matrix indexed by [int(1..11)] of int(-4..5, 2, 6) -branching on [var2_ExplicitVarSizeWithDummy, var2_ExplicitVarSizeWithFlags_Flags, var2_ExplicitVarSizeWithFlags_Values] -such that - or([var2_ExplicitVarSizeWithFlags_Flags[q19] /\ - !or([var2_ExplicitVarSizeWithDummy[q21] != 6 /\ - var2_ExplicitVarSizeWithDummy[q21] = var2_ExplicitVarSizeWithFlags_Values[q19] - | q21 : int(1..11)]) - | q19 : int(1..11)]) - \/ - or([var2_ExplicitVarSizeWithDummy[q22] != 6 /\ - !or([var2_ExplicitVarSizeWithFlags_Flags[q24] /\ - var2_ExplicitVarSizeWithFlags_Values[q24] = var2_ExplicitVarSizeWithDummy[q22] - | q24 : int(1..11)]) - | q22 : int(1..11)]), - and([var2_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - var2_ExplicitVarSizeWithFlags_Values[q1] < var2_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..10)]), - and([var2_ExplicitVarSizeWithFlags_Flags[q2] = false -> var2_ExplicitVarSizeWithFlags_Values[q2] = -4 - | q2 : int(1..11)]), - and([var2_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> var2_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..10)]), - and([var2_ExplicitVarSizeWithDummy[q6] < var2_ExplicitVarSizeWithDummy[q6 + 1] \/ - var2_ExplicitVarSizeWithDummy[q6] = 6 - | q6 : int(1..10)]), - and([var2_ExplicitVarSizeWithDummy[q7] = 6 -> var2_ExplicitVarSizeWithDummy[q7 + 1] = 6 | q7 : int(1..10)]), - and([var2_ExplicitVarSizeWithDummy[q11] != 6 -> - or([var2_ExplicitVarSizeWithFlags_Flags[q13] /\ - var2_ExplicitVarSizeWithFlags_Values[q13] = var2_ExplicitVarSizeWithDummy[q11] - | q13 : int(1..11)]) - | q11 : int(1..11)]), - and([var2_ExplicitVarSizeWithFlags_Flags[q15] -> - or([var2_ExplicitVarSizeWithDummy[q17] != 6 /\ - var2_ExplicitVarSizeWithDummy[q17] = var2_ExplicitVarSizeWithFlags_Values[q15] - | q17 : int(1..11)]) - | q15 : int(1..11)]) - diff --git a/tests/exhaustive/autogen/gen32/expected/model_4_3_1.eprime b/tests/exhaustive/autogen/gen32/expected/model_4_3_1.eprime deleted file mode 100644 index eb41be6810..0000000000 --- a/tests/exhaustive/autogen/gen32/expected/model_4_3_1.eprime +++ /dev/null @@ -1,57 +0,0 @@ -language ESSENCE' 1.0 - -letting let1 be -4 -find var2_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..11)] of bool -find var2_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..11)] of int(-4..5, 2) -find var2_ExplicitVarSizeWithMarker_Marker: int(0..11) -find var2_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..11)] of int(-4..5, 2) -find var2_Occurrence: matrix indexed by [int(-4..5, 2)] of bool -branching on - [var2_Occurrence, var2_ExplicitVarSizeWithFlags_Flags, var2_ExplicitVarSizeWithFlags_Values, - var2_ExplicitVarSizeWithMarker_Marker, var2_ExplicitVarSizeWithMarker_Values] -such that - or([var2_ExplicitVarSizeWithFlags_Flags[q19] /\ - !or([q21 <= var2_ExplicitVarSizeWithMarker_Marker /\ - var2_ExplicitVarSizeWithMarker_Values[q21] = var2_ExplicitVarSizeWithFlags_Values[q19] - | q21 : int(1..11)]) - | q19 : int(1..11)]) - \/ - or([q22 <= var2_ExplicitVarSizeWithMarker_Marker /\ - !or([var2_ExplicitVarSizeWithFlags_Flags[q24] /\ - var2_ExplicitVarSizeWithFlags_Values[q24] = var2_ExplicitVarSizeWithMarker_Values[q22] - | q24 : int(1..11)]) - | q22 : int(1..11)]), - and([var2_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - var2_ExplicitVarSizeWithFlags_Values[q1] < var2_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..10)]), - and([var2_ExplicitVarSizeWithFlags_Flags[q2] = false -> var2_ExplicitVarSizeWithFlags_Values[q2] = -4 - | q2 : int(1..11)]), - and([var2_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> var2_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..10)]), - and([q6 + 1 <= var2_ExplicitVarSizeWithMarker_Marker -> - var2_ExplicitVarSizeWithMarker_Values[q6] < var2_ExplicitVarSizeWithMarker_Values[q6 + 1] - | q6 : int(1..10)]), - and([q7 > var2_ExplicitVarSizeWithMarker_Marker -> var2_ExplicitVarSizeWithMarker_Values[q7] = -4 - | q7 : int(1..11)]), - and([q10 <= var2_ExplicitVarSizeWithMarker_Marker -> - or([var2_ExplicitVarSizeWithFlags_Flags[q12] /\ - var2_ExplicitVarSizeWithFlags_Values[q12] = var2_ExplicitVarSizeWithMarker_Values[q10] - | q12 : int(1..11)]) - | q10 : int(1..11)]), - and([var2_ExplicitVarSizeWithFlags_Flags[q14] -> - or([q16 <= var2_ExplicitVarSizeWithMarker_Marker /\ - var2_ExplicitVarSizeWithMarker_Values[q16] = var2_ExplicitVarSizeWithFlags_Values[q14] - | q16 : int(1..11)]) - | q14 : int(1..11)]), - and([var2_Occurrence[q25] -> - or([var2_ExplicitVarSizeWithFlags_Flags[q27] /\ var2_ExplicitVarSizeWithFlags_Values[q27] = q25 - | q27 : int(1..11)]) - | q25 : int(-4..5, 2)]), - and([var2_ExplicitVarSizeWithFlags_Flags[q29] -> var2_Occurrence[var2_ExplicitVarSizeWithFlags_Values[q29]] - | q29 : int(1..11)]), - and([var2_Occurrence[q30] -> - or([q32 <= var2_ExplicitVarSizeWithMarker_Marker /\ var2_ExplicitVarSizeWithMarker_Values[q32] = q30 - | q32 : int(1..11)]) - | q30 : int(-4..5, 2)]), - and([q34 <= var2_ExplicitVarSizeWithMarker_Marker -> var2_Occurrence[var2_ExplicitVarSizeWithMarker_Values[q34]] - | q34 : int(1..11)]) - diff --git a/tests/exhaustive/autogen/gen32/expected/model_4_3_2.eprime b/tests/exhaustive/autogen/gen32/expected/model_4_3_2.eprime deleted file mode 100644 index 8dcf88b159..0000000000 --- a/tests/exhaustive/autogen/gen32/expected/model_4_3_2.eprime +++ /dev/null @@ -1,69 +0,0 @@ -language ESSENCE' 1.0 - -letting let1 be -4 -find var2_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..11)] of bool -find var2_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..11)] of int(-4..5, 2) -find var2_ExplicitVarSizeWithMarker_Marker: int(0..11) -find var2_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..11)] of int(-4..5, 2) -find var2_ExplicitVarSizeWithDummy: matrix indexed by [int(1..11)] of int(-4..5, 2, 6) -branching on - [var2_ExplicitVarSizeWithDummy, var2_ExplicitVarSizeWithFlags_Flags, var2_ExplicitVarSizeWithFlags_Values, - var2_ExplicitVarSizeWithMarker_Marker, var2_ExplicitVarSizeWithMarker_Values] -such that - or([var2_ExplicitVarSizeWithFlags_Flags[q38] /\ - !or([q40 <= var2_ExplicitVarSizeWithMarker_Marker /\ - var2_ExplicitVarSizeWithMarker_Values[q40] = var2_ExplicitVarSizeWithFlags_Values[q38] - | q40 : int(1..11)]) - | q38 : int(1..11)]) - \/ - or([q41 <= var2_ExplicitVarSizeWithMarker_Marker /\ - !or([var2_ExplicitVarSizeWithFlags_Flags[q43] /\ - var2_ExplicitVarSizeWithFlags_Values[q43] = var2_ExplicitVarSizeWithMarker_Values[q41] - | q43 : int(1..11)]) - | q41 : int(1..11)]), - and([var2_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - var2_ExplicitVarSizeWithFlags_Values[q1] < var2_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..10)]), - and([var2_ExplicitVarSizeWithFlags_Flags[q2] = false -> var2_ExplicitVarSizeWithFlags_Values[q2] = -4 - | q2 : int(1..11)]), - and([var2_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> var2_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..10)]), - and([q6 + 1 <= var2_ExplicitVarSizeWithMarker_Marker -> - var2_ExplicitVarSizeWithMarker_Values[q6] < var2_ExplicitVarSizeWithMarker_Values[q6 + 1] - | q6 : int(1..10)]), - and([q7 > var2_ExplicitVarSizeWithMarker_Marker -> var2_ExplicitVarSizeWithMarker_Values[q7] = -4 - | q7 : int(1..11)]), - and([q10 <= var2_ExplicitVarSizeWithMarker_Marker -> - or([var2_ExplicitVarSizeWithFlags_Flags[q12] /\ - var2_ExplicitVarSizeWithFlags_Values[q12] = var2_ExplicitVarSizeWithMarker_Values[q10] - | q12 : int(1..11)]) - | q10 : int(1..11)]), - and([var2_ExplicitVarSizeWithFlags_Flags[q14] -> - or([q16 <= var2_ExplicitVarSizeWithMarker_Marker /\ - var2_ExplicitVarSizeWithMarker_Values[q16] = var2_ExplicitVarSizeWithFlags_Values[q14] - | q16 : int(1..11)]) - | q14 : int(1..11)]), - and([var2_ExplicitVarSizeWithDummy[q17] < var2_ExplicitVarSizeWithDummy[q17 + 1] \/ - var2_ExplicitVarSizeWithDummy[q17] = 6 - | q17 : int(1..10)]), - and([var2_ExplicitVarSizeWithDummy[q18] = 6 -> var2_ExplicitVarSizeWithDummy[q18 + 1] = 6 | q18 : int(1..10)]), - and([var2_ExplicitVarSizeWithDummy[q22] != 6 -> - or([var2_ExplicitVarSizeWithFlags_Flags[q24] /\ - var2_ExplicitVarSizeWithFlags_Values[q24] = var2_ExplicitVarSizeWithDummy[q22] - | q24 : int(1..11)]) - | q22 : int(1..11)]), - and([var2_ExplicitVarSizeWithFlags_Flags[q26] -> - or([var2_ExplicitVarSizeWithDummy[q28] != 6 /\ - var2_ExplicitVarSizeWithDummy[q28] = var2_ExplicitVarSizeWithFlags_Values[q26] - | q28 : int(1..11)]) - | q26 : int(1..11)]), - and([var2_ExplicitVarSizeWithDummy[q30] != 6 -> - or([q32 <= var2_ExplicitVarSizeWithMarker_Marker /\ - var2_ExplicitVarSizeWithMarker_Values[q32] = var2_ExplicitVarSizeWithDummy[q30] - | q32 : int(1..11)]) - | q30 : int(1..11)]), - and([q34 <= var2_ExplicitVarSizeWithMarker_Marker -> - or([var2_ExplicitVarSizeWithDummy[q36] != 6 /\ - var2_ExplicitVarSizeWithDummy[q36] = var2_ExplicitVarSizeWithMarker_Values[q34] - | q36 : int(1..11)]) - | q34 : int(1..11)]) - diff --git a/tests/exhaustive/autogen/gen32/expected/model_4_3_3.eprime b/tests/exhaustive/autogen/gen32/expected/model_4_3_3.eprime deleted file mode 100644 index d1c3ae501b..0000000000 --- a/tests/exhaustive/autogen/gen32/expected/model_4_3_3.eprime +++ /dev/null @@ -1,44 +0,0 @@ -language ESSENCE' 1.0 - -letting let1 be -4 -find var2_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..11)] of bool -find var2_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..11)] of int(-4..5, 2) -find var2_ExplicitVarSizeWithMarker_Marker: int(0..11) -find var2_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..11)] of int(-4..5, 2) -branching on - [var2_ExplicitVarSizeWithMarker_Marker, var2_ExplicitVarSizeWithMarker_Values, var2_ExplicitVarSizeWithFlags_Flags, - var2_ExplicitVarSizeWithFlags_Values] -such that - or([var2_ExplicitVarSizeWithFlags_Flags[q18] /\ - !or([q20 <= var2_ExplicitVarSizeWithMarker_Marker /\ - var2_ExplicitVarSizeWithMarker_Values[q20] = var2_ExplicitVarSizeWithFlags_Values[q18] - | q20 : int(1..11)]) - | q18 : int(1..11)]) - \/ - or([q21 <= var2_ExplicitVarSizeWithMarker_Marker /\ - !or([var2_ExplicitVarSizeWithFlags_Flags[q23] /\ - var2_ExplicitVarSizeWithFlags_Values[q23] = var2_ExplicitVarSizeWithMarker_Values[q21] - | q23 : int(1..11)]) - | q21 : int(1..11)]), - and([var2_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - var2_ExplicitVarSizeWithFlags_Values[q1] < var2_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..10)]), - and([var2_ExplicitVarSizeWithFlags_Flags[q2] = false -> var2_ExplicitVarSizeWithFlags_Values[q2] = -4 - | q2 : int(1..11)]), - and([var2_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> var2_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..10)]), - and([q6 + 1 <= var2_ExplicitVarSizeWithMarker_Marker -> - var2_ExplicitVarSizeWithMarker_Values[q6] < var2_ExplicitVarSizeWithMarker_Values[q6 + 1] - | q6 : int(1..10)]), - and([q7 > var2_ExplicitVarSizeWithMarker_Marker -> var2_ExplicitVarSizeWithMarker_Values[q7] = -4 - | q7 : int(1..11)]), - and([q10 <= var2_ExplicitVarSizeWithMarker_Marker -> - or([var2_ExplicitVarSizeWithFlags_Flags[q12] /\ - var2_ExplicitVarSizeWithFlags_Values[q12] = var2_ExplicitVarSizeWithMarker_Values[q10] - | q12 : int(1..11)]) - | q10 : int(1..11)]), - and([var2_ExplicitVarSizeWithFlags_Flags[q14] -> - or([q16 <= var2_ExplicitVarSizeWithMarker_Marker /\ - var2_ExplicitVarSizeWithMarker_Values[q16] = var2_ExplicitVarSizeWithFlags_Values[q14] - | q16 : int(1..11)]) - | q14 : int(1..11)]) - diff --git a/tests/exhaustive/autogen/gen32/expected/model_4_3_4.eprime b/tests/exhaustive/autogen/gen32/expected/model_4_3_4.eprime deleted file mode 100644 index d1c3ae501b..0000000000 --- a/tests/exhaustive/autogen/gen32/expected/model_4_3_4.eprime +++ /dev/null @@ -1,44 +0,0 @@ -language ESSENCE' 1.0 - -letting let1 be -4 -find var2_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..11)] of bool -find var2_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..11)] of int(-4..5, 2) -find var2_ExplicitVarSizeWithMarker_Marker: int(0..11) -find var2_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..11)] of int(-4..5, 2) -branching on - [var2_ExplicitVarSizeWithMarker_Marker, var2_ExplicitVarSizeWithMarker_Values, var2_ExplicitVarSizeWithFlags_Flags, - var2_ExplicitVarSizeWithFlags_Values] -such that - or([var2_ExplicitVarSizeWithFlags_Flags[q18] /\ - !or([q20 <= var2_ExplicitVarSizeWithMarker_Marker /\ - var2_ExplicitVarSizeWithMarker_Values[q20] = var2_ExplicitVarSizeWithFlags_Values[q18] - | q20 : int(1..11)]) - | q18 : int(1..11)]) - \/ - or([q21 <= var2_ExplicitVarSizeWithMarker_Marker /\ - !or([var2_ExplicitVarSizeWithFlags_Flags[q23] /\ - var2_ExplicitVarSizeWithFlags_Values[q23] = var2_ExplicitVarSizeWithMarker_Values[q21] - | q23 : int(1..11)]) - | q21 : int(1..11)]), - and([var2_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - var2_ExplicitVarSizeWithFlags_Values[q1] < var2_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..10)]), - and([var2_ExplicitVarSizeWithFlags_Flags[q2] = false -> var2_ExplicitVarSizeWithFlags_Values[q2] = -4 - | q2 : int(1..11)]), - and([var2_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> var2_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..10)]), - and([q6 + 1 <= var2_ExplicitVarSizeWithMarker_Marker -> - var2_ExplicitVarSizeWithMarker_Values[q6] < var2_ExplicitVarSizeWithMarker_Values[q6 + 1] - | q6 : int(1..10)]), - and([q7 > var2_ExplicitVarSizeWithMarker_Marker -> var2_ExplicitVarSizeWithMarker_Values[q7] = -4 - | q7 : int(1..11)]), - and([q10 <= var2_ExplicitVarSizeWithMarker_Marker -> - or([var2_ExplicitVarSizeWithFlags_Flags[q12] /\ - var2_ExplicitVarSizeWithFlags_Values[q12] = var2_ExplicitVarSizeWithMarker_Values[q10] - | q12 : int(1..11)]) - | q10 : int(1..11)]), - and([var2_ExplicitVarSizeWithFlags_Flags[q14] -> - or([q16 <= var2_ExplicitVarSizeWithMarker_Marker /\ - var2_ExplicitVarSizeWithMarker_Values[q16] = var2_ExplicitVarSizeWithFlags_Values[q14] - | q16 : int(1..11)]) - | q14 : int(1..11)]) - diff --git a/tests/exhaustive/autogen/gen32/expected/model_4_4_1.eprime b/tests/exhaustive/autogen/gen32/expected/model_4_4_1.eprime deleted file mode 100644 index dc916012b6..0000000000 --- a/tests/exhaustive/autogen/gen32/expected/model_4_4_1.eprime +++ /dev/null @@ -1,32 +0,0 @@ -language ESSENCE' 1.0 - -letting let1 be -4 -find var2_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..11)] of bool -find var2_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..11)] of int(-4..5, 2) -find var2_Occurrence: matrix indexed by [int(-4..5, 2)] of bool -branching on [var2_Occurrence, var2_ExplicitVarSizeWithFlags_Flags, var2_ExplicitVarSizeWithFlags_Values] -such that - or([var2_ExplicitVarSizeWithFlags_Flags[q8] /\ - !or([var2_ExplicitVarSizeWithFlags_Flags[q10] /\ - var2_ExplicitVarSizeWithFlags_Values[q10] = var2_ExplicitVarSizeWithFlags_Values[q8] - | q10 : int(1..11)]) - | q8 : int(1..11)]) - \/ - or([var2_ExplicitVarSizeWithFlags_Flags[q11] /\ - !or([var2_ExplicitVarSizeWithFlags_Flags[q13] /\ - var2_ExplicitVarSizeWithFlags_Values[q13] = var2_ExplicitVarSizeWithFlags_Values[q11] - | q13 : int(1..11)]) - | q11 : int(1..11)]), - and([var2_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - var2_ExplicitVarSizeWithFlags_Values[q1] < var2_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..10)]), - and([var2_ExplicitVarSizeWithFlags_Flags[q2] = false -> var2_ExplicitVarSizeWithFlags_Values[q2] = -4 - | q2 : int(1..11)]), - and([var2_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> var2_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..10)]), - and([var2_Occurrence[q14] -> - or([var2_ExplicitVarSizeWithFlags_Flags[q16] /\ var2_ExplicitVarSizeWithFlags_Values[q16] = q14 - | q16 : int(1..11)]) - | q14 : int(-4..5, 2)]), - and([var2_ExplicitVarSizeWithFlags_Flags[q18] -> var2_Occurrence[var2_ExplicitVarSizeWithFlags_Values[q18]] - | q18 : int(1..11)]) - diff --git a/tests/exhaustive/autogen/gen32/expected/model_4_4_2.eprime b/tests/exhaustive/autogen/gen32/expected/model_4_4_2.eprime deleted file mode 100644 index 26e15ff1e8..0000000000 --- a/tests/exhaustive/autogen/gen32/expected/model_4_4_2.eprime +++ /dev/null @@ -1,40 +0,0 @@ -language ESSENCE' 1.0 - -letting let1 be -4 -find var2_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..11)] of bool -find var2_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..11)] of int(-4..5, 2) -find var2_ExplicitVarSizeWithDummy: matrix indexed by [int(1..11)] of int(-4..5, 2, 6) -branching on [var2_ExplicitVarSizeWithDummy, var2_ExplicitVarSizeWithFlags_Flags, var2_ExplicitVarSizeWithFlags_Values] -such that - or([var2_ExplicitVarSizeWithFlags_Flags[q19] /\ - !or([var2_ExplicitVarSizeWithFlags_Flags[q21] /\ - var2_ExplicitVarSizeWithFlags_Values[q21] = var2_ExplicitVarSizeWithFlags_Values[q19] - | q21 : int(1..11)]) - | q19 : int(1..11)]) - \/ - or([var2_ExplicitVarSizeWithFlags_Flags[q22] /\ - !or([var2_ExplicitVarSizeWithFlags_Flags[q24] /\ - var2_ExplicitVarSizeWithFlags_Values[q24] = var2_ExplicitVarSizeWithFlags_Values[q22] - | q24 : int(1..11)]) - | q22 : int(1..11)]), - and([var2_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - var2_ExplicitVarSizeWithFlags_Values[q1] < var2_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..10)]), - and([var2_ExplicitVarSizeWithFlags_Flags[q2] = false -> var2_ExplicitVarSizeWithFlags_Values[q2] = -4 - | q2 : int(1..11)]), - and([var2_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> var2_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..10)]), - and([var2_ExplicitVarSizeWithDummy[q6] < var2_ExplicitVarSizeWithDummy[q6 + 1] \/ - var2_ExplicitVarSizeWithDummy[q6] = 6 - | q6 : int(1..10)]), - and([var2_ExplicitVarSizeWithDummy[q7] = 6 -> var2_ExplicitVarSizeWithDummy[q7 + 1] = 6 | q7 : int(1..10)]), - and([var2_ExplicitVarSizeWithDummy[q11] != 6 -> - or([var2_ExplicitVarSizeWithFlags_Flags[q13] /\ - var2_ExplicitVarSizeWithFlags_Values[q13] = var2_ExplicitVarSizeWithDummy[q11] - | q13 : int(1..11)]) - | q11 : int(1..11)]), - and([var2_ExplicitVarSizeWithFlags_Flags[q15] -> - or([var2_ExplicitVarSizeWithDummy[q17] != 6 /\ - var2_ExplicitVarSizeWithDummy[q17] = var2_ExplicitVarSizeWithFlags_Values[q15] - | q17 : int(1..11)]) - | q15 : int(1..11)]) - diff --git a/tests/exhaustive/autogen/gen32/expected/model_4_4_3.eprime b/tests/exhaustive/autogen/gen32/expected/model_4_4_3.eprime deleted file mode 100644 index a9522bafc7..0000000000 --- a/tests/exhaustive/autogen/gen32/expected/model_4_4_3.eprime +++ /dev/null @@ -1,44 +0,0 @@ -language ESSENCE' 1.0 - -letting let1 be -4 -find var2_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..11)] of bool -find var2_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..11)] of int(-4..5, 2) -find var2_ExplicitVarSizeWithMarker_Marker: int(0..11) -find var2_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..11)] of int(-4..5, 2) -branching on - [var2_ExplicitVarSizeWithMarker_Marker, var2_ExplicitVarSizeWithMarker_Values, var2_ExplicitVarSizeWithFlags_Flags, - var2_ExplicitVarSizeWithFlags_Values] -such that - or([var2_ExplicitVarSizeWithFlags_Flags[q18] /\ - !or([var2_ExplicitVarSizeWithFlags_Flags[q20] /\ - var2_ExplicitVarSizeWithFlags_Values[q20] = var2_ExplicitVarSizeWithFlags_Values[q18] - | q20 : int(1..11)]) - | q18 : int(1..11)]) - \/ - or([var2_ExplicitVarSizeWithFlags_Flags[q21] /\ - !or([var2_ExplicitVarSizeWithFlags_Flags[q23] /\ - var2_ExplicitVarSizeWithFlags_Values[q23] = var2_ExplicitVarSizeWithFlags_Values[q21] - | q23 : int(1..11)]) - | q21 : int(1..11)]), - and([var2_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - var2_ExplicitVarSizeWithFlags_Values[q1] < var2_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..10)]), - and([var2_ExplicitVarSizeWithFlags_Flags[q2] = false -> var2_ExplicitVarSizeWithFlags_Values[q2] = -4 - | q2 : int(1..11)]), - and([var2_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> var2_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..10)]), - and([q6 + 1 <= var2_ExplicitVarSizeWithMarker_Marker -> - var2_ExplicitVarSizeWithMarker_Values[q6] < var2_ExplicitVarSizeWithMarker_Values[q6 + 1] - | q6 : int(1..10)]), - and([q7 > var2_ExplicitVarSizeWithMarker_Marker -> var2_ExplicitVarSizeWithMarker_Values[q7] = -4 - | q7 : int(1..11)]), - and([q10 <= var2_ExplicitVarSizeWithMarker_Marker -> - or([var2_ExplicitVarSizeWithFlags_Flags[q12] /\ - var2_ExplicitVarSizeWithFlags_Values[q12] = var2_ExplicitVarSizeWithMarker_Values[q10] - | q12 : int(1..11)]) - | q10 : int(1..11)]), - and([var2_ExplicitVarSizeWithFlags_Flags[q14] -> - or([q16 <= var2_ExplicitVarSizeWithMarker_Marker /\ - var2_ExplicitVarSizeWithMarker_Values[q16] = var2_ExplicitVarSizeWithFlags_Values[q14] - | q16 : int(1..11)]) - | q14 : int(1..11)]) - diff --git a/tests/exhaustive/autogen/gen32/expected/model_4_4_4.eprime b/tests/exhaustive/autogen/gen32/expected/model_4_4_4.eprime deleted file mode 100644 index ec2da87b64..0000000000 --- a/tests/exhaustive/autogen/gen32/expected/model_4_4_4.eprime +++ /dev/null @@ -1,25 +0,0 @@ -language ESSENCE' 1.0 - -letting let1 be -4 -find var2_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..11)] of bool -find var2_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..11)] of int(-4..5, 2) -branching on [var2_ExplicitVarSizeWithFlags_Flags, var2_ExplicitVarSizeWithFlags_Values] -such that - or([var2_ExplicitVarSizeWithFlags_Flags[q7] /\ - !or([var2_ExplicitVarSizeWithFlags_Flags[q9] /\ - var2_ExplicitVarSizeWithFlags_Values[q9] = var2_ExplicitVarSizeWithFlags_Values[q7] - | q9 : int(1..11)]) - | q7 : int(1..11)]) - \/ - or([var2_ExplicitVarSizeWithFlags_Flags[q10] /\ - !or([var2_ExplicitVarSizeWithFlags_Flags[q12] /\ - var2_ExplicitVarSizeWithFlags_Values[q12] = var2_ExplicitVarSizeWithFlags_Values[q10] - | q12 : int(1..11)]) - | q10 : int(1..11)]), - and([var2_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - var2_ExplicitVarSizeWithFlags_Values[q1] < var2_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..10)]), - and([var2_ExplicitVarSizeWithFlags_Flags[q2] = false -> var2_ExplicitVarSizeWithFlags_Values[q2] = -4 - | q2 : int(1..11)]), - and([var2_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> var2_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..10)]) - diff --git a/tests/exhaustive/autogen/gen36/expected/model_1-solution000001.solution b/tests/exhaustive/autogen/gen36/expected/model_1-solution000001.solution deleted file mode 100644 index 78bab35d5f..0000000000 --- a/tests/exhaustive/autogen/gen36/expected/model_1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting var6 be {} diff --git a/tests/exhaustive/autogen/gen36/expected/model_1.eprime b/tests/exhaustive/autogen/gen36/expected/model_1.eprime deleted file mode 100644 index 0390940e9f..0000000000 --- a/tests/exhaustive/autogen/gen36/expected/model_1.eprime +++ /dev/null @@ -1,88 +0,0 @@ -language ESSENCE' 1.0 - -letting let1 be 2 -find var6_ExplicitVarSizeWithMarkerR18R5R2_Marker: int(0..2) -find var6_ExplicitVarSizeWithMarkerR18R5R2_Values_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker: - matrix indexed by [int(1..2)] of int(0..2) -find var6_ExplicitVarSizeWithMarkerR18R5R2_Values_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence: - matrix indexed by [int(1..2), int(1..2), int(2, 5)] of bool -branching on - [var6_ExplicitVarSizeWithMarkerR18R5R2_Marker, - var6_ExplicitVarSizeWithMarkerR18R5R2_Values_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker, - var6_ExplicitVarSizeWithMarkerR18R5R2_Values_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence] -such that - 2 <= var6_ExplicitVarSizeWithMarkerR18R5R2_Marker -> - flatten([[var6_ExplicitVarSizeWithMarkerR18R5R2_Values_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker[1]; - int(1)], - flatten([[-toInt(var6_ExplicitVarSizeWithMarkerR18R5R2_Values_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence - [1, q12, q13]) - | q13 : int(2, 5)] - | q12 : int(1..2)]); - int(1..2)]) - var6_ExplicitVarSizeWithMarkerR18R5R2_Marker -> - var6_ExplicitVarSizeWithMarkerR18R5R2_Values_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker[q2] = 0 /\ - and([and([var6_ExplicitVarSizeWithMarkerR18R5R2_Values_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence - [q2, q16, q17] - = false - | q17 : int(2, 5)]) - | q16 : int(1..2)]) - | q2 : int(1..2)]), - and([q3 <= var6_ExplicitVarSizeWithMarkerR18R5R2_Marker -> - and([1 = - sum([toInt(q18 <= - var6_ExplicitVarSizeWithMarkerR18R5R2_Values_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker - [q3] - /\ - var6_ExplicitVarSizeWithMarkerR18R5R2_Values_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence - [q3, q18, q4]) - | q18 : int(1..2)]) - | q4 : int(2, 5)]) - | q3 : int(1..2)]), - and([q3 <= var6_ExplicitVarSizeWithMarkerR18R5R2_Marker -> - and([q19 <= var6_ExplicitVarSizeWithMarkerR18R5R2_Values_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker[q3] - -> false - | q19 : int(1..2)]) - | q3 : int(1..2)]), - and([q3 <= var6_ExplicitVarSizeWithMarkerR18R5R2_Marker -> - (2 <= var6_ExplicitVarSizeWithMarkerR18R5R2_Values_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker[q3] -> - [-toInt(var6_ExplicitVarSizeWithMarkerR18R5R2_Values_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence - [q3, 1, q20]) - | q20 : int(2, 5)] - - and([q8 > var6_ExplicitVarSizeWithMarkerR18R5R2_Values_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker[q3] -> - and([var6_ExplicitVarSizeWithMarkerR18R5R2_Values_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence - [q3, q8, q22] - = false - | q22 : int(2, 5)]) - | q8 : int(1..2)]) - | q3 : int(1..2)]), - and([q3 <= var6_ExplicitVarSizeWithMarkerR18R5R2_Marker -> - 3 <= var6_ExplicitVarSizeWithMarkerR18R5R2_Values_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker[q3] - | q3 : int(1..2)]), - and([q3 <= var6_ExplicitVarSizeWithMarkerR18R5R2_Marker -> - var6_ExplicitVarSizeWithMarkerR18R5R2_Values_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker[q3] <= 2 - | q3 : int(1..2)]), - and([q3 <= var6_ExplicitVarSizeWithMarkerR18R5R2_Marker -> - and([q9 <= var6_ExplicitVarSizeWithMarkerR18R5R2_Values_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker[q3] - -> - 0 = - sum([toInt(var6_ExplicitVarSizeWithMarkerR18R5R2_Values_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence - [q3, q9, q10]) - | q10 : int(2, 5)]) - | q9 : int(1..2)]) - | q3 : int(1..2)]), - and([q3 <= var6_ExplicitVarSizeWithMarkerR18R5R2_Marker -> false | q3 : int(1..2)]) - diff --git a/tests/exhaustive/autogen/gen36/expected/model_2-solution000001.solution b/tests/exhaustive/autogen/gen36/expected/model_2-solution000001.solution deleted file mode 100644 index 78bab35d5f..0000000000 --- a/tests/exhaustive/autogen/gen36/expected/model_2-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting var6 be {} diff --git a/tests/exhaustive/autogen/gen36/expected/model_2.eprime b/tests/exhaustive/autogen/gen36/expected/model_2.eprime deleted file mode 100644 index 7d787a5d65..0000000000 --- a/tests/exhaustive/autogen/gen36/expected/model_2.eprime +++ /dev/null @@ -1,43 +0,0 @@ -language ESSENCE' 1.0 - -letting let1 be 2 -find var6_ExplicitVarSizeWithMarkerR18R5R3_Marker: int(0..2) -find var6_ExplicitVarSizeWithMarkerR18R5R3_Values_PartitionAsSet_ExplicitVarSizeWithMarkerR3_Marker: - matrix indexed by [int(1..2)] of int(0..2) -find var6_ExplicitVarSizeWithMarkerR18R5R3_Values_PartitionAsSet_ExplicitVarSizeWithMarkerR3_Values_Explicit: - matrix indexed by [int(1..2), int(1..2), int(1..0)] of int(2, 5) -branching on - [var6_ExplicitVarSizeWithMarkerR18R5R3_Marker, - var6_ExplicitVarSizeWithMarkerR18R5R3_Values_PartitionAsSet_ExplicitVarSizeWithMarkerR3_Marker, - var6_ExplicitVarSizeWithMarkerR18R5R3_Values_PartitionAsSet_ExplicitVarSizeWithMarkerR3_Values_Explicit] -such that - 2 <= var6_ExplicitVarSizeWithMarkerR18R5R3_Marker -> - flatten([[var6_ExplicitVarSizeWithMarkerR18R5R3_Values_PartitionAsSet_ExplicitVarSizeWithMarkerR3_Marker[1]; - int(1)], - ([] : `matrix indexed by [int()] of int`); - int(1..2)]) - var6_ExplicitVarSizeWithMarkerR18R5R3_Marker -> - var6_ExplicitVarSizeWithMarkerR18R5R3_Values_PartitionAsSet_ExplicitVarSizeWithMarkerR3_Marker[q2] = 0 - | q2 : int(1..2)]), - and([q3 <= var6_ExplicitVarSizeWithMarkerR18R5R3_Marker -> - and([q21 <= var6_ExplicitVarSizeWithMarkerR18R5R3_Values_PartitionAsSet_ExplicitVarSizeWithMarkerR3_Marker[q3] - -> false - | q21 : int(1..2)]) - | q3 : int(1..2)]), - and([q3 <= var6_ExplicitVarSizeWithMarkerR18R5R3_Marker -> - (2 <= var6_ExplicitVarSizeWithMarkerR18R5R3_Values_PartitionAsSet_ExplicitVarSizeWithMarkerR3_Marker[q3] -> - false) - | q3 : int(1..2)]), - and([q3 <= var6_ExplicitVarSizeWithMarkerR18R5R3_Marker -> - 3 <= var6_ExplicitVarSizeWithMarkerR18R5R3_Values_PartitionAsSet_ExplicitVarSizeWithMarkerR3_Marker[q3] - | q3 : int(1..2)]), - and([q3 <= var6_ExplicitVarSizeWithMarkerR18R5R3_Marker -> - var6_ExplicitVarSizeWithMarkerR18R5R3_Values_PartitionAsSet_ExplicitVarSizeWithMarkerR3_Marker[q3] <= 2 - | q3 : int(1..2)]), - and([q3 <= var6_ExplicitVarSizeWithMarkerR18R5R3_Marker -> false | q3 : int(1..2)]) - diff --git a/tests/exhaustive/autogen/gen36/expected/model_3-solution000001.solution b/tests/exhaustive/autogen/gen36/expected/model_3-solution000001.solution deleted file mode 100644 index 78bab35d5f..0000000000 --- a/tests/exhaustive/autogen/gen36/expected/model_3-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting var6 be {} diff --git a/tests/exhaustive/autogen/gen36/expected/model_3.eprime b/tests/exhaustive/autogen/gen36/expected/model_3.eprime deleted file mode 100644 index 8d69612405..0000000000 --- a/tests/exhaustive/autogen/gen36/expected/model_3.eprime +++ /dev/null @@ -1,100 +0,0 @@ -language ESSENCE' 1.0 - -letting let1 be 2 -find var6_ExplicitVarSizeWithMarkerR19_Marker: int(0..2) -find var6_ExplicitVarSizeWithMarkerR19_Values_PartitionOccurrence_NumParts: matrix indexed by [int(1..2)] of int(1..2) -find var6_ExplicitVarSizeWithMarkerR19_Values_PartitionOccurrence_WhichPart: - matrix indexed by [int(1..2), int(2, 5)] of int(1..2) -find var6_ExplicitVarSizeWithMarkerR19_Values_PartitionOccurrence_PartSizes: - matrix indexed by [int(1..2), int(1..2)] of int(0) -find var6_ExplicitVarSizeWithMarkerR19_Values_PartitionOccurrence_FirstIndex: - matrix indexed by [int(1..2), int(1..2)] of int(2, 5) -branching on - [var6_ExplicitVarSizeWithMarkerR19_Marker, var6_ExplicitVarSizeWithMarkerR19_Values_PartitionOccurrence_NumParts, - var6_ExplicitVarSizeWithMarkerR19_Values_PartitionOccurrence_WhichPart, - var6_ExplicitVarSizeWithMarkerR19_Values_PartitionOccurrence_PartSizes, - var6_ExplicitVarSizeWithMarkerR19_Values_PartitionOccurrence_FirstIndex] -such that - 2 <= var6_ExplicitVarSizeWithMarkerR19_Marker -> - flatten([[var6_ExplicitVarSizeWithMarkerR19_Values_PartitionOccurrence_NumParts[1]; int(1)], - flatten([[var6_ExplicitVarSizeWithMarkerR19_Values_PartitionOccurrence_WhichPart[1, q14]; int(1)] - | q14 : int(2, 5)]), - flatten([[var6_ExplicitVarSizeWithMarkerR19_Values_PartitionOccurrence_PartSizes[1, q15]; int(1)] - | q15 : int(1..2)]), - flatten([[var6_ExplicitVarSizeWithMarkerR19_Values_PartitionOccurrence_FirstIndex[1, q16]; int(1)] - | q16 : int(1..2)]); - int(1..4)]) - var6_ExplicitVarSizeWithMarkerR19_Marker -> - and([var6_ExplicitVarSizeWithMarkerR19_Values_PartitionOccurrence_NumParts[q2] = 1, - and([var6_ExplicitVarSizeWithMarkerR19_Values_PartitionOccurrence_WhichPart[q2, q20] = 1 - | q20 : int(2, 5)]), - and([var6_ExplicitVarSizeWithMarkerR19_Values_PartitionOccurrence_PartSizes[q2, q21] = 0 - | q21 : int(1..2)]), - and([var6_ExplicitVarSizeWithMarkerR19_Values_PartitionOccurrence_FirstIndex[q2, q22] = 2 - | q22 : int(1..2)]); - int(1..4)]) - | q2 : int(1..2)]), - and([q3 <= var6_ExplicitVarSizeWithMarkerR19_Marker -> - and([q4 <= var6_ExplicitVarSizeWithMarkerR19_Values_PartitionOccurrence_NumParts[q3] -> - 0 = var6_ExplicitVarSizeWithMarkerR19_Values_PartitionOccurrence_PartSizes[q3, q4] - | q4 : int(1..2)]) - | q3 : int(1..2)]), - and([q3 <= var6_ExplicitVarSizeWithMarkerR19_Marker -> - and([q4 > var6_ExplicitVarSizeWithMarkerR19_Values_PartitionOccurrence_NumParts[q3] -> - var6_ExplicitVarSizeWithMarkerR19_Values_PartitionOccurrence_PartSizes[q3, q4] = 0 - | q4 : int(1..2)]) - | q3 : int(1..2)]), - and([q3 <= var6_ExplicitVarSizeWithMarkerR19_Marker -> - 3 <= var6_ExplicitVarSizeWithMarkerR19_Values_PartitionOccurrence_NumParts[q3] - | q3 : int(1..2)]), - and([q3 <= var6_ExplicitVarSizeWithMarkerR19_Marker -> - var6_ExplicitVarSizeWithMarkerR19_Values_PartitionOccurrence_NumParts[q3] <= 2 - | q3 : int(1..2)]), - and([q3 <= var6_ExplicitVarSizeWithMarkerR19_Marker -> - var6_ExplicitVarSizeWithMarkerR19_Values_PartitionOccurrence_NumParts[q3] = - max([var6_ExplicitVarSizeWithMarkerR19_Values_PartitionOccurrence_WhichPart[q3, q7] | q7 : int(2, 5)]) - | q3 : int(1..2)]), - and([q3 <= var6_ExplicitVarSizeWithMarkerR19_Marker -> - and([var6_ExplicitVarSizeWithMarkerR19_Values_PartitionOccurrence_PartSizes[q3, q8] = - sum([toInt(var6_ExplicitVarSizeWithMarkerR19_Values_PartitionOccurrence_WhichPart[q3, q9] = q8) - | q9 : int(2, 5)]) - | q8 : int(1..2)]) - | q3 : int(1..2)]), - and([q3 <= var6_ExplicitVarSizeWithMarkerR19_Marker -> - and([q10 <= var6_ExplicitVarSizeWithMarkerR19_Values_PartitionOccurrence_NumParts[q3] -> - and([var6_ExplicitVarSizeWithMarkerR19_Values_PartitionOccurrence_WhichPart[q3, q11] = q10 -> - var6_ExplicitVarSizeWithMarkerR19_Values_PartitionOccurrence_FirstIndex[q3, q10] <= q11 - | q11 : int(2, 5)]) - | q10 : int(1..2)]) - | q3 : int(1..2)]), - and([q3 <= var6_ExplicitVarSizeWithMarkerR19_Marker -> - and([q10 <= var6_ExplicitVarSizeWithMarkerR19_Values_PartitionOccurrence_NumParts[q3] -> - or([var6_ExplicitVarSizeWithMarkerR19_Values_PartitionOccurrence_WhichPart[q3, q11] = q10 /\ - var6_ExplicitVarSizeWithMarkerR19_Values_PartitionOccurrence_FirstIndex[q3, q10] = q11 - | q11 : int(2, 5)]) - | q10 : int(1..2)]) - | q3 : int(1..2)]), - and([q3 <= var6_ExplicitVarSizeWithMarkerR19_Marker -> - and([q10 > var6_ExplicitVarSizeWithMarkerR19_Values_PartitionOccurrence_NumParts[q3] -> - var6_ExplicitVarSizeWithMarkerR19_Values_PartitionOccurrence_FirstIndex[q3, q10] = 2 - | q10 : int(1..2)]) - | q3 : int(1..2)]), - and([q3 <= var6_ExplicitVarSizeWithMarkerR19_Marker -> - and([q12 <= var6_ExplicitVarSizeWithMarkerR19_Values_PartitionOccurrence_NumParts[q3] /\ - q13 <= var6_ExplicitVarSizeWithMarkerR19_Values_PartitionOccurrence_NumParts[q3] - -> - (q12 < q13 <-> - var6_ExplicitVarSizeWithMarkerR19_Values_PartitionOccurrence_FirstIndex[q3, q12] < - var6_ExplicitVarSizeWithMarkerR19_Values_PartitionOccurrence_FirstIndex[q3, q13]) - | q12 : int(1..2), q13 : int(1..2)]) - | q3 : int(1..2)]) - diff --git a/tests/exhaustive/autogen/gen36/expected/model_4-solution000001.solution b/tests/exhaustive/autogen/gen36/expected/model_4-solution000001.solution deleted file mode 100644 index 78bab35d5f..0000000000 --- a/tests/exhaustive/autogen/gen36/expected/model_4-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting var6 be {} diff --git a/tests/exhaustive/autogen/gen36/expected/model_4.eprime b/tests/exhaustive/autogen/gen36/expected/model_4.eprime deleted file mode 100644 index ead227e9bf..0000000000 --- a/tests/exhaustive/autogen/gen36/expected/model_4.eprime +++ /dev/null @@ -1,87 +0,0 @@ -language ESSENCE' 1.0 - -letting let1 be 2 -find var6_ExplicitVarSizeWithFlagsR18R5R2_Flags: matrix indexed by [int(1..2)] of bool -find var6_ExplicitVarSizeWithFlagsR18R5R2_Values_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker: - matrix indexed by [int(1..2)] of int(0..2) -find var6_ExplicitVarSizeWithFlagsR18R5R2_Values_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence: - matrix indexed by [int(1..2), int(1..2), int(2, 5)] of bool -branching on - [var6_ExplicitVarSizeWithFlagsR18R5R2_Flags, - var6_ExplicitVarSizeWithFlagsR18R5R2_Values_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker, - var6_ExplicitVarSizeWithFlagsR18R5R2_Values_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence] -such that - var6_ExplicitVarSizeWithFlagsR18R5R2_Flags[2] -> - flatten([[var6_ExplicitVarSizeWithFlagsR18R5R2_Values_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker[1]; int(1)], - flatten([[-toInt(var6_ExplicitVarSizeWithFlagsR18R5R2_Values_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence - [1, q14, q15]) - | q15 : int(2, 5)] - | q14 : int(1..2)]); - int(1..2)]) - - var6_ExplicitVarSizeWithFlagsR18R5R2_Values_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker[q2] = 0 /\ - and([and([var6_ExplicitVarSizeWithFlagsR18R5R2_Values_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence - [q2, q18, q19] - = false - | q19 : int(2, 5)]) - | q18 : int(1..2)]) - | q2 : int(1..2)]), - var6_ExplicitVarSizeWithFlagsR18R5R2_Flags[2] -> var6_ExplicitVarSizeWithFlagsR18R5R2_Flags[1], - and([var6_ExplicitVarSizeWithFlagsR18R5R2_Flags[q5] -> - and([1 = - sum([toInt(q20 <= - var6_ExplicitVarSizeWithFlagsR18R5R2_Values_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker - [q5] - /\ - var6_ExplicitVarSizeWithFlagsR18R5R2_Values_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence - [q5, q20, q6]) - | q20 : int(1..2)]) - | q6 : int(2, 5)]) - | q5 : int(1..2)]), - and([var6_ExplicitVarSizeWithFlagsR18R5R2_Flags[q5] -> - and([q21 <= var6_ExplicitVarSizeWithFlagsR18R5R2_Values_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker[q5] - -> false - | q21 : int(1..2)]) - | q5 : int(1..2)]), - and([var6_ExplicitVarSizeWithFlagsR18R5R2_Flags[q5] -> - (2 <= var6_ExplicitVarSizeWithFlagsR18R5R2_Values_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker[q5] -> - [-toInt(var6_ExplicitVarSizeWithFlagsR18R5R2_Values_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence - [q5, 1, q22]) - | q22 : int(2, 5)] - - and([q10 > var6_ExplicitVarSizeWithFlagsR18R5R2_Values_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker[q5] -> - and([var6_ExplicitVarSizeWithFlagsR18R5R2_Values_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence - [q5, q10, q24] - = false - | q24 : int(2, 5)]) - | q10 : int(1..2)]) - | q5 : int(1..2)]), - and([var6_ExplicitVarSizeWithFlagsR18R5R2_Flags[q5] -> - 3 <= var6_ExplicitVarSizeWithFlagsR18R5R2_Values_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker[q5] - | q5 : int(1..2)]), - and([var6_ExplicitVarSizeWithFlagsR18R5R2_Flags[q5] -> - var6_ExplicitVarSizeWithFlagsR18R5R2_Values_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker[q5] <= 2 - | q5 : int(1..2)]), - and([var6_ExplicitVarSizeWithFlagsR18R5R2_Flags[q5] -> - and([q11 <= var6_ExplicitVarSizeWithFlagsR18R5R2_Values_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker[q5] - -> - 0 = - sum([toInt(var6_ExplicitVarSizeWithFlagsR18R5R2_Values_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence - [q5, q11, q12]) - | q12 : int(2, 5)]) - | q11 : int(1..2)]) - | q5 : int(1..2)]), - and([var6_ExplicitVarSizeWithFlagsR18R5R2_Flags[q5] -> false | q5 : int(1..2)]) - diff --git a/tests/exhaustive/autogen/gen36/expected/model_5-solution000001.solution b/tests/exhaustive/autogen/gen36/expected/model_5-solution000001.solution deleted file mode 100644 index 78bab35d5f..0000000000 --- a/tests/exhaustive/autogen/gen36/expected/model_5-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting var6 be {} diff --git a/tests/exhaustive/autogen/gen36/expected/model_5.eprime b/tests/exhaustive/autogen/gen36/expected/model_5.eprime deleted file mode 100644 index 7a736617ea..0000000000 --- a/tests/exhaustive/autogen/gen36/expected/model_5.eprime +++ /dev/null @@ -1,42 +0,0 @@ -language ESSENCE' 1.0 - -letting let1 be 2 -find var6_ExplicitVarSizeWithFlagsR18R5R3_Flags: matrix indexed by [int(1..2)] of bool -find var6_ExplicitVarSizeWithFlagsR18R5R3_Values_PartitionAsSet_ExplicitVarSizeWithMarkerR3_Marker: - matrix indexed by [int(1..2)] of int(0..2) -find var6_ExplicitVarSizeWithFlagsR18R5R3_Values_PartitionAsSet_ExplicitVarSizeWithMarkerR3_Values_Explicit: - matrix indexed by [int(1..2), int(1..2), int(1..0)] of int(2, 5) -branching on - [var6_ExplicitVarSizeWithFlagsR18R5R3_Flags, - var6_ExplicitVarSizeWithFlagsR18R5R3_Values_PartitionAsSet_ExplicitVarSizeWithMarkerR3_Marker, - var6_ExplicitVarSizeWithFlagsR18R5R3_Values_PartitionAsSet_ExplicitVarSizeWithMarkerR3_Values_Explicit] -such that - var6_ExplicitVarSizeWithFlagsR18R5R3_Flags[2] -> - flatten([[var6_ExplicitVarSizeWithFlagsR18R5R3_Values_PartitionAsSet_ExplicitVarSizeWithMarkerR3_Marker[1]; int(1)], - ([] : `matrix indexed by [int()] of int`); - int(1..2)]) - - var6_ExplicitVarSizeWithFlagsR18R5R3_Values_PartitionAsSet_ExplicitVarSizeWithMarkerR3_Marker[q2] = 0 - | q2 : int(1..2)]), - var6_ExplicitVarSizeWithFlagsR18R5R3_Flags[2] -> var6_ExplicitVarSizeWithFlagsR18R5R3_Flags[1], - and([var6_ExplicitVarSizeWithFlagsR18R5R3_Flags[q5] -> - and([q23 <= var6_ExplicitVarSizeWithFlagsR18R5R3_Values_PartitionAsSet_ExplicitVarSizeWithMarkerR3_Marker[q5] - -> false - | q23 : int(1..2)]) - | q5 : int(1..2)]), - and([var6_ExplicitVarSizeWithFlagsR18R5R3_Flags[q5] -> - (2 <= var6_ExplicitVarSizeWithFlagsR18R5R3_Values_PartitionAsSet_ExplicitVarSizeWithMarkerR3_Marker[q5] -> - false) - | q5 : int(1..2)]), - and([var6_ExplicitVarSizeWithFlagsR18R5R3_Flags[q5] -> - 3 <= var6_ExplicitVarSizeWithFlagsR18R5R3_Values_PartitionAsSet_ExplicitVarSizeWithMarkerR3_Marker[q5] - | q5 : int(1..2)]), - and([var6_ExplicitVarSizeWithFlagsR18R5R3_Flags[q5] -> - var6_ExplicitVarSizeWithFlagsR18R5R3_Values_PartitionAsSet_ExplicitVarSizeWithMarkerR3_Marker[q5] <= 2 - | q5 : int(1..2)]), - and([var6_ExplicitVarSizeWithFlagsR18R5R3_Flags[q5] -> false | q5 : int(1..2)]) - diff --git a/tests/exhaustive/autogen/gen36/expected/model_6-solution000001.solution b/tests/exhaustive/autogen/gen36/expected/model_6-solution000001.solution deleted file mode 100644 index 78bab35d5f..0000000000 --- a/tests/exhaustive/autogen/gen36/expected/model_6-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting var6 be {} diff --git a/tests/exhaustive/autogen/gen36/expected/model_6.eprime b/tests/exhaustive/autogen/gen36/expected/model_6.eprime deleted file mode 100644 index 4187b0baf3..0000000000 --- a/tests/exhaustive/autogen/gen36/expected/model_6.eprime +++ /dev/null @@ -1,101 +0,0 @@ -language ESSENCE' 1.0 - -letting let1 be 2 -find var6_ExplicitVarSizeWithFlagsR19_Flags: matrix indexed by [int(1..2)] of bool -find var6_ExplicitVarSizeWithFlagsR19_Values_PartitionOccurrence_NumParts: matrix indexed by [int(1..2)] of int(1..2) -find var6_ExplicitVarSizeWithFlagsR19_Values_PartitionOccurrence_WhichPart: - matrix indexed by [int(1..2), int(2, 5)] of int(1..2) -find var6_ExplicitVarSizeWithFlagsR19_Values_PartitionOccurrence_PartSizes: - matrix indexed by [int(1..2), int(1..2)] of int(0) -find var6_ExplicitVarSizeWithFlagsR19_Values_PartitionOccurrence_FirstIndex: - matrix indexed by [int(1..2), int(1..2)] of int(2, 5) -branching on - [var6_ExplicitVarSizeWithFlagsR19_Flags, var6_ExplicitVarSizeWithFlagsR19_Values_PartitionOccurrence_NumParts, - var6_ExplicitVarSizeWithFlagsR19_Values_PartitionOccurrence_WhichPart, - var6_ExplicitVarSizeWithFlagsR19_Values_PartitionOccurrence_PartSizes, - var6_ExplicitVarSizeWithFlagsR19_Values_PartitionOccurrence_FirstIndex] -such that - var6_ExplicitVarSizeWithFlagsR19_Flags[2] -> - flatten([[var6_ExplicitVarSizeWithFlagsR19_Values_PartitionOccurrence_NumParts[1]; int(1)], - flatten([[var6_ExplicitVarSizeWithFlagsR19_Values_PartitionOccurrence_WhichPart[1, q16]; int(1)] - | q16 : int(2, 5)]), - flatten([[var6_ExplicitVarSizeWithFlagsR19_Values_PartitionOccurrence_PartSizes[1, q17]; int(1)] - | q17 : int(1..2)]), - flatten([[var6_ExplicitVarSizeWithFlagsR19_Values_PartitionOccurrence_FirstIndex[1, q18]; int(1)] - | q18 : int(1..2)]); - int(1..4)]) - - and([var6_ExplicitVarSizeWithFlagsR19_Values_PartitionOccurrence_NumParts[q2] = 1, - and([var6_ExplicitVarSizeWithFlagsR19_Values_PartitionOccurrence_WhichPart[q2, q22] = 1 - | q22 : int(2, 5)]), - and([var6_ExplicitVarSizeWithFlagsR19_Values_PartitionOccurrence_PartSizes[q2, q23] = 0 - | q23 : int(1..2)]), - and([var6_ExplicitVarSizeWithFlagsR19_Values_PartitionOccurrence_FirstIndex[q2, q24] = 2 - | q24 : int(1..2)]); - int(1..4)]) - | q2 : int(1..2)]), - var6_ExplicitVarSizeWithFlagsR19_Flags[2] -> var6_ExplicitVarSizeWithFlagsR19_Flags[1], - and([var6_ExplicitVarSizeWithFlagsR19_Flags[q5] -> - and([q6 <= var6_ExplicitVarSizeWithFlagsR19_Values_PartitionOccurrence_NumParts[q5] -> - 0 = var6_ExplicitVarSizeWithFlagsR19_Values_PartitionOccurrence_PartSizes[q5, q6] - | q6 : int(1..2)]) - | q5 : int(1..2)]), - and([var6_ExplicitVarSizeWithFlagsR19_Flags[q5] -> - and([q6 > var6_ExplicitVarSizeWithFlagsR19_Values_PartitionOccurrence_NumParts[q5] -> - var6_ExplicitVarSizeWithFlagsR19_Values_PartitionOccurrence_PartSizes[q5, q6] = 0 - | q6 : int(1..2)]) - | q5 : int(1..2)]), - and([var6_ExplicitVarSizeWithFlagsR19_Flags[q5] -> - 3 <= var6_ExplicitVarSizeWithFlagsR19_Values_PartitionOccurrence_NumParts[q5] - | q5 : int(1..2)]), - and([var6_ExplicitVarSizeWithFlagsR19_Flags[q5] -> - var6_ExplicitVarSizeWithFlagsR19_Values_PartitionOccurrence_NumParts[q5] <= 2 - | q5 : int(1..2)]), - and([var6_ExplicitVarSizeWithFlagsR19_Flags[q5] -> - var6_ExplicitVarSizeWithFlagsR19_Values_PartitionOccurrence_NumParts[q5] = - max([var6_ExplicitVarSizeWithFlagsR19_Values_PartitionOccurrence_WhichPart[q5, q9] | q9 : int(2, 5)]) - | q5 : int(1..2)]), - and([var6_ExplicitVarSizeWithFlagsR19_Flags[q5] -> - and([var6_ExplicitVarSizeWithFlagsR19_Values_PartitionOccurrence_PartSizes[q5, q10] = - sum([toInt(var6_ExplicitVarSizeWithFlagsR19_Values_PartitionOccurrence_WhichPart[q5, q11] = q10) - | q11 : int(2, 5)]) - | q10 : int(1..2)]) - | q5 : int(1..2)]), - and([var6_ExplicitVarSizeWithFlagsR19_Flags[q5] -> - and([q12 <= var6_ExplicitVarSizeWithFlagsR19_Values_PartitionOccurrence_NumParts[q5] -> - and([var6_ExplicitVarSizeWithFlagsR19_Values_PartitionOccurrence_WhichPart[q5, q13] = q12 -> - var6_ExplicitVarSizeWithFlagsR19_Values_PartitionOccurrence_FirstIndex[q5, q12] <= q13 - | q13 : int(2, 5)]) - | q12 : int(1..2)]) - | q5 : int(1..2)]), - and([var6_ExplicitVarSizeWithFlagsR19_Flags[q5] -> - and([q12 <= var6_ExplicitVarSizeWithFlagsR19_Values_PartitionOccurrence_NumParts[q5] -> - or([var6_ExplicitVarSizeWithFlagsR19_Values_PartitionOccurrence_WhichPart[q5, q13] = q12 /\ - var6_ExplicitVarSizeWithFlagsR19_Values_PartitionOccurrence_FirstIndex[q5, q12] = q13 - | q13 : int(2, 5)]) - | q12 : int(1..2)]) - | q5 : int(1..2)]), - and([var6_ExplicitVarSizeWithFlagsR19_Flags[q5] -> - and([q12 > var6_ExplicitVarSizeWithFlagsR19_Values_PartitionOccurrence_NumParts[q5] -> - var6_ExplicitVarSizeWithFlagsR19_Values_PartitionOccurrence_FirstIndex[q5, q12] = 2 - | q12 : int(1..2)]) - | q5 : int(1..2)]), - and([var6_ExplicitVarSizeWithFlagsR19_Flags[q5] -> - and([q14 <= var6_ExplicitVarSizeWithFlagsR19_Values_PartitionOccurrence_NumParts[q5] /\ - q15 <= var6_ExplicitVarSizeWithFlagsR19_Values_PartitionOccurrence_NumParts[q5] - -> - (q14 < q15 <-> - var6_ExplicitVarSizeWithFlagsR19_Values_PartitionOccurrence_FirstIndex[q5, q14] < - var6_ExplicitVarSizeWithFlagsR19_Values_PartitionOccurrence_FirstIndex[q5, q15]) - | q14 : int(1..2), q15 : int(1..2)]) - | q5 : int(1..2)]) - diff --git a/tests/exhaustive/basic/comprehension_04_2/expected/model-solution000001.solution b/tests/exhaustive/basic/comprehension_04_2/expected/model-solution000001.solution deleted file mode 100644 index 440e39fbc0..0000000000 --- a/tests/exhaustive/basic/comprehension_04_2/expected/model-solution000001.solution +++ /dev/null @@ -1,5 +0,0 @@ -language Essence 1.3 - -letting x be 6 -letting y be 7 -letting z be false diff --git a/tests/exhaustive/basic/comprehension_04_2/expected/model-solution000002.solution b/tests/exhaustive/basic/comprehension_04_2/expected/model-solution000002.solution deleted file mode 100644 index 725a23fd95..0000000000 --- a/tests/exhaustive/basic/comprehension_04_2/expected/model-solution000002.solution +++ /dev/null @@ -1,5 +0,0 @@ -language Essence 1.3 - -letting x be 6 -letting y be 7 -letting z be true diff --git a/tests/exhaustive/basic/comprehension_04_2/expected/model-solution000003.solution b/tests/exhaustive/basic/comprehension_04_2/expected/model-solution000003.solution deleted file mode 100644 index d50b52fc2a..0000000000 --- a/tests/exhaustive/basic/comprehension_04_2/expected/model-solution000003.solution +++ /dev/null @@ -1,5 +0,0 @@ -language Essence 1.3 - -letting x be 6 -letting y be 8 -letting z be false diff --git a/tests/exhaustive/basic/comprehension_04_2/expected/model-solution000004.solution b/tests/exhaustive/basic/comprehension_04_2/expected/model-solution000004.solution deleted file mode 100644 index 3b8775718d..0000000000 --- a/tests/exhaustive/basic/comprehension_04_2/expected/model-solution000004.solution +++ /dev/null @@ -1,5 +0,0 @@ -language Essence 1.3 - -letting x be 6 -letting y be 8 -letting z be true diff --git a/tests/exhaustive/basic/comprehension_04_2/expected/model.eprime b/tests/exhaustive/basic/comprehension_04_2/expected/model.eprime deleted file mode 100644 index 0463a7c0be..0000000000 --- a/tests/exhaustive/basic/comprehension_04_2/expected/model.eprime +++ /dev/null @@ -1,26 +0,0 @@ -language ESSENCE' 1.0 - -find x: int(0..1000) -find y: int(7, 8) -find z: bool -branching on [x, y, z] -such that - x = - sum([toInt(or([i_ExplicitVarSizeWithMarker_Values_1[q5] = y /\ i_ExplicitVarSizeWithMarker_Values_2[q5] = z - | q5 : int(1..2), q5 <= i_ExplicitVarSizeWithMarker_Marker])) - | i_ExplicitVarSizeWithMarker_Marker : int(0..2), - i_ExplicitVarSizeWithMarker_Values_1 : matrix indexed by [int(1..2)] of int(7..9), - i_ExplicitVarSizeWithMarker_Values_2 : matrix indexed by [int(1..2)] of bool, - 2 <= i_ExplicitVarSizeWithMarker_Marker -> - flatten([[i_ExplicitVarSizeWithMarker_Values_1[1]; int(1)], - [-toInt(i_ExplicitVarSizeWithMarker_Values_2[1]); int(1)]; - int(1..2)]) - i_ExplicitVarSizeWithMarker_Marker -> - i_ExplicitVarSizeWithMarker_Values_1[q2] = 7 /\ i_ExplicitVarSizeWithMarker_Values_2[q2] = false - | q2 : int(1..2)]), - 1 <= i_ExplicitVarSizeWithMarker_Marker, i_ExplicitVarSizeWithMarker_Marker <= 2]) - diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_1-solution000001.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_1-solution000001.solution deleted file mode 100644 index 159a613983..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {2, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_1-solution000002.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_1-solution000002.solution deleted file mode 100644 index 40f3fd5c8f..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {2, 3, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_1-solution000003.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_1-solution000003.solution deleted file mode 100644 index 8b4ecbb66d..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_1-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 3} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_1-solution000004.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_1-solution000004.solution deleted file mode 100644 index 560dd0f2f7..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_1-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 3, 4} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_1-solution000005.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_1-solution000005.solution deleted file mode 100644 index 6eeacc9727..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_1-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_1-solution000006.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_1-solution000006.solution deleted file mode 100644 index 5963aac565..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_1-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 3} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_1-solution000007.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_1-solution000007.solution deleted file mode 100644 index bd956f44e3..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_1-solution000007.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 3, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_1.eprime b/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_1.eprime deleted file mode 100644 index dd4a016cc8..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_1.eprime +++ /dev/null @@ -1,25 +0,0 @@ -language ESSENCE' 1.0 - -find s_Occurrence: matrix indexed by [int(1..4)] of bool -letting let1 be -100 -find x: int(-100..100) -find conjure_aux1: int(-16..3) -branching on [s_Occurrence, x] -such that - and([s_Occurrence[i] /\ s_Occurrence[j] -> min([i + j, i - j, i * j, i / j; int(1..4)]) <= conjure_aux1 - | i : int(1..4), j : int(1..4), i != j, allDiff([i + j, i * j, i / j; int(1..3)]), (i - j) % 2 = 0]), - sum([toInt(s_Occurrence[i] /\ s_Occurrence[j]) - | i : int(1..4), j : int(1..4), i != j, allDiff([i + j, i * j, i / j; int(1..3)]), (i - j) % 2 = 0]) - > 0 - -> - or([s_Occurrence[i] /\ s_Occurrence[j] /\ min([i + j, i - j, i * j, i / j; int(1..4)]) = conjure_aux1 - | i : int(1..4), j : int(1..4), i != j, allDiff([i + j, i * j, i / j; int(1..3)]), (i - j) % 2 = 0]), - sum([toInt(s_Occurrence[i] /\ s_Occurrence[j]) - | i : int(1..4), j : int(1..4), i != j, allDiff([i + j, i * j, i / j; int(1..3)]), (i - j) % 2 = 0]) - = 0 - -> conjure_aux1 = -16, - x = conjure_aux1, - sum([toInt(s_Occurrence[i] /\ s_Occurrence[j]) - | i : int(1..4), j : int(1..4), i != j, allDiff([i + j, i * j, i / j; int(1..3)]), (i - j) % 2 = 0]) - > 0 - diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_2-solution000001.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_2-solution000001.solution deleted file mode 100644 index bd956f44e3..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 3, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_2-solution000002.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_2-solution000002.solution deleted file mode 100644 index 5963aac565..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 3} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_2-solution000003.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_2-solution000003.solution deleted file mode 100644 index 6eeacc9727..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_2-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_2-solution000004.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_2-solution000004.solution deleted file mode 100644 index 560dd0f2f7..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_2-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 3, 4} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_2-solution000005.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_2-solution000005.solution deleted file mode 100644 index 8b4ecbb66d..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_2-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 3} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_2-solution000006.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_2-solution000006.solution deleted file mode 100644 index 40f3fd5c8f..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_2-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {2, 3, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_2-solution000007.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_2-solution000007.solution deleted file mode 100644 index 159a613983..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_2-solution000007.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {2, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_2.eprime b/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_2.eprime deleted file mode 100644 index e5a61b11a8..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_2.eprime +++ /dev/null @@ -1,33 +0,0 @@ -language ESSENCE' 1.0 - -find s_Occurrence: matrix indexed by [int(1..4)] of bool -find s_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -letting let1 be -100 -find x: int(-100..100) -find conjure_aux1: int(-16..3) -branching on [s_ExplicitVarSizeWithDummy, s_Occurrence, x] -such that - and([s_Occurrence[i] /\ s_Occurrence[j] -> min([i + j, i - j, i * j, i / j; int(1..4)]) <= conjure_aux1 - | i : int(1..4), j : int(1..4), i != j, allDiff([i + j, i * j, i / j; int(1..3)]), (i - j) % 2 = 0]), - sum([toInt(s_Occurrence[i] /\ s_Occurrence[j]) - | i : int(1..4), j : int(1..4), i != j, allDiff([i + j, i * j, i / j; int(1..3)]), (i - j) % 2 = 0]) - > 0 - -> - or([s_Occurrence[i] /\ s_Occurrence[j] /\ min([i + j, i - j, i * j, i / j; int(1..4)]) = conjure_aux1 - | i : int(1..4), j : int(1..4), i != j, allDiff([i + j, i * j, i / j; int(1..3)]), (i - j) % 2 = 0]), - sum([toInt(s_Occurrence[i] /\ s_Occurrence[j]) - | i : int(1..4), j : int(1..4), i != j, allDiff([i + j, i * j, i / j; int(1..3)]), (i - j) % 2 = 0]) - = 0 - -> conjure_aux1 = -16, - x = conjure_aux1, - sum([toInt(s_Occurrence[i] /\ s_Occurrence[j]) - | i : int(1..4), j : int(1..4), i != j, allDiff([i + j, i * j, i / j; int(1..3)]), (i - j) % 2 = 0]) - > 0, - and([s_ExplicitVarSizeWithDummy[q2] < s_ExplicitVarSizeWithDummy[q2 + 1] \/ s_ExplicitVarSizeWithDummy[q2] = 5 - | q2 : int(1..3)]), - and([s_ExplicitVarSizeWithDummy[q3] = 5 -> s_ExplicitVarSizeWithDummy[q3 + 1] = 5 | q3 : int(1..3)]), - and([s_ExplicitVarSizeWithDummy[q7] != 5 -> s_Occurrence[s_ExplicitVarSizeWithDummy[q7]] | q7 : int(1..4)]), - and([s_Occurrence[q8] -> - or([s_ExplicitVarSizeWithDummy[q10] != 5 /\ s_ExplicitVarSizeWithDummy[q10] = q8 | q10 : int(1..4)]) - | q8 : int(1..4)]) - diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_3-solution000001.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_3-solution000001.solution deleted file mode 100644 index 8b4ecbb66d..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_3-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 3} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_3-solution000002.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_3-solution000002.solution deleted file mode 100644 index 159a613983..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_3-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {2, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_3-solution000003.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_3-solution000003.solution deleted file mode 100644 index 5963aac565..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_3-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 3} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_3-solution000004.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_3-solution000004.solution deleted file mode 100644 index 6eeacc9727..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_3-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_3-solution000005.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_3-solution000005.solution deleted file mode 100644 index 560dd0f2f7..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_3-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 3, 4} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_3-solution000006.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_3-solution000006.solution deleted file mode 100644 index 40f3fd5c8f..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_3-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {2, 3, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_3-solution000007.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_3-solution000007.solution deleted file mode 100644 index bd956f44e3..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_3-solution000007.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 3, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_3.eprime b/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_3.eprime deleted file mode 100644 index dc118fd71c..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_3.eprime +++ /dev/null @@ -1,36 +0,0 @@ -language ESSENCE' 1.0 - -find s_Occurrence: matrix indexed by [int(1..4)] of bool -find s_ExplicitVarSizeWithMarker_Marker: int(0..4) -find s_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -letting let1 be -100 -find x: int(-100..100) -find conjure_aux1: int(-16..3) -branching on [s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithMarker_Values, s_Occurrence, x] -such that - and([s_Occurrence[i] /\ s_Occurrence[j] -> min([i + j, i - j, i * j, i / j; int(1..4)]) <= conjure_aux1 - | i : int(1..4), j : int(1..4), i != j, allDiff([i + j, i * j, i / j; int(1..3)]), (i - j) % 2 = 0]), - sum([toInt(s_Occurrence[i] /\ s_Occurrence[j]) - | i : int(1..4), j : int(1..4), i != j, allDiff([i + j, i * j, i / j; int(1..3)]), (i - j) % 2 = 0]) - > 0 - -> - or([s_Occurrence[i] /\ s_Occurrence[j] /\ min([i + j, i - j, i * j, i / j; int(1..4)]) = conjure_aux1 - | i : int(1..4), j : int(1..4), i != j, allDiff([i + j, i * j, i / j; int(1..3)]), (i - j) % 2 = 0]), - sum([toInt(s_Occurrence[i] /\ s_Occurrence[j]) - | i : int(1..4), j : int(1..4), i != j, allDiff([i + j, i * j, i / j; int(1..3)]), (i - j) % 2 = 0]) - = 0 - -> conjure_aux1 = -16, - x = conjure_aux1, - sum([toInt(s_Occurrence[i] /\ s_Occurrence[j]) - | i : int(1..4), j : int(1..4), i != j, allDiff([i + j, i * j, i / j; int(1..3)]), (i - j) % 2 = 0]) - > 0, - and([q2 + 1 <= s_ExplicitVarSizeWithMarker_Marker -> - s_ExplicitVarSizeWithMarker_Values[q2] < s_ExplicitVarSizeWithMarker_Values[q2 + 1] - | q2 : int(1..3)]), - and([q3 > s_ExplicitVarSizeWithMarker_Marker -> s_ExplicitVarSizeWithMarker_Values[q3] = 1 | q3 : int(1..4)]), - and([q6 <= s_ExplicitVarSizeWithMarker_Marker -> s_Occurrence[s_ExplicitVarSizeWithMarker_Values[q6]] - | q6 : int(1..4)]), - and([s_Occurrence[q7] -> - or([q9 <= s_ExplicitVarSizeWithMarker_Marker /\ s_ExplicitVarSizeWithMarker_Values[q9] = q7 | q9 : int(1..4)]) - | q7 : int(1..4)]) - diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_4-solution000001.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_4-solution000001.solution deleted file mode 100644 index 8b4ecbb66d..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_4-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 3} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_4-solution000002.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_4-solution000002.solution deleted file mode 100644 index 159a613983..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_4-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {2, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_4-solution000003.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_4-solution000003.solution deleted file mode 100644 index 5963aac565..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_4-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 3} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_4-solution000004.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_4-solution000004.solution deleted file mode 100644 index 6eeacc9727..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_4-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_4-solution000005.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_4-solution000005.solution deleted file mode 100644 index 560dd0f2f7..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_4-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 3, 4} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_4-solution000006.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_4-solution000006.solution deleted file mode 100644 index 40f3fd5c8f..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_4-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {2, 3, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_4-solution000007.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_4-solution000007.solution deleted file mode 100644 index bd956f44e3..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_4-solution000007.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 3, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_4.eprime b/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_4.eprime deleted file mode 100644 index 6c66694bc5..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_4.eprime +++ /dev/null @@ -1,36 +0,0 @@ -language ESSENCE' 1.0 - -find s_Occurrence: matrix indexed by [int(1..4)] of bool -find s_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find s_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -letting let1 be -100 -find x: int(-100..100) -find conjure_aux1: int(-16..3) -branching on [s_ExplicitVarSizeWithFlags_Flags, s_ExplicitVarSizeWithFlags_Values, s_Occurrence, x] -such that - and([s_Occurrence[i] /\ s_Occurrence[j] -> min([i + j, i - j, i * j, i / j; int(1..4)]) <= conjure_aux1 - | i : int(1..4), j : int(1..4), i != j, allDiff([i + j, i * j, i / j; int(1..3)]), (i - j) % 2 = 0]), - sum([toInt(s_Occurrence[i] /\ s_Occurrence[j]) - | i : int(1..4), j : int(1..4), i != j, allDiff([i + j, i * j, i / j; int(1..3)]), (i - j) % 2 = 0]) - > 0 - -> - or([s_Occurrence[i] /\ s_Occurrence[j] /\ min([i + j, i - j, i * j, i / j; int(1..4)]) = conjure_aux1 - | i : int(1..4), j : int(1..4), i != j, allDiff([i + j, i * j, i / j; int(1..3)]), (i - j) % 2 = 0]), - sum([toInt(s_Occurrence[i] /\ s_Occurrence[j]) - | i : int(1..4), j : int(1..4), i != j, allDiff([i + j, i * j, i / j; int(1..3)]), (i - j) % 2 = 0]) - = 0 - -> conjure_aux1 = -16, - x = conjure_aux1, - sum([toInt(s_Occurrence[i] /\ s_Occurrence[j]) - | i : int(1..4), j : int(1..4), i != j, allDiff([i + j, i * j, i / j; int(1..3)]), (i - j) % 2 = 0]) - > 0, - and([s_ExplicitVarSizeWithFlags_Flags[q2 + 1] -> - s_ExplicitVarSizeWithFlags_Values[q2] < s_ExplicitVarSizeWithFlags_Values[q2 + 1] - | q2 : int(1..3)]), - and([s_ExplicitVarSizeWithFlags_Flags[q3] = false -> s_ExplicitVarSizeWithFlags_Values[q3] = 1 | q3 : int(1..4)]), - and([s_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> s_ExplicitVarSizeWithFlags_Flags[q4] | q4 : int(1..3)]), - and([s_ExplicitVarSizeWithFlags_Flags[q8] -> s_Occurrence[s_ExplicitVarSizeWithFlags_Values[q8]] | q8 : int(1..4)]), - and([s_Occurrence[q9] -> - or([s_ExplicitVarSizeWithFlags_Flags[q11] /\ s_ExplicitVarSizeWithFlags_Values[q11] = q9 | q11 : int(1..4)]) - | q9 : int(1..4)]) - diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_2_1-solution000001.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_2_1-solution000001.solution deleted file mode 100644 index bd956f44e3..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_1_2_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 3, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_2_1-solution000002.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_2_1-solution000002.solution deleted file mode 100644 index 5963aac565..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_1_2_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 3} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_2_1-solution000003.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_2_1-solution000003.solution deleted file mode 100644 index 6eeacc9727..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_1_2_1-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_2_1-solution000004.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_2_1-solution000004.solution deleted file mode 100644 index 560dd0f2f7..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_1_2_1-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 3, 4} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_2_1-solution000005.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_2_1-solution000005.solution deleted file mode 100644 index 8b4ecbb66d..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_1_2_1-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 3} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_2_1-solution000006.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_2_1-solution000006.solution deleted file mode 100644 index 40f3fd5c8f..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_1_2_1-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {2, 3, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_2_1-solution000007.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_2_1-solution000007.solution deleted file mode 100644 index 159a613983..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_1_2_1-solution000007.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {2, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_2_1.eprime b/tests/exhaustive/basic/comprehension_letting/expected/model_1_2_1.eprime deleted file mode 100644 index 8697c1dbd6..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_1_2_1.eprime +++ /dev/null @@ -1,68 +0,0 @@ -language ESSENCE' 1.0 - -find s_Occurrence: matrix indexed by [int(1..4)] of bool -find s_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -letting let1 be -100 -find x: int(-100..100) -find conjure_aux1: int(-20..3) -branching on [s_ExplicitVarSizeWithDummy, s_Occurrence, x] -such that - and([and([s_Occurrence[i], s_ExplicitVarSizeWithDummy[q11] != 5, i != s_ExplicitVarSizeWithDummy[q11], - allDiff([i + s_ExplicitVarSizeWithDummy[q11], i * s_ExplicitVarSizeWithDummy[q11], - i / s_ExplicitVarSizeWithDummy[q11]; - int(1..3)]), - (i - s_ExplicitVarSizeWithDummy[q11]) % 2 = 0; - int(1..5)]) - -> - min([i + s_ExplicitVarSizeWithDummy[q11], i - s_ExplicitVarSizeWithDummy[q11], - i * s_ExplicitVarSizeWithDummy[q11], i / s_ExplicitVarSizeWithDummy[q11]; - int(1..4)]) - <= conjure_aux1 - | i : int(1..4), q11 : int(1..4)]), - sum([toInt(and([s_Occurrence[i], s_ExplicitVarSizeWithDummy[q11] != 5, i != s_ExplicitVarSizeWithDummy[q11], - allDiff([i + s_ExplicitVarSizeWithDummy[q11], i * s_ExplicitVarSizeWithDummy[q11], - i / s_ExplicitVarSizeWithDummy[q11]; - int(1..3)]), - (i - s_ExplicitVarSizeWithDummy[q11]) % 2 = 0; - int(1..5)])) - | i : int(1..4), q11 : int(1..4)]) - > 0 - -> - or([and([s_Occurrence[i], s_ExplicitVarSizeWithDummy[q11] != 5, i != s_ExplicitVarSizeWithDummy[q11], - allDiff([i + s_ExplicitVarSizeWithDummy[q11], i * s_ExplicitVarSizeWithDummy[q11], - i / s_ExplicitVarSizeWithDummy[q11]; - int(1..3)]), - (i - s_ExplicitVarSizeWithDummy[q11]) % 2 = 0; - int(1..5)]) - /\ - min([i + s_ExplicitVarSizeWithDummy[q11], i - s_ExplicitVarSizeWithDummy[q11], - i * s_ExplicitVarSizeWithDummy[q11], i / s_ExplicitVarSizeWithDummy[q11]; - int(1..4)]) - = conjure_aux1 - | i : int(1..4), q11 : int(1..4)]), - sum([toInt(and([s_Occurrence[i], s_ExplicitVarSizeWithDummy[q11] != 5, i != s_ExplicitVarSizeWithDummy[q11], - allDiff([i + s_ExplicitVarSizeWithDummy[q11], i * s_ExplicitVarSizeWithDummy[q11], - i / s_ExplicitVarSizeWithDummy[q11]; - int(1..3)]), - (i - s_ExplicitVarSizeWithDummy[q11]) % 2 = 0; - int(1..5)])) - | i : int(1..4), q11 : int(1..4)]) - = 0 - -> conjure_aux1 = -20, - x = conjure_aux1, - sum([toInt(and([s_Occurrence[i], s_ExplicitVarSizeWithDummy[q11] != 5, i != s_ExplicitVarSizeWithDummy[q11], - allDiff([i + s_ExplicitVarSizeWithDummy[q11], i * s_ExplicitVarSizeWithDummy[q11], - i / s_ExplicitVarSizeWithDummy[q11]; - int(1..3)]), - (i - s_ExplicitVarSizeWithDummy[q11]) % 2 = 0; - int(1..5)])) - | i : int(1..4), q11 : int(1..4)]) - > 0, - and([s_ExplicitVarSizeWithDummy[q2] < s_ExplicitVarSizeWithDummy[q2 + 1] \/ s_ExplicitVarSizeWithDummy[q2] = 5 - | q2 : int(1..3)]), - and([s_ExplicitVarSizeWithDummy[q3] = 5 -> s_ExplicitVarSizeWithDummy[q3 + 1] = 5 | q3 : int(1..3)]), - and([s_ExplicitVarSizeWithDummy[q7] != 5 -> s_Occurrence[s_ExplicitVarSizeWithDummy[q7]] | q7 : int(1..4)]), - and([s_Occurrence[q8] -> - or([s_ExplicitVarSizeWithDummy[q10] != 5 /\ s_ExplicitVarSizeWithDummy[q10] = q8 | q10 : int(1..4)]) - | q8 : int(1..4)]) - diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_2_2-solution000001.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_2_2-solution000001.solution deleted file mode 100644 index bd956f44e3..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_1_2_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 3, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_2_2-solution000002.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_2_2-solution000002.solution deleted file mode 100644 index 5963aac565..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_1_2_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 3} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_2_2-solution000003.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_2_2-solution000003.solution deleted file mode 100644 index 6eeacc9727..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_1_2_2-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_2_2-solution000004.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_2_2-solution000004.solution deleted file mode 100644 index 560dd0f2f7..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_1_2_2-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 3, 4} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_2_2-solution000005.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_2_2-solution000005.solution deleted file mode 100644 index 8b4ecbb66d..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_1_2_2-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 3} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_2_2-solution000006.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_2_2-solution000006.solution deleted file mode 100644 index 40f3fd5c8f..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_1_2_2-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {2, 3, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_2_2-solution000007.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_2_2-solution000007.solution deleted file mode 100644 index 159a613983..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_1_2_2-solution000007.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {2, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_2_2.eprime b/tests/exhaustive/basic/comprehension_letting/expected/model_1_2_2.eprime deleted file mode 100644 index 8697c1dbd6..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_1_2_2.eprime +++ /dev/null @@ -1,68 +0,0 @@ -language ESSENCE' 1.0 - -find s_Occurrence: matrix indexed by [int(1..4)] of bool -find s_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -letting let1 be -100 -find x: int(-100..100) -find conjure_aux1: int(-20..3) -branching on [s_ExplicitVarSizeWithDummy, s_Occurrence, x] -such that - and([and([s_Occurrence[i], s_ExplicitVarSizeWithDummy[q11] != 5, i != s_ExplicitVarSizeWithDummy[q11], - allDiff([i + s_ExplicitVarSizeWithDummy[q11], i * s_ExplicitVarSizeWithDummy[q11], - i / s_ExplicitVarSizeWithDummy[q11]; - int(1..3)]), - (i - s_ExplicitVarSizeWithDummy[q11]) % 2 = 0; - int(1..5)]) - -> - min([i + s_ExplicitVarSizeWithDummy[q11], i - s_ExplicitVarSizeWithDummy[q11], - i * s_ExplicitVarSizeWithDummy[q11], i / s_ExplicitVarSizeWithDummy[q11]; - int(1..4)]) - <= conjure_aux1 - | i : int(1..4), q11 : int(1..4)]), - sum([toInt(and([s_Occurrence[i], s_ExplicitVarSizeWithDummy[q11] != 5, i != s_ExplicitVarSizeWithDummy[q11], - allDiff([i + s_ExplicitVarSizeWithDummy[q11], i * s_ExplicitVarSizeWithDummy[q11], - i / s_ExplicitVarSizeWithDummy[q11]; - int(1..3)]), - (i - s_ExplicitVarSizeWithDummy[q11]) % 2 = 0; - int(1..5)])) - | i : int(1..4), q11 : int(1..4)]) - > 0 - -> - or([and([s_Occurrence[i], s_ExplicitVarSizeWithDummy[q11] != 5, i != s_ExplicitVarSizeWithDummy[q11], - allDiff([i + s_ExplicitVarSizeWithDummy[q11], i * s_ExplicitVarSizeWithDummy[q11], - i / s_ExplicitVarSizeWithDummy[q11]; - int(1..3)]), - (i - s_ExplicitVarSizeWithDummy[q11]) % 2 = 0; - int(1..5)]) - /\ - min([i + s_ExplicitVarSizeWithDummy[q11], i - s_ExplicitVarSizeWithDummy[q11], - i * s_ExplicitVarSizeWithDummy[q11], i / s_ExplicitVarSizeWithDummy[q11]; - int(1..4)]) - = conjure_aux1 - | i : int(1..4), q11 : int(1..4)]), - sum([toInt(and([s_Occurrence[i], s_ExplicitVarSizeWithDummy[q11] != 5, i != s_ExplicitVarSizeWithDummy[q11], - allDiff([i + s_ExplicitVarSizeWithDummy[q11], i * s_ExplicitVarSizeWithDummy[q11], - i / s_ExplicitVarSizeWithDummy[q11]; - int(1..3)]), - (i - s_ExplicitVarSizeWithDummy[q11]) % 2 = 0; - int(1..5)])) - | i : int(1..4), q11 : int(1..4)]) - = 0 - -> conjure_aux1 = -20, - x = conjure_aux1, - sum([toInt(and([s_Occurrence[i], s_ExplicitVarSizeWithDummy[q11] != 5, i != s_ExplicitVarSizeWithDummy[q11], - allDiff([i + s_ExplicitVarSizeWithDummy[q11], i * s_ExplicitVarSizeWithDummy[q11], - i / s_ExplicitVarSizeWithDummy[q11]; - int(1..3)]), - (i - s_ExplicitVarSizeWithDummy[q11]) % 2 = 0; - int(1..5)])) - | i : int(1..4), q11 : int(1..4)]) - > 0, - and([s_ExplicitVarSizeWithDummy[q2] < s_ExplicitVarSizeWithDummy[q2 + 1] \/ s_ExplicitVarSizeWithDummy[q2] = 5 - | q2 : int(1..3)]), - and([s_ExplicitVarSizeWithDummy[q3] = 5 -> s_ExplicitVarSizeWithDummy[q3 + 1] = 5 | q3 : int(1..3)]), - and([s_ExplicitVarSizeWithDummy[q7] != 5 -> s_Occurrence[s_ExplicitVarSizeWithDummy[q7]] | q7 : int(1..4)]), - and([s_Occurrence[q8] -> - or([s_ExplicitVarSizeWithDummy[q10] != 5 /\ s_ExplicitVarSizeWithDummy[q10] = q8 | q10 : int(1..4)]) - | q8 : int(1..4)]) - diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_2_3-solution000001.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_2_3-solution000001.solution deleted file mode 100644 index 8b4ecbb66d..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_1_2_3-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 3} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_2_3-solution000002.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_2_3-solution000002.solution deleted file mode 100644 index 159a613983..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_1_2_3-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {2, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_2_3-solution000003.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_2_3-solution000003.solution deleted file mode 100644 index 5963aac565..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_1_2_3-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 3} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_2_3-solution000004.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_2_3-solution000004.solution deleted file mode 100644 index 6eeacc9727..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_1_2_3-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_2_3-solution000005.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_2_3-solution000005.solution deleted file mode 100644 index 560dd0f2f7..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_1_2_3-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 3, 4} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_2_3-solution000006.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_2_3-solution000006.solution deleted file mode 100644 index 40f3fd5c8f..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_1_2_3-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {2, 3, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_2_3-solution000007.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_2_3-solution000007.solution deleted file mode 100644 index bd956f44e3..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_1_2_3-solution000007.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 3, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_2_3.eprime b/tests/exhaustive/basic/comprehension_letting/expected/model_1_2_3.eprime deleted file mode 100644 index a5ab41cb34..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_1_2_3.eprime +++ /dev/null @@ -1,92 +0,0 @@ -language ESSENCE' 1.0 - -find s_Occurrence: matrix indexed by [int(1..4)] of bool -find s_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -find s_ExplicitVarSizeWithMarker_Marker: int(0..4) -find s_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -letting let1 be -100 -find x: int(-100..100) -find conjure_aux1: int(-20..3) -branching on - [s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithMarker_Values, s_Occurrence, s_ExplicitVarSizeWithDummy, - x] -such that - and([and([s_Occurrence[i], s_ExplicitVarSizeWithDummy[q27] != 5, i != s_ExplicitVarSizeWithDummy[q27], - allDiff([i + s_ExplicitVarSizeWithDummy[q27], i * s_ExplicitVarSizeWithDummy[q27], - i / s_ExplicitVarSizeWithDummy[q27]; - int(1..3)]), - (i - s_ExplicitVarSizeWithDummy[q27]) % 2 = 0; - int(1..5)]) - -> - min([i + s_ExplicitVarSizeWithDummy[q27], i - s_ExplicitVarSizeWithDummy[q27], - i * s_ExplicitVarSizeWithDummy[q27], i / s_ExplicitVarSizeWithDummy[q27]; - int(1..4)]) - <= conjure_aux1 - | i : int(1..4), q27 : int(1..4)]), - sum([toInt(and([s_Occurrence[i], s_ExplicitVarSizeWithDummy[q27] != 5, i != s_ExplicitVarSizeWithDummy[q27], - allDiff([i + s_ExplicitVarSizeWithDummy[q27], i * s_ExplicitVarSizeWithDummy[q27], - i / s_ExplicitVarSizeWithDummy[q27]; - int(1..3)]), - (i - s_ExplicitVarSizeWithDummy[q27]) % 2 = 0; - int(1..5)])) - | i : int(1..4), q27 : int(1..4)]) - > 0 - -> - or([and([s_Occurrence[i], s_ExplicitVarSizeWithDummy[q27] != 5, i != s_ExplicitVarSizeWithDummy[q27], - allDiff([i + s_ExplicitVarSizeWithDummy[q27], i * s_ExplicitVarSizeWithDummy[q27], - i / s_ExplicitVarSizeWithDummy[q27]; - int(1..3)]), - (i - s_ExplicitVarSizeWithDummy[q27]) % 2 = 0; - int(1..5)]) - /\ - min([i + s_ExplicitVarSizeWithDummy[q27], i - s_ExplicitVarSizeWithDummy[q27], - i * s_ExplicitVarSizeWithDummy[q27], i / s_ExplicitVarSizeWithDummy[q27]; - int(1..4)]) - = conjure_aux1 - | i : int(1..4), q27 : int(1..4)]), - sum([toInt(and([s_Occurrence[i], s_ExplicitVarSizeWithDummy[q27] != 5, i != s_ExplicitVarSizeWithDummy[q27], - allDiff([i + s_ExplicitVarSizeWithDummy[q27], i * s_ExplicitVarSizeWithDummy[q27], - i / s_ExplicitVarSizeWithDummy[q27]; - int(1..3)]), - (i - s_ExplicitVarSizeWithDummy[q27]) % 2 = 0; - int(1..5)])) - | i : int(1..4), q27 : int(1..4)]) - = 0 - -> conjure_aux1 = -20, - x = conjure_aux1, - sum([toInt(and([s_Occurrence[i], s_ExplicitVarSizeWithDummy[q27] != 5, i != s_ExplicitVarSizeWithDummy[q27], - allDiff([i + s_ExplicitVarSizeWithDummy[q27], i * s_ExplicitVarSizeWithDummy[q27], - i / s_ExplicitVarSizeWithDummy[q27]; - int(1..3)]), - (i - s_ExplicitVarSizeWithDummy[q27]) % 2 = 0; - int(1..5)])) - | i : int(1..4), q27 : int(1..4)]) - > 0, - and([s_ExplicitVarSizeWithDummy[q2] < s_ExplicitVarSizeWithDummy[q2 + 1] \/ s_ExplicitVarSizeWithDummy[q2] = 5 - | q2 : int(1..3)]), - and([s_ExplicitVarSizeWithDummy[q3] = 5 -> s_ExplicitVarSizeWithDummy[q3 + 1] = 5 | q3 : int(1..3)]), - and([s_ExplicitVarSizeWithDummy[q7] != 5 -> s_Occurrence[s_ExplicitVarSizeWithDummy[q7]] | q7 : int(1..4)]), - and([s_Occurrence[q8] -> - or([s_ExplicitVarSizeWithDummy[q10] != 5 /\ s_ExplicitVarSizeWithDummy[q10] = q8 | q10 : int(1..4)]) - | q8 : int(1..4)]), - and([q11 + 1 <= s_ExplicitVarSizeWithMarker_Marker -> - s_ExplicitVarSizeWithMarker_Values[q11] < s_ExplicitVarSizeWithMarker_Values[q11 + 1] - | q11 : int(1..3)]), - and([q12 > s_ExplicitVarSizeWithMarker_Marker -> s_ExplicitVarSizeWithMarker_Values[q12] = 1 | q12 : int(1..4)]), - and([q15 <= s_ExplicitVarSizeWithMarker_Marker -> s_Occurrence[s_ExplicitVarSizeWithMarker_Values[q15]] - | q15 : int(1..4)]), - and([s_Occurrence[q16] -> - or([q18 <= s_ExplicitVarSizeWithMarker_Marker /\ s_ExplicitVarSizeWithMarker_Values[q18] = q16 - | q18 : int(1..4)]) - | q16 : int(1..4)]), - and([q20 <= s_ExplicitVarSizeWithMarker_Marker -> - or([s_ExplicitVarSizeWithDummy[q22] != 5 /\ - s_ExplicitVarSizeWithDummy[q22] = s_ExplicitVarSizeWithMarker_Values[q20] - | q22 : int(1..4)]) - | q20 : int(1..4)]), - and([s_ExplicitVarSizeWithDummy[q24] != 5 -> - or([q26 <= s_ExplicitVarSizeWithMarker_Marker /\ - s_ExplicitVarSizeWithMarker_Values[q26] = s_ExplicitVarSizeWithDummy[q24] - | q26 : int(1..4)]) - | q24 : int(1..4)]) - diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_2_4-solution000001.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_2_4-solution000001.solution deleted file mode 100644 index 8b4ecbb66d..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_1_2_4-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 3} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_2_4-solution000002.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_2_4-solution000002.solution deleted file mode 100644 index 159a613983..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_1_2_4-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {2, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_2_4-solution000003.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_2_4-solution000003.solution deleted file mode 100644 index 5963aac565..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_1_2_4-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 3} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_2_4-solution000004.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_2_4-solution000004.solution deleted file mode 100644 index 6eeacc9727..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_1_2_4-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_2_4-solution000005.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_2_4-solution000005.solution deleted file mode 100644 index 560dd0f2f7..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_1_2_4-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 3, 4} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_2_4-solution000006.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_2_4-solution000006.solution deleted file mode 100644 index 40f3fd5c8f..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_1_2_4-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {2, 3, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_2_4-solution000007.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_2_4-solution000007.solution deleted file mode 100644 index bd956f44e3..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_1_2_4-solution000007.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 3, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_2_4.eprime b/tests/exhaustive/basic/comprehension_letting/expected/model_1_2_4.eprime deleted file mode 100644 index 264f061fe8..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_1_2_4.eprime +++ /dev/null @@ -1,92 +0,0 @@ -language ESSENCE' 1.0 - -find s_Occurrence: matrix indexed by [int(1..4)] of bool -find s_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -find s_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find s_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -letting let1 be -100 -find x: int(-100..100) -find conjure_aux1: int(-20..3) -branching on - [s_ExplicitVarSizeWithFlags_Flags, s_ExplicitVarSizeWithFlags_Values, s_Occurrence, s_ExplicitVarSizeWithDummy, x] -such that - and([and([s_Occurrence[i], s_ExplicitVarSizeWithDummy[q29] != 5, i != s_ExplicitVarSizeWithDummy[q29], - allDiff([i + s_ExplicitVarSizeWithDummy[q29], i * s_ExplicitVarSizeWithDummy[q29], - i / s_ExplicitVarSizeWithDummy[q29]; - int(1..3)]), - (i - s_ExplicitVarSizeWithDummy[q29]) % 2 = 0; - int(1..5)]) - -> - min([i + s_ExplicitVarSizeWithDummy[q29], i - s_ExplicitVarSizeWithDummy[q29], - i * s_ExplicitVarSizeWithDummy[q29], i / s_ExplicitVarSizeWithDummy[q29]; - int(1..4)]) - <= conjure_aux1 - | i : int(1..4), q29 : int(1..4)]), - sum([toInt(and([s_Occurrence[i], s_ExplicitVarSizeWithDummy[q29] != 5, i != s_ExplicitVarSizeWithDummy[q29], - allDiff([i + s_ExplicitVarSizeWithDummy[q29], i * s_ExplicitVarSizeWithDummy[q29], - i / s_ExplicitVarSizeWithDummy[q29]; - int(1..3)]), - (i - s_ExplicitVarSizeWithDummy[q29]) % 2 = 0; - int(1..5)])) - | i : int(1..4), q29 : int(1..4)]) - > 0 - -> - or([and([s_Occurrence[i], s_ExplicitVarSizeWithDummy[q29] != 5, i != s_ExplicitVarSizeWithDummy[q29], - allDiff([i + s_ExplicitVarSizeWithDummy[q29], i * s_ExplicitVarSizeWithDummy[q29], - i / s_ExplicitVarSizeWithDummy[q29]; - int(1..3)]), - (i - s_ExplicitVarSizeWithDummy[q29]) % 2 = 0; - int(1..5)]) - /\ - min([i + s_ExplicitVarSizeWithDummy[q29], i - s_ExplicitVarSizeWithDummy[q29], - i * s_ExplicitVarSizeWithDummy[q29], i / s_ExplicitVarSizeWithDummy[q29]; - int(1..4)]) - = conjure_aux1 - | i : int(1..4), q29 : int(1..4)]), - sum([toInt(and([s_Occurrence[i], s_ExplicitVarSizeWithDummy[q29] != 5, i != s_ExplicitVarSizeWithDummy[q29], - allDiff([i + s_ExplicitVarSizeWithDummy[q29], i * s_ExplicitVarSizeWithDummy[q29], - i / s_ExplicitVarSizeWithDummy[q29]; - int(1..3)]), - (i - s_ExplicitVarSizeWithDummy[q29]) % 2 = 0; - int(1..5)])) - | i : int(1..4), q29 : int(1..4)]) - = 0 - -> conjure_aux1 = -20, - x = conjure_aux1, - sum([toInt(and([s_Occurrence[i], s_ExplicitVarSizeWithDummy[q29] != 5, i != s_ExplicitVarSizeWithDummy[q29], - allDiff([i + s_ExplicitVarSizeWithDummy[q29], i * s_ExplicitVarSizeWithDummy[q29], - i / s_ExplicitVarSizeWithDummy[q29]; - int(1..3)]), - (i - s_ExplicitVarSizeWithDummy[q29]) % 2 = 0; - int(1..5)])) - | i : int(1..4), q29 : int(1..4)]) - > 0, - and([s_ExplicitVarSizeWithDummy[q2] < s_ExplicitVarSizeWithDummy[q2 + 1] \/ s_ExplicitVarSizeWithDummy[q2] = 5 - | q2 : int(1..3)]), - and([s_ExplicitVarSizeWithDummy[q3] = 5 -> s_ExplicitVarSizeWithDummy[q3 + 1] = 5 | q3 : int(1..3)]), - and([s_ExplicitVarSizeWithDummy[q7] != 5 -> s_Occurrence[s_ExplicitVarSizeWithDummy[q7]] | q7 : int(1..4)]), - and([s_Occurrence[q8] -> - or([s_ExplicitVarSizeWithDummy[q10] != 5 /\ s_ExplicitVarSizeWithDummy[q10] = q8 | q10 : int(1..4)]) - | q8 : int(1..4)]), - and([s_ExplicitVarSizeWithFlags_Flags[q11 + 1] -> - s_ExplicitVarSizeWithFlags_Values[q11] < s_ExplicitVarSizeWithFlags_Values[q11 + 1] - | q11 : int(1..3)]), - and([s_ExplicitVarSizeWithFlags_Flags[q12] = false -> s_ExplicitVarSizeWithFlags_Values[q12] = 1 - | q12 : int(1..4)]), - and([s_ExplicitVarSizeWithFlags_Flags[q13 + 1] -> s_ExplicitVarSizeWithFlags_Flags[q13] | q13 : int(1..3)]), - and([s_ExplicitVarSizeWithFlags_Flags[q17] -> s_Occurrence[s_ExplicitVarSizeWithFlags_Values[q17]] - | q17 : int(1..4)]), - and([s_Occurrence[q18] -> - or([s_ExplicitVarSizeWithFlags_Flags[q20] /\ s_ExplicitVarSizeWithFlags_Values[q20] = q18 | q20 : int(1..4)]) - | q18 : int(1..4)]), - and([s_ExplicitVarSizeWithFlags_Flags[q22] -> - or([s_ExplicitVarSizeWithDummy[q24] != 5 /\ - s_ExplicitVarSizeWithDummy[q24] = s_ExplicitVarSizeWithFlags_Values[q22] - | q24 : int(1..4)]) - | q22 : int(1..4)]), - and([s_ExplicitVarSizeWithDummy[q26] != 5 -> - or([s_ExplicitVarSizeWithFlags_Flags[q28] /\ - s_ExplicitVarSizeWithFlags_Values[q28] = s_ExplicitVarSizeWithDummy[q26] - | q28 : int(1..4)]) - | q26 : int(1..4)]) - diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_3_1-solution000001.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_3_1-solution000001.solution deleted file mode 100644 index 8b4ecbb66d..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_1_3_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 3} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_3_1-solution000002.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_3_1-solution000002.solution deleted file mode 100644 index 159a613983..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_1_3_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {2, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_3_1-solution000003.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_3_1-solution000003.solution deleted file mode 100644 index 5963aac565..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_1_3_1-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 3} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_3_1-solution000004.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_3_1-solution000004.solution deleted file mode 100644 index 6eeacc9727..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_1_3_1-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_3_1-solution000005.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_3_1-solution000005.solution deleted file mode 100644 index 560dd0f2f7..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_1_3_1-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 3, 4} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_3_1-solution000006.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_3_1-solution000006.solution deleted file mode 100644 index 40f3fd5c8f..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_1_3_1-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {2, 3, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_3_1-solution000007.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_3_1-solution000007.solution deleted file mode 100644 index bd956f44e3..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_1_3_1-solution000007.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 3, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_3_1.eprime b/tests/exhaustive/basic/comprehension_letting/expected/model_1_3_1.eprime deleted file mode 100644 index 52358293ff..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_1_3_1.eprime +++ /dev/null @@ -1,74 +0,0 @@ -language ESSENCE' 1.0 - -find s_Occurrence: matrix indexed by [int(1..4)] of bool -find s_ExplicitVarSizeWithMarker_Marker: int(0..4) -find s_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -letting let1 be -100 -find x: int(-100..100) -find conjure_aux1: int(-16..3) -branching on [s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithMarker_Values, s_Occurrence, x] -such that - and([and([s_Occurrence[i], q10 <= s_ExplicitVarSizeWithMarker_Marker, i != s_ExplicitVarSizeWithMarker_Values[q10], - allDiff([i + s_ExplicitVarSizeWithMarker_Values[q10], i * s_ExplicitVarSizeWithMarker_Values[q10], - i / s_ExplicitVarSizeWithMarker_Values[q10]; - int(1..3)]), - (i - s_ExplicitVarSizeWithMarker_Values[q10]) % 2 = 0; - int(1..5)]) - -> - min([i + s_ExplicitVarSizeWithMarker_Values[q10], i - s_ExplicitVarSizeWithMarker_Values[q10], - i * s_ExplicitVarSizeWithMarker_Values[q10], i / s_ExplicitVarSizeWithMarker_Values[q10]; - int(1..4)]) - <= conjure_aux1 - | i : int(1..4), q10 : int(1..4)]), - sum([toInt(and([s_Occurrence[i], q10 <= s_ExplicitVarSizeWithMarker_Marker, - i != s_ExplicitVarSizeWithMarker_Values[q10], - allDiff([i + s_ExplicitVarSizeWithMarker_Values[q10], i * s_ExplicitVarSizeWithMarker_Values[q10], - i / s_ExplicitVarSizeWithMarker_Values[q10]; - int(1..3)]), - (i - s_ExplicitVarSizeWithMarker_Values[q10]) % 2 = 0; - int(1..5)])) - | i : int(1..4), q10 : int(1..4)]) - > 0 - -> - or([and([s_Occurrence[i], q10 <= s_ExplicitVarSizeWithMarker_Marker, i != s_ExplicitVarSizeWithMarker_Values[q10], - allDiff([i + s_ExplicitVarSizeWithMarker_Values[q10], i * s_ExplicitVarSizeWithMarker_Values[q10], - i / s_ExplicitVarSizeWithMarker_Values[q10]; - int(1..3)]), - (i - s_ExplicitVarSizeWithMarker_Values[q10]) % 2 = 0; - int(1..5)]) - /\ - min([i + s_ExplicitVarSizeWithMarker_Values[q10], i - s_ExplicitVarSizeWithMarker_Values[q10], - i * s_ExplicitVarSizeWithMarker_Values[q10], i / s_ExplicitVarSizeWithMarker_Values[q10]; - int(1..4)]) - = conjure_aux1 - | i : int(1..4), q10 : int(1..4)]), - sum([toInt(and([s_Occurrence[i], q10 <= s_ExplicitVarSizeWithMarker_Marker, - i != s_ExplicitVarSizeWithMarker_Values[q10], - allDiff([i + s_ExplicitVarSizeWithMarker_Values[q10], i * s_ExplicitVarSizeWithMarker_Values[q10], - i / s_ExplicitVarSizeWithMarker_Values[q10]; - int(1..3)]), - (i - s_ExplicitVarSizeWithMarker_Values[q10]) % 2 = 0; - int(1..5)])) - | i : int(1..4), q10 : int(1..4)]) - = 0 - -> conjure_aux1 = -16, - x = conjure_aux1, - sum([toInt(and([s_Occurrence[i], q10 <= s_ExplicitVarSizeWithMarker_Marker, - i != s_ExplicitVarSizeWithMarker_Values[q10], - allDiff([i + s_ExplicitVarSizeWithMarker_Values[q10], i * s_ExplicitVarSizeWithMarker_Values[q10], - i / s_ExplicitVarSizeWithMarker_Values[q10]; - int(1..3)]), - (i - s_ExplicitVarSizeWithMarker_Values[q10]) % 2 = 0; - int(1..5)])) - | i : int(1..4), q10 : int(1..4)]) - > 0, - and([q2 + 1 <= s_ExplicitVarSizeWithMarker_Marker -> - s_ExplicitVarSizeWithMarker_Values[q2] < s_ExplicitVarSizeWithMarker_Values[q2 + 1] - | q2 : int(1..3)]), - and([q3 > s_ExplicitVarSizeWithMarker_Marker -> s_ExplicitVarSizeWithMarker_Values[q3] = 1 | q3 : int(1..4)]), - and([q6 <= s_ExplicitVarSizeWithMarker_Marker -> s_Occurrence[s_ExplicitVarSizeWithMarker_Values[q6]] - | q6 : int(1..4)]), - and([s_Occurrence[q7] -> - or([q9 <= s_ExplicitVarSizeWithMarker_Marker /\ s_ExplicitVarSizeWithMarker_Values[q9] = q7 | q9 : int(1..4)]) - | q7 : int(1..4)]) - diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_3_2-solution000001.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_3_2-solution000001.solution deleted file mode 100644 index bd956f44e3..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_1_3_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 3, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_3_2-solution000002.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_3_2-solution000002.solution deleted file mode 100644 index 5963aac565..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_1_3_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 3} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_3_2-solution000003.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_3_2-solution000003.solution deleted file mode 100644 index 6eeacc9727..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_1_3_2-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_3_2-solution000004.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_3_2-solution000004.solution deleted file mode 100644 index 560dd0f2f7..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_1_3_2-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 3, 4} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_3_2-solution000005.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_3_2-solution000005.solution deleted file mode 100644 index 8b4ecbb66d..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_1_3_2-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 3} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_3_2-solution000006.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_3_2-solution000006.solution deleted file mode 100644 index 40f3fd5c8f..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_1_3_2-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {2, 3, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_3_2-solution000007.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_3_2-solution000007.solution deleted file mode 100644 index 159a613983..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_1_3_2-solution000007.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {2, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_3_2.eprime b/tests/exhaustive/basic/comprehension_letting/expected/model_1_3_2.eprime deleted file mode 100644 index 8aedcdcc81..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_1_3_2.eprime +++ /dev/null @@ -1,94 +0,0 @@ -language ESSENCE' 1.0 - -find s_Occurrence: matrix indexed by [int(1..4)] of bool -find s_ExplicitVarSizeWithMarker_Marker: int(0..4) -find s_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -find s_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -letting let1 be -100 -find x: int(-100..100) -find conjure_aux1: int(-16..3) -branching on - [s_ExplicitVarSizeWithDummy, s_Occurrence, s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithMarker_Values, - x] -such that - and([and([s_Occurrence[i], q27 <= s_ExplicitVarSizeWithMarker_Marker, i != s_ExplicitVarSizeWithMarker_Values[q27], - allDiff([i + s_ExplicitVarSizeWithMarker_Values[q27], i * s_ExplicitVarSizeWithMarker_Values[q27], - i / s_ExplicitVarSizeWithMarker_Values[q27]; - int(1..3)]), - (i - s_ExplicitVarSizeWithMarker_Values[q27]) % 2 = 0; - int(1..5)]) - -> - min([i + s_ExplicitVarSizeWithMarker_Values[q27], i - s_ExplicitVarSizeWithMarker_Values[q27], - i * s_ExplicitVarSizeWithMarker_Values[q27], i / s_ExplicitVarSizeWithMarker_Values[q27]; - int(1..4)]) - <= conjure_aux1 - | i : int(1..4), q27 : int(1..4)]), - sum([toInt(and([s_Occurrence[i], q27 <= s_ExplicitVarSizeWithMarker_Marker, - i != s_ExplicitVarSizeWithMarker_Values[q27], - allDiff([i + s_ExplicitVarSizeWithMarker_Values[q27], i * s_ExplicitVarSizeWithMarker_Values[q27], - i / s_ExplicitVarSizeWithMarker_Values[q27]; - int(1..3)]), - (i - s_ExplicitVarSizeWithMarker_Values[q27]) % 2 = 0; - int(1..5)])) - | i : int(1..4), q27 : int(1..4)]) - > 0 - -> - or([and([s_Occurrence[i], q27 <= s_ExplicitVarSizeWithMarker_Marker, i != s_ExplicitVarSizeWithMarker_Values[q27], - allDiff([i + s_ExplicitVarSizeWithMarker_Values[q27], i * s_ExplicitVarSizeWithMarker_Values[q27], - i / s_ExplicitVarSizeWithMarker_Values[q27]; - int(1..3)]), - (i - s_ExplicitVarSizeWithMarker_Values[q27]) % 2 = 0; - int(1..5)]) - /\ - min([i + s_ExplicitVarSizeWithMarker_Values[q27], i - s_ExplicitVarSizeWithMarker_Values[q27], - i * s_ExplicitVarSizeWithMarker_Values[q27], i / s_ExplicitVarSizeWithMarker_Values[q27]; - int(1..4)]) - = conjure_aux1 - | i : int(1..4), q27 : int(1..4)]), - sum([toInt(and([s_Occurrence[i], q27 <= s_ExplicitVarSizeWithMarker_Marker, - i != s_ExplicitVarSizeWithMarker_Values[q27], - allDiff([i + s_ExplicitVarSizeWithMarker_Values[q27], i * s_ExplicitVarSizeWithMarker_Values[q27], - i / s_ExplicitVarSizeWithMarker_Values[q27]; - int(1..3)]), - (i - s_ExplicitVarSizeWithMarker_Values[q27]) % 2 = 0; - int(1..5)])) - | i : int(1..4), q27 : int(1..4)]) - = 0 - -> conjure_aux1 = -16, - x = conjure_aux1, - sum([toInt(and([s_Occurrence[i], q27 <= s_ExplicitVarSizeWithMarker_Marker, - i != s_ExplicitVarSizeWithMarker_Values[q27], - allDiff([i + s_ExplicitVarSizeWithMarker_Values[q27], i * s_ExplicitVarSizeWithMarker_Values[q27], - i / s_ExplicitVarSizeWithMarker_Values[q27]; - int(1..3)]), - (i - s_ExplicitVarSizeWithMarker_Values[q27]) % 2 = 0; - int(1..5)])) - | i : int(1..4), q27 : int(1..4)]) - > 0, - and([q2 + 1 <= s_ExplicitVarSizeWithMarker_Marker -> - s_ExplicitVarSizeWithMarker_Values[q2] < s_ExplicitVarSizeWithMarker_Values[q2 + 1] - | q2 : int(1..3)]), - and([q3 > s_ExplicitVarSizeWithMarker_Marker -> s_ExplicitVarSizeWithMarker_Values[q3] = 1 | q3 : int(1..4)]), - and([q6 <= s_ExplicitVarSizeWithMarker_Marker -> s_Occurrence[s_ExplicitVarSizeWithMarker_Values[q6]] - | q6 : int(1..4)]), - and([s_Occurrence[q7] -> - or([q9 <= s_ExplicitVarSizeWithMarker_Marker /\ s_ExplicitVarSizeWithMarker_Values[q9] = q7 | q9 : int(1..4)]) - | q7 : int(1..4)]), - and([s_ExplicitVarSizeWithDummy[q10] < s_ExplicitVarSizeWithDummy[q10 + 1] \/ s_ExplicitVarSizeWithDummy[q10] = 5 - | q10 : int(1..3)]), - and([s_ExplicitVarSizeWithDummy[q11] = 5 -> s_ExplicitVarSizeWithDummy[q11 + 1] = 5 | q11 : int(1..3)]), - and([s_ExplicitVarSizeWithDummy[q15] != 5 -> s_Occurrence[s_ExplicitVarSizeWithDummy[q15]] | q15 : int(1..4)]), - and([s_Occurrence[q16] -> - or([s_ExplicitVarSizeWithDummy[q18] != 5 /\ s_ExplicitVarSizeWithDummy[q18] = q16 | q18 : int(1..4)]) - | q16 : int(1..4)]), - and([s_ExplicitVarSizeWithDummy[q20] != 5 -> - or([q22 <= s_ExplicitVarSizeWithMarker_Marker /\ - s_ExplicitVarSizeWithMarker_Values[q22] = s_ExplicitVarSizeWithDummy[q20] - | q22 : int(1..4)]) - | q20 : int(1..4)]), - and([q24 <= s_ExplicitVarSizeWithMarker_Marker -> - or([s_ExplicitVarSizeWithDummy[q26] != 5 /\ - s_ExplicitVarSizeWithDummy[q26] = s_ExplicitVarSizeWithMarker_Values[q24] - | q26 : int(1..4)]) - | q24 : int(1..4)]) - diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_3_3-solution000001.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_3_3-solution000001.solution deleted file mode 100644 index 8b4ecbb66d..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_1_3_3-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 3} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_3_3-solution000002.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_3_3-solution000002.solution deleted file mode 100644 index 159a613983..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_1_3_3-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {2, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_3_3-solution000003.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_3_3-solution000003.solution deleted file mode 100644 index 5963aac565..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_1_3_3-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 3} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_3_3-solution000004.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_3_3-solution000004.solution deleted file mode 100644 index 6eeacc9727..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_1_3_3-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_3_3-solution000005.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_3_3-solution000005.solution deleted file mode 100644 index 560dd0f2f7..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_1_3_3-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 3, 4} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_3_3-solution000006.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_3_3-solution000006.solution deleted file mode 100644 index 40f3fd5c8f..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_1_3_3-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {2, 3, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_3_3-solution000007.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_3_3-solution000007.solution deleted file mode 100644 index bd956f44e3..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_1_3_3-solution000007.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 3, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_3_3.eprime b/tests/exhaustive/basic/comprehension_letting/expected/model_1_3_3.eprime deleted file mode 100644 index 52358293ff..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_1_3_3.eprime +++ /dev/null @@ -1,74 +0,0 @@ -language ESSENCE' 1.0 - -find s_Occurrence: matrix indexed by [int(1..4)] of bool -find s_ExplicitVarSizeWithMarker_Marker: int(0..4) -find s_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -letting let1 be -100 -find x: int(-100..100) -find conjure_aux1: int(-16..3) -branching on [s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithMarker_Values, s_Occurrence, x] -such that - and([and([s_Occurrence[i], q10 <= s_ExplicitVarSizeWithMarker_Marker, i != s_ExplicitVarSizeWithMarker_Values[q10], - allDiff([i + s_ExplicitVarSizeWithMarker_Values[q10], i * s_ExplicitVarSizeWithMarker_Values[q10], - i / s_ExplicitVarSizeWithMarker_Values[q10]; - int(1..3)]), - (i - s_ExplicitVarSizeWithMarker_Values[q10]) % 2 = 0; - int(1..5)]) - -> - min([i + s_ExplicitVarSizeWithMarker_Values[q10], i - s_ExplicitVarSizeWithMarker_Values[q10], - i * s_ExplicitVarSizeWithMarker_Values[q10], i / s_ExplicitVarSizeWithMarker_Values[q10]; - int(1..4)]) - <= conjure_aux1 - | i : int(1..4), q10 : int(1..4)]), - sum([toInt(and([s_Occurrence[i], q10 <= s_ExplicitVarSizeWithMarker_Marker, - i != s_ExplicitVarSizeWithMarker_Values[q10], - allDiff([i + s_ExplicitVarSizeWithMarker_Values[q10], i * s_ExplicitVarSizeWithMarker_Values[q10], - i / s_ExplicitVarSizeWithMarker_Values[q10]; - int(1..3)]), - (i - s_ExplicitVarSizeWithMarker_Values[q10]) % 2 = 0; - int(1..5)])) - | i : int(1..4), q10 : int(1..4)]) - > 0 - -> - or([and([s_Occurrence[i], q10 <= s_ExplicitVarSizeWithMarker_Marker, i != s_ExplicitVarSizeWithMarker_Values[q10], - allDiff([i + s_ExplicitVarSizeWithMarker_Values[q10], i * s_ExplicitVarSizeWithMarker_Values[q10], - i / s_ExplicitVarSizeWithMarker_Values[q10]; - int(1..3)]), - (i - s_ExplicitVarSizeWithMarker_Values[q10]) % 2 = 0; - int(1..5)]) - /\ - min([i + s_ExplicitVarSizeWithMarker_Values[q10], i - s_ExplicitVarSizeWithMarker_Values[q10], - i * s_ExplicitVarSizeWithMarker_Values[q10], i / s_ExplicitVarSizeWithMarker_Values[q10]; - int(1..4)]) - = conjure_aux1 - | i : int(1..4), q10 : int(1..4)]), - sum([toInt(and([s_Occurrence[i], q10 <= s_ExplicitVarSizeWithMarker_Marker, - i != s_ExplicitVarSizeWithMarker_Values[q10], - allDiff([i + s_ExplicitVarSizeWithMarker_Values[q10], i * s_ExplicitVarSizeWithMarker_Values[q10], - i / s_ExplicitVarSizeWithMarker_Values[q10]; - int(1..3)]), - (i - s_ExplicitVarSizeWithMarker_Values[q10]) % 2 = 0; - int(1..5)])) - | i : int(1..4), q10 : int(1..4)]) - = 0 - -> conjure_aux1 = -16, - x = conjure_aux1, - sum([toInt(and([s_Occurrence[i], q10 <= s_ExplicitVarSizeWithMarker_Marker, - i != s_ExplicitVarSizeWithMarker_Values[q10], - allDiff([i + s_ExplicitVarSizeWithMarker_Values[q10], i * s_ExplicitVarSizeWithMarker_Values[q10], - i / s_ExplicitVarSizeWithMarker_Values[q10]; - int(1..3)]), - (i - s_ExplicitVarSizeWithMarker_Values[q10]) % 2 = 0; - int(1..5)])) - | i : int(1..4), q10 : int(1..4)]) - > 0, - and([q2 + 1 <= s_ExplicitVarSizeWithMarker_Marker -> - s_ExplicitVarSizeWithMarker_Values[q2] < s_ExplicitVarSizeWithMarker_Values[q2 + 1] - | q2 : int(1..3)]), - and([q3 > s_ExplicitVarSizeWithMarker_Marker -> s_ExplicitVarSizeWithMarker_Values[q3] = 1 | q3 : int(1..4)]), - and([q6 <= s_ExplicitVarSizeWithMarker_Marker -> s_Occurrence[s_ExplicitVarSizeWithMarker_Values[q6]] - | q6 : int(1..4)]), - and([s_Occurrence[q7] -> - or([q9 <= s_ExplicitVarSizeWithMarker_Marker /\ s_ExplicitVarSizeWithMarker_Values[q9] = q7 | q9 : int(1..4)]) - | q7 : int(1..4)]) - diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_3_4-solution000001.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_3_4-solution000001.solution deleted file mode 100644 index 8b4ecbb66d..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_1_3_4-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 3} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_3_4-solution000002.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_3_4-solution000002.solution deleted file mode 100644 index 159a613983..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_1_3_4-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {2, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_3_4-solution000003.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_3_4-solution000003.solution deleted file mode 100644 index 5963aac565..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_1_3_4-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 3} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_3_4-solution000004.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_3_4-solution000004.solution deleted file mode 100644 index 6eeacc9727..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_1_3_4-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_3_4-solution000005.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_3_4-solution000005.solution deleted file mode 100644 index 560dd0f2f7..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_1_3_4-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 3, 4} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_3_4-solution000006.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_3_4-solution000006.solution deleted file mode 100644 index 40f3fd5c8f..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_1_3_4-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {2, 3, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_3_4-solution000007.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_3_4-solution000007.solution deleted file mode 100644 index bd956f44e3..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_1_3_4-solution000007.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 3, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_3_4.eprime b/tests/exhaustive/basic/comprehension_letting/expected/model_1_3_4.eprime deleted file mode 100644 index 986b4a8cc2..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_1_3_4.eprime +++ /dev/null @@ -1,99 +0,0 @@ -language ESSENCE' 1.0 - -find s_Occurrence: matrix indexed by [int(1..4)] of bool -find s_ExplicitVarSizeWithMarker_Marker: int(0..4) -find s_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -find s_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find s_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -letting let1 be -100 -find x: int(-100..100) -find conjure_aux1: int(-16..3) -branching on - [s_ExplicitVarSizeWithFlags_Flags, s_ExplicitVarSizeWithFlags_Values, s_Occurrence, - s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithMarker_Values, x] -such that - and([and([s_Occurrence[i], q28 <= s_ExplicitVarSizeWithMarker_Marker, i != s_ExplicitVarSizeWithMarker_Values[q28], - allDiff([i + s_ExplicitVarSizeWithMarker_Values[q28], i * s_ExplicitVarSizeWithMarker_Values[q28], - i / s_ExplicitVarSizeWithMarker_Values[q28]; - int(1..3)]), - (i - s_ExplicitVarSizeWithMarker_Values[q28]) % 2 = 0; - int(1..5)]) - -> - min([i + s_ExplicitVarSizeWithMarker_Values[q28], i - s_ExplicitVarSizeWithMarker_Values[q28], - i * s_ExplicitVarSizeWithMarker_Values[q28], i / s_ExplicitVarSizeWithMarker_Values[q28]; - int(1..4)]) - <= conjure_aux1 - | i : int(1..4), q28 : int(1..4)]), - sum([toInt(and([s_Occurrence[i], q28 <= s_ExplicitVarSizeWithMarker_Marker, - i != s_ExplicitVarSizeWithMarker_Values[q28], - allDiff([i + s_ExplicitVarSizeWithMarker_Values[q28], i * s_ExplicitVarSizeWithMarker_Values[q28], - i / s_ExplicitVarSizeWithMarker_Values[q28]; - int(1..3)]), - (i - s_ExplicitVarSizeWithMarker_Values[q28]) % 2 = 0; - int(1..5)])) - | i : int(1..4), q28 : int(1..4)]) - > 0 - -> - or([and([s_Occurrence[i], q28 <= s_ExplicitVarSizeWithMarker_Marker, i != s_ExplicitVarSizeWithMarker_Values[q28], - allDiff([i + s_ExplicitVarSizeWithMarker_Values[q28], i * s_ExplicitVarSizeWithMarker_Values[q28], - i / s_ExplicitVarSizeWithMarker_Values[q28]; - int(1..3)]), - (i - s_ExplicitVarSizeWithMarker_Values[q28]) % 2 = 0; - int(1..5)]) - /\ - min([i + s_ExplicitVarSizeWithMarker_Values[q28], i - s_ExplicitVarSizeWithMarker_Values[q28], - i * s_ExplicitVarSizeWithMarker_Values[q28], i / s_ExplicitVarSizeWithMarker_Values[q28]; - int(1..4)]) - = conjure_aux1 - | i : int(1..4), q28 : int(1..4)]), - sum([toInt(and([s_Occurrence[i], q28 <= s_ExplicitVarSizeWithMarker_Marker, - i != s_ExplicitVarSizeWithMarker_Values[q28], - allDiff([i + s_ExplicitVarSizeWithMarker_Values[q28], i * s_ExplicitVarSizeWithMarker_Values[q28], - i / s_ExplicitVarSizeWithMarker_Values[q28]; - int(1..3)]), - (i - s_ExplicitVarSizeWithMarker_Values[q28]) % 2 = 0; - int(1..5)])) - | i : int(1..4), q28 : int(1..4)]) - = 0 - -> conjure_aux1 = -16, - x = conjure_aux1, - sum([toInt(and([s_Occurrence[i], q28 <= s_ExplicitVarSizeWithMarker_Marker, - i != s_ExplicitVarSizeWithMarker_Values[q28], - allDiff([i + s_ExplicitVarSizeWithMarker_Values[q28], i * s_ExplicitVarSizeWithMarker_Values[q28], - i / s_ExplicitVarSizeWithMarker_Values[q28]; - int(1..3)]), - (i - s_ExplicitVarSizeWithMarker_Values[q28]) % 2 = 0; - int(1..5)])) - | i : int(1..4), q28 : int(1..4)]) - > 0, - and([q2 + 1 <= s_ExplicitVarSizeWithMarker_Marker -> - s_ExplicitVarSizeWithMarker_Values[q2] < s_ExplicitVarSizeWithMarker_Values[q2 + 1] - | q2 : int(1..3)]), - and([q3 > s_ExplicitVarSizeWithMarker_Marker -> s_ExplicitVarSizeWithMarker_Values[q3] = 1 | q3 : int(1..4)]), - and([q6 <= s_ExplicitVarSizeWithMarker_Marker -> s_Occurrence[s_ExplicitVarSizeWithMarker_Values[q6]] - | q6 : int(1..4)]), - and([s_Occurrence[q7] -> - or([q9 <= s_ExplicitVarSizeWithMarker_Marker /\ s_ExplicitVarSizeWithMarker_Values[q9] = q7 | q9 : int(1..4)]) - | q7 : int(1..4)]), - and([s_ExplicitVarSizeWithFlags_Flags[q10 + 1] -> - s_ExplicitVarSizeWithFlags_Values[q10] < s_ExplicitVarSizeWithFlags_Values[q10 + 1] - | q10 : int(1..3)]), - and([s_ExplicitVarSizeWithFlags_Flags[q11] = false -> s_ExplicitVarSizeWithFlags_Values[q11] = 1 - | q11 : int(1..4)]), - and([s_ExplicitVarSizeWithFlags_Flags[q12 + 1] -> s_ExplicitVarSizeWithFlags_Flags[q12] | q12 : int(1..3)]), - and([s_ExplicitVarSizeWithFlags_Flags[q16] -> s_Occurrence[s_ExplicitVarSizeWithFlags_Values[q16]] - | q16 : int(1..4)]), - and([s_Occurrence[q17] -> - or([s_ExplicitVarSizeWithFlags_Flags[q19] /\ s_ExplicitVarSizeWithFlags_Values[q19] = q17 | q19 : int(1..4)]) - | q17 : int(1..4)]), - and([s_ExplicitVarSizeWithFlags_Flags[q21] -> - or([q23 <= s_ExplicitVarSizeWithMarker_Marker /\ - s_ExplicitVarSizeWithMarker_Values[q23] = s_ExplicitVarSizeWithFlags_Values[q21] - | q23 : int(1..4)]) - | q21 : int(1..4)]), - and([q25 <= s_ExplicitVarSizeWithMarker_Marker -> - or([s_ExplicitVarSizeWithFlags_Flags[q27] /\ - s_ExplicitVarSizeWithFlags_Values[q27] = s_ExplicitVarSizeWithMarker_Values[q25] - | q27 : int(1..4)]) - | q25 : int(1..4)]) - diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_4_1-solution000001.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_4_1-solution000001.solution deleted file mode 100644 index 8b4ecbb66d..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_1_4_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 3} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_4_1-solution000002.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_4_1-solution000002.solution deleted file mode 100644 index 159a613983..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_1_4_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {2, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_4_1-solution000003.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_4_1-solution000003.solution deleted file mode 100644 index 5963aac565..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_1_4_1-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 3} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_4_1-solution000004.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_4_1-solution000004.solution deleted file mode 100644 index 6eeacc9727..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_1_4_1-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_4_1-solution000005.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_4_1-solution000005.solution deleted file mode 100644 index 560dd0f2f7..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_1_4_1-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 3, 4} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_4_1-solution000006.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_4_1-solution000006.solution deleted file mode 100644 index 40f3fd5c8f..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_1_4_1-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {2, 3, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_4_1-solution000007.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_4_1-solution000007.solution deleted file mode 100644 index bd956f44e3..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_1_4_1-solution000007.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 3, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_4_1.eprime b/tests/exhaustive/basic/comprehension_letting/expected/model_1_4_1.eprime deleted file mode 100644 index 2c748ac8af..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_1_4_1.eprime +++ /dev/null @@ -1,71 +0,0 @@ -language ESSENCE' 1.0 - -find s_Occurrence: matrix indexed by [int(1..4)] of bool -find s_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find s_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -letting let1 be -100 -find x: int(-100..100) -find conjure_aux1: int(-16..3) -branching on [s_ExplicitVarSizeWithFlags_Flags, s_ExplicitVarSizeWithFlags_Values, s_Occurrence, x] -such that - and([and([s_Occurrence[i], s_ExplicitVarSizeWithFlags_Flags[q12], i != s_ExplicitVarSizeWithFlags_Values[q12], - allDiff([i + s_ExplicitVarSizeWithFlags_Values[q12], i * s_ExplicitVarSizeWithFlags_Values[q12], - i / s_ExplicitVarSizeWithFlags_Values[q12]; - int(1..3)]), - (i - s_ExplicitVarSizeWithFlags_Values[q12]) % 2 = 0; - int(1..5)]) - -> - min([i + s_ExplicitVarSizeWithFlags_Values[q12], i - s_ExplicitVarSizeWithFlags_Values[q12], - i * s_ExplicitVarSizeWithFlags_Values[q12], i / s_ExplicitVarSizeWithFlags_Values[q12]; - int(1..4)]) - <= conjure_aux1 - | i : int(1..4), q12 : int(1..4)]), - sum([toInt(and([s_Occurrence[i], s_ExplicitVarSizeWithFlags_Flags[q12], i != s_ExplicitVarSizeWithFlags_Values[q12], - allDiff([i + s_ExplicitVarSizeWithFlags_Values[q12], i * s_ExplicitVarSizeWithFlags_Values[q12], - i / s_ExplicitVarSizeWithFlags_Values[q12]; - int(1..3)]), - (i - s_ExplicitVarSizeWithFlags_Values[q12]) % 2 = 0; - int(1..5)])) - | i : int(1..4), q12 : int(1..4)]) - > 0 - -> - or([and([s_Occurrence[i], s_ExplicitVarSizeWithFlags_Flags[q12], i != s_ExplicitVarSizeWithFlags_Values[q12], - allDiff([i + s_ExplicitVarSizeWithFlags_Values[q12], i * s_ExplicitVarSizeWithFlags_Values[q12], - i / s_ExplicitVarSizeWithFlags_Values[q12]; - int(1..3)]), - (i - s_ExplicitVarSizeWithFlags_Values[q12]) % 2 = 0; - int(1..5)]) - /\ - min([i + s_ExplicitVarSizeWithFlags_Values[q12], i - s_ExplicitVarSizeWithFlags_Values[q12], - i * s_ExplicitVarSizeWithFlags_Values[q12], i / s_ExplicitVarSizeWithFlags_Values[q12]; - int(1..4)]) - = conjure_aux1 - | i : int(1..4), q12 : int(1..4)]), - sum([toInt(and([s_Occurrence[i], s_ExplicitVarSizeWithFlags_Flags[q12], i != s_ExplicitVarSizeWithFlags_Values[q12], - allDiff([i + s_ExplicitVarSizeWithFlags_Values[q12], i * s_ExplicitVarSizeWithFlags_Values[q12], - i / s_ExplicitVarSizeWithFlags_Values[q12]; - int(1..3)]), - (i - s_ExplicitVarSizeWithFlags_Values[q12]) % 2 = 0; - int(1..5)])) - | i : int(1..4), q12 : int(1..4)]) - = 0 - -> conjure_aux1 = -16, - x = conjure_aux1, - sum([toInt(and([s_Occurrence[i], s_ExplicitVarSizeWithFlags_Flags[q12], i != s_ExplicitVarSizeWithFlags_Values[q12], - allDiff([i + s_ExplicitVarSizeWithFlags_Values[q12], i * s_ExplicitVarSizeWithFlags_Values[q12], - i / s_ExplicitVarSizeWithFlags_Values[q12]; - int(1..3)]), - (i - s_ExplicitVarSizeWithFlags_Values[q12]) % 2 = 0; - int(1..5)])) - | i : int(1..4), q12 : int(1..4)]) - > 0, - and([s_ExplicitVarSizeWithFlags_Flags[q2 + 1] -> - s_ExplicitVarSizeWithFlags_Values[q2] < s_ExplicitVarSizeWithFlags_Values[q2 + 1] - | q2 : int(1..3)]), - and([s_ExplicitVarSizeWithFlags_Flags[q3] = false -> s_ExplicitVarSizeWithFlags_Values[q3] = 1 | q3 : int(1..4)]), - and([s_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> s_ExplicitVarSizeWithFlags_Flags[q4] | q4 : int(1..3)]), - and([s_ExplicitVarSizeWithFlags_Flags[q8] -> s_Occurrence[s_ExplicitVarSizeWithFlags_Values[q8]] | q8 : int(1..4)]), - and([s_Occurrence[q9] -> - or([s_ExplicitVarSizeWithFlags_Flags[q11] /\ s_ExplicitVarSizeWithFlags_Values[q11] = q9 | q11 : int(1..4)]) - | q9 : int(1..4)]) - diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_4_2-solution000001.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_4_2-solution000001.solution deleted file mode 100644 index bd956f44e3..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_1_4_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 3, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_4_2-solution000002.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_4_2-solution000002.solution deleted file mode 100644 index 5963aac565..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_1_4_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 3} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_4_2-solution000003.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_4_2-solution000003.solution deleted file mode 100644 index 6eeacc9727..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_1_4_2-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_4_2-solution000004.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_4_2-solution000004.solution deleted file mode 100644 index 560dd0f2f7..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_1_4_2-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 3, 4} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_4_2-solution000005.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_4_2-solution000005.solution deleted file mode 100644 index 8b4ecbb66d..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_1_4_2-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 3} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_4_2-solution000006.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_4_2-solution000006.solution deleted file mode 100644 index 40f3fd5c8f..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_1_4_2-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {2, 3, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_4_2-solution000007.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_4_2-solution000007.solution deleted file mode 100644 index 159a613983..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_1_4_2-solution000007.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {2, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_4_2.eprime b/tests/exhaustive/basic/comprehension_letting/expected/model_1_4_2.eprime deleted file mode 100644 index 08c34a7a31..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_1_4_2.eprime +++ /dev/null @@ -1,90 +0,0 @@ -language ESSENCE' 1.0 - -find s_Occurrence: matrix indexed by [int(1..4)] of bool -find s_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find s_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -find s_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -letting let1 be -100 -find x: int(-100..100) -find conjure_aux1: int(-16..3) -branching on - [s_ExplicitVarSizeWithDummy, s_Occurrence, s_ExplicitVarSizeWithFlags_Flags, s_ExplicitVarSizeWithFlags_Values, x] -such that - and([and([s_Occurrence[i], s_ExplicitVarSizeWithFlags_Flags[q29], i != s_ExplicitVarSizeWithFlags_Values[q29], - allDiff([i + s_ExplicitVarSizeWithFlags_Values[q29], i * s_ExplicitVarSizeWithFlags_Values[q29], - i / s_ExplicitVarSizeWithFlags_Values[q29]; - int(1..3)]), - (i - s_ExplicitVarSizeWithFlags_Values[q29]) % 2 = 0; - int(1..5)]) - -> - min([i + s_ExplicitVarSizeWithFlags_Values[q29], i - s_ExplicitVarSizeWithFlags_Values[q29], - i * s_ExplicitVarSizeWithFlags_Values[q29], i / s_ExplicitVarSizeWithFlags_Values[q29]; - int(1..4)]) - <= conjure_aux1 - | i : int(1..4), q29 : int(1..4)]), - sum([toInt(and([s_Occurrence[i], s_ExplicitVarSizeWithFlags_Flags[q29], i != s_ExplicitVarSizeWithFlags_Values[q29], - allDiff([i + s_ExplicitVarSizeWithFlags_Values[q29], i * s_ExplicitVarSizeWithFlags_Values[q29], - i / s_ExplicitVarSizeWithFlags_Values[q29]; - int(1..3)]), - (i - s_ExplicitVarSizeWithFlags_Values[q29]) % 2 = 0; - int(1..5)])) - | i : int(1..4), q29 : int(1..4)]) - > 0 - -> - or([and([s_Occurrence[i], s_ExplicitVarSizeWithFlags_Flags[q29], i != s_ExplicitVarSizeWithFlags_Values[q29], - allDiff([i + s_ExplicitVarSizeWithFlags_Values[q29], i * s_ExplicitVarSizeWithFlags_Values[q29], - i / s_ExplicitVarSizeWithFlags_Values[q29]; - int(1..3)]), - (i - s_ExplicitVarSizeWithFlags_Values[q29]) % 2 = 0; - int(1..5)]) - /\ - min([i + s_ExplicitVarSizeWithFlags_Values[q29], i - s_ExplicitVarSizeWithFlags_Values[q29], - i * s_ExplicitVarSizeWithFlags_Values[q29], i / s_ExplicitVarSizeWithFlags_Values[q29]; - int(1..4)]) - = conjure_aux1 - | i : int(1..4), q29 : int(1..4)]), - sum([toInt(and([s_Occurrence[i], s_ExplicitVarSizeWithFlags_Flags[q29], i != s_ExplicitVarSizeWithFlags_Values[q29], - allDiff([i + s_ExplicitVarSizeWithFlags_Values[q29], i * s_ExplicitVarSizeWithFlags_Values[q29], - i / s_ExplicitVarSizeWithFlags_Values[q29]; - int(1..3)]), - (i - s_ExplicitVarSizeWithFlags_Values[q29]) % 2 = 0; - int(1..5)])) - | i : int(1..4), q29 : int(1..4)]) - = 0 - -> conjure_aux1 = -16, - x = conjure_aux1, - sum([toInt(and([s_Occurrence[i], s_ExplicitVarSizeWithFlags_Flags[q29], i != s_ExplicitVarSizeWithFlags_Values[q29], - allDiff([i + s_ExplicitVarSizeWithFlags_Values[q29], i * s_ExplicitVarSizeWithFlags_Values[q29], - i / s_ExplicitVarSizeWithFlags_Values[q29]; - int(1..3)]), - (i - s_ExplicitVarSizeWithFlags_Values[q29]) % 2 = 0; - int(1..5)])) - | i : int(1..4), q29 : int(1..4)]) - > 0, - and([s_ExplicitVarSizeWithFlags_Flags[q2 + 1] -> - s_ExplicitVarSizeWithFlags_Values[q2] < s_ExplicitVarSizeWithFlags_Values[q2 + 1] - | q2 : int(1..3)]), - and([s_ExplicitVarSizeWithFlags_Flags[q3] = false -> s_ExplicitVarSizeWithFlags_Values[q3] = 1 | q3 : int(1..4)]), - and([s_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> s_ExplicitVarSizeWithFlags_Flags[q4] | q4 : int(1..3)]), - and([s_ExplicitVarSizeWithFlags_Flags[q8] -> s_Occurrence[s_ExplicitVarSizeWithFlags_Values[q8]] | q8 : int(1..4)]), - and([s_Occurrence[q9] -> - or([s_ExplicitVarSizeWithFlags_Flags[q11] /\ s_ExplicitVarSizeWithFlags_Values[q11] = q9 | q11 : int(1..4)]) - | q9 : int(1..4)]), - and([s_ExplicitVarSizeWithDummy[q12] < s_ExplicitVarSizeWithDummy[q12 + 1] \/ s_ExplicitVarSizeWithDummy[q12] = 5 - | q12 : int(1..3)]), - and([s_ExplicitVarSizeWithDummy[q13] = 5 -> s_ExplicitVarSizeWithDummy[q13 + 1] = 5 | q13 : int(1..3)]), - and([s_ExplicitVarSizeWithDummy[q17] != 5 -> s_Occurrence[s_ExplicitVarSizeWithDummy[q17]] | q17 : int(1..4)]), - and([s_Occurrence[q18] -> - or([s_ExplicitVarSizeWithDummy[q20] != 5 /\ s_ExplicitVarSizeWithDummy[q20] = q18 | q20 : int(1..4)]) - | q18 : int(1..4)]), - and([s_ExplicitVarSizeWithDummy[q22] != 5 -> - or([s_ExplicitVarSizeWithFlags_Flags[q24] /\ - s_ExplicitVarSizeWithFlags_Values[q24] = s_ExplicitVarSizeWithDummy[q22] - | q24 : int(1..4)]) - | q22 : int(1..4)]), - and([s_ExplicitVarSizeWithFlags_Flags[q26] -> - or([s_ExplicitVarSizeWithDummy[q28] != 5 /\ - s_ExplicitVarSizeWithDummy[q28] = s_ExplicitVarSizeWithFlags_Values[q26] - | q28 : int(1..4)]) - | q26 : int(1..4)]) - diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_4_3-solution000001.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_4_3-solution000001.solution deleted file mode 100644 index 8b4ecbb66d..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_1_4_3-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 3} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_4_3-solution000002.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_4_3-solution000002.solution deleted file mode 100644 index 159a613983..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_1_4_3-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {2, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_4_3-solution000003.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_4_3-solution000003.solution deleted file mode 100644 index 5963aac565..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_1_4_3-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 3} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_4_3-solution000004.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_4_3-solution000004.solution deleted file mode 100644 index 6eeacc9727..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_1_4_3-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_4_3-solution000005.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_4_3-solution000005.solution deleted file mode 100644 index 560dd0f2f7..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_1_4_3-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 3, 4} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_4_3-solution000006.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_4_3-solution000006.solution deleted file mode 100644 index 40f3fd5c8f..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_1_4_3-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {2, 3, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_4_3-solution000007.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_4_3-solution000007.solution deleted file mode 100644 index bd956f44e3..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_1_4_3-solution000007.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 3, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_4_3.eprime b/tests/exhaustive/basic/comprehension_letting/expected/model_1_4_3.eprime deleted file mode 100644 index c3e1894ef9..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_1_4_3.eprime +++ /dev/null @@ -1,95 +0,0 @@ -language ESSENCE' 1.0 - -find s_Occurrence: matrix indexed by [int(1..4)] of bool -find s_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find s_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -find s_ExplicitVarSizeWithMarker_Marker: int(0..4) -find s_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -letting let1 be -100 -find x: int(-100..100) -find conjure_aux1: int(-16..3) -branching on - [s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithMarker_Values, s_Occurrence, - s_ExplicitVarSizeWithFlags_Flags, s_ExplicitVarSizeWithFlags_Values, x] -such that - and([and([s_Occurrence[i], s_ExplicitVarSizeWithFlags_Flags[q28], i != s_ExplicitVarSizeWithFlags_Values[q28], - allDiff([i + s_ExplicitVarSizeWithFlags_Values[q28], i * s_ExplicitVarSizeWithFlags_Values[q28], - i / s_ExplicitVarSizeWithFlags_Values[q28]; - int(1..3)]), - (i - s_ExplicitVarSizeWithFlags_Values[q28]) % 2 = 0; - int(1..5)]) - -> - min([i + s_ExplicitVarSizeWithFlags_Values[q28], i - s_ExplicitVarSizeWithFlags_Values[q28], - i * s_ExplicitVarSizeWithFlags_Values[q28], i / s_ExplicitVarSizeWithFlags_Values[q28]; - int(1..4)]) - <= conjure_aux1 - | i : int(1..4), q28 : int(1..4)]), - sum([toInt(and([s_Occurrence[i], s_ExplicitVarSizeWithFlags_Flags[q28], i != s_ExplicitVarSizeWithFlags_Values[q28], - allDiff([i + s_ExplicitVarSizeWithFlags_Values[q28], i * s_ExplicitVarSizeWithFlags_Values[q28], - i / s_ExplicitVarSizeWithFlags_Values[q28]; - int(1..3)]), - (i - s_ExplicitVarSizeWithFlags_Values[q28]) % 2 = 0; - int(1..5)])) - | i : int(1..4), q28 : int(1..4)]) - > 0 - -> - or([and([s_Occurrence[i], s_ExplicitVarSizeWithFlags_Flags[q28], i != s_ExplicitVarSizeWithFlags_Values[q28], - allDiff([i + s_ExplicitVarSizeWithFlags_Values[q28], i * s_ExplicitVarSizeWithFlags_Values[q28], - i / s_ExplicitVarSizeWithFlags_Values[q28]; - int(1..3)]), - (i - s_ExplicitVarSizeWithFlags_Values[q28]) % 2 = 0; - int(1..5)]) - /\ - min([i + s_ExplicitVarSizeWithFlags_Values[q28], i - s_ExplicitVarSizeWithFlags_Values[q28], - i * s_ExplicitVarSizeWithFlags_Values[q28], i / s_ExplicitVarSizeWithFlags_Values[q28]; - int(1..4)]) - = conjure_aux1 - | i : int(1..4), q28 : int(1..4)]), - sum([toInt(and([s_Occurrence[i], s_ExplicitVarSizeWithFlags_Flags[q28], i != s_ExplicitVarSizeWithFlags_Values[q28], - allDiff([i + s_ExplicitVarSizeWithFlags_Values[q28], i * s_ExplicitVarSizeWithFlags_Values[q28], - i / s_ExplicitVarSizeWithFlags_Values[q28]; - int(1..3)]), - (i - s_ExplicitVarSizeWithFlags_Values[q28]) % 2 = 0; - int(1..5)])) - | i : int(1..4), q28 : int(1..4)]) - = 0 - -> conjure_aux1 = -16, - x = conjure_aux1, - sum([toInt(and([s_Occurrence[i], s_ExplicitVarSizeWithFlags_Flags[q28], i != s_ExplicitVarSizeWithFlags_Values[q28], - allDiff([i + s_ExplicitVarSizeWithFlags_Values[q28], i * s_ExplicitVarSizeWithFlags_Values[q28], - i / s_ExplicitVarSizeWithFlags_Values[q28]; - int(1..3)]), - (i - s_ExplicitVarSizeWithFlags_Values[q28]) % 2 = 0; - int(1..5)])) - | i : int(1..4), q28 : int(1..4)]) - > 0, - and([s_ExplicitVarSizeWithFlags_Flags[q2 + 1] -> - s_ExplicitVarSizeWithFlags_Values[q2] < s_ExplicitVarSizeWithFlags_Values[q2 + 1] - | q2 : int(1..3)]), - and([s_ExplicitVarSizeWithFlags_Flags[q3] = false -> s_ExplicitVarSizeWithFlags_Values[q3] = 1 | q3 : int(1..4)]), - and([s_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> s_ExplicitVarSizeWithFlags_Flags[q4] | q4 : int(1..3)]), - and([s_ExplicitVarSizeWithFlags_Flags[q8] -> s_Occurrence[s_ExplicitVarSizeWithFlags_Values[q8]] | q8 : int(1..4)]), - and([s_Occurrence[q9] -> - or([s_ExplicitVarSizeWithFlags_Flags[q11] /\ s_ExplicitVarSizeWithFlags_Values[q11] = q9 | q11 : int(1..4)]) - | q9 : int(1..4)]), - and([q12 + 1 <= s_ExplicitVarSizeWithMarker_Marker -> - s_ExplicitVarSizeWithMarker_Values[q12] < s_ExplicitVarSizeWithMarker_Values[q12 + 1] - | q12 : int(1..3)]), - and([q13 > s_ExplicitVarSizeWithMarker_Marker -> s_ExplicitVarSizeWithMarker_Values[q13] = 1 | q13 : int(1..4)]), - and([q16 <= s_ExplicitVarSizeWithMarker_Marker -> s_Occurrence[s_ExplicitVarSizeWithMarker_Values[q16]] - | q16 : int(1..4)]), - and([s_Occurrence[q17] -> - or([q19 <= s_ExplicitVarSizeWithMarker_Marker /\ s_ExplicitVarSizeWithMarker_Values[q19] = q17 - | q19 : int(1..4)]) - | q17 : int(1..4)]), - and([q21 <= s_ExplicitVarSizeWithMarker_Marker -> - or([s_ExplicitVarSizeWithFlags_Flags[q23] /\ - s_ExplicitVarSizeWithFlags_Values[q23] = s_ExplicitVarSizeWithMarker_Values[q21] - | q23 : int(1..4)]) - | q21 : int(1..4)]), - and([s_ExplicitVarSizeWithFlags_Flags[q25] -> - or([q27 <= s_ExplicitVarSizeWithMarker_Marker /\ - s_ExplicitVarSizeWithMarker_Values[q27] = s_ExplicitVarSizeWithFlags_Values[q25] - | q27 : int(1..4)]) - | q25 : int(1..4)]) - diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_4_4-solution000001.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_4_4-solution000001.solution deleted file mode 100644 index 8b4ecbb66d..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_1_4_4-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 3} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_4_4-solution000002.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_4_4-solution000002.solution deleted file mode 100644 index 159a613983..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_1_4_4-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {2, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_4_4-solution000003.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_4_4-solution000003.solution deleted file mode 100644 index 5963aac565..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_1_4_4-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 3} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_4_4-solution000004.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_4_4-solution000004.solution deleted file mode 100644 index 6eeacc9727..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_1_4_4-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_4_4-solution000005.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_4_4-solution000005.solution deleted file mode 100644 index 560dd0f2f7..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_1_4_4-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 3, 4} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_4_4-solution000006.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_4_4-solution000006.solution deleted file mode 100644 index 40f3fd5c8f..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_1_4_4-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {2, 3, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_4_4-solution000007.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_4_4-solution000007.solution deleted file mode 100644 index bd956f44e3..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_1_4_4-solution000007.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 3, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_4_4.eprime b/tests/exhaustive/basic/comprehension_letting/expected/model_1_4_4.eprime deleted file mode 100644 index 2c748ac8af..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_1_4_4.eprime +++ /dev/null @@ -1,71 +0,0 @@ -language ESSENCE' 1.0 - -find s_Occurrence: matrix indexed by [int(1..4)] of bool -find s_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find s_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -letting let1 be -100 -find x: int(-100..100) -find conjure_aux1: int(-16..3) -branching on [s_ExplicitVarSizeWithFlags_Flags, s_ExplicitVarSizeWithFlags_Values, s_Occurrence, x] -such that - and([and([s_Occurrence[i], s_ExplicitVarSizeWithFlags_Flags[q12], i != s_ExplicitVarSizeWithFlags_Values[q12], - allDiff([i + s_ExplicitVarSizeWithFlags_Values[q12], i * s_ExplicitVarSizeWithFlags_Values[q12], - i / s_ExplicitVarSizeWithFlags_Values[q12]; - int(1..3)]), - (i - s_ExplicitVarSizeWithFlags_Values[q12]) % 2 = 0; - int(1..5)]) - -> - min([i + s_ExplicitVarSizeWithFlags_Values[q12], i - s_ExplicitVarSizeWithFlags_Values[q12], - i * s_ExplicitVarSizeWithFlags_Values[q12], i / s_ExplicitVarSizeWithFlags_Values[q12]; - int(1..4)]) - <= conjure_aux1 - | i : int(1..4), q12 : int(1..4)]), - sum([toInt(and([s_Occurrence[i], s_ExplicitVarSizeWithFlags_Flags[q12], i != s_ExplicitVarSizeWithFlags_Values[q12], - allDiff([i + s_ExplicitVarSizeWithFlags_Values[q12], i * s_ExplicitVarSizeWithFlags_Values[q12], - i / s_ExplicitVarSizeWithFlags_Values[q12]; - int(1..3)]), - (i - s_ExplicitVarSizeWithFlags_Values[q12]) % 2 = 0; - int(1..5)])) - | i : int(1..4), q12 : int(1..4)]) - > 0 - -> - or([and([s_Occurrence[i], s_ExplicitVarSizeWithFlags_Flags[q12], i != s_ExplicitVarSizeWithFlags_Values[q12], - allDiff([i + s_ExplicitVarSizeWithFlags_Values[q12], i * s_ExplicitVarSizeWithFlags_Values[q12], - i / s_ExplicitVarSizeWithFlags_Values[q12]; - int(1..3)]), - (i - s_ExplicitVarSizeWithFlags_Values[q12]) % 2 = 0; - int(1..5)]) - /\ - min([i + s_ExplicitVarSizeWithFlags_Values[q12], i - s_ExplicitVarSizeWithFlags_Values[q12], - i * s_ExplicitVarSizeWithFlags_Values[q12], i / s_ExplicitVarSizeWithFlags_Values[q12]; - int(1..4)]) - = conjure_aux1 - | i : int(1..4), q12 : int(1..4)]), - sum([toInt(and([s_Occurrence[i], s_ExplicitVarSizeWithFlags_Flags[q12], i != s_ExplicitVarSizeWithFlags_Values[q12], - allDiff([i + s_ExplicitVarSizeWithFlags_Values[q12], i * s_ExplicitVarSizeWithFlags_Values[q12], - i / s_ExplicitVarSizeWithFlags_Values[q12]; - int(1..3)]), - (i - s_ExplicitVarSizeWithFlags_Values[q12]) % 2 = 0; - int(1..5)])) - | i : int(1..4), q12 : int(1..4)]) - = 0 - -> conjure_aux1 = -16, - x = conjure_aux1, - sum([toInt(and([s_Occurrence[i], s_ExplicitVarSizeWithFlags_Flags[q12], i != s_ExplicitVarSizeWithFlags_Values[q12], - allDiff([i + s_ExplicitVarSizeWithFlags_Values[q12], i * s_ExplicitVarSizeWithFlags_Values[q12], - i / s_ExplicitVarSizeWithFlags_Values[q12]; - int(1..3)]), - (i - s_ExplicitVarSizeWithFlags_Values[q12]) % 2 = 0; - int(1..5)])) - | i : int(1..4), q12 : int(1..4)]) - > 0, - and([s_ExplicitVarSizeWithFlags_Flags[q2 + 1] -> - s_ExplicitVarSizeWithFlags_Values[q2] < s_ExplicitVarSizeWithFlags_Values[q2 + 1] - | q2 : int(1..3)]), - and([s_ExplicitVarSizeWithFlags_Flags[q3] = false -> s_ExplicitVarSizeWithFlags_Values[q3] = 1 | q3 : int(1..4)]), - and([s_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> s_ExplicitVarSizeWithFlags_Flags[q4] | q4 : int(1..3)]), - and([s_ExplicitVarSizeWithFlags_Flags[q8] -> s_Occurrence[s_ExplicitVarSizeWithFlags_Values[q8]] | q8 : int(1..4)]), - and([s_Occurrence[q9] -> - or([s_ExplicitVarSizeWithFlags_Flags[q11] /\ s_ExplicitVarSizeWithFlags_Values[q11] = q9 | q11 : int(1..4)]) - | q9 : int(1..4)]) - diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_1_1-solution000001.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_1_1-solution000001.solution deleted file mode 100644 index 159a613983..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_2_1_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {2, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_1_1-solution000002.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_1_1-solution000002.solution deleted file mode 100644 index 40f3fd5c8f..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_2_1_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {2, 3, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_1_1-solution000003.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_1_1-solution000003.solution deleted file mode 100644 index 8b4ecbb66d..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_2_1_1-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 3} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_1_1-solution000004.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_1_1-solution000004.solution deleted file mode 100644 index 560dd0f2f7..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_2_1_1-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 3, 4} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_1_1-solution000005.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_1_1-solution000005.solution deleted file mode 100644 index 6eeacc9727..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_2_1_1-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_1_1-solution000006.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_1_1-solution000006.solution deleted file mode 100644 index 5963aac565..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_2_1_1-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 3} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_1_1-solution000007.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_1_1-solution000007.solution deleted file mode 100644 index bd956f44e3..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_2_1_1-solution000007.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 3, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_1_1.eprime b/tests/exhaustive/basic/comprehension_letting/expected/model_2_1_1.eprime deleted file mode 100644 index acf6c8641f..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_2_1_1.eprime +++ /dev/null @@ -1,68 +0,0 @@ -language ESSENCE' 1.0 - -find s_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -find s_Occurrence: matrix indexed by [int(1..4)] of bool -letting let1 be -100 -find x: int(-100..100) -find conjure_aux1: int(-20..4) -branching on [s_Occurrence, s_ExplicitVarSizeWithDummy, x] -such that - and([and([s_ExplicitVarSizeWithDummy[q6] != 5, s_Occurrence[j], s_ExplicitVarSizeWithDummy[q6] != j, - allDiff([s_ExplicitVarSizeWithDummy[q6] + j, s_ExplicitVarSizeWithDummy[q6] * j, - s_ExplicitVarSizeWithDummy[q6] / j; - int(1..3)]), - (s_ExplicitVarSizeWithDummy[q6] - j) % 2 = 0; - int(1..5)]) - -> - min([s_ExplicitVarSizeWithDummy[q6] + j, s_ExplicitVarSizeWithDummy[q6] - j, - s_ExplicitVarSizeWithDummy[q6] * j, s_ExplicitVarSizeWithDummy[q6] / j; - int(1..4)]) - <= conjure_aux1 - | q6 : int(1..4), j : int(1..4)]), - sum([toInt(and([s_ExplicitVarSizeWithDummy[q6] != 5, s_Occurrence[j], s_ExplicitVarSizeWithDummy[q6] != j, - allDiff([s_ExplicitVarSizeWithDummy[q6] + j, s_ExplicitVarSizeWithDummy[q6] * j, - s_ExplicitVarSizeWithDummy[q6] / j; - int(1..3)]), - (s_ExplicitVarSizeWithDummy[q6] - j) % 2 = 0; - int(1..5)])) - | q6 : int(1..4), j : int(1..4)]) - > 0 - -> - or([and([s_ExplicitVarSizeWithDummy[q6] != 5, s_Occurrence[j], s_ExplicitVarSizeWithDummy[q6] != j, - allDiff([s_ExplicitVarSizeWithDummy[q6] + j, s_ExplicitVarSizeWithDummy[q6] * j, - s_ExplicitVarSizeWithDummy[q6] / j; - int(1..3)]), - (s_ExplicitVarSizeWithDummy[q6] - j) % 2 = 0; - int(1..5)]) - /\ - min([s_ExplicitVarSizeWithDummy[q6] + j, s_ExplicitVarSizeWithDummy[q6] - j, s_ExplicitVarSizeWithDummy[q6] * j, - s_ExplicitVarSizeWithDummy[q6] / j; - int(1..4)]) - = conjure_aux1 - | q6 : int(1..4), j : int(1..4)]), - sum([toInt(and([s_ExplicitVarSizeWithDummy[q6] != 5, s_Occurrence[j], s_ExplicitVarSizeWithDummy[q6] != j, - allDiff([s_ExplicitVarSizeWithDummy[q6] + j, s_ExplicitVarSizeWithDummy[q6] * j, - s_ExplicitVarSizeWithDummy[q6] / j; - int(1..3)]), - (s_ExplicitVarSizeWithDummy[q6] - j) % 2 = 0; - int(1..5)])) - | q6 : int(1..4), j : int(1..4)]) - = 0 - -> conjure_aux1 = -20, - x = conjure_aux1, - sum([toInt(and([s_ExplicitVarSizeWithDummy[q6] != 5, s_Occurrence[j], s_ExplicitVarSizeWithDummy[q6] != j, - allDiff([s_ExplicitVarSizeWithDummy[q6] + j, s_ExplicitVarSizeWithDummy[q6] * j, - s_ExplicitVarSizeWithDummy[q6] / j; - int(1..3)]), - (s_ExplicitVarSizeWithDummy[q6] - j) % 2 = 0; - int(1..5)])) - | q6 : int(1..4), j : int(1..4)]) - > 0, - and([s_ExplicitVarSizeWithDummy[q1] < s_ExplicitVarSizeWithDummy[q1 + 1] \/ s_ExplicitVarSizeWithDummy[q1] = 5 - | q1 : int(1..3)]), - and([s_ExplicitVarSizeWithDummy[q2] = 5 -> s_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..3)]), - and([s_Occurrence[q28] -> - or([s_ExplicitVarSizeWithDummy[q30] != 5 /\ s_ExplicitVarSizeWithDummy[q30] = q28 | q30 : int(1..4)]) - | q28 : int(1..4)]), - and([s_ExplicitVarSizeWithDummy[q32] != 5 -> s_Occurrence[s_ExplicitVarSizeWithDummy[q32]] | q32 : int(1..4)]) - diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_1_2-solution000001.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_1_2-solution000001.solution deleted file mode 100644 index 159a613983..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_2_1_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {2, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_1_2-solution000002.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_1_2-solution000002.solution deleted file mode 100644 index 40f3fd5c8f..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_2_1_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {2, 3, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_1_2-solution000003.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_1_2-solution000003.solution deleted file mode 100644 index 8b4ecbb66d..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_2_1_2-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 3} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_1_2-solution000004.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_1_2-solution000004.solution deleted file mode 100644 index 560dd0f2f7..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_2_1_2-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 3, 4} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_1_2-solution000005.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_1_2-solution000005.solution deleted file mode 100644 index 6eeacc9727..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_2_1_2-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_1_2-solution000006.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_1_2-solution000006.solution deleted file mode 100644 index 5963aac565..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_2_1_2-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 3} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_1_2-solution000007.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_1_2-solution000007.solution deleted file mode 100644 index bd956f44e3..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_2_1_2-solution000007.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 3, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_1_2.eprime b/tests/exhaustive/basic/comprehension_letting/expected/model_2_1_2.eprime deleted file mode 100644 index acf6c8641f..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_2_1_2.eprime +++ /dev/null @@ -1,68 +0,0 @@ -language ESSENCE' 1.0 - -find s_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -find s_Occurrence: matrix indexed by [int(1..4)] of bool -letting let1 be -100 -find x: int(-100..100) -find conjure_aux1: int(-20..4) -branching on [s_Occurrence, s_ExplicitVarSizeWithDummy, x] -such that - and([and([s_ExplicitVarSizeWithDummy[q6] != 5, s_Occurrence[j], s_ExplicitVarSizeWithDummy[q6] != j, - allDiff([s_ExplicitVarSizeWithDummy[q6] + j, s_ExplicitVarSizeWithDummy[q6] * j, - s_ExplicitVarSizeWithDummy[q6] / j; - int(1..3)]), - (s_ExplicitVarSizeWithDummy[q6] - j) % 2 = 0; - int(1..5)]) - -> - min([s_ExplicitVarSizeWithDummy[q6] + j, s_ExplicitVarSizeWithDummy[q6] - j, - s_ExplicitVarSizeWithDummy[q6] * j, s_ExplicitVarSizeWithDummy[q6] / j; - int(1..4)]) - <= conjure_aux1 - | q6 : int(1..4), j : int(1..4)]), - sum([toInt(and([s_ExplicitVarSizeWithDummy[q6] != 5, s_Occurrence[j], s_ExplicitVarSizeWithDummy[q6] != j, - allDiff([s_ExplicitVarSizeWithDummy[q6] + j, s_ExplicitVarSizeWithDummy[q6] * j, - s_ExplicitVarSizeWithDummy[q6] / j; - int(1..3)]), - (s_ExplicitVarSizeWithDummy[q6] - j) % 2 = 0; - int(1..5)])) - | q6 : int(1..4), j : int(1..4)]) - > 0 - -> - or([and([s_ExplicitVarSizeWithDummy[q6] != 5, s_Occurrence[j], s_ExplicitVarSizeWithDummy[q6] != j, - allDiff([s_ExplicitVarSizeWithDummy[q6] + j, s_ExplicitVarSizeWithDummy[q6] * j, - s_ExplicitVarSizeWithDummy[q6] / j; - int(1..3)]), - (s_ExplicitVarSizeWithDummy[q6] - j) % 2 = 0; - int(1..5)]) - /\ - min([s_ExplicitVarSizeWithDummy[q6] + j, s_ExplicitVarSizeWithDummy[q6] - j, s_ExplicitVarSizeWithDummy[q6] * j, - s_ExplicitVarSizeWithDummy[q6] / j; - int(1..4)]) - = conjure_aux1 - | q6 : int(1..4), j : int(1..4)]), - sum([toInt(and([s_ExplicitVarSizeWithDummy[q6] != 5, s_Occurrence[j], s_ExplicitVarSizeWithDummy[q6] != j, - allDiff([s_ExplicitVarSizeWithDummy[q6] + j, s_ExplicitVarSizeWithDummy[q6] * j, - s_ExplicitVarSizeWithDummy[q6] / j; - int(1..3)]), - (s_ExplicitVarSizeWithDummy[q6] - j) % 2 = 0; - int(1..5)])) - | q6 : int(1..4), j : int(1..4)]) - = 0 - -> conjure_aux1 = -20, - x = conjure_aux1, - sum([toInt(and([s_ExplicitVarSizeWithDummy[q6] != 5, s_Occurrence[j], s_ExplicitVarSizeWithDummy[q6] != j, - allDiff([s_ExplicitVarSizeWithDummy[q6] + j, s_ExplicitVarSizeWithDummy[q6] * j, - s_ExplicitVarSizeWithDummy[q6] / j; - int(1..3)]), - (s_ExplicitVarSizeWithDummy[q6] - j) % 2 = 0; - int(1..5)])) - | q6 : int(1..4), j : int(1..4)]) - > 0, - and([s_ExplicitVarSizeWithDummy[q1] < s_ExplicitVarSizeWithDummy[q1 + 1] \/ s_ExplicitVarSizeWithDummy[q1] = 5 - | q1 : int(1..3)]), - and([s_ExplicitVarSizeWithDummy[q2] = 5 -> s_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..3)]), - and([s_Occurrence[q28] -> - or([s_ExplicitVarSizeWithDummy[q30] != 5 /\ s_ExplicitVarSizeWithDummy[q30] = q28 | q30 : int(1..4)]) - | q28 : int(1..4)]), - and([s_ExplicitVarSizeWithDummy[q32] != 5 -> s_Occurrence[s_ExplicitVarSizeWithDummy[q32]] | q32 : int(1..4)]) - diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_1_3-solution000001.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_1_3-solution000001.solution deleted file mode 100644 index 8b4ecbb66d..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_2_1_3-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 3} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_1_3-solution000002.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_1_3-solution000002.solution deleted file mode 100644 index 159a613983..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_2_1_3-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {2, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_1_3-solution000003.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_1_3-solution000003.solution deleted file mode 100644 index 5963aac565..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_2_1_3-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 3} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_1_3-solution000004.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_1_3-solution000004.solution deleted file mode 100644 index 6eeacc9727..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_2_1_3-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_1_3-solution000005.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_1_3-solution000005.solution deleted file mode 100644 index 560dd0f2f7..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_2_1_3-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 3, 4} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_1_3-solution000006.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_1_3-solution000006.solution deleted file mode 100644 index 40f3fd5c8f..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_2_1_3-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {2, 3, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_1_3-solution000007.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_1_3-solution000007.solution deleted file mode 100644 index bd956f44e3..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_2_1_3-solution000007.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 3, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_1_3.eprime b/tests/exhaustive/basic/comprehension_letting/expected/model_2_1_3.eprime deleted file mode 100644 index 3f8f2d2249..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_2_1_3.eprime +++ /dev/null @@ -1,92 +0,0 @@ -language ESSENCE' 1.0 - -find s_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -find s_Occurrence: matrix indexed by [int(1..4)] of bool -find s_ExplicitVarSizeWithMarker_Marker: int(0..4) -find s_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -letting let1 be -100 -find x: int(-100..100) -find conjure_aux1: int(-20..4) -branching on - [s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithMarker_Values, s_ExplicitVarSizeWithDummy, s_Occurrence, - x] -such that - and([and([s_ExplicitVarSizeWithDummy[q22] != 5, s_Occurrence[j], s_ExplicitVarSizeWithDummy[q22] != j, - allDiff([s_ExplicitVarSizeWithDummy[q22] + j, s_ExplicitVarSizeWithDummy[q22] * j, - s_ExplicitVarSizeWithDummy[q22] / j; - int(1..3)]), - (s_ExplicitVarSizeWithDummy[q22] - j) % 2 = 0; - int(1..5)]) - -> - min([s_ExplicitVarSizeWithDummy[q22] + j, s_ExplicitVarSizeWithDummy[q22] - j, - s_ExplicitVarSizeWithDummy[q22] * j, s_ExplicitVarSizeWithDummy[q22] / j; - int(1..4)]) - <= conjure_aux1 - | q22 : int(1..4), j : int(1..4)]), - sum([toInt(and([s_ExplicitVarSizeWithDummy[q22] != 5, s_Occurrence[j], s_ExplicitVarSizeWithDummy[q22] != j, - allDiff([s_ExplicitVarSizeWithDummy[q22] + j, s_ExplicitVarSizeWithDummy[q22] * j, - s_ExplicitVarSizeWithDummy[q22] / j; - int(1..3)]), - (s_ExplicitVarSizeWithDummy[q22] - j) % 2 = 0; - int(1..5)])) - | q22 : int(1..4), j : int(1..4)]) - > 0 - -> - or([and([s_ExplicitVarSizeWithDummy[q22] != 5, s_Occurrence[j], s_ExplicitVarSizeWithDummy[q22] != j, - allDiff([s_ExplicitVarSizeWithDummy[q22] + j, s_ExplicitVarSizeWithDummy[q22] * j, - s_ExplicitVarSizeWithDummy[q22] / j; - int(1..3)]), - (s_ExplicitVarSizeWithDummy[q22] - j) % 2 = 0; - int(1..5)]) - /\ - min([s_ExplicitVarSizeWithDummy[q22] + j, s_ExplicitVarSizeWithDummy[q22] - j, - s_ExplicitVarSizeWithDummy[q22] * j, s_ExplicitVarSizeWithDummy[q22] / j; - int(1..4)]) - = conjure_aux1 - | q22 : int(1..4), j : int(1..4)]), - sum([toInt(and([s_ExplicitVarSizeWithDummy[q22] != 5, s_Occurrence[j], s_ExplicitVarSizeWithDummy[q22] != j, - allDiff([s_ExplicitVarSizeWithDummy[q22] + j, s_ExplicitVarSizeWithDummy[q22] * j, - s_ExplicitVarSizeWithDummy[q22] / j; - int(1..3)]), - (s_ExplicitVarSizeWithDummy[q22] - j) % 2 = 0; - int(1..5)])) - | q22 : int(1..4), j : int(1..4)]) - = 0 - -> conjure_aux1 = -20, - x = conjure_aux1, - sum([toInt(and([s_ExplicitVarSizeWithDummy[q22] != 5, s_Occurrence[j], s_ExplicitVarSizeWithDummy[q22] != j, - allDiff([s_ExplicitVarSizeWithDummy[q22] + j, s_ExplicitVarSizeWithDummy[q22] * j, - s_ExplicitVarSizeWithDummy[q22] / j; - int(1..3)]), - (s_ExplicitVarSizeWithDummy[q22] - j) % 2 = 0; - int(1..5)])) - | q22 : int(1..4), j : int(1..4)]) - > 0, - and([s_ExplicitVarSizeWithDummy[q1] < s_ExplicitVarSizeWithDummy[q1 + 1] \/ s_ExplicitVarSizeWithDummy[q1] = 5 - | q1 : int(1..3)]), - and([s_ExplicitVarSizeWithDummy[q2] = 5 -> s_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..3)]), - and([s_Occurrence[q44] -> - or([s_ExplicitVarSizeWithDummy[q46] != 5 /\ s_ExplicitVarSizeWithDummy[q46] = q44 | q46 : int(1..4)]) - | q44 : int(1..4)]), - and([s_ExplicitVarSizeWithDummy[q48] != 5 -> s_Occurrence[s_ExplicitVarSizeWithDummy[q48]] | q48 : int(1..4)]), - and([q6 + 1 <= s_ExplicitVarSizeWithMarker_Marker -> - s_ExplicitVarSizeWithMarker_Values[q6] < s_ExplicitVarSizeWithMarker_Values[q6 + 1] - | q6 : int(1..3)]), - and([q7 > s_ExplicitVarSizeWithMarker_Marker -> s_ExplicitVarSizeWithMarker_Values[q7] = 1 | q7 : int(1..4)]), - and([q10 <= s_ExplicitVarSizeWithMarker_Marker -> - or([s_ExplicitVarSizeWithDummy[q12] != 5 /\ - s_ExplicitVarSizeWithDummy[q12] = s_ExplicitVarSizeWithMarker_Values[q10] - | q12 : int(1..4)]) - | q10 : int(1..4)]), - and([s_ExplicitVarSizeWithDummy[q14] != 5 -> - or([q16 <= s_ExplicitVarSizeWithMarker_Marker /\ - s_ExplicitVarSizeWithMarker_Values[q16] = s_ExplicitVarSizeWithDummy[q14] - | q16 : int(1..4)]) - | q14 : int(1..4)]), - and([q18 <= s_ExplicitVarSizeWithMarker_Marker -> s_Occurrence[s_ExplicitVarSizeWithMarker_Values[q18]] - | q18 : int(1..4)]), - and([s_Occurrence[q19] -> - or([q21 <= s_ExplicitVarSizeWithMarker_Marker /\ s_ExplicitVarSizeWithMarker_Values[q21] = q19 - | q21 : int(1..4)]) - | q19 : int(1..4)]) - diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_1_4-solution000001.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_1_4-solution000001.solution deleted file mode 100644 index 8b4ecbb66d..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_2_1_4-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 3} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_1_4-solution000002.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_1_4-solution000002.solution deleted file mode 100644 index 159a613983..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_2_1_4-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {2, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_1_4-solution000003.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_1_4-solution000003.solution deleted file mode 100644 index 5963aac565..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_2_1_4-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 3} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_1_4-solution000004.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_1_4-solution000004.solution deleted file mode 100644 index 6eeacc9727..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_2_1_4-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_1_4-solution000005.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_1_4-solution000005.solution deleted file mode 100644 index 560dd0f2f7..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_2_1_4-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 3, 4} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_1_4-solution000006.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_1_4-solution000006.solution deleted file mode 100644 index 40f3fd5c8f..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_2_1_4-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {2, 3, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_1_4-solution000007.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_1_4-solution000007.solution deleted file mode 100644 index bd956f44e3..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_2_1_4-solution000007.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 3, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_1_4.eprime b/tests/exhaustive/basic/comprehension_letting/expected/model_2_1_4.eprime deleted file mode 100644 index a9a3e9cd12..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_2_1_4.eprime +++ /dev/null @@ -1,91 +0,0 @@ -language ESSENCE' 1.0 - -find s_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -find s_Occurrence: matrix indexed by [int(1..4)] of bool -find s_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find s_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -letting let1 be -100 -find x: int(-100..100) -find conjure_aux1: int(-20..4) -branching on - [s_ExplicitVarSizeWithFlags_Flags, s_ExplicitVarSizeWithFlags_Values, s_ExplicitVarSizeWithDummy, s_Occurrence, x] -such that - and([and([s_ExplicitVarSizeWithDummy[q24] != 5, s_Occurrence[j], s_ExplicitVarSizeWithDummy[q24] != j, - allDiff([s_ExplicitVarSizeWithDummy[q24] + j, s_ExplicitVarSizeWithDummy[q24] * j, - s_ExplicitVarSizeWithDummy[q24] / j; - int(1..3)]), - (s_ExplicitVarSizeWithDummy[q24] - j) % 2 = 0; - int(1..5)]) - -> - min([s_ExplicitVarSizeWithDummy[q24] + j, s_ExplicitVarSizeWithDummy[q24] - j, - s_ExplicitVarSizeWithDummy[q24] * j, s_ExplicitVarSizeWithDummy[q24] / j; - int(1..4)]) - <= conjure_aux1 - | q24 : int(1..4), j : int(1..4)]), - sum([toInt(and([s_ExplicitVarSizeWithDummy[q24] != 5, s_Occurrence[j], s_ExplicitVarSizeWithDummy[q24] != j, - allDiff([s_ExplicitVarSizeWithDummy[q24] + j, s_ExplicitVarSizeWithDummy[q24] * j, - s_ExplicitVarSizeWithDummy[q24] / j; - int(1..3)]), - (s_ExplicitVarSizeWithDummy[q24] - j) % 2 = 0; - int(1..5)])) - | q24 : int(1..4), j : int(1..4)]) - > 0 - -> - or([and([s_ExplicitVarSizeWithDummy[q24] != 5, s_Occurrence[j], s_ExplicitVarSizeWithDummy[q24] != j, - allDiff([s_ExplicitVarSizeWithDummy[q24] + j, s_ExplicitVarSizeWithDummy[q24] * j, - s_ExplicitVarSizeWithDummy[q24] / j; - int(1..3)]), - (s_ExplicitVarSizeWithDummy[q24] - j) % 2 = 0; - int(1..5)]) - /\ - min([s_ExplicitVarSizeWithDummy[q24] + j, s_ExplicitVarSizeWithDummy[q24] - j, - s_ExplicitVarSizeWithDummy[q24] * j, s_ExplicitVarSizeWithDummy[q24] / j; - int(1..4)]) - = conjure_aux1 - | q24 : int(1..4), j : int(1..4)]), - sum([toInt(and([s_ExplicitVarSizeWithDummy[q24] != 5, s_Occurrence[j], s_ExplicitVarSizeWithDummy[q24] != j, - allDiff([s_ExplicitVarSizeWithDummy[q24] + j, s_ExplicitVarSizeWithDummy[q24] * j, - s_ExplicitVarSizeWithDummy[q24] / j; - int(1..3)]), - (s_ExplicitVarSizeWithDummy[q24] - j) % 2 = 0; - int(1..5)])) - | q24 : int(1..4), j : int(1..4)]) - = 0 - -> conjure_aux1 = -20, - x = conjure_aux1, - sum([toInt(and([s_ExplicitVarSizeWithDummy[q24] != 5, s_Occurrence[j], s_ExplicitVarSizeWithDummy[q24] != j, - allDiff([s_ExplicitVarSizeWithDummy[q24] + j, s_ExplicitVarSizeWithDummy[q24] * j, - s_ExplicitVarSizeWithDummy[q24] / j; - int(1..3)]), - (s_ExplicitVarSizeWithDummy[q24] - j) % 2 = 0; - int(1..5)])) - | q24 : int(1..4), j : int(1..4)]) - > 0, - and([s_ExplicitVarSizeWithDummy[q1] < s_ExplicitVarSizeWithDummy[q1 + 1] \/ s_ExplicitVarSizeWithDummy[q1] = 5 - | q1 : int(1..3)]), - and([s_ExplicitVarSizeWithDummy[q2] = 5 -> s_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..3)]), - and([s_Occurrence[q46] -> - or([s_ExplicitVarSizeWithDummy[q48] != 5 /\ s_ExplicitVarSizeWithDummy[q48] = q46 | q48 : int(1..4)]) - | q46 : int(1..4)]), - and([s_ExplicitVarSizeWithDummy[q50] != 5 -> s_Occurrence[s_ExplicitVarSizeWithDummy[q50]] | q50 : int(1..4)]), - and([s_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> - s_ExplicitVarSizeWithFlags_Values[q6] < s_ExplicitVarSizeWithFlags_Values[q6 + 1] - | q6 : int(1..3)]), - and([s_ExplicitVarSizeWithFlags_Flags[q7] = false -> s_ExplicitVarSizeWithFlags_Values[q7] = 1 | q7 : int(1..4)]), - and([s_ExplicitVarSizeWithFlags_Flags[q8 + 1] -> s_ExplicitVarSizeWithFlags_Flags[q8] | q8 : int(1..3)]), - and([s_ExplicitVarSizeWithFlags_Flags[q12] -> - or([s_ExplicitVarSizeWithDummy[q14] != 5 /\ - s_ExplicitVarSizeWithDummy[q14] = s_ExplicitVarSizeWithFlags_Values[q12] - | q14 : int(1..4)]) - | q12 : int(1..4)]), - and([s_ExplicitVarSizeWithDummy[q16] != 5 -> - or([s_ExplicitVarSizeWithFlags_Flags[q18] /\ - s_ExplicitVarSizeWithFlags_Values[q18] = s_ExplicitVarSizeWithDummy[q16] - | q18 : int(1..4)]) - | q16 : int(1..4)]), - and([s_ExplicitVarSizeWithFlags_Flags[q20] -> s_Occurrence[s_ExplicitVarSizeWithFlags_Values[q20]] - | q20 : int(1..4)]), - and([s_Occurrence[q21] -> - or([s_ExplicitVarSizeWithFlags_Flags[q23] /\ s_ExplicitVarSizeWithFlags_Values[q23] = q21 | q23 : int(1..4)]) - | q21 : int(1..4)]) - diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_1-solution000001.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_1-solution000001.solution deleted file mode 100644 index 159a613983..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {2, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_1-solution000002.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_1-solution000002.solution deleted file mode 100644 index 40f3fd5c8f..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {2, 3, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_1-solution000003.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_1-solution000003.solution deleted file mode 100644 index 8b4ecbb66d..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_1-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 3} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_1-solution000004.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_1-solution000004.solution deleted file mode 100644 index 560dd0f2f7..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_1-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 3, 4} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_1-solution000005.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_1-solution000005.solution deleted file mode 100644 index 6eeacc9727..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_1-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_1-solution000006.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_1-solution000006.solution deleted file mode 100644 index 5963aac565..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_1-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 3} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_1-solution000007.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_1-solution000007.solution deleted file mode 100644 index bd956f44e3..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_1-solution000007.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 3, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_1.eprime b/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_1.eprime deleted file mode 100644 index 5d253068bc..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_1.eprime +++ /dev/null @@ -1,82 +0,0 @@ -language ESSENCE' 1.0 - -find s_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -find s_Occurrence: matrix indexed by [int(1..4)] of bool -letting let1 be -100 -find x: int(-100..100) -find conjure_aux1: int(-25..4) -branching on [s_Occurrence, s_ExplicitVarSizeWithDummy, x] -such that - and([and([s_ExplicitVarSizeWithDummy[q6] != 5, s_ExplicitVarSizeWithDummy[q7] != 5, - s_ExplicitVarSizeWithDummy[q6] != s_ExplicitVarSizeWithDummy[q7], - allDiff([s_ExplicitVarSizeWithDummy[q6] + s_ExplicitVarSizeWithDummy[q7], - s_ExplicitVarSizeWithDummy[q6] * s_ExplicitVarSizeWithDummy[q7], - s_ExplicitVarSizeWithDummy[q6] / s_ExplicitVarSizeWithDummy[q7]; - int(1..3)]), - (s_ExplicitVarSizeWithDummy[q6] - s_ExplicitVarSizeWithDummy[q7]) % 2 = 0; - int(1..5)]) - -> - min([s_ExplicitVarSizeWithDummy[q6] + s_ExplicitVarSizeWithDummy[q7], - s_ExplicitVarSizeWithDummy[q6] - s_ExplicitVarSizeWithDummy[q7], - s_ExplicitVarSizeWithDummy[q6] * s_ExplicitVarSizeWithDummy[q7], - s_ExplicitVarSizeWithDummy[q6] / s_ExplicitVarSizeWithDummy[q7]; - int(1..4)]) - <= conjure_aux1 - | q6 : int(1..4), q7 : int(1..4)]), - sum([toInt(and([s_ExplicitVarSizeWithDummy[q6] != 5, s_ExplicitVarSizeWithDummy[q7] != 5, - s_ExplicitVarSizeWithDummy[q6] != s_ExplicitVarSizeWithDummy[q7], - allDiff([s_ExplicitVarSizeWithDummy[q6] + s_ExplicitVarSizeWithDummy[q7], - s_ExplicitVarSizeWithDummy[q6] * s_ExplicitVarSizeWithDummy[q7], - s_ExplicitVarSizeWithDummy[q6] / s_ExplicitVarSizeWithDummy[q7]; - int(1..3)]), - (s_ExplicitVarSizeWithDummy[q6] - s_ExplicitVarSizeWithDummy[q7]) % 2 = 0; - int(1..5)])) - | q6 : int(1..4), q7 : int(1..4)]) - > 0 - -> - or([and([s_ExplicitVarSizeWithDummy[q6] != 5, s_ExplicitVarSizeWithDummy[q7] != 5, - s_ExplicitVarSizeWithDummy[q6] != s_ExplicitVarSizeWithDummy[q7], - allDiff([s_ExplicitVarSizeWithDummy[q6] + s_ExplicitVarSizeWithDummy[q7], - s_ExplicitVarSizeWithDummy[q6] * s_ExplicitVarSizeWithDummy[q7], - s_ExplicitVarSizeWithDummy[q6] / s_ExplicitVarSizeWithDummy[q7]; - int(1..3)]), - (s_ExplicitVarSizeWithDummy[q6] - s_ExplicitVarSizeWithDummy[q7]) % 2 = 0; - int(1..5)]) - /\ - min([s_ExplicitVarSizeWithDummy[q6] + s_ExplicitVarSizeWithDummy[q7], - s_ExplicitVarSizeWithDummy[q6] - s_ExplicitVarSizeWithDummy[q7], - s_ExplicitVarSizeWithDummy[q6] * s_ExplicitVarSizeWithDummy[q7], - s_ExplicitVarSizeWithDummy[q6] / s_ExplicitVarSizeWithDummy[q7]; - int(1..4)]) - = conjure_aux1 - | q6 : int(1..4), q7 : int(1..4)]), - sum([toInt(and([s_ExplicitVarSizeWithDummy[q6] != 5, s_ExplicitVarSizeWithDummy[q7] != 5, - s_ExplicitVarSizeWithDummy[q6] != s_ExplicitVarSizeWithDummy[q7], - allDiff([s_ExplicitVarSizeWithDummy[q6] + s_ExplicitVarSizeWithDummy[q7], - s_ExplicitVarSizeWithDummy[q6] * s_ExplicitVarSizeWithDummy[q7], - s_ExplicitVarSizeWithDummy[q6] / s_ExplicitVarSizeWithDummy[q7]; - int(1..3)]), - (s_ExplicitVarSizeWithDummy[q6] - s_ExplicitVarSizeWithDummy[q7]) % 2 = 0; - int(1..5)])) - | q6 : int(1..4), q7 : int(1..4)]) - = 0 - -> conjure_aux1 = -25, - x = conjure_aux1, - sum([toInt(and([s_ExplicitVarSizeWithDummy[q6] != 5, s_ExplicitVarSizeWithDummy[q7] != 5, - s_ExplicitVarSizeWithDummy[q6] != s_ExplicitVarSizeWithDummy[q7], - allDiff([s_ExplicitVarSizeWithDummy[q6] + s_ExplicitVarSizeWithDummy[q7], - s_ExplicitVarSizeWithDummy[q6] * s_ExplicitVarSizeWithDummy[q7], - s_ExplicitVarSizeWithDummy[q6] / s_ExplicitVarSizeWithDummy[q7]; - int(1..3)]), - (s_ExplicitVarSizeWithDummy[q6] - s_ExplicitVarSizeWithDummy[q7]) % 2 = 0; - int(1..5)])) - | q6 : int(1..4), q7 : int(1..4)]) - > 0, - and([s_ExplicitVarSizeWithDummy[q1] < s_ExplicitVarSizeWithDummy[q1 + 1] \/ s_ExplicitVarSizeWithDummy[q1] = 5 - | q1 : int(1..3)]), - and([s_ExplicitVarSizeWithDummy[q2] = 5 -> s_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..3)]), - and([s_Occurrence[q29] -> - or([s_ExplicitVarSizeWithDummy[q31] != 5 /\ s_ExplicitVarSizeWithDummy[q31] = q29 | q31 : int(1..4)]) - | q29 : int(1..4)]), - and([s_ExplicitVarSizeWithDummy[q33] != 5 -> s_Occurrence[s_ExplicitVarSizeWithDummy[q33]] | q33 : int(1..4)]) - diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_2-solution000001.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_2-solution000001.solution deleted file mode 100644 index bd956f44e3..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 3, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_2-solution000002.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_2-solution000002.solution deleted file mode 100644 index 5963aac565..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 3} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_2-solution000003.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_2-solution000003.solution deleted file mode 100644 index 6eeacc9727..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_2-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_2-solution000004.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_2-solution000004.solution deleted file mode 100644 index 560dd0f2f7..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_2-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 3, 4} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_2-solution000005.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_2-solution000005.solution deleted file mode 100644 index 8b4ecbb66d..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_2-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 3} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_2-solution000006.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_2-solution000006.solution deleted file mode 100644 index 40f3fd5c8f..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_2-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {2, 3, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_2-solution000007.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_2-solution000007.solution deleted file mode 100644 index 159a613983..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_2-solution000007.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {2, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_2.eprime b/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_2.eprime deleted file mode 100644 index 4e8c4bc4e7..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_2.eprime +++ /dev/null @@ -1,77 +0,0 @@ -language ESSENCE' 1.0 - -find s_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -letting let1 be -100 -find x: int(-100..100) -find conjure_aux1: int(-25..4) -branching on [s_ExplicitVarSizeWithDummy, x] -such that - and([and([s_ExplicitVarSizeWithDummy[q5] != 5, s_ExplicitVarSizeWithDummy[q6] != 5, - s_ExplicitVarSizeWithDummy[q5] != s_ExplicitVarSizeWithDummy[q6], - allDiff([s_ExplicitVarSizeWithDummy[q5] + s_ExplicitVarSizeWithDummy[q6], - s_ExplicitVarSizeWithDummy[q5] * s_ExplicitVarSizeWithDummy[q6], - s_ExplicitVarSizeWithDummy[q5] / s_ExplicitVarSizeWithDummy[q6]; - int(1..3)]), - (s_ExplicitVarSizeWithDummy[q5] - s_ExplicitVarSizeWithDummy[q6]) % 2 = 0; - int(1..5)]) - -> - min([s_ExplicitVarSizeWithDummy[q5] + s_ExplicitVarSizeWithDummy[q6], - s_ExplicitVarSizeWithDummy[q5] - s_ExplicitVarSizeWithDummy[q6], - s_ExplicitVarSizeWithDummy[q5] * s_ExplicitVarSizeWithDummy[q6], - s_ExplicitVarSizeWithDummy[q5] / s_ExplicitVarSizeWithDummy[q6]; - int(1..4)]) - <= conjure_aux1 - | q5 : int(1..4), q6 : int(1..4)]), - sum([toInt(and([s_ExplicitVarSizeWithDummy[q5] != 5, s_ExplicitVarSizeWithDummy[q6] != 5, - s_ExplicitVarSizeWithDummy[q5] != s_ExplicitVarSizeWithDummy[q6], - allDiff([s_ExplicitVarSizeWithDummy[q5] + s_ExplicitVarSizeWithDummy[q6], - s_ExplicitVarSizeWithDummy[q5] * s_ExplicitVarSizeWithDummy[q6], - s_ExplicitVarSizeWithDummy[q5] / s_ExplicitVarSizeWithDummy[q6]; - int(1..3)]), - (s_ExplicitVarSizeWithDummy[q5] - s_ExplicitVarSizeWithDummy[q6]) % 2 = 0; - int(1..5)])) - | q5 : int(1..4), q6 : int(1..4)]) - > 0 - -> - or([and([s_ExplicitVarSizeWithDummy[q5] != 5, s_ExplicitVarSizeWithDummy[q6] != 5, - s_ExplicitVarSizeWithDummy[q5] != s_ExplicitVarSizeWithDummy[q6], - allDiff([s_ExplicitVarSizeWithDummy[q5] + s_ExplicitVarSizeWithDummy[q6], - s_ExplicitVarSizeWithDummy[q5] * s_ExplicitVarSizeWithDummy[q6], - s_ExplicitVarSizeWithDummy[q5] / s_ExplicitVarSizeWithDummy[q6]; - int(1..3)]), - (s_ExplicitVarSizeWithDummy[q5] - s_ExplicitVarSizeWithDummy[q6]) % 2 = 0; - int(1..5)]) - /\ - min([s_ExplicitVarSizeWithDummy[q5] + s_ExplicitVarSizeWithDummy[q6], - s_ExplicitVarSizeWithDummy[q5] - s_ExplicitVarSizeWithDummy[q6], - s_ExplicitVarSizeWithDummy[q5] * s_ExplicitVarSizeWithDummy[q6], - s_ExplicitVarSizeWithDummy[q5] / s_ExplicitVarSizeWithDummy[q6]; - int(1..4)]) - = conjure_aux1 - | q5 : int(1..4), q6 : int(1..4)]), - sum([toInt(and([s_ExplicitVarSizeWithDummy[q5] != 5, s_ExplicitVarSizeWithDummy[q6] != 5, - s_ExplicitVarSizeWithDummy[q5] != s_ExplicitVarSizeWithDummy[q6], - allDiff([s_ExplicitVarSizeWithDummy[q5] + s_ExplicitVarSizeWithDummy[q6], - s_ExplicitVarSizeWithDummy[q5] * s_ExplicitVarSizeWithDummy[q6], - s_ExplicitVarSizeWithDummy[q5] / s_ExplicitVarSizeWithDummy[q6]; - int(1..3)]), - (s_ExplicitVarSizeWithDummy[q5] - s_ExplicitVarSizeWithDummy[q6]) % 2 = 0; - int(1..5)])) - | q5 : int(1..4), q6 : int(1..4)]) - = 0 - -> conjure_aux1 = -25, - x = conjure_aux1, - sum([toInt(and([s_ExplicitVarSizeWithDummy[q5] != 5, s_ExplicitVarSizeWithDummy[q6] != 5, - s_ExplicitVarSizeWithDummy[q5] != s_ExplicitVarSizeWithDummy[q6], - allDiff([s_ExplicitVarSizeWithDummy[q5] + s_ExplicitVarSizeWithDummy[q6], - s_ExplicitVarSizeWithDummy[q5] * s_ExplicitVarSizeWithDummy[q6], - s_ExplicitVarSizeWithDummy[q5] / s_ExplicitVarSizeWithDummy[q6]; - int(1..3)]), - (s_ExplicitVarSizeWithDummy[q5] - s_ExplicitVarSizeWithDummy[q6]) % 2 = 0; - int(1..5)])) - | q5 : int(1..4), q6 : int(1..4)]) - > 0, - and([s_ExplicitVarSizeWithDummy[q1] < s_ExplicitVarSizeWithDummy[q1 + 1] \/ s_ExplicitVarSizeWithDummy[q1] = 5 - | q1 : int(1..3)]), - and([s_ExplicitVarSizeWithDummy[q2] = 5 -> s_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..3)]) - diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_3-solution000001.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_3-solution000001.solution deleted file mode 100644 index 8b4ecbb66d..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_3-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 3} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_3-solution000002.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_3-solution000002.solution deleted file mode 100644 index 159a613983..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_3-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {2, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_3-solution000003.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_3-solution000003.solution deleted file mode 100644 index 5963aac565..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_3-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 3} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_3-solution000004.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_3-solution000004.solution deleted file mode 100644 index 6eeacc9727..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_3-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_3-solution000005.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_3-solution000005.solution deleted file mode 100644 index 560dd0f2f7..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_3-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 3, 4} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_3-solution000006.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_3-solution000006.solution deleted file mode 100644 index 40f3fd5c8f..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_3-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {2, 3, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_3-solution000007.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_3-solution000007.solution deleted file mode 100644 index bd956f44e3..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_3-solution000007.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 3, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_3.eprime b/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_3.eprime deleted file mode 100644 index 6d91904813..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_3.eprime +++ /dev/null @@ -1,93 +0,0 @@ -language ESSENCE' 1.0 - -find s_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -find s_ExplicitVarSizeWithMarker_Marker: int(0..4) -find s_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -letting let1 be -100 -find x: int(-100..100) -find conjure_aux1: int(-25..4) -branching on [s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithMarker_Values, s_ExplicitVarSizeWithDummy, x] -such that - and([and([s_ExplicitVarSizeWithDummy[q16] != 5, s_ExplicitVarSizeWithDummy[q17] != 5, - s_ExplicitVarSizeWithDummy[q16] != s_ExplicitVarSizeWithDummy[q17], - allDiff([s_ExplicitVarSizeWithDummy[q16] + s_ExplicitVarSizeWithDummy[q17], - s_ExplicitVarSizeWithDummy[q16] * s_ExplicitVarSizeWithDummy[q17], - s_ExplicitVarSizeWithDummy[q16] / s_ExplicitVarSizeWithDummy[q17]; - int(1..3)]), - (s_ExplicitVarSizeWithDummy[q16] - s_ExplicitVarSizeWithDummy[q17]) % 2 = 0; - int(1..5)]) - -> - min([s_ExplicitVarSizeWithDummy[q16] + s_ExplicitVarSizeWithDummy[q17], - s_ExplicitVarSizeWithDummy[q16] - s_ExplicitVarSizeWithDummy[q17], - s_ExplicitVarSizeWithDummy[q16] * s_ExplicitVarSizeWithDummy[q17], - s_ExplicitVarSizeWithDummy[q16] / s_ExplicitVarSizeWithDummy[q17]; - int(1..4)]) - <= conjure_aux1 - | q16 : int(1..4), q17 : int(1..4)]), - sum([toInt(and([s_ExplicitVarSizeWithDummy[q16] != 5, s_ExplicitVarSizeWithDummy[q17] != 5, - s_ExplicitVarSizeWithDummy[q16] != s_ExplicitVarSizeWithDummy[q17], - allDiff([s_ExplicitVarSizeWithDummy[q16] + s_ExplicitVarSizeWithDummy[q17], - s_ExplicitVarSizeWithDummy[q16] * s_ExplicitVarSizeWithDummy[q17], - s_ExplicitVarSizeWithDummy[q16] / s_ExplicitVarSizeWithDummy[q17]; - int(1..3)]), - (s_ExplicitVarSizeWithDummy[q16] - s_ExplicitVarSizeWithDummy[q17]) % 2 = 0; - int(1..5)])) - | q16 : int(1..4), q17 : int(1..4)]) - > 0 - -> - or([and([s_ExplicitVarSizeWithDummy[q16] != 5, s_ExplicitVarSizeWithDummy[q17] != 5, - s_ExplicitVarSizeWithDummy[q16] != s_ExplicitVarSizeWithDummy[q17], - allDiff([s_ExplicitVarSizeWithDummy[q16] + s_ExplicitVarSizeWithDummy[q17], - s_ExplicitVarSizeWithDummy[q16] * s_ExplicitVarSizeWithDummy[q17], - s_ExplicitVarSizeWithDummy[q16] / s_ExplicitVarSizeWithDummy[q17]; - int(1..3)]), - (s_ExplicitVarSizeWithDummy[q16] - s_ExplicitVarSizeWithDummy[q17]) % 2 = 0; - int(1..5)]) - /\ - min([s_ExplicitVarSizeWithDummy[q16] + s_ExplicitVarSizeWithDummy[q17], - s_ExplicitVarSizeWithDummy[q16] - s_ExplicitVarSizeWithDummy[q17], - s_ExplicitVarSizeWithDummy[q16] * s_ExplicitVarSizeWithDummy[q17], - s_ExplicitVarSizeWithDummy[q16] / s_ExplicitVarSizeWithDummy[q17]; - int(1..4)]) - = conjure_aux1 - | q16 : int(1..4), q17 : int(1..4)]), - sum([toInt(and([s_ExplicitVarSizeWithDummy[q16] != 5, s_ExplicitVarSizeWithDummy[q17] != 5, - s_ExplicitVarSizeWithDummy[q16] != s_ExplicitVarSizeWithDummy[q17], - allDiff([s_ExplicitVarSizeWithDummy[q16] + s_ExplicitVarSizeWithDummy[q17], - s_ExplicitVarSizeWithDummy[q16] * s_ExplicitVarSizeWithDummy[q17], - s_ExplicitVarSizeWithDummy[q16] / s_ExplicitVarSizeWithDummy[q17]; - int(1..3)]), - (s_ExplicitVarSizeWithDummy[q16] - s_ExplicitVarSizeWithDummy[q17]) % 2 = 0; - int(1..5)])) - | q16 : int(1..4), q17 : int(1..4)]) - = 0 - -> conjure_aux1 = -25, - x = conjure_aux1, - sum([toInt(and([s_ExplicitVarSizeWithDummy[q16] != 5, s_ExplicitVarSizeWithDummy[q17] != 5, - s_ExplicitVarSizeWithDummy[q16] != s_ExplicitVarSizeWithDummy[q17], - allDiff([s_ExplicitVarSizeWithDummy[q16] + s_ExplicitVarSizeWithDummy[q17], - s_ExplicitVarSizeWithDummy[q16] * s_ExplicitVarSizeWithDummy[q17], - s_ExplicitVarSizeWithDummy[q16] / s_ExplicitVarSizeWithDummy[q17]; - int(1..3)]), - (s_ExplicitVarSizeWithDummy[q16] - s_ExplicitVarSizeWithDummy[q17]) % 2 = 0; - int(1..5)])) - | q16 : int(1..4), q17 : int(1..4)]) - > 0, - and([s_ExplicitVarSizeWithDummy[q1] < s_ExplicitVarSizeWithDummy[q1 + 1] \/ s_ExplicitVarSizeWithDummy[q1] = 5 - | q1 : int(1..3)]), - and([s_ExplicitVarSizeWithDummy[q2] = 5 -> s_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..3)]), - and([q5 + 1 <= s_ExplicitVarSizeWithMarker_Marker -> - s_ExplicitVarSizeWithMarker_Values[q5] < s_ExplicitVarSizeWithMarker_Values[q5 + 1] - | q5 : int(1..3)]), - and([q6 > s_ExplicitVarSizeWithMarker_Marker -> s_ExplicitVarSizeWithMarker_Values[q6] = 1 | q6 : int(1..4)]), - and([q9 <= s_ExplicitVarSizeWithMarker_Marker -> - or([s_ExplicitVarSizeWithDummy[q11] != 5 /\ - s_ExplicitVarSizeWithDummy[q11] = s_ExplicitVarSizeWithMarker_Values[q9] - | q11 : int(1..4)]) - | q9 : int(1..4)]), - and([s_ExplicitVarSizeWithDummy[q13] != 5 -> - or([q15 <= s_ExplicitVarSizeWithMarker_Marker /\ - s_ExplicitVarSizeWithMarker_Values[q15] = s_ExplicitVarSizeWithDummy[q13] - | q15 : int(1..4)]) - | q13 : int(1..4)]) - diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_4-solution000001.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_4-solution000001.solution deleted file mode 100644 index 8b4ecbb66d..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_4-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 3} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_4-solution000002.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_4-solution000002.solution deleted file mode 100644 index 159a613983..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_4-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {2, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_4-solution000003.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_4-solution000003.solution deleted file mode 100644 index 5963aac565..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_4-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 3} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_4-solution000004.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_4-solution000004.solution deleted file mode 100644 index 6eeacc9727..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_4-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_4-solution000005.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_4-solution000005.solution deleted file mode 100644 index 560dd0f2f7..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_4-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 3, 4} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_4-solution000006.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_4-solution000006.solution deleted file mode 100644 index 40f3fd5c8f..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_4-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {2, 3, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_4-solution000007.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_4-solution000007.solution deleted file mode 100644 index bd956f44e3..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_4-solution000007.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 3, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_4.eprime b/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_4.eprime deleted file mode 100644 index 3627386375..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_4.eprime +++ /dev/null @@ -1,94 +0,0 @@ -language ESSENCE' 1.0 - -find s_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -find s_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find s_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -letting let1 be -100 -find x: int(-100..100) -find conjure_aux1: int(-25..4) -branching on [s_ExplicitVarSizeWithFlags_Flags, s_ExplicitVarSizeWithFlags_Values, s_ExplicitVarSizeWithDummy, x] -such that - and([and([s_ExplicitVarSizeWithDummy[q18] != 5, s_ExplicitVarSizeWithDummy[q19] != 5, - s_ExplicitVarSizeWithDummy[q18] != s_ExplicitVarSizeWithDummy[q19], - allDiff([s_ExplicitVarSizeWithDummy[q18] + s_ExplicitVarSizeWithDummy[q19], - s_ExplicitVarSizeWithDummy[q18] * s_ExplicitVarSizeWithDummy[q19], - s_ExplicitVarSizeWithDummy[q18] / s_ExplicitVarSizeWithDummy[q19]; - int(1..3)]), - (s_ExplicitVarSizeWithDummy[q18] - s_ExplicitVarSizeWithDummy[q19]) % 2 = 0; - int(1..5)]) - -> - min([s_ExplicitVarSizeWithDummy[q18] + s_ExplicitVarSizeWithDummy[q19], - s_ExplicitVarSizeWithDummy[q18] - s_ExplicitVarSizeWithDummy[q19], - s_ExplicitVarSizeWithDummy[q18] * s_ExplicitVarSizeWithDummy[q19], - s_ExplicitVarSizeWithDummy[q18] / s_ExplicitVarSizeWithDummy[q19]; - int(1..4)]) - <= conjure_aux1 - | q18 : int(1..4), q19 : int(1..4)]), - sum([toInt(and([s_ExplicitVarSizeWithDummy[q18] != 5, s_ExplicitVarSizeWithDummy[q19] != 5, - s_ExplicitVarSizeWithDummy[q18] != s_ExplicitVarSizeWithDummy[q19], - allDiff([s_ExplicitVarSizeWithDummy[q18] + s_ExplicitVarSizeWithDummy[q19], - s_ExplicitVarSizeWithDummy[q18] * s_ExplicitVarSizeWithDummy[q19], - s_ExplicitVarSizeWithDummy[q18] / s_ExplicitVarSizeWithDummy[q19]; - int(1..3)]), - (s_ExplicitVarSizeWithDummy[q18] - s_ExplicitVarSizeWithDummy[q19]) % 2 = 0; - int(1..5)])) - | q18 : int(1..4), q19 : int(1..4)]) - > 0 - -> - or([and([s_ExplicitVarSizeWithDummy[q18] != 5, s_ExplicitVarSizeWithDummy[q19] != 5, - s_ExplicitVarSizeWithDummy[q18] != s_ExplicitVarSizeWithDummy[q19], - allDiff([s_ExplicitVarSizeWithDummy[q18] + s_ExplicitVarSizeWithDummy[q19], - s_ExplicitVarSizeWithDummy[q18] * s_ExplicitVarSizeWithDummy[q19], - s_ExplicitVarSizeWithDummy[q18] / s_ExplicitVarSizeWithDummy[q19]; - int(1..3)]), - (s_ExplicitVarSizeWithDummy[q18] - s_ExplicitVarSizeWithDummy[q19]) % 2 = 0; - int(1..5)]) - /\ - min([s_ExplicitVarSizeWithDummy[q18] + s_ExplicitVarSizeWithDummy[q19], - s_ExplicitVarSizeWithDummy[q18] - s_ExplicitVarSizeWithDummy[q19], - s_ExplicitVarSizeWithDummy[q18] * s_ExplicitVarSizeWithDummy[q19], - s_ExplicitVarSizeWithDummy[q18] / s_ExplicitVarSizeWithDummy[q19]; - int(1..4)]) - = conjure_aux1 - | q18 : int(1..4), q19 : int(1..4)]), - sum([toInt(and([s_ExplicitVarSizeWithDummy[q18] != 5, s_ExplicitVarSizeWithDummy[q19] != 5, - s_ExplicitVarSizeWithDummy[q18] != s_ExplicitVarSizeWithDummy[q19], - allDiff([s_ExplicitVarSizeWithDummy[q18] + s_ExplicitVarSizeWithDummy[q19], - s_ExplicitVarSizeWithDummy[q18] * s_ExplicitVarSizeWithDummy[q19], - s_ExplicitVarSizeWithDummy[q18] / s_ExplicitVarSizeWithDummy[q19]; - int(1..3)]), - (s_ExplicitVarSizeWithDummy[q18] - s_ExplicitVarSizeWithDummy[q19]) % 2 = 0; - int(1..5)])) - | q18 : int(1..4), q19 : int(1..4)]) - = 0 - -> conjure_aux1 = -25, - x = conjure_aux1, - sum([toInt(and([s_ExplicitVarSizeWithDummy[q18] != 5, s_ExplicitVarSizeWithDummy[q19] != 5, - s_ExplicitVarSizeWithDummy[q18] != s_ExplicitVarSizeWithDummy[q19], - allDiff([s_ExplicitVarSizeWithDummy[q18] + s_ExplicitVarSizeWithDummy[q19], - s_ExplicitVarSizeWithDummy[q18] * s_ExplicitVarSizeWithDummy[q19], - s_ExplicitVarSizeWithDummy[q18] / s_ExplicitVarSizeWithDummy[q19]; - int(1..3)]), - (s_ExplicitVarSizeWithDummy[q18] - s_ExplicitVarSizeWithDummy[q19]) % 2 = 0; - int(1..5)])) - | q18 : int(1..4), q19 : int(1..4)]) - > 0, - and([s_ExplicitVarSizeWithDummy[q1] < s_ExplicitVarSizeWithDummy[q1 + 1] \/ s_ExplicitVarSizeWithDummy[q1] = 5 - | q1 : int(1..3)]), - and([s_ExplicitVarSizeWithDummy[q2] = 5 -> s_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..3)]), - and([s_ExplicitVarSizeWithFlags_Flags[q5 + 1] -> - s_ExplicitVarSizeWithFlags_Values[q5] < s_ExplicitVarSizeWithFlags_Values[q5 + 1] - | q5 : int(1..3)]), - and([s_ExplicitVarSizeWithFlags_Flags[q6] = false -> s_ExplicitVarSizeWithFlags_Values[q6] = 1 | q6 : int(1..4)]), - and([s_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> s_ExplicitVarSizeWithFlags_Flags[q7] | q7 : int(1..3)]), - and([s_ExplicitVarSizeWithFlags_Flags[q11] -> - or([s_ExplicitVarSizeWithDummy[q13] != 5 /\ - s_ExplicitVarSizeWithDummy[q13] = s_ExplicitVarSizeWithFlags_Values[q11] - | q13 : int(1..4)]) - | q11 : int(1..4)]), - and([s_ExplicitVarSizeWithDummy[q15] != 5 -> - or([s_ExplicitVarSizeWithFlags_Flags[q17] /\ - s_ExplicitVarSizeWithFlags_Values[q17] = s_ExplicitVarSizeWithDummy[q15] - | q17 : int(1..4)]) - | q15 : int(1..4)]) - diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_3_1-solution000001.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_3_1-solution000001.solution deleted file mode 100644 index 159a613983..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_2_3_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {2, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_3_1-solution000002.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_3_1-solution000002.solution deleted file mode 100644 index 40f3fd5c8f..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_2_3_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {2, 3, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_3_1-solution000003.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_3_1-solution000003.solution deleted file mode 100644 index 8b4ecbb66d..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_2_3_1-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 3} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_3_1-solution000004.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_3_1-solution000004.solution deleted file mode 100644 index 560dd0f2f7..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_2_3_1-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 3, 4} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_3_1-solution000005.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_3_1-solution000005.solution deleted file mode 100644 index 6eeacc9727..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_2_3_1-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_3_1-solution000006.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_3_1-solution000006.solution deleted file mode 100644 index 5963aac565..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_2_3_1-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 3} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_3_1-solution000007.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_3_1-solution000007.solution deleted file mode 100644 index bd956f44e3..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_2_3_1-solution000007.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 3, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_3_1.eprime b/tests/exhaustive/basic/comprehension_letting/expected/model_2_3_1.eprime deleted file mode 100644 index 2b18a316f8..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_2_3_1.eprime +++ /dev/null @@ -1,106 +0,0 @@ -language ESSENCE' 1.0 - -find s_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -find s_ExplicitVarSizeWithMarker_Marker: int(0..4) -find s_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -find s_Occurrence: matrix indexed by [int(1..4)] of bool -letting let1 be -100 -find x: int(-100..100) -find conjure_aux1: int(-20..4) -branching on - [s_Occurrence, s_ExplicitVarSizeWithDummy, s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithMarker_Values, - x] -such that - and([and([s_ExplicitVarSizeWithDummy[q17] != 5, q18 <= s_ExplicitVarSizeWithMarker_Marker, - s_ExplicitVarSizeWithDummy[q17] != s_ExplicitVarSizeWithMarker_Values[q18], - allDiff([s_ExplicitVarSizeWithDummy[q17] + s_ExplicitVarSizeWithMarker_Values[q18], - s_ExplicitVarSizeWithDummy[q17] * s_ExplicitVarSizeWithMarker_Values[q18], - s_ExplicitVarSizeWithDummy[q17] / s_ExplicitVarSizeWithMarker_Values[q18]; - int(1..3)]), - (s_ExplicitVarSizeWithDummy[q17] - s_ExplicitVarSizeWithMarker_Values[q18]) % 2 = 0; - int(1..5)]) - -> - min([s_ExplicitVarSizeWithDummy[q17] + s_ExplicitVarSizeWithMarker_Values[q18], - s_ExplicitVarSizeWithDummy[q17] - s_ExplicitVarSizeWithMarker_Values[q18], - s_ExplicitVarSizeWithDummy[q17] * s_ExplicitVarSizeWithMarker_Values[q18], - s_ExplicitVarSizeWithDummy[q17] / s_ExplicitVarSizeWithMarker_Values[q18]; - int(1..4)]) - <= conjure_aux1 - | q17 : int(1..4), q18 : int(1..4)]), - sum([toInt(and([s_ExplicitVarSizeWithDummy[q17] != 5, q18 <= s_ExplicitVarSizeWithMarker_Marker, - s_ExplicitVarSizeWithDummy[q17] != s_ExplicitVarSizeWithMarker_Values[q18], - allDiff([s_ExplicitVarSizeWithDummy[q17] + s_ExplicitVarSizeWithMarker_Values[q18], - s_ExplicitVarSizeWithDummy[q17] * s_ExplicitVarSizeWithMarker_Values[q18], - s_ExplicitVarSizeWithDummy[q17] / s_ExplicitVarSizeWithMarker_Values[q18]; - int(1..3)]), - (s_ExplicitVarSizeWithDummy[q17] - s_ExplicitVarSizeWithMarker_Values[q18]) % 2 = 0; - int(1..5)])) - | q17 : int(1..4), q18 : int(1..4)]) - > 0 - -> - or([and([s_ExplicitVarSizeWithDummy[q17] != 5, q18 <= s_ExplicitVarSizeWithMarker_Marker, - s_ExplicitVarSizeWithDummy[q17] != s_ExplicitVarSizeWithMarker_Values[q18], - allDiff([s_ExplicitVarSizeWithDummy[q17] + s_ExplicitVarSizeWithMarker_Values[q18], - s_ExplicitVarSizeWithDummy[q17] * s_ExplicitVarSizeWithMarker_Values[q18], - s_ExplicitVarSizeWithDummy[q17] / s_ExplicitVarSizeWithMarker_Values[q18]; - int(1..3)]), - (s_ExplicitVarSizeWithDummy[q17] - s_ExplicitVarSizeWithMarker_Values[q18]) % 2 = 0; - int(1..5)]) - /\ - min([s_ExplicitVarSizeWithDummy[q17] + s_ExplicitVarSizeWithMarker_Values[q18], - s_ExplicitVarSizeWithDummy[q17] - s_ExplicitVarSizeWithMarker_Values[q18], - s_ExplicitVarSizeWithDummy[q17] * s_ExplicitVarSizeWithMarker_Values[q18], - s_ExplicitVarSizeWithDummy[q17] / s_ExplicitVarSizeWithMarker_Values[q18]; - int(1..4)]) - = conjure_aux1 - | q17 : int(1..4), q18 : int(1..4)]), - sum([toInt(and([s_ExplicitVarSizeWithDummy[q17] != 5, q18 <= s_ExplicitVarSizeWithMarker_Marker, - s_ExplicitVarSizeWithDummy[q17] != s_ExplicitVarSizeWithMarker_Values[q18], - allDiff([s_ExplicitVarSizeWithDummy[q17] + s_ExplicitVarSizeWithMarker_Values[q18], - s_ExplicitVarSizeWithDummy[q17] * s_ExplicitVarSizeWithMarker_Values[q18], - s_ExplicitVarSizeWithDummy[q17] / s_ExplicitVarSizeWithMarker_Values[q18]; - int(1..3)]), - (s_ExplicitVarSizeWithDummy[q17] - s_ExplicitVarSizeWithMarker_Values[q18]) % 2 = 0; - int(1..5)])) - | q17 : int(1..4), q18 : int(1..4)]) - = 0 - -> conjure_aux1 = -20, - x = conjure_aux1, - sum([toInt(and([s_ExplicitVarSizeWithDummy[q17] != 5, q18 <= s_ExplicitVarSizeWithMarker_Marker, - s_ExplicitVarSizeWithDummy[q17] != s_ExplicitVarSizeWithMarker_Values[q18], - allDiff([s_ExplicitVarSizeWithDummy[q17] + s_ExplicitVarSizeWithMarker_Values[q18], - s_ExplicitVarSizeWithDummy[q17] * s_ExplicitVarSizeWithMarker_Values[q18], - s_ExplicitVarSizeWithDummy[q17] / s_ExplicitVarSizeWithMarker_Values[q18]; - int(1..3)]), - (s_ExplicitVarSizeWithDummy[q17] - s_ExplicitVarSizeWithMarker_Values[q18]) % 2 = 0; - int(1..5)])) - | q17 : int(1..4), q18 : int(1..4)]) - > 0, - and([s_ExplicitVarSizeWithDummy[q1] < s_ExplicitVarSizeWithDummy[q1 + 1] \/ s_ExplicitVarSizeWithDummy[q1] = 5 - | q1 : int(1..3)]), - and([s_ExplicitVarSizeWithDummy[q2] = 5 -> s_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..3)]), - and([q5 + 1 <= s_ExplicitVarSizeWithMarker_Marker -> - s_ExplicitVarSizeWithMarker_Values[q5] < s_ExplicitVarSizeWithMarker_Values[q5 + 1] - | q5 : int(1..3)]), - and([q6 > s_ExplicitVarSizeWithMarker_Marker -> s_ExplicitVarSizeWithMarker_Values[q6] = 1 | q6 : int(1..4)]), - and([q9 <= s_ExplicitVarSizeWithMarker_Marker -> - or([s_ExplicitVarSizeWithDummy[q11] != 5 /\ - s_ExplicitVarSizeWithDummy[q11] = s_ExplicitVarSizeWithMarker_Values[q9] - | q11 : int(1..4)]) - | q9 : int(1..4)]), - and([s_ExplicitVarSizeWithDummy[q13] != 5 -> - or([q15 <= s_ExplicitVarSizeWithMarker_Marker /\ - s_ExplicitVarSizeWithMarker_Values[q15] = s_ExplicitVarSizeWithDummy[q13] - | q15 : int(1..4)]) - | q13 : int(1..4)]), - and([s_Occurrence[q40] -> - or([s_ExplicitVarSizeWithDummy[q42] != 5 /\ s_ExplicitVarSizeWithDummy[q42] = q40 | q42 : int(1..4)]) - | q40 : int(1..4)]), - and([s_ExplicitVarSizeWithDummy[q44] != 5 -> s_Occurrence[s_ExplicitVarSizeWithDummy[q44]] | q44 : int(1..4)]), - and([s_Occurrence[q45] -> - or([q47 <= s_ExplicitVarSizeWithMarker_Marker /\ s_ExplicitVarSizeWithMarker_Values[q47] = q45 - | q47 : int(1..4)]) - | q45 : int(1..4)]), - and([q49 <= s_ExplicitVarSizeWithMarker_Marker -> s_Occurrence[s_ExplicitVarSizeWithMarker_Values[q49]] - | q49 : int(1..4)]) - diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_3_2-solution000001.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_3_2-solution000001.solution deleted file mode 100644 index 8b4ecbb66d..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_2_3_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 3} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_3_2-solution000002.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_3_2-solution000002.solution deleted file mode 100644 index 159a613983..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_2_3_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {2, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_3_2-solution000003.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_3_2-solution000003.solution deleted file mode 100644 index 5963aac565..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_2_3_2-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 3} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_3_2-solution000004.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_3_2-solution000004.solution deleted file mode 100644 index 6eeacc9727..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_2_3_2-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_3_2-solution000005.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_3_2-solution000005.solution deleted file mode 100644 index 560dd0f2f7..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_2_3_2-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 3, 4} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_3_2-solution000006.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_3_2-solution000006.solution deleted file mode 100644 index 40f3fd5c8f..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_2_3_2-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {2, 3, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_3_2-solution000007.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_3_2-solution000007.solution deleted file mode 100644 index bd956f44e3..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_2_3_2-solution000007.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 3, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_3_2.eprime b/tests/exhaustive/basic/comprehension_letting/expected/model_2_3_2.eprime deleted file mode 100644 index 6bede9f96d..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_2_3_2.eprime +++ /dev/null @@ -1,93 +0,0 @@ -language ESSENCE' 1.0 - -find s_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -find s_ExplicitVarSizeWithMarker_Marker: int(0..4) -find s_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -letting let1 be -100 -find x: int(-100..100) -find conjure_aux1: int(-20..4) -branching on [s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithMarker_Values, s_ExplicitVarSizeWithDummy, x] -such that - and([and([s_ExplicitVarSizeWithDummy[q16] != 5, q17 <= s_ExplicitVarSizeWithMarker_Marker, - s_ExplicitVarSizeWithDummy[q16] != s_ExplicitVarSizeWithMarker_Values[q17], - allDiff([s_ExplicitVarSizeWithDummy[q16] + s_ExplicitVarSizeWithMarker_Values[q17], - s_ExplicitVarSizeWithDummy[q16] * s_ExplicitVarSizeWithMarker_Values[q17], - s_ExplicitVarSizeWithDummy[q16] / s_ExplicitVarSizeWithMarker_Values[q17]; - int(1..3)]), - (s_ExplicitVarSizeWithDummy[q16] - s_ExplicitVarSizeWithMarker_Values[q17]) % 2 = 0; - int(1..5)]) - -> - min([s_ExplicitVarSizeWithDummy[q16] + s_ExplicitVarSizeWithMarker_Values[q17], - s_ExplicitVarSizeWithDummy[q16] - s_ExplicitVarSizeWithMarker_Values[q17], - s_ExplicitVarSizeWithDummy[q16] * s_ExplicitVarSizeWithMarker_Values[q17], - s_ExplicitVarSizeWithDummy[q16] / s_ExplicitVarSizeWithMarker_Values[q17]; - int(1..4)]) - <= conjure_aux1 - | q16 : int(1..4), q17 : int(1..4)]), - sum([toInt(and([s_ExplicitVarSizeWithDummy[q16] != 5, q17 <= s_ExplicitVarSizeWithMarker_Marker, - s_ExplicitVarSizeWithDummy[q16] != s_ExplicitVarSizeWithMarker_Values[q17], - allDiff([s_ExplicitVarSizeWithDummy[q16] + s_ExplicitVarSizeWithMarker_Values[q17], - s_ExplicitVarSizeWithDummy[q16] * s_ExplicitVarSizeWithMarker_Values[q17], - s_ExplicitVarSizeWithDummy[q16] / s_ExplicitVarSizeWithMarker_Values[q17]; - int(1..3)]), - (s_ExplicitVarSizeWithDummy[q16] - s_ExplicitVarSizeWithMarker_Values[q17]) % 2 = 0; - int(1..5)])) - | q16 : int(1..4), q17 : int(1..4)]) - > 0 - -> - or([and([s_ExplicitVarSizeWithDummy[q16] != 5, q17 <= s_ExplicitVarSizeWithMarker_Marker, - s_ExplicitVarSizeWithDummy[q16] != s_ExplicitVarSizeWithMarker_Values[q17], - allDiff([s_ExplicitVarSizeWithDummy[q16] + s_ExplicitVarSizeWithMarker_Values[q17], - s_ExplicitVarSizeWithDummy[q16] * s_ExplicitVarSizeWithMarker_Values[q17], - s_ExplicitVarSizeWithDummy[q16] / s_ExplicitVarSizeWithMarker_Values[q17]; - int(1..3)]), - (s_ExplicitVarSizeWithDummy[q16] - s_ExplicitVarSizeWithMarker_Values[q17]) % 2 = 0; - int(1..5)]) - /\ - min([s_ExplicitVarSizeWithDummy[q16] + s_ExplicitVarSizeWithMarker_Values[q17], - s_ExplicitVarSizeWithDummy[q16] - s_ExplicitVarSizeWithMarker_Values[q17], - s_ExplicitVarSizeWithDummy[q16] * s_ExplicitVarSizeWithMarker_Values[q17], - s_ExplicitVarSizeWithDummy[q16] / s_ExplicitVarSizeWithMarker_Values[q17]; - int(1..4)]) - = conjure_aux1 - | q16 : int(1..4), q17 : int(1..4)]), - sum([toInt(and([s_ExplicitVarSizeWithDummy[q16] != 5, q17 <= s_ExplicitVarSizeWithMarker_Marker, - s_ExplicitVarSizeWithDummy[q16] != s_ExplicitVarSizeWithMarker_Values[q17], - allDiff([s_ExplicitVarSizeWithDummy[q16] + s_ExplicitVarSizeWithMarker_Values[q17], - s_ExplicitVarSizeWithDummy[q16] * s_ExplicitVarSizeWithMarker_Values[q17], - s_ExplicitVarSizeWithDummy[q16] / s_ExplicitVarSizeWithMarker_Values[q17]; - int(1..3)]), - (s_ExplicitVarSizeWithDummy[q16] - s_ExplicitVarSizeWithMarker_Values[q17]) % 2 = 0; - int(1..5)])) - | q16 : int(1..4), q17 : int(1..4)]) - = 0 - -> conjure_aux1 = -20, - x = conjure_aux1, - sum([toInt(and([s_ExplicitVarSizeWithDummy[q16] != 5, q17 <= s_ExplicitVarSizeWithMarker_Marker, - s_ExplicitVarSizeWithDummy[q16] != s_ExplicitVarSizeWithMarker_Values[q17], - allDiff([s_ExplicitVarSizeWithDummy[q16] + s_ExplicitVarSizeWithMarker_Values[q17], - s_ExplicitVarSizeWithDummy[q16] * s_ExplicitVarSizeWithMarker_Values[q17], - s_ExplicitVarSizeWithDummy[q16] / s_ExplicitVarSizeWithMarker_Values[q17]; - int(1..3)]), - (s_ExplicitVarSizeWithDummy[q16] - s_ExplicitVarSizeWithMarker_Values[q17]) % 2 = 0; - int(1..5)])) - | q16 : int(1..4), q17 : int(1..4)]) - > 0, - and([s_ExplicitVarSizeWithDummy[q1] < s_ExplicitVarSizeWithDummy[q1 + 1] \/ s_ExplicitVarSizeWithDummy[q1] = 5 - | q1 : int(1..3)]), - and([s_ExplicitVarSizeWithDummy[q2] = 5 -> s_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..3)]), - and([q5 + 1 <= s_ExplicitVarSizeWithMarker_Marker -> - s_ExplicitVarSizeWithMarker_Values[q5] < s_ExplicitVarSizeWithMarker_Values[q5 + 1] - | q5 : int(1..3)]), - and([q6 > s_ExplicitVarSizeWithMarker_Marker -> s_ExplicitVarSizeWithMarker_Values[q6] = 1 | q6 : int(1..4)]), - and([q9 <= s_ExplicitVarSizeWithMarker_Marker -> - or([s_ExplicitVarSizeWithDummy[q11] != 5 /\ - s_ExplicitVarSizeWithDummy[q11] = s_ExplicitVarSizeWithMarker_Values[q9] - | q11 : int(1..4)]) - | q9 : int(1..4)]), - and([s_ExplicitVarSizeWithDummy[q13] != 5 -> - or([q15 <= s_ExplicitVarSizeWithMarker_Marker /\ - s_ExplicitVarSizeWithMarker_Values[q15] = s_ExplicitVarSizeWithDummy[q13] - | q15 : int(1..4)]) - | q13 : int(1..4)]) - diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_3_3-solution000001.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_3_3-solution000001.solution deleted file mode 100644 index 8b4ecbb66d..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_2_3_3-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 3} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_3_3-solution000002.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_3_3-solution000002.solution deleted file mode 100644 index 159a613983..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_2_3_3-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {2, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_3_3-solution000003.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_3_3-solution000003.solution deleted file mode 100644 index 5963aac565..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_2_3_3-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 3} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_3_3-solution000004.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_3_3-solution000004.solution deleted file mode 100644 index 6eeacc9727..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_2_3_3-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_3_3-solution000005.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_3_3-solution000005.solution deleted file mode 100644 index 560dd0f2f7..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_2_3_3-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 3, 4} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_3_3-solution000006.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_3_3-solution000006.solution deleted file mode 100644 index 40f3fd5c8f..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_2_3_3-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {2, 3, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_3_3-solution000007.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_3_3-solution000007.solution deleted file mode 100644 index bd956f44e3..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_2_3_3-solution000007.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 3, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_3_3.eprime b/tests/exhaustive/basic/comprehension_letting/expected/model_2_3_3.eprime deleted file mode 100644 index 6bede9f96d..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_2_3_3.eprime +++ /dev/null @@ -1,93 +0,0 @@ -language ESSENCE' 1.0 - -find s_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -find s_ExplicitVarSizeWithMarker_Marker: int(0..4) -find s_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -letting let1 be -100 -find x: int(-100..100) -find conjure_aux1: int(-20..4) -branching on [s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithMarker_Values, s_ExplicitVarSizeWithDummy, x] -such that - and([and([s_ExplicitVarSizeWithDummy[q16] != 5, q17 <= s_ExplicitVarSizeWithMarker_Marker, - s_ExplicitVarSizeWithDummy[q16] != s_ExplicitVarSizeWithMarker_Values[q17], - allDiff([s_ExplicitVarSizeWithDummy[q16] + s_ExplicitVarSizeWithMarker_Values[q17], - s_ExplicitVarSizeWithDummy[q16] * s_ExplicitVarSizeWithMarker_Values[q17], - s_ExplicitVarSizeWithDummy[q16] / s_ExplicitVarSizeWithMarker_Values[q17]; - int(1..3)]), - (s_ExplicitVarSizeWithDummy[q16] - s_ExplicitVarSizeWithMarker_Values[q17]) % 2 = 0; - int(1..5)]) - -> - min([s_ExplicitVarSizeWithDummy[q16] + s_ExplicitVarSizeWithMarker_Values[q17], - s_ExplicitVarSizeWithDummy[q16] - s_ExplicitVarSizeWithMarker_Values[q17], - s_ExplicitVarSizeWithDummy[q16] * s_ExplicitVarSizeWithMarker_Values[q17], - s_ExplicitVarSizeWithDummy[q16] / s_ExplicitVarSizeWithMarker_Values[q17]; - int(1..4)]) - <= conjure_aux1 - | q16 : int(1..4), q17 : int(1..4)]), - sum([toInt(and([s_ExplicitVarSizeWithDummy[q16] != 5, q17 <= s_ExplicitVarSizeWithMarker_Marker, - s_ExplicitVarSizeWithDummy[q16] != s_ExplicitVarSizeWithMarker_Values[q17], - allDiff([s_ExplicitVarSizeWithDummy[q16] + s_ExplicitVarSizeWithMarker_Values[q17], - s_ExplicitVarSizeWithDummy[q16] * s_ExplicitVarSizeWithMarker_Values[q17], - s_ExplicitVarSizeWithDummy[q16] / s_ExplicitVarSizeWithMarker_Values[q17]; - int(1..3)]), - (s_ExplicitVarSizeWithDummy[q16] - s_ExplicitVarSizeWithMarker_Values[q17]) % 2 = 0; - int(1..5)])) - | q16 : int(1..4), q17 : int(1..4)]) - > 0 - -> - or([and([s_ExplicitVarSizeWithDummy[q16] != 5, q17 <= s_ExplicitVarSizeWithMarker_Marker, - s_ExplicitVarSizeWithDummy[q16] != s_ExplicitVarSizeWithMarker_Values[q17], - allDiff([s_ExplicitVarSizeWithDummy[q16] + s_ExplicitVarSizeWithMarker_Values[q17], - s_ExplicitVarSizeWithDummy[q16] * s_ExplicitVarSizeWithMarker_Values[q17], - s_ExplicitVarSizeWithDummy[q16] / s_ExplicitVarSizeWithMarker_Values[q17]; - int(1..3)]), - (s_ExplicitVarSizeWithDummy[q16] - s_ExplicitVarSizeWithMarker_Values[q17]) % 2 = 0; - int(1..5)]) - /\ - min([s_ExplicitVarSizeWithDummy[q16] + s_ExplicitVarSizeWithMarker_Values[q17], - s_ExplicitVarSizeWithDummy[q16] - s_ExplicitVarSizeWithMarker_Values[q17], - s_ExplicitVarSizeWithDummy[q16] * s_ExplicitVarSizeWithMarker_Values[q17], - s_ExplicitVarSizeWithDummy[q16] / s_ExplicitVarSizeWithMarker_Values[q17]; - int(1..4)]) - = conjure_aux1 - | q16 : int(1..4), q17 : int(1..4)]), - sum([toInt(and([s_ExplicitVarSizeWithDummy[q16] != 5, q17 <= s_ExplicitVarSizeWithMarker_Marker, - s_ExplicitVarSizeWithDummy[q16] != s_ExplicitVarSizeWithMarker_Values[q17], - allDiff([s_ExplicitVarSizeWithDummy[q16] + s_ExplicitVarSizeWithMarker_Values[q17], - s_ExplicitVarSizeWithDummy[q16] * s_ExplicitVarSizeWithMarker_Values[q17], - s_ExplicitVarSizeWithDummy[q16] / s_ExplicitVarSizeWithMarker_Values[q17]; - int(1..3)]), - (s_ExplicitVarSizeWithDummy[q16] - s_ExplicitVarSizeWithMarker_Values[q17]) % 2 = 0; - int(1..5)])) - | q16 : int(1..4), q17 : int(1..4)]) - = 0 - -> conjure_aux1 = -20, - x = conjure_aux1, - sum([toInt(and([s_ExplicitVarSizeWithDummy[q16] != 5, q17 <= s_ExplicitVarSizeWithMarker_Marker, - s_ExplicitVarSizeWithDummy[q16] != s_ExplicitVarSizeWithMarker_Values[q17], - allDiff([s_ExplicitVarSizeWithDummy[q16] + s_ExplicitVarSizeWithMarker_Values[q17], - s_ExplicitVarSizeWithDummy[q16] * s_ExplicitVarSizeWithMarker_Values[q17], - s_ExplicitVarSizeWithDummy[q16] / s_ExplicitVarSizeWithMarker_Values[q17]; - int(1..3)]), - (s_ExplicitVarSizeWithDummy[q16] - s_ExplicitVarSizeWithMarker_Values[q17]) % 2 = 0; - int(1..5)])) - | q16 : int(1..4), q17 : int(1..4)]) - > 0, - and([s_ExplicitVarSizeWithDummy[q1] < s_ExplicitVarSizeWithDummy[q1 + 1] \/ s_ExplicitVarSizeWithDummy[q1] = 5 - | q1 : int(1..3)]), - and([s_ExplicitVarSizeWithDummy[q2] = 5 -> s_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..3)]), - and([q5 + 1 <= s_ExplicitVarSizeWithMarker_Marker -> - s_ExplicitVarSizeWithMarker_Values[q5] < s_ExplicitVarSizeWithMarker_Values[q5 + 1] - | q5 : int(1..3)]), - and([q6 > s_ExplicitVarSizeWithMarker_Marker -> s_ExplicitVarSizeWithMarker_Values[q6] = 1 | q6 : int(1..4)]), - and([q9 <= s_ExplicitVarSizeWithMarker_Marker -> - or([s_ExplicitVarSizeWithDummy[q11] != 5 /\ - s_ExplicitVarSizeWithDummy[q11] = s_ExplicitVarSizeWithMarker_Values[q9] - | q11 : int(1..4)]) - | q9 : int(1..4)]), - and([s_ExplicitVarSizeWithDummy[q13] != 5 -> - or([q15 <= s_ExplicitVarSizeWithMarker_Marker /\ - s_ExplicitVarSizeWithMarker_Values[q15] = s_ExplicitVarSizeWithDummy[q13] - | q15 : int(1..4)]) - | q13 : int(1..4)]) - diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_3_4-solution000001.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_3_4-solution000001.solution deleted file mode 100644 index 8b4ecbb66d..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_2_3_4-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 3} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_3_4-solution000002.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_3_4-solution000002.solution deleted file mode 100644 index 159a613983..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_2_3_4-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {2, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_3_4-solution000003.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_3_4-solution000003.solution deleted file mode 100644 index 5963aac565..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_2_3_4-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 3} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_3_4-solution000004.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_3_4-solution000004.solution deleted file mode 100644 index 6eeacc9727..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_2_3_4-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_3_4-solution000005.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_3_4-solution000005.solution deleted file mode 100644 index 560dd0f2f7..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_2_3_4-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 3, 4} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_3_4-solution000006.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_3_4-solution000006.solution deleted file mode 100644 index 40f3fd5c8f..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_2_3_4-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {2, 3, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_3_4-solution000007.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_3_4-solution000007.solution deleted file mode 100644 index bd956f44e3..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_2_3_4-solution000007.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 3, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_3_4.eprime b/tests/exhaustive/basic/comprehension_letting/expected/model_2_3_4.eprime deleted file mode 100644 index bb0cb8b3e9..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_2_3_4.eprime +++ /dev/null @@ -1,123 +0,0 @@ -language ESSENCE' 1.0 - -find s_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -find s_ExplicitVarSizeWithMarker_Marker: int(0..4) -find s_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -find s_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find s_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -letting let1 be -100 -find x: int(-100..100) -find conjure_aux1: int(-20..4) -branching on - [s_ExplicitVarSizeWithFlags_Flags, s_ExplicitVarSizeWithFlags_Values, s_ExplicitVarSizeWithDummy, - s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithMarker_Values, x] -such that - and([and([s_ExplicitVarSizeWithDummy[q37] != 5, q38 <= s_ExplicitVarSizeWithMarker_Marker, - s_ExplicitVarSizeWithDummy[q37] != s_ExplicitVarSizeWithMarker_Values[q38], - allDiff([s_ExplicitVarSizeWithDummy[q37] + s_ExplicitVarSizeWithMarker_Values[q38], - s_ExplicitVarSizeWithDummy[q37] * s_ExplicitVarSizeWithMarker_Values[q38], - s_ExplicitVarSizeWithDummy[q37] / s_ExplicitVarSizeWithMarker_Values[q38]; - int(1..3)]), - (s_ExplicitVarSizeWithDummy[q37] - s_ExplicitVarSizeWithMarker_Values[q38]) % 2 = 0; - int(1..5)]) - -> - min([s_ExplicitVarSizeWithDummy[q37] + s_ExplicitVarSizeWithMarker_Values[q38], - s_ExplicitVarSizeWithDummy[q37] - s_ExplicitVarSizeWithMarker_Values[q38], - s_ExplicitVarSizeWithDummy[q37] * s_ExplicitVarSizeWithMarker_Values[q38], - s_ExplicitVarSizeWithDummy[q37] / s_ExplicitVarSizeWithMarker_Values[q38]; - int(1..4)]) - <= conjure_aux1 - | q37 : int(1..4), q38 : int(1..4)]), - sum([toInt(and([s_ExplicitVarSizeWithDummy[q37] != 5, q38 <= s_ExplicitVarSizeWithMarker_Marker, - s_ExplicitVarSizeWithDummy[q37] != s_ExplicitVarSizeWithMarker_Values[q38], - allDiff([s_ExplicitVarSizeWithDummy[q37] + s_ExplicitVarSizeWithMarker_Values[q38], - s_ExplicitVarSizeWithDummy[q37] * s_ExplicitVarSizeWithMarker_Values[q38], - s_ExplicitVarSizeWithDummy[q37] / s_ExplicitVarSizeWithMarker_Values[q38]; - int(1..3)]), - (s_ExplicitVarSizeWithDummy[q37] - s_ExplicitVarSizeWithMarker_Values[q38]) % 2 = 0; - int(1..5)])) - | q37 : int(1..4), q38 : int(1..4)]) - > 0 - -> - or([and([s_ExplicitVarSizeWithDummy[q37] != 5, q38 <= s_ExplicitVarSizeWithMarker_Marker, - s_ExplicitVarSizeWithDummy[q37] != s_ExplicitVarSizeWithMarker_Values[q38], - allDiff([s_ExplicitVarSizeWithDummy[q37] + s_ExplicitVarSizeWithMarker_Values[q38], - s_ExplicitVarSizeWithDummy[q37] * s_ExplicitVarSizeWithMarker_Values[q38], - s_ExplicitVarSizeWithDummy[q37] / s_ExplicitVarSizeWithMarker_Values[q38]; - int(1..3)]), - (s_ExplicitVarSizeWithDummy[q37] - s_ExplicitVarSizeWithMarker_Values[q38]) % 2 = 0; - int(1..5)]) - /\ - min([s_ExplicitVarSizeWithDummy[q37] + s_ExplicitVarSizeWithMarker_Values[q38], - s_ExplicitVarSizeWithDummy[q37] - s_ExplicitVarSizeWithMarker_Values[q38], - s_ExplicitVarSizeWithDummy[q37] * s_ExplicitVarSizeWithMarker_Values[q38], - s_ExplicitVarSizeWithDummy[q37] / s_ExplicitVarSizeWithMarker_Values[q38]; - int(1..4)]) - = conjure_aux1 - | q37 : int(1..4), q38 : int(1..4)]), - sum([toInt(and([s_ExplicitVarSizeWithDummy[q37] != 5, q38 <= s_ExplicitVarSizeWithMarker_Marker, - s_ExplicitVarSizeWithDummy[q37] != s_ExplicitVarSizeWithMarker_Values[q38], - allDiff([s_ExplicitVarSizeWithDummy[q37] + s_ExplicitVarSizeWithMarker_Values[q38], - s_ExplicitVarSizeWithDummy[q37] * s_ExplicitVarSizeWithMarker_Values[q38], - s_ExplicitVarSizeWithDummy[q37] / s_ExplicitVarSizeWithMarker_Values[q38]; - int(1..3)]), - (s_ExplicitVarSizeWithDummy[q37] - s_ExplicitVarSizeWithMarker_Values[q38]) % 2 = 0; - int(1..5)])) - | q37 : int(1..4), q38 : int(1..4)]) - = 0 - -> conjure_aux1 = -20, - x = conjure_aux1, - sum([toInt(and([s_ExplicitVarSizeWithDummy[q37] != 5, q38 <= s_ExplicitVarSizeWithMarker_Marker, - s_ExplicitVarSizeWithDummy[q37] != s_ExplicitVarSizeWithMarker_Values[q38], - allDiff([s_ExplicitVarSizeWithDummy[q37] + s_ExplicitVarSizeWithMarker_Values[q38], - s_ExplicitVarSizeWithDummy[q37] * s_ExplicitVarSizeWithMarker_Values[q38], - s_ExplicitVarSizeWithDummy[q37] / s_ExplicitVarSizeWithMarker_Values[q38]; - int(1..3)]), - (s_ExplicitVarSizeWithDummy[q37] - s_ExplicitVarSizeWithMarker_Values[q38]) % 2 = 0; - int(1..5)])) - | q37 : int(1..4), q38 : int(1..4)]) - > 0, - and([s_ExplicitVarSizeWithDummy[q1] < s_ExplicitVarSizeWithDummy[q1 + 1] \/ s_ExplicitVarSizeWithDummy[q1] = 5 - | q1 : int(1..3)]), - and([s_ExplicitVarSizeWithDummy[q2] = 5 -> s_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..3)]), - and([q5 + 1 <= s_ExplicitVarSizeWithMarker_Marker -> - s_ExplicitVarSizeWithMarker_Values[q5] < s_ExplicitVarSizeWithMarker_Values[q5 + 1] - | q5 : int(1..3)]), - and([q6 > s_ExplicitVarSizeWithMarker_Marker -> s_ExplicitVarSizeWithMarker_Values[q6] = 1 | q6 : int(1..4)]), - and([q9 <= s_ExplicitVarSizeWithMarker_Marker -> - or([s_ExplicitVarSizeWithDummy[q11] != 5 /\ - s_ExplicitVarSizeWithDummy[q11] = s_ExplicitVarSizeWithMarker_Values[q9] - | q11 : int(1..4)]) - | q9 : int(1..4)]), - and([s_ExplicitVarSizeWithDummy[q13] != 5 -> - or([q15 <= s_ExplicitVarSizeWithMarker_Marker /\ - s_ExplicitVarSizeWithMarker_Values[q15] = s_ExplicitVarSizeWithDummy[q13] - | q15 : int(1..4)]) - | q13 : int(1..4)]), - and([s_ExplicitVarSizeWithFlags_Flags[q16 + 1] -> - s_ExplicitVarSizeWithFlags_Values[q16] < s_ExplicitVarSizeWithFlags_Values[q16 + 1] - | q16 : int(1..3)]), - and([s_ExplicitVarSizeWithFlags_Flags[q17] = false -> s_ExplicitVarSizeWithFlags_Values[q17] = 1 - | q17 : int(1..4)]), - and([s_ExplicitVarSizeWithFlags_Flags[q18 + 1] -> s_ExplicitVarSizeWithFlags_Flags[q18] | q18 : int(1..3)]), - and([s_ExplicitVarSizeWithFlags_Flags[q22] -> - or([s_ExplicitVarSizeWithDummy[q24] != 5 /\ - s_ExplicitVarSizeWithDummy[q24] = s_ExplicitVarSizeWithFlags_Values[q22] - | q24 : int(1..4)]) - | q22 : int(1..4)]), - and([s_ExplicitVarSizeWithDummy[q26] != 5 -> - or([s_ExplicitVarSizeWithFlags_Flags[q28] /\ - s_ExplicitVarSizeWithFlags_Values[q28] = s_ExplicitVarSizeWithDummy[q26] - | q28 : int(1..4)]) - | q26 : int(1..4)]), - and([s_ExplicitVarSizeWithFlags_Flags[q30] -> - or([q32 <= s_ExplicitVarSizeWithMarker_Marker /\ - s_ExplicitVarSizeWithMarker_Values[q32] = s_ExplicitVarSizeWithFlags_Values[q30] - | q32 : int(1..4)]) - | q30 : int(1..4)]), - and([q34 <= s_ExplicitVarSizeWithMarker_Marker -> - or([s_ExplicitVarSizeWithFlags_Flags[q36] /\ - s_ExplicitVarSizeWithFlags_Values[q36] = s_ExplicitVarSizeWithMarker_Values[q34] - | q36 : int(1..4)]) - | q34 : int(1..4)]) - diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_4_1-solution000001.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_4_1-solution000001.solution deleted file mode 100644 index 159a613983..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_2_4_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {2, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_4_1-solution000002.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_4_1-solution000002.solution deleted file mode 100644 index 40f3fd5c8f..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_2_4_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {2, 3, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_4_1-solution000003.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_4_1-solution000003.solution deleted file mode 100644 index 8b4ecbb66d..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_2_4_1-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 3} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_4_1-solution000004.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_4_1-solution000004.solution deleted file mode 100644 index 560dd0f2f7..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_2_4_1-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 3, 4} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_4_1-solution000005.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_4_1-solution000005.solution deleted file mode 100644 index 6eeacc9727..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_2_4_1-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_4_1-solution000006.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_4_1-solution000006.solution deleted file mode 100644 index 5963aac565..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_2_4_1-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 3} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_4_1-solution000007.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_4_1-solution000007.solution deleted file mode 100644 index bd956f44e3..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_2_4_1-solution000007.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 3, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_4_1.eprime b/tests/exhaustive/basic/comprehension_letting/expected/model_2_4_1.eprime deleted file mode 100644 index f8ee63e7f7..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_2_4_1.eprime +++ /dev/null @@ -1,105 +0,0 @@ -language ESSENCE' 1.0 - -find s_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -find s_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find s_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -find s_Occurrence: matrix indexed by [int(1..4)] of bool -letting let1 be -100 -find x: int(-100..100) -find conjure_aux1: int(-20..4) -branching on - [s_Occurrence, s_ExplicitVarSizeWithDummy, s_ExplicitVarSizeWithFlags_Flags, s_ExplicitVarSizeWithFlags_Values, x] -such that - and([and([s_ExplicitVarSizeWithDummy[q29] != 5, s_ExplicitVarSizeWithFlags_Flags[q30], - s_ExplicitVarSizeWithDummy[q29] != s_ExplicitVarSizeWithFlags_Values[q30], - allDiff([s_ExplicitVarSizeWithDummy[q29] + s_ExplicitVarSizeWithFlags_Values[q30], - s_ExplicitVarSizeWithDummy[q29] * s_ExplicitVarSizeWithFlags_Values[q30], - s_ExplicitVarSizeWithDummy[q29] / s_ExplicitVarSizeWithFlags_Values[q30]; - int(1..3)]), - (s_ExplicitVarSizeWithDummy[q29] - s_ExplicitVarSizeWithFlags_Values[q30]) % 2 = 0; - int(1..5)]) - -> - min([s_ExplicitVarSizeWithDummy[q29] + s_ExplicitVarSizeWithFlags_Values[q30], - s_ExplicitVarSizeWithDummy[q29] - s_ExplicitVarSizeWithFlags_Values[q30], - s_ExplicitVarSizeWithDummy[q29] * s_ExplicitVarSizeWithFlags_Values[q30], - s_ExplicitVarSizeWithDummy[q29] / s_ExplicitVarSizeWithFlags_Values[q30]; - int(1..4)]) - <= conjure_aux1 - | q29 : int(1..4), q30 : int(1..4)]), - sum([toInt(and([s_ExplicitVarSizeWithDummy[q29] != 5, s_ExplicitVarSizeWithFlags_Flags[q30], - s_ExplicitVarSizeWithDummy[q29] != s_ExplicitVarSizeWithFlags_Values[q30], - allDiff([s_ExplicitVarSizeWithDummy[q29] + s_ExplicitVarSizeWithFlags_Values[q30], - s_ExplicitVarSizeWithDummy[q29] * s_ExplicitVarSizeWithFlags_Values[q30], - s_ExplicitVarSizeWithDummy[q29] / s_ExplicitVarSizeWithFlags_Values[q30]; - int(1..3)]), - (s_ExplicitVarSizeWithDummy[q29] - s_ExplicitVarSizeWithFlags_Values[q30]) % 2 = 0; - int(1..5)])) - | q29 : int(1..4), q30 : int(1..4)]) - > 0 - -> - or([and([s_ExplicitVarSizeWithDummy[q29] != 5, s_ExplicitVarSizeWithFlags_Flags[q30], - s_ExplicitVarSizeWithDummy[q29] != s_ExplicitVarSizeWithFlags_Values[q30], - allDiff([s_ExplicitVarSizeWithDummy[q29] + s_ExplicitVarSizeWithFlags_Values[q30], - s_ExplicitVarSizeWithDummy[q29] * s_ExplicitVarSizeWithFlags_Values[q30], - s_ExplicitVarSizeWithDummy[q29] / s_ExplicitVarSizeWithFlags_Values[q30]; - int(1..3)]), - (s_ExplicitVarSizeWithDummy[q29] - s_ExplicitVarSizeWithFlags_Values[q30]) % 2 = 0; - int(1..5)]) - /\ - min([s_ExplicitVarSizeWithDummy[q29] + s_ExplicitVarSizeWithFlags_Values[q30], - s_ExplicitVarSizeWithDummy[q29] - s_ExplicitVarSizeWithFlags_Values[q30], - s_ExplicitVarSizeWithDummy[q29] * s_ExplicitVarSizeWithFlags_Values[q30], - s_ExplicitVarSizeWithDummy[q29] / s_ExplicitVarSizeWithFlags_Values[q30]; - int(1..4)]) - = conjure_aux1 - | q29 : int(1..4), q30 : int(1..4)]), - sum([toInt(and([s_ExplicitVarSizeWithDummy[q29] != 5, s_ExplicitVarSizeWithFlags_Flags[q30], - s_ExplicitVarSizeWithDummy[q29] != s_ExplicitVarSizeWithFlags_Values[q30], - allDiff([s_ExplicitVarSizeWithDummy[q29] + s_ExplicitVarSizeWithFlags_Values[q30], - s_ExplicitVarSizeWithDummy[q29] * s_ExplicitVarSizeWithFlags_Values[q30], - s_ExplicitVarSizeWithDummy[q29] / s_ExplicitVarSizeWithFlags_Values[q30]; - int(1..3)]), - (s_ExplicitVarSizeWithDummy[q29] - s_ExplicitVarSizeWithFlags_Values[q30]) % 2 = 0; - int(1..5)])) - | q29 : int(1..4), q30 : int(1..4)]) - = 0 - -> conjure_aux1 = -20, - x = conjure_aux1, - sum([toInt(and([s_ExplicitVarSizeWithDummy[q29] != 5, s_ExplicitVarSizeWithFlags_Flags[q30], - s_ExplicitVarSizeWithDummy[q29] != s_ExplicitVarSizeWithFlags_Values[q30], - allDiff([s_ExplicitVarSizeWithDummy[q29] + s_ExplicitVarSizeWithFlags_Values[q30], - s_ExplicitVarSizeWithDummy[q29] * s_ExplicitVarSizeWithFlags_Values[q30], - s_ExplicitVarSizeWithDummy[q29] / s_ExplicitVarSizeWithFlags_Values[q30]; - int(1..3)]), - (s_ExplicitVarSizeWithDummy[q29] - s_ExplicitVarSizeWithFlags_Values[q30]) % 2 = 0; - int(1..5)])) - | q29 : int(1..4), q30 : int(1..4)]) - > 0, - and([s_ExplicitVarSizeWithDummy[q1] < s_ExplicitVarSizeWithDummy[q1 + 1] \/ s_ExplicitVarSizeWithDummy[q1] = 5 - | q1 : int(1..3)]), - and([s_ExplicitVarSizeWithDummy[q2] = 5 -> s_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..3)]), - and([s_ExplicitVarSizeWithFlags_Flags[q5 + 1] -> - s_ExplicitVarSizeWithFlags_Values[q5] < s_ExplicitVarSizeWithFlags_Values[q5 + 1] - | q5 : int(1..3)]), - and([s_ExplicitVarSizeWithFlags_Flags[q6] = false -> s_ExplicitVarSizeWithFlags_Values[q6] = 1 | q6 : int(1..4)]), - and([s_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> s_ExplicitVarSizeWithFlags_Flags[q7] | q7 : int(1..3)]), - and([s_ExplicitVarSizeWithFlags_Flags[q11] -> - or([s_ExplicitVarSizeWithDummy[q13] != 5 /\ - s_ExplicitVarSizeWithDummy[q13] = s_ExplicitVarSizeWithFlags_Values[q11] - | q13 : int(1..4)]) - | q11 : int(1..4)]), - and([s_ExplicitVarSizeWithDummy[q15] != 5 -> - or([s_ExplicitVarSizeWithFlags_Flags[q17] /\ - s_ExplicitVarSizeWithFlags_Values[q17] = s_ExplicitVarSizeWithDummy[q15] - | q17 : int(1..4)]) - | q15 : int(1..4)]), - and([s_Occurrence[q19] -> - or([s_ExplicitVarSizeWithDummy[q21] != 5 /\ s_ExplicitVarSizeWithDummy[q21] = q19 | q21 : int(1..4)]) - | q19 : int(1..4)]), - and([s_ExplicitVarSizeWithDummy[q23] != 5 -> s_Occurrence[s_ExplicitVarSizeWithDummy[q23]] | q23 : int(1..4)]), - and([s_Occurrence[q24] -> - or([s_ExplicitVarSizeWithFlags_Flags[q26] /\ s_ExplicitVarSizeWithFlags_Values[q26] = q24 | q26 : int(1..4)]) - | q24 : int(1..4)]), - and([s_ExplicitVarSizeWithFlags_Flags[q28] -> s_Occurrence[s_ExplicitVarSizeWithFlags_Values[q28]] - | q28 : int(1..4)]) - diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_4_2-solution000001.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_4_2-solution000001.solution deleted file mode 100644 index 8b4ecbb66d..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_2_4_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 3} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_4_2-solution000002.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_4_2-solution000002.solution deleted file mode 100644 index 159a613983..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_2_4_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {2, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_4_2-solution000003.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_4_2-solution000003.solution deleted file mode 100644 index 5963aac565..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_2_4_2-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 3} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_4_2-solution000004.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_4_2-solution000004.solution deleted file mode 100644 index 6eeacc9727..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_2_4_2-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_4_2-solution000005.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_4_2-solution000005.solution deleted file mode 100644 index 560dd0f2f7..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_2_4_2-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 3, 4} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_4_2-solution000006.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_4_2-solution000006.solution deleted file mode 100644 index 40f3fd5c8f..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_2_4_2-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {2, 3, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_4_2-solution000007.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_4_2-solution000007.solution deleted file mode 100644 index bd956f44e3..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_2_4_2-solution000007.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 3, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_4_2.eprime b/tests/exhaustive/basic/comprehension_letting/expected/model_2_4_2.eprime deleted file mode 100644 index fcc240b9e7..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_2_4_2.eprime +++ /dev/null @@ -1,94 +0,0 @@ -language ESSENCE' 1.0 - -find s_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -find s_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find s_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -letting let1 be -100 -find x: int(-100..100) -find conjure_aux1: int(-20..4) -branching on [s_ExplicitVarSizeWithFlags_Flags, s_ExplicitVarSizeWithFlags_Values, s_ExplicitVarSizeWithDummy, x] -such that - and([and([s_ExplicitVarSizeWithDummy[q18] != 5, s_ExplicitVarSizeWithFlags_Flags[q19], - s_ExplicitVarSizeWithDummy[q18] != s_ExplicitVarSizeWithFlags_Values[q19], - allDiff([s_ExplicitVarSizeWithDummy[q18] + s_ExplicitVarSizeWithFlags_Values[q19], - s_ExplicitVarSizeWithDummy[q18] * s_ExplicitVarSizeWithFlags_Values[q19], - s_ExplicitVarSizeWithDummy[q18] / s_ExplicitVarSizeWithFlags_Values[q19]; - int(1..3)]), - (s_ExplicitVarSizeWithDummy[q18] - s_ExplicitVarSizeWithFlags_Values[q19]) % 2 = 0; - int(1..5)]) - -> - min([s_ExplicitVarSizeWithDummy[q18] + s_ExplicitVarSizeWithFlags_Values[q19], - s_ExplicitVarSizeWithDummy[q18] - s_ExplicitVarSizeWithFlags_Values[q19], - s_ExplicitVarSizeWithDummy[q18] * s_ExplicitVarSizeWithFlags_Values[q19], - s_ExplicitVarSizeWithDummy[q18] / s_ExplicitVarSizeWithFlags_Values[q19]; - int(1..4)]) - <= conjure_aux1 - | q18 : int(1..4), q19 : int(1..4)]), - sum([toInt(and([s_ExplicitVarSizeWithDummy[q18] != 5, s_ExplicitVarSizeWithFlags_Flags[q19], - s_ExplicitVarSizeWithDummy[q18] != s_ExplicitVarSizeWithFlags_Values[q19], - allDiff([s_ExplicitVarSizeWithDummy[q18] + s_ExplicitVarSizeWithFlags_Values[q19], - s_ExplicitVarSizeWithDummy[q18] * s_ExplicitVarSizeWithFlags_Values[q19], - s_ExplicitVarSizeWithDummy[q18] / s_ExplicitVarSizeWithFlags_Values[q19]; - int(1..3)]), - (s_ExplicitVarSizeWithDummy[q18] - s_ExplicitVarSizeWithFlags_Values[q19]) % 2 = 0; - int(1..5)])) - | q18 : int(1..4), q19 : int(1..4)]) - > 0 - -> - or([and([s_ExplicitVarSizeWithDummy[q18] != 5, s_ExplicitVarSizeWithFlags_Flags[q19], - s_ExplicitVarSizeWithDummy[q18] != s_ExplicitVarSizeWithFlags_Values[q19], - allDiff([s_ExplicitVarSizeWithDummy[q18] + s_ExplicitVarSizeWithFlags_Values[q19], - s_ExplicitVarSizeWithDummy[q18] * s_ExplicitVarSizeWithFlags_Values[q19], - s_ExplicitVarSizeWithDummy[q18] / s_ExplicitVarSizeWithFlags_Values[q19]; - int(1..3)]), - (s_ExplicitVarSizeWithDummy[q18] - s_ExplicitVarSizeWithFlags_Values[q19]) % 2 = 0; - int(1..5)]) - /\ - min([s_ExplicitVarSizeWithDummy[q18] + s_ExplicitVarSizeWithFlags_Values[q19], - s_ExplicitVarSizeWithDummy[q18] - s_ExplicitVarSizeWithFlags_Values[q19], - s_ExplicitVarSizeWithDummy[q18] * s_ExplicitVarSizeWithFlags_Values[q19], - s_ExplicitVarSizeWithDummy[q18] / s_ExplicitVarSizeWithFlags_Values[q19]; - int(1..4)]) - = conjure_aux1 - | q18 : int(1..4), q19 : int(1..4)]), - sum([toInt(and([s_ExplicitVarSizeWithDummy[q18] != 5, s_ExplicitVarSizeWithFlags_Flags[q19], - s_ExplicitVarSizeWithDummy[q18] != s_ExplicitVarSizeWithFlags_Values[q19], - allDiff([s_ExplicitVarSizeWithDummy[q18] + s_ExplicitVarSizeWithFlags_Values[q19], - s_ExplicitVarSizeWithDummy[q18] * s_ExplicitVarSizeWithFlags_Values[q19], - s_ExplicitVarSizeWithDummy[q18] / s_ExplicitVarSizeWithFlags_Values[q19]; - int(1..3)]), - (s_ExplicitVarSizeWithDummy[q18] - s_ExplicitVarSizeWithFlags_Values[q19]) % 2 = 0; - int(1..5)])) - | q18 : int(1..4), q19 : int(1..4)]) - = 0 - -> conjure_aux1 = -20, - x = conjure_aux1, - sum([toInt(and([s_ExplicitVarSizeWithDummy[q18] != 5, s_ExplicitVarSizeWithFlags_Flags[q19], - s_ExplicitVarSizeWithDummy[q18] != s_ExplicitVarSizeWithFlags_Values[q19], - allDiff([s_ExplicitVarSizeWithDummy[q18] + s_ExplicitVarSizeWithFlags_Values[q19], - s_ExplicitVarSizeWithDummy[q18] * s_ExplicitVarSizeWithFlags_Values[q19], - s_ExplicitVarSizeWithDummy[q18] / s_ExplicitVarSizeWithFlags_Values[q19]; - int(1..3)]), - (s_ExplicitVarSizeWithDummy[q18] - s_ExplicitVarSizeWithFlags_Values[q19]) % 2 = 0; - int(1..5)])) - | q18 : int(1..4), q19 : int(1..4)]) - > 0, - and([s_ExplicitVarSizeWithDummy[q1] < s_ExplicitVarSizeWithDummy[q1 + 1] \/ s_ExplicitVarSizeWithDummy[q1] = 5 - | q1 : int(1..3)]), - and([s_ExplicitVarSizeWithDummy[q2] = 5 -> s_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..3)]), - and([s_ExplicitVarSizeWithFlags_Flags[q5 + 1] -> - s_ExplicitVarSizeWithFlags_Values[q5] < s_ExplicitVarSizeWithFlags_Values[q5 + 1] - | q5 : int(1..3)]), - and([s_ExplicitVarSizeWithFlags_Flags[q6] = false -> s_ExplicitVarSizeWithFlags_Values[q6] = 1 | q6 : int(1..4)]), - and([s_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> s_ExplicitVarSizeWithFlags_Flags[q7] | q7 : int(1..3)]), - and([s_ExplicitVarSizeWithFlags_Flags[q11] -> - or([s_ExplicitVarSizeWithDummy[q13] != 5 /\ - s_ExplicitVarSizeWithDummy[q13] = s_ExplicitVarSizeWithFlags_Values[q11] - | q13 : int(1..4)]) - | q11 : int(1..4)]), - and([s_ExplicitVarSizeWithDummy[q15] != 5 -> - or([s_ExplicitVarSizeWithFlags_Flags[q17] /\ - s_ExplicitVarSizeWithFlags_Values[q17] = s_ExplicitVarSizeWithDummy[q15] - | q17 : int(1..4)]) - | q15 : int(1..4)]) - diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_4_3-solution000001.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_4_3-solution000001.solution deleted file mode 100644 index 8b4ecbb66d..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_2_4_3-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 3} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_4_3-solution000002.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_4_3-solution000002.solution deleted file mode 100644 index 159a613983..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_2_4_3-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {2, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_4_3-solution000003.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_4_3-solution000003.solution deleted file mode 100644 index 5963aac565..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_2_4_3-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 3} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_4_3-solution000004.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_4_3-solution000004.solution deleted file mode 100644 index 6eeacc9727..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_2_4_3-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_4_3-solution000005.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_4_3-solution000005.solution deleted file mode 100644 index 560dd0f2f7..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_2_4_3-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 3, 4} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_4_3-solution000006.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_4_3-solution000006.solution deleted file mode 100644 index 40f3fd5c8f..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_2_4_3-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {2, 3, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_4_3-solution000007.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_4_3-solution000007.solution deleted file mode 100644 index bd956f44e3..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_2_4_3-solution000007.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 3, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_4_3.eprime b/tests/exhaustive/basic/comprehension_letting/expected/model_2_4_3.eprime deleted file mode 100644 index aa5a1b0079..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_2_4_3.eprime +++ /dev/null @@ -1,122 +0,0 @@ -language ESSENCE' 1.0 - -find s_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -find s_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find s_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -find s_ExplicitVarSizeWithMarker_Marker: int(0..4) -find s_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -letting let1 be -100 -find x: int(-100..100) -find conjure_aux1: int(-20..4) -branching on - [s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithMarker_Values, s_ExplicitVarSizeWithDummy, - s_ExplicitVarSizeWithFlags_Flags, s_ExplicitVarSizeWithFlags_Values, x] -such that - and([and([s_ExplicitVarSizeWithDummy[q37] != 5, s_ExplicitVarSizeWithFlags_Flags[q38], - s_ExplicitVarSizeWithDummy[q37] != s_ExplicitVarSizeWithFlags_Values[q38], - allDiff([s_ExplicitVarSizeWithDummy[q37] + s_ExplicitVarSizeWithFlags_Values[q38], - s_ExplicitVarSizeWithDummy[q37] * s_ExplicitVarSizeWithFlags_Values[q38], - s_ExplicitVarSizeWithDummy[q37] / s_ExplicitVarSizeWithFlags_Values[q38]; - int(1..3)]), - (s_ExplicitVarSizeWithDummy[q37] - s_ExplicitVarSizeWithFlags_Values[q38]) % 2 = 0; - int(1..5)]) - -> - min([s_ExplicitVarSizeWithDummy[q37] + s_ExplicitVarSizeWithFlags_Values[q38], - s_ExplicitVarSizeWithDummy[q37] - s_ExplicitVarSizeWithFlags_Values[q38], - s_ExplicitVarSizeWithDummy[q37] * s_ExplicitVarSizeWithFlags_Values[q38], - s_ExplicitVarSizeWithDummy[q37] / s_ExplicitVarSizeWithFlags_Values[q38]; - int(1..4)]) - <= conjure_aux1 - | q37 : int(1..4), q38 : int(1..4)]), - sum([toInt(and([s_ExplicitVarSizeWithDummy[q37] != 5, s_ExplicitVarSizeWithFlags_Flags[q38], - s_ExplicitVarSizeWithDummy[q37] != s_ExplicitVarSizeWithFlags_Values[q38], - allDiff([s_ExplicitVarSizeWithDummy[q37] + s_ExplicitVarSizeWithFlags_Values[q38], - s_ExplicitVarSizeWithDummy[q37] * s_ExplicitVarSizeWithFlags_Values[q38], - s_ExplicitVarSizeWithDummy[q37] / s_ExplicitVarSizeWithFlags_Values[q38]; - int(1..3)]), - (s_ExplicitVarSizeWithDummy[q37] - s_ExplicitVarSizeWithFlags_Values[q38]) % 2 = 0; - int(1..5)])) - | q37 : int(1..4), q38 : int(1..4)]) - > 0 - -> - or([and([s_ExplicitVarSizeWithDummy[q37] != 5, s_ExplicitVarSizeWithFlags_Flags[q38], - s_ExplicitVarSizeWithDummy[q37] != s_ExplicitVarSizeWithFlags_Values[q38], - allDiff([s_ExplicitVarSizeWithDummy[q37] + s_ExplicitVarSizeWithFlags_Values[q38], - s_ExplicitVarSizeWithDummy[q37] * s_ExplicitVarSizeWithFlags_Values[q38], - s_ExplicitVarSizeWithDummy[q37] / s_ExplicitVarSizeWithFlags_Values[q38]; - int(1..3)]), - (s_ExplicitVarSizeWithDummy[q37] - s_ExplicitVarSizeWithFlags_Values[q38]) % 2 = 0; - int(1..5)]) - /\ - min([s_ExplicitVarSizeWithDummy[q37] + s_ExplicitVarSizeWithFlags_Values[q38], - s_ExplicitVarSizeWithDummy[q37] - s_ExplicitVarSizeWithFlags_Values[q38], - s_ExplicitVarSizeWithDummy[q37] * s_ExplicitVarSizeWithFlags_Values[q38], - s_ExplicitVarSizeWithDummy[q37] / s_ExplicitVarSizeWithFlags_Values[q38]; - int(1..4)]) - = conjure_aux1 - | q37 : int(1..4), q38 : int(1..4)]), - sum([toInt(and([s_ExplicitVarSizeWithDummy[q37] != 5, s_ExplicitVarSizeWithFlags_Flags[q38], - s_ExplicitVarSizeWithDummy[q37] != s_ExplicitVarSizeWithFlags_Values[q38], - allDiff([s_ExplicitVarSizeWithDummy[q37] + s_ExplicitVarSizeWithFlags_Values[q38], - s_ExplicitVarSizeWithDummy[q37] * s_ExplicitVarSizeWithFlags_Values[q38], - s_ExplicitVarSizeWithDummy[q37] / s_ExplicitVarSizeWithFlags_Values[q38]; - int(1..3)]), - (s_ExplicitVarSizeWithDummy[q37] - s_ExplicitVarSizeWithFlags_Values[q38]) % 2 = 0; - int(1..5)])) - | q37 : int(1..4), q38 : int(1..4)]) - = 0 - -> conjure_aux1 = -20, - x = conjure_aux1, - sum([toInt(and([s_ExplicitVarSizeWithDummy[q37] != 5, s_ExplicitVarSizeWithFlags_Flags[q38], - s_ExplicitVarSizeWithDummy[q37] != s_ExplicitVarSizeWithFlags_Values[q38], - allDiff([s_ExplicitVarSizeWithDummy[q37] + s_ExplicitVarSizeWithFlags_Values[q38], - s_ExplicitVarSizeWithDummy[q37] * s_ExplicitVarSizeWithFlags_Values[q38], - s_ExplicitVarSizeWithDummy[q37] / s_ExplicitVarSizeWithFlags_Values[q38]; - int(1..3)]), - (s_ExplicitVarSizeWithDummy[q37] - s_ExplicitVarSizeWithFlags_Values[q38]) % 2 = 0; - int(1..5)])) - | q37 : int(1..4), q38 : int(1..4)]) - > 0, - and([s_ExplicitVarSizeWithDummy[q1] < s_ExplicitVarSizeWithDummy[q1 + 1] \/ s_ExplicitVarSizeWithDummy[q1] = 5 - | q1 : int(1..3)]), - and([s_ExplicitVarSizeWithDummy[q2] = 5 -> s_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..3)]), - and([s_ExplicitVarSizeWithFlags_Flags[q5 + 1] -> - s_ExplicitVarSizeWithFlags_Values[q5] < s_ExplicitVarSizeWithFlags_Values[q5 + 1] - | q5 : int(1..3)]), - and([s_ExplicitVarSizeWithFlags_Flags[q6] = false -> s_ExplicitVarSizeWithFlags_Values[q6] = 1 | q6 : int(1..4)]), - and([s_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> s_ExplicitVarSizeWithFlags_Flags[q7] | q7 : int(1..3)]), - and([s_ExplicitVarSizeWithFlags_Flags[q11] -> - or([s_ExplicitVarSizeWithDummy[q13] != 5 /\ - s_ExplicitVarSizeWithDummy[q13] = s_ExplicitVarSizeWithFlags_Values[q11] - | q13 : int(1..4)]) - | q11 : int(1..4)]), - and([s_ExplicitVarSizeWithDummy[q15] != 5 -> - or([s_ExplicitVarSizeWithFlags_Flags[q17] /\ - s_ExplicitVarSizeWithFlags_Values[q17] = s_ExplicitVarSizeWithDummy[q15] - | q17 : int(1..4)]) - | q15 : int(1..4)]), - and([q18 + 1 <= s_ExplicitVarSizeWithMarker_Marker -> - s_ExplicitVarSizeWithMarker_Values[q18] < s_ExplicitVarSizeWithMarker_Values[q18 + 1] - | q18 : int(1..3)]), - and([q19 > s_ExplicitVarSizeWithMarker_Marker -> s_ExplicitVarSizeWithMarker_Values[q19] = 1 | q19 : int(1..4)]), - and([q22 <= s_ExplicitVarSizeWithMarker_Marker -> - or([s_ExplicitVarSizeWithDummy[q24] != 5 /\ - s_ExplicitVarSizeWithDummy[q24] = s_ExplicitVarSizeWithMarker_Values[q22] - | q24 : int(1..4)]) - | q22 : int(1..4)]), - and([s_ExplicitVarSizeWithDummy[q26] != 5 -> - or([q28 <= s_ExplicitVarSizeWithMarker_Marker /\ - s_ExplicitVarSizeWithMarker_Values[q28] = s_ExplicitVarSizeWithDummy[q26] - | q28 : int(1..4)]) - | q26 : int(1..4)]), - and([q30 <= s_ExplicitVarSizeWithMarker_Marker -> - or([s_ExplicitVarSizeWithFlags_Flags[q32] /\ - s_ExplicitVarSizeWithFlags_Values[q32] = s_ExplicitVarSizeWithMarker_Values[q30] - | q32 : int(1..4)]) - | q30 : int(1..4)]), - and([s_ExplicitVarSizeWithFlags_Flags[q34] -> - or([q36 <= s_ExplicitVarSizeWithMarker_Marker /\ - s_ExplicitVarSizeWithMarker_Values[q36] = s_ExplicitVarSizeWithFlags_Values[q34] - | q36 : int(1..4)]) - | q34 : int(1..4)]) - diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_4_4-solution000001.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_4_4-solution000001.solution deleted file mode 100644 index 8b4ecbb66d..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_2_4_4-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 3} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_4_4-solution000002.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_4_4-solution000002.solution deleted file mode 100644 index 159a613983..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_2_4_4-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {2, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_4_4-solution000003.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_4_4-solution000003.solution deleted file mode 100644 index 5963aac565..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_2_4_4-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 3} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_4_4-solution000004.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_4_4-solution000004.solution deleted file mode 100644 index 6eeacc9727..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_2_4_4-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_4_4-solution000005.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_4_4-solution000005.solution deleted file mode 100644 index 560dd0f2f7..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_2_4_4-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 3, 4} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_4_4-solution000006.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_4_4-solution000006.solution deleted file mode 100644 index 40f3fd5c8f..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_2_4_4-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {2, 3, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_4_4-solution000007.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_4_4-solution000007.solution deleted file mode 100644 index bd956f44e3..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_2_4_4-solution000007.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 3, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_4_4.eprime b/tests/exhaustive/basic/comprehension_letting/expected/model_2_4_4.eprime deleted file mode 100644 index fcc240b9e7..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_2_4_4.eprime +++ /dev/null @@ -1,94 +0,0 @@ -language ESSENCE' 1.0 - -find s_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -find s_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find s_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -letting let1 be -100 -find x: int(-100..100) -find conjure_aux1: int(-20..4) -branching on [s_ExplicitVarSizeWithFlags_Flags, s_ExplicitVarSizeWithFlags_Values, s_ExplicitVarSizeWithDummy, x] -such that - and([and([s_ExplicitVarSizeWithDummy[q18] != 5, s_ExplicitVarSizeWithFlags_Flags[q19], - s_ExplicitVarSizeWithDummy[q18] != s_ExplicitVarSizeWithFlags_Values[q19], - allDiff([s_ExplicitVarSizeWithDummy[q18] + s_ExplicitVarSizeWithFlags_Values[q19], - s_ExplicitVarSizeWithDummy[q18] * s_ExplicitVarSizeWithFlags_Values[q19], - s_ExplicitVarSizeWithDummy[q18] / s_ExplicitVarSizeWithFlags_Values[q19]; - int(1..3)]), - (s_ExplicitVarSizeWithDummy[q18] - s_ExplicitVarSizeWithFlags_Values[q19]) % 2 = 0; - int(1..5)]) - -> - min([s_ExplicitVarSizeWithDummy[q18] + s_ExplicitVarSizeWithFlags_Values[q19], - s_ExplicitVarSizeWithDummy[q18] - s_ExplicitVarSizeWithFlags_Values[q19], - s_ExplicitVarSizeWithDummy[q18] * s_ExplicitVarSizeWithFlags_Values[q19], - s_ExplicitVarSizeWithDummy[q18] / s_ExplicitVarSizeWithFlags_Values[q19]; - int(1..4)]) - <= conjure_aux1 - | q18 : int(1..4), q19 : int(1..4)]), - sum([toInt(and([s_ExplicitVarSizeWithDummy[q18] != 5, s_ExplicitVarSizeWithFlags_Flags[q19], - s_ExplicitVarSizeWithDummy[q18] != s_ExplicitVarSizeWithFlags_Values[q19], - allDiff([s_ExplicitVarSizeWithDummy[q18] + s_ExplicitVarSizeWithFlags_Values[q19], - s_ExplicitVarSizeWithDummy[q18] * s_ExplicitVarSizeWithFlags_Values[q19], - s_ExplicitVarSizeWithDummy[q18] / s_ExplicitVarSizeWithFlags_Values[q19]; - int(1..3)]), - (s_ExplicitVarSizeWithDummy[q18] - s_ExplicitVarSizeWithFlags_Values[q19]) % 2 = 0; - int(1..5)])) - | q18 : int(1..4), q19 : int(1..4)]) - > 0 - -> - or([and([s_ExplicitVarSizeWithDummy[q18] != 5, s_ExplicitVarSizeWithFlags_Flags[q19], - s_ExplicitVarSizeWithDummy[q18] != s_ExplicitVarSizeWithFlags_Values[q19], - allDiff([s_ExplicitVarSizeWithDummy[q18] + s_ExplicitVarSizeWithFlags_Values[q19], - s_ExplicitVarSizeWithDummy[q18] * s_ExplicitVarSizeWithFlags_Values[q19], - s_ExplicitVarSizeWithDummy[q18] / s_ExplicitVarSizeWithFlags_Values[q19]; - int(1..3)]), - (s_ExplicitVarSizeWithDummy[q18] - s_ExplicitVarSizeWithFlags_Values[q19]) % 2 = 0; - int(1..5)]) - /\ - min([s_ExplicitVarSizeWithDummy[q18] + s_ExplicitVarSizeWithFlags_Values[q19], - s_ExplicitVarSizeWithDummy[q18] - s_ExplicitVarSizeWithFlags_Values[q19], - s_ExplicitVarSizeWithDummy[q18] * s_ExplicitVarSizeWithFlags_Values[q19], - s_ExplicitVarSizeWithDummy[q18] / s_ExplicitVarSizeWithFlags_Values[q19]; - int(1..4)]) - = conjure_aux1 - | q18 : int(1..4), q19 : int(1..4)]), - sum([toInt(and([s_ExplicitVarSizeWithDummy[q18] != 5, s_ExplicitVarSizeWithFlags_Flags[q19], - s_ExplicitVarSizeWithDummy[q18] != s_ExplicitVarSizeWithFlags_Values[q19], - allDiff([s_ExplicitVarSizeWithDummy[q18] + s_ExplicitVarSizeWithFlags_Values[q19], - s_ExplicitVarSizeWithDummy[q18] * s_ExplicitVarSizeWithFlags_Values[q19], - s_ExplicitVarSizeWithDummy[q18] / s_ExplicitVarSizeWithFlags_Values[q19]; - int(1..3)]), - (s_ExplicitVarSizeWithDummy[q18] - s_ExplicitVarSizeWithFlags_Values[q19]) % 2 = 0; - int(1..5)])) - | q18 : int(1..4), q19 : int(1..4)]) - = 0 - -> conjure_aux1 = -20, - x = conjure_aux1, - sum([toInt(and([s_ExplicitVarSizeWithDummy[q18] != 5, s_ExplicitVarSizeWithFlags_Flags[q19], - s_ExplicitVarSizeWithDummy[q18] != s_ExplicitVarSizeWithFlags_Values[q19], - allDiff([s_ExplicitVarSizeWithDummy[q18] + s_ExplicitVarSizeWithFlags_Values[q19], - s_ExplicitVarSizeWithDummy[q18] * s_ExplicitVarSizeWithFlags_Values[q19], - s_ExplicitVarSizeWithDummy[q18] / s_ExplicitVarSizeWithFlags_Values[q19]; - int(1..3)]), - (s_ExplicitVarSizeWithDummy[q18] - s_ExplicitVarSizeWithFlags_Values[q19]) % 2 = 0; - int(1..5)])) - | q18 : int(1..4), q19 : int(1..4)]) - > 0, - and([s_ExplicitVarSizeWithDummy[q1] < s_ExplicitVarSizeWithDummy[q1 + 1] \/ s_ExplicitVarSizeWithDummy[q1] = 5 - | q1 : int(1..3)]), - and([s_ExplicitVarSizeWithDummy[q2] = 5 -> s_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..3)]), - and([s_ExplicitVarSizeWithFlags_Flags[q5 + 1] -> - s_ExplicitVarSizeWithFlags_Values[q5] < s_ExplicitVarSizeWithFlags_Values[q5 + 1] - | q5 : int(1..3)]), - and([s_ExplicitVarSizeWithFlags_Flags[q6] = false -> s_ExplicitVarSizeWithFlags_Values[q6] = 1 | q6 : int(1..4)]), - and([s_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> s_ExplicitVarSizeWithFlags_Flags[q7] | q7 : int(1..3)]), - and([s_ExplicitVarSizeWithFlags_Flags[q11] -> - or([s_ExplicitVarSizeWithDummy[q13] != 5 /\ - s_ExplicitVarSizeWithDummy[q13] = s_ExplicitVarSizeWithFlags_Values[q11] - | q13 : int(1..4)]) - | q11 : int(1..4)]), - and([s_ExplicitVarSizeWithDummy[q15] != 5 -> - or([s_ExplicitVarSizeWithFlags_Flags[q17] /\ - s_ExplicitVarSizeWithFlags_Values[q17] = s_ExplicitVarSizeWithDummy[q15] - | q17 : int(1..4)]) - | q15 : int(1..4)]) - diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_1_1-solution000001.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_1_1-solution000001.solution deleted file mode 100644 index 159a613983..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_3_1_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {2, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_1_1-solution000002.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_1_1-solution000002.solution deleted file mode 100644 index 40f3fd5c8f..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_3_1_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {2, 3, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_1_1-solution000003.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_1_1-solution000003.solution deleted file mode 100644 index 8b4ecbb66d..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_3_1_1-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 3} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_1_1-solution000004.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_1_1-solution000004.solution deleted file mode 100644 index 560dd0f2f7..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_3_1_1-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 3, 4} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_1_1-solution000005.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_1_1-solution000005.solution deleted file mode 100644 index 6eeacc9727..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_3_1_1-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_1_1-solution000006.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_1_1-solution000006.solution deleted file mode 100644 index 5963aac565..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_3_1_1-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 3} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_1_1-solution000007.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_1_1-solution000007.solution deleted file mode 100644 index bd956f44e3..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_3_1_1-solution000007.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 3, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_1_1.eprime b/tests/exhaustive/basic/comprehension_letting/expected/model_3_1_1.eprime deleted file mode 100644 index 73444ebdb1..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_3_1_1.eprime +++ /dev/null @@ -1,75 +0,0 @@ -language ESSENCE' 1.0 - -find s_ExplicitVarSizeWithMarker_Marker: int(0..4) -find s_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -find s_Occurrence: matrix indexed by [int(1..4)] of bool -letting let1 be -100 -find x: int(-100..100) -find conjure_aux1: int(-16..3) -branching on [s_Occurrence, s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithMarker_Values, x] -such that - and([and([q5 <= s_ExplicitVarSizeWithMarker_Marker, s_Occurrence[j], s_ExplicitVarSizeWithMarker_Values[q5] != j, - allDiff([s_ExplicitVarSizeWithMarker_Values[q5] + j, s_ExplicitVarSizeWithMarker_Values[q5] * j, - s_ExplicitVarSizeWithMarker_Values[q5] / j; - int(1..3)]), - (s_ExplicitVarSizeWithMarker_Values[q5] - j) % 2 = 0; - int(1..5)]) - -> - min([s_ExplicitVarSizeWithMarker_Values[q5] + j, s_ExplicitVarSizeWithMarker_Values[q5] - j, - s_ExplicitVarSizeWithMarker_Values[q5] * j, s_ExplicitVarSizeWithMarker_Values[q5] / j; - int(1..4)]) - <= conjure_aux1 - | q5 : int(1..4), j : int(1..4)]), - sum([toInt(and([q5 <= s_ExplicitVarSizeWithMarker_Marker, s_Occurrence[j], - s_ExplicitVarSizeWithMarker_Values[q5] != j, - allDiff([s_ExplicitVarSizeWithMarker_Values[q5] + j, s_ExplicitVarSizeWithMarker_Values[q5] * j, - s_ExplicitVarSizeWithMarker_Values[q5] / j; - int(1..3)]), - (s_ExplicitVarSizeWithMarker_Values[q5] - j) % 2 = 0; - int(1..5)])) - | q5 : int(1..4), j : int(1..4)]) - > 0 - -> - or([and([q5 <= s_ExplicitVarSizeWithMarker_Marker, s_Occurrence[j], s_ExplicitVarSizeWithMarker_Values[q5] != j, - allDiff([s_ExplicitVarSizeWithMarker_Values[q5] + j, s_ExplicitVarSizeWithMarker_Values[q5] * j, - s_ExplicitVarSizeWithMarker_Values[q5] / j; - int(1..3)]), - (s_ExplicitVarSizeWithMarker_Values[q5] - j) % 2 = 0; - int(1..5)]) - /\ - min([s_ExplicitVarSizeWithMarker_Values[q5] + j, s_ExplicitVarSizeWithMarker_Values[q5] - j, - s_ExplicitVarSizeWithMarker_Values[q5] * j, s_ExplicitVarSizeWithMarker_Values[q5] / j; - int(1..4)]) - = conjure_aux1 - | q5 : int(1..4), j : int(1..4)]), - sum([toInt(and([q5 <= s_ExplicitVarSizeWithMarker_Marker, s_Occurrence[j], - s_ExplicitVarSizeWithMarker_Values[q5] != j, - allDiff([s_ExplicitVarSizeWithMarker_Values[q5] + j, s_ExplicitVarSizeWithMarker_Values[q5] * j, - s_ExplicitVarSizeWithMarker_Values[q5] / j; - int(1..3)]), - (s_ExplicitVarSizeWithMarker_Values[q5] - j) % 2 = 0; - int(1..5)])) - | q5 : int(1..4), j : int(1..4)]) - = 0 - -> conjure_aux1 = -16, - x = conjure_aux1, - sum([toInt(and([q5 <= s_ExplicitVarSizeWithMarker_Marker, s_Occurrence[j], - s_ExplicitVarSizeWithMarker_Values[q5] != j, - allDiff([s_ExplicitVarSizeWithMarker_Values[q5] + j, s_ExplicitVarSizeWithMarker_Values[q5] * j, - s_ExplicitVarSizeWithMarker_Values[q5] / j; - int(1..3)]), - (s_ExplicitVarSizeWithMarker_Values[q5] - j) % 2 = 0; - int(1..5)])) - | q5 : int(1..4), j : int(1..4)]) - > 0, - and([q1 + 1 <= s_ExplicitVarSizeWithMarker_Marker -> - s_ExplicitVarSizeWithMarker_Values[q1] < s_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..3)]), - and([q2 > s_ExplicitVarSizeWithMarker_Marker -> s_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..4)]), - and([s_Occurrence[q27] -> - or([q29 <= s_ExplicitVarSizeWithMarker_Marker /\ s_ExplicitVarSizeWithMarker_Values[q29] = q27 - | q29 : int(1..4)]) - | q27 : int(1..4)]), - and([q31 <= s_ExplicitVarSizeWithMarker_Marker -> s_Occurrence[s_ExplicitVarSizeWithMarker_Values[q31]] - | q31 : int(1..4)]) - diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_1_2-solution000001.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_1_2-solution000001.solution deleted file mode 100644 index bd956f44e3..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_3_1_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 3, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_1_2-solution000002.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_1_2-solution000002.solution deleted file mode 100644 index 5963aac565..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_3_1_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 3} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_1_2-solution000003.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_1_2-solution000003.solution deleted file mode 100644 index 6eeacc9727..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_3_1_2-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_1_2-solution000004.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_1_2-solution000004.solution deleted file mode 100644 index 560dd0f2f7..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_3_1_2-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 3, 4} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_1_2-solution000005.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_1_2-solution000005.solution deleted file mode 100644 index 8b4ecbb66d..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_3_1_2-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 3} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_1_2-solution000006.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_1_2-solution000006.solution deleted file mode 100644 index 40f3fd5c8f..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_3_1_2-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {2, 3, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_1_2-solution000007.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_1_2-solution000007.solution deleted file mode 100644 index 159a613983..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_3_1_2-solution000007.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {2, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_1_2.eprime b/tests/exhaustive/basic/comprehension_letting/expected/model_3_1_2.eprime deleted file mode 100644 index 45efc09186..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_3_1_2.eprime +++ /dev/null @@ -1,95 +0,0 @@ -language ESSENCE' 1.0 - -find s_ExplicitVarSizeWithMarker_Marker: int(0..4) -find s_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -find s_Occurrence: matrix indexed by [int(1..4)] of bool -find s_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -letting let1 be -100 -find x: int(-100..100) -find conjure_aux1: int(-16..3) -branching on - [s_ExplicitVarSizeWithDummy, s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithMarker_Values, s_Occurrence, - x] -such that - and([and([q22 <= s_ExplicitVarSizeWithMarker_Marker, s_Occurrence[j], s_ExplicitVarSizeWithMarker_Values[q22] != j, - allDiff([s_ExplicitVarSizeWithMarker_Values[q22] + j, s_ExplicitVarSizeWithMarker_Values[q22] * j, - s_ExplicitVarSizeWithMarker_Values[q22] / j; - int(1..3)]), - (s_ExplicitVarSizeWithMarker_Values[q22] - j) % 2 = 0; - int(1..5)]) - -> - min([s_ExplicitVarSizeWithMarker_Values[q22] + j, s_ExplicitVarSizeWithMarker_Values[q22] - j, - s_ExplicitVarSizeWithMarker_Values[q22] * j, s_ExplicitVarSizeWithMarker_Values[q22] / j; - int(1..4)]) - <= conjure_aux1 - | q22 : int(1..4), j : int(1..4)]), - sum([toInt(and([q22 <= s_ExplicitVarSizeWithMarker_Marker, s_Occurrence[j], - s_ExplicitVarSizeWithMarker_Values[q22] != j, - allDiff([s_ExplicitVarSizeWithMarker_Values[q22] + j, s_ExplicitVarSizeWithMarker_Values[q22] * j, - s_ExplicitVarSizeWithMarker_Values[q22] / j; - int(1..3)]), - (s_ExplicitVarSizeWithMarker_Values[q22] - j) % 2 = 0; - int(1..5)])) - | q22 : int(1..4), j : int(1..4)]) - > 0 - -> - or([and([q22 <= s_ExplicitVarSizeWithMarker_Marker, s_Occurrence[j], s_ExplicitVarSizeWithMarker_Values[q22] != j, - allDiff([s_ExplicitVarSizeWithMarker_Values[q22] + j, s_ExplicitVarSizeWithMarker_Values[q22] * j, - s_ExplicitVarSizeWithMarker_Values[q22] / j; - int(1..3)]), - (s_ExplicitVarSizeWithMarker_Values[q22] - j) % 2 = 0; - int(1..5)]) - /\ - min([s_ExplicitVarSizeWithMarker_Values[q22] + j, s_ExplicitVarSizeWithMarker_Values[q22] - j, - s_ExplicitVarSizeWithMarker_Values[q22] * j, s_ExplicitVarSizeWithMarker_Values[q22] / j; - int(1..4)]) - = conjure_aux1 - | q22 : int(1..4), j : int(1..4)]), - sum([toInt(and([q22 <= s_ExplicitVarSizeWithMarker_Marker, s_Occurrence[j], - s_ExplicitVarSizeWithMarker_Values[q22] != j, - allDiff([s_ExplicitVarSizeWithMarker_Values[q22] + j, s_ExplicitVarSizeWithMarker_Values[q22] * j, - s_ExplicitVarSizeWithMarker_Values[q22] / j; - int(1..3)]), - (s_ExplicitVarSizeWithMarker_Values[q22] - j) % 2 = 0; - int(1..5)])) - | q22 : int(1..4), j : int(1..4)]) - = 0 - -> conjure_aux1 = -16, - x = conjure_aux1, - sum([toInt(and([q22 <= s_ExplicitVarSizeWithMarker_Marker, s_Occurrence[j], - s_ExplicitVarSizeWithMarker_Values[q22] != j, - allDiff([s_ExplicitVarSizeWithMarker_Values[q22] + j, s_ExplicitVarSizeWithMarker_Values[q22] * j, - s_ExplicitVarSizeWithMarker_Values[q22] / j; - int(1..3)]), - (s_ExplicitVarSizeWithMarker_Values[q22] - j) % 2 = 0; - int(1..5)])) - | q22 : int(1..4), j : int(1..4)]) - > 0, - and([q1 + 1 <= s_ExplicitVarSizeWithMarker_Marker -> - s_ExplicitVarSizeWithMarker_Values[q1] < s_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..3)]), - and([q2 > s_ExplicitVarSizeWithMarker_Marker -> s_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..4)]), - and([s_Occurrence[q44] -> - or([q46 <= s_ExplicitVarSizeWithMarker_Marker /\ s_ExplicitVarSizeWithMarker_Values[q46] = q44 - | q46 : int(1..4)]) - | q44 : int(1..4)]), - and([q48 <= s_ExplicitVarSizeWithMarker_Marker -> s_Occurrence[s_ExplicitVarSizeWithMarker_Values[q48]] - | q48 : int(1..4)]), - and([s_ExplicitVarSizeWithDummy[q5] < s_ExplicitVarSizeWithDummy[q5 + 1] \/ s_ExplicitVarSizeWithDummy[q5] = 5 - | q5 : int(1..3)]), - and([s_ExplicitVarSizeWithDummy[q6] = 5 -> s_ExplicitVarSizeWithDummy[q6 + 1] = 5 | q6 : int(1..3)]), - and([s_ExplicitVarSizeWithDummy[q10] != 5 -> - or([q12 <= s_ExplicitVarSizeWithMarker_Marker /\ - s_ExplicitVarSizeWithMarker_Values[q12] = s_ExplicitVarSizeWithDummy[q10] - | q12 : int(1..4)]) - | q10 : int(1..4)]), - and([q14 <= s_ExplicitVarSizeWithMarker_Marker -> - or([s_ExplicitVarSizeWithDummy[q16] != 5 /\ - s_ExplicitVarSizeWithDummy[q16] = s_ExplicitVarSizeWithMarker_Values[q14] - | q16 : int(1..4)]) - | q14 : int(1..4)]), - and([s_ExplicitVarSizeWithDummy[q18] != 5 -> s_Occurrence[s_ExplicitVarSizeWithDummy[q18]] | q18 : int(1..4)]), - and([s_Occurrence[q19] -> - or([s_ExplicitVarSizeWithDummy[q21] != 5 /\ s_ExplicitVarSizeWithDummy[q21] = q19 | q21 : int(1..4)]) - | q19 : int(1..4)]) - diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_1_3-solution000001.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_1_3-solution000001.solution deleted file mode 100644 index 159a613983..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_3_1_3-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {2, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_1_3-solution000002.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_1_3-solution000002.solution deleted file mode 100644 index 40f3fd5c8f..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_3_1_3-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {2, 3, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_1_3-solution000003.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_1_3-solution000003.solution deleted file mode 100644 index 8b4ecbb66d..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_3_1_3-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 3} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_1_3-solution000004.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_1_3-solution000004.solution deleted file mode 100644 index 560dd0f2f7..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_3_1_3-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 3, 4} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_1_3-solution000005.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_1_3-solution000005.solution deleted file mode 100644 index 6eeacc9727..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_3_1_3-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_1_3-solution000006.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_1_3-solution000006.solution deleted file mode 100644 index 5963aac565..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_3_1_3-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 3} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_1_3-solution000007.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_1_3-solution000007.solution deleted file mode 100644 index bd956f44e3..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_3_1_3-solution000007.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 3, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_1_3.eprime b/tests/exhaustive/basic/comprehension_letting/expected/model_3_1_3.eprime deleted file mode 100644 index 73444ebdb1..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_3_1_3.eprime +++ /dev/null @@ -1,75 +0,0 @@ -language ESSENCE' 1.0 - -find s_ExplicitVarSizeWithMarker_Marker: int(0..4) -find s_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -find s_Occurrence: matrix indexed by [int(1..4)] of bool -letting let1 be -100 -find x: int(-100..100) -find conjure_aux1: int(-16..3) -branching on [s_Occurrence, s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithMarker_Values, x] -such that - and([and([q5 <= s_ExplicitVarSizeWithMarker_Marker, s_Occurrence[j], s_ExplicitVarSizeWithMarker_Values[q5] != j, - allDiff([s_ExplicitVarSizeWithMarker_Values[q5] + j, s_ExplicitVarSizeWithMarker_Values[q5] * j, - s_ExplicitVarSizeWithMarker_Values[q5] / j; - int(1..3)]), - (s_ExplicitVarSizeWithMarker_Values[q5] - j) % 2 = 0; - int(1..5)]) - -> - min([s_ExplicitVarSizeWithMarker_Values[q5] + j, s_ExplicitVarSizeWithMarker_Values[q5] - j, - s_ExplicitVarSizeWithMarker_Values[q5] * j, s_ExplicitVarSizeWithMarker_Values[q5] / j; - int(1..4)]) - <= conjure_aux1 - | q5 : int(1..4), j : int(1..4)]), - sum([toInt(and([q5 <= s_ExplicitVarSizeWithMarker_Marker, s_Occurrence[j], - s_ExplicitVarSizeWithMarker_Values[q5] != j, - allDiff([s_ExplicitVarSizeWithMarker_Values[q5] + j, s_ExplicitVarSizeWithMarker_Values[q5] * j, - s_ExplicitVarSizeWithMarker_Values[q5] / j; - int(1..3)]), - (s_ExplicitVarSizeWithMarker_Values[q5] - j) % 2 = 0; - int(1..5)])) - | q5 : int(1..4), j : int(1..4)]) - > 0 - -> - or([and([q5 <= s_ExplicitVarSizeWithMarker_Marker, s_Occurrence[j], s_ExplicitVarSizeWithMarker_Values[q5] != j, - allDiff([s_ExplicitVarSizeWithMarker_Values[q5] + j, s_ExplicitVarSizeWithMarker_Values[q5] * j, - s_ExplicitVarSizeWithMarker_Values[q5] / j; - int(1..3)]), - (s_ExplicitVarSizeWithMarker_Values[q5] - j) % 2 = 0; - int(1..5)]) - /\ - min([s_ExplicitVarSizeWithMarker_Values[q5] + j, s_ExplicitVarSizeWithMarker_Values[q5] - j, - s_ExplicitVarSizeWithMarker_Values[q5] * j, s_ExplicitVarSizeWithMarker_Values[q5] / j; - int(1..4)]) - = conjure_aux1 - | q5 : int(1..4), j : int(1..4)]), - sum([toInt(and([q5 <= s_ExplicitVarSizeWithMarker_Marker, s_Occurrence[j], - s_ExplicitVarSizeWithMarker_Values[q5] != j, - allDiff([s_ExplicitVarSizeWithMarker_Values[q5] + j, s_ExplicitVarSizeWithMarker_Values[q5] * j, - s_ExplicitVarSizeWithMarker_Values[q5] / j; - int(1..3)]), - (s_ExplicitVarSizeWithMarker_Values[q5] - j) % 2 = 0; - int(1..5)])) - | q5 : int(1..4), j : int(1..4)]) - = 0 - -> conjure_aux1 = -16, - x = conjure_aux1, - sum([toInt(and([q5 <= s_ExplicitVarSizeWithMarker_Marker, s_Occurrence[j], - s_ExplicitVarSizeWithMarker_Values[q5] != j, - allDiff([s_ExplicitVarSizeWithMarker_Values[q5] + j, s_ExplicitVarSizeWithMarker_Values[q5] * j, - s_ExplicitVarSizeWithMarker_Values[q5] / j; - int(1..3)]), - (s_ExplicitVarSizeWithMarker_Values[q5] - j) % 2 = 0; - int(1..5)])) - | q5 : int(1..4), j : int(1..4)]) - > 0, - and([q1 + 1 <= s_ExplicitVarSizeWithMarker_Marker -> - s_ExplicitVarSizeWithMarker_Values[q1] < s_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..3)]), - and([q2 > s_ExplicitVarSizeWithMarker_Marker -> s_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..4)]), - and([s_Occurrence[q27] -> - or([q29 <= s_ExplicitVarSizeWithMarker_Marker /\ s_ExplicitVarSizeWithMarker_Values[q29] = q27 - | q29 : int(1..4)]) - | q27 : int(1..4)]), - and([q31 <= s_ExplicitVarSizeWithMarker_Marker -> s_Occurrence[s_ExplicitVarSizeWithMarker_Values[q31]] - | q31 : int(1..4)]) - diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_1_4-solution000001.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_1_4-solution000001.solution deleted file mode 100644 index 8b4ecbb66d..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_3_1_4-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 3} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_1_4-solution000002.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_1_4-solution000002.solution deleted file mode 100644 index 159a613983..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_3_1_4-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {2, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_1_4-solution000003.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_1_4-solution000003.solution deleted file mode 100644 index 5963aac565..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_3_1_4-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 3} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_1_4-solution000004.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_1_4-solution000004.solution deleted file mode 100644 index 6eeacc9727..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_3_1_4-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_1_4-solution000005.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_1_4-solution000005.solution deleted file mode 100644 index 560dd0f2f7..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_3_1_4-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 3, 4} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_1_4-solution000006.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_1_4-solution000006.solution deleted file mode 100644 index 40f3fd5c8f..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_3_1_4-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {2, 3, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_1_4-solution000007.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_1_4-solution000007.solution deleted file mode 100644 index bd956f44e3..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_3_1_4-solution000007.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 3, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_1_4.eprime b/tests/exhaustive/basic/comprehension_letting/expected/model_3_1_4.eprime deleted file mode 100644 index d5db5a23e1..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_3_1_4.eprime +++ /dev/null @@ -1,99 +0,0 @@ -language ESSENCE' 1.0 - -find s_ExplicitVarSizeWithMarker_Marker: int(0..4) -find s_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -find s_Occurrence: matrix indexed by [int(1..4)] of bool -find s_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find s_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -letting let1 be -100 -find x: int(-100..100) -find conjure_aux1: int(-16..3) -branching on - [s_ExplicitVarSizeWithFlags_Flags, s_ExplicitVarSizeWithFlags_Values, s_ExplicitVarSizeWithMarker_Marker, - s_ExplicitVarSizeWithMarker_Values, s_Occurrence, x] -such that - and([and([q23 <= s_ExplicitVarSizeWithMarker_Marker, s_Occurrence[j], s_ExplicitVarSizeWithMarker_Values[q23] != j, - allDiff([s_ExplicitVarSizeWithMarker_Values[q23] + j, s_ExplicitVarSizeWithMarker_Values[q23] * j, - s_ExplicitVarSizeWithMarker_Values[q23] / j; - int(1..3)]), - (s_ExplicitVarSizeWithMarker_Values[q23] - j) % 2 = 0; - int(1..5)]) - -> - min([s_ExplicitVarSizeWithMarker_Values[q23] + j, s_ExplicitVarSizeWithMarker_Values[q23] - j, - s_ExplicitVarSizeWithMarker_Values[q23] * j, s_ExplicitVarSizeWithMarker_Values[q23] / j; - int(1..4)]) - <= conjure_aux1 - | q23 : int(1..4), j : int(1..4)]), - sum([toInt(and([q23 <= s_ExplicitVarSizeWithMarker_Marker, s_Occurrence[j], - s_ExplicitVarSizeWithMarker_Values[q23] != j, - allDiff([s_ExplicitVarSizeWithMarker_Values[q23] + j, s_ExplicitVarSizeWithMarker_Values[q23] * j, - s_ExplicitVarSizeWithMarker_Values[q23] / j; - int(1..3)]), - (s_ExplicitVarSizeWithMarker_Values[q23] - j) % 2 = 0; - int(1..5)])) - | q23 : int(1..4), j : int(1..4)]) - > 0 - -> - or([and([q23 <= s_ExplicitVarSizeWithMarker_Marker, s_Occurrence[j], s_ExplicitVarSizeWithMarker_Values[q23] != j, - allDiff([s_ExplicitVarSizeWithMarker_Values[q23] + j, s_ExplicitVarSizeWithMarker_Values[q23] * j, - s_ExplicitVarSizeWithMarker_Values[q23] / j; - int(1..3)]), - (s_ExplicitVarSizeWithMarker_Values[q23] - j) % 2 = 0; - int(1..5)]) - /\ - min([s_ExplicitVarSizeWithMarker_Values[q23] + j, s_ExplicitVarSizeWithMarker_Values[q23] - j, - s_ExplicitVarSizeWithMarker_Values[q23] * j, s_ExplicitVarSizeWithMarker_Values[q23] / j; - int(1..4)]) - = conjure_aux1 - | q23 : int(1..4), j : int(1..4)]), - sum([toInt(and([q23 <= s_ExplicitVarSizeWithMarker_Marker, s_Occurrence[j], - s_ExplicitVarSizeWithMarker_Values[q23] != j, - allDiff([s_ExplicitVarSizeWithMarker_Values[q23] + j, s_ExplicitVarSizeWithMarker_Values[q23] * j, - s_ExplicitVarSizeWithMarker_Values[q23] / j; - int(1..3)]), - (s_ExplicitVarSizeWithMarker_Values[q23] - j) % 2 = 0; - int(1..5)])) - | q23 : int(1..4), j : int(1..4)]) - = 0 - -> conjure_aux1 = -16, - x = conjure_aux1, - sum([toInt(and([q23 <= s_ExplicitVarSizeWithMarker_Marker, s_Occurrence[j], - s_ExplicitVarSizeWithMarker_Values[q23] != j, - allDiff([s_ExplicitVarSizeWithMarker_Values[q23] + j, s_ExplicitVarSizeWithMarker_Values[q23] * j, - s_ExplicitVarSizeWithMarker_Values[q23] / j; - int(1..3)]), - (s_ExplicitVarSizeWithMarker_Values[q23] - j) % 2 = 0; - int(1..5)])) - | q23 : int(1..4), j : int(1..4)]) - > 0, - and([q1 + 1 <= s_ExplicitVarSizeWithMarker_Marker -> - s_ExplicitVarSizeWithMarker_Values[q1] < s_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..3)]), - and([q2 > s_ExplicitVarSizeWithMarker_Marker -> s_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..4)]), - and([s_Occurrence[q45] -> - or([q47 <= s_ExplicitVarSizeWithMarker_Marker /\ s_ExplicitVarSizeWithMarker_Values[q47] = q45 - | q47 : int(1..4)]) - | q45 : int(1..4)]), - and([q49 <= s_ExplicitVarSizeWithMarker_Marker -> s_Occurrence[s_ExplicitVarSizeWithMarker_Values[q49]] - | q49 : int(1..4)]), - and([s_ExplicitVarSizeWithFlags_Flags[q5 + 1] -> - s_ExplicitVarSizeWithFlags_Values[q5] < s_ExplicitVarSizeWithFlags_Values[q5 + 1] - | q5 : int(1..3)]), - and([s_ExplicitVarSizeWithFlags_Flags[q6] = false -> s_ExplicitVarSizeWithFlags_Values[q6] = 1 | q6 : int(1..4)]), - and([s_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> s_ExplicitVarSizeWithFlags_Flags[q7] | q7 : int(1..3)]), - and([s_ExplicitVarSizeWithFlags_Flags[q11] -> - or([q13 <= s_ExplicitVarSizeWithMarker_Marker /\ - s_ExplicitVarSizeWithMarker_Values[q13] = s_ExplicitVarSizeWithFlags_Values[q11] - | q13 : int(1..4)]) - | q11 : int(1..4)]), - and([q15 <= s_ExplicitVarSizeWithMarker_Marker -> - or([s_ExplicitVarSizeWithFlags_Flags[q17] /\ - s_ExplicitVarSizeWithFlags_Values[q17] = s_ExplicitVarSizeWithMarker_Values[q15] - | q17 : int(1..4)]) - | q15 : int(1..4)]), - and([s_ExplicitVarSizeWithFlags_Flags[q19] -> s_Occurrence[s_ExplicitVarSizeWithFlags_Values[q19]] - | q19 : int(1..4)]), - and([s_Occurrence[q20] -> - or([s_ExplicitVarSizeWithFlags_Flags[q22] /\ s_ExplicitVarSizeWithFlags_Values[q22] = q20 | q22 : int(1..4)]) - | q20 : int(1..4)]) - diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_2_1-solution000001.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_2_1-solution000001.solution deleted file mode 100644 index 159a613983..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_3_2_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {2, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_2_1-solution000002.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_2_1-solution000002.solution deleted file mode 100644 index 40f3fd5c8f..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_3_2_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {2, 3, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_2_1-solution000003.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_2_1-solution000003.solution deleted file mode 100644 index 8b4ecbb66d..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_3_2_1-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 3} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_2_1-solution000004.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_2_1-solution000004.solution deleted file mode 100644 index 560dd0f2f7..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_3_2_1-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 3, 4} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_2_1-solution000005.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_2_1-solution000005.solution deleted file mode 100644 index 6eeacc9727..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_3_2_1-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_2_1-solution000006.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_2_1-solution000006.solution deleted file mode 100644 index 5963aac565..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_3_2_1-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 3} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_2_1-solution000007.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_2_1-solution000007.solution deleted file mode 100644 index bd956f44e3..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_3_2_1-solution000007.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 3, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_2_1.eprime b/tests/exhaustive/basic/comprehension_letting/expected/model_3_2_1.eprime deleted file mode 100644 index b6f0c01a86..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_3_2_1.eprime +++ /dev/null @@ -1,106 +0,0 @@ -language ESSENCE' 1.0 - -find s_ExplicitVarSizeWithMarker_Marker: int(0..4) -find s_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -find s_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -find s_Occurrence: matrix indexed by [int(1..4)] of bool -letting let1 be -100 -find x: int(-100..100) -find conjure_aux1: int(-20..3) -branching on - [s_Occurrence, s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithMarker_Values, s_ExplicitVarSizeWithDummy, - x] -such that - and([and([q17 <= s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithDummy[q18] != 5, - s_ExplicitVarSizeWithMarker_Values[q17] != s_ExplicitVarSizeWithDummy[q18], - allDiff([s_ExplicitVarSizeWithMarker_Values[q17] + s_ExplicitVarSizeWithDummy[q18], - s_ExplicitVarSizeWithMarker_Values[q17] * s_ExplicitVarSizeWithDummy[q18], - s_ExplicitVarSizeWithMarker_Values[q17] / s_ExplicitVarSizeWithDummy[q18]; - int(1..3)]), - (s_ExplicitVarSizeWithMarker_Values[q17] - s_ExplicitVarSizeWithDummy[q18]) % 2 = 0; - int(1..5)]) - -> - min([s_ExplicitVarSizeWithMarker_Values[q17] + s_ExplicitVarSizeWithDummy[q18], - s_ExplicitVarSizeWithMarker_Values[q17] - s_ExplicitVarSizeWithDummy[q18], - s_ExplicitVarSizeWithMarker_Values[q17] * s_ExplicitVarSizeWithDummy[q18], - s_ExplicitVarSizeWithMarker_Values[q17] / s_ExplicitVarSizeWithDummy[q18]; - int(1..4)]) - <= conjure_aux1 - | q17 : int(1..4), q18 : int(1..4)]), - sum([toInt(and([q17 <= s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithDummy[q18] != 5, - s_ExplicitVarSizeWithMarker_Values[q17] != s_ExplicitVarSizeWithDummy[q18], - allDiff([s_ExplicitVarSizeWithMarker_Values[q17] + s_ExplicitVarSizeWithDummy[q18], - s_ExplicitVarSizeWithMarker_Values[q17] * s_ExplicitVarSizeWithDummy[q18], - s_ExplicitVarSizeWithMarker_Values[q17] / s_ExplicitVarSizeWithDummy[q18]; - int(1..3)]), - (s_ExplicitVarSizeWithMarker_Values[q17] - s_ExplicitVarSizeWithDummy[q18]) % 2 = 0; - int(1..5)])) - | q17 : int(1..4), q18 : int(1..4)]) - > 0 - -> - or([and([q17 <= s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithDummy[q18] != 5, - s_ExplicitVarSizeWithMarker_Values[q17] != s_ExplicitVarSizeWithDummy[q18], - allDiff([s_ExplicitVarSizeWithMarker_Values[q17] + s_ExplicitVarSizeWithDummy[q18], - s_ExplicitVarSizeWithMarker_Values[q17] * s_ExplicitVarSizeWithDummy[q18], - s_ExplicitVarSizeWithMarker_Values[q17] / s_ExplicitVarSizeWithDummy[q18]; - int(1..3)]), - (s_ExplicitVarSizeWithMarker_Values[q17] - s_ExplicitVarSizeWithDummy[q18]) % 2 = 0; - int(1..5)]) - /\ - min([s_ExplicitVarSizeWithMarker_Values[q17] + s_ExplicitVarSizeWithDummy[q18], - s_ExplicitVarSizeWithMarker_Values[q17] - s_ExplicitVarSizeWithDummy[q18], - s_ExplicitVarSizeWithMarker_Values[q17] * s_ExplicitVarSizeWithDummy[q18], - s_ExplicitVarSizeWithMarker_Values[q17] / s_ExplicitVarSizeWithDummy[q18]; - int(1..4)]) - = conjure_aux1 - | q17 : int(1..4), q18 : int(1..4)]), - sum([toInt(and([q17 <= s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithDummy[q18] != 5, - s_ExplicitVarSizeWithMarker_Values[q17] != s_ExplicitVarSizeWithDummy[q18], - allDiff([s_ExplicitVarSizeWithMarker_Values[q17] + s_ExplicitVarSizeWithDummy[q18], - s_ExplicitVarSizeWithMarker_Values[q17] * s_ExplicitVarSizeWithDummy[q18], - s_ExplicitVarSizeWithMarker_Values[q17] / s_ExplicitVarSizeWithDummy[q18]; - int(1..3)]), - (s_ExplicitVarSizeWithMarker_Values[q17] - s_ExplicitVarSizeWithDummy[q18]) % 2 = 0; - int(1..5)])) - | q17 : int(1..4), q18 : int(1..4)]) - = 0 - -> conjure_aux1 = -20, - x = conjure_aux1, - sum([toInt(and([q17 <= s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithDummy[q18] != 5, - s_ExplicitVarSizeWithMarker_Values[q17] != s_ExplicitVarSizeWithDummy[q18], - allDiff([s_ExplicitVarSizeWithMarker_Values[q17] + s_ExplicitVarSizeWithDummy[q18], - s_ExplicitVarSizeWithMarker_Values[q17] * s_ExplicitVarSizeWithDummy[q18], - s_ExplicitVarSizeWithMarker_Values[q17] / s_ExplicitVarSizeWithDummy[q18]; - int(1..3)]), - (s_ExplicitVarSizeWithMarker_Values[q17] - s_ExplicitVarSizeWithDummy[q18]) % 2 = 0; - int(1..5)])) - | q17 : int(1..4), q18 : int(1..4)]) - > 0, - and([q1 + 1 <= s_ExplicitVarSizeWithMarker_Marker -> - s_ExplicitVarSizeWithMarker_Values[q1] < s_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..3)]), - and([q2 > s_ExplicitVarSizeWithMarker_Marker -> s_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..4)]), - and([s_ExplicitVarSizeWithDummy[q4] < s_ExplicitVarSizeWithDummy[q4 + 1] \/ s_ExplicitVarSizeWithDummy[q4] = 5 - | q4 : int(1..3)]), - and([s_ExplicitVarSizeWithDummy[q5] = 5 -> s_ExplicitVarSizeWithDummy[q5 + 1] = 5 | q5 : int(1..3)]), - and([s_ExplicitVarSizeWithDummy[q9] != 5 -> - or([q11 <= s_ExplicitVarSizeWithMarker_Marker /\ - s_ExplicitVarSizeWithMarker_Values[q11] = s_ExplicitVarSizeWithDummy[q9] - | q11 : int(1..4)]) - | q9 : int(1..4)]), - and([q13 <= s_ExplicitVarSizeWithMarker_Marker -> - or([s_ExplicitVarSizeWithDummy[q15] != 5 /\ - s_ExplicitVarSizeWithDummy[q15] = s_ExplicitVarSizeWithMarker_Values[q13] - | q15 : int(1..4)]) - | q13 : int(1..4)]), - and([s_Occurrence[q40] -> - or([q42 <= s_ExplicitVarSizeWithMarker_Marker /\ s_ExplicitVarSizeWithMarker_Values[q42] = q40 - | q42 : int(1..4)]) - | q40 : int(1..4)]), - and([q44 <= s_ExplicitVarSizeWithMarker_Marker -> s_Occurrence[s_ExplicitVarSizeWithMarker_Values[q44]] - | q44 : int(1..4)]), - and([s_Occurrence[q45] -> - or([s_ExplicitVarSizeWithDummy[q47] != 5 /\ s_ExplicitVarSizeWithDummy[q47] = q45 | q47 : int(1..4)]) - | q45 : int(1..4)]), - and([s_ExplicitVarSizeWithDummy[q49] != 5 -> s_Occurrence[s_ExplicitVarSizeWithDummy[q49]] | q49 : int(1..4)]) - diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_2_2-solution000001.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_2_2-solution000001.solution deleted file mode 100644 index bd956f44e3..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_3_2_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 3, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_2_2-solution000002.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_2_2-solution000002.solution deleted file mode 100644 index 5963aac565..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_3_2_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 3} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_2_2-solution000003.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_2_2-solution000003.solution deleted file mode 100644 index 6eeacc9727..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_3_2_2-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_2_2-solution000004.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_2_2-solution000004.solution deleted file mode 100644 index 560dd0f2f7..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_3_2_2-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 3, 4} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_2_2-solution000005.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_2_2-solution000005.solution deleted file mode 100644 index 8b4ecbb66d..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_3_2_2-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 3} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_2_2-solution000006.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_2_2-solution000006.solution deleted file mode 100644 index 40f3fd5c8f..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_3_2_2-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {2, 3, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_2_2-solution000007.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_2_2-solution000007.solution deleted file mode 100644 index 159a613983..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_3_2_2-solution000007.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {2, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_2_2.eprime b/tests/exhaustive/basic/comprehension_letting/expected/model_3_2_2.eprime deleted file mode 100644 index 4259b37168..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_3_2_2.eprime +++ /dev/null @@ -1,93 +0,0 @@ -language ESSENCE' 1.0 - -find s_ExplicitVarSizeWithMarker_Marker: int(0..4) -find s_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -find s_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -letting let1 be -100 -find x: int(-100..100) -find conjure_aux1: int(-20..3) -branching on [s_ExplicitVarSizeWithDummy, s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithMarker_Values, x] -such that - and([and([q16 <= s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithDummy[q17] != 5, - s_ExplicitVarSizeWithMarker_Values[q16] != s_ExplicitVarSizeWithDummy[q17], - allDiff([s_ExplicitVarSizeWithMarker_Values[q16] + s_ExplicitVarSizeWithDummy[q17], - s_ExplicitVarSizeWithMarker_Values[q16] * s_ExplicitVarSizeWithDummy[q17], - s_ExplicitVarSizeWithMarker_Values[q16] / s_ExplicitVarSizeWithDummy[q17]; - int(1..3)]), - (s_ExplicitVarSizeWithMarker_Values[q16] - s_ExplicitVarSizeWithDummy[q17]) % 2 = 0; - int(1..5)]) - -> - min([s_ExplicitVarSizeWithMarker_Values[q16] + s_ExplicitVarSizeWithDummy[q17], - s_ExplicitVarSizeWithMarker_Values[q16] - s_ExplicitVarSizeWithDummy[q17], - s_ExplicitVarSizeWithMarker_Values[q16] * s_ExplicitVarSizeWithDummy[q17], - s_ExplicitVarSizeWithMarker_Values[q16] / s_ExplicitVarSizeWithDummy[q17]; - int(1..4)]) - <= conjure_aux1 - | q16 : int(1..4), q17 : int(1..4)]), - sum([toInt(and([q16 <= s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithDummy[q17] != 5, - s_ExplicitVarSizeWithMarker_Values[q16] != s_ExplicitVarSizeWithDummy[q17], - allDiff([s_ExplicitVarSizeWithMarker_Values[q16] + s_ExplicitVarSizeWithDummy[q17], - s_ExplicitVarSizeWithMarker_Values[q16] * s_ExplicitVarSizeWithDummy[q17], - s_ExplicitVarSizeWithMarker_Values[q16] / s_ExplicitVarSizeWithDummy[q17]; - int(1..3)]), - (s_ExplicitVarSizeWithMarker_Values[q16] - s_ExplicitVarSizeWithDummy[q17]) % 2 = 0; - int(1..5)])) - | q16 : int(1..4), q17 : int(1..4)]) - > 0 - -> - or([and([q16 <= s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithDummy[q17] != 5, - s_ExplicitVarSizeWithMarker_Values[q16] != s_ExplicitVarSizeWithDummy[q17], - allDiff([s_ExplicitVarSizeWithMarker_Values[q16] + s_ExplicitVarSizeWithDummy[q17], - s_ExplicitVarSizeWithMarker_Values[q16] * s_ExplicitVarSizeWithDummy[q17], - s_ExplicitVarSizeWithMarker_Values[q16] / s_ExplicitVarSizeWithDummy[q17]; - int(1..3)]), - (s_ExplicitVarSizeWithMarker_Values[q16] - s_ExplicitVarSizeWithDummy[q17]) % 2 = 0; - int(1..5)]) - /\ - min([s_ExplicitVarSizeWithMarker_Values[q16] + s_ExplicitVarSizeWithDummy[q17], - s_ExplicitVarSizeWithMarker_Values[q16] - s_ExplicitVarSizeWithDummy[q17], - s_ExplicitVarSizeWithMarker_Values[q16] * s_ExplicitVarSizeWithDummy[q17], - s_ExplicitVarSizeWithMarker_Values[q16] / s_ExplicitVarSizeWithDummy[q17]; - int(1..4)]) - = conjure_aux1 - | q16 : int(1..4), q17 : int(1..4)]), - sum([toInt(and([q16 <= s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithDummy[q17] != 5, - s_ExplicitVarSizeWithMarker_Values[q16] != s_ExplicitVarSizeWithDummy[q17], - allDiff([s_ExplicitVarSizeWithMarker_Values[q16] + s_ExplicitVarSizeWithDummy[q17], - s_ExplicitVarSizeWithMarker_Values[q16] * s_ExplicitVarSizeWithDummy[q17], - s_ExplicitVarSizeWithMarker_Values[q16] / s_ExplicitVarSizeWithDummy[q17]; - int(1..3)]), - (s_ExplicitVarSizeWithMarker_Values[q16] - s_ExplicitVarSizeWithDummy[q17]) % 2 = 0; - int(1..5)])) - | q16 : int(1..4), q17 : int(1..4)]) - = 0 - -> conjure_aux1 = -20, - x = conjure_aux1, - sum([toInt(and([q16 <= s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithDummy[q17] != 5, - s_ExplicitVarSizeWithMarker_Values[q16] != s_ExplicitVarSizeWithDummy[q17], - allDiff([s_ExplicitVarSizeWithMarker_Values[q16] + s_ExplicitVarSizeWithDummy[q17], - s_ExplicitVarSizeWithMarker_Values[q16] * s_ExplicitVarSizeWithDummy[q17], - s_ExplicitVarSizeWithMarker_Values[q16] / s_ExplicitVarSizeWithDummy[q17]; - int(1..3)]), - (s_ExplicitVarSizeWithMarker_Values[q16] - s_ExplicitVarSizeWithDummy[q17]) % 2 = 0; - int(1..5)])) - | q16 : int(1..4), q17 : int(1..4)]) - > 0, - and([q1 + 1 <= s_ExplicitVarSizeWithMarker_Marker -> - s_ExplicitVarSizeWithMarker_Values[q1] < s_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..3)]), - and([q2 > s_ExplicitVarSizeWithMarker_Marker -> s_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..4)]), - and([s_ExplicitVarSizeWithDummy[q4] < s_ExplicitVarSizeWithDummy[q4 + 1] \/ s_ExplicitVarSizeWithDummy[q4] = 5 - | q4 : int(1..3)]), - and([s_ExplicitVarSizeWithDummy[q5] = 5 -> s_ExplicitVarSizeWithDummy[q5 + 1] = 5 | q5 : int(1..3)]), - and([s_ExplicitVarSizeWithDummy[q9] != 5 -> - or([q11 <= s_ExplicitVarSizeWithMarker_Marker /\ - s_ExplicitVarSizeWithMarker_Values[q11] = s_ExplicitVarSizeWithDummy[q9] - | q11 : int(1..4)]) - | q9 : int(1..4)]), - and([q13 <= s_ExplicitVarSizeWithMarker_Marker -> - or([s_ExplicitVarSizeWithDummy[q15] != 5 /\ - s_ExplicitVarSizeWithDummy[q15] = s_ExplicitVarSizeWithMarker_Values[q13] - | q15 : int(1..4)]) - | q13 : int(1..4)]) - diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_2_3-solution000001.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_2_3-solution000001.solution deleted file mode 100644 index bd956f44e3..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_3_2_3-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 3, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_2_3-solution000002.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_2_3-solution000002.solution deleted file mode 100644 index 5963aac565..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_3_2_3-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 3} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_2_3-solution000003.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_2_3-solution000003.solution deleted file mode 100644 index 6eeacc9727..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_3_2_3-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_2_3-solution000004.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_2_3-solution000004.solution deleted file mode 100644 index 560dd0f2f7..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_3_2_3-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 3, 4} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_2_3-solution000005.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_2_3-solution000005.solution deleted file mode 100644 index 8b4ecbb66d..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_3_2_3-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 3} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_2_3-solution000006.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_2_3-solution000006.solution deleted file mode 100644 index 40f3fd5c8f..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_3_2_3-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {2, 3, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_2_3-solution000007.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_2_3-solution000007.solution deleted file mode 100644 index 159a613983..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_3_2_3-solution000007.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {2, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_2_3.eprime b/tests/exhaustive/basic/comprehension_letting/expected/model_3_2_3.eprime deleted file mode 100644 index 4259b37168..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_3_2_3.eprime +++ /dev/null @@ -1,93 +0,0 @@ -language ESSENCE' 1.0 - -find s_ExplicitVarSizeWithMarker_Marker: int(0..4) -find s_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -find s_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -letting let1 be -100 -find x: int(-100..100) -find conjure_aux1: int(-20..3) -branching on [s_ExplicitVarSizeWithDummy, s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithMarker_Values, x] -such that - and([and([q16 <= s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithDummy[q17] != 5, - s_ExplicitVarSizeWithMarker_Values[q16] != s_ExplicitVarSizeWithDummy[q17], - allDiff([s_ExplicitVarSizeWithMarker_Values[q16] + s_ExplicitVarSizeWithDummy[q17], - s_ExplicitVarSizeWithMarker_Values[q16] * s_ExplicitVarSizeWithDummy[q17], - s_ExplicitVarSizeWithMarker_Values[q16] / s_ExplicitVarSizeWithDummy[q17]; - int(1..3)]), - (s_ExplicitVarSizeWithMarker_Values[q16] - s_ExplicitVarSizeWithDummy[q17]) % 2 = 0; - int(1..5)]) - -> - min([s_ExplicitVarSizeWithMarker_Values[q16] + s_ExplicitVarSizeWithDummy[q17], - s_ExplicitVarSizeWithMarker_Values[q16] - s_ExplicitVarSizeWithDummy[q17], - s_ExplicitVarSizeWithMarker_Values[q16] * s_ExplicitVarSizeWithDummy[q17], - s_ExplicitVarSizeWithMarker_Values[q16] / s_ExplicitVarSizeWithDummy[q17]; - int(1..4)]) - <= conjure_aux1 - | q16 : int(1..4), q17 : int(1..4)]), - sum([toInt(and([q16 <= s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithDummy[q17] != 5, - s_ExplicitVarSizeWithMarker_Values[q16] != s_ExplicitVarSizeWithDummy[q17], - allDiff([s_ExplicitVarSizeWithMarker_Values[q16] + s_ExplicitVarSizeWithDummy[q17], - s_ExplicitVarSizeWithMarker_Values[q16] * s_ExplicitVarSizeWithDummy[q17], - s_ExplicitVarSizeWithMarker_Values[q16] / s_ExplicitVarSizeWithDummy[q17]; - int(1..3)]), - (s_ExplicitVarSizeWithMarker_Values[q16] - s_ExplicitVarSizeWithDummy[q17]) % 2 = 0; - int(1..5)])) - | q16 : int(1..4), q17 : int(1..4)]) - > 0 - -> - or([and([q16 <= s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithDummy[q17] != 5, - s_ExplicitVarSizeWithMarker_Values[q16] != s_ExplicitVarSizeWithDummy[q17], - allDiff([s_ExplicitVarSizeWithMarker_Values[q16] + s_ExplicitVarSizeWithDummy[q17], - s_ExplicitVarSizeWithMarker_Values[q16] * s_ExplicitVarSizeWithDummy[q17], - s_ExplicitVarSizeWithMarker_Values[q16] / s_ExplicitVarSizeWithDummy[q17]; - int(1..3)]), - (s_ExplicitVarSizeWithMarker_Values[q16] - s_ExplicitVarSizeWithDummy[q17]) % 2 = 0; - int(1..5)]) - /\ - min([s_ExplicitVarSizeWithMarker_Values[q16] + s_ExplicitVarSizeWithDummy[q17], - s_ExplicitVarSizeWithMarker_Values[q16] - s_ExplicitVarSizeWithDummy[q17], - s_ExplicitVarSizeWithMarker_Values[q16] * s_ExplicitVarSizeWithDummy[q17], - s_ExplicitVarSizeWithMarker_Values[q16] / s_ExplicitVarSizeWithDummy[q17]; - int(1..4)]) - = conjure_aux1 - | q16 : int(1..4), q17 : int(1..4)]), - sum([toInt(and([q16 <= s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithDummy[q17] != 5, - s_ExplicitVarSizeWithMarker_Values[q16] != s_ExplicitVarSizeWithDummy[q17], - allDiff([s_ExplicitVarSizeWithMarker_Values[q16] + s_ExplicitVarSizeWithDummy[q17], - s_ExplicitVarSizeWithMarker_Values[q16] * s_ExplicitVarSizeWithDummy[q17], - s_ExplicitVarSizeWithMarker_Values[q16] / s_ExplicitVarSizeWithDummy[q17]; - int(1..3)]), - (s_ExplicitVarSizeWithMarker_Values[q16] - s_ExplicitVarSizeWithDummy[q17]) % 2 = 0; - int(1..5)])) - | q16 : int(1..4), q17 : int(1..4)]) - = 0 - -> conjure_aux1 = -20, - x = conjure_aux1, - sum([toInt(and([q16 <= s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithDummy[q17] != 5, - s_ExplicitVarSizeWithMarker_Values[q16] != s_ExplicitVarSizeWithDummy[q17], - allDiff([s_ExplicitVarSizeWithMarker_Values[q16] + s_ExplicitVarSizeWithDummy[q17], - s_ExplicitVarSizeWithMarker_Values[q16] * s_ExplicitVarSizeWithDummy[q17], - s_ExplicitVarSizeWithMarker_Values[q16] / s_ExplicitVarSizeWithDummy[q17]; - int(1..3)]), - (s_ExplicitVarSizeWithMarker_Values[q16] - s_ExplicitVarSizeWithDummy[q17]) % 2 = 0; - int(1..5)])) - | q16 : int(1..4), q17 : int(1..4)]) - > 0, - and([q1 + 1 <= s_ExplicitVarSizeWithMarker_Marker -> - s_ExplicitVarSizeWithMarker_Values[q1] < s_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..3)]), - and([q2 > s_ExplicitVarSizeWithMarker_Marker -> s_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..4)]), - and([s_ExplicitVarSizeWithDummy[q4] < s_ExplicitVarSizeWithDummy[q4 + 1] \/ s_ExplicitVarSizeWithDummy[q4] = 5 - | q4 : int(1..3)]), - and([s_ExplicitVarSizeWithDummy[q5] = 5 -> s_ExplicitVarSizeWithDummy[q5 + 1] = 5 | q5 : int(1..3)]), - and([s_ExplicitVarSizeWithDummy[q9] != 5 -> - or([q11 <= s_ExplicitVarSizeWithMarker_Marker /\ - s_ExplicitVarSizeWithMarker_Values[q11] = s_ExplicitVarSizeWithDummy[q9] - | q11 : int(1..4)]) - | q9 : int(1..4)]), - and([q13 <= s_ExplicitVarSizeWithMarker_Marker -> - or([s_ExplicitVarSizeWithDummy[q15] != 5 /\ - s_ExplicitVarSizeWithDummy[q15] = s_ExplicitVarSizeWithMarker_Values[q13] - | q15 : int(1..4)]) - | q13 : int(1..4)]) - diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_2_4-solution000001.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_2_4-solution000001.solution deleted file mode 100644 index 8b4ecbb66d..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_3_2_4-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 3} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_2_4-solution000002.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_2_4-solution000002.solution deleted file mode 100644 index 159a613983..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_3_2_4-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {2, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_2_4-solution000003.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_2_4-solution000003.solution deleted file mode 100644 index 5963aac565..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_3_2_4-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 3} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_2_4-solution000004.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_2_4-solution000004.solution deleted file mode 100644 index 6eeacc9727..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_3_2_4-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_2_4-solution000005.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_2_4-solution000005.solution deleted file mode 100644 index 560dd0f2f7..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_3_2_4-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 3, 4} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_2_4-solution000006.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_2_4-solution000006.solution deleted file mode 100644 index 40f3fd5c8f..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_3_2_4-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {2, 3, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_2_4-solution000007.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_2_4-solution000007.solution deleted file mode 100644 index bd956f44e3..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_3_2_4-solution000007.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 3, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_2_4.eprime b/tests/exhaustive/basic/comprehension_letting/expected/model_3_2_4.eprime deleted file mode 100644 index 0d153c4cd7..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_3_2_4.eprime +++ /dev/null @@ -1,123 +0,0 @@ -language ESSENCE' 1.0 - -find s_ExplicitVarSizeWithMarker_Marker: int(0..4) -find s_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -find s_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -find s_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find s_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -letting let1 be -100 -find x: int(-100..100) -find conjure_aux1: int(-20..3) -branching on - [s_ExplicitVarSizeWithFlags_Flags, s_ExplicitVarSizeWithFlags_Values, s_ExplicitVarSizeWithMarker_Marker, - s_ExplicitVarSizeWithMarker_Values, s_ExplicitVarSizeWithDummy, x] -such that - and([and([q37 <= s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithDummy[q38] != 5, - s_ExplicitVarSizeWithMarker_Values[q37] != s_ExplicitVarSizeWithDummy[q38], - allDiff([s_ExplicitVarSizeWithMarker_Values[q37] + s_ExplicitVarSizeWithDummy[q38], - s_ExplicitVarSizeWithMarker_Values[q37] * s_ExplicitVarSizeWithDummy[q38], - s_ExplicitVarSizeWithMarker_Values[q37] / s_ExplicitVarSizeWithDummy[q38]; - int(1..3)]), - (s_ExplicitVarSizeWithMarker_Values[q37] - s_ExplicitVarSizeWithDummy[q38]) % 2 = 0; - int(1..5)]) - -> - min([s_ExplicitVarSizeWithMarker_Values[q37] + s_ExplicitVarSizeWithDummy[q38], - s_ExplicitVarSizeWithMarker_Values[q37] - s_ExplicitVarSizeWithDummy[q38], - s_ExplicitVarSizeWithMarker_Values[q37] * s_ExplicitVarSizeWithDummy[q38], - s_ExplicitVarSizeWithMarker_Values[q37] / s_ExplicitVarSizeWithDummy[q38]; - int(1..4)]) - <= conjure_aux1 - | q37 : int(1..4), q38 : int(1..4)]), - sum([toInt(and([q37 <= s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithDummy[q38] != 5, - s_ExplicitVarSizeWithMarker_Values[q37] != s_ExplicitVarSizeWithDummy[q38], - allDiff([s_ExplicitVarSizeWithMarker_Values[q37] + s_ExplicitVarSizeWithDummy[q38], - s_ExplicitVarSizeWithMarker_Values[q37] * s_ExplicitVarSizeWithDummy[q38], - s_ExplicitVarSizeWithMarker_Values[q37] / s_ExplicitVarSizeWithDummy[q38]; - int(1..3)]), - (s_ExplicitVarSizeWithMarker_Values[q37] - s_ExplicitVarSizeWithDummy[q38]) % 2 = 0; - int(1..5)])) - | q37 : int(1..4), q38 : int(1..4)]) - > 0 - -> - or([and([q37 <= s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithDummy[q38] != 5, - s_ExplicitVarSizeWithMarker_Values[q37] != s_ExplicitVarSizeWithDummy[q38], - allDiff([s_ExplicitVarSizeWithMarker_Values[q37] + s_ExplicitVarSizeWithDummy[q38], - s_ExplicitVarSizeWithMarker_Values[q37] * s_ExplicitVarSizeWithDummy[q38], - s_ExplicitVarSizeWithMarker_Values[q37] / s_ExplicitVarSizeWithDummy[q38]; - int(1..3)]), - (s_ExplicitVarSizeWithMarker_Values[q37] - s_ExplicitVarSizeWithDummy[q38]) % 2 = 0; - int(1..5)]) - /\ - min([s_ExplicitVarSizeWithMarker_Values[q37] + s_ExplicitVarSizeWithDummy[q38], - s_ExplicitVarSizeWithMarker_Values[q37] - s_ExplicitVarSizeWithDummy[q38], - s_ExplicitVarSizeWithMarker_Values[q37] * s_ExplicitVarSizeWithDummy[q38], - s_ExplicitVarSizeWithMarker_Values[q37] / s_ExplicitVarSizeWithDummy[q38]; - int(1..4)]) - = conjure_aux1 - | q37 : int(1..4), q38 : int(1..4)]), - sum([toInt(and([q37 <= s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithDummy[q38] != 5, - s_ExplicitVarSizeWithMarker_Values[q37] != s_ExplicitVarSizeWithDummy[q38], - allDiff([s_ExplicitVarSizeWithMarker_Values[q37] + s_ExplicitVarSizeWithDummy[q38], - s_ExplicitVarSizeWithMarker_Values[q37] * s_ExplicitVarSizeWithDummy[q38], - s_ExplicitVarSizeWithMarker_Values[q37] / s_ExplicitVarSizeWithDummy[q38]; - int(1..3)]), - (s_ExplicitVarSizeWithMarker_Values[q37] - s_ExplicitVarSizeWithDummy[q38]) % 2 = 0; - int(1..5)])) - | q37 : int(1..4), q38 : int(1..4)]) - = 0 - -> conjure_aux1 = -20, - x = conjure_aux1, - sum([toInt(and([q37 <= s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithDummy[q38] != 5, - s_ExplicitVarSizeWithMarker_Values[q37] != s_ExplicitVarSizeWithDummy[q38], - allDiff([s_ExplicitVarSizeWithMarker_Values[q37] + s_ExplicitVarSizeWithDummy[q38], - s_ExplicitVarSizeWithMarker_Values[q37] * s_ExplicitVarSizeWithDummy[q38], - s_ExplicitVarSizeWithMarker_Values[q37] / s_ExplicitVarSizeWithDummy[q38]; - int(1..3)]), - (s_ExplicitVarSizeWithMarker_Values[q37] - s_ExplicitVarSizeWithDummy[q38]) % 2 = 0; - int(1..5)])) - | q37 : int(1..4), q38 : int(1..4)]) - > 0, - and([q1 + 1 <= s_ExplicitVarSizeWithMarker_Marker -> - s_ExplicitVarSizeWithMarker_Values[q1] < s_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..3)]), - and([q2 > s_ExplicitVarSizeWithMarker_Marker -> s_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..4)]), - and([s_ExplicitVarSizeWithDummy[q4] < s_ExplicitVarSizeWithDummy[q4 + 1] \/ s_ExplicitVarSizeWithDummy[q4] = 5 - | q4 : int(1..3)]), - and([s_ExplicitVarSizeWithDummy[q5] = 5 -> s_ExplicitVarSizeWithDummy[q5 + 1] = 5 | q5 : int(1..3)]), - and([s_ExplicitVarSizeWithDummy[q9] != 5 -> - or([q11 <= s_ExplicitVarSizeWithMarker_Marker /\ - s_ExplicitVarSizeWithMarker_Values[q11] = s_ExplicitVarSizeWithDummy[q9] - | q11 : int(1..4)]) - | q9 : int(1..4)]), - and([q13 <= s_ExplicitVarSizeWithMarker_Marker -> - or([s_ExplicitVarSizeWithDummy[q15] != 5 /\ - s_ExplicitVarSizeWithDummy[q15] = s_ExplicitVarSizeWithMarker_Values[q13] - | q15 : int(1..4)]) - | q13 : int(1..4)]), - and([s_ExplicitVarSizeWithFlags_Flags[q16 + 1] -> - s_ExplicitVarSizeWithFlags_Values[q16] < s_ExplicitVarSizeWithFlags_Values[q16 + 1] - | q16 : int(1..3)]), - and([s_ExplicitVarSizeWithFlags_Flags[q17] = false -> s_ExplicitVarSizeWithFlags_Values[q17] = 1 - | q17 : int(1..4)]), - and([s_ExplicitVarSizeWithFlags_Flags[q18 + 1] -> s_ExplicitVarSizeWithFlags_Flags[q18] | q18 : int(1..3)]), - and([s_ExplicitVarSizeWithFlags_Flags[q22] -> - or([q24 <= s_ExplicitVarSizeWithMarker_Marker /\ - s_ExplicitVarSizeWithMarker_Values[q24] = s_ExplicitVarSizeWithFlags_Values[q22] - | q24 : int(1..4)]) - | q22 : int(1..4)]), - and([q26 <= s_ExplicitVarSizeWithMarker_Marker -> - or([s_ExplicitVarSizeWithFlags_Flags[q28] /\ - s_ExplicitVarSizeWithFlags_Values[q28] = s_ExplicitVarSizeWithMarker_Values[q26] - | q28 : int(1..4)]) - | q26 : int(1..4)]), - and([s_ExplicitVarSizeWithFlags_Flags[q30] -> - or([s_ExplicitVarSizeWithDummy[q32] != 5 /\ - s_ExplicitVarSizeWithDummy[q32] = s_ExplicitVarSizeWithFlags_Values[q30] - | q32 : int(1..4)]) - | q30 : int(1..4)]), - and([s_ExplicitVarSizeWithDummy[q34] != 5 -> - or([s_ExplicitVarSizeWithFlags_Flags[q36] /\ - s_ExplicitVarSizeWithFlags_Values[q36] = s_ExplicitVarSizeWithDummy[q34] - | q36 : int(1..4)]) - | q34 : int(1..4)]) - diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_1-solution000001.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_1-solution000001.solution deleted file mode 100644 index 159a613983..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {2, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_1-solution000002.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_1-solution000002.solution deleted file mode 100644 index 40f3fd5c8f..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {2, 3, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_1-solution000003.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_1-solution000003.solution deleted file mode 100644 index 8b4ecbb66d..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_1-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 3} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_1-solution000004.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_1-solution000004.solution deleted file mode 100644 index 560dd0f2f7..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_1-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 3, 4} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_1-solution000005.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_1-solution000005.solution deleted file mode 100644 index 6eeacc9727..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_1-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_1-solution000006.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_1-solution000006.solution deleted file mode 100644 index 5963aac565..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_1-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 3} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_1-solution000007.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_1-solution000007.solution deleted file mode 100644 index bd956f44e3..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_1-solution000007.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 3, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_1.eprime b/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_1.eprime deleted file mode 100644 index 7c865a4def..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_1.eprime +++ /dev/null @@ -1,86 +0,0 @@ -language ESSENCE' 1.0 - -find s_ExplicitVarSizeWithMarker_Marker: int(0..4) -find s_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -find s_Occurrence: matrix indexed by [int(1..4)] of bool -letting let1 be -100 -find x: int(-100..100) -find conjure_aux1: int(-16..3) -branching on [s_Occurrence, s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithMarker_Values, x] -such that - and([and([q5 <= s_ExplicitVarSizeWithMarker_Marker, q6 <= s_ExplicitVarSizeWithMarker_Marker, - s_ExplicitVarSizeWithMarker_Values[q5] != s_ExplicitVarSizeWithMarker_Values[q6], - allDiff([s_ExplicitVarSizeWithMarker_Values[q5] + s_ExplicitVarSizeWithMarker_Values[q6], - s_ExplicitVarSizeWithMarker_Values[q5] * s_ExplicitVarSizeWithMarker_Values[q6], - s_ExplicitVarSizeWithMarker_Values[q5] / s_ExplicitVarSizeWithMarker_Values[q6]; - int(1..3)]), - (s_ExplicitVarSizeWithMarker_Values[q5] - s_ExplicitVarSizeWithMarker_Values[q6]) % 2 = 0; - int(1..5)]) - -> - min([s_ExplicitVarSizeWithMarker_Values[q5] + s_ExplicitVarSizeWithMarker_Values[q6], - s_ExplicitVarSizeWithMarker_Values[q5] - s_ExplicitVarSizeWithMarker_Values[q6], - s_ExplicitVarSizeWithMarker_Values[q5] * s_ExplicitVarSizeWithMarker_Values[q6], - s_ExplicitVarSizeWithMarker_Values[q5] / s_ExplicitVarSizeWithMarker_Values[q6]; - int(1..4)]) - <= conjure_aux1 - | q5 : int(1..4), q6 : int(1..4)]), - sum([toInt(and([q5 <= s_ExplicitVarSizeWithMarker_Marker, q6 <= s_ExplicitVarSizeWithMarker_Marker, - s_ExplicitVarSizeWithMarker_Values[q5] != s_ExplicitVarSizeWithMarker_Values[q6], - allDiff([s_ExplicitVarSizeWithMarker_Values[q5] + s_ExplicitVarSizeWithMarker_Values[q6], - s_ExplicitVarSizeWithMarker_Values[q5] * s_ExplicitVarSizeWithMarker_Values[q6], - s_ExplicitVarSizeWithMarker_Values[q5] / s_ExplicitVarSizeWithMarker_Values[q6]; - int(1..3)]), - (s_ExplicitVarSizeWithMarker_Values[q5] - s_ExplicitVarSizeWithMarker_Values[q6]) % 2 = 0; - int(1..5)])) - | q5 : int(1..4), q6 : int(1..4)]) - > 0 - -> - or([and([q5 <= s_ExplicitVarSizeWithMarker_Marker, q6 <= s_ExplicitVarSizeWithMarker_Marker, - s_ExplicitVarSizeWithMarker_Values[q5] != s_ExplicitVarSizeWithMarker_Values[q6], - allDiff([s_ExplicitVarSizeWithMarker_Values[q5] + s_ExplicitVarSizeWithMarker_Values[q6], - s_ExplicitVarSizeWithMarker_Values[q5] * s_ExplicitVarSizeWithMarker_Values[q6], - s_ExplicitVarSizeWithMarker_Values[q5] / s_ExplicitVarSizeWithMarker_Values[q6]; - int(1..3)]), - (s_ExplicitVarSizeWithMarker_Values[q5] - s_ExplicitVarSizeWithMarker_Values[q6]) % 2 = 0; - int(1..5)]) - /\ - min([s_ExplicitVarSizeWithMarker_Values[q5] + s_ExplicitVarSizeWithMarker_Values[q6], - s_ExplicitVarSizeWithMarker_Values[q5] - s_ExplicitVarSizeWithMarker_Values[q6], - s_ExplicitVarSizeWithMarker_Values[q5] * s_ExplicitVarSizeWithMarker_Values[q6], - s_ExplicitVarSizeWithMarker_Values[q5] / s_ExplicitVarSizeWithMarker_Values[q6]; - int(1..4)]) - = conjure_aux1 - | q5 : int(1..4), q6 : int(1..4)]), - sum([toInt(and([q5 <= s_ExplicitVarSizeWithMarker_Marker, q6 <= s_ExplicitVarSizeWithMarker_Marker, - s_ExplicitVarSizeWithMarker_Values[q5] != s_ExplicitVarSizeWithMarker_Values[q6], - allDiff([s_ExplicitVarSizeWithMarker_Values[q5] + s_ExplicitVarSizeWithMarker_Values[q6], - s_ExplicitVarSizeWithMarker_Values[q5] * s_ExplicitVarSizeWithMarker_Values[q6], - s_ExplicitVarSizeWithMarker_Values[q5] / s_ExplicitVarSizeWithMarker_Values[q6]; - int(1..3)]), - (s_ExplicitVarSizeWithMarker_Values[q5] - s_ExplicitVarSizeWithMarker_Values[q6]) % 2 = 0; - int(1..5)])) - | q5 : int(1..4), q6 : int(1..4)]) - = 0 - -> conjure_aux1 = -16, - x = conjure_aux1, - sum([toInt(and([q5 <= s_ExplicitVarSizeWithMarker_Marker, q6 <= s_ExplicitVarSizeWithMarker_Marker, - s_ExplicitVarSizeWithMarker_Values[q5] != s_ExplicitVarSizeWithMarker_Values[q6], - allDiff([s_ExplicitVarSizeWithMarker_Values[q5] + s_ExplicitVarSizeWithMarker_Values[q6], - s_ExplicitVarSizeWithMarker_Values[q5] * s_ExplicitVarSizeWithMarker_Values[q6], - s_ExplicitVarSizeWithMarker_Values[q5] / s_ExplicitVarSizeWithMarker_Values[q6]; - int(1..3)]), - (s_ExplicitVarSizeWithMarker_Values[q5] - s_ExplicitVarSizeWithMarker_Values[q6]) % 2 = 0; - int(1..5)])) - | q5 : int(1..4), q6 : int(1..4)]) - > 0, - and([q1 + 1 <= s_ExplicitVarSizeWithMarker_Marker -> - s_ExplicitVarSizeWithMarker_Values[q1] < s_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..3)]), - and([q2 > s_ExplicitVarSizeWithMarker_Marker -> s_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..4)]), - and([s_Occurrence[q28] -> - or([q30 <= s_ExplicitVarSizeWithMarker_Marker /\ s_ExplicitVarSizeWithMarker_Values[q30] = q28 - | q30 : int(1..4)]) - | q28 : int(1..4)]), - and([q32 <= s_ExplicitVarSizeWithMarker_Marker -> s_Occurrence[s_ExplicitVarSizeWithMarker_Values[q32]] - | q32 : int(1..4)]) - diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_2-solution000001.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_2-solution000001.solution deleted file mode 100644 index bd956f44e3..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 3, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_2-solution000002.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_2-solution000002.solution deleted file mode 100644 index 5963aac565..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 3} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_2-solution000003.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_2-solution000003.solution deleted file mode 100644 index 6eeacc9727..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_2-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_2-solution000004.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_2-solution000004.solution deleted file mode 100644 index 560dd0f2f7..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_2-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 3, 4} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_2-solution000005.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_2-solution000005.solution deleted file mode 100644 index 8b4ecbb66d..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_2-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 3} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_2-solution000006.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_2-solution000006.solution deleted file mode 100644 index 40f3fd5c8f..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_2-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {2, 3, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_2-solution000007.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_2-solution000007.solution deleted file mode 100644 index 159a613983..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_2-solution000007.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {2, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_2.eprime b/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_2.eprime deleted file mode 100644 index 28e3beabc3..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_2.eprime +++ /dev/null @@ -1,93 +0,0 @@ -language ESSENCE' 1.0 - -find s_ExplicitVarSizeWithMarker_Marker: int(0..4) -find s_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -find s_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -letting let1 be -100 -find x: int(-100..100) -find conjure_aux1: int(-16..3) -branching on [s_ExplicitVarSizeWithDummy, s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithMarker_Values, x] -such that - and([and([q16 <= s_ExplicitVarSizeWithMarker_Marker, q17 <= s_ExplicitVarSizeWithMarker_Marker, - s_ExplicitVarSizeWithMarker_Values[q16] != s_ExplicitVarSizeWithMarker_Values[q17], - allDiff([s_ExplicitVarSizeWithMarker_Values[q16] + s_ExplicitVarSizeWithMarker_Values[q17], - s_ExplicitVarSizeWithMarker_Values[q16] * s_ExplicitVarSizeWithMarker_Values[q17], - s_ExplicitVarSizeWithMarker_Values[q16] / s_ExplicitVarSizeWithMarker_Values[q17]; - int(1..3)]), - (s_ExplicitVarSizeWithMarker_Values[q16] - s_ExplicitVarSizeWithMarker_Values[q17]) % 2 = 0; - int(1..5)]) - -> - min([s_ExplicitVarSizeWithMarker_Values[q16] + s_ExplicitVarSizeWithMarker_Values[q17], - s_ExplicitVarSizeWithMarker_Values[q16] - s_ExplicitVarSizeWithMarker_Values[q17], - s_ExplicitVarSizeWithMarker_Values[q16] * s_ExplicitVarSizeWithMarker_Values[q17], - s_ExplicitVarSizeWithMarker_Values[q16] / s_ExplicitVarSizeWithMarker_Values[q17]; - int(1..4)]) - <= conjure_aux1 - | q16 : int(1..4), q17 : int(1..4)]), - sum([toInt(and([q16 <= s_ExplicitVarSizeWithMarker_Marker, q17 <= s_ExplicitVarSizeWithMarker_Marker, - s_ExplicitVarSizeWithMarker_Values[q16] != s_ExplicitVarSizeWithMarker_Values[q17], - allDiff([s_ExplicitVarSizeWithMarker_Values[q16] + s_ExplicitVarSizeWithMarker_Values[q17], - s_ExplicitVarSizeWithMarker_Values[q16] * s_ExplicitVarSizeWithMarker_Values[q17], - s_ExplicitVarSizeWithMarker_Values[q16] / s_ExplicitVarSizeWithMarker_Values[q17]; - int(1..3)]), - (s_ExplicitVarSizeWithMarker_Values[q16] - s_ExplicitVarSizeWithMarker_Values[q17]) % 2 = 0; - int(1..5)])) - | q16 : int(1..4), q17 : int(1..4)]) - > 0 - -> - or([and([q16 <= s_ExplicitVarSizeWithMarker_Marker, q17 <= s_ExplicitVarSizeWithMarker_Marker, - s_ExplicitVarSizeWithMarker_Values[q16] != s_ExplicitVarSizeWithMarker_Values[q17], - allDiff([s_ExplicitVarSizeWithMarker_Values[q16] + s_ExplicitVarSizeWithMarker_Values[q17], - s_ExplicitVarSizeWithMarker_Values[q16] * s_ExplicitVarSizeWithMarker_Values[q17], - s_ExplicitVarSizeWithMarker_Values[q16] / s_ExplicitVarSizeWithMarker_Values[q17]; - int(1..3)]), - (s_ExplicitVarSizeWithMarker_Values[q16] - s_ExplicitVarSizeWithMarker_Values[q17]) % 2 = 0; - int(1..5)]) - /\ - min([s_ExplicitVarSizeWithMarker_Values[q16] + s_ExplicitVarSizeWithMarker_Values[q17], - s_ExplicitVarSizeWithMarker_Values[q16] - s_ExplicitVarSizeWithMarker_Values[q17], - s_ExplicitVarSizeWithMarker_Values[q16] * s_ExplicitVarSizeWithMarker_Values[q17], - s_ExplicitVarSizeWithMarker_Values[q16] / s_ExplicitVarSizeWithMarker_Values[q17]; - int(1..4)]) - = conjure_aux1 - | q16 : int(1..4), q17 : int(1..4)]), - sum([toInt(and([q16 <= s_ExplicitVarSizeWithMarker_Marker, q17 <= s_ExplicitVarSizeWithMarker_Marker, - s_ExplicitVarSizeWithMarker_Values[q16] != s_ExplicitVarSizeWithMarker_Values[q17], - allDiff([s_ExplicitVarSizeWithMarker_Values[q16] + s_ExplicitVarSizeWithMarker_Values[q17], - s_ExplicitVarSizeWithMarker_Values[q16] * s_ExplicitVarSizeWithMarker_Values[q17], - s_ExplicitVarSizeWithMarker_Values[q16] / s_ExplicitVarSizeWithMarker_Values[q17]; - int(1..3)]), - (s_ExplicitVarSizeWithMarker_Values[q16] - s_ExplicitVarSizeWithMarker_Values[q17]) % 2 = 0; - int(1..5)])) - | q16 : int(1..4), q17 : int(1..4)]) - = 0 - -> conjure_aux1 = -16, - x = conjure_aux1, - sum([toInt(and([q16 <= s_ExplicitVarSizeWithMarker_Marker, q17 <= s_ExplicitVarSizeWithMarker_Marker, - s_ExplicitVarSizeWithMarker_Values[q16] != s_ExplicitVarSizeWithMarker_Values[q17], - allDiff([s_ExplicitVarSizeWithMarker_Values[q16] + s_ExplicitVarSizeWithMarker_Values[q17], - s_ExplicitVarSizeWithMarker_Values[q16] * s_ExplicitVarSizeWithMarker_Values[q17], - s_ExplicitVarSizeWithMarker_Values[q16] / s_ExplicitVarSizeWithMarker_Values[q17]; - int(1..3)]), - (s_ExplicitVarSizeWithMarker_Values[q16] - s_ExplicitVarSizeWithMarker_Values[q17]) % 2 = 0; - int(1..5)])) - | q16 : int(1..4), q17 : int(1..4)]) - > 0, - and([q1 + 1 <= s_ExplicitVarSizeWithMarker_Marker -> - s_ExplicitVarSizeWithMarker_Values[q1] < s_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..3)]), - and([q2 > s_ExplicitVarSizeWithMarker_Marker -> s_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..4)]), - and([s_ExplicitVarSizeWithDummy[q4] < s_ExplicitVarSizeWithDummy[q4 + 1] \/ s_ExplicitVarSizeWithDummy[q4] = 5 - | q4 : int(1..3)]), - and([s_ExplicitVarSizeWithDummy[q5] = 5 -> s_ExplicitVarSizeWithDummy[q5 + 1] = 5 | q5 : int(1..3)]), - and([s_ExplicitVarSizeWithDummy[q9] != 5 -> - or([q11 <= s_ExplicitVarSizeWithMarker_Marker /\ - s_ExplicitVarSizeWithMarker_Values[q11] = s_ExplicitVarSizeWithDummy[q9] - | q11 : int(1..4)]) - | q9 : int(1..4)]), - and([q13 <= s_ExplicitVarSizeWithMarker_Marker -> - or([s_ExplicitVarSizeWithDummy[q15] != 5 /\ - s_ExplicitVarSizeWithDummy[q15] = s_ExplicitVarSizeWithMarker_Values[q13] - | q15 : int(1..4)]) - | q13 : int(1..4)]) - diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_3-solution000001.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_3-solution000001.solution deleted file mode 100644 index 8b4ecbb66d..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_3-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 3} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_3-solution000002.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_3-solution000002.solution deleted file mode 100644 index 159a613983..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_3-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {2, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_3-solution000003.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_3-solution000003.solution deleted file mode 100644 index 5963aac565..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_3-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 3} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_3-solution000004.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_3-solution000004.solution deleted file mode 100644 index 6eeacc9727..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_3-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_3-solution000005.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_3-solution000005.solution deleted file mode 100644 index 560dd0f2f7..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_3-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 3, 4} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_3-solution000006.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_3-solution000006.solution deleted file mode 100644 index 40f3fd5c8f..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_3-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {2, 3, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_3-solution000007.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_3-solution000007.solution deleted file mode 100644 index bd956f44e3..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_3-solution000007.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 3, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_3.eprime b/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_3.eprime deleted file mode 100644 index 2395a6a64c..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_3.eprime +++ /dev/null @@ -1,79 +0,0 @@ -language ESSENCE' 1.0 - -find s_ExplicitVarSizeWithMarker_Marker: int(0..4) -find s_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -letting let1 be -100 -find x: int(-100..100) -find conjure_aux1: int(-16..3) -branching on [s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithMarker_Values, x] -such that - and([and([q4 <= s_ExplicitVarSizeWithMarker_Marker, q5 <= s_ExplicitVarSizeWithMarker_Marker, - s_ExplicitVarSizeWithMarker_Values[q4] != s_ExplicitVarSizeWithMarker_Values[q5], - allDiff([s_ExplicitVarSizeWithMarker_Values[q4] + s_ExplicitVarSizeWithMarker_Values[q5], - s_ExplicitVarSizeWithMarker_Values[q4] * s_ExplicitVarSizeWithMarker_Values[q5], - s_ExplicitVarSizeWithMarker_Values[q4] / s_ExplicitVarSizeWithMarker_Values[q5]; - int(1..3)]), - (s_ExplicitVarSizeWithMarker_Values[q4] - s_ExplicitVarSizeWithMarker_Values[q5]) % 2 = 0; - int(1..5)]) - -> - min([s_ExplicitVarSizeWithMarker_Values[q4] + s_ExplicitVarSizeWithMarker_Values[q5], - s_ExplicitVarSizeWithMarker_Values[q4] - s_ExplicitVarSizeWithMarker_Values[q5], - s_ExplicitVarSizeWithMarker_Values[q4] * s_ExplicitVarSizeWithMarker_Values[q5], - s_ExplicitVarSizeWithMarker_Values[q4] / s_ExplicitVarSizeWithMarker_Values[q5]; - int(1..4)]) - <= conjure_aux1 - | q4 : int(1..4), q5 : int(1..4)]), - sum([toInt(and([q4 <= s_ExplicitVarSizeWithMarker_Marker, q5 <= s_ExplicitVarSizeWithMarker_Marker, - s_ExplicitVarSizeWithMarker_Values[q4] != s_ExplicitVarSizeWithMarker_Values[q5], - allDiff([s_ExplicitVarSizeWithMarker_Values[q4] + s_ExplicitVarSizeWithMarker_Values[q5], - s_ExplicitVarSizeWithMarker_Values[q4] * s_ExplicitVarSizeWithMarker_Values[q5], - s_ExplicitVarSizeWithMarker_Values[q4] / s_ExplicitVarSizeWithMarker_Values[q5]; - int(1..3)]), - (s_ExplicitVarSizeWithMarker_Values[q4] - s_ExplicitVarSizeWithMarker_Values[q5]) % 2 = 0; - int(1..5)])) - | q4 : int(1..4), q5 : int(1..4)]) - > 0 - -> - or([and([q4 <= s_ExplicitVarSizeWithMarker_Marker, q5 <= s_ExplicitVarSizeWithMarker_Marker, - s_ExplicitVarSizeWithMarker_Values[q4] != s_ExplicitVarSizeWithMarker_Values[q5], - allDiff([s_ExplicitVarSizeWithMarker_Values[q4] + s_ExplicitVarSizeWithMarker_Values[q5], - s_ExplicitVarSizeWithMarker_Values[q4] * s_ExplicitVarSizeWithMarker_Values[q5], - s_ExplicitVarSizeWithMarker_Values[q4] / s_ExplicitVarSizeWithMarker_Values[q5]; - int(1..3)]), - (s_ExplicitVarSizeWithMarker_Values[q4] - s_ExplicitVarSizeWithMarker_Values[q5]) % 2 = 0; - int(1..5)]) - /\ - min([s_ExplicitVarSizeWithMarker_Values[q4] + s_ExplicitVarSizeWithMarker_Values[q5], - s_ExplicitVarSizeWithMarker_Values[q4] - s_ExplicitVarSizeWithMarker_Values[q5], - s_ExplicitVarSizeWithMarker_Values[q4] * s_ExplicitVarSizeWithMarker_Values[q5], - s_ExplicitVarSizeWithMarker_Values[q4] / s_ExplicitVarSizeWithMarker_Values[q5]; - int(1..4)]) - = conjure_aux1 - | q4 : int(1..4), q5 : int(1..4)]), - sum([toInt(and([q4 <= s_ExplicitVarSizeWithMarker_Marker, q5 <= s_ExplicitVarSizeWithMarker_Marker, - s_ExplicitVarSizeWithMarker_Values[q4] != s_ExplicitVarSizeWithMarker_Values[q5], - allDiff([s_ExplicitVarSizeWithMarker_Values[q4] + s_ExplicitVarSizeWithMarker_Values[q5], - s_ExplicitVarSizeWithMarker_Values[q4] * s_ExplicitVarSizeWithMarker_Values[q5], - s_ExplicitVarSizeWithMarker_Values[q4] / s_ExplicitVarSizeWithMarker_Values[q5]; - int(1..3)]), - (s_ExplicitVarSizeWithMarker_Values[q4] - s_ExplicitVarSizeWithMarker_Values[q5]) % 2 = 0; - int(1..5)])) - | q4 : int(1..4), q5 : int(1..4)]) - = 0 - -> conjure_aux1 = -16, - x = conjure_aux1, - sum([toInt(and([q4 <= s_ExplicitVarSizeWithMarker_Marker, q5 <= s_ExplicitVarSizeWithMarker_Marker, - s_ExplicitVarSizeWithMarker_Values[q4] != s_ExplicitVarSizeWithMarker_Values[q5], - allDiff([s_ExplicitVarSizeWithMarker_Values[q4] + s_ExplicitVarSizeWithMarker_Values[q5], - s_ExplicitVarSizeWithMarker_Values[q4] * s_ExplicitVarSizeWithMarker_Values[q5], - s_ExplicitVarSizeWithMarker_Values[q4] / s_ExplicitVarSizeWithMarker_Values[q5]; - int(1..3)]), - (s_ExplicitVarSizeWithMarker_Values[q4] - s_ExplicitVarSizeWithMarker_Values[q5]) % 2 = 0; - int(1..5)])) - | q4 : int(1..4), q5 : int(1..4)]) - > 0, - and([q1 + 1 <= s_ExplicitVarSizeWithMarker_Marker -> - s_ExplicitVarSizeWithMarker_Values[q1] < s_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..3)]), - and([q2 > s_ExplicitVarSizeWithMarker_Marker -> s_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..4)]) - diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_4-solution000001.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_4-solution000001.solution deleted file mode 100644 index 8b4ecbb66d..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_4-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 3} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_4-solution000002.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_4-solution000002.solution deleted file mode 100644 index 159a613983..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_4-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {2, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_4-solution000003.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_4-solution000003.solution deleted file mode 100644 index 5963aac565..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_4-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 3} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_4-solution000004.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_4-solution000004.solution deleted file mode 100644 index 6eeacc9727..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_4-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_4-solution000005.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_4-solution000005.solution deleted file mode 100644 index 560dd0f2f7..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_4-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 3, 4} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_4-solution000006.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_4-solution000006.solution deleted file mode 100644 index 40f3fd5c8f..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_4-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {2, 3, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_4-solution000007.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_4-solution000007.solution deleted file mode 100644 index bd956f44e3..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_4-solution000007.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 3, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_4.eprime b/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_4.eprime deleted file mode 100644 index 04c74bb0a1..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_4.eprime +++ /dev/null @@ -1,98 +0,0 @@ -language ESSENCE' 1.0 - -find s_ExplicitVarSizeWithMarker_Marker: int(0..4) -find s_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -find s_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find s_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -letting let1 be -100 -find x: int(-100..100) -find conjure_aux1: int(-16..3) -branching on - [s_ExplicitVarSizeWithFlags_Flags, s_ExplicitVarSizeWithFlags_Values, s_ExplicitVarSizeWithMarker_Marker, - s_ExplicitVarSizeWithMarker_Values, x] -such that - and([and([q17 <= s_ExplicitVarSizeWithMarker_Marker, q18 <= s_ExplicitVarSizeWithMarker_Marker, - s_ExplicitVarSizeWithMarker_Values[q17] != s_ExplicitVarSizeWithMarker_Values[q18], - allDiff([s_ExplicitVarSizeWithMarker_Values[q17] + s_ExplicitVarSizeWithMarker_Values[q18], - s_ExplicitVarSizeWithMarker_Values[q17] * s_ExplicitVarSizeWithMarker_Values[q18], - s_ExplicitVarSizeWithMarker_Values[q17] / s_ExplicitVarSizeWithMarker_Values[q18]; - int(1..3)]), - (s_ExplicitVarSizeWithMarker_Values[q17] - s_ExplicitVarSizeWithMarker_Values[q18]) % 2 = 0; - int(1..5)]) - -> - min([s_ExplicitVarSizeWithMarker_Values[q17] + s_ExplicitVarSizeWithMarker_Values[q18], - s_ExplicitVarSizeWithMarker_Values[q17] - s_ExplicitVarSizeWithMarker_Values[q18], - s_ExplicitVarSizeWithMarker_Values[q17] * s_ExplicitVarSizeWithMarker_Values[q18], - s_ExplicitVarSizeWithMarker_Values[q17] / s_ExplicitVarSizeWithMarker_Values[q18]; - int(1..4)]) - <= conjure_aux1 - | q17 : int(1..4), q18 : int(1..4)]), - sum([toInt(and([q17 <= s_ExplicitVarSizeWithMarker_Marker, q18 <= s_ExplicitVarSizeWithMarker_Marker, - s_ExplicitVarSizeWithMarker_Values[q17] != s_ExplicitVarSizeWithMarker_Values[q18], - allDiff([s_ExplicitVarSizeWithMarker_Values[q17] + s_ExplicitVarSizeWithMarker_Values[q18], - s_ExplicitVarSizeWithMarker_Values[q17] * s_ExplicitVarSizeWithMarker_Values[q18], - s_ExplicitVarSizeWithMarker_Values[q17] / s_ExplicitVarSizeWithMarker_Values[q18]; - int(1..3)]), - (s_ExplicitVarSizeWithMarker_Values[q17] - s_ExplicitVarSizeWithMarker_Values[q18]) % 2 = 0; - int(1..5)])) - | q17 : int(1..4), q18 : int(1..4)]) - > 0 - -> - or([and([q17 <= s_ExplicitVarSizeWithMarker_Marker, q18 <= s_ExplicitVarSizeWithMarker_Marker, - s_ExplicitVarSizeWithMarker_Values[q17] != s_ExplicitVarSizeWithMarker_Values[q18], - allDiff([s_ExplicitVarSizeWithMarker_Values[q17] + s_ExplicitVarSizeWithMarker_Values[q18], - s_ExplicitVarSizeWithMarker_Values[q17] * s_ExplicitVarSizeWithMarker_Values[q18], - s_ExplicitVarSizeWithMarker_Values[q17] / s_ExplicitVarSizeWithMarker_Values[q18]; - int(1..3)]), - (s_ExplicitVarSizeWithMarker_Values[q17] - s_ExplicitVarSizeWithMarker_Values[q18]) % 2 = 0; - int(1..5)]) - /\ - min([s_ExplicitVarSizeWithMarker_Values[q17] + s_ExplicitVarSizeWithMarker_Values[q18], - s_ExplicitVarSizeWithMarker_Values[q17] - s_ExplicitVarSizeWithMarker_Values[q18], - s_ExplicitVarSizeWithMarker_Values[q17] * s_ExplicitVarSizeWithMarker_Values[q18], - s_ExplicitVarSizeWithMarker_Values[q17] / s_ExplicitVarSizeWithMarker_Values[q18]; - int(1..4)]) - = conjure_aux1 - | q17 : int(1..4), q18 : int(1..4)]), - sum([toInt(and([q17 <= s_ExplicitVarSizeWithMarker_Marker, q18 <= s_ExplicitVarSizeWithMarker_Marker, - s_ExplicitVarSizeWithMarker_Values[q17] != s_ExplicitVarSizeWithMarker_Values[q18], - allDiff([s_ExplicitVarSizeWithMarker_Values[q17] + s_ExplicitVarSizeWithMarker_Values[q18], - s_ExplicitVarSizeWithMarker_Values[q17] * s_ExplicitVarSizeWithMarker_Values[q18], - s_ExplicitVarSizeWithMarker_Values[q17] / s_ExplicitVarSizeWithMarker_Values[q18]; - int(1..3)]), - (s_ExplicitVarSizeWithMarker_Values[q17] - s_ExplicitVarSizeWithMarker_Values[q18]) % 2 = 0; - int(1..5)])) - | q17 : int(1..4), q18 : int(1..4)]) - = 0 - -> conjure_aux1 = -16, - x = conjure_aux1, - sum([toInt(and([q17 <= s_ExplicitVarSizeWithMarker_Marker, q18 <= s_ExplicitVarSizeWithMarker_Marker, - s_ExplicitVarSizeWithMarker_Values[q17] != s_ExplicitVarSizeWithMarker_Values[q18], - allDiff([s_ExplicitVarSizeWithMarker_Values[q17] + s_ExplicitVarSizeWithMarker_Values[q18], - s_ExplicitVarSizeWithMarker_Values[q17] * s_ExplicitVarSizeWithMarker_Values[q18], - s_ExplicitVarSizeWithMarker_Values[q17] / s_ExplicitVarSizeWithMarker_Values[q18]; - int(1..3)]), - (s_ExplicitVarSizeWithMarker_Values[q17] - s_ExplicitVarSizeWithMarker_Values[q18]) % 2 = 0; - int(1..5)])) - | q17 : int(1..4), q18 : int(1..4)]) - > 0, - and([q1 + 1 <= s_ExplicitVarSizeWithMarker_Marker -> - s_ExplicitVarSizeWithMarker_Values[q1] < s_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..3)]), - and([q2 > s_ExplicitVarSizeWithMarker_Marker -> s_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..4)]), - and([s_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> - s_ExplicitVarSizeWithFlags_Values[q4] < s_ExplicitVarSizeWithFlags_Values[q4 + 1] - | q4 : int(1..3)]), - and([s_ExplicitVarSizeWithFlags_Flags[q5] = false -> s_ExplicitVarSizeWithFlags_Values[q5] = 1 | q5 : int(1..4)]), - and([s_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> s_ExplicitVarSizeWithFlags_Flags[q6] | q6 : int(1..3)]), - and([s_ExplicitVarSizeWithFlags_Flags[q10] -> - or([q12 <= s_ExplicitVarSizeWithMarker_Marker /\ - s_ExplicitVarSizeWithMarker_Values[q12] = s_ExplicitVarSizeWithFlags_Values[q10] - | q12 : int(1..4)]) - | q10 : int(1..4)]), - and([q14 <= s_ExplicitVarSizeWithMarker_Marker -> - or([s_ExplicitVarSizeWithFlags_Flags[q16] /\ - s_ExplicitVarSizeWithFlags_Values[q16] = s_ExplicitVarSizeWithMarker_Values[q14] - | q16 : int(1..4)]) - | q14 : int(1..4)]) - diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_4_1-solution000001.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_4_1-solution000001.solution deleted file mode 100644 index 159a613983..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_3_4_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {2, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_4_1-solution000002.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_4_1-solution000002.solution deleted file mode 100644 index 40f3fd5c8f..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_3_4_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {2, 3, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_4_1-solution000003.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_4_1-solution000003.solution deleted file mode 100644 index 8b4ecbb66d..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_3_4_1-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 3} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_4_1-solution000004.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_4_1-solution000004.solution deleted file mode 100644 index 560dd0f2f7..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_3_4_1-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 3, 4} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_4_1-solution000005.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_4_1-solution000005.solution deleted file mode 100644 index 6eeacc9727..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_3_4_1-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_4_1-solution000006.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_4_1-solution000006.solution deleted file mode 100644 index 5963aac565..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_3_4_1-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 3} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_4_1-solution000007.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_4_1-solution000007.solution deleted file mode 100644 index bd956f44e3..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_3_4_1-solution000007.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 3, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_4_1.eprime b/tests/exhaustive/basic/comprehension_letting/expected/model_3_4_1.eprime deleted file mode 100644 index 04d3b5c94a..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_3_4_1.eprime +++ /dev/null @@ -1,110 +0,0 @@ -language ESSENCE' 1.0 - -find s_ExplicitVarSizeWithMarker_Marker: int(0..4) -find s_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -find s_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find s_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -find s_Occurrence: matrix indexed by [int(1..4)] of bool -letting let1 be -100 -find x: int(-100..100) -find conjure_aux1: int(-16..3) -branching on - [s_Occurrence, s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithMarker_Values, - s_ExplicitVarSizeWithFlags_Flags, s_ExplicitVarSizeWithFlags_Values, x] -such that - and([and([q28 <= s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithFlags_Flags[q29], - s_ExplicitVarSizeWithMarker_Values[q28] != s_ExplicitVarSizeWithFlags_Values[q29], - allDiff([s_ExplicitVarSizeWithMarker_Values[q28] + s_ExplicitVarSizeWithFlags_Values[q29], - s_ExplicitVarSizeWithMarker_Values[q28] * s_ExplicitVarSizeWithFlags_Values[q29], - s_ExplicitVarSizeWithMarker_Values[q28] / s_ExplicitVarSizeWithFlags_Values[q29]; - int(1..3)]), - (s_ExplicitVarSizeWithMarker_Values[q28] - s_ExplicitVarSizeWithFlags_Values[q29]) % 2 = 0; - int(1..5)]) - -> - min([s_ExplicitVarSizeWithMarker_Values[q28] + s_ExplicitVarSizeWithFlags_Values[q29], - s_ExplicitVarSizeWithMarker_Values[q28] - s_ExplicitVarSizeWithFlags_Values[q29], - s_ExplicitVarSizeWithMarker_Values[q28] * s_ExplicitVarSizeWithFlags_Values[q29], - s_ExplicitVarSizeWithMarker_Values[q28] / s_ExplicitVarSizeWithFlags_Values[q29]; - int(1..4)]) - <= conjure_aux1 - | q28 : int(1..4), q29 : int(1..4)]), - sum([toInt(and([q28 <= s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithFlags_Flags[q29], - s_ExplicitVarSizeWithMarker_Values[q28] != s_ExplicitVarSizeWithFlags_Values[q29], - allDiff([s_ExplicitVarSizeWithMarker_Values[q28] + s_ExplicitVarSizeWithFlags_Values[q29], - s_ExplicitVarSizeWithMarker_Values[q28] * s_ExplicitVarSizeWithFlags_Values[q29], - s_ExplicitVarSizeWithMarker_Values[q28] / s_ExplicitVarSizeWithFlags_Values[q29]; - int(1..3)]), - (s_ExplicitVarSizeWithMarker_Values[q28] - s_ExplicitVarSizeWithFlags_Values[q29]) % 2 = 0; - int(1..5)])) - | q28 : int(1..4), q29 : int(1..4)]) - > 0 - -> - or([and([q28 <= s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithFlags_Flags[q29], - s_ExplicitVarSizeWithMarker_Values[q28] != s_ExplicitVarSizeWithFlags_Values[q29], - allDiff([s_ExplicitVarSizeWithMarker_Values[q28] + s_ExplicitVarSizeWithFlags_Values[q29], - s_ExplicitVarSizeWithMarker_Values[q28] * s_ExplicitVarSizeWithFlags_Values[q29], - s_ExplicitVarSizeWithMarker_Values[q28] / s_ExplicitVarSizeWithFlags_Values[q29]; - int(1..3)]), - (s_ExplicitVarSizeWithMarker_Values[q28] - s_ExplicitVarSizeWithFlags_Values[q29]) % 2 = 0; - int(1..5)]) - /\ - min([s_ExplicitVarSizeWithMarker_Values[q28] + s_ExplicitVarSizeWithFlags_Values[q29], - s_ExplicitVarSizeWithMarker_Values[q28] - s_ExplicitVarSizeWithFlags_Values[q29], - s_ExplicitVarSizeWithMarker_Values[q28] * s_ExplicitVarSizeWithFlags_Values[q29], - s_ExplicitVarSizeWithMarker_Values[q28] / s_ExplicitVarSizeWithFlags_Values[q29]; - int(1..4)]) - = conjure_aux1 - | q28 : int(1..4), q29 : int(1..4)]), - sum([toInt(and([q28 <= s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithFlags_Flags[q29], - s_ExplicitVarSizeWithMarker_Values[q28] != s_ExplicitVarSizeWithFlags_Values[q29], - allDiff([s_ExplicitVarSizeWithMarker_Values[q28] + s_ExplicitVarSizeWithFlags_Values[q29], - s_ExplicitVarSizeWithMarker_Values[q28] * s_ExplicitVarSizeWithFlags_Values[q29], - s_ExplicitVarSizeWithMarker_Values[q28] / s_ExplicitVarSizeWithFlags_Values[q29]; - int(1..3)]), - (s_ExplicitVarSizeWithMarker_Values[q28] - s_ExplicitVarSizeWithFlags_Values[q29]) % 2 = 0; - int(1..5)])) - | q28 : int(1..4), q29 : int(1..4)]) - = 0 - -> conjure_aux1 = -16, - x = conjure_aux1, - sum([toInt(and([q28 <= s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithFlags_Flags[q29], - s_ExplicitVarSizeWithMarker_Values[q28] != s_ExplicitVarSizeWithFlags_Values[q29], - allDiff([s_ExplicitVarSizeWithMarker_Values[q28] + s_ExplicitVarSizeWithFlags_Values[q29], - s_ExplicitVarSizeWithMarker_Values[q28] * s_ExplicitVarSizeWithFlags_Values[q29], - s_ExplicitVarSizeWithMarker_Values[q28] / s_ExplicitVarSizeWithFlags_Values[q29]; - int(1..3)]), - (s_ExplicitVarSizeWithMarker_Values[q28] - s_ExplicitVarSizeWithFlags_Values[q29]) % 2 = 0; - int(1..5)])) - | q28 : int(1..4), q29 : int(1..4)]) - > 0, - and([q1 + 1 <= s_ExplicitVarSizeWithMarker_Marker -> - s_ExplicitVarSizeWithMarker_Values[q1] < s_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..3)]), - and([q2 > s_ExplicitVarSizeWithMarker_Marker -> s_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..4)]), - and([s_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> - s_ExplicitVarSizeWithFlags_Values[q4] < s_ExplicitVarSizeWithFlags_Values[q4 + 1] - | q4 : int(1..3)]), - and([s_ExplicitVarSizeWithFlags_Flags[q5] = false -> s_ExplicitVarSizeWithFlags_Values[q5] = 1 | q5 : int(1..4)]), - and([s_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> s_ExplicitVarSizeWithFlags_Flags[q6] | q6 : int(1..3)]), - and([s_ExplicitVarSizeWithFlags_Flags[q10] -> - or([q12 <= s_ExplicitVarSizeWithMarker_Marker /\ - s_ExplicitVarSizeWithMarker_Values[q12] = s_ExplicitVarSizeWithFlags_Values[q10] - | q12 : int(1..4)]) - | q10 : int(1..4)]), - and([q14 <= s_ExplicitVarSizeWithMarker_Marker -> - or([s_ExplicitVarSizeWithFlags_Flags[q16] /\ - s_ExplicitVarSizeWithFlags_Values[q16] = s_ExplicitVarSizeWithMarker_Values[q14] - | q16 : int(1..4)]) - | q14 : int(1..4)]), - and([s_Occurrence[q18] -> - or([q20 <= s_ExplicitVarSizeWithMarker_Marker /\ s_ExplicitVarSizeWithMarker_Values[q20] = q18 - | q20 : int(1..4)]) - | q18 : int(1..4)]), - and([q22 <= s_ExplicitVarSizeWithMarker_Marker -> s_Occurrence[s_ExplicitVarSizeWithMarker_Values[q22]] - | q22 : int(1..4)]), - and([s_Occurrence[q23] -> - or([s_ExplicitVarSizeWithFlags_Flags[q25] /\ s_ExplicitVarSizeWithFlags_Values[q25] = q23 | q25 : int(1..4)]) - | q23 : int(1..4)]), - and([s_ExplicitVarSizeWithFlags_Flags[q27] -> s_Occurrence[s_ExplicitVarSizeWithFlags_Values[q27]] - | q27 : int(1..4)]) - diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_4_2-solution000001.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_4_2-solution000001.solution deleted file mode 100644 index bd956f44e3..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_3_4_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 3, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_4_2-solution000002.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_4_2-solution000002.solution deleted file mode 100644 index 5963aac565..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_3_4_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 3} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_4_2-solution000003.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_4_2-solution000003.solution deleted file mode 100644 index 6eeacc9727..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_3_4_2-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_4_2-solution000004.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_4_2-solution000004.solution deleted file mode 100644 index 560dd0f2f7..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_3_4_2-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 3, 4} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_4_2-solution000005.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_4_2-solution000005.solution deleted file mode 100644 index 8b4ecbb66d..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_3_4_2-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 3} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_4_2-solution000006.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_4_2-solution000006.solution deleted file mode 100644 index 40f3fd5c8f..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_3_4_2-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {2, 3, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_4_2-solution000007.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_4_2-solution000007.solution deleted file mode 100644 index 159a613983..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_3_4_2-solution000007.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {2, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_4_2.eprime b/tests/exhaustive/basic/comprehension_letting/expected/model_3_4_2.eprime deleted file mode 100644 index cc4980db20..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_3_4_2.eprime +++ /dev/null @@ -1,122 +0,0 @@ -language ESSENCE' 1.0 - -find s_ExplicitVarSizeWithMarker_Marker: int(0..4) -find s_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -find s_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find s_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -find s_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -letting let1 be -100 -find x: int(-100..100) -find conjure_aux1: int(-16..3) -branching on - [s_ExplicitVarSizeWithDummy, s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithMarker_Values, - s_ExplicitVarSizeWithFlags_Flags, s_ExplicitVarSizeWithFlags_Values, x] -such that - and([and([q37 <= s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithFlags_Flags[q38], - s_ExplicitVarSizeWithMarker_Values[q37] != s_ExplicitVarSizeWithFlags_Values[q38], - allDiff([s_ExplicitVarSizeWithMarker_Values[q37] + s_ExplicitVarSizeWithFlags_Values[q38], - s_ExplicitVarSizeWithMarker_Values[q37] * s_ExplicitVarSizeWithFlags_Values[q38], - s_ExplicitVarSizeWithMarker_Values[q37] / s_ExplicitVarSizeWithFlags_Values[q38]; - int(1..3)]), - (s_ExplicitVarSizeWithMarker_Values[q37] - s_ExplicitVarSizeWithFlags_Values[q38]) % 2 = 0; - int(1..5)]) - -> - min([s_ExplicitVarSizeWithMarker_Values[q37] + s_ExplicitVarSizeWithFlags_Values[q38], - s_ExplicitVarSizeWithMarker_Values[q37] - s_ExplicitVarSizeWithFlags_Values[q38], - s_ExplicitVarSizeWithMarker_Values[q37] * s_ExplicitVarSizeWithFlags_Values[q38], - s_ExplicitVarSizeWithMarker_Values[q37] / s_ExplicitVarSizeWithFlags_Values[q38]; - int(1..4)]) - <= conjure_aux1 - | q37 : int(1..4), q38 : int(1..4)]), - sum([toInt(and([q37 <= s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithFlags_Flags[q38], - s_ExplicitVarSizeWithMarker_Values[q37] != s_ExplicitVarSizeWithFlags_Values[q38], - allDiff([s_ExplicitVarSizeWithMarker_Values[q37] + s_ExplicitVarSizeWithFlags_Values[q38], - s_ExplicitVarSizeWithMarker_Values[q37] * s_ExplicitVarSizeWithFlags_Values[q38], - s_ExplicitVarSizeWithMarker_Values[q37] / s_ExplicitVarSizeWithFlags_Values[q38]; - int(1..3)]), - (s_ExplicitVarSizeWithMarker_Values[q37] - s_ExplicitVarSizeWithFlags_Values[q38]) % 2 = 0; - int(1..5)])) - | q37 : int(1..4), q38 : int(1..4)]) - > 0 - -> - or([and([q37 <= s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithFlags_Flags[q38], - s_ExplicitVarSizeWithMarker_Values[q37] != s_ExplicitVarSizeWithFlags_Values[q38], - allDiff([s_ExplicitVarSizeWithMarker_Values[q37] + s_ExplicitVarSizeWithFlags_Values[q38], - s_ExplicitVarSizeWithMarker_Values[q37] * s_ExplicitVarSizeWithFlags_Values[q38], - s_ExplicitVarSizeWithMarker_Values[q37] / s_ExplicitVarSizeWithFlags_Values[q38]; - int(1..3)]), - (s_ExplicitVarSizeWithMarker_Values[q37] - s_ExplicitVarSizeWithFlags_Values[q38]) % 2 = 0; - int(1..5)]) - /\ - min([s_ExplicitVarSizeWithMarker_Values[q37] + s_ExplicitVarSizeWithFlags_Values[q38], - s_ExplicitVarSizeWithMarker_Values[q37] - s_ExplicitVarSizeWithFlags_Values[q38], - s_ExplicitVarSizeWithMarker_Values[q37] * s_ExplicitVarSizeWithFlags_Values[q38], - s_ExplicitVarSizeWithMarker_Values[q37] / s_ExplicitVarSizeWithFlags_Values[q38]; - int(1..4)]) - = conjure_aux1 - | q37 : int(1..4), q38 : int(1..4)]), - sum([toInt(and([q37 <= s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithFlags_Flags[q38], - s_ExplicitVarSizeWithMarker_Values[q37] != s_ExplicitVarSizeWithFlags_Values[q38], - allDiff([s_ExplicitVarSizeWithMarker_Values[q37] + s_ExplicitVarSizeWithFlags_Values[q38], - s_ExplicitVarSizeWithMarker_Values[q37] * s_ExplicitVarSizeWithFlags_Values[q38], - s_ExplicitVarSizeWithMarker_Values[q37] / s_ExplicitVarSizeWithFlags_Values[q38]; - int(1..3)]), - (s_ExplicitVarSizeWithMarker_Values[q37] - s_ExplicitVarSizeWithFlags_Values[q38]) % 2 = 0; - int(1..5)])) - | q37 : int(1..4), q38 : int(1..4)]) - = 0 - -> conjure_aux1 = -16, - x = conjure_aux1, - sum([toInt(and([q37 <= s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithFlags_Flags[q38], - s_ExplicitVarSizeWithMarker_Values[q37] != s_ExplicitVarSizeWithFlags_Values[q38], - allDiff([s_ExplicitVarSizeWithMarker_Values[q37] + s_ExplicitVarSizeWithFlags_Values[q38], - s_ExplicitVarSizeWithMarker_Values[q37] * s_ExplicitVarSizeWithFlags_Values[q38], - s_ExplicitVarSizeWithMarker_Values[q37] / s_ExplicitVarSizeWithFlags_Values[q38]; - int(1..3)]), - (s_ExplicitVarSizeWithMarker_Values[q37] - s_ExplicitVarSizeWithFlags_Values[q38]) % 2 = 0; - int(1..5)])) - | q37 : int(1..4), q38 : int(1..4)]) - > 0, - and([q1 + 1 <= s_ExplicitVarSizeWithMarker_Marker -> - s_ExplicitVarSizeWithMarker_Values[q1] < s_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..3)]), - and([q2 > s_ExplicitVarSizeWithMarker_Marker -> s_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..4)]), - and([s_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> - s_ExplicitVarSizeWithFlags_Values[q4] < s_ExplicitVarSizeWithFlags_Values[q4 + 1] - | q4 : int(1..3)]), - and([s_ExplicitVarSizeWithFlags_Flags[q5] = false -> s_ExplicitVarSizeWithFlags_Values[q5] = 1 | q5 : int(1..4)]), - and([s_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> s_ExplicitVarSizeWithFlags_Flags[q6] | q6 : int(1..3)]), - and([s_ExplicitVarSizeWithFlags_Flags[q10] -> - or([q12 <= s_ExplicitVarSizeWithMarker_Marker /\ - s_ExplicitVarSizeWithMarker_Values[q12] = s_ExplicitVarSizeWithFlags_Values[q10] - | q12 : int(1..4)]) - | q10 : int(1..4)]), - and([q14 <= s_ExplicitVarSizeWithMarker_Marker -> - or([s_ExplicitVarSizeWithFlags_Flags[q16] /\ - s_ExplicitVarSizeWithFlags_Values[q16] = s_ExplicitVarSizeWithMarker_Values[q14] - | q16 : int(1..4)]) - | q14 : int(1..4)]), - and([s_ExplicitVarSizeWithDummy[q17] < s_ExplicitVarSizeWithDummy[q17 + 1] \/ s_ExplicitVarSizeWithDummy[q17] = 5 - | q17 : int(1..3)]), - and([s_ExplicitVarSizeWithDummy[q18] = 5 -> s_ExplicitVarSizeWithDummy[q18 + 1] = 5 | q18 : int(1..3)]), - and([s_ExplicitVarSizeWithDummy[q22] != 5 -> - or([q24 <= s_ExplicitVarSizeWithMarker_Marker /\ - s_ExplicitVarSizeWithMarker_Values[q24] = s_ExplicitVarSizeWithDummy[q22] - | q24 : int(1..4)]) - | q22 : int(1..4)]), - and([q26 <= s_ExplicitVarSizeWithMarker_Marker -> - or([s_ExplicitVarSizeWithDummy[q28] != 5 /\ - s_ExplicitVarSizeWithDummy[q28] = s_ExplicitVarSizeWithMarker_Values[q26] - | q28 : int(1..4)]) - | q26 : int(1..4)]), - and([s_ExplicitVarSizeWithDummy[q30] != 5 -> - or([s_ExplicitVarSizeWithFlags_Flags[q32] /\ - s_ExplicitVarSizeWithFlags_Values[q32] = s_ExplicitVarSizeWithDummy[q30] - | q32 : int(1..4)]) - | q30 : int(1..4)]), - and([s_ExplicitVarSizeWithFlags_Flags[q34] -> - or([s_ExplicitVarSizeWithDummy[q36] != 5 /\ - s_ExplicitVarSizeWithDummy[q36] = s_ExplicitVarSizeWithFlags_Values[q34] - | q36 : int(1..4)]) - | q34 : int(1..4)]) - diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_4_3-solution000001.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_4_3-solution000001.solution deleted file mode 100644 index 8b4ecbb66d..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_3_4_3-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 3} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_4_3-solution000002.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_4_3-solution000002.solution deleted file mode 100644 index 159a613983..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_3_4_3-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {2, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_4_3-solution000003.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_4_3-solution000003.solution deleted file mode 100644 index 5963aac565..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_3_4_3-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 3} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_4_3-solution000004.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_4_3-solution000004.solution deleted file mode 100644 index 6eeacc9727..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_3_4_3-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_4_3-solution000005.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_4_3-solution000005.solution deleted file mode 100644 index 560dd0f2f7..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_3_4_3-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 3, 4} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_4_3-solution000006.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_4_3-solution000006.solution deleted file mode 100644 index 40f3fd5c8f..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_3_4_3-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {2, 3, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_4_3-solution000007.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_4_3-solution000007.solution deleted file mode 100644 index bd956f44e3..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_3_4_3-solution000007.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 3, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_4_3.eprime b/tests/exhaustive/basic/comprehension_letting/expected/model_3_4_3.eprime deleted file mode 100644 index 0a797c0a81..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_3_4_3.eprime +++ /dev/null @@ -1,98 +0,0 @@ -language ESSENCE' 1.0 - -find s_ExplicitVarSizeWithMarker_Marker: int(0..4) -find s_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -find s_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find s_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -letting let1 be -100 -find x: int(-100..100) -find conjure_aux1: int(-16..3) -branching on - [s_ExplicitVarSizeWithFlags_Flags, s_ExplicitVarSizeWithFlags_Values, s_ExplicitVarSizeWithMarker_Marker, - s_ExplicitVarSizeWithMarker_Values, x] -such that - and([and([q17 <= s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithFlags_Flags[q18], - s_ExplicitVarSizeWithMarker_Values[q17] != s_ExplicitVarSizeWithFlags_Values[q18], - allDiff([s_ExplicitVarSizeWithMarker_Values[q17] + s_ExplicitVarSizeWithFlags_Values[q18], - s_ExplicitVarSizeWithMarker_Values[q17] * s_ExplicitVarSizeWithFlags_Values[q18], - s_ExplicitVarSizeWithMarker_Values[q17] / s_ExplicitVarSizeWithFlags_Values[q18]; - int(1..3)]), - (s_ExplicitVarSizeWithMarker_Values[q17] - s_ExplicitVarSizeWithFlags_Values[q18]) % 2 = 0; - int(1..5)]) - -> - min([s_ExplicitVarSizeWithMarker_Values[q17] + s_ExplicitVarSizeWithFlags_Values[q18], - s_ExplicitVarSizeWithMarker_Values[q17] - s_ExplicitVarSizeWithFlags_Values[q18], - s_ExplicitVarSizeWithMarker_Values[q17] * s_ExplicitVarSizeWithFlags_Values[q18], - s_ExplicitVarSizeWithMarker_Values[q17] / s_ExplicitVarSizeWithFlags_Values[q18]; - int(1..4)]) - <= conjure_aux1 - | q17 : int(1..4), q18 : int(1..4)]), - sum([toInt(and([q17 <= s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithFlags_Flags[q18], - s_ExplicitVarSizeWithMarker_Values[q17] != s_ExplicitVarSizeWithFlags_Values[q18], - allDiff([s_ExplicitVarSizeWithMarker_Values[q17] + s_ExplicitVarSizeWithFlags_Values[q18], - s_ExplicitVarSizeWithMarker_Values[q17] * s_ExplicitVarSizeWithFlags_Values[q18], - s_ExplicitVarSizeWithMarker_Values[q17] / s_ExplicitVarSizeWithFlags_Values[q18]; - int(1..3)]), - (s_ExplicitVarSizeWithMarker_Values[q17] - s_ExplicitVarSizeWithFlags_Values[q18]) % 2 = 0; - int(1..5)])) - | q17 : int(1..4), q18 : int(1..4)]) - > 0 - -> - or([and([q17 <= s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithFlags_Flags[q18], - s_ExplicitVarSizeWithMarker_Values[q17] != s_ExplicitVarSizeWithFlags_Values[q18], - allDiff([s_ExplicitVarSizeWithMarker_Values[q17] + s_ExplicitVarSizeWithFlags_Values[q18], - s_ExplicitVarSizeWithMarker_Values[q17] * s_ExplicitVarSizeWithFlags_Values[q18], - s_ExplicitVarSizeWithMarker_Values[q17] / s_ExplicitVarSizeWithFlags_Values[q18]; - int(1..3)]), - (s_ExplicitVarSizeWithMarker_Values[q17] - s_ExplicitVarSizeWithFlags_Values[q18]) % 2 = 0; - int(1..5)]) - /\ - min([s_ExplicitVarSizeWithMarker_Values[q17] + s_ExplicitVarSizeWithFlags_Values[q18], - s_ExplicitVarSizeWithMarker_Values[q17] - s_ExplicitVarSizeWithFlags_Values[q18], - s_ExplicitVarSizeWithMarker_Values[q17] * s_ExplicitVarSizeWithFlags_Values[q18], - s_ExplicitVarSizeWithMarker_Values[q17] / s_ExplicitVarSizeWithFlags_Values[q18]; - int(1..4)]) - = conjure_aux1 - | q17 : int(1..4), q18 : int(1..4)]), - sum([toInt(and([q17 <= s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithFlags_Flags[q18], - s_ExplicitVarSizeWithMarker_Values[q17] != s_ExplicitVarSizeWithFlags_Values[q18], - allDiff([s_ExplicitVarSizeWithMarker_Values[q17] + s_ExplicitVarSizeWithFlags_Values[q18], - s_ExplicitVarSizeWithMarker_Values[q17] * s_ExplicitVarSizeWithFlags_Values[q18], - s_ExplicitVarSizeWithMarker_Values[q17] / s_ExplicitVarSizeWithFlags_Values[q18]; - int(1..3)]), - (s_ExplicitVarSizeWithMarker_Values[q17] - s_ExplicitVarSizeWithFlags_Values[q18]) % 2 = 0; - int(1..5)])) - | q17 : int(1..4), q18 : int(1..4)]) - = 0 - -> conjure_aux1 = -16, - x = conjure_aux1, - sum([toInt(and([q17 <= s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithFlags_Flags[q18], - s_ExplicitVarSizeWithMarker_Values[q17] != s_ExplicitVarSizeWithFlags_Values[q18], - allDiff([s_ExplicitVarSizeWithMarker_Values[q17] + s_ExplicitVarSizeWithFlags_Values[q18], - s_ExplicitVarSizeWithMarker_Values[q17] * s_ExplicitVarSizeWithFlags_Values[q18], - s_ExplicitVarSizeWithMarker_Values[q17] / s_ExplicitVarSizeWithFlags_Values[q18]; - int(1..3)]), - (s_ExplicitVarSizeWithMarker_Values[q17] - s_ExplicitVarSizeWithFlags_Values[q18]) % 2 = 0; - int(1..5)])) - | q17 : int(1..4), q18 : int(1..4)]) - > 0, - and([q1 + 1 <= s_ExplicitVarSizeWithMarker_Marker -> - s_ExplicitVarSizeWithMarker_Values[q1] < s_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..3)]), - and([q2 > s_ExplicitVarSizeWithMarker_Marker -> s_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..4)]), - and([s_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> - s_ExplicitVarSizeWithFlags_Values[q4] < s_ExplicitVarSizeWithFlags_Values[q4 + 1] - | q4 : int(1..3)]), - and([s_ExplicitVarSizeWithFlags_Flags[q5] = false -> s_ExplicitVarSizeWithFlags_Values[q5] = 1 | q5 : int(1..4)]), - and([s_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> s_ExplicitVarSizeWithFlags_Flags[q6] | q6 : int(1..3)]), - and([s_ExplicitVarSizeWithFlags_Flags[q10] -> - or([q12 <= s_ExplicitVarSizeWithMarker_Marker /\ - s_ExplicitVarSizeWithMarker_Values[q12] = s_ExplicitVarSizeWithFlags_Values[q10] - | q12 : int(1..4)]) - | q10 : int(1..4)]), - and([q14 <= s_ExplicitVarSizeWithMarker_Marker -> - or([s_ExplicitVarSizeWithFlags_Flags[q16] /\ - s_ExplicitVarSizeWithFlags_Values[q16] = s_ExplicitVarSizeWithMarker_Values[q14] - | q16 : int(1..4)]) - | q14 : int(1..4)]) - diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_4_4-solution000001.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_4_4-solution000001.solution deleted file mode 100644 index 8b4ecbb66d..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_3_4_4-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 3} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_4_4-solution000002.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_4_4-solution000002.solution deleted file mode 100644 index 159a613983..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_3_4_4-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {2, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_4_4-solution000003.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_4_4-solution000003.solution deleted file mode 100644 index 5963aac565..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_3_4_4-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 3} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_4_4-solution000004.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_4_4-solution000004.solution deleted file mode 100644 index 6eeacc9727..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_3_4_4-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_4_4-solution000005.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_4_4-solution000005.solution deleted file mode 100644 index 560dd0f2f7..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_3_4_4-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 3, 4} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_4_4-solution000006.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_4_4-solution000006.solution deleted file mode 100644 index 40f3fd5c8f..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_3_4_4-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {2, 3, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_4_4-solution000007.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_4_4-solution000007.solution deleted file mode 100644 index bd956f44e3..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_3_4_4-solution000007.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 3, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_4_4.eprime b/tests/exhaustive/basic/comprehension_letting/expected/model_3_4_4.eprime deleted file mode 100644 index 0a797c0a81..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_3_4_4.eprime +++ /dev/null @@ -1,98 +0,0 @@ -language ESSENCE' 1.0 - -find s_ExplicitVarSizeWithMarker_Marker: int(0..4) -find s_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -find s_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find s_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -letting let1 be -100 -find x: int(-100..100) -find conjure_aux1: int(-16..3) -branching on - [s_ExplicitVarSizeWithFlags_Flags, s_ExplicitVarSizeWithFlags_Values, s_ExplicitVarSizeWithMarker_Marker, - s_ExplicitVarSizeWithMarker_Values, x] -such that - and([and([q17 <= s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithFlags_Flags[q18], - s_ExplicitVarSizeWithMarker_Values[q17] != s_ExplicitVarSizeWithFlags_Values[q18], - allDiff([s_ExplicitVarSizeWithMarker_Values[q17] + s_ExplicitVarSizeWithFlags_Values[q18], - s_ExplicitVarSizeWithMarker_Values[q17] * s_ExplicitVarSizeWithFlags_Values[q18], - s_ExplicitVarSizeWithMarker_Values[q17] / s_ExplicitVarSizeWithFlags_Values[q18]; - int(1..3)]), - (s_ExplicitVarSizeWithMarker_Values[q17] - s_ExplicitVarSizeWithFlags_Values[q18]) % 2 = 0; - int(1..5)]) - -> - min([s_ExplicitVarSizeWithMarker_Values[q17] + s_ExplicitVarSizeWithFlags_Values[q18], - s_ExplicitVarSizeWithMarker_Values[q17] - s_ExplicitVarSizeWithFlags_Values[q18], - s_ExplicitVarSizeWithMarker_Values[q17] * s_ExplicitVarSizeWithFlags_Values[q18], - s_ExplicitVarSizeWithMarker_Values[q17] / s_ExplicitVarSizeWithFlags_Values[q18]; - int(1..4)]) - <= conjure_aux1 - | q17 : int(1..4), q18 : int(1..4)]), - sum([toInt(and([q17 <= s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithFlags_Flags[q18], - s_ExplicitVarSizeWithMarker_Values[q17] != s_ExplicitVarSizeWithFlags_Values[q18], - allDiff([s_ExplicitVarSizeWithMarker_Values[q17] + s_ExplicitVarSizeWithFlags_Values[q18], - s_ExplicitVarSizeWithMarker_Values[q17] * s_ExplicitVarSizeWithFlags_Values[q18], - s_ExplicitVarSizeWithMarker_Values[q17] / s_ExplicitVarSizeWithFlags_Values[q18]; - int(1..3)]), - (s_ExplicitVarSizeWithMarker_Values[q17] - s_ExplicitVarSizeWithFlags_Values[q18]) % 2 = 0; - int(1..5)])) - | q17 : int(1..4), q18 : int(1..4)]) - > 0 - -> - or([and([q17 <= s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithFlags_Flags[q18], - s_ExplicitVarSizeWithMarker_Values[q17] != s_ExplicitVarSizeWithFlags_Values[q18], - allDiff([s_ExplicitVarSizeWithMarker_Values[q17] + s_ExplicitVarSizeWithFlags_Values[q18], - s_ExplicitVarSizeWithMarker_Values[q17] * s_ExplicitVarSizeWithFlags_Values[q18], - s_ExplicitVarSizeWithMarker_Values[q17] / s_ExplicitVarSizeWithFlags_Values[q18]; - int(1..3)]), - (s_ExplicitVarSizeWithMarker_Values[q17] - s_ExplicitVarSizeWithFlags_Values[q18]) % 2 = 0; - int(1..5)]) - /\ - min([s_ExplicitVarSizeWithMarker_Values[q17] + s_ExplicitVarSizeWithFlags_Values[q18], - s_ExplicitVarSizeWithMarker_Values[q17] - s_ExplicitVarSizeWithFlags_Values[q18], - s_ExplicitVarSizeWithMarker_Values[q17] * s_ExplicitVarSizeWithFlags_Values[q18], - s_ExplicitVarSizeWithMarker_Values[q17] / s_ExplicitVarSizeWithFlags_Values[q18]; - int(1..4)]) - = conjure_aux1 - | q17 : int(1..4), q18 : int(1..4)]), - sum([toInt(and([q17 <= s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithFlags_Flags[q18], - s_ExplicitVarSizeWithMarker_Values[q17] != s_ExplicitVarSizeWithFlags_Values[q18], - allDiff([s_ExplicitVarSizeWithMarker_Values[q17] + s_ExplicitVarSizeWithFlags_Values[q18], - s_ExplicitVarSizeWithMarker_Values[q17] * s_ExplicitVarSizeWithFlags_Values[q18], - s_ExplicitVarSizeWithMarker_Values[q17] / s_ExplicitVarSizeWithFlags_Values[q18]; - int(1..3)]), - (s_ExplicitVarSizeWithMarker_Values[q17] - s_ExplicitVarSizeWithFlags_Values[q18]) % 2 = 0; - int(1..5)])) - | q17 : int(1..4), q18 : int(1..4)]) - = 0 - -> conjure_aux1 = -16, - x = conjure_aux1, - sum([toInt(and([q17 <= s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithFlags_Flags[q18], - s_ExplicitVarSizeWithMarker_Values[q17] != s_ExplicitVarSizeWithFlags_Values[q18], - allDiff([s_ExplicitVarSizeWithMarker_Values[q17] + s_ExplicitVarSizeWithFlags_Values[q18], - s_ExplicitVarSizeWithMarker_Values[q17] * s_ExplicitVarSizeWithFlags_Values[q18], - s_ExplicitVarSizeWithMarker_Values[q17] / s_ExplicitVarSizeWithFlags_Values[q18]; - int(1..3)]), - (s_ExplicitVarSizeWithMarker_Values[q17] - s_ExplicitVarSizeWithFlags_Values[q18]) % 2 = 0; - int(1..5)])) - | q17 : int(1..4), q18 : int(1..4)]) - > 0, - and([q1 + 1 <= s_ExplicitVarSizeWithMarker_Marker -> - s_ExplicitVarSizeWithMarker_Values[q1] < s_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..3)]), - and([q2 > s_ExplicitVarSizeWithMarker_Marker -> s_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..4)]), - and([s_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> - s_ExplicitVarSizeWithFlags_Values[q4] < s_ExplicitVarSizeWithFlags_Values[q4 + 1] - | q4 : int(1..3)]), - and([s_ExplicitVarSizeWithFlags_Flags[q5] = false -> s_ExplicitVarSizeWithFlags_Values[q5] = 1 | q5 : int(1..4)]), - and([s_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> s_ExplicitVarSizeWithFlags_Flags[q6] | q6 : int(1..3)]), - and([s_ExplicitVarSizeWithFlags_Flags[q10] -> - or([q12 <= s_ExplicitVarSizeWithMarker_Marker /\ - s_ExplicitVarSizeWithMarker_Values[q12] = s_ExplicitVarSizeWithFlags_Values[q10] - | q12 : int(1..4)]) - | q10 : int(1..4)]), - and([q14 <= s_ExplicitVarSizeWithMarker_Marker -> - or([s_ExplicitVarSizeWithFlags_Flags[q16] /\ - s_ExplicitVarSizeWithFlags_Values[q16] = s_ExplicitVarSizeWithMarker_Values[q14] - | q16 : int(1..4)]) - | q14 : int(1..4)]) - diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_1_1-solution000001.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_1_1-solution000001.solution deleted file mode 100644 index 159a613983..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_4_1_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {2, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_1_1-solution000002.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_1_1-solution000002.solution deleted file mode 100644 index 40f3fd5c8f..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_4_1_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {2, 3, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_1_1-solution000003.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_1_1-solution000003.solution deleted file mode 100644 index 8b4ecbb66d..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_4_1_1-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 3} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_1_1-solution000004.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_1_1-solution000004.solution deleted file mode 100644 index 560dd0f2f7..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_4_1_1-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 3, 4} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_1_1-solution000005.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_1_1-solution000005.solution deleted file mode 100644 index 6eeacc9727..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_4_1_1-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_1_1-solution000006.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_1_1-solution000006.solution deleted file mode 100644 index 5963aac565..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_4_1_1-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 3} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_1_1-solution000007.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_1_1-solution000007.solution deleted file mode 100644 index bd956f44e3..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_4_1_1-solution000007.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 3, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_1_1.eprime b/tests/exhaustive/basic/comprehension_letting/expected/model_4_1_1.eprime deleted file mode 100644 index adcf0207b3..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_4_1_1.eprime +++ /dev/null @@ -1,72 +0,0 @@ -language ESSENCE' 1.0 - -find s_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find s_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -find s_Occurrence: matrix indexed by [int(1..4)] of bool -letting let1 be -100 -find x: int(-100..100) -find conjure_aux1: int(-16..3) -branching on [s_Occurrence, s_ExplicitVarSizeWithFlags_Flags, s_ExplicitVarSizeWithFlags_Values, x] -such that - and([and([s_ExplicitVarSizeWithFlags_Flags[q12], s_Occurrence[j], s_ExplicitVarSizeWithFlags_Values[q12] != j, - allDiff([s_ExplicitVarSizeWithFlags_Values[q12] + j, s_ExplicitVarSizeWithFlags_Values[q12] * j, - s_ExplicitVarSizeWithFlags_Values[q12] / j; - int(1..3)]), - (s_ExplicitVarSizeWithFlags_Values[q12] - j) % 2 = 0; - int(1..5)]) - -> - min([s_ExplicitVarSizeWithFlags_Values[q12] + j, s_ExplicitVarSizeWithFlags_Values[q12] - j, - s_ExplicitVarSizeWithFlags_Values[q12] * j, s_ExplicitVarSizeWithFlags_Values[q12] / j; - int(1..4)]) - <= conjure_aux1 - | q12 : int(1..4), j : int(1..4)]), - sum([toInt(and([s_ExplicitVarSizeWithFlags_Flags[q12], s_Occurrence[j], s_ExplicitVarSizeWithFlags_Values[q12] != j, - allDiff([s_ExplicitVarSizeWithFlags_Values[q12] + j, s_ExplicitVarSizeWithFlags_Values[q12] * j, - s_ExplicitVarSizeWithFlags_Values[q12] / j; - int(1..3)]), - (s_ExplicitVarSizeWithFlags_Values[q12] - j) % 2 = 0; - int(1..5)])) - | q12 : int(1..4), j : int(1..4)]) - > 0 - -> - or([and([s_ExplicitVarSizeWithFlags_Flags[q12], s_Occurrence[j], s_ExplicitVarSizeWithFlags_Values[q12] != j, - allDiff([s_ExplicitVarSizeWithFlags_Values[q12] + j, s_ExplicitVarSizeWithFlags_Values[q12] * j, - s_ExplicitVarSizeWithFlags_Values[q12] / j; - int(1..3)]), - (s_ExplicitVarSizeWithFlags_Values[q12] - j) % 2 = 0; - int(1..5)]) - /\ - min([s_ExplicitVarSizeWithFlags_Values[q12] + j, s_ExplicitVarSizeWithFlags_Values[q12] - j, - s_ExplicitVarSizeWithFlags_Values[q12] * j, s_ExplicitVarSizeWithFlags_Values[q12] / j; - int(1..4)]) - = conjure_aux1 - | q12 : int(1..4), j : int(1..4)]), - sum([toInt(and([s_ExplicitVarSizeWithFlags_Flags[q12], s_Occurrence[j], s_ExplicitVarSizeWithFlags_Values[q12] != j, - allDiff([s_ExplicitVarSizeWithFlags_Values[q12] + j, s_ExplicitVarSizeWithFlags_Values[q12] * j, - s_ExplicitVarSizeWithFlags_Values[q12] / j; - int(1..3)]), - (s_ExplicitVarSizeWithFlags_Values[q12] - j) % 2 = 0; - int(1..5)])) - | q12 : int(1..4), j : int(1..4)]) - = 0 - -> conjure_aux1 = -16, - x = conjure_aux1, - sum([toInt(and([s_ExplicitVarSizeWithFlags_Flags[q12], s_Occurrence[j], s_ExplicitVarSizeWithFlags_Values[q12] != j, - allDiff([s_ExplicitVarSizeWithFlags_Values[q12] + j, s_ExplicitVarSizeWithFlags_Values[q12] * j, - s_ExplicitVarSizeWithFlags_Values[q12] / j; - int(1..3)]), - (s_ExplicitVarSizeWithFlags_Values[q12] - j) % 2 = 0; - int(1..5)])) - | q12 : int(1..4), j : int(1..4)]) - > 0, - and([s_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - s_ExplicitVarSizeWithFlags_Values[q1] < s_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..3)]), - and([s_ExplicitVarSizeWithFlags_Flags[q2] = false -> s_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..4)]), - and([s_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> s_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), - and([s_Occurrence[q7] -> - or([s_ExplicitVarSizeWithFlags_Flags[q9] /\ s_ExplicitVarSizeWithFlags_Values[q9] = q7 | q9 : int(1..4)]) - | q7 : int(1..4)]), - and([s_ExplicitVarSizeWithFlags_Flags[q11] -> s_Occurrence[s_ExplicitVarSizeWithFlags_Values[q11]] - | q11 : int(1..4)]) - diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_1_2-solution000001.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_1_2-solution000001.solution deleted file mode 100644 index bd956f44e3..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_4_1_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 3, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_1_2-solution000002.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_1_2-solution000002.solution deleted file mode 100644 index 5963aac565..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_4_1_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 3} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_1_2-solution000003.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_1_2-solution000003.solution deleted file mode 100644 index 6eeacc9727..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_4_1_2-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_1_2-solution000004.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_1_2-solution000004.solution deleted file mode 100644 index 560dd0f2f7..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_4_1_2-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 3, 4} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_1_2-solution000005.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_1_2-solution000005.solution deleted file mode 100644 index 8b4ecbb66d..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_4_1_2-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 3} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_1_2-solution000006.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_1_2-solution000006.solution deleted file mode 100644 index 40f3fd5c8f..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_4_1_2-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {2, 3, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_1_2-solution000007.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_1_2-solution000007.solution deleted file mode 100644 index 159a613983..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_4_1_2-solution000007.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {2, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_1_2.eprime b/tests/exhaustive/basic/comprehension_letting/expected/model_4_1_2.eprime deleted file mode 100644 index 9f5ba038eb..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_4_1_2.eprime +++ /dev/null @@ -1,91 +0,0 @@ -language ESSENCE' 1.0 - -find s_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find s_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -find s_Occurrence: matrix indexed by [int(1..4)] of bool -find s_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -letting let1 be -100 -find x: int(-100..100) -find conjure_aux1: int(-16..3) -branching on - [s_ExplicitVarSizeWithDummy, s_ExplicitVarSizeWithFlags_Flags, s_ExplicitVarSizeWithFlags_Values, s_Occurrence, x] -such that - and([and([s_ExplicitVarSizeWithFlags_Flags[q29], s_Occurrence[j], s_ExplicitVarSizeWithFlags_Values[q29] != j, - allDiff([s_ExplicitVarSizeWithFlags_Values[q29] + j, s_ExplicitVarSizeWithFlags_Values[q29] * j, - s_ExplicitVarSizeWithFlags_Values[q29] / j; - int(1..3)]), - (s_ExplicitVarSizeWithFlags_Values[q29] - j) % 2 = 0; - int(1..5)]) - -> - min([s_ExplicitVarSizeWithFlags_Values[q29] + j, s_ExplicitVarSizeWithFlags_Values[q29] - j, - s_ExplicitVarSizeWithFlags_Values[q29] * j, s_ExplicitVarSizeWithFlags_Values[q29] / j; - int(1..4)]) - <= conjure_aux1 - | q29 : int(1..4), j : int(1..4)]), - sum([toInt(and([s_ExplicitVarSizeWithFlags_Flags[q29], s_Occurrence[j], s_ExplicitVarSizeWithFlags_Values[q29] != j, - allDiff([s_ExplicitVarSizeWithFlags_Values[q29] + j, s_ExplicitVarSizeWithFlags_Values[q29] * j, - s_ExplicitVarSizeWithFlags_Values[q29] / j; - int(1..3)]), - (s_ExplicitVarSizeWithFlags_Values[q29] - j) % 2 = 0; - int(1..5)])) - | q29 : int(1..4), j : int(1..4)]) - > 0 - -> - or([and([s_ExplicitVarSizeWithFlags_Flags[q29], s_Occurrence[j], s_ExplicitVarSizeWithFlags_Values[q29] != j, - allDiff([s_ExplicitVarSizeWithFlags_Values[q29] + j, s_ExplicitVarSizeWithFlags_Values[q29] * j, - s_ExplicitVarSizeWithFlags_Values[q29] / j; - int(1..3)]), - (s_ExplicitVarSizeWithFlags_Values[q29] - j) % 2 = 0; - int(1..5)]) - /\ - min([s_ExplicitVarSizeWithFlags_Values[q29] + j, s_ExplicitVarSizeWithFlags_Values[q29] - j, - s_ExplicitVarSizeWithFlags_Values[q29] * j, s_ExplicitVarSizeWithFlags_Values[q29] / j; - int(1..4)]) - = conjure_aux1 - | q29 : int(1..4), j : int(1..4)]), - sum([toInt(and([s_ExplicitVarSizeWithFlags_Flags[q29], s_Occurrence[j], s_ExplicitVarSizeWithFlags_Values[q29] != j, - allDiff([s_ExplicitVarSizeWithFlags_Values[q29] + j, s_ExplicitVarSizeWithFlags_Values[q29] * j, - s_ExplicitVarSizeWithFlags_Values[q29] / j; - int(1..3)]), - (s_ExplicitVarSizeWithFlags_Values[q29] - j) % 2 = 0; - int(1..5)])) - | q29 : int(1..4), j : int(1..4)]) - = 0 - -> conjure_aux1 = -16, - x = conjure_aux1, - sum([toInt(and([s_ExplicitVarSizeWithFlags_Flags[q29], s_Occurrence[j], s_ExplicitVarSizeWithFlags_Values[q29] != j, - allDiff([s_ExplicitVarSizeWithFlags_Values[q29] + j, s_ExplicitVarSizeWithFlags_Values[q29] * j, - s_ExplicitVarSizeWithFlags_Values[q29] / j; - int(1..3)]), - (s_ExplicitVarSizeWithFlags_Values[q29] - j) % 2 = 0; - int(1..5)])) - | q29 : int(1..4), j : int(1..4)]) - > 0, - and([s_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - s_ExplicitVarSizeWithFlags_Values[q1] < s_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..3)]), - and([s_ExplicitVarSizeWithFlags_Flags[q2] = false -> s_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..4)]), - and([s_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> s_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), - and([s_Occurrence[q24] -> - or([s_ExplicitVarSizeWithFlags_Flags[q26] /\ s_ExplicitVarSizeWithFlags_Values[q26] = q24 | q26 : int(1..4)]) - | q24 : int(1..4)]), - and([s_ExplicitVarSizeWithFlags_Flags[q28] -> s_Occurrence[s_ExplicitVarSizeWithFlags_Values[q28]] - | q28 : int(1..4)]), - and([s_ExplicitVarSizeWithDummy[q7] < s_ExplicitVarSizeWithDummy[q7 + 1] \/ s_ExplicitVarSizeWithDummy[q7] = 5 - | q7 : int(1..3)]), - and([s_ExplicitVarSizeWithDummy[q8] = 5 -> s_ExplicitVarSizeWithDummy[q8 + 1] = 5 | q8 : int(1..3)]), - and([s_ExplicitVarSizeWithDummy[q12] != 5 -> - or([s_ExplicitVarSizeWithFlags_Flags[q14] /\ - s_ExplicitVarSizeWithFlags_Values[q14] = s_ExplicitVarSizeWithDummy[q12] - | q14 : int(1..4)]) - | q12 : int(1..4)]), - and([s_ExplicitVarSizeWithFlags_Flags[q16] -> - or([s_ExplicitVarSizeWithDummy[q18] != 5 /\ - s_ExplicitVarSizeWithDummy[q18] = s_ExplicitVarSizeWithFlags_Values[q16] - | q18 : int(1..4)]) - | q16 : int(1..4)]), - and([s_ExplicitVarSizeWithDummy[q20] != 5 -> s_Occurrence[s_ExplicitVarSizeWithDummy[q20]] | q20 : int(1..4)]), - and([s_Occurrence[q21] -> - or([s_ExplicitVarSizeWithDummy[q23] != 5 /\ s_ExplicitVarSizeWithDummy[q23] = q21 | q23 : int(1..4)]) - | q21 : int(1..4)]) - diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_1_3-solution000001.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_1_3-solution000001.solution deleted file mode 100644 index 8b4ecbb66d..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_4_1_3-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 3} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_1_3-solution000002.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_1_3-solution000002.solution deleted file mode 100644 index 159a613983..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_4_1_3-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {2, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_1_3-solution000003.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_1_3-solution000003.solution deleted file mode 100644 index 5963aac565..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_4_1_3-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 3} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_1_3-solution000004.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_1_3-solution000004.solution deleted file mode 100644 index 6eeacc9727..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_4_1_3-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_1_3-solution000005.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_1_3-solution000005.solution deleted file mode 100644 index 560dd0f2f7..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_4_1_3-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 3, 4} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_1_3-solution000006.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_1_3-solution000006.solution deleted file mode 100644 index 40f3fd5c8f..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_4_1_3-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {2, 3, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_1_3-solution000007.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_1_3-solution000007.solution deleted file mode 100644 index bd956f44e3..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_4_1_3-solution000007.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 3, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_1_3.eprime b/tests/exhaustive/basic/comprehension_letting/expected/model_4_1_3.eprime deleted file mode 100644 index d6762cf6f5..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_4_1_3.eprime +++ /dev/null @@ -1,96 +0,0 @@ -language ESSENCE' 1.0 - -find s_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find s_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -find s_Occurrence: matrix indexed by [int(1..4)] of bool -find s_ExplicitVarSizeWithMarker_Marker: int(0..4) -find s_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -letting let1 be -100 -find x: int(-100..100) -find conjure_aux1: int(-16..3) -branching on - [s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithMarker_Values, s_ExplicitVarSizeWithFlags_Flags, - s_ExplicitVarSizeWithFlags_Values, s_Occurrence, x] -such that - and([and([s_ExplicitVarSizeWithFlags_Flags[q28], s_Occurrence[j], s_ExplicitVarSizeWithFlags_Values[q28] != j, - allDiff([s_ExplicitVarSizeWithFlags_Values[q28] + j, s_ExplicitVarSizeWithFlags_Values[q28] * j, - s_ExplicitVarSizeWithFlags_Values[q28] / j; - int(1..3)]), - (s_ExplicitVarSizeWithFlags_Values[q28] - j) % 2 = 0; - int(1..5)]) - -> - min([s_ExplicitVarSizeWithFlags_Values[q28] + j, s_ExplicitVarSizeWithFlags_Values[q28] - j, - s_ExplicitVarSizeWithFlags_Values[q28] * j, s_ExplicitVarSizeWithFlags_Values[q28] / j; - int(1..4)]) - <= conjure_aux1 - | q28 : int(1..4), j : int(1..4)]), - sum([toInt(and([s_ExplicitVarSizeWithFlags_Flags[q28], s_Occurrence[j], s_ExplicitVarSizeWithFlags_Values[q28] != j, - allDiff([s_ExplicitVarSizeWithFlags_Values[q28] + j, s_ExplicitVarSizeWithFlags_Values[q28] * j, - s_ExplicitVarSizeWithFlags_Values[q28] / j; - int(1..3)]), - (s_ExplicitVarSizeWithFlags_Values[q28] - j) % 2 = 0; - int(1..5)])) - | q28 : int(1..4), j : int(1..4)]) - > 0 - -> - or([and([s_ExplicitVarSizeWithFlags_Flags[q28], s_Occurrence[j], s_ExplicitVarSizeWithFlags_Values[q28] != j, - allDiff([s_ExplicitVarSizeWithFlags_Values[q28] + j, s_ExplicitVarSizeWithFlags_Values[q28] * j, - s_ExplicitVarSizeWithFlags_Values[q28] / j; - int(1..3)]), - (s_ExplicitVarSizeWithFlags_Values[q28] - j) % 2 = 0; - int(1..5)]) - /\ - min([s_ExplicitVarSizeWithFlags_Values[q28] + j, s_ExplicitVarSizeWithFlags_Values[q28] - j, - s_ExplicitVarSizeWithFlags_Values[q28] * j, s_ExplicitVarSizeWithFlags_Values[q28] / j; - int(1..4)]) - = conjure_aux1 - | q28 : int(1..4), j : int(1..4)]), - sum([toInt(and([s_ExplicitVarSizeWithFlags_Flags[q28], s_Occurrence[j], s_ExplicitVarSizeWithFlags_Values[q28] != j, - allDiff([s_ExplicitVarSizeWithFlags_Values[q28] + j, s_ExplicitVarSizeWithFlags_Values[q28] * j, - s_ExplicitVarSizeWithFlags_Values[q28] / j; - int(1..3)]), - (s_ExplicitVarSizeWithFlags_Values[q28] - j) % 2 = 0; - int(1..5)])) - | q28 : int(1..4), j : int(1..4)]) - = 0 - -> conjure_aux1 = -16, - x = conjure_aux1, - sum([toInt(and([s_ExplicitVarSizeWithFlags_Flags[q28], s_Occurrence[j], s_ExplicitVarSizeWithFlags_Values[q28] != j, - allDiff([s_ExplicitVarSizeWithFlags_Values[q28] + j, s_ExplicitVarSizeWithFlags_Values[q28] * j, - s_ExplicitVarSizeWithFlags_Values[q28] / j; - int(1..3)]), - (s_ExplicitVarSizeWithFlags_Values[q28] - j) % 2 = 0; - int(1..5)])) - | q28 : int(1..4), j : int(1..4)]) - > 0, - and([s_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - s_ExplicitVarSizeWithFlags_Values[q1] < s_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..3)]), - and([s_ExplicitVarSizeWithFlags_Flags[q2] = false -> s_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..4)]), - and([s_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> s_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), - and([s_Occurrence[q23] -> - or([s_ExplicitVarSizeWithFlags_Flags[q25] /\ s_ExplicitVarSizeWithFlags_Values[q25] = q23 | q25 : int(1..4)]) - | q23 : int(1..4)]), - and([s_ExplicitVarSizeWithFlags_Flags[q27] -> s_Occurrence[s_ExplicitVarSizeWithFlags_Values[q27]] - | q27 : int(1..4)]), - and([q7 + 1 <= s_ExplicitVarSizeWithMarker_Marker -> - s_ExplicitVarSizeWithMarker_Values[q7] < s_ExplicitVarSizeWithMarker_Values[q7 + 1] - | q7 : int(1..3)]), - and([q8 > s_ExplicitVarSizeWithMarker_Marker -> s_ExplicitVarSizeWithMarker_Values[q8] = 1 | q8 : int(1..4)]), - and([q11 <= s_ExplicitVarSizeWithMarker_Marker -> - or([s_ExplicitVarSizeWithFlags_Flags[q13] /\ - s_ExplicitVarSizeWithFlags_Values[q13] = s_ExplicitVarSizeWithMarker_Values[q11] - | q13 : int(1..4)]) - | q11 : int(1..4)]), - and([s_ExplicitVarSizeWithFlags_Flags[q15] -> - or([q17 <= s_ExplicitVarSizeWithMarker_Marker /\ - s_ExplicitVarSizeWithMarker_Values[q17] = s_ExplicitVarSizeWithFlags_Values[q15] - | q17 : int(1..4)]) - | q15 : int(1..4)]), - and([q19 <= s_ExplicitVarSizeWithMarker_Marker -> s_Occurrence[s_ExplicitVarSizeWithMarker_Values[q19]] - | q19 : int(1..4)]), - and([s_Occurrence[q20] -> - or([q22 <= s_ExplicitVarSizeWithMarker_Marker /\ s_ExplicitVarSizeWithMarker_Values[q22] = q20 - | q22 : int(1..4)]) - | q20 : int(1..4)]) - diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_1_4-solution000001.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_1_4-solution000001.solution deleted file mode 100644 index 159a613983..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_4_1_4-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {2, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_1_4-solution000002.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_1_4-solution000002.solution deleted file mode 100644 index 40f3fd5c8f..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_4_1_4-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {2, 3, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_1_4-solution000003.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_1_4-solution000003.solution deleted file mode 100644 index 8b4ecbb66d..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_4_1_4-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 3} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_1_4-solution000004.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_1_4-solution000004.solution deleted file mode 100644 index 560dd0f2f7..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_4_1_4-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 3, 4} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_1_4-solution000005.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_1_4-solution000005.solution deleted file mode 100644 index 6eeacc9727..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_4_1_4-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_1_4-solution000006.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_1_4-solution000006.solution deleted file mode 100644 index 5963aac565..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_4_1_4-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 3} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_1_4-solution000007.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_1_4-solution000007.solution deleted file mode 100644 index bd956f44e3..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_4_1_4-solution000007.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 3, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_1_4.eprime b/tests/exhaustive/basic/comprehension_letting/expected/model_4_1_4.eprime deleted file mode 100644 index adcf0207b3..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_4_1_4.eprime +++ /dev/null @@ -1,72 +0,0 @@ -language ESSENCE' 1.0 - -find s_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find s_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -find s_Occurrence: matrix indexed by [int(1..4)] of bool -letting let1 be -100 -find x: int(-100..100) -find conjure_aux1: int(-16..3) -branching on [s_Occurrence, s_ExplicitVarSizeWithFlags_Flags, s_ExplicitVarSizeWithFlags_Values, x] -such that - and([and([s_ExplicitVarSizeWithFlags_Flags[q12], s_Occurrence[j], s_ExplicitVarSizeWithFlags_Values[q12] != j, - allDiff([s_ExplicitVarSizeWithFlags_Values[q12] + j, s_ExplicitVarSizeWithFlags_Values[q12] * j, - s_ExplicitVarSizeWithFlags_Values[q12] / j; - int(1..3)]), - (s_ExplicitVarSizeWithFlags_Values[q12] - j) % 2 = 0; - int(1..5)]) - -> - min([s_ExplicitVarSizeWithFlags_Values[q12] + j, s_ExplicitVarSizeWithFlags_Values[q12] - j, - s_ExplicitVarSizeWithFlags_Values[q12] * j, s_ExplicitVarSizeWithFlags_Values[q12] / j; - int(1..4)]) - <= conjure_aux1 - | q12 : int(1..4), j : int(1..4)]), - sum([toInt(and([s_ExplicitVarSizeWithFlags_Flags[q12], s_Occurrence[j], s_ExplicitVarSizeWithFlags_Values[q12] != j, - allDiff([s_ExplicitVarSizeWithFlags_Values[q12] + j, s_ExplicitVarSizeWithFlags_Values[q12] * j, - s_ExplicitVarSizeWithFlags_Values[q12] / j; - int(1..3)]), - (s_ExplicitVarSizeWithFlags_Values[q12] - j) % 2 = 0; - int(1..5)])) - | q12 : int(1..4), j : int(1..4)]) - > 0 - -> - or([and([s_ExplicitVarSizeWithFlags_Flags[q12], s_Occurrence[j], s_ExplicitVarSizeWithFlags_Values[q12] != j, - allDiff([s_ExplicitVarSizeWithFlags_Values[q12] + j, s_ExplicitVarSizeWithFlags_Values[q12] * j, - s_ExplicitVarSizeWithFlags_Values[q12] / j; - int(1..3)]), - (s_ExplicitVarSizeWithFlags_Values[q12] - j) % 2 = 0; - int(1..5)]) - /\ - min([s_ExplicitVarSizeWithFlags_Values[q12] + j, s_ExplicitVarSizeWithFlags_Values[q12] - j, - s_ExplicitVarSizeWithFlags_Values[q12] * j, s_ExplicitVarSizeWithFlags_Values[q12] / j; - int(1..4)]) - = conjure_aux1 - | q12 : int(1..4), j : int(1..4)]), - sum([toInt(and([s_ExplicitVarSizeWithFlags_Flags[q12], s_Occurrence[j], s_ExplicitVarSizeWithFlags_Values[q12] != j, - allDiff([s_ExplicitVarSizeWithFlags_Values[q12] + j, s_ExplicitVarSizeWithFlags_Values[q12] * j, - s_ExplicitVarSizeWithFlags_Values[q12] / j; - int(1..3)]), - (s_ExplicitVarSizeWithFlags_Values[q12] - j) % 2 = 0; - int(1..5)])) - | q12 : int(1..4), j : int(1..4)]) - = 0 - -> conjure_aux1 = -16, - x = conjure_aux1, - sum([toInt(and([s_ExplicitVarSizeWithFlags_Flags[q12], s_Occurrence[j], s_ExplicitVarSizeWithFlags_Values[q12] != j, - allDiff([s_ExplicitVarSizeWithFlags_Values[q12] + j, s_ExplicitVarSizeWithFlags_Values[q12] * j, - s_ExplicitVarSizeWithFlags_Values[q12] / j; - int(1..3)]), - (s_ExplicitVarSizeWithFlags_Values[q12] - j) % 2 = 0; - int(1..5)])) - | q12 : int(1..4), j : int(1..4)]) - > 0, - and([s_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - s_ExplicitVarSizeWithFlags_Values[q1] < s_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..3)]), - and([s_ExplicitVarSizeWithFlags_Flags[q2] = false -> s_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..4)]), - and([s_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> s_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), - and([s_Occurrence[q7] -> - or([s_ExplicitVarSizeWithFlags_Flags[q9] /\ s_ExplicitVarSizeWithFlags_Values[q9] = q7 | q9 : int(1..4)]) - | q7 : int(1..4)]), - and([s_ExplicitVarSizeWithFlags_Flags[q11] -> s_Occurrence[s_ExplicitVarSizeWithFlags_Values[q11]] - | q11 : int(1..4)]) - diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_2_1-solution000001.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_2_1-solution000001.solution deleted file mode 100644 index 159a613983..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_4_2_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {2, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_2_1-solution000002.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_2_1-solution000002.solution deleted file mode 100644 index 40f3fd5c8f..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_4_2_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {2, 3, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_2_1-solution000003.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_2_1-solution000003.solution deleted file mode 100644 index 8b4ecbb66d..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_4_2_1-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 3} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_2_1-solution000004.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_2_1-solution000004.solution deleted file mode 100644 index 560dd0f2f7..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_4_2_1-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 3, 4} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_2_1-solution000005.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_2_1-solution000005.solution deleted file mode 100644 index 6eeacc9727..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_4_2_1-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_2_1-solution000006.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_2_1-solution000006.solution deleted file mode 100644 index 5963aac565..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_4_2_1-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 3} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_2_1-solution000007.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_2_1-solution000007.solution deleted file mode 100644 index bd956f44e3..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_4_2_1-solution000007.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 3, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_2_1.eprime b/tests/exhaustive/basic/comprehension_letting/expected/model_4_2_1.eprime deleted file mode 100644 index 30ab2bb7fb..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_4_2_1.eprime +++ /dev/null @@ -1,105 +0,0 @@ -language ESSENCE' 1.0 - -find s_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find s_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -find s_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -find s_Occurrence: matrix indexed by [int(1..4)] of bool -letting let1 be -100 -find x: int(-100..100) -find conjure_aux1: int(-20..3) -branching on - [s_Occurrence, s_ExplicitVarSizeWithFlags_Flags, s_ExplicitVarSizeWithFlags_Values, s_ExplicitVarSizeWithDummy, x] -such that - and([and([s_ExplicitVarSizeWithFlags_Flags[q29], s_ExplicitVarSizeWithDummy[q30] != 5, - s_ExplicitVarSizeWithFlags_Values[q29] != s_ExplicitVarSizeWithDummy[q30], - allDiff([s_ExplicitVarSizeWithFlags_Values[q29] + s_ExplicitVarSizeWithDummy[q30], - s_ExplicitVarSizeWithFlags_Values[q29] * s_ExplicitVarSizeWithDummy[q30], - s_ExplicitVarSizeWithFlags_Values[q29] / s_ExplicitVarSizeWithDummy[q30]; - int(1..3)]), - (s_ExplicitVarSizeWithFlags_Values[q29] - s_ExplicitVarSizeWithDummy[q30]) % 2 = 0; - int(1..5)]) - -> - min([s_ExplicitVarSizeWithFlags_Values[q29] + s_ExplicitVarSizeWithDummy[q30], - s_ExplicitVarSizeWithFlags_Values[q29] - s_ExplicitVarSizeWithDummy[q30], - s_ExplicitVarSizeWithFlags_Values[q29] * s_ExplicitVarSizeWithDummy[q30], - s_ExplicitVarSizeWithFlags_Values[q29] / s_ExplicitVarSizeWithDummy[q30]; - int(1..4)]) - <= conjure_aux1 - | q29 : int(1..4), q30 : int(1..4)]), - sum([toInt(and([s_ExplicitVarSizeWithFlags_Flags[q29], s_ExplicitVarSizeWithDummy[q30] != 5, - s_ExplicitVarSizeWithFlags_Values[q29] != s_ExplicitVarSizeWithDummy[q30], - allDiff([s_ExplicitVarSizeWithFlags_Values[q29] + s_ExplicitVarSizeWithDummy[q30], - s_ExplicitVarSizeWithFlags_Values[q29] * s_ExplicitVarSizeWithDummy[q30], - s_ExplicitVarSizeWithFlags_Values[q29] / s_ExplicitVarSizeWithDummy[q30]; - int(1..3)]), - (s_ExplicitVarSizeWithFlags_Values[q29] - s_ExplicitVarSizeWithDummy[q30]) % 2 = 0; - int(1..5)])) - | q29 : int(1..4), q30 : int(1..4)]) - > 0 - -> - or([and([s_ExplicitVarSizeWithFlags_Flags[q29], s_ExplicitVarSizeWithDummy[q30] != 5, - s_ExplicitVarSizeWithFlags_Values[q29] != s_ExplicitVarSizeWithDummy[q30], - allDiff([s_ExplicitVarSizeWithFlags_Values[q29] + s_ExplicitVarSizeWithDummy[q30], - s_ExplicitVarSizeWithFlags_Values[q29] * s_ExplicitVarSizeWithDummy[q30], - s_ExplicitVarSizeWithFlags_Values[q29] / s_ExplicitVarSizeWithDummy[q30]; - int(1..3)]), - (s_ExplicitVarSizeWithFlags_Values[q29] - s_ExplicitVarSizeWithDummy[q30]) % 2 = 0; - int(1..5)]) - /\ - min([s_ExplicitVarSizeWithFlags_Values[q29] + s_ExplicitVarSizeWithDummy[q30], - s_ExplicitVarSizeWithFlags_Values[q29] - s_ExplicitVarSizeWithDummy[q30], - s_ExplicitVarSizeWithFlags_Values[q29] * s_ExplicitVarSizeWithDummy[q30], - s_ExplicitVarSizeWithFlags_Values[q29] / s_ExplicitVarSizeWithDummy[q30]; - int(1..4)]) - = conjure_aux1 - | q29 : int(1..4), q30 : int(1..4)]), - sum([toInt(and([s_ExplicitVarSizeWithFlags_Flags[q29], s_ExplicitVarSizeWithDummy[q30] != 5, - s_ExplicitVarSizeWithFlags_Values[q29] != s_ExplicitVarSizeWithDummy[q30], - allDiff([s_ExplicitVarSizeWithFlags_Values[q29] + s_ExplicitVarSizeWithDummy[q30], - s_ExplicitVarSizeWithFlags_Values[q29] * s_ExplicitVarSizeWithDummy[q30], - s_ExplicitVarSizeWithFlags_Values[q29] / s_ExplicitVarSizeWithDummy[q30]; - int(1..3)]), - (s_ExplicitVarSizeWithFlags_Values[q29] - s_ExplicitVarSizeWithDummy[q30]) % 2 = 0; - int(1..5)])) - | q29 : int(1..4), q30 : int(1..4)]) - = 0 - -> conjure_aux1 = -20, - x = conjure_aux1, - sum([toInt(and([s_ExplicitVarSizeWithFlags_Flags[q29], s_ExplicitVarSizeWithDummy[q30] != 5, - s_ExplicitVarSizeWithFlags_Values[q29] != s_ExplicitVarSizeWithDummy[q30], - allDiff([s_ExplicitVarSizeWithFlags_Values[q29] + s_ExplicitVarSizeWithDummy[q30], - s_ExplicitVarSizeWithFlags_Values[q29] * s_ExplicitVarSizeWithDummy[q30], - s_ExplicitVarSizeWithFlags_Values[q29] / s_ExplicitVarSizeWithDummy[q30]; - int(1..3)]), - (s_ExplicitVarSizeWithFlags_Values[q29] - s_ExplicitVarSizeWithDummy[q30]) % 2 = 0; - int(1..5)])) - | q29 : int(1..4), q30 : int(1..4)]) - > 0, - and([s_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - s_ExplicitVarSizeWithFlags_Values[q1] < s_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..3)]), - and([s_ExplicitVarSizeWithFlags_Flags[q2] = false -> s_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..4)]), - and([s_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> s_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), - and([s_ExplicitVarSizeWithDummy[q6] < s_ExplicitVarSizeWithDummy[q6 + 1] \/ s_ExplicitVarSizeWithDummy[q6] = 5 - | q6 : int(1..3)]), - and([s_ExplicitVarSizeWithDummy[q7] = 5 -> s_ExplicitVarSizeWithDummy[q7 + 1] = 5 | q7 : int(1..3)]), - and([s_ExplicitVarSizeWithDummy[q11] != 5 -> - or([s_ExplicitVarSizeWithFlags_Flags[q13] /\ - s_ExplicitVarSizeWithFlags_Values[q13] = s_ExplicitVarSizeWithDummy[q11] - | q13 : int(1..4)]) - | q11 : int(1..4)]), - and([s_ExplicitVarSizeWithFlags_Flags[q15] -> - or([s_ExplicitVarSizeWithDummy[q17] != 5 /\ - s_ExplicitVarSizeWithDummy[q17] = s_ExplicitVarSizeWithFlags_Values[q15] - | q17 : int(1..4)]) - | q15 : int(1..4)]), - and([s_Occurrence[q19] -> - or([s_ExplicitVarSizeWithFlags_Flags[q21] /\ s_ExplicitVarSizeWithFlags_Values[q21] = q19 | q21 : int(1..4)]) - | q19 : int(1..4)]), - and([s_ExplicitVarSizeWithFlags_Flags[q23] -> s_Occurrence[s_ExplicitVarSizeWithFlags_Values[q23]] - | q23 : int(1..4)]), - and([s_Occurrence[q24] -> - or([s_ExplicitVarSizeWithDummy[q26] != 5 /\ s_ExplicitVarSizeWithDummy[q26] = q24 | q26 : int(1..4)]) - | q24 : int(1..4)]), - and([s_ExplicitVarSizeWithDummy[q28] != 5 -> s_Occurrence[s_ExplicitVarSizeWithDummy[q28]] | q28 : int(1..4)]) - diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_2_2-solution000001.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_2_2-solution000001.solution deleted file mode 100644 index bd956f44e3..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_4_2_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 3, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_2_2-solution000002.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_2_2-solution000002.solution deleted file mode 100644 index 5963aac565..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_4_2_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 3} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_2_2-solution000003.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_2_2-solution000003.solution deleted file mode 100644 index 6eeacc9727..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_4_2_2-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_2_2-solution000004.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_2_2-solution000004.solution deleted file mode 100644 index 560dd0f2f7..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_4_2_2-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 3, 4} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_2_2-solution000005.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_2_2-solution000005.solution deleted file mode 100644 index 8b4ecbb66d..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_4_2_2-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 3} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_2_2-solution000006.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_2_2-solution000006.solution deleted file mode 100644 index 40f3fd5c8f..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_4_2_2-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {2, 3, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_2_2-solution000007.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_2_2-solution000007.solution deleted file mode 100644 index 159a613983..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_4_2_2-solution000007.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {2, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_2_2.eprime b/tests/exhaustive/basic/comprehension_letting/expected/model_4_2_2.eprime deleted file mode 100644 index 7d168cbf12..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_4_2_2.eprime +++ /dev/null @@ -1,94 +0,0 @@ -language ESSENCE' 1.0 - -find s_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find s_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -find s_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -letting let1 be -100 -find x: int(-100..100) -find conjure_aux1: int(-20..3) -branching on [s_ExplicitVarSizeWithDummy, s_ExplicitVarSizeWithFlags_Flags, s_ExplicitVarSizeWithFlags_Values, x] -such that - and([and([s_ExplicitVarSizeWithFlags_Flags[q18], s_ExplicitVarSizeWithDummy[q19] != 5, - s_ExplicitVarSizeWithFlags_Values[q18] != s_ExplicitVarSizeWithDummy[q19], - allDiff([s_ExplicitVarSizeWithFlags_Values[q18] + s_ExplicitVarSizeWithDummy[q19], - s_ExplicitVarSizeWithFlags_Values[q18] * s_ExplicitVarSizeWithDummy[q19], - s_ExplicitVarSizeWithFlags_Values[q18] / s_ExplicitVarSizeWithDummy[q19]; - int(1..3)]), - (s_ExplicitVarSizeWithFlags_Values[q18] - s_ExplicitVarSizeWithDummy[q19]) % 2 = 0; - int(1..5)]) - -> - min([s_ExplicitVarSizeWithFlags_Values[q18] + s_ExplicitVarSizeWithDummy[q19], - s_ExplicitVarSizeWithFlags_Values[q18] - s_ExplicitVarSizeWithDummy[q19], - s_ExplicitVarSizeWithFlags_Values[q18] * s_ExplicitVarSizeWithDummy[q19], - s_ExplicitVarSizeWithFlags_Values[q18] / s_ExplicitVarSizeWithDummy[q19]; - int(1..4)]) - <= conjure_aux1 - | q18 : int(1..4), q19 : int(1..4)]), - sum([toInt(and([s_ExplicitVarSizeWithFlags_Flags[q18], s_ExplicitVarSizeWithDummy[q19] != 5, - s_ExplicitVarSizeWithFlags_Values[q18] != s_ExplicitVarSizeWithDummy[q19], - allDiff([s_ExplicitVarSizeWithFlags_Values[q18] + s_ExplicitVarSizeWithDummy[q19], - s_ExplicitVarSizeWithFlags_Values[q18] * s_ExplicitVarSizeWithDummy[q19], - s_ExplicitVarSizeWithFlags_Values[q18] / s_ExplicitVarSizeWithDummy[q19]; - int(1..3)]), - (s_ExplicitVarSizeWithFlags_Values[q18] - s_ExplicitVarSizeWithDummy[q19]) % 2 = 0; - int(1..5)])) - | q18 : int(1..4), q19 : int(1..4)]) - > 0 - -> - or([and([s_ExplicitVarSizeWithFlags_Flags[q18], s_ExplicitVarSizeWithDummy[q19] != 5, - s_ExplicitVarSizeWithFlags_Values[q18] != s_ExplicitVarSizeWithDummy[q19], - allDiff([s_ExplicitVarSizeWithFlags_Values[q18] + s_ExplicitVarSizeWithDummy[q19], - s_ExplicitVarSizeWithFlags_Values[q18] * s_ExplicitVarSizeWithDummy[q19], - s_ExplicitVarSizeWithFlags_Values[q18] / s_ExplicitVarSizeWithDummy[q19]; - int(1..3)]), - (s_ExplicitVarSizeWithFlags_Values[q18] - s_ExplicitVarSizeWithDummy[q19]) % 2 = 0; - int(1..5)]) - /\ - min([s_ExplicitVarSizeWithFlags_Values[q18] + s_ExplicitVarSizeWithDummy[q19], - s_ExplicitVarSizeWithFlags_Values[q18] - s_ExplicitVarSizeWithDummy[q19], - s_ExplicitVarSizeWithFlags_Values[q18] * s_ExplicitVarSizeWithDummy[q19], - s_ExplicitVarSizeWithFlags_Values[q18] / s_ExplicitVarSizeWithDummy[q19]; - int(1..4)]) - = conjure_aux1 - | q18 : int(1..4), q19 : int(1..4)]), - sum([toInt(and([s_ExplicitVarSizeWithFlags_Flags[q18], s_ExplicitVarSizeWithDummy[q19] != 5, - s_ExplicitVarSizeWithFlags_Values[q18] != s_ExplicitVarSizeWithDummy[q19], - allDiff([s_ExplicitVarSizeWithFlags_Values[q18] + s_ExplicitVarSizeWithDummy[q19], - s_ExplicitVarSizeWithFlags_Values[q18] * s_ExplicitVarSizeWithDummy[q19], - s_ExplicitVarSizeWithFlags_Values[q18] / s_ExplicitVarSizeWithDummy[q19]; - int(1..3)]), - (s_ExplicitVarSizeWithFlags_Values[q18] - s_ExplicitVarSizeWithDummy[q19]) % 2 = 0; - int(1..5)])) - | q18 : int(1..4), q19 : int(1..4)]) - = 0 - -> conjure_aux1 = -20, - x = conjure_aux1, - sum([toInt(and([s_ExplicitVarSizeWithFlags_Flags[q18], s_ExplicitVarSizeWithDummy[q19] != 5, - s_ExplicitVarSizeWithFlags_Values[q18] != s_ExplicitVarSizeWithDummy[q19], - allDiff([s_ExplicitVarSizeWithFlags_Values[q18] + s_ExplicitVarSizeWithDummy[q19], - s_ExplicitVarSizeWithFlags_Values[q18] * s_ExplicitVarSizeWithDummy[q19], - s_ExplicitVarSizeWithFlags_Values[q18] / s_ExplicitVarSizeWithDummy[q19]; - int(1..3)]), - (s_ExplicitVarSizeWithFlags_Values[q18] - s_ExplicitVarSizeWithDummy[q19]) % 2 = 0; - int(1..5)])) - | q18 : int(1..4), q19 : int(1..4)]) - > 0, - and([s_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - s_ExplicitVarSizeWithFlags_Values[q1] < s_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..3)]), - and([s_ExplicitVarSizeWithFlags_Flags[q2] = false -> s_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..4)]), - and([s_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> s_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), - and([s_ExplicitVarSizeWithDummy[q6] < s_ExplicitVarSizeWithDummy[q6 + 1] \/ s_ExplicitVarSizeWithDummy[q6] = 5 - | q6 : int(1..3)]), - and([s_ExplicitVarSizeWithDummy[q7] = 5 -> s_ExplicitVarSizeWithDummy[q7 + 1] = 5 | q7 : int(1..3)]), - and([s_ExplicitVarSizeWithDummy[q11] != 5 -> - or([s_ExplicitVarSizeWithFlags_Flags[q13] /\ - s_ExplicitVarSizeWithFlags_Values[q13] = s_ExplicitVarSizeWithDummy[q11] - | q13 : int(1..4)]) - | q11 : int(1..4)]), - and([s_ExplicitVarSizeWithFlags_Flags[q15] -> - or([s_ExplicitVarSizeWithDummy[q17] != 5 /\ - s_ExplicitVarSizeWithDummy[q17] = s_ExplicitVarSizeWithFlags_Values[q15] - | q17 : int(1..4)]) - | q15 : int(1..4)]) - diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_2_3-solution000001.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_2_3-solution000001.solution deleted file mode 100644 index 8b4ecbb66d..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_4_2_3-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 3} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_2_3-solution000002.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_2_3-solution000002.solution deleted file mode 100644 index 159a613983..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_4_2_3-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {2, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_2_3-solution000003.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_2_3-solution000003.solution deleted file mode 100644 index 5963aac565..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_4_2_3-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 3} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_2_3-solution000004.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_2_3-solution000004.solution deleted file mode 100644 index 6eeacc9727..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_4_2_3-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_2_3-solution000005.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_2_3-solution000005.solution deleted file mode 100644 index 560dd0f2f7..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_4_2_3-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 3, 4} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_2_3-solution000006.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_2_3-solution000006.solution deleted file mode 100644 index 40f3fd5c8f..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_4_2_3-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {2, 3, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_2_3-solution000007.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_2_3-solution000007.solution deleted file mode 100644 index bd956f44e3..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_4_2_3-solution000007.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 3, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_2_3.eprime b/tests/exhaustive/basic/comprehension_letting/expected/model_4_2_3.eprime deleted file mode 100644 index ba3742175a..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_4_2_3.eprime +++ /dev/null @@ -1,122 +0,0 @@ -language ESSENCE' 1.0 - -find s_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find s_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -find s_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -find s_ExplicitVarSizeWithMarker_Marker: int(0..4) -find s_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -letting let1 be -100 -find x: int(-100..100) -find conjure_aux1: int(-20..3) -branching on - [s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithMarker_Values, s_ExplicitVarSizeWithFlags_Flags, - s_ExplicitVarSizeWithFlags_Values, s_ExplicitVarSizeWithDummy, x] -such that - and([and([s_ExplicitVarSizeWithFlags_Flags[q37], s_ExplicitVarSizeWithDummy[q38] != 5, - s_ExplicitVarSizeWithFlags_Values[q37] != s_ExplicitVarSizeWithDummy[q38], - allDiff([s_ExplicitVarSizeWithFlags_Values[q37] + s_ExplicitVarSizeWithDummy[q38], - s_ExplicitVarSizeWithFlags_Values[q37] * s_ExplicitVarSizeWithDummy[q38], - s_ExplicitVarSizeWithFlags_Values[q37] / s_ExplicitVarSizeWithDummy[q38]; - int(1..3)]), - (s_ExplicitVarSizeWithFlags_Values[q37] - s_ExplicitVarSizeWithDummy[q38]) % 2 = 0; - int(1..5)]) - -> - min([s_ExplicitVarSizeWithFlags_Values[q37] + s_ExplicitVarSizeWithDummy[q38], - s_ExplicitVarSizeWithFlags_Values[q37] - s_ExplicitVarSizeWithDummy[q38], - s_ExplicitVarSizeWithFlags_Values[q37] * s_ExplicitVarSizeWithDummy[q38], - s_ExplicitVarSizeWithFlags_Values[q37] / s_ExplicitVarSizeWithDummy[q38]; - int(1..4)]) - <= conjure_aux1 - | q37 : int(1..4), q38 : int(1..4)]), - sum([toInt(and([s_ExplicitVarSizeWithFlags_Flags[q37], s_ExplicitVarSizeWithDummy[q38] != 5, - s_ExplicitVarSizeWithFlags_Values[q37] != s_ExplicitVarSizeWithDummy[q38], - allDiff([s_ExplicitVarSizeWithFlags_Values[q37] + s_ExplicitVarSizeWithDummy[q38], - s_ExplicitVarSizeWithFlags_Values[q37] * s_ExplicitVarSizeWithDummy[q38], - s_ExplicitVarSizeWithFlags_Values[q37] / s_ExplicitVarSizeWithDummy[q38]; - int(1..3)]), - (s_ExplicitVarSizeWithFlags_Values[q37] - s_ExplicitVarSizeWithDummy[q38]) % 2 = 0; - int(1..5)])) - | q37 : int(1..4), q38 : int(1..4)]) - > 0 - -> - or([and([s_ExplicitVarSizeWithFlags_Flags[q37], s_ExplicitVarSizeWithDummy[q38] != 5, - s_ExplicitVarSizeWithFlags_Values[q37] != s_ExplicitVarSizeWithDummy[q38], - allDiff([s_ExplicitVarSizeWithFlags_Values[q37] + s_ExplicitVarSizeWithDummy[q38], - s_ExplicitVarSizeWithFlags_Values[q37] * s_ExplicitVarSizeWithDummy[q38], - s_ExplicitVarSizeWithFlags_Values[q37] / s_ExplicitVarSizeWithDummy[q38]; - int(1..3)]), - (s_ExplicitVarSizeWithFlags_Values[q37] - s_ExplicitVarSizeWithDummy[q38]) % 2 = 0; - int(1..5)]) - /\ - min([s_ExplicitVarSizeWithFlags_Values[q37] + s_ExplicitVarSizeWithDummy[q38], - s_ExplicitVarSizeWithFlags_Values[q37] - s_ExplicitVarSizeWithDummy[q38], - s_ExplicitVarSizeWithFlags_Values[q37] * s_ExplicitVarSizeWithDummy[q38], - s_ExplicitVarSizeWithFlags_Values[q37] / s_ExplicitVarSizeWithDummy[q38]; - int(1..4)]) - = conjure_aux1 - | q37 : int(1..4), q38 : int(1..4)]), - sum([toInt(and([s_ExplicitVarSizeWithFlags_Flags[q37], s_ExplicitVarSizeWithDummy[q38] != 5, - s_ExplicitVarSizeWithFlags_Values[q37] != s_ExplicitVarSizeWithDummy[q38], - allDiff([s_ExplicitVarSizeWithFlags_Values[q37] + s_ExplicitVarSizeWithDummy[q38], - s_ExplicitVarSizeWithFlags_Values[q37] * s_ExplicitVarSizeWithDummy[q38], - s_ExplicitVarSizeWithFlags_Values[q37] / s_ExplicitVarSizeWithDummy[q38]; - int(1..3)]), - (s_ExplicitVarSizeWithFlags_Values[q37] - s_ExplicitVarSizeWithDummy[q38]) % 2 = 0; - int(1..5)])) - | q37 : int(1..4), q38 : int(1..4)]) - = 0 - -> conjure_aux1 = -20, - x = conjure_aux1, - sum([toInt(and([s_ExplicitVarSizeWithFlags_Flags[q37], s_ExplicitVarSizeWithDummy[q38] != 5, - s_ExplicitVarSizeWithFlags_Values[q37] != s_ExplicitVarSizeWithDummy[q38], - allDiff([s_ExplicitVarSizeWithFlags_Values[q37] + s_ExplicitVarSizeWithDummy[q38], - s_ExplicitVarSizeWithFlags_Values[q37] * s_ExplicitVarSizeWithDummy[q38], - s_ExplicitVarSizeWithFlags_Values[q37] / s_ExplicitVarSizeWithDummy[q38]; - int(1..3)]), - (s_ExplicitVarSizeWithFlags_Values[q37] - s_ExplicitVarSizeWithDummy[q38]) % 2 = 0; - int(1..5)])) - | q37 : int(1..4), q38 : int(1..4)]) - > 0, - and([s_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - s_ExplicitVarSizeWithFlags_Values[q1] < s_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..3)]), - and([s_ExplicitVarSizeWithFlags_Flags[q2] = false -> s_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..4)]), - and([s_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> s_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), - and([s_ExplicitVarSizeWithDummy[q6] < s_ExplicitVarSizeWithDummy[q6 + 1] \/ s_ExplicitVarSizeWithDummy[q6] = 5 - | q6 : int(1..3)]), - and([s_ExplicitVarSizeWithDummy[q7] = 5 -> s_ExplicitVarSizeWithDummy[q7 + 1] = 5 | q7 : int(1..3)]), - and([s_ExplicitVarSizeWithDummy[q11] != 5 -> - or([s_ExplicitVarSizeWithFlags_Flags[q13] /\ - s_ExplicitVarSizeWithFlags_Values[q13] = s_ExplicitVarSizeWithDummy[q11] - | q13 : int(1..4)]) - | q11 : int(1..4)]), - and([s_ExplicitVarSizeWithFlags_Flags[q15] -> - or([s_ExplicitVarSizeWithDummy[q17] != 5 /\ - s_ExplicitVarSizeWithDummy[q17] = s_ExplicitVarSizeWithFlags_Values[q15] - | q17 : int(1..4)]) - | q15 : int(1..4)]), - and([q18 + 1 <= s_ExplicitVarSizeWithMarker_Marker -> - s_ExplicitVarSizeWithMarker_Values[q18] < s_ExplicitVarSizeWithMarker_Values[q18 + 1] - | q18 : int(1..3)]), - and([q19 > s_ExplicitVarSizeWithMarker_Marker -> s_ExplicitVarSizeWithMarker_Values[q19] = 1 | q19 : int(1..4)]), - and([q22 <= s_ExplicitVarSizeWithMarker_Marker -> - or([s_ExplicitVarSizeWithFlags_Flags[q24] /\ - s_ExplicitVarSizeWithFlags_Values[q24] = s_ExplicitVarSizeWithMarker_Values[q22] - | q24 : int(1..4)]) - | q22 : int(1..4)]), - and([s_ExplicitVarSizeWithFlags_Flags[q26] -> - or([q28 <= s_ExplicitVarSizeWithMarker_Marker /\ - s_ExplicitVarSizeWithMarker_Values[q28] = s_ExplicitVarSizeWithFlags_Values[q26] - | q28 : int(1..4)]) - | q26 : int(1..4)]), - and([q30 <= s_ExplicitVarSizeWithMarker_Marker -> - or([s_ExplicitVarSizeWithDummy[q32] != 5 /\ - s_ExplicitVarSizeWithDummy[q32] = s_ExplicitVarSizeWithMarker_Values[q30] - | q32 : int(1..4)]) - | q30 : int(1..4)]), - and([s_ExplicitVarSizeWithDummy[q34] != 5 -> - or([q36 <= s_ExplicitVarSizeWithMarker_Marker /\ - s_ExplicitVarSizeWithMarker_Values[q36] = s_ExplicitVarSizeWithDummy[q34] - | q36 : int(1..4)]) - | q34 : int(1..4)]) - diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_2_4-solution000001.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_2_4-solution000001.solution deleted file mode 100644 index bd956f44e3..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_4_2_4-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 3, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_2_4-solution000002.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_2_4-solution000002.solution deleted file mode 100644 index 5963aac565..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_4_2_4-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 3} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_2_4-solution000003.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_2_4-solution000003.solution deleted file mode 100644 index 6eeacc9727..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_4_2_4-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_2_4-solution000004.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_2_4-solution000004.solution deleted file mode 100644 index 560dd0f2f7..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_4_2_4-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 3, 4} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_2_4-solution000005.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_2_4-solution000005.solution deleted file mode 100644 index 8b4ecbb66d..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_4_2_4-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 3} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_2_4-solution000006.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_2_4-solution000006.solution deleted file mode 100644 index 40f3fd5c8f..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_4_2_4-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {2, 3, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_2_4-solution000007.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_2_4-solution000007.solution deleted file mode 100644 index 159a613983..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_4_2_4-solution000007.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {2, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_2_4.eprime b/tests/exhaustive/basic/comprehension_letting/expected/model_4_2_4.eprime deleted file mode 100644 index 7d168cbf12..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_4_2_4.eprime +++ /dev/null @@ -1,94 +0,0 @@ -language ESSENCE' 1.0 - -find s_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find s_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -find s_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -letting let1 be -100 -find x: int(-100..100) -find conjure_aux1: int(-20..3) -branching on [s_ExplicitVarSizeWithDummy, s_ExplicitVarSizeWithFlags_Flags, s_ExplicitVarSizeWithFlags_Values, x] -such that - and([and([s_ExplicitVarSizeWithFlags_Flags[q18], s_ExplicitVarSizeWithDummy[q19] != 5, - s_ExplicitVarSizeWithFlags_Values[q18] != s_ExplicitVarSizeWithDummy[q19], - allDiff([s_ExplicitVarSizeWithFlags_Values[q18] + s_ExplicitVarSizeWithDummy[q19], - s_ExplicitVarSizeWithFlags_Values[q18] * s_ExplicitVarSizeWithDummy[q19], - s_ExplicitVarSizeWithFlags_Values[q18] / s_ExplicitVarSizeWithDummy[q19]; - int(1..3)]), - (s_ExplicitVarSizeWithFlags_Values[q18] - s_ExplicitVarSizeWithDummy[q19]) % 2 = 0; - int(1..5)]) - -> - min([s_ExplicitVarSizeWithFlags_Values[q18] + s_ExplicitVarSizeWithDummy[q19], - s_ExplicitVarSizeWithFlags_Values[q18] - s_ExplicitVarSizeWithDummy[q19], - s_ExplicitVarSizeWithFlags_Values[q18] * s_ExplicitVarSizeWithDummy[q19], - s_ExplicitVarSizeWithFlags_Values[q18] / s_ExplicitVarSizeWithDummy[q19]; - int(1..4)]) - <= conjure_aux1 - | q18 : int(1..4), q19 : int(1..4)]), - sum([toInt(and([s_ExplicitVarSizeWithFlags_Flags[q18], s_ExplicitVarSizeWithDummy[q19] != 5, - s_ExplicitVarSizeWithFlags_Values[q18] != s_ExplicitVarSizeWithDummy[q19], - allDiff([s_ExplicitVarSizeWithFlags_Values[q18] + s_ExplicitVarSizeWithDummy[q19], - s_ExplicitVarSizeWithFlags_Values[q18] * s_ExplicitVarSizeWithDummy[q19], - s_ExplicitVarSizeWithFlags_Values[q18] / s_ExplicitVarSizeWithDummy[q19]; - int(1..3)]), - (s_ExplicitVarSizeWithFlags_Values[q18] - s_ExplicitVarSizeWithDummy[q19]) % 2 = 0; - int(1..5)])) - | q18 : int(1..4), q19 : int(1..4)]) - > 0 - -> - or([and([s_ExplicitVarSizeWithFlags_Flags[q18], s_ExplicitVarSizeWithDummy[q19] != 5, - s_ExplicitVarSizeWithFlags_Values[q18] != s_ExplicitVarSizeWithDummy[q19], - allDiff([s_ExplicitVarSizeWithFlags_Values[q18] + s_ExplicitVarSizeWithDummy[q19], - s_ExplicitVarSizeWithFlags_Values[q18] * s_ExplicitVarSizeWithDummy[q19], - s_ExplicitVarSizeWithFlags_Values[q18] / s_ExplicitVarSizeWithDummy[q19]; - int(1..3)]), - (s_ExplicitVarSizeWithFlags_Values[q18] - s_ExplicitVarSizeWithDummy[q19]) % 2 = 0; - int(1..5)]) - /\ - min([s_ExplicitVarSizeWithFlags_Values[q18] + s_ExplicitVarSizeWithDummy[q19], - s_ExplicitVarSizeWithFlags_Values[q18] - s_ExplicitVarSizeWithDummy[q19], - s_ExplicitVarSizeWithFlags_Values[q18] * s_ExplicitVarSizeWithDummy[q19], - s_ExplicitVarSizeWithFlags_Values[q18] / s_ExplicitVarSizeWithDummy[q19]; - int(1..4)]) - = conjure_aux1 - | q18 : int(1..4), q19 : int(1..4)]), - sum([toInt(and([s_ExplicitVarSizeWithFlags_Flags[q18], s_ExplicitVarSizeWithDummy[q19] != 5, - s_ExplicitVarSizeWithFlags_Values[q18] != s_ExplicitVarSizeWithDummy[q19], - allDiff([s_ExplicitVarSizeWithFlags_Values[q18] + s_ExplicitVarSizeWithDummy[q19], - s_ExplicitVarSizeWithFlags_Values[q18] * s_ExplicitVarSizeWithDummy[q19], - s_ExplicitVarSizeWithFlags_Values[q18] / s_ExplicitVarSizeWithDummy[q19]; - int(1..3)]), - (s_ExplicitVarSizeWithFlags_Values[q18] - s_ExplicitVarSizeWithDummy[q19]) % 2 = 0; - int(1..5)])) - | q18 : int(1..4), q19 : int(1..4)]) - = 0 - -> conjure_aux1 = -20, - x = conjure_aux1, - sum([toInt(and([s_ExplicitVarSizeWithFlags_Flags[q18], s_ExplicitVarSizeWithDummy[q19] != 5, - s_ExplicitVarSizeWithFlags_Values[q18] != s_ExplicitVarSizeWithDummy[q19], - allDiff([s_ExplicitVarSizeWithFlags_Values[q18] + s_ExplicitVarSizeWithDummy[q19], - s_ExplicitVarSizeWithFlags_Values[q18] * s_ExplicitVarSizeWithDummy[q19], - s_ExplicitVarSizeWithFlags_Values[q18] / s_ExplicitVarSizeWithDummy[q19]; - int(1..3)]), - (s_ExplicitVarSizeWithFlags_Values[q18] - s_ExplicitVarSizeWithDummy[q19]) % 2 = 0; - int(1..5)])) - | q18 : int(1..4), q19 : int(1..4)]) - > 0, - and([s_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - s_ExplicitVarSizeWithFlags_Values[q1] < s_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..3)]), - and([s_ExplicitVarSizeWithFlags_Flags[q2] = false -> s_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..4)]), - and([s_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> s_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), - and([s_ExplicitVarSizeWithDummy[q6] < s_ExplicitVarSizeWithDummy[q6 + 1] \/ s_ExplicitVarSizeWithDummy[q6] = 5 - | q6 : int(1..3)]), - and([s_ExplicitVarSizeWithDummy[q7] = 5 -> s_ExplicitVarSizeWithDummy[q7 + 1] = 5 | q7 : int(1..3)]), - and([s_ExplicitVarSizeWithDummy[q11] != 5 -> - or([s_ExplicitVarSizeWithFlags_Flags[q13] /\ - s_ExplicitVarSizeWithFlags_Values[q13] = s_ExplicitVarSizeWithDummy[q11] - | q13 : int(1..4)]) - | q11 : int(1..4)]), - and([s_ExplicitVarSizeWithFlags_Flags[q15] -> - or([s_ExplicitVarSizeWithDummy[q17] != 5 /\ - s_ExplicitVarSizeWithDummy[q17] = s_ExplicitVarSizeWithFlags_Values[q15] - | q17 : int(1..4)]) - | q15 : int(1..4)]) - diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_3_1-solution000001.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_3_1-solution000001.solution deleted file mode 100644 index 159a613983..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_4_3_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {2, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_3_1-solution000002.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_3_1-solution000002.solution deleted file mode 100644 index 40f3fd5c8f..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_4_3_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {2, 3, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_3_1-solution000003.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_3_1-solution000003.solution deleted file mode 100644 index 8b4ecbb66d..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_4_3_1-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 3} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_3_1-solution000004.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_3_1-solution000004.solution deleted file mode 100644 index 560dd0f2f7..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_4_3_1-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 3, 4} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_3_1-solution000005.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_3_1-solution000005.solution deleted file mode 100644 index 6eeacc9727..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_4_3_1-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_3_1-solution000006.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_3_1-solution000006.solution deleted file mode 100644 index 5963aac565..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_4_3_1-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 3} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_3_1-solution000007.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_3_1-solution000007.solution deleted file mode 100644 index bd956f44e3..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_4_3_1-solution000007.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 3, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_3_1.eprime b/tests/exhaustive/basic/comprehension_letting/expected/model_4_3_1.eprime deleted file mode 100644 index 5e74dde769..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_4_3_1.eprime +++ /dev/null @@ -1,110 +0,0 @@ -language ESSENCE' 1.0 - -find s_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find s_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -find s_ExplicitVarSizeWithMarker_Marker: int(0..4) -find s_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -find s_Occurrence: matrix indexed by [int(1..4)] of bool -letting let1 be -100 -find x: int(-100..100) -find conjure_aux1: int(-16..3) -branching on - [s_Occurrence, s_ExplicitVarSizeWithFlags_Flags, s_ExplicitVarSizeWithFlags_Values, - s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithMarker_Values, x] -such that - and([and([s_ExplicitVarSizeWithFlags_Flags[q28], q29 <= s_ExplicitVarSizeWithMarker_Marker, - s_ExplicitVarSizeWithFlags_Values[q28] != s_ExplicitVarSizeWithMarker_Values[q29], - allDiff([s_ExplicitVarSizeWithFlags_Values[q28] + s_ExplicitVarSizeWithMarker_Values[q29], - s_ExplicitVarSizeWithFlags_Values[q28] * s_ExplicitVarSizeWithMarker_Values[q29], - s_ExplicitVarSizeWithFlags_Values[q28] / s_ExplicitVarSizeWithMarker_Values[q29]; - int(1..3)]), - (s_ExplicitVarSizeWithFlags_Values[q28] - s_ExplicitVarSizeWithMarker_Values[q29]) % 2 = 0; - int(1..5)]) - -> - min([s_ExplicitVarSizeWithFlags_Values[q28] + s_ExplicitVarSizeWithMarker_Values[q29], - s_ExplicitVarSizeWithFlags_Values[q28] - s_ExplicitVarSizeWithMarker_Values[q29], - s_ExplicitVarSizeWithFlags_Values[q28] * s_ExplicitVarSizeWithMarker_Values[q29], - s_ExplicitVarSizeWithFlags_Values[q28] / s_ExplicitVarSizeWithMarker_Values[q29]; - int(1..4)]) - <= conjure_aux1 - | q28 : int(1..4), q29 : int(1..4)]), - sum([toInt(and([s_ExplicitVarSizeWithFlags_Flags[q28], q29 <= s_ExplicitVarSizeWithMarker_Marker, - s_ExplicitVarSizeWithFlags_Values[q28] != s_ExplicitVarSizeWithMarker_Values[q29], - allDiff([s_ExplicitVarSizeWithFlags_Values[q28] + s_ExplicitVarSizeWithMarker_Values[q29], - s_ExplicitVarSizeWithFlags_Values[q28] * s_ExplicitVarSizeWithMarker_Values[q29], - s_ExplicitVarSizeWithFlags_Values[q28] / s_ExplicitVarSizeWithMarker_Values[q29]; - int(1..3)]), - (s_ExplicitVarSizeWithFlags_Values[q28] - s_ExplicitVarSizeWithMarker_Values[q29]) % 2 = 0; - int(1..5)])) - | q28 : int(1..4), q29 : int(1..4)]) - > 0 - -> - or([and([s_ExplicitVarSizeWithFlags_Flags[q28], q29 <= s_ExplicitVarSizeWithMarker_Marker, - s_ExplicitVarSizeWithFlags_Values[q28] != s_ExplicitVarSizeWithMarker_Values[q29], - allDiff([s_ExplicitVarSizeWithFlags_Values[q28] + s_ExplicitVarSizeWithMarker_Values[q29], - s_ExplicitVarSizeWithFlags_Values[q28] * s_ExplicitVarSizeWithMarker_Values[q29], - s_ExplicitVarSizeWithFlags_Values[q28] / s_ExplicitVarSizeWithMarker_Values[q29]; - int(1..3)]), - (s_ExplicitVarSizeWithFlags_Values[q28] - s_ExplicitVarSizeWithMarker_Values[q29]) % 2 = 0; - int(1..5)]) - /\ - min([s_ExplicitVarSizeWithFlags_Values[q28] + s_ExplicitVarSizeWithMarker_Values[q29], - s_ExplicitVarSizeWithFlags_Values[q28] - s_ExplicitVarSizeWithMarker_Values[q29], - s_ExplicitVarSizeWithFlags_Values[q28] * s_ExplicitVarSizeWithMarker_Values[q29], - s_ExplicitVarSizeWithFlags_Values[q28] / s_ExplicitVarSizeWithMarker_Values[q29]; - int(1..4)]) - = conjure_aux1 - | q28 : int(1..4), q29 : int(1..4)]), - sum([toInt(and([s_ExplicitVarSizeWithFlags_Flags[q28], q29 <= s_ExplicitVarSizeWithMarker_Marker, - s_ExplicitVarSizeWithFlags_Values[q28] != s_ExplicitVarSizeWithMarker_Values[q29], - allDiff([s_ExplicitVarSizeWithFlags_Values[q28] + s_ExplicitVarSizeWithMarker_Values[q29], - s_ExplicitVarSizeWithFlags_Values[q28] * s_ExplicitVarSizeWithMarker_Values[q29], - s_ExplicitVarSizeWithFlags_Values[q28] / s_ExplicitVarSizeWithMarker_Values[q29]; - int(1..3)]), - (s_ExplicitVarSizeWithFlags_Values[q28] - s_ExplicitVarSizeWithMarker_Values[q29]) % 2 = 0; - int(1..5)])) - | q28 : int(1..4), q29 : int(1..4)]) - = 0 - -> conjure_aux1 = -16, - x = conjure_aux1, - sum([toInt(and([s_ExplicitVarSizeWithFlags_Flags[q28], q29 <= s_ExplicitVarSizeWithMarker_Marker, - s_ExplicitVarSizeWithFlags_Values[q28] != s_ExplicitVarSizeWithMarker_Values[q29], - allDiff([s_ExplicitVarSizeWithFlags_Values[q28] + s_ExplicitVarSizeWithMarker_Values[q29], - s_ExplicitVarSizeWithFlags_Values[q28] * s_ExplicitVarSizeWithMarker_Values[q29], - s_ExplicitVarSizeWithFlags_Values[q28] / s_ExplicitVarSizeWithMarker_Values[q29]; - int(1..3)]), - (s_ExplicitVarSizeWithFlags_Values[q28] - s_ExplicitVarSizeWithMarker_Values[q29]) % 2 = 0; - int(1..5)])) - | q28 : int(1..4), q29 : int(1..4)]) - > 0, - and([s_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - s_ExplicitVarSizeWithFlags_Values[q1] < s_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..3)]), - and([s_ExplicitVarSizeWithFlags_Flags[q2] = false -> s_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..4)]), - and([s_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> s_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), - and([q6 + 1 <= s_ExplicitVarSizeWithMarker_Marker -> - s_ExplicitVarSizeWithMarker_Values[q6] < s_ExplicitVarSizeWithMarker_Values[q6 + 1] - | q6 : int(1..3)]), - and([q7 > s_ExplicitVarSizeWithMarker_Marker -> s_ExplicitVarSizeWithMarker_Values[q7] = 1 | q7 : int(1..4)]), - and([q10 <= s_ExplicitVarSizeWithMarker_Marker -> - or([s_ExplicitVarSizeWithFlags_Flags[q12] /\ - s_ExplicitVarSizeWithFlags_Values[q12] = s_ExplicitVarSizeWithMarker_Values[q10] - | q12 : int(1..4)]) - | q10 : int(1..4)]), - and([s_ExplicitVarSizeWithFlags_Flags[q14] -> - or([q16 <= s_ExplicitVarSizeWithMarker_Marker /\ - s_ExplicitVarSizeWithMarker_Values[q16] = s_ExplicitVarSizeWithFlags_Values[q14] - | q16 : int(1..4)]) - | q14 : int(1..4)]), - and([s_Occurrence[q18] -> - or([s_ExplicitVarSizeWithFlags_Flags[q20] /\ s_ExplicitVarSizeWithFlags_Values[q20] = q18 | q20 : int(1..4)]) - | q18 : int(1..4)]), - and([s_ExplicitVarSizeWithFlags_Flags[q22] -> s_Occurrence[s_ExplicitVarSizeWithFlags_Values[q22]] - | q22 : int(1..4)]), - and([s_Occurrence[q23] -> - or([q25 <= s_ExplicitVarSizeWithMarker_Marker /\ s_ExplicitVarSizeWithMarker_Values[q25] = q23 - | q25 : int(1..4)]) - | q23 : int(1..4)]), - and([q27 <= s_ExplicitVarSizeWithMarker_Marker -> s_Occurrence[s_ExplicitVarSizeWithMarker_Values[q27]] - | q27 : int(1..4)]) - diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_3_2-solution000001.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_3_2-solution000001.solution deleted file mode 100644 index bd956f44e3..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_4_3_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 3, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_3_2-solution000002.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_3_2-solution000002.solution deleted file mode 100644 index 5963aac565..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_4_3_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 3} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_3_2-solution000003.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_3_2-solution000003.solution deleted file mode 100644 index 6eeacc9727..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_4_3_2-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_3_2-solution000004.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_3_2-solution000004.solution deleted file mode 100644 index 560dd0f2f7..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_4_3_2-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 3, 4} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_3_2-solution000005.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_3_2-solution000005.solution deleted file mode 100644 index 8b4ecbb66d..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_4_3_2-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 3} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_3_2-solution000006.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_3_2-solution000006.solution deleted file mode 100644 index 40f3fd5c8f..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_4_3_2-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {2, 3, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_3_2-solution000007.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_3_2-solution000007.solution deleted file mode 100644 index 159a613983..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_4_3_2-solution000007.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {2, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_3_2.eprime b/tests/exhaustive/basic/comprehension_letting/expected/model_4_3_2.eprime deleted file mode 100644 index 80a6ca3fbf..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_4_3_2.eprime +++ /dev/null @@ -1,122 +0,0 @@ -language ESSENCE' 1.0 - -find s_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find s_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -find s_ExplicitVarSizeWithMarker_Marker: int(0..4) -find s_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -find s_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -letting let1 be -100 -find x: int(-100..100) -find conjure_aux1: int(-16..3) -branching on - [s_ExplicitVarSizeWithDummy, s_ExplicitVarSizeWithFlags_Flags, s_ExplicitVarSizeWithFlags_Values, - s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithMarker_Values, x] -such that - and([and([s_ExplicitVarSizeWithFlags_Flags[q37], q38 <= s_ExplicitVarSizeWithMarker_Marker, - s_ExplicitVarSizeWithFlags_Values[q37] != s_ExplicitVarSizeWithMarker_Values[q38], - allDiff([s_ExplicitVarSizeWithFlags_Values[q37] + s_ExplicitVarSizeWithMarker_Values[q38], - s_ExplicitVarSizeWithFlags_Values[q37] * s_ExplicitVarSizeWithMarker_Values[q38], - s_ExplicitVarSizeWithFlags_Values[q37] / s_ExplicitVarSizeWithMarker_Values[q38]; - int(1..3)]), - (s_ExplicitVarSizeWithFlags_Values[q37] - s_ExplicitVarSizeWithMarker_Values[q38]) % 2 = 0; - int(1..5)]) - -> - min([s_ExplicitVarSizeWithFlags_Values[q37] + s_ExplicitVarSizeWithMarker_Values[q38], - s_ExplicitVarSizeWithFlags_Values[q37] - s_ExplicitVarSizeWithMarker_Values[q38], - s_ExplicitVarSizeWithFlags_Values[q37] * s_ExplicitVarSizeWithMarker_Values[q38], - s_ExplicitVarSizeWithFlags_Values[q37] / s_ExplicitVarSizeWithMarker_Values[q38]; - int(1..4)]) - <= conjure_aux1 - | q37 : int(1..4), q38 : int(1..4)]), - sum([toInt(and([s_ExplicitVarSizeWithFlags_Flags[q37], q38 <= s_ExplicitVarSizeWithMarker_Marker, - s_ExplicitVarSizeWithFlags_Values[q37] != s_ExplicitVarSizeWithMarker_Values[q38], - allDiff([s_ExplicitVarSizeWithFlags_Values[q37] + s_ExplicitVarSizeWithMarker_Values[q38], - s_ExplicitVarSizeWithFlags_Values[q37] * s_ExplicitVarSizeWithMarker_Values[q38], - s_ExplicitVarSizeWithFlags_Values[q37] / s_ExplicitVarSizeWithMarker_Values[q38]; - int(1..3)]), - (s_ExplicitVarSizeWithFlags_Values[q37] - s_ExplicitVarSizeWithMarker_Values[q38]) % 2 = 0; - int(1..5)])) - | q37 : int(1..4), q38 : int(1..4)]) - > 0 - -> - or([and([s_ExplicitVarSizeWithFlags_Flags[q37], q38 <= s_ExplicitVarSizeWithMarker_Marker, - s_ExplicitVarSizeWithFlags_Values[q37] != s_ExplicitVarSizeWithMarker_Values[q38], - allDiff([s_ExplicitVarSizeWithFlags_Values[q37] + s_ExplicitVarSizeWithMarker_Values[q38], - s_ExplicitVarSizeWithFlags_Values[q37] * s_ExplicitVarSizeWithMarker_Values[q38], - s_ExplicitVarSizeWithFlags_Values[q37] / s_ExplicitVarSizeWithMarker_Values[q38]; - int(1..3)]), - (s_ExplicitVarSizeWithFlags_Values[q37] - s_ExplicitVarSizeWithMarker_Values[q38]) % 2 = 0; - int(1..5)]) - /\ - min([s_ExplicitVarSizeWithFlags_Values[q37] + s_ExplicitVarSizeWithMarker_Values[q38], - s_ExplicitVarSizeWithFlags_Values[q37] - s_ExplicitVarSizeWithMarker_Values[q38], - s_ExplicitVarSizeWithFlags_Values[q37] * s_ExplicitVarSizeWithMarker_Values[q38], - s_ExplicitVarSizeWithFlags_Values[q37] / s_ExplicitVarSizeWithMarker_Values[q38]; - int(1..4)]) - = conjure_aux1 - | q37 : int(1..4), q38 : int(1..4)]), - sum([toInt(and([s_ExplicitVarSizeWithFlags_Flags[q37], q38 <= s_ExplicitVarSizeWithMarker_Marker, - s_ExplicitVarSizeWithFlags_Values[q37] != s_ExplicitVarSizeWithMarker_Values[q38], - allDiff([s_ExplicitVarSizeWithFlags_Values[q37] + s_ExplicitVarSizeWithMarker_Values[q38], - s_ExplicitVarSizeWithFlags_Values[q37] * s_ExplicitVarSizeWithMarker_Values[q38], - s_ExplicitVarSizeWithFlags_Values[q37] / s_ExplicitVarSizeWithMarker_Values[q38]; - int(1..3)]), - (s_ExplicitVarSizeWithFlags_Values[q37] - s_ExplicitVarSizeWithMarker_Values[q38]) % 2 = 0; - int(1..5)])) - | q37 : int(1..4), q38 : int(1..4)]) - = 0 - -> conjure_aux1 = -16, - x = conjure_aux1, - sum([toInt(and([s_ExplicitVarSizeWithFlags_Flags[q37], q38 <= s_ExplicitVarSizeWithMarker_Marker, - s_ExplicitVarSizeWithFlags_Values[q37] != s_ExplicitVarSizeWithMarker_Values[q38], - allDiff([s_ExplicitVarSizeWithFlags_Values[q37] + s_ExplicitVarSizeWithMarker_Values[q38], - s_ExplicitVarSizeWithFlags_Values[q37] * s_ExplicitVarSizeWithMarker_Values[q38], - s_ExplicitVarSizeWithFlags_Values[q37] / s_ExplicitVarSizeWithMarker_Values[q38]; - int(1..3)]), - (s_ExplicitVarSizeWithFlags_Values[q37] - s_ExplicitVarSizeWithMarker_Values[q38]) % 2 = 0; - int(1..5)])) - | q37 : int(1..4), q38 : int(1..4)]) - > 0, - and([s_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - s_ExplicitVarSizeWithFlags_Values[q1] < s_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..3)]), - and([s_ExplicitVarSizeWithFlags_Flags[q2] = false -> s_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..4)]), - and([s_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> s_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), - and([q6 + 1 <= s_ExplicitVarSizeWithMarker_Marker -> - s_ExplicitVarSizeWithMarker_Values[q6] < s_ExplicitVarSizeWithMarker_Values[q6 + 1] - | q6 : int(1..3)]), - and([q7 > s_ExplicitVarSizeWithMarker_Marker -> s_ExplicitVarSizeWithMarker_Values[q7] = 1 | q7 : int(1..4)]), - and([q10 <= s_ExplicitVarSizeWithMarker_Marker -> - or([s_ExplicitVarSizeWithFlags_Flags[q12] /\ - s_ExplicitVarSizeWithFlags_Values[q12] = s_ExplicitVarSizeWithMarker_Values[q10] - | q12 : int(1..4)]) - | q10 : int(1..4)]), - and([s_ExplicitVarSizeWithFlags_Flags[q14] -> - or([q16 <= s_ExplicitVarSizeWithMarker_Marker /\ - s_ExplicitVarSizeWithMarker_Values[q16] = s_ExplicitVarSizeWithFlags_Values[q14] - | q16 : int(1..4)]) - | q14 : int(1..4)]), - and([s_ExplicitVarSizeWithDummy[q17] < s_ExplicitVarSizeWithDummy[q17 + 1] \/ s_ExplicitVarSizeWithDummy[q17] = 5 - | q17 : int(1..3)]), - and([s_ExplicitVarSizeWithDummy[q18] = 5 -> s_ExplicitVarSizeWithDummy[q18 + 1] = 5 | q18 : int(1..3)]), - and([s_ExplicitVarSizeWithDummy[q22] != 5 -> - or([s_ExplicitVarSizeWithFlags_Flags[q24] /\ - s_ExplicitVarSizeWithFlags_Values[q24] = s_ExplicitVarSizeWithDummy[q22] - | q24 : int(1..4)]) - | q22 : int(1..4)]), - and([s_ExplicitVarSizeWithFlags_Flags[q26] -> - or([s_ExplicitVarSizeWithDummy[q28] != 5 /\ - s_ExplicitVarSizeWithDummy[q28] = s_ExplicitVarSizeWithFlags_Values[q26] - | q28 : int(1..4)]) - | q26 : int(1..4)]), - and([s_ExplicitVarSizeWithDummy[q30] != 5 -> - or([q32 <= s_ExplicitVarSizeWithMarker_Marker /\ - s_ExplicitVarSizeWithMarker_Values[q32] = s_ExplicitVarSizeWithDummy[q30] - | q32 : int(1..4)]) - | q30 : int(1..4)]), - and([q34 <= s_ExplicitVarSizeWithMarker_Marker -> - or([s_ExplicitVarSizeWithDummy[q36] != 5 /\ - s_ExplicitVarSizeWithDummy[q36] = s_ExplicitVarSizeWithMarker_Values[q34] - | q36 : int(1..4)]) - | q34 : int(1..4)]) - diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_3_3-solution000001.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_3_3-solution000001.solution deleted file mode 100644 index 8b4ecbb66d..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_4_3_3-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 3} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_3_3-solution000002.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_3_3-solution000002.solution deleted file mode 100644 index 159a613983..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_4_3_3-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {2, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_3_3-solution000003.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_3_3-solution000003.solution deleted file mode 100644 index 5963aac565..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_4_3_3-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 3} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_3_3-solution000004.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_3_3-solution000004.solution deleted file mode 100644 index 6eeacc9727..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_4_3_3-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_3_3-solution000005.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_3_3-solution000005.solution deleted file mode 100644 index 560dd0f2f7..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_4_3_3-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 3, 4} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_3_3-solution000006.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_3_3-solution000006.solution deleted file mode 100644 index 40f3fd5c8f..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_4_3_3-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {2, 3, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_3_3-solution000007.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_3_3-solution000007.solution deleted file mode 100644 index bd956f44e3..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_4_3_3-solution000007.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 3, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_3_3.eprime b/tests/exhaustive/basic/comprehension_letting/expected/model_4_3_3.eprime deleted file mode 100644 index 0a99214fbe..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_4_3_3.eprime +++ /dev/null @@ -1,98 +0,0 @@ -language ESSENCE' 1.0 - -find s_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find s_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -find s_ExplicitVarSizeWithMarker_Marker: int(0..4) -find s_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -letting let1 be -100 -find x: int(-100..100) -find conjure_aux1: int(-16..3) -branching on - [s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithMarker_Values, s_ExplicitVarSizeWithFlags_Flags, - s_ExplicitVarSizeWithFlags_Values, x] -such that - and([and([s_ExplicitVarSizeWithFlags_Flags[q17], q18 <= s_ExplicitVarSizeWithMarker_Marker, - s_ExplicitVarSizeWithFlags_Values[q17] != s_ExplicitVarSizeWithMarker_Values[q18], - allDiff([s_ExplicitVarSizeWithFlags_Values[q17] + s_ExplicitVarSizeWithMarker_Values[q18], - s_ExplicitVarSizeWithFlags_Values[q17] * s_ExplicitVarSizeWithMarker_Values[q18], - s_ExplicitVarSizeWithFlags_Values[q17] / s_ExplicitVarSizeWithMarker_Values[q18]; - int(1..3)]), - (s_ExplicitVarSizeWithFlags_Values[q17] - s_ExplicitVarSizeWithMarker_Values[q18]) % 2 = 0; - int(1..5)]) - -> - min([s_ExplicitVarSizeWithFlags_Values[q17] + s_ExplicitVarSizeWithMarker_Values[q18], - s_ExplicitVarSizeWithFlags_Values[q17] - s_ExplicitVarSizeWithMarker_Values[q18], - s_ExplicitVarSizeWithFlags_Values[q17] * s_ExplicitVarSizeWithMarker_Values[q18], - s_ExplicitVarSizeWithFlags_Values[q17] / s_ExplicitVarSizeWithMarker_Values[q18]; - int(1..4)]) - <= conjure_aux1 - | q17 : int(1..4), q18 : int(1..4)]), - sum([toInt(and([s_ExplicitVarSizeWithFlags_Flags[q17], q18 <= s_ExplicitVarSizeWithMarker_Marker, - s_ExplicitVarSizeWithFlags_Values[q17] != s_ExplicitVarSizeWithMarker_Values[q18], - allDiff([s_ExplicitVarSizeWithFlags_Values[q17] + s_ExplicitVarSizeWithMarker_Values[q18], - s_ExplicitVarSizeWithFlags_Values[q17] * s_ExplicitVarSizeWithMarker_Values[q18], - s_ExplicitVarSizeWithFlags_Values[q17] / s_ExplicitVarSizeWithMarker_Values[q18]; - int(1..3)]), - (s_ExplicitVarSizeWithFlags_Values[q17] - s_ExplicitVarSizeWithMarker_Values[q18]) % 2 = 0; - int(1..5)])) - | q17 : int(1..4), q18 : int(1..4)]) - > 0 - -> - or([and([s_ExplicitVarSizeWithFlags_Flags[q17], q18 <= s_ExplicitVarSizeWithMarker_Marker, - s_ExplicitVarSizeWithFlags_Values[q17] != s_ExplicitVarSizeWithMarker_Values[q18], - allDiff([s_ExplicitVarSizeWithFlags_Values[q17] + s_ExplicitVarSizeWithMarker_Values[q18], - s_ExplicitVarSizeWithFlags_Values[q17] * s_ExplicitVarSizeWithMarker_Values[q18], - s_ExplicitVarSizeWithFlags_Values[q17] / s_ExplicitVarSizeWithMarker_Values[q18]; - int(1..3)]), - (s_ExplicitVarSizeWithFlags_Values[q17] - s_ExplicitVarSizeWithMarker_Values[q18]) % 2 = 0; - int(1..5)]) - /\ - min([s_ExplicitVarSizeWithFlags_Values[q17] + s_ExplicitVarSizeWithMarker_Values[q18], - s_ExplicitVarSizeWithFlags_Values[q17] - s_ExplicitVarSizeWithMarker_Values[q18], - s_ExplicitVarSizeWithFlags_Values[q17] * s_ExplicitVarSizeWithMarker_Values[q18], - s_ExplicitVarSizeWithFlags_Values[q17] / s_ExplicitVarSizeWithMarker_Values[q18]; - int(1..4)]) - = conjure_aux1 - | q17 : int(1..4), q18 : int(1..4)]), - sum([toInt(and([s_ExplicitVarSizeWithFlags_Flags[q17], q18 <= s_ExplicitVarSizeWithMarker_Marker, - s_ExplicitVarSizeWithFlags_Values[q17] != s_ExplicitVarSizeWithMarker_Values[q18], - allDiff([s_ExplicitVarSizeWithFlags_Values[q17] + s_ExplicitVarSizeWithMarker_Values[q18], - s_ExplicitVarSizeWithFlags_Values[q17] * s_ExplicitVarSizeWithMarker_Values[q18], - s_ExplicitVarSizeWithFlags_Values[q17] / s_ExplicitVarSizeWithMarker_Values[q18]; - int(1..3)]), - (s_ExplicitVarSizeWithFlags_Values[q17] - s_ExplicitVarSizeWithMarker_Values[q18]) % 2 = 0; - int(1..5)])) - | q17 : int(1..4), q18 : int(1..4)]) - = 0 - -> conjure_aux1 = -16, - x = conjure_aux1, - sum([toInt(and([s_ExplicitVarSizeWithFlags_Flags[q17], q18 <= s_ExplicitVarSizeWithMarker_Marker, - s_ExplicitVarSizeWithFlags_Values[q17] != s_ExplicitVarSizeWithMarker_Values[q18], - allDiff([s_ExplicitVarSizeWithFlags_Values[q17] + s_ExplicitVarSizeWithMarker_Values[q18], - s_ExplicitVarSizeWithFlags_Values[q17] * s_ExplicitVarSizeWithMarker_Values[q18], - s_ExplicitVarSizeWithFlags_Values[q17] / s_ExplicitVarSizeWithMarker_Values[q18]; - int(1..3)]), - (s_ExplicitVarSizeWithFlags_Values[q17] - s_ExplicitVarSizeWithMarker_Values[q18]) % 2 = 0; - int(1..5)])) - | q17 : int(1..4), q18 : int(1..4)]) - > 0, - and([s_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - s_ExplicitVarSizeWithFlags_Values[q1] < s_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..3)]), - and([s_ExplicitVarSizeWithFlags_Flags[q2] = false -> s_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..4)]), - and([s_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> s_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), - and([q6 + 1 <= s_ExplicitVarSizeWithMarker_Marker -> - s_ExplicitVarSizeWithMarker_Values[q6] < s_ExplicitVarSizeWithMarker_Values[q6 + 1] - | q6 : int(1..3)]), - and([q7 > s_ExplicitVarSizeWithMarker_Marker -> s_ExplicitVarSizeWithMarker_Values[q7] = 1 | q7 : int(1..4)]), - and([q10 <= s_ExplicitVarSizeWithMarker_Marker -> - or([s_ExplicitVarSizeWithFlags_Flags[q12] /\ - s_ExplicitVarSizeWithFlags_Values[q12] = s_ExplicitVarSizeWithMarker_Values[q10] - | q12 : int(1..4)]) - | q10 : int(1..4)]), - and([s_ExplicitVarSizeWithFlags_Flags[q14] -> - or([q16 <= s_ExplicitVarSizeWithMarker_Marker /\ - s_ExplicitVarSizeWithMarker_Values[q16] = s_ExplicitVarSizeWithFlags_Values[q14] - | q16 : int(1..4)]) - | q14 : int(1..4)]) - diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_3_4-solution000001.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_3_4-solution000001.solution deleted file mode 100644 index 8b4ecbb66d..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_4_3_4-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 3} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_3_4-solution000002.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_3_4-solution000002.solution deleted file mode 100644 index 159a613983..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_4_3_4-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {2, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_3_4-solution000003.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_3_4-solution000003.solution deleted file mode 100644 index 5963aac565..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_4_3_4-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 3} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_3_4-solution000004.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_3_4-solution000004.solution deleted file mode 100644 index 6eeacc9727..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_4_3_4-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_3_4-solution000005.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_3_4-solution000005.solution deleted file mode 100644 index 560dd0f2f7..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_4_3_4-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 3, 4} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_3_4-solution000006.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_3_4-solution000006.solution deleted file mode 100644 index 40f3fd5c8f..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_4_3_4-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {2, 3, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_3_4-solution000007.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_3_4-solution000007.solution deleted file mode 100644 index bd956f44e3..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_4_3_4-solution000007.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 3, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_3_4.eprime b/tests/exhaustive/basic/comprehension_letting/expected/model_4_3_4.eprime deleted file mode 100644 index 0a99214fbe..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_4_3_4.eprime +++ /dev/null @@ -1,98 +0,0 @@ -language ESSENCE' 1.0 - -find s_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find s_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -find s_ExplicitVarSizeWithMarker_Marker: int(0..4) -find s_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -letting let1 be -100 -find x: int(-100..100) -find conjure_aux1: int(-16..3) -branching on - [s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithMarker_Values, s_ExplicitVarSizeWithFlags_Flags, - s_ExplicitVarSizeWithFlags_Values, x] -such that - and([and([s_ExplicitVarSizeWithFlags_Flags[q17], q18 <= s_ExplicitVarSizeWithMarker_Marker, - s_ExplicitVarSizeWithFlags_Values[q17] != s_ExplicitVarSizeWithMarker_Values[q18], - allDiff([s_ExplicitVarSizeWithFlags_Values[q17] + s_ExplicitVarSizeWithMarker_Values[q18], - s_ExplicitVarSizeWithFlags_Values[q17] * s_ExplicitVarSizeWithMarker_Values[q18], - s_ExplicitVarSizeWithFlags_Values[q17] / s_ExplicitVarSizeWithMarker_Values[q18]; - int(1..3)]), - (s_ExplicitVarSizeWithFlags_Values[q17] - s_ExplicitVarSizeWithMarker_Values[q18]) % 2 = 0; - int(1..5)]) - -> - min([s_ExplicitVarSizeWithFlags_Values[q17] + s_ExplicitVarSizeWithMarker_Values[q18], - s_ExplicitVarSizeWithFlags_Values[q17] - s_ExplicitVarSizeWithMarker_Values[q18], - s_ExplicitVarSizeWithFlags_Values[q17] * s_ExplicitVarSizeWithMarker_Values[q18], - s_ExplicitVarSizeWithFlags_Values[q17] / s_ExplicitVarSizeWithMarker_Values[q18]; - int(1..4)]) - <= conjure_aux1 - | q17 : int(1..4), q18 : int(1..4)]), - sum([toInt(and([s_ExplicitVarSizeWithFlags_Flags[q17], q18 <= s_ExplicitVarSizeWithMarker_Marker, - s_ExplicitVarSizeWithFlags_Values[q17] != s_ExplicitVarSizeWithMarker_Values[q18], - allDiff([s_ExplicitVarSizeWithFlags_Values[q17] + s_ExplicitVarSizeWithMarker_Values[q18], - s_ExplicitVarSizeWithFlags_Values[q17] * s_ExplicitVarSizeWithMarker_Values[q18], - s_ExplicitVarSizeWithFlags_Values[q17] / s_ExplicitVarSizeWithMarker_Values[q18]; - int(1..3)]), - (s_ExplicitVarSizeWithFlags_Values[q17] - s_ExplicitVarSizeWithMarker_Values[q18]) % 2 = 0; - int(1..5)])) - | q17 : int(1..4), q18 : int(1..4)]) - > 0 - -> - or([and([s_ExplicitVarSizeWithFlags_Flags[q17], q18 <= s_ExplicitVarSizeWithMarker_Marker, - s_ExplicitVarSizeWithFlags_Values[q17] != s_ExplicitVarSizeWithMarker_Values[q18], - allDiff([s_ExplicitVarSizeWithFlags_Values[q17] + s_ExplicitVarSizeWithMarker_Values[q18], - s_ExplicitVarSizeWithFlags_Values[q17] * s_ExplicitVarSizeWithMarker_Values[q18], - s_ExplicitVarSizeWithFlags_Values[q17] / s_ExplicitVarSizeWithMarker_Values[q18]; - int(1..3)]), - (s_ExplicitVarSizeWithFlags_Values[q17] - s_ExplicitVarSizeWithMarker_Values[q18]) % 2 = 0; - int(1..5)]) - /\ - min([s_ExplicitVarSizeWithFlags_Values[q17] + s_ExplicitVarSizeWithMarker_Values[q18], - s_ExplicitVarSizeWithFlags_Values[q17] - s_ExplicitVarSizeWithMarker_Values[q18], - s_ExplicitVarSizeWithFlags_Values[q17] * s_ExplicitVarSizeWithMarker_Values[q18], - s_ExplicitVarSizeWithFlags_Values[q17] / s_ExplicitVarSizeWithMarker_Values[q18]; - int(1..4)]) - = conjure_aux1 - | q17 : int(1..4), q18 : int(1..4)]), - sum([toInt(and([s_ExplicitVarSizeWithFlags_Flags[q17], q18 <= s_ExplicitVarSizeWithMarker_Marker, - s_ExplicitVarSizeWithFlags_Values[q17] != s_ExplicitVarSizeWithMarker_Values[q18], - allDiff([s_ExplicitVarSizeWithFlags_Values[q17] + s_ExplicitVarSizeWithMarker_Values[q18], - s_ExplicitVarSizeWithFlags_Values[q17] * s_ExplicitVarSizeWithMarker_Values[q18], - s_ExplicitVarSizeWithFlags_Values[q17] / s_ExplicitVarSizeWithMarker_Values[q18]; - int(1..3)]), - (s_ExplicitVarSizeWithFlags_Values[q17] - s_ExplicitVarSizeWithMarker_Values[q18]) % 2 = 0; - int(1..5)])) - | q17 : int(1..4), q18 : int(1..4)]) - = 0 - -> conjure_aux1 = -16, - x = conjure_aux1, - sum([toInt(and([s_ExplicitVarSizeWithFlags_Flags[q17], q18 <= s_ExplicitVarSizeWithMarker_Marker, - s_ExplicitVarSizeWithFlags_Values[q17] != s_ExplicitVarSizeWithMarker_Values[q18], - allDiff([s_ExplicitVarSizeWithFlags_Values[q17] + s_ExplicitVarSizeWithMarker_Values[q18], - s_ExplicitVarSizeWithFlags_Values[q17] * s_ExplicitVarSizeWithMarker_Values[q18], - s_ExplicitVarSizeWithFlags_Values[q17] / s_ExplicitVarSizeWithMarker_Values[q18]; - int(1..3)]), - (s_ExplicitVarSizeWithFlags_Values[q17] - s_ExplicitVarSizeWithMarker_Values[q18]) % 2 = 0; - int(1..5)])) - | q17 : int(1..4), q18 : int(1..4)]) - > 0, - and([s_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - s_ExplicitVarSizeWithFlags_Values[q1] < s_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..3)]), - and([s_ExplicitVarSizeWithFlags_Flags[q2] = false -> s_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..4)]), - and([s_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> s_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), - and([q6 + 1 <= s_ExplicitVarSizeWithMarker_Marker -> - s_ExplicitVarSizeWithMarker_Values[q6] < s_ExplicitVarSizeWithMarker_Values[q6 + 1] - | q6 : int(1..3)]), - and([q7 > s_ExplicitVarSizeWithMarker_Marker -> s_ExplicitVarSizeWithMarker_Values[q7] = 1 | q7 : int(1..4)]), - and([q10 <= s_ExplicitVarSizeWithMarker_Marker -> - or([s_ExplicitVarSizeWithFlags_Flags[q12] /\ - s_ExplicitVarSizeWithFlags_Values[q12] = s_ExplicitVarSizeWithMarker_Values[q10] - | q12 : int(1..4)]) - | q10 : int(1..4)]), - and([s_ExplicitVarSizeWithFlags_Flags[q14] -> - or([q16 <= s_ExplicitVarSizeWithMarker_Marker /\ - s_ExplicitVarSizeWithMarker_Values[q16] = s_ExplicitVarSizeWithFlags_Values[q14] - | q16 : int(1..4)]) - | q14 : int(1..4)]) - diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_1-solution000001.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_1-solution000001.solution deleted file mode 100644 index 159a613983..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {2, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_1-solution000002.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_1-solution000002.solution deleted file mode 100644 index 40f3fd5c8f..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {2, 3, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_1-solution000003.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_1-solution000003.solution deleted file mode 100644 index 8b4ecbb66d..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_1-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 3} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_1-solution000004.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_1-solution000004.solution deleted file mode 100644 index 560dd0f2f7..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_1-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 3, 4} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_1-solution000005.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_1-solution000005.solution deleted file mode 100644 index 6eeacc9727..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_1-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_1-solution000006.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_1-solution000006.solution deleted file mode 100644 index 5963aac565..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_1-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 3} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_1-solution000007.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_1-solution000007.solution deleted file mode 100644 index bd956f44e3..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_1-solution000007.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 3, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_1.eprime b/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_1.eprime deleted file mode 100644 index f39e4e0ee6..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_1.eprime +++ /dev/null @@ -1,86 +0,0 @@ -language ESSENCE' 1.0 - -find s_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find s_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -find s_Occurrence: matrix indexed by [int(1..4)] of bool -letting let1 be -100 -find x: int(-100..100) -find conjure_aux1: int(-16..3) -branching on [s_Occurrence, s_ExplicitVarSizeWithFlags_Flags, s_ExplicitVarSizeWithFlags_Values, x] -such that - and([and([s_ExplicitVarSizeWithFlags_Flags[q12], s_ExplicitVarSizeWithFlags_Flags[q13], - s_ExplicitVarSizeWithFlags_Values[q12] != s_ExplicitVarSizeWithFlags_Values[q13], - allDiff([s_ExplicitVarSizeWithFlags_Values[q12] + s_ExplicitVarSizeWithFlags_Values[q13], - s_ExplicitVarSizeWithFlags_Values[q12] * s_ExplicitVarSizeWithFlags_Values[q13], - s_ExplicitVarSizeWithFlags_Values[q12] / s_ExplicitVarSizeWithFlags_Values[q13]; - int(1..3)]), - (s_ExplicitVarSizeWithFlags_Values[q12] - s_ExplicitVarSizeWithFlags_Values[q13]) % 2 = 0; - int(1..5)]) - -> - min([s_ExplicitVarSizeWithFlags_Values[q12] + s_ExplicitVarSizeWithFlags_Values[q13], - s_ExplicitVarSizeWithFlags_Values[q12] - s_ExplicitVarSizeWithFlags_Values[q13], - s_ExplicitVarSizeWithFlags_Values[q12] * s_ExplicitVarSizeWithFlags_Values[q13], - s_ExplicitVarSizeWithFlags_Values[q12] / s_ExplicitVarSizeWithFlags_Values[q13]; - int(1..4)]) - <= conjure_aux1 - | q12 : int(1..4), q13 : int(1..4)]), - sum([toInt(and([s_ExplicitVarSizeWithFlags_Flags[q12], s_ExplicitVarSizeWithFlags_Flags[q13], - s_ExplicitVarSizeWithFlags_Values[q12] != s_ExplicitVarSizeWithFlags_Values[q13], - allDiff([s_ExplicitVarSizeWithFlags_Values[q12] + s_ExplicitVarSizeWithFlags_Values[q13], - s_ExplicitVarSizeWithFlags_Values[q12] * s_ExplicitVarSizeWithFlags_Values[q13], - s_ExplicitVarSizeWithFlags_Values[q12] / s_ExplicitVarSizeWithFlags_Values[q13]; - int(1..3)]), - (s_ExplicitVarSizeWithFlags_Values[q12] - s_ExplicitVarSizeWithFlags_Values[q13]) % 2 = 0; - int(1..5)])) - | q12 : int(1..4), q13 : int(1..4)]) - > 0 - -> - or([and([s_ExplicitVarSizeWithFlags_Flags[q12], s_ExplicitVarSizeWithFlags_Flags[q13], - s_ExplicitVarSizeWithFlags_Values[q12] != s_ExplicitVarSizeWithFlags_Values[q13], - allDiff([s_ExplicitVarSizeWithFlags_Values[q12] + s_ExplicitVarSizeWithFlags_Values[q13], - s_ExplicitVarSizeWithFlags_Values[q12] * s_ExplicitVarSizeWithFlags_Values[q13], - s_ExplicitVarSizeWithFlags_Values[q12] / s_ExplicitVarSizeWithFlags_Values[q13]; - int(1..3)]), - (s_ExplicitVarSizeWithFlags_Values[q12] - s_ExplicitVarSizeWithFlags_Values[q13]) % 2 = 0; - int(1..5)]) - /\ - min([s_ExplicitVarSizeWithFlags_Values[q12] + s_ExplicitVarSizeWithFlags_Values[q13], - s_ExplicitVarSizeWithFlags_Values[q12] - s_ExplicitVarSizeWithFlags_Values[q13], - s_ExplicitVarSizeWithFlags_Values[q12] * s_ExplicitVarSizeWithFlags_Values[q13], - s_ExplicitVarSizeWithFlags_Values[q12] / s_ExplicitVarSizeWithFlags_Values[q13]; - int(1..4)]) - = conjure_aux1 - | q12 : int(1..4), q13 : int(1..4)]), - sum([toInt(and([s_ExplicitVarSizeWithFlags_Flags[q12], s_ExplicitVarSizeWithFlags_Flags[q13], - s_ExplicitVarSizeWithFlags_Values[q12] != s_ExplicitVarSizeWithFlags_Values[q13], - allDiff([s_ExplicitVarSizeWithFlags_Values[q12] + s_ExplicitVarSizeWithFlags_Values[q13], - s_ExplicitVarSizeWithFlags_Values[q12] * s_ExplicitVarSizeWithFlags_Values[q13], - s_ExplicitVarSizeWithFlags_Values[q12] / s_ExplicitVarSizeWithFlags_Values[q13]; - int(1..3)]), - (s_ExplicitVarSizeWithFlags_Values[q12] - s_ExplicitVarSizeWithFlags_Values[q13]) % 2 = 0; - int(1..5)])) - | q12 : int(1..4), q13 : int(1..4)]) - = 0 - -> conjure_aux1 = -16, - x = conjure_aux1, - sum([toInt(and([s_ExplicitVarSizeWithFlags_Flags[q12], s_ExplicitVarSizeWithFlags_Flags[q13], - s_ExplicitVarSizeWithFlags_Values[q12] != s_ExplicitVarSizeWithFlags_Values[q13], - allDiff([s_ExplicitVarSizeWithFlags_Values[q12] + s_ExplicitVarSizeWithFlags_Values[q13], - s_ExplicitVarSizeWithFlags_Values[q12] * s_ExplicitVarSizeWithFlags_Values[q13], - s_ExplicitVarSizeWithFlags_Values[q12] / s_ExplicitVarSizeWithFlags_Values[q13]; - int(1..3)]), - (s_ExplicitVarSizeWithFlags_Values[q12] - s_ExplicitVarSizeWithFlags_Values[q13]) % 2 = 0; - int(1..5)])) - | q12 : int(1..4), q13 : int(1..4)]) - > 0, - and([s_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - s_ExplicitVarSizeWithFlags_Values[q1] < s_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..3)]), - and([s_ExplicitVarSizeWithFlags_Flags[q2] = false -> s_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..4)]), - and([s_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> s_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), - and([s_Occurrence[q7] -> - or([s_ExplicitVarSizeWithFlags_Flags[q9] /\ s_ExplicitVarSizeWithFlags_Values[q9] = q7 | q9 : int(1..4)]) - | q7 : int(1..4)]), - and([s_ExplicitVarSizeWithFlags_Flags[q11] -> s_Occurrence[s_ExplicitVarSizeWithFlags_Values[q11]] - | q11 : int(1..4)]) - diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_2-solution000001.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_2-solution000001.solution deleted file mode 100644 index bd956f44e3..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 3, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_2-solution000002.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_2-solution000002.solution deleted file mode 100644 index 5963aac565..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 3} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_2-solution000003.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_2-solution000003.solution deleted file mode 100644 index 6eeacc9727..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_2-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_2-solution000004.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_2-solution000004.solution deleted file mode 100644 index 560dd0f2f7..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_2-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 3, 4} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_2-solution000005.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_2-solution000005.solution deleted file mode 100644 index 8b4ecbb66d..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_2-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 3} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_2-solution000006.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_2-solution000006.solution deleted file mode 100644 index 40f3fd5c8f..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_2-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {2, 3, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_2-solution000007.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_2-solution000007.solution deleted file mode 100644 index 159a613983..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_2-solution000007.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {2, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_2.eprime b/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_2.eprime deleted file mode 100644 index 7af3076aa8..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_2.eprime +++ /dev/null @@ -1,94 +0,0 @@ -language ESSENCE' 1.0 - -find s_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find s_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -find s_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -letting let1 be -100 -find x: int(-100..100) -find conjure_aux1: int(-16..3) -branching on [s_ExplicitVarSizeWithDummy, s_ExplicitVarSizeWithFlags_Flags, s_ExplicitVarSizeWithFlags_Values, x] -such that - and([and([s_ExplicitVarSizeWithFlags_Flags[q18], s_ExplicitVarSizeWithFlags_Flags[q19], - s_ExplicitVarSizeWithFlags_Values[q18] != s_ExplicitVarSizeWithFlags_Values[q19], - allDiff([s_ExplicitVarSizeWithFlags_Values[q18] + s_ExplicitVarSizeWithFlags_Values[q19], - s_ExplicitVarSizeWithFlags_Values[q18] * s_ExplicitVarSizeWithFlags_Values[q19], - s_ExplicitVarSizeWithFlags_Values[q18] / s_ExplicitVarSizeWithFlags_Values[q19]; - int(1..3)]), - (s_ExplicitVarSizeWithFlags_Values[q18] - s_ExplicitVarSizeWithFlags_Values[q19]) % 2 = 0; - int(1..5)]) - -> - min([s_ExplicitVarSizeWithFlags_Values[q18] + s_ExplicitVarSizeWithFlags_Values[q19], - s_ExplicitVarSizeWithFlags_Values[q18] - s_ExplicitVarSizeWithFlags_Values[q19], - s_ExplicitVarSizeWithFlags_Values[q18] * s_ExplicitVarSizeWithFlags_Values[q19], - s_ExplicitVarSizeWithFlags_Values[q18] / s_ExplicitVarSizeWithFlags_Values[q19]; - int(1..4)]) - <= conjure_aux1 - | q18 : int(1..4), q19 : int(1..4)]), - sum([toInt(and([s_ExplicitVarSizeWithFlags_Flags[q18], s_ExplicitVarSizeWithFlags_Flags[q19], - s_ExplicitVarSizeWithFlags_Values[q18] != s_ExplicitVarSizeWithFlags_Values[q19], - allDiff([s_ExplicitVarSizeWithFlags_Values[q18] + s_ExplicitVarSizeWithFlags_Values[q19], - s_ExplicitVarSizeWithFlags_Values[q18] * s_ExplicitVarSizeWithFlags_Values[q19], - s_ExplicitVarSizeWithFlags_Values[q18] / s_ExplicitVarSizeWithFlags_Values[q19]; - int(1..3)]), - (s_ExplicitVarSizeWithFlags_Values[q18] - s_ExplicitVarSizeWithFlags_Values[q19]) % 2 = 0; - int(1..5)])) - | q18 : int(1..4), q19 : int(1..4)]) - > 0 - -> - or([and([s_ExplicitVarSizeWithFlags_Flags[q18], s_ExplicitVarSizeWithFlags_Flags[q19], - s_ExplicitVarSizeWithFlags_Values[q18] != s_ExplicitVarSizeWithFlags_Values[q19], - allDiff([s_ExplicitVarSizeWithFlags_Values[q18] + s_ExplicitVarSizeWithFlags_Values[q19], - s_ExplicitVarSizeWithFlags_Values[q18] * s_ExplicitVarSizeWithFlags_Values[q19], - s_ExplicitVarSizeWithFlags_Values[q18] / s_ExplicitVarSizeWithFlags_Values[q19]; - int(1..3)]), - (s_ExplicitVarSizeWithFlags_Values[q18] - s_ExplicitVarSizeWithFlags_Values[q19]) % 2 = 0; - int(1..5)]) - /\ - min([s_ExplicitVarSizeWithFlags_Values[q18] + s_ExplicitVarSizeWithFlags_Values[q19], - s_ExplicitVarSizeWithFlags_Values[q18] - s_ExplicitVarSizeWithFlags_Values[q19], - s_ExplicitVarSizeWithFlags_Values[q18] * s_ExplicitVarSizeWithFlags_Values[q19], - s_ExplicitVarSizeWithFlags_Values[q18] / s_ExplicitVarSizeWithFlags_Values[q19]; - int(1..4)]) - = conjure_aux1 - | q18 : int(1..4), q19 : int(1..4)]), - sum([toInt(and([s_ExplicitVarSizeWithFlags_Flags[q18], s_ExplicitVarSizeWithFlags_Flags[q19], - s_ExplicitVarSizeWithFlags_Values[q18] != s_ExplicitVarSizeWithFlags_Values[q19], - allDiff([s_ExplicitVarSizeWithFlags_Values[q18] + s_ExplicitVarSizeWithFlags_Values[q19], - s_ExplicitVarSizeWithFlags_Values[q18] * s_ExplicitVarSizeWithFlags_Values[q19], - s_ExplicitVarSizeWithFlags_Values[q18] / s_ExplicitVarSizeWithFlags_Values[q19]; - int(1..3)]), - (s_ExplicitVarSizeWithFlags_Values[q18] - s_ExplicitVarSizeWithFlags_Values[q19]) % 2 = 0; - int(1..5)])) - | q18 : int(1..4), q19 : int(1..4)]) - = 0 - -> conjure_aux1 = -16, - x = conjure_aux1, - sum([toInt(and([s_ExplicitVarSizeWithFlags_Flags[q18], s_ExplicitVarSizeWithFlags_Flags[q19], - s_ExplicitVarSizeWithFlags_Values[q18] != s_ExplicitVarSizeWithFlags_Values[q19], - allDiff([s_ExplicitVarSizeWithFlags_Values[q18] + s_ExplicitVarSizeWithFlags_Values[q19], - s_ExplicitVarSizeWithFlags_Values[q18] * s_ExplicitVarSizeWithFlags_Values[q19], - s_ExplicitVarSizeWithFlags_Values[q18] / s_ExplicitVarSizeWithFlags_Values[q19]; - int(1..3)]), - (s_ExplicitVarSizeWithFlags_Values[q18] - s_ExplicitVarSizeWithFlags_Values[q19]) % 2 = 0; - int(1..5)])) - | q18 : int(1..4), q19 : int(1..4)]) - > 0, - and([s_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - s_ExplicitVarSizeWithFlags_Values[q1] < s_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..3)]), - and([s_ExplicitVarSizeWithFlags_Flags[q2] = false -> s_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..4)]), - and([s_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> s_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), - and([s_ExplicitVarSizeWithDummy[q6] < s_ExplicitVarSizeWithDummy[q6 + 1] \/ s_ExplicitVarSizeWithDummy[q6] = 5 - | q6 : int(1..3)]), - and([s_ExplicitVarSizeWithDummy[q7] = 5 -> s_ExplicitVarSizeWithDummy[q7 + 1] = 5 | q7 : int(1..3)]), - and([s_ExplicitVarSizeWithDummy[q11] != 5 -> - or([s_ExplicitVarSizeWithFlags_Flags[q13] /\ - s_ExplicitVarSizeWithFlags_Values[q13] = s_ExplicitVarSizeWithDummy[q11] - | q13 : int(1..4)]) - | q11 : int(1..4)]), - and([s_ExplicitVarSizeWithFlags_Flags[q15] -> - or([s_ExplicitVarSizeWithDummy[q17] != 5 /\ - s_ExplicitVarSizeWithDummy[q17] = s_ExplicitVarSizeWithFlags_Values[q15] - | q17 : int(1..4)]) - | q15 : int(1..4)]) - diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_3-solution000001.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_3-solution000001.solution deleted file mode 100644 index 8b4ecbb66d..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_3-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 3} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_3-solution000002.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_3-solution000002.solution deleted file mode 100644 index 159a613983..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_3-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {2, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_3-solution000003.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_3-solution000003.solution deleted file mode 100644 index 5963aac565..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_3-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 3} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_3-solution000004.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_3-solution000004.solution deleted file mode 100644 index 6eeacc9727..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_3-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_3-solution000005.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_3-solution000005.solution deleted file mode 100644 index 560dd0f2f7..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_3-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 3, 4} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_3-solution000006.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_3-solution000006.solution deleted file mode 100644 index 40f3fd5c8f..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_3-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {2, 3, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_3-solution000007.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_3-solution000007.solution deleted file mode 100644 index bd956f44e3..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_3-solution000007.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 3, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_3.eprime b/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_3.eprime deleted file mode 100644 index 5854a1dbb6..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_3.eprime +++ /dev/null @@ -1,98 +0,0 @@ -language ESSENCE' 1.0 - -find s_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find s_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -find s_ExplicitVarSizeWithMarker_Marker: int(0..4) -find s_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -letting let1 be -100 -find x: int(-100..100) -find conjure_aux1: int(-16..3) -branching on - [s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithMarker_Values, s_ExplicitVarSizeWithFlags_Flags, - s_ExplicitVarSizeWithFlags_Values, x] -such that - and([and([s_ExplicitVarSizeWithFlags_Flags[q17], s_ExplicitVarSizeWithFlags_Flags[q18], - s_ExplicitVarSizeWithFlags_Values[q17] != s_ExplicitVarSizeWithFlags_Values[q18], - allDiff([s_ExplicitVarSizeWithFlags_Values[q17] + s_ExplicitVarSizeWithFlags_Values[q18], - s_ExplicitVarSizeWithFlags_Values[q17] * s_ExplicitVarSizeWithFlags_Values[q18], - s_ExplicitVarSizeWithFlags_Values[q17] / s_ExplicitVarSizeWithFlags_Values[q18]; - int(1..3)]), - (s_ExplicitVarSizeWithFlags_Values[q17] - s_ExplicitVarSizeWithFlags_Values[q18]) % 2 = 0; - int(1..5)]) - -> - min([s_ExplicitVarSizeWithFlags_Values[q17] + s_ExplicitVarSizeWithFlags_Values[q18], - s_ExplicitVarSizeWithFlags_Values[q17] - s_ExplicitVarSizeWithFlags_Values[q18], - s_ExplicitVarSizeWithFlags_Values[q17] * s_ExplicitVarSizeWithFlags_Values[q18], - s_ExplicitVarSizeWithFlags_Values[q17] / s_ExplicitVarSizeWithFlags_Values[q18]; - int(1..4)]) - <= conjure_aux1 - | q17 : int(1..4), q18 : int(1..4)]), - sum([toInt(and([s_ExplicitVarSizeWithFlags_Flags[q17], s_ExplicitVarSizeWithFlags_Flags[q18], - s_ExplicitVarSizeWithFlags_Values[q17] != s_ExplicitVarSizeWithFlags_Values[q18], - allDiff([s_ExplicitVarSizeWithFlags_Values[q17] + s_ExplicitVarSizeWithFlags_Values[q18], - s_ExplicitVarSizeWithFlags_Values[q17] * s_ExplicitVarSizeWithFlags_Values[q18], - s_ExplicitVarSizeWithFlags_Values[q17] / s_ExplicitVarSizeWithFlags_Values[q18]; - int(1..3)]), - (s_ExplicitVarSizeWithFlags_Values[q17] - s_ExplicitVarSizeWithFlags_Values[q18]) % 2 = 0; - int(1..5)])) - | q17 : int(1..4), q18 : int(1..4)]) - > 0 - -> - or([and([s_ExplicitVarSizeWithFlags_Flags[q17], s_ExplicitVarSizeWithFlags_Flags[q18], - s_ExplicitVarSizeWithFlags_Values[q17] != s_ExplicitVarSizeWithFlags_Values[q18], - allDiff([s_ExplicitVarSizeWithFlags_Values[q17] + s_ExplicitVarSizeWithFlags_Values[q18], - s_ExplicitVarSizeWithFlags_Values[q17] * s_ExplicitVarSizeWithFlags_Values[q18], - s_ExplicitVarSizeWithFlags_Values[q17] / s_ExplicitVarSizeWithFlags_Values[q18]; - int(1..3)]), - (s_ExplicitVarSizeWithFlags_Values[q17] - s_ExplicitVarSizeWithFlags_Values[q18]) % 2 = 0; - int(1..5)]) - /\ - min([s_ExplicitVarSizeWithFlags_Values[q17] + s_ExplicitVarSizeWithFlags_Values[q18], - s_ExplicitVarSizeWithFlags_Values[q17] - s_ExplicitVarSizeWithFlags_Values[q18], - s_ExplicitVarSizeWithFlags_Values[q17] * s_ExplicitVarSizeWithFlags_Values[q18], - s_ExplicitVarSizeWithFlags_Values[q17] / s_ExplicitVarSizeWithFlags_Values[q18]; - int(1..4)]) - = conjure_aux1 - | q17 : int(1..4), q18 : int(1..4)]), - sum([toInt(and([s_ExplicitVarSizeWithFlags_Flags[q17], s_ExplicitVarSizeWithFlags_Flags[q18], - s_ExplicitVarSizeWithFlags_Values[q17] != s_ExplicitVarSizeWithFlags_Values[q18], - allDiff([s_ExplicitVarSizeWithFlags_Values[q17] + s_ExplicitVarSizeWithFlags_Values[q18], - s_ExplicitVarSizeWithFlags_Values[q17] * s_ExplicitVarSizeWithFlags_Values[q18], - s_ExplicitVarSizeWithFlags_Values[q17] / s_ExplicitVarSizeWithFlags_Values[q18]; - int(1..3)]), - (s_ExplicitVarSizeWithFlags_Values[q17] - s_ExplicitVarSizeWithFlags_Values[q18]) % 2 = 0; - int(1..5)])) - | q17 : int(1..4), q18 : int(1..4)]) - = 0 - -> conjure_aux1 = -16, - x = conjure_aux1, - sum([toInt(and([s_ExplicitVarSizeWithFlags_Flags[q17], s_ExplicitVarSizeWithFlags_Flags[q18], - s_ExplicitVarSizeWithFlags_Values[q17] != s_ExplicitVarSizeWithFlags_Values[q18], - allDiff([s_ExplicitVarSizeWithFlags_Values[q17] + s_ExplicitVarSizeWithFlags_Values[q18], - s_ExplicitVarSizeWithFlags_Values[q17] * s_ExplicitVarSizeWithFlags_Values[q18], - s_ExplicitVarSizeWithFlags_Values[q17] / s_ExplicitVarSizeWithFlags_Values[q18]; - int(1..3)]), - (s_ExplicitVarSizeWithFlags_Values[q17] - s_ExplicitVarSizeWithFlags_Values[q18]) % 2 = 0; - int(1..5)])) - | q17 : int(1..4), q18 : int(1..4)]) - > 0, - and([s_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - s_ExplicitVarSizeWithFlags_Values[q1] < s_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..3)]), - and([s_ExplicitVarSizeWithFlags_Flags[q2] = false -> s_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..4)]), - and([s_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> s_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), - and([q6 + 1 <= s_ExplicitVarSizeWithMarker_Marker -> - s_ExplicitVarSizeWithMarker_Values[q6] < s_ExplicitVarSizeWithMarker_Values[q6 + 1] - | q6 : int(1..3)]), - and([q7 > s_ExplicitVarSizeWithMarker_Marker -> s_ExplicitVarSizeWithMarker_Values[q7] = 1 | q7 : int(1..4)]), - and([q10 <= s_ExplicitVarSizeWithMarker_Marker -> - or([s_ExplicitVarSizeWithFlags_Flags[q12] /\ - s_ExplicitVarSizeWithFlags_Values[q12] = s_ExplicitVarSizeWithMarker_Values[q10] - | q12 : int(1..4)]) - | q10 : int(1..4)]), - and([s_ExplicitVarSizeWithFlags_Flags[q14] -> - or([q16 <= s_ExplicitVarSizeWithMarker_Marker /\ - s_ExplicitVarSizeWithMarker_Values[q16] = s_ExplicitVarSizeWithFlags_Values[q14] - | q16 : int(1..4)]) - | q14 : int(1..4)]) - diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_4-solution000001.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_4-solution000001.solution deleted file mode 100644 index 8b4ecbb66d..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_4-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 3} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_4-solution000002.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_4-solution000002.solution deleted file mode 100644 index 159a613983..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_4-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {2, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_4-solution000003.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_4-solution000003.solution deleted file mode 100644 index 5963aac565..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_4-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 3} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_4-solution000004.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_4-solution000004.solution deleted file mode 100644 index 6eeacc9727..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_4-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_4-solution000005.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_4-solution000005.solution deleted file mode 100644 index 560dd0f2f7..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_4-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 3, 4} -letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_4-solution000006.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_4-solution000006.solution deleted file mode 100644 index 40f3fd5c8f..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_4-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {2, 3, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_4-solution000007.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_4-solution000007.solution deleted file mode 100644 index bd956f44e3..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_4-solution000007.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2, 3, 4} -letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_4.eprime b/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_4.eprime deleted file mode 100644 index bf58b8c524..0000000000 --- a/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_4.eprime +++ /dev/null @@ -1,80 +0,0 @@ -language ESSENCE' 1.0 - -find s_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find s_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -letting let1 be -100 -find x: int(-100..100) -find conjure_aux1: int(-16..3) -branching on [s_ExplicitVarSizeWithFlags_Flags, s_ExplicitVarSizeWithFlags_Values, x] -such that - and([and([s_ExplicitVarSizeWithFlags_Flags[q6], s_ExplicitVarSizeWithFlags_Flags[q7], - s_ExplicitVarSizeWithFlags_Values[q6] != s_ExplicitVarSizeWithFlags_Values[q7], - allDiff([s_ExplicitVarSizeWithFlags_Values[q6] + s_ExplicitVarSizeWithFlags_Values[q7], - s_ExplicitVarSizeWithFlags_Values[q6] * s_ExplicitVarSizeWithFlags_Values[q7], - s_ExplicitVarSizeWithFlags_Values[q6] / s_ExplicitVarSizeWithFlags_Values[q7]; - int(1..3)]), - (s_ExplicitVarSizeWithFlags_Values[q6] - s_ExplicitVarSizeWithFlags_Values[q7]) % 2 = 0; - int(1..5)]) - -> - min([s_ExplicitVarSizeWithFlags_Values[q6] + s_ExplicitVarSizeWithFlags_Values[q7], - s_ExplicitVarSizeWithFlags_Values[q6] - s_ExplicitVarSizeWithFlags_Values[q7], - s_ExplicitVarSizeWithFlags_Values[q6] * s_ExplicitVarSizeWithFlags_Values[q7], - s_ExplicitVarSizeWithFlags_Values[q6] / s_ExplicitVarSizeWithFlags_Values[q7]; - int(1..4)]) - <= conjure_aux1 - | q6 : int(1..4), q7 : int(1..4)]), - sum([toInt(and([s_ExplicitVarSizeWithFlags_Flags[q6], s_ExplicitVarSizeWithFlags_Flags[q7], - s_ExplicitVarSizeWithFlags_Values[q6] != s_ExplicitVarSizeWithFlags_Values[q7], - allDiff([s_ExplicitVarSizeWithFlags_Values[q6] + s_ExplicitVarSizeWithFlags_Values[q7], - s_ExplicitVarSizeWithFlags_Values[q6] * s_ExplicitVarSizeWithFlags_Values[q7], - s_ExplicitVarSizeWithFlags_Values[q6] / s_ExplicitVarSizeWithFlags_Values[q7]; - int(1..3)]), - (s_ExplicitVarSizeWithFlags_Values[q6] - s_ExplicitVarSizeWithFlags_Values[q7]) % 2 = 0; - int(1..5)])) - | q6 : int(1..4), q7 : int(1..4)]) - > 0 - -> - or([and([s_ExplicitVarSizeWithFlags_Flags[q6], s_ExplicitVarSizeWithFlags_Flags[q7], - s_ExplicitVarSizeWithFlags_Values[q6] != s_ExplicitVarSizeWithFlags_Values[q7], - allDiff([s_ExplicitVarSizeWithFlags_Values[q6] + s_ExplicitVarSizeWithFlags_Values[q7], - s_ExplicitVarSizeWithFlags_Values[q6] * s_ExplicitVarSizeWithFlags_Values[q7], - s_ExplicitVarSizeWithFlags_Values[q6] / s_ExplicitVarSizeWithFlags_Values[q7]; - int(1..3)]), - (s_ExplicitVarSizeWithFlags_Values[q6] - s_ExplicitVarSizeWithFlags_Values[q7]) % 2 = 0; - int(1..5)]) - /\ - min([s_ExplicitVarSizeWithFlags_Values[q6] + s_ExplicitVarSizeWithFlags_Values[q7], - s_ExplicitVarSizeWithFlags_Values[q6] - s_ExplicitVarSizeWithFlags_Values[q7], - s_ExplicitVarSizeWithFlags_Values[q6] * s_ExplicitVarSizeWithFlags_Values[q7], - s_ExplicitVarSizeWithFlags_Values[q6] / s_ExplicitVarSizeWithFlags_Values[q7]; - int(1..4)]) - = conjure_aux1 - | q6 : int(1..4), q7 : int(1..4)]), - sum([toInt(and([s_ExplicitVarSizeWithFlags_Flags[q6], s_ExplicitVarSizeWithFlags_Flags[q7], - s_ExplicitVarSizeWithFlags_Values[q6] != s_ExplicitVarSizeWithFlags_Values[q7], - allDiff([s_ExplicitVarSizeWithFlags_Values[q6] + s_ExplicitVarSizeWithFlags_Values[q7], - s_ExplicitVarSizeWithFlags_Values[q6] * s_ExplicitVarSizeWithFlags_Values[q7], - s_ExplicitVarSizeWithFlags_Values[q6] / s_ExplicitVarSizeWithFlags_Values[q7]; - int(1..3)]), - (s_ExplicitVarSizeWithFlags_Values[q6] - s_ExplicitVarSizeWithFlags_Values[q7]) % 2 = 0; - int(1..5)])) - | q6 : int(1..4), q7 : int(1..4)]) - = 0 - -> conjure_aux1 = -16, - x = conjure_aux1, - sum([toInt(and([s_ExplicitVarSizeWithFlags_Flags[q6], s_ExplicitVarSizeWithFlags_Flags[q7], - s_ExplicitVarSizeWithFlags_Values[q6] != s_ExplicitVarSizeWithFlags_Values[q7], - allDiff([s_ExplicitVarSizeWithFlags_Values[q6] + s_ExplicitVarSizeWithFlags_Values[q7], - s_ExplicitVarSizeWithFlags_Values[q6] * s_ExplicitVarSizeWithFlags_Values[q7], - s_ExplicitVarSizeWithFlags_Values[q6] / s_ExplicitVarSizeWithFlags_Values[q7]; - int(1..3)]), - (s_ExplicitVarSizeWithFlags_Values[q6] - s_ExplicitVarSizeWithFlags_Values[q7]) % 2 = 0; - int(1..5)])) - | q6 : int(1..4), q7 : int(1..4)]) - > 0, - and([s_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - s_ExplicitVarSizeWithFlags_Values[q1] < s_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..3)]), - and([s_ExplicitVarSizeWithFlags_Flags[q2] = false -> s_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..4)]), - and([s_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> s_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]) - diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_1_1-solution000001.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_1_1-solution000001.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_1_1_1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_1_1-solution000002.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_1_1-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_1_1_1-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_1_1-solution000003.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_1_1-solution000003.solution deleted file mode 100644 index de5cc861ad..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_1_1_1-solution000003.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_1_1-solution000004.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_1_1-solution000004.solution deleted file mode 100644 index a28b6d6203..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_1_1_1-solution000004.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_1_1-solution000005.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_1_1-solution000005.solution deleted file mode 100644 index 1a734343d9..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_1_1_1-solution000005.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_1_1-solution000006.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_1_1-solution000006.solution deleted file mode 100644 index 86a85825b3..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_1_1_1-solution000006.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_1_1-solution000007.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_1_1-solution000007.solution deleted file mode 100644 index 76bc8cdc32..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_1_1_1-solution000007.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_1_1-solution000008.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_1_1-solution000008.solution deleted file mode 100644 index 8dddb3b359..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_1_1_1-solution000008.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_1_1.eprime b/tests/exhaustive/basic/cut_01_on/expected/model_1_1_1.eprime deleted file mode 100644 index bc8f37139a..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_1_1_1.eprime +++ /dev/null @@ -1,10 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1..3)] of bool -find cut1: bool -find cut2: bool -branching on [cut1, cut2, x_Occurrence] -such that - !cut1 <-> x_Occurrence[1] /\ x_Occurrence[2], - !cut2 <-> x_Occurrence[1] - diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_1_2-solution000001.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_1_2-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_1_1_2-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_1_2-solution000002.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_1_2-solution000002.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_1_1_2-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_1_2-solution000003.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_1_2-solution000003.solution deleted file mode 100644 index a28b6d6203..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_1_1_2-solution000003.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_1_2-solution000004.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_1_2-solution000004.solution deleted file mode 100644 index de5cc861ad..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_1_1_2-solution000004.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_1_2-solution000005.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_1_2-solution000005.solution deleted file mode 100644 index 8dddb3b359..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_1_1_2-solution000005.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_1_2-solution000006.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_1_2-solution000006.solution deleted file mode 100644 index 76bc8cdc32..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_1_1_2-solution000006.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_1_2-solution000007.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_1_2-solution000007.solution deleted file mode 100644 index 86a85825b3..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_1_1_2-solution000007.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_1_2-solution000008.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_1_2-solution000008.solution deleted file mode 100644 index 1a734343d9..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_1_1_2-solution000008.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_1_2.eprime b/tests/exhaustive/basic/cut_01_on/expected/model_1_1_2.eprime deleted file mode 100644 index 8a8719673a..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_1_1_2.eprime +++ /dev/null @@ -1,18 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1..3)] of bool -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..3)] of int(1..4) -find cut1: bool -find cut2: bool -branching on [cut1, cut2, x_ExplicitVarSizeWithDummy, x_Occurrence] -such that - !cut1 <-> x_Occurrence[1] /\ x_Occurrence[2], - !cut2 <-> x_Occurrence[1], - and([x_ExplicitVarSizeWithDummy[q2] < x_ExplicitVarSizeWithDummy[q2 + 1] \/ x_ExplicitVarSizeWithDummy[q2] = 4 - | q2 : int(1..2)]), - and([x_ExplicitVarSizeWithDummy[q3] = 4 -> x_ExplicitVarSizeWithDummy[q3 + 1] = 4 | q3 : int(1..2)]), - and([x_ExplicitVarSizeWithDummy[q7] != 4 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q7]] | q7 : int(1..3)]), - and([x_Occurrence[q8] -> - or([x_ExplicitVarSizeWithDummy[q10] != 4 /\ x_ExplicitVarSizeWithDummy[q10] = q8 | q10 : int(1..3)]) - | q8 : int(1..3)]) - diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_1_3-solution000001.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_1_3-solution000001.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_1_1_3-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_1_3-solution000002.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_1_3-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_1_1_3-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_1_3-solution000003.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_1_3-solution000003.solution deleted file mode 100644 index de5cc861ad..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_1_1_3-solution000003.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_1_3-solution000004.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_1_3-solution000004.solution deleted file mode 100644 index a28b6d6203..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_1_1_3-solution000004.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_1_3-solution000005.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_1_3-solution000005.solution deleted file mode 100644 index 1a734343d9..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_1_1_3-solution000005.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_1_3-solution000006.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_1_3-solution000006.solution deleted file mode 100644 index 76bc8cdc32..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_1_1_3-solution000006.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_1_3-solution000007.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_1_3-solution000007.solution deleted file mode 100644 index 86a85825b3..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_1_1_3-solution000007.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_1_3-solution000008.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_1_3-solution000008.solution deleted file mode 100644 index 8dddb3b359..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_1_1_3-solution000008.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_1_3.eprime b/tests/exhaustive/basic/cut_01_on/expected/model_1_1_3.eprime deleted file mode 100644 index 5406286e79..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_1_1_3.eprime +++ /dev/null @@ -1,21 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1..3)] of bool -find x_ExplicitVarSizeWithMarker_Marker: int(0..3) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3)] of int(1..3) -find cut1: bool -find cut2: bool -branching on [cut1, cut2, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_Occurrence] -such that - !cut1 <-> x_Occurrence[1] /\ x_Occurrence[2], - !cut2 <-> x_Occurrence[1], - and([q2 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q2] < x_ExplicitVarSizeWithMarker_Values[q2 + 1] - | q2 : int(1..2)]), - and([q3 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q3] = 1 | q3 : int(1..3)]), - and([q6 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q6]] - | q6 : int(1..3)]), - and([x_Occurrence[q7] -> - or([q9 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q9] = q7 | q9 : int(1..3)]) - | q7 : int(1..3)]) - diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_1_4-solution000001.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_1_4-solution000001.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_1_1_4-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_1_4-solution000002.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_1_4-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_1_1_4-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_1_4-solution000003.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_1_4-solution000003.solution deleted file mode 100644 index de5cc861ad..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_1_1_4-solution000003.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_1_4-solution000004.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_1_4-solution000004.solution deleted file mode 100644 index a28b6d6203..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_1_1_4-solution000004.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_1_4-solution000005.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_1_4-solution000005.solution deleted file mode 100644 index 1a734343d9..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_1_1_4-solution000005.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_1_4-solution000006.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_1_4-solution000006.solution deleted file mode 100644 index 76bc8cdc32..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_1_1_4-solution000006.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_1_4-solution000007.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_1_4-solution000007.solution deleted file mode 100644 index 86a85825b3..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_1_1_4-solution000007.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_1_4-solution000008.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_1_4-solution000008.solution deleted file mode 100644 index 8dddb3b359..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_1_1_4-solution000008.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_1_4.eprime b/tests/exhaustive/basic/cut_01_on/expected/model_1_1_4.eprime deleted file mode 100644 index 97272a9274..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_1_1_4.eprime +++ /dev/null @@ -1,21 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1..3)] of bool -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..3)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3)] of int(1..3) -find cut1: bool -find cut2: bool -branching on [cut1, cut2, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_Occurrence] -such that - !cut1 <-> x_Occurrence[1] /\ x_Occurrence[2], - !cut2 <-> x_Occurrence[1], - and([x_ExplicitVarSizeWithFlags_Flags[q2 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q2] < x_ExplicitVarSizeWithFlags_Values[q2 + 1] - | q2 : int(1..2)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3] = false -> x_ExplicitVarSizeWithFlags_Values[q3] = 1 | q3 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q4] | q4 : int(1..2)]), - and([x_ExplicitVarSizeWithFlags_Flags[q8] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q8]] | q8 : int(1..3)]), - and([x_Occurrence[q9] -> - or([x_ExplicitVarSizeWithFlags_Flags[q11] /\ x_ExplicitVarSizeWithFlags_Values[q11] = q9 | q11 : int(1..3)]) - | q9 : int(1..3)]) - diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_2_1-solution000001.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_2_1-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_1_2_1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_2_1-solution000002.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_2_1-solution000002.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_1_2_1-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_2_1-solution000003.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_2_1-solution000003.solution deleted file mode 100644 index a28b6d6203..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_1_2_1-solution000003.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_2_1-solution000004.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_2_1-solution000004.solution deleted file mode 100644 index de5cc861ad..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_1_2_1-solution000004.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_2_1-solution000005.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_2_1-solution000005.solution deleted file mode 100644 index 8dddb3b359..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_1_2_1-solution000005.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_2_1-solution000006.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_2_1-solution000006.solution deleted file mode 100644 index 76bc8cdc32..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_1_2_1-solution000006.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_2_1-solution000007.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_2_1-solution000007.solution deleted file mode 100644 index 86a85825b3..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_1_2_1-solution000007.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_2_1-solution000008.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_2_1-solution000008.solution deleted file mode 100644 index 1a734343d9..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_1_2_1-solution000008.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_2_1.eprime b/tests/exhaustive/basic/cut_01_on/expected/model_1_2_1.eprime deleted file mode 100644 index d8a798d856..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_1_2_1.eprime +++ /dev/null @@ -1,18 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1..3)] of bool -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..3)] of int(1..4) -find cut1: bool -find cut2: bool -branching on [cut1, cut2, x_ExplicitVarSizeWithDummy, x_Occurrence] -such that - !cut1 <-> x_Occurrence[1] /\ x_Occurrence[2], - !cut2 <-> or([x_ExplicitVarSizeWithDummy[q14] != 4 /\ x_ExplicitVarSizeWithDummy[q14] = 1 | q14 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q2] < x_ExplicitVarSizeWithDummy[q2 + 1] \/ x_ExplicitVarSizeWithDummy[q2] = 4 - | q2 : int(1..2)]), - and([x_ExplicitVarSizeWithDummy[q3] = 4 -> x_ExplicitVarSizeWithDummy[q3 + 1] = 4 | q3 : int(1..2)]), - and([x_ExplicitVarSizeWithDummy[q7] != 4 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q7]] | q7 : int(1..3)]), - and([x_Occurrence[q8] -> - or([x_ExplicitVarSizeWithDummy[q10] != 4 /\ x_ExplicitVarSizeWithDummy[q10] = q8 | q10 : int(1..3)]) - | q8 : int(1..3)]) - diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_2_2-solution000001.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_2_2-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_1_2_2-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_2_2-solution000002.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_2_2-solution000002.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_1_2_2-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_2_2-solution000003.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_2_2-solution000003.solution deleted file mode 100644 index a28b6d6203..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_1_2_2-solution000003.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_2_2-solution000004.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_2_2-solution000004.solution deleted file mode 100644 index de5cc861ad..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_1_2_2-solution000004.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_2_2-solution000005.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_2_2-solution000005.solution deleted file mode 100644 index 8dddb3b359..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_1_2_2-solution000005.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_2_2-solution000006.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_2_2-solution000006.solution deleted file mode 100644 index 76bc8cdc32..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_1_2_2-solution000006.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_2_2-solution000007.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_2_2-solution000007.solution deleted file mode 100644 index 86a85825b3..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_1_2_2-solution000007.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_2_2-solution000008.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_2_2-solution000008.solution deleted file mode 100644 index 1a734343d9..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_1_2_2-solution000008.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_2_2.eprime b/tests/exhaustive/basic/cut_01_on/expected/model_1_2_2.eprime deleted file mode 100644 index d8a798d856..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_1_2_2.eprime +++ /dev/null @@ -1,18 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1..3)] of bool -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..3)] of int(1..4) -find cut1: bool -find cut2: bool -branching on [cut1, cut2, x_ExplicitVarSizeWithDummy, x_Occurrence] -such that - !cut1 <-> x_Occurrence[1] /\ x_Occurrence[2], - !cut2 <-> or([x_ExplicitVarSizeWithDummy[q14] != 4 /\ x_ExplicitVarSizeWithDummy[q14] = 1 | q14 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q2] < x_ExplicitVarSizeWithDummy[q2 + 1] \/ x_ExplicitVarSizeWithDummy[q2] = 4 - | q2 : int(1..2)]), - and([x_ExplicitVarSizeWithDummy[q3] = 4 -> x_ExplicitVarSizeWithDummy[q3 + 1] = 4 | q3 : int(1..2)]), - and([x_ExplicitVarSizeWithDummy[q7] != 4 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q7]] | q7 : int(1..3)]), - and([x_Occurrence[q8] -> - or([x_ExplicitVarSizeWithDummy[q10] != 4 /\ x_ExplicitVarSizeWithDummy[q10] = q8 | q10 : int(1..3)]) - | q8 : int(1..3)]) - diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_2_3-solution000001.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_2_3-solution000001.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_1_2_3-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_2_3-solution000002.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_2_3-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_1_2_3-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_2_3-solution000003.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_2_3-solution000003.solution deleted file mode 100644 index de5cc861ad..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_1_2_3-solution000003.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_2_3-solution000004.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_2_3-solution000004.solution deleted file mode 100644 index a28b6d6203..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_1_2_3-solution000004.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_2_3-solution000005.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_2_3-solution000005.solution deleted file mode 100644 index 1a734343d9..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_1_2_3-solution000005.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_2_3-solution000006.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_2_3-solution000006.solution deleted file mode 100644 index 76bc8cdc32..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_1_2_3-solution000006.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_2_3-solution000007.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_2_3-solution000007.solution deleted file mode 100644 index 86a85825b3..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_1_2_3-solution000007.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_2_3-solution000008.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_2_3-solution000008.solution deleted file mode 100644 index 8dddb3b359..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_1_2_3-solution000008.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_2_3.eprime b/tests/exhaustive/basic/cut_01_on/expected/model_1_2_3.eprime deleted file mode 100644 index 152c8566c6..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_1_2_3.eprime +++ /dev/null @@ -1,42 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1..3)] of bool -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..3)] of int(1..4) -find x_ExplicitVarSizeWithMarker_Marker: int(0..3) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3)] of int(1..3) -find cut1: bool -find cut2: bool -branching on - [cut1, cut2, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_Occurrence, - x_ExplicitVarSizeWithDummy] -such that - !cut1 <-> x_Occurrence[1] /\ x_Occurrence[2], - !cut2 <-> or([x_ExplicitVarSizeWithDummy[q30] != 4 /\ x_ExplicitVarSizeWithDummy[q30] = 1 | q30 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q2] < x_ExplicitVarSizeWithDummy[q2 + 1] \/ x_ExplicitVarSizeWithDummy[q2] = 4 - | q2 : int(1..2)]), - and([x_ExplicitVarSizeWithDummy[q3] = 4 -> x_ExplicitVarSizeWithDummy[q3 + 1] = 4 | q3 : int(1..2)]), - and([x_ExplicitVarSizeWithDummy[q7] != 4 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q7]] | q7 : int(1..3)]), - and([x_Occurrence[q8] -> - or([x_ExplicitVarSizeWithDummy[q10] != 4 /\ x_ExplicitVarSizeWithDummy[q10] = q8 | q10 : int(1..3)]) - | q8 : int(1..3)]), - and([q11 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q11] < x_ExplicitVarSizeWithMarker_Values[q11 + 1] - | q11 : int(1..2)]), - and([q12 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q12] = 1 | q12 : int(1..3)]), - and([q15 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q15]] - | q15 : int(1..3)]), - and([x_Occurrence[q16] -> - or([q18 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q18] = q16 - | q18 : int(1..3)]) - | q16 : int(1..3)]), - and([q20 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q22] != 4 /\ - x_ExplicitVarSizeWithDummy[q22] = x_ExplicitVarSizeWithMarker_Values[q20] - | q22 : int(1..3)]) - | q20 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q24] != 4 -> - or([q26 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q26] = x_ExplicitVarSizeWithDummy[q24] - | q26 : int(1..3)]) - | q24 : int(1..3)]) - diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_2_4-solution000001.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_2_4-solution000001.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_1_2_4-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_2_4-solution000002.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_2_4-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_1_2_4-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_2_4-solution000003.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_2_4-solution000003.solution deleted file mode 100644 index de5cc861ad..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_1_2_4-solution000003.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_2_4-solution000004.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_2_4-solution000004.solution deleted file mode 100644 index a28b6d6203..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_1_2_4-solution000004.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_2_4-solution000005.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_2_4-solution000005.solution deleted file mode 100644 index 1a734343d9..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_1_2_4-solution000005.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_2_4-solution000006.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_2_4-solution000006.solution deleted file mode 100644 index 76bc8cdc32..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_1_2_4-solution000006.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_2_4-solution000007.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_2_4-solution000007.solution deleted file mode 100644 index 86a85825b3..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_1_2_4-solution000007.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_2_4-solution000008.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_2_4-solution000008.solution deleted file mode 100644 index 8dddb3b359..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_1_2_4-solution000008.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_2_4.eprime b/tests/exhaustive/basic/cut_01_on/expected/model_1_2_4.eprime deleted file mode 100644 index 9affc590d9..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_1_2_4.eprime +++ /dev/null @@ -1,43 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1..3)] of bool -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..3)] of int(1..4) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..3)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3)] of int(1..3) -find cut1: bool -find cut2: bool -branching on - [cut1, cut2, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_Occurrence, - x_ExplicitVarSizeWithDummy] -such that - !cut1 <-> x_Occurrence[1] /\ x_Occurrence[2], - !cut2 <-> or([x_ExplicitVarSizeWithDummy[q32] != 4 /\ x_ExplicitVarSizeWithDummy[q32] = 1 | q32 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q2] < x_ExplicitVarSizeWithDummy[q2 + 1] \/ x_ExplicitVarSizeWithDummy[q2] = 4 - | q2 : int(1..2)]), - and([x_ExplicitVarSizeWithDummy[q3] = 4 -> x_ExplicitVarSizeWithDummy[q3 + 1] = 4 | q3 : int(1..2)]), - and([x_ExplicitVarSizeWithDummy[q7] != 4 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q7]] | q7 : int(1..3)]), - and([x_Occurrence[q8] -> - or([x_ExplicitVarSizeWithDummy[q10] != 4 /\ x_ExplicitVarSizeWithDummy[q10] = q8 | q10 : int(1..3)]) - | q8 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q11 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q11] < x_ExplicitVarSizeWithFlags_Values[q11 + 1] - | q11 : int(1..2)]), - and([x_ExplicitVarSizeWithFlags_Flags[q12] = false -> x_ExplicitVarSizeWithFlags_Values[q12] = 1 - | q12 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q13 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q13] | q13 : int(1..2)]), - and([x_ExplicitVarSizeWithFlags_Flags[q17] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q17]] - | q17 : int(1..3)]), - and([x_Occurrence[q18] -> - or([x_ExplicitVarSizeWithFlags_Flags[q20] /\ x_ExplicitVarSizeWithFlags_Values[q20] = q18 | q20 : int(1..3)]) - | q18 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q22] -> - or([x_ExplicitVarSizeWithDummy[q24] != 4 /\ - x_ExplicitVarSizeWithDummy[q24] = x_ExplicitVarSizeWithFlags_Values[q22] - | q24 : int(1..3)]) - | q22 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q26] != 4 -> - or([x_ExplicitVarSizeWithFlags_Flags[q28] /\ - x_ExplicitVarSizeWithFlags_Values[q28] = x_ExplicitVarSizeWithDummy[q26] - | q28 : int(1..3)]) - | q26 : int(1..3)]) - diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_3_1-solution000001.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_3_1-solution000001.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_1_3_1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_3_1-solution000002.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_3_1-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_1_3_1-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_3_1-solution000003.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_3_1-solution000003.solution deleted file mode 100644 index de5cc861ad..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_1_3_1-solution000003.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_3_1-solution000004.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_3_1-solution000004.solution deleted file mode 100644 index a28b6d6203..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_1_3_1-solution000004.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_3_1-solution000005.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_3_1-solution000005.solution deleted file mode 100644 index 1a734343d9..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_1_3_1-solution000005.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_3_1-solution000006.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_3_1-solution000006.solution deleted file mode 100644 index 76bc8cdc32..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_1_3_1-solution000006.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_3_1-solution000007.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_3_1-solution000007.solution deleted file mode 100644 index 86a85825b3..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_1_3_1-solution000007.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_3_1-solution000008.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_3_1-solution000008.solution deleted file mode 100644 index 8dddb3b359..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_1_3_1-solution000008.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_3_1.eprime b/tests/exhaustive/basic/cut_01_on/expected/model_1_3_1.eprime deleted file mode 100644 index 78130af4ee..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_1_3_1.eprime +++ /dev/null @@ -1,22 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1..3)] of bool -find x_ExplicitVarSizeWithMarker_Marker: int(0..3) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3)] of int(1..3) -find cut1: bool -find cut2: bool -branching on [cut1, cut2, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_Occurrence] -such that - !cut1 <-> x_Occurrence[1] /\ x_Occurrence[2], - !cut2 <-> - or([q13 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q13] = 1 | q13 : int(1..3)]), - and([q2 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q2] < x_ExplicitVarSizeWithMarker_Values[q2 + 1] - | q2 : int(1..2)]), - and([q3 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q3] = 1 | q3 : int(1..3)]), - and([q6 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q6]] - | q6 : int(1..3)]), - and([x_Occurrence[q7] -> - or([q9 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q9] = q7 | q9 : int(1..3)]) - | q7 : int(1..3)]) - diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_3_2-solution000001.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_3_2-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_1_3_2-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_3_2-solution000002.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_3_2-solution000002.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_1_3_2-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_3_2-solution000003.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_3_2-solution000003.solution deleted file mode 100644 index a28b6d6203..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_1_3_2-solution000003.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_3_2-solution000004.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_3_2-solution000004.solution deleted file mode 100644 index de5cc861ad..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_1_3_2-solution000004.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_3_2-solution000005.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_3_2-solution000005.solution deleted file mode 100644 index 8dddb3b359..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_1_3_2-solution000005.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_3_2-solution000006.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_3_2-solution000006.solution deleted file mode 100644 index 76bc8cdc32..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_1_3_2-solution000006.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_3_2-solution000007.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_3_2-solution000007.solution deleted file mode 100644 index 86a85825b3..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_1_3_2-solution000007.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_3_2-solution000008.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_3_2-solution000008.solution deleted file mode 100644 index 1a734343d9..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_1_3_2-solution000008.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_3_2.eprime b/tests/exhaustive/basic/cut_01_on/expected/model_1_3_2.eprime deleted file mode 100644 index bf2d88160d..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_1_3_2.eprime +++ /dev/null @@ -1,42 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1..3)] of bool -find x_ExplicitVarSizeWithMarker_Marker: int(0..3) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3)] of int(1..3) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..3)] of int(1..4) -find cut1: bool -find cut2: bool -branching on - [cut1, cut2, x_ExplicitVarSizeWithDummy, x_Occurrence, x_ExplicitVarSizeWithMarker_Marker, - x_ExplicitVarSizeWithMarker_Values] -such that - !cut1 <-> x_Occurrence[1] /\ x_Occurrence[2], - !cut2 <-> - or([q30 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q30] = 1 | q30 : int(1..3)]), - and([q2 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q2] < x_ExplicitVarSizeWithMarker_Values[q2 + 1] - | q2 : int(1..2)]), - and([q3 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q3] = 1 | q3 : int(1..3)]), - and([q6 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q6]] - | q6 : int(1..3)]), - and([x_Occurrence[q7] -> - or([q9 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q9] = q7 | q9 : int(1..3)]) - | q7 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q10] < x_ExplicitVarSizeWithDummy[q10 + 1] \/ x_ExplicitVarSizeWithDummy[q10] = 4 - | q10 : int(1..2)]), - and([x_ExplicitVarSizeWithDummy[q11] = 4 -> x_ExplicitVarSizeWithDummy[q11 + 1] = 4 | q11 : int(1..2)]), - and([x_ExplicitVarSizeWithDummy[q15] != 4 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q15]] | q15 : int(1..3)]), - and([x_Occurrence[q16] -> - or([x_ExplicitVarSizeWithDummy[q18] != 4 /\ x_ExplicitVarSizeWithDummy[q18] = q16 | q18 : int(1..3)]) - | q16 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q20] != 4 -> - or([q22 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q22] = x_ExplicitVarSizeWithDummy[q20] - | q22 : int(1..3)]) - | q20 : int(1..3)]), - and([q24 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q26] != 4 /\ - x_ExplicitVarSizeWithDummy[q26] = x_ExplicitVarSizeWithMarker_Values[q24] - | q26 : int(1..3)]) - | q24 : int(1..3)]) - diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_3_3-solution000001.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_3_3-solution000001.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_1_3_3-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_3_3-solution000002.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_3_3-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_1_3_3-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_3_3-solution000003.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_3_3-solution000003.solution deleted file mode 100644 index de5cc861ad..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_1_3_3-solution000003.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_3_3-solution000004.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_3_3-solution000004.solution deleted file mode 100644 index a28b6d6203..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_1_3_3-solution000004.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_3_3-solution000005.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_3_3-solution000005.solution deleted file mode 100644 index 1a734343d9..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_1_3_3-solution000005.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_3_3-solution000006.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_3_3-solution000006.solution deleted file mode 100644 index 76bc8cdc32..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_1_3_3-solution000006.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_3_3-solution000007.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_3_3-solution000007.solution deleted file mode 100644 index 86a85825b3..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_1_3_3-solution000007.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_3_3-solution000008.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_3_3-solution000008.solution deleted file mode 100644 index 8dddb3b359..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_1_3_3-solution000008.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_3_3.eprime b/tests/exhaustive/basic/cut_01_on/expected/model_1_3_3.eprime deleted file mode 100644 index 78130af4ee..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_1_3_3.eprime +++ /dev/null @@ -1,22 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1..3)] of bool -find x_ExplicitVarSizeWithMarker_Marker: int(0..3) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3)] of int(1..3) -find cut1: bool -find cut2: bool -branching on [cut1, cut2, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_Occurrence] -such that - !cut1 <-> x_Occurrence[1] /\ x_Occurrence[2], - !cut2 <-> - or([q13 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q13] = 1 | q13 : int(1..3)]), - and([q2 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q2] < x_ExplicitVarSizeWithMarker_Values[q2 + 1] - | q2 : int(1..2)]), - and([q3 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q3] = 1 | q3 : int(1..3)]), - and([q6 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q6]] - | q6 : int(1..3)]), - and([x_Occurrence[q7] -> - or([q9 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q9] = q7 | q9 : int(1..3)]) - | q7 : int(1..3)]) - diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_3_4-solution000001.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_3_4-solution000001.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_1_3_4-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_3_4-solution000002.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_3_4-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_1_3_4-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_3_4-solution000003.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_3_4-solution000003.solution deleted file mode 100644 index de5cc861ad..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_1_3_4-solution000003.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_3_4-solution000004.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_3_4-solution000004.solution deleted file mode 100644 index a28b6d6203..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_1_3_4-solution000004.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_3_4-solution000005.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_3_4-solution000005.solution deleted file mode 100644 index 1a734343d9..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_1_3_4-solution000005.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_3_4-solution000006.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_3_4-solution000006.solution deleted file mode 100644 index 76bc8cdc32..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_1_3_4-solution000006.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_3_4-solution000007.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_3_4-solution000007.solution deleted file mode 100644 index 86a85825b3..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_1_3_4-solution000007.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_3_4-solution000008.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_3_4-solution000008.solution deleted file mode 100644 index 8dddb3b359..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_1_3_4-solution000008.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_3_4.eprime b/tests/exhaustive/basic/cut_01_on/expected/model_1_3_4.eprime deleted file mode 100644 index 935a55c438..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_1_3_4.eprime +++ /dev/null @@ -1,47 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1..3)] of bool -find x_ExplicitVarSizeWithMarker_Marker: int(0..3) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3)] of int(1..3) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..3)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3)] of int(1..3) -find cut1: bool -find cut2: bool -branching on - [cut1, cut2, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_Occurrence, - x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] -such that - !cut1 <-> x_Occurrence[1] /\ x_Occurrence[2], - !cut2 <-> - or([q31 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q31] = 1 | q31 : int(1..3)]), - and([q2 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q2] < x_ExplicitVarSizeWithMarker_Values[q2 + 1] - | q2 : int(1..2)]), - and([q3 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q3] = 1 | q3 : int(1..3)]), - and([q6 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q6]] - | q6 : int(1..3)]), - and([x_Occurrence[q7] -> - or([q9 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q9] = q7 | q9 : int(1..3)]) - | q7 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q10 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q10] < x_ExplicitVarSizeWithFlags_Values[q10 + 1] - | q10 : int(1..2)]), - and([x_ExplicitVarSizeWithFlags_Flags[q11] = false -> x_ExplicitVarSizeWithFlags_Values[q11] = 1 - | q11 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q12 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q12] | q12 : int(1..2)]), - and([x_ExplicitVarSizeWithFlags_Flags[q16] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q16]] - | q16 : int(1..3)]), - and([x_Occurrence[q17] -> - or([x_ExplicitVarSizeWithFlags_Flags[q19] /\ x_ExplicitVarSizeWithFlags_Values[q19] = q17 | q19 : int(1..3)]) - | q17 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q21] -> - or([q23 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q23] = x_ExplicitVarSizeWithFlags_Values[q21] - | q23 : int(1..3)]) - | q21 : int(1..3)]), - and([q25 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q27] /\ - x_ExplicitVarSizeWithFlags_Values[q27] = x_ExplicitVarSizeWithMarker_Values[q25] - | q27 : int(1..3)]) - | q25 : int(1..3)]) - diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_4_1-solution000001.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_4_1-solution000001.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_1_4_1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_4_1-solution000002.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_4_1-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_1_4_1-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_4_1-solution000003.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_4_1-solution000003.solution deleted file mode 100644 index de5cc861ad..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_1_4_1-solution000003.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_4_1-solution000004.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_4_1-solution000004.solution deleted file mode 100644 index a28b6d6203..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_1_4_1-solution000004.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_4_1-solution000005.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_4_1-solution000005.solution deleted file mode 100644 index 1a734343d9..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_1_4_1-solution000005.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_4_1-solution000006.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_4_1-solution000006.solution deleted file mode 100644 index 76bc8cdc32..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_1_4_1-solution000006.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_4_1-solution000007.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_4_1-solution000007.solution deleted file mode 100644 index 86a85825b3..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_1_4_1-solution000007.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_4_1-solution000008.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_4_1-solution000008.solution deleted file mode 100644 index 8dddb3b359..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_1_4_1-solution000008.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_4_1.eprime b/tests/exhaustive/basic/cut_01_on/expected/model_1_4_1.eprime deleted file mode 100644 index bfd019eafe..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_1_4_1.eprime +++ /dev/null @@ -1,22 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1..3)] of bool -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..3)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3)] of int(1..3) -find cut1: bool -find cut2: bool -branching on [cut1, cut2, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_Occurrence] -such that - !cut1 <-> x_Occurrence[1] /\ x_Occurrence[2], - !cut2 <-> - or([x_ExplicitVarSizeWithFlags_Flags[q15] /\ x_ExplicitVarSizeWithFlags_Values[q15] = 1 | q15 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q2] < x_ExplicitVarSizeWithFlags_Values[q2 + 1] - | q2 : int(1..2)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3] = false -> x_ExplicitVarSizeWithFlags_Values[q3] = 1 | q3 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q4] | q4 : int(1..2)]), - and([x_ExplicitVarSizeWithFlags_Flags[q8] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q8]] | q8 : int(1..3)]), - and([x_Occurrence[q9] -> - or([x_ExplicitVarSizeWithFlags_Flags[q11] /\ x_ExplicitVarSizeWithFlags_Values[q11] = q9 | q11 : int(1..3)]) - | q9 : int(1..3)]) - diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_4_2-solution000001.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_4_2-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_1_4_2-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_4_2-solution000002.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_4_2-solution000002.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_1_4_2-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_4_2-solution000003.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_4_2-solution000003.solution deleted file mode 100644 index a28b6d6203..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_1_4_2-solution000003.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_4_2-solution000004.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_4_2-solution000004.solution deleted file mode 100644 index de5cc861ad..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_1_4_2-solution000004.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_4_2-solution000005.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_4_2-solution000005.solution deleted file mode 100644 index 8dddb3b359..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_1_4_2-solution000005.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_4_2-solution000006.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_4_2-solution000006.solution deleted file mode 100644 index 76bc8cdc32..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_1_4_2-solution000006.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_4_2-solution000007.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_4_2-solution000007.solution deleted file mode 100644 index 86a85825b3..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_1_4_2-solution000007.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_4_2-solution000008.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_4_2-solution000008.solution deleted file mode 100644 index 1a734343d9..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_1_4_2-solution000008.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_4_2.eprime b/tests/exhaustive/basic/cut_01_on/expected/model_1_4_2.eprime deleted file mode 100644 index 59b4ad5892..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_1_4_2.eprime +++ /dev/null @@ -1,42 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1..3)] of bool -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..3)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3)] of int(1..3) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..3)] of int(1..4) -find cut1: bool -find cut2: bool -branching on - [cut1, cut2, x_ExplicitVarSizeWithDummy, x_Occurrence, x_ExplicitVarSizeWithFlags_Flags, - x_ExplicitVarSizeWithFlags_Values] -such that - !cut1 <-> x_Occurrence[1] /\ x_Occurrence[2], - !cut2 <-> - or([x_ExplicitVarSizeWithFlags_Flags[q32] /\ x_ExplicitVarSizeWithFlags_Values[q32] = 1 | q32 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q2] < x_ExplicitVarSizeWithFlags_Values[q2 + 1] - | q2 : int(1..2)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3] = false -> x_ExplicitVarSizeWithFlags_Values[q3] = 1 | q3 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q4] | q4 : int(1..2)]), - and([x_ExplicitVarSizeWithFlags_Flags[q8] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q8]] | q8 : int(1..3)]), - and([x_Occurrence[q9] -> - or([x_ExplicitVarSizeWithFlags_Flags[q11] /\ x_ExplicitVarSizeWithFlags_Values[q11] = q9 | q11 : int(1..3)]) - | q9 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q12] < x_ExplicitVarSizeWithDummy[q12 + 1] \/ x_ExplicitVarSizeWithDummy[q12] = 4 - | q12 : int(1..2)]), - and([x_ExplicitVarSizeWithDummy[q13] = 4 -> x_ExplicitVarSizeWithDummy[q13 + 1] = 4 | q13 : int(1..2)]), - and([x_ExplicitVarSizeWithDummy[q17] != 4 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q17]] | q17 : int(1..3)]), - and([x_Occurrence[q18] -> - or([x_ExplicitVarSizeWithDummy[q20] != 4 /\ x_ExplicitVarSizeWithDummy[q20] = q18 | q20 : int(1..3)]) - | q18 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q22] != 4 -> - or([x_ExplicitVarSizeWithFlags_Flags[q24] /\ - x_ExplicitVarSizeWithFlags_Values[q24] = x_ExplicitVarSizeWithDummy[q22] - | q24 : int(1..3)]) - | q22 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q26] -> - or([x_ExplicitVarSizeWithDummy[q28] != 4 /\ - x_ExplicitVarSizeWithDummy[q28] = x_ExplicitVarSizeWithFlags_Values[q26] - | q28 : int(1..3)]) - | q26 : int(1..3)]) - diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_4_3-solution000001.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_4_3-solution000001.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_1_4_3-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_4_3-solution000002.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_4_3-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_1_4_3-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_4_3-solution000003.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_4_3-solution000003.solution deleted file mode 100644 index de5cc861ad..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_1_4_3-solution000003.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_4_3-solution000004.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_4_3-solution000004.solution deleted file mode 100644 index a28b6d6203..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_1_4_3-solution000004.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_4_3-solution000005.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_4_3-solution000005.solution deleted file mode 100644 index 1a734343d9..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_1_4_3-solution000005.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_4_3-solution000006.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_4_3-solution000006.solution deleted file mode 100644 index 76bc8cdc32..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_1_4_3-solution000006.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_4_3-solution000007.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_4_3-solution000007.solution deleted file mode 100644 index 86a85825b3..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_1_4_3-solution000007.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_4_3-solution000008.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_4_3-solution000008.solution deleted file mode 100644 index 8dddb3b359..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_1_4_3-solution000008.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_4_3.eprime b/tests/exhaustive/basic/cut_01_on/expected/model_1_4_3.eprime deleted file mode 100644 index 60a450a92c..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_1_4_3.eprime +++ /dev/null @@ -1,46 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1..3)] of bool -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..3)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3)] of int(1..3) -find x_ExplicitVarSizeWithMarker_Marker: int(0..3) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3)] of int(1..3) -find cut1: bool -find cut2: bool -branching on - [cut1, cut2, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_Occurrence, - x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] -such that - !cut1 <-> x_Occurrence[1] /\ x_Occurrence[2], - !cut2 <-> - or([x_ExplicitVarSizeWithFlags_Flags[q31] /\ x_ExplicitVarSizeWithFlags_Values[q31] = 1 | q31 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q2] < x_ExplicitVarSizeWithFlags_Values[q2 + 1] - | q2 : int(1..2)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3] = false -> x_ExplicitVarSizeWithFlags_Values[q3] = 1 | q3 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q4] | q4 : int(1..2)]), - and([x_ExplicitVarSizeWithFlags_Flags[q8] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q8]] | q8 : int(1..3)]), - and([x_Occurrence[q9] -> - or([x_ExplicitVarSizeWithFlags_Flags[q11] /\ x_ExplicitVarSizeWithFlags_Values[q11] = q9 | q11 : int(1..3)]) - | q9 : int(1..3)]), - and([q12 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q12] < x_ExplicitVarSizeWithMarker_Values[q12 + 1] - | q12 : int(1..2)]), - and([q13 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q13] = 1 | q13 : int(1..3)]), - and([q16 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q16]] - | q16 : int(1..3)]), - and([x_Occurrence[q17] -> - or([q19 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q19] = q17 - | q19 : int(1..3)]) - | q17 : int(1..3)]), - and([q21 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q23] /\ - x_ExplicitVarSizeWithFlags_Values[q23] = x_ExplicitVarSizeWithMarker_Values[q21] - | q23 : int(1..3)]) - | q21 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q25] -> - or([q27 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q27] = x_ExplicitVarSizeWithFlags_Values[q25] - | q27 : int(1..3)]) - | q25 : int(1..3)]) - diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_4_4-solution000001.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_4_4-solution000001.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_1_4_4-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_4_4-solution000002.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_4_4-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_1_4_4-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_4_4-solution000003.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_4_4-solution000003.solution deleted file mode 100644 index de5cc861ad..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_1_4_4-solution000003.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_4_4-solution000004.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_4_4-solution000004.solution deleted file mode 100644 index a28b6d6203..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_1_4_4-solution000004.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_4_4-solution000005.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_4_4-solution000005.solution deleted file mode 100644 index 1a734343d9..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_1_4_4-solution000005.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_4_4-solution000006.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_4_4-solution000006.solution deleted file mode 100644 index 76bc8cdc32..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_1_4_4-solution000006.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_4_4-solution000007.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_4_4-solution000007.solution deleted file mode 100644 index 86a85825b3..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_1_4_4-solution000007.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_4_4-solution000008.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_4_4-solution000008.solution deleted file mode 100644 index 8dddb3b359..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_1_4_4-solution000008.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_4_4.eprime b/tests/exhaustive/basic/cut_01_on/expected/model_1_4_4.eprime deleted file mode 100644 index bfd019eafe..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_1_4_4.eprime +++ /dev/null @@ -1,22 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1..3)] of bool -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..3)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3)] of int(1..3) -find cut1: bool -find cut2: bool -branching on [cut1, cut2, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_Occurrence] -such that - !cut1 <-> x_Occurrence[1] /\ x_Occurrence[2], - !cut2 <-> - or([x_ExplicitVarSizeWithFlags_Flags[q15] /\ x_ExplicitVarSizeWithFlags_Values[q15] = 1 | q15 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q2] < x_ExplicitVarSizeWithFlags_Values[q2 + 1] - | q2 : int(1..2)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3] = false -> x_ExplicitVarSizeWithFlags_Values[q3] = 1 | q3 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q4] | q4 : int(1..2)]), - and([x_ExplicitVarSizeWithFlags_Flags[q8] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q8]] | q8 : int(1..3)]), - and([x_Occurrence[q9] -> - or([x_ExplicitVarSizeWithFlags_Flags[q11] /\ x_ExplicitVarSizeWithFlags_Values[q11] = q9 | q11 : int(1..3)]) - | q9 : int(1..3)]) - diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_1_1-solution000001.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_1_1-solution000001.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_2_1_1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_1_1-solution000002.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_1_1-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_2_1_1-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_1_1-solution000003.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_1_1-solution000003.solution deleted file mode 100644 index de5cc861ad..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_2_1_1-solution000003.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_1_1-solution000004.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_1_1-solution000004.solution deleted file mode 100644 index a28b6d6203..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_2_1_1-solution000004.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_1_1-solution000005.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_1_1-solution000005.solution deleted file mode 100644 index 1a734343d9..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_2_1_1-solution000005.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_1_1-solution000006.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_1_1-solution000006.solution deleted file mode 100644 index 86a85825b3..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_2_1_1-solution000006.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_1_1-solution000007.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_1_1-solution000007.solution deleted file mode 100644 index 76bc8cdc32..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_2_1_1-solution000007.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_1_1-solution000008.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_1_1-solution000008.solution deleted file mode 100644 index 8dddb3b359..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_2_1_1-solution000008.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_1_1.eprime b/tests/exhaustive/basic/cut_01_on/expected/model_2_1_1.eprime deleted file mode 100644 index 6bbdfe488c..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_2_1_1.eprime +++ /dev/null @@ -1,20 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..3)] of int(1..4) -find x_Occurrence: matrix indexed by [int(1..3)] of bool -find cut1: bool -find cut2: bool -branching on [cut1, cut2, x_Occurrence, x_ExplicitVarSizeWithDummy] -such that - !cut1 <-> - or([x_ExplicitVarSizeWithDummy[q14] != 4 /\ x_ExplicitVarSizeWithDummy[q14] = 1 | q14 : int(1..3)]) /\ - or([x_ExplicitVarSizeWithDummy[q16] != 4 /\ x_ExplicitVarSizeWithDummy[q16] = 2 | q16 : int(1..3)]), - !cut2 <-> x_Occurrence[1], - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 4 - | q1 : int(1..2)]), - and([x_ExplicitVarSizeWithDummy[q2] = 4 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 4 | q2 : int(1..2)]), - and([x_Occurrence[q6] -> - or([x_ExplicitVarSizeWithDummy[q8] != 4 /\ x_ExplicitVarSizeWithDummy[q8] = q6 | q8 : int(1..3)]) - | q6 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q10] != 4 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q10]] | q10 : int(1..3)]) - diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_1_2-solution000001.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_1_2-solution000001.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_2_1_2-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_1_2-solution000002.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_1_2-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_2_1_2-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_1_2-solution000003.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_1_2-solution000003.solution deleted file mode 100644 index de5cc861ad..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_2_1_2-solution000003.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_1_2-solution000004.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_1_2-solution000004.solution deleted file mode 100644 index a28b6d6203..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_2_1_2-solution000004.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_1_2-solution000005.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_1_2-solution000005.solution deleted file mode 100644 index 1a734343d9..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_2_1_2-solution000005.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_1_2-solution000006.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_1_2-solution000006.solution deleted file mode 100644 index 86a85825b3..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_2_1_2-solution000006.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_1_2-solution000007.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_1_2-solution000007.solution deleted file mode 100644 index 76bc8cdc32..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_2_1_2-solution000007.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_1_2-solution000008.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_1_2-solution000008.solution deleted file mode 100644 index 8dddb3b359..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_2_1_2-solution000008.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_1_2.eprime b/tests/exhaustive/basic/cut_01_on/expected/model_2_1_2.eprime deleted file mode 100644 index 6bbdfe488c..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_2_1_2.eprime +++ /dev/null @@ -1,20 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..3)] of int(1..4) -find x_Occurrence: matrix indexed by [int(1..3)] of bool -find cut1: bool -find cut2: bool -branching on [cut1, cut2, x_Occurrence, x_ExplicitVarSizeWithDummy] -such that - !cut1 <-> - or([x_ExplicitVarSizeWithDummy[q14] != 4 /\ x_ExplicitVarSizeWithDummy[q14] = 1 | q14 : int(1..3)]) /\ - or([x_ExplicitVarSizeWithDummy[q16] != 4 /\ x_ExplicitVarSizeWithDummy[q16] = 2 | q16 : int(1..3)]), - !cut2 <-> x_Occurrence[1], - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 4 - | q1 : int(1..2)]), - and([x_ExplicitVarSizeWithDummy[q2] = 4 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 4 | q2 : int(1..2)]), - and([x_Occurrence[q6] -> - or([x_ExplicitVarSizeWithDummy[q8] != 4 /\ x_ExplicitVarSizeWithDummy[q8] = q6 | q8 : int(1..3)]) - | q6 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q10] != 4 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q10]] | q10 : int(1..3)]) - diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_1_3-solution000001.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_1_3-solution000001.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_2_1_3-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_1_3-solution000002.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_1_3-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_2_1_3-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_1_3-solution000003.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_1_3-solution000003.solution deleted file mode 100644 index de5cc861ad..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_2_1_3-solution000003.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_1_3-solution000004.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_1_3-solution000004.solution deleted file mode 100644 index a28b6d6203..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_2_1_3-solution000004.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_1_3-solution000005.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_1_3-solution000005.solution deleted file mode 100644 index 1a734343d9..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_2_1_3-solution000005.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_1_3-solution000006.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_1_3-solution000006.solution deleted file mode 100644 index 76bc8cdc32..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_2_1_3-solution000006.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_1_3-solution000007.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_1_3-solution000007.solution deleted file mode 100644 index 86a85825b3..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_2_1_3-solution000007.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_1_3-solution000008.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_1_3-solution000008.solution deleted file mode 100644 index 8dddb3b359..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_2_1_3-solution000008.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_1_3.eprime b/tests/exhaustive/basic/cut_01_on/expected/model_2_1_3.eprime deleted file mode 100644 index 20e72bbbda..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_2_1_3.eprime +++ /dev/null @@ -1,44 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..3)] of int(1..4) -find x_Occurrence: matrix indexed by [int(1..3)] of bool -find x_ExplicitVarSizeWithMarker_Marker: int(0..3) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3)] of int(1..3) -find cut1: bool -find cut2: bool -branching on - [cut1, cut2, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy, - x_Occurrence] -such that - !cut1 <-> - or([x_ExplicitVarSizeWithDummy[q30] != 4 /\ x_ExplicitVarSizeWithDummy[q30] = 1 | q30 : int(1..3)]) /\ - or([x_ExplicitVarSizeWithDummy[q32] != 4 /\ x_ExplicitVarSizeWithDummy[q32] = 2 | q32 : int(1..3)]), - !cut2 <-> x_Occurrence[1], - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 4 - | q1 : int(1..2)]), - and([x_ExplicitVarSizeWithDummy[q2] = 4 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 4 | q2 : int(1..2)]), - and([x_Occurrence[q22] -> - or([x_ExplicitVarSizeWithDummy[q24] != 4 /\ x_ExplicitVarSizeWithDummy[q24] = q22 | q24 : int(1..3)]) - | q22 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q26] != 4 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q26]] | q26 : int(1..3)]), - and([q6 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q6] < x_ExplicitVarSizeWithMarker_Values[q6 + 1] - | q6 : int(1..2)]), - and([q7 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q7] = 1 | q7 : int(1..3)]), - and([q10 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q12] != 4 /\ - x_ExplicitVarSizeWithDummy[q12] = x_ExplicitVarSizeWithMarker_Values[q10] - | q12 : int(1..3)]) - | q10 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q14] != 4 -> - or([q16 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q16] = x_ExplicitVarSizeWithDummy[q14] - | q16 : int(1..3)]) - | q14 : int(1..3)]), - and([q18 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q18]] - | q18 : int(1..3)]), - and([x_Occurrence[q19] -> - or([q21 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q21] = q19 - | q21 : int(1..3)]) - | q19 : int(1..3)]) - diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_1_4-solution000001.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_1_4-solution000001.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_2_1_4-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_1_4-solution000002.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_1_4-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_2_1_4-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_1_4-solution000003.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_1_4-solution000003.solution deleted file mode 100644 index de5cc861ad..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_2_1_4-solution000003.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_1_4-solution000004.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_1_4-solution000004.solution deleted file mode 100644 index a28b6d6203..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_2_1_4-solution000004.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_1_4-solution000005.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_1_4-solution000005.solution deleted file mode 100644 index 1a734343d9..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_2_1_4-solution000005.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_1_4-solution000006.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_1_4-solution000006.solution deleted file mode 100644 index 76bc8cdc32..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_2_1_4-solution000006.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_1_4-solution000007.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_1_4-solution000007.solution deleted file mode 100644 index 86a85825b3..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_2_1_4-solution000007.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_1_4-solution000008.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_1_4-solution000008.solution deleted file mode 100644 index 8dddb3b359..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_2_1_4-solution000008.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_1_4.eprime b/tests/exhaustive/basic/cut_01_on/expected/model_2_1_4.eprime deleted file mode 100644 index 2b02355693..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_2_1_4.eprime +++ /dev/null @@ -1,44 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..3)] of int(1..4) -find x_Occurrence: matrix indexed by [int(1..3)] of bool -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..3)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3)] of int(1..3) -find cut1: bool -find cut2: bool -branching on - [cut1, cut2, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy, - x_Occurrence] -such that - !cut1 <-> - or([x_ExplicitVarSizeWithDummy[q32] != 4 /\ x_ExplicitVarSizeWithDummy[q32] = 1 | q32 : int(1..3)]) /\ - or([x_ExplicitVarSizeWithDummy[q34] != 4 /\ x_ExplicitVarSizeWithDummy[q34] = 2 | q34 : int(1..3)]), - !cut2 <-> x_Occurrence[1], - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 4 - | q1 : int(1..2)]), - and([x_ExplicitVarSizeWithDummy[q2] = 4 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 4 | q2 : int(1..2)]), - and([x_Occurrence[q24] -> - or([x_ExplicitVarSizeWithDummy[q26] != 4 /\ x_ExplicitVarSizeWithDummy[q26] = q24 | q26 : int(1..3)]) - | q24 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q28] != 4 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q28]] | q28 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q6] < x_ExplicitVarSizeWithFlags_Values[q6 + 1] - | q6 : int(1..2)]), - and([x_ExplicitVarSizeWithFlags_Flags[q7] = false -> x_ExplicitVarSizeWithFlags_Values[q7] = 1 | q7 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q8 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q8] | q8 : int(1..2)]), - and([x_ExplicitVarSizeWithFlags_Flags[q12] -> - or([x_ExplicitVarSizeWithDummy[q14] != 4 /\ - x_ExplicitVarSizeWithDummy[q14] = x_ExplicitVarSizeWithFlags_Values[q12] - | q14 : int(1..3)]) - | q12 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q16] != 4 -> - or([x_ExplicitVarSizeWithFlags_Flags[q18] /\ - x_ExplicitVarSizeWithFlags_Values[q18] = x_ExplicitVarSizeWithDummy[q16] - | q18 : int(1..3)]) - | q16 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q20] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q20]] - | q20 : int(1..3)]), - and([x_Occurrence[q21] -> - or([x_ExplicitVarSizeWithFlags_Flags[q23] /\ x_ExplicitVarSizeWithFlags_Values[q23] = q21 | q23 : int(1..3)]) - | q21 : int(1..3)]) - diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_2_1-solution000001.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_2_1-solution000001.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_2_2_1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_2_1-solution000002.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_2_1-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_2_2_1-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_2_1-solution000003.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_2_1-solution000003.solution deleted file mode 100644 index de5cc861ad..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_2_2_1-solution000003.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_2_1-solution000004.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_2_1-solution000004.solution deleted file mode 100644 index a28b6d6203..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_2_2_1-solution000004.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_2_1-solution000005.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_2_1-solution000005.solution deleted file mode 100644 index 1a734343d9..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_2_2_1-solution000005.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_2_1-solution000006.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_2_1-solution000006.solution deleted file mode 100644 index 86a85825b3..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_2_2_1-solution000006.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_2_1-solution000007.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_2_1-solution000007.solution deleted file mode 100644 index 76bc8cdc32..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_2_2_1-solution000007.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_2_1-solution000008.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_2_1-solution000008.solution deleted file mode 100644 index 8dddb3b359..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_2_2_1-solution000008.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_2_1.eprime b/tests/exhaustive/basic/cut_01_on/expected/model_2_2_1.eprime deleted file mode 100644 index d4bcc8ac77..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_2_2_1.eprime +++ /dev/null @@ -1,20 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..3)] of int(1..4) -find x_Occurrence: matrix indexed by [int(1..3)] of bool -find cut1: bool -find cut2: bool -branching on [cut1, cut2, x_Occurrence, x_ExplicitVarSizeWithDummy] -such that - !cut1 <-> - or([x_ExplicitVarSizeWithDummy[q9] != 4 /\ x_ExplicitVarSizeWithDummy[q9] = 1 | q9 : int(1..3)]) /\ - or([x_ExplicitVarSizeWithDummy[q11] != 4 /\ x_ExplicitVarSizeWithDummy[q11] = 2 | q11 : int(1..3)]), - !cut2 <-> or([x_ExplicitVarSizeWithDummy[q13] != 4 /\ x_ExplicitVarSizeWithDummy[q13] = 1 | q13 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 4 - | q1 : int(1..2)]), - and([x_ExplicitVarSizeWithDummy[q2] = 4 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 4 | q2 : int(1..2)]), - and([x_Occurrence[q14] -> - or([x_ExplicitVarSizeWithDummy[q16] != 4 /\ x_ExplicitVarSizeWithDummy[q16] = q14 | q16 : int(1..3)]) - | q14 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q18] != 4 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q18]] | q18 : int(1..3)]) - diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_2_2-solution000001.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_2_2-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_2_2_2-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_2_2-solution000002.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_2_2-solution000002.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_2_2_2-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_2_2-solution000003.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_2_2-solution000003.solution deleted file mode 100644 index a28b6d6203..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_2_2_2-solution000003.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_2_2-solution000004.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_2_2-solution000004.solution deleted file mode 100644 index de5cc861ad..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_2_2_2-solution000004.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_2_2-solution000005.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_2_2-solution000005.solution deleted file mode 100644 index 8dddb3b359..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_2_2_2-solution000005.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_2_2-solution000006.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_2_2-solution000006.solution deleted file mode 100644 index 76bc8cdc32..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_2_2_2-solution000006.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_2_2-solution000007.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_2_2-solution000007.solution deleted file mode 100644 index 86a85825b3..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_2_2_2-solution000007.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_2_2-solution000008.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_2_2-solution000008.solution deleted file mode 100644 index 1a734343d9..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_2_2_2-solution000008.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_2_2.eprime b/tests/exhaustive/basic/cut_01_on/expected/model_2_2_2.eprime deleted file mode 100644 index f368d3342a..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_2_2_2.eprime +++ /dev/null @@ -1,15 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..3)] of int(1..4) -find cut1: bool -find cut2: bool -branching on [cut1, cut2, x_ExplicitVarSizeWithDummy] -such that - !cut1 <-> - or([x_ExplicitVarSizeWithDummy[q8] != 4 /\ x_ExplicitVarSizeWithDummy[q8] = 1 | q8 : int(1..3)]) /\ - or([x_ExplicitVarSizeWithDummy[q10] != 4 /\ x_ExplicitVarSizeWithDummy[q10] = 2 | q10 : int(1..3)]), - !cut2 <-> or([x_ExplicitVarSizeWithDummy[q12] != 4 /\ x_ExplicitVarSizeWithDummy[q12] = 1 | q12 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 4 - | q1 : int(1..2)]), - and([x_ExplicitVarSizeWithDummy[q2] = 4 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 4 | q2 : int(1..2)]) - diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_2_3-solution000001.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_2_3-solution000001.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_2_2_3-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_2_3-solution000002.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_2_3-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_2_2_3-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_2_3-solution000003.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_2_3-solution000003.solution deleted file mode 100644 index de5cc861ad..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_2_2_3-solution000003.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_2_3-solution000004.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_2_3-solution000004.solution deleted file mode 100644 index a28b6d6203..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_2_2_3-solution000004.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_2_3-solution000005.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_2_3-solution000005.solution deleted file mode 100644 index 1a734343d9..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_2_2_3-solution000005.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_2_3-solution000006.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_2_3-solution000006.solution deleted file mode 100644 index 76bc8cdc32..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_2_2_3-solution000006.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_2_3-solution000007.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_2_3-solution000007.solution deleted file mode 100644 index 86a85825b3..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_2_2_3-solution000007.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_2_3-solution000008.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_2_3-solution000008.solution deleted file mode 100644 index 8dddb3b359..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_2_2_3-solution000008.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_2_3.eprime b/tests/exhaustive/basic/cut_01_on/expected/model_2_2_3.eprime deleted file mode 100644 index 9e927fda51..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_2_2_3.eprime +++ /dev/null @@ -1,32 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..3)] of int(1..4) -find x_ExplicitVarSizeWithMarker_Marker: int(0..3) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3)] of int(1..3) -find cut1: bool -find cut2: bool -branching on - [cut1, cut2, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy] -such that - !cut1 <-> - or([x_ExplicitVarSizeWithDummy[q19] != 4 /\ x_ExplicitVarSizeWithDummy[q19] = 1 | q19 : int(1..3)]) /\ - or([x_ExplicitVarSizeWithDummy[q21] != 4 /\ x_ExplicitVarSizeWithDummy[q21] = 2 | q21 : int(1..3)]), - !cut2 <-> or([x_ExplicitVarSizeWithDummy[q23] != 4 /\ x_ExplicitVarSizeWithDummy[q23] = 1 | q23 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 4 - | q1 : int(1..2)]), - and([x_ExplicitVarSizeWithDummy[q2] = 4 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 4 | q2 : int(1..2)]), - and([q5 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q5] < x_ExplicitVarSizeWithMarker_Values[q5 + 1] - | q5 : int(1..2)]), - and([q6 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q6] = 1 | q6 : int(1..3)]), - and([q9 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q11] != 4 /\ - x_ExplicitVarSizeWithDummy[q11] = x_ExplicitVarSizeWithMarker_Values[q9] - | q11 : int(1..3)]) - | q9 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q13] != 4 -> - or([q15 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q15] = x_ExplicitVarSizeWithDummy[q13] - | q15 : int(1..3)]) - | q13 : int(1..3)]) - diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_2_4-solution000001.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_2_4-solution000001.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_2_2_4-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_2_4-solution000002.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_2_4-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_2_2_4-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_2_4-solution000003.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_2_4-solution000003.solution deleted file mode 100644 index de5cc861ad..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_2_2_4-solution000003.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_2_4-solution000004.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_2_4-solution000004.solution deleted file mode 100644 index a28b6d6203..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_2_2_4-solution000004.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_2_4-solution000005.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_2_4-solution000005.solution deleted file mode 100644 index 1a734343d9..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_2_2_4-solution000005.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_2_4-solution000006.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_2_4-solution000006.solution deleted file mode 100644 index 76bc8cdc32..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_2_2_4-solution000006.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_2_4-solution000007.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_2_4-solution000007.solution deleted file mode 100644 index 86a85825b3..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_2_2_4-solution000007.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_2_4-solution000008.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_2_4-solution000008.solution deleted file mode 100644 index 8dddb3b359..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_2_2_4-solution000008.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_2_4.eprime b/tests/exhaustive/basic/cut_01_on/expected/model_2_2_4.eprime deleted file mode 100644 index 2ee07dcba1..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_2_2_4.eprime +++ /dev/null @@ -1,33 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..3)] of int(1..4) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..3)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3)] of int(1..3) -find cut1: bool -find cut2: bool -branching on - [cut1, cut2, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy] -such that - !cut1 <-> - or([x_ExplicitVarSizeWithDummy[q21] != 4 /\ x_ExplicitVarSizeWithDummy[q21] = 1 | q21 : int(1..3)]) /\ - or([x_ExplicitVarSizeWithDummy[q23] != 4 /\ x_ExplicitVarSizeWithDummy[q23] = 2 | q23 : int(1..3)]), - !cut2 <-> or([x_ExplicitVarSizeWithDummy[q25] != 4 /\ x_ExplicitVarSizeWithDummy[q25] = 1 | q25 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 4 - | q1 : int(1..2)]), - and([x_ExplicitVarSizeWithDummy[q2] = 4 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 4 | q2 : int(1..2)]), - and([x_ExplicitVarSizeWithFlags_Flags[q5 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q5] < x_ExplicitVarSizeWithFlags_Values[q5 + 1] - | q5 : int(1..2)]), - and([x_ExplicitVarSizeWithFlags_Flags[q6] = false -> x_ExplicitVarSizeWithFlags_Values[q6] = 1 | q6 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q7] | q7 : int(1..2)]), - and([x_ExplicitVarSizeWithFlags_Flags[q11] -> - or([x_ExplicitVarSizeWithDummy[q13] != 4 /\ - x_ExplicitVarSizeWithDummy[q13] = x_ExplicitVarSizeWithFlags_Values[q11] - | q13 : int(1..3)]) - | q11 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q15] != 4 -> - or([x_ExplicitVarSizeWithFlags_Flags[q17] /\ - x_ExplicitVarSizeWithFlags_Values[q17] = x_ExplicitVarSizeWithDummy[q15] - | q17 : int(1..3)]) - | q15 : int(1..3)]) - diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_3_1-solution000001.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_3_1-solution000001.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_2_3_1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_3_1-solution000002.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_3_1-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_2_3_1-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_3_1-solution000003.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_3_1-solution000003.solution deleted file mode 100644 index de5cc861ad..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_2_3_1-solution000003.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_3_1-solution000004.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_3_1-solution000004.solution deleted file mode 100644 index a28b6d6203..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_2_3_1-solution000004.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_3_1-solution000005.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_3_1-solution000005.solution deleted file mode 100644 index 1a734343d9..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_2_3_1-solution000005.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_3_1-solution000006.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_3_1-solution000006.solution deleted file mode 100644 index 86a85825b3..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_2_3_1-solution000006.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_3_1-solution000007.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_3_1-solution000007.solution deleted file mode 100644 index 76bc8cdc32..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_2_3_1-solution000007.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_3_1-solution000008.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_3_1-solution000008.solution deleted file mode 100644 index 8dddb3b359..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_2_3_1-solution000008.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_3_1.eprime b/tests/exhaustive/basic/cut_01_on/expected/model_2_3_1.eprime deleted file mode 100644 index da2f0f3189..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_2_3_1.eprime +++ /dev/null @@ -1,45 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..3)] of int(1..4) -find x_ExplicitVarSizeWithMarker_Marker: int(0..3) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3)] of int(1..3) -find x_Occurrence: matrix indexed by [int(1..3)] of bool -find cut1: bool -find cut2: bool -branching on - [cut1, cut2, x_Occurrence, x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithMarker_Marker, - x_ExplicitVarSizeWithMarker_Values] -such that - !cut1 <-> - or([x_ExplicitVarSizeWithDummy[q20] != 4 /\ x_ExplicitVarSizeWithDummy[q20] = 1 | q20 : int(1..3)]) /\ - or([x_ExplicitVarSizeWithDummy[q22] != 4 /\ x_ExplicitVarSizeWithDummy[q22] = 2 | q22 : int(1..3)]), - !cut2 <-> - or([q24 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q24] = 1 | q24 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 4 - | q1 : int(1..2)]), - and([x_ExplicitVarSizeWithDummy[q2] = 4 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 4 | q2 : int(1..2)]), - and([q5 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q5] < x_ExplicitVarSizeWithMarker_Values[q5 + 1] - | q5 : int(1..2)]), - and([q6 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q6] = 1 | q6 : int(1..3)]), - and([q9 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q11] != 4 /\ - x_ExplicitVarSizeWithDummy[q11] = x_ExplicitVarSizeWithMarker_Values[q9] - | q11 : int(1..3)]) - | q9 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q13] != 4 -> - or([q15 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q15] = x_ExplicitVarSizeWithDummy[q13] - | q15 : int(1..3)]) - | q13 : int(1..3)]), - and([x_Occurrence[q25] -> - or([x_ExplicitVarSizeWithDummy[q27] != 4 /\ x_ExplicitVarSizeWithDummy[q27] = q25 | q27 : int(1..3)]) - | q25 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q29] != 4 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q29]] | q29 : int(1..3)]), - and([x_Occurrence[q30] -> - or([q32 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q32] = q30 - | q32 : int(1..3)]) - | q30 : int(1..3)]), - and([q34 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q34]] - | q34 : int(1..3)]) - diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_3_2-solution000001.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_3_2-solution000001.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_2_3_2-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_3_2-solution000002.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_3_2-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_2_3_2-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_3_2-solution000003.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_3_2-solution000003.solution deleted file mode 100644 index de5cc861ad..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_2_3_2-solution000003.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_3_2-solution000004.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_3_2-solution000004.solution deleted file mode 100644 index a28b6d6203..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_2_3_2-solution000004.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_3_2-solution000005.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_3_2-solution000005.solution deleted file mode 100644 index 1a734343d9..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_2_3_2-solution000005.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_3_2-solution000006.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_3_2-solution000006.solution deleted file mode 100644 index 76bc8cdc32..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_2_3_2-solution000006.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_3_2-solution000007.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_3_2-solution000007.solution deleted file mode 100644 index 86a85825b3..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_2_3_2-solution000007.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_3_2-solution000008.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_3_2-solution000008.solution deleted file mode 100644 index 8dddb3b359..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_2_3_2-solution000008.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_3_2.eprime b/tests/exhaustive/basic/cut_01_on/expected/model_2_3_2.eprime deleted file mode 100644 index e8d3dacd6c..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_2_3_2.eprime +++ /dev/null @@ -1,33 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..3)] of int(1..4) -find x_ExplicitVarSizeWithMarker_Marker: int(0..3) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3)] of int(1..3) -find cut1: bool -find cut2: bool -branching on - [cut1, cut2, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy] -such that - !cut1 <-> - or([x_ExplicitVarSizeWithDummy[q19] != 4 /\ x_ExplicitVarSizeWithDummy[q19] = 1 | q19 : int(1..3)]) /\ - or([x_ExplicitVarSizeWithDummy[q21] != 4 /\ x_ExplicitVarSizeWithDummy[q21] = 2 | q21 : int(1..3)]), - !cut2 <-> - or([q23 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q23] = 1 | q23 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 4 - | q1 : int(1..2)]), - and([x_ExplicitVarSizeWithDummy[q2] = 4 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 4 | q2 : int(1..2)]), - and([q5 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q5] < x_ExplicitVarSizeWithMarker_Values[q5 + 1] - | q5 : int(1..2)]), - and([q6 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q6] = 1 | q6 : int(1..3)]), - and([q9 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q11] != 4 /\ - x_ExplicitVarSizeWithDummy[q11] = x_ExplicitVarSizeWithMarker_Values[q9] - | q11 : int(1..3)]) - | q9 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q13] != 4 -> - or([q15 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q15] = x_ExplicitVarSizeWithDummy[q13] - | q15 : int(1..3)]) - | q13 : int(1..3)]) - diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_3_3-solution000001.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_3_3-solution000001.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_2_3_3-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_3_3-solution000002.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_3_3-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_2_3_3-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_3_3-solution000003.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_3_3-solution000003.solution deleted file mode 100644 index de5cc861ad..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_2_3_3-solution000003.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_3_3-solution000004.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_3_3-solution000004.solution deleted file mode 100644 index a28b6d6203..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_2_3_3-solution000004.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_3_3-solution000005.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_3_3-solution000005.solution deleted file mode 100644 index 1a734343d9..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_2_3_3-solution000005.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_3_3-solution000006.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_3_3-solution000006.solution deleted file mode 100644 index 76bc8cdc32..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_2_3_3-solution000006.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_3_3-solution000007.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_3_3-solution000007.solution deleted file mode 100644 index 86a85825b3..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_2_3_3-solution000007.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_3_3-solution000008.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_3_3-solution000008.solution deleted file mode 100644 index 8dddb3b359..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_2_3_3-solution000008.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_3_3.eprime b/tests/exhaustive/basic/cut_01_on/expected/model_2_3_3.eprime deleted file mode 100644 index e8d3dacd6c..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_2_3_3.eprime +++ /dev/null @@ -1,33 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..3)] of int(1..4) -find x_ExplicitVarSizeWithMarker_Marker: int(0..3) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3)] of int(1..3) -find cut1: bool -find cut2: bool -branching on - [cut1, cut2, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy] -such that - !cut1 <-> - or([x_ExplicitVarSizeWithDummy[q19] != 4 /\ x_ExplicitVarSizeWithDummy[q19] = 1 | q19 : int(1..3)]) /\ - or([x_ExplicitVarSizeWithDummy[q21] != 4 /\ x_ExplicitVarSizeWithDummy[q21] = 2 | q21 : int(1..3)]), - !cut2 <-> - or([q23 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q23] = 1 | q23 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 4 - | q1 : int(1..2)]), - and([x_ExplicitVarSizeWithDummy[q2] = 4 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 4 | q2 : int(1..2)]), - and([q5 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q5] < x_ExplicitVarSizeWithMarker_Values[q5 + 1] - | q5 : int(1..2)]), - and([q6 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q6] = 1 | q6 : int(1..3)]), - and([q9 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q11] != 4 /\ - x_ExplicitVarSizeWithDummy[q11] = x_ExplicitVarSizeWithMarker_Values[q9] - | q11 : int(1..3)]) - | q9 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q13] != 4 -> - or([q15 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q15] = x_ExplicitVarSizeWithDummy[q13] - | q15 : int(1..3)]) - | q13 : int(1..3)]) - diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_3_4-solution000001.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_3_4-solution000001.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_2_3_4-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_3_4-solution000002.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_3_4-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_2_3_4-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_3_4-solution000003.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_3_4-solution000003.solution deleted file mode 100644 index de5cc861ad..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_2_3_4-solution000003.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_3_4-solution000004.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_3_4-solution000004.solution deleted file mode 100644 index a28b6d6203..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_2_3_4-solution000004.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_3_4-solution000005.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_3_4-solution000005.solution deleted file mode 100644 index 1a734343d9..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_2_3_4-solution000005.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_3_4-solution000006.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_3_4-solution000006.solution deleted file mode 100644 index 76bc8cdc32..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_2_3_4-solution000006.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_3_4-solution000007.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_3_4-solution000007.solution deleted file mode 100644 index 86a85825b3..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_2_3_4-solution000007.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_3_4-solution000008.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_3_4-solution000008.solution deleted file mode 100644 index 8dddb3b359..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_2_3_4-solution000008.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_3_4.eprime b/tests/exhaustive/basic/cut_01_on/expected/model_2_3_4.eprime deleted file mode 100644 index 4db2c0e62f..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_2_3_4.eprime +++ /dev/null @@ -1,62 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..3)] of int(1..4) -find x_ExplicitVarSizeWithMarker_Marker: int(0..3) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3)] of int(1..3) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..3)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3)] of int(1..3) -find cut1: bool -find cut2: bool -branching on - [cut1, cut2, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy, - x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] -such that - !cut1 <-> - or([x_ExplicitVarSizeWithDummy[q40] != 4 /\ x_ExplicitVarSizeWithDummy[q40] = 1 | q40 : int(1..3)]) /\ - or([x_ExplicitVarSizeWithDummy[q42] != 4 /\ x_ExplicitVarSizeWithDummy[q42] = 2 | q42 : int(1..3)]), - !cut2 <-> - or([q44 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q44] = 1 | q44 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 4 - | q1 : int(1..2)]), - and([x_ExplicitVarSizeWithDummy[q2] = 4 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 4 | q2 : int(1..2)]), - and([q5 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q5] < x_ExplicitVarSizeWithMarker_Values[q5 + 1] - | q5 : int(1..2)]), - and([q6 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q6] = 1 | q6 : int(1..3)]), - and([q9 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q11] != 4 /\ - x_ExplicitVarSizeWithDummy[q11] = x_ExplicitVarSizeWithMarker_Values[q9] - | q11 : int(1..3)]) - | q9 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q13] != 4 -> - or([q15 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q15] = x_ExplicitVarSizeWithDummy[q13] - | q15 : int(1..3)]) - | q13 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q16 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q16] < x_ExplicitVarSizeWithFlags_Values[q16 + 1] - | q16 : int(1..2)]), - and([x_ExplicitVarSizeWithFlags_Flags[q17] = false -> x_ExplicitVarSizeWithFlags_Values[q17] = 1 - | q17 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q18 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q18] | q18 : int(1..2)]), - and([x_ExplicitVarSizeWithFlags_Flags[q22] -> - or([x_ExplicitVarSizeWithDummy[q24] != 4 /\ - x_ExplicitVarSizeWithDummy[q24] = x_ExplicitVarSizeWithFlags_Values[q22] - | q24 : int(1..3)]) - | q22 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q26] != 4 -> - or([x_ExplicitVarSizeWithFlags_Flags[q28] /\ - x_ExplicitVarSizeWithFlags_Values[q28] = x_ExplicitVarSizeWithDummy[q26] - | q28 : int(1..3)]) - | q26 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q30] -> - or([q32 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q32] = x_ExplicitVarSizeWithFlags_Values[q30] - | q32 : int(1..3)]) - | q30 : int(1..3)]), - and([q34 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q36] /\ - x_ExplicitVarSizeWithFlags_Values[q36] = x_ExplicitVarSizeWithMarker_Values[q34] - | q36 : int(1..3)]) - | q34 : int(1..3)]) - diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_4_1-solution000001.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_4_1-solution000001.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_2_4_1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_4_1-solution000002.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_4_1-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_2_4_1-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_4_1-solution000003.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_4_1-solution000003.solution deleted file mode 100644 index de5cc861ad..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_2_4_1-solution000003.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_4_1-solution000004.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_4_1-solution000004.solution deleted file mode 100644 index a28b6d6203..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_2_4_1-solution000004.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_4_1-solution000005.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_4_1-solution000005.solution deleted file mode 100644 index 1a734343d9..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_2_4_1-solution000005.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_4_1-solution000006.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_4_1-solution000006.solution deleted file mode 100644 index 86a85825b3..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_2_4_1-solution000006.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_4_1-solution000007.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_4_1-solution000007.solution deleted file mode 100644 index 76bc8cdc32..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_2_4_1-solution000007.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_4_1-solution000008.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_4_1-solution000008.solution deleted file mode 100644 index 8dddb3b359..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_2_4_1-solution000008.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_4_1.eprime b/tests/exhaustive/basic/cut_01_on/expected/model_2_4_1.eprime deleted file mode 100644 index fc0621d440..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_2_4_1.eprime +++ /dev/null @@ -1,45 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..3)] of int(1..4) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..3)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3)] of int(1..3) -find x_Occurrence: matrix indexed by [int(1..3)] of bool -find cut1: bool -find cut2: bool -branching on - [cut1, cut2, x_Occurrence, x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithFlags_Flags, - x_ExplicitVarSizeWithFlags_Values] -such that - !cut1 <-> - or([x_ExplicitVarSizeWithDummy[q32] != 4 /\ x_ExplicitVarSizeWithDummy[q32] = 1 | q32 : int(1..3)]) /\ - or([x_ExplicitVarSizeWithDummy[q34] != 4 /\ x_ExplicitVarSizeWithDummy[q34] = 2 | q34 : int(1..3)]), - !cut2 <-> - or([x_ExplicitVarSizeWithFlags_Flags[q36] /\ x_ExplicitVarSizeWithFlags_Values[q36] = 1 | q36 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 4 - | q1 : int(1..2)]), - and([x_ExplicitVarSizeWithDummy[q2] = 4 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 4 | q2 : int(1..2)]), - and([x_ExplicitVarSizeWithFlags_Flags[q5 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q5] < x_ExplicitVarSizeWithFlags_Values[q5 + 1] - | q5 : int(1..2)]), - and([x_ExplicitVarSizeWithFlags_Flags[q6] = false -> x_ExplicitVarSizeWithFlags_Values[q6] = 1 | q6 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q7] | q7 : int(1..2)]), - and([x_ExplicitVarSizeWithFlags_Flags[q11] -> - or([x_ExplicitVarSizeWithDummy[q13] != 4 /\ - x_ExplicitVarSizeWithDummy[q13] = x_ExplicitVarSizeWithFlags_Values[q11] - | q13 : int(1..3)]) - | q11 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q15] != 4 -> - or([x_ExplicitVarSizeWithFlags_Flags[q17] /\ - x_ExplicitVarSizeWithFlags_Values[q17] = x_ExplicitVarSizeWithDummy[q15] - | q17 : int(1..3)]) - | q15 : int(1..3)]), - and([x_Occurrence[q19] -> - or([x_ExplicitVarSizeWithDummy[q21] != 4 /\ x_ExplicitVarSizeWithDummy[q21] = q19 | q21 : int(1..3)]) - | q19 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q23] != 4 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q23]] | q23 : int(1..3)]), - and([x_Occurrence[q24] -> - or([x_ExplicitVarSizeWithFlags_Flags[q26] /\ x_ExplicitVarSizeWithFlags_Values[q26] = q24 | q26 : int(1..3)]) - | q24 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q28] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q28]] - | q28 : int(1..3)]) - diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_4_2-solution000001.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_4_2-solution000001.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_2_4_2-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_4_2-solution000002.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_4_2-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_2_4_2-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_4_2-solution000003.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_4_2-solution000003.solution deleted file mode 100644 index de5cc861ad..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_2_4_2-solution000003.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_4_2-solution000004.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_4_2-solution000004.solution deleted file mode 100644 index a28b6d6203..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_2_4_2-solution000004.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_4_2-solution000005.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_4_2-solution000005.solution deleted file mode 100644 index 1a734343d9..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_2_4_2-solution000005.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_4_2-solution000006.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_4_2-solution000006.solution deleted file mode 100644 index 76bc8cdc32..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_2_4_2-solution000006.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_4_2-solution000007.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_4_2-solution000007.solution deleted file mode 100644 index 86a85825b3..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_2_4_2-solution000007.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_4_2-solution000008.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_4_2-solution000008.solution deleted file mode 100644 index 8dddb3b359..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_2_4_2-solution000008.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_4_2.eprime b/tests/exhaustive/basic/cut_01_on/expected/model_2_4_2.eprime deleted file mode 100644 index 57bef0dd8e..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_2_4_2.eprime +++ /dev/null @@ -1,34 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..3)] of int(1..4) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..3)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3)] of int(1..3) -find cut1: bool -find cut2: bool -branching on - [cut1, cut2, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy] -such that - !cut1 <-> - or([x_ExplicitVarSizeWithDummy[q21] != 4 /\ x_ExplicitVarSizeWithDummy[q21] = 1 | q21 : int(1..3)]) /\ - or([x_ExplicitVarSizeWithDummy[q23] != 4 /\ x_ExplicitVarSizeWithDummy[q23] = 2 | q23 : int(1..3)]), - !cut2 <-> - or([x_ExplicitVarSizeWithFlags_Flags[q25] /\ x_ExplicitVarSizeWithFlags_Values[q25] = 1 | q25 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 4 - | q1 : int(1..2)]), - and([x_ExplicitVarSizeWithDummy[q2] = 4 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 4 | q2 : int(1..2)]), - and([x_ExplicitVarSizeWithFlags_Flags[q5 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q5] < x_ExplicitVarSizeWithFlags_Values[q5 + 1] - | q5 : int(1..2)]), - and([x_ExplicitVarSizeWithFlags_Flags[q6] = false -> x_ExplicitVarSizeWithFlags_Values[q6] = 1 | q6 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q7] | q7 : int(1..2)]), - and([x_ExplicitVarSizeWithFlags_Flags[q11] -> - or([x_ExplicitVarSizeWithDummy[q13] != 4 /\ - x_ExplicitVarSizeWithDummy[q13] = x_ExplicitVarSizeWithFlags_Values[q11] - | q13 : int(1..3)]) - | q11 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q15] != 4 -> - or([x_ExplicitVarSizeWithFlags_Flags[q17] /\ - x_ExplicitVarSizeWithFlags_Values[q17] = x_ExplicitVarSizeWithDummy[q15] - | q17 : int(1..3)]) - | q15 : int(1..3)]) - diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_4_3-solution000001.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_4_3-solution000001.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_2_4_3-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_4_3-solution000002.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_4_3-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_2_4_3-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_4_3-solution000003.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_4_3-solution000003.solution deleted file mode 100644 index de5cc861ad..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_2_4_3-solution000003.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_4_3-solution000004.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_4_3-solution000004.solution deleted file mode 100644 index a28b6d6203..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_2_4_3-solution000004.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_4_3-solution000005.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_4_3-solution000005.solution deleted file mode 100644 index 1a734343d9..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_2_4_3-solution000005.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_4_3-solution000006.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_4_3-solution000006.solution deleted file mode 100644 index 76bc8cdc32..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_2_4_3-solution000006.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_4_3-solution000007.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_4_3-solution000007.solution deleted file mode 100644 index 86a85825b3..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_2_4_3-solution000007.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_4_3-solution000008.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_4_3-solution000008.solution deleted file mode 100644 index 8dddb3b359..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_2_4_3-solution000008.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_4_3.eprime b/tests/exhaustive/basic/cut_01_on/expected/model_2_4_3.eprime deleted file mode 100644 index 4011d9426c..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_2_4_3.eprime +++ /dev/null @@ -1,61 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..3)] of int(1..4) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..3)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3)] of int(1..3) -find x_ExplicitVarSizeWithMarker_Marker: int(0..3) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3)] of int(1..3) -find cut1: bool -find cut2: bool -branching on - [cut1, cut2, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy, - x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] -such that - !cut1 <-> - or([x_ExplicitVarSizeWithDummy[q40] != 4 /\ x_ExplicitVarSizeWithDummy[q40] = 1 | q40 : int(1..3)]) /\ - or([x_ExplicitVarSizeWithDummy[q42] != 4 /\ x_ExplicitVarSizeWithDummy[q42] = 2 | q42 : int(1..3)]), - !cut2 <-> - or([x_ExplicitVarSizeWithFlags_Flags[q44] /\ x_ExplicitVarSizeWithFlags_Values[q44] = 1 | q44 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 4 - | q1 : int(1..2)]), - and([x_ExplicitVarSizeWithDummy[q2] = 4 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 4 | q2 : int(1..2)]), - and([x_ExplicitVarSizeWithFlags_Flags[q5 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q5] < x_ExplicitVarSizeWithFlags_Values[q5 + 1] - | q5 : int(1..2)]), - and([x_ExplicitVarSizeWithFlags_Flags[q6] = false -> x_ExplicitVarSizeWithFlags_Values[q6] = 1 | q6 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q7] | q7 : int(1..2)]), - and([x_ExplicitVarSizeWithFlags_Flags[q11] -> - or([x_ExplicitVarSizeWithDummy[q13] != 4 /\ - x_ExplicitVarSizeWithDummy[q13] = x_ExplicitVarSizeWithFlags_Values[q11] - | q13 : int(1..3)]) - | q11 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q15] != 4 -> - or([x_ExplicitVarSizeWithFlags_Flags[q17] /\ - x_ExplicitVarSizeWithFlags_Values[q17] = x_ExplicitVarSizeWithDummy[q15] - | q17 : int(1..3)]) - | q15 : int(1..3)]), - and([q18 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q18] < x_ExplicitVarSizeWithMarker_Values[q18 + 1] - | q18 : int(1..2)]), - and([q19 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q19] = 1 | q19 : int(1..3)]), - and([q22 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q24] != 4 /\ - x_ExplicitVarSizeWithDummy[q24] = x_ExplicitVarSizeWithMarker_Values[q22] - | q24 : int(1..3)]) - | q22 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q26] != 4 -> - or([q28 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q28] = x_ExplicitVarSizeWithDummy[q26] - | q28 : int(1..3)]) - | q26 : int(1..3)]), - and([q30 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q32] /\ - x_ExplicitVarSizeWithFlags_Values[q32] = x_ExplicitVarSizeWithMarker_Values[q30] - | q32 : int(1..3)]) - | q30 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q34] -> - or([q36 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q36] = x_ExplicitVarSizeWithFlags_Values[q34] - | q36 : int(1..3)]) - | q34 : int(1..3)]) - diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_4_4-solution000001.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_4_4-solution000001.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_2_4_4-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_4_4-solution000002.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_4_4-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_2_4_4-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_4_4-solution000003.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_4_4-solution000003.solution deleted file mode 100644 index de5cc861ad..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_2_4_4-solution000003.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_4_4-solution000004.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_4_4-solution000004.solution deleted file mode 100644 index a28b6d6203..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_2_4_4-solution000004.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_4_4-solution000005.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_4_4-solution000005.solution deleted file mode 100644 index 1a734343d9..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_2_4_4-solution000005.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_4_4-solution000006.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_4_4-solution000006.solution deleted file mode 100644 index 76bc8cdc32..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_2_4_4-solution000006.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_4_4-solution000007.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_4_4-solution000007.solution deleted file mode 100644 index 86a85825b3..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_2_4_4-solution000007.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_4_4-solution000008.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_4_4-solution000008.solution deleted file mode 100644 index 8dddb3b359..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_2_4_4-solution000008.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_4_4.eprime b/tests/exhaustive/basic/cut_01_on/expected/model_2_4_4.eprime deleted file mode 100644 index 57bef0dd8e..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_2_4_4.eprime +++ /dev/null @@ -1,34 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..3)] of int(1..4) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..3)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3)] of int(1..3) -find cut1: bool -find cut2: bool -branching on - [cut1, cut2, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy] -such that - !cut1 <-> - or([x_ExplicitVarSizeWithDummy[q21] != 4 /\ x_ExplicitVarSizeWithDummy[q21] = 1 | q21 : int(1..3)]) /\ - or([x_ExplicitVarSizeWithDummy[q23] != 4 /\ x_ExplicitVarSizeWithDummy[q23] = 2 | q23 : int(1..3)]), - !cut2 <-> - or([x_ExplicitVarSizeWithFlags_Flags[q25] /\ x_ExplicitVarSizeWithFlags_Values[q25] = 1 | q25 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 4 - | q1 : int(1..2)]), - and([x_ExplicitVarSizeWithDummy[q2] = 4 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 4 | q2 : int(1..2)]), - and([x_ExplicitVarSizeWithFlags_Flags[q5 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q5] < x_ExplicitVarSizeWithFlags_Values[q5 + 1] - | q5 : int(1..2)]), - and([x_ExplicitVarSizeWithFlags_Flags[q6] = false -> x_ExplicitVarSizeWithFlags_Values[q6] = 1 | q6 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q7] | q7 : int(1..2)]), - and([x_ExplicitVarSizeWithFlags_Flags[q11] -> - or([x_ExplicitVarSizeWithDummy[q13] != 4 /\ - x_ExplicitVarSizeWithDummy[q13] = x_ExplicitVarSizeWithFlags_Values[q11] - | q13 : int(1..3)]) - | q11 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q15] != 4 -> - or([x_ExplicitVarSizeWithFlags_Flags[q17] /\ - x_ExplicitVarSizeWithFlags_Values[q17] = x_ExplicitVarSizeWithDummy[q15] - | q17 : int(1..3)]) - | q15 : int(1..3)]) - diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_1_1-solution000001.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_1_1-solution000001.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_3_1_1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_1_1-solution000002.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_1_1-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_3_1_1-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_1_1-solution000003.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_1_1-solution000003.solution deleted file mode 100644 index de5cc861ad..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_3_1_1-solution000003.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_1_1-solution000004.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_1_1-solution000004.solution deleted file mode 100644 index a28b6d6203..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_3_1_1-solution000004.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_1_1-solution000005.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_1_1-solution000005.solution deleted file mode 100644 index 1a734343d9..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_3_1_1-solution000005.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_1_1-solution000006.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_1_1-solution000006.solution deleted file mode 100644 index 86a85825b3..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_3_1_1-solution000006.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_1_1-solution000007.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_1_1-solution000007.solution deleted file mode 100644 index 76bc8cdc32..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_3_1_1-solution000007.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_1_1-solution000008.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_1_1-solution000008.solution deleted file mode 100644 index 8dddb3b359..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_3_1_1-solution000008.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_1_1.eprime b/tests/exhaustive/basic/cut_01_on/expected/model_3_1_1.eprime deleted file mode 100644 index 8661f2b36d..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_3_1_1.eprime +++ /dev/null @@ -1,23 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..3) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3)] of int(1..3) -find x_Occurrence: matrix indexed by [int(1..3)] of bool -find cut1: bool -find cut2: bool -branching on [cut1, cut2, x_Occurrence, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] -such that - !cut1 <-> - or([q13 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q13] = 1 | q13 : int(1..3)]) /\ - or([q15 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q15] = 2 | q15 : int(1..3)]), - !cut2 <-> x_Occurrence[1], - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..2)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..3)]), - and([x_Occurrence[q5] -> - or([q7 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q7] = q5 | q7 : int(1..3)]) - | q5 : int(1..3)]), - and([q9 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q9]] - | q9 : int(1..3)]) - diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_1_2-solution000001.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_1_2-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_3_1_2-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_1_2-solution000002.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_1_2-solution000002.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_3_1_2-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_1_2-solution000003.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_1_2-solution000003.solution deleted file mode 100644 index a28b6d6203..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_3_1_2-solution000003.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_1_2-solution000004.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_1_2-solution000004.solution deleted file mode 100644 index de5cc861ad..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_3_1_2-solution000004.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_1_2-solution000005.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_1_2-solution000005.solution deleted file mode 100644 index 8dddb3b359..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_3_1_2-solution000005.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_1_2-solution000006.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_1_2-solution000006.solution deleted file mode 100644 index 76bc8cdc32..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_3_1_2-solution000006.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_1_2-solution000007.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_1_2-solution000007.solution deleted file mode 100644 index 86a85825b3..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_3_1_2-solution000007.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_1_2-solution000008.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_1_2-solution000008.solution deleted file mode 100644 index 1a734343d9..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_3_1_2-solution000008.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_1_2.eprime b/tests/exhaustive/basic/cut_01_on/expected/model_3_1_2.eprime deleted file mode 100644 index 6e1c73ebb0..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_3_1_2.eprime +++ /dev/null @@ -1,44 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..3) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3)] of int(1..3) -find x_Occurrence: matrix indexed by [int(1..3)] of bool -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..3)] of int(1..4) -find cut1: bool -find cut2: bool -branching on - [cut1, cut2, x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, - x_Occurrence] -such that - !cut1 <-> - or([q30 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q30] = 1 | q30 : int(1..3)]) /\ - or([q32 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q32] = 2 | q32 : int(1..3)]), - !cut2 <-> x_Occurrence[1], - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..2)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..3)]), - and([x_Occurrence[q22] -> - or([q24 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q24] = q22 - | q24 : int(1..3)]) - | q22 : int(1..3)]), - and([q26 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q26]] - | q26 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q5] < x_ExplicitVarSizeWithDummy[q5 + 1] \/ x_ExplicitVarSizeWithDummy[q5] = 4 - | q5 : int(1..2)]), - and([x_ExplicitVarSizeWithDummy[q6] = 4 -> x_ExplicitVarSizeWithDummy[q6 + 1] = 4 | q6 : int(1..2)]), - and([x_ExplicitVarSizeWithDummy[q10] != 4 -> - or([q12 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q12] = x_ExplicitVarSizeWithDummy[q10] - | q12 : int(1..3)]) - | q10 : int(1..3)]), - and([q14 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q16] != 4 /\ - x_ExplicitVarSizeWithDummy[q16] = x_ExplicitVarSizeWithMarker_Values[q14] - | q16 : int(1..3)]) - | q14 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q18] != 4 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q18]] | q18 : int(1..3)]), - and([x_Occurrence[q19] -> - or([x_ExplicitVarSizeWithDummy[q21] != 4 /\ x_ExplicitVarSizeWithDummy[q21] = q19 | q21 : int(1..3)]) - | q19 : int(1..3)]) - diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_1_3-solution000001.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_1_3-solution000001.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_3_1_3-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_1_3-solution000002.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_1_3-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_3_1_3-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_1_3-solution000003.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_1_3-solution000003.solution deleted file mode 100644 index de5cc861ad..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_3_1_3-solution000003.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_1_3-solution000004.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_1_3-solution000004.solution deleted file mode 100644 index a28b6d6203..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_3_1_3-solution000004.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_1_3-solution000005.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_1_3-solution000005.solution deleted file mode 100644 index 1a734343d9..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_3_1_3-solution000005.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_1_3-solution000006.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_1_3-solution000006.solution deleted file mode 100644 index 86a85825b3..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_3_1_3-solution000006.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_1_3-solution000007.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_1_3-solution000007.solution deleted file mode 100644 index 76bc8cdc32..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_3_1_3-solution000007.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_1_3-solution000008.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_1_3-solution000008.solution deleted file mode 100644 index 8dddb3b359..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_3_1_3-solution000008.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_1_3.eprime b/tests/exhaustive/basic/cut_01_on/expected/model_3_1_3.eprime deleted file mode 100644 index 8661f2b36d..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_3_1_3.eprime +++ /dev/null @@ -1,23 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..3) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3)] of int(1..3) -find x_Occurrence: matrix indexed by [int(1..3)] of bool -find cut1: bool -find cut2: bool -branching on [cut1, cut2, x_Occurrence, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] -such that - !cut1 <-> - or([q13 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q13] = 1 | q13 : int(1..3)]) /\ - or([q15 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q15] = 2 | q15 : int(1..3)]), - !cut2 <-> x_Occurrence[1], - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..2)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..3)]), - and([x_Occurrence[q5] -> - or([q7 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q7] = q5 | q7 : int(1..3)]) - | q5 : int(1..3)]), - and([q9 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q9]] - | q9 : int(1..3)]) - diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_1_4-solution000001.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_1_4-solution000001.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_3_1_4-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_1_4-solution000002.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_1_4-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_3_1_4-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_1_4-solution000003.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_1_4-solution000003.solution deleted file mode 100644 index de5cc861ad..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_3_1_4-solution000003.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_1_4-solution000004.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_1_4-solution000004.solution deleted file mode 100644 index a28b6d6203..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_3_1_4-solution000004.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_1_4-solution000005.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_1_4-solution000005.solution deleted file mode 100644 index 1a734343d9..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_3_1_4-solution000005.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_1_4-solution000006.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_1_4-solution000006.solution deleted file mode 100644 index 76bc8cdc32..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_3_1_4-solution000006.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_1_4-solution000007.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_1_4-solution000007.solution deleted file mode 100644 index 86a85825b3..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_3_1_4-solution000007.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_1_4-solution000008.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_1_4-solution000008.solution deleted file mode 100644 index 8dddb3b359..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_3_1_4-solution000008.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_1_4.eprime b/tests/exhaustive/basic/cut_01_on/expected/model_3_1_4.eprime deleted file mode 100644 index 2f91d5c971..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_3_1_4.eprime +++ /dev/null @@ -1,48 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..3) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3)] of int(1..3) -find x_Occurrence: matrix indexed by [int(1..3)] of bool -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..3)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3)] of int(1..3) -find cut1: bool -find cut2: bool -branching on - [cut1, cut2, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, - x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_Occurrence] -such that - !cut1 <-> - or([q31 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q31] = 1 | q31 : int(1..3)]) /\ - or([q33 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q33] = 2 | q33 : int(1..3)]), - !cut2 <-> x_Occurrence[1], - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..2)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..3)]), - and([x_Occurrence[q23] -> - or([q25 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q25] = q23 - | q25 : int(1..3)]) - | q23 : int(1..3)]), - and([q27 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q27]] - | q27 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q5 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q5] < x_ExplicitVarSizeWithFlags_Values[q5 + 1] - | q5 : int(1..2)]), - and([x_ExplicitVarSizeWithFlags_Flags[q6] = false -> x_ExplicitVarSizeWithFlags_Values[q6] = 1 | q6 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q7] | q7 : int(1..2)]), - and([x_ExplicitVarSizeWithFlags_Flags[q11] -> - or([q13 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q13] = x_ExplicitVarSizeWithFlags_Values[q11] - | q13 : int(1..3)]) - | q11 : int(1..3)]), - and([q15 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q17] /\ - x_ExplicitVarSizeWithFlags_Values[q17] = x_ExplicitVarSizeWithMarker_Values[q15] - | q17 : int(1..3)]) - | q15 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q19] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q19]] - | q19 : int(1..3)]), - and([x_Occurrence[q20] -> - or([x_ExplicitVarSizeWithFlags_Flags[q22] /\ x_ExplicitVarSizeWithFlags_Values[q22] = q20 | q22 : int(1..3)]) - | q20 : int(1..3)]) - diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_2_1-solution000001.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_2_1-solution000001.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_3_2_1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_2_1-solution000002.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_2_1-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_3_2_1-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_2_1-solution000003.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_2_1-solution000003.solution deleted file mode 100644 index de5cc861ad..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_3_2_1-solution000003.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_2_1-solution000004.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_2_1-solution000004.solution deleted file mode 100644 index a28b6d6203..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_3_2_1-solution000004.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_2_1-solution000005.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_2_1-solution000005.solution deleted file mode 100644 index 1a734343d9..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_3_2_1-solution000005.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_2_1-solution000006.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_2_1-solution000006.solution deleted file mode 100644 index 86a85825b3..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_3_2_1-solution000006.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_2_1-solution000007.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_2_1-solution000007.solution deleted file mode 100644 index 76bc8cdc32..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_3_2_1-solution000007.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_2_1-solution000008.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_2_1-solution000008.solution deleted file mode 100644 index 8dddb3b359..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_3_2_1-solution000008.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_2_1.eprime b/tests/exhaustive/basic/cut_01_on/expected/model_3_2_1.eprime deleted file mode 100644 index 4c67eec80e..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_3_2_1.eprime +++ /dev/null @@ -1,44 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..3) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3)] of int(1..3) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..3)] of int(1..4) -find x_Occurrence: matrix indexed by [int(1..3)] of bool -find cut1: bool -find cut2: bool -branching on - [cut1, cut2, x_Occurrence, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, - x_ExplicitVarSizeWithDummy] -such that - !cut1 <-> - or([q20 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q20] = 1 | q20 : int(1..3)]) /\ - or([q22 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q22] = 2 | q22 : int(1..3)]), - !cut2 <-> or([x_ExplicitVarSizeWithDummy[q24] != 4 /\ x_ExplicitVarSizeWithDummy[q24] = 1 | q24 : int(1..3)]), - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..2)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q4] < x_ExplicitVarSizeWithDummy[q4 + 1] \/ x_ExplicitVarSizeWithDummy[q4] = 4 - | q4 : int(1..2)]), - and([x_ExplicitVarSizeWithDummy[q5] = 4 -> x_ExplicitVarSizeWithDummy[q5 + 1] = 4 | q5 : int(1..2)]), - and([x_ExplicitVarSizeWithDummy[q9] != 4 -> - or([q11 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q11] = x_ExplicitVarSizeWithDummy[q9] - | q11 : int(1..3)]) - | q9 : int(1..3)]), - and([q13 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q15] != 4 /\ - x_ExplicitVarSizeWithDummy[q15] = x_ExplicitVarSizeWithMarker_Values[q13] - | q15 : int(1..3)]) - | q13 : int(1..3)]), - and([x_Occurrence[q25] -> - or([q27 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q27] = q25 - | q27 : int(1..3)]) - | q25 : int(1..3)]), - and([q29 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q29]] - | q29 : int(1..3)]), - and([x_Occurrence[q30] -> - or([x_ExplicitVarSizeWithDummy[q32] != 4 /\ x_ExplicitVarSizeWithDummy[q32] = q30 | q32 : int(1..3)]) - | q30 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q34] != 4 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q34]] | q34 : int(1..3)]) - diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_2_2-solution000001.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_2_2-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_3_2_2-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_2_2-solution000002.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_2_2-solution000002.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_3_2_2-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_2_2-solution000003.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_2_2-solution000003.solution deleted file mode 100644 index a28b6d6203..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_3_2_2-solution000003.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_2_2-solution000004.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_2_2-solution000004.solution deleted file mode 100644 index de5cc861ad..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_3_2_2-solution000004.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_2_2-solution000005.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_2_2-solution000005.solution deleted file mode 100644 index 8dddb3b359..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_3_2_2-solution000005.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_2_2-solution000006.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_2_2-solution000006.solution deleted file mode 100644 index 76bc8cdc32..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_3_2_2-solution000006.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_2_2-solution000007.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_2_2-solution000007.solution deleted file mode 100644 index 86a85825b3..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_3_2_2-solution000007.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_2_2-solution000008.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_2_2-solution000008.solution deleted file mode 100644 index 1a734343d9..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_3_2_2-solution000008.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_2_2.eprime b/tests/exhaustive/basic/cut_01_on/expected/model_3_2_2.eprime deleted file mode 100644 index 0e45bbed32..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_3_2_2.eprime +++ /dev/null @@ -1,32 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..3) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3)] of int(1..3) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..3)] of int(1..4) -find cut1: bool -find cut2: bool -branching on - [cut1, cut2, x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] -such that - !cut1 <-> - or([q19 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q19] = 1 | q19 : int(1..3)]) /\ - or([q21 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q21] = 2 | q21 : int(1..3)]), - !cut2 <-> or([x_ExplicitVarSizeWithDummy[q23] != 4 /\ x_ExplicitVarSizeWithDummy[q23] = 1 | q23 : int(1..3)]), - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..2)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q4] < x_ExplicitVarSizeWithDummy[q4 + 1] \/ x_ExplicitVarSizeWithDummy[q4] = 4 - | q4 : int(1..2)]), - and([x_ExplicitVarSizeWithDummy[q5] = 4 -> x_ExplicitVarSizeWithDummy[q5 + 1] = 4 | q5 : int(1..2)]), - and([x_ExplicitVarSizeWithDummy[q9] != 4 -> - or([q11 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q11] = x_ExplicitVarSizeWithDummy[q9] - | q11 : int(1..3)]) - | q9 : int(1..3)]), - and([q13 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q15] != 4 /\ - x_ExplicitVarSizeWithDummy[q15] = x_ExplicitVarSizeWithMarker_Values[q13] - | q15 : int(1..3)]) - | q13 : int(1..3)]) - diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_2_3-solution000001.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_2_3-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_3_2_3-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_2_3-solution000002.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_2_3-solution000002.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_3_2_3-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_2_3-solution000003.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_2_3-solution000003.solution deleted file mode 100644 index a28b6d6203..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_3_2_3-solution000003.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_2_3-solution000004.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_2_3-solution000004.solution deleted file mode 100644 index de5cc861ad..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_3_2_3-solution000004.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_2_3-solution000005.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_2_3-solution000005.solution deleted file mode 100644 index 8dddb3b359..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_3_2_3-solution000005.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_2_3-solution000006.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_2_3-solution000006.solution deleted file mode 100644 index 76bc8cdc32..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_3_2_3-solution000006.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_2_3-solution000007.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_2_3-solution000007.solution deleted file mode 100644 index 86a85825b3..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_3_2_3-solution000007.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_2_3-solution000008.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_2_3-solution000008.solution deleted file mode 100644 index 1a734343d9..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_3_2_3-solution000008.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_2_3.eprime b/tests/exhaustive/basic/cut_01_on/expected/model_3_2_3.eprime deleted file mode 100644 index 0e45bbed32..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_3_2_3.eprime +++ /dev/null @@ -1,32 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..3) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3)] of int(1..3) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..3)] of int(1..4) -find cut1: bool -find cut2: bool -branching on - [cut1, cut2, x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] -such that - !cut1 <-> - or([q19 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q19] = 1 | q19 : int(1..3)]) /\ - or([q21 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q21] = 2 | q21 : int(1..3)]), - !cut2 <-> or([x_ExplicitVarSizeWithDummy[q23] != 4 /\ x_ExplicitVarSizeWithDummy[q23] = 1 | q23 : int(1..3)]), - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..2)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q4] < x_ExplicitVarSizeWithDummy[q4 + 1] \/ x_ExplicitVarSizeWithDummy[q4] = 4 - | q4 : int(1..2)]), - and([x_ExplicitVarSizeWithDummy[q5] = 4 -> x_ExplicitVarSizeWithDummy[q5 + 1] = 4 | q5 : int(1..2)]), - and([x_ExplicitVarSizeWithDummy[q9] != 4 -> - or([q11 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q11] = x_ExplicitVarSizeWithDummy[q9] - | q11 : int(1..3)]) - | q9 : int(1..3)]), - and([q13 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q15] != 4 /\ - x_ExplicitVarSizeWithDummy[q15] = x_ExplicitVarSizeWithMarker_Values[q13] - | q15 : int(1..3)]) - | q13 : int(1..3)]) - diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_2_4-solution000001.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_2_4-solution000001.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_3_2_4-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_2_4-solution000002.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_2_4-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_3_2_4-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_2_4-solution000003.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_2_4-solution000003.solution deleted file mode 100644 index de5cc861ad..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_3_2_4-solution000003.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_2_4-solution000004.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_2_4-solution000004.solution deleted file mode 100644 index a28b6d6203..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_3_2_4-solution000004.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_2_4-solution000005.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_2_4-solution000005.solution deleted file mode 100644 index 1a734343d9..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_3_2_4-solution000005.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_2_4-solution000006.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_2_4-solution000006.solution deleted file mode 100644 index 76bc8cdc32..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_3_2_4-solution000006.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_2_4-solution000007.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_2_4-solution000007.solution deleted file mode 100644 index 86a85825b3..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_3_2_4-solution000007.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_2_4-solution000008.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_2_4-solution000008.solution deleted file mode 100644 index 8dddb3b359..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_3_2_4-solution000008.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_2_4.eprime b/tests/exhaustive/basic/cut_01_on/expected/model_3_2_4.eprime deleted file mode 100644 index 8da6820153..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_3_2_4.eprime +++ /dev/null @@ -1,61 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..3) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3)] of int(1..3) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..3)] of int(1..4) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..3)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3)] of int(1..3) -find cut1: bool -find cut2: bool -branching on - [cut1, cut2, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, - x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy] -such that - !cut1 <-> - or([q40 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q40] = 1 | q40 : int(1..3)]) /\ - or([q42 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q42] = 2 | q42 : int(1..3)]), - !cut2 <-> or([x_ExplicitVarSizeWithDummy[q44] != 4 /\ x_ExplicitVarSizeWithDummy[q44] = 1 | q44 : int(1..3)]), - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..2)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q4] < x_ExplicitVarSizeWithDummy[q4 + 1] \/ x_ExplicitVarSizeWithDummy[q4] = 4 - | q4 : int(1..2)]), - and([x_ExplicitVarSizeWithDummy[q5] = 4 -> x_ExplicitVarSizeWithDummy[q5 + 1] = 4 | q5 : int(1..2)]), - and([x_ExplicitVarSizeWithDummy[q9] != 4 -> - or([q11 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q11] = x_ExplicitVarSizeWithDummy[q9] - | q11 : int(1..3)]) - | q9 : int(1..3)]), - and([q13 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q15] != 4 /\ - x_ExplicitVarSizeWithDummy[q15] = x_ExplicitVarSizeWithMarker_Values[q13] - | q15 : int(1..3)]) - | q13 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q16 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q16] < x_ExplicitVarSizeWithFlags_Values[q16 + 1] - | q16 : int(1..2)]), - and([x_ExplicitVarSizeWithFlags_Flags[q17] = false -> x_ExplicitVarSizeWithFlags_Values[q17] = 1 - | q17 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q18 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q18] | q18 : int(1..2)]), - and([x_ExplicitVarSizeWithFlags_Flags[q22] -> - or([q24 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q24] = x_ExplicitVarSizeWithFlags_Values[q22] - | q24 : int(1..3)]) - | q22 : int(1..3)]), - and([q26 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q28] /\ - x_ExplicitVarSizeWithFlags_Values[q28] = x_ExplicitVarSizeWithMarker_Values[q26] - | q28 : int(1..3)]) - | q26 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q30] -> - or([x_ExplicitVarSizeWithDummy[q32] != 4 /\ - x_ExplicitVarSizeWithDummy[q32] = x_ExplicitVarSizeWithFlags_Values[q30] - | q32 : int(1..3)]) - | q30 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q34] != 4 -> - or([x_ExplicitVarSizeWithFlags_Flags[q36] /\ - x_ExplicitVarSizeWithFlags_Values[q36] = x_ExplicitVarSizeWithDummy[q34] - | q36 : int(1..3)]) - | q34 : int(1..3)]) - diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_3_1-solution000001.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_3_1-solution000001.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_3_3_1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_3_1-solution000002.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_3_1-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_3_3_1-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_3_1-solution000003.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_3_1-solution000003.solution deleted file mode 100644 index de5cc861ad..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_3_3_1-solution000003.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_3_1-solution000004.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_3_1-solution000004.solution deleted file mode 100644 index a28b6d6203..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_3_3_1-solution000004.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_3_1-solution000005.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_3_1-solution000005.solution deleted file mode 100644 index 1a734343d9..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_3_3_1-solution000005.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_3_1-solution000006.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_3_1-solution000006.solution deleted file mode 100644 index 86a85825b3..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_3_3_1-solution000006.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_3_1-solution000007.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_3_1-solution000007.solution deleted file mode 100644 index 76bc8cdc32..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_3_3_1-solution000007.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_3_1-solution000008.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_3_1-solution000008.solution deleted file mode 100644 index 8dddb3b359..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_3_3_1-solution000008.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_3_1.eprime b/tests/exhaustive/basic/cut_01_on/expected/model_3_3_1.eprime deleted file mode 100644 index 53d7488205..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_3_3_1.eprime +++ /dev/null @@ -1,25 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..3) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3)] of int(1..3) -find x_Occurrence: matrix indexed by [int(1..3)] of bool -find cut1: bool -find cut2: bool -branching on [cut1, cut2, x_Occurrence, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] -such that - !cut1 <-> - or([q8 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q8] = 1 | q8 : int(1..3)]) /\ - or([q10 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q10] = 2 | q10 : int(1..3)]), - !cut2 <-> - or([q12 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q12] = 1 | q12 : int(1..3)]), - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..2)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..3)]), - and([x_Occurrence[q13] -> - or([q15 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q15] = q13 - | q15 : int(1..3)]) - | q13 : int(1..3)]), - and([q17 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q17]] - | q17 : int(1..3)]) - diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_3_2-solution000001.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_3_2-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_3_3_2-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_3_2-solution000002.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_3_2-solution000002.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_3_3_2-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_3_2-solution000003.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_3_2-solution000003.solution deleted file mode 100644 index a28b6d6203..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_3_3_2-solution000003.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_3_2-solution000004.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_3_2-solution000004.solution deleted file mode 100644 index de5cc861ad..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_3_3_2-solution000004.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_3_2-solution000005.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_3_2-solution000005.solution deleted file mode 100644 index 8dddb3b359..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_3_3_2-solution000005.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_3_2-solution000006.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_3_2-solution000006.solution deleted file mode 100644 index 76bc8cdc32..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_3_3_2-solution000006.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_3_2-solution000007.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_3_2-solution000007.solution deleted file mode 100644 index 86a85825b3..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_3_3_2-solution000007.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_3_2-solution000008.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_3_2-solution000008.solution deleted file mode 100644 index 1a734343d9..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_3_3_2-solution000008.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_3_2.eprime b/tests/exhaustive/basic/cut_01_on/expected/model_3_3_2.eprime deleted file mode 100644 index 5ce3344d82..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_3_3_2.eprime +++ /dev/null @@ -1,33 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..3) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3)] of int(1..3) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..3)] of int(1..4) -find cut1: bool -find cut2: bool -branching on - [cut1, cut2, x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] -such that - !cut1 <-> - or([q19 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q19] = 1 | q19 : int(1..3)]) /\ - or([q21 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q21] = 2 | q21 : int(1..3)]), - !cut2 <-> - or([q23 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q23] = 1 | q23 : int(1..3)]), - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..2)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q4] < x_ExplicitVarSizeWithDummy[q4 + 1] \/ x_ExplicitVarSizeWithDummy[q4] = 4 - | q4 : int(1..2)]), - and([x_ExplicitVarSizeWithDummy[q5] = 4 -> x_ExplicitVarSizeWithDummy[q5 + 1] = 4 | q5 : int(1..2)]), - and([x_ExplicitVarSizeWithDummy[q9] != 4 -> - or([q11 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q11] = x_ExplicitVarSizeWithDummy[q9] - | q11 : int(1..3)]) - | q9 : int(1..3)]), - and([q13 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q15] != 4 /\ - x_ExplicitVarSizeWithDummy[q15] = x_ExplicitVarSizeWithMarker_Values[q13] - | q15 : int(1..3)]) - | q13 : int(1..3)]) - diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_3_3-solution000001.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_3_3-solution000001.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_3_3_3-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_3_3-solution000002.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_3_3-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_3_3_3-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_3_3-solution000003.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_3_3-solution000003.solution deleted file mode 100644 index de5cc861ad..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_3_3_3-solution000003.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_3_3-solution000004.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_3_3-solution000004.solution deleted file mode 100644 index a28b6d6203..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_3_3_3-solution000004.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_3_3-solution000005.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_3_3-solution000005.solution deleted file mode 100644 index 1a734343d9..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_3_3_3-solution000005.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_3_3-solution000006.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_3_3-solution000006.solution deleted file mode 100644 index 76bc8cdc32..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_3_3_3-solution000006.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_3_3-solution000007.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_3_3-solution000007.solution deleted file mode 100644 index 86a85825b3..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_3_3_3-solution000007.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_3_3-solution000008.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_3_3-solution000008.solution deleted file mode 100644 index 8dddb3b359..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_3_3_3-solution000008.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_3_3.eprime b/tests/exhaustive/basic/cut_01_on/expected/model_3_3_3.eprime deleted file mode 100644 index fc01571bcf..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_3_3_3.eprime +++ /dev/null @@ -1,18 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..3) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3)] of int(1..3) -find cut1: bool -find cut2: bool -branching on [cut1, cut2, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] -such that - !cut1 <-> - or([q7 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q7] = 1 | q7 : int(1..3)]) /\ - or([q9 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q9] = 2 | q9 : int(1..3)]), - !cut2 <-> - or([q11 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q11] = 1 | q11 : int(1..3)]), - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..2)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..3)]) - diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_3_4-solution000001.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_3_4-solution000001.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_3_3_4-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_3_4-solution000002.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_3_4-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_3_3_4-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_3_4-solution000003.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_3_4-solution000003.solution deleted file mode 100644 index de5cc861ad..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_3_3_4-solution000003.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_3_4-solution000004.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_3_4-solution000004.solution deleted file mode 100644 index a28b6d6203..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_3_3_4-solution000004.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_3_4-solution000005.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_3_4-solution000005.solution deleted file mode 100644 index 1a734343d9..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_3_3_4-solution000005.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_3_4-solution000006.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_3_4-solution000006.solution deleted file mode 100644 index 76bc8cdc32..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_3_3_4-solution000006.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_3_4-solution000007.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_3_4-solution000007.solution deleted file mode 100644 index 86a85825b3..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_3_3_4-solution000007.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_3_4-solution000008.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_3_4-solution000008.solution deleted file mode 100644 index 8dddb3b359..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_3_3_4-solution000008.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_3_4.eprime b/tests/exhaustive/basic/cut_01_on/expected/model_3_3_4.eprime deleted file mode 100644 index eaa3282438..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_3_3_4.eprime +++ /dev/null @@ -1,37 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..3) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3)] of int(1..3) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..3)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3)] of int(1..3) -find cut1: bool -find cut2: bool -branching on - [cut1, cut2, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, - x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] -such that - !cut1 <-> - or([q20 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q20] = 1 | q20 : int(1..3)]) /\ - or([q22 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q22] = 2 | q22 : int(1..3)]), - !cut2 <-> - or([q24 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q24] = 1 | q24 : int(1..3)]), - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..2)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q4] < x_ExplicitVarSizeWithFlags_Values[q4 + 1] - | q4 : int(1..2)]), - and([x_ExplicitVarSizeWithFlags_Flags[q5] = false -> x_ExplicitVarSizeWithFlags_Values[q5] = 1 | q5 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q6] | q6 : int(1..2)]), - and([x_ExplicitVarSizeWithFlags_Flags[q10] -> - or([q12 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q12] = x_ExplicitVarSizeWithFlags_Values[q10] - | q12 : int(1..3)]) - | q10 : int(1..3)]), - and([q14 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q16] /\ - x_ExplicitVarSizeWithFlags_Values[q16] = x_ExplicitVarSizeWithMarker_Values[q14] - | q16 : int(1..3)]) - | q14 : int(1..3)]) - diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_4_1-solution000001.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_4_1-solution000001.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_3_4_1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_4_1-solution000002.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_4_1-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_3_4_1-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_4_1-solution000003.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_4_1-solution000003.solution deleted file mode 100644 index de5cc861ad..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_3_4_1-solution000003.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_4_1-solution000004.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_4_1-solution000004.solution deleted file mode 100644 index a28b6d6203..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_3_4_1-solution000004.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_4_1-solution000005.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_4_1-solution000005.solution deleted file mode 100644 index 1a734343d9..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_3_4_1-solution000005.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_4_1-solution000006.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_4_1-solution000006.solution deleted file mode 100644 index 86a85825b3..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_3_4_1-solution000006.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_4_1-solution000007.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_4_1-solution000007.solution deleted file mode 100644 index 76bc8cdc32..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_3_4_1-solution000007.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_4_1-solution000008.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_4_1-solution000008.solution deleted file mode 100644 index 8dddb3b359..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_3_4_1-solution000008.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_4_1.eprime b/tests/exhaustive/basic/cut_01_on/expected/model_3_4_1.eprime deleted file mode 100644 index b76189f663..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_3_4_1.eprime +++ /dev/null @@ -1,49 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..3) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3)] of int(1..3) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..3)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3)] of int(1..3) -find x_Occurrence: matrix indexed by [int(1..3)] of bool -find cut1: bool -find cut2: bool -branching on - [cut1, cut2, x_Occurrence, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, - x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] -such that - !cut1 <-> - or([q31 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q31] = 1 | q31 : int(1..3)]) /\ - or([q33 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q33] = 2 | q33 : int(1..3)]), - !cut2 <-> - or([x_ExplicitVarSizeWithFlags_Flags[q35] /\ x_ExplicitVarSizeWithFlags_Values[q35] = 1 | q35 : int(1..3)]), - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..2)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q4] < x_ExplicitVarSizeWithFlags_Values[q4 + 1] - | q4 : int(1..2)]), - and([x_ExplicitVarSizeWithFlags_Flags[q5] = false -> x_ExplicitVarSizeWithFlags_Values[q5] = 1 | q5 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q6] | q6 : int(1..2)]), - and([x_ExplicitVarSizeWithFlags_Flags[q10] -> - or([q12 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q12] = x_ExplicitVarSizeWithFlags_Values[q10] - | q12 : int(1..3)]) - | q10 : int(1..3)]), - and([q14 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q16] /\ - x_ExplicitVarSizeWithFlags_Values[q16] = x_ExplicitVarSizeWithMarker_Values[q14] - | q16 : int(1..3)]) - | q14 : int(1..3)]), - and([x_Occurrence[q18] -> - or([q20 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q20] = q18 - | q20 : int(1..3)]) - | q18 : int(1..3)]), - and([q22 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q22]] - | q22 : int(1..3)]), - and([x_Occurrence[q23] -> - or([x_ExplicitVarSizeWithFlags_Flags[q25] /\ x_ExplicitVarSizeWithFlags_Values[q25] = q23 | q25 : int(1..3)]) - | q23 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q27] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q27]] - | q27 : int(1..3)]) - diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_4_2-solution000001.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_4_2-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_3_4_2-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_4_2-solution000002.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_4_2-solution000002.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_3_4_2-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_4_2-solution000003.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_4_2-solution000003.solution deleted file mode 100644 index a28b6d6203..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_3_4_2-solution000003.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_4_2-solution000004.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_4_2-solution000004.solution deleted file mode 100644 index de5cc861ad..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_3_4_2-solution000004.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_4_2-solution000005.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_4_2-solution000005.solution deleted file mode 100644 index 8dddb3b359..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_3_4_2-solution000005.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_4_2-solution000006.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_4_2-solution000006.solution deleted file mode 100644 index 76bc8cdc32..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_3_4_2-solution000006.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_4_2-solution000007.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_4_2-solution000007.solution deleted file mode 100644 index 86a85825b3..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_3_4_2-solution000007.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_4_2-solution000008.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_4_2-solution000008.solution deleted file mode 100644 index 1a734343d9..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_3_4_2-solution000008.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_4_2.eprime b/tests/exhaustive/basic/cut_01_on/expected/model_3_4_2.eprime deleted file mode 100644 index e5786ebbae..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_3_4_2.eprime +++ /dev/null @@ -1,61 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..3) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3)] of int(1..3) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..3)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3)] of int(1..3) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..3)] of int(1..4) -find cut1: bool -find cut2: bool -branching on - [cut1, cut2, x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, - x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] -such that - !cut1 <-> - or([q40 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q40] = 1 | q40 : int(1..3)]) /\ - or([q42 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q42] = 2 | q42 : int(1..3)]), - !cut2 <-> - or([x_ExplicitVarSizeWithFlags_Flags[q44] /\ x_ExplicitVarSizeWithFlags_Values[q44] = 1 | q44 : int(1..3)]), - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..2)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q4] < x_ExplicitVarSizeWithFlags_Values[q4 + 1] - | q4 : int(1..2)]), - and([x_ExplicitVarSizeWithFlags_Flags[q5] = false -> x_ExplicitVarSizeWithFlags_Values[q5] = 1 | q5 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q6] | q6 : int(1..2)]), - and([x_ExplicitVarSizeWithFlags_Flags[q10] -> - or([q12 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q12] = x_ExplicitVarSizeWithFlags_Values[q10] - | q12 : int(1..3)]) - | q10 : int(1..3)]), - and([q14 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q16] /\ - x_ExplicitVarSizeWithFlags_Values[q16] = x_ExplicitVarSizeWithMarker_Values[q14] - | q16 : int(1..3)]) - | q14 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q17] < x_ExplicitVarSizeWithDummy[q17 + 1] \/ x_ExplicitVarSizeWithDummy[q17] = 4 - | q17 : int(1..2)]), - and([x_ExplicitVarSizeWithDummy[q18] = 4 -> x_ExplicitVarSizeWithDummy[q18 + 1] = 4 | q18 : int(1..2)]), - and([x_ExplicitVarSizeWithDummy[q22] != 4 -> - or([q24 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q24] = x_ExplicitVarSizeWithDummy[q22] - | q24 : int(1..3)]) - | q22 : int(1..3)]), - and([q26 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q28] != 4 /\ - x_ExplicitVarSizeWithDummy[q28] = x_ExplicitVarSizeWithMarker_Values[q26] - | q28 : int(1..3)]) - | q26 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q30] != 4 -> - or([x_ExplicitVarSizeWithFlags_Flags[q32] /\ - x_ExplicitVarSizeWithFlags_Values[q32] = x_ExplicitVarSizeWithDummy[q30] - | q32 : int(1..3)]) - | q30 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q34] -> - or([x_ExplicitVarSizeWithDummy[q36] != 4 /\ - x_ExplicitVarSizeWithDummy[q36] = x_ExplicitVarSizeWithFlags_Values[q34] - | q36 : int(1..3)]) - | q34 : int(1..3)]) - diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_4_3-solution000001.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_4_3-solution000001.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_3_4_3-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_4_3-solution000002.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_4_3-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_3_4_3-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_4_3-solution000003.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_4_3-solution000003.solution deleted file mode 100644 index de5cc861ad..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_3_4_3-solution000003.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_4_3-solution000004.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_4_3-solution000004.solution deleted file mode 100644 index a28b6d6203..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_3_4_3-solution000004.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_4_3-solution000005.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_4_3-solution000005.solution deleted file mode 100644 index 1a734343d9..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_3_4_3-solution000005.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_4_3-solution000006.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_4_3-solution000006.solution deleted file mode 100644 index 76bc8cdc32..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_3_4_3-solution000006.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_4_3-solution000007.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_4_3-solution000007.solution deleted file mode 100644 index 86a85825b3..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_3_4_3-solution000007.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_4_3-solution000008.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_4_3-solution000008.solution deleted file mode 100644 index 8dddb3b359..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_3_4_3-solution000008.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_4_3.eprime b/tests/exhaustive/basic/cut_01_on/expected/model_3_4_3.eprime deleted file mode 100644 index 091740b224..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_3_4_3.eprime +++ /dev/null @@ -1,37 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..3) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3)] of int(1..3) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..3)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3)] of int(1..3) -find cut1: bool -find cut2: bool -branching on - [cut1, cut2, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, - x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] -such that - !cut1 <-> - or([q20 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q20] = 1 | q20 : int(1..3)]) /\ - or([q22 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q22] = 2 | q22 : int(1..3)]), - !cut2 <-> - or([x_ExplicitVarSizeWithFlags_Flags[q24] /\ x_ExplicitVarSizeWithFlags_Values[q24] = 1 | q24 : int(1..3)]), - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..2)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q4] < x_ExplicitVarSizeWithFlags_Values[q4 + 1] - | q4 : int(1..2)]), - and([x_ExplicitVarSizeWithFlags_Flags[q5] = false -> x_ExplicitVarSizeWithFlags_Values[q5] = 1 | q5 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q6] | q6 : int(1..2)]), - and([x_ExplicitVarSizeWithFlags_Flags[q10] -> - or([q12 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q12] = x_ExplicitVarSizeWithFlags_Values[q10] - | q12 : int(1..3)]) - | q10 : int(1..3)]), - and([q14 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q16] /\ - x_ExplicitVarSizeWithFlags_Values[q16] = x_ExplicitVarSizeWithMarker_Values[q14] - | q16 : int(1..3)]) - | q14 : int(1..3)]) - diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_4_4-solution000001.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_4_4-solution000001.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_3_4_4-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_4_4-solution000002.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_4_4-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_3_4_4-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_4_4-solution000003.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_4_4-solution000003.solution deleted file mode 100644 index de5cc861ad..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_3_4_4-solution000003.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_4_4-solution000004.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_4_4-solution000004.solution deleted file mode 100644 index a28b6d6203..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_3_4_4-solution000004.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_4_4-solution000005.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_4_4-solution000005.solution deleted file mode 100644 index 1a734343d9..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_3_4_4-solution000005.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_4_4-solution000006.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_4_4-solution000006.solution deleted file mode 100644 index 76bc8cdc32..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_3_4_4-solution000006.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_4_4-solution000007.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_4_4-solution000007.solution deleted file mode 100644 index 86a85825b3..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_3_4_4-solution000007.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_4_4-solution000008.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_4_4-solution000008.solution deleted file mode 100644 index 8dddb3b359..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_3_4_4-solution000008.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_4_4.eprime b/tests/exhaustive/basic/cut_01_on/expected/model_3_4_4.eprime deleted file mode 100644 index 091740b224..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_3_4_4.eprime +++ /dev/null @@ -1,37 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..3) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3)] of int(1..3) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..3)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3)] of int(1..3) -find cut1: bool -find cut2: bool -branching on - [cut1, cut2, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, - x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] -such that - !cut1 <-> - or([q20 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q20] = 1 | q20 : int(1..3)]) /\ - or([q22 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q22] = 2 | q22 : int(1..3)]), - !cut2 <-> - or([x_ExplicitVarSizeWithFlags_Flags[q24] /\ x_ExplicitVarSizeWithFlags_Values[q24] = 1 | q24 : int(1..3)]), - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..2)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q4] < x_ExplicitVarSizeWithFlags_Values[q4 + 1] - | q4 : int(1..2)]), - and([x_ExplicitVarSizeWithFlags_Flags[q5] = false -> x_ExplicitVarSizeWithFlags_Values[q5] = 1 | q5 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q6] | q6 : int(1..2)]), - and([x_ExplicitVarSizeWithFlags_Flags[q10] -> - or([q12 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q12] = x_ExplicitVarSizeWithFlags_Values[q10] - | q12 : int(1..3)]) - | q10 : int(1..3)]), - and([q14 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q16] /\ - x_ExplicitVarSizeWithFlags_Values[q16] = x_ExplicitVarSizeWithMarker_Values[q14] - | q16 : int(1..3)]) - | q14 : int(1..3)]) - diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_1_1-solution000001.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_1_1-solution000001.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_4_1_1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_1_1-solution000002.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_1_1-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_4_1_1-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_1_1-solution000003.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_1_1-solution000003.solution deleted file mode 100644 index de5cc861ad..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_4_1_1-solution000003.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_1_1-solution000004.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_1_1-solution000004.solution deleted file mode 100644 index a28b6d6203..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_4_1_1-solution000004.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_1_1-solution000005.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_1_1-solution000005.solution deleted file mode 100644 index 1a734343d9..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_4_1_1-solution000005.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_1_1-solution000006.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_1_1-solution000006.solution deleted file mode 100644 index 86a85825b3..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_4_1_1-solution000006.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_1_1-solution000007.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_1_1-solution000007.solution deleted file mode 100644 index 76bc8cdc32..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_4_1_1-solution000007.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_1_1-solution000008.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_1_1-solution000008.solution deleted file mode 100644 index 8dddb3b359..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_4_1_1-solution000008.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_1_1.eprime b/tests/exhaustive/basic/cut_01_on/expected/model_4_1_1.eprime deleted file mode 100644 index 07c1d226b7..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_4_1_1.eprime +++ /dev/null @@ -1,24 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..3)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3)] of int(1..3) -find x_Occurrence: matrix indexed by [int(1..3)] of bool -find cut1: bool -find cut2: bool -branching on [cut1, cut2, x_Occurrence, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] -such that - !cut1 <-> - or([x_ExplicitVarSizeWithFlags_Flags[q15] /\ x_ExplicitVarSizeWithFlags_Values[q15] = 1 | q15 : int(1..3)]) /\ - or([x_ExplicitVarSizeWithFlags_Flags[q17] /\ x_ExplicitVarSizeWithFlags_Values[q17] = 2 | q17 : int(1..3)]), - !cut2 <-> x_Occurrence[1], - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..2)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..2)]), - and([x_Occurrence[q7] -> - or([x_ExplicitVarSizeWithFlags_Flags[q9] /\ x_ExplicitVarSizeWithFlags_Values[q9] = q7 | q9 : int(1..3)]) - | q7 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q11] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q11]] - | q11 : int(1..3)]) - diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_1_2-solution000001.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_1_2-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_4_1_2-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_1_2-solution000002.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_1_2-solution000002.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_4_1_2-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_1_2-solution000003.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_1_2-solution000003.solution deleted file mode 100644 index a28b6d6203..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_4_1_2-solution000003.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_1_2-solution000004.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_1_2-solution000004.solution deleted file mode 100644 index de5cc861ad..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_4_1_2-solution000004.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_1_2-solution000005.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_1_2-solution000005.solution deleted file mode 100644 index 8dddb3b359..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_4_1_2-solution000005.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_1_2-solution000006.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_1_2-solution000006.solution deleted file mode 100644 index 76bc8cdc32..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_4_1_2-solution000006.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_1_2-solution000007.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_1_2-solution000007.solution deleted file mode 100644 index 86a85825b3..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_4_1_2-solution000007.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_1_2-solution000008.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_1_2-solution000008.solution deleted file mode 100644 index 1a734343d9..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_4_1_2-solution000008.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_1_2.eprime b/tests/exhaustive/basic/cut_01_on/expected/model_4_1_2.eprime deleted file mode 100644 index 7cc678398c..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_4_1_2.eprime +++ /dev/null @@ -1,44 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..3)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3)] of int(1..3) -find x_Occurrence: matrix indexed by [int(1..3)] of bool -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..3)] of int(1..4) -find cut1: bool -find cut2: bool -branching on - [cut1, cut2, x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, - x_Occurrence] -such that - !cut1 <-> - or([x_ExplicitVarSizeWithFlags_Flags[q32] /\ x_ExplicitVarSizeWithFlags_Values[q32] = 1 | q32 : int(1..3)]) /\ - or([x_ExplicitVarSizeWithFlags_Flags[q34] /\ x_ExplicitVarSizeWithFlags_Values[q34] = 2 | q34 : int(1..3)]), - !cut2 <-> x_Occurrence[1], - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..2)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..2)]), - and([x_Occurrence[q24] -> - or([x_ExplicitVarSizeWithFlags_Flags[q26] /\ x_ExplicitVarSizeWithFlags_Values[q26] = q24 | q26 : int(1..3)]) - | q24 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q28] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q28]] - | q28 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q7] < x_ExplicitVarSizeWithDummy[q7 + 1] \/ x_ExplicitVarSizeWithDummy[q7] = 4 - | q7 : int(1..2)]), - and([x_ExplicitVarSizeWithDummy[q8] = 4 -> x_ExplicitVarSizeWithDummy[q8 + 1] = 4 | q8 : int(1..2)]), - and([x_ExplicitVarSizeWithDummy[q12] != 4 -> - or([x_ExplicitVarSizeWithFlags_Flags[q14] /\ - x_ExplicitVarSizeWithFlags_Values[q14] = x_ExplicitVarSizeWithDummy[q12] - | q14 : int(1..3)]) - | q12 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q16] -> - or([x_ExplicitVarSizeWithDummy[q18] != 4 /\ - x_ExplicitVarSizeWithDummy[q18] = x_ExplicitVarSizeWithFlags_Values[q16] - | q18 : int(1..3)]) - | q16 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q20] != 4 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q20]] | q20 : int(1..3)]), - and([x_Occurrence[q21] -> - or([x_ExplicitVarSizeWithDummy[q23] != 4 /\ x_ExplicitVarSizeWithDummy[q23] = q21 | q23 : int(1..3)]) - | q21 : int(1..3)]) - diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_1_3-solution000001.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_1_3-solution000001.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_4_1_3-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_1_3-solution000002.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_1_3-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_4_1_3-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_1_3-solution000003.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_1_3-solution000003.solution deleted file mode 100644 index de5cc861ad..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_4_1_3-solution000003.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_1_3-solution000004.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_1_3-solution000004.solution deleted file mode 100644 index a28b6d6203..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_4_1_3-solution000004.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_1_3-solution000005.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_1_3-solution000005.solution deleted file mode 100644 index 1a734343d9..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_4_1_3-solution000005.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_1_3-solution000006.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_1_3-solution000006.solution deleted file mode 100644 index 76bc8cdc32..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_4_1_3-solution000006.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_1_3-solution000007.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_1_3-solution000007.solution deleted file mode 100644 index 86a85825b3..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_4_1_3-solution000007.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_1_3-solution000008.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_1_3-solution000008.solution deleted file mode 100644 index 8dddb3b359..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_4_1_3-solution000008.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_1_3.eprime b/tests/exhaustive/basic/cut_01_on/expected/model_4_1_3.eprime deleted file mode 100644 index 48de53f219..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_4_1_3.eprime +++ /dev/null @@ -1,48 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..3)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3)] of int(1..3) -find x_Occurrence: matrix indexed by [int(1..3)] of bool -find x_ExplicitVarSizeWithMarker_Marker: int(0..3) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3)] of int(1..3) -find cut1: bool -find cut2: bool -branching on - [cut1, cut2, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, - x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_Occurrence] -such that - !cut1 <-> - or([x_ExplicitVarSizeWithFlags_Flags[q31] /\ x_ExplicitVarSizeWithFlags_Values[q31] = 1 | q31 : int(1..3)]) /\ - or([x_ExplicitVarSizeWithFlags_Flags[q33] /\ x_ExplicitVarSizeWithFlags_Values[q33] = 2 | q33 : int(1..3)]), - !cut2 <-> x_Occurrence[1], - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..2)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..2)]), - and([x_Occurrence[q23] -> - or([x_ExplicitVarSizeWithFlags_Flags[q25] /\ x_ExplicitVarSizeWithFlags_Values[q25] = q23 | q25 : int(1..3)]) - | q23 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q27] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q27]] - | q27 : int(1..3)]), - and([q7 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q7] < x_ExplicitVarSizeWithMarker_Values[q7 + 1] - | q7 : int(1..2)]), - and([q8 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q8] = 1 | q8 : int(1..3)]), - and([q11 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q13] /\ - x_ExplicitVarSizeWithFlags_Values[q13] = x_ExplicitVarSizeWithMarker_Values[q11] - | q13 : int(1..3)]) - | q11 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q15] -> - or([q17 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q17] = x_ExplicitVarSizeWithFlags_Values[q15] - | q17 : int(1..3)]) - | q15 : int(1..3)]), - and([q19 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q19]] - | q19 : int(1..3)]), - and([x_Occurrence[q20] -> - or([q22 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q22] = q20 - | q22 : int(1..3)]) - | q20 : int(1..3)]) - diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_1_4-solution000001.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_1_4-solution000001.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_4_1_4-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_1_4-solution000002.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_1_4-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_4_1_4-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_1_4-solution000003.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_1_4-solution000003.solution deleted file mode 100644 index de5cc861ad..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_4_1_4-solution000003.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_1_4-solution000004.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_1_4-solution000004.solution deleted file mode 100644 index a28b6d6203..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_4_1_4-solution000004.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_1_4-solution000005.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_1_4-solution000005.solution deleted file mode 100644 index 1a734343d9..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_4_1_4-solution000005.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_1_4-solution000006.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_1_4-solution000006.solution deleted file mode 100644 index 86a85825b3..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_4_1_4-solution000006.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_1_4-solution000007.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_1_4-solution000007.solution deleted file mode 100644 index 76bc8cdc32..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_4_1_4-solution000007.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_1_4-solution000008.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_1_4-solution000008.solution deleted file mode 100644 index 8dddb3b359..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_4_1_4-solution000008.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_1_4.eprime b/tests/exhaustive/basic/cut_01_on/expected/model_4_1_4.eprime deleted file mode 100644 index 07c1d226b7..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_4_1_4.eprime +++ /dev/null @@ -1,24 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..3)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3)] of int(1..3) -find x_Occurrence: matrix indexed by [int(1..3)] of bool -find cut1: bool -find cut2: bool -branching on [cut1, cut2, x_Occurrence, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] -such that - !cut1 <-> - or([x_ExplicitVarSizeWithFlags_Flags[q15] /\ x_ExplicitVarSizeWithFlags_Values[q15] = 1 | q15 : int(1..3)]) /\ - or([x_ExplicitVarSizeWithFlags_Flags[q17] /\ x_ExplicitVarSizeWithFlags_Values[q17] = 2 | q17 : int(1..3)]), - !cut2 <-> x_Occurrence[1], - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..2)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..2)]), - and([x_Occurrence[q7] -> - or([x_ExplicitVarSizeWithFlags_Flags[q9] /\ x_ExplicitVarSizeWithFlags_Values[q9] = q7 | q9 : int(1..3)]) - | q7 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q11] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q11]] - | q11 : int(1..3)]) - diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_2_1-solution000001.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_2_1-solution000001.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_4_2_1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_2_1-solution000002.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_2_1-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_4_2_1-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_2_1-solution000003.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_2_1-solution000003.solution deleted file mode 100644 index de5cc861ad..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_4_2_1-solution000003.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_2_1-solution000004.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_2_1-solution000004.solution deleted file mode 100644 index a28b6d6203..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_4_2_1-solution000004.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_2_1-solution000005.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_2_1-solution000005.solution deleted file mode 100644 index 1a734343d9..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_4_2_1-solution000005.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_2_1-solution000006.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_2_1-solution000006.solution deleted file mode 100644 index 86a85825b3..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_4_2_1-solution000006.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_2_1-solution000007.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_2_1-solution000007.solution deleted file mode 100644 index 76bc8cdc32..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_4_2_1-solution000007.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_2_1-solution000008.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_2_1-solution000008.solution deleted file mode 100644 index 8dddb3b359..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_4_2_1-solution000008.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_2_1.eprime b/tests/exhaustive/basic/cut_01_on/expected/model_4_2_1.eprime deleted file mode 100644 index 4016f96947..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_4_2_1.eprime +++ /dev/null @@ -1,44 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..3)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3)] of int(1..3) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..3)] of int(1..4) -find x_Occurrence: matrix indexed by [int(1..3)] of bool -find cut1: bool -find cut2: bool -branching on - [cut1, cut2, x_Occurrence, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, - x_ExplicitVarSizeWithDummy] -such that - !cut1 <-> - or([x_ExplicitVarSizeWithFlags_Flags[q32] /\ x_ExplicitVarSizeWithFlags_Values[q32] = 1 | q32 : int(1..3)]) /\ - or([x_ExplicitVarSizeWithFlags_Flags[q34] /\ x_ExplicitVarSizeWithFlags_Values[q34] = 2 | q34 : int(1..3)]), - !cut2 <-> or([x_ExplicitVarSizeWithDummy[q36] != 4 /\ x_ExplicitVarSizeWithDummy[q36] = 1 | q36 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..2)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..2)]), - and([x_ExplicitVarSizeWithDummy[q6] < x_ExplicitVarSizeWithDummy[q6 + 1] \/ x_ExplicitVarSizeWithDummy[q6] = 4 - | q6 : int(1..2)]), - and([x_ExplicitVarSizeWithDummy[q7] = 4 -> x_ExplicitVarSizeWithDummy[q7 + 1] = 4 | q7 : int(1..2)]), - and([x_ExplicitVarSizeWithDummy[q11] != 4 -> - or([x_ExplicitVarSizeWithFlags_Flags[q13] /\ - x_ExplicitVarSizeWithFlags_Values[q13] = x_ExplicitVarSizeWithDummy[q11] - | q13 : int(1..3)]) - | q11 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q15] -> - or([x_ExplicitVarSizeWithDummy[q17] != 4 /\ - x_ExplicitVarSizeWithDummy[q17] = x_ExplicitVarSizeWithFlags_Values[q15] - | q17 : int(1..3)]) - | q15 : int(1..3)]), - and([x_Occurrence[q19] -> - or([x_ExplicitVarSizeWithFlags_Flags[q21] /\ x_ExplicitVarSizeWithFlags_Values[q21] = q19 | q21 : int(1..3)]) - | q19 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q23] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q23]] - | q23 : int(1..3)]), - and([x_Occurrence[q24] -> - or([x_ExplicitVarSizeWithDummy[q26] != 4 /\ x_ExplicitVarSizeWithDummy[q26] = q24 | q26 : int(1..3)]) - | q24 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q28] != 4 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q28]] | q28 : int(1..3)]) - diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_2_2-solution000001.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_2_2-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_4_2_2-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_2_2-solution000002.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_2_2-solution000002.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_4_2_2-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_2_2-solution000003.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_2_2-solution000003.solution deleted file mode 100644 index a28b6d6203..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_4_2_2-solution000003.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_2_2-solution000004.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_2_2-solution000004.solution deleted file mode 100644 index de5cc861ad..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_4_2_2-solution000004.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_2_2-solution000005.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_2_2-solution000005.solution deleted file mode 100644 index 8dddb3b359..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_4_2_2-solution000005.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_2_2-solution000006.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_2_2-solution000006.solution deleted file mode 100644 index 76bc8cdc32..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_4_2_2-solution000006.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_2_2-solution000007.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_2_2-solution000007.solution deleted file mode 100644 index 86a85825b3..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_4_2_2-solution000007.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_2_2-solution000008.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_2_2-solution000008.solution deleted file mode 100644 index 1a734343d9..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_4_2_2-solution000008.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_2_2.eprime b/tests/exhaustive/basic/cut_01_on/expected/model_4_2_2.eprime deleted file mode 100644 index b23cd6dc8f..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_4_2_2.eprime +++ /dev/null @@ -1,33 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..3)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3)] of int(1..3) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..3)] of int(1..4) -find cut1: bool -find cut2: bool -branching on - [cut1, cut2, x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] -such that - !cut1 <-> - or([x_ExplicitVarSizeWithFlags_Flags[q21] /\ x_ExplicitVarSizeWithFlags_Values[q21] = 1 | q21 : int(1..3)]) /\ - or([x_ExplicitVarSizeWithFlags_Flags[q23] /\ x_ExplicitVarSizeWithFlags_Values[q23] = 2 | q23 : int(1..3)]), - !cut2 <-> or([x_ExplicitVarSizeWithDummy[q25] != 4 /\ x_ExplicitVarSizeWithDummy[q25] = 1 | q25 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..2)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..2)]), - and([x_ExplicitVarSizeWithDummy[q6] < x_ExplicitVarSizeWithDummy[q6 + 1] \/ x_ExplicitVarSizeWithDummy[q6] = 4 - | q6 : int(1..2)]), - and([x_ExplicitVarSizeWithDummy[q7] = 4 -> x_ExplicitVarSizeWithDummy[q7 + 1] = 4 | q7 : int(1..2)]), - and([x_ExplicitVarSizeWithDummy[q11] != 4 -> - or([x_ExplicitVarSizeWithFlags_Flags[q13] /\ - x_ExplicitVarSizeWithFlags_Values[q13] = x_ExplicitVarSizeWithDummy[q11] - | q13 : int(1..3)]) - | q11 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q15] -> - or([x_ExplicitVarSizeWithDummy[q17] != 4 /\ - x_ExplicitVarSizeWithDummy[q17] = x_ExplicitVarSizeWithFlags_Values[q15] - | q17 : int(1..3)]) - | q15 : int(1..3)]) - diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_2_3-solution000001.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_2_3-solution000001.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_4_2_3-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_2_3-solution000002.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_2_3-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_4_2_3-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_2_3-solution000003.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_2_3-solution000003.solution deleted file mode 100644 index de5cc861ad..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_4_2_3-solution000003.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_2_3-solution000004.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_2_3-solution000004.solution deleted file mode 100644 index a28b6d6203..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_4_2_3-solution000004.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_2_3-solution000005.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_2_3-solution000005.solution deleted file mode 100644 index 1a734343d9..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_4_2_3-solution000005.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_2_3-solution000006.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_2_3-solution000006.solution deleted file mode 100644 index 76bc8cdc32..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_4_2_3-solution000006.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_2_3-solution000007.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_2_3-solution000007.solution deleted file mode 100644 index 86a85825b3..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_4_2_3-solution000007.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_2_3-solution000008.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_2_3-solution000008.solution deleted file mode 100644 index 8dddb3b359..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_4_2_3-solution000008.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_2_3.eprime b/tests/exhaustive/basic/cut_01_on/expected/model_4_2_3.eprime deleted file mode 100644 index 321cb5a34e..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_4_2_3.eprime +++ /dev/null @@ -1,60 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..3)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3)] of int(1..3) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..3)] of int(1..4) -find x_ExplicitVarSizeWithMarker_Marker: int(0..3) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3)] of int(1..3) -find cut1: bool -find cut2: bool -branching on - [cut1, cut2, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, - x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy] -such that - !cut1 <-> - or([x_ExplicitVarSizeWithFlags_Flags[q40] /\ x_ExplicitVarSizeWithFlags_Values[q40] = 1 | q40 : int(1..3)]) /\ - or([x_ExplicitVarSizeWithFlags_Flags[q42] /\ x_ExplicitVarSizeWithFlags_Values[q42] = 2 | q42 : int(1..3)]), - !cut2 <-> or([x_ExplicitVarSizeWithDummy[q44] != 4 /\ x_ExplicitVarSizeWithDummy[q44] = 1 | q44 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..2)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..2)]), - and([x_ExplicitVarSizeWithDummy[q6] < x_ExplicitVarSizeWithDummy[q6 + 1] \/ x_ExplicitVarSizeWithDummy[q6] = 4 - | q6 : int(1..2)]), - and([x_ExplicitVarSizeWithDummy[q7] = 4 -> x_ExplicitVarSizeWithDummy[q7 + 1] = 4 | q7 : int(1..2)]), - and([x_ExplicitVarSizeWithDummy[q11] != 4 -> - or([x_ExplicitVarSizeWithFlags_Flags[q13] /\ - x_ExplicitVarSizeWithFlags_Values[q13] = x_ExplicitVarSizeWithDummy[q11] - | q13 : int(1..3)]) - | q11 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q15] -> - or([x_ExplicitVarSizeWithDummy[q17] != 4 /\ - x_ExplicitVarSizeWithDummy[q17] = x_ExplicitVarSizeWithFlags_Values[q15] - | q17 : int(1..3)]) - | q15 : int(1..3)]), - and([q18 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q18] < x_ExplicitVarSizeWithMarker_Values[q18 + 1] - | q18 : int(1..2)]), - and([q19 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q19] = 1 | q19 : int(1..3)]), - and([q22 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q24] /\ - x_ExplicitVarSizeWithFlags_Values[q24] = x_ExplicitVarSizeWithMarker_Values[q22] - | q24 : int(1..3)]) - | q22 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q26] -> - or([q28 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q28] = x_ExplicitVarSizeWithFlags_Values[q26] - | q28 : int(1..3)]) - | q26 : int(1..3)]), - and([q30 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q32] != 4 /\ - x_ExplicitVarSizeWithDummy[q32] = x_ExplicitVarSizeWithMarker_Values[q30] - | q32 : int(1..3)]) - | q30 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q34] != 4 -> - or([q36 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q36] = x_ExplicitVarSizeWithDummy[q34] - | q36 : int(1..3)]) - | q34 : int(1..3)]) - diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_2_4-solution000001.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_2_4-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_4_2_4-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_2_4-solution000002.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_2_4-solution000002.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_4_2_4-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_2_4-solution000003.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_2_4-solution000003.solution deleted file mode 100644 index a28b6d6203..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_4_2_4-solution000003.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_2_4-solution000004.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_2_4-solution000004.solution deleted file mode 100644 index de5cc861ad..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_4_2_4-solution000004.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_2_4-solution000005.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_2_4-solution000005.solution deleted file mode 100644 index 8dddb3b359..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_4_2_4-solution000005.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_2_4-solution000006.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_2_4-solution000006.solution deleted file mode 100644 index 76bc8cdc32..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_4_2_4-solution000006.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_2_4-solution000007.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_2_4-solution000007.solution deleted file mode 100644 index 86a85825b3..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_4_2_4-solution000007.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_2_4-solution000008.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_2_4-solution000008.solution deleted file mode 100644 index 1a734343d9..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_4_2_4-solution000008.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_2_4.eprime b/tests/exhaustive/basic/cut_01_on/expected/model_4_2_4.eprime deleted file mode 100644 index b23cd6dc8f..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_4_2_4.eprime +++ /dev/null @@ -1,33 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..3)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3)] of int(1..3) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..3)] of int(1..4) -find cut1: bool -find cut2: bool -branching on - [cut1, cut2, x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] -such that - !cut1 <-> - or([x_ExplicitVarSizeWithFlags_Flags[q21] /\ x_ExplicitVarSizeWithFlags_Values[q21] = 1 | q21 : int(1..3)]) /\ - or([x_ExplicitVarSizeWithFlags_Flags[q23] /\ x_ExplicitVarSizeWithFlags_Values[q23] = 2 | q23 : int(1..3)]), - !cut2 <-> or([x_ExplicitVarSizeWithDummy[q25] != 4 /\ x_ExplicitVarSizeWithDummy[q25] = 1 | q25 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..2)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..2)]), - and([x_ExplicitVarSizeWithDummy[q6] < x_ExplicitVarSizeWithDummy[q6 + 1] \/ x_ExplicitVarSizeWithDummy[q6] = 4 - | q6 : int(1..2)]), - and([x_ExplicitVarSizeWithDummy[q7] = 4 -> x_ExplicitVarSizeWithDummy[q7 + 1] = 4 | q7 : int(1..2)]), - and([x_ExplicitVarSizeWithDummy[q11] != 4 -> - or([x_ExplicitVarSizeWithFlags_Flags[q13] /\ - x_ExplicitVarSizeWithFlags_Values[q13] = x_ExplicitVarSizeWithDummy[q11] - | q13 : int(1..3)]) - | q11 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q15] -> - or([x_ExplicitVarSizeWithDummy[q17] != 4 /\ - x_ExplicitVarSizeWithDummy[q17] = x_ExplicitVarSizeWithFlags_Values[q15] - | q17 : int(1..3)]) - | q15 : int(1..3)]) - diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_3_1-solution000001.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_3_1-solution000001.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_4_3_1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_3_1-solution000002.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_3_1-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_4_3_1-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_3_1-solution000003.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_3_1-solution000003.solution deleted file mode 100644 index de5cc861ad..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_4_3_1-solution000003.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_3_1-solution000004.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_3_1-solution000004.solution deleted file mode 100644 index a28b6d6203..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_4_3_1-solution000004.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_3_1-solution000005.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_3_1-solution000005.solution deleted file mode 100644 index 1a734343d9..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_4_3_1-solution000005.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_3_1-solution000006.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_3_1-solution000006.solution deleted file mode 100644 index 86a85825b3..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_4_3_1-solution000006.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_3_1-solution000007.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_3_1-solution000007.solution deleted file mode 100644 index 76bc8cdc32..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_4_3_1-solution000007.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_3_1-solution000008.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_3_1-solution000008.solution deleted file mode 100644 index 8dddb3b359..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_4_3_1-solution000008.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_3_1.eprime b/tests/exhaustive/basic/cut_01_on/expected/model_4_3_1.eprime deleted file mode 100644 index 8b7400a457..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_4_3_1.eprime +++ /dev/null @@ -1,49 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..3)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3)] of int(1..3) -find x_ExplicitVarSizeWithMarker_Marker: int(0..3) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3)] of int(1..3) -find x_Occurrence: matrix indexed by [int(1..3)] of bool -find cut1: bool -find cut2: bool -branching on - [cut1, cut2, x_Occurrence, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, - x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] -such that - !cut1 <-> - or([x_ExplicitVarSizeWithFlags_Flags[q31] /\ x_ExplicitVarSizeWithFlags_Values[q31] = 1 | q31 : int(1..3)]) /\ - or([x_ExplicitVarSizeWithFlags_Flags[q33] /\ x_ExplicitVarSizeWithFlags_Values[q33] = 2 | q33 : int(1..3)]), - !cut2 <-> - or([q35 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q35] = 1 | q35 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..2)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..2)]), - and([q6 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q6] < x_ExplicitVarSizeWithMarker_Values[q6 + 1] - | q6 : int(1..2)]), - and([q7 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q7] = 1 | q7 : int(1..3)]), - and([q10 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q12] /\ - x_ExplicitVarSizeWithFlags_Values[q12] = x_ExplicitVarSizeWithMarker_Values[q10] - | q12 : int(1..3)]) - | q10 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q14] -> - or([q16 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q16] = x_ExplicitVarSizeWithFlags_Values[q14] - | q16 : int(1..3)]) - | q14 : int(1..3)]), - and([x_Occurrence[q18] -> - or([x_ExplicitVarSizeWithFlags_Flags[q20] /\ x_ExplicitVarSizeWithFlags_Values[q20] = q18 | q20 : int(1..3)]) - | q18 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q22] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q22]] - | q22 : int(1..3)]), - and([x_Occurrence[q23] -> - or([q25 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q25] = q23 - | q25 : int(1..3)]) - | q23 : int(1..3)]), - and([q27 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q27]] - | q27 : int(1..3)]) - diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_3_2-solution000001.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_3_2-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_4_3_2-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_3_2-solution000002.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_3_2-solution000002.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_4_3_2-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_3_2-solution000003.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_3_2-solution000003.solution deleted file mode 100644 index a28b6d6203..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_4_3_2-solution000003.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_3_2-solution000004.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_3_2-solution000004.solution deleted file mode 100644 index de5cc861ad..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_4_3_2-solution000004.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_3_2-solution000005.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_3_2-solution000005.solution deleted file mode 100644 index 8dddb3b359..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_4_3_2-solution000005.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_3_2-solution000006.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_3_2-solution000006.solution deleted file mode 100644 index 76bc8cdc32..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_4_3_2-solution000006.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_3_2-solution000007.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_3_2-solution000007.solution deleted file mode 100644 index 86a85825b3..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_4_3_2-solution000007.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_3_2-solution000008.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_3_2-solution000008.solution deleted file mode 100644 index 1a734343d9..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_4_3_2-solution000008.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_3_2.eprime b/tests/exhaustive/basic/cut_01_on/expected/model_4_3_2.eprime deleted file mode 100644 index bcc2a527df..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_4_3_2.eprime +++ /dev/null @@ -1,61 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..3)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3)] of int(1..3) -find x_ExplicitVarSizeWithMarker_Marker: int(0..3) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3)] of int(1..3) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..3)] of int(1..4) -find cut1: bool -find cut2: bool -branching on - [cut1, cut2, x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, - x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] -such that - !cut1 <-> - or([x_ExplicitVarSizeWithFlags_Flags[q40] /\ x_ExplicitVarSizeWithFlags_Values[q40] = 1 | q40 : int(1..3)]) /\ - or([x_ExplicitVarSizeWithFlags_Flags[q42] /\ x_ExplicitVarSizeWithFlags_Values[q42] = 2 | q42 : int(1..3)]), - !cut2 <-> - or([q44 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q44] = 1 | q44 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..2)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..2)]), - and([q6 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q6] < x_ExplicitVarSizeWithMarker_Values[q6 + 1] - | q6 : int(1..2)]), - and([q7 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q7] = 1 | q7 : int(1..3)]), - and([q10 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q12] /\ - x_ExplicitVarSizeWithFlags_Values[q12] = x_ExplicitVarSizeWithMarker_Values[q10] - | q12 : int(1..3)]) - | q10 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q14] -> - or([q16 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q16] = x_ExplicitVarSizeWithFlags_Values[q14] - | q16 : int(1..3)]) - | q14 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q17] < x_ExplicitVarSizeWithDummy[q17 + 1] \/ x_ExplicitVarSizeWithDummy[q17] = 4 - | q17 : int(1..2)]), - and([x_ExplicitVarSizeWithDummy[q18] = 4 -> x_ExplicitVarSizeWithDummy[q18 + 1] = 4 | q18 : int(1..2)]), - and([x_ExplicitVarSizeWithDummy[q22] != 4 -> - or([x_ExplicitVarSizeWithFlags_Flags[q24] /\ - x_ExplicitVarSizeWithFlags_Values[q24] = x_ExplicitVarSizeWithDummy[q22] - | q24 : int(1..3)]) - | q22 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q26] -> - or([x_ExplicitVarSizeWithDummy[q28] != 4 /\ - x_ExplicitVarSizeWithDummy[q28] = x_ExplicitVarSizeWithFlags_Values[q26] - | q28 : int(1..3)]) - | q26 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q30] != 4 -> - or([q32 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q32] = x_ExplicitVarSizeWithDummy[q30] - | q32 : int(1..3)]) - | q30 : int(1..3)]), - and([q34 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q36] != 4 /\ - x_ExplicitVarSizeWithDummy[q36] = x_ExplicitVarSizeWithMarker_Values[q34] - | q36 : int(1..3)]) - | q34 : int(1..3)]) - diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_3_3-solution000001.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_3_3-solution000001.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_4_3_3-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_3_3-solution000002.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_3_3-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_4_3_3-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_3_3-solution000003.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_3_3-solution000003.solution deleted file mode 100644 index de5cc861ad..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_4_3_3-solution000003.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_3_3-solution000004.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_3_3-solution000004.solution deleted file mode 100644 index a28b6d6203..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_4_3_3-solution000004.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_3_3-solution000005.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_3_3-solution000005.solution deleted file mode 100644 index 1a734343d9..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_4_3_3-solution000005.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_3_3-solution000006.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_3_3-solution000006.solution deleted file mode 100644 index 76bc8cdc32..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_4_3_3-solution000006.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_3_3-solution000007.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_3_3-solution000007.solution deleted file mode 100644 index 86a85825b3..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_4_3_3-solution000007.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_3_3-solution000008.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_3_3-solution000008.solution deleted file mode 100644 index 8dddb3b359..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_4_3_3-solution000008.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_3_3.eprime b/tests/exhaustive/basic/cut_01_on/expected/model_4_3_3.eprime deleted file mode 100644 index 84c43bef49..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_4_3_3.eprime +++ /dev/null @@ -1,37 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..3)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3)] of int(1..3) -find x_ExplicitVarSizeWithMarker_Marker: int(0..3) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3)] of int(1..3) -find cut1: bool -find cut2: bool -branching on - [cut1, cut2, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, - x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] -such that - !cut1 <-> - or([x_ExplicitVarSizeWithFlags_Flags[q20] /\ x_ExplicitVarSizeWithFlags_Values[q20] = 1 | q20 : int(1..3)]) /\ - or([x_ExplicitVarSizeWithFlags_Flags[q22] /\ x_ExplicitVarSizeWithFlags_Values[q22] = 2 | q22 : int(1..3)]), - !cut2 <-> - or([q24 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q24] = 1 | q24 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..2)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..2)]), - and([q6 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q6] < x_ExplicitVarSizeWithMarker_Values[q6 + 1] - | q6 : int(1..2)]), - and([q7 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q7] = 1 | q7 : int(1..3)]), - and([q10 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q12] /\ - x_ExplicitVarSizeWithFlags_Values[q12] = x_ExplicitVarSizeWithMarker_Values[q10] - | q12 : int(1..3)]) - | q10 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q14] -> - or([q16 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q16] = x_ExplicitVarSizeWithFlags_Values[q14] - | q16 : int(1..3)]) - | q14 : int(1..3)]) - diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_3_4-solution000001.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_3_4-solution000001.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_4_3_4-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_3_4-solution000002.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_3_4-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_4_3_4-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_3_4-solution000003.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_3_4-solution000003.solution deleted file mode 100644 index de5cc861ad..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_4_3_4-solution000003.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_3_4-solution000004.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_3_4-solution000004.solution deleted file mode 100644 index a28b6d6203..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_4_3_4-solution000004.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_3_4-solution000005.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_3_4-solution000005.solution deleted file mode 100644 index 1a734343d9..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_4_3_4-solution000005.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_3_4-solution000006.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_3_4-solution000006.solution deleted file mode 100644 index 76bc8cdc32..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_4_3_4-solution000006.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_3_4-solution000007.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_3_4-solution000007.solution deleted file mode 100644 index 86a85825b3..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_4_3_4-solution000007.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_3_4-solution000008.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_3_4-solution000008.solution deleted file mode 100644 index 8dddb3b359..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_4_3_4-solution000008.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_3_4.eprime b/tests/exhaustive/basic/cut_01_on/expected/model_4_3_4.eprime deleted file mode 100644 index 84c43bef49..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_4_3_4.eprime +++ /dev/null @@ -1,37 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..3)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3)] of int(1..3) -find x_ExplicitVarSizeWithMarker_Marker: int(0..3) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3)] of int(1..3) -find cut1: bool -find cut2: bool -branching on - [cut1, cut2, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, - x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] -such that - !cut1 <-> - or([x_ExplicitVarSizeWithFlags_Flags[q20] /\ x_ExplicitVarSizeWithFlags_Values[q20] = 1 | q20 : int(1..3)]) /\ - or([x_ExplicitVarSizeWithFlags_Flags[q22] /\ x_ExplicitVarSizeWithFlags_Values[q22] = 2 | q22 : int(1..3)]), - !cut2 <-> - or([q24 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q24] = 1 | q24 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..2)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..2)]), - and([q6 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q6] < x_ExplicitVarSizeWithMarker_Values[q6 + 1] - | q6 : int(1..2)]), - and([q7 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q7] = 1 | q7 : int(1..3)]), - and([q10 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q12] /\ - x_ExplicitVarSizeWithFlags_Values[q12] = x_ExplicitVarSizeWithMarker_Values[q10] - | q12 : int(1..3)]) - | q10 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q14] -> - or([q16 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q16] = x_ExplicitVarSizeWithFlags_Values[q14] - | q16 : int(1..3)]) - | q14 : int(1..3)]) - diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_4_1-solution000001.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_4_1-solution000001.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_4_4_1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_4_1-solution000002.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_4_1-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_4_4_1-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_4_1-solution000003.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_4_1-solution000003.solution deleted file mode 100644 index de5cc861ad..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_4_4_1-solution000003.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_4_1-solution000004.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_4_1-solution000004.solution deleted file mode 100644 index a28b6d6203..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_4_4_1-solution000004.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_4_1-solution000005.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_4_1-solution000005.solution deleted file mode 100644 index 1a734343d9..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_4_4_1-solution000005.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_4_1-solution000006.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_4_1-solution000006.solution deleted file mode 100644 index 86a85825b3..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_4_4_1-solution000006.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_4_1-solution000007.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_4_1-solution000007.solution deleted file mode 100644 index 76bc8cdc32..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_4_4_1-solution000007.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_4_1-solution000008.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_4_1-solution000008.solution deleted file mode 100644 index 8dddb3b359..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_4_4_1-solution000008.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_4_1.eprime b/tests/exhaustive/basic/cut_01_on/expected/model_4_4_1.eprime deleted file mode 100644 index 66b360e0c2..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_4_4_1.eprime +++ /dev/null @@ -1,25 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..3)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3)] of int(1..3) -find x_Occurrence: matrix indexed by [int(1..3)] of bool -find cut1: bool -find cut2: bool -branching on [cut1, cut2, x_Occurrence, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] -such that - !cut1 <-> - or([x_ExplicitVarSizeWithFlags_Flags[q15] /\ x_ExplicitVarSizeWithFlags_Values[q15] = 1 | q15 : int(1..3)]) /\ - or([x_ExplicitVarSizeWithFlags_Flags[q17] /\ x_ExplicitVarSizeWithFlags_Values[q17] = 2 | q17 : int(1..3)]), - !cut2 <-> - or([x_ExplicitVarSizeWithFlags_Flags[q19] /\ x_ExplicitVarSizeWithFlags_Values[q19] = 1 | q19 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..2)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..2)]), - and([x_Occurrence[q7] -> - or([x_ExplicitVarSizeWithFlags_Flags[q9] /\ x_ExplicitVarSizeWithFlags_Values[q9] = q7 | q9 : int(1..3)]) - | q7 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q11] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q11]] - | q11 : int(1..3)]) - diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_4_2-solution000001.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_4_2-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_4_4_2-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_4_2-solution000002.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_4_2-solution000002.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_4_4_2-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_4_2-solution000003.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_4_2-solution000003.solution deleted file mode 100644 index a28b6d6203..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_4_4_2-solution000003.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_4_2-solution000004.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_4_2-solution000004.solution deleted file mode 100644 index de5cc861ad..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_4_4_2-solution000004.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_4_2-solution000005.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_4_2-solution000005.solution deleted file mode 100644 index 8dddb3b359..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_4_4_2-solution000005.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_4_2-solution000006.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_4_2-solution000006.solution deleted file mode 100644 index 76bc8cdc32..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_4_4_2-solution000006.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_4_2-solution000007.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_4_2-solution000007.solution deleted file mode 100644 index 86a85825b3..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_4_4_2-solution000007.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_4_2-solution000008.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_4_2-solution000008.solution deleted file mode 100644 index 1a734343d9..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_4_4_2-solution000008.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_4_2.eprime b/tests/exhaustive/basic/cut_01_on/expected/model_4_4_2.eprime deleted file mode 100644 index a3fd9fd7a5..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_4_4_2.eprime +++ /dev/null @@ -1,34 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..3)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3)] of int(1..3) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..3)] of int(1..4) -find cut1: bool -find cut2: bool -branching on - [cut1, cut2, x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] -such that - !cut1 <-> - or([x_ExplicitVarSizeWithFlags_Flags[q21] /\ x_ExplicitVarSizeWithFlags_Values[q21] = 1 | q21 : int(1..3)]) /\ - or([x_ExplicitVarSizeWithFlags_Flags[q23] /\ x_ExplicitVarSizeWithFlags_Values[q23] = 2 | q23 : int(1..3)]), - !cut2 <-> - or([x_ExplicitVarSizeWithFlags_Flags[q25] /\ x_ExplicitVarSizeWithFlags_Values[q25] = 1 | q25 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..2)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..2)]), - and([x_ExplicitVarSizeWithDummy[q6] < x_ExplicitVarSizeWithDummy[q6 + 1] \/ x_ExplicitVarSizeWithDummy[q6] = 4 - | q6 : int(1..2)]), - and([x_ExplicitVarSizeWithDummy[q7] = 4 -> x_ExplicitVarSizeWithDummy[q7 + 1] = 4 | q7 : int(1..2)]), - and([x_ExplicitVarSizeWithDummy[q11] != 4 -> - or([x_ExplicitVarSizeWithFlags_Flags[q13] /\ - x_ExplicitVarSizeWithFlags_Values[q13] = x_ExplicitVarSizeWithDummy[q11] - | q13 : int(1..3)]) - | q11 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q15] -> - or([x_ExplicitVarSizeWithDummy[q17] != 4 /\ - x_ExplicitVarSizeWithDummy[q17] = x_ExplicitVarSizeWithFlags_Values[q15] - | q17 : int(1..3)]) - | q15 : int(1..3)]) - diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_4_3-solution000001.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_4_3-solution000001.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_4_4_3-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_4_3-solution000002.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_4_3-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_4_4_3-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_4_3-solution000003.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_4_3-solution000003.solution deleted file mode 100644 index de5cc861ad..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_4_4_3-solution000003.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_4_3-solution000004.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_4_3-solution000004.solution deleted file mode 100644 index a28b6d6203..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_4_4_3-solution000004.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_4_3-solution000005.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_4_3-solution000005.solution deleted file mode 100644 index 1a734343d9..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_4_4_3-solution000005.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_4_3-solution000006.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_4_3-solution000006.solution deleted file mode 100644 index 76bc8cdc32..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_4_4_3-solution000006.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_4_3-solution000007.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_4_3-solution000007.solution deleted file mode 100644 index 86a85825b3..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_4_4_3-solution000007.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_4_3-solution000008.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_4_3-solution000008.solution deleted file mode 100644 index 8dddb3b359..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_4_4_3-solution000008.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_4_3.eprime b/tests/exhaustive/basic/cut_01_on/expected/model_4_4_3.eprime deleted file mode 100644 index 585ff89036..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_4_4_3.eprime +++ /dev/null @@ -1,37 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..3)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3)] of int(1..3) -find x_ExplicitVarSizeWithMarker_Marker: int(0..3) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3)] of int(1..3) -find cut1: bool -find cut2: bool -branching on - [cut1, cut2, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, - x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] -such that - !cut1 <-> - or([x_ExplicitVarSizeWithFlags_Flags[q20] /\ x_ExplicitVarSizeWithFlags_Values[q20] = 1 | q20 : int(1..3)]) /\ - or([x_ExplicitVarSizeWithFlags_Flags[q22] /\ x_ExplicitVarSizeWithFlags_Values[q22] = 2 | q22 : int(1..3)]), - !cut2 <-> - or([x_ExplicitVarSizeWithFlags_Flags[q24] /\ x_ExplicitVarSizeWithFlags_Values[q24] = 1 | q24 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..2)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..2)]), - and([q6 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q6] < x_ExplicitVarSizeWithMarker_Values[q6 + 1] - | q6 : int(1..2)]), - and([q7 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q7] = 1 | q7 : int(1..3)]), - and([q10 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q12] /\ - x_ExplicitVarSizeWithFlags_Values[q12] = x_ExplicitVarSizeWithMarker_Values[q10] - | q12 : int(1..3)]) - | q10 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q14] -> - or([q16 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q16] = x_ExplicitVarSizeWithFlags_Values[q14] - | q16 : int(1..3)]) - | q14 : int(1..3)]) - diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_4_4-solution000001.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_4_4-solution000001.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_4_4_4-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_4_4-solution000002.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_4_4-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_4_4_4-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_4_4-solution000003.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_4_4-solution000003.solution deleted file mode 100644 index de5cc861ad..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_4_4_4-solution000003.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_4_4-solution000004.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_4_4-solution000004.solution deleted file mode 100644 index a28b6d6203..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_4_4_4-solution000004.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_4_4-solution000005.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_4_4-solution000005.solution deleted file mode 100644 index 1a734343d9..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_4_4_4-solution000005.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_4_4-solution000006.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_4_4-solution000006.solution deleted file mode 100644 index 76bc8cdc32..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_4_4_4-solution000006.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_4_4-solution000007.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_4_4-solution000007.solution deleted file mode 100644 index 86a85825b3..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_4_4_4-solution000007.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_4_4-solution000008.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_4_4-solution000008.solution deleted file mode 100644 index 8dddb3b359..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_4_4_4-solution000008.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_4_4.eprime b/tests/exhaustive/basic/cut_01_on/expected/model_4_4_4.eprime deleted file mode 100644 index b250cd861e..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_4_4_4.eprime +++ /dev/null @@ -1,19 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..3)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3)] of int(1..3) -find cut1: bool -find cut2: bool -branching on [cut1, cut2, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] -such that - !cut1 <-> - or([x_ExplicitVarSizeWithFlags_Flags[q9] /\ x_ExplicitVarSizeWithFlags_Values[q9] = 1 | q9 : int(1..3)]) /\ - or([x_ExplicitVarSizeWithFlags_Flags[q11] /\ x_ExplicitVarSizeWithFlags_Values[q11] = 2 | q11 : int(1..3)]), - !cut2 <-> - or([x_ExplicitVarSizeWithFlags_Flags[q13] /\ x_ExplicitVarSizeWithFlags_Values[q13] = 1 | q13 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..2)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..2)]) - diff --git a/tests/exhaustive/basic/enum_functions/expected/model-p1-solution000001.solution b/tests/exhaustive/basic/enum_functions/expected/model-p1-solution000001.solution deleted file mode 100644 index 57b62ee93f..0000000000 --- a/tests/exhaustive/basic/enum_functions/expected/model-p1-solution000001.solution +++ /dev/null @@ -1,12 +0,0 @@ -language Essence 1.3 - -letting f be function(a --> b1, b --> b2, c --> b5) -letting g be function(b1 --> c, b4 --> b, b5 --> a) -letting t be a -letting t2 be b3 -letting x be a -letting x2 be b1 -letting y be c -letting y2 be b5 -letting z be b -letting z2 be b2 diff --git a/tests/exhaustive/basic/enum_functions/expected/model-p1-solution000002.solution b/tests/exhaustive/basic/enum_functions/expected/model-p1-solution000002.solution deleted file mode 100644 index c34674aec0..0000000000 --- a/tests/exhaustive/basic/enum_functions/expected/model-p1-solution000002.solution +++ /dev/null @@ -1,12 +0,0 @@ -language Essence 1.3 - -letting f be function(a --> b1, b --> b2, c --> b5) -letting g be function(b1 --> c, b3 --> b, b5 --> a) -letting t be a -letting t2 be b3 -letting x be a -letting x2 be b1 -letting y be c -letting y2 be b5 -letting z be b -letting z2 be b2 diff --git a/tests/exhaustive/basic/enum_functions/expected/model-p1-solution000003.solution b/tests/exhaustive/basic/enum_functions/expected/model-p1-solution000003.solution deleted file mode 100644 index 01a3a5313d..0000000000 --- a/tests/exhaustive/basic/enum_functions/expected/model-p1-solution000003.solution +++ /dev/null @@ -1,12 +0,0 @@ -language Essence 1.3 - -letting f be function(a --> b1, b --> b2, c --> b5) -letting g be function(b1 --> c, b2 --> b, b5 --> a) -letting t be a -letting t2 be b3 -letting x be a -letting x2 be b1 -letting y be c -letting y2 be b5 -letting z be b -letting z2 be b2 diff --git a/tests/exhaustive/basic/enum_functions/expected/model-p1-solution000004.solution b/tests/exhaustive/basic/enum_functions/expected/model-p1-solution000004.solution deleted file mode 100644 index eb729adcda..0000000000 --- a/tests/exhaustive/basic/enum_functions/expected/model-p1-solution000004.solution +++ /dev/null @@ -1,12 +0,0 @@ -language Essence 1.3 - -letting f be function(a --> b1, b --> b3, c --> b5) -letting g be function(b1 --> c, b4 --> b, b5 --> a) -letting t be a -letting t2 be b3 -letting x be a -letting x2 be b1 -letting y be c -letting y2 be b5 -letting z be b -letting z2 be b2 diff --git a/tests/exhaustive/basic/enum_functions/expected/model-p1-solution000005.solution b/tests/exhaustive/basic/enum_functions/expected/model-p1-solution000005.solution deleted file mode 100644 index 2e94685b85..0000000000 --- a/tests/exhaustive/basic/enum_functions/expected/model-p1-solution000005.solution +++ /dev/null @@ -1,12 +0,0 @@ -language Essence 1.3 - -letting f be function(a --> b1, b --> b3, c --> b5) -letting g be function(b1 --> c, b3 --> b, b5 --> a) -letting t be a -letting t2 be b3 -letting x be a -letting x2 be b1 -letting y be c -letting y2 be b5 -letting z be b -letting z2 be b2 diff --git a/tests/exhaustive/basic/enum_functions/expected/model-p1-solution000006.solution b/tests/exhaustive/basic/enum_functions/expected/model-p1-solution000006.solution deleted file mode 100644 index 26feac7b12..0000000000 --- a/tests/exhaustive/basic/enum_functions/expected/model-p1-solution000006.solution +++ /dev/null @@ -1,12 +0,0 @@ -language Essence 1.3 - -letting f be function(a --> b1, b --> b3, c --> b5) -letting g be function(b1 --> c, b2 --> b, b5 --> a) -letting t be a -letting t2 be b3 -letting x be a -letting x2 be b1 -letting y be c -letting y2 be b5 -letting z be b -letting z2 be b2 diff --git a/tests/exhaustive/basic/enum_functions/expected/model-p1-solution000007.solution b/tests/exhaustive/basic/enum_functions/expected/model-p1-solution000007.solution deleted file mode 100644 index b44f721a5b..0000000000 --- a/tests/exhaustive/basic/enum_functions/expected/model-p1-solution000007.solution +++ /dev/null @@ -1,12 +0,0 @@ -language Essence 1.3 - -letting f be function(a --> b1, b --> b4, c --> b5) -letting g be function(b1 --> c, b4 --> b, b5 --> a) -letting t be a -letting t2 be b3 -letting x be a -letting x2 be b1 -letting y be c -letting y2 be b5 -letting z be b -letting z2 be b2 diff --git a/tests/exhaustive/basic/enum_functions/expected/model-p1-solution000008.solution b/tests/exhaustive/basic/enum_functions/expected/model-p1-solution000008.solution deleted file mode 100644 index 0658219f70..0000000000 --- a/tests/exhaustive/basic/enum_functions/expected/model-p1-solution000008.solution +++ /dev/null @@ -1,12 +0,0 @@ -language Essence 1.3 - -letting f be function(a --> b1, b --> b4, c --> b5) -letting g be function(b1 --> c, b3 --> b, b5 --> a) -letting t be a -letting t2 be b3 -letting x be a -letting x2 be b1 -letting y be c -letting y2 be b5 -letting z be b -letting z2 be b2 diff --git a/tests/exhaustive/basic/enum_functions/expected/model-p1-solution000009.solution b/tests/exhaustive/basic/enum_functions/expected/model-p1-solution000009.solution deleted file mode 100644 index c7e024f51f..0000000000 --- a/tests/exhaustive/basic/enum_functions/expected/model-p1-solution000009.solution +++ /dev/null @@ -1,12 +0,0 @@ -language Essence 1.3 - -letting f be function(a --> b1, b --> b4, c --> b5) -letting g be function(b1 --> c, b2 --> b, b5 --> a) -letting t be a -letting t2 be b3 -letting x be a -letting x2 be b1 -letting y be c -letting y2 be b5 -letting z be b -letting z2 be b2 diff --git a/tests/exhaustive/basic/enum_functions/expected/model-p1.eprime-param b/tests/exhaustive/basic/enum_functions/expected/model-p1.eprime-param deleted file mode 100644 index 6cf8732242..0000000000 --- a/tests/exhaustive/basic/enum_functions/expected/model-p1.eprime-param +++ /dev/null @@ -1,3 +0,0 @@ -language ESSENCE' 1.0 - -letting B_EnumSize be 5 diff --git a/tests/exhaustive/basic/enum_functions/expected/model.eprime b/tests/exhaustive/basic/enum_functions/expected/model.eprime deleted file mode 100644 index 5070b7daf5..0000000000 --- a/tests/exhaustive/basic/enum_functions/expected/model.eprime +++ /dev/null @@ -1,122 +0,0 @@ -language ESSENCE' 1.0 - -find x: int(1..3) -find y: int(1..3) -find z: int(1..3) -find t: int(1..3) -given B_EnumSize: int -find x2: int(1..B_EnumSize) -find y2: int(1..B_EnumSize) -find z2: int(1..B_EnumSize) -find t2: int(1..B_EnumSize) -find f_Function1DPartial_Flags: matrix indexed by [int(1..3)] of bool -find f_Function1DPartial_Values: matrix indexed by [int(1..3)] of int(1..B_EnumSize) -find g_Function1DPartial_Flags: matrix indexed by [int(1..B_EnumSize)] of bool -find g_Function1DPartial_Values: matrix indexed by [int(1..B_EnumSize)] of int(1..3) -branching on - [x, y, z, t, x2, y2, z2, t2, f_Function1DPartial_Flags, f_Function1DPartial_Values, g_Function1DPartial_Flags, - g_Function1DPartial_Values] -such that - x = 1, - y = 3, - z = 2, - t = 1, - x2 = 1, - y2 = B_EnumSize, - z2 = 2, - t2 = B_EnumSize - 1 - 1, - f_Function1DPartial_Values[1] = 1, - f_Function1DPartial_Flags[1], - f_Function1DPartial_Values[3] = B_EnumSize, - f_Function1DPartial_Flags[3], - and([and([f_Function1DPartial_Values[i] < f_Function1DPartial_Values[i + 1], f_Function1DPartial_Flags[i], - f_Function1DPartial_Flags[i + 1]; - int(1..3)]) - | i : int(1..2)]), - and([or([f_Function1DPartial_Flags[q12] /\ - (toInt(or([f_Function1DPartial_Flags[q37] /\ - f_Function1DPartial_Values[q37] = f_Function1DPartial_Values[q12] - | q37 : int(1..3), q37 = i + 1])) - < - toInt(or([f_Function1DPartial_Flags[q15] /\ - f_Function1DPartial_Values[q15] = f_Function1DPartial_Values[q12] - | q15 : int(1..3), q15 = i])) - /\ - (and([f_Function1DPartial_Flags[q17] /\ f_Function1DPartial_Values[q17] < f_Function1DPartial_Values[q12] - -> - toInt(or([f_Function1DPartial_Flags[q23] /\ - f_Function1DPartial_Values[q23] = f_Function1DPartial_Values[q17] - | q23 : int(1..3), q23 = i + 1])) - = - toInt(or([f_Function1DPartial_Flags[q20] /\ - f_Function1DPartial_Values[q20] = f_Function1DPartial_Values[q17] - | q20 : int(1..3), q20 = i])) - | q17 : int(1..3), q17 = i + 1]) - /\ - and([and([f_Function1DPartial_Flags[q25], - !or([f_Function1DPartial_Flags[q31] /\ - f_Function1DPartial_Values[q31] = f_Function1DPartial_Values[q25] - | q31 : int(1..3), q31 = i + 1]), - f_Function1DPartial_Values[q25] < f_Function1DPartial_Values[q12]; - int(1..3)]) - -> - toInt(or([f_Function1DPartial_Flags[q34] /\ - f_Function1DPartial_Values[q34] = f_Function1DPartial_Values[q25] - | q34 : int(1..3), q34 = i + 1])) - = - toInt(or([f_Function1DPartial_Flags[q28] /\ - f_Function1DPartial_Values[q28] = f_Function1DPartial_Values[q25] - | q28 : int(1..3), q28 = i])) - | q25 : int(1..3), q25 = i]))) - | q12 : int(1..3), q12 = i + 1]) - \/ - or([f_Function1DPartial_Flags[q39] /\ - !or([f_Function1DPartial_Flags[q67] /\ f_Function1DPartial_Values[q67] = f_Function1DPartial_Values[q39] - | q67 : int(1..3), q67 = i + 1]) - /\ - (toInt(or([f_Function1DPartial_Flags[q64] /\ - f_Function1DPartial_Values[q64] = f_Function1DPartial_Values[q39] - | q64 : int(1..3), q64 = i + 1])) - < - toInt(or([f_Function1DPartial_Flags[q42] /\ - f_Function1DPartial_Values[q42] = f_Function1DPartial_Values[q39] - | q42 : int(1..3), q42 = i])) - /\ - (and([f_Function1DPartial_Flags[q44] /\ f_Function1DPartial_Values[q44] < f_Function1DPartial_Values[q39] - -> - toInt(or([f_Function1DPartial_Flags[q50] /\ - f_Function1DPartial_Values[q50] = f_Function1DPartial_Values[q44] - | q50 : int(1..3), q50 = i + 1])) - = - toInt(or([f_Function1DPartial_Flags[q47] /\ - f_Function1DPartial_Values[q47] = f_Function1DPartial_Values[q44] - | q47 : int(1..3), q47 = i])) - | q44 : int(1..3), q44 = i + 1]) - /\ - and([and([f_Function1DPartial_Flags[q52], - !or([f_Function1DPartial_Flags[q58] /\ - f_Function1DPartial_Values[q58] = f_Function1DPartial_Values[q52] - | q58 : int(1..3), q58 = i + 1]), - f_Function1DPartial_Values[q52] < f_Function1DPartial_Values[q39]; - int(1..3)]) - -> - toInt(or([f_Function1DPartial_Flags[q61] /\ - f_Function1DPartial_Values[q61] = f_Function1DPartial_Values[q52] - | q61 : int(1..3), q61 = i + 1])) - = - toInt(or([f_Function1DPartial_Flags[q55] /\ - f_Function1DPartial_Values[q55] = f_Function1DPartial_Values[q52] - | q55 : int(1..3), q55 = i])) - | q52 : int(1..3), q52 = i]))) - | q39 : int(1..3), q39 = i]) - | i : int(1..2)]), - g_Function1DPartial_Values[1] = 3, - g_Function1DPartial_Flags[1], - g_Function1DPartial_Values[B_EnumSize] = 1, - g_Function1DPartial_Flags[B_EnumSize], - and([f_Function1DPartial_Flags[q1] = false -> f_Function1DPartial_Values[q1] = 1 | q1 : int(1..3)]), - and([or([g_Function1DPartial_Flags[q5] /\ g_Function1DPartial_Values[q5] = q4 | q5 : int(1..B_EnumSize)]) - | q4 : int(1..3)]), - and([g_Function1DPartial_Flags[q6] = false -> g_Function1DPartial_Values[q6] = 1 | q6 : int(1..B_EnumSize)]), - 3 = sum([toInt(g_Function1DPartial_Flags[q7]) | q7 : int(1..B_EnumSize)]) - diff --git a/tests/exhaustive/basic/function_complex_01/expected/model_1-solution000001.solution b/tests/exhaustive/basic/function_complex_01/expected/model_1-solution000001.solution deleted file mode 100644 index 2e109b6d40..0000000000 --- a/tests/exhaustive/basic/function_complex_01/expected/model_1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be function({(7, false)} --> 17, {(7, true)} --> 13) diff --git a/tests/exhaustive/basic/function_complex_01/expected/model_1-solution000002.solution b/tests/exhaustive/basic/function_complex_01/expected/model_1-solution000002.solution deleted file mode 100644 index 626dde8770..0000000000 --- a/tests/exhaustive/basic/function_complex_01/expected/model_1-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be function({(7, false)} --> 13, {(7, true)} --> 17) diff --git a/tests/exhaustive/basic/function_complex_01/expected/model_1-solution000003.solution b/tests/exhaustive/basic/function_complex_01/expected/model_1-solution000003.solution deleted file mode 100644 index 5ebd8e1209..0000000000 --- a/tests/exhaustive/basic/function_complex_01/expected/model_1-solution000003.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be function({(7, false)} --> 13, {(7, false), (7, true)} --> 17) diff --git a/tests/exhaustive/basic/function_complex_01/expected/model_1-solution000004.solution b/tests/exhaustive/basic/function_complex_01/expected/model_1-solution000004.solution deleted file mode 100644 index ee811eb7ab..0000000000 --- a/tests/exhaustive/basic/function_complex_01/expected/model_1-solution000004.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be function({(7, false)} --> 17, {(7, false), (7, true)} --> 13) diff --git a/tests/exhaustive/basic/function_complex_01/expected/model_1-solution000005.solution b/tests/exhaustive/basic/function_complex_01/expected/model_1-solution000005.solution deleted file mode 100644 index 30b06b719d..0000000000 --- a/tests/exhaustive/basic/function_complex_01/expected/model_1-solution000005.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be function({(7, false), (7, true)} --> 17, {(7, true)} --> 13) diff --git a/tests/exhaustive/basic/function_complex_01/expected/model_1-solution000006.solution b/tests/exhaustive/basic/function_complex_01/expected/model_1-solution000006.solution deleted file mode 100644 index 65f731a60d..0000000000 --- a/tests/exhaustive/basic/function_complex_01/expected/model_1-solution000006.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be function({(7, false), (7, true)} --> 13, {(7, true)} --> 17) diff --git a/tests/exhaustive/basic/function_complex_01/expected/model_1.eprime b/tests/exhaustive/basic/function_complex_01/expected/model_1.eprime deleted file mode 100644 index 37782b4f46..0000000000 --- a/tests/exhaustive/basic/function_complex_01/expected/model_1.eprime +++ /dev/null @@ -1,174 +0,0 @@ -language ESSENCE' 1.0 - -find x_FunctionAsRelationR5_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Marker: int(0..3) -find x_FunctionAsRelationR5_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_1_ExplicitVarSizeWithMarker_Marker: - matrix indexed by [int(1..3)] of int(0..2) -find x_FunctionAsRelationR5_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_1_ExplicitVarSizeWithMarker_Values_1: - matrix indexed by [int(1..3), int(1..2)] of int(7) -find x_FunctionAsRelationR5_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_1_ExplicitVarSizeWithMarker_Values_2: - matrix indexed by [int(1..3), int(1..2)] of bool -find x_FunctionAsRelationR5_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2: - matrix indexed by [int(1..3)] of int(13, 17) -branching on - [x_FunctionAsRelationR5_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Marker, - x_FunctionAsRelationR5_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_1_ExplicitVarSizeWithMarker_Marker, - x_FunctionAsRelationR5_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_1_ExplicitVarSizeWithMarker_Values_1, - x_FunctionAsRelationR5_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_1_ExplicitVarSizeWithMarker_Values_2, - x_FunctionAsRelationR5_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2] -such that - and([q1 + 1 <= x_FunctionAsRelationR5_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Marker -> - flatten([flatten([[x_FunctionAsRelationR5_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_1_ExplicitVarSizeWithMarker_Marker - [q1]; - int(1)], - flatten([flatten([[x_FunctionAsRelationR5_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_1_ExplicitVarSizeWithMarker_Values_1 - [q1, q11]; - int(1)], - [-toInt(x_FunctionAsRelationR5_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_1_ExplicitVarSizeWithMarker_Values_2 - [q1, q11]); - int(1)]; - int(1..2)]) - | q11 : int(1..2)]); - int(1..2)]), - [x_FunctionAsRelationR5_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2[q1]; int(1)]; - int(1..2)]) - x_FunctionAsRelationR5_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Marker -> - x_FunctionAsRelationR5_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_1_ExplicitVarSizeWithMarker_Marker - [q2] - = 0 - /\ - and([x_FunctionAsRelationR5_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_1_ExplicitVarSizeWithMarker_Values_1 - [q2, q25] - = 7 - /\ - x_FunctionAsRelationR5_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_1_ExplicitVarSizeWithMarker_Values_2 - [q2, q25] - = false - | q25 : int(1..2)]) - /\ x_FunctionAsRelationR5_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2[q2] = 13 - | q2 : int(1..3)]), - 2 <= x_FunctionAsRelationR5_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Marker, - x_FunctionAsRelationR5_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Marker <= 3, - and([q3 <= x_FunctionAsRelationR5_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Marker -> - (2 <= - x_FunctionAsRelationR5_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_1_ExplicitVarSizeWithMarker_Marker - [q3] - -> - flatten([[x_FunctionAsRelationR5_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_1_ExplicitVarSizeWithMarker_Values_1 - [q3, 1]; - int(1)], - [-toInt(x_FunctionAsRelationR5_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_1_ExplicitVarSizeWithMarker_Values_2 - [q3, 1]); - int(1)]; - int(1..2)]) - - and([q5 > - x_FunctionAsRelationR5_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_1_ExplicitVarSizeWithMarker_Marker - [q3] - -> - x_FunctionAsRelationR5_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_1_ExplicitVarSizeWithMarker_Values_1 - [q3, q5] - = 7 - /\ - x_FunctionAsRelationR5_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_1_ExplicitVarSizeWithMarker_Values_2 - [q3, q5] - = false - | q5 : int(1..2)]) - | q3 : int(1..3)]), - and([q3 <= x_FunctionAsRelationR5_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Marker -> - 1 <= - x_FunctionAsRelationR5_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_1_ExplicitVarSizeWithMarker_Marker - [q3] - | q3 : int(1..3)]), - and([q3 <= x_FunctionAsRelationR5_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Marker -> - x_FunctionAsRelationR5_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_1_ExplicitVarSizeWithMarker_Marker - [q3] - <= 2 - | q3 : int(1..3)]), - and([1 >= - sum([toInt(q16 <= x_FunctionAsRelationR5_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Marker /\ - and([x_FunctionAsRelationR5_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_1_ExplicitVarSizeWithMarker_Marker - [q16] - = q7_ExplicitVarSizeWithMarker_Marker, - and([x_FunctionAsRelationR5_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_1_ExplicitVarSizeWithMarker_Values_1 - [q16, q17] - = q7_ExplicitVarSizeWithMarker_Values_1[q17] - | q17 : int(1..2)]), - and([x_FunctionAsRelationR5_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_1_ExplicitVarSizeWithMarker_Values_2 - [q16, q19] - = q7_ExplicitVarSizeWithMarker_Values_2[q19] - | q19 : int(1..2)]); - int(1..3)])) - | q16 : int(1..3)]) - | q7_ExplicitVarSizeWithMarker_Marker : int(0..2), - q7_ExplicitVarSizeWithMarker_Values_1 : matrix indexed by [int(1..2)] of int(7), - q7_ExplicitVarSizeWithMarker_Values_2 : matrix indexed by [int(1..2)] of bool, - 2 <= q7_ExplicitVarSizeWithMarker_Marker -> - flatten([[q7_ExplicitVarSizeWithMarker_Values_1[1]; int(1)], - [-toInt(q7_ExplicitVarSizeWithMarker_Values_2[1]); int(1)]; - int(1..2)]) - q7_ExplicitVarSizeWithMarker_Marker -> - q7_ExplicitVarSizeWithMarker_Values_1[q14] = 7 /\ q7_ExplicitVarSizeWithMarker_Values_2[q14] = false - | q14 : int(1..2)]), - 1 <= q7_ExplicitVarSizeWithMarker_Marker, q7_ExplicitVarSizeWithMarker_Marker <= 2]), - and([q21 <= x_FunctionAsRelationR5_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Marker /\ - q22 <= x_FunctionAsRelationR5_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Marker - -> - (flatten([[x_FunctionAsRelationR5_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_1_ExplicitVarSizeWithMarker_Marker - [q21]; - int(1)], - flatten([flatten([[x_FunctionAsRelationR5_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_1_ExplicitVarSizeWithMarker_Values_1 - [q21, q23]; - int(1)], - [-toInt(x_FunctionAsRelationR5_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_1_ExplicitVarSizeWithMarker_Values_2 - [q21, q23]); - int(1)]; - int(1..2)]) - | q23 : int(1..2)]); - int(1..2)]) - - x_FunctionAsRelationR5_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2[q21] != - x_FunctionAsRelationR5_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2[q22]) - | q21 : int(1..3), q22 : int(1..3)]) - diff --git a/tests/exhaustive/basic/function_complex_01/expected/model_2-solution000001.solution b/tests/exhaustive/basic/function_complex_01/expected/model_2-solution000001.solution deleted file mode 100644 index 2e109b6d40..0000000000 --- a/tests/exhaustive/basic/function_complex_01/expected/model_2-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be function({(7, false)} --> 17, {(7, true)} --> 13) diff --git a/tests/exhaustive/basic/function_complex_01/expected/model_2-solution000002.solution b/tests/exhaustive/basic/function_complex_01/expected/model_2-solution000002.solution deleted file mode 100644 index 626dde8770..0000000000 --- a/tests/exhaustive/basic/function_complex_01/expected/model_2-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be function({(7, false)} --> 13, {(7, true)} --> 17) diff --git a/tests/exhaustive/basic/function_complex_01/expected/model_2-solution000003.solution b/tests/exhaustive/basic/function_complex_01/expected/model_2-solution000003.solution deleted file mode 100644 index ee811eb7ab..0000000000 --- a/tests/exhaustive/basic/function_complex_01/expected/model_2-solution000003.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be function({(7, false)} --> 17, {(7, false), (7, true)} --> 13) diff --git a/tests/exhaustive/basic/function_complex_01/expected/model_2-solution000004.solution b/tests/exhaustive/basic/function_complex_01/expected/model_2-solution000004.solution deleted file mode 100644 index 5ebd8e1209..0000000000 --- a/tests/exhaustive/basic/function_complex_01/expected/model_2-solution000004.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be function({(7, false)} --> 13, {(7, false), (7, true)} --> 17) diff --git a/tests/exhaustive/basic/function_complex_01/expected/model_2-solution000005.solution b/tests/exhaustive/basic/function_complex_01/expected/model_2-solution000005.solution deleted file mode 100644 index 65f731a60d..0000000000 --- a/tests/exhaustive/basic/function_complex_01/expected/model_2-solution000005.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be function({(7, false), (7, true)} --> 13, {(7, true)} --> 17) diff --git a/tests/exhaustive/basic/function_complex_01/expected/model_2-solution000006.solution b/tests/exhaustive/basic/function_complex_01/expected/model_2-solution000006.solution deleted file mode 100644 index 30b06b719d..0000000000 --- a/tests/exhaustive/basic/function_complex_01/expected/model_2-solution000006.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be function({(7, false), (7, true)} --> 17, {(7, true)} --> 13) diff --git a/tests/exhaustive/basic/function_complex_01/expected/model_2.eprime b/tests/exhaustive/basic/function_complex_01/expected/model_2.eprime deleted file mode 100644 index 1626b2151b..0000000000 --- a/tests/exhaustive/basic/function_complex_01/expected/model_2.eprime +++ /dev/null @@ -1,196 +0,0 @@ -language ESSENCE' 1.0 - -find x_FunctionAsRelationR4_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Marker: int(0..3) -find x_FunctionAsRelationR4_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_1_ExplicitVarSizeWithFlags_Flags: - matrix indexed by [int(1..3), int(1..2)] of bool -find x_FunctionAsRelationR4_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_1_ExplicitVarSizeWithFlags_Values_1: - matrix indexed by [int(1..3), int(1..2)] of int(7) -find x_FunctionAsRelationR4_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_1_ExplicitVarSizeWithFlags_Values_2: - matrix indexed by [int(1..3), int(1..2)] of bool -find x_FunctionAsRelationR4_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2: - matrix indexed by [int(1..3)] of int(13, 17) -branching on - [x_FunctionAsRelationR4_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Marker, - x_FunctionAsRelationR4_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_1_ExplicitVarSizeWithFlags_Flags, - x_FunctionAsRelationR4_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_1_ExplicitVarSizeWithFlags_Values_1, - x_FunctionAsRelationR4_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_1_ExplicitVarSizeWithFlags_Values_2, - x_FunctionAsRelationR4_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2] -such that - and([q1 + 1 <= x_FunctionAsRelationR4_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Marker -> - flatten([flatten([flatten([[-toInt(x_FunctionAsRelationR4_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_1_ExplicitVarSizeWithFlags_Flags - [q1, q13]); - int(1)], - flatten([[x_FunctionAsRelationR4_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_1_ExplicitVarSizeWithFlags_Values_1 - [q1, q13]; - int(1)], - [-toInt(x_FunctionAsRelationR4_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_1_ExplicitVarSizeWithFlags_Values_2 - [q1, q13]); - int(1)]; - int(1..2)]); - int(1..2)]) - | q13 : int(1..2)]), - [x_FunctionAsRelationR4_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2[q1]; int(1)]; - int(1..2)]) - x_FunctionAsRelationR4_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Marker -> - and([x_FunctionAsRelationR4_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_1_ExplicitVarSizeWithFlags_Flags - [q2, q31] - = false - | q31 : int(1..2)]) - /\ - and([x_FunctionAsRelationR4_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_1_ExplicitVarSizeWithFlags_Values_1 - [q2, q32] - = 7 - /\ - x_FunctionAsRelationR4_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_1_ExplicitVarSizeWithFlags_Values_2 - [q2, q32] - = false - | q32 : int(1..2)]) - /\ x_FunctionAsRelationR4_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2[q2] = 13 - | q2 : int(1..3)]), - 2 <= x_FunctionAsRelationR4_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Marker, - x_FunctionAsRelationR4_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Marker <= 3, - and([q3 <= x_FunctionAsRelationR4_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Marker -> - (x_FunctionAsRelationR4_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_1_ExplicitVarSizeWithFlags_Flags - [q3, 2] - -> - flatten([[x_FunctionAsRelationR4_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_1_ExplicitVarSizeWithFlags_Values_1 - [q3, 1]; - int(1)], - [-toInt(x_FunctionAsRelationR4_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_1_ExplicitVarSizeWithFlags_Values_2 - [q3, 1]); - int(1)]; - int(1..2)]) - - and([x_FunctionAsRelationR4_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_1_ExplicitVarSizeWithFlags_Flags - [q3, q5] - = false - -> - x_FunctionAsRelationR4_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_1_ExplicitVarSizeWithFlags_Values_1 - [q3, q5] - = 7 - /\ - x_FunctionAsRelationR4_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_1_ExplicitVarSizeWithFlags_Values_2 - [q3, q5] - = false - | q5 : int(1..2)]) - | q3 : int(1..3)]), - and([q3 <= x_FunctionAsRelationR4_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Marker -> - (x_FunctionAsRelationR4_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_1_ExplicitVarSizeWithFlags_Flags - [q3, 2] - -> - x_FunctionAsRelationR4_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_1_ExplicitVarSizeWithFlags_Flags - [q3, 1]) - | q3 : int(1..3)]), - and([q3 <= x_FunctionAsRelationR4_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Marker -> - 1 <= - sum([toInt(x_FunctionAsRelationR4_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_1_ExplicitVarSizeWithFlags_Flags - [q3, q7]) - | q7 : int(1..2)]) - | q3 : int(1..3)]), - and([q3 <= x_FunctionAsRelationR4_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Marker -> - sum([toInt(x_FunctionAsRelationR4_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_1_ExplicitVarSizeWithFlags_Flags - [q3, q7]) - | q7 : int(1..2)]) - <= 2 - | q3 : int(1..3)]), - and([1 >= - sum([toInt(q18 <= x_FunctionAsRelationR4_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Marker /\ - (and([x_FunctionAsRelationR4_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_1_ExplicitVarSizeWithFlags_Flags - [q18, q20] - -> - or([q9_ExplicitVarSizeWithMarker_Values_1[q22] = - x_FunctionAsRelationR4_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_1_ExplicitVarSizeWithFlags_Values_1 - [q18, q20] - /\ - q9_ExplicitVarSizeWithMarker_Values_2[q22] = - x_FunctionAsRelationR4_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_1_ExplicitVarSizeWithFlags_Values_2 - [q18, q20] - | q22 : int(1..2), q22 <= q9_ExplicitVarSizeWithMarker_Marker]) - | q20 : int(1..2)]) - /\ - and([or([x_FunctionAsRelationR4_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_1_ExplicitVarSizeWithFlags_Flags - [q18, q26] - /\ - (x_FunctionAsRelationR4_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_1_ExplicitVarSizeWithFlags_Values_1 - [q18, q26] - = q9_ExplicitVarSizeWithMarker_Values_1[q24] - /\ - x_FunctionAsRelationR4_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_1_ExplicitVarSizeWithFlags_Values_2 - [q18, q26] - = q9_ExplicitVarSizeWithMarker_Values_2[q24]) - | q26 : int(1..2)]) - | q24 : int(1..2), q24 <= q9_ExplicitVarSizeWithMarker_Marker]))) - | q18 : int(1..3)]) - | q9_ExplicitVarSizeWithMarker_Marker : int(0..2), - q9_ExplicitVarSizeWithMarker_Values_1 : matrix indexed by [int(1..2)] of int(7), - q9_ExplicitVarSizeWithMarker_Values_2 : matrix indexed by [int(1..2)] of bool, - 2 <= q9_ExplicitVarSizeWithMarker_Marker -> - flatten([[q9_ExplicitVarSizeWithMarker_Values_1[1]; int(1)], - [-toInt(q9_ExplicitVarSizeWithMarker_Values_2[1]); int(1)]; - int(1..2)]) - q9_ExplicitVarSizeWithMarker_Marker -> - q9_ExplicitVarSizeWithMarker_Values_1[q16] = 7 /\ q9_ExplicitVarSizeWithMarker_Values_2[q16] = false - | q16 : int(1..2)]), - 1 <= q9_ExplicitVarSizeWithMarker_Marker, q9_ExplicitVarSizeWithMarker_Marker <= 2]), - and([q27 <= x_FunctionAsRelationR4_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Marker /\ - q28 <= x_FunctionAsRelationR4_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Marker - -> - (flatten([flatten([[-toInt(x_FunctionAsRelationR4_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_1_ExplicitVarSizeWithFlags_Flags - [q27, q29]); - int(1)], - flatten([[x_FunctionAsRelationR4_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_1_ExplicitVarSizeWithFlags_Values_1 - [q27, q29]; - int(1)], - [-toInt(x_FunctionAsRelationR4_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_1_ExplicitVarSizeWithFlags_Values_2 - [q27, q29]); - int(1)]; - int(1..2)]); - int(1..2)]) - | q29 : int(1..2)]) - - x_FunctionAsRelationR4_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2[q27] != - x_FunctionAsRelationR4_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2[q28]) - | q27 : int(1..3), q28 : int(1..3)]) - diff --git a/tests/exhaustive/basic/function_imageSet01/expected/model_1_1-solution000001.solution b/tests/exhaustive/basic/function_imageSet01/expected/model_1_1-solution000001.solution deleted file mode 100644 index ffa967d973..0000000000 --- a/tests/exhaustive/basic/function_imageSet01/expected/model_1_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function() -letting s be {} diff --git a/tests/exhaustive/basic/function_imageSet01/expected/model_1_1-solution000002.solution b/tests/exhaustive/basic/function_imageSet01/expected/model_1_1-solution000002.solution deleted file mode 100644 index 77f032a426..0000000000 --- a/tests/exhaustive/basic/function_imageSet01/expected/model_1_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 1, 2 --> 1) -letting s be {1} diff --git a/tests/exhaustive/basic/function_imageSet01/expected/model_1_1-solution000003.solution b/tests/exhaustive/basic/function_imageSet01/expected/model_1_1-solution000003.solution deleted file mode 100644 index e00a3c532c..0000000000 --- a/tests/exhaustive/basic/function_imageSet01/expected/model_1_1-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 2, 2 --> 2) -letting s be {2} diff --git a/tests/exhaustive/basic/function_imageSet01/expected/model_1_1.eprime b/tests/exhaustive/basic/function_imageSet01/expected/model_1_1.eprime deleted file mode 100644 index 52c713c920..0000000000 --- a/tests/exhaustive/basic/function_imageSet01/expected/model_1_1.eprime +++ /dev/null @@ -1,15 +0,0 @@ -language ESSENCE' 1.0 - -find f_Function1DPartial_Flags: matrix indexed by [int(1..2)] of bool -find f_Function1DPartial_Values: matrix indexed by [int(1..2)] of int(1..2) -find s_Occurrence: matrix indexed by [int(1..3)] of bool -branching on [f_Function1DPartial_Flags, f_Function1DPartial_Values, s_Occurrence] -such that - and([and([f_Function1DPartial_Flags[q7] -> s_Occurrence[f_Function1DPartial_Values[q7]] | q7 : int(1..2), q7 = i]) - /\ - and([s_Occurrence[q8] -> - or([f_Function1DPartial_Flags[q11] /\ f_Function1DPartial_Values[q11] = q8 | q11 : int(1..2), q11 = i]) - | q8 : int(1..3)]) - | i : int(1..2)]), - and([f_Function1DPartial_Flags[q1] = false -> f_Function1DPartial_Values[q1] = 1 | q1 : int(1..2)]) - diff --git a/tests/exhaustive/basic/function_imageSet01/expected/model_1_2-solution000001.solution b/tests/exhaustive/basic/function_imageSet01/expected/model_1_2-solution000001.solution deleted file mode 100644 index ffa967d973..0000000000 --- a/tests/exhaustive/basic/function_imageSet01/expected/model_1_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function() -letting s be {} diff --git a/tests/exhaustive/basic/function_imageSet01/expected/model_1_2-solution000002.solution b/tests/exhaustive/basic/function_imageSet01/expected/model_1_2-solution000002.solution deleted file mode 100644 index 77f032a426..0000000000 --- a/tests/exhaustive/basic/function_imageSet01/expected/model_1_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 1, 2 --> 1) -letting s be {1} diff --git a/tests/exhaustive/basic/function_imageSet01/expected/model_1_2-solution000003.solution b/tests/exhaustive/basic/function_imageSet01/expected/model_1_2-solution000003.solution deleted file mode 100644 index e00a3c532c..0000000000 --- a/tests/exhaustive/basic/function_imageSet01/expected/model_1_2-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 2, 2 --> 2) -letting s be {2} diff --git a/tests/exhaustive/basic/function_imageSet01/expected/model_1_2.eprime b/tests/exhaustive/basic/function_imageSet01/expected/model_1_2.eprime deleted file mode 100644 index 7867e70ce0..0000000000 --- a/tests/exhaustive/basic/function_imageSet01/expected/model_1_2.eprime +++ /dev/null @@ -1,24 +0,0 @@ -language ESSENCE' 1.0 - -find f_Function1DPartial_Flags: matrix indexed by [int(1..2)] of bool -find f_Function1DPartial_Values: matrix indexed by [int(1..2)] of int(1..2) -find s_Occurrence: matrix indexed by [int(1..3)] of bool -find s_ExplicitVarSizeWithDummy: matrix indexed by [int(1..3)] of int(1..4) -branching on [f_Function1DPartial_Flags, f_Function1DPartial_Values, s_ExplicitVarSizeWithDummy, s_Occurrence] -such that - and([and([f_Function1DPartial_Flags[q16] -> s_Occurrence[f_Function1DPartial_Values[q16]] - | q16 : int(1..2), q16 = i]) - /\ - and([s_Occurrence[q17] -> - or([f_Function1DPartial_Flags[q20] /\ f_Function1DPartial_Values[q20] = q17 | q20 : int(1..2), q20 = i]) - | q17 : int(1..3)]) - | i : int(1..2)]), - and([f_Function1DPartial_Flags[q1] = false -> f_Function1DPartial_Values[q1] = 1 | q1 : int(1..2)]), - and([s_ExplicitVarSizeWithDummy[q5] < s_ExplicitVarSizeWithDummy[q5 + 1] \/ s_ExplicitVarSizeWithDummy[q5] = 4 - | q5 : int(1..2)]), - and([s_ExplicitVarSizeWithDummy[q6] = 4 -> s_ExplicitVarSizeWithDummy[q6 + 1] = 4 | q6 : int(1..2)]), - and([s_ExplicitVarSizeWithDummy[q10] != 4 -> s_Occurrence[s_ExplicitVarSizeWithDummy[q10]] | q10 : int(1..3)]), - and([s_Occurrence[q11] -> - or([s_ExplicitVarSizeWithDummy[q13] != 4 /\ s_ExplicitVarSizeWithDummy[q13] = q11 | q13 : int(1..3)]) - | q11 : int(1..3)]) - diff --git a/tests/exhaustive/basic/function_imageSet01/expected/model_1_3-solution000001.solution b/tests/exhaustive/basic/function_imageSet01/expected/model_1_3-solution000001.solution deleted file mode 100644 index ffa967d973..0000000000 --- a/tests/exhaustive/basic/function_imageSet01/expected/model_1_3-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function() -letting s be {} diff --git a/tests/exhaustive/basic/function_imageSet01/expected/model_1_3-solution000002.solution b/tests/exhaustive/basic/function_imageSet01/expected/model_1_3-solution000002.solution deleted file mode 100644 index 77f032a426..0000000000 --- a/tests/exhaustive/basic/function_imageSet01/expected/model_1_3-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 1, 2 --> 1) -letting s be {1} diff --git a/tests/exhaustive/basic/function_imageSet01/expected/model_1_3-solution000003.solution b/tests/exhaustive/basic/function_imageSet01/expected/model_1_3-solution000003.solution deleted file mode 100644 index e00a3c532c..0000000000 --- a/tests/exhaustive/basic/function_imageSet01/expected/model_1_3-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 2, 2 --> 2) -letting s be {2} diff --git a/tests/exhaustive/basic/function_imageSet01/expected/model_1_3.eprime b/tests/exhaustive/basic/function_imageSet01/expected/model_1_3.eprime deleted file mode 100644 index 8ee6453fc4..0000000000 --- a/tests/exhaustive/basic/function_imageSet01/expected/model_1_3.eprime +++ /dev/null @@ -1,30 +0,0 @@ -language ESSENCE' 1.0 - -find f_Function1DPartial_Flags: matrix indexed by [int(1..2)] of bool -find f_Function1DPartial_Values: matrix indexed by [int(1..2)] of int(1..2) -find s_Occurrence: matrix indexed by [int(1..3)] of bool -find s_ExplicitVarSizeWithMarker_Marker: int(0..3) -find s_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3)] of int(1..3) -branching on - [f_Function1DPartial_Flags, f_Function1DPartial_Values, s_ExplicitVarSizeWithMarker_Marker, - s_ExplicitVarSizeWithMarker_Values, s_Occurrence] -such that - and([and([f_Function1DPartial_Flags[q15] -> s_Occurrence[f_Function1DPartial_Values[q15]] - | q15 : int(1..2), q15 = i]) - /\ - and([s_Occurrence[q16] -> - or([f_Function1DPartial_Flags[q19] /\ f_Function1DPartial_Values[q19] = q16 | q19 : int(1..2), q19 = i]) - | q16 : int(1..3)]) - | i : int(1..2)]), - and([f_Function1DPartial_Flags[q1] = false -> f_Function1DPartial_Values[q1] = 1 | q1 : int(1..2)]), - and([q5 + 1 <= s_ExplicitVarSizeWithMarker_Marker -> - s_ExplicitVarSizeWithMarker_Values[q5] < s_ExplicitVarSizeWithMarker_Values[q5 + 1] - | q5 : int(1..2)]), - and([q6 > s_ExplicitVarSizeWithMarker_Marker -> s_ExplicitVarSizeWithMarker_Values[q6] = 1 | q6 : int(1..3)]), - and([q9 <= s_ExplicitVarSizeWithMarker_Marker -> s_Occurrence[s_ExplicitVarSizeWithMarker_Values[q9]] - | q9 : int(1..3)]), - and([s_Occurrence[q10] -> - or([q12 <= s_ExplicitVarSizeWithMarker_Marker /\ s_ExplicitVarSizeWithMarker_Values[q12] = q10 - | q12 : int(1..3)]) - | q10 : int(1..3)]) - diff --git a/tests/exhaustive/basic/function_imageSet01/expected/model_1_4-solution000001.solution b/tests/exhaustive/basic/function_imageSet01/expected/model_1_4-solution000001.solution deleted file mode 100644 index ffa967d973..0000000000 --- a/tests/exhaustive/basic/function_imageSet01/expected/model_1_4-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function() -letting s be {} diff --git a/tests/exhaustive/basic/function_imageSet01/expected/model_1_4-solution000002.solution b/tests/exhaustive/basic/function_imageSet01/expected/model_1_4-solution000002.solution deleted file mode 100644 index 77f032a426..0000000000 --- a/tests/exhaustive/basic/function_imageSet01/expected/model_1_4-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 1, 2 --> 1) -letting s be {1} diff --git a/tests/exhaustive/basic/function_imageSet01/expected/model_1_4-solution000003.solution b/tests/exhaustive/basic/function_imageSet01/expected/model_1_4-solution000003.solution deleted file mode 100644 index e00a3c532c..0000000000 --- a/tests/exhaustive/basic/function_imageSet01/expected/model_1_4-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 2, 2 --> 2) -letting s be {2} diff --git a/tests/exhaustive/basic/function_imageSet01/expected/model_1_4.eprime b/tests/exhaustive/basic/function_imageSet01/expected/model_1_4.eprime deleted file mode 100644 index 9b5abaed43..0000000000 --- a/tests/exhaustive/basic/function_imageSet01/expected/model_1_4.eprime +++ /dev/null @@ -1,30 +0,0 @@ -language ESSENCE' 1.0 - -find f_Function1DPartial_Flags: matrix indexed by [int(1..2)] of bool -find f_Function1DPartial_Values: matrix indexed by [int(1..2)] of int(1..2) -find s_Occurrence: matrix indexed by [int(1..3)] of bool -find s_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..3)] of bool -find s_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3)] of int(1..3) -branching on - [f_Function1DPartial_Flags, f_Function1DPartial_Values, s_ExplicitVarSizeWithFlags_Flags, - s_ExplicitVarSizeWithFlags_Values, s_Occurrence] -such that - and([and([f_Function1DPartial_Flags[q17] -> s_Occurrence[f_Function1DPartial_Values[q17]] - | q17 : int(1..2), q17 = i]) - /\ - and([s_Occurrence[q18] -> - or([f_Function1DPartial_Flags[q21] /\ f_Function1DPartial_Values[q21] = q18 | q21 : int(1..2), q21 = i]) - | q18 : int(1..3)]) - | i : int(1..2)]), - and([f_Function1DPartial_Flags[q1] = false -> f_Function1DPartial_Values[q1] = 1 | q1 : int(1..2)]), - and([s_ExplicitVarSizeWithFlags_Flags[q5 + 1] -> - s_ExplicitVarSizeWithFlags_Values[q5] < s_ExplicitVarSizeWithFlags_Values[q5 + 1] - | q5 : int(1..2)]), - and([s_ExplicitVarSizeWithFlags_Flags[q6] = false -> s_ExplicitVarSizeWithFlags_Values[q6] = 1 | q6 : int(1..3)]), - and([s_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> s_ExplicitVarSizeWithFlags_Flags[q7] | q7 : int(1..2)]), - and([s_ExplicitVarSizeWithFlags_Flags[q11] -> s_Occurrence[s_ExplicitVarSizeWithFlags_Values[q11]] - | q11 : int(1..3)]), - and([s_Occurrence[q12] -> - or([s_ExplicitVarSizeWithFlags_Flags[q14] /\ s_ExplicitVarSizeWithFlags_Values[q14] = q12 | q14 : int(1..3)]) - | q12 : int(1..3)]) - diff --git a/tests/exhaustive/basic/function_imageSet01/expected/model_2_1-solution000001.solution b/tests/exhaustive/basic/function_imageSet01/expected/model_2_1-solution000001.solution deleted file mode 100644 index ffa967d973..0000000000 --- a/tests/exhaustive/basic/function_imageSet01/expected/model_2_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function() -letting s be {} diff --git a/tests/exhaustive/basic/function_imageSet01/expected/model_2_1-solution000002.solution b/tests/exhaustive/basic/function_imageSet01/expected/model_2_1-solution000002.solution deleted file mode 100644 index 77f032a426..0000000000 --- a/tests/exhaustive/basic/function_imageSet01/expected/model_2_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 1, 2 --> 1) -letting s be {1} diff --git a/tests/exhaustive/basic/function_imageSet01/expected/model_2_1-solution000003.solution b/tests/exhaustive/basic/function_imageSet01/expected/model_2_1-solution000003.solution deleted file mode 100644 index e00a3c532c..0000000000 --- a/tests/exhaustive/basic/function_imageSet01/expected/model_2_1-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 2, 2 --> 2) -letting s be {2} diff --git a/tests/exhaustive/basic/function_imageSet01/expected/model_2_1.eprime b/tests/exhaustive/basic/function_imageSet01/expected/model_2_1.eprime deleted file mode 100644 index 62a42c3217..0000000000 --- a/tests/exhaustive/basic/function_imageSet01/expected/model_2_1.eprime +++ /dev/null @@ -1,28 +0,0 @@ -language ESSENCE' 1.0 - -find f_Function1DPartial_Flags: matrix indexed by [int(1..2)] of bool -find f_Function1DPartial_Values: matrix indexed by [int(1..2)] of int(1..2) -find s_ExplicitVarSizeWithDummy: matrix indexed by [int(1..3)] of int(1..4) -find s_Occurrence: matrix indexed by [int(1..3)] of bool -branching on [f_Function1DPartial_Flags, f_Function1DPartial_Values, s_Occurrence, s_ExplicitVarSizeWithDummy] -such that - and([and([f_Function1DPartial_Flags[q16] -> - or([s_ExplicitVarSizeWithDummy[q18] != 4 /\ - s_ExplicitVarSizeWithDummy[q18] = f_Function1DPartial_Values[q16] - | q18 : int(1..3)]) - | q16 : int(1..2), q16 = i]) - /\ - and([s_ExplicitVarSizeWithDummy[q20] != 4 -> - or([f_Function1DPartial_Flags[q23] /\ f_Function1DPartial_Values[q23] = s_ExplicitVarSizeWithDummy[q20] - | q23 : int(1..2), q23 = i]) - | q20 : int(1..3)]) - | i : int(1..2)]), - and([f_Function1DPartial_Flags[q1] = false -> f_Function1DPartial_Values[q1] = 1 | q1 : int(1..2)]), - and([s_ExplicitVarSizeWithDummy[q4] < s_ExplicitVarSizeWithDummy[q4 + 1] \/ s_ExplicitVarSizeWithDummy[q4] = 4 - | q4 : int(1..2)]), - and([s_ExplicitVarSizeWithDummy[q5] = 4 -> s_ExplicitVarSizeWithDummy[q5 + 1] = 4 | q5 : int(1..2)]), - and([s_Occurrence[q9] -> - or([s_ExplicitVarSizeWithDummy[q11] != 4 /\ s_ExplicitVarSizeWithDummy[q11] = q9 | q11 : int(1..3)]) - | q9 : int(1..3)]), - and([s_ExplicitVarSizeWithDummy[q13] != 4 -> s_Occurrence[s_ExplicitVarSizeWithDummy[q13]] | q13 : int(1..3)]) - diff --git a/tests/exhaustive/basic/function_imageSet01/expected/model_2_2-solution000001.solution b/tests/exhaustive/basic/function_imageSet01/expected/model_2_2-solution000001.solution deleted file mode 100644 index ffa967d973..0000000000 --- a/tests/exhaustive/basic/function_imageSet01/expected/model_2_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function() -letting s be {} diff --git a/tests/exhaustive/basic/function_imageSet01/expected/model_2_2-solution000002.solution b/tests/exhaustive/basic/function_imageSet01/expected/model_2_2-solution000002.solution deleted file mode 100644 index 77f032a426..0000000000 --- a/tests/exhaustive/basic/function_imageSet01/expected/model_2_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 1, 2 --> 1) -letting s be {1} diff --git a/tests/exhaustive/basic/function_imageSet01/expected/model_2_2-solution000003.solution b/tests/exhaustive/basic/function_imageSet01/expected/model_2_2-solution000003.solution deleted file mode 100644 index e00a3c532c..0000000000 --- a/tests/exhaustive/basic/function_imageSet01/expected/model_2_2-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 2, 2 --> 2) -letting s be {2} diff --git a/tests/exhaustive/basic/function_imageSet01/expected/model_2_2.eprime b/tests/exhaustive/basic/function_imageSet01/expected/model_2_2.eprime deleted file mode 100644 index 50abe46c45..0000000000 --- a/tests/exhaustive/basic/function_imageSet01/expected/model_2_2.eprime +++ /dev/null @@ -1,23 +0,0 @@ -language ESSENCE' 1.0 - -find f_Function1DPartial_Flags: matrix indexed by [int(1..2)] of bool -find f_Function1DPartial_Values: matrix indexed by [int(1..2)] of int(1..2) -find s_ExplicitVarSizeWithDummy: matrix indexed by [int(1..3)] of int(1..4) -branching on [f_Function1DPartial_Flags, f_Function1DPartial_Values, s_ExplicitVarSizeWithDummy] -such that - and([and([f_Function1DPartial_Flags[q10] -> - or([s_ExplicitVarSizeWithDummy[q12] != 4 /\ - s_ExplicitVarSizeWithDummy[q12] = f_Function1DPartial_Values[q10] - | q12 : int(1..3)]) - | q10 : int(1..2), q10 = i]) - /\ - and([s_ExplicitVarSizeWithDummy[q14] != 4 -> - or([f_Function1DPartial_Flags[q17] /\ f_Function1DPartial_Values[q17] = s_ExplicitVarSizeWithDummy[q14] - | q17 : int(1..2), q17 = i]) - | q14 : int(1..3)]) - | i : int(1..2)]), - and([f_Function1DPartial_Flags[q1] = false -> f_Function1DPartial_Values[q1] = 1 | q1 : int(1..2)]), - and([s_ExplicitVarSizeWithDummy[q4] < s_ExplicitVarSizeWithDummy[q4 + 1] \/ s_ExplicitVarSizeWithDummy[q4] = 4 - | q4 : int(1..2)]), - and([s_ExplicitVarSizeWithDummy[q5] = 4 -> s_ExplicitVarSizeWithDummy[q5 + 1] = 4 | q5 : int(1..2)]) - diff --git a/tests/exhaustive/basic/function_imageSet01/expected/model_2_3-solution000001.solution b/tests/exhaustive/basic/function_imageSet01/expected/model_2_3-solution000001.solution deleted file mode 100644 index ffa967d973..0000000000 --- a/tests/exhaustive/basic/function_imageSet01/expected/model_2_3-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function() -letting s be {} diff --git a/tests/exhaustive/basic/function_imageSet01/expected/model_2_3-solution000002.solution b/tests/exhaustive/basic/function_imageSet01/expected/model_2_3-solution000002.solution deleted file mode 100644 index 77f032a426..0000000000 --- a/tests/exhaustive/basic/function_imageSet01/expected/model_2_3-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 1, 2 --> 1) -letting s be {1} diff --git a/tests/exhaustive/basic/function_imageSet01/expected/model_2_3-solution000003.solution b/tests/exhaustive/basic/function_imageSet01/expected/model_2_3-solution000003.solution deleted file mode 100644 index e00a3c532c..0000000000 --- a/tests/exhaustive/basic/function_imageSet01/expected/model_2_3-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 2, 2 --> 2) -letting s be {2} diff --git a/tests/exhaustive/basic/function_imageSet01/expected/model_2_3.eprime b/tests/exhaustive/basic/function_imageSet01/expected/model_2_3.eprime deleted file mode 100644 index ecc14a208a..0000000000 --- a/tests/exhaustive/basic/function_imageSet01/expected/model_2_3.eprime +++ /dev/null @@ -1,41 +0,0 @@ -language ESSENCE' 1.0 - -find f_Function1DPartial_Flags: matrix indexed by [int(1..2)] of bool -find f_Function1DPartial_Values: matrix indexed by [int(1..2)] of int(1..2) -find s_ExplicitVarSizeWithDummy: matrix indexed by [int(1..3)] of int(1..4) -find s_ExplicitVarSizeWithMarker_Marker: int(0..3) -find s_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3)] of int(1..3) -branching on - [f_Function1DPartial_Flags, f_Function1DPartial_Values, s_ExplicitVarSizeWithMarker_Marker, - s_ExplicitVarSizeWithMarker_Values, s_ExplicitVarSizeWithDummy] -such that - and([and([f_Function1DPartial_Flags[q21] -> - or([s_ExplicitVarSizeWithDummy[q23] != 4 /\ - s_ExplicitVarSizeWithDummy[q23] = f_Function1DPartial_Values[q21] - | q23 : int(1..3)]) - | q21 : int(1..2), q21 = i]) - /\ - and([s_ExplicitVarSizeWithDummy[q25] != 4 -> - or([f_Function1DPartial_Flags[q28] /\ f_Function1DPartial_Values[q28] = s_ExplicitVarSizeWithDummy[q25] - | q28 : int(1..2), q28 = i]) - | q25 : int(1..3)]) - | i : int(1..2)]), - and([f_Function1DPartial_Flags[q1] = false -> f_Function1DPartial_Values[q1] = 1 | q1 : int(1..2)]), - and([s_ExplicitVarSizeWithDummy[q4] < s_ExplicitVarSizeWithDummy[q4 + 1] \/ s_ExplicitVarSizeWithDummy[q4] = 4 - | q4 : int(1..2)]), - and([s_ExplicitVarSizeWithDummy[q5] = 4 -> s_ExplicitVarSizeWithDummy[q5 + 1] = 4 | q5 : int(1..2)]), - and([q8 + 1 <= s_ExplicitVarSizeWithMarker_Marker -> - s_ExplicitVarSizeWithMarker_Values[q8] < s_ExplicitVarSizeWithMarker_Values[q8 + 1] - | q8 : int(1..2)]), - and([q9 > s_ExplicitVarSizeWithMarker_Marker -> s_ExplicitVarSizeWithMarker_Values[q9] = 1 | q9 : int(1..3)]), - and([q12 <= s_ExplicitVarSizeWithMarker_Marker -> - or([s_ExplicitVarSizeWithDummy[q14] != 4 /\ - s_ExplicitVarSizeWithDummy[q14] = s_ExplicitVarSizeWithMarker_Values[q12] - | q14 : int(1..3)]) - | q12 : int(1..3)]), - and([s_ExplicitVarSizeWithDummy[q16] != 4 -> - or([q18 <= s_ExplicitVarSizeWithMarker_Marker /\ - s_ExplicitVarSizeWithMarker_Values[q18] = s_ExplicitVarSizeWithDummy[q16] - | q18 : int(1..3)]) - | q16 : int(1..3)]) - diff --git a/tests/exhaustive/basic/function_imageSet01/expected/model_2_4-solution000001.solution b/tests/exhaustive/basic/function_imageSet01/expected/model_2_4-solution000001.solution deleted file mode 100644 index ffa967d973..0000000000 --- a/tests/exhaustive/basic/function_imageSet01/expected/model_2_4-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function() -letting s be {} diff --git a/tests/exhaustive/basic/function_imageSet01/expected/model_2_4-solution000002.solution b/tests/exhaustive/basic/function_imageSet01/expected/model_2_4-solution000002.solution deleted file mode 100644 index 77f032a426..0000000000 --- a/tests/exhaustive/basic/function_imageSet01/expected/model_2_4-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 1, 2 --> 1) -letting s be {1} diff --git a/tests/exhaustive/basic/function_imageSet01/expected/model_2_4-solution000003.solution b/tests/exhaustive/basic/function_imageSet01/expected/model_2_4-solution000003.solution deleted file mode 100644 index e00a3c532c..0000000000 --- a/tests/exhaustive/basic/function_imageSet01/expected/model_2_4-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 2, 2 --> 2) -letting s be {2} diff --git a/tests/exhaustive/basic/function_imageSet01/expected/model_2_4.eprime b/tests/exhaustive/basic/function_imageSet01/expected/model_2_4.eprime deleted file mode 100644 index 0565682b54..0000000000 --- a/tests/exhaustive/basic/function_imageSet01/expected/model_2_4.eprime +++ /dev/null @@ -1,42 +0,0 @@ -language ESSENCE' 1.0 - -find f_Function1DPartial_Flags: matrix indexed by [int(1..2)] of bool -find f_Function1DPartial_Values: matrix indexed by [int(1..2)] of int(1..2) -find s_ExplicitVarSizeWithDummy: matrix indexed by [int(1..3)] of int(1..4) -find s_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..3)] of bool -find s_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3)] of int(1..3) -branching on - [f_Function1DPartial_Flags, f_Function1DPartial_Values, s_ExplicitVarSizeWithFlags_Flags, - s_ExplicitVarSizeWithFlags_Values, s_ExplicitVarSizeWithDummy] -such that - and([and([f_Function1DPartial_Flags[q23] -> - or([s_ExplicitVarSizeWithDummy[q25] != 4 /\ - s_ExplicitVarSizeWithDummy[q25] = f_Function1DPartial_Values[q23] - | q25 : int(1..3)]) - | q23 : int(1..2), q23 = i]) - /\ - and([s_ExplicitVarSizeWithDummy[q27] != 4 -> - or([f_Function1DPartial_Flags[q30] /\ f_Function1DPartial_Values[q30] = s_ExplicitVarSizeWithDummy[q27] - | q30 : int(1..2), q30 = i]) - | q27 : int(1..3)]) - | i : int(1..2)]), - and([f_Function1DPartial_Flags[q1] = false -> f_Function1DPartial_Values[q1] = 1 | q1 : int(1..2)]), - and([s_ExplicitVarSizeWithDummy[q4] < s_ExplicitVarSizeWithDummy[q4 + 1] \/ s_ExplicitVarSizeWithDummy[q4] = 4 - | q4 : int(1..2)]), - and([s_ExplicitVarSizeWithDummy[q5] = 4 -> s_ExplicitVarSizeWithDummy[q5 + 1] = 4 | q5 : int(1..2)]), - and([s_ExplicitVarSizeWithFlags_Flags[q8 + 1] -> - s_ExplicitVarSizeWithFlags_Values[q8] < s_ExplicitVarSizeWithFlags_Values[q8 + 1] - | q8 : int(1..2)]), - and([s_ExplicitVarSizeWithFlags_Flags[q9] = false -> s_ExplicitVarSizeWithFlags_Values[q9] = 1 | q9 : int(1..3)]), - and([s_ExplicitVarSizeWithFlags_Flags[q10 + 1] -> s_ExplicitVarSizeWithFlags_Flags[q10] | q10 : int(1..2)]), - and([s_ExplicitVarSizeWithFlags_Flags[q14] -> - or([s_ExplicitVarSizeWithDummy[q16] != 4 /\ - s_ExplicitVarSizeWithDummy[q16] = s_ExplicitVarSizeWithFlags_Values[q14] - | q16 : int(1..3)]) - | q14 : int(1..3)]), - and([s_ExplicitVarSizeWithDummy[q18] != 4 -> - or([s_ExplicitVarSizeWithFlags_Flags[q20] /\ - s_ExplicitVarSizeWithFlags_Values[q20] = s_ExplicitVarSizeWithDummy[q18] - | q20 : int(1..3)]) - | q18 : int(1..3)]) - diff --git a/tests/exhaustive/basic/function_imageSet01/expected/model_3_1-solution000001.solution b/tests/exhaustive/basic/function_imageSet01/expected/model_3_1-solution000001.solution deleted file mode 100644 index ffa967d973..0000000000 --- a/tests/exhaustive/basic/function_imageSet01/expected/model_3_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function() -letting s be {} diff --git a/tests/exhaustive/basic/function_imageSet01/expected/model_3_1-solution000002.solution b/tests/exhaustive/basic/function_imageSet01/expected/model_3_1-solution000002.solution deleted file mode 100644 index 77f032a426..0000000000 --- a/tests/exhaustive/basic/function_imageSet01/expected/model_3_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 1, 2 --> 1) -letting s be {1} diff --git a/tests/exhaustive/basic/function_imageSet01/expected/model_3_1-solution000003.solution b/tests/exhaustive/basic/function_imageSet01/expected/model_3_1-solution000003.solution deleted file mode 100644 index e00a3c532c..0000000000 --- a/tests/exhaustive/basic/function_imageSet01/expected/model_3_1-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 2, 2 --> 2) -letting s be {2} diff --git a/tests/exhaustive/basic/function_imageSet01/expected/model_3_1.eprime b/tests/exhaustive/basic/function_imageSet01/expected/model_3_1.eprime deleted file mode 100644 index bb7469cb9c..0000000000 --- a/tests/exhaustive/basic/function_imageSet01/expected/model_3_1.eprime +++ /dev/null @@ -1,35 +0,0 @@ -language ESSENCE' 1.0 - -find f_Function1DPartial_Flags: matrix indexed by [int(1..2)] of bool -find f_Function1DPartial_Values: matrix indexed by [int(1..2)] of int(1..2) -find s_ExplicitVarSizeWithMarker_Marker: int(0..3) -find s_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3)] of int(1..3) -find s_Occurrence: matrix indexed by [int(1..3)] of bool -branching on - [f_Function1DPartial_Flags, f_Function1DPartial_Values, s_Occurrence, s_ExplicitVarSizeWithMarker_Marker, - s_ExplicitVarSizeWithMarker_Values] -such that - and([and([f_Function1DPartial_Flags[q15] -> - or([q17 <= s_ExplicitVarSizeWithMarker_Marker /\ - s_ExplicitVarSizeWithMarker_Values[q17] = f_Function1DPartial_Values[q15] - | q17 : int(1..3)]) - | q15 : int(1..2), q15 = i]) - /\ - and([q19 <= s_ExplicitVarSizeWithMarker_Marker -> - or([f_Function1DPartial_Flags[q22] /\ - f_Function1DPartial_Values[q22] = s_ExplicitVarSizeWithMarker_Values[q19] - | q22 : int(1..2), q22 = i]) - | q19 : int(1..3)]) - | i : int(1..2)]), - and([f_Function1DPartial_Flags[q1] = false -> f_Function1DPartial_Values[q1] = 1 | q1 : int(1..2)]), - and([q4 + 1 <= s_ExplicitVarSizeWithMarker_Marker -> - s_ExplicitVarSizeWithMarker_Values[q4] < s_ExplicitVarSizeWithMarker_Values[q4 + 1] - | q4 : int(1..2)]), - and([q5 > s_ExplicitVarSizeWithMarker_Marker -> s_ExplicitVarSizeWithMarker_Values[q5] = 1 | q5 : int(1..3)]), - and([s_Occurrence[q8] -> - or([q10 <= s_ExplicitVarSizeWithMarker_Marker /\ s_ExplicitVarSizeWithMarker_Values[q10] = q8 - | q10 : int(1..3)]) - | q8 : int(1..3)]), - and([q12 <= s_ExplicitVarSizeWithMarker_Marker -> s_Occurrence[s_ExplicitVarSizeWithMarker_Values[q12]] - | q12 : int(1..3)]) - diff --git a/tests/exhaustive/basic/function_imageSet01/expected/model_3_2-solution000001.solution b/tests/exhaustive/basic/function_imageSet01/expected/model_3_2-solution000001.solution deleted file mode 100644 index ffa967d973..0000000000 --- a/tests/exhaustive/basic/function_imageSet01/expected/model_3_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function() -letting s be {} diff --git a/tests/exhaustive/basic/function_imageSet01/expected/model_3_2-solution000002.solution b/tests/exhaustive/basic/function_imageSet01/expected/model_3_2-solution000002.solution deleted file mode 100644 index 77f032a426..0000000000 --- a/tests/exhaustive/basic/function_imageSet01/expected/model_3_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 1, 2 --> 1) -letting s be {1} diff --git a/tests/exhaustive/basic/function_imageSet01/expected/model_3_2-solution000003.solution b/tests/exhaustive/basic/function_imageSet01/expected/model_3_2-solution000003.solution deleted file mode 100644 index e00a3c532c..0000000000 --- a/tests/exhaustive/basic/function_imageSet01/expected/model_3_2-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 2, 2 --> 2) -letting s be {2} diff --git a/tests/exhaustive/basic/function_imageSet01/expected/model_3_2.eprime b/tests/exhaustive/basic/function_imageSet01/expected/model_3_2.eprime deleted file mode 100644 index 4f098b5ae2..0000000000 --- a/tests/exhaustive/basic/function_imageSet01/expected/model_3_2.eprime +++ /dev/null @@ -1,42 +0,0 @@ -language ESSENCE' 1.0 - -find f_Function1DPartial_Flags: matrix indexed by [int(1..2)] of bool -find f_Function1DPartial_Values: matrix indexed by [int(1..2)] of int(1..2) -find s_ExplicitVarSizeWithMarker_Marker: int(0..3) -find s_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3)] of int(1..3) -find s_ExplicitVarSizeWithDummy: matrix indexed by [int(1..3)] of int(1..4) -branching on - [f_Function1DPartial_Flags, f_Function1DPartial_Values, s_ExplicitVarSizeWithDummy, - s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithMarker_Values] -such that - and([and([f_Function1DPartial_Flags[q21] -> - or([q23 <= s_ExplicitVarSizeWithMarker_Marker /\ - s_ExplicitVarSizeWithMarker_Values[q23] = f_Function1DPartial_Values[q21] - | q23 : int(1..3)]) - | q21 : int(1..2), q21 = i]) - /\ - and([q25 <= s_ExplicitVarSizeWithMarker_Marker -> - or([f_Function1DPartial_Flags[q28] /\ - f_Function1DPartial_Values[q28] = s_ExplicitVarSizeWithMarker_Values[q25] - | q28 : int(1..2), q28 = i]) - | q25 : int(1..3)]) - | i : int(1..2)]), - and([f_Function1DPartial_Flags[q1] = false -> f_Function1DPartial_Values[q1] = 1 | q1 : int(1..2)]), - and([q4 + 1 <= s_ExplicitVarSizeWithMarker_Marker -> - s_ExplicitVarSizeWithMarker_Values[q4] < s_ExplicitVarSizeWithMarker_Values[q4 + 1] - | q4 : int(1..2)]), - and([q5 > s_ExplicitVarSizeWithMarker_Marker -> s_ExplicitVarSizeWithMarker_Values[q5] = 1 | q5 : int(1..3)]), - and([s_ExplicitVarSizeWithDummy[q7] < s_ExplicitVarSizeWithDummy[q7 + 1] \/ s_ExplicitVarSizeWithDummy[q7] = 4 - | q7 : int(1..2)]), - and([s_ExplicitVarSizeWithDummy[q8] = 4 -> s_ExplicitVarSizeWithDummy[q8 + 1] = 4 | q8 : int(1..2)]), - and([s_ExplicitVarSizeWithDummy[q12] != 4 -> - or([q14 <= s_ExplicitVarSizeWithMarker_Marker /\ - s_ExplicitVarSizeWithMarker_Values[q14] = s_ExplicitVarSizeWithDummy[q12] - | q14 : int(1..3)]) - | q12 : int(1..3)]), - and([q16 <= s_ExplicitVarSizeWithMarker_Marker -> - or([s_ExplicitVarSizeWithDummy[q18] != 4 /\ - s_ExplicitVarSizeWithDummy[q18] = s_ExplicitVarSizeWithMarker_Values[q16] - | q18 : int(1..3)]) - | q16 : int(1..3)]) - diff --git a/tests/exhaustive/basic/function_imageSet01/expected/model_3_3-solution000001.solution b/tests/exhaustive/basic/function_imageSet01/expected/model_3_3-solution000001.solution deleted file mode 100644 index ffa967d973..0000000000 --- a/tests/exhaustive/basic/function_imageSet01/expected/model_3_3-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function() -letting s be {} diff --git a/tests/exhaustive/basic/function_imageSet01/expected/model_3_3-solution000002.solution b/tests/exhaustive/basic/function_imageSet01/expected/model_3_3-solution000002.solution deleted file mode 100644 index 77f032a426..0000000000 --- a/tests/exhaustive/basic/function_imageSet01/expected/model_3_3-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 1, 2 --> 1) -letting s be {1} diff --git a/tests/exhaustive/basic/function_imageSet01/expected/model_3_3-solution000003.solution b/tests/exhaustive/basic/function_imageSet01/expected/model_3_3-solution000003.solution deleted file mode 100644 index e00a3c532c..0000000000 --- a/tests/exhaustive/basic/function_imageSet01/expected/model_3_3-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 2, 2 --> 2) -letting s be {2} diff --git a/tests/exhaustive/basic/function_imageSet01/expected/model_3_3.eprime b/tests/exhaustive/basic/function_imageSet01/expected/model_3_3.eprime deleted file mode 100644 index 8cf196e781..0000000000 --- a/tests/exhaustive/basic/function_imageSet01/expected/model_3_3.eprime +++ /dev/null @@ -1,28 +0,0 @@ -language ESSENCE' 1.0 - -find f_Function1DPartial_Flags: matrix indexed by [int(1..2)] of bool -find f_Function1DPartial_Values: matrix indexed by [int(1..2)] of int(1..2) -find s_ExplicitVarSizeWithMarker_Marker: int(0..3) -find s_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3)] of int(1..3) -branching on - [f_Function1DPartial_Flags, f_Function1DPartial_Values, s_ExplicitVarSizeWithMarker_Marker, - s_ExplicitVarSizeWithMarker_Values] -such that - and([and([f_Function1DPartial_Flags[q9] -> - or([q11 <= s_ExplicitVarSizeWithMarker_Marker /\ - s_ExplicitVarSizeWithMarker_Values[q11] = f_Function1DPartial_Values[q9] - | q11 : int(1..3)]) - | q9 : int(1..2), q9 = i]) - /\ - and([q13 <= s_ExplicitVarSizeWithMarker_Marker -> - or([f_Function1DPartial_Flags[q16] /\ - f_Function1DPartial_Values[q16] = s_ExplicitVarSizeWithMarker_Values[q13] - | q16 : int(1..2), q16 = i]) - | q13 : int(1..3)]) - | i : int(1..2)]), - and([f_Function1DPartial_Flags[q1] = false -> f_Function1DPartial_Values[q1] = 1 | q1 : int(1..2)]), - and([q4 + 1 <= s_ExplicitVarSizeWithMarker_Marker -> - s_ExplicitVarSizeWithMarker_Values[q4] < s_ExplicitVarSizeWithMarker_Values[q4 + 1] - | q4 : int(1..2)]), - and([q5 > s_ExplicitVarSizeWithMarker_Marker -> s_ExplicitVarSizeWithMarker_Values[q5] = 1 | q5 : int(1..3)]) - diff --git a/tests/exhaustive/basic/function_imageSet01/expected/model_3_4-solution000001.solution b/tests/exhaustive/basic/function_imageSet01/expected/model_3_4-solution000001.solution deleted file mode 100644 index ffa967d973..0000000000 --- a/tests/exhaustive/basic/function_imageSet01/expected/model_3_4-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function() -letting s be {} diff --git a/tests/exhaustive/basic/function_imageSet01/expected/model_3_4-solution000002.solution b/tests/exhaustive/basic/function_imageSet01/expected/model_3_4-solution000002.solution deleted file mode 100644 index 77f032a426..0000000000 --- a/tests/exhaustive/basic/function_imageSet01/expected/model_3_4-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 1, 2 --> 1) -letting s be {1} diff --git a/tests/exhaustive/basic/function_imageSet01/expected/model_3_4-solution000003.solution b/tests/exhaustive/basic/function_imageSet01/expected/model_3_4-solution000003.solution deleted file mode 100644 index e00a3c532c..0000000000 --- a/tests/exhaustive/basic/function_imageSet01/expected/model_3_4-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 2, 2 --> 2) -letting s be {2} diff --git a/tests/exhaustive/basic/function_imageSet01/expected/model_3_4.eprime b/tests/exhaustive/basic/function_imageSet01/expected/model_3_4.eprime deleted file mode 100644 index d0c743f962..0000000000 --- a/tests/exhaustive/basic/function_imageSet01/expected/model_3_4.eprime +++ /dev/null @@ -1,45 +0,0 @@ -language ESSENCE' 1.0 - -find f_Function1DPartial_Flags: matrix indexed by [int(1..2)] of bool -find f_Function1DPartial_Values: matrix indexed by [int(1..2)] of int(1..2) -find s_ExplicitVarSizeWithMarker_Marker: int(0..3) -find s_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3)] of int(1..3) -find s_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..3)] of bool -find s_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3)] of int(1..3) -branching on - [f_Function1DPartial_Flags, f_Function1DPartial_Values, s_ExplicitVarSizeWithFlags_Flags, - s_ExplicitVarSizeWithFlags_Values, s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithMarker_Values] -such that - and([and([f_Function1DPartial_Flags[q22] -> - or([q24 <= s_ExplicitVarSizeWithMarker_Marker /\ - s_ExplicitVarSizeWithMarker_Values[q24] = f_Function1DPartial_Values[q22] - | q24 : int(1..3)]) - | q22 : int(1..2), q22 = i]) - /\ - and([q26 <= s_ExplicitVarSizeWithMarker_Marker -> - or([f_Function1DPartial_Flags[q29] /\ - f_Function1DPartial_Values[q29] = s_ExplicitVarSizeWithMarker_Values[q26] - | q29 : int(1..2), q29 = i]) - | q26 : int(1..3)]) - | i : int(1..2)]), - and([f_Function1DPartial_Flags[q1] = false -> f_Function1DPartial_Values[q1] = 1 | q1 : int(1..2)]), - and([q4 + 1 <= s_ExplicitVarSizeWithMarker_Marker -> - s_ExplicitVarSizeWithMarker_Values[q4] < s_ExplicitVarSizeWithMarker_Values[q4 + 1] - | q4 : int(1..2)]), - and([q5 > s_ExplicitVarSizeWithMarker_Marker -> s_ExplicitVarSizeWithMarker_Values[q5] = 1 | q5 : int(1..3)]), - and([s_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> - s_ExplicitVarSizeWithFlags_Values[q7] < s_ExplicitVarSizeWithFlags_Values[q7 + 1] - | q7 : int(1..2)]), - and([s_ExplicitVarSizeWithFlags_Flags[q8] = false -> s_ExplicitVarSizeWithFlags_Values[q8] = 1 | q8 : int(1..3)]), - and([s_ExplicitVarSizeWithFlags_Flags[q9 + 1] -> s_ExplicitVarSizeWithFlags_Flags[q9] | q9 : int(1..2)]), - and([s_ExplicitVarSizeWithFlags_Flags[q13] -> - or([q15 <= s_ExplicitVarSizeWithMarker_Marker /\ - s_ExplicitVarSizeWithMarker_Values[q15] = s_ExplicitVarSizeWithFlags_Values[q13] - | q15 : int(1..3)]) - | q13 : int(1..3)]), - and([q17 <= s_ExplicitVarSizeWithMarker_Marker -> - or([s_ExplicitVarSizeWithFlags_Flags[q19] /\ - s_ExplicitVarSizeWithFlags_Values[q19] = s_ExplicitVarSizeWithMarker_Values[q17] - | q19 : int(1..3)]) - | q17 : int(1..3)]) - diff --git a/tests/exhaustive/basic/function_imageSet01/expected/model_4_1-solution000001.solution b/tests/exhaustive/basic/function_imageSet01/expected/model_4_1-solution000001.solution deleted file mode 100644 index ffa967d973..0000000000 --- a/tests/exhaustive/basic/function_imageSet01/expected/model_4_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function() -letting s be {} diff --git a/tests/exhaustive/basic/function_imageSet01/expected/model_4_1-solution000002.solution b/tests/exhaustive/basic/function_imageSet01/expected/model_4_1-solution000002.solution deleted file mode 100644 index 77f032a426..0000000000 --- a/tests/exhaustive/basic/function_imageSet01/expected/model_4_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 1, 2 --> 1) -letting s be {1} diff --git a/tests/exhaustive/basic/function_imageSet01/expected/model_4_1-solution000003.solution b/tests/exhaustive/basic/function_imageSet01/expected/model_4_1-solution000003.solution deleted file mode 100644 index e00a3c532c..0000000000 --- a/tests/exhaustive/basic/function_imageSet01/expected/model_4_1-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 2, 2 --> 2) -letting s be {2} diff --git a/tests/exhaustive/basic/function_imageSet01/expected/model_4_1.eprime b/tests/exhaustive/basic/function_imageSet01/expected/model_4_1.eprime deleted file mode 100644 index 0acaaffb52..0000000000 --- a/tests/exhaustive/basic/function_imageSet01/expected/model_4_1.eprime +++ /dev/null @@ -1,35 +0,0 @@ -language ESSENCE' 1.0 - -find f_Function1DPartial_Flags: matrix indexed by [int(1..2)] of bool -find f_Function1DPartial_Values: matrix indexed by [int(1..2)] of int(1..2) -find s_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..3)] of bool -find s_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3)] of int(1..3) -find s_Occurrence: matrix indexed by [int(1..3)] of bool -branching on - [f_Function1DPartial_Flags, f_Function1DPartial_Values, s_Occurrence, s_ExplicitVarSizeWithFlags_Flags, - s_ExplicitVarSizeWithFlags_Values] -such that - and([and([f_Function1DPartial_Flags[q17] -> - or([s_ExplicitVarSizeWithFlags_Flags[q19] /\ - s_ExplicitVarSizeWithFlags_Values[q19] = f_Function1DPartial_Values[q17] - | q19 : int(1..3)]) - | q17 : int(1..2), q17 = i]) - /\ - and([s_ExplicitVarSizeWithFlags_Flags[q21] -> - or([f_Function1DPartial_Flags[q24] /\ - f_Function1DPartial_Values[q24] = s_ExplicitVarSizeWithFlags_Values[q21] - | q24 : int(1..2), q24 = i]) - | q21 : int(1..3)]) - | i : int(1..2)]), - and([f_Function1DPartial_Flags[q1] = false -> f_Function1DPartial_Values[q1] = 1 | q1 : int(1..2)]), - and([s_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> - s_ExplicitVarSizeWithFlags_Values[q4] < s_ExplicitVarSizeWithFlags_Values[q4 + 1] - | q4 : int(1..2)]), - and([s_ExplicitVarSizeWithFlags_Flags[q5] = false -> s_ExplicitVarSizeWithFlags_Values[q5] = 1 | q5 : int(1..3)]), - and([s_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> s_ExplicitVarSizeWithFlags_Flags[q6] | q6 : int(1..2)]), - and([s_Occurrence[q10] -> - or([s_ExplicitVarSizeWithFlags_Flags[q12] /\ s_ExplicitVarSizeWithFlags_Values[q12] = q10 | q12 : int(1..3)]) - | q10 : int(1..3)]), - and([s_ExplicitVarSizeWithFlags_Flags[q14] -> s_Occurrence[s_ExplicitVarSizeWithFlags_Values[q14]] - | q14 : int(1..3)]) - diff --git a/tests/exhaustive/basic/function_imageSet01/expected/model_4_2-solution000001.solution b/tests/exhaustive/basic/function_imageSet01/expected/model_4_2-solution000001.solution deleted file mode 100644 index ffa967d973..0000000000 --- a/tests/exhaustive/basic/function_imageSet01/expected/model_4_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function() -letting s be {} diff --git a/tests/exhaustive/basic/function_imageSet01/expected/model_4_2-solution000002.solution b/tests/exhaustive/basic/function_imageSet01/expected/model_4_2-solution000002.solution deleted file mode 100644 index 77f032a426..0000000000 --- a/tests/exhaustive/basic/function_imageSet01/expected/model_4_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 1, 2 --> 1) -letting s be {1} diff --git a/tests/exhaustive/basic/function_imageSet01/expected/model_4_2-solution000003.solution b/tests/exhaustive/basic/function_imageSet01/expected/model_4_2-solution000003.solution deleted file mode 100644 index e00a3c532c..0000000000 --- a/tests/exhaustive/basic/function_imageSet01/expected/model_4_2-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 2, 2 --> 2) -letting s be {2} diff --git a/tests/exhaustive/basic/function_imageSet01/expected/model_4_2.eprime b/tests/exhaustive/basic/function_imageSet01/expected/model_4_2.eprime deleted file mode 100644 index ce2acc887d..0000000000 --- a/tests/exhaustive/basic/function_imageSet01/expected/model_4_2.eprime +++ /dev/null @@ -1,43 +0,0 @@ -language ESSENCE' 1.0 - -find f_Function1DPartial_Flags: matrix indexed by [int(1..2)] of bool -find f_Function1DPartial_Values: matrix indexed by [int(1..2)] of int(1..2) -find s_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..3)] of bool -find s_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3)] of int(1..3) -find s_ExplicitVarSizeWithDummy: matrix indexed by [int(1..3)] of int(1..4) -branching on - [f_Function1DPartial_Flags, f_Function1DPartial_Values, s_ExplicitVarSizeWithDummy, - s_ExplicitVarSizeWithFlags_Flags, s_ExplicitVarSizeWithFlags_Values] -such that - and([and([f_Function1DPartial_Flags[q23] -> - or([s_ExplicitVarSizeWithFlags_Flags[q25] /\ - s_ExplicitVarSizeWithFlags_Values[q25] = f_Function1DPartial_Values[q23] - | q25 : int(1..3)]) - | q23 : int(1..2), q23 = i]) - /\ - and([s_ExplicitVarSizeWithFlags_Flags[q27] -> - or([f_Function1DPartial_Flags[q30] /\ - f_Function1DPartial_Values[q30] = s_ExplicitVarSizeWithFlags_Values[q27] - | q30 : int(1..2), q30 = i]) - | q27 : int(1..3)]) - | i : int(1..2)]), - and([f_Function1DPartial_Flags[q1] = false -> f_Function1DPartial_Values[q1] = 1 | q1 : int(1..2)]), - and([s_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> - s_ExplicitVarSizeWithFlags_Values[q4] < s_ExplicitVarSizeWithFlags_Values[q4 + 1] - | q4 : int(1..2)]), - and([s_ExplicitVarSizeWithFlags_Flags[q5] = false -> s_ExplicitVarSizeWithFlags_Values[q5] = 1 | q5 : int(1..3)]), - and([s_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> s_ExplicitVarSizeWithFlags_Flags[q6] | q6 : int(1..2)]), - and([s_ExplicitVarSizeWithDummy[q9] < s_ExplicitVarSizeWithDummy[q9 + 1] \/ s_ExplicitVarSizeWithDummy[q9] = 4 - | q9 : int(1..2)]), - and([s_ExplicitVarSizeWithDummy[q10] = 4 -> s_ExplicitVarSizeWithDummy[q10 + 1] = 4 | q10 : int(1..2)]), - and([s_ExplicitVarSizeWithDummy[q14] != 4 -> - or([s_ExplicitVarSizeWithFlags_Flags[q16] /\ - s_ExplicitVarSizeWithFlags_Values[q16] = s_ExplicitVarSizeWithDummy[q14] - | q16 : int(1..3)]) - | q14 : int(1..3)]), - and([s_ExplicitVarSizeWithFlags_Flags[q18] -> - or([s_ExplicitVarSizeWithDummy[q20] != 4 /\ - s_ExplicitVarSizeWithDummy[q20] = s_ExplicitVarSizeWithFlags_Values[q18] - | q20 : int(1..3)]) - | q18 : int(1..3)]) - diff --git a/tests/exhaustive/basic/function_imageSet01/expected/model_4_3-solution000001.solution b/tests/exhaustive/basic/function_imageSet01/expected/model_4_3-solution000001.solution deleted file mode 100644 index ffa967d973..0000000000 --- a/tests/exhaustive/basic/function_imageSet01/expected/model_4_3-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function() -letting s be {} diff --git a/tests/exhaustive/basic/function_imageSet01/expected/model_4_3-solution000002.solution b/tests/exhaustive/basic/function_imageSet01/expected/model_4_3-solution000002.solution deleted file mode 100644 index 77f032a426..0000000000 --- a/tests/exhaustive/basic/function_imageSet01/expected/model_4_3-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 1, 2 --> 1) -letting s be {1} diff --git a/tests/exhaustive/basic/function_imageSet01/expected/model_4_3-solution000003.solution b/tests/exhaustive/basic/function_imageSet01/expected/model_4_3-solution000003.solution deleted file mode 100644 index e00a3c532c..0000000000 --- a/tests/exhaustive/basic/function_imageSet01/expected/model_4_3-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 2, 2 --> 2) -letting s be {2} diff --git a/tests/exhaustive/basic/function_imageSet01/expected/model_4_3.eprime b/tests/exhaustive/basic/function_imageSet01/expected/model_4_3.eprime deleted file mode 100644 index 199404fa48..0000000000 --- a/tests/exhaustive/basic/function_imageSet01/expected/model_4_3.eprime +++ /dev/null @@ -1,45 +0,0 @@ -language ESSENCE' 1.0 - -find f_Function1DPartial_Flags: matrix indexed by [int(1..2)] of bool -find f_Function1DPartial_Values: matrix indexed by [int(1..2)] of int(1..2) -find s_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..3)] of bool -find s_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3)] of int(1..3) -find s_ExplicitVarSizeWithMarker_Marker: int(0..3) -find s_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3)] of int(1..3) -branching on - [f_Function1DPartial_Flags, f_Function1DPartial_Values, s_ExplicitVarSizeWithMarker_Marker, - s_ExplicitVarSizeWithMarker_Values, s_ExplicitVarSizeWithFlags_Flags, s_ExplicitVarSizeWithFlags_Values] -such that - and([and([f_Function1DPartial_Flags[q22] -> - or([s_ExplicitVarSizeWithFlags_Flags[q24] /\ - s_ExplicitVarSizeWithFlags_Values[q24] = f_Function1DPartial_Values[q22] - | q24 : int(1..3)]) - | q22 : int(1..2), q22 = i]) - /\ - and([s_ExplicitVarSizeWithFlags_Flags[q26] -> - or([f_Function1DPartial_Flags[q29] /\ - f_Function1DPartial_Values[q29] = s_ExplicitVarSizeWithFlags_Values[q26] - | q29 : int(1..2), q29 = i]) - | q26 : int(1..3)]) - | i : int(1..2)]), - and([f_Function1DPartial_Flags[q1] = false -> f_Function1DPartial_Values[q1] = 1 | q1 : int(1..2)]), - and([s_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> - s_ExplicitVarSizeWithFlags_Values[q4] < s_ExplicitVarSizeWithFlags_Values[q4 + 1] - | q4 : int(1..2)]), - and([s_ExplicitVarSizeWithFlags_Flags[q5] = false -> s_ExplicitVarSizeWithFlags_Values[q5] = 1 | q5 : int(1..3)]), - and([s_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> s_ExplicitVarSizeWithFlags_Flags[q6] | q6 : int(1..2)]), - and([q9 + 1 <= s_ExplicitVarSizeWithMarker_Marker -> - s_ExplicitVarSizeWithMarker_Values[q9] < s_ExplicitVarSizeWithMarker_Values[q9 + 1] - | q9 : int(1..2)]), - and([q10 > s_ExplicitVarSizeWithMarker_Marker -> s_ExplicitVarSizeWithMarker_Values[q10] = 1 | q10 : int(1..3)]), - and([q13 <= s_ExplicitVarSizeWithMarker_Marker -> - or([s_ExplicitVarSizeWithFlags_Flags[q15] /\ - s_ExplicitVarSizeWithFlags_Values[q15] = s_ExplicitVarSizeWithMarker_Values[q13] - | q15 : int(1..3)]) - | q13 : int(1..3)]), - and([s_ExplicitVarSizeWithFlags_Flags[q17] -> - or([q19 <= s_ExplicitVarSizeWithMarker_Marker /\ - s_ExplicitVarSizeWithMarker_Values[q19] = s_ExplicitVarSizeWithFlags_Values[q17] - | q19 : int(1..3)]) - | q17 : int(1..3)]) - diff --git a/tests/exhaustive/basic/function_imageSet01/expected/model_4_4-solution000001.solution b/tests/exhaustive/basic/function_imageSet01/expected/model_4_4-solution000001.solution deleted file mode 100644 index ffa967d973..0000000000 --- a/tests/exhaustive/basic/function_imageSet01/expected/model_4_4-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function() -letting s be {} diff --git a/tests/exhaustive/basic/function_imageSet01/expected/model_4_4-solution000002.solution b/tests/exhaustive/basic/function_imageSet01/expected/model_4_4-solution000002.solution deleted file mode 100644 index 77f032a426..0000000000 --- a/tests/exhaustive/basic/function_imageSet01/expected/model_4_4-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 1, 2 --> 1) -letting s be {1} diff --git a/tests/exhaustive/basic/function_imageSet01/expected/model_4_4-solution000003.solution b/tests/exhaustive/basic/function_imageSet01/expected/model_4_4-solution000003.solution deleted file mode 100644 index e00a3c532c..0000000000 --- a/tests/exhaustive/basic/function_imageSet01/expected/model_4_4-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 2, 2 --> 2) -letting s be {2} diff --git a/tests/exhaustive/basic/function_imageSet01/expected/model_4_4.eprime b/tests/exhaustive/basic/function_imageSet01/expected/model_4_4.eprime deleted file mode 100644 index f2a8ea571c..0000000000 --- a/tests/exhaustive/basic/function_imageSet01/expected/model_4_4.eprime +++ /dev/null @@ -1,29 +0,0 @@ -language ESSENCE' 1.0 - -find f_Function1DPartial_Flags: matrix indexed by [int(1..2)] of bool -find f_Function1DPartial_Values: matrix indexed by [int(1..2)] of int(1..2) -find s_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..3)] of bool -find s_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3)] of int(1..3) -branching on - [f_Function1DPartial_Flags, f_Function1DPartial_Values, s_ExplicitVarSizeWithFlags_Flags, - s_ExplicitVarSizeWithFlags_Values] -such that - and([and([f_Function1DPartial_Flags[q11] -> - or([s_ExplicitVarSizeWithFlags_Flags[q13] /\ - s_ExplicitVarSizeWithFlags_Values[q13] = f_Function1DPartial_Values[q11] - | q13 : int(1..3)]) - | q11 : int(1..2), q11 = i]) - /\ - and([s_ExplicitVarSizeWithFlags_Flags[q15] -> - or([f_Function1DPartial_Flags[q18] /\ - f_Function1DPartial_Values[q18] = s_ExplicitVarSizeWithFlags_Values[q15] - | q18 : int(1..2), q18 = i]) - | q15 : int(1..3)]) - | i : int(1..2)]), - and([f_Function1DPartial_Flags[q1] = false -> f_Function1DPartial_Values[q1] = 1 | q1 : int(1..2)]), - and([s_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> - s_ExplicitVarSizeWithFlags_Values[q4] < s_ExplicitVarSizeWithFlags_Values[q4 + 1] - | q4 : int(1..2)]), - and([s_ExplicitVarSizeWithFlags_Flags[q5] = false -> s_ExplicitVarSizeWithFlags_Values[q5] = 1 | q5 : int(1..3)]), - and([s_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> s_ExplicitVarSizeWithFlags_Flags[q6] | q6 : int(1..2)]) - diff --git a/tests/exhaustive/basic/function_range/expected/model-solution000001.solution b/tests/exhaustive/basic/function_range/expected/model-solution000001.solution deleted file mode 100644 index 6fb5128626..0000000000 --- a/tests/exhaustive/basic/function_range/expected/model-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be function(2 --> 1, 3 --> 2) diff --git a/tests/exhaustive/basic/function_range/expected/model-solution000002.solution b/tests/exhaustive/basic/function_range/expected/model-solution000002.solution deleted file mode 100644 index 64a0a87dfe..0000000000 --- a/tests/exhaustive/basic/function_range/expected/model-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be function(2 --> 2, 3 --> 1) diff --git a/tests/exhaustive/basic/function_range/expected/model-solution000003.solution b/tests/exhaustive/basic/function_range/expected/model-solution000003.solution deleted file mode 100644 index 1c52fbaaf9..0000000000 --- a/tests/exhaustive/basic/function_range/expected/model-solution000003.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be function(1 --> 1, 3 --> 2) diff --git a/tests/exhaustive/basic/function_range/expected/model-solution000004.solution b/tests/exhaustive/basic/function_range/expected/model-solution000004.solution deleted file mode 100644 index 01a2ae654b..0000000000 --- a/tests/exhaustive/basic/function_range/expected/model-solution000004.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be function(1 --> 2, 3 --> 1) diff --git a/tests/exhaustive/basic/function_range/expected/model-solution000005.solution b/tests/exhaustive/basic/function_range/expected/model-solution000005.solution deleted file mode 100644 index 214b3294db..0000000000 --- a/tests/exhaustive/basic/function_range/expected/model-solution000005.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be function(1 --> 1, 2 --> 2) diff --git a/tests/exhaustive/basic/function_range/expected/model-solution000006.solution b/tests/exhaustive/basic/function_range/expected/model-solution000006.solution deleted file mode 100644 index e77580b34a..0000000000 --- a/tests/exhaustive/basic/function_range/expected/model-solution000006.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be function(1 --> 2, 2 --> 1) diff --git a/tests/exhaustive/basic/function_range/expected/model-solution000007.solution b/tests/exhaustive/basic/function_range/expected/model-solution000007.solution deleted file mode 100644 index 31f6b7ee4e..0000000000 --- a/tests/exhaustive/basic/function_range/expected/model-solution000007.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be function(1 --> 1, 2 --> 1, 3 --> 2) diff --git a/tests/exhaustive/basic/function_range/expected/model-solution000008.solution b/tests/exhaustive/basic/function_range/expected/model-solution000008.solution deleted file mode 100644 index 0165998d35..0000000000 --- a/tests/exhaustive/basic/function_range/expected/model-solution000008.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be function(1 --> 1, 2 --> 2, 3 --> 1) diff --git a/tests/exhaustive/basic/function_range/expected/model-solution000009.solution b/tests/exhaustive/basic/function_range/expected/model-solution000009.solution deleted file mode 100644 index 1544b72f35..0000000000 --- a/tests/exhaustive/basic/function_range/expected/model-solution000009.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be function(1 --> 1, 2 --> 2, 3 --> 2) diff --git a/tests/exhaustive/basic/function_range/expected/model-solution000010.solution b/tests/exhaustive/basic/function_range/expected/model-solution000010.solution deleted file mode 100644 index 3f668249b2..0000000000 --- a/tests/exhaustive/basic/function_range/expected/model-solution000010.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be function(1 --> 2, 2 --> 1, 3 --> 1) diff --git a/tests/exhaustive/basic/function_range/expected/model-solution000011.solution b/tests/exhaustive/basic/function_range/expected/model-solution000011.solution deleted file mode 100644 index 1a87d6965c..0000000000 --- a/tests/exhaustive/basic/function_range/expected/model-solution000011.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be function(1 --> 2, 2 --> 1, 3 --> 2) diff --git a/tests/exhaustive/basic/function_range/expected/model-solution000012.solution b/tests/exhaustive/basic/function_range/expected/model-solution000012.solution deleted file mode 100644 index 31f484e2a8..0000000000 --- a/tests/exhaustive/basic/function_range/expected/model-solution000012.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be function(1 --> 2, 2 --> 2, 3 --> 1) diff --git a/tests/exhaustive/basic/function_range/expected/model.eprime b/tests/exhaustive/basic/function_range/expected/model.eprime deleted file mode 100644 index f379223eed..0000000000 --- a/tests/exhaustive/basic/function_range/expected/model.eprime +++ /dev/null @@ -1,12 +0,0 @@ -language ESSENCE' 1.0 - -find x_Function1DPartial_Flags: matrix indexed by [int(1..3)] of bool -find x_Function1DPartial_Values: matrix indexed by [int(1..3)] of int(1..3) -branching on [x_Function1DPartial_Flags, x_Function1DPartial_Values] -such that - or([x_Function1DPartial_Flags[q8] /\ x_Function1DPartial_Values[q8] = 1 | q8 : int(1..3)]), - or([x_Function1DPartial_Flags[q11] /\ x_Function1DPartial_Values[q11] = 2 | q11 : int(1..3)]), - and([x_Function1DPartial_Flags[q14] -> 1 = x_Function1DPartial_Values[q14] \/ 2 = x_Function1DPartial_Values[q14] - | q14 : int(1..3)]), - and([x_Function1DPartial_Flags[q1] = false -> x_Function1DPartial_Values[q1] = 1 | q1 : int(1..3)]) - diff --git a/tests/exhaustive/basic/matrix_of_set_02/expected/model_1_1-solution000001.solution b/tests/exhaustive/basic/matrix_of_set_02/expected/model_1_1-solution000001.solution deleted file mode 100644 index af7c1da5d8..0000000000 --- a/tests/exhaustive/basic/matrix_of_set_02/expected/model_1_1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be [{}, {}; int(1..2)] diff --git a/tests/exhaustive/basic/matrix_of_set_02/expected/model_1_1-solution000002.solution b/tests/exhaustive/basic/matrix_of_set_02/expected/model_1_1-solution000002.solution deleted file mode 100644 index 0b1f00f1a5..0000000000 --- a/tests/exhaustive/basic/matrix_of_set_02/expected/model_1_1-solution000002.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be [{}, {2}; int(1..2)] -$ Visualisation for x -$ -$ 2 - diff --git a/tests/exhaustive/basic/matrix_of_set_02/expected/model_1_1-solution000003.solution b/tests/exhaustive/basic/matrix_of_set_02/expected/model_1_1-solution000003.solution deleted file mode 100644 index cbfa586d38..0000000000 --- a/tests/exhaustive/basic/matrix_of_set_02/expected/model_1_1-solution000003.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be [{2}, {}; int(1..2)] -$ Visualisation for x -$ 2 -$ - diff --git a/tests/exhaustive/basic/matrix_of_set_02/expected/model_1_1-solution000004.solution b/tests/exhaustive/basic/matrix_of_set_02/expected/model_1_1-solution000004.solution deleted file mode 100644 index a392d5bbea..0000000000 --- a/tests/exhaustive/basic/matrix_of_set_02/expected/model_1_1-solution000004.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be [{2}, {2}; int(1..2)] -$ Visualisation for x -$ 2 -$ 2 - diff --git a/tests/exhaustive/basic/matrix_of_set_02/expected/model_1_1.eprime b/tests/exhaustive/basic/matrix_of_set_02/expected/model_1_1.eprime deleted file mode 100644 index 7986231579..0000000000 --- a/tests/exhaustive/basic/matrix_of_set_02/expected/model_1_1.eprime +++ /dev/null @@ -1,6 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1..2), int(1..3)] of bool -branching on [x_Occurrence] -such that and([x_Occurrence[j, i] -> i % 2 = 0 | j : int(1..2), i : int(1..3)]) - diff --git a/tests/exhaustive/basic/matrix_of_set_02/expected/model_1_2-solution000001.solution b/tests/exhaustive/basic/matrix_of_set_02/expected/model_1_2-solution000001.solution deleted file mode 100644 index a392d5bbea..0000000000 --- a/tests/exhaustive/basic/matrix_of_set_02/expected/model_1_2-solution000001.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be [{2}, {2}; int(1..2)] -$ Visualisation for x -$ 2 -$ 2 - diff --git a/tests/exhaustive/basic/matrix_of_set_02/expected/model_1_2-solution000002.solution b/tests/exhaustive/basic/matrix_of_set_02/expected/model_1_2-solution000002.solution deleted file mode 100644 index cbfa586d38..0000000000 --- a/tests/exhaustive/basic/matrix_of_set_02/expected/model_1_2-solution000002.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be [{2}, {}; int(1..2)] -$ Visualisation for x -$ 2 -$ - diff --git a/tests/exhaustive/basic/matrix_of_set_02/expected/model_1_2-solution000003.solution b/tests/exhaustive/basic/matrix_of_set_02/expected/model_1_2-solution000003.solution deleted file mode 100644 index 0b1f00f1a5..0000000000 --- a/tests/exhaustive/basic/matrix_of_set_02/expected/model_1_2-solution000003.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be [{}, {2}; int(1..2)] -$ Visualisation for x -$ -$ 2 - diff --git a/tests/exhaustive/basic/matrix_of_set_02/expected/model_1_2-solution000004.solution b/tests/exhaustive/basic/matrix_of_set_02/expected/model_1_2-solution000004.solution deleted file mode 100644 index af7c1da5d8..0000000000 --- a/tests/exhaustive/basic/matrix_of_set_02/expected/model_1_2-solution000004.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be [{}, {}; int(1..2)] diff --git a/tests/exhaustive/basic/matrix_of_set_02/expected/model_1_2.eprime b/tests/exhaustive/basic/matrix_of_set_02/expected/model_1_2.eprime deleted file mode 100644 index c5f1aed665..0000000000 --- a/tests/exhaustive/basic/matrix_of_set_02/expected/model_1_2.eprime +++ /dev/null @@ -1,22 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1..2), int(1..3)] of bool -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..2), int(1..3)] of int(1..4) -branching on [x_ExplicitVarSizeWithDummy, x_Occurrence] -such that - and([x_Occurrence[j, i] -> i % 2 = 0 | j : int(1..2), i : int(1..3)]), - and([and([x_ExplicitVarSizeWithDummy[q3, q4] < x_ExplicitVarSizeWithDummy[q3, q4 + 1] \/ - x_ExplicitVarSizeWithDummy[q3, q4] = 4 - | q4 : int(1..2)]) - | q3 : int(1..2)]), - and([and([x_ExplicitVarSizeWithDummy[q3, q5] = 4 -> x_ExplicitVarSizeWithDummy[q3, q5 + 1] = 4 | q5 : int(1..2)]) - | q3 : int(1..2)]), - and([and([x_ExplicitVarSizeWithDummy[q8, q11] != 4 -> x_Occurrence[q8, x_ExplicitVarSizeWithDummy[q8, q11]] - | q11 : int(1..3)]) - /\ - and([x_Occurrence[q8, q12] -> - or([x_ExplicitVarSizeWithDummy[q8, q14] != 4 /\ x_ExplicitVarSizeWithDummy[q8, q14] = q12 - | q14 : int(1..3)]) - | q12 : int(1..3)]) - | q8 : int(1..2)]) - diff --git a/tests/exhaustive/basic/matrix_of_set_02/expected/model_1_3-solution000001.solution b/tests/exhaustive/basic/matrix_of_set_02/expected/model_1_3-solution000001.solution deleted file mode 100644 index af7c1da5d8..0000000000 --- a/tests/exhaustive/basic/matrix_of_set_02/expected/model_1_3-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be [{}, {}; int(1..2)] diff --git a/tests/exhaustive/basic/matrix_of_set_02/expected/model_1_3-solution000002.solution b/tests/exhaustive/basic/matrix_of_set_02/expected/model_1_3-solution000002.solution deleted file mode 100644 index 0b1f00f1a5..0000000000 --- a/tests/exhaustive/basic/matrix_of_set_02/expected/model_1_3-solution000002.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be [{}, {2}; int(1..2)] -$ Visualisation for x -$ -$ 2 - diff --git a/tests/exhaustive/basic/matrix_of_set_02/expected/model_1_3-solution000003.solution b/tests/exhaustive/basic/matrix_of_set_02/expected/model_1_3-solution000003.solution deleted file mode 100644 index cbfa586d38..0000000000 --- a/tests/exhaustive/basic/matrix_of_set_02/expected/model_1_3-solution000003.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be [{2}, {}; int(1..2)] -$ Visualisation for x -$ 2 -$ - diff --git a/tests/exhaustive/basic/matrix_of_set_02/expected/model_1_3-solution000004.solution b/tests/exhaustive/basic/matrix_of_set_02/expected/model_1_3-solution000004.solution deleted file mode 100644 index a392d5bbea..0000000000 --- a/tests/exhaustive/basic/matrix_of_set_02/expected/model_1_3-solution000004.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be [{2}, {2}; int(1..2)] -$ Visualisation for x -$ 2 -$ 2 - diff --git a/tests/exhaustive/basic/matrix_of_set_02/expected/model_1_3.eprime b/tests/exhaustive/basic/matrix_of_set_02/expected/model_1_3.eprime deleted file mode 100644 index d5a7d54f0f..0000000000 --- a/tests/exhaustive/basic/matrix_of_set_02/expected/model_1_3.eprime +++ /dev/null @@ -1,25 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1..2), int(1..3)] of bool -find x_ExplicitVarSizeWithMarker_Marker: matrix indexed by [int(1..2)] of int(0..3) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..2), int(1..3)] of int(1..3) -branching on [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_Occurrence] -such that - and([x_Occurrence[j, i] -> i % 2 = 0 | j : int(1..2), i : int(1..3)]), - and([and([q4 + 1 <= x_ExplicitVarSizeWithMarker_Marker[q3] -> - x_ExplicitVarSizeWithMarker_Values[q3, q4] < x_ExplicitVarSizeWithMarker_Values[q3, q4 + 1] - | q4 : int(1..2)]) - | q3 : int(1..2)]), - and([and([q5 > x_ExplicitVarSizeWithMarker_Marker[q3] -> x_ExplicitVarSizeWithMarker_Values[q3, q5] = 1 - | q5 : int(1..3)]) - | q3 : int(1..2)]), - and([and([q10 <= x_ExplicitVarSizeWithMarker_Marker[q7] -> - x_Occurrence[q7, x_ExplicitVarSizeWithMarker_Values[q7, q10]] - | q10 : int(1..3)]) - /\ - and([x_Occurrence[q7, q11] -> - or([q13 <= x_ExplicitVarSizeWithMarker_Marker[q7] /\ x_ExplicitVarSizeWithMarker_Values[q7, q13] = q11 - | q13 : int(1..3)]) - | q11 : int(1..3)]) - | q7 : int(1..2)]) - diff --git a/tests/exhaustive/basic/matrix_of_set_02/expected/model_1_4-solution000001.solution b/tests/exhaustive/basic/matrix_of_set_02/expected/model_1_4-solution000001.solution deleted file mode 100644 index af7c1da5d8..0000000000 --- a/tests/exhaustive/basic/matrix_of_set_02/expected/model_1_4-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be [{}, {}; int(1..2)] diff --git a/tests/exhaustive/basic/matrix_of_set_02/expected/model_1_4-solution000002.solution b/tests/exhaustive/basic/matrix_of_set_02/expected/model_1_4-solution000002.solution deleted file mode 100644 index 0b1f00f1a5..0000000000 --- a/tests/exhaustive/basic/matrix_of_set_02/expected/model_1_4-solution000002.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be [{}, {2}; int(1..2)] -$ Visualisation for x -$ -$ 2 - diff --git a/tests/exhaustive/basic/matrix_of_set_02/expected/model_1_4-solution000003.solution b/tests/exhaustive/basic/matrix_of_set_02/expected/model_1_4-solution000003.solution deleted file mode 100644 index cbfa586d38..0000000000 --- a/tests/exhaustive/basic/matrix_of_set_02/expected/model_1_4-solution000003.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be [{2}, {}; int(1..2)] -$ Visualisation for x -$ 2 -$ - diff --git a/tests/exhaustive/basic/matrix_of_set_02/expected/model_1_4-solution000004.solution b/tests/exhaustive/basic/matrix_of_set_02/expected/model_1_4-solution000004.solution deleted file mode 100644 index a392d5bbea..0000000000 --- a/tests/exhaustive/basic/matrix_of_set_02/expected/model_1_4-solution000004.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be [{2}, {2}; int(1..2)] -$ Visualisation for x -$ 2 -$ 2 - diff --git a/tests/exhaustive/basic/matrix_of_set_02/expected/model_1_4.eprime b/tests/exhaustive/basic/matrix_of_set_02/expected/model_1_4.eprime deleted file mode 100644 index b02ce75e70..0000000000 --- a/tests/exhaustive/basic/matrix_of_set_02/expected/model_1_4.eprime +++ /dev/null @@ -1,27 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1..2), int(1..3)] of bool -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..2), int(1..3)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..2), int(1..3)] of int(1..3) -branching on [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_Occurrence] -such that - and([x_Occurrence[j, i] -> i % 2 = 0 | j : int(1..2), i : int(1..3)]), - and([and([x_ExplicitVarSizeWithFlags_Flags[q3, q4 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q3, q4] < x_ExplicitVarSizeWithFlags_Values[q3, q4 + 1] - | q4 : int(1..2)]) - | q3 : int(1..2)]), - and([and([x_ExplicitVarSizeWithFlags_Flags[q3, q5] = false -> x_ExplicitVarSizeWithFlags_Values[q3, q5] = 1 - | q5 : int(1..3)]) - | q3 : int(1..2)]), - and([and([x_ExplicitVarSizeWithFlags_Flags[q3, q6 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3, q6] - | q6 : int(1..2)]) - | q3 : int(1..2)]), - and([and([x_ExplicitVarSizeWithFlags_Flags[q9, q12] -> x_Occurrence[q9, x_ExplicitVarSizeWithFlags_Values[q9, q12]] - | q12 : int(1..3)]) - /\ - and([x_Occurrence[q9, q13] -> - or([x_ExplicitVarSizeWithFlags_Flags[q9, q15] /\ x_ExplicitVarSizeWithFlags_Values[q9, q15] = q13 - | q15 : int(1..3)]) - | q13 : int(1..3)]) - | q9 : int(1..2)]) - diff --git a/tests/exhaustive/basic/matrix_of_set_02/expected/model_2_1-solution000001.solution b/tests/exhaustive/basic/matrix_of_set_02/expected/model_2_1-solution000001.solution deleted file mode 100644 index af7c1da5d8..0000000000 --- a/tests/exhaustive/basic/matrix_of_set_02/expected/model_2_1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be [{}, {}; int(1..2)] diff --git a/tests/exhaustive/basic/matrix_of_set_02/expected/model_2_1-solution000002.solution b/tests/exhaustive/basic/matrix_of_set_02/expected/model_2_1-solution000002.solution deleted file mode 100644 index 0b1f00f1a5..0000000000 --- a/tests/exhaustive/basic/matrix_of_set_02/expected/model_2_1-solution000002.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be [{}, {2}; int(1..2)] -$ Visualisation for x -$ -$ 2 - diff --git a/tests/exhaustive/basic/matrix_of_set_02/expected/model_2_1-solution000003.solution b/tests/exhaustive/basic/matrix_of_set_02/expected/model_2_1-solution000003.solution deleted file mode 100644 index cbfa586d38..0000000000 --- a/tests/exhaustive/basic/matrix_of_set_02/expected/model_2_1-solution000003.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be [{2}, {}; int(1..2)] -$ Visualisation for x -$ 2 -$ - diff --git a/tests/exhaustive/basic/matrix_of_set_02/expected/model_2_1-solution000004.solution b/tests/exhaustive/basic/matrix_of_set_02/expected/model_2_1-solution000004.solution deleted file mode 100644 index a392d5bbea..0000000000 --- a/tests/exhaustive/basic/matrix_of_set_02/expected/model_2_1-solution000004.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be [{2}, {2}; int(1..2)] -$ Visualisation for x -$ 2 -$ 2 - diff --git a/tests/exhaustive/basic/matrix_of_set_02/expected/model_2_1.eprime b/tests/exhaustive/basic/matrix_of_set_02/expected/model_2_1.eprime deleted file mode 100644 index 0bd5a5d8b6..0000000000 --- a/tests/exhaustive/basic/matrix_of_set_02/expected/model_2_1.eprime +++ /dev/null @@ -1,23 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..2), int(1..3)] of int(1..4) -find x_Occurrence: matrix indexed by [int(1..2), int(1..3)] of bool -branching on [x_Occurrence, x_ExplicitVarSizeWithDummy] -such that - and([x_ExplicitVarSizeWithDummy[j, q8] != 4 -> x_ExplicitVarSizeWithDummy[j, q8] % 2 = 0 - | j : int(1..2), q8 : int(1..3)]), - and([and([x_ExplicitVarSizeWithDummy[q1, q2] < x_ExplicitVarSizeWithDummy[q1, q2 + 1] \/ - x_ExplicitVarSizeWithDummy[q1, q2] = 4 - | q2 : int(1..2)]) - | q1 : int(1..2)]), - and([and([x_ExplicitVarSizeWithDummy[q1, q3] = 4 -> x_ExplicitVarSizeWithDummy[q1, q3 + 1] = 4 | q3 : int(1..2)]) - | q1 : int(1..2)]), - and([and([x_Occurrence[q9, q11] -> - or([x_ExplicitVarSizeWithDummy[q9, q13] != 4 /\ x_ExplicitVarSizeWithDummy[q9, q13] = q11 - | q13 : int(1..3)]) - | q11 : int(1..3)]) - /\ - and([x_ExplicitVarSizeWithDummy[q9, q15] != 4 -> x_Occurrence[q9, x_ExplicitVarSizeWithDummy[q9, q15]] - | q15 : int(1..3)]) - | q9 : int(1..2)]) - diff --git a/tests/exhaustive/basic/matrix_of_set_02/expected/model_2_2-solution000001.solution b/tests/exhaustive/basic/matrix_of_set_02/expected/model_2_2-solution000001.solution deleted file mode 100644 index a392d5bbea..0000000000 --- a/tests/exhaustive/basic/matrix_of_set_02/expected/model_2_2-solution000001.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be [{2}, {2}; int(1..2)] -$ Visualisation for x -$ 2 -$ 2 - diff --git a/tests/exhaustive/basic/matrix_of_set_02/expected/model_2_2-solution000002.solution b/tests/exhaustive/basic/matrix_of_set_02/expected/model_2_2-solution000002.solution deleted file mode 100644 index cbfa586d38..0000000000 --- a/tests/exhaustive/basic/matrix_of_set_02/expected/model_2_2-solution000002.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be [{2}, {}; int(1..2)] -$ Visualisation for x -$ 2 -$ - diff --git a/tests/exhaustive/basic/matrix_of_set_02/expected/model_2_2-solution000003.solution b/tests/exhaustive/basic/matrix_of_set_02/expected/model_2_2-solution000003.solution deleted file mode 100644 index 0b1f00f1a5..0000000000 --- a/tests/exhaustive/basic/matrix_of_set_02/expected/model_2_2-solution000003.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be [{}, {2}; int(1..2)] -$ Visualisation for x -$ -$ 2 - diff --git a/tests/exhaustive/basic/matrix_of_set_02/expected/model_2_2-solution000004.solution b/tests/exhaustive/basic/matrix_of_set_02/expected/model_2_2-solution000004.solution deleted file mode 100644 index af7c1da5d8..0000000000 --- a/tests/exhaustive/basic/matrix_of_set_02/expected/model_2_2-solution000004.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be [{}, {}; int(1..2)] diff --git a/tests/exhaustive/basic/matrix_of_set_02/expected/model_2_2.eprime b/tests/exhaustive/basic/matrix_of_set_02/expected/model_2_2.eprime deleted file mode 100644 index fea6c8a28f..0000000000 --- a/tests/exhaustive/basic/matrix_of_set_02/expected/model_2_2.eprime +++ /dev/null @@ -1,14 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..2), int(1..3)] of int(1..4) -branching on [x_ExplicitVarSizeWithDummy] -such that - and([x_ExplicitVarSizeWithDummy[j, q6] != 4 -> x_ExplicitVarSizeWithDummy[j, q6] % 2 = 0 - | j : int(1..2), q6 : int(1..3)]), - and([and([x_ExplicitVarSizeWithDummy[q1, q2] < x_ExplicitVarSizeWithDummy[q1, q2 + 1] \/ - x_ExplicitVarSizeWithDummy[q1, q2] = 4 - | q2 : int(1..2)]) - | q1 : int(1..2)]), - and([and([x_ExplicitVarSizeWithDummy[q1, q3] = 4 -> x_ExplicitVarSizeWithDummy[q1, q3 + 1] = 4 | q3 : int(1..2)]) - | q1 : int(1..2)]) - diff --git a/tests/exhaustive/basic/matrix_of_set_02/expected/model_2_3-solution000001.solution b/tests/exhaustive/basic/matrix_of_set_02/expected/model_2_3-solution000001.solution deleted file mode 100644 index af7c1da5d8..0000000000 --- a/tests/exhaustive/basic/matrix_of_set_02/expected/model_2_3-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be [{}, {}; int(1..2)] diff --git a/tests/exhaustive/basic/matrix_of_set_02/expected/model_2_3-solution000002.solution b/tests/exhaustive/basic/matrix_of_set_02/expected/model_2_3-solution000002.solution deleted file mode 100644 index 0b1f00f1a5..0000000000 --- a/tests/exhaustive/basic/matrix_of_set_02/expected/model_2_3-solution000002.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be [{}, {2}; int(1..2)] -$ Visualisation for x -$ -$ 2 - diff --git a/tests/exhaustive/basic/matrix_of_set_02/expected/model_2_3-solution000003.solution b/tests/exhaustive/basic/matrix_of_set_02/expected/model_2_3-solution000003.solution deleted file mode 100644 index cbfa586d38..0000000000 --- a/tests/exhaustive/basic/matrix_of_set_02/expected/model_2_3-solution000003.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be [{2}, {}; int(1..2)] -$ Visualisation for x -$ 2 -$ - diff --git a/tests/exhaustive/basic/matrix_of_set_02/expected/model_2_3-solution000004.solution b/tests/exhaustive/basic/matrix_of_set_02/expected/model_2_3-solution000004.solution deleted file mode 100644 index a392d5bbea..0000000000 --- a/tests/exhaustive/basic/matrix_of_set_02/expected/model_2_3-solution000004.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be [{2}, {2}; int(1..2)] -$ Visualisation for x -$ 2 -$ 2 - diff --git a/tests/exhaustive/basic/matrix_of_set_02/expected/model_2_3.eprime b/tests/exhaustive/basic/matrix_of_set_02/expected/model_2_3.eprime deleted file mode 100644 index 7612f7e6db..0000000000 --- a/tests/exhaustive/basic/matrix_of_set_02/expected/model_2_3.eprime +++ /dev/null @@ -1,35 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..2), int(1..3)] of int(1..4) -find x_ExplicitVarSizeWithMarker_Marker: matrix indexed by [int(1..2)] of int(0..3) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..2), int(1..3)] of int(1..3) -branching on [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy] -such that - and([x_ExplicitVarSizeWithDummy[j, q20] != 4 -> x_ExplicitVarSizeWithDummy[j, q20] % 2 = 0 - | j : int(1..2), q20 : int(1..3)]), - and([and([x_ExplicitVarSizeWithDummy[q1, q2] < x_ExplicitVarSizeWithDummy[q1, q2 + 1] \/ - x_ExplicitVarSizeWithDummy[q1, q2] = 4 - | q2 : int(1..2)]) - | q1 : int(1..2)]), - and([and([x_ExplicitVarSizeWithDummy[q1, q3] = 4 -> x_ExplicitVarSizeWithDummy[q1, q3 + 1] = 4 | q3 : int(1..2)]) - | q1 : int(1..2)]), - and([and([q7 + 1 <= x_ExplicitVarSizeWithMarker_Marker[q6] -> - x_ExplicitVarSizeWithMarker_Values[q6, q7] < x_ExplicitVarSizeWithMarker_Values[q6, q7 + 1] - | q7 : int(1..2)]) - | q6 : int(1..2)]), - and([and([q8 > x_ExplicitVarSizeWithMarker_Marker[q6] -> x_ExplicitVarSizeWithMarker_Values[q6, q8] = 1 - | q8 : int(1..3)]) - | q6 : int(1..2)]), - and([and([q13 <= x_ExplicitVarSizeWithMarker_Marker[q10] -> - or([x_ExplicitVarSizeWithDummy[q10, q15] != 4 /\ - x_ExplicitVarSizeWithDummy[q10, q15] = x_ExplicitVarSizeWithMarker_Values[q10, q13] - | q15 : int(1..3)]) - | q13 : int(1..3)]) - /\ - and([x_ExplicitVarSizeWithDummy[q10, q17] != 4 -> - or([q19 <= x_ExplicitVarSizeWithMarker_Marker[q10] /\ - x_ExplicitVarSizeWithMarker_Values[q10, q19] = x_ExplicitVarSizeWithDummy[q10, q17] - | q19 : int(1..3)]) - | q17 : int(1..3)]) - | q10 : int(1..2)]) - diff --git a/tests/exhaustive/basic/matrix_of_set_02/expected/model_2_4-solution000001.solution b/tests/exhaustive/basic/matrix_of_set_02/expected/model_2_4-solution000001.solution deleted file mode 100644 index af7c1da5d8..0000000000 --- a/tests/exhaustive/basic/matrix_of_set_02/expected/model_2_4-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be [{}, {}; int(1..2)] diff --git a/tests/exhaustive/basic/matrix_of_set_02/expected/model_2_4-solution000002.solution b/tests/exhaustive/basic/matrix_of_set_02/expected/model_2_4-solution000002.solution deleted file mode 100644 index 0b1f00f1a5..0000000000 --- a/tests/exhaustive/basic/matrix_of_set_02/expected/model_2_4-solution000002.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be [{}, {2}; int(1..2)] -$ Visualisation for x -$ -$ 2 - diff --git a/tests/exhaustive/basic/matrix_of_set_02/expected/model_2_4-solution000003.solution b/tests/exhaustive/basic/matrix_of_set_02/expected/model_2_4-solution000003.solution deleted file mode 100644 index cbfa586d38..0000000000 --- a/tests/exhaustive/basic/matrix_of_set_02/expected/model_2_4-solution000003.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be [{2}, {}; int(1..2)] -$ Visualisation for x -$ 2 -$ - diff --git a/tests/exhaustive/basic/matrix_of_set_02/expected/model_2_4-solution000004.solution b/tests/exhaustive/basic/matrix_of_set_02/expected/model_2_4-solution000004.solution deleted file mode 100644 index a392d5bbea..0000000000 --- a/tests/exhaustive/basic/matrix_of_set_02/expected/model_2_4-solution000004.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be [{2}, {2}; int(1..2)] -$ Visualisation for x -$ 2 -$ 2 - diff --git a/tests/exhaustive/basic/matrix_of_set_02/expected/model_2_4.eprime b/tests/exhaustive/basic/matrix_of_set_02/expected/model_2_4.eprime deleted file mode 100644 index 65e0448bbd..0000000000 --- a/tests/exhaustive/basic/matrix_of_set_02/expected/model_2_4.eprime +++ /dev/null @@ -1,38 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..2), int(1..3)] of int(1..4) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..2), int(1..3)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..2), int(1..3)] of int(1..3) -branching on [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy] -such that - and([x_ExplicitVarSizeWithDummy[j, q22] != 4 -> x_ExplicitVarSizeWithDummy[j, q22] % 2 = 0 - | j : int(1..2), q22 : int(1..3)]), - and([and([x_ExplicitVarSizeWithDummy[q1, q2] < x_ExplicitVarSizeWithDummy[q1, q2 + 1] \/ - x_ExplicitVarSizeWithDummy[q1, q2] = 4 - | q2 : int(1..2)]) - | q1 : int(1..2)]), - and([and([x_ExplicitVarSizeWithDummy[q1, q3] = 4 -> x_ExplicitVarSizeWithDummy[q1, q3 + 1] = 4 | q3 : int(1..2)]) - | q1 : int(1..2)]), - and([and([x_ExplicitVarSizeWithFlags_Flags[q6, q7 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q6, q7] < x_ExplicitVarSizeWithFlags_Values[q6, q7 + 1] - | q7 : int(1..2)]) - | q6 : int(1..2)]), - and([and([x_ExplicitVarSizeWithFlags_Flags[q6, q8] = false -> x_ExplicitVarSizeWithFlags_Values[q6, q8] = 1 - | q8 : int(1..3)]) - | q6 : int(1..2)]), - and([and([x_ExplicitVarSizeWithFlags_Flags[q6, q9 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q6, q9] - | q9 : int(1..2)]) - | q6 : int(1..2)]), - and([and([x_ExplicitVarSizeWithFlags_Flags[q12, q15] -> - or([x_ExplicitVarSizeWithDummy[q12, q17] != 4 /\ - x_ExplicitVarSizeWithDummy[q12, q17] = x_ExplicitVarSizeWithFlags_Values[q12, q15] - | q17 : int(1..3)]) - | q15 : int(1..3)]) - /\ - and([x_ExplicitVarSizeWithDummy[q12, q19] != 4 -> - or([x_ExplicitVarSizeWithFlags_Flags[q12, q21] /\ - x_ExplicitVarSizeWithFlags_Values[q12, q21] = x_ExplicitVarSizeWithDummy[q12, q19] - | q21 : int(1..3)]) - | q19 : int(1..3)]) - | q12 : int(1..2)]) - diff --git a/tests/exhaustive/basic/matrix_of_set_02/expected/model_3_1-solution000001.solution b/tests/exhaustive/basic/matrix_of_set_02/expected/model_3_1-solution000001.solution deleted file mode 100644 index af7c1da5d8..0000000000 --- a/tests/exhaustive/basic/matrix_of_set_02/expected/model_3_1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be [{}, {}; int(1..2)] diff --git a/tests/exhaustive/basic/matrix_of_set_02/expected/model_3_1-solution000002.solution b/tests/exhaustive/basic/matrix_of_set_02/expected/model_3_1-solution000002.solution deleted file mode 100644 index 0b1f00f1a5..0000000000 --- a/tests/exhaustive/basic/matrix_of_set_02/expected/model_3_1-solution000002.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be [{}, {2}; int(1..2)] -$ Visualisation for x -$ -$ 2 - diff --git a/tests/exhaustive/basic/matrix_of_set_02/expected/model_3_1-solution000003.solution b/tests/exhaustive/basic/matrix_of_set_02/expected/model_3_1-solution000003.solution deleted file mode 100644 index cbfa586d38..0000000000 --- a/tests/exhaustive/basic/matrix_of_set_02/expected/model_3_1-solution000003.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be [{2}, {}; int(1..2)] -$ Visualisation for x -$ 2 -$ - diff --git a/tests/exhaustive/basic/matrix_of_set_02/expected/model_3_1-solution000004.solution b/tests/exhaustive/basic/matrix_of_set_02/expected/model_3_1-solution000004.solution deleted file mode 100644 index a392d5bbea..0000000000 --- a/tests/exhaustive/basic/matrix_of_set_02/expected/model_3_1-solution000004.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be [{2}, {2}; int(1..2)] -$ Visualisation for x -$ 2 -$ 2 - diff --git a/tests/exhaustive/basic/matrix_of_set_02/expected/model_3_1.eprime b/tests/exhaustive/basic/matrix_of_set_02/expected/model_3_1.eprime deleted file mode 100644 index ea86dd3c32..0000000000 --- a/tests/exhaustive/basic/matrix_of_set_02/expected/model_3_1.eprime +++ /dev/null @@ -1,26 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: matrix indexed by [int(1..2)] of int(0..3) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..2), int(1..3)] of int(1..3) -find x_Occurrence: matrix indexed by [int(1..2), int(1..3)] of bool -branching on [x_Occurrence, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] -such that - and([q7 <= x_ExplicitVarSizeWithMarker_Marker[j] -> x_ExplicitVarSizeWithMarker_Values[j, q7] % 2 = 0 - | j : int(1..2), q7 : int(1..3)]), - and([and([q2 + 1 <= x_ExplicitVarSizeWithMarker_Marker[q1] -> - x_ExplicitVarSizeWithMarker_Values[q1, q2] < x_ExplicitVarSizeWithMarker_Values[q1, q2 + 1] - | q2 : int(1..2)]) - | q1 : int(1..2)]), - and([and([q3 > x_ExplicitVarSizeWithMarker_Marker[q1] -> x_ExplicitVarSizeWithMarker_Values[q1, q3] = 1 - | q3 : int(1..3)]) - | q1 : int(1..2)]), - and([and([x_Occurrence[q8, q10] -> - or([q12 <= x_ExplicitVarSizeWithMarker_Marker[q8] /\ x_ExplicitVarSizeWithMarker_Values[q8, q12] = q10 - | q12 : int(1..3)]) - | q10 : int(1..3)]) - /\ - and([q14 <= x_ExplicitVarSizeWithMarker_Marker[q8] -> - x_Occurrence[q8, x_ExplicitVarSizeWithMarker_Values[q8, q14]] - | q14 : int(1..3)]) - | q8 : int(1..2)]) - diff --git a/tests/exhaustive/basic/matrix_of_set_02/expected/model_3_2-solution000001.solution b/tests/exhaustive/basic/matrix_of_set_02/expected/model_3_2-solution000001.solution deleted file mode 100644 index a392d5bbea..0000000000 --- a/tests/exhaustive/basic/matrix_of_set_02/expected/model_3_2-solution000001.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be [{2}, {2}; int(1..2)] -$ Visualisation for x -$ 2 -$ 2 - diff --git a/tests/exhaustive/basic/matrix_of_set_02/expected/model_3_2-solution000002.solution b/tests/exhaustive/basic/matrix_of_set_02/expected/model_3_2-solution000002.solution deleted file mode 100644 index cbfa586d38..0000000000 --- a/tests/exhaustive/basic/matrix_of_set_02/expected/model_3_2-solution000002.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be [{2}, {}; int(1..2)] -$ Visualisation for x -$ 2 -$ - diff --git a/tests/exhaustive/basic/matrix_of_set_02/expected/model_3_2-solution000003.solution b/tests/exhaustive/basic/matrix_of_set_02/expected/model_3_2-solution000003.solution deleted file mode 100644 index 0b1f00f1a5..0000000000 --- a/tests/exhaustive/basic/matrix_of_set_02/expected/model_3_2-solution000003.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be [{}, {2}; int(1..2)] -$ Visualisation for x -$ -$ 2 - diff --git a/tests/exhaustive/basic/matrix_of_set_02/expected/model_3_2-solution000004.solution b/tests/exhaustive/basic/matrix_of_set_02/expected/model_3_2-solution000004.solution deleted file mode 100644 index af7c1da5d8..0000000000 --- a/tests/exhaustive/basic/matrix_of_set_02/expected/model_3_2-solution000004.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be [{}, {}; int(1..2)] diff --git a/tests/exhaustive/basic/matrix_of_set_02/expected/model_3_2.eprime b/tests/exhaustive/basic/matrix_of_set_02/expected/model_3_2.eprime deleted file mode 100644 index d2dad6cd2c..0000000000 --- a/tests/exhaustive/basic/matrix_of_set_02/expected/model_3_2.eprime +++ /dev/null @@ -1,35 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: matrix indexed by [int(1..2)] of int(0..3) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..2), int(1..3)] of int(1..3) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..2), int(1..3)] of int(1..4) -branching on [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] -such that - and([q20 <= x_ExplicitVarSizeWithMarker_Marker[j] -> x_ExplicitVarSizeWithMarker_Values[j, q20] % 2 = 0 - | j : int(1..2), q20 : int(1..3)]), - and([and([q2 + 1 <= x_ExplicitVarSizeWithMarker_Marker[q1] -> - x_ExplicitVarSizeWithMarker_Values[q1, q2] < x_ExplicitVarSizeWithMarker_Values[q1, q2 + 1] - | q2 : int(1..2)]) - | q1 : int(1..2)]), - and([and([q3 > x_ExplicitVarSizeWithMarker_Marker[q1] -> x_ExplicitVarSizeWithMarker_Values[q1, q3] = 1 - | q3 : int(1..3)]) - | q1 : int(1..2)]), - and([and([x_ExplicitVarSizeWithDummy[q5, q6] < x_ExplicitVarSizeWithDummy[q5, q6 + 1] \/ - x_ExplicitVarSizeWithDummy[q5, q6] = 4 - | q6 : int(1..2)]) - | q5 : int(1..2)]), - and([and([x_ExplicitVarSizeWithDummy[q5, q7] = 4 -> x_ExplicitVarSizeWithDummy[q5, q7 + 1] = 4 | q7 : int(1..2)]) - | q5 : int(1..2)]), - and([and([x_ExplicitVarSizeWithDummy[q10, q13] != 4 -> - or([q15 <= x_ExplicitVarSizeWithMarker_Marker[q10] /\ - x_ExplicitVarSizeWithMarker_Values[q10, q15] = x_ExplicitVarSizeWithDummy[q10, q13] - | q15 : int(1..3)]) - | q13 : int(1..3)]) - /\ - and([q17 <= x_ExplicitVarSizeWithMarker_Marker[q10] -> - or([x_ExplicitVarSizeWithDummy[q10, q19] != 4 /\ - x_ExplicitVarSizeWithDummy[q10, q19] = x_ExplicitVarSizeWithMarker_Values[q10, q17] - | q19 : int(1..3)]) - | q17 : int(1..3)]) - | q10 : int(1..2)]) - diff --git a/tests/exhaustive/basic/matrix_of_set_02/expected/model_3_3-solution000001.solution b/tests/exhaustive/basic/matrix_of_set_02/expected/model_3_3-solution000001.solution deleted file mode 100644 index af7c1da5d8..0000000000 --- a/tests/exhaustive/basic/matrix_of_set_02/expected/model_3_3-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be [{}, {}; int(1..2)] diff --git a/tests/exhaustive/basic/matrix_of_set_02/expected/model_3_3-solution000002.solution b/tests/exhaustive/basic/matrix_of_set_02/expected/model_3_3-solution000002.solution deleted file mode 100644 index 0b1f00f1a5..0000000000 --- a/tests/exhaustive/basic/matrix_of_set_02/expected/model_3_3-solution000002.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be [{}, {2}; int(1..2)] -$ Visualisation for x -$ -$ 2 - diff --git a/tests/exhaustive/basic/matrix_of_set_02/expected/model_3_3-solution000003.solution b/tests/exhaustive/basic/matrix_of_set_02/expected/model_3_3-solution000003.solution deleted file mode 100644 index cbfa586d38..0000000000 --- a/tests/exhaustive/basic/matrix_of_set_02/expected/model_3_3-solution000003.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be [{2}, {}; int(1..2)] -$ Visualisation for x -$ 2 -$ - diff --git a/tests/exhaustive/basic/matrix_of_set_02/expected/model_3_3-solution000004.solution b/tests/exhaustive/basic/matrix_of_set_02/expected/model_3_3-solution000004.solution deleted file mode 100644 index a392d5bbea..0000000000 --- a/tests/exhaustive/basic/matrix_of_set_02/expected/model_3_3-solution000004.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be [{2}, {2}; int(1..2)] -$ Visualisation for x -$ 2 -$ 2 - diff --git a/tests/exhaustive/basic/matrix_of_set_02/expected/model_3_3.eprime b/tests/exhaustive/basic/matrix_of_set_02/expected/model_3_3.eprime deleted file mode 100644 index 8fc98162b2..0000000000 --- a/tests/exhaustive/basic/matrix_of_set_02/expected/model_3_3.eprime +++ /dev/null @@ -1,16 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: matrix indexed by [int(1..2)] of int(0..3) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..2), int(1..3)] of int(1..3) -branching on [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] -such that - and([q5 <= x_ExplicitVarSizeWithMarker_Marker[j] -> x_ExplicitVarSizeWithMarker_Values[j, q5] % 2 = 0 - | j : int(1..2), q5 : int(1..3)]), - and([and([q2 + 1 <= x_ExplicitVarSizeWithMarker_Marker[q1] -> - x_ExplicitVarSizeWithMarker_Values[q1, q2] < x_ExplicitVarSizeWithMarker_Values[q1, q2 + 1] - | q2 : int(1..2)]) - | q1 : int(1..2)]), - and([and([q3 > x_ExplicitVarSizeWithMarker_Marker[q1] -> x_ExplicitVarSizeWithMarker_Values[q1, q3] = 1 - | q3 : int(1..3)]) - | q1 : int(1..2)]) - diff --git a/tests/exhaustive/basic/matrix_of_set_02/expected/model_3_4-solution000001.solution b/tests/exhaustive/basic/matrix_of_set_02/expected/model_3_4-solution000001.solution deleted file mode 100644 index af7c1da5d8..0000000000 --- a/tests/exhaustive/basic/matrix_of_set_02/expected/model_3_4-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be [{}, {}; int(1..2)] diff --git a/tests/exhaustive/basic/matrix_of_set_02/expected/model_3_4-solution000002.solution b/tests/exhaustive/basic/matrix_of_set_02/expected/model_3_4-solution000002.solution deleted file mode 100644 index 0b1f00f1a5..0000000000 --- a/tests/exhaustive/basic/matrix_of_set_02/expected/model_3_4-solution000002.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be [{}, {2}; int(1..2)] -$ Visualisation for x -$ -$ 2 - diff --git a/tests/exhaustive/basic/matrix_of_set_02/expected/model_3_4-solution000003.solution b/tests/exhaustive/basic/matrix_of_set_02/expected/model_3_4-solution000003.solution deleted file mode 100644 index cbfa586d38..0000000000 --- a/tests/exhaustive/basic/matrix_of_set_02/expected/model_3_4-solution000003.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be [{2}, {}; int(1..2)] -$ Visualisation for x -$ 2 -$ - diff --git a/tests/exhaustive/basic/matrix_of_set_02/expected/model_3_4-solution000004.solution b/tests/exhaustive/basic/matrix_of_set_02/expected/model_3_4-solution000004.solution deleted file mode 100644 index a392d5bbea..0000000000 --- a/tests/exhaustive/basic/matrix_of_set_02/expected/model_3_4-solution000004.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be [{2}, {2}; int(1..2)] -$ Visualisation for x -$ 2 -$ 2 - diff --git a/tests/exhaustive/basic/matrix_of_set_02/expected/model_3_4.eprime b/tests/exhaustive/basic/matrix_of_set_02/expected/model_3_4.eprime deleted file mode 100644 index ad169aef90..0000000000 --- a/tests/exhaustive/basic/matrix_of_set_02/expected/model_3_4.eprime +++ /dev/null @@ -1,42 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: matrix indexed by [int(1..2)] of int(0..3) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..2), int(1..3)] of int(1..3) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..2), int(1..3)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..2), int(1..3)] of int(1..3) -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithMarker_Marker, - x_ExplicitVarSizeWithMarker_Values] -such that - and([q21 <= x_ExplicitVarSizeWithMarker_Marker[j] -> x_ExplicitVarSizeWithMarker_Values[j, q21] % 2 = 0 - | j : int(1..2), q21 : int(1..3)]), - and([and([q2 + 1 <= x_ExplicitVarSizeWithMarker_Marker[q1] -> - x_ExplicitVarSizeWithMarker_Values[q1, q2] < x_ExplicitVarSizeWithMarker_Values[q1, q2 + 1] - | q2 : int(1..2)]) - | q1 : int(1..2)]), - and([and([q3 > x_ExplicitVarSizeWithMarker_Marker[q1] -> x_ExplicitVarSizeWithMarker_Values[q1, q3] = 1 - | q3 : int(1..3)]) - | q1 : int(1..2)]), - and([and([x_ExplicitVarSizeWithFlags_Flags[q5, q6 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q5, q6] < x_ExplicitVarSizeWithFlags_Values[q5, q6 + 1] - | q6 : int(1..2)]) - | q5 : int(1..2)]), - and([and([x_ExplicitVarSizeWithFlags_Flags[q5, q7] = false -> x_ExplicitVarSizeWithFlags_Values[q5, q7] = 1 - | q7 : int(1..3)]) - | q5 : int(1..2)]), - and([and([x_ExplicitVarSizeWithFlags_Flags[q5, q8 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q5, q8] - | q8 : int(1..2)]) - | q5 : int(1..2)]), - and([and([x_ExplicitVarSizeWithFlags_Flags[q11, q14] -> - or([q16 <= x_ExplicitVarSizeWithMarker_Marker[q11] /\ - x_ExplicitVarSizeWithMarker_Values[q11, q16] = x_ExplicitVarSizeWithFlags_Values[q11, q14] - | q16 : int(1..3)]) - | q14 : int(1..3)]) - /\ - and([q18 <= x_ExplicitVarSizeWithMarker_Marker[q11] -> - or([x_ExplicitVarSizeWithFlags_Flags[q11, q20] /\ - x_ExplicitVarSizeWithFlags_Values[q11, q20] = x_ExplicitVarSizeWithMarker_Values[q11, q18] - | q20 : int(1..3)]) - | q18 : int(1..3)]) - | q11 : int(1..2)]) - diff --git a/tests/exhaustive/basic/matrix_of_set_02/expected/model_4_1-solution000001.solution b/tests/exhaustive/basic/matrix_of_set_02/expected/model_4_1-solution000001.solution deleted file mode 100644 index af7c1da5d8..0000000000 --- a/tests/exhaustive/basic/matrix_of_set_02/expected/model_4_1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be [{}, {}; int(1..2)] diff --git a/tests/exhaustive/basic/matrix_of_set_02/expected/model_4_1-solution000002.solution b/tests/exhaustive/basic/matrix_of_set_02/expected/model_4_1-solution000002.solution deleted file mode 100644 index 0b1f00f1a5..0000000000 --- a/tests/exhaustive/basic/matrix_of_set_02/expected/model_4_1-solution000002.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be [{}, {2}; int(1..2)] -$ Visualisation for x -$ -$ 2 - diff --git a/tests/exhaustive/basic/matrix_of_set_02/expected/model_4_1-solution000003.solution b/tests/exhaustive/basic/matrix_of_set_02/expected/model_4_1-solution000003.solution deleted file mode 100644 index cbfa586d38..0000000000 --- a/tests/exhaustive/basic/matrix_of_set_02/expected/model_4_1-solution000003.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be [{2}, {}; int(1..2)] -$ Visualisation for x -$ 2 -$ - diff --git a/tests/exhaustive/basic/matrix_of_set_02/expected/model_4_1-solution000004.solution b/tests/exhaustive/basic/matrix_of_set_02/expected/model_4_1-solution000004.solution deleted file mode 100644 index a392d5bbea..0000000000 --- a/tests/exhaustive/basic/matrix_of_set_02/expected/model_4_1-solution000004.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be [{2}, {2}; int(1..2)] -$ Visualisation for x -$ 2 -$ 2 - diff --git a/tests/exhaustive/basic/matrix_of_set_02/expected/model_4_1.eprime b/tests/exhaustive/basic/matrix_of_set_02/expected/model_4_1.eprime deleted file mode 100644 index 7b010d3180..0000000000 --- a/tests/exhaustive/basic/matrix_of_set_02/expected/model_4_1.eprime +++ /dev/null @@ -1,28 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..2), int(1..3)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..2), int(1..3)] of int(1..3) -find x_Occurrence: matrix indexed by [int(1..2), int(1..3)] of bool -branching on [x_Occurrence, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] -such that - and([x_ExplicitVarSizeWithFlags_Flags[j, q16] -> x_ExplicitVarSizeWithFlags_Values[j, q16] % 2 = 0 - | j : int(1..2), q16 : int(1..3)]), - and([and([x_ExplicitVarSizeWithFlags_Flags[q1, q2 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1, q2] < x_ExplicitVarSizeWithFlags_Values[q1, q2 + 1] - | q2 : int(1..2)]) - | q1 : int(1..2)]), - and([and([x_ExplicitVarSizeWithFlags_Flags[q1, q3] = false -> x_ExplicitVarSizeWithFlags_Values[q1, q3] = 1 - | q3 : int(1..3)]) - | q1 : int(1..2)]), - and([and([x_ExplicitVarSizeWithFlags_Flags[q1, q4 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q1, q4] - | q4 : int(1..2)]) - | q1 : int(1..2)]), - and([and([x_Occurrence[q9, q11] -> - or([x_ExplicitVarSizeWithFlags_Flags[q9, q13] /\ x_ExplicitVarSizeWithFlags_Values[q9, q13] = q11 - | q13 : int(1..3)]) - | q11 : int(1..3)]) - /\ - and([x_ExplicitVarSizeWithFlags_Flags[q9, q15] -> x_Occurrence[q9, x_ExplicitVarSizeWithFlags_Values[q9, q15]] - | q15 : int(1..3)]) - | q9 : int(1..2)]) - diff --git a/tests/exhaustive/basic/matrix_of_set_02/expected/model_4_2-solution000001.solution b/tests/exhaustive/basic/matrix_of_set_02/expected/model_4_2-solution000001.solution deleted file mode 100644 index a392d5bbea..0000000000 --- a/tests/exhaustive/basic/matrix_of_set_02/expected/model_4_2-solution000001.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be [{2}, {2}; int(1..2)] -$ Visualisation for x -$ 2 -$ 2 - diff --git a/tests/exhaustive/basic/matrix_of_set_02/expected/model_4_2-solution000002.solution b/tests/exhaustive/basic/matrix_of_set_02/expected/model_4_2-solution000002.solution deleted file mode 100644 index cbfa586d38..0000000000 --- a/tests/exhaustive/basic/matrix_of_set_02/expected/model_4_2-solution000002.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be [{2}, {}; int(1..2)] -$ Visualisation for x -$ 2 -$ - diff --git a/tests/exhaustive/basic/matrix_of_set_02/expected/model_4_2-solution000003.solution b/tests/exhaustive/basic/matrix_of_set_02/expected/model_4_2-solution000003.solution deleted file mode 100644 index 0b1f00f1a5..0000000000 --- a/tests/exhaustive/basic/matrix_of_set_02/expected/model_4_2-solution000003.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be [{}, {2}; int(1..2)] -$ Visualisation for x -$ -$ 2 - diff --git a/tests/exhaustive/basic/matrix_of_set_02/expected/model_4_2-solution000004.solution b/tests/exhaustive/basic/matrix_of_set_02/expected/model_4_2-solution000004.solution deleted file mode 100644 index af7c1da5d8..0000000000 --- a/tests/exhaustive/basic/matrix_of_set_02/expected/model_4_2-solution000004.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be [{}, {}; int(1..2)] diff --git a/tests/exhaustive/basic/matrix_of_set_02/expected/model_4_2.eprime b/tests/exhaustive/basic/matrix_of_set_02/expected/model_4_2.eprime deleted file mode 100644 index 39f8e990fe..0000000000 --- a/tests/exhaustive/basic/matrix_of_set_02/expected/model_4_2.eprime +++ /dev/null @@ -1,38 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..2), int(1..3)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..2), int(1..3)] of int(1..3) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..2), int(1..3)] of int(1..4) -branching on [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] -such that - and([x_ExplicitVarSizeWithFlags_Flags[j, q22] -> x_ExplicitVarSizeWithFlags_Values[j, q22] % 2 = 0 - | j : int(1..2), q22 : int(1..3)]), - and([and([x_ExplicitVarSizeWithFlags_Flags[q1, q2 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1, q2] < x_ExplicitVarSizeWithFlags_Values[q1, q2 + 1] - | q2 : int(1..2)]) - | q1 : int(1..2)]), - and([and([x_ExplicitVarSizeWithFlags_Flags[q1, q3] = false -> x_ExplicitVarSizeWithFlags_Values[q1, q3] = 1 - | q3 : int(1..3)]) - | q1 : int(1..2)]), - and([and([x_ExplicitVarSizeWithFlags_Flags[q1, q4 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q1, q4] - | q4 : int(1..2)]) - | q1 : int(1..2)]), - and([and([x_ExplicitVarSizeWithDummy[q7, q8] < x_ExplicitVarSizeWithDummy[q7, q8 + 1] \/ - x_ExplicitVarSizeWithDummy[q7, q8] = 4 - | q8 : int(1..2)]) - | q7 : int(1..2)]), - and([and([x_ExplicitVarSizeWithDummy[q7, q9] = 4 -> x_ExplicitVarSizeWithDummy[q7, q9 + 1] = 4 | q9 : int(1..2)]) - | q7 : int(1..2)]), - and([and([x_ExplicitVarSizeWithDummy[q12, q15] != 4 -> - or([x_ExplicitVarSizeWithFlags_Flags[q12, q17] /\ - x_ExplicitVarSizeWithFlags_Values[q12, q17] = x_ExplicitVarSizeWithDummy[q12, q15] - | q17 : int(1..3)]) - | q15 : int(1..3)]) - /\ - and([x_ExplicitVarSizeWithFlags_Flags[q12, q19] -> - or([x_ExplicitVarSizeWithDummy[q12, q21] != 4 /\ - x_ExplicitVarSizeWithDummy[q12, q21] = x_ExplicitVarSizeWithFlags_Values[q12, q19] - | q21 : int(1..3)]) - | q19 : int(1..3)]) - | q12 : int(1..2)]) - diff --git a/tests/exhaustive/basic/matrix_of_set_02/expected/model_4_3-solution000001.solution b/tests/exhaustive/basic/matrix_of_set_02/expected/model_4_3-solution000001.solution deleted file mode 100644 index af7c1da5d8..0000000000 --- a/tests/exhaustive/basic/matrix_of_set_02/expected/model_4_3-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be [{}, {}; int(1..2)] diff --git a/tests/exhaustive/basic/matrix_of_set_02/expected/model_4_3-solution000002.solution b/tests/exhaustive/basic/matrix_of_set_02/expected/model_4_3-solution000002.solution deleted file mode 100644 index 0b1f00f1a5..0000000000 --- a/tests/exhaustive/basic/matrix_of_set_02/expected/model_4_3-solution000002.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be [{}, {2}; int(1..2)] -$ Visualisation for x -$ -$ 2 - diff --git a/tests/exhaustive/basic/matrix_of_set_02/expected/model_4_3-solution000003.solution b/tests/exhaustive/basic/matrix_of_set_02/expected/model_4_3-solution000003.solution deleted file mode 100644 index cbfa586d38..0000000000 --- a/tests/exhaustive/basic/matrix_of_set_02/expected/model_4_3-solution000003.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be [{2}, {}; int(1..2)] -$ Visualisation for x -$ 2 -$ - diff --git a/tests/exhaustive/basic/matrix_of_set_02/expected/model_4_3-solution000004.solution b/tests/exhaustive/basic/matrix_of_set_02/expected/model_4_3-solution000004.solution deleted file mode 100644 index a392d5bbea..0000000000 --- a/tests/exhaustive/basic/matrix_of_set_02/expected/model_4_3-solution000004.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be [{2}, {2}; int(1..2)] -$ Visualisation for x -$ 2 -$ 2 - diff --git a/tests/exhaustive/basic/matrix_of_set_02/expected/model_4_3.eprime b/tests/exhaustive/basic/matrix_of_set_02/expected/model_4_3.eprime deleted file mode 100644 index a67d88de35..0000000000 --- a/tests/exhaustive/basic/matrix_of_set_02/expected/model_4_3.eprime +++ /dev/null @@ -1,42 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..2), int(1..3)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..2), int(1..3)] of int(1..3) -find x_ExplicitVarSizeWithMarker_Marker: matrix indexed by [int(1..2)] of int(0..3) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..2), int(1..3)] of int(1..3) -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithFlags_Flags, - x_ExplicitVarSizeWithFlags_Values] -such that - and([x_ExplicitVarSizeWithFlags_Flags[j, q21] -> x_ExplicitVarSizeWithFlags_Values[j, q21] % 2 = 0 - | j : int(1..2), q21 : int(1..3)]), - and([and([x_ExplicitVarSizeWithFlags_Flags[q1, q2 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1, q2] < x_ExplicitVarSizeWithFlags_Values[q1, q2 + 1] - | q2 : int(1..2)]) - | q1 : int(1..2)]), - and([and([x_ExplicitVarSizeWithFlags_Flags[q1, q3] = false -> x_ExplicitVarSizeWithFlags_Values[q1, q3] = 1 - | q3 : int(1..3)]) - | q1 : int(1..2)]), - and([and([x_ExplicitVarSizeWithFlags_Flags[q1, q4 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q1, q4] - | q4 : int(1..2)]) - | q1 : int(1..2)]), - and([and([q8 + 1 <= x_ExplicitVarSizeWithMarker_Marker[q7] -> - x_ExplicitVarSizeWithMarker_Values[q7, q8] < x_ExplicitVarSizeWithMarker_Values[q7, q8 + 1] - | q8 : int(1..2)]) - | q7 : int(1..2)]), - and([and([q9 > x_ExplicitVarSizeWithMarker_Marker[q7] -> x_ExplicitVarSizeWithMarker_Values[q7, q9] = 1 - | q9 : int(1..3)]) - | q7 : int(1..2)]), - and([and([q14 <= x_ExplicitVarSizeWithMarker_Marker[q11] -> - or([x_ExplicitVarSizeWithFlags_Flags[q11, q16] /\ - x_ExplicitVarSizeWithFlags_Values[q11, q16] = x_ExplicitVarSizeWithMarker_Values[q11, q14] - | q16 : int(1..3)]) - | q14 : int(1..3)]) - /\ - and([x_ExplicitVarSizeWithFlags_Flags[q11, q18] -> - or([q20 <= x_ExplicitVarSizeWithMarker_Marker[q11] /\ - x_ExplicitVarSizeWithMarker_Values[q11, q20] = x_ExplicitVarSizeWithFlags_Values[q11, q18] - | q20 : int(1..3)]) - | q18 : int(1..3)]) - | q11 : int(1..2)]) - diff --git a/tests/exhaustive/basic/matrix_of_set_02/expected/model_4_4-solution000001.solution b/tests/exhaustive/basic/matrix_of_set_02/expected/model_4_4-solution000001.solution deleted file mode 100644 index af7c1da5d8..0000000000 --- a/tests/exhaustive/basic/matrix_of_set_02/expected/model_4_4-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be [{}, {}; int(1..2)] diff --git a/tests/exhaustive/basic/matrix_of_set_02/expected/model_4_4-solution000002.solution b/tests/exhaustive/basic/matrix_of_set_02/expected/model_4_4-solution000002.solution deleted file mode 100644 index 0b1f00f1a5..0000000000 --- a/tests/exhaustive/basic/matrix_of_set_02/expected/model_4_4-solution000002.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be [{}, {2}; int(1..2)] -$ Visualisation for x -$ -$ 2 - diff --git a/tests/exhaustive/basic/matrix_of_set_02/expected/model_4_4-solution000003.solution b/tests/exhaustive/basic/matrix_of_set_02/expected/model_4_4-solution000003.solution deleted file mode 100644 index cbfa586d38..0000000000 --- a/tests/exhaustive/basic/matrix_of_set_02/expected/model_4_4-solution000003.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be [{2}, {}; int(1..2)] -$ Visualisation for x -$ 2 -$ - diff --git a/tests/exhaustive/basic/matrix_of_set_02/expected/model_4_4-solution000004.solution b/tests/exhaustive/basic/matrix_of_set_02/expected/model_4_4-solution000004.solution deleted file mode 100644 index a392d5bbea..0000000000 --- a/tests/exhaustive/basic/matrix_of_set_02/expected/model_4_4-solution000004.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be [{2}, {2}; int(1..2)] -$ Visualisation for x -$ 2 -$ 2 - diff --git a/tests/exhaustive/basic/matrix_of_set_02/expected/model_4_4.eprime b/tests/exhaustive/basic/matrix_of_set_02/expected/model_4_4.eprime deleted file mode 100644 index 641fab2f7f..0000000000 --- a/tests/exhaustive/basic/matrix_of_set_02/expected/model_4_4.eprime +++ /dev/null @@ -1,19 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..2), int(1..3)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..2), int(1..3)] of int(1..3) -branching on [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] -such that - and([x_ExplicitVarSizeWithFlags_Flags[j, q7] -> x_ExplicitVarSizeWithFlags_Values[j, q7] % 2 = 0 - | j : int(1..2), q7 : int(1..3)]), - and([and([x_ExplicitVarSizeWithFlags_Flags[q1, q2 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1, q2] < x_ExplicitVarSizeWithFlags_Values[q1, q2 + 1] - | q2 : int(1..2)]) - | q1 : int(1..2)]), - and([and([x_ExplicitVarSizeWithFlags_Flags[q1, q3] = false -> x_ExplicitVarSizeWithFlags_Values[q1, q3] = 1 - | q3 : int(1..3)]) - | q1 : int(1..2)]), - and([and([x_ExplicitVarSizeWithFlags_Flags[q1, q4 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q1, q4] - | q4 : int(1..2)]) - | q1 : int(1..2)]) - diff --git a/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_1_1-solution000001.solution b/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_1_1-solution000001.solution deleted file mode 100644 index 88e783b8b0..0000000000 --- a/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_1_1-solution000001.solution +++ /dev/null @@ -1,13 +0,0 @@ -language Essence 1.3 - -letting x be [[{2}, {2}, {2}; int(1..3)], [{2}, {2}, {2}; int(1..3)]; int(1..2)] -$ Visualisation for x -$ 2 -$ 2 -$ 2 -$ -$ 2 -$ 2 -$ 2 -$ - diff --git a/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_1_1.eprime b/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_1_1.eprime deleted file mode 100644 index 93e46c5fc0..0000000000 --- a/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_1_1.eprime +++ /dev/null @@ -1,8 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1..2), int(1..3), int(1..3)] of bool -branching on [x_Occurrence] -such that - and([x_Occurrence[j1, j2, i] -> i % 2 = 0 | j1 : int(1..2), j2 : int(1..3), i : int(1..3)]), - and([and([1 <= sum([toInt(x_Occurrence[q1, q2, q3]) | q3 : int(1..3)]) | q2 : int(1..3)]) | q1 : int(1..2)]) - diff --git a/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_1_2-solution000001.solution b/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_1_2-solution000001.solution deleted file mode 100644 index 88e783b8b0..0000000000 --- a/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_1_2-solution000001.solution +++ /dev/null @@ -1,13 +0,0 @@ -language Essence 1.3 - -letting x be [[{2}, {2}, {2}; int(1..3)], [{2}, {2}, {2}; int(1..3)]; int(1..2)] -$ Visualisation for x -$ 2 -$ 2 -$ 2 -$ -$ 2 -$ 2 -$ 2 -$ - diff --git a/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_1_2.eprime b/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_1_2.eprime deleted file mode 100644 index d190146044..0000000000 --- a/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_1_2.eprime +++ /dev/null @@ -1,30 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1..2), int(1..3), int(1..3)] of bool -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..2), int(1..3), int(1..3)] of int(1..4) -branching on [x_ExplicitVarSizeWithDummy, x_Occurrence] -such that - and([x_Occurrence[j1, j2, i] -> i % 2 = 0 | j1 : int(1..2), j2 : int(1..3), i : int(1..3)]), - and([and([1 <= sum([toInt(x_Occurrence[q1, q2, q3]) | q3 : int(1..3)]) | q2 : int(1..3)]) | q1 : int(1..2)]), - and([and([and([x_ExplicitVarSizeWithDummy[q4, q5, q6] < x_ExplicitVarSizeWithDummy[q4, q5, q6 + 1] \/ - x_ExplicitVarSizeWithDummy[q4, q5, q6] = 4 - | q6 : int(1..2)]) - | q5 : int(1..3)]) - | q4 : int(1..2)]), - and([and([and([x_ExplicitVarSizeWithDummy[q4, q5, q7] = 4 -> x_ExplicitVarSizeWithDummy[q4, q5, q7 + 1] = 4 - | q7 : int(1..2)]) - | q5 : int(1..3)]) - | q4 : int(1..2)]), - and([and([1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q4, q5, q8] != 4) | q8 : int(1..3)]) | q5 : int(1..3)]) - | q4 : int(1..2)]), - and([and([and([x_ExplicitVarSizeWithDummy[q10, q12, q15] != 4 -> - x_Occurrence[q10, q12, x_ExplicitVarSizeWithDummy[q10, q12, q15]] - | q15 : int(1..3)]) - /\ - and([x_Occurrence[q10, q12, q16] -> - or([x_ExplicitVarSizeWithDummy[q10, q12, q18] != 4 /\ x_ExplicitVarSizeWithDummy[q10, q12, q18] = q16 - | q18 : int(1..3)]) - | q16 : int(1..3)]) - | q12 : int(1..3)]) - | q10 : int(1..2)]) - diff --git a/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_1_3-solution000001.solution b/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_1_3-solution000001.solution deleted file mode 100644 index 88e783b8b0..0000000000 --- a/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_1_3-solution000001.solution +++ /dev/null @@ -1,13 +0,0 @@ -language Essence 1.3 - -letting x be [[{2}, {2}, {2}; int(1..3)], [{2}, {2}, {2}; int(1..3)]; int(1..2)] -$ Visualisation for x -$ 2 -$ 2 -$ 2 -$ -$ 2 -$ 2 -$ 2 -$ - diff --git a/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_1_3.eprime b/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_1_3.eprime deleted file mode 100644 index bf9afdb1e3..0000000000 --- a/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_1_3.eprime +++ /dev/null @@ -1,31 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1..2), int(1..3), int(1..3)] of bool -find x_ExplicitVarSizeWithMarker_Marker: matrix indexed by [int(1..2), int(1..3)] of int(0..3) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..2), int(1..3), int(1..3)] of int(1..3) -branching on [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_Occurrence] -such that - and([x_Occurrence[j1, j2, i] -> i % 2 = 0 | j1 : int(1..2), j2 : int(1..3), i : int(1..3)]), - and([and([1 <= sum([toInt(x_Occurrence[q1, q2, q3]) | q3 : int(1..3)]) | q2 : int(1..3)]) | q1 : int(1..2)]), - and([and([and([q6 + 1 <= x_ExplicitVarSizeWithMarker_Marker[q4, q5] -> - x_ExplicitVarSizeWithMarker_Values[q4, q5, q6] < x_ExplicitVarSizeWithMarker_Values[q4, q5, q6 + 1] - | q6 : int(1..2)]) - | q5 : int(1..3)]) - | q4 : int(1..2)]), - and([and([and([q7 > x_ExplicitVarSizeWithMarker_Marker[q4, q5] -> x_ExplicitVarSizeWithMarker_Values[q4, q5, q7] = 1 - | q7 : int(1..3)]) - | q5 : int(1..3)]) - | q4 : int(1..2)]), - and([and([1 <= x_ExplicitVarSizeWithMarker_Marker[q4, q5] | q5 : int(1..3)]) | q4 : int(1..2)]), - and([and([and([q14 <= x_ExplicitVarSizeWithMarker_Marker[q9, q11] -> - x_Occurrence[q9, q11, x_ExplicitVarSizeWithMarker_Values[q9, q11, q14]] - | q14 : int(1..3)]) - /\ - and([x_Occurrence[q9, q11, q15] -> - or([q17 <= x_ExplicitVarSizeWithMarker_Marker[q9, q11] /\ - x_ExplicitVarSizeWithMarker_Values[q9, q11, q17] = q15 - | q17 : int(1..3)]) - | q15 : int(1..3)]) - | q11 : int(1..3)]) - | q9 : int(1..2)]) - diff --git a/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_1_4-solution000001.solution b/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_1_4-solution000001.solution deleted file mode 100644 index 88e783b8b0..0000000000 --- a/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_1_4-solution000001.solution +++ /dev/null @@ -1,13 +0,0 @@ -language Essence 1.3 - -letting x be [[{2}, {2}, {2}; int(1..3)], [{2}, {2}, {2}; int(1..3)]; int(1..2)] -$ Visualisation for x -$ 2 -$ 2 -$ 2 -$ -$ 2 -$ 2 -$ 2 -$ - diff --git a/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_1_4.eprime b/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_1_4.eprime deleted file mode 100644 index 39b0762f3c..0000000000 --- a/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_1_4.eprime +++ /dev/null @@ -1,37 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1..2), int(1..3), int(1..3)] of bool -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..2), int(1..3), int(1..3)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..2), int(1..3), int(1..3)] of int(1..3) -branching on [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_Occurrence] -such that - and([x_Occurrence[j1, j2, i] -> i % 2 = 0 | j1 : int(1..2), j2 : int(1..3), i : int(1..3)]), - and([and([1 <= sum([toInt(x_Occurrence[q1, q2, q3]) | q3 : int(1..3)]) | q2 : int(1..3)]) | q1 : int(1..2)]), - and([and([and([x_ExplicitVarSizeWithFlags_Flags[q4, q5, q6 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q4, q5, q6] < x_ExplicitVarSizeWithFlags_Values[q4, q5, q6 + 1] - | q6 : int(1..2)]) - | q5 : int(1..3)]) - | q4 : int(1..2)]), - and([and([and([x_ExplicitVarSizeWithFlags_Flags[q4, q5, q7] = false -> - x_ExplicitVarSizeWithFlags_Values[q4, q5, q7] = 1 - | q7 : int(1..3)]) - | q5 : int(1..3)]) - | q4 : int(1..2)]), - and([and([and([x_ExplicitVarSizeWithFlags_Flags[q4, q5, q8 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q4, q5, q8] - | q8 : int(1..2)]) - | q5 : int(1..3)]) - | q4 : int(1..2)]), - and([and([1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4, q5, q9]) | q9 : int(1..3)]) | q5 : int(1..3)]) - | q4 : int(1..2)]), - and([and([and([x_ExplicitVarSizeWithFlags_Flags[q11, q13, q16] -> - x_Occurrence[q11, q13, x_ExplicitVarSizeWithFlags_Values[q11, q13, q16]] - | q16 : int(1..3)]) - /\ - and([x_Occurrence[q11, q13, q17] -> - or([x_ExplicitVarSizeWithFlags_Flags[q11, q13, q19] /\ - x_ExplicitVarSizeWithFlags_Values[q11, q13, q19] = q17 - | q19 : int(1..3)]) - | q17 : int(1..3)]) - | q13 : int(1..3)]) - | q11 : int(1..2)]) - diff --git a/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_2_1-solution000001.solution b/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_2_1-solution000001.solution deleted file mode 100644 index 88e783b8b0..0000000000 --- a/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_2_1-solution000001.solution +++ /dev/null @@ -1,13 +0,0 @@ -language Essence 1.3 - -letting x be [[{2}, {2}, {2}; int(1..3)], [{2}, {2}, {2}; int(1..3)]; int(1..2)] -$ Visualisation for x -$ 2 -$ 2 -$ 2 -$ -$ 2 -$ 2 -$ 2 -$ - diff --git a/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_2_1.eprime b/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_2_1.eprime deleted file mode 100644 index 930a9b9b07..0000000000 --- a/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_2_1.eprime +++ /dev/null @@ -1,31 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..2), int(1..3), int(1..3)] of int(1..4) -find x_Occurrence: matrix indexed by [int(1..2), int(1..3), int(1..3)] of bool -branching on [x_Occurrence, x_ExplicitVarSizeWithDummy] -such that - and([x_ExplicitVarSizeWithDummy[j1, j2, q19] != 4 -> x_ExplicitVarSizeWithDummy[j1, j2, q19] % 2 = 0 - | j1 : int(1..2), j2 : int(1..3), q19 : int(1..3)]), - and([and([and([x_ExplicitVarSizeWithDummy[q1, q2, q3] < x_ExplicitVarSizeWithDummy[q1, q2, q3 + 1] \/ - x_ExplicitVarSizeWithDummy[q1, q2, q3] = 4 - | q3 : int(1..2)]) - | q2 : int(1..3)]) - | q1 : int(1..2)]), - and([and([and([x_ExplicitVarSizeWithDummy[q1, q2, q4] = 4 -> x_ExplicitVarSizeWithDummy[q1, q2, q4 + 1] = 4 - | q4 : int(1..2)]) - | q2 : int(1..3)]) - | q1 : int(1..2)]), - and([and([1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q1, q2, q5] != 4) | q5 : int(1..3)]) | q2 : int(1..3)]) - | q1 : int(1..2)]), - and([and([1 <= sum([toInt(x_Occurrence[q7, q8, q9]) | q9 : int(1..3)]) | q8 : int(1..3)]) | q7 : int(1..2)]), - and([and([and([x_Occurrence[q10, q12, q14] -> - or([x_ExplicitVarSizeWithDummy[q10, q12, q16] != 4 /\ x_ExplicitVarSizeWithDummy[q10, q12, q16] = q14 - | q16 : int(1..3)]) - | q14 : int(1..3)]) - /\ - and([x_ExplicitVarSizeWithDummy[q10, q12, q18] != 4 -> - x_Occurrence[q10, q12, x_ExplicitVarSizeWithDummy[q10, q12, q18]] - | q18 : int(1..3)]) - | q12 : int(1..3)]) - | q10 : int(1..2)]) - diff --git a/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_2_2-solution000001.solution b/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_2_2-solution000001.solution deleted file mode 100644 index 88e783b8b0..0000000000 --- a/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_2_2-solution000001.solution +++ /dev/null @@ -1,13 +0,0 @@ -language Essence 1.3 - -letting x be [[{2}, {2}, {2}; int(1..3)], [{2}, {2}, {2}; int(1..3)]; int(1..2)] -$ Visualisation for x -$ 2 -$ 2 -$ 2 -$ -$ 2 -$ 2 -$ 2 -$ - diff --git a/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_2_2.eprime b/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_2_2.eprime deleted file mode 100644 index e236ad9239..0000000000 --- a/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_2_2.eprime +++ /dev/null @@ -1,19 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..2), int(1..3), int(1..3)] of int(1..4) -branching on [x_ExplicitVarSizeWithDummy] -such that - and([x_ExplicitVarSizeWithDummy[j1, j2, q7] != 4 -> x_ExplicitVarSizeWithDummy[j1, j2, q7] % 2 = 0 - | j1 : int(1..2), j2 : int(1..3), q7 : int(1..3)]), - and([and([and([x_ExplicitVarSizeWithDummy[q1, q2, q3] < x_ExplicitVarSizeWithDummy[q1, q2, q3 + 1] \/ - x_ExplicitVarSizeWithDummy[q1, q2, q3] = 4 - | q3 : int(1..2)]) - | q2 : int(1..3)]) - | q1 : int(1..2)]), - and([and([and([x_ExplicitVarSizeWithDummy[q1, q2, q4] = 4 -> x_ExplicitVarSizeWithDummy[q1, q2, q4 + 1] = 4 - | q4 : int(1..2)]) - | q2 : int(1..3)]) - | q1 : int(1..2)]), - and([and([1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q1, q2, q5] != 4) | q5 : int(1..3)]) | q2 : int(1..3)]) - | q1 : int(1..2)]) - diff --git a/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_2_3-solution000001.solution b/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_2_3-solution000001.solution deleted file mode 100644 index 88e783b8b0..0000000000 --- a/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_2_3-solution000001.solution +++ /dev/null @@ -1,13 +0,0 @@ -language Essence 1.3 - -letting x be [[{2}, {2}, {2}; int(1..3)], [{2}, {2}, {2}; int(1..3)]; int(1..2)] -$ Visualisation for x -$ 2 -$ 2 -$ 2 -$ -$ 2 -$ 2 -$ 2 -$ - diff --git a/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_2_3.eprime b/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_2_3.eprime deleted file mode 100644 index 7920954488..0000000000 --- a/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_2_3.eprime +++ /dev/null @@ -1,45 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..2), int(1..3), int(1..3)] of int(1..4) -find x_ExplicitVarSizeWithMarker_Marker: matrix indexed by [int(1..2), int(1..3)] of int(0..3) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..2), int(1..3), int(1..3)] of int(1..3) -branching on [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy] -such that - and([x_ExplicitVarSizeWithDummy[j1, j2, q24] != 4 -> x_ExplicitVarSizeWithDummy[j1, j2, q24] % 2 = 0 - | j1 : int(1..2), j2 : int(1..3), q24 : int(1..3)]), - and([and([and([x_ExplicitVarSizeWithDummy[q1, q2, q3] < x_ExplicitVarSizeWithDummy[q1, q2, q3 + 1] \/ - x_ExplicitVarSizeWithDummy[q1, q2, q3] = 4 - | q3 : int(1..2)]) - | q2 : int(1..3)]) - | q1 : int(1..2)]), - and([and([and([x_ExplicitVarSizeWithDummy[q1, q2, q4] = 4 -> x_ExplicitVarSizeWithDummy[q1, q2, q4 + 1] = 4 - | q4 : int(1..2)]) - | q2 : int(1..3)]) - | q1 : int(1..2)]), - and([and([1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q1, q2, q5] != 4) | q5 : int(1..3)]) | q2 : int(1..3)]) - | q1 : int(1..2)]), - and([and([and([q9 + 1 <= x_ExplicitVarSizeWithMarker_Marker[q7, q8] -> - x_ExplicitVarSizeWithMarker_Values[q7, q8, q9] < x_ExplicitVarSizeWithMarker_Values[q7, q8, q9 + 1] - | q9 : int(1..2)]) - | q8 : int(1..3)]) - | q7 : int(1..2)]), - and([and([and([q10 > x_ExplicitVarSizeWithMarker_Marker[q7, q8] -> - x_ExplicitVarSizeWithMarker_Values[q7, q8, q10] = 1 - | q10 : int(1..3)]) - | q8 : int(1..3)]) - | q7 : int(1..2)]), - and([and([1 <= x_ExplicitVarSizeWithMarker_Marker[q7, q8] | q8 : int(1..3)]) | q7 : int(1..2)]), - and([and([and([q17 <= x_ExplicitVarSizeWithMarker_Marker[q12, q14] -> - or([x_ExplicitVarSizeWithDummy[q12, q14, q19] != 4 /\ - x_ExplicitVarSizeWithDummy[q12, q14, q19] = x_ExplicitVarSizeWithMarker_Values[q12, q14, q17] - | q19 : int(1..3)]) - | q17 : int(1..3)]) - /\ - and([x_ExplicitVarSizeWithDummy[q12, q14, q21] != 4 -> - or([q23 <= x_ExplicitVarSizeWithMarker_Marker[q12, q14] /\ - x_ExplicitVarSizeWithMarker_Values[q12, q14, q23] = x_ExplicitVarSizeWithDummy[q12, q14, q21] - | q23 : int(1..3)]) - | q21 : int(1..3)]) - | q14 : int(1..3)]) - | q12 : int(1..2)]) - diff --git a/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_2_4-solution000001.solution b/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_2_4-solution000001.solution deleted file mode 100644 index 88e783b8b0..0000000000 --- a/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_2_4-solution000001.solution +++ /dev/null @@ -1,13 +0,0 @@ -language Essence 1.3 - -letting x be [[{2}, {2}, {2}; int(1..3)], [{2}, {2}, {2}; int(1..3)]; int(1..2)] -$ Visualisation for x -$ 2 -$ 2 -$ 2 -$ -$ 2 -$ 2 -$ 2 -$ - diff --git a/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_2_4.eprime b/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_2_4.eprime deleted file mode 100644 index 7ea793896c..0000000000 --- a/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_2_4.eprime +++ /dev/null @@ -1,50 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..2), int(1..3), int(1..3)] of int(1..4) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..2), int(1..3), int(1..3)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..2), int(1..3), int(1..3)] of int(1..3) -branching on [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy] -such that - and([x_ExplicitVarSizeWithDummy[j1, j2, q26] != 4 -> x_ExplicitVarSizeWithDummy[j1, j2, q26] % 2 = 0 - | j1 : int(1..2), j2 : int(1..3), q26 : int(1..3)]), - and([and([and([x_ExplicitVarSizeWithDummy[q1, q2, q3] < x_ExplicitVarSizeWithDummy[q1, q2, q3 + 1] \/ - x_ExplicitVarSizeWithDummy[q1, q2, q3] = 4 - | q3 : int(1..2)]) - | q2 : int(1..3)]) - | q1 : int(1..2)]), - and([and([and([x_ExplicitVarSizeWithDummy[q1, q2, q4] = 4 -> x_ExplicitVarSizeWithDummy[q1, q2, q4 + 1] = 4 - | q4 : int(1..2)]) - | q2 : int(1..3)]) - | q1 : int(1..2)]), - and([and([1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q1, q2, q5] != 4) | q5 : int(1..3)]) | q2 : int(1..3)]) - | q1 : int(1..2)]), - and([and([and([x_ExplicitVarSizeWithFlags_Flags[q7, q8, q9 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q7, q8, q9] < x_ExplicitVarSizeWithFlags_Values[q7, q8, q9 + 1] - | q9 : int(1..2)]) - | q8 : int(1..3)]) - | q7 : int(1..2)]), - and([and([and([x_ExplicitVarSizeWithFlags_Flags[q7, q8, q10] = false -> - x_ExplicitVarSizeWithFlags_Values[q7, q8, q10] = 1 - | q10 : int(1..3)]) - | q8 : int(1..3)]) - | q7 : int(1..2)]), - and([and([and([x_ExplicitVarSizeWithFlags_Flags[q7, q8, q11 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q7, q8, q11] - | q11 : int(1..2)]) - | q8 : int(1..3)]) - | q7 : int(1..2)]), - and([and([1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q7, q8, q12]) | q12 : int(1..3)]) | q8 : int(1..3)]) - | q7 : int(1..2)]), - and([and([and([x_ExplicitVarSizeWithFlags_Flags[q14, q16, q19] -> - or([x_ExplicitVarSizeWithDummy[q14, q16, q21] != 4 /\ - x_ExplicitVarSizeWithDummy[q14, q16, q21] = x_ExplicitVarSizeWithFlags_Values[q14, q16, q19] - | q21 : int(1..3)]) - | q19 : int(1..3)]) - /\ - and([x_ExplicitVarSizeWithDummy[q14, q16, q23] != 4 -> - or([x_ExplicitVarSizeWithFlags_Flags[q14, q16, q25] /\ - x_ExplicitVarSizeWithFlags_Values[q14, q16, q25] = x_ExplicitVarSizeWithDummy[q14, q16, q23] - | q25 : int(1..3)]) - | q23 : int(1..3)]) - | q16 : int(1..3)]) - | q14 : int(1..2)]) - diff --git a/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_3_1-solution000001.solution b/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_3_1-solution000001.solution deleted file mode 100644 index 88e783b8b0..0000000000 --- a/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_3_1-solution000001.solution +++ /dev/null @@ -1,13 +0,0 @@ -language Essence 1.3 - -letting x be [[{2}, {2}, {2}; int(1..3)], [{2}, {2}, {2}; int(1..3)]; int(1..2)] -$ Visualisation for x -$ 2 -$ 2 -$ 2 -$ -$ 2 -$ 2 -$ 2 -$ - diff --git a/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_3_1.eprime b/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_3_1.eprime deleted file mode 100644 index 8512304454..0000000000 --- a/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_3_1.eprime +++ /dev/null @@ -1,32 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: matrix indexed by [int(1..2), int(1..3)] of int(0..3) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..2), int(1..3), int(1..3)] of int(1..3) -find x_Occurrence: matrix indexed by [int(1..2), int(1..3), int(1..3)] of bool -branching on [x_Occurrence, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] -such that - and([q18 <= x_ExplicitVarSizeWithMarker_Marker[j1, j2] -> x_ExplicitVarSizeWithMarker_Values[j1, j2, q18] % 2 = 0 - | j1 : int(1..2), j2 : int(1..3), q18 : int(1..3)]), - and([and([and([q3 + 1 <= x_ExplicitVarSizeWithMarker_Marker[q1, q2] -> - x_ExplicitVarSizeWithMarker_Values[q1, q2, q3] < x_ExplicitVarSizeWithMarker_Values[q1, q2, q3 + 1] - | q3 : int(1..2)]) - | q2 : int(1..3)]) - | q1 : int(1..2)]), - and([and([and([q4 > x_ExplicitVarSizeWithMarker_Marker[q1, q2] -> x_ExplicitVarSizeWithMarker_Values[q1, q2, q4] = 1 - | q4 : int(1..3)]) - | q2 : int(1..3)]) - | q1 : int(1..2)]), - and([and([1 <= x_ExplicitVarSizeWithMarker_Marker[q1, q2] | q2 : int(1..3)]) | q1 : int(1..2)]), - and([and([1 <= sum([toInt(x_Occurrence[q6, q7, q8]) | q8 : int(1..3)]) | q7 : int(1..3)]) | q6 : int(1..2)]), - and([and([and([x_Occurrence[q9, q11, q13] -> - or([q15 <= x_ExplicitVarSizeWithMarker_Marker[q9, q11] /\ - x_ExplicitVarSizeWithMarker_Values[q9, q11, q15] = q13 - | q15 : int(1..3)]) - | q13 : int(1..3)]) - /\ - and([q17 <= x_ExplicitVarSizeWithMarker_Marker[q9, q11] -> - x_Occurrence[q9, q11, x_ExplicitVarSizeWithMarker_Values[q9, q11, q17]] - | q17 : int(1..3)]) - | q11 : int(1..3)]) - | q9 : int(1..2)]) - diff --git a/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_3_2-solution000001.solution b/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_3_2-solution000001.solution deleted file mode 100644 index 88e783b8b0..0000000000 --- a/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_3_2-solution000001.solution +++ /dev/null @@ -1,13 +0,0 @@ -language Essence 1.3 - -letting x be [[{2}, {2}, {2}; int(1..3)], [{2}, {2}, {2}; int(1..3)]; int(1..2)] -$ Visualisation for x -$ 2 -$ 2 -$ 2 -$ -$ 2 -$ 2 -$ 2 -$ - diff --git a/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_3_2.eprime b/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_3_2.eprime deleted file mode 100644 index 1d07948b63..0000000000 --- a/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_3_2.eprime +++ /dev/null @@ -1,44 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: matrix indexed by [int(1..2), int(1..3)] of int(0..3) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..2), int(1..3), int(1..3)] of int(1..3) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..2), int(1..3), int(1..3)] of int(1..4) -branching on [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] -such that - and([q24 <= x_ExplicitVarSizeWithMarker_Marker[j1, j2] -> x_ExplicitVarSizeWithMarker_Values[j1, j2, q24] % 2 = 0 - | j1 : int(1..2), j2 : int(1..3), q24 : int(1..3)]), - and([and([and([q3 + 1 <= x_ExplicitVarSizeWithMarker_Marker[q1, q2] -> - x_ExplicitVarSizeWithMarker_Values[q1, q2, q3] < x_ExplicitVarSizeWithMarker_Values[q1, q2, q3 + 1] - | q3 : int(1..2)]) - | q2 : int(1..3)]) - | q1 : int(1..2)]), - and([and([and([q4 > x_ExplicitVarSizeWithMarker_Marker[q1, q2] -> x_ExplicitVarSizeWithMarker_Values[q1, q2, q4] = 1 - | q4 : int(1..3)]) - | q2 : int(1..3)]) - | q1 : int(1..2)]), - and([and([1 <= x_ExplicitVarSizeWithMarker_Marker[q1, q2] | q2 : int(1..3)]) | q1 : int(1..2)]), - and([and([and([x_ExplicitVarSizeWithDummy[q6, q7, q8] < x_ExplicitVarSizeWithDummy[q6, q7, q8 + 1] \/ - x_ExplicitVarSizeWithDummy[q6, q7, q8] = 4 - | q8 : int(1..2)]) - | q7 : int(1..3)]) - | q6 : int(1..2)]), - and([and([and([x_ExplicitVarSizeWithDummy[q6, q7, q9] = 4 -> x_ExplicitVarSizeWithDummy[q6, q7, q9 + 1] = 4 - | q9 : int(1..2)]) - | q7 : int(1..3)]) - | q6 : int(1..2)]), - and([and([1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q6, q7, q10] != 4) | q10 : int(1..3)]) | q7 : int(1..3)]) - | q6 : int(1..2)]), - and([and([and([x_ExplicitVarSizeWithDummy[q12, q14, q17] != 4 -> - or([q19 <= x_ExplicitVarSizeWithMarker_Marker[q12, q14] /\ - x_ExplicitVarSizeWithMarker_Values[q12, q14, q19] = x_ExplicitVarSizeWithDummy[q12, q14, q17] - | q19 : int(1..3)]) - | q17 : int(1..3)]) - /\ - and([q21 <= x_ExplicitVarSizeWithMarker_Marker[q12, q14] -> - or([x_ExplicitVarSizeWithDummy[q12, q14, q23] != 4 /\ - x_ExplicitVarSizeWithDummy[q12, q14, q23] = x_ExplicitVarSizeWithMarker_Values[q12, q14, q21] - | q23 : int(1..3)]) - | q21 : int(1..3)]) - | q14 : int(1..3)]) - | q12 : int(1..2)]) - diff --git a/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_3_3-solution000001.solution b/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_3_3-solution000001.solution deleted file mode 100644 index 88e783b8b0..0000000000 --- a/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_3_3-solution000001.solution +++ /dev/null @@ -1,13 +0,0 @@ -language Essence 1.3 - -letting x be [[{2}, {2}, {2}; int(1..3)], [{2}, {2}, {2}; int(1..3)]; int(1..2)] -$ Visualisation for x -$ 2 -$ 2 -$ 2 -$ -$ 2 -$ 2 -$ 2 -$ - diff --git a/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_3_3.eprime b/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_3_3.eprime deleted file mode 100644 index 470bd34100..0000000000 --- a/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_3_3.eprime +++ /dev/null @@ -1,19 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: matrix indexed by [int(1..2), int(1..3)] of int(0..3) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..2), int(1..3), int(1..3)] of int(1..3) -branching on [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] -such that - and([q6 <= x_ExplicitVarSizeWithMarker_Marker[j1, j2] -> x_ExplicitVarSizeWithMarker_Values[j1, j2, q6] % 2 = 0 - | j1 : int(1..2), j2 : int(1..3), q6 : int(1..3)]), - and([and([and([q3 + 1 <= x_ExplicitVarSizeWithMarker_Marker[q1, q2] -> - x_ExplicitVarSizeWithMarker_Values[q1, q2, q3] < x_ExplicitVarSizeWithMarker_Values[q1, q2, q3 + 1] - | q3 : int(1..2)]) - | q2 : int(1..3)]) - | q1 : int(1..2)]), - and([and([and([q4 > x_ExplicitVarSizeWithMarker_Marker[q1, q2] -> x_ExplicitVarSizeWithMarker_Values[q1, q2, q4] = 1 - | q4 : int(1..3)]) - | q2 : int(1..3)]) - | q1 : int(1..2)]), - and([and([1 <= x_ExplicitVarSizeWithMarker_Marker[q1, q2] | q2 : int(1..3)]) | q1 : int(1..2)]) - diff --git a/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_3_4-solution000001.solution b/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_3_4-solution000001.solution deleted file mode 100644 index 88e783b8b0..0000000000 --- a/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_3_4-solution000001.solution +++ /dev/null @@ -1,13 +0,0 @@ -language Essence 1.3 - -letting x be [[{2}, {2}, {2}; int(1..3)], [{2}, {2}, {2}; int(1..3)]; int(1..2)] -$ Visualisation for x -$ 2 -$ 2 -$ 2 -$ -$ 2 -$ 2 -$ 2 -$ - diff --git a/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_3_4.eprime b/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_3_4.eprime deleted file mode 100644 index 3685e9f034..0000000000 --- a/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_3_4.eprime +++ /dev/null @@ -1,54 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: matrix indexed by [int(1..2), int(1..3)] of int(0..3) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..2), int(1..3), int(1..3)] of int(1..3) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..2), int(1..3), int(1..3)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..2), int(1..3), int(1..3)] of int(1..3) -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithMarker_Marker, - x_ExplicitVarSizeWithMarker_Values] -such that - and([q25 <= x_ExplicitVarSizeWithMarker_Marker[j1, j2] -> x_ExplicitVarSizeWithMarker_Values[j1, j2, q25] % 2 = 0 - | j1 : int(1..2), j2 : int(1..3), q25 : int(1..3)]), - and([and([and([q3 + 1 <= x_ExplicitVarSizeWithMarker_Marker[q1, q2] -> - x_ExplicitVarSizeWithMarker_Values[q1, q2, q3] < x_ExplicitVarSizeWithMarker_Values[q1, q2, q3 + 1] - | q3 : int(1..2)]) - | q2 : int(1..3)]) - | q1 : int(1..2)]), - and([and([and([q4 > x_ExplicitVarSizeWithMarker_Marker[q1, q2] -> x_ExplicitVarSizeWithMarker_Values[q1, q2, q4] = 1 - | q4 : int(1..3)]) - | q2 : int(1..3)]) - | q1 : int(1..2)]), - and([and([1 <= x_ExplicitVarSizeWithMarker_Marker[q1, q2] | q2 : int(1..3)]) | q1 : int(1..2)]), - and([and([and([x_ExplicitVarSizeWithFlags_Flags[q6, q7, q8 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q6, q7, q8] < x_ExplicitVarSizeWithFlags_Values[q6, q7, q8 + 1] - | q8 : int(1..2)]) - | q7 : int(1..3)]) - | q6 : int(1..2)]), - and([and([and([x_ExplicitVarSizeWithFlags_Flags[q6, q7, q9] = false -> - x_ExplicitVarSizeWithFlags_Values[q6, q7, q9] = 1 - | q9 : int(1..3)]) - | q7 : int(1..3)]) - | q6 : int(1..2)]), - and([and([and([x_ExplicitVarSizeWithFlags_Flags[q6, q7, q10 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q6, q7, q10] - | q10 : int(1..2)]) - | q7 : int(1..3)]) - | q6 : int(1..2)]), - and([and([1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q6, q7, q11]) | q11 : int(1..3)]) | q7 : int(1..3)]) - | q6 : int(1..2)]), - and([and([and([x_ExplicitVarSizeWithFlags_Flags[q13, q15, q18] -> - or([q20 <= x_ExplicitVarSizeWithMarker_Marker[q13, q15] /\ - x_ExplicitVarSizeWithMarker_Values[q13, q15, q20] = - x_ExplicitVarSizeWithFlags_Values[q13, q15, q18] - | q20 : int(1..3)]) - | q18 : int(1..3)]) - /\ - and([q22 <= x_ExplicitVarSizeWithMarker_Marker[q13, q15] -> - or([x_ExplicitVarSizeWithFlags_Flags[q13, q15, q24] /\ - x_ExplicitVarSizeWithFlags_Values[q13, q15, q24] = - x_ExplicitVarSizeWithMarker_Values[q13, q15, q22] - | q24 : int(1..3)]) - | q22 : int(1..3)]) - | q15 : int(1..3)]) - | q13 : int(1..2)]) - diff --git a/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_4_1-solution000001.solution b/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_4_1-solution000001.solution deleted file mode 100644 index 88e783b8b0..0000000000 --- a/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_4_1-solution000001.solution +++ /dev/null @@ -1,13 +0,0 @@ -language Essence 1.3 - -letting x be [[{2}, {2}, {2}; int(1..3)], [{2}, {2}, {2}; int(1..3)]; int(1..2)] -$ Visualisation for x -$ 2 -$ 2 -$ 2 -$ -$ 2 -$ 2 -$ 2 -$ - diff --git a/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_4_1.eprime b/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_4_1.eprime deleted file mode 100644 index af1e5066df..0000000000 --- a/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_4_1.eprime +++ /dev/null @@ -1,38 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..2), int(1..3), int(1..3)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..2), int(1..3), int(1..3)] of int(1..3) -find x_Occurrence: matrix indexed by [int(1..2), int(1..3), int(1..3)] of bool -branching on [x_Occurrence, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] -such that - and([x_ExplicitVarSizeWithFlags_Flags[j1, j2, q20] -> x_ExplicitVarSizeWithFlags_Values[j1, j2, q20] % 2 = 0 - | j1 : int(1..2), j2 : int(1..3), q20 : int(1..3)]), - and([and([and([x_ExplicitVarSizeWithFlags_Flags[q1, q2, q3 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1, q2, q3] < x_ExplicitVarSizeWithFlags_Values[q1, q2, q3 + 1] - | q3 : int(1..2)]) - | q2 : int(1..3)]) - | q1 : int(1..2)]), - and([and([and([x_ExplicitVarSizeWithFlags_Flags[q1, q2, q4] = false -> - x_ExplicitVarSizeWithFlags_Values[q1, q2, q4] = 1 - | q4 : int(1..3)]) - | q2 : int(1..3)]) - | q1 : int(1..2)]), - and([and([and([x_ExplicitVarSizeWithFlags_Flags[q1, q2, q5 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q1, q2, q5] - | q5 : int(1..2)]) - | q2 : int(1..3)]) - | q1 : int(1..2)]), - and([and([1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q1, q2, q6]) | q6 : int(1..3)]) | q2 : int(1..3)]) - | q1 : int(1..2)]), - and([and([1 <= sum([toInt(x_Occurrence[q8, q9, q10]) | q10 : int(1..3)]) | q9 : int(1..3)]) | q8 : int(1..2)]), - and([and([and([x_Occurrence[q11, q13, q15] -> - or([x_ExplicitVarSizeWithFlags_Flags[q11, q13, q17] /\ - x_ExplicitVarSizeWithFlags_Values[q11, q13, q17] = q15 - | q17 : int(1..3)]) - | q15 : int(1..3)]) - /\ - and([x_ExplicitVarSizeWithFlags_Flags[q11, q13, q19] -> - x_Occurrence[q11, q13, x_ExplicitVarSizeWithFlags_Values[q11, q13, q19]] - | q19 : int(1..3)]) - | q13 : int(1..3)]) - | q11 : int(1..2)]) - diff --git a/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_4_2-solution000001.solution b/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_4_2-solution000001.solution deleted file mode 100644 index 88e783b8b0..0000000000 --- a/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_4_2-solution000001.solution +++ /dev/null @@ -1,13 +0,0 @@ -language Essence 1.3 - -letting x be [[{2}, {2}, {2}; int(1..3)], [{2}, {2}, {2}; int(1..3)]; int(1..2)] -$ Visualisation for x -$ 2 -$ 2 -$ 2 -$ -$ 2 -$ 2 -$ 2 -$ - diff --git a/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_4_2.eprime b/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_4_2.eprime deleted file mode 100644 index 18fd6c5c2f..0000000000 --- a/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_4_2.eprime +++ /dev/null @@ -1,50 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..2), int(1..3), int(1..3)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..2), int(1..3), int(1..3)] of int(1..3) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..2), int(1..3), int(1..3)] of int(1..4) -branching on [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] -such that - and([x_ExplicitVarSizeWithFlags_Flags[j1, j2, q26] -> x_ExplicitVarSizeWithFlags_Values[j1, j2, q26] % 2 = 0 - | j1 : int(1..2), j2 : int(1..3), q26 : int(1..3)]), - and([and([and([x_ExplicitVarSizeWithFlags_Flags[q1, q2, q3 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1, q2, q3] < x_ExplicitVarSizeWithFlags_Values[q1, q2, q3 + 1] - | q3 : int(1..2)]) - | q2 : int(1..3)]) - | q1 : int(1..2)]), - and([and([and([x_ExplicitVarSizeWithFlags_Flags[q1, q2, q4] = false -> - x_ExplicitVarSizeWithFlags_Values[q1, q2, q4] = 1 - | q4 : int(1..3)]) - | q2 : int(1..3)]) - | q1 : int(1..2)]), - and([and([and([x_ExplicitVarSizeWithFlags_Flags[q1, q2, q5 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q1, q2, q5] - | q5 : int(1..2)]) - | q2 : int(1..3)]) - | q1 : int(1..2)]), - and([and([1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q1, q2, q6]) | q6 : int(1..3)]) | q2 : int(1..3)]) - | q1 : int(1..2)]), - and([and([and([x_ExplicitVarSizeWithDummy[q8, q9, q10] < x_ExplicitVarSizeWithDummy[q8, q9, q10 + 1] \/ - x_ExplicitVarSizeWithDummy[q8, q9, q10] = 4 - | q10 : int(1..2)]) - | q9 : int(1..3)]) - | q8 : int(1..2)]), - and([and([and([x_ExplicitVarSizeWithDummy[q8, q9, q11] = 4 -> x_ExplicitVarSizeWithDummy[q8, q9, q11 + 1] = 4 - | q11 : int(1..2)]) - | q9 : int(1..3)]) - | q8 : int(1..2)]), - and([and([1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q8, q9, q12] != 4) | q12 : int(1..3)]) | q9 : int(1..3)]) - | q8 : int(1..2)]), - and([and([and([x_ExplicitVarSizeWithDummy[q14, q16, q19] != 4 -> - or([x_ExplicitVarSizeWithFlags_Flags[q14, q16, q21] /\ - x_ExplicitVarSizeWithFlags_Values[q14, q16, q21] = x_ExplicitVarSizeWithDummy[q14, q16, q19] - | q21 : int(1..3)]) - | q19 : int(1..3)]) - /\ - and([x_ExplicitVarSizeWithFlags_Flags[q14, q16, q23] -> - or([x_ExplicitVarSizeWithDummy[q14, q16, q25] != 4 /\ - x_ExplicitVarSizeWithDummy[q14, q16, q25] = x_ExplicitVarSizeWithFlags_Values[q14, q16, q23] - | q25 : int(1..3)]) - | q23 : int(1..3)]) - | q16 : int(1..3)]) - | q14 : int(1..2)]) - diff --git a/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_4_3-solution000001.solution b/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_4_3-solution000001.solution deleted file mode 100644 index 88e783b8b0..0000000000 --- a/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_4_3-solution000001.solution +++ /dev/null @@ -1,13 +0,0 @@ -language Essence 1.3 - -letting x be [[{2}, {2}, {2}; int(1..3)], [{2}, {2}, {2}; int(1..3)]; int(1..2)] -$ Visualisation for x -$ 2 -$ 2 -$ 2 -$ -$ 2 -$ 2 -$ 2 -$ - diff --git a/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_4_3.eprime b/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_4_3.eprime deleted file mode 100644 index 0716f2019d..0000000000 --- a/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_4_3.eprime +++ /dev/null @@ -1,55 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..2), int(1..3), int(1..3)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..2), int(1..3), int(1..3)] of int(1..3) -find x_ExplicitVarSizeWithMarker_Marker: matrix indexed by [int(1..2), int(1..3)] of int(0..3) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..2), int(1..3), int(1..3)] of int(1..3) -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithFlags_Flags, - x_ExplicitVarSizeWithFlags_Values] -such that - and([x_ExplicitVarSizeWithFlags_Flags[j1, j2, q25] -> x_ExplicitVarSizeWithFlags_Values[j1, j2, q25] % 2 = 0 - | j1 : int(1..2), j2 : int(1..3), q25 : int(1..3)]), - and([and([and([x_ExplicitVarSizeWithFlags_Flags[q1, q2, q3 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1, q2, q3] < x_ExplicitVarSizeWithFlags_Values[q1, q2, q3 + 1] - | q3 : int(1..2)]) - | q2 : int(1..3)]) - | q1 : int(1..2)]), - and([and([and([x_ExplicitVarSizeWithFlags_Flags[q1, q2, q4] = false -> - x_ExplicitVarSizeWithFlags_Values[q1, q2, q4] = 1 - | q4 : int(1..3)]) - | q2 : int(1..3)]) - | q1 : int(1..2)]), - and([and([and([x_ExplicitVarSizeWithFlags_Flags[q1, q2, q5 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q1, q2, q5] - | q5 : int(1..2)]) - | q2 : int(1..3)]) - | q1 : int(1..2)]), - and([and([1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q1, q2, q6]) | q6 : int(1..3)]) | q2 : int(1..3)]) - | q1 : int(1..2)]), - and([and([and([q10 + 1 <= x_ExplicitVarSizeWithMarker_Marker[q8, q9] -> - x_ExplicitVarSizeWithMarker_Values[q8, q9, q10] < x_ExplicitVarSizeWithMarker_Values[q8, q9, q10 + 1] - | q10 : int(1..2)]) - | q9 : int(1..3)]) - | q8 : int(1..2)]), - and([and([and([q11 > x_ExplicitVarSizeWithMarker_Marker[q8, q9] -> - x_ExplicitVarSizeWithMarker_Values[q8, q9, q11] = 1 - | q11 : int(1..3)]) - | q9 : int(1..3)]) - | q8 : int(1..2)]), - and([and([1 <= x_ExplicitVarSizeWithMarker_Marker[q8, q9] | q9 : int(1..3)]) | q8 : int(1..2)]), - and([and([and([q18 <= x_ExplicitVarSizeWithMarker_Marker[q13, q15] -> - or([x_ExplicitVarSizeWithFlags_Flags[q13, q15, q20] /\ - x_ExplicitVarSizeWithFlags_Values[q13, q15, q20] = - x_ExplicitVarSizeWithMarker_Values[q13, q15, q18] - | q20 : int(1..3)]) - | q18 : int(1..3)]) - /\ - and([x_ExplicitVarSizeWithFlags_Flags[q13, q15, q22] -> - or([q24 <= x_ExplicitVarSizeWithMarker_Marker[q13, q15] /\ - x_ExplicitVarSizeWithMarker_Values[q13, q15, q24] = - x_ExplicitVarSizeWithFlags_Values[q13, q15, q22] - | q24 : int(1..3)]) - | q22 : int(1..3)]) - | q15 : int(1..3)]) - | q13 : int(1..2)]) - diff --git a/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_4_4-solution000001.solution b/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_4_4-solution000001.solution deleted file mode 100644 index 88e783b8b0..0000000000 --- a/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_4_4-solution000001.solution +++ /dev/null @@ -1,13 +0,0 @@ -language Essence 1.3 - -letting x be [[{2}, {2}, {2}; int(1..3)], [{2}, {2}, {2}; int(1..3)]; int(1..2)] -$ Visualisation for x -$ 2 -$ 2 -$ 2 -$ -$ 2 -$ 2 -$ 2 -$ - diff --git a/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_4_4.eprime b/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_4_4.eprime deleted file mode 100644 index a9f5c660d9..0000000000 --- a/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_4_4.eprime +++ /dev/null @@ -1,25 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..2), int(1..3), int(1..3)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..2), int(1..3), int(1..3)] of int(1..3) -branching on [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] -such that - and([x_ExplicitVarSizeWithFlags_Flags[j1, j2, q8] -> x_ExplicitVarSizeWithFlags_Values[j1, j2, q8] % 2 = 0 - | j1 : int(1..2), j2 : int(1..3), q8 : int(1..3)]), - and([and([and([x_ExplicitVarSizeWithFlags_Flags[q1, q2, q3 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1, q2, q3] < x_ExplicitVarSizeWithFlags_Values[q1, q2, q3 + 1] - | q3 : int(1..2)]) - | q2 : int(1..3)]) - | q1 : int(1..2)]), - and([and([and([x_ExplicitVarSizeWithFlags_Flags[q1, q2, q4] = false -> - x_ExplicitVarSizeWithFlags_Values[q1, q2, q4] = 1 - | q4 : int(1..3)]) - | q2 : int(1..3)]) - | q1 : int(1..2)]), - and([and([and([x_ExplicitVarSizeWithFlags_Flags[q1, q2, q5 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q1, q2, q5] - | q5 : int(1..2)]) - | q2 : int(1..3)]) - | q1 : int(1..2)]), - and([and([1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q1, q2, q6]) | q6 : int(1..3)]) | q2 : int(1..3)]) - | q1 : int(1..2)]) - diff --git a/tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_1_1_1_1-solution000001.solution b/tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_1_1_1_1-solution000001.solution deleted file mode 100644 index 908faf0601..0000000000 --- a/tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_1_1_1_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be {2} -letting b be {2} diff --git a/tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_1_1_1_1.eprime b/tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_1_1_1_1.eprime deleted file mode 100644 index f6094ed941..0000000000 --- a/tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_1_1_1_1.eprime +++ /dev/null @@ -1,11 +0,0 @@ -language ESSENCE' 1.0 - -find a_Occurrence: matrix indexed by [int(1..3)] of bool -find b_Occurrence: matrix indexed by [int(1..3)] of bool -branching on [a_Occurrence, b_Occurrence] -such that - and([a_Occurrence[i] -> i % 2 = 0 | i : int(1..3)]), - and([b_Occurrence[i] -> i % 2 = 0 | i : int(1..3)]), - 1 = sum([toInt(a_Occurrence[q1]) | q1 : int(1..3)]), - 1 = sum([toInt(b_Occurrence[q2]) | q2 : int(1..3)]) - diff --git a/tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_1_1_1_2-solution000001.solution b/tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_1_1_1_2-solution000001.solution deleted file mode 100644 index 908faf0601..0000000000 --- a/tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_1_1_1_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be {2} -letting b be {2} diff --git a/tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_1_1_1_2.eprime b/tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_1_1_1_2.eprime deleted file mode 100644 index c4d66a6fb5..0000000000 --- a/tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_1_1_1_2.eprime +++ /dev/null @@ -1,14 +0,0 @@ -language ESSENCE' 1.0 - -find a_Occurrence: matrix indexed by [int(1..3)] of bool -find b_Occurrence: matrix indexed by [int(1..3)] of bool -find b_Explicit: matrix indexed by [int(1)] of int(1..3) -branching on [a_Occurrence, b_Explicit, b_Occurrence] -such that - and([a_Occurrence[i] -> i % 2 = 0 | i : int(1..3)]), - and([b_Occurrence[i] -> i % 2 = 0 | i : int(1..3)]), - 1 = sum([toInt(a_Occurrence[q1]) | q1 : int(1..3)]), - 1 = sum([toInt(b_Occurrence[q2]) | q2 : int(1..3)]), - b_Occurrence[b_Explicit[1]], - and([b_Occurrence[q7] -> b_Explicit[1] = q7 | q7 : int(1..3)]) - diff --git a/tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_1_1_2_1-solution000001.solution b/tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_1_1_2_1-solution000001.solution deleted file mode 100644 index 908faf0601..0000000000 --- a/tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_1_1_2_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be {2} -letting b be {2} diff --git a/tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_1_1_2_1.eprime b/tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_1_1_2_1.eprime deleted file mode 100644 index 2da2930acb..0000000000 --- a/tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_1_1_2_1.eprime +++ /dev/null @@ -1,14 +0,0 @@ -language ESSENCE' 1.0 - -find a_Occurrence: matrix indexed by [int(1..3)] of bool -find a_Explicit: matrix indexed by [int(1)] of int(1..3) -find b_Occurrence: matrix indexed by [int(1..3)] of bool -branching on [a_Explicit, a_Occurrence, b_Occurrence] -such that - and([a_Occurrence[i] -> i % 2 = 0 | i : int(1..3)]), - and([b_Occurrence[i] -> i % 2 = 0 | i : int(1..3)]), - 1 = sum([toInt(a_Occurrence[q1]) | q1 : int(1..3)]), - 1 = sum([toInt(b_Occurrence[q2]) | q2 : int(1..3)]), - a_Occurrence[a_Explicit[1]], - and([a_Occurrence[q7] -> a_Explicit[1] = q7 | q7 : int(1..3)]) - diff --git a/tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_1_1_2_2-solution000001.solution b/tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_1_1_2_2-solution000001.solution deleted file mode 100644 index 908faf0601..0000000000 --- a/tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_1_1_2_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be {2} -letting b be {2} diff --git a/tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_1_1_2_2.eprime b/tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_1_1_2_2.eprime deleted file mode 100644 index d0a08b30ee..0000000000 --- a/tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_1_1_2_2.eprime +++ /dev/null @@ -1,17 +0,0 @@ -language ESSENCE' 1.0 - -find a_Occurrence: matrix indexed by [int(1..3)] of bool -find a_Explicit: matrix indexed by [int(1)] of int(1..3) -find b_Occurrence: matrix indexed by [int(1..3)] of bool -find b_Explicit: matrix indexed by [int(1)] of int(1..3) -branching on [a_Explicit, a_Occurrence, b_Explicit, b_Occurrence] -such that - and([a_Occurrence[i] -> i % 2 = 0 | i : int(1..3)]), - and([b_Occurrence[i] -> i % 2 = 0 | i : int(1..3)]), - 1 = sum([toInt(a_Occurrence[q1]) | q1 : int(1..3)]), - 1 = sum([toInt(b_Occurrence[q2]) | q2 : int(1..3)]), - a_Occurrence[a_Explicit[1]], - and([a_Occurrence[q7] -> a_Explicit[1] = q7 | q7 : int(1..3)]), - b_Occurrence[b_Explicit[1]], - and([b_Occurrence[q14] -> b_Explicit[1] = q14 | q14 : int(1..3)]) - diff --git a/tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_1_2_1_1-solution000001.solution b/tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_1_2_1_1-solution000001.solution deleted file mode 100644 index 908faf0601..0000000000 --- a/tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_1_2_1_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be {2} -letting b be {2} diff --git a/tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_1_2_1_1.eprime b/tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_1_2_1_1.eprime deleted file mode 100644 index 201bf886f1..0000000000 --- a/tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_1_2_1_1.eprime +++ /dev/null @@ -1,14 +0,0 @@ -language ESSENCE' 1.0 - -find a_Occurrence: matrix indexed by [int(1..3)] of bool -find b_Explicit: matrix indexed by [int(1)] of int(1..3) -find b_Occurrence: matrix indexed by [int(1..3)] of bool -branching on [a_Occurrence, b_Occurrence, b_Explicit] -such that - and([a_Occurrence[i] -> i % 2 = 0 | i : int(1..3)]), - b_Explicit[1] % 2 = 0, - 1 = sum([toInt(a_Occurrence[q1]) | q1 : int(1..3)]), - 1 = sum([toInt(b_Occurrence[q4]) | q4 : int(1..3)]), - and([b_Occurrence[q5] -> b_Explicit[1] = q5 | q5 : int(1..3)]), - b_Occurrence[b_Explicit[1]] - diff --git a/tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_1_2_1_2-solution000001.solution b/tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_1_2_1_2-solution000001.solution deleted file mode 100644 index 908faf0601..0000000000 --- a/tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_1_2_1_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be {2} -letting b be {2} diff --git a/tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_1_2_1_2.eprime b/tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_1_2_1_2.eprime deleted file mode 100644 index af268d8049..0000000000 --- a/tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_1_2_1_2.eprime +++ /dev/null @@ -1,10 +0,0 @@ -language ESSENCE' 1.0 - -find a_Occurrence: matrix indexed by [int(1..3)] of bool -find b_Explicit: matrix indexed by [int(1)] of int(1..3) -branching on [a_Occurrence, b_Explicit] -such that - and([a_Occurrence[i] -> i % 2 = 0 | i : int(1..3)]), - b_Explicit[1] % 2 = 0, - 1 = sum([toInt(a_Occurrence[q1]) | q1 : int(1..3)]) - diff --git a/tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_1_2_2_1-solution000001.solution b/tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_1_2_2_1-solution000001.solution deleted file mode 100644 index 908faf0601..0000000000 --- a/tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_1_2_2_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be {2} -letting b be {2} diff --git a/tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_1_2_2_1.eprime b/tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_1_2_2_1.eprime deleted file mode 100644 index 8abeaf7bf5..0000000000 --- a/tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_1_2_2_1.eprime +++ /dev/null @@ -1,17 +0,0 @@ -language ESSENCE' 1.0 - -find a_Occurrence: matrix indexed by [int(1..3)] of bool -find a_Explicit: matrix indexed by [int(1)] of int(1..3) -find b_Explicit: matrix indexed by [int(1)] of int(1..3) -find b_Occurrence: matrix indexed by [int(1..3)] of bool -branching on [a_Explicit, a_Occurrence, b_Occurrence, b_Explicit] -such that - and([a_Occurrence[i] -> i % 2 = 0 | i : int(1..3)]), - b_Explicit[1] % 2 = 0, - 1 = sum([toInt(a_Occurrence[q1]) | q1 : int(1..3)]), - a_Occurrence[a_Explicit[1]], - and([a_Occurrence[q8] -> a_Explicit[1] = q8 | q8 : int(1..3)]), - 1 = sum([toInt(b_Occurrence[q11]) | q11 : int(1..3)]), - and([b_Occurrence[q12] -> b_Explicit[1] = q12 | q12 : int(1..3)]), - b_Occurrence[b_Explicit[1]] - diff --git a/tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_1_2_2_2-solution000001.solution b/tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_1_2_2_2-solution000001.solution deleted file mode 100644 index 908faf0601..0000000000 --- a/tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_1_2_2_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be {2} -letting b be {2} diff --git a/tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_1_2_2_2.eprime b/tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_1_2_2_2.eprime deleted file mode 100644 index a5c23cafce..0000000000 --- a/tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_1_2_2_2.eprime +++ /dev/null @@ -1,13 +0,0 @@ -language ESSENCE' 1.0 - -find a_Occurrence: matrix indexed by [int(1..3)] of bool -find a_Explicit: matrix indexed by [int(1)] of int(1..3) -find b_Explicit: matrix indexed by [int(1)] of int(1..3) -branching on [a_Explicit, a_Occurrence, b_Explicit] -such that - and([a_Occurrence[i] -> i % 2 = 0 | i : int(1..3)]), - b_Explicit[1] % 2 = 0, - 1 = sum([toInt(a_Occurrence[q1]) | q1 : int(1..3)]), - a_Occurrence[a_Explicit[1]], - and([a_Occurrence[q8] -> a_Explicit[1] = q8 | q8 : int(1..3)]) - diff --git a/tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_2_1_1_1-solution000001.solution b/tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_2_1_1_1-solution000001.solution deleted file mode 100644 index 908faf0601..0000000000 --- a/tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_2_1_1_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be {2} -letting b be {2} diff --git a/tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_2_1_1_1.eprime b/tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_2_1_1_1.eprime deleted file mode 100644 index 1bf246428a..0000000000 --- a/tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_2_1_1_1.eprime +++ /dev/null @@ -1,14 +0,0 @@ -language ESSENCE' 1.0 - -find a_Explicit: matrix indexed by [int(1)] of int(1..3) -find a_Occurrence: matrix indexed by [int(1..3)] of bool -find b_Occurrence: matrix indexed by [int(1..3)] of bool -branching on [a_Occurrence, a_Explicit, b_Occurrence] -such that - a_Explicit[1] % 2 = 0, - and([b_Occurrence[i] -> i % 2 = 0 | i : int(1..3)]), - 1 = sum([toInt(b_Occurrence[q3]) | q3 : int(1..3)]), - 1 = sum([toInt(a_Occurrence[q4]) | q4 : int(1..3)]), - and([a_Occurrence[q5] -> a_Explicit[1] = q5 | q5 : int(1..3)]), - a_Occurrence[a_Explicit[1]] - diff --git a/tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_2_1_1_2-solution000001.solution b/tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_2_1_1_2-solution000001.solution deleted file mode 100644 index 908faf0601..0000000000 --- a/tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_2_1_1_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be {2} -letting b be {2} diff --git a/tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_2_1_1_2.eprime b/tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_2_1_1_2.eprime deleted file mode 100644 index b15f403f90..0000000000 --- a/tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_2_1_1_2.eprime +++ /dev/null @@ -1,17 +0,0 @@ -language ESSENCE' 1.0 - -find a_Explicit: matrix indexed by [int(1)] of int(1..3) -find a_Occurrence: matrix indexed by [int(1..3)] of bool -find b_Occurrence: matrix indexed by [int(1..3)] of bool -find b_Explicit: matrix indexed by [int(1)] of int(1..3) -branching on [a_Occurrence, a_Explicit, b_Explicit, b_Occurrence] -such that - a_Explicit[1] % 2 = 0, - and([b_Occurrence[i] -> i % 2 = 0 | i : int(1..3)]), - 1 = sum([toInt(b_Occurrence[q3]) | q3 : int(1..3)]), - 1 = sum([toInt(a_Occurrence[q4]) | q4 : int(1..3)]), - and([a_Occurrence[q12] -> a_Explicit[1] = q12 | q12 : int(1..3)]), - a_Occurrence[a_Explicit[1]], - b_Occurrence[b_Explicit[1]], - and([b_Occurrence[q9] -> b_Explicit[1] = q9 | q9 : int(1..3)]) - diff --git a/tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_2_1_2_1-solution000001.solution b/tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_2_1_2_1-solution000001.solution deleted file mode 100644 index 908faf0601..0000000000 --- a/tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_2_1_2_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be {2} -letting b be {2} diff --git a/tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_2_1_2_1.eprime b/tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_2_1_2_1.eprime deleted file mode 100644 index 8205d32206..0000000000 --- a/tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_2_1_2_1.eprime +++ /dev/null @@ -1,10 +0,0 @@ -language ESSENCE' 1.0 - -find a_Explicit: matrix indexed by [int(1)] of int(1..3) -find b_Occurrence: matrix indexed by [int(1..3)] of bool -branching on [a_Explicit, b_Occurrence] -such that - a_Explicit[1] % 2 = 0, - and([b_Occurrence[i] -> i % 2 = 0 | i : int(1..3)]), - 1 = sum([toInt(b_Occurrence[q3]) | q3 : int(1..3)]) - diff --git a/tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_2_1_2_2-solution000001.solution b/tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_2_1_2_2-solution000001.solution deleted file mode 100644 index 908faf0601..0000000000 --- a/tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_2_1_2_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be {2} -letting b be {2} diff --git a/tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_2_1_2_2.eprime b/tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_2_1_2_2.eprime deleted file mode 100644 index 6672e139c6..0000000000 --- a/tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_2_1_2_2.eprime +++ /dev/null @@ -1,13 +0,0 @@ -language ESSENCE' 1.0 - -find a_Explicit: matrix indexed by [int(1)] of int(1..3) -find b_Occurrence: matrix indexed by [int(1..3)] of bool -find b_Explicit: matrix indexed by [int(1)] of int(1..3) -branching on [a_Explicit, b_Explicit, b_Occurrence] -such that - a_Explicit[1] % 2 = 0, - and([b_Occurrence[i] -> i % 2 = 0 | i : int(1..3)]), - 1 = sum([toInt(b_Occurrence[q3]) | q3 : int(1..3)]), - b_Occurrence[b_Explicit[1]], - and([b_Occurrence[q8] -> b_Explicit[1] = q8 | q8 : int(1..3)]) - diff --git a/tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_2_2_1_1-solution000001.solution b/tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_2_2_1_1-solution000001.solution deleted file mode 100644 index 908faf0601..0000000000 --- a/tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_2_2_1_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be {2} -letting b be {2} diff --git a/tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_2_2_1_1.eprime b/tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_2_2_1_1.eprime deleted file mode 100644 index c8a6dddfb6..0000000000 --- a/tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_2_2_1_1.eprime +++ /dev/null @@ -1,17 +0,0 @@ -language ESSENCE' 1.0 - -find a_Explicit: matrix indexed by [int(1)] of int(1..3) -find a_Occurrence: matrix indexed by [int(1..3)] of bool -find b_Explicit: matrix indexed by [int(1)] of int(1..3) -find b_Occurrence: matrix indexed by [int(1..3)] of bool -branching on [a_Occurrence, a_Explicit, b_Occurrence, b_Explicit] -such that - a_Explicit[1] % 2 = 0, - b_Explicit[1] % 2 = 0, - 1 = sum([toInt(a_Occurrence[q5]) | q5 : int(1..3)]), - and([a_Occurrence[q18] -> a_Explicit[1] = q18 | q18 : int(1..3)]), - a_Occurrence[a_Explicit[1]], - 1 = sum([toInt(b_Occurrence[q6]) | q6 : int(1..3)]), - and([b_Occurrence[q7] -> b_Explicit[1] = q7 | q7 : int(1..3)]), - b_Occurrence[b_Explicit[1]] - diff --git a/tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_2_2_1_2-solution000001.solution b/tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_2_2_1_2-solution000001.solution deleted file mode 100644 index 908faf0601..0000000000 --- a/tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_2_2_1_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be {2} -letting b be {2} diff --git a/tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_2_2_1_2.eprime b/tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_2_2_1_2.eprime deleted file mode 100644 index debcf16b90..0000000000 --- a/tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_2_2_1_2.eprime +++ /dev/null @@ -1,13 +0,0 @@ -language ESSENCE' 1.0 - -find a_Explicit: matrix indexed by [int(1)] of int(1..3) -find a_Occurrence: matrix indexed by [int(1..3)] of bool -find b_Explicit: matrix indexed by [int(1)] of int(1..3) -branching on [a_Occurrence, a_Explicit, b_Explicit] -such that - a_Explicit[1] % 2 = 0, - b_Explicit[1] % 2 = 0, - 1 = sum([toInt(a_Occurrence[q5]) | q5 : int(1..3)]), - and([a_Occurrence[q6] -> a_Explicit[1] = q6 | q6 : int(1..3)]), - a_Occurrence[a_Explicit[1]] - diff --git a/tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_2_2_2_1-solution000001.solution b/tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_2_2_2_1-solution000001.solution deleted file mode 100644 index 908faf0601..0000000000 --- a/tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_2_2_2_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be {2} -letting b be {2} diff --git a/tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_2_2_2_1.eprime b/tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_2_2_2_1.eprime deleted file mode 100644 index df3cd50506..0000000000 --- a/tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_2_2_2_1.eprime +++ /dev/null @@ -1,13 +0,0 @@ -language ESSENCE' 1.0 - -find a_Explicit: matrix indexed by [int(1)] of int(1..3) -find b_Explicit: matrix indexed by [int(1)] of int(1..3) -find b_Occurrence: matrix indexed by [int(1..3)] of bool -branching on [a_Explicit, b_Occurrence, b_Explicit] -such that - a_Explicit[1] % 2 = 0, - b_Explicit[1] % 2 = 0, - 1 = sum([toInt(b_Occurrence[q5]) | q5 : int(1..3)]), - and([b_Occurrence[q6] -> b_Explicit[1] = q6 | q6 : int(1..3)]), - b_Occurrence[b_Explicit[1]] - diff --git a/tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_2_2_2_2-solution000001.solution b/tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_2_2_2_2-solution000001.solution deleted file mode 100644 index 908faf0601..0000000000 --- a/tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_2_2_2_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be {2} -letting b be {2} diff --git a/tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_2_2_2_2.eprime b/tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_2_2_2_2.eprime deleted file mode 100644 index 8b067964c0..0000000000 --- a/tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_2_2_2_2.eprime +++ /dev/null @@ -1,9 +0,0 @@ -language ESSENCE' 1.0 - -find a_Explicit: matrix indexed by [int(1)] of int(1..3) -find b_Explicit: matrix indexed by [int(1)] of int(1..3) -branching on [a_Explicit, b_Explicit] -such that - a_Explicit[1] % 2 = 0, - b_Explicit[1] % 2 = 0 - diff --git a/tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_1_1_1_1-solution000001.solution b/tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_1_1_1_1-solution000001.solution deleted file mode 100644 index 908faf0601..0000000000 --- a/tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_1_1_1_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be {2} -letting b be {2} diff --git a/tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_1_1_1_1.eprime b/tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_1_1_1_1.eprime deleted file mode 100644 index 5af4dc2baa..0000000000 --- a/tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_1_1_1_1.eprime +++ /dev/null @@ -1,11 +0,0 @@ -language ESSENCE' 1.0 - -find a_Occurrence: matrix indexed by [int(1..3)] of bool -find b_Occurrence: matrix indexed by [int(1..3)] of bool -branching on [a_Occurrence, b_Occurrence] -such that - and([a_Occurrence[i] -> i % 2 = 0 | j1 : int(1..2), j2 : int(1..3), i : int(1..3), 2 = j2, 1 = j1]), - and([b_Occurrence[i] -> i % 2 = 0 | j1 : int(1..2), j2 : int(1..3), i : int(1..3), 3 = j2, 2 = j1]), - 1 = sum([toInt(a_Occurrence[q1]) | q1 : int(1..3)]), - 1 = sum([toInt(b_Occurrence[q2]) | q2 : int(1..3)]) - diff --git a/tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_1_1_1_2-solution000001.solution b/tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_1_1_1_2-solution000001.solution deleted file mode 100644 index 908faf0601..0000000000 --- a/tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_1_1_1_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be {2} -letting b be {2} diff --git a/tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_1_1_1_2.eprime b/tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_1_1_1_2.eprime deleted file mode 100644 index bf86f624b1..0000000000 --- a/tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_1_1_1_2.eprime +++ /dev/null @@ -1,14 +0,0 @@ -language ESSENCE' 1.0 - -find a_Occurrence: matrix indexed by [int(1..3)] of bool -find b_Occurrence: matrix indexed by [int(1..3)] of bool -find b_Explicit: matrix indexed by [int(1)] of int(1..3) -branching on [a_Occurrence, b_Explicit, b_Occurrence] -such that - and([a_Occurrence[i] -> i % 2 = 0 | j1 : int(1..2), j2 : int(1..3), i : int(1..3), 2 = j2, 1 = j1]), - and([b_Occurrence[i] -> i % 2 = 0 | j1 : int(1..2), j2 : int(1..3), i : int(1..3), 3 = j2, 2 = j1]), - 1 = sum([toInt(a_Occurrence[q1]) | q1 : int(1..3)]), - 1 = sum([toInt(b_Occurrence[q2]) | q2 : int(1..3)]), - b_Occurrence[b_Explicit[1]], - and([b_Occurrence[q7] -> b_Explicit[1] = q7 | q7 : int(1..3)]) - diff --git a/tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_1_1_2_1-solution000001.solution b/tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_1_1_2_1-solution000001.solution deleted file mode 100644 index 908faf0601..0000000000 --- a/tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_1_1_2_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be {2} -letting b be {2} diff --git a/tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_1_1_2_1.eprime b/tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_1_1_2_1.eprime deleted file mode 100644 index 174f682f97..0000000000 --- a/tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_1_1_2_1.eprime +++ /dev/null @@ -1,14 +0,0 @@ -language ESSENCE' 1.0 - -find a_Occurrence: matrix indexed by [int(1..3)] of bool -find a_Explicit: matrix indexed by [int(1)] of int(1..3) -find b_Occurrence: matrix indexed by [int(1..3)] of bool -branching on [a_Explicit, a_Occurrence, b_Occurrence] -such that - and([a_Occurrence[i] -> i % 2 = 0 | j1 : int(1..2), j2 : int(1..3), i : int(1..3), 2 = j2, 1 = j1]), - and([b_Occurrence[i] -> i % 2 = 0 | j1 : int(1..2), j2 : int(1..3), i : int(1..3), 3 = j2, 2 = j1]), - 1 = sum([toInt(a_Occurrence[q1]) | q1 : int(1..3)]), - 1 = sum([toInt(b_Occurrence[q2]) | q2 : int(1..3)]), - a_Occurrence[a_Explicit[1]], - and([a_Occurrence[q7] -> a_Explicit[1] = q7 | q7 : int(1..3)]) - diff --git a/tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_1_1_2_2-solution000001.solution b/tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_1_1_2_2-solution000001.solution deleted file mode 100644 index 908faf0601..0000000000 --- a/tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_1_1_2_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be {2} -letting b be {2} diff --git a/tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_1_1_2_2.eprime b/tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_1_1_2_2.eprime deleted file mode 100644 index ffecec8aba..0000000000 --- a/tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_1_1_2_2.eprime +++ /dev/null @@ -1,17 +0,0 @@ -language ESSENCE' 1.0 - -find a_Occurrence: matrix indexed by [int(1..3)] of bool -find a_Explicit: matrix indexed by [int(1)] of int(1..3) -find b_Occurrence: matrix indexed by [int(1..3)] of bool -find b_Explicit: matrix indexed by [int(1)] of int(1..3) -branching on [a_Explicit, a_Occurrence, b_Explicit, b_Occurrence] -such that - and([a_Occurrence[i] -> i % 2 = 0 | j1 : int(1..2), j2 : int(1..3), i : int(1..3), 2 = j2, 1 = j1]), - and([b_Occurrence[i] -> i % 2 = 0 | j1 : int(1..2), j2 : int(1..3), i : int(1..3), 3 = j2, 2 = j1]), - 1 = sum([toInt(a_Occurrence[q1]) | q1 : int(1..3)]), - 1 = sum([toInt(b_Occurrence[q2]) | q2 : int(1..3)]), - a_Occurrence[a_Explicit[1]], - and([a_Occurrence[q7] -> a_Explicit[1] = q7 | q7 : int(1..3)]), - b_Occurrence[b_Explicit[1]], - and([b_Occurrence[q14] -> b_Explicit[1] = q14 | q14 : int(1..3)]) - diff --git a/tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_1_2_1_1-solution000001.solution b/tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_1_2_1_1-solution000001.solution deleted file mode 100644 index 908faf0601..0000000000 --- a/tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_1_2_1_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be {2} -letting b be {2} diff --git a/tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_1_2_1_1.eprime b/tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_1_2_1_1.eprime deleted file mode 100644 index 9082843267..0000000000 --- a/tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_1_2_1_1.eprime +++ /dev/null @@ -1,14 +0,0 @@ -language ESSENCE' 1.0 - -find a_Occurrence: matrix indexed by [int(1..3)] of bool -find b_Explicit: matrix indexed by [int(1)] of int(1..3) -find b_Occurrence: matrix indexed by [int(1..3)] of bool -branching on [a_Occurrence, b_Occurrence, b_Explicit] -such that - and([a_Occurrence[i] -> i % 2 = 0 | j1 : int(1..2), j2 : int(1..3), i : int(1..3), 2 = j2, 1 = j1]), - and([b_Explicit[1] % 2 = 0 | j1 : int(1..2), j2 : int(1..3), 3 = j2, 2 = j1]), - 1 = sum([toInt(a_Occurrence[q1]) | q1 : int(1..3)]), - 1 = sum([toInt(b_Occurrence[q5]) | q5 : int(1..3)]), - and([b_Occurrence[q6] -> b_Explicit[1] = q6 | q6 : int(1..3)]), - b_Occurrence[b_Explicit[1]] - diff --git a/tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_1_2_1_2-solution000001.solution b/tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_1_2_1_2-solution000001.solution deleted file mode 100644 index 908faf0601..0000000000 --- a/tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_1_2_1_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be {2} -letting b be {2} diff --git a/tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_1_2_1_2.eprime b/tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_1_2_1_2.eprime deleted file mode 100644 index 7aa6b60a2b..0000000000 --- a/tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_1_2_1_2.eprime +++ /dev/null @@ -1,10 +0,0 @@ -language ESSENCE' 1.0 - -find a_Occurrence: matrix indexed by [int(1..3)] of bool -find b_Explicit: matrix indexed by [int(1)] of int(1..3) -branching on [a_Occurrence, b_Explicit] -such that - and([a_Occurrence[i] -> i % 2 = 0 | j1 : int(1..2), j2 : int(1..3), i : int(1..3), 2 = j2, 1 = j1]), - and([b_Explicit[1] % 2 = 0 | j1 : int(1..2), j2 : int(1..3), 3 = j2, 2 = j1]), - 1 = sum([toInt(a_Occurrence[q1]) | q1 : int(1..3)]) - diff --git a/tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_1_2_2_1-solution000001.solution b/tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_1_2_2_1-solution000001.solution deleted file mode 100644 index 908faf0601..0000000000 --- a/tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_1_2_2_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be {2} -letting b be {2} diff --git a/tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_1_2_2_1.eprime b/tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_1_2_2_1.eprime deleted file mode 100644 index b75f0d4e6f..0000000000 --- a/tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_1_2_2_1.eprime +++ /dev/null @@ -1,17 +0,0 @@ -language ESSENCE' 1.0 - -find a_Occurrence: matrix indexed by [int(1..3)] of bool -find a_Explicit: matrix indexed by [int(1)] of int(1..3) -find b_Explicit: matrix indexed by [int(1)] of int(1..3) -find b_Occurrence: matrix indexed by [int(1..3)] of bool -branching on [a_Explicit, a_Occurrence, b_Occurrence, b_Explicit] -such that - and([a_Occurrence[i] -> i % 2 = 0 | j1 : int(1..2), j2 : int(1..3), i : int(1..3), 2 = j2, 1 = j1]), - and([b_Explicit[1] % 2 = 0 | j1 : int(1..2), j2 : int(1..3), 3 = j2, 2 = j1]), - 1 = sum([toInt(a_Occurrence[q1]) | q1 : int(1..3)]), - a_Occurrence[a_Explicit[1]], - and([a_Occurrence[q9] -> a_Explicit[1] = q9 | q9 : int(1..3)]), - 1 = sum([toInt(b_Occurrence[q12]) | q12 : int(1..3)]), - and([b_Occurrence[q13] -> b_Explicit[1] = q13 | q13 : int(1..3)]), - b_Occurrence[b_Explicit[1]] - diff --git a/tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_1_2_2_2-solution000001.solution b/tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_1_2_2_2-solution000001.solution deleted file mode 100644 index 908faf0601..0000000000 --- a/tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_1_2_2_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be {2} -letting b be {2} diff --git a/tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_1_2_2_2.eprime b/tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_1_2_2_2.eprime deleted file mode 100644 index 1a22390b4d..0000000000 --- a/tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_1_2_2_2.eprime +++ /dev/null @@ -1,13 +0,0 @@ -language ESSENCE' 1.0 - -find a_Occurrence: matrix indexed by [int(1..3)] of bool -find a_Explicit: matrix indexed by [int(1)] of int(1..3) -find b_Explicit: matrix indexed by [int(1)] of int(1..3) -branching on [a_Explicit, a_Occurrence, b_Explicit] -such that - and([a_Occurrence[i] -> i % 2 = 0 | j1 : int(1..2), j2 : int(1..3), i : int(1..3), 2 = j2, 1 = j1]), - and([b_Explicit[1] % 2 = 0 | j1 : int(1..2), j2 : int(1..3), 3 = j2, 2 = j1]), - 1 = sum([toInt(a_Occurrence[q1]) | q1 : int(1..3)]), - a_Occurrence[a_Explicit[1]], - and([a_Occurrence[q9] -> a_Explicit[1] = q9 | q9 : int(1..3)]) - diff --git a/tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_2_1_1_1-solution000001.solution b/tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_2_1_1_1-solution000001.solution deleted file mode 100644 index 908faf0601..0000000000 --- a/tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_2_1_1_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be {2} -letting b be {2} diff --git a/tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_2_1_1_1.eprime b/tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_2_1_1_1.eprime deleted file mode 100644 index 58a7d829b5..0000000000 --- a/tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_2_1_1_1.eprime +++ /dev/null @@ -1,14 +0,0 @@ -language ESSENCE' 1.0 - -find a_Explicit: matrix indexed by [int(1)] of int(1..3) -find a_Occurrence: matrix indexed by [int(1..3)] of bool -find b_Occurrence: matrix indexed by [int(1..3)] of bool -branching on [a_Occurrence, a_Explicit, b_Occurrence] -such that - and([a_Explicit[1] % 2 = 0 | j1 : int(1..2), j2 : int(1..3), 2 = j2, 1 = j1]), - and([b_Occurrence[i] -> i % 2 = 0 | j1 : int(1..2), j2 : int(1..3), i : int(1..3), 3 = j2, 2 = j1]), - 1 = sum([toInt(b_Occurrence[q3]) | q3 : int(1..3)]), - 1 = sum([toInt(a_Occurrence[q5]) | q5 : int(1..3)]), - and([a_Occurrence[q6] -> a_Explicit[1] = q6 | q6 : int(1..3)]), - a_Occurrence[a_Explicit[1]] - diff --git a/tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_2_1_1_2-solution000001.solution b/tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_2_1_1_2-solution000001.solution deleted file mode 100644 index 908faf0601..0000000000 --- a/tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_2_1_1_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be {2} -letting b be {2} diff --git a/tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_2_1_1_2.eprime b/tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_2_1_1_2.eprime deleted file mode 100644 index 769a749476..0000000000 --- a/tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_2_1_1_2.eprime +++ /dev/null @@ -1,17 +0,0 @@ -language ESSENCE' 1.0 - -find a_Explicit: matrix indexed by [int(1)] of int(1..3) -find a_Occurrence: matrix indexed by [int(1..3)] of bool -find b_Occurrence: matrix indexed by [int(1..3)] of bool -find b_Explicit: matrix indexed by [int(1)] of int(1..3) -branching on [a_Occurrence, a_Explicit, b_Explicit, b_Occurrence] -such that - and([a_Explicit[1] % 2 = 0 | j1 : int(1..2), j2 : int(1..3), 2 = j2, 1 = j1]), - and([b_Occurrence[i] -> i % 2 = 0 | j1 : int(1..2), j2 : int(1..3), i : int(1..3), 3 = j2, 2 = j1]), - 1 = sum([toInt(b_Occurrence[q3]) | q3 : int(1..3)]), - 1 = sum([toInt(a_Occurrence[q5]) | q5 : int(1..3)]), - and([a_Occurrence[q13] -> a_Explicit[1] = q13 | q13 : int(1..3)]), - a_Occurrence[a_Explicit[1]], - b_Occurrence[b_Explicit[1]], - and([b_Occurrence[q10] -> b_Explicit[1] = q10 | q10 : int(1..3)]) - diff --git a/tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_2_1_2_1-solution000001.solution b/tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_2_1_2_1-solution000001.solution deleted file mode 100644 index 908faf0601..0000000000 --- a/tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_2_1_2_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be {2} -letting b be {2} diff --git a/tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_2_1_2_1.eprime b/tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_2_1_2_1.eprime deleted file mode 100644 index f9a5c3e238..0000000000 --- a/tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_2_1_2_1.eprime +++ /dev/null @@ -1,10 +0,0 @@ -language ESSENCE' 1.0 - -find a_Explicit: matrix indexed by [int(1)] of int(1..3) -find b_Occurrence: matrix indexed by [int(1..3)] of bool -branching on [a_Explicit, b_Occurrence] -such that - and([a_Explicit[1] % 2 = 0 | j1 : int(1..2), j2 : int(1..3), 2 = j2, 1 = j1]), - and([b_Occurrence[i] -> i % 2 = 0 | j1 : int(1..2), j2 : int(1..3), i : int(1..3), 3 = j2, 2 = j1]), - 1 = sum([toInt(b_Occurrence[q3]) | q3 : int(1..3)]) - diff --git a/tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_2_1_2_2-solution000001.solution b/tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_2_1_2_2-solution000001.solution deleted file mode 100644 index 908faf0601..0000000000 --- a/tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_2_1_2_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be {2} -letting b be {2} diff --git a/tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_2_1_2_2.eprime b/tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_2_1_2_2.eprime deleted file mode 100644 index cc00b4b51d..0000000000 --- a/tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_2_1_2_2.eprime +++ /dev/null @@ -1,13 +0,0 @@ -language ESSENCE' 1.0 - -find a_Explicit: matrix indexed by [int(1)] of int(1..3) -find b_Occurrence: matrix indexed by [int(1..3)] of bool -find b_Explicit: matrix indexed by [int(1)] of int(1..3) -branching on [a_Explicit, b_Explicit, b_Occurrence] -such that - and([a_Explicit[1] % 2 = 0 | j1 : int(1..2), j2 : int(1..3), 2 = j2, 1 = j1]), - and([b_Occurrence[i] -> i % 2 = 0 | j1 : int(1..2), j2 : int(1..3), i : int(1..3), 3 = j2, 2 = j1]), - 1 = sum([toInt(b_Occurrence[q3]) | q3 : int(1..3)]), - b_Occurrence[b_Explicit[1]], - and([b_Occurrence[q9] -> b_Explicit[1] = q9 | q9 : int(1..3)]) - diff --git a/tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_2_2_1_1-solution000001.solution b/tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_2_2_1_1-solution000001.solution deleted file mode 100644 index 908faf0601..0000000000 --- a/tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_2_2_1_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be {2} -letting b be {2} diff --git a/tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_2_2_1_1.eprime b/tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_2_2_1_1.eprime deleted file mode 100644 index 60ff0b33a7..0000000000 --- a/tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_2_2_1_1.eprime +++ /dev/null @@ -1,17 +0,0 @@ -language ESSENCE' 1.0 - -find a_Explicit: matrix indexed by [int(1)] of int(1..3) -find a_Occurrence: matrix indexed by [int(1..3)] of bool -find b_Explicit: matrix indexed by [int(1)] of int(1..3) -find b_Occurrence: matrix indexed by [int(1..3)] of bool -branching on [a_Occurrence, a_Explicit, b_Occurrence, b_Explicit] -such that - and([a_Explicit[1] % 2 = 0 | j1 : int(1..2), j2 : int(1..3), 2 = j2, 1 = j1]), - and([b_Explicit[1] % 2 = 0 | j1 : int(1..2), j2 : int(1..3), 3 = j2, 2 = j1]), - 1 = sum([toInt(a_Occurrence[q7]) | q7 : int(1..3)]), - and([a_Occurrence[q14] -> a_Explicit[1] = q14 | q14 : int(1..3)]), - a_Occurrence[a_Explicit[1]], - 1 = sum([toInt(b_Occurrence[q8]) | q8 : int(1..3)]), - and([b_Occurrence[q9] -> b_Explicit[1] = q9 | q9 : int(1..3)]), - b_Occurrence[b_Explicit[1]] - diff --git a/tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_2_2_1_2-solution000001.solution b/tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_2_2_1_2-solution000001.solution deleted file mode 100644 index 908faf0601..0000000000 --- a/tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_2_2_1_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be {2} -letting b be {2} diff --git a/tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_2_2_1_2.eprime b/tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_2_2_1_2.eprime deleted file mode 100644 index 1a53a1b4a3..0000000000 --- a/tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_2_2_1_2.eprime +++ /dev/null @@ -1,13 +0,0 @@ -language ESSENCE' 1.0 - -find a_Explicit: matrix indexed by [int(1)] of int(1..3) -find a_Occurrence: matrix indexed by [int(1..3)] of bool -find b_Explicit: matrix indexed by [int(1)] of int(1..3) -branching on [a_Occurrence, a_Explicit, b_Explicit] -such that - and([a_Explicit[1] % 2 = 0 | j1 : int(1..2), j2 : int(1..3), 2 = j2, 1 = j1]), - and([b_Explicit[1] % 2 = 0 | j1 : int(1..2), j2 : int(1..3), 3 = j2, 2 = j1]), - 1 = sum([toInt(a_Occurrence[q7]) | q7 : int(1..3)]), - and([a_Occurrence[q8] -> a_Explicit[1] = q8 | q8 : int(1..3)]), - a_Occurrence[a_Explicit[1]] - diff --git a/tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_2_2_2_1-solution000001.solution b/tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_2_2_2_1-solution000001.solution deleted file mode 100644 index 908faf0601..0000000000 --- a/tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_2_2_2_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be {2} -letting b be {2} diff --git a/tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_2_2_2_1.eprime b/tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_2_2_2_1.eprime deleted file mode 100644 index eb8d5cbf5a..0000000000 --- a/tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_2_2_2_1.eprime +++ /dev/null @@ -1,13 +0,0 @@ -language ESSENCE' 1.0 - -find a_Explicit: matrix indexed by [int(1)] of int(1..3) -find b_Explicit: matrix indexed by [int(1)] of int(1..3) -find b_Occurrence: matrix indexed by [int(1..3)] of bool -branching on [a_Explicit, b_Occurrence, b_Explicit] -such that - and([a_Explicit[1] % 2 = 0 | j1 : int(1..2), j2 : int(1..3), 2 = j2, 1 = j1]), - and([b_Explicit[1] % 2 = 0 | j1 : int(1..2), j2 : int(1..3), 3 = j2, 2 = j1]), - 1 = sum([toInt(b_Occurrence[q7]) | q7 : int(1..3)]), - and([b_Occurrence[q8] -> b_Explicit[1] = q8 | q8 : int(1..3)]), - b_Occurrence[b_Explicit[1]] - diff --git a/tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_2_2_2_2-solution000001.solution b/tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_2_2_2_2-solution000001.solution deleted file mode 100644 index 908faf0601..0000000000 --- a/tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_2_2_2_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be {2} -letting b be {2} diff --git a/tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_2_2_2_2.eprime b/tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_2_2_2_2.eprime deleted file mode 100644 index 09fc19740e..0000000000 --- a/tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_2_2_2_2.eprime +++ /dev/null @@ -1,9 +0,0 @@ -language ESSENCE' 1.0 - -find a_Explicit: matrix indexed by [int(1)] of int(1..3) -find b_Explicit: matrix indexed by [int(1)] of int(1..3) -branching on [a_Explicit, b_Explicit] -such that - and([a_Explicit[1] % 2 = 0 | j1 : int(1..2), j2 : int(1..3), 2 = j2, 1 = j1]), - and([b_Explicit[1] % 2 = 0 | j1 : int(1..2), j2 : int(1..3), 3 = j2, 2 = j1]) - diff --git a/tests/exhaustive/basic/mset01_param/expected/model_1_1-param1-solution000001.solution b/tests/exhaustive/basic/mset01_param/expected/model_1_1-param1-solution000001.solution deleted file mode 100644 index 3fc3fafe52..0000000000 --- a/tests/exhaustive/basic/mset01_param/expected/model_1_1-param1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be mset() diff --git a/tests/exhaustive/basic/mset01_param/expected/model_1_1-param1.eprime-param b/tests/exhaustive/basic/mset01_param/expected/model_1_1-param1.eprime-param deleted file mode 100644 index 62e729a0fe..0000000000 --- a/tests/exhaustive/basic/mset01_param/expected/model_1_1-param1.eprime-param +++ /dev/null @@ -1,5 +0,0 @@ -language ESSENCE' 1.0 - -letting g_ExplicitWithFlags_Flags be ([] : `matrix indexed by [int()] of bool`) -letting g_ExplicitWithFlags_Values be ([] : `matrix indexed by [int()] of int`) -letting fin1 be 0 diff --git a/tests/exhaustive/basic/mset01_param/expected/model_1_1-param4-solution000001.solution b/tests/exhaustive/basic/mset01_param/expected/model_1_1-param4-solution000001.solution deleted file mode 100644 index 43c40d1c6b..0000000000 --- a/tests/exhaustive/basic/mset01_param/expected/model_1_1-param4-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be mset(1, 2) diff --git a/tests/exhaustive/basic/mset01_param/expected/model_1_1-param4.eprime-param b/tests/exhaustive/basic/mset01_param/expected/model_1_1-param4.eprime-param deleted file mode 100644 index f1da505f58..0000000000 --- a/tests/exhaustive/basic/mset01_param/expected/model_1_1-param4.eprime-param +++ /dev/null @@ -1,5 +0,0 @@ -language ESSENCE' 1.0 - -letting g_ExplicitWithFlags_Flags be [1, 1; int(1..2)] -letting g_ExplicitWithFlags_Values be [1, 2; int(1..2)] -letting fin1 be 2 diff --git a/tests/exhaustive/basic/mset01_param/expected/model_1_1-param7-solution000001.solution b/tests/exhaustive/basic/mset01_param/expected/model_1_1-param7-solution000001.solution deleted file mode 100644 index 06be1e3b32..0000000000 --- a/tests/exhaustive/basic/mset01_param/expected/model_1_1-param7-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be mset(2, 2) diff --git a/tests/exhaustive/basic/mset01_param/expected/model_1_1-param7.eprime-param b/tests/exhaustive/basic/mset01_param/expected/model_1_1-param7.eprime-param deleted file mode 100644 index 468cfba281..0000000000 --- a/tests/exhaustive/basic/mset01_param/expected/model_1_1-param7.eprime-param +++ /dev/null @@ -1,5 +0,0 @@ -language ESSENCE' 1.0 - -letting g_ExplicitWithFlags_Flags be [2, 0; int(1..2)] -letting g_ExplicitWithFlags_Values be [2, 1; int(1..2)] -letting fin1 be 2 diff --git a/tests/exhaustive/basic/mset01_param/expected/model_1_1.eprime b/tests/exhaustive/basic/mset01_param/expected/model_1_1.eprime deleted file mode 100644 index 62c9a5d2b2..0000000000 --- a/tests/exhaustive/basic/mset01_param/expected/model_1_1.eprime +++ /dev/null @@ -1,31 +0,0 @@ -language ESSENCE' 1.0 - -given fin1: int -given g_ExplicitWithFlags_Flags: matrix indexed by [int(1..fin1)] of int(0..2) -given g_ExplicitWithFlags_Values: matrix indexed by [int(1..fin1)] of int(1..2) -find x_ExplicitWithFlags_Flags: matrix indexed by [int(1..4)] of int(0..2) -find x_ExplicitWithFlags_Values: matrix indexed by [int(1..4)] of int(1..2) -branching on [x_ExplicitWithFlags_Flags, x_ExplicitWithFlags_Values] -such that - and([sum([g_ExplicitWithFlags_Flags[q9] - | q9 : int(1..fin1), g_ExplicitWithFlags_Values[q9] = g_ExplicitWithFlags_Values[q8]]) - = - sum([toInt(x_ExplicitWithFlags_Values[q10] = g_ExplicitWithFlags_Values[q8]) * - catchUndef(x_ExplicitWithFlags_Flags[q10], 0) - | q10 : int(1..4)]) - | q8 : int(1..fin1), g_ExplicitWithFlags_Flags[q8] > 0]), - and([x_ExplicitWithFlags_Flags[q11] > 0 -> - sum([toInt(g_ExplicitWithFlags_Values[q12] = x_ExplicitWithFlags_Values[q11]) * - catchUndef(g_ExplicitWithFlags_Flags[q12], 0) - | q12 : int(1..fin1)]) - = - sum([toInt(x_ExplicitWithFlags_Values[q13] = x_ExplicitWithFlags_Values[q11]) * - catchUndef(x_ExplicitWithFlags_Flags[q13], 0) - | q13 : int(1..4)]) - | q11 : int(1..4)]), - and([x_ExplicitWithFlags_Flags[q1 + 1] > 0 -> x_ExplicitWithFlags_Values[q1] < x_ExplicitWithFlags_Values[q1 + 1] - | q1 : int(1..3)]), - and([x_ExplicitWithFlags_Flags[q2] = 0 -> x_ExplicitWithFlags_Values[q2] = 1 | q2 : int(1..4)]), - and([x_ExplicitWithFlags_Flags[q3 + 1] > 0 -> x_ExplicitWithFlags_Flags[q3] > 0 | q3 : int(1..3)]), - sum([x_ExplicitWithFlags_Flags[q5] | q5 : int(1..4)]) <= 4 - diff --git a/tests/exhaustive/basic/mset01_param/expected/model_1_2-param1-solution000001.solution b/tests/exhaustive/basic/mset01_param/expected/model_1_2-param1-solution000001.solution deleted file mode 100644 index 3fc3fafe52..0000000000 --- a/tests/exhaustive/basic/mset01_param/expected/model_1_2-param1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be mset() diff --git a/tests/exhaustive/basic/mset01_param/expected/model_1_2-param1.eprime-param b/tests/exhaustive/basic/mset01_param/expected/model_1_2-param1.eprime-param deleted file mode 100644 index 62e729a0fe..0000000000 --- a/tests/exhaustive/basic/mset01_param/expected/model_1_2-param1.eprime-param +++ /dev/null @@ -1,5 +0,0 @@ -language ESSENCE' 1.0 - -letting g_ExplicitWithFlags_Flags be ([] : `matrix indexed by [int()] of bool`) -letting g_ExplicitWithFlags_Values be ([] : `matrix indexed by [int()] of int`) -letting fin1 be 0 diff --git a/tests/exhaustive/basic/mset01_param/expected/model_1_2-param4-solution000001.solution b/tests/exhaustive/basic/mset01_param/expected/model_1_2-param4-solution000001.solution deleted file mode 100644 index 43c40d1c6b..0000000000 --- a/tests/exhaustive/basic/mset01_param/expected/model_1_2-param4-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be mset(1, 2) diff --git a/tests/exhaustive/basic/mset01_param/expected/model_1_2-param4.eprime-param b/tests/exhaustive/basic/mset01_param/expected/model_1_2-param4.eprime-param deleted file mode 100644 index f1da505f58..0000000000 --- a/tests/exhaustive/basic/mset01_param/expected/model_1_2-param4.eprime-param +++ /dev/null @@ -1,5 +0,0 @@ -language ESSENCE' 1.0 - -letting g_ExplicitWithFlags_Flags be [1, 1; int(1..2)] -letting g_ExplicitWithFlags_Values be [1, 2; int(1..2)] -letting fin1 be 2 diff --git a/tests/exhaustive/basic/mset01_param/expected/model_1_2-param7-solution000001.solution b/tests/exhaustive/basic/mset01_param/expected/model_1_2-param7-solution000001.solution deleted file mode 100644 index 06be1e3b32..0000000000 --- a/tests/exhaustive/basic/mset01_param/expected/model_1_2-param7-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be mset(2, 2) diff --git a/tests/exhaustive/basic/mset01_param/expected/model_1_2-param7.eprime-param b/tests/exhaustive/basic/mset01_param/expected/model_1_2-param7.eprime-param deleted file mode 100644 index 468cfba281..0000000000 --- a/tests/exhaustive/basic/mset01_param/expected/model_1_2-param7.eprime-param +++ /dev/null @@ -1,5 +0,0 @@ -language ESSENCE' 1.0 - -letting g_ExplicitWithFlags_Flags be [2, 0; int(1..2)] -letting g_ExplicitWithFlags_Values be [2, 1; int(1..2)] -letting fin1 be 2 diff --git a/tests/exhaustive/basic/mset01_param/expected/model_1_2.eprime b/tests/exhaustive/basic/mset01_param/expected/model_1_2.eprime deleted file mode 100644 index 9f99f600b3..0000000000 --- a/tests/exhaustive/basic/mset01_param/expected/model_1_2.eprime +++ /dev/null @@ -1,64 +0,0 @@ -language ESSENCE' 1.0 - -given fin1: int -given g_ExplicitWithFlags_Flags: matrix indexed by [int(1..fin1)] of int(0..2) -given g_ExplicitWithFlags_Values: matrix indexed by [int(1..fin1)] of int(1..2) -find x_ExplicitWithFlags_Flags: matrix indexed by [int(1..4)] of int(0..2) -find x_ExplicitWithFlags_Values: matrix indexed by [int(1..4)] of int(1..2) -find x_ExplicitWithRepetition_Flag: int(0..4) -find x_ExplicitWithRepetition_Values: matrix indexed by [int(1..4)] of int(1..2) -branching on - [x_ExplicitWithRepetition_Flag, x_ExplicitWithRepetition_Values, x_ExplicitWithFlags_Flags, - x_ExplicitWithFlags_Values] -such that - and([sum([g_ExplicitWithFlags_Flags[q25] - | q25 : int(1..fin1), g_ExplicitWithFlags_Values[q25] = g_ExplicitWithFlags_Values[q24]]) - = - sum([toInt(x_ExplicitWithFlags_Values[q26] = g_ExplicitWithFlags_Values[q24]) * - catchUndef(x_ExplicitWithFlags_Flags[q26], 0) - | q26 : int(1..4)]) - | q24 : int(1..fin1), g_ExplicitWithFlags_Flags[q24] > 0]), - and([x_ExplicitWithFlags_Flags[q27] > 0 -> - sum([toInt(g_ExplicitWithFlags_Values[q28] = x_ExplicitWithFlags_Values[q27]) * - catchUndef(g_ExplicitWithFlags_Flags[q28], 0) - | q28 : int(1..fin1)]) - = - sum([toInt(x_ExplicitWithFlags_Values[q29] = x_ExplicitWithFlags_Values[q27]) * - catchUndef(x_ExplicitWithFlags_Flags[q29], 0) - | q29 : int(1..4)]) - | q27 : int(1..4)]), - and([x_ExplicitWithFlags_Flags[q1 + 1] > 0 -> x_ExplicitWithFlags_Values[q1] < x_ExplicitWithFlags_Values[q1 + 1] - | q1 : int(1..3)]), - and([x_ExplicitWithFlags_Flags[q2] = 0 -> x_ExplicitWithFlags_Values[q2] = 1 | q2 : int(1..4)]), - and([x_ExplicitWithFlags_Flags[q3 + 1] > 0 -> x_ExplicitWithFlags_Flags[q3] > 0 | q3 : int(1..3)]), - sum([x_ExplicitWithFlags_Flags[q5] | q5 : int(1..4)]) <= 4, - and([q7 + 1 <= x_ExplicitWithRepetition_Flag -> - x_ExplicitWithRepetition_Values[q7] <= x_ExplicitWithRepetition_Values[q7 + 1] - | q7 : int(1..3)]), - and([q8 > x_ExplicitWithRepetition_Flag -> x_ExplicitWithRepetition_Values[q8] = 1 | q8 : int(1..4)]), - and([q10 <= x_ExplicitWithRepetition_Flag -> - sum([toInt(q13 <= x_ExplicitWithRepetition_Flag) * - catchUndef(toInt(x_ExplicitWithRepetition_Values[q13] = x_ExplicitWithRepetition_Values[q10]), 0) - | q13 : int(1..4)]) - <= 2 - | q10 : int(1..4)]), - x_ExplicitWithRepetition_Flag <= 4, - and([q15 <= x_ExplicitWithRepetition_Flag -> - sum([toInt(q18 <= x_ExplicitWithRepetition_Flag) * - catchUndef(toInt(x_ExplicitWithRepetition_Values[q18] = x_ExplicitWithRepetition_Values[q15]), 0) - | q18 : int(1..4)]) - = - sum([toInt(x_ExplicitWithFlags_Values[q16] = x_ExplicitWithRepetition_Values[q15]) * - catchUndef(x_ExplicitWithFlags_Flags[q16], 0) - | q16 : int(1..4)]) - | q15 : int(1..4)]), - and([x_ExplicitWithFlags_Flags[q19] > 0 -> - sum([toInt(q22 <= x_ExplicitWithRepetition_Flag) * - catchUndef(toInt(x_ExplicitWithRepetition_Values[q22] = x_ExplicitWithFlags_Values[q19]), 0) - | q22 : int(1..4)]) - = - sum([toInt(x_ExplicitWithFlags_Values[q20] = x_ExplicitWithFlags_Values[q19]) * - catchUndef(x_ExplicitWithFlags_Flags[q20], 0) - | q20 : int(1..4)]) - | q19 : int(1..4)]) - diff --git a/tests/exhaustive/basic/mset01_param/expected/model_1_3-param1-solution000001.solution b/tests/exhaustive/basic/mset01_param/expected/model_1_3-param1-solution000001.solution deleted file mode 100644 index 3fc3fafe52..0000000000 --- a/tests/exhaustive/basic/mset01_param/expected/model_1_3-param1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be mset() diff --git a/tests/exhaustive/basic/mset01_param/expected/model_1_3-param1.eprime-param b/tests/exhaustive/basic/mset01_param/expected/model_1_3-param1.eprime-param deleted file mode 100644 index 62e729a0fe..0000000000 --- a/tests/exhaustive/basic/mset01_param/expected/model_1_3-param1.eprime-param +++ /dev/null @@ -1,5 +0,0 @@ -language ESSENCE' 1.0 - -letting g_ExplicitWithFlags_Flags be ([] : `matrix indexed by [int()] of bool`) -letting g_ExplicitWithFlags_Values be ([] : `matrix indexed by [int()] of int`) -letting fin1 be 0 diff --git a/tests/exhaustive/basic/mset01_param/expected/model_1_3-param4-solution000001.solution b/tests/exhaustive/basic/mset01_param/expected/model_1_3-param4-solution000001.solution deleted file mode 100644 index 43c40d1c6b..0000000000 --- a/tests/exhaustive/basic/mset01_param/expected/model_1_3-param4-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be mset(1, 2) diff --git a/tests/exhaustive/basic/mset01_param/expected/model_1_3-param4.eprime-param b/tests/exhaustive/basic/mset01_param/expected/model_1_3-param4.eprime-param deleted file mode 100644 index f1da505f58..0000000000 --- a/tests/exhaustive/basic/mset01_param/expected/model_1_3-param4.eprime-param +++ /dev/null @@ -1,5 +0,0 @@ -language ESSENCE' 1.0 - -letting g_ExplicitWithFlags_Flags be [1, 1; int(1..2)] -letting g_ExplicitWithFlags_Values be [1, 2; int(1..2)] -letting fin1 be 2 diff --git a/tests/exhaustive/basic/mset01_param/expected/model_1_3-param7-solution000001.solution b/tests/exhaustive/basic/mset01_param/expected/model_1_3-param7-solution000001.solution deleted file mode 100644 index 06be1e3b32..0000000000 --- a/tests/exhaustive/basic/mset01_param/expected/model_1_3-param7-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be mset(2, 2) diff --git a/tests/exhaustive/basic/mset01_param/expected/model_1_3-param7.eprime-param b/tests/exhaustive/basic/mset01_param/expected/model_1_3-param7.eprime-param deleted file mode 100644 index 468cfba281..0000000000 --- a/tests/exhaustive/basic/mset01_param/expected/model_1_3-param7.eprime-param +++ /dev/null @@ -1,5 +0,0 @@ -language ESSENCE' 1.0 - -letting g_ExplicitWithFlags_Flags be [2, 0; int(1..2)] -letting g_ExplicitWithFlags_Values be [2, 1; int(1..2)] -letting fin1 be 2 diff --git a/tests/exhaustive/basic/mset01_param/expected/model_1_3.eprime b/tests/exhaustive/basic/mset01_param/expected/model_1_3.eprime deleted file mode 100644 index 013bcfe9be..0000000000 --- a/tests/exhaustive/basic/mset01_param/expected/model_1_3.eprime +++ /dev/null @@ -1,44 +0,0 @@ -language ESSENCE' 1.0 - -given fin1: int -given g_ExplicitWithFlags_Flags: matrix indexed by [int(1..fin1)] of int(0..2) -given g_ExplicitWithFlags_Values: matrix indexed by [int(1..fin1)] of int(1..2) -find x_ExplicitWithFlags_Flags: matrix indexed by [int(1..4)] of int(0..2) -find x_ExplicitWithFlags_Values: matrix indexed by [int(1..4)] of int(1..2) -find x_MOccurrence: matrix indexed by [int(1..2)] of int(0..2) -branching on [x_MOccurrence, x_ExplicitWithFlags_Flags, x_ExplicitWithFlags_Values] -such that - and([sum([g_ExplicitWithFlags_Flags[q15] - | q15 : int(1..fin1), g_ExplicitWithFlags_Values[q15] = g_ExplicitWithFlags_Values[q14]]) - = - sum([toInt(x_ExplicitWithFlags_Values[q16] = g_ExplicitWithFlags_Values[q14]) * - catchUndef(x_ExplicitWithFlags_Flags[q16], 0) - | q16 : int(1..4)]) - | q14 : int(1..fin1), g_ExplicitWithFlags_Flags[q14] > 0]), - and([x_ExplicitWithFlags_Flags[q17] > 0 -> - sum([toInt(g_ExplicitWithFlags_Values[q18] = x_ExplicitWithFlags_Values[q17]) * - catchUndef(g_ExplicitWithFlags_Flags[q18], 0) - | q18 : int(1..fin1)]) - = - sum([toInt(x_ExplicitWithFlags_Values[q19] = x_ExplicitWithFlags_Values[q17]) * - catchUndef(x_ExplicitWithFlags_Flags[q19], 0) - | q19 : int(1..4)]) - | q17 : int(1..4)]), - and([x_ExplicitWithFlags_Flags[q1 + 1] > 0 -> x_ExplicitWithFlags_Values[q1] < x_ExplicitWithFlags_Values[q1 + 1] - | q1 : int(1..3)]), - and([x_ExplicitWithFlags_Flags[q2] = 0 -> x_ExplicitWithFlags_Values[q2] = 1 | q2 : int(1..4)]), - and([x_ExplicitWithFlags_Flags[q3 + 1] > 0 -> x_ExplicitWithFlags_Flags[q3] > 0 | q3 : int(1..3)]), - sum([x_ExplicitWithFlags_Flags[q5] | q5 : int(1..4)]) <= 4, - sum([x_MOccurrence[q7] | q7 : int(1..2)]) <= 4, - and([x_MOccurrence[q9] > 0 -> - x_MOccurrence[q9] = - sum([toInt(x_ExplicitWithFlags_Values[q10] = q9) * catchUndef(x_ExplicitWithFlags_Flags[q10], 0) - | q10 : int(1..4)]) - | q9 : int(1..2)]), - and([x_ExplicitWithFlags_Flags[q11] > 0 -> - x_MOccurrence[x_ExplicitWithFlags_Values[q11]] = - sum([toInt(x_ExplicitWithFlags_Values[q12] = x_ExplicitWithFlags_Values[q11]) * - catchUndef(x_ExplicitWithFlags_Flags[q12], 0) - | q12 : int(1..4)]) - | q11 : int(1..4)]) - diff --git a/tests/exhaustive/basic/mset01_param/expected/model_2_1-param1-solution000001.solution b/tests/exhaustive/basic/mset01_param/expected/model_2_1-param1-solution000001.solution deleted file mode 100644 index 3fc3fafe52..0000000000 --- a/tests/exhaustive/basic/mset01_param/expected/model_2_1-param1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be mset() diff --git a/tests/exhaustive/basic/mset01_param/expected/model_2_1-param1.eprime-param b/tests/exhaustive/basic/mset01_param/expected/model_2_1-param1.eprime-param deleted file mode 100644 index 62e729a0fe..0000000000 --- a/tests/exhaustive/basic/mset01_param/expected/model_2_1-param1.eprime-param +++ /dev/null @@ -1,5 +0,0 @@ -language ESSENCE' 1.0 - -letting g_ExplicitWithFlags_Flags be ([] : `matrix indexed by [int()] of bool`) -letting g_ExplicitWithFlags_Values be ([] : `matrix indexed by [int()] of int`) -letting fin1 be 0 diff --git a/tests/exhaustive/basic/mset01_param/expected/model_2_1-param4-solution000001.solution b/tests/exhaustive/basic/mset01_param/expected/model_2_1-param4-solution000001.solution deleted file mode 100644 index 43c40d1c6b..0000000000 --- a/tests/exhaustive/basic/mset01_param/expected/model_2_1-param4-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be mset(1, 2) diff --git a/tests/exhaustive/basic/mset01_param/expected/model_2_1-param4.eprime-param b/tests/exhaustive/basic/mset01_param/expected/model_2_1-param4.eprime-param deleted file mode 100644 index f1da505f58..0000000000 --- a/tests/exhaustive/basic/mset01_param/expected/model_2_1-param4.eprime-param +++ /dev/null @@ -1,5 +0,0 @@ -language ESSENCE' 1.0 - -letting g_ExplicitWithFlags_Flags be [1, 1; int(1..2)] -letting g_ExplicitWithFlags_Values be [1, 2; int(1..2)] -letting fin1 be 2 diff --git a/tests/exhaustive/basic/mset01_param/expected/model_2_1-param7-solution000001.solution b/tests/exhaustive/basic/mset01_param/expected/model_2_1-param7-solution000001.solution deleted file mode 100644 index 06be1e3b32..0000000000 --- a/tests/exhaustive/basic/mset01_param/expected/model_2_1-param7-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be mset(2, 2) diff --git a/tests/exhaustive/basic/mset01_param/expected/model_2_1-param7.eprime-param b/tests/exhaustive/basic/mset01_param/expected/model_2_1-param7.eprime-param deleted file mode 100644 index 468cfba281..0000000000 --- a/tests/exhaustive/basic/mset01_param/expected/model_2_1-param7.eprime-param +++ /dev/null @@ -1,5 +0,0 @@ -language ESSENCE' 1.0 - -letting g_ExplicitWithFlags_Flags be [2, 0; int(1..2)] -letting g_ExplicitWithFlags_Values be [2, 1; int(1..2)] -letting fin1 be 2 diff --git a/tests/exhaustive/basic/mset01_param/expected/model_2_1.eprime b/tests/exhaustive/basic/mset01_param/expected/model_2_1.eprime deleted file mode 100644 index ad4c16d309..0000000000 --- a/tests/exhaustive/basic/mset01_param/expected/model_2_1.eprime +++ /dev/null @@ -1,64 +0,0 @@ -language ESSENCE' 1.0 - -given fin1: int -given g_ExplicitWithFlags_Flags: matrix indexed by [int(1..fin1)] of int(0..2) -given g_ExplicitWithFlags_Values: matrix indexed by [int(1..fin1)] of int(1..2) -find x_ExplicitWithRepetition_Flag: int(0..4) -find x_ExplicitWithRepetition_Values: matrix indexed by [int(1..4)] of int(1..2) -find x_ExplicitWithFlags_Flags: matrix indexed by [int(1..4)] of int(0..2) -find x_ExplicitWithFlags_Values: matrix indexed by [int(1..4)] of int(1..2) -branching on - [x_ExplicitWithFlags_Flags, x_ExplicitWithFlags_Values, x_ExplicitWithRepetition_Flag, - x_ExplicitWithRepetition_Values] -such that - and([sum([g_ExplicitWithFlags_Flags[q25] - | q25 : int(1..fin1), g_ExplicitWithFlags_Values[q25] = g_ExplicitWithFlags_Values[q24]]) - = - sum([toInt(q27 <= x_ExplicitWithRepetition_Flag) * - catchUndef(toInt(x_ExplicitWithRepetition_Values[q27] = g_ExplicitWithFlags_Values[q24]), 0) - | q27 : int(1..4)]) - | q24 : int(1..fin1), g_ExplicitWithFlags_Flags[q24] > 0]), - and([q28 <= x_ExplicitWithRepetition_Flag -> - sum([toInt(g_ExplicitWithFlags_Values[q29] = x_ExplicitWithRepetition_Values[q28]) * - catchUndef(g_ExplicitWithFlags_Flags[q29], 0) - | q29 : int(1..fin1)]) - = - sum([toInt(q31 <= x_ExplicitWithRepetition_Flag) * - catchUndef(toInt(x_ExplicitWithRepetition_Values[q31] = x_ExplicitWithRepetition_Values[q28]), 0) - | q31 : int(1..4)]) - | q28 : int(1..4)]), - and([q1 + 1 <= x_ExplicitWithRepetition_Flag -> - x_ExplicitWithRepetition_Values[q1] <= x_ExplicitWithRepetition_Values[q1 + 1] - | q1 : int(1..3)]), - and([q2 > x_ExplicitWithRepetition_Flag -> x_ExplicitWithRepetition_Values[q2] = 1 | q2 : int(1..4)]), - and([q4 <= x_ExplicitWithRepetition_Flag -> - sum([toInt(q7 <= x_ExplicitWithRepetition_Flag) * - catchUndef(toInt(x_ExplicitWithRepetition_Values[q7] = x_ExplicitWithRepetition_Values[q4]), 0) - | q7 : int(1..4)]) - <= 2 - | q4 : int(1..4)]), - x_ExplicitWithRepetition_Flag <= 4, - and([x_ExplicitWithFlags_Flags[q8 + 1] > 0 -> x_ExplicitWithFlags_Values[q8] < x_ExplicitWithFlags_Values[q8 + 1] - | q8 : int(1..3)]), - and([x_ExplicitWithFlags_Flags[q9] = 0 -> x_ExplicitWithFlags_Values[q9] = 1 | q9 : int(1..4)]), - and([x_ExplicitWithFlags_Flags[q10 + 1] > 0 -> x_ExplicitWithFlags_Flags[q10] > 0 | q10 : int(1..3)]), - sum([x_ExplicitWithFlags_Flags[q12] | q12 : int(1..4)]) <= 4, - and([x_ExplicitWithFlags_Flags[q15] > 0 -> - sum([toInt(x_ExplicitWithFlags_Values[q16] = x_ExplicitWithFlags_Values[q15]) * - catchUndef(x_ExplicitWithFlags_Flags[q16], 0) - | q16 : int(1..4)]) - = - sum([toInt(q18 <= x_ExplicitWithRepetition_Flag) * - catchUndef(toInt(x_ExplicitWithRepetition_Values[q18] = x_ExplicitWithFlags_Values[q15]), 0) - | q18 : int(1..4)]) - | q15 : int(1..4)]), - and([q19 <= x_ExplicitWithRepetition_Flag -> - sum([toInt(x_ExplicitWithFlags_Values[q20] = x_ExplicitWithRepetition_Values[q19]) * - catchUndef(x_ExplicitWithFlags_Flags[q20], 0) - | q20 : int(1..4)]) - = - sum([toInt(q22 <= x_ExplicitWithRepetition_Flag) * - catchUndef(toInt(x_ExplicitWithRepetition_Values[q22] = x_ExplicitWithRepetition_Values[q19]), 0) - | q22 : int(1..4)]) - | q19 : int(1..4)]) - diff --git a/tests/exhaustive/basic/mset01_param/expected/model_2_2-param1-solution000001.solution b/tests/exhaustive/basic/mset01_param/expected/model_2_2-param1-solution000001.solution deleted file mode 100644 index 3fc3fafe52..0000000000 --- a/tests/exhaustive/basic/mset01_param/expected/model_2_2-param1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be mset() diff --git a/tests/exhaustive/basic/mset01_param/expected/model_2_2-param1.eprime-param b/tests/exhaustive/basic/mset01_param/expected/model_2_2-param1.eprime-param deleted file mode 100644 index 62e729a0fe..0000000000 --- a/tests/exhaustive/basic/mset01_param/expected/model_2_2-param1.eprime-param +++ /dev/null @@ -1,5 +0,0 @@ -language ESSENCE' 1.0 - -letting g_ExplicitWithFlags_Flags be ([] : `matrix indexed by [int()] of bool`) -letting g_ExplicitWithFlags_Values be ([] : `matrix indexed by [int()] of int`) -letting fin1 be 0 diff --git a/tests/exhaustive/basic/mset01_param/expected/model_2_2-param4-solution000001.solution b/tests/exhaustive/basic/mset01_param/expected/model_2_2-param4-solution000001.solution deleted file mode 100644 index 43c40d1c6b..0000000000 --- a/tests/exhaustive/basic/mset01_param/expected/model_2_2-param4-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be mset(1, 2) diff --git a/tests/exhaustive/basic/mset01_param/expected/model_2_2-param4.eprime-param b/tests/exhaustive/basic/mset01_param/expected/model_2_2-param4.eprime-param deleted file mode 100644 index f1da505f58..0000000000 --- a/tests/exhaustive/basic/mset01_param/expected/model_2_2-param4.eprime-param +++ /dev/null @@ -1,5 +0,0 @@ -language ESSENCE' 1.0 - -letting g_ExplicitWithFlags_Flags be [1, 1; int(1..2)] -letting g_ExplicitWithFlags_Values be [1, 2; int(1..2)] -letting fin1 be 2 diff --git a/tests/exhaustive/basic/mset01_param/expected/model_2_2-param7-solution000001.solution b/tests/exhaustive/basic/mset01_param/expected/model_2_2-param7-solution000001.solution deleted file mode 100644 index 06be1e3b32..0000000000 --- a/tests/exhaustive/basic/mset01_param/expected/model_2_2-param7-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be mset(2, 2) diff --git a/tests/exhaustive/basic/mset01_param/expected/model_2_2-param7.eprime-param b/tests/exhaustive/basic/mset01_param/expected/model_2_2-param7.eprime-param deleted file mode 100644 index 468cfba281..0000000000 --- a/tests/exhaustive/basic/mset01_param/expected/model_2_2-param7.eprime-param +++ /dev/null @@ -1,5 +0,0 @@ -language ESSENCE' 1.0 - -letting g_ExplicitWithFlags_Flags be [2, 0; int(1..2)] -letting g_ExplicitWithFlags_Values be [2, 1; int(1..2)] -letting fin1 be 2 diff --git a/tests/exhaustive/basic/mset01_param/expected/model_2_2.eprime b/tests/exhaustive/basic/mset01_param/expected/model_2_2.eprime deleted file mode 100644 index a7170a2566..0000000000 --- a/tests/exhaustive/basic/mset01_param/expected/model_2_2.eprime +++ /dev/null @@ -1,37 +0,0 @@ -language ESSENCE' 1.0 - -given fin1: int -given g_ExplicitWithFlags_Flags: matrix indexed by [int(1..fin1)] of int(0..2) -given g_ExplicitWithFlags_Values: matrix indexed by [int(1..fin1)] of int(1..2) -find x_ExplicitWithRepetition_Flag: int(0..4) -find x_ExplicitWithRepetition_Values: matrix indexed by [int(1..4)] of int(1..2) -branching on [x_ExplicitWithRepetition_Flag, x_ExplicitWithRepetition_Values] -such that - and([sum([g_ExplicitWithFlags_Flags[q10] - | q10 : int(1..fin1), g_ExplicitWithFlags_Values[q10] = g_ExplicitWithFlags_Values[q9]]) - = - sum([toInt(q12 <= x_ExplicitWithRepetition_Flag) * - catchUndef(toInt(x_ExplicitWithRepetition_Values[q12] = g_ExplicitWithFlags_Values[q9]), 0) - | q12 : int(1..4)]) - | q9 : int(1..fin1), g_ExplicitWithFlags_Flags[q9] > 0]), - and([q13 <= x_ExplicitWithRepetition_Flag -> - sum([toInt(g_ExplicitWithFlags_Values[q14] = x_ExplicitWithRepetition_Values[q13]) * - catchUndef(g_ExplicitWithFlags_Flags[q14], 0) - | q14 : int(1..fin1)]) - = - sum([toInt(q16 <= x_ExplicitWithRepetition_Flag) * - catchUndef(toInt(x_ExplicitWithRepetition_Values[q16] = x_ExplicitWithRepetition_Values[q13]), 0) - | q16 : int(1..4)]) - | q13 : int(1..4)]), - and([q1 + 1 <= x_ExplicitWithRepetition_Flag -> - x_ExplicitWithRepetition_Values[q1] <= x_ExplicitWithRepetition_Values[q1 + 1] - | q1 : int(1..3)]), - and([q2 > x_ExplicitWithRepetition_Flag -> x_ExplicitWithRepetition_Values[q2] = 1 | q2 : int(1..4)]), - and([q4 <= x_ExplicitWithRepetition_Flag -> - sum([toInt(q7 <= x_ExplicitWithRepetition_Flag) * - catchUndef(toInt(x_ExplicitWithRepetition_Values[q7] = x_ExplicitWithRepetition_Values[q4]), 0) - | q7 : int(1..4)]) - <= 2 - | q4 : int(1..4)]), - x_ExplicitWithRepetition_Flag <= 4 - diff --git a/tests/exhaustive/basic/mset01_param/expected/model_2_3-param1-solution000001.solution b/tests/exhaustive/basic/mset01_param/expected/model_2_3-param1-solution000001.solution deleted file mode 100644 index 3fc3fafe52..0000000000 --- a/tests/exhaustive/basic/mset01_param/expected/model_2_3-param1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be mset() diff --git a/tests/exhaustive/basic/mset01_param/expected/model_2_3-param1.eprime-param b/tests/exhaustive/basic/mset01_param/expected/model_2_3-param1.eprime-param deleted file mode 100644 index 62e729a0fe..0000000000 --- a/tests/exhaustive/basic/mset01_param/expected/model_2_3-param1.eprime-param +++ /dev/null @@ -1,5 +0,0 @@ -language ESSENCE' 1.0 - -letting g_ExplicitWithFlags_Flags be ([] : `matrix indexed by [int()] of bool`) -letting g_ExplicitWithFlags_Values be ([] : `matrix indexed by [int()] of int`) -letting fin1 be 0 diff --git a/tests/exhaustive/basic/mset01_param/expected/model_2_3-param4-solution000001.solution b/tests/exhaustive/basic/mset01_param/expected/model_2_3-param4-solution000001.solution deleted file mode 100644 index 43c40d1c6b..0000000000 --- a/tests/exhaustive/basic/mset01_param/expected/model_2_3-param4-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be mset(1, 2) diff --git a/tests/exhaustive/basic/mset01_param/expected/model_2_3-param4.eprime-param b/tests/exhaustive/basic/mset01_param/expected/model_2_3-param4.eprime-param deleted file mode 100644 index f1da505f58..0000000000 --- a/tests/exhaustive/basic/mset01_param/expected/model_2_3-param4.eprime-param +++ /dev/null @@ -1,5 +0,0 @@ -language ESSENCE' 1.0 - -letting g_ExplicitWithFlags_Flags be [1, 1; int(1..2)] -letting g_ExplicitWithFlags_Values be [1, 2; int(1..2)] -letting fin1 be 2 diff --git a/tests/exhaustive/basic/mset01_param/expected/model_2_3-param7-solution000001.solution b/tests/exhaustive/basic/mset01_param/expected/model_2_3-param7-solution000001.solution deleted file mode 100644 index 06be1e3b32..0000000000 --- a/tests/exhaustive/basic/mset01_param/expected/model_2_3-param7-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be mset(2, 2) diff --git a/tests/exhaustive/basic/mset01_param/expected/model_2_3-param7.eprime-param b/tests/exhaustive/basic/mset01_param/expected/model_2_3-param7.eprime-param deleted file mode 100644 index 468cfba281..0000000000 --- a/tests/exhaustive/basic/mset01_param/expected/model_2_3-param7.eprime-param +++ /dev/null @@ -1,5 +0,0 @@ -language ESSENCE' 1.0 - -letting g_ExplicitWithFlags_Flags be [2, 0; int(1..2)] -letting g_ExplicitWithFlags_Values be [2, 1; int(1..2)] -letting fin1 be 2 diff --git a/tests/exhaustive/basic/mset01_param/expected/model_2_3.eprime b/tests/exhaustive/basic/mset01_param/expected/model_2_3.eprime deleted file mode 100644 index 333e369e13..0000000000 --- a/tests/exhaustive/basic/mset01_param/expected/model_2_3.eprime +++ /dev/null @@ -1,51 +0,0 @@ -language ESSENCE' 1.0 - -given fin1: int -given g_ExplicitWithFlags_Flags: matrix indexed by [int(1..fin1)] of int(0..2) -given g_ExplicitWithFlags_Values: matrix indexed by [int(1..fin1)] of int(1..2) -find x_ExplicitWithRepetition_Flag: int(0..4) -find x_ExplicitWithRepetition_Values: matrix indexed by [int(1..4)] of int(1..2) -find x_MOccurrence: matrix indexed by [int(1..2)] of int(0..2) -branching on [x_MOccurrence, x_ExplicitWithRepetition_Flag, x_ExplicitWithRepetition_Values] -such that - and([sum([g_ExplicitWithFlags_Flags[q18] - | q18 : int(1..fin1), g_ExplicitWithFlags_Values[q18] = g_ExplicitWithFlags_Values[q17]]) - = - sum([toInt(q20 <= x_ExplicitWithRepetition_Flag) * - catchUndef(toInt(x_ExplicitWithRepetition_Values[q20] = g_ExplicitWithFlags_Values[q17]), 0) - | q20 : int(1..4)]) - | q17 : int(1..fin1), g_ExplicitWithFlags_Flags[q17] > 0]), - and([q21 <= x_ExplicitWithRepetition_Flag -> - sum([toInt(g_ExplicitWithFlags_Values[q22] = x_ExplicitWithRepetition_Values[q21]) * - catchUndef(g_ExplicitWithFlags_Flags[q22], 0) - | q22 : int(1..fin1)]) - = - sum([toInt(q24 <= x_ExplicitWithRepetition_Flag) * - catchUndef(toInt(x_ExplicitWithRepetition_Values[q24] = x_ExplicitWithRepetition_Values[q21]), 0) - | q24 : int(1..4)]) - | q21 : int(1..4)]), - and([q1 + 1 <= x_ExplicitWithRepetition_Flag -> - x_ExplicitWithRepetition_Values[q1] <= x_ExplicitWithRepetition_Values[q1 + 1] - | q1 : int(1..3)]), - and([q2 > x_ExplicitWithRepetition_Flag -> x_ExplicitWithRepetition_Values[q2] = 1 | q2 : int(1..4)]), - and([q4 <= x_ExplicitWithRepetition_Flag -> - sum([toInt(q7 <= x_ExplicitWithRepetition_Flag) * - catchUndef(toInt(x_ExplicitWithRepetition_Values[q7] = x_ExplicitWithRepetition_Values[q4]), 0) - | q7 : int(1..4)]) - <= 2 - | q4 : int(1..4)]), - x_ExplicitWithRepetition_Flag <= 4, - sum([x_MOccurrence[q8] | q8 : int(1..2)]) <= 4, - and([x_MOccurrence[q10] > 0 -> - x_MOccurrence[q10] = - sum([toInt(q12 <= x_ExplicitWithRepetition_Flag) * - catchUndef(toInt(x_ExplicitWithRepetition_Values[q12] = q10), 0) - | q12 : int(1..4)]) - | q10 : int(1..2)]), - and([q13 <= x_ExplicitWithRepetition_Flag -> - x_MOccurrence[x_ExplicitWithRepetition_Values[q13]] = - sum([toInt(q15 <= x_ExplicitWithRepetition_Flag) * - catchUndef(toInt(x_ExplicitWithRepetition_Values[q15] = x_ExplicitWithRepetition_Values[q13]), 0) - | q15 : int(1..4)]) - | q13 : int(1..4)]) - diff --git a/tests/exhaustive/basic/mset01_param/expected/model_3_1-param1-solution000001.solution b/tests/exhaustive/basic/mset01_param/expected/model_3_1-param1-solution000001.solution deleted file mode 100644 index 3fc3fafe52..0000000000 --- a/tests/exhaustive/basic/mset01_param/expected/model_3_1-param1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be mset() diff --git a/tests/exhaustive/basic/mset01_param/expected/model_3_1-param1.eprime-param b/tests/exhaustive/basic/mset01_param/expected/model_3_1-param1.eprime-param deleted file mode 100644 index 62e729a0fe..0000000000 --- a/tests/exhaustive/basic/mset01_param/expected/model_3_1-param1.eprime-param +++ /dev/null @@ -1,5 +0,0 @@ -language ESSENCE' 1.0 - -letting g_ExplicitWithFlags_Flags be ([] : `matrix indexed by [int()] of bool`) -letting g_ExplicitWithFlags_Values be ([] : `matrix indexed by [int()] of int`) -letting fin1 be 0 diff --git a/tests/exhaustive/basic/mset01_param/expected/model_3_1-param4-solution000001.solution b/tests/exhaustive/basic/mset01_param/expected/model_3_1-param4-solution000001.solution deleted file mode 100644 index 43c40d1c6b..0000000000 --- a/tests/exhaustive/basic/mset01_param/expected/model_3_1-param4-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be mset(1, 2) diff --git a/tests/exhaustive/basic/mset01_param/expected/model_3_1-param4.eprime-param b/tests/exhaustive/basic/mset01_param/expected/model_3_1-param4.eprime-param deleted file mode 100644 index f1da505f58..0000000000 --- a/tests/exhaustive/basic/mset01_param/expected/model_3_1-param4.eprime-param +++ /dev/null @@ -1,5 +0,0 @@ -language ESSENCE' 1.0 - -letting g_ExplicitWithFlags_Flags be [1, 1; int(1..2)] -letting g_ExplicitWithFlags_Values be [1, 2; int(1..2)] -letting fin1 be 2 diff --git a/tests/exhaustive/basic/mset01_param/expected/model_3_1-param7-solution000001.solution b/tests/exhaustive/basic/mset01_param/expected/model_3_1-param7-solution000001.solution deleted file mode 100644 index 06be1e3b32..0000000000 --- a/tests/exhaustive/basic/mset01_param/expected/model_3_1-param7-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be mset(2, 2) diff --git a/tests/exhaustive/basic/mset01_param/expected/model_3_1-param7.eprime-param b/tests/exhaustive/basic/mset01_param/expected/model_3_1-param7.eprime-param deleted file mode 100644 index 468cfba281..0000000000 --- a/tests/exhaustive/basic/mset01_param/expected/model_3_1-param7.eprime-param +++ /dev/null @@ -1,5 +0,0 @@ -language ESSENCE' 1.0 - -letting g_ExplicitWithFlags_Flags be [2, 0; int(1..2)] -letting g_ExplicitWithFlags_Values be [2, 1; int(1..2)] -letting fin1 be 2 diff --git a/tests/exhaustive/basic/mset01_param/expected/model_3_1.eprime b/tests/exhaustive/basic/mset01_param/expected/model_3_1.eprime deleted file mode 100644 index 872e16c02d..0000000000 --- a/tests/exhaustive/basic/mset01_param/expected/model_3_1.eprime +++ /dev/null @@ -1,36 +0,0 @@ -language ESSENCE' 1.0 - -given fin1: int -given g_ExplicitWithFlags_Flags: matrix indexed by [int(1..fin1)] of int(0..2) -given g_ExplicitWithFlags_Values: matrix indexed by [int(1..fin1)] of int(1..2) -find x_MOccurrence: matrix indexed by [int(1..2)] of int(0..2) -find x_ExplicitWithFlags_Flags: matrix indexed by [int(1..4)] of int(0..2) -find x_ExplicitWithFlags_Values: matrix indexed by [int(1..4)] of int(1..2) -branching on [x_ExplicitWithFlags_Flags, x_ExplicitWithFlags_Values, x_MOccurrence] -such that - and([sum([g_ExplicitWithFlags_Flags[q15] - | q15 : int(1..fin1), g_ExplicitWithFlags_Values[q15] = g_ExplicitWithFlags_Values[q14]]) - = x_MOccurrence[g_ExplicitWithFlags_Values[q14]] - | q14 : int(1..fin1), g_ExplicitWithFlags_Flags[q14] > 0]), - and([x_MOccurrence[q16] > 0 -> - sum([g_ExplicitWithFlags_Flags[q17] | q17 : int(1..fin1), g_ExplicitWithFlags_Values[q17] = q16]) = - x_MOccurrence[q16] - | q16 : int(1..2)]), - sum([x_MOccurrence[q1] | q1 : int(1..2)]) <= 4, - and([x_ExplicitWithFlags_Flags[q2 + 1] > 0 -> x_ExplicitWithFlags_Values[q2] < x_ExplicitWithFlags_Values[q2 + 1] - | q2 : int(1..3)]), - and([x_ExplicitWithFlags_Flags[q3] = 0 -> x_ExplicitWithFlags_Values[q3] = 1 | q3 : int(1..4)]), - and([x_ExplicitWithFlags_Flags[q4 + 1] > 0 -> x_ExplicitWithFlags_Flags[q4] > 0 | q4 : int(1..3)]), - sum([x_ExplicitWithFlags_Flags[q6] | q6 : int(1..4)]) <= 4, - and([x_ExplicitWithFlags_Flags[q9] > 0 -> - sum([toInt(x_ExplicitWithFlags_Values[q10] = x_ExplicitWithFlags_Values[q9]) * - catchUndef(x_ExplicitWithFlags_Flags[q10], 0) - | q10 : int(1..4)]) - = x_MOccurrence[x_ExplicitWithFlags_Values[q9]] - | q9 : int(1..4)]), - and([x_MOccurrence[q11] > 0 -> - sum([toInt(x_ExplicitWithFlags_Values[q12] = q11) * catchUndef(x_ExplicitWithFlags_Flags[q12], 0) - | q12 : int(1..4)]) - = x_MOccurrence[q11] - | q11 : int(1..2)]) - diff --git a/tests/exhaustive/basic/mset01_param/expected/model_3_2-param1-solution000001.solution b/tests/exhaustive/basic/mset01_param/expected/model_3_2-param1-solution000001.solution deleted file mode 100644 index 3fc3fafe52..0000000000 --- a/tests/exhaustive/basic/mset01_param/expected/model_3_2-param1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be mset() diff --git a/tests/exhaustive/basic/mset01_param/expected/model_3_2-param1.eprime-param b/tests/exhaustive/basic/mset01_param/expected/model_3_2-param1.eprime-param deleted file mode 100644 index 62e729a0fe..0000000000 --- a/tests/exhaustive/basic/mset01_param/expected/model_3_2-param1.eprime-param +++ /dev/null @@ -1,5 +0,0 @@ -language ESSENCE' 1.0 - -letting g_ExplicitWithFlags_Flags be ([] : `matrix indexed by [int()] of bool`) -letting g_ExplicitWithFlags_Values be ([] : `matrix indexed by [int()] of int`) -letting fin1 be 0 diff --git a/tests/exhaustive/basic/mset01_param/expected/model_3_2-param4-solution000001.solution b/tests/exhaustive/basic/mset01_param/expected/model_3_2-param4-solution000001.solution deleted file mode 100644 index 43c40d1c6b..0000000000 --- a/tests/exhaustive/basic/mset01_param/expected/model_3_2-param4-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be mset(1, 2) diff --git a/tests/exhaustive/basic/mset01_param/expected/model_3_2-param4.eprime-param b/tests/exhaustive/basic/mset01_param/expected/model_3_2-param4.eprime-param deleted file mode 100644 index f1da505f58..0000000000 --- a/tests/exhaustive/basic/mset01_param/expected/model_3_2-param4.eprime-param +++ /dev/null @@ -1,5 +0,0 @@ -language ESSENCE' 1.0 - -letting g_ExplicitWithFlags_Flags be [1, 1; int(1..2)] -letting g_ExplicitWithFlags_Values be [1, 2; int(1..2)] -letting fin1 be 2 diff --git a/tests/exhaustive/basic/mset01_param/expected/model_3_2-param7-solution000001.solution b/tests/exhaustive/basic/mset01_param/expected/model_3_2-param7-solution000001.solution deleted file mode 100644 index 06be1e3b32..0000000000 --- a/tests/exhaustive/basic/mset01_param/expected/model_3_2-param7-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be mset(2, 2) diff --git a/tests/exhaustive/basic/mset01_param/expected/model_3_2-param7.eprime-param b/tests/exhaustive/basic/mset01_param/expected/model_3_2-param7.eprime-param deleted file mode 100644 index 468cfba281..0000000000 --- a/tests/exhaustive/basic/mset01_param/expected/model_3_2-param7.eprime-param +++ /dev/null @@ -1,5 +0,0 @@ -language ESSENCE' 1.0 - -letting g_ExplicitWithFlags_Flags be [2, 0; int(1..2)] -letting g_ExplicitWithFlags_Values be [2, 1; int(1..2)] -letting fin1 be 2 diff --git a/tests/exhaustive/basic/mset01_param/expected/model_3_2.eprime b/tests/exhaustive/basic/mset01_param/expected/model_3_2.eprime deleted file mode 100644 index 40b69ccf3d..0000000000 --- a/tests/exhaustive/basic/mset01_param/expected/model_3_2.eprime +++ /dev/null @@ -1,43 +0,0 @@ -language ESSENCE' 1.0 - -given fin1: int -given g_ExplicitWithFlags_Flags: matrix indexed by [int(1..fin1)] of int(0..2) -given g_ExplicitWithFlags_Values: matrix indexed by [int(1..fin1)] of int(1..2) -find x_MOccurrence: matrix indexed by [int(1..2)] of int(0..2) -find x_ExplicitWithRepetition_Flag: int(0..4) -find x_ExplicitWithRepetition_Values: matrix indexed by [int(1..4)] of int(1..2) -branching on [x_ExplicitWithRepetition_Flag, x_ExplicitWithRepetition_Values, x_MOccurrence] -such that - and([sum([g_ExplicitWithFlags_Flags[q18] - | q18 : int(1..fin1), g_ExplicitWithFlags_Values[q18] = g_ExplicitWithFlags_Values[q17]]) - = x_MOccurrence[g_ExplicitWithFlags_Values[q17]] - | q17 : int(1..fin1), g_ExplicitWithFlags_Flags[q17] > 0]), - and([x_MOccurrence[q19] > 0 -> - sum([g_ExplicitWithFlags_Flags[q20] | q20 : int(1..fin1), g_ExplicitWithFlags_Values[q20] = q19]) = - x_MOccurrence[q19] - | q19 : int(1..2)]), - sum([x_MOccurrence[q1] | q1 : int(1..2)]) <= 4, - and([q2 + 1 <= x_ExplicitWithRepetition_Flag -> - x_ExplicitWithRepetition_Values[q2] <= x_ExplicitWithRepetition_Values[q2 + 1] - | q2 : int(1..3)]), - and([q3 > x_ExplicitWithRepetition_Flag -> x_ExplicitWithRepetition_Values[q3] = 1 | q3 : int(1..4)]), - and([q5 <= x_ExplicitWithRepetition_Flag -> - sum([toInt(q8 <= x_ExplicitWithRepetition_Flag) * - catchUndef(toInt(x_ExplicitWithRepetition_Values[q8] = x_ExplicitWithRepetition_Values[q5]), 0) - | q8 : int(1..4)]) - <= 2 - | q5 : int(1..4)]), - x_ExplicitWithRepetition_Flag <= 4, - and([q10 <= x_ExplicitWithRepetition_Flag -> - sum([toInt(q12 <= x_ExplicitWithRepetition_Flag) * - catchUndef(toInt(x_ExplicitWithRepetition_Values[q12] = x_ExplicitWithRepetition_Values[q10]), 0) - | q12 : int(1..4)]) - = x_MOccurrence[x_ExplicitWithRepetition_Values[q10]] - | q10 : int(1..4)]), - and([x_MOccurrence[q13] > 0 -> - sum([toInt(q15 <= x_ExplicitWithRepetition_Flag) * - catchUndef(toInt(x_ExplicitWithRepetition_Values[q15] = q13), 0) - | q15 : int(1..4)]) - = x_MOccurrence[q13] - | q13 : int(1..2)]) - diff --git a/tests/exhaustive/basic/mset01_param/expected/model_3_3-param1-solution000001.solution b/tests/exhaustive/basic/mset01_param/expected/model_3_3-param1-solution000001.solution deleted file mode 100644 index 3fc3fafe52..0000000000 --- a/tests/exhaustive/basic/mset01_param/expected/model_3_3-param1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be mset() diff --git a/tests/exhaustive/basic/mset01_param/expected/model_3_3-param1.eprime-param b/tests/exhaustive/basic/mset01_param/expected/model_3_3-param1.eprime-param deleted file mode 100644 index 62e729a0fe..0000000000 --- a/tests/exhaustive/basic/mset01_param/expected/model_3_3-param1.eprime-param +++ /dev/null @@ -1,5 +0,0 @@ -language ESSENCE' 1.0 - -letting g_ExplicitWithFlags_Flags be ([] : `matrix indexed by [int()] of bool`) -letting g_ExplicitWithFlags_Values be ([] : `matrix indexed by [int()] of int`) -letting fin1 be 0 diff --git a/tests/exhaustive/basic/mset01_param/expected/model_3_3-param4-solution000001.solution b/tests/exhaustive/basic/mset01_param/expected/model_3_3-param4-solution000001.solution deleted file mode 100644 index 43c40d1c6b..0000000000 --- a/tests/exhaustive/basic/mset01_param/expected/model_3_3-param4-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be mset(1, 2) diff --git a/tests/exhaustive/basic/mset01_param/expected/model_3_3-param4.eprime-param b/tests/exhaustive/basic/mset01_param/expected/model_3_3-param4.eprime-param deleted file mode 100644 index f1da505f58..0000000000 --- a/tests/exhaustive/basic/mset01_param/expected/model_3_3-param4.eprime-param +++ /dev/null @@ -1,5 +0,0 @@ -language ESSENCE' 1.0 - -letting g_ExplicitWithFlags_Flags be [1, 1; int(1..2)] -letting g_ExplicitWithFlags_Values be [1, 2; int(1..2)] -letting fin1 be 2 diff --git a/tests/exhaustive/basic/mset01_param/expected/model_3_3-param7-solution000001.solution b/tests/exhaustive/basic/mset01_param/expected/model_3_3-param7-solution000001.solution deleted file mode 100644 index 06be1e3b32..0000000000 --- a/tests/exhaustive/basic/mset01_param/expected/model_3_3-param7-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be mset(2, 2) diff --git a/tests/exhaustive/basic/mset01_param/expected/model_3_3-param7.eprime-param b/tests/exhaustive/basic/mset01_param/expected/model_3_3-param7.eprime-param deleted file mode 100644 index 468cfba281..0000000000 --- a/tests/exhaustive/basic/mset01_param/expected/model_3_3-param7.eprime-param +++ /dev/null @@ -1,5 +0,0 @@ -language ESSENCE' 1.0 - -letting g_ExplicitWithFlags_Flags be [2, 0; int(1..2)] -letting g_ExplicitWithFlags_Values be [2, 1; int(1..2)] -letting fin1 be 2 diff --git a/tests/exhaustive/basic/mset01_param/expected/model_3_3.eprime b/tests/exhaustive/basic/mset01_param/expected/model_3_3.eprime deleted file mode 100644 index c7c31d20ea..0000000000 --- a/tests/exhaustive/basic/mset01_param/expected/model_3_3.eprime +++ /dev/null @@ -1,18 +0,0 @@ -language ESSENCE' 1.0 - -given fin1: int -given g_ExplicitWithFlags_Flags: matrix indexed by [int(1..fin1)] of int(0..2) -given g_ExplicitWithFlags_Values: matrix indexed by [int(1..fin1)] of int(1..2) -find x_MOccurrence: matrix indexed by [int(1..2)] of int(0..2) -branching on [x_MOccurrence] -such that - and([sum([g_ExplicitWithFlags_Flags[q4] - | q4 : int(1..fin1), g_ExplicitWithFlags_Values[q4] = g_ExplicitWithFlags_Values[q3]]) - = x_MOccurrence[g_ExplicitWithFlags_Values[q3]] - | q3 : int(1..fin1), g_ExplicitWithFlags_Flags[q3] > 0]), - and([x_MOccurrence[q5] > 0 -> - sum([g_ExplicitWithFlags_Flags[q6] | q6 : int(1..fin1), g_ExplicitWithFlags_Values[q6] = q5]) = - x_MOccurrence[q5] - | q5 : int(1..2)]), - sum([x_MOccurrence[q1] | q1 : int(1..2)]) <= 4 - diff --git a/tests/exhaustive/basic/name-reuse/expected/model_1_1-solution000001.solution b/tests/exhaustive/basic/name-reuse/expected/model_1_1-solution000001.solution deleted file mode 100644 index d4f1477569..0000000000 --- a/tests/exhaustive/basic/name-reuse/expected/model_1_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting conjure_aux1 be 1 -letting s be {3} diff --git a/tests/exhaustive/basic/name-reuse/expected/model_1_1-solution000002.solution b/tests/exhaustive/basic/name-reuse/expected/model_1_1-solution000002.solution deleted file mode 100644 index ab91f42e83..0000000000 --- a/tests/exhaustive/basic/name-reuse/expected/model_1_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting conjure_aux1 be 1 -letting s be {3, 4} diff --git a/tests/exhaustive/basic/name-reuse/expected/model_1_1.eprime b/tests/exhaustive/basic/name-reuse/expected/model_1_1.eprime deleted file mode 100644 index 225fffebc9..0000000000 --- a/tests/exhaustive/basic/name-reuse/expected/model_1_1.eprime +++ /dev/null @@ -1,13 +0,0 @@ -language ESSENCE' 1.0 - -find conjure_aux1: int(1) -find s_Occurrence: matrix indexed by [int(1..4)] of bool -find conjure_aux2: int(1..4) -branching on [conjure_aux1, s_Occurrence] -such that - and([s_Occurrence[q2] -> q2 >= conjure_aux2 | q2 : int(1..4)]), - sum([toInt(s_Occurrence[q2]) | q2 : int(1..4)]) > 0 -> or([s_Occurrence[q2] /\ q2 = conjure_aux2 | q2 : int(1..4)]), - sum([toInt(s_Occurrence[q2]) | q2 : int(1..4)]) = 0 -> conjure_aux2 = 1, - conjure_aux2 = 3, - sum([toInt(s_Occurrence[q2]) | q2 : int(1..4)]) > 0 - diff --git a/tests/exhaustive/basic/name-reuse/expected/model_1_2-solution000001.solution b/tests/exhaustive/basic/name-reuse/expected/model_1_2-solution000001.solution deleted file mode 100644 index ab91f42e83..0000000000 --- a/tests/exhaustive/basic/name-reuse/expected/model_1_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting conjure_aux1 be 1 -letting s be {3, 4} diff --git a/tests/exhaustive/basic/name-reuse/expected/model_1_2-solution000002.solution b/tests/exhaustive/basic/name-reuse/expected/model_1_2-solution000002.solution deleted file mode 100644 index d4f1477569..0000000000 --- a/tests/exhaustive/basic/name-reuse/expected/model_1_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting conjure_aux1 be 1 -letting s be {3} diff --git a/tests/exhaustive/basic/name-reuse/expected/model_1_2.eprime b/tests/exhaustive/basic/name-reuse/expected/model_1_2.eprime deleted file mode 100644 index 1aaa5e2e02..0000000000 --- a/tests/exhaustive/basic/name-reuse/expected/model_1_2.eprime +++ /dev/null @@ -1,22 +0,0 @@ -language ESSENCE' 1.0 - -find conjure_aux1: int(1) -find s_Occurrence: matrix indexed by [int(1..4)] of bool -find s_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -find conjure_aux2: int(1..4) -branching on [conjure_aux1, s_ExplicitVarSizeWithDummy, s_Occurrence] -such that - and([s_Occurrence[q11] -> q11 >= conjure_aux2 | q11 : int(1..4)]), - sum([toInt(s_Occurrence[q11]) | q11 : int(1..4)]) > 0 -> - or([s_Occurrence[q11] /\ q11 = conjure_aux2 | q11 : int(1..4)]), - sum([toInt(s_Occurrence[q11]) | q11 : int(1..4)]) = 0 -> conjure_aux2 = 1, - conjure_aux2 = 3, - sum([toInt(s_Occurrence[q11]) | q11 : int(1..4)]) > 0, - and([s_ExplicitVarSizeWithDummy[q2] < s_ExplicitVarSizeWithDummy[q2 + 1] \/ s_ExplicitVarSizeWithDummy[q2] = 5 - | q2 : int(1..3)]), - and([s_ExplicitVarSizeWithDummy[q3] = 5 -> s_ExplicitVarSizeWithDummy[q3 + 1] = 5 | q3 : int(1..3)]), - and([s_ExplicitVarSizeWithDummy[q7] != 5 -> s_Occurrence[s_ExplicitVarSizeWithDummy[q7]] | q7 : int(1..4)]), - and([s_Occurrence[q8] -> - or([s_ExplicitVarSizeWithDummy[q10] != 5 /\ s_ExplicitVarSizeWithDummy[q10] = q8 | q10 : int(1..4)]) - | q8 : int(1..4)]) - diff --git a/tests/exhaustive/basic/name-reuse/expected/model_1_3-solution000001.solution b/tests/exhaustive/basic/name-reuse/expected/model_1_3-solution000001.solution deleted file mode 100644 index d4f1477569..0000000000 --- a/tests/exhaustive/basic/name-reuse/expected/model_1_3-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting conjure_aux1 be 1 -letting s be {3} diff --git a/tests/exhaustive/basic/name-reuse/expected/model_1_3-solution000002.solution b/tests/exhaustive/basic/name-reuse/expected/model_1_3-solution000002.solution deleted file mode 100644 index ab91f42e83..0000000000 --- a/tests/exhaustive/basic/name-reuse/expected/model_1_3-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting conjure_aux1 be 1 -letting s be {3, 4} diff --git a/tests/exhaustive/basic/name-reuse/expected/model_1_3.eprime b/tests/exhaustive/basic/name-reuse/expected/model_1_3.eprime deleted file mode 100644 index 90ed8b70f3..0000000000 --- a/tests/exhaustive/basic/name-reuse/expected/model_1_3.eprime +++ /dev/null @@ -1,25 +0,0 @@ -language ESSENCE' 1.0 - -find conjure_aux1: int(1) -find s_Occurrence: matrix indexed by [int(1..4)] of bool -find s_ExplicitVarSizeWithMarker_Marker: int(0..4) -find s_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -find conjure_aux2: int(1..4) -branching on [conjure_aux1, s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithMarker_Values, s_Occurrence] -such that - and([s_Occurrence[q10] -> q10 >= conjure_aux2 | q10 : int(1..4)]), - sum([toInt(s_Occurrence[q10]) | q10 : int(1..4)]) > 0 -> - or([s_Occurrence[q10] /\ q10 = conjure_aux2 | q10 : int(1..4)]), - sum([toInt(s_Occurrence[q10]) | q10 : int(1..4)]) = 0 -> conjure_aux2 = 1, - conjure_aux2 = 3, - sum([toInt(s_Occurrence[q10]) | q10 : int(1..4)]) > 0, - and([q2 + 1 <= s_ExplicitVarSizeWithMarker_Marker -> - s_ExplicitVarSizeWithMarker_Values[q2] < s_ExplicitVarSizeWithMarker_Values[q2 + 1] - | q2 : int(1..3)]), - and([q3 > s_ExplicitVarSizeWithMarker_Marker -> s_ExplicitVarSizeWithMarker_Values[q3] = 1 | q3 : int(1..4)]), - and([q6 <= s_ExplicitVarSizeWithMarker_Marker -> s_Occurrence[s_ExplicitVarSizeWithMarker_Values[q6]] - | q6 : int(1..4)]), - and([s_Occurrence[q7] -> - or([q9 <= s_ExplicitVarSizeWithMarker_Marker /\ s_ExplicitVarSizeWithMarker_Values[q9] = q7 | q9 : int(1..4)]) - | q7 : int(1..4)]) - diff --git a/tests/exhaustive/basic/name-reuse/expected/model_1_4-solution000001.solution b/tests/exhaustive/basic/name-reuse/expected/model_1_4-solution000001.solution deleted file mode 100644 index d4f1477569..0000000000 --- a/tests/exhaustive/basic/name-reuse/expected/model_1_4-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting conjure_aux1 be 1 -letting s be {3} diff --git a/tests/exhaustive/basic/name-reuse/expected/model_1_4-solution000002.solution b/tests/exhaustive/basic/name-reuse/expected/model_1_4-solution000002.solution deleted file mode 100644 index ab91f42e83..0000000000 --- a/tests/exhaustive/basic/name-reuse/expected/model_1_4-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting conjure_aux1 be 1 -letting s be {3, 4} diff --git a/tests/exhaustive/basic/name-reuse/expected/model_1_4.eprime b/tests/exhaustive/basic/name-reuse/expected/model_1_4.eprime deleted file mode 100644 index f0a2271016..0000000000 --- a/tests/exhaustive/basic/name-reuse/expected/model_1_4.eprime +++ /dev/null @@ -1,25 +0,0 @@ -language ESSENCE' 1.0 - -find conjure_aux1: int(1) -find s_Occurrence: matrix indexed by [int(1..4)] of bool -find s_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find s_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -find conjure_aux2: int(1..4) -branching on [conjure_aux1, s_ExplicitVarSizeWithFlags_Flags, s_ExplicitVarSizeWithFlags_Values, s_Occurrence] -such that - and([s_Occurrence[q12] -> q12 >= conjure_aux2 | q12 : int(1..4)]), - sum([toInt(s_Occurrence[q12]) | q12 : int(1..4)]) > 0 -> - or([s_Occurrence[q12] /\ q12 = conjure_aux2 | q12 : int(1..4)]), - sum([toInt(s_Occurrence[q12]) | q12 : int(1..4)]) = 0 -> conjure_aux2 = 1, - conjure_aux2 = 3, - sum([toInt(s_Occurrence[q12]) | q12 : int(1..4)]) > 0, - and([s_ExplicitVarSizeWithFlags_Flags[q2 + 1] -> - s_ExplicitVarSizeWithFlags_Values[q2] < s_ExplicitVarSizeWithFlags_Values[q2 + 1] - | q2 : int(1..3)]), - and([s_ExplicitVarSizeWithFlags_Flags[q3] = false -> s_ExplicitVarSizeWithFlags_Values[q3] = 1 | q3 : int(1..4)]), - and([s_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> s_ExplicitVarSizeWithFlags_Flags[q4] | q4 : int(1..3)]), - and([s_ExplicitVarSizeWithFlags_Flags[q8] -> s_Occurrence[s_ExplicitVarSizeWithFlags_Values[q8]] | q8 : int(1..4)]), - and([s_Occurrence[q9] -> - or([s_ExplicitVarSizeWithFlags_Flags[q11] /\ s_ExplicitVarSizeWithFlags_Values[q11] = q9 | q11 : int(1..4)]) - | q9 : int(1..4)]) - diff --git a/tests/exhaustive/basic/name-reuse/expected/model_2_1-solution000001.solution b/tests/exhaustive/basic/name-reuse/expected/model_2_1-solution000001.solution deleted file mode 100644 index d4f1477569..0000000000 --- a/tests/exhaustive/basic/name-reuse/expected/model_2_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting conjure_aux1 be 1 -letting s be {3} diff --git a/tests/exhaustive/basic/name-reuse/expected/model_2_1-solution000002.solution b/tests/exhaustive/basic/name-reuse/expected/model_2_1-solution000002.solution deleted file mode 100644 index ab91f42e83..0000000000 --- a/tests/exhaustive/basic/name-reuse/expected/model_2_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting conjure_aux1 be 1 -letting s be {3, 4} diff --git a/tests/exhaustive/basic/name-reuse/expected/model_2_1.eprime b/tests/exhaustive/basic/name-reuse/expected/model_2_1.eprime deleted file mode 100644 index 7abd51269f..0000000000 --- a/tests/exhaustive/basic/name-reuse/expected/model_2_1.eprime +++ /dev/null @@ -1,22 +0,0 @@ -language ESSENCE' 1.0 - -find conjure_aux1: int(1) -find s_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -find s_Occurrence: matrix indexed by [int(1..4)] of bool -find conjure_aux2: int(1..5) -branching on [conjure_aux1, s_Occurrence, s_ExplicitVarSizeWithDummy] -such that - and([s_ExplicitVarSizeWithDummy[q7] != 5 -> s_ExplicitVarSizeWithDummy[q7] >= conjure_aux2 | q7 : int(1..4)]), - sum([toInt(s_ExplicitVarSizeWithDummy[q7] != 5) | q7 : int(1..4)]) > 0 -> - or([s_ExplicitVarSizeWithDummy[q7] != 5 /\ s_ExplicitVarSizeWithDummy[q7] = conjure_aux2 | q7 : int(1..4)]), - sum([toInt(s_ExplicitVarSizeWithDummy[q7] != 5) | q7 : int(1..4)]) = 0 -> conjure_aux2 = 1, - conjure_aux2 = 3, - sum([toInt(s_ExplicitVarSizeWithDummy[q7] != 5) | q7 : int(1..4)]) > 0, - and([s_ExplicitVarSizeWithDummy[q1] < s_ExplicitVarSizeWithDummy[q1 + 1] \/ s_ExplicitVarSizeWithDummy[q1] = 5 - | q1 : int(1..3)]), - and([s_ExplicitVarSizeWithDummy[q2] = 5 -> s_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..3)]), - and([s_Occurrence[q8] -> - or([s_ExplicitVarSizeWithDummy[q10] != 5 /\ s_ExplicitVarSizeWithDummy[q10] = q8 | q10 : int(1..4)]) - | q8 : int(1..4)]), - and([s_ExplicitVarSizeWithDummy[q12] != 5 -> s_Occurrence[s_ExplicitVarSizeWithDummy[q12]] | q12 : int(1..4)]) - diff --git a/tests/exhaustive/basic/name-reuse/expected/model_2_2-solution000001.solution b/tests/exhaustive/basic/name-reuse/expected/model_2_2-solution000001.solution deleted file mode 100644 index ab91f42e83..0000000000 --- a/tests/exhaustive/basic/name-reuse/expected/model_2_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting conjure_aux1 be 1 -letting s be {3, 4} diff --git a/tests/exhaustive/basic/name-reuse/expected/model_2_2-solution000002.solution b/tests/exhaustive/basic/name-reuse/expected/model_2_2-solution000002.solution deleted file mode 100644 index d4f1477569..0000000000 --- a/tests/exhaustive/basic/name-reuse/expected/model_2_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting conjure_aux1 be 1 -letting s be {3} diff --git a/tests/exhaustive/basic/name-reuse/expected/model_2_2.eprime b/tests/exhaustive/basic/name-reuse/expected/model_2_2.eprime deleted file mode 100644 index 706b338fed..0000000000 --- a/tests/exhaustive/basic/name-reuse/expected/model_2_2.eprime +++ /dev/null @@ -1,17 +0,0 @@ -language ESSENCE' 1.0 - -find conjure_aux1: int(1) -find s_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -find conjure_aux2: int(1..5) -branching on [conjure_aux1, s_ExplicitVarSizeWithDummy] -such that - and([s_ExplicitVarSizeWithDummy[q6] != 5 -> s_ExplicitVarSizeWithDummy[q6] >= conjure_aux2 | q6 : int(1..4)]), - sum([toInt(s_ExplicitVarSizeWithDummy[q6] != 5) | q6 : int(1..4)]) > 0 -> - or([s_ExplicitVarSizeWithDummy[q6] != 5 /\ s_ExplicitVarSizeWithDummy[q6] = conjure_aux2 | q6 : int(1..4)]), - sum([toInt(s_ExplicitVarSizeWithDummy[q6] != 5) | q6 : int(1..4)]) = 0 -> conjure_aux2 = 1, - conjure_aux2 = 3, - sum([toInt(s_ExplicitVarSizeWithDummy[q6] != 5) | q6 : int(1..4)]) > 0, - and([s_ExplicitVarSizeWithDummy[q1] < s_ExplicitVarSizeWithDummy[q1 + 1] \/ s_ExplicitVarSizeWithDummy[q1] = 5 - | q1 : int(1..3)]), - and([s_ExplicitVarSizeWithDummy[q2] = 5 -> s_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..3)]) - diff --git a/tests/exhaustive/basic/name-reuse/expected/model_2_3-solution000001.solution b/tests/exhaustive/basic/name-reuse/expected/model_2_3-solution000001.solution deleted file mode 100644 index d4f1477569..0000000000 --- a/tests/exhaustive/basic/name-reuse/expected/model_2_3-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting conjure_aux1 be 1 -letting s be {3} diff --git a/tests/exhaustive/basic/name-reuse/expected/model_2_3-solution000002.solution b/tests/exhaustive/basic/name-reuse/expected/model_2_3-solution000002.solution deleted file mode 100644 index ab91f42e83..0000000000 --- a/tests/exhaustive/basic/name-reuse/expected/model_2_3-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting conjure_aux1 be 1 -letting s be {3, 4} diff --git a/tests/exhaustive/basic/name-reuse/expected/model_2_3.eprime b/tests/exhaustive/basic/name-reuse/expected/model_2_3.eprime deleted file mode 100644 index 91c6277604..0000000000 --- a/tests/exhaustive/basic/name-reuse/expected/model_2_3.eprime +++ /dev/null @@ -1,34 +0,0 @@ -language ESSENCE' 1.0 - -find conjure_aux1: int(1) -find s_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -find s_ExplicitVarSizeWithMarker_Marker: int(0..4) -find s_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -find conjure_aux2: int(1..5) -branching on - [conjure_aux1, s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithMarker_Values, s_ExplicitVarSizeWithDummy] -such that - and([s_ExplicitVarSizeWithDummy[q17] != 5 -> s_ExplicitVarSizeWithDummy[q17] >= conjure_aux2 | q17 : int(1..4)]), - sum([toInt(s_ExplicitVarSizeWithDummy[q17] != 5) | q17 : int(1..4)]) > 0 -> - or([s_ExplicitVarSizeWithDummy[q17] != 5 /\ s_ExplicitVarSizeWithDummy[q17] = conjure_aux2 | q17 : int(1..4)]), - sum([toInt(s_ExplicitVarSizeWithDummy[q17] != 5) | q17 : int(1..4)]) = 0 -> conjure_aux2 = 1, - conjure_aux2 = 3, - sum([toInt(s_ExplicitVarSizeWithDummy[q17] != 5) | q17 : int(1..4)]) > 0, - and([s_ExplicitVarSizeWithDummy[q1] < s_ExplicitVarSizeWithDummy[q1 + 1] \/ s_ExplicitVarSizeWithDummy[q1] = 5 - | q1 : int(1..3)]), - and([s_ExplicitVarSizeWithDummy[q2] = 5 -> s_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..3)]), - and([q5 + 1 <= s_ExplicitVarSizeWithMarker_Marker -> - s_ExplicitVarSizeWithMarker_Values[q5] < s_ExplicitVarSizeWithMarker_Values[q5 + 1] - | q5 : int(1..3)]), - and([q6 > s_ExplicitVarSizeWithMarker_Marker -> s_ExplicitVarSizeWithMarker_Values[q6] = 1 | q6 : int(1..4)]), - and([q9 <= s_ExplicitVarSizeWithMarker_Marker -> - or([s_ExplicitVarSizeWithDummy[q11] != 5 /\ - s_ExplicitVarSizeWithDummy[q11] = s_ExplicitVarSizeWithMarker_Values[q9] - | q11 : int(1..4)]) - | q9 : int(1..4)]), - and([s_ExplicitVarSizeWithDummy[q13] != 5 -> - or([q15 <= s_ExplicitVarSizeWithMarker_Marker /\ - s_ExplicitVarSizeWithMarker_Values[q15] = s_ExplicitVarSizeWithDummy[q13] - | q15 : int(1..4)]) - | q13 : int(1..4)]) - diff --git a/tests/exhaustive/basic/name-reuse/expected/model_2_4-solution000001.solution b/tests/exhaustive/basic/name-reuse/expected/model_2_4-solution000001.solution deleted file mode 100644 index d4f1477569..0000000000 --- a/tests/exhaustive/basic/name-reuse/expected/model_2_4-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting conjure_aux1 be 1 -letting s be {3} diff --git a/tests/exhaustive/basic/name-reuse/expected/model_2_4-solution000002.solution b/tests/exhaustive/basic/name-reuse/expected/model_2_4-solution000002.solution deleted file mode 100644 index ab91f42e83..0000000000 --- a/tests/exhaustive/basic/name-reuse/expected/model_2_4-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting conjure_aux1 be 1 -letting s be {3, 4} diff --git a/tests/exhaustive/basic/name-reuse/expected/model_2_4.eprime b/tests/exhaustive/basic/name-reuse/expected/model_2_4.eprime deleted file mode 100644 index a42a0dabce..0000000000 --- a/tests/exhaustive/basic/name-reuse/expected/model_2_4.eprime +++ /dev/null @@ -1,35 +0,0 @@ -language ESSENCE' 1.0 - -find conjure_aux1: int(1) -find s_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -find s_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find s_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -find conjure_aux2: int(1..5) -branching on - [conjure_aux1, s_ExplicitVarSizeWithFlags_Flags, s_ExplicitVarSizeWithFlags_Values, s_ExplicitVarSizeWithDummy] -such that - and([s_ExplicitVarSizeWithDummy[q19] != 5 -> s_ExplicitVarSizeWithDummy[q19] >= conjure_aux2 | q19 : int(1..4)]), - sum([toInt(s_ExplicitVarSizeWithDummy[q19] != 5) | q19 : int(1..4)]) > 0 -> - or([s_ExplicitVarSizeWithDummy[q19] != 5 /\ s_ExplicitVarSizeWithDummy[q19] = conjure_aux2 | q19 : int(1..4)]), - sum([toInt(s_ExplicitVarSizeWithDummy[q19] != 5) | q19 : int(1..4)]) = 0 -> conjure_aux2 = 1, - conjure_aux2 = 3, - sum([toInt(s_ExplicitVarSizeWithDummy[q19] != 5) | q19 : int(1..4)]) > 0, - and([s_ExplicitVarSizeWithDummy[q1] < s_ExplicitVarSizeWithDummy[q1 + 1] \/ s_ExplicitVarSizeWithDummy[q1] = 5 - | q1 : int(1..3)]), - and([s_ExplicitVarSizeWithDummy[q2] = 5 -> s_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..3)]), - and([s_ExplicitVarSizeWithFlags_Flags[q5 + 1] -> - s_ExplicitVarSizeWithFlags_Values[q5] < s_ExplicitVarSizeWithFlags_Values[q5 + 1] - | q5 : int(1..3)]), - and([s_ExplicitVarSizeWithFlags_Flags[q6] = false -> s_ExplicitVarSizeWithFlags_Values[q6] = 1 | q6 : int(1..4)]), - and([s_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> s_ExplicitVarSizeWithFlags_Flags[q7] | q7 : int(1..3)]), - and([s_ExplicitVarSizeWithFlags_Flags[q11] -> - or([s_ExplicitVarSizeWithDummy[q13] != 5 /\ - s_ExplicitVarSizeWithDummy[q13] = s_ExplicitVarSizeWithFlags_Values[q11] - | q13 : int(1..4)]) - | q11 : int(1..4)]), - and([s_ExplicitVarSizeWithDummy[q15] != 5 -> - or([s_ExplicitVarSizeWithFlags_Flags[q17] /\ - s_ExplicitVarSizeWithFlags_Values[q17] = s_ExplicitVarSizeWithDummy[q15] - | q17 : int(1..4)]) - | q15 : int(1..4)]) - diff --git a/tests/exhaustive/basic/name-reuse/expected/model_3_1-solution000001.solution b/tests/exhaustive/basic/name-reuse/expected/model_3_1-solution000001.solution deleted file mode 100644 index d4f1477569..0000000000 --- a/tests/exhaustive/basic/name-reuse/expected/model_3_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting conjure_aux1 be 1 -letting s be {3} diff --git a/tests/exhaustive/basic/name-reuse/expected/model_3_1-solution000002.solution b/tests/exhaustive/basic/name-reuse/expected/model_3_1-solution000002.solution deleted file mode 100644 index ab91f42e83..0000000000 --- a/tests/exhaustive/basic/name-reuse/expected/model_3_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting conjure_aux1 be 1 -letting s be {3, 4} diff --git a/tests/exhaustive/basic/name-reuse/expected/model_3_1.eprime b/tests/exhaustive/basic/name-reuse/expected/model_3_1.eprime deleted file mode 100644 index 0f6a2844e2..0000000000 --- a/tests/exhaustive/basic/name-reuse/expected/model_3_1.eprime +++ /dev/null @@ -1,27 +0,0 @@ -language ESSENCE' 1.0 - -find conjure_aux1: int(1) -find s_ExplicitVarSizeWithMarker_Marker: int(0..4) -find s_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -find s_Occurrence: matrix indexed by [int(1..4)] of bool -find conjure_aux2: int(1..4) -branching on [conjure_aux1, s_Occurrence, s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithMarker_Values] -such that - and([q6 <= s_ExplicitVarSizeWithMarker_Marker -> s_ExplicitVarSizeWithMarker_Values[q6] >= conjure_aux2 - | q6 : int(1..4)]), - sum([toInt(q6 <= s_ExplicitVarSizeWithMarker_Marker) | q6 : int(1..4)]) > 0 -> - or([q6 <= s_ExplicitVarSizeWithMarker_Marker /\ s_ExplicitVarSizeWithMarker_Values[q6] = conjure_aux2 - | q6 : int(1..4)]), - sum([toInt(q6 <= s_ExplicitVarSizeWithMarker_Marker) | q6 : int(1..4)]) = 0 -> conjure_aux2 = 1, - conjure_aux2 = 3, - sum([toInt(q6 <= s_ExplicitVarSizeWithMarker_Marker) | q6 : int(1..4)]) > 0, - and([q1 + 1 <= s_ExplicitVarSizeWithMarker_Marker -> - s_ExplicitVarSizeWithMarker_Values[q1] < s_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..3)]), - and([q2 > s_ExplicitVarSizeWithMarker_Marker -> s_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..4)]), - and([s_Occurrence[q7] -> - or([q9 <= s_ExplicitVarSizeWithMarker_Marker /\ s_ExplicitVarSizeWithMarker_Values[q9] = q7 | q9 : int(1..4)]) - | q7 : int(1..4)]), - and([q11 <= s_ExplicitVarSizeWithMarker_Marker -> s_Occurrence[s_ExplicitVarSizeWithMarker_Values[q11]] - | q11 : int(1..4)]) - diff --git a/tests/exhaustive/basic/name-reuse/expected/model_3_2-solution000001.solution b/tests/exhaustive/basic/name-reuse/expected/model_3_2-solution000001.solution deleted file mode 100644 index ab91f42e83..0000000000 --- a/tests/exhaustive/basic/name-reuse/expected/model_3_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting conjure_aux1 be 1 -letting s be {3, 4} diff --git a/tests/exhaustive/basic/name-reuse/expected/model_3_2-solution000002.solution b/tests/exhaustive/basic/name-reuse/expected/model_3_2-solution000002.solution deleted file mode 100644 index d4f1477569..0000000000 --- a/tests/exhaustive/basic/name-reuse/expected/model_3_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting conjure_aux1 be 1 -letting s be {3} diff --git a/tests/exhaustive/basic/name-reuse/expected/model_3_2.eprime b/tests/exhaustive/basic/name-reuse/expected/model_3_2.eprime deleted file mode 100644 index ae3b9a8a9d..0000000000 --- a/tests/exhaustive/basic/name-reuse/expected/model_3_2.eprime +++ /dev/null @@ -1,36 +0,0 @@ -language ESSENCE' 1.0 - -find conjure_aux1: int(1) -find s_ExplicitVarSizeWithMarker_Marker: int(0..4) -find s_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -find s_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -find conjure_aux2: int(1..4) -branching on - [conjure_aux1, s_ExplicitVarSizeWithDummy, s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithMarker_Values] -such that - and([q17 <= s_ExplicitVarSizeWithMarker_Marker -> s_ExplicitVarSizeWithMarker_Values[q17] >= conjure_aux2 - | q17 : int(1..4)]), - sum([toInt(q17 <= s_ExplicitVarSizeWithMarker_Marker) | q17 : int(1..4)]) > 0 -> - or([q17 <= s_ExplicitVarSizeWithMarker_Marker /\ s_ExplicitVarSizeWithMarker_Values[q17] = conjure_aux2 - | q17 : int(1..4)]), - sum([toInt(q17 <= s_ExplicitVarSizeWithMarker_Marker) | q17 : int(1..4)]) = 0 -> conjure_aux2 = 1, - conjure_aux2 = 3, - sum([toInt(q17 <= s_ExplicitVarSizeWithMarker_Marker) | q17 : int(1..4)]) > 0, - and([q1 + 1 <= s_ExplicitVarSizeWithMarker_Marker -> - s_ExplicitVarSizeWithMarker_Values[q1] < s_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..3)]), - and([q2 > s_ExplicitVarSizeWithMarker_Marker -> s_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..4)]), - and([s_ExplicitVarSizeWithDummy[q4] < s_ExplicitVarSizeWithDummy[q4 + 1] \/ s_ExplicitVarSizeWithDummy[q4] = 5 - | q4 : int(1..3)]), - and([s_ExplicitVarSizeWithDummy[q5] = 5 -> s_ExplicitVarSizeWithDummy[q5 + 1] = 5 | q5 : int(1..3)]), - and([s_ExplicitVarSizeWithDummy[q9] != 5 -> - or([q11 <= s_ExplicitVarSizeWithMarker_Marker /\ - s_ExplicitVarSizeWithMarker_Values[q11] = s_ExplicitVarSizeWithDummy[q9] - | q11 : int(1..4)]) - | q9 : int(1..4)]), - and([q13 <= s_ExplicitVarSizeWithMarker_Marker -> - or([s_ExplicitVarSizeWithDummy[q15] != 5 /\ - s_ExplicitVarSizeWithDummy[q15] = s_ExplicitVarSizeWithMarker_Values[q13] - | q15 : int(1..4)]) - | q13 : int(1..4)]) - diff --git a/tests/exhaustive/basic/name-reuse/expected/model_3_3-solution000001.solution b/tests/exhaustive/basic/name-reuse/expected/model_3_3-solution000001.solution deleted file mode 100644 index d4f1477569..0000000000 --- a/tests/exhaustive/basic/name-reuse/expected/model_3_3-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting conjure_aux1 be 1 -letting s be {3} diff --git a/tests/exhaustive/basic/name-reuse/expected/model_3_3-solution000002.solution b/tests/exhaustive/basic/name-reuse/expected/model_3_3-solution000002.solution deleted file mode 100644 index ab91f42e83..0000000000 --- a/tests/exhaustive/basic/name-reuse/expected/model_3_3-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting conjure_aux1 be 1 -letting s be {3, 4} diff --git a/tests/exhaustive/basic/name-reuse/expected/model_3_3.eprime b/tests/exhaustive/basic/name-reuse/expected/model_3_3.eprime deleted file mode 100644 index ce6a4c6421..0000000000 --- a/tests/exhaustive/basic/name-reuse/expected/model_3_3.eprime +++ /dev/null @@ -1,21 +0,0 @@ -language ESSENCE' 1.0 - -find conjure_aux1: int(1) -find s_ExplicitVarSizeWithMarker_Marker: int(0..4) -find s_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -find conjure_aux2: int(1..4) -branching on [conjure_aux1, s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithMarker_Values] -such that - and([q5 <= s_ExplicitVarSizeWithMarker_Marker -> s_ExplicitVarSizeWithMarker_Values[q5] >= conjure_aux2 - | q5 : int(1..4)]), - sum([toInt(q5 <= s_ExplicitVarSizeWithMarker_Marker) | q5 : int(1..4)]) > 0 -> - or([q5 <= s_ExplicitVarSizeWithMarker_Marker /\ s_ExplicitVarSizeWithMarker_Values[q5] = conjure_aux2 - | q5 : int(1..4)]), - sum([toInt(q5 <= s_ExplicitVarSizeWithMarker_Marker) | q5 : int(1..4)]) = 0 -> conjure_aux2 = 1, - conjure_aux2 = 3, - sum([toInt(q5 <= s_ExplicitVarSizeWithMarker_Marker) | q5 : int(1..4)]) > 0, - and([q1 + 1 <= s_ExplicitVarSizeWithMarker_Marker -> - s_ExplicitVarSizeWithMarker_Values[q1] < s_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..3)]), - and([q2 > s_ExplicitVarSizeWithMarker_Marker -> s_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..4)]) - diff --git a/tests/exhaustive/basic/name-reuse/expected/model_3_4-solution000001.solution b/tests/exhaustive/basic/name-reuse/expected/model_3_4-solution000001.solution deleted file mode 100644 index d4f1477569..0000000000 --- a/tests/exhaustive/basic/name-reuse/expected/model_3_4-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting conjure_aux1 be 1 -letting s be {3} diff --git a/tests/exhaustive/basic/name-reuse/expected/model_3_4-solution000002.solution b/tests/exhaustive/basic/name-reuse/expected/model_3_4-solution000002.solution deleted file mode 100644 index ab91f42e83..0000000000 --- a/tests/exhaustive/basic/name-reuse/expected/model_3_4-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting conjure_aux1 be 1 -letting s be {3, 4} diff --git a/tests/exhaustive/basic/name-reuse/expected/model_3_4.eprime b/tests/exhaustive/basic/name-reuse/expected/model_3_4.eprime deleted file mode 100644 index a98bd89235..0000000000 --- a/tests/exhaustive/basic/name-reuse/expected/model_3_4.eprime +++ /dev/null @@ -1,40 +0,0 @@ -language ESSENCE' 1.0 - -find conjure_aux1: int(1) -find s_ExplicitVarSizeWithMarker_Marker: int(0..4) -find s_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -find s_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find s_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -find conjure_aux2: int(1..4) -branching on - [conjure_aux1, s_ExplicitVarSizeWithFlags_Flags, s_ExplicitVarSizeWithFlags_Values, - s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithMarker_Values] -such that - and([q18 <= s_ExplicitVarSizeWithMarker_Marker -> s_ExplicitVarSizeWithMarker_Values[q18] >= conjure_aux2 - | q18 : int(1..4)]), - sum([toInt(q18 <= s_ExplicitVarSizeWithMarker_Marker) | q18 : int(1..4)]) > 0 -> - or([q18 <= s_ExplicitVarSizeWithMarker_Marker /\ s_ExplicitVarSizeWithMarker_Values[q18] = conjure_aux2 - | q18 : int(1..4)]), - sum([toInt(q18 <= s_ExplicitVarSizeWithMarker_Marker) | q18 : int(1..4)]) = 0 -> conjure_aux2 = 1, - conjure_aux2 = 3, - sum([toInt(q18 <= s_ExplicitVarSizeWithMarker_Marker) | q18 : int(1..4)]) > 0, - and([q1 + 1 <= s_ExplicitVarSizeWithMarker_Marker -> - s_ExplicitVarSizeWithMarker_Values[q1] < s_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..3)]), - and([q2 > s_ExplicitVarSizeWithMarker_Marker -> s_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..4)]), - and([s_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> - s_ExplicitVarSizeWithFlags_Values[q4] < s_ExplicitVarSizeWithFlags_Values[q4 + 1] - | q4 : int(1..3)]), - and([s_ExplicitVarSizeWithFlags_Flags[q5] = false -> s_ExplicitVarSizeWithFlags_Values[q5] = 1 | q5 : int(1..4)]), - and([s_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> s_ExplicitVarSizeWithFlags_Flags[q6] | q6 : int(1..3)]), - and([s_ExplicitVarSizeWithFlags_Flags[q10] -> - or([q12 <= s_ExplicitVarSizeWithMarker_Marker /\ - s_ExplicitVarSizeWithMarker_Values[q12] = s_ExplicitVarSizeWithFlags_Values[q10] - | q12 : int(1..4)]) - | q10 : int(1..4)]), - and([q14 <= s_ExplicitVarSizeWithMarker_Marker -> - or([s_ExplicitVarSizeWithFlags_Flags[q16] /\ - s_ExplicitVarSizeWithFlags_Values[q16] = s_ExplicitVarSizeWithMarker_Values[q14] - | q16 : int(1..4)]) - | q14 : int(1..4)]) - diff --git a/tests/exhaustive/basic/name-reuse/expected/model_4_1-solution000001.solution b/tests/exhaustive/basic/name-reuse/expected/model_4_1-solution000001.solution deleted file mode 100644 index d4f1477569..0000000000 --- a/tests/exhaustive/basic/name-reuse/expected/model_4_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting conjure_aux1 be 1 -letting s be {3} diff --git a/tests/exhaustive/basic/name-reuse/expected/model_4_1-solution000002.solution b/tests/exhaustive/basic/name-reuse/expected/model_4_1-solution000002.solution deleted file mode 100644 index ab91f42e83..0000000000 --- a/tests/exhaustive/basic/name-reuse/expected/model_4_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting conjure_aux1 be 1 -letting s be {3, 4} diff --git a/tests/exhaustive/basic/name-reuse/expected/model_4_1.eprime b/tests/exhaustive/basic/name-reuse/expected/model_4_1.eprime deleted file mode 100644 index 598929e0aa..0000000000 --- a/tests/exhaustive/basic/name-reuse/expected/model_4_1.eprime +++ /dev/null @@ -1,28 +0,0 @@ -language ESSENCE' 1.0 - -find conjure_aux1: int(1) -find s_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find s_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -find s_Occurrence: matrix indexed by [int(1..4)] of bool -find conjure_aux2: int(1..4) -branching on [conjure_aux1, s_Occurrence, s_ExplicitVarSizeWithFlags_Flags, s_ExplicitVarSizeWithFlags_Values] -such that - and([s_ExplicitVarSizeWithFlags_Flags[q13] -> s_ExplicitVarSizeWithFlags_Values[q13] >= conjure_aux2 - | q13 : int(1..4)]), - sum([toInt(s_ExplicitVarSizeWithFlags_Flags[q13]) | q13 : int(1..4)]) > 0 -> - or([s_ExplicitVarSizeWithFlags_Flags[q13] /\ s_ExplicitVarSizeWithFlags_Values[q13] = conjure_aux2 - | q13 : int(1..4)]), - sum([toInt(s_ExplicitVarSizeWithFlags_Flags[q13]) | q13 : int(1..4)]) = 0 -> conjure_aux2 = 1, - conjure_aux2 = 3, - sum([toInt(s_ExplicitVarSizeWithFlags_Flags[q13]) | q13 : int(1..4)]) > 0, - and([s_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - s_ExplicitVarSizeWithFlags_Values[q1] < s_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..3)]), - and([s_ExplicitVarSizeWithFlags_Flags[q2] = false -> s_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..4)]), - and([s_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> s_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), - and([s_Occurrence[q7] -> - or([s_ExplicitVarSizeWithFlags_Flags[q9] /\ s_ExplicitVarSizeWithFlags_Values[q9] = q7 | q9 : int(1..4)]) - | q7 : int(1..4)]), - and([s_ExplicitVarSizeWithFlags_Flags[q11] -> s_Occurrence[s_ExplicitVarSizeWithFlags_Values[q11]] - | q11 : int(1..4)]) - diff --git a/tests/exhaustive/basic/name-reuse/expected/model_4_2-solution000001.solution b/tests/exhaustive/basic/name-reuse/expected/model_4_2-solution000001.solution deleted file mode 100644 index ab91f42e83..0000000000 --- a/tests/exhaustive/basic/name-reuse/expected/model_4_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting conjure_aux1 be 1 -letting s be {3, 4} diff --git a/tests/exhaustive/basic/name-reuse/expected/model_4_2-solution000002.solution b/tests/exhaustive/basic/name-reuse/expected/model_4_2-solution000002.solution deleted file mode 100644 index d4f1477569..0000000000 --- a/tests/exhaustive/basic/name-reuse/expected/model_4_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting conjure_aux1 be 1 -letting s be {3} diff --git a/tests/exhaustive/basic/name-reuse/expected/model_4_2.eprime b/tests/exhaustive/basic/name-reuse/expected/model_4_2.eprime deleted file mode 100644 index 41f3fb08cd..0000000000 --- a/tests/exhaustive/basic/name-reuse/expected/model_4_2.eprime +++ /dev/null @@ -1,37 +0,0 @@ -language ESSENCE' 1.0 - -find conjure_aux1: int(1) -find s_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find s_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -find s_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -find conjure_aux2: int(1..4) -branching on - [conjure_aux1, s_ExplicitVarSizeWithDummy, s_ExplicitVarSizeWithFlags_Flags, s_ExplicitVarSizeWithFlags_Values] -such that - and([s_ExplicitVarSizeWithFlags_Flags[q19] -> s_ExplicitVarSizeWithFlags_Values[q19] >= conjure_aux2 - | q19 : int(1..4)]), - sum([toInt(s_ExplicitVarSizeWithFlags_Flags[q19]) | q19 : int(1..4)]) > 0 -> - or([s_ExplicitVarSizeWithFlags_Flags[q19] /\ s_ExplicitVarSizeWithFlags_Values[q19] = conjure_aux2 - | q19 : int(1..4)]), - sum([toInt(s_ExplicitVarSizeWithFlags_Flags[q19]) | q19 : int(1..4)]) = 0 -> conjure_aux2 = 1, - conjure_aux2 = 3, - sum([toInt(s_ExplicitVarSizeWithFlags_Flags[q19]) | q19 : int(1..4)]) > 0, - and([s_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - s_ExplicitVarSizeWithFlags_Values[q1] < s_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..3)]), - and([s_ExplicitVarSizeWithFlags_Flags[q2] = false -> s_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..4)]), - and([s_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> s_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), - and([s_ExplicitVarSizeWithDummy[q6] < s_ExplicitVarSizeWithDummy[q6 + 1] \/ s_ExplicitVarSizeWithDummy[q6] = 5 - | q6 : int(1..3)]), - and([s_ExplicitVarSizeWithDummy[q7] = 5 -> s_ExplicitVarSizeWithDummy[q7 + 1] = 5 | q7 : int(1..3)]), - and([s_ExplicitVarSizeWithDummy[q11] != 5 -> - or([s_ExplicitVarSizeWithFlags_Flags[q13] /\ - s_ExplicitVarSizeWithFlags_Values[q13] = s_ExplicitVarSizeWithDummy[q11] - | q13 : int(1..4)]) - | q11 : int(1..4)]), - and([s_ExplicitVarSizeWithFlags_Flags[q15] -> - or([s_ExplicitVarSizeWithDummy[q17] != 5 /\ - s_ExplicitVarSizeWithDummy[q17] = s_ExplicitVarSizeWithFlags_Values[q15] - | q17 : int(1..4)]) - | q15 : int(1..4)]) - diff --git a/tests/exhaustive/basic/name-reuse/expected/model_4_3-solution000001.solution b/tests/exhaustive/basic/name-reuse/expected/model_4_3-solution000001.solution deleted file mode 100644 index d4f1477569..0000000000 --- a/tests/exhaustive/basic/name-reuse/expected/model_4_3-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting conjure_aux1 be 1 -letting s be {3} diff --git a/tests/exhaustive/basic/name-reuse/expected/model_4_3-solution000002.solution b/tests/exhaustive/basic/name-reuse/expected/model_4_3-solution000002.solution deleted file mode 100644 index ab91f42e83..0000000000 --- a/tests/exhaustive/basic/name-reuse/expected/model_4_3-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting conjure_aux1 be 1 -letting s be {3, 4} diff --git a/tests/exhaustive/basic/name-reuse/expected/model_4_3.eprime b/tests/exhaustive/basic/name-reuse/expected/model_4_3.eprime deleted file mode 100644 index 36aeadc30e..0000000000 --- a/tests/exhaustive/basic/name-reuse/expected/model_4_3.eprime +++ /dev/null @@ -1,40 +0,0 @@ -language ESSENCE' 1.0 - -find conjure_aux1: int(1) -find s_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find s_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -find s_ExplicitVarSizeWithMarker_Marker: int(0..4) -find s_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -find conjure_aux2: int(1..4) -branching on - [conjure_aux1, s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithMarker_Values, - s_ExplicitVarSizeWithFlags_Flags, s_ExplicitVarSizeWithFlags_Values] -such that - and([s_ExplicitVarSizeWithFlags_Flags[q18] -> s_ExplicitVarSizeWithFlags_Values[q18] >= conjure_aux2 - | q18 : int(1..4)]), - sum([toInt(s_ExplicitVarSizeWithFlags_Flags[q18]) | q18 : int(1..4)]) > 0 -> - or([s_ExplicitVarSizeWithFlags_Flags[q18] /\ s_ExplicitVarSizeWithFlags_Values[q18] = conjure_aux2 - | q18 : int(1..4)]), - sum([toInt(s_ExplicitVarSizeWithFlags_Flags[q18]) | q18 : int(1..4)]) = 0 -> conjure_aux2 = 1, - conjure_aux2 = 3, - sum([toInt(s_ExplicitVarSizeWithFlags_Flags[q18]) | q18 : int(1..4)]) > 0, - and([s_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - s_ExplicitVarSizeWithFlags_Values[q1] < s_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..3)]), - and([s_ExplicitVarSizeWithFlags_Flags[q2] = false -> s_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..4)]), - and([s_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> s_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), - and([q6 + 1 <= s_ExplicitVarSizeWithMarker_Marker -> - s_ExplicitVarSizeWithMarker_Values[q6] < s_ExplicitVarSizeWithMarker_Values[q6 + 1] - | q6 : int(1..3)]), - and([q7 > s_ExplicitVarSizeWithMarker_Marker -> s_ExplicitVarSizeWithMarker_Values[q7] = 1 | q7 : int(1..4)]), - and([q10 <= s_ExplicitVarSizeWithMarker_Marker -> - or([s_ExplicitVarSizeWithFlags_Flags[q12] /\ - s_ExplicitVarSizeWithFlags_Values[q12] = s_ExplicitVarSizeWithMarker_Values[q10] - | q12 : int(1..4)]) - | q10 : int(1..4)]), - and([s_ExplicitVarSizeWithFlags_Flags[q14] -> - or([q16 <= s_ExplicitVarSizeWithMarker_Marker /\ - s_ExplicitVarSizeWithMarker_Values[q16] = s_ExplicitVarSizeWithFlags_Values[q14] - | q16 : int(1..4)]) - | q14 : int(1..4)]) - diff --git a/tests/exhaustive/basic/name-reuse/expected/model_4_4-solution000001.solution b/tests/exhaustive/basic/name-reuse/expected/model_4_4-solution000001.solution deleted file mode 100644 index d4f1477569..0000000000 --- a/tests/exhaustive/basic/name-reuse/expected/model_4_4-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting conjure_aux1 be 1 -letting s be {3} diff --git a/tests/exhaustive/basic/name-reuse/expected/model_4_4-solution000002.solution b/tests/exhaustive/basic/name-reuse/expected/model_4_4-solution000002.solution deleted file mode 100644 index ab91f42e83..0000000000 --- a/tests/exhaustive/basic/name-reuse/expected/model_4_4-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting conjure_aux1 be 1 -letting s be {3, 4} diff --git a/tests/exhaustive/basic/name-reuse/expected/model_4_4.eprime b/tests/exhaustive/basic/name-reuse/expected/model_4_4.eprime deleted file mode 100644 index 1347ac40de..0000000000 --- a/tests/exhaustive/basic/name-reuse/expected/model_4_4.eprime +++ /dev/null @@ -1,21 +0,0 @@ -language ESSENCE' 1.0 - -find conjure_aux1: int(1) -find s_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find s_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -find conjure_aux2: int(1..4) -branching on [conjure_aux1, s_ExplicitVarSizeWithFlags_Flags, s_ExplicitVarSizeWithFlags_Values] -such that - and([s_ExplicitVarSizeWithFlags_Flags[q7] -> s_ExplicitVarSizeWithFlags_Values[q7] >= conjure_aux2 - | q7 : int(1..4)]), - sum([toInt(s_ExplicitVarSizeWithFlags_Flags[q7]) | q7 : int(1..4)]) > 0 -> - or([s_ExplicitVarSizeWithFlags_Flags[q7] /\ s_ExplicitVarSizeWithFlags_Values[q7] = conjure_aux2 | q7 : int(1..4)]), - sum([toInt(s_ExplicitVarSizeWithFlags_Flags[q7]) | q7 : int(1..4)]) = 0 -> conjure_aux2 = 1, - conjure_aux2 = 3, - sum([toInt(s_ExplicitVarSizeWithFlags_Flags[q7]) | q7 : int(1..4)]) > 0, - and([s_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - s_ExplicitVarSizeWithFlags_Values[q1] < s_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..3)]), - and([s_ExplicitVarSizeWithFlags_Flags[q2] = false -> s_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..4)]), - and([s_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> s_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]) - diff --git a/tests/exhaustive/basic/partition_05_1/expected/model_1-solution000001.solution b/tests/exhaustive/basic/partition_05_1/expected/model_1-solution000001.solution deleted file mode 100644 index b616543ee7..0000000000 --- a/tests/exhaustive/basic/partition_05_1/expected/model_1-solution000001.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be partition({1, 3}, {2, 4}) -$ Visualisation for x -$ 1 3 -$ 2 4 - diff --git a/tests/exhaustive/basic/partition_05_1/expected/model_1.eprime b/tests/exhaustive/basic/partition_05_1/expected/model_1.eprime deleted file mode 100644 index 457d853645..0000000000 --- a/tests/exhaustive/basic/partition_05_1/expected/model_1.eprime +++ /dev/null @@ -1,48 +0,0 @@ -language ESSENCE' 1.0 - -find x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker: int(0..4) -find x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence: matrix indexed by [int(1..4), int(1..4)] of bool -branching on - [x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker, - x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence] -such that - or([q27 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ - (x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q27, 1] /\ - x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q27, 3]) - | q27 : int(1..4)]), - and([q34 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> - !(x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q34, 1] /\ - x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q34, 2]) - | q34 : int(1..4)]), - and([1 = - sum([toInt(q16 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ - x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q16, q1]) - | q16 : int(1..4)]) - | q1 : int(1..4)]), - and([q17 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ - q18 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker - -> - sum([toInt(x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q17, q19]) | q19 : int(1..4)]) = - sum([toInt(x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q18, q20]) | q20 : int(1..4)]) - | q17 : int(1..4), q18 : int(1..4)]), - and([q21 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> - sum([toInt(x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q21, q22]) | q22 : int(1..4)]) >= 1 - | q21 : int(1..4)]), - and([q6 + 1 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> - [-toInt(x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q6, q11]) | q11 : int(1..4)] x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> - and([x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q7, q13] = false | q13 : int(1..4)]) - | q7 : int(1..4)]), - x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker <= 4, - and([q8 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> - sum([toInt(x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q8, q9]) | q9 : int(1..4)]) <= 4 - | q8 : int(1..4)]), - 4 = - sum([toInt(q14 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker) * - catchUndef(sum([toInt(x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q14, q15]) - | q15 : int(1..4)]), - 0) - | q14 : int(1..4)]) - diff --git a/tests/exhaustive/basic/partition_05_1/expected/model_2-solution000001.solution b/tests/exhaustive/basic/partition_05_1/expected/model_2-solution000001.solution deleted file mode 100644 index b616543ee7..0000000000 --- a/tests/exhaustive/basic/partition_05_1/expected/model_2-solution000001.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be partition({1, 3}, {2, 4}) -$ Visualisation for x -$ 1 3 -$ 2 4 - diff --git a/tests/exhaustive/basic/partition_05_1/expected/model_2.eprime b/tests/exhaustive/basic/partition_05_1/expected/model_2.eprime deleted file mode 100644 index d385f064be..0000000000 --- a/tests/exhaustive/basic/partition_05_1/expected/model_2.eprime +++ /dev/null @@ -1,83 +0,0 @@ -language ESSENCE' 1.0 - -find x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker: int(0..4) -find x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy: - matrix indexed by [int(1..4), int(1..4)] of int(1..5) -branching on - [x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker, - x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy] -such that - or([q35 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ - (or([x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q35, q39] != 5 /\ - x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q35, q39] = 1 - | q39 : int(1..4)]) - /\ - or([x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q35, q41] != 5 /\ - x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q35, q41] = 3 - | q41 : int(1..4)])) - | q35 : int(1..4)]), - and([q46 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - !(or([x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q46, q50] != 5 /\ - x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q46, q50] = 1 - | q50 : int(1..4)]) - /\ - or([x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q46, q52] != 5 /\ - x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q46, q52] = 2 - | q52 : int(1..4)])) - | q46 : int(1..4)]), - alldifferent_except([toInt(q20 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ - x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q20, q21] != - 5) - * - catchUndef(x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q20, q21], - 0) - | q20 : int(1..4), q21 : int(1..4)], - 0), - and([q22 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ - q23 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker - -> - sum([toInt(x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q22, q25] != 5) - | q25 : int(1..4)]) - = - sum([toInt(x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q23, q27] != 5) - | q27 : int(1..4)]) - | q22 : int(1..4), q23 : int(1..4)]), - and([q28 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - sum([toInt(x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q28, q30] != 5) - | q30 : int(1..4)]) - >= 1 - | q28 : int(1..4)]), - and([q6 + 1 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - [x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q6, q14] | q14 : int(1..4)] x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - and([x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q7, q19] = 1 - | q19 : int(1..4)]) - | q7 : int(1..4)]), - x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker <= 4, - and([q8 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - and([x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q8, q9] < - x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q8, q9 + 1] - \/ x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q8, q9] = 5 - | q9 : int(1..3)]) - | q8 : int(1..4)]), - and([q8 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - and([x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q8, q10] = 5 -> - x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q8, q10 + 1] = 5 - | q10 : int(1..3)]) - | q8 : int(1..4)]), - and([q8 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - sum([toInt(x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q8, q11] != 5) - | q11 : int(1..4)]) - <= 4 - | q8 : int(1..4)]), - 4 = - sum([toInt(q16 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker) * - catchUndef(sum([toInt(x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q16, q18] != - 5) - | q18 : int(1..4)]), - 0) - | q16 : int(1..4)]) - diff --git a/tests/exhaustive/basic/partition_05_1/expected/model_3-solution000001.solution b/tests/exhaustive/basic/partition_05_1/expected/model_3-solution000001.solution deleted file mode 100644 index b616543ee7..0000000000 --- a/tests/exhaustive/basic/partition_05_1/expected/model_3-solution000001.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be partition({1, 3}, {2, 4}) -$ Visualisation for x -$ 1 3 -$ 2 4 - diff --git a/tests/exhaustive/basic/partition_05_1/expected/model_3.eprime b/tests/exhaustive/basic/partition_05_1/expected/model_3.eprime deleted file mode 100644 index b56ece4838..0000000000 --- a/tests/exhaustive/basic/partition_05_1/expected/model_3.eprime +++ /dev/null @@ -1,90 +0,0 @@ -language ESSENCE' 1.0 - -find x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker: int(0..4) -find x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker: - matrix indexed by [int(1..4)] of int(0..4) -find x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values: - matrix indexed by [int(1..4), int(1..4)] of int(1..4) -branching on - [x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker, - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker, - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values] -such that - or([q26 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - (or([q30 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q26] /\ - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q26, q30] = 1 - | q30 : int(1..4)]) - /\ - or([q32 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q26] /\ - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q26, q32] = 3 - | q32 : int(1..4)])) - | q26 : int(1..4)]), - and([q37 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - !(or([q41 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q37] /\ - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q37, q41] = 1 - | q41 : int(1..4)]) - /\ - or([q43 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q37] /\ - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q37, q43] = 2 - | q43 : int(1..4)])) - | q37 : int(1..4)]), - alldifferent_except([toInt(q17 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - q18 <= - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q17]) - * - catchUndef(x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q17, q18], - 0) - | q17 : int(1..4), q18 : int(1..4)], - 0), - and([q19 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - q20 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker - -> - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q19] = - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q20] - | q19 : int(1..4), q20 : int(1..4)]), - and([q21 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q21] >= 1 - | q21 : int(1..4)]), - and([q6 + 1 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - flatten([[x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q6]; int(1)], - flatten([[x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q6, q13]; - int(1)] - | q13 : int(1..4)]); - int(1..2)]) - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q7] = 0 /\ - and([x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q7, q16] = 1 - | q16 : int(1..4)]) - | q7 : int(1..4)]), - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker <= 4, - and([q8 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - and([q9 + 1 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q8] -> - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q8, q9] < - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q8, q9 + 1] - | q9 : int(1..3)]) - | q8 : int(1..4)]), - and([q8 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - and([q10 > x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q8] -> - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q8, q10] = 1 - | q10 : int(1..4)]) - | q8 : int(1..4)]), - and([q8 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q8] <= 4 - | q8 : int(1..4)]), - 4 = - sum([toInt(q15 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker) * - catchUndef(x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q15], 0) - | q15 : int(1..4)]) - diff --git a/tests/exhaustive/basic/partition_05_1/expected/model_4-solution000001.solution b/tests/exhaustive/basic/partition_05_1/expected/model_4-solution000001.solution deleted file mode 100644 index b616543ee7..0000000000 --- a/tests/exhaustive/basic/partition_05_1/expected/model_4-solution000001.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be partition({1, 3}, {2, 4}) -$ Visualisation for x -$ 1 3 -$ 2 4 - diff --git a/tests/exhaustive/basic/partition_05_1/expected/model_4.eprime b/tests/exhaustive/basic/partition_05_1/expected/model_4.eprime deleted file mode 100644 index 5771a6fb07..0000000000 --- a/tests/exhaustive/basic/partition_05_1/expected/model_4.eprime +++ /dev/null @@ -1,40 +0,0 @@ -language ESSENCE' 1.0 - -find x_PartitionOccurrence_NumParts: int(1..4) -find x_PartitionOccurrence_WhichPart: matrix indexed by [int(1..4)] of int(1..4) -find x_PartitionOccurrence_PartSizes: matrix indexed by [int(1..4)] of int(0..4) -find x_PartitionOccurrence_FirstIndex: matrix indexed by [int(1..4)] of int(1..4) -branching on - [x_PartitionOccurrence_NumParts, x_PartitionOccurrence_WhichPart, x_PartitionOccurrence_PartSizes, - x_PartitionOccurrence_FirstIndex] -such that - or([q15 <= x_PartitionOccurrence_NumParts /\ - (or([x_PartitionOccurrence_WhichPart[q20] = q15 /\ q20 = 1 | q20 : int(1..4)]) /\ - or([x_PartitionOccurrence_WhichPart[q22] = q15 /\ q22 = 3 | q22 : int(1..4)])) - | q15 : int(1..4)]), - and([q26 <= x_PartitionOccurrence_NumParts -> - !(or([x_PartitionOccurrence_WhichPart[q31] = q26 /\ q31 = 1 | q31 : int(1..4)]) /\ - or([x_PartitionOccurrence_WhichPart[q33] = q26 /\ q33 = 2 | q33 : int(1..4)])) - | q26 : int(1..4)]), - and([q1 <= x_PartitionOccurrence_NumParts -> x_PartitionOccurrence_PartSizes[q1] <= 4 | q1 : int(1..4)]), - and([q1 > x_PartitionOccurrence_NumParts -> x_PartitionOccurrence_PartSizes[q1] = 0 | q1 : int(1..4)]), - x_PartitionOccurrence_NumParts <= 4, - and([q2 <= x_PartitionOccurrence_NumParts -> or([x_PartitionOccurrence_WhichPart[q3] = q2 | q3 : int(1..4)]) - | q2 : int(3..4)]), - and([q4 <= x_PartitionOccurrence_NumParts -> - x_PartitionOccurrence_PartSizes[q4 - 1] = x_PartitionOccurrence_PartSizes[q4] - | q4 : int(2..4)]), - x_PartitionOccurrence_NumParts = max([x_PartitionOccurrence_WhichPart[q5] | q5 : int(1..4)]), - and([x_PartitionOccurrence_PartSizes[q6] = sum([toInt(x_PartitionOccurrence_WhichPart[q7] = q6) | q7 : int(1..4)]) - | q6 : int(1..4)]), - and([q8 <= x_PartitionOccurrence_NumParts -> - and([x_PartitionOccurrence_WhichPart[q9] = q8 -> x_PartitionOccurrence_FirstIndex[q8] <= q9 | q9 : int(1..4)]) - | q8 : int(1..4)]), - and([q8 <= x_PartitionOccurrence_NumParts -> - or([x_PartitionOccurrence_WhichPart[q9] = q8 /\ x_PartitionOccurrence_FirstIndex[q8] = q9 | q9 : int(1..4)]) - | q8 : int(1..4)]), - and([q8 > x_PartitionOccurrence_NumParts -> x_PartitionOccurrence_FirstIndex[q8] = 1 | q8 : int(1..4)]), - and([q10 <= x_PartitionOccurrence_NumParts /\ q11 <= x_PartitionOccurrence_NumParts -> - (q10 < q11 <-> x_PartitionOccurrence_FirstIndex[q10] < x_PartitionOccurrence_FirstIndex[q11]) - | q10 : int(1..4), q11 : int(1..4)]) - diff --git a/tests/exhaustive/basic/partition_05_2/expected/model_1-solution000001.solution b/tests/exhaustive/basic/partition_05_2/expected/model_1-solution000001.solution deleted file mode 100644 index b616543ee7..0000000000 --- a/tests/exhaustive/basic/partition_05_2/expected/model_1-solution000001.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be partition({1, 3}, {2, 4}) -$ Visualisation for x -$ 1 3 -$ 2 4 - diff --git a/tests/exhaustive/basic/partition_05_2/expected/model_1.eprime b/tests/exhaustive/basic/partition_05_2/expected/model_1.eprime deleted file mode 100644 index 3705a51155..0000000000 --- a/tests/exhaustive/basic/partition_05_2/expected/model_1.eprime +++ /dev/null @@ -1,78 +0,0 @@ -language ESSENCE' 1.0 - -find x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker: int(0..4) -find x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence: matrix indexed by [int(1..4), int(1..4)] of bool -branching on - [x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker, - x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence] -such that - and([and([q27 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker, - x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q27, 2], - x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q27, q25]; - int(1..3)]) - -> 4 = q25 \/ 2 = q25 - | q27 : int(1..4), q25 : int(1..4)]), - or([and([q36 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker, - x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q36, 2], - x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q36, q34]; - int(1..3)]) - /\ q34 = 4 - | q36 : int(1..4), q34 : int(1..4)]), - or([and([q41 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker, - x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q41, 2], - x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q41, q39]; - int(1..3)]) - /\ q39 = 2 - | q41 : int(1..4), q39 : int(1..4)]), - and([q46 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ - x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q46, q44] - -> or([1 = q44, 2 = q44, 3 = q44, 4 = q44; int(1..4)]) - | q46 : int(1..4), q44 : int(1..4)]), - or([q55 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ - x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q55, q53] - /\ q53 = 1 - | q55 : int(1..4), q53 : int(1..4)]), - or([q60 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ - x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q60, q58] - /\ q58 = 2 - | q60 : int(1..4), q58 : int(1..4)]), - or([q65 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ - x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q65, q63] - /\ q63 = 3 - | q65 : int(1..4), q63 : int(1..4)]), - or([q70 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ - x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q70, q68] - /\ q68 = 4 - | q70 : int(1..4), q68 : int(1..4)]), - and([1 = - sum([toInt(q16 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ - x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q16, q1]) - | q16 : int(1..4)]) - | q1 : int(1..4)]), - and([q17 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ - q18 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker - -> - sum([toInt(x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q17, q19]) | q19 : int(1..4)]) = - sum([toInt(x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q18, q20]) | q20 : int(1..4)]) - | q17 : int(1..4), q18 : int(1..4)]), - and([q21 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> - sum([toInt(x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q21, q22]) | q22 : int(1..4)]) >= 1 - | q21 : int(1..4)]), - and([q6 + 1 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> - [-toInt(x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q6, q11]) | q11 : int(1..4)] x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> - and([x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q7, q13] = false | q13 : int(1..4)]) - | q7 : int(1..4)]), - x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker <= 4, - and([q8 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> - sum([toInt(x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q8, q9]) | q9 : int(1..4)]) <= 4 - | q8 : int(1..4)]), - 4 = - sum([toInt(q14 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker) * - catchUndef(sum([toInt(x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q14, q15]) - | q15 : int(1..4)]), - 0) - | q14 : int(1..4)]) - diff --git a/tests/exhaustive/basic/partition_05_2/expected/model_2-solution000001.solution b/tests/exhaustive/basic/partition_05_2/expected/model_2-solution000001.solution deleted file mode 100644 index b616543ee7..0000000000 --- a/tests/exhaustive/basic/partition_05_2/expected/model_2-solution000001.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be partition({1, 3}, {2, 4}) -$ Visualisation for x -$ 1 3 -$ 2 4 - diff --git a/tests/exhaustive/basic/partition_05_2/expected/model_2.eprime b/tests/exhaustive/basic/partition_05_2/expected/model_2.eprime deleted file mode 100644 index 6bd4e14438..0000000000 --- a/tests/exhaustive/basic/partition_05_2/expected/model_2.eprime +++ /dev/null @@ -1,116 +0,0 @@ -language ESSENCE' 1.0 - -find x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker: int(0..4) -find x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy: - matrix indexed by [int(1..4), int(1..4)] of int(1..5) -branching on - [x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker, - x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy] -such that - and([and([q35 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker, - or([x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q35, q40] != 5 /\ - x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q35, q40] = 2 - | q40 : int(1..4)]), - x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q35, q36] != 5; - int(1..3)]) - -> - 4 = x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q35, q36] \/ - 2 = x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q35, q36] - | q35 : int(1..4), q36 : int(1..4)]), - or([and([q47 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker, - or([x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q47, q50] != 5 /\ - x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q47, q50] = 2 - | q50 : int(1..4)]), - x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q47, q48] != 5; - int(1..3)]) - /\ x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q47, q48] = 4 - | q47 : int(1..4), q48 : int(1..4)]), - or([and([q55 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker, - or([x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q55, q58] != 5 /\ - x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q55, q58] = 2 - | q58 : int(1..4)]), - x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q55, q56] != 5; - int(1..3)]) - /\ x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q55, q56] = 2 - | q55 : int(1..4), q56 : int(1..4)]), - and([q63 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ - x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q63, q64] != 5 - -> - or([1 = x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q63, q64], - 2 = x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q63, q64], - 3 = x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q63, q64], - 4 = x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q63, q64]; - int(1..4)]) - | q63 : int(1..4), q64 : int(1..4)]), - or([q73 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ - x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q73, q74] != 5 - /\ x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q73, q74] = 1 - | q73 : int(1..4), q74 : int(1..4)]), - or([q79 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ - x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q79, q80] != 5 - /\ x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q79, q80] = 2 - | q79 : int(1..4), q80 : int(1..4)]), - or([q85 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ - x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q85, q86] != 5 - /\ x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q85, q86] = 3 - | q85 : int(1..4), q86 : int(1..4)]), - or([q91 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ - x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q91, q92] != 5 - /\ x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q91, q92] = 4 - | q91 : int(1..4), q92 : int(1..4)]), - alldifferent_except([toInt(q20 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ - x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q20, q21] != - 5) - * - catchUndef(x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q20, q21], - 0) - | q20 : int(1..4), q21 : int(1..4)], - 0), - and([q22 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ - q23 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker - -> - sum([toInt(x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q22, q25] != 5) - | q25 : int(1..4)]) - = - sum([toInt(x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q23, q27] != 5) - | q27 : int(1..4)]) - | q22 : int(1..4), q23 : int(1..4)]), - and([q28 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - sum([toInt(x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q28, q30] != 5) - | q30 : int(1..4)]) - >= 1 - | q28 : int(1..4)]), - and([q6 + 1 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - [x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q6, q14] | q14 : int(1..4)] x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - and([x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q7, q19] = 1 - | q19 : int(1..4)]) - | q7 : int(1..4)]), - x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker <= 4, - and([q8 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - and([x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q8, q9] < - x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q8, q9 + 1] - \/ x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q8, q9] = 5 - | q9 : int(1..3)]) - | q8 : int(1..4)]), - and([q8 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - and([x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q8, q10] = 5 -> - x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q8, q10 + 1] = 5 - | q10 : int(1..3)]) - | q8 : int(1..4)]), - and([q8 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - sum([toInt(x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q8, q11] != 5) - | q11 : int(1..4)]) - <= 4 - | q8 : int(1..4)]), - 4 = - sum([toInt(q16 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker) * - catchUndef(sum([toInt(x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q16, q18] != - 5) - | q18 : int(1..4)]), - 0) - | q16 : int(1..4)]) - diff --git a/tests/exhaustive/basic/partition_05_2/expected/model_3-solution000001.solution b/tests/exhaustive/basic/partition_05_2/expected/model_3-solution000001.solution deleted file mode 100644 index b616543ee7..0000000000 --- a/tests/exhaustive/basic/partition_05_2/expected/model_3-solution000001.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be partition({1, 3}, {2, 4}) -$ Visualisation for x -$ 1 3 -$ 2 4 - diff --git a/tests/exhaustive/basic/partition_05_2/expected/model_3.eprime b/tests/exhaustive/basic/partition_05_2/expected/model_3.eprime deleted file mode 100644 index e7162e8bdb..0000000000 --- a/tests/exhaustive/basic/partition_05_2/expected/model_3.eprime +++ /dev/null @@ -1,123 +0,0 @@ -language ESSENCE' 1.0 - -find x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker: int(0..4) -find x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker: - matrix indexed by [int(1..4)] of int(0..4) -find x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values: - matrix indexed by [int(1..4), int(1..4)] of int(1..4) -branching on - [x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker, - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker, - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values] -such that - and([and([q26 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker, - or([q31 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q26] /\ - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q26, q31] = 2 - | q31 : int(1..4)]), - q27 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q26]; - int(1..3)]) - -> - 4 = x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q26, q27] \/ - 2 = x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q26, q27] - | q26 : int(1..4), q27 : int(1..4)]), - or([and([q38 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker, - or([q41 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q38] /\ - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q38, q41] = 2 - | q41 : int(1..4)]), - q39 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q38]; - int(1..3)]) - /\ x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q38, q39] = 4 - | q38 : int(1..4), q39 : int(1..4)]), - or([and([q46 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker, - or([q49 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q46] /\ - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q46, q49] = 2 - | q49 : int(1..4)]), - q47 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q46]; - int(1..3)]) - /\ x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q46, q47] = 2 - | q46 : int(1..4), q47 : int(1..4)]), - and([q54 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - q55 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q54] - -> - or([1 = x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q54, q55], - 2 = x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q54, q55], - 3 = x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q54, q55], - 4 = x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q54, q55]; - int(1..4)]) - | q54 : int(1..4), q55 : int(1..4)]), - or([q64 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - q65 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q64] - /\ x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q64, q65] = 1 - | q64 : int(1..4), q65 : int(1..4)]), - or([q70 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - q71 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q70] - /\ x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q70, q71] = 2 - | q70 : int(1..4), q71 : int(1..4)]), - or([q76 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - q77 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q76] - /\ x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q76, q77] = 3 - | q76 : int(1..4), q77 : int(1..4)]), - or([q82 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - q83 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q82] - /\ x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q82, q83] = 4 - | q82 : int(1..4), q83 : int(1..4)]), - alldifferent_except([toInt(q17 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - q18 <= - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q17]) - * - catchUndef(x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q17, q18], - 0) - | q17 : int(1..4), q18 : int(1..4)], - 0), - and([q19 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - q20 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker - -> - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q19] = - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q20] - | q19 : int(1..4), q20 : int(1..4)]), - and([q21 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q21] >= 1 - | q21 : int(1..4)]), - and([q6 + 1 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - flatten([[x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q6]; int(1)], - flatten([[x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q6, q13]; - int(1)] - | q13 : int(1..4)]); - int(1..2)]) - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q7] = 0 /\ - and([x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q7, q16] = 1 - | q16 : int(1..4)]) - | q7 : int(1..4)]), - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker <= 4, - and([q8 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - and([q9 + 1 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q8] -> - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q8, q9] < - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q8, q9 + 1] - | q9 : int(1..3)]) - | q8 : int(1..4)]), - and([q8 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - and([q10 > x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q8] -> - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q8, q10] = 1 - | q10 : int(1..4)]) - | q8 : int(1..4)]), - and([q8 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q8] <= 4 - | q8 : int(1..4)]), - 4 = - sum([toInt(q15 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker) * - catchUndef(x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q15], 0) - | q15 : int(1..4)]) - diff --git a/tests/exhaustive/basic/partition_05_2/expected/model_4-solution000001.solution b/tests/exhaustive/basic/partition_05_2/expected/model_4-solution000001.solution deleted file mode 100644 index b616543ee7..0000000000 --- a/tests/exhaustive/basic/partition_05_2/expected/model_4-solution000001.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be partition({1, 3}, {2, 4}) -$ Visualisation for x -$ 1 3 -$ 2 4 - diff --git a/tests/exhaustive/basic/partition_05_2/expected/model_4.eprime b/tests/exhaustive/basic/partition_05_2/expected/model_4.eprime deleted file mode 100644 index 989ba1bdb3..0000000000 --- a/tests/exhaustive/basic/partition_05_2/expected/model_4.eprime +++ /dev/null @@ -1,61 +0,0 @@ -language ESSENCE' 1.0 - -find x_PartitionOccurrence_NumParts: int(1..4) -find x_PartitionOccurrence_WhichPart: matrix indexed by [int(1..4)] of int(1..4) -find x_PartitionOccurrence_PartSizes: matrix indexed by [int(1..4)] of int(0..4) -find x_PartitionOccurrence_FirstIndex: matrix indexed by [int(1..4)] of int(1..4) -branching on - [x_PartitionOccurrence_NumParts, x_PartitionOccurrence_WhichPart, x_PartitionOccurrence_PartSizes, - x_PartitionOccurrence_FirstIndex] -such that - and([and([q15 <= x_PartitionOccurrence_NumParts, - or([x_PartitionOccurrence_WhichPart[q21] = q15 /\ q21 = 2 | q21 : int(1..4)]), - x_PartitionOccurrence_WhichPart[q17] = q15; - int(1..3)]) - -> 4 = q17 \/ 2 = q17 - | q15 : int(1..4), q17 : int(1..4)]), - or([and([q27 <= x_PartitionOccurrence_NumParts, - or([x_PartitionOccurrence_WhichPart[q31] = q27 /\ q31 = 2 | q31 : int(1..4)]), - x_PartitionOccurrence_WhichPart[q29] = q27; - int(1..3)]) - /\ q29 = 4 - | q27 : int(1..4), q29 : int(1..4)]), - or([and([q35 <= x_PartitionOccurrence_NumParts, - or([x_PartitionOccurrence_WhichPart[q39] = q35 /\ q39 = 2 | q39 : int(1..4)]), - x_PartitionOccurrence_WhichPart[q37] = q35; - int(1..3)]) - /\ q37 = 2 - | q35 : int(1..4), q37 : int(1..4)]), - and([q43 <= x_PartitionOccurrence_NumParts /\ x_PartitionOccurrence_WhichPart[q45] = q43 -> - or([1 = q45, 2 = q45, 3 = q45, 4 = q45; int(1..4)]) - | q43 : int(1..4), q45 : int(1..4)]), - or([q53 <= x_PartitionOccurrence_NumParts /\ x_PartitionOccurrence_WhichPart[q55] = q53 /\ q55 = 1 - | q53 : int(1..4), q55 : int(1..4)]), - or([q59 <= x_PartitionOccurrence_NumParts /\ x_PartitionOccurrence_WhichPart[q61] = q59 /\ q61 = 2 - | q59 : int(1..4), q61 : int(1..4)]), - or([q65 <= x_PartitionOccurrence_NumParts /\ x_PartitionOccurrence_WhichPart[q67] = q65 /\ q67 = 3 - | q65 : int(1..4), q67 : int(1..4)]), - or([q71 <= x_PartitionOccurrence_NumParts /\ x_PartitionOccurrence_WhichPart[q73] = q71 /\ q73 = 4 - | q71 : int(1..4), q73 : int(1..4)]), - and([q1 <= x_PartitionOccurrence_NumParts -> x_PartitionOccurrence_PartSizes[q1] <= 4 | q1 : int(1..4)]), - and([q1 > x_PartitionOccurrence_NumParts -> x_PartitionOccurrence_PartSizes[q1] = 0 | q1 : int(1..4)]), - x_PartitionOccurrence_NumParts <= 4, - and([q2 <= x_PartitionOccurrence_NumParts -> or([x_PartitionOccurrence_WhichPart[q3] = q2 | q3 : int(1..4)]) - | q2 : int(3..4)]), - and([q4 <= x_PartitionOccurrence_NumParts -> - x_PartitionOccurrence_PartSizes[q4 - 1] = x_PartitionOccurrence_PartSizes[q4] - | q4 : int(2..4)]), - x_PartitionOccurrence_NumParts = max([x_PartitionOccurrence_WhichPart[q5] | q5 : int(1..4)]), - and([x_PartitionOccurrence_PartSizes[q6] = sum([toInt(x_PartitionOccurrence_WhichPart[q7] = q6) | q7 : int(1..4)]) - | q6 : int(1..4)]), - and([q8 <= x_PartitionOccurrence_NumParts -> - and([x_PartitionOccurrence_WhichPart[q9] = q8 -> x_PartitionOccurrence_FirstIndex[q8] <= q9 | q9 : int(1..4)]) - | q8 : int(1..4)]), - and([q8 <= x_PartitionOccurrence_NumParts -> - or([x_PartitionOccurrence_WhichPart[q9] = q8 /\ x_PartitionOccurrence_FirstIndex[q8] = q9 | q9 : int(1..4)]) - | q8 : int(1..4)]), - and([q8 > x_PartitionOccurrence_NumParts -> x_PartitionOccurrence_FirstIndex[q8] = 1 | q8 : int(1..4)]), - and([q10 <= x_PartitionOccurrence_NumParts /\ q11 <= x_PartitionOccurrence_NumParts -> - (q10 < q11 <-> x_PartitionOccurrence_FirstIndex[q10] < x_PartitionOccurrence_FirstIndex[q11]) - | q10 : int(1..4), q11 : int(1..4)]) - diff --git a/tests/exhaustive/basic/partition_06/expected/model_1_1-solution000001.solution b/tests/exhaustive/basic/partition_06/expected/model_1_1-solution000001.solution deleted file mode 100644 index 8d196199c8..0000000000 --- a/tests/exhaustive/basic/partition_06/expected/model_1_1-solution000001.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be partition({1, 4}, {2, 3}) -$ Visualisation for x -$ 1 4 -$ 2 3 - diff --git a/tests/exhaustive/basic/partition_06/expected/model_1_1-solution000002.solution b/tests/exhaustive/basic/partition_06/expected/model_1_1-solution000002.solution deleted file mode 100644 index b616543ee7..0000000000 --- a/tests/exhaustive/basic/partition_06/expected/model_1_1-solution000002.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be partition({1, 3}, {2, 4}) -$ Visualisation for x -$ 1 3 -$ 2 4 - diff --git a/tests/exhaustive/basic/partition_06/expected/model_1_1-solution000003.solution b/tests/exhaustive/basic/partition_06/expected/model_1_1-solution000003.solution deleted file mode 100644 index bdecd9ce5b..0000000000 --- a/tests/exhaustive/basic/partition_06/expected/model_1_1-solution000003.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be partition({1, 2}, {3, 4}) -$ Visualisation for x -$ 1 2 -$ 3 4 - diff --git a/tests/exhaustive/basic/partition_06/expected/model_1_1.eprime b/tests/exhaustive/basic/partition_06/expected/model_1_1.eprime deleted file mode 100644 index 0185996261..0000000000 --- a/tests/exhaustive/basic/partition_06/expected/model_1_1.eprime +++ /dev/null @@ -1,37 +0,0 @@ -language ESSENCE' 1.0 - -find x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker: int(0..4) -find x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence: matrix indexed by [int(1..4), int(1..4)] of bool -branching on - [x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker, - x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence] -such that - and([q18 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> - sum([toInt(x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q18, q19]) | q19 : int(1..4)]) = 2 - | q18 : int(1..4)]), - and([1 = - sum([toInt(q14 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ - x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q14, q1]) - | q14 : int(1..4)]) - | q1 : int(1..4)]), - and([q15 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> - sum([toInt(x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q15, q16]) | q16 : int(1..4)]) >= 1 - | q15 : int(1..4)]), - and([q4 + 1 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> - [-toInt(x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q4, q9]) | q9 : int(1..4)] x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> - and([x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q5, q11] = false | q11 : int(1..4)]) - | q5 : int(1..4)]), - x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker <= 4, - and([q6 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> - sum([toInt(x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q6, q7]) | q7 : int(1..4)]) <= 4 - | q6 : int(1..4)]), - 4 = - sum([toInt(q12 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker) * - catchUndef(sum([toInt(x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q12, q13]) - | q13 : int(1..4)]), - 0) - | q12 : int(1..4)]) - diff --git a/tests/exhaustive/basic/partition_06/expected/model_1_2-solution000001.solution b/tests/exhaustive/basic/partition_06/expected/model_1_2-solution000001.solution deleted file mode 100644 index bdecd9ce5b..0000000000 --- a/tests/exhaustive/basic/partition_06/expected/model_1_2-solution000001.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be partition({1, 2}, {3, 4}) -$ Visualisation for x -$ 1 2 -$ 3 4 - diff --git a/tests/exhaustive/basic/partition_06/expected/model_1_2-solution000002.solution b/tests/exhaustive/basic/partition_06/expected/model_1_2-solution000002.solution deleted file mode 100644 index b616543ee7..0000000000 --- a/tests/exhaustive/basic/partition_06/expected/model_1_2-solution000002.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be partition({1, 3}, {2, 4}) -$ Visualisation for x -$ 1 3 -$ 2 4 - diff --git a/tests/exhaustive/basic/partition_06/expected/model_1_2-solution000003.solution b/tests/exhaustive/basic/partition_06/expected/model_1_2-solution000003.solution deleted file mode 100644 index 8d196199c8..0000000000 --- a/tests/exhaustive/basic/partition_06/expected/model_1_2-solution000003.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be partition({1, 4}, {2, 3}) -$ Visualisation for x -$ 1 4 -$ 2 3 - diff --git a/tests/exhaustive/basic/partition_06/expected/model_1_2.eprime b/tests/exhaustive/basic/partition_06/expected/model_1_2.eprime deleted file mode 100644 index 337e8fc3c9..0000000000 --- a/tests/exhaustive/basic/partition_06/expected/model_1_2.eprime +++ /dev/null @@ -1,116 +0,0 @@ -language ESSENCE' 1.0 - -find x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker: int(0..4) -find x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence: matrix indexed by [int(1..4), int(1..4)] of bool -find x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker: int(0..4) -find x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy: - matrix indexed by [int(1..4), int(1..4)] of int(1..5) -branching on - [x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker, - x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy, - x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker, - x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence] -such that - and([q55 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> - sum([toInt(x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q55, q56]) | q56 : int(1..4)]) = 2 - | q55 : int(1..4)]), - and([1 = - sum([toInt(q52 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ - x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q52, q1]) - | q52 : int(1..4)]) - | q1 : int(1..4)]), - and([q57 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> - sum([toInt(x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q57, q58]) | q58 : int(1..4)]) >= 1 - | q57 : int(1..4)]), - and([q4 + 1 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> - [-toInt(x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q4, q9]) | q9 : int(1..4)] x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> - and([x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q5, q11] = false | q11 : int(1..4)]) - | q5 : int(1..4)]), - x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker <= 4, - and([q6 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> - sum([toInt(x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q6, q7]) | q7 : int(1..4)]) <= 4 - | q6 : int(1..4)]), - 4 = - sum([toInt(q12 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker) * - catchUndef(sum([toInt(x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q12, q13]) - | q13 : int(1..4)]), - 0) - | q12 : int(1..4)]), - alldifferent_except([toInt(q59 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ - x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q59, q60] != - 5) - * - catchUndef(x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q59, q60], - 0) - | q59 : int(1..4), q60 : int(1..4)], - 0), - and([q61 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - sum([toInt(x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q61, q63] != 5) - | q63 : int(1..4)]) - >= 1 - | q61 : int(1..4)]), - and([q17 + 1 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - [x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q17, q25] | q25 : int(1..4)] x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - and([x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q18, q53] = 1 - | q53 : int(1..4)]) - | q18 : int(1..4)]), - x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker <= 4, - and([q19 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - and([x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q19, q20] < - x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q19, q20 + 1] - \/ x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q19, q20] = 5 - | q20 : int(1..3)]) - | q19 : int(1..4)]), - and([q19 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - and([x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q19, q21] = 5 -> - x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q19, q21 + 1] = 5 - | q21 : int(1..3)]) - | q19 : int(1..4)]), - and([q19 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - sum([toInt(x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q19, q22] != 5) - | q22 : int(1..4)]) - <= 4 - | q19 : int(1..4)]), - 4 = - sum([toInt(q27 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker) * - catchUndef(sum([toInt(x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q27, q29] != - 5) - | q29 : int(1..4)]), - 0) - | q27 : int(1..4)]), - and([q32 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - or([q35 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ - (and([x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q35, q36] -> - or([x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q32, q38] != 5 /\ - x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q32, q38] = q36 - | q38 : int(1..4)]) - | q36 : int(1..4)]) - /\ - and([x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q32, q40] != 5 -> - x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence - [q35, x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q32, q40]] - | q40 : int(1..4)])) - | q35 : int(1..4)]) - | q32 : int(1..4)]), - and([q43 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> - or([q46 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ - (and([x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q46, q48] != 5 -> - x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence - [q43, x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q46, q48]] - | q48 : int(1..4)]) - /\ - and([x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q43, q49] -> - or([x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q46, q51] != 5 /\ - x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q46, q51] = q49 - | q51 : int(1..4)]) - | q49 : int(1..4)])) - | q46 : int(1..4)]) - | q43 : int(1..4)]) - diff --git a/tests/exhaustive/basic/partition_06/expected/model_1_3-solution000001.solution b/tests/exhaustive/basic/partition_06/expected/model_1_3-solution000001.solution deleted file mode 100644 index bdecd9ce5b..0000000000 --- a/tests/exhaustive/basic/partition_06/expected/model_1_3-solution000001.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be partition({1, 2}, {3, 4}) -$ Visualisation for x -$ 1 2 -$ 3 4 - diff --git a/tests/exhaustive/basic/partition_06/expected/model_1_3-solution000002.solution b/tests/exhaustive/basic/partition_06/expected/model_1_3-solution000002.solution deleted file mode 100644 index b616543ee7..0000000000 --- a/tests/exhaustive/basic/partition_06/expected/model_1_3-solution000002.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be partition({1, 3}, {2, 4}) -$ Visualisation for x -$ 1 3 -$ 2 4 - diff --git a/tests/exhaustive/basic/partition_06/expected/model_1_3-solution000003.solution b/tests/exhaustive/basic/partition_06/expected/model_1_3-solution000003.solution deleted file mode 100644 index 8d196199c8..0000000000 --- a/tests/exhaustive/basic/partition_06/expected/model_1_3-solution000003.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be partition({1, 4}, {2, 3}) -$ Visualisation for x -$ 1 4 -$ 2 3 - diff --git a/tests/exhaustive/basic/partition_06/expected/model_1_3.eprime b/tests/exhaustive/basic/partition_06/expected/model_1_3.eprime deleted file mode 100644 index dc3d568e08..0000000000 --- a/tests/exhaustive/basic/partition_06/expected/model_1_3.eprime +++ /dev/null @@ -1,130 +0,0 @@ -language ESSENCE' 1.0 - -find x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker: int(0..4) -find x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence: matrix indexed by [int(1..4), int(1..4)] of bool -find x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker: int(0..4) -find x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker: - matrix indexed by [int(1..4)] of int(0..4) -find x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values: - matrix indexed by [int(1..4), int(1..4)] of int(1..4) -branching on - [x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker, - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker, - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values, - x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker, - x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence] -such that - and([q52 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> - sum([toInt(x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q52, q53]) | q53 : int(1..4)]) = 2 - | q52 : int(1..4)]), - and([1 = - sum([toInt(q49 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ - x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q49, q1]) - | q49 : int(1..4)]) - | q1 : int(1..4)]), - and([q54 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> - sum([toInt(x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q54, q55]) | q55 : int(1..4)]) >= 1 - | q54 : int(1..4)]), - and([q4 + 1 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> - [-toInt(x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q4, q9]) | q9 : int(1..4)] x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> - and([x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q5, q11] = false | q11 : int(1..4)]) - | q5 : int(1..4)]), - x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker <= 4, - and([q6 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> - sum([toInt(x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q6, q7]) | q7 : int(1..4)]) <= 4 - | q6 : int(1..4)]), - 4 = - sum([toInt(q12 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker) * - catchUndef(sum([toInt(x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q12, q13]) - | q13 : int(1..4)]), - 0) - | q12 : int(1..4)]), - alldifferent_except([toInt(q56 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - q57 <= - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q56]) - * - catchUndef(x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q56, q57], - 0) - | q56 : int(1..4), q57 : int(1..4)], - 0), - and([q58 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q58] >= 1 - | q58 : int(1..4)]), - and([q17 + 1 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - flatten([[x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q17]; int(1)], - flatten([[x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q17, q24]; - int(1)] - | q24 : int(1..4)]); - int(1..2)]) - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q18] = 0 /\ - and([x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q18, q50] = 1 - | q50 : int(1..4)]) - | q18 : int(1..4)]), - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker <= 4, - and([q19 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - and([q20 + 1 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q19] -> - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q19, q20] < - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q19, q20 + 1] - | q20 : int(1..3)]) - | q19 : int(1..4)]), - and([q19 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - and([q21 > x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q19] -> - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q19, q21] = 1 - | q21 : int(1..4)]) - | q19 : int(1..4)]), - and([q19 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q19] <= 4 - | q19 : int(1..4)]), - 4 = - sum([toInt(q26 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker) * - catchUndef(x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q26], 0) - | q26 : int(1..4)]), - and([q29 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - or([q32 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ - (and([x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q32, q33] -> - or([q35 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q29] - /\ - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q29, q35] = - q33 | q35 : int(1..4)]) - | q33 : int(1..4)]) - /\ - and([q37 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q29] -> - x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence - [q32, - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q29, q37]] - | q37 : int(1..4)])) - | q32 : int(1..4)]) - | q29 : int(1..4)]), - and([q40 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> - or([q43 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - (and([q45 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q43] -> - x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence - [q40, - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q43, q45]] - | q45 : int(1..4)]) - /\ - and([x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q40, q46] -> - or([q48 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q43] - /\ - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q43, q48] = - q46 | q48 : int(1..4)]) - | q46 : int(1..4)])) - | q43 : int(1..4)]) - | q40 : int(1..4)]) - diff --git a/tests/exhaustive/basic/partition_06/expected/model_1_4-solution000001.solution b/tests/exhaustive/basic/partition_06/expected/model_1_4-solution000001.solution deleted file mode 100644 index bdecd9ce5b..0000000000 --- a/tests/exhaustive/basic/partition_06/expected/model_1_4-solution000001.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be partition({1, 2}, {3, 4}) -$ Visualisation for x -$ 1 2 -$ 3 4 - diff --git a/tests/exhaustive/basic/partition_06/expected/model_1_4-solution000002.solution b/tests/exhaustive/basic/partition_06/expected/model_1_4-solution000002.solution deleted file mode 100644 index b616543ee7..0000000000 --- a/tests/exhaustive/basic/partition_06/expected/model_1_4-solution000002.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be partition({1, 3}, {2, 4}) -$ Visualisation for x -$ 1 3 -$ 2 4 - diff --git a/tests/exhaustive/basic/partition_06/expected/model_1_4-solution000003.solution b/tests/exhaustive/basic/partition_06/expected/model_1_4-solution000003.solution deleted file mode 100644 index 8d196199c8..0000000000 --- a/tests/exhaustive/basic/partition_06/expected/model_1_4-solution000003.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be partition({1, 4}, {2, 3}) -$ Visualisation for x -$ 1 4 -$ 2 3 - diff --git a/tests/exhaustive/basic/partition_06/expected/model_1_4.eprime b/tests/exhaustive/basic/partition_06/expected/model_1_4.eprime deleted file mode 100644 index fe7ae25188..0000000000 --- a/tests/exhaustive/basic/partition_06/expected/model_1_4.eprime +++ /dev/null @@ -1,85 +0,0 @@ -language ESSENCE' 1.0 - -find x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker: int(0..4) -find x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence: matrix indexed by [int(1..4), int(1..4)] of bool -find x_PartitionOccurrence_NumParts: int(1..4) -find x_PartitionOccurrence_WhichPart: matrix indexed by [int(1..4)] of int(1..4) -find x_PartitionOccurrence_PartSizes: matrix indexed by [int(1..4)] of int(0..4) -find x_PartitionOccurrence_FirstIndex: matrix indexed by [int(1..4)] of int(1..4) -branching on - [x_PartitionOccurrence_NumParts, x_PartitionOccurrence_WhichPart, x_PartitionOccurrence_PartSizes, - x_PartitionOccurrence_FirstIndex, x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker, - x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence] -such that - and([q48 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> - sum([toInt(x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q48, q49]) | q49 : int(1..4)]) = 2 - | q48 : int(1..4)]), - and([1 = - sum([toInt(q24 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ - x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q24, q1]) - | q24 : int(1..4)]) - | q1 : int(1..4)]), - and([q50 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> - sum([toInt(x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q50, q51]) | q51 : int(1..4)]) >= 1 - | q50 : int(1..4)]), - and([q4 + 1 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> - [-toInt(x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q4, q9]) | q9 : int(1..4)] x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> - and([x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q5, q11] = false | q11 : int(1..4)]) - | q5 : int(1..4)]), - x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker <= 4, - and([q6 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> - sum([toInt(x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q6, q7]) | q7 : int(1..4)]) <= 4 - | q6 : int(1..4)]), - 4 = - sum([toInt(q12 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker) * - catchUndef(sum([toInt(x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q12, q13]) - | q13 : int(1..4)]), - 0) - | q12 : int(1..4)]), - and([q14 <= x_PartitionOccurrence_NumParts -> x_PartitionOccurrence_PartSizes[q14] <= 4 | q14 : int(1..4)]), - and([q14 > x_PartitionOccurrence_NumParts -> x_PartitionOccurrence_PartSizes[q14] = 0 | q14 : int(1..4)]), - x_PartitionOccurrence_NumParts <= 4, - and([q15 <= x_PartitionOccurrence_NumParts -> or([x_PartitionOccurrence_WhichPart[q16] = q15 | q16 : int(1..4)]) - | q15 : int(3..4)]), - x_PartitionOccurrence_NumParts = max([x_PartitionOccurrence_WhichPart[q17] | q17 : int(1..4)]), - and([x_PartitionOccurrence_PartSizes[q18] = - sum([toInt(x_PartitionOccurrence_WhichPart[q19] = q18) | q19 : int(1..4)]) - | q18 : int(1..4)]), - and([q20 <= x_PartitionOccurrence_NumParts -> - and([x_PartitionOccurrence_WhichPart[q21] = q20 -> x_PartitionOccurrence_FirstIndex[q20] <= q21 - | q21 : int(1..4)]) - | q20 : int(1..4)]), - and([q20 <= x_PartitionOccurrence_NumParts -> - or([x_PartitionOccurrence_WhichPart[q21] = q20 /\ x_PartitionOccurrence_FirstIndex[q20] = q21 - | q21 : int(1..4)]) - | q20 : int(1..4)]), - and([q20 > x_PartitionOccurrence_NumParts -> x_PartitionOccurrence_FirstIndex[q20] = 1 | q20 : int(1..4)]), - and([q22 <= x_PartitionOccurrence_NumParts /\ q23 <= x_PartitionOccurrence_NumParts -> - (q22 < q23 <-> x_PartitionOccurrence_FirstIndex[q22] < x_PartitionOccurrence_FirstIndex[q23]) - | q22 : int(1..4), q23 : int(1..4)]), - and([q26 <= x_PartitionOccurrence_NumParts -> - or([q30 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ - (and([x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q30, q31] -> - or([x_PartitionOccurrence_WhichPart[q33] = q26 /\ q33 = q31 | q33 : int(1..4)]) - | q31 : int(1..4)]) - /\ - and([x_PartitionOccurrence_WhichPart[q35] = q26 -> - x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q30, q35] - | q35 : int(1..4)])) - | q30 : int(1..4)]) - | q26 : int(1..4)]), - and([q38 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> - or([q40 <= x_PartitionOccurrence_NumParts /\ - (and([x_PartitionOccurrence_WhichPart[q43] = q40 -> - x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q38, q43] - | q43 : int(1..4)]) - /\ - and([x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q38, q44] -> - or([x_PartitionOccurrence_WhichPart[q46] = q40 /\ q46 = q44 | q46 : int(1..4)]) - | q44 : int(1..4)])) - | q40 : int(1..4)]) - | q38 : int(1..4)]) - diff --git a/tests/exhaustive/basic/partition_06/expected/model_2_1-solution000001.solution b/tests/exhaustive/basic/partition_06/expected/model_2_1-solution000001.solution deleted file mode 100644 index 8d196199c8..0000000000 --- a/tests/exhaustive/basic/partition_06/expected/model_2_1-solution000001.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be partition({1, 4}, {2, 3}) -$ Visualisation for x -$ 1 4 -$ 2 3 - diff --git a/tests/exhaustive/basic/partition_06/expected/model_2_1-solution000002.solution b/tests/exhaustive/basic/partition_06/expected/model_2_1-solution000002.solution deleted file mode 100644 index b616543ee7..0000000000 --- a/tests/exhaustive/basic/partition_06/expected/model_2_1-solution000002.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be partition({1, 3}, {2, 4}) -$ Visualisation for x -$ 1 3 -$ 2 4 - diff --git a/tests/exhaustive/basic/partition_06/expected/model_2_1-solution000003.solution b/tests/exhaustive/basic/partition_06/expected/model_2_1-solution000003.solution deleted file mode 100644 index bdecd9ce5b..0000000000 --- a/tests/exhaustive/basic/partition_06/expected/model_2_1-solution000003.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be partition({1, 2}, {3, 4}) -$ Visualisation for x -$ 1 2 -$ 3 4 - diff --git a/tests/exhaustive/basic/partition_06/expected/model_2_1.eprime b/tests/exhaustive/basic/partition_06/expected/model_2_1.eprime deleted file mode 100644 index 8f0bcabfd6..0000000000 --- a/tests/exhaustive/basic/partition_06/expected/model_2_1.eprime +++ /dev/null @@ -1,117 +0,0 @@ -language ESSENCE' 1.0 - -find x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker: int(0..4) -find x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy: - matrix indexed by [int(1..4), int(1..4)] of int(1..5) -find x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker: int(0..4) -find x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence: matrix indexed by [int(1..4), int(1..4)] of bool -branching on - [x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker, - x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence, - x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker, - x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy] -such that - and([q57 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - sum([toInt(x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q57, q59] != 5) - | q59 : int(1..4)]) - = 2 | q57 : int(1..4)]), - alldifferent_except([toInt(q60 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ - x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q60, q61] != - 5) - * - catchUndef(x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q60, q61], - 0) - | q60 : int(1..4), q61 : int(1..4)], - 0), - and([q62 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - sum([toInt(x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q62, q64] != 5) - | q64 : int(1..4)]) - >= 1 - | q62 : int(1..4)]), - and([q4 + 1 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - [x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q4, q12] | q12 : int(1..4)] x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - and([x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q5, q52] = 1 - | q52 : int(1..4)]) - | q5 : int(1..4)]), - x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker <= 4, - and([q6 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - and([x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q6, q7] < - x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q6, q7 + 1] - \/ x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q6, q7] = 5 - | q7 : int(1..3)]) - | q6 : int(1..4)]), - and([q6 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - and([x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q6, q8] = 5 -> - x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q6, q8 + 1] = 5 - | q8 : int(1..3)]) - | q6 : int(1..4)]), - and([q6 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - sum([toInt(x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q6, q9] != 5) - | q9 : int(1..4)]) - <= 4 - | q6 : int(1..4)]), - 4 = - sum([toInt(q14 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker) * - catchUndef(sum([toInt(x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q14, q16] != - 5) - | q16 : int(1..4)]), - 0) - | q14 : int(1..4)]), - and([1 = - sum([toInt(q53 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ - x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q53, q17]) - | q53 : int(1..4)]) - | q17 : int(1..4)]), - and([q54 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> - sum([toInt(x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q54, q55]) | q55 : int(1..4)]) >= 1 - | q54 : int(1..4)]), - and([q20 + 1 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> - [-toInt(x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q20, q25]) | q25 : int(1..4)] x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> - and([x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q21, q27] = false | q27 : int(1..4)]) - | q21 : int(1..4)]), - x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker <= 4, - and([q22 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> - sum([toInt(x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q22, q23]) | q23 : int(1..4)]) <= 4 - | q22 : int(1..4)]), - 4 = - sum([toInt(q28 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker) * - catchUndef(sum([toInt(x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q28, q29]) - | q29 : int(1..4)]), - 0) - | q28 : int(1..4)]), - and([q32 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> - or([q35 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ - (and([x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q35, q37] != 5 -> - x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence - [q32, x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q35, q37]] - | q37 : int(1..4)]) - /\ - and([x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q32, q38] -> - or([x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q35, q40] != 5 /\ - x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q35, q40] = q38 - | q40 : int(1..4)]) - | q38 : int(1..4)])) - | q35 : int(1..4)]) - | q32 : int(1..4)]), - and([q43 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - or([q46 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ - (and([x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q46, q47] -> - or([x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q43, q49] != 5 /\ - x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q43, q49] = q47 - | q49 : int(1..4)]) - | q47 : int(1..4)]) - /\ - and([x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q43, q51] != 5 -> - x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence - [q46, x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q43, q51]] - | q51 : int(1..4)])) - | q46 : int(1..4)]) - | q43 : int(1..4)]) - diff --git a/tests/exhaustive/basic/partition_06/expected/model_2_2-solution000001.solution b/tests/exhaustive/basic/partition_06/expected/model_2_2-solution000001.solution deleted file mode 100644 index bdecd9ce5b..0000000000 --- a/tests/exhaustive/basic/partition_06/expected/model_2_2-solution000001.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be partition({1, 2}, {3, 4}) -$ Visualisation for x -$ 1 2 -$ 3 4 - diff --git a/tests/exhaustive/basic/partition_06/expected/model_2_2-solution000002.solution b/tests/exhaustive/basic/partition_06/expected/model_2_2-solution000002.solution deleted file mode 100644 index b616543ee7..0000000000 --- a/tests/exhaustive/basic/partition_06/expected/model_2_2-solution000002.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be partition({1, 3}, {2, 4}) -$ Visualisation for x -$ 1 3 -$ 2 4 - diff --git a/tests/exhaustive/basic/partition_06/expected/model_2_2-solution000003.solution b/tests/exhaustive/basic/partition_06/expected/model_2_2-solution000003.solution deleted file mode 100644 index 8d196199c8..0000000000 --- a/tests/exhaustive/basic/partition_06/expected/model_2_2-solution000003.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be partition({1, 4}, {2, 3}) -$ Visualisation for x -$ 1 4 -$ 2 3 - diff --git a/tests/exhaustive/basic/partition_06/expected/model_2_2.eprime b/tests/exhaustive/basic/partition_06/expected/model_2_2.eprime deleted file mode 100644 index 4220a0f519..0000000000 --- a/tests/exhaustive/basic/partition_06/expected/model_2_2.eprime +++ /dev/null @@ -1,60 +0,0 @@ -language ESSENCE' 1.0 - -find x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker: int(0..4) -find x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy: - matrix indexed by [int(1..4), int(1..4)] of int(1..5) -branching on - [x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker, - x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy] -such that - and([q19 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - sum([toInt(x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q19, q21] != 5) - | q21 : int(1..4)]) - = 2 | q19 : int(1..4)]), - alldifferent_except([toInt(q22 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ - x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q22, q23] != - 5) - * - catchUndef(x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q22, q23], - 0) - | q22 : int(1..4), q23 : int(1..4)], - 0), - and([q24 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - sum([toInt(x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q24, q26] != 5) - | q26 : int(1..4)]) - >= 1 - | q24 : int(1..4)]), - and([q4 + 1 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - [x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q4, q12] | q12 : int(1..4)] x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - and([x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q5, q17] = 1 - | q17 : int(1..4)]) - | q5 : int(1..4)]), - x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker <= 4, - and([q6 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - and([x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q6, q7] < - x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q6, q7 + 1] - \/ x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q6, q7] = 5 - | q7 : int(1..3)]) - | q6 : int(1..4)]), - and([q6 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - and([x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q6, q8] = 5 -> - x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q6, q8 + 1] = 5 - | q8 : int(1..3)]) - | q6 : int(1..4)]), - and([q6 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - sum([toInt(x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q6, q9] != 5) - | q9 : int(1..4)]) - <= 4 - | q6 : int(1..4)]), - 4 = - sum([toInt(q14 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker) * - catchUndef(sum([toInt(x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q14, q16] != - 5) - | q16 : int(1..4)]), - 0) - | q14 : int(1..4)]) - diff --git a/tests/exhaustive/basic/partition_06/expected/model_2_3-solution000001.solution b/tests/exhaustive/basic/partition_06/expected/model_2_3-solution000001.solution deleted file mode 100644 index bdecd9ce5b..0000000000 --- a/tests/exhaustive/basic/partition_06/expected/model_2_3-solution000001.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be partition({1, 2}, {3, 4}) -$ Visualisation for x -$ 1 2 -$ 3 4 - diff --git a/tests/exhaustive/basic/partition_06/expected/model_2_3-solution000002.solution b/tests/exhaustive/basic/partition_06/expected/model_2_3-solution000002.solution deleted file mode 100644 index b616543ee7..0000000000 --- a/tests/exhaustive/basic/partition_06/expected/model_2_3-solution000002.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be partition({1, 3}, {2, 4}) -$ Visualisation for x -$ 1 3 -$ 2 4 - diff --git a/tests/exhaustive/basic/partition_06/expected/model_2_3-solution000003.solution b/tests/exhaustive/basic/partition_06/expected/model_2_3-solution000003.solution deleted file mode 100644 index 8d196199c8..0000000000 --- a/tests/exhaustive/basic/partition_06/expected/model_2_3-solution000003.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be partition({1, 4}, {2, 3}) -$ Visualisation for x -$ 1 4 -$ 2 3 - diff --git a/tests/exhaustive/basic/partition_06/expected/model_2_3.eprime b/tests/exhaustive/basic/partition_06/expected/model_2_3.eprime deleted file mode 100644 index 7badd3fc56..0000000000 --- a/tests/exhaustive/basic/partition_06/expected/model_2_3.eprime +++ /dev/null @@ -1,157 +0,0 @@ -language ESSENCE' 1.0 - -find x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker: int(0..4) -find x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy: - matrix indexed by [int(1..4), int(1..4)] of int(1..5) -find x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker: int(0..4) -find x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker: - matrix indexed by [int(1..4)] of int(0..4) -find x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values: - matrix indexed by [int(1..4), int(1..4)] of int(1..4) -branching on - [x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker, - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker, - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values, - x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker, - x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy] -such that - and([q61 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - sum([toInt(x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q61, q63] != 5) - | q63 : int(1..4)]) - = 2 | q61 : int(1..4)]), - alldifferent_except([toInt(q64 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ - x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q64, q65] != - 5) - * - catchUndef(x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q64, q65], - 0) - | q64 : int(1..4), q65 : int(1..4)], - 0), - and([q66 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - sum([toInt(x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q66, q68] != 5) - | q68 : int(1..4)]) - >= 1 - | q66 : int(1..4)]), - and([q4 + 1 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - [x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q4, q12] | q12 : int(1..4)] x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - and([x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q5, q58] = 1 - | q58 : int(1..4)]) - | q5 : int(1..4)]), - x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker <= 4, - and([q6 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - and([x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q6, q7] < - x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q6, q7 + 1] - \/ x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q6, q7] = 5 - | q7 : int(1..3)]) - | q6 : int(1..4)]), - and([q6 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - and([x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q6, q8] = 5 -> - x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q6, q8 + 1] = 5 - | q8 : int(1..3)]) - | q6 : int(1..4)]), - and([q6 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - sum([toInt(x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q6, q9] != 5) - | q9 : int(1..4)]) - <= 4 - | q6 : int(1..4)]), - 4 = - sum([toInt(q14 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker) * - catchUndef(sum([toInt(x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q14, q16] != - 5) - | q16 : int(1..4)]), - 0) - | q14 : int(1..4)]), - alldifferent_except([toInt(q69 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - q70 <= - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q69]) - * - catchUndef(x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q69, q70], - 0) - | q69 : int(1..4), q70 : int(1..4)], - 0), - and([q71 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q71] >= 1 - | q71 : int(1..4)]), - and([q20 + 1 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - flatten([[x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q20]; int(1)], - flatten([[x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q20, q27]; - int(1)] - | q27 : int(1..4)]); - int(1..2)]) - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q21] = 0 /\ - and([x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q21, q59] = 1 - | q59 : int(1..4)]) - | q21 : int(1..4)]), - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker <= 4, - and([q22 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - and([q23 + 1 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q22] -> - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q22, q23] < - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q22, q23 + 1] - | q23 : int(1..3)]) - | q22 : int(1..4)]), - and([q22 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - and([q24 > x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q22] -> - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q22, q24] = 1 - | q24 : int(1..4)]) - | q22 : int(1..4)]), - and([q22 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q22] <= 4 - | q22 : int(1..4)]), - 4 = - sum([toInt(q29 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker) * - catchUndef(x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q29], 0) - | q29 : int(1..4)]), - and([q32 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - or([q35 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ - (and([x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q35, q37] != 5 -> - or([q39 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q32] - /\ - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q32, q39] = - x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q35, q37] - | q39 : int(1..4)]) - | q37 : int(1..4)]) - /\ - and([q41 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q32] -> - or([x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q35, q43] != 5 /\ - x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q35, q43] = - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q32, q41] - | q43 : int(1..4)]) - | q41 : int(1..4)])) - | q35 : int(1..4)]) - | q32 : int(1..4)]), - and([q46 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - or([q49 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - (and([q51 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q49] -> - or([x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q46, q53] != 5 /\ - x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q46, q53] = - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q49, q51] - | q53 : int(1..4)]) - | q51 : int(1..4)]) - /\ - and([x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q46, q55] != 5 -> - or([q57 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q49] - /\ - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q49, q57] = - x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q46, q55] - | q57 : int(1..4)]) - | q55 : int(1..4)])) - | q49 : int(1..4)]) - | q46 : int(1..4)]) - diff --git a/tests/exhaustive/basic/partition_06/expected/model_2_4-solution000001.solution b/tests/exhaustive/basic/partition_06/expected/model_2_4-solution000001.solution deleted file mode 100644 index bdecd9ce5b..0000000000 --- a/tests/exhaustive/basic/partition_06/expected/model_2_4-solution000001.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be partition({1, 2}, {3, 4}) -$ Visualisation for x -$ 1 2 -$ 3 4 - diff --git a/tests/exhaustive/basic/partition_06/expected/model_2_4-solution000002.solution b/tests/exhaustive/basic/partition_06/expected/model_2_4-solution000002.solution deleted file mode 100644 index b616543ee7..0000000000 --- a/tests/exhaustive/basic/partition_06/expected/model_2_4-solution000002.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be partition({1, 3}, {2, 4}) -$ Visualisation for x -$ 1 3 -$ 2 4 - diff --git a/tests/exhaustive/basic/partition_06/expected/model_2_4-solution000003.solution b/tests/exhaustive/basic/partition_06/expected/model_2_4-solution000003.solution deleted file mode 100644 index 8d196199c8..0000000000 --- a/tests/exhaustive/basic/partition_06/expected/model_2_4-solution000003.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be partition({1, 4}, {2, 3}) -$ Visualisation for x -$ 1 4 -$ 2 3 - diff --git a/tests/exhaustive/basic/partition_06/expected/model_2_4.eprime b/tests/exhaustive/basic/partition_06/expected/model_2_4.eprime deleted file mode 100644 index bbbd3ba3be..0000000000 --- a/tests/exhaustive/basic/partition_06/expected/model_2_4.eprime +++ /dev/null @@ -1,116 +0,0 @@ -language ESSENCE' 1.0 - -find x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker: int(0..4) -find x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy: - matrix indexed by [int(1..4), int(1..4)] of int(1..5) -find x_PartitionOccurrence_NumParts: int(1..4) -find x_PartitionOccurrence_WhichPart: matrix indexed by [int(1..4)] of int(1..4) -find x_PartitionOccurrence_PartSizes: matrix indexed by [int(1..4)] of int(0..4) -find x_PartitionOccurrence_FirstIndex: matrix indexed by [int(1..4)] of int(1..4) -branching on - [x_PartitionOccurrence_NumParts, x_PartitionOccurrence_WhichPart, x_PartitionOccurrence_PartSizes, - x_PartitionOccurrence_FirstIndex, x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker, - x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy] -such that - and([q57 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - sum([toInt(x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q57, q59] != 5) - | q59 : int(1..4)]) - = 2 | q57 : int(1..4)]), - alldifferent_except([toInt(q60 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ - x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q60, q61] != - 5) - * - catchUndef(x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q60, q61], - 0) - | q60 : int(1..4), q61 : int(1..4)], - 0), - and([q62 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - sum([toInt(x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q62, q64] != 5) - | q64 : int(1..4)]) - >= 1 - | q62 : int(1..4)]), - and([q4 + 1 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - [x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q4, q12] | q12 : int(1..4)] x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - and([x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q5, q27] = 1 - | q27 : int(1..4)]) - | q5 : int(1..4)]), - x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker <= 4, - and([q6 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - and([x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q6, q7] < - x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q6, q7 + 1] - \/ x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q6, q7] = 5 - | q7 : int(1..3)]) - | q6 : int(1..4)]), - and([q6 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - and([x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q6, q8] = 5 -> - x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q6, q8 + 1] = 5 - | q8 : int(1..3)]) - | q6 : int(1..4)]), - and([q6 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - sum([toInt(x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q6, q9] != 5) - | q9 : int(1..4)]) - <= 4 - | q6 : int(1..4)]), - 4 = - sum([toInt(q14 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker) * - catchUndef(sum([toInt(x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q14, q16] != - 5) - | q16 : int(1..4)]), - 0) - | q14 : int(1..4)]), - and([q17 <= x_PartitionOccurrence_NumParts -> x_PartitionOccurrence_PartSizes[q17] <= 4 | q17 : int(1..4)]), - and([q17 > x_PartitionOccurrence_NumParts -> x_PartitionOccurrence_PartSizes[q17] = 0 | q17 : int(1..4)]), - x_PartitionOccurrence_NumParts <= 4, - and([q18 <= x_PartitionOccurrence_NumParts -> or([x_PartitionOccurrence_WhichPart[q19] = q18 | q19 : int(1..4)]) - | q18 : int(3..4)]), - x_PartitionOccurrence_NumParts = max([x_PartitionOccurrence_WhichPart[q20] | q20 : int(1..4)]), - and([x_PartitionOccurrence_PartSizes[q21] = - sum([toInt(x_PartitionOccurrence_WhichPart[q22] = q21) | q22 : int(1..4)]) - | q21 : int(1..4)]), - and([q23 <= x_PartitionOccurrence_NumParts -> - and([x_PartitionOccurrence_WhichPart[q24] = q23 -> x_PartitionOccurrence_FirstIndex[q23] <= q24 - | q24 : int(1..4)]) - | q23 : int(1..4)]), - and([q23 <= x_PartitionOccurrence_NumParts -> - or([x_PartitionOccurrence_WhichPart[q24] = q23 /\ x_PartitionOccurrence_FirstIndex[q23] = q24 - | q24 : int(1..4)]) - | q23 : int(1..4)]), - and([q23 > x_PartitionOccurrence_NumParts -> x_PartitionOccurrence_FirstIndex[q23] = 1 | q23 : int(1..4)]), - and([q25 <= x_PartitionOccurrence_NumParts /\ q26 <= x_PartitionOccurrence_NumParts -> - (q25 < q26 <-> x_PartitionOccurrence_FirstIndex[q25] < x_PartitionOccurrence_FirstIndex[q26]) - | q25 : int(1..4), q26 : int(1..4)]), - and([q29 <= x_PartitionOccurrence_NumParts -> - or([q33 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ - (and([x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q33, q35] != 5 -> - or([x_PartitionOccurrence_WhichPart[q37] = q29 /\ - q37 = x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q33, q35] - | q37 : int(1..4)]) - | q35 : int(1..4)]) - /\ - and([x_PartitionOccurrence_WhichPart[q39] = q29 -> - or([x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q33, q41] != 5 /\ - x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q33, q41] = q39 - | q41 : int(1..4)]) - | q39 : int(1..4)])) - | q33 : int(1..4)]) - | q29 : int(1..4)]), - and([q44 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - or([q46 <= x_PartitionOccurrence_NumParts /\ - (and([x_PartitionOccurrence_WhichPart[q49] = q46 -> - or([x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q44, q51] != 5 /\ - x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q44, q51] = q49 - | q51 : int(1..4)]) - | q49 : int(1..4)]) - /\ - and([x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q44, q53] != 5 -> - or([x_PartitionOccurrence_WhichPart[q55] = q46 /\ - q55 = x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q44, q53] - | q55 : int(1..4)]) - | q53 : int(1..4)])) - | q46 : int(1..4)]) - | q44 : int(1..4)]) - diff --git a/tests/exhaustive/basic/partition_06/expected/model_3_1-solution000001.solution b/tests/exhaustive/basic/partition_06/expected/model_3_1-solution000001.solution deleted file mode 100644 index 8d196199c8..0000000000 --- a/tests/exhaustive/basic/partition_06/expected/model_3_1-solution000001.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be partition({1, 4}, {2, 3}) -$ Visualisation for x -$ 1 4 -$ 2 3 - diff --git a/tests/exhaustive/basic/partition_06/expected/model_3_1-solution000002.solution b/tests/exhaustive/basic/partition_06/expected/model_3_1-solution000002.solution deleted file mode 100644 index b616543ee7..0000000000 --- a/tests/exhaustive/basic/partition_06/expected/model_3_1-solution000002.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be partition({1, 3}, {2, 4}) -$ Visualisation for x -$ 1 3 -$ 2 4 - diff --git a/tests/exhaustive/basic/partition_06/expected/model_3_1-solution000003.solution b/tests/exhaustive/basic/partition_06/expected/model_3_1-solution000003.solution deleted file mode 100644 index bdecd9ce5b..0000000000 --- a/tests/exhaustive/basic/partition_06/expected/model_3_1-solution000003.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be partition({1, 2}, {3, 4}) -$ Visualisation for x -$ 1 2 -$ 3 4 - diff --git a/tests/exhaustive/basic/partition_06/expected/model_3_1.eprime b/tests/exhaustive/basic/partition_06/expected/model_3_1.eprime deleted file mode 100644 index 181a1b4158..0000000000 --- a/tests/exhaustive/basic/partition_06/expected/model_3_1.eprime +++ /dev/null @@ -1,130 +0,0 @@ -language ESSENCE' 1.0 - -find x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker: int(0..4) -find x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker: - matrix indexed by [int(1..4)] of int(0..4) -find x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values: - matrix indexed by [int(1..4), int(1..4)] of int(1..4) -find x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker: int(0..4) -find x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence: matrix indexed by [int(1..4), int(1..4)] of bool -branching on - [x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker, - x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence, - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker, - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker, - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values] -such that - and([q54 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q54] = 2 - | q54 : int(1..4)]), - alldifferent_except([toInt(q55 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - q56 <= - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q55]) - * - catchUndef(x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q55, q56], - 0) - | q55 : int(1..4), q56 : int(1..4)], - 0), - and([q57 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q57] >= 1 - | q57 : int(1..4)]), - and([q4 + 1 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - flatten([[x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q4]; int(1)], - flatten([[x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q4, q11]; - int(1)] - | q11 : int(1..4)]); - int(1..2)]) - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q5] = 0 /\ - and([x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q5, q49] = 1 - | q49 : int(1..4)]) - | q5 : int(1..4)]), - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker <= 4, - and([q6 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - and([q7 + 1 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q6] -> - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q6, q7] < - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q6, q7 + 1] - | q7 : int(1..3)]) - | q6 : int(1..4)]), - and([q6 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - and([q8 > x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q6] -> - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q6, q8] = 1 - | q8 : int(1..4)]) - | q6 : int(1..4)]), - and([q6 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q6] <= 4 - | q6 : int(1..4)]), - 4 = - sum([toInt(q13 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker) * - catchUndef(x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q13], 0) - | q13 : int(1..4)]), - and([1 = - sum([toInt(q50 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ - x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q50, q14]) - | q50 : int(1..4)]) - | q14 : int(1..4)]), - and([q51 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> - sum([toInt(x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q51, q52]) | q52 : int(1..4)]) >= 1 - | q51 : int(1..4)]), - and([q17 + 1 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> - [-toInt(x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q17, q22]) | q22 : int(1..4)] x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> - and([x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q18, q24] = false | q24 : int(1..4)]) - | q18 : int(1..4)]), - x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker <= 4, - and([q19 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> - sum([toInt(x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q19, q20]) | q20 : int(1..4)]) <= 4 - | q19 : int(1..4)]), - 4 = - sum([toInt(q25 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker) * - catchUndef(sum([toInt(x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q25, q26]) - | q26 : int(1..4)]), - 0) - | q25 : int(1..4)]), - and([q29 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> - or([q32 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - (and([q34 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q32] -> - x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence - [q29, - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q32, q34]] - | q34 : int(1..4)]) - /\ - and([x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q29, q35] -> - or([q37 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q32] - /\ - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q32, q37] = - q35 | q37 : int(1..4)]) - | q35 : int(1..4)])) - | q32 : int(1..4)]) - | q29 : int(1..4)]), - and([q40 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - or([q43 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ - (and([x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q43, q44] -> - or([q46 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q40] - /\ - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q40, q46] = - q44 | q46 : int(1..4)]) - | q44 : int(1..4)]) - /\ - and([q48 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q40] -> - x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence - [q43, - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q40, q48]] - | q48 : int(1..4)])) - | q43 : int(1..4)]) - | q40 : int(1..4)]) - diff --git a/tests/exhaustive/basic/partition_06/expected/model_3_2-solution000001.solution b/tests/exhaustive/basic/partition_06/expected/model_3_2-solution000001.solution deleted file mode 100644 index bdecd9ce5b..0000000000 --- a/tests/exhaustive/basic/partition_06/expected/model_3_2-solution000001.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be partition({1, 2}, {3, 4}) -$ Visualisation for x -$ 1 2 -$ 3 4 - diff --git a/tests/exhaustive/basic/partition_06/expected/model_3_2-solution000002.solution b/tests/exhaustive/basic/partition_06/expected/model_3_2-solution000002.solution deleted file mode 100644 index b616543ee7..0000000000 --- a/tests/exhaustive/basic/partition_06/expected/model_3_2-solution000002.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be partition({1, 3}, {2, 4}) -$ Visualisation for x -$ 1 3 -$ 2 4 - diff --git a/tests/exhaustive/basic/partition_06/expected/model_3_2-solution000003.solution b/tests/exhaustive/basic/partition_06/expected/model_3_2-solution000003.solution deleted file mode 100644 index 8d196199c8..0000000000 --- a/tests/exhaustive/basic/partition_06/expected/model_3_2-solution000003.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be partition({1, 4}, {2, 3}) -$ Visualisation for x -$ 1 4 -$ 2 3 - diff --git a/tests/exhaustive/basic/partition_06/expected/model_3_2.eprime b/tests/exhaustive/basic/partition_06/expected/model_3_2.eprime deleted file mode 100644 index 69bd264681..0000000000 --- a/tests/exhaustive/basic/partition_06/expected/model_3_2.eprime +++ /dev/null @@ -1,156 +0,0 @@ -language ESSENCE' 1.0 - -find x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker: int(0..4) -find x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker: - matrix indexed by [int(1..4)] of int(0..4) -find x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values: - matrix indexed by [int(1..4), int(1..4)] of int(1..4) -find x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker: int(0..4) -find x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy: - matrix indexed by [int(1..4), int(1..4)] of int(1..5) -branching on - [x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker, - x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy, - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker, - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker, - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values] -such that - and([q61 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q61] = 2 - | q61 : int(1..4)]), - alldifferent_except([toInt(q62 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - q63 <= - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q62]) - * - catchUndef(x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q62, q63], - 0) - | q62 : int(1..4), q63 : int(1..4)], - 0), - and([q64 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q64] >= 1 - | q64 : int(1..4)]), - and([q4 + 1 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - flatten([[x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q4]; int(1)], - flatten([[x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q4, q11]; - int(1)] - | q11 : int(1..4)]); - int(1..2)]) - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q5] = 0 /\ - and([x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q5, q58] = 1 - | q58 : int(1..4)]) - | q5 : int(1..4)]), - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker <= 4, - and([q6 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - and([q7 + 1 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q6] -> - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q6, q7] < - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q6, q7 + 1] - | q7 : int(1..3)]) - | q6 : int(1..4)]), - and([q6 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - and([q8 > x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q6] -> - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q6, q8] = 1 - | q8 : int(1..4)]) - | q6 : int(1..4)]), - and([q6 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q6] <= 4 - | q6 : int(1..4)]), - 4 = - sum([toInt(q13 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker) * - catchUndef(x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q13], 0) - | q13 : int(1..4)]), - alldifferent_except([toInt(q65 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ - x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q65, q66] != - 5) - * - catchUndef(x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q65, q66], - 0) - | q65 : int(1..4), q66 : int(1..4)], - 0), - and([q67 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - sum([toInt(x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q67, q69] != 5) - | q69 : int(1..4)]) - >= 1 - | q67 : int(1..4)]), - and([q17 + 1 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - [x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q17, q25] | q25 : int(1..4)] x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - and([x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q18, q59] = 1 - | q59 : int(1..4)]) - | q18 : int(1..4)]), - x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker <= 4, - and([q19 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - and([x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q19, q20] < - x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q19, q20 + 1] - \/ x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q19, q20] = 5 - | q20 : int(1..3)]) - | q19 : int(1..4)]), - and([q19 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - and([x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q19, q21] = 5 -> - x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q19, q21 + 1] = 5 - | q21 : int(1..3)]) - | q19 : int(1..4)]), - and([q19 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - sum([toInt(x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q19, q22] != 5) - | q22 : int(1..4)]) - <= 4 - | q19 : int(1..4)]), - 4 = - sum([toInt(q27 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker) * - catchUndef(sum([toInt(x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q27, q29] != - 5) - | q29 : int(1..4)]), - 0) - | q27 : int(1..4)]), - and([q32 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - or([q35 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - (and([q37 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q35] -> - or([x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q32, q39] != 5 /\ - x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q32, q39] = - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q35, q37] - | q39 : int(1..4)]) - | q37 : int(1..4)]) - /\ - and([x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q32, q41] != 5 -> - or([q43 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q35] - /\ - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q35, q43] = - x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q32, q41] - | q43 : int(1..4)]) - | q41 : int(1..4)])) - | q35 : int(1..4)]) - | q32 : int(1..4)]), - and([q46 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - or([q49 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ - (and([x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q49, q51] != 5 -> - or([q53 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q46] - /\ - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q46, q53] = - x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q49, q51] - | q53 : int(1..4)]) - | q51 : int(1..4)]) - /\ - and([q55 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q46] -> - or([x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q49, q57] != 5 /\ - x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q49, q57] = - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q46, q55] - | q57 : int(1..4)]) - | q55 : int(1..4)])) - | q49 : int(1..4)]) - | q46 : int(1..4)]) - diff --git a/tests/exhaustive/basic/partition_06/expected/model_3_3-solution000001.solution b/tests/exhaustive/basic/partition_06/expected/model_3_3-solution000001.solution deleted file mode 100644 index bdecd9ce5b..0000000000 --- a/tests/exhaustive/basic/partition_06/expected/model_3_3-solution000001.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be partition({1, 2}, {3, 4}) -$ Visualisation for x -$ 1 2 -$ 3 4 - diff --git a/tests/exhaustive/basic/partition_06/expected/model_3_3-solution000002.solution b/tests/exhaustive/basic/partition_06/expected/model_3_3-solution000002.solution deleted file mode 100644 index b616543ee7..0000000000 --- a/tests/exhaustive/basic/partition_06/expected/model_3_3-solution000002.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be partition({1, 3}, {2, 4}) -$ Visualisation for x -$ 1 3 -$ 2 4 - diff --git a/tests/exhaustive/basic/partition_06/expected/model_3_3-solution000003.solution b/tests/exhaustive/basic/partition_06/expected/model_3_3-solution000003.solution deleted file mode 100644 index 8d196199c8..0000000000 --- a/tests/exhaustive/basic/partition_06/expected/model_3_3-solution000003.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be partition({1, 4}, {2, 3}) -$ Visualisation for x -$ 1 4 -$ 2 3 - diff --git a/tests/exhaustive/basic/partition_06/expected/model_3_3.eprime b/tests/exhaustive/basic/partition_06/expected/model_3_3.eprime deleted file mode 100644 index b8a4ab8b6e..0000000000 --- a/tests/exhaustive/basic/partition_06/expected/model_3_3.eprime +++ /dev/null @@ -1,69 +0,0 @@ -language ESSENCE' 1.0 - -find x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker: int(0..4) -find x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker: - matrix indexed by [int(1..4)] of int(0..4) -find x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values: - matrix indexed by [int(1..4), int(1..4)] of int(1..4) -branching on - [x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker, - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker, - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values] -such that - and([q16 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q16] = 2 - | q16 : int(1..4)]), - alldifferent_except([toInt(q17 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - q18 <= - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q17]) - * - catchUndef(x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q17, q18], - 0) - | q17 : int(1..4), q18 : int(1..4)], - 0), - and([q19 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q19] >= 1 - | q19 : int(1..4)]), - and([q4 + 1 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - flatten([[x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q4]; int(1)], - flatten([[x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q4, q11]; - int(1)] - | q11 : int(1..4)]); - int(1..2)]) - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q5] = 0 /\ - and([x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q5, q14] = 1 - | q14 : int(1..4)]) - | q5 : int(1..4)]), - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker <= 4, - and([q6 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - and([q7 + 1 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q6] -> - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q6, q7] < - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q6, q7 + 1] - | q7 : int(1..3)]) - | q6 : int(1..4)]), - and([q6 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - and([q8 > x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q6] -> - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q6, q8] = 1 - | q8 : int(1..4)]) - | q6 : int(1..4)]), - and([q6 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q6] <= 4 - | q6 : int(1..4)]), - 4 = - sum([toInt(q13 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker) * - catchUndef(x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q13], 0) - | q13 : int(1..4)]) - diff --git a/tests/exhaustive/basic/partition_06/expected/model_3_4-solution000001.solution b/tests/exhaustive/basic/partition_06/expected/model_3_4-solution000001.solution deleted file mode 100644 index bdecd9ce5b..0000000000 --- a/tests/exhaustive/basic/partition_06/expected/model_3_4-solution000001.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be partition({1, 2}, {3, 4}) -$ Visualisation for x -$ 1 2 -$ 3 4 - diff --git a/tests/exhaustive/basic/partition_06/expected/model_3_4-solution000002.solution b/tests/exhaustive/basic/partition_06/expected/model_3_4-solution000002.solution deleted file mode 100644 index b616543ee7..0000000000 --- a/tests/exhaustive/basic/partition_06/expected/model_3_4-solution000002.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be partition({1, 3}, {2, 4}) -$ Visualisation for x -$ 1 3 -$ 2 4 - diff --git a/tests/exhaustive/basic/partition_06/expected/model_3_4-solution000003.solution b/tests/exhaustive/basic/partition_06/expected/model_3_4-solution000003.solution deleted file mode 100644 index 8d196199c8..0000000000 --- a/tests/exhaustive/basic/partition_06/expected/model_3_4-solution000003.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be partition({1, 4}, {2, 3}) -$ Visualisation for x -$ 1 4 -$ 2 3 - diff --git a/tests/exhaustive/basic/partition_06/expected/model_3_4.eprime b/tests/exhaustive/basic/partition_06/expected/model_3_4.eprime deleted file mode 100644 index 9f6f3cb851..0000000000 --- a/tests/exhaustive/basic/partition_06/expected/model_3_4.eprime +++ /dev/null @@ -1,129 +0,0 @@ -language ESSENCE' 1.0 - -find x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker: int(0..4) -find x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker: - matrix indexed by [int(1..4)] of int(0..4) -find x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values: - matrix indexed by [int(1..4), int(1..4)] of int(1..4) -find x_PartitionOccurrence_NumParts: int(1..4) -find x_PartitionOccurrence_WhichPart: matrix indexed by [int(1..4)] of int(1..4) -find x_PartitionOccurrence_PartSizes: matrix indexed by [int(1..4)] of int(0..4) -find x_PartitionOccurrence_FirstIndex: matrix indexed by [int(1..4)] of int(1..4) -branching on - [x_PartitionOccurrence_NumParts, x_PartitionOccurrence_WhichPart, x_PartitionOccurrence_PartSizes, - x_PartitionOccurrence_FirstIndex, x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker, - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker, - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values] -such that - and([q54 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q54] = 2 - | q54 : int(1..4)]), - alldifferent_except([toInt(q55 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - q56 <= - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q55]) - * - catchUndef(x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q55, q56], - 0) - | q55 : int(1..4), q56 : int(1..4)], - 0), - and([q57 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q57] >= 1 - | q57 : int(1..4)]), - and([q4 + 1 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - flatten([[x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q4]; int(1)], - flatten([[x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q4, q11]; - int(1)] - | q11 : int(1..4)]); - int(1..2)]) - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q5] = 0 /\ - and([x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q5, q24] = 1 - | q24 : int(1..4)]) - | q5 : int(1..4)]), - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker <= 4, - and([q6 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - and([q7 + 1 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q6] -> - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q6, q7] < - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q6, q7 + 1] - | q7 : int(1..3)]) - | q6 : int(1..4)]), - and([q6 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - and([q8 > x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q6] -> - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q6, q8] = 1 - | q8 : int(1..4)]) - | q6 : int(1..4)]), - and([q6 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q6] <= 4 - | q6 : int(1..4)]), - 4 = - sum([toInt(q13 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker) * - catchUndef(x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q13], 0) - | q13 : int(1..4)]), - and([q14 <= x_PartitionOccurrence_NumParts -> x_PartitionOccurrence_PartSizes[q14] <= 4 | q14 : int(1..4)]), - and([q14 > x_PartitionOccurrence_NumParts -> x_PartitionOccurrence_PartSizes[q14] = 0 | q14 : int(1..4)]), - x_PartitionOccurrence_NumParts <= 4, - and([q15 <= x_PartitionOccurrence_NumParts -> or([x_PartitionOccurrence_WhichPart[q16] = q15 | q16 : int(1..4)]) - | q15 : int(3..4)]), - x_PartitionOccurrence_NumParts = max([x_PartitionOccurrence_WhichPart[q17] | q17 : int(1..4)]), - and([x_PartitionOccurrence_PartSizes[q18] = - sum([toInt(x_PartitionOccurrence_WhichPart[q19] = q18) | q19 : int(1..4)]) - | q18 : int(1..4)]), - and([q20 <= x_PartitionOccurrence_NumParts -> - and([x_PartitionOccurrence_WhichPart[q21] = q20 -> x_PartitionOccurrence_FirstIndex[q20] <= q21 - | q21 : int(1..4)]) - | q20 : int(1..4)]), - and([q20 <= x_PartitionOccurrence_NumParts -> - or([x_PartitionOccurrence_WhichPart[q21] = q20 /\ x_PartitionOccurrence_FirstIndex[q20] = q21 - | q21 : int(1..4)]) - | q20 : int(1..4)]), - and([q20 > x_PartitionOccurrence_NumParts -> x_PartitionOccurrence_FirstIndex[q20] = 1 | q20 : int(1..4)]), - and([q22 <= x_PartitionOccurrence_NumParts /\ q23 <= x_PartitionOccurrence_NumParts -> - (q22 < q23 <-> x_PartitionOccurrence_FirstIndex[q22] < x_PartitionOccurrence_FirstIndex[q23]) - | q22 : int(1..4), q23 : int(1..4)]), - and([q26 <= x_PartitionOccurrence_NumParts -> - or([q30 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - (and([q32 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q30] -> - or([x_PartitionOccurrence_WhichPart[q34] = q26 /\ - q34 = - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q30, q32] - | q34 : int(1..4)]) - | q32 : int(1..4)]) - /\ - and([x_PartitionOccurrence_WhichPart[q36] = q26 -> - or([q38 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q30] - /\ - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q30, q38] = - q36 | q38 : int(1..4)]) - | q36 : int(1..4)])) - | q30 : int(1..4)]) - | q26 : int(1..4)]), - and([q41 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - or([q43 <= x_PartitionOccurrence_NumParts /\ - (and([x_PartitionOccurrence_WhichPart[q46] = q43 -> - or([q48 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q41] - /\ - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q41, q48] = - q46 | q48 : int(1..4)]) - | q46 : int(1..4)]) - /\ - and([q50 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q41] -> - or([x_PartitionOccurrence_WhichPart[q52] = q43 /\ - q52 = - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q41, q50] - | q52 : int(1..4)]) - | q50 : int(1..4)])) - | q43 : int(1..4)]) - | q41 : int(1..4)]) - diff --git a/tests/exhaustive/basic/partition_06/expected/model_4_1-solution000001.solution b/tests/exhaustive/basic/partition_06/expected/model_4_1-solution000001.solution deleted file mode 100644 index 8d196199c8..0000000000 --- a/tests/exhaustive/basic/partition_06/expected/model_4_1-solution000001.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be partition({1, 4}, {2, 3}) -$ Visualisation for x -$ 1 4 -$ 2 3 - diff --git a/tests/exhaustive/basic/partition_06/expected/model_4_1-solution000002.solution b/tests/exhaustive/basic/partition_06/expected/model_4_1-solution000002.solution deleted file mode 100644 index b616543ee7..0000000000 --- a/tests/exhaustive/basic/partition_06/expected/model_4_1-solution000002.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be partition({1, 3}, {2, 4}) -$ Visualisation for x -$ 1 3 -$ 2 4 - diff --git a/tests/exhaustive/basic/partition_06/expected/model_4_1-solution000003.solution b/tests/exhaustive/basic/partition_06/expected/model_4_1-solution000003.solution deleted file mode 100644 index bdecd9ce5b..0000000000 --- a/tests/exhaustive/basic/partition_06/expected/model_4_1-solution000003.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be partition({1, 2}, {3, 4}) -$ Visualisation for x -$ 1 2 -$ 3 4 - diff --git a/tests/exhaustive/basic/partition_06/expected/model_4_1.eprime b/tests/exhaustive/basic/partition_06/expected/model_4_1.eprime deleted file mode 100644 index 7b16b63344..0000000000 --- a/tests/exhaustive/basic/partition_06/expected/model_4_1.eprime +++ /dev/null @@ -1,82 +0,0 @@ -language ESSENCE' 1.0 - -find x_PartitionOccurrence_NumParts: int(1..4) -find x_PartitionOccurrence_WhichPart: matrix indexed by [int(1..4)] of int(1..4) -find x_PartitionOccurrence_PartSizes: matrix indexed by [int(1..4)] of int(0..4) -find x_PartitionOccurrence_FirstIndex: matrix indexed by [int(1..4)] of int(1..4) -find x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker: int(0..4) -find x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence: matrix indexed by [int(1..4), int(1..4)] of bool -branching on - [x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker, - x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence, x_PartitionOccurrence_NumParts, - x_PartitionOccurrence_WhichPart, x_PartitionOccurrence_PartSizes, x_PartitionOccurrence_FirstIndex] -such that - and([q49 <= x_PartitionOccurrence_NumParts -> - sum([toInt(x_PartitionOccurrence_WhichPart[q52] = q49) | q52 : int(1..4)]) = 2 - | q49 : int(1..4)]), - and([q1 <= x_PartitionOccurrence_NumParts -> x_PartitionOccurrence_PartSizes[q1] <= 4 | q1 : int(1..4)]), - and([q1 > x_PartitionOccurrence_NumParts -> x_PartitionOccurrence_PartSizes[q1] = 0 | q1 : int(1..4)]), - x_PartitionOccurrence_NumParts <= 4, - and([q2 <= x_PartitionOccurrence_NumParts -> or([x_PartitionOccurrence_WhichPart[q3] = q2 | q3 : int(1..4)]) - | q2 : int(3..4)]), - x_PartitionOccurrence_NumParts = max([x_PartitionOccurrence_WhichPart[q4] | q4 : int(1..4)]), - and([x_PartitionOccurrence_PartSizes[q5] = sum([toInt(x_PartitionOccurrence_WhichPart[q6] = q5) | q6 : int(1..4)]) - | q5 : int(1..4)]), - and([q7 <= x_PartitionOccurrence_NumParts -> - and([x_PartitionOccurrence_WhichPart[q8] = q7 -> x_PartitionOccurrence_FirstIndex[q7] <= q8 | q8 : int(1..4)]) - | q7 : int(1..4)]), - and([q7 <= x_PartitionOccurrence_NumParts -> - or([x_PartitionOccurrence_WhichPart[q8] = q7 /\ x_PartitionOccurrence_FirstIndex[q7] = q8 | q8 : int(1..4)]) - | q7 : int(1..4)]), - and([q7 > x_PartitionOccurrence_NumParts -> x_PartitionOccurrence_FirstIndex[q7] = 1 | q7 : int(1..4)]), - and([q9 <= x_PartitionOccurrence_NumParts /\ q10 <= x_PartitionOccurrence_NumParts -> - (q9 < q10 <-> x_PartitionOccurrence_FirstIndex[q9] < x_PartitionOccurrence_FirstIndex[q10]) - | q9 : int(1..4), q10 : int(1..4)]), - and([1 = - sum([toInt(q46 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ - x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q46, q11]) - | q46 : int(1..4)]) - | q11 : int(1..4)]), - and([q47 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> - sum([toInt(x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q47, q48]) | q48 : int(1..4)]) >= 1 - | q47 : int(1..4)]), - and([q14 + 1 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> - [-toInt(x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q14, q19]) | q19 : int(1..4)] x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> - and([x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q15, q21] = false | q21 : int(1..4)]) - | q15 : int(1..4)]), - x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker <= 4, - and([q16 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> - sum([toInt(x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q16, q17]) | q17 : int(1..4)]) <= 4 - | q16 : int(1..4)]), - 4 = - sum([toInt(q22 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker) * - catchUndef(sum([toInt(x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q22, q23]) - | q23 : int(1..4)]), - 0) - | q22 : int(1..4)]), - and([q26 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> - or([q28 <= x_PartitionOccurrence_NumParts /\ - (and([x_PartitionOccurrence_WhichPart[q31] = q28 -> - x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q26, q31] - | q31 : int(1..4)]) - /\ - and([x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q26, q32] -> - or([x_PartitionOccurrence_WhichPart[q34] = q28 /\ q34 = q32 | q34 : int(1..4)]) - | q32 : int(1..4)])) - | q28 : int(1..4)]) - | q26 : int(1..4)]), - and([q36 <= x_PartitionOccurrence_NumParts -> - or([q40 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ - (and([x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q40, q41] -> - or([x_PartitionOccurrence_WhichPart[q43] = q36 /\ q43 = q41 | q43 : int(1..4)]) - | q41 : int(1..4)]) - /\ - and([x_PartitionOccurrence_WhichPart[q45] = q36 -> - x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q40, q45] - | q45 : int(1..4)])) - | q40 : int(1..4)]) - | q36 : int(1..4)]) - diff --git a/tests/exhaustive/basic/partition_06/expected/model_4_2-solution000001.solution b/tests/exhaustive/basic/partition_06/expected/model_4_2-solution000001.solution deleted file mode 100644 index bdecd9ce5b..0000000000 --- a/tests/exhaustive/basic/partition_06/expected/model_4_2-solution000001.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be partition({1, 2}, {3, 4}) -$ Visualisation for x -$ 1 2 -$ 3 4 - diff --git a/tests/exhaustive/basic/partition_06/expected/model_4_2-solution000002.solution b/tests/exhaustive/basic/partition_06/expected/model_4_2-solution000002.solution deleted file mode 100644 index b616543ee7..0000000000 --- a/tests/exhaustive/basic/partition_06/expected/model_4_2-solution000002.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be partition({1, 3}, {2, 4}) -$ Visualisation for x -$ 1 3 -$ 2 4 - diff --git a/tests/exhaustive/basic/partition_06/expected/model_4_2-solution000003.solution b/tests/exhaustive/basic/partition_06/expected/model_4_2-solution000003.solution deleted file mode 100644 index 8d196199c8..0000000000 --- a/tests/exhaustive/basic/partition_06/expected/model_4_2-solution000003.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be partition({1, 4}, {2, 3}) -$ Visualisation for x -$ 1 4 -$ 2 3 - diff --git a/tests/exhaustive/basic/partition_06/expected/model_4_2.eprime b/tests/exhaustive/basic/partition_06/expected/model_4_2.eprime deleted file mode 100644 index 7413ed3262..0000000000 --- a/tests/exhaustive/basic/partition_06/expected/model_4_2.eprime +++ /dev/null @@ -1,112 +0,0 @@ -language ESSENCE' 1.0 - -find x_PartitionOccurrence_NumParts: int(1..4) -find x_PartitionOccurrence_WhichPart: matrix indexed by [int(1..4)] of int(1..4) -find x_PartitionOccurrence_PartSizes: matrix indexed by [int(1..4)] of int(0..4) -find x_PartitionOccurrence_FirstIndex: matrix indexed by [int(1..4)] of int(1..4) -find x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker: int(0..4) -find x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy: - matrix indexed by [int(1..4), int(1..4)] of int(1..5) -branching on - [x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker, - x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy, x_PartitionOccurrence_NumParts, - x_PartitionOccurrence_WhichPart, x_PartitionOccurrence_PartSizes, x_PartitionOccurrence_FirstIndex] -such that - and([q56 <= x_PartitionOccurrence_NumParts -> - sum([toInt(x_PartitionOccurrence_WhichPart[q59] = q56) | q59 : int(1..4)]) = 2 - | q56 : int(1..4)]), - and([q1 <= x_PartitionOccurrence_NumParts -> x_PartitionOccurrence_PartSizes[q1] <= 4 | q1 : int(1..4)]), - and([q1 > x_PartitionOccurrence_NumParts -> x_PartitionOccurrence_PartSizes[q1] = 0 | q1 : int(1..4)]), - x_PartitionOccurrence_NumParts <= 4, - and([q2 <= x_PartitionOccurrence_NumParts -> or([x_PartitionOccurrence_WhichPart[q3] = q2 | q3 : int(1..4)]) - | q2 : int(3..4)]), - x_PartitionOccurrence_NumParts = max([x_PartitionOccurrence_WhichPart[q4] | q4 : int(1..4)]), - and([x_PartitionOccurrence_PartSizes[q5] = sum([toInt(x_PartitionOccurrence_WhichPart[q6] = q5) | q6 : int(1..4)]) - | q5 : int(1..4)]), - and([q7 <= x_PartitionOccurrence_NumParts -> - and([x_PartitionOccurrence_WhichPart[q8] = q7 -> x_PartitionOccurrence_FirstIndex[q7] <= q8 | q8 : int(1..4)]) - | q7 : int(1..4)]), - and([q7 <= x_PartitionOccurrence_NumParts -> - or([x_PartitionOccurrence_WhichPart[q8] = q7 /\ x_PartitionOccurrence_FirstIndex[q7] = q8 | q8 : int(1..4)]) - | q7 : int(1..4)]), - and([q7 > x_PartitionOccurrence_NumParts -> x_PartitionOccurrence_FirstIndex[q7] = 1 | q7 : int(1..4)]), - and([q9 <= x_PartitionOccurrence_NumParts /\ q10 <= x_PartitionOccurrence_NumParts -> - (q9 < q10 <-> x_PartitionOccurrence_FirstIndex[q9] < x_PartitionOccurrence_FirstIndex[q10]) - | q9 : int(1..4), q10 : int(1..4)]), - alldifferent_except([toInt(q60 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ - x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q60, q61] != - 5) - * - catchUndef(x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q60, q61], - 0) - | q60 : int(1..4), q61 : int(1..4)], - 0), - and([q62 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - sum([toInt(x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q62, q64] != 5) - | q64 : int(1..4)]) - >= 1 - | q62 : int(1..4)]), - and([q14 + 1 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - [x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q14, q22] | q22 : int(1..4)] x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - and([x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q15, q55] = 1 - | q55 : int(1..4)]) - | q15 : int(1..4)]), - x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker <= 4, - and([q16 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - and([x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q16, q17] < - x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q16, q17 + 1] - \/ x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q16, q17] = 5 - | q17 : int(1..3)]) - | q16 : int(1..4)]), - and([q16 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - and([x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q16, q18] = 5 -> - x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q16, q18 + 1] = 5 - | q18 : int(1..3)]) - | q16 : int(1..4)]), - and([q16 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - sum([toInt(x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q16, q19] != 5) - | q19 : int(1..4)]) - <= 4 - | q16 : int(1..4)]), - 4 = - sum([toInt(q24 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker) * - catchUndef(sum([toInt(x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q24, q26] != - 5) - | q26 : int(1..4)]), - 0) - | q24 : int(1..4)]), - and([q29 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - or([q31 <= x_PartitionOccurrence_NumParts /\ - (and([x_PartitionOccurrence_WhichPart[q34] = q31 -> - or([x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q29, q36] != 5 /\ - x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q29, q36] = q34 - | q36 : int(1..4)]) - | q34 : int(1..4)]) - /\ - and([x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q29, q38] != 5 -> - or([x_PartitionOccurrence_WhichPart[q40] = q31 /\ - q40 = x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q29, q38] - | q40 : int(1..4)]) - | q38 : int(1..4)])) - | q31 : int(1..4)]) - | q29 : int(1..4)]), - and([q42 <= x_PartitionOccurrence_NumParts -> - or([q46 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ - (and([x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q46, q48] != 5 -> - or([x_PartitionOccurrence_WhichPart[q50] = q42 /\ - q50 = x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q46, q48] - | q50 : int(1..4)]) - | q48 : int(1..4)]) - /\ - and([x_PartitionOccurrence_WhichPart[q52] = q42 -> - or([x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q46, q54] != 5 /\ - x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q46, q54] = q52 - | q54 : int(1..4)]) - | q52 : int(1..4)])) - | q46 : int(1..4)]) - | q42 : int(1..4)]) - diff --git a/tests/exhaustive/basic/partition_06/expected/model_4_3-solution000001.solution b/tests/exhaustive/basic/partition_06/expected/model_4_3-solution000001.solution deleted file mode 100644 index bdecd9ce5b..0000000000 --- a/tests/exhaustive/basic/partition_06/expected/model_4_3-solution000001.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be partition({1, 2}, {3, 4}) -$ Visualisation for x -$ 1 2 -$ 3 4 - diff --git a/tests/exhaustive/basic/partition_06/expected/model_4_3-solution000002.solution b/tests/exhaustive/basic/partition_06/expected/model_4_3-solution000002.solution deleted file mode 100644 index b616543ee7..0000000000 --- a/tests/exhaustive/basic/partition_06/expected/model_4_3-solution000002.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be partition({1, 3}, {2, 4}) -$ Visualisation for x -$ 1 3 -$ 2 4 - diff --git a/tests/exhaustive/basic/partition_06/expected/model_4_3-solution000003.solution b/tests/exhaustive/basic/partition_06/expected/model_4_3-solution000003.solution deleted file mode 100644 index 8d196199c8..0000000000 --- a/tests/exhaustive/basic/partition_06/expected/model_4_3-solution000003.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be partition({1, 4}, {2, 3}) -$ Visualisation for x -$ 1 4 -$ 2 3 - diff --git a/tests/exhaustive/basic/partition_06/expected/model_4_3.eprime b/tests/exhaustive/basic/partition_06/expected/model_4_3.eprime deleted file mode 100644 index 30afcd8ed6..0000000000 --- a/tests/exhaustive/basic/partition_06/expected/model_4_3.eprime +++ /dev/null @@ -1,127 +0,0 @@ -language ESSENCE' 1.0 - -find x_PartitionOccurrence_NumParts: int(1..4) -find x_PartitionOccurrence_WhichPart: matrix indexed by [int(1..4)] of int(1..4) -find x_PartitionOccurrence_PartSizes: matrix indexed by [int(1..4)] of int(0..4) -find x_PartitionOccurrence_FirstIndex: matrix indexed by [int(1..4)] of int(1..4) -find x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker: int(0..4) -find x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker: - matrix indexed by [int(1..4)] of int(0..4) -find x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values: - matrix indexed by [int(1..4), int(1..4)] of int(1..4) -branching on - [x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker, - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker, - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values, - x_PartitionOccurrence_NumParts, x_PartitionOccurrence_WhichPart, x_PartitionOccurrence_PartSizes, - x_PartitionOccurrence_FirstIndex] -such that - and([q53 <= x_PartitionOccurrence_NumParts -> - sum([toInt(x_PartitionOccurrence_WhichPart[q56] = q53) | q56 : int(1..4)]) = 2 - | q53 : int(1..4)]), - and([q1 <= x_PartitionOccurrence_NumParts -> x_PartitionOccurrence_PartSizes[q1] <= 4 | q1 : int(1..4)]), - and([q1 > x_PartitionOccurrence_NumParts -> x_PartitionOccurrence_PartSizes[q1] = 0 | q1 : int(1..4)]), - x_PartitionOccurrence_NumParts <= 4, - and([q2 <= x_PartitionOccurrence_NumParts -> or([x_PartitionOccurrence_WhichPart[q3] = q2 | q3 : int(1..4)]) - | q2 : int(3..4)]), - x_PartitionOccurrence_NumParts = max([x_PartitionOccurrence_WhichPart[q4] | q4 : int(1..4)]), - and([x_PartitionOccurrence_PartSizes[q5] = sum([toInt(x_PartitionOccurrence_WhichPart[q6] = q5) | q6 : int(1..4)]) - | q5 : int(1..4)]), - and([q7 <= x_PartitionOccurrence_NumParts -> - and([x_PartitionOccurrence_WhichPart[q8] = q7 -> x_PartitionOccurrence_FirstIndex[q7] <= q8 | q8 : int(1..4)]) - | q7 : int(1..4)]), - and([q7 <= x_PartitionOccurrence_NumParts -> - or([x_PartitionOccurrence_WhichPart[q8] = q7 /\ x_PartitionOccurrence_FirstIndex[q7] = q8 | q8 : int(1..4)]) - | q7 : int(1..4)]), - and([q7 > x_PartitionOccurrence_NumParts -> x_PartitionOccurrence_FirstIndex[q7] = 1 | q7 : int(1..4)]), - and([q9 <= x_PartitionOccurrence_NumParts /\ q10 <= x_PartitionOccurrence_NumParts -> - (q9 < q10 <-> x_PartitionOccurrence_FirstIndex[q9] < x_PartitionOccurrence_FirstIndex[q10]) - | q9 : int(1..4), q10 : int(1..4)]), - alldifferent_except([toInt(q57 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - q58 <= - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q57]) - * - catchUndef(x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q57, q58], - 0) - | q57 : int(1..4), q58 : int(1..4)], - 0), - and([q59 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q59] >= 1 - | q59 : int(1..4)]), - and([q14 + 1 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - flatten([[x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q14]; int(1)], - flatten([[x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q14, q21]; - int(1)] - | q21 : int(1..4)]); - int(1..2)]) - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q15] = 0 /\ - and([x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q15, q52] = 1 - | q52 : int(1..4)]) - | q15 : int(1..4)]), - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker <= 4, - and([q16 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - and([q17 + 1 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q16] -> - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q16, q17] < - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q16, q17 + 1] - | q17 : int(1..3)]) - | q16 : int(1..4)]), - and([q16 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - and([q18 > x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q16] -> - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q16, q18] = 1 - | q18 : int(1..4)]) - | q16 : int(1..4)]), - and([q16 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q16] <= 4 - | q16 : int(1..4)]), - 4 = - sum([toInt(q23 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker) * - catchUndef(x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q23], 0) - | q23 : int(1..4)]), - and([q26 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - or([q28 <= x_PartitionOccurrence_NumParts /\ - (and([x_PartitionOccurrence_WhichPart[q31] = q28 -> - or([q33 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q26] - /\ - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q26, q33] = - q31 | q33 : int(1..4)]) - | q31 : int(1..4)]) - /\ - and([q35 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q26] -> - or([x_PartitionOccurrence_WhichPart[q37] = q28 /\ - q37 = - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q26, q35] - | q37 : int(1..4)]) - | q35 : int(1..4)])) - | q28 : int(1..4)]) - | q26 : int(1..4)]), - and([q39 <= x_PartitionOccurrence_NumParts -> - or([q43 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - (and([q45 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q43] -> - or([x_PartitionOccurrence_WhichPart[q47] = q39 /\ - q47 = - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q43, q45] - | q47 : int(1..4)]) - | q45 : int(1..4)]) - /\ - and([x_PartitionOccurrence_WhichPart[q49] = q39 -> - or([q51 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q43] - /\ - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q43, q51] = - q49 | q51 : int(1..4)]) - | q49 : int(1..4)])) - | q43 : int(1..4)]) - | q39 : int(1..4)]) - diff --git a/tests/exhaustive/basic/partition_06/expected/model_4_4-solution000001.solution b/tests/exhaustive/basic/partition_06/expected/model_4_4-solution000001.solution deleted file mode 100644 index bdecd9ce5b..0000000000 --- a/tests/exhaustive/basic/partition_06/expected/model_4_4-solution000001.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be partition({1, 2}, {3, 4}) -$ Visualisation for x -$ 1 2 -$ 3 4 - diff --git a/tests/exhaustive/basic/partition_06/expected/model_4_4-solution000002.solution b/tests/exhaustive/basic/partition_06/expected/model_4_4-solution000002.solution deleted file mode 100644 index b616543ee7..0000000000 --- a/tests/exhaustive/basic/partition_06/expected/model_4_4-solution000002.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be partition({1, 3}, {2, 4}) -$ Visualisation for x -$ 1 3 -$ 2 4 - diff --git a/tests/exhaustive/basic/partition_06/expected/model_4_4-solution000003.solution b/tests/exhaustive/basic/partition_06/expected/model_4_4-solution000003.solution deleted file mode 100644 index 8d196199c8..0000000000 --- a/tests/exhaustive/basic/partition_06/expected/model_4_4-solution000003.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be partition({1, 4}, {2, 3}) -$ Visualisation for x -$ 1 4 -$ 2 3 - diff --git a/tests/exhaustive/basic/partition_06/expected/model_4_4.eprime b/tests/exhaustive/basic/partition_06/expected/model_4_4.eprime deleted file mode 100644 index 6be4048cce..0000000000 --- a/tests/exhaustive/basic/partition_06/expected/model_4_4.eprime +++ /dev/null @@ -1,32 +0,0 @@ -language ESSENCE' 1.0 - -find x_PartitionOccurrence_NumParts: int(1..4) -find x_PartitionOccurrence_WhichPart: matrix indexed by [int(1..4)] of int(1..4) -find x_PartitionOccurrence_PartSizes: matrix indexed by [int(1..4)] of int(0..4) -find x_PartitionOccurrence_FirstIndex: matrix indexed by [int(1..4)] of int(1..4) -branching on - [x_PartitionOccurrence_NumParts, x_PartitionOccurrence_WhichPart, x_PartitionOccurrence_PartSizes, - x_PartitionOccurrence_FirstIndex] -such that - and([q11 <= x_PartitionOccurrence_NumParts -> - sum([toInt(x_PartitionOccurrence_WhichPart[q14] = q11) | q14 : int(1..4)]) = 2 - | q11 : int(1..4)]), - and([q1 <= x_PartitionOccurrence_NumParts -> x_PartitionOccurrence_PartSizes[q1] <= 4 | q1 : int(1..4)]), - and([q1 > x_PartitionOccurrence_NumParts -> x_PartitionOccurrence_PartSizes[q1] = 0 | q1 : int(1..4)]), - x_PartitionOccurrence_NumParts <= 4, - and([q2 <= x_PartitionOccurrence_NumParts -> or([x_PartitionOccurrence_WhichPart[q3] = q2 | q3 : int(1..4)]) - | q2 : int(3..4)]), - x_PartitionOccurrence_NumParts = max([x_PartitionOccurrence_WhichPart[q4] | q4 : int(1..4)]), - and([x_PartitionOccurrence_PartSizes[q5] = sum([toInt(x_PartitionOccurrence_WhichPart[q6] = q5) | q6 : int(1..4)]) - | q5 : int(1..4)]), - and([q7 <= x_PartitionOccurrence_NumParts -> - and([x_PartitionOccurrence_WhichPart[q8] = q7 -> x_PartitionOccurrence_FirstIndex[q7] <= q8 | q8 : int(1..4)]) - | q7 : int(1..4)]), - and([q7 <= x_PartitionOccurrence_NumParts -> - or([x_PartitionOccurrence_WhichPart[q8] = q7 /\ x_PartitionOccurrence_FirstIndex[q7] = q8 | q8 : int(1..4)]) - | q7 : int(1..4)]), - and([q7 > x_PartitionOccurrence_NumParts -> x_PartitionOccurrence_FirstIndex[q7] = 1 | q7 : int(1..4)]), - and([q9 <= x_PartitionOccurrence_NumParts /\ q10 <= x_PartitionOccurrence_NumParts -> - (q9 < q10 <-> x_PartitionOccurrence_FirstIndex[q9] < x_PartitionOccurrence_FirstIndex[q10]) - | q9 : int(1..4), q10 : int(1..4)]) - diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_1-p-solution000001.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_1-p-solution000001.solution deleted file mode 100644 index 991fac89aa..0000000000 --- a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_1-p-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {2, 4} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_1-p-solution000002.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_1-p-solution000002.solution deleted file mode 100644 index 8dddb3b359..0000000000 --- a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_1-p-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {2, 3} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_1-p-solution000003.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_1-p-solution000003.solution deleted file mode 100644 index be06a54735..0000000000 --- a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_1-p-solution000003.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 4} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_1-p-solution000004.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_1-p-solution000004.solution deleted file mode 100644 index a28b6d6203..0000000000 --- a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_1-p-solution000004.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 3} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_1-p-solution000005.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_1-p-solution000005.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_1-p-solution000005.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_1-p-solution000006.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_1-p-solution000006.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_1-p-solution000006.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_1-p.eprime-param b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_1-p.eprime-param deleted file mode 100644 index 7d6b9721c5..0000000000 --- a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_1-p.eprime-param +++ /dev/null @@ -1,5 +0,0 @@ -language ESSENCE' 1.0 - -letting n be 2 -letting a be 1 -letting b be 4 diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_1.eprime b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_1.eprime deleted file mode 100644 index 029d9f718f..0000000000 --- a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_1.eprime +++ /dev/null @@ -1,20 +0,0 @@ -language ESSENCE' 1.0 - -given n: int -given a: int -given b: int -find x_Occurrence: matrix indexed by [int(a..b)] of bool -branching on [x_Occurrence] -such that - and([and([x_Occurrence[t_ExplicitVarSizeWithDummy[q7]] - | q7 : int(1..1 + (b - a)), t_ExplicitVarSizeWithDummy[q7] != b + 1]) - -> - sum([t_ExplicitVarSizeWithDummy[q8] | q8 : int(1..1 + (b - a)), t_ExplicitVarSizeWithDummy[q8] != b + 1]) <= 6 - | t_ExplicitVarSizeWithDummy : matrix indexed by [int(1..1 + (b - a))] of int(a..b + 1), - and([t_ExplicitVarSizeWithDummy[q2] < t_ExplicitVarSizeWithDummy[q2 + 1] \/ - t_ExplicitVarSizeWithDummy[q2] = b + 1 - | q2 : int(1..1 + (b - a) - 1)]), - and([t_ExplicitVarSizeWithDummy[q3] = b + 1 -> t_ExplicitVarSizeWithDummy[q3 + 1] = b + 1 - | q3 : int(1..1 + (b - a) - 1)])]), - n <= sum([toInt(x_Occurrence[q1]) | q1 : int(a..b)]) - diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_2-p-solution000001.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_2-p-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_2-p-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_2-p-solution000002.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_2-p-solution000002.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_2-p-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_2-p-solution000003.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_2-p-solution000003.solution deleted file mode 100644 index a28b6d6203..0000000000 --- a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_2-p-solution000003.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 3} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_2-p-solution000004.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_2-p-solution000004.solution deleted file mode 100644 index be06a54735..0000000000 --- a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_2-p-solution000004.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 4} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_2-p-solution000005.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_2-p-solution000005.solution deleted file mode 100644 index 8dddb3b359..0000000000 --- a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_2-p-solution000005.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {2, 3} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_2-p-solution000006.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_2-p-solution000006.solution deleted file mode 100644 index 991fac89aa..0000000000 --- a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_2-p-solution000006.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {2, 4} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_2-p.eprime-param b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_2-p.eprime-param deleted file mode 100644 index 7d6b9721c5..0000000000 --- a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_2-p.eprime-param +++ /dev/null @@ -1,5 +0,0 @@ -language ESSENCE' 1.0 - -letting n be 2 -letting a be 1 -letting b be 4 diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_2.eprime b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_2.eprime deleted file mode 100644 index 2334196ec8..0000000000 --- a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_2.eprime +++ /dev/null @@ -1,32 +0,0 @@ -language ESSENCE' 1.0 - -given n: int -given a: int -given b: int -find x_Occurrence: matrix indexed by [int(a..b)] of bool -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..1 + (b - a))] of int(a..b + 1) -branching on [x_ExplicitVarSizeWithDummy, x_Occurrence] -such that - and([and([x_Occurrence[t_ExplicitVarSizeWithDummy[q16]] - | q16 : int(1..1 + (b - a)), t_ExplicitVarSizeWithDummy[q16] != b + 1]) - -> - sum([t_ExplicitVarSizeWithDummy[q17] | q17 : int(1..1 + (b - a)), t_ExplicitVarSizeWithDummy[q17] != b + 1]) <= - 6 | t_ExplicitVarSizeWithDummy : matrix indexed by [int(1..1 + (b - a))] of int(a..b + 1), - and([t_ExplicitVarSizeWithDummy[q11] < t_ExplicitVarSizeWithDummy[q11 + 1] \/ - t_ExplicitVarSizeWithDummy[q11] = b + 1 - | q11 : int(1..1 + (b - a) - 1)]), - and([t_ExplicitVarSizeWithDummy[q12] = b + 1 -> t_ExplicitVarSizeWithDummy[q12 + 1] = b + 1 - | q12 : int(1..1 + (b - a) - 1)])]), - n <= sum([toInt(x_Occurrence[q1]) | q1 : int(a..b)]), - and([x_ExplicitVarSizeWithDummy[q2] < x_ExplicitVarSizeWithDummy[q2 + 1] \/ x_ExplicitVarSizeWithDummy[q2] = b + 1 - | q2 : int(1..1 + (b - a) - 1)]), - and([x_ExplicitVarSizeWithDummy[q3] = b + 1 -> x_ExplicitVarSizeWithDummy[q3 + 1] = b + 1 - | q3 : int(1..1 + (b - a) - 1)]), - n <= sum([toInt(x_ExplicitVarSizeWithDummy[q4] != b + 1) | q4 : int(1..1 + (b - a))]), - and([x_ExplicitVarSizeWithDummy[q7] != b + 1 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q7]] - | q7 : int(1..1 + (b - a))]), - and([x_Occurrence[q8] -> - or([x_ExplicitVarSizeWithDummy[q10] != b + 1 /\ x_ExplicitVarSizeWithDummy[q10] = q8 - | q10 : int(1..1 + (b - a))]) - | q8 : int(a..b)]) - diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_3-p-solution000001.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_3-p-solution000001.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_3-p-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_3-p-solution000002.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_3-p-solution000002.solution deleted file mode 100644 index a28b6d6203..0000000000 --- a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_3-p-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 3} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_3-p-solution000003.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_3-p-solution000003.solution deleted file mode 100644 index be06a54735..0000000000 --- a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_3-p-solution000003.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 4} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_3-p-solution000004.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_3-p-solution000004.solution deleted file mode 100644 index 8dddb3b359..0000000000 --- a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_3-p-solution000004.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {2, 3} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_3-p-solution000005.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_3-p-solution000005.solution deleted file mode 100644 index 991fac89aa..0000000000 --- a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_3-p-solution000005.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {2, 4} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_3-p-solution000006.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_3-p-solution000006.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_3-p-solution000006.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_3-p.eprime-param b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_3-p.eprime-param deleted file mode 100644 index 7d6b9721c5..0000000000 --- a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_3-p.eprime-param +++ /dev/null @@ -1,5 +0,0 @@ -language ESSENCE' 1.0 - -letting n be 2 -letting a be 1 -letting b be 4 diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_3.eprime b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_3.eprime deleted file mode 100644 index d44b8ab518..0000000000 --- a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_3.eprime +++ /dev/null @@ -1,34 +0,0 @@ -language ESSENCE' 1.0 - -given n: int -given a: int -given b: int -find x_Occurrence: matrix indexed by [int(a..b)] of bool -find x_ExplicitVarSizeWithMarker_Marker: int(0..1 + (b - a)) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..1 + (b - a))] of int(a..b) -branching on [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_Occurrence] -such that - and([and([x_Occurrence[t_ExplicitVarSizeWithDummy[q15]] - | q15 : int(1..1 + (b - a)), t_ExplicitVarSizeWithDummy[q15] != b + 1]) - -> - sum([t_ExplicitVarSizeWithDummy[q16] | q16 : int(1..1 + (b - a)), t_ExplicitVarSizeWithDummy[q16] != b + 1]) <= - 6 | t_ExplicitVarSizeWithDummy : matrix indexed by [int(1..1 + (b - a))] of int(a..b + 1), - and([t_ExplicitVarSizeWithDummy[q10] < t_ExplicitVarSizeWithDummy[q10 + 1] \/ - t_ExplicitVarSizeWithDummy[q10] = b + 1 - | q10 : int(1..1 + (b - a) - 1)]), - and([t_ExplicitVarSizeWithDummy[q11] = b + 1 -> t_ExplicitVarSizeWithDummy[q11 + 1] = b + 1 - | q11 : int(1..1 + (b - a) - 1)])]), - n <= sum([toInt(x_Occurrence[q1]) | q1 : int(a..b)]), - and([q2 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q2] < x_ExplicitVarSizeWithMarker_Values[q2 + 1] - | q2 : int(1..1 + (b - a) - 1)]), - and([q3 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q3] = a - | q3 : int(1..1 + (b - a))]), - n <= x_ExplicitVarSizeWithMarker_Marker, - and([q6 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q6]] - | q6 : int(1..1 + (b - a))]), - and([x_Occurrence[q7] -> - or([q9 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q9] = q7 - | q9 : int(1..1 + (b - a))]) - | q7 : int(a..b)]) - diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_4-p-solution000001.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_4-p-solution000001.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_4-p-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_4-p-solution000002.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_4-p-solution000002.solution deleted file mode 100644 index a28b6d6203..0000000000 --- a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_4-p-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 3} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_4-p-solution000003.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_4-p-solution000003.solution deleted file mode 100644 index be06a54735..0000000000 --- a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_4-p-solution000003.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 4} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_4-p-solution000004.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_4-p-solution000004.solution deleted file mode 100644 index 8dddb3b359..0000000000 --- a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_4-p-solution000004.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {2, 3} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_4-p-solution000005.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_4-p-solution000005.solution deleted file mode 100644 index 991fac89aa..0000000000 --- a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_4-p-solution000005.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {2, 4} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_4-p-solution000006.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_4-p-solution000006.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_4-p-solution000006.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_4-p.eprime-param b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_4-p.eprime-param deleted file mode 100644 index 7d6b9721c5..0000000000 --- a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_4-p.eprime-param +++ /dev/null @@ -1,5 +0,0 @@ -language ESSENCE' 1.0 - -letting n be 2 -letting a be 1 -letting b be 4 diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_4.eprime b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_4.eprime deleted file mode 100644 index c5a3851fe1..0000000000 --- a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_4.eprime +++ /dev/null @@ -1,36 +0,0 @@ -language ESSENCE' 1.0 - -given n: int -given a: int -given b: int -find x_Occurrence: matrix indexed by [int(a..b)] of bool -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..1 + (b - a))] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..1 + (b - a))] of int(a..b) -branching on [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_Occurrence] -such that - and([and([x_Occurrence[t_ExplicitVarSizeWithDummy[q17]] - | q17 : int(1..1 + (b - a)), t_ExplicitVarSizeWithDummy[q17] != b + 1]) - -> - sum([t_ExplicitVarSizeWithDummy[q18] | q18 : int(1..1 + (b - a)), t_ExplicitVarSizeWithDummy[q18] != b + 1]) <= - 6 | t_ExplicitVarSizeWithDummy : matrix indexed by [int(1..1 + (b - a))] of int(a..b + 1), - and([t_ExplicitVarSizeWithDummy[q12] < t_ExplicitVarSizeWithDummy[q12 + 1] \/ - t_ExplicitVarSizeWithDummy[q12] = b + 1 - | q12 : int(1..1 + (b - a) - 1)]), - and([t_ExplicitVarSizeWithDummy[q13] = b + 1 -> t_ExplicitVarSizeWithDummy[q13 + 1] = b + 1 - | q13 : int(1..1 + (b - a) - 1)])]), - n <= sum([toInt(x_Occurrence[q1]) | q1 : int(a..b)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q2] < x_ExplicitVarSizeWithFlags_Values[q2 + 1] - | q2 : int(1..1 + (b - a) - 1)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3] = false -> x_ExplicitVarSizeWithFlags_Values[q3] = a - | q3 : int(1..1 + (b - a))]), - and([x_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q4] - | q4 : int(1..1 + (b - a) - 1)]), - n <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q5]) | q5 : int(1..1 + (b - a))]), - and([x_ExplicitVarSizeWithFlags_Flags[q8] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q8]] - | q8 : int(1..1 + (b - a))]), - and([x_Occurrence[q9] -> - or([x_ExplicitVarSizeWithFlags_Flags[q11] /\ x_ExplicitVarSizeWithFlags_Values[q11] = q9 - | q11 : int(1..1 + (b - a))]) - | q9 : int(a..b)]) - diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_1-p-solution000001.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_1-p-solution000001.solution deleted file mode 100644 index 991fac89aa..0000000000 --- a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_1-p-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {2, 4} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_1-p-solution000002.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_1-p-solution000002.solution deleted file mode 100644 index 8dddb3b359..0000000000 --- a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_1-p-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {2, 3} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_1-p-solution000003.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_1-p-solution000003.solution deleted file mode 100644 index be06a54735..0000000000 --- a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_1-p-solution000003.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 4} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_1-p-solution000004.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_1-p-solution000004.solution deleted file mode 100644 index a28b6d6203..0000000000 --- a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_1-p-solution000004.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 3} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_1-p-solution000005.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_1-p-solution000005.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_1-p-solution000005.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_1-p-solution000006.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_1-p-solution000006.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_1-p-solution000006.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_1-p.eprime-param b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_1-p.eprime-param deleted file mode 100644 index 7d6b9721c5..0000000000 --- a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_1-p.eprime-param +++ /dev/null @@ -1,5 +0,0 @@ -language ESSENCE' 1.0 - -letting n be 2 -letting a be 1 -letting b be 4 diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_1.eprime b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_1.eprime deleted file mode 100644 index 6a88075ca6..0000000000 --- a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_1.eprime +++ /dev/null @@ -1,33 +0,0 @@ -language ESSENCE' 1.0 - -given n: int -given a: int -given b: int -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..1 + (b - a))] of int(a..b + 1) -find x_Occurrence: matrix indexed by [int(a..b)] of bool -branching on [x_Occurrence, x_ExplicitVarSizeWithDummy] -such that - and([and([or([x_ExplicitVarSizeWithDummy[q18] != b + 1 /\ - x_ExplicitVarSizeWithDummy[q18] = t_ExplicitVarSizeWithDummy[q16] - | q18 : int(1..1 + (b - a))]) - | q16 : int(1..1 + (b - a)), t_ExplicitVarSizeWithDummy[q16] != b + 1]) - -> - sum([t_ExplicitVarSizeWithDummy[q19] | q19 : int(1..1 + (b - a)), t_ExplicitVarSizeWithDummy[q19] != b + 1]) <= - 6 | t_ExplicitVarSizeWithDummy : matrix indexed by [int(1..1 + (b - a))] of int(a..b + 1), - and([t_ExplicitVarSizeWithDummy[q11] < t_ExplicitVarSizeWithDummy[q11 + 1] \/ - t_ExplicitVarSizeWithDummy[q11] = b + 1 - | q11 : int(1..1 + (b - a) - 1)]), - and([t_ExplicitVarSizeWithDummy[q12] = b + 1 -> t_ExplicitVarSizeWithDummy[q12 + 1] = b + 1 - | q12 : int(1..1 + (b - a) - 1)])]), - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = b + 1 - | q1 : int(1..1 + (b - a) - 1)]), - and([x_ExplicitVarSizeWithDummy[q2] = b + 1 -> x_ExplicitVarSizeWithDummy[q2 + 1] = b + 1 - | q2 : int(1..1 + (b - a) - 1)]), - n <= sum([toInt(x_ExplicitVarSizeWithDummy[q3] != b + 1) | q3 : int(1..1 + (b - a))]), - n <= sum([toInt(x_Occurrence[q5]) | q5 : int(a..b)]), - and([x_Occurrence[q6] -> - or([x_ExplicitVarSizeWithDummy[q8] != b + 1 /\ x_ExplicitVarSizeWithDummy[q8] = q6 | q8 : int(1..1 + (b - a))]) - | q6 : int(a..b)]), - and([x_ExplicitVarSizeWithDummy[q10] != b + 1 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q10]] - | q10 : int(1..1 + (b - a))]) - diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_2-p-solution000001.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_2-p-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_2-p-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_2-p-solution000002.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_2-p-solution000002.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_2-p-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_2-p-solution000003.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_2-p-solution000003.solution deleted file mode 100644 index a28b6d6203..0000000000 --- a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_2-p-solution000003.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 3} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_2-p-solution000004.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_2-p-solution000004.solution deleted file mode 100644 index be06a54735..0000000000 --- a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_2-p-solution000004.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 4} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_2-p-solution000005.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_2-p-solution000005.solution deleted file mode 100644 index 8dddb3b359..0000000000 --- a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_2-p-solution000005.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {2, 3} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_2-p-solution000006.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_2-p-solution000006.solution deleted file mode 100644 index 991fac89aa..0000000000 --- a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_2-p-solution000006.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {2, 4} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_2-p.eprime-param b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_2-p.eprime-param deleted file mode 100644 index 7d6b9721c5..0000000000 --- a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_2-p.eprime-param +++ /dev/null @@ -1,5 +0,0 @@ -language ESSENCE' 1.0 - -letting n be 2 -letting a be 1 -letting b be 4 diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_2.eprime b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_2.eprime deleted file mode 100644 index f4dd241cca..0000000000 --- a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_2.eprime +++ /dev/null @@ -1,26 +0,0 @@ -language ESSENCE' 1.0 - -given n: int -given a: int -given b: int -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..1 + (b - a))] of int(a..b + 1) -branching on [x_ExplicitVarSizeWithDummy] -such that - and([and([or([x_ExplicitVarSizeWithDummy[q12] != b + 1 /\ - x_ExplicitVarSizeWithDummy[q12] = t_ExplicitVarSizeWithDummy[q10] - | q12 : int(1..1 + (b - a))]) - | q10 : int(1..1 + (b - a)), t_ExplicitVarSizeWithDummy[q10] != b + 1]) - -> - sum([t_ExplicitVarSizeWithDummy[q13] | q13 : int(1..1 + (b - a)), t_ExplicitVarSizeWithDummy[q13] != b + 1]) <= - 6 | t_ExplicitVarSizeWithDummy : matrix indexed by [int(1..1 + (b - a))] of int(a..b + 1), - and([t_ExplicitVarSizeWithDummy[q5] < t_ExplicitVarSizeWithDummy[q5 + 1] \/ - t_ExplicitVarSizeWithDummy[q5] = b + 1 - | q5 : int(1..1 + (b - a) - 1)]), - and([t_ExplicitVarSizeWithDummy[q6] = b + 1 -> t_ExplicitVarSizeWithDummy[q6 + 1] = b + 1 - | q6 : int(1..1 + (b - a) - 1)])]), - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = b + 1 - | q1 : int(1..1 + (b - a) - 1)]), - and([x_ExplicitVarSizeWithDummy[q2] = b + 1 -> x_ExplicitVarSizeWithDummy[q2 + 1] = b + 1 - | q2 : int(1..1 + (b - a) - 1)]), - n <= sum([toInt(x_ExplicitVarSizeWithDummy[q3] != b + 1) | q3 : int(1..1 + (b - a))]) - diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_3-p-solution000001.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_3-p-solution000001.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_3-p-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_3-p-solution000002.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_3-p-solution000002.solution deleted file mode 100644 index a28b6d6203..0000000000 --- a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_3-p-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 3} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_3-p-solution000003.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_3-p-solution000003.solution deleted file mode 100644 index be06a54735..0000000000 --- a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_3-p-solution000003.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 4} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_3-p-solution000004.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_3-p-solution000004.solution deleted file mode 100644 index 8dddb3b359..0000000000 --- a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_3-p-solution000004.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {2, 3} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_3-p-solution000005.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_3-p-solution000005.solution deleted file mode 100644 index 991fac89aa..0000000000 --- a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_3-p-solution000005.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {2, 4} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_3-p-solution000006.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_3-p-solution000006.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_3-p-solution000006.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_3-p.eprime-param b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_3-p.eprime-param deleted file mode 100644 index 7d6b9721c5..0000000000 --- a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_3-p.eprime-param +++ /dev/null @@ -1,5 +0,0 @@ -language ESSENCE' 1.0 - -letting n be 2 -letting a be 1 -letting b be 4 diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_3.eprime b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_3.eprime deleted file mode 100644 index 92c80b9133..0000000000 --- a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_3.eprime +++ /dev/null @@ -1,44 +0,0 @@ -language ESSENCE' 1.0 - -given n: int -given a: int -given b: int -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..1 + (b - a))] of int(a..b + 1) -find x_ExplicitVarSizeWithMarker_Marker: int(0..1 + (b - a)) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..1 + (b - a))] of int(a..b) -branching on [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy] -such that - and([and([or([x_ExplicitVarSizeWithDummy[q23] != b + 1 /\ - x_ExplicitVarSizeWithDummy[q23] = t_ExplicitVarSizeWithDummy[q21] - | q23 : int(1..1 + (b - a))]) - | q21 : int(1..1 + (b - a)), t_ExplicitVarSizeWithDummy[q21] != b + 1]) - -> - sum([t_ExplicitVarSizeWithDummy[q24] | q24 : int(1..1 + (b - a)), t_ExplicitVarSizeWithDummy[q24] != b + 1]) <= - 6 | t_ExplicitVarSizeWithDummy : matrix indexed by [int(1..1 + (b - a))] of int(a..b + 1), - and([t_ExplicitVarSizeWithDummy[q16] < t_ExplicitVarSizeWithDummy[q16 + 1] \/ - t_ExplicitVarSizeWithDummy[q16] = b + 1 - | q16 : int(1..1 + (b - a) - 1)]), - and([t_ExplicitVarSizeWithDummy[q17] = b + 1 -> t_ExplicitVarSizeWithDummy[q17 + 1] = b + 1 - | q17 : int(1..1 + (b - a) - 1)])]), - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = b + 1 - | q1 : int(1..1 + (b - a) - 1)]), - and([x_ExplicitVarSizeWithDummy[q2] = b + 1 -> x_ExplicitVarSizeWithDummy[q2 + 1] = b + 1 - | q2 : int(1..1 + (b - a) - 1)]), - n <= sum([toInt(x_ExplicitVarSizeWithDummy[q3] != b + 1) | q3 : int(1..1 + (b - a))]), - and([q5 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q5] < x_ExplicitVarSizeWithMarker_Values[q5 + 1] - | q5 : int(1..1 + (b - a) - 1)]), - and([q6 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q6] = a - | q6 : int(1..1 + (b - a))]), - n <= x_ExplicitVarSizeWithMarker_Marker, - and([q9 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q11] != b + 1 /\ - x_ExplicitVarSizeWithDummy[q11] = x_ExplicitVarSizeWithMarker_Values[q9] - | q11 : int(1..1 + (b - a))]) - | q9 : int(1..1 + (b - a))]), - and([x_ExplicitVarSizeWithDummy[q13] != b + 1 -> - or([q15 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q15] = x_ExplicitVarSizeWithDummy[q13] - | q15 : int(1..1 + (b - a))]) - | q13 : int(1..1 + (b - a))]) - diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_4-p-solution000001.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_4-p-solution000001.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_4-p-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_4-p-solution000002.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_4-p-solution000002.solution deleted file mode 100644 index a28b6d6203..0000000000 --- a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_4-p-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 3} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_4-p-solution000003.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_4-p-solution000003.solution deleted file mode 100644 index be06a54735..0000000000 --- a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_4-p-solution000003.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 4} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_4-p-solution000004.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_4-p-solution000004.solution deleted file mode 100644 index 8dddb3b359..0000000000 --- a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_4-p-solution000004.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {2, 3} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_4-p-solution000005.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_4-p-solution000005.solution deleted file mode 100644 index 991fac89aa..0000000000 --- a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_4-p-solution000005.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {2, 4} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_4-p-solution000006.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_4-p-solution000006.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_4-p-solution000006.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_4-p.eprime-param b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_4-p.eprime-param deleted file mode 100644 index 7d6b9721c5..0000000000 --- a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_4-p.eprime-param +++ /dev/null @@ -1,5 +0,0 @@ -language ESSENCE' 1.0 - -letting n be 2 -letting a be 1 -letting b be 4 diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_4.eprime b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_4.eprime deleted file mode 100644 index 4b598c63b3..0000000000 --- a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_4.eprime +++ /dev/null @@ -1,46 +0,0 @@ -language ESSENCE' 1.0 - -given n: int -given a: int -given b: int -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..1 + (b - a))] of int(a..b + 1) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..1 + (b - a))] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..1 + (b - a))] of int(a..b) -branching on [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy] -such that - and([and([or([x_ExplicitVarSizeWithDummy[q25] != b + 1 /\ - x_ExplicitVarSizeWithDummy[q25] = t_ExplicitVarSizeWithDummy[q23] - | q25 : int(1..1 + (b - a))]) - | q23 : int(1..1 + (b - a)), t_ExplicitVarSizeWithDummy[q23] != b + 1]) - -> - sum([t_ExplicitVarSizeWithDummy[q26] | q26 : int(1..1 + (b - a)), t_ExplicitVarSizeWithDummy[q26] != b + 1]) <= - 6 | t_ExplicitVarSizeWithDummy : matrix indexed by [int(1..1 + (b - a))] of int(a..b + 1), - and([t_ExplicitVarSizeWithDummy[q18] < t_ExplicitVarSizeWithDummy[q18 + 1] \/ - t_ExplicitVarSizeWithDummy[q18] = b + 1 - | q18 : int(1..1 + (b - a) - 1)]), - and([t_ExplicitVarSizeWithDummy[q19] = b + 1 -> t_ExplicitVarSizeWithDummy[q19 + 1] = b + 1 - | q19 : int(1..1 + (b - a) - 1)])]), - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = b + 1 - | q1 : int(1..1 + (b - a) - 1)]), - and([x_ExplicitVarSizeWithDummy[q2] = b + 1 -> x_ExplicitVarSizeWithDummy[q2 + 1] = b + 1 - | q2 : int(1..1 + (b - a) - 1)]), - n <= sum([toInt(x_ExplicitVarSizeWithDummy[q3] != b + 1) | q3 : int(1..1 + (b - a))]), - and([x_ExplicitVarSizeWithFlags_Flags[q5 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q5] < x_ExplicitVarSizeWithFlags_Values[q5 + 1] - | q5 : int(1..1 + (b - a) - 1)]), - and([x_ExplicitVarSizeWithFlags_Flags[q6] = false -> x_ExplicitVarSizeWithFlags_Values[q6] = a - | q6 : int(1..1 + (b - a))]), - and([x_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q7] - | q7 : int(1..1 + (b - a) - 1)]), - n <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q8]) | q8 : int(1..1 + (b - a))]), - and([x_ExplicitVarSizeWithFlags_Flags[q11] -> - or([x_ExplicitVarSizeWithDummy[q13] != b + 1 /\ - x_ExplicitVarSizeWithDummy[q13] = x_ExplicitVarSizeWithFlags_Values[q11] - | q13 : int(1..1 + (b - a))]) - | q11 : int(1..1 + (b - a))]), - and([x_ExplicitVarSizeWithDummy[q15] != b + 1 -> - or([x_ExplicitVarSizeWithFlags_Flags[q17] /\ - x_ExplicitVarSizeWithFlags_Values[q17] = x_ExplicitVarSizeWithDummy[q15] - | q17 : int(1..1 + (b - a))]) - | q15 : int(1..1 + (b - a))]) - diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_1-p-solution000001.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_1-p-solution000001.solution deleted file mode 100644 index 991fac89aa..0000000000 --- a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_1-p-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {2, 4} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_1-p-solution000002.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_1-p-solution000002.solution deleted file mode 100644 index 8dddb3b359..0000000000 --- a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_1-p-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {2, 3} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_1-p-solution000003.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_1-p-solution000003.solution deleted file mode 100644 index be06a54735..0000000000 --- a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_1-p-solution000003.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 4} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_1-p-solution000004.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_1-p-solution000004.solution deleted file mode 100644 index a28b6d6203..0000000000 --- a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_1-p-solution000004.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 3} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_1-p-solution000005.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_1-p-solution000005.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_1-p-solution000005.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_1-p-solution000006.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_1-p-solution000006.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_1-p-solution000006.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_1-p.eprime-param b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_1-p.eprime-param deleted file mode 100644 index 7d6b9721c5..0000000000 --- a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_1-p.eprime-param +++ /dev/null @@ -1,5 +0,0 @@ -language ESSENCE' 1.0 - -letting n be 2 -letting a be 1 -letting b be 4 diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_1.eprime b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_1.eprime deleted file mode 100644 index 00361f80a7..0000000000 --- a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_1.eprime +++ /dev/null @@ -1,36 +0,0 @@ -language ESSENCE' 1.0 - -given n: int -given a: int -given b: int -find x_ExplicitVarSizeWithMarker_Marker: int(0..1 + (b - a)) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..1 + (b - a))] of int(a..b) -find x_Occurrence: matrix indexed by [int(a..b)] of bool -branching on [x_Occurrence, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] -such that - and([and([or([q17 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q17] = t_ExplicitVarSizeWithDummy[q15] - | q17 : int(1..1 + (b - a))]) - | q15 : int(1..1 + (b - a)), t_ExplicitVarSizeWithDummy[q15] != b + 1]) - -> - sum([t_ExplicitVarSizeWithDummy[q18] | q18 : int(1..1 + (b - a)), t_ExplicitVarSizeWithDummy[q18] != b + 1]) <= - 6 | t_ExplicitVarSizeWithDummy : matrix indexed by [int(1..1 + (b - a))] of int(a..b + 1), - and([t_ExplicitVarSizeWithDummy[q10] < t_ExplicitVarSizeWithDummy[q10 + 1] \/ - t_ExplicitVarSizeWithDummy[q10] = b + 1 - | q10 : int(1..1 + (b - a) - 1)]), - and([t_ExplicitVarSizeWithDummy[q11] = b + 1 -> t_ExplicitVarSizeWithDummy[q11 + 1] = b + 1 - | q11 : int(1..1 + (b - a) - 1)])]), - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..1 + (b - a) - 1)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = a - | q2 : int(1..1 + (b - a))]), - n <= x_ExplicitVarSizeWithMarker_Marker, - n <= sum([toInt(x_Occurrence[q4]) | q4 : int(a..b)]), - and([x_Occurrence[q5] -> - or([q7 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q7] = q5 - | q7 : int(1..1 + (b - a))]) - | q5 : int(a..b)]), - and([q9 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q9]] - | q9 : int(1..1 + (b - a))]) - diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_2-p-solution000001.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_2-p-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_2-p-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_2-p-solution000002.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_2-p-solution000002.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_2-p-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_2-p-solution000003.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_2-p-solution000003.solution deleted file mode 100644 index a28b6d6203..0000000000 --- a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_2-p-solution000003.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 3} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_2-p-solution000004.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_2-p-solution000004.solution deleted file mode 100644 index be06a54735..0000000000 --- a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_2-p-solution000004.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 4} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_2-p-solution000005.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_2-p-solution000005.solution deleted file mode 100644 index 8dddb3b359..0000000000 --- a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_2-p-solution000005.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {2, 3} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_2-p-solution000006.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_2-p-solution000006.solution deleted file mode 100644 index 991fac89aa..0000000000 --- a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_2-p-solution000006.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {2, 4} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_2-p.eprime-param b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_2-p.eprime-param deleted file mode 100644 index 7d6b9721c5..0000000000 --- a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_2-p.eprime-param +++ /dev/null @@ -1,5 +0,0 @@ -language ESSENCE' 1.0 - -letting n be 2 -letting a be 1 -letting b be 4 diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_2.eprime b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_2.eprime deleted file mode 100644 index f071e0ff08..0000000000 --- a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_2.eprime +++ /dev/null @@ -1,44 +0,0 @@ -language ESSENCE' 1.0 - -given n: int -given a: int -given b: int -find x_ExplicitVarSizeWithMarker_Marker: int(0..1 + (b - a)) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..1 + (b - a))] of int(a..b) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..1 + (b - a))] of int(a..b + 1) -branching on [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] -such that - and([and([or([q23 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q23] = t_ExplicitVarSizeWithDummy[q21] - | q23 : int(1..1 + (b - a))]) - | q21 : int(1..1 + (b - a)), t_ExplicitVarSizeWithDummy[q21] != b + 1]) - -> - sum([t_ExplicitVarSizeWithDummy[q24] | q24 : int(1..1 + (b - a)), t_ExplicitVarSizeWithDummy[q24] != b + 1]) <= - 6 | t_ExplicitVarSizeWithDummy : matrix indexed by [int(1..1 + (b - a))] of int(a..b + 1), - and([t_ExplicitVarSizeWithDummy[q16] < t_ExplicitVarSizeWithDummy[q16 + 1] \/ - t_ExplicitVarSizeWithDummy[q16] = b + 1 - | q16 : int(1..1 + (b - a) - 1)]), - and([t_ExplicitVarSizeWithDummy[q17] = b + 1 -> t_ExplicitVarSizeWithDummy[q17 + 1] = b + 1 - | q17 : int(1..1 + (b - a) - 1)])]), - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..1 + (b - a) - 1)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = a - | q2 : int(1..1 + (b - a))]), - n <= x_ExplicitVarSizeWithMarker_Marker, - and([x_ExplicitVarSizeWithDummy[q4] < x_ExplicitVarSizeWithDummy[q4 + 1] \/ x_ExplicitVarSizeWithDummy[q4] = b + 1 - | q4 : int(1..1 + (b - a) - 1)]), - and([x_ExplicitVarSizeWithDummy[q5] = b + 1 -> x_ExplicitVarSizeWithDummy[q5 + 1] = b + 1 - | q5 : int(1..1 + (b - a) - 1)]), - n <= sum([toInt(x_ExplicitVarSizeWithDummy[q6] != b + 1) | q6 : int(1..1 + (b - a))]), - and([x_ExplicitVarSizeWithDummy[q9] != b + 1 -> - or([q11 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q11] = x_ExplicitVarSizeWithDummy[q9] - | q11 : int(1..1 + (b - a))]) - | q9 : int(1..1 + (b - a))]), - and([q13 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q15] != b + 1 /\ - x_ExplicitVarSizeWithDummy[q15] = x_ExplicitVarSizeWithMarker_Values[q13] - | q15 : int(1..1 + (b - a))]) - | q13 : int(1..1 + (b - a))]) - diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_3-p-solution000001.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_3-p-solution000001.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_3-p-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_3-p-solution000002.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_3-p-solution000002.solution deleted file mode 100644 index a28b6d6203..0000000000 --- a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_3-p-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 3} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_3-p-solution000003.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_3-p-solution000003.solution deleted file mode 100644 index be06a54735..0000000000 --- a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_3-p-solution000003.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 4} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_3-p-solution000004.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_3-p-solution000004.solution deleted file mode 100644 index 8dddb3b359..0000000000 --- a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_3-p-solution000004.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {2, 3} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_3-p-solution000005.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_3-p-solution000005.solution deleted file mode 100644 index 991fac89aa..0000000000 --- a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_3-p-solution000005.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {2, 4} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_3-p-solution000006.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_3-p-solution000006.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_3-p-solution000006.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_3-p.eprime-param b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_3-p.eprime-param deleted file mode 100644 index 7d6b9721c5..0000000000 --- a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_3-p.eprime-param +++ /dev/null @@ -1,5 +0,0 @@ -language ESSENCE' 1.0 - -letting n be 2 -letting a be 1 -letting b be 4 diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_3.eprime b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_3.eprime deleted file mode 100644 index 8fa49fbf6d..0000000000 --- a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_3.eprime +++ /dev/null @@ -1,28 +0,0 @@ -language ESSENCE' 1.0 - -given n: int -given a: int -given b: int -find x_ExplicitVarSizeWithMarker_Marker: int(0..1 + (b - a)) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..1 + (b - a))] of int(a..b) -branching on [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] -such that - and([and([or([q11 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q11] = t_ExplicitVarSizeWithDummy[q9] - | q11 : int(1..1 + (b - a))]) - | q9 : int(1..1 + (b - a)), t_ExplicitVarSizeWithDummy[q9] != b + 1]) - -> - sum([t_ExplicitVarSizeWithDummy[q12] | q12 : int(1..1 + (b - a)), t_ExplicitVarSizeWithDummy[q12] != b + 1]) <= - 6 | t_ExplicitVarSizeWithDummy : matrix indexed by [int(1..1 + (b - a))] of int(a..b + 1), - and([t_ExplicitVarSizeWithDummy[q4] < t_ExplicitVarSizeWithDummy[q4 + 1] \/ - t_ExplicitVarSizeWithDummy[q4] = b + 1 - | q4 : int(1..1 + (b - a) - 1)]), - and([t_ExplicitVarSizeWithDummy[q5] = b + 1 -> t_ExplicitVarSizeWithDummy[q5 + 1] = b + 1 - | q5 : int(1..1 + (b - a) - 1)])]), - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..1 + (b - a) - 1)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = a - | q2 : int(1..1 + (b - a))]), - n <= x_ExplicitVarSizeWithMarker_Marker - diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_4-p-solution000001.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_4-p-solution000001.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_4-p-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_4-p-solution000002.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_4-p-solution000002.solution deleted file mode 100644 index a28b6d6203..0000000000 --- a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_4-p-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 3} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_4-p-solution000003.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_4-p-solution000003.solution deleted file mode 100644 index be06a54735..0000000000 --- a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_4-p-solution000003.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 4} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_4-p-solution000004.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_4-p-solution000004.solution deleted file mode 100644 index 8dddb3b359..0000000000 --- a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_4-p-solution000004.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {2, 3} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_4-p-solution000005.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_4-p-solution000005.solution deleted file mode 100644 index 991fac89aa..0000000000 --- a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_4-p-solution000005.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {2, 4} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_4-p-solution000006.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_4-p-solution000006.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_4-p-solution000006.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_4-p.eprime-param b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_4-p.eprime-param deleted file mode 100644 index 7d6b9721c5..0000000000 --- a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_4-p.eprime-param +++ /dev/null @@ -1,5 +0,0 @@ -language ESSENCE' 1.0 - -letting n be 2 -letting a be 1 -letting b be 4 diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_4.eprime b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_4.eprime deleted file mode 100644 index bacc7d46b3..0000000000 --- a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_4.eprime +++ /dev/null @@ -1,50 +0,0 @@ -language ESSENCE' 1.0 - -given n: int -given a: int -given b: int -find x_ExplicitVarSizeWithMarker_Marker: int(0..1 + (b - a)) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..1 + (b - a))] of int(a..b) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..1 + (b - a))] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..1 + (b - a))] of int(a..b) -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithMarker_Marker, - x_ExplicitVarSizeWithMarker_Values] -such that - and([and([or([q24 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q24] = t_ExplicitVarSizeWithDummy[q22] - | q24 : int(1..1 + (b - a))]) - | q22 : int(1..1 + (b - a)), t_ExplicitVarSizeWithDummy[q22] != b + 1]) - -> - sum([t_ExplicitVarSizeWithDummy[q25] | q25 : int(1..1 + (b - a)), t_ExplicitVarSizeWithDummy[q25] != b + 1]) <= - 6 | t_ExplicitVarSizeWithDummy : matrix indexed by [int(1..1 + (b - a))] of int(a..b + 1), - and([t_ExplicitVarSizeWithDummy[q17] < t_ExplicitVarSizeWithDummy[q17 + 1] \/ - t_ExplicitVarSizeWithDummy[q17] = b + 1 - | q17 : int(1..1 + (b - a) - 1)]), - and([t_ExplicitVarSizeWithDummy[q18] = b + 1 -> t_ExplicitVarSizeWithDummy[q18 + 1] = b + 1 - | q18 : int(1..1 + (b - a) - 1)])]), - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..1 + (b - a) - 1)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = a - | q2 : int(1..1 + (b - a))]), - n <= x_ExplicitVarSizeWithMarker_Marker, - and([x_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q4] < x_ExplicitVarSizeWithFlags_Values[q4 + 1] - | q4 : int(1..1 + (b - a) - 1)]), - and([x_ExplicitVarSizeWithFlags_Flags[q5] = false -> x_ExplicitVarSizeWithFlags_Values[q5] = a - | q5 : int(1..1 + (b - a))]), - and([x_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q6] - | q6 : int(1..1 + (b - a) - 1)]), - n <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q7]) | q7 : int(1..1 + (b - a))]), - and([x_ExplicitVarSizeWithFlags_Flags[q10] -> - or([q12 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q12] = x_ExplicitVarSizeWithFlags_Values[q10] - | q12 : int(1..1 + (b - a))]) - | q10 : int(1..1 + (b - a))]), - and([q14 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q16] /\ - x_ExplicitVarSizeWithFlags_Values[q16] = x_ExplicitVarSizeWithMarker_Values[q14] - | q16 : int(1..1 + (b - a))]) - | q14 : int(1..1 + (b - a))]) - diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_1-p-solution000001.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_1-p-solution000001.solution deleted file mode 100644 index 991fac89aa..0000000000 --- a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_1-p-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {2, 4} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_1-p-solution000002.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_1-p-solution000002.solution deleted file mode 100644 index 8dddb3b359..0000000000 --- a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_1-p-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {2, 3} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_1-p-solution000003.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_1-p-solution000003.solution deleted file mode 100644 index be06a54735..0000000000 --- a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_1-p-solution000003.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 4} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_1-p-solution000004.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_1-p-solution000004.solution deleted file mode 100644 index a28b6d6203..0000000000 --- a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_1-p-solution000004.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 3} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_1-p-solution000005.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_1-p-solution000005.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_1-p-solution000005.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_1-p-solution000006.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_1-p-solution000006.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_1-p-solution000006.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_1-p.eprime-param b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_1-p.eprime-param deleted file mode 100644 index 7d6b9721c5..0000000000 --- a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_1-p.eprime-param +++ /dev/null @@ -1,5 +0,0 @@ -language ESSENCE' 1.0 - -letting n be 2 -letting a be 1 -letting b be 4 diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_1.eprime b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_1.eprime deleted file mode 100644 index 5b6f7598a4..0000000000 --- a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_1.eprime +++ /dev/null @@ -1,38 +0,0 @@ -language ESSENCE' 1.0 - -given n: int -given a: int -given b: int -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..1 + (b - a))] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..1 + (b - a))] of int(a..b) -find x_Occurrence: matrix indexed by [int(a..b)] of bool -branching on [x_Occurrence, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] -such that - and([and([or([x_ExplicitVarSizeWithFlags_Flags[q19] /\ - x_ExplicitVarSizeWithFlags_Values[q19] = t_ExplicitVarSizeWithDummy[q17] - | q19 : int(1..1 + (b - a))]) - | q17 : int(1..1 + (b - a)), t_ExplicitVarSizeWithDummy[q17] != b + 1]) - -> - sum([t_ExplicitVarSizeWithDummy[q20] | q20 : int(1..1 + (b - a)), t_ExplicitVarSizeWithDummy[q20] != b + 1]) <= - 6 | t_ExplicitVarSizeWithDummy : matrix indexed by [int(1..1 + (b - a))] of int(a..b + 1), - and([t_ExplicitVarSizeWithDummy[q12] < t_ExplicitVarSizeWithDummy[q12 + 1] \/ - t_ExplicitVarSizeWithDummy[q12] = b + 1 - | q12 : int(1..1 + (b - a) - 1)]), - and([t_ExplicitVarSizeWithDummy[q13] = b + 1 -> t_ExplicitVarSizeWithDummy[q13 + 1] = b + 1 - | q13 : int(1..1 + (b - a) - 1)])]), - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..1 + (b - a) - 1)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = a - | q2 : int(1..1 + (b - a))]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] - | q3 : int(1..1 + (b - a) - 1)]), - n <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..1 + (b - a))]), - n <= sum([toInt(x_Occurrence[q6]) | q6 : int(a..b)]), - and([x_Occurrence[q7] -> - or([x_ExplicitVarSizeWithFlags_Flags[q9] /\ x_ExplicitVarSizeWithFlags_Values[q9] = q7 - | q9 : int(1..1 + (b - a))]) - | q7 : int(a..b)]), - and([x_ExplicitVarSizeWithFlags_Flags[q11] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q11]] - | q11 : int(1..1 + (b - a))]) - diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_2-p-solution000001.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_2-p-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_2-p-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_2-p-solution000002.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_2-p-solution000002.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_2-p-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_2-p-solution000003.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_2-p-solution000003.solution deleted file mode 100644 index a28b6d6203..0000000000 --- a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_2-p-solution000003.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 3} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_2-p-solution000004.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_2-p-solution000004.solution deleted file mode 100644 index be06a54735..0000000000 --- a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_2-p-solution000004.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 4} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_2-p-solution000005.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_2-p-solution000005.solution deleted file mode 100644 index 8dddb3b359..0000000000 --- a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_2-p-solution000005.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {2, 3} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_2-p-solution000006.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_2-p-solution000006.solution deleted file mode 100644 index 991fac89aa..0000000000 --- a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_2-p-solution000006.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {2, 4} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_2-p.eprime-param b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_2-p.eprime-param deleted file mode 100644 index 7d6b9721c5..0000000000 --- a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_2-p.eprime-param +++ /dev/null @@ -1,5 +0,0 @@ -language ESSENCE' 1.0 - -letting n be 2 -letting a be 1 -letting b be 4 diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_2.eprime b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_2.eprime deleted file mode 100644 index 97885f92e5..0000000000 --- a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_2.eprime +++ /dev/null @@ -1,46 +0,0 @@ -language ESSENCE' 1.0 - -given n: int -given a: int -given b: int -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..1 + (b - a))] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..1 + (b - a))] of int(a..b) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..1 + (b - a))] of int(a..b + 1) -branching on [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] -such that - and([and([or([x_ExplicitVarSizeWithFlags_Flags[q25] /\ - x_ExplicitVarSizeWithFlags_Values[q25] = t_ExplicitVarSizeWithDummy[q23] - | q25 : int(1..1 + (b - a))]) - | q23 : int(1..1 + (b - a)), t_ExplicitVarSizeWithDummy[q23] != b + 1]) - -> - sum([t_ExplicitVarSizeWithDummy[q26] | q26 : int(1..1 + (b - a)), t_ExplicitVarSizeWithDummy[q26] != b + 1]) <= - 6 | t_ExplicitVarSizeWithDummy : matrix indexed by [int(1..1 + (b - a))] of int(a..b + 1), - and([t_ExplicitVarSizeWithDummy[q18] < t_ExplicitVarSizeWithDummy[q18 + 1] \/ - t_ExplicitVarSizeWithDummy[q18] = b + 1 - | q18 : int(1..1 + (b - a) - 1)]), - and([t_ExplicitVarSizeWithDummy[q19] = b + 1 -> t_ExplicitVarSizeWithDummy[q19 + 1] = b + 1 - | q19 : int(1..1 + (b - a) - 1)])]), - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..1 + (b - a) - 1)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = a - | q2 : int(1..1 + (b - a))]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] - | q3 : int(1..1 + (b - a) - 1)]), - n <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..1 + (b - a))]), - and([x_ExplicitVarSizeWithDummy[q6] < x_ExplicitVarSizeWithDummy[q6 + 1] \/ x_ExplicitVarSizeWithDummy[q6] = b + 1 - | q6 : int(1..1 + (b - a) - 1)]), - and([x_ExplicitVarSizeWithDummy[q7] = b + 1 -> x_ExplicitVarSizeWithDummy[q7 + 1] = b + 1 - | q7 : int(1..1 + (b - a) - 1)]), - n <= sum([toInt(x_ExplicitVarSizeWithDummy[q8] != b + 1) | q8 : int(1..1 + (b - a))]), - and([x_ExplicitVarSizeWithDummy[q11] != b + 1 -> - or([x_ExplicitVarSizeWithFlags_Flags[q13] /\ - x_ExplicitVarSizeWithFlags_Values[q13] = x_ExplicitVarSizeWithDummy[q11] - | q13 : int(1..1 + (b - a))]) - | q11 : int(1..1 + (b - a))]), - and([x_ExplicitVarSizeWithFlags_Flags[q15] -> - or([x_ExplicitVarSizeWithDummy[q17] != b + 1 /\ - x_ExplicitVarSizeWithDummy[q17] = x_ExplicitVarSizeWithFlags_Values[q15] - | q17 : int(1..1 + (b - a))]) - | q15 : int(1..1 + (b - a))]) - diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_3-p-solution000001.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_3-p-solution000001.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_3-p-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_3-p-solution000002.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_3-p-solution000002.solution deleted file mode 100644 index a28b6d6203..0000000000 --- a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_3-p-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 3} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_3-p-solution000003.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_3-p-solution000003.solution deleted file mode 100644 index be06a54735..0000000000 --- a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_3-p-solution000003.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 4} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_3-p-solution000004.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_3-p-solution000004.solution deleted file mode 100644 index 8dddb3b359..0000000000 --- a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_3-p-solution000004.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {2, 3} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_3-p-solution000005.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_3-p-solution000005.solution deleted file mode 100644 index 991fac89aa..0000000000 --- a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_3-p-solution000005.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {2, 4} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_3-p-solution000006.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_3-p-solution000006.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_3-p-solution000006.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_3-p.eprime-param b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_3-p.eprime-param deleted file mode 100644 index 7d6b9721c5..0000000000 --- a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_3-p.eprime-param +++ /dev/null @@ -1,5 +0,0 @@ -language ESSENCE' 1.0 - -letting n be 2 -letting a be 1 -letting b be 4 diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_3.eprime b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_3.eprime deleted file mode 100644 index 60687fba2b..0000000000 --- a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_3.eprime +++ /dev/null @@ -1,50 +0,0 @@ -language ESSENCE' 1.0 - -given n: int -given a: int -given b: int -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..1 + (b - a))] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..1 + (b - a))] of int(a..b) -find x_ExplicitVarSizeWithMarker_Marker: int(0..1 + (b - a)) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..1 + (b - a))] of int(a..b) -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithFlags_Flags, - x_ExplicitVarSizeWithFlags_Values] -such that - and([and([or([x_ExplicitVarSizeWithFlags_Flags[q24] /\ - x_ExplicitVarSizeWithFlags_Values[q24] = t_ExplicitVarSizeWithDummy[q22] - | q24 : int(1..1 + (b - a))]) - | q22 : int(1..1 + (b - a)), t_ExplicitVarSizeWithDummy[q22] != b + 1]) - -> - sum([t_ExplicitVarSizeWithDummy[q25] | q25 : int(1..1 + (b - a)), t_ExplicitVarSizeWithDummy[q25] != b + 1]) <= - 6 | t_ExplicitVarSizeWithDummy : matrix indexed by [int(1..1 + (b - a))] of int(a..b + 1), - and([t_ExplicitVarSizeWithDummy[q17] < t_ExplicitVarSizeWithDummy[q17 + 1] \/ - t_ExplicitVarSizeWithDummy[q17] = b + 1 - | q17 : int(1..1 + (b - a) - 1)]), - and([t_ExplicitVarSizeWithDummy[q18] = b + 1 -> t_ExplicitVarSizeWithDummy[q18 + 1] = b + 1 - | q18 : int(1..1 + (b - a) - 1)])]), - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..1 + (b - a) - 1)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = a - | q2 : int(1..1 + (b - a))]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] - | q3 : int(1..1 + (b - a) - 1)]), - n <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..1 + (b - a))]), - and([q6 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q6] < x_ExplicitVarSizeWithMarker_Values[q6 + 1] - | q6 : int(1..1 + (b - a) - 1)]), - and([q7 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q7] = a - | q7 : int(1..1 + (b - a))]), - n <= x_ExplicitVarSizeWithMarker_Marker, - and([q10 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q12] /\ - x_ExplicitVarSizeWithFlags_Values[q12] = x_ExplicitVarSizeWithMarker_Values[q10] - | q12 : int(1..1 + (b - a))]) - | q10 : int(1..1 + (b - a))]), - and([x_ExplicitVarSizeWithFlags_Flags[q14] -> - or([q16 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q16] = x_ExplicitVarSizeWithFlags_Values[q14] - | q16 : int(1..1 + (b - a))]) - | q14 : int(1..1 + (b - a))]) - diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_4-p-solution000001.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_4-p-solution000001.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_4-p-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_4-p-solution000002.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_4-p-solution000002.solution deleted file mode 100644 index a28b6d6203..0000000000 --- a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_4-p-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 3} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_4-p-solution000003.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_4-p-solution000003.solution deleted file mode 100644 index be06a54735..0000000000 --- a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_4-p-solution000003.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 4} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_4-p-solution000004.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_4-p-solution000004.solution deleted file mode 100644 index 8dddb3b359..0000000000 --- a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_4-p-solution000004.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {2, 3} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_4-p-solution000005.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_4-p-solution000005.solution deleted file mode 100644 index 991fac89aa..0000000000 --- a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_4-p-solution000005.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {2, 4} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_4-p-solution000006.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_4-p-solution000006.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_4-p-solution000006.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_4-p.eprime-param b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_4-p.eprime-param deleted file mode 100644 index 7d6b9721c5..0000000000 --- a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_4-p.eprime-param +++ /dev/null @@ -1,5 +0,0 @@ -language ESSENCE' 1.0 - -letting n be 2 -letting a be 1 -letting b be 4 diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_4.eprime b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_4.eprime deleted file mode 100644 index ba348b8892..0000000000 --- a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_4.eprime +++ /dev/null @@ -1,30 +0,0 @@ -language ESSENCE' 1.0 - -given n: int -given a: int -given b: int -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..1 + (b - a))] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..1 + (b - a))] of int(a..b) -branching on [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] -such that - and([and([or([x_ExplicitVarSizeWithFlags_Flags[q13] /\ - x_ExplicitVarSizeWithFlags_Values[q13] = t_ExplicitVarSizeWithDummy[q11] - | q13 : int(1..1 + (b - a))]) - | q11 : int(1..1 + (b - a)), t_ExplicitVarSizeWithDummy[q11] != b + 1]) - -> - sum([t_ExplicitVarSizeWithDummy[q14] | q14 : int(1..1 + (b - a)), t_ExplicitVarSizeWithDummy[q14] != b + 1]) <= - 6 | t_ExplicitVarSizeWithDummy : matrix indexed by [int(1..1 + (b - a))] of int(a..b + 1), - and([t_ExplicitVarSizeWithDummy[q6] < t_ExplicitVarSizeWithDummy[q6 + 1] \/ - t_ExplicitVarSizeWithDummy[q6] = b + 1 - | q6 : int(1..1 + (b - a) - 1)]), - and([t_ExplicitVarSizeWithDummy[q7] = b + 1 -> t_ExplicitVarSizeWithDummy[q7 + 1] = b + 1 - | q7 : int(1..1 + (b - a) - 1)])]), - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..1 + (b - a) - 1)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = a - | q2 : int(1..1 + (b - a))]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] - | q3 : int(1..1 + (b - a) - 1)]), - n <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..1 + (b - a))]) - diff --git a/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_1_1-solution000001.solution b/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_1_1-solution000001.solution deleted file mode 100644 index f1495354fe..0000000000 --- a/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_1_1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 4, 7} diff --git a/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_1_1.eprime b/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_1_1.eprime deleted file mode 100644 index b9c9ef2a41..0000000000 --- a/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_1_1.eprime +++ /dev/null @@ -1,8 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1..7)] of bool -branching on [x_Occurrence] -such that - and([x_Occurrence[i] /\ x_Occurrence[j] -> |i - j| >= 3 | i : int(1..7), j : int(1..7), j > i]), - 3 <= sum([toInt(x_Occurrence[q1]) | q1 : int(1..7)]) - diff --git a/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_1_2-solution000001.solution b/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_1_2-solution000001.solution deleted file mode 100644 index f1495354fe..0000000000 --- a/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_1_2-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 4, 7} diff --git a/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_1_2.eprime b/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_1_2.eprime deleted file mode 100644 index f4555045bf..0000000000 --- a/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_1_2.eprime +++ /dev/null @@ -1,17 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1..7)] of bool -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..7)] of int(1..8) -branching on [x_ExplicitVarSizeWithDummy, x_Occurrence] -such that - and([x_Occurrence[i] /\ x_Occurrence[j] -> |i - j| >= 3 | i : int(1..7), j : int(1..7), j > i]), - 3 <= sum([toInt(x_Occurrence[q1]) | q1 : int(1..7)]), - and([x_ExplicitVarSizeWithDummy[q2] < x_ExplicitVarSizeWithDummy[q2 + 1] \/ x_ExplicitVarSizeWithDummy[q2] = 8 - | q2 : int(1..6)]), - and([x_ExplicitVarSizeWithDummy[q3] = 8 -> x_ExplicitVarSizeWithDummy[q3 + 1] = 8 | q3 : int(1..6)]), - 3 <= sum([toInt(x_ExplicitVarSizeWithDummy[q4] != 8) | q4 : int(1..7)]), - and([x_ExplicitVarSizeWithDummy[q7] != 8 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q7]] | q7 : int(1..7)]), - and([x_Occurrence[q8] -> - or([x_ExplicitVarSizeWithDummy[q10] != 8 /\ x_ExplicitVarSizeWithDummy[q10] = q8 | q10 : int(1..7)]) - | q8 : int(1..7)]) - diff --git a/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_1_3-solution000001.solution b/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_1_3-solution000001.solution deleted file mode 100644 index f1495354fe..0000000000 --- a/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_1_3-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 4, 7} diff --git a/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_1_3.eprime b/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_1_3.eprime deleted file mode 100644 index a9df3b1a89..0000000000 --- a/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_1_3.eprime +++ /dev/null @@ -1,20 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1..7)] of bool -find x_ExplicitVarSizeWithMarker_Marker: int(0..7) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..7)] of int(1..7) -branching on [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_Occurrence] -such that - and([x_Occurrence[i] /\ x_Occurrence[j] -> |i - j| >= 3 | i : int(1..7), j : int(1..7), j > i]), - 3 <= sum([toInt(x_Occurrence[q1]) | q1 : int(1..7)]), - and([q2 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q2] < x_ExplicitVarSizeWithMarker_Values[q2 + 1] - | q2 : int(1..6)]), - and([q3 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q3] = 1 | q3 : int(1..7)]), - 3 <= x_ExplicitVarSizeWithMarker_Marker, - and([q6 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q6]] - | q6 : int(1..7)]), - and([x_Occurrence[q7] -> - or([q9 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q9] = q7 | q9 : int(1..7)]) - | q7 : int(1..7)]) - diff --git a/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_1_4-solution000001.solution b/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_1_4-solution000001.solution deleted file mode 100644 index f1495354fe..0000000000 --- a/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_1_4-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 4, 7} diff --git a/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_1_4.eprime b/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_1_4.eprime deleted file mode 100644 index f343493acc..0000000000 --- a/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_1_4.eprime +++ /dev/null @@ -1,20 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1..7)] of bool -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..7)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..7)] of int(1..7) -branching on [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_Occurrence] -such that - and([x_Occurrence[i] /\ x_Occurrence[j] -> |i - j| >= 3 | i : int(1..7), j : int(1..7), j > i]), - 3 <= sum([toInt(x_Occurrence[q1]) | q1 : int(1..7)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q2] < x_ExplicitVarSizeWithFlags_Values[q2 + 1] - | q2 : int(1..6)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3] = false -> x_ExplicitVarSizeWithFlags_Values[q3] = 1 | q3 : int(1..7)]), - and([x_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q4] | q4 : int(1..6)]), - 3 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q5]) | q5 : int(1..7)]), - and([x_ExplicitVarSizeWithFlags_Flags[q8] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q8]] | q8 : int(1..7)]), - and([x_Occurrence[q9] -> - or([x_ExplicitVarSizeWithFlags_Flags[q11] /\ x_ExplicitVarSizeWithFlags_Values[q11] = q9 | q11 : int(1..7)]) - | q9 : int(1..7)]) - diff --git a/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_2_1-solution000001.solution b/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_2_1-solution000001.solution deleted file mode 100644 index f1495354fe..0000000000 --- a/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_2_1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 4, 7} diff --git a/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_2_1.eprime b/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_2_1.eprime deleted file mode 100644 index 0f44241558..0000000000 --- a/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_2_1.eprime +++ /dev/null @@ -1,19 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..7)] of int(1..8) -find x_Occurrence: matrix indexed by [int(1..7)] of bool -branching on [x_Occurrence, x_ExplicitVarSizeWithDummy] -such that - and([x_ExplicitVarSizeWithDummy[q11] != 8 /\ x_ExplicitVarSizeWithDummy[q12] != 8 -> - |x_ExplicitVarSizeWithDummy[q11] - x_ExplicitVarSizeWithDummy[q12]| >= 3 - | q11 : int(1..7), q12 : int(1..7), q12 > q11]), - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 8 - | q1 : int(1..6)]), - and([x_ExplicitVarSizeWithDummy[q2] = 8 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 8 | q2 : int(1..6)]), - 3 <= sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 8) | q3 : int(1..7)]), - 3 <= sum([toInt(x_Occurrence[q5]) | q5 : int(1..7)]), - and([x_Occurrence[q6] -> - or([x_ExplicitVarSizeWithDummy[q8] != 8 /\ x_ExplicitVarSizeWithDummy[q8] = q6 | q8 : int(1..7)]) - | q6 : int(1..7)]), - and([x_ExplicitVarSizeWithDummy[q10] != 8 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q10]] | q10 : int(1..7)]) - diff --git a/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_2_2-solution000001.solution b/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_2_2-solution000001.solution deleted file mode 100644 index f1495354fe..0000000000 --- a/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_2_2-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 4, 7} diff --git a/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_2_2.eprime b/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_2_2.eprime deleted file mode 100644 index 4fb1321636..0000000000 --- a/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_2_2.eprime +++ /dev/null @@ -1,13 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..7)] of int(1..8) -branching on [x_ExplicitVarSizeWithDummy] -such that - and([x_ExplicitVarSizeWithDummy[q5] != 8 /\ x_ExplicitVarSizeWithDummy[q6] != 8 -> - |x_ExplicitVarSizeWithDummy[q5] - x_ExplicitVarSizeWithDummy[q6]| >= 3 - | q5 : int(1..7), q6 : int(1..7), q6 > q5]), - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 8 - | q1 : int(1..6)]), - and([x_ExplicitVarSizeWithDummy[q2] = 8 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 8 | q2 : int(1..6)]), - 3 <= sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 8) | q3 : int(1..7)]) - diff --git a/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_2_3-solution000001.solution b/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_2_3-solution000001.solution deleted file mode 100644 index f1495354fe..0000000000 --- a/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_2_3-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 4, 7} diff --git a/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_2_3.eprime b/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_2_3.eprime deleted file mode 100644 index 0c4c4b73d9..0000000000 --- a/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_2_3.eprime +++ /dev/null @@ -1,30 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..7)] of int(1..8) -find x_ExplicitVarSizeWithMarker_Marker: int(0..7) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..7)] of int(1..7) -branching on [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy] -such that - and([x_ExplicitVarSizeWithDummy[q16] != 8 /\ x_ExplicitVarSizeWithDummy[q17] != 8 -> - |x_ExplicitVarSizeWithDummy[q16] - x_ExplicitVarSizeWithDummy[q17]| >= 3 - | q16 : int(1..7), q17 : int(1..7), q17 > q16]), - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 8 - | q1 : int(1..6)]), - and([x_ExplicitVarSizeWithDummy[q2] = 8 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 8 | q2 : int(1..6)]), - 3 <= sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 8) | q3 : int(1..7)]), - and([q5 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q5] < x_ExplicitVarSizeWithMarker_Values[q5 + 1] - | q5 : int(1..6)]), - and([q6 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q6] = 1 | q6 : int(1..7)]), - 3 <= x_ExplicitVarSizeWithMarker_Marker, - and([q9 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q11] != 8 /\ - x_ExplicitVarSizeWithDummy[q11] = x_ExplicitVarSizeWithMarker_Values[q9] - | q11 : int(1..7)]) - | q9 : int(1..7)]), - and([x_ExplicitVarSizeWithDummy[q13] != 8 -> - or([q15 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q15] = x_ExplicitVarSizeWithDummy[q13] - | q15 : int(1..7)]) - | q13 : int(1..7)]) - diff --git a/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_2_4-solution000001.solution b/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_2_4-solution000001.solution deleted file mode 100644 index f1495354fe..0000000000 --- a/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_2_4-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 4, 7} diff --git a/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_2_4.eprime b/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_2_4.eprime deleted file mode 100644 index dde41e36d9..0000000000 --- a/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_2_4.eprime +++ /dev/null @@ -1,31 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..7)] of int(1..8) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..7)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..7)] of int(1..7) -branching on [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy] -such that - and([x_ExplicitVarSizeWithDummy[q18] != 8 /\ x_ExplicitVarSizeWithDummy[q19] != 8 -> - |x_ExplicitVarSizeWithDummy[q18] - x_ExplicitVarSizeWithDummy[q19]| >= 3 - | q18 : int(1..7), q19 : int(1..7), q19 > q18]), - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 8 - | q1 : int(1..6)]), - and([x_ExplicitVarSizeWithDummy[q2] = 8 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 8 | q2 : int(1..6)]), - 3 <= sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 8) | q3 : int(1..7)]), - and([x_ExplicitVarSizeWithFlags_Flags[q5 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q5] < x_ExplicitVarSizeWithFlags_Values[q5 + 1] - | q5 : int(1..6)]), - and([x_ExplicitVarSizeWithFlags_Flags[q6] = false -> x_ExplicitVarSizeWithFlags_Values[q6] = 1 | q6 : int(1..7)]), - and([x_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q7] | q7 : int(1..6)]), - 3 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q8]) | q8 : int(1..7)]), - and([x_ExplicitVarSizeWithFlags_Flags[q11] -> - or([x_ExplicitVarSizeWithDummy[q13] != 8 /\ - x_ExplicitVarSizeWithDummy[q13] = x_ExplicitVarSizeWithFlags_Values[q11] - | q13 : int(1..7)]) - | q11 : int(1..7)]), - and([x_ExplicitVarSizeWithDummy[q15] != 8 -> - or([x_ExplicitVarSizeWithFlags_Flags[q17] /\ - x_ExplicitVarSizeWithFlags_Values[q17] = x_ExplicitVarSizeWithDummy[q15] - | q17 : int(1..7)]) - | q15 : int(1..7)]) - diff --git a/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_3_1-solution000001.solution b/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_3_1-solution000001.solution deleted file mode 100644 index f1495354fe..0000000000 --- a/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_3_1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 4, 7} diff --git a/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_3_1.eprime b/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_3_1.eprime deleted file mode 100644 index 8a8eb99ad1..0000000000 --- a/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_3_1.eprime +++ /dev/null @@ -1,22 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..7) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..7)] of int(1..7) -find x_Occurrence: matrix indexed by [int(1..7)] of bool -branching on [x_Occurrence, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] -such that - and([q10 <= x_ExplicitVarSizeWithMarker_Marker /\ q11 <= x_ExplicitVarSizeWithMarker_Marker -> - |x_ExplicitVarSizeWithMarker_Values[q10] - x_ExplicitVarSizeWithMarker_Values[q11]| >= 3 - | q10 : int(1..7), q11 : int(1..7), q11 > q10]), - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..6)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..7)]), - 3 <= x_ExplicitVarSizeWithMarker_Marker, - 3 <= sum([toInt(x_Occurrence[q4]) | q4 : int(1..7)]), - and([x_Occurrence[q5] -> - or([q7 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q7] = q5 | q7 : int(1..7)]) - | q5 : int(1..7)]), - and([q9 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q9]] - | q9 : int(1..7)]) - diff --git a/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_3_2-solution000001.solution b/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_3_2-solution000001.solution deleted file mode 100644 index f1495354fe..0000000000 --- a/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_3_2-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 4, 7} diff --git a/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_3_2.eprime b/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_3_2.eprime deleted file mode 100644 index dfacb2f87a..0000000000 --- a/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_3_2.eprime +++ /dev/null @@ -1,30 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..7) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..7)] of int(1..7) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..7)] of int(1..8) -branching on [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] -such that - and([q16 <= x_ExplicitVarSizeWithMarker_Marker /\ q17 <= x_ExplicitVarSizeWithMarker_Marker -> - |x_ExplicitVarSizeWithMarker_Values[q16] - x_ExplicitVarSizeWithMarker_Values[q17]| >= 3 - | q16 : int(1..7), q17 : int(1..7), q17 > q16]), - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..6)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..7)]), - 3 <= x_ExplicitVarSizeWithMarker_Marker, - and([x_ExplicitVarSizeWithDummy[q4] < x_ExplicitVarSizeWithDummy[q4 + 1] \/ x_ExplicitVarSizeWithDummy[q4] = 8 - | q4 : int(1..6)]), - and([x_ExplicitVarSizeWithDummy[q5] = 8 -> x_ExplicitVarSizeWithDummy[q5 + 1] = 8 | q5 : int(1..6)]), - 3 <= sum([toInt(x_ExplicitVarSizeWithDummy[q6] != 8) | q6 : int(1..7)]), - and([x_ExplicitVarSizeWithDummy[q9] != 8 -> - or([q11 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q11] = x_ExplicitVarSizeWithDummy[q9] - | q11 : int(1..7)]) - | q9 : int(1..7)]), - and([q13 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q15] != 8 /\ - x_ExplicitVarSizeWithDummy[q15] = x_ExplicitVarSizeWithMarker_Values[q13] - | q15 : int(1..7)]) - | q13 : int(1..7)]) - diff --git a/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_3_3-solution000001.solution b/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_3_3-solution000001.solution deleted file mode 100644 index f1495354fe..0000000000 --- a/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_3_3-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 4, 7} diff --git a/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_3_3.eprime b/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_3_3.eprime deleted file mode 100644 index a58004f8c5..0000000000 --- a/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_3_3.eprime +++ /dev/null @@ -1,15 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..7) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..7)] of int(1..7) -branching on [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] -such that - and([q4 <= x_ExplicitVarSizeWithMarker_Marker /\ q5 <= x_ExplicitVarSizeWithMarker_Marker -> - |x_ExplicitVarSizeWithMarker_Values[q4] - x_ExplicitVarSizeWithMarker_Values[q5]| >= 3 - | q4 : int(1..7), q5 : int(1..7), q5 > q4]), - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..6)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..7)]), - 3 <= x_ExplicitVarSizeWithMarker_Marker - diff --git a/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_3_4-solution000001.solution b/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_3_4-solution000001.solution deleted file mode 100644 index f1495354fe..0000000000 --- a/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_3_4-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 4, 7} diff --git a/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_3_4.eprime b/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_3_4.eprime deleted file mode 100644 index 0e6666e578..0000000000 --- a/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_3_4.eprime +++ /dev/null @@ -1,35 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..7) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..7)] of int(1..7) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..7)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..7)] of int(1..7) -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithMarker_Marker, - x_ExplicitVarSizeWithMarker_Values] -such that - and([q17 <= x_ExplicitVarSizeWithMarker_Marker /\ q18 <= x_ExplicitVarSizeWithMarker_Marker -> - |x_ExplicitVarSizeWithMarker_Values[q17] - x_ExplicitVarSizeWithMarker_Values[q18]| >= 3 - | q17 : int(1..7), q18 : int(1..7), q18 > q17]), - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..6)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..7)]), - 3 <= x_ExplicitVarSizeWithMarker_Marker, - and([x_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q4] < x_ExplicitVarSizeWithFlags_Values[q4 + 1] - | q4 : int(1..6)]), - and([x_ExplicitVarSizeWithFlags_Flags[q5] = false -> x_ExplicitVarSizeWithFlags_Values[q5] = 1 | q5 : int(1..7)]), - and([x_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q6] | q6 : int(1..6)]), - 3 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q7]) | q7 : int(1..7)]), - and([x_ExplicitVarSizeWithFlags_Flags[q10] -> - or([q12 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q12] = x_ExplicitVarSizeWithFlags_Values[q10] - | q12 : int(1..7)]) - | q10 : int(1..7)]), - and([q14 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q16] /\ - x_ExplicitVarSizeWithFlags_Values[q16] = x_ExplicitVarSizeWithMarker_Values[q14] - | q16 : int(1..7)]) - | q14 : int(1..7)]) - diff --git a/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_4_1-solution000001.solution b/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_4_1-solution000001.solution deleted file mode 100644 index f1495354fe..0000000000 --- a/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_4_1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 4, 7} diff --git a/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_4_1.eprime b/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_4_1.eprime deleted file mode 100644 index 65f611992a..0000000000 --- a/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_4_1.eprime +++ /dev/null @@ -1,23 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..7)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..7)] of int(1..7) -find x_Occurrence: matrix indexed by [int(1..7)] of bool -branching on [x_Occurrence, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] -such that - and([x_ExplicitVarSizeWithFlags_Flags[q12] /\ x_ExplicitVarSizeWithFlags_Flags[q13] -> - |x_ExplicitVarSizeWithFlags_Values[q12] - x_ExplicitVarSizeWithFlags_Values[q13]| >= 3 - | q12 : int(1..7), q13 : int(1..7), q13 > q12]), - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..6)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..7)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..6)]), - 3 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..7)]), - 3 <= sum([toInt(x_Occurrence[q6]) | q6 : int(1..7)]), - and([x_Occurrence[q7] -> - or([x_ExplicitVarSizeWithFlags_Flags[q9] /\ x_ExplicitVarSizeWithFlags_Values[q9] = q7 | q9 : int(1..7)]) - | q7 : int(1..7)]), - and([x_ExplicitVarSizeWithFlags_Flags[q11] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q11]] - | q11 : int(1..7)]) - diff --git a/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_4_2-solution000001.solution b/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_4_2-solution000001.solution deleted file mode 100644 index f1495354fe..0000000000 --- a/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_4_2-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 4, 7} diff --git a/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_4_2.eprime b/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_4_2.eprime deleted file mode 100644 index ff6745f307..0000000000 --- a/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_4_2.eprime +++ /dev/null @@ -1,31 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..7)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..7)] of int(1..7) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..7)] of int(1..8) -branching on [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] -such that - and([x_ExplicitVarSizeWithFlags_Flags[q18] /\ x_ExplicitVarSizeWithFlags_Flags[q19] -> - |x_ExplicitVarSizeWithFlags_Values[q18] - x_ExplicitVarSizeWithFlags_Values[q19]| >= 3 - | q18 : int(1..7), q19 : int(1..7), q19 > q18]), - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..6)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..7)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..6)]), - 3 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..7)]), - and([x_ExplicitVarSizeWithDummy[q6] < x_ExplicitVarSizeWithDummy[q6 + 1] \/ x_ExplicitVarSizeWithDummy[q6] = 8 - | q6 : int(1..6)]), - and([x_ExplicitVarSizeWithDummy[q7] = 8 -> x_ExplicitVarSizeWithDummy[q7 + 1] = 8 | q7 : int(1..6)]), - 3 <= sum([toInt(x_ExplicitVarSizeWithDummy[q8] != 8) | q8 : int(1..7)]), - and([x_ExplicitVarSizeWithDummy[q11] != 8 -> - or([x_ExplicitVarSizeWithFlags_Flags[q13] /\ - x_ExplicitVarSizeWithFlags_Values[q13] = x_ExplicitVarSizeWithDummy[q11] - | q13 : int(1..7)]) - | q11 : int(1..7)]), - and([x_ExplicitVarSizeWithFlags_Flags[q15] -> - or([x_ExplicitVarSizeWithDummy[q17] != 8 /\ - x_ExplicitVarSizeWithDummy[q17] = x_ExplicitVarSizeWithFlags_Values[q15] - | q17 : int(1..7)]) - | q15 : int(1..7)]) - diff --git a/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_4_3-solution000001.solution b/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_4_3-solution000001.solution deleted file mode 100644 index f1495354fe..0000000000 --- a/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_4_3-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 4, 7} diff --git a/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_4_3.eprime b/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_4_3.eprime deleted file mode 100644 index 1d7cf573bd..0000000000 --- a/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_4_3.eprime +++ /dev/null @@ -1,35 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..7)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..7)] of int(1..7) -find x_ExplicitVarSizeWithMarker_Marker: int(0..7) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..7)] of int(1..7) -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithFlags_Flags, - x_ExplicitVarSizeWithFlags_Values] -such that - and([x_ExplicitVarSizeWithFlags_Flags[q17] /\ x_ExplicitVarSizeWithFlags_Flags[q18] -> - |x_ExplicitVarSizeWithFlags_Values[q17] - x_ExplicitVarSizeWithFlags_Values[q18]| >= 3 - | q17 : int(1..7), q18 : int(1..7), q18 > q17]), - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..6)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..7)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..6)]), - 3 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..7)]), - and([q6 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q6] < x_ExplicitVarSizeWithMarker_Values[q6 + 1] - | q6 : int(1..6)]), - and([q7 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q7] = 1 | q7 : int(1..7)]), - 3 <= x_ExplicitVarSizeWithMarker_Marker, - and([q10 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q12] /\ - x_ExplicitVarSizeWithFlags_Values[q12] = x_ExplicitVarSizeWithMarker_Values[q10] - | q12 : int(1..7)]) - | q10 : int(1..7)]), - and([x_ExplicitVarSizeWithFlags_Flags[q14] -> - or([q16 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q16] = x_ExplicitVarSizeWithFlags_Values[q14] - | q16 : int(1..7)]) - | q14 : int(1..7)]) - diff --git a/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_4_4-solution000001.solution b/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_4_4-solution000001.solution deleted file mode 100644 index f1495354fe..0000000000 --- a/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_4_4-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 4, 7} diff --git a/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_4_4.eprime b/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_4_4.eprime deleted file mode 100644 index 4d96a6fb8a..0000000000 --- a/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_4_4.eprime +++ /dev/null @@ -1,16 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..7)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..7)] of int(1..7) -branching on [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] -such that - and([x_ExplicitVarSizeWithFlags_Flags[q6] /\ x_ExplicitVarSizeWithFlags_Flags[q7] -> - |x_ExplicitVarSizeWithFlags_Values[q6] - x_ExplicitVarSizeWithFlags_Values[q7]| >= 3 - | q6 : int(1..7), q7 : int(1..7), q7 > q6]), - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..6)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..7)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..6)]), - 3 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..7)]) - diff --git a/tests/exhaustive/basic/relation04_param/expected/model_1_1-param4-solution000001.solution b/tests/exhaustive/basic/relation04_param/expected/model_1_1-param4-solution000001.solution deleted file mode 100644 index 547e6d2e7e..0000000000 --- a/tests/exhaustive/basic/relation04_param/expected/model_1_1-param4-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting r be relation((3, {2}, 6), (3, {3}, 9)) diff --git a/tests/exhaustive/basic/relation04_param/expected/model_1_1-param4.eprime-param b/tests/exhaustive/basic/relation04_param/expected/model_1_1-param4.eprime-param deleted file mode 100644 index 87708d95a4..0000000000 --- a/tests/exhaustive/basic/relation04_param/expected/model_1_1-param4.eprime-param +++ /dev/null @@ -1,11 +0,0 @@ -language ESSENCE' 1.0 - -letting a_RelationAsSetR6_ExplicitR6_1 be [3, 3; int(1..2)] -letting a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy be [[2; int(1)], [3; int(1)]; int(1..2)] -$ Visualisation for a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy -$ 2 -$ 3 - -letting a_RelationAsSetR6_ExplicitR6_3 be [6, 9; int(1..2)] -letting fin1 be 2 -letting fin2 be 1 diff --git a/tests/exhaustive/basic/relation04_param/expected/model_1_1.eprime b/tests/exhaustive/basic/relation04_param/expected/model_1_1.eprime deleted file mode 100644 index 2ec04d204d..0000000000 --- a/tests/exhaustive/basic/relation04_param/expected/model_1_1.eprime +++ /dev/null @@ -1,70 +0,0 @@ -language ESSENCE' 1.0 - -given fin1: int -given fin2: int -given a_RelationAsSetR6_ExplicitR6_1: matrix indexed by [int(1..fin1)] of int(1..3) -given a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy: - matrix indexed by [int(1..fin1), int(1..fin2)] of int(2..4) -given a_RelationAsSetR6_ExplicitR6_3: matrix indexed by [int(1..fin1)] of int(4..10) -find r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Marker: int(0..84) -find r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_1: matrix indexed by [int(1..84)] of int(1..3) -find r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_2_Occurrence: - matrix indexed by [int(1..84), int(2..3)] of bool -find r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_3: matrix indexed by [int(1..84)] of int(4..10) -branching on - [r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Marker, r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_1, - r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_2_Occurrence, - r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_3] -such that - and([q9 <= r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Marker -> - or([and([a_RelationAsSetR6_ExplicitR6_1[q11] = r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_1[q9], - and([r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_2_Occurrence - [q9, a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q11, q13]] - | q13 : int(1..fin2), - a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q11, q13] != 4]) - /\ - and([r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_2_Occurrence[q9, q14] -> - or([a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q11, q16] = q14 - | q16 : int(1..fin2), - a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q11, q16] != 4]) - | q14 : int(2..3)]), - a_RelationAsSetR6_ExplicitR6_3[q11] = r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_3[q9]; - int(1..3)]) - | q11 : int(1..fin1)]) - | q9 : int(1..84)]), - and([or([q19 <= r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Marker /\ - and([r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_1[q19] = a_RelationAsSetR6_ExplicitR6_1[q17], - and([r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_2_Occurrence[q19, q20] -> - or([a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q17, q22] = q20 - | q22 : int(1..fin2), - a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q17, q22] != 4]) - | q20 : int(2..3)]) - /\ - and([r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_2_Occurrence - [q19, a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q17, q24]] - | q24 : int(1..fin2), - a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q17, q24] != 4]), - r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_3[q19] = a_RelationAsSetR6_ExplicitR6_3[q17]; - int(1..3)]) - | q19 : int(1..84)]) - | q17 : int(1..fin1)]), - r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Marker = fin1, - and([q1 + 1 <= r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Marker -> - flatten([[r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_1[q1]; int(1)], - [-toInt(r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_2_Occurrence[q1, q5]) | q5 : int(2..3)], - [r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_3[q1]; int(1)]; - int(1..3)]) - r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Marker -> - and([r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_1[q2] = 1, - and([r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_2_Occurrence[q2, q7] = false | q7 : int(2..3)]), - r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_3[q2] = 4; - int(1..3)]) - | q2 : int(1..84)]) - diff --git a/tests/exhaustive/basic/relation04_param/expected/model_1_2-param4-solution000001.solution b/tests/exhaustive/basic/relation04_param/expected/model_1_2-param4-solution000001.solution deleted file mode 100644 index 547e6d2e7e..0000000000 --- a/tests/exhaustive/basic/relation04_param/expected/model_1_2-param4-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting r be relation((3, {2}, 6), (3, {3}, 9)) diff --git a/tests/exhaustive/basic/relation04_param/expected/model_1_2-param4.eprime-param b/tests/exhaustive/basic/relation04_param/expected/model_1_2-param4.eprime-param deleted file mode 100644 index 87708d95a4..0000000000 --- a/tests/exhaustive/basic/relation04_param/expected/model_1_2-param4.eprime-param +++ /dev/null @@ -1,11 +0,0 @@ -language ESSENCE' 1.0 - -letting a_RelationAsSetR6_ExplicitR6_1 be [3, 3; int(1..2)] -letting a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy be [[2; int(1)], [3; int(1)]; int(1..2)] -$ Visualisation for a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy -$ 2 -$ 3 - -letting a_RelationAsSetR6_ExplicitR6_3 be [6, 9; int(1..2)] -letting fin1 be 2 -letting fin2 be 1 diff --git a/tests/exhaustive/basic/relation04_param/expected/model_1_2.eprime b/tests/exhaustive/basic/relation04_param/expected/model_1_2.eprime deleted file mode 100644 index 2a255134f0..0000000000 --- a/tests/exhaustive/basic/relation04_param/expected/model_1_2.eprime +++ /dev/null @@ -1,152 +0,0 @@ -language ESSENCE' 1.0 - -given fin1: int -given fin2: int -given a_RelationAsSetR6_ExplicitR6_1: matrix indexed by [int(1..fin1)] of int(1..3) -given a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy: - matrix indexed by [int(1..fin1), int(1..fin2)] of int(2..4) -given a_RelationAsSetR6_ExplicitR6_3: matrix indexed by [int(1..fin1)] of int(4..10) -find r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Marker: int(0..84) -find r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_1: matrix indexed by [int(1..84)] of int(1..3) -find r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_2_Occurrence: - matrix indexed by [int(1..84), int(2..3)] of bool -find r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_3: matrix indexed by [int(1..84)] of int(4..10) -find r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Marker: int(0..84) -find r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_1: matrix indexed by [int(1..84)] of int(1..3) -find r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy: - matrix indexed by [int(1..84), int(1..2)] of int(2..4) -find r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_3: matrix indexed by [int(1..84)] of int(4..10) -branching on - [r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Marker, r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_1, - r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy, - r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_3, r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Marker, - r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_1, - r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_2_Occurrence, - r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_3] -such that - and([q36 <= r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Marker -> - or([and([a_RelationAsSetR6_ExplicitR6_1[q38] = r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_1[q36], - and([r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_2_Occurrence - [q36, a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q38, q40]] - | q40 : int(1..fin2), - a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q38, q40] != 4]) - /\ - and([r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_2_Occurrence[q36, q41] -> - or([a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q38, q43] = q41 - | q43 : int(1..fin2), - a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q38, q43] != 4]) - | q41 : int(2..3)]), - a_RelationAsSetR6_ExplicitR6_3[q38] = r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_3[q36]; - int(1..3)]) - | q38 : int(1..fin1)]) - | q36 : int(1..84)]), - and([or([q46 <= r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Marker /\ - and([r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_1[q46] = a_RelationAsSetR6_ExplicitR6_1[q44], - and([r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_2_Occurrence[q46, q47] -> - or([a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q44, q49] = q47 - | q49 : int(1..fin2), - a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q44, q49] != 4]) - | q47 : int(2..3)]) - /\ - and([r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_2_Occurrence - [q46, a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q44, q51]] - | q51 : int(1..fin2), - a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q44, q51] != 4]), - r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_3[q46] = a_RelationAsSetR6_ExplicitR6_3[q44]; - int(1..3)]) - | q46 : int(1..84)]) - | q44 : int(1..fin1)]), - r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Marker = fin1, - and([q1 + 1 <= r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Marker -> - flatten([[r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_1[q1]; int(1)], - [-toInt(r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_2_Occurrence[q1, q5]) | q5 : int(2..3)], - [r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_3[q1]; int(1)]; - int(1..3)]) - r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Marker -> - and([r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_1[q2] = 1, - and([r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_2_Occurrence[q2, q7] = false | q7 : int(2..3)]), - r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_3[q2] = 4; - int(1..3)]) - | q2 : int(1..84)]), - and([q8 + 1 <= r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Marker -> - flatten([[r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_1[q8]; int(1)], - [r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q8, q15] - | q15 : int(1..2)], - [r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_3[q8]; int(1)]; - int(1..3)]) - r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Marker -> - and([r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_1[q9] = 1, - and([r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q9, q17] = 2 - | q17 : int(1..2)]), - r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_3[q9] = 4; - int(1..3)]) - | q9 : int(1..84)]), - and([q10 <= r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Marker -> - r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q10, 1] < - r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q10, 2] - \/ r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q10, 1] = 4 - | q10 : int(1..84)]), - and([q10 <= r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Marker -> - (r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q10, 1] = 4 -> - r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q10, 2] = 4) - | q10 : int(1..84)]), - and([q19 <= r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Marker -> - or([q21 <= r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Marker /\ - and([r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_1[q21] = - r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_1[q19], - and([r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_2_Occurrence[q21, q22] -> - or([r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q19, q24] != - 4 - /\ - r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q19, q24] = - q22 | q24 : int(1..2)]) - | q22 : int(2..3)]) - /\ - and([r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q19, q26] != 4 -> - r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_2_Occurrence - [q21, - r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q19, q26]] - | q26 : int(1..2)]), - r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_3[q21] = - r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_3[q19]; - int(1..3)]) - | q21 : int(1..84)]) - | q19 : int(1..84)]), - and([q27 <= r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Marker -> - or([q29 <= r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Marker /\ - and([r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_1[q29] = - r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_1[q27], - and([r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q29, q31] != 4 -> - r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_2_Occurrence - [q27, - r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q29, q31]] - | q31 : int(1..2)]) - /\ - and([r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_2_Occurrence[q27, q32] -> - or([r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q29, q34] != - 4 - /\ - r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q29, q34] = - q32 | q34 : int(1..2)]) - | q32 : int(2..3)]), - r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_3[q29] = - r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_3[q27]; - int(1..3)]) - | q29 : int(1..84)]) - | q27 : int(1..84)]), - r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Marker = r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Marker - diff --git a/tests/exhaustive/basic/relation04_param/expected/model_1_3-param4-solution000001.solution b/tests/exhaustive/basic/relation04_param/expected/model_1_3-param4-solution000001.solution deleted file mode 100644 index 547e6d2e7e..0000000000 --- a/tests/exhaustive/basic/relation04_param/expected/model_1_3-param4-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting r be relation((3, {2}, 6), (3, {3}, 9)) diff --git a/tests/exhaustive/basic/relation04_param/expected/model_1_3-param4.eprime-param b/tests/exhaustive/basic/relation04_param/expected/model_1_3-param4.eprime-param deleted file mode 100644 index 87708d95a4..0000000000 --- a/tests/exhaustive/basic/relation04_param/expected/model_1_3-param4.eprime-param +++ /dev/null @@ -1,11 +0,0 @@ -language ESSENCE' 1.0 - -letting a_RelationAsSetR6_ExplicitR6_1 be [3, 3; int(1..2)] -letting a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy be [[2; int(1)], [3; int(1)]; int(1..2)] -$ Visualisation for a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy -$ 2 -$ 3 - -letting a_RelationAsSetR6_ExplicitR6_3 be [6, 9; int(1..2)] -letting fin1 be 2 -letting fin2 be 1 diff --git a/tests/exhaustive/basic/relation04_param/expected/model_1_3.eprime b/tests/exhaustive/basic/relation04_param/expected/model_1_3.eprime deleted file mode 100644 index ede514684e..0000000000 --- a/tests/exhaustive/basic/relation04_param/expected/model_1_3.eprime +++ /dev/null @@ -1,178 +0,0 @@ -language ESSENCE' 1.0 - -given fin1: int -given fin2: int -given a_RelationAsSetR6_ExplicitR6_1: matrix indexed by [int(1..fin1)] of int(1..3) -given a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy: - matrix indexed by [int(1..fin1), int(1..fin2)] of int(2..4) -given a_RelationAsSetR6_ExplicitR6_3: matrix indexed by [int(1..fin1)] of int(4..10) -find r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Marker: int(0..84) -find r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_1: matrix indexed by [int(1..84)] of int(1..3) -find r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_2_Occurrence: - matrix indexed by [int(1..84), int(2..3)] of bool -find r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_3: matrix indexed by [int(1..84)] of int(4..10) -find r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Marker: int(0..84) -find r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_1: matrix indexed by [int(1..84)] of int(1..3) -find r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Marker: - matrix indexed by [int(1..84)] of int(0..2) -find r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Values: - matrix indexed by [int(1..84), int(1..2)] of int(2..3) -find r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_3: matrix indexed by [int(1..84)] of int(4..10) -branching on - [r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Marker, r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_1, - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Marker, - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Values, - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_3, r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Marker, - r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_1, - r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_2_Occurrence, - r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_3] -such that - and([q35 <= r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Marker -> - or([and([a_RelationAsSetR6_ExplicitR6_1[q37] = r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_1[q35], - and([r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_2_Occurrence - [q35, a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q37, q39]] - | q39 : int(1..fin2), - a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q37, q39] != 4]) - /\ - and([r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_2_Occurrence[q35, q40] -> - or([a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q37, q42] = q40 - | q42 : int(1..fin2), - a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q37, q42] != 4]) - | q40 : int(2..3)]), - a_RelationAsSetR6_ExplicitR6_3[q37] = r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_3[q35]; - int(1..3)]) - | q37 : int(1..fin1)]) - | q35 : int(1..84)]), - and([or([q45 <= r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Marker /\ - and([r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_1[q45] = a_RelationAsSetR6_ExplicitR6_1[q43], - and([r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_2_Occurrence[q45, q46] -> - or([a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q43, q48] = q46 - | q48 : int(1..fin2), - a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q43, q48] != 4]) - | q46 : int(2..3)]) - /\ - and([r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_2_Occurrence - [q45, a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q43, q50]] - | q50 : int(1..fin2), - a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q43, q50] != 4]), - r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_3[q45] = a_RelationAsSetR6_ExplicitR6_3[q43]; - int(1..3)]) - | q45 : int(1..84)]) - | q43 : int(1..fin1)]), - r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Marker = fin1, - and([q1 + 1 <= r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Marker -> - flatten([[r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_1[q1]; int(1)], - [-toInt(r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_2_Occurrence[q1, q5]) | q5 : int(2..3)], - [r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_3[q1]; int(1)]; - int(1..3)]) - r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Marker -> - and([r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_1[q2] = 1, - and([r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_2_Occurrence[q2, q7] = false | q7 : int(2..3)]), - r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_3[q2] = 4; - int(1..3)]) - | q2 : int(1..84)]), - and([q8 + 1 <= r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Marker -> - flatten([[r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_1[q8]; int(1)], - flatten([[r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Marker[q8]; - int(1)], - flatten([[r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Values - [q8, q14]; - int(1)] - | q14 : int(1..2)]); - int(1..2)]), - [r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_3[q8]; int(1)]; - int(1..3)]) - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Marker -> - and([r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_1[q9] = 1, - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Marker[q9] = 0 /\ - and([r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Values[q9, q16] = 2 - | q16 : int(1..2)]), - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_3[q9] = 4; - int(1..3)]) - | q9 : int(1..84)]), - and([q10 <= r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Marker -> - (2 <= r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Marker[q10] -> - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Values[q10, 1] < - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Values[q10, 2]) - | q10 : int(1..84)]), - and([q10 <= r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Marker -> - and([q12 > r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Marker[q10] -> - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Values[q10, q12] = 2 - | q12 : int(1..2)]) - | q10 : int(1..84)]), - and([q18 <= r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Marker -> - or([q20 <= r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Marker /\ - and([r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_1[q20] = - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_1[q18], - and([r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_2_Occurrence[q20, q21] -> - or([q23 <= - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Marker[q18] - /\ - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Values - [q18, q23] - = q21 - | q23 : int(1..2)]) - | q21 : int(2..3)]) - /\ - and([q25 <= - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Marker[q18] - -> - r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_2_Occurrence - [q20, - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Values - [q18, q25]] - | q25 : int(1..2)]), - r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_3[q20] = - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_3[q18]; - int(1..3)]) - | q20 : int(1..84)]) - | q18 : int(1..84)]), - and([q26 <= r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Marker -> - or([q28 <= r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Marker /\ - and([r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_1[q28] = - r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_1[q26], - and([q30 <= - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Marker[q28] - -> - r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_2_Occurrence - [q26, - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Values - [q28, q30]] - | q30 : int(1..2)]) - /\ - and([r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_2_Occurrence[q26, q31] -> - or([q33 <= - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Marker[q28] - /\ - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Values - [q28, q33] - = q31 - | q33 : int(1..2)]) - | q31 : int(2..3)]), - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_3[q28] = - r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_3[q26]; - int(1..3)]) - | q28 : int(1..84)]) - | q26 : int(1..84)]), - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Marker = r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Marker - diff --git a/tests/exhaustive/basic/relation04_param/expected/model_1_4-param4-solution000001.solution b/tests/exhaustive/basic/relation04_param/expected/model_1_4-param4-solution000001.solution deleted file mode 100644 index 547e6d2e7e..0000000000 --- a/tests/exhaustive/basic/relation04_param/expected/model_1_4-param4-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting r be relation((3, {2}, 6), (3, {3}, 9)) diff --git a/tests/exhaustive/basic/relation04_param/expected/model_1_4-param4.eprime-param b/tests/exhaustive/basic/relation04_param/expected/model_1_4-param4.eprime-param deleted file mode 100644 index 87708d95a4..0000000000 --- a/tests/exhaustive/basic/relation04_param/expected/model_1_4-param4.eprime-param +++ /dev/null @@ -1,11 +0,0 @@ -language ESSENCE' 1.0 - -letting a_RelationAsSetR6_ExplicitR6_1 be [3, 3; int(1..2)] -letting a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy be [[2; int(1)], [3; int(1)]; int(1..2)] -$ Visualisation for a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy -$ 2 -$ 3 - -letting a_RelationAsSetR6_ExplicitR6_3 be [6, 9; int(1..2)] -letting fin1 be 2 -letting fin2 be 1 diff --git a/tests/exhaustive/basic/relation04_param/expected/model_1_4.eprime b/tests/exhaustive/basic/relation04_param/expected/model_1_4.eprime deleted file mode 100644 index b140b9955b..0000000000 --- a/tests/exhaustive/basic/relation04_param/expected/model_1_4.eprime +++ /dev/null @@ -1,184 +0,0 @@ -language ESSENCE' 1.0 - -given fin1: int -given fin2: int -given a_RelationAsSetR6_ExplicitR6_1: matrix indexed by [int(1..fin1)] of int(1..3) -given a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy: - matrix indexed by [int(1..fin1), int(1..fin2)] of int(2..4) -given a_RelationAsSetR6_ExplicitR6_3: matrix indexed by [int(1..fin1)] of int(4..10) -find r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Marker: int(0..84) -find r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_1: matrix indexed by [int(1..84)] of int(1..3) -find r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_2_Occurrence: - matrix indexed by [int(1..84), int(2..3)] of bool -find r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_3: matrix indexed by [int(1..84)] of int(4..10) -find r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Marker: int(0..84) -find r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_1: matrix indexed by [int(1..84)] of int(1..3) -find r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Flags: - matrix indexed by [int(1..84), int(1..2)] of bool -find r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Values: - matrix indexed by [int(1..84), int(1..2)] of int(2..3) -find r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_3: matrix indexed by [int(1..84)] of int(4..10) -branching on - [r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Marker, r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_1, - r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Flags, - r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Values, - r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_3, r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Marker, - r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_1, - r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_2_Occurrence, - r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_3] -such that - and([q38 <= r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Marker -> - or([and([a_RelationAsSetR6_ExplicitR6_1[q40] = r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_1[q38], - and([r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_2_Occurrence - [q38, a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q40, q42]] - | q42 : int(1..fin2), - a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q40, q42] != 4]) - /\ - and([r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_2_Occurrence[q38, q43] -> - or([a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q40, q45] = q43 - | q45 : int(1..fin2), - a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q40, q45] != 4]) - | q43 : int(2..3)]), - a_RelationAsSetR6_ExplicitR6_3[q40] = r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_3[q38]; - int(1..3)]) - | q40 : int(1..fin1)]) - | q38 : int(1..84)]), - and([or([q48 <= r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Marker /\ - and([r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_1[q48] = a_RelationAsSetR6_ExplicitR6_1[q46], - and([r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_2_Occurrence[q48, q49] -> - or([a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q46, q51] = q49 - | q51 : int(1..fin2), - a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q46, q51] != 4]) - | q49 : int(2..3)]) - /\ - and([r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_2_Occurrence - [q48, a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q46, q53]] - | q53 : int(1..fin2), - a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q46, q53] != 4]), - r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_3[q48] = a_RelationAsSetR6_ExplicitR6_3[q46]; - int(1..3)]) - | q48 : int(1..84)]) - | q46 : int(1..fin1)]), - r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Marker = fin1, - and([q1 + 1 <= r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Marker -> - flatten([[r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_1[q1]; int(1)], - [-toInt(r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_2_Occurrence[q1, q5]) | q5 : int(2..3)], - [r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_3[q1]; int(1)]; - int(1..3)]) - r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Marker -> - and([r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_1[q2] = 1, - and([r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_2_Occurrence[q2, q7] = false | q7 : int(2..3)]), - r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_3[q2] = 4; - int(1..3)]) - | q2 : int(1..84)]), - and([q8 + 1 <= r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Marker -> - flatten([[r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_1[q8]; int(1)], - flatten([flatten([[-toInt(r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Flags - [q8, q16]); - int(1)], - [r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Values - [q8, q16]; - int(1)]; - int(1..2)]) - | q16 : int(1..2)]), - [r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_3[q8]; int(1)]; - int(1..3)]) - r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Marker -> - and([r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_1[q9] = 1, - and([r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Flags[q9, q18] = - false - | q18 : int(1..2)]) - /\ - and([r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Values[q9, q19] = 2 - | q19 : int(1..2)]), - r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_3[q9] = 4; - int(1..3)]) - | q9 : int(1..84)]), - and([q10 <= r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Marker -> - (r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Flags[q10, 2] -> - r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Values[q10, 1] < - r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Values[q10, 2]) - | q10 : int(1..84)]), - and([q10 <= r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Marker -> - and([r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Flags[q10, q12] = false -> - r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Values[q10, q12] = 2 - | q12 : int(1..2)]) - | q10 : int(1..84)]), - and([q10 <= r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Marker -> - (r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Flags[q10, 2] -> - r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Flags[q10, 1]) - | q10 : int(1..84)]), - and([q21 <= r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Marker -> - or([q23 <= r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Marker /\ - and([r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_1[q23] = - r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_1[q21], - and([r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_2_Occurrence[q23, q24] -> - or([r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Flags - [q21, q26] - /\ - r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Values - [q21, q26] - = q24 - | q26 : int(1..2)]) - | q24 : int(2..3)]) - /\ - and([r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Flags[q21, q28] - -> - r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_2_Occurrence - [q23, - r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Values - [q21, q28]] - | q28 : int(1..2)]), - r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_3[q23] = - r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_3[q21]; - int(1..3)]) - | q23 : int(1..84)]) - | q21 : int(1..84)]), - and([q29 <= r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Marker -> - or([q31 <= r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Marker /\ - and([r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_1[q31] = - r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_1[q29], - and([r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Flags[q31, q33] - -> - r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_2_Occurrence - [q29, - r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Values - [q31, q33]] - | q33 : int(1..2)]) - /\ - and([r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_2_Occurrence[q29, q34] -> - or([r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Flags - [q31, q36] - /\ - r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Values - [q31, q36] - = q34 - | q36 : int(1..2)]) - | q34 : int(2..3)]), - r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_3[q31] = - r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_3[q29]; - int(1..3)]) - | q31 : int(1..84)]) - | q29 : int(1..84)]), - r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Marker = r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Marker - diff --git a/tests/exhaustive/basic/relation04_param/expected/model_2_1-param4-solution000001.solution b/tests/exhaustive/basic/relation04_param/expected/model_2_1-param4-solution000001.solution deleted file mode 100644 index 547e6d2e7e..0000000000 --- a/tests/exhaustive/basic/relation04_param/expected/model_2_1-param4-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting r be relation((3, {2}, 6), (3, {3}, 9)) diff --git a/tests/exhaustive/basic/relation04_param/expected/model_2_1-param4.eprime-param b/tests/exhaustive/basic/relation04_param/expected/model_2_1-param4.eprime-param deleted file mode 100644 index 87708d95a4..0000000000 --- a/tests/exhaustive/basic/relation04_param/expected/model_2_1-param4.eprime-param +++ /dev/null @@ -1,11 +0,0 @@ -language ESSENCE' 1.0 - -letting a_RelationAsSetR6_ExplicitR6_1 be [3, 3; int(1..2)] -letting a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy be [[2; int(1)], [3; int(1)]; int(1..2)] -$ Visualisation for a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy -$ 2 -$ 3 - -letting a_RelationAsSetR6_ExplicitR6_3 be [6, 9; int(1..2)] -letting fin1 be 2 -letting fin2 be 1 diff --git a/tests/exhaustive/basic/relation04_param/expected/model_2_1.eprime b/tests/exhaustive/basic/relation04_param/expected/model_2_1.eprime deleted file mode 100644 index ca4ced56b2..0000000000 --- a/tests/exhaustive/basic/relation04_param/expected/model_2_1.eprime +++ /dev/null @@ -1,164 +0,0 @@ -language ESSENCE' 1.0 - -given fin1: int -given fin2: int -given a_RelationAsSetR6_ExplicitR6_1: matrix indexed by [int(1..fin1)] of int(1..3) -given a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy: - matrix indexed by [int(1..fin1), int(1..fin2)] of int(2..4) -given a_RelationAsSetR6_ExplicitR6_3: matrix indexed by [int(1..fin1)] of int(4..10) -find r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Marker: int(0..84) -find r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_1: matrix indexed by [int(1..84)] of int(1..3) -find r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy: - matrix indexed by [int(1..84), int(1..2)] of int(2..4) -find r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_3: matrix indexed by [int(1..84)] of int(4..10) -find r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Marker: int(0..84) -find r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_1: matrix indexed by [int(1..84)] of int(1..3) -find r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_2_Occurrence: - matrix indexed by [int(1..84), int(2..3)] of bool -find r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_3: matrix indexed by [int(1..84)] of int(4..10) -branching on - [r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Marker, r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_1, - r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_2_Occurrence, - r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_3, r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Marker, - r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_1, - r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy, - r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_3] -such that - and([q36 <= r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Marker -> - or([and([a_RelationAsSetR6_ExplicitR6_1[q38] = r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_1[q36], - and([or([r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q36, q42] != - 4 - /\ - r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q36, q42] = - a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q38, q40] - | q42 : int(1..2)]) - | q40 : int(1..fin2), - a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q38, q40] != 4]) - /\ - and([r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q36, q44] != 4 -> - or([a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q38, q46] = - r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q36, q44] - | q46 : int(1..fin2), - a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q38, q46] != 4]) - | q44 : int(1..2)]), - a_RelationAsSetR6_ExplicitR6_3[q38] = r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_3[q36]; - int(1..3)]) - | q38 : int(1..fin1)]) - | q36 : int(1..84)]), - and([or([q49 <= r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Marker /\ - and([r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_1[q49] = a_RelationAsSetR6_ExplicitR6_1[q47], - and([r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q49, q51] != 4 -> - or([a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q47, q53] = - r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q49, q51] - | q53 : int(1..fin2), - a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q47, q53] != 4]) - | q51 : int(1..2)]) - /\ - and([or([r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q49, q57] != - 4 - /\ - r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q49, q57] = - a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q47, q55] - | q57 : int(1..2)]) - | q55 : int(1..fin2), - a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q47, q55] != 4]), - r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_3[q49] = a_RelationAsSetR6_ExplicitR6_3[q47]; - int(1..3)]) - | q49 : int(1..84)]) - | q47 : int(1..fin1)]), - r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Marker = fin1, - and([q1 + 1 <= r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Marker -> - flatten([[r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_1[q1]; int(1)], - [r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q1, q8] - | q8 : int(1..2)], - [r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_3[q1]; int(1)]; - int(1..3)]) - r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Marker -> - and([r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_1[q2] = 1, - and([r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q2, q10] = 2 - | q10 : int(1..2)]), - r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_3[q2] = 4; - int(1..3)]) - | q2 : int(1..84)]), - and([q3 <= r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Marker -> - r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q3, 1] < - r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q3, 2] - \/ r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q3, 1] = 4 - | q3 : int(1..84)]), - and([q3 <= r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Marker -> - (r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q3, 1] = 4 -> - r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q3, 2] = 4) - | q3 : int(1..84)]), - and([q11 + 1 <= r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Marker -> - flatten([[r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_1[q11]; int(1)], - [-toInt(r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_2_Occurrence[q11, q15]) - | q15 : int(2..3)], - [r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_3[q11]; int(1)]; - int(1..3)]) - r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Marker -> - and([r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_1[q12] = 1, - and([r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_2_Occurrence[q12, q17] = false - | q17 : int(2..3)]), - r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_3[q12] = 4; - int(1..3)]) - | q12 : int(1..84)]), - and([q19 <= r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Marker -> - or([q21 <= r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Marker /\ - and([r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_1[q21] = - r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_1[q19], - and([r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q21, q23] != 4 -> - r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_2_Occurrence - [q19, - r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q21, q23]] - | q23 : int(1..2)]) - /\ - and([r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_2_Occurrence[q19, q24] -> - or([r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q21, q26] != - 4 - /\ - r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q21, q26] = - q24 | q26 : int(1..2)]) - | q24 : int(2..3)]), - r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_3[q21] = - r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_3[q19]; - int(1..3)]) - | q21 : int(1..84)]) - | q19 : int(1..84)]), - and([q27 <= r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Marker -> - or([q29 <= r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Marker /\ - and([r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_1[q29] = - r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_1[q27], - and([r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_2_Occurrence[q29, q30] -> - or([r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q27, q32] != - 4 - /\ - r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q27, q32] = - q30 | q32 : int(1..2)]) - | q30 : int(2..3)]) - /\ - and([r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q27, q34] != 4 -> - r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_2_Occurrence - [q29, - r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q27, q34]] - | q34 : int(1..2)]), - r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_3[q29] = - r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_3[q27]; - int(1..3)]) - | q29 : int(1..84)]) - | q27 : int(1..84)]), - r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Marker = r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Marker - diff --git a/tests/exhaustive/basic/relation04_param/expected/model_2_2-param4-solution000001.solution b/tests/exhaustive/basic/relation04_param/expected/model_2_2-param4-solution000001.solution deleted file mode 100644 index 547e6d2e7e..0000000000 --- a/tests/exhaustive/basic/relation04_param/expected/model_2_2-param4-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting r be relation((3, {2}, 6), (3, {3}, 9)) diff --git a/tests/exhaustive/basic/relation04_param/expected/model_2_2-param4.eprime-param b/tests/exhaustive/basic/relation04_param/expected/model_2_2-param4.eprime-param deleted file mode 100644 index 87708d95a4..0000000000 --- a/tests/exhaustive/basic/relation04_param/expected/model_2_2-param4.eprime-param +++ /dev/null @@ -1,11 +0,0 @@ -language ESSENCE' 1.0 - -letting a_RelationAsSetR6_ExplicitR6_1 be [3, 3; int(1..2)] -letting a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy be [[2; int(1)], [3; int(1)]; int(1..2)] -$ Visualisation for a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy -$ 2 -$ 3 - -letting a_RelationAsSetR6_ExplicitR6_3 be [6, 9; int(1..2)] -letting fin1 be 2 -letting fin2 be 1 diff --git a/tests/exhaustive/basic/relation04_param/expected/model_2_2.eprime b/tests/exhaustive/basic/relation04_param/expected/model_2_2.eprime deleted file mode 100644 index bda11c6f36..0000000000 --- a/tests/exhaustive/basic/relation04_param/expected/model_2_2.eprime +++ /dev/null @@ -1,91 +0,0 @@ -language ESSENCE' 1.0 - -given fin1: int -given fin2: int -given a_RelationAsSetR6_ExplicitR6_1: matrix indexed by [int(1..fin1)] of int(1..3) -given a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy: - matrix indexed by [int(1..fin1), int(1..fin2)] of int(2..4) -given a_RelationAsSetR6_ExplicitR6_3: matrix indexed by [int(1..fin1)] of int(4..10) -find r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Marker: int(0..84) -find r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_1: matrix indexed by [int(1..84)] of int(1..3) -find r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy: - matrix indexed by [int(1..84), int(1..2)] of int(2..4) -find r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_3: matrix indexed by [int(1..84)] of int(4..10) -branching on - [r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Marker, r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_1, - r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy, - r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_3] -such that - and([q12 <= r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Marker -> - or([and([a_RelationAsSetR6_ExplicitR6_1[q14] = r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_1[q12], - and([or([r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q12, q18] != - 4 - /\ - r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q12, q18] = - a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q14, q16] - | q18 : int(1..2)]) - | q16 : int(1..fin2), - a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q14, q16] != 4]) - /\ - and([r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q12, q20] != 4 -> - or([a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q14, q22] = - r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q12, q20] - | q22 : int(1..fin2), - a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q14, q22] != 4]) - | q20 : int(1..2)]), - a_RelationAsSetR6_ExplicitR6_3[q14] = r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_3[q12]; - int(1..3)]) - | q14 : int(1..fin1)]) - | q12 : int(1..84)]), - and([or([q25 <= r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Marker /\ - and([r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_1[q25] = a_RelationAsSetR6_ExplicitR6_1[q23], - and([r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q25, q27] != 4 -> - or([a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q23, q29] = - r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q25, q27] - | q29 : int(1..fin2), - a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q23, q29] != 4]) - | q27 : int(1..2)]) - /\ - and([or([r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q25, q33] != - 4 - /\ - r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q25, q33] = - a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q23, q31] - | q33 : int(1..2)]) - | q31 : int(1..fin2), - a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q23, q31] != 4]), - r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_3[q25] = a_RelationAsSetR6_ExplicitR6_3[q23]; - int(1..3)]) - | q25 : int(1..84)]) - | q23 : int(1..fin1)]), - r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Marker = fin1, - and([q1 + 1 <= r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Marker -> - flatten([[r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_1[q1]; int(1)], - [r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q1, q8] - | q8 : int(1..2)], - [r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_3[q1]; int(1)]; - int(1..3)]) - r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Marker -> - and([r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_1[q2] = 1, - and([r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q2, q10] = 2 - | q10 : int(1..2)]), - r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_3[q2] = 4; - int(1..3)]) - | q2 : int(1..84)]), - and([q3 <= r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Marker -> - r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q3, 1] < - r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q3, 2] - \/ r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q3, 1] = 4 - | q3 : int(1..84)]), - and([q3 <= r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Marker -> - (r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q3, 1] = 4 -> - r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q3, 2] = 4) - | q3 : int(1..84)]) - diff --git a/tests/exhaustive/basic/relation04_param/expected/model_2_3-param4-solution000001.solution b/tests/exhaustive/basic/relation04_param/expected/model_2_3-param4-solution000001.solution deleted file mode 100644 index 547e6d2e7e..0000000000 --- a/tests/exhaustive/basic/relation04_param/expected/model_2_3-param4-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting r be relation((3, {2}, 6), (3, {3}, 9)) diff --git a/tests/exhaustive/basic/relation04_param/expected/model_2_3-param4.eprime-param b/tests/exhaustive/basic/relation04_param/expected/model_2_3-param4.eprime-param deleted file mode 100644 index 87708d95a4..0000000000 --- a/tests/exhaustive/basic/relation04_param/expected/model_2_3-param4.eprime-param +++ /dev/null @@ -1,11 +0,0 @@ -language ESSENCE' 1.0 - -letting a_RelationAsSetR6_ExplicitR6_1 be [3, 3; int(1..2)] -letting a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy be [[2; int(1)], [3; int(1)]; int(1..2)] -$ Visualisation for a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy -$ 2 -$ 3 - -letting a_RelationAsSetR6_ExplicitR6_3 be [6, 9; int(1..2)] -letting fin1 be 2 -letting fin2 be 1 diff --git a/tests/exhaustive/basic/relation04_param/expected/model_2_3.eprime b/tests/exhaustive/basic/relation04_param/expected/model_2_3.eprime deleted file mode 100644 index e7ed4344fa..0000000000 --- a/tests/exhaustive/basic/relation04_param/expected/model_2_3.eprime +++ /dev/null @@ -1,206 +0,0 @@ -language ESSENCE' 1.0 - -given fin1: int -given fin2: int -given a_RelationAsSetR6_ExplicitR6_1: matrix indexed by [int(1..fin1)] of int(1..3) -given a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy: - matrix indexed by [int(1..fin1), int(1..fin2)] of int(2..4) -given a_RelationAsSetR6_ExplicitR6_3: matrix indexed by [int(1..fin1)] of int(4..10) -find r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Marker: int(0..84) -find r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_1: matrix indexed by [int(1..84)] of int(1..3) -find r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy: - matrix indexed by [int(1..84), int(1..2)] of int(2..4) -find r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_3: matrix indexed by [int(1..84)] of int(4..10) -find r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Marker: int(0..84) -find r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_1: matrix indexed by [int(1..84)] of int(1..3) -find r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Marker: - matrix indexed by [int(1..84)] of int(0..2) -find r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Values: - matrix indexed by [int(1..84), int(1..2)] of int(2..3) -find r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_3: matrix indexed by [int(1..84)] of int(4..10) -branching on - [r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Marker, r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_1, - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Marker, - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Values, - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_3, r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Marker, - r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_1, - r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy, - r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_3] -such that - and([q44 <= r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Marker -> - or([and([a_RelationAsSetR6_ExplicitR6_1[q46] = r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_1[q44], - and([or([r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q44, q50] != - 4 - /\ - r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q44, q50] = - a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q46, q48] - | q50 : int(1..2)]) - | q48 : int(1..fin2), - a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q46, q48] != 4]) - /\ - and([r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q44, q52] != 4 -> - or([a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q46, q54] = - r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q44, q52] - | q54 : int(1..fin2), - a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q46, q54] != 4]) - | q52 : int(1..2)]), - a_RelationAsSetR6_ExplicitR6_3[q46] = r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_3[q44]; - int(1..3)]) - | q46 : int(1..fin1)]) - | q44 : int(1..84)]), - and([or([q57 <= r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Marker /\ - and([r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_1[q57] = a_RelationAsSetR6_ExplicitR6_1[q55], - and([r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q57, q59] != 4 -> - or([a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q55, q61] = - r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q57, q59] - | q61 : int(1..fin2), - a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q55, q61] != 4]) - | q59 : int(1..2)]) - /\ - and([or([r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q57, q65] != - 4 - /\ - r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q57, q65] = - a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q55, q63] - | q65 : int(1..2)]) - | q63 : int(1..fin2), - a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q55, q63] != 4]), - r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_3[q57] = a_RelationAsSetR6_ExplicitR6_3[q55]; - int(1..3)]) - | q57 : int(1..84)]) - | q55 : int(1..fin1)]), - r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Marker = fin1, - and([q1 + 1 <= r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Marker -> - flatten([[r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_1[q1]; int(1)], - [r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q1, q8] - | q8 : int(1..2)], - [r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_3[q1]; int(1)]; - int(1..3)]) - r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Marker -> - and([r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_1[q2] = 1, - and([r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q2, q10] = 2 - | q10 : int(1..2)]), - r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_3[q2] = 4; - int(1..3)]) - | q2 : int(1..84)]), - and([q3 <= r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Marker -> - r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q3, 1] < - r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q3, 2] - \/ r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q3, 1] = 4 - | q3 : int(1..84)]), - and([q3 <= r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Marker -> - (r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q3, 1] = 4 -> - r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q3, 2] = 4) - | q3 : int(1..84)]), - and([q11 + 1 <= r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Marker -> - flatten([[r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_1[q11]; int(1)], - flatten([[r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Marker - [q11]; - int(1)], - flatten([[r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Values - [q11, q17]; - int(1)] - | q17 : int(1..2)]); - int(1..2)]), - [r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_3[q11]; int(1)]; - int(1..3)]) - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Marker -> - and([r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_1[q12] = 1, - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Marker[q12] = 0 /\ - and([r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Values[q12, q19] = 2 - | q19 : int(1..2)]), - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_3[q12] = 4; - int(1..3)]) - | q12 : int(1..84)]), - and([q13 <= r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Marker -> - (2 <= r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Marker[q13] -> - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Values[q13, 1] < - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Values[q13, 2]) - | q13 : int(1..84)]), - and([q13 <= r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Marker -> - and([q15 > r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Marker[q13] -> - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Values[q13, q15] = 2 - | q15 : int(1..2)]) - | q13 : int(1..84)]), - and([q21 <= r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Marker -> - or([q23 <= r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Marker /\ - and([r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_1[q23] = - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_1[q21], - and([r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q23, q25] != 4 -> - or([q27 <= - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Marker[q21] - /\ - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Values - [q21, q27] - = r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q23, q25] - | q27 : int(1..2)]) - | q25 : int(1..2)]) - /\ - and([q29 <= - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Marker[q21] - -> - or([r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q23, q31] != - 4 - /\ - r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q23, q31] = - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Values - [q21, q29] - | q31 : int(1..2)]) - | q29 : int(1..2)]), - r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_3[q23] = - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_3[q21]; - int(1..3)]) - | q23 : int(1..84)]) - | q21 : int(1..84)]), - and([q32 <= r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Marker -> - or([q34 <= r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Marker /\ - and([r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_1[q34] = - r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_1[q32], - and([q36 <= - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Marker[q34] - -> - or([r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q32, q38] != - 4 - /\ - r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q32, q38] = - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Values - [q34, q36] - | q38 : int(1..2)]) - | q36 : int(1..2)]) - /\ - and([r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q32, q40] != 4 -> - or([q42 <= - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Marker[q34] - /\ - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Values - [q34, q42] - = r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q32, q40] - | q42 : int(1..2)]) - | q40 : int(1..2)]), - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_3[q34] = - r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_3[q32]; - int(1..3)]) - | q34 : int(1..84)]) - | q32 : int(1..84)]), - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Marker = r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Marker - diff --git a/tests/exhaustive/basic/relation04_param/expected/model_2_4-param4-solution000001.solution b/tests/exhaustive/basic/relation04_param/expected/model_2_4-param4-solution000001.solution deleted file mode 100644 index 547e6d2e7e..0000000000 --- a/tests/exhaustive/basic/relation04_param/expected/model_2_4-param4-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting r be relation((3, {2}, 6), (3, {3}, 9)) diff --git a/tests/exhaustive/basic/relation04_param/expected/model_2_4-param4.eprime-param b/tests/exhaustive/basic/relation04_param/expected/model_2_4-param4.eprime-param deleted file mode 100644 index 87708d95a4..0000000000 --- a/tests/exhaustive/basic/relation04_param/expected/model_2_4-param4.eprime-param +++ /dev/null @@ -1,11 +0,0 @@ -language ESSENCE' 1.0 - -letting a_RelationAsSetR6_ExplicitR6_1 be [3, 3; int(1..2)] -letting a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy be [[2; int(1)], [3; int(1)]; int(1..2)] -$ Visualisation for a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy -$ 2 -$ 3 - -letting a_RelationAsSetR6_ExplicitR6_3 be [6, 9; int(1..2)] -letting fin1 be 2 -letting fin2 be 1 diff --git a/tests/exhaustive/basic/relation04_param/expected/model_2_4.eprime b/tests/exhaustive/basic/relation04_param/expected/model_2_4.eprime deleted file mode 100644 index 9f13f2adc7..0000000000 --- a/tests/exhaustive/basic/relation04_param/expected/model_2_4.eprime +++ /dev/null @@ -1,211 +0,0 @@ -language ESSENCE' 1.0 - -given fin1: int -given fin2: int -given a_RelationAsSetR6_ExplicitR6_1: matrix indexed by [int(1..fin1)] of int(1..3) -given a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy: - matrix indexed by [int(1..fin1), int(1..fin2)] of int(2..4) -given a_RelationAsSetR6_ExplicitR6_3: matrix indexed by [int(1..fin1)] of int(4..10) -find r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Marker: int(0..84) -find r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_1: matrix indexed by [int(1..84)] of int(1..3) -find r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy: - matrix indexed by [int(1..84), int(1..2)] of int(2..4) -find r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_3: matrix indexed by [int(1..84)] of int(4..10) -find r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Marker: int(0..84) -find r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_1: matrix indexed by [int(1..84)] of int(1..3) -find r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Flags: - matrix indexed by [int(1..84), int(1..2)] of bool -find r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Values: - matrix indexed by [int(1..84), int(1..2)] of int(2..3) -find r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_3: matrix indexed by [int(1..84)] of int(4..10) -branching on - [r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Marker, r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_1, - r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Flags, - r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Values, - r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_3, r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Marker, - r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_1, - r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy, - r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_3] -such that - and([q47 <= r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Marker -> - or([and([a_RelationAsSetR6_ExplicitR6_1[q49] = r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_1[q47], - and([or([r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q47, q53] != - 4 - /\ - r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q47, q53] = - a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q49, q51] - | q53 : int(1..2)]) - | q51 : int(1..fin2), - a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q49, q51] != 4]) - /\ - and([r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q47, q55] != 4 -> - or([a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q49, q57] = - r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q47, q55] - | q57 : int(1..fin2), - a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q49, q57] != 4]) - | q55 : int(1..2)]), - a_RelationAsSetR6_ExplicitR6_3[q49] = r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_3[q47]; - int(1..3)]) - | q49 : int(1..fin1)]) - | q47 : int(1..84)]), - and([or([q60 <= r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Marker /\ - and([r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_1[q60] = a_RelationAsSetR6_ExplicitR6_1[q58], - and([r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q60, q62] != 4 -> - or([a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q58, q64] = - r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q60, q62] - | q64 : int(1..fin2), - a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q58, q64] != 4]) - | q62 : int(1..2)]) - /\ - and([or([r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q60, q68] != - 4 - /\ - r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q60, q68] = - a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q58, q66] - | q68 : int(1..2)]) - | q66 : int(1..fin2), - a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q58, q66] != 4]), - r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_3[q60] = a_RelationAsSetR6_ExplicitR6_3[q58]; - int(1..3)]) - | q60 : int(1..84)]) - | q58 : int(1..fin1)]), - r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Marker = fin1, - and([q1 + 1 <= r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Marker -> - flatten([[r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_1[q1]; int(1)], - [r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q1, q8] - | q8 : int(1..2)], - [r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_3[q1]; int(1)]; - int(1..3)]) - r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Marker -> - and([r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_1[q2] = 1, - and([r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q2, q10] = 2 - | q10 : int(1..2)]), - r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_3[q2] = 4; - int(1..3)]) - | q2 : int(1..84)]), - and([q3 <= r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Marker -> - r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q3, 1] < - r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q3, 2] - \/ r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q3, 1] = 4 - | q3 : int(1..84)]), - and([q3 <= r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Marker -> - (r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q3, 1] = 4 -> - r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q3, 2] = 4) - | q3 : int(1..84)]), - and([q11 + 1 <= r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Marker -> - flatten([[r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_1[q11]; int(1)], - flatten([flatten([[-toInt(r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Flags - [q11, q19]); - int(1)], - [r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Values - [q11, q19]; - int(1)]; - int(1..2)]) - | q19 : int(1..2)]), - [r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_3[q11]; int(1)]; - int(1..3)]) - r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Marker -> - and([r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_1[q12] = 1, - and([r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Flags[q12, q21] = - false - | q21 : int(1..2)]) - /\ - and([r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Values[q12, q22] = 2 - | q22 : int(1..2)]), - r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_3[q12] = 4; - int(1..3)]) - | q12 : int(1..84)]), - and([q13 <= r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Marker -> - (r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Flags[q13, 2] -> - r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Values[q13, 1] < - r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Values[q13, 2]) - | q13 : int(1..84)]), - and([q13 <= r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Marker -> - and([r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Flags[q13, q15] = false -> - r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Values[q13, q15] = 2 - | q15 : int(1..2)]) - | q13 : int(1..84)]), - and([q13 <= r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Marker -> - (r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Flags[q13, 2] -> - r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Flags[q13, 1]) - | q13 : int(1..84)]), - and([q24 <= r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Marker -> - or([q26 <= r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Marker /\ - and([r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_1[q26] = - r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_1[q24], - and([r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q26, q28] != 4 -> - or([r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Flags - [q24, q30] - /\ - r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Values - [q24, q30] - = r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q26, q28] - | q30 : int(1..2)]) - | q28 : int(1..2)]) - /\ - and([r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Flags[q24, q32] - -> - or([r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q26, q34] != - 4 - /\ - r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q26, q34] = - r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Values - [q24, q32] - | q34 : int(1..2)]) - | q32 : int(1..2)]), - r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_3[q26] = - r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_3[q24]; - int(1..3)]) - | q26 : int(1..84)]) - | q24 : int(1..84)]), - and([q35 <= r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Marker -> - or([q37 <= r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Marker /\ - and([r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_1[q37] = - r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_1[q35], - and([r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Flags[q37, q39] - -> - or([r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q35, q41] != - 4 - /\ - r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q35, q41] = - r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Values - [q37, q39] - | q41 : int(1..2)]) - | q39 : int(1..2)]) - /\ - and([r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q35, q43] != 4 -> - or([r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Flags - [q37, q45] - /\ - r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Values - [q37, q45] - = r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q35, q43] - | q45 : int(1..2)]) - | q43 : int(1..2)]), - r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_3[q37] = - r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_3[q35]; - int(1..3)]) - | q37 : int(1..84)]) - | q35 : int(1..84)]), - r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Marker = r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Marker - diff --git a/tests/exhaustive/basic/relation04_param/expected/model_3_1-param4-solution000001.solution b/tests/exhaustive/basic/relation04_param/expected/model_3_1-param4-solution000001.solution deleted file mode 100644 index 547e6d2e7e..0000000000 --- a/tests/exhaustive/basic/relation04_param/expected/model_3_1-param4-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting r be relation((3, {2}, 6), (3, {3}, 9)) diff --git a/tests/exhaustive/basic/relation04_param/expected/model_3_1-param4.eprime-param b/tests/exhaustive/basic/relation04_param/expected/model_3_1-param4.eprime-param deleted file mode 100644 index 87708d95a4..0000000000 --- a/tests/exhaustive/basic/relation04_param/expected/model_3_1-param4.eprime-param +++ /dev/null @@ -1,11 +0,0 @@ -language ESSENCE' 1.0 - -letting a_RelationAsSetR6_ExplicitR6_1 be [3, 3; int(1..2)] -letting a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy be [[2; int(1)], [3; int(1)]; int(1..2)] -$ Visualisation for a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy -$ 2 -$ 3 - -letting a_RelationAsSetR6_ExplicitR6_3 be [6, 9; int(1..2)] -letting fin1 be 2 -letting fin2 be 1 diff --git a/tests/exhaustive/basic/relation04_param/expected/model_3_1.eprime b/tests/exhaustive/basic/relation04_param/expected/model_3_1.eprime deleted file mode 100644 index d16486b7e5..0000000000 --- a/tests/exhaustive/basic/relation04_param/expected/model_3_1.eprime +++ /dev/null @@ -1,198 +0,0 @@ -language ESSENCE' 1.0 - -given fin1: int -given fin2: int -given a_RelationAsSetR6_ExplicitR6_1: matrix indexed by [int(1..fin1)] of int(1..3) -given a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy: - matrix indexed by [int(1..fin1), int(1..fin2)] of int(2..4) -given a_RelationAsSetR6_ExplicitR6_3: matrix indexed by [int(1..fin1)] of int(4..10) -find r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Marker: int(0..84) -find r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_1: matrix indexed by [int(1..84)] of int(1..3) -find r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Marker: - matrix indexed by [int(1..84)] of int(0..2) -find r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Values: - matrix indexed by [int(1..84), int(1..2)] of int(2..3) -find r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_3: matrix indexed by [int(1..84)] of int(4..10) -find r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Marker: int(0..84) -find r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_1: matrix indexed by [int(1..84)] of int(1..3) -find r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_2_Occurrence: - matrix indexed by [int(1..84), int(2..3)] of bool -find r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_3: matrix indexed by [int(1..84)] of int(4..10) -branching on - [r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Marker, r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_1, - r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_2_Occurrence, - r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_3, r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Marker, - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_1, - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Marker, - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Values, - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_3] -such that - and([q35 <= r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Marker -> - or([and([a_RelationAsSetR6_ExplicitR6_1[q37] = r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_1[q35], - and([or([q41 <= - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Marker[q35] - /\ - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Values - [q35, q41] - = a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q37, q39] - | q41 : int(1..2)]) - | q39 : int(1..fin2), - a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q37, q39] != 4]) - /\ - and([q43 <= - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Marker[q35] - -> - or([a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q37, q45] = - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Values - [q35, q43] - | q45 : int(1..fin2), - a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q37, q45] != 4]) - | q43 : int(1..2)]), - a_RelationAsSetR6_ExplicitR6_3[q37] = r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_3[q35]; - int(1..3)]) - | q37 : int(1..fin1)]) - | q35 : int(1..84)]), - and([or([q48 <= r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Marker /\ - and([r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_1[q48] = a_RelationAsSetR6_ExplicitR6_1[q46], - and([q50 <= - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Marker[q48] - -> - or([a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q46, q52] = - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Values - [q48, q50] - | q52 : int(1..fin2), - a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q46, q52] != 4]) - | q50 : int(1..2)]) - /\ - and([or([q56 <= - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Marker[q48] - /\ - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Values - [q48, q56] - = a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q46, q54] - | q56 : int(1..2)]) - | q54 : int(1..fin2), - a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q46, q54] != 4]), - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_3[q48] = a_RelationAsSetR6_ExplicitR6_3[q46]; - int(1..3)]) - | q48 : int(1..84)]) - | q46 : int(1..fin1)]), - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Marker = fin1, - and([q1 + 1 <= r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Marker -> - flatten([[r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_1[q1]; int(1)], - flatten([[r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Marker[q1]; - int(1)], - flatten([[r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Values - [q1, q7]; - int(1)] - | q7 : int(1..2)]); - int(1..2)]), - [r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_3[q1]; int(1)]; - int(1..3)]) - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Marker -> - and([r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_1[q2] = 1, - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Marker[q2] = 0 /\ - and([r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Values[q2, q9] = 2 - | q9 : int(1..2)]), - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_3[q2] = 4; - int(1..3)]) - | q2 : int(1..84)]), - and([q3 <= r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Marker -> - (2 <= r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Marker[q3] -> - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Values[q3, 1] < - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Values[q3, 2]) - | q3 : int(1..84)]), - and([q3 <= r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Marker -> - and([q5 > r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Marker[q3] -> - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Values[q3, q5] = 2 - | q5 : int(1..2)]) - | q3 : int(1..84)]), - and([q10 + 1 <= r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Marker -> - flatten([[r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_1[q10]; int(1)], - [-toInt(r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_2_Occurrence[q10, q14]) - | q14 : int(2..3)], - [r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_3[q10]; int(1)]; - int(1..3)]) - r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Marker -> - and([r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_1[q11] = 1, - and([r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_2_Occurrence[q11, q16] = false - | q16 : int(2..3)]), - r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_3[q11] = 4; - int(1..3)]) - | q11 : int(1..84)]), - and([q18 <= r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Marker -> - or([q20 <= r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Marker /\ - and([r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_1[q20] = - r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_1[q18], - and([q22 <= - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Marker[q20] - -> - r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_2_Occurrence - [q18, - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Values - [q20, q22]] - | q22 : int(1..2)]) - /\ - and([r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_2_Occurrence[q18, q23] -> - or([q25 <= - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Marker[q20] - /\ - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Values - [q20, q25] - = q23 - | q25 : int(1..2)]) - | q23 : int(2..3)]), - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_3[q20] = - r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_3[q18]; - int(1..3)]) - | q20 : int(1..84)]) - | q18 : int(1..84)]), - and([q26 <= r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Marker -> - or([q28 <= r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Marker /\ - and([r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_1[q28] = - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_1[q26], - and([r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_2_Occurrence[q28, q29] -> - or([q31 <= - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Marker[q26] - /\ - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Values - [q26, q31] - = q29 - | q31 : int(1..2)]) - | q29 : int(2..3)]) - /\ - and([q33 <= - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Marker[q26] - -> - r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_2_Occurrence - [q28, - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Values - [q26, q33]] - | q33 : int(1..2)]), - r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_3[q28] = - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_3[q26]; - int(1..3)]) - | q28 : int(1..84)]) - | q26 : int(1..84)]), - r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Marker = r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Marker - diff --git a/tests/exhaustive/basic/relation04_param/expected/model_3_2-param4-solution000001.solution b/tests/exhaustive/basic/relation04_param/expected/model_3_2-param4-solution000001.solution deleted file mode 100644 index 547e6d2e7e..0000000000 --- a/tests/exhaustive/basic/relation04_param/expected/model_3_2-param4-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting r be relation((3, {2}, 6), (3, {3}, 9)) diff --git a/tests/exhaustive/basic/relation04_param/expected/model_3_2-param4.eprime-param b/tests/exhaustive/basic/relation04_param/expected/model_3_2-param4.eprime-param deleted file mode 100644 index 87708d95a4..0000000000 --- a/tests/exhaustive/basic/relation04_param/expected/model_3_2-param4.eprime-param +++ /dev/null @@ -1,11 +0,0 @@ -language ESSENCE' 1.0 - -letting a_RelationAsSetR6_ExplicitR6_1 be [3, 3; int(1..2)] -letting a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy be [[2; int(1)], [3; int(1)]; int(1..2)] -$ Visualisation for a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy -$ 2 -$ 3 - -letting a_RelationAsSetR6_ExplicitR6_3 be [6, 9; int(1..2)] -letting fin1 be 2 -letting fin2 be 1 diff --git a/tests/exhaustive/basic/relation04_param/expected/model_3_2.eprime b/tests/exhaustive/basic/relation04_param/expected/model_3_2.eprime deleted file mode 100644 index 8e5b91eaac..0000000000 --- a/tests/exhaustive/basic/relation04_param/expected/model_3_2.eprime +++ /dev/null @@ -1,213 +0,0 @@ -language ESSENCE' 1.0 - -given fin1: int -given fin2: int -given a_RelationAsSetR6_ExplicitR6_1: matrix indexed by [int(1..fin1)] of int(1..3) -given a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy: - matrix indexed by [int(1..fin1), int(1..fin2)] of int(2..4) -given a_RelationAsSetR6_ExplicitR6_3: matrix indexed by [int(1..fin1)] of int(4..10) -find r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Marker: int(0..84) -find r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_1: matrix indexed by [int(1..84)] of int(1..3) -find r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Marker: - matrix indexed by [int(1..84)] of int(0..2) -find r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Values: - matrix indexed by [int(1..84), int(1..2)] of int(2..3) -find r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_3: matrix indexed by [int(1..84)] of int(4..10) -find r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Marker: int(0..84) -find r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_1: matrix indexed by [int(1..84)] of int(1..3) -find r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy: - matrix indexed by [int(1..84), int(1..2)] of int(2..4) -find r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_3: matrix indexed by [int(1..84)] of int(4..10) -branching on - [r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Marker, r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_1, - r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy, - r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_3, r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Marker, - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_1, - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Marker, - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Values, - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_3] -such that - and([q44 <= r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Marker -> - or([and([a_RelationAsSetR6_ExplicitR6_1[q46] = r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_1[q44], - and([or([q50 <= - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Marker[q44] - /\ - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Values - [q44, q50] - = a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q46, q48] - | q50 : int(1..2)]) - | q48 : int(1..fin2), - a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q46, q48] != 4]) - /\ - and([q52 <= - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Marker[q44] - -> - or([a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q46, q54] = - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Values - [q44, q52] - | q54 : int(1..fin2), - a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q46, q54] != 4]) - | q52 : int(1..2)]), - a_RelationAsSetR6_ExplicitR6_3[q46] = r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_3[q44]; - int(1..3)]) - | q46 : int(1..fin1)]) - | q44 : int(1..84)]), - and([or([q57 <= r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Marker /\ - and([r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_1[q57] = a_RelationAsSetR6_ExplicitR6_1[q55], - and([q59 <= - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Marker[q57] - -> - or([a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q55, q61] = - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Values - [q57, q59] - | q61 : int(1..fin2), - a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q55, q61] != 4]) - | q59 : int(1..2)]) - /\ - and([or([q65 <= - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Marker[q57] - /\ - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Values - [q57, q65] - = a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q55, q63] - | q65 : int(1..2)]) - | q63 : int(1..fin2), - a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q55, q63] != 4]), - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_3[q57] = a_RelationAsSetR6_ExplicitR6_3[q55]; - int(1..3)]) - | q57 : int(1..84)]) - | q55 : int(1..fin1)]), - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Marker = fin1, - and([q1 + 1 <= r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Marker -> - flatten([[r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_1[q1]; int(1)], - flatten([[r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Marker[q1]; - int(1)], - flatten([[r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Values - [q1, q7]; - int(1)] - | q7 : int(1..2)]); - int(1..2)]), - [r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_3[q1]; int(1)]; - int(1..3)]) - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Marker -> - and([r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_1[q2] = 1, - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Marker[q2] = 0 /\ - and([r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Values[q2, q9] = 2 - | q9 : int(1..2)]), - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_3[q2] = 4; - int(1..3)]) - | q2 : int(1..84)]), - and([q3 <= r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Marker -> - (2 <= r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Marker[q3] -> - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Values[q3, 1] < - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Values[q3, 2]) - | q3 : int(1..84)]), - and([q3 <= r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Marker -> - and([q5 > r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Marker[q3] -> - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Values[q3, q5] = 2 - | q5 : int(1..2)]) - | q3 : int(1..84)]), - and([q10 + 1 <= r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Marker -> - flatten([[r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_1[q10]; int(1)], - [r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q10, q17] - | q17 : int(1..2)], - [r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_3[q10]; int(1)]; - int(1..3)]) - r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Marker -> - and([r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_1[q11] = 1, - and([r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q11, q19] = 2 - | q19 : int(1..2)]), - r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_3[q11] = 4; - int(1..3)]) - | q11 : int(1..84)]), - and([q12 <= r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Marker -> - r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q12, 1] < - r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q12, 2] - \/ r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q12, 1] = 4 - | q12 : int(1..84)]), - and([q12 <= r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Marker -> - (r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q12, 1] = 4 -> - r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q12, 2] = 4) - | q12 : int(1..84)]), - and([q21 <= r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Marker -> - or([q23 <= r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Marker /\ - and([r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_1[q23] = - r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_1[q21], - and([q25 <= - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Marker[q23] - -> - or([r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q21, q27] != - 4 - /\ - r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q21, q27] = - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Values - [q23, q25] - | q27 : int(1..2)]) - | q25 : int(1..2)]) - /\ - and([r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q21, q29] != 4 -> - or([q31 <= - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Marker[q23] - /\ - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Values - [q23, q31] - = r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q21, q29] - | q31 : int(1..2)]) - | q29 : int(1..2)]), - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_3[q23] = - r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_3[q21]; - int(1..3)]) - | q23 : int(1..84)]) - | q21 : int(1..84)]), - and([q32 <= r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Marker -> - or([q34 <= r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Marker /\ - and([r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_1[q34] = - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_1[q32], - and([r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q34, q36] != 4 -> - or([q38 <= - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Marker[q32] - /\ - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Values - [q32, q38] - = r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q34, q36] - | q38 : int(1..2)]) - | q36 : int(1..2)]) - /\ - and([q40 <= - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Marker[q32] - -> - or([r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q34, q42] != - 4 - /\ - r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q34, q42] = - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Values - [q32, q40] - | q42 : int(1..2)]) - | q40 : int(1..2)]), - r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_3[q34] = - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_3[q32]; - int(1..3)]) - | q34 : int(1..84)]) - | q32 : int(1..84)]), - r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Marker = r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Marker - diff --git a/tests/exhaustive/basic/relation04_param/expected/model_3_3-param4-solution000001.solution b/tests/exhaustive/basic/relation04_param/expected/model_3_3-param4-solution000001.solution deleted file mode 100644 index 547e6d2e7e..0000000000 --- a/tests/exhaustive/basic/relation04_param/expected/model_3_3-param4-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting r be relation((3, {2}, 6), (3, {3}, 9)) diff --git a/tests/exhaustive/basic/relation04_param/expected/model_3_3-param4.eprime-param b/tests/exhaustive/basic/relation04_param/expected/model_3_3-param4.eprime-param deleted file mode 100644 index 87708d95a4..0000000000 --- a/tests/exhaustive/basic/relation04_param/expected/model_3_3-param4.eprime-param +++ /dev/null @@ -1,11 +0,0 @@ -language ESSENCE' 1.0 - -letting a_RelationAsSetR6_ExplicitR6_1 be [3, 3; int(1..2)] -letting a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy be [[2; int(1)], [3; int(1)]; int(1..2)] -$ Visualisation for a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy -$ 2 -$ 3 - -letting a_RelationAsSetR6_ExplicitR6_3 be [6, 9; int(1..2)] -letting fin1 be 2 -letting fin2 be 1 diff --git a/tests/exhaustive/basic/relation04_param/expected/model_3_3.eprime b/tests/exhaustive/basic/relation04_param/expected/model_3_3.eprime deleted file mode 100644 index 8d25b34922..0000000000 --- a/tests/exhaustive/basic/relation04_param/expected/model_3_3.eprime +++ /dev/null @@ -1,115 +0,0 @@ -language ESSENCE' 1.0 - -given fin1: int -given fin2: int -given a_RelationAsSetR6_ExplicitR6_1: matrix indexed by [int(1..fin1)] of int(1..3) -given a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy: - matrix indexed by [int(1..fin1), int(1..fin2)] of int(2..4) -given a_RelationAsSetR6_ExplicitR6_3: matrix indexed by [int(1..fin1)] of int(4..10) -find r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Marker: int(0..84) -find r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_1: matrix indexed by [int(1..84)] of int(1..3) -find r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Marker: - matrix indexed by [int(1..84)] of int(0..2) -find r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Values: - matrix indexed by [int(1..84), int(1..2)] of int(2..3) -find r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_3: matrix indexed by [int(1..84)] of int(4..10) -branching on - [r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Marker, r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_1, - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Marker, - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Values, - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_3] -such that - and([q11 <= r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Marker -> - or([and([a_RelationAsSetR6_ExplicitR6_1[q13] = r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_1[q11], - and([or([q17 <= - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Marker[q11] - /\ - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Values - [q11, q17] - = a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q13, q15] - | q17 : int(1..2)]) - | q15 : int(1..fin2), - a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q13, q15] != 4]) - /\ - and([q19 <= - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Marker[q11] - -> - or([a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q13, q21] = - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Values - [q11, q19] - | q21 : int(1..fin2), - a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q13, q21] != 4]) - | q19 : int(1..2)]), - a_RelationAsSetR6_ExplicitR6_3[q13] = r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_3[q11]; - int(1..3)]) - | q13 : int(1..fin1)]) - | q11 : int(1..84)]), - and([or([q24 <= r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Marker /\ - and([r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_1[q24] = a_RelationAsSetR6_ExplicitR6_1[q22], - and([q26 <= - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Marker[q24] - -> - or([a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q22, q28] = - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Values - [q24, q26] - | q28 : int(1..fin2), - a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q22, q28] != 4]) - | q26 : int(1..2)]) - /\ - and([or([q32 <= - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Marker[q24] - /\ - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Values - [q24, q32] - = a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q22, q30] - | q32 : int(1..2)]) - | q30 : int(1..fin2), - a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q22, q30] != 4]), - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_3[q24] = a_RelationAsSetR6_ExplicitR6_3[q22]; - int(1..3)]) - | q24 : int(1..84)]) - | q22 : int(1..fin1)]), - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Marker = fin1, - and([q1 + 1 <= r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Marker -> - flatten([[r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_1[q1]; int(1)], - flatten([[r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Marker[q1]; - int(1)], - flatten([[r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Values - [q1, q7]; - int(1)] - | q7 : int(1..2)]); - int(1..2)]), - [r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_3[q1]; int(1)]; - int(1..3)]) - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Marker -> - and([r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_1[q2] = 1, - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Marker[q2] = 0 /\ - and([r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Values[q2, q9] = 2 - | q9 : int(1..2)]), - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_3[q2] = 4; - int(1..3)]) - | q2 : int(1..84)]), - and([q3 <= r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Marker -> - (2 <= r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Marker[q3] -> - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Values[q3, 1] < - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Values[q3, 2]) - | q3 : int(1..84)]), - and([q3 <= r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Marker -> - and([q5 > r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Marker[q3] -> - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Values[q3, q5] = 2 - | q5 : int(1..2)]) - | q3 : int(1..84)]) - diff --git a/tests/exhaustive/basic/relation04_param/expected/model_3_4-param4-solution000001.solution b/tests/exhaustive/basic/relation04_param/expected/model_3_4-param4-solution000001.solution deleted file mode 100644 index 547e6d2e7e..0000000000 --- a/tests/exhaustive/basic/relation04_param/expected/model_3_4-param4-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting r be relation((3, {2}, 6), (3, {3}, 9)) diff --git a/tests/exhaustive/basic/relation04_param/expected/model_3_4-param4.eprime-param b/tests/exhaustive/basic/relation04_param/expected/model_3_4-param4.eprime-param deleted file mode 100644 index 87708d95a4..0000000000 --- a/tests/exhaustive/basic/relation04_param/expected/model_3_4-param4.eprime-param +++ /dev/null @@ -1,11 +0,0 @@ -language ESSENCE' 1.0 - -letting a_RelationAsSetR6_ExplicitR6_1 be [3, 3; int(1..2)] -letting a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy be [[2; int(1)], [3; int(1)]; int(1..2)] -$ Visualisation for a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy -$ 2 -$ 3 - -letting a_RelationAsSetR6_ExplicitR6_3 be [6, 9; int(1..2)] -letting fin1 be 2 -letting fin2 be 1 diff --git a/tests/exhaustive/basic/relation04_param/expected/model_3_4.eprime b/tests/exhaustive/basic/relation04_param/expected/model_3_4.eprime deleted file mode 100644 index c8579b9ea9..0000000000 --- a/tests/exhaustive/basic/relation04_param/expected/model_3_4.eprime +++ /dev/null @@ -1,247 +0,0 @@ -language ESSENCE' 1.0 - -given fin1: int -given fin2: int -given a_RelationAsSetR6_ExplicitR6_1: matrix indexed by [int(1..fin1)] of int(1..3) -given a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy: - matrix indexed by [int(1..fin1), int(1..fin2)] of int(2..4) -given a_RelationAsSetR6_ExplicitR6_3: matrix indexed by [int(1..fin1)] of int(4..10) -find r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Marker: int(0..84) -find r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_1: matrix indexed by [int(1..84)] of int(1..3) -find r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Marker: - matrix indexed by [int(1..84)] of int(0..2) -find r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Values: - matrix indexed by [int(1..84), int(1..2)] of int(2..3) -find r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_3: matrix indexed by [int(1..84)] of int(4..10) -find r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Marker: int(0..84) -find r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_1: matrix indexed by [int(1..84)] of int(1..3) -find r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Flags: - matrix indexed by [int(1..84), int(1..2)] of bool -find r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Values: - matrix indexed by [int(1..84), int(1..2)] of int(2..3) -find r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_3: matrix indexed by [int(1..84)] of int(4..10) -branching on - [r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Marker, r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_1, - r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Flags, - r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Values, - r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_3, r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Marker, - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_1, - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Marker, - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Values, - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_3] -such that - and([q46 <= r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Marker -> - or([and([a_RelationAsSetR6_ExplicitR6_1[q48] = r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_1[q46], - and([or([q52 <= - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Marker[q46] - /\ - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Values - [q46, q52] - = a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q48, q50] - | q52 : int(1..2)]) - | q50 : int(1..fin2), - a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q48, q50] != 4]) - /\ - and([q54 <= - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Marker[q46] - -> - or([a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q48, q56] = - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Values - [q46, q54] - | q56 : int(1..fin2), - a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q48, q56] != 4]) - | q54 : int(1..2)]), - a_RelationAsSetR6_ExplicitR6_3[q48] = r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_3[q46]; - int(1..3)]) - | q48 : int(1..fin1)]) - | q46 : int(1..84)]), - and([or([q59 <= r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Marker /\ - and([r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_1[q59] = a_RelationAsSetR6_ExplicitR6_1[q57], - and([q61 <= - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Marker[q59] - -> - or([a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q57, q63] = - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Values - [q59, q61] - | q63 : int(1..fin2), - a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q57, q63] != 4]) - | q61 : int(1..2)]) - /\ - and([or([q67 <= - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Marker[q59] - /\ - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Values - [q59, q67] - = a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q57, q65] - | q67 : int(1..2)]) - | q65 : int(1..fin2), - a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q57, q65] != 4]), - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_3[q59] = a_RelationAsSetR6_ExplicitR6_3[q57]; - int(1..3)]) - | q59 : int(1..84)]) - | q57 : int(1..fin1)]), - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Marker = fin1, - and([q1 + 1 <= r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Marker -> - flatten([[r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_1[q1]; int(1)], - flatten([[r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Marker[q1]; - int(1)], - flatten([[r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Values - [q1, q7]; - int(1)] - | q7 : int(1..2)]); - int(1..2)]), - [r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_3[q1]; int(1)]; - int(1..3)]) - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Marker -> - and([r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_1[q2] = 1, - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Marker[q2] = 0 /\ - and([r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Values[q2, q9] = 2 - | q9 : int(1..2)]), - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_3[q2] = 4; - int(1..3)]) - | q2 : int(1..84)]), - and([q3 <= r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Marker -> - (2 <= r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Marker[q3] -> - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Values[q3, 1] < - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Values[q3, 2]) - | q3 : int(1..84)]), - and([q3 <= r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Marker -> - and([q5 > r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Marker[q3] -> - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Values[q3, q5] = 2 - | q5 : int(1..2)]) - | q3 : int(1..84)]), - and([q10 + 1 <= r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Marker -> - flatten([[r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_1[q10]; int(1)], - flatten([flatten([[-toInt(r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Flags - [q10, q18]); - int(1)], - [r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Values - [q10, q18]; - int(1)]; - int(1..2)]) - | q18 : int(1..2)]), - [r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_3[q10]; int(1)]; - int(1..3)]) - r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Marker -> - and([r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_1[q11] = 1, - and([r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Flags[q11, q20] = - false - | q20 : int(1..2)]) - /\ - and([r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Values[q11, q21] = 2 - | q21 : int(1..2)]), - r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_3[q11] = 4; - int(1..3)]) - | q11 : int(1..84)]), - and([q12 <= r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Marker -> - (r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Flags[q12, 2] -> - r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Values[q12, 1] < - r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Values[q12, 2]) - | q12 : int(1..84)]), - and([q12 <= r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Marker -> - and([r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Flags[q12, q14] = false -> - r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Values[q12, q14] = 2 - | q14 : int(1..2)]) - | q12 : int(1..84)]), - and([q12 <= r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Marker -> - (r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Flags[q12, 2] -> - r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Flags[q12, 1]) - | q12 : int(1..84)]), - and([q23 <= r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Marker -> - or([q25 <= r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Marker /\ - and([r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_1[q25] = - r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_1[q23], - and([q27 <= - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Marker[q25] - -> - or([r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Flags - [q23, q29] - /\ - r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Values - [q23, q29] - = - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Values - [q25, q27] - | q29 : int(1..2)]) - | q27 : int(1..2)]) - /\ - and([r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Flags[q23, q31] - -> - or([q33 <= - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Marker[q25] - /\ - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Values - [q25, q33] - = - r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Values - [q23, q31] - | q33 : int(1..2)]) - | q31 : int(1..2)]), - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_3[q25] = - r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_3[q23]; - int(1..3)]) - | q25 : int(1..84)]) - | q23 : int(1..84)]), - and([q34 <= r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Marker -> - or([q36 <= r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Marker /\ - and([r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_1[q36] = - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_1[q34], - and([r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Flags[q36, q38] - -> - or([q40 <= - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Marker[q34] - /\ - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Values - [q34, q40] - = - r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Values - [q36, q38] - | q40 : int(1..2)]) - | q38 : int(1..2)]) - /\ - and([q42 <= - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Marker[q34] - -> - or([r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Flags - [q36, q44] - /\ - r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Values - [q36, q44] - = - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Values - [q34, q42] - | q44 : int(1..2)]) - | q42 : int(1..2)]), - r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_3[q36] = - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_3[q34]; - int(1..3)]) - | q36 : int(1..84)]) - | q34 : int(1..84)]), - r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Marker = r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Marker - diff --git a/tests/exhaustive/basic/relation04_param/expected/model_4_1-param4-solution000001.solution b/tests/exhaustive/basic/relation04_param/expected/model_4_1-param4-solution000001.solution deleted file mode 100644 index 547e6d2e7e..0000000000 --- a/tests/exhaustive/basic/relation04_param/expected/model_4_1-param4-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting r be relation((3, {2}, 6), (3, {3}, 9)) diff --git a/tests/exhaustive/basic/relation04_param/expected/model_4_1-param4.eprime-param b/tests/exhaustive/basic/relation04_param/expected/model_4_1-param4.eprime-param deleted file mode 100644 index 87708d95a4..0000000000 --- a/tests/exhaustive/basic/relation04_param/expected/model_4_1-param4.eprime-param +++ /dev/null @@ -1,11 +0,0 @@ -language ESSENCE' 1.0 - -letting a_RelationAsSetR6_ExplicitR6_1 be [3, 3; int(1..2)] -letting a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy be [[2; int(1)], [3; int(1)]; int(1..2)] -$ Visualisation for a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy -$ 2 -$ 3 - -letting a_RelationAsSetR6_ExplicitR6_3 be [6, 9; int(1..2)] -letting fin1 be 2 -letting fin2 be 1 diff --git a/tests/exhaustive/basic/relation04_param/expected/model_4_1.eprime b/tests/exhaustive/basic/relation04_param/expected/model_4_1.eprime deleted file mode 100644 index 6539c4f97f..0000000000 --- a/tests/exhaustive/basic/relation04_param/expected/model_4_1.eprime +++ /dev/null @@ -1,202 +0,0 @@ -language ESSENCE' 1.0 - -given fin1: int -given fin2: int -given a_RelationAsSetR6_ExplicitR6_1: matrix indexed by [int(1..fin1)] of int(1..3) -given a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy: - matrix indexed by [int(1..fin1), int(1..fin2)] of int(2..4) -given a_RelationAsSetR6_ExplicitR6_3: matrix indexed by [int(1..fin1)] of int(4..10) -find r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Marker: int(0..84) -find r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_1: matrix indexed by [int(1..84)] of int(1..3) -find r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Flags: - matrix indexed by [int(1..84), int(1..2)] of bool -find r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Values: - matrix indexed by [int(1..84), int(1..2)] of int(2..3) -find r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_3: matrix indexed by [int(1..84)] of int(4..10) -find r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Marker: int(0..84) -find r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_1: matrix indexed by [int(1..84)] of int(1..3) -find r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_2_Occurrence: - matrix indexed by [int(1..84), int(2..3)] of bool -find r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_3: matrix indexed by [int(1..84)] of int(4..10) -branching on - [r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Marker, r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_1, - r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_2_Occurrence, - r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_3, r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Marker, - r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_1, - r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Flags, - r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Values, - r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_3] -such that - and([q38 <= r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Marker -> - or([and([a_RelationAsSetR6_ExplicitR6_1[q40] = r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_1[q38], - and([or([r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Flags - [q38, q44] - /\ - r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Values - [q38, q44] - = a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q40, q42] - | q44 : int(1..2)]) - | q42 : int(1..fin2), - a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q40, q42] != 4]) - /\ - and([r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Flags[q38, q46] - -> - or([a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q40, q48] = - r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Values - [q38, q46] - | q48 : int(1..fin2), - a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q40, q48] != 4]) - | q46 : int(1..2)]), - a_RelationAsSetR6_ExplicitR6_3[q40] = r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_3[q38]; - int(1..3)]) - | q40 : int(1..fin1)]) - | q38 : int(1..84)]), - and([or([q51 <= r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Marker /\ - and([r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_1[q51] = a_RelationAsSetR6_ExplicitR6_1[q49], - and([r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Flags[q51, q53] - -> - or([a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q49, q55] = - r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Values - [q51, q53] - | q55 : int(1..fin2), - a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q49, q55] != 4]) - | q53 : int(1..2)]) - /\ - and([or([r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Flags - [q51, q59] - /\ - r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Values - [q51, q59] - = a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q49, q57] - | q59 : int(1..2)]) - | q57 : int(1..fin2), - a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q49, q57] != 4]), - r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_3[q51] = a_RelationAsSetR6_ExplicitR6_3[q49]; - int(1..3)]) - | q51 : int(1..84)]) - | q49 : int(1..fin1)]), - r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Marker = fin1, - and([q1 + 1 <= r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Marker -> - flatten([[r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_1[q1]; int(1)], - flatten([flatten([[-toInt(r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Flags - [q1, q9]); - int(1)], - [r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Values - [q1, q9]; - int(1)]; - int(1..2)]) - | q9 : int(1..2)]), - [r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_3[q1]; int(1)]; - int(1..3)]) - r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Marker -> - and([r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_1[q2] = 1, - and([r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Flags[q2, q11] = - false - | q11 : int(1..2)]) - /\ - and([r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Values[q2, q12] = 2 - | q12 : int(1..2)]), - r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_3[q2] = 4; - int(1..3)]) - | q2 : int(1..84)]), - and([q3 <= r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Marker -> - (r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Flags[q3, 2] -> - r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Values[q3, 1] < - r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Values[q3, 2]) - | q3 : int(1..84)]), - and([q3 <= r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Marker -> - and([r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Flags[q3, q5] = false -> - r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Values[q3, q5] = 2 - | q5 : int(1..2)]) - | q3 : int(1..84)]), - and([q3 <= r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Marker -> - (r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Flags[q3, 2] -> - r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Flags[q3, 1]) - | q3 : int(1..84)]), - and([q13 + 1 <= r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Marker -> - flatten([[r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_1[q13]; int(1)], - [-toInt(r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_2_Occurrence[q13, q17]) - | q17 : int(2..3)], - [r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_3[q13]; int(1)]; - int(1..3)]) - r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Marker -> - and([r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_1[q14] = 1, - and([r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_2_Occurrence[q14, q19] = false - | q19 : int(2..3)]), - r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_3[q14] = 4; - int(1..3)]) - | q14 : int(1..84)]), - and([q21 <= r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Marker -> - or([q23 <= r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Marker /\ - and([r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_1[q23] = - r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_1[q21], - and([r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Flags[q23, q25] - -> - r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_2_Occurrence - [q21, - r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Values - [q23, q25]] - | q25 : int(1..2)]) - /\ - and([r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_2_Occurrence[q21, q26] -> - or([r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Flags - [q23, q28] - /\ - r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Values - [q23, q28] - = q26 - | q28 : int(1..2)]) - | q26 : int(2..3)]), - r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_3[q23] = - r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_3[q21]; - int(1..3)]) - | q23 : int(1..84)]) - | q21 : int(1..84)]), - and([q29 <= r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Marker -> - or([q31 <= r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Marker /\ - and([r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_1[q31] = - r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_1[q29], - and([r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_2_Occurrence[q31, q32] -> - or([r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Flags - [q29, q34] - /\ - r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Values - [q29, q34] - = q32 - | q34 : int(1..2)]) - | q32 : int(2..3)]) - /\ - and([r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Flags[q29, q36] - -> - r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_2_Occurrence - [q31, - r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Values - [q29, q36]] - | q36 : int(1..2)]), - r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_3[q31] = - r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_3[q29]; - int(1..3)]) - | q31 : int(1..84)]) - | q29 : int(1..84)]), - r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Marker = r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Marker - diff --git a/tests/exhaustive/basic/relation04_param/expected/model_4_2-param4-solution000001.solution b/tests/exhaustive/basic/relation04_param/expected/model_4_2-param4-solution000001.solution deleted file mode 100644 index 547e6d2e7e..0000000000 --- a/tests/exhaustive/basic/relation04_param/expected/model_4_2-param4-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting r be relation((3, {2}, 6), (3, {3}, 9)) diff --git a/tests/exhaustive/basic/relation04_param/expected/model_4_2-param4.eprime-param b/tests/exhaustive/basic/relation04_param/expected/model_4_2-param4.eprime-param deleted file mode 100644 index 87708d95a4..0000000000 --- a/tests/exhaustive/basic/relation04_param/expected/model_4_2-param4.eprime-param +++ /dev/null @@ -1,11 +0,0 @@ -language ESSENCE' 1.0 - -letting a_RelationAsSetR6_ExplicitR6_1 be [3, 3; int(1..2)] -letting a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy be [[2; int(1)], [3; int(1)]; int(1..2)] -$ Visualisation for a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy -$ 2 -$ 3 - -letting a_RelationAsSetR6_ExplicitR6_3 be [6, 9; int(1..2)] -letting fin1 be 2 -letting fin2 be 1 diff --git a/tests/exhaustive/basic/relation04_param/expected/model_4_2.eprime b/tests/exhaustive/basic/relation04_param/expected/model_4_2.eprime deleted file mode 100644 index d76b74b4f4..0000000000 --- a/tests/exhaustive/basic/relation04_param/expected/model_4_2.eprime +++ /dev/null @@ -1,217 +0,0 @@ -language ESSENCE' 1.0 - -given fin1: int -given fin2: int -given a_RelationAsSetR6_ExplicitR6_1: matrix indexed by [int(1..fin1)] of int(1..3) -given a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy: - matrix indexed by [int(1..fin1), int(1..fin2)] of int(2..4) -given a_RelationAsSetR6_ExplicitR6_3: matrix indexed by [int(1..fin1)] of int(4..10) -find r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Marker: int(0..84) -find r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_1: matrix indexed by [int(1..84)] of int(1..3) -find r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Flags: - matrix indexed by [int(1..84), int(1..2)] of bool -find r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Values: - matrix indexed by [int(1..84), int(1..2)] of int(2..3) -find r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_3: matrix indexed by [int(1..84)] of int(4..10) -find r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Marker: int(0..84) -find r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_1: matrix indexed by [int(1..84)] of int(1..3) -find r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy: - matrix indexed by [int(1..84), int(1..2)] of int(2..4) -find r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_3: matrix indexed by [int(1..84)] of int(4..10) -branching on - [r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Marker, r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_1, - r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy, - r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_3, r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Marker, - r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_1, - r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Flags, - r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Values, - r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_3] -such that - and([q47 <= r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Marker -> - or([and([a_RelationAsSetR6_ExplicitR6_1[q49] = r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_1[q47], - and([or([r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Flags - [q47, q53] - /\ - r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Values - [q47, q53] - = a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q49, q51] - | q53 : int(1..2)]) - | q51 : int(1..fin2), - a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q49, q51] != 4]) - /\ - and([r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Flags[q47, q55] - -> - or([a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q49, q57] = - r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Values - [q47, q55] - | q57 : int(1..fin2), - a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q49, q57] != 4]) - | q55 : int(1..2)]), - a_RelationAsSetR6_ExplicitR6_3[q49] = r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_3[q47]; - int(1..3)]) - | q49 : int(1..fin1)]) - | q47 : int(1..84)]), - and([or([q60 <= r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Marker /\ - and([r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_1[q60] = a_RelationAsSetR6_ExplicitR6_1[q58], - and([r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Flags[q60, q62] - -> - or([a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q58, q64] = - r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Values - [q60, q62] - | q64 : int(1..fin2), - a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q58, q64] != 4]) - | q62 : int(1..2)]) - /\ - and([or([r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Flags - [q60, q68] - /\ - r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Values - [q60, q68] - = a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q58, q66] - | q68 : int(1..2)]) - | q66 : int(1..fin2), - a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q58, q66] != 4]), - r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_3[q60] = a_RelationAsSetR6_ExplicitR6_3[q58]; - int(1..3)]) - | q60 : int(1..84)]) - | q58 : int(1..fin1)]), - r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Marker = fin1, - and([q1 + 1 <= r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Marker -> - flatten([[r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_1[q1]; int(1)], - flatten([flatten([[-toInt(r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Flags - [q1, q9]); - int(1)], - [r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Values - [q1, q9]; - int(1)]; - int(1..2)]) - | q9 : int(1..2)]), - [r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_3[q1]; int(1)]; - int(1..3)]) - r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Marker -> - and([r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_1[q2] = 1, - and([r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Flags[q2, q11] = - false - | q11 : int(1..2)]) - /\ - and([r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Values[q2, q12] = 2 - | q12 : int(1..2)]), - r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_3[q2] = 4; - int(1..3)]) - | q2 : int(1..84)]), - and([q3 <= r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Marker -> - (r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Flags[q3, 2] -> - r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Values[q3, 1] < - r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Values[q3, 2]) - | q3 : int(1..84)]), - and([q3 <= r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Marker -> - and([r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Flags[q3, q5] = false -> - r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Values[q3, q5] = 2 - | q5 : int(1..2)]) - | q3 : int(1..84)]), - and([q3 <= r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Marker -> - (r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Flags[q3, 2] -> - r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Flags[q3, 1]) - | q3 : int(1..84)]), - and([q13 + 1 <= r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Marker -> - flatten([[r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_1[q13]; int(1)], - [r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q13, q20] - | q20 : int(1..2)], - [r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_3[q13]; int(1)]; - int(1..3)]) - r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Marker -> - and([r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_1[q14] = 1, - and([r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q14, q22] = 2 - | q22 : int(1..2)]), - r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_3[q14] = 4; - int(1..3)]) - | q14 : int(1..84)]), - and([q15 <= r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Marker -> - r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q15, 1] < - r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q15, 2] - \/ r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q15, 1] = 4 - | q15 : int(1..84)]), - and([q15 <= r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Marker -> - (r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q15, 1] = 4 -> - r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q15, 2] = 4) - | q15 : int(1..84)]), - and([q24 <= r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Marker -> - or([q26 <= r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Marker /\ - and([r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_1[q26] = - r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_1[q24], - and([r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Flags[q26, q28] - -> - or([r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q24, q30] != - 4 - /\ - r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q24, q30] = - r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Values - [q26, q28] - | q30 : int(1..2)]) - | q28 : int(1..2)]) - /\ - and([r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q24, q32] != 4 -> - or([r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Flags - [q26, q34] - /\ - r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Values - [q26, q34] - = r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q24, q32] - | q34 : int(1..2)]) - | q32 : int(1..2)]), - r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_3[q26] = - r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_3[q24]; - int(1..3)]) - | q26 : int(1..84)]) - | q24 : int(1..84)]), - and([q35 <= r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Marker -> - or([q37 <= r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Marker /\ - and([r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_1[q37] = - r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_1[q35], - and([r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q37, q39] != 4 -> - or([r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Flags - [q35, q41] - /\ - r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Values - [q35, q41] - = r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q37, q39] - | q41 : int(1..2)]) - | q39 : int(1..2)]) - /\ - and([r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Flags[q35, q43] - -> - or([r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q37, q45] != - 4 - /\ - r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q37, q45] = - r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Values - [q35, q43] - | q45 : int(1..2)]) - | q43 : int(1..2)]), - r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_3[q37] = - r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_3[q35]; - int(1..3)]) - | q37 : int(1..84)]) - | q35 : int(1..84)]), - r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Marker = r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Marker - diff --git a/tests/exhaustive/basic/relation04_param/expected/model_4_3-param4-solution000001.solution b/tests/exhaustive/basic/relation04_param/expected/model_4_3-param4-solution000001.solution deleted file mode 100644 index 547e6d2e7e..0000000000 --- a/tests/exhaustive/basic/relation04_param/expected/model_4_3-param4-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting r be relation((3, {2}, 6), (3, {3}, 9)) diff --git a/tests/exhaustive/basic/relation04_param/expected/model_4_3-param4.eprime-param b/tests/exhaustive/basic/relation04_param/expected/model_4_3-param4.eprime-param deleted file mode 100644 index 87708d95a4..0000000000 --- a/tests/exhaustive/basic/relation04_param/expected/model_4_3-param4.eprime-param +++ /dev/null @@ -1,11 +0,0 @@ -language ESSENCE' 1.0 - -letting a_RelationAsSetR6_ExplicitR6_1 be [3, 3; int(1..2)] -letting a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy be [[2; int(1)], [3; int(1)]; int(1..2)] -$ Visualisation for a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy -$ 2 -$ 3 - -letting a_RelationAsSetR6_ExplicitR6_3 be [6, 9; int(1..2)] -letting fin1 be 2 -letting fin2 be 1 diff --git a/tests/exhaustive/basic/relation04_param/expected/model_4_3.eprime b/tests/exhaustive/basic/relation04_param/expected/model_4_3.eprime deleted file mode 100644 index 4bb8397894..0000000000 --- a/tests/exhaustive/basic/relation04_param/expected/model_4_3.eprime +++ /dev/null @@ -1,246 +0,0 @@ -language ESSENCE' 1.0 - -given fin1: int -given fin2: int -given a_RelationAsSetR6_ExplicitR6_1: matrix indexed by [int(1..fin1)] of int(1..3) -given a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy: - matrix indexed by [int(1..fin1), int(1..fin2)] of int(2..4) -given a_RelationAsSetR6_ExplicitR6_3: matrix indexed by [int(1..fin1)] of int(4..10) -find r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Marker: int(0..84) -find r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_1: matrix indexed by [int(1..84)] of int(1..3) -find r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Flags: - matrix indexed by [int(1..84), int(1..2)] of bool -find r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Values: - matrix indexed by [int(1..84), int(1..2)] of int(2..3) -find r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_3: matrix indexed by [int(1..84)] of int(4..10) -find r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Marker: int(0..84) -find r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_1: matrix indexed by [int(1..84)] of int(1..3) -find r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Marker: - matrix indexed by [int(1..84)] of int(0..2) -find r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Values: - matrix indexed by [int(1..84), int(1..2)] of int(2..3) -find r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_3: matrix indexed by [int(1..84)] of int(4..10) -branching on - [r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Marker, r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_1, - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Marker, - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Values, - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_3, r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Marker, - r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_1, - r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Flags, - r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Values, - r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_3] -such that - and([q46 <= r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Marker -> - or([and([a_RelationAsSetR6_ExplicitR6_1[q48] = r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_1[q46], - and([or([r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Flags - [q46, q52] - /\ - r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Values - [q46, q52] - = a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q48, q50] - | q52 : int(1..2)]) - | q50 : int(1..fin2), - a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q48, q50] != 4]) - /\ - and([r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Flags[q46, q54] - -> - or([a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q48, q56] = - r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Values - [q46, q54] - | q56 : int(1..fin2), - a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q48, q56] != 4]) - | q54 : int(1..2)]), - a_RelationAsSetR6_ExplicitR6_3[q48] = r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_3[q46]; - int(1..3)]) - | q48 : int(1..fin1)]) - | q46 : int(1..84)]), - and([or([q59 <= r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Marker /\ - and([r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_1[q59] = a_RelationAsSetR6_ExplicitR6_1[q57], - and([r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Flags[q59, q61] - -> - or([a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q57, q63] = - r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Values - [q59, q61] - | q63 : int(1..fin2), - a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q57, q63] != 4]) - | q61 : int(1..2)]) - /\ - and([or([r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Flags - [q59, q67] - /\ - r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Values - [q59, q67] - = a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q57, q65] - | q67 : int(1..2)]) - | q65 : int(1..fin2), - a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q57, q65] != 4]), - r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_3[q59] = a_RelationAsSetR6_ExplicitR6_3[q57]; - int(1..3)]) - | q59 : int(1..84)]) - | q57 : int(1..fin1)]), - r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Marker = fin1, - and([q1 + 1 <= r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Marker -> - flatten([[r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_1[q1]; int(1)], - flatten([flatten([[-toInt(r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Flags - [q1, q9]); - int(1)], - [r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Values - [q1, q9]; - int(1)]; - int(1..2)]) - | q9 : int(1..2)]), - [r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_3[q1]; int(1)]; - int(1..3)]) - r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Marker -> - and([r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_1[q2] = 1, - and([r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Flags[q2, q11] = - false - | q11 : int(1..2)]) - /\ - and([r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Values[q2, q12] = 2 - | q12 : int(1..2)]), - r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_3[q2] = 4; - int(1..3)]) - | q2 : int(1..84)]), - and([q3 <= r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Marker -> - (r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Flags[q3, 2] -> - r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Values[q3, 1] < - r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Values[q3, 2]) - | q3 : int(1..84)]), - and([q3 <= r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Marker -> - and([r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Flags[q3, q5] = false -> - r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Values[q3, q5] = 2 - | q5 : int(1..2)]) - | q3 : int(1..84)]), - and([q3 <= r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Marker -> - (r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Flags[q3, 2] -> - r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Flags[q3, 1]) - | q3 : int(1..84)]), - and([q13 + 1 <= r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Marker -> - flatten([[r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_1[q13]; int(1)], - flatten([[r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Marker - [q13]; - int(1)], - flatten([[r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Values - [q13, q19]; - int(1)] - | q19 : int(1..2)]); - int(1..2)]), - [r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_3[q13]; int(1)]; - int(1..3)]) - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Marker -> - and([r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_1[q14] = 1, - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Marker[q14] = 0 /\ - and([r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Values[q14, q21] = 2 - | q21 : int(1..2)]), - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_3[q14] = 4; - int(1..3)]) - | q14 : int(1..84)]), - and([q15 <= r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Marker -> - (2 <= r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Marker[q15] -> - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Values[q15, 1] < - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Values[q15, 2]) - | q15 : int(1..84)]), - and([q15 <= r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Marker -> - and([q17 > r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Marker[q15] -> - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Values[q15, q17] = 2 - | q17 : int(1..2)]) - | q15 : int(1..84)]), - and([q23 <= r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Marker -> - or([q25 <= r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Marker /\ - and([r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_1[q25] = - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_1[q23], - and([r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Flags[q25, q27] - -> - or([q29 <= - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Marker[q23] - /\ - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Values - [q23, q29] - = - r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Values - [q25, q27] - | q29 : int(1..2)]) - | q27 : int(1..2)]) - /\ - and([q31 <= - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Marker[q23] - -> - or([r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Flags - [q25, q33] - /\ - r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Values - [q25, q33] - = - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Values - [q23, q31] - | q33 : int(1..2)]) - | q31 : int(1..2)]), - r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_3[q25] = - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_3[q23]; - int(1..3)]) - | q25 : int(1..84)]) - | q23 : int(1..84)]), - and([q34 <= r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Marker -> - or([q36 <= r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Marker /\ - and([r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_1[q36] = - r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_1[q34], - and([q38 <= - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Marker[q36] - -> - or([r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Flags - [q34, q40] - /\ - r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Values - [q34, q40] - = - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Values - [q36, q38] - | q40 : int(1..2)]) - | q38 : int(1..2)]) - /\ - and([r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Flags[q34, q42] - -> - or([q44 <= - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Marker[q36] - /\ - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Values - [q36, q44] - = - r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Values - [q34, q42] - | q44 : int(1..2)]) - | q42 : int(1..2)]), - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_3[q36] = - r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_3[q34]; - int(1..3)]) - | q36 : int(1..84)]) - | q34 : int(1..84)]), - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Marker = r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Marker - diff --git a/tests/exhaustive/basic/relation04_param/expected/model_4_4-param4-solution000001.solution b/tests/exhaustive/basic/relation04_param/expected/model_4_4-param4-solution000001.solution deleted file mode 100644 index 547e6d2e7e..0000000000 --- a/tests/exhaustive/basic/relation04_param/expected/model_4_4-param4-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting r be relation((3, {2}, 6), (3, {3}, 9)) diff --git a/tests/exhaustive/basic/relation04_param/expected/model_4_4-param4.eprime-param b/tests/exhaustive/basic/relation04_param/expected/model_4_4-param4.eprime-param deleted file mode 100644 index 87708d95a4..0000000000 --- a/tests/exhaustive/basic/relation04_param/expected/model_4_4-param4.eprime-param +++ /dev/null @@ -1,11 +0,0 @@ -language ESSENCE' 1.0 - -letting a_RelationAsSetR6_ExplicitR6_1 be [3, 3; int(1..2)] -letting a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy be [[2; int(1)], [3; int(1)]; int(1..2)] -$ Visualisation for a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy -$ 2 -$ 3 - -letting a_RelationAsSetR6_ExplicitR6_3 be [6, 9; int(1..2)] -letting fin1 be 2 -letting fin2 be 1 diff --git a/tests/exhaustive/basic/relation04_param/expected/model_4_4.eprime b/tests/exhaustive/basic/relation04_param/expected/model_4_4.eprime deleted file mode 100644 index e4cbdf3e64..0000000000 --- a/tests/exhaustive/basic/relation04_param/expected/model_4_4.eprime +++ /dev/null @@ -1,121 +0,0 @@ -language ESSENCE' 1.0 - -given fin1: int -given fin2: int -given a_RelationAsSetR6_ExplicitR6_1: matrix indexed by [int(1..fin1)] of int(1..3) -given a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy: - matrix indexed by [int(1..fin1), int(1..fin2)] of int(2..4) -given a_RelationAsSetR6_ExplicitR6_3: matrix indexed by [int(1..fin1)] of int(4..10) -find r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Marker: int(0..84) -find r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_1: matrix indexed by [int(1..84)] of int(1..3) -find r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Flags: - matrix indexed by [int(1..84), int(1..2)] of bool -find r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Values: - matrix indexed by [int(1..84), int(1..2)] of int(2..3) -find r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_3: matrix indexed by [int(1..84)] of int(4..10) -branching on - [r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Marker, r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_1, - r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Flags, - r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Values, - r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_3] -such that - and([q14 <= r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Marker -> - or([and([a_RelationAsSetR6_ExplicitR6_1[q16] = r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_1[q14], - and([or([r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Flags - [q14, q20] - /\ - r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Values - [q14, q20] - = a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q16, q18] - | q20 : int(1..2)]) - | q18 : int(1..fin2), - a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q16, q18] != 4]) - /\ - and([r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Flags[q14, q22] - -> - or([a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q16, q24] = - r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Values - [q14, q22] - | q24 : int(1..fin2), - a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q16, q24] != 4]) - | q22 : int(1..2)]), - a_RelationAsSetR6_ExplicitR6_3[q16] = r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_3[q14]; - int(1..3)]) - | q16 : int(1..fin1)]) - | q14 : int(1..84)]), - and([or([q27 <= r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Marker /\ - and([r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_1[q27] = a_RelationAsSetR6_ExplicitR6_1[q25], - and([r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Flags[q27, q29] - -> - or([a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q25, q31] = - r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Values - [q27, q29] - | q31 : int(1..fin2), - a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q25, q31] != 4]) - | q29 : int(1..2)]) - /\ - and([or([r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Flags - [q27, q35] - /\ - r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Values - [q27, q35] - = a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q25, q33] - | q35 : int(1..2)]) - | q33 : int(1..fin2), - a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q25, q33] != 4]), - r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_3[q27] = a_RelationAsSetR6_ExplicitR6_3[q25]; - int(1..3)]) - | q27 : int(1..84)]) - | q25 : int(1..fin1)]), - r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Marker = fin1, - and([q1 + 1 <= r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Marker -> - flatten([[r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_1[q1]; int(1)], - flatten([flatten([[-toInt(r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Flags - [q1, q9]); - int(1)], - [r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Values - [q1, q9]; - int(1)]; - int(1..2)]) - | q9 : int(1..2)]), - [r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_3[q1]; int(1)]; - int(1..3)]) - r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Marker -> - and([r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_1[q2] = 1, - and([r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Flags[q2, q11] = - false - | q11 : int(1..2)]) - /\ - and([r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Values[q2, q12] = 2 - | q12 : int(1..2)]), - r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_3[q2] = 4; - int(1..3)]) - | q2 : int(1..84)]), - and([q3 <= r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Marker -> - (r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Flags[q3, 2] -> - r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Values[q3, 1] < - r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Values[q3, 2]) - | q3 : int(1..84)]), - and([q3 <= r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Marker -> - and([r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Flags[q3, q5] = false -> - r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Values[q3, q5] = 2 - | q5 : int(1..2)]) - | q3 : int(1..84)]), - and([q3 <= r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Marker -> - (r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Flags[q3, 2] -> - r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Flags[q3, 1]) - | q3 : int(1..84)]) - diff --git a/tests/exhaustive/basic/set03/expected/model_1_1-solution000001.solution b/tests/exhaustive/basic/set03/expected/model_1_1-solution000001.solution deleted file mode 100644 index de5cc861ad..0000000000 --- a/tests/exhaustive/basic/set03/expected/model_1_1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1} diff --git a/tests/exhaustive/basic/set03/expected/model_1_1-solution000002.solution b/tests/exhaustive/basic/set03/expected/model_1_1-solution000002.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/set03/expected/model_1_1-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/set03/expected/model_1_1.eprime b/tests/exhaustive/basic/set03/expected/model_1_1.eprime deleted file mode 100644 index 16b384a5f6..0000000000 --- a/tests/exhaustive/basic/set03/expected/model_1_1.eprime +++ /dev/null @@ -1,8 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1..2)] of bool -branching on [x_Occurrence] -such that - x_Occurrence[1], - sum([toInt(x_Occurrence[q1]) | q1 : int(1..2)]) <= 2 - diff --git a/tests/exhaustive/basic/set03/expected/model_1_2-solution000001.solution b/tests/exhaustive/basic/set03/expected/model_1_2-solution000001.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/set03/expected/model_1_2-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/set03/expected/model_1_2-solution000002.solution b/tests/exhaustive/basic/set03/expected/model_1_2-solution000002.solution deleted file mode 100644 index de5cc861ad..0000000000 --- a/tests/exhaustive/basic/set03/expected/model_1_2-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1} diff --git a/tests/exhaustive/basic/set03/expected/model_1_2.eprime b/tests/exhaustive/basic/set03/expected/model_1_2.eprime deleted file mode 100644 index 8e12c0f3a2..0000000000 --- a/tests/exhaustive/basic/set03/expected/model_1_2.eprime +++ /dev/null @@ -1,16 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1..2)] of bool -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..2)] of int(1..3) -branching on [x_ExplicitVarSizeWithDummy, x_Occurrence] -such that - x_Occurrence[1], - sum([toInt(x_Occurrence[q1]) | q1 : int(1..2)]) <= 2, - x_ExplicitVarSizeWithDummy[1] < x_ExplicitVarSizeWithDummy[2] \/ x_ExplicitVarSizeWithDummy[1] = 3, - x_ExplicitVarSizeWithDummy[1] = 3 -> x_ExplicitVarSizeWithDummy[2] = 3, - sum([toInt(x_ExplicitVarSizeWithDummy[q4] != 3) | q4 : int(1..2)]) <= 2, - and([x_ExplicitVarSizeWithDummy[q7] != 3 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q7]] | q7 : int(1..2)]), - and([x_Occurrence[q8] -> - or([x_ExplicitVarSizeWithDummy[q10] != 3 /\ x_ExplicitVarSizeWithDummy[q10] = q8 | q10 : int(1..2)]) - | q8 : int(1..2)]) - diff --git a/tests/exhaustive/basic/set03/expected/model_1_3-solution000001.solution b/tests/exhaustive/basic/set03/expected/model_1_3-solution000001.solution deleted file mode 100644 index de5cc861ad..0000000000 --- a/tests/exhaustive/basic/set03/expected/model_1_3-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1} diff --git a/tests/exhaustive/basic/set03/expected/model_1_3-solution000002.solution b/tests/exhaustive/basic/set03/expected/model_1_3-solution000002.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/set03/expected/model_1_3-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/set03/expected/model_1_3.eprime b/tests/exhaustive/basic/set03/expected/model_1_3.eprime deleted file mode 100644 index 6fb9afa1ba..0000000000 --- a/tests/exhaustive/basic/set03/expected/model_1_3.eprime +++ /dev/null @@ -1,19 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1..2)] of bool -find x_ExplicitVarSizeWithMarker_Marker: int(0..2) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..2)] of int(1..2) -branching on [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_Occurrence] -such that - x_Occurrence[1], - sum([toInt(x_Occurrence[q1]) | q1 : int(1..2)]) <= 2, - 2 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[1] < x_ExplicitVarSizeWithMarker_Values[2], - and([q3 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q3] = 1 | q3 : int(1..2)]), - x_ExplicitVarSizeWithMarker_Marker <= 2, - and([q6 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q6]] - | q6 : int(1..2)]), - and([x_Occurrence[q7] -> - or([q9 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q9] = q7 | q9 : int(1..2)]) - | q7 : int(1..2)]) - diff --git a/tests/exhaustive/basic/set03/expected/model_1_4-solution000001.solution b/tests/exhaustive/basic/set03/expected/model_1_4-solution000001.solution deleted file mode 100644 index de5cc861ad..0000000000 --- a/tests/exhaustive/basic/set03/expected/model_1_4-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1} diff --git a/tests/exhaustive/basic/set03/expected/model_1_4-solution000002.solution b/tests/exhaustive/basic/set03/expected/model_1_4-solution000002.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/set03/expected/model_1_4-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/set03/expected/model_1_4.eprime b/tests/exhaustive/basic/set03/expected/model_1_4.eprime deleted file mode 100644 index 6301346892..0000000000 --- a/tests/exhaustive/basic/set03/expected/model_1_4.eprime +++ /dev/null @@ -1,18 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1..2)] of bool -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..2)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..2)] of int(1..2) -branching on [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_Occurrence] -such that - x_Occurrence[1], - sum([toInt(x_Occurrence[q1]) | q1 : int(1..2)]) <= 2, - x_ExplicitVarSizeWithFlags_Flags[2] -> x_ExplicitVarSizeWithFlags_Values[1] < x_ExplicitVarSizeWithFlags_Values[2], - and([x_ExplicitVarSizeWithFlags_Flags[q3] = false -> x_ExplicitVarSizeWithFlags_Values[q3] = 1 | q3 : int(1..2)]), - x_ExplicitVarSizeWithFlags_Flags[2] -> x_ExplicitVarSizeWithFlags_Flags[1], - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q5]) | q5 : int(1..2)]) <= 2, - and([x_ExplicitVarSizeWithFlags_Flags[q8] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q8]] | q8 : int(1..2)]), - and([x_Occurrence[q9] -> - or([x_ExplicitVarSizeWithFlags_Flags[q11] /\ x_ExplicitVarSizeWithFlags_Values[q11] = q9 | q11 : int(1..2)]) - | q9 : int(1..2)]) - diff --git a/tests/exhaustive/basic/set03/expected/model_2_1-solution000001.solution b/tests/exhaustive/basic/set03/expected/model_2_1-solution000001.solution deleted file mode 100644 index de5cc861ad..0000000000 --- a/tests/exhaustive/basic/set03/expected/model_2_1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1} diff --git a/tests/exhaustive/basic/set03/expected/model_2_1-solution000002.solution b/tests/exhaustive/basic/set03/expected/model_2_1-solution000002.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/set03/expected/model_2_1-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/set03/expected/model_2_1.eprime b/tests/exhaustive/basic/set03/expected/model_2_1.eprime deleted file mode 100644 index b209f517b3..0000000000 --- a/tests/exhaustive/basic/set03/expected/model_2_1.eprime +++ /dev/null @@ -1,16 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..2)] of int(1..3) -find x_Occurrence: matrix indexed by [int(1..2)] of bool -branching on [x_Occurrence, x_ExplicitVarSizeWithDummy] -such that - or([x_ExplicitVarSizeWithDummy[q12] != 3 /\ x_ExplicitVarSizeWithDummy[q12] = 1 | q12 : int(1..2)]), - x_ExplicitVarSizeWithDummy[1] < x_ExplicitVarSizeWithDummy[2] \/ x_ExplicitVarSizeWithDummy[1] = 3, - x_ExplicitVarSizeWithDummy[1] = 3 -> x_ExplicitVarSizeWithDummy[2] = 3, - sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 3) | q3 : int(1..2)]) <= 2, - sum([toInt(x_Occurrence[q5]) | q5 : int(1..2)]) <= 2, - and([x_Occurrence[q6] -> - or([x_ExplicitVarSizeWithDummy[q8] != 3 /\ x_ExplicitVarSizeWithDummy[q8] = q6 | q8 : int(1..2)]) - | q6 : int(1..2)]), - and([x_ExplicitVarSizeWithDummy[q10] != 3 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q10]] | q10 : int(1..2)]) - diff --git a/tests/exhaustive/basic/set03/expected/model_2_2-solution000001.solution b/tests/exhaustive/basic/set03/expected/model_2_2-solution000001.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/set03/expected/model_2_2-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/set03/expected/model_2_2-solution000002.solution b/tests/exhaustive/basic/set03/expected/model_2_2-solution000002.solution deleted file mode 100644 index de5cc861ad..0000000000 --- a/tests/exhaustive/basic/set03/expected/model_2_2-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1} diff --git a/tests/exhaustive/basic/set03/expected/model_2_2.eprime b/tests/exhaustive/basic/set03/expected/model_2_2.eprime deleted file mode 100644 index 99d5e5a575..0000000000 --- a/tests/exhaustive/basic/set03/expected/model_2_2.eprime +++ /dev/null @@ -1,10 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..2)] of int(1..3) -branching on [x_ExplicitVarSizeWithDummy] -such that - or([x_ExplicitVarSizeWithDummy[q6] != 3 /\ x_ExplicitVarSizeWithDummy[q6] = 1 | q6 : int(1..2)]), - x_ExplicitVarSizeWithDummy[1] < x_ExplicitVarSizeWithDummy[2] \/ x_ExplicitVarSizeWithDummy[1] = 3, - x_ExplicitVarSizeWithDummy[1] = 3 -> x_ExplicitVarSizeWithDummy[2] = 3, - sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 3) | q3 : int(1..2)]) <= 2 - diff --git a/tests/exhaustive/basic/set03/expected/model_2_3-solution000001.solution b/tests/exhaustive/basic/set03/expected/model_2_3-solution000001.solution deleted file mode 100644 index de5cc861ad..0000000000 --- a/tests/exhaustive/basic/set03/expected/model_2_3-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1} diff --git a/tests/exhaustive/basic/set03/expected/model_2_3-solution000002.solution b/tests/exhaustive/basic/set03/expected/model_2_3-solution000002.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/set03/expected/model_2_3-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/set03/expected/model_2_3.eprime b/tests/exhaustive/basic/set03/expected/model_2_3.eprime deleted file mode 100644 index 94cefde44a..0000000000 --- a/tests/exhaustive/basic/set03/expected/model_2_3.eprime +++ /dev/null @@ -1,26 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..2)] of int(1..3) -find x_ExplicitVarSizeWithMarker_Marker: int(0..2) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..2)] of int(1..2) -branching on [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy] -such that - or([x_ExplicitVarSizeWithDummy[q17] != 3 /\ x_ExplicitVarSizeWithDummy[q17] = 1 | q17 : int(1..2)]), - x_ExplicitVarSizeWithDummy[1] < x_ExplicitVarSizeWithDummy[2] \/ x_ExplicitVarSizeWithDummy[1] = 3, - x_ExplicitVarSizeWithDummy[1] = 3 -> x_ExplicitVarSizeWithDummy[2] = 3, - sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 3) | q3 : int(1..2)]) <= 2, - 2 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[1] < x_ExplicitVarSizeWithMarker_Values[2], - and([q6 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q6] = 1 | q6 : int(1..2)]), - x_ExplicitVarSizeWithMarker_Marker <= 2, - and([q9 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q11] != 3 /\ - x_ExplicitVarSizeWithDummy[q11] = x_ExplicitVarSizeWithMarker_Values[q9] - | q11 : int(1..2)]) - | q9 : int(1..2)]), - and([x_ExplicitVarSizeWithDummy[q13] != 3 -> - or([q15 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q15] = x_ExplicitVarSizeWithDummy[q13] - | q15 : int(1..2)]) - | q13 : int(1..2)]) - diff --git a/tests/exhaustive/basic/set03/expected/model_2_4-solution000001.solution b/tests/exhaustive/basic/set03/expected/model_2_4-solution000001.solution deleted file mode 100644 index de5cc861ad..0000000000 --- a/tests/exhaustive/basic/set03/expected/model_2_4-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1} diff --git a/tests/exhaustive/basic/set03/expected/model_2_4-solution000002.solution b/tests/exhaustive/basic/set03/expected/model_2_4-solution000002.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/set03/expected/model_2_4-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/set03/expected/model_2_4.eprime b/tests/exhaustive/basic/set03/expected/model_2_4.eprime deleted file mode 100644 index 3b3251ce37..0000000000 --- a/tests/exhaustive/basic/set03/expected/model_2_4.eprime +++ /dev/null @@ -1,26 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..2)] of int(1..3) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..2)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..2)] of int(1..2) -branching on [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy] -such that - or([x_ExplicitVarSizeWithDummy[q19] != 3 /\ x_ExplicitVarSizeWithDummy[q19] = 1 | q19 : int(1..2)]), - x_ExplicitVarSizeWithDummy[1] < x_ExplicitVarSizeWithDummy[2] \/ x_ExplicitVarSizeWithDummy[1] = 3, - x_ExplicitVarSizeWithDummy[1] = 3 -> x_ExplicitVarSizeWithDummy[2] = 3, - sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 3) | q3 : int(1..2)]) <= 2, - x_ExplicitVarSizeWithFlags_Flags[2] -> x_ExplicitVarSizeWithFlags_Values[1] < x_ExplicitVarSizeWithFlags_Values[2], - and([x_ExplicitVarSizeWithFlags_Flags[q6] = false -> x_ExplicitVarSizeWithFlags_Values[q6] = 1 | q6 : int(1..2)]), - x_ExplicitVarSizeWithFlags_Flags[2] -> x_ExplicitVarSizeWithFlags_Flags[1], - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q8]) | q8 : int(1..2)]) <= 2, - and([x_ExplicitVarSizeWithFlags_Flags[q11] -> - or([x_ExplicitVarSizeWithDummy[q13] != 3 /\ - x_ExplicitVarSizeWithDummy[q13] = x_ExplicitVarSizeWithFlags_Values[q11] - | q13 : int(1..2)]) - | q11 : int(1..2)]), - and([x_ExplicitVarSizeWithDummy[q15] != 3 -> - or([x_ExplicitVarSizeWithFlags_Flags[q17] /\ - x_ExplicitVarSizeWithFlags_Values[q17] = x_ExplicitVarSizeWithDummy[q15] - | q17 : int(1..2)]) - | q15 : int(1..2)]) - diff --git a/tests/exhaustive/basic/set03/expected/model_3_1-solution000001.solution b/tests/exhaustive/basic/set03/expected/model_3_1-solution000001.solution deleted file mode 100644 index de5cc861ad..0000000000 --- a/tests/exhaustive/basic/set03/expected/model_3_1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1} diff --git a/tests/exhaustive/basic/set03/expected/model_3_1-solution000002.solution b/tests/exhaustive/basic/set03/expected/model_3_1-solution000002.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/set03/expected/model_3_1-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/set03/expected/model_3_1.eprime b/tests/exhaustive/basic/set03/expected/model_3_1.eprime deleted file mode 100644 index fe211d2c59..0000000000 --- a/tests/exhaustive/basic/set03/expected/model_3_1.eprime +++ /dev/null @@ -1,19 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..2) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..2)] of int(1..2) -find x_Occurrence: matrix indexed by [int(1..2)] of bool -branching on [x_Occurrence, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] -such that - or([q11 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q11] = 1 | q11 : int(1..2)]), - 2 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[1] < x_ExplicitVarSizeWithMarker_Values[2], - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..2)]), - x_ExplicitVarSizeWithMarker_Marker <= 2, - sum([toInt(x_Occurrence[q4]) | q4 : int(1..2)]) <= 2, - and([x_Occurrence[q5] -> - or([q7 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q7] = q5 | q7 : int(1..2)]) - | q5 : int(1..2)]), - and([q9 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q9]] - | q9 : int(1..2)]) - diff --git a/tests/exhaustive/basic/set03/expected/model_3_2-solution000001.solution b/tests/exhaustive/basic/set03/expected/model_3_2-solution000001.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/set03/expected/model_3_2-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/set03/expected/model_3_2-solution000002.solution b/tests/exhaustive/basic/set03/expected/model_3_2-solution000002.solution deleted file mode 100644 index de5cc861ad..0000000000 --- a/tests/exhaustive/basic/set03/expected/model_3_2-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1} diff --git a/tests/exhaustive/basic/set03/expected/model_3_2.eprime b/tests/exhaustive/basic/set03/expected/model_3_2.eprime deleted file mode 100644 index f1ac7634ba..0000000000 --- a/tests/exhaustive/basic/set03/expected/model_3_2.eprime +++ /dev/null @@ -1,26 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..2) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..2)] of int(1..2) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..2)] of int(1..3) -branching on [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] -such that - or([q17 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q17] = 1 | q17 : int(1..2)]), - 2 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[1] < x_ExplicitVarSizeWithMarker_Values[2], - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..2)]), - x_ExplicitVarSizeWithMarker_Marker <= 2, - x_ExplicitVarSizeWithDummy[1] < x_ExplicitVarSizeWithDummy[2] \/ x_ExplicitVarSizeWithDummy[1] = 3, - x_ExplicitVarSizeWithDummy[1] = 3 -> x_ExplicitVarSizeWithDummy[2] = 3, - sum([toInt(x_ExplicitVarSizeWithDummy[q6] != 3) | q6 : int(1..2)]) <= 2, - and([x_ExplicitVarSizeWithDummy[q9] != 3 -> - or([q11 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q11] = x_ExplicitVarSizeWithDummy[q9] - | q11 : int(1..2)]) - | q9 : int(1..2)]), - and([q13 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q15] != 3 /\ - x_ExplicitVarSizeWithDummy[q15] = x_ExplicitVarSizeWithMarker_Values[q13] - | q15 : int(1..2)]) - | q13 : int(1..2)]) - diff --git a/tests/exhaustive/basic/set03/expected/model_3_3-solution000001.solution b/tests/exhaustive/basic/set03/expected/model_3_3-solution000001.solution deleted file mode 100644 index de5cc861ad..0000000000 --- a/tests/exhaustive/basic/set03/expected/model_3_3-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1} diff --git a/tests/exhaustive/basic/set03/expected/model_3_3-solution000002.solution b/tests/exhaustive/basic/set03/expected/model_3_3-solution000002.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/set03/expected/model_3_3-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/set03/expected/model_3_3.eprime b/tests/exhaustive/basic/set03/expected/model_3_3.eprime deleted file mode 100644 index aebac4895f..0000000000 --- a/tests/exhaustive/basic/set03/expected/model_3_3.eprime +++ /dev/null @@ -1,12 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..2) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..2)] of int(1..2) -branching on [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] -such that - or([q5 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q5] = 1 | q5 : int(1..2)]), - 2 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[1] < x_ExplicitVarSizeWithMarker_Values[2], - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..2)]), - x_ExplicitVarSizeWithMarker_Marker <= 2 - diff --git a/tests/exhaustive/basic/set03/expected/model_3_4-solution000001.solution b/tests/exhaustive/basic/set03/expected/model_3_4-solution000001.solution deleted file mode 100644 index de5cc861ad..0000000000 --- a/tests/exhaustive/basic/set03/expected/model_3_4-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1} diff --git a/tests/exhaustive/basic/set03/expected/model_3_4-solution000002.solution b/tests/exhaustive/basic/set03/expected/model_3_4-solution000002.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/set03/expected/model_3_4-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/set03/expected/model_3_4.eprime b/tests/exhaustive/basic/set03/expected/model_3_4.eprime deleted file mode 100644 index c839c9c5b8..0000000000 --- a/tests/exhaustive/basic/set03/expected/model_3_4.eprime +++ /dev/null @@ -1,30 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..2) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..2)] of int(1..2) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..2)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..2)] of int(1..2) -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithMarker_Marker, - x_ExplicitVarSizeWithMarker_Values] -such that - or([q18 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q18] = 1 | q18 : int(1..2)]), - 2 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[1] < x_ExplicitVarSizeWithMarker_Values[2], - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..2)]), - x_ExplicitVarSizeWithMarker_Marker <= 2, - x_ExplicitVarSizeWithFlags_Flags[2] -> x_ExplicitVarSizeWithFlags_Values[1] < x_ExplicitVarSizeWithFlags_Values[2], - and([x_ExplicitVarSizeWithFlags_Flags[q5] = false -> x_ExplicitVarSizeWithFlags_Values[q5] = 1 | q5 : int(1..2)]), - x_ExplicitVarSizeWithFlags_Flags[2] -> x_ExplicitVarSizeWithFlags_Flags[1], - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q7]) | q7 : int(1..2)]) <= 2, - and([x_ExplicitVarSizeWithFlags_Flags[q10] -> - or([q12 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q12] = x_ExplicitVarSizeWithFlags_Values[q10] - | q12 : int(1..2)]) - | q10 : int(1..2)]), - and([q14 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q16] /\ - x_ExplicitVarSizeWithFlags_Values[q16] = x_ExplicitVarSizeWithMarker_Values[q14] - | q16 : int(1..2)]) - | q14 : int(1..2)]) - diff --git a/tests/exhaustive/basic/set03/expected/model_4_1-solution000001.solution b/tests/exhaustive/basic/set03/expected/model_4_1-solution000001.solution deleted file mode 100644 index de5cc861ad..0000000000 --- a/tests/exhaustive/basic/set03/expected/model_4_1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1} diff --git a/tests/exhaustive/basic/set03/expected/model_4_1-solution000002.solution b/tests/exhaustive/basic/set03/expected/model_4_1-solution000002.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/set03/expected/model_4_1-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/set03/expected/model_4_1.eprime b/tests/exhaustive/basic/set03/expected/model_4_1.eprime deleted file mode 100644 index 248c3e3b42..0000000000 --- a/tests/exhaustive/basic/set03/expected/model_4_1.eprime +++ /dev/null @@ -1,19 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..2)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..2)] of int(1..2) -find x_Occurrence: matrix indexed by [int(1..2)] of bool -branching on [x_Occurrence, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] -such that - or([x_ExplicitVarSizeWithFlags_Flags[q13] /\ x_ExplicitVarSizeWithFlags_Values[q13] = 1 | q13 : int(1..2)]), - x_ExplicitVarSizeWithFlags_Flags[2] -> x_ExplicitVarSizeWithFlags_Values[1] < x_ExplicitVarSizeWithFlags_Values[2], - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..2)]), - x_ExplicitVarSizeWithFlags_Flags[2] -> x_ExplicitVarSizeWithFlags_Flags[1], - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..2)]) <= 2, - sum([toInt(x_Occurrence[q6]) | q6 : int(1..2)]) <= 2, - and([x_Occurrence[q7] -> - or([x_ExplicitVarSizeWithFlags_Flags[q9] /\ x_ExplicitVarSizeWithFlags_Values[q9] = q7 | q9 : int(1..2)]) - | q7 : int(1..2)]), - and([x_ExplicitVarSizeWithFlags_Flags[q11] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q11]] - | q11 : int(1..2)]) - diff --git a/tests/exhaustive/basic/set03/expected/model_4_2-solution000001.solution b/tests/exhaustive/basic/set03/expected/model_4_2-solution000001.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/set03/expected/model_4_2-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/set03/expected/model_4_2-solution000002.solution b/tests/exhaustive/basic/set03/expected/model_4_2-solution000002.solution deleted file mode 100644 index de5cc861ad..0000000000 --- a/tests/exhaustive/basic/set03/expected/model_4_2-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1} diff --git a/tests/exhaustive/basic/set03/expected/model_4_2.eprime b/tests/exhaustive/basic/set03/expected/model_4_2.eprime deleted file mode 100644 index ab8292a451..0000000000 --- a/tests/exhaustive/basic/set03/expected/model_4_2.eprime +++ /dev/null @@ -1,26 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..2)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..2)] of int(1..2) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..2)] of int(1..3) -branching on [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] -such that - or([x_ExplicitVarSizeWithFlags_Flags[q19] /\ x_ExplicitVarSizeWithFlags_Values[q19] = 1 | q19 : int(1..2)]), - x_ExplicitVarSizeWithFlags_Flags[2] -> x_ExplicitVarSizeWithFlags_Values[1] < x_ExplicitVarSizeWithFlags_Values[2], - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..2)]), - x_ExplicitVarSizeWithFlags_Flags[2] -> x_ExplicitVarSizeWithFlags_Flags[1], - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..2)]) <= 2, - x_ExplicitVarSizeWithDummy[1] < x_ExplicitVarSizeWithDummy[2] \/ x_ExplicitVarSizeWithDummy[1] = 3, - x_ExplicitVarSizeWithDummy[1] = 3 -> x_ExplicitVarSizeWithDummy[2] = 3, - sum([toInt(x_ExplicitVarSizeWithDummy[q8] != 3) | q8 : int(1..2)]) <= 2, - and([x_ExplicitVarSizeWithDummy[q11] != 3 -> - or([x_ExplicitVarSizeWithFlags_Flags[q13] /\ - x_ExplicitVarSizeWithFlags_Values[q13] = x_ExplicitVarSizeWithDummy[q11] - | q13 : int(1..2)]) - | q11 : int(1..2)]), - and([x_ExplicitVarSizeWithFlags_Flags[q15] -> - or([x_ExplicitVarSizeWithDummy[q17] != 3 /\ - x_ExplicitVarSizeWithDummy[q17] = x_ExplicitVarSizeWithFlags_Values[q15] - | q17 : int(1..2)]) - | q15 : int(1..2)]) - diff --git a/tests/exhaustive/basic/set03/expected/model_4_3-solution000001.solution b/tests/exhaustive/basic/set03/expected/model_4_3-solution000001.solution deleted file mode 100644 index de5cc861ad..0000000000 --- a/tests/exhaustive/basic/set03/expected/model_4_3-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1} diff --git a/tests/exhaustive/basic/set03/expected/model_4_3-solution000002.solution b/tests/exhaustive/basic/set03/expected/model_4_3-solution000002.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/set03/expected/model_4_3-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/set03/expected/model_4_3.eprime b/tests/exhaustive/basic/set03/expected/model_4_3.eprime deleted file mode 100644 index 3a1cb29286..0000000000 --- a/tests/exhaustive/basic/set03/expected/model_4_3.eprime +++ /dev/null @@ -1,30 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..2)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..2)] of int(1..2) -find x_ExplicitVarSizeWithMarker_Marker: int(0..2) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..2)] of int(1..2) -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithFlags_Flags, - x_ExplicitVarSizeWithFlags_Values] -such that - or([x_ExplicitVarSizeWithFlags_Flags[q18] /\ x_ExplicitVarSizeWithFlags_Values[q18] = 1 | q18 : int(1..2)]), - x_ExplicitVarSizeWithFlags_Flags[2] -> x_ExplicitVarSizeWithFlags_Values[1] < x_ExplicitVarSizeWithFlags_Values[2], - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..2)]), - x_ExplicitVarSizeWithFlags_Flags[2] -> x_ExplicitVarSizeWithFlags_Flags[1], - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..2)]) <= 2, - 2 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[1] < x_ExplicitVarSizeWithMarker_Values[2], - and([q7 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q7] = 1 | q7 : int(1..2)]), - x_ExplicitVarSizeWithMarker_Marker <= 2, - and([q10 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q12] /\ - x_ExplicitVarSizeWithFlags_Values[q12] = x_ExplicitVarSizeWithMarker_Values[q10] - | q12 : int(1..2)]) - | q10 : int(1..2)]), - and([x_ExplicitVarSizeWithFlags_Flags[q14] -> - or([q16 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q16] = x_ExplicitVarSizeWithFlags_Values[q14] - | q16 : int(1..2)]) - | q14 : int(1..2)]) - diff --git a/tests/exhaustive/basic/set03/expected/model_4_4-solution000001.solution b/tests/exhaustive/basic/set03/expected/model_4_4-solution000001.solution deleted file mode 100644 index de5cc861ad..0000000000 --- a/tests/exhaustive/basic/set03/expected/model_4_4-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1} diff --git a/tests/exhaustive/basic/set03/expected/model_4_4-solution000002.solution b/tests/exhaustive/basic/set03/expected/model_4_4-solution000002.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/set03/expected/model_4_4-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/set03/expected/model_4_4.eprime b/tests/exhaustive/basic/set03/expected/model_4_4.eprime deleted file mode 100644 index ec9b61f711..0000000000 --- a/tests/exhaustive/basic/set03/expected/model_4_4.eprime +++ /dev/null @@ -1,12 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..2)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..2)] of int(1..2) -branching on [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] -such that - or([x_ExplicitVarSizeWithFlags_Flags[q7] /\ x_ExplicitVarSizeWithFlags_Values[q7] = 1 | q7 : int(1..2)]), - x_ExplicitVarSizeWithFlags_Flags[2] -> x_ExplicitVarSizeWithFlags_Values[1] < x_ExplicitVarSizeWithFlags_Values[2], - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..2)]), - x_ExplicitVarSizeWithFlags_Flags[2] -> x_ExplicitVarSizeWithFlags_Flags[1], - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..2)]) <= 2 - diff --git a/tests/exhaustive/basic/set04/expected/model_1_1_1-solution000001.solution b/tests/exhaustive/basic/set04/expected/model_1_1_1-solution000001.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_1_1_1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/set04/expected/model_1_1_1-solution000002.solution b/tests/exhaustive/basic/set04/expected/model_1_1_1-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_1_1_1-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set04/expected/model_1_1_1.eprime b/tests/exhaustive/basic/set04/expected/model_1_1_1.eprime deleted file mode 100644 index 758eeb2d3a..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_1_1_1.eprime +++ /dev/null @@ -1,9 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1..3)] of bool -branching on [x_Occurrence] -such that - x_Occurrence[1], - x_Occurrence[2], - sum([toInt(x_Occurrence[q1]) | q1 : int(1..3)]) <= 3 - diff --git a/tests/exhaustive/basic/set04/expected/model_1_1_2-solution000001.solution b/tests/exhaustive/basic/set04/expected/model_1_1_2-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_1_1_2-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set04/expected/model_1_1_2-solution000002.solution b/tests/exhaustive/basic/set04/expected/model_1_1_2-solution000002.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_1_1_2-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/set04/expected/model_1_1_2.eprime b/tests/exhaustive/basic/set04/expected/model_1_1_2.eprime deleted file mode 100644 index f368f0ac5a..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_1_1_2.eprime +++ /dev/null @@ -1,18 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1..3)] of bool -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..3)] of int(1..4) -branching on [x_ExplicitVarSizeWithDummy, x_Occurrence] -such that - x_Occurrence[1], - x_Occurrence[2], - sum([toInt(x_Occurrence[q1]) | q1 : int(1..3)]) <= 3, - and([x_ExplicitVarSizeWithDummy[q2] < x_ExplicitVarSizeWithDummy[q2 + 1] \/ x_ExplicitVarSizeWithDummy[q2] = 4 - | q2 : int(1..2)]), - and([x_ExplicitVarSizeWithDummy[q3] = 4 -> x_ExplicitVarSizeWithDummy[q3 + 1] = 4 | q3 : int(1..2)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q4] != 4) | q4 : int(1..3)]) <= 3, - and([x_ExplicitVarSizeWithDummy[q7] != 4 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q7]] | q7 : int(1..3)]), - and([x_Occurrence[q8] -> - or([x_ExplicitVarSizeWithDummy[q10] != 4 /\ x_ExplicitVarSizeWithDummy[q10] = q8 | q10 : int(1..3)]) - | q8 : int(1..3)]) - diff --git a/tests/exhaustive/basic/set04/expected/model_1_1_3-solution000001.solution b/tests/exhaustive/basic/set04/expected/model_1_1_3-solution000001.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_1_1_3-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/set04/expected/model_1_1_3-solution000002.solution b/tests/exhaustive/basic/set04/expected/model_1_1_3-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_1_1_3-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set04/expected/model_1_1_3.eprime b/tests/exhaustive/basic/set04/expected/model_1_1_3.eprime deleted file mode 100644 index 2eabb913cf..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_1_1_3.eprime +++ /dev/null @@ -1,21 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1..3)] of bool -find x_ExplicitVarSizeWithMarker_Marker: int(0..3) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3)] of int(1..3) -branching on [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_Occurrence] -such that - x_Occurrence[1], - x_Occurrence[2], - sum([toInt(x_Occurrence[q1]) | q1 : int(1..3)]) <= 3, - and([q2 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q2] < x_ExplicitVarSizeWithMarker_Values[q2 + 1] - | q2 : int(1..2)]), - and([q3 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q3] = 1 | q3 : int(1..3)]), - x_ExplicitVarSizeWithMarker_Marker <= 3, - and([q6 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q6]] - | q6 : int(1..3)]), - and([x_Occurrence[q7] -> - or([q9 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q9] = q7 | q9 : int(1..3)]) - | q7 : int(1..3)]) - diff --git a/tests/exhaustive/basic/set04/expected/model_1_1_4-solution000001.solution b/tests/exhaustive/basic/set04/expected/model_1_1_4-solution000001.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_1_1_4-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/set04/expected/model_1_1_4-solution000002.solution b/tests/exhaustive/basic/set04/expected/model_1_1_4-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_1_1_4-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set04/expected/model_1_1_4.eprime b/tests/exhaustive/basic/set04/expected/model_1_1_4.eprime deleted file mode 100644 index ab61dc16a9..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_1_1_4.eprime +++ /dev/null @@ -1,21 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1..3)] of bool -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..3)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3)] of int(1..3) -branching on [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_Occurrence] -such that - x_Occurrence[1], - x_Occurrence[2], - sum([toInt(x_Occurrence[q1]) | q1 : int(1..3)]) <= 3, - and([x_ExplicitVarSizeWithFlags_Flags[q2 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q2] < x_ExplicitVarSizeWithFlags_Values[q2 + 1] - | q2 : int(1..2)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3] = false -> x_ExplicitVarSizeWithFlags_Values[q3] = 1 | q3 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q4] | q4 : int(1..2)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q5]) | q5 : int(1..3)]) <= 3, - and([x_ExplicitVarSizeWithFlags_Flags[q8] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q8]] | q8 : int(1..3)]), - and([x_Occurrence[q9] -> - or([x_ExplicitVarSizeWithFlags_Flags[q11] /\ x_ExplicitVarSizeWithFlags_Values[q11] = q9 | q11 : int(1..3)]) - | q9 : int(1..3)]) - diff --git a/tests/exhaustive/basic/set04/expected/model_1_2_1-solution000001.solution b/tests/exhaustive/basic/set04/expected/model_1_2_1-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_1_2_1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set04/expected/model_1_2_1-solution000002.solution b/tests/exhaustive/basic/set04/expected/model_1_2_1-solution000002.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_1_2_1-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/set04/expected/model_1_2_1.eprime b/tests/exhaustive/basic/set04/expected/model_1_2_1.eprime deleted file mode 100644 index f3b700efaf..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_1_2_1.eprime +++ /dev/null @@ -1,18 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1..3)] of bool -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..3)] of int(1..4) -branching on [x_ExplicitVarSizeWithDummy, x_Occurrence] -such that - x_Occurrence[1], - or([x_ExplicitVarSizeWithDummy[q12] != 4 /\ x_ExplicitVarSizeWithDummy[q12] = 2 | q12 : int(1..3)]), - sum([toInt(x_Occurrence[q1]) | q1 : int(1..3)]) <= 3, - and([x_ExplicitVarSizeWithDummy[q2] < x_ExplicitVarSizeWithDummy[q2 + 1] \/ x_ExplicitVarSizeWithDummy[q2] = 4 - | q2 : int(1..2)]), - and([x_ExplicitVarSizeWithDummy[q3] = 4 -> x_ExplicitVarSizeWithDummy[q3 + 1] = 4 | q3 : int(1..2)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q4] != 4) | q4 : int(1..3)]) <= 3, - and([x_ExplicitVarSizeWithDummy[q7] != 4 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q7]] | q7 : int(1..3)]), - and([x_Occurrence[q8] -> - or([x_ExplicitVarSizeWithDummy[q10] != 4 /\ x_ExplicitVarSizeWithDummy[q10] = q8 | q10 : int(1..3)]) - | q8 : int(1..3)]) - diff --git a/tests/exhaustive/basic/set04/expected/model_1_2_2-solution000001.solution b/tests/exhaustive/basic/set04/expected/model_1_2_2-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_1_2_2-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set04/expected/model_1_2_2-solution000002.solution b/tests/exhaustive/basic/set04/expected/model_1_2_2-solution000002.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_1_2_2-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/set04/expected/model_1_2_2.eprime b/tests/exhaustive/basic/set04/expected/model_1_2_2.eprime deleted file mode 100644 index f3b700efaf..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_1_2_2.eprime +++ /dev/null @@ -1,18 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1..3)] of bool -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..3)] of int(1..4) -branching on [x_ExplicitVarSizeWithDummy, x_Occurrence] -such that - x_Occurrence[1], - or([x_ExplicitVarSizeWithDummy[q12] != 4 /\ x_ExplicitVarSizeWithDummy[q12] = 2 | q12 : int(1..3)]), - sum([toInt(x_Occurrence[q1]) | q1 : int(1..3)]) <= 3, - and([x_ExplicitVarSizeWithDummy[q2] < x_ExplicitVarSizeWithDummy[q2 + 1] \/ x_ExplicitVarSizeWithDummy[q2] = 4 - | q2 : int(1..2)]), - and([x_ExplicitVarSizeWithDummy[q3] = 4 -> x_ExplicitVarSizeWithDummy[q3 + 1] = 4 | q3 : int(1..2)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q4] != 4) | q4 : int(1..3)]) <= 3, - and([x_ExplicitVarSizeWithDummy[q7] != 4 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q7]] | q7 : int(1..3)]), - and([x_Occurrence[q8] -> - or([x_ExplicitVarSizeWithDummy[q10] != 4 /\ x_ExplicitVarSizeWithDummy[q10] = q8 | q10 : int(1..3)]) - | q8 : int(1..3)]) - diff --git a/tests/exhaustive/basic/set04/expected/model_1_2_3-solution000001.solution b/tests/exhaustive/basic/set04/expected/model_1_2_3-solution000001.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_1_2_3-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/set04/expected/model_1_2_3-solution000002.solution b/tests/exhaustive/basic/set04/expected/model_1_2_3-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_1_2_3-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set04/expected/model_1_2_3.eprime b/tests/exhaustive/basic/set04/expected/model_1_2_3.eprime deleted file mode 100644 index 72080d2343..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_1_2_3.eprime +++ /dev/null @@ -1,42 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1..3)] of bool -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..3)] of int(1..4) -find x_ExplicitVarSizeWithMarker_Marker: int(0..3) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3)] of int(1..3) -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_Occurrence, x_ExplicitVarSizeWithDummy] -such that - x_Occurrence[1], - or([x_ExplicitVarSizeWithDummy[q28] != 4 /\ x_ExplicitVarSizeWithDummy[q28] = 2 | q28 : int(1..3)]), - sum([toInt(x_Occurrence[q1]) | q1 : int(1..3)]) <= 3, - and([x_ExplicitVarSizeWithDummy[q2] < x_ExplicitVarSizeWithDummy[q2 + 1] \/ x_ExplicitVarSizeWithDummy[q2] = 4 - | q2 : int(1..2)]), - and([x_ExplicitVarSizeWithDummy[q3] = 4 -> x_ExplicitVarSizeWithDummy[q3 + 1] = 4 | q3 : int(1..2)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q4] != 4) | q4 : int(1..3)]) <= 3, - and([x_ExplicitVarSizeWithDummy[q7] != 4 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q7]] | q7 : int(1..3)]), - and([x_Occurrence[q8] -> - or([x_ExplicitVarSizeWithDummy[q10] != 4 /\ x_ExplicitVarSizeWithDummy[q10] = q8 | q10 : int(1..3)]) - | q8 : int(1..3)]), - and([q11 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q11] < x_ExplicitVarSizeWithMarker_Values[q11 + 1] - | q11 : int(1..2)]), - and([q12 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q12] = 1 | q12 : int(1..3)]), - x_ExplicitVarSizeWithMarker_Marker <= 3, - and([q15 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q15]] - | q15 : int(1..3)]), - and([x_Occurrence[q16] -> - or([q18 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q18] = q16 - | q18 : int(1..3)]) - | q16 : int(1..3)]), - and([q20 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q22] != 4 /\ - x_ExplicitVarSizeWithDummy[q22] = x_ExplicitVarSizeWithMarker_Values[q20] - | q22 : int(1..3)]) - | q20 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q24] != 4 -> - or([q26 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q26] = x_ExplicitVarSizeWithDummy[q24] - | q26 : int(1..3)]) - | q24 : int(1..3)]) - diff --git a/tests/exhaustive/basic/set04/expected/model_1_2_4-solution000001.solution b/tests/exhaustive/basic/set04/expected/model_1_2_4-solution000001.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_1_2_4-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/set04/expected/model_1_2_4-solution000002.solution b/tests/exhaustive/basic/set04/expected/model_1_2_4-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_1_2_4-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set04/expected/model_1_2_4.eprime b/tests/exhaustive/basic/set04/expected/model_1_2_4.eprime deleted file mode 100644 index 245f216d5c..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_1_2_4.eprime +++ /dev/null @@ -1,43 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1..3)] of bool -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..3)] of int(1..4) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..3)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3)] of int(1..3) -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_Occurrence, x_ExplicitVarSizeWithDummy] -such that - x_Occurrence[1], - or([x_ExplicitVarSizeWithDummy[q30] != 4 /\ x_ExplicitVarSizeWithDummy[q30] = 2 | q30 : int(1..3)]), - sum([toInt(x_Occurrence[q1]) | q1 : int(1..3)]) <= 3, - and([x_ExplicitVarSizeWithDummy[q2] < x_ExplicitVarSizeWithDummy[q2 + 1] \/ x_ExplicitVarSizeWithDummy[q2] = 4 - | q2 : int(1..2)]), - and([x_ExplicitVarSizeWithDummy[q3] = 4 -> x_ExplicitVarSizeWithDummy[q3 + 1] = 4 | q3 : int(1..2)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q4] != 4) | q4 : int(1..3)]) <= 3, - and([x_ExplicitVarSizeWithDummy[q7] != 4 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q7]] | q7 : int(1..3)]), - and([x_Occurrence[q8] -> - or([x_ExplicitVarSizeWithDummy[q10] != 4 /\ x_ExplicitVarSizeWithDummy[q10] = q8 | q10 : int(1..3)]) - | q8 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q11 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q11] < x_ExplicitVarSizeWithFlags_Values[q11 + 1] - | q11 : int(1..2)]), - and([x_ExplicitVarSizeWithFlags_Flags[q12] = false -> x_ExplicitVarSizeWithFlags_Values[q12] = 1 - | q12 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q13 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q13] | q13 : int(1..2)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q14]) | q14 : int(1..3)]) <= 3, - and([x_ExplicitVarSizeWithFlags_Flags[q17] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q17]] - | q17 : int(1..3)]), - and([x_Occurrence[q18] -> - or([x_ExplicitVarSizeWithFlags_Flags[q20] /\ x_ExplicitVarSizeWithFlags_Values[q20] = q18 | q20 : int(1..3)]) - | q18 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q22] -> - or([x_ExplicitVarSizeWithDummy[q24] != 4 /\ - x_ExplicitVarSizeWithDummy[q24] = x_ExplicitVarSizeWithFlags_Values[q22] - | q24 : int(1..3)]) - | q22 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q26] != 4 -> - or([x_ExplicitVarSizeWithFlags_Flags[q28] /\ - x_ExplicitVarSizeWithFlags_Values[q28] = x_ExplicitVarSizeWithDummy[q26] - | q28 : int(1..3)]) - | q26 : int(1..3)]) - diff --git a/tests/exhaustive/basic/set04/expected/model_1_3_1-solution000001.solution b/tests/exhaustive/basic/set04/expected/model_1_3_1-solution000001.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_1_3_1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/set04/expected/model_1_3_1-solution000002.solution b/tests/exhaustive/basic/set04/expected/model_1_3_1-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_1_3_1-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set04/expected/model_1_3_1.eprime b/tests/exhaustive/basic/set04/expected/model_1_3_1.eprime deleted file mode 100644 index 567ac8830a..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_1_3_1.eprime +++ /dev/null @@ -1,21 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1..3)] of bool -find x_ExplicitVarSizeWithMarker_Marker: int(0..3) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3)] of int(1..3) -branching on [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_Occurrence] -such that - x_Occurrence[1], - or([q11 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q11] = 2 | q11 : int(1..3)]), - sum([toInt(x_Occurrence[q1]) | q1 : int(1..3)]) <= 3, - and([q2 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q2] < x_ExplicitVarSizeWithMarker_Values[q2 + 1] - | q2 : int(1..2)]), - and([q3 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q3] = 1 | q3 : int(1..3)]), - x_ExplicitVarSizeWithMarker_Marker <= 3, - and([q6 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q6]] - | q6 : int(1..3)]), - and([x_Occurrence[q7] -> - or([q9 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q9] = q7 | q9 : int(1..3)]) - | q7 : int(1..3)]) - diff --git a/tests/exhaustive/basic/set04/expected/model_1_3_2-solution000001.solution b/tests/exhaustive/basic/set04/expected/model_1_3_2-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_1_3_2-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set04/expected/model_1_3_2-solution000002.solution b/tests/exhaustive/basic/set04/expected/model_1_3_2-solution000002.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_1_3_2-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/set04/expected/model_1_3_2.eprime b/tests/exhaustive/basic/set04/expected/model_1_3_2.eprime deleted file mode 100644 index 8afee978bf..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_1_3_2.eprime +++ /dev/null @@ -1,41 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1..3)] of bool -find x_ExplicitVarSizeWithMarker_Marker: int(0..3) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3)] of int(1..3) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..3)] of int(1..4) -branching on - [x_ExplicitVarSizeWithDummy, x_Occurrence, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] -such that - x_Occurrence[1], - or([q28 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q28] = 2 | q28 : int(1..3)]), - sum([toInt(x_Occurrence[q1]) | q1 : int(1..3)]) <= 3, - and([q2 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q2] < x_ExplicitVarSizeWithMarker_Values[q2 + 1] - | q2 : int(1..2)]), - and([q3 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q3] = 1 | q3 : int(1..3)]), - x_ExplicitVarSizeWithMarker_Marker <= 3, - and([q6 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q6]] - | q6 : int(1..3)]), - and([x_Occurrence[q7] -> - or([q9 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q9] = q7 | q9 : int(1..3)]) - | q7 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q10] < x_ExplicitVarSizeWithDummy[q10 + 1] \/ x_ExplicitVarSizeWithDummy[q10] = 4 - | q10 : int(1..2)]), - and([x_ExplicitVarSizeWithDummy[q11] = 4 -> x_ExplicitVarSizeWithDummy[q11 + 1] = 4 | q11 : int(1..2)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q12] != 4) | q12 : int(1..3)]) <= 3, - and([x_ExplicitVarSizeWithDummy[q15] != 4 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q15]] | q15 : int(1..3)]), - and([x_Occurrence[q16] -> - or([x_ExplicitVarSizeWithDummy[q18] != 4 /\ x_ExplicitVarSizeWithDummy[q18] = q16 | q18 : int(1..3)]) - | q16 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q20] != 4 -> - or([q22 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q22] = x_ExplicitVarSizeWithDummy[q20] - | q22 : int(1..3)]) - | q20 : int(1..3)]), - and([q24 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q26] != 4 /\ - x_ExplicitVarSizeWithDummy[q26] = x_ExplicitVarSizeWithMarker_Values[q24] - | q26 : int(1..3)]) - | q24 : int(1..3)]) - diff --git a/tests/exhaustive/basic/set04/expected/model_1_3_3-solution000001.solution b/tests/exhaustive/basic/set04/expected/model_1_3_3-solution000001.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_1_3_3-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/set04/expected/model_1_3_3-solution000002.solution b/tests/exhaustive/basic/set04/expected/model_1_3_3-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_1_3_3-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set04/expected/model_1_3_3.eprime b/tests/exhaustive/basic/set04/expected/model_1_3_3.eprime deleted file mode 100644 index 567ac8830a..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_1_3_3.eprime +++ /dev/null @@ -1,21 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1..3)] of bool -find x_ExplicitVarSizeWithMarker_Marker: int(0..3) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3)] of int(1..3) -branching on [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_Occurrence] -such that - x_Occurrence[1], - or([q11 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q11] = 2 | q11 : int(1..3)]), - sum([toInt(x_Occurrence[q1]) | q1 : int(1..3)]) <= 3, - and([q2 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q2] < x_ExplicitVarSizeWithMarker_Values[q2 + 1] - | q2 : int(1..2)]), - and([q3 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q3] = 1 | q3 : int(1..3)]), - x_ExplicitVarSizeWithMarker_Marker <= 3, - and([q6 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q6]] - | q6 : int(1..3)]), - and([x_Occurrence[q7] -> - or([q9 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q9] = q7 | q9 : int(1..3)]) - | q7 : int(1..3)]) - diff --git a/tests/exhaustive/basic/set04/expected/model_1_3_4-solution000001.solution b/tests/exhaustive/basic/set04/expected/model_1_3_4-solution000001.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_1_3_4-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/set04/expected/model_1_3_4-solution000002.solution b/tests/exhaustive/basic/set04/expected/model_1_3_4-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_1_3_4-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set04/expected/model_1_3_4.eprime b/tests/exhaustive/basic/set04/expected/model_1_3_4.eprime deleted file mode 100644 index 6d2bd5ff5b..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_1_3_4.eprime +++ /dev/null @@ -1,47 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1..3)] of bool -find x_ExplicitVarSizeWithMarker_Marker: int(0..3) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3)] of int(1..3) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..3)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3)] of int(1..3) -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_Occurrence, - x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] -such that - x_Occurrence[1], - or([q29 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q29] = 2 | q29 : int(1..3)]), - sum([toInt(x_Occurrence[q1]) | q1 : int(1..3)]) <= 3, - and([q2 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q2] < x_ExplicitVarSizeWithMarker_Values[q2 + 1] - | q2 : int(1..2)]), - and([q3 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q3] = 1 | q3 : int(1..3)]), - x_ExplicitVarSizeWithMarker_Marker <= 3, - and([q6 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q6]] - | q6 : int(1..3)]), - and([x_Occurrence[q7] -> - or([q9 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q9] = q7 | q9 : int(1..3)]) - | q7 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q10 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q10] < x_ExplicitVarSizeWithFlags_Values[q10 + 1] - | q10 : int(1..2)]), - and([x_ExplicitVarSizeWithFlags_Flags[q11] = false -> x_ExplicitVarSizeWithFlags_Values[q11] = 1 - | q11 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q12 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q12] | q12 : int(1..2)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q13]) | q13 : int(1..3)]) <= 3, - and([x_ExplicitVarSizeWithFlags_Flags[q16] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q16]] - | q16 : int(1..3)]), - and([x_Occurrence[q17] -> - or([x_ExplicitVarSizeWithFlags_Flags[q19] /\ x_ExplicitVarSizeWithFlags_Values[q19] = q17 | q19 : int(1..3)]) - | q17 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q21] -> - or([q23 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q23] = x_ExplicitVarSizeWithFlags_Values[q21] - | q23 : int(1..3)]) - | q21 : int(1..3)]), - and([q25 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q27] /\ - x_ExplicitVarSizeWithFlags_Values[q27] = x_ExplicitVarSizeWithMarker_Values[q25] - | q27 : int(1..3)]) - | q25 : int(1..3)]) - diff --git a/tests/exhaustive/basic/set04/expected/model_1_4_1-solution000001.solution b/tests/exhaustive/basic/set04/expected/model_1_4_1-solution000001.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_1_4_1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/set04/expected/model_1_4_1-solution000002.solution b/tests/exhaustive/basic/set04/expected/model_1_4_1-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_1_4_1-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set04/expected/model_1_4_1.eprime b/tests/exhaustive/basic/set04/expected/model_1_4_1.eprime deleted file mode 100644 index 5915d91c83..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_1_4_1.eprime +++ /dev/null @@ -1,21 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1..3)] of bool -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..3)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3)] of int(1..3) -branching on [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_Occurrence] -such that - x_Occurrence[1], - or([x_ExplicitVarSizeWithFlags_Flags[q13] /\ x_ExplicitVarSizeWithFlags_Values[q13] = 2 | q13 : int(1..3)]), - sum([toInt(x_Occurrence[q1]) | q1 : int(1..3)]) <= 3, - and([x_ExplicitVarSizeWithFlags_Flags[q2 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q2] < x_ExplicitVarSizeWithFlags_Values[q2 + 1] - | q2 : int(1..2)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3] = false -> x_ExplicitVarSizeWithFlags_Values[q3] = 1 | q3 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q4] | q4 : int(1..2)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q5]) | q5 : int(1..3)]) <= 3, - and([x_ExplicitVarSizeWithFlags_Flags[q8] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q8]] | q8 : int(1..3)]), - and([x_Occurrence[q9] -> - or([x_ExplicitVarSizeWithFlags_Flags[q11] /\ x_ExplicitVarSizeWithFlags_Values[q11] = q9 | q11 : int(1..3)]) - | q9 : int(1..3)]) - diff --git a/tests/exhaustive/basic/set04/expected/model_1_4_2-solution000001.solution b/tests/exhaustive/basic/set04/expected/model_1_4_2-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_1_4_2-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set04/expected/model_1_4_2-solution000002.solution b/tests/exhaustive/basic/set04/expected/model_1_4_2-solution000002.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_1_4_2-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/set04/expected/model_1_4_2.eprime b/tests/exhaustive/basic/set04/expected/model_1_4_2.eprime deleted file mode 100644 index 2b37e1dd5a..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_1_4_2.eprime +++ /dev/null @@ -1,41 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1..3)] of bool -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..3)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3)] of int(1..3) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..3)] of int(1..4) -branching on - [x_ExplicitVarSizeWithDummy, x_Occurrence, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] -such that - x_Occurrence[1], - or([x_ExplicitVarSizeWithFlags_Flags[q30] /\ x_ExplicitVarSizeWithFlags_Values[q30] = 2 | q30 : int(1..3)]), - sum([toInt(x_Occurrence[q1]) | q1 : int(1..3)]) <= 3, - and([x_ExplicitVarSizeWithFlags_Flags[q2 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q2] < x_ExplicitVarSizeWithFlags_Values[q2 + 1] - | q2 : int(1..2)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3] = false -> x_ExplicitVarSizeWithFlags_Values[q3] = 1 | q3 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q4] | q4 : int(1..2)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q5]) | q5 : int(1..3)]) <= 3, - and([x_ExplicitVarSizeWithFlags_Flags[q8] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q8]] | q8 : int(1..3)]), - and([x_Occurrence[q9] -> - or([x_ExplicitVarSizeWithFlags_Flags[q11] /\ x_ExplicitVarSizeWithFlags_Values[q11] = q9 | q11 : int(1..3)]) - | q9 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q12] < x_ExplicitVarSizeWithDummy[q12 + 1] \/ x_ExplicitVarSizeWithDummy[q12] = 4 - | q12 : int(1..2)]), - and([x_ExplicitVarSizeWithDummy[q13] = 4 -> x_ExplicitVarSizeWithDummy[q13 + 1] = 4 | q13 : int(1..2)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q14] != 4) | q14 : int(1..3)]) <= 3, - and([x_ExplicitVarSizeWithDummy[q17] != 4 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q17]] | q17 : int(1..3)]), - and([x_Occurrence[q18] -> - or([x_ExplicitVarSizeWithDummy[q20] != 4 /\ x_ExplicitVarSizeWithDummy[q20] = q18 | q20 : int(1..3)]) - | q18 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q22] != 4 -> - or([x_ExplicitVarSizeWithFlags_Flags[q24] /\ - x_ExplicitVarSizeWithFlags_Values[q24] = x_ExplicitVarSizeWithDummy[q22] - | q24 : int(1..3)]) - | q22 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q26] -> - or([x_ExplicitVarSizeWithDummy[q28] != 4 /\ - x_ExplicitVarSizeWithDummy[q28] = x_ExplicitVarSizeWithFlags_Values[q26] - | q28 : int(1..3)]) - | q26 : int(1..3)]) - diff --git a/tests/exhaustive/basic/set04/expected/model_1_4_3-solution000001.solution b/tests/exhaustive/basic/set04/expected/model_1_4_3-solution000001.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_1_4_3-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/set04/expected/model_1_4_3-solution000002.solution b/tests/exhaustive/basic/set04/expected/model_1_4_3-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_1_4_3-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set04/expected/model_1_4_3.eprime b/tests/exhaustive/basic/set04/expected/model_1_4_3.eprime deleted file mode 100644 index df30a96b17..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_1_4_3.eprime +++ /dev/null @@ -1,46 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1..3)] of bool -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..3)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3)] of int(1..3) -find x_ExplicitVarSizeWithMarker_Marker: int(0..3) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3)] of int(1..3) -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_Occurrence, - x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] -such that - x_Occurrence[1], - or([x_ExplicitVarSizeWithFlags_Flags[q29] /\ x_ExplicitVarSizeWithFlags_Values[q29] = 2 | q29 : int(1..3)]), - sum([toInt(x_Occurrence[q1]) | q1 : int(1..3)]) <= 3, - and([x_ExplicitVarSizeWithFlags_Flags[q2 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q2] < x_ExplicitVarSizeWithFlags_Values[q2 + 1] - | q2 : int(1..2)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3] = false -> x_ExplicitVarSizeWithFlags_Values[q3] = 1 | q3 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q4] | q4 : int(1..2)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q5]) | q5 : int(1..3)]) <= 3, - and([x_ExplicitVarSizeWithFlags_Flags[q8] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q8]] | q8 : int(1..3)]), - and([x_Occurrence[q9] -> - or([x_ExplicitVarSizeWithFlags_Flags[q11] /\ x_ExplicitVarSizeWithFlags_Values[q11] = q9 | q11 : int(1..3)]) - | q9 : int(1..3)]), - and([q12 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q12] < x_ExplicitVarSizeWithMarker_Values[q12 + 1] - | q12 : int(1..2)]), - and([q13 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q13] = 1 | q13 : int(1..3)]), - x_ExplicitVarSizeWithMarker_Marker <= 3, - and([q16 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q16]] - | q16 : int(1..3)]), - and([x_Occurrence[q17] -> - or([q19 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q19] = q17 - | q19 : int(1..3)]) - | q17 : int(1..3)]), - and([q21 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q23] /\ - x_ExplicitVarSizeWithFlags_Values[q23] = x_ExplicitVarSizeWithMarker_Values[q21] - | q23 : int(1..3)]) - | q21 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q25] -> - or([q27 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q27] = x_ExplicitVarSizeWithFlags_Values[q25] - | q27 : int(1..3)]) - | q25 : int(1..3)]) - diff --git a/tests/exhaustive/basic/set04/expected/model_1_4_4-solution000001.solution b/tests/exhaustive/basic/set04/expected/model_1_4_4-solution000001.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_1_4_4-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/set04/expected/model_1_4_4-solution000002.solution b/tests/exhaustive/basic/set04/expected/model_1_4_4-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_1_4_4-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set04/expected/model_1_4_4.eprime b/tests/exhaustive/basic/set04/expected/model_1_4_4.eprime deleted file mode 100644 index 5915d91c83..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_1_4_4.eprime +++ /dev/null @@ -1,21 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1..3)] of bool -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..3)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3)] of int(1..3) -branching on [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_Occurrence] -such that - x_Occurrence[1], - or([x_ExplicitVarSizeWithFlags_Flags[q13] /\ x_ExplicitVarSizeWithFlags_Values[q13] = 2 | q13 : int(1..3)]), - sum([toInt(x_Occurrence[q1]) | q1 : int(1..3)]) <= 3, - and([x_ExplicitVarSizeWithFlags_Flags[q2 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q2] < x_ExplicitVarSizeWithFlags_Values[q2 + 1] - | q2 : int(1..2)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3] = false -> x_ExplicitVarSizeWithFlags_Values[q3] = 1 | q3 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q4] | q4 : int(1..2)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q5]) | q5 : int(1..3)]) <= 3, - and([x_ExplicitVarSizeWithFlags_Flags[q8] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q8]] | q8 : int(1..3)]), - and([x_Occurrence[q9] -> - or([x_ExplicitVarSizeWithFlags_Flags[q11] /\ x_ExplicitVarSizeWithFlags_Values[q11] = q9 | q11 : int(1..3)]) - | q9 : int(1..3)]) - diff --git a/tests/exhaustive/basic/set04/expected/model_2_1_1-solution000001.solution b/tests/exhaustive/basic/set04/expected/model_2_1_1-solution000001.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_2_1_1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/set04/expected/model_2_1_1-solution000002.solution b/tests/exhaustive/basic/set04/expected/model_2_1_1-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_2_1_1-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set04/expected/model_2_1_1.eprime b/tests/exhaustive/basic/set04/expected/model_2_1_1.eprime deleted file mode 100644 index 3f095c1e18..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_2_1_1.eprime +++ /dev/null @@ -1,18 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..3)] of int(1..4) -find x_Occurrence: matrix indexed by [int(1..3)] of bool -branching on [x_Occurrence, x_ExplicitVarSizeWithDummy] -such that - or([x_ExplicitVarSizeWithDummy[q12] != 4 /\ x_ExplicitVarSizeWithDummy[q12] = 1 | q12 : int(1..3)]), - x_Occurrence[2], - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 4 - | q1 : int(1..2)]), - and([x_ExplicitVarSizeWithDummy[q2] = 4 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 4 | q2 : int(1..2)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 4) | q3 : int(1..3)]) <= 3, - sum([toInt(x_Occurrence[q5]) | q5 : int(1..3)]) <= 3, - and([x_Occurrence[q6] -> - or([x_ExplicitVarSizeWithDummy[q8] != 4 /\ x_ExplicitVarSizeWithDummy[q8] = q6 | q8 : int(1..3)]) - | q6 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q10] != 4 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q10]] | q10 : int(1..3)]) - diff --git a/tests/exhaustive/basic/set04/expected/model_2_1_2-solution000001.solution b/tests/exhaustive/basic/set04/expected/model_2_1_2-solution000001.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_2_1_2-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/set04/expected/model_2_1_2-solution000002.solution b/tests/exhaustive/basic/set04/expected/model_2_1_2-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_2_1_2-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set04/expected/model_2_1_2.eprime b/tests/exhaustive/basic/set04/expected/model_2_1_2.eprime deleted file mode 100644 index 3f095c1e18..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_2_1_2.eprime +++ /dev/null @@ -1,18 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..3)] of int(1..4) -find x_Occurrence: matrix indexed by [int(1..3)] of bool -branching on [x_Occurrence, x_ExplicitVarSizeWithDummy] -such that - or([x_ExplicitVarSizeWithDummy[q12] != 4 /\ x_ExplicitVarSizeWithDummy[q12] = 1 | q12 : int(1..3)]), - x_Occurrence[2], - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 4 - | q1 : int(1..2)]), - and([x_ExplicitVarSizeWithDummy[q2] = 4 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 4 | q2 : int(1..2)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 4) | q3 : int(1..3)]) <= 3, - sum([toInt(x_Occurrence[q5]) | q5 : int(1..3)]) <= 3, - and([x_Occurrence[q6] -> - or([x_ExplicitVarSizeWithDummy[q8] != 4 /\ x_ExplicitVarSizeWithDummy[q8] = q6 | q8 : int(1..3)]) - | q6 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q10] != 4 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q10]] | q10 : int(1..3)]) - diff --git a/tests/exhaustive/basic/set04/expected/model_2_1_3-solution000001.solution b/tests/exhaustive/basic/set04/expected/model_2_1_3-solution000001.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_2_1_3-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/set04/expected/model_2_1_3-solution000002.solution b/tests/exhaustive/basic/set04/expected/model_2_1_3-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_2_1_3-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set04/expected/model_2_1_3.eprime b/tests/exhaustive/basic/set04/expected/model_2_1_3.eprime deleted file mode 100644 index c0e6fb3f20..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_2_1_3.eprime +++ /dev/null @@ -1,42 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..3)] of int(1..4) -find x_Occurrence: matrix indexed by [int(1..3)] of bool -find x_ExplicitVarSizeWithMarker_Marker: int(0..3) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3)] of int(1..3) -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy, x_Occurrence] -such that - or([x_ExplicitVarSizeWithDummy[q28] != 4 /\ x_ExplicitVarSizeWithDummy[q28] = 1 | q28 : int(1..3)]), - x_Occurrence[2], - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 4 - | q1 : int(1..2)]), - and([x_ExplicitVarSizeWithDummy[q2] = 4 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 4 | q2 : int(1..2)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 4) | q3 : int(1..3)]) <= 3, - sum([toInt(x_Occurrence[q5]) | q5 : int(1..3)]) <= 3, - and([x_Occurrence[q22] -> - or([x_ExplicitVarSizeWithDummy[q24] != 4 /\ x_ExplicitVarSizeWithDummy[q24] = q22 | q24 : int(1..3)]) - | q22 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q26] != 4 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q26]] | q26 : int(1..3)]), - and([q6 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q6] < x_ExplicitVarSizeWithMarker_Values[q6 + 1] - | q6 : int(1..2)]), - and([q7 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q7] = 1 | q7 : int(1..3)]), - x_ExplicitVarSizeWithMarker_Marker <= 3, - and([q10 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q12] != 4 /\ - x_ExplicitVarSizeWithDummy[q12] = x_ExplicitVarSizeWithMarker_Values[q10] - | q12 : int(1..3)]) - | q10 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q14] != 4 -> - or([q16 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q16] = x_ExplicitVarSizeWithDummy[q14] - | q16 : int(1..3)]) - | q14 : int(1..3)]), - and([q18 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q18]] - | q18 : int(1..3)]), - and([x_Occurrence[q19] -> - or([q21 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q21] = q19 - | q21 : int(1..3)]) - | q19 : int(1..3)]) - diff --git a/tests/exhaustive/basic/set04/expected/model_2_1_4-solution000001.solution b/tests/exhaustive/basic/set04/expected/model_2_1_4-solution000001.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_2_1_4-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/set04/expected/model_2_1_4-solution000002.solution b/tests/exhaustive/basic/set04/expected/model_2_1_4-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_2_1_4-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set04/expected/model_2_1_4.eprime b/tests/exhaustive/basic/set04/expected/model_2_1_4.eprime deleted file mode 100644 index 5636e1d31f..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_2_1_4.eprime +++ /dev/null @@ -1,42 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..3)] of int(1..4) -find x_Occurrence: matrix indexed by [int(1..3)] of bool -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..3)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3)] of int(1..3) -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy, x_Occurrence] -such that - or([x_ExplicitVarSizeWithDummy[q30] != 4 /\ x_ExplicitVarSizeWithDummy[q30] = 1 | q30 : int(1..3)]), - x_Occurrence[2], - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 4 - | q1 : int(1..2)]), - and([x_ExplicitVarSizeWithDummy[q2] = 4 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 4 | q2 : int(1..2)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 4) | q3 : int(1..3)]) <= 3, - sum([toInt(x_Occurrence[q5]) | q5 : int(1..3)]) <= 3, - and([x_Occurrence[q24] -> - or([x_ExplicitVarSizeWithDummy[q26] != 4 /\ x_ExplicitVarSizeWithDummy[q26] = q24 | q26 : int(1..3)]) - | q24 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q28] != 4 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q28]] | q28 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q6] < x_ExplicitVarSizeWithFlags_Values[q6 + 1] - | q6 : int(1..2)]), - and([x_ExplicitVarSizeWithFlags_Flags[q7] = false -> x_ExplicitVarSizeWithFlags_Values[q7] = 1 | q7 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q8 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q8] | q8 : int(1..2)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q9]) | q9 : int(1..3)]) <= 3, - and([x_ExplicitVarSizeWithFlags_Flags[q12] -> - or([x_ExplicitVarSizeWithDummy[q14] != 4 /\ - x_ExplicitVarSizeWithDummy[q14] = x_ExplicitVarSizeWithFlags_Values[q12] - | q14 : int(1..3)]) - | q12 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q16] != 4 -> - or([x_ExplicitVarSizeWithFlags_Flags[q18] /\ - x_ExplicitVarSizeWithFlags_Values[q18] = x_ExplicitVarSizeWithDummy[q16] - | q18 : int(1..3)]) - | q16 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q20] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q20]] - | q20 : int(1..3)]), - and([x_Occurrence[q21] -> - or([x_ExplicitVarSizeWithFlags_Flags[q23] /\ x_ExplicitVarSizeWithFlags_Values[q23] = q21 | q23 : int(1..3)]) - | q21 : int(1..3)]) - diff --git a/tests/exhaustive/basic/set04/expected/model_2_2_1-solution000001.solution b/tests/exhaustive/basic/set04/expected/model_2_2_1-solution000001.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_2_2_1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/set04/expected/model_2_2_1-solution000002.solution b/tests/exhaustive/basic/set04/expected/model_2_2_1-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_2_2_1-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set04/expected/model_2_2_1.eprime b/tests/exhaustive/basic/set04/expected/model_2_2_1.eprime deleted file mode 100644 index ab9e099117..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_2_2_1.eprime +++ /dev/null @@ -1,18 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..3)] of int(1..4) -find x_Occurrence: matrix indexed by [int(1..3)] of bool -branching on [x_Occurrence, x_ExplicitVarSizeWithDummy] -such that - or([x_ExplicitVarSizeWithDummy[q12] != 4 /\ x_ExplicitVarSizeWithDummy[q12] = 1 | q12 : int(1..3)]), - or([x_ExplicitVarSizeWithDummy[q14] != 4 /\ x_ExplicitVarSizeWithDummy[q14] = 2 | q14 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 4 - | q1 : int(1..2)]), - and([x_ExplicitVarSizeWithDummy[q2] = 4 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 4 | q2 : int(1..2)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 4) | q3 : int(1..3)]) <= 3, - sum([toInt(x_Occurrence[q5]) | q5 : int(1..3)]) <= 3, - and([x_Occurrence[q6] -> - or([x_ExplicitVarSizeWithDummy[q8] != 4 /\ x_ExplicitVarSizeWithDummy[q8] = q6 | q8 : int(1..3)]) - | q6 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q10] != 4 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q10]] | q10 : int(1..3)]) - diff --git a/tests/exhaustive/basic/set04/expected/model_2_2_2-solution000001.solution b/tests/exhaustive/basic/set04/expected/model_2_2_2-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_2_2_2-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set04/expected/model_2_2_2-solution000002.solution b/tests/exhaustive/basic/set04/expected/model_2_2_2-solution000002.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_2_2_2-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/set04/expected/model_2_2_2.eprime b/tests/exhaustive/basic/set04/expected/model_2_2_2.eprime deleted file mode 100644 index 6f4df0cbd5..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_2_2_2.eprime +++ /dev/null @@ -1,12 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..3)] of int(1..4) -branching on [x_ExplicitVarSizeWithDummy] -such that - or([x_ExplicitVarSizeWithDummy[q6] != 4 /\ x_ExplicitVarSizeWithDummy[q6] = 1 | q6 : int(1..3)]), - or([x_ExplicitVarSizeWithDummy[q8] != 4 /\ x_ExplicitVarSizeWithDummy[q8] = 2 | q8 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 4 - | q1 : int(1..2)]), - and([x_ExplicitVarSizeWithDummy[q2] = 4 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 4 | q2 : int(1..2)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 4) | q3 : int(1..3)]) <= 3 - diff --git a/tests/exhaustive/basic/set04/expected/model_2_2_3-solution000001.solution b/tests/exhaustive/basic/set04/expected/model_2_2_3-solution000001.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_2_2_3-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/set04/expected/model_2_2_3-solution000002.solution b/tests/exhaustive/basic/set04/expected/model_2_2_3-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_2_2_3-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set04/expected/model_2_2_3.eprime b/tests/exhaustive/basic/set04/expected/model_2_2_3.eprime deleted file mode 100644 index 047d06d041..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_2_2_3.eprime +++ /dev/null @@ -1,29 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..3)] of int(1..4) -find x_ExplicitVarSizeWithMarker_Marker: int(0..3) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3)] of int(1..3) -branching on [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy] -such that - or([x_ExplicitVarSizeWithDummy[q17] != 4 /\ x_ExplicitVarSizeWithDummy[q17] = 1 | q17 : int(1..3)]), - or([x_ExplicitVarSizeWithDummy[q19] != 4 /\ x_ExplicitVarSizeWithDummy[q19] = 2 | q19 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 4 - | q1 : int(1..2)]), - and([x_ExplicitVarSizeWithDummy[q2] = 4 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 4 | q2 : int(1..2)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 4) | q3 : int(1..3)]) <= 3, - and([q5 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q5] < x_ExplicitVarSizeWithMarker_Values[q5 + 1] - | q5 : int(1..2)]), - and([q6 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q6] = 1 | q6 : int(1..3)]), - x_ExplicitVarSizeWithMarker_Marker <= 3, - and([q9 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q11] != 4 /\ - x_ExplicitVarSizeWithDummy[q11] = x_ExplicitVarSizeWithMarker_Values[q9] - | q11 : int(1..3)]) - | q9 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q13] != 4 -> - or([q15 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q15] = x_ExplicitVarSizeWithDummy[q13] - | q15 : int(1..3)]) - | q13 : int(1..3)]) - diff --git a/tests/exhaustive/basic/set04/expected/model_2_2_4-solution000001.solution b/tests/exhaustive/basic/set04/expected/model_2_2_4-solution000001.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_2_2_4-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/set04/expected/model_2_2_4-solution000002.solution b/tests/exhaustive/basic/set04/expected/model_2_2_4-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_2_2_4-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set04/expected/model_2_2_4.eprime b/tests/exhaustive/basic/set04/expected/model_2_2_4.eprime deleted file mode 100644 index 05a8f136b6..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_2_2_4.eprime +++ /dev/null @@ -1,30 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..3)] of int(1..4) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..3)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3)] of int(1..3) -branching on [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy] -such that - or([x_ExplicitVarSizeWithDummy[q19] != 4 /\ x_ExplicitVarSizeWithDummy[q19] = 1 | q19 : int(1..3)]), - or([x_ExplicitVarSizeWithDummy[q21] != 4 /\ x_ExplicitVarSizeWithDummy[q21] = 2 | q21 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 4 - | q1 : int(1..2)]), - and([x_ExplicitVarSizeWithDummy[q2] = 4 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 4 | q2 : int(1..2)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 4) | q3 : int(1..3)]) <= 3, - and([x_ExplicitVarSizeWithFlags_Flags[q5 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q5] < x_ExplicitVarSizeWithFlags_Values[q5 + 1] - | q5 : int(1..2)]), - and([x_ExplicitVarSizeWithFlags_Flags[q6] = false -> x_ExplicitVarSizeWithFlags_Values[q6] = 1 | q6 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q7] | q7 : int(1..2)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q8]) | q8 : int(1..3)]) <= 3, - and([x_ExplicitVarSizeWithFlags_Flags[q11] -> - or([x_ExplicitVarSizeWithDummy[q13] != 4 /\ - x_ExplicitVarSizeWithDummy[q13] = x_ExplicitVarSizeWithFlags_Values[q11] - | q13 : int(1..3)]) - | q11 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q15] != 4 -> - or([x_ExplicitVarSizeWithFlags_Flags[q17] /\ - x_ExplicitVarSizeWithFlags_Values[q17] = x_ExplicitVarSizeWithDummy[q15] - | q17 : int(1..3)]) - | q15 : int(1..3)]) - diff --git a/tests/exhaustive/basic/set04/expected/model_2_3_1-solution000001.solution b/tests/exhaustive/basic/set04/expected/model_2_3_1-solution000001.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_2_3_1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/set04/expected/model_2_3_1-solution000002.solution b/tests/exhaustive/basic/set04/expected/model_2_3_1-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_2_3_1-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set04/expected/model_2_3_1.eprime b/tests/exhaustive/basic/set04/expected/model_2_3_1.eprime deleted file mode 100644 index 9c7150af48..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_2_3_1.eprime +++ /dev/null @@ -1,42 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..3)] of int(1..4) -find x_ExplicitVarSizeWithMarker_Marker: int(0..3) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3)] of int(1..3) -find x_Occurrence: matrix indexed by [int(1..3)] of bool -branching on - [x_Occurrence, x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] -such that - or([x_ExplicitVarSizeWithDummy[q28] != 4 /\ x_ExplicitVarSizeWithDummy[q28] = 1 | q28 : int(1..3)]), - or([q30 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q30] = 2 | q30 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 4 - | q1 : int(1..2)]), - and([x_ExplicitVarSizeWithDummy[q2] = 4 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 4 | q2 : int(1..2)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 4) | q3 : int(1..3)]) <= 3, - and([q5 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q5] < x_ExplicitVarSizeWithMarker_Values[q5 + 1] - | q5 : int(1..2)]), - and([q6 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q6] = 1 | q6 : int(1..3)]), - x_ExplicitVarSizeWithMarker_Marker <= 3, - and([q9 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q11] != 4 /\ - x_ExplicitVarSizeWithDummy[q11] = x_ExplicitVarSizeWithMarker_Values[q9] - | q11 : int(1..3)]) - | q9 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q13] != 4 -> - or([q15 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q15] = x_ExplicitVarSizeWithDummy[q13] - | q15 : int(1..3)]) - | q13 : int(1..3)]), - sum([toInt(x_Occurrence[q16]) | q16 : int(1..3)]) <= 3, - and([x_Occurrence[q17] -> - or([x_ExplicitVarSizeWithDummy[q19] != 4 /\ x_ExplicitVarSizeWithDummy[q19] = q17 | q19 : int(1..3)]) - | q17 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q21] != 4 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q21]] | q21 : int(1..3)]), - and([x_Occurrence[q22] -> - or([q24 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q24] = q22 - | q24 : int(1..3)]) - | q22 : int(1..3)]), - and([q26 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q26]] - | q26 : int(1..3)]) - diff --git a/tests/exhaustive/basic/set04/expected/model_2_3_2-solution000001.solution b/tests/exhaustive/basic/set04/expected/model_2_3_2-solution000001.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_2_3_2-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/set04/expected/model_2_3_2-solution000002.solution b/tests/exhaustive/basic/set04/expected/model_2_3_2-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_2_3_2-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set04/expected/model_2_3_2.eprime b/tests/exhaustive/basic/set04/expected/model_2_3_2.eprime deleted file mode 100644 index 3aa6f1b412..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_2_3_2.eprime +++ /dev/null @@ -1,29 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..3)] of int(1..4) -find x_ExplicitVarSizeWithMarker_Marker: int(0..3) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3)] of int(1..3) -branching on [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy] -such that - or([x_ExplicitVarSizeWithDummy[q17] != 4 /\ x_ExplicitVarSizeWithDummy[q17] = 1 | q17 : int(1..3)]), - or([q19 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q19] = 2 | q19 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 4 - | q1 : int(1..2)]), - and([x_ExplicitVarSizeWithDummy[q2] = 4 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 4 | q2 : int(1..2)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 4) | q3 : int(1..3)]) <= 3, - and([q5 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q5] < x_ExplicitVarSizeWithMarker_Values[q5 + 1] - | q5 : int(1..2)]), - and([q6 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q6] = 1 | q6 : int(1..3)]), - x_ExplicitVarSizeWithMarker_Marker <= 3, - and([q9 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q11] != 4 /\ - x_ExplicitVarSizeWithDummy[q11] = x_ExplicitVarSizeWithMarker_Values[q9] - | q11 : int(1..3)]) - | q9 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q13] != 4 -> - or([q15 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q15] = x_ExplicitVarSizeWithDummy[q13] - | q15 : int(1..3)]) - | q13 : int(1..3)]) - diff --git a/tests/exhaustive/basic/set04/expected/model_2_3_3-solution000001.solution b/tests/exhaustive/basic/set04/expected/model_2_3_3-solution000001.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_2_3_3-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/set04/expected/model_2_3_3-solution000002.solution b/tests/exhaustive/basic/set04/expected/model_2_3_3-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_2_3_3-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set04/expected/model_2_3_3.eprime b/tests/exhaustive/basic/set04/expected/model_2_3_3.eprime deleted file mode 100644 index 3aa6f1b412..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_2_3_3.eprime +++ /dev/null @@ -1,29 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..3)] of int(1..4) -find x_ExplicitVarSizeWithMarker_Marker: int(0..3) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3)] of int(1..3) -branching on [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy] -such that - or([x_ExplicitVarSizeWithDummy[q17] != 4 /\ x_ExplicitVarSizeWithDummy[q17] = 1 | q17 : int(1..3)]), - or([q19 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q19] = 2 | q19 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 4 - | q1 : int(1..2)]), - and([x_ExplicitVarSizeWithDummy[q2] = 4 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 4 | q2 : int(1..2)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 4) | q3 : int(1..3)]) <= 3, - and([q5 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q5] < x_ExplicitVarSizeWithMarker_Values[q5 + 1] - | q5 : int(1..2)]), - and([q6 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q6] = 1 | q6 : int(1..3)]), - x_ExplicitVarSizeWithMarker_Marker <= 3, - and([q9 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q11] != 4 /\ - x_ExplicitVarSizeWithDummy[q11] = x_ExplicitVarSizeWithMarker_Values[q9] - | q11 : int(1..3)]) - | q9 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q13] != 4 -> - or([q15 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q15] = x_ExplicitVarSizeWithDummy[q13] - | q15 : int(1..3)]) - | q13 : int(1..3)]) - diff --git a/tests/exhaustive/basic/set04/expected/model_2_3_4-solution000001.solution b/tests/exhaustive/basic/set04/expected/model_2_3_4-solution000001.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_2_3_4-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/set04/expected/model_2_3_4-solution000002.solution b/tests/exhaustive/basic/set04/expected/model_2_3_4-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_2_3_4-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set04/expected/model_2_3_4.eprime b/tests/exhaustive/basic/set04/expected/model_2_3_4.eprime deleted file mode 100644 index cc9085b2c5..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_2_3_4.eprime +++ /dev/null @@ -1,60 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..3)] of int(1..4) -find x_ExplicitVarSizeWithMarker_Marker: int(0..3) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3)] of int(1..3) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..3)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3)] of int(1..3) -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy, - x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] -such that - or([x_ExplicitVarSizeWithDummy[q38] != 4 /\ x_ExplicitVarSizeWithDummy[q38] = 1 | q38 : int(1..3)]), - or([q40 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q40] = 2 | q40 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 4 - | q1 : int(1..2)]), - and([x_ExplicitVarSizeWithDummy[q2] = 4 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 4 | q2 : int(1..2)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 4) | q3 : int(1..3)]) <= 3, - and([q5 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q5] < x_ExplicitVarSizeWithMarker_Values[q5 + 1] - | q5 : int(1..2)]), - and([q6 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q6] = 1 | q6 : int(1..3)]), - x_ExplicitVarSizeWithMarker_Marker <= 3, - and([q9 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q11] != 4 /\ - x_ExplicitVarSizeWithDummy[q11] = x_ExplicitVarSizeWithMarker_Values[q9] - | q11 : int(1..3)]) - | q9 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q13] != 4 -> - or([q15 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q15] = x_ExplicitVarSizeWithDummy[q13] - | q15 : int(1..3)]) - | q13 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q16 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q16] < x_ExplicitVarSizeWithFlags_Values[q16 + 1] - | q16 : int(1..2)]), - and([x_ExplicitVarSizeWithFlags_Flags[q17] = false -> x_ExplicitVarSizeWithFlags_Values[q17] = 1 - | q17 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q18 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q18] | q18 : int(1..2)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q19]) | q19 : int(1..3)]) <= 3, - and([x_ExplicitVarSizeWithFlags_Flags[q22] -> - or([x_ExplicitVarSizeWithDummy[q24] != 4 /\ - x_ExplicitVarSizeWithDummy[q24] = x_ExplicitVarSizeWithFlags_Values[q22] - | q24 : int(1..3)]) - | q22 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q26] != 4 -> - or([x_ExplicitVarSizeWithFlags_Flags[q28] /\ - x_ExplicitVarSizeWithFlags_Values[q28] = x_ExplicitVarSizeWithDummy[q26] - | q28 : int(1..3)]) - | q26 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q30] -> - or([q32 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q32] = x_ExplicitVarSizeWithFlags_Values[q30] - | q32 : int(1..3)]) - | q30 : int(1..3)]), - and([q34 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q36] /\ - x_ExplicitVarSizeWithFlags_Values[q36] = x_ExplicitVarSizeWithMarker_Values[q34] - | q36 : int(1..3)]) - | q34 : int(1..3)]) - diff --git a/tests/exhaustive/basic/set04/expected/model_2_4_1-solution000001.solution b/tests/exhaustive/basic/set04/expected/model_2_4_1-solution000001.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_2_4_1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/set04/expected/model_2_4_1-solution000002.solution b/tests/exhaustive/basic/set04/expected/model_2_4_1-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_2_4_1-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set04/expected/model_2_4_1.eprime b/tests/exhaustive/basic/set04/expected/model_2_4_1.eprime deleted file mode 100644 index f56d2aa970..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_2_4_1.eprime +++ /dev/null @@ -1,42 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..3)] of int(1..4) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..3)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3)] of int(1..3) -find x_Occurrence: matrix indexed by [int(1..3)] of bool -branching on - [x_Occurrence, x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] -such that - or([x_ExplicitVarSizeWithDummy[q30] != 4 /\ x_ExplicitVarSizeWithDummy[q30] = 1 | q30 : int(1..3)]), - or([x_ExplicitVarSizeWithFlags_Flags[q32] /\ x_ExplicitVarSizeWithFlags_Values[q32] = 2 | q32 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 4 - | q1 : int(1..2)]), - and([x_ExplicitVarSizeWithDummy[q2] = 4 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 4 | q2 : int(1..2)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 4) | q3 : int(1..3)]) <= 3, - and([x_ExplicitVarSizeWithFlags_Flags[q5 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q5] < x_ExplicitVarSizeWithFlags_Values[q5 + 1] - | q5 : int(1..2)]), - and([x_ExplicitVarSizeWithFlags_Flags[q6] = false -> x_ExplicitVarSizeWithFlags_Values[q6] = 1 | q6 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q7] | q7 : int(1..2)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q8]) | q8 : int(1..3)]) <= 3, - and([x_ExplicitVarSizeWithFlags_Flags[q11] -> - or([x_ExplicitVarSizeWithDummy[q13] != 4 /\ - x_ExplicitVarSizeWithDummy[q13] = x_ExplicitVarSizeWithFlags_Values[q11] - | q13 : int(1..3)]) - | q11 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q15] != 4 -> - or([x_ExplicitVarSizeWithFlags_Flags[q17] /\ - x_ExplicitVarSizeWithFlags_Values[q17] = x_ExplicitVarSizeWithDummy[q15] - | q17 : int(1..3)]) - | q15 : int(1..3)]), - sum([toInt(x_Occurrence[q18]) | q18 : int(1..3)]) <= 3, - and([x_Occurrence[q19] -> - or([x_ExplicitVarSizeWithDummy[q21] != 4 /\ x_ExplicitVarSizeWithDummy[q21] = q19 | q21 : int(1..3)]) - | q19 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q23] != 4 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q23]] | q23 : int(1..3)]), - and([x_Occurrence[q24] -> - or([x_ExplicitVarSizeWithFlags_Flags[q26] /\ x_ExplicitVarSizeWithFlags_Values[q26] = q24 | q26 : int(1..3)]) - | q24 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q28] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q28]] - | q28 : int(1..3)]) - diff --git a/tests/exhaustive/basic/set04/expected/model_2_4_2-solution000001.solution b/tests/exhaustive/basic/set04/expected/model_2_4_2-solution000001.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_2_4_2-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/set04/expected/model_2_4_2-solution000002.solution b/tests/exhaustive/basic/set04/expected/model_2_4_2-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_2_4_2-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set04/expected/model_2_4_2.eprime b/tests/exhaustive/basic/set04/expected/model_2_4_2.eprime deleted file mode 100644 index 3e7f4a0be3..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_2_4_2.eprime +++ /dev/null @@ -1,30 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..3)] of int(1..4) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..3)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3)] of int(1..3) -branching on [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy] -such that - or([x_ExplicitVarSizeWithDummy[q19] != 4 /\ x_ExplicitVarSizeWithDummy[q19] = 1 | q19 : int(1..3)]), - or([x_ExplicitVarSizeWithFlags_Flags[q21] /\ x_ExplicitVarSizeWithFlags_Values[q21] = 2 | q21 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 4 - | q1 : int(1..2)]), - and([x_ExplicitVarSizeWithDummy[q2] = 4 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 4 | q2 : int(1..2)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 4) | q3 : int(1..3)]) <= 3, - and([x_ExplicitVarSizeWithFlags_Flags[q5 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q5] < x_ExplicitVarSizeWithFlags_Values[q5 + 1] - | q5 : int(1..2)]), - and([x_ExplicitVarSizeWithFlags_Flags[q6] = false -> x_ExplicitVarSizeWithFlags_Values[q6] = 1 | q6 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q7] | q7 : int(1..2)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q8]) | q8 : int(1..3)]) <= 3, - and([x_ExplicitVarSizeWithFlags_Flags[q11] -> - or([x_ExplicitVarSizeWithDummy[q13] != 4 /\ - x_ExplicitVarSizeWithDummy[q13] = x_ExplicitVarSizeWithFlags_Values[q11] - | q13 : int(1..3)]) - | q11 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q15] != 4 -> - or([x_ExplicitVarSizeWithFlags_Flags[q17] /\ - x_ExplicitVarSizeWithFlags_Values[q17] = x_ExplicitVarSizeWithDummy[q15] - | q17 : int(1..3)]) - | q15 : int(1..3)]) - diff --git a/tests/exhaustive/basic/set04/expected/model_2_4_3-solution000001.solution b/tests/exhaustive/basic/set04/expected/model_2_4_3-solution000001.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_2_4_3-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/set04/expected/model_2_4_3-solution000002.solution b/tests/exhaustive/basic/set04/expected/model_2_4_3-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_2_4_3-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set04/expected/model_2_4_3.eprime b/tests/exhaustive/basic/set04/expected/model_2_4_3.eprime deleted file mode 100644 index 71047bdbd3..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_2_4_3.eprime +++ /dev/null @@ -1,59 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..3)] of int(1..4) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..3)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3)] of int(1..3) -find x_ExplicitVarSizeWithMarker_Marker: int(0..3) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3)] of int(1..3) -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy, - x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] -such that - or([x_ExplicitVarSizeWithDummy[q38] != 4 /\ x_ExplicitVarSizeWithDummy[q38] = 1 | q38 : int(1..3)]), - or([x_ExplicitVarSizeWithFlags_Flags[q40] /\ x_ExplicitVarSizeWithFlags_Values[q40] = 2 | q40 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 4 - | q1 : int(1..2)]), - and([x_ExplicitVarSizeWithDummy[q2] = 4 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 4 | q2 : int(1..2)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 4) | q3 : int(1..3)]) <= 3, - and([x_ExplicitVarSizeWithFlags_Flags[q5 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q5] < x_ExplicitVarSizeWithFlags_Values[q5 + 1] - | q5 : int(1..2)]), - and([x_ExplicitVarSizeWithFlags_Flags[q6] = false -> x_ExplicitVarSizeWithFlags_Values[q6] = 1 | q6 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q7] | q7 : int(1..2)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q8]) | q8 : int(1..3)]) <= 3, - and([x_ExplicitVarSizeWithFlags_Flags[q11] -> - or([x_ExplicitVarSizeWithDummy[q13] != 4 /\ - x_ExplicitVarSizeWithDummy[q13] = x_ExplicitVarSizeWithFlags_Values[q11] - | q13 : int(1..3)]) - | q11 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q15] != 4 -> - or([x_ExplicitVarSizeWithFlags_Flags[q17] /\ - x_ExplicitVarSizeWithFlags_Values[q17] = x_ExplicitVarSizeWithDummy[q15] - | q17 : int(1..3)]) - | q15 : int(1..3)]), - and([q18 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q18] < x_ExplicitVarSizeWithMarker_Values[q18 + 1] - | q18 : int(1..2)]), - and([q19 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q19] = 1 | q19 : int(1..3)]), - x_ExplicitVarSizeWithMarker_Marker <= 3, - and([q22 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q24] != 4 /\ - x_ExplicitVarSizeWithDummy[q24] = x_ExplicitVarSizeWithMarker_Values[q22] - | q24 : int(1..3)]) - | q22 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q26] != 4 -> - or([q28 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q28] = x_ExplicitVarSizeWithDummy[q26] - | q28 : int(1..3)]) - | q26 : int(1..3)]), - and([q30 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q32] /\ - x_ExplicitVarSizeWithFlags_Values[q32] = x_ExplicitVarSizeWithMarker_Values[q30] - | q32 : int(1..3)]) - | q30 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q34] -> - or([q36 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q36] = x_ExplicitVarSizeWithFlags_Values[q34] - | q36 : int(1..3)]) - | q34 : int(1..3)]) - diff --git a/tests/exhaustive/basic/set04/expected/model_2_4_4-solution000001.solution b/tests/exhaustive/basic/set04/expected/model_2_4_4-solution000001.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_2_4_4-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/set04/expected/model_2_4_4-solution000002.solution b/tests/exhaustive/basic/set04/expected/model_2_4_4-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_2_4_4-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set04/expected/model_2_4_4.eprime b/tests/exhaustive/basic/set04/expected/model_2_4_4.eprime deleted file mode 100644 index 3e7f4a0be3..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_2_4_4.eprime +++ /dev/null @@ -1,30 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..3)] of int(1..4) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..3)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3)] of int(1..3) -branching on [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy] -such that - or([x_ExplicitVarSizeWithDummy[q19] != 4 /\ x_ExplicitVarSizeWithDummy[q19] = 1 | q19 : int(1..3)]), - or([x_ExplicitVarSizeWithFlags_Flags[q21] /\ x_ExplicitVarSizeWithFlags_Values[q21] = 2 | q21 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 4 - | q1 : int(1..2)]), - and([x_ExplicitVarSizeWithDummy[q2] = 4 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 4 | q2 : int(1..2)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 4) | q3 : int(1..3)]) <= 3, - and([x_ExplicitVarSizeWithFlags_Flags[q5 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q5] < x_ExplicitVarSizeWithFlags_Values[q5 + 1] - | q5 : int(1..2)]), - and([x_ExplicitVarSizeWithFlags_Flags[q6] = false -> x_ExplicitVarSizeWithFlags_Values[q6] = 1 | q6 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q7] | q7 : int(1..2)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q8]) | q8 : int(1..3)]) <= 3, - and([x_ExplicitVarSizeWithFlags_Flags[q11] -> - or([x_ExplicitVarSizeWithDummy[q13] != 4 /\ - x_ExplicitVarSizeWithDummy[q13] = x_ExplicitVarSizeWithFlags_Values[q11] - | q13 : int(1..3)]) - | q11 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q15] != 4 -> - or([x_ExplicitVarSizeWithFlags_Flags[q17] /\ - x_ExplicitVarSizeWithFlags_Values[q17] = x_ExplicitVarSizeWithDummy[q15] - | q17 : int(1..3)]) - | q15 : int(1..3)]) - diff --git a/tests/exhaustive/basic/set04/expected/model_3_1_1-solution000001.solution b/tests/exhaustive/basic/set04/expected/model_3_1_1-solution000001.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_3_1_1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/set04/expected/model_3_1_1-solution000002.solution b/tests/exhaustive/basic/set04/expected/model_3_1_1-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_3_1_1-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set04/expected/model_3_1_1.eprime b/tests/exhaustive/basic/set04/expected/model_3_1_1.eprime deleted file mode 100644 index 11b75e4c19..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_3_1_1.eprime +++ /dev/null @@ -1,21 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..3) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3)] of int(1..3) -find x_Occurrence: matrix indexed by [int(1..3)] of bool -branching on [x_Occurrence, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] -such that - or([q11 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q11] = 1 | q11 : int(1..3)]), - x_Occurrence[2], - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..2)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..3)]), - x_ExplicitVarSizeWithMarker_Marker <= 3, - sum([toInt(x_Occurrence[q4]) | q4 : int(1..3)]) <= 3, - and([x_Occurrence[q5] -> - or([q7 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q7] = q5 | q7 : int(1..3)]) - | q5 : int(1..3)]), - and([q9 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q9]] - | q9 : int(1..3)]) - diff --git a/tests/exhaustive/basic/set04/expected/model_3_1_2-solution000001.solution b/tests/exhaustive/basic/set04/expected/model_3_1_2-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_3_1_2-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set04/expected/model_3_1_2-solution000002.solution b/tests/exhaustive/basic/set04/expected/model_3_1_2-solution000002.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_3_1_2-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/set04/expected/model_3_1_2.eprime b/tests/exhaustive/basic/set04/expected/model_3_1_2.eprime deleted file mode 100644 index 5a6b86cc08..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_3_1_2.eprime +++ /dev/null @@ -1,42 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..3) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3)] of int(1..3) -find x_Occurrence: matrix indexed by [int(1..3)] of bool -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..3)] of int(1..4) -branching on - [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_Occurrence] -such that - or([q28 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q28] = 1 | q28 : int(1..3)]), - x_Occurrence[2], - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..2)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..3)]), - x_ExplicitVarSizeWithMarker_Marker <= 3, - sum([toInt(x_Occurrence[q4]) | q4 : int(1..3)]) <= 3, - and([x_Occurrence[q22] -> - or([q24 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q24] = q22 - | q24 : int(1..3)]) - | q22 : int(1..3)]), - and([q26 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q26]] - | q26 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q5] < x_ExplicitVarSizeWithDummy[q5 + 1] \/ x_ExplicitVarSizeWithDummy[q5] = 4 - | q5 : int(1..2)]), - and([x_ExplicitVarSizeWithDummy[q6] = 4 -> x_ExplicitVarSizeWithDummy[q6 + 1] = 4 | q6 : int(1..2)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q7] != 4) | q7 : int(1..3)]) <= 3, - and([x_ExplicitVarSizeWithDummy[q10] != 4 -> - or([q12 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q12] = x_ExplicitVarSizeWithDummy[q10] - | q12 : int(1..3)]) - | q10 : int(1..3)]), - and([q14 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q16] != 4 /\ - x_ExplicitVarSizeWithDummy[q16] = x_ExplicitVarSizeWithMarker_Values[q14] - | q16 : int(1..3)]) - | q14 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q18] != 4 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q18]] | q18 : int(1..3)]), - and([x_Occurrence[q19] -> - or([x_ExplicitVarSizeWithDummy[q21] != 4 /\ x_ExplicitVarSizeWithDummy[q21] = q19 | q21 : int(1..3)]) - | q19 : int(1..3)]) - diff --git a/tests/exhaustive/basic/set04/expected/model_3_1_3-solution000001.solution b/tests/exhaustive/basic/set04/expected/model_3_1_3-solution000001.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_3_1_3-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/set04/expected/model_3_1_3-solution000002.solution b/tests/exhaustive/basic/set04/expected/model_3_1_3-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_3_1_3-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set04/expected/model_3_1_3.eprime b/tests/exhaustive/basic/set04/expected/model_3_1_3.eprime deleted file mode 100644 index 11b75e4c19..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_3_1_3.eprime +++ /dev/null @@ -1,21 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..3) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3)] of int(1..3) -find x_Occurrence: matrix indexed by [int(1..3)] of bool -branching on [x_Occurrence, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] -such that - or([q11 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q11] = 1 | q11 : int(1..3)]), - x_Occurrence[2], - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..2)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..3)]), - x_ExplicitVarSizeWithMarker_Marker <= 3, - sum([toInt(x_Occurrence[q4]) | q4 : int(1..3)]) <= 3, - and([x_Occurrence[q5] -> - or([q7 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q7] = q5 | q7 : int(1..3)]) - | q5 : int(1..3)]), - and([q9 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q9]] - | q9 : int(1..3)]) - diff --git a/tests/exhaustive/basic/set04/expected/model_3_1_4-solution000001.solution b/tests/exhaustive/basic/set04/expected/model_3_1_4-solution000001.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_3_1_4-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/set04/expected/model_3_1_4-solution000002.solution b/tests/exhaustive/basic/set04/expected/model_3_1_4-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_3_1_4-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set04/expected/model_3_1_4.eprime b/tests/exhaustive/basic/set04/expected/model_3_1_4.eprime deleted file mode 100644 index d07b3c46b8..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_3_1_4.eprime +++ /dev/null @@ -1,47 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..3) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3)] of int(1..3) -find x_Occurrence: matrix indexed by [int(1..3)] of bool -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..3)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3)] of int(1..3) -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithMarker_Marker, - x_ExplicitVarSizeWithMarker_Values, x_Occurrence] -such that - or([q29 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q29] = 1 | q29 : int(1..3)]), - x_Occurrence[2], - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..2)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..3)]), - x_ExplicitVarSizeWithMarker_Marker <= 3, - sum([toInt(x_Occurrence[q4]) | q4 : int(1..3)]) <= 3, - and([x_Occurrence[q23] -> - or([q25 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q25] = q23 - | q25 : int(1..3)]) - | q23 : int(1..3)]), - and([q27 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q27]] - | q27 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q5 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q5] < x_ExplicitVarSizeWithFlags_Values[q5 + 1] - | q5 : int(1..2)]), - and([x_ExplicitVarSizeWithFlags_Flags[q6] = false -> x_ExplicitVarSizeWithFlags_Values[q6] = 1 | q6 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q7] | q7 : int(1..2)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q8]) | q8 : int(1..3)]) <= 3, - and([x_ExplicitVarSizeWithFlags_Flags[q11] -> - or([q13 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q13] = x_ExplicitVarSizeWithFlags_Values[q11] - | q13 : int(1..3)]) - | q11 : int(1..3)]), - and([q15 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q17] /\ - x_ExplicitVarSizeWithFlags_Values[q17] = x_ExplicitVarSizeWithMarker_Values[q15] - | q17 : int(1..3)]) - | q15 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q19] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q19]] - | q19 : int(1..3)]), - and([x_Occurrence[q20] -> - or([x_ExplicitVarSizeWithFlags_Flags[q22] /\ x_ExplicitVarSizeWithFlags_Values[q22] = q20 | q22 : int(1..3)]) - | q20 : int(1..3)]) - diff --git a/tests/exhaustive/basic/set04/expected/model_3_2_1-solution000001.solution b/tests/exhaustive/basic/set04/expected/model_3_2_1-solution000001.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_3_2_1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/set04/expected/model_3_2_1-solution000002.solution b/tests/exhaustive/basic/set04/expected/model_3_2_1-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_3_2_1-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set04/expected/model_3_2_1.eprime b/tests/exhaustive/basic/set04/expected/model_3_2_1.eprime deleted file mode 100644 index e22f63bd77..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_3_2_1.eprime +++ /dev/null @@ -1,42 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..3) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3)] of int(1..3) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..3)] of int(1..4) -find x_Occurrence: matrix indexed by [int(1..3)] of bool -branching on - [x_Occurrence, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy] -such that - or([q28 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q28] = 1 | q28 : int(1..3)]), - or([x_ExplicitVarSizeWithDummy[q30] != 4 /\ x_ExplicitVarSizeWithDummy[q30] = 2 | q30 : int(1..3)]), - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..2)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..3)]), - x_ExplicitVarSizeWithMarker_Marker <= 3, - and([x_ExplicitVarSizeWithDummy[q4] < x_ExplicitVarSizeWithDummy[q4 + 1] \/ x_ExplicitVarSizeWithDummy[q4] = 4 - | q4 : int(1..2)]), - and([x_ExplicitVarSizeWithDummy[q5] = 4 -> x_ExplicitVarSizeWithDummy[q5 + 1] = 4 | q5 : int(1..2)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q6] != 4) | q6 : int(1..3)]) <= 3, - and([x_ExplicitVarSizeWithDummy[q9] != 4 -> - or([q11 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q11] = x_ExplicitVarSizeWithDummy[q9] - | q11 : int(1..3)]) - | q9 : int(1..3)]), - and([q13 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q15] != 4 /\ - x_ExplicitVarSizeWithDummy[q15] = x_ExplicitVarSizeWithMarker_Values[q13] - | q15 : int(1..3)]) - | q13 : int(1..3)]), - sum([toInt(x_Occurrence[q16]) | q16 : int(1..3)]) <= 3, - and([x_Occurrence[q17] -> - or([q19 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q19] = q17 - | q19 : int(1..3)]) - | q17 : int(1..3)]), - and([q21 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q21]] - | q21 : int(1..3)]), - and([x_Occurrence[q22] -> - or([x_ExplicitVarSizeWithDummy[q24] != 4 /\ x_ExplicitVarSizeWithDummy[q24] = q22 | q24 : int(1..3)]) - | q22 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q26] != 4 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q26]] | q26 : int(1..3)]) - diff --git a/tests/exhaustive/basic/set04/expected/model_3_2_2-solution000001.solution b/tests/exhaustive/basic/set04/expected/model_3_2_2-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_3_2_2-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set04/expected/model_3_2_2-solution000002.solution b/tests/exhaustive/basic/set04/expected/model_3_2_2-solution000002.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_3_2_2-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/set04/expected/model_3_2_2.eprime b/tests/exhaustive/basic/set04/expected/model_3_2_2.eprime deleted file mode 100644 index 29d9a0d39b..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_3_2_2.eprime +++ /dev/null @@ -1,29 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..3) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3)] of int(1..3) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..3)] of int(1..4) -branching on [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] -such that - or([q17 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q17] = 1 | q17 : int(1..3)]), - or([x_ExplicitVarSizeWithDummy[q19] != 4 /\ x_ExplicitVarSizeWithDummy[q19] = 2 | q19 : int(1..3)]), - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..2)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..3)]), - x_ExplicitVarSizeWithMarker_Marker <= 3, - and([x_ExplicitVarSizeWithDummy[q4] < x_ExplicitVarSizeWithDummy[q4 + 1] \/ x_ExplicitVarSizeWithDummy[q4] = 4 - | q4 : int(1..2)]), - and([x_ExplicitVarSizeWithDummy[q5] = 4 -> x_ExplicitVarSizeWithDummy[q5 + 1] = 4 | q5 : int(1..2)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q6] != 4) | q6 : int(1..3)]) <= 3, - and([x_ExplicitVarSizeWithDummy[q9] != 4 -> - or([q11 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q11] = x_ExplicitVarSizeWithDummy[q9] - | q11 : int(1..3)]) - | q9 : int(1..3)]), - and([q13 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q15] != 4 /\ - x_ExplicitVarSizeWithDummy[q15] = x_ExplicitVarSizeWithMarker_Values[q13] - | q15 : int(1..3)]) - | q13 : int(1..3)]) - diff --git a/tests/exhaustive/basic/set04/expected/model_3_2_3-solution000001.solution b/tests/exhaustive/basic/set04/expected/model_3_2_3-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_3_2_3-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set04/expected/model_3_2_3-solution000002.solution b/tests/exhaustive/basic/set04/expected/model_3_2_3-solution000002.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_3_2_3-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/set04/expected/model_3_2_3.eprime b/tests/exhaustive/basic/set04/expected/model_3_2_3.eprime deleted file mode 100644 index 29d9a0d39b..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_3_2_3.eprime +++ /dev/null @@ -1,29 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..3) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3)] of int(1..3) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..3)] of int(1..4) -branching on [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] -such that - or([q17 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q17] = 1 | q17 : int(1..3)]), - or([x_ExplicitVarSizeWithDummy[q19] != 4 /\ x_ExplicitVarSizeWithDummy[q19] = 2 | q19 : int(1..3)]), - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..2)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..3)]), - x_ExplicitVarSizeWithMarker_Marker <= 3, - and([x_ExplicitVarSizeWithDummy[q4] < x_ExplicitVarSizeWithDummy[q4 + 1] \/ x_ExplicitVarSizeWithDummy[q4] = 4 - | q4 : int(1..2)]), - and([x_ExplicitVarSizeWithDummy[q5] = 4 -> x_ExplicitVarSizeWithDummy[q5 + 1] = 4 | q5 : int(1..2)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q6] != 4) | q6 : int(1..3)]) <= 3, - and([x_ExplicitVarSizeWithDummy[q9] != 4 -> - or([q11 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q11] = x_ExplicitVarSizeWithDummy[q9] - | q11 : int(1..3)]) - | q9 : int(1..3)]), - and([q13 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q15] != 4 /\ - x_ExplicitVarSizeWithDummy[q15] = x_ExplicitVarSizeWithMarker_Values[q13] - | q15 : int(1..3)]) - | q13 : int(1..3)]) - diff --git a/tests/exhaustive/basic/set04/expected/model_3_2_4-solution000001.solution b/tests/exhaustive/basic/set04/expected/model_3_2_4-solution000001.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_3_2_4-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/set04/expected/model_3_2_4-solution000002.solution b/tests/exhaustive/basic/set04/expected/model_3_2_4-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_3_2_4-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set04/expected/model_3_2_4.eprime b/tests/exhaustive/basic/set04/expected/model_3_2_4.eprime deleted file mode 100644 index 73a3773a1d..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_3_2_4.eprime +++ /dev/null @@ -1,60 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..3) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3)] of int(1..3) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..3)] of int(1..4) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..3)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3)] of int(1..3) -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithMarker_Marker, - x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy] -such that - or([q38 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q38] = 1 | q38 : int(1..3)]), - or([x_ExplicitVarSizeWithDummy[q40] != 4 /\ x_ExplicitVarSizeWithDummy[q40] = 2 | q40 : int(1..3)]), - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..2)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..3)]), - x_ExplicitVarSizeWithMarker_Marker <= 3, - and([x_ExplicitVarSizeWithDummy[q4] < x_ExplicitVarSizeWithDummy[q4 + 1] \/ x_ExplicitVarSizeWithDummy[q4] = 4 - | q4 : int(1..2)]), - and([x_ExplicitVarSizeWithDummy[q5] = 4 -> x_ExplicitVarSizeWithDummy[q5 + 1] = 4 | q5 : int(1..2)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q6] != 4) | q6 : int(1..3)]) <= 3, - and([x_ExplicitVarSizeWithDummy[q9] != 4 -> - or([q11 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q11] = x_ExplicitVarSizeWithDummy[q9] - | q11 : int(1..3)]) - | q9 : int(1..3)]), - and([q13 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q15] != 4 /\ - x_ExplicitVarSizeWithDummy[q15] = x_ExplicitVarSizeWithMarker_Values[q13] - | q15 : int(1..3)]) - | q13 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q16 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q16] < x_ExplicitVarSizeWithFlags_Values[q16 + 1] - | q16 : int(1..2)]), - and([x_ExplicitVarSizeWithFlags_Flags[q17] = false -> x_ExplicitVarSizeWithFlags_Values[q17] = 1 - | q17 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q18 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q18] | q18 : int(1..2)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q19]) | q19 : int(1..3)]) <= 3, - and([x_ExplicitVarSizeWithFlags_Flags[q22] -> - or([q24 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q24] = x_ExplicitVarSizeWithFlags_Values[q22] - | q24 : int(1..3)]) - | q22 : int(1..3)]), - and([q26 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q28] /\ - x_ExplicitVarSizeWithFlags_Values[q28] = x_ExplicitVarSizeWithMarker_Values[q26] - | q28 : int(1..3)]) - | q26 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q30] -> - or([x_ExplicitVarSizeWithDummy[q32] != 4 /\ - x_ExplicitVarSizeWithDummy[q32] = x_ExplicitVarSizeWithFlags_Values[q30] - | q32 : int(1..3)]) - | q30 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q34] != 4 -> - or([x_ExplicitVarSizeWithFlags_Flags[q36] /\ - x_ExplicitVarSizeWithFlags_Values[q36] = x_ExplicitVarSizeWithDummy[q34] - | q36 : int(1..3)]) - | q34 : int(1..3)]) - diff --git a/tests/exhaustive/basic/set04/expected/model_3_3_1-solution000001.solution b/tests/exhaustive/basic/set04/expected/model_3_3_1-solution000001.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_3_3_1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/set04/expected/model_3_3_1-solution000002.solution b/tests/exhaustive/basic/set04/expected/model_3_3_1-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_3_3_1-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set04/expected/model_3_3_1.eprime b/tests/exhaustive/basic/set04/expected/model_3_3_1.eprime deleted file mode 100644 index 2c7c27bef8..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_3_3_1.eprime +++ /dev/null @@ -1,21 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..3) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3)] of int(1..3) -find x_Occurrence: matrix indexed by [int(1..3)] of bool -branching on [x_Occurrence, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] -such that - or([q11 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q11] = 1 | q11 : int(1..3)]), - or([q13 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q13] = 2 | q13 : int(1..3)]), - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..2)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..3)]), - x_ExplicitVarSizeWithMarker_Marker <= 3, - sum([toInt(x_Occurrence[q4]) | q4 : int(1..3)]) <= 3, - and([x_Occurrence[q5] -> - or([q7 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q7] = q5 | q7 : int(1..3)]) - | q5 : int(1..3)]), - and([q9 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q9]] - | q9 : int(1..3)]) - diff --git a/tests/exhaustive/basic/set04/expected/model_3_3_2-solution000001.solution b/tests/exhaustive/basic/set04/expected/model_3_3_2-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_3_3_2-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set04/expected/model_3_3_2-solution000002.solution b/tests/exhaustive/basic/set04/expected/model_3_3_2-solution000002.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_3_3_2-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/set04/expected/model_3_3_2.eprime b/tests/exhaustive/basic/set04/expected/model_3_3_2.eprime deleted file mode 100644 index 3b583676e9..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_3_3_2.eprime +++ /dev/null @@ -1,29 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..3) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3)] of int(1..3) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..3)] of int(1..4) -branching on [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] -such that - or([q17 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q17] = 1 | q17 : int(1..3)]), - or([q19 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q19] = 2 | q19 : int(1..3)]), - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..2)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..3)]), - x_ExplicitVarSizeWithMarker_Marker <= 3, - and([x_ExplicitVarSizeWithDummy[q4] < x_ExplicitVarSizeWithDummy[q4 + 1] \/ x_ExplicitVarSizeWithDummy[q4] = 4 - | q4 : int(1..2)]), - and([x_ExplicitVarSizeWithDummy[q5] = 4 -> x_ExplicitVarSizeWithDummy[q5 + 1] = 4 | q5 : int(1..2)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q6] != 4) | q6 : int(1..3)]) <= 3, - and([x_ExplicitVarSizeWithDummy[q9] != 4 -> - or([q11 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q11] = x_ExplicitVarSizeWithDummy[q9] - | q11 : int(1..3)]) - | q9 : int(1..3)]), - and([q13 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q15] != 4 /\ - x_ExplicitVarSizeWithDummy[q15] = x_ExplicitVarSizeWithMarker_Values[q13] - | q15 : int(1..3)]) - | q13 : int(1..3)]) - diff --git a/tests/exhaustive/basic/set04/expected/model_3_3_3-solution000001.solution b/tests/exhaustive/basic/set04/expected/model_3_3_3-solution000001.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_3_3_3-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/set04/expected/model_3_3_3-solution000002.solution b/tests/exhaustive/basic/set04/expected/model_3_3_3-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_3_3_3-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set04/expected/model_3_3_3.eprime b/tests/exhaustive/basic/set04/expected/model_3_3_3.eprime deleted file mode 100644 index ac50cfaa35..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_3_3_3.eprime +++ /dev/null @@ -1,14 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..3) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3)] of int(1..3) -branching on [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] -such that - or([q5 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q5] = 1 | q5 : int(1..3)]), - or([q7 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q7] = 2 | q7 : int(1..3)]), - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..2)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..3)]), - x_ExplicitVarSizeWithMarker_Marker <= 3 - diff --git a/tests/exhaustive/basic/set04/expected/model_3_3_4-solution000001.solution b/tests/exhaustive/basic/set04/expected/model_3_3_4-solution000001.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_3_3_4-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/set04/expected/model_3_3_4-solution000002.solution b/tests/exhaustive/basic/set04/expected/model_3_3_4-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_3_3_4-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set04/expected/model_3_3_4.eprime b/tests/exhaustive/basic/set04/expected/model_3_3_4.eprime deleted file mode 100644 index d4336a8b4e..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_3_3_4.eprime +++ /dev/null @@ -1,34 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..3) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3)] of int(1..3) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..3)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3)] of int(1..3) -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithMarker_Marker, - x_ExplicitVarSizeWithMarker_Values] -such that - or([q18 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q18] = 1 | q18 : int(1..3)]), - or([q20 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q20] = 2 | q20 : int(1..3)]), - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..2)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..3)]), - x_ExplicitVarSizeWithMarker_Marker <= 3, - and([x_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q4] < x_ExplicitVarSizeWithFlags_Values[q4 + 1] - | q4 : int(1..2)]), - and([x_ExplicitVarSizeWithFlags_Flags[q5] = false -> x_ExplicitVarSizeWithFlags_Values[q5] = 1 | q5 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q6] | q6 : int(1..2)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q7]) | q7 : int(1..3)]) <= 3, - and([x_ExplicitVarSizeWithFlags_Flags[q10] -> - or([q12 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q12] = x_ExplicitVarSizeWithFlags_Values[q10] - | q12 : int(1..3)]) - | q10 : int(1..3)]), - and([q14 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q16] /\ - x_ExplicitVarSizeWithFlags_Values[q16] = x_ExplicitVarSizeWithMarker_Values[q14] - | q16 : int(1..3)]) - | q14 : int(1..3)]) - diff --git a/tests/exhaustive/basic/set04/expected/model_3_4_1-solution000001.solution b/tests/exhaustive/basic/set04/expected/model_3_4_1-solution000001.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_3_4_1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/set04/expected/model_3_4_1-solution000002.solution b/tests/exhaustive/basic/set04/expected/model_3_4_1-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_3_4_1-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set04/expected/model_3_4_1.eprime b/tests/exhaustive/basic/set04/expected/model_3_4_1.eprime deleted file mode 100644 index 72055038e8..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_3_4_1.eprime +++ /dev/null @@ -1,47 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..3) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3)] of int(1..3) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..3)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3)] of int(1..3) -find x_Occurrence: matrix indexed by [int(1..3)] of bool -branching on - [x_Occurrence, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, - x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] -such that - or([q29 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q29] = 1 | q29 : int(1..3)]), - or([x_ExplicitVarSizeWithFlags_Flags[q31] /\ x_ExplicitVarSizeWithFlags_Values[q31] = 2 | q31 : int(1..3)]), - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..2)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..3)]), - x_ExplicitVarSizeWithMarker_Marker <= 3, - and([x_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q4] < x_ExplicitVarSizeWithFlags_Values[q4 + 1] - | q4 : int(1..2)]), - and([x_ExplicitVarSizeWithFlags_Flags[q5] = false -> x_ExplicitVarSizeWithFlags_Values[q5] = 1 | q5 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q6] | q6 : int(1..2)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q7]) | q7 : int(1..3)]) <= 3, - and([x_ExplicitVarSizeWithFlags_Flags[q10] -> - or([q12 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q12] = x_ExplicitVarSizeWithFlags_Values[q10] - | q12 : int(1..3)]) - | q10 : int(1..3)]), - and([q14 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q16] /\ - x_ExplicitVarSizeWithFlags_Values[q16] = x_ExplicitVarSizeWithMarker_Values[q14] - | q16 : int(1..3)]) - | q14 : int(1..3)]), - sum([toInt(x_Occurrence[q17]) | q17 : int(1..3)]) <= 3, - and([x_Occurrence[q18] -> - or([q20 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q20] = q18 - | q20 : int(1..3)]) - | q18 : int(1..3)]), - and([q22 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q22]] - | q22 : int(1..3)]), - and([x_Occurrence[q23] -> - or([x_ExplicitVarSizeWithFlags_Flags[q25] /\ x_ExplicitVarSizeWithFlags_Values[q25] = q23 | q25 : int(1..3)]) - | q23 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q27] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q27]] - | q27 : int(1..3)]) - diff --git a/tests/exhaustive/basic/set04/expected/model_3_4_2-solution000001.solution b/tests/exhaustive/basic/set04/expected/model_3_4_2-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_3_4_2-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set04/expected/model_3_4_2-solution000002.solution b/tests/exhaustive/basic/set04/expected/model_3_4_2-solution000002.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_3_4_2-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/set04/expected/model_3_4_2.eprime b/tests/exhaustive/basic/set04/expected/model_3_4_2.eprime deleted file mode 100644 index 3d0a63ab93..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_3_4_2.eprime +++ /dev/null @@ -1,59 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..3) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3)] of int(1..3) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..3)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3)] of int(1..3) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..3)] of int(1..4) -branching on - [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, - x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] -such that - or([q38 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q38] = 1 | q38 : int(1..3)]), - or([x_ExplicitVarSizeWithFlags_Flags[q40] /\ x_ExplicitVarSizeWithFlags_Values[q40] = 2 | q40 : int(1..3)]), - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..2)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..3)]), - x_ExplicitVarSizeWithMarker_Marker <= 3, - and([x_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q4] < x_ExplicitVarSizeWithFlags_Values[q4 + 1] - | q4 : int(1..2)]), - and([x_ExplicitVarSizeWithFlags_Flags[q5] = false -> x_ExplicitVarSizeWithFlags_Values[q5] = 1 | q5 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q6] | q6 : int(1..2)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q7]) | q7 : int(1..3)]) <= 3, - and([x_ExplicitVarSizeWithFlags_Flags[q10] -> - or([q12 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q12] = x_ExplicitVarSizeWithFlags_Values[q10] - | q12 : int(1..3)]) - | q10 : int(1..3)]), - and([q14 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q16] /\ - x_ExplicitVarSizeWithFlags_Values[q16] = x_ExplicitVarSizeWithMarker_Values[q14] - | q16 : int(1..3)]) - | q14 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q17] < x_ExplicitVarSizeWithDummy[q17 + 1] \/ x_ExplicitVarSizeWithDummy[q17] = 4 - | q17 : int(1..2)]), - and([x_ExplicitVarSizeWithDummy[q18] = 4 -> x_ExplicitVarSizeWithDummy[q18 + 1] = 4 | q18 : int(1..2)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q19] != 4) | q19 : int(1..3)]) <= 3, - and([x_ExplicitVarSizeWithDummy[q22] != 4 -> - or([q24 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q24] = x_ExplicitVarSizeWithDummy[q22] - | q24 : int(1..3)]) - | q22 : int(1..3)]), - and([q26 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q28] != 4 /\ - x_ExplicitVarSizeWithDummy[q28] = x_ExplicitVarSizeWithMarker_Values[q26] - | q28 : int(1..3)]) - | q26 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q30] != 4 -> - or([x_ExplicitVarSizeWithFlags_Flags[q32] /\ - x_ExplicitVarSizeWithFlags_Values[q32] = x_ExplicitVarSizeWithDummy[q30] - | q32 : int(1..3)]) - | q30 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q34] -> - or([x_ExplicitVarSizeWithDummy[q36] != 4 /\ - x_ExplicitVarSizeWithDummy[q36] = x_ExplicitVarSizeWithFlags_Values[q34] - | q36 : int(1..3)]) - | q34 : int(1..3)]) - diff --git a/tests/exhaustive/basic/set04/expected/model_3_4_3-solution000001.solution b/tests/exhaustive/basic/set04/expected/model_3_4_3-solution000001.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_3_4_3-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/set04/expected/model_3_4_3-solution000002.solution b/tests/exhaustive/basic/set04/expected/model_3_4_3-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_3_4_3-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set04/expected/model_3_4_3.eprime b/tests/exhaustive/basic/set04/expected/model_3_4_3.eprime deleted file mode 100644 index 0c780bf7c5..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_3_4_3.eprime +++ /dev/null @@ -1,34 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..3) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3)] of int(1..3) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..3)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3)] of int(1..3) -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithMarker_Marker, - x_ExplicitVarSizeWithMarker_Values] -such that - or([q18 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q18] = 1 | q18 : int(1..3)]), - or([x_ExplicitVarSizeWithFlags_Flags[q20] /\ x_ExplicitVarSizeWithFlags_Values[q20] = 2 | q20 : int(1..3)]), - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..2)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..3)]), - x_ExplicitVarSizeWithMarker_Marker <= 3, - and([x_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q4] < x_ExplicitVarSizeWithFlags_Values[q4 + 1] - | q4 : int(1..2)]), - and([x_ExplicitVarSizeWithFlags_Flags[q5] = false -> x_ExplicitVarSizeWithFlags_Values[q5] = 1 | q5 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q6] | q6 : int(1..2)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q7]) | q7 : int(1..3)]) <= 3, - and([x_ExplicitVarSizeWithFlags_Flags[q10] -> - or([q12 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q12] = x_ExplicitVarSizeWithFlags_Values[q10] - | q12 : int(1..3)]) - | q10 : int(1..3)]), - and([q14 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q16] /\ - x_ExplicitVarSizeWithFlags_Values[q16] = x_ExplicitVarSizeWithMarker_Values[q14] - | q16 : int(1..3)]) - | q14 : int(1..3)]) - diff --git a/tests/exhaustive/basic/set04/expected/model_3_4_4-solution000001.solution b/tests/exhaustive/basic/set04/expected/model_3_4_4-solution000001.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_3_4_4-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/set04/expected/model_3_4_4-solution000002.solution b/tests/exhaustive/basic/set04/expected/model_3_4_4-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_3_4_4-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set04/expected/model_3_4_4.eprime b/tests/exhaustive/basic/set04/expected/model_3_4_4.eprime deleted file mode 100644 index 0c780bf7c5..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_3_4_4.eprime +++ /dev/null @@ -1,34 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..3) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3)] of int(1..3) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..3)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3)] of int(1..3) -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithMarker_Marker, - x_ExplicitVarSizeWithMarker_Values] -such that - or([q18 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q18] = 1 | q18 : int(1..3)]), - or([x_ExplicitVarSizeWithFlags_Flags[q20] /\ x_ExplicitVarSizeWithFlags_Values[q20] = 2 | q20 : int(1..3)]), - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..2)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..3)]), - x_ExplicitVarSizeWithMarker_Marker <= 3, - and([x_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q4] < x_ExplicitVarSizeWithFlags_Values[q4 + 1] - | q4 : int(1..2)]), - and([x_ExplicitVarSizeWithFlags_Flags[q5] = false -> x_ExplicitVarSizeWithFlags_Values[q5] = 1 | q5 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q6] | q6 : int(1..2)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q7]) | q7 : int(1..3)]) <= 3, - and([x_ExplicitVarSizeWithFlags_Flags[q10] -> - or([q12 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q12] = x_ExplicitVarSizeWithFlags_Values[q10] - | q12 : int(1..3)]) - | q10 : int(1..3)]), - and([q14 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q16] /\ - x_ExplicitVarSizeWithFlags_Values[q16] = x_ExplicitVarSizeWithMarker_Values[q14] - | q16 : int(1..3)]) - | q14 : int(1..3)]) - diff --git a/tests/exhaustive/basic/set04/expected/model_4_1_1-solution000001.solution b/tests/exhaustive/basic/set04/expected/model_4_1_1-solution000001.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_4_1_1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/set04/expected/model_4_1_1-solution000002.solution b/tests/exhaustive/basic/set04/expected/model_4_1_1-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_4_1_1-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set04/expected/model_4_1_1.eprime b/tests/exhaustive/basic/set04/expected/model_4_1_1.eprime deleted file mode 100644 index 5e98c11020..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_4_1_1.eprime +++ /dev/null @@ -1,22 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..3)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3)] of int(1..3) -find x_Occurrence: matrix indexed by [int(1..3)] of bool -branching on [x_Occurrence, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] -such that - or([x_ExplicitVarSizeWithFlags_Flags[q13] /\ x_ExplicitVarSizeWithFlags_Values[q13] = 1 | q13 : int(1..3)]), - x_Occurrence[2], - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..2)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..2)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..3)]) <= 3, - sum([toInt(x_Occurrence[q6]) | q6 : int(1..3)]) <= 3, - and([x_Occurrence[q7] -> - or([x_ExplicitVarSizeWithFlags_Flags[q9] /\ x_ExplicitVarSizeWithFlags_Values[q9] = q7 | q9 : int(1..3)]) - | q7 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q11] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q11]] - | q11 : int(1..3)]) - diff --git a/tests/exhaustive/basic/set04/expected/model_4_1_2-solution000001.solution b/tests/exhaustive/basic/set04/expected/model_4_1_2-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_4_1_2-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set04/expected/model_4_1_2-solution000002.solution b/tests/exhaustive/basic/set04/expected/model_4_1_2-solution000002.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_4_1_2-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/set04/expected/model_4_1_2.eprime b/tests/exhaustive/basic/set04/expected/model_4_1_2.eprime deleted file mode 100644 index 22076b537b..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_4_1_2.eprime +++ /dev/null @@ -1,42 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..3)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3)] of int(1..3) -find x_Occurrence: matrix indexed by [int(1..3)] of bool -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..3)] of int(1..4) -branching on - [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_Occurrence] -such that - or([x_ExplicitVarSizeWithFlags_Flags[q30] /\ x_ExplicitVarSizeWithFlags_Values[q30] = 1 | q30 : int(1..3)]), - x_Occurrence[2], - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..2)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..2)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..3)]) <= 3, - sum([toInt(x_Occurrence[q6]) | q6 : int(1..3)]) <= 3, - and([x_Occurrence[q24] -> - or([x_ExplicitVarSizeWithFlags_Flags[q26] /\ x_ExplicitVarSizeWithFlags_Values[q26] = q24 | q26 : int(1..3)]) - | q24 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q28] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q28]] - | q28 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q7] < x_ExplicitVarSizeWithDummy[q7 + 1] \/ x_ExplicitVarSizeWithDummy[q7] = 4 - | q7 : int(1..2)]), - and([x_ExplicitVarSizeWithDummy[q8] = 4 -> x_ExplicitVarSizeWithDummy[q8 + 1] = 4 | q8 : int(1..2)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q9] != 4) | q9 : int(1..3)]) <= 3, - and([x_ExplicitVarSizeWithDummy[q12] != 4 -> - or([x_ExplicitVarSizeWithFlags_Flags[q14] /\ - x_ExplicitVarSizeWithFlags_Values[q14] = x_ExplicitVarSizeWithDummy[q12] - | q14 : int(1..3)]) - | q12 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q16] -> - or([x_ExplicitVarSizeWithDummy[q18] != 4 /\ - x_ExplicitVarSizeWithDummy[q18] = x_ExplicitVarSizeWithFlags_Values[q16] - | q18 : int(1..3)]) - | q16 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q20] != 4 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q20]] | q20 : int(1..3)]), - and([x_Occurrence[q21] -> - or([x_ExplicitVarSizeWithDummy[q23] != 4 /\ x_ExplicitVarSizeWithDummy[q23] = q21 | q23 : int(1..3)]) - | q21 : int(1..3)]) - diff --git a/tests/exhaustive/basic/set04/expected/model_4_1_3-solution000001.solution b/tests/exhaustive/basic/set04/expected/model_4_1_3-solution000001.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_4_1_3-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/set04/expected/model_4_1_3-solution000002.solution b/tests/exhaustive/basic/set04/expected/model_4_1_3-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_4_1_3-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set04/expected/model_4_1_3.eprime b/tests/exhaustive/basic/set04/expected/model_4_1_3.eprime deleted file mode 100644 index c4e74c86f3..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_4_1_3.eprime +++ /dev/null @@ -1,47 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..3)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3)] of int(1..3) -find x_Occurrence: matrix indexed by [int(1..3)] of bool -find x_ExplicitVarSizeWithMarker_Marker: int(0..3) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3)] of int(1..3) -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithFlags_Flags, - x_ExplicitVarSizeWithFlags_Values, x_Occurrence] -such that - or([x_ExplicitVarSizeWithFlags_Flags[q29] /\ x_ExplicitVarSizeWithFlags_Values[q29] = 1 | q29 : int(1..3)]), - x_Occurrence[2], - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..2)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..2)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..3)]) <= 3, - sum([toInt(x_Occurrence[q6]) | q6 : int(1..3)]) <= 3, - and([x_Occurrence[q23] -> - or([x_ExplicitVarSizeWithFlags_Flags[q25] /\ x_ExplicitVarSizeWithFlags_Values[q25] = q23 | q25 : int(1..3)]) - | q23 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q27] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q27]] - | q27 : int(1..3)]), - and([q7 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q7] < x_ExplicitVarSizeWithMarker_Values[q7 + 1] - | q7 : int(1..2)]), - and([q8 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q8] = 1 | q8 : int(1..3)]), - x_ExplicitVarSizeWithMarker_Marker <= 3, - and([q11 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q13] /\ - x_ExplicitVarSizeWithFlags_Values[q13] = x_ExplicitVarSizeWithMarker_Values[q11] - | q13 : int(1..3)]) - | q11 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q15] -> - or([q17 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q17] = x_ExplicitVarSizeWithFlags_Values[q15] - | q17 : int(1..3)]) - | q15 : int(1..3)]), - and([q19 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q19]] - | q19 : int(1..3)]), - and([x_Occurrence[q20] -> - or([q22 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q22] = q20 - | q22 : int(1..3)]) - | q20 : int(1..3)]) - diff --git a/tests/exhaustive/basic/set04/expected/model_4_1_4-solution000001.solution b/tests/exhaustive/basic/set04/expected/model_4_1_4-solution000001.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_4_1_4-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/set04/expected/model_4_1_4-solution000002.solution b/tests/exhaustive/basic/set04/expected/model_4_1_4-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_4_1_4-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set04/expected/model_4_1_4.eprime b/tests/exhaustive/basic/set04/expected/model_4_1_4.eprime deleted file mode 100644 index 5e98c11020..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_4_1_4.eprime +++ /dev/null @@ -1,22 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..3)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3)] of int(1..3) -find x_Occurrence: matrix indexed by [int(1..3)] of bool -branching on [x_Occurrence, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] -such that - or([x_ExplicitVarSizeWithFlags_Flags[q13] /\ x_ExplicitVarSizeWithFlags_Values[q13] = 1 | q13 : int(1..3)]), - x_Occurrence[2], - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..2)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..2)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..3)]) <= 3, - sum([toInt(x_Occurrence[q6]) | q6 : int(1..3)]) <= 3, - and([x_Occurrence[q7] -> - or([x_ExplicitVarSizeWithFlags_Flags[q9] /\ x_ExplicitVarSizeWithFlags_Values[q9] = q7 | q9 : int(1..3)]) - | q7 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q11] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q11]] - | q11 : int(1..3)]) - diff --git a/tests/exhaustive/basic/set04/expected/model_4_2_1-solution000001.solution b/tests/exhaustive/basic/set04/expected/model_4_2_1-solution000001.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_4_2_1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/set04/expected/model_4_2_1-solution000002.solution b/tests/exhaustive/basic/set04/expected/model_4_2_1-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_4_2_1-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set04/expected/model_4_2_1.eprime b/tests/exhaustive/basic/set04/expected/model_4_2_1.eprime deleted file mode 100644 index 3e4cb54b04..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_4_2_1.eprime +++ /dev/null @@ -1,42 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..3)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3)] of int(1..3) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..3)] of int(1..4) -find x_Occurrence: matrix indexed by [int(1..3)] of bool -branching on - [x_Occurrence, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy] -such that - or([x_ExplicitVarSizeWithFlags_Flags[q30] /\ x_ExplicitVarSizeWithFlags_Values[q30] = 1 | q30 : int(1..3)]), - or([x_ExplicitVarSizeWithDummy[q32] != 4 /\ x_ExplicitVarSizeWithDummy[q32] = 2 | q32 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..2)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..2)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..3)]) <= 3, - and([x_ExplicitVarSizeWithDummy[q6] < x_ExplicitVarSizeWithDummy[q6 + 1] \/ x_ExplicitVarSizeWithDummy[q6] = 4 - | q6 : int(1..2)]), - and([x_ExplicitVarSizeWithDummy[q7] = 4 -> x_ExplicitVarSizeWithDummy[q7 + 1] = 4 | q7 : int(1..2)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q8] != 4) | q8 : int(1..3)]) <= 3, - and([x_ExplicitVarSizeWithDummy[q11] != 4 -> - or([x_ExplicitVarSizeWithFlags_Flags[q13] /\ - x_ExplicitVarSizeWithFlags_Values[q13] = x_ExplicitVarSizeWithDummy[q11] - | q13 : int(1..3)]) - | q11 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q15] -> - or([x_ExplicitVarSizeWithDummy[q17] != 4 /\ - x_ExplicitVarSizeWithDummy[q17] = x_ExplicitVarSizeWithFlags_Values[q15] - | q17 : int(1..3)]) - | q15 : int(1..3)]), - sum([toInt(x_Occurrence[q18]) | q18 : int(1..3)]) <= 3, - and([x_Occurrence[q19] -> - or([x_ExplicitVarSizeWithFlags_Flags[q21] /\ x_ExplicitVarSizeWithFlags_Values[q21] = q19 | q21 : int(1..3)]) - | q19 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q23] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q23]] - | q23 : int(1..3)]), - and([x_Occurrence[q24] -> - or([x_ExplicitVarSizeWithDummy[q26] != 4 /\ x_ExplicitVarSizeWithDummy[q26] = q24 | q26 : int(1..3)]) - | q24 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q28] != 4 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q28]] | q28 : int(1..3)]) - diff --git a/tests/exhaustive/basic/set04/expected/model_4_2_2-solution000001.solution b/tests/exhaustive/basic/set04/expected/model_4_2_2-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_4_2_2-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set04/expected/model_4_2_2-solution000002.solution b/tests/exhaustive/basic/set04/expected/model_4_2_2-solution000002.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_4_2_2-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/set04/expected/model_4_2_2.eprime b/tests/exhaustive/basic/set04/expected/model_4_2_2.eprime deleted file mode 100644 index 42d1680aae..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_4_2_2.eprime +++ /dev/null @@ -1,30 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..3)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3)] of int(1..3) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..3)] of int(1..4) -branching on [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] -such that - or([x_ExplicitVarSizeWithFlags_Flags[q19] /\ x_ExplicitVarSizeWithFlags_Values[q19] = 1 | q19 : int(1..3)]), - or([x_ExplicitVarSizeWithDummy[q21] != 4 /\ x_ExplicitVarSizeWithDummy[q21] = 2 | q21 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..2)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..2)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..3)]) <= 3, - and([x_ExplicitVarSizeWithDummy[q6] < x_ExplicitVarSizeWithDummy[q6 + 1] \/ x_ExplicitVarSizeWithDummy[q6] = 4 - | q6 : int(1..2)]), - and([x_ExplicitVarSizeWithDummy[q7] = 4 -> x_ExplicitVarSizeWithDummy[q7 + 1] = 4 | q7 : int(1..2)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q8] != 4) | q8 : int(1..3)]) <= 3, - and([x_ExplicitVarSizeWithDummy[q11] != 4 -> - or([x_ExplicitVarSizeWithFlags_Flags[q13] /\ - x_ExplicitVarSizeWithFlags_Values[q13] = x_ExplicitVarSizeWithDummy[q11] - | q13 : int(1..3)]) - | q11 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q15] -> - or([x_ExplicitVarSizeWithDummy[q17] != 4 /\ - x_ExplicitVarSizeWithDummy[q17] = x_ExplicitVarSizeWithFlags_Values[q15] - | q17 : int(1..3)]) - | q15 : int(1..3)]) - diff --git a/tests/exhaustive/basic/set04/expected/model_4_2_3-solution000001.solution b/tests/exhaustive/basic/set04/expected/model_4_2_3-solution000001.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_4_2_3-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/set04/expected/model_4_2_3-solution000002.solution b/tests/exhaustive/basic/set04/expected/model_4_2_3-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_4_2_3-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set04/expected/model_4_2_3.eprime b/tests/exhaustive/basic/set04/expected/model_4_2_3.eprime deleted file mode 100644 index 01219074fb..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_4_2_3.eprime +++ /dev/null @@ -1,59 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..3)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3)] of int(1..3) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..3)] of int(1..4) -find x_ExplicitVarSizeWithMarker_Marker: int(0..3) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3)] of int(1..3) -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithFlags_Flags, - x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy] -such that - or([x_ExplicitVarSizeWithFlags_Flags[q38] /\ x_ExplicitVarSizeWithFlags_Values[q38] = 1 | q38 : int(1..3)]), - or([x_ExplicitVarSizeWithDummy[q40] != 4 /\ x_ExplicitVarSizeWithDummy[q40] = 2 | q40 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..2)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..2)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..3)]) <= 3, - and([x_ExplicitVarSizeWithDummy[q6] < x_ExplicitVarSizeWithDummy[q6 + 1] \/ x_ExplicitVarSizeWithDummy[q6] = 4 - | q6 : int(1..2)]), - and([x_ExplicitVarSizeWithDummy[q7] = 4 -> x_ExplicitVarSizeWithDummy[q7 + 1] = 4 | q7 : int(1..2)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q8] != 4) | q8 : int(1..3)]) <= 3, - and([x_ExplicitVarSizeWithDummy[q11] != 4 -> - or([x_ExplicitVarSizeWithFlags_Flags[q13] /\ - x_ExplicitVarSizeWithFlags_Values[q13] = x_ExplicitVarSizeWithDummy[q11] - | q13 : int(1..3)]) - | q11 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q15] -> - or([x_ExplicitVarSizeWithDummy[q17] != 4 /\ - x_ExplicitVarSizeWithDummy[q17] = x_ExplicitVarSizeWithFlags_Values[q15] - | q17 : int(1..3)]) - | q15 : int(1..3)]), - and([q18 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q18] < x_ExplicitVarSizeWithMarker_Values[q18 + 1] - | q18 : int(1..2)]), - and([q19 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q19] = 1 | q19 : int(1..3)]), - x_ExplicitVarSizeWithMarker_Marker <= 3, - and([q22 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q24] /\ - x_ExplicitVarSizeWithFlags_Values[q24] = x_ExplicitVarSizeWithMarker_Values[q22] - | q24 : int(1..3)]) - | q22 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q26] -> - or([q28 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q28] = x_ExplicitVarSizeWithFlags_Values[q26] - | q28 : int(1..3)]) - | q26 : int(1..3)]), - and([q30 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q32] != 4 /\ - x_ExplicitVarSizeWithDummy[q32] = x_ExplicitVarSizeWithMarker_Values[q30] - | q32 : int(1..3)]) - | q30 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q34] != 4 -> - or([q36 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q36] = x_ExplicitVarSizeWithDummy[q34] - | q36 : int(1..3)]) - | q34 : int(1..3)]) - diff --git a/tests/exhaustive/basic/set04/expected/model_4_2_4-solution000001.solution b/tests/exhaustive/basic/set04/expected/model_4_2_4-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_4_2_4-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set04/expected/model_4_2_4-solution000002.solution b/tests/exhaustive/basic/set04/expected/model_4_2_4-solution000002.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_4_2_4-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/set04/expected/model_4_2_4.eprime b/tests/exhaustive/basic/set04/expected/model_4_2_4.eprime deleted file mode 100644 index 42d1680aae..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_4_2_4.eprime +++ /dev/null @@ -1,30 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..3)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3)] of int(1..3) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..3)] of int(1..4) -branching on [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] -such that - or([x_ExplicitVarSizeWithFlags_Flags[q19] /\ x_ExplicitVarSizeWithFlags_Values[q19] = 1 | q19 : int(1..3)]), - or([x_ExplicitVarSizeWithDummy[q21] != 4 /\ x_ExplicitVarSizeWithDummy[q21] = 2 | q21 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..2)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..2)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..3)]) <= 3, - and([x_ExplicitVarSizeWithDummy[q6] < x_ExplicitVarSizeWithDummy[q6 + 1] \/ x_ExplicitVarSizeWithDummy[q6] = 4 - | q6 : int(1..2)]), - and([x_ExplicitVarSizeWithDummy[q7] = 4 -> x_ExplicitVarSizeWithDummy[q7 + 1] = 4 | q7 : int(1..2)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q8] != 4) | q8 : int(1..3)]) <= 3, - and([x_ExplicitVarSizeWithDummy[q11] != 4 -> - or([x_ExplicitVarSizeWithFlags_Flags[q13] /\ - x_ExplicitVarSizeWithFlags_Values[q13] = x_ExplicitVarSizeWithDummy[q11] - | q13 : int(1..3)]) - | q11 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q15] -> - or([x_ExplicitVarSizeWithDummy[q17] != 4 /\ - x_ExplicitVarSizeWithDummy[q17] = x_ExplicitVarSizeWithFlags_Values[q15] - | q17 : int(1..3)]) - | q15 : int(1..3)]) - diff --git a/tests/exhaustive/basic/set04/expected/model_4_3_1-solution000001.solution b/tests/exhaustive/basic/set04/expected/model_4_3_1-solution000001.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_4_3_1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/set04/expected/model_4_3_1-solution000002.solution b/tests/exhaustive/basic/set04/expected/model_4_3_1-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_4_3_1-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set04/expected/model_4_3_1.eprime b/tests/exhaustive/basic/set04/expected/model_4_3_1.eprime deleted file mode 100644 index 87587667fc..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_4_3_1.eprime +++ /dev/null @@ -1,47 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..3)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3)] of int(1..3) -find x_ExplicitVarSizeWithMarker_Marker: int(0..3) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3)] of int(1..3) -find x_Occurrence: matrix indexed by [int(1..3)] of bool -branching on - [x_Occurrence, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, - x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] -such that - or([x_ExplicitVarSizeWithFlags_Flags[q29] /\ x_ExplicitVarSizeWithFlags_Values[q29] = 1 | q29 : int(1..3)]), - or([q31 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q31] = 2 | q31 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..2)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..2)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..3)]) <= 3, - and([q6 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q6] < x_ExplicitVarSizeWithMarker_Values[q6 + 1] - | q6 : int(1..2)]), - and([q7 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q7] = 1 | q7 : int(1..3)]), - x_ExplicitVarSizeWithMarker_Marker <= 3, - and([q10 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q12] /\ - x_ExplicitVarSizeWithFlags_Values[q12] = x_ExplicitVarSizeWithMarker_Values[q10] - | q12 : int(1..3)]) - | q10 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q14] -> - or([q16 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q16] = x_ExplicitVarSizeWithFlags_Values[q14] - | q16 : int(1..3)]) - | q14 : int(1..3)]), - sum([toInt(x_Occurrence[q17]) | q17 : int(1..3)]) <= 3, - and([x_Occurrence[q18] -> - or([x_ExplicitVarSizeWithFlags_Flags[q20] /\ x_ExplicitVarSizeWithFlags_Values[q20] = q18 | q20 : int(1..3)]) - | q18 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q22] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q22]] - | q22 : int(1..3)]), - and([x_Occurrence[q23] -> - or([q25 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q25] = q23 - | q25 : int(1..3)]) - | q23 : int(1..3)]), - and([q27 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q27]] - | q27 : int(1..3)]) - diff --git a/tests/exhaustive/basic/set04/expected/model_4_3_2-solution000001.solution b/tests/exhaustive/basic/set04/expected/model_4_3_2-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_4_3_2-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set04/expected/model_4_3_2-solution000002.solution b/tests/exhaustive/basic/set04/expected/model_4_3_2-solution000002.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_4_3_2-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/set04/expected/model_4_3_2.eprime b/tests/exhaustive/basic/set04/expected/model_4_3_2.eprime deleted file mode 100644 index 8a1052d0da..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_4_3_2.eprime +++ /dev/null @@ -1,59 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..3)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3)] of int(1..3) -find x_ExplicitVarSizeWithMarker_Marker: int(0..3) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3)] of int(1..3) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..3)] of int(1..4) -branching on - [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, - x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] -such that - or([x_ExplicitVarSizeWithFlags_Flags[q38] /\ x_ExplicitVarSizeWithFlags_Values[q38] = 1 | q38 : int(1..3)]), - or([q40 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q40] = 2 | q40 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..2)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..2)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..3)]) <= 3, - and([q6 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q6] < x_ExplicitVarSizeWithMarker_Values[q6 + 1] - | q6 : int(1..2)]), - and([q7 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q7] = 1 | q7 : int(1..3)]), - x_ExplicitVarSizeWithMarker_Marker <= 3, - and([q10 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q12] /\ - x_ExplicitVarSizeWithFlags_Values[q12] = x_ExplicitVarSizeWithMarker_Values[q10] - | q12 : int(1..3)]) - | q10 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q14] -> - or([q16 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q16] = x_ExplicitVarSizeWithFlags_Values[q14] - | q16 : int(1..3)]) - | q14 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q17] < x_ExplicitVarSizeWithDummy[q17 + 1] \/ x_ExplicitVarSizeWithDummy[q17] = 4 - | q17 : int(1..2)]), - and([x_ExplicitVarSizeWithDummy[q18] = 4 -> x_ExplicitVarSizeWithDummy[q18 + 1] = 4 | q18 : int(1..2)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q19] != 4) | q19 : int(1..3)]) <= 3, - and([x_ExplicitVarSizeWithDummy[q22] != 4 -> - or([x_ExplicitVarSizeWithFlags_Flags[q24] /\ - x_ExplicitVarSizeWithFlags_Values[q24] = x_ExplicitVarSizeWithDummy[q22] - | q24 : int(1..3)]) - | q22 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q26] -> - or([x_ExplicitVarSizeWithDummy[q28] != 4 /\ - x_ExplicitVarSizeWithDummy[q28] = x_ExplicitVarSizeWithFlags_Values[q26] - | q28 : int(1..3)]) - | q26 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q30] != 4 -> - or([q32 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q32] = x_ExplicitVarSizeWithDummy[q30] - | q32 : int(1..3)]) - | q30 : int(1..3)]), - and([q34 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q36] != 4 /\ - x_ExplicitVarSizeWithDummy[q36] = x_ExplicitVarSizeWithMarker_Values[q34] - | q36 : int(1..3)]) - | q34 : int(1..3)]) - diff --git a/tests/exhaustive/basic/set04/expected/model_4_3_3-solution000001.solution b/tests/exhaustive/basic/set04/expected/model_4_3_3-solution000001.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_4_3_3-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/set04/expected/model_4_3_3-solution000002.solution b/tests/exhaustive/basic/set04/expected/model_4_3_3-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_4_3_3-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set04/expected/model_4_3_3.eprime b/tests/exhaustive/basic/set04/expected/model_4_3_3.eprime deleted file mode 100644 index 50c9eadc30..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_4_3_3.eprime +++ /dev/null @@ -1,34 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..3)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3)] of int(1..3) -find x_ExplicitVarSizeWithMarker_Marker: int(0..3) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3)] of int(1..3) -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithFlags_Flags, - x_ExplicitVarSizeWithFlags_Values] -such that - or([x_ExplicitVarSizeWithFlags_Flags[q18] /\ x_ExplicitVarSizeWithFlags_Values[q18] = 1 | q18 : int(1..3)]), - or([q20 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q20] = 2 | q20 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..2)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..2)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..3)]) <= 3, - and([q6 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q6] < x_ExplicitVarSizeWithMarker_Values[q6 + 1] - | q6 : int(1..2)]), - and([q7 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q7] = 1 | q7 : int(1..3)]), - x_ExplicitVarSizeWithMarker_Marker <= 3, - and([q10 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q12] /\ - x_ExplicitVarSizeWithFlags_Values[q12] = x_ExplicitVarSizeWithMarker_Values[q10] - | q12 : int(1..3)]) - | q10 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q14] -> - or([q16 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q16] = x_ExplicitVarSizeWithFlags_Values[q14] - | q16 : int(1..3)]) - | q14 : int(1..3)]) - diff --git a/tests/exhaustive/basic/set04/expected/model_4_3_4-solution000001.solution b/tests/exhaustive/basic/set04/expected/model_4_3_4-solution000001.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_4_3_4-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/set04/expected/model_4_3_4-solution000002.solution b/tests/exhaustive/basic/set04/expected/model_4_3_4-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_4_3_4-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set04/expected/model_4_3_4.eprime b/tests/exhaustive/basic/set04/expected/model_4_3_4.eprime deleted file mode 100644 index 50c9eadc30..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_4_3_4.eprime +++ /dev/null @@ -1,34 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..3)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3)] of int(1..3) -find x_ExplicitVarSizeWithMarker_Marker: int(0..3) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3)] of int(1..3) -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithFlags_Flags, - x_ExplicitVarSizeWithFlags_Values] -such that - or([x_ExplicitVarSizeWithFlags_Flags[q18] /\ x_ExplicitVarSizeWithFlags_Values[q18] = 1 | q18 : int(1..3)]), - or([q20 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q20] = 2 | q20 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..2)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..2)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..3)]) <= 3, - and([q6 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q6] < x_ExplicitVarSizeWithMarker_Values[q6 + 1] - | q6 : int(1..2)]), - and([q7 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q7] = 1 | q7 : int(1..3)]), - x_ExplicitVarSizeWithMarker_Marker <= 3, - and([q10 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q12] /\ - x_ExplicitVarSizeWithFlags_Values[q12] = x_ExplicitVarSizeWithMarker_Values[q10] - | q12 : int(1..3)]) - | q10 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q14] -> - or([q16 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q16] = x_ExplicitVarSizeWithFlags_Values[q14] - | q16 : int(1..3)]) - | q14 : int(1..3)]) - diff --git a/tests/exhaustive/basic/set04/expected/model_4_4_1-solution000001.solution b/tests/exhaustive/basic/set04/expected/model_4_4_1-solution000001.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_4_4_1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/set04/expected/model_4_4_1-solution000002.solution b/tests/exhaustive/basic/set04/expected/model_4_4_1-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_4_4_1-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set04/expected/model_4_4_1.eprime b/tests/exhaustive/basic/set04/expected/model_4_4_1.eprime deleted file mode 100644 index 1679fe4372..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_4_4_1.eprime +++ /dev/null @@ -1,22 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..3)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3)] of int(1..3) -find x_Occurrence: matrix indexed by [int(1..3)] of bool -branching on [x_Occurrence, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] -such that - or([x_ExplicitVarSizeWithFlags_Flags[q13] /\ x_ExplicitVarSizeWithFlags_Values[q13] = 1 | q13 : int(1..3)]), - or([x_ExplicitVarSizeWithFlags_Flags[q15] /\ x_ExplicitVarSizeWithFlags_Values[q15] = 2 | q15 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..2)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..2)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..3)]) <= 3, - sum([toInt(x_Occurrence[q6]) | q6 : int(1..3)]) <= 3, - and([x_Occurrence[q7] -> - or([x_ExplicitVarSizeWithFlags_Flags[q9] /\ x_ExplicitVarSizeWithFlags_Values[q9] = q7 | q9 : int(1..3)]) - | q7 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q11] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q11]] - | q11 : int(1..3)]) - diff --git a/tests/exhaustive/basic/set04/expected/model_4_4_2-solution000001.solution b/tests/exhaustive/basic/set04/expected/model_4_4_2-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_4_4_2-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set04/expected/model_4_4_2-solution000002.solution b/tests/exhaustive/basic/set04/expected/model_4_4_2-solution000002.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_4_4_2-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/set04/expected/model_4_4_2.eprime b/tests/exhaustive/basic/set04/expected/model_4_4_2.eprime deleted file mode 100644 index 41d16504a6..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_4_4_2.eprime +++ /dev/null @@ -1,30 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..3)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3)] of int(1..3) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..3)] of int(1..4) -branching on [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] -such that - or([x_ExplicitVarSizeWithFlags_Flags[q19] /\ x_ExplicitVarSizeWithFlags_Values[q19] = 1 | q19 : int(1..3)]), - or([x_ExplicitVarSizeWithFlags_Flags[q21] /\ x_ExplicitVarSizeWithFlags_Values[q21] = 2 | q21 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..2)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..2)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..3)]) <= 3, - and([x_ExplicitVarSizeWithDummy[q6] < x_ExplicitVarSizeWithDummy[q6 + 1] \/ x_ExplicitVarSizeWithDummy[q6] = 4 - | q6 : int(1..2)]), - and([x_ExplicitVarSizeWithDummy[q7] = 4 -> x_ExplicitVarSizeWithDummy[q7 + 1] = 4 | q7 : int(1..2)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q8] != 4) | q8 : int(1..3)]) <= 3, - and([x_ExplicitVarSizeWithDummy[q11] != 4 -> - or([x_ExplicitVarSizeWithFlags_Flags[q13] /\ - x_ExplicitVarSizeWithFlags_Values[q13] = x_ExplicitVarSizeWithDummy[q11] - | q13 : int(1..3)]) - | q11 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q15] -> - or([x_ExplicitVarSizeWithDummy[q17] != 4 /\ - x_ExplicitVarSizeWithDummy[q17] = x_ExplicitVarSizeWithFlags_Values[q15] - | q17 : int(1..3)]) - | q15 : int(1..3)]) - diff --git a/tests/exhaustive/basic/set04/expected/model_4_4_3-solution000001.solution b/tests/exhaustive/basic/set04/expected/model_4_4_3-solution000001.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_4_4_3-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/set04/expected/model_4_4_3-solution000002.solution b/tests/exhaustive/basic/set04/expected/model_4_4_3-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_4_4_3-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set04/expected/model_4_4_3.eprime b/tests/exhaustive/basic/set04/expected/model_4_4_3.eprime deleted file mode 100644 index 6c0162b987..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_4_4_3.eprime +++ /dev/null @@ -1,34 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..3)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3)] of int(1..3) -find x_ExplicitVarSizeWithMarker_Marker: int(0..3) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3)] of int(1..3) -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithFlags_Flags, - x_ExplicitVarSizeWithFlags_Values] -such that - or([x_ExplicitVarSizeWithFlags_Flags[q18] /\ x_ExplicitVarSizeWithFlags_Values[q18] = 1 | q18 : int(1..3)]), - or([x_ExplicitVarSizeWithFlags_Flags[q20] /\ x_ExplicitVarSizeWithFlags_Values[q20] = 2 | q20 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..2)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..2)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..3)]) <= 3, - and([q6 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q6] < x_ExplicitVarSizeWithMarker_Values[q6 + 1] - | q6 : int(1..2)]), - and([q7 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q7] = 1 | q7 : int(1..3)]), - x_ExplicitVarSizeWithMarker_Marker <= 3, - and([q10 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q12] /\ - x_ExplicitVarSizeWithFlags_Values[q12] = x_ExplicitVarSizeWithMarker_Values[q10] - | q12 : int(1..3)]) - | q10 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q14] -> - or([q16 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q16] = x_ExplicitVarSizeWithFlags_Values[q14] - | q16 : int(1..3)]) - | q14 : int(1..3)]) - diff --git a/tests/exhaustive/basic/set04/expected/model_4_4_4-solution000001.solution b/tests/exhaustive/basic/set04/expected/model_4_4_4-solution000001.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_4_4_4-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/set04/expected/model_4_4_4-solution000002.solution b/tests/exhaustive/basic/set04/expected/model_4_4_4-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_4_4_4-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set04/expected/model_4_4_4.eprime b/tests/exhaustive/basic/set04/expected/model_4_4_4.eprime deleted file mode 100644 index a91619f489..0000000000 --- a/tests/exhaustive/basic/set04/expected/model_4_4_4.eprime +++ /dev/null @@ -1,15 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..3)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3)] of int(1..3) -branching on [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] -such that - or([x_ExplicitVarSizeWithFlags_Flags[q7] /\ x_ExplicitVarSizeWithFlags_Values[q7] = 1 | q7 : int(1..3)]), - or([x_ExplicitVarSizeWithFlags_Flags[q9] /\ x_ExplicitVarSizeWithFlags_Values[q9] = 2 | q9 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..2)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..2)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..3)]) <= 3 - diff --git a/tests/exhaustive/basic/set05/expected/model_1_1_1-solution000001.solution b/tests/exhaustive/basic/set05/expected/model_1_1_1-solution000001.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_1_1_1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/set05/expected/model_1_1_1-solution000002.solution b/tests/exhaustive/basic/set05/expected/model_1_1_1-solution000002.solution deleted file mode 100644 index fdc0f02f96..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_1_1_1-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 4} diff --git a/tests/exhaustive/basic/set05/expected/model_1_1_1-solution000003.solution b/tests/exhaustive/basic/set05/expected/model_1_1_1-solution000003.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_1_1_1-solution000003.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set05/expected/model_1_1_1.eprime b/tests/exhaustive/basic/set05/expected/model_1_1_1.eprime deleted file mode 100644 index 3c56114ac2..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_1_1_1.eprime +++ /dev/null @@ -1,9 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1..4)] of bool -branching on [x_Occurrence] -such that - x_Occurrence[1], - x_Occurrence[2], - sum([toInt(x_Occurrence[q1]) | q1 : int(1..4)]) <= 3 - diff --git a/tests/exhaustive/basic/set05/expected/model_1_1_2-solution000001.solution b/tests/exhaustive/basic/set05/expected/model_1_1_2-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_1_1_2-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set05/expected/model_1_1_2-solution000002.solution b/tests/exhaustive/basic/set05/expected/model_1_1_2-solution000002.solution deleted file mode 100644 index fdc0f02f96..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_1_1_2-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 4} diff --git a/tests/exhaustive/basic/set05/expected/model_1_1_2-solution000003.solution b/tests/exhaustive/basic/set05/expected/model_1_1_2-solution000003.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_1_1_2-solution000003.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/set05/expected/model_1_1_2.eprime b/tests/exhaustive/basic/set05/expected/model_1_1_2.eprime deleted file mode 100644 index 17c15fcd6b..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_1_1_2.eprime +++ /dev/null @@ -1,18 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..3)] of int(1..5) -branching on [x_ExplicitVarSizeWithDummy, x_Occurrence] -such that - x_Occurrence[1], - x_Occurrence[2], - sum([toInt(x_Occurrence[q1]) | q1 : int(1..4)]) <= 3, - and([x_ExplicitVarSizeWithDummy[q2] < x_ExplicitVarSizeWithDummy[q2 + 1] \/ x_ExplicitVarSizeWithDummy[q2] = 5 - | q2 : int(1..2)]), - and([x_ExplicitVarSizeWithDummy[q3] = 5 -> x_ExplicitVarSizeWithDummy[q3 + 1] = 5 | q3 : int(1..2)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q4] != 5) | q4 : int(1..3)]) <= 3, - and([x_ExplicitVarSizeWithDummy[q7] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q7]] | q7 : int(1..3)]), - and([x_Occurrence[q8] -> - or([x_ExplicitVarSizeWithDummy[q10] != 5 /\ x_ExplicitVarSizeWithDummy[q10] = q8 | q10 : int(1..3)]) - | q8 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set05/expected/model_1_1_3-solution000001.solution b/tests/exhaustive/basic/set05/expected/model_1_1_3-solution000001.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_1_1_3-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/set05/expected/model_1_1_3-solution000002.solution b/tests/exhaustive/basic/set05/expected/model_1_1_3-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_1_1_3-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set05/expected/model_1_1_3-solution000003.solution b/tests/exhaustive/basic/set05/expected/model_1_1_3-solution000003.solution deleted file mode 100644 index fdc0f02f96..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_1_1_3-solution000003.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 4} diff --git a/tests/exhaustive/basic/set05/expected/model_1_1_3.eprime b/tests/exhaustive/basic/set05/expected/model_1_1_3.eprime deleted file mode 100644 index 70361154b0..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_1_1_3.eprime +++ /dev/null @@ -1,21 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithMarker_Marker: int(0..3) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3)] of int(1..4) -branching on [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_Occurrence] -such that - x_Occurrence[1], - x_Occurrence[2], - sum([toInt(x_Occurrence[q1]) | q1 : int(1..4)]) <= 3, - and([q2 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q2] < x_ExplicitVarSizeWithMarker_Values[q2 + 1] - | q2 : int(1..2)]), - and([q3 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q3] = 1 | q3 : int(1..3)]), - x_ExplicitVarSizeWithMarker_Marker <= 3, - and([q6 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q6]] - | q6 : int(1..3)]), - and([x_Occurrence[q7] -> - or([q9 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q9] = q7 | q9 : int(1..3)]) - | q7 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set05/expected/model_1_1_4-solution000001.solution b/tests/exhaustive/basic/set05/expected/model_1_1_4-solution000001.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_1_1_4-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/set05/expected/model_1_1_4-solution000002.solution b/tests/exhaustive/basic/set05/expected/model_1_1_4-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_1_1_4-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set05/expected/model_1_1_4-solution000003.solution b/tests/exhaustive/basic/set05/expected/model_1_1_4-solution000003.solution deleted file mode 100644 index fdc0f02f96..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_1_1_4-solution000003.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 4} diff --git a/tests/exhaustive/basic/set05/expected/model_1_1_4.eprime b/tests/exhaustive/basic/set05/expected/model_1_1_4.eprime deleted file mode 100644 index 42983848f0..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_1_1_4.eprime +++ /dev/null @@ -1,21 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..3)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3)] of int(1..4) -branching on [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_Occurrence] -such that - x_Occurrence[1], - x_Occurrence[2], - sum([toInt(x_Occurrence[q1]) | q1 : int(1..4)]) <= 3, - and([x_ExplicitVarSizeWithFlags_Flags[q2 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q2] < x_ExplicitVarSizeWithFlags_Values[q2 + 1] - | q2 : int(1..2)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3] = false -> x_ExplicitVarSizeWithFlags_Values[q3] = 1 | q3 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q4] | q4 : int(1..2)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q5]) | q5 : int(1..3)]) <= 3, - and([x_ExplicitVarSizeWithFlags_Flags[q8] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q8]] | q8 : int(1..3)]), - and([x_Occurrence[q9] -> - or([x_ExplicitVarSizeWithFlags_Flags[q11] /\ x_ExplicitVarSizeWithFlags_Values[q11] = q9 | q11 : int(1..3)]) - | q9 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set05/expected/model_1_2_1-solution000001.solution b/tests/exhaustive/basic/set05/expected/model_1_2_1-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_1_2_1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set05/expected/model_1_2_1-solution000002.solution b/tests/exhaustive/basic/set05/expected/model_1_2_1-solution000002.solution deleted file mode 100644 index fdc0f02f96..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_1_2_1-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 4} diff --git a/tests/exhaustive/basic/set05/expected/model_1_2_1-solution000003.solution b/tests/exhaustive/basic/set05/expected/model_1_2_1-solution000003.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_1_2_1-solution000003.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/set05/expected/model_1_2_1.eprime b/tests/exhaustive/basic/set05/expected/model_1_2_1.eprime deleted file mode 100644 index c5886a217c..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_1_2_1.eprime +++ /dev/null @@ -1,18 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..3)] of int(1..5) -branching on [x_ExplicitVarSizeWithDummy, x_Occurrence] -such that - x_Occurrence[1], - or([x_ExplicitVarSizeWithDummy[q12] != 5 /\ x_ExplicitVarSizeWithDummy[q12] = 2 | q12 : int(1..3)]), - sum([toInt(x_Occurrence[q1]) | q1 : int(1..4)]) <= 3, - and([x_ExplicitVarSizeWithDummy[q2] < x_ExplicitVarSizeWithDummy[q2 + 1] \/ x_ExplicitVarSizeWithDummy[q2] = 5 - | q2 : int(1..2)]), - and([x_ExplicitVarSizeWithDummy[q3] = 5 -> x_ExplicitVarSizeWithDummy[q3 + 1] = 5 | q3 : int(1..2)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q4] != 5) | q4 : int(1..3)]) <= 3, - and([x_ExplicitVarSizeWithDummy[q7] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q7]] | q7 : int(1..3)]), - and([x_Occurrence[q8] -> - or([x_ExplicitVarSizeWithDummy[q10] != 5 /\ x_ExplicitVarSizeWithDummy[q10] = q8 | q10 : int(1..3)]) - | q8 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set05/expected/model_1_2_2-solution000001.solution b/tests/exhaustive/basic/set05/expected/model_1_2_2-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_1_2_2-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set05/expected/model_1_2_2-solution000002.solution b/tests/exhaustive/basic/set05/expected/model_1_2_2-solution000002.solution deleted file mode 100644 index fdc0f02f96..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_1_2_2-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 4} diff --git a/tests/exhaustive/basic/set05/expected/model_1_2_2-solution000003.solution b/tests/exhaustive/basic/set05/expected/model_1_2_2-solution000003.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_1_2_2-solution000003.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/set05/expected/model_1_2_2.eprime b/tests/exhaustive/basic/set05/expected/model_1_2_2.eprime deleted file mode 100644 index c5886a217c..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_1_2_2.eprime +++ /dev/null @@ -1,18 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..3)] of int(1..5) -branching on [x_ExplicitVarSizeWithDummy, x_Occurrence] -such that - x_Occurrence[1], - or([x_ExplicitVarSizeWithDummy[q12] != 5 /\ x_ExplicitVarSizeWithDummy[q12] = 2 | q12 : int(1..3)]), - sum([toInt(x_Occurrence[q1]) | q1 : int(1..4)]) <= 3, - and([x_ExplicitVarSizeWithDummy[q2] < x_ExplicitVarSizeWithDummy[q2 + 1] \/ x_ExplicitVarSizeWithDummy[q2] = 5 - | q2 : int(1..2)]), - and([x_ExplicitVarSizeWithDummy[q3] = 5 -> x_ExplicitVarSizeWithDummy[q3 + 1] = 5 | q3 : int(1..2)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q4] != 5) | q4 : int(1..3)]) <= 3, - and([x_ExplicitVarSizeWithDummy[q7] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q7]] | q7 : int(1..3)]), - and([x_Occurrence[q8] -> - or([x_ExplicitVarSizeWithDummy[q10] != 5 /\ x_ExplicitVarSizeWithDummy[q10] = q8 | q10 : int(1..3)]) - | q8 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set05/expected/model_1_2_3-solution000001.solution b/tests/exhaustive/basic/set05/expected/model_1_2_3-solution000001.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_1_2_3-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/set05/expected/model_1_2_3-solution000002.solution b/tests/exhaustive/basic/set05/expected/model_1_2_3-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_1_2_3-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set05/expected/model_1_2_3-solution000003.solution b/tests/exhaustive/basic/set05/expected/model_1_2_3-solution000003.solution deleted file mode 100644 index fdc0f02f96..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_1_2_3-solution000003.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 4} diff --git a/tests/exhaustive/basic/set05/expected/model_1_2_3.eprime b/tests/exhaustive/basic/set05/expected/model_1_2_3.eprime deleted file mode 100644 index 2ef8fa28a9..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_1_2_3.eprime +++ /dev/null @@ -1,42 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..3)] of int(1..5) -find x_ExplicitVarSizeWithMarker_Marker: int(0..3) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3)] of int(1..4) -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_Occurrence, x_ExplicitVarSizeWithDummy] -such that - x_Occurrence[1], - or([x_ExplicitVarSizeWithDummy[q28] != 5 /\ x_ExplicitVarSizeWithDummy[q28] = 2 | q28 : int(1..3)]), - sum([toInt(x_Occurrence[q1]) | q1 : int(1..4)]) <= 3, - and([x_ExplicitVarSizeWithDummy[q2] < x_ExplicitVarSizeWithDummy[q2 + 1] \/ x_ExplicitVarSizeWithDummy[q2] = 5 - | q2 : int(1..2)]), - and([x_ExplicitVarSizeWithDummy[q3] = 5 -> x_ExplicitVarSizeWithDummy[q3 + 1] = 5 | q3 : int(1..2)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q4] != 5) | q4 : int(1..3)]) <= 3, - and([x_ExplicitVarSizeWithDummy[q7] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q7]] | q7 : int(1..3)]), - and([x_Occurrence[q8] -> - or([x_ExplicitVarSizeWithDummy[q10] != 5 /\ x_ExplicitVarSizeWithDummy[q10] = q8 | q10 : int(1..3)]) - | q8 : int(1..4)]), - and([q11 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q11] < x_ExplicitVarSizeWithMarker_Values[q11 + 1] - | q11 : int(1..2)]), - and([q12 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q12] = 1 | q12 : int(1..3)]), - x_ExplicitVarSizeWithMarker_Marker <= 3, - and([q15 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q15]] - | q15 : int(1..3)]), - and([x_Occurrence[q16] -> - or([q18 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q18] = q16 - | q18 : int(1..3)]) - | q16 : int(1..4)]), - and([q20 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q22] != 5 /\ - x_ExplicitVarSizeWithDummy[q22] = x_ExplicitVarSizeWithMarker_Values[q20] - | q22 : int(1..3)]) - | q20 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q24] != 5 -> - or([q26 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q26] = x_ExplicitVarSizeWithDummy[q24] - | q26 : int(1..3)]) - | q24 : int(1..3)]) - diff --git a/tests/exhaustive/basic/set05/expected/model_1_2_4-solution000001.solution b/tests/exhaustive/basic/set05/expected/model_1_2_4-solution000001.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_1_2_4-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/set05/expected/model_1_2_4-solution000002.solution b/tests/exhaustive/basic/set05/expected/model_1_2_4-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_1_2_4-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set05/expected/model_1_2_4-solution000003.solution b/tests/exhaustive/basic/set05/expected/model_1_2_4-solution000003.solution deleted file mode 100644 index fdc0f02f96..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_1_2_4-solution000003.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 4} diff --git a/tests/exhaustive/basic/set05/expected/model_1_2_4.eprime b/tests/exhaustive/basic/set05/expected/model_1_2_4.eprime deleted file mode 100644 index 6970c8923c..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_1_2_4.eprime +++ /dev/null @@ -1,43 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..3)] of int(1..5) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..3)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3)] of int(1..4) -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_Occurrence, x_ExplicitVarSizeWithDummy] -such that - x_Occurrence[1], - or([x_ExplicitVarSizeWithDummy[q30] != 5 /\ x_ExplicitVarSizeWithDummy[q30] = 2 | q30 : int(1..3)]), - sum([toInt(x_Occurrence[q1]) | q1 : int(1..4)]) <= 3, - and([x_ExplicitVarSizeWithDummy[q2] < x_ExplicitVarSizeWithDummy[q2 + 1] \/ x_ExplicitVarSizeWithDummy[q2] = 5 - | q2 : int(1..2)]), - and([x_ExplicitVarSizeWithDummy[q3] = 5 -> x_ExplicitVarSizeWithDummy[q3 + 1] = 5 | q3 : int(1..2)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q4] != 5) | q4 : int(1..3)]) <= 3, - and([x_ExplicitVarSizeWithDummy[q7] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q7]] | q7 : int(1..3)]), - and([x_Occurrence[q8] -> - or([x_ExplicitVarSizeWithDummy[q10] != 5 /\ x_ExplicitVarSizeWithDummy[q10] = q8 | q10 : int(1..3)]) - | q8 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q11 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q11] < x_ExplicitVarSizeWithFlags_Values[q11 + 1] - | q11 : int(1..2)]), - and([x_ExplicitVarSizeWithFlags_Flags[q12] = false -> x_ExplicitVarSizeWithFlags_Values[q12] = 1 - | q12 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q13 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q13] | q13 : int(1..2)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q14]) | q14 : int(1..3)]) <= 3, - and([x_ExplicitVarSizeWithFlags_Flags[q17] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q17]] - | q17 : int(1..3)]), - and([x_Occurrence[q18] -> - or([x_ExplicitVarSizeWithFlags_Flags[q20] /\ x_ExplicitVarSizeWithFlags_Values[q20] = q18 | q20 : int(1..3)]) - | q18 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q22] -> - or([x_ExplicitVarSizeWithDummy[q24] != 5 /\ - x_ExplicitVarSizeWithDummy[q24] = x_ExplicitVarSizeWithFlags_Values[q22] - | q24 : int(1..3)]) - | q22 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q26] != 5 -> - or([x_ExplicitVarSizeWithFlags_Flags[q28] /\ - x_ExplicitVarSizeWithFlags_Values[q28] = x_ExplicitVarSizeWithDummy[q26] - | q28 : int(1..3)]) - | q26 : int(1..3)]) - diff --git a/tests/exhaustive/basic/set05/expected/model_1_3_1-solution000001.solution b/tests/exhaustive/basic/set05/expected/model_1_3_1-solution000001.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_1_3_1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/set05/expected/model_1_3_1-solution000002.solution b/tests/exhaustive/basic/set05/expected/model_1_3_1-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_1_3_1-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set05/expected/model_1_3_1-solution000003.solution b/tests/exhaustive/basic/set05/expected/model_1_3_1-solution000003.solution deleted file mode 100644 index fdc0f02f96..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_1_3_1-solution000003.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 4} diff --git a/tests/exhaustive/basic/set05/expected/model_1_3_1.eprime b/tests/exhaustive/basic/set05/expected/model_1_3_1.eprime deleted file mode 100644 index 79fbdc8209..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_1_3_1.eprime +++ /dev/null @@ -1,21 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithMarker_Marker: int(0..3) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3)] of int(1..4) -branching on [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_Occurrence] -such that - x_Occurrence[1], - or([q11 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q11] = 2 | q11 : int(1..3)]), - sum([toInt(x_Occurrence[q1]) | q1 : int(1..4)]) <= 3, - and([q2 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q2] < x_ExplicitVarSizeWithMarker_Values[q2 + 1] - | q2 : int(1..2)]), - and([q3 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q3] = 1 | q3 : int(1..3)]), - x_ExplicitVarSizeWithMarker_Marker <= 3, - and([q6 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q6]] - | q6 : int(1..3)]), - and([x_Occurrence[q7] -> - or([q9 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q9] = q7 | q9 : int(1..3)]) - | q7 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set05/expected/model_1_3_2-solution000001.solution b/tests/exhaustive/basic/set05/expected/model_1_3_2-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_1_3_2-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set05/expected/model_1_3_2-solution000002.solution b/tests/exhaustive/basic/set05/expected/model_1_3_2-solution000002.solution deleted file mode 100644 index fdc0f02f96..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_1_3_2-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 4} diff --git a/tests/exhaustive/basic/set05/expected/model_1_3_2-solution000003.solution b/tests/exhaustive/basic/set05/expected/model_1_3_2-solution000003.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_1_3_2-solution000003.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/set05/expected/model_1_3_2.eprime b/tests/exhaustive/basic/set05/expected/model_1_3_2.eprime deleted file mode 100644 index 85dcbc6f16..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_1_3_2.eprime +++ /dev/null @@ -1,41 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithMarker_Marker: int(0..3) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3)] of int(1..4) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..3)] of int(1..5) -branching on - [x_ExplicitVarSizeWithDummy, x_Occurrence, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] -such that - x_Occurrence[1], - or([q28 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q28] = 2 | q28 : int(1..3)]), - sum([toInt(x_Occurrence[q1]) | q1 : int(1..4)]) <= 3, - and([q2 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q2] < x_ExplicitVarSizeWithMarker_Values[q2 + 1] - | q2 : int(1..2)]), - and([q3 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q3] = 1 | q3 : int(1..3)]), - x_ExplicitVarSizeWithMarker_Marker <= 3, - and([q6 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q6]] - | q6 : int(1..3)]), - and([x_Occurrence[q7] -> - or([q9 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q9] = q7 | q9 : int(1..3)]) - | q7 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q10] < x_ExplicitVarSizeWithDummy[q10 + 1] \/ x_ExplicitVarSizeWithDummy[q10] = 5 - | q10 : int(1..2)]), - and([x_ExplicitVarSizeWithDummy[q11] = 5 -> x_ExplicitVarSizeWithDummy[q11 + 1] = 5 | q11 : int(1..2)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q12] != 5) | q12 : int(1..3)]) <= 3, - and([x_ExplicitVarSizeWithDummy[q15] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q15]] | q15 : int(1..3)]), - and([x_Occurrence[q16] -> - or([x_ExplicitVarSizeWithDummy[q18] != 5 /\ x_ExplicitVarSizeWithDummy[q18] = q16 | q18 : int(1..3)]) - | q16 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q20] != 5 -> - or([q22 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q22] = x_ExplicitVarSizeWithDummy[q20] - | q22 : int(1..3)]) - | q20 : int(1..3)]), - and([q24 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q26] != 5 /\ - x_ExplicitVarSizeWithDummy[q26] = x_ExplicitVarSizeWithMarker_Values[q24] - | q26 : int(1..3)]) - | q24 : int(1..3)]) - diff --git a/tests/exhaustive/basic/set05/expected/model_1_3_3-solution000001.solution b/tests/exhaustive/basic/set05/expected/model_1_3_3-solution000001.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_1_3_3-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/set05/expected/model_1_3_3-solution000002.solution b/tests/exhaustive/basic/set05/expected/model_1_3_3-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_1_3_3-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set05/expected/model_1_3_3-solution000003.solution b/tests/exhaustive/basic/set05/expected/model_1_3_3-solution000003.solution deleted file mode 100644 index fdc0f02f96..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_1_3_3-solution000003.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 4} diff --git a/tests/exhaustive/basic/set05/expected/model_1_3_3.eprime b/tests/exhaustive/basic/set05/expected/model_1_3_3.eprime deleted file mode 100644 index 79fbdc8209..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_1_3_3.eprime +++ /dev/null @@ -1,21 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithMarker_Marker: int(0..3) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3)] of int(1..4) -branching on [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_Occurrence] -such that - x_Occurrence[1], - or([q11 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q11] = 2 | q11 : int(1..3)]), - sum([toInt(x_Occurrence[q1]) | q1 : int(1..4)]) <= 3, - and([q2 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q2] < x_ExplicitVarSizeWithMarker_Values[q2 + 1] - | q2 : int(1..2)]), - and([q3 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q3] = 1 | q3 : int(1..3)]), - x_ExplicitVarSizeWithMarker_Marker <= 3, - and([q6 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q6]] - | q6 : int(1..3)]), - and([x_Occurrence[q7] -> - or([q9 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q9] = q7 | q9 : int(1..3)]) - | q7 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set05/expected/model_1_3_4-solution000001.solution b/tests/exhaustive/basic/set05/expected/model_1_3_4-solution000001.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_1_3_4-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/set05/expected/model_1_3_4-solution000002.solution b/tests/exhaustive/basic/set05/expected/model_1_3_4-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_1_3_4-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set05/expected/model_1_3_4-solution000003.solution b/tests/exhaustive/basic/set05/expected/model_1_3_4-solution000003.solution deleted file mode 100644 index fdc0f02f96..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_1_3_4-solution000003.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 4} diff --git a/tests/exhaustive/basic/set05/expected/model_1_3_4.eprime b/tests/exhaustive/basic/set05/expected/model_1_3_4.eprime deleted file mode 100644 index 5d9c9d1d13..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_1_3_4.eprime +++ /dev/null @@ -1,47 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithMarker_Marker: int(0..3) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3)] of int(1..4) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..3)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3)] of int(1..4) -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_Occurrence, - x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] -such that - x_Occurrence[1], - or([q29 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q29] = 2 | q29 : int(1..3)]), - sum([toInt(x_Occurrence[q1]) | q1 : int(1..4)]) <= 3, - and([q2 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q2] < x_ExplicitVarSizeWithMarker_Values[q2 + 1] - | q2 : int(1..2)]), - and([q3 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q3] = 1 | q3 : int(1..3)]), - x_ExplicitVarSizeWithMarker_Marker <= 3, - and([q6 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q6]] - | q6 : int(1..3)]), - and([x_Occurrence[q7] -> - or([q9 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q9] = q7 | q9 : int(1..3)]) - | q7 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q10 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q10] < x_ExplicitVarSizeWithFlags_Values[q10 + 1] - | q10 : int(1..2)]), - and([x_ExplicitVarSizeWithFlags_Flags[q11] = false -> x_ExplicitVarSizeWithFlags_Values[q11] = 1 - | q11 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q12 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q12] | q12 : int(1..2)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q13]) | q13 : int(1..3)]) <= 3, - and([x_ExplicitVarSizeWithFlags_Flags[q16] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q16]] - | q16 : int(1..3)]), - and([x_Occurrence[q17] -> - or([x_ExplicitVarSizeWithFlags_Flags[q19] /\ x_ExplicitVarSizeWithFlags_Values[q19] = q17 | q19 : int(1..3)]) - | q17 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q21] -> - or([q23 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q23] = x_ExplicitVarSizeWithFlags_Values[q21] - | q23 : int(1..3)]) - | q21 : int(1..3)]), - and([q25 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q27] /\ - x_ExplicitVarSizeWithFlags_Values[q27] = x_ExplicitVarSizeWithMarker_Values[q25] - | q27 : int(1..3)]) - | q25 : int(1..3)]) - diff --git a/tests/exhaustive/basic/set05/expected/model_1_4_1-solution000001.solution b/tests/exhaustive/basic/set05/expected/model_1_4_1-solution000001.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_1_4_1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/set05/expected/model_1_4_1-solution000002.solution b/tests/exhaustive/basic/set05/expected/model_1_4_1-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_1_4_1-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set05/expected/model_1_4_1-solution000003.solution b/tests/exhaustive/basic/set05/expected/model_1_4_1-solution000003.solution deleted file mode 100644 index fdc0f02f96..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_1_4_1-solution000003.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 4} diff --git a/tests/exhaustive/basic/set05/expected/model_1_4_1.eprime b/tests/exhaustive/basic/set05/expected/model_1_4_1.eprime deleted file mode 100644 index 9ede8575b3..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_1_4_1.eprime +++ /dev/null @@ -1,21 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..3)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3)] of int(1..4) -branching on [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_Occurrence] -such that - x_Occurrence[1], - or([x_ExplicitVarSizeWithFlags_Flags[q13] /\ x_ExplicitVarSizeWithFlags_Values[q13] = 2 | q13 : int(1..3)]), - sum([toInt(x_Occurrence[q1]) | q1 : int(1..4)]) <= 3, - and([x_ExplicitVarSizeWithFlags_Flags[q2 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q2] < x_ExplicitVarSizeWithFlags_Values[q2 + 1] - | q2 : int(1..2)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3] = false -> x_ExplicitVarSizeWithFlags_Values[q3] = 1 | q3 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q4] | q4 : int(1..2)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q5]) | q5 : int(1..3)]) <= 3, - and([x_ExplicitVarSizeWithFlags_Flags[q8] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q8]] | q8 : int(1..3)]), - and([x_Occurrence[q9] -> - or([x_ExplicitVarSizeWithFlags_Flags[q11] /\ x_ExplicitVarSizeWithFlags_Values[q11] = q9 | q11 : int(1..3)]) - | q9 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set05/expected/model_1_4_2-solution000001.solution b/tests/exhaustive/basic/set05/expected/model_1_4_2-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_1_4_2-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set05/expected/model_1_4_2-solution000002.solution b/tests/exhaustive/basic/set05/expected/model_1_4_2-solution000002.solution deleted file mode 100644 index fdc0f02f96..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_1_4_2-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 4} diff --git a/tests/exhaustive/basic/set05/expected/model_1_4_2-solution000003.solution b/tests/exhaustive/basic/set05/expected/model_1_4_2-solution000003.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_1_4_2-solution000003.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/set05/expected/model_1_4_2.eprime b/tests/exhaustive/basic/set05/expected/model_1_4_2.eprime deleted file mode 100644 index ee08cbe011..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_1_4_2.eprime +++ /dev/null @@ -1,41 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..3)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3)] of int(1..4) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..3)] of int(1..5) -branching on - [x_ExplicitVarSizeWithDummy, x_Occurrence, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] -such that - x_Occurrence[1], - or([x_ExplicitVarSizeWithFlags_Flags[q30] /\ x_ExplicitVarSizeWithFlags_Values[q30] = 2 | q30 : int(1..3)]), - sum([toInt(x_Occurrence[q1]) | q1 : int(1..4)]) <= 3, - and([x_ExplicitVarSizeWithFlags_Flags[q2 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q2] < x_ExplicitVarSizeWithFlags_Values[q2 + 1] - | q2 : int(1..2)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3] = false -> x_ExplicitVarSizeWithFlags_Values[q3] = 1 | q3 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q4] | q4 : int(1..2)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q5]) | q5 : int(1..3)]) <= 3, - and([x_ExplicitVarSizeWithFlags_Flags[q8] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q8]] | q8 : int(1..3)]), - and([x_Occurrence[q9] -> - or([x_ExplicitVarSizeWithFlags_Flags[q11] /\ x_ExplicitVarSizeWithFlags_Values[q11] = q9 | q11 : int(1..3)]) - | q9 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q12] < x_ExplicitVarSizeWithDummy[q12 + 1] \/ x_ExplicitVarSizeWithDummy[q12] = 5 - | q12 : int(1..2)]), - and([x_ExplicitVarSizeWithDummy[q13] = 5 -> x_ExplicitVarSizeWithDummy[q13 + 1] = 5 | q13 : int(1..2)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q14] != 5) | q14 : int(1..3)]) <= 3, - and([x_ExplicitVarSizeWithDummy[q17] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q17]] | q17 : int(1..3)]), - and([x_Occurrence[q18] -> - or([x_ExplicitVarSizeWithDummy[q20] != 5 /\ x_ExplicitVarSizeWithDummy[q20] = q18 | q20 : int(1..3)]) - | q18 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q22] != 5 -> - or([x_ExplicitVarSizeWithFlags_Flags[q24] /\ - x_ExplicitVarSizeWithFlags_Values[q24] = x_ExplicitVarSizeWithDummy[q22] - | q24 : int(1..3)]) - | q22 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q26] -> - or([x_ExplicitVarSizeWithDummy[q28] != 5 /\ - x_ExplicitVarSizeWithDummy[q28] = x_ExplicitVarSizeWithFlags_Values[q26] - | q28 : int(1..3)]) - | q26 : int(1..3)]) - diff --git a/tests/exhaustive/basic/set05/expected/model_1_4_3-solution000001.solution b/tests/exhaustive/basic/set05/expected/model_1_4_3-solution000001.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_1_4_3-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/set05/expected/model_1_4_3-solution000002.solution b/tests/exhaustive/basic/set05/expected/model_1_4_3-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_1_4_3-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set05/expected/model_1_4_3-solution000003.solution b/tests/exhaustive/basic/set05/expected/model_1_4_3-solution000003.solution deleted file mode 100644 index fdc0f02f96..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_1_4_3-solution000003.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 4} diff --git a/tests/exhaustive/basic/set05/expected/model_1_4_3.eprime b/tests/exhaustive/basic/set05/expected/model_1_4_3.eprime deleted file mode 100644 index 387a3320f5..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_1_4_3.eprime +++ /dev/null @@ -1,46 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..3)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3)] of int(1..4) -find x_ExplicitVarSizeWithMarker_Marker: int(0..3) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3)] of int(1..4) -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_Occurrence, - x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] -such that - x_Occurrence[1], - or([x_ExplicitVarSizeWithFlags_Flags[q29] /\ x_ExplicitVarSizeWithFlags_Values[q29] = 2 | q29 : int(1..3)]), - sum([toInt(x_Occurrence[q1]) | q1 : int(1..4)]) <= 3, - and([x_ExplicitVarSizeWithFlags_Flags[q2 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q2] < x_ExplicitVarSizeWithFlags_Values[q2 + 1] - | q2 : int(1..2)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3] = false -> x_ExplicitVarSizeWithFlags_Values[q3] = 1 | q3 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q4] | q4 : int(1..2)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q5]) | q5 : int(1..3)]) <= 3, - and([x_ExplicitVarSizeWithFlags_Flags[q8] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q8]] | q8 : int(1..3)]), - and([x_Occurrence[q9] -> - or([x_ExplicitVarSizeWithFlags_Flags[q11] /\ x_ExplicitVarSizeWithFlags_Values[q11] = q9 | q11 : int(1..3)]) - | q9 : int(1..4)]), - and([q12 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q12] < x_ExplicitVarSizeWithMarker_Values[q12 + 1] - | q12 : int(1..2)]), - and([q13 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q13] = 1 | q13 : int(1..3)]), - x_ExplicitVarSizeWithMarker_Marker <= 3, - and([q16 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q16]] - | q16 : int(1..3)]), - and([x_Occurrence[q17] -> - or([q19 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q19] = q17 - | q19 : int(1..3)]) - | q17 : int(1..4)]), - and([q21 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q23] /\ - x_ExplicitVarSizeWithFlags_Values[q23] = x_ExplicitVarSizeWithMarker_Values[q21] - | q23 : int(1..3)]) - | q21 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q25] -> - or([q27 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q27] = x_ExplicitVarSizeWithFlags_Values[q25] - | q27 : int(1..3)]) - | q25 : int(1..3)]) - diff --git a/tests/exhaustive/basic/set05/expected/model_1_4_4-solution000001.solution b/tests/exhaustive/basic/set05/expected/model_1_4_4-solution000001.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_1_4_4-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/set05/expected/model_1_4_4-solution000002.solution b/tests/exhaustive/basic/set05/expected/model_1_4_4-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_1_4_4-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set05/expected/model_1_4_4-solution000003.solution b/tests/exhaustive/basic/set05/expected/model_1_4_4-solution000003.solution deleted file mode 100644 index fdc0f02f96..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_1_4_4-solution000003.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 4} diff --git a/tests/exhaustive/basic/set05/expected/model_1_4_4.eprime b/tests/exhaustive/basic/set05/expected/model_1_4_4.eprime deleted file mode 100644 index 9ede8575b3..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_1_4_4.eprime +++ /dev/null @@ -1,21 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..3)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3)] of int(1..4) -branching on [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_Occurrence] -such that - x_Occurrence[1], - or([x_ExplicitVarSizeWithFlags_Flags[q13] /\ x_ExplicitVarSizeWithFlags_Values[q13] = 2 | q13 : int(1..3)]), - sum([toInt(x_Occurrence[q1]) | q1 : int(1..4)]) <= 3, - and([x_ExplicitVarSizeWithFlags_Flags[q2 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q2] < x_ExplicitVarSizeWithFlags_Values[q2 + 1] - | q2 : int(1..2)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3] = false -> x_ExplicitVarSizeWithFlags_Values[q3] = 1 | q3 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q4] | q4 : int(1..2)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q5]) | q5 : int(1..3)]) <= 3, - and([x_ExplicitVarSizeWithFlags_Flags[q8] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q8]] | q8 : int(1..3)]), - and([x_Occurrence[q9] -> - or([x_ExplicitVarSizeWithFlags_Flags[q11] /\ x_ExplicitVarSizeWithFlags_Values[q11] = q9 | q11 : int(1..3)]) - | q9 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set05/expected/model_2_1_1-solution000001.solution b/tests/exhaustive/basic/set05/expected/model_2_1_1-solution000001.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_2_1_1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/set05/expected/model_2_1_1-solution000002.solution b/tests/exhaustive/basic/set05/expected/model_2_1_1-solution000002.solution deleted file mode 100644 index fdc0f02f96..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_2_1_1-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 4} diff --git a/tests/exhaustive/basic/set05/expected/model_2_1_1-solution000003.solution b/tests/exhaustive/basic/set05/expected/model_2_1_1-solution000003.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_2_1_1-solution000003.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set05/expected/model_2_1_1.eprime b/tests/exhaustive/basic/set05/expected/model_2_1_1.eprime deleted file mode 100644 index 6b99e48d14..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_2_1_1.eprime +++ /dev/null @@ -1,18 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..3)] of int(1..5) -find x_Occurrence: matrix indexed by [int(1..4)] of bool -branching on [x_Occurrence, x_ExplicitVarSizeWithDummy] -such that - or([x_ExplicitVarSizeWithDummy[q12] != 5 /\ x_ExplicitVarSizeWithDummy[q12] = 1 | q12 : int(1..3)]), - x_Occurrence[2], - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 5 - | q1 : int(1..2)]), - and([x_ExplicitVarSizeWithDummy[q2] = 5 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..2)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 5) | q3 : int(1..3)]) <= 3, - sum([toInt(x_Occurrence[q5]) | q5 : int(1..4)]) <= 3, - and([x_Occurrence[q6] -> - or([x_ExplicitVarSizeWithDummy[q8] != 5 /\ x_ExplicitVarSizeWithDummy[q8] = q6 | q8 : int(1..3)]) - | q6 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q10] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q10]] | q10 : int(1..3)]) - diff --git a/tests/exhaustive/basic/set05/expected/model_2_1_2-solution000001.solution b/tests/exhaustive/basic/set05/expected/model_2_1_2-solution000001.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_2_1_2-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/set05/expected/model_2_1_2-solution000002.solution b/tests/exhaustive/basic/set05/expected/model_2_1_2-solution000002.solution deleted file mode 100644 index fdc0f02f96..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_2_1_2-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 4} diff --git a/tests/exhaustive/basic/set05/expected/model_2_1_2-solution000003.solution b/tests/exhaustive/basic/set05/expected/model_2_1_2-solution000003.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_2_1_2-solution000003.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set05/expected/model_2_1_2.eprime b/tests/exhaustive/basic/set05/expected/model_2_1_2.eprime deleted file mode 100644 index 6b99e48d14..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_2_1_2.eprime +++ /dev/null @@ -1,18 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..3)] of int(1..5) -find x_Occurrence: matrix indexed by [int(1..4)] of bool -branching on [x_Occurrence, x_ExplicitVarSizeWithDummy] -such that - or([x_ExplicitVarSizeWithDummy[q12] != 5 /\ x_ExplicitVarSizeWithDummy[q12] = 1 | q12 : int(1..3)]), - x_Occurrence[2], - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 5 - | q1 : int(1..2)]), - and([x_ExplicitVarSizeWithDummy[q2] = 5 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..2)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 5) | q3 : int(1..3)]) <= 3, - sum([toInt(x_Occurrence[q5]) | q5 : int(1..4)]) <= 3, - and([x_Occurrence[q6] -> - or([x_ExplicitVarSizeWithDummy[q8] != 5 /\ x_ExplicitVarSizeWithDummy[q8] = q6 | q8 : int(1..3)]) - | q6 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q10] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q10]] | q10 : int(1..3)]) - diff --git a/tests/exhaustive/basic/set05/expected/model_2_1_3-solution000001.solution b/tests/exhaustive/basic/set05/expected/model_2_1_3-solution000001.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_2_1_3-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/set05/expected/model_2_1_3-solution000002.solution b/tests/exhaustive/basic/set05/expected/model_2_1_3-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_2_1_3-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set05/expected/model_2_1_3-solution000003.solution b/tests/exhaustive/basic/set05/expected/model_2_1_3-solution000003.solution deleted file mode 100644 index fdc0f02f96..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_2_1_3-solution000003.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 4} diff --git a/tests/exhaustive/basic/set05/expected/model_2_1_3.eprime b/tests/exhaustive/basic/set05/expected/model_2_1_3.eprime deleted file mode 100644 index 3afbad58c6..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_2_1_3.eprime +++ /dev/null @@ -1,42 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..3)] of int(1..5) -find x_Occurrence: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithMarker_Marker: int(0..3) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3)] of int(1..4) -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy, x_Occurrence] -such that - or([x_ExplicitVarSizeWithDummy[q28] != 5 /\ x_ExplicitVarSizeWithDummy[q28] = 1 | q28 : int(1..3)]), - x_Occurrence[2], - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 5 - | q1 : int(1..2)]), - and([x_ExplicitVarSizeWithDummy[q2] = 5 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..2)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 5) | q3 : int(1..3)]) <= 3, - sum([toInt(x_Occurrence[q5]) | q5 : int(1..4)]) <= 3, - and([x_Occurrence[q22] -> - or([x_ExplicitVarSizeWithDummy[q24] != 5 /\ x_ExplicitVarSizeWithDummy[q24] = q22 | q24 : int(1..3)]) - | q22 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q26] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q26]] | q26 : int(1..3)]), - and([q6 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q6] < x_ExplicitVarSizeWithMarker_Values[q6 + 1] - | q6 : int(1..2)]), - and([q7 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q7] = 1 | q7 : int(1..3)]), - x_ExplicitVarSizeWithMarker_Marker <= 3, - and([q10 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q12] != 5 /\ - x_ExplicitVarSizeWithDummy[q12] = x_ExplicitVarSizeWithMarker_Values[q10] - | q12 : int(1..3)]) - | q10 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q14] != 5 -> - or([q16 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q16] = x_ExplicitVarSizeWithDummy[q14] - | q16 : int(1..3)]) - | q14 : int(1..3)]), - and([q18 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q18]] - | q18 : int(1..3)]), - and([x_Occurrence[q19] -> - or([q21 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q21] = q19 - | q21 : int(1..3)]) - | q19 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set05/expected/model_2_1_4-solution000001.solution b/tests/exhaustive/basic/set05/expected/model_2_1_4-solution000001.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_2_1_4-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/set05/expected/model_2_1_4-solution000002.solution b/tests/exhaustive/basic/set05/expected/model_2_1_4-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_2_1_4-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set05/expected/model_2_1_4-solution000003.solution b/tests/exhaustive/basic/set05/expected/model_2_1_4-solution000003.solution deleted file mode 100644 index fdc0f02f96..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_2_1_4-solution000003.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 4} diff --git a/tests/exhaustive/basic/set05/expected/model_2_1_4.eprime b/tests/exhaustive/basic/set05/expected/model_2_1_4.eprime deleted file mode 100644 index 3cf7e10a32..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_2_1_4.eprime +++ /dev/null @@ -1,42 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..3)] of int(1..5) -find x_Occurrence: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..3)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3)] of int(1..4) -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy, x_Occurrence] -such that - or([x_ExplicitVarSizeWithDummy[q30] != 5 /\ x_ExplicitVarSizeWithDummy[q30] = 1 | q30 : int(1..3)]), - x_Occurrence[2], - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 5 - | q1 : int(1..2)]), - and([x_ExplicitVarSizeWithDummy[q2] = 5 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..2)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 5) | q3 : int(1..3)]) <= 3, - sum([toInt(x_Occurrence[q5]) | q5 : int(1..4)]) <= 3, - and([x_Occurrence[q24] -> - or([x_ExplicitVarSizeWithDummy[q26] != 5 /\ x_ExplicitVarSizeWithDummy[q26] = q24 | q26 : int(1..3)]) - | q24 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q28] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q28]] | q28 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q6] < x_ExplicitVarSizeWithFlags_Values[q6 + 1] - | q6 : int(1..2)]), - and([x_ExplicitVarSizeWithFlags_Flags[q7] = false -> x_ExplicitVarSizeWithFlags_Values[q7] = 1 | q7 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q8 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q8] | q8 : int(1..2)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q9]) | q9 : int(1..3)]) <= 3, - and([x_ExplicitVarSizeWithFlags_Flags[q12] -> - or([x_ExplicitVarSizeWithDummy[q14] != 5 /\ - x_ExplicitVarSizeWithDummy[q14] = x_ExplicitVarSizeWithFlags_Values[q12] - | q14 : int(1..3)]) - | q12 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q16] != 5 -> - or([x_ExplicitVarSizeWithFlags_Flags[q18] /\ - x_ExplicitVarSizeWithFlags_Values[q18] = x_ExplicitVarSizeWithDummy[q16] - | q18 : int(1..3)]) - | q16 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q20] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q20]] - | q20 : int(1..3)]), - and([x_Occurrence[q21] -> - or([x_ExplicitVarSizeWithFlags_Flags[q23] /\ x_ExplicitVarSizeWithFlags_Values[q23] = q21 | q23 : int(1..3)]) - | q21 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set05/expected/model_2_2_1-solution000001.solution b/tests/exhaustive/basic/set05/expected/model_2_2_1-solution000001.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_2_2_1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/set05/expected/model_2_2_1-solution000002.solution b/tests/exhaustive/basic/set05/expected/model_2_2_1-solution000002.solution deleted file mode 100644 index fdc0f02f96..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_2_2_1-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 4} diff --git a/tests/exhaustive/basic/set05/expected/model_2_2_1-solution000003.solution b/tests/exhaustive/basic/set05/expected/model_2_2_1-solution000003.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_2_2_1-solution000003.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set05/expected/model_2_2_1.eprime b/tests/exhaustive/basic/set05/expected/model_2_2_1.eprime deleted file mode 100644 index cb17af9c96..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_2_2_1.eprime +++ /dev/null @@ -1,18 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..3)] of int(1..5) -find x_Occurrence: matrix indexed by [int(1..4)] of bool -branching on [x_Occurrence, x_ExplicitVarSizeWithDummy] -such that - or([x_ExplicitVarSizeWithDummy[q12] != 5 /\ x_ExplicitVarSizeWithDummy[q12] = 1 | q12 : int(1..3)]), - or([x_ExplicitVarSizeWithDummy[q14] != 5 /\ x_ExplicitVarSizeWithDummy[q14] = 2 | q14 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 5 - | q1 : int(1..2)]), - and([x_ExplicitVarSizeWithDummy[q2] = 5 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..2)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 5) | q3 : int(1..3)]) <= 3, - sum([toInt(x_Occurrence[q5]) | q5 : int(1..4)]) <= 3, - and([x_Occurrence[q6] -> - or([x_ExplicitVarSizeWithDummy[q8] != 5 /\ x_ExplicitVarSizeWithDummy[q8] = q6 | q8 : int(1..3)]) - | q6 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q10] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q10]] | q10 : int(1..3)]) - diff --git a/tests/exhaustive/basic/set05/expected/model_2_2_2-solution000001.solution b/tests/exhaustive/basic/set05/expected/model_2_2_2-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_2_2_2-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set05/expected/model_2_2_2-solution000002.solution b/tests/exhaustive/basic/set05/expected/model_2_2_2-solution000002.solution deleted file mode 100644 index fdc0f02f96..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_2_2_2-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 4} diff --git a/tests/exhaustive/basic/set05/expected/model_2_2_2-solution000003.solution b/tests/exhaustive/basic/set05/expected/model_2_2_2-solution000003.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_2_2_2-solution000003.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/set05/expected/model_2_2_2.eprime b/tests/exhaustive/basic/set05/expected/model_2_2_2.eprime deleted file mode 100644 index 4cb7d7d439..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_2_2_2.eprime +++ /dev/null @@ -1,12 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..3)] of int(1..5) -branching on [x_ExplicitVarSizeWithDummy] -such that - or([x_ExplicitVarSizeWithDummy[q6] != 5 /\ x_ExplicitVarSizeWithDummy[q6] = 1 | q6 : int(1..3)]), - or([x_ExplicitVarSizeWithDummy[q8] != 5 /\ x_ExplicitVarSizeWithDummy[q8] = 2 | q8 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 5 - | q1 : int(1..2)]), - and([x_ExplicitVarSizeWithDummy[q2] = 5 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..2)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 5) | q3 : int(1..3)]) <= 3 - diff --git a/tests/exhaustive/basic/set05/expected/model_2_2_3-solution000001.solution b/tests/exhaustive/basic/set05/expected/model_2_2_3-solution000001.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_2_2_3-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/set05/expected/model_2_2_3-solution000002.solution b/tests/exhaustive/basic/set05/expected/model_2_2_3-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_2_2_3-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set05/expected/model_2_2_3-solution000003.solution b/tests/exhaustive/basic/set05/expected/model_2_2_3-solution000003.solution deleted file mode 100644 index fdc0f02f96..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_2_2_3-solution000003.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 4} diff --git a/tests/exhaustive/basic/set05/expected/model_2_2_3.eprime b/tests/exhaustive/basic/set05/expected/model_2_2_3.eprime deleted file mode 100644 index e60bea847e..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_2_2_3.eprime +++ /dev/null @@ -1,29 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..3)] of int(1..5) -find x_ExplicitVarSizeWithMarker_Marker: int(0..3) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3)] of int(1..4) -branching on [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy] -such that - or([x_ExplicitVarSizeWithDummy[q17] != 5 /\ x_ExplicitVarSizeWithDummy[q17] = 1 | q17 : int(1..3)]), - or([x_ExplicitVarSizeWithDummy[q19] != 5 /\ x_ExplicitVarSizeWithDummy[q19] = 2 | q19 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 5 - | q1 : int(1..2)]), - and([x_ExplicitVarSizeWithDummy[q2] = 5 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..2)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 5) | q3 : int(1..3)]) <= 3, - and([q5 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q5] < x_ExplicitVarSizeWithMarker_Values[q5 + 1] - | q5 : int(1..2)]), - and([q6 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q6] = 1 | q6 : int(1..3)]), - x_ExplicitVarSizeWithMarker_Marker <= 3, - and([q9 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q11] != 5 /\ - x_ExplicitVarSizeWithDummy[q11] = x_ExplicitVarSizeWithMarker_Values[q9] - | q11 : int(1..3)]) - | q9 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q13] != 5 -> - or([q15 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q15] = x_ExplicitVarSizeWithDummy[q13] - | q15 : int(1..3)]) - | q13 : int(1..3)]) - diff --git a/tests/exhaustive/basic/set05/expected/model_2_2_4-solution000001.solution b/tests/exhaustive/basic/set05/expected/model_2_2_4-solution000001.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_2_2_4-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/set05/expected/model_2_2_4-solution000002.solution b/tests/exhaustive/basic/set05/expected/model_2_2_4-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_2_2_4-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set05/expected/model_2_2_4-solution000003.solution b/tests/exhaustive/basic/set05/expected/model_2_2_4-solution000003.solution deleted file mode 100644 index fdc0f02f96..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_2_2_4-solution000003.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 4} diff --git a/tests/exhaustive/basic/set05/expected/model_2_2_4.eprime b/tests/exhaustive/basic/set05/expected/model_2_2_4.eprime deleted file mode 100644 index 06f804e4d5..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_2_2_4.eprime +++ /dev/null @@ -1,30 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..3)] of int(1..5) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..3)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3)] of int(1..4) -branching on [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy] -such that - or([x_ExplicitVarSizeWithDummy[q19] != 5 /\ x_ExplicitVarSizeWithDummy[q19] = 1 | q19 : int(1..3)]), - or([x_ExplicitVarSizeWithDummy[q21] != 5 /\ x_ExplicitVarSizeWithDummy[q21] = 2 | q21 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 5 - | q1 : int(1..2)]), - and([x_ExplicitVarSizeWithDummy[q2] = 5 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..2)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 5) | q3 : int(1..3)]) <= 3, - and([x_ExplicitVarSizeWithFlags_Flags[q5 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q5] < x_ExplicitVarSizeWithFlags_Values[q5 + 1] - | q5 : int(1..2)]), - and([x_ExplicitVarSizeWithFlags_Flags[q6] = false -> x_ExplicitVarSizeWithFlags_Values[q6] = 1 | q6 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q7] | q7 : int(1..2)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q8]) | q8 : int(1..3)]) <= 3, - and([x_ExplicitVarSizeWithFlags_Flags[q11] -> - or([x_ExplicitVarSizeWithDummy[q13] != 5 /\ - x_ExplicitVarSizeWithDummy[q13] = x_ExplicitVarSizeWithFlags_Values[q11] - | q13 : int(1..3)]) - | q11 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q15] != 5 -> - or([x_ExplicitVarSizeWithFlags_Flags[q17] /\ - x_ExplicitVarSizeWithFlags_Values[q17] = x_ExplicitVarSizeWithDummy[q15] - | q17 : int(1..3)]) - | q15 : int(1..3)]) - diff --git a/tests/exhaustive/basic/set05/expected/model_2_3_1-solution000001.solution b/tests/exhaustive/basic/set05/expected/model_2_3_1-solution000001.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_2_3_1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/set05/expected/model_2_3_1-solution000002.solution b/tests/exhaustive/basic/set05/expected/model_2_3_1-solution000002.solution deleted file mode 100644 index fdc0f02f96..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_2_3_1-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 4} diff --git a/tests/exhaustive/basic/set05/expected/model_2_3_1-solution000003.solution b/tests/exhaustive/basic/set05/expected/model_2_3_1-solution000003.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_2_3_1-solution000003.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set05/expected/model_2_3_1.eprime b/tests/exhaustive/basic/set05/expected/model_2_3_1.eprime deleted file mode 100644 index 40eab4116d..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_2_3_1.eprime +++ /dev/null @@ -1,42 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..3)] of int(1..5) -find x_ExplicitVarSizeWithMarker_Marker: int(0..3) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3)] of int(1..4) -find x_Occurrence: matrix indexed by [int(1..4)] of bool -branching on - [x_Occurrence, x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] -such that - or([x_ExplicitVarSizeWithDummy[q28] != 5 /\ x_ExplicitVarSizeWithDummy[q28] = 1 | q28 : int(1..3)]), - or([q30 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q30] = 2 | q30 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 5 - | q1 : int(1..2)]), - and([x_ExplicitVarSizeWithDummy[q2] = 5 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..2)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 5) | q3 : int(1..3)]) <= 3, - and([q5 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q5] < x_ExplicitVarSizeWithMarker_Values[q5 + 1] - | q5 : int(1..2)]), - and([q6 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q6] = 1 | q6 : int(1..3)]), - x_ExplicitVarSizeWithMarker_Marker <= 3, - and([q9 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q11] != 5 /\ - x_ExplicitVarSizeWithDummy[q11] = x_ExplicitVarSizeWithMarker_Values[q9] - | q11 : int(1..3)]) - | q9 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q13] != 5 -> - or([q15 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q15] = x_ExplicitVarSizeWithDummy[q13] - | q15 : int(1..3)]) - | q13 : int(1..3)]), - sum([toInt(x_Occurrence[q16]) | q16 : int(1..4)]) <= 3, - and([x_Occurrence[q17] -> - or([x_ExplicitVarSizeWithDummy[q19] != 5 /\ x_ExplicitVarSizeWithDummy[q19] = q17 | q19 : int(1..3)]) - | q17 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q21] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q21]] | q21 : int(1..3)]), - and([x_Occurrence[q22] -> - or([q24 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q24] = q22 - | q24 : int(1..3)]) - | q22 : int(1..4)]), - and([q26 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q26]] - | q26 : int(1..3)]) - diff --git a/tests/exhaustive/basic/set05/expected/model_2_3_2-solution000001.solution b/tests/exhaustive/basic/set05/expected/model_2_3_2-solution000001.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_2_3_2-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/set05/expected/model_2_3_2-solution000002.solution b/tests/exhaustive/basic/set05/expected/model_2_3_2-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_2_3_2-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set05/expected/model_2_3_2-solution000003.solution b/tests/exhaustive/basic/set05/expected/model_2_3_2-solution000003.solution deleted file mode 100644 index fdc0f02f96..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_2_3_2-solution000003.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 4} diff --git a/tests/exhaustive/basic/set05/expected/model_2_3_2.eprime b/tests/exhaustive/basic/set05/expected/model_2_3_2.eprime deleted file mode 100644 index 9ddf8ddf04..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_2_3_2.eprime +++ /dev/null @@ -1,29 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..3)] of int(1..5) -find x_ExplicitVarSizeWithMarker_Marker: int(0..3) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3)] of int(1..4) -branching on [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy] -such that - or([x_ExplicitVarSizeWithDummy[q17] != 5 /\ x_ExplicitVarSizeWithDummy[q17] = 1 | q17 : int(1..3)]), - or([q19 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q19] = 2 | q19 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 5 - | q1 : int(1..2)]), - and([x_ExplicitVarSizeWithDummy[q2] = 5 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..2)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 5) | q3 : int(1..3)]) <= 3, - and([q5 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q5] < x_ExplicitVarSizeWithMarker_Values[q5 + 1] - | q5 : int(1..2)]), - and([q6 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q6] = 1 | q6 : int(1..3)]), - x_ExplicitVarSizeWithMarker_Marker <= 3, - and([q9 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q11] != 5 /\ - x_ExplicitVarSizeWithDummy[q11] = x_ExplicitVarSizeWithMarker_Values[q9] - | q11 : int(1..3)]) - | q9 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q13] != 5 -> - or([q15 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q15] = x_ExplicitVarSizeWithDummy[q13] - | q15 : int(1..3)]) - | q13 : int(1..3)]) - diff --git a/tests/exhaustive/basic/set05/expected/model_2_3_3-solution000001.solution b/tests/exhaustive/basic/set05/expected/model_2_3_3-solution000001.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_2_3_3-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/set05/expected/model_2_3_3-solution000002.solution b/tests/exhaustive/basic/set05/expected/model_2_3_3-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_2_3_3-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set05/expected/model_2_3_3-solution000003.solution b/tests/exhaustive/basic/set05/expected/model_2_3_3-solution000003.solution deleted file mode 100644 index fdc0f02f96..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_2_3_3-solution000003.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 4} diff --git a/tests/exhaustive/basic/set05/expected/model_2_3_3.eprime b/tests/exhaustive/basic/set05/expected/model_2_3_3.eprime deleted file mode 100644 index 9ddf8ddf04..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_2_3_3.eprime +++ /dev/null @@ -1,29 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..3)] of int(1..5) -find x_ExplicitVarSizeWithMarker_Marker: int(0..3) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3)] of int(1..4) -branching on [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy] -such that - or([x_ExplicitVarSizeWithDummy[q17] != 5 /\ x_ExplicitVarSizeWithDummy[q17] = 1 | q17 : int(1..3)]), - or([q19 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q19] = 2 | q19 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 5 - | q1 : int(1..2)]), - and([x_ExplicitVarSizeWithDummy[q2] = 5 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..2)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 5) | q3 : int(1..3)]) <= 3, - and([q5 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q5] < x_ExplicitVarSizeWithMarker_Values[q5 + 1] - | q5 : int(1..2)]), - and([q6 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q6] = 1 | q6 : int(1..3)]), - x_ExplicitVarSizeWithMarker_Marker <= 3, - and([q9 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q11] != 5 /\ - x_ExplicitVarSizeWithDummy[q11] = x_ExplicitVarSizeWithMarker_Values[q9] - | q11 : int(1..3)]) - | q9 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q13] != 5 -> - or([q15 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q15] = x_ExplicitVarSizeWithDummy[q13] - | q15 : int(1..3)]) - | q13 : int(1..3)]) - diff --git a/tests/exhaustive/basic/set05/expected/model_2_3_4-solution000001.solution b/tests/exhaustive/basic/set05/expected/model_2_3_4-solution000001.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_2_3_4-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/set05/expected/model_2_3_4-solution000002.solution b/tests/exhaustive/basic/set05/expected/model_2_3_4-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_2_3_4-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set05/expected/model_2_3_4-solution000003.solution b/tests/exhaustive/basic/set05/expected/model_2_3_4-solution000003.solution deleted file mode 100644 index fdc0f02f96..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_2_3_4-solution000003.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 4} diff --git a/tests/exhaustive/basic/set05/expected/model_2_3_4.eprime b/tests/exhaustive/basic/set05/expected/model_2_3_4.eprime deleted file mode 100644 index 933ef63b6a..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_2_3_4.eprime +++ /dev/null @@ -1,60 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..3)] of int(1..5) -find x_ExplicitVarSizeWithMarker_Marker: int(0..3) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3)] of int(1..4) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..3)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3)] of int(1..4) -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy, - x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] -such that - or([x_ExplicitVarSizeWithDummy[q38] != 5 /\ x_ExplicitVarSizeWithDummy[q38] = 1 | q38 : int(1..3)]), - or([q40 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q40] = 2 | q40 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 5 - | q1 : int(1..2)]), - and([x_ExplicitVarSizeWithDummy[q2] = 5 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..2)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 5) | q3 : int(1..3)]) <= 3, - and([q5 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q5] < x_ExplicitVarSizeWithMarker_Values[q5 + 1] - | q5 : int(1..2)]), - and([q6 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q6] = 1 | q6 : int(1..3)]), - x_ExplicitVarSizeWithMarker_Marker <= 3, - and([q9 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q11] != 5 /\ - x_ExplicitVarSizeWithDummy[q11] = x_ExplicitVarSizeWithMarker_Values[q9] - | q11 : int(1..3)]) - | q9 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q13] != 5 -> - or([q15 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q15] = x_ExplicitVarSizeWithDummy[q13] - | q15 : int(1..3)]) - | q13 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q16 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q16] < x_ExplicitVarSizeWithFlags_Values[q16 + 1] - | q16 : int(1..2)]), - and([x_ExplicitVarSizeWithFlags_Flags[q17] = false -> x_ExplicitVarSizeWithFlags_Values[q17] = 1 - | q17 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q18 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q18] | q18 : int(1..2)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q19]) | q19 : int(1..3)]) <= 3, - and([x_ExplicitVarSizeWithFlags_Flags[q22] -> - or([x_ExplicitVarSizeWithDummy[q24] != 5 /\ - x_ExplicitVarSizeWithDummy[q24] = x_ExplicitVarSizeWithFlags_Values[q22] - | q24 : int(1..3)]) - | q22 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q26] != 5 -> - or([x_ExplicitVarSizeWithFlags_Flags[q28] /\ - x_ExplicitVarSizeWithFlags_Values[q28] = x_ExplicitVarSizeWithDummy[q26] - | q28 : int(1..3)]) - | q26 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q30] -> - or([q32 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q32] = x_ExplicitVarSizeWithFlags_Values[q30] - | q32 : int(1..3)]) - | q30 : int(1..3)]), - and([q34 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q36] /\ - x_ExplicitVarSizeWithFlags_Values[q36] = x_ExplicitVarSizeWithMarker_Values[q34] - | q36 : int(1..3)]) - | q34 : int(1..3)]) - diff --git a/tests/exhaustive/basic/set05/expected/model_2_4_1-solution000001.solution b/tests/exhaustive/basic/set05/expected/model_2_4_1-solution000001.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_2_4_1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/set05/expected/model_2_4_1-solution000002.solution b/tests/exhaustive/basic/set05/expected/model_2_4_1-solution000002.solution deleted file mode 100644 index fdc0f02f96..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_2_4_1-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 4} diff --git a/tests/exhaustive/basic/set05/expected/model_2_4_1-solution000003.solution b/tests/exhaustive/basic/set05/expected/model_2_4_1-solution000003.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_2_4_1-solution000003.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set05/expected/model_2_4_1.eprime b/tests/exhaustive/basic/set05/expected/model_2_4_1.eprime deleted file mode 100644 index 81a9200abd..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_2_4_1.eprime +++ /dev/null @@ -1,42 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..3)] of int(1..5) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..3)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3)] of int(1..4) -find x_Occurrence: matrix indexed by [int(1..4)] of bool -branching on - [x_Occurrence, x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] -such that - or([x_ExplicitVarSizeWithDummy[q30] != 5 /\ x_ExplicitVarSizeWithDummy[q30] = 1 | q30 : int(1..3)]), - or([x_ExplicitVarSizeWithFlags_Flags[q32] /\ x_ExplicitVarSizeWithFlags_Values[q32] = 2 | q32 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 5 - | q1 : int(1..2)]), - and([x_ExplicitVarSizeWithDummy[q2] = 5 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..2)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 5) | q3 : int(1..3)]) <= 3, - and([x_ExplicitVarSizeWithFlags_Flags[q5 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q5] < x_ExplicitVarSizeWithFlags_Values[q5 + 1] - | q5 : int(1..2)]), - and([x_ExplicitVarSizeWithFlags_Flags[q6] = false -> x_ExplicitVarSizeWithFlags_Values[q6] = 1 | q6 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q7] | q7 : int(1..2)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q8]) | q8 : int(1..3)]) <= 3, - and([x_ExplicitVarSizeWithFlags_Flags[q11] -> - or([x_ExplicitVarSizeWithDummy[q13] != 5 /\ - x_ExplicitVarSizeWithDummy[q13] = x_ExplicitVarSizeWithFlags_Values[q11] - | q13 : int(1..3)]) - | q11 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q15] != 5 -> - or([x_ExplicitVarSizeWithFlags_Flags[q17] /\ - x_ExplicitVarSizeWithFlags_Values[q17] = x_ExplicitVarSizeWithDummy[q15] - | q17 : int(1..3)]) - | q15 : int(1..3)]), - sum([toInt(x_Occurrence[q18]) | q18 : int(1..4)]) <= 3, - and([x_Occurrence[q19] -> - or([x_ExplicitVarSizeWithDummy[q21] != 5 /\ x_ExplicitVarSizeWithDummy[q21] = q19 | q21 : int(1..3)]) - | q19 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q23] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q23]] | q23 : int(1..3)]), - and([x_Occurrence[q24] -> - or([x_ExplicitVarSizeWithFlags_Flags[q26] /\ x_ExplicitVarSizeWithFlags_Values[q26] = q24 | q26 : int(1..3)]) - | q24 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q28] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q28]] - | q28 : int(1..3)]) - diff --git a/tests/exhaustive/basic/set05/expected/model_2_4_2-solution000001.solution b/tests/exhaustive/basic/set05/expected/model_2_4_2-solution000001.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_2_4_2-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/set05/expected/model_2_4_2-solution000002.solution b/tests/exhaustive/basic/set05/expected/model_2_4_2-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_2_4_2-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set05/expected/model_2_4_2-solution000003.solution b/tests/exhaustive/basic/set05/expected/model_2_4_2-solution000003.solution deleted file mode 100644 index fdc0f02f96..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_2_4_2-solution000003.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 4} diff --git a/tests/exhaustive/basic/set05/expected/model_2_4_2.eprime b/tests/exhaustive/basic/set05/expected/model_2_4_2.eprime deleted file mode 100644 index c9dd09c7ea..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_2_4_2.eprime +++ /dev/null @@ -1,30 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..3)] of int(1..5) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..3)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3)] of int(1..4) -branching on [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy] -such that - or([x_ExplicitVarSizeWithDummy[q19] != 5 /\ x_ExplicitVarSizeWithDummy[q19] = 1 | q19 : int(1..3)]), - or([x_ExplicitVarSizeWithFlags_Flags[q21] /\ x_ExplicitVarSizeWithFlags_Values[q21] = 2 | q21 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 5 - | q1 : int(1..2)]), - and([x_ExplicitVarSizeWithDummy[q2] = 5 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..2)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 5) | q3 : int(1..3)]) <= 3, - and([x_ExplicitVarSizeWithFlags_Flags[q5 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q5] < x_ExplicitVarSizeWithFlags_Values[q5 + 1] - | q5 : int(1..2)]), - and([x_ExplicitVarSizeWithFlags_Flags[q6] = false -> x_ExplicitVarSizeWithFlags_Values[q6] = 1 | q6 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q7] | q7 : int(1..2)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q8]) | q8 : int(1..3)]) <= 3, - and([x_ExplicitVarSizeWithFlags_Flags[q11] -> - or([x_ExplicitVarSizeWithDummy[q13] != 5 /\ - x_ExplicitVarSizeWithDummy[q13] = x_ExplicitVarSizeWithFlags_Values[q11] - | q13 : int(1..3)]) - | q11 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q15] != 5 -> - or([x_ExplicitVarSizeWithFlags_Flags[q17] /\ - x_ExplicitVarSizeWithFlags_Values[q17] = x_ExplicitVarSizeWithDummy[q15] - | q17 : int(1..3)]) - | q15 : int(1..3)]) - diff --git a/tests/exhaustive/basic/set05/expected/model_2_4_3-solution000001.solution b/tests/exhaustive/basic/set05/expected/model_2_4_3-solution000001.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_2_4_3-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/set05/expected/model_2_4_3-solution000002.solution b/tests/exhaustive/basic/set05/expected/model_2_4_3-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_2_4_3-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set05/expected/model_2_4_3-solution000003.solution b/tests/exhaustive/basic/set05/expected/model_2_4_3-solution000003.solution deleted file mode 100644 index fdc0f02f96..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_2_4_3-solution000003.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 4} diff --git a/tests/exhaustive/basic/set05/expected/model_2_4_3.eprime b/tests/exhaustive/basic/set05/expected/model_2_4_3.eprime deleted file mode 100644 index b649797fe9..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_2_4_3.eprime +++ /dev/null @@ -1,59 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..3)] of int(1..5) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..3)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3)] of int(1..4) -find x_ExplicitVarSizeWithMarker_Marker: int(0..3) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3)] of int(1..4) -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy, - x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] -such that - or([x_ExplicitVarSizeWithDummy[q38] != 5 /\ x_ExplicitVarSizeWithDummy[q38] = 1 | q38 : int(1..3)]), - or([x_ExplicitVarSizeWithFlags_Flags[q40] /\ x_ExplicitVarSizeWithFlags_Values[q40] = 2 | q40 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 5 - | q1 : int(1..2)]), - and([x_ExplicitVarSizeWithDummy[q2] = 5 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..2)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 5) | q3 : int(1..3)]) <= 3, - and([x_ExplicitVarSizeWithFlags_Flags[q5 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q5] < x_ExplicitVarSizeWithFlags_Values[q5 + 1] - | q5 : int(1..2)]), - and([x_ExplicitVarSizeWithFlags_Flags[q6] = false -> x_ExplicitVarSizeWithFlags_Values[q6] = 1 | q6 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q7] | q7 : int(1..2)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q8]) | q8 : int(1..3)]) <= 3, - and([x_ExplicitVarSizeWithFlags_Flags[q11] -> - or([x_ExplicitVarSizeWithDummy[q13] != 5 /\ - x_ExplicitVarSizeWithDummy[q13] = x_ExplicitVarSizeWithFlags_Values[q11] - | q13 : int(1..3)]) - | q11 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q15] != 5 -> - or([x_ExplicitVarSizeWithFlags_Flags[q17] /\ - x_ExplicitVarSizeWithFlags_Values[q17] = x_ExplicitVarSizeWithDummy[q15] - | q17 : int(1..3)]) - | q15 : int(1..3)]), - and([q18 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q18] < x_ExplicitVarSizeWithMarker_Values[q18 + 1] - | q18 : int(1..2)]), - and([q19 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q19] = 1 | q19 : int(1..3)]), - x_ExplicitVarSizeWithMarker_Marker <= 3, - and([q22 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q24] != 5 /\ - x_ExplicitVarSizeWithDummy[q24] = x_ExplicitVarSizeWithMarker_Values[q22] - | q24 : int(1..3)]) - | q22 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q26] != 5 -> - or([q28 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q28] = x_ExplicitVarSizeWithDummy[q26] - | q28 : int(1..3)]) - | q26 : int(1..3)]), - and([q30 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q32] /\ - x_ExplicitVarSizeWithFlags_Values[q32] = x_ExplicitVarSizeWithMarker_Values[q30] - | q32 : int(1..3)]) - | q30 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q34] -> - or([q36 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q36] = x_ExplicitVarSizeWithFlags_Values[q34] - | q36 : int(1..3)]) - | q34 : int(1..3)]) - diff --git a/tests/exhaustive/basic/set05/expected/model_2_4_4-solution000001.solution b/tests/exhaustive/basic/set05/expected/model_2_4_4-solution000001.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_2_4_4-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/set05/expected/model_2_4_4-solution000002.solution b/tests/exhaustive/basic/set05/expected/model_2_4_4-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_2_4_4-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set05/expected/model_2_4_4-solution000003.solution b/tests/exhaustive/basic/set05/expected/model_2_4_4-solution000003.solution deleted file mode 100644 index fdc0f02f96..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_2_4_4-solution000003.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 4} diff --git a/tests/exhaustive/basic/set05/expected/model_2_4_4.eprime b/tests/exhaustive/basic/set05/expected/model_2_4_4.eprime deleted file mode 100644 index c9dd09c7ea..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_2_4_4.eprime +++ /dev/null @@ -1,30 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..3)] of int(1..5) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..3)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3)] of int(1..4) -branching on [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy] -such that - or([x_ExplicitVarSizeWithDummy[q19] != 5 /\ x_ExplicitVarSizeWithDummy[q19] = 1 | q19 : int(1..3)]), - or([x_ExplicitVarSizeWithFlags_Flags[q21] /\ x_ExplicitVarSizeWithFlags_Values[q21] = 2 | q21 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 5 - | q1 : int(1..2)]), - and([x_ExplicitVarSizeWithDummy[q2] = 5 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..2)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 5) | q3 : int(1..3)]) <= 3, - and([x_ExplicitVarSizeWithFlags_Flags[q5 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q5] < x_ExplicitVarSizeWithFlags_Values[q5 + 1] - | q5 : int(1..2)]), - and([x_ExplicitVarSizeWithFlags_Flags[q6] = false -> x_ExplicitVarSizeWithFlags_Values[q6] = 1 | q6 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q7] | q7 : int(1..2)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q8]) | q8 : int(1..3)]) <= 3, - and([x_ExplicitVarSizeWithFlags_Flags[q11] -> - or([x_ExplicitVarSizeWithDummy[q13] != 5 /\ - x_ExplicitVarSizeWithDummy[q13] = x_ExplicitVarSizeWithFlags_Values[q11] - | q13 : int(1..3)]) - | q11 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q15] != 5 -> - or([x_ExplicitVarSizeWithFlags_Flags[q17] /\ - x_ExplicitVarSizeWithFlags_Values[q17] = x_ExplicitVarSizeWithDummy[q15] - | q17 : int(1..3)]) - | q15 : int(1..3)]) - diff --git a/tests/exhaustive/basic/set05/expected/model_3_1_1-solution000001.solution b/tests/exhaustive/basic/set05/expected/model_3_1_1-solution000001.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_3_1_1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/set05/expected/model_3_1_1-solution000002.solution b/tests/exhaustive/basic/set05/expected/model_3_1_1-solution000002.solution deleted file mode 100644 index fdc0f02f96..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_3_1_1-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 4} diff --git a/tests/exhaustive/basic/set05/expected/model_3_1_1-solution000003.solution b/tests/exhaustive/basic/set05/expected/model_3_1_1-solution000003.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_3_1_1-solution000003.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set05/expected/model_3_1_1.eprime b/tests/exhaustive/basic/set05/expected/model_3_1_1.eprime deleted file mode 100644 index 18b6d63112..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_3_1_1.eprime +++ /dev/null @@ -1,21 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..3) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3)] of int(1..4) -find x_Occurrence: matrix indexed by [int(1..4)] of bool -branching on [x_Occurrence, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] -such that - or([q11 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q11] = 1 | q11 : int(1..3)]), - x_Occurrence[2], - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..2)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..3)]), - x_ExplicitVarSizeWithMarker_Marker <= 3, - sum([toInt(x_Occurrence[q4]) | q4 : int(1..4)]) <= 3, - and([x_Occurrence[q5] -> - or([q7 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q7] = q5 | q7 : int(1..3)]) - | q5 : int(1..4)]), - and([q9 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q9]] - | q9 : int(1..3)]) - diff --git a/tests/exhaustive/basic/set05/expected/model_3_1_2-solution000001.solution b/tests/exhaustive/basic/set05/expected/model_3_1_2-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_3_1_2-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set05/expected/model_3_1_2-solution000002.solution b/tests/exhaustive/basic/set05/expected/model_3_1_2-solution000002.solution deleted file mode 100644 index fdc0f02f96..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_3_1_2-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 4} diff --git a/tests/exhaustive/basic/set05/expected/model_3_1_2-solution000003.solution b/tests/exhaustive/basic/set05/expected/model_3_1_2-solution000003.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_3_1_2-solution000003.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/set05/expected/model_3_1_2.eprime b/tests/exhaustive/basic/set05/expected/model_3_1_2.eprime deleted file mode 100644 index 56c03f8d80..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_3_1_2.eprime +++ /dev/null @@ -1,42 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..3) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3)] of int(1..4) -find x_Occurrence: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..3)] of int(1..5) -branching on - [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_Occurrence] -such that - or([q28 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q28] = 1 | q28 : int(1..3)]), - x_Occurrence[2], - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..2)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..3)]), - x_ExplicitVarSizeWithMarker_Marker <= 3, - sum([toInt(x_Occurrence[q4]) | q4 : int(1..4)]) <= 3, - and([x_Occurrence[q22] -> - or([q24 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q24] = q22 - | q24 : int(1..3)]) - | q22 : int(1..4)]), - and([q26 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q26]] - | q26 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q5] < x_ExplicitVarSizeWithDummy[q5 + 1] \/ x_ExplicitVarSizeWithDummy[q5] = 5 - | q5 : int(1..2)]), - and([x_ExplicitVarSizeWithDummy[q6] = 5 -> x_ExplicitVarSizeWithDummy[q6 + 1] = 5 | q6 : int(1..2)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q7] != 5) | q7 : int(1..3)]) <= 3, - and([x_ExplicitVarSizeWithDummy[q10] != 5 -> - or([q12 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q12] = x_ExplicitVarSizeWithDummy[q10] - | q12 : int(1..3)]) - | q10 : int(1..3)]), - and([q14 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q16] != 5 /\ - x_ExplicitVarSizeWithDummy[q16] = x_ExplicitVarSizeWithMarker_Values[q14] - | q16 : int(1..3)]) - | q14 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q18] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q18]] | q18 : int(1..3)]), - and([x_Occurrence[q19] -> - or([x_ExplicitVarSizeWithDummy[q21] != 5 /\ x_ExplicitVarSizeWithDummy[q21] = q19 | q21 : int(1..3)]) - | q19 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set05/expected/model_3_1_3-solution000001.solution b/tests/exhaustive/basic/set05/expected/model_3_1_3-solution000001.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_3_1_3-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/set05/expected/model_3_1_3-solution000002.solution b/tests/exhaustive/basic/set05/expected/model_3_1_3-solution000002.solution deleted file mode 100644 index fdc0f02f96..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_3_1_3-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 4} diff --git a/tests/exhaustive/basic/set05/expected/model_3_1_3-solution000003.solution b/tests/exhaustive/basic/set05/expected/model_3_1_3-solution000003.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_3_1_3-solution000003.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set05/expected/model_3_1_3.eprime b/tests/exhaustive/basic/set05/expected/model_3_1_3.eprime deleted file mode 100644 index 18b6d63112..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_3_1_3.eprime +++ /dev/null @@ -1,21 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..3) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3)] of int(1..4) -find x_Occurrence: matrix indexed by [int(1..4)] of bool -branching on [x_Occurrence, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] -such that - or([q11 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q11] = 1 | q11 : int(1..3)]), - x_Occurrence[2], - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..2)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..3)]), - x_ExplicitVarSizeWithMarker_Marker <= 3, - sum([toInt(x_Occurrence[q4]) | q4 : int(1..4)]) <= 3, - and([x_Occurrence[q5] -> - or([q7 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q7] = q5 | q7 : int(1..3)]) - | q5 : int(1..4)]), - and([q9 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q9]] - | q9 : int(1..3)]) - diff --git a/tests/exhaustive/basic/set05/expected/model_3_1_4-solution000001.solution b/tests/exhaustive/basic/set05/expected/model_3_1_4-solution000001.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_3_1_4-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/set05/expected/model_3_1_4-solution000002.solution b/tests/exhaustive/basic/set05/expected/model_3_1_4-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_3_1_4-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set05/expected/model_3_1_4-solution000003.solution b/tests/exhaustive/basic/set05/expected/model_3_1_4-solution000003.solution deleted file mode 100644 index fdc0f02f96..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_3_1_4-solution000003.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 4} diff --git a/tests/exhaustive/basic/set05/expected/model_3_1_4.eprime b/tests/exhaustive/basic/set05/expected/model_3_1_4.eprime deleted file mode 100644 index 742dd902aa..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_3_1_4.eprime +++ /dev/null @@ -1,47 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..3) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3)] of int(1..4) -find x_Occurrence: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..3)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3)] of int(1..4) -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithMarker_Marker, - x_ExplicitVarSizeWithMarker_Values, x_Occurrence] -such that - or([q29 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q29] = 1 | q29 : int(1..3)]), - x_Occurrence[2], - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..2)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..3)]), - x_ExplicitVarSizeWithMarker_Marker <= 3, - sum([toInt(x_Occurrence[q4]) | q4 : int(1..4)]) <= 3, - and([x_Occurrence[q23] -> - or([q25 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q25] = q23 - | q25 : int(1..3)]) - | q23 : int(1..4)]), - and([q27 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q27]] - | q27 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q5 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q5] < x_ExplicitVarSizeWithFlags_Values[q5 + 1] - | q5 : int(1..2)]), - and([x_ExplicitVarSizeWithFlags_Flags[q6] = false -> x_ExplicitVarSizeWithFlags_Values[q6] = 1 | q6 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q7] | q7 : int(1..2)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q8]) | q8 : int(1..3)]) <= 3, - and([x_ExplicitVarSizeWithFlags_Flags[q11] -> - or([q13 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q13] = x_ExplicitVarSizeWithFlags_Values[q11] - | q13 : int(1..3)]) - | q11 : int(1..3)]), - and([q15 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q17] /\ - x_ExplicitVarSizeWithFlags_Values[q17] = x_ExplicitVarSizeWithMarker_Values[q15] - | q17 : int(1..3)]) - | q15 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q19] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q19]] - | q19 : int(1..3)]), - and([x_Occurrence[q20] -> - or([x_ExplicitVarSizeWithFlags_Flags[q22] /\ x_ExplicitVarSizeWithFlags_Values[q22] = q20 | q22 : int(1..3)]) - | q20 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set05/expected/model_3_2_1-solution000001.solution b/tests/exhaustive/basic/set05/expected/model_3_2_1-solution000001.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_3_2_1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/set05/expected/model_3_2_1-solution000002.solution b/tests/exhaustive/basic/set05/expected/model_3_2_1-solution000002.solution deleted file mode 100644 index fdc0f02f96..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_3_2_1-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 4} diff --git a/tests/exhaustive/basic/set05/expected/model_3_2_1-solution000003.solution b/tests/exhaustive/basic/set05/expected/model_3_2_1-solution000003.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_3_2_1-solution000003.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set05/expected/model_3_2_1.eprime b/tests/exhaustive/basic/set05/expected/model_3_2_1.eprime deleted file mode 100644 index 4d541e34ee..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_3_2_1.eprime +++ /dev/null @@ -1,42 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..3) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3)] of int(1..4) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..3)] of int(1..5) -find x_Occurrence: matrix indexed by [int(1..4)] of bool -branching on - [x_Occurrence, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy] -such that - or([q28 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q28] = 1 | q28 : int(1..3)]), - or([x_ExplicitVarSizeWithDummy[q30] != 5 /\ x_ExplicitVarSizeWithDummy[q30] = 2 | q30 : int(1..3)]), - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..2)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..3)]), - x_ExplicitVarSizeWithMarker_Marker <= 3, - and([x_ExplicitVarSizeWithDummy[q4] < x_ExplicitVarSizeWithDummy[q4 + 1] \/ x_ExplicitVarSizeWithDummy[q4] = 5 - | q4 : int(1..2)]), - and([x_ExplicitVarSizeWithDummy[q5] = 5 -> x_ExplicitVarSizeWithDummy[q5 + 1] = 5 | q5 : int(1..2)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q6] != 5) | q6 : int(1..3)]) <= 3, - and([x_ExplicitVarSizeWithDummy[q9] != 5 -> - or([q11 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q11] = x_ExplicitVarSizeWithDummy[q9] - | q11 : int(1..3)]) - | q9 : int(1..3)]), - and([q13 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q15] != 5 /\ - x_ExplicitVarSizeWithDummy[q15] = x_ExplicitVarSizeWithMarker_Values[q13] - | q15 : int(1..3)]) - | q13 : int(1..3)]), - sum([toInt(x_Occurrence[q16]) | q16 : int(1..4)]) <= 3, - and([x_Occurrence[q17] -> - or([q19 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q19] = q17 - | q19 : int(1..3)]) - | q17 : int(1..4)]), - and([q21 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q21]] - | q21 : int(1..3)]), - and([x_Occurrence[q22] -> - or([x_ExplicitVarSizeWithDummy[q24] != 5 /\ x_ExplicitVarSizeWithDummy[q24] = q22 | q24 : int(1..3)]) - | q22 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q26] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q26]] | q26 : int(1..3)]) - diff --git a/tests/exhaustive/basic/set05/expected/model_3_2_2-solution000001.solution b/tests/exhaustive/basic/set05/expected/model_3_2_2-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_3_2_2-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set05/expected/model_3_2_2-solution000002.solution b/tests/exhaustive/basic/set05/expected/model_3_2_2-solution000002.solution deleted file mode 100644 index fdc0f02f96..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_3_2_2-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 4} diff --git a/tests/exhaustive/basic/set05/expected/model_3_2_2-solution000003.solution b/tests/exhaustive/basic/set05/expected/model_3_2_2-solution000003.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_3_2_2-solution000003.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/set05/expected/model_3_2_2.eprime b/tests/exhaustive/basic/set05/expected/model_3_2_2.eprime deleted file mode 100644 index aff63a4eef..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_3_2_2.eprime +++ /dev/null @@ -1,29 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..3) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3)] of int(1..4) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..3)] of int(1..5) -branching on [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] -such that - or([q17 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q17] = 1 | q17 : int(1..3)]), - or([x_ExplicitVarSizeWithDummy[q19] != 5 /\ x_ExplicitVarSizeWithDummy[q19] = 2 | q19 : int(1..3)]), - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..2)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..3)]), - x_ExplicitVarSizeWithMarker_Marker <= 3, - and([x_ExplicitVarSizeWithDummy[q4] < x_ExplicitVarSizeWithDummy[q4 + 1] \/ x_ExplicitVarSizeWithDummy[q4] = 5 - | q4 : int(1..2)]), - and([x_ExplicitVarSizeWithDummy[q5] = 5 -> x_ExplicitVarSizeWithDummy[q5 + 1] = 5 | q5 : int(1..2)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q6] != 5) | q6 : int(1..3)]) <= 3, - and([x_ExplicitVarSizeWithDummy[q9] != 5 -> - or([q11 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q11] = x_ExplicitVarSizeWithDummy[q9] - | q11 : int(1..3)]) - | q9 : int(1..3)]), - and([q13 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q15] != 5 /\ - x_ExplicitVarSizeWithDummy[q15] = x_ExplicitVarSizeWithMarker_Values[q13] - | q15 : int(1..3)]) - | q13 : int(1..3)]) - diff --git a/tests/exhaustive/basic/set05/expected/model_3_2_3-solution000001.solution b/tests/exhaustive/basic/set05/expected/model_3_2_3-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_3_2_3-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set05/expected/model_3_2_3-solution000002.solution b/tests/exhaustive/basic/set05/expected/model_3_2_3-solution000002.solution deleted file mode 100644 index fdc0f02f96..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_3_2_3-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 4} diff --git a/tests/exhaustive/basic/set05/expected/model_3_2_3-solution000003.solution b/tests/exhaustive/basic/set05/expected/model_3_2_3-solution000003.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_3_2_3-solution000003.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/set05/expected/model_3_2_3.eprime b/tests/exhaustive/basic/set05/expected/model_3_2_3.eprime deleted file mode 100644 index aff63a4eef..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_3_2_3.eprime +++ /dev/null @@ -1,29 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..3) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3)] of int(1..4) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..3)] of int(1..5) -branching on [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] -such that - or([q17 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q17] = 1 | q17 : int(1..3)]), - or([x_ExplicitVarSizeWithDummy[q19] != 5 /\ x_ExplicitVarSizeWithDummy[q19] = 2 | q19 : int(1..3)]), - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..2)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..3)]), - x_ExplicitVarSizeWithMarker_Marker <= 3, - and([x_ExplicitVarSizeWithDummy[q4] < x_ExplicitVarSizeWithDummy[q4 + 1] \/ x_ExplicitVarSizeWithDummy[q4] = 5 - | q4 : int(1..2)]), - and([x_ExplicitVarSizeWithDummy[q5] = 5 -> x_ExplicitVarSizeWithDummy[q5 + 1] = 5 | q5 : int(1..2)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q6] != 5) | q6 : int(1..3)]) <= 3, - and([x_ExplicitVarSizeWithDummy[q9] != 5 -> - or([q11 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q11] = x_ExplicitVarSizeWithDummy[q9] - | q11 : int(1..3)]) - | q9 : int(1..3)]), - and([q13 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q15] != 5 /\ - x_ExplicitVarSizeWithDummy[q15] = x_ExplicitVarSizeWithMarker_Values[q13] - | q15 : int(1..3)]) - | q13 : int(1..3)]) - diff --git a/tests/exhaustive/basic/set05/expected/model_3_2_4-solution000001.solution b/tests/exhaustive/basic/set05/expected/model_3_2_4-solution000001.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_3_2_4-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/set05/expected/model_3_2_4-solution000002.solution b/tests/exhaustive/basic/set05/expected/model_3_2_4-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_3_2_4-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set05/expected/model_3_2_4-solution000003.solution b/tests/exhaustive/basic/set05/expected/model_3_2_4-solution000003.solution deleted file mode 100644 index fdc0f02f96..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_3_2_4-solution000003.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 4} diff --git a/tests/exhaustive/basic/set05/expected/model_3_2_4.eprime b/tests/exhaustive/basic/set05/expected/model_3_2_4.eprime deleted file mode 100644 index ca17b6551d..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_3_2_4.eprime +++ /dev/null @@ -1,60 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..3) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3)] of int(1..4) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..3)] of int(1..5) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..3)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3)] of int(1..4) -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithMarker_Marker, - x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy] -such that - or([q38 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q38] = 1 | q38 : int(1..3)]), - or([x_ExplicitVarSizeWithDummy[q40] != 5 /\ x_ExplicitVarSizeWithDummy[q40] = 2 | q40 : int(1..3)]), - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..2)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..3)]), - x_ExplicitVarSizeWithMarker_Marker <= 3, - and([x_ExplicitVarSizeWithDummy[q4] < x_ExplicitVarSizeWithDummy[q4 + 1] \/ x_ExplicitVarSizeWithDummy[q4] = 5 - | q4 : int(1..2)]), - and([x_ExplicitVarSizeWithDummy[q5] = 5 -> x_ExplicitVarSizeWithDummy[q5 + 1] = 5 | q5 : int(1..2)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q6] != 5) | q6 : int(1..3)]) <= 3, - and([x_ExplicitVarSizeWithDummy[q9] != 5 -> - or([q11 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q11] = x_ExplicitVarSizeWithDummy[q9] - | q11 : int(1..3)]) - | q9 : int(1..3)]), - and([q13 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q15] != 5 /\ - x_ExplicitVarSizeWithDummy[q15] = x_ExplicitVarSizeWithMarker_Values[q13] - | q15 : int(1..3)]) - | q13 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q16 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q16] < x_ExplicitVarSizeWithFlags_Values[q16 + 1] - | q16 : int(1..2)]), - and([x_ExplicitVarSizeWithFlags_Flags[q17] = false -> x_ExplicitVarSizeWithFlags_Values[q17] = 1 - | q17 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q18 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q18] | q18 : int(1..2)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q19]) | q19 : int(1..3)]) <= 3, - and([x_ExplicitVarSizeWithFlags_Flags[q22] -> - or([q24 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q24] = x_ExplicitVarSizeWithFlags_Values[q22] - | q24 : int(1..3)]) - | q22 : int(1..3)]), - and([q26 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q28] /\ - x_ExplicitVarSizeWithFlags_Values[q28] = x_ExplicitVarSizeWithMarker_Values[q26] - | q28 : int(1..3)]) - | q26 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q30] -> - or([x_ExplicitVarSizeWithDummy[q32] != 5 /\ - x_ExplicitVarSizeWithDummy[q32] = x_ExplicitVarSizeWithFlags_Values[q30] - | q32 : int(1..3)]) - | q30 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q34] != 5 -> - or([x_ExplicitVarSizeWithFlags_Flags[q36] /\ - x_ExplicitVarSizeWithFlags_Values[q36] = x_ExplicitVarSizeWithDummy[q34] - | q36 : int(1..3)]) - | q34 : int(1..3)]) - diff --git a/tests/exhaustive/basic/set05/expected/model_3_3_1-solution000001.solution b/tests/exhaustive/basic/set05/expected/model_3_3_1-solution000001.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_3_3_1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/set05/expected/model_3_3_1-solution000002.solution b/tests/exhaustive/basic/set05/expected/model_3_3_1-solution000002.solution deleted file mode 100644 index fdc0f02f96..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_3_3_1-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 4} diff --git a/tests/exhaustive/basic/set05/expected/model_3_3_1-solution000003.solution b/tests/exhaustive/basic/set05/expected/model_3_3_1-solution000003.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_3_3_1-solution000003.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set05/expected/model_3_3_1.eprime b/tests/exhaustive/basic/set05/expected/model_3_3_1.eprime deleted file mode 100644 index 5def062aca..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_3_3_1.eprime +++ /dev/null @@ -1,21 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..3) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3)] of int(1..4) -find x_Occurrence: matrix indexed by [int(1..4)] of bool -branching on [x_Occurrence, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] -such that - or([q11 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q11] = 1 | q11 : int(1..3)]), - or([q13 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q13] = 2 | q13 : int(1..3)]), - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..2)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..3)]), - x_ExplicitVarSizeWithMarker_Marker <= 3, - sum([toInt(x_Occurrence[q4]) | q4 : int(1..4)]) <= 3, - and([x_Occurrence[q5] -> - or([q7 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q7] = q5 | q7 : int(1..3)]) - | q5 : int(1..4)]), - and([q9 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q9]] - | q9 : int(1..3)]) - diff --git a/tests/exhaustive/basic/set05/expected/model_3_3_2-solution000001.solution b/tests/exhaustive/basic/set05/expected/model_3_3_2-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_3_3_2-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set05/expected/model_3_3_2-solution000002.solution b/tests/exhaustive/basic/set05/expected/model_3_3_2-solution000002.solution deleted file mode 100644 index fdc0f02f96..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_3_3_2-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 4} diff --git a/tests/exhaustive/basic/set05/expected/model_3_3_2-solution000003.solution b/tests/exhaustive/basic/set05/expected/model_3_3_2-solution000003.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_3_3_2-solution000003.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/set05/expected/model_3_3_2.eprime b/tests/exhaustive/basic/set05/expected/model_3_3_2.eprime deleted file mode 100644 index c7e4092e7b..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_3_3_2.eprime +++ /dev/null @@ -1,29 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..3) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3)] of int(1..4) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..3)] of int(1..5) -branching on [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] -such that - or([q17 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q17] = 1 | q17 : int(1..3)]), - or([q19 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q19] = 2 | q19 : int(1..3)]), - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..2)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..3)]), - x_ExplicitVarSizeWithMarker_Marker <= 3, - and([x_ExplicitVarSizeWithDummy[q4] < x_ExplicitVarSizeWithDummy[q4 + 1] \/ x_ExplicitVarSizeWithDummy[q4] = 5 - | q4 : int(1..2)]), - and([x_ExplicitVarSizeWithDummy[q5] = 5 -> x_ExplicitVarSizeWithDummy[q5 + 1] = 5 | q5 : int(1..2)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q6] != 5) | q6 : int(1..3)]) <= 3, - and([x_ExplicitVarSizeWithDummy[q9] != 5 -> - or([q11 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q11] = x_ExplicitVarSizeWithDummy[q9] - | q11 : int(1..3)]) - | q9 : int(1..3)]), - and([q13 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q15] != 5 /\ - x_ExplicitVarSizeWithDummy[q15] = x_ExplicitVarSizeWithMarker_Values[q13] - | q15 : int(1..3)]) - | q13 : int(1..3)]) - diff --git a/tests/exhaustive/basic/set05/expected/model_3_3_3-solution000001.solution b/tests/exhaustive/basic/set05/expected/model_3_3_3-solution000001.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_3_3_3-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/set05/expected/model_3_3_3-solution000002.solution b/tests/exhaustive/basic/set05/expected/model_3_3_3-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_3_3_3-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set05/expected/model_3_3_3-solution000003.solution b/tests/exhaustive/basic/set05/expected/model_3_3_3-solution000003.solution deleted file mode 100644 index fdc0f02f96..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_3_3_3-solution000003.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 4} diff --git a/tests/exhaustive/basic/set05/expected/model_3_3_3.eprime b/tests/exhaustive/basic/set05/expected/model_3_3_3.eprime deleted file mode 100644 index 30415d39e4..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_3_3_3.eprime +++ /dev/null @@ -1,14 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..3) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3)] of int(1..4) -branching on [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] -such that - or([q5 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q5] = 1 | q5 : int(1..3)]), - or([q7 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q7] = 2 | q7 : int(1..3)]), - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..2)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..3)]), - x_ExplicitVarSizeWithMarker_Marker <= 3 - diff --git a/tests/exhaustive/basic/set05/expected/model_3_3_4-solution000001.solution b/tests/exhaustive/basic/set05/expected/model_3_3_4-solution000001.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_3_3_4-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/set05/expected/model_3_3_4-solution000002.solution b/tests/exhaustive/basic/set05/expected/model_3_3_4-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_3_3_4-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set05/expected/model_3_3_4-solution000003.solution b/tests/exhaustive/basic/set05/expected/model_3_3_4-solution000003.solution deleted file mode 100644 index fdc0f02f96..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_3_3_4-solution000003.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 4} diff --git a/tests/exhaustive/basic/set05/expected/model_3_3_4.eprime b/tests/exhaustive/basic/set05/expected/model_3_3_4.eprime deleted file mode 100644 index 5a6f8f4a1f..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_3_3_4.eprime +++ /dev/null @@ -1,34 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..3) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3)] of int(1..4) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..3)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3)] of int(1..4) -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithMarker_Marker, - x_ExplicitVarSizeWithMarker_Values] -such that - or([q18 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q18] = 1 | q18 : int(1..3)]), - or([q20 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q20] = 2 | q20 : int(1..3)]), - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..2)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..3)]), - x_ExplicitVarSizeWithMarker_Marker <= 3, - and([x_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q4] < x_ExplicitVarSizeWithFlags_Values[q4 + 1] - | q4 : int(1..2)]), - and([x_ExplicitVarSizeWithFlags_Flags[q5] = false -> x_ExplicitVarSizeWithFlags_Values[q5] = 1 | q5 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q6] | q6 : int(1..2)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q7]) | q7 : int(1..3)]) <= 3, - and([x_ExplicitVarSizeWithFlags_Flags[q10] -> - or([q12 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q12] = x_ExplicitVarSizeWithFlags_Values[q10] - | q12 : int(1..3)]) - | q10 : int(1..3)]), - and([q14 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q16] /\ - x_ExplicitVarSizeWithFlags_Values[q16] = x_ExplicitVarSizeWithMarker_Values[q14] - | q16 : int(1..3)]) - | q14 : int(1..3)]) - diff --git a/tests/exhaustive/basic/set05/expected/model_3_4_1-solution000001.solution b/tests/exhaustive/basic/set05/expected/model_3_4_1-solution000001.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_3_4_1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/set05/expected/model_3_4_1-solution000002.solution b/tests/exhaustive/basic/set05/expected/model_3_4_1-solution000002.solution deleted file mode 100644 index fdc0f02f96..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_3_4_1-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 4} diff --git a/tests/exhaustive/basic/set05/expected/model_3_4_1-solution000003.solution b/tests/exhaustive/basic/set05/expected/model_3_4_1-solution000003.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_3_4_1-solution000003.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set05/expected/model_3_4_1.eprime b/tests/exhaustive/basic/set05/expected/model_3_4_1.eprime deleted file mode 100644 index 8aebac7513..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_3_4_1.eprime +++ /dev/null @@ -1,47 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..3) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3)] of int(1..4) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..3)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3)] of int(1..4) -find x_Occurrence: matrix indexed by [int(1..4)] of bool -branching on - [x_Occurrence, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, - x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] -such that - or([q29 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q29] = 1 | q29 : int(1..3)]), - or([x_ExplicitVarSizeWithFlags_Flags[q31] /\ x_ExplicitVarSizeWithFlags_Values[q31] = 2 | q31 : int(1..3)]), - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..2)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..3)]), - x_ExplicitVarSizeWithMarker_Marker <= 3, - and([x_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q4] < x_ExplicitVarSizeWithFlags_Values[q4 + 1] - | q4 : int(1..2)]), - and([x_ExplicitVarSizeWithFlags_Flags[q5] = false -> x_ExplicitVarSizeWithFlags_Values[q5] = 1 | q5 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q6] | q6 : int(1..2)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q7]) | q7 : int(1..3)]) <= 3, - and([x_ExplicitVarSizeWithFlags_Flags[q10] -> - or([q12 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q12] = x_ExplicitVarSizeWithFlags_Values[q10] - | q12 : int(1..3)]) - | q10 : int(1..3)]), - and([q14 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q16] /\ - x_ExplicitVarSizeWithFlags_Values[q16] = x_ExplicitVarSizeWithMarker_Values[q14] - | q16 : int(1..3)]) - | q14 : int(1..3)]), - sum([toInt(x_Occurrence[q17]) | q17 : int(1..4)]) <= 3, - and([x_Occurrence[q18] -> - or([q20 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q20] = q18 - | q20 : int(1..3)]) - | q18 : int(1..4)]), - and([q22 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q22]] - | q22 : int(1..3)]), - and([x_Occurrence[q23] -> - or([x_ExplicitVarSizeWithFlags_Flags[q25] /\ x_ExplicitVarSizeWithFlags_Values[q25] = q23 | q25 : int(1..3)]) - | q23 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q27] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q27]] - | q27 : int(1..3)]) - diff --git a/tests/exhaustive/basic/set05/expected/model_3_4_2-solution000001.solution b/tests/exhaustive/basic/set05/expected/model_3_4_2-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_3_4_2-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set05/expected/model_3_4_2-solution000002.solution b/tests/exhaustive/basic/set05/expected/model_3_4_2-solution000002.solution deleted file mode 100644 index fdc0f02f96..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_3_4_2-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 4} diff --git a/tests/exhaustive/basic/set05/expected/model_3_4_2-solution000003.solution b/tests/exhaustive/basic/set05/expected/model_3_4_2-solution000003.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_3_4_2-solution000003.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/set05/expected/model_3_4_2.eprime b/tests/exhaustive/basic/set05/expected/model_3_4_2.eprime deleted file mode 100644 index 5f5f7c970d..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_3_4_2.eprime +++ /dev/null @@ -1,59 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..3) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3)] of int(1..4) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..3)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3)] of int(1..4) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..3)] of int(1..5) -branching on - [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, - x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] -such that - or([q38 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q38] = 1 | q38 : int(1..3)]), - or([x_ExplicitVarSizeWithFlags_Flags[q40] /\ x_ExplicitVarSizeWithFlags_Values[q40] = 2 | q40 : int(1..3)]), - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..2)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..3)]), - x_ExplicitVarSizeWithMarker_Marker <= 3, - and([x_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q4] < x_ExplicitVarSizeWithFlags_Values[q4 + 1] - | q4 : int(1..2)]), - and([x_ExplicitVarSizeWithFlags_Flags[q5] = false -> x_ExplicitVarSizeWithFlags_Values[q5] = 1 | q5 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q6] | q6 : int(1..2)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q7]) | q7 : int(1..3)]) <= 3, - and([x_ExplicitVarSizeWithFlags_Flags[q10] -> - or([q12 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q12] = x_ExplicitVarSizeWithFlags_Values[q10] - | q12 : int(1..3)]) - | q10 : int(1..3)]), - and([q14 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q16] /\ - x_ExplicitVarSizeWithFlags_Values[q16] = x_ExplicitVarSizeWithMarker_Values[q14] - | q16 : int(1..3)]) - | q14 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q17] < x_ExplicitVarSizeWithDummy[q17 + 1] \/ x_ExplicitVarSizeWithDummy[q17] = 5 - | q17 : int(1..2)]), - and([x_ExplicitVarSizeWithDummy[q18] = 5 -> x_ExplicitVarSizeWithDummy[q18 + 1] = 5 | q18 : int(1..2)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q19] != 5) | q19 : int(1..3)]) <= 3, - and([x_ExplicitVarSizeWithDummy[q22] != 5 -> - or([q24 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q24] = x_ExplicitVarSizeWithDummy[q22] - | q24 : int(1..3)]) - | q22 : int(1..3)]), - and([q26 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q28] != 5 /\ - x_ExplicitVarSizeWithDummy[q28] = x_ExplicitVarSizeWithMarker_Values[q26] - | q28 : int(1..3)]) - | q26 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q30] != 5 -> - or([x_ExplicitVarSizeWithFlags_Flags[q32] /\ - x_ExplicitVarSizeWithFlags_Values[q32] = x_ExplicitVarSizeWithDummy[q30] - | q32 : int(1..3)]) - | q30 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q34] -> - or([x_ExplicitVarSizeWithDummy[q36] != 5 /\ - x_ExplicitVarSizeWithDummy[q36] = x_ExplicitVarSizeWithFlags_Values[q34] - | q36 : int(1..3)]) - | q34 : int(1..3)]) - diff --git a/tests/exhaustive/basic/set05/expected/model_3_4_3-solution000001.solution b/tests/exhaustive/basic/set05/expected/model_3_4_3-solution000001.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_3_4_3-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/set05/expected/model_3_4_3-solution000002.solution b/tests/exhaustive/basic/set05/expected/model_3_4_3-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_3_4_3-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set05/expected/model_3_4_3-solution000003.solution b/tests/exhaustive/basic/set05/expected/model_3_4_3-solution000003.solution deleted file mode 100644 index fdc0f02f96..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_3_4_3-solution000003.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 4} diff --git a/tests/exhaustive/basic/set05/expected/model_3_4_3.eprime b/tests/exhaustive/basic/set05/expected/model_3_4_3.eprime deleted file mode 100644 index b29a9e6cdd..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_3_4_3.eprime +++ /dev/null @@ -1,34 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..3) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3)] of int(1..4) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..3)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3)] of int(1..4) -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithMarker_Marker, - x_ExplicitVarSizeWithMarker_Values] -such that - or([q18 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q18] = 1 | q18 : int(1..3)]), - or([x_ExplicitVarSizeWithFlags_Flags[q20] /\ x_ExplicitVarSizeWithFlags_Values[q20] = 2 | q20 : int(1..3)]), - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..2)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..3)]), - x_ExplicitVarSizeWithMarker_Marker <= 3, - and([x_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q4] < x_ExplicitVarSizeWithFlags_Values[q4 + 1] - | q4 : int(1..2)]), - and([x_ExplicitVarSizeWithFlags_Flags[q5] = false -> x_ExplicitVarSizeWithFlags_Values[q5] = 1 | q5 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q6] | q6 : int(1..2)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q7]) | q7 : int(1..3)]) <= 3, - and([x_ExplicitVarSizeWithFlags_Flags[q10] -> - or([q12 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q12] = x_ExplicitVarSizeWithFlags_Values[q10] - | q12 : int(1..3)]) - | q10 : int(1..3)]), - and([q14 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q16] /\ - x_ExplicitVarSizeWithFlags_Values[q16] = x_ExplicitVarSizeWithMarker_Values[q14] - | q16 : int(1..3)]) - | q14 : int(1..3)]) - diff --git a/tests/exhaustive/basic/set05/expected/model_3_4_4-solution000001.solution b/tests/exhaustive/basic/set05/expected/model_3_4_4-solution000001.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_3_4_4-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/set05/expected/model_3_4_4-solution000002.solution b/tests/exhaustive/basic/set05/expected/model_3_4_4-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_3_4_4-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set05/expected/model_3_4_4-solution000003.solution b/tests/exhaustive/basic/set05/expected/model_3_4_4-solution000003.solution deleted file mode 100644 index fdc0f02f96..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_3_4_4-solution000003.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 4} diff --git a/tests/exhaustive/basic/set05/expected/model_3_4_4.eprime b/tests/exhaustive/basic/set05/expected/model_3_4_4.eprime deleted file mode 100644 index b29a9e6cdd..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_3_4_4.eprime +++ /dev/null @@ -1,34 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..3) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3)] of int(1..4) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..3)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3)] of int(1..4) -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithMarker_Marker, - x_ExplicitVarSizeWithMarker_Values] -such that - or([q18 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q18] = 1 | q18 : int(1..3)]), - or([x_ExplicitVarSizeWithFlags_Flags[q20] /\ x_ExplicitVarSizeWithFlags_Values[q20] = 2 | q20 : int(1..3)]), - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..2)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..3)]), - x_ExplicitVarSizeWithMarker_Marker <= 3, - and([x_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q4] < x_ExplicitVarSizeWithFlags_Values[q4 + 1] - | q4 : int(1..2)]), - and([x_ExplicitVarSizeWithFlags_Flags[q5] = false -> x_ExplicitVarSizeWithFlags_Values[q5] = 1 | q5 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q6] | q6 : int(1..2)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q7]) | q7 : int(1..3)]) <= 3, - and([x_ExplicitVarSizeWithFlags_Flags[q10] -> - or([q12 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q12] = x_ExplicitVarSizeWithFlags_Values[q10] - | q12 : int(1..3)]) - | q10 : int(1..3)]), - and([q14 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q16] /\ - x_ExplicitVarSizeWithFlags_Values[q16] = x_ExplicitVarSizeWithMarker_Values[q14] - | q16 : int(1..3)]) - | q14 : int(1..3)]) - diff --git a/tests/exhaustive/basic/set05/expected/model_4_1_1-solution000001.solution b/tests/exhaustive/basic/set05/expected/model_4_1_1-solution000001.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_4_1_1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/set05/expected/model_4_1_1-solution000002.solution b/tests/exhaustive/basic/set05/expected/model_4_1_1-solution000002.solution deleted file mode 100644 index fdc0f02f96..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_4_1_1-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 4} diff --git a/tests/exhaustive/basic/set05/expected/model_4_1_1-solution000003.solution b/tests/exhaustive/basic/set05/expected/model_4_1_1-solution000003.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_4_1_1-solution000003.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set05/expected/model_4_1_1.eprime b/tests/exhaustive/basic/set05/expected/model_4_1_1.eprime deleted file mode 100644 index 9358d40bd8..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_4_1_1.eprime +++ /dev/null @@ -1,22 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..3)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3)] of int(1..4) -find x_Occurrence: matrix indexed by [int(1..4)] of bool -branching on [x_Occurrence, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] -such that - or([x_ExplicitVarSizeWithFlags_Flags[q13] /\ x_ExplicitVarSizeWithFlags_Values[q13] = 1 | q13 : int(1..3)]), - x_Occurrence[2], - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..2)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..2)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..3)]) <= 3, - sum([toInt(x_Occurrence[q6]) | q6 : int(1..4)]) <= 3, - and([x_Occurrence[q7] -> - or([x_ExplicitVarSizeWithFlags_Flags[q9] /\ x_ExplicitVarSizeWithFlags_Values[q9] = q7 | q9 : int(1..3)]) - | q7 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q11] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q11]] - | q11 : int(1..3)]) - diff --git a/tests/exhaustive/basic/set05/expected/model_4_1_2-solution000001.solution b/tests/exhaustive/basic/set05/expected/model_4_1_2-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_4_1_2-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set05/expected/model_4_1_2-solution000002.solution b/tests/exhaustive/basic/set05/expected/model_4_1_2-solution000002.solution deleted file mode 100644 index fdc0f02f96..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_4_1_2-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 4} diff --git a/tests/exhaustive/basic/set05/expected/model_4_1_2-solution000003.solution b/tests/exhaustive/basic/set05/expected/model_4_1_2-solution000003.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_4_1_2-solution000003.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/set05/expected/model_4_1_2.eprime b/tests/exhaustive/basic/set05/expected/model_4_1_2.eprime deleted file mode 100644 index d279aa617d..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_4_1_2.eprime +++ /dev/null @@ -1,42 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..3)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3)] of int(1..4) -find x_Occurrence: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..3)] of int(1..5) -branching on - [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_Occurrence] -such that - or([x_ExplicitVarSizeWithFlags_Flags[q30] /\ x_ExplicitVarSizeWithFlags_Values[q30] = 1 | q30 : int(1..3)]), - x_Occurrence[2], - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..2)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..2)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..3)]) <= 3, - sum([toInt(x_Occurrence[q6]) | q6 : int(1..4)]) <= 3, - and([x_Occurrence[q24] -> - or([x_ExplicitVarSizeWithFlags_Flags[q26] /\ x_ExplicitVarSizeWithFlags_Values[q26] = q24 | q26 : int(1..3)]) - | q24 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q28] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q28]] - | q28 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q7] < x_ExplicitVarSizeWithDummy[q7 + 1] \/ x_ExplicitVarSizeWithDummy[q7] = 5 - | q7 : int(1..2)]), - and([x_ExplicitVarSizeWithDummy[q8] = 5 -> x_ExplicitVarSizeWithDummy[q8 + 1] = 5 | q8 : int(1..2)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q9] != 5) | q9 : int(1..3)]) <= 3, - and([x_ExplicitVarSizeWithDummy[q12] != 5 -> - or([x_ExplicitVarSizeWithFlags_Flags[q14] /\ - x_ExplicitVarSizeWithFlags_Values[q14] = x_ExplicitVarSizeWithDummy[q12] - | q14 : int(1..3)]) - | q12 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q16] -> - or([x_ExplicitVarSizeWithDummy[q18] != 5 /\ - x_ExplicitVarSizeWithDummy[q18] = x_ExplicitVarSizeWithFlags_Values[q16] - | q18 : int(1..3)]) - | q16 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q20] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q20]] | q20 : int(1..3)]), - and([x_Occurrence[q21] -> - or([x_ExplicitVarSizeWithDummy[q23] != 5 /\ x_ExplicitVarSizeWithDummy[q23] = q21 | q23 : int(1..3)]) - | q21 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set05/expected/model_4_1_3-solution000001.solution b/tests/exhaustive/basic/set05/expected/model_4_1_3-solution000001.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_4_1_3-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/set05/expected/model_4_1_3-solution000002.solution b/tests/exhaustive/basic/set05/expected/model_4_1_3-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_4_1_3-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set05/expected/model_4_1_3-solution000003.solution b/tests/exhaustive/basic/set05/expected/model_4_1_3-solution000003.solution deleted file mode 100644 index fdc0f02f96..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_4_1_3-solution000003.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 4} diff --git a/tests/exhaustive/basic/set05/expected/model_4_1_3.eprime b/tests/exhaustive/basic/set05/expected/model_4_1_3.eprime deleted file mode 100644 index f773f1d64b..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_4_1_3.eprime +++ /dev/null @@ -1,47 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..3)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3)] of int(1..4) -find x_Occurrence: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithMarker_Marker: int(0..3) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3)] of int(1..4) -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithFlags_Flags, - x_ExplicitVarSizeWithFlags_Values, x_Occurrence] -such that - or([x_ExplicitVarSizeWithFlags_Flags[q29] /\ x_ExplicitVarSizeWithFlags_Values[q29] = 1 | q29 : int(1..3)]), - x_Occurrence[2], - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..2)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..2)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..3)]) <= 3, - sum([toInt(x_Occurrence[q6]) | q6 : int(1..4)]) <= 3, - and([x_Occurrence[q23] -> - or([x_ExplicitVarSizeWithFlags_Flags[q25] /\ x_ExplicitVarSizeWithFlags_Values[q25] = q23 | q25 : int(1..3)]) - | q23 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q27] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q27]] - | q27 : int(1..3)]), - and([q7 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q7] < x_ExplicitVarSizeWithMarker_Values[q7 + 1] - | q7 : int(1..2)]), - and([q8 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q8] = 1 | q8 : int(1..3)]), - x_ExplicitVarSizeWithMarker_Marker <= 3, - and([q11 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q13] /\ - x_ExplicitVarSizeWithFlags_Values[q13] = x_ExplicitVarSizeWithMarker_Values[q11] - | q13 : int(1..3)]) - | q11 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q15] -> - or([q17 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q17] = x_ExplicitVarSizeWithFlags_Values[q15] - | q17 : int(1..3)]) - | q15 : int(1..3)]), - and([q19 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q19]] - | q19 : int(1..3)]), - and([x_Occurrence[q20] -> - or([q22 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q22] = q20 - | q22 : int(1..3)]) - | q20 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set05/expected/model_4_1_4-solution000001.solution b/tests/exhaustive/basic/set05/expected/model_4_1_4-solution000001.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_4_1_4-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/set05/expected/model_4_1_4-solution000002.solution b/tests/exhaustive/basic/set05/expected/model_4_1_4-solution000002.solution deleted file mode 100644 index fdc0f02f96..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_4_1_4-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 4} diff --git a/tests/exhaustive/basic/set05/expected/model_4_1_4-solution000003.solution b/tests/exhaustive/basic/set05/expected/model_4_1_4-solution000003.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_4_1_4-solution000003.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set05/expected/model_4_1_4.eprime b/tests/exhaustive/basic/set05/expected/model_4_1_4.eprime deleted file mode 100644 index 9358d40bd8..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_4_1_4.eprime +++ /dev/null @@ -1,22 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..3)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3)] of int(1..4) -find x_Occurrence: matrix indexed by [int(1..4)] of bool -branching on [x_Occurrence, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] -such that - or([x_ExplicitVarSizeWithFlags_Flags[q13] /\ x_ExplicitVarSizeWithFlags_Values[q13] = 1 | q13 : int(1..3)]), - x_Occurrence[2], - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..2)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..2)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..3)]) <= 3, - sum([toInt(x_Occurrence[q6]) | q6 : int(1..4)]) <= 3, - and([x_Occurrence[q7] -> - or([x_ExplicitVarSizeWithFlags_Flags[q9] /\ x_ExplicitVarSizeWithFlags_Values[q9] = q7 | q9 : int(1..3)]) - | q7 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q11] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q11]] - | q11 : int(1..3)]) - diff --git a/tests/exhaustive/basic/set05/expected/model_4_2_1-solution000001.solution b/tests/exhaustive/basic/set05/expected/model_4_2_1-solution000001.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_4_2_1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/set05/expected/model_4_2_1-solution000002.solution b/tests/exhaustive/basic/set05/expected/model_4_2_1-solution000002.solution deleted file mode 100644 index fdc0f02f96..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_4_2_1-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 4} diff --git a/tests/exhaustive/basic/set05/expected/model_4_2_1-solution000003.solution b/tests/exhaustive/basic/set05/expected/model_4_2_1-solution000003.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_4_2_1-solution000003.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set05/expected/model_4_2_1.eprime b/tests/exhaustive/basic/set05/expected/model_4_2_1.eprime deleted file mode 100644 index 4459490acf..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_4_2_1.eprime +++ /dev/null @@ -1,42 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..3)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3)] of int(1..4) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..3)] of int(1..5) -find x_Occurrence: matrix indexed by [int(1..4)] of bool -branching on - [x_Occurrence, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy] -such that - or([x_ExplicitVarSizeWithFlags_Flags[q30] /\ x_ExplicitVarSizeWithFlags_Values[q30] = 1 | q30 : int(1..3)]), - or([x_ExplicitVarSizeWithDummy[q32] != 5 /\ x_ExplicitVarSizeWithDummy[q32] = 2 | q32 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..2)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..2)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..3)]) <= 3, - and([x_ExplicitVarSizeWithDummy[q6] < x_ExplicitVarSizeWithDummy[q6 + 1] \/ x_ExplicitVarSizeWithDummy[q6] = 5 - | q6 : int(1..2)]), - and([x_ExplicitVarSizeWithDummy[q7] = 5 -> x_ExplicitVarSizeWithDummy[q7 + 1] = 5 | q7 : int(1..2)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q8] != 5) | q8 : int(1..3)]) <= 3, - and([x_ExplicitVarSizeWithDummy[q11] != 5 -> - or([x_ExplicitVarSizeWithFlags_Flags[q13] /\ - x_ExplicitVarSizeWithFlags_Values[q13] = x_ExplicitVarSizeWithDummy[q11] - | q13 : int(1..3)]) - | q11 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q15] -> - or([x_ExplicitVarSizeWithDummy[q17] != 5 /\ - x_ExplicitVarSizeWithDummy[q17] = x_ExplicitVarSizeWithFlags_Values[q15] - | q17 : int(1..3)]) - | q15 : int(1..3)]), - sum([toInt(x_Occurrence[q18]) | q18 : int(1..4)]) <= 3, - and([x_Occurrence[q19] -> - or([x_ExplicitVarSizeWithFlags_Flags[q21] /\ x_ExplicitVarSizeWithFlags_Values[q21] = q19 | q21 : int(1..3)]) - | q19 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q23] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q23]] - | q23 : int(1..3)]), - and([x_Occurrence[q24] -> - or([x_ExplicitVarSizeWithDummy[q26] != 5 /\ x_ExplicitVarSizeWithDummy[q26] = q24 | q26 : int(1..3)]) - | q24 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q28] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q28]] | q28 : int(1..3)]) - diff --git a/tests/exhaustive/basic/set05/expected/model_4_2_2-solution000001.solution b/tests/exhaustive/basic/set05/expected/model_4_2_2-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_4_2_2-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set05/expected/model_4_2_2-solution000002.solution b/tests/exhaustive/basic/set05/expected/model_4_2_2-solution000002.solution deleted file mode 100644 index fdc0f02f96..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_4_2_2-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 4} diff --git a/tests/exhaustive/basic/set05/expected/model_4_2_2-solution000003.solution b/tests/exhaustive/basic/set05/expected/model_4_2_2-solution000003.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_4_2_2-solution000003.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/set05/expected/model_4_2_2.eprime b/tests/exhaustive/basic/set05/expected/model_4_2_2.eprime deleted file mode 100644 index 1fc3837d42..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_4_2_2.eprime +++ /dev/null @@ -1,30 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..3)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3)] of int(1..4) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..3)] of int(1..5) -branching on [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] -such that - or([x_ExplicitVarSizeWithFlags_Flags[q19] /\ x_ExplicitVarSizeWithFlags_Values[q19] = 1 | q19 : int(1..3)]), - or([x_ExplicitVarSizeWithDummy[q21] != 5 /\ x_ExplicitVarSizeWithDummy[q21] = 2 | q21 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..2)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..2)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..3)]) <= 3, - and([x_ExplicitVarSizeWithDummy[q6] < x_ExplicitVarSizeWithDummy[q6 + 1] \/ x_ExplicitVarSizeWithDummy[q6] = 5 - | q6 : int(1..2)]), - and([x_ExplicitVarSizeWithDummy[q7] = 5 -> x_ExplicitVarSizeWithDummy[q7 + 1] = 5 | q7 : int(1..2)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q8] != 5) | q8 : int(1..3)]) <= 3, - and([x_ExplicitVarSizeWithDummy[q11] != 5 -> - or([x_ExplicitVarSizeWithFlags_Flags[q13] /\ - x_ExplicitVarSizeWithFlags_Values[q13] = x_ExplicitVarSizeWithDummy[q11] - | q13 : int(1..3)]) - | q11 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q15] -> - or([x_ExplicitVarSizeWithDummy[q17] != 5 /\ - x_ExplicitVarSizeWithDummy[q17] = x_ExplicitVarSizeWithFlags_Values[q15] - | q17 : int(1..3)]) - | q15 : int(1..3)]) - diff --git a/tests/exhaustive/basic/set05/expected/model_4_2_3-solution000001.solution b/tests/exhaustive/basic/set05/expected/model_4_2_3-solution000001.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_4_2_3-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/set05/expected/model_4_2_3-solution000002.solution b/tests/exhaustive/basic/set05/expected/model_4_2_3-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_4_2_3-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set05/expected/model_4_2_3-solution000003.solution b/tests/exhaustive/basic/set05/expected/model_4_2_3-solution000003.solution deleted file mode 100644 index fdc0f02f96..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_4_2_3-solution000003.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 4} diff --git a/tests/exhaustive/basic/set05/expected/model_4_2_3.eprime b/tests/exhaustive/basic/set05/expected/model_4_2_3.eprime deleted file mode 100644 index e3382d275b..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_4_2_3.eprime +++ /dev/null @@ -1,59 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..3)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3)] of int(1..4) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..3)] of int(1..5) -find x_ExplicitVarSizeWithMarker_Marker: int(0..3) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3)] of int(1..4) -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithFlags_Flags, - x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy] -such that - or([x_ExplicitVarSizeWithFlags_Flags[q38] /\ x_ExplicitVarSizeWithFlags_Values[q38] = 1 | q38 : int(1..3)]), - or([x_ExplicitVarSizeWithDummy[q40] != 5 /\ x_ExplicitVarSizeWithDummy[q40] = 2 | q40 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..2)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..2)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..3)]) <= 3, - and([x_ExplicitVarSizeWithDummy[q6] < x_ExplicitVarSizeWithDummy[q6 + 1] \/ x_ExplicitVarSizeWithDummy[q6] = 5 - | q6 : int(1..2)]), - and([x_ExplicitVarSizeWithDummy[q7] = 5 -> x_ExplicitVarSizeWithDummy[q7 + 1] = 5 | q7 : int(1..2)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q8] != 5) | q8 : int(1..3)]) <= 3, - and([x_ExplicitVarSizeWithDummy[q11] != 5 -> - or([x_ExplicitVarSizeWithFlags_Flags[q13] /\ - x_ExplicitVarSizeWithFlags_Values[q13] = x_ExplicitVarSizeWithDummy[q11] - | q13 : int(1..3)]) - | q11 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q15] -> - or([x_ExplicitVarSizeWithDummy[q17] != 5 /\ - x_ExplicitVarSizeWithDummy[q17] = x_ExplicitVarSizeWithFlags_Values[q15] - | q17 : int(1..3)]) - | q15 : int(1..3)]), - and([q18 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q18] < x_ExplicitVarSizeWithMarker_Values[q18 + 1] - | q18 : int(1..2)]), - and([q19 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q19] = 1 | q19 : int(1..3)]), - x_ExplicitVarSizeWithMarker_Marker <= 3, - and([q22 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q24] /\ - x_ExplicitVarSizeWithFlags_Values[q24] = x_ExplicitVarSizeWithMarker_Values[q22] - | q24 : int(1..3)]) - | q22 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q26] -> - or([q28 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q28] = x_ExplicitVarSizeWithFlags_Values[q26] - | q28 : int(1..3)]) - | q26 : int(1..3)]), - and([q30 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q32] != 5 /\ - x_ExplicitVarSizeWithDummy[q32] = x_ExplicitVarSizeWithMarker_Values[q30] - | q32 : int(1..3)]) - | q30 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q34] != 5 -> - or([q36 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q36] = x_ExplicitVarSizeWithDummy[q34] - | q36 : int(1..3)]) - | q34 : int(1..3)]) - diff --git a/tests/exhaustive/basic/set05/expected/model_4_2_4-solution000001.solution b/tests/exhaustive/basic/set05/expected/model_4_2_4-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_4_2_4-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set05/expected/model_4_2_4-solution000002.solution b/tests/exhaustive/basic/set05/expected/model_4_2_4-solution000002.solution deleted file mode 100644 index fdc0f02f96..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_4_2_4-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 4} diff --git a/tests/exhaustive/basic/set05/expected/model_4_2_4-solution000003.solution b/tests/exhaustive/basic/set05/expected/model_4_2_4-solution000003.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_4_2_4-solution000003.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/set05/expected/model_4_2_4.eprime b/tests/exhaustive/basic/set05/expected/model_4_2_4.eprime deleted file mode 100644 index 1fc3837d42..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_4_2_4.eprime +++ /dev/null @@ -1,30 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..3)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3)] of int(1..4) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..3)] of int(1..5) -branching on [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] -such that - or([x_ExplicitVarSizeWithFlags_Flags[q19] /\ x_ExplicitVarSizeWithFlags_Values[q19] = 1 | q19 : int(1..3)]), - or([x_ExplicitVarSizeWithDummy[q21] != 5 /\ x_ExplicitVarSizeWithDummy[q21] = 2 | q21 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..2)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..2)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..3)]) <= 3, - and([x_ExplicitVarSizeWithDummy[q6] < x_ExplicitVarSizeWithDummy[q6 + 1] \/ x_ExplicitVarSizeWithDummy[q6] = 5 - | q6 : int(1..2)]), - and([x_ExplicitVarSizeWithDummy[q7] = 5 -> x_ExplicitVarSizeWithDummy[q7 + 1] = 5 | q7 : int(1..2)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q8] != 5) | q8 : int(1..3)]) <= 3, - and([x_ExplicitVarSizeWithDummy[q11] != 5 -> - or([x_ExplicitVarSizeWithFlags_Flags[q13] /\ - x_ExplicitVarSizeWithFlags_Values[q13] = x_ExplicitVarSizeWithDummy[q11] - | q13 : int(1..3)]) - | q11 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q15] -> - or([x_ExplicitVarSizeWithDummy[q17] != 5 /\ - x_ExplicitVarSizeWithDummy[q17] = x_ExplicitVarSizeWithFlags_Values[q15] - | q17 : int(1..3)]) - | q15 : int(1..3)]) - diff --git a/tests/exhaustive/basic/set05/expected/model_4_3_1-solution000001.solution b/tests/exhaustive/basic/set05/expected/model_4_3_1-solution000001.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_4_3_1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/set05/expected/model_4_3_1-solution000002.solution b/tests/exhaustive/basic/set05/expected/model_4_3_1-solution000002.solution deleted file mode 100644 index fdc0f02f96..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_4_3_1-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 4} diff --git a/tests/exhaustive/basic/set05/expected/model_4_3_1-solution000003.solution b/tests/exhaustive/basic/set05/expected/model_4_3_1-solution000003.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_4_3_1-solution000003.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set05/expected/model_4_3_1.eprime b/tests/exhaustive/basic/set05/expected/model_4_3_1.eprime deleted file mode 100644 index 1a72db7f80..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_4_3_1.eprime +++ /dev/null @@ -1,47 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..3)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3)] of int(1..4) -find x_ExplicitVarSizeWithMarker_Marker: int(0..3) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3)] of int(1..4) -find x_Occurrence: matrix indexed by [int(1..4)] of bool -branching on - [x_Occurrence, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, - x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] -such that - or([x_ExplicitVarSizeWithFlags_Flags[q29] /\ x_ExplicitVarSizeWithFlags_Values[q29] = 1 | q29 : int(1..3)]), - or([q31 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q31] = 2 | q31 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..2)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..2)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..3)]) <= 3, - and([q6 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q6] < x_ExplicitVarSizeWithMarker_Values[q6 + 1] - | q6 : int(1..2)]), - and([q7 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q7] = 1 | q7 : int(1..3)]), - x_ExplicitVarSizeWithMarker_Marker <= 3, - and([q10 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q12] /\ - x_ExplicitVarSizeWithFlags_Values[q12] = x_ExplicitVarSizeWithMarker_Values[q10] - | q12 : int(1..3)]) - | q10 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q14] -> - or([q16 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q16] = x_ExplicitVarSizeWithFlags_Values[q14] - | q16 : int(1..3)]) - | q14 : int(1..3)]), - sum([toInt(x_Occurrence[q17]) | q17 : int(1..4)]) <= 3, - and([x_Occurrence[q18] -> - or([x_ExplicitVarSizeWithFlags_Flags[q20] /\ x_ExplicitVarSizeWithFlags_Values[q20] = q18 | q20 : int(1..3)]) - | q18 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q22] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q22]] - | q22 : int(1..3)]), - and([x_Occurrence[q23] -> - or([q25 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q25] = q23 - | q25 : int(1..3)]) - | q23 : int(1..4)]), - and([q27 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q27]] - | q27 : int(1..3)]) - diff --git a/tests/exhaustive/basic/set05/expected/model_4_3_2-solution000001.solution b/tests/exhaustive/basic/set05/expected/model_4_3_2-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_4_3_2-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set05/expected/model_4_3_2-solution000002.solution b/tests/exhaustive/basic/set05/expected/model_4_3_2-solution000002.solution deleted file mode 100644 index fdc0f02f96..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_4_3_2-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 4} diff --git a/tests/exhaustive/basic/set05/expected/model_4_3_2-solution000003.solution b/tests/exhaustive/basic/set05/expected/model_4_3_2-solution000003.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_4_3_2-solution000003.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/set05/expected/model_4_3_2.eprime b/tests/exhaustive/basic/set05/expected/model_4_3_2.eprime deleted file mode 100644 index 411a506bdc..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_4_3_2.eprime +++ /dev/null @@ -1,59 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..3)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3)] of int(1..4) -find x_ExplicitVarSizeWithMarker_Marker: int(0..3) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3)] of int(1..4) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..3)] of int(1..5) -branching on - [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, - x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] -such that - or([x_ExplicitVarSizeWithFlags_Flags[q38] /\ x_ExplicitVarSizeWithFlags_Values[q38] = 1 | q38 : int(1..3)]), - or([q40 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q40] = 2 | q40 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..2)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..2)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..3)]) <= 3, - and([q6 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q6] < x_ExplicitVarSizeWithMarker_Values[q6 + 1] - | q6 : int(1..2)]), - and([q7 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q7] = 1 | q7 : int(1..3)]), - x_ExplicitVarSizeWithMarker_Marker <= 3, - and([q10 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q12] /\ - x_ExplicitVarSizeWithFlags_Values[q12] = x_ExplicitVarSizeWithMarker_Values[q10] - | q12 : int(1..3)]) - | q10 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q14] -> - or([q16 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q16] = x_ExplicitVarSizeWithFlags_Values[q14] - | q16 : int(1..3)]) - | q14 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q17] < x_ExplicitVarSizeWithDummy[q17 + 1] \/ x_ExplicitVarSizeWithDummy[q17] = 5 - | q17 : int(1..2)]), - and([x_ExplicitVarSizeWithDummy[q18] = 5 -> x_ExplicitVarSizeWithDummy[q18 + 1] = 5 | q18 : int(1..2)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q19] != 5) | q19 : int(1..3)]) <= 3, - and([x_ExplicitVarSizeWithDummy[q22] != 5 -> - or([x_ExplicitVarSizeWithFlags_Flags[q24] /\ - x_ExplicitVarSizeWithFlags_Values[q24] = x_ExplicitVarSizeWithDummy[q22] - | q24 : int(1..3)]) - | q22 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q26] -> - or([x_ExplicitVarSizeWithDummy[q28] != 5 /\ - x_ExplicitVarSizeWithDummy[q28] = x_ExplicitVarSizeWithFlags_Values[q26] - | q28 : int(1..3)]) - | q26 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q30] != 5 -> - or([q32 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q32] = x_ExplicitVarSizeWithDummy[q30] - | q32 : int(1..3)]) - | q30 : int(1..3)]), - and([q34 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q36] != 5 /\ - x_ExplicitVarSizeWithDummy[q36] = x_ExplicitVarSizeWithMarker_Values[q34] - | q36 : int(1..3)]) - | q34 : int(1..3)]) - diff --git a/tests/exhaustive/basic/set05/expected/model_4_3_3-solution000001.solution b/tests/exhaustive/basic/set05/expected/model_4_3_3-solution000001.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_4_3_3-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/set05/expected/model_4_3_3-solution000002.solution b/tests/exhaustive/basic/set05/expected/model_4_3_3-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_4_3_3-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set05/expected/model_4_3_3-solution000003.solution b/tests/exhaustive/basic/set05/expected/model_4_3_3-solution000003.solution deleted file mode 100644 index fdc0f02f96..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_4_3_3-solution000003.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 4} diff --git a/tests/exhaustive/basic/set05/expected/model_4_3_3.eprime b/tests/exhaustive/basic/set05/expected/model_4_3_3.eprime deleted file mode 100644 index e1aec900de..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_4_3_3.eprime +++ /dev/null @@ -1,34 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..3)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3)] of int(1..4) -find x_ExplicitVarSizeWithMarker_Marker: int(0..3) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3)] of int(1..4) -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithFlags_Flags, - x_ExplicitVarSizeWithFlags_Values] -such that - or([x_ExplicitVarSizeWithFlags_Flags[q18] /\ x_ExplicitVarSizeWithFlags_Values[q18] = 1 | q18 : int(1..3)]), - or([q20 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q20] = 2 | q20 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..2)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..2)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..3)]) <= 3, - and([q6 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q6] < x_ExplicitVarSizeWithMarker_Values[q6 + 1] - | q6 : int(1..2)]), - and([q7 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q7] = 1 | q7 : int(1..3)]), - x_ExplicitVarSizeWithMarker_Marker <= 3, - and([q10 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q12] /\ - x_ExplicitVarSizeWithFlags_Values[q12] = x_ExplicitVarSizeWithMarker_Values[q10] - | q12 : int(1..3)]) - | q10 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q14] -> - or([q16 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q16] = x_ExplicitVarSizeWithFlags_Values[q14] - | q16 : int(1..3)]) - | q14 : int(1..3)]) - diff --git a/tests/exhaustive/basic/set05/expected/model_4_3_4-solution000001.solution b/tests/exhaustive/basic/set05/expected/model_4_3_4-solution000001.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_4_3_4-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/set05/expected/model_4_3_4-solution000002.solution b/tests/exhaustive/basic/set05/expected/model_4_3_4-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_4_3_4-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set05/expected/model_4_3_4-solution000003.solution b/tests/exhaustive/basic/set05/expected/model_4_3_4-solution000003.solution deleted file mode 100644 index fdc0f02f96..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_4_3_4-solution000003.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 4} diff --git a/tests/exhaustive/basic/set05/expected/model_4_3_4.eprime b/tests/exhaustive/basic/set05/expected/model_4_3_4.eprime deleted file mode 100644 index e1aec900de..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_4_3_4.eprime +++ /dev/null @@ -1,34 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..3)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3)] of int(1..4) -find x_ExplicitVarSizeWithMarker_Marker: int(0..3) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3)] of int(1..4) -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithFlags_Flags, - x_ExplicitVarSizeWithFlags_Values] -such that - or([x_ExplicitVarSizeWithFlags_Flags[q18] /\ x_ExplicitVarSizeWithFlags_Values[q18] = 1 | q18 : int(1..3)]), - or([q20 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q20] = 2 | q20 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..2)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..2)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..3)]) <= 3, - and([q6 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q6] < x_ExplicitVarSizeWithMarker_Values[q6 + 1] - | q6 : int(1..2)]), - and([q7 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q7] = 1 | q7 : int(1..3)]), - x_ExplicitVarSizeWithMarker_Marker <= 3, - and([q10 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q12] /\ - x_ExplicitVarSizeWithFlags_Values[q12] = x_ExplicitVarSizeWithMarker_Values[q10] - | q12 : int(1..3)]) - | q10 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q14] -> - or([q16 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q16] = x_ExplicitVarSizeWithFlags_Values[q14] - | q16 : int(1..3)]) - | q14 : int(1..3)]) - diff --git a/tests/exhaustive/basic/set05/expected/model_4_4_1-solution000001.solution b/tests/exhaustive/basic/set05/expected/model_4_4_1-solution000001.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_4_4_1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/set05/expected/model_4_4_1-solution000002.solution b/tests/exhaustive/basic/set05/expected/model_4_4_1-solution000002.solution deleted file mode 100644 index fdc0f02f96..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_4_4_1-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 4} diff --git a/tests/exhaustive/basic/set05/expected/model_4_4_1-solution000003.solution b/tests/exhaustive/basic/set05/expected/model_4_4_1-solution000003.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_4_4_1-solution000003.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set05/expected/model_4_4_1.eprime b/tests/exhaustive/basic/set05/expected/model_4_4_1.eprime deleted file mode 100644 index 728004701a..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_4_4_1.eprime +++ /dev/null @@ -1,22 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..3)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3)] of int(1..4) -find x_Occurrence: matrix indexed by [int(1..4)] of bool -branching on [x_Occurrence, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] -such that - or([x_ExplicitVarSizeWithFlags_Flags[q13] /\ x_ExplicitVarSizeWithFlags_Values[q13] = 1 | q13 : int(1..3)]), - or([x_ExplicitVarSizeWithFlags_Flags[q15] /\ x_ExplicitVarSizeWithFlags_Values[q15] = 2 | q15 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..2)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..2)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..3)]) <= 3, - sum([toInt(x_Occurrence[q6]) | q6 : int(1..4)]) <= 3, - and([x_Occurrence[q7] -> - or([x_ExplicitVarSizeWithFlags_Flags[q9] /\ x_ExplicitVarSizeWithFlags_Values[q9] = q7 | q9 : int(1..3)]) - | q7 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q11] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q11]] - | q11 : int(1..3)]) - diff --git a/tests/exhaustive/basic/set05/expected/model_4_4_2-solution000001.solution b/tests/exhaustive/basic/set05/expected/model_4_4_2-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_4_4_2-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set05/expected/model_4_4_2-solution000002.solution b/tests/exhaustive/basic/set05/expected/model_4_4_2-solution000002.solution deleted file mode 100644 index fdc0f02f96..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_4_4_2-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 4} diff --git a/tests/exhaustive/basic/set05/expected/model_4_4_2-solution000003.solution b/tests/exhaustive/basic/set05/expected/model_4_4_2-solution000003.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_4_4_2-solution000003.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/set05/expected/model_4_4_2.eprime b/tests/exhaustive/basic/set05/expected/model_4_4_2.eprime deleted file mode 100644 index 0a5bd5c53a..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_4_4_2.eprime +++ /dev/null @@ -1,30 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..3)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3)] of int(1..4) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..3)] of int(1..5) -branching on [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] -such that - or([x_ExplicitVarSizeWithFlags_Flags[q19] /\ x_ExplicitVarSizeWithFlags_Values[q19] = 1 | q19 : int(1..3)]), - or([x_ExplicitVarSizeWithFlags_Flags[q21] /\ x_ExplicitVarSizeWithFlags_Values[q21] = 2 | q21 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..2)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..2)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..3)]) <= 3, - and([x_ExplicitVarSizeWithDummy[q6] < x_ExplicitVarSizeWithDummy[q6 + 1] \/ x_ExplicitVarSizeWithDummy[q6] = 5 - | q6 : int(1..2)]), - and([x_ExplicitVarSizeWithDummy[q7] = 5 -> x_ExplicitVarSizeWithDummy[q7 + 1] = 5 | q7 : int(1..2)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q8] != 5) | q8 : int(1..3)]) <= 3, - and([x_ExplicitVarSizeWithDummy[q11] != 5 -> - or([x_ExplicitVarSizeWithFlags_Flags[q13] /\ - x_ExplicitVarSizeWithFlags_Values[q13] = x_ExplicitVarSizeWithDummy[q11] - | q13 : int(1..3)]) - | q11 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q15] -> - or([x_ExplicitVarSizeWithDummy[q17] != 5 /\ - x_ExplicitVarSizeWithDummy[q17] = x_ExplicitVarSizeWithFlags_Values[q15] - | q17 : int(1..3)]) - | q15 : int(1..3)]) - diff --git a/tests/exhaustive/basic/set05/expected/model_4_4_3-solution000001.solution b/tests/exhaustive/basic/set05/expected/model_4_4_3-solution000001.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_4_4_3-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/set05/expected/model_4_4_3-solution000002.solution b/tests/exhaustive/basic/set05/expected/model_4_4_3-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_4_4_3-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set05/expected/model_4_4_3-solution000003.solution b/tests/exhaustive/basic/set05/expected/model_4_4_3-solution000003.solution deleted file mode 100644 index fdc0f02f96..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_4_4_3-solution000003.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 4} diff --git a/tests/exhaustive/basic/set05/expected/model_4_4_3.eprime b/tests/exhaustive/basic/set05/expected/model_4_4_3.eprime deleted file mode 100644 index ac17616362..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_4_4_3.eprime +++ /dev/null @@ -1,34 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..3)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3)] of int(1..4) -find x_ExplicitVarSizeWithMarker_Marker: int(0..3) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3)] of int(1..4) -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithFlags_Flags, - x_ExplicitVarSizeWithFlags_Values] -such that - or([x_ExplicitVarSizeWithFlags_Flags[q18] /\ x_ExplicitVarSizeWithFlags_Values[q18] = 1 | q18 : int(1..3)]), - or([x_ExplicitVarSizeWithFlags_Flags[q20] /\ x_ExplicitVarSizeWithFlags_Values[q20] = 2 | q20 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..2)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..2)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..3)]) <= 3, - and([q6 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q6] < x_ExplicitVarSizeWithMarker_Values[q6 + 1] - | q6 : int(1..2)]), - and([q7 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q7] = 1 | q7 : int(1..3)]), - x_ExplicitVarSizeWithMarker_Marker <= 3, - and([q10 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q12] /\ - x_ExplicitVarSizeWithFlags_Values[q12] = x_ExplicitVarSizeWithMarker_Values[q10] - | q12 : int(1..3)]) - | q10 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q14] -> - or([q16 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q16] = x_ExplicitVarSizeWithFlags_Values[q14] - | q16 : int(1..3)]) - | q14 : int(1..3)]) - diff --git a/tests/exhaustive/basic/set05/expected/model_4_4_4-solution000001.solution b/tests/exhaustive/basic/set05/expected/model_4_4_4-solution000001.solution deleted file mode 100644 index f90e0ba18c..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_4_4_4-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2} diff --git a/tests/exhaustive/basic/set05/expected/model_4_4_4-solution000002.solution b/tests/exhaustive/basic/set05/expected/model_4_4_4-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_4_4_4-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set05/expected/model_4_4_4-solution000003.solution b/tests/exhaustive/basic/set05/expected/model_4_4_4-solution000003.solution deleted file mode 100644 index fdc0f02f96..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_4_4_4-solution000003.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 4} diff --git a/tests/exhaustive/basic/set05/expected/model_4_4_4.eprime b/tests/exhaustive/basic/set05/expected/model_4_4_4.eprime deleted file mode 100644 index e4489eba01..0000000000 --- a/tests/exhaustive/basic/set05/expected/model_4_4_4.eprime +++ /dev/null @@ -1,15 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..3)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3)] of int(1..4) -branching on [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] -such that - or([x_ExplicitVarSizeWithFlags_Flags[q7] /\ x_ExplicitVarSizeWithFlags_Values[q7] = 1 | q7 : int(1..3)]), - or([x_ExplicitVarSizeWithFlags_Flags[q9] /\ x_ExplicitVarSizeWithFlags_Values[q9] = 2 | q9 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..2)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..2)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..3)]) <= 3 - diff --git a/tests/exhaustive/basic/set06/expected/model_1_1_1_1-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_1_1_1_1-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_1_1_1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_1_1_1_1-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_1_1_1_1-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_1_1_1-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_1_1_1_1.eprime b/tests/exhaustive/basic/set06/expected/model_1_1_1_1.eprime deleted file mode 100644 index f1447509f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_1_1_1.eprime +++ /dev/null @@ -1,10 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1..4)] of bool -branching on [x_Occurrence] -such that - x_Occurrence[1], - x_Occurrence[2], - x_Occurrence[3], - sum([toInt(x_Occurrence[q1]) | q1 : int(1..4)]) <= 4 - diff --git a/tests/exhaustive/basic/set06/expected/model_1_1_1_2-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_1_1_1_2-solution000001.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_1_1_2-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_1_1_1_2-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_1_1_1_2-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_1_1_2-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_1_1_1_2.eprime b/tests/exhaustive/basic/set06/expected/model_1_1_1_2.eprime deleted file mode 100644 index da7b2486bc..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_1_1_2.eprime +++ /dev/null @@ -1,19 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -branching on [x_ExplicitVarSizeWithDummy, x_Occurrence] -such that - x_Occurrence[1], - x_Occurrence[2], - x_Occurrence[3], - sum([toInt(x_Occurrence[q1]) | q1 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithDummy[q2] < x_ExplicitVarSizeWithDummy[q2 + 1] \/ x_ExplicitVarSizeWithDummy[q2] = 5 - | q2 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q3] = 5 -> x_ExplicitVarSizeWithDummy[q3 + 1] = 5 | q3 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q4] != 5) | q4 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithDummy[q7] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q7]] | q7 : int(1..4)]), - and([x_Occurrence[q8] -> - or([x_ExplicitVarSizeWithDummy[q10] != 5 /\ x_ExplicitVarSizeWithDummy[q10] = q8 | q10 : int(1..4)]) - | q8 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_1_1_1_3-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_1_1_1_3-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_1_1_3-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_1_1_1_3-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_1_1_1_3-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_1_1_3-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_1_1_1_3.eprime b/tests/exhaustive/basic/set06/expected/model_1_1_1_3.eprime deleted file mode 100644 index d1ee49268b..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_1_1_3.eprime +++ /dev/null @@ -1,22 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -branching on [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_Occurrence] -such that - x_Occurrence[1], - x_Occurrence[2], - x_Occurrence[3], - sum([toInt(x_Occurrence[q1]) | q1 : int(1..4)]) <= 4, - and([q2 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q2] < x_ExplicitVarSizeWithMarker_Values[q2 + 1] - | q2 : int(1..3)]), - and([q3 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q3] = 1 | q3 : int(1..4)]), - x_ExplicitVarSizeWithMarker_Marker <= 4, - and([q6 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q6]] - | q6 : int(1..4)]), - and([x_Occurrence[q7] -> - or([q9 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q9] = q7 | q9 : int(1..4)]) - | q7 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_1_1_1_4-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_1_1_1_4-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_1_1_4-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_1_1_1_4-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_1_1_1_4-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_1_1_4-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_1_1_1_4.eprime b/tests/exhaustive/basic/set06/expected/model_1_1_1_4.eprime deleted file mode 100644 index 52a9a6c855..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_1_1_4.eprime +++ /dev/null @@ -1,22 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -branching on [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_Occurrence] -such that - x_Occurrence[1], - x_Occurrence[2], - x_Occurrence[3], - sum([toInt(x_Occurrence[q1]) | q1 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithFlags_Flags[q2 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q2] < x_ExplicitVarSizeWithFlags_Values[q2 + 1] - | q2 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3] = false -> x_ExplicitVarSizeWithFlags_Values[q3] = 1 | q3 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q4] | q4 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q5]) | q5 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithFlags_Flags[q8] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q8]] | q8 : int(1..4)]), - and([x_Occurrence[q9] -> - or([x_ExplicitVarSizeWithFlags_Flags[q11] /\ x_ExplicitVarSizeWithFlags_Values[q11] = q9 | q11 : int(1..4)]) - | q9 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_1_1_2_1-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_1_1_2_1-solution000001.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_1_2_1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_1_1_2_1-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_1_1_2_1-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_1_2_1-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_1_1_2_1.eprime b/tests/exhaustive/basic/set06/expected/model_1_1_2_1.eprime deleted file mode 100644 index f6358320c2..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_1_2_1.eprime +++ /dev/null @@ -1,19 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -branching on [x_ExplicitVarSizeWithDummy, x_Occurrence] -such that - x_Occurrence[1], - x_Occurrence[2], - or([x_ExplicitVarSizeWithDummy[q12] != 5 /\ x_ExplicitVarSizeWithDummy[q12] = 3 | q12 : int(1..4)]), - sum([toInt(x_Occurrence[q1]) | q1 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithDummy[q2] < x_ExplicitVarSizeWithDummy[q2 + 1] \/ x_ExplicitVarSizeWithDummy[q2] = 5 - | q2 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q3] = 5 -> x_ExplicitVarSizeWithDummy[q3 + 1] = 5 | q3 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q4] != 5) | q4 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithDummy[q7] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q7]] | q7 : int(1..4)]), - and([x_Occurrence[q8] -> - or([x_ExplicitVarSizeWithDummy[q10] != 5 /\ x_ExplicitVarSizeWithDummy[q10] = q8 | q10 : int(1..4)]) - | q8 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_1_1_2_2-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_1_1_2_2-solution000001.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_1_2_2-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_1_1_2_2-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_1_1_2_2-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_1_2_2-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_1_1_2_2.eprime b/tests/exhaustive/basic/set06/expected/model_1_1_2_2.eprime deleted file mode 100644 index f6358320c2..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_1_2_2.eprime +++ /dev/null @@ -1,19 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -branching on [x_ExplicitVarSizeWithDummy, x_Occurrence] -such that - x_Occurrence[1], - x_Occurrence[2], - or([x_ExplicitVarSizeWithDummy[q12] != 5 /\ x_ExplicitVarSizeWithDummy[q12] = 3 | q12 : int(1..4)]), - sum([toInt(x_Occurrence[q1]) | q1 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithDummy[q2] < x_ExplicitVarSizeWithDummy[q2 + 1] \/ x_ExplicitVarSizeWithDummy[q2] = 5 - | q2 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q3] = 5 -> x_ExplicitVarSizeWithDummy[q3 + 1] = 5 | q3 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q4] != 5) | q4 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithDummy[q7] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q7]] | q7 : int(1..4)]), - and([x_Occurrence[q8] -> - or([x_ExplicitVarSizeWithDummy[q10] != 5 /\ x_ExplicitVarSizeWithDummy[q10] = q8 | q10 : int(1..4)]) - | q8 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_1_1_2_3-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_1_1_2_3-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_1_2_3-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_1_1_2_3-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_1_1_2_3-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_1_2_3-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_1_1_2_3.eprime b/tests/exhaustive/basic/set06/expected/model_1_1_2_3.eprime deleted file mode 100644 index 38d4e045e4..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_1_2_3.eprime +++ /dev/null @@ -1,43 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_Occurrence, x_ExplicitVarSizeWithDummy] -such that - x_Occurrence[1], - x_Occurrence[2], - or([x_ExplicitVarSizeWithDummy[q28] != 5 /\ x_ExplicitVarSizeWithDummy[q28] = 3 | q28 : int(1..4)]), - sum([toInt(x_Occurrence[q1]) | q1 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithDummy[q2] < x_ExplicitVarSizeWithDummy[q2 + 1] \/ x_ExplicitVarSizeWithDummy[q2] = 5 - | q2 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q3] = 5 -> x_ExplicitVarSizeWithDummy[q3 + 1] = 5 | q3 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q4] != 5) | q4 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithDummy[q7] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q7]] | q7 : int(1..4)]), - and([x_Occurrence[q8] -> - or([x_ExplicitVarSizeWithDummy[q10] != 5 /\ x_ExplicitVarSizeWithDummy[q10] = q8 | q10 : int(1..4)]) - | q8 : int(1..4)]), - and([q11 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q11] < x_ExplicitVarSizeWithMarker_Values[q11 + 1] - | q11 : int(1..3)]), - and([q12 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q12] = 1 | q12 : int(1..4)]), - x_ExplicitVarSizeWithMarker_Marker <= 4, - and([q15 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q15]] - | q15 : int(1..4)]), - and([x_Occurrence[q16] -> - or([q18 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q18] = q16 - | q18 : int(1..4)]) - | q16 : int(1..4)]), - and([q20 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q22] != 5 /\ - x_ExplicitVarSizeWithDummy[q22] = x_ExplicitVarSizeWithMarker_Values[q20] - | q22 : int(1..4)]) - | q20 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q24] != 5 -> - or([q26 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q26] = x_ExplicitVarSizeWithDummy[q24] - | q26 : int(1..4)]) - | q24 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_1_1_2_4-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_1_1_2_4-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_1_2_4-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_1_1_2_4-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_1_1_2_4-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_1_2_4-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_1_1_2_4.eprime b/tests/exhaustive/basic/set06/expected/model_1_1_2_4.eprime deleted file mode 100644 index ef4fbb7269..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_1_2_4.eprime +++ /dev/null @@ -1,44 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_Occurrence, x_ExplicitVarSizeWithDummy] -such that - x_Occurrence[1], - x_Occurrence[2], - or([x_ExplicitVarSizeWithDummy[q30] != 5 /\ x_ExplicitVarSizeWithDummy[q30] = 3 | q30 : int(1..4)]), - sum([toInt(x_Occurrence[q1]) | q1 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithDummy[q2] < x_ExplicitVarSizeWithDummy[q2 + 1] \/ x_ExplicitVarSizeWithDummy[q2] = 5 - | q2 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q3] = 5 -> x_ExplicitVarSizeWithDummy[q3 + 1] = 5 | q3 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q4] != 5) | q4 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithDummy[q7] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q7]] | q7 : int(1..4)]), - and([x_Occurrence[q8] -> - or([x_ExplicitVarSizeWithDummy[q10] != 5 /\ x_ExplicitVarSizeWithDummy[q10] = q8 | q10 : int(1..4)]) - | q8 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q11 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q11] < x_ExplicitVarSizeWithFlags_Values[q11 + 1] - | q11 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q12] = false -> x_ExplicitVarSizeWithFlags_Values[q12] = 1 - | q12 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q13 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q13] | q13 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q14]) | q14 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithFlags_Flags[q17] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q17]] - | q17 : int(1..4)]), - and([x_Occurrence[q18] -> - or([x_ExplicitVarSizeWithFlags_Flags[q20] /\ x_ExplicitVarSizeWithFlags_Values[q20] = q18 | q20 : int(1..4)]) - | q18 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q22] -> - or([x_ExplicitVarSizeWithDummy[q24] != 5 /\ - x_ExplicitVarSizeWithDummy[q24] = x_ExplicitVarSizeWithFlags_Values[q22] - | q24 : int(1..4)]) - | q22 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q26] != 5 -> - or([x_ExplicitVarSizeWithFlags_Flags[q28] /\ - x_ExplicitVarSizeWithFlags_Values[q28] = x_ExplicitVarSizeWithDummy[q26] - | q28 : int(1..4)]) - | q26 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_1_1_3_1-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_1_1_3_1-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_1_3_1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_1_1_3_1-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_1_1_3_1-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_1_3_1-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_1_1_3_1.eprime b/tests/exhaustive/basic/set06/expected/model_1_1_3_1.eprime deleted file mode 100644 index 70953f52c2..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_1_3_1.eprime +++ /dev/null @@ -1,22 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -branching on [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_Occurrence] -such that - x_Occurrence[1], - x_Occurrence[2], - or([q11 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q11] = 3 | q11 : int(1..4)]), - sum([toInt(x_Occurrence[q1]) | q1 : int(1..4)]) <= 4, - and([q2 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q2] < x_ExplicitVarSizeWithMarker_Values[q2 + 1] - | q2 : int(1..3)]), - and([q3 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q3] = 1 | q3 : int(1..4)]), - x_ExplicitVarSizeWithMarker_Marker <= 4, - and([q6 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q6]] - | q6 : int(1..4)]), - and([x_Occurrence[q7] -> - or([q9 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q9] = q7 | q9 : int(1..4)]) - | q7 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_1_1_3_2-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_1_1_3_2-solution000001.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_1_3_2-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_1_1_3_2-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_1_1_3_2-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_1_3_2-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_1_1_3_2.eprime b/tests/exhaustive/basic/set06/expected/model_1_1_3_2.eprime deleted file mode 100644 index 07088141cf..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_1_3_2.eprime +++ /dev/null @@ -1,42 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -branching on - [x_ExplicitVarSizeWithDummy, x_Occurrence, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] -such that - x_Occurrence[1], - x_Occurrence[2], - or([q28 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q28] = 3 | q28 : int(1..4)]), - sum([toInt(x_Occurrence[q1]) | q1 : int(1..4)]) <= 4, - and([q2 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q2] < x_ExplicitVarSizeWithMarker_Values[q2 + 1] - | q2 : int(1..3)]), - and([q3 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q3] = 1 | q3 : int(1..4)]), - x_ExplicitVarSizeWithMarker_Marker <= 4, - and([q6 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q6]] - | q6 : int(1..4)]), - and([x_Occurrence[q7] -> - or([q9 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q9] = q7 | q9 : int(1..4)]) - | q7 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q10] < x_ExplicitVarSizeWithDummy[q10 + 1] \/ x_ExplicitVarSizeWithDummy[q10] = 5 - | q10 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q11] = 5 -> x_ExplicitVarSizeWithDummy[q11 + 1] = 5 | q11 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q12] != 5) | q12 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithDummy[q15] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q15]] | q15 : int(1..4)]), - and([x_Occurrence[q16] -> - or([x_ExplicitVarSizeWithDummy[q18] != 5 /\ x_ExplicitVarSizeWithDummy[q18] = q16 | q18 : int(1..4)]) - | q16 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q20] != 5 -> - or([q22 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q22] = x_ExplicitVarSizeWithDummy[q20] - | q22 : int(1..4)]) - | q20 : int(1..4)]), - and([q24 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q26] != 5 /\ - x_ExplicitVarSizeWithDummy[q26] = x_ExplicitVarSizeWithMarker_Values[q24] - | q26 : int(1..4)]) - | q24 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_1_1_3_3-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_1_1_3_3-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_1_3_3-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_1_1_3_3-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_1_1_3_3-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_1_3_3-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_1_1_3_3.eprime b/tests/exhaustive/basic/set06/expected/model_1_1_3_3.eprime deleted file mode 100644 index 70953f52c2..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_1_3_3.eprime +++ /dev/null @@ -1,22 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -branching on [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_Occurrence] -such that - x_Occurrence[1], - x_Occurrence[2], - or([q11 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q11] = 3 | q11 : int(1..4)]), - sum([toInt(x_Occurrence[q1]) | q1 : int(1..4)]) <= 4, - and([q2 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q2] < x_ExplicitVarSizeWithMarker_Values[q2 + 1] - | q2 : int(1..3)]), - and([q3 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q3] = 1 | q3 : int(1..4)]), - x_ExplicitVarSizeWithMarker_Marker <= 4, - and([q6 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q6]] - | q6 : int(1..4)]), - and([x_Occurrence[q7] -> - or([q9 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q9] = q7 | q9 : int(1..4)]) - | q7 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_1_1_3_4-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_1_1_3_4-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_1_3_4-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_1_1_3_4-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_1_1_3_4-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_1_3_4-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_1_1_3_4.eprime b/tests/exhaustive/basic/set06/expected/model_1_1_3_4.eprime deleted file mode 100644 index 9e996001f2..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_1_3_4.eprime +++ /dev/null @@ -1,48 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_Occurrence, - x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] -such that - x_Occurrence[1], - x_Occurrence[2], - or([q29 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q29] = 3 | q29 : int(1..4)]), - sum([toInt(x_Occurrence[q1]) | q1 : int(1..4)]) <= 4, - and([q2 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q2] < x_ExplicitVarSizeWithMarker_Values[q2 + 1] - | q2 : int(1..3)]), - and([q3 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q3] = 1 | q3 : int(1..4)]), - x_ExplicitVarSizeWithMarker_Marker <= 4, - and([q6 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q6]] - | q6 : int(1..4)]), - and([x_Occurrence[q7] -> - or([q9 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q9] = q7 | q9 : int(1..4)]) - | q7 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q10 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q10] < x_ExplicitVarSizeWithFlags_Values[q10 + 1] - | q10 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q11] = false -> x_ExplicitVarSizeWithFlags_Values[q11] = 1 - | q11 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q12 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q12] | q12 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q13]) | q13 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithFlags_Flags[q16] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q16]] - | q16 : int(1..4)]), - and([x_Occurrence[q17] -> - or([x_ExplicitVarSizeWithFlags_Flags[q19] /\ x_ExplicitVarSizeWithFlags_Values[q19] = q17 | q19 : int(1..4)]) - | q17 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q21] -> - or([q23 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q23] = x_ExplicitVarSizeWithFlags_Values[q21] - | q23 : int(1..4)]) - | q21 : int(1..4)]), - and([q25 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q27] /\ - x_ExplicitVarSizeWithFlags_Values[q27] = x_ExplicitVarSizeWithMarker_Values[q25] - | q27 : int(1..4)]) - | q25 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_1_1_4_1-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_1_1_4_1-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_1_4_1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_1_1_4_1-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_1_1_4_1-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_1_4_1-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_1_1_4_1.eprime b/tests/exhaustive/basic/set06/expected/model_1_1_4_1.eprime deleted file mode 100644 index 2ced4fdbb0..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_1_4_1.eprime +++ /dev/null @@ -1,22 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -branching on [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_Occurrence] -such that - x_Occurrence[1], - x_Occurrence[2], - or([x_ExplicitVarSizeWithFlags_Flags[q13] /\ x_ExplicitVarSizeWithFlags_Values[q13] = 3 | q13 : int(1..4)]), - sum([toInt(x_Occurrence[q1]) | q1 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithFlags_Flags[q2 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q2] < x_ExplicitVarSizeWithFlags_Values[q2 + 1] - | q2 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3] = false -> x_ExplicitVarSizeWithFlags_Values[q3] = 1 | q3 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q4] | q4 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q5]) | q5 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithFlags_Flags[q8] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q8]] | q8 : int(1..4)]), - and([x_Occurrence[q9] -> - or([x_ExplicitVarSizeWithFlags_Flags[q11] /\ x_ExplicitVarSizeWithFlags_Values[q11] = q9 | q11 : int(1..4)]) - | q9 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_1_1_4_2-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_1_1_4_2-solution000001.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_1_4_2-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_1_1_4_2-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_1_1_4_2-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_1_4_2-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_1_1_4_2.eprime b/tests/exhaustive/basic/set06/expected/model_1_1_4_2.eprime deleted file mode 100644 index faf6fcb130..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_1_4_2.eprime +++ /dev/null @@ -1,42 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -branching on - [x_ExplicitVarSizeWithDummy, x_Occurrence, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] -such that - x_Occurrence[1], - x_Occurrence[2], - or([x_ExplicitVarSizeWithFlags_Flags[q30] /\ x_ExplicitVarSizeWithFlags_Values[q30] = 3 | q30 : int(1..4)]), - sum([toInt(x_Occurrence[q1]) | q1 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithFlags_Flags[q2 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q2] < x_ExplicitVarSizeWithFlags_Values[q2 + 1] - | q2 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3] = false -> x_ExplicitVarSizeWithFlags_Values[q3] = 1 | q3 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q4] | q4 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q5]) | q5 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithFlags_Flags[q8] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q8]] | q8 : int(1..4)]), - and([x_Occurrence[q9] -> - or([x_ExplicitVarSizeWithFlags_Flags[q11] /\ x_ExplicitVarSizeWithFlags_Values[q11] = q9 | q11 : int(1..4)]) - | q9 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q12] < x_ExplicitVarSizeWithDummy[q12 + 1] \/ x_ExplicitVarSizeWithDummy[q12] = 5 - | q12 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q13] = 5 -> x_ExplicitVarSizeWithDummy[q13 + 1] = 5 | q13 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q14] != 5) | q14 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithDummy[q17] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q17]] | q17 : int(1..4)]), - and([x_Occurrence[q18] -> - or([x_ExplicitVarSizeWithDummy[q20] != 5 /\ x_ExplicitVarSizeWithDummy[q20] = q18 | q20 : int(1..4)]) - | q18 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q22] != 5 -> - or([x_ExplicitVarSizeWithFlags_Flags[q24] /\ - x_ExplicitVarSizeWithFlags_Values[q24] = x_ExplicitVarSizeWithDummy[q22] - | q24 : int(1..4)]) - | q22 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q26] -> - or([x_ExplicitVarSizeWithDummy[q28] != 5 /\ - x_ExplicitVarSizeWithDummy[q28] = x_ExplicitVarSizeWithFlags_Values[q26] - | q28 : int(1..4)]) - | q26 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_1_1_4_3-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_1_1_4_3-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_1_4_3-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_1_1_4_3-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_1_1_4_3-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_1_4_3-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_1_1_4_3.eprime b/tests/exhaustive/basic/set06/expected/model_1_1_4_3.eprime deleted file mode 100644 index 21bbdced45..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_1_4_3.eprime +++ /dev/null @@ -1,47 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_Occurrence, - x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] -such that - x_Occurrence[1], - x_Occurrence[2], - or([x_ExplicitVarSizeWithFlags_Flags[q29] /\ x_ExplicitVarSizeWithFlags_Values[q29] = 3 | q29 : int(1..4)]), - sum([toInt(x_Occurrence[q1]) | q1 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithFlags_Flags[q2 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q2] < x_ExplicitVarSizeWithFlags_Values[q2 + 1] - | q2 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3] = false -> x_ExplicitVarSizeWithFlags_Values[q3] = 1 | q3 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q4] | q4 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q5]) | q5 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithFlags_Flags[q8] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q8]] | q8 : int(1..4)]), - and([x_Occurrence[q9] -> - or([x_ExplicitVarSizeWithFlags_Flags[q11] /\ x_ExplicitVarSizeWithFlags_Values[q11] = q9 | q11 : int(1..4)]) - | q9 : int(1..4)]), - and([q12 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q12] < x_ExplicitVarSizeWithMarker_Values[q12 + 1] - | q12 : int(1..3)]), - and([q13 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q13] = 1 | q13 : int(1..4)]), - x_ExplicitVarSizeWithMarker_Marker <= 4, - and([q16 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q16]] - | q16 : int(1..4)]), - and([x_Occurrence[q17] -> - or([q19 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q19] = q17 - | q19 : int(1..4)]) - | q17 : int(1..4)]), - and([q21 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q23] /\ - x_ExplicitVarSizeWithFlags_Values[q23] = x_ExplicitVarSizeWithMarker_Values[q21] - | q23 : int(1..4)]) - | q21 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q25] -> - or([q27 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q27] = x_ExplicitVarSizeWithFlags_Values[q25] - | q27 : int(1..4)]) - | q25 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_1_1_4_4-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_1_1_4_4-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_1_4_4-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_1_1_4_4-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_1_1_4_4-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_1_4_4-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_1_1_4_4.eprime b/tests/exhaustive/basic/set06/expected/model_1_1_4_4.eprime deleted file mode 100644 index 2ced4fdbb0..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_1_4_4.eprime +++ /dev/null @@ -1,22 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -branching on [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_Occurrence] -such that - x_Occurrence[1], - x_Occurrence[2], - or([x_ExplicitVarSizeWithFlags_Flags[q13] /\ x_ExplicitVarSizeWithFlags_Values[q13] = 3 | q13 : int(1..4)]), - sum([toInt(x_Occurrence[q1]) | q1 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithFlags_Flags[q2 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q2] < x_ExplicitVarSizeWithFlags_Values[q2 + 1] - | q2 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3] = false -> x_ExplicitVarSizeWithFlags_Values[q3] = 1 | q3 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q4] | q4 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q5]) | q5 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithFlags_Flags[q8] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q8]] | q8 : int(1..4)]), - and([x_Occurrence[q9] -> - or([x_ExplicitVarSizeWithFlags_Flags[q11] /\ x_ExplicitVarSizeWithFlags_Values[q11] = q9 | q11 : int(1..4)]) - | q9 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_1_2_1_1-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_1_2_1_1-solution000001.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_2_1_1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_1_2_1_1-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_1_2_1_1-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_2_1_1-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_1_2_1_1.eprime b/tests/exhaustive/basic/set06/expected/model_1_2_1_1.eprime deleted file mode 100644 index fd00042c48..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_2_1_1.eprime +++ /dev/null @@ -1,19 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -branching on [x_ExplicitVarSizeWithDummy, x_Occurrence] -such that - x_Occurrence[1], - or([x_ExplicitVarSizeWithDummy[q12] != 5 /\ x_ExplicitVarSizeWithDummy[q12] = 2 | q12 : int(1..4)]), - x_Occurrence[3], - sum([toInt(x_Occurrence[q1]) | q1 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithDummy[q2] < x_ExplicitVarSizeWithDummy[q2 + 1] \/ x_ExplicitVarSizeWithDummy[q2] = 5 - | q2 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q3] = 5 -> x_ExplicitVarSizeWithDummy[q3 + 1] = 5 | q3 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q4] != 5) | q4 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithDummy[q7] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q7]] | q7 : int(1..4)]), - and([x_Occurrence[q8] -> - or([x_ExplicitVarSizeWithDummy[q10] != 5 /\ x_ExplicitVarSizeWithDummy[q10] = q8 | q10 : int(1..4)]) - | q8 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_1_2_1_2-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_1_2_1_2-solution000001.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_2_1_2-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_1_2_1_2-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_1_2_1_2-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_2_1_2-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_1_2_1_2.eprime b/tests/exhaustive/basic/set06/expected/model_1_2_1_2.eprime deleted file mode 100644 index fd00042c48..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_2_1_2.eprime +++ /dev/null @@ -1,19 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -branching on [x_ExplicitVarSizeWithDummy, x_Occurrence] -such that - x_Occurrence[1], - or([x_ExplicitVarSizeWithDummy[q12] != 5 /\ x_ExplicitVarSizeWithDummy[q12] = 2 | q12 : int(1..4)]), - x_Occurrence[3], - sum([toInt(x_Occurrence[q1]) | q1 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithDummy[q2] < x_ExplicitVarSizeWithDummy[q2 + 1] \/ x_ExplicitVarSizeWithDummy[q2] = 5 - | q2 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q3] = 5 -> x_ExplicitVarSizeWithDummy[q3 + 1] = 5 | q3 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q4] != 5) | q4 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithDummy[q7] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q7]] | q7 : int(1..4)]), - and([x_Occurrence[q8] -> - or([x_ExplicitVarSizeWithDummy[q10] != 5 /\ x_ExplicitVarSizeWithDummy[q10] = q8 | q10 : int(1..4)]) - | q8 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_1_2_1_3-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_1_2_1_3-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_2_1_3-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_1_2_1_3-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_1_2_1_3-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_2_1_3-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_1_2_1_3.eprime b/tests/exhaustive/basic/set06/expected/model_1_2_1_3.eprime deleted file mode 100644 index 9cd2a1ceb8..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_2_1_3.eprime +++ /dev/null @@ -1,43 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_Occurrence, x_ExplicitVarSizeWithDummy] -such that - x_Occurrence[1], - or([x_ExplicitVarSizeWithDummy[q28] != 5 /\ x_ExplicitVarSizeWithDummy[q28] = 2 | q28 : int(1..4)]), - x_Occurrence[3], - sum([toInt(x_Occurrence[q1]) | q1 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithDummy[q2] < x_ExplicitVarSizeWithDummy[q2 + 1] \/ x_ExplicitVarSizeWithDummy[q2] = 5 - | q2 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q3] = 5 -> x_ExplicitVarSizeWithDummy[q3 + 1] = 5 | q3 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q4] != 5) | q4 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithDummy[q7] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q7]] | q7 : int(1..4)]), - and([x_Occurrence[q8] -> - or([x_ExplicitVarSizeWithDummy[q10] != 5 /\ x_ExplicitVarSizeWithDummy[q10] = q8 | q10 : int(1..4)]) - | q8 : int(1..4)]), - and([q11 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q11] < x_ExplicitVarSizeWithMarker_Values[q11 + 1] - | q11 : int(1..3)]), - and([q12 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q12] = 1 | q12 : int(1..4)]), - x_ExplicitVarSizeWithMarker_Marker <= 4, - and([q15 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q15]] - | q15 : int(1..4)]), - and([x_Occurrence[q16] -> - or([q18 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q18] = q16 - | q18 : int(1..4)]) - | q16 : int(1..4)]), - and([q20 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q22] != 5 /\ - x_ExplicitVarSizeWithDummy[q22] = x_ExplicitVarSizeWithMarker_Values[q20] - | q22 : int(1..4)]) - | q20 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q24] != 5 -> - or([q26 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q26] = x_ExplicitVarSizeWithDummy[q24] - | q26 : int(1..4)]) - | q24 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_1_2_1_4-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_1_2_1_4-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_2_1_4-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_1_2_1_4-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_1_2_1_4-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_2_1_4-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_1_2_1_4.eprime b/tests/exhaustive/basic/set06/expected/model_1_2_1_4.eprime deleted file mode 100644 index 16ffeaa1a3..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_2_1_4.eprime +++ /dev/null @@ -1,44 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_Occurrence, x_ExplicitVarSizeWithDummy] -such that - x_Occurrence[1], - or([x_ExplicitVarSizeWithDummy[q30] != 5 /\ x_ExplicitVarSizeWithDummy[q30] = 2 | q30 : int(1..4)]), - x_Occurrence[3], - sum([toInt(x_Occurrence[q1]) | q1 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithDummy[q2] < x_ExplicitVarSizeWithDummy[q2 + 1] \/ x_ExplicitVarSizeWithDummy[q2] = 5 - | q2 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q3] = 5 -> x_ExplicitVarSizeWithDummy[q3 + 1] = 5 | q3 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q4] != 5) | q4 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithDummy[q7] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q7]] | q7 : int(1..4)]), - and([x_Occurrence[q8] -> - or([x_ExplicitVarSizeWithDummy[q10] != 5 /\ x_ExplicitVarSizeWithDummy[q10] = q8 | q10 : int(1..4)]) - | q8 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q11 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q11] < x_ExplicitVarSizeWithFlags_Values[q11 + 1] - | q11 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q12] = false -> x_ExplicitVarSizeWithFlags_Values[q12] = 1 - | q12 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q13 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q13] | q13 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q14]) | q14 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithFlags_Flags[q17] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q17]] - | q17 : int(1..4)]), - and([x_Occurrence[q18] -> - or([x_ExplicitVarSizeWithFlags_Flags[q20] /\ x_ExplicitVarSizeWithFlags_Values[q20] = q18 | q20 : int(1..4)]) - | q18 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q22] -> - or([x_ExplicitVarSizeWithDummy[q24] != 5 /\ - x_ExplicitVarSizeWithDummy[q24] = x_ExplicitVarSizeWithFlags_Values[q22] - | q24 : int(1..4)]) - | q22 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q26] != 5 -> - or([x_ExplicitVarSizeWithFlags_Flags[q28] /\ - x_ExplicitVarSizeWithFlags_Values[q28] = x_ExplicitVarSizeWithDummy[q26] - | q28 : int(1..4)]) - | q26 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_1_2_2_1-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_1_2_2_1-solution000001.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_2_2_1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_1_2_2_1-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_1_2_2_1-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_2_2_1-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_1_2_2_1.eprime b/tests/exhaustive/basic/set06/expected/model_1_2_2_1.eprime deleted file mode 100644 index 31cd01bf55..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_2_2_1.eprime +++ /dev/null @@ -1,19 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -branching on [x_ExplicitVarSizeWithDummy, x_Occurrence] -such that - x_Occurrence[1], - or([x_ExplicitVarSizeWithDummy[q12] != 5 /\ x_ExplicitVarSizeWithDummy[q12] = 2 | q12 : int(1..4)]), - or([x_ExplicitVarSizeWithDummy[q14] != 5 /\ x_ExplicitVarSizeWithDummy[q14] = 3 | q14 : int(1..4)]), - sum([toInt(x_Occurrence[q1]) | q1 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithDummy[q2] < x_ExplicitVarSizeWithDummy[q2 + 1] \/ x_ExplicitVarSizeWithDummy[q2] = 5 - | q2 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q3] = 5 -> x_ExplicitVarSizeWithDummy[q3 + 1] = 5 | q3 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q4] != 5) | q4 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithDummy[q7] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q7]] | q7 : int(1..4)]), - and([x_Occurrence[q8] -> - or([x_ExplicitVarSizeWithDummy[q10] != 5 /\ x_ExplicitVarSizeWithDummy[q10] = q8 | q10 : int(1..4)]) - | q8 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_1_2_2_2-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_1_2_2_2-solution000001.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_2_2_2-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_1_2_2_2-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_1_2_2_2-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_2_2_2-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_1_2_2_2.eprime b/tests/exhaustive/basic/set06/expected/model_1_2_2_2.eprime deleted file mode 100644 index 31cd01bf55..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_2_2_2.eprime +++ /dev/null @@ -1,19 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -branching on [x_ExplicitVarSizeWithDummy, x_Occurrence] -such that - x_Occurrence[1], - or([x_ExplicitVarSizeWithDummy[q12] != 5 /\ x_ExplicitVarSizeWithDummy[q12] = 2 | q12 : int(1..4)]), - or([x_ExplicitVarSizeWithDummy[q14] != 5 /\ x_ExplicitVarSizeWithDummy[q14] = 3 | q14 : int(1..4)]), - sum([toInt(x_Occurrence[q1]) | q1 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithDummy[q2] < x_ExplicitVarSizeWithDummy[q2 + 1] \/ x_ExplicitVarSizeWithDummy[q2] = 5 - | q2 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q3] = 5 -> x_ExplicitVarSizeWithDummy[q3 + 1] = 5 | q3 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q4] != 5) | q4 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithDummy[q7] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q7]] | q7 : int(1..4)]), - and([x_Occurrence[q8] -> - or([x_ExplicitVarSizeWithDummy[q10] != 5 /\ x_ExplicitVarSizeWithDummy[q10] = q8 | q10 : int(1..4)]) - | q8 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_1_2_2_3-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_1_2_2_3-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_2_2_3-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_1_2_2_3-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_1_2_2_3-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_2_2_3-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_1_2_2_3.eprime b/tests/exhaustive/basic/set06/expected/model_1_2_2_3.eprime deleted file mode 100644 index 2a7394dd4b..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_2_2_3.eprime +++ /dev/null @@ -1,43 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_Occurrence, x_ExplicitVarSizeWithDummy] -such that - x_Occurrence[1], - or([x_ExplicitVarSizeWithDummy[q28] != 5 /\ x_ExplicitVarSizeWithDummy[q28] = 2 | q28 : int(1..4)]), - or([x_ExplicitVarSizeWithDummy[q30] != 5 /\ x_ExplicitVarSizeWithDummy[q30] = 3 | q30 : int(1..4)]), - sum([toInt(x_Occurrence[q1]) | q1 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithDummy[q2] < x_ExplicitVarSizeWithDummy[q2 + 1] \/ x_ExplicitVarSizeWithDummy[q2] = 5 - | q2 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q3] = 5 -> x_ExplicitVarSizeWithDummy[q3 + 1] = 5 | q3 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q4] != 5) | q4 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithDummy[q7] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q7]] | q7 : int(1..4)]), - and([x_Occurrence[q8] -> - or([x_ExplicitVarSizeWithDummy[q10] != 5 /\ x_ExplicitVarSizeWithDummy[q10] = q8 | q10 : int(1..4)]) - | q8 : int(1..4)]), - and([q11 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q11] < x_ExplicitVarSizeWithMarker_Values[q11 + 1] - | q11 : int(1..3)]), - and([q12 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q12] = 1 | q12 : int(1..4)]), - x_ExplicitVarSizeWithMarker_Marker <= 4, - and([q15 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q15]] - | q15 : int(1..4)]), - and([x_Occurrence[q16] -> - or([q18 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q18] = q16 - | q18 : int(1..4)]) - | q16 : int(1..4)]), - and([q20 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q22] != 5 /\ - x_ExplicitVarSizeWithDummy[q22] = x_ExplicitVarSizeWithMarker_Values[q20] - | q22 : int(1..4)]) - | q20 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q24] != 5 -> - or([q26 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q26] = x_ExplicitVarSizeWithDummy[q24] - | q26 : int(1..4)]) - | q24 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_1_2_2_4-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_1_2_2_4-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_2_2_4-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_1_2_2_4-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_1_2_2_4-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_2_2_4-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_1_2_2_4.eprime b/tests/exhaustive/basic/set06/expected/model_1_2_2_4.eprime deleted file mode 100644 index cd3be25f64..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_2_2_4.eprime +++ /dev/null @@ -1,44 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_Occurrence, x_ExplicitVarSizeWithDummy] -such that - x_Occurrence[1], - or([x_ExplicitVarSizeWithDummy[q30] != 5 /\ x_ExplicitVarSizeWithDummy[q30] = 2 | q30 : int(1..4)]), - or([x_ExplicitVarSizeWithDummy[q32] != 5 /\ x_ExplicitVarSizeWithDummy[q32] = 3 | q32 : int(1..4)]), - sum([toInt(x_Occurrence[q1]) | q1 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithDummy[q2] < x_ExplicitVarSizeWithDummy[q2 + 1] \/ x_ExplicitVarSizeWithDummy[q2] = 5 - | q2 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q3] = 5 -> x_ExplicitVarSizeWithDummy[q3 + 1] = 5 | q3 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q4] != 5) | q4 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithDummy[q7] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q7]] | q7 : int(1..4)]), - and([x_Occurrence[q8] -> - or([x_ExplicitVarSizeWithDummy[q10] != 5 /\ x_ExplicitVarSizeWithDummy[q10] = q8 | q10 : int(1..4)]) - | q8 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q11 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q11] < x_ExplicitVarSizeWithFlags_Values[q11 + 1] - | q11 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q12] = false -> x_ExplicitVarSizeWithFlags_Values[q12] = 1 - | q12 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q13 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q13] | q13 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q14]) | q14 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithFlags_Flags[q17] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q17]] - | q17 : int(1..4)]), - and([x_Occurrence[q18] -> - or([x_ExplicitVarSizeWithFlags_Flags[q20] /\ x_ExplicitVarSizeWithFlags_Values[q20] = q18 | q20 : int(1..4)]) - | q18 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q22] -> - or([x_ExplicitVarSizeWithDummy[q24] != 5 /\ - x_ExplicitVarSizeWithDummy[q24] = x_ExplicitVarSizeWithFlags_Values[q22] - | q24 : int(1..4)]) - | q22 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q26] != 5 -> - or([x_ExplicitVarSizeWithFlags_Flags[q28] /\ - x_ExplicitVarSizeWithFlags_Values[q28] = x_ExplicitVarSizeWithDummy[q26] - | q28 : int(1..4)]) - | q26 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_1_2_3_1-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_1_2_3_1-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_2_3_1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_1_2_3_1-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_1_2_3_1-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_2_3_1-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_1_2_3_1.eprime b/tests/exhaustive/basic/set06/expected/model_1_2_3_1.eprime deleted file mode 100644 index c6b9ef4264..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_2_3_1.eprime +++ /dev/null @@ -1,43 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_Occurrence, x_ExplicitVarSizeWithDummy] -such that - x_Occurrence[1], - or([x_ExplicitVarSizeWithDummy[q28] != 5 /\ x_ExplicitVarSizeWithDummy[q28] = 2 | q28 : int(1..4)]), - or([q30 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q30] = 3 | q30 : int(1..4)]), - sum([toInt(x_Occurrence[q1]) | q1 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithDummy[q2] < x_ExplicitVarSizeWithDummy[q2 + 1] \/ x_ExplicitVarSizeWithDummy[q2] = 5 - | q2 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q3] = 5 -> x_ExplicitVarSizeWithDummy[q3 + 1] = 5 | q3 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q4] != 5) | q4 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithDummy[q7] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q7]] | q7 : int(1..4)]), - and([x_Occurrence[q8] -> - or([x_ExplicitVarSizeWithDummy[q10] != 5 /\ x_ExplicitVarSizeWithDummy[q10] = q8 | q10 : int(1..4)]) - | q8 : int(1..4)]), - and([q11 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q11] < x_ExplicitVarSizeWithMarker_Values[q11 + 1] - | q11 : int(1..3)]), - and([q12 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q12] = 1 | q12 : int(1..4)]), - x_ExplicitVarSizeWithMarker_Marker <= 4, - and([q15 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q15]] - | q15 : int(1..4)]), - and([x_Occurrence[q16] -> - or([q18 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q18] = q16 - | q18 : int(1..4)]) - | q16 : int(1..4)]), - and([q20 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q22] != 5 /\ - x_ExplicitVarSizeWithDummy[q22] = x_ExplicitVarSizeWithMarker_Values[q20] - | q22 : int(1..4)]) - | q20 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q24] != 5 -> - or([q26 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q26] = x_ExplicitVarSizeWithDummy[q24] - | q26 : int(1..4)]) - | q24 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_1_2_3_2-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_1_2_3_2-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_2_3_2-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_1_2_3_2-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_1_2_3_2-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_2_3_2-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_1_2_3_2.eprime b/tests/exhaustive/basic/set06/expected/model_1_2_3_2.eprime deleted file mode 100644 index c6b9ef4264..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_2_3_2.eprime +++ /dev/null @@ -1,43 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_Occurrence, x_ExplicitVarSizeWithDummy] -such that - x_Occurrence[1], - or([x_ExplicitVarSizeWithDummy[q28] != 5 /\ x_ExplicitVarSizeWithDummy[q28] = 2 | q28 : int(1..4)]), - or([q30 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q30] = 3 | q30 : int(1..4)]), - sum([toInt(x_Occurrence[q1]) | q1 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithDummy[q2] < x_ExplicitVarSizeWithDummy[q2 + 1] \/ x_ExplicitVarSizeWithDummy[q2] = 5 - | q2 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q3] = 5 -> x_ExplicitVarSizeWithDummy[q3 + 1] = 5 | q3 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q4] != 5) | q4 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithDummy[q7] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q7]] | q7 : int(1..4)]), - and([x_Occurrence[q8] -> - or([x_ExplicitVarSizeWithDummy[q10] != 5 /\ x_ExplicitVarSizeWithDummy[q10] = q8 | q10 : int(1..4)]) - | q8 : int(1..4)]), - and([q11 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q11] < x_ExplicitVarSizeWithMarker_Values[q11 + 1] - | q11 : int(1..3)]), - and([q12 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q12] = 1 | q12 : int(1..4)]), - x_ExplicitVarSizeWithMarker_Marker <= 4, - and([q15 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q15]] - | q15 : int(1..4)]), - and([x_Occurrence[q16] -> - or([q18 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q18] = q16 - | q18 : int(1..4)]) - | q16 : int(1..4)]), - and([q20 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q22] != 5 /\ - x_ExplicitVarSizeWithDummy[q22] = x_ExplicitVarSizeWithMarker_Values[q20] - | q22 : int(1..4)]) - | q20 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q24] != 5 -> - or([q26 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q26] = x_ExplicitVarSizeWithDummy[q24] - | q26 : int(1..4)]) - | q24 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_1_2_3_3-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_1_2_3_3-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_2_3_3-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_1_2_3_3-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_1_2_3_3-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_2_3_3-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_1_2_3_3.eprime b/tests/exhaustive/basic/set06/expected/model_1_2_3_3.eprime deleted file mode 100644 index c6b9ef4264..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_2_3_3.eprime +++ /dev/null @@ -1,43 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_Occurrence, x_ExplicitVarSizeWithDummy] -such that - x_Occurrence[1], - or([x_ExplicitVarSizeWithDummy[q28] != 5 /\ x_ExplicitVarSizeWithDummy[q28] = 2 | q28 : int(1..4)]), - or([q30 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q30] = 3 | q30 : int(1..4)]), - sum([toInt(x_Occurrence[q1]) | q1 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithDummy[q2] < x_ExplicitVarSizeWithDummy[q2 + 1] \/ x_ExplicitVarSizeWithDummy[q2] = 5 - | q2 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q3] = 5 -> x_ExplicitVarSizeWithDummy[q3 + 1] = 5 | q3 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q4] != 5) | q4 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithDummy[q7] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q7]] | q7 : int(1..4)]), - and([x_Occurrence[q8] -> - or([x_ExplicitVarSizeWithDummy[q10] != 5 /\ x_ExplicitVarSizeWithDummy[q10] = q8 | q10 : int(1..4)]) - | q8 : int(1..4)]), - and([q11 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q11] < x_ExplicitVarSizeWithMarker_Values[q11 + 1] - | q11 : int(1..3)]), - and([q12 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q12] = 1 | q12 : int(1..4)]), - x_ExplicitVarSizeWithMarker_Marker <= 4, - and([q15 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q15]] - | q15 : int(1..4)]), - and([x_Occurrence[q16] -> - or([q18 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q18] = q16 - | q18 : int(1..4)]) - | q16 : int(1..4)]), - and([q20 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q22] != 5 /\ - x_ExplicitVarSizeWithDummy[q22] = x_ExplicitVarSizeWithMarker_Values[q20] - | q22 : int(1..4)]) - | q20 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q24] != 5 -> - or([q26 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q26] = x_ExplicitVarSizeWithDummy[q24] - | q26 : int(1..4)]) - | q24 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_1_2_3_4-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_1_2_3_4-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_2_3_4-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_1_2_3_4-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_1_2_3_4-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_2_3_4-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_1_2_3_4.eprime b/tests/exhaustive/basic/set06/expected/model_1_2_3_4.eprime deleted file mode 100644 index 6015b45fb3..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_2_3_4.eprime +++ /dev/null @@ -1,78 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_Occurrence, x_ExplicitVarSizeWithDummy, - x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] -such that - x_Occurrence[1], - or([x_ExplicitVarSizeWithDummy[q54] != 5 /\ x_ExplicitVarSizeWithDummy[q54] = 2 | q54 : int(1..4)]), - or([q56 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q56] = 3 | q56 : int(1..4)]), - sum([toInt(x_Occurrence[q1]) | q1 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithDummy[q2] < x_ExplicitVarSizeWithDummy[q2 + 1] \/ x_ExplicitVarSizeWithDummy[q2] = 5 - | q2 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q3] = 5 -> x_ExplicitVarSizeWithDummy[q3 + 1] = 5 | q3 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q4] != 5) | q4 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithDummy[q7] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q7]] | q7 : int(1..4)]), - and([x_Occurrence[q8] -> - or([x_ExplicitVarSizeWithDummy[q10] != 5 /\ x_ExplicitVarSizeWithDummy[q10] = q8 | q10 : int(1..4)]) - | q8 : int(1..4)]), - and([q11 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q11] < x_ExplicitVarSizeWithMarker_Values[q11 + 1] - | q11 : int(1..3)]), - and([q12 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q12] = 1 | q12 : int(1..4)]), - x_ExplicitVarSizeWithMarker_Marker <= 4, - and([q15 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q15]] - | q15 : int(1..4)]), - and([x_Occurrence[q16] -> - or([q18 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q18] = q16 - | q18 : int(1..4)]) - | q16 : int(1..4)]), - and([q20 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q22] != 5 /\ - x_ExplicitVarSizeWithDummy[q22] = x_ExplicitVarSizeWithMarker_Values[q20] - | q22 : int(1..4)]) - | q20 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q24] != 5 -> - or([q26 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q26] = x_ExplicitVarSizeWithDummy[q24] - | q26 : int(1..4)]) - | q24 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q27 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q27] < x_ExplicitVarSizeWithFlags_Values[q27 + 1] - | q27 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q28] = false -> x_ExplicitVarSizeWithFlags_Values[q28] = 1 - | q28 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q29 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q29] | q29 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q30]) | q30 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithFlags_Flags[q33] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q33]] - | q33 : int(1..4)]), - and([x_Occurrence[q34] -> - or([x_ExplicitVarSizeWithFlags_Flags[q36] /\ x_ExplicitVarSizeWithFlags_Values[q36] = q34 | q36 : int(1..4)]) - | q34 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q38] -> - or([x_ExplicitVarSizeWithDummy[q40] != 5 /\ - x_ExplicitVarSizeWithDummy[q40] = x_ExplicitVarSizeWithFlags_Values[q38] - | q40 : int(1..4)]) - | q38 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q42] != 5 -> - or([x_ExplicitVarSizeWithFlags_Flags[q44] /\ - x_ExplicitVarSizeWithFlags_Values[q44] = x_ExplicitVarSizeWithDummy[q42] - | q44 : int(1..4)]) - | q42 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q46] -> - or([q48 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q48] = x_ExplicitVarSizeWithFlags_Values[q46] - | q48 : int(1..4)]) - | q46 : int(1..4)]), - and([q50 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q52] /\ - x_ExplicitVarSizeWithFlags_Values[q52] = x_ExplicitVarSizeWithMarker_Values[q50] - | q52 : int(1..4)]) - | q50 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_1_2_4_1-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_1_2_4_1-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_2_4_1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_1_2_4_1-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_1_2_4_1-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_2_4_1-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_1_2_4_1.eprime b/tests/exhaustive/basic/set06/expected/model_1_2_4_1.eprime deleted file mode 100644 index aed016ee53..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_2_4_1.eprime +++ /dev/null @@ -1,44 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_Occurrence, x_ExplicitVarSizeWithDummy] -such that - x_Occurrence[1], - or([x_ExplicitVarSizeWithDummy[q30] != 5 /\ x_ExplicitVarSizeWithDummy[q30] = 2 | q30 : int(1..4)]), - or([x_ExplicitVarSizeWithFlags_Flags[q32] /\ x_ExplicitVarSizeWithFlags_Values[q32] = 3 | q32 : int(1..4)]), - sum([toInt(x_Occurrence[q1]) | q1 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithDummy[q2] < x_ExplicitVarSizeWithDummy[q2 + 1] \/ x_ExplicitVarSizeWithDummy[q2] = 5 - | q2 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q3] = 5 -> x_ExplicitVarSizeWithDummy[q3 + 1] = 5 | q3 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q4] != 5) | q4 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithDummy[q7] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q7]] | q7 : int(1..4)]), - and([x_Occurrence[q8] -> - or([x_ExplicitVarSizeWithDummy[q10] != 5 /\ x_ExplicitVarSizeWithDummy[q10] = q8 | q10 : int(1..4)]) - | q8 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q11 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q11] < x_ExplicitVarSizeWithFlags_Values[q11 + 1] - | q11 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q12] = false -> x_ExplicitVarSizeWithFlags_Values[q12] = 1 - | q12 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q13 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q13] | q13 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q14]) | q14 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithFlags_Flags[q17] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q17]] - | q17 : int(1..4)]), - and([x_Occurrence[q18] -> - or([x_ExplicitVarSizeWithFlags_Flags[q20] /\ x_ExplicitVarSizeWithFlags_Values[q20] = q18 | q20 : int(1..4)]) - | q18 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q22] -> - or([x_ExplicitVarSizeWithDummy[q24] != 5 /\ - x_ExplicitVarSizeWithDummy[q24] = x_ExplicitVarSizeWithFlags_Values[q22] - | q24 : int(1..4)]) - | q22 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q26] != 5 -> - or([x_ExplicitVarSizeWithFlags_Flags[q28] /\ - x_ExplicitVarSizeWithFlags_Values[q28] = x_ExplicitVarSizeWithDummy[q26] - | q28 : int(1..4)]) - | q26 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_1_2_4_2-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_1_2_4_2-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_2_4_2-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_1_2_4_2-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_1_2_4_2-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_2_4_2-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_1_2_4_2.eprime b/tests/exhaustive/basic/set06/expected/model_1_2_4_2.eprime deleted file mode 100644 index aed016ee53..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_2_4_2.eprime +++ /dev/null @@ -1,44 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_Occurrence, x_ExplicitVarSizeWithDummy] -such that - x_Occurrence[1], - or([x_ExplicitVarSizeWithDummy[q30] != 5 /\ x_ExplicitVarSizeWithDummy[q30] = 2 | q30 : int(1..4)]), - or([x_ExplicitVarSizeWithFlags_Flags[q32] /\ x_ExplicitVarSizeWithFlags_Values[q32] = 3 | q32 : int(1..4)]), - sum([toInt(x_Occurrence[q1]) | q1 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithDummy[q2] < x_ExplicitVarSizeWithDummy[q2 + 1] \/ x_ExplicitVarSizeWithDummy[q2] = 5 - | q2 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q3] = 5 -> x_ExplicitVarSizeWithDummy[q3 + 1] = 5 | q3 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q4] != 5) | q4 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithDummy[q7] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q7]] | q7 : int(1..4)]), - and([x_Occurrence[q8] -> - or([x_ExplicitVarSizeWithDummy[q10] != 5 /\ x_ExplicitVarSizeWithDummy[q10] = q8 | q10 : int(1..4)]) - | q8 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q11 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q11] < x_ExplicitVarSizeWithFlags_Values[q11 + 1] - | q11 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q12] = false -> x_ExplicitVarSizeWithFlags_Values[q12] = 1 - | q12 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q13 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q13] | q13 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q14]) | q14 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithFlags_Flags[q17] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q17]] - | q17 : int(1..4)]), - and([x_Occurrence[q18] -> - or([x_ExplicitVarSizeWithFlags_Flags[q20] /\ x_ExplicitVarSizeWithFlags_Values[q20] = q18 | q20 : int(1..4)]) - | q18 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q22] -> - or([x_ExplicitVarSizeWithDummy[q24] != 5 /\ - x_ExplicitVarSizeWithDummy[q24] = x_ExplicitVarSizeWithFlags_Values[q22] - | q24 : int(1..4)]) - | q22 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q26] != 5 -> - or([x_ExplicitVarSizeWithFlags_Flags[q28] /\ - x_ExplicitVarSizeWithFlags_Values[q28] = x_ExplicitVarSizeWithDummy[q26] - | q28 : int(1..4)]) - | q26 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_1_2_4_3-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_1_2_4_3-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_2_4_3-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_1_2_4_3-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_1_2_4_3-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_2_4_3-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_1_2_4_3.eprime b/tests/exhaustive/basic/set06/expected/model_1_2_4_3.eprime deleted file mode 100644 index bb79bbed91..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_2_4_3.eprime +++ /dev/null @@ -1,78 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_Occurrence, x_ExplicitVarSizeWithDummy, - x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] -such that - x_Occurrence[1], - or([x_ExplicitVarSizeWithDummy[q54] != 5 /\ x_ExplicitVarSizeWithDummy[q54] = 2 | q54 : int(1..4)]), - or([x_ExplicitVarSizeWithFlags_Flags[q56] /\ x_ExplicitVarSizeWithFlags_Values[q56] = 3 | q56 : int(1..4)]), - sum([toInt(x_Occurrence[q1]) | q1 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithDummy[q2] < x_ExplicitVarSizeWithDummy[q2 + 1] \/ x_ExplicitVarSizeWithDummy[q2] = 5 - | q2 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q3] = 5 -> x_ExplicitVarSizeWithDummy[q3 + 1] = 5 | q3 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q4] != 5) | q4 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithDummy[q7] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q7]] | q7 : int(1..4)]), - and([x_Occurrence[q8] -> - or([x_ExplicitVarSizeWithDummy[q10] != 5 /\ x_ExplicitVarSizeWithDummy[q10] = q8 | q10 : int(1..4)]) - | q8 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q11 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q11] < x_ExplicitVarSizeWithFlags_Values[q11 + 1] - | q11 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q12] = false -> x_ExplicitVarSizeWithFlags_Values[q12] = 1 - | q12 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q13 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q13] | q13 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q14]) | q14 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithFlags_Flags[q17] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q17]] - | q17 : int(1..4)]), - and([x_Occurrence[q18] -> - or([x_ExplicitVarSizeWithFlags_Flags[q20] /\ x_ExplicitVarSizeWithFlags_Values[q20] = q18 | q20 : int(1..4)]) - | q18 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q22] -> - or([x_ExplicitVarSizeWithDummy[q24] != 5 /\ - x_ExplicitVarSizeWithDummy[q24] = x_ExplicitVarSizeWithFlags_Values[q22] - | q24 : int(1..4)]) - | q22 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q26] != 5 -> - or([x_ExplicitVarSizeWithFlags_Flags[q28] /\ - x_ExplicitVarSizeWithFlags_Values[q28] = x_ExplicitVarSizeWithDummy[q26] - | q28 : int(1..4)]) - | q26 : int(1..4)]), - and([q29 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q29] < x_ExplicitVarSizeWithMarker_Values[q29 + 1] - | q29 : int(1..3)]), - and([q30 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q30] = 1 | q30 : int(1..4)]), - x_ExplicitVarSizeWithMarker_Marker <= 4, - and([q33 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q33]] - | q33 : int(1..4)]), - and([x_Occurrence[q34] -> - or([q36 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q36] = q34 - | q36 : int(1..4)]) - | q34 : int(1..4)]), - and([q38 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q40] != 5 /\ - x_ExplicitVarSizeWithDummy[q40] = x_ExplicitVarSizeWithMarker_Values[q38] - | q40 : int(1..4)]) - | q38 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q42] != 5 -> - or([q44 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q44] = x_ExplicitVarSizeWithDummy[q42] - | q44 : int(1..4)]) - | q42 : int(1..4)]), - and([q46 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q48] /\ - x_ExplicitVarSizeWithFlags_Values[q48] = x_ExplicitVarSizeWithMarker_Values[q46] - | q48 : int(1..4)]) - | q46 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q50] -> - or([q52 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q52] = x_ExplicitVarSizeWithFlags_Values[q50] - | q52 : int(1..4)]) - | q50 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_1_2_4_4-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_1_2_4_4-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_2_4_4-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_1_2_4_4-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_1_2_4_4-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_2_4_4-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_1_2_4_4.eprime b/tests/exhaustive/basic/set06/expected/model_1_2_4_4.eprime deleted file mode 100644 index aed016ee53..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_2_4_4.eprime +++ /dev/null @@ -1,44 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_Occurrence, x_ExplicitVarSizeWithDummy] -such that - x_Occurrence[1], - or([x_ExplicitVarSizeWithDummy[q30] != 5 /\ x_ExplicitVarSizeWithDummy[q30] = 2 | q30 : int(1..4)]), - or([x_ExplicitVarSizeWithFlags_Flags[q32] /\ x_ExplicitVarSizeWithFlags_Values[q32] = 3 | q32 : int(1..4)]), - sum([toInt(x_Occurrence[q1]) | q1 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithDummy[q2] < x_ExplicitVarSizeWithDummy[q2 + 1] \/ x_ExplicitVarSizeWithDummy[q2] = 5 - | q2 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q3] = 5 -> x_ExplicitVarSizeWithDummy[q3 + 1] = 5 | q3 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q4] != 5) | q4 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithDummy[q7] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q7]] | q7 : int(1..4)]), - and([x_Occurrence[q8] -> - or([x_ExplicitVarSizeWithDummy[q10] != 5 /\ x_ExplicitVarSizeWithDummy[q10] = q8 | q10 : int(1..4)]) - | q8 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q11 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q11] < x_ExplicitVarSizeWithFlags_Values[q11 + 1] - | q11 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q12] = false -> x_ExplicitVarSizeWithFlags_Values[q12] = 1 - | q12 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q13 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q13] | q13 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q14]) | q14 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithFlags_Flags[q17] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q17]] - | q17 : int(1..4)]), - and([x_Occurrence[q18] -> - or([x_ExplicitVarSizeWithFlags_Flags[q20] /\ x_ExplicitVarSizeWithFlags_Values[q20] = q18 | q20 : int(1..4)]) - | q18 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q22] -> - or([x_ExplicitVarSizeWithDummy[q24] != 5 /\ - x_ExplicitVarSizeWithDummy[q24] = x_ExplicitVarSizeWithFlags_Values[q22] - | q24 : int(1..4)]) - | q22 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q26] != 5 -> - or([x_ExplicitVarSizeWithFlags_Flags[q28] /\ - x_ExplicitVarSizeWithFlags_Values[q28] = x_ExplicitVarSizeWithDummy[q26] - | q28 : int(1..4)]) - | q26 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_1_3_1_1-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_1_3_1_1-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_3_1_1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_1_3_1_1-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_1_3_1_1-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_3_1_1-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_1_3_1_1.eprime b/tests/exhaustive/basic/set06/expected/model_1_3_1_1.eprime deleted file mode 100644 index 534888a487..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_3_1_1.eprime +++ /dev/null @@ -1,22 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -branching on [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_Occurrence] -such that - x_Occurrence[1], - or([q11 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q11] = 2 | q11 : int(1..4)]), - x_Occurrence[3], - sum([toInt(x_Occurrence[q1]) | q1 : int(1..4)]) <= 4, - and([q2 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q2] < x_ExplicitVarSizeWithMarker_Values[q2 + 1] - | q2 : int(1..3)]), - and([q3 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q3] = 1 | q3 : int(1..4)]), - x_ExplicitVarSizeWithMarker_Marker <= 4, - and([q6 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q6]] - | q6 : int(1..4)]), - and([x_Occurrence[q7] -> - or([q9 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q9] = q7 | q9 : int(1..4)]) - | q7 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_1_3_1_2-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_1_3_1_2-solution000001.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_3_1_2-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_1_3_1_2-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_1_3_1_2-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_3_1_2-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_1_3_1_2.eprime b/tests/exhaustive/basic/set06/expected/model_1_3_1_2.eprime deleted file mode 100644 index 3a488b51f2..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_3_1_2.eprime +++ /dev/null @@ -1,42 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -branching on - [x_ExplicitVarSizeWithDummy, x_Occurrence, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] -such that - x_Occurrence[1], - or([q28 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q28] = 2 | q28 : int(1..4)]), - x_Occurrence[3], - sum([toInt(x_Occurrence[q1]) | q1 : int(1..4)]) <= 4, - and([q2 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q2] < x_ExplicitVarSizeWithMarker_Values[q2 + 1] - | q2 : int(1..3)]), - and([q3 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q3] = 1 | q3 : int(1..4)]), - x_ExplicitVarSizeWithMarker_Marker <= 4, - and([q6 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q6]] - | q6 : int(1..4)]), - and([x_Occurrence[q7] -> - or([q9 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q9] = q7 | q9 : int(1..4)]) - | q7 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q10] < x_ExplicitVarSizeWithDummy[q10 + 1] \/ x_ExplicitVarSizeWithDummy[q10] = 5 - | q10 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q11] = 5 -> x_ExplicitVarSizeWithDummy[q11 + 1] = 5 | q11 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q12] != 5) | q12 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithDummy[q15] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q15]] | q15 : int(1..4)]), - and([x_Occurrence[q16] -> - or([x_ExplicitVarSizeWithDummy[q18] != 5 /\ x_ExplicitVarSizeWithDummy[q18] = q16 | q18 : int(1..4)]) - | q16 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q20] != 5 -> - or([q22 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q22] = x_ExplicitVarSizeWithDummy[q20] - | q22 : int(1..4)]) - | q20 : int(1..4)]), - and([q24 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q26] != 5 /\ - x_ExplicitVarSizeWithDummy[q26] = x_ExplicitVarSizeWithMarker_Values[q24] - | q26 : int(1..4)]) - | q24 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_1_3_1_3-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_1_3_1_3-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_3_1_3-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_1_3_1_3-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_1_3_1_3-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_3_1_3-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_1_3_1_3.eprime b/tests/exhaustive/basic/set06/expected/model_1_3_1_3.eprime deleted file mode 100644 index 534888a487..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_3_1_3.eprime +++ /dev/null @@ -1,22 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -branching on [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_Occurrence] -such that - x_Occurrence[1], - or([q11 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q11] = 2 | q11 : int(1..4)]), - x_Occurrence[3], - sum([toInt(x_Occurrence[q1]) | q1 : int(1..4)]) <= 4, - and([q2 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q2] < x_ExplicitVarSizeWithMarker_Values[q2 + 1] - | q2 : int(1..3)]), - and([q3 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q3] = 1 | q3 : int(1..4)]), - x_ExplicitVarSizeWithMarker_Marker <= 4, - and([q6 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q6]] - | q6 : int(1..4)]), - and([x_Occurrence[q7] -> - or([q9 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q9] = q7 | q9 : int(1..4)]) - | q7 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_1_3_1_4-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_1_3_1_4-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_3_1_4-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_1_3_1_4-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_1_3_1_4-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_3_1_4-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_1_3_1_4.eprime b/tests/exhaustive/basic/set06/expected/model_1_3_1_4.eprime deleted file mode 100644 index c11065ed05..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_3_1_4.eprime +++ /dev/null @@ -1,48 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_Occurrence, - x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] -such that - x_Occurrence[1], - or([q29 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q29] = 2 | q29 : int(1..4)]), - x_Occurrence[3], - sum([toInt(x_Occurrence[q1]) | q1 : int(1..4)]) <= 4, - and([q2 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q2] < x_ExplicitVarSizeWithMarker_Values[q2 + 1] - | q2 : int(1..3)]), - and([q3 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q3] = 1 | q3 : int(1..4)]), - x_ExplicitVarSizeWithMarker_Marker <= 4, - and([q6 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q6]] - | q6 : int(1..4)]), - and([x_Occurrence[q7] -> - or([q9 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q9] = q7 | q9 : int(1..4)]) - | q7 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q10 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q10] < x_ExplicitVarSizeWithFlags_Values[q10 + 1] - | q10 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q11] = false -> x_ExplicitVarSizeWithFlags_Values[q11] = 1 - | q11 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q12 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q12] | q12 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q13]) | q13 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithFlags_Flags[q16] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q16]] - | q16 : int(1..4)]), - and([x_Occurrence[q17] -> - or([x_ExplicitVarSizeWithFlags_Flags[q19] /\ x_ExplicitVarSizeWithFlags_Values[q19] = q17 | q19 : int(1..4)]) - | q17 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q21] -> - or([q23 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q23] = x_ExplicitVarSizeWithFlags_Values[q21] - | q23 : int(1..4)]) - | q21 : int(1..4)]), - and([q25 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q27] /\ - x_ExplicitVarSizeWithFlags_Values[q27] = x_ExplicitVarSizeWithMarker_Values[q25] - | q27 : int(1..4)]) - | q25 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_1_3_2_1-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_1_3_2_1-solution000001.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_3_2_1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_1_3_2_1-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_1_3_2_1-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_3_2_1-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_1_3_2_1.eprime b/tests/exhaustive/basic/set06/expected/model_1_3_2_1.eprime deleted file mode 100644 index 1df703b36a..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_3_2_1.eprime +++ /dev/null @@ -1,42 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -branching on - [x_ExplicitVarSizeWithDummy, x_Occurrence, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] -such that - x_Occurrence[1], - or([q28 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q28] = 2 | q28 : int(1..4)]), - or([x_ExplicitVarSizeWithDummy[q30] != 5 /\ x_ExplicitVarSizeWithDummy[q30] = 3 | q30 : int(1..4)]), - sum([toInt(x_Occurrence[q1]) | q1 : int(1..4)]) <= 4, - and([q2 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q2] < x_ExplicitVarSizeWithMarker_Values[q2 + 1] - | q2 : int(1..3)]), - and([q3 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q3] = 1 | q3 : int(1..4)]), - x_ExplicitVarSizeWithMarker_Marker <= 4, - and([q6 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q6]] - | q6 : int(1..4)]), - and([x_Occurrence[q7] -> - or([q9 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q9] = q7 | q9 : int(1..4)]) - | q7 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q10] < x_ExplicitVarSizeWithDummy[q10 + 1] \/ x_ExplicitVarSizeWithDummy[q10] = 5 - | q10 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q11] = 5 -> x_ExplicitVarSizeWithDummy[q11 + 1] = 5 | q11 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q12] != 5) | q12 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithDummy[q15] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q15]] | q15 : int(1..4)]), - and([x_Occurrence[q16] -> - or([x_ExplicitVarSizeWithDummy[q18] != 5 /\ x_ExplicitVarSizeWithDummy[q18] = q16 | q18 : int(1..4)]) - | q16 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q20] != 5 -> - or([q22 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q22] = x_ExplicitVarSizeWithDummy[q20] - | q22 : int(1..4)]) - | q20 : int(1..4)]), - and([q24 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q26] != 5 /\ - x_ExplicitVarSizeWithDummy[q26] = x_ExplicitVarSizeWithMarker_Values[q24] - | q26 : int(1..4)]) - | q24 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_1_3_2_2-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_1_3_2_2-solution000001.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_3_2_2-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_1_3_2_2-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_1_3_2_2-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_3_2_2-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_1_3_2_2.eprime b/tests/exhaustive/basic/set06/expected/model_1_3_2_2.eprime deleted file mode 100644 index 1df703b36a..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_3_2_2.eprime +++ /dev/null @@ -1,42 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -branching on - [x_ExplicitVarSizeWithDummy, x_Occurrence, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] -such that - x_Occurrence[1], - or([q28 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q28] = 2 | q28 : int(1..4)]), - or([x_ExplicitVarSizeWithDummy[q30] != 5 /\ x_ExplicitVarSizeWithDummy[q30] = 3 | q30 : int(1..4)]), - sum([toInt(x_Occurrence[q1]) | q1 : int(1..4)]) <= 4, - and([q2 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q2] < x_ExplicitVarSizeWithMarker_Values[q2 + 1] - | q2 : int(1..3)]), - and([q3 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q3] = 1 | q3 : int(1..4)]), - x_ExplicitVarSizeWithMarker_Marker <= 4, - and([q6 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q6]] - | q6 : int(1..4)]), - and([x_Occurrence[q7] -> - or([q9 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q9] = q7 | q9 : int(1..4)]) - | q7 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q10] < x_ExplicitVarSizeWithDummy[q10 + 1] \/ x_ExplicitVarSizeWithDummy[q10] = 5 - | q10 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q11] = 5 -> x_ExplicitVarSizeWithDummy[q11 + 1] = 5 | q11 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q12] != 5) | q12 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithDummy[q15] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q15]] | q15 : int(1..4)]), - and([x_Occurrence[q16] -> - or([x_ExplicitVarSizeWithDummy[q18] != 5 /\ x_ExplicitVarSizeWithDummy[q18] = q16 | q18 : int(1..4)]) - | q16 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q20] != 5 -> - or([q22 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q22] = x_ExplicitVarSizeWithDummy[q20] - | q22 : int(1..4)]) - | q20 : int(1..4)]), - and([q24 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q26] != 5 /\ - x_ExplicitVarSizeWithDummy[q26] = x_ExplicitVarSizeWithMarker_Values[q24] - | q26 : int(1..4)]) - | q24 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_1_3_2_3-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_1_3_2_3-solution000001.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_3_2_3-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_1_3_2_3-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_1_3_2_3-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_3_2_3-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_1_3_2_3.eprime b/tests/exhaustive/basic/set06/expected/model_1_3_2_3.eprime deleted file mode 100644 index 1df703b36a..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_3_2_3.eprime +++ /dev/null @@ -1,42 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -branching on - [x_ExplicitVarSizeWithDummy, x_Occurrence, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] -such that - x_Occurrence[1], - or([q28 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q28] = 2 | q28 : int(1..4)]), - or([x_ExplicitVarSizeWithDummy[q30] != 5 /\ x_ExplicitVarSizeWithDummy[q30] = 3 | q30 : int(1..4)]), - sum([toInt(x_Occurrence[q1]) | q1 : int(1..4)]) <= 4, - and([q2 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q2] < x_ExplicitVarSizeWithMarker_Values[q2 + 1] - | q2 : int(1..3)]), - and([q3 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q3] = 1 | q3 : int(1..4)]), - x_ExplicitVarSizeWithMarker_Marker <= 4, - and([q6 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q6]] - | q6 : int(1..4)]), - and([x_Occurrence[q7] -> - or([q9 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q9] = q7 | q9 : int(1..4)]) - | q7 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q10] < x_ExplicitVarSizeWithDummy[q10 + 1] \/ x_ExplicitVarSizeWithDummy[q10] = 5 - | q10 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q11] = 5 -> x_ExplicitVarSizeWithDummy[q11 + 1] = 5 | q11 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q12] != 5) | q12 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithDummy[q15] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q15]] | q15 : int(1..4)]), - and([x_Occurrence[q16] -> - or([x_ExplicitVarSizeWithDummy[q18] != 5 /\ x_ExplicitVarSizeWithDummy[q18] = q16 | q18 : int(1..4)]) - | q16 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q20] != 5 -> - or([q22 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q22] = x_ExplicitVarSizeWithDummy[q20] - | q22 : int(1..4)]) - | q20 : int(1..4)]), - and([q24 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q26] != 5 /\ - x_ExplicitVarSizeWithDummy[q26] = x_ExplicitVarSizeWithMarker_Values[q24] - | q26 : int(1..4)]) - | q24 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_1_3_2_4-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_1_3_2_4-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_3_2_4-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_1_3_2_4-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_1_3_2_4-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_3_2_4-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_1_3_2_4.eprime b/tests/exhaustive/basic/set06/expected/model_1_3_2_4.eprime deleted file mode 100644 index d71d427457..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_3_2_4.eprime +++ /dev/null @@ -1,77 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_Occurrence, - x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy] -such that - x_Occurrence[1], - or([q54 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q54] = 2 | q54 : int(1..4)]), - or([x_ExplicitVarSizeWithDummy[q56] != 5 /\ x_ExplicitVarSizeWithDummy[q56] = 3 | q56 : int(1..4)]), - sum([toInt(x_Occurrence[q1]) | q1 : int(1..4)]) <= 4, - and([q2 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q2] < x_ExplicitVarSizeWithMarker_Values[q2 + 1] - | q2 : int(1..3)]), - and([q3 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q3] = 1 | q3 : int(1..4)]), - x_ExplicitVarSizeWithMarker_Marker <= 4, - and([q6 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q6]] - | q6 : int(1..4)]), - and([x_Occurrence[q7] -> - or([q9 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q9] = q7 | q9 : int(1..4)]) - | q7 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q10] < x_ExplicitVarSizeWithDummy[q10 + 1] \/ x_ExplicitVarSizeWithDummy[q10] = 5 - | q10 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q11] = 5 -> x_ExplicitVarSizeWithDummy[q11 + 1] = 5 | q11 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q12] != 5) | q12 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithDummy[q15] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q15]] | q15 : int(1..4)]), - and([x_Occurrence[q16] -> - or([x_ExplicitVarSizeWithDummy[q18] != 5 /\ x_ExplicitVarSizeWithDummy[q18] = q16 | q18 : int(1..4)]) - | q16 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q20] != 5 -> - or([q22 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q22] = x_ExplicitVarSizeWithDummy[q20] - | q22 : int(1..4)]) - | q20 : int(1..4)]), - and([q24 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q26] != 5 /\ - x_ExplicitVarSizeWithDummy[q26] = x_ExplicitVarSizeWithMarker_Values[q24] - | q26 : int(1..4)]) - | q24 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q27 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q27] < x_ExplicitVarSizeWithFlags_Values[q27 + 1] - | q27 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q28] = false -> x_ExplicitVarSizeWithFlags_Values[q28] = 1 - | q28 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q29 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q29] | q29 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q30]) | q30 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithFlags_Flags[q33] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q33]] - | q33 : int(1..4)]), - and([x_Occurrence[q34] -> - or([x_ExplicitVarSizeWithFlags_Flags[q36] /\ x_ExplicitVarSizeWithFlags_Values[q36] = q34 | q36 : int(1..4)]) - | q34 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q38] -> - or([q40 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q40] = x_ExplicitVarSizeWithFlags_Values[q38] - | q40 : int(1..4)]) - | q38 : int(1..4)]), - and([q42 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q44] /\ - x_ExplicitVarSizeWithFlags_Values[q44] = x_ExplicitVarSizeWithMarker_Values[q42] - | q44 : int(1..4)]) - | q42 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q46] -> - or([x_ExplicitVarSizeWithDummy[q48] != 5 /\ - x_ExplicitVarSizeWithDummy[q48] = x_ExplicitVarSizeWithFlags_Values[q46] - | q48 : int(1..4)]) - | q46 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q50] != 5 -> - or([x_ExplicitVarSizeWithFlags_Flags[q52] /\ - x_ExplicitVarSizeWithFlags_Values[q52] = x_ExplicitVarSizeWithDummy[q50] - | q52 : int(1..4)]) - | q50 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_1_3_3_1-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_1_3_3_1-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_3_3_1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_1_3_3_1-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_1_3_3_1-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_3_3_1-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_1_3_3_1.eprime b/tests/exhaustive/basic/set06/expected/model_1_3_3_1.eprime deleted file mode 100644 index 10616f2d34..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_3_3_1.eprime +++ /dev/null @@ -1,22 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -branching on [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_Occurrence] -such that - x_Occurrence[1], - or([q11 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q11] = 2 | q11 : int(1..4)]), - or([q13 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q13] = 3 | q13 : int(1..4)]), - sum([toInt(x_Occurrence[q1]) | q1 : int(1..4)]) <= 4, - and([q2 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q2] < x_ExplicitVarSizeWithMarker_Values[q2 + 1] - | q2 : int(1..3)]), - and([q3 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q3] = 1 | q3 : int(1..4)]), - x_ExplicitVarSizeWithMarker_Marker <= 4, - and([q6 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q6]] - | q6 : int(1..4)]), - and([x_Occurrence[q7] -> - or([q9 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q9] = q7 | q9 : int(1..4)]) - | q7 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_1_3_3_2-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_1_3_3_2-solution000001.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_3_3_2-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_1_3_3_2-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_1_3_3_2-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_3_3_2-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_1_3_3_2.eprime b/tests/exhaustive/basic/set06/expected/model_1_3_3_2.eprime deleted file mode 100644 index 0a6a65be24..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_3_3_2.eprime +++ /dev/null @@ -1,42 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -branching on - [x_ExplicitVarSizeWithDummy, x_Occurrence, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] -such that - x_Occurrence[1], - or([q28 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q28] = 2 | q28 : int(1..4)]), - or([q30 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q30] = 3 | q30 : int(1..4)]), - sum([toInt(x_Occurrence[q1]) | q1 : int(1..4)]) <= 4, - and([q2 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q2] < x_ExplicitVarSizeWithMarker_Values[q2 + 1] - | q2 : int(1..3)]), - and([q3 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q3] = 1 | q3 : int(1..4)]), - x_ExplicitVarSizeWithMarker_Marker <= 4, - and([q6 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q6]] - | q6 : int(1..4)]), - and([x_Occurrence[q7] -> - or([q9 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q9] = q7 | q9 : int(1..4)]) - | q7 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q10] < x_ExplicitVarSizeWithDummy[q10 + 1] \/ x_ExplicitVarSizeWithDummy[q10] = 5 - | q10 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q11] = 5 -> x_ExplicitVarSizeWithDummy[q11 + 1] = 5 | q11 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q12] != 5) | q12 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithDummy[q15] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q15]] | q15 : int(1..4)]), - and([x_Occurrence[q16] -> - or([x_ExplicitVarSizeWithDummy[q18] != 5 /\ x_ExplicitVarSizeWithDummy[q18] = q16 | q18 : int(1..4)]) - | q16 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q20] != 5 -> - or([q22 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q22] = x_ExplicitVarSizeWithDummy[q20] - | q22 : int(1..4)]) - | q20 : int(1..4)]), - and([q24 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q26] != 5 /\ - x_ExplicitVarSizeWithDummy[q26] = x_ExplicitVarSizeWithMarker_Values[q24] - | q26 : int(1..4)]) - | q24 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_1_3_3_3-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_1_3_3_3-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_3_3_3-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_1_3_3_3-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_1_3_3_3-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_3_3_3-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_1_3_3_3.eprime b/tests/exhaustive/basic/set06/expected/model_1_3_3_3.eprime deleted file mode 100644 index 10616f2d34..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_3_3_3.eprime +++ /dev/null @@ -1,22 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -branching on [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_Occurrence] -such that - x_Occurrence[1], - or([q11 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q11] = 2 | q11 : int(1..4)]), - or([q13 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q13] = 3 | q13 : int(1..4)]), - sum([toInt(x_Occurrence[q1]) | q1 : int(1..4)]) <= 4, - and([q2 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q2] < x_ExplicitVarSizeWithMarker_Values[q2 + 1] - | q2 : int(1..3)]), - and([q3 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q3] = 1 | q3 : int(1..4)]), - x_ExplicitVarSizeWithMarker_Marker <= 4, - and([q6 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q6]] - | q6 : int(1..4)]), - and([x_Occurrence[q7] -> - or([q9 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q9] = q7 | q9 : int(1..4)]) - | q7 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_1_3_3_4-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_1_3_3_4-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_3_3_4-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_1_3_3_4-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_1_3_3_4-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_3_3_4-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_1_3_3_4.eprime b/tests/exhaustive/basic/set06/expected/model_1_3_3_4.eprime deleted file mode 100644 index 0d2728b93c..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_3_3_4.eprime +++ /dev/null @@ -1,48 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_Occurrence, - x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] -such that - x_Occurrence[1], - or([q29 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q29] = 2 | q29 : int(1..4)]), - or([q31 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q31] = 3 | q31 : int(1..4)]), - sum([toInt(x_Occurrence[q1]) | q1 : int(1..4)]) <= 4, - and([q2 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q2] < x_ExplicitVarSizeWithMarker_Values[q2 + 1] - | q2 : int(1..3)]), - and([q3 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q3] = 1 | q3 : int(1..4)]), - x_ExplicitVarSizeWithMarker_Marker <= 4, - and([q6 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q6]] - | q6 : int(1..4)]), - and([x_Occurrence[q7] -> - or([q9 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q9] = q7 | q9 : int(1..4)]) - | q7 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q10 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q10] < x_ExplicitVarSizeWithFlags_Values[q10 + 1] - | q10 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q11] = false -> x_ExplicitVarSizeWithFlags_Values[q11] = 1 - | q11 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q12 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q12] | q12 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q13]) | q13 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithFlags_Flags[q16] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q16]] - | q16 : int(1..4)]), - and([x_Occurrence[q17] -> - or([x_ExplicitVarSizeWithFlags_Flags[q19] /\ x_ExplicitVarSizeWithFlags_Values[q19] = q17 | q19 : int(1..4)]) - | q17 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q21] -> - or([q23 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q23] = x_ExplicitVarSizeWithFlags_Values[q21] - | q23 : int(1..4)]) - | q21 : int(1..4)]), - and([q25 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q27] /\ - x_ExplicitVarSizeWithFlags_Values[q27] = x_ExplicitVarSizeWithMarker_Values[q25] - | q27 : int(1..4)]) - | q25 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_1_3_4_1-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_1_3_4_1-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_3_4_1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_1_3_4_1-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_1_3_4_1-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_3_4_1-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_1_3_4_1.eprime b/tests/exhaustive/basic/set06/expected/model_1_3_4_1.eprime deleted file mode 100644 index 73b9732e42..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_3_4_1.eprime +++ /dev/null @@ -1,48 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_Occurrence, - x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] -such that - x_Occurrence[1], - or([q29 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q29] = 2 | q29 : int(1..4)]), - or([x_ExplicitVarSizeWithFlags_Flags[q31] /\ x_ExplicitVarSizeWithFlags_Values[q31] = 3 | q31 : int(1..4)]), - sum([toInt(x_Occurrence[q1]) | q1 : int(1..4)]) <= 4, - and([q2 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q2] < x_ExplicitVarSizeWithMarker_Values[q2 + 1] - | q2 : int(1..3)]), - and([q3 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q3] = 1 | q3 : int(1..4)]), - x_ExplicitVarSizeWithMarker_Marker <= 4, - and([q6 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q6]] - | q6 : int(1..4)]), - and([x_Occurrence[q7] -> - or([q9 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q9] = q7 | q9 : int(1..4)]) - | q7 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q10 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q10] < x_ExplicitVarSizeWithFlags_Values[q10 + 1] - | q10 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q11] = false -> x_ExplicitVarSizeWithFlags_Values[q11] = 1 - | q11 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q12 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q12] | q12 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q13]) | q13 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithFlags_Flags[q16] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q16]] - | q16 : int(1..4)]), - and([x_Occurrence[q17] -> - or([x_ExplicitVarSizeWithFlags_Flags[q19] /\ x_ExplicitVarSizeWithFlags_Values[q19] = q17 | q19 : int(1..4)]) - | q17 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q21] -> - or([q23 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q23] = x_ExplicitVarSizeWithFlags_Values[q21] - | q23 : int(1..4)]) - | q21 : int(1..4)]), - and([q25 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q27] /\ - x_ExplicitVarSizeWithFlags_Values[q27] = x_ExplicitVarSizeWithMarker_Values[q25] - | q27 : int(1..4)]) - | q25 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_1_3_4_2-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_1_3_4_2-solution000001.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_3_4_2-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_1_3_4_2-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_1_3_4_2-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_3_4_2-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_1_3_4_2.eprime b/tests/exhaustive/basic/set06/expected/model_1_3_4_2.eprime deleted file mode 100644 index 1c2efaa35b..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_3_4_2.eprime +++ /dev/null @@ -1,77 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -branching on - [x_ExplicitVarSizeWithDummy, x_Occurrence, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, - x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] -such that - x_Occurrence[1], - or([q54 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q54] = 2 | q54 : int(1..4)]), - or([x_ExplicitVarSizeWithFlags_Flags[q56] /\ x_ExplicitVarSizeWithFlags_Values[q56] = 3 | q56 : int(1..4)]), - sum([toInt(x_Occurrence[q1]) | q1 : int(1..4)]) <= 4, - and([q2 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q2] < x_ExplicitVarSizeWithMarker_Values[q2 + 1] - | q2 : int(1..3)]), - and([q3 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q3] = 1 | q3 : int(1..4)]), - x_ExplicitVarSizeWithMarker_Marker <= 4, - and([q6 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q6]] - | q6 : int(1..4)]), - and([x_Occurrence[q7] -> - or([q9 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q9] = q7 | q9 : int(1..4)]) - | q7 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q10 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q10] < x_ExplicitVarSizeWithFlags_Values[q10 + 1] - | q10 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q11] = false -> x_ExplicitVarSizeWithFlags_Values[q11] = 1 - | q11 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q12 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q12] | q12 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q13]) | q13 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithFlags_Flags[q16] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q16]] - | q16 : int(1..4)]), - and([x_Occurrence[q17] -> - or([x_ExplicitVarSizeWithFlags_Flags[q19] /\ x_ExplicitVarSizeWithFlags_Values[q19] = q17 | q19 : int(1..4)]) - | q17 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q21] -> - or([q23 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q23] = x_ExplicitVarSizeWithFlags_Values[q21] - | q23 : int(1..4)]) - | q21 : int(1..4)]), - and([q25 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q27] /\ - x_ExplicitVarSizeWithFlags_Values[q27] = x_ExplicitVarSizeWithMarker_Values[q25] - | q27 : int(1..4)]) - | q25 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q28] < x_ExplicitVarSizeWithDummy[q28 + 1] \/ x_ExplicitVarSizeWithDummy[q28] = 5 - | q28 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q29] = 5 -> x_ExplicitVarSizeWithDummy[q29 + 1] = 5 | q29 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q30] != 5) | q30 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithDummy[q33] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q33]] | q33 : int(1..4)]), - and([x_Occurrence[q34] -> - or([x_ExplicitVarSizeWithDummy[q36] != 5 /\ x_ExplicitVarSizeWithDummy[q36] = q34 | q36 : int(1..4)]) - | q34 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q38] != 5 -> - or([q40 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q40] = x_ExplicitVarSizeWithDummy[q38] - | q40 : int(1..4)]) - | q38 : int(1..4)]), - and([q42 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q44] != 5 /\ - x_ExplicitVarSizeWithDummy[q44] = x_ExplicitVarSizeWithMarker_Values[q42] - | q44 : int(1..4)]) - | q42 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q46] != 5 -> - or([x_ExplicitVarSizeWithFlags_Flags[q48] /\ - x_ExplicitVarSizeWithFlags_Values[q48] = x_ExplicitVarSizeWithDummy[q46] - | q48 : int(1..4)]) - | q46 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q50] -> - or([x_ExplicitVarSizeWithDummy[q52] != 5 /\ - x_ExplicitVarSizeWithDummy[q52] = x_ExplicitVarSizeWithFlags_Values[q50] - | q52 : int(1..4)]) - | q50 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_1_3_4_3-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_1_3_4_3-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_3_4_3-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_1_3_4_3-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_1_3_4_3-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_3_4_3-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_1_3_4_3.eprime b/tests/exhaustive/basic/set06/expected/model_1_3_4_3.eprime deleted file mode 100644 index 73b9732e42..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_3_4_3.eprime +++ /dev/null @@ -1,48 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_Occurrence, - x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] -such that - x_Occurrence[1], - or([q29 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q29] = 2 | q29 : int(1..4)]), - or([x_ExplicitVarSizeWithFlags_Flags[q31] /\ x_ExplicitVarSizeWithFlags_Values[q31] = 3 | q31 : int(1..4)]), - sum([toInt(x_Occurrence[q1]) | q1 : int(1..4)]) <= 4, - and([q2 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q2] < x_ExplicitVarSizeWithMarker_Values[q2 + 1] - | q2 : int(1..3)]), - and([q3 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q3] = 1 | q3 : int(1..4)]), - x_ExplicitVarSizeWithMarker_Marker <= 4, - and([q6 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q6]] - | q6 : int(1..4)]), - and([x_Occurrence[q7] -> - or([q9 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q9] = q7 | q9 : int(1..4)]) - | q7 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q10 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q10] < x_ExplicitVarSizeWithFlags_Values[q10 + 1] - | q10 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q11] = false -> x_ExplicitVarSizeWithFlags_Values[q11] = 1 - | q11 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q12 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q12] | q12 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q13]) | q13 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithFlags_Flags[q16] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q16]] - | q16 : int(1..4)]), - and([x_Occurrence[q17] -> - or([x_ExplicitVarSizeWithFlags_Flags[q19] /\ x_ExplicitVarSizeWithFlags_Values[q19] = q17 | q19 : int(1..4)]) - | q17 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q21] -> - or([q23 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q23] = x_ExplicitVarSizeWithFlags_Values[q21] - | q23 : int(1..4)]) - | q21 : int(1..4)]), - and([q25 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q27] /\ - x_ExplicitVarSizeWithFlags_Values[q27] = x_ExplicitVarSizeWithMarker_Values[q25] - | q27 : int(1..4)]) - | q25 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_1_3_4_4-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_1_3_4_4-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_3_4_4-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_1_3_4_4-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_1_3_4_4-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_3_4_4-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_1_3_4_4.eprime b/tests/exhaustive/basic/set06/expected/model_1_3_4_4.eprime deleted file mode 100644 index 73b9732e42..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_3_4_4.eprime +++ /dev/null @@ -1,48 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_Occurrence, - x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] -such that - x_Occurrence[1], - or([q29 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q29] = 2 | q29 : int(1..4)]), - or([x_ExplicitVarSizeWithFlags_Flags[q31] /\ x_ExplicitVarSizeWithFlags_Values[q31] = 3 | q31 : int(1..4)]), - sum([toInt(x_Occurrence[q1]) | q1 : int(1..4)]) <= 4, - and([q2 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q2] < x_ExplicitVarSizeWithMarker_Values[q2 + 1] - | q2 : int(1..3)]), - and([q3 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q3] = 1 | q3 : int(1..4)]), - x_ExplicitVarSizeWithMarker_Marker <= 4, - and([q6 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q6]] - | q6 : int(1..4)]), - and([x_Occurrence[q7] -> - or([q9 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q9] = q7 | q9 : int(1..4)]) - | q7 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q10 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q10] < x_ExplicitVarSizeWithFlags_Values[q10 + 1] - | q10 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q11] = false -> x_ExplicitVarSizeWithFlags_Values[q11] = 1 - | q11 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q12 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q12] | q12 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q13]) | q13 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithFlags_Flags[q16] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q16]] - | q16 : int(1..4)]), - and([x_Occurrence[q17] -> - or([x_ExplicitVarSizeWithFlags_Flags[q19] /\ x_ExplicitVarSizeWithFlags_Values[q19] = q17 | q19 : int(1..4)]) - | q17 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q21] -> - or([q23 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q23] = x_ExplicitVarSizeWithFlags_Values[q21] - | q23 : int(1..4)]) - | q21 : int(1..4)]), - and([q25 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q27] /\ - x_ExplicitVarSizeWithFlags_Values[q27] = x_ExplicitVarSizeWithMarker_Values[q25] - | q27 : int(1..4)]) - | q25 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_1_4_1_1-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_1_4_1_1-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_4_1_1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_1_4_1_1-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_1_4_1_1-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_4_1_1-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_1_4_1_1.eprime b/tests/exhaustive/basic/set06/expected/model_1_4_1_1.eprime deleted file mode 100644 index d01150a180..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_4_1_1.eprime +++ /dev/null @@ -1,22 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -branching on [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_Occurrence] -such that - x_Occurrence[1], - or([x_ExplicitVarSizeWithFlags_Flags[q13] /\ x_ExplicitVarSizeWithFlags_Values[q13] = 2 | q13 : int(1..4)]), - x_Occurrence[3], - sum([toInt(x_Occurrence[q1]) | q1 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithFlags_Flags[q2 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q2] < x_ExplicitVarSizeWithFlags_Values[q2 + 1] - | q2 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3] = false -> x_ExplicitVarSizeWithFlags_Values[q3] = 1 | q3 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q4] | q4 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q5]) | q5 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithFlags_Flags[q8] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q8]] | q8 : int(1..4)]), - and([x_Occurrence[q9] -> - or([x_ExplicitVarSizeWithFlags_Flags[q11] /\ x_ExplicitVarSizeWithFlags_Values[q11] = q9 | q11 : int(1..4)]) - | q9 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_1_4_1_2-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_1_4_1_2-solution000001.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_4_1_2-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_1_4_1_2-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_1_4_1_2-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_4_1_2-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_1_4_1_2.eprime b/tests/exhaustive/basic/set06/expected/model_1_4_1_2.eprime deleted file mode 100644 index dd23a21391..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_4_1_2.eprime +++ /dev/null @@ -1,42 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -branching on - [x_ExplicitVarSizeWithDummy, x_Occurrence, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] -such that - x_Occurrence[1], - or([x_ExplicitVarSizeWithFlags_Flags[q30] /\ x_ExplicitVarSizeWithFlags_Values[q30] = 2 | q30 : int(1..4)]), - x_Occurrence[3], - sum([toInt(x_Occurrence[q1]) | q1 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithFlags_Flags[q2 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q2] < x_ExplicitVarSizeWithFlags_Values[q2 + 1] - | q2 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3] = false -> x_ExplicitVarSizeWithFlags_Values[q3] = 1 | q3 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q4] | q4 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q5]) | q5 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithFlags_Flags[q8] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q8]] | q8 : int(1..4)]), - and([x_Occurrence[q9] -> - or([x_ExplicitVarSizeWithFlags_Flags[q11] /\ x_ExplicitVarSizeWithFlags_Values[q11] = q9 | q11 : int(1..4)]) - | q9 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q12] < x_ExplicitVarSizeWithDummy[q12 + 1] \/ x_ExplicitVarSizeWithDummy[q12] = 5 - | q12 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q13] = 5 -> x_ExplicitVarSizeWithDummy[q13 + 1] = 5 | q13 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q14] != 5) | q14 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithDummy[q17] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q17]] | q17 : int(1..4)]), - and([x_Occurrence[q18] -> - or([x_ExplicitVarSizeWithDummy[q20] != 5 /\ x_ExplicitVarSizeWithDummy[q20] = q18 | q20 : int(1..4)]) - | q18 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q22] != 5 -> - or([x_ExplicitVarSizeWithFlags_Flags[q24] /\ - x_ExplicitVarSizeWithFlags_Values[q24] = x_ExplicitVarSizeWithDummy[q22] - | q24 : int(1..4)]) - | q22 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q26] -> - or([x_ExplicitVarSizeWithDummy[q28] != 5 /\ - x_ExplicitVarSizeWithDummy[q28] = x_ExplicitVarSizeWithFlags_Values[q26] - | q28 : int(1..4)]) - | q26 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_1_4_1_3-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_1_4_1_3-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_4_1_3-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_1_4_1_3-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_1_4_1_3-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_4_1_3-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_1_4_1_3.eprime b/tests/exhaustive/basic/set06/expected/model_1_4_1_3.eprime deleted file mode 100644 index a6b5c001d1..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_4_1_3.eprime +++ /dev/null @@ -1,47 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_Occurrence, - x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] -such that - x_Occurrence[1], - or([x_ExplicitVarSizeWithFlags_Flags[q29] /\ x_ExplicitVarSizeWithFlags_Values[q29] = 2 | q29 : int(1..4)]), - x_Occurrence[3], - sum([toInt(x_Occurrence[q1]) | q1 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithFlags_Flags[q2 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q2] < x_ExplicitVarSizeWithFlags_Values[q2 + 1] - | q2 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3] = false -> x_ExplicitVarSizeWithFlags_Values[q3] = 1 | q3 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q4] | q4 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q5]) | q5 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithFlags_Flags[q8] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q8]] | q8 : int(1..4)]), - and([x_Occurrence[q9] -> - or([x_ExplicitVarSizeWithFlags_Flags[q11] /\ x_ExplicitVarSizeWithFlags_Values[q11] = q9 | q11 : int(1..4)]) - | q9 : int(1..4)]), - and([q12 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q12] < x_ExplicitVarSizeWithMarker_Values[q12 + 1] - | q12 : int(1..3)]), - and([q13 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q13] = 1 | q13 : int(1..4)]), - x_ExplicitVarSizeWithMarker_Marker <= 4, - and([q16 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q16]] - | q16 : int(1..4)]), - and([x_Occurrence[q17] -> - or([q19 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q19] = q17 - | q19 : int(1..4)]) - | q17 : int(1..4)]), - and([q21 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q23] /\ - x_ExplicitVarSizeWithFlags_Values[q23] = x_ExplicitVarSizeWithMarker_Values[q21] - | q23 : int(1..4)]) - | q21 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q25] -> - or([q27 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q27] = x_ExplicitVarSizeWithFlags_Values[q25] - | q27 : int(1..4)]) - | q25 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_1_4_1_4-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_1_4_1_4-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_4_1_4-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_1_4_1_4-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_1_4_1_4-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_4_1_4-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_1_4_1_4.eprime b/tests/exhaustive/basic/set06/expected/model_1_4_1_4.eprime deleted file mode 100644 index d01150a180..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_4_1_4.eprime +++ /dev/null @@ -1,22 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -branching on [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_Occurrence] -such that - x_Occurrence[1], - or([x_ExplicitVarSizeWithFlags_Flags[q13] /\ x_ExplicitVarSizeWithFlags_Values[q13] = 2 | q13 : int(1..4)]), - x_Occurrence[3], - sum([toInt(x_Occurrence[q1]) | q1 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithFlags_Flags[q2 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q2] < x_ExplicitVarSizeWithFlags_Values[q2 + 1] - | q2 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3] = false -> x_ExplicitVarSizeWithFlags_Values[q3] = 1 | q3 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q4] | q4 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q5]) | q5 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithFlags_Flags[q8] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q8]] | q8 : int(1..4)]), - and([x_Occurrence[q9] -> - or([x_ExplicitVarSizeWithFlags_Flags[q11] /\ x_ExplicitVarSizeWithFlags_Values[q11] = q9 | q11 : int(1..4)]) - | q9 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_1_4_2_1-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_1_4_2_1-solution000001.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_4_2_1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_1_4_2_1-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_1_4_2_1-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_4_2_1-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_1_4_2_1.eprime b/tests/exhaustive/basic/set06/expected/model_1_4_2_1.eprime deleted file mode 100644 index 551631d48b..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_4_2_1.eprime +++ /dev/null @@ -1,42 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -branching on - [x_ExplicitVarSizeWithDummy, x_Occurrence, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] -such that - x_Occurrence[1], - or([x_ExplicitVarSizeWithFlags_Flags[q30] /\ x_ExplicitVarSizeWithFlags_Values[q30] = 2 | q30 : int(1..4)]), - or([x_ExplicitVarSizeWithDummy[q32] != 5 /\ x_ExplicitVarSizeWithDummy[q32] = 3 | q32 : int(1..4)]), - sum([toInt(x_Occurrence[q1]) | q1 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithFlags_Flags[q2 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q2] < x_ExplicitVarSizeWithFlags_Values[q2 + 1] - | q2 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3] = false -> x_ExplicitVarSizeWithFlags_Values[q3] = 1 | q3 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q4] | q4 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q5]) | q5 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithFlags_Flags[q8] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q8]] | q8 : int(1..4)]), - and([x_Occurrence[q9] -> - or([x_ExplicitVarSizeWithFlags_Flags[q11] /\ x_ExplicitVarSizeWithFlags_Values[q11] = q9 | q11 : int(1..4)]) - | q9 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q12] < x_ExplicitVarSizeWithDummy[q12 + 1] \/ x_ExplicitVarSizeWithDummy[q12] = 5 - | q12 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q13] = 5 -> x_ExplicitVarSizeWithDummy[q13 + 1] = 5 | q13 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q14] != 5) | q14 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithDummy[q17] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q17]] | q17 : int(1..4)]), - and([x_Occurrence[q18] -> - or([x_ExplicitVarSizeWithDummy[q20] != 5 /\ x_ExplicitVarSizeWithDummy[q20] = q18 | q20 : int(1..4)]) - | q18 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q22] != 5 -> - or([x_ExplicitVarSizeWithFlags_Flags[q24] /\ - x_ExplicitVarSizeWithFlags_Values[q24] = x_ExplicitVarSizeWithDummy[q22] - | q24 : int(1..4)]) - | q22 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q26] -> - or([x_ExplicitVarSizeWithDummy[q28] != 5 /\ - x_ExplicitVarSizeWithDummy[q28] = x_ExplicitVarSizeWithFlags_Values[q26] - | q28 : int(1..4)]) - | q26 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_1_4_2_2-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_1_4_2_2-solution000001.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_4_2_2-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_1_4_2_2-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_1_4_2_2-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_4_2_2-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_1_4_2_2.eprime b/tests/exhaustive/basic/set06/expected/model_1_4_2_2.eprime deleted file mode 100644 index 551631d48b..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_4_2_2.eprime +++ /dev/null @@ -1,42 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -branching on - [x_ExplicitVarSizeWithDummy, x_Occurrence, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] -such that - x_Occurrence[1], - or([x_ExplicitVarSizeWithFlags_Flags[q30] /\ x_ExplicitVarSizeWithFlags_Values[q30] = 2 | q30 : int(1..4)]), - or([x_ExplicitVarSizeWithDummy[q32] != 5 /\ x_ExplicitVarSizeWithDummy[q32] = 3 | q32 : int(1..4)]), - sum([toInt(x_Occurrence[q1]) | q1 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithFlags_Flags[q2 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q2] < x_ExplicitVarSizeWithFlags_Values[q2 + 1] - | q2 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3] = false -> x_ExplicitVarSizeWithFlags_Values[q3] = 1 | q3 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q4] | q4 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q5]) | q5 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithFlags_Flags[q8] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q8]] | q8 : int(1..4)]), - and([x_Occurrence[q9] -> - or([x_ExplicitVarSizeWithFlags_Flags[q11] /\ x_ExplicitVarSizeWithFlags_Values[q11] = q9 | q11 : int(1..4)]) - | q9 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q12] < x_ExplicitVarSizeWithDummy[q12 + 1] \/ x_ExplicitVarSizeWithDummy[q12] = 5 - | q12 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q13] = 5 -> x_ExplicitVarSizeWithDummy[q13 + 1] = 5 | q13 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q14] != 5) | q14 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithDummy[q17] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q17]] | q17 : int(1..4)]), - and([x_Occurrence[q18] -> - or([x_ExplicitVarSizeWithDummy[q20] != 5 /\ x_ExplicitVarSizeWithDummy[q20] = q18 | q20 : int(1..4)]) - | q18 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q22] != 5 -> - or([x_ExplicitVarSizeWithFlags_Flags[q24] /\ - x_ExplicitVarSizeWithFlags_Values[q24] = x_ExplicitVarSizeWithDummy[q22] - | q24 : int(1..4)]) - | q22 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q26] -> - or([x_ExplicitVarSizeWithDummy[q28] != 5 /\ - x_ExplicitVarSizeWithDummy[q28] = x_ExplicitVarSizeWithFlags_Values[q26] - | q28 : int(1..4)]) - | q26 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_1_4_2_3-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_1_4_2_3-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_4_2_3-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_1_4_2_3-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_1_4_2_3-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_4_2_3-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_1_4_2_3.eprime b/tests/exhaustive/basic/set06/expected/model_1_4_2_3.eprime deleted file mode 100644 index 380d82c5c6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_4_2_3.eprime +++ /dev/null @@ -1,76 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_Occurrence, - x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy] -such that - x_Occurrence[1], - or([x_ExplicitVarSizeWithFlags_Flags[q54] /\ x_ExplicitVarSizeWithFlags_Values[q54] = 2 | q54 : int(1..4)]), - or([x_ExplicitVarSizeWithDummy[q56] != 5 /\ x_ExplicitVarSizeWithDummy[q56] = 3 | q56 : int(1..4)]), - sum([toInt(x_Occurrence[q1]) | q1 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithFlags_Flags[q2 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q2] < x_ExplicitVarSizeWithFlags_Values[q2 + 1] - | q2 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3] = false -> x_ExplicitVarSizeWithFlags_Values[q3] = 1 | q3 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q4] | q4 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q5]) | q5 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithFlags_Flags[q8] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q8]] | q8 : int(1..4)]), - and([x_Occurrence[q9] -> - or([x_ExplicitVarSizeWithFlags_Flags[q11] /\ x_ExplicitVarSizeWithFlags_Values[q11] = q9 | q11 : int(1..4)]) - | q9 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q12] < x_ExplicitVarSizeWithDummy[q12 + 1] \/ x_ExplicitVarSizeWithDummy[q12] = 5 - | q12 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q13] = 5 -> x_ExplicitVarSizeWithDummy[q13 + 1] = 5 | q13 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q14] != 5) | q14 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithDummy[q17] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q17]] | q17 : int(1..4)]), - and([x_Occurrence[q18] -> - or([x_ExplicitVarSizeWithDummy[q20] != 5 /\ x_ExplicitVarSizeWithDummy[q20] = q18 | q20 : int(1..4)]) - | q18 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q22] != 5 -> - or([x_ExplicitVarSizeWithFlags_Flags[q24] /\ - x_ExplicitVarSizeWithFlags_Values[q24] = x_ExplicitVarSizeWithDummy[q22] - | q24 : int(1..4)]) - | q22 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q26] -> - or([x_ExplicitVarSizeWithDummy[q28] != 5 /\ - x_ExplicitVarSizeWithDummy[q28] = x_ExplicitVarSizeWithFlags_Values[q26] - | q28 : int(1..4)]) - | q26 : int(1..4)]), - and([q29 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q29] < x_ExplicitVarSizeWithMarker_Values[q29 + 1] - | q29 : int(1..3)]), - and([q30 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q30] = 1 | q30 : int(1..4)]), - x_ExplicitVarSizeWithMarker_Marker <= 4, - and([q33 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q33]] - | q33 : int(1..4)]), - and([x_Occurrence[q34] -> - or([q36 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q36] = q34 - | q36 : int(1..4)]) - | q34 : int(1..4)]), - and([q38 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q40] /\ - x_ExplicitVarSizeWithFlags_Values[q40] = x_ExplicitVarSizeWithMarker_Values[q38] - | q40 : int(1..4)]) - | q38 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q42] -> - or([q44 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q44] = x_ExplicitVarSizeWithFlags_Values[q42] - | q44 : int(1..4)]) - | q42 : int(1..4)]), - and([q46 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q48] != 5 /\ - x_ExplicitVarSizeWithDummy[q48] = x_ExplicitVarSizeWithMarker_Values[q46] - | q48 : int(1..4)]) - | q46 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q50] != 5 -> - or([q52 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q52] = x_ExplicitVarSizeWithDummy[q50] - | q52 : int(1..4)]) - | q50 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_1_4_2_4-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_1_4_2_4-solution000001.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_4_2_4-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_1_4_2_4-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_1_4_2_4-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_4_2_4-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_1_4_2_4.eprime b/tests/exhaustive/basic/set06/expected/model_1_4_2_4.eprime deleted file mode 100644 index 551631d48b..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_4_2_4.eprime +++ /dev/null @@ -1,42 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -branching on - [x_ExplicitVarSizeWithDummy, x_Occurrence, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] -such that - x_Occurrence[1], - or([x_ExplicitVarSizeWithFlags_Flags[q30] /\ x_ExplicitVarSizeWithFlags_Values[q30] = 2 | q30 : int(1..4)]), - or([x_ExplicitVarSizeWithDummy[q32] != 5 /\ x_ExplicitVarSizeWithDummy[q32] = 3 | q32 : int(1..4)]), - sum([toInt(x_Occurrence[q1]) | q1 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithFlags_Flags[q2 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q2] < x_ExplicitVarSizeWithFlags_Values[q2 + 1] - | q2 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3] = false -> x_ExplicitVarSizeWithFlags_Values[q3] = 1 | q3 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q4] | q4 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q5]) | q5 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithFlags_Flags[q8] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q8]] | q8 : int(1..4)]), - and([x_Occurrence[q9] -> - or([x_ExplicitVarSizeWithFlags_Flags[q11] /\ x_ExplicitVarSizeWithFlags_Values[q11] = q9 | q11 : int(1..4)]) - | q9 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q12] < x_ExplicitVarSizeWithDummy[q12 + 1] \/ x_ExplicitVarSizeWithDummy[q12] = 5 - | q12 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q13] = 5 -> x_ExplicitVarSizeWithDummy[q13 + 1] = 5 | q13 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q14] != 5) | q14 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithDummy[q17] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q17]] | q17 : int(1..4)]), - and([x_Occurrence[q18] -> - or([x_ExplicitVarSizeWithDummy[q20] != 5 /\ x_ExplicitVarSizeWithDummy[q20] = q18 | q20 : int(1..4)]) - | q18 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q22] != 5 -> - or([x_ExplicitVarSizeWithFlags_Flags[q24] /\ - x_ExplicitVarSizeWithFlags_Values[q24] = x_ExplicitVarSizeWithDummy[q22] - | q24 : int(1..4)]) - | q22 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q26] -> - or([x_ExplicitVarSizeWithDummy[q28] != 5 /\ - x_ExplicitVarSizeWithDummy[q28] = x_ExplicitVarSizeWithFlags_Values[q26] - | q28 : int(1..4)]) - | q26 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_1_4_3_1-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_1_4_3_1-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_4_3_1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_1_4_3_1-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_1_4_3_1-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_4_3_1-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_1_4_3_1.eprime b/tests/exhaustive/basic/set06/expected/model_1_4_3_1.eprime deleted file mode 100644 index f88dbdf42f..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_4_3_1.eprime +++ /dev/null @@ -1,47 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_Occurrence, - x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] -such that - x_Occurrence[1], - or([x_ExplicitVarSizeWithFlags_Flags[q29] /\ x_ExplicitVarSizeWithFlags_Values[q29] = 2 | q29 : int(1..4)]), - or([q31 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q31] = 3 | q31 : int(1..4)]), - sum([toInt(x_Occurrence[q1]) | q1 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithFlags_Flags[q2 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q2] < x_ExplicitVarSizeWithFlags_Values[q2 + 1] - | q2 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3] = false -> x_ExplicitVarSizeWithFlags_Values[q3] = 1 | q3 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q4] | q4 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q5]) | q5 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithFlags_Flags[q8] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q8]] | q8 : int(1..4)]), - and([x_Occurrence[q9] -> - or([x_ExplicitVarSizeWithFlags_Flags[q11] /\ x_ExplicitVarSizeWithFlags_Values[q11] = q9 | q11 : int(1..4)]) - | q9 : int(1..4)]), - and([q12 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q12] < x_ExplicitVarSizeWithMarker_Values[q12 + 1] - | q12 : int(1..3)]), - and([q13 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q13] = 1 | q13 : int(1..4)]), - x_ExplicitVarSizeWithMarker_Marker <= 4, - and([q16 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q16]] - | q16 : int(1..4)]), - and([x_Occurrence[q17] -> - or([q19 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q19] = q17 - | q19 : int(1..4)]) - | q17 : int(1..4)]), - and([q21 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q23] /\ - x_ExplicitVarSizeWithFlags_Values[q23] = x_ExplicitVarSizeWithMarker_Values[q21] - | q23 : int(1..4)]) - | q21 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q25] -> - or([q27 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q27] = x_ExplicitVarSizeWithFlags_Values[q25] - | q27 : int(1..4)]) - | q25 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_1_4_3_2-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_1_4_3_2-solution000001.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_4_3_2-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_1_4_3_2-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_1_4_3_2-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_4_3_2-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_1_4_3_2.eprime b/tests/exhaustive/basic/set06/expected/model_1_4_3_2.eprime deleted file mode 100644 index 708901a3dd..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_4_3_2.eprime +++ /dev/null @@ -1,76 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -branching on - [x_ExplicitVarSizeWithDummy, x_Occurrence, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, - x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] -such that - x_Occurrence[1], - or([x_ExplicitVarSizeWithFlags_Flags[q54] /\ x_ExplicitVarSizeWithFlags_Values[q54] = 2 | q54 : int(1..4)]), - or([q56 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q56] = 3 | q56 : int(1..4)]), - sum([toInt(x_Occurrence[q1]) | q1 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithFlags_Flags[q2 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q2] < x_ExplicitVarSizeWithFlags_Values[q2 + 1] - | q2 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3] = false -> x_ExplicitVarSizeWithFlags_Values[q3] = 1 | q3 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q4] | q4 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q5]) | q5 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithFlags_Flags[q8] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q8]] | q8 : int(1..4)]), - and([x_Occurrence[q9] -> - or([x_ExplicitVarSizeWithFlags_Flags[q11] /\ x_ExplicitVarSizeWithFlags_Values[q11] = q9 | q11 : int(1..4)]) - | q9 : int(1..4)]), - and([q12 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q12] < x_ExplicitVarSizeWithMarker_Values[q12 + 1] - | q12 : int(1..3)]), - and([q13 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q13] = 1 | q13 : int(1..4)]), - x_ExplicitVarSizeWithMarker_Marker <= 4, - and([q16 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q16]] - | q16 : int(1..4)]), - and([x_Occurrence[q17] -> - or([q19 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q19] = q17 - | q19 : int(1..4)]) - | q17 : int(1..4)]), - and([q21 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q23] /\ - x_ExplicitVarSizeWithFlags_Values[q23] = x_ExplicitVarSizeWithMarker_Values[q21] - | q23 : int(1..4)]) - | q21 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q25] -> - or([q27 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q27] = x_ExplicitVarSizeWithFlags_Values[q25] - | q27 : int(1..4)]) - | q25 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q28] < x_ExplicitVarSizeWithDummy[q28 + 1] \/ x_ExplicitVarSizeWithDummy[q28] = 5 - | q28 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q29] = 5 -> x_ExplicitVarSizeWithDummy[q29 + 1] = 5 | q29 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q30] != 5) | q30 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithDummy[q33] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q33]] | q33 : int(1..4)]), - and([x_Occurrence[q34] -> - or([x_ExplicitVarSizeWithDummy[q36] != 5 /\ x_ExplicitVarSizeWithDummy[q36] = q34 | q36 : int(1..4)]) - | q34 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q38] != 5 -> - or([x_ExplicitVarSizeWithFlags_Flags[q40] /\ - x_ExplicitVarSizeWithFlags_Values[q40] = x_ExplicitVarSizeWithDummy[q38] - | q40 : int(1..4)]) - | q38 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q42] -> - or([x_ExplicitVarSizeWithDummy[q44] != 5 /\ - x_ExplicitVarSizeWithDummy[q44] = x_ExplicitVarSizeWithFlags_Values[q42] - | q44 : int(1..4)]) - | q42 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q46] != 5 -> - or([q48 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q48] = x_ExplicitVarSizeWithDummy[q46] - | q48 : int(1..4)]) - | q46 : int(1..4)]), - and([q50 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q52] != 5 /\ - x_ExplicitVarSizeWithDummy[q52] = x_ExplicitVarSizeWithMarker_Values[q50] - | q52 : int(1..4)]) - | q50 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_1_4_3_3-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_1_4_3_3-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_4_3_3-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_1_4_3_3-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_1_4_3_3-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_4_3_3-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_1_4_3_3.eprime b/tests/exhaustive/basic/set06/expected/model_1_4_3_3.eprime deleted file mode 100644 index f88dbdf42f..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_4_3_3.eprime +++ /dev/null @@ -1,47 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_Occurrence, - x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] -such that - x_Occurrence[1], - or([x_ExplicitVarSizeWithFlags_Flags[q29] /\ x_ExplicitVarSizeWithFlags_Values[q29] = 2 | q29 : int(1..4)]), - or([q31 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q31] = 3 | q31 : int(1..4)]), - sum([toInt(x_Occurrence[q1]) | q1 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithFlags_Flags[q2 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q2] < x_ExplicitVarSizeWithFlags_Values[q2 + 1] - | q2 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3] = false -> x_ExplicitVarSizeWithFlags_Values[q3] = 1 | q3 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q4] | q4 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q5]) | q5 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithFlags_Flags[q8] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q8]] | q8 : int(1..4)]), - and([x_Occurrence[q9] -> - or([x_ExplicitVarSizeWithFlags_Flags[q11] /\ x_ExplicitVarSizeWithFlags_Values[q11] = q9 | q11 : int(1..4)]) - | q9 : int(1..4)]), - and([q12 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q12] < x_ExplicitVarSizeWithMarker_Values[q12 + 1] - | q12 : int(1..3)]), - and([q13 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q13] = 1 | q13 : int(1..4)]), - x_ExplicitVarSizeWithMarker_Marker <= 4, - and([q16 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q16]] - | q16 : int(1..4)]), - and([x_Occurrence[q17] -> - or([q19 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q19] = q17 - | q19 : int(1..4)]) - | q17 : int(1..4)]), - and([q21 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q23] /\ - x_ExplicitVarSizeWithFlags_Values[q23] = x_ExplicitVarSizeWithMarker_Values[q21] - | q23 : int(1..4)]) - | q21 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q25] -> - or([q27 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q27] = x_ExplicitVarSizeWithFlags_Values[q25] - | q27 : int(1..4)]) - | q25 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_1_4_3_4-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_1_4_3_4-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_4_3_4-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_1_4_3_4-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_1_4_3_4-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_4_3_4-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_1_4_3_4.eprime b/tests/exhaustive/basic/set06/expected/model_1_4_3_4.eprime deleted file mode 100644 index f88dbdf42f..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_4_3_4.eprime +++ /dev/null @@ -1,47 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_Occurrence, - x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] -such that - x_Occurrence[1], - or([x_ExplicitVarSizeWithFlags_Flags[q29] /\ x_ExplicitVarSizeWithFlags_Values[q29] = 2 | q29 : int(1..4)]), - or([q31 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q31] = 3 | q31 : int(1..4)]), - sum([toInt(x_Occurrence[q1]) | q1 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithFlags_Flags[q2 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q2] < x_ExplicitVarSizeWithFlags_Values[q2 + 1] - | q2 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3] = false -> x_ExplicitVarSizeWithFlags_Values[q3] = 1 | q3 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q4] | q4 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q5]) | q5 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithFlags_Flags[q8] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q8]] | q8 : int(1..4)]), - and([x_Occurrence[q9] -> - or([x_ExplicitVarSizeWithFlags_Flags[q11] /\ x_ExplicitVarSizeWithFlags_Values[q11] = q9 | q11 : int(1..4)]) - | q9 : int(1..4)]), - and([q12 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q12] < x_ExplicitVarSizeWithMarker_Values[q12 + 1] - | q12 : int(1..3)]), - and([q13 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q13] = 1 | q13 : int(1..4)]), - x_ExplicitVarSizeWithMarker_Marker <= 4, - and([q16 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q16]] - | q16 : int(1..4)]), - and([x_Occurrence[q17] -> - or([q19 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q19] = q17 - | q19 : int(1..4)]) - | q17 : int(1..4)]), - and([q21 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q23] /\ - x_ExplicitVarSizeWithFlags_Values[q23] = x_ExplicitVarSizeWithMarker_Values[q21] - | q23 : int(1..4)]) - | q21 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q25] -> - or([q27 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q27] = x_ExplicitVarSizeWithFlags_Values[q25] - | q27 : int(1..4)]) - | q25 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_1_4_4_1-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_1_4_4_1-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_4_4_1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_1_4_4_1-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_1_4_4_1-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_4_4_1-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_1_4_4_1.eprime b/tests/exhaustive/basic/set06/expected/model_1_4_4_1.eprime deleted file mode 100644 index 3ed6afb03d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_4_4_1.eprime +++ /dev/null @@ -1,22 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -branching on [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_Occurrence] -such that - x_Occurrence[1], - or([x_ExplicitVarSizeWithFlags_Flags[q13] /\ x_ExplicitVarSizeWithFlags_Values[q13] = 2 | q13 : int(1..4)]), - or([x_ExplicitVarSizeWithFlags_Flags[q15] /\ x_ExplicitVarSizeWithFlags_Values[q15] = 3 | q15 : int(1..4)]), - sum([toInt(x_Occurrence[q1]) | q1 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithFlags_Flags[q2 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q2] < x_ExplicitVarSizeWithFlags_Values[q2 + 1] - | q2 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3] = false -> x_ExplicitVarSizeWithFlags_Values[q3] = 1 | q3 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q4] | q4 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q5]) | q5 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithFlags_Flags[q8] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q8]] | q8 : int(1..4)]), - and([x_Occurrence[q9] -> - or([x_ExplicitVarSizeWithFlags_Flags[q11] /\ x_ExplicitVarSizeWithFlags_Values[q11] = q9 | q11 : int(1..4)]) - | q9 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_1_4_4_2-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_1_4_4_2-solution000001.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_4_4_2-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_1_4_4_2-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_1_4_4_2-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_4_4_2-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_1_4_4_2.eprime b/tests/exhaustive/basic/set06/expected/model_1_4_4_2.eprime deleted file mode 100644 index a5be74d4e9..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_4_4_2.eprime +++ /dev/null @@ -1,42 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -branching on - [x_ExplicitVarSizeWithDummy, x_Occurrence, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] -such that - x_Occurrence[1], - or([x_ExplicitVarSizeWithFlags_Flags[q30] /\ x_ExplicitVarSizeWithFlags_Values[q30] = 2 | q30 : int(1..4)]), - or([x_ExplicitVarSizeWithFlags_Flags[q32] /\ x_ExplicitVarSizeWithFlags_Values[q32] = 3 | q32 : int(1..4)]), - sum([toInt(x_Occurrence[q1]) | q1 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithFlags_Flags[q2 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q2] < x_ExplicitVarSizeWithFlags_Values[q2 + 1] - | q2 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3] = false -> x_ExplicitVarSizeWithFlags_Values[q3] = 1 | q3 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q4] | q4 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q5]) | q5 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithFlags_Flags[q8] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q8]] | q8 : int(1..4)]), - and([x_Occurrence[q9] -> - or([x_ExplicitVarSizeWithFlags_Flags[q11] /\ x_ExplicitVarSizeWithFlags_Values[q11] = q9 | q11 : int(1..4)]) - | q9 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q12] < x_ExplicitVarSizeWithDummy[q12 + 1] \/ x_ExplicitVarSizeWithDummy[q12] = 5 - | q12 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q13] = 5 -> x_ExplicitVarSizeWithDummy[q13 + 1] = 5 | q13 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q14] != 5) | q14 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithDummy[q17] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q17]] | q17 : int(1..4)]), - and([x_Occurrence[q18] -> - or([x_ExplicitVarSizeWithDummy[q20] != 5 /\ x_ExplicitVarSizeWithDummy[q20] = q18 | q20 : int(1..4)]) - | q18 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q22] != 5 -> - or([x_ExplicitVarSizeWithFlags_Flags[q24] /\ - x_ExplicitVarSizeWithFlags_Values[q24] = x_ExplicitVarSizeWithDummy[q22] - | q24 : int(1..4)]) - | q22 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q26] -> - or([x_ExplicitVarSizeWithDummy[q28] != 5 /\ - x_ExplicitVarSizeWithDummy[q28] = x_ExplicitVarSizeWithFlags_Values[q26] - | q28 : int(1..4)]) - | q26 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_1_4_4_3-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_1_4_4_3-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_4_4_3-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_1_4_4_3-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_1_4_4_3-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_4_4_3-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_1_4_4_3.eprime b/tests/exhaustive/basic/set06/expected/model_1_4_4_3.eprime deleted file mode 100644 index 8cdcc8bdaa..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_4_4_3.eprime +++ /dev/null @@ -1,47 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_Occurrence, - x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] -such that - x_Occurrence[1], - or([x_ExplicitVarSizeWithFlags_Flags[q29] /\ x_ExplicitVarSizeWithFlags_Values[q29] = 2 | q29 : int(1..4)]), - or([x_ExplicitVarSizeWithFlags_Flags[q31] /\ x_ExplicitVarSizeWithFlags_Values[q31] = 3 | q31 : int(1..4)]), - sum([toInt(x_Occurrence[q1]) | q1 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithFlags_Flags[q2 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q2] < x_ExplicitVarSizeWithFlags_Values[q2 + 1] - | q2 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3] = false -> x_ExplicitVarSizeWithFlags_Values[q3] = 1 | q3 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q4] | q4 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q5]) | q5 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithFlags_Flags[q8] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q8]] | q8 : int(1..4)]), - and([x_Occurrence[q9] -> - or([x_ExplicitVarSizeWithFlags_Flags[q11] /\ x_ExplicitVarSizeWithFlags_Values[q11] = q9 | q11 : int(1..4)]) - | q9 : int(1..4)]), - and([q12 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q12] < x_ExplicitVarSizeWithMarker_Values[q12 + 1] - | q12 : int(1..3)]), - and([q13 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q13] = 1 | q13 : int(1..4)]), - x_ExplicitVarSizeWithMarker_Marker <= 4, - and([q16 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q16]] - | q16 : int(1..4)]), - and([x_Occurrence[q17] -> - or([q19 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q19] = q17 - | q19 : int(1..4)]) - | q17 : int(1..4)]), - and([q21 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q23] /\ - x_ExplicitVarSizeWithFlags_Values[q23] = x_ExplicitVarSizeWithMarker_Values[q21] - | q23 : int(1..4)]) - | q21 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q25] -> - or([q27 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q27] = x_ExplicitVarSizeWithFlags_Values[q25] - | q27 : int(1..4)]) - | q25 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_1_4_4_4-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_1_4_4_4-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_4_4_4-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_1_4_4_4-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_1_4_4_4-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_4_4_4-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_1_4_4_4.eprime b/tests/exhaustive/basic/set06/expected/model_1_4_4_4.eprime deleted file mode 100644 index 3ed6afb03d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_1_4_4_4.eprime +++ /dev/null @@ -1,22 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -branching on [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_Occurrence] -such that - x_Occurrence[1], - or([x_ExplicitVarSizeWithFlags_Flags[q13] /\ x_ExplicitVarSizeWithFlags_Values[q13] = 2 | q13 : int(1..4)]), - or([x_ExplicitVarSizeWithFlags_Flags[q15] /\ x_ExplicitVarSizeWithFlags_Values[q15] = 3 | q15 : int(1..4)]), - sum([toInt(x_Occurrence[q1]) | q1 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithFlags_Flags[q2 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q2] < x_ExplicitVarSizeWithFlags_Values[q2 + 1] - | q2 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3] = false -> x_ExplicitVarSizeWithFlags_Values[q3] = 1 | q3 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q4] | q4 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q5]) | q5 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithFlags_Flags[q8] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q8]] | q8 : int(1..4)]), - and([x_Occurrence[q9] -> - or([x_ExplicitVarSizeWithFlags_Flags[q11] /\ x_ExplicitVarSizeWithFlags_Values[q11] = q9 | q11 : int(1..4)]) - | q9 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_2_1_1_1-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_2_1_1_1-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_1_1_1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_2_1_1_1-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_2_1_1_1-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_1_1_1-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_2_1_1_1.eprime b/tests/exhaustive/basic/set06/expected/model_2_1_1_1.eprime deleted file mode 100644 index 1f68a56e57..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_1_1_1.eprime +++ /dev/null @@ -1,19 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -find x_Occurrence: matrix indexed by [int(1..4)] of bool -branching on [x_Occurrence, x_ExplicitVarSizeWithDummy] -such that - or([x_ExplicitVarSizeWithDummy[q12] != 5 /\ x_ExplicitVarSizeWithDummy[q12] = 1 | q12 : int(1..4)]), - x_Occurrence[2], - x_Occurrence[3], - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 5 - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q2] = 5 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 5) | q3 : int(1..4)]) <= 4, - sum([toInt(x_Occurrence[q5]) | q5 : int(1..4)]) <= 4, - and([x_Occurrence[q6] -> - or([x_ExplicitVarSizeWithDummy[q8] != 5 /\ x_ExplicitVarSizeWithDummy[q8] = q6 | q8 : int(1..4)]) - | q6 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q10] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q10]] | q10 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_2_1_1_2-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_2_1_1_2-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_1_1_2-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_2_1_1_2-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_2_1_1_2-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_1_1_2-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_2_1_1_2.eprime b/tests/exhaustive/basic/set06/expected/model_2_1_1_2.eprime deleted file mode 100644 index 1f68a56e57..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_1_1_2.eprime +++ /dev/null @@ -1,19 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -find x_Occurrence: matrix indexed by [int(1..4)] of bool -branching on [x_Occurrence, x_ExplicitVarSizeWithDummy] -such that - or([x_ExplicitVarSizeWithDummy[q12] != 5 /\ x_ExplicitVarSizeWithDummy[q12] = 1 | q12 : int(1..4)]), - x_Occurrence[2], - x_Occurrence[3], - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 5 - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q2] = 5 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 5) | q3 : int(1..4)]) <= 4, - sum([toInt(x_Occurrence[q5]) | q5 : int(1..4)]) <= 4, - and([x_Occurrence[q6] -> - or([x_ExplicitVarSizeWithDummy[q8] != 5 /\ x_ExplicitVarSizeWithDummy[q8] = q6 | q8 : int(1..4)]) - | q6 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q10] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q10]] | q10 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_2_1_1_3-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_2_1_1_3-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_1_1_3-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_2_1_1_3-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_2_1_1_3-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_1_1_3-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_2_1_1_3.eprime b/tests/exhaustive/basic/set06/expected/model_2_1_1_3.eprime deleted file mode 100644 index 7a02ca5f86..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_1_1_3.eprime +++ /dev/null @@ -1,43 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -find x_Occurrence: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy, x_Occurrence] -such that - or([x_ExplicitVarSizeWithDummy[q28] != 5 /\ x_ExplicitVarSizeWithDummy[q28] = 1 | q28 : int(1..4)]), - x_Occurrence[2], - x_Occurrence[3], - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 5 - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q2] = 5 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 5) | q3 : int(1..4)]) <= 4, - sum([toInt(x_Occurrence[q5]) | q5 : int(1..4)]) <= 4, - and([x_Occurrence[q22] -> - or([x_ExplicitVarSizeWithDummy[q24] != 5 /\ x_ExplicitVarSizeWithDummy[q24] = q22 | q24 : int(1..4)]) - | q22 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q26] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q26]] | q26 : int(1..4)]), - and([q6 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q6] < x_ExplicitVarSizeWithMarker_Values[q6 + 1] - | q6 : int(1..3)]), - and([q7 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q7] = 1 | q7 : int(1..4)]), - x_ExplicitVarSizeWithMarker_Marker <= 4, - and([q10 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q12] != 5 /\ - x_ExplicitVarSizeWithDummy[q12] = x_ExplicitVarSizeWithMarker_Values[q10] - | q12 : int(1..4)]) - | q10 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q14] != 5 -> - or([q16 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q16] = x_ExplicitVarSizeWithDummy[q14] - | q16 : int(1..4)]) - | q14 : int(1..4)]), - and([q18 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q18]] - | q18 : int(1..4)]), - and([x_Occurrence[q19] -> - or([q21 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q21] = q19 - | q21 : int(1..4)]) - | q19 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_2_1_1_4-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_2_1_1_4-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_1_1_4-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_2_1_1_4-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_2_1_1_4-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_1_1_4-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_2_1_1_4.eprime b/tests/exhaustive/basic/set06/expected/model_2_1_1_4.eprime deleted file mode 100644 index e966231466..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_1_1_4.eprime +++ /dev/null @@ -1,43 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -find x_Occurrence: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy, x_Occurrence] -such that - or([x_ExplicitVarSizeWithDummy[q30] != 5 /\ x_ExplicitVarSizeWithDummy[q30] = 1 | q30 : int(1..4)]), - x_Occurrence[2], - x_Occurrence[3], - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 5 - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q2] = 5 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 5) | q3 : int(1..4)]) <= 4, - sum([toInt(x_Occurrence[q5]) | q5 : int(1..4)]) <= 4, - and([x_Occurrence[q24] -> - or([x_ExplicitVarSizeWithDummy[q26] != 5 /\ x_ExplicitVarSizeWithDummy[q26] = q24 | q26 : int(1..4)]) - | q24 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q28] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q28]] | q28 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q6] < x_ExplicitVarSizeWithFlags_Values[q6 + 1] - | q6 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q7] = false -> x_ExplicitVarSizeWithFlags_Values[q7] = 1 | q7 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q8 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q8] | q8 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q9]) | q9 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithFlags_Flags[q12] -> - or([x_ExplicitVarSizeWithDummy[q14] != 5 /\ - x_ExplicitVarSizeWithDummy[q14] = x_ExplicitVarSizeWithFlags_Values[q12] - | q14 : int(1..4)]) - | q12 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q16] != 5 -> - or([x_ExplicitVarSizeWithFlags_Flags[q18] /\ - x_ExplicitVarSizeWithFlags_Values[q18] = x_ExplicitVarSizeWithDummy[q16] - | q18 : int(1..4)]) - | q16 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q20] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q20]] - | q20 : int(1..4)]), - and([x_Occurrence[q21] -> - or([x_ExplicitVarSizeWithFlags_Flags[q23] /\ x_ExplicitVarSizeWithFlags_Values[q23] = q21 | q23 : int(1..4)]) - | q21 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_2_1_2_1-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_2_1_2_1-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_1_2_1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_2_1_2_1-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_2_1_2_1-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_1_2_1-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_2_1_2_1.eprime b/tests/exhaustive/basic/set06/expected/model_2_1_2_1.eprime deleted file mode 100644 index 9cfdfdc9c0..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_1_2_1.eprime +++ /dev/null @@ -1,19 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -find x_Occurrence: matrix indexed by [int(1..4)] of bool -branching on [x_Occurrence, x_ExplicitVarSizeWithDummy] -such that - or([x_ExplicitVarSizeWithDummy[q14] != 5 /\ x_ExplicitVarSizeWithDummy[q14] = 1 | q14 : int(1..4)]), - x_Occurrence[2], - or([x_ExplicitVarSizeWithDummy[q12] != 5 /\ x_ExplicitVarSizeWithDummy[q12] = 3 | q12 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 5 - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q2] = 5 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 5) | q3 : int(1..4)]) <= 4, - sum([toInt(x_Occurrence[q5]) | q5 : int(1..4)]) <= 4, - and([x_Occurrence[q6] -> - or([x_ExplicitVarSizeWithDummy[q8] != 5 /\ x_ExplicitVarSizeWithDummy[q8] = q6 | q8 : int(1..4)]) - | q6 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q10] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q10]] | q10 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_2_1_2_2-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_2_1_2_2-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_1_2_2-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_2_1_2_2-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_2_1_2_2-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_1_2_2-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_2_1_2_2.eprime b/tests/exhaustive/basic/set06/expected/model_2_1_2_2.eprime deleted file mode 100644 index 9cfdfdc9c0..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_1_2_2.eprime +++ /dev/null @@ -1,19 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -find x_Occurrence: matrix indexed by [int(1..4)] of bool -branching on [x_Occurrence, x_ExplicitVarSizeWithDummy] -such that - or([x_ExplicitVarSizeWithDummy[q14] != 5 /\ x_ExplicitVarSizeWithDummy[q14] = 1 | q14 : int(1..4)]), - x_Occurrence[2], - or([x_ExplicitVarSizeWithDummy[q12] != 5 /\ x_ExplicitVarSizeWithDummy[q12] = 3 | q12 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 5 - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q2] = 5 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 5) | q3 : int(1..4)]) <= 4, - sum([toInt(x_Occurrence[q5]) | q5 : int(1..4)]) <= 4, - and([x_Occurrence[q6] -> - or([x_ExplicitVarSizeWithDummy[q8] != 5 /\ x_ExplicitVarSizeWithDummy[q8] = q6 | q8 : int(1..4)]) - | q6 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q10] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q10]] | q10 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_2_1_2_3-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_2_1_2_3-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_1_2_3-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_2_1_2_3-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_2_1_2_3-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_1_2_3-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_2_1_2_3.eprime b/tests/exhaustive/basic/set06/expected/model_2_1_2_3.eprime deleted file mode 100644 index 2fe1df7714..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_1_2_3.eprime +++ /dev/null @@ -1,43 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -find x_Occurrence: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy, x_Occurrence] -such that - or([x_ExplicitVarSizeWithDummy[q30] != 5 /\ x_ExplicitVarSizeWithDummy[q30] = 1 | q30 : int(1..4)]), - x_Occurrence[2], - or([x_ExplicitVarSizeWithDummy[q28] != 5 /\ x_ExplicitVarSizeWithDummy[q28] = 3 | q28 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 5 - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q2] = 5 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 5) | q3 : int(1..4)]) <= 4, - sum([toInt(x_Occurrence[q5]) | q5 : int(1..4)]) <= 4, - and([x_Occurrence[q22] -> - or([x_ExplicitVarSizeWithDummy[q24] != 5 /\ x_ExplicitVarSizeWithDummy[q24] = q22 | q24 : int(1..4)]) - | q22 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q26] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q26]] | q26 : int(1..4)]), - and([q6 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q6] < x_ExplicitVarSizeWithMarker_Values[q6 + 1] - | q6 : int(1..3)]), - and([q7 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q7] = 1 | q7 : int(1..4)]), - x_ExplicitVarSizeWithMarker_Marker <= 4, - and([q10 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q12] != 5 /\ - x_ExplicitVarSizeWithDummy[q12] = x_ExplicitVarSizeWithMarker_Values[q10] - | q12 : int(1..4)]) - | q10 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q14] != 5 -> - or([q16 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q16] = x_ExplicitVarSizeWithDummy[q14] - | q16 : int(1..4)]) - | q14 : int(1..4)]), - and([q18 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q18]] - | q18 : int(1..4)]), - and([x_Occurrence[q19] -> - or([q21 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q21] = q19 - | q21 : int(1..4)]) - | q19 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_2_1_2_4-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_2_1_2_4-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_1_2_4-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_2_1_2_4-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_2_1_2_4-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_1_2_4-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_2_1_2_4.eprime b/tests/exhaustive/basic/set06/expected/model_2_1_2_4.eprime deleted file mode 100644 index 36aec49af7..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_1_2_4.eprime +++ /dev/null @@ -1,43 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -find x_Occurrence: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy, x_Occurrence] -such that - or([x_ExplicitVarSizeWithDummy[q32] != 5 /\ x_ExplicitVarSizeWithDummy[q32] = 1 | q32 : int(1..4)]), - x_Occurrence[2], - or([x_ExplicitVarSizeWithDummy[q25] != 5 /\ x_ExplicitVarSizeWithDummy[q25] = 3 | q25 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 5 - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q2] = 5 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 5) | q3 : int(1..4)]) <= 4, - sum([toInt(x_Occurrence[q5]) | q5 : int(1..4)]) <= 4, - and([x_Occurrence[q26] -> - or([x_ExplicitVarSizeWithDummy[q28] != 5 /\ x_ExplicitVarSizeWithDummy[q28] = q26 | q28 : int(1..4)]) - | q26 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q30] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q30]] | q30 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q6] < x_ExplicitVarSizeWithFlags_Values[q6 + 1] - | q6 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q7] = false -> x_ExplicitVarSizeWithFlags_Values[q7] = 1 | q7 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q8 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q8] | q8 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q9]) | q9 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithFlags_Flags[q12] -> - or([x_ExplicitVarSizeWithDummy[q14] != 5 /\ - x_ExplicitVarSizeWithDummy[q14] = x_ExplicitVarSizeWithFlags_Values[q12] - | q14 : int(1..4)]) - | q12 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q16] != 5 -> - or([x_ExplicitVarSizeWithFlags_Flags[q18] /\ - x_ExplicitVarSizeWithFlags_Values[q18] = x_ExplicitVarSizeWithDummy[q16] - | q18 : int(1..4)]) - | q16 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q20] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q20]] - | q20 : int(1..4)]), - and([x_Occurrence[q21] -> - or([x_ExplicitVarSizeWithFlags_Flags[q23] /\ x_ExplicitVarSizeWithFlags_Values[q23] = q21 | q23 : int(1..4)]) - | q21 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_2_1_3_1-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_2_1_3_1-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_1_3_1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_2_1_3_1-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_2_1_3_1-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_1_3_1-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_2_1_3_1.eprime b/tests/exhaustive/basic/set06/expected/model_2_1_3_1.eprime deleted file mode 100644 index 1efc26667b..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_1_3_1.eprime +++ /dev/null @@ -1,43 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -find x_Occurrence: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy, x_Occurrence] -such that - or([x_ExplicitVarSizeWithDummy[q30] != 5 /\ x_ExplicitVarSizeWithDummy[q30] = 1 | q30 : int(1..4)]), - x_Occurrence[2], - or([q28 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q28] = 3 | q28 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 5 - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q2] = 5 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 5) | q3 : int(1..4)]) <= 4, - sum([toInt(x_Occurrence[q5]) | q5 : int(1..4)]) <= 4, - and([x_Occurrence[q22] -> - or([x_ExplicitVarSizeWithDummy[q24] != 5 /\ x_ExplicitVarSizeWithDummy[q24] = q22 | q24 : int(1..4)]) - | q22 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q26] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q26]] | q26 : int(1..4)]), - and([q6 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q6] < x_ExplicitVarSizeWithMarker_Values[q6 + 1] - | q6 : int(1..3)]), - and([q7 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q7] = 1 | q7 : int(1..4)]), - x_ExplicitVarSizeWithMarker_Marker <= 4, - and([q10 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q12] != 5 /\ - x_ExplicitVarSizeWithDummy[q12] = x_ExplicitVarSizeWithMarker_Values[q10] - | q12 : int(1..4)]) - | q10 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q14] != 5 -> - or([q16 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q16] = x_ExplicitVarSizeWithDummy[q14] - | q16 : int(1..4)]) - | q14 : int(1..4)]), - and([q18 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q18]] - | q18 : int(1..4)]), - and([x_Occurrence[q19] -> - or([q21 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q21] = q19 - | q21 : int(1..4)]) - | q19 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_2_1_3_2-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_2_1_3_2-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_1_3_2-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_2_1_3_2-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_2_1_3_2-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_1_3_2-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_2_1_3_2.eprime b/tests/exhaustive/basic/set06/expected/model_2_1_3_2.eprime deleted file mode 100644 index 1efc26667b..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_1_3_2.eprime +++ /dev/null @@ -1,43 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -find x_Occurrence: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy, x_Occurrence] -such that - or([x_ExplicitVarSizeWithDummy[q30] != 5 /\ x_ExplicitVarSizeWithDummy[q30] = 1 | q30 : int(1..4)]), - x_Occurrence[2], - or([q28 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q28] = 3 | q28 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 5 - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q2] = 5 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 5) | q3 : int(1..4)]) <= 4, - sum([toInt(x_Occurrence[q5]) | q5 : int(1..4)]) <= 4, - and([x_Occurrence[q22] -> - or([x_ExplicitVarSizeWithDummy[q24] != 5 /\ x_ExplicitVarSizeWithDummy[q24] = q22 | q24 : int(1..4)]) - | q22 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q26] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q26]] | q26 : int(1..4)]), - and([q6 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q6] < x_ExplicitVarSizeWithMarker_Values[q6 + 1] - | q6 : int(1..3)]), - and([q7 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q7] = 1 | q7 : int(1..4)]), - x_ExplicitVarSizeWithMarker_Marker <= 4, - and([q10 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q12] != 5 /\ - x_ExplicitVarSizeWithDummy[q12] = x_ExplicitVarSizeWithMarker_Values[q10] - | q12 : int(1..4)]) - | q10 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q14] != 5 -> - or([q16 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q16] = x_ExplicitVarSizeWithDummy[q14] - | q16 : int(1..4)]) - | q14 : int(1..4)]), - and([q18 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q18]] - | q18 : int(1..4)]), - and([x_Occurrence[q19] -> - or([q21 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q21] = q19 - | q21 : int(1..4)]) - | q19 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_2_1_3_3-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_2_1_3_3-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_1_3_3-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_2_1_3_3-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_2_1_3_3-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_1_3_3-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_2_1_3_3.eprime b/tests/exhaustive/basic/set06/expected/model_2_1_3_3.eprime deleted file mode 100644 index 1efc26667b..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_1_3_3.eprime +++ /dev/null @@ -1,43 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -find x_Occurrence: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy, x_Occurrence] -such that - or([x_ExplicitVarSizeWithDummy[q30] != 5 /\ x_ExplicitVarSizeWithDummy[q30] = 1 | q30 : int(1..4)]), - x_Occurrence[2], - or([q28 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q28] = 3 | q28 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 5 - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q2] = 5 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 5) | q3 : int(1..4)]) <= 4, - sum([toInt(x_Occurrence[q5]) | q5 : int(1..4)]) <= 4, - and([x_Occurrence[q22] -> - or([x_ExplicitVarSizeWithDummy[q24] != 5 /\ x_ExplicitVarSizeWithDummy[q24] = q22 | q24 : int(1..4)]) - | q22 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q26] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q26]] | q26 : int(1..4)]), - and([q6 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q6] < x_ExplicitVarSizeWithMarker_Values[q6 + 1] - | q6 : int(1..3)]), - and([q7 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q7] = 1 | q7 : int(1..4)]), - x_ExplicitVarSizeWithMarker_Marker <= 4, - and([q10 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q12] != 5 /\ - x_ExplicitVarSizeWithDummy[q12] = x_ExplicitVarSizeWithMarker_Values[q10] - | q12 : int(1..4)]) - | q10 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q14] != 5 -> - or([q16 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q16] = x_ExplicitVarSizeWithDummy[q14] - | q16 : int(1..4)]) - | q14 : int(1..4)]), - and([q18 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q18]] - | q18 : int(1..4)]), - and([x_Occurrence[q19] -> - or([q21 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q21] = q19 - | q21 : int(1..4)]) - | q19 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_2_1_3_4-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_2_1_3_4-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_1_3_4-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_2_1_3_4-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_2_1_3_4-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_1_3_4-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_2_1_3_4.eprime b/tests/exhaustive/basic/set06/expected/model_2_1_3_4.eprime deleted file mode 100644 index ced251790b..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_1_3_4.eprime +++ /dev/null @@ -1,78 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -find x_Occurrence: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy, x_Occurrence, - x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] -such that - or([x_ExplicitVarSizeWithDummy[q56] != 5 /\ x_ExplicitVarSizeWithDummy[q56] = 1 | q56 : int(1..4)]), - x_Occurrence[2], - or([q49 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q49] = 3 | q49 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 5 - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q2] = 5 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 5) | q3 : int(1..4)]) <= 4, - sum([toInt(x_Occurrence[q5]) | q5 : int(1..4)]) <= 4, - and([x_Occurrence[q50] -> - or([x_ExplicitVarSizeWithDummy[q52] != 5 /\ x_ExplicitVarSizeWithDummy[q52] = q50 | q52 : int(1..4)]) - | q50 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q54] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q54]] | q54 : int(1..4)]), - and([q6 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q6] < x_ExplicitVarSizeWithMarker_Values[q6 + 1] - | q6 : int(1..3)]), - and([q7 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q7] = 1 | q7 : int(1..4)]), - x_ExplicitVarSizeWithMarker_Marker <= 4, - and([q10 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q12] != 5 /\ - x_ExplicitVarSizeWithDummy[q12] = x_ExplicitVarSizeWithMarker_Values[q10] - | q12 : int(1..4)]) - | q10 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q14] != 5 -> - or([q16 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q16] = x_ExplicitVarSizeWithDummy[q14] - | q16 : int(1..4)]) - | q14 : int(1..4)]), - and([q18 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q18]] - | q18 : int(1..4)]), - and([x_Occurrence[q19] -> - or([q21 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q21] = q19 - | q21 : int(1..4)]) - | q19 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q22 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q22] < x_ExplicitVarSizeWithFlags_Values[q22 + 1] - | q22 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q23] = false -> x_ExplicitVarSizeWithFlags_Values[q23] = 1 - | q23 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q24 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q24] | q24 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q25]) | q25 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithFlags_Flags[q28] -> - or([x_ExplicitVarSizeWithDummy[q30] != 5 /\ - x_ExplicitVarSizeWithDummy[q30] = x_ExplicitVarSizeWithFlags_Values[q28] - | q30 : int(1..4)]) - | q28 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q32] != 5 -> - or([x_ExplicitVarSizeWithFlags_Flags[q34] /\ - x_ExplicitVarSizeWithFlags_Values[q34] = x_ExplicitVarSizeWithDummy[q32] - | q34 : int(1..4)]) - | q32 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q36] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q36]] - | q36 : int(1..4)]), - and([x_Occurrence[q37] -> - or([x_ExplicitVarSizeWithFlags_Flags[q39] /\ x_ExplicitVarSizeWithFlags_Values[q39] = q37 | q39 : int(1..4)]) - | q37 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q41] -> - or([q43 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q43] = x_ExplicitVarSizeWithFlags_Values[q41] - | q43 : int(1..4)]) - | q41 : int(1..4)]), - and([q45 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q47] /\ - x_ExplicitVarSizeWithFlags_Values[q47] = x_ExplicitVarSizeWithMarker_Values[q45] - | q47 : int(1..4)]) - | q45 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_2_1_4_1-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_2_1_4_1-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_1_4_1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_2_1_4_1-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_2_1_4_1-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_1_4_1-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_2_1_4_1.eprime b/tests/exhaustive/basic/set06/expected/model_2_1_4_1.eprime deleted file mode 100644 index 4763aec36a..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_1_4_1.eprime +++ /dev/null @@ -1,43 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -find x_Occurrence: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy, x_Occurrence] -such that - or([x_ExplicitVarSizeWithDummy[q32] != 5 /\ x_ExplicitVarSizeWithDummy[q32] = 1 | q32 : int(1..4)]), - x_Occurrence[2], - or([x_ExplicitVarSizeWithFlags_Flags[q25] /\ x_ExplicitVarSizeWithFlags_Values[q25] = 3 | q25 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 5 - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q2] = 5 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 5) | q3 : int(1..4)]) <= 4, - sum([toInt(x_Occurrence[q5]) | q5 : int(1..4)]) <= 4, - and([x_Occurrence[q26] -> - or([x_ExplicitVarSizeWithDummy[q28] != 5 /\ x_ExplicitVarSizeWithDummy[q28] = q26 | q28 : int(1..4)]) - | q26 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q30] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q30]] | q30 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q6] < x_ExplicitVarSizeWithFlags_Values[q6 + 1] - | q6 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q7] = false -> x_ExplicitVarSizeWithFlags_Values[q7] = 1 | q7 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q8 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q8] | q8 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q9]) | q9 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithFlags_Flags[q12] -> - or([x_ExplicitVarSizeWithDummy[q14] != 5 /\ - x_ExplicitVarSizeWithDummy[q14] = x_ExplicitVarSizeWithFlags_Values[q12] - | q14 : int(1..4)]) - | q12 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q16] != 5 -> - or([x_ExplicitVarSizeWithFlags_Flags[q18] /\ - x_ExplicitVarSizeWithFlags_Values[q18] = x_ExplicitVarSizeWithDummy[q16] - | q18 : int(1..4)]) - | q16 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q20] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q20]] - | q20 : int(1..4)]), - and([x_Occurrence[q21] -> - or([x_ExplicitVarSizeWithFlags_Flags[q23] /\ x_ExplicitVarSizeWithFlags_Values[q23] = q21 | q23 : int(1..4)]) - | q21 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_2_1_4_2-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_2_1_4_2-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_1_4_2-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_2_1_4_2-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_2_1_4_2-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_1_4_2-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_2_1_4_2.eprime b/tests/exhaustive/basic/set06/expected/model_2_1_4_2.eprime deleted file mode 100644 index 4763aec36a..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_1_4_2.eprime +++ /dev/null @@ -1,43 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -find x_Occurrence: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy, x_Occurrence] -such that - or([x_ExplicitVarSizeWithDummy[q32] != 5 /\ x_ExplicitVarSizeWithDummy[q32] = 1 | q32 : int(1..4)]), - x_Occurrence[2], - or([x_ExplicitVarSizeWithFlags_Flags[q25] /\ x_ExplicitVarSizeWithFlags_Values[q25] = 3 | q25 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 5 - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q2] = 5 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 5) | q3 : int(1..4)]) <= 4, - sum([toInt(x_Occurrence[q5]) | q5 : int(1..4)]) <= 4, - and([x_Occurrence[q26] -> - or([x_ExplicitVarSizeWithDummy[q28] != 5 /\ x_ExplicitVarSizeWithDummy[q28] = q26 | q28 : int(1..4)]) - | q26 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q30] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q30]] | q30 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q6] < x_ExplicitVarSizeWithFlags_Values[q6 + 1] - | q6 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q7] = false -> x_ExplicitVarSizeWithFlags_Values[q7] = 1 | q7 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q8 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q8] | q8 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q9]) | q9 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithFlags_Flags[q12] -> - or([x_ExplicitVarSizeWithDummy[q14] != 5 /\ - x_ExplicitVarSizeWithDummy[q14] = x_ExplicitVarSizeWithFlags_Values[q12] - | q14 : int(1..4)]) - | q12 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q16] != 5 -> - or([x_ExplicitVarSizeWithFlags_Flags[q18] /\ - x_ExplicitVarSizeWithFlags_Values[q18] = x_ExplicitVarSizeWithDummy[q16] - | q18 : int(1..4)]) - | q16 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q20] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q20]] - | q20 : int(1..4)]), - and([x_Occurrence[q21] -> - or([x_ExplicitVarSizeWithFlags_Flags[q23] /\ x_ExplicitVarSizeWithFlags_Values[q23] = q21 | q23 : int(1..4)]) - | q21 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_2_1_4_3-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_2_1_4_3-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_1_4_3-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_2_1_4_3-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_2_1_4_3-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_1_4_3-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_2_1_4_3.eprime b/tests/exhaustive/basic/set06/expected/model_2_1_4_3.eprime deleted file mode 100644 index f9660743b6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_1_4_3.eprime +++ /dev/null @@ -1,77 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -find x_Occurrence: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy, x_Occurrence, - x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] -such that - or([x_ExplicitVarSizeWithDummy[q56] != 5 /\ x_ExplicitVarSizeWithDummy[q56] = 1 | q56 : int(1..4)]), - x_Occurrence[2], - or([x_ExplicitVarSizeWithFlags_Flags[q49] /\ x_ExplicitVarSizeWithFlags_Values[q49] = 3 | q49 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 5 - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q2] = 5 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 5) | q3 : int(1..4)]) <= 4, - sum([toInt(x_Occurrence[q5]) | q5 : int(1..4)]) <= 4, - and([x_Occurrence[q50] -> - or([x_ExplicitVarSizeWithDummy[q52] != 5 /\ x_ExplicitVarSizeWithDummy[q52] = q50 | q52 : int(1..4)]) - | q50 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q54] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q54]] | q54 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q6] < x_ExplicitVarSizeWithFlags_Values[q6 + 1] - | q6 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q7] = false -> x_ExplicitVarSizeWithFlags_Values[q7] = 1 | q7 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q8 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q8] | q8 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q9]) | q9 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithFlags_Flags[q12] -> - or([x_ExplicitVarSizeWithDummy[q14] != 5 /\ - x_ExplicitVarSizeWithDummy[q14] = x_ExplicitVarSizeWithFlags_Values[q12] - | q14 : int(1..4)]) - | q12 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q16] != 5 -> - or([x_ExplicitVarSizeWithFlags_Flags[q18] /\ - x_ExplicitVarSizeWithFlags_Values[q18] = x_ExplicitVarSizeWithDummy[q16] - | q18 : int(1..4)]) - | q16 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q20] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q20]] - | q20 : int(1..4)]), - and([x_Occurrence[q21] -> - or([x_ExplicitVarSizeWithFlags_Flags[q23] /\ x_ExplicitVarSizeWithFlags_Values[q23] = q21 | q23 : int(1..4)]) - | q21 : int(1..4)]), - and([q24 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q24] < x_ExplicitVarSizeWithMarker_Values[q24 + 1] - | q24 : int(1..3)]), - and([q25 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q25] = 1 | q25 : int(1..4)]), - x_ExplicitVarSizeWithMarker_Marker <= 4, - and([q28 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q30] != 5 /\ - x_ExplicitVarSizeWithDummy[q30] = x_ExplicitVarSizeWithMarker_Values[q28] - | q30 : int(1..4)]) - | q28 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q32] != 5 -> - or([q34 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q34] = x_ExplicitVarSizeWithDummy[q32] - | q34 : int(1..4)]) - | q32 : int(1..4)]), - and([q36 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q36]] - | q36 : int(1..4)]), - and([x_Occurrence[q37] -> - or([q39 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q39] = q37 - | q39 : int(1..4)]) - | q37 : int(1..4)]), - and([q41 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q43] /\ - x_ExplicitVarSizeWithFlags_Values[q43] = x_ExplicitVarSizeWithMarker_Values[q41] - | q43 : int(1..4)]) - | q41 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q45] -> - or([q47 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q47] = x_ExplicitVarSizeWithFlags_Values[q45] - | q47 : int(1..4)]) - | q45 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_2_1_4_4-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_2_1_4_4-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_1_4_4-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_2_1_4_4-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_2_1_4_4-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_1_4_4-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_2_1_4_4.eprime b/tests/exhaustive/basic/set06/expected/model_2_1_4_4.eprime deleted file mode 100644 index 4763aec36a..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_1_4_4.eprime +++ /dev/null @@ -1,43 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -find x_Occurrence: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy, x_Occurrence] -such that - or([x_ExplicitVarSizeWithDummy[q32] != 5 /\ x_ExplicitVarSizeWithDummy[q32] = 1 | q32 : int(1..4)]), - x_Occurrence[2], - or([x_ExplicitVarSizeWithFlags_Flags[q25] /\ x_ExplicitVarSizeWithFlags_Values[q25] = 3 | q25 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 5 - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q2] = 5 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 5) | q3 : int(1..4)]) <= 4, - sum([toInt(x_Occurrence[q5]) | q5 : int(1..4)]) <= 4, - and([x_Occurrence[q26] -> - or([x_ExplicitVarSizeWithDummy[q28] != 5 /\ x_ExplicitVarSizeWithDummy[q28] = q26 | q28 : int(1..4)]) - | q26 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q30] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q30]] | q30 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q6] < x_ExplicitVarSizeWithFlags_Values[q6 + 1] - | q6 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q7] = false -> x_ExplicitVarSizeWithFlags_Values[q7] = 1 | q7 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q8 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q8] | q8 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q9]) | q9 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithFlags_Flags[q12] -> - or([x_ExplicitVarSizeWithDummy[q14] != 5 /\ - x_ExplicitVarSizeWithDummy[q14] = x_ExplicitVarSizeWithFlags_Values[q12] - | q14 : int(1..4)]) - | q12 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q16] != 5 -> - or([x_ExplicitVarSizeWithFlags_Flags[q18] /\ - x_ExplicitVarSizeWithFlags_Values[q18] = x_ExplicitVarSizeWithDummy[q16] - | q18 : int(1..4)]) - | q16 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q20] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q20]] - | q20 : int(1..4)]), - and([x_Occurrence[q21] -> - or([x_ExplicitVarSizeWithFlags_Flags[q23] /\ x_ExplicitVarSizeWithFlags_Values[q23] = q21 | q23 : int(1..4)]) - | q21 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_2_2_1_1-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_2_2_1_1-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_2_1_1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_2_2_1_1-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_2_2_1_1-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_2_1_1-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_2_2_1_1.eprime b/tests/exhaustive/basic/set06/expected/model_2_2_1_1.eprime deleted file mode 100644 index c05e9cc08f..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_2_1_1.eprime +++ /dev/null @@ -1,19 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -find x_Occurrence: matrix indexed by [int(1..4)] of bool -branching on [x_Occurrence, x_ExplicitVarSizeWithDummy] -such that - or([x_ExplicitVarSizeWithDummy[q12] != 5 /\ x_ExplicitVarSizeWithDummy[q12] = 1 | q12 : int(1..4)]), - or([x_ExplicitVarSizeWithDummy[q14] != 5 /\ x_ExplicitVarSizeWithDummy[q14] = 2 | q14 : int(1..4)]), - x_Occurrence[3], - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 5 - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q2] = 5 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 5) | q3 : int(1..4)]) <= 4, - sum([toInt(x_Occurrence[q5]) | q5 : int(1..4)]) <= 4, - and([x_Occurrence[q6] -> - or([x_ExplicitVarSizeWithDummy[q8] != 5 /\ x_ExplicitVarSizeWithDummy[q8] = q6 | q8 : int(1..4)]) - | q6 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q10] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q10]] | q10 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_2_2_1_2-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_2_2_1_2-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_2_1_2-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_2_2_1_2-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_2_2_1_2-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_2_1_2-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_2_2_1_2.eprime b/tests/exhaustive/basic/set06/expected/model_2_2_1_2.eprime deleted file mode 100644 index c05e9cc08f..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_2_1_2.eprime +++ /dev/null @@ -1,19 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -find x_Occurrence: matrix indexed by [int(1..4)] of bool -branching on [x_Occurrence, x_ExplicitVarSizeWithDummy] -such that - or([x_ExplicitVarSizeWithDummy[q12] != 5 /\ x_ExplicitVarSizeWithDummy[q12] = 1 | q12 : int(1..4)]), - or([x_ExplicitVarSizeWithDummy[q14] != 5 /\ x_ExplicitVarSizeWithDummy[q14] = 2 | q14 : int(1..4)]), - x_Occurrence[3], - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 5 - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q2] = 5 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 5) | q3 : int(1..4)]) <= 4, - sum([toInt(x_Occurrence[q5]) | q5 : int(1..4)]) <= 4, - and([x_Occurrence[q6] -> - or([x_ExplicitVarSizeWithDummy[q8] != 5 /\ x_ExplicitVarSizeWithDummy[q8] = q6 | q8 : int(1..4)]) - | q6 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q10] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q10]] | q10 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_2_2_1_3-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_2_2_1_3-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_2_1_3-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_2_2_1_3-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_2_2_1_3-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_2_1_3-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_2_2_1_3.eprime b/tests/exhaustive/basic/set06/expected/model_2_2_1_3.eprime deleted file mode 100644 index ca46d4ab65..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_2_1_3.eprime +++ /dev/null @@ -1,43 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -find x_Occurrence: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy, x_Occurrence] -such that - or([x_ExplicitVarSizeWithDummy[q28] != 5 /\ x_ExplicitVarSizeWithDummy[q28] = 1 | q28 : int(1..4)]), - or([x_ExplicitVarSizeWithDummy[q30] != 5 /\ x_ExplicitVarSizeWithDummy[q30] = 2 | q30 : int(1..4)]), - x_Occurrence[3], - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 5 - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q2] = 5 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 5) | q3 : int(1..4)]) <= 4, - sum([toInt(x_Occurrence[q5]) | q5 : int(1..4)]) <= 4, - and([x_Occurrence[q22] -> - or([x_ExplicitVarSizeWithDummy[q24] != 5 /\ x_ExplicitVarSizeWithDummy[q24] = q22 | q24 : int(1..4)]) - | q22 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q26] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q26]] | q26 : int(1..4)]), - and([q6 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q6] < x_ExplicitVarSizeWithMarker_Values[q6 + 1] - | q6 : int(1..3)]), - and([q7 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q7] = 1 | q7 : int(1..4)]), - x_ExplicitVarSizeWithMarker_Marker <= 4, - and([q10 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q12] != 5 /\ - x_ExplicitVarSizeWithDummy[q12] = x_ExplicitVarSizeWithMarker_Values[q10] - | q12 : int(1..4)]) - | q10 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q14] != 5 -> - or([q16 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q16] = x_ExplicitVarSizeWithDummy[q14] - | q16 : int(1..4)]) - | q14 : int(1..4)]), - and([q18 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q18]] - | q18 : int(1..4)]), - and([x_Occurrence[q19] -> - or([q21 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q21] = q19 - | q21 : int(1..4)]) - | q19 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_2_2_1_4-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_2_2_1_4-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_2_1_4-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_2_2_1_4-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_2_2_1_4-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_2_1_4-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_2_2_1_4.eprime b/tests/exhaustive/basic/set06/expected/model_2_2_1_4.eprime deleted file mode 100644 index 354ad47498..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_2_1_4.eprime +++ /dev/null @@ -1,43 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -find x_Occurrence: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy, x_Occurrence] -such that - or([x_ExplicitVarSizeWithDummy[q30] != 5 /\ x_ExplicitVarSizeWithDummy[q30] = 1 | q30 : int(1..4)]), - or([x_ExplicitVarSizeWithDummy[q32] != 5 /\ x_ExplicitVarSizeWithDummy[q32] = 2 | q32 : int(1..4)]), - x_Occurrence[3], - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 5 - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q2] = 5 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 5) | q3 : int(1..4)]) <= 4, - sum([toInt(x_Occurrence[q5]) | q5 : int(1..4)]) <= 4, - and([x_Occurrence[q24] -> - or([x_ExplicitVarSizeWithDummy[q26] != 5 /\ x_ExplicitVarSizeWithDummy[q26] = q24 | q26 : int(1..4)]) - | q24 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q28] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q28]] | q28 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q6] < x_ExplicitVarSizeWithFlags_Values[q6 + 1] - | q6 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q7] = false -> x_ExplicitVarSizeWithFlags_Values[q7] = 1 | q7 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q8 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q8] | q8 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q9]) | q9 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithFlags_Flags[q12] -> - or([x_ExplicitVarSizeWithDummy[q14] != 5 /\ - x_ExplicitVarSizeWithDummy[q14] = x_ExplicitVarSizeWithFlags_Values[q12] - | q14 : int(1..4)]) - | q12 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q16] != 5 -> - or([x_ExplicitVarSizeWithFlags_Flags[q18] /\ - x_ExplicitVarSizeWithFlags_Values[q18] = x_ExplicitVarSizeWithDummy[q16] - | q18 : int(1..4)]) - | q16 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q20] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q20]] - | q20 : int(1..4)]), - and([x_Occurrence[q21] -> - or([x_ExplicitVarSizeWithFlags_Flags[q23] /\ x_ExplicitVarSizeWithFlags_Values[q23] = q21 | q23 : int(1..4)]) - | q21 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_2_2_2_1-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_2_2_2_1-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_2_2_1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_2_2_2_1-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_2_2_2_1-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_2_2_1-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_2_2_2_1.eprime b/tests/exhaustive/basic/set06/expected/model_2_2_2_1.eprime deleted file mode 100644 index 4a891ab86b..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_2_2_1.eprime +++ /dev/null @@ -1,19 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -find x_Occurrence: matrix indexed by [int(1..4)] of bool -branching on [x_Occurrence, x_ExplicitVarSizeWithDummy] -such that - or([x_ExplicitVarSizeWithDummy[q12] != 5 /\ x_ExplicitVarSizeWithDummy[q12] = 1 | q12 : int(1..4)]), - or([x_ExplicitVarSizeWithDummy[q14] != 5 /\ x_ExplicitVarSizeWithDummy[q14] = 2 | q14 : int(1..4)]), - or([x_ExplicitVarSizeWithDummy[q16] != 5 /\ x_ExplicitVarSizeWithDummy[q16] = 3 | q16 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 5 - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q2] = 5 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 5) | q3 : int(1..4)]) <= 4, - sum([toInt(x_Occurrence[q5]) | q5 : int(1..4)]) <= 4, - and([x_Occurrence[q6] -> - or([x_ExplicitVarSizeWithDummy[q8] != 5 /\ x_ExplicitVarSizeWithDummy[q8] = q6 | q8 : int(1..4)]) - | q6 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q10] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q10]] | q10 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_2_2_2_2-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_2_2_2_2-solution000001.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_2_2_2-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_2_2_2_2-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_2_2_2_2-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_2_2_2-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_2_2_2_2.eprime b/tests/exhaustive/basic/set06/expected/model_2_2_2_2.eprime deleted file mode 100644 index c69010fadb..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_2_2_2.eprime +++ /dev/null @@ -1,13 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -branching on [x_ExplicitVarSizeWithDummy] -such that - or([x_ExplicitVarSizeWithDummy[q6] != 5 /\ x_ExplicitVarSizeWithDummy[q6] = 1 | q6 : int(1..4)]), - or([x_ExplicitVarSizeWithDummy[q8] != 5 /\ x_ExplicitVarSizeWithDummy[q8] = 2 | q8 : int(1..4)]), - or([x_ExplicitVarSizeWithDummy[q10] != 5 /\ x_ExplicitVarSizeWithDummy[q10] = 3 | q10 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 5 - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q2] = 5 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 5) | q3 : int(1..4)]) <= 4 - diff --git a/tests/exhaustive/basic/set06/expected/model_2_2_2_3-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_2_2_2_3-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_2_2_3-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_2_2_2_3-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_2_2_2_3-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_2_2_3-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_2_2_2_3.eprime b/tests/exhaustive/basic/set06/expected/model_2_2_2_3.eprime deleted file mode 100644 index 18a5bb99e1..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_2_2_3.eprime +++ /dev/null @@ -1,30 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -branching on [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy] -such that - or([x_ExplicitVarSizeWithDummy[q17] != 5 /\ x_ExplicitVarSizeWithDummy[q17] = 1 | q17 : int(1..4)]), - or([x_ExplicitVarSizeWithDummy[q19] != 5 /\ x_ExplicitVarSizeWithDummy[q19] = 2 | q19 : int(1..4)]), - or([x_ExplicitVarSizeWithDummy[q21] != 5 /\ x_ExplicitVarSizeWithDummy[q21] = 3 | q21 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 5 - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q2] = 5 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 5) | q3 : int(1..4)]) <= 4, - and([q5 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q5] < x_ExplicitVarSizeWithMarker_Values[q5 + 1] - | q5 : int(1..3)]), - and([q6 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q6] = 1 | q6 : int(1..4)]), - x_ExplicitVarSizeWithMarker_Marker <= 4, - and([q9 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q11] != 5 /\ - x_ExplicitVarSizeWithDummy[q11] = x_ExplicitVarSizeWithMarker_Values[q9] - | q11 : int(1..4)]) - | q9 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q13] != 5 -> - or([q15 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q15] = x_ExplicitVarSizeWithDummy[q13] - | q15 : int(1..4)]) - | q13 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_2_2_2_4-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_2_2_2_4-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_2_2_4-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_2_2_2_4-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_2_2_2_4-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_2_2_4-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_2_2_2_4.eprime b/tests/exhaustive/basic/set06/expected/model_2_2_2_4.eprime deleted file mode 100644 index dcecde5147..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_2_2_4.eprime +++ /dev/null @@ -1,31 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -branching on [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy] -such that - or([x_ExplicitVarSizeWithDummy[q19] != 5 /\ x_ExplicitVarSizeWithDummy[q19] = 1 | q19 : int(1..4)]), - or([x_ExplicitVarSizeWithDummy[q21] != 5 /\ x_ExplicitVarSizeWithDummy[q21] = 2 | q21 : int(1..4)]), - or([x_ExplicitVarSizeWithDummy[q23] != 5 /\ x_ExplicitVarSizeWithDummy[q23] = 3 | q23 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 5 - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q2] = 5 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 5) | q3 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithFlags_Flags[q5 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q5] < x_ExplicitVarSizeWithFlags_Values[q5 + 1] - | q5 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q6] = false -> x_ExplicitVarSizeWithFlags_Values[q6] = 1 | q6 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q7] | q7 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q8]) | q8 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithFlags_Flags[q11] -> - or([x_ExplicitVarSizeWithDummy[q13] != 5 /\ - x_ExplicitVarSizeWithDummy[q13] = x_ExplicitVarSizeWithFlags_Values[q11] - | q13 : int(1..4)]) - | q11 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q15] != 5 -> - or([x_ExplicitVarSizeWithFlags_Flags[q17] /\ - x_ExplicitVarSizeWithFlags_Values[q17] = x_ExplicitVarSizeWithDummy[q15] - | q17 : int(1..4)]) - | q15 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_2_2_3_1-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_2_2_3_1-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_2_3_1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_2_2_3_1-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_2_2_3_1-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_2_3_1-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_2_2_3_1.eprime b/tests/exhaustive/basic/set06/expected/model_2_2_3_1.eprime deleted file mode 100644 index 0ba2c449b2..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_2_3_1.eprime +++ /dev/null @@ -1,43 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_Occurrence: matrix indexed by [int(1..4)] of bool -branching on - [x_Occurrence, x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] -such that - or([x_ExplicitVarSizeWithDummy[q28] != 5 /\ x_ExplicitVarSizeWithDummy[q28] = 1 | q28 : int(1..4)]), - or([x_ExplicitVarSizeWithDummy[q30] != 5 /\ x_ExplicitVarSizeWithDummy[q30] = 2 | q30 : int(1..4)]), - or([q32 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q32] = 3 | q32 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 5 - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q2] = 5 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 5) | q3 : int(1..4)]) <= 4, - and([q5 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q5] < x_ExplicitVarSizeWithMarker_Values[q5 + 1] - | q5 : int(1..3)]), - and([q6 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q6] = 1 | q6 : int(1..4)]), - x_ExplicitVarSizeWithMarker_Marker <= 4, - and([q9 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q11] != 5 /\ - x_ExplicitVarSizeWithDummy[q11] = x_ExplicitVarSizeWithMarker_Values[q9] - | q11 : int(1..4)]) - | q9 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q13] != 5 -> - or([q15 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q15] = x_ExplicitVarSizeWithDummy[q13] - | q15 : int(1..4)]) - | q13 : int(1..4)]), - sum([toInt(x_Occurrence[q16]) | q16 : int(1..4)]) <= 4, - and([x_Occurrence[q17] -> - or([x_ExplicitVarSizeWithDummy[q19] != 5 /\ x_ExplicitVarSizeWithDummy[q19] = q17 | q19 : int(1..4)]) - | q17 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q21] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q21]] | q21 : int(1..4)]), - and([x_Occurrence[q22] -> - or([q24 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q24] = q22 - | q24 : int(1..4)]) - | q22 : int(1..4)]), - and([q26 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q26]] - | q26 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_2_2_3_2-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_2_2_3_2-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_2_3_2-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_2_2_3_2-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_2_2_3_2-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_2_3_2-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_2_2_3_2.eprime b/tests/exhaustive/basic/set06/expected/model_2_2_3_2.eprime deleted file mode 100644 index 875689727a..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_2_3_2.eprime +++ /dev/null @@ -1,30 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -branching on [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy] -such that - or([x_ExplicitVarSizeWithDummy[q17] != 5 /\ x_ExplicitVarSizeWithDummy[q17] = 1 | q17 : int(1..4)]), - or([x_ExplicitVarSizeWithDummy[q19] != 5 /\ x_ExplicitVarSizeWithDummy[q19] = 2 | q19 : int(1..4)]), - or([q21 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q21] = 3 | q21 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 5 - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q2] = 5 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 5) | q3 : int(1..4)]) <= 4, - and([q5 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q5] < x_ExplicitVarSizeWithMarker_Values[q5 + 1] - | q5 : int(1..3)]), - and([q6 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q6] = 1 | q6 : int(1..4)]), - x_ExplicitVarSizeWithMarker_Marker <= 4, - and([q9 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q11] != 5 /\ - x_ExplicitVarSizeWithDummy[q11] = x_ExplicitVarSizeWithMarker_Values[q9] - | q11 : int(1..4)]) - | q9 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q13] != 5 -> - or([q15 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q15] = x_ExplicitVarSizeWithDummy[q13] - | q15 : int(1..4)]) - | q13 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_2_2_3_3-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_2_2_3_3-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_2_3_3-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_2_2_3_3-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_2_2_3_3-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_2_3_3-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_2_2_3_3.eprime b/tests/exhaustive/basic/set06/expected/model_2_2_3_3.eprime deleted file mode 100644 index 875689727a..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_2_3_3.eprime +++ /dev/null @@ -1,30 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -branching on [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy] -such that - or([x_ExplicitVarSizeWithDummy[q17] != 5 /\ x_ExplicitVarSizeWithDummy[q17] = 1 | q17 : int(1..4)]), - or([x_ExplicitVarSizeWithDummy[q19] != 5 /\ x_ExplicitVarSizeWithDummy[q19] = 2 | q19 : int(1..4)]), - or([q21 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q21] = 3 | q21 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 5 - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q2] = 5 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 5) | q3 : int(1..4)]) <= 4, - and([q5 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q5] < x_ExplicitVarSizeWithMarker_Values[q5 + 1] - | q5 : int(1..3)]), - and([q6 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q6] = 1 | q6 : int(1..4)]), - x_ExplicitVarSizeWithMarker_Marker <= 4, - and([q9 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q11] != 5 /\ - x_ExplicitVarSizeWithDummy[q11] = x_ExplicitVarSizeWithMarker_Values[q9] - | q11 : int(1..4)]) - | q9 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q13] != 5 -> - or([q15 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q15] = x_ExplicitVarSizeWithDummy[q13] - | q15 : int(1..4)]) - | q13 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_2_2_3_4-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_2_2_3_4-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_2_3_4-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_2_2_3_4-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_2_2_3_4-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_2_3_4-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_2_2_3_4.eprime b/tests/exhaustive/basic/set06/expected/model_2_2_3_4.eprime deleted file mode 100644 index ca3fdd46a7..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_2_3_4.eprime +++ /dev/null @@ -1,61 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy, - x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] -such that - or([x_ExplicitVarSizeWithDummy[q38] != 5 /\ x_ExplicitVarSizeWithDummy[q38] = 1 | q38 : int(1..4)]), - or([x_ExplicitVarSizeWithDummy[q40] != 5 /\ x_ExplicitVarSizeWithDummy[q40] = 2 | q40 : int(1..4)]), - or([q42 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q42] = 3 | q42 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 5 - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q2] = 5 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 5) | q3 : int(1..4)]) <= 4, - and([q5 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q5] < x_ExplicitVarSizeWithMarker_Values[q5 + 1] - | q5 : int(1..3)]), - and([q6 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q6] = 1 | q6 : int(1..4)]), - x_ExplicitVarSizeWithMarker_Marker <= 4, - and([q9 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q11] != 5 /\ - x_ExplicitVarSizeWithDummy[q11] = x_ExplicitVarSizeWithMarker_Values[q9] - | q11 : int(1..4)]) - | q9 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q13] != 5 -> - or([q15 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q15] = x_ExplicitVarSizeWithDummy[q13] - | q15 : int(1..4)]) - | q13 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q16 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q16] < x_ExplicitVarSizeWithFlags_Values[q16 + 1] - | q16 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q17] = false -> x_ExplicitVarSizeWithFlags_Values[q17] = 1 - | q17 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q18 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q18] | q18 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q19]) | q19 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithFlags_Flags[q22] -> - or([x_ExplicitVarSizeWithDummy[q24] != 5 /\ - x_ExplicitVarSizeWithDummy[q24] = x_ExplicitVarSizeWithFlags_Values[q22] - | q24 : int(1..4)]) - | q22 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q26] != 5 -> - or([x_ExplicitVarSizeWithFlags_Flags[q28] /\ - x_ExplicitVarSizeWithFlags_Values[q28] = x_ExplicitVarSizeWithDummy[q26] - | q28 : int(1..4)]) - | q26 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q30] -> - or([q32 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q32] = x_ExplicitVarSizeWithFlags_Values[q30] - | q32 : int(1..4)]) - | q30 : int(1..4)]), - and([q34 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q36] /\ - x_ExplicitVarSizeWithFlags_Values[q36] = x_ExplicitVarSizeWithMarker_Values[q34] - | q36 : int(1..4)]) - | q34 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_2_2_4_1-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_2_2_4_1-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_2_4_1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_2_2_4_1-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_2_2_4_1-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_2_4_1-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_2_2_4_1.eprime b/tests/exhaustive/basic/set06/expected/model_2_2_4_1.eprime deleted file mode 100644 index 9dbf7c903e..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_2_4_1.eprime +++ /dev/null @@ -1,43 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_Occurrence: matrix indexed by [int(1..4)] of bool -branching on - [x_Occurrence, x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] -such that - or([x_ExplicitVarSizeWithDummy[q30] != 5 /\ x_ExplicitVarSizeWithDummy[q30] = 1 | q30 : int(1..4)]), - or([x_ExplicitVarSizeWithDummy[q32] != 5 /\ x_ExplicitVarSizeWithDummy[q32] = 2 | q32 : int(1..4)]), - or([x_ExplicitVarSizeWithFlags_Flags[q34] /\ x_ExplicitVarSizeWithFlags_Values[q34] = 3 | q34 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 5 - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q2] = 5 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 5) | q3 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithFlags_Flags[q5 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q5] < x_ExplicitVarSizeWithFlags_Values[q5 + 1] - | q5 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q6] = false -> x_ExplicitVarSizeWithFlags_Values[q6] = 1 | q6 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q7] | q7 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q8]) | q8 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithFlags_Flags[q11] -> - or([x_ExplicitVarSizeWithDummy[q13] != 5 /\ - x_ExplicitVarSizeWithDummy[q13] = x_ExplicitVarSizeWithFlags_Values[q11] - | q13 : int(1..4)]) - | q11 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q15] != 5 -> - or([x_ExplicitVarSizeWithFlags_Flags[q17] /\ - x_ExplicitVarSizeWithFlags_Values[q17] = x_ExplicitVarSizeWithDummy[q15] - | q17 : int(1..4)]) - | q15 : int(1..4)]), - sum([toInt(x_Occurrence[q18]) | q18 : int(1..4)]) <= 4, - and([x_Occurrence[q19] -> - or([x_ExplicitVarSizeWithDummy[q21] != 5 /\ x_ExplicitVarSizeWithDummy[q21] = q19 | q21 : int(1..4)]) - | q19 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q23] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q23]] | q23 : int(1..4)]), - and([x_Occurrence[q24] -> - or([x_ExplicitVarSizeWithFlags_Flags[q26] /\ x_ExplicitVarSizeWithFlags_Values[q26] = q24 | q26 : int(1..4)]) - | q24 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q28] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q28]] - | q28 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_2_2_4_2-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_2_2_4_2-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_2_4_2-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_2_2_4_2-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_2_2_4_2-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_2_4_2-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_2_2_4_2.eprime b/tests/exhaustive/basic/set06/expected/model_2_2_4_2.eprime deleted file mode 100644 index 8a79eef455..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_2_4_2.eprime +++ /dev/null @@ -1,31 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -branching on [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy] -such that - or([x_ExplicitVarSizeWithDummy[q19] != 5 /\ x_ExplicitVarSizeWithDummy[q19] = 1 | q19 : int(1..4)]), - or([x_ExplicitVarSizeWithDummy[q21] != 5 /\ x_ExplicitVarSizeWithDummy[q21] = 2 | q21 : int(1..4)]), - or([x_ExplicitVarSizeWithFlags_Flags[q23] /\ x_ExplicitVarSizeWithFlags_Values[q23] = 3 | q23 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 5 - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q2] = 5 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 5) | q3 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithFlags_Flags[q5 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q5] < x_ExplicitVarSizeWithFlags_Values[q5 + 1] - | q5 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q6] = false -> x_ExplicitVarSizeWithFlags_Values[q6] = 1 | q6 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q7] | q7 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q8]) | q8 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithFlags_Flags[q11] -> - or([x_ExplicitVarSizeWithDummy[q13] != 5 /\ - x_ExplicitVarSizeWithDummy[q13] = x_ExplicitVarSizeWithFlags_Values[q11] - | q13 : int(1..4)]) - | q11 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q15] != 5 -> - or([x_ExplicitVarSizeWithFlags_Flags[q17] /\ - x_ExplicitVarSizeWithFlags_Values[q17] = x_ExplicitVarSizeWithDummy[q15] - | q17 : int(1..4)]) - | q15 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_2_2_4_3-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_2_2_4_3-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_2_4_3-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_2_2_4_3-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_2_2_4_3-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_2_4_3-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_2_2_4_3.eprime b/tests/exhaustive/basic/set06/expected/model_2_2_4_3.eprime deleted file mode 100644 index 7d292ec23b..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_2_4_3.eprime +++ /dev/null @@ -1,60 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy, - x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] -such that - or([x_ExplicitVarSizeWithDummy[q38] != 5 /\ x_ExplicitVarSizeWithDummy[q38] = 1 | q38 : int(1..4)]), - or([x_ExplicitVarSizeWithDummy[q40] != 5 /\ x_ExplicitVarSizeWithDummy[q40] = 2 | q40 : int(1..4)]), - or([x_ExplicitVarSizeWithFlags_Flags[q42] /\ x_ExplicitVarSizeWithFlags_Values[q42] = 3 | q42 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 5 - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q2] = 5 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 5) | q3 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithFlags_Flags[q5 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q5] < x_ExplicitVarSizeWithFlags_Values[q5 + 1] - | q5 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q6] = false -> x_ExplicitVarSizeWithFlags_Values[q6] = 1 | q6 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q7] | q7 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q8]) | q8 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithFlags_Flags[q11] -> - or([x_ExplicitVarSizeWithDummy[q13] != 5 /\ - x_ExplicitVarSizeWithDummy[q13] = x_ExplicitVarSizeWithFlags_Values[q11] - | q13 : int(1..4)]) - | q11 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q15] != 5 -> - or([x_ExplicitVarSizeWithFlags_Flags[q17] /\ - x_ExplicitVarSizeWithFlags_Values[q17] = x_ExplicitVarSizeWithDummy[q15] - | q17 : int(1..4)]) - | q15 : int(1..4)]), - and([q18 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q18] < x_ExplicitVarSizeWithMarker_Values[q18 + 1] - | q18 : int(1..3)]), - and([q19 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q19] = 1 | q19 : int(1..4)]), - x_ExplicitVarSizeWithMarker_Marker <= 4, - and([q22 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q24] != 5 /\ - x_ExplicitVarSizeWithDummy[q24] = x_ExplicitVarSizeWithMarker_Values[q22] - | q24 : int(1..4)]) - | q22 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q26] != 5 -> - or([q28 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q28] = x_ExplicitVarSizeWithDummy[q26] - | q28 : int(1..4)]) - | q26 : int(1..4)]), - and([q30 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q32] /\ - x_ExplicitVarSizeWithFlags_Values[q32] = x_ExplicitVarSizeWithMarker_Values[q30] - | q32 : int(1..4)]) - | q30 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q34] -> - or([q36 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q36] = x_ExplicitVarSizeWithFlags_Values[q34] - | q36 : int(1..4)]) - | q34 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_2_2_4_4-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_2_2_4_4-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_2_4_4-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_2_2_4_4-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_2_2_4_4-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_2_4_4-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_2_2_4_4.eprime b/tests/exhaustive/basic/set06/expected/model_2_2_4_4.eprime deleted file mode 100644 index 8a79eef455..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_2_4_4.eprime +++ /dev/null @@ -1,31 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -branching on [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy] -such that - or([x_ExplicitVarSizeWithDummy[q19] != 5 /\ x_ExplicitVarSizeWithDummy[q19] = 1 | q19 : int(1..4)]), - or([x_ExplicitVarSizeWithDummy[q21] != 5 /\ x_ExplicitVarSizeWithDummy[q21] = 2 | q21 : int(1..4)]), - or([x_ExplicitVarSizeWithFlags_Flags[q23] /\ x_ExplicitVarSizeWithFlags_Values[q23] = 3 | q23 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 5 - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q2] = 5 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 5) | q3 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithFlags_Flags[q5 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q5] < x_ExplicitVarSizeWithFlags_Values[q5 + 1] - | q5 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q6] = false -> x_ExplicitVarSizeWithFlags_Values[q6] = 1 | q6 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q7] | q7 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q8]) | q8 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithFlags_Flags[q11] -> - or([x_ExplicitVarSizeWithDummy[q13] != 5 /\ - x_ExplicitVarSizeWithDummy[q13] = x_ExplicitVarSizeWithFlags_Values[q11] - | q13 : int(1..4)]) - | q11 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q15] != 5 -> - or([x_ExplicitVarSizeWithFlags_Flags[q17] /\ - x_ExplicitVarSizeWithFlags_Values[q17] = x_ExplicitVarSizeWithDummy[q15] - | q17 : int(1..4)]) - | q15 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_2_3_1_1-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_2_3_1_1-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_3_1_1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_2_3_1_1-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_2_3_1_1-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_3_1_1-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_2_3_1_1.eprime b/tests/exhaustive/basic/set06/expected/model_2_3_1_1.eprime deleted file mode 100644 index 38b040fe91..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_3_1_1.eprime +++ /dev/null @@ -1,43 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_Occurrence: matrix indexed by [int(1..4)] of bool -branching on - [x_Occurrence, x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] -such that - or([x_ExplicitVarSizeWithDummy[q28] != 5 /\ x_ExplicitVarSizeWithDummy[q28] = 1 | q28 : int(1..4)]), - or([q30 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q30] = 2 | q30 : int(1..4)]), - x_Occurrence[3], - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 5 - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q2] = 5 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 5) | q3 : int(1..4)]) <= 4, - and([q5 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q5] < x_ExplicitVarSizeWithMarker_Values[q5 + 1] - | q5 : int(1..3)]), - and([q6 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q6] = 1 | q6 : int(1..4)]), - x_ExplicitVarSizeWithMarker_Marker <= 4, - and([q9 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q11] != 5 /\ - x_ExplicitVarSizeWithDummy[q11] = x_ExplicitVarSizeWithMarker_Values[q9] - | q11 : int(1..4)]) - | q9 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q13] != 5 -> - or([q15 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q15] = x_ExplicitVarSizeWithDummy[q13] - | q15 : int(1..4)]) - | q13 : int(1..4)]), - sum([toInt(x_Occurrence[q16]) | q16 : int(1..4)]) <= 4, - and([x_Occurrence[q17] -> - or([x_ExplicitVarSizeWithDummy[q19] != 5 /\ x_ExplicitVarSizeWithDummy[q19] = q17 | q19 : int(1..4)]) - | q17 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q21] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q21]] | q21 : int(1..4)]), - and([x_Occurrence[q22] -> - or([q24 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q24] = q22 - | q24 : int(1..4)]) - | q22 : int(1..4)]), - and([q26 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q26]] - | q26 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_2_3_1_2-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_2_3_1_2-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_3_1_2-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_2_3_1_2-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_2_3_1_2-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_3_1_2-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_2_3_1_2.eprime b/tests/exhaustive/basic/set06/expected/model_2_3_1_2.eprime deleted file mode 100644 index 38b040fe91..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_3_1_2.eprime +++ /dev/null @@ -1,43 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_Occurrence: matrix indexed by [int(1..4)] of bool -branching on - [x_Occurrence, x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] -such that - or([x_ExplicitVarSizeWithDummy[q28] != 5 /\ x_ExplicitVarSizeWithDummy[q28] = 1 | q28 : int(1..4)]), - or([q30 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q30] = 2 | q30 : int(1..4)]), - x_Occurrence[3], - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 5 - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q2] = 5 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 5) | q3 : int(1..4)]) <= 4, - and([q5 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q5] < x_ExplicitVarSizeWithMarker_Values[q5 + 1] - | q5 : int(1..3)]), - and([q6 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q6] = 1 | q6 : int(1..4)]), - x_ExplicitVarSizeWithMarker_Marker <= 4, - and([q9 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q11] != 5 /\ - x_ExplicitVarSizeWithDummy[q11] = x_ExplicitVarSizeWithMarker_Values[q9] - | q11 : int(1..4)]) - | q9 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q13] != 5 -> - or([q15 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q15] = x_ExplicitVarSizeWithDummy[q13] - | q15 : int(1..4)]) - | q13 : int(1..4)]), - sum([toInt(x_Occurrence[q16]) | q16 : int(1..4)]) <= 4, - and([x_Occurrence[q17] -> - or([x_ExplicitVarSizeWithDummy[q19] != 5 /\ x_ExplicitVarSizeWithDummy[q19] = q17 | q19 : int(1..4)]) - | q17 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q21] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q21]] | q21 : int(1..4)]), - and([x_Occurrence[q22] -> - or([q24 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q24] = q22 - | q24 : int(1..4)]) - | q22 : int(1..4)]), - and([q26 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q26]] - | q26 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_2_3_1_3-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_2_3_1_3-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_3_1_3-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_2_3_1_3-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_2_3_1_3-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_3_1_3-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_2_3_1_3.eprime b/tests/exhaustive/basic/set06/expected/model_2_3_1_3.eprime deleted file mode 100644 index 38b040fe91..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_3_1_3.eprime +++ /dev/null @@ -1,43 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_Occurrence: matrix indexed by [int(1..4)] of bool -branching on - [x_Occurrence, x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] -such that - or([x_ExplicitVarSizeWithDummy[q28] != 5 /\ x_ExplicitVarSizeWithDummy[q28] = 1 | q28 : int(1..4)]), - or([q30 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q30] = 2 | q30 : int(1..4)]), - x_Occurrence[3], - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 5 - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q2] = 5 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 5) | q3 : int(1..4)]) <= 4, - and([q5 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q5] < x_ExplicitVarSizeWithMarker_Values[q5 + 1] - | q5 : int(1..3)]), - and([q6 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q6] = 1 | q6 : int(1..4)]), - x_ExplicitVarSizeWithMarker_Marker <= 4, - and([q9 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q11] != 5 /\ - x_ExplicitVarSizeWithDummy[q11] = x_ExplicitVarSizeWithMarker_Values[q9] - | q11 : int(1..4)]) - | q9 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q13] != 5 -> - or([q15 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q15] = x_ExplicitVarSizeWithDummy[q13] - | q15 : int(1..4)]) - | q13 : int(1..4)]), - sum([toInt(x_Occurrence[q16]) | q16 : int(1..4)]) <= 4, - and([x_Occurrence[q17] -> - or([x_ExplicitVarSizeWithDummy[q19] != 5 /\ x_ExplicitVarSizeWithDummy[q19] = q17 | q19 : int(1..4)]) - | q17 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q21] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q21]] | q21 : int(1..4)]), - and([x_Occurrence[q22] -> - or([q24 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q24] = q22 - | q24 : int(1..4)]) - | q22 : int(1..4)]), - and([q26 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q26]] - | q26 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_2_3_1_4-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_2_3_1_4-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_3_1_4-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_2_3_1_4-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_2_3_1_4-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_3_1_4-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_2_3_1_4.eprime b/tests/exhaustive/basic/set06/expected/model_2_3_1_4.eprime deleted file mode 100644 index 02a7c6a35f..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_3_1_4.eprime +++ /dev/null @@ -1,78 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_Occurrence: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy, - x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_Occurrence] -such that - or([x_ExplicitVarSizeWithDummy[q54] != 5 /\ x_ExplicitVarSizeWithDummy[q54] = 1 | q54 : int(1..4)]), - or([q56 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q56] = 2 | q56 : int(1..4)]), - x_Occurrence[3], - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 5 - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q2] = 5 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 5) | q3 : int(1..4)]) <= 4, - and([q5 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q5] < x_ExplicitVarSizeWithMarker_Values[q5 + 1] - | q5 : int(1..3)]), - and([q6 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q6] = 1 | q6 : int(1..4)]), - x_ExplicitVarSizeWithMarker_Marker <= 4, - and([q9 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q11] != 5 /\ - x_ExplicitVarSizeWithDummy[q11] = x_ExplicitVarSizeWithMarker_Values[q9] - | q11 : int(1..4)]) - | q9 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q13] != 5 -> - or([q15 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q15] = x_ExplicitVarSizeWithDummy[q13] - | q15 : int(1..4)]) - | q13 : int(1..4)]), - sum([toInt(x_Occurrence[q16]) | q16 : int(1..4)]) <= 4, - and([x_Occurrence[q43] -> - or([x_ExplicitVarSizeWithDummy[q45] != 5 /\ x_ExplicitVarSizeWithDummy[q45] = q43 | q45 : int(1..4)]) - | q43 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q47] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q47]] | q47 : int(1..4)]), - and([x_Occurrence[q48] -> - or([q50 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q50] = q48 - | q50 : int(1..4)]) - | q48 : int(1..4)]), - and([q52 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q52]] - | q52 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q17 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q17] < x_ExplicitVarSizeWithFlags_Values[q17 + 1] - | q17 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q18] = false -> x_ExplicitVarSizeWithFlags_Values[q18] = 1 - | q18 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q19 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q19] | q19 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q20]) | q20 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithFlags_Flags[q23] -> - or([x_ExplicitVarSizeWithDummy[q25] != 5 /\ - x_ExplicitVarSizeWithDummy[q25] = x_ExplicitVarSizeWithFlags_Values[q23] - | q25 : int(1..4)]) - | q23 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q27] != 5 -> - or([x_ExplicitVarSizeWithFlags_Flags[q29] /\ - x_ExplicitVarSizeWithFlags_Values[q29] = x_ExplicitVarSizeWithDummy[q27] - | q29 : int(1..4)]) - | q27 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q31] -> - or([q33 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q33] = x_ExplicitVarSizeWithFlags_Values[q31] - | q33 : int(1..4)]) - | q31 : int(1..4)]), - and([q35 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q37] /\ - x_ExplicitVarSizeWithFlags_Values[q37] = x_ExplicitVarSizeWithMarker_Values[q35] - | q37 : int(1..4)]) - | q35 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q39] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q39]] - | q39 : int(1..4)]), - and([x_Occurrence[q40] -> - or([x_ExplicitVarSizeWithFlags_Flags[q42] /\ x_ExplicitVarSizeWithFlags_Values[q42] = q40 | q42 : int(1..4)]) - | q40 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_2_3_2_1-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_2_3_2_1-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_3_2_1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_2_3_2_1-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_2_3_2_1-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_3_2_1-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_2_3_2_1.eprime b/tests/exhaustive/basic/set06/expected/model_2_3_2_1.eprime deleted file mode 100644 index 69afb8a756..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_3_2_1.eprime +++ /dev/null @@ -1,43 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_Occurrence: matrix indexed by [int(1..4)] of bool -branching on - [x_Occurrence, x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] -such that - or([x_ExplicitVarSizeWithDummy[q28] != 5 /\ x_ExplicitVarSizeWithDummy[q28] = 1 | q28 : int(1..4)]), - or([q30 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q30] = 2 | q30 : int(1..4)]), - or([x_ExplicitVarSizeWithDummy[q32] != 5 /\ x_ExplicitVarSizeWithDummy[q32] = 3 | q32 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 5 - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q2] = 5 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 5) | q3 : int(1..4)]) <= 4, - and([q5 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q5] < x_ExplicitVarSizeWithMarker_Values[q5 + 1] - | q5 : int(1..3)]), - and([q6 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q6] = 1 | q6 : int(1..4)]), - x_ExplicitVarSizeWithMarker_Marker <= 4, - and([q9 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q11] != 5 /\ - x_ExplicitVarSizeWithDummy[q11] = x_ExplicitVarSizeWithMarker_Values[q9] - | q11 : int(1..4)]) - | q9 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q13] != 5 -> - or([q15 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q15] = x_ExplicitVarSizeWithDummy[q13] - | q15 : int(1..4)]) - | q13 : int(1..4)]), - sum([toInt(x_Occurrence[q16]) | q16 : int(1..4)]) <= 4, - and([x_Occurrence[q17] -> - or([x_ExplicitVarSizeWithDummy[q19] != 5 /\ x_ExplicitVarSizeWithDummy[q19] = q17 | q19 : int(1..4)]) - | q17 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q21] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q21]] | q21 : int(1..4)]), - and([x_Occurrence[q22] -> - or([q24 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q24] = q22 - | q24 : int(1..4)]) - | q22 : int(1..4)]), - and([q26 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q26]] - | q26 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_2_3_2_2-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_2_3_2_2-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_3_2_2-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_2_3_2_2-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_2_3_2_2-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_3_2_2-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_2_3_2_2.eprime b/tests/exhaustive/basic/set06/expected/model_2_3_2_2.eprime deleted file mode 100644 index 9902fda506..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_3_2_2.eprime +++ /dev/null @@ -1,30 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -branching on [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy] -such that - or([x_ExplicitVarSizeWithDummy[q17] != 5 /\ x_ExplicitVarSizeWithDummy[q17] = 1 | q17 : int(1..4)]), - or([q19 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q19] = 2 | q19 : int(1..4)]), - or([x_ExplicitVarSizeWithDummy[q21] != 5 /\ x_ExplicitVarSizeWithDummy[q21] = 3 | q21 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 5 - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q2] = 5 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 5) | q3 : int(1..4)]) <= 4, - and([q5 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q5] < x_ExplicitVarSizeWithMarker_Values[q5 + 1] - | q5 : int(1..3)]), - and([q6 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q6] = 1 | q6 : int(1..4)]), - x_ExplicitVarSizeWithMarker_Marker <= 4, - and([q9 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q11] != 5 /\ - x_ExplicitVarSizeWithDummy[q11] = x_ExplicitVarSizeWithMarker_Values[q9] - | q11 : int(1..4)]) - | q9 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q13] != 5 -> - or([q15 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q15] = x_ExplicitVarSizeWithDummy[q13] - | q15 : int(1..4)]) - | q13 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_2_3_2_3-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_2_3_2_3-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_3_2_3-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_2_3_2_3-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_2_3_2_3-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_3_2_3-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_2_3_2_3.eprime b/tests/exhaustive/basic/set06/expected/model_2_3_2_3.eprime deleted file mode 100644 index 9902fda506..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_3_2_3.eprime +++ /dev/null @@ -1,30 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -branching on [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy] -such that - or([x_ExplicitVarSizeWithDummy[q17] != 5 /\ x_ExplicitVarSizeWithDummy[q17] = 1 | q17 : int(1..4)]), - or([q19 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q19] = 2 | q19 : int(1..4)]), - or([x_ExplicitVarSizeWithDummy[q21] != 5 /\ x_ExplicitVarSizeWithDummy[q21] = 3 | q21 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 5 - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q2] = 5 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 5) | q3 : int(1..4)]) <= 4, - and([q5 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q5] < x_ExplicitVarSizeWithMarker_Values[q5 + 1] - | q5 : int(1..3)]), - and([q6 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q6] = 1 | q6 : int(1..4)]), - x_ExplicitVarSizeWithMarker_Marker <= 4, - and([q9 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q11] != 5 /\ - x_ExplicitVarSizeWithDummy[q11] = x_ExplicitVarSizeWithMarker_Values[q9] - | q11 : int(1..4)]) - | q9 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q13] != 5 -> - or([q15 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q15] = x_ExplicitVarSizeWithDummy[q13] - | q15 : int(1..4)]) - | q13 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_2_3_2_4-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_2_3_2_4-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_3_2_4-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_2_3_2_4-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_2_3_2_4-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_3_2_4-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_2_3_2_4.eprime b/tests/exhaustive/basic/set06/expected/model_2_3_2_4.eprime deleted file mode 100644 index 5697b5087d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_3_2_4.eprime +++ /dev/null @@ -1,61 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy, - x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] -such that - or([x_ExplicitVarSizeWithDummy[q38] != 5 /\ x_ExplicitVarSizeWithDummy[q38] = 1 | q38 : int(1..4)]), - or([q40 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q40] = 2 | q40 : int(1..4)]), - or([x_ExplicitVarSizeWithDummy[q42] != 5 /\ x_ExplicitVarSizeWithDummy[q42] = 3 | q42 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 5 - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q2] = 5 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 5) | q3 : int(1..4)]) <= 4, - and([q5 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q5] < x_ExplicitVarSizeWithMarker_Values[q5 + 1] - | q5 : int(1..3)]), - and([q6 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q6] = 1 | q6 : int(1..4)]), - x_ExplicitVarSizeWithMarker_Marker <= 4, - and([q9 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q11] != 5 /\ - x_ExplicitVarSizeWithDummy[q11] = x_ExplicitVarSizeWithMarker_Values[q9] - | q11 : int(1..4)]) - | q9 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q13] != 5 -> - or([q15 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q15] = x_ExplicitVarSizeWithDummy[q13] - | q15 : int(1..4)]) - | q13 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q16 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q16] < x_ExplicitVarSizeWithFlags_Values[q16 + 1] - | q16 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q17] = false -> x_ExplicitVarSizeWithFlags_Values[q17] = 1 - | q17 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q18 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q18] | q18 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q19]) | q19 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithFlags_Flags[q22] -> - or([x_ExplicitVarSizeWithDummy[q24] != 5 /\ - x_ExplicitVarSizeWithDummy[q24] = x_ExplicitVarSizeWithFlags_Values[q22] - | q24 : int(1..4)]) - | q22 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q26] != 5 -> - or([x_ExplicitVarSizeWithFlags_Flags[q28] /\ - x_ExplicitVarSizeWithFlags_Values[q28] = x_ExplicitVarSizeWithDummy[q26] - | q28 : int(1..4)]) - | q26 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q30] -> - or([q32 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q32] = x_ExplicitVarSizeWithFlags_Values[q30] - | q32 : int(1..4)]) - | q30 : int(1..4)]), - and([q34 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q36] /\ - x_ExplicitVarSizeWithFlags_Values[q36] = x_ExplicitVarSizeWithMarker_Values[q34] - | q36 : int(1..4)]) - | q34 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_2_3_3_1-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_2_3_3_1-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_3_3_1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_2_3_3_1-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_2_3_3_1-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_3_3_1-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_2_3_3_1.eprime b/tests/exhaustive/basic/set06/expected/model_2_3_3_1.eprime deleted file mode 100644 index 37607392b7..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_3_3_1.eprime +++ /dev/null @@ -1,43 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_Occurrence: matrix indexed by [int(1..4)] of bool -branching on - [x_Occurrence, x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] -such that - or([x_ExplicitVarSizeWithDummy[q28] != 5 /\ x_ExplicitVarSizeWithDummy[q28] = 1 | q28 : int(1..4)]), - or([q30 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q30] = 2 | q30 : int(1..4)]), - or([q32 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q32] = 3 | q32 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 5 - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q2] = 5 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 5) | q3 : int(1..4)]) <= 4, - and([q5 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q5] < x_ExplicitVarSizeWithMarker_Values[q5 + 1] - | q5 : int(1..3)]), - and([q6 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q6] = 1 | q6 : int(1..4)]), - x_ExplicitVarSizeWithMarker_Marker <= 4, - and([q9 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q11] != 5 /\ - x_ExplicitVarSizeWithDummy[q11] = x_ExplicitVarSizeWithMarker_Values[q9] - | q11 : int(1..4)]) - | q9 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q13] != 5 -> - or([q15 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q15] = x_ExplicitVarSizeWithDummy[q13] - | q15 : int(1..4)]) - | q13 : int(1..4)]), - sum([toInt(x_Occurrence[q16]) | q16 : int(1..4)]) <= 4, - and([x_Occurrence[q17] -> - or([x_ExplicitVarSizeWithDummy[q19] != 5 /\ x_ExplicitVarSizeWithDummy[q19] = q17 | q19 : int(1..4)]) - | q17 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q21] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q21]] | q21 : int(1..4)]), - and([x_Occurrence[q22] -> - or([q24 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q24] = q22 - | q24 : int(1..4)]) - | q22 : int(1..4)]), - and([q26 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q26]] - | q26 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_2_3_3_2-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_2_3_3_2-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_3_3_2-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_2_3_3_2-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_2_3_3_2-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_3_3_2-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_2_3_3_2.eprime b/tests/exhaustive/basic/set06/expected/model_2_3_3_2.eprime deleted file mode 100644 index 1f36b524f8..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_3_3_2.eprime +++ /dev/null @@ -1,30 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -branching on [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy] -such that - or([x_ExplicitVarSizeWithDummy[q17] != 5 /\ x_ExplicitVarSizeWithDummy[q17] = 1 | q17 : int(1..4)]), - or([q19 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q19] = 2 | q19 : int(1..4)]), - or([q21 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q21] = 3 | q21 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 5 - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q2] = 5 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 5) | q3 : int(1..4)]) <= 4, - and([q5 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q5] < x_ExplicitVarSizeWithMarker_Values[q5 + 1] - | q5 : int(1..3)]), - and([q6 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q6] = 1 | q6 : int(1..4)]), - x_ExplicitVarSizeWithMarker_Marker <= 4, - and([q9 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q11] != 5 /\ - x_ExplicitVarSizeWithDummy[q11] = x_ExplicitVarSizeWithMarker_Values[q9] - | q11 : int(1..4)]) - | q9 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q13] != 5 -> - or([q15 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q15] = x_ExplicitVarSizeWithDummy[q13] - | q15 : int(1..4)]) - | q13 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_2_3_3_3-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_2_3_3_3-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_3_3_3-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_2_3_3_3-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_2_3_3_3-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_3_3_3-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_2_3_3_3.eprime b/tests/exhaustive/basic/set06/expected/model_2_3_3_3.eprime deleted file mode 100644 index 1f36b524f8..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_3_3_3.eprime +++ /dev/null @@ -1,30 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -branching on [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy] -such that - or([x_ExplicitVarSizeWithDummy[q17] != 5 /\ x_ExplicitVarSizeWithDummy[q17] = 1 | q17 : int(1..4)]), - or([q19 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q19] = 2 | q19 : int(1..4)]), - or([q21 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q21] = 3 | q21 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 5 - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q2] = 5 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 5) | q3 : int(1..4)]) <= 4, - and([q5 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q5] < x_ExplicitVarSizeWithMarker_Values[q5 + 1] - | q5 : int(1..3)]), - and([q6 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q6] = 1 | q6 : int(1..4)]), - x_ExplicitVarSizeWithMarker_Marker <= 4, - and([q9 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q11] != 5 /\ - x_ExplicitVarSizeWithDummy[q11] = x_ExplicitVarSizeWithMarker_Values[q9] - | q11 : int(1..4)]) - | q9 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q13] != 5 -> - or([q15 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q15] = x_ExplicitVarSizeWithDummy[q13] - | q15 : int(1..4)]) - | q13 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_2_3_3_4-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_2_3_3_4-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_3_3_4-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_2_3_3_4-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_2_3_3_4-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_3_3_4-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_2_3_3_4.eprime b/tests/exhaustive/basic/set06/expected/model_2_3_3_4.eprime deleted file mode 100644 index b9010e4669..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_3_3_4.eprime +++ /dev/null @@ -1,61 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy, - x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] -such that - or([x_ExplicitVarSizeWithDummy[q38] != 5 /\ x_ExplicitVarSizeWithDummy[q38] = 1 | q38 : int(1..4)]), - or([q40 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q40] = 2 | q40 : int(1..4)]), - or([q42 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q42] = 3 | q42 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 5 - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q2] = 5 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 5) | q3 : int(1..4)]) <= 4, - and([q5 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q5] < x_ExplicitVarSizeWithMarker_Values[q5 + 1] - | q5 : int(1..3)]), - and([q6 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q6] = 1 | q6 : int(1..4)]), - x_ExplicitVarSizeWithMarker_Marker <= 4, - and([q9 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q11] != 5 /\ - x_ExplicitVarSizeWithDummy[q11] = x_ExplicitVarSizeWithMarker_Values[q9] - | q11 : int(1..4)]) - | q9 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q13] != 5 -> - or([q15 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q15] = x_ExplicitVarSizeWithDummy[q13] - | q15 : int(1..4)]) - | q13 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q16 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q16] < x_ExplicitVarSizeWithFlags_Values[q16 + 1] - | q16 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q17] = false -> x_ExplicitVarSizeWithFlags_Values[q17] = 1 - | q17 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q18 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q18] | q18 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q19]) | q19 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithFlags_Flags[q22] -> - or([x_ExplicitVarSizeWithDummy[q24] != 5 /\ - x_ExplicitVarSizeWithDummy[q24] = x_ExplicitVarSizeWithFlags_Values[q22] - | q24 : int(1..4)]) - | q22 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q26] != 5 -> - or([x_ExplicitVarSizeWithFlags_Flags[q28] /\ - x_ExplicitVarSizeWithFlags_Values[q28] = x_ExplicitVarSizeWithDummy[q26] - | q28 : int(1..4)]) - | q26 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q30] -> - or([q32 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q32] = x_ExplicitVarSizeWithFlags_Values[q30] - | q32 : int(1..4)]) - | q30 : int(1..4)]), - and([q34 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q36] /\ - x_ExplicitVarSizeWithFlags_Values[q36] = x_ExplicitVarSizeWithMarker_Values[q34] - | q36 : int(1..4)]) - | q34 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_2_3_4_1-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_2_3_4_1-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_3_4_1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_2_3_4_1-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_2_3_4_1-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_3_4_1-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_2_3_4_1.eprime b/tests/exhaustive/basic/set06/expected/model_2_3_4_1.eprime deleted file mode 100644 index 3132c81925..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_3_4_1.eprime +++ /dev/null @@ -1,78 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_Occurrence: matrix indexed by [int(1..4)] of bool -branching on - [x_Occurrence, x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, - x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] -such that - or([x_ExplicitVarSizeWithDummy[q54] != 5 /\ x_ExplicitVarSizeWithDummy[q54] = 1 | q54 : int(1..4)]), - or([q56 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q56] = 2 | q56 : int(1..4)]), - or([x_ExplicitVarSizeWithFlags_Flags[q58] /\ x_ExplicitVarSizeWithFlags_Values[q58] = 3 | q58 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 5 - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q2] = 5 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 5) | q3 : int(1..4)]) <= 4, - and([q5 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q5] < x_ExplicitVarSizeWithMarker_Values[q5 + 1] - | q5 : int(1..3)]), - and([q6 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q6] = 1 | q6 : int(1..4)]), - x_ExplicitVarSizeWithMarker_Marker <= 4, - and([q9 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q11] != 5 /\ - x_ExplicitVarSizeWithDummy[q11] = x_ExplicitVarSizeWithMarker_Values[q9] - | q11 : int(1..4)]) - | q9 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q13] != 5 -> - or([q15 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q15] = x_ExplicitVarSizeWithDummy[q13] - | q15 : int(1..4)]) - | q13 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q16 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q16] < x_ExplicitVarSizeWithFlags_Values[q16 + 1] - | q16 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q17] = false -> x_ExplicitVarSizeWithFlags_Values[q17] = 1 - | q17 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q18 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q18] | q18 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q19]) | q19 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithFlags_Flags[q22] -> - or([x_ExplicitVarSizeWithDummy[q24] != 5 /\ - x_ExplicitVarSizeWithDummy[q24] = x_ExplicitVarSizeWithFlags_Values[q22] - | q24 : int(1..4)]) - | q22 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q26] != 5 -> - or([x_ExplicitVarSizeWithFlags_Flags[q28] /\ - x_ExplicitVarSizeWithFlags_Values[q28] = x_ExplicitVarSizeWithDummy[q26] - | q28 : int(1..4)]) - | q26 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q30] -> - or([q32 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q32] = x_ExplicitVarSizeWithFlags_Values[q30] - | q32 : int(1..4)]) - | q30 : int(1..4)]), - and([q34 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q36] /\ - x_ExplicitVarSizeWithFlags_Values[q36] = x_ExplicitVarSizeWithMarker_Values[q34] - | q36 : int(1..4)]) - | q34 : int(1..4)]), - sum([toInt(x_Occurrence[q37]) | q37 : int(1..4)]) <= 4, - and([x_Occurrence[q38] -> - or([x_ExplicitVarSizeWithDummy[q40] != 5 /\ x_ExplicitVarSizeWithDummy[q40] = q38 | q40 : int(1..4)]) - | q38 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q42] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q42]] | q42 : int(1..4)]), - and([x_Occurrence[q43] -> - or([q45 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q45] = q43 - | q45 : int(1..4)]) - | q43 : int(1..4)]), - and([q47 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q47]] - | q47 : int(1..4)]), - and([x_Occurrence[q48] -> - or([x_ExplicitVarSizeWithFlags_Flags[q50] /\ x_ExplicitVarSizeWithFlags_Values[q50] = q48 | q50 : int(1..4)]) - | q48 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q52] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q52]] - | q52 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_2_3_4_2-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_2_3_4_2-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_3_4_2-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_2_3_4_2-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_2_3_4_2-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_3_4_2-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_2_3_4_2.eprime b/tests/exhaustive/basic/set06/expected/model_2_3_4_2.eprime deleted file mode 100644 index 1359af27c8..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_3_4_2.eprime +++ /dev/null @@ -1,61 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy, - x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] -such that - or([x_ExplicitVarSizeWithDummy[q38] != 5 /\ x_ExplicitVarSizeWithDummy[q38] = 1 | q38 : int(1..4)]), - or([q40 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q40] = 2 | q40 : int(1..4)]), - or([x_ExplicitVarSizeWithFlags_Flags[q42] /\ x_ExplicitVarSizeWithFlags_Values[q42] = 3 | q42 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 5 - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q2] = 5 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 5) | q3 : int(1..4)]) <= 4, - and([q5 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q5] < x_ExplicitVarSizeWithMarker_Values[q5 + 1] - | q5 : int(1..3)]), - and([q6 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q6] = 1 | q6 : int(1..4)]), - x_ExplicitVarSizeWithMarker_Marker <= 4, - and([q9 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q11] != 5 /\ - x_ExplicitVarSizeWithDummy[q11] = x_ExplicitVarSizeWithMarker_Values[q9] - | q11 : int(1..4)]) - | q9 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q13] != 5 -> - or([q15 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q15] = x_ExplicitVarSizeWithDummy[q13] - | q15 : int(1..4)]) - | q13 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q16 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q16] < x_ExplicitVarSizeWithFlags_Values[q16 + 1] - | q16 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q17] = false -> x_ExplicitVarSizeWithFlags_Values[q17] = 1 - | q17 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q18 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q18] | q18 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q19]) | q19 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithFlags_Flags[q22] -> - or([x_ExplicitVarSizeWithDummy[q24] != 5 /\ - x_ExplicitVarSizeWithDummy[q24] = x_ExplicitVarSizeWithFlags_Values[q22] - | q24 : int(1..4)]) - | q22 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q26] != 5 -> - or([x_ExplicitVarSizeWithFlags_Flags[q28] /\ - x_ExplicitVarSizeWithFlags_Values[q28] = x_ExplicitVarSizeWithDummy[q26] - | q28 : int(1..4)]) - | q26 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q30] -> - or([q32 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q32] = x_ExplicitVarSizeWithFlags_Values[q30] - | q32 : int(1..4)]) - | q30 : int(1..4)]), - and([q34 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q36] /\ - x_ExplicitVarSizeWithFlags_Values[q36] = x_ExplicitVarSizeWithMarker_Values[q34] - | q36 : int(1..4)]) - | q34 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_2_3_4_3-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_2_3_4_3-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_3_4_3-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_2_3_4_3-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_2_3_4_3-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_3_4_3-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_2_3_4_3.eprime b/tests/exhaustive/basic/set06/expected/model_2_3_4_3.eprime deleted file mode 100644 index 1359af27c8..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_3_4_3.eprime +++ /dev/null @@ -1,61 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy, - x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] -such that - or([x_ExplicitVarSizeWithDummy[q38] != 5 /\ x_ExplicitVarSizeWithDummy[q38] = 1 | q38 : int(1..4)]), - or([q40 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q40] = 2 | q40 : int(1..4)]), - or([x_ExplicitVarSizeWithFlags_Flags[q42] /\ x_ExplicitVarSizeWithFlags_Values[q42] = 3 | q42 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 5 - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q2] = 5 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 5) | q3 : int(1..4)]) <= 4, - and([q5 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q5] < x_ExplicitVarSizeWithMarker_Values[q5 + 1] - | q5 : int(1..3)]), - and([q6 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q6] = 1 | q6 : int(1..4)]), - x_ExplicitVarSizeWithMarker_Marker <= 4, - and([q9 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q11] != 5 /\ - x_ExplicitVarSizeWithDummy[q11] = x_ExplicitVarSizeWithMarker_Values[q9] - | q11 : int(1..4)]) - | q9 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q13] != 5 -> - or([q15 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q15] = x_ExplicitVarSizeWithDummy[q13] - | q15 : int(1..4)]) - | q13 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q16 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q16] < x_ExplicitVarSizeWithFlags_Values[q16 + 1] - | q16 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q17] = false -> x_ExplicitVarSizeWithFlags_Values[q17] = 1 - | q17 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q18 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q18] | q18 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q19]) | q19 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithFlags_Flags[q22] -> - or([x_ExplicitVarSizeWithDummy[q24] != 5 /\ - x_ExplicitVarSizeWithDummy[q24] = x_ExplicitVarSizeWithFlags_Values[q22] - | q24 : int(1..4)]) - | q22 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q26] != 5 -> - or([x_ExplicitVarSizeWithFlags_Flags[q28] /\ - x_ExplicitVarSizeWithFlags_Values[q28] = x_ExplicitVarSizeWithDummy[q26] - | q28 : int(1..4)]) - | q26 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q30] -> - or([q32 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q32] = x_ExplicitVarSizeWithFlags_Values[q30] - | q32 : int(1..4)]) - | q30 : int(1..4)]), - and([q34 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q36] /\ - x_ExplicitVarSizeWithFlags_Values[q36] = x_ExplicitVarSizeWithMarker_Values[q34] - | q36 : int(1..4)]) - | q34 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_2_3_4_4-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_2_3_4_4-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_3_4_4-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_2_3_4_4-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_2_3_4_4-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_3_4_4-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_2_3_4_4.eprime b/tests/exhaustive/basic/set06/expected/model_2_3_4_4.eprime deleted file mode 100644 index 1359af27c8..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_3_4_4.eprime +++ /dev/null @@ -1,61 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy, - x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] -such that - or([x_ExplicitVarSizeWithDummy[q38] != 5 /\ x_ExplicitVarSizeWithDummy[q38] = 1 | q38 : int(1..4)]), - or([q40 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q40] = 2 | q40 : int(1..4)]), - or([x_ExplicitVarSizeWithFlags_Flags[q42] /\ x_ExplicitVarSizeWithFlags_Values[q42] = 3 | q42 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 5 - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q2] = 5 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 5) | q3 : int(1..4)]) <= 4, - and([q5 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q5] < x_ExplicitVarSizeWithMarker_Values[q5 + 1] - | q5 : int(1..3)]), - and([q6 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q6] = 1 | q6 : int(1..4)]), - x_ExplicitVarSizeWithMarker_Marker <= 4, - and([q9 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q11] != 5 /\ - x_ExplicitVarSizeWithDummy[q11] = x_ExplicitVarSizeWithMarker_Values[q9] - | q11 : int(1..4)]) - | q9 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q13] != 5 -> - or([q15 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q15] = x_ExplicitVarSizeWithDummy[q13] - | q15 : int(1..4)]) - | q13 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q16 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q16] < x_ExplicitVarSizeWithFlags_Values[q16 + 1] - | q16 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q17] = false -> x_ExplicitVarSizeWithFlags_Values[q17] = 1 - | q17 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q18 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q18] | q18 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q19]) | q19 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithFlags_Flags[q22] -> - or([x_ExplicitVarSizeWithDummy[q24] != 5 /\ - x_ExplicitVarSizeWithDummy[q24] = x_ExplicitVarSizeWithFlags_Values[q22] - | q24 : int(1..4)]) - | q22 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q26] != 5 -> - or([x_ExplicitVarSizeWithFlags_Flags[q28] /\ - x_ExplicitVarSizeWithFlags_Values[q28] = x_ExplicitVarSizeWithDummy[q26] - | q28 : int(1..4)]) - | q26 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q30] -> - or([q32 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q32] = x_ExplicitVarSizeWithFlags_Values[q30] - | q32 : int(1..4)]) - | q30 : int(1..4)]), - and([q34 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q36] /\ - x_ExplicitVarSizeWithFlags_Values[q36] = x_ExplicitVarSizeWithMarker_Values[q34] - | q36 : int(1..4)]) - | q34 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_2_4_1_1-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_2_4_1_1-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_4_1_1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_2_4_1_1-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_2_4_1_1-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_4_1_1-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_2_4_1_1.eprime b/tests/exhaustive/basic/set06/expected/model_2_4_1_1.eprime deleted file mode 100644 index 632496e075..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_4_1_1.eprime +++ /dev/null @@ -1,43 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_Occurrence: matrix indexed by [int(1..4)] of bool -branching on - [x_Occurrence, x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] -such that - or([x_ExplicitVarSizeWithDummy[q30] != 5 /\ x_ExplicitVarSizeWithDummy[q30] = 1 | q30 : int(1..4)]), - or([x_ExplicitVarSizeWithFlags_Flags[q32] /\ x_ExplicitVarSizeWithFlags_Values[q32] = 2 | q32 : int(1..4)]), - x_Occurrence[3], - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 5 - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q2] = 5 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 5) | q3 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithFlags_Flags[q5 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q5] < x_ExplicitVarSizeWithFlags_Values[q5 + 1] - | q5 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q6] = false -> x_ExplicitVarSizeWithFlags_Values[q6] = 1 | q6 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q7] | q7 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q8]) | q8 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithFlags_Flags[q11] -> - or([x_ExplicitVarSizeWithDummy[q13] != 5 /\ - x_ExplicitVarSizeWithDummy[q13] = x_ExplicitVarSizeWithFlags_Values[q11] - | q13 : int(1..4)]) - | q11 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q15] != 5 -> - or([x_ExplicitVarSizeWithFlags_Flags[q17] /\ - x_ExplicitVarSizeWithFlags_Values[q17] = x_ExplicitVarSizeWithDummy[q15] - | q17 : int(1..4)]) - | q15 : int(1..4)]), - sum([toInt(x_Occurrence[q18]) | q18 : int(1..4)]) <= 4, - and([x_Occurrence[q19] -> - or([x_ExplicitVarSizeWithDummy[q21] != 5 /\ x_ExplicitVarSizeWithDummy[q21] = q19 | q21 : int(1..4)]) - | q19 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q23] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q23]] | q23 : int(1..4)]), - and([x_Occurrence[q24] -> - or([x_ExplicitVarSizeWithFlags_Flags[q26] /\ x_ExplicitVarSizeWithFlags_Values[q26] = q24 | q26 : int(1..4)]) - | q24 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q28] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q28]] - | q28 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_2_4_1_2-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_2_4_1_2-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_4_1_2-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_2_4_1_2-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_2_4_1_2-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_4_1_2-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_2_4_1_2.eprime b/tests/exhaustive/basic/set06/expected/model_2_4_1_2.eprime deleted file mode 100644 index 632496e075..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_4_1_2.eprime +++ /dev/null @@ -1,43 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_Occurrence: matrix indexed by [int(1..4)] of bool -branching on - [x_Occurrence, x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] -such that - or([x_ExplicitVarSizeWithDummy[q30] != 5 /\ x_ExplicitVarSizeWithDummy[q30] = 1 | q30 : int(1..4)]), - or([x_ExplicitVarSizeWithFlags_Flags[q32] /\ x_ExplicitVarSizeWithFlags_Values[q32] = 2 | q32 : int(1..4)]), - x_Occurrence[3], - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 5 - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q2] = 5 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 5) | q3 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithFlags_Flags[q5 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q5] < x_ExplicitVarSizeWithFlags_Values[q5 + 1] - | q5 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q6] = false -> x_ExplicitVarSizeWithFlags_Values[q6] = 1 | q6 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q7] | q7 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q8]) | q8 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithFlags_Flags[q11] -> - or([x_ExplicitVarSizeWithDummy[q13] != 5 /\ - x_ExplicitVarSizeWithDummy[q13] = x_ExplicitVarSizeWithFlags_Values[q11] - | q13 : int(1..4)]) - | q11 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q15] != 5 -> - or([x_ExplicitVarSizeWithFlags_Flags[q17] /\ - x_ExplicitVarSizeWithFlags_Values[q17] = x_ExplicitVarSizeWithDummy[q15] - | q17 : int(1..4)]) - | q15 : int(1..4)]), - sum([toInt(x_Occurrence[q18]) | q18 : int(1..4)]) <= 4, - and([x_Occurrence[q19] -> - or([x_ExplicitVarSizeWithDummy[q21] != 5 /\ x_ExplicitVarSizeWithDummy[q21] = q19 | q21 : int(1..4)]) - | q19 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q23] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q23]] | q23 : int(1..4)]), - and([x_Occurrence[q24] -> - or([x_ExplicitVarSizeWithFlags_Flags[q26] /\ x_ExplicitVarSizeWithFlags_Values[q26] = q24 | q26 : int(1..4)]) - | q24 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q28] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q28]] - | q28 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_2_4_1_3-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_2_4_1_3-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_4_1_3-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_2_4_1_3-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_2_4_1_3-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_4_1_3-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_2_4_1_3.eprime b/tests/exhaustive/basic/set06/expected/model_2_4_1_3.eprime deleted file mode 100644 index 1e494d1026..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_4_1_3.eprime +++ /dev/null @@ -1,77 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_Occurrence: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy, - x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_Occurrence] -such that - or([x_ExplicitVarSizeWithDummy[q54] != 5 /\ x_ExplicitVarSizeWithDummy[q54] = 1 | q54 : int(1..4)]), - or([x_ExplicitVarSizeWithFlags_Flags[q56] /\ x_ExplicitVarSizeWithFlags_Values[q56] = 2 | q56 : int(1..4)]), - x_Occurrence[3], - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 5 - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q2] = 5 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 5) | q3 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithFlags_Flags[q5 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q5] < x_ExplicitVarSizeWithFlags_Values[q5 + 1] - | q5 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q6] = false -> x_ExplicitVarSizeWithFlags_Values[q6] = 1 | q6 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q7] | q7 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q8]) | q8 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithFlags_Flags[q11] -> - or([x_ExplicitVarSizeWithDummy[q13] != 5 /\ - x_ExplicitVarSizeWithDummy[q13] = x_ExplicitVarSizeWithFlags_Values[q11] - | q13 : int(1..4)]) - | q11 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q15] != 5 -> - or([x_ExplicitVarSizeWithFlags_Flags[q17] /\ - x_ExplicitVarSizeWithFlags_Values[q17] = x_ExplicitVarSizeWithDummy[q15] - | q17 : int(1..4)]) - | q15 : int(1..4)]), - sum([toInt(x_Occurrence[q18]) | q18 : int(1..4)]) <= 4, - and([x_Occurrence[q43] -> - or([x_ExplicitVarSizeWithDummy[q45] != 5 /\ x_ExplicitVarSizeWithDummy[q45] = q43 | q45 : int(1..4)]) - | q43 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q47] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q47]] | q47 : int(1..4)]), - and([x_Occurrence[q48] -> - or([x_ExplicitVarSizeWithFlags_Flags[q50] /\ x_ExplicitVarSizeWithFlags_Values[q50] = q48 | q50 : int(1..4)]) - | q48 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q52] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q52]] - | q52 : int(1..4)]), - and([q19 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q19] < x_ExplicitVarSizeWithMarker_Values[q19 + 1] - | q19 : int(1..3)]), - and([q20 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q20] = 1 | q20 : int(1..4)]), - x_ExplicitVarSizeWithMarker_Marker <= 4, - and([q23 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q25] != 5 /\ - x_ExplicitVarSizeWithDummy[q25] = x_ExplicitVarSizeWithMarker_Values[q23] - | q25 : int(1..4)]) - | q23 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q27] != 5 -> - or([q29 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q29] = x_ExplicitVarSizeWithDummy[q27] - | q29 : int(1..4)]) - | q27 : int(1..4)]), - and([q31 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q33] /\ - x_ExplicitVarSizeWithFlags_Values[q33] = x_ExplicitVarSizeWithMarker_Values[q31] - | q33 : int(1..4)]) - | q31 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q35] -> - or([q37 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q37] = x_ExplicitVarSizeWithFlags_Values[q35] - | q37 : int(1..4)]) - | q35 : int(1..4)]), - and([q39 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q39]] - | q39 : int(1..4)]), - and([x_Occurrence[q40] -> - or([q42 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q42] = q40 - | q42 : int(1..4)]) - | q40 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_2_4_1_4-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_2_4_1_4-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_4_1_4-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_2_4_1_4-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_2_4_1_4-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_4_1_4-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_2_4_1_4.eprime b/tests/exhaustive/basic/set06/expected/model_2_4_1_4.eprime deleted file mode 100644 index 632496e075..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_4_1_4.eprime +++ /dev/null @@ -1,43 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_Occurrence: matrix indexed by [int(1..4)] of bool -branching on - [x_Occurrence, x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] -such that - or([x_ExplicitVarSizeWithDummy[q30] != 5 /\ x_ExplicitVarSizeWithDummy[q30] = 1 | q30 : int(1..4)]), - or([x_ExplicitVarSizeWithFlags_Flags[q32] /\ x_ExplicitVarSizeWithFlags_Values[q32] = 2 | q32 : int(1..4)]), - x_Occurrence[3], - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 5 - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q2] = 5 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 5) | q3 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithFlags_Flags[q5 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q5] < x_ExplicitVarSizeWithFlags_Values[q5 + 1] - | q5 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q6] = false -> x_ExplicitVarSizeWithFlags_Values[q6] = 1 | q6 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q7] | q7 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q8]) | q8 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithFlags_Flags[q11] -> - or([x_ExplicitVarSizeWithDummy[q13] != 5 /\ - x_ExplicitVarSizeWithDummy[q13] = x_ExplicitVarSizeWithFlags_Values[q11] - | q13 : int(1..4)]) - | q11 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q15] != 5 -> - or([x_ExplicitVarSizeWithFlags_Flags[q17] /\ - x_ExplicitVarSizeWithFlags_Values[q17] = x_ExplicitVarSizeWithDummy[q15] - | q17 : int(1..4)]) - | q15 : int(1..4)]), - sum([toInt(x_Occurrence[q18]) | q18 : int(1..4)]) <= 4, - and([x_Occurrence[q19] -> - or([x_ExplicitVarSizeWithDummy[q21] != 5 /\ x_ExplicitVarSizeWithDummy[q21] = q19 | q21 : int(1..4)]) - | q19 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q23] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q23]] | q23 : int(1..4)]), - and([x_Occurrence[q24] -> - or([x_ExplicitVarSizeWithFlags_Flags[q26] /\ x_ExplicitVarSizeWithFlags_Values[q26] = q24 | q26 : int(1..4)]) - | q24 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q28] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q28]] - | q28 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_2_4_2_1-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_2_4_2_1-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_4_2_1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_2_4_2_1-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_2_4_2_1-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_4_2_1-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_2_4_2_1.eprime b/tests/exhaustive/basic/set06/expected/model_2_4_2_1.eprime deleted file mode 100644 index fc14f2c0db..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_4_2_1.eprime +++ /dev/null @@ -1,43 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_Occurrence: matrix indexed by [int(1..4)] of bool -branching on - [x_Occurrence, x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] -such that - or([x_ExplicitVarSizeWithDummy[q30] != 5 /\ x_ExplicitVarSizeWithDummy[q30] = 1 | q30 : int(1..4)]), - or([x_ExplicitVarSizeWithFlags_Flags[q32] /\ x_ExplicitVarSizeWithFlags_Values[q32] = 2 | q32 : int(1..4)]), - or([x_ExplicitVarSizeWithDummy[q34] != 5 /\ x_ExplicitVarSizeWithDummy[q34] = 3 | q34 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 5 - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q2] = 5 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 5) | q3 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithFlags_Flags[q5 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q5] < x_ExplicitVarSizeWithFlags_Values[q5 + 1] - | q5 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q6] = false -> x_ExplicitVarSizeWithFlags_Values[q6] = 1 | q6 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q7] | q7 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q8]) | q8 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithFlags_Flags[q11] -> - or([x_ExplicitVarSizeWithDummy[q13] != 5 /\ - x_ExplicitVarSizeWithDummy[q13] = x_ExplicitVarSizeWithFlags_Values[q11] - | q13 : int(1..4)]) - | q11 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q15] != 5 -> - or([x_ExplicitVarSizeWithFlags_Flags[q17] /\ - x_ExplicitVarSizeWithFlags_Values[q17] = x_ExplicitVarSizeWithDummy[q15] - | q17 : int(1..4)]) - | q15 : int(1..4)]), - sum([toInt(x_Occurrence[q18]) | q18 : int(1..4)]) <= 4, - and([x_Occurrence[q19] -> - or([x_ExplicitVarSizeWithDummy[q21] != 5 /\ x_ExplicitVarSizeWithDummy[q21] = q19 | q21 : int(1..4)]) - | q19 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q23] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q23]] | q23 : int(1..4)]), - and([x_Occurrence[q24] -> - or([x_ExplicitVarSizeWithFlags_Flags[q26] /\ x_ExplicitVarSizeWithFlags_Values[q26] = q24 | q26 : int(1..4)]) - | q24 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q28] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q28]] - | q28 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_2_4_2_2-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_2_4_2_2-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_4_2_2-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_2_4_2_2-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_2_4_2_2-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_4_2_2-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_2_4_2_2.eprime b/tests/exhaustive/basic/set06/expected/model_2_4_2_2.eprime deleted file mode 100644 index c887a723c4..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_4_2_2.eprime +++ /dev/null @@ -1,31 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -branching on [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy] -such that - or([x_ExplicitVarSizeWithDummy[q19] != 5 /\ x_ExplicitVarSizeWithDummy[q19] = 1 | q19 : int(1..4)]), - or([x_ExplicitVarSizeWithFlags_Flags[q21] /\ x_ExplicitVarSizeWithFlags_Values[q21] = 2 | q21 : int(1..4)]), - or([x_ExplicitVarSizeWithDummy[q23] != 5 /\ x_ExplicitVarSizeWithDummy[q23] = 3 | q23 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 5 - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q2] = 5 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 5) | q3 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithFlags_Flags[q5 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q5] < x_ExplicitVarSizeWithFlags_Values[q5 + 1] - | q5 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q6] = false -> x_ExplicitVarSizeWithFlags_Values[q6] = 1 | q6 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q7] | q7 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q8]) | q8 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithFlags_Flags[q11] -> - or([x_ExplicitVarSizeWithDummy[q13] != 5 /\ - x_ExplicitVarSizeWithDummy[q13] = x_ExplicitVarSizeWithFlags_Values[q11] - | q13 : int(1..4)]) - | q11 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q15] != 5 -> - or([x_ExplicitVarSizeWithFlags_Flags[q17] /\ - x_ExplicitVarSizeWithFlags_Values[q17] = x_ExplicitVarSizeWithDummy[q15] - | q17 : int(1..4)]) - | q15 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_2_4_2_3-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_2_4_2_3-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_4_2_3-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_2_4_2_3-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_2_4_2_3-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_4_2_3-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_2_4_2_3.eprime b/tests/exhaustive/basic/set06/expected/model_2_4_2_3.eprime deleted file mode 100644 index 9f009dc6b0..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_4_2_3.eprime +++ /dev/null @@ -1,60 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy, - x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] -such that - or([x_ExplicitVarSizeWithDummy[q38] != 5 /\ x_ExplicitVarSizeWithDummy[q38] = 1 | q38 : int(1..4)]), - or([x_ExplicitVarSizeWithFlags_Flags[q40] /\ x_ExplicitVarSizeWithFlags_Values[q40] = 2 | q40 : int(1..4)]), - or([x_ExplicitVarSizeWithDummy[q42] != 5 /\ x_ExplicitVarSizeWithDummy[q42] = 3 | q42 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 5 - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q2] = 5 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 5) | q3 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithFlags_Flags[q5 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q5] < x_ExplicitVarSizeWithFlags_Values[q5 + 1] - | q5 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q6] = false -> x_ExplicitVarSizeWithFlags_Values[q6] = 1 | q6 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q7] | q7 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q8]) | q8 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithFlags_Flags[q11] -> - or([x_ExplicitVarSizeWithDummy[q13] != 5 /\ - x_ExplicitVarSizeWithDummy[q13] = x_ExplicitVarSizeWithFlags_Values[q11] - | q13 : int(1..4)]) - | q11 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q15] != 5 -> - or([x_ExplicitVarSizeWithFlags_Flags[q17] /\ - x_ExplicitVarSizeWithFlags_Values[q17] = x_ExplicitVarSizeWithDummy[q15] - | q17 : int(1..4)]) - | q15 : int(1..4)]), - and([q18 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q18] < x_ExplicitVarSizeWithMarker_Values[q18 + 1] - | q18 : int(1..3)]), - and([q19 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q19] = 1 | q19 : int(1..4)]), - x_ExplicitVarSizeWithMarker_Marker <= 4, - and([q22 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q24] != 5 /\ - x_ExplicitVarSizeWithDummy[q24] = x_ExplicitVarSizeWithMarker_Values[q22] - | q24 : int(1..4)]) - | q22 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q26] != 5 -> - or([q28 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q28] = x_ExplicitVarSizeWithDummy[q26] - | q28 : int(1..4)]) - | q26 : int(1..4)]), - and([q30 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q32] /\ - x_ExplicitVarSizeWithFlags_Values[q32] = x_ExplicitVarSizeWithMarker_Values[q30] - | q32 : int(1..4)]) - | q30 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q34] -> - or([q36 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q36] = x_ExplicitVarSizeWithFlags_Values[q34] - | q36 : int(1..4)]) - | q34 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_2_4_2_4-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_2_4_2_4-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_4_2_4-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_2_4_2_4-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_2_4_2_4-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_4_2_4-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_2_4_2_4.eprime b/tests/exhaustive/basic/set06/expected/model_2_4_2_4.eprime deleted file mode 100644 index c887a723c4..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_4_2_4.eprime +++ /dev/null @@ -1,31 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -branching on [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy] -such that - or([x_ExplicitVarSizeWithDummy[q19] != 5 /\ x_ExplicitVarSizeWithDummy[q19] = 1 | q19 : int(1..4)]), - or([x_ExplicitVarSizeWithFlags_Flags[q21] /\ x_ExplicitVarSizeWithFlags_Values[q21] = 2 | q21 : int(1..4)]), - or([x_ExplicitVarSizeWithDummy[q23] != 5 /\ x_ExplicitVarSizeWithDummy[q23] = 3 | q23 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 5 - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q2] = 5 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 5) | q3 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithFlags_Flags[q5 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q5] < x_ExplicitVarSizeWithFlags_Values[q5 + 1] - | q5 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q6] = false -> x_ExplicitVarSizeWithFlags_Values[q6] = 1 | q6 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q7] | q7 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q8]) | q8 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithFlags_Flags[q11] -> - or([x_ExplicitVarSizeWithDummy[q13] != 5 /\ - x_ExplicitVarSizeWithDummy[q13] = x_ExplicitVarSizeWithFlags_Values[q11] - | q13 : int(1..4)]) - | q11 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q15] != 5 -> - or([x_ExplicitVarSizeWithFlags_Flags[q17] /\ - x_ExplicitVarSizeWithFlags_Values[q17] = x_ExplicitVarSizeWithDummy[q15] - | q17 : int(1..4)]) - | q15 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_2_4_3_1-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_2_4_3_1-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_4_3_1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_2_4_3_1-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_2_4_3_1-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_4_3_1-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_2_4_3_1.eprime b/tests/exhaustive/basic/set06/expected/model_2_4_3_1.eprime deleted file mode 100644 index c5d220fcc3..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_4_3_1.eprime +++ /dev/null @@ -1,77 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_Occurrence: matrix indexed by [int(1..4)] of bool -branching on - [x_Occurrence, x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, - x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] -such that - or([x_ExplicitVarSizeWithDummy[q54] != 5 /\ x_ExplicitVarSizeWithDummy[q54] = 1 | q54 : int(1..4)]), - or([x_ExplicitVarSizeWithFlags_Flags[q56] /\ x_ExplicitVarSizeWithFlags_Values[q56] = 2 | q56 : int(1..4)]), - or([q58 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q58] = 3 | q58 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 5 - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q2] = 5 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 5) | q3 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithFlags_Flags[q5 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q5] < x_ExplicitVarSizeWithFlags_Values[q5 + 1] - | q5 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q6] = false -> x_ExplicitVarSizeWithFlags_Values[q6] = 1 | q6 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q7] | q7 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q8]) | q8 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithFlags_Flags[q11] -> - or([x_ExplicitVarSizeWithDummy[q13] != 5 /\ - x_ExplicitVarSizeWithDummy[q13] = x_ExplicitVarSizeWithFlags_Values[q11] - | q13 : int(1..4)]) - | q11 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q15] != 5 -> - or([x_ExplicitVarSizeWithFlags_Flags[q17] /\ - x_ExplicitVarSizeWithFlags_Values[q17] = x_ExplicitVarSizeWithDummy[q15] - | q17 : int(1..4)]) - | q15 : int(1..4)]), - and([q18 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q18] < x_ExplicitVarSizeWithMarker_Values[q18 + 1] - | q18 : int(1..3)]), - and([q19 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q19] = 1 | q19 : int(1..4)]), - x_ExplicitVarSizeWithMarker_Marker <= 4, - and([q22 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q24] != 5 /\ - x_ExplicitVarSizeWithDummy[q24] = x_ExplicitVarSizeWithMarker_Values[q22] - | q24 : int(1..4)]) - | q22 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q26] != 5 -> - or([q28 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q28] = x_ExplicitVarSizeWithDummy[q26] - | q28 : int(1..4)]) - | q26 : int(1..4)]), - and([q30 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q32] /\ - x_ExplicitVarSizeWithFlags_Values[q32] = x_ExplicitVarSizeWithMarker_Values[q30] - | q32 : int(1..4)]) - | q30 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q34] -> - or([q36 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q36] = x_ExplicitVarSizeWithFlags_Values[q34] - | q36 : int(1..4)]) - | q34 : int(1..4)]), - sum([toInt(x_Occurrence[q37]) | q37 : int(1..4)]) <= 4, - and([x_Occurrence[q38] -> - or([x_ExplicitVarSizeWithDummy[q40] != 5 /\ x_ExplicitVarSizeWithDummy[q40] = q38 | q40 : int(1..4)]) - | q38 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q42] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q42]] | q42 : int(1..4)]), - and([x_Occurrence[q43] -> - or([x_ExplicitVarSizeWithFlags_Flags[q45] /\ x_ExplicitVarSizeWithFlags_Values[q45] = q43 | q45 : int(1..4)]) - | q43 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q47] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q47]] - | q47 : int(1..4)]), - and([x_Occurrence[q48] -> - or([q50 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q50] = q48 - | q50 : int(1..4)]) - | q48 : int(1..4)]), - and([q52 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q52]] - | q52 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_2_4_3_2-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_2_4_3_2-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_4_3_2-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_2_4_3_2-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_2_4_3_2-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_4_3_2-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_2_4_3_2.eprime b/tests/exhaustive/basic/set06/expected/model_2_4_3_2.eprime deleted file mode 100644 index 58bc43d769..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_4_3_2.eprime +++ /dev/null @@ -1,60 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy, - x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] -such that - or([x_ExplicitVarSizeWithDummy[q38] != 5 /\ x_ExplicitVarSizeWithDummy[q38] = 1 | q38 : int(1..4)]), - or([x_ExplicitVarSizeWithFlags_Flags[q40] /\ x_ExplicitVarSizeWithFlags_Values[q40] = 2 | q40 : int(1..4)]), - or([q42 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q42] = 3 | q42 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 5 - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q2] = 5 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 5) | q3 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithFlags_Flags[q5 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q5] < x_ExplicitVarSizeWithFlags_Values[q5 + 1] - | q5 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q6] = false -> x_ExplicitVarSizeWithFlags_Values[q6] = 1 | q6 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q7] | q7 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q8]) | q8 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithFlags_Flags[q11] -> - or([x_ExplicitVarSizeWithDummy[q13] != 5 /\ - x_ExplicitVarSizeWithDummy[q13] = x_ExplicitVarSizeWithFlags_Values[q11] - | q13 : int(1..4)]) - | q11 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q15] != 5 -> - or([x_ExplicitVarSizeWithFlags_Flags[q17] /\ - x_ExplicitVarSizeWithFlags_Values[q17] = x_ExplicitVarSizeWithDummy[q15] - | q17 : int(1..4)]) - | q15 : int(1..4)]), - and([q18 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q18] < x_ExplicitVarSizeWithMarker_Values[q18 + 1] - | q18 : int(1..3)]), - and([q19 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q19] = 1 | q19 : int(1..4)]), - x_ExplicitVarSizeWithMarker_Marker <= 4, - and([q22 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q24] != 5 /\ - x_ExplicitVarSizeWithDummy[q24] = x_ExplicitVarSizeWithMarker_Values[q22] - | q24 : int(1..4)]) - | q22 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q26] != 5 -> - or([q28 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q28] = x_ExplicitVarSizeWithDummy[q26] - | q28 : int(1..4)]) - | q26 : int(1..4)]), - and([q30 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q32] /\ - x_ExplicitVarSizeWithFlags_Values[q32] = x_ExplicitVarSizeWithMarker_Values[q30] - | q32 : int(1..4)]) - | q30 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q34] -> - or([q36 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q36] = x_ExplicitVarSizeWithFlags_Values[q34] - | q36 : int(1..4)]) - | q34 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_2_4_3_3-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_2_4_3_3-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_4_3_3-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_2_4_3_3-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_2_4_3_3-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_4_3_3-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_2_4_3_3.eprime b/tests/exhaustive/basic/set06/expected/model_2_4_3_3.eprime deleted file mode 100644 index 58bc43d769..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_4_3_3.eprime +++ /dev/null @@ -1,60 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy, - x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] -such that - or([x_ExplicitVarSizeWithDummy[q38] != 5 /\ x_ExplicitVarSizeWithDummy[q38] = 1 | q38 : int(1..4)]), - or([x_ExplicitVarSizeWithFlags_Flags[q40] /\ x_ExplicitVarSizeWithFlags_Values[q40] = 2 | q40 : int(1..4)]), - or([q42 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q42] = 3 | q42 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 5 - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q2] = 5 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 5) | q3 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithFlags_Flags[q5 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q5] < x_ExplicitVarSizeWithFlags_Values[q5 + 1] - | q5 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q6] = false -> x_ExplicitVarSizeWithFlags_Values[q6] = 1 | q6 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q7] | q7 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q8]) | q8 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithFlags_Flags[q11] -> - or([x_ExplicitVarSizeWithDummy[q13] != 5 /\ - x_ExplicitVarSizeWithDummy[q13] = x_ExplicitVarSizeWithFlags_Values[q11] - | q13 : int(1..4)]) - | q11 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q15] != 5 -> - or([x_ExplicitVarSizeWithFlags_Flags[q17] /\ - x_ExplicitVarSizeWithFlags_Values[q17] = x_ExplicitVarSizeWithDummy[q15] - | q17 : int(1..4)]) - | q15 : int(1..4)]), - and([q18 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q18] < x_ExplicitVarSizeWithMarker_Values[q18 + 1] - | q18 : int(1..3)]), - and([q19 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q19] = 1 | q19 : int(1..4)]), - x_ExplicitVarSizeWithMarker_Marker <= 4, - and([q22 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q24] != 5 /\ - x_ExplicitVarSizeWithDummy[q24] = x_ExplicitVarSizeWithMarker_Values[q22] - | q24 : int(1..4)]) - | q22 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q26] != 5 -> - or([q28 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q28] = x_ExplicitVarSizeWithDummy[q26] - | q28 : int(1..4)]) - | q26 : int(1..4)]), - and([q30 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q32] /\ - x_ExplicitVarSizeWithFlags_Values[q32] = x_ExplicitVarSizeWithMarker_Values[q30] - | q32 : int(1..4)]) - | q30 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q34] -> - or([q36 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q36] = x_ExplicitVarSizeWithFlags_Values[q34] - | q36 : int(1..4)]) - | q34 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_2_4_3_4-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_2_4_3_4-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_4_3_4-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_2_4_3_4-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_2_4_3_4-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_4_3_4-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_2_4_3_4.eprime b/tests/exhaustive/basic/set06/expected/model_2_4_3_4.eprime deleted file mode 100644 index 58bc43d769..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_4_3_4.eprime +++ /dev/null @@ -1,60 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy, - x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] -such that - or([x_ExplicitVarSizeWithDummy[q38] != 5 /\ x_ExplicitVarSizeWithDummy[q38] = 1 | q38 : int(1..4)]), - or([x_ExplicitVarSizeWithFlags_Flags[q40] /\ x_ExplicitVarSizeWithFlags_Values[q40] = 2 | q40 : int(1..4)]), - or([q42 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q42] = 3 | q42 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 5 - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q2] = 5 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 5) | q3 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithFlags_Flags[q5 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q5] < x_ExplicitVarSizeWithFlags_Values[q5 + 1] - | q5 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q6] = false -> x_ExplicitVarSizeWithFlags_Values[q6] = 1 | q6 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q7] | q7 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q8]) | q8 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithFlags_Flags[q11] -> - or([x_ExplicitVarSizeWithDummy[q13] != 5 /\ - x_ExplicitVarSizeWithDummy[q13] = x_ExplicitVarSizeWithFlags_Values[q11] - | q13 : int(1..4)]) - | q11 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q15] != 5 -> - or([x_ExplicitVarSizeWithFlags_Flags[q17] /\ - x_ExplicitVarSizeWithFlags_Values[q17] = x_ExplicitVarSizeWithDummy[q15] - | q17 : int(1..4)]) - | q15 : int(1..4)]), - and([q18 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q18] < x_ExplicitVarSizeWithMarker_Values[q18 + 1] - | q18 : int(1..3)]), - and([q19 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q19] = 1 | q19 : int(1..4)]), - x_ExplicitVarSizeWithMarker_Marker <= 4, - and([q22 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q24] != 5 /\ - x_ExplicitVarSizeWithDummy[q24] = x_ExplicitVarSizeWithMarker_Values[q22] - | q24 : int(1..4)]) - | q22 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q26] != 5 -> - or([q28 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q28] = x_ExplicitVarSizeWithDummy[q26] - | q28 : int(1..4)]) - | q26 : int(1..4)]), - and([q30 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q32] /\ - x_ExplicitVarSizeWithFlags_Values[q32] = x_ExplicitVarSizeWithMarker_Values[q30] - | q32 : int(1..4)]) - | q30 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q34] -> - or([q36 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q36] = x_ExplicitVarSizeWithFlags_Values[q34] - | q36 : int(1..4)]) - | q34 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_2_4_4_1-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_2_4_4_1-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_4_4_1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_2_4_4_1-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_2_4_4_1-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_4_4_1-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_2_4_4_1.eprime b/tests/exhaustive/basic/set06/expected/model_2_4_4_1.eprime deleted file mode 100644 index 5312aea309..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_4_4_1.eprime +++ /dev/null @@ -1,43 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_Occurrence: matrix indexed by [int(1..4)] of bool -branching on - [x_Occurrence, x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] -such that - or([x_ExplicitVarSizeWithDummy[q30] != 5 /\ x_ExplicitVarSizeWithDummy[q30] = 1 | q30 : int(1..4)]), - or([x_ExplicitVarSizeWithFlags_Flags[q32] /\ x_ExplicitVarSizeWithFlags_Values[q32] = 2 | q32 : int(1..4)]), - or([x_ExplicitVarSizeWithFlags_Flags[q34] /\ x_ExplicitVarSizeWithFlags_Values[q34] = 3 | q34 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 5 - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q2] = 5 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 5) | q3 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithFlags_Flags[q5 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q5] < x_ExplicitVarSizeWithFlags_Values[q5 + 1] - | q5 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q6] = false -> x_ExplicitVarSizeWithFlags_Values[q6] = 1 | q6 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q7] | q7 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q8]) | q8 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithFlags_Flags[q11] -> - or([x_ExplicitVarSizeWithDummy[q13] != 5 /\ - x_ExplicitVarSizeWithDummy[q13] = x_ExplicitVarSizeWithFlags_Values[q11] - | q13 : int(1..4)]) - | q11 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q15] != 5 -> - or([x_ExplicitVarSizeWithFlags_Flags[q17] /\ - x_ExplicitVarSizeWithFlags_Values[q17] = x_ExplicitVarSizeWithDummy[q15] - | q17 : int(1..4)]) - | q15 : int(1..4)]), - sum([toInt(x_Occurrence[q18]) | q18 : int(1..4)]) <= 4, - and([x_Occurrence[q19] -> - or([x_ExplicitVarSizeWithDummy[q21] != 5 /\ x_ExplicitVarSizeWithDummy[q21] = q19 | q21 : int(1..4)]) - | q19 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q23] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q23]] | q23 : int(1..4)]), - and([x_Occurrence[q24] -> - or([x_ExplicitVarSizeWithFlags_Flags[q26] /\ x_ExplicitVarSizeWithFlags_Values[q26] = q24 | q26 : int(1..4)]) - | q24 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q28] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q28]] - | q28 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_2_4_4_2-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_2_4_4_2-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_4_4_2-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_2_4_4_2-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_2_4_4_2-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_4_4_2-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_2_4_4_2.eprime b/tests/exhaustive/basic/set06/expected/model_2_4_4_2.eprime deleted file mode 100644 index 819431e7aa..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_4_4_2.eprime +++ /dev/null @@ -1,31 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -branching on [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy] -such that - or([x_ExplicitVarSizeWithDummy[q19] != 5 /\ x_ExplicitVarSizeWithDummy[q19] = 1 | q19 : int(1..4)]), - or([x_ExplicitVarSizeWithFlags_Flags[q21] /\ x_ExplicitVarSizeWithFlags_Values[q21] = 2 | q21 : int(1..4)]), - or([x_ExplicitVarSizeWithFlags_Flags[q23] /\ x_ExplicitVarSizeWithFlags_Values[q23] = 3 | q23 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 5 - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q2] = 5 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 5) | q3 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithFlags_Flags[q5 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q5] < x_ExplicitVarSizeWithFlags_Values[q5 + 1] - | q5 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q6] = false -> x_ExplicitVarSizeWithFlags_Values[q6] = 1 | q6 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q7] | q7 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q8]) | q8 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithFlags_Flags[q11] -> - or([x_ExplicitVarSizeWithDummy[q13] != 5 /\ - x_ExplicitVarSizeWithDummy[q13] = x_ExplicitVarSizeWithFlags_Values[q11] - | q13 : int(1..4)]) - | q11 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q15] != 5 -> - or([x_ExplicitVarSizeWithFlags_Flags[q17] /\ - x_ExplicitVarSizeWithFlags_Values[q17] = x_ExplicitVarSizeWithDummy[q15] - | q17 : int(1..4)]) - | q15 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_2_4_4_3-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_2_4_4_3-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_4_4_3-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_2_4_4_3-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_2_4_4_3-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_4_4_3-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_2_4_4_3.eprime b/tests/exhaustive/basic/set06/expected/model_2_4_4_3.eprime deleted file mode 100644 index 7c6e3d9d88..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_4_4_3.eprime +++ /dev/null @@ -1,60 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy, - x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] -such that - or([x_ExplicitVarSizeWithDummy[q38] != 5 /\ x_ExplicitVarSizeWithDummy[q38] = 1 | q38 : int(1..4)]), - or([x_ExplicitVarSizeWithFlags_Flags[q40] /\ x_ExplicitVarSizeWithFlags_Values[q40] = 2 | q40 : int(1..4)]), - or([x_ExplicitVarSizeWithFlags_Flags[q42] /\ x_ExplicitVarSizeWithFlags_Values[q42] = 3 | q42 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 5 - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q2] = 5 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 5) | q3 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithFlags_Flags[q5 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q5] < x_ExplicitVarSizeWithFlags_Values[q5 + 1] - | q5 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q6] = false -> x_ExplicitVarSizeWithFlags_Values[q6] = 1 | q6 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q7] | q7 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q8]) | q8 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithFlags_Flags[q11] -> - or([x_ExplicitVarSizeWithDummy[q13] != 5 /\ - x_ExplicitVarSizeWithDummy[q13] = x_ExplicitVarSizeWithFlags_Values[q11] - | q13 : int(1..4)]) - | q11 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q15] != 5 -> - or([x_ExplicitVarSizeWithFlags_Flags[q17] /\ - x_ExplicitVarSizeWithFlags_Values[q17] = x_ExplicitVarSizeWithDummy[q15] - | q17 : int(1..4)]) - | q15 : int(1..4)]), - and([q18 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q18] < x_ExplicitVarSizeWithMarker_Values[q18 + 1] - | q18 : int(1..3)]), - and([q19 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q19] = 1 | q19 : int(1..4)]), - x_ExplicitVarSizeWithMarker_Marker <= 4, - and([q22 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q24] != 5 /\ - x_ExplicitVarSizeWithDummy[q24] = x_ExplicitVarSizeWithMarker_Values[q22] - | q24 : int(1..4)]) - | q22 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q26] != 5 -> - or([q28 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q28] = x_ExplicitVarSizeWithDummy[q26] - | q28 : int(1..4)]) - | q26 : int(1..4)]), - and([q30 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q32] /\ - x_ExplicitVarSizeWithFlags_Values[q32] = x_ExplicitVarSizeWithMarker_Values[q30] - | q32 : int(1..4)]) - | q30 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q34] -> - or([q36 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q36] = x_ExplicitVarSizeWithFlags_Values[q34] - | q36 : int(1..4)]) - | q34 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_2_4_4_4-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_2_4_4_4-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_4_4_4-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_2_4_4_4-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_2_4_4_4-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_4_4_4-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_2_4_4_4.eprime b/tests/exhaustive/basic/set06/expected/model_2_4_4_4.eprime deleted file mode 100644 index 819431e7aa..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_2_4_4_4.eprime +++ /dev/null @@ -1,31 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -branching on [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy] -such that - or([x_ExplicitVarSizeWithDummy[q19] != 5 /\ x_ExplicitVarSizeWithDummy[q19] = 1 | q19 : int(1..4)]), - or([x_ExplicitVarSizeWithFlags_Flags[q21] /\ x_ExplicitVarSizeWithFlags_Values[q21] = 2 | q21 : int(1..4)]), - or([x_ExplicitVarSizeWithFlags_Flags[q23] /\ x_ExplicitVarSizeWithFlags_Values[q23] = 3 | q23 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 5 - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q2] = 5 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 5) | q3 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithFlags_Flags[q5 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q5] < x_ExplicitVarSizeWithFlags_Values[q5 + 1] - | q5 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q6] = false -> x_ExplicitVarSizeWithFlags_Values[q6] = 1 | q6 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q7] | q7 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q8]) | q8 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithFlags_Flags[q11] -> - or([x_ExplicitVarSizeWithDummy[q13] != 5 /\ - x_ExplicitVarSizeWithDummy[q13] = x_ExplicitVarSizeWithFlags_Values[q11] - | q13 : int(1..4)]) - | q11 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q15] != 5 -> - or([x_ExplicitVarSizeWithFlags_Flags[q17] /\ - x_ExplicitVarSizeWithFlags_Values[q17] = x_ExplicitVarSizeWithDummy[q15] - | q17 : int(1..4)]) - | q15 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_3_1_1_1-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_3_1_1_1-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_1_1_1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_3_1_1_1-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_3_1_1_1-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_1_1_1-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_3_1_1_1.eprime b/tests/exhaustive/basic/set06/expected/model_3_1_1_1.eprime deleted file mode 100644 index b786f3d150..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_1_1_1.eprime +++ /dev/null @@ -1,22 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_Occurrence: matrix indexed by [int(1..4)] of bool -branching on [x_Occurrence, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] -such that - or([q11 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q11] = 1 | q11 : int(1..4)]), - x_Occurrence[2], - x_Occurrence[3], - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..3)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..4)]), - x_ExplicitVarSizeWithMarker_Marker <= 4, - sum([toInt(x_Occurrence[q4]) | q4 : int(1..4)]) <= 4, - and([x_Occurrence[q5] -> - or([q7 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q7] = q5 | q7 : int(1..4)]) - | q5 : int(1..4)]), - and([q9 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q9]] - | q9 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_3_1_1_2-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_3_1_1_2-solution000001.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_1_1_2-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_3_1_1_2-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_3_1_1_2-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_1_1_2-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_3_1_1_2.eprime b/tests/exhaustive/basic/set06/expected/model_3_1_1_2.eprime deleted file mode 100644 index 8f65d99356..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_1_1_2.eprime +++ /dev/null @@ -1,43 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_Occurrence: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -branching on - [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_Occurrence] -such that - or([q28 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q28] = 1 | q28 : int(1..4)]), - x_Occurrence[2], - x_Occurrence[3], - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..3)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..4)]), - x_ExplicitVarSizeWithMarker_Marker <= 4, - sum([toInt(x_Occurrence[q4]) | q4 : int(1..4)]) <= 4, - and([x_Occurrence[q22] -> - or([q24 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q24] = q22 - | q24 : int(1..4)]) - | q22 : int(1..4)]), - and([q26 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q26]] - | q26 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q5] < x_ExplicitVarSizeWithDummy[q5 + 1] \/ x_ExplicitVarSizeWithDummy[q5] = 5 - | q5 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q6] = 5 -> x_ExplicitVarSizeWithDummy[q6 + 1] = 5 | q6 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q7] != 5) | q7 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithDummy[q10] != 5 -> - or([q12 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q12] = x_ExplicitVarSizeWithDummy[q10] - | q12 : int(1..4)]) - | q10 : int(1..4)]), - and([q14 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q16] != 5 /\ - x_ExplicitVarSizeWithDummy[q16] = x_ExplicitVarSizeWithMarker_Values[q14] - | q16 : int(1..4)]) - | q14 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q18] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q18]] | q18 : int(1..4)]), - and([x_Occurrence[q19] -> - or([x_ExplicitVarSizeWithDummy[q21] != 5 /\ x_ExplicitVarSizeWithDummy[q21] = q19 | q21 : int(1..4)]) - | q19 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_3_1_1_3-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_3_1_1_3-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_1_1_3-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_3_1_1_3-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_3_1_1_3-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_1_1_3-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_3_1_1_3.eprime b/tests/exhaustive/basic/set06/expected/model_3_1_1_3.eprime deleted file mode 100644 index b786f3d150..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_1_1_3.eprime +++ /dev/null @@ -1,22 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_Occurrence: matrix indexed by [int(1..4)] of bool -branching on [x_Occurrence, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] -such that - or([q11 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q11] = 1 | q11 : int(1..4)]), - x_Occurrence[2], - x_Occurrence[3], - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..3)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..4)]), - x_ExplicitVarSizeWithMarker_Marker <= 4, - sum([toInt(x_Occurrence[q4]) | q4 : int(1..4)]) <= 4, - and([x_Occurrence[q5] -> - or([q7 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q7] = q5 | q7 : int(1..4)]) - | q5 : int(1..4)]), - and([q9 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q9]] - | q9 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_3_1_1_4-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_3_1_1_4-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_1_1_4-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_3_1_1_4-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_3_1_1_4-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_1_1_4-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_3_1_1_4.eprime b/tests/exhaustive/basic/set06/expected/model_3_1_1_4.eprime deleted file mode 100644 index a8dbd5fdde..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_1_1_4.eprime +++ /dev/null @@ -1,48 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_Occurrence: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithMarker_Marker, - x_ExplicitVarSizeWithMarker_Values, x_Occurrence] -such that - or([q29 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q29] = 1 | q29 : int(1..4)]), - x_Occurrence[2], - x_Occurrence[3], - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..3)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..4)]), - x_ExplicitVarSizeWithMarker_Marker <= 4, - sum([toInt(x_Occurrence[q4]) | q4 : int(1..4)]) <= 4, - and([x_Occurrence[q23] -> - or([q25 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q25] = q23 - | q25 : int(1..4)]) - | q23 : int(1..4)]), - and([q27 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q27]] - | q27 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q5 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q5] < x_ExplicitVarSizeWithFlags_Values[q5 + 1] - | q5 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q6] = false -> x_ExplicitVarSizeWithFlags_Values[q6] = 1 | q6 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q7] | q7 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q8]) | q8 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithFlags_Flags[q11] -> - or([q13 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q13] = x_ExplicitVarSizeWithFlags_Values[q11] - | q13 : int(1..4)]) - | q11 : int(1..4)]), - and([q15 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q17] /\ - x_ExplicitVarSizeWithFlags_Values[q17] = x_ExplicitVarSizeWithMarker_Values[q15] - | q17 : int(1..4)]) - | q15 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q19] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q19]] - | q19 : int(1..4)]), - and([x_Occurrence[q20] -> - or([x_ExplicitVarSizeWithFlags_Flags[q22] /\ x_ExplicitVarSizeWithFlags_Values[q22] = q20 | q22 : int(1..4)]) - | q20 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_3_1_2_1-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_3_1_2_1-solution000001.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_1_2_1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_3_1_2_1-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_3_1_2_1-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_1_2_1-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_3_1_2_1.eprime b/tests/exhaustive/basic/set06/expected/model_3_1_2_1.eprime deleted file mode 100644 index f2fd3908db..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_1_2_1.eprime +++ /dev/null @@ -1,43 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_Occurrence: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -branching on - [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_Occurrence] -such that - or([q30 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q30] = 1 | q30 : int(1..4)]), - x_Occurrence[2], - or([x_ExplicitVarSizeWithDummy[q28] != 5 /\ x_ExplicitVarSizeWithDummy[q28] = 3 | q28 : int(1..4)]), - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..3)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..4)]), - x_ExplicitVarSizeWithMarker_Marker <= 4, - sum([toInt(x_Occurrence[q4]) | q4 : int(1..4)]) <= 4, - and([x_Occurrence[q22] -> - or([q24 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q24] = q22 - | q24 : int(1..4)]) - | q22 : int(1..4)]), - and([q26 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q26]] - | q26 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q5] < x_ExplicitVarSizeWithDummy[q5 + 1] \/ x_ExplicitVarSizeWithDummy[q5] = 5 - | q5 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q6] = 5 -> x_ExplicitVarSizeWithDummy[q6 + 1] = 5 | q6 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q7] != 5) | q7 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithDummy[q10] != 5 -> - or([q12 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q12] = x_ExplicitVarSizeWithDummy[q10] - | q12 : int(1..4)]) - | q10 : int(1..4)]), - and([q14 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q16] != 5 /\ - x_ExplicitVarSizeWithDummy[q16] = x_ExplicitVarSizeWithMarker_Values[q14] - | q16 : int(1..4)]) - | q14 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q18] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q18]] | q18 : int(1..4)]), - and([x_Occurrence[q19] -> - or([x_ExplicitVarSizeWithDummy[q21] != 5 /\ x_ExplicitVarSizeWithDummy[q21] = q19 | q21 : int(1..4)]) - | q19 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_3_1_2_2-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_3_1_2_2-solution000001.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_1_2_2-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_3_1_2_2-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_3_1_2_2-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_1_2_2-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_3_1_2_2.eprime b/tests/exhaustive/basic/set06/expected/model_3_1_2_2.eprime deleted file mode 100644 index f2fd3908db..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_1_2_2.eprime +++ /dev/null @@ -1,43 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_Occurrence: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -branching on - [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_Occurrence] -such that - or([q30 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q30] = 1 | q30 : int(1..4)]), - x_Occurrence[2], - or([x_ExplicitVarSizeWithDummy[q28] != 5 /\ x_ExplicitVarSizeWithDummy[q28] = 3 | q28 : int(1..4)]), - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..3)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..4)]), - x_ExplicitVarSizeWithMarker_Marker <= 4, - sum([toInt(x_Occurrence[q4]) | q4 : int(1..4)]) <= 4, - and([x_Occurrence[q22] -> - or([q24 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q24] = q22 - | q24 : int(1..4)]) - | q22 : int(1..4)]), - and([q26 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q26]] - | q26 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q5] < x_ExplicitVarSizeWithDummy[q5 + 1] \/ x_ExplicitVarSizeWithDummy[q5] = 5 - | q5 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q6] = 5 -> x_ExplicitVarSizeWithDummy[q6 + 1] = 5 | q6 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q7] != 5) | q7 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithDummy[q10] != 5 -> - or([q12 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q12] = x_ExplicitVarSizeWithDummy[q10] - | q12 : int(1..4)]) - | q10 : int(1..4)]), - and([q14 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q16] != 5 /\ - x_ExplicitVarSizeWithDummy[q16] = x_ExplicitVarSizeWithMarker_Values[q14] - | q16 : int(1..4)]) - | q14 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q18] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q18]] | q18 : int(1..4)]), - and([x_Occurrence[q19] -> - or([x_ExplicitVarSizeWithDummy[q21] != 5 /\ x_ExplicitVarSizeWithDummy[q21] = q19 | q21 : int(1..4)]) - | q19 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_3_1_2_3-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_3_1_2_3-solution000001.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_1_2_3-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_3_1_2_3-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_3_1_2_3-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_1_2_3-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_3_1_2_3.eprime b/tests/exhaustive/basic/set06/expected/model_3_1_2_3.eprime deleted file mode 100644 index f2fd3908db..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_1_2_3.eprime +++ /dev/null @@ -1,43 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_Occurrence: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -branching on - [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_Occurrence] -such that - or([q30 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q30] = 1 | q30 : int(1..4)]), - x_Occurrence[2], - or([x_ExplicitVarSizeWithDummy[q28] != 5 /\ x_ExplicitVarSizeWithDummy[q28] = 3 | q28 : int(1..4)]), - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..3)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..4)]), - x_ExplicitVarSizeWithMarker_Marker <= 4, - sum([toInt(x_Occurrence[q4]) | q4 : int(1..4)]) <= 4, - and([x_Occurrence[q22] -> - or([q24 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q24] = q22 - | q24 : int(1..4)]) - | q22 : int(1..4)]), - and([q26 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q26]] - | q26 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q5] < x_ExplicitVarSizeWithDummy[q5 + 1] \/ x_ExplicitVarSizeWithDummy[q5] = 5 - | q5 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q6] = 5 -> x_ExplicitVarSizeWithDummy[q6 + 1] = 5 | q6 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q7] != 5) | q7 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithDummy[q10] != 5 -> - or([q12 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q12] = x_ExplicitVarSizeWithDummy[q10] - | q12 : int(1..4)]) - | q10 : int(1..4)]), - and([q14 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q16] != 5 /\ - x_ExplicitVarSizeWithDummy[q16] = x_ExplicitVarSizeWithMarker_Values[q14] - | q16 : int(1..4)]) - | q14 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q18] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q18]] | q18 : int(1..4)]), - and([x_Occurrence[q19] -> - or([x_ExplicitVarSizeWithDummy[q21] != 5 /\ x_ExplicitVarSizeWithDummy[q21] = q19 | q21 : int(1..4)]) - | q19 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_3_1_2_4-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_3_1_2_4-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_1_2_4-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_3_1_2_4-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_3_1_2_4-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_1_2_4-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_3_1_2_4.eprime b/tests/exhaustive/basic/set06/expected/model_3_1_2_4.eprime deleted file mode 100644 index 525362fb4b..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_1_2_4.eprime +++ /dev/null @@ -1,78 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_Occurrence: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithMarker_Marker, - x_ExplicitVarSizeWithMarker_Values, x_Occurrence, x_ExplicitVarSizeWithDummy] -such that - or([q56 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q56] = 1 | q56 : int(1..4)]), - x_Occurrence[2], - or([x_ExplicitVarSizeWithDummy[q49] != 5 /\ x_ExplicitVarSizeWithDummy[q49] = 3 | q49 : int(1..4)]), - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..3)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..4)]), - x_ExplicitVarSizeWithMarker_Marker <= 4, - sum([toInt(x_Occurrence[q4]) | q4 : int(1..4)]) <= 4, - and([x_Occurrence[q50] -> - or([q52 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q52] = q50 - | q52 : int(1..4)]) - | q50 : int(1..4)]), - and([q54 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q54]] - | q54 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q5] < x_ExplicitVarSizeWithDummy[q5 + 1] \/ x_ExplicitVarSizeWithDummy[q5] = 5 - | q5 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q6] = 5 -> x_ExplicitVarSizeWithDummy[q6 + 1] = 5 | q6 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q7] != 5) | q7 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithDummy[q10] != 5 -> - or([q12 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q12] = x_ExplicitVarSizeWithDummy[q10] - | q12 : int(1..4)]) - | q10 : int(1..4)]), - and([q14 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q16] != 5 /\ - x_ExplicitVarSizeWithDummy[q16] = x_ExplicitVarSizeWithMarker_Values[q14] - | q16 : int(1..4)]) - | q14 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q18] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q18]] | q18 : int(1..4)]), - and([x_Occurrence[q19] -> - or([x_ExplicitVarSizeWithDummy[q21] != 5 /\ x_ExplicitVarSizeWithDummy[q21] = q19 | q21 : int(1..4)]) - | q19 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q22 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q22] < x_ExplicitVarSizeWithFlags_Values[q22 + 1] - | q22 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q23] = false -> x_ExplicitVarSizeWithFlags_Values[q23] = 1 - | q23 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q24 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q24] | q24 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q25]) | q25 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithFlags_Flags[q28] -> - or([q30 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q30] = x_ExplicitVarSizeWithFlags_Values[q28] - | q30 : int(1..4)]) - | q28 : int(1..4)]), - and([q32 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q34] /\ - x_ExplicitVarSizeWithFlags_Values[q34] = x_ExplicitVarSizeWithMarker_Values[q32] - | q34 : int(1..4)]) - | q32 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q36] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q36]] - | q36 : int(1..4)]), - and([x_Occurrence[q37] -> - or([x_ExplicitVarSizeWithFlags_Flags[q39] /\ x_ExplicitVarSizeWithFlags_Values[q39] = q37 | q39 : int(1..4)]) - | q37 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q41] -> - or([x_ExplicitVarSizeWithDummy[q43] != 5 /\ - x_ExplicitVarSizeWithDummy[q43] = x_ExplicitVarSizeWithFlags_Values[q41] - | q43 : int(1..4)]) - | q41 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q45] != 5 -> - or([x_ExplicitVarSizeWithFlags_Flags[q47] /\ - x_ExplicitVarSizeWithFlags_Values[q47] = x_ExplicitVarSizeWithDummy[q45] - | q47 : int(1..4)]) - | q45 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_3_1_3_1-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_3_1_3_1-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_1_3_1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_3_1_3_1-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_3_1_3_1-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_1_3_1-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_3_1_3_1.eprime b/tests/exhaustive/basic/set06/expected/model_3_1_3_1.eprime deleted file mode 100644 index 5e6282546a..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_1_3_1.eprime +++ /dev/null @@ -1,22 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_Occurrence: matrix indexed by [int(1..4)] of bool -branching on [x_Occurrence, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] -such that - or([q13 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q13] = 1 | q13 : int(1..4)]), - x_Occurrence[2], - or([q11 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q11] = 3 | q11 : int(1..4)]), - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..3)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..4)]), - x_ExplicitVarSizeWithMarker_Marker <= 4, - sum([toInt(x_Occurrence[q4]) | q4 : int(1..4)]) <= 4, - and([x_Occurrence[q5] -> - or([q7 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q7] = q5 | q7 : int(1..4)]) - | q5 : int(1..4)]), - and([q9 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q9]] - | q9 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_3_1_3_2-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_3_1_3_2-solution000001.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_1_3_2-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_3_1_3_2-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_3_1_3_2-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_1_3_2-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_3_1_3_2.eprime b/tests/exhaustive/basic/set06/expected/model_3_1_3_2.eprime deleted file mode 100644 index b537bac469..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_1_3_2.eprime +++ /dev/null @@ -1,43 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_Occurrence: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -branching on - [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_Occurrence] -such that - or([q30 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q30] = 1 | q30 : int(1..4)]), - x_Occurrence[2], - or([q28 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q28] = 3 | q28 : int(1..4)]), - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..3)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..4)]), - x_ExplicitVarSizeWithMarker_Marker <= 4, - sum([toInt(x_Occurrence[q4]) | q4 : int(1..4)]) <= 4, - and([x_Occurrence[q22] -> - or([q24 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q24] = q22 - | q24 : int(1..4)]) - | q22 : int(1..4)]), - and([q26 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q26]] - | q26 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q5] < x_ExplicitVarSizeWithDummy[q5 + 1] \/ x_ExplicitVarSizeWithDummy[q5] = 5 - | q5 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q6] = 5 -> x_ExplicitVarSizeWithDummy[q6 + 1] = 5 | q6 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q7] != 5) | q7 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithDummy[q10] != 5 -> - or([q12 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q12] = x_ExplicitVarSizeWithDummy[q10] - | q12 : int(1..4)]) - | q10 : int(1..4)]), - and([q14 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q16] != 5 /\ - x_ExplicitVarSizeWithDummy[q16] = x_ExplicitVarSizeWithMarker_Values[q14] - | q16 : int(1..4)]) - | q14 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q18] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q18]] | q18 : int(1..4)]), - and([x_Occurrence[q19] -> - or([x_ExplicitVarSizeWithDummy[q21] != 5 /\ x_ExplicitVarSizeWithDummy[q21] = q19 | q21 : int(1..4)]) - | q19 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_3_1_3_3-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_3_1_3_3-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_1_3_3-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_3_1_3_3-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_3_1_3_3-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_1_3_3-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_3_1_3_3.eprime b/tests/exhaustive/basic/set06/expected/model_3_1_3_3.eprime deleted file mode 100644 index 5e6282546a..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_1_3_3.eprime +++ /dev/null @@ -1,22 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_Occurrence: matrix indexed by [int(1..4)] of bool -branching on [x_Occurrence, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] -such that - or([q13 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q13] = 1 | q13 : int(1..4)]), - x_Occurrence[2], - or([q11 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q11] = 3 | q11 : int(1..4)]), - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..3)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..4)]), - x_ExplicitVarSizeWithMarker_Marker <= 4, - sum([toInt(x_Occurrence[q4]) | q4 : int(1..4)]) <= 4, - and([x_Occurrence[q5] -> - or([q7 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q7] = q5 | q7 : int(1..4)]) - | q5 : int(1..4)]), - and([q9 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q9]] - | q9 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_3_1_3_4-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_3_1_3_4-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_1_3_4-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_3_1_3_4-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_3_1_3_4-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_1_3_4-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_3_1_3_4.eprime b/tests/exhaustive/basic/set06/expected/model_3_1_3_4.eprime deleted file mode 100644 index 3befc5cd42..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_1_3_4.eprime +++ /dev/null @@ -1,48 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_Occurrence: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithMarker_Marker, - x_ExplicitVarSizeWithMarker_Values, x_Occurrence] -such that - or([q31 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q31] = 1 | q31 : int(1..4)]), - x_Occurrence[2], - or([q24 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q24] = 3 | q24 : int(1..4)]), - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..3)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..4)]), - x_ExplicitVarSizeWithMarker_Marker <= 4, - sum([toInt(x_Occurrence[q4]) | q4 : int(1..4)]) <= 4, - and([x_Occurrence[q25] -> - or([q27 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q27] = q25 - | q27 : int(1..4)]) - | q25 : int(1..4)]), - and([q29 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q29]] - | q29 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q5 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q5] < x_ExplicitVarSizeWithFlags_Values[q5 + 1] - | q5 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q6] = false -> x_ExplicitVarSizeWithFlags_Values[q6] = 1 | q6 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q7] | q7 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q8]) | q8 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithFlags_Flags[q11] -> - or([q13 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q13] = x_ExplicitVarSizeWithFlags_Values[q11] - | q13 : int(1..4)]) - | q11 : int(1..4)]), - and([q15 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q17] /\ - x_ExplicitVarSizeWithFlags_Values[q17] = x_ExplicitVarSizeWithMarker_Values[q15] - | q17 : int(1..4)]) - | q15 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q19] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q19]] - | q19 : int(1..4)]), - and([x_Occurrence[q20] -> - or([x_ExplicitVarSizeWithFlags_Flags[q22] /\ x_ExplicitVarSizeWithFlags_Values[q22] = q20 | q22 : int(1..4)]) - | q20 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_3_1_4_1-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_3_1_4_1-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_1_4_1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_3_1_4_1-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_3_1_4_1-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_1_4_1-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_3_1_4_1.eprime b/tests/exhaustive/basic/set06/expected/model_3_1_4_1.eprime deleted file mode 100644 index 8671f81ae6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_1_4_1.eprime +++ /dev/null @@ -1,48 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_Occurrence: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithMarker_Marker, - x_ExplicitVarSizeWithMarker_Values, x_Occurrence] -such that - or([q31 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q31] = 1 | q31 : int(1..4)]), - x_Occurrence[2], - or([x_ExplicitVarSizeWithFlags_Flags[q24] /\ x_ExplicitVarSizeWithFlags_Values[q24] = 3 | q24 : int(1..4)]), - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..3)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..4)]), - x_ExplicitVarSizeWithMarker_Marker <= 4, - sum([toInt(x_Occurrence[q4]) | q4 : int(1..4)]) <= 4, - and([x_Occurrence[q25] -> - or([q27 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q27] = q25 - | q27 : int(1..4)]) - | q25 : int(1..4)]), - and([q29 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q29]] - | q29 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q5 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q5] < x_ExplicitVarSizeWithFlags_Values[q5 + 1] - | q5 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q6] = false -> x_ExplicitVarSizeWithFlags_Values[q6] = 1 | q6 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q7] | q7 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q8]) | q8 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithFlags_Flags[q11] -> - or([q13 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q13] = x_ExplicitVarSizeWithFlags_Values[q11] - | q13 : int(1..4)]) - | q11 : int(1..4)]), - and([q15 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q17] /\ - x_ExplicitVarSizeWithFlags_Values[q17] = x_ExplicitVarSizeWithMarker_Values[q15] - | q17 : int(1..4)]) - | q15 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q19] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q19]] - | q19 : int(1..4)]), - and([x_Occurrence[q20] -> - or([x_ExplicitVarSizeWithFlags_Flags[q22] /\ x_ExplicitVarSizeWithFlags_Values[q22] = q20 | q22 : int(1..4)]) - | q20 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_3_1_4_2-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_3_1_4_2-solution000001.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_1_4_2-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_3_1_4_2-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_3_1_4_2-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_1_4_2-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_3_1_4_2.eprime b/tests/exhaustive/basic/set06/expected/model_3_1_4_2.eprime deleted file mode 100644 index 66ffd146e3..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_1_4_2.eprime +++ /dev/null @@ -1,77 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_Occurrence: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -branching on - [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_Occurrence, - x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] -such that - or([q56 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q56] = 1 | q56 : int(1..4)]), - x_Occurrence[2], - or([x_ExplicitVarSizeWithFlags_Flags[q49] /\ x_ExplicitVarSizeWithFlags_Values[q49] = 3 | q49 : int(1..4)]), - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..3)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..4)]), - x_ExplicitVarSizeWithMarker_Marker <= 4, - sum([toInt(x_Occurrence[q4]) | q4 : int(1..4)]) <= 4, - and([x_Occurrence[q50] -> - or([q52 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q52] = q50 - | q52 : int(1..4)]) - | q50 : int(1..4)]), - and([q54 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q54]] - | q54 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q5 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q5] < x_ExplicitVarSizeWithFlags_Values[q5 + 1] - | q5 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q6] = false -> x_ExplicitVarSizeWithFlags_Values[q6] = 1 | q6 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q7] | q7 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q8]) | q8 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithFlags_Flags[q11] -> - or([q13 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q13] = x_ExplicitVarSizeWithFlags_Values[q11] - | q13 : int(1..4)]) - | q11 : int(1..4)]), - and([q15 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q17] /\ - x_ExplicitVarSizeWithFlags_Values[q17] = x_ExplicitVarSizeWithMarker_Values[q15] - | q17 : int(1..4)]) - | q15 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q19] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q19]] - | q19 : int(1..4)]), - and([x_Occurrence[q20] -> - or([x_ExplicitVarSizeWithFlags_Flags[q22] /\ x_ExplicitVarSizeWithFlags_Values[q22] = q20 | q22 : int(1..4)]) - | q20 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q23] < x_ExplicitVarSizeWithDummy[q23 + 1] \/ x_ExplicitVarSizeWithDummy[q23] = 5 - | q23 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q24] = 5 -> x_ExplicitVarSizeWithDummy[q24 + 1] = 5 | q24 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q25] != 5) | q25 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithDummy[q28] != 5 -> - or([q30 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q30] = x_ExplicitVarSizeWithDummy[q28] - | q30 : int(1..4)]) - | q28 : int(1..4)]), - and([q32 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q34] != 5 /\ - x_ExplicitVarSizeWithDummy[q34] = x_ExplicitVarSizeWithMarker_Values[q32] - | q34 : int(1..4)]) - | q32 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q36] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q36]] | q36 : int(1..4)]), - and([x_Occurrence[q37] -> - or([x_ExplicitVarSizeWithDummy[q39] != 5 /\ x_ExplicitVarSizeWithDummy[q39] = q37 | q39 : int(1..4)]) - | q37 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q41] != 5 -> - or([x_ExplicitVarSizeWithFlags_Flags[q43] /\ - x_ExplicitVarSizeWithFlags_Values[q43] = x_ExplicitVarSizeWithDummy[q41] - | q43 : int(1..4)]) - | q41 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q45] -> - or([x_ExplicitVarSizeWithDummy[q47] != 5 /\ - x_ExplicitVarSizeWithDummy[q47] = x_ExplicitVarSizeWithFlags_Values[q45] - | q47 : int(1..4)]) - | q45 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_3_1_4_3-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_3_1_4_3-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_1_4_3-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_3_1_4_3-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_3_1_4_3-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_1_4_3-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_3_1_4_3.eprime b/tests/exhaustive/basic/set06/expected/model_3_1_4_3.eprime deleted file mode 100644 index 8671f81ae6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_1_4_3.eprime +++ /dev/null @@ -1,48 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_Occurrence: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithMarker_Marker, - x_ExplicitVarSizeWithMarker_Values, x_Occurrence] -such that - or([q31 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q31] = 1 | q31 : int(1..4)]), - x_Occurrence[2], - or([x_ExplicitVarSizeWithFlags_Flags[q24] /\ x_ExplicitVarSizeWithFlags_Values[q24] = 3 | q24 : int(1..4)]), - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..3)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..4)]), - x_ExplicitVarSizeWithMarker_Marker <= 4, - sum([toInt(x_Occurrence[q4]) | q4 : int(1..4)]) <= 4, - and([x_Occurrence[q25] -> - or([q27 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q27] = q25 - | q27 : int(1..4)]) - | q25 : int(1..4)]), - and([q29 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q29]] - | q29 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q5 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q5] < x_ExplicitVarSizeWithFlags_Values[q5 + 1] - | q5 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q6] = false -> x_ExplicitVarSizeWithFlags_Values[q6] = 1 | q6 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q7] | q7 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q8]) | q8 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithFlags_Flags[q11] -> - or([q13 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q13] = x_ExplicitVarSizeWithFlags_Values[q11] - | q13 : int(1..4)]) - | q11 : int(1..4)]), - and([q15 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q17] /\ - x_ExplicitVarSizeWithFlags_Values[q17] = x_ExplicitVarSizeWithMarker_Values[q15] - | q17 : int(1..4)]) - | q15 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q19] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q19]] - | q19 : int(1..4)]), - and([x_Occurrence[q20] -> - or([x_ExplicitVarSizeWithFlags_Flags[q22] /\ x_ExplicitVarSizeWithFlags_Values[q22] = q20 | q22 : int(1..4)]) - | q20 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_3_1_4_4-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_3_1_4_4-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_1_4_4-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_3_1_4_4-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_3_1_4_4-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_1_4_4-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_3_1_4_4.eprime b/tests/exhaustive/basic/set06/expected/model_3_1_4_4.eprime deleted file mode 100644 index 8671f81ae6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_1_4_4.eprime +++ /dev/null @@ -1,48 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_Occurrence: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithMarker_Marker, - x_ExplicitVarSizeWithMarker_Values, x_Occurrence] -such that - or([q31 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q31] = 1 | q31 : int(1..4)]), - x_Occurrence[2], - or([x_ExplicitVarSizeWithFlags_Flags[q24] /\ x_ExplicitVarSizeWithFlags_Values[q24] = 3 | q24 : int(1..4)]), - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..3)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..4)]), - x_ExplicitVarSizeWithMarker_Marker <= 4, - sum([toInt(x_Occurrence[q4]) | q4 : int(1..4)]) <= 4, - and([x_Occurrence[q25] -> - or([q27 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q27] = q25 - | q27 : int(1..4)]) - | q25 : int(1..4)]), - and([q29 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q29]] - | q29 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q5 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q5] < x_ExplicitVarSizeWithFlags_Values[q5 + 1] - | q5 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q6] = false -> x_ExplicitVarSizeWithFlags_Values[q6] = 1 | q6 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q7] | q7 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q8]) | q8 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithFlags_Flags[q11] -> - or([q13 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q13] = x_ExplicitVarSizeWithFlags_Values[q11] - | q13 : int(1..4)]) - | q11 : int(1..4)]), - and([q15 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q17] /\ - x_ExplicitVarSizeWithFlags_Values[q17] = x_ExplicitVarSizeWithMarker_Values[q15] - | q17 : int(1..4)]) - | q15 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q19] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q19]] - | q19 : int(1..4)]), - and([x_Occurrence[q20] -> - or([x_ExplicitVarSizeWithFlags_Flags[q22] /\ x_ExplicitVarSizeWithFlags_Values[q22] = q20 | q22 : int(1..4)]) - | q20 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_3_2_1_1-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_3_2_1_1-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_2_1_1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_3_2_1_1-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_3_2_1_1-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_2_1_1-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_3_2_1_1.eprime b/tests/exhaustive/basic/set06/expected/model_3_2_1_1.eprime deleted file mode 100644 index 9ce4f6b713..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_2_1_1.eprime +++ /dev/null @@ -1,43 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -find x_Occurrence: matrix indexed by [int(1..4)] of bool -branching on - [x_Occurrence, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy] -such that - or([q28 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q28] = 1 | q28 : int(1..4)]), - or([x_ExplicitVarSizeWithDummy[q30] != 5 /\ x_ExplicitVarSizeWithDummy[q30] = 2 | q30 : int(1..4)]), - x_Occurrence[3], - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..3)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..4)]), - x_ExplicitVarSizeWithMarker_Marker <= 4, - and([x_ExplicitVarSizeWithDummy[q4] < x_ExplicitVarSizeWithDummy[q4 + 1] \/ x_ExplicitVarSizeWithDummy[q4] = 5 - | q4 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q5] = 5 -> x_ExplicitVarSizeWithDummy[q5 + 1] = 5 | q5 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q6] != 5) | q6 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithDummy[q9] != 5 -> - or([q11 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q11] = x_ExplicitVarSizeWithDummy[q9] - | q11 : int(1..4)]) - | q9 : int(1..4)]), - and([q13 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q15] != 5 /\ - x_ExplicitVarSizeWithDummy[q15] = x_ExplicitVarSizeWithMarker_Values[q13] - | q15 : int(1..4)]) - | q13 : int(1..4)]), - sum([toInt(x_Occurrence[q16]) | q16 : int(1..4)]) <= 4, - and([x_Occurrence[q17] -> - or([q19 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q19] = q17 - | q19 : int(1..4)]) - | q17 : int(1..4)]), - and([q21 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q21]] - | q21 : int(1..4)]), - and([x_Occurrence[q22] -> - or([x_ExplicitVarSizeWithDummy[q24] != 5 /\ x_ExplicitVarSizeWithDummy[q24] = q22 | q24 : int(1..4)]) - | q22 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q26] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q26]] | q26 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_3_2_1_2-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_3_2_1_2-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_2_1_2-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_3_2_1_2-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_3_2_1_2-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_2_1_2-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_3_2_1_2.eprime b/tests/exhaustive/basic/set06/expected/model_3_2_1_2.eprime deleted file mode 100644 index 9ce4f6b713..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_2_1_2.eprime +++ /dev/null @@ -1,43 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -find x_Occurrence: matrix indexed by [int(1..4)] of bool -branching on - [x_Occurrence, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy] -such that - or([q28 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q28] = 1 | q28 : int(1..4)]), - or([x_ExplicitVarSizeWithDummy[q30] != 5 /\ x_ExplicitVarSizeWithDummy[q30] = 2 | q30 : int(1..4)]), - x_Occurrence[3], - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..3)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..4)]), - x_ExplicitVarSizeWithMarker_Marker <= 4, - and([x_ExplicitVarSizeWithDummy[q4] < x_ExplicitVarSizeWithDummy[q4 + 1] \/ x_ExplicitVarSizeWithDummy[q4] = 5 - | q4 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q5] = 5 -> x_ExplicitVarSizeWithDummy[q5 + 1] = 5 | q5 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q6] != 5) | q6 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithDummy[q9] != 5 -> - or([q11 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q11] = x_ExplicitVarSizeWithDummy[q9] - | q11 : int(1..4)]) - | q9 : int(1..4)]), - and([q13 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q15] != 5 /\ - x_ExplicitVarSizeWithDummy[q15] = x_ExplicitVarSizeWithMarker_Values[q13] - | q15 : int(1..4)]) - | q13 : int(1..4)]), - sum([toInt(x_Occurrence[q16]) | q16 : int(1..4)]) <= 4, - and([x_Occurrence[q17] -> - or([q19 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q19] = q17 - | q19 : int(1..4)]) - | q17 : int(1..4)]), - and([q21 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q21]] - | q21 : int(1..4)]), - and([x_Occurrence[q22] -> - or([x_ExplicitVarSizeWithDummy[q24] != 5 /\ x_ExplicitVarSizeWithDummy[q24] = q22 | q24 : int(1..4)]) - | q22 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q26] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q26]] | q26 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_3_2_1_3-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_3_2_1_3-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_2_1_3-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_3_2_1_3-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_3_2_1_3-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_2_1_3-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_3_2_1_3.eprime b/tests/exhaustive/basic/set06/expected/model_3_2_1_3.eprime deleted file mode 100644 index 9ce4f6b713..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_2_1_3.eprime +++ /dev/null @@ -1,43 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -find x_Occurrence: matrix indexed by [int(1..4)] of bool -branching on - [x_Occurrence, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy] -such that - or([q28 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q28] = 1 | q28 : int(1..4)]), - or([x_ExplicitVarSizeWithDummy[q30] != 5 /\ x_ExplicitVarSizeWithDummy[q30] = 2 | q30 : int(1..4)]), - x_Occurrence[3], - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..3)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..4)]), - x_ExplicitVarSizeWithMarker_Marker <= 4, - and([x_ExplicitVarSizeWithDummy[q4] < x_ExplicitVarSizeWithDummy[q4 + 1] \/ x_ExplicitVarSizeWithDummy[q4] = 5 - | q4 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q5] = 5 -> x_ExplicitVarSizeWithDummy[q5 + 1] = 5 | q5 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q6] != 5) | q6 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithDummy[q9] != 5 -> - or([q11 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q11] = x_ExplicitVarSizeWithDummy[q9] - | q11 : int(1..4)]) - | q9 : int(1..4)]), - and([q13 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q15] != 5 /\ - x_ExplicitVarSizeWithDummy[q15] = x_ExplicitVarSizeWithMarker_Values[q13] - | q15 : int(1..4)]) - | q13 : int(1..4)]), - sum([toInt(x_Occurrence[q16]) | q16 : int(1..4)]) <= 4, - and([x_Occurrence[q17] -> - or([q19 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q19] = q17 - | q19 : int(1..4)]) - | q17 : int(1..4)]), - and([q21 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q21]] - | q21 : int(1..4)]), - and([x_Occurrence[q22] -> - or([x_ExplicitVarSizeWithDummy[q24] != 5 /\ x_ExplicitVarSizeWithDummy[q24] = q22 | q24 : int(1..4)]) - | q22 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q26] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q26]] | q26 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_3_2_1_4-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_3_2_1_4-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_2_1_4-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_3_2_1_4-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_3_2_1_4-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_2_1_4-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_3_2_1_4.eprime b/tests/exhaustive/basic/set06/expected/model_3_2_1_4.eprime deleted file mode 100644 index 89bd1983d1..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_2_1_4.eprime +++ /dev/null @@ -1,78 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -find x_Occurrence: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithMarker_Marker, - x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy, x_Occurrence] -such that - or([q54 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q54] = 1 | q54 : int(1..4)]), - or([x_ExplicitVarSizeWithDummy[q56] != 5 /\ x_ExplicitVarSizeWithDummy[q56] = 2 | q56 : int(1..4)]), - x_Occurrence[3], - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..3)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..4)]), - x_ExplicitVarSizeWithMarker_Marker <= 4, - and([x_ExplicitVarSizeWithDummy[q4] < x_ExplicitVarSizeWithDummy[q4 + 1] \/ x_ExplicitVarSizeWithDummy[q4] = 5 - | q4 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q5] = 5 -> x_ExplicitVarSizeWithDummy[q5 + 1] = 5 | q5 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q6] != 5) | q6 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithDummy[q9] != 5 -> - or([q11 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q11] = x_ExplicitVarSizeWithDummy[q9] - | q11 : int(1..4)]) - | q9 : int(1..4)]), - and([q13 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q15] != 5 /\ - x_ExplicitVarSizeWithDummy[q15] = x_ExplicitVarSizeWithMarker_Values[q13] - | q15 : int(1..4)]) - | q13 : int(1..4)]), - sum([toInt(x_Occurrence[q16]) | q16 : int(1..4)]) <= 4, - and([x_Occurrence[q43] -> - or([q45 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q45] = q43 - | q45 : int(1..4)]) - | q43 : int(1..4)]), - and([q47 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q47]] - | q47 : int(1..4)]), - and([x_Occurrence[q48] -> - or([x_ExplicitVarSizeWithDummy[q50] != 5 /\ x_ExplicitVarSizeWithDummy[q50] = q48 | q50 : int(1..4)]) - | q48 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q52] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q52]] | q52 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q17 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q17] < x_ExplicitVarSizeWithFlags_Values[q17 + 1] - | q17 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q18] = false -> x_ExplicitVarSizeWithFlags_Values[q18] = 1 - | q18 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q19 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q19] | q19 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q20]) | q20 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithFlags_Flags[q23] -> - or([q25 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q25] = x_ExplicitVarSizeWithFlags_Values[q23] - | q25 : int(1..4)]) - | q23 : int(1..4)]), - and([q27 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q29] /\ - x_ExplicitVarSizeWithFlags_Values[q29] = x_ExplicitVarSizeWithMarker_Values[q27] - | q29 : int(1..4)]) - | q27 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q31] -> - or([x_ExplicitVarSizeWithDummy[q33] != 5 /\ - x_ExplicitVarSizeWithDummy[q33] = x_ExplicitVarSizeWithFlags_Values[q31] - | q33 : int(1..4)]) - | q31 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q35] != 5 -> - or([x_ExplicitVarSizeWithFlags_Flags[q37] /\ - x_ExplicitVarSizeWithFlags_Values[q37] = x_ExplicitVarSizeWithDummy[q35] - | q37 : int(1..4)]) - | q35 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q39] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q39]] - | q39 : int(1..4)]), - and([x_Occurrence[q40] -> - or([x_ExplicitVarSizeWithFlags_Flags[q42] /\ x_ExplicitVarSizeWithFlags_Values[q42] = q40 | q42 : int(1..4)]) - | q40 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_3_2_2_1-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_3_2_2_1-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_2_2_1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_3_2_2_1-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_3_2_2_1-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_2_2_1-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_3_2_2_1.eprime b/tests/exhaustive/basic/set06/expected/model_3_2_2_1.eprime deleted file mode 100644 index 0bc238b946..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_2_2_1.eprime +++ /dev/null @@ -1,43 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -find x_Occurrence: matrix indexed by [int(1..4)] of bool -branching on - [x_Occurrence, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy] -such that - or([q28 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q28] = 1 | q28 : int(1..4)]), - or([x_ExplicitVarSizeWithDummy[q30] != 5 /\ x_ExplicitVarSizeWithDummy[q30] = 2 | q30 : int(1..4)]), - or([x_ExplicitVarSizeWithDummy[q32] != 5 /\ x_ExplicitVarSizeWithDummy[q32] = 3 | q32 : int(1..4)]), - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..3)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..4)]), - x_ExplicitVarSizeWithMarker_Marker <= 4, - and([x_ExplicitVarSizeWithDummy[q4] < x_ExplicitVarSizeWithDummy[q4 + 1] \/ x_ExplicitVarSizeWithDummy[q4] = 5 - | q4 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q5] = 5 -> x_ExplicitVarSizeWithDummy[q5 + 1] = 5 | q5 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q6] != 5) | q6 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithDummy[q9] != 5 -> - or([q11 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q11] = x_ExplicitVarSizeWithDummy[q9] - | q11 : int(1..4)]) - | q9 : int(1..4)]), - and([q13 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q15] != 5 /\ - x_ExplicitVarSizeWithDummy[q15] = x_ExplicitVarSizeWithMarker_Values[q13] - | q15 : int(1..4)]) - | q13 : int(1..4)]), - sum([toInt(x_Occurrence[q16]) | q16 : int(1..4)]) <= 4, - and([x_Occurrence[q17] -> - or([q19 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q19] = q17 - | q19 : int(1..4)]) - | q17 : int(1..4)]), - and([q21 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q21]] - | q21 : int(1..4)]), - and([x_Occurrence[q22] -> - or([x_ExplicitVarSizeWithDummy[q24] != 5 /\ x_ExplicitVarSizeWithDummy[q24] = q22 | q24 : int(1..4)]) - | q22 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q26] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q26]] | q26 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_3_2_2_2-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_3_2_2_2-solution000001.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_2_2_2-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_3_2_2_2-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_3_2_2_2-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_2_2_2-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_3_2_2_2.eprime b/tests/exhaustive/basic/set06/expected/model_3_2_2_2.eprime deleted file mode 100644 index dbfe72b7f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_2_2_2.eprime +++ /dev/null @@ -1,30 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -branching on [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] -such that - or([q17 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q17] = 1 | q17 : int(1..4)]), - or([x_ExplicitVarSizeWithDummy[q19] != 5 /\ x_ExplicitVarSizeWithDummy[q19] = 2 | q19 : int(1..4)]), - or([x_ExplicitVarSizeWithDummy[q21] != 5 /\ x_ExplicitVarSizeWithDummy[q21] = 3 | q21 : int(1..4)]), - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..3)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..4)]), - x_ExplicitVarSizeWithMarker_Marker <= 4, - and([x_ExplicitVarSizeWithDummy[q4] < x_ExplicitVarSizeWithDummy[q4 + 1] \/ x_ExplicitVarSizeWithDummy[q4] = 5 - | q4 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q5] = 5 -> x_ExplicitVarSizeWithDummy[q5 + 1] = 5 | q5 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q6] != 5) | q6 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithDummy[q9] != 5 -> - or([q11 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q11] = x_ExplicitVarSizeWithDummy[q9] - | q11 : int(1..4)]) - | q9 : int(1..4)]), - and([q13 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q15] != 5 /\ - x_ExplicitVarSizeWithDummy[q15] = x_ExplicitVarSizeWithMarker_Values[q13] - | q15 : int(1..4)]) - | q13 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_3_2_2_3-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_3_2_2_3-solution000001.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_2_2_3-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_3_2_2_3-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_3_2_2_3-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_2_2_3-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_3_2_2_3.eprime b/tests/exhaustive/basic/set06/expected/model_3_2_2_3.eprime deleted file mode 100644 index dbfe72b7f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_2_2_3.eprime +++ /dev/null @@ -1,30 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -branching on [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] -such that - or([q17 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q17] = 1 | q17 : int(1..4)]), - or([x_ExplicitVarSizeWithDummy[q19] != 5 /\ x_ExplicitVarSizeWithDummy[q19] = 2 | q19 : int(1..4)]), - or([x_ExplicitVarSizeWithDummy[q21] != 5 /\ x_ExplicitVarSizeWithDummy[q21] = 3 | q21 : int(1..4)]), - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..3)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..4)]), - x_ExplicitVarSizeWithMarker_Marker <= 4, - and([x_ExplicitVarSizeWithDummy[q4] < x_ExplicitVarSizeWithDummy[q4 + 1] \/ x_ExplicitVarSizeWithDummy[q4] = 5 - | q4 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q5] = 5 -> x_ExplicitVarSizeWithDummy[q5 + 1] = 5 | q5 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q6] != 5) | q6 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithDummy[q9] != 5 -> - or([q11 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q11] = x_ExplicitVarSizeWithDummy[q9] - | q11 : int(1..4)]) - | q9 : int(1..4)]), - and([q13 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q15] != 5 /\ - x_ExplicitVarSizeWithDummy[q15] = x_ExplicitVarSizeWithMarker_Values[q13] - | q15 : int(1..4)]) - | q13 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_3_2_2_4-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_3_2_2_4-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_2_2_4-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_3_2_2_4-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_3_2_2_4-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_2_2_4-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_3_2_2_4.eprime b/tests/exhaustive/basic/set06/expected/model_3_2_2_4.eprime deleted file mode 100644 index 7a1a6ff738..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_2_2_4.eprime +++ /dev/null @@ -1,61 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithMarker_Marker, - x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy] -such that - or([q38 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q38] = 1 | q38 : int(1..4)]), - or([x_ExplicitVarSizeWithDummy[q40] != 5 /\ x_ExplicitVarSizeWithDummy[q40] = 2 | q40 : int(1..4)]), - or([x_ExplicitVarSizeWithDummy[q42] != 5 /\ x_ExplicitVarSizeWithDummy[q42] = 3 | q42 : int(1..4)]), - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..3)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..4)]), - x_ExplicitVarSizeWithMarker_Marker <= 4, - and([x_ExplicitVarSizeWithDummy[q4] < x_ExplicitVarSizeWithDummy[q4 + 1] \/ x_ExplicitVarSizeWithDummy[q4] = 5 - | q4 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q5] = 5 -> x_ExplicitVarSizeWithDummy[q5 + 1] = 5 | q5 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q6] != 5) | q6 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithDummy[q9] != 5 -> - or([q11 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q11] = x_ExplicitVarSizeWithDummy[q9] - | q11 : int(1..4)]) - | q9 : int(1..4)]), - and([q13 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q15] != 5 /\ - x_ExplicitVarSizeWithDummy[q15] = x_ExplicitVarSizeWithMarker_Values[q13] - | q15 : int(1..4)]) - | q13 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q16 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q16] < x_ExplicitVarSizeWithFlags_Values[q16 + 1] - | q16 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q17] = false -> x_ExplicitVarSizeWithFlags_Values[q17] = 1 - | q17 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q18 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q18] | q18 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q19]) | q19 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithFlags_Flags[q22] -> - or([q24 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q24] = x_ExplicitVarSizeWithFlags_Values[q22] - | q24 : int(1..4)]) - | q22 : int(1..4)]), - and([q26 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q28] /\ - x_ExplicitVarSizeWithFlags_Values[q28] = x_ExplicitVarSizeWithMarker_Values[q26] - | q28 : int(1..4)]) - | q26 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q30] -> - or([x_ExplicitVarSizeWithDummy[q32] != 5 /\ - x_ExplicitVarSizeWithDummy[q32] = x_ExplicitVarSizeWithFlags_Values[q30] - | q32 : int(1..4)]) - | q30 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q34] != 5 -> - or([x_ExplicitVarSizeWithFlags_Flags[q36] /\ - x_ExplicitVarSizeWithFlags_Values[q36] = x_ExplicitVarSizeWithDummy[q34] - | q36 : int(1..4)]) - | q34 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_3_2_3_1-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_3_2_3_1-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_2_3_1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_3_2_3_1-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_3_2_3_1-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_2_3_1-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_3_2_3_1.eprime b/tests/exhaustive/basic/set06/expected/model_3_2_3_1.eprime deleted file mode 100644 index ff7bb579b2..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_2_3_1.eprime +++ /dev/null @@ -1,43 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -find x_Occurrence: matrix indexed by [int(1..4)] of bool -branching on - [x_Occurrence, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy] -such that - or([q28 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q28] = 1 | q28 : int(1..4)]), - or([x_ExplicitVarSizeWithDummy[q30] != 5 /\ x_ExplicitVarSizeWithDummy[q30] = 2 | q30 : int(1..4)]), - or([q32 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q32] = 3 | q32 : int(1..4)]), - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..3)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..4)]), - x_ExplicitVarSizeWithMarker_Marker <= 4, - and([x_ExplicitVarSizeWithDummy[q4] < x_ExplicitVarSizeWithDummy[q4 + 1] \/ x_ExplicitVarSizeWithDummy[q4] = 5 - | q4 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q5] = 5 -> x_ExplicitVarSizeWithDummy[q5 + 1] = 5 | q5 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q6] != 5) | q6 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithDummy[q9] != 5 -> - or([q11 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q11] = x_ExplicitVarSizeWithDummy[q9] - | q11 : int(1..4)]) - | q9 : int(1..4)]), - and([q13 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q15] != 5 /\ - x_ExplicitVarSizeWithDummy[q15] = x_ExplicitVarSizeWithMarker_Values[q13] - | q15 : int(1..4)]) - | q13 : int(1..4)]), - sum([toInt(x_Occurrence[q16]) | q16 : int(1..4)]) <= 4, - and([x_Occurrence[q17] -> - or([q19 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q19] = q17 - | q19 : int(1..4)]) - | q17 : int(1..4)]), - and([q21 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q21]] - | q21 : int(1..4)]), - and([x_Occurrence[q22] -> - or([x_ExplicitVarSizeWithDummy[q24] != 5 /\ x_ExplicitVarSizeWithDummy[q24] = q22 | q24 : int(1..4)]) - | q22 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q26] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q26]] | q26 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_3_2_3_2-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_3_2_3_2-solution000001.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_2_3_2-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_3_2_3_2-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_3_2_3_2-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_2_3_2-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_3_2_3_2.eprime b/tests/exhaustive/basic/set06/expected/model_3_2_3_2.eprime deleted file mode 100644 index e1d4abb5fe..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_2_3_2.eprime +++ /dev/null @@ -1,30 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -branching on [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] -such that - or([q17 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q17] = 1 | q17 : int(1..4)]), - or([x_ExplicitVarSizeWithDummy[q19] != 5 /\ x_ExplicitVarSizeWithDummy[q19] = 2 | q19 : int(1..4)]), - or([q21 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q21] = 3 | q21 : int(1..4)]), - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..3)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..4)]), - x_ExplicitVarSizeWithMarker_Marker <= 4, - and([x_ExplicitVarSizeWithDummy[q4] < x_ExplicitVarSizeWithDummy[q4 + 1] \/ x_ExplicitVarSizeWithDummy[q4] = 5 - | q4 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q5] = 5 -> x_ExplicitVarSizeWithDummy[q5 + 1] = 5 | q5 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q6] != 5) | q6 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithDummy[q9] != 5 -> - or([q11 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q11] = x_ExplicitVarSizeWithDummy[q9] - | q11 : int(1..4)]) - | q9 : int(1..4)]), - and([q13 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q15] != 5 /\ - x_ExplicitVarSizeWithDummy[q15] = x_ExplicitVarSizeWithMarker_Values[q13] - | q15 : int(1..4)]) - | q13 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_3_2_3_3-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_3_2_3_3-solution000001.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_2_3_3-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_3_2_3_3-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_3_2_3_3-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_2_3_3-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_3_2_3_3.eprime b/tests/exhaustive/basic/set06/expected/model_3_2_3_3.eprime deleted file mode 100644 index e1d4abb5fe..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_2_3_3.eprime +++ /dev/null @@ -1,30 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -branching on [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] -such that - or([q17 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q17] = 1 | q17 : int(1..4)]), - or([x_ExplicitVarSizeWithDummy[q19] != 5 /\ x_ExplicitVarSizeWithDummy[q19] = 2 | q19 : int(1..4)]), - or([q21 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q21] = 3 | q21 : int(1..4)]), - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..3)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..4)]), - x_ExplicitVarSizeWithMarker_Marker <= 4, - and([x_ExplicitVarSizeWithDummy[q4] < x_ExplicitVarSizeWithDummy[q4 + 1] \/ x_ExplicitVarSizeWithDummy[q4] = 5 - | q4 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q5] = 5 -> x_ExplicitVarSizeWithDummy[q5 + 1] = 5 | q5 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q6] != 5) | q6 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithDummy[q9] != 5 -> - or([q11 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q11] = x_ExplicitVarSizeWithDummy[q9] - | q11 : int(1..4)]) - | q9 : int(1..4)]), - and([q13 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q15] != 5 /\ - x_ExplicitVarSizeWithDummy[q15] = x_ExplicitVarSizeWithMarker_Values[q13] - | q15 : int(1..4)]) - | q13 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_3_2_3_4-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_3_2_3_4-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_2_3_4-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_3_2_3_4-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_3_2_3_4-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_2_3_4-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_3_2_3_4.eprime b/tests/exhaustive/basic/set06/expected/model_3_2_3_4.eprime deleted file mode 100644 index b28bec21c6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_2_3_4.eprime +++ /dev/null @@ -1,61 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithMarker_Marker, - x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy] -such that - or([q38 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q38] = 1 | q38 : int(1..4)]), - or([x_ExplicitVarSizeWithDummy[q40] != 5 /\ x_ExplicitVarSizeWithDummy[q40] = 2 | q40 : int(1..4)]), - or([q42 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q42] = 3 | q42 : int(1..4)]), - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..3)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..4)]), - x_ExplicitVarSizeWithMarker_Marker <= 4, - and([x_ExplicitVarSizeWithDummy[q4] < x_ExplicitVarSizeWithDummy[q4 + 1] \/ x_ExplicitVarSizeWithDummy[q4] = 5 - | q4 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q5] = 5 -> x_ExplicitVarSizeWithDummy[q5 + 1] = 5 | q5 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q6] != 5) | q6 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithDummy[q9] != 5 -> - or([q11 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q11] = x_ExplicitVarSizeWithDummy[q9] - | q11 : int(1..4)]) - | q9 : int(1..4)]), - and([q13 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q15] != 5 /\ - x_ExplicitVarSizeWithDummy[q15] = x_ExplicitVarSizeWithMarker_Values[q13] - | q15 : int(1..4)]) - | q13 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q16 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q16] < x_ExplicitVarSizeWithFlags_Values[q16 + 1] - | q16 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q17] = false -> x_ExplicitVarSizeWithFlags_Values[q17] = 1 - | q17 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q18 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q18] | q18 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q19]) | q19 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithFlags_Flags[q22] -> - or([q24 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q24] = x_ExplicitVarSizeWithFlags_Values[q22] - | q24 : int(1..4)]) - | q22 : int(1..4)]), - and([q26 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q28] /\ - x_ExplicitVarSizeWithFlags_Values[q28] = x_ExplicitVarSizeWithMarker_Values[q26] - | q28 : int(1..4)]) - | q26 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q30] -> - or([x_ExplicitVarSizeWithDummy[q32] != 5 /\ - x_ExplicitVarSizeWithDummy[q32] = x_ExplicitVarSizeWithFlags_Values[q30] - | q32 : int(1..4)]) - | q30 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q34] != 5 -> - or([x_ExplicitVarSizeWithFlags_Flags[q36] /\ - x_ExplicitVarSizeWithFlags_Values[q36] = x_ExplicitVarSizeWithDummy[q34] - | q36 : int(1..4)]) - | q34 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_3_2_4_1-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_3_2_4_1-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_2_4_1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_3_2_4_1-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_3_2_4_1-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_2_4_1-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_3_2_4_1.eprime b/tests/exhaustive/basic/set06/expected/model_3_2_4_1.eprime deleted file mode 100644 index 5966d0ab74..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_2_4_1.eprime +++ /dev/null @@ -1,78 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_Occurrence: matrix indexed by [int(1..4)] of bool -branching on - [x_Occurrence, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy, - x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] -such that - or([q54 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q54] = 1 | q54 : int(1..4)]), - or([x_ExplicitVarSizeWithDummy[q56] != 5 /\ x_ExplicitVarSizeWithDummy[q56] = 2 | q56 : int(1..4)]), - or([x_ExplicitVarSizeWithFlags_Flags[q58] /\ x_ExplicitVarSizeWithFlags_Values[q58] = 3 | q58 : int(1..4)]), - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..3)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..4)]), - x_ExplicitVarSizeWithMarker_Marker <= 4, - and([x_ExplicitVarSizeWithDummy[q4] < x_ExplicitVarSizeWithDummy[q4 + 1] \/ x_ExplicitVarSizeWithDummy[q4] = 5 - | q4 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q5] = 5 -> x_ExplicitVarSizeWithDummy[q5 + 1] = 5 | q5 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q6] != 5) | q6 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithDummy[q9] != 5 -> - or([q11 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q11] = x_ExplicitVarSizeWithDummy[q9] - | q11 : int(1..4)]) - | q9 : int(1..4)]), - and([q13 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q15] != 5 /\ - x_ExplicitVarSizeWithDummy[q15] = x_ExplicitVarSizeWithMarker_Values[q13] - | q15 : int(1..4)]) - | q13 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q16 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q16] < x_ExplicitVarSizeWithFlags_Values[q16 + 1] - | q16 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q17] = false -> x_ExplicitVarSizeWithFlags_Values[q17] = 1 - | q17 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q18 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q18] | q18 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q19]) | q19 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithFlags_Flags[q22] -> - or([q24 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q24] = x_ExplicitVarSizeWithFlags_Values[q22] - | q24 : int(1..4)]) - | q22 : int(1..4)]), - and([q26 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q28] /\ - x_ExplicitVarSizeWithFlags_Values[q28] = x_ExplicitVarSizeWithMarker_Values[q26] - | q28 : int(1..4)]) - | q26 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q30] -> - or([x_ExplicitVarSizeWithDummy[q32] != 5 /\ - x_ExplicitVarSizeWithDummy[q32] = x_ExplicitVarSizeWithFlags_Values[q30] - | q32 : int(1..4)]) - | q30 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q34] != 5 -> - or([x_ExplicitVarSizeWithFlags_Flags[q36] /\ - x_ExplicitVarSizeWithFlags_Values[q36] = x_ExplicitVarSizeWithDummy[q34] - | q36 : int(1..4)]) - | q34 : int(1..4)]), - sum([toInt(x_Occurrence[q37]) | q37 : int(1..4)]) <= 4, - and([x_Occurrence[q38] -> - or([q40 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q40] = q38 - | q40 : int(1..4)]) - | q38 : int(1..4)]), - and([q42 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q42]] - | q42 : int(1..4)]), - and([x_Occurrence[q43] -> - or([x_ExplicitVarSizeWithDummy[q45] != 5 /\ x_ExplicitVarSizeWithDummy[q45] = q43 | q45 : int(1..4)]) - | q43 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q47] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q47]] | q47 : int(1..4)]), - and([x_Occurrence[q48] -> - or([x_ExplicitVarSizeWithFlags_Flags[q50] /\ x_ExplicitVarSizeWithFlags_Values[q50] = q48 | q50 : int(1..4)]) - | q48 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q52] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q52]] - | q52 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_3_2_4_2-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_3_2_4_2-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_2_4_2-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_3_2_4_2-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_3_2_4_2-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_2_4_2-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_3_2_4_2.eprime b/tests/exhaustive/basic/set06/expected/model_3_2_4_2.eprime deleted file mode 100644 index d35a7e7b68..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_2_4_2.eprime +++ /dev/null @@ -1,61 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithMarker_Marker, - x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy] -such that - or([q38 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q38] = 1 | q38 : int(1..4)]), - or([x_ExplicitVarSizeWithDummy[q40] != 5 /\ x_ExplicitVarSizeWithDummy[q40] = 2 | q40 : int(1..4)]), - or([x_ExplicitVarSizeWithFlags_Flags[q42] /\ x_ExplicitVarSizeWithFlags_Values[q42] = 3 | q42 : int(1..4)]), - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..3)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..4)]), - x_ExplicitVarSizeWithMarker_Marker <= 4, - and([x_ExplicitVarSizeWithDummy[q4] < x_ExplicitVarSizeWithDummy[q4 + 1] \/ x_ExplicitVarSizeWithDummy[q4] = 5 - | q4 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q5] = 5 -> x_ExplicitVarSizeWithDummy[q5 + 1] = 5 | q5 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q6] != 5) | q6 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithDummy[q9] != 5 -> - or([q11 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q11] = x_ExplicitVarSizeWithDummy[q9] - | q11 : int(1..4)]) - | q9 : int(1..4)]), - and([q13 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q15] != 5 /\ - x_ExplicitVarSizeWithDummy[q15] = x_ExplicitVarSizeWithMarker_Values[q13] - | q15 : int(1..4)]) - | q13 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q16 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q16] < x_ExplicitVarSizeWithFlags_Values[q16 + 1] - | q16 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q17] = false -> x_ExplicitVarSizeWithFlags_Values[q17] = 1 - | q17 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q18 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q18] | q18 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q19]) | q19 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithFlags_Flags[q22] -> - or([q24 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q24] = x_ExplicitVarSizeWithFlags_Values[q22] - | q24 : int(1..4)]) - | q22 : int(1..4)]), - and([q26 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q28] /\ - x_ExplicitVarSizeWithFlags_Values[q28] = x_ExplicitVarSizeWithMarker_Values[q26] - | q28 : int(1..4)]) - | q26 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q30] -> - or([x_ExplicitVarSizeWithDummy[q32] != 5 /\ - x_ExplicitVarSizeWithDummy[q32] = x_ExplicitVarSizeWithFlags_Values[q30] - | q32 : int(1..4)]) - | q30 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q34] != 5 -> - or([x_ExplicitVarSizeWithFlags_Flags[q36] /\ - x_ExplicitVarSizeWithFlags_Values[q36] = x_ExplicitVarSizeWithDummy[q34] - | q36 : int(1..4)]) - | q34 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_3_2_4_3-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_3_2_4_3-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_2_4_3-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_3_2_4_3-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_3_2_4_3-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_2_4_3-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_3_2_4_3.eprime b/tests/exhaustive/basic/set06/expected/model_3_2_4_3.eprime deleted file mode 100644 index d35a7e7b68..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_2_4_3.eprime +++ /dev/null @@ -1,61 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithMarker_Marker, - x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy] -such that - or([q38 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q38] = 1 | q38 : int(1..4)]), - or([x_ExplicitVarSizeWithDummy[q40] != 5 /\ x_ExplicitVarSizeWithDummy[q40] = 2 | q40 : int(1..4)]), - or([x_ExplicitVarSizeWithFlags_Flags[q42] /\ x_ExplicitVarSizeWithFlags_Values[q42] = 3 | q42 : int(1..4)]), - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..3)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..4)]), - x_ExplicitVarSizeWithMarker_Marker <= 4, - and([x_ExplicitVarSizeWithDummy[q4] < x_ExplicitVarSizeWithDummy[q4 + 1] \/ x_ExplicitVarSizeWithDummy[q4] = 5 - | q4 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q5] = 5 -> x_ExplicitVarSizeWithDummy[q5 + 1] = 5 | q5 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q6] != 5) | q6 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithDummy[q9] != 5 -> - or([q11 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q11] = x_ExplicitVarSizeWithDummy[q9] - | q11 : int(1..4)]) - | q9 : int(1..4)]), - and([q13 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q15] != 5 /\ - x_ExplicitVarSizeWithDummy[q15] = x_ExplicitVarSizeWithMarker_Values[q13] - | q15 : int(1..4)]) - | q13 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q16 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q16] < x_ExplicitVarSizeWithFlags_Values[q16 + 1] - | q16 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q17] = false -> x_ExplicitVarSizeWithFlags_Values[q17] = 1 - | q17 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q18 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q18] | q18 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q19]) | q19 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithFlags_Flags[q22] -> - or([q24 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q24] = x_ExplicitVarSizeWithFlags_Values[q22] - | q24 : int(1..4)]) - | q22 : int(1..4)]), - and([q26 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q28] /\ - x_ExplicitVarSizeWithFlags_Values[q28] = x_ExplicitVarSizeWithMarker_Values[q26] - | q28 : int(1..4)]) - | q26 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q30] -> - or([x_ExplicitVarSizeWithDummy[q32] != 5 /\ - x_ExplicitVarSizeWithDummy[q32] = x_ExplicitVarSizeWithFlags_Values[q30] - | q32 : int(1..4)]) - | q30 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q34] != 5 -> - or([x_ExplicitVarSizeWithFlags_Flags[q36] /\ - x_ExplicitVarSizeWithFlags_Values[q36] = x_ExplicitVarSizeWithDummy[q34] - | q36 : int(1..4)]) - | q34 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_3_2_4_4-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_3_2_4_4-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_2_4_4-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_3_2_4_4-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_3_2_4_4-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_2_4_4-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_3_2_4_4.eprime b/tests/exhaustive/basic/set06/expected/model_3_2_4_4.eprime deleted file mode 100644 index d35a7e7b68..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_2_4_4.eprime +++ /dev/null @@ -1,61 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithMarker_Marker, - x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy] -such that - or([q38 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q38] = 1 | q38 : int(1..4)]), - or([x_ExplicitVarSizeWithDummy[q40] != 5 /\ x_ExplicitVarSizeWithDummy[q40] = 2 | q40 : int(1..4)]), - or([x_ExplicitVarSizeWithFlags_Flags[q42] /\ x_ExplicitVarSizeWithFlags_Values[q42] = 3 | q42 : int(1..4)]), - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..3)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..4)]), - x_ExplicitVarSizeWithMarker_Marker <= 4, - and([x_ExplicitVarSizeWithDummy[q4] < x_ExplicitVarSizeWithDummy[q4 + 1] \/ x_ExplicitVarSizeWithDummy[q4] = 5 - | q4 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q5] = 5 -> x_ExplicitVarSizeWithDummy[q5 + 1] = 5 | q5 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q6] != 5) | q6 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithDummy[q9] != 5 -> - or([q11 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q11] = x_ExplicitVarSizeWithDummy[q9] - | q11 : int(1..4)]) - | q9 : int(1..4)]), - and([q13 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q15] != 5 /\ - x_ExplicitVarSizeWithDummy[q15] = x_ExplicitVarSizeWithMarker_Values[q13] - | q15 : int(1..4)]) - | q13 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q16 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q16] < x_ExplicitVarSizeWithFlags_Values[q16 + 1] - | q16 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q17] = false -> x_ExplicitVarSizeWithFlags_Values[q17] = 1 - | q17 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q18 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q18] | q18 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q19]) | q19 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithFlags_Flags[q22] -> - or([q24 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q24] = x_ExplicitVarSizeWithFlags_Values[q22] - | q24 : int(1..4)]) - | q22 : int(1..4)]), - and([q26 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q28] /\ - x_ExplicitVarSizeWithFlags_Values[q28] = x_ExplicitVarSizeWithMarker_Values[q26] - | q28 : int(1..4)]) - | q26 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q30] -> - or([x_ExplicitVarSizeWithDummy[q32] != 5 /\ - x_ExplicitVarSizeWithDummy[q32] = x_ExplicitVarSizeWithFlags_Values[q30] - | q32 : int(1..4)]) - | q30 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q34] != 5 -> - or([x_ExplicitVarSizeWithFlags_Flags[q36] /\ - x_ExplicitVarSizeWithFlags_Values[q36] = x_ExplicitVarSizeWithDummy[q34] - | q36 : int(1..4)]) - | q34 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_3_3_1_1-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_3_3_1_1-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_3_1_1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_3_3_1_1-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_3_3_1_1-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_3_1_1-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_3_3_1_1.eprime b/tests/exhaustive/basic/set06/expected/model_3_3_1_1.eprime deleted file mode 100644 index 80713ad04e..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_3_1_1.eprime +++ /dev/null @@ -1,22 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_Occurrence: matrix indexed by [int(1..4)] of bool -branching on [x_Occurrence, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] -such that - or([q11 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q11] = 1 | q11 : int(1..4)]), - or([q13 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q13] = 2 | q13 : int(1..4)]), - x_Occurrence[3], - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..3)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..4)]), - x_ExplicitVarSizeWithMarker_Marker <= 4, - sum([toInt(x_Occurrence[q4]) | q4 : int(1..4)]) <= 4, - and([x_Occurrence[q5] -> - or([q7 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q7] = q5 | q7 : int(1..4)]) - | q5 : int(1..4)]), - and([q9 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q9]] - | q9 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_3_3_1_2-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_3_3_1_2-solution000001.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_3_1_2-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_3_3_1_2-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_3_3_1_2-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_3_1_2-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_3_3_1_2.eprime b/tests/exhaustive/basic/set06/expected/model_3_3_1_2.eprime deleted file mode 100644 index 53cfc835b6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_3_1_2.eprime +++ /dev/null @@ -1,43 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_Occurrence: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -branching on - [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_Occurrence] -such that - or([q28 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q28] = 1 | q28 : int(1..4)]), - or([q30 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q30] = 2 | q30 : int(1..4)]), - x_Occurrence[3], - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..3)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..4)]), - x_ExplicitVarSizeWithMarker_Marker <= 4, - sum([toInt(x_Occurrence[q4]) | q4 : int(1..4)]) <= 4, - and([x_Occurrence[q22] -> - or([q24 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q24] = q22 - | q24 : int(1..4)]) - | q22 : int(1..4)]), - and([q26 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q26]] - | q26 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q5] < x_ExplicitVarSizeWithDummy[q5 + 1] \/ x_ExplicitVarSizeWithDummy[q5] = 5 - | q5 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q6] = 5 -> x_ExplicitVarSizeWithDummy[q6 + 1] = 5 | q6 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q7] != 5) | q7 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithDummy[q10] != 5 -> - or([q12 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q12] = x_ExplicitVarSizeWithDummy[q10] - | q12 : int(1..4)]) - | q10 : int(1..4)]), - and([q14 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q16] != 5 /\ - x_ExplicitVarSizeWithDummy[q16] = x_ExplicitVarSizeWithMarker_Values[q14] - | q16 : int(1..4)]) - | q14 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q18] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q18]] | q18 : int(1..4)]), - and([x_Occurrence[q19] -> - or([x_ExplicitVarSizeWithDummy[q21] != 5 /\ x_ExplicitVarSizeWithDummy[q21] = q19 | q21 : int(1..4)]) - | q19 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_3_3_1_3-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_3_3_1_3-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_3_1_3-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_3_3_1_3-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_3_3_1_3-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_3_1_3-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_3_3_1_3.eprime b/tests/exhaustive/basic/set06/expected/model_3_3_1_3.eprime deleted file mode 100644 index 80713ad04e..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_3_1_3.eprime +++ /dev/null @@ -1,22 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_Occurrence: matrix indexed by [int(1..4)] of bool -branching on [x_Occurrence, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] -such that - or([q11 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q11] = 1 | q11 : int(1..4)]), - or([q13 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q13] = 2 | q13 : int(1..4)]), - x_Occurrence[3], - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..3)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..4)]), - x_ExplicitVarSizeWithMarker_Marker <= 4, - sum([toInt(x_Occurrence[q4]) | q4 : int(1..4)]) <= 4, - and([x_Occurrence[q5] -> - or([q7 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q7] = q5 | q7 : int(1..4)]) - | q5 : int(1..4)]), - and([q9 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q9]] - | q9 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_3_3_1_4-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_3_3_1_4-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_3_1_4-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_3_3_1_4-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_3_3_1_4-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_3_1_4-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_3_3_1_4.eprime b/tests/exhaustive/basic/set06/expected/model_3_3_1_4.eprime deleted file mode 100644 index 0f704594c0..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_3_1_4.eprime +++ /dev/null @@ -1,48 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_Occurrence: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithMarker_Marker, - x_ExplicitVarSizeWithMarker_Values, x_Occurrence] -such that - or([q29 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q29] = 1 | q29 : int(1..4)]), - or([q31 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q31] = 2 | q31 : int(1..4)]), - x_Occurrence[3], - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..3)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..4)]), - x_ExplicitVarSizeWithMarker_Marker <= 4, - sum([toInt(x_Occurrence[q4]) | q4 : int(1..4)]) <= 4, - and([x_Occurrence[q23] -> - or([q25 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q25] = q23 - | q25 : int(1..4)]) - | q23 : int(1..4)]), - and([q27 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q27]] - | q27 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q5 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q5] < x_ExplicitVarSizeWithFlags_Values[q5 + 1] - | q5 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q6] = false -> x_ExplicitVarSizeWithFlags_Values[q6] = 1 | q6 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q7] | q7 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q8]) | q8 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithFlags_Flags[q11] -> - or([q13 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q13] = x_ExplicitVarSizeWithFlags_Values[q11] - | q13 : int(1..4)]) - | q11 : int(1..4)]), - and([q15 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q17] /\ - x_ExplicitVarSizeWithFlags_Values[q17] = x_ExplicitVarSizeWithMarker_Values[q15] - | q17 : int(1..4)]) - | q15 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q19] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q19]] - | q19 : int(1..4)]), - and([x_Occurrence[q20] -> - or([x_ExplicitVarSizeWithFlags_Flags[q22] /\ x_ExplicitVarSizeWithFlags_Values[q22] = q20 | q22 : int(1..4)]) - | q20 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_3_3_2_1-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_3_3_2_1-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_3_2_1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_3_3_2_1-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_3_3_2_1-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_3_2_1-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_3_3_2_1.eprime b/tests/exhaustive/basic/set06/expected/model_3_3_2_1.eprime deleted file mode 100644 index 918bc71bcb..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_3_2_1.eprime +++ /dev/null @@ -1,43 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -find x_Occurrence: matrix indexed by [int(1..4)] of bool -branching on - [x_Occurrence, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy] -such that - or([q28 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q28] = 1 | q28 : int(1..4)]), - or([q30 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q30] = 2 | q30 : int(1..4)]), - or([x_ExplicitVarSizeWithDummy[q32] != 5 /\ x_ExplicitVarSizeWithDummy[q32] = 3 | q32 : int(1..4)]), - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..3)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..4)]), - x_ExplicitVarSizeWithMarker_Marker <= 4, - and([x_ExplicitVarSizeWithDummy[q4] < x_ExplicitVarSizeWithDummy[q4 + 1] \/ x_ExplicitVarSizeWithDummy[q4] = 5 - | q4 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q5] = 5 -> x_ExplicitVarSizeWithDummy[q5 + 1] = 5 | q5 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q6] != 5) | q6 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithDummy[q9] != 5 -> - or([q11 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q11] = x_ExplicitVarSizeWithDummy[q9] - | q11 : int(1..4)]) - | q9 : int(1..4)]), - and([q13 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q15] != 5 /\ - x_ExplicitVarSizeWithDummy[q15] = x_ExplicitVarSizeWithMarker_Values[q13] - | q15 : int(1..4)]) - | q13 : int(1..4)]), - sum([toInt(x_Occurrence[q16]) | q16 : int(1..4)]) <= 4, - and([x_Occurrence[q17] -> - or([q19 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q19] = q17 - | q19 : int(1..4)]) - | q17 : int(1..4)]), - and([q21 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q21]] - | q21 : int(1..4)]), - and([x_Occurrence[q22] -> - or([x_ExplicitVarSizeWithDummy[q24] != 5 /\ x_ExplicitVarSizeWithDummy[q24] = q22 | q24 : int(1..4)]) - | q22 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q26] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q26]] | q26 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_3_3_2_2-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_3_3_2_2-solution000001.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_3_2_2-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_3_3_2_2-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_3_3_2_2-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_3_2_2-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_3_3_2_2.eprime b/tests/exhaustive/basic/set06/expected/model_3_3_2_2.eprime deleted file mode 100644 index ddb40c5b40..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_3_2_2.eprime +++ /dev/null @@ -1,30 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -branching on [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] -such that - or([q17 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q17] = 1 | q17 : int(1..4)]), - or([q19 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q19] = 2 | q19 : int(1..4)]), - or([x_ExplicitVarSizeWithDummy[q21] != 5 /\ x_ExplicitVarSizeWithDummy[q21] = 3 | q21 : int(1..4)]), - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..3)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..4)]), - x_ExplicitVarSizeWithMarker_Marker <= 4, - and([x_ExplicitVarSizeWithDummy[q4] < x_ExplicitVarSizeWithDummy[q4 + 1] \/ x_ExplicitVarSizeWithDummy[q4] = 5 - | q4 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q5] = 5 -> x_ExplicitVarSizeWithDummy[q5 + 1] = 5 | q5 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q6] != 5) | q6 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithDummy[q9] != 5 -> - or([q11 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q11] = x_ExplicitVarSizeWithDummy[q9] - | q11 : int(1..4)]) - | q9 : int(1..4)]), - and([q13 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q15] != 5 /\ - x_ExplicitVarSizeWithDummy[q15] = x_ExplicitVarSizeWithMarker_Values[q13] - | q15 : int(1..4)]) - | q13 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_3_3_2_3-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_3_3_2_3-solution000001.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_3_2_3-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_3_3_2_3-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_3_3_2_3-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_3_2_3-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_3_3_2_3.eprime b/tests/exhaustive/basic/set06/expected/model_3_3_2_3.eprime deleted file mode 100644 index ddb40c5b40..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_3_2_3.eprime +++ /dev/null @@ -1,30 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -branching on [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] -such that - or([q17 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q17] = 1 | q17 : int(1..4)]), - or([q19 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q19] = 2 | q19 : int(1..4)]), - or([x_ExplicitVarSizeWithDummy[q21] != 5 /\ x_ExplicitVarSizeWithDummy[q21] = 3 | q21 : int(1..4)]), - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..3)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..4)]), - x_ExplicitVarSizeWithMarker_Marker <= 4, - and([x_ExplicitVarSizeWithDummy[q4] < x_ExplicitVarSizeWithDummy[q4 + 1] \/ x_ExplicitVarSizeWithDummy[q4] = 5 - | q4 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q5] = 5 -> x_ExplicitVarSizeWithDummy[q5 + 1] = 5 | q5 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q6] != 5) | q6 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithDummy[q9] != 5 -> - or([q11 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q11] = x_ExplicitVarSizeWithDummy[q9] - | q11 : int(1..4)]) - | q9 : int(1..4)]), - and([q13 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q15] != 5 /\ - x_ExplicitVarSizeWithDummy[q15] = x_ExplicitVarSizeWithMarker_Values[q13] - | q15 : int(1..4)]) - | q13 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_3_3_2_4-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_3_3_2_4-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_3_2_4-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_3_3_2_4-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_3_3_2_4-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_3_2_4-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_3_3_2_4.eprime b/tests/exhaustive/basic/set06/expected/model_3_3_2_4.eprime deleted file mode 100644 index f03b23d86a..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_3_2_4.eprime +++ /dev/null @@ -1,61 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithMarker_Marker, - x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy] -such that - or([q38 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q38] = 1 | q38 : int(1..4)]), - or([q40 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q40] = 2 | q40 : int(1..4)]), - or([x_ExplicitVarSizeWithDummy[q42] != 5 /\ x_ExplicitVarSizeWithDummy[q42] = 3 | q42 : int(1..4)]), - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..3)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..4)]), - x_ExplicitVarSizeWithMarker_Marker <= 4, - and([x_ExplicitVarSizeWithDummy[q4] < x_ExplicitVarSizeWithDummy[q4 + 1] \/ x_ExplicitVarSizeWithDummy[q4] = 5 - | q4 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q5] = 5 -> x_ExplicitVarSizeWithDummy[q5 + 1] = 5 | q5 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q6] != 5) | q6 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithDummy[q9] != 5 -> - or([q11 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q11] = x_ExplicitVarSizeWithDummy[q9] - | q11 : int(1..4)]) - | q9 : int(1..4)]), - and([q13 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q15] != 5 /\ - x_ExplicitVarSizeWithDummy[q15] = x_ExplicitVarSizeWithMarker_Values[q13] - | q15 : int(1..4)]) - | q13 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q16 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q16] < x_ExplicitVarSizeWithFlags_Values[q16 + 1] - | q16 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q17] = false -> x_ExplicitVarSizeWithFlags_Values[q17] = 1 - | q17 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q18 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q18] | q18 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q19]) | q19 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithFlags_Flags[q22] -> - or([q24 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q24] = x_ExplicitVarSizeWithFlags_Values[q22] - | q24 : int(1..4)]) - | q22 : int(1..4)]), - and([q26 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q28] /\ - x_ExplicitVarSizeWithFlags_Values[q28] = x_ExplicitVarSizeWithMarker_Values[q26] - | q28 : int(1..4)]) - | q26 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q30] -> - or([x_ExplicitVarSizeWithDummy[q32] != 5 /\ - x_ExplicitVarSizeWithDummy[q32] = x_ExplicitVarSizeWithFlags_Values[q30] - | q32 : int(1..4)]) - | q30 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q34] != 5 -> - or([x_ExplicitVarSizeWithFlags_Flags[q36] /\ - x_ExplicitVarSizeWithFlags_Values[q36] = x_ExplicitVarSizeWithDummy[q34] - | q36 : int(1..4)]) - | q34 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_3_3_3_1-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_3_3_3_1-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_3_3_1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_3_3_3_1-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_3_3_3_1-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_3_3_1-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_3_3_3_1.eprime b/tests/exhaustive/basic/set06/expected/model_3_3_3_1.eprime deleted file mode 100644 index c15dc11975..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_3_3_1.eprime +++ /dev/null @@ -1,22 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_Occurrence: matrix indexed by [int(1..4)] of bool -branching on [x_Occurrence, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] -such that - or([q11 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q11] = 1 | q11 : int(1..4)]), - or([q13 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q13] = 2 | q13 : int(1..4)]), - or([q15 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q15] = 3 | q15 : int(1..4)]), - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..3)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..4)]), - x_ExplicitVarSizeWithMarker_Marker <= 4, - sum([toInt(x_Occurrence[q4]) | q4 : int(1..4)]) <= 4, - and([x_Occurrence[q5] -> - or([q7 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q7] = q5 | q7 : int(1..4)]) - | q5 : int(1..4)]), - and([q9 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q9]] - | q9 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_3_3_3_2-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_3_3_3_2-solution000001.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_3_3_2-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_3_3_3_2-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_3_3_3_2-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_3_3_2-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_3_3_3_2.eprime b/tests/exhaustive/basic/set06/expected/model_3_3_3_2.eprime deleted file mode 100644 index 85731e5fd2..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_3_3_2.eprime +++ /dev/null @@ -1,30 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -branching on [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] -such that - or([q17 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q17] = 1 | q17 : int(1..4)]), - or([q19 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q19] = 2 | q19 : int(1..4)]), - or([q21 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q21] = 3 | q21 : int(1..4)]), - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..3)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..4)]), - x_ExplicitVarSizeWithMarker_Marker <= 4, - and([x_ExplicitVarSizeWithDummy[q4] < x_ExplicitVarSizeWithDummy[q4 + 1] \/ x_ExplicitVarSizeWithDummy[q4] = 5 - | q4 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q5] = 5 -> x_ExplicitVarSizeWithDummy[q5 + 1] = 5 | q5 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q6] != 5) | q6 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithDummy[q9] != 5 -> - or([q11 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q11] = x_ExplicitVarSizeWithDummy[q9] - | q11 : int(1..4)]) - | q9 : int(1..4)]), - and([q13 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q15] != 5 /\ - x_ExplicitVarSizeWithDummy[q15] = x_ExplicitVarSizeWithMarker_Values[q13] - | q15 : int(1..4)]) - | q13 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_3_3_3_3-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_3_3_3_3-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_3_3_3-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_3_3_3_3-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_3_3_3_3-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_3_3_3-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_3_3_3_3.eprime b/tests/exhaustive/basic/set06/expected/model_3_3_3_3.eprime deleted file mode 100644 index 68ea664f7c..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_3_3_3.eprime +++ /dev/null @@ -1,15 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -branching on [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] -such that - or([q5 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q5] = 1 | q5 : int(1..4)]), - or([q7 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q7] = 2 | q7 : int(1..4)]), - or([q9 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q9] = 3 | q9 : int(1..4)]), - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..3)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..4)]), - x_ExplicitVarSizeWithMarker_Marker <= 4 - diff --git a/tests/exhaustive/basic/set06/expected/model_3_3_3_4-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_3_3_3_4-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_3_3_4-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_3_3_3_4-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_3_3_3_4-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_3_3_4-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_3_3_3_4.eprime b/tests/exhaustive/basic/set06/expected/model_3_3_3_4.eprime deleted file mode 100644 index 5ea57c61e2..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_3_3_4.eprime +++ /dev/null @@ -1,35 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithMarker_Marker, - x_ExplicitVarSizeWithMarker_Values] -such that - or([q18 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q18] = 1 | q18 : int(1..4)]), - or([q20 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q20] = 2 | q20 : int(1..4)]), - or([q22 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q22] = 3 | q22 : int(1..4)]), - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..3)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..4)]), - x_ExplicitVarSizeWithMarker_Marker <= 4, - and([x_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q4] < x_ExplicitVarSizeWithFlags_Values[q4 + 1] - | q4 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q5] = false -> x_ExplicitVarSizeWithFlags_Values[q5] = 1 | q5 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q6] | q6 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q7]) | q7 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithFlags_Flags[q10] -> - or([q12 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q12] = x_ExplicitVarSizeWithFlags_Values[q10] - | q12 : int(1..4)]) - | q10 : int(1..4)]), - and([q14 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q16] /\ - x_ExplicitVarSizeWithFlags_Values[q16] = x_ExplicitVarSizeWithMarker_Values[q14] - | q16 : int(1..4)]) - | q14 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_3_3_4_1-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_3_3_4_1-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_3_4_1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_3_3_4_1-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_3_3_4_1-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_3_4_1-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_3_3_4_1.eprime b/tests/exhaustive/basic/set06/expected/model_3_3_4_1.eprime deleted file mode 100644 index 73c28def99..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_3_4_1.eprime +++ /dev/null @@ -1,48 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_Occurrence: matrix indexed by [int(1..4)] of bool -branching on - [x_Occurrence, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, - x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] -such that - or([q29 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q29] = 1 | q29 : int(1..4)]), - or([q31 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q31] = 2 | q31 : int(1..4)]), - or([x_ExplicitVarSizeWithFlags_Flags[q33] /\ x_ExplicitVarSizeWithFlags_Values[q33] = 3 | q33 : int(1..4)]), - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..3)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..4)]), - x_ExplicitVarSizeWithMarker_Marker <= 4, - and([x_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q4] < x_ExplicitVarSizeWithFlags_Values[q4 + 1] - | q4 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q5] = false -> x_ExplicitVarSizeWithFlags_Values[q5] = 1 | q5 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q6] | q6 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q7]) | q7 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithFlags_Flags[q10] -> - or([q12 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q12] = x_ExplicitVarSizeWithFlags_Values[q10] - | q12 : int(1..4)]) - | q10 : int(1..4)]), - and([q14 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q16] /\ - x_ExplicitVarSizeWithFlags_Values[q16] = x_ExplicitVarSizeWithMarker_Values[q14] - | q16 : int(1..4)]) - | q14 : int(1..4)]), - sum([toInt(x_Occurrence[q17]) | q17 : int(1..4)]) <= 4, - and([x_Occurrence[q18] -> - or([q20 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q20] = q18 - | q20 : int(1..4)]) - | q18 : int(1..4)]), - and([q22 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q22]] - | q22 : int(1..4)]), - and([x_Occurrence[q23] -> - or([x_ExplicitVarSizeWithFlags_Flags[q25] /\ x_ExplicitVarSizeWithFlags_Values[q25] = q23 | q25 : int(1..4)]) - | q23 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q27] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q27]] - | q27 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_3_3_4_2-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_3_3_4_2-solution000001.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_3_4_2-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_3_3_4_2-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_3_3_4_2-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_3_4_2-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_3_3_4_2.eprime b/tests/exhaustive/basic/set06/expected/model_3_3_4_2.eprime deleted file mode 100644 index d37fd441e0..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_3_4_2.eprime +++ /dev/null @@ -1,60 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -branching on - [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, - x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] -such that - or([q38 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q38] = 1 | q38 : int(1..4)]), - or([q40 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q40] = 2 | q40 : int(1..4)]), - or([x_ExplicitVarSizeWithFlags_Flags[q42] /\ x_ExplicitVarSizeWithFlags_Values[q42] = 3 | q42 : int(1..4)]), - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..3)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..4)]), - x_ExplicitVarSizeWithMarker_Marker <= 4, - and([x_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q4] < x_ExplicitVarSizeWithFlags_Values[q4 + 1] - | q4 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q5] = false -> x_ExplicitVarSizeWithFlags_Values[q5] = 1 | q5 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q6] | q6 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q7]) | q7 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithFlags_Flags[q10] -> - or([q12 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q12] = x_ExplicitVarSizeWithFlags_Values[q10] - | q12 : int(1..4)]) - | q10 : int(1..4)]), - and([q14 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q16] /\ - x_ExplicitVarSizeWithFlags_Values[q16] = x_ExplicitVarSizeWithMarker_Values[q14] - | q16 : int(1..4)]) - | q14 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q17] < x_ExplicitVarSizeWithDummy[q17 + 1] \/ x_ExplicitVarSizeWithDummy[q17] = 5 - | q17 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q18] = 5 -> x_ExplicitVarSizeWithDummy[q18 + 1] = 5 | q18 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q19] != 5) | q19 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithDummy[q22] != 5 -> - or([q24 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q24] = x_ExplicitVarSizeWithDummy[q22] - | q24 : int(1..4)]) - | q22 : int(1..4)]), - and([q26 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q28] != 5 /\ - x_ExplicitVarSizeWithDummy[q28] = x_ExplicitVarSizeWithMarker_Values[q26] - | q28 : int(1..4)]) - | q26 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q30] != 5 -> - or([x_ExplicitVarSizeWithFlags_Flags[q32] /\ - x_ExplicitVarSizeWithFlags_Values[q32] = x_ExplicitVarSizeWithDummy[q30] - | q32 : int(1..4)]) - | q30 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q34] -> - or([x_ExplicitVarSizeWithDummy[q36] != 5 /\ - x_ExplicitVarSizeWithDummy[q36] = x_ExplicitVarSizeWithFlags_Values[q34] - | q36 : int(1..4)]) - | q34 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_3_3_4_3-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_3_3_4_3-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_3_4_3-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_3_3_4_3-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_3_3_4_3-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_3_4_3-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_3_3_4_3.eprime b/tests/exhaustive/basic/set06/expected/model_3_3_4_3.eprime deleted file mode 100644 index 8356b4d465..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_3_4_3.eprime +++ /dev/null @@ -1,35 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithMarker_Marker, - x_ExplicitVarSizeWithMarker_Values] -such that - or([q18 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q18] = 1 | q18 : int(1..4)]), - or([q20 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q20] = 2 | q20 : int(1..4)]), - or([x_ExplicitVarSizeWithFlags_Flags[q22] /\ x_ExplicitVarSizeWithFlags_Values[q22] = 3 | q22 : int(1..4)]), - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..3)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..4)]), - x_ExplicitVarSizeWithMarker_Marker <= 4, - and([x_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q4] < x_ExplicitVarSizeWithFlags_Values[q4 + 1] - | q4 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q5] = false -> x_ExplicitVarSizeWithFlags_Values[q5] = 1 | q5 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q6] | q6 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q7]) | q7 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithFlags_Flags[q10] -> - or([q12 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q12] = x_ExplicitVarSizeWithFlags_Values[q10] - | q12 : int(1..4)]) - | q10 : int(1..4)]), - and([q14 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q16] /\ - x_ExplicitVarSizeWithFlags_Values[q16] = x_ExplicitVarSizeWithMarker_Values[q14] - | q16 : int(1..4)]) - | q14 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_3_3_4_4-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_3_3_4_4-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_3_4_4-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_3_3_4_4-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_3_3_4_4-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_3_4_4-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_3_3_4_4.eprime b/tests/exhaustive/basic/set06/expected/model_3_3_4_4.eprime deleted file mode 100644 index 8356b4d465..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_3_4_4.eprime +++ /dev/null @@ -1,35 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithMarker_Marker, - x_ExplicitVarSizeWithMarker_Values] -such that - or([q18 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q18] = 1 | q18 : int(1..4)]), - or([q20 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q20] = 2 | q20 : int(1..4)]), - or([x_ExplicitVarSizeWithFlags_Flags[q22] /\ x_ExplicitVarSizeWithFlags_Values[q22] = 3 | q22 : int(1..4)]), - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..3)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..4)]), - x_ExplicitVarSizeWithMarker_Marker <= 4, - and([x_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q4] < x_ExplicitVarSizeWithFlags_Values[q4 + 1] - | q4 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q5] = false -> x_ExplicitVarSizeWithFlags_Values[q5] = 1 | q5 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q6] | q6 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q7]) | q7 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithFlags_Flags[q10] -> - or([q12 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q12] = x_ExplicitVarSizeWithFlags_Values[q10] - | q12 : int(1..4)]) - | q10 : int(1..4)]), - and([q14 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q16] /\ - x_ExplicitVarSizeWithFlags_Values[q16] = x_ExplicitVarSizeWithMarker_Values[q14] - | q16 : int(1..4)]) - | q14 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_3_4_1_1-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_3_4_1_1-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_4_1_1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_3_4_1_1-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_3_4_1_1-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_4_1_1-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_3_4_1_1.eprime b/tests/exhaustive/basic/set06/expected/model_3_4_1_1.eprime deleted file mode 100644 index 4e52803143..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_4_1_1.eprime +++ /dev/null @@ -1,48 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_Occurrence: matrix indexed by [int(1..4)] of bool -branching on - [x_Occurrence, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, - x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] -such that - or([q29 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q29] = 1 | q29 : int(1..4)]), - or([x_ExplicitVarSizeWithFlags_Flags[q31] /\ x_ExplicitVarSizeWithFlags_Values[q31] = 2 | q31 : int(1..4)]), - x_Occurrence[3], - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..3)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..4)]), - x_ExplicitVarSizeWithMarker_Marker <= 4, - and([x_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q4] < x_ExplicitVarSizeWithFlags_Values[q4 + 1] - | q4 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q5] = false -> x_ExplicitVarSizeWithFlags_Values[q5] = 1 | q5 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q6] | q6 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q7]) | q7 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithFlags_Flags[q10] -> - or([q12 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q12] = x_ExplicitVarSizeWithFlags_Values[q10] - | q12 : int(1..4)]) - | q10 : int(1..4)]), - and([q14 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q16] /\ - x_ExplicitVarSizeWithFlags_Values[q16] = x_ExplicitVarSizeWithMarker_Values[q14] - | q16 : int(1..4)]) - | q14 : int(1..4)]), - sum([toInt(x_Occurrence[q17]) | q17 : int(1..4)]) <= 4, - and([x_Occurrence[q18] -> - or([q20 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q20] = q18 - | q20 : int(1..4)]) - | q18 : int(1..4)]), - and([q22 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q22]] - | q22 : int(1..4)]), - and([x_Occurrence[q23] -> - or([x_ExplicitVarSizeWithFlags_Flags[q25] /\ x_ExplicitVarSizeWithFlags_Values[q25] = q23 | q25 : int(1..4)]) - | q23 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q27] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q27]] - | q27 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_3_4_1_2-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_3_4_1_2-solution000001.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_4_1_2-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_3_4_1_2-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_3_4_1_2-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_4_1_2-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_3_4_1_2.eprime b/tests/exhaustive/basic/set06/expected/model_3_4_1_2.eprime deleted file mode 100644 index 74a01c0599..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_4_1_2.eprime +++ /dev/null @@ -1,77 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_Occurrence: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -branching on - [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, - x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_Occurrence] -such that - or([q54 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q54] = 1 | q54 : int(1..4)]), - or([x_ExplicitVarSizeWithFlags_Flags[q56] /\ x_ExplicitVarSizeWithFlags_Values[q56] = 2 | q56 : int(1..4)]), - x_Occurrence[3], - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..3)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..4)]), - x_ExplicitVarSizeWithMarker_Marker <= 4, - and([x_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q4] < x_ExplicitVarSizeWithFlags_Values[q4 + 1] - | q4 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q5] = false -> x_ExplicitVarSizeWithFlags_Values[q5] = 1 | q5 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q6] | q6 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q7]) | q7 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithFlags_Flags[q10] -> - or([q12 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q12] = x_ExplicitVarSizeWithFlags_Values[q10] - | q12 : int(1..4)]) - | q10 : int(1..4)]), - and([q14 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q16] /\ - x_ExplicitVarSizeWithFlags_Values[q16] = x_ExplicitVarSizeWithMarker_Values[q14] - | q16 : int(1..4)]) - | q14 : int(1..4)]), - sum([toInt(x_Occurrence[q17]) | q17 : int(1..4)]) <= 4, - and([x_Occurrence[q43] -> - or([q45 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q45] = q43 - | q45 : int(1..4)]) - | q43 : int(1..4)]), - and([q47 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q47]] - | q47 : int(1..4)]), - and([x_Occurrence[q48] -> - or([x_ExplicitVarSizeWithFlags_Flags[q50] /\ x_ExplicitVarSizeWithFlags_Values[q50] = q48 | q50 : int(1..4)]) - | q48 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q52] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q52]] - | q52 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q18] < x_ExplicitVarSizeWithDummy[q18 + 1] \/ x_ExplicitVarSizeWithDummy[q18] = 5 - | q18 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q19] = 5 -> x_ExplicitVarSizeWithDummy[q19 + 1] = 5 | q19 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q20] != 5) | q20 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithDummy[q23] != 5 -> - or([q25 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q25] = x_ExplicitVarSizeWithDummy[q23] - | q25 : int(1..4)]) - | q23 : int(1..4)]), - and([q27 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q29] != 5 /\ - x_ExplicitVarSizeWithDummy[q29] = x_ExplicitVarSizeWithMarker_Values[q27] - | q29 : int(1..4)]) - | q27 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q31] != 5 -> - or([x_ExplicitVarSizeWithFlags_Flags[q33] /\ - x_ExplicitVarSizeWithFlags_Values[q33] = x_ExplicitVarSizeWithDummy[q31] - | q33 : int(1..4)]) - | q31 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q35] -> - or([x_ExplicitVarSizeWithDummy[q37] != 5 /\ - x_ExplicitVarSizeWithDummy[q37] = x_ExplicitVarSizeWithFlags_Values[q35] - | q37 : int(1..4)]) - | q35 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q39] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q39]] | q39 : int(1..4)]), - and([x_Occurrence[q40] -> - or([x_ExplicitVarSizeWithDummy[q42] != 5 /\ x_ExplicitVarSizeWithDummy[q42] = q40 | q42 : int(1..4)]) - | q40 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_3_4_1_3-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_3_4_1_3-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_4_1_3-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_3_4_1_3-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_3_4_1_3-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_4_1_3-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_3_4_1_3.eprime b/tests/exhaustive/basic/set06/expected/model_3_4_1_3.eprime deleted file mode 100644 index 4e52803143..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_4_1_3.eprime +++ /dev/null @@ -1,48 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_Occurrence: matrix indexed by [int(1..4)] of bool -branching on - [x_Occurrence, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, - x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] -such that - or([q29 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q29] = 1 | q29 : int(1..4)]), - or([x_ExplicitVarSizeWithFlags_Flags[q31] /\ x_ExplicitVarSizeWithFlags_Values[q31] = 2 | q31 : int(1..4)]), - x_Occurrence[3], - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..3)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..4)]), - x_ExplicitVarSizeWithMarker_Marker <= 4, - and([x_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q4] < x_ExplicitVarSizeWithFlags_Values[q4 + 1] - | q4 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q5] = false -> x_ExplicitVarSizeWithFlags_Values[q5] = 1 | q5 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q6] | q6 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q7]) | q7 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithFlags_Flags[q10] -> - or([q12 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q12] = x_ExplicitVarSizeWithFlags_Values[q10] - | q12 : int(1..4)]) - | q10 : int(1..4)]), - and([q14 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q16] /\ - x_ExplicitVarSizeWithFlags_Values[q16] = x_ExplicitVarSizeWithMarker_Values[q14] - | q16 : int(1..4)]) - | q14 : int(1..4)]), - sum([toInt(x_Occurrence[q17]) | q17 : int(1..4)]) <= 4, - and([x_Occurrence[q18] -> - or([q20 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q20] = q18 - | q20 : int(1..4)]) - | q18 : int(1..4)]), - and([q22 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q22]] - | q22 : int(1..4)]), - and([x_Occurrence[q23] -> - or([x_ExplicitVarSizeWithFlags_Flags[q25] /\ x_ExplicitVarSizeWithFlags_Values[q25] = q23 | q25 : int(1..4)]) - | q23 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q27] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q27]] - | q27 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_3_4_1_4-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_3_4_1_4-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_4_1_4-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_3_4_1_4-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_3_4_1_4-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_4_1_4-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_3_4_1_4.eprime b/tests/exhaustive/basic/set06/expected/model_3_4_1_4.eprime deleted file mode 100644 index 4e52803143..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_4_1_4.eprime +++ /dev/null @@ -1,48 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_Occurrence: matrix indexed by [int(1..4)] of bool -branching on - [x_Occurrence, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, - x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] -such that - or([q29 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q29] = 1 | q29 : int(1..4)]), - or([x_ExplicitVarSizeWithFlags_Flags[q31] /\ x_ExplicitVarSizeWithFlags_Values[q31] = 2 | q31 : int(1..4)]), - x_Occurrence[3], - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..3)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..4)]), - x_ExplicitVarSizeWithMarker_Marker <= 4, - and([x_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q4] < x_ExplicitVarSizeWithFlags_Values[q4 + 1] - | q4 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q5] = false -> x_ExplicitVarSizeWithFlags_Values[q5] = 1 | q5 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q6] | q6 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q7]) | q7 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithFlags_Flags[q10] -> - or([q12 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q12] = x_ExplicitVarSizeWithFlags_Values[q10] - | q12 : int(1..4)]) - | q10 : int(1..4)]), - and([q14 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q16] /\ - x_ExplicitVarSizeWithFlags_Values[q16] = x_ExplicitVarSizeWithMarker_Values[q14] - | q16 : int(1..4)]) - | q14 : int(1..4)]), - sum([toInt(x_Occurrence[q17]) | q17 : int(1..4)]) <= 4, - and([x_Occurrence[q18] -> - or([q20 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q20] = q18 - | q20 : int(1..4)]) - | q18 : int(1..4)]), - and([q22 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q22]] - | q22 : int(1..4)]), - and([x_Occurrence[q23] -> - or([x_ExplicitVarSizeWithFlags_Flags[q25] /\ x_ExplicitVarSizeWithFlags_Values[q25] = q23 | q25 : int(1..4)]) - | q23 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q27] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q27]] - | q27 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_3_4_2_1-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_3_4_2_1-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_4_2_1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_3_4_2_1-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_3_4_2_1-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_4_2_1-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_3_4_2_1.eprime b/tests/exhaustive/basic/set06/expected/model_3_4_2_1.eprime deleted file mode 100644 index f93afbb056..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_4_2_1.eprime +++ /dev/null @@ -1,77 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -find x_Occurrence: matrix indexed by [int(1..4)] of bool -branching on - [x_Occurrence, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, - x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy] -such that - or([q54 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q54] = 1 | q54 : int(1..4)]), - or([x_ExplicitVarSizeWithFlags_Flags[q56] /\ x_ExplicitVarSizeWithFlags_Values[q56] = 2 | q56 : int(1..4)]), - or([x_ExplicitVarSizeWithDummy[q58] != 5 /\ x_ExplicitVarSizeWithDummy[q58] = 3 | q58 : int(1..4)]), - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..3)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..4)]), - x_ExplicitVarSizeWithMarker_Marker <= 4, - and([x_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q4] < x_ExplicitVarSizeWithFlags_Values[q4 + 1] - | q4 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q5] = false -> x_ExplicitVarSizeWithFlags_Values[q5] = 1 | q5 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q6] | q6 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q7]) | q7 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithFlags_Flags[q10] -> - or([q12 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q12] = x_ExplicitVarSizeWithFlags_Values[q10] - | q12 : int(1..4)]) - | q10 : int(1..4)]), - and([q14 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q16] /\ - x_ExplicitVarSizeWithFlags_Values[q16] = x_ExplicitVarSizeWithMarker_Values[q14] - | q16 : int(1..4)]) - | q14 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q17] < x_ExplicitVarSizeWithDummy[q17 + 1] \/ x_ExplicitVarSizeWithDummy[q17] = 5 - | q17 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q18] = 5 -> x_ExplicitVarSizeWithDummy[q18 + 1] = 5 | q18 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q19] != 5) | q19 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithDummy[q22] != 5 -> - or([q24 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q24] = x_ExplicitVarSizeWithDummy[q22] - | q24 : int(1..4)]) - | q22 : int(1..4)]), - and([q26 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q28] != 5 /\ - x_ExplicitVarSizeWithDummy[q28] = x_ExplicitVarSizeWithMarker_Values[q26] - | q28 : int(1..4)]) - | q26 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q30] != 5 -> - or([x_ExplicitVarSizeWithFlags_Flags[q32] /\ - x_ExplicitVarSizeWithFlags_Values[q32] = x_ExplicitVarSizeWithDummy[q30] - | q32 : int(1..4)]) - | q30 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q34] -> - or([x_ExplicitVarSizeWithDummy[q36] != 5 /\ - x_ExplicitVarSizeWithDummy[q36] = x_ExplicitVarSizeWithFlags_Values[q34] - | q36 : int(1..4)]) - | q34 : int(1..4)]), - sum([toInt(x_Occurrence[q37]) | q37 : int(1..4)]) <= 4, - and([x_Occurrence[q38] -> - or([q40 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q40] = q38 - | q40 : int(1..4)]) - | q38 : int(1..4)]), - and([q42 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q42]] - | q42 : int(1..4)]), - and([x_Occurrence[q43] -> - or([x_ExplicitVarSizeWithFlags_Flags[q45] /\ x_ExplicitVarSizeWithFlags_Values[q45] = q43 | q45 : int(1..4)]) - | q43 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q47] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q47]] - | q47 : int(1..4)]), - and([x_Occurrence[q48] -> - or([x_ExplicitVarSizeWithDummy[q50] != 5 /\ x_ExplicitVarSizeWithDummy[q50] = q48 | q50 : int(1..4)]) - | q48 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q52] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q52]] | q52 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_3_4_2_2-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_3_4_2_2-solution000001.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_4_2_2-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_3_4_2_2-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_3_4_2_2-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_4_2_2-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_3_4_2_2.eprime b/tests/exhaustive/basic/set06/expected/model_3_4_2_2.eprime deleted file mode 100644 index f2d9d0a651..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_4_2_2.eprime +++ /dev/null @@ -1,60 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -branching on - [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, - x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] -such that - or([q38 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q38] = 1 | q38 : int(1..4)]), - or([x_ExplicitVarSizeWithFlags_Flags[q40] /\ x_ExplicitVarSizeWithFlags_Values[q40] = 2 | q40 : int(1..4)]), - or([x_ExplicitVarSizeWithDummy[q42] != 5 /\ x_ExplicitVarSizeWithDummy[q42] = 3 | q42 : int(1..4)]), - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..3)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..4)]), - x_ExplicitVarSizeWithMarker_Marker <= 4, - and([x_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q4] < x_ExplicitVarSizeWithFlags_Values[q4 + 1] - | q4 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q5] = false -> x_ExplicitVarSizeWithFlags_Values[q5] = 1 | q5 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q6] | q6 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q7]) | q7 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithFlags_Flags[q10] -> - or([q12 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q12] = x_ExplicitVarSizeWithFlags_Values[q10] - | q12 : int(1..4)]) - | q10 : int(1..4)]), - and([q14 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q16] /\ - x_ExplicitVarSizeWithFlags_Values[q16] = x_ExplicitVarSizeWithMarker_Values[q14] - | q16 : int(1..4)]) - | q14 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q17] < x_ExplicitVarSizeWithDummy[q17 + 1] \/ x_ExplicitVarSizeWithDummy[q17] = 5 - | q17 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q18] = 5 -> x_ExplicitVarSizeWithDummy[q18 + 1] = 5 | q18 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q19] != 5) | q19 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithDummy[q22] != 5 -> - or([q24 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q24] = x_ExplicitVarSizeWithDummy[q22] - | q24 : int(1..4)]) - | q22 : int(1..4)]), - and([q26 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q28] != 5 /\ - x_ExplicitVarSizeWithDummy[q28] = x_ExplicitVarSizeWithMarker_Values[q26] - | q28 : int(1..4)]) - | q26 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q30] != 5 -> - or([x_ExplicitVarSizeWithFlags_Flags[q32] /\ - x_ExplicitVarSizeWithFlags_Values[q32] = x_ExplicitVarSizeWithDummy[q30] - | q32 : int(1..4)]) - | q30 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q34] -> - or([x_ExplicitVarSizeWithDummy[q36] != 5 /\ - x_ExplicitVarSizeWithDummy[q36] = x_ExplicitVarSizeWithFlags_Values[q34] - | q36 : int(1..4)]) - | q34 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_3_4_2_3-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_3_4_2_3-solution000001.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_4_2_3-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_3_4_2_3-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_3_4_2_3-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_4_2_3-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_3_4_2_3.eprime b/tests/exhaustive/basic/set06/expected/model_3_4_2_3.eprime deleted file mode 100644 index f2d9d0a651..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_4_2_3.eprime +++ /dev/null @@ -1,60 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -branching on - [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, - x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] -such that - or([q38 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q38] = 1 | q38 : int(1..4)]), - or([x_ExplicitVarSizeWithFlags_Flags[q40] /\ x_ExplicitVarSizeWithFlags_Values[q40] = 2 | q40 : int(1..4)]), - or([x_ExplicitVarSizeWithDummy[q42] != 5 /\ x_ExplicitVarSizeWithDummy[q42] = 3 | q42 : int(1..4)]), - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..3)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..4)]), - x_ExplicitVarSizeWithMarker_Marker <= 4, - and([x_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q4] < x_ExplicitVarSizeWithFlags_Values[q4 + 1] - | q4 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q5] = false -> x_ExplicitVarSizeWithFlags_Values[q5] = 1 | q5 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q6] | q6 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q7]) | q7 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithFlags_Flags[q10] -> - or([q12 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q12] = x_ExplicitVarSizeWithFlags_Values[q10] - | q12 : int(1..4)]) - | q10 : int(1..4)]), - and([q14 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q16] /\ - x_ExplicitVarSizeWithFlags_Values[q16] = x_ExplicitVarSizeWithMarker_Values[q14] - | q16 : int(1..4)]) - | q14 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q17] < x_ExplicitVarSizeWithDummy[q17 + 1] \/ x_ExplicitVarSizeWithDummy[q17] = 5 - | q17 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q18] = 5 -> x_ExplicitVarSizeWithDummy[q18 + 1] = 5 | q18 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q19] != 5) | q19 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithDummy[q22] != 5 -> - or([q24 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q24] = x_ExplicitVarSizeWithDummy[q22] - | q24 : int(1..4)]) - | q22 : int(1..4)]), - and([q26 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q28] != 5 /\ - x_ExplicitVarSizeWithDummy[q28] = x_ExplicitVarSizeWithMarker_Values[q26] - | q28 : int(1..4)]) - | q26 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q30] != 5 -> - or([x_ExplicitVarSizeWithFlags_Flags[q32] /\ - x_ExplicitVarSizeWithFlags_Values[q32] = x_ExplicitVarSizeWithDummy[q30] - | q32 : int(1..4)]) - | q30 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q34] -> - or([x_ExplicitVarSizeWithDummy[q36] != 5 /\ - x_ExplicitVarSizeWithDummy[q36] = x_ExplicitVarSizeWithFlags_Values[q34] - | q36 : int(1..4)]) - | q34 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_3_4_2_4-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_3_4_2_4-solution000001.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_4_2_4-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_3_4_2_4-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_3_4_2_4-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_4_2_4-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_3_4_2_4.eprime b/tests/exhaustive/basic/set06/expected/model_3_4_2_4.eprime deleted file mode 100644 index f2d9d0a651..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_4_2_4.eprime +++ /dev/null @@ -1,60 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -branching on - [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, - x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] -such that - or([q38 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q38] = 1 | q38 : int(1..4)]), - or([x_ExplicitVarSizeWithFlags_Flags[q40] /\ x_ExplicitVarSizeWithFlags_Values[q40] = 2 | q40 : int(1..4)]), - or([x_ExplicitVarSizeWithDummy[q42] != 5 /\ x_ExplicitVarSizeWithDummy[q42] = 3 | q42 : int(1..4)]), - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..3)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..4)]), - x_ExplicitVarSizeWithMarker_Marker <= 4, - and([x_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q4] < x_ExplicitVarSizeWithFlags_Values[q4 + 1] - | q4 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q5] = false -> x_ExplicitVarSizeWithFlags_Values[q5] = 1 | q5 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q6] | q6 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q7]) | q7 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithFlags_Flags[q10] -> - or([q12 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q12] = x_ExplicitVarSizeWithFlags_Values[q10] - | q12 : int(1..4)]) - | q10 : int(1..4)]), - and([q14 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q16] /\ - x_ExplicitVarSizeWithFlags_Values[q16] = x_ExplicitVarSizeWithMarker_Values[q14] - | q16 : int(1..4)]) - | q14 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q17] < x_ExplicitVarSizeWithDummy[q17 + 1] \/ x_ExplicitVarSizeWithDummy[q17] = 5 - | q17 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q18] = 5 -> x_ExplicitVarSizeWithDummy[q18 + 1] = 5 | q18 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q19] != 5) | q19 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithDummy[q22] != 5 -> - or([q24 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q24] = x_ExplicitVarSizeWithDummy[q22] - | q24 : int(1..4)]) - | q22 : int(1..4)]), - and([q26 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q28] != 5 /\ - x_ExplicitVarSizeWithDummy[q28] = x_ExplicitVarSizeWithMarker_Values[q26] - | q28 : int(1..4)]) - | q26 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q30] != 5 -> - or([x_ExplicitVarSizeWithFlags_Flags[q32] /\ - x_ExplicitVarSizeWithFlags_Values[q32] = x_ExplicitVarSizeWithDummy[q30] - | q32 : int(1..4)]) - | q30 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q34] -> - or([x_ExplicitVarSizeWithDummy[q36] != 5 /\ - x_ExplicitVarSizeWithDummy[q36] = x_ExplicitVarSizeWithFlags_Values[q34] - | q36 : int(1..4)]) - | q34 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_3_4_3_1-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_3_4_3_1-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_4_3_1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_3_4_3_1-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_3_4_3_1-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_4_3_1-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_3_4_3_1.eprime b/tests/exhaustive/basic/set06/expected/model_3_4_3_1.eprime deleted file mode 100644 index eb620a3fab..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_4_3_1.eprime +++ /dev/null @@ -1,48 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_Occurrence: matrix indexed by [int(1..4)] of bool -branching on - [x_Occurrence, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, - x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] -such that - or([q29 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q29] = 1 | q29 : int(1..4)]), - or([x_ExplicitVarSizeWithFlags_Flags[q31] /\ x_ExplicitVarSizeWithFlags_Values[q31] = 2 | q31 : int(1..4)]), - or([q33 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q33] = 3 | q33 : int(1..4)]), - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..3)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..4)]), - x_ExplicitVarSizeWithMarker_Marker <= 4, - and([x_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q4] < x_ExplicitVarSizeWithFlags_Values[q4 + 1] - | q4 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q5] = false -> x_ExplicitVarSizeWithFlags_Values[q5] = 1 | q5 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q6] | q6 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q7]) | q7 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithFlags_Flags[q10] -> - or([q12 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q12] = x_ExplicitVarSizeWithFlags_Values[q10] - | q12 : int(1..4)]) - | q10 : int(1..4)]), - and([q14 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q16] /\ - x_ExplicitVarSizeWithFlags_Values[q16] = x_ExplicitVarSizeWithMarker_Values[q14] - | q16 : int(1..4)]) - | q14 : int(1..4)]), - sum([toInt(x_Occurrence[q17]) | q17 : int(1..4)]) <= 4, - and([x_Occurrence[q18] -> - or([q20 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q20] = q18 - | q20 : int(1..4)]) - | q18 : int(1..4)]), - and([q22 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q22]] - | q22 : int(1..4)]), - and([x_Occurrence[q23] -> - or([x_ExplicitVarSizeWithFlags_Flags[q25] /\ x_ExplicitVarSizeWithFlags_Values[q25] = q23 | q25 : int(1..4)]) - | q23 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q27] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q27]] - | q27 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_3_4_3_2-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_3_4_3_2-solution000001.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_4_3_2-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_3_4_3_2-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_3_4_3_2-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_4_3_2-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_3_4_3_2.eprime b/tests/exhaustive/basic/set06/expected/model_3_4_3_2.eprime deleted file mode 100644 index 99ec382079..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_4_3_2.eprime +++ /dev/null @@ -1,60 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -branching on - [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, - x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] -such that - or([q38 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q38] = 1 | q38 : int(1..4)]), - or([x_ExplicitVarSizeWithFlags_Flags[q40] /\ x_ExplicitVarSizeWithFlags_Values[q40] = 2 | q40 : int(1..4)]), - or([q42 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q42] = 3 | q42 : int(1..4)]), - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..3)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..4)]), - x_ExplicitVarSizeWithMarker_Marker <= 4, - and([x_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q4] < x_ExplicitVarSizeWithFlags_Values[q4 + 1] - | q4 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q5] = false -> x_ExplicitVarSizeWithFlags_Values[q5] = 1 | q5 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q6] | q6 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q7]) | q7 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithFlags_Flags[q10] -> - or([q12 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q12] = x_ExplicitVarSizeWithFlags_Values[q10] - | q12 : int(1..4)]) - | q10 : int(1..4)]), - and([q14 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q16] /\ - x_ExplicitVarSizeWithFlags_Values[q16] = x_ExplicitVarSizeWithMarker_Values[q14] - | q16 : int(1..4)]) - | q14 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q17] < x_ExplicitVarSizeWithDummy[q17 + 1] \/ x_ExplicitVarSizeWithDummy[q17] = 5 - | q17 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q18] = 5 -> x_ExplicitVarSizeWithDummy[q18 + 1] = 5 | q18 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q19] != 5) | q19 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithDummy[q22] != 5 -> - or([q24 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q24] = x_ExplicitVarSizeWithDummy[q22] - | q24 : int(1..4)]) - | q22 : int(1..4)]), - and([q26 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q28] != 5 /\ - x_ExplicitVarSizeWithDummy[q28] = x_ExplicitVarSizeWithMarker_Values[q26] - | q28 : int(1..4)]) - | q26 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q30] != 5 -> - or([x_ExplicitVarSizeWithFlags_Flags[q32] /\ - x_ExplicitVarSizeWithFlags_Values[q32] = x_ExplicitVarSizeWithDummy[q30] - | q32 : int(1..4)]) - | q30 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q34] -> - or([x_ExplicitVarSizeWithDummy[q36] != 5 /\ - x_ExplicitVarSizeWithDummy[q36] = x_ExplicitVarSizeWithFlags_Values[q34] - | q36 : int(1..4)]) - | q34 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_3_4_3_3-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_3_4_3_3-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_4_3_3-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_3_4_3_3-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_3_4_3_3-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_4_3_3-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_3_4_3_3.eprime b/tests/exhaustive/basic/set06/expected/model_3_4_3_3.eprime deleted file mode 100644 index 5a5960dab7..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_4_3_3.eprime +++ /dev/null @@ -1,35 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithMarker_Marker, - x_ExplicitVarSizeWithMarker_Values] -such that - or([q18 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q18] = 1 | q18 : int(1..4)]), - or([x_ExplicitVarSizeWithFlags_Flags[q20] /\ x_ExplicitVarSizeWithFlags_Values[q20] = 2 | q20 : int(1..4)]), - or([q22 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q22] = 3 | q22 : int(1..4)]), - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..3)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..4)]), - x_ExplicitVarSizeWithMarker_Marker <= 4, - and([x_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q4] < x_ExplicitVarSizeWithFlags_Values[q4 + 1] - | q4 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q5] = false -> x_ExplicitVarSizeWithFlags_Values[q5] = 1 | q5 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q6] | q6 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q7]) | q7 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithFlags_Flags[q10] -> - or([q12 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q12] = x_ExplicitVarSizeWithFlags_Values[q10] - | q12 : int(1..4)]) - | q10 : int(1..4)]), - and([q14 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q16] /\ - x_ExplicitVarSizeWithFlags_Values[q16] = x_ExplicitVarSizeWithMarker_Values[q14] - | q16 : int(1..4)]) - | q14 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_3_4_3_4-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_3_4_3_4-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_4_3_4-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_3_4_3_4-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_3_4_3_4-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_4_3_4-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_3_4_3_4.eprime b/tests/exhaustive/basic/set06/expected/model_3_4_3_4.eprime deleted file mode 100644 index 5a5960dab7..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_4_3_4.eprime +++ /dev/null @@ -1,35 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithMarker_Marker, - x_ExplicitVarSizeWithMarker_Values] -such that - or([q18 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q18] = 1 | q18 : int(1..4)]), - or([x_ExplicitVarSizeWithFlags_Flags[q20] /\ x_ExplicitVarSizeWithFlags_Values[q20] = 2 | q20 : int(1..4)]), - or([q22 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q22] = 3 | q22 : int(1..4)]), - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..3)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..4)]), - x_ExplicitVarSizeWithMarker_Marker <= 4, - and([x_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q4] < x_ExplicitVarSizeWithFlags_Values[q4 + 1] - | q4 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q5] = false -> x_ExplicitVarSizeWithFlags_Values[q5] = 1 | q5 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q6] | q6 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q7]) | q7 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithFlags_Flags[q10] -> - or([q12 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q12] = x_ExplicitVarSizeWithFlags_Values[q10] - | q12 : int(1..4)]) - | q10 : int(1..4)]), - and([q14 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q16] /\ - x_ExplicitVarSizeWithFlags_Values[q16] = x_ExplicitVarSizeWithMarker_Values[q14] - | q16 : int(1..4)]) - | q14 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_3_4_4_1-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_3_4_4_1-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_4_4_1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_3_4_4_1-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_3_4_4_1-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_4_4_1-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_3_4_4_1.eprime b/tests/exhaustive/basic/set06/expected/model_3_4_4_1.eprime deleted file mode 100644 index 5887490b4d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_4_4_1.eprime +++ /dev/null @@ -1,48 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_Occurrence: matrix indexed by [int(1..4)] of bool -branching on - [x_Occurrence, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, - x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] -such that - or([q29 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q29] = 1 | q29 : int(1..4)]), - or([x_ExplicitVarSizeWithFlags_Flags[q31] /\ x_ExplicitVarSizeWithFlags_Values[q31] = 2 | q31 : int(1..4)]), - or([x_ExplicitVarSizeWithFlags_Flags[q33] /\ x_ExplicitVarSizeWithFlags_Values[q33] = 3 | q33 : int(1..4)]), - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..3)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..4)]), - x_ExplicitVarSizeWithMarker_Marker <= 4, - and([x_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q4] < x_ExplicitVarSizeWithFlags_Values[q4 + 1] - | q4 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q5] = false -> x_ExplicitVarSizeWithFlags_Values[q5] = 1 | q5 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q6] | q6 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q7]) | q7 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithFlags_Flags[q10] -> - or([q12 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q12] = x_ExplicitVarSizeWithFlags_Values[q10] - | q12 : int(1..4)]) - | q10 : int(1..4)]), - and([q14 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q16] /\ - x_ExplicitVarSizeWithFlags_Values[q16] = x_ExplicitVarSizeWithMarker_Values[q14] - | q16 : int(1..4)]) - | q14 : int(1..4)]), - sum([toInt(x_Occurrence[q17]) | q17 : int(1..4)]) <= 4, - and([x_Occurrence[q18] -> - or([q20 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q20] = q18 - | q20 : int(1..4)]) - | q18 : int(1..4)]), - and([q22 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q22]] - | q22 : int(1..4)]), - and([x_Occurrence[q23] -> - or([x_ExplicitVarSizeWithFlags_Flags[q25] /\ x_ExplicitVarSizeWithFlags_Values[q25] = q23 | q25 : int(1..4)]) - | q23 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q27] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q27]] - | q27 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_3_4_4_2-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_3_4_4_2-solution000001.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_4_4_2-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_3_4_4_2-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_3_4_4_2-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_4_4_2-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_3_4_4_2.eprime b/tests/exhaustive/basic/set06/expected/model_3_4_4_2.eprime deleted file mode 100644 index 5acf1611b5..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_4_4_2.eprime +++ /dev/null @@ -1,60 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -branching on - [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, - x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] -such that - or([q38 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q38] = 1 | q38 : int(1..4)]), - or([x_ExplicitVarSizeWithFlags_Flags[q40] /\ x_ExplicitVarSizeWithFlags_Values[q40] = 2 | q40 : int(1..4)]), - or([x_ExplicitVarSizeWithFlags_Flags[q42] /\ x_ExplicitVarSizeWithFlags_Values[q42] = 3 | q42 : int(1..4)]), - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..3)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..4)]), - x_ExplicitVarSizeWithMarker_Marker <= 4, - and([x_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q4] < x_ExplicitVarSizeWithFlags_Values[q4 + 1] - | q4 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q5] = false -> x_ExplicitVarSizeWithFlags_Values[q5] = 1 | q5 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q6] | q6 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q7]) | q7 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithFlags_Flags[q10] -> - or([q12 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q12] = x_ExplicitVarSizeWithFlags_Values[q10] - | q12 : int(1..4)]) - | q10 : int(1..4)]), - and([q14 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q16] /\ - x_ExplicitVarSizeWithFlags_Values[q16] = x_ExplicitVarSizeWithMarker_Values[q14] - | q16 : int(1..4)]) - | q14 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q17] < x_ExplicitVarSizeWithDummy[q17 + 1] \/ x_ExplicitVarSizeWithDummy[q17] = 5 - | q17 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q18] = 5 -> x_ExplicitVarSizeWithDummy[q18 + 1] = 5 | q18 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q19] != 5) | q19 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithDummy[q22] != 5 -> - or([q24 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q24] = x_ExplicitVarSizeWithDummy[q22] - | q24 : int(1..4)]) - | q22 : int(1..4)]), - and([q26 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q28] != 5 /\ - x_ExplicitVarSizeWithDummy[q28] = x_ExplicitVarSizeWithMarker_Values[q26] - | q28 : int(1..4)]) - | q26 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q30] != 5 -> - or([x_ExplicitVarSizeWithFlags_Flags[q32] /\ - x_ExplicitVarSizeWithFlags_Values[q32] = x_ExplicitVarSizeWithDummy[q30] - | q32 : int(1..4)]) - | q30 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q34] -> - or([x_ExplicitVarSizeWithDummy[q36] != 5 /\ - x_ExplicitVarSizeWithDummy[q36] = x_ExplicitVarSizeWithFlags_Values[q34] - | q36 : int(1..4)]) - | q34 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_3_4_4_3-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_3_4_4_3-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_4_4_3-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_3_4_4_3-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_3_4_4_3-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_4_4_3-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_3_4_4_3.eprime b/tests/exhaustive/basic/set06/expected/model_3_4_4_3.eprime deleted file mode 100644 index fadbf77294..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_4_4_3.eprime +++ /dev/null @@ -1,35 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithMarker_Marker, - x_ExplicitVarSizeWithMarker_Values] -such that - or([q18 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q18] = 1 | q18 : int(1..4)]), - or([x_ExplicitVarSizeWithFlags_Flags[q20] /\ x_ExplicitVarSizeWithFlags_Values[q20] = 2 | q20 : int(1..4)]), - or([x_ExplicitVarSizeWithFlags_Flags[q22] /\ x_ExplicitVarSizeWithFlags_Values[q22] = 3 | q22 : int(1..4)]), - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..3)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..4)]), - x_ExplicitVarSizeWithMarker_Marker <= 4, - and([x_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q4] < x_ExplicitVarSizeWithFlags_Values[q4 + 1] - | q4 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q5] = false -> x_ExplicitVarSizeWithFlags_Values[q5] = 1 | q5 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q6] | q6 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q7]) | q7 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithFlags_Flags[q10] -> - or([q12 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q12] = x_ExplicitVarSizeWithFlags_Values[q10] - | q12 : int(1..4)]) - | q10 : int(1..4)]), - and([q14 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q16] /\ - x_ExplicitVarSizeWithFlags_Values[q16] = x_ExplicitVarSizeWithMarker_Values[q14] - | q16 : int(1..4)]) - | q14 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_3_4_4_4-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_3_4_4_4-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_4_4_4-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_3_4_4_4-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_3_4_4_4-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_4_4_4-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_3_4_4_4.eprime b/tests/exhaustive/basic/set06/expected/model_3_4_4_4.eprime deleted file mode 100644 index fadbf77294..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_3_4_4_4.eprime +++ /dev/null @@ -1,35 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithMarker_Marker, - x_ExplicitVarSizeWithMarker_Values] -such that - or([q18 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q18] = 1 | q18 : int(1..4)]), - or([x_ExplicitVarSizeWithFlags_Flags[q20] /\ x_ExplicitVarSizeWithFlags_Values[q20] = 2 | q20 : int(1..4)]), - or([x_ExplicitVarSizeWithFlags_Flags[q22] /\ x_ExplicitVarSizeWithFlags_Values[q22] = 3 | q22 : int(1..4)]), - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..3)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..4)]), - x_ExplicitVarSizeWithMarker_Marker <= 4, - and([x_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q4] < x_ExplicitVarSizeWithFlags_Values[q4 + 1] - | q4 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q5] = false -> x_ExplicitVarSizeWithFlags_Values[q5] = 1 | q5 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q6] | q6 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q7]) | q7 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithFlags_Flags[q10] -> - or([q12 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q12] = x_ExplicitVarSizeWithFlags_Values[q10] - | q12 : int(1..4)]) - | q10 : int(1..4)]), - and([q14 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q16] /\ - x_ExplicitVarSizeWithFlags_Values[q16] = x_ExplicitVarSizeWithMarker_Values[q14] - | q16 : int(1..4)]) - | q14 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_4_1_1_1-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_4_1_1_1-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_1_1_1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_4_1_1_1-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_4_1_1_1-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_1_1_1-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_4_1_1_1.eprime b/tests/exhaustive/basic/set06/expected/model_4_1_1_1.eprime deleted file mode 100644 index 840476d8f2..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_1_1_1.eprime +++ /dev/null @@ -1,23 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_Occurrence: matrix indexed by [int(1..4)] of bool -branching on [x_Occurrence, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] -such that - or([x_ExplicitVarSizeWithFlags_Flags[q13] /\ x_ExplicitVarSizeWithFlags_Values[q13] = 1 | q13 : int(1..4)]), - x_Occurrence[2], - x_Occurrence[3], - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]) <= 4, - sum([toInt(x_Occurrence[q6]) | q6 : int(1..4)]) <= 4, - and([x_Occurrence[q7] -> - or([x_ExplicitVarSizeWithFlags_Flags[q9] /\ x_ExplicitVarSizeWithFlags_Values[q9] = q7 | q9 : int(1..4)]) - | q7 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q11] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q11]] - | q11 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_4_1_1_2-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_4_1_1_2-solution000001.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_1_1_2-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_4_1_1_2-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_4_1_1_2-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_1_1_2-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_4_1_1_2.eprime b/tests/exhaustive/basic/set06/expected/model_4_1_1_2.eprime deleted file mode 100644 index c40a34fba9..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_1_1_2.eprime +++ /dev/null @@ -1,43 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_Occurrence: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -branching on - [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_Occurrence] -such that - or([x_ExplicitVarSizeWithFlags_Flags[q30] /\ x_ExplicitVarSizeWithFlags_Values[q30] = 1 | q30 : int(1..4)]), - x_Occurrence[2], - x_Occurrence[3], - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]) <= 4, - sum([toInt(x_Occurrence[q6]) | q6 : int(1..4)]) <= 4, - and([x_Occurrence[q24] -> - or([x_ExplicitVarSizeWithFlags_Flags[q26] /\ x_ExplicitVarSizeWithFlags_Values[q26] = q24 | q26 : int(1..4)]) - | q24 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q28] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q28]] - | q28 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q7] < x_ExplicitVarSizeWithDummy[q7 + 1] \/ x_ExplicitVarSizeWithDummy[q7] = 5 - | q7 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q8] = 5 -> x_ExplicitVarSizeWithDummy[q8 + 1] = 5 | q8 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q9] != 5) | q9 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithDummy[q12] != 5 -> - or([x_ExplicitVarSizeWithFlags_Flags[q14] /\ - x_ExplicitVarSizeWithFlags_Values[q14] = x_ExplicitVarSizeWithDummy[q12] - | q14 : int(1..4)]) - | q12 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q16] -> - or([x_ExplicitVarSizeWithDummy[q18] != 5 /\ - x_ExplicitVarSizeWithDummy[q18] = x_ExplicitVarSizeWithFlags_Values[q16] - | q18 : int(1..4)]) - | q16 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q20] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q20]] | q20 : int(1..4)]), - and([x_Occurrence[q21] -> - or([x_ExplicitVarSizeWithDummy[q23] != 5 /\ x_ExplicitVarSizeWithDummy[q23] = q21 | q23 : int(1..4)]) - | q21 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_4_1_1_3-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_4_1_1_3-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_1_1_3-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_4_1_1_3-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_4_1_1_3-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_1_1_3-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_4_1_1_3.eprime b/tests/exhaustive/basic/set06/expected/model_4_1_1_3.eprime deleted file mode 100644 index cf6fdd09fe..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_1_1_3.eprime +++ /dev/null @@ -1,48 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_Occurrence: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithFlags_Flags, - x_ExplicitVarSizeWithFlags_Values, x_Occurrence] -such that - or([x_ExplicitVarSizeWithFlags_Flags[q29] /\ x_ExplicitVarSizeWithFlags_Values[q29] = 1 | q29 : int(1..4)]), - x_Occurrence[2], - x_Occurrence[3], - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]) <= 4, - sum([toInt(x_Occurrence[q6]) | q6 : int(1..4)]) <= 4, - and([x_Occurrence[q23] -> - or([x_ExplicitVarSizeWithFlags_Flags[q25] /\ x_ExplicitVarSizeWithFlags_Values[q25] = q23 | q25 : int(1..4)]) - | q23 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q27] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q27]] - | q27 : int(1..4)]), - and([q7 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q7] < x_ExplicitVarSizeWithMarker_Values[q7 + 1] - | q7 : int(1..3)]), - and([q8 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q8] = 1 | q8 : int(1..4)]), - x_ExplicitVarSizeWithMarker_Marker <= 4, - and([q11 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q13] /\ - x_ExplicitVarSizeWithFlags_Values[q13] = x_ExplicitVarSizeWithMarker_Values[q11] - | q13 : int(1..4)]) - | q11 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q15] -> - or([q17 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q17] = x_ExplicitVarSizeWithFlags_Values[q15] - | q17 : int(1..4)]) - | q15 : int(1..4)]), - and([q19 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q19]] - | q19 : int(1..4)]), - and([x_Occurrence[q20] -> - or([q22 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q22] = q20 - | q22 : int(1..4)]) - | q20 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_4_1_1_4-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_4_1_1_4-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_1_1_4-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_4_1_1_4-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_4_1_1_4-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_1_1_4-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_4_1_1_4.eprime b/tests/exhaustive/basic/set06/expected/model_4_1_1_4.eprime deleted file mode 100644 index 840476d8f2..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_1_1_4.eprime +++ /dev/null @@ -1,23 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_Occurrence: matrix indexed by [int(1..4)] of bool -branching on [x_Occurrence, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] -such that - or([x_ExplicitVarSizeWithFlags_Flags[q13] /\ x_ExplicitVarSizeWithFlags_Values[q13] = 1 | q13 : int(1..4)]), - x_Occurrence[2], - x_Occurrence[3], - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]) <= 4, - sum([toInt(x_Occurrence[q6]) | q6 : int(1..4)]) <= 4, - and([x_Occurrence[q7] -> - or([x_ExplicitVarSizeWithFlags_Flags[q9] /\ x_ExplicitVarSizeWithFlags_Values[q9] = q7 | q9 : int(1..4)]) - | q7 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q11] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q11]] - | q11 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_4_1_2_1-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_4_1_2_1-solution000001.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_1_2_1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_4_1_2_1-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_4_1_2_1-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_1_2_1-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_4_1_2_1.eprime b/tests/exhaustive/basic/set06/expected/model_4_1_2_1.eprime deleted file mode 100644 index 4e673b02e4..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_1_2_1.eprime +++ /dev/null @@ -1,43 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_Occurrence: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -branching on - [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_Occurrence] -such that - or([x_ExplicitVarSizeWithFlags_Flags[q32] /\ x_ExplicitVarSizeWithFlags_Values[q32] = 1 | q32 : int(1..4)]), - x_Occurrence[2], - or([x_ExplicitVarSizeWithDummy[q30] != 5 /\ x_ExplicitVarSizeWithDummy[q30] = 3 | q30 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]) <= 4, - sum([toInt(x_Occurrence[q6]) | q6 : int(1..4)]) <= 4, - and([x_Occurrence[q24] -> - or([x_ExplicitVarSizeWithFlags_Flags[q26] /\ x_ExplicitVarSizeWithFlags_Values[q26] = q24 | q26 : int(1..4)]) - | q24 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q28] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q28]] - | q28 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q7] < x_ExplicitVarSizeWithDummy[q7 + 1] \/ x_ExplicitVarSizeWithDummy[q7] = 5 - | q7 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q8] = 5 -> x_ExplicitVarSizeWithDummy[q8 + 1] = 5 | q8 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q9] != 5) | q9 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithDummy[q12] != 5 -> - or([x_ExplicitVarSizeWithFlags_Flags[q14] /\ - x_ExplicitVarSizeWithFlags_Values[q14] = x_ExplicitVarSizeWithDummy[q12] - | q14 : int(1..4)]) - | q12 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q16] -> - or([x_ExplicitVarSizeWithDummy[q18] != 5 /\ - x_ExplicitVarSizeWithDummy[q18] = x_ExplicitVarSizeWithFlags_Values[q16] - | q18 : int(1..4)]) - | q16 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q20] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q20]] | q20 : int(1..4)]), - and([x_Occurrence[q21] -> - or([x_ExplicitVarSizeWithDummy[q23] != 5 /\ x_ExplicitVarSizeWithDummy[q23] = q21 | q23 : int(1..4)]) - | q21 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_4_1_2_2-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_4_1_2_2-solution000001.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_1_2_2-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_4_1_2_2-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_4_1_2_2-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_1_2_2-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_4_1_2_2.eprime b/tests/exhaustive/basic/set06/expected/model_4_1_2_2.eprime deleted file mode 100644 index 4e673b02e4..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_1_2_2.eprime +++ /dev/null @@ -1,43 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_Occurrence: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -branching on - [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_Occurrence] -such that - or([x_ExplicitVarSizeWithFlags_Flags[q32] /\ x_ExplicitVarSizeWithFlags_Values[q32] = 1 | q32 : int(1..4)]), - x_Occurrence[2], - or([x_ExplicitVarSizeWithDummy[q30] != 5 /\ x_ExplicitVarSizeWithDummy[q30] = 3 | q30 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]) <= 4, - sum([toInt(x_Occurrence[q6]) | q6 : int(1..4)]) <= 4, - and([x_Occurrence[q24] -> - or([x_ExplicitVarSizeWithFlags_Flags[q26] /\ x_ExplicitVarSizeWithFlags_Values[q26] = q24 | q26 : int(1..4)]) - | q24 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q28] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q28]] - | q28 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q7] < x_ExplicitVarSizeWithDummy[q7 + 1] \/ x_ExplicitVarSizeWithDummy[q7] = 5 - | q7 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q8] = 5 -> x_ExplicitVarSizeWithDummy[q8 + 1] = 5 | q8 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q9] != 5) | q9 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithDummy[q12] != 5 -> - or([x_ExplicitVarSizeWithFlags_Flags[q14] /\ - x_ExplicitVarSizeWithFlags_Values[q14] = x_ExplicitVarSizeWithDummy[q12] - | q14 : int(1..4)]) - | q12 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q16] -> - or([x_ExplicitVarSizeWithDummy[q18] != 5 /\ - x_ExplicitVarSizeWithDummy[q18] = x_ExplicitVarSizeWithFlags_Values[q16] - | q18 : int(1..4)]) - | q16 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q20] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q20]] | q20 : int(1..4)]), - and([x_Occurrence[q21] -> - or([x_ExplicitVarSizeWithDummy[q23] != 5 /\ x_ExplicitVarSizeWithDummy[q23] = q21 | q23 : int(1..4)]) - | q21 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_4_1_2_3-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_4_1_2_3-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_1_2_3-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_4_1_2_3-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_4_1_2_3-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_1_2_3-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_4_1_2_3.eprime b/tests/exhaustive/basic/set06/expected/model_4_1_2_3.eprime deleted file mode 100644 index f80a5a1df4..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_1_2_3.eprime +++ /dev/null @@ -1,77 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_Occurrence: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithFlags_Flags, - x_ExplicitVarSizeWithFlags_Values, x_Occurrence, x_ExplicitVarSizeWithDummy] -such that - or([x_ExplicitVarSizeWithFlags_Flags[q56] /\ x_ExplicitVarSizeWithFlags_Values[q56] = 1 | q56 : int(1..4)]), - x_Occurrence[2], - or([x_ExplicitVarSizeWithDummy[q54] != 5 /\ x_ExplicitVarSizeWithDummy[q54] = 3 | q54 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]) <= 4, - sum([toInt(x_Occurrence[q6]) | q6 : int(1..4)]) <= 4, - and([x_Occurrence[q48] -> - or([x_ExplicitVarSizeWithFlags_Flags[q50] /\ x_ExplicitVarSizeWithFlags_Values[q50] = q48 | q50 : int(1..4)]) - | q48 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q52] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q52]] - | q52 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q7] < x_ExplicitVarSizeWithDummy[q7 + 1] \/ x_ExplicitVarSizeWithDummy[q7] = 5 - | q7 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q8] = 5 -> x_ExplicitVarSizeWithDummy[q8 + 1] = 5 | q8 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q9] != 5) | q9 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithDummy[q12] != 5 -> - or([x_ExplicitVarSizeWithFlags_Flags[q14] /\ - x_ExplicitVarSizeWithFlags_Values[q14] = x_ExplicitVarSizeWithDummy[q12] - | q14 : int(1..4)]) - | q12 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q16] -> - or([x_ExplicitVarSizeWithDummy[q18] != 5 /\ - x_ExplicitVarSizeWithDummy[q18] = x_ExplicitVarSizeWithFlags_Values[q16] - | q18 : int(1..4)]) - | q16 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q20] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q20]] | q20 : int(1..4)]), - and([x_Occurrence[q21] -> - or([x_ExplicitVarSizeWithDummy[q23] != 5 /\ x_ExplicitVarSizeWithDummy[q23] = q21 | q23 : int(1..4)]) - | q21 : int(1..4)]), - and([q24 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q24] < x_ExplicitVarSizeWithMarker_Values[q24 + 1] - | q24 : int(1..3)]), - and([q25 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q25] = 1 | q25 : int(1..4)]), - x_ExplicitVarSizeWithMarker_Marker <= 4, - and([q28 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q30] /\ - x_ExplicitVarSizeWithFlags_Values[q30] = x_ExplicitVarSizeWithMarker_Values[q28] - | q30 : int(1..4)]) - | q28 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q32] -> - or([q34 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q34] = x_ExplicitVarSizeWithFlags_Values[q32] - | q34 : int(1..4)]) - | q32 : int(1..4)]), - and([q36 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q36]] - | q36 : int(1..4)]), - and([x_Occurrence[q37] -> - or([q39 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q39] = q37 - | q39 : int(1..4)]) - | q37 : int(1..4)]), - and([q41 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q43] != 5 /\ - x_ExplicitVarSizeWithDummy[q43] = x_ExplicitVarSizeWithMarker_Values[q41] - | q43 : int(1..4)]) - | q41 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q45] != 5 -> - or([q47 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q47] = x_ExplicitVarSizeWithDummy[q45] - | q47 : int(1..4)]) - | q45 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_4_1_2_4-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_4_1_2_4-solution000001.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_1_2_4-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_4_1_2_4-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_4_1_2_4-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_1_2_4-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_4_1_2_4.eprime b/tests/exhaustive/basic/set06/expected/model_4_1_2_4.eprime deleted file mode 100644 index 4e673b02e4..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_1_2_4.eprime +++ /dev/null @@ -1,43 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_Occurrence: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -branching on - [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_Occurrence] -such that - or([x_ExplicitVarSizeWithFlags_Flags[q32] /\ x_ExplicitVarSizeWithFlags_Values[q32] = 1 | q32 : int(1..4)]), - x_Occurrence[2], - or([x_ExplicitVarSizeWithDummy[q30] != 5 /\ x_ExplicitVarSizeWithDummy[q30] = 3 | q30 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]) <= 4, - sum([toInt(x_Occurrence[q6]) | q6 : int(1..4)]) <= 4, - and([x_Occurrence[q24] -> - or([x_ExplicitVarSizeWithFlags_Flags[q26] /\ x_ExplicitVarSizeWithFlags_Values[q26] = q24 | q26 : int(1..4)]) - | q24 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q28] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q28]] - | q28 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q7] < x_ExplicitVarSizeWithDummy[q7 + 1] \/ x_ExplicitVarSizeWithDummy[q7] = 5 - | q7 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q8] = 5 -> x_ExplicitVarSizeWithDummy[q8 + 1] = 5 | q8 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q9] != 5) | q9 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithDummy[q12] != 5 -> - or([x_ExplicitVarSizeWithFlags_Flags[q14] /\ - x_ExplicitVarSizeWithFlags_Values[q14] = x_ExplicitVarSizeWithDummy[q12] - | q14 : int(1..4)]) - | q12 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q16] -> - or([x_ExplicitVarSizeWithDummy[q18] != 5 /\ - x_ExplicitVarSizeWithDummy[q18] = x_ExplicitVarSizeWithFlags_Values[q16] - | q18 : int(1..4)]) - | q16 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q20] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q20]] | q20 : int(1..4)]), - and([x_Occurrence[q21] -> - or([x_ExplicitVarSizeWithDummy[q23] != 5 /\ x_ExplicitVarSizeWithDummy[q23] = q21 | q23 : int(1..4)]) - | q21 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_4_1_3_1-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_4_1_3_1-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_1_3_1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_4_1_3_1-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_4_1_3_1-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_1_3_1-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_4_1_3_1.eprime b/tests/exhaustive/basic/set06/expected/model_4_1_3_1.eprime deleted file mode 100644 index 408fd414ac..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_1_3_1.eprime +++ /dev/null @@ -1,48 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_Occurrence: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithFlags_Flags, - x_ExplicitVarSizeWithFlags_Values, x_Occurrence] -such that - or([x_ExplicitVarSizeWithFlags_Flags[q31] /\ x_ExplicitVarSizeWithFlags_Values[q31] = 1 | q31 : int(1..4)]), - x_Occurrence[2], - or([q29 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q29] = 3 | q29 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]) <= 4, - sum([toInt(x_Occurrence[q6]) | q6 : int(1..4)]) <= 4, - and([x_Occurrence[q23] -> - or([x_ExplicitVarSizeWithFlags_Flags[q25] /\ x_ExplicitVarSizeWithFlags_Values[q25] = q23 | q25 : int(1..4)]) - | q23 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q27] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q27]] - | q27 : int(1..4)]), - and([q7 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q7] < x_ExplicitVarSizeWithMarker_Values[q7 + 1] - | q7 : int(1..3)]), - and([q8 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q8] = 1 | q8 : int(1..4)]), - x_ExplicitVarSizeWithMarker_Marker <= 4, - and([q11 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q13] /\ - x_ExplicitVarSizeWithFlags_Values[q13] = x_ExplicitVarSizeWithMarker_Values[q11] - | q13 : int(1..4)]) - | q11 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q15] -> - or([q17 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q17] = x_ExplicitVarSizeWithFlags_Values[q15] - | q17 : int(1..4)]) - | q15 : int(1..4)]), - and([q19 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q19]] - | q19 : int(1..4)]), - and([x_Occurrence[q20] -> - or([q22 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q22] = q20 - | q22 : int(1..4)]) - | q20 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_4_1_3_2-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_4_1_3_2-solution000001.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_1_3_2-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_4_1_3_2-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_4_1_3_2-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_1_3_2-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_4_1_3_2.eprime b/tests/exhaustive/basic/set06/expected/model_4_1_3_2.eprime deleted file mode 100644 index d20e6ad442..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_1_3_2.eprime +++ /dev/null @@ -1,77 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_Occurrence: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -branching on - [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_Occurrence, - x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] -such that - or([x_ExplicitVarSizeWithFlags_Flags[q56] /\ x_ExplicitVarSizeWithFlags_Values[q56] = 1 | q56 : int(1..4)]), - x_Occurrence[2], - or([q54 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q54] = 3 | q54 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]) <= 4, - sum([toInt(x_Occurrence[q6]) | q6 : int(1..4)]) <= 4, - and([x_Occurrence[q48] -> - or([x_ExplicitVarSizeWithFlags_Flags[q50] /\ x_ExplicitVarSizeWithFlags_Values[q50] = q48 | q50 : int(1..4)]) - | q48 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q52] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q52]] - | q52 : int(1..4)]), - and([q7 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q7] < x_ExplicitVarSizeWithMarker_Values[q7 + 1] - | q7 : int(1..3)]), - and([q8 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q8] = 1 | q8 : int(1..4)]), - x_ExplicitVarSizeWithMarker_Marker <= 4, - and([q11 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q13] /\ - x_ExplicitVarSizeWithFlags_Values[q13] = x_ExplicitVarSizeWithMarker_Values[q11] - | q13 : int(1..4)]) - | q11 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q15] -> - or([q17 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q17] = x_ExplicitVarSizeWithFlags_Values[q15] - | q17 : int(1..4)]) - | q15 : int(1..4)]), - and([q19 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q19]] - | q19 : int(1..4)]), - and([x_Occurrence[q20] -> - or([q22 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q22] = q20 - | q22 : int(1..4)]) - | q20 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q23] < x_ExplicitVarSizeWithDummy[q23 + 1] \/ x_ExplicitVarSizeWithDummy[q23] = 5 - | q23 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q24] = 5 -> x_ExplicitVarSizeWithDummy[q24 + 1] = 5 | q24 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q25] != 5) | q25 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithDummy[q28] != 5 -> - or([x_ExplicitVarSizeWithFlags_Flags[q30] /\ - x_ExplicitVarSizeWithFlags_Values[q30] = x_ExplicitVarSizeWithDummy[q28] - | q30 : int(1..4)]) - | q28 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q32] -> - or([x_ExplicitVarSizeWithDummy[q34] != 5 /\ - x_ExplicitVarSizeWithDummy[q34] = x_ExplicitVarSizeWithFlags_Values[q32] - | q34 : int(1..4)]) - | q32 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q36] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q36]] | q36 : int(1..4)]), - and([x_Occurrence[q37] -> - or([x_ExplicitVarSizeWithDummy[q39] != 5 /\ x_ExplicitVarSizeWithDummy[q39] = q37 | q39 : int(1..4)]) - | q37 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q41] != 5 -> - or([q43 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q43] = x_ExplicitVarSizeWithDummy[q41] - | q43 : int(1..4)]) - | q41 : int(1..4)]), - and([q45 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q47] != 5 /\ - x_ExplicitVarSizeWithDummy[q47] = x_ExplicitVarSizeWithMarker_Values[q45] - | q47 : int(1..4)]) - | q45 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_4_1_3_3-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_4_1_3_3-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_1_3_3-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_4_1_3_3-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_4_1_3_3-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_1_3_3-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_4_1_3_3.eprime b/tests/exhaustive/basic/set06/expected/model_4_1_3_3.eprime deleted file mode 100644 index 408fd414ac..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_1_3_3.eprime +++ /dev/null @@ -1,48 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_Occurrence: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithFlags_Flags, - x_ExplicitVarSizeWithFlags_Values, x_Occurrence] -such that - or([x_ExplicitVarSizeWithFlags_Flags[q31] /\ x_ExplicitVarSizeWithFlags_Values[q31] = 1 | q31 : int(1..4)]), - x_Occurrence[2], - or([q29 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q29] = 3 | q29 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]) <= 4, - sum([toInt(x_Occurrence[q6]) | q6 : int(1..4)]) <= 4, - and([x_Occurrence[q23] -> - or([x_ExplicitVarSizeWithFlags_Flags[q25] /\ x_ExplicitVarSizeWithFlags_Values[q25] = q23 | q25 : int(1..4)]) - | q23 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q27] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q27]] - | q27 : int(1..4)]), - and([q7 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q7] < x_ExplicitVarSizeWithMarker_Values[q7 + 1] - | q7 : int(1..3)]), - and([q8 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q8] = 1 | q8 : int(1..4)]), - x_ExplicitVarSizeWithMarker_Marker <= 4, - and([q11 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q13] /\ - x_ExplicitVarSizeWithFlags_Values[q13] = x_ExplicitVarSizeWithMarker_Values[q11] - | q13 : int(1..4)]) - | q11 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q15] -> - or([q17 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q17] = x_ExplicitVarSizeWithFlags_Values[q15] - | q17 : int(1..4)]) - | q15 : int(1..4)]), - and([q19 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q19]] - | q19 : int(1..4)]), - and([x_Occurrence[q20] -> - or([q22 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q22] = q20 - | q22 : int(1..4)]) - | q20 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_4_1_3_4-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_4_1_3_4-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_1_3_4-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_4_1_3_4-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_4_1_3_4-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_1_3_4-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_4_1_3_4.eprime b/tests/exhaustive/basic/set06/expected/model_4_1_3_4.eprime deleted file mode 100644 index 408fd414ac..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_1_3_4.eprime +++ /dev/null @@ -1,48 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_Occurrence: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithFlags_Flags, - x_ExplicitVarSizeWithFlags_Values, x_Occurrence] -such that - or([x_ExplicitVarSizeWithFlags_Flags[q31] /\ x_ExplicitVarSizeWithFlags_Values[q31] = 1 | q31 : int(1..4)]), - x_Occurrence[2], - or([q29 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q29] = 3 | q29 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]) <= 4, - sum([toInt(x_Occurrence[q6]) | q6 : int(1..4)]) <= 4, - and([x_Occurrence[q23] -> - or([x_ExplicitVarSizeWithFlags_Flags[q25] /\ x_ExplicitVarSizeWithFlags_Values[q25] = q23 | q25 : int(1..4)]) - | q23 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q27] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q27]] - | q27 : int(1..4)]), - and([q7 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q7] < x_ExplicitVarSizeWithMarker_Values[q7 + 1] - | q7 : int(1..3)]), - and([q8 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q8] = 1 | q8 : int(1..4)]), - x_ExplicitVarSizeWithMarker_Marker <= 4, - and([q11 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q13] /\ - x_ExplicitVarSizeWithFlags_Values[q13] = x_ExplicitVarSizeWithMarker_Values[q11] - | q13 : int(1..4)]) - | q11 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q15] -> - or([q17 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q17] = x_ExplicitVarSizeWithFlags_Values[q15] - | q17 : int(1..4)]) - | q15 : int(1..4)]), - and([q19 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q19]] - | q19 : int(1..4)]), - and([x_Occurrence[q20] -> - or([q22 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q22] = q20 - | q22 : int(1..4)]) - | q20 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_4_1_4_1-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_4_1_4_1-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_1_4_1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_4_1_4_1-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_4_1_4_1-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_1_4_1-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_4_1_4_1.eprime b/tests/exhaustive/basic/set06/expected/model_4_1_4_1.eprime deleted file mode 100644 index ab45974aa0..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_1_4_1.eprime +++ /dev/null @@ -1,23 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_Occurrence: matrix indexed by [int(1..4)] of bool -branching on [x_Occurrence, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] -such that - or([x_ExplicitVarSizeWithFlags_Flags[q15] /\ x_ExplicitVarSizeWithFlags_Values[q15] = 1 | q15 : int(1..4)]), - x_Occurrence[2], - or([x_ExplicitVarSizeWithFlags_Flags[q13] /\ x_ExplicitVarSizeWithFlags_Values[q13] = 3 | q13 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]) <= 4, - sum([toInt(x_Occurrence[q6]) | q6 : int(1..4)]) <= 4, - and([x_Occurrence[q7] -> - or([x_ExplicitVarSizeWithFlags_Flags[q9] /\ x_ExplicitVarSizeWithFlags_Values[q9] = q7 | q9 : int(1..4)]) - | q7 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q11] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q11]] - | q11 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_4_1_4_2-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_4_1_4_2-solution000001.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_1_4_2-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_4_1_4_2-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_4_1_4_2-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_1_4_2-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_4_1_4_2.eprime b/tests/exhaustive/basic/set06/expected/model_4_1_4_2.eprime deleted file mode 100644 index db7ef3b013..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_1_4_2.eprime +++ /dev/null @@ -1,43 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_Occurrence: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -branching on - [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_Occurrence] -such that - or([x_ExplicitVarSizeWithFlags_Flags[q32] /\ x_ExplicitVarSizeWithFlags_Values[q32] = 1 | q32 : int(1..4)]), - x_Occurrence[2], - or([x_ExplicitVarSizeWithFlags_Flags[q30] /\ x_ExplicitVarSizeWithFlags_Values[q30] = 3 | q30 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]) <= 4, - sum([toInt(x_Occurrence[q6]) | q6 : int(1..4)]) <= 4, - and([x_Occurrence[q24] -> - or([x_ExplicitVarSizeWithFlags_Flags[q26] /\ x_ExplicitVarSizeWithFlags_Values[q26] = q24 | q26 : int(1..4)]) - | q24 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q28] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q28]] - | q28 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q7] < x_ExplicitVarSizeWithDummy[q7 + 1] \/ x_ExplicitVarSizeWithDummy[q7] = 5 - | q7 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q8] = 5 -> x_ExplicitVarSizeWithDummy[q8 + 1] = 5 | q8 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q9] != 5) | q9 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithDummy[q12] != 5 -> - or([x_ExplicitVarSizeWithFlags_Flags[q14] /\ - x_ExplicitVarSizeWithFlags_Values[q14] = x_ExplicitVarSizeWithDummy[q12] - | q14 : int(1..4)]) - | q12 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q16] -> - or([x_ExplicitVarSizeWithDummy[q18] != 5 /\ - x_ExplicitVarSizeWithDummy[q18] = x_ExplicitVarSizeWithFlags_Values[q16] - | q18 : int(1..4)]) - | q16 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q20] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q20]] | q20 : int(1..4)]), - and([x_Occurrence[q21] -> - or([x_ExplicitVarSizeWithDummy[q23] != 5 /\ x_ExplicitVarSizeWithDummy[q23] = q21 | q23 : int(1..4)]) - | q21 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_4_1_4_3-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_4_1_4_3-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_1_4_3-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_4_1_4_3-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_4_1_4_3-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_1_4_3-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_4_1_4_3.eprime b/tests/exhaustive/basic/set06/expected/model_4_1_4_3.eprime deleted file mode 100644 index 4cec8ec549..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_1_4_3.eprime +++ /dev/null @@ -1,48 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_Occurrence: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithFlags_Flags, - x_ExplicitVarSizeWithFlags_Values, x_Occurrence] -such that - or([x_ExplicitVarSizeWithFlags_Flags[q31] /\ x_ExplicitVarSizeWithFlags_Values[q31] = 1 | q31 : int(1..4)]), - x_Occurrence[2], - or([x_ExplicitVarSizeWithFlags_Flags[q29] /\ x_ExplicitVarSizeWithFlags_Values[q29] = 3 | q29 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]) <= 4, - sum([toInt(x_Occurrence[q6]) | q6 : int(1..4)]) <= 4, - and([x_Occurrence[q23] -> - or([x_ExplicitVarSizeWithFlags_Flags[q25] /\ x_ExplicitVarSizeWithFlags_Values[q25] = q23 | q25 : int(1..4)]) - | q23 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q27] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q27]] - | q27 : int(1..4)]), - and([q7 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q7] < x_ExplicitVarSizeWithMarker_Values[q7 + 1] - | q7 : int(1..3)]), - and([q8 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q8] = 1 | q8 : int(1..4)]), - x_ExplicitVarSizeWithMarker_Marker <= 4, - and([q11 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q13] /\ - x_ExplicitVarSizeWithFlags_Values[q13] = x_ExplicitVarSizeWithMarker_Values[q11] - | q13 : int(1..4)]) - | q11 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q15] -> - or([q17 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q17] = x_ExplicitVarSizeWithFlags_Values[q15] - | q17 : int(1..4)]) - | q15 : int(1..4)]), - and([q19 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q19]] - | q19 : int(1..4)]), - and([x_Occurrence[q20] -> - or([q22 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q22] = q20 - | q22 : int(1..4)]) - | q20 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_4_1_4_4-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_4_1_4_4-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_1_4_4-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_4_1_4_4-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_4_1_4_4-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_1_4_4-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_4_1_4_4.eprime b/tests/exhaustive/basic/set06/expected/model_4_1_4_4.eprime deleted file mode 100644 index ab45974aa0..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_1_4_4.eprime +++ /dev/null @@ -1,23 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_Occurrence: matrix indexed by [int(1..4)] of bool -branching on [x_Occurrence, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] -such that - or([x_ExplicitVarSizeWithFlags_Flags[q15] /\ x_ExplicitVarSizeWithFlags_Values[q15] = 1 | q15 : int(1..4)]), - x_Occurrence[2], - or([x_ExplicitVarSizeWithFlags_Flags[q13] /\ x_ExplicitVarSizeWithFlags_Values[q13] = 3 | q13 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]) <= 4, - sum([toInt(x_Occurrence[q6]) | q6 : int(1..4)]) <= 4, - and([x_Occurrence[q7] -> - or([x_ExplicitVarSizeWithFlags_Flags[q9] /\ x_ExplicitVarSizeWithFlags_Values[q9] = q7 | q9 : int(1..4)]) - | q7 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q11] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q11]] - | q11 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_4_2_1_1-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_4_2_1_1-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_2_1_1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_4_2_1_1-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_4_2_1_1-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_2_1_1-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_4_2_1_1.eprime b/tests/exhaustive/basic/set06/expected/model_4_2_1_1.eprime deleted file mode 100644 index ab9510be14..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_2_1_1.eprime +++ /dev/null @@ -1,43 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -find x_Occurrence: matrix indexed by [int(1..4)] of bool -branching on - [x_Occurrence, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy] -such that - or([x_ExplicitVarSizeWithFlags_Flags[q30] /\ x_ExplicitVarSizeWithFlags_Values[q30] = 1 | q30 : int(1..4)]), - or([x_ExplicitVarSizeWithDummy[q32] != 5 /\ x_ExplicitVarSizeWithDummy[q32] = 2 | q32 : int(1..4)]), - x_Occurrence[3], - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithDummy[q6] < x_ExplicitVarSizeWithDummy[q6 + 1] \/ x_ExplicitVarSizeWithDummy[q6] = 5 - | q6 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q7] = 5 -> x_ExplicitVarSizeWithDummy[q7 + 1] = 5 | q7 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q8] != 5) | q8 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithDummy[q11] != 5 -> - or([x_ExplicitVarSizeWithFlags_Flags[q13] /\ - x_ExplicitVarSizeWithFlags_Values[q13] = x_ExplicitVarSizeWithDummy[q11] - | q13 : int(1..4)]) - | q11 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q15] -> - or([x_ExplicitVarSizeWithDummy[q17] != 5 /\ - x_ExplicitVarSizeWithDummy[q17] = x_ExplicitVarSizeWithFlags_Values[q15] - | q17 : int(1..4)]) - | q15 : int(1..4)]), - sum([toInt(x_Occurrence[q18]) | q18 : int(1..4)]) <= 4, - and([x_Occurrence[q19] -> - or([x_ExplicitVarSizeWithFlags_Flags[q21] /\ x_ExplicitVarSizeWithFlags_Values[q21] = q19 | q21 : int(1..4)]) - | q19 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q23] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q23]] - | q23 : int(1..4)]), - and([x_Occurrence[q24] -> - or([x_ExplicitVarSizeWithDummy[q26] != 5 /\ x_ExplicitVarSizeWithDummy[q26] = q24 | q26 : int(1..4)]) - | q24 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q28] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q28]] | q28 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_4_2_1_2-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_4_2_1_2-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_2_1_2-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_4_2_1_2-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_4_2_1_2-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_2_1_2-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_4_2_1_2.eprime b/tests/exhaustive/basic/set06/expected/model_4_2_1_2.eprime deleted file mode 100644 index ab9510be14..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_2_1_2.eprime +++ /dev/null @@ -1,43 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -find x_Occurrence: matrix indexed by [int(1..4)] of bool -branching on - [x_Occurrence, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy] -such that - or([x_ExplicitVarSizeWithFlags_Flags[q30] /\ x_ExplicitVarSizeWithFlags_Values[q30] = 1 | q30 : int(1..4)]), - or([x_ExplicitVarSizeWithDummy[q32] != 5 /\ x_ExplicitVarSizeWithDummy[q32] = 2 | q32 : int(1..4)]), - x_Occurrence[3], - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithDummy[q6] < x_ExplicitVarSizeWithDummy[q6 + 1] \/ x_ExplicitVarSizeWithDummy[q6] = 5 - | q6 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q7] = 5 -> x_ExplicitVarSizeWithDummy[q7 + 1] = 5 | q7 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q8] != 5) | q8 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithDummy[q11] != 5 -> - or([x_ExplicitVarSizeWithFlags_Flags[q13] /\ - x_ExplicitVarSizeWithFlags_Values[q13] = x_ExplicitVarSizeWithDummy[q11] - | q13 : int(1..4)]) - | q11 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q15] -> - or([x_ExplicitVarSizeWithDummy[q17] != 5 /\ - x_ExplicitVarSizeWithDummy[q17] = x_ExplicitVarSizeWithFlags_Values[q15] - | q17 : int(1..4)]) - | q15 : int(1..4)]), - sum([toInt(x_Occurrence[q18]) | q18 : int(1..4)]) <= 4, - and([x_Occurrence[q19] -> - or([x_ExplicitVarSizeWithFlags_Flags[q21] /\ x_ExplicitVarSizeWithFlags_Values[q21] = q19 | q21 : int(1..4)]) - | q19 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q23] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q23]] - | q23 : int(1..4)]), - and([x_Occurrence[q24] -> - or([x_ExplicitVarSizeWithDummy[q26] != 5 /\ x_ExplicitVarSizeWithDummy[q26] = q24 | q26 : int(1..4)]) - | q24 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q28] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q28]] | q28 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_4_2_1_3-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_4_2_1_3-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_2_1_3-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_4_2_1_3-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_4_2_1_3-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_2_1_3-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_4_2_1_3.eprime b/tests/exhaustive/basic/set06/expected/model_4_2_1_3.eprime deleted file mode 100644 index 85e53801b8..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_2_1_3.eprime +++ /dev/null @@ -1,77 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -find x_Occurrence: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithFlags_Flags, - x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy, x_Occurrence] -such that - or([x_ExplicitVarSizeWithFlags_Flags[q54] /\ x_ExplicitVarSizeWithFlags_Values[q54] = 1 | q54 : int(1..4)]), - or([x_ExplicitVarSizeWithDummy[q56] != 5 /\ x_ExplicitVarSizeWithDummy[q56] = 2 | q56 : int(1..4)]), - x_Occurrence[3], - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithDummy[q6] < x_ExplicitVarSizeWithDummy[q6 + 1] \/ x_ExplicitVarSizeWithDummy[q6] = 5 - | q6 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q7] = 5 -> x_ExplicitVarSizeWithDummy[q7 + 1] = 5 | q7 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q8] != 5) | q8 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithDummy[q11] != 5 -> - or([x_ExplicitVarSizeWithFlags_Flags[q13] /\ - x_ExplicitVarSizeWithFlags_Values[q13] = x_ExplicitVarSizeWithDummy[q11] - | q13 : int(1..4)]) - | q11 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q15] -> - or([x_ExplicitVarSizeWithDummy[q17] != 5 /\ - x_ExplicitVarSizeWithDummy[q17] = x_ExplicitVarSizeWithFlags_Values[q15] - | q17 : int(1..4)]) - | q15 : int(1..4)]), - sum([toInt(x_Occurrence[q18]) | q18 : int(1..4)]) <= 4, - and([x_Occurrence[q43] -> - or([x_ExplicitVarSizeWithFlags_Flags[q45] /\ x_ExplicitVarSizeWithFlags_Values[q45] = q43 | q45 : int(1..4)]) - | q43 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q47] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q47]] - | q47 : int(1..4)]), - and([x_Occurrence[q48] -> - or([x_ExplicitVarSizeWithDummy[q50] != 5 /\ x_ExplicitVarSizeWithDummy[q50] = q48 | q50 : int(1..4)]) - | q48 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q52] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q52]] | q52 : int(1..4)]), - and([q19 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q19] < x_ExplicitVarSizeWithMarker_Values[q19 + 1] - | q19 : int(1..3)]), - and([q20 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q20] = 1 | q20 : int(1..4)]), - x_ExplicitVarSizeWithMarker_Marker <= 4, - and([q23 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q25] /\ - x_ExplicitVarSizeWithFlags_Values[q25] = x_ExplicitVarSizeWithMarker_Values[q23] - | q25 : int(1..4)]) - | q23 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q27] -> - or([q29 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q29] = x_ExplicitVarSizeWithFlags_Values[q27] - | q29 : int(1..4)]) - | q27 : int(1..4)]), - and([q31 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q33] != 5 /\ - x_ExplicitVarSizeWithDummy[q33] = x_ExplicitVarSizeWithMarker_Values[q31] - | q33 : int(1..4)]) - | q31 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q35] != 5 -> - or([q37 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q37] = x_ExplicitVarSizeWithDummy[q35] - | q37 : int(1..4)]) - | q35 : int(1..4)]), - and([q39 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q39]] - | q39 : int(1..4)]), - and([x_Occurrence[q40] -> - or([q42 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q42] = q40 - | q42 : int(1..4)]) - | q40 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_4_2_1_4-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_4_2_1_4-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_2_1_4-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_4_2_1_4-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_4_2_1_4-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_2_1_4-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_4_2_1_4.eprime b/tests/exhaustive/basic/set06/expected/model_4_2_1_4.eprime deleted file mode 100644 index ab9510be14..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_2_1_4.eprime +++ /dev/null @@ -1,43 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -find x_Occurrence: matrix indexed by [int(1..4)] of bool -branching on - [x_Occurrence, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy] -such that - or([x_ExplicitVarSizeWithFlags_Flags[q30] /\ x_ExplicitVarSizeWithFlags_Values[q30] = 1 | q30 : int(1..4)]), - or([x_ExplicitVarSizeWithDummy[q32] != 5 /\ x_ExplicitVarSizeWithDummy[q32] = 2 | q32 : int(1..4)]), - x_Occurrence[3], - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithDummy[q6] < x_ExplicitVarSizeWithDummy[q6 + 1] \/ x_ExplicitVarSizeWithDummy[q6] = 5 - | q6 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q7] = 5 -> x_ExplicitVarSizeWithDummy[q7 + 1] = 5 | q7 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q8] != 5) | q8 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithDummy[q11] != 5 -> - or([x_ExplicitVarSizeWithFlags_Flags[q13] /\ - x_ExplicitVarSizeWithFlags_Values[q13] = x_ExplicitVarSizeWithDummy[q11] - | q13 : int(1..4)]) - | q11 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q15] -> - or([x_ExplicitVarSizeWithDummy[q17] != 5 /\ - x_ExplicitVarSizeWithDummy[q17] = x_ExplicitVarSizeWithFlags_Values[q15] - | q17 : int(1..4)]) - | q15 : int(1..4)]), - sum([toInt(x_Occurrence[q18]) | q18 : int(1..4)]) <= 4, - and([x_Occurrence[q19] -> - or([x_ExplicitVarSizeWithFlags_Flags[q21] /\ x_ExplicitVarSizeWithFlags_Values[q21] = q19 | q21 : int(1..4)]) - | q19 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q23] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q23]] - | q23 : int(1..4)]), - and([x_Occurrence[q24] -> - or([x_ExplicitVarSizeWithDummy[q26] != 5 /\ x_ExplicitVarSizeWithDummy[q26] = q24 | q26 : int(1..4)]) - | q24 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q28] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q28]] | q28 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_4_2_2_1-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_4_2_2_1-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_2_2_1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_4_2_2_1-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_4_2_2_1-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_2_2_1-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_4_2_2_1.eprime b/tests/exhaustive/basic/set06/expected/model_4_2_2_1.eprime deleted file mode 100644 index dad34d0ed0..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_2_2_1.eprime +++ /dev/null @@ -1,43 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -find x_Occurrence: matrix indexed by [int(1..4)] of bool -branching on - [x_Occurrence, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy] -such that - or([x_ExplicitVarSizeWithFlags_Flags[q30] /\ x_ExplicitVarSizeWithFlags_Values[q30] = 1 | q30 : int(1..4)]), - or([x_ExplicitVarSizeWithDummy[q32] != 5 /\ x_ExplicitVarSizeWithDummy[q32] = 2 | q32 : int(1..4)]), - or([x_ExplicitVarSizeWithDummy[q34] != 5 /\ x_ExplicitVarSizeWithDummy[q34] = 3 | q34 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithDummy[q6] < x_ExplicitVarSizeWithDummy[q6 + 1] \/ x_ExplicitVarSizeWithDummy[q6] = 5 - | q6 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q7] = 5 -> x_ExplicitVarSizeWithDummy[q7 + 1] = 5 | q7 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q8] != 5) | q8 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithDummy[q11] != 5 -> - or([x_ExplicitVarSizeWithFlags_Flags[q13] /\ - x_ExplicitVarSizeWithFlags_Values[q13] = x_ExplicitVarSizeWithDummy[q11] - | q13 : int(1..4)]) - | q11 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q15] -> - or([x_ExplicitVarSizeWithDummy[q17] != 5 /\ - x_ExplicitVarSizeWithDummy[q17] = x_ExplicitVarSizeWithFlags_Values[q15] - | q17 : int(1..4)]) - | q15 : int(1..4)]), - sum([toInt(x_Occurrence[q18]) | q18 : int(1..4)]) <= 4, - and([x_Occurrence[q19] -> - or([x_ExplicitVarSizeWithFlags_Flags[q21] /\ x_ExplicitVarSizeWithFlags_Values[q21] = q19 | q21 : int(1..4)]) - | q19 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q23] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q23]] - | q23 : int(1..4)]), - and([x_Occurrence[q24] -> - or([x_ExplicitVarSizeWithDummy[q26] != 5 /\ x_ExplicitVarSizeWithDummy[q26] = q24 | q26 : int(1..4)]) - | q24 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q28] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q28]] | q28 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_4_2_2_2-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_4_2_2_2-solution000001.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_2_2_2-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_4_2_2_2-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_4_2_2_2-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_2_2_2-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_4_2_2_2.eprime b/tests/exhaustive/basic/set06/expected/model_4_2_2_2.eprime deleted file mode 100644 index 669eaa19ca..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_2_2_2.eprime +++ /dev/null @@ -1,31 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -branching on [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] -such that - or([x_ExplicitVarSizeWithFlags_Flags[q19] /\ x_ExplicitVarSizeWithFlags_Values[q19] = 1 | q19 : int(1..4)]), - or([x_ExplicitVarSizeWithDummy[q21] != 5 /\ x_ExplicitVarSizeWithDummy[q21] = 2 | q21 : int(1..4)]), - or([x_ExplicitVarSizeWithDummy[q23] != 5 /\ x_ExplicitVarSizeWithDummy[q23] = 3 | q23 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithDummy[q6] < x_ExplicitVarSizeWithDummy[q6 + 1] \/ x_ExplicitVarSizeWithDummy[q6] = 5 - | q6 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q7] = 5 -> x_ExplicitVarSizeWithDummy[q7 + 1] = 5 | q7 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q8] != 5) | q8 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithDummy[q11] != 5 -> - or([x_ExplicitVarSizeWithFlags_Flags[q13] /\ - x_ExplicitVarSizeWithFlags_Values[q13] = x_ExplicitVarSizeWithDummy[q11] - | q13 : int(1..4)]) - | q11 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q15] -> - or([x_ExplicitVarSizeWithDummy[q17] != 5 /\ - x_ExplicitVarSizeWithDummy[q17] = x_ExplicitVarSizeWithFlags_Values[q15] - | q17 : int(1..4)]) - | q15 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_4_2_2_3-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_4_2_2_3-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_2_2_3-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_4_2_2_3-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_4_2_2_3-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_2_2_3-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_4_2_2_3.eprime b/tests/exhaustive/basic/set06/expected/model_4_2_2_3.eprime deleted file mode 100644 index 61e6544c34..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_2_2_3.eprime +++ /dev/null @@ -1,60 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithFlags_Flags, - x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy] -such that - or([x_ExplicitVarSizeWithFlags_Flags[q38] /\ x_ExplicitVarSizeWithFlags_Values[q38] = 1 | q38 : int(1..4)]), - or([x_ExplicitVarSizeWithDummy[q40] != 5 /\ x_ExplicitVarSizeWithDummy[q40] = 2 | q40 : int(1..4)]), - or([x_ExplicitVarSizeWithDummy[q42] != 5 /\ x_ExplicitVarSizeWithDummy[q42] = 3 | q42 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithDummy[q6] < x_ExplicitVarSizeWithDummy[q6 + 1] \/ x_ExplicitVarSizeWithDummy[q6] = 5 - | q6 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q7] = 5 -> x_ExplicitVarSizeWithDummy[q7 + 1] = 5 | q7 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q8] != 5) | q8 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithDummy[q11] != 5 -> - or([x_ExplicitVarSizeWithFlags_Flags[q13] /\ - x_ExplicitVarSizeWithFlags_Values[q13] = x_ExplicitVarSizeWithDummy[q11] - | q13 : int(1..4)]) - | q11 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q15] -> - or([x_ExplicitVarSizeWithDummy[q17] != 5 /\ - x_ExplicitVarSizeWithDummy[q17] = x_ExplicitVarSizeWithFlags_Values[q15] - | q17 : int(1..4)]) - | q15 : int(1..4)]), - and([q18 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q18] < x_ExplicitVarSizeWithMarker_Values[q18 + 1] - | q18 : int(1..3)]), - and([q19 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q19] = 1 | q19 : int(1..4)]), - x_ExplicitVarSizeWithMarker_Marker <= 4, - and([q22 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q24] /\ - x_ExplicitVarSizeWithFlags_Values[q24] = x_ExplicitVarSizeWithMarker_Values[q22] - | q24 : int(1..4)]) - | q22 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q26] -> - or([q28 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q28] = x_ExplicitVarSizeWithFlags_Values[q26] - | q28 : int(1..4)]) - | q26 : int(1..4)]), - and([q30 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q32] != 5 /\ - x_ExplicitVarSizeWithDummy[q32] = x_ExplicitVarSizeWithMarker_Values[q30] - | q32 : int(1..4)]) - | q30 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q34] != 5 -> - or([q36 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q36] = x_ExplicitVarSizeWithDummy[q34] - | q36 : int(1..4)]) - | q34 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_4_2_2_4-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_4_2_2_4-solution000001.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_2_2_4-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_4_2_2_4-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_4_2_2_4-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_2_2_4-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_4_2_2_4.eprime b/tests/exhaustive/basic/set06/expected/model_4_2_2_4.eprime deleted file mode 100644 index 669eaa19ca..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_2_2_4.eprime +++ /dev/null @@ -1,31 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -branching on [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] -such that - or([x_ExplicitVarSizeWithFlags_Flags[q19] /\ x_ExplicitVarSizeWithFlags_Values[q19] = 1 | q19 : int(1..4)]), - or([x_ExplicitVarSizeWithDummy[q21] != 5 /\ x_ExplicitVarSizeWithDummy[q21] = 2 | q21 : int(1..4)]), - or([x_ExplicitVarSizeWithDummy[q23] != 5 /\ x_ExplicitVarSizeWithDummy[q23] = 3 | q23 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithDummy[q6] < x_ExplicitVarSizeWithDummy[q6 + 1] \/ x_ExplicitVarSizeWithDummy[q6] = 5 - | q6 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q7] = 5 -> x_ExplicitVarSizeWithDummy[q7 + 1] = 5 | q7 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q8] != 5) | q8 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithDummy[q11] != 5 -> - or([x_ExplicitVarSizeWithFlags_Flags[q13] /\ - x_ExplicitVarSizeWithFlags_Values[q13] = x_ExplicitVarSizeWithDummy[q11] - | q13 : int(1..4)]) - | q11 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q15] -> - or([x_ExplicitVarSizeWithDummy[q17] != 5 /\ - x_ExplicitVarSizeWithDummy[q17] = x_ExplicitVarSizeWithFlags_Values[q15] - | q17 : int(1..4)]) - | q15 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_4_2_3_1-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_4_2_3_1-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_2_3_1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_4_2_3_1-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_4_2_3_1-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_2_3_1-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_4_2_3_1.eprime b/tests/exhaustive/basic/set06/expected/model_4_2_3_1.eprime deleted file mode 100644 index 1199423e9f..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_2_3_1.eprime +++ /dev/null @@ -1,77 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_Occurrence: matrix indexed by [int(1..4)] of bool -branching on - [x_Occurrence, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy, - x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] -such that - or([x_ExplicitVarSizeWithFlags_Flags[q54] /\ x_ExplicitVarSizeWithFlags_Values[q54] = 1 | q54 : int(1..4)]), - or([x_ExplicitVarSizeWithDummy[q56] != 5 /\ x_ExplicitVarSizeWithDummy[q56] = 2 | q56 : int(1..4)]), - or([q58 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q58] = 3 | q58 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithDummy[q6] < x_ExplicitVarSizeWithDummy[q6 + 1] \/ x_ExplicitVarSizeWithDummy[q6] = 5 - | q6 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q7] = 5 -> x_ExplicitVarSizeWithDummy[q7 + 1] = 5 | q7 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q8] != 5) | q8 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithDummy[q11] != 5 -> - or([x_ExplicitVarSizeWithFlags_Flags[q13] /\ - x_ExplicitVarSizeWithFlags_Values[q13] = x_ExplicitVarSizeWithDummy[q11] - | q13 : int(1..4)]) - | q11 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q15] -> - or([x_ExplicitVarSizeWithDummy[q17] != 5 /\ - x_ExplicitVarSizeWithDummy[q17] = x_ExplicitVarSizeWithFlags_Values[q15] - | q17 : int(1..4)]) - | q15 : int(1..4)]), - and([q18 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q18] < x_ExplicitVarSizeWithMarker_Values[q18 + 1] - | q18 : int(1..3)]), - and([q19 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q19] = 1 | q19 : int(1..4)]), - x_ExplicitVarSizeWithMarker_Marker <= 4, - and([q22 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q24] /\ - x_ExplicitVarSizeWithFlags_Values[q24] = x_ExplicitVarSizeWithMarker_Values[q22] - | q24 : int(1..4)]) - | q22 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q26] -> - or([q28 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q28] = x_ExplicitVarSizeWithFlags_Values[q26] - | q28 : int(1..4)]) - | q26 : int(1..4)]), - and([q30 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q32] != 5 /\ - x_ExplicitVarSizeWithDummy[q32] = x_ExplicitVarSizeWithMarker_Values[q30] - | q32 : int(1..4)]) - | q30 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q34] != 5 -> - or([q36 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q36] = x_ExplicitVarSizeWithDummy[q34] - | q36 : int(1..4)]) - | q34 : int(1..4)]), - sum([toInt(x_Occurrence[q37]) | q37 : int(1..4)]) <= 4, - and([x_Occurrence[q38] -> - or([x_ExplicitVarSizeWithFlags_Flags[q40] /\ x_ExplicitVarSizeWithFlags_Values[q40] = q38 | q40 : int(1..4)]) - | q38 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q42] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q42]] - | q42 : int(1..4)]), - and([x_Occurrence[q43] -> - or([x_ExplicitVarSizeWithDummy[q45] != 5 /\ x_ExplicitVarSizeWithDummy[q45] = q43 | q45 : int(1..4)]) - | q43 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q47] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q47]] | q47 : int(1..4)]), - and([x_Occurrence[q48] -> - or([q50 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q50] = q48 - | q50 : int(1..4)]) - | q48 : int(1..4)]), - and([q52 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q52]] - | q52 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_4_2_3_2-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_4_2_3_2-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_2_3_2-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_4_2_3_2-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_4_2_3_2-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_2_3_2-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_4_2_3_2.eprime b/tests/exhaustive/basic/set06/expected/model_4_2_3_2.eprime deleted file mode 100644 index 81418c3d6c..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_2_3_2.eprime +++ /dev/null @@ -1,60 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithFlags_Flags, - x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy] -such that - or([x_ExplicitVarSizeWithFlags_Flags[q38] /\ x_ExplicitVarSizeWithFlags_Values[q38] = 1 | q38 : int(1..4)]), - or([x_ExplicitVarSizeWithDummy[q40] != 5 /\ x_ExplicitVarSizeWithDummy[q40] = 2 | q40 : int(1..4)]), - or([q42 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q42] = 3 | q42 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithDummy[q6] < x_ExplicitVarSizeWithDummy[q6 + 1] \/ x_ExplicitVarSizeWithDummy[q6] = 5 - | q6 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q7] = 5 -> x_ExplicitVarSizeWithDummy[q7 + 1] = 5 | q7 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q8] != 5) | q8 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithDummy[q11] != 5 -> - or([x_ExplicitVarSizeWithFlags_Flags[q13] /\ - x_ExplicitVarSizeWithFlags_Values[q13] = x_ExplicitVarSizeWithDummy[q11] - | q13 : int(1..4)]) - | q11 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q15] -> - or([x_ExplicitVarSizeWithDummy[q17] != 5 /\ - x_ExplicitVarSizeWithDummy[q17] = x_ExplicitVarSizeWithFlags_Values[q15] - | q17 : int(1..4)]) - | q15 : int(1..4)]), - and([q18 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q18] < x_ExplicitVarSizeWithMarker_Values[q18 + 1] - | q18 : int(1..3)]), - and([q19 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q19] = 1 | q19 : int(1..4)]), - x_ExplicitVarSizeWithMarker_Marker <= 4, - and([q22 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q24] /\ - x_ExplicitVarSizeWithFlags_Values[q24] = x_ExplicitVarSizeWithMarker_Values[q22] - | q24 : int(1..4)]) - | q22 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q26] -> - or([q28 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q28] = x_ExplicitVarSizeWithFlags_Values[q26] - | q28 : int(1..4)]) - | q26 : int(1..4)]), - and([q30 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q32] != 5 /\ - x_ExplicitVarSizeWithDummy[q32] = x_ExplicitVarSizeWithMarker_Values[q30] - | q32 : int(1..4)]) - | q30 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q34] != 5 -> - or([q36 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q36] = x_ExplicitVarSizeWithDummy[q34] - | q36 : int(1..4)]) - | q34 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_4_2_3_3-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_4_2_3_3-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_2_3_3-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_4_2_3_3-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_4_2_3_3-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_2_3_3-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_4_2_3_3.eprime b/tests/exhaustive/basic/set06/expected/model_4_2_3_3.eprime deleted file mode 100644 index 81418c3d6c..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_2_3_3.eprime +++ /dev/null @@ -1,60 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithFlags_Flags, - x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy] -such that - or([x_ExplicitVarSizeWithFlags_Flags[q38] /\ x_ExplicitVarSizeWithFlags_Values[q38] = 1 | q38 : int(1..4)]), - or([x_ExplicitVarSizeWithDummy[q40] != 5 /\ x_ExplicitVarSizeWithDummy[q40] = 2 | q40 : int(1..4)]), - or([q42 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q42] = 3 | q42 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithDummy[q6] < x_ExplicitVarSizeWithDummy[q6 + 1] \/ x_ExplicitVarSizeWithDummy[q6] = 5 - | q6 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q7] = 5 -> x_ExplicitVarSizeWithDummy[q7 + 1] = 5 | q7 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q8] != 5) | q8 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithDummy[q11] != 5 -> - or([x_ExplicitVarSizeWithFlags_Flags[q13] /\ - x_ExplicitVarSizeWithFlags_Values[q13] = x_ExplicitVarSizeWithDummy[q11] - | q13 : int(1..4)]) - | q11 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q15] -> - or([x_ExplicitVarSizeWithDummy[q17] != 5 /\ - x_ExplicitVarSizeWithDummy[q17] = x_ExplicitVarSizeWithFlags_Values[q15] - | q17 : int(1..4)]) - | q15 : int(1..4)]), - and([q18 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q18] < x_ExplicitVarSizeWithMarker_Values[q18 + 1] - | q18 : int(1..3)]), - and([q19 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q19] = 1 | q19 : int(1..4)]), - x_ExplicitVarSizeWithMarker_Marker <= 4, - and([q22 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q24] /\ - x_ExplicitVarSizeWithFlags_Values[q24] = x_ExplicitVarSizeWithMarker_Values[q22] - | q24 : int(1..4)]) - | q22 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q26] -> - or([q28 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q28] = x_ExplicitVarSizeWithFlags_Values[q26] - | q28 : int(1..4)]) - | q26 : int(1..4)]), - and([q30 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q32] != 5 /\ - x_ExplicitVarSizeWithDummy[q32] = x_ExplicitVarSizeWithMarker_Values[q30] - | q32 : int(1..4)]) - | q30 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q34] != 5 -> - or([q36 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q36] = x_ExplicitVarSizeWithDummy[q34] - | q36 : int(1..4)]) - | q34 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_4_2_3_4-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_4_2_3_4-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_2_3_4-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_4_2_3_4-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_4_2_3_4-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_2_3_4-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_4_2_3_4.eprime b/tests/exhaustive/basic/set06/expected/model_4_2_3_4.eprime deleted file mode 100644 index 81418c3d6c..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_2_3_4.eprime +++ /dev/null @@ -1,60 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithFlags_Flags, - x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy] -such that - or([x_ExplicitVarSizeWithFlags_Flags[q38] /\ x_ExplicitVarSizeWithFlags_Values[q38] = 1 | q38 : int(1..4)]), - or([x_ExplicitVarSizeWithDummy[q40] != 5 /\ x_ExplicitVarSizeWithDummy[q40] = 2 | q40 : int(1..4)]), - or([q42 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q42] = 3 | q42 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithDummy[q6] < x_ExplicitVarSizeWithDummy[q6 + 1] \/ x_ExplicitVarSizeWithDummy[q6] = 5 - | q6 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q7] = 5 -> x_ExplicitVarSizeWithDummy[q7 + 1] = 5 | q7 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q8] != 5) | q8 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithDummy[q11] != 5 -> - or([x_ExplicitVarSizeWithFlags_Flags[q13] /\ - x_ExplicitVarSizeWithFlags_Values[q13] = x_ExplicitVarSizeWithDummy[q11] - | q13 : int(1..4)]) - | q11 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q15] -> - or([x_ExplicitVarSizeWithDummy[q17] != 5 /\ - x_ExplicitVarSizeWithDummy[q17] = x_ExplicitVarSizeWithFlags_Values[q15] - | q17 : int(1..4)]) - | q15 : int(1..4)]), - and([q18 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q18] < x_ExplicitVarSizeWithMarker_Values[q18 + 1] - | q18 : int(1..3)]), - and([q19 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q19] = 1 | q19 : int(1..4)]), - x_ExplicitVarSizeWithMarker_Marker <= 4, - and([q22 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q24] /\ - x_ExplicitVarSizeWithFlags_Values[q24] = x_ExplicitVarSizeWithMarker_Values[q22] - | q24 : int(1..4)]) - | q22 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q26] -> - or([q28 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q28] = x_ExplicitVarSizeWithFlags_Values[q26] - | q28 : int(1..4)]) - | q26 : int(1..4)]), - and([q30 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q32] != 5 /\ - x_ExplicitVarSizeWithDummy[q32] = x_ExplicitVarSizeWithMarker_Values[q30] - | q32 : int(1..4)]) - | q30 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q34] != 5 -> - or([q36 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q36] = x_ExplicitVarSizeWithDummy[q34] - | q36 : int(1..4)]) - | q34 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_4_2_4_1-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_4_2_4_1-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_2_4_1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_4_2_4_1-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_4_2_4_1-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_2_4_1-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_4_2_4_1.eprime b/tests/exhaustive/basic/set06/expected/model_4_2_4_1.eprime deleted file mode 100644 index a14326708e..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_2_4_1.eprime +++ /dev/null @@ -1,43 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -find x_Occurrence: matrix indexed by [int(1..4)] of bool -branching on - [x_Occurrence, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy] -such that - or([x_ExplicitVarSizeWithFlags_Flags[q30] /\ x_ExplicitVarSizeWithFlags_Values[q30] = 1 | q30 : int(1..4)]), - or([x_ExplicitVarSizeWithDummy[q32] != 5 /\ x_ExplicitVarSizeWithDummy[q32] = 2 | q32 : int(1..4)]), - or([x_ExplicitVarSizeWithFlags_Flags[q34] /\ x_ExplicitVarSizeWithFlags_Values[q34] = 3 | q34 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithDummy[q6] < x_ExplicitVarSizeWithDummy[q6 + 1] \/ x_ExplicitVarSizeWithDummy[q6] = 5 - | q6 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q7] = 5 -> x_ExplicitVarSizeWithDummy[q7 + 1] = 5 | q7 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q8] != 5) | q8 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithDummy[q11] != 5 -> - or([x_ExplicitVarSizeWithFlags_Flags[q13] /\ - x_ExplicitVarSizeWithFlags_Values[q13] = x_ExplicitVarSizeWithDummy[q11] - | q13 : int(1..4)]) - | q11 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q15] -> - or([x_ExplicitVarSizeWithDummy[q17] != 5 /\ - x_ExplicitVarSizeWithDummy[q17] = x_ExplicitVarSizeWithFlags_Values[q15] - | q17 : int(1..4)]) - | q15 : int(1..4)]), - sum([toInt(x_Occurrence[q18]) | q18 : int(1..4)]) <= 4, - and([x_Occurrence[q19] -> - or([x_ExplicitVarSizeWithFlags_Flags[q21] /\ x_ExplicitVarSizeWithFlags_Values[q21] = q19 | q21 : int(1..4)]) - | q19 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q23] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q23]] - | q23 : int(1..4)]), - and([x_Occurrence[q24] -> - or([x_ExplicitVarSizeWithDummy[q26] != 5 /\ x_ExplicitVarSizeWithDummy[q26] = q24 | q26 : int(1..4)]) - | q24 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q28] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q28]] | q28 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_4_2_4_2-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_4_2_4_2-solution000001.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_2_4_2-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_4_2_4_2-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_4_2_4_2-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_2_4_2-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_4_2_4_2.eprime b/tests/exhaustive/basic/set06/expected/model_4_2_4_2.eprime deleted file mode 100644 index e7dbd3a21e..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_2_4_2.eprime +++ /dev/null @@ -1,31 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -branching on [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] -such that - or([x_ExplicitVarSizeWithFlags_Flags[q19] /\ x_ExplicitVarSizeWithFlags_Values[q19] = 1 | q19 : int(1..4)]), - or([x_ExplicitVarSizeWithDummy[q21] != 5 /\ x_ExplicitVarSizeWithDummy[q21] = 2 | q21 : int(1..4)]), - or([x_ExplicitVarSizeWithFlags_Flags[q23] /\ x_ExplicitVarSizeWithFlags_Values[q23] = 3 | q23 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithDummy[q6] < x_ExplicitVarSizeWithDummy[q6 + 1] \/ x_ExplicitVarSizeWithDummy[q6] = 5 - | q6 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q7] = 5 -> x_ExplicitVarSizeWithDummy[q7 + 1] = 5 | q7 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q8] != 5) | q8 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithDummy[q11] != 5 -> - or([x_ExplicitVarSizeWithFlags_Flags[q13] /\ - x_ExplicitVarSizeWithFlags_Values[q13] = x_ExplicitVarSizeWithDummy[q11] - | q13 : int(1..4)]) - | q11 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q15] -> - or([x_ExplicitVarSizeWithDummy[q17] != 5 /\ - x_ExplicitVarSizeWithDummy[q17] = x_ExplicitVarSizeWithFlags_Values[q15] - | q17 : int(1..4)]) - | q15 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_4_2_4_3-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_4_2_4_3-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_2_4_3-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_4_2_4_3-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_4_2_4_3-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_2_4_3-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_4_2_4_3.eprime b/tests/exhaustive/basic/set06/expected/model_4_2_4_3.eprime deleted file mode 100644 index 148d795f19..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_2_4_3.eprime +++ /dev/null @@ -1,60 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithFlags_Flags, - x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy] -such that - or([x_ExplicitVarSizeWithFlags_Flags[q38] /\ x_ExplicitVarSizeWithFlags_Values[q38] = 1 | q38 : int(1..4)]), - or([x_ExplicitVarSizeWithDummy[q40] != 5 /\ x_ExplicitVarSizeWithDummy[q40] = 2 | q40 : int(1..4)]), - or([x_ExplicitVarSizeWithFlags_Flags[q42] /\ x_ExplicitVarSizeWithFlags_Values[q42] = 3 | q42 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithDummy[q6] < x_ExplicitVarSizeWithDummy[q6 + 1] \/ x_ExplicitVarSizeWithDummy[q6] = 5 - | q6 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q7] = 5 -> x_ExplicitVarSizeWithDummy[q7 + 1] = 5 | q7 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q8] != 5) | q8 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithDummy[q11] != 5 -> - or([x_ExplicitVarSizeWithFlags_Flags[q13] /\ - x_ExplicitVarSizeWithFlags_Values[q13] = x_ExplicitVarSizeWithDummy[q11] - | q13 : int(1..4)]) - | q11 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q15] -> - or([x_ExplicitVarSizeWithDummy[q17] != 5 /\ - x_ExplicitVarSizeWithDummy[q17] = x_ExplicitVarSizeWithFlags_Values[q15] - | q17 : int(1..4)]) - | q15 : int(1..4)]), - and([q18 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q18] < x_ExplicitVarSizeWithMarker_Values[q18 + 1] - | q18 : int(1..3)]), - and([q19 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q19] = 1 | q19 : int(1..4)]), - x_ExplicitVarSizeWithMarker_Marker <= 4, - and([q22 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q24] /\ - x_ExplicitVarSizeWithFlags_Values[q24] = x_ExplicitVarSizeWithMarker_Values[q22] - | q24 : int(1..4)]) - | q22 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q26] -> - or([q28 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q28] = x_ExplicitVarSizeWithFlags_Values[q26] - | q28 : int(1..4)]) - | q26 : int(1..4)]), - and([q30 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q32] != 5 /\ - x_ExplicitVarSizeWithDummy[q32] = x_ExplicitVarSizeWithMarker_Values[q30] - | q32 : int(1..4)]) - | q30 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q34] != 5 -> - or([q36 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q36] = x_ExplicitVarSizeWithDummy[q34] - | q36 : int(1..4)]) - | q34 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_4_2_4_4-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_4_2_4_4-solution000001.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_2_4_4-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_4_2_4_4-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_4_2_4_4-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_2_4_4-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_4_2_4_4.eprime b/tests/exhaustive/basic/set06/expected/model_4_2_4_4.eprime deleted file mode 100644 index e7dbd3a21e..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_2_4_4.eprime +++ /dev/null @@ -1,31 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -branching on [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] -such that - or([x_ExplicitVarSizeWithFlags_Flags[q19] /\ x_ExplicitVarSizeWithFlags_Values[q19] = 1 | q19 : int(1..4)]), - or([x_ExplicitVarSizeWithDummy[q21] != 5 /\ x_ExplicitVarSizeWithDummy[q21] = 2 | q21 : int(1..4)]), - or([x_ExplicitVarSizeWithFlags_Flags[q23] /\ x_ExplicitVarSizeWithFlags_Values[q23] = 3 | q23 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithDummy[q6] < x_ExplicitVarSizeWithDummy[q6 + 1] \/ x_ExplicitVarSizeWithDummy[q6] = 5 - | q6 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q7] = 5 -> x_ExplicitVarSizeWithDummy[q7 + 1] = 5 | q7 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q8] != 5) | q8 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithDummy[q11] != 5 -> - or([x_ExplicitVarSizeWithFlags_Flags[q13] /\ - x_ExplicitVarSizeWithFlags_Values[q13] = x_ExplicitVarSizeWithDummy[q11] - | q13 : int(1..4)]) - | q11 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q15] -> - or([x_ExplicitVarSizeWithDummy[q17] != 5 /\ - x_ExplicitVarSizeWithDummy[q17] = x_ExplicitVarSizeWithFlags_Values[q15] - | q17 : int(1..4)]) - | q15 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_4_3_1_1-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_4_3_1_1-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_3_1_1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_4_3_1_1-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_4_3_1_1-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_3_1_1-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_4_3_1_1.eprime b/tests/exhaustive/basic/set06/expected/model_4_3_1_1.eprime deleted file mode 100644 index ac596bf128..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_3_1_1.eprime +++ /dev/null @@ -1,48 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_Occurrence: matrix indexed by [int(1..4)] of bool -branching on - [x_Occurrence, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, - x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] -such that - or([x_ExplicitVarSizeWithFlags_Flags[q29] /\ x_ExplicitVarSizeWithFlags_Values[q29] = 1 | q29 : int(1..4)]), - or([q31 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q31] = 2 | q31 : int(1..4)]), - x_Occurrence[3], - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]) <= 4, - and([q6 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q6] < x_ExplicitVarSizeWithMarker_Values[q6 + 1] - | q6 : int(1..3)]), - and([q7 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q7] = 1 | q7 : int(1..4)]), - x_ExplicitVarSizeWithMarker_Marker <= 4, - and([q10 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q12] /\ - x_ExplicitVarSizeWithFlags_Values[q12] = x_ExplicitVarSizeWithMarker_Values[q10] - | q12 : int(1..4)]) - | q10 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q14] -> - or([q16 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q16] = x_ExplicitVarSizeWithFlags_Values[q14] - | q16 : int(1..4)]) - | q14 : int(1..4)]), - sum([toInt(x_Occurrence[q17]) | q17 : int(1..4)]) <= 4, - and([x_Occurrence[q18] -> - or([x_ExplicitVarSizeWithFlags_Flags[q20] /\ x_ExplicitVarSizeWithFlags_Values[q20] = q18 | q20 : int(1..4)]) - | q18 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q22] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q22]] - | q22 : int(1..4)]), - and([x_Occurrence[q23] -> - or([q25 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q25] = q23 - | q25 : int(1..4)]) - | q23 : int(1..4)]), - and([q27 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q27]] - | q27 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_4_3_1_2-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_4_3_1_2-solution000001.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_3_1_2-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_4_3_1_2-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_4_3_1_2-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_3_1_2-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_4_3_1_2.eprime b/tests/exhaustive/basic/set06/expected/model_4_3_1_2.eprime deleted file mode 100644 index 17571cdb85..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_3_1_2.eprime +++ /dev/null @@ -1,77 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_Occurrence: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -branching on - [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, - x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_Occurrence] -such that - or([x_ExplicitVarSizeWithFlags_Flags[q54] /\ x_ExplicitVarSizeWithFlags_Values[q54] = 1 | q54 : int(1..4)]), - or([q56 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q56] = 2 | q56 : int(1..4)]), - x_Occurrence[3], - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]) <= 4, - and([q6 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q6] < x_ExplicitVarSizeWithMarker_Values[q6 + 1] - | q6 : int(1..3)]), - and([q7 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q7] = 1 | q7 : int(1..4)]), - x_ExplicitVarSizeWithMarker_Marker <= 4, - and([q10 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q12] /\ - x_ExplicitVarSizeWithFlags_Values[q12] = x_ExplicitVarSizeWithMarker_Values[q10] - | q12 : int(1..4)]) - | q10 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q14] -> - or([q16 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q16] = x_ExplicitVarSizeWithFlags_Values[q14] - | q16 : int(1..4)]) - | q14 : int(1..4)]), - sum([toInt(x_Occurrence[q17]) | q17 : int(1..4)]) <= 4, - and([x_Occurrence[q43] -> - or([x_ExplicitVarSizeWithFlags_Flags[q45] /\ x_ExplicitVarSizeWithFlags_Values[q45] = q43 | q45 : int(1..4)]) - | q43 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q47] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q47]] - | q47 : int(1..4)]), - and([x_Occurrence[q48] -> - or([q50 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q50] = q48 - | q50 : int(1..4)]) - | q48 : int(1..4)]), - and([q52 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q52]] - | q52 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q18] < x_ExplicitVarSizeWithDummy[q18 + 1] \/ x_ExplicitVarSizeWithDummy[q18] = 5 - | q18 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q19] = 5 -> x_ExplicitVarSizeWithDummy[q19 + 1] = 5 | q19 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q20] != 5) | q20 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithDummy[q23] != 5 -> - or([x_ExplicitVarSizeWithFlags_Flags[q25] /\ - x_ExplicitVarSizeWithFlags_Values[q25] = x_ExplicitVarSizeWithDummy[q23] - | q25 : int(1..4)]) - | q23 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q27] -> - or([x_ExplicitVarSizeWithDummy[q29] != 5 /\ - x_ExplicitVarSizeWithDummy[q29] = x_ExplicitVarSizeWithFlags_Values[q27] - | q29 : int(1..4)]) - | q27 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q31] != 5 -> - or([q33 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q33] = x_ExplicitVarSizeWithDummy[q31] - | q33 : int(1..4)]) - | q31 : int(1..4)]), - and([q35 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q37] != 5 /\ - x_ExplicitVarSizeWithDummy[q37] = x_ExplicitVarSizeWithMarker_Values[q35] - | q37 : int(1..4)]) - | q35 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q39] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q39]] | q39 : int(1..4)]), - and([x_Occurrence[q40] -> - or([x_ExplicitVarSizeWithDummy[q42] != 5 /\ x_ExplicitVarSizeWithDummy[q42] = q40 | q42 : int(1..4)]) - | q40 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_4_3_1_3-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_4_3_1_3-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_3_1_3-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_4_3_1_3-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_4_3_1_3-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_3_1_3-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_4_3_1_3.eprime b/tests/exhaustive/basic/set06/expected/model_4_3_1_3.eprime deleted file mode 100644 index ac596bf128..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_3_1_3.eprime +++ /dev/null @@ -1,48 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_Occurrence: matrix indexed by [int(1..4)] of bool -branching on - [x_Occurrence, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, - x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] -such that - or([x_ExplicitVarSizeWithFlags_Flags[q29] /\ x_ExplicitVarSizeWithFlags_Values[q29] = 1 | q29 : int(1..4)]), - or([q31 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q31] = 2 | q31 : int(1..4)]), - x_Occurrence[3], - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]) <= 4, - and([q6 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q6] < x_ExplicitVarSizeWithMarker_Values[q6 + 1] - | q6 : int(1..3)]), - and([q7 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q7] = 1 | q7 : int(1..4)]), - x_ExplicitVarSizeWithMarker_Marker <= 4, - and([q10 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q12] /\ - x_ExplicitVarSizeWithFlags_Values[q12] = x_ExplicitVarSizeWithMarker_Values[q10] - | q12 : int(1..4)]) - | q10 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q14] -> - or([q16 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q16] = x_ExplicitVarSizeWithFlags_Values[q14] - | q16 : int(1..4)]) - | q14 : int(1..4)]), - sum([toInt(x_Occurrence[q17]) | q17 : int(1..4)]) <= 4, - and([x_Occurrence[q18] -> - or([x_ExplicitVarSizeWithFlags_Flags[q20] /\ x_ExplicitVarSizeWithFlags_Values[q20] = q18 | q20 : int(1..4)]) - | q18 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q22] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q22]] - | q22 : int(1..4)]), - and([x_Occurrence[q23] -> - or([q25 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q25] = q23 - | q25 : int(1..4)]) - | q23 : int(1..4)]), - and([q27 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q27]] - | q27 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_4_3_1_4-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_4_3_1_4-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_3_1_4-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_4_3_1_4-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_4_3_1_4-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_3_1_4-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_4_3_1_4.eprime b/tests/exhaustive/basic/set06/expected/model_4_3_1_4.eprime deleted file mode 100644 index ac596bf128..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_3_1_4.eprime +++ /dev/null @@ -1,48 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_Occurrence: matrix indexed by [int(1..4)] of bool -branching on - [x_Occurrence, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, - x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] -such that - or([x_ExplicitVarSizeWithFlags_Flags[q29] /\ x_ExplicitVarSizeWithFlags_Values[q29] = 1 | q29 : int(1..4)]), - or([q31 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q31] = 2 | q31 : int(1..4)]), - x_Occurrence[3], - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]) <= 4, - and([q6 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q6] < x_ExplicitVarSizeWithMarker_Values[q6 + 1] - | q6 : int(1..3)]), - and([q7 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q7] = 1 | q7 : int(1..4)]), - x_ExplicitVarSizeWithMarker_Marker <= 4, - and([q10 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q12] /\ - x_ExplicitVarSizeWithFlags_Values[q12] = x_ExplicitVarSizeWithMarker_Values[q10] - | q12 : int(1..4)]) - | q10 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q14] -> - or([q16 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q16] = x_ExplicitVarSizeWithFlags_Values[q14] - | q16 : int(1..4)]) - | q14 : int(1..4)]), - sum([toInt(x_Occurrence[q17]) | q17 : int(1..4)]) <= 4, - and([x_Occurrence[q18] -> - or([x_ExplicitVarSizeWithFlags_Flags[q20] /\ x_ExplicitVarSizeWithFlags_Values[q20] = q18 | q20 : int(1..4)]) - | q18 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q22] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q22]] - | q22 : int(1..4)]), - and([x_Occurrence[q23] -> - or([q25 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q25] = q23 - | q25 : int(1..4)]) - | q23 : int(1..4)]), - and([q27 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q27]] - | q27 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_4_3_2_1-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_4_3_2_1-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_3_2_1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_4_3_2_1-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_4_3_2_1-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_3_2_1-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_4_3_2_1.eprime b/tests/exhaustive/basic/set06/expected/model_4_3_2_1.eprime deleted file mode 100644 index 5b1aff728e..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_3_2_1.eprime +++ /dev/null @@ -1,77 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -find x_Occurrence: matrix indexed by [int(1..4)] of bool -branching on - [x_Occurrence, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, - x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy] -such that - or([x_ExplicitVarSizeWithFlags_Flags[q54] /\ x_ExplicitVarSizeWithFlags_Values[q54] = 1 | q54 : int(1..4)]), - or([q56 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q56] = 2 | q56 : int(1..4)]), - or([x_ExplicitVarSizeWithDummy[q58] != 5 /\ x_ExplicitVarSizeWithDummy[q58] = 3 | q58 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]) <= 4, - and([q6 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q6] < x_ExplicitVarSizeWithMarker_Values[q6 + 1] - | q6 : int(1..3)]), - and([q7 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q7] = 1 | q7 : int(1..4)]), - x_ExplicitVarSizeWithMarker_Marker <= 4, - and([q10 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q12] /\ - x_ExplicitVarSizeWithFlags_Values[q12] = x_ExplicitVarSizeWithMarker_Values[q10] - | q12 : int(1..4)]) - | q10 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q14] -> - or([q16 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q16] = x_ExplicitVarSizeWithFlags_Values[q14] - | q16 : int(1..4)]) - | q14 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q17] < x_ExplicitVarSizeWithDummy[q17 + 1] \/ x_ExplicitVarSizeWithDummy[q17] = 5 - | q17 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q18] = 5 -> x_ExplicitVarSizeWithDummy[q18 + 1] = 5 | q18 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q19] != 5) | q19 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithDummy[q22] != 5 -> - or([x_ExplicitVarSizeWithFlags_Flags[q24] /\ - x_ExplicitVarSizeWithFlags_Values[q24] = x_ExplicitVarSizeWithDummy[q22] - | q24 : int(1..4)]) - | q22 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q26] -> - or([x_ExplicitVarSizeWithDummy[q28] != 5 /\ - x_ExplicitVarSizeWithDummy[q28] = x_ExplicitVarSizeWithFlags_Values[q26] - | q28 : int(1..4)]) - | q26 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q30] != 5 -> - or([q32 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q32] = x_ExplicitVarSizeWithDummy[q30] - | q32 : int(1..4)]) - | q30 : int(1..4)]), - and([q34 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q36] != 5 /\ - x_ExplicitVarSizeWithDummy[q36] = x_ExplicitVarSizeWithMarker_Values[q34] - | q36 : int(1..4)]) - | q34 : int(1..4)]), - sum([toInt(x_Occurrence[q37]) | q37 : int(1..4)]) <= 4, - and([x_Occurrence[q38] -> - or([x_ExplicitVarSizeWithFlags_Flags[q40] /\ x_ExplicitVarSizeWithFlags_Values[q40] = q38 | q40 : int(1..4)]) - | q38 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q42] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q42]] - | q42 : int(1..4)]), - and([x_Occurrence[q43] -> - or([q45 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q45] = q43 - | q45 : int(1..4)]) - | q43 : int(1..4)]), - and([q47 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q47]] - | q47 : int(1..4)]), - and([x_Occurrence[q48] -> - or([x_ExplicitVarSizeWithDummy[q50] != 5 /\ x_ExplicitVarSizeWithDummy[q50] = q48 | q50 : int(1..4)]) - | q48 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q52] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q52]] | q52 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_4_3_2_2-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_4_3_2_2-solution000001.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_3_2_2-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_4_3_2_2-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_4_3_2_2-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_3_2_2-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_4_3_2_2.eprime b/tests/exhaustive/basic/set06/expected/model_4_3_2_2.eprime deleted file mode 100644 index 76550b1cd1..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_3_2_2.eprime +++ /dev/null @@ -1,60 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -branching on - [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, - x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] -such that - or([x_ExplicitVarSizeWithFlags_Flags[q38] /\ x_ExplicitVarSizeWithFlags_Values[q38] = 1 | q38 : int(1..4)]), - or([q40 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q40] = 2 | q40 : int(1..4)]), - or([x_ExplicitVarSizeWithDummy[q42] != 5 /\ x_ExplicitVarSizeWithDummy[q42] = 3 | q42 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]) <= 4, - and([q6 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q6] < x_ExplicitVarSizeWithMarker_Values[q6 + 1] - | q6 : int(1..3)]), - and([q7 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q7] = 1 | q7 : int(1..4)]), - x_ExplicitVarSizeWithMarker_Marker <= 4, - and([q10 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q12] /\ - x_ExplicitVarSizeWithFlags_Values[q12] = x_ExplicitVarSizeWithMarker_Values[q10] - | q12 : int(1..4)]) - | q10 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q14] -> - or([q16 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q16] = x_ExplicitVarSizeWithFlags_Values[q14] - | q16 : int(1..4)]) - | q14 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q17] < x_ExplicitVarSizeWithDummy[q17 + 1] \/ x_ExplicitVarSizeWithDummy[q17] = 5 - | q17 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q18] = 5 -> x_ExplicitVarSizeWithDummy[q18 + 1] = 5 | q18 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q19] != 5) | q19 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithDummy[q22] != 5 -> - or([x_ExplicitVarSizeWithFlags_Flags[q24] /\ - x_ExplicitVarSizeWithFlags_Values[q24] = x_ExplicitVarSizeWithDummy[q22] - | q24 : int(1..4)]) - | q22 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q26] -> - or([x_ExplicitVarSizeWithDummy[q28] != 5 /\ - x_ExplicitVarSizeWithDummy[q28] = x_ExplicitVarSizeWithFlags_Values[q26] - | q28 : int(1..4)]) - | q26 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q30] != 5 -> - or([q32 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q32] = x_ExplicitVarSizeWithDummy[q30] - | q32 : int(1..4)]) - | q30 : int(1..4)]), - and([q34 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q36] != 5 /\ - x_ExplicitVarSizeWithDummy[q36] = x_ExplicitVarSizeWithMarker_Values[q34] - | q36 : int(1..4)]) - | q34 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_4_3_2_3-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_4_3_2_3-solution000001.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_3_2_3-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_4_3_2_3-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_4_3_2_3-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_3_2_3-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_4_3_2_3.eprime b/tests/exhaustive/basic/set06/expected/model_4_3_2_3.eprime deleted file mode 100644 index 76550b1cd1..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_3_2_3.eprime +++ /dev/null @@ -1,60 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -branching on - [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, - x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] -such that - or([x_ExplicitVarSizeWithFlags_Flags[q38] /\ x_ExplicitVarSizeWithFlags_Values[q38] = 1 | q38 : int(1..4)]), - or([q40 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q40] = 2 | q40 : int(1..4)]), - or([x_ExplicitVarSizeWithDummy[q42] != 5 /\ x_ExplicitVarSizeWithDummy[q42] = 3 | q42 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]) <= 4, - and([q6 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q6] < x_ExplicitVarSizeWithMarker_Values[q6 + 1] - | q6 : int(1..3)]), - and([q7 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q7] = 1 | q7 : int(1..4)]), - x_ExplicitVarSizeWithMarker_Marker <= 4, - and([q10 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q12] /\ - x_ExplicitVarSizeWithFlags_Values[q12] = x_ExplicitVarSizeWithMarker_Values[q10] - | q12 : int(1..4)]) - | q10 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q14] -> - or([q16 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q16] = x_ExplicitVarSizeWithFlags_Values[q14] - | q16 : int(1..4)]) - | q14 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q17] < x_ExplicitVarSizeWithDummy[q17 + 1] \/ x_ExplicitVarSizeWithDummy[q17] = 5 - | q17 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q18] = 5 -> x_ExplicitVarSizeWithDummy[q18 + 1] = 5 | q18 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q19] != 5) | q19 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithDummy[q22] != 5 -> - or([x_ExplicitVarSizeWithFlags_Flags[q24] /\ - x_ExplicitVarSizeWithFlags_Values[q24] = x_ExplicitVarSizeWithDummy[q22] - | q24 : int(1..4)]) - | q22 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q26] -> - or([x_ExplicitVarSizeWithDummy[q28] != 5 /\ - x_ExplicitVarSizeWithDummy[q28] = x_ExplicitVarSizeWithFlags_Values[q26] - | q28 : int(1..4)]) - | q26 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q30] != 5 -> - or([q32 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q32] = x_ExplicitVarSizeWithDummy[q30] - | q32 : int(1..4)]) - | q30 : int(1..4)]), - and([q34 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q36] != 5 /\ - x_ExplicitVarSizeWithDummy[q36] = x_ExplicitVarSizeWithMarker_Values[q34] - | q36 : int(1..4)]) - | q34 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_4_3_2_4-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_4_3_2_4-solution000001.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_3_2_4-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_4_3_2_4-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_4_3_2_4-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_3_2_4-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_4_3_2_4.eprime b/tests/exhaustive/basic/set06/expected/model_4_3_2_4.eprime deleted file mode 100644 index 76550b1cd1..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_3_2_4.eprime +++ /dev/null @@ -1,60 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -branching on - [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, - x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] -such that - or([x_ExplicitVarSizeWithFlags_Flags[q38] /\ x_ExplicitVarSizeWithFlags_Values[q38] = 1 | q38 : int(1..4)]), - or([q40 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q40] = 2 | q40 : int(1..4)]), - or([x_ExplicitVarSizeWithDummy[q42] != 5 /\ x_ExplicitVarSizeWithDummy[q42] = 3 | q42 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]) <= 4, - and([q6 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q6] < x_ExplicitVarSizeWithMarker_Values[q6 + 1] - | q6 : int(1..3)]), - and([q7 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q7] = 1 | q7 : int(1..4)]), - x_ExplicitVarSizeWithMarker_Marker <= 4, - and([q10 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q12] /\ - x_ExplicitVarSizeWithFlags_Values[q12] = x_ExplicitVarSizeWithMarker_Values[q10] - | q12 : int(1..4)]) - | q10 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q14] -> - or([q16 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q16] = x_ExplicitVarSizeWithFlags_Values[q14] - | q16 : int(1..4)]) - | q14 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q17] < x_ExplicitVarSizeWithDummy[q17 + 1] \/ x_ExplicitVarSizeWithDummy[q17] = 5 - | q17 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q18] = 5 -> x_ExplicitVarSizeWithDummy[q18 + 1] = 5 | q18 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q19] != 5) | q19 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithDummy[q22] != 5 -> - or([x_ExplicitVarSizeWithFlags_Flags[q24] /\ - x_ExplicitVarSizeWithFlags_Values[q24] = x_ExplicitVarSizeWithDummy[q22] - | q24 : int(1..4)]) - | q22 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q26] -> - or([x_ExplicitVarSizeWithDummy[q28] != 5 /\ - x_ExplicitVarSizeWithDummy[q28] = x_ExplicitVarSizeWithFlags_Values[q26] - | q28 : int(1..4)]) - | q26 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q30] != 5 -> - or([q32 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q32] = x_ExplicitVarSizeWithDummy[q30] - | q32 : int(1..4)]) - | q30 : int(1..4)]), - and([q34 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q36] != 5 /\ - x_ExplicitVarSizeWithDummy[q36] = x_ExplicitVarSizeWithMarker_Values[q34] - | q36 : int(1..4)]) - | q34 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_4_3_3_1-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_4_3_3_1-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_3_3_1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_4_3_3_1-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_4_3_3_1-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_3_3_1-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_4_3_3_1.eprime b/tests/exhaustive/basic/set06/expected/model_4_3_3_1.eprime deleted file mode 100644 index 9a58f97a9b..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_3_3_1.eprime +++ /dev/null @@ -1,48 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_Occurrence: matrix indexed by [int(1..4)] of bool -branching on - [x_Occurrence, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, - x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] -such that - or([x_ExplicitVarSizeWithFlags_Flags[q29] /\ x_ExplicitVarSizeWithFlags_Values[q29] = 1 | q29 : int(1..4)]), - or([q31 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q31] = 2 | q31 : int(1..4)]), - or([q33 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q33] = 3 | q33 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]) <= 4, - and([q6 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q6] < x_ExplicitVarSizeWithMarker_Values[q6 + 1] - | q6 : int(1..3)]), - and([q7 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q7] = 1 | q7 : int(1..4)]), - x_ExplicitVarSizeWithMarker_Marker <= 4, - and([q10 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q12] /\ - x_ExplicitVarSizeWithFlags_Values[q12] = x_ExplicitVarSizeWithMarker_Values[q10] - | q12 : int(1..4)]) - | q10 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q14] -> - or([q16 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q16] = x_ExplicitVarSizeWithFlags_Values[q14] - | q16 : int(1..4)]) - | q14 : int(1..4)]), - sum([toInt(x_Occurrence[q17]) | q17 : int(1..4)]) <= 4, - and([x_Occurrence[q18] -> - or([x_ExplicitVarSizeWithFlags_Flags[q20] /\ x_ExplicitVarSizeWithFlags_Values[q20] = q18 | q20 : int(1..4)]) - | q18 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q22] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q22]] - | q22 : int(1..4)]), - and([x_Occurrence[q23] -> - or([q25 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q25] = q23 - | q25 : int(1..4)]) - | q23 : int(1..4)]), - and([q27 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q27]] - | q27 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_4_3_3_2-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_4_3_3_2-solution000001.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_3_3_2-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_4_3_3_2-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_4_3_3_2-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_3_3_2-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_4_3_3_2.eprime b/tests/exhaustive/basic/set06/expected/model_4_3_3_2.eprime deleted file mode 100644 index f359e7ac0b..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_3_3_2.eprime +++ /dev/null @@ -1,60 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -branching on - [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, - x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] -such that - or([x_ExplicitVarSizeWithFlags_Flags[q38] /\ x_ExplicitVarSizeWithFlags_Values[q38] = 1 | q38 : int(1..4)]), - or([q40 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q40] = 2 | q40 : int(1..4)]), - or([q42 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q42] = 3 | q42 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]) <= 4, - and([q6 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q6] < x_ExplicitVarSizeWithMarker_Values[q6 + 1] - | q6 : int(1..3)]), - and([q7 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q7] = 1 | q7 : int(1..4)]), - x_ExplicitVarSizeWithMarker_Marker <= 4, - and([q10 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q12] /\ - x_ExplicitVarSizeWithFlags_Values[q12] = x_ExplicitVarSizeWithMarker_Values[q10] - | q12 : int(1..4)]) - | q10 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q14] -> - or([q16 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q16] = x_ExplicitVarSizeWithFlags_Values[q14] - | q16 : int(1..4)]) - | q14 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q17] < x_ExplicitVarSizeWithDummy[q17 + 1] \/ x_ExplicitVarSizeWithDummy[q17] = 5 - | q17 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q18] = 5 -> x_ExplicitVarSizeWithDummy[q18 + 1] = 5 | q18 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q19] != 5) | q19 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithDummy[q22] != 5 -> - or([x_ExplicitVarSizeWithFlags_Flags[q24] /\ - x_ExplicitVarSizeWithFlags_Values[q24] = x_ExplicitVarSizeWithDummy[q22] - | q24 : int(1..4)]) - | q22 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q26] -> - or([x_ExplicitVarSizeWithDummy[q28] != 5 /\ - x_ExplicitVarSizeWithDummy[q28] = x_ExplicitVarSizeWithFlags_Values[q26] - | q28 : int(1..4)]) - | q26 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q30] != 5 -> - or([q32 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q32] = x_ExplicitVarSizeWithDummy[q30] - | q32 : int(1..4)]) - | q30 : int(1..4)]), - and([q34 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q36] != 5 /\ - x_ExplicitVarSizeWithDummy[q36] = x_ExplicitVarSizeWithMarker_Values[q34] - | q36 : int(1..4)]) - | q34 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_4_3_3_3-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_4_3_3_3-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_3_3_3-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_4_3_3_3-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_4_3_3_3-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_3_3_3-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_4_3_3_3.eprime b/tests/exhaustive/basic/set06/expected/model_4_3_3_3.eprime deleted file mode 100644 index aac2bf1a2e..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_3_3_3.eprime +++ /dev/null @@ -1,35 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithFlags_Flags, - x_ExplicitVarSizeWithFlags_Values] -such that - or([x_ExplicitVarSizeWithFlags_Flags[q18] /\ x_ExplicitVarSizeWithFlags_Values[q18] = 1 | q18 : int(1..4)]), - or([q20 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q20] = 2 | q20 : int(1..4)]), - or([q22 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q22] = 3 | q22 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]) <= 4, - and([q6 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q6] < x_ExplicitVarSizeWithMarker_Values[q6 + 1] - | q6 : int(1..3)]), - and([q7 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q7] = 1 | q7 : int(1..4)]), - x_ExplicitVarSizeWithMarker_Marker <= 4, - and([q10 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q12] /\ - x_ExplicitVarSizeWithFlags_Values[q12] = x_ExplicitVarSizeWithMarker_Values[q10] - | q12 : int(1..4)]) - | q10 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q14] -> - or([q16 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q16] = x_ExplicitVarSizeWithFlags_Values[q14] - | q16 : int(1..4)]) - | q14 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_4_3_3_4-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_4_3_3_4-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_3_3_4-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_4_3_3_4-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_4_3_3_4-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_3_3_4-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_4_3_3_4.eprime b/tests/exhaustive/basic/set06/expected/model_4_3_3_4.eprime deleted file mode 100644 index aac2bf1a2e..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_3_3_4.eprime +++ /dev/null @@ -1,35 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithFlags_Flags, - x_ExplicitVarSizeWithFlags_Values] -such that - or([x_ExplicitVarSizeWithFlags_Flags[q18] /\ x_ExplicitVarSizeWithFlags_Values[q18] = 1 | q18 : int(1..4)]), - or([q20 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q20] = 2 | q20 : int(1..4)]), - or([q22 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q22] = 3 | q22 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]) <= 4, - and([q6 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q6] < x_ExplicitVarSizeWithMarker_Values[q6 + 1] - | q6 : int(1..3)]), - and([q7 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q7] = 1 | q7 : int(1..4)]), - x_ExplicitVarSizeWithMarker_Marker <= 4, - and([q10 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q12] /\ - x_ExplicitVarSizeWithFlags_Values[q12] = x_ExplicitVarSizeWithMarker_Values[q10] - | q12 : int(1..4)]) - | q10 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q14] -> - or([q16 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q16] = x_ExplicitVarSizeWithFlags_Values[q14] - | q16 : int(1..4)]) - | q14 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_4_3_4_1-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_4_3_4_1-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_3_4_1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_4_3_4_1-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_4_3_4_1-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_3_4_1-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_4_3_4_1.eprime b/tests/exhaustive/basic/set06/expected/model_4_3_4_1.eprime deleted file mode 100644 index 42f3b460a6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_3_4_1.eprime +++ /dev/null @@ -1,48 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_Occurrence: matrix indexed by [int(1..4)] of bool -branching on - [x_Occurrence, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, - x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] -such that - or([x_ExplicitVarSizeWithFlags_Flags[q29] /\ x_ExplicitVarSizeWithFlags_Values[q29] = 1 | q29 : int(1..4)]), - or([q31 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q31] = 2 | q31 : int(1..4)]), - or([x_ExplicitVarSizeWithFlags_Flags[q33] /\ x_ExplicitVarSizeWithFlags_Values[q33] = 3 | q33 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]) <= 4, - and([q6 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q6] < x_ExplicitVarSizeWithMarker_Values[q6 + 1] - | q6 : int(1..3)]), - and([q7 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q7] = 1 | q7 : int(1..4)]), - x_ExplicitVarSizeWithMarker_Marker <= 4, - and([q10 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q12] /\ - x_ExplicitVarSizeWithFlags_Values[q12] = x_ExplicitVarSizeWithMarker_Values[q10] - | q12 : int(1..4)]) - | q10 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q14] -> - or([q16 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q16] = x_ExplicitVarSizeWithFlags_Values[q14] - | q16 : int(1..4)]) - | q14 : int(1..4)]), - sum([toInt(x_Occurrence[q17]) | q17 : int(1..4)]) <= 4, - and([x_Occurrence[q18] -> - or([x_ExplicitVarSizeWithFlags_Flags[q20] /\ x_ExplicitVarSizeWithFlags_Values[q20] = q18 | q20 : int(1..4)]) - | q18 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q22] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q22]] - | q22 : int(1..4)]), - and([x_Occurrence[q23] -> - or([q25 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q25] = q23 - | q25 : int(1..4)]) - | q23 : int(1..4)]), - and([q27 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q27]] - | q27 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_4_3_4_2-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_4_3_4_2-solution000001.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_3_4_2-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_4_3_4_2-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_4_3_4_2-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_3_4_2-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_4_3_4_2.eprime b/tests/exhaustive/basic/set06/expected/model_4_3_4_2.eprime deleted file mode 100644 index 215f736030..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_3_4_2.eprime +++ /dev/null @@ -1,60 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -branching on - [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, - x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] -such that - or([x_ExplicitVarSizeWithFlags_Flags[q38] /\ x_ExplicitVarSizeWithFlags_Values[q38] = 1 | q38 : int(1..4)]), - or([q40 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q40] = 2 | q40 : int(1..4)]), - or([x_ExplicitVarSizeWithFlags_Flags[q42] /\ x_ExplicitVarSizeWithFlags_Values[q42] = 3 | q42 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]) <= 4, - and([q6 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q6] < x_ExplicitVarSizeWithMarker_Values[q6 + 1] - | q6 : int(1..3)]), - and([q7 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q7] = 1 | q7 : int(1..4)]), - x_ExplicitVarSizeWithMarker_Marker <= 4, - and([q10 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q12] /\ - x_ExplicitVarSizeWithFlags_Values[q12] = x_ExplicitVarSizeWithMarker_Values[q10] - | q12 : int(1..4)]) - | q10 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q14] -> - or([q16 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q16] = x_ExplicitVarSizeWithFlags_Values[q14] - | q16 : int(1..4)]) - | q14 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q17] < x_ExplicitVarSizeWithDummy[q17 + 1] \/ x_ExplicitVarSizeWithDummy[q17] = 5 - | q17 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q18] = 5 -> x_ExplicitVarSizeWithDummy[q18 + 1] = 5 | q18 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q19] != 5) | q19 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithDummy[q22] != 5 -> - or([x_ExplicitVarSizeWithFlags_Flags[q24] /\ - x_ExplicitVarSizeWithFlags_Values[q24] = x_ExplicitVarSizeWithDummy[q22] - | q24 : int(1..4)]) - | q22 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q26] -> - or([x_ExplicitVarSizeWithDummy[q28] != 5 /\ - x_ExplicitVarSizeWithDummy[q28] = x_ExplicitVarSizeWithFlags_Values[q26] - | q28 : int(1..4)]) - | q26 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q30] != 5 -> - or([q32 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q32] = x_ExplicitVarSizeWithDummy[q30] - | q32 : int(1..4)]) - | q30 : int(1..4)]), - and([q34 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q36] != 5 /\ - x_ExplicitVarSizeWithDummy[q36] = x_ExplicitVarSizeWithMarker_Values[q34] - | q36 : int(1..4)]) - | q34 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_4_3_4_3-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_4_3_4_3-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_3_4_3-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_4_3_4_3-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_4_3_4_3-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_3_4_3-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_4_3_4_3.eprime b/tests/exhaustive/basic/set06/expected/model_4_3_4_3.eprime deleted file mode 100644 index f84e5ef823..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_3_4_3.eprime +++ /dev/null @@ -1,35 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithFlags_Flags, - x_ExplicitVarSizeWithFlags_Values] -such that - or([x_ExplicitVarSizeWithFlags_Flags[q18] /\ x_ExplicitVarSizeWithFlags_Values[q18] = 1 | q18 : int(1..4)]), - or([q20 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q20] = 2 | q20 : int(1..4)]), - or([x_ExplicitVarSizeWithFlags_Flags[q22] /\ x_ExplicitVarSizeWithFlags_Values[q22] = 3 | q22 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]) <= 4, - and([q6 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q6] < x_ExplicitVarSizeWithMarker_Values[q6 + 1] - | q6 : int(1..3)]), - and([q7 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q7] = 1 | q7 : int(1..4)]), - x_ExplicitVarSizeWithMarker_Marker <= 4, - and([q10 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q12] /\ - x_ExplicitVarSizeWithFlags_Values[q12] = x_ExplicitVarSizeWithMarker_Values[q10] - | q12 : int(1..4)]) - | q10 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q14] -> - or([q16 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q16] = x_ExplicitVarSizeWithFlags_Values[q14] - | q16 : int(1..4)]) - | q14 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_4_3_4_4-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_4_3_4_4-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_3_4_4-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_4_3_4_4-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_4_3_4_4-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_3_4_4-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_4_3_4_4.eprime b/tests/exhaustive/basic/set06/expected/model_4_3_4_4.eprime deleted file mode 100644 index f84e5ef823..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_3_4_4.eprime +++ /dev/null @@ -1,35 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithFlags_Flags, - x_ExplicitVarSizeWithFlags_Values] -such that - or([x_ExplicitVarSizeWithFlags_Flags[q18] /\ x_ExplicitVarSizeWithFlags_Values[q18] = 1 | q18 : int(1..4)]), - or([q20 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q20] = 2 | q20 : int(1..4)]), - or([x_ExplicitVarSizeWithFlags_Flags[q22] /\ x_ExplicitVarSizeWithFlags_Values[q22] = 3 | q22 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]) <= 4, - and([q6 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q6] < x_ExplicitVarSizeWithMarker_Values[q6 + 1] - | q6 : int(1..3)]), - and([q7 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q7] = 1 | q7 : int(1..4)]), - x_ExplicitVarSizeWithMarker_Marker <= 4, - and([q10 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q12] /\ - x_ExplicitVarSizeWithFlags_Values[q12] = x_ExplicitVarSizeWithMarker_Values[q10] - | q12 : int(1..4)]) - | q10 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q14] -> - or([q16 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q16] = x_ExplicitVarSizeWithFlags_Values[q14] - | q16 : int(1..4)]) - | q14 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_4_4_1_1-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_4_4_1_1-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_4_1_1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_4_4_1_1-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_4_4_1_1-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_4_1_1-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_4_4_1_1.eprime b/tests/exhaustive/basic/set06/expected/model_4_4_1_1.eprime deleted file mode 100644 index 89df5f9b59..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_4_1_1.eprime +++ /dev/null @@ -1,23 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_Occurrence: matrix indexed by [int(1..4)] of bool -branching on [x_Occurrence, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] -such that - or([x_ExplicitVarSizeWithFlags_Flags[q13] /\ x_ExplicitVarSizeWithFlags_Values[q13] = 1 | q13 : int(1..4)]), - or([x_ExplicitVarSizeWithFlags_Flags[q15] /\ x_ExplicitVarSizeWithFlags_Values[q15] = 2 | q15 : int(1..4)]), - x_Occurrence[3], - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]) <= 4, - sum([toInt(x_Occurrence[q6]) | q6 : int(1..4)]) <= 4, - and([x_Occurrence[q7] -> - or([x_ExplicitVarSizeWithFlags_Flags[q9] /\ x_ExplicitVarSizeWithFlags_Values[q9] = q7 | q9 : int(1..4)]) - | q7 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q11] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q11]] - | q11 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_4_4_1_2-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_4_4_1_2-solution000001.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_4_1_2-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_4_4_1_2-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_4_4_1_2-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_4_1_2-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_4_4_1_2.eprime b/tests/exhaustive/basic/set06/expected/model_4_4_1_2.eprime deleted file mode 100644 index fb935649b7..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_4_1_2.eprime +++ /dev/null @@ -1,43 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_Occurrence: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -branching on - [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_Occurrence] -such that - or([x_ExplicitVarSizeWithFlags_Flags[q30] /\ x_ExplicitVarSizeWithFlags_Values[q30] = 1 | q30 : int(1..4)]), - or([x_ExplicitVarSizeWithFlags_Flags[q32] /\ x_ExplicitVarSizeWithFlags_Values[q32] = 2 | q32 : int(1..4)]), - x_Occurrence[3], - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]) <= 4, - sum([toInt(x_Occurrence[q6]) | q6 : int(1..4)]) <= 4, - and([x_Occurrence[q24] -> - or([x_ExplicitVarSizeWithFlags_Flags[q26] /\ x_ExplicitVarSizeWithFlags_Values[q26] = q24 | q26 : int(1..4)]) - | q24 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q28] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q28]] - | q28 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q7] < x_ExplicitVarSizeWithDummy[q7 + 1] \/ x_ExplicitVarSizeWithDummy[q7] = 5 - | q7 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q8] = 5 -> x_ExplicitVarSizeWithDummy[q8 + 1] = 5 | q8 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q9] != 5) | q9 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithDummy[q12] != 5 -> - or([x_ExplicitVarSizeWithFlags_Flags[q14] /\ - x_ExplicitVarSizeWithFlags_Values[q14] = x_ExplicitVarSizeWithDummy[q12] - | q14 : int(1..4)]) - | q12 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q16] -> - or([x_ExplicitVarSizeWithDummy[q18] != 5 /\ - x_ExplicitVarSizeWithDummy[q18] = x_ExplicitVarSizeWithFlags_Values[q16] - | q18 : int(1..4)]) - | q16 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q20] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q20]] | q20 : int(1..4)]), - and([x_Occurrence[q21] -> - or([x_ExplicitVarSizeWithDummy[q23] != 5 /\ x_ExplicitVarSizeWithDummy[q23] = q21 | q23 : int(1..4)]) - | q21 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_4_4_1_3-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_4_4_1_3-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_4_1_3-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_4_4_1_3-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_4_4_1_3-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_4_1_3-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_4_4_1_3.eprime b/tests/exhaustive/basic/set06/expected/model_4_4_1_3.eprime deleted file mode 100644 index 188765c81e..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_4_1_3.eprime +++ /dev/null @@ -1,48 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_Occurrence: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithFlags_Flags, - x_ExplicitVarSizeWithFlags_Values, x_Occurrence] -such that - or([x_ExplicitVarSizeWithFlags_Flags[q29] /\ x_ExplicitVarSizeWithFlags_Values[q29] = 1 | q29 : int(1..4)]), - or([x_ExplicitVarSizeWithFlags_Flags[q31] /\ x_ExplicitVarSizeWithFlags_Values[q31] = 2 | q31 : int(1..4)]), - x_Occurrence[3], - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]) <= 4, - sum([toInt(x_Occurrence[q6]) | q6 : int(1..4)]) <= 4, - and([x_Occurrence[q23] -> - or([x_ExplicitVarSizeWithFlags_Flags[q25] /\ x_ExplicitVarSizeWithFlags_Values[q25] = q23 | q25 : int(1..4)]) - | q23 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q27] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q27]] - | q27 : int(1..4)]), - and([q7 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q7] < x_ExplicitVarSizeWithMarker_Values[q7 + 1] - | q7 : int(1..3)]), - and([q8 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q8] = 1 | q8 : int(1..4)]), - x_ExplicitVarSizeWithMarker_Marker <= 4, - and([q11 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q13] /\ - x_ExplicitVarSizeWithFlags_Values[q13] = x_ExplicitVarSizeWithMarker_Values[q11] - | q13 : int(1..4)]) - | q11 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q15] -> - or([q17 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q17] = x_ExplicitVarSizeWithFlags_Values[q15] - | q17 : int(1..4)]) - | q15 : int(1..4)]), - and([q19 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q19]] - | q19 : int(1..4)]), - and([x_Occurrence[q20] -> - or([q22 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q22] = q20 - | q22 : int(1..4)]) - | q20 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_4_4_1_4-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_4_4_1_4-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_4_1_4-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_4_4_1_4-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_4_4_1_4-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_4_1_4-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_4_4_1_4.eprime b/tests/exhaustive/basic/set06/expected/model_4_4_1_4.eprime deleted file mode 100644 index 89df5f9b59..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_4_1_4.eprime +++ /dev/null @@ -1,23 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_Occurrence: matrix indexed by [int(1..4)] of bool -branching on [x_Occurrence, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] -such that - or([x_ExplicitVarSizeWithFlags_Flags[q13] /\ x_ExplicitVarSizeWithFlags_Values[q13] = 1 | q13 : int(1..4)]), - or([x_ExplicitVarSizeWithFlags_Flags[q15] /\ x_ExplicitVarSizeWithFlags_Values[q15] = 2 | q15 : int(1..4)]), - x_Occurrence[3], - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]) <= 4, - sum([toInt(x_Occurrence[q6]) | q6 : int(1..4)]) <= 4, - and([x_Occurrence[q7] -> - or([x_ExplicitVarSizeWithFlags_Flags[q9] /\ x_ExplicitVarSizeWithFlags_Values[q9] = q7 | q9 : int(1..4)]) - | q7 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q11] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q11]] - | q11 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_4_4_2_1-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_4_4_2_1-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_4_2_1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_4_4_2_1-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_4_4_2_1-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_4_2_1-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_4_4_2_1.eprime b/tests/exhaustive/basic/set06/expected/model_4_4_2_1.eprime deleted file mode 100644 index 5efd46fc5d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_4_2_1.eprime +++ /dev/null @@ -1,43 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -find x_Occurrence: matrix indexed by [int(1..4)] of bool -branching on - [x_Occurrence, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy] -such that - or([x_ExplicitVarSizeWithFlags_Flags[q30] /\ x_ExplicitVarSizeWithFlags_Values[q30] = 1 | q30 : int(1..4)]), - or([x_ExplicitVarSizeWithFlags_Flags[q32] /\ x_ExplicitVarSizeWithFlags_Values[q32] = 2 | q32 : int(1..4)]), - or([x_ExplicitVarSizeWithDummy[q34] != 5 /\ x_ExplicitVarSizeWithDummy[q34] = 3 | q34 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithDummy[q6] < x_ExplicitVarSizeWithDummy[q6 + 1] \/ x_ExplicitVarSizeWithDummy[q6] = 5 - | q6 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q7] = 5 -> x_ExplicitVarSizeWithDummy[q7 + 1] = 5 | q7 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q8] != 5) | q8 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithDummy[q11] != 5 -> - or([x_ExplicitVarSizeWithFlags_Flags[q13] /\ - x_ExplicitVarSizeWithFlags_Values[q13] = x_ExplicitVarSizeWithDummy[q11] - | q13 : int(1..4)]) - | q11 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q15] -> - or([x_ExplicitVarSizeWithDummy[q17] != 5 /\ - x_ExplicitVarSizeWithDummy[q17] = x_ExplicitVarSizeWithFlags_Values[q15] - | q17 : int(1..4)]) - | q15 : int(1..4)]), - sum([toInt(x_Occurrence[q18]) | q18 : int(1..4)]) <= 4, - and([x_Occurrence[q19] -> - or([x_ExplicitVarSizeWithFlags_Flags[q21] /\ x_ExplicitVarSizeWithFlags_Values[q21] = q19 | q21 : int(1..4)]) - | q19 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q23] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q23]] - | q23 : int(1..4)]), - and([x_Occurrence[q24] -> - or([x_ExplicitVarSizeWithDummy[q26] != 5 /\ x_ExplicitVarSizeWithDummy[q26] = q24 | q26 : int(1..4)]) - | q24 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q28] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q28]] | q28 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_4_4_2_2-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_4_4_2_2-solution000001.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_4_2_2-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_4_4_2_2-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_4_4_2_2-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_4_2_2-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_4_4_2_2.eprime b/tests/exhaustive/basic/set06/expected/model_4_4_2_2.eprime deleted file mode 100644 index 0fa0747d3f..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_4_2_2.eprime +++ /dev/null @@ -1,31 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -branching on [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] -such that - or([x_ExplicitVarSizeWithFlags_Flags[q19] /\ x_ExplicitVarSizeWithFlags_Values[q19] = 1 | q19 : int(1..4)]), - or([x_ExplicitVarSizeWithFlags_Flags[q21] /\ x_ExplicitVarSizeWithFlags_Values[q21] = 2 | q21 : int(1..4)]), - or([x_ExplicitVarSizeWithDummy[q23] != 5 /\ x_ExplicitVarSizeWithDummy[q23] = 3 | q23 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithDummy[q6] < x_ExplicitVarSizeWithDummy[q6 + 1] \/ x_ExplicitVarSizeWithDummy[q6] = 5 - | q6 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q7] = 5 -> x_ExplicitVarSizeWithDummy[q7 + 1] = 5 | q7 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q8] != 5) | q8 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithDummy[q11] != 5 -> - or([x_ExplicitVarSizeWithFlags_Flags[q13] /\ - x_ExplicitVarSizeWithFlags_Values[q13] = x_ExplicitVarSizeWithDummy[q11] - | q13 : int(1..4)]) - | q11 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q15] -> - or([x_ExplicitVarSizeWithDummy[q17] != 5 /\ - x_ExplicitVarSizeWithDummy[q17] = x_ExplicitVarSizeWithFlags_Values[q15] - | q17 : int(1..4)]) - | q15 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_4_4_2_3-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_4_4_2_3-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_4_2_3-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_4_4_2_3-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_4_4_2_3-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_4_2_3-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_4_4_2_3.eprime b/tests/exhaustive/basic/set06/expected/model_4_4_2_3.eprime deleted file mode 100644 index 4fe9b7fb6a..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_4_2_3.eprime +++ /dev/null @@ -1,60 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithFlags_Flags, - x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy] -such that - or([x_ExplicitVarSizeWithFlags_Flags[q38] /\ x_ExplicitVarSizeWithFlags_Values[q38] = 1 | q38 : int(1..4)]), - or([x_ExplicitVarSizeWithFlags_Flags[q40] /\ x_ExplicitVarSizeWithFlags_Values[q40] = 2 | q40 : int(1..4)]), - or([x_ExplicitVarSizeWithDummy[q42] != 5 /\ x_ExplicitVarSizeWithDummy[q42] = 3 | q42 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithDummy[q6] < x_ExplicitVarSizeWithDummy[q6 + 1] \/ x_ExplicitVarSizeWithDummy[q6] = 5 - | q6 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q7] = 5 -> x_ExplicitVarSizeWithDummy[q7 + 1] = 5 | q7 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q8] != 5) | q8 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithDummy[q11] != 5 -> - or([x_ExplicitVarSizeWithFlags_Flags[q13] /\ - x_ExplicitVarSizeWithFlags_Values[q13] = x_ExplicitVarSizeWithDummy[q11] - | q13 : int(1..4)]) - | q11 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q15] -> - or([x_ExplicitVarSizeWithDummy[q17] != 5 /\ - x_ExplicitVarSizeWithDummy[q17] = x_ExplicitVarSizeWithFlags_Values[q15] - | q17 : int(1..4)]) - | q15 : int(1..4)]), - and([q18 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q18] < x_ExplicitVarSizeWithMarker_Values[q18 + 1] - | q18 : int(1..3)]), - and([q19 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q19] = 1 | q19 : int(1..4)]), - x_ExplicitVarSizeWithMarker_Marker <= 4, - and([q22 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q24] /\ - x_ExplicitVarSizeWithFlags_Values[q24] = x_ExplicitVarSizeWithMarker_Values[q22] - | q24 : int(1..4)]) - | q22 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q26] -> - or([q28 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q28] = x_ExplicitVarSizeWithFlags_Values[q26] - | q28 : int(1..4)]) - | q26 : int(1..4)]), - and([q30 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q32] != 5 /\ - x_ExplicitVarSizeWithDummy[q32] = x_ExplicitVarSizeWithMarker_Values[q30] - | q32 : int(1..4)]) - | q30 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q34] != 5 -> - or([q36 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q36] = x_ExplicitVarSizeWithDummy[q34] - | q36 : int(1..4)]) - | q34 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_4_4_2_4-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_4_4_2_4-solution000001.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_4_2_4-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_4_4_2_4-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_4_4_2_4-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_4_2_4-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_4_4_2_4.eprime b/tests/exhaustive/basic/set06/expected/model_4_4_2_4.eprime deleted file mode 100644 index 0fa0747d3f..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_4_2_4.eprime +++ /dev/null @@ -1,31 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -branching on [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] -such that - or([x_ExplicitVarSizeWithFlags_Flags[q19] /\ x_ExplicitVarSizeWithFlags_Values[q19] = 1 | q19 : int(1..4)]), - or([x_ExplicitVarSizeWithFlags_Flags[q21] /\ x_ExplicitVarSizeWithFlags_Values[q21] = 2 | q21 : int(1..4)]), - or([x_ExplicitVarSizeWithDummy[q23] != 5 /\ x_ExplicitVarSizeWithDummy[q23] = 3 | q23 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithDummy[q6] < x_ExplicitVarSizeWithDummy[q6 + 1] \/ x_ExplicitVarSizeWithDummy[q6] = 5 - | q6 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q7] = 5 -> x_ExplicitVarSizeWithDummy[q7 + 1] = 5 | q7 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q8] != 5) | q8 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithDummy[q11] != 5 -> - or([x_ExplicitVarSizeWithFlags_Flags[q13] /\ - x_ExplicitVarSizeWithFlags_Values[q13] = x_ExplicitVarSizeWithDummy[q11] - | q13 : int(1..4)]) - | q11 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q15] -> - or([x_ExplicitVarSizeWithDummy[q17] != 5 /\ - x_ExplicitVarSizeWithDummy[q17] = x_ExplicitVarSizeWithFlags_Values[q15] - | q17 : int(1..4)]) - | q15 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_4_4_3_1-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_4_4_3_1-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_4_3_1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_4_4_3_1-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_4_4_3_1-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_4_3_1-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_4_4_3_1.eprime b/tests/exhaustive/basic/set06/expected/model_4_4_3_1.eprime deleted file mode 100644 index 9eb1652af5..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_4_3_1.eprime +++ /dev/null @@ -1,48 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_Occurrence: matrix indexed by [int(1..4)] of bool -branching on - [x_Occurrence, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, - x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] -such that - or([x_ExplicitVarSizeWithFlags_Flags[q29] /\ x_ExplicitVarSizeWithFlags_Values[q29] = 1 | q29 : int(1..4)]), - or([x_ExplicitVarSizeWithFlags_Flags[q31] /\ x_ExplicitVarSizeWithFlags_Values[q31] = 2 | q31 : int(1..4)]), - or([q33 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q33] = 3 | q33 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]) <= 4, - and([q6 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q6] < x_ExplicitVarSizeWithMarker_Values[q6 + 1] - | q6 : int(1..3)]), - and([q7 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q7] = 1 | q7 : int(1..4)]), - x_ExplicitVarSizeWithMarker_Marker <= 4, - and([q10 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q12] /\ - x_ExplicitVarSizeWithFlags_Values[q12] = x_ExplicitVarSizeWithMarker_Values[q10] - | q12 : int(1..4)]) - | q10 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q14] -> - or([q16 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q16] = x_ExplicitVarSizeWithFlags_Values[q14] - | q16 : int(1..4)]) - | q14 : int(1..4)]), - sum([toInt(x_Occurrence[q17]) | q17 : int(1..4)]) <= 4, - and([x_Occurrence[q18] -> - or([x_ExplicitVarSizeWithFlags_Flags[q20] /\ x_ExplicitVarSizeWithFlags_Values[q20] = q18 | q20 : int(1..4)]) - | q18 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q22] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q22]] - | q22 : int(1..4)]), - and([x_Occurrence[q23] -> - or([q25 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q25] = q23 - | q25 : int(1..4)]) - | q23 : int(1..4)]), - and([q27 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q27]] - | q27 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_4_4_3_2-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_4_4_3_2-solution000001.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_4_3_2-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_4_4_3_2-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_4_4_3_2-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_4_3_2-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_4_4_3_2.eprime b/tests/exhaustive/basic/set06/expected/model_4_4_3_2.eprime deleted file mode 100644 index bf7ce16ba1..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_4_3_2.eprime +++ /dev/null @@ -1,60 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -branching on - [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, - x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] -such that - or([x_ExplicitVarSizeWithFlags_Flags[q38] /\ x_ExplicitVarSizeWithFlags_Values[q38] = 1 | q38 : int(1..4)]), - or([x_ExplicitVarSizeWithFlags_Flags[q40] /\ x_ExplicitVarSizeWithFlags_Values[q40] = 2 | q40 : int(1..4)]), - or([q42 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q42] = 3 | q42 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]) <= 4, - and([q6 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q6] < x_ExplicitVarSizeWithMarker_Values[q6 + 1] - | q6 : int(1..3)]), - and([q7 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q7] = 1 | q7 : int(1..4)]), - x_ExplicitVarSizeWithMarker_Marker <= 4, - and([q10 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q12] /\ - x_ExplicitVarSizeWithFlags_Values[q12] = x_ExplicitVarSizeWithMarker_Values[q10] - | q12 : int(1..4)]) - | q10 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q14] -> - or([q16 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q16] = x_ExplicitVarSizeWithFlags_Values[q14] - | q16 : int(1..4)]) - | q14 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q17] < x_ExplicitVarSizeWithDummy[q17 + 1] \/ x_ExplicitVarSizeWithDummy[q17] = 5 - | q17 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q18] = 5 -> x_ExplicitVarSizeWithDummy[q18 + 1] = 5 | q18 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q19] != 5) | q19 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithDummy[q22] != 5 -> - or([x_ExplicitVarSizeWithFlags_Flags[q24] /\ - x_ExplicitVarSizeWithFlags_Values[q24] = x_ExplicitVarSizeWithDummy[q22] - | q24 : int(1..4)]) - | q22 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q26] -> - or([x_ExplicitVarSizeWithDummy[q28] != 5 /\ - x_ExplicitVarSizeWithDummy[q28] = x_ExplicitVarSizeWithFlags_Values[q26] - | q28 : int(1..4)]) - | q26 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q30] != 5 -> - or([q32 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q32] = x_ExplicitVarSizeWithDummy[q30] - | q32 : int(1..4)]) - | q30 : int(1..4)]), - and([q34 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q36] != 5 /\ - x_ExplicitVarSizeWithDummy[q36] = x_ExplicitVarSizeWithMarker_Values[q34] - | q36 : int(1..4)]) - | q34 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_4_4_3_3-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_4_4_3_3-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_4_3_3-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_4_4_3_3-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_4_4_3_3-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_4_3_3-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_4_4_3_3.eprime b/tests/exhaustive/basic/set06/expected/model_4_4_3_3.eprime deleted file mode 100644 index 7c1be4c4b9..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_4_3_3.eprime +++ /dev/null @@ -1,35 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithFlags_Flags, - x_ExplicitVarSizeWithFlags_Values] -such that - or([x_ExplicitVarSizeWithFlags_Flags[q18] /\ x_ExplicitVarSizeWithFlags_Values[q18] = 1 | q18 : int(1..4)]), - or([x_ExplicitVarSizeWithFlags_Flags[q20] /\ x_ExplicitVarSizeWithFlags_Values[q20] = 2 | q20 : int(1..4)]), - or([q22 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q22] = 3 | q22 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]) <= 4, - and([q6 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q6] < x_ExplicitVarSizeWithMarker_Values[q6 + 1] - | q6 : int(1..3)]), - and([q7 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q7] = 1 | q7 : int(1..4)]), - x_ExplicitVarSizeWithMarker_Marker <= 4, - and([q10 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q12] /\ - x_ExplicitVarSizeWithFlags_Values[q12] = x_ExplicitVarSizeWithMarker_Values[q10] - | q12 : int(1..4)]) - | q10 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q14] -> - or([q16 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q16] = x_ExplicitVarSizeWithFlags_Values[q14] - | q16 : int(1..4)]) - | q14 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_4_4_3_4-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_4_4_3_4-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_4_3_4-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_4_4_3_4-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_4_4_3_4-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_4_3_4-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_4_4_3_4.eprime b/tests/exhaustive/basic/set06/expected/model_4_4_3_4.eprime deleted file mode 100644 index 7c1be4c4b9..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_4_3_4.eprime +++ /dev/null @@ -1,35 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithFlags_Flags, - x_ExplicitVarSizeWithFlags_Values] -such that - or([x_ExplicitVarSizeWithFlags_Flags[q18] /\ x_ExplicitVarSizeWithFlags_Values[q18] = 1 | q18 : int(1..4)]), - or([x_ExplicitVarSizeWithFlags_Flags[q20] /\ x_ExplicitVarSizeWithFlags_Values[q20] = 2 | q20 : int(1..4)]), - or([q22 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q22] = 3 | q22 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]) <= 4, - and([q6 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q6] < x_ExplicitVarSizeWithMarker_Values[q6 + 1] - | q6 : int(1..3)]), - and([q7 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q7] = 1 | q7 : int(1..4)]), - x_ExplicitVarSizeWithMarker_Marker <= 4, - and([q10 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q12] /\ - x_ExplicitVarSizeWithFlags_Values[q12] = x_ExplicitVarSizeWithMarker_Values[q10] - | q12 : int(1..4)]) - | q10 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q14] -> - or([q16 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q16] = x_ExplicitVarSizeWithFlags_Values[q14] - | q16 : int(1..4)]) - | q14 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_4_4_4_1-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_4_4_4_1-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_4_4_1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_4_4_4_1-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_4_4_4_1-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_4_4_1-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_4_4_4_1.eprime b/tests/exhaustive/basic/set06/expected/model_4_4_4_1.eprime deleted file mode 100644 index 5ce826b766..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_4_4_1.eprime +++ /dev/null @@ -1,23 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_Occurrence: matrix indexed by [int(1..4)] of bool -branching on [x_Occurrence, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] -such that - or([x_ExplicitVarSizeWithFlags_Flags[q13] /\ x_ExplicitVarSizeWithFlags_Values[q13] = 1 | q13 : int(1..4)]), - or([x_ExplicitVarSizeWithFlags_Flags[q15] /\ x_ExplicitVarSizeWithFlags_Values[q15] = 2 | q15 : int(1..4)]), - or([x_ExplicitVarSizeWithFlags_Flags[q17] /\ x_ExplicitVarSizeWithFlags_Values[q17] = 3 | q17 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]) <= 4, - sum([toInt(x_Occurrence[q6]) | q6 : int(1..4)]) <= 4, - and([x_Occurrence[q7] -> - or([x_ExplicitVarSizeWithFlags_Flags[q9] /\ x_ExplicitVarSizeWithFlags_Values[q9] = q7 | q9 : int(1..4)]) - | q7 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q11] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q11]] - | q11 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_4_4_4_2-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_4_4_4_2-solution000001.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_4_4_2-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_4_4_4_2-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_4_4_4_2-solution000002.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_4_4_2-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_4_4_4_2.eprime b/tests/exhaustive/basic/set06/expected/model_4_4_4_2.eprime deleted file mode 100644 index c25dce1965..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_4_4_2.eprime +++ /dev/null @@ -1,31 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -branching on [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] -such that - or([x_ExplicitVarSizeWithFlags_Flags[q19] /\ x_ExplicitVarSizeWithFlags_Values[q19] = 1 | q19 : int(1..4)]), - or([x_ExplicitVarSizeWithFlags_Flags[q21] /\ x_ExplicitVarSizeWithFlags_Values[q21] = 2 | q21 : int(1..4)]), - or([x_ExplicitVarSizeWithFlags_Flags[q23] /\ x_ExplicitVarSizeWithFlags_Values[q23] = 3 | q23 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithDummy[q6] < x_ExplicitVarSizeWithDummy[q6 + 1] \/ x_ExplicitVarSizeWithDummy[q6] = 5 - | q6 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q7] = 5 -> x_ExplicitVarSizeWithDummy[q7 + 1] = 5 | q7 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithDummy[q8] != 5) | q8 : int(1..4)]) <= 4, - and([x_ExplicitVarSizeWithDummy[q11] != 5 -> - or([x_ExplicitVarSizeWithFlags_Flags[q13] /\ - x_ExplicitVarSizeWithFlags_Values[q13] = x_ExplicitVarSizeWithDummy[q11] - | q13 : int(1..4)]) - | q11 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q15] -> - or([x_ExplicitVarSizeWithDummy[q17] != 5 /\ - x_ExplicitVarSizeWithDummy[q17] = x_ExplicitVarSizeWithFlags_Values[q15] - | q17 : int(1..4)]) - | q15 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_4_4_4_3-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_4_4_4_3-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_4_4_3-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_4_4_4_3-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_4_4_4_3-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_4_4_3-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_4_4_4_3.eprime b/tests/exhaustive/basic/set06/expected/model_4_4_4_3.eprime deleted file mode 100644 index b5daed7250..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_4_4_3.eprime +++ /dev/null @@ -1,35 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithFlags_Flags, - x_ExplicitVarSizeWithFlags_Values] -such that - or([x_ExplicitVarSizeWithFlags_Flags[q18] /\ x_ExplicitVarSizeWithFlags_Values[q18] = 1 | q18 : int(1..4)]), - or([x_ExplicitVarSizeWithFlags_Flags[q20] /\ x_ExplicitVarSizeWithFlags_Values[q20] = 2 | q20 : int(1..4)]), - or([x_ExplicitVarSizeWithFlags_Flags[q22] /\ x_ExplicitVarSizeWithFlags_Values[q22] = 3 | q22 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]) <= 4, - and([q6 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q6] < x_ExplicitVarSizeWithMarker_Values[q6 + 1] - | q6 : int(1..3)]), - and([q7 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q7] = 1 | q7 : int(1..4)]), - x_ExplicitVarSizeWithMarker_Marker <= 4, - and([q10 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q12] /\ - x_ExplicitVarSizeWithFlags_Values[q12] = x_ExplicitVarSizeWithMarker_Values[q10] - | q12 : int(1..4)]) - | q10 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q14] -> - or([q16 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q16] = x_ExplicitVarSizeWithFlags_Values[q14] - | q16 : int(1..4)]) - | q14 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set06/expected/model_4_4_4_4-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_4_4_4_4-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_4_4_4-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_4_4_4_4-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_4_4_4_4-solution000002.solution deleted file mode 100644 index 85149821f6..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_4_4_4-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_4_4_4_4.eprime b/tests/exhaustive/basic/set06/expected/model_4_4_4_4.eprime deleted file mode 100644 index 9cb0f0f85d..0000000000 --- a/tests/exhaustive/basic/set06/expected/model_4_4_4_4.eprime +++ /dev/null @@ -1,16 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -branching on [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] -such that - or([x_ExplicitVarSizeWithFlags_Flags[q7] /\ x_ExplicitVarSizeWithFlags_Values[q7] = 1 | q7 : int(1..4)]), - or([x_ExplicitVarSizeWithFlags_Flags[q9] /\ x_ExplicitVarSizeWithFlags_Values[q9] = 2 | q9 : int(1..4)]), - or([x_ExplicitVarSizeWithFlags_Flags[q11] /\ x_ExplicitVarSizeWithFlags_Values[q11] = 3 | q11 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]) <= 4 - diff --git a/tests/exhaustive/basic/set07/expected/model_1_1_1-solution000001.solution b/tests/exhaustive/basic/set07/expected/model_1_1_1-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set07/expected/model_1_1_1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set07/expected/model_1_1_1.eprime b/tests/exhaustive/basic/set07/expected/model_1_1_1.eprime deleted file mode 100644 index 1c2a0f3332..0000000000 --- a/tests/exhaustive/basic/set07/expected/model_1_1_1.eprime +++ /dev/null @@ -1,6 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1..4)] of bool -branching on [x_Occurrence] -such that and([x_Occurrence[q2_1] /\ !x_Occurrence[q2_2] | q2_1 : int(1..3), q2_2 : int(4..9)]) - diff --git a/tests/exhaustive/basic/set07/expected/model_1_1_2-solution000001.solution b/tests/exhaustive/basic/set07/expected/model_1_1_2-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set07/expected/model_1_1_2-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set07/expected/model_1_1_2.eprime b/tests/exhaustive/basic/set07/expected/model_1_1_2.eprime deleted file mode 100644 index db14667a95..0000000000 --- a/tests/exhaustive/basic/set07/expected/model_1_1_2.eprime +++ /dev/null @@ -1,15 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -branching on [x_ExplicitVarSizeWithDummy, x_Occurrence] -such that - and([x_Occurrence[q11_1] /\ !x_Occurrence[q11_2] | q11_1 : int(1..3), q11_2 : int(4..9)]), - and([x_ExplicitVarSizeWithDummy[q2] < x_ExplicitVarSizeWithDummy[q2 + 1] \/ x_ExplicitVarSizeWithDummy[q2] = 5 - | q2 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q3] = 5 -> x_ExplicitVarSizeWithDummy[q3 + 1] = 5 | q3 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q7] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q7]] | q7 : int(1..4)]), - and([x_Occurrence[q8] -> - or([x_ExplicitVarSizeWithDummy[q10] != 5 /\ x_ExplicitVarSizeWithDummy[q10] = q8 | q10 : int(1..4)]) - | q8 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set07/expected/model_1_1_3-solution000001.solution b/tests/exhaustive/basic/set07/expected/model_1_1_3-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set07/expected/model_1_1_3-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set07/expected/model_1_1_3.eprime b/tests/exhaustive/basic/set07/expected/model_1_1_3.eprime deleted file mode 100644 index c710eaa6a1..0000000000 --- a/tests/exhaustive/basic/set07/expected/model_1_1_3.eprime +++ /dev/null @@ -1,18 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -branching on [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_Occurrence] -such that - and([x_Occurrence[q10_1] /\ !x_Occurrence[q10_2] | q10_1 : int(1..3), q10_2 : int(4..9)]), - and([q2 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q2] < x_ExplicitVarSizeWithMarker_Values[q2 + 1] - | q2 : int(1..3)]), - and([q3 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q3] = 1 | q3 : int(1..4)]), - and([q6 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q6]] - | q6 : int(1..4)]), - and([x_Occurrence[q7] -> - or([q9 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q9] = q7 | q9 : int(1..4)]) - | q7 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set07/expected/model_1_1_4-solution000001.solution b/tests/exhaustive/basic/set07/expected/model_1_1_4-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set07/expected/model_1_1_4-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set07/expected/model_1_1_4.eprime b/tests/exhaustive/basic/set07/expected/model_1_1_4.eprime deleted file mode 100644 index 71e8baf956..0000000000 --- a/tests/exhaustive/basic/set07/expected/model_1_1_4.eprime +++ /dev/null @@ -1,18 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -branching on [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_Occurrence] -such that - and([x_Occurrence[q12_1] /\ !x_Occurrence[q12_2] | q12_1 : int(1..3), q12_2 : int(4..9)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q2] < x_ExplicitVarSizeWithFlags_Values[q2 + 1] - | q2 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3] = false -> x_ExplicitVarSizeWithFlags_Values[q3] = 1 | q3 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q4] | q4 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q8] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q8]] | q8 : int(1..4)]), - and([x_Occurrence[q9] -> - or([x_ExplicitVarSizeWithFlags_Flags[q11] /\ x_ExplicitVarSizeWithFlags_Values[q11] = q9 | q11 : int(1..4)]) - | q9 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set07/expected/model_1_2_1-solution000001.solution b/tests/exhaustive/basic/set07/expected/model_1_2_1-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set07/expected/model_1_2_1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set07/expected/model_1_2_1.eprime b/tests/exhaustive/basic/set07/expected/model_1_2_1.eprime deleted file mode 100644 index 43b3a76c2e..0000000000 --- a/tests/exhaustive/basic/set07/expected/model_1_2_1.eprime +++ /dev/null @@ -1,17 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -branching on [x_ExplicitVarSizeWithDummy, x_Occurrence] -such that - and([x_Occurrence[q13_1] /\ - !or([x_ExplicitVarSizeWithDummy[q12] != 5 /\ x_ExplicitVarSizeWithDummy[q12] = q13_2 | q12 : int(1..4)]) - | q13_1 : int(1..3), q13_2 : int(4..9)]), - and([x_ExplicitVarSizeWithDummy[q2] < x_ExplicitVarSizeWithDummy[q2 + 1] \/ x_ExplicitVarSizeWithDummy[q2] = 5 - | q2 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q3] = 5 -> x_ExplicitVarSizeWithDummy[q3 + 1] = 5 | q3 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q7] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q7]] | q7 : int(1..4)]), - and([x_Occurrence[q8] -> - or([x_ExplicitVarSizeWithDummy[q10] != 5 /\ x_ExplicitVarSizeWithDummy[q10] = q8 | q10 : int(1..4)]) - | q8 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set07/expected/model_1_2_2-solution000001.solution b/tests/exhaustive/basic/set07/expected/model_1_2_2-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set07/expected/model_1_2_2-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set07/expected/model_1_2_2.eprime b/tests/exhaustive/basic/set07/expected/model_1_2_2.eprime deleted file mode 100644 index 43b3a76c2e..0000000000 --- a/tests/exhaustive/basic/set07/expected/model_1_2_2.eprime +++ /dev/null @@ -1,17 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -branching on [x_ExplicitVarSizeWithDummy, x_Occurrence] -such that - and([x_Occurrence[q13_1] /\ - !or([x_ExplicitVarSizeWithDummy[q12] != 5 /\ x_ExplicitVarSizeWithDummy[q12] = q13_2 | q12 : int(1..4)]) - | q13_1 : int(1..3), q13_2 : int(4..9)]), - and([x_ExplicitVarSizeWithDummy[q2] < x_ExplicitVarSizeWithDummy[q2 + 1] \/ x_ExplicitVarSizeWithDummy[q2] = 5 - | q2 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q3] = 5 -> x_ExplicitVarSizeWithDummy[q3 + 1] = 5 | q3 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q7] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q7]] | q7 : int(1..4)]), - and([x_Occurrence[q8] -> - or([x_ExplicitVarSizeWithDummy[q10] != 5 /\ x_ExplicitVarSizeWithDummy[q10] = q8 | q10 : int(1..4)]) - | q8 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set07/expected/model_1_2_3-solution000001.solution b/tests/exhaustive/basic/set07/expected/model_1_2_3-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set07/expected/model_1_2_3-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set07/expected/model_1_2_3.eprime b/tests/exhaustive/basic/set07/expected/model_1_2_3.eprime deleted file mode 100644 index 2a83287908..0000000000 --- a/tests/exhaustive/basic/set07/expected/model_1_2_3.eprime +++ /dev/null @@ -1,40 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_Occurrence, x_ExplicitVarSizeWithDummy] -such that - and([x_Occurrence[q29_1] /\ - !or([x_ExplicitVarSizeWithDummy[q28] != 5 /\ x_ExplicitVarSizeWithDummy[q28] = q29_2 | q28 : int(1..4)]) - | q29_1 : int(1..3), q29_2 : int(4..9)]), - and([x_ExplicitVarSizeWithDummy[q2] < x_ExplicitVarSizeWithDummy[q2 + 1] \/ x_ExplicitVarSizeWithDummy[q2] = 5 - | q2 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q3] = 5 -> x_ExplicitVarSizeWithDummy[q3 + 1] = 5 | q3 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q7] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q7]] | q7 : int(1..4)]), - and([x_Occurrence[q8] -> - or([x_ExplicitVarSizeWithDummy[q10] != 5 /\ x_ExplicitVarSizeWithDummy[q10] = q8 | q10 : int(1..4)]) - | q8 : int(1..4)]), - and([q11 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q11] < x_ExplicitVarSizeWithMarker_Values[q11 + 1] - | q11 : int(1..3)]), - and([q12 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q12] = 1 | q12 : int(1..4)]), - and([q15 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q15]] - | q15 : int(1..4)]), - and([x_Occurrence[q16] -> - or([q18 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q18] = q16 - | q18 : int(1..4)]) - | q16 : int(1..4)]), - and([q20 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q22] != 5 /\ - x_ExplicitVarSizeWithDummy[q22] = x_ExplicitVarSizeWithMarker_Values[q20] - | q22 : int(1..4)]) - | q20 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q24] != 5 -> - or([q26 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q26] = x_ExplicitVarSizeWithDummy[q24] - | q26 : int(1..4)]) - | q24 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set07/expected/model_1_2_4-solution000001.solution b/tests/exhaustive/basic/set07/expected/model_1_2_4-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set07/expected/model_1_2_4-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set07/expected/model_1_2_4.eprime b/tests/exhaustive/basic/set07/expected/model_1_2_4.eprime deleted file mode 100644 index 4700b607d4..0000000000 --- a/tests/exhaustive/basic/set07/expected/model_1_2_4.eprime +++ /dev/null @@ -1,41 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_Occurrence, x_ExplicitVarSizeWithDummy] -such that - and([x_Occurrence[q31_1] /\ - !or([x_ExplicitVarSizeWithDummy[q30] != 5 /\ x_ExplicitVarSizeWithDummy[q30] = q31_2 | q30 : int(1..4)]) - | q31_1 : int(1..3), q31_2 : int(4..9)]), - and([x_ExplicitVarSizeWithDummy[q2] < x_ExplicitVarSizeWithDummy[q2 + 1] \/ x_ExplicitVarSizeWithDummy[q2] = 5 - | q2 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q3] = 5 -> x_ExplicitVarSizeWithDummy[q3 + 1] = 5 | q3 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q7] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q7]] | q7 : int(1..4)]), - and([x_Occurrence[q8] -> - or([x_ExplicitVarSizeWithDummy[q10] != 5 /\ x_ExplicitVarSizeWithDummy[q10] = q8 | q10 : int(1..4)]) - | q8 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q11 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q11] < x_ExplicitVarSizeWithFlags_Values[q11 + 1] - | q11 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q12] = false -> x_ExplicitVarSizeWithFlags_Values[q12] = 1 - | q12 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q13 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q13] | q13 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q17] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q17]] - | q17 : int(1..4)]), - and([x_Occurrence[q18] -> - or([x_ExplicitVarSizeWithFlags_Flags[q20] /\ x_ExplicitVarSizeWithFlags_Values[q20] = q18 | q20 : int(1..4)]) - | q18 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q22] -> - or([x_ExplicitVarSizeWithDummy[q24] != 5 /\ - x_ExplicitVarSizeWithDummy[q24] = x_ExplicitVarSizeWithFlags_Values[q22] - | q24 : int(1..4)]) - | q22 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q26] != 5 -> - or([x_ExplicitVarSizeWithFlags_Flags[q28] /\ - x_ExplicitVarSizeWithFlags_Values[q28] = x_ExplicitVarSizeWithDummy[q26] - | q28 : int(1..4)]) - | q26 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set07/expected/model_1_3_1-solution000001.solution b/tests/exhaustive/basic/set07/expected/model_1_3_1-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set07/expected/model_1_3_1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set07/expected/model_1_3_1.eprime b/tests/exhaustive/basic/set07/expected/model_1_3_1.eprime deleted file mode 100644 index 6da06e040b..0000000000 --- a/tests/exhaustive/basic/set07/expected/model_1_3_1.eprime +++ /dev/null @@ -1,21 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -branching on [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_Occurrence] -such that - and([x_Occurrence[q12_1] /\ - !or([q11 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q11] = q12_2 - | q11 : int(1..4)]) - | q12_1 : int(1..3), q12_2 : int(4..9)]), - and([q2 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q2] < x_ExplicitVarSizeWithMarker_Values[q2 + 1] - | q2 : int(1..3)]), - and([q3 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q3] = 1 | q3 : int(1..4)]), - and([q6 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q6]] - | q6 : int(1..4)]), - and([x_Occurrence[q7] -> - or([q9 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q9] = q7 | q9 : int(1..4)]) - | q7 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set07/expected/model_1_3_2-solution000001.solution b/tests/exhaustive/basic/set07/expected/model_1_3_2-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set07/expected/model_1_3_2-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set07/expected/model_1_3_2.eprime b/tests/exhaustive/basic/set07/expected/model_1_3_2.eprime deleted file mode 100644 index f8fefa8170..0000000000 --- a/tests/exhaustive/basic/set07/expected/model_1_3_2.eprime +++ /dev/null @@ -1,40 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -branching on - [x_ExplicitVarSizeWithDummy, x_Occurrence, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] -such that - and([x_Occurrence[q29_1] /\ - !or([q28 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q28] = q29_2 - | q28 : int(1..4)]) - | q29_1 : int(1..3), q29_2 : int(4..9)]), - and([q2 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q2] < x_ExplicitVarSizeWithMarker_Values[q2 + 1] - | q2 : int(1..3)]), - and([q3 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q3] = 1 | q3 : int(1..4)]), - and([q6 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q6]] - | q6 : int(1..4)]), - and([x_Occurrence[q7] -> - or([q9 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q9] = q7 | q9 : int(1..4)]) - | q7 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q10] < x_ExplicitVarSizeWithDummy[q10 + 1] \/ x_ExplicitVarSizeWithDummy[q10] = 5 - | q10 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q11] = 5 -> x_ExplicitVarSizeWithDummy[q11 + 1] = 5 | q11 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q15] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q15]] | q15 : int(1..4)]), - and([x_Occurrence[q16] -> - or([x_ExplicitVarSizeWithDummy[q18] != 5 /\ x_ExplicitVarSizeWithDummy[q18] = q16 | q18 : int(1..4)]) - | q16 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q20] != 5 -> - or([q22 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q22] = x_ExplicitVarSizeWithDummy[q20] - | q22 : int(1..4)]) - | q20 : int(1..4)]), - and([q24 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q26] != 5 /\ - x_ExplicitVarSizeWithDummy[q26] = x_ExplicitVarSizeWithMarker_Values[q24] - | q26 : int(1..4)]) - | q24 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set07/expected/model_1_3_3-solution000001.solution b/tests/exhaustive/basic/set07/expected/model_1_3_3-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set07/expected/model_1_3_3-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set07/expected/model_1_3_3.eprime b/tests/exhaustive/basic/set07/expected/model_1_3_3.eprime deleted file mode 100644 index 6da06e040b..0000000000 --- a/tests/exhaustive/basic/set07/expected/model_1_3_3.eprime +++ /dev/null @@ -1,21 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -branching on [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_Occurrence] -such that - and([x_Occurrence[q12_1] /\ - !or([q11 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q11] = q12_2 - | q11 : int(1..4)]) - | q12_1 : int(1..3), q12_2 : int(4..9)]), - and([q2 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q2] < x_ExplicitVarSizeWithMarker_Values[q2 + 1] - | q2 : int(1..3)]), - and([q3 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q3] = 1 | q3 : int(1..4)]), - and([q6 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q6]] - | q6 : int(1..4)]), - and([x_Occurrence[q7] -> - or([q9 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q9] = q7 | q9 : int(1..4)]) - | q7 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set07/expected/model_1_3_4-solution000001.solution b/tests/exhaustive/basic/set07/expected/model_1_3_4-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set07/expected/model_1_3_4-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set07/expected/model_1_3_4.eprime b/tests/exhaustive/basic/set07/expected/model_1_3_4.eprime deleted file mode 100644 index 744a29abf7..0000000000 --- a/tests/exhaustive/basic/set07/expected/model_1_3_4.eprime +++ /dev/null @@ -1,46 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_Occurrence, - x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] -such that - and([x_Occurrence[q30_1] /\ - !or([q29 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q29] = q30_2 - | q29 : int(1..4)]) - | q30_1 : int(1..3), q30_2 : int(4..9)]), - and([q2 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q2] < x_ExplicitVarSizeWithMarker_Values[q2 + 1] - | q2 : int(1..3)]), - and([q3 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q3] = 1 | q3 : int(1..4)]), - and([q6 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q6]] - | q6 : int(1..4)]), - and([x_Occurrence[q7] -> - or([q9 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q9] = q7 | q9 : int(1..4)]) - | q7 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q10 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q10] < x_ExplicitVarSizeWithFlags_Values[q10 + 1] - | q10 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q11] = false -> x_ExplicitVarSizeWithFlags_Values[q11] = 1 - | q11 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q12 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q12] | q12 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q16] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q16]] - | q16 : int(1..4)]), - and([x_Occurrence[q17] -> - or([x_ExplicitVarSizeWithFlags_Flags[q19] /\ x_ExplicitVarSizeWithFlags_Values[q19] = q17 | q19 : int(1..4)]) - | q17 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q21] -> - or([q23 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q23] = x_ExplicitVarSizeWithFlags_Values[q21] - | q23 : int(1..4)]) - | q21 : int(1..4)]), - and([q25 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q27] /\ - x_ExplicitVarSizeWithFlags_Values[q27] = x_ExplicitVarSizeWithMarker_Values[q25] - | q27 : int(1..4)]) - | q25 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set07/expected/model_1_4_1-solution000001.solution b/tests/exhaustive/basic/set07/expected/model_1_4_1-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set07/expected/model_1_4_1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set07/expected/model_1_4_1.eprime b/tests/exhaustive/basic/set07/expected/model_1_4_1.eprime deleted file mode 100644 index 38303ddfee..0000000000 --- a/tests/exhaustive/basic/set07/expected/model_1_4_1.eprime +++ /dev/null @@ -1,21 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -branching on [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_Occurrence] -such that - and([x_Occurrence[q14_1] /\ - !or([x_ExplicitVarSizeWithFlags_Flags[q13] /\ x_ExplicitVarSizeWithFlags_Values[q13] = q14_2 - | q13 : int(1..4)]) - | q14_1 : int(1..3), q14_2 : int(4..9)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q2] < x_ExplicitVarSizeWithFlags_Values[q2 + 1] - | q2 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3] = false -> x_ExplicitVarSizeWithFlags_Values[q3] = 1 | q3 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q4] | q4 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q8] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q8]] | q8 : int(1..4)]), - and([x_Occurrence[q9] -> - or([x_ExplicitVarSizeWithFlags_Flags[q11] /\ x_ExplicitVarSizeWithFlags_Values[q11] = q9 | q11 : int(1..4)]) - | q9 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set07/expected/model_1_4_2-solution000001.solution b/tests/exhaustive/basic/set07/expected/model_1_4_2-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set07/expected/model_1_4_2-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set07/expected/model_1_4_2.eprime b/tests/exhaustive/basic/set07/expected/model_1_4_2.eprime deleted file mode 100644 index e9a9b228b7..0000000000 --- a/tests/exhaustive/basic/set07/expected/model_1_4_2.eprime +++ /dev/null @@ -1,40 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -branching on - [x_ExplicitVarSizeWithDummy, x_Occurrence, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] -such that - and([x_Occurrence[q31_1] /\ - !or([x_ExplicitVarSizeWithFlags_Flags[q30] /\ x_ExplicitVarSizeWithFlags_Values[q30] = q31_2 - | q30 : int(1..4)]) - | q31_1 : int(1..3), q31_2 : int(4..9)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q2] < x_ExplicitVarSizeWithFlags_Values[q2 + 1] - | q2 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3] = false -> x_ExplicitVarSizeWithFlags_Values[q3] = 1 | q3 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q4] | q4 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q8] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q8]] | q8 : int(1..4)]), - and([x_Occurrence[q9] -> - or([x_ExplicitVarSizeWithFlags_Flags[q11] /\ x_ExplicitVarSizeWithFlags_Values[q11] = q9 | q11 : int(1..4)]) - | q9 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q12] < x_ExplicitVarSizeWithDummy[q12 + 1] \/ x_ExplicitVarSizeWithDummy[q12] = 5 - | q12 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q13] = 5 -> x_ExplicitVarSizeWithDummy[q13 + 1] = 5 | q13 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q17] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q17]] | q17 : int(1..4)]), - and([x_Occurrence[q18] -> - or([x_ExplicitVarSizeWithDummy[q20] != 5 /\ x_ExplicitVarSizeWithDummy[q20] = q18 | q20 : int(1..4)]) - | q18 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q22] != 5 -> - or([x_ExplicitVarSizeWithFlags_Flags[q24] /\ - x_ExplicitVarSizeWithFlags_Values[q24] = x_ExplicitVarSizeWithDummy[q22] - | q24 : int(1..4)]) - | q22 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q26] -> - or([x_ExplicitVarSizeWithDummy[q28] != 5 /\ - x_ExplicitVarSizeWithDummy[q28] = x_ExplicitVarSizeWithFlags_Values[q26] - | q28 : int(1..4)]) - | q26 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set07/expected/model_1_4_3-solution000001.solution b/tests/exhaustive/basic/set07/expected/model_1_4_3-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set07/expected/model_1_4_3-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set07/expected/model_1_4_3.eprime b/tests/exhaustive/basic/set07/expected/model_1_4_3.eprime deleted file mode 100644 index 7b8fce9b8d..0000000000 --- a/tests/exhaustive/basic/set07/expected/model_1_4_3.eprime +++ /dev/null @@ -1,45 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_Occurrence, - x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] -such that - and([x_Occurrence[q30_1] /\ - !or([x_ExplicitVarSizeWithFlags_Flags[q29] /\ x_ExplicitVarSizeWithFlags_Values[q29] = q30_2 - | q29 : int(1..4)]) - | q30_1 : int(1..3), q30_2 : int(4..9)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q2] < x_ExplicitVarSizeWithFlags_Values[q2 + 1] - | q2 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3] = false -> x_ExplicitVarSizeWithFlags_Values[q3] = 1 | q3 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q4] | q4 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q8] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q8]] | q8 : int(1..4)]), - and([x_Occurrence[q9] -> - or([x_ExplicitVarSizeWithFlags_Flags[q11] /\ x_ExplicitVarSizeWithFlags_Values[q11] = q9 | q11 : int(1..4)]) - | q9 : int(1..4)]), - and([q12 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q12] < x_ExplicitVarSizeWithMarker_Values[q12 + 1] - | q12 : int(1..3)]), - and([q13 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q13] = 1 | q13 : int(1..4)]), - and([q16 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q16]] - | q16 : int(1..4)]), - and([x_Occurrence[q17] -> - or([q19 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q19] = q17 - | q19 : int(1..4)]) - | q17 : int(1..4)]), - and([q21 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q23] /\ - x_ExplicitVarSizeWithFlags_Values[q23] = x_ExplicitVarSizeWithMarker_Values[q21] - | q23 : int(1..4)]) - | q21 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q25] -> - or([q27 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q27] = x_ExplicitVarSizeWithFlags_Values[q25] - | q27 : int(1..4)]) - | q25 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set07/expected/model_1_4_4-solution000001.solution b/tests/exhaustive/basic/set07/expected/model_1_4_4-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set07/expected/model_1_4_4-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set07/expected/model_1_4_4.eprime b/tests/exhaustive/basic/set07/expected/model_1_4_4.eprime deleted file mode 100644 index 38303ddfee..0000000000 --- a/tests/exhaustive/basic/set07/expected/model_1_4_4.eprime +++ /dev/null @@ -1,21 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -branching on [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_Occurrence] -such that - and([x_Occurrence[q14_1] /\ - !or([x_ExplicitVarSizeWithFlags_Flags[q13] /\ x_ExplicitVarSizeWithFlags_Values[q13] = q14_2 - | q13 : int(1..4)]) - | q14_1 : int(1..3), q14_2 : int(4..9)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q2] < x_ExplicitVarSizeWithFlags_Values[q2 + 1] - | q2 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3] = false -> x_ExplicitVarSizeWithFlags_Values[q3] = 1 | q3 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q4] | q4 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q8] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q8]] | q8 : int(1..4)]), - and([x_Occurrence[q9] -> - or([x_ExplicitVarSizeWithFlags_Flags[q11] /\ x_ExplicitVarSizeWithFlags_Values[q11] = q9 | q11 : int(1..4)]) - | q9 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set07/expected/model_2_1_1-solution000001.solution b/tests/exhaustive/basic/set07/expected/model_2_1_1-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set07/expected/model_2_1_1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set07/expected/model_2_1_1.eprime b/tests/exhaustive/basic/set07/expected/model_2_1_1.eprime deleted file mode 100644 index 9157723de1..0000000000 --- a/tests/exhaustive/basic/set07/expected/model_2_1_1.eprime +++ /dev/null @@ -1,17 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -find x_Occurrence: matrix indexed by [int(1..4)] of bool -branching on [x_Occurrence, x_ExplicitVarSizeWithDummy] -such that - and([or([x_ExplicitVarSizeWithDummy[q7] != 5 /\ x_ExplicitVarSizeWithDummy[q7] = q8_1 | q7 : int(1..4)]) /\ - !x_Occurrence[q8_2] - | q8_1 : int(1..3), q8_2 : int(4..9)]), - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 5 - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q2] = 5 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..3)]), - and([x_Occurrence[q9] -> - or([x_ExplicitVarSizeWithDummy[q11] != 5 /\ x_ExplicitVarSizeWithDummy[q11] = q9 | q11 : int(1..4)]) - | q9 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q13] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q13]] | q13 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set07/expected/model_2_1_2-solution000001.solution b/tests/exhaustive/basic/set07/expected/model_2_1_2-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set07/expected/model_2_1_2-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set07/expected/model_2_1_2.eprime b/tests/exhaustive/basic/set07/expected/model_2_1_2.eprime deleted file mode 100644 index 9157723de1..0000000000 --- a/tests/exhaustive/basic/set07/expected/model_2_1_2.eprime +++ /dev/null @@ -1,17 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -find x_Occurrence: matrix indexed by [int(1..4)] of bool -branching on [x_Occurrence, x_ExplicitVarSizeWithDummy] -such that - and([or([x_ExplicitVarSizeWithDummy[q7] != 5 /\ x_ExplicitVarSizeWithDummy[q7] = q8_1 | q7 : int(1..4)]) /\ - !x_Occurrence[q8_2] - | q8_1 : int(1..3), q8_2 : int(4..9)]), - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 5 - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q2] = 5 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..3)]), - and([x_Occurrence[q9] -> - or([x_ExplicitVarSizeWithDummy[q11] != 5 /\ x_ExplicitVarSizeWithDummy[q11] = q9 | q11 : int(1..4)]) - | q9 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q13] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q13]] | q13 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set07/expected/model_2_1_3-solution000001.solution b/tests/exhaustive/basic/set07/expected/model_2_1_3-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set07/expected/model_2_1_3-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set07/expected/model_2_1_3.eprime b/tests/exhaustive/basic/set07/expected/model_2_1_3.eprime deleted file mode 100644 index 71931d01a0..0000000000 --- a/tests/exhaustive/basic/set07/expected/model_2_1_3.eprime +++ /dev/null @@ -1,40 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -find x_Occurrence: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy, x_Occurrence] -such that - and([or([x_ExplicitVarSizeWithDummy[q23] != 5 /\ x_ExplicitVarSizeWithDummy[q23] = q24_1 | q23 : int(1..4)]) /\ - !x_Occurrence[q24_2] - | q24_1 : int(1..3), q24_2 : int(4..9)]), - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 5 - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q2] = 5 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..3)]), - and([x_Occurrence[q25] -> - or([x_ExplicitVarSizeWithDummy[q27] != 5 /\ x_ExplicitVarSizeWithDummy[q27] = q25 | q27 : int(1..4)]) - | q25 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q29] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q29]] | q29 : int(1..4)]), - and([q6 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q6] < x_ExplicitVarSizeWithMarker_Values[q6 + 1] - | q6 : int(1..3)]), - and([q7 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q7] = 1 | q7 : int(1..4)]), - and([q10 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q12] != 5 /\ - x_ExplicitVarSizeWithDummy[q12] = x_ExplicitVarSizeWithMarker_Values[q10] - | q12 : int(1..4)]) - | q10 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q14] != 5 -> - or([q16 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q16] = x_ExplicitVarSizeWithDummy[q14] - | q16 : int(1..4)]) - | q14 : int(1..4)]), - and([q18 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q18]] - | q18 : int(1..4)]), - and([x_Occurrence[q19] -> - or([q21 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q21] = q19 - | q21 : int(1..4)]) - | q19 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set07/expected/model_2_1_4-solution000001.solution b/tests/exhaustive/basic/set07/expected/model_2_1_4-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set07/expected/model_2_1_4-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set07/expected/model_2_1_4.eprime b/tests/exhaustive/basic/set07/expected/model_2_1_4.eprime deleted file mode 100644 index 1b82376576..0000000000 --- a/tests/exhaustive/basic/set07/expected/model_2_1_4.eprime +++ /dev/null @@ -1,40 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -find x_Occurrence: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy, x_Occurrence] -such that - and([or([x_ExplicitVarSizeWithDummy[q25] != 5 /\ x_ExplicitVarSizeWithDummy[q25] = q26_1 | q25 : int(1..4)]) /\ - !x_Occurrence[q26_2] - | q26_1 : int(1..3), q26_2 : int(4..9)]), - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 5 - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q2] = 5 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..3)]), - and([x_Occurrence[q27] -> - or([x_ExplicitVarSizeWithDummy[q29] != 5 /\ x_ExplicitVarSizeWithDummy[q29] = q27 | q29 : int(1..4)]) - | q27 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q31] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q31]] | q31 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q6] < x_ExplicitVarSizeWithFlags_Values[q6 + 1] - | q6 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q7] = false -> x_ExplicitVarSizeWithFlags_Values[q7] = 1 | q7 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q8 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q8] | q8 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q12] -> - or([x_ExplicitVarSizeWithDummy[q14] != 5 /\ - x_ExplicitVarSizeWithDummy[q14] = x_ExplicitVarSizeWithFlags_Values[q12] - | q14 : int(1..4)]) - | q12 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q16] != 5 -> - or([x_ExplicitVarSizeWithFlags_Flags[q18] /\ - x_ExplicitVarSizeWithFlags_Values[q18] = x_ExplicitVarSizeWithDummy[q16] - | q18 : int(1..4)]) - | q16 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q20] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q20]] - | q20 : int(1..4)]), - and([x_Occurrence[q21] -> - or([x_ExplicitVarSizeWithFlags_Flags[q23] /\ x_ExplicitVarSizeWithFlags_Values[q23] = q21 | q23 : int(1..4)]) - | q21 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set07/expected/model_2_2_1-solution000001.solution b/tests/exhaustive/basic/set07/expected/model_2_2_1-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set07/expected/model_2_2_1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set07/expected/model_2_2_1.eprime b/tests/exhaustive/basic/set07/expected/model_2_2_1.eprime deleted file mode 100644 index f490f980a2..0000000000 --- a/tests/exhaustive/basic/set07/expected/model_2_2_1.eprime +++ /dev/null @@ -1,17 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -find x_Occurrence: matrix indexed by [int(1..4)] of bool -branching on [x_Occurrence, x_ExplicitVarSizeWithDummy] -such that - and([or([x_ExplicitVarSizeWithDummy[q7] != 5 /\ x_ExplicitVarSizeWithDummy[q7] = q10_1 | q7 : int(1..4)]) /\ - !or([x_ExplicitVarSizeWithDummy[q9] != 5 /\ x_ExplicitVarSizeWithDummy[q9] = q10_2 | q9 : int(1..4)]) - | q10_1 : int(1..3), q10_2 : int(4..9)]), - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 5 - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q2] = 5 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..3)]), - and([x_Occurrence[q11] -> - or([x_ExplicitVarSizeWithDummy[q13] != 5 /\ x_ExplicitVarSizeWithDummy[q13] = q11 | q13 : int(1..4)]) - | q11 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q15] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q15]] | q15 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set07/expected/model_2_2_2-solution000001.solution b/tests/exhaustive/basic/set07/expected/model_2_2_2-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set07/expected/model_2_2_2-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set07/expected/model_2_2_2.eprime b/tests/exhaustive/basic/set07/expected/model_2_2_2.eprime deleted file mode 100644 index ccc364f0fe..0000000000 --- a/tests/exhaustive/basic/set07/expected/model_2_2_2.eprime +++ /dev/null @@ -1,12 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -branching on [x_ExplicitVarSizeWithDummy] -such that - and([or([x_ExplicitVarSizeWithDummy[q6] != 5 /\ x_ExplicitVarSizeWithDummy[q6] = q9_1 | q6 : int(1..4)]) /\ - !or([x_ExplicitVarSizeWithDummy[q8] != 5 /\ x_ExplicitVarSizeWithDummy[q8] = q9_2 | q8 : int(1..4)]) - | q9_1 : int(1..3), q9_2 : int(4..9)]), - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 5 - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q2] = 5 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..3)]) - diff --git a/tests/exhaustive/basic/set07/expected/model_2_2_3-solution000001.solution b/tests/exhaustive/basic/set07/expected/model_2_2_3-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set07/expected/model_2_2_3-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set07/expected/model_2_2_3.eprime b/tests/exhaustive/basic/set07/expected/model_2_2_3.eprime deleted file mode 100644 index c1bc8f0602..0000000000 --- a/tests/exhaustive/basic/set07/expected/model_2_2_3.eprime +++ /dev/null @@ -1,28 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -branching on [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy] -such that - and([or([x_ExplicitVarSizeWithDummy[q17] != 5 /\ x_ExplicitVarSizeWithDummy[q17] = q20_1 | q17 : int(1..4)]) /\ - !or([x_ExplicitVarSizeWithDummy[q19] != 5 /\ x_ExplicitVarSizeWithDummy[q19] = q20_2 | q19 : int(1..4)]) - | q20_1 : int(1..3), q20_2 : int(4..9)]), - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 5 - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q2] = 5 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..3)]), - and([q5 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q5] < x_ExplicitVarSizeWithMarker_Values[q5 + 1] - | q5 : int(1..3)]), - and([q6 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q6] = 1 | q6 : int(1..4)]), - and([q9 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q11] != 5 /\ - x_ExplicitVarSizeWithDummy[q11] = x_ExplicitVarSizeWithMarker_Values[q9] - | q11 : int(1..4)]) - | q9 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q13] != 5 -> - or([q15 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q15] = x_ExplicitVarSizeWithDummy[q13] - | q15 : int(1..4)]) - | q13 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set07/expected/model_2_2_4-solution000001.solution b/tests/exhaustive/basic/set07/expected/model_2_2_4-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set07/expected/model_2_2_4-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set07/expected/model_2_2_4.eprime b/tests/exhaustive/basic/set07/expected/model_2_2_4.eprime deleted file mode 100644 index 128577ea84..0000000000 --- a/tests/exhaustive/basic/set07/expected/model_2_2_4.eprime +++ /dev/null @@ -1,29 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -branching on [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy] -such that - and([or([x_ExplicitVarSizeWithDummy[q19] != 5 /\ x_ExplicitVarSizeWithDummy[q19] = q22_1 | q19 : int(1..4)]) /\ - !or([x_ExplicitVarSizeWithDummy[q21] != 5 /\ x_ExplicitVarSizeWithDummy[q21] = q22_2 | q21 : int(1..4)]) - | q22_1 : int(1..3), q22_2 : int(4..9)]), - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 5 - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q2] = 5 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q5 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q5] < x_ExplicitVarSizeWithFlags_Values[q5 + 1] - | q5 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q6] = false -> x_ExplicitVarSizeWithFlags_Values[q6] = 1 | q6 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q7] | q7 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q11] -> - or([x_ExplicitVarSizeWithDummy[q13] != 5 /\ - x_ExplicitVarSizeWithDummy[q13] = x_ExplicitVarSizeWithFlags_Values[q11] - | q13 : int(1..4)]) - | q11 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q15] != 5 -> - or([x_ExplicitVarSizeWithFlags_Flags[q17] /\ - x_ExplicitVarSizeWithFlags_Values[q17] = x_ExplicitVarSizeWithDummy[q15] - | q17 : int(1..4)]) - | q15 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set07/expected/model_2_3_1-solution000001.solution b/tests/exhaustive/basic/set07/expected/model_2_3_1-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set07/expected/model_2_3_1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set07/expected/model_2_3_1.eprime b/tests/exhaustive/basic/set07/expected/model_2_3_1.eprime deleted file mode 100644 index bb5d893672..0000000000 --- a/tests/exhaustive/basic/set07/expected/model_2_3_1.eprime +++ /dev/null @@ -1,41 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_Occurrence: matrix indexed by [int(1..4)] of bool -branching on - [x_Occurrence, x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] -such that - and([or([x_ExplicitVarSizeWithDummy[q18] != 5 /\ x_ExplicitVarSizeWithDummy[q18] = q21_1 | q18 : int(1..4)]) /\ - !or([q20 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q20] = q21_2 - | q20 : int(1..4)]) - | q21_1 : int(1..3), q21_2 : int(4..9)]), - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 5 - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q2] = 5 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..3)]), - and([q5 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q5] < x_ExplicitVarSizeWithMarker_Values[q5 + 1] - | q5 : int(1..3)]), - and([q6 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q6] = 1 | q6 : int(1..4)]), - and([q9 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q11] != 5 /\ - x_ExplicitVarSizeWithDummy[q11] = x_ExplicitVarSizeWithMarker_Values[q9] - | q11 : int(1..4)]) - | q9 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q13] != 5 -> - or([q15 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q15] = x_ExplicitVarSizeWithDummy[q13] - | q15 : int(1..4)]) - | q13 : int(1..4)]), - and([x_Occurrence[q22] -> - or([x_ExplicitVarSizeWithDummy[q24] != 5 /\ x_ExplicitVarSizeWithDummy[q24] = q22 | q24 : int(1..4)]) - | q22 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q26] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q26]] | q26 : int(1..4)]), - and([x_Occurrence[q27] -> - or([q29 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q29] = q27 - | q29 : int(1..4)]) - | q27 : int(1..4)]), - and([q31 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q31]] - | q31 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set07/expected/model_2_3_2-solution000001.solution b/tests/exhaustive/basic/set07/expected/model_2_3_2-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set07/expected/model_2_3_2-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set07/expected/model_2_3_2.eprime b/tests/exhaustive/basic/set07/expected/model_2_3_2.eprime deleted file mode 100644 index 9623bc7a26..0000000000 --- a/tests/exhaustive/basic/set07/expected/model_2_3_2.eprime +++ /dev/null @@ -1,29 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -branching on [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy] -such that - and([or([x_ExplicitVarSizeWithDummy[q17] != 5 /\ x_ExplicitVarSizeWithDummy[q17] = q20_1 | q17 : int(1..4)]) /\ - !or([q19 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q19] = q20_2 - | q19 : int(1..4)]) - | q20_1 : int(1..3), q20_2 : int(4..9)]), - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 5 - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q2] = 5 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..3)]), - and([q5 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q5] < x_ExplicitVarSizeWithMarker_Values[q5 + 1] - | q5 : int(1..3)]), - and([q6 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q6] = 1 | q6 : int(1..4)]), - and([q9 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q11] != 5 /\ - x_ExplicitVarSizeWithDummy[q11] = x_ExplicitVarSizeWithMarker_Values[q9] - | q11 : int(1..4)]) - | q9 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q13] != 5 -> - or([q15 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q15] = x_ExplicitVarSizeWithDummy[q13] - | q15 : int(1..4)]) - | q13 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set07/expected/model_2_3_3-solution000001.solution b/tests/exhaustive/basic/set07/expected/model_2_3_3-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set07/expected/model_2_3_3-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set07/expected/model_2_3_3.eprime b/tests/exhaustive/basic/set07/expected/model_2_3_3.eprime deleted file mode 100644 index 9623bc7a26..0000000000 --- a/tests/exhaustive/basic/set07/expected/model_2_3_3.eprime +++ /dev/null @@ -1,29 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -branching on [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy] -such that - and([or([x_ExplicitVarSizeWithDummy[q17] != 5 /\ x_ExplicitVarSizeWithDummy[q17] = q20_1 | q17 : int(1..4)]) /\ - !or([q19 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q19] = q20_2 - | q19 : int(1..4)]) - | q20_1 : int(1..3), q20_2 : int(4..9)]), - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 5 - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q2] = 5 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..3)]), - and([q5 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q5] < x_ExplicitVarSizeWithMarker_Values[q5 + 1] - | q5 : int(1..3)]), - and([q6 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q6] = 1 | q6 : int(1..4)]), - and([q9 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q11] != 5 /\ - x_ExplicitVarSizeWithDummy[q11] = x_ExplicitVarSizeWithMarker_Values[q9] - | q11 : int(1..4)]) - | q9 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q13] != 5 -> - or([q15 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q15] = x_ExplicitVarSizeWithDummy[q13] - | q15 : int(1..4)]) - | q13 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set07/expected/model_2_3_4-solution000001.solution b/tests/exhaustive/basic/set07/expected/model_2_3_4-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set07/expected/model_2_3_4-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set07/expected/model_2_3_4.eprime b/tests/exhaustive/basic/set07/expected/model_2_3_4.eprime deleted file mode 100644 index 5172fad9a2..0000000000 --- a/tests/exhaustive/basic/set07/expected/model_2_3_4.eprime +++ /dev/null @@ -1,59 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy, - x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] -such that - and([or([x_ExplicitVarSizeWithDummy[q38] != 5 /\ x_ExplicitVarSizeWithDummy[q38] = q41_1 | q38 : int(1..4)]) /\ - !or([q40 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q40] = q41_2 - | q40 : int(1..4)]) - | q41_1 : int(1..3), q41_2 : int(4..9)]), - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 5 - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q2] = 5 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..3)]), - and([q5 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q5] < x_ExplicitVarSizeWithMarker_Values[q5 + 1] - | q5 : int(1..3)]), - and([q6 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q6] = 1 | q6 : int(1..4)]), - and([q9 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q11] != 5 /\ - x_ExplicitVarSizeWithDummy[q11] = x_ExplicitVarSizeWithMarker_Values[q9] - | q11 : int(1..4)]) - | q9 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q13] != 5 -> - or([q15 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q15] = x_ExplicitVarSizeWithDummy[q13] - | q15 : int(1..4)]) - | q13 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q16 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q16] < x_ExplicitVarSizeWithFlags_Values[q16 + 1] - | q16 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q17] = false -> x_ExplicitVarSizeWithFlags_Values[q17] = 1 - | q17 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q18 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q18] | q18 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q22] -> - or([x_ExplicitVarSizeWithDummy[q24] != 5 /\ - x_ExplicitVarSizeWithDummy[q24] = x_ExplicitVarSizeWithFlags_Values[q22] - | q24 : int(1..4)]) - | q22 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q26] != 5 -> - or([x_ExplicitVarSizeWithFlags_Flags[q28] /\ - x_ExplicitVarSizeWithFlags_Values[q28] = x_ExplicitVarSizeWithDummy[q26] - | q28 : int(1..4)]) - | q26 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q30] -> - or([q32 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q32] = x_ExplicitVarSizeWithFlags_Values[q30] - | q32 : int(1..4)]) - | q30 : int(1..4)]), - and([q34 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q36] /\ - x_ExplicitVarSizeWithFlags_Values[q36] = x_ExplicitVarSizeWithMarker_Values[q34] - | q36 : int(1..4)]) - | q34 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set07/expected/model_2_4_1-solution000001.solution b/tests/exhaustive/basic/set07/expected/model_2_4_1-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set07/expected/model_2_4_1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set07/expected/model_2_4_1.eprime b/tests/exhaustive/basic/set07/expected/model_2_4_1.eprime deleted file mode 100644 index d96379070f..0000000000 --- a/tests/exhaustive/basic/set07/expected/model_2_4_1.eprime +++ /dev/null @@ -1,41 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_Occurrence: matrix indexed by [int(1..4)] of bool -branching on - [x_Occurrence, x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] -such that - and([or([x_ExplicitVarSizeWithDummy[q30] != 5 /\ x_ExplicitVarSizeWithDummy[q30] = q33_1 | q30 : int(1..4)]) /\ - !or([x_ExplicitVarSizeWithFlags_Flags[q32] /\ x_ExplicitVarSizeWithFlags_Values[q32] = q33_2 - | q32 : int(1..4)]) - | q33_1 : int(1..3), q33_2 : int(4..9)]), - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 5 - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q2] = 5 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q5 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q5] < x_ExplicitVarSizeWithFlags_Values[q5 + 1] - | q5 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q6] = false -> x_ExplicitVarSizeWithFlags_Values[q6] = 1 | q6 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q7] | q7 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q11] -> - or([x_ExplicitVarSizeWithDummy[q13] != 5 /\ - x_ExplicitVarSizeWithDummy[q13] = x_ExplicitVarSizeWithFlags_Values[q11] - | q13 : int(1..4)]) - | q11 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q15] != 5 -> - or([x_ExplicitVarSizeWithFlags_Flags[q17] /\ - x_ExplicitVarSizeWithFlags_Values[q17] = x_ExplicitVarSizeWithDummy[q15] - | q17 : int(1..4)]) - | q15 : int(1..4)]), - and([x_Occurrence[q19] -> - or([x_ExplicitVarSizeWithDummy[q21] != 5 /\ x_ExplicitVarSizeWithDummy[q21] = q19 | q21 : int(1..4)]) - | q19 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q23] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q23]] | q23 : int(1..4)]), - and([x_Occurrence[q24] -> - or([x_ExplicitVarSizeWithFlags_Flags[q26] /\ x_ExplicitVarSizeWithFlags_Values[q26] = q24 | q26 : int(1..4)]) - | q24 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q28] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q28]] - | q28 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set07/expected/model_2_4_2-solution000001.solution b/tests/exhaustive/basic/set07/expected/model_2_4_2-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set07/expected/model_2_4_2-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set07/expected/model_2_4_2.eprime b/tests/exhaustive/basic/set07/expected/model_2_4_2.eprime deleted file mode 100644 index 82fca6cda7..0000000000 --- a/tests/exhaustive/basic/set07/expected/model_2_4_2.eprime +++ /dev/null @@ -1,30 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -branching on [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy] -such that - and([or([x_ExplicitVarSizeWithDummy[q19] != 5 /\ x_ExplicitVarSizeWithDummy[q19] = q22_1 | q19 : int(1..4)]) /\ - !or([x_ExplicitVarSizeWithFlags_Flags[q21] /\ x_ExplicitVarSizeWithFlags_Values[q21] = q22_2 - | q21 : int(1..4)]) - | q22_1 : int(1..3), q22_2 : int(4..9)]), - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 5 - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q2] = 5 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q5 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q5] < x_ExplicitVarSizeWithFlags_Values[q5 + 1] - | q5 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q6] = false -> x_ExplicitVarSizeWithFlags_Values[q6] = 1 | q6 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q7] | q7 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q11] -> - or([x_ExplicitVarSizeWithDummy[q13] != 5 /\ - x_ExplicitVarSizeWithDummy[q13] = x_ExplicitVarSizeWithFlags_Values[q11] - | q13 : int(1..4)]) - | q11 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q15] != 5 -> - or([x_ExplicitVarSizeWithFlags_Flags[q17] /\ - x_ExplicitVarSizeWithFlags_Values[q17] = x_ExplicitVarSizeWithDummy[q15] - | q17 : int(1..4)]) - | q15 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set07/expected/model_2_4_3-solution000001.solution b/tests/exhaustive/basic/set07/expected/model_2_4_3-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set07/expected/model_2_4_3-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set07/expected/model_2_4_3.eprime b/tests/exhaustive/basic/set07/expected/model_2_4_3.eprime deleted file mode 100644 index d9bc3fdee6..0000000000 --- a/tests/exhaustive/basic/set07/expected/model_2_4_3.eprime +++ /dev/null @@ -1,58 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy, - x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] -such that - and([or([x_ExplicitVarSizeWithDummy[q38] != 5 /\ x_ExplicitVarSizeWithDummy[q38] = q41_1 | q38 : int(1..4)]) /\ - !or([x_ExplicitVarSizeWithFlags_Flags[q40] /\ x_ExplicitVarSizeWithFlags_Values[q40] = q41_2 - | q40 : int(1..4)]) - | q41_1 : int(1..3), q41_2 : int(4..9)]), - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 5 - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q2] = 5 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q5 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q5] < x_ExplicitVarSizeWithFlags_Values[q5 + 1] - | q5 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q6] = false -> x_ExplicitVarSizeWithFlags_Values[q6] = 1 | q6 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q7] | q7 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q11] -> - or([x_ExplicitVarSizeWithDummy[q13] != 5 /\ - x_ExplicitVarSizeWithDummy[q13] = x_ExplicitVarSizeWithFlags_Values[q11] - | q13 : int(1..4)]) - | q11 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q15] != 5 -> - or([x_ExplicitVarSizeWithFlags_Flags[q17] /\ - x_ExplicitVarSizeWithFlags_Values[q17] = x_ExplicitVarSizeWithDummy[q15] - | q17 : int(1..4)]) - | q15 : int(1..4)]), - and([q18 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q18] < x_ExplicitVarSizeWithMarker_Values[q18 + 1] - | q18 : int(1..3)]), - and([q19 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q19] = 1 | q19 : int(1..4)]), - and([q22 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q24] != 5 /\ - x_ExplicitVarSizeWithDummy[q24] = x_ExplicitVarSizeWithMarker_Values[q22] - | q24 : int(1..4)]) - | q22 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q26] != 5 -> - or([q28 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q28] = x_ExplicitVarSizeWithDummy[q26] - | q28 : int(1..4)]) - | q26 : int(1..4)]), - and([q30 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q32] /\ - x_ExplicitVarSizeWithFlags_Values[q32] = x_ExplicitVarSizeWithMarker_Values[q30] - | q32 : int(1..4)]) - | q30 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q34] -> - or([q36 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q36] = x_ExplicitVarSizeWithFlags_Values[q34] - | q36 : int(1..4)]) - | q34 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set07/expected/model_2_4_4-solution000001.solution b/tests/exhaustive/basic/set07/expected/model_2_4_4-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set07/expected/model_2_4_4-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set07/expected/model_2_4_4.eprime b/tests/exhaustive/basic/set07/expected/model_2_4_4.eprime deleted file mode 100644 index 82fca6cda7..0000000000 --- a/tests/exhaustive/basic/set07/expected/model_2_4_4.eprime +++ /dev/null @@ -1,30 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -branching on [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy] -such that - and([or([x_ExplicitVarSizeWithDummy[q19] != 5 /\ x_ExplicitVarSizeWithDummy[q19] = q22_1 | q19 : int(1..4)]) /\ - !or([x_ExplicitVarSizeWithFlags_Flags[q21] /\ x_ExplicitVarSizeWithFlags_Values[q21] = q22_2 - | q21 : int(1..4)]) - | q22_1 : int(1..3), q22_2 : int(4..9)]), - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 5 - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q2] = 5 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q5 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q5] < x_ExplicitVarSizeWithFlags_Values[q5 + 1] - | q5 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q6] = false -> x_ExplicitVarSizeWithFlags_Values[q6] = 1 | q6 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q7] | q7 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q11] -> - or([x_ExplicitVarSizeWithDummy[q13] != 5 /\ - x_ExplicitVarSizeWithDummy[q13] = x_ExplicitVarSizeWithFlags_Values[q11] - | q13 : int(1..4)]) - | q11 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q15] != 5 -> - or([x_ExplicitVarSizeWithFlags_Flags[q17] /\ - x_ExplicitVarSizeWithFlags_Values[q17] = x_ExplicitVarSizeWithDummy[q15] - | q17 : int(1..4)]) - | q15 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set07/expected/model_3_1_1-solution000001.solution b/tests/exhaustive/basic/set07/expected/model_3_1_1-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set07/expected/model_3_1_1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set07/expected/model_3_1_1.eprime b/tests/exhaustive/basic/set07/expected/model_3_1_1.eprime deleted file mode 100644 index a9299de8e5..0000000000 --- a/tests/exhaustive/basic/set07/expected/model_3_1_1.eprime +++ /dev/null @@ -1,22 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_Occurrence: matrix indexed by [int(1..4)] of bool -branching on [x_Occurrence, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] -such that - and([or([q6 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q6] = q7_1 - | q6 : int(1..4)]) - /\ !x_Occurrence[q7_2] - | q7_1 : int(1..3), q7_2 : int(4..9)]), - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..3)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..4)]), - and([x_Occurrence[q8] -> - or([q10 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q10] = q8 - | q10 : int(1..4)]) - | q8 : int(1..4)]), - and([q12 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q12]] - | q12 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set07/expected/model_3_1_2-solution000001.solution b/tests/exhaustive/basic/set07/expected/model_3_1_2-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set07/expected/model_3_1_2-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set07/expected/model_3_1_2.eprime b/tests/exhaustive/basic/set07/expected/model_3_1_2.eprime deleted file mode 100644 index 8897452e59..0000000000 --- a/tests/exhaustive/basic/set07/expected/model_3_1_2.eprime +++ /dev/null @@ -1,41 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_Occurrence: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -branching on - [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_Occurrence] -such that - and([or([q23 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q23] = q24_1 - | q23 : int(1..4)]) - /\ !x_Occurrence[q24_2] - | q24_1 : int(1..3), q24_2 : int(4..9)]), - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..3)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..4)]), - and([x_Occurrence[q25] -> - or([q27 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q27] = q25 - | q27 : int(1..4)]) - | q25 : int(1..4)]), - and([q29 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q29]] - | q29 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q5] < x_ExplicitVarSizeWithDummy[q5 + 1] \/ x_ExplicitVarSizeWithDummy[q5] = 5 - | q5 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q6] = 5 -> x_ExplicitVarSizeWithDummy[q6 + 1] = 5 | q6 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q10] != 5 -> - or([q12 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q12] = x_ExplicitVarSizeWithDummy[q10] - | q12 : int(1..4)]) - | q10 : int(1..4)]), - and([q14 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q16] != 5 /\ - x_ExplicitVarSizeWithDummy[q16] = x_ExplicitVarSizeWithMarker_Values[q14] - | q16 : int(1..4)]) - | q14 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q18] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q18]] | q18 : int(1..4)]), - and([x_Occurrence[q19] -> - or([x_ExplicitVarSizeWithDummy[q21] != 5 /\ x_ExplicitVarSizeWithDummy[q21] = q19 | q21 : int(1..4)]) - | q19 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set07/expected/model_3_1_3-solution000001.solution b/tests/exhaustive/basic/set07/expected/model_3_1_3-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set07/expected/model_3_1_3-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set07/expected/model_3_1_3.eprime b/tests/exhaustive/basic/set07/expected/model_3_1_3.eprime deleted file mode 100644 index a9299de8e5..0000000000 --- a/tests/exhaustive/basic/set07/expected/model_3_1_3.eprime +++ /dev/null @@ -1,22 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_Occurrence: matrix indexed by [int(1..4)] of bool -branching on [x_Occurrence, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] -such that - and([or([q6 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q6] = q7_1 - | q6 : int(1..4)]) - /\ !x_Occurrence[q7_2] - | q7_1 : int(1..3), q7_2 : int(4..9)]), - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..3)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..4)]), - and([x_Occurrence[q8] -> - or([q10 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q10] = q8 - | q10 : int(1..4)]) - | q8 : int(1..4)]), - and([q12 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q12]] - | q12 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set07/expected/model_3_1_4-solution000001.solution b/tests/exhaustive/basic/set07/expected/model_3_1_4-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set07/expected/model_3_1_4-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set07/expected/model_3_1_4.eprime b/tests/exhaustive/basic/set07/expected/model_3_1_4.eprime deleted file mode 100644 index e3716d35cd..0000000000 --- a/tests/exhaustive/basic/set07/expected/model_3_1_4.eprime +++ /dev/null @@ -1,46 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_Occurrence: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithMarker_Marker, - x_ExplicitVarSizeWithMarker_Values, x_Occurrence] -such that - and([or([q24 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q24] = q25_1 - | q24 : int(1..4)]) - /\ !x_Occurrence[q25_2] - | q25_1 : int(1..3), q25_2 : int(4..9)]), - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..3)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..4)]), - and([x_Occurrence[q26] -> - or([q28 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q28] = q26 - | q28 : int(1..4)]) - | q26 : int(1..4)]), - and([q30 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q30]] - | q30 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q5 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q5] < x_ExplicitVarSizeWithFlags_Values[q5 + 1] - | q5 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q6] = false -> x_ExplicitVarSizeWithFlags_Values[q6] = 1 | q6 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q7] | q7 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q11] -> - or([q13 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q13] = x_ExplicitVarSizeWithFlags_Values[q11] - | q13 : int(1..4)]) - | q11 : int(1..4)]), - and([q15 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q17] /\ - x_ExplicitVarSizeWithFlags_Values[q17] = x_ExplicitVarSizeWithMarker_Values[q15] - | q17 : int(1..4)]) - | q15 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q19] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q19]] - | q19 : int(1..4)]), - and([x_Occurrence[q20] -> - or([x_ExplicitVarSizeWithFlags_Flags[q22] /\ x_ExplicitVarSizeWithFlags_Values[q22] = q20 | q22 : int(1..4)]) - | q20 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set07/expected/model_3_2_1-solution000001.solution b/tests/exhaustive/basic/set07/expected/model_3_2_1-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set07/expected/model_3_2_1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set07/expected/model_3_2_1.eprime b/tests/exhaustive/basic/set07/expected/model_3_2_1.eprime deleted file mode 100644 index a4f4f9d9e3..0000000000 --- a/tests/exhaustive/basic/set07/expected/model_3_2_1.eprime +++ /dev/null @@ -1,41 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -find x_Occurrence: matrix indexed by [int(1..4)] of bool -branching on - [x_Occurrence, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy] -such that - and([or([q18 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q18] = q21_1 - | q18 : int(1..4)]) - /\ !or([x_ExplicitVarSizeWithDummy[q20] != 5 /\ x_ExplicitVarSizeWithDummy[q20] = q21_2 | q20 : int(1..4)]) - | q21_1 : int(1..3), q21_2 : int(4..9)]), - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..3)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q4] < x_ExplicitVarSizeWithDummy[q4 + 1] \/ x_ExplicitVarSizeWithDummy[q4] = 5 - | q4 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q5] = 5 -> x_ExplicitVarSizeWithDummy[q5 + 1] = 5 | q5 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q9] != 5 -> - or([q11 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q11] = x_ExplicitVarSizeWithDummy[q9] - | q11 : int(1..4)]) - | q9 : int(1..4)]), - and([q13 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q15] != 5 /\ - x_ExplicitVarSizeWithDummy[q15] = x_ExplicitVarSizeWithMarker_Values[q13] - | q15 : int(1..4)]) - | q13 : int(1..4)]), - and([x_Occurrence[q22] -> - or([q24 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q24] = q22 - | q24 : int(1..4)]) - | q22 : int(1..4)]), - and([q26 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q26]] - | q26 : int(1..4)]), - and([x_Occurrence[q27] -> - or([x_ExplicitVarSizeWithDummy[q29] != 5 /\ x_ExplicitVarSizeWithDummy[q29] = q27 | q29 : int(1..4)]) - | q27 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q31] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q31]] | q31 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set07/expected/model_3_2_2-solution000001.solution b/tests/exhaustive/basic/set07/expected/model_3_2_2-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set07/expected/model_3_2_2-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set07/expected/model_3_2_2.eprime b/tests/exhaustive/basic/set07/expected/model_3_2_2.eprime deleted file mode 100644 index a7e9b28aa7..0000000000 --- a/tests/exhaustive/basic/set07/expected/model_3_2_2.eprime +++ /dev/null @@ -1,29 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -branching on [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] -such that - and([or([q17 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q17] = q20_1 - | q17 : int(1..4)]) - /\ !or([x_ExplicitVarSizeWithDummy[q19] != 5 /\ x_ExplicitVarSizeWithDummy[q19] = q20_2 | q19 : int(1..4)]) - | q20_1 : int(1..3), q20_2 : int(4..9)]), - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..3)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q4] < x_ExplicitVarSizeWithDummy[q4 + 1] \/ x_ExplicitVarSizeWithDummy[q4] = 5 - | q4 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q5] = 5 -> x_ExplicitVarSizeWithDummy[q5 + 1] = 5 | q5 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q9] != 5 -> - or([q11 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q11] = x_ExplicitVarSizeWithDummy[q9] - | q11 : int(1..4)]) - | q9 : int(1..4)]), - and([q13 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q15] != 5 /\ - x_ExplicitVarSizeWithDummy[q15] = x_ExplicitVarSizeWithMarker_Values[q13] - | q15 : int(1..4)]) - | q13 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set07/expected/model_3_2_3-solution000001.solution b/tests/exhaustive/basic/set07/expected/model_3_2_3-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set07/expected/model_3_2_3-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set07/expected/model_3_2_3.eprime b/tests/exhaustive/basic/set07/expected/model_3_2_3.eprime deleted file mode 100644 index a7e9b28aa7..0000000000 --- a/tests/exhaustive/basic/set07/expected/model_3_2_3.eprime +++ /dev/null @@ -1,29 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -branching on [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] -such that - and([or([q17 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q17] = q20_1 - | q17 : int(1..4)]) - /\ !or([x_ExplicitVarSizeWithDummy[q19] != 5 /\ x_ExplicitVarSizeWithDummy[q19] = q20_2 | q19 : int(1..4)]) - | q20_1 : int(1..3), q20_2 : int(4..9)]), - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..3)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q4] < x_ExplicitVarSizeWithDummy[q4 + 1] \/ x_ExplicitVarSizeWithDummy[q4] = 5 - | q4 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q5] = 5 -> x_ExplicitVarSizeWithDummy[q5 + 1] = 5 | q5 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q9] != 5 -> - or([q11 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q11] = x_ExplicitVarSizeWithDummy[q9] - | q11 : int(1..4)]) - | q9 : int(1..4)]), - and([q13 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q15] != 5 /\ - x_ExplicitVarSizeWithDummy[q15] = x_ExplicitVarSizeWithMarker_Values[q13] - | q15 : int(1..4)]) - | q13 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set07/expected/model_3_2_4-solution000001.solution b/tests/exhaustive/basic/set07/expected/model_3_2_4-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set07/expected/model_3_2_4-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set07/expected/model_3_2_4.eprime b/tests/exhaustive/basic/set07/expected/model_3_2_4.eprime deleted file mode 100644 index 9ba2c2499e..0000000000 --- a/tests/exhaustive/basic/set07/expected/model_3_2_4.eprime +++ /dev/null @@ -1,59 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithMarker_Marker, - x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy] -such that - and([or([q38 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q38] = q41_1 - | q38 : int(1..4)]) - /\ !or([x_ExplicitVarSizeWithDummy[q40] != 5 /\ x_ExplicitVarSizeWithDummy[q40] = q41_2 | q40 : int(1..4)]) - | q41_1 : int(1..3), q41_2 : int(4..9)]), - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..3)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q4] < x_ExplicitVarSizeWithDummy[q4 + 1] \/ x_ExplicitVarSizeWithDummy[q4] = 5 - | q4 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q5] = 5 -> x_ExplicitVarSizeWithDummy[q5 + 1] = 5 | q5 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q9] != 5 -> - or([q11 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q11] = x_ExplicitVarSizeWithDummy[q9] - | q11 : int(1..4)]) - | q9 : int(1..4)]), - and([q13 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q15] != 5 /\ - x_ExplicitVarSizeWithDummy[q15] = x_ExplicitVarSizeWithMarker_Values[q13] - | q15 : int(1..4)]) - | q13 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q16 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q16] < x_ExplicitVarSizeWithFlags_Values[q16 + 1] - | q16 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q17] = false -> x_ExplicitVarSizeWithFlags_Values[q17] = 1 - | q17 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q18 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q18] | q18 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q22] -> - or([q24 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q24] = x_ExplicitVarSizeWithFlags_Values[q22] - | q24 : int(1..4)]) - | q22 : int(1..4)]), - and([q26 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q28] /\ - x_ExplicitVarSizeWithFlags_Values[q28] = x_ExplicitVarSizeWithMarker_Values[q26] - | q28 : int(1..4)]) - | q26 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q30] -> - or([x_ExplicitVarSizeWithDummy[q32] != 5 /\ - x_ExplicitVarSizeWithDummy[q32] = x_ExplicitVarSizeWithFlags_Values[q30] - | q32 : int(1..4)]) - | q30 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q34] != 5 -> - or([x_ExplicitVarSizeWithFlags_Flags[q36] /\ - x_ExplicitVarSizeWithFlags_Values[q36] = x_ExplicitVarSizeWithDummy[q34] - | q36 : int(1..4)]) - | q34 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set07/expected/model_3_3_1-solution000001.solution b/tests/exhaustive/basic/set07/expected/model_3_3_1-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set07/expected/model_3_3_1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set07/expected/model_3_3_1.eprime b/tests/exhaustive/basic/set07/expected/model_3_3_1.eprime deleted file mode 100644 index f69ec68546..0000000000 --- a/tests/exhaustive/basic/set07/expected/model_3_3_1.eprime +++ /dev/null @@ -1,24 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_Occurrence: matrix indexed by [int(1..4)] of bool -branching on [x_Occurrence, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] -such that - and([or([q6 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q6] = q9_1 - | q6 : int(1..4)]) - /\ - !or([q8 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q8] = q9_2 - | q8 : int(1..4)]) - | q9_1 : int(1..3), q9_2 : int(4..9)]), - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..3)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..4)]), - and([x_Occurrence[q10] -> - or([q12 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q12] = q10 - | q12 : int(1..4)]) - | q10 : int(1..4)]), - and([q14 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q14]] - | q14 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set07/expected/model_3_3_2-solution000001.solution b/tests/exhaustive/basic/set07/expected/model_3_3_2-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set07/expected/model_3_3_2-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set07/expected/model_3_3_2.eprime b/tests/exhaustive/basic/set07/expected/model_3_3_2.eprime deleted file mode 100644 index adc45bc4e1..0000000000 --- a/tests/exhaustive/basic/set07/expected/model_3_3_2.eprime +++ /dev/null @@ -1,31 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -branching on [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] -such that - and([or([q17 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q17] = q20_1 - | q17 : int(1..4)]) - /\ - !or([q19 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q19] = q20_2 - | q19 : int(1..4)]) - | q20_1 : int(1..3), q20_2 : int(4..9)]), - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..3)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q4] < x_ExplicitVarSizeWithDummy[q4 + 1] \/ x_ExplicitVarSizeWithDummy[q4] = 5 - | q4 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q5] = 5 -> x_ExplicitVarSizeWithDummy[q5 + 1] = 5 | q5 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q9] != 5 -> - or([q11 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q11] = x_ExplicitVarSizeWithDummy[q9] - | q11 : int(1..4)]) - | q9 : int(1..4)]), - and([q13 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q15] != 5 /\ - x_ExplicitVarSizeWithDummy[q15] = x_ExplicitVarSizeWithMarker_Values[q13] - | q15 : int(1..4)]) - | q13 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set07/expected/model_3_3_3-solution000001.solution b/tests/exhaustive/basic/set07/expected/model_3_3_3-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set07/expected/model_3_3_3-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set07/expected/model_3_3_3.eprime b/tests/exhaustive/basic/set07/expected/model_3_3_3.eprime deleted file mode 100644 index fbcbcb55a2..0000000000 --- a/tests/exhaustive/basic/set07/expected/model_3_3_3.eprime +++ /dev/null @@ -1,17 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -branching on [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] -such that - and([or([q5 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q5] = q8_1 - | q5 : int(1..4)]) - /\ - !or([q7 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q7] = q8_2 - | q7 : int(1..4)]) - | q8_1 : int(1..3), q8_2 : int(4..9)]), - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..3)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set07/expected/model_3_3_4-solution000001.solution b/tests/exhaustive/basic/set07/expected/model_3_3_4-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set07/expected/model_3_3_4-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set07/expected/model_3_3_4.eprime b/tests/exhaustive/basic/set07/expected/model_3_3_4.eprime deleted file mode 100644 index 50a1db36c3..0000000000 --- a/tests/exhaustive/basic/set07/expected/model_3_3_4.eprime +++ /dev/null @@ -1,36 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithMarker_Marker, - x_ExplicitVarSizeWithMarker_Values] -such that - and([or([q18 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q18] = q21_1 - | q18 : int(1..4)]) - /\ - !or([q20 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q20] = q21_2 - | q20 : int(1..4)]) - | q21_1 : int(1..3), q21_2 : int(4..9)]), - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..3)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q4] < x_ExplicitVarSizeWithFlags_Values[q4 + 1] - | q4 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q5] = false -> x_ExplicitVarSizeWithFlags_Values[q5] = 1 | q5 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q6] | q6 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q10] -> - or([q12 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q12] = x_ExplicitVarSizeWithFlags_Values[q10] - | q12 : int(1..4)]) - | q10 : int(1..4)]), - and([q14 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q16] /\ - x_ExplicitVarSizeWithFlags_Values[q16] = x_ExplicitVarSizeWithMarker_Values[q14] - | q16 : int(1..4)]) - | q14 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set07/expected/model_3_4_1-solution000001.solution b/tests/exhaustive/basic/set07/expected/model_3_4_1-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set07/expected/model_3_4_1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set07/expected/model_3_4_1.eprime b/tests/exhaustive/basic/set07/expected/model_3_4_1.eprime deleted file mode 100644 index 61e664ad10..0000000000 --- a/tests/exhaustive/basic/set07/expected/model_3_4_1.eprime +++ /dev/null @@ -1,48 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_Occurrence: matrix indexed by [int(1..4)] of bool -branching on - [x_Occurrence, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, - x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] -such that - and([or([q29 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q29] = q32_1 - | q29 : int(1..4)]) - /\ - !or([x_ExplicitVarSizeWithFlags_Flags[q31] /\ x_ExplicitVarSizeWithFlags_Values[q31] = q32_2 - | q31 : int(1..4)]) - | q32_1 : int(1..3), q32_2 : int(4..9)]), - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..3)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q4] < x_ExplicitVarSizeWithFlags_Values[q4 + 1] - | q4 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q5] = false -> x_ExplicitVarSizeWithFlags_Values[q5] = 1 | q5 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q6] | q6 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q10] -> - or([q12 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q12] = x_ExplicitVarSizeWithFlags_Values[q10] - | q12 : int(1..4)]) - | q10 : int(1..4)]), - and([q14 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q16] /\ - x_ExplicitVarSizeWithFlags_Values[q16] = x_ExplicitVarSizeWithMarker_Values[q14] - | q16 : int(1..4)]) - | q14 : int(1..4)]), - and([x_Occurrence[q18] -> - or([q20 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q20] = q18 - | q20 : int(1..4)]) - | q18 : int(1..4)]), - and([q22 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q22]] - | q22 : int(1..4)]), - and([x_Occurrence[q23] -> - or([x_ExplicitVarSizeWithFlags_Flags[q25] /\ x_ExplicitVarSizeWithFlags_Values[q25] = q23 | q25 : int(1..4)]) - | q23 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q27] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q27]] - | q27 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set07/expected/model_3_4_2-solution000001.solution b/tests/exhaustive/basic/set07/expected/model_3_4_2-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set07/expected/model_3_4_2-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set07/expected/model_3_4_2.eprime b/tests/exhaustive/basic/set07/expected/model_3_4_2.eprime deleted file mode 100644 index b565f5f402..0000000000 --- a/tests/exhaustive/basic/set07/expected/model_3_4_2.eprime +++ /dev/null @@ -1,60 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -branching on - [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, - x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] -such that - and([or([q38 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q38] = q41_1 - | q38 : int(1..4)]) - /\ - !or([x_ExplicitVarSizeWithFlags_Flags[q40] /\ x_ExplicitVarSizeWithFlags_Values[q40] = q41_2 - | q40 : int(1..4)]) - | q41_1 : int(1..3), q41_2 : int(4..9)]), - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..3)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q4] < x_ExplicitVarSizeWithFlags_Values[q4 + 1] - | q4 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q5] = false -> x_ExplicitVarSizeWithFlags_Values[q5] = 1 | q5 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q6] | q6 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q10] -> - or([q12 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q12] = x_ExplicitVarSizeWithFlags_Values[q10] - | q12 : int(1..4)]) - | q10 : int(1..4)]), - and([q14 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q16] /\ - x_ExplicitVarSizeWithFlags_Values[q16] = x_ExplicitVarSizeWithMarker_Values[q14] - | q16 : int(1..4)]) - | q14 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q17] < x_ExplicitVarSizeWithDummy[q17 + 1] \/ x_ExplicitVarSizeWithDummy[q17] = 5 - | q17 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q18] = 5 -> x_ExplicitVarSizeWithDummy[q18 + 1] = 5 | q18 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q22] != 5 -> - or([q24 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q24] = x_ExplicitVarSizeWithDummy[q22] - | q24 : int(1..4)]) - | q22 : int(1..4)]), - and([q26 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q28] != 5 /\ - x_ExplicitVarSizeWithDummy[q28] = x_ExplicitVarSizeWithMarker_Values[q26] - | q28 : int(1..4)]) - | q26 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q30] != 5 -> - or([x_ExplicitVarSizeWithFlags_Flags[q32] /\ - x_ExplicitVarSizeWithFlags_Values[q32] = x_ExplicitVarSizeWithDummy[q30] - | q32 : int(1..4)]) - | q30 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q34] -> - or([x_ExplicitVarSizeWithDummy[q36] != 5 /\ - x_ExplicitVarSizeWithDummy[q36] = x_ExplicitVarSizeWithFlags_Values[q34] - | q36 : int(1..4)]) - | q34 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set07/expected/model_3_4_3-solution000001.solution b/tests/exhaustive/basic/set07/expected/model_3_4_3-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set07/expected/model_3_4_3-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set07/expected/model_3_4_3.eprime b/tests/exhaustive/basic/set07/expected/model_3_4_3.eprime deleted file mode 100644 index d801442667..0000000000 --- a/tests/exhaustive/basic/set07/expected/model_3_4_3.eprime +++ /dev/null @@ -1,36 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithMarker_Marker, - x_ExplicitVarSizeWithMarker_Values] -such that - and([or([q18 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q18] = q21_1 - | q18 : int(1..4)]) - /\ - !or([x_ExplicitVarSizeWithFlags_Flags[q20] /\ x_ExplicitVarSizeWithFlags_Values[q20] = q21_2 - | q20 : int(1..4)]) - | q21_1 : int(1..3), q21_2 : int(4..9)]), - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..3)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q4] < x_ExplicitVarSizeWithFlags_Values[q4 + 1] - | q4 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q5] = false -> x_ExplicitVarSizeWithFlags_Values[q5] = 1 | q5 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q6] | q6 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q10] -> - or([q12 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q12] = x_ExplicitVarSizeWithFlags_Values[q10] - | q12 : int(1..4)]) - | q10 : int(1..4)]), - and([q14 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q16] /\ - x_ExplicitVarSizeWithFlags_Values[q16] = x_ExplicitVarSizeWithMarker_Values[q14] - | q16 : int(1..4)]) - | q14 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set07/expected/model_3_4_4-solution000001.solution b/tests/exhaustive/basic/set07/expected/model_3_4_4-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set07/expected/model_3_4_4-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set07/expected/model_3_4_4.eprime b/tests/exhaustive/basic/set07/expected/model_3_4_4.eprime deleted file mode 100644 index d801442667..0000000000 --- a/tests/exhaustive/basic/set07/expected/model_3_4_4.eprime +++ /dev/null @@ -1,36 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithMarker_Marker, - x_ExplicitVarSizeWithMarker_Values] -such that - and([or([q18 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q18] = q21_1 - | q18 : int(1..4)]) - /\ - !or([x_ExplicitVarSizeWithFlags_Flags[q20] /\ x_ExplicitVarSizeWithFlags_Values[q20] = q21_2 - | q20 : int(1..4)]) - | q21_1 : int(1..3), q21_2 : int(4..9)]), - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..3)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q4] < x_ExplicitVarSizeWithFlags_Values[q4 + 1] - | q4 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q5] = false -> x_ExplicitVarSizeWithFlags_Values[q5] = 1 | q5 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q6] | q6 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q10] -> - or([q12 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q12] = x_ExplicitVarSizeWithFlags_Values[q10] - | q12 : int(1..4)]) - | q10 : int(1..4)]), - and([q14 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q16] /\ - x_ExplicitVarSizeWithFlags_Values[q16] = x_ExplicitVarSizeWithMarker_Values[q14] - | q16 : int(1..4)]) - | q14 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set07/expected/model_4_1_1-solution000001.solution b/tests/exhaustive/basic/set07/expected/model_4_1_1-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set07/expected/model_4_1_1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set07/expected/model_4_1_1.eprime b/tests/exhaustive/basic/set07/expected/model_4_1_1.eprime deleted file mode 100644 index 981837a4f9..0000000000 --- a/tests/exhaustive/basic/set07/expected/model_4_1_1.eprime +++ /dev/null @@ -1,21 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_Occurrence: matrix indexed by [int(1..4)] of bool -branching on [x_Occurrence, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] -such that - and([or([x_ExplicitVarSizeWithFlags_Flags[q13] /\ x_ExplicitVarSizeWithFlags_Values[q13] = q14_1 | q13 : int(1..4)]) - /\ !x_Occurrence[q14_2] - | q14_1 : int(1..3), q14_2 : int(4..9)]), - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), - and([x_Occurrence[q7] -> - or([x_ExplicitVarSizeWithFlags_Flags[q9] /\ x_ExplicitVarSizeWithFlags_Values[q9] = q7 | q9 : int(1..4)]) - | q7 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q11] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q11]] - | q11 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set07/expected/model_4_1_2-solution000001.solution b/tests/exhaustive/basic/set07/expected/model_4_1_2-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set07/expected/model_4_1_2-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set07/expected/model_4_1_2.eprime b/tests/exhaustive/basic/set07/expected/model_4_1_2.eprime deleted file mode 100644 index 3c2a07f559..0000000000 --- a/tests/exhaustive/basic/set07/expected/model_4_1_2.eprime +++ /dev/null @@ -1,40 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_Occurrence: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -branching on - [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_Occurrence] -such that - and([or([x_ExplicitVarSizeWithFlags_Flags[q30] /\ x_ExplicitVarSizeWithFlags_Values[q30] = q31_1 | q30 : int(1..4)]) - /\ !x_Occurrence[q31_2] - | q31_1 : int(1..3), q31_2 : int(4..9)]), - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), - and([x_Occurrence[q24] -> - or([x_ExplicitVarSizeWithFlags_Flags[q26] /\ x_ExplicitVarSizeWithFlags_Values[q26] = q24 | q26 : int(1..4)]) - | q24 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q28] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q28]] - | q28 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q7] < x_ExplicitVarSizeWithDummy[q7 + 1] \/ x_ExplicitVarSizeWithDummy[q7] = 5 - | q7 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q8] = 5 -> x_ExplicitVarSizeWithDummy[q8 + 1] = 5 | q8 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q12] != 5 -> - or([x_ExplicitVarSizeWithFlags_Flags[q14] /\ - x_ExplicitVarSizeWithFlags_Values[q14] = x_ExplicitVarSizeWithDummy[q12] - | q14 : int(1..4)]) - | q12 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q16] -> - or([x_ExplicitVarSizeWithDummy[q18] != 5 /\ - x_ExplicitVarSizeWithDummy[q18] = x_ExplicitVarSizeWithFlags_Values[q16] - | q18 : int(1..4)]) - | q16 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q20] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q20]] | q20 : int(1..4)]), - and([x_Occurrence[q21] -> - or([x_ExplicitVarSizeWithDummy[q23] != 5 /\ x_ExplicitVarSizeWithDummy[q23] = q21 | q23 : int(1..4)]) - | q21 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set07/expected/model_4_1_3-solution000001.solution b/tests/exhaustive/basic/set07/expected/model_4_1_3-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set07/expected/model_4_1_3-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set07/expected/model_4_1_3.eprime b/tests/exhaustive/basic/set07/expected/model_4_1_3.eprime deleted file mode 100644 index 00c2bc51f1..0000000000 --- a/tests/exhaustive/basic/set07/expected/model_4_1_3.eprime +++ /dev/null @@ -1,45 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_Occurrence: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithFlags_Flags, - x_ExplicitVarSizeWithFlags_Values, x_Occurrence] -such that - and([or([x_ExplicitVarSizeWithFlags_Flags[q29] /\ x_ExplicitVarSizeWithFlags_Values[q29] = q30_1 | q29 : int(1..4)]) - /\ !x_Occurrence[q30_2] - | q30_1 : int(1..3), q30_2 : int(4..9)]), - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), - and([x_Occurrence[q23] -> - or([x_ExplicitVarSizeWithFlags_Flags[q25] /\ x_ExplicitVarSizeWithFlags_Values[q25] = q23 | q25 : int(1..4)]) - | q23 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q27] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q27]] - | q27 : int(1..4)]), - and([q7 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q7] < x_ExplicitVarSizeWithMarker_Values[q7 + 1] - | q7 : int(1..3)]), - and([q8 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q8] = 1 | q8 : int(1..4)]), - and([q11 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q13] /\ - x_ExplicitVarSizeWithFlags_Values[q13] = x_ExplicitVarSizeWithMarker_Values[q11] - | q13 : int(1..4)]) - | q11 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q15] -> - or([q17 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q17] = x_ExplicitVarSizeWithFlags_Values[q15] - | q17 : int(1..4)]) - | q15 : int(1..4)]), - and([q19 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q19]] - | q19 : int(1..4)]), - and([x_Occurrence[q20] -> - or([q22 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q22] = q20 - | q22 : int(1..4)]) - | q20 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set07/expected/model_4_1_4-solution000001.solution b/tests/exhaustive/basic/set07/expected/model_4_1_4-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set07/expected/model_4_1_4-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set07/expected/model_4_1_4.eprime b/tests/exhaustive/basic/set07/expected/model_4_1_4.eprime deleted file mode 100644 index 981837a4f9..0000000000 --- a/tests/exhaustive/basic/set07/expected/model_4_1_4.eprime +++ /dev/null @@ -1,21 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_Occurrence: matrix indexed by [int(1..4)] of bool -branching on [x_Occurrence, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] -such that - and([or([x_ExplicitVarSizeWithFlags_Flags[q13] /\ x_ExplicitVarSizeWithFlags_Values[q13] = q14_1 | q13 : int(1..4)]) - /\ !x_Occurrence[q14_2] - | q14_1 : int(1..3), q14_2 : int(4..9)]), - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), - and([x_Occurrence[q7] -> - or([x_ExplicitVarSizeWithFlags_Flags[q9] /\ x_ExplicitVarSizeWithFlags_Values[q9] = q7 | q9 : int(1..4)]) - | q7 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q11] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q11]] - | q11 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set07/expected/model_4_2_1-solution000001.solution b/tests/exhaustive/basic/set07/expected/model_4_2_1-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set07/expected/model_4_2_1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set07/expected/model_4_2_1.eprime b/tests/exhaustive/basic/set07/expected/model_4_2_1.eprime deleted file mode 100644 index c197a46407..0000000000 --- a/tests/exhaustive/basic/set07/expected/model_4_2_1.eprime +++ /dev/null @@ -1,40 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -find x_Occurrence: matrix indexed by [int(1..4)] of bool -branching on - [x_Occurrence, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy] -such that - and([or([x_ExplicitVarSizeWithFlags_Flags[q30] /\ x_ExplicitVarSizeWithFlags_Values[q30] = q33_1 | q30 : int(1..4)]) - /\ !or([x_ExplicitVarSizeWithDummy[q32] != 5 /\ x_ExplicitVarSizeWithDummy[q32] = q33_2 | q32 : int(1..4)]) - | q33_1 : int(1..3), q33_2 : int(4..9)]), - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q6] < x_ExplicitVarSizeWithDummy[q6 + 1] \/ x_ExplicitVarSizeWithDummy[q6] = 5 - | q6 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q7] = 5 -> x_ExplicitVarSizeWithDummy[q7 + 1] = 5 | q7 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q11] != 5 -> - or([x_ExplicitVarSizeWithFlags_Flags[q13] /\ - x_ExplicitVarSizeWithFlags_Values[q13] = x_ExplicitVarSizeWithDummy[q11] - | q13 : int(1..4)]) - | q11 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q15] -> - or([x_ExplicitVarSizeWithDummy[q17] != 5 /\ - x_ExplicitVarSizeWithDummy[q17] = x_ExplicitVarSizeWithFlags_Values[q15] - | q17 : int(1..4)]) - | q15 : int(1..4)]), - and([x_Occurrence[q19] -> - or([x_ExplicitVarSizeWithFlags_Flags[q21] /\ x_ExplicitVarSizeWithFlags_Values[q21] = q19 | q21 : int(1..4)]) - | q19 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q23] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q23]] - | q23 : int(1..4)]), - and([x_Occurrence[q24] -> - or([x_ExplicitVarSizeWithDummy[q26] != 5 /\ x_ExplicitVarSizeWithDummy[q26] = q24 | q26 : int(1..4)]) - | q24 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q28] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q28]] | q28 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set07/expected/model_4_2_2-solution000001.solution b/tests/exhaustive/basic/set07/expected/model_4_2_2-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set07/expected/model_4_2_2-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set07/expected/model_4_2_2.eprime b/tests/exhaustive/basic/set07/expected/model_4_2_2.eprime deleted file mode 100644 index 8c36b6b158..0000000000 --- a/tests/exhaustive/basic/set07/expected/model_4_2_2.eprime +++ /dev/null @@ -1,29 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -branching on [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] -such that - and([or([x_ExplicitVarSizeWithFlags_Flags[q19] /\ x_ExplicitVarSizeWithFlags_Values[q19] = q22_1 | q19 : int(1..4)]) - /\ !or([x_ExplicitVarSizeWithDummy[q21] != 5 /\ x_ExplicitVarSizeWithDummy[q21] = q22_2 | q21 : int(1..4)]) - | q22_1 : int(1..3), q22_2 : int(4..9)]), - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q6] < x_ExplicitVarSizeWithDummy[q6 + 1] \/ x_ExplicitVarSizeWithDummy[q6] = 5 - | q6 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q7] = 5 -> x_ExplicitVarSizeWithDummy[q7 + 1] = 5 | q7 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q11] != 5 -> - or([x_ExplicitVarSizeWithFlags_Flags[q13] /\ - x_ExplicitVarSizeWithFlags_Values[q13] = x_ExplicitVarSizeWithDummy[q11] - | q13 : int(1..4)]) - | q11 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q15] -> - or([x_ExplicitVarSizeWithDummy[q17] != 5 /\ - x_ExplicitVarSizeWithDummy[q17] = x_ExplicitVarSizeWithFlags_Values[q15] - | q17 : int(1..4)]) - | q15 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set07/expected/model_4_2_3-solution000001.solution b/tests/exhaustive/basic/set07/expected/model_4_2_3-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set07/expected/model_4_2_3-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set07/expected/model_4_2_3.eprime b/tests/exhaustive/basic/set07/expected/model_4_2_3.eprime deleted file mode 100644 index 99e67ea897..0000000000 --- a/tests/exhaustive/basic/set07/expected/model_4_2_3.eprime +++ /dev/null @@ -1,57 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithFlags_Flags, - x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy] -such that - and([or([x_ExplicitVarSizeWithFlags_Flags[q38] /\ x_ExplicitVarSizeWithFlags_Values[q38] = q41_1 | q38 : int(1..4)]) - /\ !or([x_ExplicitVarSizeWithDummy[q40] != 5 /\ x_ExplicitVarSizeWithDummy[q40] = q41_2 | q40 : int(1..4)]) - | q41_1 : int(1..3), q41_2 : int(4..9)]), - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q6] < x_ExplicitVarSizeWithDummy[q6 + 1] \/ x_ExplicitVarSizeWithDummy[q6] = 5 - | q6 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q7] = 5 -> x_ExplicitVarSizeWithDummy[q7 + 1] = 5 | q7 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q11] != 5 -> - or([x_ExplicitVarSizeWithFlags_Flags[q13] /\ - x_ExplicitVarSizeWithFlags_Values[q13] = x_ExplicitVarSizeWithDummy[q11] - | q13 : int(1..4)]) - | q11 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q15] -> - or([x_ExplicitVarSizeWithDummy[q17] != 5 /\ - x_ExplicitVarSizeWithDummy[q17] = x_ExplicitVarSizeWithFlags_Values[q15] - | q17 : int(1..4)]) - | q15 : int(1..4)]), - and([q18 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q18] < x_ExplicitVarSizeWithMarker_Values[q18 + 1] - | q18 : int(1..3)]), - and([q19 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q19] = 1 | q19 : int(1..4)]), - and([q22 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q24] /\ - x_ExplicitVarSizeWithFlags_Values[q24] = x_ExplicitVarSizeWithMarker_Values[q22] - | q24 : int(1..4)]) - | q22 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q26] -> - or([q28 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q28] = x_ExplicitVarSizeWithFlags_Values[q26] - | q28 : int(1..4)]) - | q26 : int(1..4)]), - and([q30 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q32] != 5 /\ - x_ExplicitVarSizeWithDummy[q32] = x_ExplicitVarSizeWithMarker_Values[q30] - | q32 : int(1..4)]) - | q30 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q34] != 5 -> - or([q36 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q36] = x_ExplicitVarSizeWithDummy[q34] - | q36 : int(1..4)]) - | q34 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set07/expected/model_4_2_4-solution000001.solution b/tests/exhaustive/basic/set07/expected/model_4_2_4-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set07/expected/model_4_2_4-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set07/expected/model_4_2_4.eprime b/tests/exhaustive/basic/set07/expected/model_4_2_4.eprime deleted file mode 100644 index 8c36b6b158..0000000000 --- a/tests/exhaustive/basic/set07/expected/model_4_2_4.eprime +++ /dev/null @@ -1,29 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -branching on [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] -such that - and([or([x_ExplicitVarSizeWithFlags_Flags[q19] /\ x_ExplicitVarSizeWithFlags_Values[q19] = q22_1 | q19 : int(1..4)]) - /\ !or([x_ExplicitVarSizeWithDummy[q21] != 5 /\ x_ExplicitVarSizeWithDummy[q21] = q22_2 | q21 : int(1..4)]) - | q22_1 : int(1..3), q22_2 : int(4..9)]), - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q6] < x_ExplicitVarSizeWithDummy[q6 + 1] \/ x_ExplicitVarSizeWithDummy[q6] = 5 - | q6 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q7] = 5 -> x_ExplicitVarSizeWithDummy[q7 + 1] = 5 | q7 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q11] != 5 -> - or([x_ExplicitVarSizeWithFlags_Flags[q13] /\ - x_ExplicitVarSizeWithFlags_Values[q13] = x_ExplicitVarSizeWithDummy[q11] - | q13 : int(1..4)]) - | q11 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q15] -> - or([x_ExplicitVarSizeWithDummy[q17] != 5 /\ - x_ExplicitVarSizeWithDummy[q17] = x_ExplicitVarSizeWithFlags_Values[q15] - | q17 : int(1..4)]) - | q15 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set07/expected/model_4_3_1-solution000001.solution b/tests/exhaustive/basic/set07/expected/model_4_3_1-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set07/expected/model_4_3_1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set07/expected/model_4_3_1.eprime b/tests/exhaustive/basic/set07/expected/model_4_3_1.eprime deleted file mode 100644 index f8b5b0c4f9..0000000000 --- a/tests/exhaustive/basic/set07/expected/model_4_3_1.eprime +++ /dev/null @@ -1,47 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_Occurrence: matrix indexed by [int(1..4)] of bool -branching on - [x_Occurrence, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, - x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] -such that - and([or([x_ExplicitVarSizeWithFlags_Flags[q29] /\ x_ExplicitVarSizeWithFlags_Values[q29] = q32_1 | q29 : int(1..4)]) - /\ - !or([q31 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q31] = q32_2 - | q31 : int(1..4)]) - | q32_1 : int(1..3), q32_2 : int(4..9)]), - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), - and([q6 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q6] < x_ExplicitVarSizeWithMarker_Values[q6 + 1] - | q6 : int(1..3)]), - and([q7 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q7] = 1 | q7 : int(1..4)]), - and([q10 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q12] /\ - x_ExplicitVarSizeWithFlags_Values[q12] = x_ExplicitVarSizeWithMarker_Values[q10] - | q12 : int(1..4)]) - | q10 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q14] -> - or([q16 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q16] = x_ExplicitVarSizeWithFlags_Values[q14] - | q16 : int(1..4)]) - | q14 : int(1..4)]), - and([x_Occurrence[q18] -> - or([x_ExplicitVarSizeWithFlags_Flags[q20] /\ x_ExplicitVarSizeWithFlags_Values[q20] = q18 | q20 : int(1..4)]) - | q18 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q22] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q22]] - | q22 : int(1..4)]), - and([x_Occurrence[q23] -> - or([q25 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q25] = q23 - | q25 : int(1..4)]) - | q23 : int(1..4)]), - and([q27 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q27]] - | q27 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set07/expected/model_4_3_2-solution000001.solution b/tests/exhaustive/basic/set07/expected/model_4_3_2-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set07/expected/model_4_3_2-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set07/expected/model_4_3_2.eprime b/tests/exhaustive/basic/set07/expected/model_4_3_2.eprime deleted file mode 100644 index 7b940b4c6d..0000000000 --- a/tests/exhaustive/basic/set07/expected/model_4_3_2.eprime +++ /dev/null @@ -1,59 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -branching on - [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, - x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] -such that - and([or([x_ExplicitVarSizeWithFlags_Flags[q38] /\ x_ExplicitVarSizeWithFlags_Values[q38] = q41_1 | q38 : int(1..4)]) - /\ - !or([q40 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q40] = q41_2 - | q40 : int(1..4)]) - | q41_1 : int(1..3), q41_2 : int(4..9)]), - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), - and([q6 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q6] < x_ExplicitVarSizeWithMarker_Values[q6 + 1] - | q6 : int(1..3)]), - and([q7 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q7] = 1 | q7 : int(1..4)]), - and([q10 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q12] /\ - x_ExplicitVarSizeWithFlags_Values[q12] = x_ExplicitVarSizeWithMarker_Values[q10] - | q12 : int(1..4)]) - | q10 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q14] -> - or([q16 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q16] = x_ExplicitVarSizeWithFlags_Values[q14] - | q16 : int(1..4)]) - | q14 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q17] < x_ExplicitVarSizeWithDummy[q17 + 1] \/ x_ExplicitVarSizeWithDummy[q17] = 5 - | q17 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q18] = 5 -> x_ExplicitVarSizeWithDummy[q18 + 1] = 5 | q18 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q22] != 5 -> - or([x_ExplicitVarSizeWithFlags_Flags[q24] /\ - x_ExplicitVarSizeWithFlags_Values[q24] = x_ExplicitVarSizeWithDummy[q22] - | q24 : int(1..4)]) - | q22 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q26] -> - or([x_ExplicitVarSizeWithDummy[q28] != 5 /\ - x_ExplicitVarSizeWithDummy[q28] = x_ExplicitVarSizeWithFlags_Values[q26] - | q28 : int(1..4)]) - | q26 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q30] != 5 -> - or([q32 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q32] = x_ExplicitVarSizeWithDummy[q30] - | q32 : int(1..4)]) - | q30 : int(1..4)]), - and([q34 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q36] != 5 /\ - x_ExplicitVarSizeWithDummy[q36] = x_ExplicitVarSizeWithMarker_Values[q34] - | q36 : int(1..4)]) - | q34 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set07/expected/model_4_3_3-solution000001.solution b/tests/exhaustive/basic/set07/expected/model_4_3_3-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set07/expected/model_4_3_3-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set07/expected/model_4_3_3.eprime b/tests/exhaustive/basic/set07/expected/model_4_3_3.eprime deleted file mode 100644 index 430b2929c9..0000000000 --- a/tests/exhaustive/basic/set07/expected/model_4_3_3.eprime +++ /dev/null @@ -1,35 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithFlags_Flags, - x_ExplicitVarSizeWithFlags_Values] -such that - and([or([x_ExplicitVarSizeWithFlags_Flags[q18] /\ x_ExplicitVarSizeWithFlags_Values[q18] = q21_1 | q18 : int(1..4)]) - /\ - !or([q20 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q20] = q21_2 - | q20 : int(1..4)]) - | q21_1 : int(1..3), q21_2 : int(4..9)]), - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), - and([q6 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q6] < x_ExplicitVarSizeWithMarker_Values[q6 + 1] - | q6 : int(1..3)]), - and([q7 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q7] = 1 | q7 : int(1..4)]), - and([q10 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q12] /\ - x_ExplicitVarSizeWithFlags_Values[q12] = x_ExplicitVarSizeWithMarker_Values[q10] - | q12 : int(1..4)]) - | q10 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q14] -> - or([q16 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q16] = x_ExplicitVarSizeWithFlags_Values[q14] - | q16 : int(1..4)]) - | q14 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set07/expected/model_4_3_4-solution000001.solution b/tests/exhaustive/basic/set07/expected/model_4_3_4-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set07/expected/model_4_3_4-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set07/expected/model_4_3_4.eprime b/tests/exhaustive/basic/set07/expected/model_4_3_4.eprime deleted file mode 100644 index 430b2929c9..0000000000 --- a/tests/exhaustive/basic/set07/expected/model_4_3_4.eprime +++ /dev/null @@ -1,35 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithFlags_Flags, - x_ExplicitVarSizeWithFlags_Values] -such that - and([or([x_ExplicitVarSizeWithFlags_Flags[q18] /\ x_ExplicitVarSizeWithFlags_Values[q18] = q21_1 | q18 : int(1..4)]) - /\ - !or([q20 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q20] = q21_2 - | q20 : int(1..4)]) - | q21_1 : int(1..3), q21_2 : int(4..9)]), - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), - and([q6 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q6] < x_ExplicitVarSizeWithMarker_Values[q6 + 1] - | q6 : int(1..3)]), - and([q7 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q7] = 1 | q7 : int(1..4)]), - and([q10 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q12] /\ - x_ExplicitVarSizeWithFlags_Values[q12] = x_ExplicitVarSizeWithMarker_Values[q10] - | q12 : int(1..4)]) - | q10 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q14] -> - or([q16 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q16] = x_ExplicitVarSizeWithFlags_Values[q14] - | q16 : int(1..4)]) - | q14 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set07/expected/model_4_4_1-solution000001.solution b/tests/exhaustive/basic/set07/expected/model_4_4_1-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set07/expected/model_4_4_1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set07/expected/model_4_4_1.eprime b/tests/exhaustive/basic/set07/expected/model_4_4_1.eprime deleted file mode 100644 index c330baaa50..0000000000 --- a/tests/exhaustive/basic/set07/expected/model_4_4_1.eprime +++ /dev/null @@ -1,23 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_Occurrence: matrix indexed by [int(1..4)] of bool -branching on [x_Occurrence, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] -such that - and([or([x_ExplicitVarSizeWithFlags_Flags[q13] /\ x_ExplicitVarSizeWithFlags_Values[q13] = q16_1 | q13 : int(1..4)]) - /\ - !or([x_ExplicitVarSizeWithFlags_Flags[q15] /\ x_ExplicitVarSizeWithFlags_Values[q15] = q16_2 - | q15 : int(1..4)]) - | q16_1 : int(1..3), q16_2 : int(4..9)]), - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), - and([x_Occurrence[q7] -> - or([x_ExplicitVarSizeWithFlags_Flags[q9] /\ x_ExplicitVarSizeWithFlags_Values[q9] = q7 | q9 : int(1..4)]) - | q7 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q11] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q11]] - | q11 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set07/expected/model_4_4_2-solution000001.solution b/tests/exhaustive/basic/set07/expected/model_4_4_2-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set07/expected/model_4_4_2-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set07/expected/model_4_4_2.eprime b/tests/exhaustive/basic/set07/expected/model_4_4_2.eprime deleted file mode 100644 index 73b079af26..0000000000 --- a/tests/exhaustive/basic/set07/expected/model_4_4_2.eprime +++ /dev/null @@ -1,31 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) -branching on [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] -such that - and([or([x_ExplicitVarSizeWithFlags_Flags[q19] /\ x_ExplicitVarSizeWithFlags_Values[q19] = q22_1 | q19 : int(1..4)]) - /\ - !or([x_ExplicitVarSizeWithFlags_Flags[q21] /\ x_ExplicitVarSizeWithFlags_Values[q21] = q22_2 - | q21 : int(1..4)]) - | q22_1 : int(1..3), q22_2 : int(4..9)]), - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q6] < x_ExplicitVarSizeWithDummy[q6 + 1] \/ x_ExplicitVarSizeWithDummy[q6] = 5 - | q6 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q7] = 5 -> x_ExplicitVarSizeWithDummy[q7 + 1] = 5 | q7 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q11] != 5 -> - or([x_ExplicitVarSizeWithFlags_Flags[q13] /\ - x_ExplicitVarSizeWithFlags_Values[q13] = x_ExplicitVarSizeWithDummy[q11] - | q13 : int(1..4)]) - | q11 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q15] -> - or([x_ExplicitVarSizeWithDummy[q17] != 5 /\ - x_ExplicitVarSizeWithDummy[q17] = x_ExplicitVarSizeWithFlags_Values[q15] - | q17 : int(1..4)]) - | q15 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set07/expected/model_4_4_3-solution000001.solution b/tests/exhaustive/basic/set07/expected/model_4_4_3-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set07/expected/model_4_4_3-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set07/expected/model_4_4_3.eprime b/tests/exhaustive/basic/set07/expected/model_4_4_3.eprime deleted file mode 100644 index e83bd430d2..0000000000 --- a/tests/exhaustive/basic/set07/expected/model_4_4_3.eprime +++ /dev/null @@ -1,35 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithFlags_Flags, - x_ExplicitVarSizeWithFlags_Values] -such that - and([or([x_ExplicitVarSizeWithFlags_Flags[q18] /\ x_ExplicitVarSizeWithFlags_Values[q18] = q21_1 | q18 : int(1..4)]) - /\ - !or([x_ExplicitVarSizeWithFlags_Flags[q20] /\ x_ExplicitVarSizeWithFlags_Values[q20] = q21_2 - | q20 : int(1..4)]) - | q21_1 : int(1..3), q21_2 : int(4..9)]), - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), - and([q6 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q6] < x_ExplicitVarSizeWithMarker_Values[q6 + 1] - | q6 : int(1..3)]), - and([q7 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q7] = 1 | q7 : int(1..4)]), - and([q10 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q12] /\ - x_ExplicitVarSizeWithFlags_Values[q12] = x_ExplicitVarSizeWithMarker_Values[q10] - | q12 : int(1..4)]) - | q10 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q14] -> - or([q16 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q16] = x_ExplicitVarSizeWithFlags_Values[q14] - | q16 : int(1..4)]) - | q14 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set07/expected/model_4_4_4-solution000001.solution b/tests/exhaustive/basic/set07/expected/model_4_4_4-solution000001.solution deleted file mode 100644 index f909cc486d..0000000000 --- a/tests/exhaustive/basic/set07/expected/model_4_4_4-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set07/expected/model_4_4_4.eprime b/tests/exhaustive/basic/set07/expected/model_4_4_4.eprime deleted file mode 100644 index c0bc6dbb9a..0000000000 --- a/tests/exhaustive/basic/set07/expected/model_4_4_4.eprime +++ /dev/null @@ -1,15 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) -branching on [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] -such that - and([or([x_ExplicitVarSizeWithFlags_Flags[q7] /\ x_ExplicitVarSizeWithFlags_Values[q7] = q10_1 | q7 : int(1..4)]) /\ - !or([x_ExplicitVarSizeWithFlags_Flags[q9] /\ x_ExplicitVarSizeWithFlags_Values[q9] = q10_2 | q9 : int(1..4)]) - | q10_1 : int(1..3), q10_2 : int(4..9)]), - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]) - diff --git a/tests/exhaustive/basic/set08/expected/model_1_1-solution000001.solution b/tests/exhaustive/basic/set08/expected/model_1_1-solution000001.solution deleted file mode 100644 index cb83c94151..0000000000 --- a/tests/exhaustive/basic/set08/expected/model_1_1-solution000001.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {(3, 3), (4, 4)} -$ Visualisation for x -$ 3 3 -$ 4 4 - diff --git a/tests/exhaustive/basic/set08/expected/model_1_1.eprime b/tests/exhaustive/basic/set08/expected/model_1_1.eprime deleted file mode 100644 index 95a52bf5c1..0000000000 --- a/tests/exhaustive/basic/set08/expected/model_1_1.eprime +++ /dev/null @@ -1,25 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..16) -find x_ExplicitVarSizeWithMarker_Values_1: matrix indexed by [int(1..16)] of int(1..4) -find x_ExplicitVarSizeWithMarker_Values_2: matrix indexed by [int(1..16)] of int(3..6) -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values_1, x_ExplicitVarSizeWithMarker_Values_2] -such that - and([q5 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values_1[q5] = x_ExplicitVarSizeWithMarker_Values_2[q5] - | q5 : int(1..16)]), - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - flatten([[x_ExplicitVarSizeWithMarker_Values_1[q1]; int(1)], - [x_ExplicitVarSizeWithMarker_Values_2[q1]; int(1)]; - int(1..2)]) - x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values_1[q2] = 1 /\ x_ExplicitVarSizeWithMarker_Values_2[q2] = 3 - | q2 : int(1..16)]), - 2 <= x_ExplicitVarSizeWithMarker_Marker - diff --git a/tests/exhaustive/basic/set08/expected/model_1_2-solution000001.solution b/tests/exhaustive/basic/set08/expected/model_1_2-solution000001.solution deleted file mode 100644 index cb83c94151..0000000000 --- a/tests/exhaustive/basic/set08/expected/model_1_2-solution000001.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {(3, 3), (4, 4)} -$ Visualisation for x -$ 3 3 -$ 4 4 - diff --git a/tests/exhaustive/basic/set08/expected/model_1_2.eprime b/tests/exhaustive/basic/set08/expected/model_1_2.eprime deleted file mode 100644 index 659a99c583..0000000000 --- a/tests/exhaustive/basic/set08/expected/model_1_2.eprime +++ /dev/null @@ -1,54 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..16) -find x_ExplicitVarSizeWithMarker_Values_1: matrix indexed by [int(1..16)] of int(1..4) -find x_ExplicitVarSizeWithMarker_Values_2: matrix indexed by [int(1..16)] of int(3..6) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..16)] of bool -find x_ExplicitVarSizeWithFlags_Values_1: matrix indexed by [int(1..16)] of int(1..4) -find x_ExplicitVarSizeWithFlags_Values_2: matrix indexed by [int(1..16)] of int(3..6) -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values_1, x_ExplicitVarSizeWithFlags_Values_2, - x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values_1, x_ExplicitVarSizeWithMarker_Values_2] -such that - and([q18 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values_1[q18] = x_ExplicitVarSizeWithMarker_Values_2[q18] - | q18 : int(1..16)]), - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - flatten([[x_ExplicitVarSizeWithMarker_Values_1[q1]; int(1)], - [x_ExplicitVarSizeWithMarker_Values_2[q1]; int(1)]; - int(1..2)]) - x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values_1[q2] = 1 /\ x_ExplicitVarSizeWithMarker_Values_2[q2] = 3 - | q2 : int(1..16)]), - 2 <= x_ExplicitVarSizeWithMarker_Marker, - and([x_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> - flatten([[x_ExplicitVarSizeWithFlags_Values_1[q4]; int(1)], [x_ExplicitVarSizeWithFlags_Values_2[q4]; int(1)]; - int(1..2)]) - - x_ExplicitVarSizeWithFlags_Values_1[q5] = 1 /\ x_ExplicitVarSizeWithFlags_Values_2[q5] = 3 - | q5 : int(1..16)]), - and([x_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q6] | q6 : int(1..15)]), - 2 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q7]) | q7 : int(1..16)]), - and([x_ExplicitVarSizeWithFlags_Flags[q10] -> - or([q12 <= x_ExplicitVarSizeWithMarker_Marker /\ - (x_ExplicitVarSizeWithMarker_Values_1[q12] = x_ExplicitVarSizeWithFlags_Values_1[q10] /\ - x_ExplicitVarSizeWithMarker_Values_2[q12] = x_ExplicitVarSizeWithFlags_Values_2[q10]) - | q12 : int(1..16)]) - | q10 : int(1..16)]), - and([q14 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q16] /\ - (x_ExplicitVarSizeWithFlags_Values_1[q16] = x_ExplicitVarSizeWithMarker_Values_1[q14] /\ - x_ExplicitVarSizeWithFlags_Values_2[q16] = x_ExplicitVarSizeWithMarker_Values_2[q14]) - | q16 : int(1..16)]) - | q14 : int(1..16)]) - diff --git a/tests/exhaustive/basic/set08/expected/model_2_1-solution000001.solution b/tests/exhaustive/basic/set08/expected/model_2_1-solution000001.solution deleted file mode 100644 index cb83c94151..0000000000 --- a/tests/exhaustive/basic/set08/expected/model_2_1-solution000001.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {(3, 3), (4, 4)} -$ Visualisation for x -$ 3 3 -$ 4 4 - diff --git a/tests/exhaustive/basic/set08/expected/model_2_1.eprime b/tests/exhaustive/basic/set08/expected/model_2_1.eprime deleted file mode 100644 index cb39a7bb11..0000000000 --- a/tests/exhaustive/basic/set08/expected/model_2_1.eprime +++ /dev/null @@ -1,54 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..16)] of bool -find x_ExplicitVarSizeWithFlags_Values_1: matrix indexed by [int(1..16)] of int(1..4) -find x_ExplicitVarSizeWithFlags_Values_2: matrix indexed by [int(1..16)] of int(3..6) -find x_ExplicitVarSizeWithMarker_Marker: int(0..16) -find x_ExplicitVarSizeWithMarker_Values_1: matrix indexed by [int(1..16)] of int(1..4) -find x_ExplicitVarSizeWithMarker_Values_2: matrix indexed by [int(1..16)] of int(3..6) -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values_1, x_ExplicitVarSizeWithMarker_Values_2, - x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values_1, x_ExplicitVarSizeWithFlags_Values_2] -such that - and([x_ExplicitVarSizeWithFlags_Flags[q18] -> - x_ExplicitVarSizeWithFlags_Values_1[q18] = x_ExplicitVarSizeWithFlags_Values_2[q18] - | q18 : int(1..16)]), - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - flatten([[x_ExplicitVarSizeWithFlags_Values_1[q1]; int(1)], [x_ExplicitVarSizeWithFlags_Values_2[q1]; int(1)]; - int(1..2)]) - - x_ExplicitVarSizeWithFlags_Values_1[q2] = 1 /\ x_ExplicitVarSizeWithFlags_Values_2[q2] = 3 - | q2 : int(1..16)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..15)]), - 2 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..16)]), - and([q6 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - flatten([[x_ExplicitVarSizeWithMarker_Values_1[q6]; int(1)], - [x_ExplicitVarSizeWithMarker_Values_2[q6]; int(1)]; - int(1..2)]) - x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values_1[q7] = 1 /\ x_ExplicitVarSizeWithMarker_Values_2[q7] = 3 - | q7 : int(1..16)]), - 2 <= x_ExplicitVarSizeWithMarker_Marker, - and([q10 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q12] /\ - (x_ExplicitVarSizeWithFlags_Values_1[q12] = x_ExplicitVarSizeWithMarker_Values_1[q10] /\ - x_ExplicitVarSizeWithFlags_Values_2[q12] = x_ExplicitVarSizeWithMarker_Values_2[q10]) - | q12 : int(1..16)]) - | q10 : int(1..16)]), - and([x_ExplicitVarSizeWithFlags_Flags[q14] -> - or([q16 <= x_ExplicitVarSizeWithMarker_Marker /\ - (x_ExplicitVarSizeWithMarker_Values_1[q16] = x_ExplicitVarSizeWithFlags_Values_1[q14] /\ - x_ExplicitVarSizeWithMarker_Values_2[q16] = x_ExplicitVarSizeWithFlags_Values_2[q14]) - | q16 : int(1..16)]) - | q14 : int(1..16)]) - diff --git a/tests/exhaustive/basic/set08/expected/model_2_2-solution000001.solution b/tests/exhaustive/basic/set08/expected/model_2_2-solution000001.solution deleted file mode 100644 index cb83c94151..0000000000 --- a/tests/exhaustive/basic/set08/expected/model_2_2-solution000001.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {(3, 3), (4, 4)} -$ Visualisation for x -$ 3 3 -$ 4 4 - diff --git a/tests/exhaustive/basic/set08/expected/model_2_2.eprime b/tests/exhaustive/basic/set08/expected/model_2_2.eprime deleted file mode 100644 index 7cd4078178..0000000000 --- a/tests/exhaustive/basic/set08/expected/model_2_2.eprime +++ /dev/null @@ -1,25 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..16)] of bool -find x_ExplicitVarSizeWithFlags_Values_1: matrix indexed by [int(1..16)] of int(1..4) -find x_ExplicitVarSizeWithFlags_Values_2: matrix indexed by [int(1..16)] of int(3..6) -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values_1, x_ExplicitVarSizeWithFlags_Values_2] -such that - and([x_ExplicitVarSizeWithFlags_Flags[q7] -> - x_ExplicitVarSizeWithFlags_Values_1[q7] = x_ExplicitVarSizeWithFlags_Values_2[q7] - | q7 : int(1..16)]), - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - flatten([[x_ExplicitVarSizeWithFlags_Values_1[q1]; int(1)], [x_ExplicitVarSizeWithFlags_Values_2[q1]; int(1)]; - int(1..2)]) - - x_ExplicitVarSizeWithFlags_Values_1[q2] = 1 /\ x_ExplicitVarSizeWithFlags_Values_2[q2] = 3 - | q2 : int(1..16)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..15)]), - 2 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..16)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_1_1_1_1-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_1_1_1_1-solution000001.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_1_1_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_1_1_1_1-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_1_1_1_1-solution000002.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_1_1_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_1_1_1_1.eprime b/tests/exhaustive/basic/set09/expected/model_1_1_1_1.eprime deleted file mode 100644 index 0a40809bac..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_1_1_1.eprime +++ /dev/null @@ -1,10 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(2..5)] of bool -find y_Occurrence: matrix indexed by [int(2..5)] of bool -branching on [x_Occurrence, y_Occurrence] -such that - and([x_Occurrence[i] /\ y_Occurrence[j] -> i + 2 = j | i : int(2..5), j : int(2..5)]), - 1 <= sum([toInt(x_Occurrence[q1]) | q1 : int(2..5)]), - 1 <= sum([toInt(y_Occurrence[q2]) | q2 : int(2..5)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_1_1_1_2-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_1_1_1_2-solution000001.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_1_1_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_1_1_1_2-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_1_1_1_2-solution000002.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_1_1_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_1_1_1_2.eprime b/tests/exhaustive/basic/set09/expected/model_1_1_1_2.eprime deleted file mode 100644 index 3ef4eacc1f..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_1_1_2.eprime +++ /dev/null @@ -1,19 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(2..5)] of bool -find y_Occurrence: matrix indexed by [int(2..5)] of bool -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -branching on [x_Occurrence, y_ExplicitVarSizeWithDummy, y_Occurrence] -such that - and([x_Occurrence[i] /\ y_Occurrence[j] -> i + 2 = j | i : int(2..5), j : int(2..5)]), - 1 <= sum([toInt(x_Occurrence[q1]) | q1 : int(2..5)]), - 1 <= sum([toInt(y_Occurrence[q2]) | q2 : int(2..5)]), - and([y_ExplicitVarSizeWithDummy[q3] < y_ExplicitVarSizeWithDummy[q3 + 1] \/ y_ExplicitVarSizeWithDummy[q3] = 6 - | q3 : int(1..3)]), - and([y_ExplicitVarSizeWithDummy[q4] = 6 -> y_ExplicitVarSizeWithDummy[q4 + 1] = 6 | q4 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q5] != 6) | q5 : int(1..4)]), - and([y_ExplicitVarSizeWithDummy[q8] != 6 -> y_Occurrence[y_ExplicitVarSizeWithDummy[q8]] | q8 : int(1..4)]), - and([y_Occurrence[q9] -> - or([y_ExplicitVarSizeWithDummy[q11] != 6 /\ y_ExplicitVarSizeWithDummy[q11] = q9 | q11 : int(1..4)]) - | q9 : int(2..5)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_1_1_1_3-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_1_1_1_3-solution000001.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_1_1_3-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_1_1_1_3-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_1_1_1_3-solution000002.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_1_1_3-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_1_1_1_3.eprime b/tests/exhaustive/basic/set09/expected/model_1_1_1_3.eprime deleted file mode 100644 index 0079456c1a..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_1_1_3.eprime +++ /dev/null @@ -1,23 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(2..5)] of bool -find y_Occurrence: matrix indexed by [int(2..5)] of bool -find y_ExplicitVarSizeWithMarker_Marker: int(0..4) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -branching on [x_Occurrence, y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values, y_Occurrence] -such that - and([x_Occurrence[i] /\ y_Occurrence[j] -> i + 2 = j | i : int(2..5), j : int(2..5)]), - 1 <= sum([toInt(x_Occurrence[q1]) | q1 : int(2..5)]), - 1 <= sum([toInt(y_Occurrence[q2]) | q2 : int(2..5)]), - and([q3 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> - y_ExplicitVarSizeWithMarker_Values[q3] < y_ExplicitVarSizeWithMarker_Values[q3 + 1] - | q3 : int(1..3)]), - and([q4 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q4] = 2 | q4 : int(1..4)]), - 1 <= y_ExplicitVarSizeWithMarker_Marker, - and([q7 <= y_ExplicitVarSizeWithMarker_Marker -> y_Occurrence[y_ExplicitVarSizeWithMarker_Values[q7]] - | q7 : int(1..4)]), - and([y_Occurrence[q8] -> - or([q10 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[q10] = q8 - | q10 : int(1..4)]) - | q8 : int(2..5)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_1_1_1_4-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_1_1_1_4-solution000001.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_1_1_4-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_1_1_1_4-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_1_1_1_4-solution000002.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_1_1_4-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_1_1_1_4.eprime b/tests/exhaustive/basic/set09/expected/model_1_1_1_4.eprime deleted file mode 100644 index ec2d788f13..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_1_1_4.eprime +++ /dev/null @@ -1,22 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(2..5)] of bool -find y_Occurrence: matrix indexed by [int(2..5)] of bool -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -branching on [x_Occurrence, y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values, y_Occurrence] -such that - and([x_Occurrence[i] /\ y_Occurrence[j] -> i + 2 = j | i : int(2..5), j : int(2..5)]), - 1 <= sum([toInt(x_Occurrence[q1]) | q1 : int(2..5)]), - 1 <= sum([toInt(y_Occurrence[q2]) | q2 : int(2..5)]), - and([y_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> - y_ExplicitVarSizeWithFlags_Values[q3] < y_ExplicitVarSizeWithFlags_Values[q3 + 1] - | q3 : int(1..3)]), - and([y_ExplicitVarSizeWithFlags_Flags[q4] = false -> y_ExplicitVarSizeWithFlags_Values[q4] = 2 | q4 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q5 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q5] | q5 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q6]) | q6 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q9] -> y_Occurrence[y_ExplicitVarSizeWithFlags_Values[q9]] | q9 : int(1..4)]), - and([y_Occurrence[q10] -> - or([y_ExplicitVarSizeWithFlags_Flags[q12] /\ y_ExplicitVarSizeWithFlags_Values[q12] = q10 | q12 : int(1..4)]) - | q10 : int(2..5)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_1_1_2_1-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_1_1_2_1-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_1_2_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_1_1_2_1-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_1_1_2_1-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_1_2_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_1_1_2_1.eprime b/tests/exhaustive/basic/set09/expected/model_1_1_2_1.eprime deleted file mode 100644 index 9f2dbd49dd..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_1_2_1.eprime +++ /dev/null @@ -1,19 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(2..5)] of bool -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -find y_Occurrence: matrix indexed by [int(2..5)] of bool -branching on [x_ExplicitVarSizeWithDummy, x_Occurrence, y_Occurrence] -such that - and([x_Occurrence[i] /\ y_Occurrence[j] -> i + 2 = j | i : int(2..5), j : int(2..5)]), - 1 <= sum([toInt(x_Occurrence[q1]) | q1 : int(2..5)]), - 1 <= sum([toInt(y_Occurrence[q2]) | q2 : int(2..5)]), - and([x_ExplicitVarSizeWithDummy[q3] < x_ExplicitVarSizeWithDummy[q3 + 1] \/ x_ExplicitVarSizeWithDummy[q3] = 6 - | q3 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q4] = 6 -> x_ExplicitVarSizeWithDummy[q4 + 1] = 6 | q4 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q5] != 6) | q5 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q8] != 6 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q8]] | q8 : int(1..4)]), - and([x_Occurrence[q9] -> - or([x_ExplicitVarSizeWithDummy[q11] != 6 /\ x_ExplicitVarSizeWithDummy[q11] = q9 | q11 : int(1..4)]) - | q9 : int(2..5)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_1_1_2_2-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_1_1_2_2-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_1_2_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_1_1_2_2-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_1_1_2_2-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_1_2_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_1_1_2_2.eprime b/tests/exhaustive/basic/set09/expected/model_1_1_2_2.eprime deleted file mode 100644 index 40de4c9235..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_1_2_2.eprime +++ /dev/null @@ -1,28 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(2..5)] of bool -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -find y_Occurrence: matrix indexed by [int(2..5)] of bool -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -branching on [x_ExplicitVarSizeWithDummy, x_Occurrence, y_ExplicitVarSizeWithDummy, y_Occurrence] -such that - and([x_Occurrence[i] /\ y_Occurrence[j] -> i + 2 = j | i : int(2..5), j : int(2..5)]), - 1 <= sum([toInt(x_Occurrence[q1]) | q1 : int(2..5)]), - 1 <= sum([toInt(y_Occurrence[q2]) | q2 : int(2..5)]), - and([x_ExplicitVarSizeWithDummy[q3] < x_ExplicitVarSizeWithDummy[q3 + 1] \/ x_ExplicitVarSizeWithDummy[q3] = 6 - | q3 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q4] = 6 -> x_ExplicitVarSizeWithDummy[q4 + 1] = 6 | q4 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q5] != 6) | q5 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q8] != 6 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q8]] | q8 : int(1..4)]), - and([x_Occurrence[q9] -> - or([x_ExplicitVarSizeWithDummy[q11] != 6 /\ x_ExplicitVarSizeWithDummy[q11] = q9 | q11 : int(1..4)]) - | q9 : int(2..5)]), - and([y_ExplicitVarSizeWithDummy[q12] < y_ExplicitVarSizeWithDummy[q12 + 1] \/ y_ExplicitVarSizeWithDummy[q12] = 6 - | q12 : int(1..3)]), - and([y_ExplicitVarSizeWithDummy[q13] = 6 -> y_ExplicitVarSizeWithDummy[q13 + 1] = 6 | q13 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q14] != 6) | q14 : int(1..4)]), - and([y_ExplicitVarSizeWithDummy[q17] != 6 -> y_Occurrence[y_ExplicitVarSizeWithDummy[q17]] | q17 : int(1..4)]), - and([y_Occurrence[q18] -> - or([y_ExplicitVarSizeWithDummy[q20] != 6 /\ y_ExplicitVarSizeWithDummy[q20] = q18 | q20 : int(1..4)]) - | q18 : int(2..5)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_1_1_2_3-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_1_1_2_3-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_1_2_3-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_1_1_2_3-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_1_1_2_3-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_1_2_3-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_1_1_2_3.eprime b/tests/exhaustive/basic/set09/expected/model_1_1_2_3.eprime deleted file mode 100644 index c2ab749e23..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_1_2_3.eprime +++ /dev/null @@ -1,34 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(2..5)] of bool -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -find y_Occurrence: matrix indexed by [int(2..5)] of bool -find y_ExplicitVarSizeWithMarker_Marker: int(0..4) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -branching on - [x_ExplicitVarSizeWithDummy, x_Occurrence, y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values, - y_Occurrence] -such that - and([x_Occurrence[i] /\ y_Occurrence[j] -> i + 2 = j | i : int(2..5), j : int(2..5)]), - 1 <= sum([toInt(x_Occurrence[q1]) | q1 : int(2..5)]), - 1 <= sum([toInt(y_Occurrence[q2]) | q2 : int(2..5)]), - and([x_ExplicitVarSizeWithDummy[q3] < x_ExplicitVarSizeWithDummy[q3 + 1] \/ x_ExplicitVarSizeWithDummy[q3] = 6 - | q3 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q4] = 6 -> x_ExplicitVarSizeWithDummy[q4 + 1] = 6 | q4 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q5] != 6) | q5 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q8] != 6 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q8]] | q8 : int(1..4)]), - and([x_Occurrence[q9] -> - or([x_ExplicitVarSizeWithDummy[q11] != 6 /\ x_ExplicitVarSizeWithDummy[q11] = q9 | q11 : int(1..4)]) - | q9 : int(2..5)]), - and([q12 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> - y_ExplicitVarSizeWithMarker_Values[q12] < y_ExplicitVarSizeWithMarker_Values[q12 + 1] - | q12 : int(1..3)]), - and([q13 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q13] = 2 | q13 : int(1..4)]), - 1 <= y_ExplicitVarSizeWithMarker_Marker, - and([q16 <= y_ExplicitVarSizeWithMarker_Marker -> y_Occurrence[y_ExplicitVarSizeWithMarker_Values[q16]] - | q16 : int(1..4)]), - and([y_Occurrence[q17] -> - or([q19 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[q19] = q17 - | q19 : int(1..4)]) - | q17 : int(2..5)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_1_1_2_4-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_1_1_2_4-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_1_2_4-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_1_1_2_4-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_1_1_2_4-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_1_2_4-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_1_1_2_4.eprime b/tests/exhaustive/basic/set09/expected/model_1_1_2_4.eprime deleted file mode 100644 index 3439f1ddf8..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_1_2_4.eprime +++ /dev/null @@ -1,35 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(2..5)] of bool -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -find y_Occurrence: matrix indexed by [int(2..5)] of bool -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -branching on - [x_ExplicitVarSizeWithDummy, x_Occurrence, y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values, - y_Occurrence] -such that - and([x_Occurrence[i] /\ y_Occurrence[j] -> i + 2 = j | i : int(2..5), j : int(2..5)]), - 1 <= sum([toInt(x_Occurrence[q1]) | q1 : int(2..5)]), - 1 <= sum([toInt(y_Occurrence[q2]) | q2 : int(2..5)]), - and([x_ExplicitVarSizeWithDummy[q3] < x_ExplicitVarSizeWithDummy[q3 + 1] \/ x_ExplicitVarSizeWithDummy[q3] = 6 - | q3 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q4] = 6 -> x_ExplicitVarSizeWithDummy[q4 + 1] = 6 | q4 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q5] != 6) | q5 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q8] != 6 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q8]] | q8 : int(1..4)]), - and([x_Occurrence[q9] -> - or([x_ExplicitVarSizeWithDummy[q11] != 6 /\ x_ExplicitVarSizeWithDummy[q11] = q9 | q11 : int(1..4)]) - | q9 : int(2..5)]), - and([y_ExplicitVarSizeWithFlags_Flags[q12 + 1] -> - y_ExplicitVarSizeWithFlags_Values[q12] < y_ExplicitVarSizeWithFlags_Values[q12 + 1] - | q12 : int(1..3)]), - and([y_ExplicitVarSizeWithFlags_Flags[q13] = false -> y_ExplicitVarSizeWithFlags_Values[q13] = 2 - | q13 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q14 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q14] | q14 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q15]) | q15 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q18] -> y_Occurrence[y_ExplicitVarSizeWithFlags_Values[q18]] - | q18 : int(1..4)]), - and([y_Occurrence[q19] -> - or([y_ExplicitVarSizeWithFlags_Flags[q21] /\ y_ExplicitVarSizeWithFlags_Values[q21] = q19 | q21 : int(1..4)]) - | q19 : int(2..5)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_1_1_3_1-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_1_1_3_1-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_1_3_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_1_1_3_1-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_1_1_3_1-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_1_3_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_1_1_3_1.eprime b/tests/exhaustive/basic/set09/expected/model_1_1_3_1.eprime deleted file mode 100644 index 745ddbf47d..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_1_3_1.eprime +++ /dev/null @@ -1,23 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(2..5)] of bool -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_Occurrence: matrix indexed by [int(2..5)] of bool -branching on [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_Occurrence, y_Occurrence] -such that - and([x_Occurrence[i] /\ y_Occurrence[j] -> i + 2 = j | i : int(2..5), j : int(2..5)]), - 1 <= sum([toInt(x_Occurrence[q1]) | q1 : int(2..5)]), - 1 <= sum([toInt(y_Occurrence[q2]) | q2 : int(2..5)]), - and([q3 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q3] < x_ExplicitVarSizeWithMarker_Values[q3 + 1] - | q3 : int(1..3)]), - and([q4 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q4] = 2 | q4 : int(1..4)]), - 1 <= x_ExplicitVarSizeWithMarker_Marker, - and([q7 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q7]] - | q7 : int(1..4)]), - and([x_Occurrence[q8] -> - or([q10 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q10] = q8 - | q10 : int(1..4)]) - | q8 : int(2..5)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_1_1_3_2-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_1_1_3_2-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_1_3_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_1_1_3_2-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_1_1_3_2-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_1_3_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_1_1_3_2.eprime b/tests/exhaustive/basic/set09/expected/model_1_1_3_2.eprime deleted file mode 100644 index 6ac452cb87..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_1_3_2.eprime +++ /dev/null @@ -1,34 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(2..5)] of bool -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_Occurrence: matrix indexed by [int(2..5)] of bool -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_Occurrence, y_ExplicitVarSizeWithDummy, - y_Occurrence] -such that - and([x_Occurrence[i] /\ y_Occurrence[j] -> i + 2 = j | i : int(2..5), j : int(2..5)]), - 1 <= sum([toInt(x_Occurrence[q1]) | q1 : int(2..5)]), - 1 <= sum([toInt(y_Occurrence[q2]) | q2 : int(2..5)]), - and([q3 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q3] < x_ExplicitVarSizeWithMarker_Values[q3 + 1] - | q3 : int(1..3)]), - and([q4 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q4] = 2 | q4 : int(1..4)]), - 1 <= x_ExplicitVarSizeWithMarker_Marker, - and([q7 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q7]] - | q7 : int(1..4)]), - and([x_Occurrence[q8] -> - or([q10 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q10] = q8 - | q10 : int(1..4)]) - | q8 : int(2..5)]), - and([y_ExplicitVarSizeWithDummy[q11] < y_ExplicitVarSizeWithDummy[q11 + 1] \/ y_ExplicitVarSizeWithDummy[q11] = 6 - | q11 : int(1..3)]), - and([y_ExplicitVarSizeWithDummy[q12] = 6 -> y_ExplicitVarSizeWithDummy[q12 + 1] = 6 | q12 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q13] != 6) | q13 : int(1..4)]), - and([y_ExplicitVarSizeWithDummy[q16] != 6 -> y_Occurrence[y_ExplicitVarSizeWithDummy[q16]] | q16 : int(1..4)]), - and([y_Occurrence[q17] -> - or([y_ExplicitVarSizeWithDummy[q19] != 6 /\ y_ExplicitVarSizeWithDummy[q19] = q17 | q19 : int(1..4)]) - | q17 : int(2..5)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_1_1_3_3-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_1_1_3_3-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_1_3_3-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_1_1_3_3-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_1_1_3_3-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_1_3_3-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_1_1_3_3.eprime b/tests/exhaustive/basic/set09/expected/model_1_1_3_3.eprime deleted file mode 100644 index 9477b707c7..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_1_3_3.eprime +++ /dev/null @@ -1,38 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(2..5)] of bool -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_Occurrence: matrix indexed by [int(2..5)] of bool -find y_ExplicitVarSizeWithMarker_Marker: int(0..4) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_Occurrence, - y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values, y_Occurrence] -such that - and([x_Occurrence[i] /\ y_Occurrence[j] -> i + 2 = j | i : int(2..5), j : int(2..5)]), - 1 <= sum([toInt(x_Occurrence[q1]) | q1 : int(2..5)]), - 1 <= sum([toInt(y_Occurrence[q2]) | q2 : int(2..5)]), - and([q3 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q3] < x_ExplicitVarSizeWithMarker_Values[q3 + 1] - | q3 : int(1..3)]), - and([q4 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q4] = 2 | q4 : int(1..4)]), - 1 <= x_ExplicitVarSizeWithMarker_Marker, - and([q7 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q7]] - | q7 : int(1..4)]), - and([x_Occurrence[q8] -> - or([q10 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q10] = q8 - | q10 : int(1..4)]) - | q8 : int(2..5)]), - and([q11 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> - y_ExplicitVarSizeWithMarker_Values[q11] < y_ExplicitVarSizeWithMarker_Values[q11 + 1] - | q11 : int(1..3)]), - and([q12 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q12] = 2 | q12 : int(1..4)]), - 1 <= y_ExplicitVarSizeWithMarker_Marker, - and([q15 <= y_ExplicitVarSizeWithMarker_Marker -> y_Occurrence[y_ExplicitVarSizeWithMarker_Values[q15]] - | q15 : int(1..4)]), - and([y_Occurrence[q16] -> - or([q18 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[q18] = q16 - | q18 : int(1..4)]) - | q16 : int(2..5)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_1_1_3_4-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_1_1_3_4-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_1_3_4-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_1_1_3_4-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_1_1_3_4-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_1_3_4-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_1_1_3_4.eprime b/tests/exhaustive/basic/set09/expected/model_1_1_3_4.eprime deleted file mode 100644 index a002cc2f24..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_1_3_4.eprime +++ /dev/null @@ -1,39 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(2..5)] of bool -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_Occurrence: matrix indexed by [int(2..5)] of bool -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_Occurrence, - y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values, y_Occurrence] -such that - and([x_Occurrence[i] /\ y_Occurrence[j] -> i + 2 = j | i : int(2..5), j : int(2..5)]), - 1 <= sum([toInt(x_Occurrence[q1]) | q1 : int(2..5)]), - 1 <= sum([toInt(y_Occurrence[q2]) | q2 : int(2..5)]), - and([q3 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q3] < x_ExplicitVarSizeWithMarker_Values[q3 + 1] - | q3 : int(1..3)]), - and([q4 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q4] = 2 | q4 : int(1..4)]), - 1 <= x_ExplicitVarSizeWithMarker_Marker, - and([q7 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q7]] - | q7 : int(1..4)]), - and([x_Occurrence[q8] -> - or([q10 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q10] = q8 - | q10 : int(1..4)]) - | q8 : int(2..5)]), - and([y_ExplicitVarSizeWithFlags_Flags[q11 + 1] -> - y_ExplicitVarSizeWithFlags_Values[q11] < y_ExplicitVarSizeWithFlags_Values[q11 + 1] - | q11 : int(1..3)]), - and([y_ExplicitVarSizeWithFlags_Flags[q12] = false -> y_ExplicitVarSizeWithFlags_Values[q12] = 2 - | q12 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q13 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q13] | q13 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q14]) | q14 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q17] -> y_Occurrence[y_ExplicitVarSizeWithFlags_Values[q17]] - | q17 : int(1..4)]), - and([y_Occurrence[q18] -> - or([y_ExplicitVarSizeWithFlags_Flags[q20] /\ y_ExplicitVarSizeWithFlags_Values[q20] = q18 | q20 : int(1..4)]) - | q18 : int(2..5)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_1_1_4_1-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_1_1_4_1-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_1_4_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_1_1_4_1-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_1_1_4_1-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_1_4_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_1_1_4_1.eprime b/tests/exhaustive/basic/set09/expected/model_1_1_4_1.eprime deleted file mode 100644 index ef5ab46d55..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_1_4_1.eprime +++ /dev/null @@ -1,22 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(2..5)] of bool -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_Occurrence: matrix indexed by [int(2..5)] of bool -branching on [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_Occurrence, y_Occurrence] -such that - and([x_Occurrence[i] /\ y_Occurrence[j] -> i + 2 = j | i : int(2..5), j : int(2..5)]), - 1 <= sum([toInt(x_Occurrence[q1]) | q1 : int(2..5)]), - 1 <= sum([toInt(y_Occurrence[q2]) | q2 : int(2..5)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q3] < x_ExplicitVarSizeWithFlags_Values[q3 + 1] - | q3 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q4] = false -> x_ExplicitVarSizeWithFlags_Values[q4] = 2 | q4 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q5 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q5] | q5 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q6]) | q6 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q9] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q9]] | q9 : int(1..4)]), - and([x_Occurrence[q10] -> - or([x_ExplicitVarSizeWithFlags_Flags[q12] /\ x_ExplicitVarSizeWithFlags_Values[q12] = q10 | q12 : int(1..4)]) - | q10 : int(2..5)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_1_1_4_2-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_1_1_4_2-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_1_4_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_1_1_4_2-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_1_1_4_2-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_1_4_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_1_1_4_2.eprime b/tests/exhaustive/basic/set09/expected/model_1_1_4_2.eprime deleted file mode 100644 index 5f1fccfa5a..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_1_4_2.eprime +++ /dev/null @@ -1,33 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(2..5)] of bool -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_Occurrence: matrix indexed by [int(2..5)] of bool -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_Occurrence, y_ExplicitVarSizeWithDummy, - y_Occurrence] -such that - and([x_Occurrence[i] /\ y_Occurrence[j] -> i + 2 = j | i : int(2..5), j : int(2..5)]), - 1 <= sum([toInt(x_Occurrence[q1]) | q1 : int(2..5)]), - 1 <= sum([toInt(y_Occurrence[q2]) | q2 : int(2..5)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q3] < x_ExplicitVarSizeWithFlags_Values[q3 + 1] - | q3 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q4] = false -> x_ExplicitVarSizeWithFlags_Values[q4] = 2 | q4 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q5 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q5] | q5 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q6]) | q6 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q9] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q9]] | q9 : int(1..4)]), - and([x_Occurrence[q10] -> - or([x_ExplicitVarSizeWithFlags_Flags[q12] /\ x_ExplicitVarSizeWithFlags_Values[q12] = q10 | q12 : int(1..4)]) - | q10 : int(2..5)]), - and([y_ExplicitVarSizeWithDummy[q13] < y_ExplicitVarSizeWithDummy[q13 + 1] \/ y_ExplicitVarSizeWithDummy[q13] = 6 - | q13 : int(1..3)]), - and([y_ExplicitVarSizeWithDummy[q14] = 6 -> y_ExplicitVarSizeWithDummy[q14 + 1] = 6 | q14 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q15] != 6) | q15 : int(1..4)]), - and([y_ExplicitVarSizeWithDummy[q18] != 6 -> y_Occurrence[y_ExplicitVarSizeWithDummy[q18]] | q18 : int(1..4)]), - and([y_Occurrence[q19] -> - or([y_ExplicitVarSizeWithDummy[q21] != 6 /\ y_ExplicitVarSizeWithDummy[q21] = q19 | q21 : int(1..4)]) - | q19 : int(2..5)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_1_1_4_3-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_1_1_4_3-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_1_4_3-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_1_1_4_3-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_1_1_4_3-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_1_4_3-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_1_1_4_3.eprime b/tests/exhaustive/basic/set09/expected/model_1_1_4_3.eprime deleted file mode 100644 index e9925fe769..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_1_4_3.eprime +++ /dev/null @@ -1,37 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(2..5)] of bool -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_Occurrence: matrix indexed by [int(2..5)] of bool -find y_ExplicitVarSizeWithMarker_Marker: int(0..4) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_Occurrence, - y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values, y_Occurrence] -such that - and([x_Occurrence[i] /\ y_Occurrence[j] -> i + 2 = j | i : int(2..5), j : int(2..5)]), - 1 <= sum([toInt(x_Occurrence[q1]) | q1 : int(2..5)]), - 1 <= sum([toInt(y_Occurrence[q2]) | q2 : int(2..5)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q3] < x_ExplicitVarSizeWithFlags_Values[q3 + 1] - | q3 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q4] = false -> x_ExplicitVarSizeWithFlags_Values[q4] = 2 | q4 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q5 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q5] | q5 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q6]) | q6 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q9] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q9]] | q9 : int(1..4)]), - and([x_Occurrence[q10] -> - or([x_ExplicitVarSizeWithFlags_Flags[q12] /\ x_ExplicitVarSizeWithFlags_Values[q12] = q10 | q12 : int(1..4)]) - | q10 : int(2..5)]), - and([q13 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> - y_ExplicitVarSizeWithMarker_Values[q13] < y_ExplicitVarSizeWithMarker_Values[q13 + 1] - | q13 : int(1..3)]), - and([q14 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q14] = 2 | q14 : int(1..4)]), - 1 <= y_ExplicitVarSizeWithMarker_Marker, - and([q17 <= y_ExplicitVarSizeWithMarker_Marker -> y_Occurrence[y_ExplicitVarSizeWithMarker_Values[q17]] - | q17 : int(1..4)]), - and([y_Occurrence[q18] -> - or([q20 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[q20] = q18 - | q20 : int(1..4)]) - | q18 : int(2..5)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_1_1_4_4-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_1_1_4_4-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_1_4_4-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_1_1_4_4-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_1_1_4_4-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_1_4_4-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_1_1_4_4.eprime b/tests/exhaustive/basic/set09/expected/model_1_1_4_4.eprime deleted file mode 100644 index 83b55b09e8..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_1_4_4.eprime +++ /dev/null @@ -1,38 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(2..5)] of bool -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_Occurrence: matrix indexed by [int(2..5)] of bool -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_Occurrence, - y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values, y_Occurrence] -such that - and([x_Occurrence[i] /\ y_Occurrence[j] -> i + 2 = j | i : int(2..5), j : int(2..5)]), - 1 <= sum([toInt(x_Occurrence[q1]) | q1 : int(2..5)]), - 1 <= sum([toInt(y_Occurrence[q2]) | q2 : int(2..5)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q3] < x_ExplicitVarSizeWithFlags_Values[q3 + 1] - | q3 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q4] = false -> x_ExplicitVarSizeWithFlags_Values[q4] = 2 | q4 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q5 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q5] | q5 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q6]) | q6 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q9] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q9]] | q9 : int(1..4)]), - and([x_Occurrence[q10] -> - or([x_ExplicitVarSizeWithFlags_Flags[q12] /\ x_ExplicitVarSizeWithFlags_Values[q12] = q10 | q12 : int(1..4)]) - | q10 : int(2..5)]), - and([y_ExplicitVarSizeWithFlags_Flags[q13 + 1] -> - y_ExplicitVarSizeWithFlags_Values[q13] < y_ExplicitVarSizeWithFlags_Values[q13 + 1] - | q13 : int(1..3)]), - and([y_ExplicitVarSizeWithFlags_Flags[q14] = false -> y_ExplicitVarSizeWithFlags_Values[q14] = 2 - | q14 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q15 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q15] | q15 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q16]) | q16 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q19] -> y_Occurrence[y_ExplicitVarSizeWithFlags_Values[q19]] - | q19 : int(1..4)]), - and([y_Occurrence[q20] -> - or([y_ExplicitVarSizeWithFlags_Flags[q22] /\ y_ExplicitVarSizeWithFlags_Values[q22] = q20 | q22 : int(1..4)]) - | q20 : int(2..5)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_1_2_1_1-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_1_2_1_1-solution000001.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_2_1_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_1_2_1_1-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_1_2_1_1-solution000002.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_2_1_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_1_2_1_1.eprime b/tests/exhaustive/basic/set09/expected/model_1_2_1_1.eprime deleted file mode 100644 index a263bf4a81..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_2_1_1.eprime +++ /dev/null @@ -1,20 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(2..5)] of bool -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -find y_Occurrence: matrix indexed by [int(2..5)] of bool -branching on [x_Occurrence, y_Occurrence, y_ExplicitVarSizeWithDummy] -such that - and([x_Occurrence[i] /\ y_ExplicitVarSizeWithDummy[q12] != 6 -> i + 2 = y_ExplicitVarSizeWithDummy[q12] - | i : int(2..5), q12 : int(1..4)]), - 1 <= sum([toInt(x_Occurrence[q1]) | q1 : int(2..5)]), - and([y_ExplicitVarSizeWithDummy[q2] < y_ExplicitVarSizeWithDummy[q2 + 1] \/ y_ExplicitVarSizeWithDummy[q2] = 6 - | q2 : int(1..3)]), - and([y_ExplicitVarSizeWithDummy[q3] = 6 -> y_ExplicitVarSizeWithDummy[q3 + 1] = 6 | q3 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q4] != 6) | q4 : int(1..4)]), - 1 <= sum([toInt(y_Occurrence[q6]) | q6 : int(2..5)]), - and([y_Occurrence[q7] -> - or([y_ExplicitVarSizeWithDummy[q9] != 6 /\ y_ExplicitVarSizeWithDummy[q9] = q7 | q9 : int(1..4)]) - | q7 : int(2..5)]), - and([y_ExplicitVarSizeWithDummy[q11] != 6 -> y_Occurrence[y_ExplicitVarSizeWithDummy[q11]] | q11 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_1_2_1_2-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_1_2_1_2-solution000001.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_2_1_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_1_2_1_2-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_1_2_1_2-solution000002.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_2_1_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_1_2_1_2.eprime b/tests/exhaustive/basic/set09/expected/model_1_2_1_2.eprime deleted file mode 100644 index 970b65361f..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_2_1_2.eprime +++ /dev/null @@ -1,14 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(2..5)] of bool -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -branching on [x_Occurrence, y_ExplicitVarSizeWithDummy] -such that - and([x_Occurrence[i] /\ y_ExplicitVarSizeWithDummy[q6] != 6 -> i + 2 = y_ExplicitVarSizeWithDummy[q6] - | i : int(2..5), q6 : int(1..4)]), - 1 <= sum([toInt(x_Occurrence[q1]) | q1 : int(2..5)]), - and([y_ExplicitVarSizeWithDummy[q2] < y_ExplicitVarSizeWithDummy[q2 + 1] \/ y_ExplicitVarSizeWithDummy[q2] = 6 - | q2 : int(1..3)]), - and([y_ExplicitVarSizeWithDummy[q3] = 6 -> y_ExplicitVarSizeWithDummy[q3 + 1] = 6 | q3 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q4] != 6) | q4 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_1_2_1_3-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_1_2_1_3-solution000001.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_2_1_3-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_1_2_1_3-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_1_2_1_3-solution000002.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_2_1_3-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_1_2_1_3.eprime b/tests/exhaustive/basic/set09/expected/model_1_2_1_3.eprime deleted file mode 100644 index 34f57c451d..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_2_1_3.eprime +++ /dev/null @@ -1,32 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(2..5)] of bool -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -find y_ExplicitVarSizeWithMarker_Marker: int(0..4) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -branching on - [x_Occurrence, y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithDummy] -such that - and([x_Occurrence[i] /\ y_ExplicitVarSizeWithDummy[q17] != 6 -> i + 2 = y_ExplicitVarSizeWithDummy[q17] - | i : int(2..5), q17 : int(1..4)]), - 1 <= sum([toInt(x_Occurrence[q1]) | q1 : int(2..5)]), - and([y_ExplicitVarSizeWithDummy[q2] < y_ExplicitVarSizeWithDummy[q2 + 1] \/ y_ExplicitVarSizeWithDummy[q2] = 6 - | q2 : int(1..3)]), - and([y_ExplicitVarSizeWithDummy[q3] = 6 -> y_ExplicitVarSizeWithDummy[q3 + 1] = 6 | q3 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q4] != 6) | q4 : int(1..4)]), - and([q6 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> - y_ExplicitVarSizeWithMarker_Values[q6] < y_ExplicitVarSizeWithMarker_Values[q6 + 1] - | q6 : int(1..3)]), - and([q7 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q7] = 2 | q7 : int(1..4)]), - 1 <= y_ExplicitVarSizeWithMarker_Marker, - and([q10 <= y_ExplicitVarSizeWithMarker_Marker -> - or([y_ExplicitVarSizeWithDummy[q12] != 6 /\ - y_ExplicitVarSizeWithDummy[q12] = y_ExplicitVarSizeWithMarker_Values[q10] - | q12 : int(1..4)]) - | q10 : int(1..4)]), - and([y_ExplicitVarSizeWithDummy[q14] != 6 -> - or([q16 <= y_ExplicitVarSizeWithMarker_Marker /\ - y_ExplicitVarSizeWithMarker_Values[q16] = y_ExplicitVarSizeWithDummy[q14] - | q16 : int(1..4)]) - | q14 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_1_2_1_4-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_1_2_1_4-solution000001.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_2_1_4-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_1_2_1_4-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_1_2_1_4-solution000002.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_2_1_4-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_1_2_1_4.eprime b/tests/exhaustive/basic/set09/expected/model_1_2_1_4.eprime deleted file mode 100644 index e89acaaa36..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_2_1_4.eprime +++ /dev/null @@ -1,33 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(2..5)] of bool -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -branching on - [x_Occurrence, y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithDummy] -such that - and([x_Occurrence[i] /\ y_ExplicitVarSizeWithDummy[q19] != 6 -> i + 2 = y_ExplicitVarSizeWithDummy[q19] - | i : int(2..5), q19 : int(1..4)]), - 1 <= sum([toInt(x_Occurrence[q1]) | q1 : int(2..5)]), - and([y_ExplicitVarSizeWithDummy[q2] < y_ExplicitVarSizeWithDummy[q2 + 1] \/ y_ExplicitVarSizeWithDummy[q2] = 6 - | q2 : int(1..3)]), - and([y_ExplicitVarSizeWithDummy[q3] = 6 -> y_ExplicitVarSizeWithDummy[q3 + 1] = 6 | q3 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q4] != 6) | q4 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> - y_ExplicitVarSizeWithFlags_Values[q6] < y_ExplicitVarSizeWithFlags_Values[q6 + 1] - | q6 : int(1..3)]), - and([y_ExplicitVarSizeWithFlags_Flags[q7] = false -> y_ExplicitVarSizeWithFlags_Values[q7] = 2 | q7 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q8 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q8] | q8 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q9]) | q9 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q12] -> - or([y_ExplicitVarSizeWithDummy[q14] != 6 /\ - y_ExplicitVarSizeWithDummy[q14] = y_ExplicitVarSizeWithFlags_Values[q12] - | q14 : int(1..4)]) - | q12 : int(1..4)]), - and([y_ExplicitVarSizeWithDummy[q16] != 6 -> - or([y_ExplicitVarSizeWithFlags_Flags[q18] /\ - y_ExplicitVarSizeWithFlags_Values[q18] = y_ExplicitVarSizeWithDummy[q16] - | q18 : int(1..4)]) - | q16 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_1_2_2_1-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_1_2_2_1-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_2_2_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_1_2_2_1-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_1_2_2_1-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_2_2_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_1_2_2_1.eprime b/tests/exhaustive/basic/set09/expected/model_1_2_2_1.eprime deleted file mode 100644 index b50b8217a7..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_2_2_1.eprime +++ /dev/null @@ -1,29 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(2..5)] of bool -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -find y_Occurrence: matrix indexed by [int(2..5)] of bool -branching on [x_ExplicitVarSizeWithDummy, x_Occurrence, y_Occurrence, y_ExplicitVarSizeWithDummy] -such that - and([x_Occurrence[i] /\ y_ExplicitVarSizeWithDummy[q21] != 6 -> i + 2 = y_ExplicitVarSizeWithDummy[q21] - | i : int(2..5), q21 : int(1..4)]), - 1 <= sum([toInt(x_Occurrence[q1]) | q1 : int(2..5)]), - and([y_ExplicitVarSizeWithDummy[q2] < y_ExplicitVarSizeWithDummy[q2 + 1] \/ y_ExplicitVarSizeWithDummy[q2] = 6 - | q2 : int(1..3)]), - and([y_ExplicitVarSizeWithDummy[q3] = 6 -> y_ExplicitVarSizeWithDummy[q3 + 1] = 6 | q3 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q4] != 6) | q4 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q6] < x_ExplicitVarSizeWithDummy[q6 + 1] \/ x_ExplicitVarSizeWithDummy[q6] = 6 - | q6 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q7] = 6 -> x_ExplicitVarSizeWithDummy[q7 + 1] = 6 | q7 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q8] != 6) | q8 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q11] != 6 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q11]] | q11 : int(1..4)]), - and([x_Occurrence[q12] -> - or([x_ExplicitVarSizeWithDummy[q14] != 6 /\ x_ExplicitVarSizeWithDummy[q14] = q12 | q14 : int(1..4)]) - | q12 : int(2..5)]), - 1 <= sum([toInt(y_Occurrence[q15]) | q15 : int(2..5)]), - and([y_Occurrence[q16] -> - or([y_ExplicitVarSizeWithDummy[q18] != 6 /\ y_ExplicitVarSizeWithDummy[q18] = q16 | q18 : int(1..4)]) - | q16 : int(2..5)]), - and([y_ExplicitVarSizeWithDummy[q20] != 6 -> y_Occurrence[y_ExplicitVarSizeWithDummy[q20]] | q20 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_1_2_2_2-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_1_2_2_2-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_2_2_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_1_2_2_2-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_1_2_2_2-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_2_2_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_1_2_2_2.eprime b/tests/exhaustive/basic/set09/expected/model_1_2_2_2.eprime deleted file mode 100644 index 97ccb1e791..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_2_2_2.eprime +++ /dev/null @@ -1,23 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(2..5)] of bool -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -branching on [x_ExplicitVarSizeWithDummy, x_Occurrence, y_ExplicitVarSizeWithDummy] -such that - and([x_Occurrence[i] /\ y_ExplicitVarSizeWithDummy[q15] != 6 -> i + 2 = y_ExplicitVarSizeWithDummy[q15] - | i : int(2..5), q15 : int(1..4)]), - 1 <= sum([toInt(x_Occurrence[q1]) | q1 : int(2..5)]), - and([y_ExplicitVarSizeWithDummy[q2] < y_ExplicitVarSizeWithDummy[q2 + 1] \/ y_ExplicitVarSizeWithDummy[q2] = 6 - | q2 : int(1..3)]), - and([y_ExplicitVarSizeWithDummy[q3] = 6 -> y_ExplicitVarSizeWithDummy[q3 + 1] = 6 | q3 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q4] != 6) | q4 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q6] < x_ExplicitVarSizeWithDummy[q6 + 1] \/ x_ExplicitVarSizeWithDummy[q6] = 6 - | q6 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q7] = 6 -> x_ExplicitVarSizeWithDummy[q7 + 1] = 6 | q7 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q8] != 6) | q8 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q11] != 6 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q11]] | q11 : int(1..4)]), - and([x_Occurrence[q12] -> - or([x_ExplicitVarSizeWithDummy[q14] != 6 /\ x_ExplicitVarSizeWithDummy[q14] = q12 | q14 : int(1..4)]) - | q12 : int(2..5)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_1_2_2_3-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_1_2_2_3-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_2_2_3-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_1_2_2_3-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_1_2_2_3-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_2_2_3-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_1_2_2_3.eprime b/tests/exhaustive/basic/set09/expected/model_1_2_2_3.eprime deleted file mode 100644 index 834e686023..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_2_2_3.eprime +++ /dev/null @@ -1,42 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(2..5)] of bool -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -find y_ExplicitVarSizeWithMarker_Marker: int(0..4) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -branching on - [x_ExplicitVarSizeWithDummy, x_Occurrence, y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values, - y_ExplicitVarSizeWithDummy] -such that - and([x_Occurrence[i] /\ y_ExplicitVarSizeWithDummy[q26] != 6 -> i + 2 = y_ExplicitVarSizeWithDummy[q26] - | i : int(2..5), q26 : int(1..4)]), - 1 <= sum([toInt(x_Occurrence[q1]) | q1 : int(2..5)]), - and([y_ExplicitVarSizeWithDummy[q2] < y_ExplicitVarSizeWithDummy[q2 + 1] \/ y_ExplicitVarSizeWithDummy[q2] = 6 - | q2 : int(1..3)]), - and([y_ExplicitVarSizeWithDummy[q3] = 6 -> y_ExplicitVarSizeWithDummy[q3 + 1] = 6 | q3 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q4] != 6) | q4 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q6] < x_ExplicitVarSizeWithDummy[q6 + 1] \/ x_ExplicitVarSizeWithDummy[q6] = 6 - | q6 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q7] = 6 -> x_ExplicitVarSizeWithDummy[q7 + 1] = 6 | q7 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q8] != 6) | q8 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q11] != 6 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q11]] | q11 : int(1..4)]), - and([x_Occurrence[q12] -> - or([x_ExplicitVarSizeWithDummy[q14] != 6 /\ x_ExplicitVarSizeWithDummy[q14] = q12 | q14 : int(1..4)]) - | q12 : int(2..5)]), - and([q15 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> - y_ExplicitVarSizeWithMarker_Values[q15] < y_ExplicitVarSizeWithMarker_Values[q15 + 1] - | q15 : int(1..3)]), - and([q16 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q16] = 2 | q16 : int(1..4)]), - 1 <= y_ExplicitVarSizeWithMarker_Marker, - and([q19 <= y_ExplicitVarSizeWithMarker_Marker -> - or([y_ExplicitVarSizeWithDummy[q21] != 6 /\ - y_ExplicitVarSizeWithDummy[q21] = y_ExplicitVarSizeWithMarker_Values[q19] - | q21 : int(1..4)]) - | q19 : int(1..4)]), - and([y_ExplicitVarSizeWithDummy[q23] != 6 -> - or([q25 <= y_ExplicitVarSizeWithMarker_Marker /\ - y_ExplicitVarSizeWithMarker_Values[q25] = y_ExplicitVarSizeWithDummy[q23] - | q25 : int(1..4)]) - | q23 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_1_2_2_4-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_1_2_2_4-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_2_2_4-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_1_2_2_4-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_1_2_2_4-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_2_2_4-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_1_2_2_4.eprime b/tests/exhaustive/basic/set09/expected/model_1_2_2_4.eprime deleted file mode 100644 index 7f9c9565ff..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_2_2_4.eprime +++ /dev/null @@ -1,44 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(2..5)] of bool -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -branching on - [x_ExplicitVarSizeWithDummy, x_Occurrence, y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values, - y_ExplicitVarSizeWithDummy] -such that - and([x_Occurrence[i] /\ y_ExplicitVarSizeWithDummy[q28] != 6 -> i + 2 = y_ExplicitVarSizeWithDummy[q28] - | i : int(2..5), q28 : int(1..4)]), - 1 <= sum([toInt(x_Occurrence[q1]) | q1 : int(2..5)]), - and([y_ExplicitVarSizeWithDummy[q2] < y_ExplicitVarSizeWithDummy[q2 + 1] \/ y_ExplicitVarSizeWithDummy[q2] = 6 - | q2 : int(1..3)]), - and([y_ExplicitVarSizeWithDummy[q3] = 6 -> y_ExplicitVarSizeWithDummy[q3 + 1] = 6 | q3 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q4] != 6) | q4 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q6] < x_ExplicitVarSizeWithDummy[q6 + 1] \/ x_ExplicitVarSizeWithDummy[q6] = 6 - | q6 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q7] = 6 -> x_ExplicitVarSizeWithDummy[q7 + 1] = 6 | q7 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q8] != 6) | q8 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q11] != 6 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q11]] | q11 : int(1..4)]), - and([x_Occurrence[q12] -> - or([x_ExplicitVarSizeWithDummy[q14] != 6 /\ x_ExplicitVarSizeWithDummy[q14] = q12 | q14 : int(1..4)]) - | q12 : int(2..5)]), - and([y_ExplicitVarSizeWithFlags_Flags[q15 + 1] -> - y_ExplicitVarSizeWithFlags_Values[q15] < y_ExplicitVarSizeWithFlags_Values[q15 + 1] - | q15 : int(1..3)]), - and([y_ExplicitVarSizeWithFlags_Flags[q16] = false -> y_ExplicitVarSizeWithFlags_Values[q16] = 2 - | q16 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q17 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q17] | q17 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q18]) | q18 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q21] -> - or([y_ExplicitVarSizeWithDummy[q23] != 6 /\ - y_ExplicitVarSizeWithDummy[q23] = y_ExplicitVarSizeWithFlags_Values[q21] - | q23 : int(1..4)]) - | q21 : int(1..4)]), - and([y_ExplicitVarSizeWithDummy[q25] != 6 -> - or([y_ExplicitVarSizeWithFlags_Flags[q27] /\ - y_ExplicitVarSizeWithFlags_Values[q27] = y_ExplicitVarSizeWithDummy[q25] - | q27 : int(1..4)]) - | q25 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_1_2_3_1-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_1_2_3_1-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_2_3_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_1_2_3_1-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_1_2_3_1-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_2_3_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_1_2_3_1.eprime b/tests/exhaustive/basic/set09/expected/model_1_2_3_1.eprime deleted file mode 100644 index a173ae9198..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_2_3_1.eprime +++ /dev/null @@ -1,35 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(2..5)] of bool -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -find y_Occurrence: matrix indexed by [int(2..5)] of bool -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_Occurrence, y_Occurrence, - y_ExplicitVarSizeWithDummy] -such that - and([x_Occurrence[i] /\ y_ExplicitVarSizeWithDummy[q20] != 6 -> i + 2 = y_ExplicitVarSizeWithDummy[q20] - | i : int(2..5), q20 : int(1..4)]), - 1 <= sum([toInt(x_Occurrence[q1]) | q1 : int(2..5)]), - and([y_ExplicitVarSizeWithDummy[q2] < y_ExplicitVarSizeWithDummy[q2 + 1] \/ y_ExplicitVarSizeWithDummy[q2] = 6 - | q2 : int(1..3)]), - and([y_ExplicitVarSizeWithDummy[q3] = 6 -> y_ExplicitVarSizeWithDummy[q3 + 1] = 6 | q3 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q4] != 6) | q4 : int(1..4)]), - and([q6 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q6] < x_ExplicitVarSizeWithMarker_Values[q6 + 1] - | q6 : int(1..3)]), - and([q7 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q7] = 2 | q7 : int(1..4)]), - 1 <= x_ExplicitVarSizeWithMarker_Marker, - and([q10 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q10]] - | q10 : int(1..4)]), - and([x_Occurrence[q11] -> - or([q13 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q13] = q11 - | q13 : int(1..4)]) - | q11 : int(2..5)]), - 1 <= sum([toInt(y_Occurrence[q14]) | q14 : int(2..5)]), - and([y_Occurrence[q15] -> - or([y_ExplicitVarSizeWithDummy[q17] != 6 /\ y_ExplicitVarSizeWithDummy[q17] = q15 | q17 : int(1..4)]) - | q15 : int(2..5)]), - and([y_ExplicitVarSizeWithDummy[q19] != 6 -> y_Occurrence[y_ExplicitVarSizeWithDummy[q19]] | q19 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_1_2_3_2-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_1_2_3_2-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_2_3_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_1_2_3_2-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_1_2_3_2-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_2_3_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_1_2_3_2.eprime b/tests/exhaustive/basic/set09/expected/model_1_2_3_2.eprime deleted file mode 100644 index 85a3d62f8d..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_2_3_2.eprime +++ /dev/null @@ -1,28 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(2..5)] of bool -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_Occurrence, y_ExplicitVarSizeWithDummy] -such that - and([x_Occurrence[i] /\ y_ExplicitVarSizeWithDummy[q14] != 6 -> i + 2 = y_ExplicitVarSizeWithDummy[q14] - | i : int(2..5), q14 : int(1..4)]), - 1 <= sum([toInt(x_Occurrence[q1]) | q1 : int(2..5)]), - and([y_ExplicitVarSizeWithDummy[q2] < y_ExplicitVarSizeWithDummy[q2 + 1] \/ y_ExplicitVarSizeWithDummy[q2] = 6 - | q2 : int(1..3)]), - and([y_ExplicitVarSizeWithDummy[q3] = 6 -> y_ExplicitVarSizeWithDummy[q3 + 1] = 6 | q3 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q4] != 6) | q4 : int(1..4)]), - and([q6 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q6] < x_ExplicitVarSizeWithMarker_Values[q6 + 1] - | q6 : int(1..3)]), - and([q7 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q7] = 2 | q7 : int(1..4)]), - 1 <= x_ExplicitVarSizeWithMarker_Marker, - and([q10 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q10]] - | q10 : int(1..4)]), - and([x_Occurrence[q11] -> - or([q13 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q13] = q11 - | q13 : int(1..4)]) - | q11 : int(2..5)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_1_2_3_3-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_1_2_3_3-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_2_3_3-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_1_2_3_3-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_1_2_3_3-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_2_3_3-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_1_2_3_3.eprime b/tests/exhaustive/basic/set09/expected/model_1_2_3_3.eprime deleted file mode 100644 index 7e2bed2d00..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_2_3_3.eprime +++ /dev/null @@ -1,46 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(2..5)] of bool -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -find y_ExplicitVarSizeWithMarker_Marker: int(0..4) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_Occurrence, - y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithDummy] -such that - and([x_Occurrence[i] /\ y_ExplicitVarSizeWithDummy[q25] != 6 -> i + 2 = y_ExplicitVarSizeWithDummy[q25] - | i : int(2..5), q25 : int(1..4)]), - 1 <= sum([toInt(x_Occurrence[q1]) | q1 : int(2..5)]), - and([y_ExplicitVarSizeWithDummy[q2] < y_ExplicitVarSizeWithDummy[q2 + 1] \/ y_ExplicitVarSizeWithDummy[q2] = 6 - | q2 : int(1..3)]), - and([y_ExplicitVarSizeWithDummy[q3] = 6 -> y_ExplicitVarSizeWithDummy[q3 + 1] = 6 | q3 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q4] != 6) | q4 : int(1..4)]), - and([q6 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q6] < x_ExplicitVarSizeWithMarker_Values[q6 + 1] - | q6 : int(1..3)]), - and([q7 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q7] = 2 | q7 : int(1..4)]), - 1 <= x_ExplicitVarSizeWithMarker_Marker, - and([q10 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q10]] - | q10 : int(1..4)]), - and([x_Occurrence[q11] -> - or([q13 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q13] = q11 - | q13 : int(1..4)]) - | q11 : int(2..5)]), - and([q14 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> - y_ExplicitVarSizeWithMarker_Values[q14] < y_ExplicitVarSizeWithMarker_Values[q14 + 1] - | q14 : int(1..3)]), - and([q15 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q15] = 2 | q15 : int(1..4)]), - 1 <= y_ExplicitVarSizeWithMarker_Marker, - and([q18 <= y_ExplicitVarSizeWithMarker_Marker -> - or([y_ExplicitVarSizeWithDummy[q20] != 6 /\ - y_ExplicitVarSizeWithDummy[q20] = y_ExplicitVarSizeWithMarker_Values[q18] - | q20 : int(1..4)]) - | q18 : int(1..4)]), - and([y_ExplicitVarSizeWithDummy[q22] != 6 -> - or([q24 <= y_ExplicitVarSizeWithMarker_Marker /\ - y_ExplicitVarSizeWithMarker_Values[q24] = y_ExplicitVarSizeWithDummy[q22] - | q24 : int(1..4)]) - | q22 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_1_2_3_4-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_1_2_3_4-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_2_3_4-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_1_2_3_4-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_1_2_3_4-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_2_3_4-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_1_2_3_4.eprime b/tests/exhaustive/basic/set09/expected/model_1_2_3_4.eprime deleted file mode 100644 index fac749f4d5..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_2_3_4.eprime +++ /dev/null @@ -1,48 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(2..5)] of bool -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_Occurrence, - y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithDummy] -such that - and([x_Occurrence[i] /\ y_ExplicitVarSizeWithDummy[q27] != 6 -> i + 2 = y_ExplicitVarSizeWithDummy[q27] - | i : int(2..5), q27 : int(1..4)]), - 1 <= sum([toInt(x_Occurrence[q1]) | q1 : int(2..5)]), - and([y_ExplicitVarSizeWithDummy[q2] < y_ExplicitVarSizeWithDummy[q2 + 1] \/ y_ExplicitVarSizeWithDummy[q2] = 6 - | q2 : int(1..3)]), - and([y_ExplicitVarSizeWithDummy[q3] = 6 -> y_ExplicitVarSizeWithDummy[q3 + 1] = 6 | q3 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q4] != 6) | q4 : int(1..4)]), - and([q6 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q6] < x_ExplicitVarSizeWithMarker_Values[q6 + 1] - | q6 : int(1..3)]), - and([q7 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q7] = 2 | q7 : int(1..4)]), - 1 <= x_ExplicitVarSizeWithMarker_Marker, - and([q10 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q10]] - | q10 : int(1..4)]), - and([x_Occurrence[q11] -> - or([q13 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q13] = q11 - | q13 : int(1..4)]) - | q11 : int(2..5)]), - and([y_ExplicitVarSizeWithFlags_Flags[q14 + 1] -> - y_ExplicitVarSizeWithFlags_Values[q14] < y_ExplicitVarSizeWithFlags_Values[q14 + 1] - | q14 : int(1..3)]), - and([y_ExplicitVarSizeWithFlags_Flags[q15] = false -> y_ExplicitVarSizeWithFlags_Values[q15] = 2 - | q15 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q16 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q16] | q16 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q17]) | q17 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q20] -> - or([y_ExplicitVarSizeWithDummy[q22] != 6 /\ - y_ExplicitVarSizeWithDummy[q22] = y_ExplicitVarSizeWithFlags_Values[q20] - | q22 : int(1..4)]) - | q20 : int(1..4)]), - and([y_ExplicitVarSizeWithDummy[q24] != 6 -> - or([y_ExplicitVarSizeWithFlags_Flags[q26] /\ - y_ExplicitVarSizeWithFlags_Values[q26] = y_ExplicitVarSizeWithDummy[q24] - | q26 : int(1..4)]) - | q24 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_1_2_4_1-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_1_2_4_1-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_2_4_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_1_2_4_1-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_1_2_4_1-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_2_4_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_1_2_4_1.eprime b/tests/exhaustive/basic/set09/expected/model_1_2_4_1.eprime deleted file mode 100644 index eec7a2f559..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_2_4_1.eprime +++ /dev/null @@ -1,35 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(2..5)] of bool -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -find y_Occurrence: matrix indexed by [int(2..5)] of bool -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_Occurrence, y_Occurrence, - y_ExplicitVarSizeWithDummy] -such that - and([x_Occurrence[i] /\ y_ExplicitVarSizeWithDummy[q22] != 6 -> i + 2 = y_ExplicitVarSizeWithDummy[q22] - | i : int(2..5), q22 : int(1..4)]), - 1 <= sum([toInt(x_Occurrence[q1]) | q1 : int(2..5)]), - and([y_ExplicitVarSizeWithDummy[q2] < y_ExplicitVarSizeWithDummy[q2 + 1] \/ y_ExplicitVarSizeWithDummy[q2] = 6 - | q2 : int(1..3)]), - and([y_ExplicitVarSizeWithDummy[q3] = 6 -> y_ExplicitVarSizeWithDummy[q3 + 1] = 6 | q3 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q4] != 6) | q4 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q6] < x_ExplicitVarSizeWithFlags_Values[q6 + 1] - | q6 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q7] = false -> x_ExplicitVarSizeWithFlags_Values[q7] = 2 | q7 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q8 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q8] | q8 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q9]) | q9 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q12] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q12]] - | q12 : int(1..4)]), - and([x_Occurrence[q13] -> - or([x_ExplicitVarSizeWithFlags_Flags[q15] /\ x_ExplicitVarSizeWithFlags_Values[q15] = q13 | q15 : int(1..4)]) - | q13 : int(2..5)]), - 1 <= sum([toInt(y_Occurrence[q16]) | q16 : int(2..5)]), - and([y_Occurrence[q17] -> - or([y_ExplicitVarSizeWithDummy[q19] != 6 /\ y_ExplicitVarSizeWithDummy[q19] = q17 | q19 : int(1..4)]) - | q17 : int(2..5)]), - and([y_ExplicitVarSizeWithDummy[q21] != 6 -> y_Occurrence[y_ExplicitVarSizeWithDummy[q21]] | q21 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_1_2_4_2-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_1_2_4_2-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_2_4_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_1_2_4_2-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_1_2_4_2-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_2_4_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_1_2_4_2.eprime b/tests/exhaustive/basic/set09/expected/model_1_2_4_2.eprime deleted file mode 100644 index fbd69fb422..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_2_4_2.eprime +++ /dev/null @@ -1,28 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(2..5)] of bool -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_Occurrence, y_ExplicitVarSizeWithDummy] -such that - and([x_Occurrence[i] /\ y_ExplicitVarSizeWithDummy[q16] != 6 -> i + 2 = y_ExplicitVarSizeWithDummy[q16] - | i : int(2..5), q16 : int(1..4)]), - 1 <= sum([toInt(x_Occurrence[q1]) | q1 : int(2..5)]), - and([y_ExplicitVarSizeWithDummy[q2] < y_ExplicitVarSizeWithDummy[q2 + 1] \/ y_ExplicitVarSizeWithDummy[q2] = 6 - | q2 : int(1..3)]), - and([y_ExplicitVarSizeWithDummy[q3] = 6 -> y_ExplicitVarSizeWithDummy[q3 + 1] = 6 | q3 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q4] != 6) | q4 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q6] < x_ExplicitVarSizeWithFlags_Values[q6 + 1] - | q6 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q7] = false -> x_ExplicitVarSizeWithFlags_Values[q7] = 2 | q7 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q8 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q8] | q8 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q9]) | q9 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q12] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q12]] - | q12 : int(1..4)]), - and([x_Occurrence[q13] -> - or([x_ExplicitVarSizeWithFlags_Flags[q15] /\ x_ExplicitVarSizeWithFlags_Values[q15] = q13 | q15 : int(1..4)]) - | q13 : int(2..5)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_1_2_4_3-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_1_2_4_3-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_2_4_3-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_1_2_4_3-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_1_2_4_3-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_2_4_3-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_1_2_4_3.eprime b/tests/exhaustive/basic/set09/expected/model_1_2_4_3.eprime deleted file mode 100644 index db9fd6336e..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_2_4_3.eprime +++ /dev/null @@ -1,46 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(2..5)] of bool -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -find y_ExplicitVarSizeWithMarker_Marker: int(0..4) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_Occurrence, - y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithDummy] -such that - and([x_Occurrence[i] /\ y_ExplicitVarSizeWithDummy[q27] != 6 -> i + 2 = y_ExplicitVarSizeWithDummy[q27] - | i : int(2..5), q27 : int(1..4)]), - 1 <= sum([toInt(x_Occurrence[q1]) | q1 : int(2..5)]), - and([y_ExplicitVarSizeWithDummy[q2] < y_ExplicitVarSizeWithDummy[q2 + 1] \/ y_ExplicitVarSizeWithDummy[q2] = 6 - | q2 : int(1..3)]), - and([y_ExplicitVarSizeWithDummy[q3] = 6 -> y_ExplicitVarSizeWithDummy[q3 + 1] = 6 | q3 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q4] != 6) | q4 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q6] < x_ExplicitVarSizeWithFlags_Values[q6 + 1] - | q6 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q7] = false -> x_ExplicitVarSizeWithFlags_Values[q7] = 2 | q7 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q8 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q8] | q8 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q9]) | q9 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q12] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q12]] - | q12 : int(1..4)]), - and([x_Occurrence[q13] -> - or([x_ExplicitVarSizeWithFlags_Flags[q15] /\ x_ExplicitVarSizeWithFlags_Values[q15] = q13 | q15 : int(1..4)]) - | q13 : int(2..5)]), - and([q16 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> - y_ExplicitVarSizeWithMarker_Values[q16] < y_ExplicitVarSizeWithMarker_Values[q16 + 1] - | q16 : int(1..3)]), - and([q17 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q17] = 2 | q17 : int(1..4)]), - 1 <= y_ExplicitVarSizeWithMarker_Marker, - and([q20 <= y_ExplicitVarSizeWithMarker_Marker -> - or([y_ExplicitVarSizeWithDummy[q22] != 6 /\ - y_ExplicitVarSizeWithDummy[q22] = y_ExplicitVarSizeWithMarker_Values[q20] - | q22 : int(1..4)]) - | q20 : int(1..4)]), - and([y_ExplicitVarSizeWithDummy[q24] != 6 -> - or([q26 <= y_ExplicitVarSizeWithMarker_Marker /\ - y_ExplicitVarSizeWithMarker_Values[q26] = y_ExplicitVarSizeWithDummy[q24] - | q26 : int(1..4)]) - | q24 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_1_2_4_4-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_1_2_4_4-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_2_4_4-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_1_2_4_4-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_1_2_4_4-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_2_4_4-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_1_2_4_4.eprime b/tests/exhaustive/basic/set09/expected/model_1_2_4_4.eprime deleted file mode 100644 index f82060de74..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_2_4_4.eprime +++ /dev/null @@ -1,48 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(2..5)] of bool -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_Occurrence, - y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithDummy] -such that - and([x_Occurrence[i] /\ y_ExplicitVarSizeWithDummy[q29] != 6 -> i + 2 = y_ExplicitVarSizeWithDummy[q29] - | i : int(2..5), q29 : int(1..4)]), - 1 <= sum([toInt(x_Occurrence[q1]) | q1 : int(2..5)]), - and([y_ExplicitVarSizeWithDummy[q2] < y_ExplicitVarSizeWithDummy[q2 + 1] \/ y_ExplicitVarSizeWithDummy[q2] = 6 - | q2 : int(1..3)]), - and([y_ExplicitVarSizeWithDummy[q3] = 6 -> y_ExplicitVarSizeWithDummy[q3 + 1] = 6 | q3 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q4] != 6) | q4 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q6] < x_ExplicitVarSizeWithFlags_Values[q6 + 1] - | q6 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q7] = false -> x_ExplicitVarSizeWithFlags_Values[q7] = 2 | q7 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q8 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q8] | q8 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q9]) | q9 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q12] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q12]] - | q12 : int(1..4)]), - and([x_Occurrence[q13] -> - or([x_ExplicitVarSizeWithFlags_Flags[q15] /\ x_ExplicitVarSizeWithFlags_Values[q15] = q13 | q15 : int(1..4)]) - | q13 : int(2..5)]), - and([y_ExplicitVarSizeWithFlags_Flags[q16 + 1] -> - y_ExplicitVarSizeWithFlags_Values[q16] < y_ExplicitVarSizeWithFlags_Values[q16 + 1] - | q16 : int(1..3)]), - and([y_ExplicitVarSizeWithFlags_Flags[q17] = false -> y_ExplicitVarSizeWithFlags_Values[q17] = 2 - | q17 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q18 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q18] | q18 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q19]) | q19 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q22] -> - or([y_ExplicitVarSizeWithDummy[q24] != 6 /\ - y_ExplicitVarSizeWithDummy[q24] = y_ExplicitVarSizeWithFlags_Values[q22] - | q24 : int(1..4)]) - | q22 : int(1..4)]), - and([y_ExplicitVarSizeWithDummy[q26] != 6 -> - or([y_ExplicitVarSizeWithFlags_Flags[q28] /\ - y_ExplicitVarSizeWithFlags_Values[q28] = y_ExplicitVarSizeWithDummy[q26] - | q28 : int(1..4)]) - | q26 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_1_3_1_1-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_1_3_1_1-solution000001.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_3_1_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_1_3_1_1-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_1_3_1_1-solution000002.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_3_1_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_1_3_1_1.eprime b/tests/exhaustive/basic/set09/expected/model_1_3_1_1.eprime deleted file mode 100644 index 5aa5be2149..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_3_1_1.eprime +++ /dev/null @@ -1,23 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(2..5)] of bool -find y_ExplicitVarSizeWithMarker_Marker: int(0..4) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_Occurrence: matrix indexed by [int(2..5)] of bool -branching on [x_Occurrence, y_Occurrence, y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values] -such that - and([x_Occurrence[i] /\ q11 <= y_ExplicitVarSizeWithMarker_Marker -> i + 2 = y_ExplicitVarSizeWithMarker_Values[q11] - | i : int(2..5), q11 : int(1..4)]), - 1 <= sum([toInt(x_Occurrence[q1]) | q1 : int(2..5)]), - and([q2 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> - y_ExplicitVarSizeWithMarker_Values[q2] < y_ExplicitVarSizeWithMarker_Values[q2 + 1] - | q2 : int(1..3)]), - and([q3 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q3] = 2 | q3 : int(1..4)]), - 1 <= y_ExplicitVarSizeWithMarker_Marker, - 1 <= sum([toInt(y_Occurrence[q5]) | q5 : int(2..5)]), - and([y_Occurrence[q6] -> - or([q8 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[q8] = q6 | q8 : int(1..4)]) - | q6 : int(2..5)]), - and([q10 <= y_ExplicitVarSizeWithMarker_Marker -> y_Occurrence[y_ExplicitVarSizeWithMarker_Values[q10]] - | q10 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_1_3_1_2-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_1_3_1_2-solution000001.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_3_1_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_1_3_1_2-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_1_3_1_2-solution000002.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_3_1_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_1_3_1_2.eprime b/tests/exhaustive/basic/set09/expected/model_1_3_1_2.eprime deleted file mode 100644 index fd2bbeeb87..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_3_1_2.eprime +++ /dev/null @@ -1,32 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(2..5)] of bool -find y_ExplicitVarSizeWithMarker_Marker: int(0..4) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -branching on - [x_Occurrence, y_ExplicitVarSizeWithDummy, y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values] -such that - and([x_Occurrence[i] /\ q17 <= y_ExplicitVarSizeWithMarker_Marker -> i + 2 = y_ExplicitVarSizeWithMarker_Values[q17] - | i : int(2..5), q17 : int(1..4)]), - 1 <= sum([toInt(x_Occurrence[q1]) | q1 : int(2..5)]), - and([q2 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> - y_ExplicitVarSizeWithMarker_Values[q2] < y_ExplicitVarSizeWithMarker_Values[q2 + 1] - | q2 : int(1..3)]), - and([q3 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q3] = 2 | q3 : int(1..4)]), - 1 <= y_ExplicitVarSizeWithMarker_Marker, - and([y_ExplicitVarSizeWithDummy[q5] < y_ExplicitVarSizeWithDummy[q5 + 1] \/ y_ExplicitVarSizeWithDummy[q5] = 6 - | q5 : int(1..3)]), - and([y_ExplicitVarSizeWithDummy[q6] = 6 -> y_ExplicitVarSizeWithDummy[q6 + 1] = 6 | q6 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q7] != 6) | q7 : int(1..4)]), - and([y_ExplicitVarSizeWithDummy[q10] != 6 -> - or([q12 <= y_ExplicitVarSizeWithMarker_Marker /\ - y_ExplicitVarSizeWithMarker_Values[q12] = y_ExplicitVarSizeWithDummy[q10] - | q12 : int(1..4)]) - | q10 : int(1..4)]), - and([q14 <= y_ExplicitVarSizeWithMarker_Marker -> - or([y_ExplicitVarSizeWithDummy[q16] != 6 /\ - y_ExplicitVarSizeWithDummy[q16] = y_ExplicitVarSizeWithMarker_Values[q14] - | q16 : int(1..4)]) - | q14 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_1_3_1_3-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_1_3_1_3-solution000001.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_3_1_3-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_1_3_1_3-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_1_3_1_3-solution000002.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_3_1_3-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_1_3_1_3.eprime b/tests/exhaustive/basic/set09/expected/model_1_3_1_3.eprime deleted file mode 100644 index a2de25f50a..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_3_1_3.eprime +++ /dev/null @@ -1,16 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(2..5)] of bool -find y_ExplicitVarSizeWithMarker_Marker: int(0..4) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -branching on [x_Occurrence, y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values] -such that - and([x_Occurrence[i] /\ q5 <= y_ExplicitVarSizeWithMarker_Marker -> i + 2 = y_ExplicitVarSizeWithMarker_Values[q5] - | i : int(2..5), q5 : int(1..4)]), - 1 <= sum([toInt(x_Occurrence[q1]) | q1 : int(2..5)]), - and([q2 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> - y_ExplicitVarSizeWithMarker_Values[q2] < y_ExplicitVarSizeWithMarker_Values[q2 + 1] - | q2 : int(1..3)]), - and([q3 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q3] = 2 | q3 : int(1..4)]), - 1 <= y_ExplicitVarSizeWithMarker_Marker - diff --git a/tests/exhaustive/basic/set09/expected/model_1_3_1_4-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_1_3_1_4-solution000001.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_3_1_4-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_1_3_1_4-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_1_3_1_4-solution000002.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_3_1_4-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_1_3_1_4.eprime b/tests/exhaustive/basic/set09/expected/model_1_3_1_4.eprime deleted file mode 100644 index 7d10ae0289..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_3_1_4.eprime +++ /dev/null @@ -1,36 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(2..5)] of bool -find y_ExplicitVarSizeWithMarker_Marker: int(0..4) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -branching on - [x_Occurrence, y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values, - y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values] -such that - and([x_Occurrence[i] /\ q18 <= y_ExplicitVarSizeWithMarker_Marker -> i + 2 = y_ExplicitVarSizeWithMarker_Values[q18] - | i : int(2..5), q18 : int(1..4)]), - 1 <= sum([toInt(x_Occurrence[q1]) | q1 : int(2..5)]), - and([q2 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> - y_ExplicitVarSizeWithMarker_Values[q2] < y_ExplicitVarSizeWithMarker_Values[q2 + 1] - | q2 : int(1..3)]), - and([q3 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q3] = 2 | q3 : int(1..4)]), - 1 <= y_ExplicitVarSizeWithMarker_Marker, - and([y_ExplicitVarSizeWithFlags_Flags[q5 + 1] -> - y_ExplicitVarSizeWithFlags_Values[q5] < y_ExplicitVarSizeWithFlags_Values[q5 + 1] - | q5 : int(1..3)]), - and([y_ExplicitVarSizeWithFlags_Flags[q6] = false -> y_ExplicitVarSizeWithFlags_Values[q6] = 2 | q6 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q7] | q7 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q8]) | q8 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q11] -> - or([q13 <= y_ExplicitVarSizeWithMarker_Marker /\ - y_ExplicitVarSizeWithMarker_Values[q13] = y_ExplicitVarSizeWithFlags_Values[q11] - | q13 : int(1..4)]) - | q11 : int(1..4)]), - and([q15 <= y_ExplicitVarSizeWithMarker_Marker -> - or([y_ExplicitVarSizeWithFlags_Flags[q17] /\ - y_ExplicitVarSizeWithFlags_Values[q17] = y_ExplicitVarSizeWithMarker_Values[q15] - | q17 : int(1..4)]) - | q15 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_1_3_2_1-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_1_3_2_1-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_3_2_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_1_3_2_1-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_1_3_2_1-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_3_2_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_1_3_2_1.eprime b/tests/exhaustive/basic/set09/expected/model_1_3_2_1.eprime deleted file mode 100644 index aa45ad18ec..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_3_2_1.eprime +++ /dev/null @@ -1,35 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(2..5)] of bool -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -find y_ExplicitVarSizeWithMarker_Marker: int(0..4) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_Occurrence: matrix indexed by [int(2..5)] of bool -branching on - [x_ExplicitVarSizeWithDummy, x_Occurrence, y_Occurrence, y_ExplicitVarSizeWithMarker_Marker, - y_ExplicitVarSizeWithMarker_Values] -such that - and([x_Occurrence[i] /\ q20 <= y_ExplicitVarSizeWithMarker_Marker -> i + 2 = y_ExplicitVarSizeWithMarker_Values[q20] - | i : int(2..5), q20 : int(1..4)]), - 1 <= sum([toInt(x_Occurrence[q1]) | q1 : int(2..5)]), - and([q2 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> - y_ExplicitVarSizeWithMarker_Values[q2] < y_ExplicitVarSizeWithMarker_Values[q2 + 1] - | q2 : int(1..3)]), - and([q3 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q3] = 2 | q3 : int(1..4)]), - 1 <= y_ExplicitVarSizeWithMarker_Marker, - and([x_ExplicitVarSizeWithDummy[q5] < x_ExplicitVarSizeWithDummy[q5 + 1] \/ x_ExplicitVarSizeWithDummy[q5] = 6 - | q5 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q6] = 6 -> x_ExplicitVarSizeWithDummy[q6 + 1] = 6 | q6 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q7] != 6) | q7 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q10] != 6 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q10]] | q10 : int(1..4)]), - and([x_Occurrence[q11] -> - or([x_ExplicitVarSizeWithDummy[q13] != 6 /\ x_ExplicitVarSizeWithDummy[q13] = q11 | q13 : int(1..4)]) - | q11 : int(2..5)]), - 1 <= sum([toInt(y_Occurrence[q14]) | q14 : int(2..5)]), - and([y_Occurrence[q15] -> - or([q17 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[q17] = q15 - | q17 : int(1..4)]) - | q15 : int(2..5)]), - and([q19 <= y_ExplicitVarSizeWithMarker_Marker -> y_Occurrence[y_ExplicitVarSizeWithMarker_Values[q19]] - | q19 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_1_3_2_2-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_1_3_2_2-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_3_2_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_1_3_2_2-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_1_3_2_2-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_3_2_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_1_3_2_2.eprime b/tests/exhaustive/basic/set09/expected/model_1_3_2_2.eprime deleted file mode 100644 index 12abc5a79c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_3_2_2.eprime +++ /dev/null @@ -1,42 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(2..5)] of bool -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -find y_ExplicitVarSizeWithMarker_Marker: int(0..4) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -branching on - [x_ExplicitVarSizeWithDummy, x_Occurrence, y_ExplicitVarSizeWithDummy, y_ExplicitVarSizeWithMarker_Marker, - y_ExplicitVarSizeWithMarker_Values] -such that - and([x_Occurrence[i] /\ q26 <= y_ExplicitVarSizeWithMarker_Marker -> i + 2 = y_ExplicitVarSizeWithMarker_Values[q26] - | i : int(2..5), q26 : int(1..4)]), - 1 <= sum([toInt(x_Occurrence[q1]) | q1 : int(2..5)]), - and([q2 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> - y_ExplicitVarSizeWithMarker_Values[q2] < y_ExplicitVarSizeWithMarker_Values[q2 + 1] - | q2 : int(1..3)]), - and([q3 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q3] = 2 | q3 : int(1..4)]), - 1 <= y_ExplicitVarSizeWithMarker_Marker, - and([x_ExplicitVarSizeWithDummy[q5] < x_ExplicitVarSizeWithDummy[q5 + 1] \/ x_ExplicitVarSizeWithDummy[q5] = 6 - | q5 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q6] = 6 -> x_ExplicitVarSizeWithDummy[q6 + 1] = 6 | q6 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q7] != 6) | q7 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q10] != 6 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q10]] | q10 : int(1..4)]), - and([x_Occurrence[q11] -> - or([x_ExplicitVarSizeWithDummy[q13] != 6 /\ x_ExplicitVarSizeWithDummy[q13] = q11 | q13 : int(1..4)]) - | q11 : int(2..5)]), - and([y_ExplicitVarSizeWithDummy[q14] < y_ExplicitVarSizeWithDummy[q14 + 1] \/ y_ExplicitVarSizeWithDummy[q14] = 6 - | q14 : int(1..3)]), - and([y_ExplicitVarSizeWithDummy[q15] = 6 -> y_ExplicitVarSizeWithDummy[q15 + 1] = 6 | q15 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q16] != 6) | q16 : int(1..4)]), - and([y_ExplicitVarSizeWithDummy[q19] != 6 -> - or([q21 <= y_ExplicitVarSizeWithMarker_Marker /\ - y_ExplicitVarSizeWithMarker_Values[q21] = y_ExplicitVarSizeWithDummy[q19] - | q21 : int(1..4)]) - | q19 : int(1..4)]), - and([q23 <= y_ExplicitVarSizeWithMarker_Marker -> - or([y_ExplicitVarSizeWithDummy[q25] != 6 /\ - y_ExplicitVarSizeWithDummy[q25] = y_ExplicitVarSizeWithMarker_Values[q23] - | q25 : int(1..4)]) - | q23 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_1_3_2_3-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_1_3_2_3-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_3_2_3-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_1_3_2_3-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_1_3_2_3-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_3_2_3-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_1_3_2_3.eprime b/tests/exhaustive/basic/set09/expected/model_1_3_2_3.eprime deleted file mode 100644 index beae6fe911..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_3_2_3.eprime +++ /dev/null @@ -1,26 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(2..5)] of bool -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -find y_ExplicitVarSizeWithMarker_Marker: int(0..4) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -branching on - [x_ExplicitVarSizeWithDummy, x_Occurrence, y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values] -such that - and([x_Occurrence[i] /\ q14 <= y_ExplicitVarSizeWithMarker_Marker -> i + 2 = y_ExplicitVarSizeWithMarker_Values[q14] - | i : int(2..5), q14 : int(1..4)]), - 1 <= sum([toInt(x_Occurrence[q1]) | q1 : int(2..5)]), - and([q2 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> - y_ExplicitVarSizeWithMarker_Values[q2] < y_ExplicitVarSizeWithMarker_Values[q2 + 1] - | q2 : int(1..3)]), - and([q3 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q3] = 2 | q3 : int(1..4)]), - 1 <= y_ExplicitVarSizeWithMarker_Marker, - and([x_ExplicitVarSizeWithDummy[q5] < x_ExplicitVarSizeWithDummy[q5 + 1] \/ x_ExplicitVarSizeWithDummy[q5] = 6 - | q5 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q6] = 6 -> x_ExplicitVarSizeWithDummy[q6 + 1] = 6 | q6 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q7] != 6) | q7 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q10] != 6 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q10]] | q10 : int(1..4)]), - and([x_Occurrence[q11] -> - or([x_ExplicitVarSizeWithDummy[q13] != 6 /\ x_ExplicitVarSizeWithDummy[q13] = q11 | q13 : int(1..4)]) - | q11 : int(2..5)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_1_3_2_4-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_1_3_2_4-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_3_2_4-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_1_3_2_4-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_1_3_2_4-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_3_2_4-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_1_3_2_4.eprime b/tests/exhaustive/basic/set09/expected/model_1_3_2_4.eprime deleted file mode 100644 index 0129c25cc0..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_3_2_4.eprime +++ /dev/null @@ -1,46 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(2..5)] of bool -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -find y_ExplicitVarSizeWithMarker_Marker: int(0..4) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -branching on - [x_ExplicitVarSizeWithDummy, x_Occurrence, y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values, - y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values] -such that - and([x_Occurrence[i] /\ q27 <= y_ExplicitVarSizeWithMarker_Marker -> i + 2 = y_ExplicitVarSizeWithMarker_Values[q27] - | i : int(2..5), q27 : int(1..4)]), - 1 <= sum([toInt(x_Occurrence[q1]) | q1 : int(2..5)]), - and([q2 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> - y_ExplicitVarSizeWithMarker_Values[q2] < y_ExplicitVarSizeWithMarker_Values[q2 + 1] - | q2 : int(1..3)]), - and([q3 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q3] = 2 | q3 : int(1..4)]), - 1 <= y_ExplicitVarSizeWithMarker_Marker, - and([x_ExplicitVarSizeWithDummy[q5] < x_ExplicitVarSizeWithDummy[q5 + 1] \/ x_ExplicitVarSizeWithDummy[q5] = 6 - | q5 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q6] = 6 -> x_ExplicitVarSizeWithDummy[q6 + 1] = 6 | q6 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q7] != 6) | q7 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q10] != 6 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q10]] | q10 : int(1..4)]), - and([x_Occurrence[q11] -> - or([x_ExplicitVarSizeWithDummy[q13] != 6 /\ x_ExplicitVarSizeWithDummy[q13] = q11 | q13 : int(1..4)]) - | q11 : int(2..5)]), - and([y_ExplicitVarSizeWithFlags_Flags[q14 + 1] -> - y_ExplicitVarSizeWithFlags_Values[q14] < y_ExplicitVarSizeWithFlags_Values[q14 + 1] - | q14 : int(1..3)]), - and([y_ExplicitVarSizeWithFlags_Flags[q15] = false -> y_ExplicitVarSizeWithFlags_Values[q15] = 2 - | q15 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q16 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q16] | q16 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q17]) | q17 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q20] -> - or([q22 <= y_ExplicitVarSizeWithMarker_Marker /\ - y_ExplicitVarSizeWithMarker_Values[q22] = y_ExplicitVarSizeWithFlags_Values[q20] - | q22 : int(1..4)]) - | q20 : int(1..4)]), - and([q24 <= y_ExplicitVarSizeWithMarker_Marker -> - or([y_ExplicitVarSizeWithFlags_Flags[q26] /\ - y_ExplicitVarSizeWithFlags_Values[q26] = y_ExplicitVarSizeWithMarker_Values[q24] - | q26 : int(1..4)]) - | q24 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_1_3_3_1-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_1_3_3_1-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_3_3_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_1_3_3_1-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_1_3_3_1-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_3_3_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_1_3_3_1.eprime b/tests/exhaustive/basic/set09/expected/model_1_3_3_1.eprime deleted file mode 100644 index e299f22797..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_3_3_1.eprime +++ /dev/null @@ -1,39 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(2..5)] of bool -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_ExplicitVarSizeWithMarker_Marker: int(0..4) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_Occurrence: matrix indexed by [int(2..5)] of bool -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_Occurrence, y_Occurrence, - y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values] -such that - and([x_Occurrence[i] /\ q19 <= y_ExplicitVarSizeWithMarker_Marker -> i + 2 = y_ExplicitVarSizeWithMarker_Values[q19] - | i : int(2..5), q19 : int(1..4)]), - 1 <= sum([toInt(x_Occurrence[q1]) | q1 : int(2..5)]), - and([q2 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> - y_ExplicitVarSizeWithMarker_Values[q2] < y_ExplicitVarSizeWithMarker_Values[q2 + 1] - | q2 : int(1..3)]), - and([q3 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q3] = 2 | q3 : int(1..4)]), - 1 <= y_ExplicitVarSizeWithMarker_Marker, - and([q5 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q5] < x_ExplicitVarSizeWithMarker_Values[q5 + 1] - | q5 : int(1..3)]), - and([q6 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q6] = 2 | q6 : int(1..4)]), - 1 <= x_ExplicitVarSizeWithMarker_Marker, - and([q9 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q9]] - | q9 : int(1..4)]), - and([x_Occurrence[q10] -> - or([q12 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q12] = q10 - | q12 : int(1..4)]) - | q10 : int(2..5)]), - 1 <= sum([toInt(y_Occurrence[q13]) | q13 : int(2..5)]), - and([y_Occurrence[q14] -> - or([q16 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[q16] = q14 - | q16 : int(1..4)]) - | q14 : int(2..5)]), - and([q18 <= y_ExplicitVarSizeWithMarker_Marker -> y_Occurrence[y_ExplicitVarSizeWithMarker_Values[q18]] - | q18 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_1_3_3_2-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_1_3_3_2-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_3_3_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_1_3_3_2-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_1_3_3_2-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_3_3_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_1_3_3_2.eprime b/tests/exhaustive/basic/set09/expected/model_1_3_3_2.eprime deleted file mode 100644 index 75e285106e..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_3_3_2.eprime +++ /dev/null @@ -1,46 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(2..5)] of bool -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_ExplicitVarSizeWithMarker_Marker: int(0..4) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_Occurrence, y_ExplicitVarSizeWithDummy, - y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values] -such that - and([x_Occurrence[i] /\ q25 <= y_ExplicitVarSizeWithMarker_Marker -> i + 2 = y_ExplicitVarSizeWithMarker_Values[q25] - | i : int(2..5), q25 : int(1..4)]), - 1 <= sum([toInt(x_Occurrence[q1]) | q1 : int(2..5)]), - and([q2 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> - y_ExplicitVarSizeWithMarker_Values[q2] < y_ExplicitVarSizeWithMarker_Values[q2 + 1] - | q2 : int(1..3)]), - and([q3 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q3] = 2 | q3 : int(1..4)]), - 1 <= y_ExplicitVarSizeWithMarker_Marker, - and([q5 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q5] < x_ExplicitVarSizeWithMarker_Values[q5 + 1] - | q5 : int(1..3)]), - and([q6 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q6] = 2 | q6 : int(1..4)]), - 1 <= x_ExplicitVarSizeWithMarker_Marker, - and([q9 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q9]] - | q9 : int(1..4)]), - and([x_Occurrence[q10] -> - or([q12 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q12] = q10 - | q12 : int(1..4)]) - | q10 : int(2..5)]), - and([y_ExplicitVarSizeWithDummy[q13] < y_ExplicitVarSizeWithDummy[q13 + 1] \/ y_ExplicitVarSizeWithDummy[q13] = 6 - | q13 : int(1..3)]), - and([y_ExplicitVarSizeWithDummy[q14] = 6 -> y_ExplicitVarSizeWithDummy[q14 + 1] = 6 | q14 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q15] != 6) | q15 : int(1..4)]), - and([y_ExplicitVarSizeWithDummy[q18] != 6 -> - or([q20 <= y_ExplicitVarSizeWithMarker_Marker /\ - y_ExplicitVarSizeWithMarker_Values[q20] = y_ExplicitVarSizeWithDummy[q18] - | q20 : int(1..4)]) - | q18 : int(1..4)]), - and([q22 <= y_ExplicitVarSizeWithMarker_Marker -> - or([y_ExplicitVarSizeWithDummy[q24] != 6 /\ - y_ExplicitVarSizeWithDummy[q24] = y_ExplicitVarSizeWithMarker_Values[q22] - | q24 : int(1..4)]) - | q22 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_1_3_3_3-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_1_3_3_3-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_3_3_3-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_1_3_3_3-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_1_3_3_3-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_3_3_3-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_1_3_3_3.eprime b/tests/exhaustive/basic/set09/expected/model_1_3_3_3.eprime deleted file mode 100644 index c8c2dc92cf..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_3_3_3.eprime +++ /dev/null @@ -1,31 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(2..5)] of bool -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_ExplicitVarSizeWithMarker_Marker: int(0..4) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_Occurrence, - y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values] -such that - and([x_Occurrence[i] /\ q13 <= y_ExplicitVarSizeWithMarker_Marker -> i + 2 = y_ExplicitVarSizeWithMarker_Values[q13] - | i : int(2..5), q13 : int(1..4)]), - 1 <= sum([toInt(x_Occurrence[q1]) | q1 : int(2..5)]), - and([q2 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> - y_ExplicitVarSizeWithMarker_Values[q2] < y_ExplicitVarSizeWithMarker_Values[q2 + 1] - | q2 : int(1..3)]), - and([q3 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q3] = 2 | q3 : int(1..4)]), - 1 <= y_ExplicitVarSizeWithMarker_Marker, - and([q5 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q5] < x_ExplicitVarSizeWithMarker_Values[q5 + 1] - | q5 : int(1..3)]), - and([q6 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q6] = 2 | q6 : int(1..4)]), - 1 <= x_ExplicitVarSizeWithMarker_Marker, - and([q9 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q9]] - | q9 : int(1..4)]), - and([x_Occurrence[q10] -> - or([q12 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q12] = q10 - | q12 : int(1..4)]) - | q10 : int(2..5)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_1_3_3_4-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_1_3_3_4-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_3_3_4-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_1_3_3_4-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_1_3_3_4-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_3_3_4-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_1_3_3_4.eprime b/tests/exhaustive/basic/set09/expected/model_1_3_3_4.eprime deleted file mode 100644 index 04d78aaca9..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_3_3_4.eprime +++ /dev/null @@ -1,51 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(2..5)] of bool -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_ExplicitVarSizeWithMarker_Marker: int(0..4) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_Occurrence, - y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithMarker_Marker, - y_ExplicitVarSizeWithMarker_Values] -such that - and([x_Occurrence[i] /\ q26 <= y_ExplicitVarSizeWithMarker_Marker -> i + 2 = y_ExplicitVarSizeWithMarker_Values[q26] - | i : int(2..5), q26 : int(1..4)]), - 1 <= sum([toInt(x_Occurrence[q1]) | q1 : int(2..5)]), - and([q2 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> - y_ExplicitVarSizeWithMarker_Values[q2] < y_ExplicitVarSizeWithMarker_Values[q2 + 1] - | q2 : int(1..3)]), - and([q3 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q3] = 2 | q3 : int(1..4)]), - 1 <= y_ExplicitVarSizeWithMarker_Marker, - and([q5 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q5] < x_ExplicitVarSizeWithMarker_Values[q5 + 1] - | q5 : int(1..3)]), - and([q6 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q6] = 2 | q6 : int(1..4)]), - 1 <= x_ExplicitVarSizeWithMarker_Marker, - and([q9 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q9]] - | q9 : int(1..4)]), - and([x_Occurrence[q10] -> - or([q12 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q12] = q10 - | q12 : int(1..4)]) - | q10 : int(2..5)]), - and([y_ExplicitVarSizeWithFlags_Flags[q13 + 1] -> - y_ExplicitVarSizeWithFlags_Values[q13] < y_ExplicitVarSizeWithFlags_Values[q13 + 1] - | q13 : int(1..3)]), - and([y_ExplicitVarSizeWithFlags_Flags[q14] = false -> y_ExplicitVarSizeWithFlags_Values[q14] = 2 - | q14 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q15 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q15] | q15 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q16]) | q16 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q19] -> - or([q21 <= y_ExplicitVarSizeWithMarker_Marker /\ - y_ExplicitVarSizeWithMarker_Values[q21] = y_ExplicitVarSizeWithFlags_Values[q19] - | q21 : int(1..4)]) - | q19 : int(1..4)]), - and([q23 <= y_ExplicitVarSizeWithMarker_Marker -> - or([y_ExplicitVarSizeWithFlags_Flags[q25] /\ - y_ExplicitVarSizeWithFlags_Values[q25] = y_ExplicitVarSizeWithMarker_Values[q23] - | q25 : int(1..4)]) - | q23 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_1_3_4_1-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_1_3_4_1-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_3_4_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_1_3_4_1-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_1_3_4_1-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_3_4_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_1_3_4_1.eprime b/tests/exhaustive/basic/set09/expected/model_1_3_4_1.eprime deleted file mode 100644 index 4beb160d92..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_3_4_1.eprime +++ /dev/null @@ -1,39 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(2..5)] of bool -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_ExplicitVarSizeWithMarker_Marker: int(0..4) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_Occurrence: matrix indexed by [int(2..5)] of bool -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_Occurrence, y_Occurrence, - y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values] -such that - and([x_Occurrence[i] /\ q21 <= y_ExplicitVarSizeWithMarker_Marker -> i + 2 = y_ExplicitVarSizeWithMarker_Values[q21] - | i : int(2..5), q21 : int(1..4)]), - 1 <= sum([toInt(x_Occurrence[q1]) | q1 : int(2..5)]), - and([q2 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> - y_ExplicitVarSizeWithMarker_Values[q2] < y_ExplicitVarSizeWithMarker_Values[q2 + 1] - | q2 : int(1..3)]), - and([q3 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q3] = 2 | q3 : int(1..4)]), - 1 <= y_ExplicitVarSizeWithMarker_Marker, - and([x_ExplicitVarSizeWithFlags_Flags[q5 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q5] < x_ExplicitVarSizeWithFlags_Values[q5 + 1] - | q5 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q6] = false -> x_ExplicitVarSizeWithFlags_Values[q6] = 2 | q6 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q7] | q7 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q8]) | q8 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q11] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q11]] - | q11 : int(1..4)]), - and([x_Occurrence[q12] -> - or([x_ExplicitVarSizeWithFlags_Flags[q14] /\ x_ExplicitVarSizeWithFlags_Values[q14] = q12 | q14 : int(1..4)]) - | q12 : int(2..5)]), - 1 <= sum([toInt(y_Occurrence[q15]) | q15 : int(2..5)]), - and([y_Occurrence[q16] -> - or([q18 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[q18] = q16 - | q18 : int(1..4)]) - | q16 : int(2..5)]), - and([q20 <= y_ExplicitVarSizeWithMarker_Marker -> y_Occurrence[y_ExplicitVarSizeWithMarker_Values[q20]] - | q20 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_1_3_4_2-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_1_3_4_2-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_3_4_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_1_3_4_2-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_1_3_4_2-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_3_4_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_1_3_4_2.eprime b/tests/exhaustive/basic/set09/expected/model_1_3_4_2.eprime deleted file mode 100644 index 9db3707298..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_3_4_2.eprime +++ /dev/null @@ -1,46 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(2..5)] of bool -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_ExplicitVarSizeWithMarker_Marker: int(0..4) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_Occurrence, y_ExplicitVarSizeWithDummy, - y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values] -such that - and([x_Occurrence[i] /\ q27 <= y_ExplicitVarSizeWithMarker_Marker -> i + 2 = y_ExplicitVarSizeWithMarker_Values[q27] - | i : int(2..5), q27 : int(1..4)]), - 1 <= sum([toInt(x_Occurrence[q1]) | q1 : int(2..5)]), - and([q2 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> - y_ExplicitVarSizeWithMarker_Values[q2] < y_ExplicitVarSizeWithMarker_Values[q2 + 1] - | q2 : int(1..3)]), - and([q3 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q3] = 2 | q3 : int(1..4)]), - 1 <= y_ExplicitVarSizeWithMarker_Marker, - and([x_ExplicitVarSizeWithFlags_Flags[q5 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q5] < x_ExplicitVarSizeWithFlags_Values[q5 + 1] - | q5 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q6] = false -> x_ExplicitVarSizeWithFlags_Values[q6] = 2 | q6 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q7] | q7 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q8]) | q8 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q11] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q11]] - | q11 : int(1..4)]), - and([x_Occurrence[q12] -> - or([x_ExplicitVarSizeWithFlags_Flags[q14] /\ x_ExplicitVarSizeWithFlags_Values[q14] = q12 | q14 : int(1..4)]) - | q12 : int(2..5)]), - and([y_ExplicitVarSizeWithDummy[q15] < y_ExplicitVarSizeWithDummy[q15 + 1] \/ y_ExplicitVarSizeWithDummy[q15] = 6 - | q15 : int(1..3)]), - and([y_ExplicitVarSizeWithDummy[q16] = 6 -> y_ExplicitVarSizeWithDummy[q16 + 1] = 6 | q16 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q17] != 6) | q17 : int(1..4)]), - and([y_ExplicitVarSizeWithDummy[q20] != 6 -> - or([q22 <= y_ExplicitVarSizeWithMarker_Marker /\ - y_ExplicitVarSizeWithMarker_Values[q22] = y_ExplicitVarSizeWithDummy[q20] - | q22 : int(1..4)]) - | q20 : int(1..4)]), - and([q24 <= y_ExplicitVarSizeWithMarker_Marker -> - or([y_ExplicitVarSizeWithDummy[q26] != 6 /\ - y_ExplicitVarSizeWithDummy[q26] = y_ExplicitVarSizeWithMarker_Values[q24] - | q26 : int(1..4)]) - | q24 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_1_3_4_3-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_1_3_4_3-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_3_4_3-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_1_3_4_3-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_1_3_4_3-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_3_4_3-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_1_3_4_3.eprime b/tests/exhaustive/basic/set09/expected/model_1_3_4_3.eprime deleted file mode 100644 index f452bb39ff..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_3_4_3.eprime +++ /dev/null @@ -1,31 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(2..5)] of bool -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_ExplicitVarSizeWithMarker_Marker: int(0..4) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_Occurrence, - y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values] -such that - and([x_Occurrence[i] /\ q15 <= y_ExplicitVarSizeWithMarker_Marker -> i + 2 = y_ExplicitVarSizeWithMarker_Values[q15] - | i : int(2..5), q15 : int(1..4)]), - 1 <= sum([toInt(x_Occurrence[q1]) | q1 : int(2..5)]), - and([q2 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> - y_ExplicitVarSizeWithMarker_Values[q2] < y_ExplicitVarSizeWithMarker_Values[q2 + 1] - | q2 : int(1..3)]), - and([q3 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q3] = 2 | q3 : int(1..4)]), - 1 <= y_ExplicitVarSizeWithMarker_Marker, - and([x_ExplicitVarSizeWithFlags_Flags[q5 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q5] < x_ExplicitVarSizeWithFlags_Values[q5 + 1] - | q5 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q6] = false -> x_ExplicitVarSizeWithFlags_Values[q6] = 2 | q6 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q7] | q7 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q8]) | q8 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q11] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q11]] - | q11 : int(1..4)]), - and([x_Occurrence[q12] -> - or([x_ExplicitVarSizeWithFlags_Flags[q14] /\ x_ExplicitVarSizeWithFlags_Values[q14] = q12 | q14 : int(1..4)]) - | q12 : int(2..5)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_1_3_4_4-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_1_3_4_4-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_3_4_4-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_1_3_4_4-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_1_3_4_4-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_3_4_4-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_1_3_4_4.eprime b/tests/exhaustive/basic/set09/expected/model_1_3_4_4.eprime deleted file mode 100644 index dec6657450..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_3_4_4.eprime +++ /dev/null @@ -1,51 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(2..5)] of bool -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_ExplicitVarSizeWithMarker_Marker: int(0..4) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_Occurrence, - y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithMarker_Marker, - y_ExplicitVarSizeWithMarker_Values] -such that - and([x_Occurrence[i] /\ q28 <= y_ExplicitVarSizeWithMarker_Marker -> i + 2 = y_ExplicitVarSizeWithMarker_Values[q28] - | i : int(2..5), q28 : int(1..4)]), - 1 <= sum([toInt(x_Occurrence[q1]) | q1 : int(2..5)]), - and([q2 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> - y_ExplicitVarSizeWithMarker_Values[q2] < y_ExplicitVarSizeWithMarker_Values[q2 + 1] - | q2 : int(1..3)]), - and([q3 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q3] = 2 | q3 : int(1..4)]), - 1 <= y_ExplicitVarSizeWithMarker_Marker, - and([x_ExplicitVarSizeWithFlags_Flags[q5 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q5] < x_ExplicitVarSizeWithFlags_Values[q5 + 1] - | q5 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q6] = false -> x_ExplicitVarSizeWithFlags_Values[q6] = 2 | q6 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q7] | q7 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q8]) | q8 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q11] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q11]] - | q11 : int(1..4)]), - and([x_Occurrence[q12] -> - or([x_ExplicitVarSizeWithFlags_Flags[q14] /\ x_ExplicitVarSizeWithFlags_Values[q14] = q12 | q14 : int(1..4)]) - | q12 : int(2..5)]), - and([y_ExplicitVarSizeWithFlags_Flags[q15 + 1] -> - y_ExplicitVarSizeWithFlags_Values[q15] < y_ExplicitVarSizeWithFlags_Values[q15 + 1] - | q15 : int(1..3)]), - and([y_ExplicitVarSizeWithFlags_Flags[q16] = false -> y_ExplicitVarSizeWithFlags_Values[q16] = 2 - | q16 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q17 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q17] | q17 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q18]) | q18 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q21] -> - or([q23 <= y_ExplicitVarSizeWithMarker_Marker /\ - y_ExplicitVarSizeWithMarker_Values[q23] = y_ExplicitVarSizeWithFlags_Values[q21] - | q23 : int(1..4)]) - | q21 : int(1..4)]), - and([q25 <= y_ExplicitVarSizeWithMarker_Marker -> - or([y_ExplicitVarSizeWithFlags_Flags[q27] /\ - y_ExplicitVarSizeWithFlags_Values[q27] = y_ExplicitVarSizeWithMarker_Values[q25] - | q27 : int(1..4)]) - | q25 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_1_4_1_1-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_1_4_1_1-solution000001.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_4_1_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_1_4_1_1-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_1_4_1_1-solution000002.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_4_1_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_1_4_1_1.eprime b/tests/exhaustive/basic/set09/expected/model_1_4_1_1.eprime deleted file mode 100644 index 6809b5e1fc..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_4_1_1.eprime +++ /dev/null @@ -1,24 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(2..5)] of bool -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_Occurrence: matrix indexed by [int(2..5)] of bool -branching on [x_Occurrence, y_Occurrence, y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values] -such that - and([x_Occurrence[i] /\ y_ExplicitVarSizeWithFlags_Flags[q13] -> i + 2 = y_ExplicitVarSizeWithFlags_Values[q13] - | i : int(2..5), q13 : int(1..4)]), - 1 <= sum([toInt(x_Occurrence[q1]) | q1 : int(2..5)]), - and([y_ExplicitVarSizeWithFlags_Flags[q2 + 1] -> - y_ExplicitVarSizeWithFlags_Values[q2] < y_ExplicitVarSizeWithFlags_Values[q2 + 1] - | q2 : int(1..3)]), - and([y_ExplicitVarSizeWithFlags_Flags[q3] = false -> y_ExplicitVarSizeWithFlags_Values[q3] = 2 | q3 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q4] | q4 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q5]) | q5 : int(1..4)]), - 1 <= sum([toInt(y_Occurrence[q7]) | q7 : int(2..5)]), - and([y_Occurrence[q8] -> - or([y_ExplicitVarSizeWithFlags_Flags[q10] /\ y_ExplicitVarSizeWithFlags_Values[q10] = q8 | q10 : int(1..4)]) - | q8 : int(2..5)]), - and([y_ExplicitVarSizeWithFlags_Flags[q12] -> y_Occurrence[y_ExplicitVarSizeWithFlags_Values[q12]] - | q12 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_1_4_1_2-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_1_4_1_2-solution000001.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_4_1_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_1_4_1_2-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_1_4_1_2-solution000002.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_4_1_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_1_4_1_2.eprime b/tests/exhaustive/basic/set09/expected/model_1_4_1_2.eprime deleted file mode 100644 index 771b008b83..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_4_1_2.eprime +++ /dev/null @@ -1,33 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(2..5)] of bool -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -branching on - [x_Occurrence, y_ExplicitVarSizeWithDummy, y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values] -such that - and([x_Occurrence[i] /\ y_ExplicitVarSizeWithFlags_Flags[q19] -> i + 2 = y_ExplicitVarSizeWithFlags_Values[q19] - | i : int(2..5), q19 : int(1..4)]), - 1 <= sum([toInt(x_Occurrence[q1]) | q1 : int(2..5)]), - and([y_ExplicitVarSizeWithFlags_Flags[q2 + 1] -> - y_ExplicitVarSizeWithFlags_Values[q2] < y_ExplicitVarSizeWithFlags_Values[q2 + 1] - | q2 : int(1..3)]), - and([y_ExplicitVarSizeWithFlags_Flags[q3] = false -> y_ExplicitVarSizeWithFlags_Values[q3] = 2 | q3 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q4] | q4 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q5]) | q5 : int(1..4)]), - and([y_ExplicitVarSizeWithDummy[q7] < y_ExplicitVarSizeWithDummy[q7 + 1] \/ y_ExplicitVarSizeWithDummy[q7] = 6 - | q7 : int(1..3)]), - and([y_ExplicitVarSizeWithDummy[q8] = 6 -> y_ExplicitVarSizeWithDummy[q8 + 1] = 6 | q8 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q9] != 6) | q9 : int(1..4)]), - and([y_ExplicitVarSizeWithDummy[q12] != 6 -> - or([y_ExplicitVarSizeWithFlags_Flags[q14] /\ - y_ExplicitVarSizeWithFlags_Values[q14] = y_ExplicitVarSizeWithDummy[q12] - | q14 : int(1..4)]) - | q12 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q16] -> - or([y_ExplicitVarSizeWithDummy[q18] != 6 /\ - y_ExplicitVarSizeWithDummy[q18] = y_ExplicitVarSizeWithFlags_Values[q16] - | q18 : int(1..4)]) - | q16 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_1_4_1_3-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_1_4_1_3-solution000001.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_4_1_3-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_1_4_1_3-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_1_4_1_3-solution000002.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_4_1_3-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_1_4_1_3.eprime b/tests/exhaustive/basic/set09/expected/model_1_4_1_3.eprime deleted file mode 100644 index 366e35ebb5..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_4_1_3.eprime +++ /dev/null @@ -1,36 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(2..5)] of bool -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_ExplicitVarSizeWithMarker_Marker: int(0..4) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -branching on - [x_Occurrence, y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values, - y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values] -such that - and([x_Occurrence[i] /\ y_ExplicitVarSizeWithFlags_Flags[q18] -> i + 2 = y_ExplicitVarSizeWithFlags_Values[q18] - | i : int(2..5), q18 : int(1..4)]), - 1 <= sum([toInt(x_Occurrence[q1]) | q1 : int(2..5)]), - and([y_ExplicitVarSizeWithFlags_Flags[q2 + 1] -> - y_ExplicitVarSizeWithFlags_Values[q2] < y_ExplicitVarSizeWithFlags_Values[q2 + 1] - | q2 : int(1..3)]), - and([y_ExplicitVarSizeWithFlags_Flags[q3] = false -> y_ExplicitVarSizeWithFlags_Values[q3] = 2 | q3 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q4] | q4 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q5]) | q5 : int(1..4)]), - and([q7 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> - y_ExplicitVarSizeWithMarker_Values[q7] < y_ExplicitVarSizeWithMarker_Values[q7 + 1] - | q7 : int(1..3)]), - and([q8 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q8] = 2 | q8 : int(1..4)]), - 1 <= y_ExplicitVarSizeWithMarker_Marker, - and([q11 <= y_ExplicitVarSizeWithMarker_Marker -> - or([y_ExplicitVarSizeWithFlags_Flags[q13] /\ - y_ExplicitVarSizeWithFlags_Values[q13] = y_ExplicitVarSizeWithMarker_Values[q11] - | q13 : int(1..4)]) - | q11 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q15] -> - or([q17 <= y_ExplicitVarSizeWithMarker_Marker /\ - y_ExplicitVarSizeWithMarker_Values[q17] = y_ExplicitVarSizeWithFlags_Values[q15] - | q17 : int(1..4)]) - | q15 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_1_4_1_4-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_1_4_1_4-solution000001.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_4_1_4-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_1_4_1_4-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_1_4_1_4-solution000002.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_4_1_4-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_1_4_1_4.eprime b/tests/exhaustive/basic/set09/expected/model_1_4_1_4.eprime deleted file mode 100644 index bfdab410df..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_4_1_4.eprime +++ /dev/null @@ -1,17 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(2..5)] of bool -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -branching on [x_Occurrence, y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values] -such that - and([x_Occurrence[i] /\ y_ExplicitVarSizeWithFlags_Flags[q7] -> i + 2 = y_ExplicitVarSizeWithFlags_Values[q7] - | i : int(2..5), q7 : int(1..4)]), - 1 <= sum([toInt(x_Occurrence[q1]) | q1 : int(2..5)]), - and([y_ExplicitVarSizeWithFlags_Flags[q2 + 1] -> - y_ExplicitVarSizeWithFlags_Values[q2] < y_ExplicitVarSizeWithFlags_Values[q2 + 1] - | q2 : int(1..3)]), - and([y_ExplicitVarSizeWithFlags_Flags[q3] = false -> y_ExplicitVarSizeWithFlags_Values[q3] = 2 | q3 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q4] | q4 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q5]) | q5 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_1_4_2_1-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_1_4_2_1-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_4_2_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_1_4_2_1-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_1_4_2_1-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_4_2_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_1_4_2_1.eprime b/tests/exhaustive/basic/set09/expected/model_1_4_2_1.eprime deleted file mode 100644 index e41a4cfc54..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_4_2_1.eprime +++ /dev/null @@ -1,35 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(2..5)] of bool -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_Occurrence: matrix indexed by [int(2..5)] of bool -branching on - [x_ExplicitVarSizeWithDummy, x_Occurrence, y_Occurrence, y_ExplicitVarSizeWithFlags_Flags, - y_ExplicitVarSizeWithFlags_Values] -such that - and([x_Occurrence[i] /\ y_ExplicitVarSizeWithFlags_Flags[q22] -> i + 2 = y_ExplicitVarSizeWithFlags_Values[q22] - | i : int(2..5), q22 : int(1..4)]), - 1 <= sum([toInt(x_Occurrence[q1]) | q1 : int(2..5)]), - and([y_ExplicitVarSizeWithFlags_Flags[q2 + 1] -> - y_ExplicitVarSizeWithFlags_Values[q2] < y_ExplicitVarSizeWithFlags_Values[q2 + 1] - | q2 : int(1..3)]), - and([y_ExplicitVarSizeWithFlags_Flags[q3] = false -> y_ExplicitVarSizeWithFlags_Values[q3] = 2 | q3 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q4] | q4 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q5]) | q5 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q7] < x_ExplicitVarSizeWithDummy[q7 + 1] \/ x_ExplicitVarSizeWithDummy[q7] = 6 - | q7 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q8] = 6 -> x_ExplicitVarSizeWithDummy[q8 + 1] = 6 | q8 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q9] != 6) | q9 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q12] != 6 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q12]] | q12 : int(1..4)]), - and([x_Occurrence[q13] -> - or([x_ExplicitVarSizeWithDummy[q15] != 6 /\ x_ExplicitVarSizeWithDummy[q15] = q13 | q15 : int(1..4)]) - | q13 : int(2..5)]), - 1 <= sum([toInt(y_Occurrence[q16]) | q16 : int(2..5)]), - and([y_Occurrence[q17] -> - or([y_ExplicitVarSizeWithFlags_Flags[q19] /\ y_ExplicitVarSizeWithFlags_Values[q19] = q17 | q19 : int(1..4)]) - | q17 : int(2..5)]), - and([y_ExplicitVarSizeWithFlags_Flags[q21] -> y_Occurrence[y_ExplicitVarSizeWithFlags_Values[q21]] - | q21 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_1_4_2_2-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_1_4_2_2-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_4_2_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_1_4_2_2-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_1_4_2_2-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_4_2_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_1_4_2_2.eprime b/tests/exhaustive/basic/set09/expected/model_1_4_2_2.eprime deleted file mode 100644 index 64521d1cd6..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_4_2_2.eprime +++ /dev/null @@ -1,43 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(2..5)] of bool -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -branching on - [x_ExplicitVarSizeWithDummy, x_Occurrence, y_ExplicitVarSizeWithDummy, y_ExplicitVarSizeWithFlags_Flags, - y_ExplicitVarSizeWithFlags_Values] -such that - and([x_Occurrence[i] /\ y_ExplicitVarSizeWithFlags_Flags[q28] -> i + 2 = y_ExplicitVarSizeWithFlags_Values[q28] - | i : int(2..5), q28 : int(1..4)]), - 1 <= sum([toInt(x_Occurrence[q1]) | q1 : int(2..5)]), - and([y_ExplicitVarSizeWithFlags_Flags[q2 + 1] -> - y_ExplicitVarSizeWithFlags_Values[q2] < y_ExplicitVarSizeWithFlags_Values[q2 + 1] - | q2 : int(1..3)]), - and([y_ExplicitVarSizeWithFlags_Flags[q3] = false -> y_ExplicitVarSizeWithFlags_Values[q3] = 2 | q3 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q4] | q4 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q5]) | q5 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q7] < x_ExplicitVarSizeWithDummy[q7 + 1] \/ x_ExplicitVarSizeWithDummy[q7] = 6 - | q7 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q8] = 6 -> x_ExplicitVarSizeWithDummy[q8 + 1] = 6 | q8 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q9] != 6) | q9 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q12] != 6 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q12]] | q12 : int(1..4)]), - and([x_Occurrence[q13] -> - or([x_ExplicitVarSizeWithDummy[q15] != 6 /\ x_ExplicitVarSizeWithDummy[q15] = q13 | q15 : int(1..4)]) - | q13 : int(2..5)]), - and([y_ExplicitVarSizeWithDummy[q16] < y_ExplicitVarSizeWithDummy[q16 + 1] \/ y_ExplicitVarSizeWithDummy[q16] = 6 - | q16 : int(1..3)]), - and([y_ExplicitVarSizeWithDummy[q17] = 6 -> y_ExplicitVarSizeWithDummy[q17 + 1] = 6 | q17 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q18] != 6) | q18 : int(1..4)]), - and([y_ExplicitVarSizeWithDummy[q21] != 6 -> - or([y_ExplicitVarSizeWithFlags_Flags[q23] /\ - y_ExplicitVarSizeWithFlags_Values[q23] = y_ExplicitVarSizeWithDummy[q21] - | q23 : int(1..4)]) - | q21 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q25] -> - or([y_ExplicitVarSizeWithDummy[q27] != 6 /\ - y_ExplicitVarSizeWithDummy[q27] = y_ExplicitVarSizeWithFlags_Values[q25] - | q27 : int(1..4)]) - | q25 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_1_4_2_3-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_1_4_2_3-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_4_2_3-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_1_4_2_3-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_1_4_2_3-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_4_2_3-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_1_4_2_3.eprime b/tests/exhaustive/basic/set09/expected/model_1_4_2_3.eprime deleted file mode 100644 index 68e8249552..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_4_2_3.eprime +++ /dev/null @@ -1,45 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(2..5)] of bool -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_ExplicitVarSizeWithMarker_Marker: int(0..4) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -branching on - [x_ExplicitVarSizeWithDummy, x_Occurrence, y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values, - y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values] -such that - and([x_Occurrence[i] /\ y_ExplicitVarSizeWithFlags_Flags[q27] -> i + 2 = y_ExplicitVarSizeWithFlags_Values[q27] - | i : int(2..5), q27 : int(1..4)]), - 1 <= sum([toInt(x_Occurrence[q1]) | q1 : int(2..5)]), - and([y_ExplicitVarSizeWithFlags_Flags[q2 + 1] -> - y_ExplicitVarSizeWithFlags_Values[q2] < y_ExplicitVarSizeWithFlags_Values[q2 + 1] - | q2 : int(1..3)]), - and([y_ExplicitVarSizeWithFlags_Flags[q3] = false -> y_ExplicitVarSizeWithFlags_Values[q3] = 2 | q3 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q4] | q4 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q5]) | q5 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q7] < x_ExplicitVarSizeWithDummy[q7 + 1] \/ x_ExplicitVarSizeWithDummy[q7] = 6 - | q7 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q8] = 6 -> x_ExplicitVarSizeWithDummy[q8 + 1] = 6 | q8 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q9] != 6) | q9 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q12] != 6 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q12]] | q12 : int(1..4)]), - and([x_Occurrence[q13] -> - or([x_ExplicitVarSizeWithDummy[q15] != 6 /\ x_ExplicitVarSizeWithDummy[q15] = q13 | q15 : int(1..4)]) - | q13 : int(2..5)]), - and([q16 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> - y_ExplicitVarSizeWithMarker_Values[q16] < y_ExplicitVarSizeWithMarker_Values[q16 + 1] - | q16 : int(1..3)]), - and([q17 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q17] = 2 | q17 : int(1..4)]), - 1 <= y_ExplicitVarSizeWithMarker_Marker, - and([q20 <= y_ExplicitVarSizeWithMarker_Marker -> - or([y_ExplicitVarSizeWithFlags_Flags[q22] /\ - y_ExplicitVarSizeWithFlags_Values[q22] = y_ExplicitVarSizeWithMarker_Values[q20] - | q22 : int(1..4)]) - | q20 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q24] -> - or([q26 <= y_ExplicitVarSizeWithMarker_Marker /\ - y_ExplicitVarSizeWithMarker_Values[q26] = y_ExplicitVarSizeWithFlags_Values[q24] - | q26 : int(1..4)]) - | q24 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_1_4_2_4-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_1_4_2_4-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_4_2_4-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_1_4_2_4-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_1_4_2_4-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_4_2_4-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_1_4_2_4.eprime b/tests/exhaustive/basic/set09/expected/model_1_4_2_4.eprime deleted file mode 100644 index 2c847ef491..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_4_2_4.eprime +++ /dev/null @@ -1,27 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(2..5)] of bool -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -branching on - [x_ExplicitVarSizeWithDummy, x_Occurrence, y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values] -such that - and([x_Occurrence[i] /\ y_ExplicitVarSizeWithFlags_Flags[q16] -> i + 2 = y_ExplicitVarSizeWithFlags_Values[q16] - | i : int(2..5), q16 : int(1..4)]), - 1 <= sum([toInt(x_Occurrence[q1]) | q1 : int(2..5)]), - and([y_ExplicitVarSizeWithFlags_Flags[q2 + 1] -> - y_ExplicitVarSizeWithFlags_Values[q2] < y_ExplicitVarSizeWithFlags_Values[q2 + 1] - | q2 : int(1..3)]), - and([y_ExplicitVarSizeWithFlags_Flags[q3] = false -> y_ExplicitVarSizeWithFlags_Values[q3] = 2 | q3 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q4] | q4 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q5]) | q5 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q7] < x_ExplicitVarSizeWithDummy[q7 + 1] \/ x_ExplicitVarSizeWithDummy[q7] = 6 - | q7 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q8] = 6 -> x_ExplicitVarSizeWithDummy[q8 + 1] = 6 | q8 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q9] != 6) | q9 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q12] != 6 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q12]] | q12 : int(1..4)]), - and([x_Occurrence[q13] -> - or([x_ExplicitVarSizeWithDummy[q15] != 6 /\ x_ExplicitVarSizeWithDummy[q15] = q13 | q15 : int(1..4)]) - | q13 : int(2..5)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_1_4_3_1-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_1_4_3_1-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_4_3_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_1_4_3_1-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_1_4_3_1-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_4_3_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_1_4_3_1.eprime b/tests/exhaustive/basic/set09/expected/model_1_4_3_1.eprime deleted file mode 100644 index 2c2cd8735b..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_4_3_1.eprime +++ /dev/null @@ -1,39 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(2..5)] of bool -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_Occurrence: matrix indexed by [int(2..5)] of bool -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_Occurrence, y_Occurrence, - y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values] -such that - and([x_Occurrence[i] /\ y_ExplicitVarSizeWithFlags_Flags[q21] -> i + 2 = y_ExplicitVarSizeWithFlags_Values[q21] - | i : int(2..5), q21 : int(1..4)]), - 1 <= sum([toInt(x_Occurrence[q1]) | q1 : int(2..5)]), - and([y_ExplicitVarSizeWithFlags_Flags[q2 + 1] -> - y_ExplicitVarSizeWithFlags_Values[q2] < y_ExplicitVarSizeWithFlags_Values[q2 + 1] - | q2 : int(1..3)]), - and([y_ExplicitVarSizeWithFlags_Flags[q3] = false -> y_ExplicitVarSizeWithFlags_Values[q3] = 2 | q3 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q4] | q4 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q5]) | q5 : int(1..4)]), - and([q7 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q7] < x_ExplicitVarSizeWithMarker_Values[q7 + 1] - | q7 : int(1..3)]), - and([q8 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q8] = 2 | q8 : int(1..4)]), - 1 <= x_ExplicitVarSizeWithMarker_Marker, - and([q11 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q11]] - | q11 : int(1..4)]), - and([x_Occurrence[q12] -> - or([q14 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q14] = q12 - | q14 : int(1..4)]) - | q12 : int(2..5)]), - 1 <= sum([toInt(y_Occurrence[q15]) | q15 : int(2..5)]), - and([y_Occurrence[q16] -> - or([y_ExplicitVarSizeWithFlags_Flags[q18] /\ y_ExplicitVarSizeWithFlags_Values[q18] = q16 | q18 : int(1..4)]) - | q16 : int(2..5)]), - and([y_ExplicitVarSizeWithFlags_Flags[q20] -> y_Occurrence[y_ExplicitVarSizeWithFlags_Values[q20]] - | q20 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_1_4_3_2-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_1_4_3_2-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_4_3_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_1_4_3_2-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_1_4_3_2-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_4_3_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_1_4_3_2.eprime b/tests/exhaustive/basic/set09/expected/model_1_4_3_2.eprime deleted file mode 100644 index dca70c6bd1..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_4_3_2.eprime +++ /dev/null @@ -1,47 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(2..5)] of bool -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_Occurrence, y_ExplicitVarSizeWithDummy, - y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values] -such that - and([x_Occurrence[i] /\ y_ExplicitVarSizeWithFlags_Flags[q27] -> i + 2 = y_ExplicitVarSizeWithFlags_Values[q27] - | i : int(2..5), q27 : int(1..4)]), - 1 <= sum([toInt(x_Occurrence[q1]) | q1 : int(2..5)]), - and([y_ExplicitVarSizeWithFlags_Flags[q2 + 1] -> - y_ExplicitVarSizeWithFlags_Values[q2] < y_ExplicitVarSizeWithFlags_Values[q2 + 1] - | q2 : int(1..3)]), - and([y_ExplicitVarSizeWithFlags_Flags[q3] = false -> y_ExplicitVarSizeWithFlags_Values[q3] = 2 | q3 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q4] | q4 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q5]) | q5 : int(1..4)]), - and([q7 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q7] < x_ExplicitVarSizeWithMarker_Values[q7 + 1] - | q7 : int(1..3)]), - and([q8 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q8] = 2 | q8 : int(1..4)]), - 1 <= x_ExplicitVarSizeWithMarker_Marker, - and([q11 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q11]] - | q11 : int(1..4)]), - and([x_Occurrence[q12] -> - or([q14 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q14] = q12 - | q14 : int(1..4)]) - | q12 : int(2..5)]), - and([y_ExplicitVarSizeWithDummy[q15] < y_ExplicitVarSizeWithDummy[q15 + 1] \/ y_ExplicitVarSizeWithDummy[q15] = 6 - | q15 : int(1..3)]), - and([y_ExplicitVarSizeWithDummy[q16] = 6 -> y_ExplicitVarSizeWithDummy[q16 + 1] = 6 | q16 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q17] != 6) | q17 : int(1..4)]), - and([y_ExplicitVarSizeWithDummy[q20] != 6 -> - or([y_ExplicitVarSizeWithFlags_Flags[q22] /\ - y_ExplicitVarSizeWithFlags_Values[q22] = y_ExplicitVarSizeWithDummy[q20] - | q22 : int(1..4)]) - | q20 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q24] -> - or([y_ExplicitVarSizeWithDummy[q26] != 6 /\ - y_ExplicitVarSizeWithDummy[q26] = y_ExplicitVarSizeWithFlags_Values[q24] - | q26 : int(1..4)]) - | q24 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_1_4_3_3-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_1_4_3_3-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_4_3_3-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_1_4_3_3-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_1_4_3_3-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_4_3_3-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_1_4_3_3.eprime b/tests/exhaustive/basic/set09/expected/model_1_4_3_3.eprime deleted file mode 100644 index bd28a832b9..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_4_3_3.eprime +++ /dev/null @@ -1,50 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(2..5)] of bool -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_ExplicitVarSizeWithMarker_Marker: int(0..4) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_Occurrence, - y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithFlags_Flags, - y_ExplicitVarSizeWithFlags_Values] -such that - and([x_Occurrence[i] /\ y_ExplicitVarSizeWithFlags_Flags[q26] -> i + 2 = y_ExplicitVarSizeWithFlags_Values[q26] - | i : int(2..5), q26 : int(1..4)]), - 1 <= sum([toInt(x_Occurrence[q1]) | q1 : int(2..5)]), - and([y_ExplicitVarSizeWithFlags_Flags[q2 + 1] -> - y_ExplicitVarSizeWithFlags_Values[q2] < y_ExplicitVarSizeWithFlags_Values[q2 + 1] - | q2 : int(1..3)]), - and([y_ExplicitVarSizeWithFlags_Flags[q3] = false -> y_ExplicitVarSizeWithFlags_Values[q3] = 2 | q3 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q4] | q4 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q5]) | q5 : int(1..4)]), - and([q7 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q7] < x_ExplicitVarSizeWithMarker_Values[q7 + 1] - | q7 : int(1..3)]), - and([q8 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q8] = 2 | q8 : int(1..4)]), - 1 <= x_ExplicitVarSizeWithMarker_Marker, - and([q11 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q11]] - | q11 : int(1..4)]), - and([x_Occurrence[q12] -> - or([q14 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q14] = q12 - | q14 : int(1..4)]) - | q12 : int(2..5)]), - and([q15 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> - y_ExplicitVarSizeWithMarker_Values[q15] < y_ExplicitVarSizeWithMarker_Values[q15 + 1] - | q15 : int(1..3)]), - and([q16 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q16] = 2 | q16 : int(1..4)]), - 1 <= y_ExplicitVarSizeWithMarker_Marker, - and([q19 <= y_ExplicitVarSizeWithMarker_Marker -> - or([y_ExplicitVarSizeWithFlags_Flags[q21] /\ - y_ExplicitVarSizeWithFlags_Values[q21] = y_ExplicitVarSizeWithMarker_Values[q19] - | q21 : int(1..4)]) - | q19 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q23] -> - or([q25 <= y_ExplicitVarSizeWithMarker_Marker /\ - y_ExplicitVarSizeWithMarker_Values[q25] = y_ExplicitVarSizeWithFlags_Values[q23] - | q25 : int(1..4)]) - | q23 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_1_4_3_4-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_1_4_3_4-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_4_3_4-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_1_4_3_4-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_1_4_3_4-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_4_3_4-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_1_4_3_4.eprime b/tests/exhaustive/basic/set09/expected/model_1_4_3_4.eprime deleted file mode 100644 index 276806a903..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_4_3_4.eprime +++ /dev/null @@ -1,32 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(2..5)] of bool -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_Occurrence, - y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values] -such that - and([x_Occurrence[i] /\ y_ExplicitVarSizeWithFlags_Flags[q15] -> i + 2 = y_ExplicitVarSizeWithFlags_Values[q15] - | i : int(2..5), q15 : int(1..4)]), - 1 <= sum([toInt(x_Occurrence[q1]) | q1 : int(2..5)]), - and([y_ExplicitVarSizeWithFlags_Flags[q2 + 1] -> - y_ExplicitVarSizeWithFlags_Values[q2] < y_ExplicitVarSizeWithFlags_Values[q2 + 1] - | q2 : int(1..3)]), - and([y_ExplicitVarSizeWithFlags_Flags[q3] = false -> y_ExplicitVarSizeWithFlags_Values[q3] = 2 | q3 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q4] | q4 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q5]) | q5 : int(1..4)]), - and([q7 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q7] < x_ExplicitVarSizeWithMarker_Values[q7 + 1] - | q7 : int(1..3)]), - and([q8 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q8] = 2 | q8 : int(1..4)]), - 1 <= x_ExplicitVarSizeWithMarker_Marker, - and([q11 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q11]] - | q11 : int(1..4)]), - and([x_Occurrence[q12] -> - or([q14 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q14] = q12 - | q14 : int(1..4)]) - | q12 : int(2..5)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_1_4_4_1-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_1_4_4_1-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_4_4_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_1_4_4_1-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_1_4_4_1-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_4_4_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_1_4_4_1.eprime b/tests/exhaustive/basic/set09/expected/model_1_4_4_1.eprime deleted file mode 100644 index f3dfc3a80b..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_4_4_1.eprime +++ /dev/null @@ -1,39 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(2..5)] of bool -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_Occurrence: matrix indexed by [int(2..5)] of bool -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_Occurrence, y_Occurrence, - y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values] -such that - and([x_Occurrence[i] /\ y_ExplicitVarSizeWithFlags_Flags[q23] -> i + 2 = y_ExplicitVarSizeWithFlags_Values[q23] - | i : int(2..5), q23 : int(1..4)]), - 1 <= sum([toInt(x_Occurrence[q1]) | q1 : int(2..5)]), - and([y_ExplicitVarSizeWithFlags_Flags[q2 + 1] -> - y_ExplicitVarSizeWithFlags_Values[q2] < y_ExplicitVarSizeWithFlags_Values[q2 + 1] - | q2 : int(1..3)]), - and([y_ExplicitVarSizeWithFlags_Flags[q3] = false -> y_ExplicitVarSizeWithFlags_Values[q3] = 2 | q3 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q4] | q4 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q5]) | q5 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q7] < x_ExplicitVarSizeWithFlags_Values[q7 + 1] - | q7 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q8] = false -> x_ExplicitVarSizeWithFlags_Values[q8] = 2 | q8 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q9 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q9] | q9 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q10]) | q10 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q13] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q13]] - | q13 : int(1..4)]), - and([x_Occurrence[q14] -> - or([x_ExplicitVarSizeWithFlags_Flags[q16] /\ x_ExplicitVarSizeWithFlags_Values[q16] = q14 | q16 : int(1..4)]) - | q14 : int(2..5)]), - 1 <= sum([toInt(y_Occurrence[q17]) | q17 : int(2..5)]), - and([y_Occurrence[q18] -> - or([y_ExplicitVarSizeWithFlags_Flags[q20] /\ y_ExplicitVarSizeWithFlags_Values[q20] = q18 | q20 : int(1..4)]) - | q18 : int(2..5)]), - and([y_ExplicitVarSizeWithFlags_Flags[q22] -> y_Occurrence[y_ExplicitVarSizeWithFlags_Values[q22]] - | q22 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_1_4_4_2-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_1_4_4_2-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_4_4_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_1_4_4_2-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_1_4_4_2-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_4_4_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_1_4_4_2.eprime b/tests/exhaustive/basic/set09/expected/model_1_4_4_2.eprime deleted file mode 100644 index 7d3a34561a..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_4_4_2.eprime +++ /dev/null @@ -1,47 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(2..5)] of bool -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_Occurrence, y_ExplicitVarSizeWithDummy, - y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values] -such that - and([x_Occurrence[i] /\ y_ExplicitVarSizeWithFlags_Flags[q29] -> i + 2 = y_ExplicitVarSizeWithFlags_Values[q29] - | i : int(2..5), q29 : int(1..4)]), - 1 <= sum([toInt(x_Occurrence[q1]) | q1 : int(2..5)]), - and([y_ExplicitVarSizeWithFlags_Flags[q2 + 1] -> - y_ExplicitVarSizeWithFlags_Values[q2] < y_ExplicitVarSizeWithFlags_Values[q2 + 1] - | q2 : int(1..3)]), - and([y_ExplicitVarSizeWithFlags_Flags[q3] = false -> y_ExplicitVarSizeWithFlags_Values[q3] = 2 | q3 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q4] | q4 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q5]) | q5 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q7] < x_ExplicitVarSizeWithFlags_Values[q7 + 1] - | q7 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q8] = false -> x_ExplicitVarSizeWithFlags_Values[q8] = 2 | q8 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q9 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q9] | q9 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q10]) | q10 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q13] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q13]] - | q13 : int(1..4)]), - and([x_Occurrence[q14] -> - or([x_ExplicitVarSizeWithFlags_Flags[q16] /\ x_ExplicitVarSizeWithFlags_Values[q16] = q14 | q16 : int(1..4)]) - | q14 : int(2..5)]), - and([y_ExplicitVarSizeWithDummy[q17] < y_ExplicitVarSizeWithDummy[q17 + 1] \/ y_ExplicitVarSizeWithDummy[q17] = 6 - | q17 : int(1..3)]), - and([y_ExplicitVarSizeWithDummy[q18] = 6 -> y_ExplicitVarSizeWithDummy[q18 + 1] = 6 | q18 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q19] != 6) | q19 : int(1..4)]), - and([y_ExplicitVarSizeWithDummy[q22] != 6 -> - or([y_ExplicitVarSizeWithFlags_Flags[q24] /\ - y_ExplicitVarSizeWithFlags_Values[q24] = y_ExplicitVarSizeWithDummy[q22] - | q24 : int(1..4)]) - | q22 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q26] -> - or([y_ExplicitVarSizeWithDummy[q28] != 6 /\ - y_ExplicitVarSizeWithDummy[q28] = y_ExplicitVarSizeWithFlags_Values[q26] - | q28 : int(1..4)]) - | q26 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_1_4_4_3-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_1_4_4_3-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_4_4_3-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_1_4_4_3-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_1_4_4_3-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_4_4_3-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_1_4_4_3.eprime b/tests/exhaustive/basic/set09/expected/model_1_4_4_3.eprime deleted file mode 100644 index eeb7266e57..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_4_4_3.eprime +++ /dev/null @@ -1,50 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(2..5)] of bool -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_ExplicitVarSizeWithMarker_Marker: int(0..4) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_Occurrence, - y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithFlags_Flags, - y_ExplicitVarSizeWithFlags_Values] -such that - and([x_Occurrence[i] /\ y_ExplicitVarSizeWithFlags_Flags[q28] -> i + 2 = y_ExplicitVarSizeWithFlags_Values[q28] - | i : int(2..5), q28 : int(1..4)]), - 1 <= sum([toInt(x_Occurrence[q1]) | q1 : int(2..5)]), - and([y_ExplicitVarSizeWithFlags_Flags[q2 + 1] -> - y_ExplicitVarSizeWithFlags_Values[q2] < y_ExplicitVarSizeWithFlags_Values[q2 + 1] - | q2 : int(1..3)]), - and([y_ExplicitVarSizeWithFlags_Flags[q3] = false -> y_ExplicitVarSizeWithFlags_Values[q3] = 2 | q3 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q4] | q4 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q5]) | q5 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q7] < x_ExplicitVarSizeWithFlags_Values[q7 + 1] - | q7 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q8] = false -> x_ExplicitVarSizeWithFlags_Values[q8] = 2 | q8 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q9 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q9] | q9 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q10]) | q10 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q13] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q13]] - | q13 : int(1..4)]), - and([x_Occurrence[q14] -> - or([x_ExplicitVarSizeWithFlags_Flags[q16] /\ x_ExplicitVarSizeWithFlags_Values[q16] = q14 | q16 : int(1..4)]) - | q14 : int(2..5)]), - and([q17 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> - y_ExplicitVarSizeWithMarker_Values[q17] < y_ExplicitVarSizeWithMarker_Values[q17 + 1] - | q17 : int(1..3)]), - and([q18 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q18] = 2 | q18 : int(1..4)]), - 1 <= y_ExplicitVarSizeWithMarker_Marker, - and([q21 <= y_ExplicitVarSizeWithMarker_Marker -> - or([y_ExplicitVarSizeWithFlags_Flags[q23] /\ - y_ExplicitVarSizeWithFlags_Values[q23] = y_ExplicitVarSizeWithMarker_Values[q21] - | q23 : int(1..4)]) - | q21 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q25] -> - or([q27 <= y_ExplicitVarSizeWithMarker_Marker /\ - y_ExplicitVarSizeWithMarker_Values[q27] = y_ExplicitVarSizeWithFlags_Values[q25] - | q27 : int(1..4)]) - | q25 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_1_4_4_4-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_1_4_4_4-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_4_4_4-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_1_4_4_4-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_1_4_4_4-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_4_4_4-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_1_4_4_4.eprime b/tests/exhaustive/basic/set09/expected/model_1_4_4_4.eprime deleted file mode 100644 index f0669c2cb4..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_1_4_4_4.eprime +++ /dev/null @@ -1,32 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(2..5)] of bool -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_Occurrence, - y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values] -such that - and([x_Occurrence[i] /\ y_ExplicitVarSizeWithFlags_Flags[q17] -> i + 2 = y_ExplicitVarSizeWithFlags_Values[q17] - | i : int(2..5), q17 : int(1..4)]), - 1 <= sum([toInt(x_Occurrence[q1]) | q1 : int(2..5)]), - and([y_ExplicitVarSizeWithFlags_Flags[q2 + 1] -> - y_ExplicitVarSizeWithFlags_Values[q2] < y_ExplicitVarSizeWithFlags_Values[q2 + 1] - | q2 : int(1..3)]), - and([y_ExplicitVarSizeWithFlags_Flags[q3] = false -> y_ExplicitVarSizeWithFlags_Values[q3] = 2 | q3 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q4] | q4 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q5]) | q5 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q7] < x_ExplicitVarSizeWithFlags_Values[q7 + 1] - | q7 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q8] = false -> x_ExplicitVarSizeWithFlags_Values[q8] = 2 | q8 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q9 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q9] | q9 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q10]) | q10 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q13] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q13]] - | q13 : int(1..4)]), - and([x_Occurrence[q14] -> - or([x_ExplicitVarSizeWithFlags_Flags[q16] /\ x_ExplicitVarSizeWithFlags_Values[q16] = q14 | q16 : int(1..4)]) - | q14 : int(2..5)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_2_1_1_1-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_2_1_1_1-solution000001.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_1_1_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_2_1_1_1-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_2_1_1_1-solution000002.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_1_1_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_2_1_1_1.eprime b/tests/exhaustive/basic/set09/expected/model_2_1_1_1.eprime deleted file mode 100644 index 761535fe98..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_1_1_1.eprime +++ /dev/null @@ -1,20 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -find x_Occurrence: matrix indexed by [int(2..5)] of bool -find y_Occurrence: matrix indexed by [int(2..5)] of bool -branching on [x_Occurrence, x_ExplicitVarSizeWithDummy, y_Occurrence] -such that - and([x_ExplicitVarSizeWithDummy[q12] != 6 /\ y_Occurrence[j] -> x_ExplicitVarSizeWithDummy[q12] + 2 = j - | q12 : int(1..4), j : int(2..5)]), - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 6 - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q2] = 6 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 6 | q2 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 6) | q3 : int(1..4)]), - 1 <= sum([toInt(y_Occurrence[q5]) | q5 : int(2..5)]), - 1 <= sum([toInt(x_Occurrence[q6]) | q6 : int(2..5)]), - and([x_Occurrence[q7] -> - or([x_ExplicitVarSizeWithDummy[q9] != 6 /\ x_ExplicitVarSizeWithDummy[q9] = q7 | q9 : int(1..4)]) - | q7 : int(2..5)]), - and([x_ExplicitVarSizeWithDummy[q11] != 6 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q11]] | q11 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_2_1_1_2-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_2_1_1_2-solution000001.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_1_1_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_2_1_1_2-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_2_1_1_2-solution000002.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_1_1_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_2_1_1_2.eprime b/tests/exhaustive/basic/set09/expected/model_2_1_1_2.eprime deleted file mode 100644 index b519538402..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_1_1_2.eprime +++ /dev/null @@ -1,29 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -find x_Occurrence: matrix indexed by [int(2..5)] of bool -find y_Occurrence: matrix indexed by [int(2..5)] of bool -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -branching on [x_Occurrence, x_ExplicitVarSizeWithDummy, y_ExplicitVarSizeWithDummy, y_Occurrence] -such that - and([x_ExplicitVarSizeWithDummy[q21] != 6 /\ y_Occurrence[j] -> x_ExplicitVarSizeWithDummy[q21] + 2 = j - | q21 : int(1..4), j : int(2..5)]), - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 6 - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q2] = 6 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 6 | q2 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 6) | q3 : int(1..4)]), - 1 <= sum([toInt(y_Occurrence[q5]) | q5 : int(2..5)]), - 1 <= sum([toInt(x_Occurrence[q6]) | q6 : int(2..5)]), - and([x_Occurrence[q16] -> - or([x_ExplicitVarSizeWithDummy[q18] != 6 /\ x_ExplicitVarSizeWithDummy[q18] = q16 | q18 : int(1..4)]) - | q16 : int(2..5)]), - and([x_ExplicitVarSizeWithDummy[q20] != 6 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q20]] | q20 : int(1..4)]), - and([y_ExplicitVarSizeWithDummy[q7] < y_ExplicitVarSizeWithDummy[q7 + 1] \/ y_ExplicitVarSizeWithDummy[q7] = 6 - | q7 : int(1..3)]), - and([y_ExplicitVarSizeWithDummy[q8] = 6 -> y_ExplicitVarSizeWithDummy[q8 + 1] = 6 | q8 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q9] != 6) | q9 : int(1..4)]), - and([y_ExplicitVarSizeWithDummy[q12] != 6 -> y_Occurrence[y_ExplicitVarSizeWithDummy[q12]] | q12 : int(1..4)]), - and([y_Occurrence[q13] -> - or([y_ExplicitVarSizeWithDummy[q15] != 6 /\ y_ExplicitVarSizeWithDummy[q15] = q13 | q15 : int(1..4)]) - | q13 : int(2..5)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_2_1_1_3-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_2_1_1_3-solution000001.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_1_1_3-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_2_1_1_3-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_2_1_1_3-solution000002.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_1_1_3-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_2_1_1_3.eprime b/tests/exhaustive/basic/set09/expected/model_2_1_1_3.eprime deleted file mode 100644 index 0726845331..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_1_1_3.eprime +++ /dev/null @@ -1,35 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -find x_Occurrence: matrix indexed by [int(2..5)] of bool -find y_Occurrence: matrix indexed by [int(2..5)] of bool -find y_ExplicitVarSizeWithMarker_Marker: int(0..4) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -branching on - [x_Occurrence, x_ExplicitVarSizeWithDummy, y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values, - y_Occurrence] -such that - and([x_ExplicitVarSizeWithDummy[q20] != 6 /\ y_Occurrence[j] -> x_ExplicitVarSizeWithDummy[q20] + 2 = j - | q20 : int(1..4), j : int(2..5)]), - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 6 - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q2] = 6 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 6 | q2 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 6) | q3 : int(1..4)]), - 1 <= sum([toInt(y_Occurrence[q5]) | q5 : int(2..5)]), - 1 <= sum([toInt(x_Occurrence[q6]) | q6 : int(2..5)]), - and([x_Occurrence[q15] -> - or([x_ExplicitVarSizeWithDummy[q17] != 6 /\ x_ExplicitVarSizeWithDummy[q17] = q15 | q17 : int(1..4)]) - | q15 : int(2..5)]), - and([x_ExplicitVarSizeWithDummy[q19] != 6 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q19]] | q19 : int(1..4)]), - and([q7 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> - y_ExplicitVarSizeWithMarker_Values[q7] < y_ExplicitVarSizeWithMarker_Values[q7 + 1] - | q7 : int(1..3)]), - and([q8 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q8] = 2 | q8 : int(1..4)]), - 1 <= y_ExplicitVarSizeWithMarker_Marker, - and([q11 <= y_ExplicitVarSizeWithMarker_Marker -> y_Occurrence[y_ExplicitVarSizeWithMarker_Values[q11]] - | q11 : int(1..4)]), - and([y_Occurrence[q12] -> - or([q14 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[q14] = q12 - | q14 : int(1..4)]) - | q12 : int(2..5)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_2_1_1_4-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_2_1_1_4-solution000001.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_1_1_4-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_2_1_1_4-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_2_1_1_4-solution000002.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_1_1_4-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_2_1_1_4.eprime b/tests/exhaustive/basic/set09/expected/model_2_1_1_4.eprime deleted file mode 100644 index 9d5ebd556d..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_1_1_4.eprime +++ /dev/null @@ -1,35 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -find x_Occurrence: matrix indexed by [int(2..5)] of bool -find y_Occurrence: matrix indexed by [int(2..5)] of bool -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -branching on - [x_Occurrence, x_ExplicitVarSizeWithDummy, y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values, - y_Occurrence] -such that - and([x_ExplicitVarSizeWithDummy[q22] != 6 /\ y_Occurrence[j] -> x_ExplicitVarSizeWithDummy[q22] + 2 = j - | q22 : int(1..4), j : int(2..5)]), - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 6 - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q2] = 6 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 6 | q2 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 6) | q3 : int(1..4)]), - 1 <= sum([toInt(y_Occurrence[q5]) | q5 : int(2..5)]), - 1 <= sum([toInt(x_Occurrence[q6]) | q6 : int(2..5)]), - and([x_Occurrence[q17] -> - or([x_ExplicitVarSizeWithDummy[q19] != 6 /\ x_ExplicitVarSizeWithDummy[q19] = q17 | q19 : int(1..4)]) - | q17 : int(2..5)]), - and([x_ExplicitVarSizeWithDummy[q21] != 6 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q21]] | q21 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> - y_ExplicitVarSizeWithFlags_Values[q7] < y_ExplicitVarSizeWithFlags_Values[q7 + 1] - | q7 : int(1..3)]), - and([y_ExplicitVarSizeWithFlags_Flags[q8] = false -> y_ExplicitVarSizeWithFlags_Values[q8] = 2 | q8 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q9 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q9] | q9 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q10]) | q10 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q13] -> y_Occurrence[y_ExplicitVarSizeWithFlags_Values[q13]] - | q13 : int(1..4)]), - and([y_Occurrence[q14] -> - or([y_ExplicitVarSizeWithFlags_Flags[q16] /\ y_ExplicitVarSizeWithFlags_Values[q16] = q14 | q16 : int(1..4)]) - | q14 : int(2..5)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_2_1_2_1-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_2_1_2_1-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_1_2_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_2_1_2_1-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_2_1_2_1-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_1_2_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_2_1_2_1.eprime b/tests/exhaustive/basic/set09/expected/model_2_1_2_1.eprime deleted file mode 100644 index 5a90ec4c66..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_1_2_1.eprime +++ /dev/null @@ -1,14 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -find y_Occurrence: matrix indexed by [int(2..5)] of bool -branching on [x_ExplicitVarSizeWithDummy, y_Occurrence] -such that - and([x_ExplicitVarSizeWithDummy[q6] != 6 /\ y_Occurrence[j] -> x_ExplicitVarSizeWithDummy[q6] + 2 = j - | q6 : int(1..4), j : int(2..5)]), - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 6 - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q2] = 6 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 6 | q2 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 6) | q3 : int(1..4)]), - 1 <= sum([toInt(y_Occurrence[q5]) | q5 : int(2..5)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_2_1_2_2-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_2_1_2_2-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_1_2_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_2_1_2_2-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_2_1_2_2-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_1_2_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_2_1_2_2.eprime b/tests/exhaustive/basic/set09/expected/model_2_1_2_2.eprime deleted file mode 100644 index 8811fd557f..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_1_2_2.eprime +++ /dev/null @@ -1,23 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -find y_Occurrence: matrix indexed by [int(2..5)] of bool -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -branching on [x_ExplicitVarSizeWithDummy, y_ExplicitVarSizeWithDummy, y_Occurrence] -such that - and([x_ExplicitVarSizeWithDummy[q15] != 6 /\ y_Occurrence[j] -> x_ExplicitVarSizeWithDummy[q15] + 2 = j - | q15 : int(1..4), j : int(2..5)]), - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 6 - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q2] = 6 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 6 | q2 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 6) | q3 : int(1..4)]), - 1 <= sum([toInt(y_Occurrence[q5]) | q5 : int(2..5)]), - and([y_ExplicitVarSizeWithDummy[q6] < y_ExplicitVarSizeWithDummy[q6 + 1] \/ y_ExplicitVarSizeWithDummy[q6] = 6 - | q6 : int(1..3)]), - and([y_ExplicitVarSizeWithDummy[q7] = 6 -> y_ExplicitVarSizeWithDummy[q7 + 1] = 6 | q7 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q8] != 6) | q8 : int(1..4)]), - and([y_ExplicitVarSizeWithDummy[q11] != 6 -> y_Occurrence[y_ExplicitVarSizeWithDummy[q11]] | q11 : int(1..4)]), - and([y_Occurrence[q12] -> - or([y_ExplicitVarSizeWithDummy[q14] != 6 /\ y_ExplicitVarSizeWithDummy[q14] = q12 | q14 : int(1..4)]) - | q12 : int(2..5)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_2_1_2_3-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_2_1_2_3-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_1_2_3-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_2_1_2_3-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_2_1_2_3-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_1_2_3-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_2_1_2_3.eprime b/tests/exhaustive/basic/set09/expected/model_2_1_2_3.eprime deleted file mode 100644 index 5f0bbfbbee..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_1_2_3.eprime +++ /dev/null @@ -1,28 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -find y_Occurrence: matrix indexed by [int(2..5)] of bool -find y_ExplicitVarSizeWithMarker_Marker: int(0..4) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -branching on - [x_ExplicitVarSizeWithDummy, y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values, y_Occurrence] -such that - and([x_ExplicitVarSizeWithDummy[q14] != 6 /\ y_Occurrence[j] -> x_ExplicitVarSizeWithDummy[q14] + 2 = j - | q14 : int(1..4), j : int(2..5)]), - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 6 - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q2] = 6 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 6 | q2 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 6) | q3 : int(1..4)]), - 1 <= sum([toInt(y_Occurrence[q5]) | q5 : int(2..5)]), - and([q6 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> - y_ExplicitVarSizeWithMarker_Values[q6] < y_ExplicitVarSizeWithMarker_Values[q6 + 1] - | q6 : int(1..3)]), - and([q7 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q7] = 2 | q7 : int(1..4)]), - 1 <= y_ExplicitVarSizeWithMarker_Marker, - and([q10 <= y_ExplicitVarSizeWithMarker_Marker -> y_Occurrence[y_ExplicitVarSizeWithMarker_Values[q10]] - | q10 : int(1..4)]), - and([y_Occurrence[q11] -> - or([q13 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[q13] = q11 - | q13 : int(1..4)]) - | q11 : int(2..5)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_2_1_2_4-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_2_1_2_4-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_1_2_4-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_2_1_2_4-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_2_1_2_4-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_1_2_4-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_2_1_2_4.eprime b/tests/exhaustive/basic/set09/expected/model_2_1_2_4.eprime deleted file mode 100644 index d9eedcd6c7..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_1_2_4.eprime +++ /dev/null @@ -1,28 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -find y_Occurrence: matrix indexed by [int(2..5)] of bool -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -branching on - [x_ExplicitVarSizeWithDummy, y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values, y_Occurrence] -such that - and([x_ExplicitVarSizeWithDummy[q16] != 6 /\ y_Occurrence[j] -> x_ExplicitVarSizeWithDummy[q16] + 2 = j - | q16 : int(1..4), j : int(2..5)]), - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 6 - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q2] = 6 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 6 | q2 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 6) | q3 : int(1..4)]), - 1 <= sum([toInt(y_Occurrence[q5]) | q5 : int(2..5)]), - and([y_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> - y_ExplicitVarSizeWithFlags_Values[q6] < y_ExplicitVarSizeWithFlags_Values[q6 + 1] - | q6 : int(1..3)]), - and([y_ExplicitVarSizeWithFlags_Flags[q7] = false -> y_ExplicitVarSizeWithFlags_Values[q7] = 2 | q7 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q8 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q8] | q8 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q9]) | q9 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q12] -> y_Occurrence[y_ExplicitVarSizeWithFlags_Values[q12]] - | q12 : int(1..4)]), - and([y_Occurrence[q13] -> - or([y_ExplicitVarSizeWithFlags_Flags[q15] /\ y_ExplicitVarSizeWithFlags_Values[q15] = q13 | q15 : int(1..4)]) - | q13 : int(2..5)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_2_1_3_1-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_2_1_3_1-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_1_3_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_2_1_3_1-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_2_1_3_1-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_1_3_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_2_1_3_1.eprime b/tests/exhaustive/basic/set09/expected/model_2_1_3_1.eprime deleted file mode 100644 index 65dba9f00f..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_1_3_1.eprime +++ /dev/null @@ -1,32 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_Occurrence: matrix indexed by [int(2..5)] of bool -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy, y_Occurrence] -such that - and([x_ExplicitVarSizeWithDummy[q17] != 6 /\ y_Occurrence[j] -> x_ExplicitVarSizeWithDummy[q17] + 2 = j - | q17 : int(1..4), j : int(2..5)]), - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 6 - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q2] = 6 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 6 | q2 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 6) | q3 : int(1..4)]), - 1 <= sum([toInt(y_Occurrence[q5]) | q5 : int(2..5)]), - and([q6 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q6] < x_ExplicitVarSizeWithMarker_Values[q6 + 1] - | q6 : int(1..3)]), - and([q7 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q7] = 2 | q7 : int(1..4)]), - 1 <= x_ExplicitVarSizeWithMarker_Marker, - and([q10 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q12] != 6 /\ - x_ExplicitVarSizeWithDummy[q12] = x_ExplicitVarSizeWithMarker_Values[q10] - | q12 : int(1..4)]) - | q10 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q14] != 6 -> - or([q16 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q16] = x_ExplicitVarSizeWithDummy[q14] - | q16 : int(1..4)]) - | q14 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_2_1_3_2-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_2_1_3_2-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_1_3_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_2_1_3_2-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_2_1_3_2-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_1_3_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_2_1_3_2.eprime b/tests/exhaustive/basic/set09/expected/model_2_1_3_2.eprime deleted file mode 100644 index d2382f30b2..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_1_3_2.eprime +++ /dev/null @@ -1,42 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_Occurrence: matrix indexed by [int(2..5)] of bool -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy, - y_ExplicitVarSizeWithDummy, y_Occurrence] -such that - and([x_ExplicitVarSizeWithDummy[q26] != 6 /\ y_Occurrence[j] -> x_ExplicitVarSizeWithDummy[q26] + 2 = j - | q26 : int(1..4), j : int(2..5)]), - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 6 - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q2] = 6 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 6 | q2 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 6) | q3 : int(1..4)]), - 1 <= sum([toInt(y_Occurrence[q5]) | q5 : int(2..5)]), - and([q6 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q6] < x_ExplicitVarSizeWithMarker_Values[q6 + 1] - | q6 : int(1..3)]), - and([q7 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q7] = 2 | q7 : int(1..4)]), - 1 <= x_ExplicitVarSizeWithMarker_Marker, - and([q10 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q12] != 6 /\ - x_ExplicitVarSizeWithDummy[q12] = x_ExplicitVarSizeWithMarker_Values[q10] - | q12 : int(1..4)]) - | q10 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q14] != 6 -> - or([q16 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q16] = x_ExplicitVarSizeWithDummy[q14] - | q16 : int(1..4)]) - | q14 : int(1..4)]), - and([y_ExplicitVarSizeWithDummy[q17] < y_ExplicitVarSizeWithDummy[q17 + 1] \/ y_ExplicitVarSizeWithDummy[q17] = 6 - | q17 : int(1..3)]), - and([y_ExplicitVarSizeWithDummy[q18] = 6 -> y_ExplicitVarSizeWithDummy[q18 + 1] = 6 | q18 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q19] != 6) | q19 : int(1..4)]), - and([y_ExplicitVarSizeWithDummy[q22] != 6 -> y_Occurrence[y_ExplicitVarSizeWithDummy[q22]] | q22 : int(1..4)]), - and([y_Occurrence[q23] -> - or([y_ExplicitVarSizeWithDummy[q25] != 6 /\ y_ExplicitVarSizeWithDummy[q25] = q23 | q25 : int(1..4)]) - | q23 : int(2..5)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_2_1_3_3-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_2_1_3_3-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_1_3_3-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_2_1_3_3-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_2_1_3_3-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_1_3_3-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_2_1_3_3.eprime b/tests/exhaustive/basic/set09/expected/model_2_1_3_3.eprime deleted file mode 100644 index 1ab91b53e0..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_1_3_3.eprime +++ /dev/null @@ -1,46 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_Occurrence: matrix indexed by [int(2..5)] of bool -find y_ExplicitVarSizeWithMarker_Marker: int(0..4) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy, - y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values, y_Occurrence] -such that - and([x_ExplicitVarSizeWithDummy[q25] != 6 /\ y_Occurrence[j] -> x_ExplicitVarSizeWithDummy[q25] + 2 = j - | q25 : int(1..4), j : int(2..5)]), - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 6 - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q2] = 6 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 6 | q2 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 6) | q3 : int(1..4)]), - 1 <= sum([toInt(y_Occurrence[q5]) | q5 : int(2..5)]), - and([q6 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q6] < x_ExplicitVarSizeWithMarker_Values[q6 + 1] - | q6 : int(1..3)]), - and([q7 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q7] = 2 | q7 : int(1..4)]), - 1 <= x_ExplicitVarSizeWithMarker_Marker, - and([q10 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q12] != 6 /\ - x_ExplicitVarSizeWithDummy[q12] = x_ExplicitVarSizeWithMarker_Values[q10] - | q12 : int(1..4)]) - | q10 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q14] != 6 -> - or([q16 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q16] = x_ExplicitVarSizeWithDummy[q14] - | q16 : int(1..4)]) - | q14 : int(1..4)]), - and([q17 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> - y_ExplicitVarSizeWithMarker_Values[q17] < y_ExplicitVarSizeWithMarker_Values[q17 + 1] - | q17 : int(1..3)]), - and([q18 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q18] = 2 | q18 : int(1..4)]), - 1 <= y_ExplicitVarSizeWithMarker_Marker, - and([q21 <= y_ExplicitVarSizeWithMarker_Marker -> y_Occurrence[y_ExplicitVarSizeWithMarker_Values[q21]] - | q21 : int(1..4)]), - and([y_Occurrence[q22] -> - or([q24 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[q24] = q22 - | q24 : int(1..4)]) - | q22 : int(2..5)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_2_1_3_4-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_2_1_3_4-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_1_3_4-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_2_1_3_4-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_2_1_3_4-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_1_3_4-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_2_1_3_4.eprime b/tests/exhaustive/basic/set09/expected/model_2_1_3_4.eprime deleted file mode 100644 index 43ccdc1260..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_1_3_4.eprime +++ /dev/null @@ -1,47 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_Occurrence: matrix indexed by [int(2..5)] of bool -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy, - y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values, y_Occurrence] -such that - and([x_ExplicitVarSizeWithDummy[q27] != 6 /\ y_Occurrence[j] -> x_ExplicitVarSizeWithDummy[q27] + 2 = j - | q27 : int(1..4), j : int(2..5)]), - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 6 - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q2] = 6 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 6 | q2 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 6) | q3 : int(1..4)]), - 1 <= sum([toInt(y_Occurrence[q5]) | q5 : int(2..5)]), - and([q6 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q6] < x_ExplicitVarSizeWithMarker_Values[q6 + 1] - | q6 : int(1..3)]), - and([q7 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q7] = 2 | q7 : int(1..4)]), - 1 <= x_ExplicitVarSizeWithMarker_Marker, - and([q10 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q12] != 6 /\ - x_ExplicitVarSizeWithDummy[q12] = x_ExplicitVarSizeWithMarker_Values[q10] - | q12 : int(1..4)]) - | q10 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q14] != 6 -> - or([q16 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q16] = x_ExplicitVarSizeWithDummy[q14] - | q16 : int(1..4)]) - | q14 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q17 + 1] -> - y_ExplicitVarSizeWithFlags_Values[q17] < y_ExplicitVarSizeWithFlags_Values[q17 + 1] - | q17 : int(1..3)]), - and([y_ExplicitVarSizeWithFlags_Flags[q18] = false -> y_ExplicitVarSizeWithFlags_Values[q18] = 2 - | q18 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q19 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q19] | q19 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q20]) | q20 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q23] -> y_Occurrence[y_ExplicitVarSizeWithFlags_Values[q23]] - | q23 : int(1..4)]), - and([y_Occurrence[q24] -> - or([y_ExplicitVarSizeWithFlags_Flags[q26] /\ y_ExplicitVarSizeWithFlags_Values[q26] = q24 | q26 : int(1..4)]) - | q24 : int(2..5)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_2_1_4_1-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_2_1_4_1-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_1_4_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_2_1_4_1-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_2_1_4_1-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_1_4_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_2_1_4_1.eprime b/tests/exhaustive/basic/set09/expected/model_2_1_4_1.eprime deleted file mode 100644 index b726d03c45..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_1_4_1.eprime +++ /dev/null @@ -1,33 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_Occurrence: matrix indexed by [int(2..5)] of bool -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy, y_Occurrence] -such that - and([x_ExplicitVarSizeWithDummy[q19] != 6 /\ y_Occurrence[j] -> x_ExplicitVarSizeWithDummy[q19] + 2 = j - | q19 : int(1..4), j : int(2..5)]), - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 6 - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q2] = 6 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 6 | q2 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 6) | q3 : int(1..4)]), - 1 <= sum([toInt(y_Occurrence[q5]) | q5 : int(2..5)]), - and([x_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q6] < x_ExplicitVarSizeWithFlags_Values[q6 + 1] - | q6 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q7] = false -> x_ExplicitVarSizeWithFlags_Values[q7] = 2 | q7 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q8 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q8] | q8 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q9]) | q9 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q12] -> - or([x_ExplicitVarSizeWithDummy[q14] != 6 /\ - x_ExplicitVarSizeWithDummy[q14] = x_ExplicitVarSizeWithFlags_Values[q12] - | q14 : int(1..4)]) - | q12 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q16] != 6 -> - or([x_ExplicitVarSizeWithFlags_Flags[q18] /\ - x_ExplicitVarSizeWithFlags_Values[q18] = x_ExplicitVarSizeWithDummy[q16] - | q18 : int(1..4)]) - | q16 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_2_1_4_2-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_2_1_4_2-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_1_4_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_2_1_4_2-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_2_1_4_2-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_1_4_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_2_1_4_2.eprime b/tests/exhaustive/basic/set09/expected/model_2_1_4_2.eprime deleted file mode 100644 index 6e2528d6b3..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_1_4_2.eprime +++ /dev/null @@ -1,43 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_Occurrence: matrix indexed by [int(2..5)] of bool -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy, - y_ExplicitVarSizeWithDummy, y_Occurrence] -such that - and([x_ExplicitVarSizeWithDummy[q28] != 6 /\ y_Occurrence[j] -> x_ExplicitVarSizeWithDummy[q28] + 2 = j - | q28 : int(1..4), j : int(2..5)]), - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 6 - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q2] = 6 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 6 | q2 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 6) | q3 : int(1..4)]), - 1 <= sum([toInt(y_Occurrence[q5]) | q5 : int(2..5)]), - and([x_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q6] < x_ExplicitVarSizeWithFlags_Values[q6 + 1] - | q6 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q7] = false -> x_ExplicitVarSizeWithFlags_Values[q7] = 2 | q7 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q8 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q8] | q8 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q9]) | q9 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q12] -> - or([x_ExplicitVarSizeWithDummy[q14] != 6 /\ - x_ExplicitVarSizeWithDummy[q14] = x_ExplicitVarSizeWithFlags_Values[q12] - | q14 : int(1..4)]) - | q12 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q16] != 6 -> - or([x_ExplicitVarSizeWithFlags_Flags[q18] /\ - x_ExplicitVarSizeWithFlags_Values[q18] = x_ExplicitVarSizeWithDummy[q16] - | q18 : int(1..4)]) - | q16 : int(1..4)]), - and([y_ExplicitVarSizeWithDummy[q19] < y_ExplicitVarSizeWithDummy[q19 + 1] \/ y_ExplicitVarSizeWithDummy[q19] = 6 - | q19 : int(1..3)]), - and([y_ExplicitVarSizeWithDummy[q20] = 6 -> y_ExplicitVarSizeWithDummy[q20 + 1] = 6 | q20 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q21] != 6) | q21 : int(1..4)]), - and([y_ExplicitVarSizeWithDummy[q24] != 6 -> y_Occurrence[y_ExplicitVarSizeWithDummy[q24]] | q24 : int(1..4)]), - and([y_Occurrence[q25] -> - or([y_ExplicitVarSizeWithDummy[q27] != 6 /\ y_ExplicitVarSizeWithDummy[q27] = q25 | q27 : int(1..4)]) - | q25 : int(2..5)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_2_1_4_3-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_2_1_4_3-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_1_4_3-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_2_1_4_3-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_2_1_4_3-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_1_4_3-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_2_1_4_3.eprime b/tests/exhaustive/basic/set09/expected/model_2_1_4_3.eprime deleted file mode 100644 index 6517abff37..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_1_4_3.eprime +++ /dev/null @@ -1,47 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_Occurrence: matrix indexed by [int(2..5)] of bool -find y_ExplicitVarSizeWithMarker_Marker: int(0..4) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy, - y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values, y_Occurrence] -such that - and([x_ExplicitVarSizeWithDummy[q27] != 6 /\ y_Occurrence[j] -> x_ExplicitVarSizeWithDummy[q27] + 2 = j - | q27 : int(1..4), j : int(2..5)]), - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 6 - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q2] = 6 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 6 | q2 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 6) | q3 : int(1..4)]), - 1 <= sum([toInt(y_Occurrence[q5]) | q5 : int(2..5)]), - and([x_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q6] < x_ExplicitVarSizeWithFlags_Values[q6 + 1] - | q6 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q7] = false -> x_ExplicitVarSizeWithFlags_Values[q7] = 2 | q7 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q8 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q8] | q8 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q9]) | q9 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q12] -> - or([x_ExplicitVarSizeWithDummy[q14] != 6 /\ - x_ExplicitVarSizeWithDummy[q14] = x_ExplicitVarSizeWithFlags_Values[q12] - | q14 : int(1..4)]) - | q12 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q16] != 6 -> - or([x_ExplicitVarSizeWithFlags_Flags[q18] /\ - x_ExplicitVarSizeWithFlags_Values[q18] = x_ExplicitVarSizeWithDummy[q16] - | q18 : int(1..4)]) - | q16 : int(1..4)]), - and([q19 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> - y_ExplicitVarSizeWithMarker_Values[q19] < y_ExplicitVarSizeWithMarker_Values[q19 + 1] - | q19 : int(1..3)]), - and([q20 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q20] = 2 | q20 : int(1..4)]), - 1 <= y_ExplicitVarSizeWithMarker_Marker, - and([q23 <= y_ExplicitVarSizeWithMarker_Marker -> y_Occurrence[y_ExplicitVarSizeWithMarker_Values[q23]] - | q23 : int(1..4)]), - and([y_Occurrence[q24] -> - or([q26 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[q26] = q24 - | q26 : int(1..4)]) - | q24 : int(2..5)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_2_1_4_4-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_2_1_4_4-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_1_4_4-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_2_1_4_4-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_2_1_4_4-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_1_4_4-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_2_1_4_4.eprime b/tests/exhaustive/basic/set09/expected/model_2_1_4_4.eprime deleted file mode 100644 index a99b49c2ba..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_1_4_4.eprime +++ /dev/null @@ -1,48 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_Occurrence: matrix indexed by [int(2..5)] of bool -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy, - y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values, y_Occurrence] -such that - and([x_ExplicitVarSizeWithDummy[q29] != 6 /\ y_Occurrence[j] -> x_ExplicitVarSizeWithDummy[q29] + 2 = j - | q29 : int(1..4), j : int(2..5)]), - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 6 - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q2] = 6 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 6 | q2 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 6) | q3 : int(1..4)]), - 1 <= sum([toInt(y_Occurrence[q5]) | q5 : int(2..5)]), - and([x_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q6] < x_ExplicitVarSizeWithFlags_Values[q6 + 1] - | q6 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q7] = false -> x_ExplicitVarSizeWithFlags_Values[q7] = 2 | q7 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q8 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q8] | q8 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q9]) | q9 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q12] -> - or([x_ExplicitVarSizeWithDummy[q14] != 6 /\ - x_ExplicitVarSizeWithDummy[q14] = x_ExplicitVarSizeWithFlags_Values[q12] - | q14 : int(1..4)]) - | q12 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q16] != 6 -> - or([x_ExplicitVarSizeWithFlags_Flags[q18] /\ - x_ExplicitVarSizeWithFlags_Values[q18] = x_ExplicitVarSizeWithDummy[q16] - | q18 : int(1..4)]) - | q16 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q19 + 1] -> - y_ExplicitVarSizeWithFlags_Values[q19] < y_ExplicitVarSizeWithFlags_Values[q19 + 1] - | q19 : int(1..3)]), - and([y_ExplicitVarSizeWithFlags_Flags[q20] = false -> y_ExplicitVarSizeWithFlags_Values[q20] = 2 - | q20 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q21 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q21] | q21 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q22]) | q22 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q25] -> y_Occurrence[y_ExplicitVarSizeWithFlags_Values[q25]] - | q25 : int(1..4)]), - and([y_Occurrence[q26] -> - or([y_ExplicitVarSizeWithFlags_Flags[q28] /\ y_ExplicitVarSizeWithFlags_Values[q28] = q26 | q28 : int(1..4)]) - | q26 : int(2..5)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_2_2_1_1-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_2_2_1_1-solution000001.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_2_1_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_2_2_1_1-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_2_2_1_1-solution000002.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_2_1_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_2_2_1_1.eprime b/tests/exhaustive/basic/set09/expected/model_2_2_1_1.eprime deleted file mode 100644 index 6abf3ea8b6..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_2_1_1.eprime +++ /dev/null @@ -1,30 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -find x_Occurrence: matrix indexed by [int(2..5)] of bool -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -find y_Occurrence: matrix indexed by [int(2..5)] of bool -branching on [x_Occurrence, x_ExplicitVarSizeWithDummy, y_Occurrence, y_ExplicitVarSizeWithDummy] -such that - and([x_ExplicitVarSizeWithDummy[q16] != 6 /\ y_ExplicitVarSizeWithDummy[q17] != 6 -> - x_ExplicitVarSizeWithDummy[q16] + 2 = y_ExplicitVarSizeWithDummy[q17] - | q16 : int(1..4), q17 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 6 - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q2] = 6 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 6 | q2 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 6) | q3 : int(1..4)]), - and([y_ExplicitVarSizeWithDummy[q5] < y_ExplicitVarSizeWithDummy[q5 + 1] \/ y_ExplicitVarSizeWithDummy[q5] = 6 - | q5 : int(1..3)]), - and([y_ExplicitVarSizeWithDummy[q6] = 6 -> y_ExplicitVarSizeWithDummy[q6 + 1] = 6 | q6 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q7] != 6) | q7 : int(1..4)]), - 1 <= sum([toInt(x_Occurrence[q9]) | q9 : int(2..5)]), - and([x_Occurrence[q18] -> - or([x_ExplicitVarSizeWithDummy[q20] != 6 /\ x_ExplicitVarSizeWithDummy[q20] = q18 | q20 : int(1..4)]) - | q18 : int(2..5)]), - and([x_ExplicitVarSizeWithDummy[q22] != 6 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q22]] | q22 : int(1..4)]), - 1 <= sum([toInt(y_Occurrence[q10]) | q10 : int(2..5)]), - and([y_Occurrence[q11] -> - or([y_ExplicitVarSizeWithDummy[q13] != 6 /\ y_ExplicitVarSizeWithDummy[q13] = q11 | q13 : int(1..4)]) - | q11 : int(2..5)]), - and([y_ExplicitVarSizeWithDummy[q15] != 6 -> y_Occurrence[y_ExplicitVarSizeWithDummy[q15]] | q15 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_2_2_1_2-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_2_2_1_2-solution000001.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_2_1_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_2_2_1_2-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_2_2_1_2-solution000002.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_2_1_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_2_2_1_2.eprime b/tests/exhaustive/basic/set09/expected/model_2_2_1_2.eprime deleted file mode 100644 index 0b17a9f152..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_2_1_2.eprime +++ /dev/null @@ -1,24 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -find x_Occurrence: matrix indexed by [int(2..5)] of bool -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -branching on [x_Occurrence, x_ExplicitVarSizeWithDummy, y_ExplicitVarSizeWithDummy] -such that - and([x_ExplicitVarSizeWithDummy[q15] != 6 /\ y_ExplicitVarSizeWithDummy[q16] != 6 -> - x_ExplicitVarSizeWithDummy[q15] + 2 = y_ExplicitVarSizeWithDummy[q16] - | q15 : int(1..4), q16 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 6 - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q2] = 6 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 6 | q2 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 6) | q3 : int(1..4)]), - and([y_ExplicitVarSizeWithDummy[q5] < y_ExplicitVarSizeWithDummy[q5 + 1] \/ y_ExplicitVarSizeWithDummy[q5] = 6 - | q5 : int(1..3)]), - and([y_ExplicitVarSizeWithDummy[q6] = 6 -> y_ExplicitVarSizeWithDummy[q6 + 1] = 6 | q6 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q7] != 6) | q7 : int(1..4)]), - 1 <= sum([toInt(x_Occurrence[q9]) | q9 : int(2..5)]), - and([x_Occurrence[q10] -> - or([x_ExplicitVarSizeWithDummy[q12] != 6 /\ x_ExplicitVarSizeWithDummy[q12] = q10 | q12 : int(1..4)]) - | q10 : int(2..5)]), - and([x_ExplicitVarSizeWithDummy[q14] != 6 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q14]] | q14 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_2_2_1_3-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_2_2_1_3-solution000001.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_2_1_3-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_2_2_1_3-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_2_2_1_3-solution000002.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_2_1_3-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_2_2_1_3.eprime b/tests/exhaustive/basic/set09/expected/model_2_2_1_3.eprime deleted file mode 100644 index c40c45e8b1..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_2_1_3.eprime +++ /dev/null @@ -1,43 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -find x_Occurrence: matrix indexed by [int(2..5)] of bool -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -find y_ExplicitVarSizeWithMarker_Marker: int(0..4) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -branching on - [x_Occurrence, x_ExplicitVarSizeWithDummy, y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values, - y_ExplicitVarSizeWithDummy] -such that - and([x_ExplicitVarSizeWithDummy[q26] != 6 /\ y_ExplicitVarSizeWithDummy[q27] != 6 -> - x_ExplicitVarSizeWithDummy[q26] + 2 = y_ExplicitVarSizeWithDummy[q27] - | q26 : int(1..4), q27 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 6 - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q2] = 6 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 6 | q2 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 6) | q3 : int(1..4)]), - and([y_ExplicitVarSizeWithDummy[q5] < y_ExplicitVarSizeWithDummy[q5 + 1] \/ y_ExplicitVarSizeWithDummy[q5] = 6 - | q5 : int(1..3)]), - and([y_ExplicitVarSizeWithDummy[q6] = 6 -> y_ExplicitVarSizeWithDummy[q6 + 1] = 6 | q6 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q7] != 6) | q7 : int(1..4)]), - 1 <= sum([toInt(x_Occurrence[q9]) | q9 : int(2..5)]), - and([x_Occurrence[q21] -> - or([x_ExplicitVarSizeWithDummy[q23] != 6 /\ x_ExplicitVarSizeWithDummy[q23] = q21 | q23 : int(1..4)]) - | q21 : int(2..5)]), - and([x_ExplicitVarSizeWithDummy[q25] != 6 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q25]] | q25 : int(1..4)]), - and([q10 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> - y_ExplicitVarSizeWithMarker_Values[q10] < y_ExplicitVarSizeWithMarker_Values[q10 + 1] - | q10 : int(1..3)]), - and([q11 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q11] = 2 | q11 : int(1..4)]), - 1 <= y_ExplicitVarSizeWithMarker_Marker, - and([q14 <= y_ExplicitVarSizeWithMarker_Marker -> - or([y_ExplicitVarSizeWithDummy[q16] != 6 /\ - y_ExplicitVarSizeWithDummy[q16] = y_ExplicitVarSizeWithMarker_Values[q14] - | q16 : int(1..4)]) - | q14 : int(1..4)]), - and([y_ExplicitVarSizeWithDummy[q18] != 6 -> - or([q20 <= y_ExplicitVarSizeWithMarker_Marker /\ - y_ExplicitVarSizeWithMarker_Values[q20] = y_ExplicitVarSizeWithDummy[q18] - | q20 : int(1..4)]) - | q18 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_2_2_1_4-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_2_2_1_4-solution000001.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_2_1_4-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_2_2_1_4-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_2_2_1_4-solution000002.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_2_1_4-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_2_2_1_4.eprime b/tests/exhaustive/basic/set09/expected/model_2_2_1_4.eprime deleted file mode 100644 index 0cdf8a54bd..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_2_1_4.eprime +++ /dev/null @@ -1,45 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -find x_Occurrence: matrix indexed by [int(2..5)] of bool -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -branching on - [x_Occurrence, x_ExplicitVarSizeWithDummy, y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values, - y_ExplicitVarSizeWithDummy] -such that - and([x_ExplicitVarSizeWithDummy[q28] != 6 /\ y_ExplicitVarSizeWithDummy[q29] != 6 -> - x_ExplicitVarSizeWithDummy[q28] + 2 = y_ExplicitVarSizeWithDummy[q29] - | q28 : int(1..4), q29 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 6 - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q2] = 6 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 6 | q2 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 6) | q3 : int(1..4)]), - and([y_ExplicitVarSizeWithDummy[q5] < y_ExplicitVarSizeWithDummy[q5 + 1] \/ y_ExplicitVarSizeWithDummy[q5] = 6 - | q5 : int(1..3)]), - and([y_ExplicitVarSizeWithDummy[q6] = 6 -> y_ExplicitVarSizeWithDummy[q6 + 1] = 6 | q6 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q7] != 6) | q7 : int(1..4)]), - 1 <= sum([toInt(x_Occurrence[q9]) | q9 : int(2..5)]), - and([x_Occurrence[q23] -> - or([x_ExplicitVarSizeWithDummy[q25] != 6 /\ x_ExplicitVarSizeWithDummy[q25] = q23 | q25 : int(1..4)]) - | q23 : int(2..5)]), - and([x_ExplicitVarSizeWithDummy[q27] != 6 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q27]] | q27 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q10 + 1] -> - y_ExplicitVarSizeWithFlags_Values[q10] < y_ExplicitVarSizeWithFlags_Values[q10 + 1] - | q10 : int(1..3)]), - and([y_ExplicitVarSizeWithFlags_Flags[q11] = false -> y_ExplicitVarSizeWithFlags_Values[q11] = 2 - | q11 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q12 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q12] | q12 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q13]) | q13 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q16] -> - or([y_ExplicitVarSizeWithDummy[q18] != 6 /\ - y_ExplicitVarSizeWithDummy[q18] = y_ExplicitVarSizeWithFlags_Values[q16] - | q18 : int(1..4)]) - | q16 : int(1..4)]), - and([y_ExplicitVarSizeWithDummy[q20] != 6 -> - or([y_ExplicitVarSizeWithFlags_Flags[q22] /\ - y_ExplicitVarSizeWithFlags_Values[q22] = y_ExplicitVarSizeWithDummy[q20] - | q22 : int(1..4)]) - | q20 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_2_2_2_1-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_2_2_2_1-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_2_2_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_2_2_2_1-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_2_2_2_1-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_2_2_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_2_2_2_1.eprime b/tests/exhaustive/basic/set09/expected/model_2_2_2_1.eprime deleted file mode 100644 index ccc426d080..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_2_2_1.eprime +++ /dev/null @@ -1,24 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -find y_Occurrence: matrix indexed by [int(2..5)] of bool -branching on [x_ExplicitVarSizeWithDummy, y_Occurrence, y_ExplicitVarSizeWithDummy] -such that - and([x_ExplicitVarSizeWithDummy[q15] != 6 /\ y_ExplicitVarSizeWithDummy[q16] != 6 -> - x_ExplicitVarSizeWithDummy[q15] + 2 = y_ExplicitVarSizeWithDummy[q16] - | q15 : int(1..4), q16 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 6 - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q2] = 6 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 6 | q2 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 6) | q3 : int(1..4)]), - and([y_ExplicitVarSizeWithDummy[q5] < y_ExplicitVarSizeWithDummy[q5 + 1] \/ y_ExplicitVarSizeWithDummy[q5] = 6 - | q5 : int(1..3)]), - and([y_ExplicitVarSizeWithDummy[q6] = 6 -> y_ExplicitVarSizeWithDummy[q6 + 1] = 6 | q6 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q7] != 6) | q7 : int(1..4)]), - 1 <= sum([toInt(y_Occurrence[q9]) | q9 : int(2..5)]), - and([y_Occurrence[q10] -> - or([y_ExplicitVarSizeWithDummy[q12] != 6 /\ y_ExplicitVarSizeWithDummy[q12] = q10 | q12 : int(1..4)]) - | q10 : int(2..5)]), - and([y_ExplicitVarSizeWithDummy[q14] != 6 -> y_Occurrence[y_ExplicitVarSizeWithDummy[q14]] | q14 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_2_2_2_2-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_2_2_2_2-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_2_2_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_2_2_2_2-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_2_2_2_2-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_2_2_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_2_2_2_2.eprime b/tests/exhaustive/basic/set09/expected/model_2_2_2_2.eprime deleted file mode 100644 index bce1fcad7f..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_2_2_2.eprime +++ /dev/null @@ -1,18 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -branching on [x_ExplicitVarSizeWithDummy, y_ExplicitVarSizeWithDummy] -such that - and([x_ExplicitVarSizeWithDummy[q9] != 6 /\ y_ExplicitVarSizeWithDummy[q10] != 6 -> - x_ExplicitVarSizeWithDummy[q9] + 2 = y_ExplicitVarSizeWithDummy[q10] - | q9 : int(1..4), q10 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 6 - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q2] = 6 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 6 | q2 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 6) | q3 : int(1..4)]), - and([y_ExplicitVarSizeWithDummy[q5] < y_ExplicitVarSizeWithDummy[q5 + 1] \/ y_ExplicitVarSizeWithDummy[q5] = 6 - | q5 : int(1..3)]), - and([y_ExplicitVarSizeWithDummy[q6] = 6 -> y_ExplicitVarSizeWithDummy[q6 + 1] = 6 | q6 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q7] != 6) | q7 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_2_2_2_3-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_2_2_2_3-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_2_2_3-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_2_2_2_3-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_2_2_2_3-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_2_2_3-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_2_2_2_3.eprime b/tests/exhaustive/basic/set09/expected/model_2_2_2_3.eprime deleted file mode 100644 index f3540e7f47..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_2_2_3.eprime +++ /dev/null @@ -1,37 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -find y_ExplicitVarSizeWithMarker_Marker: int(0..4) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -branching on - [x_ExplicitVarSizeWithDummy, y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values, - y_ExplicitVarSizeWithDummy] -such that - and([x_ExplicitVarSizeWithDummy[q20] != 6 /\ y_ExplicitVarSizeWithDummy[q21] != 6 -> - x_ExplicitVarSizeWithDummy[q20] + 2 = y_ExplicitVarSizeWithDummy[q21] - | q20 : int(1..4), q21 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 6 - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q2] = 6 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 6 | q2 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 6) | q3 : int(1..4)]), - and([y_ExplicitVarSizeWithDummy[q5] < y_ExplicitVarSizeWithDummy[q5 + 1] \/ y_ExplicitVarSizeWithDummy[q5] = 6 - | q5 : int(1..3)]), - and([y_ExplicitVarSizeWithDummy[q6] = 6 -> y_ExplicitVarSizeWithDummy[q6 + 1] = 6 | q6 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q7] != 6) | q7 : int(1..4)]), - and([q9 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> - y_ExplicitVarSizeWithMarker_Values[q9] < y_ExplicitVarSizeWithMarker_Values[q9 + 1] - | q9 : int(1..3)]), - and([q10 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q10] = 2 | q10 : int(1..4)]), - 1 <= y_ExplicitVarSizeWithMarker_Marker, - and([q13 <= y_ExplicitVarSizeWithMarker_Marker -> - or([y_ExplicitVarSizeWithDummy[q15] != 6 /\ - y_ExplicitVarSizeWithDummy[q15] = y_ExplicitVarSizeWithMarker_Values[q13] - | q15 : int(1..4)]) - | q13 : int(1..4)]), - and([y_ExplicitVarSizeWithDummy[q17] != 6 -> - or([q19 <= y_ExplicitVarSizeWithMarker_Marker /\ - y_ExplicitVarSizeWithMarker_Values[q19] = y_ExplicitVarSizeWithDummy[q17] - | q19 : int(1..4)]) - | q17 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_2_2_2_4-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_2_2_2_4-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_2_2_4-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_2_2_2_4-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_2_2_2_4-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_2_2_4-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_2_2_2_4.eprime b/tests/exhaustive/basic/set09/expected/model_2_2_2_4.eprime deleted file mode 100644 index 88248fc78d..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_2_2_4.eprime +++ /dev/null @@ -1,39 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -branching on - [x_ExplicitVarSizeWithDummy, y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values, - y_ExplicitVarSizeWithDummy] -such that - and([x_ExplicitVarSizeWithDummy[q22] != 6 /\ y_ExplicitVarSizeWithDummy[q23] != 6 -> - x_ExplicitVarSizeWithDummy[q22] + 2 = y_ExplicitVarSizeWithDummy[q23] - | q22 : int(1..4), q23 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 6 - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q2] = 6 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 6 | q2 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 6) | q3 : int(1..4)]), - and([y_ExplicitVarSizeWithDummy[q5] < y_ExplicitVarSizeWithDummy[q5 + 1] \/ y_ExplicitVarSizeWithDummy[q5] = 6 - | q5 : int(1..3)]), - and([y_ExplicitVarSizeWithDummy[q6] = 6 -> y_ExplicitVarSizeWithDummy[q6 + 1] = 6 | q6 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q7] != 6) | q7 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q9 + 1] -> - y_ExplicitVarSizeWithFlags_Values[q9] < y_ExplicitVarSizeWithFlags_Values[q9 + 1] - | q9 : int(1..3)]), - and([y_ExplicitVarSizeWithFlags_Flags[q10] = false -> y_ExplicitVarSizeWithFlags_Values[q10] = 2 - | q10 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q11 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q11] | q11 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q12]) | q12 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q15] -> - or([y_ExplicitVarSizeWithDummy[q17] != 6 /\ - y_ExplicitVarSizeWithDummy[q17] = y_ExplicitVarSizeWithFlags_Values[q15] - | q17 : int(1..4)]) - | q15 : int(1..4)]), - and([y_ExplicitVarSizeWithDummy[q19] != 6 -> - or([y_ExplicitVarSizeWithFlags_Flags[q21] /\ - y_ExplicitVarSizeWithFlags_Values[q21] = y_ExplicitVarSizeWithDummy[q19] - | q21 : int(1..4)]) - | q19 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_2_2_3_1-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_2_2_3_1-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_2_3_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_2_2_3_1-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_2_2_3_1-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_2_3_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_2_2_3_1.eprime b/tests/exhaustive/basic/set09/expected/model_2_2_3_1.eprime deleted file mode 100644 index bf64c42988..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_2_3_1.eprime +++ /dev/null @@ -1,43 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -find y_Occurrence: matrix indexed by [int(2..5)] of bool -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy, y_Occurrence, - y_ExplicitVarSizeWithDummy] -such that - and([x_ExplicitVarSizeWithDummy[q26] != 6 /\ y_ExplicitVarSizeWithDummy[q27] != 6 -> - x_ExplicitVarSizeWithDummy[q26] + 2 = y_ExplicitVarSizeWithDummy[q27] - | q26 : int(1..4), q27 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 6 - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q2] = 6 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 6 | q2 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 6) | q3 : int(1..4)]), - and([y_ExplicitVarSizeWithDummy[q5] < y_ExplicitVarSizeWithDummy[q5 + 1] \/ y_ExplicitVarSizeWithDummy[q5] = 6 - | q5 : int(1..3)]), - and([y_ExplicitVarSizeWithDummy[q6] = 6 -> y_ExplicitVarSizeWithDummy[q6 + 1] = 6 | q6 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q7] != 6) | q7 : int(1..4)]), - and([q9 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q9] < x_ExplicitVarSizeWithMarker_Values[q9 + 1] - | q9 : int(1..3)]), - and([q10 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q10] = 2 | q10 : int(1..4)]), - 1 <= x_ExplicitVarSizeWithMarker_Marker, - and([q13 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q15] != 6 /\ - x_ExplicitVarSizeWithDummy[q15] = x_ExplicitVarSizeWithMarker_Values[q13] - | q15 : int(1..4)]) - | q13 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q17] != 6 -> - or([q19 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q19] = x_ExplicitVarSizeWithDummy[q17] - | q19 : int(1..4)]) - | q17 : int(1..4)]), - 1 <= sum([toInt(y_Occurrence[q20]) | q20 : int(2..5)]), - and([y_Occurrence[q21] -> - or([y_ExplicitVarSizeWithDummy[q23] != 6 /\ y_ExplicitVarSizeWithDummy[q23] = q21 | q23 : int(1..4)]) - | q21 : int(2..5)]), - and([y_ExplicitVarSizeWithDummy[q25] != 6 -> y_Occurrence[y_ExplicitVarSizeWithDummy[q25]] | q25 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_2_2_3_2-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_2_2_3_2-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_2_3_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_2_2_3_2-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_2_2_3_2-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_2_3_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_2_2_3_2.eprime b/tests/exhaustive/basic/set09/expected/model_2_2_3_2.eprime deleted file mode 100644 index e948b9d5dd..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_2_3_2.eprime +++ /dev/null @@ -1,37 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy, - y_ExplicitVarSizeWithDummy] -such that - and([x_ExplicitVarSizeWithDummy[q20] != 6 /\ y_ExplicitVarSizeWithDummy[q21] != 6 -> - x_ExplicitVarSizeWithDummy[q20] + 2 = y_ExplicitVarSizeWithDummy[q21] - | q20 : int(1..4), q21 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 6 - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q2] = 6 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 6 | q2 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 6) | q3 : int(1..4)]), - and([y_ExplicitVarSizeWithDummy[q5] < y_ExplicitVarSizeWithDummy[q5 + 1] \/ y_ExplicitVarSizeWithDummy[q5] = 6 - | q5 : int(1..3)]), - and([y_ExplicitVarSizeWithDummy[q6] = 6 -> y_ExplicitVarSizeWithDummy[q6 + 1] = 6 | q6 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q7] != 6) | q7 : int(1..4)]), - and([q9 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q9] < x_ExplicitVarSizeWithMarker_Values[q9 + 1] - | q9 : int(1..3)]), - and([q10 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q10] = 2 | q10 : int(1..4)]), - 1 <= x_ExplicitVarSizeWithMarker_Marker, - and([q13 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q15] != 6 /\ - x_ExplicitVarSizeWithDummy[q15] = x_ExplicitVarSizeWithMarker_Values[q13] - | q15 : int(1..4)]) - | q13 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q17] != 6 -> - or([q19 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q19] = x_ExplicitVarSizeWithDummy[q17] - | q19 : int(1..4)]) - | q17 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_2_2_3_3-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_2_2_3_3-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_2_3_3-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_2_2_3_3-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_2_2_3_3-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_2_3_3-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_2_2_3_3.eprime b/tests/exhaustive/basic/set09/expected/model_2_2_3_3.eprime deleted file mode 100644 index 96a79f1b62..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_2_3_3.eprime +++ /dev/null @@ -1,54 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -find y_ExplicitVarSizeWithMarker_Marker: int(0..4) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy, - y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithDummy] -such that - and([x_ExplicitVarSizeWithDummy[q31] != 6 /\ y_ExplicitVarSizeWithDummy[q32] != 6 -> - x_ExplicitVarSizeWithDummy[q31] + 2 = y_ExplicitVarSizeWithDummy[q32] - | q31 : int(1..4), q32 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 6 - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q2] = 6 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 6 | q2 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 6) | q3 : int(1..4)]), - and([y_ExplicitVarSizeWithDummy[q5] < y_ExplicitVarSizeWithDummy[q5 + 1] \/ y_ExplicitVarSizeWithDummy[q5] = 6 - | q5 : int(1..3)]), - and([y_ExplicitVarSizeWithDummy[q6] = 6 -> y_ExplicitVarSizeWithDummy[q6 + 1] = 6 | q6 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q7] != 6) | q7 : int(1..4)]), - and([q9 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q9] < x_ExplicitVarSizeWithMarker_Values[q9 + 1] - | q9 : int(1..3)]), - and([q10 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q10] = 2 | q10 : int(1..4)]), - 1 <= x_ExplicitVarSizeWithMarker_Marker, - and([q13 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q15] != 6 /\ - x_ExplicitVarSizeWithDummy[q15] = x_ExplicitVarSizeWithMarker_Values[q13] - | q15 : int(1..4)]) - | q13 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q17] != 6 -> - or([q19 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q19] = x_ExplicitVarSizeWithDummy[q17] - | q19 : int(1..4)]) - | q17 : int(1..4)]), - and([q20 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> - y_ExplicitVarSizeWithMarker_Values[q20] < y_ExplicitVarSizeWithMarker_Values[q20 + 1] - | q20 : int(1..3)]), - and([q21 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q21] = 2 | q21 : int(1..4)]), - 1 <= y_ExplicitVarSizeWithMarker_Marker, - and([q24 <= y_ExplicitVarSizeWithMarker_Marker -> - or([y_ExplicitVarSizeWithDummy[q26] != 6 /\ - y_ExplicitVarSizeWithDummy[q26] = y_ExplicitVarSizeWithMarker_Values[q24] - | q26 : int(1..4)]) - | q24 : int(1..4)]), - and([y_ExplicitVarSizeWithDummy[q28] != 6 -> - or([q30 <= y_ExplicitVarSizeWithMarker_Marker /\ - y_ExplicitVarSizeWithMarker_Values[q30] = y_ExplicitVarSizeWithDummy[q28] - | q30 : int(1..4)]) - | q28 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_2_2_3_4-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_2_2_3_4-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_2_3_4-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_2_2_3_4-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_2_2_3_4-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_2_3_4-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_2_2_3_4.eprime b/tests/exhaustive/basic/set09/expected/model_2_2_3_4.eprime deleted file mode 100644 index 466ab4e3bf..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_2_3_4.eprime +++ /dev/null @@ -1,56 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy, - y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithDummy] -such that - and([x_ExplicitVarSizeWithDummy[q33] != 6 /\ y_ExplicitVarSizeWithDummy[q34] != 6 -> - x_ExplicitVarSizeWithDummy[q33] + 2 = y_ExplicitVarSizeWithDummy[q34] - | q33 : int(1..4), q34 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 6 - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q2] = 6 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 6 | q2 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 6) | q3 : int(1..4)]), - and([y_ExplicitVarSizeWithDummy[q5] < y_ExplicitVarSizeWithDummy[q5 + 1] \/ y_ExplicitVarSizeWithDummy[q5] = 6 - | q5 : int(1..3)]), - and([y_ExplicitVarSizeWithDummy[q6] = 6 -> y_ExplicitVarSizeWithDummy[q6 + 1] = 6 | q6 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q7] != 6) | q7 : int(1..4)]), - and([q9 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q9] < x_ExplicitVarSizeWithMarker_Values[q9 + 1] - | q9 : int(1..3)]), - and([q10 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q10] = 2 | q10 : int(1..4)]), - 1 <= x_ExplicitVarSizeWithMarker_Marker, - and([q13 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q15] != 6 /\ - x_ExplicitVarSizeWithDummy[q15] = x_ExplicitVarSizeWithMarker_Values[q13] - | q15 : int(1..4)]) - | q13 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q17] != 6 -> - or([q19 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q19] = x_ExplicitVarSizeWithDummy[q17] - | q19 : int(1..4)]) - | q17 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q20 + 1] -> - y_ExplicitVarSizeWithFlags_Values[q20] < y_ExplicitVarSizeWithFlags_Values[q20 + 1] - | q20 : int(1..3)]), - and([y_ExplicitVarSizeWithFlags_Flags[q21] = false -> y_ExplicitVarSizeWithFlags_Values[q21] = 2 - | q21 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q22 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q22] | q22 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q23]) | q23 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q26] -> - or([y_ExplicitVarSizeWithDummy[q28] != 6 /\ - y_ExplicitVarSizeWithDummy[q28] = y_ExplicitVarSizeWithFlags_Values[q26] - | q28 : int(1..4)]) - | q26 : int(1..4)]), - and([y_ExplicitVarSizeWithDummy[q30] != 6 -> - or([y_ExplicitVarSizeWithFlags_Flags[q32] /\ - y_ExplicitVarSizeWithFlags_Values[q32] = y_ExplicitVarSizeWithDummy[q30] - | q32 : int(1..4)]) - | q30 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_2_2_4_1-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_2_2_4_1-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_2_4_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_2_2_4_1-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_2_2_4_1-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_2_4_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_2_2_4_1.eprime b/tests/exhaustive/basic/set09/expected/model_2_2_4_1.eprime deleted file mode 100644 index a1084e9824..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_2_4_1.eprime +++ /dev/null @@ -1,45 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -find y_Occurrence: matrix indexed by [int(2..5)] of bool -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy, y_Occurrence, - y_ExplicitVarSizeWithDummy] -such that - and([x_ExplicitVarSizeWithDummy[q28] != 6 /\ y_ExplicitVarSizeWithDummy[q29] != 6 -> - x_ExplicitVarSizeWithDummy[q28] + 2 = y_ExplicitVarSizeWithDummy[q29] - | q28 : int(1..4), q29 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 6 - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q2] = 6 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 6 | q2 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 6) | q3 : int(1..4)]), - and([y_ExplicitVarSizeWithDummy[q5] < y_ExplicitVarSizeWithDummy[q5 + 1] \/ y_ExplicitVarSizeWithDummy[q5] = 6 - | q5 : int(1..3)]), - and([y_ExplicitVarSizeWithDummy[q6] = 6 -> y_ExplicitVarSizeWithDummy[q6 + 1] = 6 | q6 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q7] != 6) | q7 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q9 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q9] < x_ExplicitVarSizeWithFlags_Values[q9 + 1] - | q9 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q10] = false -> x_ExplicitVarSizeWithFlags_Values[q10] = 2 - | q10 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q11 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q11] | q11 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q12]) | q12 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q15] -> - or([x_ExplicitVarSizeWithDummy[q17] != 6 /\ - x_ExplicitVarSizeWithDummy[q17] = x_ExplicitVarSizeWithFlags_Values[q15] - | q17 : int(1..4)]) - | q15 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q19] != 6 -> - or([x_ExplicitVarSizeWithFlags_Flags[q21] /\ - x_ExplicitVarSizeWithFlags_Values[q21] = x_ExplicitVarSizeWithDummy[q19] - | q21 : int(1..4)]) - | q19 : int(1..4)]), - 1 <= sum([toInt(y_Occurrence[q22]) | q22 : int(2..5)]), - and([y_Occurrence[q23] -> - or([y_ExplicitVarSizeWithDummy[q25] != 6 /\ y_ExplicitVarSizeWithDummy[q25] = q23 | q25 : int(1..4)]) - | q23 : int(2..5)]), - and([y_ExplicitVarSizeWithDummy[q27] != 6 -> y_Occurrence[y_ExplicitVarSizeWithDummy[q27]] | q27 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_2_2_4_2-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_2_2_4_2-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_2_4_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_2_2_4_2-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_2_2_4_2-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_2_4_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_2_2_4_2.eprime b/tests/exhaustive/basic/set09/expected/model_2_2_4_2.eprime deleted file mode 100644 index 43b2f0a07f..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_2_4_2.eprime +++ /dev/null @@ -1,39 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy, - y_ExplicitVarSizeWithDummy] -such that - and([x_ExplicitVarSizeWithDummy[q22] != 6 /\ y_ExplicitVarSizeWithDummy[q23] != 6 -> - x_ExplicitVarSizeWithDummy[q22] + 2 = y_ExplicitVarSizeWithDummy[q23] - | q22 : int(1..4), q23 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 6 - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q2] = 6 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 6 | q2 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 6) | q3 : int(1..4)]), - and([y_ExplicitVarSizeWithDummy[q5] < y_ExplicitVarSizeWithDummy[q5 + 1] \/ y_ExplicitVarSizeWithDummy[q5] = 6 - | q5 : int(1..3)]), - and([y_ExplicitVarSizeWithDummy[q6] = 6 -> y_ExplicitVarSizeWithDummy[q6 + 1] = 6 | q6 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q7] != 6) | q7 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q9 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q9] < x_ExplicitVarSizeWithFlags_Values[q9 + 1] - | q9 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q10] = false -> x_ExplicitVarSizeWithFlags_Values[q10] = 2 - | q10 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q11 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q11] | q11 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q12]) | q12 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q15] -> - or([x_ExplicitVarSizeWithDummy[q17] != 6 /\ - x_ExplicitVarSizeWithDummy[q17] = x_ExplicitVarSizeWithFlags_Values[q15] - | q17 : int(1..4)]) - | q15 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q19] != 6 -> - or([x_ExplicitVarSizeWithFlags_Flags[q21] /\ - x_ExplicitVarSizeWithFlags_Values[q21] = x_ExplicitVarSizeWithDummy[q19] - | q21 : int(1..4)]) - | q19 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_2_2_4_3-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_2_2_4_3-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_2_4_3-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_2_2_4_3-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_2_2_4_3-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_2_4_3-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_2_2_4_3.eprime b/tests/exhaustive/basic/set09/expected/model_2_2_4_3.eprime deleted file mode 100644 index d589c54438..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_2_4_3.eprime +++ /dev/null @@ -1,56 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -find y_ExplicitVarSizeWithMarker_Marker: int(0..4) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy, - y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithDummy] -such that - and([x_ExplicitVarSizeWithDummy[q33] != 6 /\ y_ExplicitVarSizeWithDummy[q34] != 6 -> - x_ExplicitVarSizeWithDummy[q33] + 2 = y_ExplicitVarSizeWithDummy[q34] - | q33 : int(1..4), q34 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 6 - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q2] = 6 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 6 | q2 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 6) | q3 : int(1..4)]), - and([y_ExplicitVarSizeWithDummy[q5] < y_ExplicitVarSizeWithDummy[q5 + 1] \/ y_ExplicitVarSizeWithDummy[q5] = 6 - | q5 : int(1..3)]), - and([y_ExplicitVarSizeWithDummy[q6] = 6 -> y_ExplicitVarSizeWithDummy[q6 + 1] = 6 | q6 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q7] != 6) | q7 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q9 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q9] < x_ExplicitVarSizeWithFlags_Values[q9 + 1] - | q9 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q10] = false -> x_ExplicitVarSizeWithFlags_Values[q10] = 2 - | q10 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q11 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q11] | q11 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q12]) | q12 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q15] -> - or([x_ExplicitVarSizeWithDummy[q17] != 6 /\ - x_ExplicitVarSizeWithDummy[q17] = x_ExplicitVarSizeWithFlags_Values[q15] - | q17 : int(1..4)]) - | q15 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q19] != 6 -> - or([x_ExplicitVarSizeWithFlags_Flags[q21] /\ - x_ExplicitVarSizeWithFlags_Values[q21] = x_ExplicitVarSizeWithDummy[q19] - | q21 : int(1..4)]) - | q19 : int(1..4)]), - and([q22 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> - y_ExplicitVarSizeWithMarker_Values[q22] < y_ExplicitVarSizeWithMarker_Values[q22 + 1] - | q22 : int(1..3)]), - and([q23 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q23] = 2 | q23 : int(1..4)]), - 1 <= y_ExplicitVarSizeWithMarker_Marker, - and([q26 <= y_ExplicitVarSizeWithMarker_Marker -> - or([y_ExplicitVarSizeWithDummy[q28] != 6 /\ - y_ExplicitVarSizeWithDummy[q28] = y_ExplicitVarSizeWithMarker_Values[q26] - | q28 : int(1..4)]) - | q26 : int(1..4)]), - and([y_ExplicitVarSizeWithDummy[q30] != 6 -> - or([q32 <= y_ExplicitVarSizeWithMarker_Marker /\ - y_ExplicitVarSizeWithMarker_Values[q32] = y_ExplicitVarSizeWithDummy[q30] - | q32 : int(1..4)]) - | q30 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_2_2_4_4-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_2_2_4_4-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_2_4_4-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_2_2_4_4-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_2_2_4_4-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_2_4_4-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_2_2_4_4.eprime b/tests/exhaustive/basic/set09/expected/model_2_2_4_4.eprime deleted file mode 100644 index eccd37c27c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_2_4_4.eprime +++ /dev/null @@ -1,58 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy, - y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithDummy] -such that - and([x_ExplicitVarSizeWithDummy[q35] != 6 /\ y_ExplicitVarSizeWithDummy[q36] != 6 -> - x_ExplicitVarSizeWithDummy[q35] + 2 = y_ExplicitVarSizeWithDummy[q36] - | q35 : int(1..4), q36 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 6 - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q2] = 6 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 6 | q2 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 6) | q3 : int(1..4)]), - and([y_ExplicitVarSizeWithDummy[q5] < y_ExplicitVarSizeWithDummy[q5 + 1] \/ y_ExplicitVarSizeWithDummy[q5] = 6 - | q5 : int(1..3)]), - and([y_ExplicitVarSizeWithDummy[q6] = 6 -> y_ExplicitVarSizeWithDummy[q6 + 1] = 6 | q6 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q7] != 6) | q7 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q9 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q9] < x_ExplicitVarSizeWithFlags_Values[q9 + 1] - | q9 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q10] = false -> x_ExplicitVarSizeWithFlags_Values[q10] = 2 - | q10 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q11 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q11] | q11 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q12]) | q12 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q15] -> - or([x_ExplicitVarSizeWithDummy[q17] != 6 /\ - x_ExplicitVarSizeWithDummy[q17] = x_ExplicitVarSizeWithFlags_Values[q15] - | q17 : int(1..4)]) - | q15 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q19] != 6 -> - or([x_ExplicitVarSizeWithFlags_Flags[q21] /\ - x_ExplicitVarSizeWithFlags_Values[q21] = x_ExplicitVarSizeWithDummy[q19] - | q21 : int(1..4)]) - | q19 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q22 + 1] -> - y_ExplicitVarSizeWithFlags_Values[q22] < y_ExplicitVarSizeWithFlags_Values[q22 + 1] - | q22 : int(1..3)]), - and([y_ExplicitVarSizeWithFlags_Flags[q23] = false -> y_ExplicitVarSizeWithFlags_Values[q23] = 2 - | q23 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q24 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q24] | q24 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q25]) | q25 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q28] -> - or([y_ExplicitVarSizeWithDummy[q30] != 6 /\ - y_ExplicitVarSizeWithDummy[q30] = y_ExplicitVarSizeWithFlags_Values[q28] - | q30 : int(1..4)]) - | q28 : int(1..4)]), - and([y_ExplicitVarSizeWithDummy[q32] != 6 -> - or([y_ExplicitVarSizeWithFlags_Flags[q34] /\ - y_ExplicitVarSizeWithFlags_Values[q34] = y_ExplicitVarSizeWithDummy[q32] - | q34 : int(1..4)]) - | q32 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_2_3_1_1-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_2_3_1_1-solution000001.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_3_1_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_2_3_1_1-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_2_3_1_1-solution000002.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_3_1_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_2_3_1_1.eprime b/tests/exhaustive/basic/set09/expected/model_2_3_1_1.eprime deleted file mode 100644 index 37bb76ce7c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_3_1_1.eprime +++ /dev/null @@ -1,36 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -find x_Occurrence: matrix indexed by [int(2..5)] of bool -find y_ExplicitVarSizeWithMarker_Marker: int(0..4) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_Occurrence: matrix indexed by [int(2..5)] of bool -branching on - [x_Occurrence, x_ExplicitVarSizeWithDummy, y_Occurrence, y_ExplicitVarSizeWithMarker_Marker, - y_ExplicitVarSizeWithMarker_Values] -such that - and([x_ExplicitVarSizeWithDummy[q15] != 6 /\ q16 <= y_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithDummy[q15] + 2 = y_ExplicitVarSizeWithMarker_Values[q16] - | q15 : int(1..4), q16 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 6 - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q2] = 6 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 6 | q2 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 6) | q3 : int(1..4)]), - and([q5 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> - y_ExplicitVarSizeWithMarker_Values[q5] < y_ExplicitVarSizeWithMarker_Values[q5 + 1] - | q5 : int(1..3)]), - and([q6 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q6] = 2 | q6 : int(1..4)]), - 1 <= y_ExplicitVarSizeWithMarker_Marker, - 1 <= sum([toInt(x_Occurrence[q8]) | q8 : int(2..5)]), - and([x_Occurrence[q17] -> - or([x_ExplicitVarSizeWithDummy[q19] != 6 /\ x_ExplicitVarSizeWithDummy[q19] = q17 | q19 : int(1..4)]) - | q17 : int(2..5)]), - and([x_ExplicitVarSizeWithDummy[q21] != 6 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q21]] | q21 : int(1..4)]), - 1 <= sum([toInt(y_Occurrence[q9]) | q9 : int(2..5)]), - and([y_Occurrence[q10] -> - or([q12 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[q12] = q10 - | q12 : int(1..4)]) - | q10 : int(2..5)]), - and([q14 <= y_ExplicitVarSizeWithMarker_Marker -> y_Occurrence[y_ExplicitVarSizeWithMarker_Values[q14]] - | q14 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_2_3_1_2-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_2_3_1_2-solution000001.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_3_1_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_2_3_1_2-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_2_3_1_2-solution000002.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_3_1_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_2_3_1_2.eprime b/tests/exhaustive/basic/set09/expected/model_2_3_1_2.eprime deleted file mode 100644 index ef24047245..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_3_1_2.eprime +++ /dev/null @@ -1,43 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -find x_Occurrence: matrix indexed by [int(2..5)] of bool -find y_ExplicitVarSizeWithMarker_Marker: int(0..4) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -branching on - [x_Occurrence, x_ExplicitVarSizeWithDummy, y_ExplicitVarSizeWithDummy, y_ExplicitVarSizeWithMarker_Marker, - y_ExplicitVarSizeWithMarker_Values] -such that - and([x_ExplicitVarSizeWithDummy[q26] != 6 /\ q27 <= y_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithDummy[q26] + 2 = y_ExplicitVarSizeWithMarker_Values[q27] - | q26 : int(1..4), q27 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 6 - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q2] = 6 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 6 | q2 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 6) | q3 : int(1..4)]), - and([q5 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> - y_ExplicitVarSizeWithMarker_Values[q5] < y_ExplicitVarSizeWithMarker_Values[q5 + 1] - | q5 : int(1..3)]), - and([q6 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q6] = 2 | q6 : int(1..4)]), - 1 <= y_ExplicitVarSizeWithMarker_Marker, - 1 <= sum([toInt(x_Occurrence[q8]) | q8 : int(2..5)]), - and([x_Occurrence[q21] -> - or([x_ExplicitVarSizeWithDummy[q23] != 6 /\ x_ExplicitVarSizeWithDummy[q23] = q21 | q23 : int(1..4)]) - | q21 : int(2..5)]), - and([x_ExplicitVarSizeWithDummy[q25] != 6 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q25]] | q25 : int(1..4)]), - and([y_ExplicitVarSizeWithDummy[q9] < y_ExplicitVarSizeWithDummy[q9 + 1] \/ y_ExplicitVarSizeWithDummy[q9] = 6 - | q9 : int(1..3)]), - and([y_ExplicitVarSizeWithDummy[q10] = 6 -> y_ExplicitVarSizeWithDummy[q10 + 1] = 6 | q10 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q11] != 6) | q11 : int(1..4)]), - and([y_ExplicitVarSizeWithDummy[q14] != 6 -> - or([q16 <= y_ExplicitVarSizeWithMarker_Marker /\ - y_ExplicitVarSizeWithMarker_Values[q16] = y_ExplicitVarSizeWithDummy[q14] - | q16 : int(1..4)]) - | q14 : int(1..4)]), - and([q18 <= y_ExplicitVarSizeWithMarker_Marker -> - or([y_ExplicitVarSizeWithDummy[q20] != 6 /\ - y_ExplicitVarSizeWithDummy[q20] = y_ExplicitVarSizeWithMarker_Values[q18] - | q20 : int(1..4)]) - | q18 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_2_3_1_3-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_2_3_1_3-solution000001.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_3_1_3-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_2_3_1_3-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_2_3_1_3-solution000002.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_3_1_3-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_2_3_1_3.eprime b/tests/exhaustive/basic/set09/expected/model_2_3_1_3.eprime deleted file mode 100644 index e78df8b806..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_3_1_3.eprime +++ /dev/null @@ -1,27 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -find x_Occurrence: matrix indexed by [int(2..5)] of bool -find y_ExplicitVarSizeWithMarker_Marker: int(0..4) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -branching on - [x_Occurrence, x_ExplicitVarSizeWithDummy, y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values] -such that - and([x_ExplicitVarSizeWithDummy[q14] != 6 /\ q15 <= y_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithDummy[q14] + 2 = y_ExplicitVarSizeWithMarker_Values[q15] - | q14 : int(1..4), q15 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 6 - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q2] = 6 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 6 | q2 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 6) | q3 : int(1..4)]), - and([q5 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> - y_ExplicitVarSizeWithMarker_Values[q5] < y_ExplicitVarSizeWithMarker_Values[q5 + 1] - | q5 : int(1..3)]), - and([q6 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q6] = 2 | q6 : int(1..4)]), - 1 <= y_ExplicitVarSizeWithMarker_Marker, - 1 <= sum([toInt(x_Occurrence[q8]) | q8 : int(2..5)]), - and([x_Occurrence[q9] -> - or([x_ExplicitVarSizeWithDummy[q11] != 6 /\ x_ExplicitVarSizeWithDummy[q11] = q9 | q11 : int(1..4)]) - | q9 : int(2..5)]), - and([x_ExplicitVarSizeWithDummy[q13] != 6 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q13]] | q13 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_2_3_1_4-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_2_3_1_4-solution000001.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_3_1_4-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_2_3_1_4-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_2_3_1_4-solution000002.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_3_1_4-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_2_3_1_4.eprime b/tests/exhaustive/basic/set09/expected/model_2_3_1_4.eprime deleted file mode 100644 index 1760ad207f..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_3_1_4.eprime +++ /dev/null @@ -1,47 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -find x_Occurrence: matrix indexed by [int(2..5)] of bool -find y_ExplicitVarSizeWithMarker_Marker: int(0..4) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -branching on - [x_Occurrence, x_ExplicitVarSizeWithDummy, y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values, - y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values] -such that - and([x_ExplicitVarSizeWithDummy[q27] != 6 /\ q28 <= y_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithDummy[q27] + 2 = y_ExplicitVarSizeWithMarker_Values[q28] - | q27 : int(1..4), q28 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 6 - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q2] = 6 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 6 | q2 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 6) | q3 : int(1..4)]), - and([q5 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> - y_ExplicitVarSizeWithMarker_Values[q5] < y_ExplicitVarSizeWithMarker_Values[q5 + 1] - | q5 : int(1..3)]), - and([q6 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q6] = 2 | q6 : int(1..4)]), - 1 <= y_ExplicitVarSizeWithMarker_Marker, - 1 <= sum([toInt(x_Occurrence[q8]) | q8 : int(2..5)]), - and([x_Occurrence[q22] -> - or([x_ExplicitVarSizeWithDummy[q24] != 6 /\ x_ExplicitVarSizeWithDummy[q24] = q22 | q24 : int(1..4)]) - | q22 : int(2..5)]), - and([x_ExplicitVarSizeWithDummy[q26] != 6 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q26]] | q26 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q9 + 1] -> - y_ExplicitVarSizeWithFlags_Values[q9] < y_ExplicitVarSizeWithFlags_Values[q9 + 1] - | q9 : int(1..3)]), - and([y_ExplicitVarSizeWithFlags_Flags[q10] = false -> y_ExplicitVarSizeWithFlags_Values[q10] = 2 - | q10 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q11 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q11] | q11 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q12]) | q12 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q15] -> - or([q17 <= y_ExplicitVarSizeWithMarker_Marker /\ - y_ExplicitVarSizeWithMarker_Values[q17] = y_ExplicitVarSizeWithFlags_Values[q15] - | q17 : int(1..4)]) - | q15 : int(1..4)]), - and([q19 <= y_ExplicitVarSizeWithMarker_Marker -> - or([y_ExplicitVarSizeWithFlags_Flags[q21] /\ - y_ExplicitVarSizeWithFlags_Values[q21] = y_ExplicitVarSizeWithMarker_Values[q19] - | q21 : int(1..4)]) - | q19 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_2_3_2_1-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_2_3_2_1-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_3_2_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_2_3_2_1-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_2_3_2_1-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_3_2_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_2_3_2_1.eprime b/tests/exhaustive/basic/set09/expected/model_2_3_2_1.eprime deleted file mode 100644 index 230e345c18..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_3_2_1.eprime +++ /dev/null @@ -1,29 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -find y_ExplicitVarSizeWithMarker_Marker: int(0..4) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_Occurrence: matrix indexed by [int(2..5)] of bool -branching on - [x_ExplicitVarSizeWithDummy, y_Occurrence, y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values] -such that - and([x_ExplicitVarSizeWithDummy[q14] != 6 /\ q15 <= y_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithDummy[q14] + 2 = y_ExplicitVarSizeWithMarker_Values[q15] - | q14 : int(1..4), q15 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 6 - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q2] = 6 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 6 | q2 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 6) | q3 : int(1..4)]), - and([q5 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> - y_ExplicitVarSizeWithMarker_Values[q5] < y_ExplicitVarSizeWithMarker_Values[q5 + 1] - | q5 : int(1..3)]), - and([q6 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q6] = 2 | q6 : int(1..4)]), - 1 <= y_ExplicitVarSizeWithMarker_Marker, - 1 <= sum([toInt(y_Occurrence[q8]) | q8 : int(2..5)]), - and([y_Occurrence[q9] -> - or([q11 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[q11] = q9 - | q11 : int(1..4)]) - | q9 : int(2..5)]), - and([q13 <= y_ExplicitVarSizeWithMarker_Marker -> y_Occurrence[y_ExplicitVarSizeWithMarker_Values[q13]] - | q13 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_2_3_2_2-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_2_3_2_2-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_3_2_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_2_3_2_2-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_2_3_2_2-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_3_2_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_2_3_2_2.eprime b/tests/exhaustive/basic/set09/expected/model_2_3_2_2.eprime deleted file mode 100644 index f2e207b1c7..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_3_2_2.eprime +++ /dev/null @@ -1,37 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -find y_ExplicitVarSizeWithMarker_Marker: int(0..4) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -branching on - [x_ExplicitVarSizeWithDummy, y_ExplicitVarSizeWithDummy, y_ExplicitVarSizeWithMarker_Marker, - y_ExplicitVarSizeWithMarker_Values] -such that - and([x_ExplicitVarSizeWithDummy[q20] != 6 /\ q21 <= y_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithDummy[q20] + 2 = y_ExplicitVarSizeWithMarker_Values[q21] - | q20 : int(1..4), q21 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 6 - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q2] = 6 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 6 | q2 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 6) | q3 : int(1..4)]), - and([q5 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> - y_ExplicitVarSizeWithMarker_Values[q5] < y_ExplicitVarSizeWithMarker_Values[q5 + 1] - | q5 : int(1..3)]), - and([q6 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q6] = 2 | q6 : int(1..4)]), - 1 <= y_ExplicitVarSizeWithMarker_Marker, - and([y_ExplicitVarSizeWithDummy[q8] < y_ExplicitVarSizeWithDummy[q8 + 1] \/ y_ExplicitVarSizeWithDummy[q8] = 6 - | q8 : int(1..3)]), - and([y_ExplicitVarSizeWithDummy[q9] = 6 -> y_ExplicitVarSizeWithDummy[q9 + 1] = 6 | q9 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q10] != 6) | q10 : int(1..4)]), - and([y_ExplicitVarSizeWithDummy[q13] != 6 -> - or([q15 <= y_ExplicitVarSizeWithMarker_Marker /\ - y_ExplicitVarSizeWithMarker_Values[q15] = y_ExplicitVarSizeWithDummy[q13] - | q15 : int(1..4)]) - | q13 : int(1..4)]), - and([q17 <= y_ExplicitVarSizeWithMarker_Marker -> - or([y_ExplicitVarSizeWithDummy[q19] != 6 /\ - y_ExplicitVarSizeWithDummy[q19] = y_ExplicitVarSizeWithMarker_Values[q17] - | q19 : int(1..4)]) - | q17 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_2_3_2_3-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_2_3_2_3-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_3_2_3-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_2_3_2_3-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_2_3_2_3-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_3_2_3-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_2_3_2_3.eprime b/tests/exhaustive/basic/set09/expected/model_2_3_2_3.eprime deleted file mode 100644 index 55128bbafc..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_3_2_3.eprime +++ /dev/null @@ -1,20 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -find y_ExplicitVarSizeWithMarker_Marker: int(0..4) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -branching on [x_ExplicitVarSizeWithDummy, y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values] -such that - and([x_ExplicitVarSizeWithDummy[q8] != 6 /\ q9 <= y_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithDummy[q8] + 2 = y_ExplicitVarSizeWithMarker_Values[q9] - | q8 : int(1..4), q9 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 6 - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q2] = 6 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 6 | q2 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 6) | q3 : int(1..4)]), - and([q5 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> - y_ExplicitVarSizeWithMarker_Values[q5] < y_ExplicitVarSizeWithMarker_Values[q5 + 1] - | q5 : int(1..3)]), - and([q6 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q6] = 2 | q6 : int(1..4)]), - 1 <= y_ExplicitVarSizeWithMarker_Marker - diff --git a/tests/exhaustive/basic/set09/expected/model_2_3_2_4-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_2_3_2_4-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_3_2_4-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_2_3_2_4-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_2_3_2_4-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_3_2_4-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_2_3_2_4.eprime b/tests/exhaustive/basic/set09/expected/model_2_3_2_4.eprime deleted file mode 100644 index f69d957f61..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_3_2_4.eprime +++ /dev/null @@ -1,40 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -find y_ExplicitVarSizeWithMarker_Marker: int(0..4) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -branching on - [x_ExplicitVarSizeWithDummy, y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values, - y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values] -such that - and([x_ExplicitVarSizeWithDummy[q21] != 6 /\ q22 <= y_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithDummy[q21] + 2 = y_ExplicitVarSizeWithMarker_Values[q22] - | q21 : int(1..4), q22 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 6 - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q2] = 6 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 6 | q2 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 6) | q3 : int(1..4)]), - and([q5 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> - y_ExplicitVarSizeWithMarker_Values[q5] < y_ExplicitVarSizeWithMarker_Values[q5 + 1] - | q5 : int(1..3)]), - and([q6 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q6] = 2 | q6 : int(1..4)]), - 1 <= y_ExplicitVarSizeWithMarker_Marker, - and([y_ExplicitVarSizeWithFlags_Flags[q8 + 1] -> - y_ExplicitVarSizeWithFlags_Values[q8] < y_ExplicitVarSizeWithFlags_Values[q8 + 1] - | q8 : int(1..3)]), - and([y_ExplicitVarSizeWithFlags_Flags[q9] = false -> y_ExplicitVarSizeWithFlags_Values[q9] = 2 | q9 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q10 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q10] | q10 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q11]) | q11 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q14] -> - or([q16 <= y_ExplicitVarSizeWithMarker_Marker /\ - y_ExplicitVarSizeWithMarker_Values[q16] = y_ExplicitVarSizeWithFlags_Values[q14] - | q16 : int(1..4)]) - | q14 : int(1..4)]), - and([q18 <= y_ExplicitVarSizeWithMarker_Marker -> - or([y_ExplicitVarSizeWithFlags_Flags[q20] /\ - y_ExplicitVarSizeWithFlags_Values[q20] = y_ExplicitVarSizeWithMarker_Values[q18] - | q20 : int(1..4)]) - | q18 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_2_3_3_1-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_2_3_3_1-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_3_3_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_2_3_3_1-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_2_3_3_1-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_3_3_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_2_3_3_1.eprime b/tests/exhaustive/basic/set09/expected/model_2_3_3_1.eprime deleted file mode 100644 index a25e81deb3..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_3_3_1.eprime +++ /dev/null @@ -1,47 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_ExplicitVarSizeWithMarker_Marker: int(0..4) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_Occurrence: matrix indexed by [int(2..5)] of bool -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy, y_Occurrence, - y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values] -such that - and([x_ExplicitVarSizeWithDummy[q25] != 6 /\ q26 <= y_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithDummy[q25] + 2 = y_ExplicitVarSizeWithMarker_Values[q26] - | q25 : int(1..4), q26 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 6 - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q2] = 6 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 6 | q2 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 6) | q3 : int(1..4)]), - and([q5 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> - y_ExplicitVarSizeWithMarker_Values[q5] < y_ExplicitVarSizeWithMarker_Values[q5 + 1] - | q5 : int(1..3)]), - and([q6 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q6] = 2 | q6 : int(1..4)]), - 1 <= y_ExplicitVarSizeWithMarker_Marker, - and([q8 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q8] < x_ExplicitVarSizeWithMarker_Values[q8 + 1] - | q8 : int(1..3)]), - and([q9 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q9] = 2 | q9 : int(1..4)]), - 1 <= x_ExplicitVarSizeWithMarker_Marker, - and([q12 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q14] != 6 /\ - x_ExplicitVarSizeWithDummy[q14] = x_ExplicitVarSizeWithMarker_Values[q12] - | q14 : int(1..4)]) - | q12 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q16] != 6 -> - or([q18 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q18] = x_ExplicitVarSizeWithDummy[q16] - | q18 : int(1..4)]) - | q16 : int(1..4)]), - 1 <= sum([toInt(y_Occurrence[q19]) | q19 : int(2..5)]), - and([y_Occurrence[q20] -> - or([q22 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[q22] = q20 - | q22 : int(1..4)]) - | q20 : int(2..5)]), - and([q24 <= y_ExplicitVarSizeWithMarker_Marker -> y_Occurrence[y_ExplicitVarSizeWithMarker_Values[q24]] - | q24 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_2_3_3_2-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_2_3_3_2-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_3_3_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_2_3_3_2-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_2_3_3_2-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_3_3_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_2_3_3_2.eprime b/tests/exhaustive/basic/set09/expected/model_2_3_3_2.eprime deleted file mode 100644 index f4cb2aafb3..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_3_3_2.eprime +++ /dev/null @@ -1,54 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_ExplicitVarSizeWithMarker_Marker: int(0..4) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy, - y_ExplicitVarSizeWithDummy, y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values] -such that - and([x_ExplicitVarSizeWithDummy[q31] != 6 /\ q32 <= y_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithDummy[q31] + 2 = y_ExplicitVarSizeWithMarker_Values[q32] - | q31 : int(1..4), q32 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 6 - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q2] = 6 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 6 | q2 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 6) | q3 : int(1..4)]), - and([q5 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> - y_ExplicitVarSizeWithMarker_Values[q5] < y_ExplicitVarSizeWithMarker_Values[q5 + 1] - | q5 : int(1..3)]), - and([q6 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q6] = 2 | q6 : int(1..4)]), - 1 <= y_ExplicitVarSizeWithMarker_Marker, - and([q8 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q8] < x_ExplicitVarSizeWithMarker_Values[q8 + 1] - | q8 : int(1..3)]), - and([q9 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q9] = 2 | q9 : int(1..4)]), - 1 <= x_ExplicitVarSizeWithMarker_Marker, - and([q12 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q14] != 6 /\ - x_ExplicitVarSizeWithDummy[q14] = x_ExplicitVarSizeWithMarker_Values[q12] - | q14 : int(1..4)]) - | q12 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q16] != 6 -> - or([q18 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q18] = x_ExplicitVarSizeWithDummy[q16] - | q18 : int(1..4)]) - | q16 : int(1..4)]), - and([y_ExplicitVarSizeWithDummy[q19] < y_ExplicitVarSizeWithDummy[q19 + 1] \/ y_ExplicitVarSizeWithDummy[q19] = 6 - | q19 : int(1..3)]), - and([y_ExplicitVarSizeWithDummy[q20] = 6 -> y_ExplicitVarSizeWithDummy[q20 + 1] = 6 | q20 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q21] != 6) | q21 : int(1..4)]), - and([y_ExplicitVarSizeWithDummy[q24] != 6 -> - or([q26 <= y_ExplicitVarSizeWithMarker_Marker /\ - y_ExplicitVarSizeWithMarker_Values[q26] = y_ExplicitVarSizeWithDummy[q24] - | q26 : int(1..4)]) - | q24 : int(1..4)]), - and([q28 <= y_ExplicitVarSizeWithMarker_Marker -> - or([y_ExplicitVarSizeWithDummy[q30] != 6 /\ - y_ExplicitVarSizeWithDummy[q30] = y_ExplicitVarSizeWithMarker_Values[q28] - | q30 : int(1..4)]) - | q28 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_2_3_3_3-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_2_3_3_3-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_3_3_3-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_2_3_3_3-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_2_3_3_3-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_3_3_3-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_2_3_3_3.eprime b/tests/exhaustive/basic/set09/expected/model_2_3_3_3.eprime deleted file mode 100644 index 8cb929ecd5..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_3_3_3.eprime +++ /dev/null @@ -1,39 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_ExplicitVarSizeWithMarker_Marker: int(0..4) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy, - y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values] -such that - and([x_ExplicitVarSizeWithDummy[q19] != 6 /\ q20 <= y_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithDummy[q19] + 2 = y_ExplicitVarSizeWithMarker_Values[q20] - | q19 : int(1..4), q20 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 6 - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q2] = 6 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 6 | q2 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 6) | q3 : int(1..4)]), - and([q5 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> - y_ExplicitVarSizeWithMarker_Values[q5] < y_ExplicitVarSizeWithMarker_Values[q5 + 1] - | q5 : int(1..3)]), - and([q6 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q6] = 2 | q6 : int(1..4)]), - 1 <= y_ExplicitVarSizeWithMarker_Marker, - and([q8 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q8] < x_ExplicitVarSizeWithMarker_Values[q8 + 1] - | q8 : int(1..3)]), - and([q9 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q9] = 2 | q9 : int(1..4)]), - 1 <= x_ExplicitVarSizeWithMarker_Marker, - and([q12 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q14] != 6 /\ - x_ExplicitVarSizeWithDummy[q14] = x_ExplicitVarSizeWithMarker_Values[q12] - | q14 : int(1..4)]) - | q12 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q16] != 6 -> - or([q18 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q18] = x_ExplicitVarSizeWithDummy[q16] - | q18 : int(1..4)]) - | q16 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_2_3_3_4-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_2_3_3_4-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_3_3_4-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_2_3_3_4-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_2_3_3_4-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_3_3_4-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_2_3_3_4.eprime b/tests/exhaustive/basic/set09/expected/model_2_3_3_4.eprime deleted file mode 100644 index 28b7796968..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_3_3_4.eprime +++ /dev/null @@ -1,59 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_ExplicitVarSizeWithMarker_Marker: int(0..4) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy, - y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithMarker_Marker, - y_ExplicitVarSizeWithMarker_Values] -such that - and([x_ExplicitVarSizeWithDummy[q32] != 6 /\ q33 <= y_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithDummy[q32] + 2 = y_ExplicitVarSizeWithMarker_Values[q33] - | q32 : int(1..4), q33 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 6 - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q2] = 6 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 6 | q2 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 6) | q3 : int(1..4)]), - and([q5 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> - y_ExplicitVarSizeWithMarker_Values[q5] < y_ExplicitVarSizeWithMarker_Values[q5 + 1] - | q5 : int(1..3)]), - and([q6 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q6] = 2 | q6 : int(1..4)]), - 1 <= y_ExplicitVarSizeWithMarker_Marker, - and([q8 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q8] < x_ExplicitVarSizeWithMarker_Values[q8 + 1] - | q8 : int(1..3)]), - and([q9 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q9] = 2 | q9 : int(1..4)]), - 1 <= x_ExplicitVarSizeWithMarker_Marker, - and([q12 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q14] != 6 /\ - x_ExplicitVarSizeWithDummy[q14] = x_ExplicitVarSizeWithMarker_Values[q12] - | q14 : int(1..4)]) - | q12 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q16] != 6 -> - or([q18 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q18] = x_ExplicitVarSizeWithDummy[q16] - | q18 : int(1..4)]) - | q16 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q19 + 1] -> - y_ExplicitVarSizeWithFlags_Values[q19] < y_ExplicitVarSizeWithFlags_Values[q19 + 1] - | q19 : int(1..3)]), - and([y_ExplicitVarSizeWithFlags_Flags[q20] = false -> y_ExplicitVarSizeWithFlags_Values[q20] = 2 - | q20 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q21 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q21] | q21 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q22]) | q22 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q25] -> - or([q27 <= y_ExplicitVarSizeWithMarker_Marker /\ - y_ExplicitVarSizeWithMarker_Values[q27] = y_ExplicitVarSizeWithFlags_Values[q25] - | q27 : int(1..4)]) - | q25 : int(1..4)]), - and([q29 <= y_ExplicitVarSizeWithMarker_Marker -> - or([y_ExplicitVarSizeWithFlags_Flags[q31] /\ - y_ExplicitVarSizeWithFlags_Values[q31] = y_ExplicitVarSizeWithMarker_Values[q29] - | q31 : int(1..4)]) - | q29 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_2_3_4_1-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_2_3_4_1-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_3_4_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_2_3_4_1-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_2_3_4_1-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_3_4_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_2_3_4_1.eprime b/tests/exhaustive/basic/set09/expected/model_2_3_4_1.eprime deleted file mode 100644 index 65a1069752..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_3_4_1.eprime +++ /dev/null @@ -1,48 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_ExplicitVarSizeWithMarker_Marker: int(0..4) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_Occurrence: matrix indexed by [int(2..5)] of bool -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy, y_Occurrence, - y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values] -such that - and([x_ExplicitVarSizeWithDummy[q27] != 6 /\ q28 <= y_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithDummy[q27] + 2 = y_ExplicitVarSizeWithMarker_Values[q28] - | q27 : int(1..4), q28 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 6 - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q2] = 6 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 6 | q2 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 6) | q3 : int(1..4)]), - and([q5 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> - y_ExplicitVarSizeWithMarker_Values[q5] < y_ExplicitVarSizeWithMarker_Values[q5 + 1] - | q5 : int(1..3)]), - and([q6 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q6] = 2 | q6 : int(1..4)]), - 1 <= y_ExplicitVarSizeWithMarker_Marker, - and([x_ExplicitVarSizeWithFlags_Flags[q8 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q8] < x_ExplicitVarSizeWithFlags_Values[q8 + 1] - | q8 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q9] = false -> x_ExplicitVarSizeWithFlags_Values[q9] = 2 | q9 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q10 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q10] | q10 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q11]) | q11 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q14] -> - or([x_ExplicitVarSizeWithDummy[q16] != 6 /\ - x_ExplicitVarSizeWithDummy[q16] = x_ExplicitVarSizeWithFlags_Values[q14] - | q16 : int(1..4)]) - | q14 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q18] != 6 -> - or([x_ExplicitVarSizeWithFlags_Flags[q20] /\ - x_ExplicitVarSizeWithFlags_Values[q20] = x_ExplicitVarSizeWithDummy[q18] - | q20 : int(1..4)]) - | q18 : int(1..4)]), - 1 <= sum([toInt(y_Occurrence[q21]) | q21 : int(2..5)]), - and([y_Occurrence[q22] -> - or([q24 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[q24] = q22 - | q24 : int(1..4)]) - | q22 : int(2..5)]), - and([q26 <= y_ExplicitVarSizeWithMarker_Marker -> y_Occurrence[y_ExplicitVarSizeWithMarker_Values[q26]] - | q26 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_2_3_4_2-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_2_3_4_2-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_3_4_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_2_3_4_2-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_2_3_4_2-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_3_4_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_2_3_4_2.eprime b/tests/exhaustive/basic/set09/expected/model_2_3_4_2.eprime deleted file mode 100644 index 6026ed497b..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_3_4_2.eprime +++ /dev/null @@ -1,55 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_ExplicitVarSizeWithMarker_Marker: int(0..4) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy, - y_ExplicitVarSizeWithDummy, y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values] -such that - and([x_ExplicitVarSizeWithDummy[q33] != 6 /\ q34 <= y_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithDummy[q33] + 2 = y_ExplicitVarSizeWithMarker_Values[q34] - | q33 : int(1..4), q34 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 6 - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q2] = 6 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 6 | q2 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 6) | q3 : int(1..4)]), - and([q5 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> - y_ExplicitVarSizeWithMarker_Values[q5] < y_ExplicitVarSizeWithMarker_Values[q5 + 1] - | q5 : int(1..3)]), - and([q6 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q6] = 2 | q6 : int(1..4)]), - 1 <= y_ExplicitVarSizeWithMarker_Marker, - and([x_ExplicitVarSizeWithFlags_Flags[q8 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q8] < x_ExplicitVarSizeWithFlags_Values[q8 + 1] - | q8 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q9] = false -> x_ExplicitVarSizeWithFlags_Values[q9] = 2 | q9 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q10 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q10] | q10 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q11]) | q11 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q14] -> - or([x_ExplicitVarSizeWithDummy[q16] != 6 /\ - x_ExplicitVarSizeWithDummy[q16] = x_ExplicitVarSizeWithFlags_Values[q14] - | q16 : int(1..4)]) - | q14 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q18] != 6 -> - or([x_ExplicitVarSizeWithFlags_Flags[q20] /\ - x_ExplicitVarSizeWithFlags_Values[q20] = x_ExplicitVarSizeWithDummy[q18] - | q20 : int(1..4)]) - | q18 : int(1..4)]), - and([y_ExplicitVarSizeWithDummy[q21] < y_ExplicitVarSizeWithDummy[q21 + 1] \/ y_ExplicitVarSizeWithDummy[q21] = 6 - | q21 : int(1..3)]), - and([y_ExplicitVarSizeWithDummy[q22] = 6 -> y_ExplicitVarSizeWithDummy[q22 + 1] = 6 | q22 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q23] != 6) | q23 : int(1..4)]), - and([y_ExplicitVarSizeWithDummy[q26] != 6 -> - or([q28 <= y_ExplicitVarSizeWithMarker_Marker /\ - y_ExplicitVarSizeWithMarker_Values[q28] = y_ExplicitVarSizeWithDummy[q26] - | q28 : int(1..4)]) - | q26 : int(1..4)]), - and([q30 <= y_ExplicitVarSizeWithMarker_Marker -> - or([y_ExplicitVarSizeWithDummy[q32] != 6 /\ - y_ExplicitVarSizeWithDummy[q32] = y_ExplicitVarSizeWithMarker_Values[q30] - | q32 : int(1..4)]) - | q30 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_2_3_4_3-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_2_3_4_3-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_3_4_3-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_2_3_4_3-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_2_3_4_3-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_3_4_3-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_2_3_4_3.eprime b/tests/exhaustive/basic/set09/expected/model_2_3_4_3.eprime deleted file mode 100644 index f8dcddf3df..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_3_4_3.eprime +++ /dev/null @@ -1,40 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_ExplicitVarSizeWithMarker_Marker: int(0..4) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy, - y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values] -such that - and([x_ExplicitVarSizeWithDummy[q21] != 6 /\ q22 <= y_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithDummy[q21] + 2 = y_ExplicitVarSizeWithMarker_Values[q22] - | q21 : int(1..4), q22 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 6 - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q2] = 6 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 6 | q2 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 6) | q3 : int(1..4)]), - and([q5 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> - y_ExplicitVarSizeWithMarker_Values[q5] < y_ExplicitVarSizeWithMarker_Values[q5 + 1] - | q5 : int(1..3)]), - and([q6 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q6] = 2 | q6 : int(1..4)]), - 1 <= y_ExplicitVarSizeWithMarker_Marker, - and([x_ExplicitVarSizeWithFlags_Flags[q8 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q8] < x_ExplicitVarSizeWithFlags_Values[q8 + 1] - | q8 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q9] = false -> x_ExplicitVarSizeWithFlags_Values[q9] = 2 | q9 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q10 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q10] | q10 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q11]) | q11 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q14] -> - or([x_ExplicitVarSizeWithDummy[q16] != 6 /\ - x_ExplicitVarSizeWithDummy[q16] = x_ExplicitVarSizeWithFlags_Values[q14] - | q16 : int(1..4)]) - | q14 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q18] != 6 -> - or([x_ExplicitVarSizeWithFlags_Flags[q20] /\ - x_ExplicitVarSizeWithFlags_Values[q20] = x_ExplicitVarSizeWithDummy[q18] - | q20 : int(1..4)]) - | q18 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_2_3_4_4-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_2_3_4_4-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_3_4_4-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_2_3_4_4-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_2_3_4_4-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_3_4_4-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_2_3_4_4.eprime b/tests/exhaustive/basic/set09/expected/model_2_3_4_4.eprime deleted file mode 100644 index 1cc5077042..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_3_4_4.eprime +++ /dev/null @@ -1,60 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_ExplicitVarSizeWithMarker_Marker: int(0..4) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy, - y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithMarker_Marker, - y_ExplicitVarSizeWithMarker_Values] -such that - and([x_ExplicitVarSizeWithDummy[q34] != 6 /\ q35 <= y_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithDummy[q34] + 2 = y_ExplicitVarSizeWithMarker_Values[q35] - | q34 : int(1..4), q35 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 6 - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q2] = 6 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 6 | q2 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 6) | q3 : int(1..4)]), - and([q5 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> - y_ExplicitVarSizeWithMarker_Values[q5] < y_ExplicitVarSizeWithMarker_Values[q5 + 1] - | q5 : int(1..3)]), - and([q6 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q6] = 2 | q6 : int(1..4)]), - 1 <= y_ExplicitVarSizeWithMarker_Marker, - and([x_ExplicitVarSizeWithFlags_Flags[q8 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q8] < x_ExplicitVarSizeWithFlags_Values[q8 + 1] - | q8 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q9] = false -> x_ExplicitVarSizeWithFlags_Values[q9] = 2 | q9 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q10 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q10] | q10 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q11]) | q11 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q14] -> - or([x_ExplicitVarSizeWithDummy[q16] != 6 /\ - x_ExplicitVarSizeWithDummy[q16] = x_ExplicitVarSizeWithFlags_Values[q14] - | q16 : int(1..4)]) - | q14 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q18] != 6 -> - or([x_ExplicitVarSizeWithFlags_Flags[q20] /\ - x_ExplicitVarSizeWithFlags_Values[q20] = x_ExplicitVarSizeWithDummy[q18] - | q20 : int(1..4)]) - | q18 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q21 + 1] -> - y_ExplicitVarSizeWithFlags_Values[q21] < y_ExplicitVarSizeWithFlags_Values[q21 + 1] - | q21 : int(1..3)]), - and([y_ExplicitVarSizeWithFlags_Flags[q22] = false -> y_ExplicitVarSizeWithFlags_Values[q22] = 2 - | q22 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q23 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q23] | q23 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q24]) | q24 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q27] -> - or([q29 <= y_ExplicitVarSizeWithMarker_Marker /\ - y_ExplicitVarSizeWithMarker_Values[q29] = y_ExplicitVarSizeWithFlags_Values[q27] - | q29 : int(1..4)]) - | q27 : int(1..4)]), - and([q31 <= y_ExplicitVarSizeWithMarker_Marker -> - or([y_ExplicitVarSizeWithFlags_Flags[q33] /\ - y_ExplicitVarSizeWithFlags_Values[q33] = y_ExplicitVarSizeWithMarker_Values[q31] - | q33 : int(1..4)]) - | q31 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_2_4_1_1-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_2_4_1_1-solution000001.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_4_1_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_2_4_1_1-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_2_4_1_1-solution000002.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_4_1_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_2_4_1_1.eprime b/tests/exhaustive/basic/set09/expected/model_2_4_1_1.eprime deleted file mode 100644 index 51a23a711f..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_4_1_1.eprime +++ /dev/null @@ -1,36 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -find x_Occurrence: matrix indexed by [int(2..5)] of bool -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_Occurrence: matrix indexed by [int(2..5)] of bool -branching on - [x_Occurrence, x_ExplicitVarSizeWithDummy, y_Occurrence, y_ExplicitVarSizeWithFlags_Flags, - y_ExplicitVarSizeWithFlags_Values] -such that - and([x_ExplicitVarSizeWithDummy[q17] != 6 /\ y_ExplicitVarSizeWithFlags_Flags[q18] -> - x_ExplicitVarSizeWithDummy[q17] + 2 = y_ExplicitVarSizeWithFlags_Values[q18] - | q17 : int(1..4), q18 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 6 - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q2] = 6 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 6 | q2 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 6) | q3 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q5 + 1] -> - y_ExplicitVarSizeWithFlags_Values[q5] < y_ExplicitVarSizeWithFlags_Values[q5 + 1] - | q5 : int(1..3)]), - and([y_ExplicitVarSizeWithFlags_Flags[q6] = false -> y_ExplicitVarSizeWithFlags_Values[q6] = 2 | q6 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q7] | q7 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q8]) | q8 : int(1..4)]), - 1 <= sum([toInt(x_Occurrence[q10]) | q10 : int(2..5)]), - and([x_Occurrence[q19] -> - or([x_ExplicitVarSizeWithDummy[q21] != 6 /\ x_ExplicitVarSizeWithDummy[q21] = q19 | q21 : int(1..4)]) - | q19 : int(2..5)]), - and([x_ExplicitVarSizeWithDummy[q23] != 6 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q23]] | q23 : int(1..4)]), - 1 <= sum([toInt(y_Occurrence[q11]) | q11 : int(2..5)]), - and([y_Occurrence[q12] -> - or([y_ExplicitVarSizeWithFlags_Flags[q14] /\ y_ExplicitVarSizeWithFlags_Values[q14] = q12 | q14 : int(1..4)]) - | q12 : int(2..5)]), - and([y_ExplicitVarSizeWithFlags_Flags[q16] -> y_Occurrence[y_ExplicitVarSizeWithFlags_Values[q16]] - | q16 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_2_4_1_2-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_2_4_1_2-solution000001.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_4_1_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_2_4_1_2-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_2_4_1_2-solution000002.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_4_1_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_2_4_1_2.eprime b/tests/exhaustive/basic/set09/expected/model_2_4_1_2.eprime deleted file mode 100644 index 083bfa5f86..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_4_1_2.eprime +++ /dev/null @@ -1,44 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -find x_Occurrence: matrix indexed by [int(2..5)] of bool -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -branching on - [x_Occurrence, x_ExplicitVarSizeWithDummy, y_ExplicitVarSizeWithDummy, y_ExplicitVarSizeWithFlags_Flags, - y_ExplicitVarSizeWithFlags_Values] -such that - and([x_ExplicitVarSizeWithDummy[q28] != 6 /\ y_ExplicitVarSizeWithFlags_Flags[q29] -> - x_ExplicitVarSizeWithDummy[q28] + 2 = y_ExplicitVarSizeWithFlags_Values[q29] - | q28 : int(1..4), q29 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 6 - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q2] = 6 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 6 | q2 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 6) | q3 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q5 + 1] -> - y_ExplicitVarSizeWithFlags_Values[q5] < y_ExplicitVarSizeWithFlags_Values[q5 + 1] - | q5 : int(1..3)]), - and([y_ExplicitVarSizeWithFlags_Flags[q6] = false -> y_ExplicitVarSizeWithFlags_Values[q6] = 2 | q6 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q7] | q7 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q8]) | q8 : int(1..4)]), - 1 <= sum([toInt(x_Occurrence[q10]) | q10 : int(2..5)]), - and([x_Occurrence[q23] -> - or([x_ExplicitVarSizeWithDummy[q25] != 6 /\ x_ExplicitVarSizeWithDummy[q25] = q23 | q25 : int(1..4)]) - | q23 : int(2..5)]), - and([x_ExplicitVarSizeWithDummy[q27] != 6 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q27]] | q27 : int(1..4)]), - and([y_ExplicitVarSizeWithDummy[q11] < y_ExplicitVarSizeWithDummy[q11 + 1] \/ y_ExplicitVarSizeWithDummy[q11] = 6 - | q11 : int(1..3)]), - and([y_ExplicitVarSizeWithDummy[q12] = 6 -> y_ExplicitVarSizeWithDummy[q12 + 1] = 6 | q12 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q13] != 6) | q13 : int(1..4)]), - and([y_ExplicitVarSizeWithDummy[q16] != 6 -> - or([y_ExplicitVarSizeWithFlags_Flags[q18] /\ - y_ExplicitVarSizeWithFlags_Values[q18] = y_ExplicitVarSizeWithDummy[q16] - | q18 : int(1..4)]) - | q16 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q20] -> - or([y_ExplicitVarSizeWithDummy[q22] != 6 /\ - y_ExplicitVarSizeWithDummy[q22] = y_ExplicitVarSizeWithFlags_Values[q20] - | q22 : int(1..4)]) - | q20 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_2_4_1_3-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_2_4_1_3-solution000001.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_4_1_3-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_2_4_1_3-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_2_4_1_3-solution000002.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_4_1_3-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_2_4_1_3.eprime b/tests/exhaustive/basic/set09/expected/model_2_4_1_3.eprime deleted file mode 100644 index c74d6fc321..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_4_1_3.eprime +++ /dev/null @@ -1,46 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -find x_Occurrence: matrix indexed by [int(2..5)] of bool -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_ExplicitVarSizeWithMarker_Marker: int(0..4) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -branching on - [x_Occurrence, x_ExplicitVarSizeWithDummy, y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values, - y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values] -such that - and([x_ExplicitVarSizeWithDummy[q27] != 6 /\ y_ExplicitVarSizeWithFlags_Flags[q28] -> - x_ExplicitVarSizeWithDummy[q27] + 2 = y_ExplicitVarSizeWithFlags_Values[q28] - | q27 : int(1..4), q28 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 6 - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q2] = 6 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 6 | q2 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 6) | q3 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q5 + 1] -> - y_ExplicitVarSizeWithFlags_Values[q5] < y_ExplicitVarSizeWithFlags_Values[q5 + 1] - | q5 : int(1..3)]), - and([y_ExplicitVarSizeWithFlags_Flags[q6] = false -> y_ExplicitVarSizeWithFlags_Values[q6] = 2 | q6 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q7] | q7 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q8]) | q8 : int(1..4)]), - 1 <= sum([toInt(x_Occurrence[q10]) | q10 : int(2..5)]), - and([x_Occurrence[q22] -> - or([x_ExplicitVarSizeWithDummy[q24] != 6 /\ x_ExplicitVarSizeWithDummy[q24] = q22 | q24 : int(1..4)]) - | q22 : int(2..5)]), - and([x_ExplicitVarSizeWithDummy[q26] != 6 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q26]] | q26 : int(1..4)]), - and([q11 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> - y_ExplicitVarSizeWithMarker_Values[q11] < y_ExplicitVarSizeWithMarker_Values[q11 + 1] - | q11 : int(1..3)]), - and([q12 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q12] = 2 | q12 : int(1..4)]), - 1 <= y_ExplicitVarSizeWithMarker_Marker, - and([q15 <= y_ExplicitVarSizeWithMarker_Marker -> - or([y_ExplicitVarSizeWithFlags_Flags[q17] /\ - y_ExplicitVarSizeWithFlags_Values[q17] = y_ExplicitVarSizeWithMarker_Values[q15] - | q17 : int(1..4)]) - | q15 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q19] -> - or([q21 <= y_ExplicitVarSizeWithMarker_Marker /\ - y_ExplicitVarSizeWithMarker_Values[q21] = y_ExplicitVarSizeWithFlags_Values[q19] - | q21 : int(1..4)]) - | q19 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_2_4_1_4-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_2_4_1_4-solution000001.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_4_1_4-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_2_4_1_4-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_2_4_1_4-solution000002.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_4_1_4-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_2_4_1_4.eprime b/tests/exhaustive/basic/set09/expected/model_2_4_1_4.eprime deleted file mode 100644 index 97d878a880..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_4_1_4.eprime +++ /dev/null @@ -1,28 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -find x_Occurrence: matrix indexed by [int(2..5)] of bool -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -branching on - [x_Occurrence, x_ExplicitVarSizeWithDummy, y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values] -such that - and([x_ExplicitVarSizeWithDummy[q16] != 6 /\ y_ExplicitVarSizeWithFlags_Flags[q17] -> - x_ExplicitVarSizeWithDummy[q16] + 2 = y_ExplicitVarSizeWithFlags_Values[q17] - | q16 : int(1..4), q17 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 6 - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q2] = 6 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 6 | q2 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 6) | q3 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q5 + 1] -> - y_ExplicitVarSizeWithFlags_Values[q5] < y_ExplicitVarSizeWithFlags_Values[q5 + 1] - | q5 : int(1..3)]), - and([y_ExplicitVarSizeWithFlags_Flags[q6] = false -> y_ExplicitVarSizeWithFlags_Values[q6] = 2 | q6 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q7] | q7 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q8]) | q8 : int(1..4)]), - 1 <= sum([toInt(x_Occurrence[q10]) | q10 : int(2..5)]), - and([x_Occurrence[q11] -> - or([x_ExplicitVarSizeWithDummy[q13] != 6 /\ x_ExplicitVarSizeWithDummy[q13] = q11 | q13 : int(1..4)]) - | q11 : int(2..5)]), - and([x_ExplicitVarSizeWithDummy[q15] != 6 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q15]] | q15 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_2_4_2_1-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_2_4_2_1-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_4_2_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_2_4_2_1-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_2_4_2_1-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_4_2_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_2_4_2_1.eprime b/tests/exhaustive/basic/set09/expected/model_2_4_2_1.eprime deleted file mode 100644 index d2d26b37e7..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_4_2_1.eprime +++ /dev/null @@ -1,29 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_Occurrence: matrix indexed by [int(2..5)] of bool -branching on - [x_ExplicitVarSizeWithDummy, y_Occurrence, y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values] -such that - and([x_ExplicitVarSizeWithDummy[q16] != 6 /\ y_ExplicitVarSizeWithFlags_Flags[q17] -> - x_ExplicitVarSizeWithDummy[q16] + 2 = y_ExplicitVarSizeWithFlags_Values[q17] - | q16 : int(1..4), q17 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 6 - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q2] = 6 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 6 | q2 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 6) | q3 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q5 + 1] -> - y_ExplicitVarSizeWithFlags_Values[q5] < y_ExplicitVarSizeWithFlags_Values[q5 + 1] - | q5 : int(1..3)]), - and([y_ExplicitVarSizeWithFlags_Flags[q6] = false -> y_ExplicitVarSizeWithFlags_Values[q6] = 2 | q6 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q7] | q7 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q8]) | q8 : int(1..4)]), - 1 <= sum([toInt(y_Occurrence[q10]) | q10 : int(2..5)]), - and([y_Occurrence[q11] -> - or([y_ExplicitVarSizeWithFlags_Flags[q13] /\ y_ExplicitVarSizeWithFlags_Values[q13] = q11 | q13 : int(1..4)]) - | q11 : int(2..5)]), - and([y_ExplicitVarSizeWithFlags_Flags[q15] -> y_Occurrence[y_ExplicitVarSizeWithFlags_Values[q15]] - | q15 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_2_4_2_2-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_2_4_2_2-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_4_2_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_2_4_2_2-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_2_4_2_2-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_4_2_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_2_4_2_2.eprime b/tests/exhaustive/basic/set09/expected/model_2_4_2_2.eprime deleted file mode 100644 index 327bbcc12e..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_4_2_2.eprime +++ /dev/null @@ -1,38 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -branching on - [x_ExplicitVarSizeWithDummy, y_ExplicitVarSizeWithDummy, y_ExplicitVarSizeWithFlags_Flags, - y_ExplicitVarSizeWithFlags_Values] -such that - and([x_ExplicitVarSizeWithDummy[q22] != 6 /\ y_ExplicitVarSizeWithFlags_Flags[q23] -> - x_ExplicitVarSizeWithDummy[q22] + 2 = y_ExplicitVarSizeWithFlags_Values[q23] - | q22 : int(1..4), q23 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 6 - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q2] = 6 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 6 | q2 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 6) | q3 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q5 + 1] -> - y_ExplicitVarSizeWithFlags_Values[q5] < y_ExplicitVarSizeWithFlags_Values[q5 + 1] - | q5 : int(1..3)]), - and([y_ExplicitVarSizeWithFlags_Flags[q6] = false -> y_ExplicitVarSizeWithFlags_Values[q6] = 2 | q6 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q7] | q7 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q8]) | q8 : int(1..4)]), - and([y_ExplicitVarSizeWithDummy[q10] < y_ExplicitVarSizeWithDummy[q10 + 1] \/ y_ExplicitVarSizeWithDummy[q10] = 6 - | q10 : int(1..3)]), - and([y_ExplicitVarSizeWithDummy[q11] = 6 -> y_ExplicitVarSizeWithDummy[q11 + 1] = 6 | q11 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q12] != 6) | q12 : int(1..4)]), - and([y_ExplicitVarSizeWithDummy[q15] != 6 -> - or([y_ExplicitVarSizeWithFlags_Flags[q17] /\ - y_ExplicitVarSizeWithFlags_Values[q17] = y_ExplicitVarSizeWithDummy[q15] - | q17 : int(1..4)]) - | q15 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q19] -> - or([y_ExplicitVarSizeWithDummy[q21] != 6 /\ - y_ExplicitVarSizeWithDummy[q21] = y_ExplicitVarSizeWithFlags_Values[q19] - | q21 : int(1..4)]) - | q19 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_2_4_2_3-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_2_4_2_3-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_4_2_3-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_2_4_2_3-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_2_4_2_3-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_4_2_3-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_2_4_2_3.eprime b/tests/exhaustive/basic/set09/expected/model_2_4_2_3.eprime deleted file mode 100644 index 7b22da50fd..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_4_2_3.eprime +++ /dev/null @@ -1,40 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_ExplicitVarSizeWithMarker_Marker: int(0..4) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -branching on - [x_ExplicitVarSizeWithDummy, y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values, - y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values] -such that - and([x_ExplicitVarSizeWithDummy[q21] != 6 /\ y_ExplicitVarSizeWithFlags_Flags[q22] -> - x_ExplicitVarSizeWithDummy[q21] + 2 = y_ExplicitVarSizeWithFlags_Values[q22] - | q21 : int(1..4), q22 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 6 - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q2] = 6 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 6 | q2 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 6) | q3 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q5 + 1] -> - y_ExplicitVarSizeWithFlags_Values[q5] < y_ExplicitVarSizeWithFlags_Values[q5 + 1] - | q5 : int(1..3)]), - and([y_ExplicitVarSizeWithFlags_Flags[q6] = false -> y_ExplicitVarSizeWithFlags_Values[q6] = 2 | q6 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q7] | q7 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q8]) | q8 : int(1..4)]), - and([q10 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> - y_ExplicitVarSizeWithMarker_Values[q10] < y_ExplicitVarSizeWithMarker_Values[q10 + 1] - | q10 : int(1..3)]), - and([q11 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q11] = 2 | q11 : int(1..4)]), - 1 <= y_ExplicitVarSizeWithMarker_Marker, - and([q14 <= y_ExplicitVarSizeWithMarker_Marker -> - or([y_ExplicitVarSizeWithFlags_Flags[q16] /\ - y_ExplicitVarSizeWithFlags_Values[q16] = y_ExplicitVarSizeWithMarker_Values[q14] - | q16 : int(1..4)]) - | q14 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q18] -> - or([q20 <= y_ExplicitVarSizeWithMarker_Marker /\ - y_ExplicitVarSizeWithMarker_Values[q20] = y_ExplicitVarSizeWithFlags_Values[q18] - | q20 : int(1..4)]) - | q18 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_2_4_2_4-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_2_4_2_4-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_4_2_4-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_2_4_2_4-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_2_4_2_4-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_4_2_4-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_2_4_2_4.eprime b/tests/exhaustive/basic/set09/expected/model_2_4_2_4.eprime deleted file mode 100644 index 1fa334760d..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_4_2_4.eprime +++ /dev/null @@ -1,21 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -branching on [x_ExplicitVarSizeWithDummy, y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values] -such that - and([x_ExplicitVarSizeWithDummy[q10] != 6 /\ y_ExplicitVarSizeWithFlags_Flags[q11] -> - x_ExplicitVarSizeWithDummy[q10] + 2 = y_ExplicitVarSizeWithFlags_Values[q11] - | q10 : int(1..4), q11 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 6 - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q2] = 6 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 6 | q2 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 6) | q3 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q5 + 1] -> - y_ExplicitVarSizeWithFlags_Values[q5] < y_ExplicitVarSizeWithFlags_Values[q5 + 1] - | q5 : int(1..3)]), - and([y_ExplicitVarSizeWithFlags_Flags[q6] = false -> y_ExplicitVarSizeWithFlags_Values[q6] = 2 | q6 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q7] | q7 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q8]) | q8 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_2_4_3_1-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_2_4_3_1-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_4_3_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_2_4_3_1-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_2_4_3_1-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_4_3_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_2_4_3_1.eprime b/tests/exhaustive/basic/set09/expected/model_2_4_3_1.eprime deleted file mode 100644 index 25a9e61546..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_4_3_1.eprime +++ /dev/null @@ -1,47 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_Occurrence: matrix indexed by [int(2..5)] of bool -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy, y_Occurrence, - y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values] -such that - and([x_ExplicitVarSizeWithDummy[q27] != 6 /\ y_ExplicitVarSizeWithFlags_Flags[q28] -> - x_ExplicitVarSizeWithDummy[q27] + 2 = y_ExplicitVarSizeWithFlags_Values[q28] - | q27 : int(1..4), q28 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 6 - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q2] = 6 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 6 | q2 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 6) | q3 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q5 + 1] -> - y_ExplicitVarSizeWithFlags_Values[q5] < y_ExplicitVarSizeWithFlags_Values[q5 + 1] - | q5 : int(1..3)]), - and([y_ExplicitVarSizeWithFlags_Flags[q6] = false -> y_ExplicitVarSizeWithFlags_Values[q6] = 2 | q6 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q7] | q7 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q8]) | q8 : int(1..4)]), - and([q10 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q10] < x_ExplicitVarSizeWithMarker_Values[q10 + 1] - | q10 : int(1..3)]), - and([q11 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q11] = 2 | q11 : int(1..4)]), - 1 <= x_ExplicitVarSizeWithMarker_Marker, - and([q14 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q16] != 6 /\ - x_ExplicitVarSizeWithDummy[q16] = x_ExplicitVarSizeWithMarker_Values[q14] - | q16 : int(1..4)]) - | q14 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q18] != 6 -> - or([q20 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q20] = x_ExplicitVarSizeWithDummy[q18] - | q20 : int(1..4)]) - | q18 : int(1..4)]), - 1 <= sum([toInt(y_Occurrence[q21]) | q21 : int(2..5)]), - and([y_Occurrence[q22] -> - or([y_ExplicitVarSizeWithFlags_Flags[q24] /\ y_ExplicitVarSizeWithFlags_Values[q24] = q22 | q24 : int(1..4)]) - | q22 : int(2..5)]), - and([y_ExplicitVarSizeWithFlags_Flags[q26] -> y_Occurrence[y_ExplicitVarSizeWithFlags_Values[q26]] - | q26 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_2_4_3_2-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_2_4_3_2-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_4_3_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_2_4_3_2-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_2_4_3_2-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_4_3_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_2_4_3_2.eprime b/tests/exhaustive/basic/set09/expected/model_2_4_3_2.eprime deleted file mode 100644 index 64200ff954..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_4_3_2.eprime +++ /dev/null @@ -1,55 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy, - y_ExplicitVarSizeWithDummy, y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values] -such that - and([x_ExplicitVarSizeWithDummy[q33] != 6 /\ y_ExplicitVarSizeWithFlags_Flags[q34] -> - x_ExplicitVarSizeWithDummy[q33] + 2 = y_ExplicitVarSizeWithFlags_Values[q34] - | q33 : int(1..4), q34 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 6 - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q2] = 6 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 6 | q2 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 6) | q3 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q5 + 1] -> - y_ExplicitVarSizeWithFlags_Values[q5] < y_ExplicitVarSizeWithFlags_Values[q5 + 1] - | q5 : int(1..3)]), - and([y_ExplicitVarSizeWithFlags_Flags[q6] = false -> y_ExplicitVarSizeWithFlags_Values[q6] = 2 | q6 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q7] | q7 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q8]) | q8 : int(1..4)]), - and([q10 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q10] < x_ExplicitVarSizeWithMarker_Values[q10 + 1] - | q10 : int(1..3)]), - and([q11 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q11] = 2 | q11 : int(1..4)]), - 1 <= x_ExplicitVarSizeWithMarker_Marker, - and([q14 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q16] != 6 /\ - x_ExplicitVarSizeWithDummy[q16] = x_ExplicitVarSizeWithMarker_Values[q14] - | q16 : int(1..4)]) - | q14 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q18] != 6 -> - or([q20 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q20] = x_ExplicitVarSizeWithDummy[q18] - | q20 : int(1..4)]) - | q18 : int(1..4)]), - and([y_ExplicitVarSizeWithDummy[q21] < y_ExplicitVarSizeWithDummy[q21 + 1] \/ y_ExplicitVarSizeWithDummy[q21] = 6 - | q21 : int(1..3)]), - and([y_ExplicitVarSizeWithDummy[q22] = 6 -> y_ExplicitVarSizeWithDummy[q22 + 1] = 6 | q22 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q23] != 6) | q23 : int(1..4)]), - and([y_ExplicitVarSizeWithDummy[q26] != 6 -> - or([y_ExplicitVarSizeWithFlags_Flags[q28] /\ - y_ExplicitVarSizeWithFlags_Values[q28] = y_ExplicitVarSizeWithDummy[q26] - | q28 : int(1..4)]) - | q26 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q30] -> - or([y_ExplicitVarSizeWithDummy[q32] != 6 /\ - y_ExplicitVarSizeWithDummy[q32] = y_ExplicitVarSizeWithFlags_Values[q30] - | q32 : int(1..4)]) - | q30 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_2_4_3_3-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_2_4_3_3-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_4_3_3-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_2_4_3_3-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_2_4_3_3-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_4_3_3-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_2_4_3_3.eprime b/tests/exhaustive/basic/set09/expected/model_2_4_3_3.eprime deleted file mode 100644 index ccb1314b95..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_4_3_3.eprime +++ /dev/null @@ -1,58 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_ExplicitVarSizeWithMarker_Marker: int(0..4) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy, - y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithFlags_Flags, - y_ExplicitVarSizeWithFlags_Values] -such that - and([x_ExplicitVarSizeWithDummy[q32] != 6 /\ y_ExplicitVarSizeWithFlags_Flags[q33] -> - x_ExplicitVarSizeWithDummy[q32] + 2 = y_ExplicitVarSizeWithFlags_Values[q33] - | q32 : int(1..4), q33 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 6 - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q2] = 6 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 6 | q2 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 6) | q3 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q5 + 1] -> - y_ExplicitVarSizeWithFlags_Values[q5] < y_ExplicitVarSizeWithFlags_Values[q5 + 1] - | q5 : int(1..3)]), - and([y_ExplicitVarSizeWithFlags_Flags[q6] = false -> y_ExplicitVarSizeWithFlags_Values[q6] = 2 | q6 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q7] | q7 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q8]) | q8 : int(1..4)]), - and([q10 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q10] < x_ExplicitVarSizeWithMarker_Values[q10 + 1] - | q10 : int(1..3)]), - and([q11 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q11] = 2 | q11 : int(1..4)]), - 1 <= x_ExplicitVarSizeWithMarker_Marker, - and([q14 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q16] != 6 /\ - x_ExplicitVarSizeWithDummy[q16] = x_ExplicitVarSizeWithMarker_Values[q14] - | q16 : int(1..4)]) - | q14 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q18] != 6 -> - or([q20 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q20] = x_ExplicitVarSizeWithDummy[q18] - | q20 : int(1..4)]) - | q18 : int(1..4)]), - and([q21 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> - y_ExplicitVarSizeWithMarker_Values[q21] < y_ExplicitVarSizeWithMarker_Values[q21 + 1] - | q21 : int(1..3)]), - and([q22 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q22] = 2 | q22 : int(1..4)]), - 1 <= y_ExplicitVarSizeWithMarker_Marker, - and([q25 <= y_ExplicitVarSizeWithMarker_Marker -> - or([y_ExplicitVarSizeWithFlags_Flags[q27] /\ - y_ExplicitVarSizeWithFlags_Values[q27] = y_ExplicitVarSizeWithMarker_Values[q25] - | q27 : int(1..4)]) - | q25 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q29] -> - or([q31 <= y_ExplicitVarSizeWithMarker_Marker /\ - y_ExplicitVarSizeWithMarker_Values[q31] = y_ExplicitVarSizeWithFlags_Values[q29] - | q31 : int(1..4)]) - | q29 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_2_4_3_4-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_2_4_3_4-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_4_3_4-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_2_4_3_4-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_2_4_3_4-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_4_3_4-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_2_4_3_4.eprime b/tests/exhaustive/basic/set09/expected/model_2_4_3_4.eprime deleted file mode 100644 index f3cf03d434..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_4_3_4.eprime +++ /dev/null @@ -1,40 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy, - y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values] -such that - and([x_ExplicitVarSizeWithDummy[q21] != 6 /\ y_ExplicitVarSizeWithFlags_Flags[q22] -> - x_ExplicitVarSizeWithDummy[q21] + 2 = y_ExplicitVarSizeWithFlags_Values[q22] - | q21 : int(1..4), q22 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 6 - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q2] = 6 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 6 | q2 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 6) | q3 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q5 + 1] -> - y_ExplicitVarSizeWithFlags_Values[q5] < y_ExplicitVarSizeWithFlags_Values[q5 + 1] - | q5 : int(1..3)]), - and([y_ExplicitVarSizeWithFlags_Flags[q6] = false -> y_ExplicitVarSizeWithFlags_Values[q6] = 2 | q6 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q7] | q7 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q8]) | q8 : int(1..4)]), - and([q10 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q10] < x_ExplicitVarSizeWithMarker_Values[q10 + 1] - | q10 : int(1..3)]), - and([q11 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q11] = 2 | q11 : int(1..4)]), - 1 <= x_ExplicitVarSizeWithMarker_Marker, - and([q14 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q16] != 6 /\ - x_ExplicitVarSizeWithDummy[q16] = x_ExplicitVarSizeWithMarker_Values[q14] - | q16 : int(1..4)]) - | q14 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q18] != 6 -> - or([q20 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q20] = x_ExplicitVarSizeWithDummy[q18] - | q20 : int(1..4)]) - | q18 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_2_4_4_1-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_2_4_4_1-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_4_4_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_2_4_4_1-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_2_4_4_1-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_4_4_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_2_4_4_1.eprime b/tests/exhaustive/basic/set09/expected/model_2_4_4_1.eprime deleted file mode 100644 index 2e1cf8717a..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_4_4_1.eprime +++ /dev/null @@ -1,49 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_Occurrence: matrix indexed by [int(2..5)] of bool -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy, y_Occurrence, - y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values] -such that - and([x_ExplicitVarSizeWithDummy[q29] != 6 /\ y_ExplicitVarSizeWithFlags_Flags[q30] -> - x_ExplicitVarSizeWithDummy[q29] + 2 = y_ExplicitVarSizeWithFlags_Values[q30] - | q29 : int(1..4), q30 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 6 - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q2] = 6 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 6 | q2 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 6) | q3 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q5 + 1] -> - y_ExplicitVarSizeWithFlags_Values[q5] < y_ExplicitVarSizeWithFlags_Values[q5 + 1] - | q5 : int(1..3)]), - and([y_ExplicitVarSizeWithFlags_Flags[q6] = false -> y_ExplicitVarSizeWithFlags_Values[q6] = 2 | q6 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q7] | q7 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q8]) | q8 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q10 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q10] < x_ExplicitVarSizeWithFlags_Values[q10 + 1] - | q10 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q11] = false -> x_ExplicitVarSizeWithFlags_Values[q11] = 2 - | q11 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q12 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q12] | q12 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q13]) | q13 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q16] -> - or([x_ExplicitVarSizeWithDummy[q18] != 6 /\ - x_ExplicitVarSizeWithDummy[q18] = x_ExplicitVarSizeWithFlags_Values[q16] - | q18 : int(1..4)]) - | q16 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q20] != 6 -> - or([x_ExplicitVarSizeWithFlags_Flags[q22] /\ - x_ExplicitVarSizeWithFlags_Values[q22] = x_ExplicitVarSizeWithDummy[q20] - | q22 : int(1..4)]) - | q20 : int(1..4)]), - 1 <= sum([toInt(y_Occurrence[q23]) | q23 : int(2..5)]), - and([y_Occurrence[q24] -> - or([y_ExplicitVarSizeWithFlags_Flags[q26] /\ y_ExplicitVarSizeWithFlags_Values[q26] = q24 | q26 : int(1..4)]) - | q24 : int(2..5)]), - and([y_ExplicitVarSizeWithFlags_Flags[q28] -> y_Occurrence[y_ExplicitVarSizeWithFlags_Values[q28]] - | q28 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_2_4_4_2-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_2_4_4_2-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_4_4_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_2_4_4_2-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_2_4_4_2-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_4_4_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_2_4_4_2.eprime b/tests/exhaustive/basic/set09/expected/model_2_4_4_2.eprime deleted file mode 100644 index ad0d98f173..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_4_4_2.eprime +++ /dev/null @@ -1,57 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy, - y_ExplicitVarSizeWithDummy, y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values] -such that - and([x_ExplicitVarSizeWithDummy[q35] != 6 /\ y_ExplicitVarSizeWithFlags_Flags[q36] -> - x_ExplicitVarSizeWithDummy[q35] + 2 = y_ExplicitVarSizeWithFlags_Values[q36] - | q35 : int(1..4), q36 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 6 - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q2] = 6 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 6 | q2 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 6) | q3 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q5 + 1] -> - y_ExplicitVarSizeWithFlags_Values[q5] < y_ExplicitVarSizeWithFlags_Values[q5 + 1] - | q5 : int(1..3)]), - and([y_ExplicitVarSizeWithFlags_Flags[q6] = false -> y_ExplicitVarSizeWithFlags_Values[q6] = 2 | q6 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q7] | q7 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q8]) | q8 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q10 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q10] < x_ExplicitVarSizeWithFlags_Values[q10 + 1] - | q10 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q11] = false -> x_ExplicitVarSizeWithFlags_Values[q11] = 2 - | q11 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q12 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q12] | q12 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q13]) | q13 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q16] -> - or([x_ExplicitVarSizeWithDummy[q18] != 6 /\ - x_ExplicitVarSizeWithDummy[q18] = x_ExplicitVarSizeWithFlags_Values[q16] - | q18 : int(1..4)]) - | q16 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q20] != 6 -> - or([x_ExplicitVarSizeWithFlags_Flags[q22] /\ - x_ExplicitVarSizeWithFlags_Values[q22] = x_ExplicitVarSizeWithDummy[q20] - | q22 : int(1..4)]) - | q20 : int(1..4)]), - and([y_ExplicitVarSizeWithDummy[q23] < y_ExplicitVarSizeWithDummy[q23 + 1] \/ y_ExplicitVarSizeWithDummy[q23] = 6 - | q23 : int(1..3)]), - and([y_ExplicitVarSizeWithDummy[q24] = 6 -> y_ExplicitVarSizeWithDummy[q24 + 1] = 6 | q24 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q25] != 6) | q25 : int(1..4)]), - and([y_ExplicitVarSizeWithDummy[q28] != 6 -> - or([y_ExplicitVarSizeWithFlags_Flags[q30] /\ - y_ExplicitVarSizeWithFlags_Values[q30] = y_ExplicitVarSizeWithDummy[q28] - | q30 : int(1..4)]) - | q28 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q32] -> - or([y_ExplicitVarSizeWithDummy[q34] != 6 /\ - y_ExplicitVarSizeWithDummy[q34] = y_ExplicitVarSizeWithFlags_Values[q32] - | q34 : int(1..4)]) - | q32 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_2_4_4_3-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_2_4_4_3-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_4_4_3-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_2_4_4_3-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_2_4_4_3-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_4_4_3-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_2_4_4_3.eprime b/tests/exhaustive/basic/set09/expected/model_2_4_4_3.eprime deleted file mode 100644 index c1250928a1..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_4_4_3.eprime +++ /dev/null @@ -1,60 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_ExplicitVarSizeWithMarker_Marker: int(0..4) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy, - y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithFlags_Flags, - y_ExplicitVarSizeWithFlags_Values] -such that - and([x_ExplicitVarSizeWithDummy[q34] != 6 /\ y_ExplicitVarSizeWithFlags_Flags[q35] -> - x_ExplicitVarSizeWithDummy[q34] + 2 = y_ExplicitVarSizeWithFlags_Values[q35] - | q34 : int(1..4), q35 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 6 - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q2] = 6 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 6 | q2 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 6) | q3 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q5 + 1] -> - y_ExplicitVarSizeWithFlags_Values[q5] < y_ExplicitVarSizeWithFlags_Values[q5 + 1] - | q5 : int(1..3)]), - and([y_ExplicitVarSizeWithFlags_Flags[q6] = false -> y_ExplicitVarSizeWithFlags_Values[q6] = 2 | q6 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q7] | q7 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q8]) | q8 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q10 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q10] < x_ExplicitVarSizeWithFlags_Values[q10 + 1] - | q10 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q11] = false -> x_ExplicitVarSizeWithFlags_Values[q11] = 2 - | q11 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q12 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q12] | q12 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q13]) | q13 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q16] -> - or([x_ExplicitVarSizeWithDummy[q18] != 6 /\ - x_ExplicitVarSizeWithDummy[q18] = x_ExplicitVarSizeWithFlags_Values[q16] - | q18 : int(1..4)]) - | q16 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q20] != 6 -> - or([x_ExplicitVarSizeWithFlags_Flags[q22] /\ - x_ExplicitVarSizeWithFlags_Values[q22] = x_ExplicitVarSizeWithDummy[q20] - | q22 : int(1..4)]) - | q20 : int(1..4)]), - and([q23 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> - y_ExplicitVarSizeWithMarker_Values[q23] < y_ExplicitVarSizeWithMarker_Values[q23 + 1] - | q23 : int(1..3)]), - and([q24 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q24] = 2 | q24 : int(1..4)]), - 1 <= y_ExplicitVarSizeWithMarker_Marker, - and([q27 <= y_ExplicitVarSizeWithMarker_Marker -> - or([y_ExplicitVarSizeWithFlags_Flags[q29] /\ - y_ExplicitVarSizeWithFlags_Values[q29] = y_ExplicitVarSizeWithMarker_Values[q27] - | q29 : int(1..4)]) - | q27 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q31] -> - or([q33 <= y_ExplicitVarSizeWithMarker_Marker /\ - y_ExplicitVarSizeWithMarker_Values[q33] = y_ExplicitVarSizeWithFlags_Values[q31] - | q33 : int(1..4)]) - | q31 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_2_4_4_4-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_2_4_4_4-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_4_4_4-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_2_4_4_4-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_2_4_4_4-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_4_4_4-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_2_4_4_4.eprime b/tests/exhaustive/basic/set09/expected/model_2_4_4_4.eprime deleted file mode 100644 index b577e5f27d..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_2_4_4_4.eprime +++ /dev/null @@ -1,42 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy, - y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values] -such that - and([x_ExplicitVarSizeWithDummy[q23] != 6 /\ y_ExplicitVarSizeWithFlags_Flags[q24] -> - x_ExplicitVarSizeWithDummy[q23] + 2 = y_ExplicitVarSizeWithFlags_Values[q24] - | q23 : int(1..4), q24 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 6 - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q2] = 6 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 6 | q2 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 6) | q3 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q5 + 1] -> - y_ExplicitVarSizeWithFlags_Values[q5] < y_ExplicitVarSizeWithFlags_Values[q5 + 1] - | q5 : int(1..3)]), - and([y_ExplicitVarSizeWithFlags_Flags[q6] = false -> y_ExplicitVarSizeWithFlags_Values[q6] = 2 | q6 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q7] | q7 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q8]) | q8 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q10 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q10] < x_ExplicitVarSizeWithFlags_Values[q10 + 1] - | q10 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q11] = false -> x_ExplicitVarSizeWithFlags_Values[q11] = 2 - | q11 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q12 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q12] | q12 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q13]) | q13 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q16] -> - or([x_ExplicitVarSizeWithDummy[q18] != 6 /\ - x_ExplicitVarSizeWithDummy[q18] = x_ExplicitVarSizeWithFlags_Values[q16] - | q18 : int(1..4)]) - | q16 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q20] != 6 -> - or([x_ExplicitVarSizeWithFlags_Flags[q22] /\ - x_ExplicitVarSizeWithFlags_Values[q22] = x_ExplicitVarSizeWithDummy[q20] - | q22 : int(1..4)]) - | q20 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_3_1_1_1-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_3_1_1_1-solution000001.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_1_1_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_3_1_1_1-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_3_1_1_1-solution000002.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_1_1_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_3_1_1_1.eprime b/tests/exhaustive/basic/set09/expected/model_3_1_1_1.eprime deleted file mode 100644 index 0898d273ff..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_1_1_1.eprime +++ /dev/null @@ -1,23 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -find x_Occurrence: matrix indexed by [int(2..5)] of bool -find y_Occurrence: matrix indexed by [int(2..5)] of bool -branching on [x_Occurrence, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, y_Occurrence] -such that - and([q11 <= x_ExplicitVarSizeWithMarker_Marker /\ y_Occurrence[j] -> x_ExplicitVarSizeWithMarker_Values[q11] + 2 = j - | q11 : int(1..4), j : int(2..5)]), - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..3)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 2 | q2 : int(1..4)]), - 1 <= x_ExplicitVarSizeWithMarker_Marker, - 1 <= sum([toInt(y_Occurrence[q4]) | q4 : int(2..5)]), - 1 <= sum([toInt(x_Occurrence[q5]) | q5 : int(2..5)]), - and([x_Occurrence[q6] -> - or([q8 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q8] = q6 | q8 : int(1..4)]) - | q6 : int(2..5)]), - and([q10 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q10]] - | q10 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_3_1_1_2-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_3_1_1_2-solution000001.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_1_1_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_3_1_1_2-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_3_1_1_2-solution000002.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_1_1_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_3_1_1_2.eprime b/tests/exhaustive/basic/set09/expected/model_3_1_1_2.eprime deleted file mode 100644 index 0d82bb728f..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_1_1_2.eprime +++ /dev/null @@ -1,35 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -find x_Occurrence: matrix indexed by [int(2..5)] of bool -find y_Occurrence: matrix indexed by [int(2..5)] of bool -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -branching on - [x_Occurrence, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithDummy, - y_Occurrence] -such that - and([q20 <= x_ExplicitVarSizeWithMarker_Marker /\ y_Occurrence[j] -> x_ExplicitVarSizeWithMarker_Values[q20] + 2 = j - | q20 : int(1..4), j : int(2..5)]), - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..3)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 2 | q2 : int(1..4)]), - 1 <= x_ExplicitVarSizeWithMarker_Marker, - 1 <= sum([toInt(y_Occurrence[q4]) | q4 : int(2..5)]), - 1 <= sum([toInt(x_Occurrence[q5]) | q5 : int(2..5)]), - and([x_Occurrence[q15] -> - or([q17 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q17] = q15 - | q17 : int(1..4)]) - | q15 : int(2..5)]), - and([q19 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q19]] - | q19 : int(1..4)]), - and([y_ExplicitVarSizeWithDummy[q6] < y_ExplicitVarSizeWithDummy[q6 + 1] \/ y_ExplicitVarSizeWithDummy[q6] = 6 - | q6 : int(1..3)]), - and([y_ExplicitVarSizeWithDummy[q7] = 6 -> y_ExplicitVarSizeWithDummy[q7 + 1] = 6 | q7 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q8] != 6) | q8 : int(1..4)]), - and([y_ExplicitVarSizeWithDummy[q11] != 6 -> y_Occurrence[y_ExplicitVarSizeWithDummy[q11]] | q11 : int(1..4)]), - and([y_Occurrence[q12] -> - or([y_ExplicitVarSizeWithDummy[q14] != 6 /\ y_ExplicitVarSizeWithDummy[q14] = q12 | q14 : int(1..4)]) - | q12 : int(2..5)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_3_1_1_3-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_3_1_1_3-solution000001.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_1_1_3-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_3_1_1_3-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_3_1_1_3-solution000002.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_1_1_3-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_3_1_1_3.eprime b/tests/exhaustive/basic/set09/expected/model_3_1_1_3.eprime deleted file mode 100644 index 19d7d14337..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_1_1_3.eprime +++ /dev/null @@ -1,39 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -find x_Occurrence: matrix indexed by [int(2..5)] of bool -find y_Occurrence: matrix indexed by [int(2..5)] of bool -find y_ExplicitVarSizeWithMarker_Marker: int(0..4) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -branching on - [x_Occurrence, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, - y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values, y_Occurrence] -such that - and([q19 <= x_ExplicitVarSizeWithMarker_Marker /\ y_Occurrence[j] -> x_ExplicitVarSizeWithMarker_Values[q19] + 2 = j - | q19 : int(1..4), j : int(2..5)]), - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..3)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 2 | q2 : int(1..4)]), - 1 <= x_ExplicitVarSizeWithMarker_Marker, - 1 <= sum([toInt(y_Occurrence[q4]) | q4 : int(2..5)]), - 1 <= sum([toInt(x_Occurrence[q5]) | q5 : int(2..5)]), - and([x_Occurrence[q14] -> - or([q16 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q16] = q14 - | q16 : int(1..4)]) - | q14 : int(2..5)]), - and([q18 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q18]] - | q18 : int(1..4)]), - and([q6 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> - y_ExplicitVarSizeWithMarker_Values[q6] < y_ExplicitVarSizeWithMarker_Values[q6 + 1] - | q6 : int(1..3)]), - and([q7 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q7] = 2 | q7 : int(1..4)]), - 1 <= y_ExplicitVarSizeWithMarker_Marker, - and([q10 <= y_ExplicitVarSizeWithMarker_Marker -> y_Occurrence[y_ExplicitVarSizeWithMarker_Values[q10]] - | q10 : int(1..4)]), - and([y_Occurrence[q11] -> - or([q13 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[q13] = q11 - | q13 : int(1..4)]) - | q11 : int(2..5)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_3_1_1_4-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_3_1_1_4-solution000001.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_1_1_4-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_3_1_1_4-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_3_1_1_4-solution000002.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_1_1_4-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_3_1_1_4.eprime b/tests/exhaustive/basic/set09/expected/model_3_1_1_4.eprime deleted file mode 100644 index 367803c85b..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_1_1_4.eprime +++ /dev/null @@ -1,39 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -find x_Occurrence: matrix indexed by [int(2..5)] of bool -find y_Occurrence: matrix indexed by [int(2..5)] of bool -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -branching on - [x_Occurrence, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, - y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values, y_Occurrence] -such that - and([q21 <= x_ExplicitVarSizeWithMarker_Marker /\ y_Occurrence[j] -> x_ExplicitVarSizeWithMarker_Values[q21] + 2 = j - | q21 : int(1..4), j : int(2..5)]), - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..3)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 2 | q2 : int(1..4)]), - 1 <= x_ExplicitVarSizeWithMarker_Marker, - 1 <= sum([toInt(y_Occurrence[q4]) | q4 : int(2..5)]), - 1 <= sum([toInt(x_Occurrence[q5]) | q5 : int(2..5)]), - and([x_Occurrence[q16] -> - or([q18 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q18] = q16 - | q18 : int(1..4)]) - | q16 : int(2..5)]), - and([q20 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q20]] - | q20 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> - y_ExplicitVarSizeWithFlags_Values[q6] < y_ExplicitVarSizeWithFlags_Values[q6 + 1] - | q6 : int(1..3)]), - and([y_ExplicitVarSizeWithFlags_Flags[q7] = false -> y_ExplicitVarSizeWithFlags_Values[q7] = 2 | q7 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q8 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q8] | q8 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q9]) | q9 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q12] -> y_Occurrence[y_ExplicitVarSizeWithFlags_Values[q12]] - | q12 : int(1..4)]), - and([y_Occurrence[q13] -> - or([y_ExplicitVarSizeWithFlags_Flags[q15] /\ y_ExplicitVarSizeWithFlags_Values[q15] = q13 | q15 : int(1..4)]) - | q13 : int(2..5)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_3_1_2_1-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_3_1_2_1-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_1_2_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_3_1_2_1-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_3_1_2_1-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_1_2_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_3_1_2_1.eprime b/tests/exhaustive/basic/set09/expected/model_3_1_2_1.eprime deleted file mode 100644 index 5fb49b3743..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_1_2_1.eprime +++ /dev/null @@ -1,32 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -find y_Occurrence: matrix indexed by [int(2..5)] of bool -branching on - [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, y_Occurrence] -such that - and([q17 <= x_ExplicitVarSizeWithMarker_Marker /\ y_Occurrence[j] -> x_ExplicitVarSizeWithMarker_Values[q17] + 2 = j - | q17 : int(1..4), j : int(2..5)]), - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..3)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 2 | q2 : int(1..4)]), - 1 <= x_ExplicitVarSizeWithMarker_Marker, - 1 <= sum([toInt(y_Occurrence[q4]) | q4 : int(2..5)]), - and([x_ExplicitVarSizeWithDummy[q5] < x_ExplicitVarSizeWithDummy[q5 + 1] \/ x_ExplicitVarSizeWithDummy[q5] = 6 - | q5 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q6] = 6 -> x_ExplicitVarSizeWithDummy[q6 + 1] = 6 | q6 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q7] != 6) | q7 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q10] != 6 -> - or([q12 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q12] = x_ExplicitVarSizeWithDummy[q10] - | q12 : int(1..4)]) - | q10 : int(1..4)]), - and([q14 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q16] != 6 /\ - x_ExplicitVarSizeWithDummy[q16] = x_ExplicitVarSizeWithMarker_Values[q14] - | q16 : int(1..4)]) - | q14 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_3_1_2_2-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_3_1_2_2-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_1_2_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_3_1_2_2-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_3_1_2_2-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_1_2_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_3_1_2_2.eprime b/tests/exhaustive/basic/set09/expected/model_3_1_2_2.eprime deleted file mode 100644 index 76e803c650..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_1_2_2.eprime +++ /dev/null @@ -1,42 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -find y_Occurrence: matrix indexed by [int(2..5)] of bool -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -branching on - [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, - y_ExplicitVarSizeWithDummy, y_Occurrence] -such that - and([q26 <= x_ExplicitVarSizeWithMarker_Marker /\ y_Occurrence[j] -> x_ExplicitVarSizeWithMarker_Values[q26] + 2 = j - | q26 : int(1..4), j : int(2..5)]), - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..3)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 2 | q2 : int(1..4)]), - 1 <= x_ExplicitVarSizeWithMarker_Marker, - 1 <= sum([toInt(y_Occurrence[q4]) | q4 : int(2..5)]), - and([x_ExplicitVarSizeWithDummy[q5] < x_ExplicitVarSizeWithDummy[q5 + 1] \/ x_ExplicitVarSizeWithDummy[q5] = 6 - | q5 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q6] = 6 -> x_ExplicitVarSizeWithDummy[q6 + 1] = 6 | q6 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q7] != 6) | q7 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q10] != 6 -> - or([q12 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q12] = x_ExplicitVarSizeWithDummy[q10] - | q12 : int(1..4)]) - | q10 : int(1..4)]), - and([q14 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q16] != 6 /\ - x_ExplicitVarSizeWithDummy[q16] = x_ExplicitVarSizeWithMarker_Values[q14] - | q16 : int(1..4)]) - | q14 : int(1..4)]), - and([y_ExplicitVarSizeWithDummy[q17] < y_ExplicitVarSizeWithDummy[q17 + 1] \/ y_ExplicitVarSizeWithDummy[q17] = 6 - | q17 : int(1..3)]), - and([y_ExplicitVarSizeWithDummy[q18] = 6 -> y_ExplicitVarSizeWithDummy[q18 + 1] = 6 | q18 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q19] != 6) | q19 : int(1..4)]), - and([y_ExplicitVarSizeWithDummy[q22] != 6 -> y_Occurrence[y_ExplicitVarSizeWithDummy[q22]] | q22 : int(1..4)]), - and([y_Occurrence[q23] -> - or([y_ExplicitVarSizeWithDummy[q25] != 6 /\ y_ExplicitVarSizeWithDummy[q25] = q23 | q25 : int(1..4)]) - | q23 : int(2..5)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_3_1_2_3-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_3_1_2_3-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_1_2_3-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_3_1_2_3-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_3_1_2_3-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_1_2_3-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_3_1_2_3.eprime b/tests/exhaustive/basic/set09/expected/model_3_1_2_3.eprime deleted file mode 100644 index 8f44fada43..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_1_2_3.eprime +++ /dev/null @@ -1,46 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -find y_Occurrence: matrix indexed by [int(2..5)] of bool -find y_ExplicitVarSizeWithMarker_Marker: int(0..4) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -branching on - [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, - y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values, y_Occurrence] -such that - and([q25 <= x_ExplicitVarSizeWithMarker_Marker /\ y_Occurrence[j] -> x_ExplicitVarSizeWithMarker_Values[q25] + 2 = j - | q25 : int(1..4), j : int(2..5)]), - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..3)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 2 | q2 : int(1..4)]), - 1 <= x_ExplicitVarSizeWithMarker_Marker, - 1 <= sum([toInt(y_Occurrence[q4]) | q4 : int(2..5)]), - and([x_ExplicitVarSizeWithDummy[q5] < x_ExplicitVarSizeWithDummy[q5 + 1] \/ x_ExplicitVarSizeWithDummy[q5] = 6 - | q5 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q6] = 6 -> x_ExplicitVarSizeWithDummy[q6 + 1] = 6 | q6 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q7] != 6) | q7 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q10] != 6 -> - or([q12 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q12] = x_ExplicitVarSizeWithDummy[q10] - | q12 : int(1..4)]) - | q10 : int(1..4)]), - and([q14 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q16] != 6 /\ - x_ExplicitVarSizeWithDummy[q16] = x_ExplicitVarSizeWithMarker_Values[q14] - | q16 : int(1..4)]) - | q14 : int(1..4)]), - and([q17 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> - y_ExplicitVarSizeWithMarker_Values[q17] < y_ExplicitVarSizeWithMarker_Values[q17 + 1] - | q17 : int(1..3)]), - and([q18 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q18] = 2 | q18 : int(1..4)]), - 1 <= y_ExplicitVarSizeWithMarker_Marker, - and([q21 <= y_ExplicitVarSizeWithMarker_Marker -> y_Occurrence[y_ExplicitVarSizeWithMarker_Values[q21]] - | q21 : int(1..4)]), - and([y_Occurrence[q22] -> - or([q24 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[q24] = q22 - | q24 : int(1..4)]) - | q22 : int(2..5)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_3_1_2_4-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_3_1_2_4-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_1_2_4-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_3_1_2_4-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_3_1_2_4-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_1_2_4-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_3_1_2_4.eprime b/tests/exhaustive/basic/set09/expected/model_3_1_2_4.eprime deleted file mode 100644 index 228e19fb6b..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_1_2_4.eprime +++ /dev/null @@ -1,47 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -find y_Occurrence: matrix indexed by [int(2..5)] of bool -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -branching on - [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, - y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values, y_Occurrence] -such that - and([q27 <= x_ExplicitVarSizeWithMarker_Marker /\ y_Occurrence[j] -> x_ExplicitVarSizeWithMarker_Values[q27] + 2 = j - | q27 : int(1..4), j : int(2..5)]), - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..3)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 2 | q2 : int(1..4)]), - 1 <= x_ExplicitVarSizeWithMarker_Marker, - 1 <= sum([toInt(y_Occurrence[q4]) | q4 : int(2..5)]), - and([x_ExplicitVarSizeWithDummy[q5] < x_ExplicitVarSizeWithDummy[q5 + 1] \/ x_ExplicitVarSizeWithDummy[q5] = 6 - | q5 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q6] = 6 -> x_ExplicitVarSizeWithDummy[q6 + 1] = 6 | q6 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q7] != 6) | q7 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q10] != 6 -> - or([q12 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q12] = x_ExplicitVarSizeWithDummy[q10] - | q12 : int(1..4)]) - | q10 : int(1..4)]), - and([q14 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q16] != 6 /\ - x_ExplicitVarSizeWithDummy[q16] = x_ExplicitVarSizeWithMarker_Values[q14] - | q16 : int(1..4)]) - | q14 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q17 + 1] -> - y_ExplicitVarSizeWithFlags_Values[q17] < y_ExplicitVarSizeWithFlags_Values[q17 + 1] - | q17 : int(1..3)]), - and([y_ExplicitVarSizeWithFlags_Flags[q18] = false -> y_ExplicitVarSizeWithFlags_Values[q18] = 2 - | q18 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q19 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q19] | q19 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q20]) | q20 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q23] -> y_Occurrence[y_ExplicitVarSizeWithFlags_Values[q23]] - | q23 : int(1..4)]), - and([y_Occurrence[q24] -> - or([y_ExplicitVarSizeWithFlags_Flags[q26] /\ y_ExplicitVarSizeWithFlags_Values[q26] = q24 | q26 : int(1..4)]) - | q24 : int(2..5)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_3_1_3_1-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_3_1_3_1-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_1_3_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_3_1_3_1-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_3_1_3_1-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_1_3_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_3_1_3_1.eprime b/tests/exhaustive/basic/set09/expected/model_3_1_3_1.eprime deleted file mode 100644 index 1b5ab3050f..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_1_3_1.eprime +++ /dev/null @@ -1,16 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_Occurrence: matrix indexed by [int(2..5)] of bool -branching on [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, y_Occurrence] -such that - and([q5 <= x_ExplicitVarSizeWithMarker_Marker /\ y_Occurrence[j] -> x_ExplicitVarSizeWithMarker_Values[q5] + 2 = j - | q5 : int(1..4), j : int(2..5)]), - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..3)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 2 | q2 : int(1..4)]), - 1 <= x_ExplicitVarSizeWithMarker_Marker, - 1 <= sum([toInt(y_Occurrence[q4]) | q4 : int(2..5)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_3_1_3_2-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_3_1_3_2-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_1_3_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_3_1_3_2-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_3_1_3_2-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_1_3_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_3_1_3_2.eprime b/tests/exhaustive/basic/set09/expected/model_3_1_3_2.eprime deleted file mode 100644 index 67c1711a50..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_1_3_2.eprime +++ /dev/null @@ -1,26 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_Occurrence: matrix indexed by [int(2..5)] of bool -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithDummy, y_Occurrence] -such that - and([q14 <= x_ExplicitVarSizeWithMarker_Marker /\ y_Occurrence[j] -> x_ExplicitVarSizeWithMarker_Values[q14] + 2 = j - | q14 : int(1..4), j : int(2..5)]), - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..3)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 2 | q2 : int(1..4)]), - 1 <= x_ExplicitVarSizeWithMarker_Marker, - 1 <= sum([toInt(y_Occurrence[q4]) | q4 : int(2..5)]), - and([y_ExplicitVarSizeWithDummy[q5] < y_ExplicitVarSizeWithDummy[q5 + 1] \/ y_ExplicitVarSizeWithDummy[q5] = 6 - | q5 : int(1..3)]), - and([y_ExplicitVarSizeWithDummy[q6] = 6 -> y_ExplicitVarSizeWithDummy[q6 + 1] = 6 | q6 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q7] != 6) | q7 : int(1..4)]), - and([y_ExplicitVarSizeWithDummy[q10] != 6 -> y_Occurrence[y_ExplicitVarSizeWithDummy[q10]] | q10 : int(1..4)]), - and([y_Occurrence[q11] -> - or([y_ExplicitVarSizeWithDummy[q13] != 6 /\ y_ExplicitVarSizeWithDummy[q13] = q11 | q13 : int(1..4)]) - | q11 : int(2..5)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_3_1_3_3-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_3_1_3_3-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_1_3_3-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_3_1_3_3-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_3_1_3_3-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_1_3_3-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_3_1_3_3.eprime b/tests/exhaustive/basic/set09/expected/model_3_1_3_3.eprime deleted file mode 100644 index ae76323065..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_1_3_3.eprime +++ /dev/null @@ -1,31 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_Occurrence: matrix indexed by [int(2..5)] of bool -find y_ExplicitVarSizeWithMarker_Marker: int(0..4) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithMarker_Marker, - y_ExplicitVarSizeWithMarker_Values, y_Occurrence] -such that - and([q13 <= x_ExplicitVarSizeWithMarker_Marker /\ y_Occurrence[j] -> x_ExplicitVarSizeWithMarker_Values[q13] + 2 = j - | q13 : int(1..4), j : int(2..5)]), - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..3)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 2 | q2 : int(1..4)]), - 1 <= x_ExplicitVarSizeWithMarker_Marker, - 1 <= sum([toInt(y_Occurrence[q4]) | q4 : int(2..5)]), - and([q5 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> - y_ExplicitVarSizeWithMarker_Values[q5] < y_ExplicitVarSizeWithMarker_Values[q5 + 1] - | q5 : int(1..3)]), - and([q6 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q6] = 2 | q6 : int(1..4)]), - 1 <= y_ExplicitVarSizeWithMarker_Marker, - and([q9 <= y_ExplicitVarSizeWithMarker_Marker -> y_Occurrence[y_ExplicitVarSizeWithMarker_Values[q9]] - | q9 : int(1..4)]), - and([y_Occurrence[q10] -> - or([q12 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[q12] = q10 - | q12 : int(1..4)]) - | q10 : int(2..5)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_3_1_3_4-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_3_1_3_4-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_1_3_4-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_3_1_3_4-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_3_1_3_4-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_1_3_4-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_3_1_3_4.eprime b/tests/exhaustive/basic/set09/expected/model_3_1_3_4.eprime deleted file mode 100644 index c222d89b6a..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_1_3_4.eprime +++ /dev/null @@ -1,31 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_Occurrence: matrix indexed by [int(2..5)] of bool -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithFlags_Flags, - y_ExplicitVarSizeWithFlags_Values, y_Occurrence] -such that - and([q15 <= x_ExplicitVarSizeWithMarker_Marker /\ y_Occurrence[j] -> x_ExplicitVarSizeWithMarker_Values[q15] + 2 = j - | q15 : int(1..4), j : int(2..5)]), - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..3)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 2 | q2 : int(1..4)]), - 1 <= x_ExplicitVarSizeWithMarker_Marker, - 1 <= sum([toInt(y_Occurrence[q4]) | q4 : int(2..5)]), - and([y_ExplicitVarSizeWithFlags_Flags[q5 + 1] -> - y_ExplicitVarSizeWithFlags_Values[q5] < y_ExplicitVarSizeWithFlags_Values[q5 + 1] - | q5 : int(1..3)]), - and([y_ExplicitVarSizeWithFlags_Flags[q6] = false -> y_ExplicitVarSizeWithFlags_Values[q6] = 2 | q6 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q7] | q7 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q8]) | q8 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q11] -> y_Occurrence[y_ExplicitVarSizeWithFlags_Values[q11]] - | q11 : int(1..4)]), - and([y_Occurrence[q12] -> - or([y_ExplicitVarSizeWithFlags_Flags[q14] /\ y_ExplicitVarSizeWithFlags_Values[q14] = q12 | q14 : int(1..4)]) - | q12 : int(2..5)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_3_1_4_1-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_3_1_4_1-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_1_4_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_3_1_4_1-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_3_1_4_1-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_1_4_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_3_1_4_1.eprime b/tests/exhaustive/basic/set09/expected/model_3_1_4_1.eprime deleted file mode 100644 index d55d8473f1..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_1_4_1.eprime +++ /dev/null @@ -1,36 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_Occurrence: matrix indexed by [int(2..5)] of bool -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithMarker_Marker, - x_ExplicitVarSizeWithMarker_Values, y_Occurrence] -such that - and([q18 <= x_ExplicitVarSizeWithMarker_Marker /\ y_Occurrence[j] -> x_ExplicitVarSizeWithMarker_Values[q18] + 2 = j - | q18 : int(1..4), j : int(2..5)]), - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..3)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 2 | q2 : int(1..4)]), - 1 <= x_ExplicitVarSizeWithMarker_Marker, - 1 <= sum([toInt(y_Occurrence[q4]) | q4 : int(2..5)]), - and([x_ExplicitVarSizeWithFlags_Flags[q5 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q5] < x_ExplicitVarSizeWithFlags_Values[q5 + 1] - | q5 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q6] = false -> x_ExplicitVarSizeWithFlags_Values[q6] = 2 | q6 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q7] | q7 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q8]) | q8 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q11] -> - or([q13 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q13] = x_ExplicitVarSizeWithFlags_Values[q11] - | q13 : int(1..4)]) - | q11 : int(1..4)]), - and([q15 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q17] /\ - x_ExplicitVarSizeWithFlags_Values[q17] = x_ExplicitVarSizeWithMarker_Values[q15] - | q17 : int(1..4)]) - | q15 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_3_1_4_2-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_3_1_4_2-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_1_4_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_3_1_4_2-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_3_1_4_2-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_1_4_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_3_1_4_2.eprime b/tests/exhaustive/basic/set09/expected/model_3_1_4_2.eprime deleted file mode 100644 index 4db7080ac5..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_1_4_2.eprime +++ /dev/null @@ -1,45 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_Occurrence: matrix indexed by [int(2..5)] of bool -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithMarker_Marker, - x_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithDummy, y_Occurrence] -such that - and([q27 <= x_ExplicitVarSizeWithMarker_Marker /\ y_Occurrence[j] -> x_ExplicitVarSizeWithMarker_Values[q27] + 2 = j - | q27 : int(1..4), j : int(2..5)]), - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..3)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 2 | q2 : int(1..4)]), - 1 <= x_ExplicitVarSizeWithMarker_Marker, - 1 <= sum([toInt(y_Occurrence[q4]) | q4 : int(2..5)]), - and([x_ExplicitVarSizeWithFlags_Flags[q5 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q5] < x_ExplicitVarSizeWithFlags_Values[q5 + 1] - | q5 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q6] = false -> x_ExplicitVarSizeWithFlags_Values[q6] = 2 | q6 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q7] | q7 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q8]) | q8 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q11] -> - or([q13 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q13] = x_ExplicitVarSizeWithFlags_Values[q11] - | q13 : int(1..4)]) - | q11 : int(1..4)]), - and([q15 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q17] /\ - x_ExplicitVarSizeWithFlags_Values[q17] = x_ExplicitVarSizeWithMarker_Values[q15] - | q17 : int(1..4)]) - | q15 : int(1..4)]), - and([y_ExplicitVarSizeWithDummy[q18] < y_ExplicitVarSizeWithDummy[q18 + 1] \/ y_ExplicitVarSizeWithDummy[q18] = 6 - | q18 : int(1..3)]), - and([y_ExplicitVarSizeWithDummy[q19] = 6 -> y_ExplicitVarSizeWithDummy[q19 + 1] = 6 | q19 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q20] != 6) | q20 : int(1..4)]), - and([y_ExplicitVarSizeWithDummy[q23] != 6 -> y_Occurrence[y_ExplicitVarSizeWithDummy[q23]] | q23 : int(1..4)]), - and([y_Occurrence[q24] -> - or([y_ExplicitVarSizeWithDummy[q26] != 6 /\ y_ExplicitVarSizeWithDummy[q26] = q24 | q26 : int(1..4)]) - | q24 : int(2..5)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_3_1_4_3-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_3_1_4_3-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_1_4_3-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_3_1_4_3-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_3_1_4_3-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_1_4_3-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_3_1_4_3.eprime b/tests/exhaustive/basic/set09/expected/model_3_1_4_3.eprime deleted file mode 100644 index cc9cb3a8fe..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_1_4_3.eprime +++ /dev/null @@ -1,50 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_Occurrence: matrix indexed by [int(2..5)] of bool -find y_ExplicitVarSizeWithMarker_Marker: int(0..4) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithMarker_Marker, - x_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values, - y_Occurrence] -such that - and([q26 <= x_ExplicitVarSizeWithMarker_Marker /\ y_Occurrence[j] -> x_ExplicitVarSizeWithMarker_Values[q26] + 2 = j - | q26 : int(1..4), j : int(2..5)]), - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..3)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 2 | q2 : int(1..4)]), - 1 <= x_ExplicitVarSizeWithMarker_Marker, - 1 <= sum([toInt(y_Occurrence[q4]) | q4 : int(2..5)]), - and([x_ExplicitVarSizeWithFlags_Flags[q5 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q5] < x_ExplicitVarSizeWithFlags_Values[q5 + 1] - | q5 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q6] = false -> x_ExplicitVarSizeWithFlags_Values[q6] = 2 | q6 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q7] | q7 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q8]) | q8 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q11] -> - or([q13 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q13] = x_ExplicitVarSizeWithFlags_Values[q11] - | q13 : int(1..4)]) - | q11 : int(1..4)]), - and([q15 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q17] /\ - x_ExplicitVarSizeWithFlags_Values[q17] = x_ExplicitVarSizeWithMarker_Values[q15] - | q17 : int(1..4)]) - | q15 : int(1..4)]), - and([q18 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> - y_ExplicitVarSizeWithMarker_Values[q18] < y_ExplicitVarSizeWithMarker_Values[q18 + 1] - | q18 : int(1..3)]), - and([q19 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q19] = 2 | q19 : int(1..4)]), - 1 <= y_ExplicitVarSizeWithMarker_Marker, - and([q22 <= y_ExplicitVarSizeWithMarker_Marker -> y_Occurrence[y_ExplicitVarSizeWithMarker_Values[q22]] - | q22 : int(1..4)]), - and([y_Occurrence[q23] -> - or([q25 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[q25] = q23 - | q25 : int(1..4)]) - | q23 : int(2..5)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_3_1_4_4-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_3_1_4_4-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_1_4_4-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_3_1_4_4-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_3_1_4_4-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_1_4_4-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_3_1_4_4.eprime b/tests/exhaustive/basic/set09/expected/model_3_1_4_4.eprime deleted file mode 100644 index 286649e6b5..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_1_4_4.eprime +++ /dev/null @@ -1,51 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_Occurrence: matrix indexed by [int(2..5)] of bool -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithMarker_Marker, - x_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values, - y_Occurrence] -such that - and([q28 <= x_ExplicitVarSizeWithMarker_Marker /\ y_Occurrence[j] -> x_ExplicitVarSizeWithMarker_Values[q28] + 2 = j - | q28 : int(1..4), j : int(2..5)]), - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..3)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 2 | q2 : int(1..4)]), - 1 <= x_ExplicitVarSizeWithMarker_Marker, - 1 <= sum([toInt(y_Occurrence[q4]) | q4 : int(2..5)]), - and([x_ExplicitVarSizeWithFlags_Flags[q5 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q5] < x_ExplicitVarSizeWithFlags_Values[q5 + 1] - | q5 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q6] = false -> x_ExplicitVarSizeWithFlags_Values[q6] = 2 | q6 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q7] | q7 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q8]) | q8 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q11] -> - or([q13 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q13] = x_ExplicitVarSizeWithFlags_Values[q11] - | q13 : int(1..4)]) - | q11 : int(1..4)]), - and([q15 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q17] /\ - x_ExplicitVarSizeWithFlags_Values[q17] = x_ExplicitVarSizeWithMarker_Values[q15] - | q17 : int(1..4)]) - | q15 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q18 + 1] -> - y_ExplicitVarSizeWithFlags_Values[q18] < y_ExplicitVarSizeWithFlags_Values[q18 + 1] - | q18 : int(1..3)]), - and([y_ExplicitVarSizeWithFlags_Flags[q19] = false -> y_ExplicitVarSizeWithFlags_Values[q19] = 2 - | q19 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q20 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q20] | q20 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q21]) | q21 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q24] -> y_Occurrence[y_ExplicitVarSizeWithFlags_Values[q24]] - | q24 : int(1..4)]), - and([y_Occurrence[q25] -> - or([y_ExplicitVarSizeWithFlags_Flags[q27] /\ y_ExplicitVarSizeWithFlags_Values[q27] = q25 | q27 : int(1..4)]) - | q25 : int(2..5)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_3_2_1_1-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_3_2_1_1-solution000001.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_2_1_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_3_2_1_1-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_3_2_1_1-solution000002.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_2_1_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_3_2_1_1.eprime b/tests/exhaustive/basic/set09/expected/model_3_2_1_1.eprime deleted file mode 100644 index 3478aef4b6..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_2_1_1.eprime +++ /dev/null @@ -1,36 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -find x_Occurrence: matrix indexed by [int(2..5)] of bool -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -find y_Occurrence: matrix indexed by [int(2..5)] of bool -branching on - [x_Occurrence, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, y_Occurrence, - y_ExplicitVarSizeWithDummy] -such that - and([q15 <= x_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithDummy[q16] != 6 -> - x_ExplicitVarSizeWithMarker_Values[q15] + 2 = y_ExplicitVarSizeWithDummy[q16] - | q15 : int(1..4), q16 : int(1..4)]), - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..3)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 2 | q2 : int(1..4)]), - 1 <= x_ExplicitVarSizeWithMarker_Marker, - and([y_ExplicitVarSizeWithDummy[q4] < y_ExplicitVarSizeWithDummy[q4 + 1] \/ y_ExplicitVarSizeWithDummy[q4] = 6 - | q4 : int(1..3)]), - and([y_ExplicitVarSizeWithDummy[q5] = 6 -> y_ExplicitVarSizeWithDummy[q5 + 1] = 6 | q5 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q6] != 6) | q6 : int(1..4)]), - 1 <= sum([toInt(x_Occurrence[q8]) | q8 : int(2..5)]), - and([x_Occurrence[q17] -> - or([q19 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q19] = q17 - | q19 : int(1..4)]) - | q17 : int(2..5)]), - and([q21 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q21]] - | q21 : int(1..4)]), - 1 <= sum([toInt(y_Occurrence[q9]) | q9 : int(2..5)]), - and([y_Occurrence[q10] -> - or([y_ExplicitVarSizeWithDummy[q12] != 6 /\ y_ExplicitVarSizeWithDummy[q12] = q10 | q12 : int(1..4)]) - | q10 : int(2..5)]), - and([y_ExplicitVarSizeWithDummy[q14] != 6 -> y_Occurrence[y_ExplicitVarSizeWithDummy[q14]] | q14 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_3_2_1_2-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_3_2_1_2-solution000001.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_2_1_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_3_2_1_2-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_3_2_1_2-solution000002.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_2_1_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_3_2_1_2.eprime b/tests/exhaustive/basic/set09/expected/model_3_2_1_2.eprime deleted file mode 100644 index fd0da5899f..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_2_1_2.eprime +++ /dev/null @@ -1,29 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -find x_Occurrence: matrix indexed by [int(2..5)] of bool -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -branching on - [x_Occurrence, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithDummy] -such that - and([q14 <= x_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithDummy[q15] != 6 -> - x_ExplicitVarSizeWithMarker_Values[q14] + 2 = y_ExplicitVarSizeWithDummy[q15] - | q14 : int(1..4), q15 : int(1..4)]), - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..3)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 2 | q2 : int(1..4)]), - 1 <= x_ExplicitVarSizeWithMarker_Marker, - and([y_ExplicitVarSizeWithDummy[q4] < y_ExplicitVarSizeWithDummy[q4 + 1] \/ y_ExplicitVarSizeWithDummy[q4] = 6 - | q4 : int(1..3)]), - and([y_ExplicitVarSizeWithDummy[q5] = 6 -> y_ExplicitVarSizeWithDummy[q5 + 1] = 6 | q5 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q6] != 6) | q6 : int(1..4)]), - 1 <= sum([toInt(x_Occurrence[q8]) | q8 : int(2..5)]), - and([x_Occurrence[q9] -> - or([q11 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q11] = q9 - | q11 : int(1..4)]) - | q9 : int(2..5)]), - and([q13 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q13]] - | q13 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_3_2_1_3-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_3_2_1_3-solution000001.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_2_1_3-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_3_2_1_3-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_3_2_1_3-solution000002.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_2_1_3-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_3_2_1_3.eprime b/tests/exhaustive/basic/set09/expected/model_3_2_1_3.eprime deleted file mode 100644 index bbd02c7005..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_2_1_3.eprime +++ /dev/null @@ -1,47 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -find x_Occurrence: matrix indexed by [int(2..5)] of bool -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -find y_ExplicitVarSizeWithMarker_Marker: int(0..4) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -branching on - [x_Occurrence, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, - y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithDummy] -such that - and([q25 <= x_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithDummy[q26] != 6 -> - x_ExplicitVarSizeWithMarker_Values[q25] + 2 = y_ExplicitVarSizeWithDummy[q26] - | q25 : int(1..4), q26 : int(1..4)]), - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..3)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 2 | q2 : int(1..4)]), - 1 <= x_ExplicitVarSizeWithMarker_Marker, - and([y_ExplicitVarSizeWithDummy[q4] < y_ExplicitVarSizeWithDummy[q4 + 1] \/ y_ExplicitVarSizeWithDummy[q4] = 6 - | q4 : int(1..3)]), - and([y_ExplicitVarSizeWithDummy[q5] = 6 -> y_ExplicitVarSizeWithDummy[q5 + 1] = 6 | q5 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q6] != 6) | q6 : int(1..4)]), - 1 <= sum([toInt(x_Occurrence[q8]) | q8 : int(2..5)]), - and([x_Occurrence[q20] -> - or([q22 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q22] = q20 - | q22 : int(1..4)]) - | q20 : int(2..5)]), - and([q24 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q24]] - | q24 : int(1..4)]), - and([q9 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> - y_ExplicitVarSizeWithMarker_Values[q9] < y_ExplicitVarSizeWithMarker_Values[q9 + 1] - | q9 : int(1..3)]), - and([q10 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q10] = 2 | q10 : int(1..4)]), - 1 <= y_ExplicitVarSizeWithMarker_Marker, - and([q13 <= y_ExplicitVarSizeWithMarker_Marker -> - or([y_ExplicitVarSizeWithDummy[q15] != 6 /\ - y_ExplicitVarSizeWithDummy[q15] = y_ExplicitVarSizeWithMarker_Values[q13] - | q15 : int(1..4)]) - | q13 : int(1..4)]), - and([y_ExplicitVarSizeWithDummy[q17] != 6 -> - or([q19 <= y_ExplicitVarSizeWithMarker_Marker /\ - y_ExplicitVarSizeWithMarker_Values[q19] = y_ExplicitVarSizeWithDummy[q17] - | q19 : int(1..4)]) - | q17 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_3_2_1_4-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_3_2_1_4-solution000001.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_2_1_4-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_3_2_1_4-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_3_2_1_4-solution000002.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_2_1_4-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_3_2_1_4.eprime b/tests/exhaustive/basic/set09/expected/model_3_2_1_4.eprime deleted file mode 100644 index f53ee8d570..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_2_1_4.eprime +++ /dev/null @@ -1,49 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -find x_Occurrence: matrix indexed by [int(2..5)] of bool -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -branching on - [x_Occurrence, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, - y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithDummy] -such that - and([q27 <= x_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithDummy[q28] != 6 -> - x_ExplicitVarSizeWithMarker_Values[q27] + 2 = y_ExplicitVarSizeWithDummy[q28] - | q27 : int(1..4), q28 : int(1..4)]), - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..3)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 2 | q2 : int(1..4)]), - 1 <= x_ExplicitVarSizeWithMarker_Marker, - and([y_ExplicitVarSizeWithDummy[q4] < y_ExplicitVarSizeWithDummy[q4 + 1] \/ y_ExplicitVarSizeWithDummy[q4] = 6 - | q4 : int(1..3)]), - and([y_ExplicitVarSizeWithDummy[q5] = 6 -> y_ExplicitVarSizeWithDummy[q5 + 1] = 6 | q5 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q6] != 6) | q6 : int(1..4)]), - 1 <= sum([toInt(x_Occurrence[q8]) | q8 : int(2..5)]), - and([x_Occurrence[q22] -> - or([q24 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q24] = q22 - | q24 : int(1..4)]) - | q22 : int(2..5)]), - and([q26 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q26]] - | q26 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q9 + 1] -> - y_ExplicitVarSizeWithFlags_Values[q9] < y_ExplicitVarSizeWithFlags_Values[q9 + 1] - | q9 : int(1..3)]), - and([y_ExplicitVarSizeWithFlags_Flags[q10] = false -> y_ExplicitVarSizeWithFlags_Values[q10] = 2 - | q10 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q11 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q11] | q11 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q12]) | q12 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q15] -> - or([y_ExplicitVarSizeWithDummy[q17] != 6 /\ - y_ExplicitVarSizeWithDummy[q17] = y_ExplicitVarSizeWithFlags_Values[q15] - | q17 : int(1..4)]) - | q15 : int(1..4)]), - and([y_ExplicitVarSizeWithDummy[q19] != 6 -> - or([y_ExplicitVarSizeWithFlags_Flags[q21] /\ - y_ExplicitVarSizeWithFlags_Values[q21] = y_ExplicitVarSizeWithDummy[q19] - | q21 : int(1..4)]) - | q19 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_3_2_2_1-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_3_2_2_1-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_2_2_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_3_2_2_1-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_3_2_2_1-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_2_2_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_3_2_2_1.eprime b/tests/exhaustive/basic/set09/expected/model_3_2_2_1.eprime deleted file mode 100644 index 6a169fe5a6..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_2_2_1.eprime +++ /dev/null @@ -1,43 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -find y_Occurrence: matrix indexed by [int(2..5)] of bool -branching on - [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, y_Occurrence, - y_ExplicitVarSizeWithDummy] -such that - and([q26 <= x_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithDummy[q27] != 6 -> - x_ExplicitVarSizeWithMarker_Values[q26] + 2 = y_ExplicitVarSizeWithDummy[q27] - | q26 : int(1..4), q27 : int(1..4)]), - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..3)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 2 | q2 : int(1..4)]), - 1 <= x_ExplicitVarSizeWithMarker_Marker, - and([y_ExplicitVarSizeWithDummy[q4] < y_ExplicitVarSizeWithDummy[q4 + 1] \/ y_ExplicitVarSizeWithDummy[q4] = 6 - | q4 : int(1..3)]), - and([y_ExplicitVarSizeWithDummy[q5] = 6 -> y_ExplicitVarSizeWithDummy[q5 + 1] = 6 | q5 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q6] != 6) | q6 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q8] < x_ExplicitVarSizeWithDummy[q8 + 1] \/ x_ExplicitVarSizeWithDummy[q8] = 6 - | q8 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q9] = 6 -> x_ExplicitVarSizeWithDummy[q9 + 1] = 6 | q9 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q10] != 6) | q10 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q13] != 6 -> - or([q15 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q15] = x_ExplicitVarSizeWithDummy[q13] - | q15 : int(1..4)]) - | q13 : int(1..4)]), - and([q17 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q19] != 6 /\ - x_ExplicitVarSizeWithDummy[q19] = x_ExplicitVarSizeWithMarker_Values[q17] - | q19 : int(1..4)]) - | q17 : int(1..4)]), - 1 <= sum([toInt(y_Occurrence[q20]) | q20 : int(2..5)]), - and([y_Occurrence[q21] -> - or([y_ExplicitVarSizeWithDummy[q23] != 6 /\ y_ExplicitVarSizeWithDummy[q23] = q21 | q23 : int(1..4)]) - | q21 : int(2..5)]), - and([y_ExplicitVarSizeWithDummy[q25] != 6 -> y_Occurrence[y_ExplicitVarSizeWithDummy[q25]] | q25 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_3_2_2_2-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_3_2_2_2-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_2_2_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_3_2_2_2-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_3_2_2_2-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_2_2_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_3_2_2_2.eprime b/tests/exhaustive/basic/set09/expected/model_3_2_2_2.eprime deleted file mode 100644 index 7f3fb2bd48..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_2_2_2.eprime +++ /dev/null @@ -1,37 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -branching on - [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, - y_ExplicitVarSizeWithDummy] -such that - and([q20 <= x_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithDummy[q21] != 6 -> - x_ExplicitVarSizeWithMarker_Values[q20] + 2 = y_ExplicitVarSizeWithDummy[q21] - | q20 : int(1..4), q21 : int(1..4)]), - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..3)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 2 | q2 : int(1..4)]), - 1 <= x_ExplicitVarSizeWithMarker_Marker, - and([y_ExplicitVarSizeWithDummy[q4] < y_ExplicitVarSizeWithDummy[q4 + 1] \/ y_ExplicitVarSizeWithDummy[q4] = 6 - | q4 : int(1..3)]), - and([y_ExplicitVarSizeWithDummy[q5] = 6 -> y_ExplicitVarSizeWithDummy[q5 + 1] = 6 | q5 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q6] != 6) | q6 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q8] < x_ExplicitVarSizeWithDummy[q8 + 1] \/ x_ExplicitVarSizeWithDummy[q8] = 6 - | q8 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q9] = 6 -> x_ExplicitVarSizeWithDummy[q9 + 1] = 6 | q9 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q10] != 6) | q10 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q13] != 6 -> - or([q15 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q15] = x_ExplicitVarSizeWithDummy[q13] - | q15 : int(1..4)]) - | q13 : int(1..4)]), - and([q17 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q19] != 6 /\ - x_ExplicitVarSizeWithDummy[q19] = x_ExplicitVarSizeWithMarker_Values[q17] - | q19 : int(1..4)]) - | q17 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_3_2_2_3-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_3_2_2_3-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_2_2_3-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_3_2_2_3-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_3_2_2_3-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_2_2_3-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_3_2_2_3.eprime b/tests/exhaustive/basic/set09/expected/model_3_2_2_3.eprime deleted file mode 100644 index cc44894190..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_2_2_3.eprime +++ /dev/null @@ -1,54 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -find y_ExplicitVarSizeWithMarker_Marker: int(0..4) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -branching on - [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, - y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithDummy] -such that - and([q31 <= x_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithDummy[q32] != 6 -> - x_ExplicitVarSizeWithMarker_Values[q31] + 2 = y_ExplicitVarSizeWithDummy[q32] - | q31 : int(1..4), q32 : int(1..4)]), - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..3)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 2 | q2 : int(1..4)]), - 1 <= x_ExplicitVarSizeWithMarker_Marker, - and([y_ExplicitVarSizeWithDummy[q4] < y_ExplicitVarSizeWithDummy[q4 + 1] \/ y_ExplicitVarSizeWithDummy[q4] = 6 - | q4 : int(1..3)]), - and([y_ExplicitVarSizeWithDummy[q5] = 6 -> y_ExplicitVarSizeWithDummy[q5 + 1] = 6 | q5 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q6] != 6) | q6 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q8] < x_ExplicitVarSizeWithDummy[q8 + 1] \/ x_ExplicitVarSizeWithDummy[q8] = 6 - | q8 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q9] = 6 -> x_ExplicitVarSizeWithDummy[q9 + 1] = 6 | q9 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q10] != 6) | q10 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q13] != 6 -> - or([q15 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q15] = x_ExplicitVarSizeWithDummy[q13] - | q15 : int(1..4)]) - | q13 : int(1..4)]), - and([q17 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q19] != 6 /\ - x_ExplicitVarSizeWithDummy[q19] = x_ExplicitVarSizeWithMarker_Values[q17] - | q19 : int(1..4)]) - | q17 : int(1..4)]), - and([q20 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> - y_ExplicitVarSizeWithMarker_Values[q20] < y_ExplicitVarSizeWithMarker_Values[q20 + 1] - | q20 : int(1..3)]), - and([q21 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q21] = 2 | q21 : int(1..4)]), - 1 <= y_ExplicitVarSizeWithMarker_Marker, - and([q24 <= y_ExplicitVarSizeWithMarker_Marker -> - or([y_ExplicitVarSizeWithDummy[q26] != 6 /\ - y_ExplicitVarSizeWithDummy[q26] = y_ExplicitVarSizeWithMarker_Values[q24] - | q26 : int(1..4)]) - | q24 : int(1..4)]), - and([y_ExplicitVarSizeWithDummy[q28] != 6 -> - or([q30 <= y_ExplicitVarSizeWithMarker_Marker /\ - y_ExplicitVarSizeWithMarker_Values[q30] = y_ExplicitVarSizeWithDummy[q28] - | q30 : int(1..4)]) - | q28 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_3_2_2_4-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_3_2_2_4-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_2_2_4-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_3_2_2_4-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_3_2_2_4-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_2_2_4-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_3_2_2_4.eprime b/tests/exhaustive/basic/set09/expected/model_3_2_2_4.eprime deleted file mode 100644 index c22f517453..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_2_2_4.eprime +++ /dev/null @@ -1,56 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -branching on - [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, - y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithDummy] -such that - and([q33 <= x_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithDummy[q34] != 6 -> - x_ExplicitVarSizeWithMarker_Values[q33] + 2 = y_ExplicitVarSizeWithDummy[q34] - | q33 : int(1..4), q34 : int(1..4)]), - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..3)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 2 | q2 : int(1..4)]), - 1 <= x_ExplicitVarSizeWithMarker_Marker, - and([y_ExplicitVarSizeWithDummy[q4] < y_ExplicitVarSizeWithDummy[q4 + 1] \/ y_ExplicitVarSizeWithDummy[q4] = 6 - | q4 : int(1..3)]), - and([y_ExplicitVarSizeWithDummy[q5] = 6 -> y_ExplicitVarSizeWithDummy[q5 + 1] = 6 | q5 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q6] != 6) | q6 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q8] < x_ExplicitVarSizeWithDummy[q8 + 1] \/ x_ExplicitVarSizeWithDummy[q8] = 6 - | q8 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q9] = 6 -> x_ExplicitVarSizeWithDummy[q9 + 1] = 6 | q9 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q10] != 6) | q10 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q13] != 6 -> - or([q15 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q15] = x_ExplicitVarSizeWithDummy[q13] - | q15 : int(1..4)]) - | q13 : int(1..4)]), - and([q17 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q19] != 6 /\ - x_ExplicitVarSizeWithDummy[q19] = x_ExplicitVarSizeWithMarker_Values[q17] - | q19 : int(1..4)]) - | q17 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q20 + 1] -> - y_ExplicitVarSizeWithFlags_Values[q20] < y_ExplicitVarSizeWithFlags_Values[q20 + 1] - | q20 : int(1..3)]), - and([y_ExplicitVarSizeWithFlags_Flags[q21] = false -> y_ExplicitVarSizeWithFlags_Values[q21] = 2 - | q21 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q22 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q22] | q22 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q23]) | q23 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q26] -> - or([y_ExplicitVarSizeWithDummy[q28] != 6 /\ - y_ExplicitVarSizeWithDummy[q28] = y_ExplicitVarSizeWithFlags_Values[q26] - | q28 : int(1..4)]) - | q26 : int(1..4)]), - and([y_ExplicitVarSizeWithDummy[q30] != 6 -> - or([y_ExplicitVarSizeWithFlags_Flags[q32] /\ - y_ExplicitVarSizeWithFlags_Values[q32] = y_ExplicitVarSizeWithDummy[q30] - | q32 : int(1..4)]) - | q30 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_3_2_3_1-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_3_2_3_1-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_2_3_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_3_2_3_1-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_3_2_3_1-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_2_3_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_3_2_3_1.eprime b/tests/exhaustive/basic/set09/expected/model_3_2_3_1.eprime deleted file mode 100644 index 0059fed8b2..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_2_3_1.eprime +++ /dev/null @@ -1,27 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -find y_Occurrence: matrix indexed by [int(2..5)] of bool -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, y_Occurrence, y_ExplicitVarSizeWithDummy] -such that - and([q14 <= x_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithDummy[q15] != 6 -> - x_ExplicitVarSizeWithMarker_Values[q14] + 2 = y_ExplicitVarSizeWithDummy[q15] - | q14 : int(1..4), q15 : int(1..4)]), - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..3)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 2 | q2 : int(1..4)]), - 1 <= x_ExplicitVarSizeWithMarker_Marker, - and([y_ExplicitVarSizeWithDummy[q4] < y_ExplicitVarSizeWithDummy[q4 + 1] \/ y_ExplicitVarSizeWithDummy[q4] = 6 - | q4 : int(1..3)]), - and([y_ExplicitVarSizeWithDummy[q5] = 6 -> y_ExplicitVarSizeWithDummy[q5 + 1] = 6 | q5 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q6] != 6) | q6 : int(1..4)]), - 1 <= sum([toInt(y_Occurrence[q8]) | q8 : int(2..5)]), - and([y_Occurrence[q9] -> - or([y_ExplicitVarSizeWithDummy[q11] != 6 /\ y_ExplicitVarSizeWithDummy[q11] = q9 | q11 : int(1..4)]) - | q9 : int(2..5)]), - and([y_ExplicitVarSizeWithDummy[q13] != 6 -> y_Occurrence[y_ExplicitVarSizeWithDummy[q13]] | q13 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_3_2_3_2-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_3_2_3_2-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_2_3_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_3_2_3_2-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_3_2_3_2-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_2_3_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_3_2_3_2.eprime b/tests/exhaustive/basic/set09/expected/model_3_2_3_2.eprime deleted file mode 100644 index 99499bc7b1..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_2_3_2.eprime +++ /dev/null @@ -1,20 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -branching on [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithDummy] -such that - and([q8 <= x_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithDummy[q9] != 6 -> - x_ExplicitVarSizeWithMarker_Values[q8] + 2 = y_ExplicitVarSizeWithDummy[q9] - | q8 : int(1..4), q9 : int(1..4)]), - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..3)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 2 | q2 : int(1..4)]), - 1 <= x_ExplicitVarSizeWithMarker_Marker, - and([y_ExplicitVarSizeWithDummy[q4] < y_ExplicitVarSizeWithDummy[q4 + 1] \/ y_ExplicitVarSizeWithDummy[q4] = 6 - | q4 : int(1..3)]), - and([y_ExplicitVarSizeWithDummy[q5] = 6 -> y_ExplicitVarSizeWithDummy[q5 + 1] = 6 | q5 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q6] != 6) | q6 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_3_2_3_3-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_3_2_3_3-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_2_3_3-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_3_2_3_3-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_3_2_3_3-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_2_3_3-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_3_2_3_3.eprime b/tests/exhaustive/basic/set09/expected/model_3_2_3_3.eprime deleted file mode 100644 index 45e304f746..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_2_3_3.eprime +++ /dev/null @@ -1,39 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -find y_ExplicitVarSizeWithMarker_Marker: int(0..4) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithMarker_Marker, - y_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithDummy] -such that - and([q19 <= x_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithDummy[q20] != 6 -> - x_ExplicitVarSizeWithMarker_Values[q19] + 2 = y_ExplicitVarSizeWithDummy[q20] - | q19 : int(1..4), q20 : int(1..4)]), - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..3)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 2 | q2 : int(1..4)]), - 1 <= x_ExplicitVarSizeWithMarker_Marker, - and([y_ExplicitVarSizeWithDummy[q4] < y_ExplicitVarSizeWithDummy[q4 + 1] \/ y_ExplicitVarSizeWithDummy[q4] = 6 - | q4 : int(1..3)]), - and([y_ExplicitVarSizeWithDummy[q5] = 6 -> y_ExplicitVarSizeWithDummy[q5 + 1] = 6 | q5 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q6] != 6) | q6 : int(1..4)]), - and([q8 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> - y_ExplicitVarSizeWithMarker_Values[q8] < y_ExplicitVarSizeWithMarker_Values[q8 + 1] - | q8 : int(1..3)]), - and([q9 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q9] = 2 | q9 : int(1..4)]), - 1 <= y_ExplicitVarSizeWithMarker_Marker, - and([q12 <= y_ExplicitVarSizeWithMarker_Marker -> - or([y_ExplicitVarSizeWithDummy[q14] != 6 /\ - y_ExplicitVarSizeWithDummy[q14] = y_ExplicitVarSizeWithMarker_Values[q12] - | q14 : int(1..4)]) - | q12 : int(1..4)]), - and([y_ExplicitVarSizeWithDummy[q16] != 6 -> - or([q18 <= y_ExplicitVarSizeWithMarker_Marker /\ - y_ExplicitVarSizeWithMarker_Values[q18] = y_ExplicitVarSizeWithDummy[q16] - | q18 : int(1..4)]) - | q16 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_3_2_3_4-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_3_2_3_4-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_2_3_4-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_3_2_3_4-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_3_2_3_4-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_2_3_4-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_3_2_3_4.eprime b/tests/exhaustive/basic/set09/expected/model_3_2_3_4.eprime deleted file mode 100644 index f098a13d32..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_2_3_4.eprime +++ /dev/null @@ -1,40 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithFlags_Flags, - y_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithDummy] -such that - and([q21 <= x_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithDummy[q22] != 6 -> - x_ExplicitVarSizeWithMarker_Values[q21] + 2 = y_ExplicitVarSizeWithDummy[q22] - | q21 : int(1..4), q22 : int(1..4)]), - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..3)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 2 | q2 : int(1..4)]), - 1 <= x_ExplicitVarSizeWithMarker_Marker, - and([y_ExplicitVarSizeWithDummy[q4] < y_ExplicitVarSizeWithDummy[q4 + 1] \/ y_ExplicitVarSizeWithDummy[q4] = 6 - | q4 : int(1..3)]), - and([y_ExplicitVarSizeWithDummy[q5] = 6 -> y_ExplicitVarSizeWithDummy[q5 + 1] = 6 | q5 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q6] != 6) | q6 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q8 + 1] -> - y_ExplicitVarSizeWithFlags_Values[q8] < y_ExplicitVarSizeWithFlags_Values[q8 + 1] - | q8 : int(1..3)]), - and([y_ExplicitVarSizeWithFlags_Flags[q9] = false -> y_ExplicitVarSizeWithFlags_Values[q9] = 2 | q9 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q10 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q10] | q10 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q11]) | q11 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q14] -> - or([y_ExplicitVarSizeWithDummy[q16] != 6 /\ - y_ExplicitVarSizeWithDummy[q16] = y_ExplicitVarSizeWithFlags_Values[q14] - | q16 : int(1..4)]) - | q14 : int(1..4)]), - and([y_ExplicitVarSizeWithDummy[q18] != 6 -> - or([y_ExplicitVarSizeWithFlags_Flags[q20] /\ - y_ExplicitVarSizeWithFlags_Values[q20] = y_ExplicitVarSizeWithDummy[q18] - | q20 : int(1..4)]) - | q18 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_3_2_4_1-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_3_2_4_1-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_2_4_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_3_2_4_1-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_3_2_4_1-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_2_4_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_3_2_4_1.eprime b/tests/exhaustive/basic/set09/expected/model_3_2_4_1.eprime deleted file mode 100644 index 6fc2962eea..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_2_4_1.eprime +++ /dev/null @@ -1,46 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -find y_Occurrence: matrix indexed by [int(2..5)] of bool -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithMarker_Marker, - x_ExplicitVarSizeWithMarker_Values, y_Occurrence, y_ExplicitVarSizeWithDummy] -such that - and([q27 <= x_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithDummy[q28] != 6 -> - x_ExplicitVarSizeWithMarker_Values[q27] + 2 = y_ExplicitVarSizeWithDummy[q28] - | q27 : int(1..4), q28 : int(1..4)]), - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..3)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 2 | q2 : int(1..4)]), - 1 <= x_ExplicitVarSizeWithMarker_Marker, - and([y_ExplicitVarSizeWithDummy[q4] < y_ExplicitVarSizeWithDummy[q4 + 1] \/ y_ExplicitVarSizeWithDummy[q4] = 6 - | q4 : int(1..3)]), - and([y_ExplicitVarSizeWithDummy[q5] = 6 -> y_ExplicitVarSizeWithDummy[q5 + 1] = 6 | q5 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q6] != 6) | q6 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q8 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q8] < x_ExplicitVarSizeWithFlags_Values[q8 + 1] - | q8 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q9] = false -> x_ExplicitVarSizeWithFlags_Values[q9] = 2 | q9 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q10 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q10] | q10 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q11]) | q11 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q14] -> - or([q16 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q16] = x_ExplicitVarSizeWithFlags_Values[q14] - | q16 : int(1..4)]) - | q14 : int(1..4)]), - and([q18 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q20] /\ - x_ExplicitVarSizeWithFlags_Values[q20] = x_ExplicitVarSizeWithMarker_Values[q18] - | q20 : int(1..4)]) - | q18 : int(1..4)]), - 1 <= sum([toInt(y_Occurrence[q21]) | q21 : int(2..5)]), - and([y_Occurrence[q22] -> - or([y_ExplicitVarSizeWithDummy[q24] != 6 /\ y_ExplicitVarSizeWithDummy[q24] = q22 | q24 : int(1..4)]) - | q22 : int(2..5)]), - and([y_ExplicitVarSizeWithDummy[q26] != 6 -> y_Occurrence[y_ExplicitVarSizeWithDummy[q26]] | q26 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_3_2_4_2-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_3_2_4_2-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_2_4_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_3_2_4_2-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_3_2_4_2-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_2_4_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_3_2_4_2.eprime b/tests/exhaustive/basic/set09/expected/model_3_2_4_2.eprime deleted file mode 100644 index dbe9bc7729..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_2_4_2.eprime +++ /dev/null @@ -1,40 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithMarker_Marker, - x_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithDummy] -such that - and([q21 <= x_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithDummy[q22] != 6 -> - x_ExplicitVarSizeWithMarker_Values[q21] + 2 = y_ExplicitVarSizeWithDummy[q22] - | q21 : int(1..4), q22 : int(1..4)]), - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..3)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 2 | q2 : int(1..4)]), - 1 <= x_ExplicitVarSizeWithMarker_Marker, - and([y_ExplicitVarSizeWithDummy[q4] < y_ExplicitVarSizeWithDummy[q4 + 1] \/ y_ExplicitVarSizeWithDummy[q4] = 6 - | q4 : int(1..3)]), - and([y_ExplicitVarSizeWithDummy[q5] = 6 -> y_ExplicitVarSizeWithDummy[q5 + 1] = 6 | q5 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q6] != 6) | q6 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q8 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q8] < x_ExplicitVarSizeWithFlags_Values[q8 + 1] - | q8 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q9] = false -> x_ExplicitVarSizeWithFlags_Values[q9] = 2 | q9 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q10 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q10] | q10 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q11]) | q11 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q14] -> - or([q16 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q16] = x_ExplicitVarSizeWithFlags_Values[q14] - | q16 : int(1..4)]) - | q14 : int(1..4)]), - and([q18 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q20] /\ - x_ExplicitVarSizeWithFlags_Values[q20] = x_ExplicitVarSizeWithMarker_Values[q18] - | q20 : int(1..4)]) - | q18 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_3_2_4_3-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_3_2_4_3-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_2_4_3-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_3_2_4_3-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_3_2_4_3-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_2_4_3-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_3_2_4_3.eprime b/tests/exhaustive/basic/set09/expected/model_3_2_4_3.eprime deleted file mode 100644 index 39e771368e..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_2_4_3.eprime +++ /dev/null @@ -1,58 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -find y_ExplicitVarSizeWithMarker_Marker: int(0..4) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithMarker_Marker, - x_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values, - y_ExplicitVarSizeWithDummy] -such that - and([q32 <= x_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithDummy[q33] != 6 -> - x_ExplicitVarSizeWithMarker_Values[q32] + 2 = y_ExplicitVarSizeWithDummy[q33] - | q32 : int(1..4), q33 : int(1..4)]), - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..3)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 2 | q2 : int(1..4)]), - 1 <= x_ExplicitVarSizeWithMarker_Marker, - and([y_ExplicitVarSizeWithDummy[q4] < y_ExplicitVarSizeWithDummy[q4 + 1] \/ y_ExplicitVarSizeWithDummy[q4] = 6 - | q4 : int(1..3)]), - and([y_ExplicitVarSizeWithDummy[q5] = 6 -> y_ExplicitVarSizeWithDummy[q5 + 1] = 6 | q5 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q6] != 6) | q6 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q8 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q8] < x_ExplicitVarSizeWithFlags_Values[q8 + 1] - | q8 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q9] = false -> x_ExplicitVarSizeWithFlags_Values[q9] = 2 | q9 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q10 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q10] | q10 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q11]) | q11 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q14] -> - or([q16 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q16] = x_ExplicitVarSizeWithFlags_Values[q14] - | q16 : int(1..4)]) - | q14 : int(1..4)]), - and([q18 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q20] /\ - x_ExplicitVarSizeWithFlags_Values[q20] = x_ExplicitVarSizeWithMarker_Values[q18] - | q20 : int(1..4)]) - | q18 : int(1..4)]), - and([q21 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> - y_ExplicitVarSizeWithMarker_Values[q21] < y_ExplicitVarSizeWithMarker_Values[q21 + 1] - | q21 : int(1..3)]), - and([q22 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q22] = 2 | q22 : int(1..4)]), - 1 <= y_ExplicitVarSizeWithMarker_Marker, - and([q25 <= y_ExplicitVarSizeWithMarker_Marker -> - or([y_ExplicitVarSizeWithDummy[q27] != 6 /\ - y_ExplicitVarSizeWithDummy[q27] = y_ExplicitVarSizeWithMarker_Values[q25] - | q27 : int(1..4)]) - | q25 : int(1..4)]), - and([y_ExplicitVarSizeWithDummy[q29] != 6 -> - or([q31 <= y_ExplicitVarSizeWithMarker_Marker /\ - y_ExplicitVarSizeWithMarker_Values[q31] = y_ExplicitVarSizeWithDummy[q29] - | q31 : int(1..4)]) - | q29 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_3_2_4_4-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_3_2_4_4-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_2_4_4-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_3_2_4_4-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_3_2_4_4-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_2_4_4-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_3_2_4_4.eprime b/tests/exhaustive/basic/set09/expected/model_3_2_4_4.eprime deleted file mode 100644 index 6425ad0a2b..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_2_4_4.eprime +++ /dev/null @@ -1,60 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithMarker_Marker, - x_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values, - y_ExplicitVarSizeWithDummy] -such that - and([q34 <= x_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithDummy[q35] != 6 -> - x_ExplicitVarSizeWithMarker_Values[q34] + 2 = y_ExplicitVarSizeWithDummy[q35] - | q34 : int(1..4), q35 : int(1..4)]), - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..3)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 2 | q2 : int(1..4)]), - 1 <= x_ExplicitVarSizeWithMarker_Marker, - and([y_ExplicitVarSizeWithDummy[q4] < y_ExplicitVarSizeWithDummy[q4 + 1] \/ y_ExplicitVarSizeWithDummy[q4] = 6 - | q4 : int(1..3)]), - and([y_ExplicitVarSizeWithDummy[q5] = 6 -> y_ExplicitVarSizeWithDummy[q5 + 1] = 6 | q5 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q6] != 6) | q6 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q8 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q8] < x_ExplicitVarSizeWithFlags_Values[q8 + 1] - | q8 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q9] = false -> x_ExplicitVarSizeWithFlags_Values[q9] = 2 | q9 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q10 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q10] | q10 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q11]) | q11 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q14] -> - or([q16 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q16] = x_ExplicitVarSizeWithFlags_Values[q14] - | q16 : int(1..4)]) - | q14 : int(1..4)]), - and([q18 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q20] /\ - x_ExplicitVarSizeWithFlags_Values[q20] = x_ExplicitVarSizeWithMarker_Values[q18] - | q20 : int(1..4)]) - | q18 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q21 + 1] -> - y_ExplicitVarSizeWithFlags_Values[q21] < y_ExplicitVarSizeWithFlags_Values[q21 + 1] - | q21 : int(1..3)]), - and([y_ExplicitVarSizeWithFlags_Flags[q22] = false -> y_ExplicitVarSizeWithFlags_Values[q22] = 2 - | q22 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q23 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q23] | q23 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q24]) | q24 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q27] -> - or([y_ExplicitVarSizeWithDummy[q29] != 6 /\ - y_ExplicitVarSizeWithDummy[q29] = y_ExplicitVarSizeWithFlags_Values[q27] - | q29 : int(1..4)]) - | q27 : int(1..4)]), - and([y_ExplicitVarSizeWithDummy[q31] != 6 -> - or([y_ExplicitVarSizeWithFlags_Flags[q33] /\ - y_ExplicitVarSizeWithFlags_Values[q33] = y_ExplicitVarSizeWithDummy[q31] - | q33 : int(1..4)]) - | q31 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_3_3_1_1-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_3_3_1_1-solution000001.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_3_1_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_3_3_1_1-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_3_3_1_1-solution000002.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_3_1_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_3_3_1_1.eprime b/tests/exhaustive/basic/set09/expected/model_3_3_1_1.eprime deleted file mode 100644 index 3ec2bcc362..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_3_1_1.eprime +++ /dev/null @@ -1,40 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -find x_Occurrence: matrix indexed by [int(2..5)] of bool -find y_ExplicitVarSizeWithMarker_Marker: int(0..4) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_Occurrence: matrix indexed by [int(2..5)] of bool -branching on - [x_Occurrence, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, y_Occurrence, - y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values] -such that - and([q14 <= x_ExplicitVarSizeWithMarker_Marker /\ q15 <= y_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q14] + 2 = y_ExplicitVarSizeWithMarker_Values[q15] - | q14 : int(1..4), q15 : int(1..4)]), - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..3)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 2 | q2 : int(1..4)]), - 1 <= x_ExplicitVarSizeWithMarker_Marker, - and([q4 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> - y_ExplicitVarSizeWithMarker_Values[q4] < y_ExplicitVarSizeWithMarker_Values[q4 + 1] - | q4 : int(1..3)]), - and([q5 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q5] = 2 | q5 : int(1..4)]), - 1 <= y_ExplicitVarSizeWithMarker_Marker, - 1 <= sum([toInt(x_Occurrence[q7]) | q7 : int(2..5)]), - and([x_Occurrence[q16] -> - or([q18 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q18] = q16 - | q18 : int(1..4)]) - | q16 : int(2..5)]), - and([q20 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q20]] - | q20 : int(1..4)]), - 1 <= sum([toInt(y_Occurrence[q8]) | q8 : int(2..5)]), - and([y_Occurrence[q9] -> - or([q11 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[q11] = q9 - | q11 : int(1..4)]) - | q9 : int(2..5)]), - and([q13 <= y_ExplicitVarSizeWithMarker_Marker -> y_Occurrence[y_ExplicitVarSizeWithMarker_Values[q13]] - | q13 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_3_3_1_2-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_3_3_1_2-solution000001.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_3_1_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_3_3_1_2-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_3_3_1_2-solution000002.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_3_1_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_3_3_1_2.eprime b/tests/exhaustive/basic/set09/expected/model_3_3_1_2.eprime deleted file mode 100644 index 8eaef50691..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_3_1_2.eprime +++ /dev/null @@ -1,47 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -find x_Occurrence: matrix indexed by [int(2..5)] of bool -find y_ExplicitVarSizeWithMarker_Marker: int(0..4) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -branching on - [x_Occurrence, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithDummy, - y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values] -such that - and([q25 <= x_ExplicitVarSizeWithMarker_Marker /\ q26 <= y_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q25] + 2 = y_ExplicitVarSizeWithMarker_Values[q26] - | q25 : int(1..4), q26 : int(1..4)]), - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..3)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 2 | q2 : int(1..4)]), - 1 <= x_ExplicitVarSizeWithMarker_Marker, - and([q4 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> - y_ExplicitVarSizeWithMarker_Values[q4] < y_ExplicitVarSizeWithMarker_Values[q4 + 1] - | q4 : int(1..3)]), - and([q5 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q5] = 2 | q5 : int(1..4)]), - 1 <= y_ExplicitVarSizeWithMarker_Marker, - 1 <= sum([toInt(x_Occurrence[q7]) | q7 : int(2..5)]), - and([x_Occurrence[q20] -> - or([q22 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q22] = q20 - | q22 : int(1..4)]) - | q20 : int(2..5)]), - and([q24 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q24]] - | q24 : int(1..4)]), - and([y_ExplicitVarSizeWithDummy[q8] < y_ExplicitVarSizeWithDummy[q8 + 1] \/ y_ExplicitVarSizeWithDummy[q8] = 6 - | q8 : int(1..3)]), - and([y_ExplicitVarSizeWithDummy[q9] = 6 -> y_ExplicitVarSizeWithDummy[q9 + 1] = 6 | q9 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q10] != 6) | q10 : int(1..4)]), - and([y_ExplicitVarSizeWithDummy[q13] != 6 -> - or([q15 <= y_ExplicitVarSizeWithMarker_Marker /\ - y_ExplicitVarSizeWithMarker_Values[q15] = y_ExplicitVarSizeWithDummy[q13] - | q15 : int(1..4)]) - | q13 : int(1..4)]), - and([q17 <= y_ExplicitVarSizeWithMarker_Marker -> - or([y_ExplicitVarSizeWithDummy[q19] != 6 /\ - y_ExplicitVarSizeWithDummy[q19] = y_ExplicitVarSizeWithMarker_Values[q17] - | q19 : int(1..4)]) - | q17 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_3_3_1_3-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_3_3_1_3-solution000001.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_3_1_3-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_3_3_1_3-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_3_3_1_3-solution000002.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_3_1_3-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_3_3_1_3.eprime b/tests/exhaustive/basic/set09/expected/model_3_3_1_3.eprime deleted file mode 100644 index 16bba88020..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_3_1_3.eprime +++ /dev/null @@ -1,32 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -find x_Occurrence: matrix indexed by [int(2..5)] of bool -find y_ExplicitVarSizeWithMarker_Marker: int(0..4) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -branching on - [x_Occurrence, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, - y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values] -such that - and([q13 <= x_ExplicitVarSizeWithMarker_Marker /\ q14 <= y_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q13] + 2 = y_ExplicitVarSizeWithMarker_Values[q14] - | q13 : int(1..4), q14 : int(1..4)]), - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..3)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 2 | q2 : int(1..4)]), - 1 <= x_ExplicitVarSizeWithMarker_Marker, - and([q4 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> - y_ExplicitVarSizeWithMarker_Values[q4] < y_ExplicitVarSizeWithMarker_Values[q4 + 1] - | q4 : int(1..3)]), - and([q5 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q5] = 2 | q5 : int(1..4)]), - 1 <= y_ExplicitVarSizeWithMarker_Marker, - 1 <= sum([toInt(x_Occurrence[q7]) | q7 : int(2..5)]), - and([x_Occurrence[q8] -> - or([q10 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q10] = q8 - | q10 : int(1..4)]) - | q8 : int(2..5)]), - and([q12 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q12]] - | q12 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_3_3_1_4-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_3_3_1_4-solution000001.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_3_1_4-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_3_3_1_4-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_3_3_1_4-solution000002.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_3_1_4-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_3_3_1_4.eprime b/tests/exhaustive/basic/set09/expected/model_3_3_1_4.eprime deleted file mode 100644 index 487253019b..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_3_1_4.eprime +++ /dev/null @@ -1,51 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -find x_Occurrence: matrix indexed by [int(2..5)] of bool -find y_ExplicitVarSizeWithMarker_Marker: int(0..4) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -branching on - [x_Occurrence, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, - y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithMarker_Marker, - y_ExplicitVarSizeWithMarker_Values] -such that - and([q26 <= x_ExplicitVarSizeWithMarker_Marker /\ q27 <= y_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q26] + 2 = y_ExplicitVarSizeWithMarker_Values[q27] - | q26 : int(1..4), q27 : int(1..4)]), - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..3)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 2 | q2 : int(1..4)]), - 1 <= x_ExplicitVarSizeWithMarker_Marker, - and([q4 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> - y_ExplicitVarSizeWithMarker_Values[q4] < y_ExplicitVarSizeWithMarker_Values[q4 + 1] - | q4 : int(1..3)]), - and([q5 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q5] = 2 | q5 : int(1..4)]), - 1 <= y_ExplicitVarSizeWithMarker_Marker, - 1 <= sum([toInt(x_Occurrence[q7]) | q7 : int(2..5)]), - and([x_Occurrence[q21] -> - or([q23 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q23] = q21 - | q23 : int(1..4)]) - | q21 : int(2..5)]), - and([q25 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q25]] - | q25 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q8 + 1] -> - y_ExplicitVarSizeWithFlags_Values[q8] < y_ExplicitVarSizeWithFlags_Values[q8 + 1] - | q8 : int(1..3)]), - and([y_ExplicitVarSizeWithFlags_Flags[q9] = false -> y_ExplicitVarSizeWithFlags_Values[q9] = 2 | q9 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q10 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q10] | q10 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q11]) | q11 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q14] -> - or([q16 <= y_ExplicitVarSizeWithMarker_Marker /\ - y_ExplicitVarSizeWithMarker_Values[q16] = y_ExplicitVarSizeWithFlags_Values[q14] - | q16 : int(1..4)]) - | q14 : int(1..4)]), - and([q18 <= y_ExplicitVarSizeWithMarker_Marker -> - or([y_ExplicitVarSizeWithFlags_Flags[q20] /\ - y_ExplicitVarSizeWithFlags_Values[q20] = y_ExplicitVarSizeWithMarker_Values[q18] - | q20 : int(1..4)]) - | q18 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_3_3_2_1-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_3_3_2_1-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_3_2_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_3_3_2_1-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_3_3_2_1-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_3_2_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_3_3_2_1.eprime b/tests/exhaustive/basic/set09/expected/model_3_3_2_1.eprime deleted file mode 100644 index 124edd1223..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_3_2_1.eprime +++ /dev/null @@ -1,47 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -find y_ExplicitVarSizeWithMarker_Marker: int(0..4) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_Occurrence: matrix indexed by [int(2..5)] of bool -branching on - [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, y_Occurrence, - y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values] -such that - and([q25 <= x_ExplicitVarSizeWithMarker_Marker /\ q26 <= y_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q25] + 2 = y_ExplicitVarSizeWithMarker_Values[q26] - | q25 : int(1..4), q26 : int(1..4)]), - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..3)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 2 | q2 : int(1..4)]), - 1 <= x_ExplicitVarSizeWithMarker_Marker, - and([q4 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> - y_ExplicitVarSizeWithMarker_Values[q4] < y_ExplicitVarSizeWithMarker_Values[q4 + 1] - | q4 : int(1..3)]), - and([q5 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q5] = 2 | q5 : int(1..4)]), - 1 <= y_ExplicitVarSizeWithMarker_Marker, - and([x_ExplicitVarSizeWithDummy[q7] < x_ExplicitVarSizeWithDummy[q7 + 1] \/ x_ExplicitVarSizeWithDummy[q7] = 6 - | q7 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q8] = 6 -> x_ExplicitVarSizeWithDummy[q8 + 1] = 6 | q8 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q9] != 6) | q9 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q12] != 6 -> - or([q14 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q14] = x_ExplicitVarSizeWithDummy[q12] - | q14 : int(1..4)]) - | q12 : int(1..4)]), - and([q16 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q18] != 6 /\ - x_ExplicitVarSizeWithDummy[q18] = x_ExplicitVarSizeWithMarker_Values[q16] - | q18 : int(1..4)]) - | q16 : int(1..4)]), - 1 <= sum([toInt(y_Occurrence[q19]) | q19 : int(2..5)]), - and([y_Occurrence[q20] -> - or([q22 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[q22] = q20 - | q22 : int(1..4)]) - | q20 : int(2..5)]), - and([q24 <= y_ExplicitVarSizeWithMarker_Marker -> y_Occurrence[y_ExplicitVarSizeWithMarker_Values[q24]] - | q24 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_3_3_2_2-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_3_3_2_2-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_3_2_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_3_3_2_2-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_3_3_2_2-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_3_2_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_3_3_2_2.eprime b/tests/exhaustive/basic/set09/expected/model_3_3_2_2.eprime deleted file mode 100644 index 7806a133c2..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_3_2_2.eprime +++ /dev/null @@ -1,54 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -find y_ExplicitVarSizeWithMarker_Marker: int(0..4) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -branching on - [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, - y_ExplicitVarSizeWithDummy, y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values] -such that - and([q31 <= x_ExplicitVarSizeWithMarker_Marker /\ q32 <= y_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q31] + 2 = y_ExplicitVarSizeWithMarker_Values[q32] - | q31 : int(1..4), q32 : int(1..4)]), - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..3)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 2 | q2 : int(1..4)]), - 1 <= x_ExplicitVarSizeWithMarker_Marker, - and([q4 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> - y_ExplicitVarSizeWithMarker_Values[q4] < y_ExplicitVarSizeWithMarker_Values[q4 + 1] - | q4 : int(1..3)]), - and([q5 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q5] = 2 | q5 : int(1..4)]), - 1 <= y_ExplicitVarSizeWithMarker_Marker, - and([x_ExplicitVarSizeWithDummy[q7] < x_ExplicitVarSizeWithDummy[q7 + 1] \/ x_ExplicitVarSizeWithDummy[q7] = 6 - | q7 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q8] = 6 -> x_ExplicitVarSizeWithDummy[q8 + 1] = 6 | q8 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q9] != 6) | q9 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q12] != 6 -> - or([q14 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q14] = x_ExplicitVarSizeWithDummy[q12] - | q14 : int(1..4)]) - | q12 : int(1..4)]), - and([q16 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q18] != 6 /\ - x_ExplicitVarSizeWithDummy[q18] = x_ExplicitVarSizeWithMarker_Values[q16] - | q18 : int(1..4)]) - | q16 : int(1..4)]), - and([y_ExplicitVarSizeWithDummy[q19] < y_ExplicitVarSizeWithDummy[q19 + 1] \/ y_ExplicitVarSizeWithDummy[q19] = 6 - | q19 : int(1..3)]), - and([y_ExplicitVarSizeWithDummy[q20] = 6 -> y_ExplicitVarSizeWithDummy[q20 + 1] = 6 | q20 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q21] != 6) | q21 : int(1..4)]), - and([y_ExplicitVarSizeWithDummy[q24] != 6 -> - or([q26 <= y_ExplicitVarSizeWithMarker_Marker /\ - y_ExplicitVarSizeWithMarker_Values[q26] = y_ExplicitVarSizeWithDummy[q24] - | q26 : int(1..4)]) - | q24 : int(1..4)]), - and([q28 <= y_ExplicitVarSizeWithMarker_Marker -> - or([y_ExplicitVarSizeWithDummy[q30] != 6 /\ - y_ExplicitVarSizeWithDummy[q30] = y_ExplicitVarSizeWithMarker_Values[q28] - | q30 : int(1..4)]) - | q28 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_3_3_2_3-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_3_3_2_3-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_3_2_3-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_3_3_2_3-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_3_3_2_3-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_3_2_3-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_3_3_2_3.eprime b/tests/exhaustive/basic/set09/expected/model_3_3_2_3.eprime deleted file mode 100644 index 8c27f375ef..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_3_2_3.eprime +++ /dev/null @@ -1,39 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -find y_ExplicitVarSizeWithMarker_Marker: int(0..4) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -branching on - [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, - y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values] -such that - and([q19 <= x_ExplicitVarSizeWithMarker_Marker /\ q20 <= y_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q19] + 2 = y_ExplicitVarSizeWithMarker_Values[q20] - | q19 : int(1..4), q20 : int(1..4)]), - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..3)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 2 | q2 : int(1..4)]), - 1 <= x_ExplicitVarSizeWithMarker_Marker, - and([q4 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> - y_ExplicitVarSizeWithMarker_Values[q4] < y_ExplicitVarSizeWithMarker_Values[q4 + 1] - | q4 : int(1..3)]), - and([q5 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q5] = 2 | q5 : int(1..4)]), - 1 <= y_ExplicitVarSizeWithMarker_Marker, - and([x_ExplicitVarSizeWithDummy[q7] < x_ExplicitVarSizeWithDummy[q7 + 1] \/ x_ExplicitVarSizeWithDummy[q7] = 6 - | q7 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q8] = 6 -> x_ExplicitVarSizeWithDummy[q8 + 1] = 6 | q8 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q9] != 6) | q9 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q12] != 6 -> - or([q14 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q14] = x_ExplicitVarSizeWithDummy[q12] - | q14 : int(1..4)]) - | q12 : int(1..4)]), - and([q16 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q18] != 6 /\ - x_ExplicitVarSizeWithDummy[q18] = x_ExplicitVarSizeWithMarker_Values[q16] - | q18 : int(1..4)]) - | q16 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_3_3_2_4-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_3_3_2_4-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_3_2_4-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_3_3_2_4-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_3_3_2_4-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_3_2_4-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_3_3_2_4.eprime b/tests/exhaustive/basic/set09/expected/model_3_3_2_4.eprime deleted file mode 100644 index 85a12b9508..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_3_2_4.eprime +++ /dev/null @@ -1,59 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -find y_ExplicitVarSizeWithMarker_Marker: int(0..4) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -branching on - [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, - y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithMarker_Marker, - y_ExplicitVarSizeWithMarker_Values] -such that - and([q32 <= x_ExplicitVarSizeWithMarker_Marker /\ q33 <= y_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q32] + 2 = y_ExplicitVarSizeWithMarker_Values[q33] - | q32 : int(1..4), q33 : int(1..4)]), - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..3)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 2 | q2 : int(1..4)]), - 1 <= x_ExplicitVarSizeWithMarker_Marker, - and([q4 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> - y_ExplicitVarSizeWithMarker_Values[q4] < y_ExplicitVarSizeWithMarker_Values[q4 + 1] - | q4 : int(1..3)]), - and([q5 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q5] = 2 | q5 : int(1..4)]), - 1 <= y_ExplicitVarSizeWithMarker_Marker, - and([x_ExplicitVarSizeWithDummy[q7] < x_ExplicitVarSizeWithDummy[q7 + 1] \/ x_ExplicitVarSizeWithDummy[q7] = 6 - | q7 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q8] = 6 -> x_ExplicitVarSizeWithDummy[q8 + 1] = 6 | q8 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q9] != 6) | q9 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q12] != 6 -> - or([q14 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q14] = x_ExplicitVarSizeWithDummy[q12] - | q14 : int(1..4)]) - | q12 : int(1..4)]), - and([q16 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q18] != 6 /\ - x_ExplicitVarSizeWithDummy[q18] = x_ExplicitVarSizeWithMarker_Values[q16] - | q18 : int(1..4)]) - | q16 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q19 + 1] -> - y_ExplicitVarSizeWithFlags_Values[q19] < y_ExplicitVarSizeWithFlags_Values[q19 + 1] - | q19 : int(1..3)]), - and([y_ExplicitVarSizeWithFlags_Flags[q20] = false -> y_ExplicitVarSizeWithFlags_Values[q20] = 2 - | q20 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q21 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q21] | q21 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q22]) | q22 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q25] -> - or([q27 <= y_ExplicitVarSizeWithMarker_Marker /\ - y_ExplicitVarSizeWithMarker_Values[q27] = y_ExplicitVarSizeWithFlags_Values[q25] - | q27 : int(1..4)]) - | q25 : int(1..4)]), - and([q29 <= y_ExplicitVarSizeWithMarker_Marker -> - or([y_ExplicitVarSizeWithFlags_Flags[q31] /\ - y_ExplicitVarSizeWithFlags_Values[q31] = y_ExplicitVarSizeWithMarker_Values[q29] - | q31 : int(1..4)]) - | q29 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_3_3_3_1-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_3_3_3_1-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_3_3_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_3_3_3_1-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_3_3_3_1-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_3_3_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_3_3_3_1.eprime b/tests/exhaustive/basic/set09/expected/model_3_3_3_1.eprime deleted file mode 100644 index 66dc7e15ca..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_3_3_1.eprime +++ /dev/null @@ -1,32 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_ExplicitVarSizeWithMarker_Marker: int(0..4) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_Occurrence: matrix indexed by [int(2..5)] of bool -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, y_Occurrence, - y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values] -such that - and([q13 <= x_ExplicitVarSizeWithMarker_Marker /\ q14 <= y_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q13] + 2 = y_ExplicitVarSizeWithMarker_Values[q14] - | q13 : int(1..4), q14 : int(1..4)]), - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..3)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 2 | q2 : int(1..4)]), - 1 <= x_ExplicitVarSizeWithMarker_Marker, - and([q4 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> - y_ExplicitVarSizeWithMarker_Values[q4] < y_ExplicitVarSizeWithMarker_Values[q4 + 1] - | q4 : int(1..3)]), - and([q5 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q5] = 2 | q5 : int(1..4)]), - 1 <= y_ExplicitVarSizeWithMarker_Marker, - 1 <= sum([toInt(y_Occurrence[q7]) | q7 : int(2..5)]), - and([y_Occurrence[q8] -> - or([q10 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[q10] = q8 - | q10 : int(1..4)]) - | q8 : int(2..5)]), - and([q12 <= y_ExplicitVarSizeWithMarker_Marker -> y_Occurrence[y_ExplicitVarSizeWithMarker_Values[q12]] - | q12 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_3_3_3_2-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_3_3_3_2-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_3_3_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_3_3_3_2-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_3_3_3_2-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_3_3_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_3_3_3_2.eprime b/tests/exhaustive/basic/set09/expected/model_3_3_3_2.eprime deleted file mode 100644 index 9618629cd8..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_3_3_2.eprime +++ /dev/null @@ -1,39 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_ExplicitVarSizeWithMarker_Marker: int(0..4) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithDummy, - y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values] -such that - and([q19 <= x_ExplicitVarSizeWithMarker_Marker /\ q20 <= y_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q19] + 2 = y_ExplicitVarSizeWithMarker_Values[q20] - | q19 : int(1..4), q20 : int(1..4)]), - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..3)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 2 | q2 : int(1..4)]), - 1 <= x_ExplicitVarSizeWithMarker_Marker, - and([q4 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> - y_ExplicitVarSizeWithMarker_Values[q4] < y_ExplicitVarSizeWithMarker_Values[q4 + 1] - | q4 : int(1..3)]), - and([q5 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q5] = 2 | q5 : int(1..4)]), - 1 <= y_ExplicitVarSizeWithMarker_Marker, - and([y_ExplicitVarSizeWithDummy[q7] < y_ExplicitVarSizeWithDummy[q7 + 1] \/ y_ExplicitVarSizeWithDummy[q7] = 6 - | q7 : int(1..3)]), - and([y_ExplicitVarSizeWithDummy[q8] = 6 -> y_ExplicitVarSizeWithDummy[q8 + 1] = 6 | q8 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q9] != 6) | q9 : int(1..4)]), - and([y_ExplicitVarSizeWithDummy[q12] != 6 -> - or([q14 <= y_ExplicitVarSizeWithMarker_Marker /\ - y_ExplicitVarSizeWithMarker_Values[q14] = y_ExplicitVarSizeWithDummy[q12] - | q14 : int(1..4)]) - | q12 : int(1..4)]), - and([q16 <= y_ExplicitVarSizeWithMarker_Marker -> - or([y_ExplicitVarSizeWithDummy[q18] != 6 /\ - y_ExplicitVarSizeWithDummy[q18] = y_ExplicitVarSizeWithMarker_Values[q16] - | q18 : int(1..4)]) - | q16 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_3_3_3_3-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_3_3_3_3-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_3_3_3-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_3_3_3_3-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_3_3_3_3-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_3_3_3-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_3_3_3_3.eprime b/tests/exhaustive/basic/set09/expected/model_3_3_3_3.eprime deleted file mode 100644 index ad1e9ea981..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_3_3_3.eprime +++ /dev/null @@ -1,24 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_ExplicitVarSizeWithMarker_Marker: int(0..4) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithMarker_Marker, - y_ExplicitVarSizeWithMarker_Values] -such that - and([q7 <= x_ExplicitVarSizeWithMarker_Marker /\ q8 <= y_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q7] + 2 = y_ExplicitVarSizeWithMarker_Values[q8] - | q7 : int(1..4), q8 : int(1..4)]), - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..3)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 2 | q2 : int(1..4)]), - 1 <= x_ExplicitVarSizeWithMarker_Marker, - and([q4 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> - y_ExplicitVarSizeWithMarker_Values[q4] < y_ExplicitVarSizeWithMarker_Values[q4 + 1] - | q4 : int(1..3)]), - and([q5 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q5] = 2 | q5 : int(1..4)]), - 1 <= y_ExplicitVarSizeWithMarker_Marker - diff --git a/tests/exhaustive/basic/set09/expected/model_3_3_3_4-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_3_3_3_4-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_3_3_4-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_3_3_3_4-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_3_3_3_4-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_3_3_4-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_3_3_3_4.eprime b/tests/exhaustive/basic/set09/expected/model_3_3_3_4.eprime deleted file mode 100644 index 4fbee84c05..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_3_3_4.eprime +++ /dev/null @@ -1,42 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_ExplicitVarSizeWithMarker_Marker: int(0..4) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithFlags_Flags, - y_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values] -such that - and([q20 <= x_ExplicitVarSizeWithMarker_Marker /\ q21 <= y_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q20] + 2 = y_ExplicitVarSizeWithMarker_Values[q21] - | q20 : int(1..4), q21 : int(1..4)]), - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..3)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 2 | q2 : int(1..4)]), - 1 <= x_ExplicitVarSizeWithMarker_Marker, - and([q4 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> - y_ExplicitVarSizeWithMarker_Values[q4] < y_ExplicitVarSizeWithMarker_Values[q4 + 1] - | q4 : int(1..3)]), - and([q5 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q5] = 2 | q5 : int(1..4)]), - 1 <= y_ExplicitVarSizeWithMarker_Marker, - and([y_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> - y_ExplicitVarSizeWithFlags_Values[q7] < y_ExplicitVarSizeWithFlags_Values[q7 + 1] - | q7 : int(1..3)]), - and([y_ExplicitVarSizeWithFlags_Flags[q8] = false -> y_ExplicitVarSizeWithFlags_Values[q8] = 2 | q8 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q9 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q9] | q9 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q10]) | q10 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q13] -> - or([q15 <= y_ExplicitVarSizeWithMarker_Marker /\ - y_ExplicitVarSizeWithMarker_Values[q15] = y_ExplicitVarSizeWithFlags_Values[q13] - | q15 : int(1..4)]) - | q13 : int(1..4)]), - and([q17 <= y_ExplicitVarSizeWithMarker_Marker -> - or([y_ExplicitVarSizeWithFlags_Flags[q19] /\ - y_ExplicitVarSizeWithFlags_Values[q19] = y_ExplicitVarSizeWithMarker_Values[q17] - | q19 : int(1..4)]) - | q17 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_3_3_4_1-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_3_3_4_1-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_3_4_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_3_3_4_1-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_3_3_4_1-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_3_4_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_3_3_4_1.eprime b/tests/exhaustive/basic/set09/expected/model_3_3_4_1.eprime deleted file mode 100644 index 54b4d0bf42..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_3_4_1.eprime +++ /dev/null @@ -1,51 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_ExplicitVarSizeWithMarker_Marker: int(0..4) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_Occurrence: matrix indexed by [int(2..5)] of bool -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithMarker_Marker, - x_ExplicitVarSizeWithMarker_Values, y_Occurrence, y_ExplicitVarSizeWithMarker_Marker, - y_ExplicitVarSizeWithMarker_Values] -such that - and([q26 <= x_ExplicitVarSizeWithMarker_Marker /\ q27 <= y_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q26] + 2 = y_ExplicitVarSizeWithMarker_Values[q27] - | q26 : int(1..4), q27 : int(1..4)]), - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..3)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 2 | q2 : int(1..4)]), - 1 <= x_ExplicitVarSizeWithMarker_Marker, - and([q4 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> - y_ExplicitVarSizeWithMarker_Values[q4] < y_ExplicitVarSizeWithMarker_Values[q4 + 1] - | q4 : int(1..3)]), - and([q5 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q5] = 2 | q5 : int(1..4)]), - 1 <= y_ExplicitVarSizeWithMarker_Marker, - and([x_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q7] < x_ExplicitVarSizeWithFlags_Values[q7 + 1] - | q7 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q8] = false -> x_ExplicitVarSizeWithFlags_Values[q8] = 2 | q8 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q9 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q9] | q9 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q10]) | q10 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q13] -> - or([q15 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q15] = x_ExplicitVarSizeWithFlags_Values[q13] - | q15 : int(1..4)]) - | q13 : int(1..4)]), - and([q17 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q19] /\ - x_ExplicitVarSizeWithFlags_Values[q19] = x_ExplicitVarSizeWithMarker_Values[q17] - | q19 : int(1..4)]) - | q17 : int(1..4)]), - 1 <= sum([toInt(y_Occurrence[q20]) | q20 : int(2..5)]), - and([y_Occurrence[q21] -> - or([q23 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[q23] = q21 - | q23 : int(1..4)]) - | q21 : int(2..5)]), - and([q25 <= y_ExplicitVarSizeWithMarker_Marker -> y_Occurrence[y_ExplicitVarSizeWithMarker_Values[q25]] - | q25 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_3_3_4_2-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_3_3_4_2-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_3_4_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_3_3_4_2-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_3_3_4_2-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_3_4_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_3_3_4_2.eprime b/tests/exhaustive/basic/set09/expected/model_3_3_4_2.eprime deleted file mode 100644 index 157e866343..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_3_4_2.eprime +++ /dev/null @@ -1,58 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_ExplicitVarSizeWithMarker_Marker: int(0..4) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithMarker_Marker, - x_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithDummy, y_ExplicitVarSizeWithMarker_Marker, - y_ExplicitVarSizeWithMarker_Values] -such that - and([q32 <= x_ExplicitVarSizeWithMarker_Marker /\ q33 <= y_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q32] + 2 = y_ExplicitVarSizeWithMarker_Values[q33] - | q32 : int(1..4), q33 : int(1..4)]), - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..3)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 2 | q2 : int(1..4)]), - 1 <= x_ExplicitVarSizeWithMarker_Marker, - and([q4 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> - y_ExplicitVarSizeWithMarker_Values[q4] < y_ExplicitVarSizeWithMarker_Values[q4 + 1] - | q4 : int(1..3)]), - and([q5 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q5] = 2 | q5 : int(1..4)]), - 1 <= y_ExplicitVarSizeWithMarker_Marker, - and([x_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q7] < x_ExplicitVarSizeWithFlags_Values[q7 + 1] - | q7 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q8] = false -> x_ExplicitVarSizeWithFlags_Values[q8] = 2 | q8 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q9 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q9] | q9 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q10]) | q10 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q13] -> - or([q15 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q15] = x_ExplicitVarSizeWithFlags_Values[q13] - | q15 : int(1..4)]) - | q13 : int(1..4)]), - and([q17 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q19] /\ - x_ExplicitVarSizeWithFlags_Values[q19] = x_ExplicitVarSizeWithMarker_Values[q17] - | q19 : int(1..4)]) - | q17 : int(1..4)]), - and([y_ExplicitVarSizeWithDummy[q20] < y_ExplicitVarSizeWithDummy[q20 + 1] \/ y_ExplicitVarSizeWithDummy[q20] = 6 - | q20 : int(1..3)]), - and([y_ExplicitVarSizeWithDummy[q21] = 6 -> y_ExplicitVarSizeWithDummy[q21 + 1] = 6 | q21 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q22] != 6) | q22 : int(1..4)]), - and([y_ExplicitVarSizeWithDummy[q25] != 6 -> - or([q27 <= y_ExplicitVarSizeWithMarker_Marker /\ - y_ExplicitVarSizeWithMarker_Values[q27] = y_ExplicitVarSizeWithDummy[q25] - | q27 : int(1..4)]) - | q25 : int(1..4)]), - and([q29 <= y_ExplicitVarSizeWithMarker_Marker -> - or([y_ExplicitVarSizeWithDummy[q31] != 6 /\ - y_ExplicitVarSizeWithDummy[q31] = y_ExplicitVarSizeWithMarker_Values[q29] - | q31 : int(1..4)]) - | q29 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_3_3_4_3-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_3_3_4_3-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_3_4_3-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_3_3_4_3-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_3_3_4_3-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_3_4_3-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_3_3_4_3.eprime b/tests/exhaustive/basic/set09/expected/model_3_3_4_3.eprime deleted file mode 100644 index 58d27cf48a..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_3_4_3.eprime +++ /dev/null @@ -1,42 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_ExplicitVarSizeWithMarker_Marker: int(0..4) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithMarker_Marker, - x_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values] -such that - and([q20 <= x_ExplicitVarSizeWithMarker_Marker /\ q21 <= y_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q20] + 2 = y_ExplicitVarSizeWithMarker_Values[q21] - | q20 : int(1..4), q21 : int(1..4)]), - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..3)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 2 | q2 : int(1..4)]), - 1 <= x_ExplicitVarSizeWithMarker_Marker, - and([q4 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> - y_ExplicitVarSizeWithMarker_Values[q4] < y_ExplicitVarSizeWithMarker_Values[q4 + 1] - | q4 : int(1..3)]), - and([q5 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q5] = 2 | q5 : int(1..4)]), - 1 <= y_ExplicitVarSizeWithMarker_Marker, - and([x_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q7] < x_ExplicitVarSizeWithFlags_Values[q7 + 1] - | q7 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q8] = false -> x_ExplicitVarSizeWithFlags_Values[q8] = 2 | q8 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q9 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q9] | q9 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q10]) | q10 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q13] -> - or([q15 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q15] = x_ExplicitVarSizeWithFlags_Values[q13] - | q15 : int(1..4)]) - | q13 : int(1..4)]), - and([q17 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q19] /\ - x_ExplicitVarSizeWithFlags_Values[q19] = x_ExplicitVarSizeWithMarker_Values[q17] - | q19 : int(1..4)]) - | q17 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_3_3_4_4-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_3_3_4_4-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_3_4_4-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_3_3_4_4-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_3_3_4_4-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_3_4_4-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_3_3_4_4.eprime b/tests/exhaustive/basic/set09/expected/model_3_3_4_4.eprime deleted file mode 100644 index 8eeab52a56..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_3_4_4.eprime +++ /dev/null @@ -1,62 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_ExplicitVarSizeWithMarker_Marker: int(0..4) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithMarker_Marker, - x_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values, - y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values] -such that - and([q33 <= x_ExplicitVarSizeWithMarker_Marker /\ q34 <= y_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q33] + 2 = y_ExplicitVarSizeWithMarker_Values[q34] - | q33 : int(1..4), q34 : int(1..4)]), - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..3)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 2 | q2 : int(1..4)]), - 1 <= x_ExplicitVarSizeWithMarker_Marker, - and([q4 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> - y_ExplicitVarSizeWithMarker_Values[q4] < y_ExplicitVarSizeWithMarker_Values[q4 + 1] - | q4 : int(1..3)]), - and([q5 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q5] = 2 | q5 : int(1..4)]), - 1 <= y_ExplicitVarSizeWithMarker_Marker, - and([x_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q7] < x_ExplicitVarSizeWithFlags_Values[q7 + 1] - | q7 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q8] = false -> x_ExplicitVarSizeWithFlags_Values[q8] = 2 | q8 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q9 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q9] | q9 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q10]) | q10 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q13] -> - or([q15 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q15] = x_ExplicitVarSizeWithFlags_Values[q13] - | q15 : int(1..4)]) - | q13 : int(1..4)]), - and([q17 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q19] /\ - x_ExplicitVarSizeWithFlags_Values[q19] = x_ExplicitVarSizeWithMarker_Values[q17] - | q19 : int(1..4)]) - | q17 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q20 + 1] -> - y_ExplicitVarSizeWithFlags_Values[q20] < y_ExplicitVarSizeWithFlags_Values[q20 + 1] - | q20 : int(1..3)]), - and([y_ExplicitVarSizeWithFlags_Flags[q21] = false -> y_ExplicitVarSizeWithFlags_Values[q21] = 2 - | q21 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q22 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q22] | q22 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q23]) | q23 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q26] -> - or([q28 <= y_ExplicitVarSizeWithMarker_Marker /\ - y_ExplicitVarSizeWithMarker_Values[q28] = y_ExplicitVarSizeWithFlags_Values[q26] - | q28 : int(1..4)]) - | q26 : int(1..4)]), - and([q30 <= y_ExplicitVarSizeWithMarker_Marker -> - or([y_ExplicitVarSizeWithFlags_Flags[q32] /\ - y_ExplicitVarSizeWithFlags_Values[q32] = y_ExplicitVarSizeWithMarker_Values[q30] - | q32 : int(1..4)]) - | q30 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_3_4_1_1-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_3_4_1_1-solution000001.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_4_1_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_3_4_1_1-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_3_4_1_1-solution000002.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_4_1_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_3_4_1_1.eprime b/tests/exhaustive/basic/set09/expected/model_3_4_1_1.eprime deleted file mode 100644 index 842f840473..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_4_1_1.eprime +++ /dev/null @@ -1,40 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -find x_Occurrence: matrix indexed by [int(2..5)] of bool -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_Occurrence: matrix indexed by [int(2..5)] of bool -branching on - [x_Occurrence, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, y_Occurrence, - y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values] -such that - and([q16 <= x_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithFlags_Flags[q17] -> - x_ExplicitVarSizeWithMarker_Values[q16] + 2 = y_ExplicitVarSizeWithFlags_Values[q17] - | q16 : int(1..4), q17 : int(1..4)]), - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..3)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 2 | q2 : int(1..4)]), - 1 <= x_ExplicitVarSizeWithMarker_Marker, - and([y_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> - y_ExplicitVarSizeWithFlags_Values[q4] < y_ExplicitVarSizeWithFlags_Values[q4 + 1] - | q4 : int(1..3)]), - and([y_ExplicitVarSizeWithFlags_Flags[q5] = false -> y_ExplicitVarSizeWithFlags_Values[q5] = 2 | q5 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q6] | q6 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q7]) | q7 : int(1..4)]), - 1 <= sum([toInt(x_Occurrence[q9]) | q9 : int(2..5)]), - and([x_Occurrence[q18] -> - or([q20 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q20] = q18 - | q20 : int(1..4)]) - | q18 : int(2..5)]), - and([q22 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q22]] - | q22 : int(1..4)]), - 1 <= sum([toInt(y_Occurrence[q10]) | q10 : int(2..5)]), - and([y_Occurrence[q11] -> - or([y_ExplicitVarSizeWithFlags_Flags[q13] /\ y_ExplicitVarSizeWithFlags_Values[q13] = q11 | q13 : int(1..4)]) - | q11 : int(2..5)]), - and([y_ExplicitVarSizeWithFlags_Flags[q15] -> y_Occurrence[y_ExplicitVarSizeWithFlags_Values[q15]] - | q15 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_3_4_1_2-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_3_4_1_2-solution000001.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_4_1_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_3_4_1_2-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_3_4_1_2-solution000002.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_4_1_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_3_4_1_2.eprime b/tests/exhaustive/basic/set09/expected/model_3_4_1_2.eprime deleted file mode 100644 index 5d8608bb70..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_4_1_2.eprime +++ /dev/null @@ -1,48 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -find x_Occurrence: matrix indexed by [int(2..5)] of bool -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -branching on - [x_Occurrence, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithDummy, - y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values] -such that - and([q27 <= x_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithFlags_Flags[q28] -> - x_ExplicitVarSizeWithMarker_Values[q27] + 2 = y_ExplicitVarSizeWithFlags_Values[q28] - | q27 : int(1..4), q28 : int(1..4)]), - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..3)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 2 | q2 : int(1..4)]), - 1 <= x_ExplicitVarSizeWithMarker_Marker, - and([y_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> - y_ExplicitVarSizeWithFlags_Values[q4] < y_ExplicitVarSizeWithFlags_Values[q4 + 1] - | q4 : int(1..3)]), - and([y_ExplicitVarSizeWithFlags_Flags[q5] = false -> y_ExplicitVarSizeWithFlags_Values[q5] = 2 | q5 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q6] | q6 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q7]) | q7 : int(1..4)]), - 1 <= sum([toInt(x_Occurrence[q9]) | q9 : int(2..5)]), - and([x_Occurrence[q22] -> - or([q24 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q24] = q22 - | q24 : int(1..4)]) - | q22 : int(2..5)]), - and([q26 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q26]] - | q26 : int(1..4)]), - and([y_ExplicitVarSizeWithDummy[q10] < y_ExplicitVarSizeWithDummy[q10 + 1] \/ y_ExplicitVarSizeWithDummy[q10] = 6 - | q10 : int(1..3)]), - and([y_ExplicitVarSizeWithDummy[q11] = 6 -> y_ExplicitVarSizeWithDummy[q11 + 1] = 6 | q11 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q12] != 6) | q12 : int(1..4)]), - and([y_ExplicitVarSizeWithDummy[q15] != 6 -> - or([y_ExplicitVarSizeWithFlags_Flags[q17] /\ - y_ExplicitVarSizeWithFlags_Values[q17] = y_ExplicitVarSizeWithDummy[q15] - | q17 : int(1..4)]) - | q15 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q19] -> - or([y_ExplicitVarSizeWithDummy[q21] != 6 /\ - y_ExplicitVarSizeWithDummy[q21] = y_ExplicitVarSizeWithFlags_Values[q19] - | q21 : int(1..4)]) - | q19 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_3_4_1_3-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_3_4_1_3-solution000001.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_4_1_3-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_3_4_1_3-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_3_4_1_3-solution000002.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_4_1_3-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_3_4_1_3.eprime b/tests/exhaustive/basic/set09/expected/model_3_4_1_3.eprime deleted file mode 100644 index 0920bc13d0..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_4_1_3.eprime +++ /dev/null @@ -1,51 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -find x_Occurrence: matrix indexed by [int(2..5)] of bool -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_ExplicitVarSizeWithMarker_Marker: int(0..4) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -branching on - [x_Occurrence, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, - y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithFlags_Flags, - y_ExplicitVarSizeWithFlags_Values] -such that - and([q26 <= x_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithFlags_Flags[q27] -> - x_ExplicitVarSizeWithMarker_Values[q26] + 2 = y_ExplicitVarSizeWithFlags_Values[q27] - | q26 : int(1..4), q27 : int(1..4)]), - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..3)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 2 | q2 : int(1..4)]), - 1 <= x_ExplicitVarSizeWithMarker_Marker, - and([y_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> - y_ExplicitVarSizeWithFlags_Values[q4] < y_ExplicitVarSizeWithFlags_Values[q4 + 1] - | q4 : int(1..3)]), - and([y_ExplicitVarSizeWithFlags_Flags[q5] = false -> y_ExplicitVarSizeWithFlags_Values[q5] = 2 | q5 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q6] | q6 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q7]) | q7 : int(1..4)]), - 1 <= sum([toInt(x_Occurrence[q9]) | q9 : int(2..5)]), - and([x_Occurrence[q21] -> - or([q23 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q23] = q21 - | q23 : int(1..4)]) - | q21 : int(2..5)]), - and([q25 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q25]] - | q25 : int(1..4)]), - and([q10 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> - y_ExplicitVarSizeWithMarker_Values[q10] < y_ExplicitVarSizeWithMarker_Values[q10 + 1] - | q10 : int(1..3)]), - and([q11 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q11] = 2 | q11 : int(1..4)]), - 1 <= y_ExplicitVarSizeWithMarker_Marker, - and([q14 <= y_ExplicitVarSizeWithMarker_Marker -> - or([y_ExplicitVarSizeWithFlags_Flags[q16] /\ - y_ExplicitVarSizeWithFlags_Values[q16] = y_ExplicitVarSizeWithMarker_Values[q14] - | q16 : int(1..4)]) - | q14 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q18] -> - or([q20 <= y_ExplicitVarSizeWithMarker_Marker /\ - y_ExplicitVarSizeWithMarker_Values[q20] = y_ExplicitVarSizeWithFlags_Values[q18] - | q20 : int(1..4)]) - | q18 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_3_4_1_4-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_3_4_1_4-solution000001.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_4_1_4-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_3_4_1_4-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_3_4_1_4-solution000002.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_4_1_4-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_3_4_1_4.eprime b/tests/exhaustive/basic/set09/expected/model_3_4_1_4.eprime deleted file mode 100644 index 7ce0db61d8..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_4_1_4.eprime +++ /dev/null @@ -1,33 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -find x_Occurrence: matrix indexed by [int(2..5)] of bool -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -branching on - [x_Occurrence, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, - y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values] -such that - and([q15 <= x_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithFlags_Flags[q16] -> - x_ExplicitVarSizeWithMarker_Values[q15] + 2 = y_ExplicitVarSizeWithFlags_Values[q16] - | q15 : int(1..4), q16 : int(1..4)]), - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..3)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 2 | q2 : int(1..4)]), - 1 <= x_ExplicitVarSizeWithMarker_Marker, - and([y_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> - y_ExplicitVarSizeWithFlags_Values[q4] < y_ExplicitVarSizeWithFlags_Values[q4 + 1] - | q4 : int(1..3)]), - and([y_ExplicitVarSizeWithFlags_Flags[q5] = false -> y_ExplicitVarSizeWithFlags_Values[q5] = 2 | q5 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q6] | q6 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q7]) | q7 : int(1..4)]), - 1 <= sum([toInt(x_Occurrence[q9]) | q9 : int(2..5)]), - and([x_Occurrence[q10] -> - or([q12 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q12] = q10 - | q12 : int(1..4)]) - | q10 : int(2..5)]), - and([q14 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q14]] - | q14 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_3_4_2_1-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_3_4_2_1-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_4_2_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_3_4_2_1-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_3_4_2_1-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_4_2_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_3_4_2_1.eprime b/tests/exhaustive/basic/set09/expected/model_3_4_2_1.eprime deleted file mode 100644 index 61f44c9622..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_4_2_1.eprime +++ /dev/null @@ -1,47 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_Occurrence: matrix indexed by [int(2..5)] of bool -branching on - [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, y_Occurrence, - y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values] -such that - and([q27 <= x_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithFlags_Flags[q28] -> - x_ExplicitVarSizeWithMarker_Values[q27] + 2 = y_ExplicitVarSizeWithFlags_Values[q28] - | q27 : int(1..4), q28 : int(1..4)]), - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..3)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 2 | q2 : int(1..4)]), - 1 <= x_ExplicitVarSizeWithMarker_Marker, - and([y_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> - y_ExplicitVarSizeWithFlags_Values[q4] < y_ExplicitVarSizeWithFlags_Values[q4 + 1] - | q4 : int(1..3)]), - and([y_ExplicitVarSizeWithFlags_Flags[q5] = false -> y_ExplicitVarSizeWithFlags_Values[q5] = 2 | q5 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q6] | q6 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q7]) | q7 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q9] < x_ExplicitVarSizeWithDummy[q9 + 1] \/ x_ExplicitVarSizeWithDummy[q9] = 6 - | q9 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q10] = 6 -> x_ExplicitVarSizeWithDummy[q10 + 1] = 6 | q10 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q11] != 6) | q11 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q14] != 6 -> - or([q16 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q16] = x_ExplicitVarSizeWithDummy[q14] - | q16 : int(1..4)]) - | q14 : int(1..4)]), - and([q18 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q20] != 6 /\ - x_ExplicitVarSizeWithDummy[q20] = x_ExplicitVarSizeWithMarker_Values[q18] - | q20 : int(1..4)]) - | q18 : int(1..4)]), - 1 <= sum([toInt(y_Occurrence[q21]) | q21 : int(2..5)]), - and([y_Occurrence[q22] -> - or([y_ExplicitVarSizeWithFlags_Flags[q24] /\ y_ExplicitVarSizeWithFlags_Values[q24] = q22 | q24 : int(1..4)]) - | q22 : int(2..5)]), - and([y_ExplicitVarSizeWithFlags_Flags[q26] -> y_Occurrence[y_ExplicitVarSizeWithFlags_Values[q26]] - | q26 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_3_4_2_2-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_3_4_2_2-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_4_2_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_3_4_2_2-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_3_4_2_2-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_4_2_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_3_4_2_2.eprime b/tests/exhaustive/basic/set09/expected/model_3_4_2_2.eprime deleted file mode 100644 index 0fed7c779e..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_4_2_2.eprime +++ /dev/null @@ -1,55 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -branching on - [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, - y_ExplicitVarSizeWithDummy, y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values] -such that - and([q33 <= x_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithFlags_Flags[q34] -> - x_ExplicitVarSizeWithMarker_Values[q33] + 2 = y_ExplicitVarSizeWithFlags_Values[q34] - | q33 : int(1..4), q34 : int(1..4)]), - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..3)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 2 | q2 : int(1..4)]), - 1 <= x_ExplicitVarSizeWithMarker_Marker, - and([y_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> - y_ExplicitVarSizeWithFlags_Values[q4] < y_ExplicitVarSizeWithFlags_Values[q4 + 1] - | q4 : int(1..3)]), - and([y_ExplicitVarSizeWithFlags_Flags[q5] = false -> y_ExplicitVarSizeWithFlags_Values[q5] = 2 | q5 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q6] | q6 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q7]) | q7 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q9] < x_ExplicitVarSizeWithDummy[q9 + 1] \/ x_ExplicitVarSizeWithDummy[q9] = 6 - | q9 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q10] = 6 -> x_ExplicitVarSizeWithDummy[q10 + 1] = 6 | q10 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q11] != 6) | q11 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q14] != 6 -> - or([q16 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q16] = x_ExplicitVarSizeWithDummy[q14] - | q16 : int(1..4)]) - | q14 : int(1..4)]), - and([q18 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q20] != 6 /\ - x_ExplicitVarSizeWithDummy[q20] = x_ExplicitVarSizeWithMarker_Values[q18] - | q20 : int(1..4)]) - | q18 : int(1..4)]), - and([y_ExplicitVarSizeWithDummy[q21] < y_ExplicitVarSizeWithDummy[q21 + 1] \/ y_ExplicitVarSizeWithDummy[q21] = 6 - | q21 : int(1..3)]), - and([y_ExplicitVarSizeWithDummy[q22] = 6 -> y_ExplicitVarSizeWithDummy[q22 + 1] = 6 | q22 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q23] != 6) | q23 : int(1..4)]), - and([y_ExplicitVarSizeWithDummy[q26] != 6 -> - or([y_ExplicitVarSizeWithFlags_Flags[q28] /\ - y_ExplicitVarSizeWithFlags_Values[q28] = y_ExplicitVarSizeWithDummy[q26] - | q28 : int(1..4)]) - | q26 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q30] -> - or([y_ExplicitVarSizeWithDummy[q32] != 6 /\ - y_ExplicitVarSizeWithDummy[q32] = y_ExplicitVarSizeWithFlags_Values[q30] - | q32 : int(1..4)]) - | q30 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_3_4_2_3-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_3_4_2_3-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_4_2_3-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_3_4_2_3-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_3_4_2_3-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_4_2_3-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_3_4_2_3.eprime b/tests/exhaustive/basic/set09/expected/model_3_4_2_3.eprime deleted file mode 100644 index 0a78494f0e..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_4_2_3.eprime +++ /dev/null @@ -1,58 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_ExplicitVarSizeWithMarker_Marker: int(0..4) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -branching on - [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, - y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithFlags_Flags, - y_ExplicitVarSizeWithFlags_Values] -such that - and([q32 <= x_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithFlags_Flags[q33] -> - x_ExplicitVarSizeWithMarker_Values[q32] + 2 = y_ExplicitVarSizeWithFlags_Values[q33] - | q32 : int(1..4), q33 : int(1..4)]), - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..3)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 2 | q2 : int(1..4)]), - 1 <= x_ExplicitVarSizeWithMarker_Marker, - and([y_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> - y_ExplicitVarSizeWithFlags_Values[q4] < y_ExplicitVarSizeWithFlags_Values[q4 + 1] - | q4 : int(1..3)]), - and([y_ExplicitVarSizeWithFlags_Flags[q5] = false -> y_ExplicitVarSizeWithFlags_Values[q5] = 2 | q5 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q6] | q6 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q7]) | q7 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q9] < x_ExplicitVarSizeWithDummy[q9 + 1] \/ x_ExplicitVarSizeWithDummy[q9] = 6 - | q9 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q10] = 6 -> x_ExplicitVarSizeWithDummy[q10 + 1] = 6 | q10 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q11] != 6) | q11 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q14] != 6 -> - or([q16 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q16] = x_ExplicitVarSizeWithDummy[q14] - | q16 : int(1..4)]) - | q14 : int(1..4)]), - and([q18 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q20] != 6 /\ - x_ExplicitVarSizeWithDummy[q20] = x_ExplicitVarSizeWithMarker_Values[q18] - | q20 : int(1..4)]) - | q18 : int(1..4)]), - and([q21 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> - y_ExplicitVarSizeWithMarker_Values[q21] < y_ExplicitVarSizeWithMarker_Values[q21 + 1] - | q21 : int(1..3)]), - and([q22 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q22] = 2 | q22 : int(1..4)]), - 1 <= y_ExplicitVarSizeWithMarker_Marker, - and([q25 <= y_ExplicitVarSizeWithMarker_Marker -> - or([y_ExplicitVarSizeWithFlags_Flags[q27] /\ - y_ExplicitVarSizeWithFlags_Values[q27] = y_ExplicitVarSizeWithMarker_Values[q25] - | q27 : int(1..4)]) - | q25 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q29] -> - or([q31 <= y_ExplicitVarSizeWithMarker_Marker /\ - y_ExplicitVarSizeWithMarker_Values[q31] = y_ExplicitVarSizeWithFlags_Values[q29] - | q31 : int(1..4)]) - | q29 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_3_4_2_4-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_3_4_2_4-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_4_2_4-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_3_4_2_4-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_3_4_2_4-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_4_2_4-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_3_4_2_4.eprime b/tests/exhaustive/basic/set09/expected/model_3_4_2_4.eprime deleted file mode 100644 index e10ef03824..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_4_2_4.eprime +++ /dev/null @@ -1,40 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -branching on - [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, - y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values] -such that - and([q21 <= x_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithFlags_Flags[q22] -> - x_ExplicitVarSizeWithMarker_Values[q21] + 2 = y_ExplicitVarSizeWithFlags_Values[q22] - | q21 : int(1..4), q22 : int(1..4)]), - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..3)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 2 | q2 : int(1..4)]), - 1 <= x_ExplicitVarSizeWithMarker_Marker, - and([y_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> - y_ExplicitVarSizeWithFlags_Values[q4] < y_ExplicitVarSizeWithFlags_Values[q4 + 1] - | q4 : int(1..3)]), - and([y_ExplicitVarSizeWithFlags_Flags[q5] = false -> y_ExplicitVarSizeWithFlags_Values[q5] = 2 | q5 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q6] | q6 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q7]) | q7 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q9] < x_ExplicitVarSizeWithDummy[q9 + 1] \/ x_ExplicitVarSizeWithDummy[q9] = 6 - | q9 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q10] = 6 -> x_ExplicitVarSizeWithDummy[q10 + 1] = 6 | q10 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q11] != 6) | q11 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q14] != 6 -> - or([q16 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q16] = x_ExplicitVarSizeWithDummy[q14] - | q16 : int(1..4)]) - | q14 : int(1..4)]), - and([q18 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q20] != 6 /\ - x_ExplicitVarSizeWithDummy[q20] = x_ExplicitVarSizeWithMarker_Values[q18] - | q20 : int(1..4)]) - | q18 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_3_4_3_1-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_3_4_3_1-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_4_3_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_3_4_3_1-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_3_4_3_1-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_4_3_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_3_4_3_1.eprime b/tests/exhaustive/basic/set09/expected/model_3_4_3_1.eprime deleted file mode 100644 index d7781435b7..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_4_3_1.eprime +++ /dev/null @@ -1,32 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_Occurrence: matrix indexed by [int(2..5)] of bool -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, y_Occurrence, - y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values] -such that - and([q15 <= x_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithFlags_Flags[q16] -> - x_ExplicitVarSizeWithMarker_Values[q15] + 2 = y_ExplicitVarSizeWithFlags_Values[q16] - | q15 : int(1..4), q16 : int(1..4)]), - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..3)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 2 | q2 : int(1..4)]), - 1 <= x_ExplicitVarSizeWithMarker_Marker, - and([y_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> - y_ExplicitVarSizeWithFlags_Values[q4] < y_ExplicitVarSizeWithFlags_Values[q4 + 1] - | q4 : int(1..3)]), - and([y_ExplicitVarSizeWithFlags_Flags[q5] = false -> y_ExplicitVarSizeWithFlags_Values[q5] = 2 | q5 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q6] | q6 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q7]) | q7 : int(1..4)]), - 1 <= sum([toInt(y_Occurrence[q9]) | q9 : int(2..5)]), - and([y_Occurrence[q10] -> - or([y_ExplicitVarSizeWithFlags_Flags[q12] /\ y_ExplicitVarSizeWithFlags_Values[q12] = q10 | q12 : int(1..4)]) - | q10 : int(2..5)]), - and([y_ExplicitVarSizeWithFlags_Flags[q14] -> y_Occurrence[y_ExplicitVarSizeWithFlags_Values[q14]] - | q14 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_3_4_3_2-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_3_4_3_2-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_4_3_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_3_4_3_2-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_3_4_3_2-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_4_3_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_3_4_3_2.eprime b/tests/exhaustive/basic/set09/expected/model_3_4_3_2.eprime deleted file mode 100644 index 2ce2ee5eab..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_4_3_2.eprime +++ /dev/null @@ -1,40 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithDummy, - y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values] -such that - and([q21 <= x_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithFlags_Flags[q22] -> - x_ExplicitVarSizeWithMarker_Values[q21] + 2 = y_ExplicitVarSizeWithFlags_Values[q22] - | q21 : int(1..4), q22 : int(1..4)]), - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..3)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 2 | q2 : int(1..4)]), - 1 <= x_ExplicitVarSizeWithMarker_Marker, - and([y_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> - y_ExplicitVarSizeWithFlags_Values[q4] < y_ExplicitVarSizeWithFlags_Values[q4 + 1] - | q4 : int(1..3)]), - and([y_ExplicitVarSizeWithFlags_Flags[q5] = false -> y_ExplicitVarSizeWithFlags_Values[q5] = 2 | q5 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q6] | q6 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q7]) | q7 : int(1..4)]), - and([y_ExplicitVarSizeWithDummy[q9] < y_ExplicitVarSizeWithDummy[q9 + 1] \/ y_ExplicitVarSizeWithDummy[q9] = 6 - | q9 : int(1..3)]), - and([y_ExplicitVarSizeWithDummy[q10] = 6 -> y_ExplicitVarSizeWithDummy[q10 + 1] = 6 | q10 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q11] != 6) | q11 : int(1..4)]), - and([y_ExplicitVarSizeWithDummy[q14] != 6 -> - or([y_ExplicitVarSizeWithFlags_Flags[q16] /\ - y_ExplicitVarSizeWithFlags_Values[q16] = y_ExplicitVarSizeWithDummy[q14] - | q16 : int(1..4)]) - | q14 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q18] -> - or([y_ExplicitVarSizeWithDummy[q20] != 6 /\ - y_ExplicitVarSizeWithDummy[q20] = y_ExplicitVarSizeWithFlags_Values[q18] - | q20 : int(1..4)]) - | q18 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_3_4_3_3-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_3_4_3_3-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_4_3_3-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_3_4_3_3-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_3_4_3_3-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_4_3_3-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_3_4_3_3.eprime b/tests/exhaustive/basic/set09/expected/model_3_4_3_3.eprime deleted file mode 100644 index c121faa238..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_4_3_3.eprime +++ /dev/null @@ -1,42 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_ExplicitVarSizeWithMarker_Marker: int(0..4) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithMarker_Marker, - y_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values] -such that - and([q20 <= x_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithFlags_Flags[q21] -> - x_ExplicitVarSizeWithMarker_Values[q20] + 2 = y_ExplicitVarSizeWithFlags_Values[q21] - | q20 : int(1..4), q21 : int(1..4)]), - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..3)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 2 | q2 : int(1..4)]), - 1 <= x_ExplicitVarSizeWithMarker_Marker, - and([y_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> - y_ExplicitVarSizeWithFlags_Values[q4] < y_ExplicitVarSizeWithFlags_Values[q4 + 1] - | q4 : int(1..3)]), - and([y_ExplicitVarSizeWithFlags_Flags[q5] = false -> y_ExplicitVarSizeWithFlags_Values[q5] = 2 | q5 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q6] | q6 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q7]) | q7 : int(1..4)]), - and([q9 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> - y_ExplicitVarSizeWithMarker_Values[q9] < y_ExplicitVarSizeWithMarker_Values[q9 + 1] - | q9 : int(1..3)]), - and([q10 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q10] = 2 | q10 : int(1..4)]), - 1 <= y_ExplicitVarSizeWithMarker_Marker, - and([q13 <= y_ExplicitVarSizeWithMarker_Marker -> - or([y_ExplicitVarSizeWithFlags_Flags[q15] /\ - y_ExplicitVarSizeWithFlags_Values[q15] = y_ExplicitVarSizeWithMarker_Values[q13] - | q15 : int(1..4)]) - | q13 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q17] -> - or([q19 <= y_ExplicitVarSizeWithMarker_Marker /\ - y_ExplicitVarSizeWithMarker_Values[q19] = y_ExplicitVarSizeWithFlags_Values[q17] - | q19 : int(1..4)]) - | q17 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_3_4_3_4-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_3_4_3_4-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_4_3_4-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_3_4_3_4-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_3_4_3_4-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_4_3_4-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_3_4_3_4.eprime b/tests/exhaustive/basic/set09/expected/model_3_4_3_4.eprime deleted file mode 100644 index ca62bca40e..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_4_3_4.eprime +++ /dev/null @@ -1,25 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithFlags_Flags, - y_ExplicitVarSizeWithFlags_Values] -such that - and([q9 <= x_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithFlags_Flags[q10] -> - x_ExplicitVarSizeWithMarker_Values[q9] + 2 = y_ExplicitVarSizeWithFlags_Values[q10] - | q9 : int(1..4), q10 : int(1..4)]), - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..3)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 2 | q2 : int(1..4)]), - 1 <= x_ExplicitVarSizeWithMarker_Marker, - and([y_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> - y_ExplicitVarSizeWithFlags_Values[q4] < y_ExplicitVarSizeWithFlags_Values[q4 + 1] - | q4 : int(1..3)]), - and([y_ExplicitVarSizeWithFlags_Flags[q5] = false -> y_ExplicitVarSizeWithFlags_Values[q5] = 2 | q5 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q6] | q6 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q7]) | q7 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_3_4_4_1-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_3_4_4_1-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_4_4_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_3_4_4_1-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_3_4_4_1-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_4_4_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_3_4_4_1.eprime b/tests/exhaustive/basic/set09/expected/model_3_4_4_1.eprime deleted file mode 100644 index 196b11abfb..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_4_4_1.eprime +++ /dev/null @@ -1,52 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_Occurrence: matrix indexed by [int(2..5)] of bool -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithMarker_Marker, - x_ExplicitVarSizeWithMarker_Values, y_Occurrence, y_ExplicitVarSizeWithFlags_Flags, - y_ExplicitVarSizeWithFlags_Values] -such that - and([q28 <= x_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithFlags_Flags[q29] -> - x_ExplicitVarSizeWithMarker_Values[q28] + 2 = y_ExplicitVarSizeWithFlags_Values[q29] - | q28 : int(1..4), q29 : int(1..4)]), - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..3)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 2 | q2 : int(1..4)]), - 1 <= x_ExplicitVarSizeWithMarker_Marker, - and([y_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> - y_ExplicitVarSizeWithFlags_Values[q4] < y_ExplicitVarSizeWithFlags_Values[q4 + 1] - | q4 : int(1..3)]), - and([y_ExplicitVarSizeWithFlags_Flags[q5] = false -> y_ExplicitVarSizeWithFlags_Values[q5] = 2 | q5 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q6] | q6 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q7]) | q7 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q9 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q9] < x_ExplicitVarSizeWithFlags_Values[q9 + 1] - | q9 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q10] = false -> x_ExplicitVarSizeWithFlags_Values[q10] = 2 - | q10 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q11 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q11] | q11 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q12]) | q12 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q15] -> - or([q17 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q17] = x_ExplicitVarSizeWithFlags_Values[q15] - | q17 : int(1..4)]) - | q15 : int(1..4)]), - and([q19 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q21] /\ - x_ExplicitVarSizeWithFlags_Values[q21] = x_ExplicitVarSizeWithMarker_Values[q19] - | q21 : int(1..4)]) - | q19 : int(1..4)]), - 1 <= sum([toInt(y_Occurrence[q22]) | q22 : int(2..5)]), - and([y_Occurrence[q23] -> - or([y_ExplicitVarSizeWithFlags_Flags[q25] /\ y_ExplicitVarSizeWithFlags_Values[q25] = q23 | q25 : int(1..4)]) - | q23 : int(2..5)]), - and([y_ExplicitVarSizeWithFlags_Flags[q27] -> y_Occurrence[y_ExplicitVarSizeWithFlags_Values[q27]] - | q27 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_3_4_4_2-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_3_4_4_2-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_4_4_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_3_4_4_2-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_3_4_4_2-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_4_4_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_3_4_4_2.eprime b/tests/exhaustive/basic/set09/expected/model_3_4_4_2.eprime deleted file mode 100644 index fe5ba424a2..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_4_4_2.eprime +++ /dev/null @@ -1,60 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithMarker_Marker, - x_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithDummy, y_ExplicitVarSizeWithFlags_Flags, - y_ExplicitVarSizeWithFlags_Values] -such that - and([q34 <= x_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithFlags_Flags[q35] -> - x_ExplicitVarSizeWithMarker_Values[q34] + 2 = y_ExplicitVarSizeWithFlags_Values[q35] - | q34 : int(1..4), q35 : int(1..4)]), - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..3)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 2 | q2 : int(1..4)]), - 1 <= x_ExplicitVarSizeWithMarker_Marker, - and([y_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> - y_ExplicitVarSizeWithFlags_Values[q4] < y_ExplicitVarSizeWithFlags_Values[q4 + 1] - | q4 : int(1..3)]), - and([y_ExplicitVarSizeWithFlags_Flags[q5] = false -> y_ExplicitVarSizeWithFlags_Values[q5] = 2 | q5 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q6] | q6 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q7]) | q7 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q9 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q9] < x_ExplicitVarSizeWithFlags_Values[q9 + 1] - | q9 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q10] = false -> x_ExplicitVarSizeWithFlags_Values[q10] = 2 - | q10 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q11 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q11] | q11 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q12]) | q12 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q15] -> - or([q17 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q17] = x_ExplicitVarSizeWithFlags_Values[q15] - | q17 : int(1..4)]) - | q15 : int(1..4)]), - and([q19 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q21] /\ - x_ExplicitVarSizeWithFlags_Values[q21] = x_ExplicitVarSizeWithMarker_Values[q19] - | q21 : int(1..4)]) - | q19 : int(1..4)]), - and([y_ExplicitVarSizeWithDummy[q22] < y_ExplicitVarSizeWithDummy[q22 + 1] \/ y_ExplicitVarSizeWithDummy[q22] = 6 - | q22 : int(1..3)]), - and([y_ExplicitVarSizeWithDummy[q23] = 6 -> y_ExplicitVarSizeWithDummy[q23 + 1] = 6 | q23 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q24] != 6) | q24 : int(1..4)]), - and([y_ExplicitVarSizeWithDummy[q27] != 6 -> - or([y_ExplicitVarSizeWithFlags_Flags[q29] /\ - y_ExplicitVarSizeWithFlags_Values[q29] = y_ExplicitVarSizeWithDummy[q27] - | q29 : int(1..4)]) - | q27 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q31] -> - or([y_ExplicitVarSizeWithDummy[q33] != 6 /\ - y_ExplicitVarSizeWithDummy[q33] = y_ExplicitVarSizeWithFlags_Values[q31] - | q33 : int(1..4)]) - | q31 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_3_4_4_3-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_3_4_4_3-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_4_4_3-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_3_4_4_3-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_3_4_4_3-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_4_4_3-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_3_4_4_3.eprime b/tests/exhaustive/basic/set09/expected/model_3_4_4_3.eprime deleted file mode 100644 index 6761996efd..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_4_4_3.eprime +++ /dev/null @@ -1,62 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_ExplicitVarSizeWithMarker_Marker: int(0..4) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithMarker_Marker, - x_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values, - y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values] -such that - and([q33 <= x_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithFlags_Flags[q34] -> - x_ExplicitVarSizeWithMarker_Values[q33] + 2 = y_ExplicitVarSizeWithFlags_Values[q34] - | q33 : int(1..4), q34 : int(1..4)]), - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..3)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 2 | q2 : int(1..4)]), - 1 <= x_ExplicitVarSizeWithMarker_Marker, - and([y_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> - y_ExplicitVarSizeWithFlags_Values[q4] < y_ExplicitVarSizeWithFlags_Values[q4 + 1] - | q4 : int(1..3)]), - and([y_ExplicitVarSizeWithFlags_Flags[q5] = false -> y_ExplicitVarSizeWithFlags_Values[q5] = 2 | q5 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q6] | q6 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q7]) | q7 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q9 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q9] < x_ExplicitVarSizeWithFlags_Values[q9 + 1] - | q9 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q10] = false -> x_ExplicitVarSizeWithFlags_Values[q10] = 2 - | q10 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q11 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q11] | q11 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q12]) | q12 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q15] -> - or([q17 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q17] = x_ExplicitVarSizeWithFlags_Values[q15] - | q17 : int(1..4)]) - | q15 : int(1..4)]), - and([q19 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q21] /\ - x_ExplicitVarSizeWithFlags_Values[q21] = x_ExplicitVarSizeWithMarker_Values[q19] - | q21 : int(1..4)]) - | q19 : int(1..4)]), - and([q22 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> - y_ExplicitVarSizeWithMarker_Values[q22] < y_ExplicitVarSizeWithMarker_Values[q22 + 1] - | q22 : int(1..3)]), - and([q23 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q23] = 2 | q23 : int(1..4)]), - 1 <= y_ExplicitVarSizeWithMarker_Marker, - and([q26 <= y_ExplicitVarSizeWithMarker_Marker -> - or([y_ExplicitVarSizeWithFlags_Flags[q28] /\ - y_ExplicitVarSizeWithFlags_Values[q28] = y_ExplicitVarSizeWithMarker_Values[q26] - | q28 : int(1..4)]) - | q26 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q30] -> - or([q32 <= y_ExplicitVarSizeWithMarker_Marker /\ - y_ExplicitVarSizeWithMarker_Values[q32] = y_ExplicitVarSizeWithFlags_Values[q30] - | q32 : int(1..4)]) - | q30 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_3_4_4_4-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_3_4_4_4-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_4_4_4-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_3_4_4_4-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_3_4_4_4-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_4_4_4-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_3_4_4_4.eprime b/tests/exhaustive/basic/set09/expected/model_3_4_4_4.eprime deleted file mode 100644 index 647b4c3d5f..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_3_4_4_4.eprime +++ /dev/null @@ -1,44 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithMarker_Marker, - x_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values] -such that - and([q22 <= x_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithFlags_Flags[q23] -> - x_ExplicitVarSizeWithMarker_Values[q22] + 2 = y_ExplicitVarSizeWithFlags_Values[q23] - | q22 : int(1..4), q23 : int(1..4)]), - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..3)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 2 | q2 : int(1..4)]), - 1 <= x_ExplicitVarSizeWithMarker_Marker, - and([y_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> - y_ExplicitVarSizeWithFlags_Values[q4] < y_ExplicitVarSizeWithFlags_Values[q4 + 1] - | q4 : int(1..3)]), - and([y_ExplicitVarSizeWithFlags_Flags[q5] = false -> y_ExplicitVarSizeWithFlags_Values[q5] = 2 | q5 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q6] | q6 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q7]) | q7 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q9 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q9] < x_ExplicitVarSizeWithFlags_Values[q9 + 1] - | q9 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q10] = false -> x_ExplicitVarSizeWithFlags_Values[q10] = 2 - | q10 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q11 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q11] | q11 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q12]) | q12 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q15] -> - or([q17 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q17] = x_ExplicitVarSizeWithFlags_Values[q15] - | q17 : int(1..4)]) - | q15 : int(1..4)]), - and([q19 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q21] /\ - x_ExplicitVarSizeWithFlags_Values[q21] = x_ExplicitVarSizeWithMarker_Values[q19] - | q21 : int(1..4)]) - | q19 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_4_1_1_1-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_4_1_1_1-solution000001.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_1_1_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_4_1_1_1-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_4_1_1_1-solution000002.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_1_1_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_4_1_1_1.eprime b/tests/exhaustive/basic/set09/expected/model_4_1_1_1.eprime deleted file mode 100644 index 3b3dd72895..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_1_1_1.eprime +++ /dev/null @@ -1,24 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -find x_Occurrence: matrix indexed by [int(2..5)] of bool -find y_Occurrence: matrix indexed by [int(2..5)] of bool -branching on [x_Occurrence, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, y_Occurrence] -such that - and([x_ExplicitVarSizeWithFlags_Flags[q13] /\ y_Occurrence[j] -> x_ExplicitVarSizeWithFlags_Values[q13] + 2 = j - | q13 : int(1..4), j : int(2..5)]), - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 2 | q2 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]), - 1 <= sum([toInt(y_Occurrence[q6]) | q6 : int(2..5)]), - 1 <= sum([toInt(x_Occurrence[q7]) | q7 : int(2..5)]), - and([x_Occurrence[q8] -> - or([x_ExplicitVarSizeWithFlags_Flags[q10] /\ x_ExplicitVarSizeWithFlags_Values[q10] = q8 | q10 : int(1..4)]) - | q8 : int(2..5)]), - and([x_ExplicitVarSizeWithFlags_Flags[q12] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q12]] - | q12 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_4_1_1_2-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_4_1_1_2-solution000001.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_1_1_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_4_1_1_2-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_4_1_1_2-solution000002.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_1_1_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_4_1_1_2.eprime b/tests/exhaustive/basic/set09/expected/model_4_1_1_2.eprime deleted file mode 100644 index c7b6641b99..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_1_1_2.eprime +++ /dev/null @@ -1,35 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -find x_Occurrence: matrix indexed by [int(2..5)] of bool -find y_Occurrence: matrix indexed by [int(2..5)] of bool -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -branching on - [x_Occurrence, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithDummy, - y_Occurrence] -such that - and([x_ExplicitVarSizeWithFlags_Flags[q22] /\ y_Occurrence[j] -> x_ExplicitVarSizeWithFlags_Values[q22] + 2 = j - | q22 : int(1..4), j : int(2..5)]), - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 2 | q2 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]), - 1 <= sum([toInt(y_Occurrence[q6]) | q6 : int(2..5)]), - 1 <= sum([toInt(x_Occurrence[q7]) | q7 : int(2..5)]), - and([x_Occurrence[q17] -> - or([x_ExplicitVarSizeWithFlags_Flags[q19] /\ x_ExplicitVarSizeWithFlags_Values[q19] = q17 | q19 : int(1..4)]) - | q17 : int(2..5)]), - and([x_ExplicitVarSizeWithFlags_Flags[q21] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q21]] - | q21 : int(1..4)]), - and([y_ExplicitVarSizeWithDummy[q8] < y_ExplicitVarSizeWithDummy[q8 + 1] \/ y_ExplicitVarSizeWithDummy[q8] = 6 - | q8 : int(1..3)]), - and([y_ExplicitVarSizeWithDummy[q9] = 6 -> y_ExplicitVarSizeWithDummy[q9 + 1] = 6 | q9 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q10] != 6) | q10 : int(1..4)]), - and([y_ExplicitVarSizeWithDummy[q13] != 6 -> y_Occurrence[y_ExplicitVarSizeWithDummy[q13]] | q13 : int(1..4)]), - and([y_Occurrence[q14] -> - or([y_ExplicitVarSizeWithDummy[q16] != 6 /\ y_ExplicitVarSizeWithDummy[q16] = q14 | q16 : int(1..4)]) - | q14 : int(2..5)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_4_1_1_3-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_4_1_1_3-solution000001.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_1_1_3-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_4_1_1_3-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_4_1_1_3-solution000002.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_1_1_3-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_4_1_1_3.eprime b/tests/exhaustive/basic/set09/expected/model_4_1_1_3.eprime deleted file mode 100644 index 8883ffc92f..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_1_1_3.eprime +++ /dev/null @@ -1,39 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -find x_Occurrence: matrix indexed by [int(2..5)] of bool -find y_Occurrence: matrix indexed by [int(2..5)] of bool -find y_ExplicitVarSizeWithMarker_Marker: int(0..4) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -branching on - [x_Occurrence, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, - y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values, y_Occurrence] -such that - and([x_ExplicitVarSizeWithFlags_Flags[q21] /\ y_Occurrence[j] -> x_ExplicitVarSizeWithFlags_Values[q21] + 2 = j - | q21 : int(1..4), j : int(2..5)]), - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 2 | q2 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]), - 1 <= sum([toInt(y_Occurrence[q6]) | q6 : int(2..5)]), - 1 <= sum([toInt(x_Occurrence[q7]) | q7 : int(2..5)]), - and([x_Occurrence[q16] -> - or([x_ExplicitVarSizeWithFlags_Flags[q18] /\ x_ExplicitVarSizeWithFlags_Values[q18] = q16 | q18 : int(1..4)]) - | q16 : int(2..5)]), - and([x_ExplicitVarSizeWithFlags_Flags[q20] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q20]] - | q20 : int(1..4)]), - and([q8 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> - y_ExplicitVarSizeWithMarker_Values[q8] < y_ExplicitVarSizeWithMarker_Values[q8 + 1] - | q8 : int(1..3)]), - and([q9 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q9] = 2 | q9 : int(1..4)]), - 1 <= y_ExplicitVarSizeWithMarker_Marker, - and([q12 <= y_ExplicitVarSizeWithMarker_Marker -> y_Occurrence[y_ExplicitVarSizeWithMarker_Values[q12]] - | q12 : int(1..4)]), - and([y_Occurrence[q13] -> - or([q15 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[q15] = q13 - | q15 : int(1..4)]) - | q13 : int(2..5)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_4_1_1_4-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_4_1_1_4-solution000001.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_1_1_4-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_4_1_1_4-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_4_1_1_4-solution000002.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_1_1_4-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_4_1_1_4.eprime b/tests/exhaustive/basic/set09/expected/model_4_1_1_4.eprime deleted file mode 100644 index e566516efd..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_1_1_4.eprime +++ /dev/null @@ -1,39 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -find x_Occurrence: matrix indexed by [int(2..5)] of bool -find y_Occurrence: matrix indexed by [int(2..5)] of bool -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -branching on - [x_Occurrence, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, - y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values, y_Occurrence] -such that - and([x_ExplicitVarSizeWithFlags_Flags[q23] /\ y_Occurrence[j] -> x_ExplicitVarSizeWithFlags_Values[q23] + 2 = j - | q23 : int(1..4), j : int(2..5)]), - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 2 | q2 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]), - 1 <= sum([toInt(y_Occurrence[q6]) | q6 : int(2..5)]), - 1 <= sum([toInt(x_Occurrence[q7]) | q7 : int(2..5)]), - and([x_Occurrence[q18] -> - or([x_ExplicitVarSizeWithFlags_Flags[q20] /\ x_ExplicitVarSizeWithFlags_Values[q20] = q18 | q20 : int(1..4)]) - | q18 : int(2..5)]), - and([x_ExplicitVarSizeWithFlags_Flags[q22] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q22]] - | q22 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q8 + 1] -> - y_ExplicitVarSizeWithFlags_Values[q8] < y_ExplicitVarSizeWithFlags_Values[q8 + 1] - | q8 : int(1..3)]), - and([y_ExplicitVarSizeWithFlags_Flags[q9] = false -> y_ExplicitVarSizeWithFlags_Values[q9] = 2 | q9 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q10 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q10] | q10 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q11]) | q11 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q14] -> y_Occurrence[y_ExplicitVarSizeWithFlags_Values[q14]] - | q14 : int(1..4)]), - and([y_Occurrence[q15] -> - or([y_ExplicitVarSizeWithFlags_Flags[q17] /\ y_ExplicitVarSizeWithFlags_Values[q17] = q15 | q17 : int(1..4)]) - | q15 : int(2..5)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_4_1_2_1-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_4_1_2_1-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_1_2_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_4_1_2_1-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_4_1_2_1-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_1_2_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_4_1_2_1.eprime b/tests/exhaustive/basic/set09/expected/model_4_1_2_1.eprime deleted file mode 100644 index afaea477ca..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_1_2_1.eprime +++ /dev/null @@ -1,33 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -find y_Occurrence: matrix indexed by [int(2..5)] of bool -branching on - [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, y_Occurrence] -such that - and([x_ExplicitVarSizeWithFlags_Flags[q19] /\ y_Occurrence[j] -> x_ExplicitVarSizeWithFlags_Values[q19] + 2 = j - | q19 : int(1..4), j : int(2..5)]), - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 2 | q2 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]), - 1 <= sum([toInt(y_Occurrence[q6]) | q6 : int(2..5)]), - and([x_ExplicitVarSizeWithDummy[q7] < x_ExplicitVarSizeWithDummy[q7 + 1] \/ x_ExplicitVarSizeWithDummy[q7] = 6 - | q7 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q8] = 6 -> x_ExplicitVarSizeWithDummy[q8 + 1] = 6 | q8 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q9] != 6) | q9 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q12] != 6 -> - or([x_ExplicitVarSizeWithFlags_Flags[q14] /\ - x_ExplicitVarSizeWithFlags_Values[q14] = x_ExplicitVarSizeWithDummy[q12] - | q14 : int(1..4)]) - | q12 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q16] -> - or([x_ExplicitVarSizeWithDummy[q18] != 6 /\ - x_ExplicitVarSizeWithDummy[q18] = x_ExplicitVarSizeWithFlags_Values[q16] - | q18 : int(1..4)]) - | q16 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_4_1_2_2-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_4_1_2_2-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_1_2_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_4_1_2_2-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_4_1_2_2-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_1_2_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_4_1_2_2.eprime b/tests/exhaustive/basic/set09/expected/model_4_1_2_2.eprime deleted file mode 100644 index 2de99626cb..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_1_2_2.eprime +++ /dev/null @@ -1,43 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -find y_Occurrence: matrix indexed by [int(2..5)] of bool -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -branching on - [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, - y_ExplicitVarSizeWithDummy, y_Occurrence] -such that - and([x_ExplicitVarSizeWithFlags_Flags[q28] /\ y_Occurrence[j] -> x_ExplicitVarSizeWithFlags_Values[q28] + 2 = j - | q28 : int(1..4), j : int(2..5)]), - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 2 | q2 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]), - 1 <= sum([toInt(y_Occurrence[q6]) | q6 : int(2..5)]), - and([x_ExplicitVarSizeWithDummy[q7] < x_ExplicitVarSizeWithDummy[q7 + 1] \/ x_ExplicitVarSizeWithDummy[q7] = 6 - | q7 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q8] = 6 -> x_ExplicitVarSizeWithDummy[q8 + 1] = 6 | q8 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q9] != 6) | q9 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q12] != 6 -> - or([x_ExplicitVarSizeWithFlags_Flags[q14] /\ - x_ExplicitVarSizeWithFlags_Values[q14] = x_ExplicitVarSizeWithDummy[q12] - | q14 : int(1..4)]) - | q12 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q16] -> - or([x_ExplicitVarSizeWithDummy[q18] != 6 /\ - x_ExplicitVarSizeWithDummy[q18] = x_ExplicitVarSizeWithFlags_Values[q16] - | q18 : int(1..4)]) - | q16 : int(1..4)]), - and([y_ExplicitVarSizeWithDummy[q19] < y_ExplicitVarSizeWithDummy[q19 + 1] \/ y_ExplicitVarSizeWithDummy[q19] = 6 - | q19 : int(1..3)]), - and([y_ExplicitVarSizeWithDummy[q20] = 6 -> y_ExplicitVarSizeWithDummy[q20 + 1] = 6 | q20 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q21] != 6) | q21 : int(1..4)]), - and([y_ExplicitVarSizeWithDummy[q24] != 6 -> y_Occurrence[y_ExplicitVarSizeWithDummy[q24]] | q24 : int(1..4)]), - and([y_Occurrence[q25] -> - or([y_ExplicitVarSizeWithDummy[q27] != 6 /\ y_ExplicitVarSizeWithDummy[q27] = q25 | q27 : int(1..4)]) - | q25 : int(2..5)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_4_1_2_3-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_4_1_2_3-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_1_2_3-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_4_1_2_3-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_4_1_2_3-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_1_2_3-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_4_1_2_3.eprime b/tests/exhaustive/basic/set09/expected/model_4_1_2_3.eprime deleted file mode 100644 index 654da549aa..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_1_2_3.eprime +++ /dev/null @@ -1,47 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -find y_Occurrence: matrix indexed by [int(2..5)] of bool -find y_ExplicitVarSizeWithMarker_Marker: int(0..4) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -branching on - [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, - y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values, y_Occurrence] -such that - and([x_ExplicitVarSizeWithFlags_Flags[q27] /\ y_Occurrence[j] -> x_ExplicitVarSizeWithFlags_Values[q27] + 2 = j - | q27 : int(1..4), j : int(2..5)]), - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 2 | q2 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]), - 1 <= sum([toInt(y_Occurrence[q6]) | q6 : int(2..5)]), - and([x_ExplicitVarSizeWithDummy[q7] < x_ExplicitVarSizeWithDummy[q7 + 1] \/ x_ExplicitVarSizeWithDummy[q7] = 6 - | q7 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q8] = 6 -> x_ExplicitVarSizeWithDummy[q8 + 1] = 6 | q8 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q9] != 6) | q9 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q12] != 6 -> - or([x_ExplicitVarSizeWithFlags_Flags[q14] /\ - x_ExplicitVarSizeWithFlags_Values[q14] = x_ExplicitVarSizeWithDummy[q12] - | q14 : int(1..4)]) - | q12 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q16] -> - or([x_ExplicitVarSizeWithDummy[q18] != 6 /\ - x_ExplicitVarSizeWithDummy[q18] = x_ExplicitVarSizeWithFlags_Values[q16] - | q18 : int(1..4)]) - | q16 : int(1..4)]), - and([q19 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> - y_ExplicitVarSizeWithMarker_Values[q19] < y_ExplicitVarSizeWithMarker_Values[q19 + 1] - | q19 : int(1..3)]), - and([q20 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q20] = 2 | q20 : int(1..4)]), - 1 <= y_ExplicitVarSizeWithMarker_Marker, - and([q23 <= y_ExplicitVarSizeWithMarker_Marker -> y_Occurrence[y_ExplicitVarSizeWithMarker_Values[q23]] - | q23 : int(1..4)]), - and([y_Occurrence[q24] -> - or([q26 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[q26] = q24 - | q26 : int(1..4)]) - | q24 : int(2..5)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_4_1_2_4-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_4_1_2_4-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_1_2_4-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_4_1_2_4-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_4_1_2_4-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_1_2_4-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_4_1_2_4.eprime b/tests/exhaustive/basic/set09/expected/model_4_1_2_4.eprime deleted file mode 100644 index af1a93b8b4..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_1_2_4.eprime +++ /dev/null @@ -1,48 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -find y_Occurrence: matrix indexed by [int(2..5)] of bool -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -branching on - [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, - y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values, y_Occurrence] -such that - and([x_ExplicitVarSizeWithFlags_Flags[q29] /\ y_Occurrence[j] -> x_ExplicitVarSizeWithFlags_Values[q29] + 2 = j - | q29 : int(1..4), j : int(2..5)]), - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 2 | q2 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]), - 1 <= sum([toInt(y_Occurrence[q6]) | q6 : int(2..5)]), - and([x_ExplicitVarSizeWithDummy[q7] < x_ExplicitVarSizeWithDummy[q7 + 1] \/ x_ExplicitVarSizeWithDummy[q7] = 6 - | q7 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q8] = 6 -> x_ExplicitVarSizeWithDummy[q8 + 1] = 6 | q8 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q9] != 6) | q9 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q12] != 6 -> - or([x_ExplicitVarSizeWithFlags_Flags[q14] /\ - x_ExplicitVarSizeWithFlags_Values[q14] = x_ExplicitVarSizeWithDummy[q12] - | q14 : int(1..4)]) - | q12 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q16] -> - or([x_ExplicitVarSizeWithDummy[q18] != 6 /\ - x_ExplicitVarSizeWithDummy[q18] = x_ExplicitVarSizeWithFlags_Values[q16] - | q18 : int(1..4)]) - | q16 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q19 + 1] -> - y_ExplicitVarSizeWithFlags_Values[q19] < y_ExplicitVarSizeWithFlags_Values[q19 + 1] - | q19 : int(1..3)]), - and([y_ExplicitVarSizeWithFlags_Flags[q20] = false -> y_ExplicitVarSizeWithFlags_Values[q20] = 2 - | q20 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q21 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q21] | q21 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q22]) | q22 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q25] -> y_Occurrence[y_ExplicitVarSizeWithFlags_Values[q25]] - | q25 : int(1..4)]), - and([y_Occurrence[q26] -> - or([y_ExplicitVarSizeWithFlags_Flags[q28] /\ y_ExplicitVarSizeWithFlags_Values[q28] = q26 | q28 : int(1..4)]) - | q26 : int(2..5)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_4_1_3_1-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_4_1_3_1-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_1_3_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_4_1_3_1-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_4_1_3_1-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_1_3_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_4_1_3_1.eprime b/tests/exhaustive/basic/set09/expected/model_4_1_3_1.eprime deleted file mode 100644 index 2a4f8d9d12..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_1_3_1.eprime +++ /dev/null @@ -1,36 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_Occurrence: matrix indexed by [int(2..5)] of bool -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithFlags_Flags, - x_ExplicitVarSizeWithFlags_Values, y_Occurrence] -such that - and([x_ExplicitVarSizeWithFlags_Flags[q18] /\ y_Occurrence[j] -> x_ExplicitVarSizeWithFlags_Values[q18] + 2 = j - | q18 : int(1..4), j : int(2..5)]), - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 2 | q2 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]), - 1 <= sum([toInt(y_Occurrence[q6]) | q6 : int(2..5)]), - and([q7 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q7] < x_ExplicitVarSizeWithMarker_Values[q7 + 1] - | q7 : int(1..3)]), - and([q8 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q8] = 2 | q8 : int(1..4)]), - 1 <= x_ExplicitVarSizeWithMarker_Marker, - and([q11 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q13] /\ - x_ExplicitVarSizeWithFlags_Values[q13] = x_ExplicitVarSizeWithMarker_Values[q11] - | q13 : int(1..4)]) - | q11 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q15] -> - or([q17 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q17] = x_ExplicitVarSizeWithFlags_Values[q15] - | q17 : int(1..4)]) - | q15 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_4_1_3_2-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_4_1_3_2-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_1_3_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_4_1_3_2-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_4_1_3_2-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_1_3_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_4_1_3_2.eprime b/tests/exhaustive/basic/set09/expected/model_4_1_3_2.eprime deleted file mode 100644 index 237665c083..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_1_3_2.eprime +++ /dev/null @@ -1,45 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_Occurrence: matrix indexed by [int(2..5)] of bool -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithFlags_Flags, - x_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithDummy, y_Occurrence] -such that - and([x_ExplicitVarSizeWithFlags_Flags[q27] /\ y_Occurrence[j] -> x_ExplicitVarSizeWithFlags_Values[q27] + 2 = j - | q27 : int(1..4), j : int(2..5)]), - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 2 | q2 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]), - 1 <= sum([toInt(y_Occurrence[q6]) | q6 : int(2..5)]), - and([q7 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q7] < x_ExplicitVarSizeWithMarker_Values[q7 + 1] - | q7 : int(1..3)]), - and([q8 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q8] = 2 | q8 : int(1..4)]), - 1 <= x_ExplicitVarSizeWithMarker_Marker, - and([q11 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q13] /\ - x_ExplicitVarSizeWithFlags_Values[q13] = x_ExplicitVarSizeWithMarker_Values[q11] - | q13 : int(1..4)]) - | q11 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q15] -> - or([q17 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q17] = x_ExplicitVarSizeWithFlags_Values[q15] - | q17 : int(1..4)]) - | q15 : int(1..4)]), - and([y_ExplicitVarSizeWithDummy[q18] < y_ExplicitVarSizeWithDummy[q18 + 1] \/ y_ExplicitVarSizeWithDummy[q18] = 6 - | q18 : int(1..3)]), - and([y_ExplicitVarSizeWithDummy[q19] = 6 -> y_ExplicitVarSizeWithDummy[q19 + 1] = 6 | q19 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q20] != 6) | q20 : int(1..4)]), - and([y_ExplicitVarSizeWithDummy[q23] != 6 -> y_Occurrence[y_ExplicitVarSizeWithDummy[q23]] | q23 : int(1..4)]), - and([y_Occurrence[q24] -> - or([y_ExplicitVarSizeWithDummy[q26] != 6 /\ y_ExplicitVarSizeWithDummy[q26] = q24 | q26 : int(1..4)]) - | q24 : int(2..5)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_4_1_3_3-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_4_1_3_3-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_1_3_3-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_4_1_3_3-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_4_1_3_3-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_1_3_3-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_4_1_3_3.eprime b/tests/exhaustive/basic/set09/expected/model_4_1_3_3.eprime deleted file mode 100644 index 78ff28ba58..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_1_3_3.eprime +++ /dev/null @@ -1,50 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_Occurrence: matrix indexed by [int(2..5)] of bool -find y_ExplicitVarSizeWithMarker_Marker: int(0..4) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithFlags_Flags, - x_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values, - y_Occurrence] -such that - and([x_ExplicitVarSizeWithFlags_Flags[q26] /\ y_Occurrence[j] -> x_ExplicitVarSizeWithFlags_Values[q26] + 2 = j - | q26 : int(1..4), j : int(2..5)]), - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 2 | q2 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]), - 1 <= sum([toInt(y_Occurrence[q6]) | q6 : int(2..5)]), - and([q7 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q7] < x_ExplicitVarSizeWithMarker_Values[q7 + 1] - | q7 : int(1..3)]), - and([q8 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q8] = 2 | q8 : int(1..4)]), - 1 <= x_ExplicitVarSizeWithMarker_Marker, - and([q11 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q13] /\ - x_ExplicitVarSizeWithFlags_Values[q13] = x_ExplicitVarSizeWithMarker_Values[q11] - | q13 : int(1..4)]) - | q11 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q15] -> - or([q17 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q17] = x_ExplicitVarSizeWithFlags_Values[q15] - | q17 : int(1..4)]) - | q15 : int(1..4)]), - and([q18 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> - y_ExplicitVarSizeWithMarker_Values[q18] < y_ExplicitVarSizeWithMarker_Values[q18 + 1] - | q18 : int(1..3)]), - and([q19 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q19] = 2 | q19 : int(1..4)]), - 1 <= y_ExplicitVarSizeWithMarker_Marker, - and([q22 <= y_ExplicitVarSizeWithMarker_Marker -> y_Occurrence[y_ExplicitVarSizeWithMarker_Values[q22]] - | q22 : int(1..4)]), - and([y_Occurrence[q23] -> - or([q25 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[q25] = q23 - | q25 : int(1..4)]) - | q23 : int(2..5)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_4_1_3_4-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_4_1_3_4-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_1_3_4-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_4_1_3_4-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_4_1_3_4-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_1_3_4-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_4_1_3_4.eprime b/tests/exhaustive/basic/set09/expected/model_4_1_3_4.eprime deleted file mode 100644 index e8221a747a..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_1_3_4.eprime +++ /dev/null @@ -1,51 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_Occurrence: matrix indexed by [int(2..5)] of bool -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithFlags_Flags, - x_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values, - y_Occurrence] -such that - and([x_ExplicitVarSizeWithFlags_Flags[q28] /\ y_Occurrence[j] -> x_ExplicitVarSizeWithFlags_Values[q28] + 2 = j - | q28 : int(1..4), j : int(2..5)]), - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 2 | q2 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]), - 1 <= sum([toInt(y_Occurrence[q6]) | q6 : int(2..5)]), - and([q7 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q7] < x_ExplicitVarSizeWithMarker_Values[q7 + 1] - | q7 : int(1..3)]), - and([q8 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q8] = 2 | q8 : int(1..4)]), - 1 <= x_ExplicitVarSizeWithMarker_Marker, - and([q11 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q13] /\ - x_ExplicitVarSizeWithFlags_Values[q13] = x_ExplicitVarSizeWithMarker_Values[q11] - | q13 : int(1..4)]) - | q11 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q15] -> - or([q17 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q17] = x_ExplicitVarSizeWithFlags_Values[q15] - | q17 : int(1..4)]) - | q15 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q18 + 1] -> - y_ExplicitVarSizeWithFlags_Values[q18] < y_ExplicitVarSizeWithFlags_Values[q18 + 1] - | q18 : int(1..3)]), - and([y_ExplicitVarSizeWithFlags_Flags[q19] = false -> y_ExplicitVarSizeWithFlags_Values[q19] = 2 - | q19 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q20 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q20] | q20 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q21]) | q21 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q24] -> y_Occurrence[y_ExplicitVarSizeWithFlags_Values[q24]] - | q24 : int(1..4)]), - and([y_Occurrence[q25] -> - or([y_ExplicitVarSizeWithFlags_Flags[q27] /\ y_ExplicitVarSizeWithFlags_Values[q27] = q25 | q27 : int(1..4)]) - | q25 : int(2..5)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_4_1_4_1-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_4_1_4_1-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_1_4_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_4_1_4_1-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_4_1_4_1-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_1_4_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_4_1_4_1.eprime b/tests/exhaustive/basic/set09/expected/model_4_1_4_1.eprime deleted file mode 100644 index 109e0f0711..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_1_4_1.eprime +++ /dev/null @@ -1,17 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_Occurrence: matrix indexed by [int(2..5)] of bool -branching on [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, y_Occurrence] -such that - and([x_ExplicitVarSizeWithFlags_Flags[q7] /\ y_Occurrence[j] -> x_ExplicitVarSizeWithFlags_Values[q7] + 2 = j - | q7 : int(1..4), j : int(2..5)]), - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 2 | q2 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]), - 1 <= sum([toInt(y_Occurrence[q6]) | q6 : int(2..5)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_4_1_4_2-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_4_1_4_2-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_1_4_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_4_1_4_2-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_4_1_4_2-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_1_4_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_4_1_4_2.eprime b/tests/exhaustive/basic/set09/expected/model_4_1_4_2.eprime deleted file mode 100644 index 76ef2af84d..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_1_4_2.eprime +++ /dev/null @@ -1,27 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_Occurrence: matrix indexed by [int(2..5)] of bool -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithDummy, y_Occurrence] -such that - and([x_ExplicitVarSizeWithFlags_Flags[q16] /\ y_Occurrence[j] -> x_ExplicitVarSizeWithFlags_Values[q16] + 2 = j - | q16 : int(1..4), j : int(2..5)]), - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 2 | q2 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]), - 1 <= sum([toInt(y_Occurrence[q6]) | q6 : int(2..5)]), - and([y_ExplicitVarSizeWithDummy[q7] < y_ExplicitVarSizeWithDummy[q7 + 1] \/ y_ExplicitVarSizeWithDummy[q7] = 6 - | q7 : int(1..3)]), - and([y_ExplicitVarSizeWithDummy[q8] = 6 -> y_ExplicitVarSizeWithDummy[q8 + 1] = 6 | q8 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q9] != 6) | q9 : int(1..4)]), - and([y_ExplicitVarSizeWithDummy[q12] != 6 -> y_Occurrence[y_ExplicitVarSizeWithDummy[q12]] | q12 : int(1..4)]), - and([y_Occurrence[q13] -> - or([y_ExplicitVarSizeWithDummy[q15] != 6 /\ y_ExplicitVarSizeWithDummy[q15] = q13 | q15 : int(1..4)]) - | q13 : int(2..5)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_4_1_4_3-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_4_1_4_3-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_1_4_3-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_4_1_4_3-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_4_1_4_3-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_1_4_3-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_4_1_4_3.eprime b/tests/exhaustive/basic/set09/expected/model_4_1_4_3.eprime deleted file mode 100644 index c7bf7b7442..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_1_4_3.eprime +++ /dev/null @@ -1,32 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_Occurrence: matrix indexed by [int(2..5)] of bool -find y_ExplicitVarSizeWithMarker_Marker: int(0..4) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithMarker_Marker, - y_ExplicitVarSizeWithMarker_Values, y_Occurrence] -such that - and([x_ExplicitVarSizeWithFlags_Flags[q15] /\ y_Occurrence[j] -> x_ExplicitVarSizeWithFlags_Values[q15] + 2 = j - | q15 : int(1..4), j : int(2..5)]), - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 2 | q2 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]), - 1 <= sum([toInt(y_Occurrence[q6]) | q6 : int(2..5)]), - and([q7 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> - y_ExplicitVarSizeWithMarker_Values[q7] < y_ExplicitVarSizeWithMarker_Values[q7 + 1] - | q7 : int(1..3)]), - and([q8 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q8] = 2 | q8 : int(1..4)]), - 1 <= y_ExplicitVarSizeWithMarker_Marker, - and([q11 <= y_ExplicitVarSizeWithMarker_Marker -> y_Occurrence[y_ExplicitVarSizeWithMarker_Values[q11]] - | q11 : int(1..4)]), - and([y_Occurrence[q12] -> - or([q14 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[q14] = q12 - | q14 : int(1..4)]) - | q12 : int(2..5)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_4_1_4_4-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_4_1_4_4-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_1_4_4-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_4_1_4_4-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_4_1_4_4-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_1_4_4-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_4_1_4_4.eprime b/tests/exhaustive/basic/set09/expected/model_4_1_4_4.eprime deleted file mode 100644 index 8108a5b294..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_1_4_4.eprime +++ /dev/null @@ -1,32 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_Occurrence: matrix indexed by [int(2..5)] of bool -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithFlags_Flags, - y_ExplicitVarSizeWithFlags_Values, y_Occurrence] -such that - and([x_ExplicitVarSizeWithFlags_Flags[q17] /\ y_Occurrence[j] -> x_ExplicitVarSizeWithFlags_Values[q17] + 2 = j - | q17 : int(1..4), j : int(2..5)]), - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 2 | q2 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]), - 1 <= sum([toInt(y_Occurrence[q6]) | q6 : int(2..5)]), - and([y_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> - y_ExplicitVarSizeWithFlags_Values[q7] < y_ExplicitVarSizeWithFlags_Values[q7 + 1] - | q7 : int(1..3)]), - and([y_ExplicitVarSizeWithFlags_Flags[q8] = false -> y_ExplicitVarSizeWithFlags_Values[q8] = 2 | q8 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q9 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q9] | q9 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q10]) | q10 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q13] -> y_Occurrence[y_ExplicitVarSizeWithFlags_Values[q13]] - | q13 : int(1..4)]), - and([y_Occurrence[q14] -> - or([y_ExplicitVarSizeWithFlags_Flags[q16] /\ y_ExplicitVarSizeWithFlags_Values[q16] = q14 | q16 : int(1..4)]) - | q14 : int(2..5)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_4_2_1_1-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_4_2_1_1-solution000001.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_2_1_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_4_2_1_1-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_4_2_1_1-solution000002.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_2_1_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_4_2_1_1.eprime b/tests/exhaustive/basic/set09/expected/model_4_2_1_1.eprime deleted file mode 100644 index 58ed3249aa..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_2_1_1.eprime +++ /dev/null @@ -1,36 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -find x_Occurrence: matrix indexed by [int(2..5)] of bool -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -find y_Occurrence: matrix indexed by [int(2..5)] of bool -branching on - [x_Occurrence, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, y_Occurrence, - y_ExplicitVarSizeWithDummy] -such that - and([x_ExplicitVarSizeWithFlags_Flags[q17] /\ y_ExplicitVarSizeWithDummy[q18] != 6 -> - x_ExplicitVarSizeWithFlags_Values[q17] + 2 = y_ExplicitVarSizeWithDummy[q18] - | q17 : int(1..4), q18 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 2 | q2 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]), - and([y_ExplicitVarSizeWithDummy[q6] < y_ExplicitVarSizeWithDummy[q6 + 1] \/ y_ExplicitVarSizeWithDummy[q6] = 6 - | q6 : int(1..3)]), - and([y_ExplicitVarSizeWithDummy[q7] = 6 -> y_ExplicitVarSizeWithDummy[q7 + 1] = 6 | q7 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q8] != 6) | q8 : int(1..4)]), - 1 <= sum([toInt(x_Occurrence[q10]) | q10 : int(2..5)]), - and([x_Occurrence[q19] -> - or([x_ExplicitVarSizeWithFlags_Flags[q21] /\ x_ExplicitVarSizeWithFlags_Values[q21] = q19 | q21 : int(1..4)]) - | q19 : int(2..5)]), - and([x_ExplicitVarSizeWithFlags_Flags[q23] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q23]] - | q23 : int(1..4)]), - 1 <= sum([toInt(y_Occurrence[q11]) | q11 : int(2..5)]), - and([y_Occurrence[q12] -> - or([y_ExplicitVarSizeWithDummy[q14] != 6 /\ y_ExplicitVarSizeWithDummy[q14] = q12 | q14 : int(1..4)]) - | q12 : int(2..5)]), - and([y_ExplicitVarSizeWithDummy[q16] != 6 -> y_Occurrence[y_ExplicitVarSizeWithDummy[q16]] | q16 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_4_2_1_2-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_4_2_1_2-solution000001.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_2_1_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_4_2_1_2-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_4_2_1_2-solution000002.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_2_1_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_4_2_1_2.eprime b/tests/exhaustive/basic/set09/expected/model_4_2_1_2.eprime deleted file mode 100644 index b326331c8d..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_2_1_2.eprime +++ /dev/null @@ -1,29 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -find x_Occurrence: matrix indexed by [int(2..5)] of bool -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -branching on - [x_Occurrence, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithDummy] -such that - and([x_ExplicitVarSizeWithFlags_Flags[q16] /\ y_ExplicitVarSizeWithDummy[q17] != 6 -> - x_ExplicitVarSizeWithFlags_Values[q16] + 2 = y_ExplicitVarSizeWithDummy[q17] - | q16 : int(1..4), q17 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 2 | q2 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]), - and([y_ExplicitVarSizeWithDummy[q6] < y_ExplicitVarSizeWithDummy[q6 + 1] \/ y_ExplicitVarSizeWithDummy[q6] = 6 - | q6 : int(1..3)]), - and([y_ExplicitVarSizeWithDummy[q7] = 6 -> y_ExplicitVarSizeWithDummy[q7 + 1] = 6 | q7 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q8] != 6) | q8 : int(1..4)]), - 1 <= sum([toInt(x_Occurrence[q10]) | q10 : int(2..5)]), - and([x_Occurrence[q11] -> - or([x_ExplicitVarSizeWithFlags_Flags[q13] /\ x_ExplicitVarSizeWithFlags_Values[q13] = q11 | q13 : int(1..4)]) - | q11 : int(2..5)]), - and([x_ExplicitVarSizeWithFlags_Flags[q15] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q15]] - | q15 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_4_2_1_3-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_4_2_1_3-solution000001.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_2_1_3-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_4_2_1_3-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_4_2_1_3-solution000002.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_2_1_3-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_4_2_1_3.eprime b/tests/exhaustive/basic/set09/expected/model_4_2_1_3.eprime deleted file mode 100644 index 10b83edfd1..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_2_1_3.eprime +++ /dev/null @@ -1,47 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -find x_Occurrence: matrix indexed by [int(2..5)] of bool -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -find y_ExplicitVarSizeWithMarker_Marker: int(0..4) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -branching on - [x_Occurrence, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, - y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithDummy] -such that - and([x_ExplicitVarSizeWithFlags_Flags[q27] /\ y_ExplicitVarSizeWithDummy[q28] != 6 -> - x_ExplicitVarSizeWithFlags_Values[q27] + 2 = y_ExplicitVarSizeWithDummy[q28] - | q27 : int(1..4), q28 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 2 | q2 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]), - and([y_ExplicitVarSizeWithDummy[q6] < y_ExplicitVarSizeWithDummy[q6 + 1] \/ y_ExplicitVarSizeWithDummy[q6] = 6 - | q6 : int(1..3)]), - and([y_ExplicitVarSizeWithDummy[q7] = 6 -> y_ExplicitVarSizeWithDummy[q7 + 1] = 6 | q7 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q8] != 6) | q8 : int(1..4)]), - 1 <= sum([toInt(x_Occurrence[q10]) | q10 : int(2..5)]), - and([x_Occurrence[q22] -> - or([x_ExplicitVarSizeWithFlags_Flags[q24] /\ x_ExplicitVarSizeWithFlags_Values[q24] = q22 | q24 : int(1..4)]) - | q22 : int(2..5)]), - and([x_ExplicitVarSizeWithFlags_Flags[q26] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q26]] - | q26 : int(1..4)]), - and([q11 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> - y_ExplicitVarSizeWithMarker_Values[q11] < y_ExplicitVarSizeWithMarker_Values[q11 + 1] - | q11 : int(1..3)]), - and([q12 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q12] = 2 | q12 : int(1..4)]), - 1 <= y_ExplicitVarSizeWithMarker_Marker, - and([q15 <= y_ExplicitVarSizeWithMarker_Marker -> - or([y_ExplicitVarSizeWithDummy[q17] != 6 /\ - y_ExplicitVarSizeWithDummy[q17] = y_ExplicitVarSizeWithMarker_Values[q15] - | q17 : int(1..4)]) - | q15 : int(1..4)]), - and([y_ExplicitVarSizeWithDummy[q19] != 6 -> - or([q21 <= y_ExplicitVarSizeWithMarker_Marker /\ - y_ExplicitVarSizeWithMarker_Values[q21] = y_ExplicitVarSizeWithDummy[q19] - | q21 : int(1..4)]) - | q19 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_4_2_1_4-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_4_2_1_4-solution000001.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_2_1_4-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_4_2_1_4-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_4_2_1_4-solution000002.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_2_1_4-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_4_2_1_4.eprime b/tests/exhaustive/basic/set09/expected/model_4_2_1_4.eprime deleted file mode 100644 index 9b32a426d0..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_2_1_4.eprime +++ /dev/null @@ -1,49 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -find x_Occurrence: matrix indexed by [int(2..5)] of bool -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -branching on - [x_Occurrence, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, - y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithDummy] -such that - and([x_ExplicitVarSizeWithFlags_Flags[q29] /\ y_ExplicitVarSizeWithDummy[q30] != 6 -> - x_ExplicitVarSizeWithFlags_Values[q29] + 2 = y_ExplicitVarSizeWithDummy[q30] - | q29 : int(1..4), q30 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 2 | q2 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]), - and([y_ExplicitVarSizeWithDummy[q6] < y_ExplicitVarSizeWithDummy[q6 + 1] \/ y_ExplicitVarSizeWithDummy[q6] = 6 - | q6 : int(1..3)]), - and([y_ExplicitVarSizeWithDummy[q7] = 6 -> y_ExplicitVarSizeWithDummy[q7 + 1] = 6 | q7 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q8] != 6) | q8 : int(1..4)]), - 1 <= sum([toInt(x_Occurrence[q10]) | q10 : int(2..5)]), - and([x_Occurrence[q24] -> - or([x_ExplicitVarSizeWithFlags_Flags[q26] /\ x_ExplicitVarSizeWithFlags_Values[q26] = q24 | q26 : int(1..4)]) - | q24 : int(2..5)]), - and([x_ExplicitVarSizeWithFlags_Flags[q28] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q28]] - | q28 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q11 + 1] -> - y_ExplicitVarSizeWithFlags_Values[q11] < y_ExplicitVarSizeWithFlags_Values[q11 + 1] - | q11 : int(1..3)]), - and([y_ExplicitVarSizeWithFlags_Flags[q12] = false -> y_ExplicitVarSizeWithFlags_Values[q12] = 2 - | q12 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q13 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q13] | q13 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q14]) | q14 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q17] -> - or([y_ExplicitVarSizeWithDummy[q19] != 6 /\ - y_ExplicitVarSizeWithDummy[q19] = y_ExplicitVarSizeWithFlags_Values[q17] - | q19 : int(1..4)]) - | q17 : int(1..4)]), - and([y_ExplicitVarSizeWithDummy[q21] != 6 -> - or([y_ExplicitVarSizeWithFlags_Flags[q23] /\ - y_ExplicitVarSizeWithFlags_Values[q23] = y_ExplicitVarSizeWithDummy[q21] - | q23 : int(1..4)]) - | q21 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_4_2_2_1-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_4_2_2_1-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_2_2_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_4_2_2_1-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_4_2_2_1-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_2_2_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_4_2_2_1.eprime b/tests/exhaustive/basic/set09/expected/model_4_2_2_1.eprime deleted file mode 100644 index 04f00777cf..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_2_2_1.eprime +++ /dev/null @@ -1,44 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -find y_Occurrence: matrix indexed by [int(2..5)] of bool -branching on - [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, y_Occurrence, - y_ExplicitVarSizeWithDummy] -such that - and([x_ExplicitVarSizeWithFlags_Flags[q28] /\ y_ExplicitVarSizeWithDummy[q29] != 6 -> - x_ExplicitVarSizeWithFlags_Values[q28] + 2 = y_ExplicitVarSizeWithDummy[q29] - | q28 : int(1..4), q29 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 2 | q2 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]), - and([y_ExplicitVarSizeWithDummy[q6] < y_ExplicitVarSizeWithDummy[q6 + 1] \/ y_ExplicitVarSizeWithDummy[q6] = 6 - | q6 : int(1..3)]), - and([y_ExplicitVarSizeWithDummy[q7] = 6 -> y_ExplicitVarSizeWithDummy[q7 + 1] = 6 | q7 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q8] != 6) | q8 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q10] < x_ExplicitVarSizeWithDummy[q10 + 1] \/ x_ExplicitVarSizeWithDummy[q10] = 6 - | q10 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q11] = 6 -> x_ExplicitVarSizeWithDummy[q11 + 1] = 6 | q11 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q12] != 6) | q12 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q15] != 6 -> - or([x_ExplicitVarSizeWithFlags_Flags[q17] /\ - x_ExplicitVarSizeWithFlags_Values[q17] = x_ExplicitVarSizeWithDummy[q15] - | q17 : int(1..4)]) - | q15 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q19] -> - or([x_ExplicitVarSizeWithDummy[q21] != 6 /\ - x_ExplicitVarSizeWithDummy[q21] = x_ExplicitVarSizeWithFlags_Values[q19] - | q21 : int(1..4)]) - | q19 : int(1..4)]), - 1 <= sum([toInt(y_Occurrence[q22]) | q22 : int(2..5)]), - and([y_Occurrence[q23] -> - or([y_ExplicitVarSizeWithDummy[q25] != 6 /\ y_ExplicitVarSizeWithDummy[q25] = q23 | q25 : int(1..4)]) - | q23 : int(2..5)]), - and([y_ExplicitVarSizeWithDummy[q27] != 6 -> y_Occurrence[y_ExplicitVarSizeWithDummy[q27]] | q27 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_4_2_2_2-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_4_2_2_2-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_2_2_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_4_2_2_2-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_4_2_2_2-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_2_2_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_4_2_2_2.eprime b/tests/exhaustive/basic/set09/expected/model_4_2_2_2.eprime deleted file mode 100644 index 6d1e92a973..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_2_2_2.eprime +++ /dev/null @@ -1,38 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -branching on - [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, - y_ExplicitVarSizeWithDummy] -such that - and([x_ExplicitVarSizeWithFlags_Flags[q22] /\ y_ExplicitVarSizeWithDummy[q23] != 6 -> - x_ExplicitVarSizeWithFlags_Values[q22] + 2 = y_ExplicitVarSizeWithDummy[q23] - | q22 : int(1..4), q23 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 2 | q2 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]), - and([y_ExplicitVarSizeWithDummy[q6] < y_ExplicitVarSizeWithDummy[q6 + 1] \/ y_ExplicitVarSizeWithDummy[q6] = 6 - | q6 : int(1..3)]), - and([y_ExplicitVarSizeWithDummy[q7] = 6 -> y_ExplicitVarSizeWithDummy[q7 + 1] = 6 | q7 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q8] != 6) | q8 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q10] < x_ExplicitVarSizeWithDummy[q10 + 1] \/ x_ExplicitVarSizeWithDummy[q10] = 6 - | q10 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q11] = 6 -> x_ExplicitVarSizeWithDummy[q11 + 1] = 6 | q11 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q12] != 6) | q12 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q15] != 6 -> - or([x_ExplicitVarSizeWithFlags_Flags[q17] /\ - x_ExplicitVarSizeWithFlags_Values[q17] = x_ExplicitVarSizeWithDummy[q15] - | q17 : int(1..4)]) - | q15 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q19] -> - or([x_ExplicitVarSizeWithDummy[q21] != 6 /\ - x_ExplicitVarSizeWithDummy[q21] = x_ExplicitVarSizeWithFlags_Values[q19] - | q21 : int(1..4)]) - | q19 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_4_2_2_3-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_4_2_2_3-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_2_2_3-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_4_2_2_3-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_4_2_2_3-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_2_2_3-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_4_2_2_3.eprime b/tests/exhaustive/basic/set09/expected/model_4_2_2_3.eprime deleted file mode 100644 index 10a511c037..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_2_2_3.eprime +++ /dev/null @@ -1,55 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -find y_ExplicitVarSizeWithMarker_Marker: int(0..4) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -branching on - [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, - y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithDummy] -such that - and([x_ExplicitVarSizeWithFlags_Flags[q33] /\ y_ExplicitVarSizeWithDummy[q34] != 6 -> - x_ExplicitVarSizeWithFlags_Values[q33] + 2 = y_ExplicitVarSizeWithDummy[q34] - | q33 : int(1..4), q34 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 2 | q2 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]), - and([y_ExplicitVarSizeWithDummy[q6] < y_ExplicitVarSizeWithDummy[q6 + 1] \/ y_ExplicitVarSizeWithDummy[q6] = 6 - | q6 : int(1..3)]), - and([y_ExplicitVarSizeWithDummy[q7] = 6 -> y_ExplicitVarSizeWithDummy[q7 + 1] = 6 | q7 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q8] != 6) | q8 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q10] < x_ExplicitVarSizeWithDummy[q10 + 1] \/ x_ExplicitVarSizeWithDummy[q10] = 6 - | q10 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q11] = 6 -> x_ExplicitVarSizeWithDummy[q11 + 1] = 6 | q11 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q12] != 6) | q12 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q15] != 6 -> - or([x_ExplicitVarSizeWithFlags_Flags[q17] /\ - x_ExplicitVarSizeWithFlags_Values[q17] = x_ExplicitVarSizeWithDummy[q15] - | q17 : int(1..4)]) - | q15 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q19] -> - or([x_ExplicitVarSizeWithDummy[q21] != 6 /\ - x_ExplicitVarSizeWithDummy[q21] = x_ExplicitVarSizeWithFlags_Values[q19] - | q21 : int(1..4)]) - | q19 : int(1..4)]), - and([q22 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> - y_ExplicitVarSizeWithMarker_Values[q22] < y_ExplicitVarSizeWithMarker_Values[q22 + 1] - | q22 : int(1..3)]), - and([q23 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q23] = 2 | q23 : int(1..4)]), - 1 <= y_ExplicitVarSizeWithMarker_Marker, - and([q26 <= y_ExplicitVarSizeWithMarker_Marker -> - or([y_ExplicitVarSizeWithDummy[q28] != 6 /\ - y_ExplicitVarSizeWithDummy[q28] = y_ExplicitVarSizeWithMarker_Values[q26] - | q28 : int(1..4)]) - | q26 : int(1..4)]), - and([y_ExplicitVarSizeWithDummy[q30] != 6 -> - or([q32 <= y_ExplicitVarSizeWithMarker_Marker /\ - y_ExplicitVarSizeWithMarker_Values[q32] = y_ExplicitVarSizeWithDummy[q30] - | q32 : int(1..4)]) - | q30 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_4_2_2_4-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_4_2_2_4-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_2_2_4-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_4_2_2_4-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_4_2_2_4-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_2_2_4-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_4_2_2_4.eprime b/tests/exhaustive/basic/set09/expected/model_4_2_2_4.eprime deleted file mode 100644 index fbaabfe3f8..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_2_2_4.eprime +++ /dev/null @@ -1,57 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -branching on - [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, - y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithDummy] -such that - and([x_ExplicitVarSizeWithFlags_Flags[q35] /\ y_ExplicitVarSizeWithDummy[q36] != 6 -> - x_ExplicitVarSizeWithFlags_Values[q35] + 2 = y_ExplicitVarSizeWithDummy[q36] - | q35 : int(1..4), q36 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 2 | q2 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]), - and([y_ExplicitVarSizeWithDummy[q6] < y_ExplicitVarSizeWithDummy[q6 + 1] \/ y_ExplicitVarSizeWithDummy[q6] = 6 - | q6 : int(1..3)]), - and([y_ExplicitVarSizeWithDummy[q7] = 6 -> y_ExplicitVarSizeWithDummy[q7 + 1] = 6 | q7 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q8] != 6) | q8 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q10] < x_ExplicitVarSizeWithDummy[q10 + 1] \/ x_ExplicitVarSizeWithDummy[q10] = 6 - | q10 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q11] = 6 -> x_ExplicitVarSizeWithDummy[q11 + 1] = 6 | q11 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q12] != 6) | q12 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q15] != 6 -> - or([x_ExplicitVarSizeWithFlags_Flags[q17] /\ - x_ExplicitVarSizeWithFlags_Values[q17] = x_ExplicitVarSizeWithDummy[q15] - | q17 : int(1..4)]) - | q15 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q19] -> - or([x_ExplicitVarSizeWithDummy[q21] != 6 /\ - x_ExplicitVarSizeWithDummy[q21] = x_ExplicitVarSizeWithFlags_Values[q19] - | q21 : int(1..4)]) - | q19 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q22 + 1] -> - y_ExplicitVarSizeWithFlags_Values[q22] < y_ExplicitVarSizeWithFlags_Values[q22 + 1] - | q22 : int(1..3)]), - and([y_ExplicitVarSizeWithFlags_Flags[q23] = false -> y_ExplicitVarSizeWithFlags_Values[q23] = 2 - | q23 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q24 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q24] | q24 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q25]) | q25 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q28] -> - or([y_ExplicitVarSizeWithDummy[q30] != 6 /\ - y_ExplicitVarSizeWithDummy[q30] = y_ExplicitVarSizeWithFlags_Values[q28] - | q30 : int(1..4)]) - | q28 : int(1..4)]), - and([y_ExplicitVarSizeWithDummy[q32] != 6 -> - or([y_ExplicitVarSizeWithFlags_Flags[q34] /\ - y_ExplicitVarSizeWithFlags_Values[q34] = y_ExplicitVarSizeWithDummy[q32] - | q34 : int(1..4)]) - | q32 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_4_2_3_1-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_4_2_3_1-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_2_3_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_4_2_3_1-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_4_2_3_1-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_2_3_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_4_2_3_1.eprime b/tests/exhaustive/basic/set09/expected/model_4_2_3_1.eprime deleted file mode 100644 index 457cc6deb1..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_2_3_1.eprime +++ /dev/null @@ -1,46 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -find y_Occurrence: matrix indexed by [int(2..5)] of bool -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithFlags_Flags, - x_ExplicitVarSizeWithFlags_Values, y_Occurrence, y_ExplicitVarSizeWithDummy] -such that - and([x_ExplicitVarSizeWithFlags_Flags[q27] /\ y_ExplicitVarSizeWithDummy[q28] != 6 -> - x_ExplicitVarSizeWithFlags_Values[q27] + 2 = y_ExplicitVarSizeWithDummy[q28] - | q27 : int(1..4), q28 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 2 | q2 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]), - and([y_ExplicitVarSizeWithDummy[q6] < y_ExplicitVarSizeWithDummy[q6 + 1] \/ y_ExplicitVarSizeWithDummy[q6] = 6 - | q6 : int(1..3)]), - and([y_ExplicitVarSizeWithDummy[q7] = 6 -> y_ExplicitVarSizeWithDummy[q7 + 1] = 6 | q7 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q8] != 6) | q8 : int(1..4)]), - and([q10 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q10] < x_ExplicitVarSizeWithMarker_Values[q10 + 1] - | q10 : int(1..3)]), - and([q11 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q11] = 2 | q11 : int(1..4)]), - 1 <= x_ExplicitVarSizeWithMarker_Marker, - and([q14 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q16] /\ - x_ExplicitVarSizeWithFlags_Values[q16] = x_ExplicitVarSizeWithMarker_Values[q14] - | q16 : int(1..4)]) - | q14 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q18] -> - or([q20 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q20] = x_ExplicitVarSizeWithFlags_Values[q18] - | q20 : int(1..4)]) - | q18 : int(1..4)]), - 1 <= sum([toInt(y_Occurrence[q21]) | q21 : int(2..5)]), - and([y_Occurrence[q22] -> - or([y_ExplicitVarSizeWithDummy[q24] != 6 /\ y_ExplicitVarSizeWithDummy[q24] = q22 | q24 : int(1..4)]) - | q22 : int(2..5)]), - and([y_ExplicitVarSizeWithDummy[q26] != 6 -> y_Occurrence[y_ExplicitVarSizeWithDummy[q26]] | q26 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_4_2_3_2-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_4_2_3_2-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_2_3_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_4_2_3_2-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_4_2_3_2-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_2_3_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_4_2_3_2.eprime b/tests/exhaustive/basic/set09/expected/model_4_2_3_2.eprime deleted file mode 100644 index 1fdcd43cc3..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_2_3_2.eprime +++ /dev/null @@ -1,40 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithFlags_Flags, - x_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithDummy] -such that - and([x_ExplicitVarSizeWithFlags_Flags[q21] /\ y_ExplicitVarSizeWithDummy[q22] != 6 -> - x_ExplicitVarSizeWithFlags_Values[q21] + 2 = y_ExplicitVarSizeWithDummy[q22] - | q21 : int(1..4), q22 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 2 | q2 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]), - and([y_ExplicitVarSizeWithDummy[q6] < y_ExplicitVarSizeWithDummy[q6 + 1] \/ y_ExplicitVarSizeWithDummy[q6] = 6 - | q6 : int(1..3)]), - and([y_ExplicitVarSizeWithDummy[q7] = 6 -> y_ExplicitVarSizeWithDummy[q7 + 1] = 6 | q7 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q8] != 6) | q8 : int(1..4)]), - and([q10 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q10] < x_ExplicitVarSizeWithMarker_Values[q10 + 1] - | q10 : int(1..3)]), - and([q11 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q11] = 2 | q11 : int(1..4)]), - 1 <= x_ExplicitVarSizeWithMarker_Marker, - and([q14 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q16] /\ - x_ExplicitVarSizeWithFlags_Values[q16] = x_ExplicitVarSizeWithMarker_Values[q14] - | q16 : int(1..4)]) - | q14 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q18] -> - or([q20 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q20] = x_ExplicitVarSizeWithFlags_Values[q18] - | q20 : int(1..4)]) - | q18 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_4_2_3_3-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_4_2_3_3-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_2_3_3-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_4_2_3_3-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_4_2_3_3-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_2_3_3-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_4_2_3_3.eprime b/tests/exhaustive/basic/set09/expected/model_4_2_3_3.eprime deleted file mode 100644 index 18c16908d3..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_2_3_3.eprime +++ /dev/null @@ -1,58 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -find y_ExplicitVarSizeWithMarker_Marker: int(0..4) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithFlags_Flags, - x_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values, - y_ExplicitVarSizeWithDummy] -such that - and([x_ExplicitVarSizeWithFlags_Flags[q32] /\ y_ExplicitVarSizeWithDummy[q33] != 6 -> - x_ExplicitVarSizeWithFlags_Values[q32] + 2 = y_ExplicitVarSizeWithDummy[q33] - | q32 : int(1..4), q33 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 2 | q2 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]), - and([y_ExplicitVarSizeWithDummy[q6] < y_ExplicitVarSizeWithDummy[q6 + 1] \/ y_ExplicitVarSizeWithDummy[q6] = 6 - | q6 : int(1..3)]), - and([y_ExplicitVarSizeWithDummy[q7] = 6 -> y_ExplicitVarSizeWithDummy[q7 + 1] = 6 | q7 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q8] != 6) | q8 : int(1..4)]), - and([q10 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q10] < x_ExplicitVarSizeWithMarker_Values[q10 + 1] - | q10 : int(1..3)]), - and([q11 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q11] = 2 | q11 : int(1..4)]), - 1 <= x_ExplicitVarSizeWithMarker_Marker, - and([q14 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q16] /\ - x_ExplicitVarSizeWithFlags_Values[q16] = x_ExplicitVarSizeWithMarker_Values[q14] - | q16 : int(1..4)]) - | q14 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q18] -> - or([q20 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q20] = x_ExplicitVarSizeWithFlags_Values[q18] - | q20 : int(1..4)]) - | q18 : int(1..4)]), - and([q21 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> - y_ExplicitVarSizeWithMarker_Values[q21] < y_ExplicitVarSizeWithMarker_Values[q21 + 1] - | q21 : int(1..3)]), - and([q22 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q22] = 2 | q22 : int(1..4)]), - 1 <= y_ExplicitVarSizeWithMarker_Marker, - and([q25 <= y_ExplicitVarSizeWithMarker_Marker -> - or([y_ExplicitVarSizeWithDummy[q27] != 6 /\ - y_ExplicitVarSizeWithDummy[q27] = y_ExplicitVarSizeWithMarker_Values[q25] - | q27 : int(1..4)]) - | q25 : int(1..4)]), - and([y_ExplicitVarSizeWithDummy[q29] != 6 -> - or([q31 <= y_ExplicitVarSizeWithMarker_Marker /\ - y_ExplicitVarSizeWithMarker_Values[q31] = y_ExplicitVarSizeWithDummy[q29] - | q31 : int(1..4)]) - | q29 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_4_2_3_4-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_4_2_3_4-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_2_3_4-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_4_2_3_4-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_4_2_3_4-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_2_3_4-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_4_2_3_4.eprime b/tests/exhaustive/basic/set09/expected/model_4_2_3_4.eprime deleted file mode 100644 index d099b0582b..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_2_3_4.eprime +++ /dev/null @@ -1,60 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithFlags_Flags, - x_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values, - y_ExplicitVarSizeWithDummy] -such that - and([x_ExplicitVarSizeWithFlags_Flags[q34] /\ y_ExplicitVarSizeWithDummy[q35] != 6 -> - x_ExplicitVarSizeWithFlags_Values[q34] + 2 = y_ExplicitVarSizeWithDummy[q35] - | q34 : int(1..4), q35 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 2 | q2 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]), - and([y_ExplicitVarSizeWithDummy[q6] < y_ExplicitVarSizeWithDummy[q6 + 1] \/ y_ExplicitVarSizeWithDummy[q6] = 6 - | q6 : int(1..3)]), - and([y_ExplicitVarSizeWithDummy[q7] = 6 -> y_ExplicitVarSizeWithDummy[q7 + 1] = 6 | q7 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q8] != 6) | q8 : int(1..4)]), - and([q10 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q10] < x_ExplicitVarSizeWithMarker_Values[q10 + 1] - | q10 : int(1..3)]), - and([q11 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q11] = 2 | q11 : int(1..4)]), - 1 <= x_ExplicitVarSizeWithMarker_Marker, - and([q14 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q16] /\ - x_ExplicitVarSizeWithFlags_Values[q16] = x_ExplicitVarSizeWithMarker_Values[q14] - | q16 : int(1..4)]) - | q14 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q18] -> - or([q20 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q20] = x_ExplicitVarSizeWithFlags_Values[q18] - | q20 : int(1..4)]) - | q18 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q21 + 1] -> - y_ExplicitVarSizeWithFlags_Values[q21] < y_ExplicitVarSizeWithFlags_Values[q21 + 1] - | q21 : int(1..3)]), - and([y_ExplicitVarSizeWithFlags_Flags[q22] = false -> y_ExplicitVarSizeWithFlags_Values[q22] = 2 - | q22 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q23 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q23] | q23 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q24]) | q24 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q27] -> - or([y_ExplicitVarSizeWithDummy[q29] != 6 /\ - y_ExplicitVarSizeWithDummy[q29] = y_ExplicitVarSizeWithFlags_Values[q27] - | q29 : int(1..4)]) - | q27 : int(1..4)]), - and([y_ExplicitVarSizeWithDummy[q31] != 6 -> - or([y_ExplicitVarSizeWithFlags_Flags[q33] /\ - y_ExplicitVarSizeWithFlags_Values[q33] = y_ExplicitVarSizeWithDummy[q31] - | q33 : int(1..4)]) - | q31 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_4_2_4_1-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_4_2_4_1-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_2_4_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_4_2_4_1-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_4_2_4_1-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_2_4_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_4_2_4_1.eprime b/tests/exhaustive/basic/set09/expected/model_4_2_4_1.eprime deleted file mode 100644 index f587016cd9..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_2_4_1.eprime +++ /dev/null @@ -1,28 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -find y_Occurrence: matrix indexed by [int(2..5)] of bool -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, y_Occurrence, y_ExplicitVarSizeWithDummy] -such that - and([x_ExplicitVarSizeWithFlags_Flags[q16] /\ y_ExplicitVarSizeWithDummy[q17] != 6 -> - x_ExplicitVarSizeWithFlags_Values[q16] + 2 = y_ExplicitVarSizeWithDummy[q17] - | q16 : int(1..4), q17 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 2 | q2 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]), - and([y_ExplicitVarSizeWithDummy[q6] < y_ExplicitVarSizeWithDummy[q6 + 1] \/ y_ExplicitVarSizeWithDummy[q6] = 6 - | q6 : int(1..3)]), - and([y_ExplicitVarSizeWithDummy[q7] = 6 -> y_ExplicitVarSizeWithDummy[q7 + 1] = 6 | q7 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q8] != 6) | q8 : int(1..4)]), - 1 <= sum([toInt(y_Occurrence[q10]) | q10 : int(2..5)]), - and([y_Occurrence[q11] -> - or([y_ExplicitVarSizeWithDummy[q13] != 6 /\ y_ExplicitVarSizeWithDummy[q13] = q11 | q13 : int(1..4)]) - | q11 : int(2..5)]), - and([y_ExplicitVarSizeWithDummy[q15] != 6 -> y_Occurrence[y_ExplicitVarSizeWithDummy[q15]] | q15 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_4_2_4_2-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_4_2_4_2-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_2_4_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_4_2_4_2-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_4_2_4_2-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_2_4_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_4_2_4_2.eprime b/tests/exhaustive/basic/set09/expected/model_4_2_4_2.eprime deleted file mode 100644 index f30467528a..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_2_4_2.eprime +++ /dev/null @@ -1,21 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -branching on [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithDummy] -such that - and([x_ExplicitVarSizeWithFlags_Flags[q10] /\ y_ExplicitVarSizeWithDummy[q11] != 6 -> - x_ExplicitVarSizeWithFlags_Values[q10] + 2 = y_ExplicitVarSizeWithDummy[q11] - | q10 : int(1..4), q11 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 2 | q2 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]), - and([y_ExplicitVarSizeWithDummy[q6] < y_ExplicitVarSizeWithDummy[q6 + 1] \/ y_ExplicitVarSizeWithDummy[q6] = 6 - | q6 : int(1..3)]), - and([y_ExplicitVarSizeWithDummy[q7] = 6 -> y_ExplicitVarSizeWithDummy[q7 + 1] = 6 | q7 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q8] != 6) | q8 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_4_2_4_3-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_4_2_4_3-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_2_4_3-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_4_2_4_3-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_4_2_4_3-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_2_4_3-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_4_2_4_3.eprime b/tests/exhaustive/basic/set09/expected/model_4_2_4_3.eprime deleted file mode 100644 index e871f919f3..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_2_4_3.eprime +++ /dev/null @@ -1,40 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -find y_ExplicitVarSizeWithMarker_Marker: int(0..4) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithMarker_Marker, - y_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithDummy] -such that - and([x_ExplicitVarSizeWithFlags_Flags[q21] /\ y_ExplicitVarSizeWithDummy[q22] != 6 -> - x_ExplicitVarSizeWithFlags_Values[q21] + 2 = y_ExplicitVarSizeWithDummy[q22] - | q21 : int(1..4), q22 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 2 | q2 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]), - and([y_ExplicitVarSizeWithDummy[q6] < y_ExplicitVarSizeWithDummy[q6 + 1] \/ y_ExplicitVarSizeWithDummy[q6] = 6 - | q6 : int(1..3)]), - and([y_ExplicitVarSizeWithDummy[q7] = 6 -> y_ExplicitVarSizeWithDummy[q7 + 1] = 6 | q7 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q8] != 6) | q8 : int(1..4)]), - and([q10 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> - y_ExplicitVarSizeWithMarker_Values[q10] < y_ExplicitVarSizeWithMarker_Values[q10 + 1] - | q10 : int(1..3)]), - and([q11 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q11] = 2 | q11 : int(1..4)]), - 1 <= y_ExplicitVarSizeWithMarker_Marker, - and([q14 <= y_ExplicitVarSizeWithMarker_Marker -> - or([y_ExplicitVarSizeWithDummy[q16] != 6 /\ - y_ExplicitVarSizeWithDummy[q16] = y_ExplicitVarSizeWithMarker_Values[q14] - | q16 : int(1..4)]) - | q14 : int(1..4)]), - and([y_ExplicitVarSizeWithDummy[q18] != 6 -> - or([q20 <= y_ExplicitVarSizeWithMarker_Marker /\ - y_ExplicitVarSizeWithMarker_Values[q20] = y_ExplicitVarSizeWithDummy[q18] - | q20 : int(1..4)]) - | q18 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_4_2_4_4-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_4_2_4_4-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_2_4_4-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_4_2_4_4-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_4_2_4_4-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_2_4_4-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_4_2_4_4.eprime b/tests/exhaustive/basic/set09/expected/model_4_2_4_4.eprime deleted file mode 100644 index 8954f9bfa2..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_2_4_4.eprime +++ /dev/null @@ -1,42 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithFlags_Flags, - y_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithDummy] -such that - and([x_ExplicitVarSizeWithFlags_Flags[q23] /\ y_ExplicitVarSizeWithDummy[q24] != 6 -> - x_ExplicitVarSizeWithFlags_Values[q23] + 2 = y_ExplicitVarSizeWithDummy[q24] - | q23 : int(1..4), q24 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 2 | q2 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]), - and([y_ExplicitVarSizeWithDummy[q6] < y_ExplicitVarSizeWithDummy[q6 + 1] \/ y_ExplicitVarSizeWithDummy[q6] = 6 - | q6 : int(1..3)]), - and([y_ExplicitVarSizeWithDummy[q7] = 6 -> y_ExplicitVarSizeWithDummy[q7 + 1] = 6 | q7 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q8] != 6) | q8 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q10 + 1] -> - y_ExplicitVarSizeWithFlags_Values[q10] < y_ExplicitVarSizeWithFlags_Values[q10 + 1] - | q10 : int(1..3)]), - and([y_ExplicitVarSizeWithFlags_Flags[q11] = false -> y_ExplicitVarSizeWithFlags_Values[q11] = 2 - | q11 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q12 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q12] | q12 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q13]) | q13 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q16] -> - or([y_ExplicitVarSizeWithDummy[q18] != 6 /\ - y_ExplicitVarSizeWithDummy[q18] = y_ExplicitVarSizeWithFlags_Values[q16] - | q18 : int(1..4)]) - | q16 : int(1..4)]), - and([y_ExplicitVarSizeWithDummy[q20] != 6 -> - or([y_ExplicitVarSizeWithFlags_Flags[q22] /\ - y_ExplicitVarSizeWithFlags_Values[q22] = y_ExplicitVarSizeWithDummy[q20] - | q22 : int(1..4)]) - | q20 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_4_3_1_1-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_4_3_1_1-solution000001.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_3_1_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_4_3_1_1-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_4_3_1_1-solution000002.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_3_1_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_4_3_1_1.eprime b/tests/exhaustive/basic/set09/expected/model_4_3_1_1.eprime deleted file mode 100644 index e2ae63fc2c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_3_1_1.eprime +++ /dev/null @@ -1,40 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -find x_Occurrence: matrix indexed by [int(2..5)] of bool -find y_ExplicitVarSizeWithMarker_Marker: int(0..4) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_Occurrence: matrix indexed by [int(2..5)] of bool -branching on - [x_Occurrence, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, y_Occurrence, - y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values] -such that - and([x_ExplicitVarSizeWithFlags_Flags[q16] /\ q17 <= y_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithFlags_Values[q16] + 2 = y_ExplicitVarSizeWithMarker_Values[q17] - | q16 : int(1..4), q17 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 2 | q2 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]), - and([q6 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> - y_ExplicitVarSizeWithMarker_Values[q6] < y_ExplicitVarSizeWithMarker_Values[q6 + 1] - | q6 : int(1..3)]), - and([q7 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q7] = 2 | q7 : int(1..4)]), - 1 <= y_ExplicitVarSizeWithMarker_Marker, - 1 <= sum([toInt(x_Occurrence[q9]) | q9 : int(2..5)]), - and([x_Occurrence[q18] -> - or([x_ExplicitVarSizeWithFlags_Flags[q20] /\ x_ExplicitVarSizeWithFlags_Values[q20] = q18 | q20 : int(1..4)]) - | q18 : int(2..5)]), - and([x_ExplicitVarSizeWithFlags_Flags[q22] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q22]] - | q22 : int(1..4)]), - 1 <= sum([toInt(y_Occurrence[q10]) | q10 : int(2..5)]), - and([y_Occurrence[q11] -> - or([q13 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[q13] = q11 - | q13 : int(1..4)]) - | q11 : int(2..5)]), - and([q15 <= y_ExplicitVarSizeWithMarker_Marker -> y_Occurrence[y_ExplicitVarSizeWithMarker_Values[q15]] - | q15 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_4_3_1_2-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_4_3_1_2-solution000001.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_3_1_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_4_3_1_2-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_4_3_1_2-solution000002.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_3_1_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_4_3_1_2.eprime b/tests/exhaustive/basic/set09/expected/model_4_3_1_2.eprime deleted file mode 100644 index ae45352286..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_3_1_2.eprime +++ /dev/null @@ -1,47 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -find x_Occurrence: matrix indexed by [int(2..5)] of bool -find y_ExplicitVarSizeWithMarker_Marker: int(0..4) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -branching on - [x_Occurrence, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithDummy, - y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values] -such that - and([x_ExplicitVarSizeWithFlags_Flags[q27] /\ q28 <= y_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithFlags_Values[q27] + 2 = y_ExplicitVarSizeWithMarker_Values[q28] - | q27 : int(1..4), q28 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 2 | q2 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]), - and([q6 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> - y_ExplicitVarSizeWithMarker_Values[q6] < y_ExplicitVarSizeWithMarker_Values[q6 + 1] - | q6 : int(1..3)]), - and([q7 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q7] = 2 | q7 : int(1..4)]), - 1 <= y_ExplicitVarSizeWithMarker_Marker, - 1 <= sum([toInt(x_Occurrence[q9]) | q9 : int(2..5)]), - and([x_Occurrence[q22] -> - or([x_ExplicitVarSizeWithFlags_Flags[q24] /\ x_ExplicitVarSizeWithFlags_Values[q24] = q22 | q24 : int(1..4)]) - | q22 : int(2..5)]), - and([x_ExplicitVarSizeWithFlags_Flags[q26] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q26]] - | q26 : int(1..4)]), - and([y_ExplicitVarSizeWithDummy[q10] < y_ExplicitVarSizeWithDummy[q10 + 1] \/ y_ExplicitVarSizeWithDummy[q10] = 6 - | q10 : int(1..3)]), - and([y_ExplicitVarSizeWithDummy[q11] = 6 -> y_ExplicitVarSizeWithDummy[q11 + 1] = 6 | q11 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q12] != 6) | q12 : int(1..4)]), - and([y_ExplicitVarSizeWithDummy[q15] != 6 -> - or([q17 <= y_ExplicitVarSizeWithMarker_Marker /\ - y_ExplicitVarSizeWithMarker_Values[q17] = y_ExplicitVarSizeWithDummy[q15] - | q17 : int(1..4)]) - | q15 : int(1..4)]), - and([q19 <= y_ExplicitVarSizeWithMarker_Marker -> - or([y_ExplicitVarSizeWithDummy[q21] != 6 /\ - y_ExplicitVarSizeWithDummy[q21] = y_ExplicitVarSizeWithMarker_Values[q19] - | q21 : int(1..4)]) - | q19 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_4_3_1_3-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_4_3_1_3-solution000001.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_3_1_3-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_4_3_1_3-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_4_3_1_3-solution000002.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_3_1_3-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_4_3_1_3.eprime b/tests/exhaustive/basic/set09/expected/model_4_3_1_3.eprime deleted file mode 100644 index cd001ff305..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_3_1_3.eprime +++ /dev/null @@ -1,32 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -find x_Occurrence: matrix indexed by [int(2..5)] of bool -find y_ExplicitVarSizeWithMarker_Marker: int(0..4) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -branching on - [x_Occurrence, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, - y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values] -such that - and([x_ExplicitVarSizeWithFlags_Flags[q15] /\ q16 <= y_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithFlags_Values[q15] + 2 = y_ExplicitVarSizeWithMarker_Values[q16] - | q15 : int(1..4), q16 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 2 | q2 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]), - and([q6 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> - y_ExplicitVarSizeWithMarker_Values[q6] < y_ExplicitVarSizeWithMarker_Values[q6 + 1] - | q6 : int(1..3)]), - and([q7 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q7] = 2 | q7 : int(1..4)]), - 1 <= y_ExplicitVarSizeWithMarker_Marker, - 1 <= sum([toInt(x_Occurrence[q9]) | q9 : int(2..5)]), - and([x_Occurrence[q10] -> - or([x_ExplicitVarSizeWithFlags_Flags[q12] /\ x_ExplicitVarSizeWithFlags_Values[q12] = q10 | q12 : int(1..4)]) - | q10 : int(2..5)]), - and([x_ExplicitVarSizeWithFlags_Flags[q14] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q14]] - | q14 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_4_3_1_4-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_4_3_1_4-solution000001.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_3_1_4-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_4_3_1_4-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_4_3_1_4-solution000002.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_3_1_4-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_4_3_1_4.eprime b/tests/exhaustive/basic/set09/expected/model_4_3_1_4.eprime deleted file mode 100644 index c1ff4e46c8..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_3_1_4.eprime +++ /dev/null @@ -1,52 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -find x_Occurrence: matrix indexed by [int(2..5)] of bool -find y_ExplicitVarSizeWithMarker_Marker: int(0..4) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -branching on - [x_Occurrence, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, - y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithMarker_Marker, - y_ExplicitVarSizeWithMarker_Values] -such that - and([x_ExplicitVarSizeWithFlags_Flags[q28] /\ q29 <= y_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithFlags_Values[q28] + 2 = y_ExplicitVarSizeWithMarker_Values[q29] - | q28 : int(1..4), q29 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 2 | q2 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]), - and([q6 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> - y_ExplicitVarSizeWithMarker_Values[q6] < y_ExplicitVarSizeWithMarker_Values[q6 + 1] - | q6 : int(1..3)]), - and([q7 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q7] = 2 | q7 : int(1..4)]), - 1 <= y_ExplicitVarSizeWithMarker_Marker, - 1 <= sum([toInt(x_Occurrence[q9]) | q9 : int(2..5)]), - and([x_Occurrence[q23] -> - or([x_ExplicitVarSizeWithFlags_Flags[q25] /\ x_ExplicitVarSizeWithFlags_Values[q25] = q23 | q25 : int(1..4)]) - | q23 : int(2..5)]), - and([x_ExplicitVarSizeWithFlags_Flags[q27] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q27]] - | q27 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q10 + 1] -> - y_ExplicitVarSizeWithFlags_Values[q10] < y_ExplicitVarSizeWithFlags_Values[q10 + 1] - | q10 : int(1..3)]), - and([y_ExplicitVarSizeWithFlags_Flags[q11] = false -> y_ExplicitVarSizeWithFlags_Values[q11] = 2 - | q11 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q12 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q12] | q12 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q13]) | q13 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q16] -> - or([q18 <= y_ExplicitVarSizeWithMarker_Marker /\ - y_ExplicitVarSizeWithMarker_Values[q18] = y_ExplicitVarSizeWithFlags_Values[q16] - | q18 : int(1..4)]) - | q16 : int(1..4)]), - and([q20 <= y_ExplicitVarSizeWithMarker_Marker -> - or([y_ExplicitVarSizeWithFlags_Flags[q22] /\ - y_ExplicitVarSizeWithFlags_Values[q22] = y_ExplicitVarSizeWithMarker_Values[q20] - | q22 : int(1..4)]) - | q20 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_4_3_2_1-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_4_3_2_1-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_3_2_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_4_3_2_1-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_4_3_2_1-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_3_2_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_4_3_2_1.eprime b/tests/exhaustive/basic/set09/expected/model_4_3_2_1.eprime deleted file mode 100644 index ebbb2075a2..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_3_2_1.eprime +++ /dev/null @@ -1,48 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -find y_ExplicitVarSizeWithMarker_Marker: int(0..4) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_Occurrence: matrix indexed by [int(2..5)] of bool -branching on - [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, y_Occurrence, - y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values] -such that - and([x_ExplicitVarSizeWithFlags_Flags[q27] /\ q28 <= y_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithFlags_Values[q27] + 2 = y_ExplicitVarSizeWithMarker_Values[q28] - | q27 : int(1..4), q28 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 2 | q2 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]), - and([q6 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> - y_ExplicitVarSizeWithMarker_Values[q6] < y_ExplicitVarSizeWithMarker_Values[q6 + 1] - | q6 : int(1..3)]), - and([q7 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q7] = 2 | q7 : int(1..4)]), - 1 <= y_ExplicitVarSizeWithMarker_Marker, - and([x_ExplicitVarSizeWithDummy[q9] < x_ExplicitVarSizeWithDummy[q9 + 1] \/ x_ExplicitVarSizeWithDummy[q9] = 6 - | q9 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q10] = 6 -> x_ExplicitVarSizeWithDummy[q10 + 1] = 6 | q10 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q11] != 6) | q11 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q14] != 6 -> - or([x_ExplicitVarSizeWithFlags_Flags[q16] /\ - x_ExplicitVarSizeWithFlags_Values[q16] = x_ExplicitVarSizeWithDummy[q14] - | q16 : int(1..4)]) - | q14 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q18] -> - or([x_ExplicitVarSizeWithDummy[q20] != 6 /\ - x_ExplicitVarSizeWithDummy[q20] = x_ExplicitVarSizeWithFlags_Values[q18] - | q20 : int(1..4)]) - | q18 : int(1..4)]), - 1 <= sum([toInt(y_Occurrence[q21]) | q21 : int(2..5)]), - and([y_Occurrence[q22] -> - or([q24 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[q24] = q22 - | q24 : int(1..4)]) - | q22 : int(2..5)]), - and([q26 <= y_ExplicitVarSizeWithMarker_Marker -> y_Occurrence[y_ExplicitVarSizeWithMarker_Values[q26]] - | q26 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_4_3_2_2-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_4_3_2_2-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_3_2_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_4_3_2_2-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_4_3_2_2-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_3_2_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_4_3_2_2.eprime b/tests/exhaustive/basic/set09/expected/model_4_3_2_2.eprime deleted file mode 100644 index 96ae673549..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_3_2_2.eprime +++ /dev/null @@ -1,55 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -find y_ExplicitVarSizeWithMarker_Marker: int(0..4) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -branching on - [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, - y_ExplicitVarSizeWithDummy, y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values] -such that - and([x_ExplicitVarSizeWithFlags_Flags[q33] /\ q34 <= y_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithFlags_Values[q33] + 2 = y_ExplicitVarSizeWithMarker_Values[q34] - | q33 : int(1..4), q34 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 2 | q2 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]), - and([q6 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> - y_ExplicitVarSizeWithMarker_Values[q6] < y_ExplicitVarSizeWithMarker_Values[q6 + 1] - | q6 : int(1..3)]), - and([q7 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q7] = 2 | q7 : int(1..4)]), - 1 <= y_ExplicitVarSizeWithMarker_Marker, - and([x_ExplicitVarSizeWithDummy[q9] < x_ExplicitVarSizeWithDummy[q9 + 1] \/ x_ExplicitVarSizeWithDummy[q9] = 6 - | q9 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q10] = 6 -> x_ExplicitVarSizeWithDummy[q10 + 1] = 6 | q10 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q11] != 6) | q11 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q14] != 6 -> - or([x_ExplicitVarSizeWithFlags_Flags[q16] /\ - x_ExplicitVarSizeWithFlags_Values[q16] = x_ExplicitVarSizeWithDummy[q14] - | q16 : int(1..4)]) - | q14 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q18] -> - or([x_ExplicitVarSizeWithDummy[q20] != 6 /\ - x_ExplicitVarSizeWithDummy[q20] = x_ExplicitVarSizeWithFlags_Values[q18] - | q20 : int(1..4)]) - | q18 : int(1..4)]), - and([y_ExplicitVarSizeWithDummy[q21] < y_ExplicitVarSizeWithDummy[q21 + 1] \/ y_ExplicitVarSizeWithDummy[q21] = 6 - | q21 : int(1..3)]), - and([y_ExplicitVarSizeWithDummy[q22] = 6 -> y_ExplicitVarSizeWithDummy[q22 + 1] = 6 | q22 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q23] != 6) | q23 : int(1..4)]), - and([y_ExplicitVarSizeWithDummy[q26] != 6 -> - or([q28 <= y_ExplicitVarSizeWithMarker_Marker /\ - y_ExplicitVarSizeWithMarker_Values[q28] = y_ExplicitVarSizeWithDummy[q26] - | q28 : int(1..4)]) - | q26 : int(1..4)]), - and([q30 <= y_ExplicitVarSizeWithMarker_Marker -> - or([y_ExplicitVarSizeWithDummy[q32] != 6 /\ - y_ExplicitVarSizeWithDummy[q32] = y_ExplicitVarSizeWithMarker_Values[q30] - | q32 : int(1..4)]) - | q30 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_4_3_2_3-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_4_3_2_3-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_3_2_3-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_4_3_2_3-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_4_3_2_3-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_3_2_3-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_4_3_2_3.eprime b/tests/exhaustive/basic/set09/expected/model_4_3_2_3.eprime deleted file mode 100644 index 6f50c8c681..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_3_2_3.eprime +++ /dev/null @@ -1,40 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -find y_ExplicitVarSizeWithMarker_Marker: int(0..4) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -branching on - [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, - y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values] -such that - and([x_ExplicitVarSizeWithFlags_Flags[q21] /\ q22 <= y_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithFlags_Values[q21] + 2 = y_ExplicitVarSizeWithMarker_Values[q22] - | q21 : int(1..4), q22 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 2 | q2 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]), - and([q6 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> - y_ExplicitVarSizeWithMarker_Values[q6] < y_ExplicitVarSizeWithMarker_Values[q6 + 1] - | q6 : int(1..3)]), - and([q7 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q7] = 2 | q7 : int(1..4)]), - 1 <= y_ExplicitVarSizeWithMarker_Marker, - and([x_ExplicitVarSizeWithDummy[q9] < x_ExplicitVarSizeWithDummy[q9 + 1] \/ x_ExplicitVarSizeWithDummy[q9] = 6 - | q9 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q10] = 6 -> x_ExplicitVarSizeWithDummy[q10 + 1] = 6 | q10 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q11] != 6) | q11 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q14] != 6 -> - or([x_ExplicitVarSizeWithFlags_Flags[q16] /\ - x_ExplicitVarSizeWithFlags_Values[q16] = x_ExplicitVarSizeWithDummy[q14] - | q16 : int(1..4)]) - | q14 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q18] -> - or([x_ExplicitVarSizeWithDummy[q20] != 6 /\ - x_ExplicitVarSizeWithDummy[q20] = x_ExplicitVarSizeWithFlags_Values[q18] - | q20 : int(1..4)]) - | q18 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_4_3_2_4-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_4_3_2_4-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_3_2_4-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_4_3_2_4-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_4_3_2_4-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_3_2_4-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_4_3_2_4.eprime b/tests/exhaustive/basic/set09/expected/model_4_3_2_4.eprime deleted file mode 100644 index a06fe066bf..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_3_2_4.eprime +++ /dev/null @@ -1,60 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -find y_ExplicitVarSizeWithMarker_Marker: int(0..4) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -branching on - [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, - y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithMarker_Marker, - y_ExplicitVarSizeWithMarker_Values] -such that - and([x_ExplicitVarSizeWithFlags_Flags[q34] /\ q35 <= y_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithFlags_Values[q34] + 2 = y_ExplicitVarSizeWithMarker_Values[q35] - | q34 : int(1..4), q35 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 2 | q2 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]), - and([q6 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> - y_ExplicitVarSizeWithMarker_Values[q6] < y_ExplicitVarSizeWithMarker_Values[q6 + 1] - | q6 : int(1..3)]), - and([q7 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q7] = 2 | q7 : int(1..4)]), - 1 <= y_ExplicitVarSizeWithMarker_Marker, - and([x_ExplicitVarSizeWithDummy[q9] < x_ExplicitVarSizeWithDummy[q9 + 1] \/ x_ExplicitVarSizeWithDummy[q9] = 6 - | q9 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q10] = 6 -> x_ExplicitVarSizeWithDummy[q10 + 1] = 6 | q10 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q11] != 6) | q11 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q14] != 6 -> - or([x_ExplicitVarSizeWithFlags_Flags[q16] /\ - x_ExplicitVarSizeWithFlags_Values[q16] = x_ExplicitVarSizeWithDummy[q14] - | q16 : int(1..4)]) - | q14 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q18] -> - or([x_ExplicitVarSizeWithDummy[q20] != 6 /\ - x_ExplicitVarSizeWithDummy[q20] = x_ExplicitVarSizeWithFlags_Values[q18] - | q20 : int(1..4)]) - | q18 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q21 + 1] -> - y_ExplicitVarSizeWithFlags_Values[q21] < y_ExplicitVarSizeWithFlags_Values[q21 + 1] - | q21 : int(1..3)]), - and([y_ExplicitVarSizeWithFlags_Flags[q22] = false -> y_ExplicitVarSizeWithFlags_Values[q22] = 2 - | q22 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q23 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q23] | q23 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q24]) | q24 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q27] -> - or([q29 <= y_ExplicitVarSizeWithMarker_Marker /\ - y_ExplicitVarSizeWithMarker_Values[q29] = y_ExplicitVarSizeWithFlags_Values[q27] - | q29 : int(1..4)]) - | q27 : int(1..4)]), - and([q31 <= y_ExplicitVarSizeWithMarker_Marker -> - or([y_ExplicitVarSizeWithFlags_Flags[q33] /\ - y_ExplicitVarSizeWithFlags_Values[q33] = y_ExplicitVarSizeWithMarker_Values[q31] - | q33 : int(1..4)]) - | q31 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_4_3_3_1-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_4_3_3_1-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_3_3_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_4_3_3_1-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_4_3_3_1-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_3_3_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_4_3_3_1.eprime b/tests/exhaustive/basic/set09/expected/model_4_3_3_1.eprime deleted file mode 100644 index 956990ea06..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_3_3_1.eprime +++ /dev/null @@ -1,51 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_ExplicitVarSizeWithMarker_Marker: int(0..4) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_Occurrence: matrix indexed by [int(2..5)] of bool -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithFlags_Flags, - x_ExplicitVarSizeWithFlags_Values, y_Occurrence, y_ExplicitVarSizeWithMarker_Marker, - y_ExplicitVarSizeWithMarker_Values] -such that - and([x_ExplicitVarSizeWithFlags_Flags[q26] /\ q27 <= y_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithFlags_Values[q26] + 2 = y_ExplicitVarSizeWithMarker_Values[q27] - | q26 : int(1..4), q27 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 2 | q2 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]), - and([q6 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> - y_ExplicitVarSizeWithMarker_Values[q6] < y_ExplicitVarSizeWithMarker_Values[q6 + 1] - | q6 : int(1..3)]), - and([q7 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q7] = 2 | q7 : int(1..4)]), - 1 <= y_ExplicitVarSizeWithMarker_Marker, - and([q9 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q9] < x_ExplicitVarSizeWithMarker_Values[q9 + 1] - | q9 : int(1..3)]), - and([q10 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q10] = 2 | q10 : int(1..4)]), - 1 <= x_ExplicitVarSizeWithMarker_Marker, - and([q13 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q15] /\ - x_ExplicitVarSizeWithFlags_Values[q15] = x_ExplicitVarSizeWithMarker_Values[q13] - | q15 : int(1..4)]) - | q13 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q17] -> - or([q19 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q19] = x_ExplicitVarSizeWithFlags_Values[q17] - | q19 : int(1..4)]) - | q17 : int(1..4)]), - 1 <= sum([toInt(y_Occurrence[q20]) | q20 : int(2..5)]), - and([y_Occurrence[q21] -> - or([q23 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[q23] = q21 - | q23 : int(1..4)]) - | q21 : int(2..5)]), - and([q25 <= y_ExplicitVarSizeWithMarker_Marker -> y_Occurrence[y_ExplicitVarSizeWithMarker_Values[q25]] - | q25 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_4_3_3_2-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_4_3_3_2-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_3_3_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_4_3_3_2-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_4_3_3_2-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_3_3_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_4_3_3_2.eprime b/tests/exhaustive/basic/set09/expected/model_4_3_3_2.eprime deleted file mode 100644 index 76cc5a8aed..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_3_3_2.eprime +++ /dev/null @@ -1,58 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_ExplicitVarSizeWithMarker_Marker: int(0..4) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithFlags_Flags, - x_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithDummy, y_ExplicitVarSizeWithMarker_Marker, - y_ExplicitVarSizeWithMarker_Values] -such that - and([x_ExplicitVarSizeWithFlags_Flags[q32] /\ q33 <= y_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithFlags_Values[q32] + 2 = y_ExplicitVarSizeWithMarker_Values[q33] - | q32 : int(1..4), q33 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 2 | q2 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]), - and([q6 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> - y_ExplicitVarSizeWithMarker_Values[q6] < y_ExplicitVarSizeWithMarker_Values[q6 + 1] - | q6 : int(1..3)]), - and([q7 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q7] = 2 | q7 : int(1..4)]), - 1 <= y_ExplicitVarSizeWithMarker_Marker, - and([q9 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q9] < x_ExplicitVarSizeWithMarker_Values[q9 + 1] - | q9 : int(1..3)]), - and([q10 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q10] = 2 | q10 : int(1..4)]), - 1 <= x_ExplicitVarSizeWithMarker_Marker, - and([q13 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q15] /\ - x_ExplicitVarSizeWithFlags_Values[q15] = x_ExplicitVarSizeWithMarker_Values[q13] - | q15 : int(1..4)]) - | q13 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q17] -> - or([q19 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q19] = x_ExplicitVarSizeWithFlags_Values[q17] - | q19 : int(1..4)]) - | q17 : int(1..4)]), - and([y_ExplicitVarSizeWithDummy[q20] < y_ExplicitVarSizeWithDummy[q20 + 1] \/ y_ExplicitVarSizeWithDummy[q20] = 6 - | q20 : int(1..3)]), - and([y_ExplicitVarSizeWithDummy[q21] = 6 -> y_ExplicitVarSizeWithDummy[q21 + 1] = 6 | q21 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q22] != 6) | q22 : int(1..4)]), - and([y_ExplicitVarSizeWithDummy[q25] != 6 -> - or([q27 <= y_ExplicitVarSizeWithMarker_Marker /\ - y_ExplicitVarSizeWithMarker_Values[q27] = y_ExplicitVarSizeWithDummy[q25] - | q27 : int(1..4)]) - | q25 : int(1..4)]), - and([q29 <= y_ExplicitVarSizeWithMarker_Marker -> - or([y_ExplicitVarSizeWithDummy[q31] != 6 /\ - y_ExplicitVarSizeWithDummy[q31] = y_ExplicitVarSizeWithMarker_Values[q29] - | q31 : int(1..4)]) - | q29 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_4_3_3_3-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_4_3_3_3-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_3_3_3-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_4_3_3_3-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_4_3_3_3-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_3_3_3-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_4_3_3_3.eprime b/tests/exhaustive/basic/set09/expected/model_4_3_3_3.eprime deleted file mode 100644 index f90dae8a31..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_3_3_3.eprime +++ /dev/null @@ -1,42 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_ExplicitVarSizeWithMarker_Marker: int(0..4) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithFlags_Flags, - x_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values] -such that - and([x_ExplicitVarSizeWithFlags_Flags[q20] /\ q21 <= y_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithFlags_Values[q20] + 2 = y_ExplicitVarSizeWithMarker_Values[q21] - | q20 : int(1..4), q21 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 2 | q2 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]), - and([q6 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> - y_ExplicitVarSizeWithMarker_Values[q6] < y_ExplicitVarSizeWithMarker_Values[q6 + 1] - | q6 : int(1..3)]), - and([q7 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q7] = 2 | q7 : int(1..4)]), - 1 <= y_ExplicitVarSizeWithMarker_Marker, - and([q9 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q9] < x_ExplicitVarSizeWithMarker_Values[q9 + 1] - | q9 : int(1..3)]), - and([q10 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q10] = 2 | q10 : int(1..4)]), - 1 <= x_ExplicitVarSizeWithMarker_Marker, - and([q13 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q15] /\ - x_ExplicitVarSizeWithFlags_Values[q15] = x_ExplicitVarSizeWithMarker_Values[q13] - | q15 : int(1..4)]) - | q13 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q17] -> - or([q19 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q19] = x_ExplicitVarSizeWithFlags_Values[q17] - | q19 : int(1..4)]) - | q17 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_4_3_3_4-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_4_3_3_4-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_3_3_4-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_4_3_3_4-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_4_3_3_4-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_3_3_4-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_4_3_3_4.eprime b/tests/exhaustive/basic/set09/expected/model_4_3_3_4.eprime deleted file mode 100644 index a3ac3373bb..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_3_3_4.eprime +++ /dev/null @@ -1,62 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_ExplicitVarSizeWithMarker_Marker: int(0..4) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithFlags_Flags, - x_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values, - y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values] -such that - and([x_ExplicitVarSizeWithFlags_Flags[q33] /\ q34 <= y_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithFlags_Values[q33] + 2 = y_ExplicitVarSizeWithMarker_Values[q34] - | q33 : int(1..4), q34 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 2 | q2 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]), - and([q6 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> - y_ExplicitVarSizeWithMarker_Values[q6] < y_ExplicitVarSizeWithMarker_Values[q6 + 1] - | q6 : int(1..3)]), - and([q7 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q7] = 2 | q7 : int(1..4)]), - 1 <= y_ExplicitVarSizeWithMarker_Marker, - and([q9 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q9] < x_ExplicitVarSizeWithMarker_Values[q9 + 1] - | q9 : int(1..3)]), - and([q10 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q10] = 2 | q10 : int(1..4)]), - 1 <= x_ExplicitVarSizeWithMarker_Marker, - and([q13 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q15] /\ - x_ExplicitVarSizeWithFlags_Values[q15] = x_ExplicitVarSizeWithMarker_Values[q13] - | q15 : int(1..4)]) - | q13 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q17] -> - or([q19 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q19] = x_ExplicitVarSizeWithFlags_Values[q17] - | q19 : int(1..4)]) - | q17 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q20 + 1] -> - y_ExplicitVarSizeWithFlags_Values[q20] < y_ExplicitVarSizeWithFlags_Values[q20 + 1] - | q20 : int(1..3)]), - and([y_ExplicitVarSizeWithFlags_Flags[q21] = false -> y_ExplicitVarSizeWithFlags_Values[q21] = 2 - | q21 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q22 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q22] | q22 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q23]) | q23 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q26] -> - or([q28 <= y_ExplicitVarSizeWithMarker_Marker /\ - y_ExplicitVarSizeWithMarker_Values[q28] = y_ExplicitVarSizeWithFlags_Values[q26] - | q28 : int(1..4)]) - | q26 : int(1..4)]), - and([q30 <= y_ExplicitVarSizeWithMarker_Marker -> - or([y_ExplicitVarSizeWithFlags_Flags[q32] /\ - y_ExplicitVarSizeWithFlags_Values[q32] = y_ExplicitVarSizeWithMarker_Values[q30] - | q32 : int(1..4)]) - | q30 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_4_3_4_1-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_4_3_4_1-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_3_4_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_4_3_4_1-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_4_3_4_1-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_3_4_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_4_3_4_1.eprime b/tests/exhaustive/basic/set09/expected/model_4_3_4_1.eprime deleted file mode 100644 index d57282a34a..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_3_4_1.eprime +++ /dev/null @@ -1,33 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_ExplicitVarSizeWithMarker_Marker: int(0..4) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_Occurrence: matrix indexed by [int(2..5)] of bool -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, y_Occurrence, - y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values] -such that - and([x_ExplicitVarSizeWithFlags_Flags[q15] /\ q16 <= y_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithFlags_Values[q15] + 2 = y_ExplicitVarSizeWithMarker_Values[q16] - | q15 : int(1..4), q16 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 2 | q2 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]), - and([q6 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> - y_ExplicitVarSizeWithMarker_Values[q6] < y_ExplicitVarSizeWithMarker_Values[q6 + 1] - | q6 : int(1..3)]), - and([q7 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q7] = 2 | q7 : int(1..4)]), - 1 <= y_ExplicitVarSizeWithMarker_Marker, - 1 <= sum([toInt(y_Occurrence[q9]) | q9 : int(2..5)]), - and([y_Occurrence[q10] -> - or([q12 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[q12] = q10 - | q12 : int(1..4)]) - | q10 : int(2..5)]), - and([q14 <= y_ExplicitVarSizeWithMarker_Marker -> y_Occurrence[y_ExplicitVarSizeWithMarker_Values[q14]] - | q14 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_4_3_4_2-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_4_3_4_2-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_3_4_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_4_3_4_2-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_4_3_4_2-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_3_4_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_4_3_4_2.eprime b/tests/exhaustive/basic/set09/expected/model_4_3_4_2.eprime deleted file mode 100644 index 71131e9ed0..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_3_4_2.eprime +++ /dev/null @@ -1,40 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_ExplicitVarSizeWithMarker_Marker: int(0..4) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithDummy, - y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values] -such that - and([x_ExplicitVarSizeWithFlags_Flags[q21] /\ q22 <= y_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithFlags_Values[q21] + 2 = y_ExplicitVarSizeWithMarker_Values[q22] - | q21 : int(1..4), q22 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 2 | q2 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]), - and([q6 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> - y_ExplicitVarSizeWithMarker_Values[q6] < y_ExplicitVarSizeWithMarker_Values[q6 + 1] - | q6 : int(1..3)]), - and([q7 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q7] = 2 | q7 : int(1..4)]), - 1 <= y_ExplicitVarSizeWithMarker_Marker, - and([y_ExplicitVarSizeWithDummy[q9] < y_ExplicitVarSizeWithDummy[q9 + 1] \/ y_ExplicitVarSizeWithDummy[q9] = 6 - | q9 : int(1..3)]), - and([y_ExplicitVarSizeWithDummy[q10] = 6 -> y_ExplicitVarSizeWithDummy[q10 + 1] = 6 | q10 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q11] != 6) | q11 : int(1..4)]), - and([y_ExplicitVarSizeWithDummy[q14] != 6 -> - or([q16 <= y_ExplicitVarSizeWithMarker_Marker /\ - y_ExplicitVarSizeWithMarker_Values[q16] = y_ExplicitVarSizeWithDummy[q14] - | q16 : int(1..4)]) - | q14 : int(1..4)]), - and([q18 <= y_ExplicitVarSizeWithMarker_Marker -> - or([y_ExplicitVarSizeWithDummy[q20] != 6 /\ - y_ExplicitVarSizeWithDummy[q20] = y_ExplicitVarSizeWithMarker_Values[q18] - | q20 : int(1..4)]) - | q18 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_4_3_4_3-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_4_3_4_3-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_3_4_3-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_4_3_4_3-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_4_3_4_3-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_3_4_3-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_4_3_4_3.eprime b/tests/exhaustive/basic/set09/expected/model_4_3_4_3.eprime deleted file mode 100644 index 926828d190..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_3_4_3.eprime +++ /dev/null @@ -1,25 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_ExplicitVarSizeWithMarker_Marker: int(0..4) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithMarker_Marker, - y_ExplicitVarSizeWithMarker_Values] -such that - and([x_ExplicitVarSizeWithFlags_Flags[q9] /\ q10 <= y_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithFlags_Values[q9] + 2 = y_ExplicitVarSizeWithMarker_Values[q10] - | q9 : int(1..4), q10 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 2 | q2 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]), - and([q6 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> - y_ExplicitVarSizeWithMarker_Values[q6] < y_ExplicitVarSizeWithMarker_Values[q6 + 1] - | q6 : int(1..3)]), - and([q7 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q7] = 2 | q7 : int(1..4)]), - 1 <= y_ExplicitVarSizeWithMarker_Marker - diff --git a/tests/exhaustive/basic/set09/expected/model_4_3_4_4-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_4_3_4_4-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_3_4_4-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_4_3_4_4-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_4_3_4_4-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_3_4_4-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_4_3_4_4.eprime b/tests/exhaustive/basic/set09/expected/model_4_3_4_4.eprime deleted file mode 100644 index e141685012..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_3_4_4.eprime +++ /dev/null @@ -1,44 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_ExplicitVarSizeWithMarker_Marker: int(0..4) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithFlags_Flags, - y_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values] -such that - and([x_ExplicitVarSizeWithFlags_Flags[q22] /\ q23 <= y_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithFlags_Values[q22] + 2 = y_ExplicitVarSizeWithMarker_Values[q23] - | q22 : int(1..4), q23 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 2 | q2 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]), - and([q6 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> - y_ExplicitVarSizeWithMarker_Values[q6] < y_ExplicitVarSizeWithMarker_Values[q6 + 1] - | q6 : int(1..3)]), - and([q7 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q7] = 2 | q7 : int(1..4)]), - 1 <= y_ExplicitVarSizeWithMarker_Marker, - and([y_ExplicitVarSizeWithFlags_Flags[q9 + 1] -> - y_ExplicitVarSizeWithFlags_Values[q9] < y_ExplicitVarSizeWithFlags_Values[q9 + 1] - | q9 : int(1..3)]), - and([y_ExplicitVarSizeWithFlags_Flags[q10] = false -> y_ExplicitVarSizeWithFlags_Values[q10] = 2 - | q10 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q11 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q11] | q11 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q12]) | q12 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q15] -> - or([q17 <= y_ExplicitVarSizeWithMarker_Marker /\ - y_ExplicitVarSizeWithMarker_Values[q17] = y_ExplicitVarSizeWithFlags_Values[q15] - | q17 : int(1..4)]) - | q15 : int(1..4)]), - and([q19 <= y_ExplicitVarSizeWithMarker_Marker -> - or([y_ExplicitVarSizeWithFlags_Flags[q21] /\ - y_ExplicitVarSizeWithFlags_Values[q21] = y_ExplicitVarSizeWithMarker_Values[q19] - | q21 : int(1..4)]) - | q19 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_4_4_1_1-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_4_4_1_1-solution000001.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_4_1_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_4_4_1_1-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_4_4_1_1-solution000002.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_4_1_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_4_4_1_1.eprime b/tests/exhaustive/basic/set09/expected/model_4_4_1_1.eprime deleted file mode 100644 index 902354c009..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_4_1_1.eprime +++ /dev/null @@ -1,40 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -find x_Occurrence: matrix indexed by [int(2..5)] of bool -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_Occurrence: matrix indexed by [int(2..5)] of bool -branching on - [x_Occurrence, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, y_Occurrence, - y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values] -such that - and([x_ExplicitVarSizeWithFlags_Flags[q18] /\ y_ExplicitVarSizeWithFlags_Flags[q19] -> - x_ExplicitVarSizeWithFlags_Values[q18] + 2 = y_ExplicitVarSizeWithFlags_Values[q19] - | q18 : int(1..4), q19 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 2 | q2 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> - y_ExplicitVarSizeWithFlags_Values[q6] < y_ExplicitVarSizeWithFlags_Values[q6 + 1] - | q6 : int(1..3)]), - and([y_ExplicitVarSizeWithFlags_Flags[q7] = false -> y_ExplicitVarSizeWithFlags_Values[q7] = 2 | q7 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q8 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q8] | q8 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q9]) | q9 : int(1..4)]), - 1 <= sum([toInt(x_Occurrence[q11]) | q11 : int(2..5)]), - and([x_Occurrence[q20] -> - or([x_ExplicitVarSizeWithFlags_Flags[q22] /\ x_ExplicitVarSizeWithFlags_Values[q22] = q20 | q22 : int(1..4)]) - | q20 : int(2..5)]), - and([x_ExplicitVarSizeWithFlags_Flags[q24] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q24]] - | q24 : int(1..4)]), - 1 <= sum([toInt(y_Occurrence[q12]) | q12 : int(2..5)]), - and([y_Occurrence[q13] -> - or([y_ExplicitVarSizeWithFlags_Flags[q15] /\ y_ExplicitVarSizeWithFlags_Values[q15] = q13 | q15 : int(1..4)]) - | q13 : int(2..5)]), - and([y_ExplicitVarSizeWithFlags_Flags[q17] -> y_Occurrence[y_ExplicitVarSizeWithFlags_Values[q17]] - | q17 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_4_4_1_2-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_4_4_1_2-solution000001.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_4_1_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_4_4_1_2-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_4_4_1_2-solution000002.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_4_1_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_4_4_1_2.eprime b/tests/exhaustive/basic/set09/expected/model_4_4_1_2.eprime deleted file mode 100644 index 2093b2c8e5..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_4_1_2.eprime +++ /dev/null @@ -1,48 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -find x_Occurrence: matrix indexed by [int(2..5)] of bool -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -branching on - [x_Occurrence, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithDummy, - y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values] -such that - and([x_ExplicitVarSizeWithFlags_Flags[q29] /\ y_ExplicitVarSizeWithFlags_Flags[q30] -> - x_ExplicitVarSizeWithFlags_Values[q29] + 2 = y_ExplicitVarSizeWithFlags_Values[q30] - | q29 : int(1..4), q30 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 2 | q2 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> - y_ExplicitVarSizeWithFlags_Values[q6] < y_ExplicitVarSizeWithFlags_Values[q6 + 1] - | q6 : int(1..3)]), - and([y_ExplicitVarSizeWithFlags_Flags[q7] = false -> y_ExplicitVarSizeWithFlags_Values[q7] = 2 | q7 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q8 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q8] | q8 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q9]) | q9 : int(1..4)]), - 1 <= sum([toInt(x_Occurrence[q11]) | q11 : int(2..5)]), - and([x_Occurrence[q24] -> - or([x_ExplicitVarSizeWithFlags_Flags[q26] /\ x_ExplicitVarSizeWithFlags_Values[q26] = q24 | q26 : int(1..4)]) - | q24 : int(2..5)]), - and([x_ExplicitVarSizeWithFlags_Flags[q28] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q28]] - | q28 : int(1..4)]), - and([y_ExplicitVarSizeWithDummy[q12] < y_ExplicitVarSizeWithDummy[q12 + 1] \/ y_ExplicitVarSizeWithDummy[q12] = 6 - | q12 : int(1..3)]), - and([y_ExplicitVarSizeWithDummy[q13] = 6 -> y_ExplicitVarSizeWithDummy[q13 + 1] = 6 | q13 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q14] != 6) | q14 : int(1..4)]), - and([y_ExplicitVarSizeWithDummy[q17] != 6 -> - or([y_ExplicitVarSizeWithFlags_Flags[q19] /\ - y_ExplicitVarSizeWithFlags_Values[q19] = y_ExplicitVarSizeWithDummy[q17] - | q19 : int(1..4)]) - | q17 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q21] -> - or([y_ExplicitVarSizeWithDummy[q23] != 6 /\ - y_ExplicitVarSizeWithDummy[q23] = y_ExplicitVarSizeWithFlags_Values[q21] - | q23 : int(1..4)]) - | q21 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_4_4_1_3-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_4_4_1_3-solution000001.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_4_1_3-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_4_4_1_3-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_4_4_1_3-solution000002.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_4_1_3-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_4_4_1_3.eprime b/tests/exhaustive/basic/set09/expected/model_4_4_1_3.eprime deleted file mode 100644 index f2ea1ae61a..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_4_1_3.eprime +++ /dev/null @@ -1,51 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -find x_Occurrence: matrix indexed by [int(2..5)] of bool -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_ExplicitVarSizeWithMarker_Marker: int(0..4) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -branching on - [x_Occurrence, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, - y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithFlags_Flags, - y_ExplicitVarSizeWithFlags_Values] -such that - and([x_ExplicitVarSizeWithFlags_Flags[q28] /\ y_ExplicitVarSizeWithFlags_Flags[q29] -> - x_ExplicitVarSizeWithFlags_Values[q28] + 2 = y_ExplicitVarSizeWithFlags_Values[q29] - | q28 : int(1..4), q29 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 2 | q2 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> - y_ExplicitVarSizeWithFlags_Values[q6] < y_ExplicitVarSizeWithFlags_Values[q6 + 1] - | q6 : int(1..3)]), - and([y_ExplicitVarSizeWithFlags_Flags[q7] = false -> y_ExplicitVarSizeWithFlags_Values[q7] = 2 | q7 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q8 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q8] | q8 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q9]) | q9 : int(1..4)]), - 1 <= sum([toInt(x_Occurrence[q11]) | q11 : int(2..5)]), - and([x_Occurrence[q23] -> - or([x_ExplicitVarSizeWithFlags_Flags[q25] /\ x_ExplicitVarSizeWithFlags_Values[q25] = q23 | q25 : int(1..4)]) - | q23 : int(2..5)]), - and([x_ExplicitVarSizeWithFlags_Flags[q27] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q27]] - | q27 : int(1..4)]), - and([q12 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> - y_ExplicitVarSizeWithMarker_Values[q12] < y_ExplicitVarSizeWithMarker_Values[q12 + 1] - | q12 : int(1..3)]), - and([q13 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q13] = 2 | q13 : int(1..4)]), - 1 <= y_ExplicitVarSizeWithMarker_Marker, - and([q16 <= y_ExplicitVarSizeWithMarker_Marker -> - or([y_ExplicitVarSizeWithFlags_Flags[q18] /\ - y_ExplicitVarSizeWithFlags_Values[q18] = y_ExplicitVarSizeWithMarker_Values[q16] - | q18 : int(1..4)]) - | q16 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q20] -> - or([q22 <= y_ExplicitVarSizeWithMarker_Marker /\ - y_ExplicitVarSizeWithMarker_Values[q22] = y_ExplicitVarSizeWithFlags_Values[q20] - | q22 : int(1..4)]) - | q20 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_4_4_1_4-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_4_4_1_4-solution000001.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_4_1_4-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_4_4_1_4-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_4_4_1_4-solution000002.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_4_1_4-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_4_4_1_4.eprime b/tests/exhaustive/basic/set09/expected/model_4_4_1_4.eprime deleted file mode 100644 index ca5e2cadb0..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_4_1_4.eprime +++ /dev/null @@ -1,33 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -find x_Occurrence: matrix indexed by [int(2..5)] of bool -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -branching on - [x_Occurrence, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, - y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values] -such that - and([x_ExplicitVarSizeWithFlags_Flags[q17] /\ y_ExplicitVarSizeWithFlags_Flags[q18] -> - x_ExplicitVarSizeWithFlags_Values[q17] + 2 = y_ExplicitVarSizeWithFlags_Values[q18] - | q17 : int(1..4), q18 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 2 | q2 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> - y_ExplicitVarSizeWithFlags_Values[q6] < y_ExplicitVarSizeWithFlags_Values[q6 + 1] - | q6 : int(1..3)]), - and([y_ExplicitVarSizeWithFlags_Flags[q7] = false -> y_ExplicitVarSizeWithFlags_Values[q7] = 2 | q7 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q8 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q8] | q8 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q9]) | q9 : int(1..4)]), - 1 <= sum([toInt(x_Occurrence[q11]) | q11 : int(2..5)]), - and([x_Occurrence[q12] -> - or([x_ExplicitVarSizeWithFlags_Flags[q14] /\ x_ExplicitVarSizeWithFlags_Values[q14] = q12 | q14 : int(1..4)]) - | q12 : int(2..5)]), - and([x_ExplicitVarSizeWithFlags_Flags[q16] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q16]] - | q16 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_4_4_2_1-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_4_4_2_1-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_4_2_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_4_4_2_1-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_4_4_2_1-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_4_2_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_4_4_2_1.eprime b/tests/exhaustive/basic/set09/expected/model_4_4_2_1.eprime deleted file mode 100644 index 627fd329ca..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_4_2_1.eprime +++ /dev/null @@ -1,48 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_Occurrence: matrix indexed by [int(2..5)] of bool -branching on - [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, y_Occurrence, - y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values] -such that - and([x_ExplicitVarSizeWithFlags_Flags[q29] /\ y_ExplicitVarSizeWithFlags_Flags[q30] -> - x_ExplicitVarSizeWithFlags_Values[q29] + 2 = y_ExplicitVarSizeWithFlags_Values[q30] - | q29 : int(1..4), q30 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 2 | q2 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> - y_ExplicitVarSizeWithFlags_Values[q6] < y_ExplicitVarSizeWithFlags_Values[q6 + 1] - | q6 : int(1..3)]), - and([y_ExplicitVarSizeWithFlags_Flags[q7] = false -> y_ExplicitVarSizeWithFlags_Values[q7] = 2 | q7 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q8 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q8] | q8 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q9]) | q9 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q11] < x_ExplicitVarSizeWithDummy[q11 + 1] \/ x_ExplicitVarSizeWithDummy[q11] = 6 - | q11 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q12] = 6 -> x_ExplicitVarSizeWithDummy[q12 + 1] = 6 | q12 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q13] != 6) | q13 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q16] != 6 -> - or([x_ExplicitVarSizeWithFlags_Flags[q18] /\ - x_ExplicitVarSizeWithFlags_Values[q18] = x_ExplicitVarSizeWithDummy[q16] - | q18 : int(1..4)]) - | q16 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q20] -> - or([x_ExplicitVarSizeWithDummy[q22] != 6 /\ - x_ExplicitVarSizeWithDummy[q22] = x_ExplicitVarSizeWithFlags_Values[q20] - | q22 : int(1..4)]) - | q20 : int(1..4)]), - 1 <= sum([toInt(y_Occurrence[q23]) | q23 : int(2..5)]), - and([y_Occurrence[q24] -> - or([y_ExplicitVarSizeWithFlags_Flags[q26] /\ y_ExplicitVarSizeWithFlags_Values[q26] = q24 | q26 : int(1..4)]) - | q24 : int(2..5)]), - and([y_ExplicitVarSizeWithFlags_Flags[q28] -> y_Occurrence[y_ExplicitVarSizeWithFlags_Values[q28]] - | q28 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_4_4_2_2-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_4_4_2_2-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_4_2_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_4_4_2_2-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_4_4_2_2-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_4_2_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_4_4_2_2.eprime b/tests/exhaustive/basic/set09/expected/model_4_4_2_2.eprime deleted file mode 100644 index 0002083a4b..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_4_2_2.eprime +++ /dev/null @@ -1,56 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -branching on - [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, - y_ExplicitVarSizeWithDummy, y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values] -such that - and([x_ExplicitVarSizeWithFlags_Flags[q35] /\ y_ExplicitVarSizeWithFlags_Flags[q36] -> - x_ExplicitVarSizeWithFlags_Values[q35] + 2 = y_ExplicitVarSizeWithFlags_Values[q36] - | q35 : int(1..4), q36 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 2 | q2 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> - y_ExplicitVarSizeWithFlags_Values[q6] < y_ExplicitVarSizeWithFlags_Values[q6 + 1] - | q6 : int(1..3)]), - and([y_ExplicitVarSizeWithFlags_Flags[q7] = false -> y_ExplicitVarSizeWithFlags_Values[q7] = 2 | q7 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q8 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q8] | q8 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q9]) | q9 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q11] < x_ExplicitVarSizeWithDummy[q11 + 1] \/ x_ExplicitVarSizeWithDummy[q11] = 6 - | q11 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q12] = 6 -> x_ExplicitVarSizeWithDummy[q12 + 1] = 6 | q12 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q13] != 6) | q13 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q16] != 6 -> - or([x_ExplicitVarSizeWithFlags_Flags[q18] /\ - x_ExplicitVarSizeWithFlags_Values[q18] = x_ExplicitVarSizeWithDummy[q16] - | q18 : int(1..4)]) - | q16 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q20] -> - or([x_ExplicitVarSizeWithDummy[q22] != 6 /\ - x_ExplicitVarSizeWithDummy[q22] = x_ExplicitVarSizeWithFlags_Values[q20] - | q22 : int(1..4)]) - | q20 : int(1..4)]), - and([y_ExplicitVarSizeWithDummy[q23] < y_ExplicitVarSizeWithDummy[q23 + 1] \/ y_ExplicitVarSizeWithDummy[q23] = 6 - | q23 : int(1..3)]), - and([y_ExplicitVarSizeWithDummy[q24] = 6 -> y_ExplicitVarSizeWithDummy[q24 + 1] = 6 | q24 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q25] != 6) | q25 : int(1..4)]), - and([y_ExplicitVarSizeWithDummy[q28] != 6 -> - or([y_ExplicitVarSizeWithFlags_Flags[q30] /\ - y_ExplicitVarSizeWithFlags_Values[q30] = y_ExplicitVarSizeWithDummy[q28] - | q30 : int(1..4)]) - | q28 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q32] -> - or([y_ExplicitVarSizeWithDummy[q34] != 6 /\ - y_ExplicitVarSizeWithDummy[q34] = y_ExplicitVarSizeWithFlags_Values[q32] - | q34 : int(1..4)]) - | q32 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_4_4_2_3-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_4_4_2_3-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_4_2_3-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_4_4_2_3-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_4_4_2_3-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_4_2_3-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_4_4_2_3.eprime b/tests/exhaustive/basic/set09/expected/model_4_4_2_3.eprime deleted file mode 100644 index 95276e3dcb..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_4_2_3.eprime +++ /dev/null @@ -1,59 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_ExplicitVarSizeWithMarker_Marker: int(0..4) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -branching on - [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, - y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithFlags_Flags, - y_ExplicitVarSizeWithFlags_Values] -such that - and([x_ExplicitVarSizeWithFlags_Flags[q34] /\ y_ExplicitVarSizeWithFlags_Flags[q35] -> - x_ExplicitVarSizeWithFlags_Values[q34] + 2 = y_ExplicitVarSizeWithFlags_Values[q35] - | q34 : int(1..4), q35 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 2 | q2 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> - y_ExplicitVarSizeWithFlags_Values[q6] < y_ExplicitVarSizeWithFlags_Values[q6 + 1] - | q6 : int(1..3)]), - and([y_ExplicitVarSizeWithFlags_Flags[q7] = false -> y_ExplicitVarSizeWithFlags_Values[q7] = 2 | q7 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q8 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q8] | q8 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q9]) | q9 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q11] < x_ExplicitVarSizeWithDummy[q11 + 1] \/ x_ExplicitVarSizeWithDummy[q11] = 6 - | q11 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q12] = 6 -> x_ExplicitVarSizeWithDummy[q12 + 1] = 6 | q12 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q13] != 6) | q13 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q16] != 6 -> - or([x_ExplicitVarSizeWithFlags_Flags[q18] /\ - x_ExplicitVarSizeWithFlags_Values[q18] = x_ExplicitVarSizeWithDummy[q16] - | q18 : int(1..4)]) - | q16 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q20] -> - or([x_ExplicitVarSizeWithDummy[q22] != 6 /\ - x_ExplicitVarSizeWithDummy[q22] = x_ExplicitVarSizeWithFlags_Values[q20] - | q22 : int(1..4)]) - | q20 : int(1..4)]), - and([q23 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> - y_ExplicitVarSizeWithMarker_Values[q23] < y_ExplicitVarSizeWithMarker_Values[q23 + 1] - | q23 : int(1..3)]), - and([q24 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q24] = 2 | q24 : int(1..4)]), - 1 <= y_ExplicitVarSizeWithMarker_Marker, - and([q27 <= y_ExplicitVarSizeWithMarker_Marker -> - or([y_ExplicitVarSizeWithFlags_Flags[q29] /\ - y_ExplicitVarSizeWithFlags_Values[q29] = y_ExplicitVarSizeWithMarker_Values[q27] - | q29 : int(1..4)]) - | q27 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q31] -> - or([q33 <= y_ExplicitVarSizeWithMarker_Marker /\ - y_ExplicitVarSizeWithMarker_Values[q33] = y_ExplicitVarSizeWithFlags_Values[q31] - | q33 : int(1..4)]) - | q31 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_4_4_2_4-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_4_4_2_4-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_4_2_4-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_4_4_2_4-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_4_4_2_4-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_4_2_4-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_4_4_2_4.eprime b/tests/exhaustive/basic/set09/expected/model_4_4_2_4.eprime deleted file mode 100644 index 05c62046ee..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_4_2_4.eprime +++ /dev/null @@ -1,41 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -branching on - [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, - y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values] -such that - and([x_ExplicitVarSizeWithFlags_Flags[q23] /\ y_ExplicitVarSizeWithFlags_Flags[q24] -> - x_ExplicitVarSizeWithFlags_Values[q23] + 2 = y_ExplicitVarSizeWithFlags_Values[q24] - | q23 : int(1..4), q24 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 2 | q2 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> - y_ExplicitVarSizeWithFlags_Values[q6] < y_ExplicitVarSizeWithFlags_Values[q6 + 1] - | q6 : int(1..3)]), - and([y_ExplicitVarSizeWithFlags_Flags[q7] = false -> y_ExplicitVarSizeWithFlags_Values[q7] = 2 | q7 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q8 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q8] | q8 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q9]) | q9 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q11] < x_ExplicitVarSizeWithDummy[q11 + 1] \/ x_ExplicitVarSizeWithDummy[q11] = 6 - | q11 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q12] = 6 -> x_ExplicitVarSizeWithDummy[q12 + 1] = 6 | q12 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q13] != 6) | q13 : int(1..4)]), - and([x_ExplicitVarSizeWithDummy[q16] != 6 -> - or([x_ExplicitVarSizeWithFlags_Flags[q18] /\ - x_ExplicitVarSizeWithFlags_Values[q18] = x_ExplicitVarSizeWithDummy[q16] - | q18 : int(1..4)]) - | q16 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q20] -> - or([x_ExplicitVarSizeWithDummy[q22] != 6 /\ - x_ExplicitVarSizeWithDummy[q22] = x_ExplicitVarSizeWithFlags_Values[q20] - | q22 : int(1..4)]) - | q20 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_4_4_3_1-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_4_4_3_1-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_4_3_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_4_4_3_1-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_4_4_3_1-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_4_3_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_4_4_3_1.eprime b/tests/exhaustive/basic/set09/expected/model_4_4_3_1.eprime deleted file mode 100644 index 310494b661..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_4_3_1.eprime +++ /dev/null @@ -1,51 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_Occurrence: matrix indexed by [int(2..5)] of bool -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithFlags_Flags, - x_ExplicitVarSizeWithFlags_Values, y_Occurrence, y_ExplicitVarSizeWithFlags_Flags, - y_ExplicitVarSizeWithFlags_Values] -such that - and([x_ExplicitVarSizeWithFlags_Flags[q28] /\ y_ExplicitVarSizeWithFlags_Flags[q29] -> - x_ExplicitVarSizeWithFlags_Values[q28] + 2 = y_ExplicitVarSizeWithFlags_Values[q29] - | q28 : int(1..4), q29 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 2 | q2 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> - y_ExplicitVarSizeWithFlags_Values[q6] < y_ExplicitVarSizeWithFlags_Values[q6 + 1] - | q6 : int(1..3)]), - and([y_ExplicitVarSizeWithFlags_Flags[q7] = false -> y_ExplicitVarSizeWithFlags_Values[q7] = 2 | q7 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q8 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q8] | q8 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q9]) | q9 : int(1..4)]), - and([q11 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q11] < x_ExplicitVarSizeWithMarker_Values[q11 + 1] - | q11 : int(1..3)]), - and([q12 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q12] = 2 | q12 : int(1..4)]), - 1 <= x_ExplicitVarSizeWithMarker_Marker, - and([q15 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q17] /\ - x_ExplicitVarSizeWithFlags_Values[q17] = x_ExplicitVarSizeWithMarker_Values[q15] - | q17 : int(1..4)]) - | q15 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q19] -> - or([q21 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q21] = x_ExplicitVarSizeWithFlags_Values[q19] - | q21 : int(1..4)]) - | q19 : int(1..4)]), - 1 <= sum([toInt(y_Occurrence[q22]) | q22 : int(2..5)]), - and([y_Occurrence[q23] -> - or([y_ExplicitVarSizeWithFlags_Flags[q25] /\ y_ExplicitVarSizeWithFlags_Values[q25] = q23 | q25 : int(1..4)]) - | q23 : int(2..5)]), - and([y_ExplicitVarSizeWithFlags_Flags[q27] -> y_Occurrence[y_ExplicitVarSizeWithFlags_Values[q27]] - | q27 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_4_4_3_2-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_4_4_3_2-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_4_3_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_4_4_3_2-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_4_4_3_2-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_4_3_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_4_4_3_2.eprime b/tests/exhaustive/basic/set09/expected/model_4_4_3_2.eprime deleted file mode 100644 index 8fbea0fc93..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_4_3_2.eprime +++ /dev/null @@ -1,59 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithFlags_Flags, - x_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithDummy, y_ExplicitVarSizeWithFlags_Flags, - y_ExplicitVarSizeWithFlags_Values] -such that - and([x_ExplicitVarSizeWithFlags_Flags[q34] /\ y_ExplicitVarSizeWithFlags_Flags[q35] -> - x_ExplicitVarSizeWithFlags_Values[q34] + 2 = y_ExplicitVarSizeWithFlags_Values[q35] - | q34 : int(1..4), q35 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 2 | q2 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> - y_ExplicitVarSizeWithFlags_Values[q6] < y_ExplicitVarSizeWithFlags_Values[q6 + 1] - | q6 : int(1..3)]), - and([y_ExplicitVarSizeWithFlags_Flags[q7] = false -> y_ExplicitVarSizeWithFlags_Values[q7] = 2 | q7 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q8 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q8] | q8 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q9]) | q9 : int(1..4)]), - and([q11 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q11] < x_ExplicitVarSizeWithMarker_Values[q11 + 1] - | q11 : int(1..3)]), - and([q12 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q12] = 2 | q12 : int(1..4)]), - 1 <= x_ExplicitVarSizeWithMarker_Marker, - and([q15 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q17] /\ - x_ExplicitVarSizeWithFlags_Values[q17] = x_ExplicitVarSizeWithMarker_Values[q15] - | q17 : int(1..4)]) - | q15 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q19] -> - or([q21 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q21] = x_ExplicitVarSizeWithFlags_Values[q19] - | q21 : int(1..4)]) - | q19 : int(1..4)]), - and([y_ExplicitVarSizeWithDummy[q22] < y_ExplicitVarSizeWithDummy[q22 + 1] \/ y_ExplicitVarSizeWithDummy[q22] = 6 - | q22 : int(1..3)]), - and([y_ExplicitVarSizeWithDummy[q23] = 6 -> y_ExplicitVarSizeWithDummy[q23 + 1] = 6 | q23 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q24] != 6) | q24 : int(1..4)]), - and([y_ExplicitVarSizeWithDummy[q27] != 6 -> - or([y_ExplicitVarSizeWithFlags_Flags[q29] /\ - y_ExplicitVarSizeWithFlags_Values[q29] = y_ExplicitVarSizeWithDummy[q27] - | q29 : int(1..4)]) - | q27 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q31] -> - or([y_ExplicitVarSizeWithDummy[q33] != 6 /\ - y_ExplicitVarSizeWithDummy[q33] = y_ExplicitVarSizeWithFlags_Values[q31] - | q33 : int(1..4)]) - | q31 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_4_4_3_3-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_4_4_3_3-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_4_3_3-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_4_4_3_3-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_4_4_3_3-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_4_3_3-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_4_4_3_3.eprime b/tests/exhaustive/basic/set09/expected/model_4_4_3_3.eprime deleted file mode 100644 index a1e6b33da9..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_4_3_3.eprime +++ /dev/null @@ -1,61 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_ExplicitVarSizeWithMarker_Marker: int(0..4) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithFlags_Flags, - x_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values, - y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values] -such that - and([x_ExplicitVarSizeWithFlags_Flags[q33] /\ y_ExplicitVarSizeWithFlags_Flags[q34] -> - x_ExplicitVarSizeWithFlags_Values[q33] + 2 = y_ExplicitVarSizeWithFlags_Values[q34] - | q33 : int(1..4), q34 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 2 | q2 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> - y_ExplicitVarSizeWithFlags_Values[q6] < y_ExplicitVarSizeWithFlags_Values[q6 + 1] - | q6 : int(1..3)]), - and([y_ExplicitVarSizeWithFlags_Flags[q7] = false -> y_ExplicitVarSizeWithFlags_Values[q7] = 2 | q7 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q8 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q8] | q8 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q9]) | q9 : int(1..4)]), - and([q11 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q11] < x_ExplicitVarSizeWithMarker_Values[q11 + 1] - | q11 : int(1..3)]), - and([q12 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q12] = 2 | q12 : int(1..4)]), - 1 <= x_ExplicitVarSizeWithMarker_Marker, - and([q15 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q17] /\ - x_ExplicitVarSizeWithFlags_Values[q17] = x_ExplicitVarSizeWithMarker_Values[q15] - | q17 : int(1..4)]) - | q15 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q19] -> - or([q21 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q21] = x_ExplicitVarSizeWithFlags_Values[q19] - | q21 : int(1..4)]) - | q19 : int(1..4)]), - and([q22 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> - y_ExplicitVarSizeWithMarker_Values[q22] < y_ExplicitVarSizeWithMarker_Values[q22 + 1] - | q22 : int(1..3)]), - and([q23 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q23] = 2 | q23 : int(1..4)]), - 1 <= y_ExplicitVarSizeWithMarker_Marker, - and([q26 <= y_ExplicitVarSizeWithMarker_Marker -> - or([y_ExplicitVarSizeWithFlags_Flags[q28] /\ - y_ExplicitVarSizeWithFlags_Values[q28] = y_ExplicitVarSizeWithMarker_Values[q26] - | q28 : int(1..4)]) - | q26 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q30] -> - or([q32 <= y_ExplicitVarSizeWithMarker_Marker /\ - y_ExplicitVarSizeWithMarker_Values[q32] = y_ExplicitVarSizeWithFlags_Values[q30] - | q32 : int(1..4)]) - | q30 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_4_4_3_4-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_4_4_3_4-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_4_3_4-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_4_4_3_4-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_4_4_3_4-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_4_3_4-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_4_4_3_4.eprime b/tests/exhaustive/basic/set09/expected/model_4_4_3_4.eprime deleted file mode 100644 index fd4427c028..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_4_3_4.eprime +++ /dev/null @@ -1,43 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -find x_ExplicitVarSizeWithMarker_Marker: int(0..4) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithFlags_Flags, - x_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values] -such that - and([x_ExplicitVarSizeWithFlags_Flags[q22] /\ y_ExplicitVarSizeWithFlags_Flags[q23] -> - x_ExplicitVarSizeWithFlags_Values[q22] + 2 = y_ExplicitVarSizeWithFlags_Values[q23] - | q22 : int(1..4), q23 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 2 | q2 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> - y_ExplicitVarSizeWithFlags_Values[q6] < y_ExplicitVarSizeWithFlags_Values[q6 + 1] - | q6 : int(1..3)]), - and([y_ExplicitVarSizeWithFlags_Flags[q7] = false -> y_ExplicitVarSizeWithFlags_Values[q7] = 2 | q7 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q8 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q8] | q8 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q9]) | q9 : int(1..4)]), - and([q11 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q11] < x_ExplicitVarSizeWithMarker_Values[q11 + 1] - | q11 : int(1..3)]), - and([q12 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q12] = 2 | q12 : int(1..4)]), - 1 <= x_ExplicitVarSizeWithMarker_Marker, - and([q15 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q17] /\ - x_ExplicitVarSizeWithFlags_Values[q17] = x_ExplicitVarSizeWithMarker_Values[q15] - | q17 : int(1..4)]) - | q15 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q19] -> - or([q21 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q21] = x_ExplicitVarSizeWithFlags_Values[q19] - | q21 : int(1..4)]) - | q19 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_4_4_4_1-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_4_4_4_1-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_4_4_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_4_4_4_1-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_4_4_4_1-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_4_4_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_4_4_4_1.eprime b/tests/exhaustive/basic/set09/expected/model_4_4_4_1.eprime deleted file mode 100644 index 3dd731472f..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_4_4_1.eprime +++ /dev/null @@ -1,33 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_Occurrence: matrix indexed by [int(2..5)] of bool -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, y_Occurrence, - y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values] -such that - and([x_ExplicitVarSizeWithFlags_Flags[q17] /\ y_ExplicitVarSizeWithFlags_Flags[q18] -> - x_ExplicitVarSizeWithFlags_Values[q17] + 2 = y_ExplicitVarSizeWithFlags_Values[q18] - | q17 : int(1..4), q18 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 2 | q2 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> - y_ExplicitVarSizeWithFlags_Values[q6] < y_ExplicitVarSizeWithFlags_Values[q6 + 1] - | q6 : int(1..3)]), - and([y_ExplicitVarSizeWithFlags_Flags[q7] = false -> y_ExplicitVarSizeWithFlags_Values[q7] = 2 | q7 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q8 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q8] | q8 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q9]) | q9 : int(1..4)]), - 1 <= sum([toInt(y_Occurrence[q11]) | q11 : int(2..5)]), - and([y_Occurrence[q12] -> - or([y_ExplicitVarSizeWithFlags_Flags[q14] /\ y_ExplicitVarSizeWithFlags_Values[q14] = q12 | q14 : int(1..4)]) - | q12 : int(2..5)]), - and([y_ExplicitVarSizeWithFlags_Flags[q16] -> y_Occurrence[y_ExplicitVarSizeWithFlags_Values[q16]] - | q16 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_4_4_4_2-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_4_4_4_2-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_4_4_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_4_4_4_2-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_4_4_4_2-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_4_4_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_4_4_4_2.eprime b/tests/exhaustive/basic/set09/expected/model_4_4_4_2.eprime deleted file mode 100644 index 256ad5b5d2..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_4_4_2.eprime +++ /dev/null @@ -1,41 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithDummy, - y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values] -such that - and([x_ExplicitVarSizeWithFlags_Flags[q23] /\ y_ExplicitVarSizeWithFlags_Flags[q24] -> - x_ExplicitVarSizeWithFlags_Values[q23] + 2 = y_ExplicitVarSizeWithFlags_Values[q24] - | q23 : int(1..4), q24 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 2 | q2 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> - y_ExplicitVarSizeWithFlags_Values[q6] < y_ExplicitVarSizeWithFlags_Values[q6 + 1] - | q6 : int(1..3)]), - and([y_ExplicitVarSizeWithFlags_Flags[q7] = false -> y_ExplicitVarSizeWithFlags_Values[q7] = 2 | q7 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q8 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q8] | q8 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q9]) | q9 : int(1..4)]), - and([y_ExplicitVarSizeWithDummy[q11] < y_ExplicitVarSizeWithDummy[q11 + 1] \/ y_ExplicitVarSizeWithDummy[q11] = 6 - | q11 : int(1..3)]), - and([y_ExplicitVarSizeWithDummy[q12] = 6 -> y_ExplicitVarSizeWithDummy[q12 + 1] = 6 | q12 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q13] != 6) | q13 : int(1..4)]), - and([y_ExplicitVarSizeWithDummy[q16] != 6 -> - or([y_ExplicitVarSizeWithFlags_Flags[q18] /\ - y_ExplicitVarSizeWithFlags_Values[q18] = y_ExplicitVarSizeWithDummy[q16] - | q18 : int(1..4)]) - | q16 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q20] -> - or([y_ExplicitVarSizeWithDummy[q22] != 6 /\ - y_ExplicitVarSizeWithDummy[q22] = y_ExplicitVarSizeWithFlags_Values[q20] - | q22 : int(1..4)]) - | q20 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_4_4_4_3-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_4_4_4_3-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_4_4_3-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_4_4_4_3-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_4_4_4_3-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_4_4_3-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_4_4_4_3.eprime b/tests/exhaustive/basic/set09/expected/model_4_4_4_3.eprime deleted file mode 100644 index c694863719..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_4_4_3.eprime +++ /dev/null @@ -1,43 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_ExplicitVarSizeWithMarker_Marker: int(0..4) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithMarker_Marker, - y_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values] -such that - and([x_ExplicitVarSizeWithFlags_Flags[q22] /\ y_ExplicitVarSizeWithFlags_Flags[q23] -> - x_ExplicitVarSizeWithFlags_Values[q22] + 2 = y_ExplicitVarSizeWithFlags_Values[q23] - | q22 : int(1..4), q23 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 2 | q2 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> - y_ExplicitVarSizeWithFlags_Values[q6] < y_ExplicitVarSizeWithFlags_Values[q6 + 1] - | q6 : int(1..3)]), - and([y_ExplicitVarSizeWithFlags_Flags[q7] = false -> y_ExplicitVarSizeWithFlags_Values[q7] = 2 | q7 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q8 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q8] | q8 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q9]) | q9 : int(1..4)]), - and([q11 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> - y_ExplicitVarSizeWithMarker_Values[q11] < y_ExplicitVarSizeWithMarker_Values[q11 + 1] - | q11 : int(1..3)]), - and([q12 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q12] = 2 | q12 : int(1..4)]), - 1 <= y_ExplicitVarSizeWithMarker_Marker, - and([q15 <= y_ExplicitVarSizeWithMarker_Marker -> - or([y_ExplicitVarSizeWithFlags_Flags[q17] /\ - y_ExplicitVarSizeWithFlags_Values[q17] = y_ExplicitVarSizeWithMarker_Values[q15] - | q17 : int(1..4)]) - | q15 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q19] -> - or([q21 <= y_ExplicitVarSizeWithMarker_Marker /\ - y_ExplicitVarSizeWithMarker_Values[q21] = y_ExplicitVarSizeWithFlags_Values[q19] - | q21 : int(1..4)]) - | q19 : int(1..4)]) - diff --git a/tests/exhaustive/basic/set09/expected/model_4_4_4_4-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_4_4_4_4-solution000001.solution deleted file mode 100644 index 48003f5fce..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_4_4_4-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {2} -letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_4_4_4_4-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_4_4_4_4-solution000002.solution deleted file mode 100644 index 0b94905e4c..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_4_4_4-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {3} -letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_4_4_4_4.eprime b/tests/exhaustive/basic/set09/expected/model_4_4_4_4.eprime deleted file mode 100644 index 1741be5b67..0000000000 --- a/tests/exhaustive/basic/set09/expected/model_4_4_4_4.eprime +++ /dev/null @@ -1,26 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithFlags_Flags, - y_ExplicitVarSizeWithFlags_Values] -such that - and([x_ExplicitVarSizeWithFlags_Flags[q11] /\ y_ExplicitVarSizeWithFlags_Flags[q12] -> - x_ExplicitVarSizeWithFlags_Values[q11] + 2 = y_ExplicitVarSizeWithFlags_Values[q12] - | q11 : int(1..4), q12 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 2 | q2 : int(1..4)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> - y_ExplicitVarSizeWithFlags_Values[q6] < y_ExplicitVarSizeWithFlags_Values[q6 + 1] - | q6 : int(1..3)]), - and([y_ExplicitVarSizeWithFlags_Flags[q7] = false -> y_ExplicitVarSizeWithFlags_Values[q7] = 2 | q7 : int(1..4)]), - and([y_ExplicitVarSizeWithFlags_Flags[q8 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q8] | q8 : int(1..3)]), - 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q9]) | q9 : int(1..4)]) - diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_1-solution000001.solution b/tests/exhaustive/basic/setOfSet01/expected/model_1-solution000001.solution deleted file mode 100644 index 1a734343d9..0000000000 --- a/tests/exhaustive/basic/setOfSet01/expected/model_1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {} diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_1-solution000002.solution b/tests/exhaustive/basic/setOfSet01/expected/model_1-solution000002.solution deleted file mode 100644 index 7c5b3bfc58..0000000000 --- a/tests/exhaustive/basic/setOfSet01/expected/model_1-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {{}} diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_1-solution000003.solution b/tests/exhaustive/basic/setOfSet01/expected/model_1-solution000003.solution deleted file mode 100644 index 550c68f48c..0000000000 --- a/tests/exhaustive/basic/setOfSet01/expected/model_1-solution000003.solution +++ /dev/null @@ -1,6 +0,0 @@ -language Essence 1.3 - -letting x be {{2}} -$ Visualisation for x -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_1-solution000004.solution b/tests/exhaustive/basic/setOfSet01/expected/model_1-solution000004.solution deleted file mode 100644 index 69bc828bbc..0000000000 --- a/tests/exhaustive/basic/setOfSet01/expected/model_1-solution000004.solution +++ /dev/null @@ -1,6 +0,0 @@ -language Essence 1.3 - -letting x be {{1}} -$ Visualisation for x -$ 1 - diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_1-solution000005.solution b/tests/exhaustive/basic/setOfSet01/expected/model_1-solution000005.solution deleted file mode 100644 index 114bad5315..0000000000 --- a/tests/exhaustive/basic/setOfSet01/expected/model_1-solution000005.solution +++ /dev/null @@ -1,6 +0,0 @@ -language Essence 1.3 - -letting x be {{1, 2}} -$ Visualisation for x -$ 1 2 - diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_1-solution000006.solution b/tests/exhaustive/basic/setOfSet01/expected/model_1-solution000006.solution deleted file mode 100644 index c8946f3d06..0000000000 --- a/tests/exhaustive/basic/setOfSet01/expected/model_1-solution000006.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {2}} -$ Visualisation for x -$ -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_1-solution000007.solution b/tests/exhaustive/basic/setOfSet01/expected/model_1-solution000007.solution deleted file mode 100644 index 3ec452354e..0000000000 --- a/tests/exhaustive/basic/setOfSet01/expected/model_1-solution000007.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {1}} -$ Visualisation for x -$ -$ 1 - diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_1-solution000008.solution b/tests/exhaustive/basic/setOfSet01/expected/model_1-solution000008.solution deleted file mode 100644 index af16592c51..0000000000 --- a/tests/exhaustive/basic/setOfSet01/expected/model_1-solution000008.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1}, {2}} -$ Visualisation for x -$ 1 -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_1-solution000009.solution b/tests/exhaustive/basic/setOfSet01/expected/model_1-solution000009.solution deleted file mode 100644 index a6c0b6a43e..0000000000 --- a/tests/exhaustive/basic/setOfSet01/expected/model_1-solution000009.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {1, 2}} -$ Visualisation for x -$ -$ 1 2 - diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_1-solution000010.solution b/tests/exhaustive/basic/setOfSet01/expected/model_1-solution000010.solution deleted file mode 100644 index 9bf2af0712..0000000000 --- a/tests/exhaustive/basic/setOfSet01/expected/model_1-solution000010.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1, 2}, {2}} -$ Visualisation for x -$ 1 2 -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_1-solution000011.solution b/tests/exhaustive/basic/setOfSet01/expected/model_1-solution000011.solution deleted file mode 100644 index 38937c9389..0000000000 --- a/tests/exhaustive/basic/setOfSet01/expected/model_1-solution000011.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1}, {1, 2}} -$ Visualisation for x -$ 1 -$ 1 2 - diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_1-solution000012.solution b/tests/exhaustive/basic/setOfSet01/expected/model_1-solution000012.solution deleted file mode 100644 index f1a04b347c..0000000000 --- a/tests/exhaustive/basic/setOfSet01/expected/model_1-solution000012.solution +++ /dev/null @@ -1,8 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {1}, {2}} -$ Visualisation for x -$ -$ 1 -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_1-solution000013.solution b/tests/exhaustive/basic/setOfSet01/expected/model_1-solution000013.solution deleted file mode 100644 index b1673f700a..0000000000 --- a/tests/exhaustive/basic/setOfSet01/expected/model_1-solution000013.solution +++ /dev/null @@ -1,8 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {1, 2}, {2}} -$ Visualisation for x -$ -$ 1 2 -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_1-solution000014.solution b/tests/exhaustive/basic/setOfSet01/expected/model_1-solution000014.solution deleted file mode 100644 index 8400fcb8c1..0000000000 --- a/tests/exhaustive/basic/setOfSet01/expected/model_1-solution000014.solution +++ /dev/null @@ -1,8 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {1}, {1, 2}} -$ Visualisation for x -$ -$ 1 -$ 1 2 - diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_1-solution000015.solution b/tests/exhaustive/basic/setOfSet01/expected/model_1-solution000015.solution deleted file mode 100644 index 7c7f2e98ea..0000000000 --- a/tests/exhaustive/basic/setOfSet01/expected/model_1-solution000015.solution +++ /dev/null @@ -1,8 +0,0 @@ -language Essence 1.3 - -letting x be {{1}, {1, 2}, {2}} -$ Visualisation for x -$ 1 -$ 1 2 -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_1-solution000016.solution b/tests/exhaustive/basic/setOfSet01/expected/model_1-solution000016.solution deleted file mode 100644 index 29f10f5fb0..0000000000 --- a/tests/exhaustive/basic/setOfSet01/expected/model_1-solution000016.solution +++ /dev/null @@ -1,9 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {1}, {1, 2}, {2}} -$ Visualisation for x -$ -$ 1 -$ 1 2 -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_1.eprime b/tests/exhaustive/basic/setOfSet01/expected/model_1.eprime deleted file mode 100644 index ec206e1289..0000000000 --- a/tests/exhaustive/basic/setOfSet01/expected/model_1.eprime +++ /dev/null @@ -1,14 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarkerR2_Marker: int(0..4) -find x_ExplicitVarSizeWithMarkerR2_Values_Occurrence: matrix indexed by [int(1..4), int(1..2)] of bool -branching on [x_ExplicitVarSizeWithMarkerR2_Marker, x_ExplicitVarSizeWithMarkerR2_Values_Occurrence] -such that - and([q1 + 1 <= x_ExplicitVarSizeWithMarkerR2_Marker -> - [-toInt(x_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q1, q5]) | q5 : int(1..2)] x_ExplicitVarSizeWithMarkerR2_Marker -> - and([x_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q2, q7] = false | q7 : int(1..2)]) - | q2 : int(1..4)]) - diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_2-solution000001.solution b/tests/exhaustive/basic/setOfSet01/expected/model_2-solution000001.solution deleted file mode 100644 index 1a734343d9..0000000000 --- a/tests/exhaustive/basic/setOfSet01/expected/model_2-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {} diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_2-solution000002.solution b/tests/exhaustive/basic/setOfSet01/expected/model_2-solution000002.solution deleted file mode 100644 index 114bad5315..0000000000 --- a/tests/exhaustive/basic/setOfSet01/expected/model_2-solution000002.solution +++ /dev/null @@ -1,6 +0,0 @@ -language Essence 1.3 - -letting x be {{1, 2}} -$ Visualisation for x -$ 1 2 - diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_2-solution000003.solution b/tests/exhaustive/basic/setOfSet01/expected/model_2-solution000003.solution deleted file mode 100644 index 69bc828bbc..0000000000 --- a/tests/exhaustive/basic/setOfSet01/expected/model_2-solution000003.solution +++ /dev/null @@ -1,6 +0,0 @@ -language Essence 1.3 - -letting x be {{1}} -$ Visualisation for x -$ 1 - diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_2-solution000004.solution b/tests/exhaustive/basic/setOfSet01/expected/model_2-solution000004.solution deleted file mode 100644 index 550c68f48c..0000000000 --- a/tests/exhaustive/basic/setOfSet01/expected/model_2-solution000004.solution +++ /dev/null @@ -1,6 +0,0 @@ -language Essence 1.3 - -letting x be {{2}} -$ Visualisation for x -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_2-solution000005.solution b/tests/exhaustive/basic/setOfSet01/expected/model_2-solution000005.solution deleted file mode 100644 index 7c5b3bfc58..0000000000 --- a/tests/exhaustive/basic/setOfSet01/expected/model_2-solution000005.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {{}} diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_2-solution000006.solution b/tests/exhaustive/basic/setOfSet01/expected/model_2-solution000006.solution deleted file mode 100644 index 38937c9389..0000000000 --- a/tests/exhaustive/basic/setOfSet01/expected/model_2-solution000006.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1}, {1, 2}} -$ Visualisation for x -$ 1 -$ 1 2 - diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_2-solution000007.solution b/tests/exhaustive/basic/setOfSet01/expected/model_2-solution000007.solution deleted file mode 100644 index 9bf2af0712..0000000000 --- a/tests/exhaustive/basic/setOfSet01/expected/model_2-solution000007.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1, 2}, {2}} -$ Visualisation for x -$ 1 2 -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_2-solution000008.solution b/tests/exhaustive/basic/setOfSet01/expected/model_2-solution000008.solution deleted file mode 100644 index a6c0b6a43e..0000000000 --- a/tests/exhaustive/basic/setOfSet01/expected/model_2-solution000008.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {1, 2}} -$ Visualisation for x -$ -$ 1 2 - diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_2-solution000009.solution b/tests/exhaustive/basic/setOfSet01/expected/model_2-solution000009.solution deleted file mode 100644 index af16592c51..0000000000 --- a/tests/exhaustive/basic/setOfSet01/expected/model_2-solution000009.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1}, {2}} -$ Visualisation for x -$ 1 -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_2-solution000010.solution b/tests/exhaustive/basic/setOfSet01/expected/model_2-solution000010.solution deleted file mode 100644 index 3ec452354e..0000000000 --- a/tests/exhaustive/basic/setOfSet01/expected/model_2-solution000010.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {1}} -$ Visualisation for x -$ -$ 1 - diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_2-solution000011.solution b/tests/exhaustive/basic/setOfSet01/expected/model_2-solution000011.solution deleted file mode 100644 index c8946f3d06..0000000000 --- a/tests/exhaustive/basic/setOfSet01/expected/model_2-solution000011.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {2}} -$ Visualisation for x -$ -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_2-solution000012.solution b/tests/exhaustive/basic/setOfSet01/expected/model_2-solution000012.solution deleted file mode 100644 index 7c7f2e98ea..0000000000 --- a/tests/exhaustive/basic/setOfSet01/expected/model_2-solution000012.solution +++ /dev/null @@ -1,8 +0,0 @@ -language Essence 1.3 - -letting x be {{1}, {1, 2}, {2}} -$ Visualisation for x -$ 1 -$ 1 2 -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_2-solution000013.solution b/tests/exhaustive/basic/setOfSet01/expected/model_2-solution000013.solution deleted file mode 100644 index 8400fcb8c1..0000000000 --- a/tests/exhaustive/basic/setOfSet01/expected/model_2-solution000013.solution +++ /dev/null @@ -1,8 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {1}, {1, 2}} -$ Visualisation for x -$ -$ 1 -$ 1 2 - diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_2-solution000014.solution b/tests/exhaustive/basic/setOfSet01/expected/model_2-solution000014.solution deleted file mode 100644 index b1673f700a..0000000000 --- a/tests/exhaustive/basic/setOfSet01/expected/model_2-solution000014.solution +++ /dev/null @@ -1,8 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {1, 2}, {2}} -$ Visualisation for x -$ -$ 1 2 -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_2-solution000015.solution b/tests/exhaustive/basic/setOfSet01/expected/model_2-solution000015.solution deleted file mode 100644 index f1a04b347c..0000000000 --- a/tests/exhaustive/basic/setOfSet01/expected/model_2-solution000015.solution +++ /dev/null @@ -1,8 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {1}, {2}} -$ Visualisation for x -$ -$ 1 -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_2-solution000016.solution b/tests/exhaustive/basic/setOfSet01/expected/model_2-solution000016.solution deleted file mode 100644 index 29f10f5fb0..0000000000 --- a/tests/exhaustive/basic/setOfSet01/expected/model_2-solution000016.solution +++ /dev/null @@ -1,9 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {1}, {1, 2}, {2}} -$ Visualisation for x -$ -$ 1 -$ 1 2 -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_2.eprime b/tests/exhaustive/basic/setOfSet01/expected/model_2.eprime deleted file mode 100644 index 2bba65c207..0000000000 --- a/tests/exhaustive/basic/setOfSet01/expected/model_2.eprime +++ /dev/null @@ -1,24 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarkerR6_Marker: int(0..4) -find x_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy: - matrix indexed by [int(1..4), int(1..2)] of int(1..3) -branching on [x_ExplicitVarSizeWithMarkerR6_Marker, x_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy] -such that - and([q1 + 1 <= x_ExplicitVarSizeWithMarkerR6_Marker -> - [x_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q1, q8] | q8 : int(1..2)] x_ExplicitVarSizeWithMarkerR6_Marker -> - and([x_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q2, q10] = 1 | q10 : int(1..2)]) - | q2 : int(1..4)]), - and([q3 <= x_ExplicitVarSizeWithMarkerR6_Marker -> - x_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q3, 1] < - x_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q3, 2] - \/ x_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q3, 1] = 3 - | q3 : int(1..4)]), - and([q3 <= x_ExplicitVarSizeWithMarkerR6_Marker -> - (x_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q3, 1] = 3 -> - x_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q3, 2] = 3) - | q3 : int(1..4)]) - diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_3-solution000001.solution b/tests/exhaustive/basic/setOfSet01/expected/model_3-solution000001.solution deleted file mode 100644 index 1a734343d9..0000000000 --- a/tests/exhaustive/basic/setOfSet01/expected/model_3-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {} diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_3-solution000002.solution b/tests/exhaustive/basic/setOfSet01/expected/model_3-solution000002.solution deleted file mode 100644 index 7c5b3bfc58..0000000000 --- a/tests/exhaustive/basic/setOfSet01/expected/model_3-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {{}} diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_3-solution000003.solution b/tests/exhaustive/basic/setOfSet01/expected/model_3-solution000003.solution deleted file mode 100644 index 69bc828bbc..0000000000 --- a/tests/exhaustive/basic/setOfSet01/expected/model_3-solution000003.solution +++ /dev/null @@ -1,6 +0,0 @@ -language Essence 1.3 - -letting x be {{1}} -$ Visualisation for x -$ 1 - diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_3-solution000004.solution b/tests/exhaustive/basic/setOfSet01/expected/model_3-solution000004.solution deleted file mode 100644 index 550c68f48c..0000000000 --- a/tests/exhaustive/basic/setOfSet01/expected/model_3-solution000004.solution +++ /dev/null @@ -1,6 +0,0 @@ -language Essence 1.3 - -letting x be {{2}} -$ Visualisation for x -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_3-solution000005.solution b/tests/exhaustive/basic/setOfSet01/expected/model_3-solution000005.solution deleted file mode 100644 index 114bad5315..0000000000 --- a/tests/exhaustive/basic/setOfSet01/expected/model_3-solution000005.solution +++ /dev/null @@ -1,6 +0,0 @@ -language Essence 1.3 - -letting x be {{1, 2}} -$ Visualisation for x -$ 1 2 - diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_3-solution000006.solution b/tests/exhaustive/basic/setOfSet01/expected/model_3-solution000006.solution deleted file mode 100644 index 3ec452354e..0000000000 --- a/tests/exhaustive/basic/setOfSet01/expected/model_3-solution000006.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {1}} -$ Visualisation for x -$ -$ 1 - diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_3-solution000007.solution b/tests/exhaustive/basic/setOfSet01/expected/model_3-solution000007.solution deleted file mode 100644 index c8946f3d06..0000000000 --- a/tests/exhaustive/basic/setOfSet01/expected/model_3-solution000007.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {2}} -$ Visualisation for x -$ -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_3-solution000008.solution b/tests/exhaustive/basic/setOfSet01/expected/model_3-solution000008.solution deleted file mode 100644 index a6c0b6a43e..0000000000 --- a/tests/exhaustive/basic/setOfSet01/expected/model_3-solution000008.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {1, 2}} -$ Visualisation for x -$ -$ 1 2 - diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_3-solution000009.solution b/tests/exhaustive/basic/setOfSet01/expected/model_3-solution000009.solution deleted file mode 100644 index af16592c51..0000000000 --- a/tests/exhaustive/basic/setOfSet01/expected/model_3-solution000009.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1}, {2}} -$ Visualisation for x -$ 1 -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_3-solution000010.solution b/tests/exhaustive/basic/setOfSet01/expected/model_3-solution000010.solution deleted file mode 100644 index 38937c9389..0000000000 --- a/tests/exhaustive/basic/setOfSet01/expected/model_3-solution000010.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1}, {1, 2}} -$ Visualisation for x -$ 1 -$ 1 2 - diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_3-solution000011.solution b/tests/exhaustive/basic/setOfSet01/expected/model_3-solution000011.solution deleted file mode 100644 index 9bf2af0712..0000000000 --- a/tests/exhaustive/basic/setOfSet01/expected/model_3-solution000011.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1, 2}, {2}} -$ Visualisation for x -$ 1 2 -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_3-solution000012.solution b/tests/exhaustive/basic/setOfSet01/expected/model_3-solution000012.solution deleted file mode 100644 index f1a04b347c..0000000000 --- a/tests/exhaustive/basic/setOfSet01/expected/model_3-solution000012.solution +++ /dev/null @@ -1,8 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {1}, {2}} -$ Visualisation for x -$ -$ 1 -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_3-solution000013.solution b/tests/exhaustive/basic/setOfSet01/expected/model_3-solution000013.solution deleted file mode 100644 index 8400fcb8c1..0000000000 --- a/tests/exhaustive/basic/setOfSet01/expected/model_3-solution000013.solution +++ /dev/null @@ -1,8 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {1}, {1, 2}} -$ Visualisation for x -$ -$ 1 -$ 1 2 - diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_3-solution000014.solution b/tests/exhaustive/basic/setOfSet01/expected/model_3-solution000014.solution deleted file mode 100644 index b1673f700a..0000000000 --- a/tests/exhaustive/basic/setOfSet01/expected/model_3-solution000014.solution +++ /dev/null @@ -1,8 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {1, 2}, {2}} -$ Visualisation for x -$ -$ 1 2 -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_3-solution000015.solution b/tests/exhaustive/basic/setOfSet01/expected/model_3-solution000015.solution deleted file mode 100644 index 7c7f2e98ea..0000000000 --- a/tests/exhaustive/basic/setOfSet01/expected/model_3-solution000015.solution +++ /dev/null @@ -1,8 +0,0 @@ -language Essence 1.3 - -letting x be {{1}, {1, 2}, {2}} -$ Visualisation for x -$ 1 -$ 1 2 -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_3-solution000016.solution b/tests/exhaustive/basic/setOfSet01/expected/model_3-solution000016.solution deleted file mode 100644 index 29f10f5fb0..0000000000 --- a/tests/exhaustive/basic/setOfSet01/expected/model_3-solution000016.solution +++ /dev/null @@ -1,9 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {1}, {1, 2}, {2}} -$ Visualisation for x -$ -$ 1 -$ 1 2 -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_3.eprime b/tests/exhaustive/basic/setOfSet01/expected/model_3.eprime deleted file mode 100644 index dce2bb0e4f..0000000000 --- a/tests/exhaustive/basic/setOfSet01/expected/model_3.eprime +++ /dev/null @@ -1,36 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarkerR5_Marker: int(0..4) -find x_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker: matrix indexed by [int(1..4)] of int(0..2) -find x_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values: - matrix indexed by [int(1..4), int(1..2)] of int(1..2) -branching on - [x_ExplicitVarSizeWithMarkerR5_Marker, x_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker, - x_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values] -such that - and([q1 + 1 <= x_ExplicitVarSizeWithMarkerR5_Marker -> - flatten([[x_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q1]; int(1)], - flatten([[x_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q1, q7]; int(1)] - | q7 : int(1..2)]); - int(1..2)]) - x_ExplicitVarSizeWithMarkerR5_Marker -> - x_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q2] = 0 /\ - and([x_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q2, q9] = 1 | q9 : int(1..2)]) - | q2 : int(1..4)]), - and([q3 <= x_ExplicitVarSizeWithMarkerR5_Marker -> - (2 <= x_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q3] -> - x_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q3, 1] < - x_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q3, 2]) - | q3 : int(1..4)]), - and([q3 <= x_ExplicitVarSizeWithMarkerR5_Marker -> - and([q5 > x_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q3] -> - x_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q3, q5] = 1 - | q5 : int(1..2)]) - | q3 : int(1..4)]) - diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_4-solution000001.solution b/tests/exhaustive/basic/setOfSet01/expected/model_4-solution000001.solution deleted file mode 100644 index 1a734343d9..0000000000 --- a/tests/exhaustive/basic/setOfSet01/expected/model_4-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {} diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_4-solution000002.solution b/tests/exhaustive/basic/setOfSet01/expected/model_4-solution000002.solution deleted file mode 100644 index 7c5b3bfc58..0000000000 --- a/tests/exhaustive/basic/setOfSet01/expected/model_4-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {{}} diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_4-solution000003.solution b/tests/exhaustive/basic/setOfSet01/expected/model_4-solution000003.solution deleted file mode 100644 index 69bc828bbc..0000000000 --- a/tests/exhaustive/basic/setOfSet01/expected/model_4-solution000003.solution +++ /dev/null @@ -1,6 +0,0 @@ -language Essence 1.3 - -letting x be {{1}} -$ Visualisation for x -$ 1 - diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_4-solution000004.solution b/tests/exhaustive/basic/setOfSet01/expected/model_4-solution000004.solution deleted file mode 100644 index 550c68f48c..0000000000 --- a/tests/exhaustive/basic/setOfSet01/expected/model_4-solution000004.solution +++ /dev/null @@ -1,6 +0,0 @@ -language Essence 1.3 - -letting x be {{2}} -$ Visualisation for x -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_4-solution000005.solution b/tests/exhaustive/basic/setOfSet01/expected/model_4-solution000005.solution deleted file mode 100644 index 114bad5315..0000000000 --- a/tests/exhaustive/basic/setOfSet01/expected/model_4-solution000005.solution +++ /dev/null @@ -1,6 +0,0 @@ -language Essence 1.3 - -letting x be {{1, 2}} -$ Visualisation for x -$ 1 2 - diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_4-solution000006.solution b/tests/exhaustive/basic/setOfSet01/expected/model_4-solution000006.solution deleted file mode 100644 index 3ec452354e..0000000000 --- a/tests/exhaustive/basic/setOfSet01/expected/model_4-solution000006.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {1}} -$ Visualisation for x -$ -$ 1 - diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_4-solution000007.solution b/tests/exhaustive/basic/setOfSet01/expected/model_4-solution000007.solution deleted file mode 100644 index c8946f3d06..0000000000 --- a/tests/exhaustive/basic/setOfSet01/expected/model_4-solution000007.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {2}} -$ Visualisation for x -$ -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_4-solution000008.solution b/tests/exhaustive/basic/setOfSet01/expected/model_4-solution000008.solution deleted file mode 100644 index af16592c51..0000000000 --- a/tests/exhaustive/basic/setOfSet01/expected/model_4-solution000008.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1}, {2}} -$ Visualisation for x -$ 1 -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_4-solution000009.solution b/tests/exhaustive/basic/setOfSet01/expected/model_4-solution000009.solution deleted file mode 100644 index a6c0b6a43e..0000000000 --- a/tests/exhaustive/basic/setOfSet01/expected/model_4-solution000009.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {1, 2}} -$ Visualisation for x -$ -$ 1 2 - diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_4-solution000010.solution b/tests/exhaustive/basic/setOfSet01/expected/model_4-solution000010.solution deleted file mode 100644 index 38937c9389..0000000000 --- a/tests/exhaustive/basic/setOfSet01/expected/model_4-solution000010.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1}, {1, 2}} -$ Visualisation for x -$ 1 -$ 1 2 - diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_4-solution000011.solution b/tests/exhaustive/basic/setOfSet01/expected/model_4-solution000011.solution deleted file mode 100644 index 9bf2af0712..0000000000 --- a/tests/exhaustive/basic/setOfSet01/expected/model_4-solution000011.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1, 2}, {2}} -$ Visualisation for x -$ 1 2 -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_4-solution000012.solution b/tests/exhaustive/basic/setOfSet01/expected/model_4-solution000012.solution deleted file mode 100644 index f1a04b347c..0000000000 --- a/tests/exhaustive/basic/setOfSet01/expected/model_4-solution000012.solution +++ /dev/null @@ -1,8 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {1}, {2}} -$ Visualisation for x -$ -$ 1 -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_4-solution000013.solution b/tests/exhaustive/basic/setOfSet01/expected/model_4-solution000013.solution deleted file mode 100644 index 8400fcb8c1..0000000000 --- a/tests/exhaustive/basic/setOfSet01/expected/model_4-solution000013.solution +++ /dev/null @@ -1,8 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {1}, {1, 2}} -$ Visualisation for x -$ -$ 1 -$ 1 2 - diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_4-solution000014.solution b/tests/exhaustive/basic/setOfSet01/expected/model_4-solution000014.solution deleted file mode 100644 index b1673f700a..0000000000 --- a/tests/exhaustive/basic/setOfSet01/expected/model_4-solution000014.solution +++ /dev/null @@ -1,8 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {1, 2}, {2}} -$ Visualisation for x -$ -$ 1 2 -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_4-solution000015.solution b/tests/exhaustive/basic/setOfSet01/expected/model_4-solution000015.solution deleted file mode 100644 index 7c7f2e98ea..0000000000 --- a/tests/exhaustive/basic/setOfSet01/expected/model_4-solution000015.solution +++ /dev/null @@ -1,8 +0,0 @@ -language Essence 1.3 - -letting x be {{1}, {1, 2}, {2}} -$ Visualisation for x -$ 1 -$ 1 2 -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_4-solution000016.solution b/tests/exhaustive/basic/setOfSet01/expected/model_4-solution000016.solution deleted file mode 100644 index 29f10f5fb0..0000000000 --- a/tests/exhaustive/basic/setOfSet01/expected/model_4-solution000016.solution +++ /dev/null @@ -1,9 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {1}, {1, 2}, {2}} -$ Visualisation for x -$ -$ 1 -$ 1 2 -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_4.eprime b/tests/exhaustive/basic/setOfSet01/expected/model_4.eprime deleted file mode 100644 index 979f6d52c7..0000000000 --- a/tests/exhaustive/basic/setOfSet01/expected/model_4.eprime +++ /dev/null @@ -1,43 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarkerR4_Marker: int(0..4) -find x_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Flags: - matrix indexed by [int(1..4), int(1..2)] of bool -find x_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Values: - matrix indexed by [int(1..4), int(1..2)] of int(1..2) -branching on - [x_ExplicitVarSizeWithMarkerR4_Marker, x_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Flags, - x_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Values] -such that - and([q1 + 1 <= x_ExplicitVarSizeWithMarkerR4_Marker -> - flatten([flatten([[-toInt(x_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Flags[q1, q9]); - int(1)], - [x_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Values[q1, q9]; int(1)]; - int(1..2)]) - | q9 : int(1..2)]) - x_ExplicitVarSizeWithMarkerR4_Marker -> - and([x_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Flags[q2, q11] = false | q11 : int(1..2)]) - /\ and([x_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Values[q2, q12] = 1 | q12 : int(1..2)]) - | q2 : int(1..4)]), - and([q3 <= x_ExplicitVarSizeWithMarkerR4_Marker -> - (x_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Flags[q3, 2] -> - x_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Values[q3, 1] < - x_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Values[q3, 2]) - | q3 : int(1..4)]), - and([q3 <= x_ExplicitVarSizeWithMarkerR4_Marker -> - and([x_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Flags[q3, q5] = false -> - x_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Values[q3, q5] = 1 - | q5 : int(1..2)]) - | q3 : int(1..4)]), - and([q3 <= x_ExplicitVarSizeWithMarkerR4_Marker -> - (x_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Flags[q3, 2] -> - x_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Flags[q3, 1]) - | q3 : int(1..4)]) - diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_5-solution000001.solution b/tests/exhaustive/basic/setOfSet01/expected/model_5-solution000001.solution deleted file mode 100644 index 1a734343d9..0000000000 --- a/tests/exhaustive/basic/setOfSet01/expected/model_5-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {} diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_5-solution000002.solution b/tests/exhaustive/basic/setOfSet01/expected/model_5-solution000002.solution deleted file mode 100644 index 7c5b3bfc58..0000000000 --- a/tests/exhaustive/basic/setOfSet01/expected/model_5-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {{}} diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_5-solution000003.solution b/tests/exhaustive/basic/setOfSet01/expected/model_5-solution000003.solution deleted file mode 100644 index 550c68f48c..0000000000 --- a/tests/exhaustive/basic/setOfSet01/expected/model_5-solution000003.solution +++ /dev/null @@ -1,6 +0,0 @@ -language Essence 1.3 - -letting x be {{2}} -$ Visualisation for x -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_5-solution000004.solution b/tests/exhaustive/basic/setOfSet01/expected/model_5-solution000004.solution deleted file mode 100644 index 69bc828bbc..0000000000 --- a/tests/exhaustive/basic/setOfSet01/expected/model_5-solution000004.solution +++ /dev/null @@ -1,6 +0,0 @@ -language Essence 1.3 - -letting x be {{1}} -$ Visualisation for x -$ 1 - diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_5-solution000005.solution b/tests/exhaustive/basic/setOfSet01/expected/model_5-solution000005.solution deleted file mode 100644 index 114bad5315..0000000000 --- a/tests/exhaustive/basic/setOfSet01/expected/model_5-solution000005.solution +++ /dev/null @@ -1,6 +0,0 @@ -language Essence 1.3 - -letting x be {{1, 2}} -$ Visualisation for x -$ 1 2 - diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_5-solution000006.solution b/tests/exhaustive/basic/setOfSet01/expected/model_5-solution000006.solution deleted file mode 100644 index c8946f3d06..0000000000 --- a/tests/exhaustive/basic/setOfSet01/expected/model_5-solution000006.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {2}} -$ Visualisation for x -$ -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_5-solution000007.solution b/tests/exhaustive/basic/setOfSet01/expected/model_5-solution000007.solution deleted file mode 100644 index 3ec452354e..0000000000 --- a/tests/exhaustive/basic/setOfSet01/expected/model_5-solution000007.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {1}} -$ Visualisation for x -$ -$ 1 - diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_5-solution000008.solution b/tests/exhaustive/basic/setOfSet01/expected/model_5-solution000008.solution deleted file mode 100644 index af16592c51..0000000000 --- a/tests/exhaustive/basic/setOfSet01/expected/model_5-solution000008.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1}, {2}} -$ Visualisation for x -$ 1 -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_5-solution000009.solution b/tests/exhaustive/basic/setOfSet01/expected/model_5-solution000009.solution deleted file mode 100644 index a6c0b6a43e..0000000000 --- a/tests/exhaustive/basic/setOfSet01/expected/model_5-solution000009.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {1, 2}} -$ Visualisation for x -$ -$ 1 2 - diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_5-solution000010.solution b/tests/exhaustive/basic/setOfSet01/expected/model_5-solution000010.solution deleted file mode 100644 index 9bf2af0712..0000000000 --- a/tests/exhaustive/basic/setOfSet01/expected/model_5-solution000010.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1, 2}, {2}} -$ Visualisation for x -$ 1 2 -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_5-solution000011.solution b/tests/exhaustive/basic/setOfSet01/expected/model_5-solution000011.solution deleted file mode 100644 index 38937c9389..0000000000 --- a/tests/exhaustive/basic/setOfSet01/expected/model_5-solution000011.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1}, {1, 2}} -$ Visualisation for x -$ 1 -$ 1 2 - diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_5-solution000012.solution b/tests/exhaustive/basic/setOfSet01/expected/model_5-solution000012.solution deleted file mode 100644 index f1a04b347c..0000000000 --- a/tests/exhaustive/basic/setOfSet01/expected/model_5-solution000012.solution +++ /dev/null @@ -1,8 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {1}, {2}} -$ Visualisation for x -$ -$ 1 -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_5-solution000013.solution b/tests/exhaustive/basic/setOfSet01/expected/model_5-solution000013.solution deleted file mode 100644 index b1673f700a..0000000000 --- a/tests/exhaustive/basic/setOfSet01/expected/model_5-solution000013.solution +++ /dev/null @@ -1,8 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {1, 2}, {2}} -$ Visualisation for x -$ -$ 1 2 -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_5-solution000014.solution b/tests/exhaustive/basic/setOfSet01/expected/model_5-solution000014.solution deleted file mode 100644 index 8400fcb8c1..0000000000 --- a/tests/exhaustive/basic/setOfSet01/expected/model_5-solution000014.solution +++ /dev/null @@ -1,8 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {1}, {1, 2}} -$ Visualisation for x -$ -$ 1 -$ 1 2 - diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_5-solution000015.solution b/tests/exhaustive/basic/setOfSet01/expected/model_5-solution000015.solution deleted file mode 100644 index 7c7f2e98ea..0000000000 --- a/tests/exhaustive/basic/setOfSet01/expected/model_5-solution000015.solution +++ /dev/null @@ -1,8 +0,0 @@ -language Essence 1.3 - -letting x be {{1}, {1, 2}, {2}} -$ Visualisation for x -$ 1 -$ 1 2 -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_5-solution000016.solution b/tests/exhaustive/basic/setOfSet01/expected/model_5-solution000016.solution deleted file mode 100644 index 29f10f5fb0..0000000000 --- a/tests/exhaustive/basic/setOfSet01/expected/model_5-solution000016.solution +++ /dev/null @@ -1,9 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {1}, {1, 2}, {2}} -$ Visualisation for x -$ -$ 1 -$ 1 2 -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_5.eprime b/tests/exhaustive/basic/setOfSet01/expected/model_5.eprime deleted file mode 100644 index f99416596c..0000000000 --- a/tests/exhaustive/basic/setOfSet01/expected/model_5.eprime +++ /dev/null @@ -1,15 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlagsR2_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlagsR2_Values_Occurrence: matrix indexed by [int(1..4), int(1..2)] of bool -branching on [x_ExplicitVarSizeWithFlagsR2_Flags, x_ExplicitVarSizeWithFlagsR2_Values_Occurrence] -such that - and([x_ExplicitVarSizeWithFlagsR2_Flags[q1 + 1] -> - [-toInt(x_ExplicitVarSizeWithFlagsR2_Values_Occurrence[q1, q7]) | q7 : int(1..2)] - and([x_ExplicitVarSizeWithFlagsR2_Values_Occurrence[q2, q9] = false | q9 : int(1..2)]) - | q2 : int(1..4)]), - and([x_ExplicitVarSizeWithFlagsR2_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlagsR2_Flags[q3] | q3 : int(1..3)]) - diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_6-solution000001.solution b/tests/exhaustive/basic/setOfSet01/expected/model_6-solution000001.solution deleted file mode 100644 index 1a734343d9..0000000000 --- a/tests/exhaustive/basic/setOfSet01/expected/model_6-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {} diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_6-solution000002.solution b/tests/exhaustive/basic/setOfSet01/expected/model_6-solution000002.solution deleted file mode 100644 index 114bad5315..0000000000 --- a/tests/exhaustive/basic/setOfSet01/expected/model_6-solution000002.solution +++ /dev/null @@ -1,6 +0,0 @@ -language Essence 1.3 - -letting x be {{1, 2}} -$ Visualisation for x -$ 1 2 - diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_6-solution000003.solution b/tests/exhaustive/basic/setOfSet01/expected/model_6-solution000003.solution deleted file mode 100644 index 69bc828bbc..0000000000 --- a/tests/exhaustive/basic/setOfSet01/expected/model_6-solution000003.solution +++ /dev/null @@ -1,6 +0,0 @@ -language Essence 1.3 - -letting x be {{1}} -$ Visualisation for x -$ 1 - diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_6-solution000004.solution b/tests/exhaustive/basic/setOfSet01/expected/model_6-solution000004.solution deleted file mode 100644 index 550c68f48c..0000000000 --- a/tests/exhaustive/basic/setOfSet01/expected/model_6-solution000004.solution +++ /dev/null @@ -1,6 +0,0 @@ -language Essence 1.3 - -letting x be {{2}} -$ Visualisation for x -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_6-solution000005.solution b/tests/exhaustive/basic/setOfSet01/expected/model_6-solution000005.solution deleted file mode 100644 index 7c5b3bfc58..0000000000 --- a/tests/exhaustive/basic/setOfSet01/expected/model_6-solution000005.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {{}} diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_6-solution000006.solution b/tests/exhaustive/basic/setOfSet01/expected/model_6-solution000006.solution deleted file mode 100644 index 38937c9389..0000000000 --- a/tests/exhaustive/basic/setOfSet01/expected/model_6-solution000006.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1}, {1, 2}} -$ Visualisation for x -$ 1 -$ 1 2 - diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_6-solution000007.solution b/tests/exhaustive/basic/setOfSet01/expected/model_6-solution000007.solution deleted file mode 100644 index 9bf2af0712..0000000000 --- a/tests/exhaustive/basic/setOfSet01/expected/model_6-solution000007.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1, 2}, {2}} -$ Visualisation for x -$ 1 2 -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_6-solution000008.solution b/tests/exhaustive/basic/setOfSet01/expected/model_6-solution000008.solution deleted file mode 100644 index a6c0b6a43e..0000000000 --- a/tests/exhaustive/basic/setOfSet01/expected/model_6-solution000008.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {1, 2}} -$ Visualisation for x -$ -$ 1 2 - diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_6-solution000009.solution b/tests/exhaustive/basic/setOfSet01/expected/model_6-solution000009.solution deleted file mode 100644 index af16592c51..0000000000 --- a/tests/exhaustive/basic/setOfSet01/expected/model_6-solution000009.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1}, {2}} -$ Visualisation for x -$ 1 -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_6-solution000010.solution b/tests/exhaustive/basic/setOfSet01/expected/model_6-solution000010.solution deleted file mode 100644 index 3ec452354e..0000000000 --- a/tests/exhaustive/basic/setOfSet01/expected/model_6-solution000010.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {1}} -$ Visualisation for x -$ -$ 1 - diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_6-solution000011.solution b/tests/exhaustive/basic/setOfSet01/expected/model_6-solution000011.solution deleted file mode 100644 index c8946f3d06..0000000000 --- a/tests/exhaustive/basic/setOfSet01/expected/model_6-solution000011.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {2}} -$ Visualisation for x -$ -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_6-solution000012.solution b/tests/exhaustive/basic/setOfSet01/expected/model_6-solution000012.solution deleted file mode 100644 index 7c7f2e98ea..0000000000 --- a/tests/exhaustive/basic/setOfSet01/expected/model_6-solution000012.solution +++ /dev/null @@ -1,8 +0,0 @@ -language Essence 1.3 - -letting x be {{1}, {1, 2}, {2}} -$ Visualisation for x -$ 1 -$ 1 2 -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_6-solution000013.solution b/tests/exhaustive/basic/setOfSet01/expected/model_6-solution000013.solution deleted file mode 100644 index 8400fcb8c1..0000000000 --- a/tests/exhaustive/basic/setOfSet01/expected/model_6-solution000013.solution +++ /dev/null @@ -1,8 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {1}, {1, 2}} -$ Visualisation for x -$ -$ 1 -$ 1 2 - diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_6-solution000014.solution b/tests/exhaustive/basic/setOfSet01/expected/model_6-solution000014.solution deleted file mode 100644 index b1673f700a..0000000000 --- a/tests/exhaustive/basic/setOfSet01/expected/model_6-solution000014.solution +++ /dev/null @@ -1,8 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {1, 2}, {2}} -$ Visualisation for x -$ -$ 1 2 -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_6-solution000015.solution b/tests/exhaustive/basic/setOfSet01/expected/model_6-solution000015.solution deleted file mode 100644 index f1a04b347c..0000000000 --- a/tests/exhaustive/basic/setOfSet01/expected/model_6-solution000015.solution +++ /dev/null @@ -1,8 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {1}, {2}} -$ Visualisation for x -$ -$ 1 -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_6-solution000016.solution b/tests/exhaustive/basic/setOfSet01/expected/model_6-solution000016.solution deleted file mode 100644 index 29f10f5fb0..0000000000 --- a/tests/exhaustive/basic/setOfSet01/expected/model_6-solution000016.solution +++ /dev/null @@ -1,9 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {1}, {1, 2}, {2}} -$ Visualisation for x -$ -$ 1 -$ 1 2 -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_6.eprime b/tests/exhaustive/basic/setOfSet01/expected/model_6.eprime deleted file mode 100644 index f1ff4362d3..0000000000 --- a/tests/exhaustive/basic/setOfSet01/expected/model_6.eprime +++ /dev/null @@ -1,24 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlagsR6_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlagsR6_Values_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4), int(1..2)] of int(1..3) -branching on [x_ExplicitVarSizeWithFlagsR6_Flags, x_ExplicitVarSizeWithFlagsR6_Values_ExplicitVarSizeWithDummy] -such that - and([x_ExplicitVarSizeWithFlagsR6_Flags[q1 + 1] -> - [x_ExplicitVarSizeWithFlagsR6_Values_ExplicitVarSizeWithDummy[q1, q10] | q10 : int(1..2)] - and([x_ExplicitVarSizeWithFlagsR6_Values_ExplicitVarSizeWithDummy[q2, q12] = 1 | q12 : int(1..2)]) - | q2 : int(1..4)]), - and([x_ExplicitVarSizeWithFlagsR6_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlagsR6_Flags[q3] | q3 : int(1..3)]), - and([x_ExplicitVarSizeWithFlagsR6_Flags[q5] -> - x_ExplicitVarSizeWithFlagsR6_Values_ExplicitVarSizeWithDummy[q5, 1] < - x_ExplicitVarSizeWithFlagsR6_Values_ExplicitVarSizeWithDummy[q5, 2] - \/ x_ExplicitVarSizeWithFlagsR6_Values_ExplicitVarSizeWithDummy[q5, 1] = 3 - | q5 : int(1..4)]), - and([x_ExplicitVarSizeWithFlagsR6_Flags[q5] -> - (x_ExplicitVarSizeWithFlagsR6_Values_ExplicitVarSizeWithDummy[q5, 1] = 3 -> - x_ExplicitVarSizeWithFlagsR6_Values_ExplicitVarSizeWithDummy[q5, 2] = 3) - | q5 : int(1..4)]) - diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_7-solution000001.solution b/tests/exhaustive/basic/setOfSet01/expected/model_7-solution000001.solution deleted file mode 100644 index 1a734343d9..0000000000 --- a/tests/exhaustive/basic/setOfSet01/expected/model_7-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {} diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_7-solution000002.solution b/tests/exhaustive/basic/setOfSet01/expected/model_7-solution000002.solution deleted file mode 100644 index 7c5b3bfc58..0000000000 --- a/tests/exhaustive/basic/setOfSet01/expected/model_7-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {{}} diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_7-solution000003.solution b/tests/exhaustive/basic/setOfSet01/expected/model_7-solution000003.solution deleted file mode 100644 index 69bc828bbc..0000000000 --- a/tests/exhaustive/basic/setOfSet01/expected/model_7-solution000003.solution +++ /dev/null @@ -1,6 +0,0 @@ -language Essence 1.3 - -letting x be {{1}} -$ Visualisation for x -$ 1 - diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_7-solution000004.solution b/tests/exhaustive/basic/setOfSet01/expected/model_7-solution000004.solution deleted file mode 100644 index 550c68f48c..0000000000 --- a/tests/exhaustive/basic/setOfSet01/expected/model_7-solution000004.solution +++ /dev/null @@ -1,6 +0,0 @@ -language Essence 1.3 - -letting x be {{2}} -$ Visualisation for x -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_7-solution000005.solution b/tests/exhaustive/basic/setOfSet01/expected/model_7-solution000005.solution deleted file mode 100644 index 114bad5315..0000000000 --- a/tests/exhaustive/basic/setOfSet01/expected/model_7-solution000005.solution +++ /dev/null @@ -1,6 +0,0 @@ -language Essence 1.3 - -letting x be {{1, 2}} -$ Visualisation for x -$ 1 2 - diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_7-solution000006.solution b/tests/exhaustive/basic/setOfSet01/expected/model_7-solution000006.solution deleted file mode 100644 index 3ec452354e..0000000000 --- a/tests/exhaustive/basic/setOfSet01/expected/model_7-solution000006.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {1}} -$ Visualisation for x -$ -$ 1 - diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_7-solution000007.solution b/tests/exhaustive/basic/setOfSet01/expected/model_7-solution000007.solution deleted file mode 100644 index c8946f3d06..0000000000 --- a/tests/exhaustive/basic/setOfSet01/expected/model_7-solution000007.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {2}} -$ Visualisation for x -$ -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_7-solution000008.solution b/tests/exhaustive/basic/setOfSet01/expected/model_7-solution000008.solution deleted file mode 100644 index a6c0b6a43e..0000000000 --- a/tests/exhaustive/basic/setOfSet01/expected/model_7-solution000008.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {1, 2}} -$ Visualisation for x -$ -$ 1 2 - diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_7-solution000009.solution b/tests/exhaustive/basic/setOfSet01/expected/model_7-solution000009.solution deleted file mode 100644 index af16592c51..0000000000 --- a/tests/exhaustive/basic/setOfSet01/expected/model_7-solution000009.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1}, {2}} -$ Visualisation for x -$ 1 -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_7-solution000010.solution b/tests/exhaustive/basic/setOfSet01/expected/model_7-solution000010.solution deleted file mode 100644 index 38937c9389..0000000000 --- a/tests/exhaustive/basic/setOfSet01/expected/model_7-solution000010.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1}, {1, 2}} -$ Visualisation for x -$ 1 -$ 1 2 - diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_7-solution000011.solution b/tests/exhaustive/basic/setOfSet01/expected/model_7-solution000011.solution deleted file mode 100644 index 9bf2af0712..0000000000 --- a/tests/exhaustive/basic/setOfSet01/expected/model_7-solution000011.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1, 2}, {2}} -$ Visualisation for x -$ 1 2 -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_7-solution000012.solution b/tests/exhaustive/basic/setOfSet01/expected/model_7-solution000012.solution deleted file mode 100644 index f1a04b347c..0000000000 --- a/tests/exhaustive/basic/setOfSet01/expected/model_7-solution000012.solution +++ /dev/null @@ -1,8 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {1}, {2}} -$ Visualisation for x -$ -$ 1 -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_7-solution000013.solution b/tests/exhaustive/basic/setOfSet01/expected/model_7-solution000013.solution deleted file mode 100644 index 8400fcb8c1..0000000000 --- a/tests/exhaustive/basic/setOfSet01/expected/model_7-solution000013.solution +++ /dev/null @@ -1,8 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {1}, {1, 2}} -$ Visualisation for x -$ -$ 1 -$ 1 2 - diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_7-solution000014.solution b/tests/exhaustive/basic/setOfSet01/expected/model_7-solution000014.solution deleted file mode 100644 index b1673f700a..0000000000 --- a/tests/exhaustive/basic/setOfSet01/expected/model_7-solution000014.solution +++ /dev/null @@ -1,8 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {1, 2}, {2}} -$ Visualisation for x -$ -$ 1 2 -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_7-solution000015.solution b/tests/exhaustive/basic/setOfSet01/expected/model_7-solution000015.solution deleted file mode 100644 index 7c7f2e98ea..0000000000 --- a/tests/exhaustive/basic/setOfSet01/expected/model_7-solution000015.solution +++ /dev/null @@ -1,8 +0,0 @@ -language Essence 1.3 - -letting x be {{1}, {1, 2}, {2}} -$ Visualisation for x -$ 1 -$ 1 2 -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_7-solution000016.solution b/tests/exhaustive/basic/setOfSet01/expected/model_7-solution000016.solution deleted file mode 100644 index 29f10f5fb0..0000000000 --- a/tests/exhaustive/basic/setOfSet01/expected/model_7-solution000016.solution +++ /dev/null @@ -1,9 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {1}, {1, 2}, {2}} -$ Visualisation for x -$ -$ 1 -$ 1 2 -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_7.eprime b/tests/exhaustive/basic/setOfSet01/expected/model_7.eprime deleted file mode 100644 index 16bde38bdd..0000000000 --- a/tests/exhaustive/basic/setOfSet01/expected/model_7.eprime +++ /dev/null @@ -1,37 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlagsR5_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Marker: matrix indexed by [int(1..4)] of int(0..2) -find x_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Values: - matrix indexed by [int(1..4), int(1..2)] of int(1..2) -branching on - [x_ExplicitVarSizeWithFlagsR5_Flags, x_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Marker, - x_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Values] -such that - and([x_ExplicitVarSizeWithFlagsR5_Flags[q1 + 1] -> - flatten([[x_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Marker[q1]; int(1)], - flatten([[x_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Values[q1, q9]; int(1)] - | q9 : int(1..2)]); - int(1..2)]) - - x_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Marker[q2] = 0 /\ - and([x_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Values[q2, q11] = 1 | q11 : int(1..2)]) - | q2 : int(1..4)]), - and([x_ExplicitVarSizeWithFlagsR5_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlagsR5_Flags[q3] | q3 : int(1..3)]), - and([x_ExplicitVarSizeWithFlagsR5_Flags[q5] -> - (2 <= x_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Marker[q5] -> - x_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Values[q5, 1] < - x_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Values[q5, 2]) - | q5 : int(1..4)]), - and([x_ExplicitVarSizeWithFlagsR5_Flags[q5] -> - and([q7 > x_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Marker[q5] -> - x_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Values[q5, q7] = 1 - | q7 : int(1..2)]) - | q5 : int(1..4)]) - diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_8-solution000001.solution b/tests/exhaustive/basic/setOfSet01/expected/model_8-solution000001.solution deleted file mode 100644 index 1a734343d9..0000000000 --- a/tests/exhaustive/basic/setOfSet01/expected/model_8-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {} diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_8-solution000002.solution b/tests/exhaustive/basic/setOfSet01/expected/model_8-solution000002.solution deleted file mode 100644 index 7c5b3bfc58..0000000000 --- a/tests/exhaustive/basic/setOfSet01/expected/model_8-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {{}} diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_8-solution000003.solution b/tests/exhaustive/basic/setOfSet01/expected/model_8-solution000003.solution deleted file mode 100644 index 69bc828bbc..0000000000 --- a/tests/exhaustive/basic/setOfSet01/expected/model_8-solution000003.solution +++ /dev/null @@ -1,6 +0,0 @@ -language Essence 1.3 - -letting x be {{1}} -$ Visualisation for x -$ 1 - diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_8-solution000004.solution b/tests/exhaustive/basic/setOfSet01/expected/model_8-solution000004.solution deleted file mode 100644 index 550c68f48c..0000000000 --- a/tests/exhaustive/basic/setOfSet01/expected/model_8-solution000004.solution +++ /dev/null @@ -1,6 +0,0 @@ -language Essence 1.3 - -letting x be {{2}} -$ Visualisation for x -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_8-solution000005.solution b/tests/exhaustive/basic/setOfSet01/expected/model_8-solution000005.solution deleted file mode 100644 index 114bad5315..0000000000 --- a/tests/exhaustive/basic/setOfSet01/expected/model_8-solution000005.solution +++ /dev/null @@ -1,6 +0,0 @@ -language Essence 1.3 - -letting x be {{1, 2}} -$ Visualisation for x -$ 1 2 - diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_8-solution000006.solution b/tests/exhaustive/basic/setOfSet01/expected/model_8-solution000006.solution deleted file mode 100644 index 3ec452354e..0000000000 --- a/tests/exhaustive/basic/setOfSet01/expected/model_8-solution000006.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {1}} -$ Visualisation for x -$ -$ 1 - diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_8-solution000007.solution b/tests/exhaustive/basic/setOfSet01/expected/model_8-solution000007.solution deleted file mode 100644 index c8946f3d06..0000000000 --- a/tests/exhaustive/basic/setOfSet01/expected/model_8-solution000007.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {2}} -$ Visualisation for x -$ -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_8-solution000008.solution b/tests/exhaustive/basic/setOfSet01/expected/model_8-solution000008.solution deleted file mode 100644 index af16592c51..0000000000 --- a/tests/exhaustive/basic/setOfSet01/expected/model_8-solution000008.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1}, {2}} -$ Visualisation for x -$ 1 -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_8-solution000009.solution b/tests/exhaustive/basic/setOfSet01/expected/model_8-solution000009.solution deleted file mode 100644 index a6c0b6a43e..0000000000 --- a/tests/exhaustive/basic/setOfSet01/expected/model_8-solution000009.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {1, 2}} -$ Visualisation for x -$ -$ 1 2 - diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_8-solution000010.solution b/tests/exhaustive/basic/setOfSet01/expected/model_8-solution000010.solution deleted file mode 100644 index 38937c9389..0000000000 --- a/tests/exhaustive/basic/setOfSet01/expected/model_8-solution000010.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1}, {1, 2}} -$ Visualisation for x -$ 1 -$ 1 2 - diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_8-solution000011.solution b/tests/exhaustive/basic/setOfSet01/expected/model_8-solution000011.solution deleted file mode 100644 index 9bf2af0712..0000000000 --- a/tests/exhaustive/basic/setOfSet01/expected/model_8-solution000011.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1, 2}, {2}} -$ Visualisation for x -$ 1 2 -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_8-solution000012.solution b/tests/exhaustive/basic/setOfSet01/expected/model_8-solution000012.solution deleted file mode 100644 index f1a04b347c..0000000000 --- a/tests/exhaustive/basic/setOfSet01/expected/model_8-solution000012.solution +++ /dev/null @@ -1,8 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {1}, {2}} -$ Visualisation for x -$ -$ 1 -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_8-solution000013.solution b/tests/exhaustive/basic/setOfSet01/expected/model_8-solution000013.solution deleted file mode 100644 index 8400fcb8c1..0000000000 --- a/tests/exhaustive/basic/setOfSet01/expected/model_8-solution000013.solution +++ /dev/null @@ -1,8 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {1}, {1, 2}} -$ Visualisation for x -$ -$ 1 -$ 1 2 - diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_8-solution000014.solution b/tests/exhaustive/basic/setOfSet01/expected/model_8-solution000014.solution deleted file mode 100644 index b1673f700a..0000000000 --- a/tests/exhaustive/basic/setOfSet01/expected/model_8-solution000014.solution +++ /dev/null @@ -1,8 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {1, 2}, {2}} -$ Visualisation for x -$ -$ 1 2 -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_8-solution000015.solution b/tests/exhaustive/basic/setOfSet01/expected/model_8-solution000015.solution deleted file mode 100644 index 7c7f2e98ea..0000000000 --- a/tests/exhaustive/basic/setOfSet01/expected/model_8-solution000015.solution +++ /dev/null @@ -1,8 +0,0 @@ -language Essence 1.3 - -letting x be {{1}, {1, 2}, {2}} -$ Visualisation for x -$ 1 -$ 1 2 -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_8-solution000016.solution b/tests/exhaustive/basic/setOfSet01/expected/model_8-solution000016.solution deleted file mode 100644 index 29f10f5fb0..0000000000 --- a/tests/exhaustive/basic/setOfSet01/expected/model_8-solution000016.solution +++ /dev/null @@ -1,9 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {1}, {1, 2}, {2}} -$ Visualisation for x -$ -$ 1 -$ 1 2 -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_8.eprime b/tests/exhaustive/basic/setOfSet01/expected/model_8.eprime deleted file mode 100644 index 2e31cf9b1f..0000000000 --- a/tests/exhaustive/basic/setOfSet01/expected/model_8.eprime +++ /dev/null @@ -1,44 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlagsR4_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Flags: - matrix indexed by [int(1..4), int(1..2)] of bool -find x_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Values: - matrix indexed by [int(1..4), int(1..2)] of int(1..2) -branching on - [x_ExplicitVarSizeWithFlagsR4_Flags, x_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Flags, - x_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Values] -such that - and([x_ExplicitVarSizeWithFlagsR4_Flags[q1 + 1] -> - flatten([flatten([[-toInt(x_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Flags[q1, q11]); - int(1)], - [x_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Values[q1, q11]; int(1)]; - int(1..2)]) - | q11 : int(1..2)]) - - and([x_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Flags[q2, q13] = false | q13 : int(1..2)]) /\ - and([x_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Values[q2, q14] = 1 | q14 : int(1..2)]) - | q2 : int(1..4)]), - and([x_ExplicitVarSizeWithFlagsR4_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlagsR4_Flags[q3] | q3 : int(1..3)]), - and([x_ExplicitVarSizeWithFlagsR4_Flags[q5] -> - (x_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Flags[q5, 2] -> - x_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Values[q5, 1] < - x_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Values[q5, 2]) - | q5 : int(1..4)]), - and([x_ExplicitVarSizeWithFlagsR4_Flags[q5] -> - and([x_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Flags[q5, q7] = false -> - x_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Values[q5, q7] = 1 - | q7 : int(1..2)]) - | q5 : int(1..4)]), - and([x_ExplicitVarSizeWithFlagsR4_Flags[q5] -> - (x_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Flags[q5, 2] -> - x_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Flags[q5, 1]) - | q5 : int(1..4)]) - diff --git a/tests/exhaustive/basic/setOfSet02/expected/model_1_1-solution000001.solution b/tests/exhaustive/basic/setOfSet02/expected/model_1_1-solution000001.solution deleted file mode 100644 index 655f6dc09d..0000000000 --- a/tests/exhaustive/basic/setOfSet02/expected/model_1_1-solution000001.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1, 2, 3}, {2, 3, 4}} -$ Visualisation for x -$ 1 2 3 -$ 2 3 4 - diff --git a/tests/exhaustive/basic/setOfSet02/expected/model_1_1-solution000002.solution b/tests/exhaustive/basic/setOfSet02/expected/model_1_1-solution000002.solution deleted file mode 100644 index 707d6ddaf7..0000000000 --- a/tests/exhaustive/basic/setOfSet02/expected/model_1_1-solution000002.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1, 2, 3}, {1, 3, 4}} -$ Visualisation for x -$ 1 2 3 -$ 1 3 4 - diff --git a/tests/exhaustive/basic/setOfSet02/expected/model_1_1-solution000003.solution b/tests/exhaustive/basic/setOfSet02/expected/model_1_1-solution000003.solution deleted file mode 100644 index 8fed97dc70..0000000000 --- a/tests/exhaustive/basic/setOfSet02/expected/model_1_1-solution000003.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1, 2, 3}, {1, 2, 4}} -$ Visualisation for x -$ 1 2 3 -$ 1 2 4 - diff --git a/tests/exhaustive/basic/setOfSet02/expected/model_1_1.eprime b/tests/exhaustive/basic/setOfSet02/expected/model_1_1.eprime deleted file mode 100644 index 21cd13a0b4..0000000000 --- a/tests/exhaustive/basic/setOfSet02/expected/model_1_1.eprime +++ /dev/null @@ -1,12 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitR2_Occurrence: matrix indexed by [int(1..2), int(1..4)] of bool -branching on [x_ExplicitR2_Occurrence] -such that - or([and([x_ExplicitR2_Occurrence[q7, q8] -> or([1 = q8, 2 = q8, 3 = q8; int(1..3)]) | q8 : int(1..4)]) /\ - and([x_ExplicitR2_Occurrence[q7, 1], x_ExplicitR2_Occurrence[q7, 2], x_ExplicitR2_Occurrence[q7, 3]; int(1..3)]) - | q7 : int(1..2)]), - [-toInt(x_ExplicitR2_Occurrence[1, q4]) | q4 : int(1..4)] or([1 = q32, 2 = q32, 3 = q32; int(1..3)]) | q32 : int(1..4)]) /\ - and([x_ExplicitR2_Occurrence[q31, 1], x_ExplicitR2_Occurrence[q31, 2], x_ExplicitR2_Occurrence[q31, 3]; - int(1..3)]) - | q31 : int(1..2)]), - [-toInt(x_ExplicitR2_Occurrence[1, q4]) | q4 : int(1..4)] or([x_ExplicitR3_Explicit[q13, q18] = q16 | q18 : int(1..3)]) - | q16 : int(1..4)]) - /\ and([x_ExplicitR2_Occurrence[q15, x_ExplicitR3_Explicit[q13, q20]] | q20 : int(1..3)]) - | q15 : int(1..2)]) - | q13 : int(1..2)]), - and([or([and([x_ExplicitR2_Occurrence[q22, x_ExplicitR3_Explicit[q24, q26]] | q26 : int(1..3)]) /\ - and([x_ExplicitR2_Occurrence[q22, q27] -> or([x_ExplicitR3_Explicit[q24, q29] = q27 | q29 : int(1..3)]) - | q27 : int(1..4)]) - | q24 : int(1..2)]) - | q22 : int(1..2)]) - diff --git a/tests/exhaustive/basic/setOfSet02/expected/model_2_1-solution000001.solution b/tests/exhaustive/basic/setOfSet02/expected/model_2_1-solution000001.solution deleted file mode 100644 index 655f6dc09d..0000000000 --- a/tests/exhaustive/basic/setOfSet02/expected/model_2_1-solution000001.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1, 2, 3}, {2, 3, 4}} -$ Visualisation for x -$ 1 2 3 -$ 2 3 4 - diff --git a/tests/exhaustive/basic/setOfSet02/expected/model_2_1-solution000002.solution b/tests/exhaustive/basic/setOfSet02/expected/model_2_1-solution000002.solution deleted file mode 100644 index 707d6ddaf7..0000000000 --- a/tests/exhaustive/basic/setOfSet02/expected/model_2_1-solution000002.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1, 2, 3}, {1, 3, 4}} -$ Visualisation for x -$ 1 2 3 -$ 1 3 4 - diff --git a/tests/exhaustive/basic/setOfSet02/expected/model_2_1-solution000003.solution b/tests/exhaustive/basic/setOfSet02/expected/model_2_1-solution000003.solution deleted file mode 100644 index 8fed97dc70..0000000000 --- a/tests/exhaustive/basic/setOfSet02/expected/model_2_1-solution000003.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1, 2, 3}, {1, 2, 4}} -$ Visualisation for x -$ 1 2 3 -$ 1 2 4 - diff --git a/tests/exhaustive/basic/setOfSet02/expected/model_2_1.eprime b/tests/exhaustive/basic/setOfSet02/expected/model_2_1.eprime deleted file mode 100644 index 98d4009220..0000000000 --- a/tests/exhaustive/basic/setOfSet02/expected/model_2_1.eprime +++ /dev/null @@ -1,33 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitR3_Explicit: matrix indexed by [int(1..2), int(1..3)] of int(1..4) -find x_ExplicitR2_Occurrence: matrix indexed by [int(1..2), int(1..4)] of bool -branching on [x_ExplicitR2_Occurrence, x_ExplicitR3_Explicit] -such that - or([and([or([1 = x_ExplicitR3_Explicit[q31, q33], 2 = x_ExplicitR3_Explicit[q31, q33], - 3 = x_ExplicitR3_Explicit[q31, q33]; - int(1..3)]) - | q33 : int(1..3)]) - /\ - and([or([x_ExplicitR3_Explicit[q31, q39] = 1 | q39 : int(1..3)]), - or([x_ExplicitR3_Explicit[q31, q41] = 2 | q41 : int(1..3)]), - or([x_ExplicitR3_Explicit[q31, q43] = 3 | q43 : int(1..3)]); - int(1..3)]) - | q31 : int(1..2)]), - flatten([[x_ExplicitR3_Explicit[1, q5]; int(1)] | q5 : int(1..3)]) or([x_ExplicitR3_Explicit[q15, q20] = q18 | q20 : int(1..3)]) - | q18 : int(1..4)]) - | q15 : int(1..2)]) - | q13 : int(1..2)]), - and([or([and([x_ExplicitR2_Occurrence[q24, q25] -> or([x_ExplicitR3_Explicit[q22, q27] = q25 | q27 : int(1..3)]) - | q25 : int(1..4)]) - /\ and([x_ExplicitR2_Occurrence[q24, x_ExplicitR3_Explicit[q22, q29]] | q29 : int(1..3)]) - | q24 : int(1..2)]) - | q22 : int(1..2)]) - diff --git a/tests/exhaustive/basic/setOfSet02/expected/model_2_2-solution000001.solution b/tests/exhaustive/basic/setOfSet02/expected/model_2_2-solution000001.solution deleted file mode 100644 index 8fed97dc70..0000000000 --- a/tests/exhaustive/basic/setOfSet02/expected/model_2_2-solution000001.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1, 2, 3}, {1, 2, 4}} -$ Visualisation for x -$ 1 2 3 -$ 1 2 4 - diff --git a/tests/exhaustive/basic/setOfSet02/expected/model_2_2-solution000002.solution b/tests/exhaustive/basic/setOfSet02/expected/model_2_2-solution000002.solution deleted file mode 100644 index 707d6ddaf7..0000000000 --- a/tests/exhaustive/basic/setOfSet02/expected/model_2_2-solution000002.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1, 2, 3}, {1, 3, 4}} -$ Visualisation for x -$ 1 2 3 -$ 1 3 4 - diff --git a/tests/exhaustive/basic/setOfSet02/expected/model_2_2-solution000003.solution b/tests/exhaustive/basic/setOfSet02/expected/model_2_2-solution000003.solution deleted file mode 100644 index 655f6dc09d..0000000000 --- a/tests/exhaustive/basic/setOfSet02/expected/model_2_2-solution000003.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1, 2, 3}, {2, 3, 4}} -$ Visualisation for x -$ 1 2 3 -$ 2 3 4 - diff --git a/tests/exhaustive/basic/setOfSet02/expected/model_2_2.eprime b/tests/exhaustive/basic/setOfSet02/expected/model_2_2.eprime deleted file mode 100644 index f2b4b38350..0000000000 --- a/tests/exhaustive/basic/setOfSet02/expected/model_2_2.eprime +++ /dev/null @@ -1,19 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitR3_Explicit: matrix indexed by [int(1..2), int(1..3)] of int(1..4) -branching on [x_ExplicitR3_Explicit] -such that - or([and([or([1 = x_ExplicitR3_Explicit[q8, q10], 2 = x_ExplicitR3_Explicit[q8, q10], - 3 = x_ExplicitR3_Explicit[q8, q10]; - int(1..3)]) - | q10 : int(1..3)]) - /\ - and([or([x_ExplicitR3_Explicit[q8, q16] = 1 | q16 : int(1..3)]), - or([x_ExplicitR3_Explicit[q8, q18] = 2 | q18 : int(1..3)]), - or([x_ExplicitR3_Explicit[q8, q20] = 3 | q20 : int(1..3)]); - int(1..3)]) - | q8 : int(1..2)]), - flatten([[x_ExplicitR3_Explicit[1, q5]; int(1)] | q5 : int(1..3)]) x_ExplicitR6_ExplicitVarSizeWithDummy[q7, q9 + 1] = 3 - | q9 : int(1..2)]) - | q7 : int(1..2)]), - and([sum([toInt(x_ExplicitR6_ExplicitVarSizeWithDummy[q7, q10] != 3) | q10 : int(1..3)]) <= 3 | q7 : int(1..2)]), - and([or([and([x_ExplicitR2_Occurrence[q17, q18] -> - or([x_ExplicitR6_ExplicitVarSizeWithDummy[q15, q20] != 3 /\ - x_ExplicitR6_ExplicitVarSizeWithDummy[q15, q20] = q18 - | q20 : int(1..3)]) - | q18 : int(1..2)]) - /\ - and([x_ExplicitR6_ExplicitVarSizeWithDummy[q15, q22] != 3 -> - x_ExplicitR2_Occurrence[q17, x_ExplicitR6_ExplicitVarSizeWithDummy[q15, q22]] - | q22 : int(1..3)]) - | q17 : int(1..2)]) - | q15 : int(1..2)]), - and([or([and([x_ExplicitR6_ExplicitVarSizeWithDummy[q26, q28] != 3 -> - x_ExplicitR2_Occurrence[q24, x_ExplicitR6_ExplicitVarSizeWithDummy[q26, q28]] - | q28 : int(1..3)]) - /\ - and([x_ExplicitR2_Occurrence[q24, q29] -> - or([x_ExplicitR6_ExplicitVarSizeWithDummy[q26, q31] != 3 /\ - x_ExplicitR6_ExplicitVarSizeWithDummy[q26, q31] = q29 - | q31 : int(1..3)]) - | q29 : int(1..2)]) - | q26 : int(1..2)]) - | q24 : int(1..2)]) - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_1_1_3-solution000001.solution b/tests/exhaustive/basic/setOfSet04/expected/model_1_1_3-solution000001.solution deleted file mode 100644 index 3ec452354e..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_1_1_3-solution000001.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {1}} -$ Visualisation for x -$ -$ 1 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_1_1_3-solution000002.solution b/tests/exhaustive/basic/setOfSet04/expected/model_1_1_3-solution000002.solution deleted file mode 100644 index c8946f3d06..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_1_1_3-solution000002.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {2}} -$ Visualisation for x -$ -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_1_1_3-solution000003.solution b/tests/exhaustive/basic/setOfSet04/expected/model_1_1_3-solution000003.solution deleted file mode 100644 index a6c0b6a43e..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_1_1_3-solution000003.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {1, 2}} -$ Visualisation for x -$ -$ 1 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_1_1_3-solution000004.solution b/tests/exhaustive/basic/setOfSet04/expected/model_1_1_3-solution000004.solution deleted file mode 100644 index af16592c51..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_1_1_3-solution000004.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1}, {2}} -$ Visualisation for x -$ 1 -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_1_1_3-solution000005.solution b/tests/exhaustive/basic/setOfSet04/expected/model_1_1_3-solution000005.solution deleted file mode 100644 index 38937c9389..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_1_1_3-solution000005.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1}, {1, 2}} -$ Visualisation for x -$ 1 -$ 1 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_1_1_3-solution000006.solution b/tests/exhaustive/basic/setOfSet04/expected/model_1_1_3-solution000006.solution deleted file mode 100644 index 9bf2af0712..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_1_1_3-solution000006.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1, 2}, {2}} -$ Visualisation for x -$ 1 2 -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_1_1_3.eprime b/tests/exhaustive/basic/setOfSet04/expected/model_1_1_3.eprime deleted file mode 100644 index 78583ea34f..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_1_1_3.eprime +++ /dev/null @@ -1,52 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitR2_Occurrence: matrix indexed by [int(1..2), int(1..2)] of bool -find x_ExplicitR5_ExplicitVarSizeWithMarker_Marker: matrix indexed by [int(1..2)] of int(0..3) -find x_ExplicitR5_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..2), int(1..3)] of int(1..2) -branching on - [x_ExplicitR5_ExplicitVarSizeWithMarker_Marker, x_ExplicitR5_ExplicitVarSizeWithMarker_Values, - x_ExplicitR2_Occurrence] -such that - [-toInt(x_ExplicitR2_Occurrence[1, q4]) | q4 : int(1..2)] - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q7, q8] < - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q7, q8 + 1] - | q8 : int(1..2)]) - | q7 : int(1..2)]), - and([and([q9 > x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q7] -> - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q7, q9] = 1 - | q9 : int(1..3)]) - | q7 : int(1..2)]), - and([x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q7] <= 3 | q7 : int(1..2)]), - and([or([and([x_ExplicitR2_Occurrence[q16, q17] -> - or([q19 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q14] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q14, q19] = q17 - | q19 : int(1..3)]) - | q17 : int(1..2)]) - /\ - and([q21 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q14] -> - x_ExplicitR2_Occurrence[q16, x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q14, q21]] - | q21 : int(1..3)]) - | q16 : int(1..2)]) - | q14 : int(1..2)]), - and([or([and([q27 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q25] -> - x_ExplicitR2_Occurrence[q23, x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q25, q27]] - | q27 : int(1..3)]) - /\ - and([x_ExplicitR2_Occurrence[q23, q28] -> - or([q30 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q25] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q25, q30] = q28 - | q30 : int(1..3)]) - | q28 : int(1..2)]) - | q25 : int(1..2)]) - | q23 : int(1..2)]) - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_1_1_4-solution000001.solution b/tests/exhaustive/basic/setOfSet04/expected/model_1_1_4-solution000001.solution deleted file mode 100644 index 3ec452354e..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_1_1_4-solution000001.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {1}} -$ Visualisation for x -$ -$ 1 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_1_1_4-solution000002.solution b/tests/exhaustive/basic/setOfSet04/expected/model_1_1_4-solution000002.solution deleted file mode 100644 index c8946f3d06..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_1_1_4-solution000002.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {2}} -$ Visualisation for x -$ -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_1_1_4-solution000003.solution b/tests/exhaustive/basic/setOfSet04/expected/model_1_1_4-solution000003.solution deleted file mode 100644 index af16592c51..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_1_1_4-solution000003.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1}, {2}} -$ Visualisation for x -$ 1 -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_1_1_4-solution000004.solution b/tests/exhaustive/basic/setOfSet04/expected/model_1_1_4-solution000004.solution deleted file mode 100644 index a6c0b6a43e..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_1_1_4-solution000004.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {1, 2}} -$ Visualisation for x -$ -$ 1 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_1_1_4-solution000005.solution b/tests/exhaustive/basic/setOfSet04/expected/model_1_1_4-solution000005.solution deleted file mode 100644 index 38937c9389..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_1_1_4-solution000005.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1}, {1, 2}} -$ Visualisation for x -$ 1 -$ 1 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_1_1_4-solution000006.solution b/tests/exhaustive/basic/setOfSet04/expected/model_1_1_4-solution000006.solution deleted file mode 100644 index 9bf2af0712..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_1_1_4-solution000006.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1, 2}, {2}} -$ Visualisation for x -$ 1 2 -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_1_1_4.eprime b/tests/exhaustive/basic/setOfSet04/expected/model_1_1_4.eprime deleted file mode 100644 index 47eebe1823..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_1_1_4.eprime +++ /dev/null @@ -1,57 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitR2_Occurrence: matrix indexed by [int(1..2), int(1..2)] of bool -find x_ExplicitR4_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..2), int(1..3)] of bool -find x_ExplicitR4_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..2), int(1..3)] of int(1..2) -branching on - [x_ExplicitR4_ExplicitVarSizeWithFlags_Flags, x_ExplicitR4_ExplicitVarSizeWithFlags_Values, x_ExplicitR2_Occurrence] -such that - [-toInt(x_ExplicitR2_Occurrence[1, q4]) | q4 : int(1..2)] - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q7, q8] < - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q7, q8 + 1] - | q8 : int(1..2)]) - | q7 : int(1..2)]), - and([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q7, q9] = false -> - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q7, q9] = 1 - | q9 : int(1..3)]) - | q7 : int(1..2)]), - and([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q7, q10 + 1] -> - x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q7, q10] - | q10 : int(1..2)]) - | q7 : int(1..2)]), - and([sum([toInt(x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q7, q11]) | q11 : int(1..3)]) <= 3 | q7 : int(1..2)]), - and([or([and([x_ExplicitR2_Occurrence[q18, q19] -> - or([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q16, q21] /\ - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q16, q21] = q19 - | q21 : int(1..3)]) - | q19 : int(1..2)]) - /\ - and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q16, q23] -> - x_ExplicitR2_Occurrence[q18, x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q16, q23]] - | q23 : int(1..3)]) - | q18 : int(1..2)]) - | q16 : int(1..2)]), - and([or([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q27, q29] -> - x_ExplicitR2_Occurrence[q25, x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q27, q29]] - | q29 : int(1..3)]) - /\ - and([x_ExplicitR2_Occurrence[q25, q30] -> - or([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q27, q32] /\ - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q27, q32] = q30 - | q32 : int(1..3)]) - | q30 : int(1..2)]) - | q27 : int(1..2)]) - | q25 : int(1..2)]) - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_1_2_1-solution000001.solution b/tests/exhaustive/basic/setOfSet04/expected/model_1_2_1-solution000001.solution deleted file mode 100644 index 38937c9389..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_1_2_1-solution000001.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1}, {1, 2}} -$ Visualisation for x -$ 1 -$ 1 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_1_2_1-solution000002.solution b/tests/exhaustive/basic/setOfSet04/expected/model_1_2_1-solution000002.solution deleted file mode 100644 index 9bf2af0712..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_1_2_1-solution000002.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1, 2}, {2}} -$ Visualisation for x -$ 1 2 -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_1_2_1-solution000003.solution b/tests/exhaustive/basic/setOfSet04/expected/model_1_2_1-solution000003.solution deleted file mode 100644 index a6c0b6a43e..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_1_2_1-solution000003.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {1, 2}} -$ Visualisation for x -$ -$ 1 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_1_2_1-solution000004.solution b/tests/exhaustive/basic/setOfSet04/expected/model_1_2_1-solution000004.solution deleted file mode 100644 index af16592c51..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_1_2_1-solution000004.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1}, {2}} -$ Visualisation for x -$ 1 -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_1_2_1-solution000005.solution b/tests/exhaustive/basic/setOfSet04/expected/model_1_2_1-solution000005.solution deleted file mode 100644 index 3ec452354e..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_1_2_1-solution000005.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {1}} -$ Visualisation for x -$ -$ 1 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_1_2_1-solution000006.solution b/tests/exhaustive/basic/setOfSet04/expected/model_1_2_1-solution000006.solution deleted file mode 100644 index c8946f3d06..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_1_2_1-solution000006.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {2}} -$ Visualisation for x -$ -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_1_2_1.eprime b/tests/exhaustive/basic/setOfSet04/expected/model_1_2_1.eprime deleted file mode 100644 index ec811f5ef0..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_1_2_1.eprime +++ /dev/null @@ -1,42 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitR2_Occurrence: matrix indexed by [int(1..2), int(1..2)] of bool -find x_ExplicitR6_ExplicitVarSizeWithDummy: matrix indexed by [int(1..2), int(1..3)] of int(1..3) -branching on [x_ExplicitR6_ExplicitVarSizeWithDummy, x_ExplicitR2_Occurrence] -such that - [-toInt(x_ExplicitR2_Occurrence[1, q4]) | q4 : int(1..2)] x_ExplicitR6_ExplicitVarSizeWithDummy[q7, q9 + 1] = 3 - | q9 : int(1..2)]) - | q7 : int(1..2)]), - and([sum([toInt(x_ExplicitR6_ExplicitVarSizeWithDummy[q7, q10] != 3) | q10 : int(1..3)]) <= 3 | q7 : int(1..2)]), - and([or([and([x_ExplicitR2_Occurrence[q17, q18] -> - or([x_ExplicitR6_ExplicitVarSizeWithDummy[q15, q20] != 3 /\ - x_ExplicitR6_ExplicitVarSizeWithDummy[q15, q20] = q18 - | q20 : int(1..3)]) - | q18 : int(1..2)]) - /\ - and([x_ExplicitR6_ExplicitVarSizeWithDummy[q15, q22] != 3 -> - x_ExplicitR2_Occurrence[q17, x_ExplicitR6_ExplicitVarSizeWithDummy[q15, q22]] - | q22 : int(1..3)]) - | q17 : int(1..2)]) - | q15 : int(1..2)]), - and([or([and([x_ExplicitR6_ExplicitVarSizeWithDummy[q26, q28] != 3 -> - x_ExplicitR2_Occurrence[q24, x_ExplicitR6_ExplicitVarSizeWithDummy[q26, q28]] - | q28 : int(1..3)]) - /\ - and([x_ExplicitR2_Occurrence[q24, q29] -> - or([x_ExplicitR6_ExplicitVarSizeWithDummy[q26, q31] != 3 /\ - x_ExplicitR6_ExplicitVarSizeWithDummy[q26, q31] = q29 - | q31 : int(1..3)]) - | q29 : int(1..2)]) - | q26 : int(1..2)]) - | q24 : int(1..2)]) - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_1_2_2-solution000001.solution b/tests/exhaustive/basic/setOfSet04/expected/model_1_2_2-solution000001.solution deleted file mode 100644 index 38937c9389..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_1_2_2-solution000001.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1}, {1, 2}} -$ Visualisation for x -$ 1 -$ 1 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_1_2_2-solution000002.solution b/tests/exhaustive/basic/setOfSet04/expected/model_1_2_2-solution000002.solution deleted file mode 100644 index 9bf2af0712..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_1_2_2-solution000002.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1, 2}, {2}} -$ Visualisation for x -$ 1 2 -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_1_2_2-solution000003.solution b/tests/exhaustive/basic/setOfSet04/expected/model_1_2_2-solution000003.solution deleted file mode 100644 index a6c0b6a43e..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_1_2_2-solution000003.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {1, 2}} -$ Visualisation for x -$ -$ 1 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_1_2_2-solution000004.solution b/tests/exhaustive/basic/setOfSet04/expected/model_1_2_2-solution000004.solution deleted file mode 100644 index af16592c51..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_1_2_2-solution000004.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1}, {2}} -$ Visualisation for x -$ 1 -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_1_2_2-solution000005.solution b/tests/exhaustive/basic/setOfSet04/expected/model_1_2_2-solution000005.solution deleted file mode 100644 index 3ec452354e..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_1_2_2-solution000005.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {1}} -$ Visualisation for x -$ -$ 1 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_1_2_2-solution000006.solution b/tests/exhaustive/basic/setOfSet04/expected/model_1_2_2-solution000006.solution deleted file mode 100644 index c8946f3d06..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_1_2_2-solution000006.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {2}} -$ Visualisation for x -$ -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_1_2_2.eprime b/tests/exhaustive/basic/setOfSet04/expected/model_1_2_2.eprime deleted file mode 100644 index ec811f5ef0..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_1_2_2.eprime +++ /dev/null @@ -1,42 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitR2_Occurrence: matrix indexed by [int(1..2), int(1..2)] of bool -find x_ExplicitR6_ExplicitVarSizeWithDummy: matrix indexed by [int(1..2), int(1..3)] of int(1..3) -branching on [x_ExplicitR6_ExplicitVarSizeWithDummy, x_ExplicitR2_Occurrence] -such that - [-toInt(x_ExplicitR2_Occurrence[1, q4]) | q4 : int(1..2)] x_ExplicitR6_ExplicitVarSizeWithDummy[q7, q9 + 1] = 3 - | q9 : int(1..2)]) - | q7 : int(1..2)]), - and([sum([toInt(x_ExplicitR6_ExplicitVarSizeWithDummy[q7, q10] != 3) | q10 : int(1..3)]) <= 3 | q7 : int(1..2)]), - and([or([and([x_ExplicitR2_Occurrence[q17, q18] -> - or([x_ExplicitR6_ExplicitVarSizeWithDummy[q15, q20] != 3 /\ - x_ExplicitR6_ExplicitVarSizeWithDummy[q15, q20] = q18 - | q20 : int(1..3)]) - | q18 : int(1..2)]) - /\ - and([x_ExplicitR6_ExplicitVarSizeWithDummy[q15, q22] != 3 -> - x_ExplicitR2_Occurrence[q17, x_ExplicitR6_ExplicitVarSizeWithDummy[q15, q22]] - | q22 : int(1..3)]) - | q17 : int(1..2)]) - | q15 : int(1..2)]), - and([or([and([x_ExplicitR6_ExplicitVarSizeWithDummy[q26, q28] != 3 -> - x_ExplicitR2_Occurrence[q24, x_ExplicitR6_ExplicitVarSizeWithDummy[q26, q28]] - | q28 : int(1..3)]) - /\ - and([x_ExplicitR2_Occurrence[q24, q29] -> - or([x_ExplicitR6_ExplicitVarSizeWithDummy[q26, q31] != 3 /\ - x_ExplicitR6_ExplicitVarSizeWithDummy[q26, q31] = q29 - | q31 : int(1..3)]) - | q29 : int(1..2)]) - | q26 : int(1..2)]) - | q24 : int(1..2)]) - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_1_2_3-solution000001.solution b/tests/exhaustive/basic/setOfSet04/expected/model_1_2_3-solution000001.solution deleted file mode 100644 index 3ec452354e..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_1_2_3-solution000001.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {1}} -$ Visualisation for x -$ -$ 1 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_1_2_3-solution000002.solution b/tests/exhaustive/basic/setOfSet04/expected/model_1_2_3-solution000002.solution deleted file mode 100644 index c8946f3d06..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_1_2_3-solution000002.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {2}} -$ Visualisation for x -$ -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_1_2_3-solution000003.solution b/tests/exhaustive/basic/setOfSet04/expected/model_1_2_3-solution000003.solution deleted file mode 100644 index a6c0b6a43e..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_1_2_3-solution000003.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {1, 2}} -$ Visualisation for x -$ -$ 1 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_1_2_3-solution000004.solution b/tests/exhaustive/basic/setOfSet04/expected/model_1_2_3-solution000004.solution deleted file mode 100644 index af16592c51..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_1_2_3-solution000004.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1}, {2}} -$ Visualisation for x -$ 1 -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_1_2_3-solution000005.solution b/tests/exhaustive/basic/setOfSet04/expected/model_1_2_3-solution000005.solution deleted file mode 100644 index 38937c9389..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_1_2_3-solution000005.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1}, {1, 2}} -$ Visualisation for x -$ 1 -$ 1 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_1_2_3-solution000006.solution b/tests/exhaustive/basic/setOfSet04/expected/model_1_2_3-solution000006.solution deleted file mode 100644 index 9bf2af0712..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_1_2_3-solution000006.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1, 2}, {2}} -$ Visualisation for x -$ 1 2 -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_1_2_3.eprime b/tests/exhaustive/basic/setOfSet04/expected/model_1_2_3.eprime deleted file mode 100644 index 2cc616dcfb..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_1_2_3.eprime +++ /dev/null @@ -1,115 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitR2_Occurrence: matrix indexed by [int(1..2), int(1..2)] of bool -find x_ExplicitR6_ExplicitVarSizeWithDummy: matrix indexed by [int(1..2), int(1..3)] of int(1..3) -find x_ExplicitR5_ExplicitVarSizeWithMarker_Marker: matrix indexed by [int(1..2)] of int(0..3) -find x_ExplicitR5_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..2), int(1..3)] of int(1..2) -branching on - [x_ExplicitR5_ExplicitVarSizeWithMarker_Marker, x_ExplicitR5_ExplicitVarSizeWithMarker_Values, - x_ExplicitR2_Occurrence, x_ExplicitR6_ExplicitVarSizeWithDummy] -such that - [-toInt(x_ExplicitR2_Occurrence[1, q4]) | q4 : int(1..2)] x_ExplicitR6_ExplicitVarSizeWithDummy[q7, q9 + 1] = 3 - | q9 : int(1..2)]) - | q7 : int(1..2)]), - and([sum([toInt(x_ExplicitR6_ExplicitVarSizeWithDummy[q7, q10] != 3) | q10 : int(1..3)]) <= 3 | q7 : int(1..2)]), - and([or([and([x_ExplicitR2_Occurrence[q17, q18] -> - or([x_ExplicitR6_ExplicitVarSizeWithDummy[q15, q20] != 3 /\ - x_ExplicitR6_ExplicitVarSizeWithDummy[q15, q20] = q18 - | q20 : int(1..3)]) - | q18 : int(1..2)]) - /\ - and([x_ExplicitR6_ExplicitVarSizeWithDummy[q15, q22] != 3 -> - x_ExplicitR2_Occurrence[q17, x_ExplicitR6_ExplicitVarSizeWithDummy[q15, q22]] - | q22 : int(1..3)]) - | q17 : int(1..2)]) - | q15 : int(1..2)]), - and([or([and([x_ExplicitR6_ExplicitVarSizeWithDummy[q26, q28] != 3 -> - x_ExplicitR2_Occurrence[q24, x_ExplicitR6_ExplicitVarSizeWithDummy[q26, q28]] - | q28 : int(1..3)]) - /\ - and([x_ExplicitR2_Occurrence[q24, q29] -> - or([x_ExplicitR6_ExplicitVarSizeWithDummy[q26, q31] != 3 /\ - x_ExplicitR6_ExplicitVarSizeWithDummy[q26, q31] = q29 - | q31 : int(1..3)]) - | q29 : int(1..2)]) - | q26 : int(1..2)]) - | q24 : int(1..2)]), - flatten([[x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[1]; int(1)], - flatten([[x_ExplicitR5_ExplicitVarSizeWithMarker_Values[1, q37]; int(1)] | q37 : int(1..3)]); - int(1..2)]) - - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q33, q34] < - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q33, q34 + 1] - | q34 : int(1..2)]) - | q33 : int(1..2)]), - and([and([q35 > x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q33] -> - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q33, q35] = 1 - | q35 : int(1..3)]) - | q33 : int(1..2)]), - and([x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q33] <= 3 | q33 : int(1..2)]), - and([or([and([x_ExplicitR2_Occurrence[q42, q43] -> - or([q45 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q40] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q40, q45] = q43 - | q45 : int(1..3)]) - | q43 : int(1..2)]) - /\ - and([q47 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q40] -> - x_ExplicitR2_Occurrence[q42, x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q40, q47]] - | q47 : int(1..3)]) - | q42 : int(1..2)]) - | q40 : int(1..2)]), - and([or([and([q53 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q51] -> - x_ExplicitR2_Occurrence[q49, x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q51, q53]] - | q53 : int(1..3)]) - /\ - and([x_ExplicitR2_Occurrence[q49, q54] -> - or([q56 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q51] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q51, q56] = q54 - | q56 : int(1..3)]) - | q54 : int(1..2)]) - | q51 : int(1..2)]) - | q49 : int(1..2)]), - and([or([and([x_ExplicitR6_ExplicitVarSizeWithDummy[q60, q62] != 3 -> - or([q64 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q58] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q58, q64] = - x_ExplicitR6_ExplicitVarSizeWithDummy[q60, q62] - | q64 : int(1..3)]) - | q62 : int(1..3)]) - /\ - and([q66 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q58] -> - or([x_ExplicitR6_ExplicitVarSizeWithDummy[q60, q68] != 3 /\ - x_ExplicitR6_ExplicitVarSizeWithDummy[q60, q68] = - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q58, q66] - | q68 : int(1..3)]) - | q66 : int(1..3)]) - | q60 : int(1..2)]) - | q58 : int(1..2)]), - and([or([and([q74 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q72] -> - or([x_ExplicitR6_ExplicitVarSizeWithDummy[q70, q76] != 3 /\ - x_ExplicitR6_ExplicitVarSizeWithDummy[q70, q76] = - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q72, q74] - | q76 : int(1..3)]) - | q74 : int(1..3)]) - /\ - and([x_ExplicitR6_ExplicitVarSizeWithDummy[q70, q78] != 3 -> - or([q80 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q72] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q72, q80] = - x_ExplicitR6_ExplicitVarSizeWithDummy[q70, q78] - | q80 : int(1..3)]) - | q78 : int(1..3)]) - | q72 : int(1..2)]) - | q70 : int(1..2)]) - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_1_2_4-solution000001.solution b/tests/exhaustive/basic/setOfSet04/expected/model_1_2_4-solution000001.solution deleted file mode 100644 index 3ec452354e..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_1_2_4-solution000001.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {1}} -$ Visualisation for x -$ -$ 1 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_1_2_4-solution000002.solution b/tests/exhaustive/basic/setOfSet04/expected/model_1_2_4-solution000002.solution deleted file mode 100644 index c8946f3d06..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_1_2_4-solution000002.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {2}} -$ Visualisation for x -$ -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_1_2_4-solution000003.solution b/tests/exhaustive/basic/setOfSet04/expected/model_1_2_4-solution000003.solution deleted file mode 100644 index af16592c51..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_1_2_4-solution000003.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1}, {2}} -$ Visualisation for x -$ 1 -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_1_2_4-solution000004.solution b/tests/exhaustive/basic/setOfSet04/expected/model_1_2_4-solution000004.solution deleted file mode 100644 index a6c0b6a43e..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_1_2_4-solution000004.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {1, 2}} -$ Visualisation for x -$ -$ 1 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_1_2_4-solution000005.solution b/tests/exhaustive/basic/setOfSet04/expected/model_1_2_4-solution000005.solution deleted file mode 100644 index 38937c9389..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_1_2_4-solution000005.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1}, {1, 2}} -$ Visualisation for x -$ 1 -$ 1 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_1_2_4-solution000006.solution b/tests/exhaustive/basic/setOfSet04/expected/model_1_2_4-solution000006.solution deleted file mode 100644 index 9bf2af0712..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_1_2_4-solution000006.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1, 2}, {2}} -$ Visualisation for x -$ 1 2 -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_1_2_4.eprime b/tests/exhaustive/basic/setOfSet04/expected/model_1_2_4.eprime deleted file mode 100644 index 46fba1f2be..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_1_2_4.eprime +++ /dev/null @@ -1,121 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitR2_Occurrence: matrix indexed by [int(1..2), int(1..2)] of bool -find x_ExplicitR6_ExplicitVarSizeWithDummy: matrix indexed by [int(1..2), int(1..3)] of int(1..3) -find x_ExplicitR4_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..2), int(1..3)] of bool -find x_ExplicitR4_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..2), int(1..3)] of int(1..2) -branching on - [x_ExplicitR4_ExplicitVarSizeWithFlags_Flags, x_ExplicitR4_ExplicitVarSizeWithFlags_Values, x_ExplicitR2_Occurrence, - x_ExplicitR6_ExplicitVarSizeWithDummy] -such that - [-toInt(x_ExplicitR2_Occurrence[1, q4]) | q4 : int(1..2)] x_ExplicitR6_ExplicitVarSizeWithDummy[q7, q9 + 1] = 3 - | q9 : int(1..2)]) - | q7 : int(1..2)]), - and([sum([toInt(x_ExplicitR6_ExplicitVarSizeWithDummy[q7, q10] != 3) | q10 : int(1..3)]) <= 3 | q7 : int(1..2)]), - and([or([and([x_ExplicitR2_Occurrence[q17, q18] -> - or([x_ExplicitR6_ExplicitVarSizeWithDummy[q15, q20] != 3 /\ - x_ExplicitR6_ExplicitVarSizeWithDummy[q15, q20] = q18 - | q20 : int(1..3)]) - | q18 : int(1..2)]) - /\ - and([x_ExplicitR6_ExplicitVarSizeWithDummy[q15, q22] != 3 -> - x_ExplicitR2_Occurrence[q17, x_ExplicitR6_ExplicitVarSizeWithDummy[q15, q22]] - | q22 : int(1..3)]) - | q17 : int(1..2)]) - | q15 : int(1..2)]), - and([or([and([x_ExplicitR6_ExplicitVarSizeWithDummy[q26, q28] != 3 -> - x_ExplicitR2_Occurrence[q24, x_ExplicitR6_ExplicitVarSizeWithDummy[q26, q28]] - | q28 : int(1..3)]) - /\ - and([x_ExplicitR2_Occurrence[q24, q29] -> - or([x_ExplicitR6_ExplicitVarSizeWithDummy[q26, q31] != 3 /\ - x_ExplicitR6_ExplicitVarSizeWithDummy[q26, q31] = q29 - | q31 : int(1..3)]) - | q29 : int(1..2)]) - | q26 : int(1..2)]) - | q24 : int(1..2)]), - flatten([flatten([[-toInt(x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[1, q39]); int(1)], - [x_ExplicitR4_ExplicitVarSizeWithFlags_Values[1, q39]; int(1)]; - int(1..2)]) - | q39 : int(1..3)]) - - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q33, q34] < - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q33, q34 + 1] - | q34 : int(1..2)]) - | q33 : int(1..2)]), - and([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q33, q35] = false -> - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q33, q35] = 1 - | q35 : int(1..3)]) - | q33 : int(1..2)]), - and([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q33, q36 + 1] -> - x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q33, q36] - | q36 : int(1..2)]) - | q33 : int(1..2)]), - and([sum([toInt(x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q33, q37]) | q37 : int(1..3)]) <= 3 | q33 : int(1..2)]), - and([or([and([x_ExplicitR2_Occurrence[q44, q45] -> - or([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q42, q47] /\ - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q42, q47] = q45 - | q47 : int(1..3)]) - | q45 : int(1..2)]) - /\ - and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q42, q49] -> - x_ExplicitR2_Occurrence[q44, x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q42, q49]] - | q49 : int(1..3)]) - | q44 : int(1..2)]) - | q42 : int(1..2)]), - and([or([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q53, q55] -> - x_ExplicitR2_Occurrence[q51, x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q53, q55]] - | q55 : int(1..3)]) - /\ - and([x_ExplicitR2_Occurrence[q51, q56] -> - or([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q53, q58] /\ - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q53, q58] = q56 - | q58 : int(1..3)]) - | q56 : int(1..2)]) - | q53 : int(1..2)]) - | q51 : int(1..2)]), - and([or([and([x_ExplicitR6_ExplicitVarSizeWithDummy[q62, q64] != 3 -> - or([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q60, q66] /\ - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q60, q66] = - x_ExplicitR6_ExplicitVarSizeWithDummy[q62, q64] - | q66 : int(1..3)]) - | q64 : int(1..3)]) - /\ - and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q60, q68] -> - or([x_ExplicitR6_ExplicitVarSizeWithDummy[q62, q70] != 3 /\ - x_ExplicitR6_ExplicitVarSizeWithDummy[q62, q70] = - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q60, q68] - | q70 : int(1..3)]) - | q68 : int(1..3)]) - | q62 : int(1..2)]) - | q60 : int(1..2)]), - and([or([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q74, q76] -> - or([x_ExplicitR6_ExplicitVarSizeWithDummy[q72, q78] != 3 /\ - x_ExplicitR6_ExplicitVarSizeWithDummy[q72, q78] = - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q74, q76] - | q78 : int(1..3)]) - | q76 : int(1..3)]) - /\ - and([x_ExplicitR6_ExplicitVarSizeWithDummy[q72, q80] != 3 -> - or([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q74, q82] /\ - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q74, q82] = - x_ExplicitR6_ExplicitVarSizeWithDummy[q72, q80] - | q82 : int(1..3)]) - | q80 : int(1..3)]) - | q74 : int(1..2)]) - | q72 : int(1..2)]) - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_1_3_1-solution000001.solution b/tests/exhaustive/basic/setOfSet04/expected/model_1_3_1-solution000001.solution deleted file mode 100644 index 3ec452354e..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_1_3_1-solution000001.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {1}} -$ Visualisation for x -$ -$ 1 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_1_3_1-solution000002.solution b/tests/exhaustive/basic/setOfSet04/expected/model_1_3_1-solution000002.solution deleted file mode 100644 index c8946f3d06..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_1_3_1-solution000002.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {2}} -$ Visualisation for x -$ -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_1_3_1-solution000003.solution b/tests/exhaustive/basic/setOfSet04/expected/model_1_3_1-solution000003.solution deleted file mode 100644 index a6c0b6a43e..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_1_3_1-solution000003.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {1, 2}} -$ Visualisation for x -$ -$ 1 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_1_3_1-solution000004.solution b/tests/exhaustive/basic/setOfSet04/expected/model_1_3_1-solution000004.solution deleted file mode 100644 index af16592c51..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_1_3_1-solution000004.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1}, {2}} -$ Visualisation for x -$ 1 -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_1_3_1-solution000005.solution b/tests/exhaustive/basic/setOfSet04/expected/model_1_3_1-solution000005.solution deleted file mode 100644 index 38937c9389..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_1_3_1-solution000005.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1}, {1, 2}} -$ Visualisation for x -$ 1 -$ 1 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_1_3_1-solution000006.solution b/tests/exhaustive/basic/setOfSet04/expected/model_1_3_1-solution000006.solution deleted file mode 100644 index 9bf2af0712..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_1_3_1-solution000006.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1, 2}, {2}} -$ Visualisation for x -$ 1 2 -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_1_3_1.eprime b/tests/exhaustive/basic/setOfSet04/expected/model_1_3_1.eprime deleted file mode 100644 index 78583ea34f..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_1_3_1.eprime +++ /dev/null @@ -1,52 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitR2_Occurrence: matrix indexed by [int(1..2), int(1..2)] of bool -find x_ExplicitR5_ExplicitVarSizeWithMarker_Marker: matrix indexed by [int(1..2)] of int(0..3) -find x_ExplicitR5_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..2), int(1..3)] of int(1..2) -branching on - [x_ExplicitR5_ExplicitVarSizeWithMarker_Marker, x_ExplicitR5_ExplicitVarSizeWithMarker_Values, - x_ExplicitR2_Occurrence] -such that - [-toInt(x_ExplicitR2_Occurrence[1, q4]) | q4 : int(1..2)] - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q7, q8] < - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q7, q8 + 1] - | q8 : int(1..2)]) - | q7 : int(1..2)]), - and([and([q9 > x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q7] -> - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q7, q9] = 1 - | q9 : int(1..3)]) - | q7 : int(1..2)]), - and([x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q7] <= 3 | q7 : int(1..2)]), - and([or([and([x_ExplicitR2_Occurrence[q16, q17] -> - or([q19 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q14] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q14, q19] = q17 - | q19 : int(1..3)]) - | q17 : int(1..2)]) - /\ - and([q21 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q14] -> - x_ExplicitR2_Occurrence[q16, x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q14, q21]] - | q21 : int(1..3)]) - | q16 : int(1..2)]) - | q14 : int(1..2)]), - and([or([and([q27 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q25] -> - x_ExplicitR2_Occurrence[q23, x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q25, q27]] - | q27 : int(1..3)]) - /\ - and([x_ExplicitR2_Occurrence[q23, q28] -> - or([q30 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q25] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q25, q30] = q28 - | q30 : int(1..3)]) - | q28 : int(1..2)]) - | q25 : int(1..2)]) - | q23 : int(1..2)]) - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_1_3_2-solution000001.solution b/tests/exhaustive/basic/setOfSet04/expected/model_1_3_2-solution000001.solution deleted file mode 100644 index 38937c9389..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_1_3_2-solution000001.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1}, {1, 2}} -$ Visualisation for x -$ 1 -$ 1 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_1_3_2-solution000002.solution b/tests/exhaustive/basic/setOfSet04/expected/model_1_3_2-solution000002.solution deleted file mode 100644 index 9bf2af0712..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_1_3_2-solution000002.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1, 2}, {2}} -$ Visualisation for x -$ 1 2 -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_1_3_2-solution000003.solution b/tests/exhaustive/basic/setOfSet04/expected/model_1_3_2-solution000003.solution deleted file mode 100644 index a6c0b6a43e..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_1_3_2-solution000003.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {1, 2}} -$ Visualisation for x -$ -$ 1 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_1_3_2-solution000004.solution b/tests/exhaustive/basic/setOfSet04/expected/model_1_3_2-solution000004.solution deleted file mode 100644 index af16592c51..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_1_3_2-solution000004.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1}, {2}} -$ Visualisation for x -$ 1 -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_1_3_2-solution000005.solution b/tests/exhaustive/basic/setOfSet04/expected/model_1_3_2-solution000005.solution deleted file mode 100644 index 3ec452354e..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_1_3_2-solution000005.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {1}} -$ Visualisation for x -$ -$ 1 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_1_3_2-solution000006.solution b/tests/exhaustive/basic/setOfSet04/expected/model_1_3_2-solution000006.solution deleted file mode 100644 index c8946f3d06..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_1_3_2-solution000006.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {2}} -$ Visualisation for x -$ -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_1_3_2.eprime b/tests/exhaustive/basic/setOfSet04/expected/model_1_3_2.eprime deleted file mode 100644 index 6510867813..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_1_3_2.eprime +++ /dev/null @@ -1,116 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitR2_Occurrence: matrix indexed by [int(1..2), int(1..2)] of bool -find x_ExplicitR5_ExplicitVarSizeWithMarker_Marker: matrix indexed by [int(1..2)] of int(0..3) -find x_ExplicitR5_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..2), int(1..3)] of int(1..2) -find x_ExplicitR6_ExplicitVarSizeWithDummy: matrix indexed by [int(1..2), int(1..3)] of int(1..3) -branching on - [x_ExplicitR6_ExplicitVarSizeWithDummy, x_ExplicitR2_Occurrence, x_ExplicitR5_ExplicitVarSizeWithMarker_Marker, - x_ExplicitR5_ExplicitVarSizeWithMarker_Values] -such that - [-toInt(x_ExplicitR2_Occurrence[1, q4]) | q4 : int(1..2)] - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q7, q8] < - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q7, q8 + 1] - | q8 : int(1..2)]) - | q7 : int(1..2)]), - and([and([q9 > x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q7] -> - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q7, q9] = 1 - | q9 : int(1..3)]) - | q7 : int(1..2)]), - and([x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q7] <= 3 | q7 : int(1..2)]), - and([or([and([x_ExplicitR2_Occurrence[q16, q17] -> - or([q19 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q14] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q14, q19] = q17 - | q19 : int(1..3)]) - | q17 : int(1..2)]) - /\ - and([q21 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q14] -> - x_ExplicitR2_Occurrence[q16, x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q14, q21]] - | q21 : int(1..3)]) - | q16 : int(1..2)]) - | q14 : int(1..2)]), - and([or([and([q27 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q25] -> - x_ExplicitR2_Occurrence[q23, x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q25, q27]] - | q27 : int(1..3)]) - /\ - and([x_ExplicitR2_Occurrence[q23, q28] -> - or([q30 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q25] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q25, q30] = q28 - | q30 : int(1..3)]) - | q28 : int(1..2)]) - | q25 : int(1..2)]) - | q23 : int(1..2)]), - [x_ExplicitR6_ExplicitVarSizeWithDummy[1, q37] | q37 : int(1..3)] - x_ExplicitR6_ExplicitVarSizeWithDummy[q32, q34 + 1] = 3 - | q34 : int(1..2)]) - | q32 : int(1..2)]), - and([sum([toInt(x_ExplicitR6_ExplicitVarSizeWithDummy[q32, q35] != 3) | q35 : int(1..3)]) <= 3 | q32 : int(1..2)]), - and([or([and([x_ExplicitR2_Occurrence[q42, q43] -> - or([x_ExplicitR6_ExplicitVarSizeWithDummy[q40, q45] != 3 /\ - x_ExplicitR6_ExplicitVarSizeWithDummy[q40, q45] = q43 - | q45 : int(1..3)]) - | q43 : int(1..2)]) - /\ - and([x_ExplicitR6_ExplicitVarSizeWithDummy[q40, q47] != 3 -> - x_ExplicitR2_Occurrence[q42, x_ExplicitR6_ExplicitVarSizeWithDummy[q40, q47]] - | q47 : int(1..3)]) - | q42 : int(1..2)]) - | q40 : int(1..2)]), - and([or([and([x_ExplicitR6_ExplicitVarSizeWithDummy[q51, q53] != 3 -> - x_ExplicitR2_Occurrence[q49, x_ExplicitR6_ExplicitVarSizeWithDummy[q51, q53]] - | q53 : int(1..3)]) - /\ - and([x_ExplicitR2_Occurrence[q49, q54] -> - or([x_ExplicitR6_ExplicitVarSizeWithDummy[q51, q56] != 3 /\ - x_ExplicitR6_ExplicitVarSizeWithDummy[q51, q56] = q54 - | q56 : int(1..3)]) - | q54 : int(1..2)]) - | q51 : int(1..2)]) - | q49 : int(1..2)]), - and([or([and([q62 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q60] -> - or([x_ExplicitR6_ExplicitVarSizeWithDummy[q58, q64] != 3 /\ - x_ExplicitR6_ExplicitVarSizeWithDummy[q58, q64] = - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q60, q62] - | q64 : int(1..3)]) - | q62 : int(1..3)]) - /\ - and([x_ExplicitR6_ExplicitVarSizeWithDummy[q58, q66] != 3 -> - or([q68 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q60] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q60, q68] = - x_ExplicitR6_ExplicitVarSizeWithDummy[q58, q66] - | q68 : int(1..3)]) - | q66 : int(1..3)]) - | q60 : int(1..2)]) - | q58 : int(1..2)]), - and([or([and([x_ExplicitR6_ExplicitVarSizeWithDummy[q72, q74] != 3 -> - or([q76 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q70] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q70, q76] = - x_ExplicitR6_ExplicitVarSizeWithDummy[q72, q74] - | q76 : int(1..3)]) - | q74 : int(1..3)]) - /\ - and([q78 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q70] -> - or([x_ExplicitR6_ExplicitVarSizeWithDummy[q72, q80] != 3 /\ - x_ExplicitR6_ExplicitVarSizeWithDummy[q72, q80] = - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q70, q78] - | q80 : int(1..3)]) - | q78 : int(1..3)]) - | q72 : int(1..2)]) - | q70 : int(1..2)]) - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_1_3_3-solution000001.solution b/tests/exhaustive/basic/setOfSet04/expected/model_1_3_3-solution000001.solution deleted file mode 100644 index 3ec452354e..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_1_3_3-solution000001.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {1}} -$ Visualisation for x -$ -$ 1 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_1_3_3-solution000002.solution b/tests/exhaustive/basic/setOfSet04/expected/model_1_3_3-solution000002.solution deleted file mode 100644 index c8946f3d06..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_1_3_3-solution000002.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {2}} -$ Visualisation for x -$ -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_1_3_3-solution000003.solution b/tests/exhaustive/basic/setOfSet04/expected/model_1_3_3-solution000003.solution deleted file mode 100644 index a6c0b6a43e..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_1_3_3-solution000003.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {1, 2}} -$ Visualisation for x -$ -$ 1 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_1_3_3-solution000004.solution b/tests/exhaustive/basic/setOfSet04/expected/model_1_3_3-solution000004.solution deleted file mode 100644 index af16592c51..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_1_3_3-solution000004.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1}, {2}} -$ Visualisation for x -$ 1 -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_1_3_3-solution000005.solution b/tests/exhaustive/basic/setOfSet04/expected/model_1_3_3-solution000005.solution deleted file mode 100644 index 38937c9389..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_1_3_3-solution000005.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1}, {1, 2}} -$ Visualisation for x -$ 1 -$ 1 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_1_3_3-solution000006.solution b/tests/exhaustive/basic/setOfSet04/expected/model_1_3_3-solution000006.solution deleted file mode 100644 index 9bf2af0712..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_1_3_3-solution000006.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1, 2}, {2}} -$ Visualisation for x -$ 1 2 -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_1_3_3.eprime b/tests/exhaustive/basic/setOfSet04/expected/model_1_3_3.eprime deleted file mode 100644 index 78583ea34f..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_1_3_3.eprime +++ /dev/null @@ -1,52 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitR2_Occurrence: matrix indexed by [int(1..2), int(1..2)] of bool -find x_ExplicitR5_ExplicitVarSizeWithMarker_Marker: matrix indexed by [int(1..2)] of int(0..3) -find x_ExplicitR5_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..2), int(1..3)] of int(1..2) -branching on - [x_ExplicitR5_ExplicitVarSizeWithMarker_Marker, x_ExplicitR5_ExplicitVarSizeWithMarker_Values, - x_ExplicitR2_Occurrence] -such that - [-toInt(x_ExplicitR2_Occurrence[1, q4]) | q4 : int(1..2)] - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q7, q8] < - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q7, q8 + 1] - | q8 : int(1..2)]) - | q7 : int(1..2)]), - and([and([q9 > x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q7] -> - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q7, q9] = 1 - | q9 : int(1..3)]) - | q7 : int(1..2)]), - and([x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q7] <= 3 | q7 : int(1..2)]), - and([or([and([x_ExplicitR2_Occurrence[q16, q17] -> - or([q19 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q14] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q14, q19] = q17 - | q19 : int(1..3)]) - | q17 : int(1..2)]) - /\ - and([q21 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q14] -> - x_ExplicitR2_Occurrence[q16, x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q14, q21]] - | q21 : int(1..3)]) - | q16 : int(1..2)]) - | q14 : int(1..2)]), - and([or([and([q27 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q25] -> - x_ExplicitR2_Occurrence[q23, x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q25, q27]] - | q27 : int(1..3)]) - /\ - and([x_ExplicitR2_Occurrence[q23, q28] -> - or([q30 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q25] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q25, q30] = q28 - | q30 : int(1..3)]) - | q28 : int(1..2)]) - | q25 : int(1..2)]) - | q23 : int(1..2)]) - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_1_3_4-solution000001.solution b/tests/exhaustive/basic/setOfSet04/expected/model_1_3_4-solution000001.solution deleted file mode 100644 index 3ec452354e..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_1_3_4-solution000001.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {1}} -$ Visualisation for x -$ -$ 1 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_1_3_4-solution000002.solution b/tests/exhaustive/basic/setOfSet04/expected/model_1_3_4-solution000002.solution deleted file mode 100644 index c8946f3d06..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_1_3_4-solution000002.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {2}} -$ Visualisation for x -$ -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_1_3_4-solution000003.solution b/tests/exhaustive/basic/setOfSet04/expected/model_1_3_4-solution000003.solution deleted file mode 100644 index af16592c51..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_1_3_4-solution000003.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1}, {2}} -$ Visualisation for x -$ 1 -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_1_3_4-solution000004.solution b/tests/exhaustive/basic/setOfSet04/expected/model_1_3_4-solution000004.solution deleted file mode 100644 index a6c0b6a43e..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_1_3_4-solution000004.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {1, 2}} -$ Visualisation for x -$ -$ 1 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_1_3_4-solution000005.solution b/tests/exhaustive/basic/setOfSet04/expected/model_1_3_4-solution000005.solution deleted file mode 100644 index 38937c9389..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_1_3_4-solution000005.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1}, {1, 2}} -$ Visualisation for x -$ 1 -$ 1 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_1_3_4-solution000006.solution b/tests/exhaustive/basic/setOfSet04/expected/model_1_3_4-solution000006.solution deleted file mode 100644 index 9bf2af0712..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_1_3_4-solution000006.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1, 2}, {2}} -$ Visualisation for x -$ 1 2 -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_1_3_4.eprime b/tests/exhaustive/basic/setOfSet04/expected/model_1_3_4.eprime deleted file mode 100644 index 68d90232e9..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_1_3_4.eprime +++ /dev/null @@ -1,129 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitR2_Occurrence: matrix indexed by [int(1..2), int(1..2)] of bool -find x_ExplicitR5_ExplicitVarSizeWithMarker_Marker: matrix indexed by [int(1..2)] of int(0..3) -find x_ExplicitR5_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..2), int(1..3)] of int(1..2) -find x_ExplicitR4_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..2), int(1..3)] of bool -find x_ExplicitR4_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..2), int(1..3)] of int(1..2) -branching on - [x_ExplicitR4_ExplicitVarSizeWithFlags_Flags, x_ExplicitR4_ExplicitVarSizeWithFlags_Values, x_ExplicitR2_Occurrence, - x_ExplicitR5_ExplicitVarSizeWithMarker_Marker, x_ExplicitR5_ExplicitVarSizeWithMarker_Values] -such that - [-toInt(x_ExplicitR2_Occurrence[1, q4]) | q4 : int(1..2)] - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q7, q8] < - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q7, q8 + 1] - | q8 : int(1..2)]) - | q7 : int(1..2)]), - and([and([q9 > x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q7] -> - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q7, q9] = 1 - | q9 : int(1..3)]) - | q7 : int(1..2)]), - and([x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q7] <= 3 | q7 : int(1..2)]), - and([or([and([x_ExplicitR2_Occurrence[q16, q17] -> - or([q19 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q14] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q14, q19] = q17 - | q19 : int(1..3)]) - | q17 : int(1..2)]) - /\ - and([q21 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q14] -> - x_ExplicitR2_Occurrence[q16, x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q14, q21]] - | q21 : int(1..3)]) - | q16 : int(1..2)]) - | q14 : int(1..2)]), - and([or([and([q27 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q25] -> - x_ExplicitR2_Occurrence[q23, x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q25, q27]] - | q27 : int(1..3)]) - /\ - and([x_ExplicitR2_Occurrence[q23, q28] -> - or([q30 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q25] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q25, q30] = q28 - | q30 : int(1..3)]) - | q28 : int(1..2)]) - | q25 : int(1..2)]) - | q23 : int(1..2)]), - flatten([flatten([[-toInt(x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[1, q38]); int(1)], - [x_ExplicitR4_ExplicitVarSizeWithFlags_Values[1, q38]; int(1)]; - int(1..2)]) - | q38 : int(1..3)]) - - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q32, q33] < - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q32, q33 + 1] - | q33 : int(1..2)]) - | q32 : int(1..2)]), - and([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q32, q34] = false -> - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q32, q34] = 1 - | q34 : int(1..3)]) - | q32 : int(1..2)]), - and([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q32, q35 + 1] -> - x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q32, q35] - | q35 : int(1..2)]) - | q32 : int(1..2)]), - and([sum([toInt(x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q32, q36]) | q36 : int(1..3)]) <= 3 | q32 : int(1..2)]), - and([or([and([x_ExplicitR2_Occurrence[q43, q44] -> - or([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q41, q46] /\ - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q41, q46] = q44 - | q46 : int(1..3)]) - | q44 : int(1..2)]) - /\ - and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q41, q48] -> - x_ExplicitR2_Occurrence[q43, x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q41, q48]] - | q48 : int(1..3)]) - | q43 : int(1..2)]) - | q41 : int(1..2)]), - and([or([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q52, q54] -> - x_ExplicitR2_Occurrence[q50, x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q52, q54]] - | q54 : int(1..3)]) - /\ - and([x_ExplicitR2_Occurrence[q50, q55] -> - or([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q52, q57] /\ - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q52, q57] = q55 - | q57 : int(1..3)]) - | q55 : int(1..2)]) - | q52 : int(1..2)]) - | q50 : int(1..2)]), - and([or([and([q63 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q61] -> - or([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q59, q65] /\ - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q59, q65] = - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q61, q63] - | q65 : int(1..3)]) - | q63 : int(1..3)]) - /\ - and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q59, q67] -> - or([q69 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q61] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q61, q69] = - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q59, q67] - | q69 : int(1..3)]) - | q67 : int(1..3)]) - | q61 : int(1..2)]) - | q59 : int(1..2)]), - and([or([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q73, q75] -> - or([q77 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q71] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q71, q77] = - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q73, q75] - | q77 : int(1..3)]) - | q75 : int(1..3)]) - /\ - and([q79 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q71] -> - or([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q73, q81] /\ - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q73, q81] = - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q71, q79] - | q81 : int(1..3)]) - | q79 : int(1..3)]) - | q73 : int(1..2)]) - | q71 : int(1..2)]) - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_1_4_1-solution000001.solution b/tests/exhaustive/basic/setOfSet04/expected/model_1_4_1-solution000001.solution deleted file mode 100644 index 3ec452354e..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_1_4_1-solution000001.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {1}} -$ Visualisation for x -$ -$ 1 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_1_4_1-solution000002.solution b/tests/exhaustive/basic/setOfSet04/expected/model_1_4_1-solution000002.solution deleted file mode 100644 index c8946f3d06..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_1_4_1-solution000002.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {2}} -$ Visualisation for x -$ -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_1_4_1-solution000003.solution b/tests/exhaustive/basic/setOfSet04/expected/model_1_4_1-solution000003.solution deleted file mode 100644 index af16592c51..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_1_4_1-solution000003.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1}, {2}} -$ Visualisation for x -$ 1 -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_1_4_1-solution000004.solution b/tests/exhaustive/basic/setOfSet04/expected/model_1_4_1-solution000004.solution deleted file mode 100644 index a6c0b6a43e..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_1_4_1-solution000004.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {1, 2}} -$ Visualisation for x -$ -$ 1 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_1_4_1-solution000005.solution b/tests/exhaustive/basic/setOfSet04/expected/model_1_4_1-solution000005.solution deleted file mode 100644 index 38937c9389..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_1_4_1-solution000005.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1}, {1, 2}} -$ Visualisation for x -$ 1 -$ 1 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_1_4_1-solution000006.solution b/tests/exhaustive/basic/setOfSet04/expected/model_1_4_1-solution000006.solution deleted file mode 100644 index 9bf2af0712..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_1_4_1-solution000006.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1, 2}, {2}} -$ Visualisation for x -$ 1 2 -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_1_4_1.eprime b/tests/exhaustive/basic/setOfSet04/expected/model_1_4_1.eprime deleted file mode 100644 index 47eebe1823..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_1_4_1.eprime +++ /dev/null @@ -1,57 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitR2_Occurrence: matrix indexed by [int(1..2), int(1..2)] of bool -find x_ExplicitR4_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..2), int(1..3)] of bool -find x_ExplicitR4_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..2), int(1..3)] of int(1..2) -branching on - [x_ExplicitR4_ExplicitVarSizeWithFlags_Flags, x_ExplicitR4_ExplicitVarSizeWithFlags_Values, x_ExplicitR2_Occurrence] -such that - [-toInt(x_ExplicitR2_Occurrence[1, q4]) | q4 : int(1..2)] - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q7, q8] < - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q7, q8 + 1] - | q8 : int(1..2)]) - | q7 : int(1..2)]), - and([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q7, q9] = false -> - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q7, q9] = 1 - | q9 : int(1..3)]) - | q7 : int(1..2)]), - and([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q7, q10 + 1] -> - x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q7, q10] - | q10 : int(1..2)]) - | q7 : int(1..2)]), - and([sum([toInt(x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q7, q11]) | q11 : int(1..3)]) <= 3 | q7 : int(1..2)]), - and([or([and([x_ExplicitR2_Occurrence[q18, q19] -> - or([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q16, q21] /\ - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q16, q21] = q19 - | q21 : int(1..3)]) - | q19 : int(1..2)]) - /\ - and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q16, q23] -> - x_ExplicitR2_Occurrence[q18, x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q16, q23]] - | q23 : int(1..3)]) - | q18 : int(1..2)]) - | q16 : int(1..2)]), - and([or([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q27, q29] -> - x_ExplicitR2_Occurrence[q25, x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q27, q29]] - | q29 : int(1..3)]) - /\ - and([x_ExplicitR2_Occurrence[q25, q30] -> - or([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q27, q32] /\ - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q27, q32] = q30 - | q32 : int(1..3)]) - | q30 : int(1..2)]) - | q27 : int(1..2)]) - | q25 : int(1..2)]) - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_1_4_2-solution000001.solution b/tests/exhaustive/basic/setOfSet04/expected/model_1_4_2-solution000001.solution deleted file mode 100644 index 38937c9389..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_1_4_2-solution000001.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1}, {1, 2}} -$ Visualisation for x -$ 1 -$ 1 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_1_4_2-solution000002.solution b/tests/exhaustive/basic/setOfSet04/expected/model_1_4_2-solution000002.solution deleted file mode 100644 index 9bf2af0712..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_1_4_2-solution000002.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1, 2}, {2}} -$ Visualisation for x -$ 1 2 -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_1_4_2-solution000003.solution b/tests/exhaustive/basic/setOfSet04/expected/model_1_4_2-solution000003.solution deleted file mode 100644 index a6c0b6a43e..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_1_4_2-solution000003.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {1, 2}} -$ Visualisation for x -$ -$ 1 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_1_4_2-solution000004.solution b/tests/exhaustive/basic/setOfSet04/expected/model_1_4_2-solution000004.solution deleted file mode 100644 index af16592c51..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_1_4_2-solution000004.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1}, {2}} -$ Visualisation for x -$ 1 -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_1_4_2-solution000005.solution b/tests/exhaustive/basic/setOfSet04/expected/model_1_4_2-solution000005.solution deleted file mode 100644 index 3ec452354e..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_1_4_2-solution000005.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {1}} -$ Visualisation for x -$ -$ 1 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_1_4_2-solution000006.solution b/tests/exhaustive/basic/setOfSet04/expected/model_1_4_2-solution000006.solution deleted file mode 100644 index c8946f3d06..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_1_4_2-solution000006.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {2}} -$ Visualisation for x -$ -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_1_4_2.eprime b/tests/exhaustive/basic/setOfSet04/expected/model_1_4_2.eprime deleted file mode 100644 index cd957e819c..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_1_4_2.eprime +++ /dev/null @@ -1,122 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitR2_Occurrence: matrix indexed by [int(1..2), int(1..2)] of bool -find x_ExplicitR4_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..2), int(1..3)] of bool -find x_ExplicitR4_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..2), int(1..3)] of int(1..2) -find x_ExplicitR6_ExplicitVarSizeWithDummy: matrix indexed by [int(1..2), int(1..3)] of int(1..3) -branching on - [x_ExplicitR6_ExplicitVarSizeWithDummy, x_ExplicitR2_Occurrence, x_ExplicitR4_ExplicitVarSizeWithFlags_Flags, - x_ExplicitR4_ExplicitVarSizeWithFlags_Values] -such that - [-toInt(x_ExplicitR2_Occurrence[1, q4]) | q4 : int(1..2)] - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q7, q8] < - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q7, q8 + 1] - | q8 : int(1..2)]) - | q7 : int(1..2)]), - and([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q7, q9] = false -> - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q7, q9] = 1 - | q9 : int(1..3)]) - | q7 : int(1..2)]), - and([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q7, q10 + 1] -> - x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q7, q10] - | q10 : int(1..2)]) - | q7 : int(1..2)]), - and([sum([toInt(x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q7, q11]) | q11 : int(1..3)]) <= 3 | q7 : int(1..2)]), - and([or([and([x_ExplicitR2_Occurrence[q18, q19] -> - or([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q16, q21] /\ - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q16, q21] = q19 - | q21 : int(1..3)]) - | q19 : int(1..2)]) - /\ - and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q16, q23] -> - x_ExplicitR2_Occurrence[q18, x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q16, q23]] - | q23 : int(1..3)]) - | q18 : int(1..2)]) - | q16 : int(1..2)]), - and([or([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q27, q29] -> - x_ExplicitR2_Occurrence[q25, x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q27, q29]] - | q29 : int(1..3)]) - /\ - and([x_ExplicitR2_Occurrence[q25, q30] -> - or([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q27, q32] /\ - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q27, q32] = q30 - | q32 : int(1..3)]) - | q30 : int(1..2)]) - | q27 : int(1..2)]) - | q25 : int(1..2)]), - [x_ExplicitR6_ExplicitVarSizeWithDummy[1, q39] | q39 : int(1..3)] - x_ExplicitR6_ExplicitVarSizeWithDummy[q34, q36 + 1] = 3 - | q36 : int(1..2)]) - | q34 : int(1..2)]), - and([sum([toInt(x_ExplicitR6_ExplicitVarSizeWithDummy[q34, q37] != 3) | q37 : int(1..3)]) <= 3 | q34 : int(1..2)]), - and([or([and([x_ExplicitR2_Occurrence[q44, q45] -> - or([x_ExplicitR6_ExplicitVarSizeWithDummy[q42, q47] != 3 /\ - x_ExplicitR6_ExplicitVarSizeWithDummy[q42, q47] = q45 - | q47 : int(1..3)]) - | q45 : int(1..2)]) - /\ - and([x_ExplicitR6_ExplicitVarSizeWithDummy[q42, q49] != 3 -> - x_ExplicitR2_Occurrence[q44, x_ExplicitR6_ExplicitVarSizeWithDummy[q42, q49]] - | q49 : int(1..3)]) - | q44 : int(1..2)]) - | q42 : int(1..2)]), - and([or([and([x_ExplicitR6_ExplicitVarSizeWithDummy[q53, q55] != 3 -> - x_ExplicitR2_Occurrence[q51, x_ExplicitR6_ExplicitVarSizeWithDummy[q53, q55]] - | q55 : int(1..3)]) - /\ - and([x_ExplicitR2_Occurrence[q51, q56] -> - or([x_ExplicitR6_ExplicitVarSizeWithDummy[q53, q58] != 3 /\ - x_ExplicitR6_ExplicitVarSizeWithDummy[q53, q58] = q56 - | q58 : int(1..3)]) - | q56 : int(1..2)]) - | q53 : int(1..2)]) - | q51 : int(1..2)]), - and([or([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q62, q64] -> - or([x_ExplicitR6_ExplicitVarSizeWithDummy[q60, q66] != 3 /\ - x_ExplicitR6_ExplicitVarSizeWithDummy[q60, q66] = - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q62, q64] - | q66 : int(1..3)]) - | q64 : int(1..3)]) - /\ - and([x_ExplicitR6_ExplicitVarSizeWithDummy[q60, q68] != 3 -> - or([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q62, q70] /\ - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q62, q70] = - x_ExplicitR6_ExplicitVarSizeWithDummy[q60, q68] - | q70 : int(1..3)]) - | q68 : int(1..3)]) - | q62 : int(1..2)]) - | q60 : int(1..2)]), - and([or([and([x_ExplicitR6_ExplicitVarSizeWithDummy[q74, q76] != 3 -> - or([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q72, q78] /\ - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q72, q78] = - x_ExplicitR6_ExplicitVarSizeWithDummy[q74, q76] - | q78 : int(1..3)]) - | q76 : int(1..3)]) - /\ - and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q72, q80] -> - or([x_ExplicitR6_ExplicitVarSizeWithDummy[q74, q82] != 3 /\ - x_ExplicitR6_ExplicitVarSizeWithDummy[q74, q82] = - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q72, q80] - | q82 : int(1..3)]) - | q80 : int(1..3)]) - | q74 : int(1..2)]) - | q72 : int(1..2)]) - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_1_4_3-solution000001.solution b/tests/exhaustive/basic/setOfSet04/expected/model_1_4_3-solution000001.solution deleted file mode 100644 index 3ec452354e..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_1_4_3-solution000001.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {1}} -$ Visualisation for x -$ -$ 1 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_1_4_3-solution000002.solution b/tests/exhaustive/basic/setOfSet04/expected/model_1_4_3-solution000002.solution deleted file mode 100644 index c8946f3d06..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_1_4_3-solution000002.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {2}} -$ Visualisation for x -$ -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_1_4_3-solution000003.solution b/tests/exhaustive/basic/setOfSet04/expected/model_1_4_3-solution000003.solution deleted file mode 100644 index a6c0b6a43e..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_1_4_3-solution000003.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {1, 2}} -$ Visualisation for x -$ -$ 1 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_1_4_3-solution000004.solution b/tests/exhaustive/basic/setOfSet04/expected/model_1_4_3-solution000004.solution deleted file mode 100644 index af16592c51..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_1_4_3-solution000004.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1}, {2}} -$ Visualisation for x -$ 1 -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_1_4_3-solution000005.solution b/tests/exhaustive/basic/setOfSet04/expected/model_1_4_3-solution000005.solution deleted file mode 100644 index 38937c9389..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_1_4_3-solution000005.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1}, {1, 2}} -$ Visualisation for x -$ 1 -$ 1 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_1_4_3-solution000006.solution b/tests/exhaustive/basic/setOfSet04/expected/model_1_4_3-solution000006.solution deleted file mode 100644 index 9bf2af0712..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_1_4_3-solution000006.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1, 2}, {2}} -$ Visualisation for x -$ 1 2 -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_1_4_3.eprime b/tests/exhaustive/basic/setOfSet04/expected/model_1_4_3.eprime deleted file mode 100644 index 2a16337699..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_1_4_3.eprime +++ /dev/null @@ -1,129 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitR2_Occurrence: matrix indexed by [int(1..2), int(1..2)] of bool -find x_ExplicitR4_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..2), int(1..3)] of bool -find x_ExplicitR4_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..2), int(1..3)] of int(1..2) -find x_ExplicitR5_ExplicitVarSizeWithMarker_Marker: matrix indexed by [int(1..2)] of int(0..3) -find x_ExplicitR5_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..2), int(1..3)] of int(1..2) -branching on - [x_ExplicitR5_ExplicitVarSizeWithMarker_Marker, x_ExplicitR5_ExplicitVarSizeWithMarker_Values, - x_ExplicitR2_Occurrence, x_ExplicitR4_ExplicitVarSizeWithFlags_Flags, x_ExplicitR4_ExplicitVarSizeWithFlags_Values] -such that - [-toInt(x_ExplicitR2_Occurrence[1, q4]) | q4 : int(1..2)] - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q7, q8] < - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q7, q8 + 1] - | q8 : int(1..2)]) - | q7 : int(1..2)]), - and([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q7, q9] = false -> - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q7, q9] = 1 - | q9 : int(1..3)]) - | q7 : int(1..2)]), - and([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q7, q10 + 1] -> - x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q7, q10] - | q10 : int(1..2)]) - | q7 : int(1..2)]), - and([sum([toInt(x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q7, q11]) | q11 : int(1..3)]) <= 3 | q7 : int(1..2)]), - and([or([and([x_ExplicitR2_Occurrence[q18, q19] -> - or([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q16, q21] /\ - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q16, q21] = q19 - | q21 : int(1..3)]) - | q19 : int(1..2)]) - /\ - and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q16, q23] -> - x_ExplicitR2_Occurrence[q18, x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q16, q23]] - | q23 : int(1..3)]) - | q18 : int(1..2)]) - | q16 : int(1..2)]), - and([or([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q27, q29] -> - x_ExplicitR2_Occurrence[q25, x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q27, q29]] - | q29 : int(1..3)]) - /\ - and([x_ExplicitR2_Occurrence[q25, q30] -> - or([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q27, q32] /\ - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q27, q32] = q30 - | q32 : int(1..3)]) - | q30 : int(1..2)]) - | q27 : int(1..2)]) - | q25 : int(1..2)]), - flatten([[x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[1]; int(1)], - flatten([[x_ExplicitR5_ExplicitVarSizeWithMarker_Values[1, q38]; int(1)] | q38 : int(1..3)]); - int(1..2)]) - - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q34, q35] < - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q34, q35 + 1] - | q35 : int(1..2)]) - | q34 : int(1..2)]), - and([and([q36 > x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q34] -> - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q34, q36] = 1 - | q36 : int(1..3)]) - | q34 : int(1..2)]), - and([x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q34] <= 3 | q34 : int(1..2)]), - and([or([and([x_ExplicitR2_Occurrence[q43, q44] -> - or([q46 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q41] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q41, q46] = q44 - | q46 : int(1..3)]) - | q44 : int(1..2)]) - /\ - and([q48 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q41] -> - x_ExplicitR2_Occurrence[q43, x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q41, q48]] - | q48 : int(1..3)]) - | q43 : int(1..2)]) - | q41 : int(1..2)]), - and([or([and([q54 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q52] -> - x_ExplicitR2_Occurrence[q50, x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q52, q54]] - | q54 : int(1..3)]) - /\ - and([x_ExplicitR2_Occurrence[q50, q55] -> - or([q57 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q52] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q52, q57] = q55 - | q57 : int(1..3)]) - | q55 : int(1..2)]) - | q52 : int(1..2)]) - | q50 : int(1..2)]), - and([or([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q61, q63] -> - or([q65 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q59] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q59, q65] = - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q61, q63] - | q65 : int(1..3)]) - | q63 : int(1..3)]) - /\ - and([q67 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q59] -> - or([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q61, q69] /\ - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q61, q69] = - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q59, q67] - | q69 : int(1..3)]) - | q67 : int(1..3)]) - | q61 : int(1..2)]) - | q59 : int(1..2)]), - and([or([and([q75 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q73] -> - or([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q71, q77] /\ - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q71, q77] = - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q73, q75] - | q77 : int(1..3)]) - | q75 : int(1..3)]) - /\ - and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q71, q79] -> - or([q81 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q73] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q73, q81] = - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q71, q79] - | q81 : int(1..3)]) - | q79 : int(1..3)]) - | q73 : int(1..2)]) - | q71 : int(1..2)]) - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_1_4_4-solution000001.solution b/tests/exhaustive/basic/setOfSet04/expected/model_1_4_4-solution000001.solution deleted file mode 100644 index 3ec452354e..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_1_4_4-solution000001.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {1}} -$ Visualisation for x -$ -$ 1 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_1_4_4-solution000002.solution b/tests/exhaustive/basic/setOfSet04/expected/model_1_4_4-solution000002.solution deleted file mode 100644 index c8946f3d06..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_1_4_4-solution000002.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {2}} -$ Visualisation for x -$ -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_1_4_4-solution000003.solution b/tests/exhaustive/basic/setOfSet04/expected/model_1_4_4-solution000003.solution deleted file mode 100644 index af16592c51..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_1_4_4-solution000003.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1}, {2}} -$ Visualisation for x -$ 1 -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_1_4_4-solution000004.solution b/tests/exhaustive/basic/setOfSet04/expected/model_1_4_4-solution000004.solution deleted file mode 100644 index a6c0b6a43e..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_1_4_4-solution000004.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {1, 2}} -$ Visualisation for x -$ -$ 1 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_1_4_4-solution000005.solution b/tests/exhaustive/basic/setOfSet04/expected/model_1_4_4-solution000005.solution deleted file mode 100644 index 38937c9389..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_1_4_4-solution000005.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1}, {1, 2}} -$ Visualisation for x -$ 1 -$ 1 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_1_4_4-solution000006.solution b/tests/exhaustive/basic/setOfSet04/expected/model_1_4_4-solution000006.solution deleted file mode 100644 index 9bf2af0712..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_1_4_4-solution000006.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1, 2}, {2}} -$ Visualisation for x -$ 1 2 -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_1_4_4.eprime b/tests/exhaustive/basic/setOfSet04/expected/model_1_4_4.eprime deleted file mode 100644 index 47eebe1823..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_1_4_4.eprime +++ /dev/null @@ -1,57 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitR2_Occurrence: matrix indexed by [int(1..2), int(1..2)] of bool -find x_ExplicitR4_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..2), int(1..3)] of bool -find x_ExplicitR4_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..2), int(1..3)] of int(1..2) -branching on - [x_ExplicitR4_ExplicitVarSizeWithFlags_Flags, x_ExplicitR4_ExplicitVarSizeWithFlags_Values, x_ExplicitR2_Occurrence] -such that - [-toInt(x_ExplicitR2_Occurrence[1, q4]) | q4 : int(1..2)] - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q7, q8] < - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q7, q8 + 1] - | q8 : int(1..2)]) - | q7 : int(1..2)]), - and([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q7, q9] = false -> - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q7, q9] = 1 - | q9 : int(1..3)]) - | q7 : int(1..2)]), - and([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q7, q10 + 1] -> - x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q7, q10] - | q10 : int(1..2)]) - | q7 : int(1..2)]), - and([sum([toInt(x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q7, q11]) | q11 : int(1..3)]) <= 3 | q7 : int(1..2)]), - and([or([and([x_ExplicitR2_Occurrence[q18, q19] -> - or([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q16, q21] /\ - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q16, q21] = q19 - | q21 : int(1..3)]) - | q19 : int(1..2)]) - /\ - and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q16, q23] -> - x_ExplicitR2_Occurrence[q18, x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q16, q23]] - | q23 : int(1..3)]) - | q18 : int(1..2)]) - | q16 : int(1..2)]), - and([or([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q27, q29] -> - x_ExplicitR2_Occurrence[q25, x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q27, q29]] - | q29 : int(1..3)]) - /\ - and([x_ExplicitR2_Occurrence[q25, q30] -> - or([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q27, q32] /\ - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q27, q32] = q30 - | q32 : int(1..3)]) - | q30 : int(1..2)]) - | q27 : int(1..2)]) - | q25 : int(1..2)]) - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_2_1_1-solution000001.solution b/tests/exhaustive/basic/setOfSet04/expected/model_2_1_1-solution000001.solution deleted file mode 100644 index c8946f3d06..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_2_1_1-solution000001.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {2}} -$ Visualisation for x -$ -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_2_1_1-solution000002.solution b/tests/exhaustive/basic/setOfSet04/expected/model_2_1_1-solution000002.solution deleted file mode 100644 index 3ec452354e..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_2_1_1-solution000002.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {1}} -$ Visualisation for x -$ -$ 1 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_2_1_1-solution000003.solution b/tests/exhaustive/basic/setOfSet04/expected/model_2_1_1-solution000003.solution deleted file mode 100644 index af16592c51..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_2_1_1-solution000003.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1}, {2}} -$ Visualisation for x -$ 1 -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_2_1_1-solution000004.solution b/tests/exhaustive/basic/setOfSet04/expected/model_2_1_1-solution000004.solution deleted file mode 100644 index a6c0b6a43e..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_2_1_1-solution000004.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {1, 2}} -$ Visualisation for x -$ -$ 1 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_2_1_1-solution000005.solution b/tests/exhaustive/basic/setOfSet04/expected/model_2_1_1-solution000005.solution deleted file mode 100644 index 9bf2af0712..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_2_1_1-solution000005.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1, 2}, {2}} -$ Visualisation for x -$ 1 2 -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_2_1_1-solution000006.solution b/tests/exhaustive/basic/setOfSet04/expected/model_2_1_1-solution000006.solution deleted file mode 100644 index 38937c9389..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_2_1_1-solution000006.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1}, {1, 2}} -$ Visualisation for x -$ 1 -$ 1 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_2_1_1.eprime b/tests/exhaustive/basic/setOfSet04/expected/model_2_1_1.eprime deleted file mode 100644 index 3b170dc84f..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_2_1_1.eprime +++ /dev/null @@ -1,42 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitR6_ExplicitVarSizeWithDummy: matrix indexed by [int(1..2), int(1..3)] of int(1..3) -find x_ExplicitR2_Occurrence: matrix indexed by [int(1..2), int(1..2)] of bool -branching on [x_ExplicitR2_Occurrence, x_ExplicitR6_ExplicitVarSizeWithDummy] -such that - [x_ExplicitR6_ExplicitVarSizeWithDummy[1, q7] | q7 : int(1..3)] x_ExplicitR6_ExplicitVarSizeWithDummy[q2, q4 + 1] = 3 - | q4 : int(1..2)]) - | q2 : int(1..2)]), - and([sum([toInt(x_ExplicitR6_ExplicitVarSizeWithDummy[q2, q5] != 3) | q5 : int(1..3)]) <= 3 | q2 : int(1..2)]), - [-toInt(x_ExplicitR2_Occurrence[1, q12]) | q12 : int(1..2)] - x_ExplicitR2_Occurrence[q15, x_ExplicitR6_ExplicitVarSizeWithDummy[q17, q19]] - | q19 : int(1..3)]) - /\ - and([x_ExplicitR2_Occurrence[q15, q20] -> - or([x_ExplicitR6_ExplicitVarSizeWithDummy[q17, q22] != 3 /\ - x_ExplicitR6_ExplicitVarSizeWithDummy[q17, q22] = q20 - | q22 : int(1..3)]) - | q20 : int(1..2)]) - | q17 : int(1..2)]) - | q15 : int(1..2)]), - and([or([and([x_ExplicitR2_Occurrence[q26, q27] -> - or([x_ExplicitR6_ExplicitVarSizeWithDummy[q24, q29] != 3 /\ - x_ExplicitR6_ExplicitVarSizeWithDummy[q24, q29] = q27 - | q29 : int(1..3)]) - | q27 : int(1..2)]) - /\ - and([x_ExplicitR6_ExplicitVarSizeWithDummy[q24, q31] != 3 -> - x_ExplicitR2_Occurrence[q26, x_ExplicitR6_ExplicitVarSizeWithDummy[q24, q31]] - | q31 : int(1..3)]) - | q26 : int(1..2)]) - | q24 : int(1..2)]) - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_2_1_2-solution000001.solution b/tests/exhaustive/basic/setOfSet04/expected/model_2_1_2-solution000001.solution deleted file mode 100644 index c8946f3d06..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_2_1_2-solution000001.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {2}} -$ Visualisation for x -$ -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_2_1_2-solution000002.solution b/tests/exhaustive/basic/setOfSet04/expected/model_2_1_2-solution000002.solution deleted file mode 100644 index 3ec452354e..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_2_1_2-solution000002.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {1}} -$ Visualisation for x -$ -$ 1 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_2_1_2-solution000003.solution b/tests/exhaustive/basic/setOfSet04/expected/model_2_1_2-solution000003.solution deleted file mode 100644 index af16592c51..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_2_1_2-solution000003.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1}, {2}} -$ Visualisation for x -$ 1 -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_2_1_2-solution000004.solution b/tests/exhaustive/basic/setOfSet04/expected/model_2_1_2-solution000004.solution deleted file mode 100644 index a6c0b6a43e..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_2_1_2-solution000004.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {1, 2}} -$ Visualisation for x -$ -$ 1 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_2_1_2-solution000005.solution b/tests/exhaustive/basic/setOfSet04/expected/model_2_1_2-solution000005.solution deleted file mode 100644 index 9bf2af0712..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_2_1_2-solution000005.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1, 2}, {2}} -$ Visualisation for x -$ 1 2 -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_2_1_2-solution000006.solution b/tests/exhaustive/basic/setOfSet04/expected/model_2_1_2-solution000006.solution deleted file mode 100644 index 38937c9389..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_2_1_2-solution000006.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1}, {1, 2}} -$ Visualisation for x -$ 1 -$ 1 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_2_1_2.eprime b/tests/exhaustive/basic/setOfSet04/expected/model_2_1_2.eprime deleted file mode 100644 index 3b170dc84f..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_2_1_2.eprime +++ /dev/null @@ -1,42 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitR6_ExplicitVarSizeWithDummy: matrix indexed by [int(1..2), int(1..3)] of int(1..3) -find x_ExplicitR2_Occurrence: matrix indexed by [int(1..2), int(1..2)] of bool -branching on [x_ExplicitR2_Occurrence, x_ExplicitR6_ExplicitVarSizeWithDummy] -such that - [x_ExplicitR6_ExplicitVarSizeWithDummy[1, q7] | q7 : int(1..3)] x_ExplicitR6_ExplicitVarSizeWithDummy[q2, q4 + 1] = 3 - | q4 : int(1..2)]) - | q2 : int(1..2)]), - and([sum([toInt(x_ExplicitR6_ExplicitVarSizeWithDummy[q2, q5] != 3) | q5 : int(1..3)]) <= 3 | q2 : int(1..2)]), - [-toInt(x_ExplicitR2_Occurrence[1, q12]) | q12 : int(1..2)] - x_ExplicitR2_Occurrence[q15, x_ExplicitR6_ExplicitVarSizeWithDummy[q17, q19]] - | q19 : int(1..3)]) - /\ - and([x_ExplicitR2_Occurrence[q15, q20] -> - or([x_ExplicitR6_ExplicitVarSizeWithDummy[q17, q22] != 3 /\ - x_ExplicitR6_ExplicitVarSizeWithDummy[q17, q22] = q20 - | q22 : int(1..3)]) - | q20 : int(1..2)]) - | q17 : int(1..2)]) - | q15 : int(1..2)]), - and([or([and([x_ExplicitR2_Occurrence[q26, q27] -> - or([x_ExplicitR6_ExplicitVarSizeWithDummy[q24, q29] != 3 /\ - x_ExplicitR6_ExplicitVarSizeWithDummy[q24, q29] = q27 - | q29 : int(1..3)]) - | q27 : int(1..2)]) - /\ - and([x_ExplicitR6_ExplicitVarSizeWithDummy[q24, q31] != 3 -> - x_ExplicitR2_Occurrence[q26, x_ExplicitR6_ExplicitVarSizeWithDummy[q24, q31]] - | q31 : int(1..3)]) - | q26 : int(1..2)]) - | q24 : int(1..2)]) - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_2_1_3-solution000001.solution b/tests/exhaustive/basic/setOfSet04/expected/model_2_1_3-solution000001.solution deleted file mode 100644 index 3ec452354e..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_2_1_3-solution000001.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {1}} -$ Visualisation for x -$ -$ 1 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_2_1_3-solution000002.solution b/tests/exhaustive/basic/setOfSet04/expected/model_2_1_3-solution000002.solution deleted file mode 100644 index c8946f3d06..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_2_1_3-solution000002.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {2}} -$ Visualisation for x -$ -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_2_1_3-solution000003.solution b/tests/exhaustive/basic/setOfSet04/expected/model_2_1_3-solution000003.solution deleted file mode 100644 index a6c0b6a43e..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_2_1_3-solution000003.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {1, 2}} -$ Visualisation for x -$ -$ 1 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_2_1_3-solution000004.solution b/tests/exhaustive/basic/setOfSet04/expected/model_2_1_3-solution000004.solution deleted file mode 100644 index af16592c51..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_2_1_3-solution000004.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1}, {2}} -$ Visualisation for x -$ 1 -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_2_1_3-solution000005.solution b/tests/exhaustive/basic/setOfSet04/expected/model_2_1_3-solution000005.solution deleted file mode 100644 index 38937c9389..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_2_1_3-solution000005.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1}, {1, 2}} -$ Visualisation for x -$ 1 -$ 1 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_2_1_3-solution000006.solution b/tests/exhaustive/basic/setOfSet04/expected/model_2_1_3-solution000006.solution deleted file mode 100644 index 9bf2af0712..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_2_1_3-solution000006.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1, 2}, {2}} -$ Visualisation for x -$ 1 2 -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_2_1_3.eprime b/tests/exhaustive/basic/setOfSet04/expected/model_2_1_3.eprime deleted file mode 100644 index e8174888c8..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_2_1_3.eprime +++ /dev/null @@ -1,115 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitR6_ExplicitVarSizeWithDummy: matrix indexed by [int(1..2), int(1..3)] of int(1..3) -find x_ExplicitR2_Occurrence: matrix indexed by [int(1..2), int(1..2)] of bool -find x_ExplicitR5_ExplicitVarSizeWithMarker_Marker: matrix indexed by [int(1..2)] of int(0..3) -find x_ExplicitR5_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..2), int(1..3)] of int(1..2) -branching on - [x_ExplicitR5_ExplicitVarSizeWithMarker_Marker, x_ExplicitR5_ExplicitVarSizeWithMarker_Values, - x_ExplicitR6_ExplicitVarSizeWithDummy, x_ExplicitR2_Occurrence] -such that - [x_ExplicitR6_ExplicitVarSizeWithDummy[1, q7] | q7 : int(1..3)] x_ExplicitR6_ExplicitVarSizeWithDummy[q2, q4 + 1] = 3 - | q4 : int(1..2)]) - | q2 : int(1..2)]), - and([sum([toInt(x_ExplicitR6_ExplicitVarSizeWithDummy[q2, q5] != 3) | q5 : int(1..3)]) <= 3 | q2 : int(1..2)]), - [-toInt(x_ExplicitR2_Occurrence[1, q12]) | q12 : int(1..2)] - x_ExplicitR2_Occurrence[q15, x_ExplicitR6_ExplicitVarSizeWithDummy[q17, q19]] - | q19 : int(1..3)]) - /\ - and([x_ExplicitR2_Occurrence[q15, q20] -> - or([x_ExplicitR6_ExplicitVarSizeWithDummy[q17, q22] != 3 /\ - x_ExplicitR6_ExplicitVarSizeWithDummy[q17, q22] = q20 - | q22 : int(1..3)]) - | q20 : int(1..2)]) - | q17 : int(1..2)]) - | q15 : int(1..2)]), - and([or([and([x_ExplicitR2_Occurrence[q26, q27] -> - or([x_ExplicitR6_ExplicitVarSizeWithDummy[q24, q29] != 3 /\ - x_ExplicitR6_ExplicitVarSizeWithDummy[q24, q29] = q27 - | q29 : int(1..3)]) - | q27 : int(1..2)]) - /\ - and([x_ExplicitR6_ExplicitVarSizeWithDummy[q24, q31] != 3 -> - x_ExplicitR2_Occurrence[q26, x_ExplicitR6_ExplicitVarSizeWithDummy[q24, q31]] - | q31 : int(1..3)]) - | q26 : int(1..2)]) - | q24 : int(1..2)]), - flatten([[x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[1]; int(1)], - flatten([[x_ExplicitR5_ExplicitVarSizeWithMarker_Values[1, q37]; int(1)] | q37 : int(1..3)]); - int(1..2)]) - - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q33, q34] < - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q33, q34 + 1] - | q34 : int(1..2)]) - | q33 : int(1..2)]), - and([and([q35 > x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q33] -> - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q33, q35] = 1 - | q35 : int(1..3)]) - | q33 : int(1..2)]), - and([x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q33] <= 3 | q33 : int(1..2)]), - and([or([and([x_ExplicitR6_ExplicitVarSizeWithDummy[q42, q44] != 3 -> - or([q46 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q40] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q40, q46] = - x_ExplicitR6_ExplicitVarSizeWithDummy[q42, q44] - | q46 : int(1..3)]) - | q44 : int(1..3)]) - /\ - and([q48 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q40] -> - or([x_ExplicitR6_ExplicitVarSizeWithDummy[q42, q50] != 3 /\ - x_ExplicitR6_ExplicitVarSizeWithDummy[q42, q50] = - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q40, q48] - | q50 : int(1..3)]) - | q48 : int(1..3)]) - | q42 : int(1..2)]) - | q40 : int(1..2)]), - and([or([and([q56 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q54] -> - or([x_ExplicitR6_ExplicitVarSizeWithDummy[q52, q58] != 3 /\ - x_ExplicitR6_ExplicitVarSizeWithDummy[q52, q58] = - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q54, q56] - | q58 : int(1..3)]) - | q56 : int(1..3)]) - /\ - and([x_ExplicitR6_ExplicitVarSizeWithDummy[q52, q60] != 3 -> - or([q62 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q54] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q54, q62] = - x_ExplicitR6_ExplicitVarSizeWithDummy[q52, q60] - | q62 : int(1..3)]) - | q60 : int(1..3)]) - | q54 : int(1..2)]) - | q52 : int(1..2)]), - and([or([and([x_ExplicitR2_Occurrence[q66, q67] -> - or([q69 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q64] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q64, q69] = q67 - | q69 : int(1..3)]) - | q67 : int(1..2)]) - /\ - and([q71 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q64] -> - x_ExplicitR2_Occurrence[q66, x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q64, q71]] - | q71 : int(1..3)]) - | q66 : int(1..2)]) - | q64 : int(1..2)]), - and([or([and([q77 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q75] -> - x_ExplicitR2_Occurrence[q73, x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q75, q77]] - | q77 : int(1..3)]) - /\ - and([x_ExplicitR2_Occurrence[q73, q78] -> - or([q80 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q75] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q75, q80] = q78 - | q80 : int(1..3)]) - | q78 : int(1..2)]) - | q75 : int(1..2)]) - | q73 : int(1..2)]) - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_2_1_4-solution000001.solution b/tests/exhaustive/basic/setOfSet04/expected/model_2_1_4-solution000001.solution deleted file mode 100644 index 3ec452354e..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_2_1_4-solution000001.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {1}} -$ Visualisation for x -$ -$ 1 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_2_1_4-solution000002.solution b/tests/exhaustive/basic/setOfSet04/expected/model_2_1_4-solution000002.solution deleted file mode 100644 index c8946f3d06..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_2_1_4-solution000002.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {2}} -$ Visualisation for x -$ -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_2_1_4-solution000003.solution b/tests/exhaustive/basic/setOfSet04/expected/model_2_1_4-solution000003.solution deleted file mode 100644 index af16592c51..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_2_1_4-solution000003.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1}, {2}} -$ Visualisation for x -$ 1 -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_2_1_4-solution000004.solution b/tests/exhaustive/basic/setOfSet04/expected/model_2_1_4-solution000004.solution deleted file mode 100644 index a6c0b6a43e..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_2_1_4-solution000004.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {1, 2}} -$ Visualisation for x -$ -$ 1 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_2_1_4-solution000005.solution b/tests/exhaustive/basic/setOfSet04/expected/model_2_1_4-solution000005.solution deleted file mode 100644 index 38937c9389..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_2_1_4-solution000005.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1}, {1, 2}} -$ Visualisation for x -$ 1 -$ 1 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_2_1_4-solution000006.solution b/tests/exhaustive/basic/setOfSet04/expected/model_2_1_4-solution000006.solution deleted file mode 100644 index 9bf2af0712..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_2_1_4-solution000006.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1, 2}, {2}} -$ Visualisation for x -$ 1 2 -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_2_1_4.eprime b/tests/exhaustive/basic/setOfSet04/expected/model_2_1_4.eprime deleted file mode 100644 index 169610bca6..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_2_1_4.eprime +++ /dev/null @@ -1,121 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitR6_ExplicitVarSizeWithDummy: matrix indexed by [int(1..2), int(1..3)] of int(1..3) -find x_ExplicitR2_Occurrence: matrix indexed by [int(1..2), int(1..2)] of bool -find x_ExplicitR4_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..2), int(1..3)] of bool -find x_ExplicitR4_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..2), int(1..3)] of int(1..2) -branching on - [x_ExplicitR4_ExplicitVarSizeWithFlags_Flags, x_ExplicitR4_ExplicitVarSizeWithFlags_Values, - x_ExplicitR6_ExplicitVarSizeWithDummy, x_ExplicitR2_Occurrence] -such that - [x_ExplicitR6_ExplicitVarSizeWithDummy[1, q7] | q7 : int(1..3)] x_ExplicitR6_ExplicitVarSizeWithDummy[q2, q4 + 1] = 3 - | q4 : int(1..2)]) - | q2 : int(1..2)]), - and([sum([toInt(x_ExplicitR6_ExplicitVarSizeWithDummy[q2, q5] != 3) | q5 : int(1..3)]) <= 3 | q2 : int(1..2)]), - [-toInt(x_ExplicitR2_Occurrence[1, q12]) | q12 : int(1..2)] - x_ExplicitR2_Occurrence[q15, x_ExplicitR6_ExplicitVarSizeWithDummy[q17, q19]] - | q19 : int(1..3)]) - /\ - and([x_ExplicitR2_Occurrence[q15, q20] -> - or([x_ExplicitR6_ExplicitVarSizeWithDummy[q17, q22] != 3 /\ - x_ExplicitR6_ExplicitVarSizeWithDummy[q17, q22] = q20 - | q22 : int(1..3)]) - | q20 : int(1..2)]) - | q17 : int(1..2)]) - | q15 : int(1..2)]), - and([or([and([x_ExplicitR2_Occurrence[q26, q27] -> - or([x_ExplicitR6_ExplicitVarSizeWithDummy[q24, q29] != 3 /\ - x_ExplicitR6_ExplicitVarSizeWithDummy[q24, q29] = q27 - | q29 : int(1..3)]) - | q27 : int(1..2)]) - /\ - and([x_ExplicitR6_ExplicitVarSizeWithDummy[q24, q31] != 3 -> - x_ExplicitR2_Occurrence[q26, x_ExplicitR6_ExplicitVarSizeWithDummy[q24, q31]] - | q31 : int(1..3)]) - | q26 : int(1..2)]) - | q24 : int(1..2)]), - flatten([flatten([[-toInt(x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[1, q39]); int(1)], - [x_ExplicitR4_ExplicitVarSizeWithFlags_Values[1, q39]; int(1)]; - int(1..2)]) - | q39 : int(1..3)]) - - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q33, q34] < - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q33, q34 + 1] - | q34 : int(1..2)]) - | q33 : int(1..2)]), - and([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q33, q35] = false -> - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q33, q35] = 1 - | q35 : int(1..3)]) - | q33 : int(1..2)]), - and([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q33, q36 + 1] -> - x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q33, q36] - | q36 : int(1..2)]) - | q33 : int(1..2)]), - and([sum([toInt(x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q33, q37]) | q37 : int(1..3)]) <= 3 | q33 : int(1..2)]), - and([or([and([x_ExplicitR6_ExplicitVarSizeWithDummy[q44, q46] != 3 -> - or([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q42, q48] /\ - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q42, q48] = - x_ExplicitR6_ExplicitVarSizeWithDummy[q44, q46] - | q48 : int(1..3)]) - | q46 : int(1..3)]) - /\ - and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q42, q50] -> - or([x_ExplicitR6_ExplicitVarSizeWithDummy[q44, q52] != 3 /\ - x_ExplicitR6_ExplicitVarSizeWithDummy[q44, q52] = - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q42, q50] - | q52 : int(1..3)]) - | q50 : int(1..3)]) - | q44 : int(1..2)]) - | q42 : int(1..2)]), - and([or([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q56, q58] -> - or([x_ExplicitR6_ExplicitVarSizeWithDummy[q54, q60] != 3 /\ - x_ExplicitR6_ExplicitVarSizeWithDummy[q54, q60] = - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q56, q58] - | q60 : int(1..3)]) - | q58 : int(1..3)]) - /\ - and([x_ExplicitR6_ExplicitVarSizeWithDummy[q54, q62] != 3 -> - or([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q56, q64] /\ - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q56, q64] = - x_ExplicitR6_ExplicitVarSizeWithDummy[q54, q62] - | q64 : int(1..3)]) - | q62 : int(1..3)]) - | q56 : int(1..2)]) - | q54 : int(1..2)]), - and([or([and([x_ExplicitR2_Occurrence[q68, q69] -> - or([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q66, q71] /\ - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q66, q71] = q69 - | q71 : int(1..3)]) - | q69 : int(1..2)]) - /\ - and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q66, q73] -> - x_ExplicitR2_Occurrence[q68, x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q66, q73]] - | q73 : int(1..3)]) - | q68 : int(1..2)]) - | q66 : int(1..2)]), - and([or([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q77, q79] -> - x_ExplicitR2_Occurrence[q75, x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q77, q79]] - | q79 : int(1..3)]) - /\ - and([x_ExplicitR2_Occurrence[q75, q80] -> - or([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q77, q82] /\ - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q77, q82] = q80 - | q82 : int(1..3)]) - | q80 : int(1..2)]) - | q77 : int(1..2)]) - | q75 : int(1..2)]) - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_2_2_1-solution000001.solution b/tests/exhaustive/basic/setOfSet04/expected/model_2_2_1-solution000001.solution deleted file mode 100644 index c8946f3d06..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_2_2_1-solution000001.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {2}} -$ Visualisation for x -$ -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_2_2_1-solution000002.solution b/tests/exhaustive/basic/setOfSet04/expected/model_2_2_1-solution000002.solution deleted file mode 100644 index 3ec452354e..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_2_2_1-solution000002.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {1}} -$ Visualisation for x -$ -$ 1 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_2_2_1-solution000003.solution b/tests/exhaustive/basic/setOfSet04/expected/model_2_2_1-solution000003.solution deleted file mode 100644 index af16592c51..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_2_2_1-solution000003.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1}, {2}} -$ Visualisation for x -$ 1 -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_2_2_1-solution000004.solution b/tests/exhaustive/basic/setOfSet04/expected/model_2_2_1-solution000004.solution deleted file mode 100644 index a6c0b6a43e..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_2_2_1-solution000004.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {1, 2}} -$ Visualisation for x -$ -$ 1 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_2_2_1-solution000005.solution b/tests/exhaustive/basic/setOfSet04/expected/model_2_2_1-solution000005.solution deleted file mode 100644 index 9bf2af0712..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_2_2_1-solution000005.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1, 2}, {2}} -$ Visualisation for x -$ 1 2 -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_2_2_1-solution000006.solution b/tests/exhaustive/basic/setOfSet04/expected/model_2_2_1-solution000006.solution deleted file mode 100644 index 38937c9389..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_2_2_1-solution000006.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1}, {1, 2}} -$ Visualisation for x -$ 1 -$ 1 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_2_2_1.eprime b/tests/exhaustive/basic/setOfSet04/expected/model_2_2_1.eprime deleted file mode 100644 index 3b170dc84f..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_2_2_1.eprime +++ /dev/null @@ -1,42 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitR6_ExplicitVarSizeWithDummy: matrix indexed by [int(1..2), int(1..3)] of int(1..3) -find x_ExplicitR2_Occurrence: matrix indexed by [int(1..2), int(1..2)] of bool -branching on [x_ExplicitR2_Occurrence, x_ExplicitR6_ExplicitVarSizeWithDummy] -such that - [x_ExplicitR6_ExplicitVarSizeWithDummy[1, q7] | q7 : int(1..3)] x_ExplicitR6_ExplicitVarSizeWithDummy[q2, q4 + 1] = 3 - | q4 : int(1..2)]) - | q2 : int(1..2)]), - and([sum([toInt(x_ExplicitR6_ExplicitVarSizeWithDummy[q2, q5] != 3) | q5 : int(1..3)]) <= 3 | q2 : int(1..2)]), - [-toInt(x_ExplicitR2_Occurrence[1, q12]) | q12 : int(1..2)] - x_ExplicitR2_Occurrence[q15, x_ExplicitR6_ExplicitVarSizeWithDummy[q17, q19]] - | q19 : int(1..3)]) - /\ - and([x_ExplicitR2_Occurrence[q15, q20] -> - or([x_ExplicitR6_ExplicitVarSizeWithDummy[q17, q22] != 3 /\ - x_ExplicitR6_ExplicitVarSizeWithDummy[q17, q22] = q20 - | q22 : int(1..3)]) - | q20 : int(1..2)]) - | q17 : int(1..2)]) - | q15 : int(1..2)]), - and([or([and([x_ExplicitR2_Occurrence[q26, q27] -> - or([x_ExplicitR6_ExplicitVarSizeWithDummy[q24, q29] != 3 /\ - x_ExplicitR6_ExplicitVarSizeWithDummy[q24, q29] = q27 - | q29 : int(1..3)]) - | q27 : int(1..2)]) - /\ - and([x_ExplicitR6_ExplicitVarSizeWithDummy[q24, q31] != 3 -> - x_ExplicitR2_Occurrence[q26, x_ExplicitR6_ExplicitVarSizeWithDummy[q24, q31]] - | q31 : int(1..3)]) - | q26 : int(1..2)]) - | q24 : int(1..2)]) - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_2_2_2-solution000001.solution b/tests/exhaustive/basic/setOfSet04/expected/model_2_2_2-solution000001.solution deleted file mode 100644 index 38937c9389..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_2_2_2-solution000001.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1}, {1, 2}} -$ Visualisation for x -$ 1 -$ 1 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_2_2_2-solution000002.solution b/tests/exhaustive/basic/setOfSet04/expected/model_2_2_2-solution000002.solution deleted file mode 100644 index 9bf2af0712..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_2_2_2-solution000002.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1, 2}, {2}} -$ Visualisation for x -$ 1 2 -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_2_2_2-solution000003.solution b/tests/exhaustive/basic/setOfSet04/expected/model_2_2_2-solution000003.solution deleted file mode 100644 index a6c0b6a43e..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_2_2_2-solution000003.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {1, 2}} -$ Visualisation for x -$ -$ 1 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_2_2_2-solution000004.solution b/tests/exhaustive/basic/setOfSet04/expected/model_2_2_2-solution000004.solution deleted file mode 100644 index af16592c51..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_2_2_2-solution000004.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1}, {2}} -$ Visualisation for x -$ 1 -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_2_2_2-solution000005.solution b/tests/exhaustive/basic/setOfSet04/expected/model_2_2_2-solution000005.solution deleted file mode 100644 index 3ec452354e..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_2_2_2-solution000005.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {1}} -$ Visualisation for x -$ -$ 1 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_2_2_2-solution000006.solution b/tests/exhaustive/basic/setOfSet04/expected/model_2_2_2-solution000006.solution deleted file mode 100644 index c8946f3d06..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_2_2_2-solution000006.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {2}} -$ Visualisation for x -$ -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_2_2_2.eprime b/tests/exhaustive/basic/setOfSet04/expected/model_2_2_2.eprime deleted file mode 100644 index 82d1d04484..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_2_2_2.eprime +++ /dev/null @@ -1,16 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitR6_ExplicitVarSizeWithDummy: matrix indexed by [int(1..2), int(1..3)] of int(1..3) -branching on [x_ExplicitR6_ExplicitVarSizeWithDummy] -such that - [x_ExplicitR6_ExplicitVarSizeWithDummy[1, q7] | q7 : int(1..3)] x_ExplicitR6_ExplicitVarSizeWithDummy[q2, q4 + 1] = 3 - | q4 : int(1..2)]) - | q2 : int(1..2)]), - and([sum([toInt(x_ExplicitR6_ExplicitVarSizeWithDummy[q2, q5] != 3) | q5 : int(1..3)]) <= 3 | q2 : int(1..2)]) - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_2_2_3-solution000001.solution b/tests/exhaustive/basic/setOfSet04/expected/model_2_2_3-solution000001.solution deleted file mode 100644 index 3ec452354e..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_2_2_3-solution000001.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {1}} -$ Visualisation for x -$ -$ 1 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_2_2_3-solution000002.solution b/tests/exhaustive/basic/setOfSet04/expected/model_2_2_3-solution000002.solution deleted file mode 100644 index c8946f3d06..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_2_2_3-solution000002.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {2}} -$ Visualisation for x -$ -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_2_2_3-solution000003.solution b/tests/exhaustive/basic/setOfSet04/expected/model_2_2_3-solution000003.solution deleted file mode 100644 index a6c0b6a43e..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_2_2_3-solution000003.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {1, 2}} -$ Visualisation for x -$ -$ 1 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_2_2_3-solution000004.solution b/tests/exhaustive/basic/setOfSet04/expected/model_2_2_3-solution000004.solution deleted file mode 100644 index af16592c51..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_2_2_3-solution000004.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1}, {2}} -$ Visualisation for x -$ 1 -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_2_2_3-solution000005.solution b/tests/exhaustive/basic/setOfSet04/expected/model_2_2_3-solution000005.solution deleted file mode 100644 index 38937c9389..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_2_2_3-solution000005.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1}, {1, 2}} -$ Visualisation for x -$ 1 -$ 1 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_2_2_3-solution000006.solution b/tests/exhaustive/basic/setOfSet04/expected/model_2_2_3-solution000006.solution deleted file mode 100644 index 9bf2af0712..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_2_2_3-solution000006.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1, 2}, {2}} -$ Visualisation for x -$ 1 2 -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_2_2_3.eprime b/tests/exhaustive/basic/setOfSet04/expected/model_2_2_3.eprime deleted file mode 100644 index 5eeb0ebc4a..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_2_2_3.eprime +++ /dev/null @@ -1,67 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitR6_ExplicitVarSizeWithDummy: matrix indexed by [int(1..2), int(1..3)] of int(1..3) -find x_ExplicitR5_ExplicitVarSizeWithMarker_Marker: matrix indexed by [int(1..2)] of int(0..3) -find x_ExplicitR5_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..2), int(1..3)] of int(1..2) -branching on - [x_ExplicitR5_ExplicitVarSizeWithMarker_Marker, x_ExplicitR5_ExplicitVarSizeWithMarker_Values, - x_ExplicitR6_ExplicitVarSizeWithDummy] -such that - [x_ExplicitR6_ExplicitVarSizeWithDummy[1, q7] | q7 : int(1..3)] x_ExplicitR6_ExplicitVarSizeWithDummy[q2, q4 + 1] = 3 - | q4 : int(1..2)]) - | q2 : int(1..2)]), - and([sum([toInt(x_ExplicitR6_ExplicitVarSizeWithDummy[q2, q5] != 3) | q5 : int(1..3)]) <= 3 | q2 : int(1..2)]), - flatten([[x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[1]; int(1)], - flatten([[x_ExplicitR5_ExplicitVarSizeWithMarker_Values[1, q14]; int(1)] | q14 : int(1..3)]); - int(1..2)]) - - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q10, q11] < - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q10, q11 + 1] - | q11 : int(1..2)]) - | q10 : int(1..2)]), - and([and([q12 > x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q10] -> - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q10, q12] = 1 - | q12 : int(1..3)]) - | q10 : int(1..2)]), - and([x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q10] <= 3 | q10 : int(1..2)]), - and([or([and([x_ExplicitR6_ExplicitVarSizeWithDummy[q19, q21] != 3 -> - or([q23 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q17] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q17, q23] = - x_ExplicitR6_ExplicitVarSizeWithDummy[q19, q21] - | q23 : int(1..3)]) - | q21 : int(1..3)]) - /\ - and([q25 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q17] -> - or([x_ExplicitR6_ExplicitVarSizeWithDummy[q19, q27] != 3 /\ - x_ExplicitR6_ExplicitVarSizeWithDummy[q19, q27] = - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q17, q25] - | q27 : int(1..3)]) - | q25 : int(1..3)]) - | q19 : int(1..2)]) - | q17 : int(1..2)]), - and([or([and([q33 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q31] -> - or([x_ExplicitR6_ExplicitVarSizeWithDummy[q29, q35] != 3 /\ - x_ExplicitR6_ExplicitVarSizeWithDummy[q29, q35] = - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q31, q33] - | q35 : int(1..3)]) - | q33 : int(1..3)]) - /\ - and([x_ExplicitR6_ExplicitVarSizeWithDummy[q29, q37] != 3 -> - or([q39 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q31] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q31, q39] = - x_ExplicitR6_ExplicitVarSizeWithDummy[q29, q37] - | q39 : int(1..3)]) - | q37 : int(1..3)]) - | q31 : int(1..2)]) - | q29 : int(1..2)]) - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_2_2_4-solution000001.solution b/tests/exhaustive/basic/setOfSet04/expected/model_2_2_4-solution000001.solution deleted file mode 100644 index 3ec452354e..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_2_2_4-solution000001.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {1}} -$ Visualisation for x -$ -$ 1 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_2_2_4-solution000002.solution b/tests/exhaustive/basic/setOfSet04/expected/model_2_2_4-solution000002.solution deleted file mode 100644 index c8946f3d06..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_2_2_4-solution000002.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {2}} -$ Visualisation for x -$ -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_2_2_4-solution000003.solution b/tests/exhaustive/basic/setOfSet04/expected/model_2_2_4-solution000003.solution deleted file mode 100644 index af16592c51..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_2_2_4-solution000003.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1}, {2}} -$ Visualisation for x -$ 1 -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_2_2_4-solution000004.solution b/tests/exhaustive/basic/setOfSet04/expected/model_2_2_4-solution000004.solution deleted file mode 100644 index a6c0b6a43e..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_2_2_4-solution000004.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {1, 2}} -$ Visualisation for x -$ -$ 1 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_2_2_4-solution000005.solution b/tests/exhaustive/basic/setOfSet04/expected/model_2_2_4-solution000005.solution deleted file mode 100644 index 38937c9389..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_2_2_4-solution000005.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1}, {1, 2}} -$ Visualisation for x -$ 1 -$ 1 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_2_2_4-solution000006.solution b/tests/exhaustive/basic/setOfSet04/expected/model_2_2_4-solution000006.solution deleted file mode 100644 index 9bf2af0712..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_2_2_4-solution000006.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1, 2}, {2}} -$ Visualisation for x -$ 1 2 -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_2_2_4.eprime b/tests/exhaustive/basic/setOfSet04/expected/model_2_2_4.eprime deleted file mode 100644 index 247428fb21..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_2_2_4.eprime +++ /dev/null @@ -1,73 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitR6_ExplicitVarSizeWithDummy: matrix indexed by [int(1..2), int(1..3)] of int(1..3) -find x_ExplicitR4_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..2), int(1..3)] of bool -find x_ExplicitR4_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..2), int(1..3)] of int(1..2) -branching on - [x_ExplicitR4_ExplicitVarSizeWithFlags_Flags, x_ExplicitR4_ExplicitVarSizeWithFlags_Values, - x_ExplicitR6_ExplicitVarSizeWithDummy] -such that - [x_ExplicitR6_ExplicitVarSizeWithDummy[1, q7] | q7 : int(1..3)] x_ExplicitR6_ExplicitVarSizeWithDummy[q2, q4 + 1] = 3 - | q4 : int(1..2)]) - | q2 : int(1..2)]), - and([sum([toInt(x_ExplicitR6_ExplicitVarSizeWithDummy[q2, q5] != 3) | q5 : int(1..3)]) <= 3 | q2 : int(1..2)]), - flatten([flatten([[-toInt(x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[1, q16]); int(1)], - [x_ExplicitR4_ExplicitVarSizeWithFlags_Values[1, q16]; int(1)]; - int(1..2)]) - | q16 : int(1..3)]) - - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q10, q11] < - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q10, q11 + 1] - | q11 : int(1..2)]) - | q10 : int(1..2)]), - and([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q10, q12] = false -> - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q10, q12] = 1 - | q12 : int(1..3)]) - | q10 : int(1..2)]), - and([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q10, q13 + 1] -> - x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q10, q13] - | q13 : int(1..2)]) - | q10 : int(1..2)]), - and([sum([toInt(x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q10, q14]) | q14 : int(1..3)]) <= 3 | q10 : int(1..2)]), - and([or([and([x_ExplicitR6_ExplicitVarSizeWithDummy[q21, q23] != 3 -> - or([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q19, q25] /\ - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q19, q25] = - x_ExplicitR6_ExplicitVarSizeWithDummy[q21, q23] - | q25 : int(1..3)]) - | q23 : int(1..3)]) - /\ - and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q19, q27] -> - or([x_ExplicitR6_ExplicitVarSizeWithDummy[q21, q29] != 3 /\ - x_ExplicitR6_ExplicitVarSizeWithDummy[q21, q29] = - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q19, q27] - | q29 : int(1..3)]) - | q27 : int(1..3)]) - | q21 : int(1..2)]) - | q19 : int(1..2)]), - and([or([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q33, q35] -> - or([x_ExplicitR6_ExplicitVarSizeWithDummy[q31, q37] != 3 /\ - x_ExplicitR6_ExplicitVarSizeWithDummy[q31, q37] = - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q33, q35] - | q37 : int(1..3)]) - | q35 : int(1..3)]) - /\ - and([x_ExplicitR6_ExplicitVarSizeWithDummy[q31, q39] != 3 -> - or([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q33, q41] /\ - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q33, q41] = - x_ExplicitR6_ExplicitVarSizeWithDummy[q31, q39] - | q41 : int(1..3)]) - | q39 : int(1..3)]) - | q33 : int(1..2)]) - | q31 : int(1..2)]) - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_2_3_1-solution000001.solution b/tests/exhaustive/basic/setOfSet04/expected/model_2_3_1-solution000001.solution deleted file mode 100644 index c8946f3d06..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_2_3_1-solution000001.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {2}} -$ Visualisation for x -$ -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_2_3_1-solution000002.solution b/tests/exhaustive/basic/setOfSet04/expected/model_2_3_1-solution000002.solution deleted file mode 100644 index 3ec452354e..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_2_3_1-solution000002.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {1}} -$ Visualisation for x -$ -$ 1 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_2_3_1-solution000003.solution b/tests/exhaustive/basic/setOfSet04/expected/model_2_3_1-solution000003.solution deleted file mode 100644 index af16592c51..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_2_3_1-solution000003.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1}, {2}} -$ Visualisation for x -$ 1 -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_2_3_1-solution000004.solution b/tests/exhaustive/basic/setOfSet04/expected/model_2_3_1-solution000004.solution deleted file mode 100644 index a6c0b6a43e..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_2_3_1-solution000004.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {1, 2}} -$ Visualisation for x -$ -$ 1 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_2_3_1-solution000005.solution b/tests/exhaustive/basic/setOfSet04/expected/model_2_3_1-solution000005.solution deleted file mode 100644 index 9bf2af0712..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_2_3_1-solution000005.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1, 2}, {2}} -$ Visualisation for x -$ 1 2 -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_2_3_1-solution000006.solution b/tests/exhaustive/basic/setOfSet04/expected/model_2_3_1-solution000006.solution deleted file mode 100644 index 38937c9389..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_2_3_1-solution000006.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1}, {1, 2}} -$ Visualisation for x -$ 1 -$ 1 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_2_3_1.eprime b/tests/exhaustive/basic/setOfSet04/expected/model_2_3_1.eprime deleted file mode 100644 index 4d78b43715..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_2_3_1.eprime +++ /dev/null @@ -1,115 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitR6_ExplicitVarSizeWithDummy: matrix indexed by [int(1..2), int(1..3)] of int(1..3) -find x_ExplicitR5_ExplicitVarSizeWithMarker_Marker: matrix indexed by [int(1..2)] of int(0..3) -find x_ExplicitR5_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..2), int(1..3)] of int(1..2) -find x_ExplicitR2_Occurrence: matrix indexed by [int(1..2), int(1..2)] of bool -branching on - [x_ExplicitR2_Occurrence, x_ExplicitR6_ExplicitVarSizeWithDummy, x_ExplicitR5_ExplicitVarSizeWithMarker_Marker, - x_ExplicitR5_ExplicitVarSizeWithMarker_Values] -such that - [x_ExplicitR6_ExplicitVarSizeWithDummy[1, q7] | q7 : int(1..3)] x_ExplicitR6_ExplicitVarSizeWithDummy[q2, q4 + 1] = 3 - | q4 : int(1..2)]) - | q2 : int(1..2)]), - and([sum([toInt(x_ExplicitR6_ExplicitVarSizeWithDummy[q2, q5] != 3) | q5 : int(1..3)]) <= 3 | q2 : int(1..2)]), - flatten([[x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[1]; int(1)], - flatten([[x_ExplicitR5_ExplicitVarSizeWithMarker_Values[1, q14]; int(1)] | q14 : int(1..3)]); - int(1..2)]) - - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q10, q11] < - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q10, q11 + 1] - | q11 : int(1..2)]) - | q10 : int(1..2)]), - and([and([q12 > x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q10] -> - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q10, q12] = 1 - | q12 : int(1..3)]) - | q10 : int(1..2)]), - and([x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q10] <= 3 | q10 : int(1..2)]), - and([or([and([x_ExplicitR6_ExplicitVarSizeWithDummy[q19, q21] != 3 -> - or([q23 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q17] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q17, q23] = - x_ExplicitR6_ExplicitVarSizeWithDummy[q19, q21] - | q23 : int(1..3)]) - | q21 : int(1..3)]) - /\ - and([q25 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q17] -> - or([x_ExplicitR6_ExplicitVarSizeWithDummy[q19, q27] != 3 /\ - x_ExplicitR6_ExplicitVarSizeWithDummy[q19, q27] = - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q17, q25] - | q27 : int(1..3)]) - | q25 : int(1..3)]) - | q19 : int(1..2)]) - | q17 : int(1..2)]), - and([or([and([q33 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q31] -> - or([x_ExplicitR6_ExplicitVarSizeWithDummy[q29, q35] != 3 /\ - x_ExplicitR6_ExplicitVarSizeWithDummy[q29, q35] = - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q31, q33] - | q35 : int(1..3)]) - | q33 : int(1..3)]) - /\ - and([x_ExplicitR6_ExplicitVarSizeWithDummy[q29, q37] != 3 -> - or([q39 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q31] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q31, q39] = - x_ExplicitR6_ExplicitVarSizeWithDummy[q29, q37] - | q39 : int(1..3)]) - | q37 : int(1..3)]) - | q31 : int(1..2)]) - | q29 : int(1..2)]), - [-toInt(x_ExplicitR2_Occurrence[1, q43]) | q43 : int(1..2)] - x_ExplicitR2_Occurrence[q46, x_ExplicitR6_ExplicitVarSizeWithDummy[q48, q50]] - | q50 : int(1..3)]) - /\ - and([x_ExplicitR2_Occurrence[q46, q51] -> - or([x_ExplicitR6_ExplicitVarSizeWithDummy[q48, q53] != 3 /\ - x_ExplicitR6_ExplicitVarSizeWithDummy[q48, q53] = q51 - | q53 : int(1..3)]) - | q51 : int(1..2)]) - | q48 : int(1..2)]) - | q46 : int(1..2)]), - and([or([and([x_ExplicitR2_Occurrence[q57, q58] -> - or([x_ExplicitR6_ExplicitVarSizeWithDummy[q55, q60] != 3 /\ - x_ExplicitR6_ExplicitVarSizeWithDummy[q55, q60] = q58 - | q60 : int(1..3)]) - | q58 : int(1..2)]) - /\ - and([x_ExplicitR6_ExplicitVarSizeWithDummy[q55, q62] != 3 -> - x_ExplicitR2_Occurrence[q57, x_ExplicitR6_ExplicitVarSizeWithDummy[q55, q62]] - | q62 : int(1..3)]) - | q57 : int(1..2)]) - | q55 : int(1..2)]), - and([or([and([q68 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q66] -> - x_ExplicitR2_Occurrence[q64, x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q66, q68]] - | q68 : int(1..3)]) - /\ - and([x_ExplicitR2_Occurrence[q64, q69] -> - or([q71 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q66] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q66, q71] = q69 - | q71 : int(1..3)]) - | q69 : int(1..2)]) - | q66 : int(1..2)]) - | q64 : int(1..2)]), - and([or([and([x_ExplicitR2_Occurrence[q75, q76] -> - or([q78 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q73] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q73, q78] = q76 - | q78 : int(1..3)]) - | q76 : int(1..2)]) - /\ - and([q80 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q73] -> - x_ExplicitR2_Occurrence[q75, x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q73, q80]] - | q80 : int(1..3)]) - | q75 : int(1..2)]) - | q73 : int(1..2)]) - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_2_3_2-solution000001.solution b/tests/exhaustive/basic/setOfSet04/expected/model_2_3_2-solution000001.solution deleted file mode 100644 index 3ec452354e..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_2_3_2-solution000001.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {1}} -$ Visualisation for x -$ -$ 1 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_2_3_2-solution000002.solution b/tests/exhaustive/basic/setOfSet04/expected/model_2_3_2-solution000002.solution deleted file mode 100644 index c8946f3d06..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_2_3_2-solution000002.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {2}} -$ Visualisation for x -$ -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_2_3_2-solution000003.solution b/tests/exhaustive/basic/setOfSet04/expected/model_2_3_2-solution000003.solution deleted file mode 100644 index a6c0b6a43e..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_2_3_2-solution000003.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {1, 2}} -$ Visualisation for x -$ -$ 1 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_2_3_2-solution000004.solution b/tests/exhaustive/basic/setOfSet04/expected/model_2_3_2-solution000004.solution deleted file mode 100644 index af16592c51..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_2_3_2-solution000004.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1}, {2}} -$ Visualisation for x -$ 1 -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_2_3_2-solution000005.solution b/tests/exhaustive/basic/setOfSet04/expected/model_2_3_2-solution000005.solution deleted file mode 100644 index 38937c9389..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_2_3_2-solution000005.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1}, {1, 2}} -$ Visualisation for x -$ 1 -$ 1 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_2_3_2-solution000006.solution b/tests/exhaustive/basic/setOfSet04/expected/model_2_3_2-solution000006.solution deleted file mode 100644 index 9bf2af0712..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_2_3_2-solution000006.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1, 2}, {2}} -$ Visualisation for x -$ 1 2 -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_2_3_2.eprime b/tests/exhaustive/basic/setOfSet04/expected/model_2_3_2.eprime deleted file mode 100644 index 5eeb0ebc4a..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_2_3_2.eprime +++ /dev/null @@ -1,67 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitR6_ExplicitVarSizeWithDummy: matrix indexed by [int(1..2), int(1..3)] of int(1..3) -find x_ExplicitR5_ExplicitVarSizeWithMarker_Marker: matrix indexed by [int(1..2)] of int(0..3) -find x_ExplicitR5_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..2), int(1..3)] of int(1..2) -branching on - [x_ExplicitR5_ExplicitVarSizeWithMarker_Marker, x_ExplicitR5_ExplicitVarSizeWithMarker_Values, - x_ExplicitR6_ExplicitVarSizeWithDummy] -such that - [x_ExplicitR6_ExplicitVarSizeWithDummy[1, q7] | q7 : int(1..3)] x_ExplicitR6_ExplicitVarSizeWithDummy[q2, q4 + 1] = 3 - | q4 : int(1..2)]) - | q2 : int(1..2)]), - and([sum([toInt(x_ExplicitR6_ExplicitVarSizeWithDummy[q2, q5] != 3) | q5 : int(1..3)]) <= 3 | q2 : int(1..2)]), - flatten([[x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[1]; int(1)], - flatten([[x_ExplicitR5_ExplicitVarSizeWithMarker_Values[1, q14]; int(1)] | q14 : int(1..3)]); - int(1..2)]) - - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q10, q11] < - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q10, q11 + 1] - | q11 : int(1..2)]) - | q10 : int(1..2)]), - and([and([q12 > x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q10] -> - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q10, q12] = 1 - | q12 : int(1..3)]) - | q10 : int(1..2)]), - and([x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q10] <= 3 | q10 : int(1..2)]), - and([or([and([x_ExplicitR6_ExplicitVarSizeWithDummy[q19, q21] != 3 -> - or([q23 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q17] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q17, q23] = - x_ExplicitR6_ExplicitVarSizeWithDummy[q19, q21] - | q23 : int(1..3)]) - | q21 : int(1..3)]) - /\ - and([q25 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q17] -> - or([x_ExplicitR6_ExplicitVarSizeWithDummy[q19, q27] != 3 /\ - x_ExplicitR6_ExplicitVarSizeWithDummy[q19, q27] = - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q17, q25] - | q27 : int(1..3)]) - | q25 : int(1..3)]) - | q19 : int(1..2)]) - | q17 : int(1..2)]), - and([or([and([q33 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q31] -> - or([x_ExplicitR6_ExplicitVarSizeWithDummy[q29, q35] != 3 /\ - x_ExplicitR6_ExplicitVarSizeWithDummy[q29, q35] = - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q31, q33] - | q35 : int(1..3)]) - | q33 : int(1..3)]) - /\ - and([x_ExplicitR6_ExplicitVarSizeWithDummy[q29, q37] != 3 -> - or([q39 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q31] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q31, q39] = - x_ExplicitR6_ExplicitVarSizeWithDummy[q29, q37] - | q39 : int(1..3)]) - | q37 : int(1..3)]) - | q31 : int(1..2)]) - | q29 : int(1..2)]) - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_2_3_3-solution000001.solution b/tests/exhaustive/basic/setOfSet04/expected/model_2_3_3-solution000001.solution deleted file mode 100644 index 3ec452354e..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_2_3_3-solution000001.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {1}} -$ Visualisation for x -$ -$ 1 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_2_3_3-solution000002.solution b/tests/exhaustive/basic/setOfSet04/expected/model_2_3_3-solution000002.solution deleted file mode 100644 index c8946f3d06..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_2_3_3-solution000002.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {2}} -$ Visualisation for x -$ -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_2_3_3-solution000003.solution b/tests/exhaustive/basic/setOfSet04/expected/model_2_3_3-solution000003.solution deleted file mode 100644 index a6c0b6a43e..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_2_3_3-solution000003.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {1, 2}} -$ Visualisation for x -$ -$ 1 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_2_3_3-solution000004.solution b/tests/exhaustive/basic/setOfSet04/expected/model_2_3_3-solution000004.solution deleted file mode 100644 index af16592c51..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_2_3_3-solution000004.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1}, {2}} -$ Visualisation for x -$ 1 -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_2_3_3-solution000005.solution b/tests/exhaustive/basic/setOfSet04/expected/model_2_3_3-solution000005.solution deleted file mode 100644 index 38937c9389..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_2_3_3-solution000005.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1}, {1, 2}} -$ Visualisation for x -$ 1 -$ 1 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_2_3_3-solution000006.solution b/tests/exhaustive/basic/setOfSet04/expected/model_2_3_3-solution000006.solution deleted file mode 100644 index 9bf2af0712..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_2_3_3-solution000006.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1, 2}, {2}} -$ Visualisation for x -$ 1 2 -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_2_3_3.eprime b/tests/exhaustive/basic/setOfSet04/expected/model_2_3_3.eprime deleted file mode 100644 index 5eeb0ebc4a..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_2_3_3.eprime +++ /dev/null @@ -1,67 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitR6_ExplicitVarSizeWithDummy: matrix indexed by [int(1..2), int(1..3)] of int(1..3) -find x_ExplicitR5_ExplicitVarSizeWithMarker_Marker: matrix indexed by [int(1..2)] of int(0..3) -find x_ExplicitR5_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..2), int(1..3)] of int(1..2) -branching on - [x_ExplicitR5_ExplicitVarSizeWithMarker_Marker, x_ExplicitR5_ExplicitVarSizeWithMarker_Values, - x_ExplicitR6_ExplicitVarSizeWithDummy] -such that - [x_ExplicitR6_ExplicitVarSizeWithDummy[1, q7] | q7 : int(1..3)] x_ExplicitR6_ExplicitVarSizeWithDummy[q2, q4 + 1] = 3 - | q4 : int(1..2)]) - | q2 : int(1..2)]), - and([sum([toInt(x_ExplicitR6_ExplicitVarSizeWithDummy[q2, q5] != 3) | q5 : int(1..3)]) <= 3 | q2 : int(1..2)]), - flatten([[x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[1]; int(1)], - flatten([[x_ExplicitR5_ExplicitVarSizeWithMarker_Values[1, q14]; int(1)] | q14 : int(1..3)]); - int(1..2)]) - - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q10, q11] < - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q10, q11 + 1] - | q11 : int(1..2)]) - | q10 : int(1..2)]), - and([and([q12 > x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q10] -> - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q10, q12] = 1 - | q12 : int(1..3)]) - | q10 : int(1..2)]), - and([x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q10] <= 3 | q10 : int(1..2)]), - and([or([and([x_ExplicitR6_ExplicitVarSizeWithDummy[q19, q21] != 3 -> - or([q23 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q17] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q17, q23] = - x_ExplicitR6_ExplicitVarSizeWithDummy[q19, q21] - | q23 : int(1..3)]) - | q21 : int(1..3)]) - /\ - and([q25 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q17] -> - or([x_ExplicitR6_ExplicitVarSizeWithDummy[q19, q27] != 3 /\ - x_ExplicitR6_ExplicitVarSizeWithDummy[q19, q27] = - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q17, q25] - | q27 : int(1..3)]) - | q25 : int(1..3)]) - | q19 : int(1..2)]) - | q17 : int(1..2)]), - and([or([and([q33 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q31] -> - or([x_ExplicitR6_ExplicitVarSizeWithDummy[q29, q35] != 3 /\ - x_ExplicitR6_ExplicitVarSizeWithDummy[q29, q35] = - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q31, q33] - | q35 : int(1..3)]) - | q33 : int(1..3)]) - /\ - and([x_ExplicitR6_ExplicitVarSizeWithDummy[q29, q37] != 3 -> - or([q39 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q31] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q31, q39] = - x_ExplicitR6_ExplicitVarSizeWithDummy[q29, q37] - | q39 : int(1..3)]) - | q37 : int(1..3)]) - | q31 : int(1..2)]) - | q29 : int(1..2)]) - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_2_3_4-solution000001.solution b/tests/exhaustive/basic/setOfSet04/expected/model_2_3_4-solution000001.solution deleted file mode 100644 index 3ec452354e..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_2_3_4-solution000001.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {1}} -$ Visualisation for x -$ -$ 1 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_2_3_4-solution000002.solution b/tests/exhaustive/basic/setOfSet04/expected/model_2_3_4-solution000002.solution deleted file mode 100644 index c8946f3d06..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_2_3_4-solution000002.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {2}} -$ Visualisation for x -$ -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_2_3_4-solution000003.solution b/tests/exhaustive/basic/setOfSet04/expected/model_2_3_4-solution000003.solution deleted file mode 100644 index af16592c51..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_2_3_4-solution000003.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1}, {2}} -$ Visualisation for x -$ 1 -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_2_3_4-solution000004.solution b/tests/exhaustive/basic/setOfSet04/expected/model_2_3_4-solution000004.solution deleted file mode 100644 index a6c0b6a43e..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_2_3_4-solution000004.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {1, 2}} -$ Visualisation for x -$ -$ 1 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_2_3_4-solution000005.solution b/tests/exhaustive/basic/setOfSet04/expected/model_2_3_4-solution000005.solution deleted file mode 100644 index 38937c9389..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_2_3_4-solution000005.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1}, {1, 2}} -$ Visualisation for x -$ 1 -$ 1 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_2_3_4-solution000006.solution b/tests/exhaustive/basic/setOfSet04/expected/model_2_3_4-solution000006.solution deleted file mode 100644 index 9bf2af0712..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_2_3_4-solution000006.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1, 2}, {2}} -$ Visualisation for x -$ 1 2 -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_2_3_4.eprime b/tests/exhaustive/basic/setOfSet04/expected/model_2_3_4.eprime deleted file mode 100644 index d7228f96df..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_2_3_4.eprime +++ /dev/null @@ -1,153 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitR6_ExplicitVarSizeWithDummy: matrix indexed by [int(1..2), int(1..3)] of int(1..3) -find x_ExplicitR5_ExplicitVarSizeWithMarker_Marker: matrix indexed by [int(1..2)] of int(0..3) -find x_ExplicitR5_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..2), int(1..3)] of int(1..2) -find x_ExplicitR4_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..2), int(1..3)] of bool -find x_ExplicitR4_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..2), int(1..3)] of int(1..2) -branching on - [x_ExplicitR4_ExplicitVarSizeWithFlags_Flags, x_ExplicitR4_ExplicitVarSizeWithFlags_Values, - x_ExplicitR6_ExplicitVarSizeWithDummy, x_ExplicitR5_ExplicitVarSizeWithMarker_Marker, - x_ExplicitR5_ExplicitVarSizeWithMarker_Values] -such that - [x_ExplicitR6_ExplicitVarSizeWithDummy[1, q7] | q7 : int(1..3)] x_ExplicitR6_ExplicitVarSizeWithDummy[q2, q4 + 1] = 3 - | q4 : int(1..2)]) - | q2 : int(1..2)]), - and([sum([toInt(x_ExplicitR6_ExplicitVarSizeWithDummy[q2, q5] != 3) | q5 : int(1..3)]) <= 3 | q2 : int(1..2)]), - flatten([[x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[1]; int(1)], - flatten([[x_ExplicitR5_ExplicitVarSizeWithMarker_Values[1, q14]; int(1)] | q14 : int(1..3)]); - int(1..2)]) - - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q10, q11] < - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q10, q11 + 1] - | q11 : int(1..2)]) - | q10 : int(1..2)]), - and([and([q12 > x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q10] -> - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q10, q12] = 1 - | q12 : int(1..3)]) - | q10 : int(1..2)]), - and([x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q10] <= 3 | q10 : int(1..2)]), - and([or([and([x_ExplicitR6_ExplicitVarSizeWithDummy[q19, q21] != 3 -> - or([q23 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q17] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q17, q23] = - x_ExplicitR6_ExplicitVarSizeWithDummy[q19, q21] - | q23 : int(1..3)]) - | q21 : int(1..3)]) - /\ - and([q25 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q17] -> - or([x_ExplicitR6_ExplicitVarSizeWithDummy[q19, q27] != 3 /\ - x_ExplicitR6_ExplicitVarSizeWithDummy[q19, q27] = - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q17, q25] - | q27 : int(1..3)]) - | q25 : int(1..3)]) - | q19 : int(1..2)]) - | q17 : int(1..2)]), - and([or([and([q33 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q31] -> - or([x_ExplicitR6_ExplicitVarSizeWithDummy[q29, q35] != 3 /\ - x_ExplicitR6_ExplicitVarSizeWithDummy[q29, q35] = - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q31, q33] - | q35 : int(1..3)]) - | q33 : int(1..3)]) - /\ - and([x_ExplicitR6_ExplicitVarSizeWithDummy[q29, q37] != 3 -> - or([q39 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q31] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q31, q39] = - x_ExplicitR6_ExplicitVarSizeWithDummy[q29, q37] - | q39 : int(1..3)]) - | q37 : int(1..3)]) - | q31 : int(1..2)]) - | q29 : int(1..2)]), - flatten([flatten([[-toInt(x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[1, q47]); int(1)], - [x_ExplicitR4_ExplicitVarSizeWithFlags_Values[1, q47]; int(1)]; - int(1..2)]) - | q47 : int(1..3)]) - - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q41, q42] < - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q41, q42 + 1] - | q42 : int(1..2)]) - | q41 : int(1..2)]), - and([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q41, q43] = false -> - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q41, q43] = 1 - | q43 : int(1..3)]) - | q41 : int(1..2)]), - and([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q41, q44 + 1] -> - x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q41, q44] - | q44 : int(1..2)]) - | q41 : int(1..2)]), - and([sum([toInt(x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q41, q45]) | q45 : int(1..3)]) <= 3 | q41 : int(1..2)]), - and([or([and([x_ExplicitR6_ExplicitVarSizeWithDummy[q52, q54] != 3 -> - or([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q50, q56] /\ - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q50, q56] = - x_ExplicitR6_ExplicitVarSizeWithDummy[q52, q54] - | q56 : int(1..3)]) - | q54 : int(1..3)]) - /\ - and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q50, q58] -> - or([x_ExplicitR6_ExplicitVarSizeWithDummy[q52, q60] != 3 /\ - x_ExplicitR6_ExplicitVarSizeWithDummy[q52, q60] = - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q50, q58] - | q60 : int(1..3)]) - | q58 : int(1..3)]) - | q52 : int(1..2)]) - | q50 : int(1..2)]), - and([or([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q64, q66] -> - or([x_ExplicitR6_ExplicitVarSizeWithDummy[q62, q68] != 3 /\ - x_ExplicitR6_ExplicitVarSizeWithDummy[q62, q68] = - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q64, q66] - | q68 : int(1..3)]) - | q66 : int(1..3)]) - /\ - and([x_ExplicitR6_ExplicitVarSizeWithDummy[q62, q70] != 3 -> - or([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q64, q72] /\ - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q64, q72] = - x_ExplicitR6_ExplicitVarSizeWithDummy[q62, q70] - | q72 : int(1..3)]) - | q70 : int(1..3)]) - | q64 : int(1..2)]) - | q62 : int(1..2)]), - and([or([and([q78 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q76] -> - or([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q74, q80] /\ - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q74, q80] = - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q76, q78] - | q80 : int(1..3)]) - | q78 : int(1..3)]) - /\ - and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q74, q82] -> - or([q84 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q76] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q76, q84] = - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q74, q82] - | q84 : int(1..3)]) - | q82 : int(1..3)]) - | q76 : int(1..2)]) - | q74 : int(1..2)]), - and([or([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q88, q90] -> - or([q92 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q86] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q86, q92] = - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q88, q90] - | q92 : int(1..3)]) - | q90 : int(1..3)]) - /\ - and([q94 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q86] -> - or([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q88, q96] /\ - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q88, q96] = - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q86, q94] - | q96 : int(1..3)]) - | q94 : int(1..3)]) - | q88 : int(1..2)]) - | q86 : int(1..2)]) - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_2_4_1-solution000001.solution b/tests/exhaustive/basic/setOfSet04/expected/model_2_4_1-solution000001.solution deleted file mode 100644 index c8946f3d06..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_2_4_1-solution000001.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {2}} -$ Visualisation for x -$ -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_2_4_1-solution000002.solution b/tests/exhaustive/basic/setOfSet04/expected/model_2_4_1-solution000002.solution deleted file mode 100644 index 3ec452354e..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_2_4_1-solution000002.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {1}} -$ Visualisation for x -$ -$ 1 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_2_4_1-solution000003.solution b/tests/exhaustive/basic/setOfSet04/expected/model_2_4_1-solution000003.solution deleted file mode 100644 index af16592c51..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_2_4_1-solution000003.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1}, {2}} -$ Visualisation for x -$ 1 -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_2_4_1-solution000004.solution b/tests/exhaustive/basic/setOfSet04/expected/model_2_4_1-solution000004.solution deleted file mode 100644 index a6c0b6a43e..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_2_4_1-solution000004.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {1, 2}} -$ Visualisation for x -$ -$ 1 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_2_4_1-solution000005.solution b/tests/exhaustive/basic/setOfSet04/expected/model_2_4_1-solution000005.solution deleted file mode 100644 index 9bf2af0712..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_2_4_1-solution000005.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1, 2}, {2}} -$ Visualisation for x -$ 1 2 -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_2_4_1-solution000006.solution b/tests/exhaustive/basic/setOfSet04/expected/model_2_4_1-solution000006.solution deleted file mode 100644 index 38937c9389..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_2_4_1-solution000006.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1}, {1, 2}} -$ Visualisation for x -$ 1 -$ 1 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_2_4_1.eprime b/tests/exhaustive/basic/setOfSet04/expected/model_2_4_1.eprime deleted file mode 100644 index ed505c7c7d..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_2_4_1.eprime +++ /dev/null @@ -1,121 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitR6_ExplicitVarSizeWithDummy: matrix indexed by [int(1..2), int(1..3)] of int(1..3) -find x_ExplicitR4_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..2), int(1..3)] of bool -find x_ExplicitR4_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..2), int(1..3)] of int(1..2) -find x_ExplicitR2_Occurrence: matrix indexed by [int(1..2), int(1..2)] of bool -branching on - [x_ExplicitR2_Occurrence, x_ExplicitR6_ExplicitVarSizeWithDummy, x_ExplicitR4_ExplicitVarSizeWithFlags_Flags, - x_ExplicitR4_ExplicitVarSizeWithFlags_Values] -such that - [x_ExplicitR6_ExplicitVarSizeWithDummy[1, q7] | q7 : int(1..3)] x_ExplicitR6_ExplicitVarSizeWithDummy[q2, q4 + 1] = 3 - | q4 : int(1..2)]) - | q2 : int(1..2)]), - and([sum([toInt(x_ExplicitR6_ExplicitVarSizeWithDummy[q2, q5] != 3) | q5 : int(1..3)]) <= 3 | q2 : int(1..2)]), - flatten([flatten([[-toInt(x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[1, q16]); int(1)], - [x_ExplicitR4_ExplicitVarSizeWithFlags_Values[1, q16]; int(1)]; - int(1..2)]) - | q16 : int(1..3)]) - - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q10, q11] < - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q10, q11 + 1] - | q11 : int(1..2)]) - | q10 : int(1..2)]), - and([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q10, q12] = false -> - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q10, q12] = 1 - | q12 : int(1..3)]) - | q10 : int(1..2)]), - and([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q10, q13 + 1] -> - x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q10, q13] - | q13 : int(1..2)]) - | q10 : int(1..2)]), - and([sum([toInt(x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q10, q14]) | q14 : int(1..3)]) <= 3 | q10 : int(1..2)]), - and([or([and([x_ExplicitR6_ExplicitVarSizeWithDummy[q21, q23] != 3 -> - or([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q19, q25] /\ - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q19, q25] = - x_ExplicitR6_ExplicitVarSizeWithDummy[q21, q23] - | q25 : int(1..3)]) - | q23 : int(1..3)]) - /\ - and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q19, q27] -> - or([x_ExplicitR6_ExplicitVarSizeWithDummy[q21, q29] != 3 /\ - x_ExplicitR6_ExplicitVarSizeWithDummy[q21, q29] = - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q19, q27] - | q29 : int(1..3)]) - | q27 : int(1..3)]) - | q21 : int(1..2)]) - | q19 : int(1..2)]), - and([or([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q33, q35] -> - or([x_ExplicitR6_ExplicitVarSizeWithDummy[q31, q37] != 3 /\ - x_ExplicitR6_ExplicitVarSizeWithDummy[q31, q37] = - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q33, q35] - | q37 : int(1..3)]) - | q35 : int(1..3)]) - /\ - and([x_ExplicitR6_ExplicitVarSizeWithDummy[q31, q39] != 3 -> - or([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q33, q41] /\ - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q33, q41] = - x_ExplicitR6_ExplicitVarSizeWithDummy[q31, q39] - | q41 : int(1..3)]) - | q39 : int(1..3)]) - | q33 : int(1..2)]) - | q31 : int(1..2)]), - [-toInt(x_ExplicitR2_Occurrence[1, q45]) | q45 : int(1..2)] - x_ExplicitR2_Occurrence[q48, x_ExplicitR6_ExplicitVarSizeWithDummy[q50, q52]] - | q52 : int(1..3)]) - /\ - and([x_ExplicitR2_Occurrence[q48, q53] -> - or([x_ExplicitR6_ExplicitVarSizeWithDummy[q50, q55] != 3 /\ - x_ExplicitR6_ExplicitVarSizeWithDummy[q50, q55] = q53 - | q55 : int(1..3)]) - | q53 : int(1..2)]) - | q50 : int(1..2)]) - | q48 : int(1..2)]), - and([or([and([x_ExplicitR2_Occurrence[q59, q60] -> - or([x_ExplicitR6_ExplicitVarSizeWithDummy[q57, q62] != 3 /\ - x_ExplicitR6_ExplicitVarSizeWithDummy[q57, q62] = q60 - | q62 : int(1..3)]) - | q60 : int(1..2)]) - /\ - and([x_ExplicitR6_ExplicitVarSizeWithDummy[q57, q64] != 3 -> - x_ExplicitR2_Occurrence[q59, x_ExplicitR6_ExplicitVarSizeWithDummy[q57, q64]] - | q64 : int(1..3)]) - | q59 : int(1..2)]) - | q57 : int(1..2)]), - and([or([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q68, q70] -> - x_ExplicitR2_Occurrence[q66, x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q68, q70]] - | q70 : int(1..3)]) - /\ - and([x_ExplicitR2_Occurrence[q66, q71] -> - or([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q68, q73] /\ - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q68, q73] = q71 - | q73 : int(1..3)]) - | q71 : int(1..2)]) - | q68 : int(1..2)]) - | q66 : int(1..2)]), - and([or([and([x_ExplicitR2_Occurrence[q77, q78] -> - or([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q75, q80] /\ - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q75, q80] = q78 - | q80 : int(1..3)]) - | q78 : int(1..2)]) - /\ - and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q75, q82] -> - x_ExplicitR2_Occurrence[q77, x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q75, q82]] - | q82 : int(1..3)]) - | q77 : int(1..2)]) - | q75 : int(1..2)]) - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_2_4_2-solution000001.solution b/tests/exhaustive/basic/setOfSet04/expected/model_2_4_2-solution000001.solution deleted file mode 100644 index 3ec452354e..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_2_4_2-solution000001.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {1}} -$ Visualisation for x -$ -$ 1 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_2_4_2-solution000002.solution b/tests/exhaustive/basic/setOfSet04/expected/model_2_4_2-solution000002.solution deleted file mode 100644 index c8946f3d06..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_2_4_2-solution000002.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {2}} -$ Visualisation for x -$ -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_2_4_2-solution000003.solution b/tests/exhaustive/basic/setOfSet04/expected/model_2_4_2-solution000003.solution deleted file mode 100644 index af16592c51..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_2_4_2-solution000003.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1}, {2}} -$ Visualisation for x -$ 1 -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_2_4_2-solution000004.solution b/tests/exhaustive/basic/setOfSet04/expected/model_2_4_2-solution000004.solution deleted file mode 100644 index a6c0b6a43e..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_2_4_2-solution000004.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {1, 2}} -$ Visualisation for x -$ -$ 1 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_2_4_2-solution000005.solution b/tests/exhaustive/basic/setOfSet04/expected/model_2_4_2-solution000005.solution deleted file mode 100644 index 38937c9389..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_2_4_2-solution000005.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1}, {1, 2}} -$ Visualisation for x -$ 1 -$ 1 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_2_4_2-solution000006.solution b/tests/exhaustive/basic/setOfSet04/expected/model_2_4_2-solution000006.solution deleted file mode 100644 index 9bf2af0712..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_2_4_2-solution000006.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1, 2}, {2}} -$ Visualisation for x -$ 1 2 -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_2_4_2.eprime b/tests/exhaustive/basic/setOfSet04/expected/model_2_4_2.eprime deleted file mode 100644 index 247428fb21..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_2_4_2.eprime +++ /dev/null @@ -1,73 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitR6_ExplicitVarSizeWithDummy: matrix indexed by [int(1..2), int(1..3)] of int(1..3) -find x_ExplicitR4_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..2), int(1..3)] of bool -find x_ExplicitR4_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..2), int(1..3)] of int(1..2) -branching on - [x_ExplicitR4_ExplicitVarSizeWithFlags_Flags, x_ExplicitR4_ExplicitVarSizeWithFlags_Values, - x_ExplicitR6_ExplicitVarSizeWithDummy] -such that - [x_ExplicitR6_ExplicitVarSizeWithDummy[1, q7] | q7 : int(1..3)] x_ExplicitR6_ExplicitVarSizeWithDummy[q2, q4 + 1] = 3 - | q4 : int(1..2)]) - | q2 : int(1..2)]), - and([sum([toInt(x_ExplicitR6_ExplicitVarSizeWithDummy[q2, q5] != 3) | q5 : int(1..3)]) <= 3 | q2 : int(1..2)]), - flatten([flatten([[-toInt(x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[1, q16]); int(1)], - [x_ExplicitR4_ExplicitVarSizeWithFlags_Values[1, q16]; int(1)]; - int(1..2)]) - | q16 : int(1..3)]) - - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q10, q11] < - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q10, q11 + 1] - | q11 : int(1..2)]) - | q10 : int(1..2)]), - and([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q10, q12] = false -> - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q10, q12] = 1 - | q12 : int(1..3)]) - | q10 : int(1..2)]), - and([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q10, q13 + 1] -> - x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q10, q13] - | q13 : int(1..2)]) - | q10 : int(1..2)]), - and([sum([toInt(x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q10, q14]) | q14 : int(1..3)]) <= 3 | q10 : int(1..2)]), - and([or([and([x_ExplicitR6_ExplicitVarSizeWithDummy[q21, q23] != 3 -> - or([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q19, q25] /\ - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q19, q25] = - x_ExplicitR6_ExplicitVarSizeWithDummy[q21, q23] - | q25 : int(1..3)]) - | q23 : int(1..3)]) - /\ - and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q19, q27] -> - or([x_ExplicitR6_ExplicitVarSizeWithDummy[q21, q29] != 3 /\ - x_ExplicitR6_ExplicitVarSizeWithDummy[q21, q29] = - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q19, q27] - | q29 : int(1..3)]) - | q27 : int(1..3)]) - | q21 : int(1..2)]) - | q19 : int(1..2)]), - and([or([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q33, q35] -> - or([x_ExplicitR6_ExplicitVarSizeWithDummy[q31, q37] != 3 /\ - x_ExplicitR6_ExplicitVarSizeWithDummy[q31, q37] = - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q33, q35] - | q37 : int(1..3)]) - | q35 : int(1..3)]) - /\ - and([x_ExplicitR6_ExplicitVarSizeWithDummy[q31, q39] != 3 -> - or([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q33, q41] /\ - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q33, q41] = - x_ExplicitR6_ExplicitVarSizeWithDummy[q31, q39] - | q41 : int(1..3)]) - | q39 : int(1..3)]) - | q33 : int(1..2)]) - | q31 : int(1..2)]) - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_2_4_3-solution000001.solution b/tests/exhaustive/basic/setOfSet04/expected/model_2_4_3-solution000001.solution deleted file mode 100644 index 3ec452354e..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_2_4_3-solution000001.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {1}} -$ Visualisation for x -$ -$ 1 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_2_4_3-solution000002.solution b/tests/exhaustive/basic/setOfSet04/expected/model_2_4_3-solution000002.solution deleted file mode 100644 index c8946f3d06..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_2_4_3-solution000002.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {2}} -$ Visualisation for x -$ -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_2_4_3-solution000003.solution b/tests/exhaustive/basic/setOfSet04/expected/model_2_4_3-solution000003.solution deleted file mode 100644 index a6c0b6a43e..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_2_4_3-solution000003.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {1, 2}} -$ Visualisation for x -$ -$ 1 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_2_4_3-solution000004.solution b/tests/exhaustive/basic/setOfSet04/expected/model_2_4_3-solution000004.solution deleted file mode 100644 index af16592c51..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_2_4_3-solution000004.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1}, {2}} -$ Visualisation for x -$ 1 -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_2_4_3-solution000005.solution b/tests/exhaustive/basic/setOfSet04/expected/model_2_4_3-solution000005.solution deleted file mode 100644 index 38937c9389..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_2_4_3-solution000005.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1}, {1, 2}} -$ Visualisation for x -$ 1 -$ 1 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_2_4_3-solution000006.solution b/tests/exhaustive/basic/setOfSet04/expected/model_2_4_3-solution000006.solution deleted file mode 100644 index 9bf2af0712..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_2_4_3-solution000006.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1, 2}, {2}} -$ Visualisation for x -$ 1 2 -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_2_4_3.eprime b/tests/exhaustive/basic/setOfSet04/expected/model_2_4_3.eprime deleted file mode 100644 index 0e0a70ce69..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_2_4_3.eprime +++ /dev/null @@ -1,153 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitR6_ExplicitVarSizeWithDummy: matrix indexed by [int(1..2), int(1..3)] of int(1..3) -find x_ExplicitR4_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..2), int(1..3)] of bool -find x_ExplicitR4_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..2), int(1..3)] of int(1..2) -find x_ExplicitR5_ExplicitVarSizeWithMarker_Marker: matrix indexed by [int(1..2)] of int(0..3) -find x_ExplicitR5_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..2), int(1..3)] of int(1..2) -branching on - [x_ExplicitR5_ExplicitVarSizeWithMarker_Marker, x_ExplicitR5_ExplicitVarSizeWithMarker_Values, - x_ExplicitR6_ExplicitVarSizeWithDummy, x_ExplicitR4_ExplicitVarSizeWithFlags_Flags, - x_ExplicitR4_ExplicitVarSizeWithFlags_Values] -such that - [x_ExplicitR6_ExplicitVarSizeWithDummy[1, q7] | q7 : int(1..3)] x_ExplicitR6_ExplicitVarSizeWithDummy[q2, q4 + 1] = 3 - | q4 : int(1..2)]) - | q2 : int(1..2)]), - and([sum([toInt(x_ExplicitR6_ExplicitVarSizeWithDummy[q2, q5] != 3) | q5 : int(1..3)]) <= 3 | q2 : int(1..2)]), - flatten([flatten([[-toInt(x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[1, q16]); int(1)], - [x_ExplicitR4_ExplicitVarSizeWithFlags_Values[1, q16]; int(1)]; - int(1..2)]) - | q16 : int(1..3)]) - - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q10, q11] < - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q10, q11 + 1] - | q11 : int(1..2)]) - | q10 : int(1..2)]), - and([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q10, q12] = false -> - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q10, q12] = 1 - | q12 : int(1..3)]) - | q10 : int(1..2)]), - and([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q10, q13 + 1] -> - x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q10, q13] - | q13 : int(1..2)]) - | q10 : int(1..2)]), - and([sum([toInt(x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q10, q14]) | q14 : int(1..3)]) <= 3 | q10 : int(1..2)]), - and([or([and([x_ExplicitR6_ExplicitVarSizeWithDummy[q21, q23] != 3 -> - or([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q19, q25] /\ - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q19, q25] = - x_ExplicitR6_ExplicitVarSizeWithDummy[q21, q23] - | q25 : int(1..3)]) - | q23 : int(1..3)]) - /\ - and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q19, q27] -> - or([x_ExplicitR6_ExplicitVarSizeWithDummy[q21, q29] != 3 /\ - x_ExplicitR6_ExplicitVarSizeWithDummy[q21, q29] = - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q19, q27] - | q29 : int(1..3)]) - | q27 : int(1..3)]) - | q21 : int(1..2)]) - | q19 : int(1..2)]), - and([or([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q33, q35] -> - or([x_ExplicitR6_ExplicitVarSizeWithDummy[q31, q37] != 3 /\ - x_ExplicitR6_ExplicitVarSizeWithDummy[q31, q37] = - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q33, q35] - | q37 : int(1..3)]) - | q35 : int(1..3)]) - /\ - and([x_ExplicitR6_ExplicitVarSizeWithDummy[q31, q39] != 3 -> - or([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q33, q41] /\ - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q33, q41] = - x_ExplicitR6_ExplicitVarSizeWithDummy[q31, q39] - | q41 : int(1..3)]) - | q39 : int(1..3)]) - | q33 : int(1..2)]) - | q31 : int(1..2)]), - flatten([[x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[1]; int(1)], - flatten([[x_ExplicitR5_ExplicitVarSizeWithMarker_Values[1, q47]; int(1)] | q47 : int(1..3)]); - int(1..2)]) - - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q43, q44] < - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q43, q44 + 1] - | q44 : int(1..2)]) - | q43 : int(1..2)]), - and([and([q45 > x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q43] -> - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q43, q45] = 1 - | q45 : int(1..3)]) - | q43 : int(1..2)]), - and([x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q43] <= 3 | q43 : int(1..2)]), - and([or([and([x_ExplicitR6_ExplicitVarSizeWithDummy[q52, q54] != 3 -> - or([q56 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q50] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q50, q56] = - x_ExplicitR6_ExplicitVarSizeWithDummy[q52, q54] - | q56 : int(1..3)]) - | q54 : int(1..3)]) - /\ - and([q58 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q50] -> - or([x_ExplicitR6_ExplicitVarSizeWithDummy[q52, q60] != 3 /\ - x_ExplicitR6_ExplicitVarSizeWithDummy[q52, q60] = - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q50, q58] - | q60 : int(1..3)]) - | q58 : int(1..3)]) - | q52 : int(1..2)]) - | q50 : int(1..2)]), - and([or([and([q66 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q64] -> - or([x_ExplicitR6_ExplicitVarSizeWithDummy[q62, q68] != 3 /\ - x_ExplicitR6_ExplicitVarSizeWithDummy[q62, q68] = - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q64, q66] - | q68 : int(1..3)]) - | q66 : int(1..3)]) - /\ - and([x_ExplicitR6_ExplicitVarSizeWithDummy[q62, q70] != 3 -> - or([q72 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q64] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q64, q72] = - x_ExplicitR6_ExplicitVarSizeWithDummy[q62, q70] - | q72 : int(1..3)]) - | q70 : int(1..3)]) - | q64 : int(1..2)]) - | q62 : int(1..2)]), - and([or([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q76, q78] -> - or([q80 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q74] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q74, q80] = - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q76, q78] - | q80 : int(1..3)]) - | q78 : int(1..3)]) - /\ - and([q82 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q74] -> - or([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q76, q84] /\ - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q76, q84] = - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q74, q82] - | q84 : int(1..3)]) - | q82 : int(1..3)]) - | q76 : int(1..2)]) - | q74 : int(1..2)]), - and([or([and([q90 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q88] -> - or([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q86, q92] /\ - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q86, q92] = - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q88, q90] - | q92 : int(1..3)]) - | q90 : int(1..3)]) - /\ - and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q86, q94] -> - or([q96 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q88] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q88, q96] = - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q86, q94] - | q96 : int(1..3)]) - | q94 : int(1..3)]) - | q88 : int(1..2)]) - | q86 : int(1..2)]) - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_2_4_4-solution000001.solution b/tests/exhaustive/basic/setOfSet04/expected/model_2_4_4-solution000001.solution deleted file mode 100644 index 3ec452354e..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_2_4_4-solution000001.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {1}} -$ Visualisation for x -$ -$ 1 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_2_4_4-solution000002.solution b/tests/exhaustive/basic/setOfSet04/expected/model_2_4_4-solution000002.solution deleted file mode 100644 index c8946f3d06..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_2_4_4-solution000002.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {2}} -$ Visualisation for x -$ -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_2_4_4-solution000003.solution b/tests/exhaustive/basic/setOfSet04/expected/model_2_4_4-solution000003.solution deleted file mode 100644 index af16592c51..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_2_4_4-solution000003.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1}, {2}} -$ Visualisation for x -$ 1 -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_2_4_4-solution000004.solution b/tests/exhaustive/basic/setOfSet04/expected/model_2_4_4-solution000004.solution deleted file mode 100644 index a6c0b6a43e..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_2_4_4-solution000004.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {1, 2}} -$ Visualisation for x -$ -$ 1 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_2_4_4-solution000005.solution b/tests/exhaustive/basic/setOfSet04/expected/model_2_4_4-solution000005.solution deleted file mode 100644 index 38937c9389..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_2_4_4-solution000005.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1}, {1, 2}} -$ Visualisation for x -$ 1 -$ 1 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_2_4_4-solution000006.solution b/tests/exhaustive/basic/setOfSet04/expected/model_2_4_4-solution000006.solution deleted file mode 100644 index 9bf2af0712..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_2_4_4-solution000006.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1, 2}, {2}} -$ Visualisation for x -$ 1 2 -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_2_4_4.eprime b/tests/exhaustive/basic/setOfSet04/expected/model_2_4_4.eprime deleted file mode 100644 index 247428fb21..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_2_4_4.eprime +++ /dev/null @@ -1,73 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitR6_ExplicitVarSizeWithDummy: matrix indexed by [int(1..2), int(1..3)] of int(1..3) -find x_ExplicitR4_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..2), int(1..3)] of bool -find x_ExplicitR4_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..2), int(1..3)] of int(1..2) -branching on - [x_ExplicitR4_ExplicitVarSizeWithFlags_Flags, x_ExplicitR4_ExplicitVarSizeWithFlags_Values, - x_ExplicitR6_ExplicitVarSizeWithDummy] -such that - [x_ExplicitR6_ExplicitVarSizeWithDummy[1, q7] | q7 : int(1..3)] x_ExplicitR6_ExplicitVarSizeWithDummy[q2, q4 + 1] = 3 - | q4 : int(1..2)]) - | q2 : int(1..2)]), - and([sum([toInt(x_ExplicitR6_ExplicitVarSizeWithDummy[q2, q5] != 3) | q5 : int(1..3)]) <= 3 | q2 : int(1..2)]), - flatten([flatten([[-toInt(x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[1, q16]); int(1)], - [x_ExplicitR4_ExplicitVarSizeWithFlags_Values[1, q16]; int(1)]; - int(1..2)]) - | q16 : int(1..3)]) - - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q10, q11] < - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q10, q11 + 1] - | q11 : int(1..2)]) - | q10 : int(1..2)]), - and([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q10, q12] = false -> - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q10, q12] = 1 - | q12 : int(1..3)]) - | q10 : int(1..2)]), - and([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q10, q13 + 1] -> - x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q10, q13] - | q13 : int(1..2)]) - | q10 : int(1..2)]), - and([sum([toInt(x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q10, q14]) | q14 : int(1..3)]) <= 3 | q10 : int(1..2)]), - and([or([and([x_ExplicitR6_ExplicitVarSizeWithDummy[q21, q23] != 3 -> - or([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q19, q25] /\ - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q19, q25] = - x_ExplicitR6_ExplicitVarSizeWithDummy[q21, q23] - | q25 : int(1..3)]) - | q23 : int(1..3)]) - /\ - and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q19, q27] -> - or([x_ExplicitR6_ExplicitVarSizeWithDummy[q21, q29] != 3 /\ - x_ExplicitR6_ExplicitVarSizeWithDummy[q21, q29] = - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q19, q27] - | q29 : int(1..3)]) - | q27 : int(1..3)]) - | q21 : int(1..2)]) - | q19 : int(1..2)]), - and([or([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q33, q35] -> - or([x_ExplicitR6_ExplicitVarSizeWithDummy[q31, q37] != 3 /\ - x_ExplicitR6_ExplicitVarSizeWithDummy[q31, q37] = - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q33, q35] - | q37 : int(1..3)]) - | q35 : int(1..3)]) - /\ - and([x_ExplicitR6_ExplicitVarSizeWithDummy[q31, q39] != 3 -> - or([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q33, q41] /\ - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q33, q41] = - x_ExplicitR6_ExplicitVarSizeWithDummy[q31, q39] - | q41 : int(1..3)]) - | q39 : int(1..3)]) - | q33 : int(1..2)]) - | q31 : int(1..2)]) - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_3_1_1-solution000001.solution b/tests/exhaustive/basic/setOfSet04/expected/model_3_1_1-solution000001.solution deleted file mode 100644 index c8946f3d06..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_3_1_1-solution000001.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {2}} -$ Visualisation for x -$ -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_3_1_1-solution000002.solution b/tests/exhaustive/basic/setOfSet04/expected/model_3_1_1-solution000002.solution deleted file mode 100644 index 3ec452354e..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_3_1_1-solution000002.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {1}} -$ Visualisation for x -$ -$ 1 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_3_1_1-solution000003.solution b/tests/exhaustive/basic/setOfSet04/expected/model_3_1_1-solution000003.solution deleted file mode 100644 index af16592c51..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_3_1_1-solution000003.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1}, {2}} -$ Visualisation for x -$ 1 -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_3_1_1-solution000004.solution b/tests/exhaustive/basic/setOfSet04/expected/model_3_1_1-solution000004.solution deleted file mode 100644 index a6c0b6a43e..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_3_1_1-solution000004.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {1, 2}} -$ Visualisation for x -$ -$ 1 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_3_1_1-solution000005.solution b/tests/exhaustive/basic/setOfSet04/expected/model_3_1_1-solution000005.solution deleted file mode 100644 index 9bf2af0712..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_3_1_1-solution000005.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1, 2}, {2}} -$ Visualisation for x -$ 1 2 -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_3_1_1-solution000006.solution b/tests/exhaustive/basic/setOfSet04/expected/model_3_1_1-solution000006.solution deleted file mode 100644 index 38937c9389..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_3_1_1-solution000006.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1}, {1, 2}} -$ Visualisation for x -$ 1 -$ 1 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_3_1_1.eprime b/tests/exhaustive/basic/setOfSet04/expected/model_3_1_1.eprime deleted file mode 100644 index e420029404..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_3_1_1.eprime +++ /dev/null @@ -1,52 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitR5_ExplicitVarSizeWithMarker_Marker: matrix indexed by [int(1..2)] of int(0..3) -find x_ExplicitR5_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..2), int(1..3)] of int(1..2) -find x_ExplicitR2_Occurrence: matrix indexed by [int(1..2), int(1..2)] of bool -branching on - [x_ExplicitR2_Occurrence, x_ExplicitR5_ExplicitVarSizeWithMarker_Marker, - x_ExplicitR5_ExplicitVarSizeWithMarker_Values] -such that - flatten([[x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[1]; int(1)], - flatten([[x_ExplicitR5_ExplicitVarSizeWithMarker_Values[1, q6]; int(1)] | q6 : int(1..3)]); - int(1..2)]) - - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q2, q3] < - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q2, q3 + 1] - | q3 : int(1..2)]) - | q2 : int(1..2)]), - and([and([q4 > x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q2] -> - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q2, q4] = 1 - | q4 : int(1..3)]) - | q2 : int(1..2)]), - and([x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q2] <= 3 | q2 : int(1..2)]), - [-toInt(x_ExplicitR2_Occurrence[1, q11]) | q11 : int(1..2)] - x_ExplicitR2_Occurrence[q14, x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q16, q18]] - | q18 : int(1..3)]) - /\ - and([x_ExplicitR2_Occurrence[q14, q19] -> - or([q21 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q16] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q16, q21] = q19 - | q21 : int(1..3)]) - | q19 : int(1..2)]) - | q16 : int(1..2)]) - | q14 : int(1..2)]), - and([or([and([x_ExplicitR2_Occurrence[q25, q26] -> - or([q28 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q23] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q23, q28] = q26 - | q28 : int(1..3)]) - | q26 : int(1..2)]) - /\ - and([q30 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q23] -> - x_ExplicitR2_Occurrence[q25, x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q23, q30]] - | q30 : int(1..3)]) - | q25 : int(1..2)]) - | q23 : int(1..2)]) - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_3_1_2-solution000001.solution b/tests/exhaustive/basic/setOfSet04/expected/model_3_1_2-solution000001.solution deleted file mode 100644 index 38937c9389..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_3_1_2-solution000001.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1}, {1, 2}} -$ Visualisation for x -$ 1 -$ 1 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_3_1_2-solution000002.solution b/tests/exhaustive/basic/setOfSet04/expected/model_3_1_2-solution000002.solution deleted file mode 100644 index 9bf2af0712..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_3_1_2-solution000002.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1, 2}, {2}} -$ Visualisation for x -$ 1 2 -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_3_1_2-solution000003.solution b/tests/exhaustive/basic/setOfSet04/expected/model_3_1_2-solution000003.solution deleted file mode 100644 index a6c0b6a43e..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_3_1_2-solution000003.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {1, 2}} -$ Visualisation for x -$ -$ 1 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_3_1_2-solution000004.solution b/tests/exhaustive/basic/setOfSet04/expected/model_3_1_2-solution000004.solution deleted file mode 100644 index af16592c51..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_3_1_2-solution000004.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1}, {2}} -$ Visualisation for x -$ 1 -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_3_1_2-solution000005.solution b/tests/exhaustive/basic/setOfSet04/expected/model_3_1_2-solution000005.solution deleted file mode 100644 index 3ec452354e..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_3_1_2-solution000005.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {1}} -$ Visualisation for x -$ -$ 1 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_3_1_2-solution000006.solution b/tests/exhaustive/basic/setOfSet04/expected/model_3_1_2-solution000006.solution deleted file mode 100644 index c8946f3d06..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_3_1_2-solution000006.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {2}} -$ Visualisation for x -$ -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_3_1_2.eprime b/tests/exhaustive/basic/setOfSet04/expected/model_3_1_2.eprime deleted file mode 100644 index 526ee1c02c..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_3_1_2.eprime +++ /dev/null @@ -1,116 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitR5_ExplicitVarSizeWithMarker_Marker: matrix indexed by [int(1..2)] of int(0..3) -find x_ExplicitR5_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..2), int(1..3)] of int(1..2) -find x_ExplicitR2_Occurrence: matrix indexed by [int(1..2), int(1..2)] of bool -find x_ExplicitR6_ExplicitVarSizeWithDummy: matrix indexed by [int(1..2), int(1..3)] of int(1..3) -branching on - [x_ExplicitR6_ExplicitVarSizeWithDummy, x_ExplicitR5_ExplicitVarSizeWithMarker_Marker, - x_ExplicitR5_ExplicitVarSizeWithMarker_Values, x_ExplicitR2_Occurrence] -such that - flatten([[x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[1]; int(1)], - flatten([[x_ExplicitR5_ExplicitVarSizeWithMarker_Values[1, q6]; int(1)] | q6 : int(1..3)]); - int(1..2)]) - - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q2, q3] < - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q2, q3 + 1] - | q3 : int(1..2)]) - | q2 : int(1..2)]), - and([and([q4 > x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q2] -> - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q2, q4] = 1 - | q4 : int(1..3)]) - | q2 : int(1..2)]), - and([x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q2] <= 3 | q2 : int(1..2)]), - [-toInt(x_ExplicitR2_Occurrence[1, q11]) | q11 : int(1..2)] - x_ExplicitR2_Occurrence[q14, x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q16, q18]] - | q18 : int(1..3)]) - /\ - and([x_ExplicitR2_Occurrence[q14, q19] -> - or([q21 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q16] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q16, q21] = q19 - | q21 : int(1..3)]) - | q19 : int(1..2)]) - | q16 : int(1..2)]) - | q14 : int(1..2)]), - and([or([and([x_ExplicitR2_Occurrence[q25, q26] -> - or([q28 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q23] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q23, q28] = q26 - | q28 : int(1..3)]) - | q26 : int(1..2)]) - /\ - and([q30 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q23] -> - x_ExplicitR2_Occurrence[q25, x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q23, q30]] - | q30 : int(1..3)]) - | q25 : int(1..2)]) - | q23 : int(1..2)]), - [x_ExplicitR6_ExplicitVarSizeWithDummy[1, q37] | q37 : int(1..3)] - x_ExplicitR6_ExplicitVarSizeWithDummy[q32, q34 + 1] = 3 - | q34 : int(1..2)]) - | q32 : int(1..2)]), - and([sum([toInt(x_ExplicitR6_ExplicitVarSizeWithDummy[q32, q35] != 3) | q35 : int(1..3)]) <= 3 | q32 : int(1..2)]), - and([or([and([q44 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q42] -> - or([x_ExplicitR6_ExplicitVarSizeWithDummy[q40, q46] != 3 /\ - x_ExplicitR6_ExplicitVarSizeWithDummy[q40, q46] = - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q42, q44] - | q46 : int(1..3)]) - | q44 : int(1..3)]) - /\ - and([x_ExplicitR6_ExplicitVarSizeWithDummy[q40, q48] != 3 -> - or([q50 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q42] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q42, q50] = - x_ExplicitR6_ExplicitVarSizeWithDummy[q40, q48] - | q50 : int(1..3)]) - | q48 : int(1..3)]) - | q42 : int(1..2)]) - | q40 : int(1..2)]), - and([or([and([x_ExplicitR6_ExplicitVarSizeWithDummy[q54, q56] != 3 -> - or([q58 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q52] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q52, q58] = - x_ExplicitR6_ExplicitVarSizeWithDummy[q54, q56] - | q58 : int(1..3)]) - | q56 : int(1..3)]) - /\ - and([q60 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q52] -> - or([x_ExplicitR6_ExplicitVarSizeWithDummy[q54, q62] != 3 /\ - x_ExplicitR6_ExplicitVarSizeWithDummy[q54, q62] = - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q52, q60] - | q62 : int(1..3)]) - | q60 : int(1..3)]) - | q54 : int(1..2)]) - | q52 : int(1..2)]), - and([or([and([x_ExplicitR2_Occurrence[q66, q67] -> - or([x_ExplicitR6_ExplicitVarSizeWithDummy[q64, q69] != 3 /\ - x_ExplicitR6_ExplicitVarSizeWithDummy[q64, q69] = q67 - | q69 : int(1..3)]) - | q67 : int(1..2)]) - /\ - and([x_ExplicitR6_ExplicitVarSizeWithDummy[q64, q71] != 3 -> - x_ExplicitR2_Occurrence[q66, x_ExplicitR6_ExplicitVarSizeWithDummy[q64, q71]] - | q71 : int(1..3)]) - | q66 : int(1..2)]) - | q64 : int(1..2)]), - and([or([and([x_ExplicitR6_ExplicitVarSizeWithDummy[q75, q77] != 3 -> - x_ExplicitR2_Occurrence[q73, x_ExplicitR6_ExplicitVarSizeWithDummy[q75, q77]] - | q77 : int(1..3)]) - /\ - and([x_ExplicitR2_Occurrence[q73, q78] -> - or([x_ExplicitR6_ExplicitVarSizeWithDummy[q75, q80] != 3 /\ - x_ExplicitR6_ExplicitVarSizeWithDummy[q75, q80] = q78 - | q80 : int(1..3)]) - | q78 : int(1..2)]) - | q75 : int(1..2)]) - | q73 : int(1..2)]) - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_3_1_3-solution000001.solution b/tests/exhaustive/basic/setOfSet04/expected/model_3_1_3-solution000001.solution deleted file mode 100644 index c8946f3d06..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_3_1_3-solution000001.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {2}} -$ Visualisation for x -$ -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_3_1_3-solution000002.solution b/tests/exhaustive/basic/setOfSet04/expected/model_3_1_3-solution000002.solution deleted file mode 100644 index 3ec452354e..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_3_1_3-solution000002.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {1}} -$ Visualisation for x -$ -$ 1 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_3_1_3-solution000003.solution b/tests/exhaustive/basic/setOfSet04/expected/model_3_1_3-solution000003.solution deleted file mode 100644 index af16592c51..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_3_1_3-solution000003.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1}, {2}} -$ Visualisation for x -$ 1 -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_3_1_3-solution000004.solution b/tests/exhaustive/basic/setOfSet04/expected/model_3_1_3-solution000004.solution deleted file mode 100644 index a6c0b6a43e..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_3_1_3-solution000004.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {1, 2}} -$ Visualisation for x -$ -$ 1 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_3_1_3-solution000005.solution b/tests/exhaustive/basic/setOfSet04/expected/model_3_1_3-solution000005.solution deleted file mode 100644 index 9bf2af0712..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_3_1_3-solution000005.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1, 2}, {2}} -$ Visualisation for x -$ 1 2 -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_3_1_3-solution000006.solution b/tests/exhaustive/basic/setOfSet04/expected/model_3_1_3-solution000006.solution deleted file mode 100644 index 38937c9389..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_3_1_3-solution000006.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1}, {1, 2}} -$ Visualisation for x -$ 1 -$ 1 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_3_1_3.eprime b/tests/exhaustive/basic/setOfSet04/expected/model_3_1_3.eprime deleted file mode 100644 index e420029404..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_3_1_3.eprime +++ /dev/null @@ -1,52 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitR5_ExplicitVarSizeWithMarker_Marker: matrix indexed by [int(1..2)] of int(0..3) -find x_ExplicitR5_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..2), int(1..3)] of int(1..2) -find x_ExplicitR2_Occurrence: matrix indexed by [int(1..2), int(1..2)] of bool -branching on - [x_ExplicitR2_Occurrence, x_ExplicitR5_ExplicitVarSizeWithMarker_Marker, - x_ExplicitR5_ExplicitVarSizeWithMarker_Values] -such that - flatten([[x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[1]; int(1)], - flatten([[x_ExplicitR5_ExplicitVarSizeWithMarker_Values[1, q6]; int(1)] | q6 : int(1..3)]); - int(1..2)]) - - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q2, q3] < - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q2, q3 + 1] - | q3 : int(1..2)]) - | q2 : int(1..2)]), - and([and([q4 > x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q2] -> - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q2, q4] = 1 - | q4 : int(1..3)]) - | q2 : int(1..2)]), - and([x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q2] <= 3 | q2 : int(1..2)]), - [-toInt(x_ExplicitR2_Occurrence[1, q11]) | q11 : int(1..2)] - x_ExplicitR2_Occurrence[q14, x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q16, q18]] - | q18 : int(1..3)]) - /\ - and([x_ExplicitR2_Occurrence[q14, q19] -> - or([q21 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q16] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q16, q21] = q19 - | q21 : int(1..3)]) - | q19 : int(1..2)]) - | q16 : int(1..2)]) - | q14 : int(1..2)]), - and([or([and([x_ExplicitR2_Occurrence[q25, q26] -> - or([q28 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q23] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q23, q28] = q26 - | q28 : int(1..3)]) - | q26 : int(1..2)]) - /\ - and([q30 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q23] -> - x_ExplicitR2_Occurrence[q25, x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q23, q30]] - | q30 : int(1..3)]) - | q25 : int(1..2)]) - | q23 : int(1..2)]) - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_3_1_4-solution000001.solution b/tests/exhaustive/basic/setOfSet04/expected/model_3_1_4-solution000001.solution deleted file mode 100644 index 3ec452354e..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_3_1_4-solution000001.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {1}} -$ Visualisation for x -$ -$ 1 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_3_1_4-solution000002.solution b/tests/exhaustive/basic/setOfSet04/expected/model_3_1_4-solution000002.solution deleted file mode 100644 index c8946f3d06..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_3_1_4-solution000002.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {2}} -$ Visualisation for x -$ -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_3_1_4-solution000003.solution b/tests/exhaustive/basic/setOfSet04/expected/model_3_1_4-solution000003.solution deleted file mode 100644 index af16592c51..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_3_1_4-solution000003.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1}, {2}} -$ Visualisation for x -$ 1 -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_3_1_4-solution000004.solution b/tests/exhaustive/basic/setOfSet04/expected/model_3_1_4-solution000004.solution deleted file mode 100644 index a6c0b6a43e..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_3_1_4-solution000004.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {1, 2}} -$ Visualisation for x -$ -$ 1 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_3_1_4-solution000005.solution b/tests/exhaustive/basic/setOfSet04/expected/model_3_1_4-solution000005.solution deleted file mode 100644 index 38937c9389..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_3_1_4-solution000005.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1}, {1, 2}} -$ Visualisation for x -$ 1 -$ 1 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_3_1_4-solution000006.solution b/tests/exhaustive/basic/setOfSet04/expected/model_3_1_4-solution000006.solution deleted file mode 100644 index 9bf2af0712..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_3_1_4-solution000006.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1, 2}, {2}} -$ Visualisation for x -$ 1 2 -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_3_1_4.eprime b/tests/exhaustive/basic/setOfSet04/expected/model_3_1_4.eprime deleted file mode 100644 index d149dc0309..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_3_1_4.eprime +++ /dev/null @@ -1,130 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitR5_ExplicitVarSizeWithMarker_Marker: matrix indexed by [int(1..2)] of int(0..3) -find x_ExplicitR5_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..2), int(1..3)] of int(1..2) -find x_ExplicitR2_Occurrence: matrix indexed by [int(1..2), int(1..2)] of bool -find x_ExplicitR4_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..2), int(1..3)] of bool -find x_ExplicitR4_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..2), int(1..3)] of int(1..2) -branching on - [x_ExplicitR4_ExplicitVarSizeWithFlags_Flags, x_ExplicitR4_ExplicitVarSizeWithFlags_Values, - x_ExplicitR5_ExplicitVarSizeWithMarker_Marker, x_ExplicitR5_ExplicitVarSizeWithMarker_Values, - x_ExplicitR2_Occurrence] -such that - flatten([[x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[1]; int(1)], - flatten([[x_ExplicitR5_ExplicitVarSizeWithMarker_Values[1, q6]; int(1)] | q6 : int(1..3)]); - int(1..2)]) - - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q2, q3] < - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q2, q3 + 1] - | q3 : int(1..2)]) - | q2 : int(1..2)]), - and([and([q4 > x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q2] -> - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q2, q4] = 1 - | q4 : int(1..3)]) - | q2 : int(1..2)]), - and([x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q2] <= 3 | q2 : int(1..2)]), - [-toInt(x_ExplicitR2_Occurrence[1, q11]) | q11 : int(1..2)] - x_ExplicitR2_Occurrence[q14, x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q16, q18]] - | q18 : int(1..3)]) - /\ - and([x_ExplicitR2_Occurrence[q14, q19] -> - or([q21 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q16] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q16, q21] = q19 - | q21 : int(1..3)]) - | q19 : int(1..2)]) - | q16 : int(1..2)]) - | q14 : int(1..2)]), - and([or([and([x_ExplicitR2_Occurrence[q25, q26] -> - or([q28 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q23] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q23, q28] = q26 - | q28 : int(1..3)]) - | q26 : int(1..2)]) - /\ - and([q30 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q23] -> - x_ExplicitR2_Occurrence[q25, x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q23, q30]] - | q30 : int(1..3)]) - | q25 : int(1..2)]) - | q23 : int(1..2)]), - flatten([flatten([[-toInt(x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[1, q38]); int(1)], - [x_ExplicitR4_ExplicitVarSizeWithFlags_Values[1, q38]; int(1)]; - int(1..2)]) - | q38 : int(1..3)]) - - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q32, q33] < - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q32, q33 + 1] - | q33 : int(1..2)]) - | q32 : int(1..2)]), - and([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q32, q34] = false -> - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q32, q34] = 1 - | q34 : int(1..3)]) - | q32 : int(1..2)]), - and([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q32, q35 + 1] -> - x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q32, q35] - | q35 : int(1..2)]) - | q32 : int(1..2)]), - and([sum([toInt(x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q32, q36]) | q36 : int(1..3)]) <= 3 | q32 : int(1..2)]), - and([or([and([q45 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q43] -> - or([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q41, q47] /\ - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q41, q47] = - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q43, q45] - | q47 : int(1..3)]) - | q45 : int(1..3)]) - /\ - and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q41, q49] -> - or([q51 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q43] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q43, q51] = - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q41, q49] - | q51 : int(1..3)]) - | q49 : int(1..3)]) - | q43 : int(1..2)]) - | q41 : int(1..2)]), - and([or([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q55, q57] -> - or([q59 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q53] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q53, q59] = - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q55, q57] - | q59 : int(1..3)]) - | q57 : int(1..3)]) - /\ - and([q61 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q53] -> - or([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q55, q63] /\ - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q55, q63] = - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q53, q61] - | q63 : int(1..3)]) - | q61 : int(1..3)]) - | q55 : int(1..2)]) - | q53 : int(1..2)]), - and([or([and([x_ExplicitR2_Occurrence[q67, q68] -> - or([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q65, q70] /\ - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q65, q70] = q68 - | q70 : int(1..3)]) - | q68 : int(1..2)]) - /\ - and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q65, q72] -> - x_ExplicitR2_Occurrence[q67, x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q65, q72]] - | q72 : int(1..3)]) - | q67 : int(1..2)]) - | q65 : int(1..2)]), - and([or([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q76, q78] -> - x_ExplicitR2_Occurrence[q74, x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q76, q78]] - | q78 : int(1..3)]) - /\ - and([x_ExplicitR2_Occurrence[q74, q79] -> - or([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q76, q81] /\ - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q76, q81] = q79 - | q81 : int(1..3)]) - | q79 : int(1..2)]) - | q76 : int(1..2)]) - | q74 : int(1..2)]) - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_3_2_1-solution000001.solution b/tests/exhaustive/basic/setOfSet04/expected/model_3_2_1-solution000001.solution deleted file mode 100644 index c8946f3d06..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_3_2_1-solution000001.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {2}} -$ Visualisation for x -$ -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_3_2_1-solution000002.solution b/tests/exhaustive/basic/setOfSet04/expected/model_3_2_1-solution000002.solution deleted file mode 100644 index 3ec452354e..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_3_2_1-solution000002.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {1}} -$ Visualisation for x -$ -$ 1 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_3_2_1-solution000003.solution b/tests/exhaustive/basic/setOfSet04/expected/model_3_2_1-solution000003.solution deleted file mode 100644 index af16592c51..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_3_2_1-solution000003.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1}, {2}} -$ Visualisation for x -$ 1 -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_3_2_1-solution000004.solution b/tests/exhaustive/basic/setOfSet04/expected/model_3_2_1-solution000004.solution deleted file mode 100644 index a6c0b6a43e..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_3_2_1-solution000004.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {1, 2}} -$ Visualisation for x -$ -$ 1 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_3_2_1-solution000005.solution b/tests/exhaustive/basic/setOfSet04/expected/model_3_2_1-solution000005.solution deleted file mode 100644 index 9bf2af0712..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_3_2_1-solution000005.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1, 2}, {2}} -$ Visualisation for x -$ 1 2 -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_3_2_1-solution000006.solution b/tests/exhaustive/basic/setOfSet04/expected/model_3_2_1-solution000006.solution deleted file mode 100644 index 38937c9389..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_3_2_1-solution000006.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1}, {1, 2}} -$ Visualisation for x -$ 1 -$ 1 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_3_2_1.eprime b/tests/exhaustive/basic/setOfSet04/expected/model_3_2_1.eprime deleted file mode 100644 index 18a2b1cf15..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_3_2_1.eprime +++ /dev/null @@ -1,116 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitR5_ExplicitVarSizeWithMarker_Marker: matrix indexed by [int(1..2)] of int(0..3) -find x_ExplicitR5_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..2), int(1..3)] of int(1..2) -find x_ExplicitR6_ExplicitVarSizeWithDummy: matrix indexed by [int(1..2), int(1..3)] of int(1..3) -find x_ExplicitR2_Occurrence: matrix indexed by [int(1..2), int(1..2)] of bool -branching on - [x_ExplicitR2_Occurrence, x_ExplicitR5_ExplicitVarSizeWithMarker_Marker, - x_ExplicitR5_ExplicitVarSizeWithMarker_Values, x_ExplicitR6_ExplicitVarSizeWithDummy] -such that - flatten([[x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[1]; int(1)], - flatten([[x_ExplicitR5_ExplicitVarSizeWithMarker_Values[1, q6]; int(1)] | q6 : int(1..3)]); - int(1..2)]) - - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q2, q3] < - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q2, q3 + 1] - | q3 : int(1..2)]) - | q2 : int(1..2)]), - and([and([q4 > x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q2] -> - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q2, q4] = 1 - | q4 : int(1..3)]) - | q2 : int(1..2)]), - and([x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q2] <= 3 | q2 : int(1..2)]), - [x_ExplicitR6_ExplicitVarSizeWithDummy[1, q14] | q14 : int(1..3)] - x_ExplicitR6_ExplicitVarSizeWithDummy[q9, q11 + 1] = 3 - | q11 : int(1..2)]) - | q9 : int(1..2)]), - and([sum([toInt(x_ExplicitR6_ExplicitVarSizeWithDummy[q9, q12] != 3) | q12 : int(1..3)]) <= 3 | q9 : int(1..2)]), - and([or([and([q21 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q19] -> - or([x_ExplicitR6_ExplicitVarSizeWithDummy[q17, q23] != 3 /\ - x_ExplicitR6_ExplicitVarSizeWithDummy[q17, q23] = - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q19, q21] - | q23 : int(1..3)]) - | q21 : int(1..3)]) - /\ - and([x_ExplicitR6_ExplicitVarSizeWithDummy[q17, q25] != 3 -> - or([q27 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q19] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q19, q27] = - x_ExplicitR6_ExplicitVarSizeWithDummy[q17, q25] - | q27 : int(1..3)]) - | q25 : int(1..3)]) - | q19 : int(1..2)]) - | q17 : int(1..2)]), - and([or([and([x_ExplicitR6_ExplicitVarSizeWithDummy[q31, q33] != 3 -> - or([q35 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q29] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q29, q35] = - x_ExplicitR6_ExplicitVarSizeWithDummy[q31, q33] - | q35 : int(1..3)]) - | q33 : int(1..3)]) - /\ - and([q37 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q29] -> - or([x_ExplicitR6_ExplicitVarSizeWithDummy[q31, q39] != 3 /\ - x_ExplicitR6_ExplicitVarSizeWithDummy[q31, q39] = - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q29, q37] - | q39 : int(1..3)]) - | q37 : int(1..3)]) - | q31 : int(1..2)]) - | q29 : int(1..2)]), - [-toInt(x_ExplicitR2_Occurrence[1, q43]) | q43 : int(1..2)] - x_ExplicitR2_Occurrence[q46, x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q48, q50]] - | q50 : int(1..3)]) - /\ - and([x_ExplicitR2_Occurrence[q46, q51] -> - or([q53 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q48] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q48, q53] = q51 - | q53 : int(1..3)]) - | q51 : int(1..2)]) - | q48 : int(1..2)]) - | q46 : int(1..2)]), - and([or([and([x_ExplicitR2_Occurrence[q57, q58] -> - or([q60 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q55] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q55, q60] = q58 - | q60 : int(1..3)]) - | q58 : int(1..2)]) - /\ - and([q62 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q55] -> - x_ExplicitR2_Occurrence[q57, x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q55, q62]] - | q62 : int(1..3)]) - | q57 : int(1..2)]) - | q55 : int(1..2)]), - and([or([and([x_ExplicitR6_ExplicitVarSizeWithDummy[q66, q68] != 3 -> - x_ExplicitR2_Occurrence[q64, x_ExplicitR6_ExplicitVarSizeWithDummy[q66, q68]] - | q68 : int(1..3)]) - /\ - and([x_ExplicitR2_Occurrence[q64, q69] -> - or([x_ExplicitR6_ExplicitVarSizeWithDummy[q66, q71] != 3 /\ - x_ExplicitR6_ExplicitVarSizeWithDummy[q66, q71] = q69 - | q71 : int(1..3)]) - | q69 : int(1..2)]) - | q66 : int(1..2)]) - | q64 : int(1..2)]), - and([or([and([x_ExplicitR2_Occurrence[q75, q76] -> - or([x_ExplicitR6_ExplicitVarSizeWithDummy[q73, q78] != 3 /\ - x_ExplicitR6_ExplicitVarSizeWithDummy[q73, q78] = q76 - | q78 : int(1..3)]) - | q76 : int(1..2)]) - /\ - and([x_ExplicitR6_ExplicitVarSizeWithDummy[q73, q80] != 3 -> - x_ExplicitR2_Occurrence[q75, x_ExplicitR6_ExplicitVarSizeWithDummy[q73, q80]] - | q80 : int(1..3)]) - | q75 : int(1..2)]) - | q73 : int(1..2)]) - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_3_2_2-solution000001.solution b/tests/exhaustive/basic/setOfSet04/expected/model_3_2_2-solution000001.solution deleted file mode 100644 index 38937c9389..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_3_2_2-solution000001.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1}, {1, 2}} -$ Visualisation for x -$ 1 -$ 1 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_3_2_2-solution000002.solution b/tests/exhaustive/basic/setOfSet04/expected/model_3_2_2-solution000002.solution deleted file mode 100644 index 9bf2af0712..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_3_2_2-solution000002.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1, 2}, {2}} -$ Visualisation for x -$ 1 2 -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_3_2_2-solution000003.solution b/tests/exhaustive/basic/setOfSet04/expected/model_3_2_2-solution000003.solution deleted file mode 100644 index a6c0b6a43e..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_3_2_2-solution000003.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {1, 2}} -$ Visualisation for x -$ -$ 1 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_3_2_2-solution000004.solution b/tests/exhaustive/basic/setOfSet04/expected/model_3_2_2-solution000004.solution deleted file mode 100644 index af16592c51..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_3_2_2-solution000004.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1}, {2}} -$ Visualisation for x -$ 1 -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_3_2_2-solution000005.solution b/tests/exhaustive/basic/setOfSet04/expected/model_3_2_2-solution000005.solution deleted file mode 100644 index 3ec452354e..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_3_2_2-solution000005.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {1}} -$ Visualisation for x -$ -$ 1 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_3_2_2-solution000006.solution b/tests/exhaustive/basic/setOfSet04/expected/model_3_2_2-solution000006.solution deleted file mode 100644 index c8946f3d06..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_3_2_2-solution000006.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {2}} -$ Visualisation for x -$ -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_3_2_2.eprime b/tests/exhaustive/basic/setOfSet04/expected/model_3_2_2.eprime deleted file mode 100644 index 1c05e43b68..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_3_2_2.eprime +++ /dev/null @@ -1,68 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitR5_ExplicitVarSizeWithMarker_Marker: matrix indexed by [int(1..2)] of int(0..3) -find x_ExplicitR5_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..2), int(1..3)] of int(1..2) -find x_ExplicitR6_ExplicitVarSizeWithDummy: matrix indexed by [int(1..2), int(1..3)] of int(1..3) -branching on - [x_ExplicitR6_ExplicitVarSizeWithDummy, x_ExplicitR5_ExplicitVarSizeWithMarker_Marker, - x_ExplicitR5_ExplicitVarSizeWithMarker_Values] -such that - flatten([[x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[1]; int(1)], - flatten([[x_ExplicitR5_ExplicitVarSizeWithMarker_Values[1, q6]; int(1)] | q6 : int(1..3)]); - int(1..2)]) - - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q2, q3] < - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q2, q3 + 1] - | q3 : int(1..2)]) - | q2 : int(1..2)]), - and([and([q4 > x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q2] -> - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q2, q4] = 1 - | q4 : int(1..3)]) - | q2 : int(1..2)]), - and([x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q2] <= 3 | q2 : int(1..2)]), - [x_ExplicitR6_ExplicitVarSizeWithDummy[1, q14] | q14 : int(1..3)] - x_ExplicitR6_ExplicitVarSizeWithDummy[q9, q11 + 1] = 3 - | q11 : int(1..2)]) - | q9 : int(1..2)]), - and([sum([toInt(x_ExplicitR6_ExplicitVarSizeWithDummy[q9, q12] != 3) | q12 : int(1..3)]) <= 3 | q9 : int(1..2)]), - and([or([and([q21 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q19] -> - or([x_ExplicitR6_ExplicitVarSizeWithDummy[q17, q23] != 3 /\ - x_ExplicitR6_ExplicitVarSizeWithDummy[q17, q23] = - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q19, q21] - | q23 : int(1..3)]) - | q21 : int(1..3)]) - /\ - and([x_ExplicitR6_ExplicitVarSizeWithDummy[q17, q25] != 3 -> - or([q27 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q19] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q19, q27] = - x_ExplicitR6_ExplicitVarSizeWithDummy[q17, q25] - | q27 : int(1..3)]) - | q25 : int(1..3)]) - | q19 : int(1..2)]) - | q17 : int(1..2)]), - and([or([and([x_ExplicitR6_ExplicitVarSizeWithDummy[q31, q33] != 3 -> - or([q35 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q29] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q29, q35] = - x_ExplicitR6_ExplicitVarSizeWithDummy[q31, q33] - | q35 : int(1..3)]) - | q33 : int(1..3)]) - /\ - and([q37 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q29] -> - or([x_ExplicitR6_ExplicitVarSizeWithDummy[q31, q39] != 3 /\ - x_ExplicitR6_ExplicitVarSizeWithDummy[q31, q39] = - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q29, q37] - | q39 : int(1..3)]) - | q37 : int(1..3)]) - | q31 : int(1..2)]) - | q29 : int(1..2)]) - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_3_2_3-solution000001.solution b/tests/exhaustive/basic/setOfSet04/expected/model_3_2_3-solution000001.solution deleted file mode 100644 index 38937c9389..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_3_2_3-solution000001.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1}, {1, 2}} -$ Visualisation for x -$ 1 -$ 1 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_3_2_3-solution000002.solution b/tests/exhaustive/basic/setOfSet04/expected/model_3_2_3-solution000002.solution deleted file mode 100644 index 9bf2af0712..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_3_2_3-solution000002.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1, 2}, {2}} -$ Visualisation for x -$ 1 2 -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_3_2_3-solution000003.solution b/tests/exhaustive/basic/setOfSet04/expected/model_3_2_3-solution000003.solution deleted file mode 100644 index a6c0b6a43e..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_3_2_3-solution000003.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {1, 2}} -$ Visualisation for x -$ -$ 1 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_3_2_3-solution000004.solution b/tests/exhaustive/basic/setOfSet04/expected/model_3_2_3-solution000004.solution deleted file mode 100644 index af16592c51..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_3_2_3-solution000004.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1}, {2}} -$ Visualisation for x -$ 1 -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_3_2_3-solution000005.solution b/tests/exhaustive/basic/setOfSet04/expected/model_3_2_3-solution000005.solution deleted file mode 100644 index 3ec452354e..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_3_2_3-solution000005.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {1}} -$ Visualisation for x -$ -$ 1 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_3_2_3-solution000006.solution b/tests/exhaustive/basic/setOfSet04/expected/model_3_2_3-solution000006.solution deleted file mode 100644 index c8946f3d06..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_3_2_3-solution000006.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {2}} -$ Visualisation for x -$ -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_3_2_3.eprime b/tests/exhaustive/basic/setOfSet04/expected/model_3_2_3.eprime deleted file mode 100644 index 1c05e43b68..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_3_2_3.eprime +++ /dev/null @@ -1,68 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitR5_ExplicitVarSizeWithMarker_Marker: matrix indexed by [int(1..2)] of int(0..3) -find x_ExplicitR5_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..2), int(1..3)] of int(1..2) -find x_ExplicitR6_ExplicitVarSizeWithDummy: matrix indexed by [int(1..2), int(1..3)] of int(1..3) -branching on - [x_ExplicitR6_ExplicitVarSizeWithDummy, x_ExplicitR5_ExplicitVarSizeWithMarker_Marker, - x_ExplicitR5_ExplicitVarSizeWithMarker_Values] -such that - flatten([[x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[1]; int(1)], - flatten([[x_ExplicitR5_ExplicitVarSizeWithMarker_Values[1, q6]; int(1)] | q6 : int(1..3)]); - int(1..2)]) - - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q2, q3] < - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q2, q3 + 1] - | q3 : int(1..2)]) - | q2 : int(1..2)]), - and([and([q4 > x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q2] -> - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q2, q4] = 1 - | q4 : int(1..3)]) - | q2 : int(1..2)]), - and([x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q2] <= 3 | q2 : int(1..2)]), - [x_ExplicitR6_ExplicitVarSizeWithDummy[1, q14] | q14 : int(1..3)] - x_ExplicitR6_ExplicitVarSizeWithDummy[q9, q11 + 1] = 3 - | q11 : int(1..2)]) - | q9 : int(1..2)]), - and([sum([toInt(x_ExplicitR6_ExplicitVarSizeWithDummy[q9, q12] != 3) | q12 : int(1..3)]) <= 3 | q9 : int(1..2)]), - and([or([and([q21 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q19] -> - or([x_ExplicitR6_ExplicitVarSizeWithDummy[q17, q23] != 3 /\ - x_ExplicitR6_ExplicitVarSizeWithDummy[q17, q23] = - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q19, q21] - | q23 : int(1..3)]) - | q21 : int(1..3)]) - /\ - and([x_ExplicitR6_ExplicitVarSizeWithDummy[q17, q25] != 3 -> - or([q27 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q19] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q19, q27] = - x_ExplicitR6_ExplicitVarSizeWithDummy[q17, q25] - | q27 : int(1..3)]) - | q25 : int(1..3)]) - | q19 : int(1..2)]) - | q17 : int(1..2)]), - and([or([and([x_ExplicitR6_ExplicitVarSizeWithDummy[q31, q33] != 3 -> - or([q35 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q29] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q29, q35] = - x_ExplicitR6_ExplicitVarSizeWithDummy[q31, q33] - | q35 : int(1..3)]) - | q33 : int(1..3)]) - /\ - and([q37 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q29] -> - or([x_ExplicitR6_ExplicitVarSizeWithDummy[q31, q39] != 3 /\ - x_ExplicitR6_ExplicitVarSizeWithDummy[q31, q39] = - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q29, q37] - | q39 : int(1..3)]) - | q37 : int(1..3)]) - | q31 : int(1..2)]) - | q29 : int(1..2)]) - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_3_2_4-solution000001.solution b/tests/exhaustive/basic/setOfSet04/expected/model_3_2_4-solution000001.solution deleted file mode 100644 index 3ec452354e..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_3_2_4-solution000001.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {1}} -$ Visualisation for x -$ -$ 1 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_3_2_4-solution000002.solution b/tests/exhaustive/basic/setOfSet04/expected/model_3_2_4-solution000002.solution deleted file mode 100644 index c8946f3d06..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_3_2_4-solution000002.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {2}} -$ Visualisation for x -$ -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_3_2_4-solution000003.solution b/tests/exhaustive/basic/setOfSet04/expected/model_3_2_4-solution000003.solution deleted file mode 100644 index af16592c51..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_3_2_4-solution000003.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1}, {2}} -$ Visualisation for x -$ 1 -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_3_2_4-solution000004.solution b/tests/exhaustive/basic/setOfSet04/expected/model_3_2_4-solution000004.solution deleted file mode 100644 index a6c0b6a43e..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_3_2_4-solution000004.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {1, 2}} -$ Visualisation for x -$ -$ 1 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_3_2_4-solution000005.solution b/tests/exhaustive/basic/setOfSet04/expected/model_3_2_4-solution000005.solution deleted file mode 100644 index 38937c9389..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_3_2_4-solution000005.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1}, {1, 2}} -$ Visualisation for x -$ 1 -$ 1 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_3_2_4-solution000006.solution b/tests/exhaustive/basic/setOfSet04/expected/model_3_2_4-solution000006.solution deleted file mode 100644 index 9bf2af0712..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_3_2_4-solution000006.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1, 2}, {2}} -$ Visualisation for x -$ 1 2 -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_3_2_4.eprime b/tests/exhaustive/basic/setOfSet04/expected/model_3_2_4.eprime deleted file mode 100644 index 88bf50e159..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_3_2_4.eprime +++ /dev/null @@ -1,154 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitR5_ExplicitVarSizeWithMarker_Marker: matrix indexed by [int(1..2)] of int(0..3) -find x_ExplicitR5_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..2), int(1..3)] of int(1..2) -find x_ExplicitR6_ExplicitVarSizeWithDummy: matrix indexed by [int(1..2), int(1..3)] of int(1..3) -find x_ExplicitR4_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..2), int(1..3)] of bool -find x_ExplicitR4_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..2), int(1..3)] of int(1..2) -branching on - [x_ExplicitR4_ExplicitVarSizeWithFlags_Flags, x_ExplicitR4_ExplicitVarSizeWithFlags_Values, - x_ExplicitR5_ExplicitVarSizeWithMarker_Marker, x_ExplicitR5_ExplicitVarSizeWithMarker_Values, - x_ExplicitR6_ExplicitVarSizeWithDummy] -such that - flatten([[x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[1]; int(1)], - flatten([[x_ExplicitR5_ExplicitVarSizeWithMarker_Values[1, q6]; int(1)] | q6 : int(1..3)]); - int(1..2)]) - - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q2, q3] < - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q2, q3 + 1] - | q3 : int(1..2)]) - | q2 : int(1..2)]), - and([and([q4 > x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q2] -> - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q2, q4] = 1 - | q4 : int(1..3)]) - | q2 : int(1..2)]), - and([x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q2] <= 3 | q2 : int(1..2)]), - [x_ExplicitR6_ExplicitVarSizeWithDummy[1, q14] | q14 : int(1..3)] - x_ExplicitR6_ExplicitVarSizeWithDummy[q9, q11 + 1] = 3 - | q11 : int(1..2)]) - | q9 : int(1..2)]), - and([sum([toInt(x_ExplicitR6_ExplicitVarSizeWithDummy[q9, q12] != 3) | q12 : int(1..3)]) <= 3 | q9 : int(1..2)]), - and([or([and([q21 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q19] -> - or([x_ExplicitR6_ExplicitVarSizeWithDummy[q17, q23] != 3 /\ - x_ExplicitR6_ExplicitVarSizeWithDummy[q17, q23] = - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q19, q21] - | q23 : int(1..3)]) - | q21 : int(1..3)]) - /\ - and([x_ExplicitR6_ExplicitVarSizeWithDummy[q17, q25] != 3 -> - or([q27 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q19] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q19, q27] = - x_ExplicitR6_ExplicitVarSizeWithDummy[q17, q25] - | q27 : int(1..3)]) - | q25 : int(1..3)]) - | q19 : int(1..2)]) - | q17 : int(1..2)]), - and([or([and([x_ExplicitR6_ExplicitVarSizeWithDummy[q31, q33] != 3 -> - or([q35 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q29] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q29, q35] = - x_ExplicitR6_ExplicitVarSizeWithDummy[q31, q33] - | q35 : int(1..3)]) - | q33 : int(1..3)]) - /\ - and([q37 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q29] -> - or([x_ExplicitR6_ExplicitVarSizeWithDummy[q31, q39] != 3 /\ - x_ExplicitR6_ExplicitVarSizeWithDummy[q31, q39] = - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q29, q37] - | q39 : int(1..3)]) - | q37 : int(1..3)]) - | q31 : int(1..2)]) - | q29 : int(1..2)]), - flatten([flatten([[-toInt(x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[1, q47]); int(1)], - [x_ExplicitR4_ExplicitVarSizeWithFlags_Values[1, q47]; int(1)]; - int(1..2)]) - | q47 : int(1..3)]) - - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q41, q42] < - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q41, q42 + 1] - | q42 : int(1..2)]) - | q41 : int(1..2)]), - and([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q41, q43] = false -> - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q41, q43] = 1 - | q43 : int(1..3)]) - | q41 : int(1..2)]), - and([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q41, q44 + 1] -> - x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q41, q44] - | q44 : int(1..2)]) - | q41 : int(1..2)]), - and([sum([toInt(x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q41, q45]) | q45 : int(1..3)]) <= 3 | q41 : int(1..2)]), - and([or([and([q54 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q52] -> - or([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q50, q56] /\ - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q50, q56] = - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q52, q54] - | q56 : int(1..3)]) - | q54 : int(1..3)]) - /\ - and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q50, q58] -> - or([q60 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q52] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q52, q60] = - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q50, q58] - | q60 : int(1..3)]) - | q58 : int(1..3)]) - | q52 : int(1..2)]) - | q50 : int(1..2)]), - and([or([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q64, q66] -> - or([q68 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q62] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q62, q68] = - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q64, q66] - | q68 : int(1..3)]) - | q66 : int(1..3)]) - /\ - and([q70 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q62] -> - or([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q64, q72] /\ - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q64, q72] = - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q62, q70] - | q72 : int(1..3)]) - | q70 : int(1..3)]) - | q64 : int(1..2)]) - | q62 : int(1..2)]), - and([or([and([x_ExplicitR6_ExplicitVarSizeWithDummy[q76, q78] != 3 -> - or([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q74, q80] /\ - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q74, q80] = - x_ExplicitR6_ExplicitVarSizeWithDummy[q76, q78] - | q80 : int(1..3)]) - | q78 : int(1..3)]) - /\ - and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q74, q82] -> - or([x_ExplicitR6_ExplicitVarSizeWithDummy[q76, q84] != 3 /\ - x_ExplicitR6_ExplicitVarSizeWithDummy[q76, q84] = - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q74, q82] - | q84 : int(1..3)]) - | q82 : int(1..3)]) - | q76 : int(1..2)]) - | q74 : int(1..2)]), - and([or([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q88, q90] -> - or([x_ExplicitR6_ExplicitVarSizeWithDummy[q86, q92] != 3 /\ - x_ExplicitR6_ExplicitVarSizeWithDummy[q86, q92] = - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q88, q90] - | q92 : int(1..3)]) - | q90 : int(1..3)]) - /\ - and([x_ExplicitR6_ExplicitVarSizeWithDummy[q86, q94] != 3 -> - or([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q88, q96] /\ - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q88, q96] = - x_ExplicitR6_ExplicitVarSizeWithDummy[q86, q94] - | q96 : int(1..3)]) - | q94 : int(1..3)]) - | q88 : int(1..2)]) - | q86 : int(1..2)]) - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_3_3_1-solution000001.solution b/tests/exhaustive/basic/setOfSet04/expected/model_3_3_1-solution000001.solution deleted file mode 100644 index c8946f3d06..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_3_3_1-solution000001.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {2}} -$ Visualisation for x -$ -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_3_3_1-solution000002.solution b/tests/exhaustive/basic/setOfSet04/expected/model_3_3_1-solution000002.solution deleted file mode 100644 index 3ec452354e..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_3_3_1-solution000002.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {1}} -$ Visualisation for x -$ -$ 1 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_3_3_1-solution000003.solution b/tests/exhaustive/basic/setOfSet04/expected/model_3_3_1-solution000003.solution deleted file mode 100644 index af16592c51..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_3_3_1-solution000003.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1}, {2}} -$ Visualisation for x -$ 1 -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_3_3_1-solution000004.solution b/tests/exhaustive/basic/setOfSet04/expected/model_3_3_1-solution000004.solution deleted file mode 100644 index a6c0b6a43e..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_3_3_1-solution000004.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {1, 2}} -$ Visualisation for x -$ -$ 1 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_3_3_1-solution000005.solution b/tests/exhaustive/basic/setOfSet04/expected/model_3_3_1-solution000005.solution deleted file mode 100644 index 9bf2af0712..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_3_3_1-solution000005.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1, 2}, {2}} -$ Visualisation for x -$ 1 2 -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_3_3_1-solution000006.solution b/tests/exhaustive/basic/setOfSet04/expected/model_3_3_1-solution000006.solution deleted file mode 100644 index 38937c9389..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_3_3_1-solution000006.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1}, {1, 2}} -$ Visualisation for x -$ 1 -$ 1 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_3_3_1.eprime b/tests/exhaustive/basic/setOfSet04/expected/model_3_3_1.eprime deleted file mode 100644 index e420029404..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_3_3_1.eprime +++ /dev/null @@ -1,52 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitR5_ExplicitVarSizeWithMarker_Marker: matrix indexed by [int(1..2)] of int(0..3) -find x_ExplicitR5_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..2), int(1..3)] of int(1..2) -find x_ExplicitR2_Occurrence: matrix indexed by [int(1..2), int(1..2)] of bool -branching on - [x_ExplicitR2_Occurrence, x_ExplicitR5_ExplicitVarSizeWithMarker_Marker, - x_ExplicitR5_ExplicitVarSizeWithMarker_Values] -such that - flatten([[x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[1]; int(1)], - flatten([[x_ExplicitR5_ExplicitVarSizeWithMarker_Values[1, q6]; int(1)] | q6 : int(1..3)]); - int(1..2)]) - - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q2, q3] < - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q2, q3 + 1] - | q3 : int(1..2)]) - | q2 : int(1..2)]), - and([and([q4 > x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q2] -> - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q2, q4] = 1 - | q4 : int(1..3)]) - | q2 : int(1..2)]), - and([x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q2] <= 3 | q2 : int(1..2)]), - [-toInt(x_ExplicitR2_Occurrence[1, q11]) | q11 : int(1..2)] - x_ExplicitR2_Occurrence[q14, x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q16, q18]] - | q18 : int(1..3)]) - /\ - and([x_ExplicitR2_Occurrence[q14, q19] -> - or([q21 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q16] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q16, q21] = q19 - | q21 : int(1..3)]) - | q19 : int(1..2)]) - | q16 : int(1..2)]) - | q14 : int(1..2)]), - and([or([and([x_ExplicitR2_Occurrence[q25, q26] -> - or([q28 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q23] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q23, q28] = q26 - | q28 : int(1..3)]) - | q26 : int(1..2)]) - /\ - and([q30 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q23] -> - x_ExplicitR2_Occurrence[q25, x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q23, q30]] - | q30 : int(1..3)]) - | q25 : int(1..2)]) - | q23 : int(1..2)]) - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_3_3_2-solution000001.solution b/tests/exhaustive/basic/setOfSet04/expected/model_3_3_2-solution000001.solution deleted file mode 100644 index 38937c9389..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_3_3_2-solution000001.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1}, {1, 2}} -$ Visualisation for x -$ 1 -$ 1 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_3_3_2-solution000002.solution b/tests/exhaustive/basic/setOfSet04/expected/model_3_3_2-solution000002.solution deleted file mode 100644 index 9bf2af0712..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_3_3_2-solution000002.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1, 2}, {2}} -$ Visualisation for x -$ 1 2 -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_3_3_2-solution000003.solution b/tests/exhaustive/basic/setOfSet04/expected/model_3_3_2-solution000003.solution deleted file mode 100644 index a6c0b6a43e..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_3_3_2-solution000003.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {1, 2}} -$ Visualisation for x -$ -$ 1 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_3_3_2-solution000004.solution b/tests/exhaustive/basic/setOfSet04/expected/model_3_3_2-solution000004.solution deleted file mode 100644 index af16592c51..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_3_3_2-solution000004.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1}, {2}} -$ Visualisation for x -$ 1 -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_3_3_2-solution000005.solution b/tests/exhaustive/basic/setOfSet04/expected/model_3_3_2-solution000005.solution deleted file mode 100644 index 3ec452354e..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_3_3_2-solution000005.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {1}} -$ Visualisation for x -$ -$ 1 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_3_3_2-solution000006.solution b/tests/exhaustive/basic/setOfSet04/expected/model_3_3_2-solution000006.solution deleted file mode 100644 index c8946f3d06..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_3_3_2-solution000006.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {2}} -$ Visualisation for x -$ -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_3_3_2.eprime b/tests/exhaustive/basic/setOfSet04/expected/model_3_3_2.eprime deleted file mode 100644 index 1c05e43b68..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_3_3_2.eprime +++ /dev/null @@ -1,68 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitR5_ExplicitVarSizeWithMarker_Marker: matrix indexed by [int(1..2)] of int(0..3) -find x_ExplicitR5_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..2), int(1..3)] of int(1..2) -find x_ExplicitR6_ExplicitVarSizeWithDummy: matrix indexed by [int(1..2), int(1..3)] of int(1..3) -branching on - [x_ExplicitR6_ExplicitVarSizeWithDummy, x_ExplicitR5_ExplicitVarSizeWithMarker_Marker, - x_ExplicitR5_ExplicitVarSizeWithMarker_Values] -such that - flatten([[x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[1]; int(1)], - flatten([[x_ExplicitR5_ExplicitVarSizeWithMarker_Values[1, q6]; int(1)] | q6 : int(1..3)]); - int(1..2)]) - - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q2, q3] < - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q2, q3 + 1] - | q3 : int(1..2)]) - | q2 : int(1..2)]), - and([and([q4 > x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q2] -> - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q2, q4] = 1 - | q4 : int(1..3)]) - | q2 : int(1..2)]), - and([x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q2] <= 3 | q2 : int(1..2)]), - [x_ExplicitR6_ExplicitVarSizeWithDummy[1, q14] | q14 : int(1..3)] - x_ExplicitR6_ExplicitVarSizeWithDummy[q9, q11 + 1] = 3 - | q11 : int(1..2)]) - | q9 : int(1..2)]), - and([sum([toInt(x_ExplicitR6_ExplicitVarSizeWithDummy[q9, q12] != 3) | q12 : int(1..3)]) <= 3 | q9 : int(1..2)]), - and([or([and([q21 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q19] -> - or([x_ExplicitR6_ExplicitVarSizeWithDummy[q17, q23] != 3 /\ - x_ExplicitR6_ExplicitVarSizeWithDummy[q17, q23] = - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q19, q21] - | q23 : int(1..3)]) - | q21 : int(1..3)]) - /\ - and([x_ExplicitR6_ExplicitVarSizeWithDummy[q17, q25] != 3 -> - or([q27 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q19] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q19, q27] = - x_ExplicitR6_ExplicitVarSizeWithDummy[q17, q25] - | q27 : int(1..3)]) - | q25 : int(1..3)]) - | q19 : int(1..2)]) - | q17 : int(1..2)]), - and([or([and([x_ExplicitR6_ExplicitVarSizeWithDummy[q31, q33] != 3 -> - or([q35 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q29] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q29, q35] = - x_ExplicitR6_ExplicitVarSizeWithDummy[q31, q33] - | q35 : int(1..3)]) - | q33 : int(1..3)]) - /\ - and([q37 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q29] -> - or([x_ExplicitR6_ExplicitVarSizeWithDummy[q31, q39] != 3 /\ - x_ExplicitR6_ExplicitVarSizeWithDummy[q31, q39] = - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q29, q37] - | q39 : int(1..3)]) - | q37 : int(1..3)]) - | q31 : int(1..2)]) - | q29 : int(1..2)]) - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_3_3_3-solution000001.solution b/tests/exhaustive/basic/setOfSet04/expected/model_3_3_3-solution000001.solution deleted file mode 100644 index 3ec452354e..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_3_3_3-solution000001.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {1}} -$ Visualisation for x -$ -$ 1 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_3_3_3-solution000002.solution b/tests/exhaustive/basic/setOfSet04/expected/model_3_3_3-solution000002.solution deleted file mode 100644 index c8946f3d06..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_3_3_3-solution000002.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {2}} -$ Visualisation for x -$ -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_3_3_3-solution000003.solution b/tests/exhaustive/basic/setOfSet04/expected/model_3_3_3-solution000003.solution deleted file mode 100644 index a6c0b6a43e..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_3_3_3-solution000003.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {1, 2}} -$ Visualisation for x -$ -$ 1 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_3_3_3-solution000004.solution b/tests/exhaustive/basic/setOfSet04/expected/model_3_3_3-solution000004.solution deleted file mode 100644 index af16592c51..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_3_3_3-solution000004.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1}, {2}} -$ Visualisation for x -$ 1 -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_3_3_3-solution000005.solution b/tests/exhaustive/basic/setOfSet04/expected/model_3_3_3-solution000005.solution deleted file mode 100644 index 38937c9389..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_3_3_3-solution000005.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1}, {1, 2}} -$ Visualisation for x -$ 1 -$ 1 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_3_3_3-solution000006.solution b/tests/exhaustive/basic/setOfSet04/expected/model_3_3_3-solution000006.solution deleted file mode 100644 index 9bf2af0712..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_3_3_3-solution000006.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1, 2}, {2}} -$ Visualisation for x -$ 1 2 -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_3_3_3.eprime b/tests/exhaustive/basic/setOfSet04/expected/model_3_3_3.eprime deleted file mode 100644 index 42638c06b8..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_3_3_3.eprime +++ /dev/null @@ -1,24 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitR5_ExplicitVarSizeWithMarker_Marker: matrix indexed by [int(1..2)] of int(0..3) -find x_ExplicitR5_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..2), int(1..3)] of int(1..2) -branching on [x_ExplicitR5_ExplicitVarSizeWithMarker_Marker, x_ExplicitR5_ExplicitVarSizeWithMarker_Values] -such that - flatten([[x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[1]; int(1)], - flatten([[x_ExplicitR5_ExplicitVarSizeWithMarker_Values[1, q6]; int(1)] | q6 : int(1..3)]); - int(1..2)]) - - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q2, q3] < - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q2, q3 + 1] - | q3 : int(1..2)]) - | q2 : int(1..2)]), - and([and([q4 > x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q2] -> - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q2, q4] = 1 - | q4 : int(1..3)]) - | q2 : int(1..2)]), - and([x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q2] <= 3 | q2 : int(1..2)]) - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_3_3_4-solution000001.solution b/tests/exhaustive/basic/setOfSet04/expected/model_3_3_4-solution000001.solution deleted file mode 100644 index 3ec452354e..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_3_3_4-solution000001.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {1}} -$ Visualisation for x -$ -$ 1 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_3_3_4-solution000002.solution b/tests/exhaustive/basic/setOfSet04/expected/model_3_3_4-solution000002.solution deleted file mode 100644 index c8946f3d06..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_3_3_4-solution000002.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {2}} -$ Visualisation for x -$ -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_3_3_4-solution000003.solution b/tests/exhaustive/basic/setOfSet04/expected/model_3_3_4-solution000003.solution deleted file mode 100644 index af16592c51..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_3_3_4-solution000003.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1}, {2}} -$ Visualisation for x -$ 1 -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_3_3_4-solution000004.solution b/tests/exhaustive/basic/setOfSet04/expected/model_3_3_4-solution000004.solution deleted file mode 100644 index a6c0b6a43e..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_3_3_4-solution000004.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {1, 2}} -$ Visualisation for x -$ -$ 1 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_3_3_4-solution000005.solution b/tests/exhaustive/basic/setOfSet04/expected/model_3_3_4-solution000005.solution deleted file mode 100644 index 38937c9389..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_3_3_4-solution000005.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1}, {1, 2}} -$ Visualisation for x -$ 1 -$ 1 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_3_3_4-solution000006.solution b/tests/exhaustive/basic/setOfSet04/expected/model_3_3_4-solution000006.solution deleted file mode 100644 index 9bf2af0712..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_3_3_4-solution000006.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1, 2}, {2}} -$ Visualisation for x -$ 1 2 -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_3_3_4.eprime b/tests/exhaustive/basic/setOfSet04/expected/model_3_3_4.eprime deleted file mode 100644 index 473d929c0b..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_3_3_4.eprime +++ /dev/null @@ -1,81 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitR5_ExplicitVarSizeWithMarker_Marker: matrix indexed by [int(1..2)] of int(0..3) -find x_ExplicitR5_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..2), int(1..3)] of int(1..2) -find x_ExplicitR4_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..2), int(1..3)] of bool -find x_ExplicitR4_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..2), int(1..3)] of int(1..2) -branching on - [x_ExplicitR4_ExplicitVarSizeWithFlags_Flags, x_ExplicitR4_ExplicitVarSizeWithFlags_Values, - x_ExplicitR5_ExplicitVarSizeWithMarker_Marker, x_ExplicitR5_ExplicitVarSizeWithMarker_Values] -such that - flatten([[x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[1]; int(1)], - flatten([[x_ExplicitR5_ExplicitVarSizeWithMarker_Values[1, q6]; int(1)] | q6 : int(1..3)]); - int(1..2)]) - - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q2, q3] < - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q2, q3 + 1] - | q3 : int(1..2)]) - | q2 : int(1..2)]), - and([and([q4 > x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q2] -> - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q2, q4] = 1 - | q4 : int(1..3)]) - | q2 : int(1..2)]), - and([x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q2] <= 3 | q2 : int(1..2)]), - flatten([flatten([[-toInt(x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[1, q15]); int(1)], - [x_ExplicitR4_ExplicitVarSizeWithFlags_Values[1, q15]; int(1)]; - int(1..2)]) - | q15 : int(1..3)]) - - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q9, q10] < - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q9, q10 + 1] - | q10 : int(1..2)]) - | q9 : int(1..2)]), - and([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q9, q11] = false -> - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q9, q11] = 1 - | q11 : int(1..3)]) - | q9 : int(1..2)]), - and([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q9, q12 + 1] -> - x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q9, q12] - | q12 : int(1..2)]) - | q9 : int(1..2)]), - and([sum([toInt(x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q9, q13]) | q13 : int(1..3)]) <= 3 | q9 : int(1..2)]), - and([or([and([q22 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q20] -> - or([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q18, q24] /\ - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q18, q24] = - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q20, q22] - | q24 : int(1..3)]) - | q22 : int(1..3)]) - /\ - and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q18, q26] -> - or([q28 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q20] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q20, q28] = - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q18, q26] - | q28 : int(1..3)]) - | q26 : int(1..3)]) - | q20 : int(1..2)]) - | q18 : int(1..2)]), - and([or([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q32, q34] -> - or([q36 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q30] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q30, q36] = - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q32, q34] - | q36 : int(1..3)]) - | q34 : int(1..3)]) - /\ - and([q38 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q30] -> - or([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q32, q40] /\ - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q32, q40] = - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q30, q38] - | q40 : int(1..3)]) - | q38 : int(1..3)]) - | q32 : int(1..2)]) - | q30 : int(1..2)]) - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_3_4_1-solution000001.solution b/tests/exhaustive/basic/setOfSet04/expected/model_3_4_1-solution000001.solution deleted file mode 100644 index c8946f3d06..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_3_4_1-solution000001.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {2}} -$ Visualisation for x -$ -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_3_4_1-solution000002.solution b/tests/exhaustive/basic/setOfSet04/expected/model_3_4_1-solution000002.solution deleted file mode 100644 index 3ec452354e..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_3_4_1-solution000002.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {1}} -$ Visualisation for x -$ -$ 1 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_3_4_1-solution000003.solution b/tests/exhaustive/basic/setOfSet04/expected/model_3_4_1-solution000003.solution deleted file mode 100644 index af16592c51..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_3_4_1-solution000003.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1}, {2}} -$ Visualisation for x -$ 1 -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_3_4_1-solution000004.solution b/tests/exhaustive/basic/setOfSet04/expected/model_3_4_1-solution000004.solution deleted file mode 100644 index a6c0b6a43e..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_3_4_1-solution000004.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {1, 2}} -$ Visualisation for x -$ -$ 1 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_3_4_1-solution000005.solution b/tests/exhaustive/basic/setOfSet04/expected/model_3_4_1-solution000005.solution deleted file mode 100644 index 9bf2af0712..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_3_4_1-solution000005.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1, 2}, {2}} -$ Visualisation for x -$ 1 2 -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_3_4_1-solution000006.solution b/tests/exhaustive/basic/setOfSet04/expected/model_3_4_1-solution000006.solution deleted file mode 100644 index 38937c9389..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_3_4_1-solution000006.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1}, {1, 2}} -$ Visualisation for x -$ 1 -$ 1 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_3_4_1.eprime b/tests/exhaustive/basic/setOfSet04/expected/model_3_4_1.eprime deleted file mode 100644 index 43242d3d14..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_3_4_1.eprime +++ /dev/null @@ -1,130 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitR5_ExplicitVarSizeWithMarker_Marker: matrix indexed by [int(1..2)] of int(0..3) -find x_ExplicitR5_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..2), int(1..3)] of int(1..2) -find x_ExplicitR4_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..2), int(1..3)] of bool -find x_ExplicitR4_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..2), int(1..3)] of int(1..2) -find x_ExplicitR2_Occurrence: matrix indexed by [int(1..2), int(1..2)] of bool -branching on - [x_ExplicitR2_Occurrence, x_ExplicitR5_ExplicitVarSizeWithMarker_Marker, - x_ExplicitR5_ExplicitVarSizeWithMarker_Values, x_ExplicitR4_ExplicitVarSizeWithFlags_Flags, - x_ExplicitR4_ExplicitVarSizeWithFlags_Values] -such that - flatten([[x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[1]; int(1)], - flatten([[x_ExplicitR5_ExplicitVarSizeWithMarker_Values[1, q6]; int(1)] | q6 : int(1..3)]); - int(1..2)]) - - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q2, q3] < - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q2, q3 + 1] - | q3 : int(1..2)]) - | q2 : int(1..2)]), - and([and([q4 > x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q2] -> - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q2, q4] = 1 - | q4 : int(1..3)]) - | q2 : int(1..2)]), - and([x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q2] <= 3 | q2 : int(1..2)]), - flatten([flatten([[-toInt(x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[1, q15]); int(1)], - [x_ExplicitR4_ExplicitVarSizeWithFlags_Values[1, q15]; int(1)]; - int(1..2)]) - | q15 : int(1..3)]) - - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q9, q10] < - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q9, q10 + 1] - | q10 : int(1..2)]) - | q9 : int(1..2)]), - and([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q9, q11] = false -> - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q9, q11] = 1 - | q11 : int(1..3)]) - | q9 : int(1..2)]), - and([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q9, q12 + 1] -> - x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q9, q12] - | q12 : int(1..2)]) - | q9 : int(1..2)]), - and([sum([toInt(x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q9, q13]) | q13 : int(1..3)]) <= 3 | q9 : int(1..2)]), - and([or([and([q22 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q20] -> - or([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q18, q24] /\ - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q18, q24] = - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q20, q22] - | q24 : int(1..3)]) - | q22 : int(1..3)]) - /\ - and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q18, q26] -> - or([q28 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q20] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q20, q28] = - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q18, q26] - | q28 : int(1..3)]) - | q26 : int(1..3)]) - | q20 : int(1..2)]) - | q18 : int(1..2)]), - and([or([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q32, q34] -> - or([q36 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q30] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q30, q36] = - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q32, q34] - | q36 : int(1..3)]) - | q34 : int(1..3)]) - /\ - and([q38 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q30] -> - or([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q32, q40] /\ - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q32, q40] = - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q30, q38] - | q40 : int(1..3)]) - | q38 : int(1..3)]) - | q32 : int(1..2)]) - | q30 : int(1..2)]), - [-toInt(x_ExplicitR2_Occurrence[1, q44]) | q44 : int(1..2)] - x_ExplicitR2_Occurrence[q47, x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q49, q51]] - | q51 : int(1..3)]) - /\ - and([x_ExplicitR2_Occurrence[q47, q52] -> - or([q54 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q49] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q49, q54] = q52 - | q54 : int(1..3)]) - | q52 : int(1..2)]) - | q49 : int(1..2)]) - | q47 : int(1..2)]), - and([or([and([x_ExplicitR2_Occurrence[q58, q59] -> - or([q61 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q56] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q56, q61] = q59 - | q61 : int(1..3)]) - | q59 : int(1..2)]) - /\ - and([q63 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q56] -> - x_ExplicitR2_Occurrence[q58, x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q56, q63]] - | q63 : int(1..3)]) - | q58 : int(1..2)]) - | q56 : int(1..2)]), - and([or([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q67, q69] -> - x_ExplicitR2_Occurrence[q65, x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q67, q69]] - | q69 : int(1..3)]) - /\ - and([x_ExplicitR2_Occurrence[q65, q70] -> - or([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q67, q72] /\ - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q67, q72] = q70 - | q72 : int(1..3)]) - | q70 : int(1..2)]) - | q67 : int(1..2)]) - | q65 : int(1..2)]), - and([or([and([x_ExplicitR2_Occurrence[q76, q77] -> - or([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q74, q79] /\ - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q74, q79] = q77 - | q79 : int(1..3)]) - | q77 : int(1..2)]) - /\ - and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q74, q81] -> - x_ExplicitR2_Occurrence[q76, x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q74, q81]] - | q81 : int(1..3)]) - | q76 : int(1..2)]) - | q74 : int(1..2)]) - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_3_4_2-solution000001.solution b/tests/exhaustive/basic/setOfSet04/expected/model_3_4_2-solution000001.solution deleted file mode 100644 index 38937c9389..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_3_4_2-solution000001.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1}, {1, 2}} -$ Visualisation for x -$ 1 -$ 1 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_3_4_2-solution000002.solution b/tests/exhaustive/basic/setOfSet04/expected/model_3_4_2-solution000002.solution deleted file mode 100644 index 9bf2af0712..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_3_4_2-solution000002.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1, 2}, {2}} -$ Visualisation for x -$ 1 2 -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_3_4_2-solution000003.solution b/tests/exhaustive/basic/setOfSet04/expected/model_3_4_2-solution000003.solution deleted file mode 100644 index a6c0b6a43e..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_3_4_2-solution000003.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {1, 2}} -$ Visualisation for x -$ -$ 1 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_3_4_2-solution000004.solution b/tests/exhaustive/basic/setOfSet04/expected/model_3_4_2-solution000004.solution deleted file mode 100644 index af16592c51..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_3_4_2-solution000004.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1}, {2}} -$ Visualisation for x -$ 1 -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_3_4_2-solution000005.solution b/tests/exhaustive/basic/setOfSet04/expected/model_3_4_2-solution000005.solution deleted file mode 100644 index 3ec452354e..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_3_4_2-solution000005.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {1}} -$ Visualisation for x -$ -$ 1 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_3_4_2-solution000006.solution b/tests/exhaustive/basic/setOfSet04/expected/model_3_4_2-solution000006.solution deleted file mode 100644 index c8946f3d06..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_3_4_2-solution000006.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {2}} -$ Visualisation for x -$ -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_3_4_2.eprime b/tests/exhaustive/basic/setOfSet04/expected/model_3_4_2.eprime deleted file mode 100644 index 2a793f961f..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_3_4_2.eprime +++ /dev/null @@ -1,154 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitR5_ExplicitVarSizeWithMarker_Marker: matrix indexed by [int(1..2)] of int(0..3) -find x_ExplicitR5_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..2), int(1..3)] of int(1..2) -find x_ExplicitR4_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..2), int(1..3)] of bool -find x_ExplicitR4_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..2), int(1..3)] of int(1..2) -find x_ExplicitR6_ExplicitVarSizeWithDummy: matrix indexed by [int(1..2), int(1..3)] of int(1..3) -branching on - [x_ExplicitR6_ExplicitVarSizeWithDummy, x_ExplicitR5_ExplicitVarSizeWithMarker_Marker, - x_ExplicitR5_ExplicitVarSizeWithMarker_Values, x_ExplicitR4_ExplicitVarSizeWithFlags_Flags, - x_ExplicitR4_ExplicitVarSizeWithFlags_Values] -such that - flatten([[x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[1]; int(1)], - flatten([[x_ExplicitR5_ExplicitVarSizeWithMarker_Values[1, q6]; int(1)] | q6 : int(1..3)]); - int(1..2)]) - - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q2, q3] < - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q2, q3 + 1] - | q3 : int(1..2)]) - | q2 : int(1..2)]), - and([and([q4 > x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q2] -> - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q2, q4] = 1 - | q4 : int(1..3)]) - | q2 : int(1..2)]), - and([x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q2] <= 3 | q2 : int(1..2)]), - flatten([flatten([[-toInt(x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[1, q15]); int(1)], - [x_ExplicitR4_ExplicitVarSizeWithFlags_Values[1, q15]; int(1)]; - int(1..2)]) - | q15 : int(1..3)]) - - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q9, q10] < - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q9, q10 + 1] - | q10 : int(1..2)]) - | q9 : int(1..2)]), - and([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q9, q11] = false -> - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q9, q11] = 1 - | q11 : int(1..3)]) - | q9 : int(1..2)]), - and([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q9, q12 + 1] -> - x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q9, q12] - | q12 : int(1..2)]) - | q9 : int(1..2)]), - and([sum([toInt(x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q9, q13]) | q13 : int(1..3)]) <= 3 | q9 : int(1..2)]), - and([or([and([q22 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q20] -> - or([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q18, q24] /\ - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q18, q24] = - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q20, q22] - | q24 : int(1..3)]) - | q22 : int(1..3)]) - /\ - and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q18, q26] -> - or([q28 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q20] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q20, q28] = - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q18, q26] - | q28 : int(1..3)]) - | q26 : int(1..3)]) - | q20 : int(1..2)]) - | q18 : int(1..2)]), - and([or([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q32, q34] -> - or([q36 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q30] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q30, q36] = - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q32, q34] - | q36 : int(1..3)]) - | q34 : int(1..3)]) - /\ - and([q38 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q30] -> - or([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q32, q40] /\ - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q32, q40] = - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q30, q38] - | q40 : int(1..3)]) - | q38 : int(1..3)]) - | q32 : int(1..2)]) - | q30 : int(1..2)]), - [x_ExplicitR6_ExplicitVarSizeWithDummy[1, q47] | q47 : int(1..3)] - x_ExplicitR6_ExplicitVarSizeWithDummy[q42, q44 + 1] = 3 - | q44 : int(1..2)]) - | q42 : int(1..2)]), - and([sum([toInt(x_ExplicitR6_ExplicitVarSizeWithDummy[q42, q45] != 3) | q45 : int(1..3)]) <= 3 | q42 : int(1..2)]), - and([or([and([q54 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q52] -> - or([x_ExplicitR6_ExplicitVarSizeWithDummy[q50, q56] != 3 /\ - x_ExplicitR6_ExplicitVarSizeWithDummy[q50, q56] = - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q52, q54] - | q56 : int(1..3)]) - | q54 : int(1..3)]) - /\ - and([x_ExplicitR6_ExplicitVarSizeWithDummy[q50, q58] != 3 -> - or([q60 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q52] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q52, q60] = - x_ExplicitR6_ExplicitVarSizeWithDummy[q50, q58] - | q60 : int(1..3)]) - | q58 : int(1..3)]) - | q52 : int(1..2)]) - | q50 : int(1..2)]), - and([or([and([x_ExplicitR6_ExplicitVarSizeWithDummy[q64, q66] != 3 -> - or([q68 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q62] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q62, q68] = - x_ExplicitR6_ExplicitVarSizeWithDummy[q64, q66] - | q68 : int(1..3)]) - | q66 : int(1..3)]) - /\ - and([q70 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q62] -> - or([x_ExplicitR6_ExplicitVarSizeWithDummy[q64, q72] != 3 /\ - x_ExplicitR6_ExplicitVarSizeWithDummy[q64, q72] = - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q62, q70] - | q72 : int(1..3)]) - | q70 : int(1..3)]) - | q64 : int(1..2)]) - | q62 : int(1..2)]), - and([or([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q76, q78] -> - or([x_ExplicitR6_ExplicitVarSizeWithDummy[q74, q80] != 3 /\ - x_ExplicitR6_ExplicitVarSizeWithDummy[q74, q80] = - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q76, q78] - | q80 : int(1..3)]) - | q78 : int(1..3)]) - /\ - and([x_ExplicitR6_ExplicitVarSizeWithDummy[q74, q82] != 3 -> - or([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q76, q84] /\ - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q76, q84] = - x_ExplicitR6_ExplicitVarSizeWithDummy[q74, q82] - | q84 : int(1..3)]) - | q82 : int(1..3)]) - | q76 : int(1..2)]) - | q74 : int(1..2)]), - and([or([and([x_ExplicitR6_ExplicitVarSizeWithDummy[q88, q90] != 3 -> - or([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q86, q92] /\ - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q86, q92] = - x_ExplicitR6_ExplicitVarSizeWithDummy[q88, q90] - | q92 : int(1..3)]) - | q90 : int(1..3)]) - /\ - and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q86, q94] -> - or([x_ExplicitR6_ExplicitVarSizeWithDummy[q88, q96] != 3 /\ - x_ExplicitR6_ExplicitVarSizeWithDummy[q88, q96] = - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q86, q94] - | q96 : int(1..3)]) - | q94 : int(1..3)]) - | q88 : int(1..2)]) - | q86 : int(1..2)]) - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_3_4_3-solution000001.solution b/tests/exhaustive/basic/setOfSet04/expected/model_3_4_3-solution000001.solution deleted file mode 100644 index 3ec452354e..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_3_4_3-solution000001.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {1}} -$ Visualisation for x -$ -$ 1 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_3_4_3-solution000002.solution b/tests/exhaustive/basic/setOfSet04/expected/model_3_4_3-solution000002.solution deleted file mode 100644 index c8946f3d06..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_3_4_3-solution000002.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {2}} -$ Visualisation for x -$ -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_3_4_3-solution000003.solution b/tests/exhaustive/basic/setOfSet04/expected/model_3_4_3-solution000003.solution deleted file mode 100644 index af16592c51..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_3_4_3-solution000003.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1}, {2}} -$ Visualisation for x -$ 1 -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_3_4_3-solution000004.solution b/tests/exhaustive/basic/setOfSet04/expected/model_3_4_3-solution000004.solution deleted file mode 100644 index a6c0b6a43e..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_3_4_3-solution000004.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {1, 2}} -$ Visualisation for x -$ -$ 1 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_3_4_3-solution000005.solution b/tests/exhaustive/basic/setOfSet04/expected/model_3_4_3-solution000005.solution deleted file mode 100644 index 38937c9389..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_3_4_3-solution000005.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1}, {1, 2}} -$ Visualisation for x -$ 1 -$ 1 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_3_4_3-solution000006.solution b/tests/exhaustive/basic/setOfSet04/expected/model_3_4_3-solution000006.solution deleted file mode 100644 index 9bf2af0712..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_3_4_3-solution000006.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1, 2}, {2}} -$ Visualisation for x -$ 1 2 -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_3_4_3.eprime b/tests/exhaustive/basic/setOfSet04/expected/model_3_4_3.eprime deleted file mode 100644 index 473d929c0b..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_3_4_3.eprime +++ /dev/null @@ -1,81 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitR5_ExplicitVarSizeWithMarker_Marker: matrix indexed by [int(1..2)] of int(0..3) -find x_ExplicitR5_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..2), int(1..3)] of int(1..2) -find x_ExplicitR4_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..2), int(1..3)] of bool -find x_ExplicitR4_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..2), int(1..3)] of int(1..2) -branching on - [x_ExplicitR4_ExplicitVarSizeWithFlags_Flags, x_ExplicitR4_ExplicitVarSizeWithFlags_Values, - x_ExplicitR5_ExplicitVarSizeWithMarker_Marker, x_ExplicitR5_ExplicitVarSizeWithMarker_Values] -such that - flatten([[x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[1]; int(1)], - flatten([[x_ExplicitR5_ExplicitVarSizeWithMarker_Values[1, q6]; int(1)] | q6 : int(1..3)]); - int(1..2)]) - - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q2, q3] < - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q2, q3 + 1] - | q3 : int(1..2)]) - | q2 : int(1..2)]), - and([and([q4 > x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q2] -> - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q2, q4] = 1 - | q4 : int(1..3)]) - | q2 : int(1..2)]), - and([x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q2] <= 3 | q2 : int(1..2)]), - flatten([flatten([[-toInt(x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[1, q15]); int(1)], - [x_ExplicitR4_ExplicitVarSizeWithFlags_Values[1, q15]; int(1)]; - int(1..2)]) - | q15 : int(1..3)]) - - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q9, q10] < - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q9, q10 + 1] - | q10 : int(1..2)]) - | q9 : int(1..2)]), - and([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q9, q11] = false -> - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q9, q11] = 1 - | q11 : int(1..3)]) - | q9 : int(1..2)]), - and([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q9, q12 + 1] -> - x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q9, q12] - | q12 : int(1..2)]) - | q9 : int(1..2)]), - and([sum([toInt(x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q9, q13]) | q13 : int(1..3)]) <= 3 | q9 : int(1..2)]), - and([or([and([q22 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q20] -> - or([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q18, q24] /\ - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q18, q24] = - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q20, q22] - | q24 : int(1..3)]) - | q22 : int(1..3)]) - /\ - and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q18, q26] -> - or([q28 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q20] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q20, q28] = - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q18, q26] - | q28 : int(1..3)]) - | q26 : int(1..3)]) - | q20 : int(1..2)]) - | q18 : int(1..2)]), - and([or([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q32, q34] -> - or([q36 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q30] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q30, q36] = - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q32, q34] - | q36 : int(1..3)]) - | q34 : int(1..3)]) - /\ - and([q38 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q30] -> - or([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q32, q40] /\ - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q32, q40] = - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q30, q38] - | q40 : int(1..3)]) - | q38 : int(1..3)]) - | q32 : int(1..2)]) - | q30 : int(1..2)]) - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_3_4_4-solution000001.solution b/tests/exhaustive/basic/setOfSet04/expected/model_3_4_4-solution000001.solution deleted file mode 100644 index 3ec452354e..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_3_4_4-solution000001.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {1}} -$ Visualisation for x -$ -$ 1 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_3_4_4-solution000002.solution b/tests/exhaustive/basic/setOfSet04/expected/model_3_4_4-solution000002.solution deleted file mode 100644 index c8946f3d06..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_3_4_4-solution000002.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {2}} -$ Visualisation for x -$ -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_3_4_4-solution000003.solution b/tests/exhaustive/basic/setOfSet04/expected/model_3_4_4-solution000003.solution deleted file mode 100644 index af16592c51..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_3_4_4-solution000003.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1}, {2}} -$ Visualisation for x -$ 1 -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_3_4_4-solution000004.solution b/tests/exhaustive/basic/setOfSet04/expected/model_3_4_4-solution000004.solution deleted file mode 100644 index a6c0b6a43e..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_3_4_4-solution000004.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {1, 2}} -$ Visualisation for x -$ -$ 1 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_3_4_4-solution000005.solution b/tests/exhaustive/basic/setOfSet04/expected/model_3_4_4-solution000005.solution deleted file mode 100644 index 38937c9389..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_3_4_4-solution000005.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1}, {1, 2}} -$ Visualisation for x -$ 1 -$ 1 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_3_4_4-solution000006.solution b/tests/exhaustive/basic/setOfSet04/expected/model_3_4_4-solution000006.solution deleted file mode 100644 index 9bf2af0712..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_3_4_4-solution000006.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1, 2}, {2}} -$ Visualisation for x -$ 1 2 -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_3_4_4.eprime b/tests/exhaustive/basic/setOfSet04/expected/model_3_4_4.eprime deleted file mode 100644 index 473d929c0b..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_3_4_4.eprime +++ /dev/null @@ -1,81 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitR5_ExplicitVarSizeWithMarker_Marker: matrix indexed by [int(1..2)] of int(0..3) -find x_ExplicitR5_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..2), int(1..3)] of int(1..2) -find x_ExplicitR4_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..2), int(1..3)] of bool -find x_ExplicitR4_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..2), int(1..3)] of int(1..2) -branching on - [x_ExplicitR4_ExplicitVarSizeWithFlags_Flags, x_ExplicitR4_ExplicitVarSizeWithFlags_Values, - x_ExplicitR5_ExplicitVarSizeWithMarker_Marker, x_ExplicitR5_ExplicitVarSizeWithMarker_Values] -such that - flatten([[x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[1]; int(1)], - flatten([[x_ExplicitR5_ExplicitVarSizeWithMarker_Values[1, q6]; int(1)] | q6 : int(1..3)]); - int(1..2)]) - - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q2, q3] < - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q2, q3 + 1] - | q3 : int(1..2)]) - | q2 : int(1..2)]), - and([and([q4 > x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q2] -> - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q2, q4] = 1 - | q4 : int(1..3)]) - | q2 : int(1..2)]), - and([x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q2] <= 3 | q2 : int(1..2)]), - flatten([flatten([[-toInt(x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[1, q15]); int(1)], - [x_ExplicitR4_ExplicitVarSizeWithFlags_Values[1, q15]; int(1)]; - int(1..2)]) - | q15 : int(1..3)]) - - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q9, q10] < - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q9, q10 + 1] - | q10 : int(1..2)]) - | q9 : int(1..2)]), - and([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q9, q11] = false -> - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q9, q11] = 1 - | q11 : int(1..3)]) - | q9 : int(1..2)]), - and([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q9, q12 + 1] -> - x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q9, q12] - | q12 : int(1..2)]) - | q9 : int(1..2)]), - and([sum([toInt(x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q9, q13]) | q13 : int(1..3)]) <= 3 | q9 : int(1..2)]), - and([or([and([q22 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q20] -> - or([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q18, q24] /\ - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q18, q24] = - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q20, q22] - | q24 : int(1..3)]) - | q22 : int(1..3)]) - /\ - and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q18, q26] -> - or([q28 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q20] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q20, q28] = - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q18, q26] - | q28 : int(1..3)]) - | q26 : int(1..3)]) - | q20 : int(1..2)]) - | q18 : int(1..2)]), - and([or([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q32, q34] -> - or([q36 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q30] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q30, q36] = - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q32, q34] - | q36 : int(1..3)]) - | q34 : int(1..3)]) - /\ - and([q38 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q30] -> - or([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q32, q40] /\ - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q32, q40] = - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q30, q38] - | q40 : int(1..3)]) - | q38 : int(1..3)]) - | q32 : int(1..2)]) - | q30 : int(1..2)]) - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_4_1_1-solution000001.solution b/tests/exhaustive/basic/setOfSet04/expected/model_4_1_1-solution000001.solution deleted file mode 100644 index c8946f3d06..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_4_1_1-solution000001.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {2}} -$ Visualisation for x -$ -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_4_1_1-solution000002.solution b/tests/exhaustive/basic/setOfSet04/expected/model_4_1_1-solution000002.solution deleted file mode 100644 index 3ec452354e..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_4_1_1-solution000002.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {1}} -$ Visualisation for x -$ -$ 1 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_4_1_1-solution000003.solution b/tests/exhaustive/basic/setOfSet04/expected/model_4_1_1-solution000003.solution deleted file mode 100644 index af16592c51..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_4_1_1-solution000003.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1}, {2}} -$ Visualisation for x -$ 1 -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_4_1_1-solution000004.solution b/tests/exhaustive/basic/setOfSet04/expected/model_4_1_1-solution000004.solution deleted file mode 100644 index a6c0b6a43e..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_4_1_1-solution000004.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {1, 2}} -$ Visualisation for x -$ -$ 1 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_4_1_1-solution000005.solution b/tests/exhaustive/basic/setOfSet04/expected/model_4_1_1-solution000005.solution deleted file mode 100644 index 9bf2af0712..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_4_1_1-solution000005.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1, 2}, {2}} -$ Visualisation for x -$ 1 2 -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_4_1_1-solution000006.solution b/tests/exhaustive/basic/setOfSet04/expected/model_4_1_1-solution000006.solution deleted file mode 100644 index 38937c9389..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_4_1_1-solution000006.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1}, {1, 2}} -$ Visualisation for x -$ 1 -$ 1 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_4_1_1.eprime b/tests/exhaustive/basic/setOfSet04/expected/model_4_1_1.eprime deleted file mode 100644 index c7f842826d..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_4_1_1.eprime +++ /dev/null @@ -1,57 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitR4_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..2), int(1..3)] of bool -find x_ExplicitR4_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..2), int(1..3)] of int(1..2) -find x_ExplicitR2_Occurrence: matrix indexed by [int(1..2), int(1..2)] of bool -branching on - [x_ExplicitR2_Occurrence, x_ExplicitR4_ExplicitVarSizeWithFlags_Flags, x_ExplicitR4_ExplicitVarSizeWithFlags_Values] -such that - flatten([flatten([[-toInt(x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[1, q8]); int(1)], - [x_ExplicitR4_ExplicitVarSizeWithFlags_Values[1, q8]; int(1)]; - int(1..2)]) - | q8 : int(1..3)]) - - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q2, q3] < - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q2, q3 + 1] - | q3 : int(1..2)]) - | q2 : int(1..2)]), - and([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q2, q4] = false -> - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q2, q4] = 1 - | q4 : int(1..3)]) - | q2 : int(1..2)]), - and([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q2, q5 + 1] -> - x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q2, q5] - | q5 : int(1..2)]) - | q2 : int(1..2)]), - and([sum([toInt(x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q2, q6]) | q6 : int(1..3)]) <= 3 | q2 : int(1..2)]), - [-toInt(x_ExplicitR2_Occurrence[1, q13]) | q13 : int(1..2)] - x_ExplicitR2_Occurrence[q16, x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q18, q20]] - | q20 : int(1..3)]) - /\ - and([x_ExplicitR2_Occurrence[q16, q21] -> - or([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q18, q23] /\ - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q18, q23] = q21 - | q23 : int(1..3)]) - | q21 : int(1..2)]) - | q18 : int(1..2)]) - | q16 : int(1..2)]), - and([or([and([x_ExplicitR2_Occurrence[q27, q28] -> - or([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q25, q30] /\ - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q25, q30] = q28 - | q30 : int(1..3)]) - | q28 : int(1..2)]) - /\ - and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q25, q32] -> - x_ExplicitR2_Occurrence[q27, x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q25, q32]] - | q32 : int(1..3)]) - | q27 : int(1..2)]) - | q25 : int(1..2)]) - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_4_1_2-solution000001.solution b/tests/exhaustive/basic/setOfSet04/expected/model_4_1_2-solution000001.solution deleted file mode 100644 index 38937c9389..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_4_1_2-solution000001.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1}, {1, 2}} -$ Visualisation for x -$ 1 -$ 1 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_4_1_2-solution000002.solution b/tests/exhaustive/basic/setOfSet04/expected/model_4_1_2-solution000002.solution deleted file mode 100644 index 9bf2af0712..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_4_1_2-solution000002.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1, 2}, {2}} -$ Visualisation for x -$ 1 2 -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_4_1_2-solution000003.solution b/tests/exhaustive/basic/setOfSet04/expected/model_4_1_2-solution000003.solution deleted file mode 100644 index a6c0b6a43e..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_4_1_2-solution000003.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {1, 2}} -$ Visualisation for x -$ -$ 1 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_4_1_2-solution000004.solution b/tests/exhaustive/basic/setOfSet04/expected/model_4_1_2-solution000004.solution deleted file mode 100644 index af16592c51..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_4_1_2-solution000004.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1}, {2}} -$ Visualisation for x -$ 1 -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_4_1_2-solution000005.solution b/tests/exhaustive/basic/setOfSet04/expected/model_4_1_2-solution000005.solution deleted file mode 100644 index 3ec452354e..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_4_1_2-solution000005.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {1}} -$ Visualisation for x -$ -$ 1 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_4_1_2-solution000006.solution b/tests/exhaustive/basic/setOfSet04/expected/model_4_1_2-solution000006.solution deleted file mode 100644 index c8946f3d06..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_4_1_2-solution000006.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {2}} -$ Visualisation for x -$ -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_4_1_2.eprime b/tests/exhaustive/basic/setOfSet04/expected/model_4_1_2.eprime deleted file mode 100644 index b766299560..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_4_1_2.eprime +++ /dev/null @@ -1,122 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitR4_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..2), int(1..3)] of bool -find x_ExplicitR4_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..2), int(1..3)] of int(1..2) -find x_ExplicitR2_Occurrence: matrix indexed by [int(1..2), int(1..2)] of bool -find x_ExplicitR6_ExplicitVarSizeWithDummy: matrix indexed by [int(1..2), int(1..3)] of int(1..3) -branching on - [x_ExplicitR6_ExplicitVarSizeWithDummy, x_ExplicitR4_ExplicitVarSizeWithFlags_Flags, - x_ExplicitR4_ExplicitVarSizeWithFlags_Values, x_ExplicitR2_Occurrence] -such that - flatten([flatten([[-toInt(x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[1, q8]); int(1)], - [x_ExplicitR4_ExplicitVarSizeWithFlags_Values[1, q8]; int(1)]; - int(1..2)]) - | q8 : int(1..3)]) - - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q2, q3] < - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q2, q3 + 1] - | q3 : int(1..2)]) - | q2 : int(1..2)]), - and([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q2, q4] = false -> - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q2, q4] = 1 - | q4 : int(1..3)]) - | q2 : int(1..2)]), - and([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q2, q5 + 1] -> - x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q2, q5] - | q5 : int(1..2)]) - | q2 : int(1..2)]), - and([sum([toInt(x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q2, q6]) | q6 : int(1..3)]) <= 3 | q2 : int(1..2)]), - [-toInt(x_ExplicitR2_Occurrence[1, q13]) | q13 : int(1..2)] - x_ExplicitR2_Occurrence[q16, x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q18, q20]] - | q20 : int(1..3)]) - /\ - and([x_ExplicitR2_Occurrence[q16, q21] -> - or([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q18, q23] /\ - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q18, q23] = q21 - | q23 : int(1..3)]) - | q21 : int(1..2)]) - | q18 : int(1..2)]) - | q16 : int(1..2)]), - and([or([and([x_ExplicitR2_Occurrence[q27, q28] -> - or([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q25, q30] /\ - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q25, q30] = q28 - | q30 : int(1..3)]) - | q28 : int(1..2)]) - /\ - and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q25, q32] -> - x_ExplicitR2_Occurrence[q27, x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q25, q32]] - | q32 : int(1..3)]) - | q27 : int(1..2)]) - | q25 : int(1..2)]), - [x_ExplicitR6_ExplicitVarSizeWithDummy[1, q39] | q39 : int(1..3)] - x_ExplicitR6_ExplicitVarSizeWithDummy[q34, q36 + 1] = 3 - | q36 : int(1..2)]) - | q34 : int(1..2)]), - and([sum([toInt(x_ExplicitR6_ExplicitVarSizeWithDummy[q34, q37] != 3) | q37 : int(1..3)]) <= 3 | q34 : int(1..2)]), - and([or([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q44, q46] -> - or([x_ExplicitR6_ExplicitVarSizeWithDummy[q42, q48] != 3 /\ - x_ExplicitR6_ExplicitVarSizeWithDummy[q42, q48] = - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q44, q46] - | q48 : int(1..3)]) - | q46 : int(1..3)]) - /\ - and([x_ExplicitR6_ExplicitVarSizeWithDummy[q42, q50] != 3 -> - or([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q44, q52] /\ - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q44, q52] = - x_ExplicitR6_ExplicitVarSizeWithDummy[q42, q50] - | q52 : int(1..3)]) - | q50 : int(1..3)]) - | q44 : int(1..2)]) - | q42 : int(1..2)]), - and([or([and([x_ExplicitR6_ExplicitVarSizeWithDummy[q56, q58] != 3 -> - or([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q54, q60] /\ - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q54, q60] = - x_ExplicitR6_ExplicitVarSizeWithDummy[q56, q58] - | q60 : int(1..3)]) - | q58 : int(1..3)]) - /\ - and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q54, q62] -> - or([x_ExplicitR6_ExplicitVarSizeWithDummy[q56, q64] != 3 /\ - x_ExplicitR6_ExplicitVarSizeWithDummy[q56, q64] = - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q54, q62] - | q64 : int(1..3)]) - | q62 : int(1..3)]) - | q56 : int(1..2)]) - | q54 : int(1..2)]), - and([or([and([x_ExplicitR2_Occurrence[q68, q69] -> - or([x_ExplicitR6_ExplicitVarSizeWithDummy[q66, q71] != 3 /\ - x_ExplicitR6_ExplicitVarSizeWithDummy[q66, q71] = q69 - | q71 : int(1..3)]) - | q69 : int(1..2)]) - /\ - and([x_ExplicitR6_ExplicitVarSizeWithDummy[q66, q73] != 3 -> - x_ExplicitR2_Occurrence[q68, x_ExplicitR6_ExplicitVarSizeWithDummy[q66, q73]] - | q73 : int(1..3)]) - | q68 : int(1..2)]) - | q66 : int(1..2)]), - and([or([and([x_ExplicitR6_ExplicitVarSizeWithDummy[q77, q79] != 3 -> - x_ExplicitR2_Occurrence[q75, x_ExplicitR6_ExplicitVarSizeWithDummy[q77, q79]] - | q79 : int(1..3)]) - /\ - and([x_ExplicitR2_Occurrence[q75, q80] -> - or([x_ExplicitR6_ExplicitVarSizeWithDummy[q77, q82] != 3 /\ - x_ExplicitR6_ExplicitVarSizeWithDummy[q77, q82] = q80 - | q82 : int(1..3)]) - | q80 : int(1..2)]) - | q77 : int(1..2)]) - | q75 : int(1..2)]) - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_4_1_3-solution000001.solution b/tests/exhaustive/basic/setOfSet04/expected/model_4_1_3-solution000001.solution deleted file mode 100644 index 3ec452354e..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_4_1_3-solution000001.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {1}} -$ Visualisation for x -$ -$ 1 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_4_1_3-solution000002.solution b/tests/exhaustive/basic/setOfSet04/expected/model_4_1_3-solution000002.solution deleted file mode 100644 index c8946f3d06..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_4_1_3-solution000002.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {2}} -$ Visualisation for x -$ -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_4_1_3-solution000003.solution b/tests/exhaustive/basic/setOfSet04/expected/model_4_1_3-solution000003.solution deleted file mode 100644 index a6c0b6a43e..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_4_1_3-solution000003.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {1, 2}} -$ Visualisation for x -$ -$ 1 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_4_1_3-solution000004.solution b/tests/exhaustive/basic/setOfSet04/expected/model_4_1_3-solution000004.solution deleted file mode 100644 index af16592c51..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_4_1_3-solution000004.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1}, {2}} -$ Visualisation for x -$ 1 -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_4_1_3-solution000005.solution b/tests/exhaustive/basic/setOfSet04/expected/model_4_1_3-solution000005.solution deleted file mode 100644 index 38937c9389..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_4_1_3-solution000005.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1}, {1, 2}} -$ Visualisation for x -$ 1 -$ 1 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_4_1_3-solution000006.solution b/tests/exhaustive/basic/setOfSet04/expected/model_4_1_3-solution000006.solution deleted file mode 100644 index 9bf2af0712..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_4_1_3-solution000006.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1, 2}, {2}} -$ Visualisation for x -$ 1 2 -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_4_1_3.eprime b/tests/exhaustive/basic/setOfSet04/expected/model_4_1_3.eprime deleted file mode 100644 index 5dc923e40f..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_4_1_3.eprime +++ /dev/null @@ -1,129 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitR4_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..2), int(1..3)] of bool -find x_ExplicitR4_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..2), int(1..3)] of int(1..2) -find x_ExplicitR2_Occurrence: matrix indexed by [int(1..2), int(1..2)] of bool -find x_ExplicitR5_ExplicitVarSizeWithMarker_Marker: matrix indexed by [int(1..2)] of int(0..3) -find x_ExplicitR5_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..2), int(1..3)] of int(1..2) -branching on - [x_ExplicitR5_ExplicitVarSizeWithMarker_Marker, x_ExplicitR5_ExplicitVarSizeWithMarker_Values, - x_ExplicitR4_ExplicitVarSizeWithFlags_Flags, x_ExplicitR4_ExplicitVarSizeWithFlags_Values, x_ExplicitR2_Occurrence] -such that - flatten([flatten([[-toInt(x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[1, q8]); int(1)], - [x_ExplicitR4_ExplicitVarSizeWithFlags_Values[1, q8]; int(1)]; - int(1..2)]) - | q8 : int(1..3)]) - - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q2, q3] < - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q2, q3 + 1] - | q3 : int(1..2)]) - | q2 : int(1..2)]), - and([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q2, q4] = false -> - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q2, q4] = 1 - | q4 : int(1..3)]) - | q2 : int(1..2)]), - and([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q2, q5 + 1] -> - x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q2, q5] - | q5 : int(1..2)]) - | q2 : int(1..2)]), - and([sum([toInt(x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q2, q6]) | q6 : int(1..3)]) <= 3 | q2 : int(1..2)]), - [-toInt(x_ExplicitR2_Occurrence[1, q13]) | q13 : int(1..2)] - x_ExplicitR2_Occurrence[q16, x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q18, q20]] - | q20 : int(1..3)]) - /\ - and([x_ExplicitR2_Occurrence[q16, q21] -> - or([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q18, q23] /\ - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q18, q23] = q21 - | q23 : int(1..3)]) - | q21 : int(1..2)]) - | q18 : int(1..2)]) - | q16 : int(1..2)]), - and([or([and([x_ExplicitR2_Occurrence[q27, q28] -> - or([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q25, q30] /\ - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q25, q30] = q28 - | q30 : int(1..3)]) - | q28 : int(1..2)]) - /\ - and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q25, q32] -> - x_ExplicitR2_Occurrence[q27, x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q25, q32]] - | q32 : int(1..3)]) - | q27 : int(1..2)]) - | q25 : int(1..2)]), - flatten([[x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[1]; int(1)], - flatten([[x_ExplicitR5_ExplicitVarSizeWithMarker_Values[1, q38]; int(1)] | q38 : int(1..3)]); - int(1..2)]) - - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q34, q35] < - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q34, q35 + 1] - | q35 : int(1..2)]) - | q34 : int(1..2)]), - and([and([q36 > x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q34] -> - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q34, q36] = 1 - | q36 : int(1..3)]) - | q34 : int(1..2)]), - and([x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q34] <= 3 | q34 : int(1..2)]), - and([or([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q43, q45] -> - or([q47 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q41] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q41, q47] = - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q43, q45] - | q47 : int(1..3)]) - | q45 : int(1..3)]) - /\ - and([q49 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q41] -> - or([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q43, q51] /\ - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q43, q51] = - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q41, q49] - | q51 : int(1..3)]) - | q49 : int(1..3)]) - | q43 : int(1..2)]) - | q41 : int(1..2)]), - and([or([and([q57 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q55] -> - or([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q53, q59] /\ - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q53, q59] = - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q55, q57] - | q59 : int(1..3)]) - | q57 : int(1..3)]) - /\ - and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q53, q61] -> - or([q63 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q55] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q55, q63] = - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q53, q61] - | q63 : int(1..3)]) - | q61 : int(1..3)]) - | q55 : int(1..2)]) - | q53 : int(1..2)]), - and([or([and([x_ExplicitR2_Occurrence[q67, q68] -> - or([q70 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q65] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q65, q70] = q68 - | q70 : int(1..3)]) - | q68 : int(1..2)]) - /\ - and([q72 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q65] -> - x_ExplicitR2_Occurrence[q67, x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q65, q72]] - | q72 : int(1..3)]) - | q67 : int(1..2)]) - | q65 : int(1..2)]), - and([or([and([q78 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q76] -> - x_ExplicitR2_Occurrence[q74, x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q76, q78]] - | q78 : int(1..3)]) - /\ - and([x_ExplicitR2_Occurrence[q74, q79] -> - or([q81 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q76] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q76, q81] = q79 - | q81 : int(1..3)]) - | q79 : int(1..2)]) - | q76 : int(1..2)]) - | q74 : int(1..2)]) - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_4_1_4-solution000001.solution b/tests/exhaustive/basic/setOfSet04/expected/model_4_1_4-solution000001.solution deleted file mode 100644 index c8946f3d06..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_4_1_4-solution000001.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {2}} -$ Visualisation for x -$ -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_4_1_4-solution000002.solution b/tests/exhaustive/basic/setOfSet04/expected/model_4_1_4-solution000002.solution deleted file mode 100644 index 3ec452354e..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_4_1_4-solution000002.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {1}} -$ Visualisation for x -$ -$ 1 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_4_1_4-solution000003.solution b/tests/exhaustive/basic/setOfSet04/expected/model_4_1_4-solution000003.solution deleted file mode 100644 index af16592c51..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_4_1_4-solution000003.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1}, {2}} -$ Visualisation for x -$ 1 -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_4_1_4-solution000004.solution b/tests/exhaustive/basic/setOfSet04/expected/model_4_1_4-solution000004.solution deleted file mode 100644 index a6c0b6a43e..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_4_1_4-solution000004.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {1, 2}} -$ Visualisation for x -$ -$ 1 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_4_1_4-solution000005.solution b/tests/exhaustive/basic/setOfSet04/expected/model_4_1_4-solution000005.solution deleted file mode 100644 index 9bf2af0712..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_4_1_4-solution000005.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1, 2}, {2}} -$ Visualisation for x -$ 1 2 -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_4_1_4-solution000006.solution b/tests/exhaustive/basic/setOfSet04/expected/model_4_1_4-solution000006.solution deleted file mode 100644 index 38937c9389..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_4_1_4-solution000006.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1}, {1, 2}} -$ Visualisation for x -$ 1 -$ 1 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_4_1_4.eprime b/tests/exhaustive/basic/setOfSet04/expected/model_4_1_4.eprime deleted file mode 100644 index c7f842826d..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_4_1_4.eprime +++ /dev/null @@ -1,57 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitR4_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..2), int(1..3)] of bool -find x_ExplicitR4_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..2), int(1..3)] of int(1..2) -find x_ExplicitR2_Occurrence: matrix indexed by [int(1..2), int(1..2)] of bool -branching on - [x_ExplicitR2_Occurrence, x_ExplicitR4_ExplicitVarSizeWithFlags_Flags, x_ExplicitR4_ExplicitVarSizeWithFlags_Values] -such that - flatten([flatten([[-toInt(x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[1, q8]); int(1)], - [x_ExplicitR4_ExplicitVarSizeWithFlags_Values[1, q8]; int(1)]; - int(1..2)]) - | q8 : int(1..3)]) - - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q2, q3] < - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q2, q3 + 1] - | q3 : int(1..2)]) - | q2 : int(1..2)]), - and([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q2, q4] = false -> - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q2, q4] = 1 - | q4 : int(1..3)]) - | q2 : int(1..2)]), - and([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q2, q5 + 1] -> - x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q2, q5] - | q5 : int(1..2)]) - | q2 : int(1..2)]), - and([sum([toInt(x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q2, q6]) | q6 : int(1..3)]) <= 3 | q2 : int(1..2)]), - [-toInt(x_ExplicitR2_Occurrence[1, q13]) | q13 : int(1..2)] - x_ExplicitR2_Occurrence[q16, x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q18, q20]] - | q20 : int(1..3)]) - /\ - and([x_ExplicitR2_Occurrence[q16, q21] -> - or([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q18, q23] /\ - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q18, q23] = q21 - | q23 : int(1..3)]) - | q21 : int(1..2)]) - | q18 : int(1..2)]) - | q16 : int(1..2)]), - and([or([and([x_ExplicitR2_Occurrence[q27, q28] -> - or([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q25, q30] /\ - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q25, q30] = q28 - | q30 : int(1..3)]) - | q28 : int(1..2)]) - /\ - and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q25, q32] -> - x_ExplicitR2_Occurrence[q27, x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q25, q32]] - | q32 : int(1..3)]) - | q27 : int(1..2)]) - | q25 : int(1..2)]) - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_4_2_1-solution000001.solution b/tests/exhaustive/basic/setOfSet04/expected/model_4_2_1-solution000001.solution deleted file mode 100644 index c8946f3d06..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_4_2_1-solution000001.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {2}} -$ Visualisation for x -$ -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_4_2_1-solution000002.solution b/tests/exhaustive/basic/setOfSet04/expected/model_4_2_1-solution000002.solution deleted file mode 100644 index 3ec452354e..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_4_2_1-solution000002.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {1}} -$ Visualisation for x -$ -$ 1 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_4_2_1-solution000003.solution b/tests/exhaustive/basic/setOfSet04/expected/model_4_2_1-solution000003.solution deleted file mode 100644 index af16592c51..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_4_2_1-solution000003.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1}, {2}} -$ Visualisation for x -$ 1 -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_4_2_1-solution000004.solution b/tests/exhaustive/basic/setOfSet04/expected/model_4_2_1-solution000004.solution deleted file mode 100644 index a6c0b6a43e..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_4_2_1-solution000004.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {1, 2}} -$ Visualisation for x -$ -$ 1 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_4_2_1-solution000005.solution b/tests/exhaustive/basic/setOfSet04/expected/model_4_2_1-solution000005.solution deleted file mode 100644 index 9bf2af0712..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_4_2_1-solution000005.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1, 2}, {2}} -$ Visualisation for x -$ 1 2 -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_4_2_1-solution000006.solution b/tests/exhaustive/basic/setOfSet04/expected/model_4_2_1-solution000006.solution deleted file mode 100644 index 38937c9389..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_4_2_1-solution000006.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1}, {1, 2}} -$ Visualisation for x -$ 1 -$ 1 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_4_2_1.eprime b/tests/exhaustive/basic/setOfSet04/expected/model_4_2_1.eprime deleted file mode 100644 index 972c2b1a63..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_4_2_1.eprime +++ /dev/null @@ -1,122 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitR4_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..2), int(1..3)] of bool -find x_ExplicitR4_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..2), int(1..3)] of int(1..2) -find x_ExplicitR6_ExplicitVarSizeWithDummy: matrix indexed by [int(1..2), int(1..3)] of int(1..3) -find x_ExplicitR2_Occurrence: matrix indexed by [int(1..2), int(1..2)] of bool -branching on - [x_ExplicitR2_Occurrence, x_ExplicitR4_ExplicitVarSizeWithFlags_Flags, x_ExplicitR4_ExplicitVarSizeWithFlags_Values, - x_ExplicitR6_ExplicitVarSizeWithDummy] -such that - flatten([flatten([[-toInt(x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[1, q8]); int(1)], - [x_ExplicitR4_ExplicitVarSizeWithFlags_Values[1, q8]; int(1)]; - int(1..2)]) - | q8 : int(1..3)]) - - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q2, q3] < - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q2, q3 + 1] - | q3 : int(1..2)]) - | q2 : int(1..2)]), - and([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q2, q4] = false -> - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q2, q4] = 1 - | q4 : int(1..3)]) - | q2 : int(1..2)]), - and([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q2, q5 + 1] -> - x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q2, q5] - | q5 : int(1..2)]) - | q2 : int(1..2)]), - and([sum([toInt(x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q2, q6]) | q6 : int(1..3)]) <= 3 | q2 : int(1..2)]), - [x_ExplicitR6_ExplicitVarSizeWithDummy[1, q16] | q16 : int(1..3)] - x_ExplicitR6_ExplicitVarSizeWithDummy[q11, q13 + 1] = 3 - | q13 : int(1..2)]) - | q11 : int(1..2)]), - and([sum([toInt(x_ExplicitR6_ExplicitVarSizeWithDummy[q11, q14] != 3) | q14 : int(1..3)]) <= 3 | q11 : int(1..2)]), - and([or([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q21, q23] -> - or([x_ExplicitR6_ExplicitVarSizeWithDummy[q19, q25] != 3 /\ - x_ExplicitR6_ExplicitVarSizeWithDummy[q19, q25] = - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q21, q23] - | q25 : int(1..3)]) - | q23 : int(1..3)]) - /\ - and([x_ExplicitR6_ExplicitVarSizeWithDummy[q19, q27] != 3 -> - or([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q21, q29] /\ - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q21, q29] = - x_ExplicitR6_ExplicitVarSizeWithDummy[q19, q27] - | q29 : int(1..3)]) - | q27 : int(1..3)]) - | q21 : int(1..2)]) - | q19 : int(1..2)]), - and([or([and([x_ExplicitR6_ExplicitVarSizeWithDummy[q33, q35] != 3 -> - or([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q31, q37] /\ - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q31, q37] = - x_ExplicitR6_ExplicitVarSizeWithDummy[q33, q35] - | q37 : int(1..3)]) - | q35 : int(1..3)]) - /\ - and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q31, q39] -> - or([x_ExplicitR6_ExplicitVarSizeWithDummy[q33, q41] != 3 /\ - x_ExplicitR6_ExplicitVarSizeWithDummy[q33, q41] = - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q31, q39] - | q41 : int(1..3)]) - | q39 : int(1..3)]) - | q33 : int(1..2)]) - | q31 : int(1..2)]), - [-toInt(x_ExplicitR2_Occurrence[1, q45]) | q45 : int(1..2)] - x_ExplicitR2_Occurrence[q48, x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q50, q52]] - | q52 : int(1..3)]) - /\ - and([x_ExplicitR2_Occurrence[q48, q53] -> - or([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q50, q55] /\ - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q50, q55] = q53 - | q55 : int(1..3)]) - | q53 : int(1..2)]) - | q50 : int(1..2)]) - | q48 : int(1..2)]), - and([or([and([x_ExplicitR2_Occurrence[q59, q60] -> - or([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q57, q62] /\ - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q57, q62] = q60 - | q62 : int(1..3)]) - | q60 : int(1..2)]) - /\ - and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q57, q64] -> - x_ExplicitR2_Occurrence[q59, x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q57, q64]] - | q64 : int(1..3)]) - | q59 : int(1..2)]) - | q57 : int(1..2)]), - and([or([and([x_ExplicitR6_ExplicitVarSizeWithDummy[q68, q70] != 3 -> - x_ExplicitR2_Occurrence[q66, x_ExplicitR6_ExplicitVarSizeWithDummy[q68, q70]] - | q70 : int(1..3)]) - /\ - and([x_ExplicitR2_Occurrence[q66, q71] -> - or([x_ExplicitR6_ExplicitVarSizeWithDummy[q68, q73] != 3 /\ - x_ExplicitR6_ExplicitVarSizeWithDummy[q68, q73] = q71 - | q73 : int(1..3)]) - | q71 : int(1..2)]) - | q68 : int(1..2)]) - | q66 : int(1..2)]), - and([or([and([x_ExplicitR2_Occurrence[q77, q78] -> - or([x_ExplicitR6_ExplicitVarSizeWithDummy[q75, q80] != 3 /\ - x_ExplicitR6_ExplicitVarSizeWithDummy[q75, q80] = q78 - | q80 : int(1..3)]) - | q78 : int(1..2)]) - /\ - and([x_ExplicitR6_ExplicitVarSizeWithDummy[q75, q82] != 3 -> - x_ExplicitR2_Occurrence[q77, x_ExplicitR6_ExplicitVarSizeWithDummy[q75, q82]] - | q82 : int(1..3)]) - | q77 : int(1..2)]) - | q75 : int(1..2)]) - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_4_2_2-solution000001.solution b/tests/exhaustive/basic/setOfSet04/expected/model_4_2_2-solution000001.solution deleted file mode 100644 index 38937c9389..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_4_2_2-solution000001.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1}, {1, 2}} -$ Visualisation for x -$ 1 -$ 1 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_4_2_2-solution000002.solution b/tests/exhaustive/basic/setOfSet04/expected/model_4_2_2-solution000002.solution deleted file mode 100644 index 9bf2af0712..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_4_2_2-solution000002.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1, 2}, {2}} -$ Visualisation for x -$ 1 2 -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_4_2_2-solution000003.solution b/tests/exhaustive/basic/setOfSet04/expected/model_4_2_2-solution000003.solution deleted file mode 100644 index a6c0b6a43e..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_4_2_2-solution000003.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {1, 2}} -$ Visualisation for x -$ -$ 1 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_4_2_2-solution000004.solution b/tests/exhaustive/basic/setOfSet04/expected/model_4_2_2-solution000004.solution deleted file mode 100644 index af16592c51..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_4_2_2-solution000004.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1}, {2}} -$ Visualisation for x -$ 1 -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_4_2_2-solution000005.solution b/tests/exhaustive/basic/setOfSet04/expected/model_4_2_2-solution000005.solution deleted file mode 100644 index 3ec452354e..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_4_2_2-solution000005.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {1}} -$ Visualisation for x -$ -$ 1 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_4_2_2-solution000006.solution b/tests/exhaustive/basic/setOfSet04/expected/model_4_2_2-solution000006.solution deleted file mode 100644 index c8946f3d06..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_4_2_2-solution000006.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {2}} -$ Visualisation for x -$ -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_4_2_2.eprime b/tests/exhaustive/basic/setOfSet04/expected/model_4_2_2.eprime deleted file mode 100644 index 048ac1ff0c..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_4_2_2.eprime +++ /dev/null @@ -1,74 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitR4_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..2), int(1..3)] of bool -find x_ExplicitR4_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..2), int(1..3)] of int(1..2) -find x_ExplicitR6_ExplicitVarSizeWithDummy: matrix indexed by [int(1..2), int(1..3)] of int(1..3) -branching on - [x_ExplicitR6_ExplicitVarSizeWithDummy, x_ExplicitR4_ExplicitVarSizeWithFlags_Flags, - x_ExplicitR4_ExplicitVarSizeWithFlags_Values] -such that - flatten([flatten([[-toInt(x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[1, q8]); int(1)], - [x_ExplicitR4_ExplicitVarSizeWithFlags_Values[1, q8]; int(1)]; - int(1..2)]) - | q8 : int(1..3)]) - - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q2, q3] < - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q2, q3 + 1] - | q3 : int(1..2)]) - | q2 : int(1..2)]), - and([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q2, q4] = false -> - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q2, q4] = 1 - | q4 : int(1..3)]) - | q2 : int(1..2)]), - and([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q2, q5 + 1] -> - x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q2, q5] - | q5 : int(1..2)]) - | q2 : int(1..2)]), - and([sum([toInt(x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q2, q6]) | q6 : int(1..3)]) <= 3 | q2 : int(1..2)]), - [x_ExplicitR6_ExplicitVarSizeWithDummy[1, q16] | q16 : int(1..3)] - x_ExplicitR6_ExplicitVarSizeWithDummy[q11, q13 + 1] = 3 - | q13 : int(1..2)]) - | q11 : int(1..2)]), - and([sum([toInt(x_ExplicitR6_ExplicitVarSizeWithDummy[q11, q14] != 3) | q14 : int(1..3)]) <= 3 | q11 : int(1..2)]), - and([or([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q21, q23] -> - or([x_ExplicitR6_ExplicitVarSizeWithDummy[q19, q25] != 3 /\ - x_ExplicitR6_ExplicitVarSizeWithDummy[q19, q25] = - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q21, q23] - | q25 : int(1..3)]) - | q23 : int(1..3)]) - /\ - and([x_ExplicitR6_ExplicitVarSizeWithDummy[q19, q27] != 3 -> - or([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q21, q29] /\ - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q21, q29] = - x_ExplicitR6_ExplicitVarSizeWithDummy[q19, q27] - | q29 : int(1..3)]) - | q27 : int(1..3)]) - | q21 : int(1..2)]) - | q19 : int(1..2)]), - and([or([and([x_ExplicitR6_ExplicitVarSizeWithDummy[q33, q35] != 3 -> - or([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q31, q37] /\ - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q31, q37] = - x_ExplicitR6_ExplicitVarSizeWithDummy[q33, q35] - | q37 : int(1..3)]) - | q35 : int(1..3)]) - /\ - and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q31, q39] -> - or([x_ExplicitR6_ExplicitVarSizeWithDummy[q33, q41] != 3 /\ - x_ExplicitR6_ExplicitVarSizeWithDummy[q33, q41] = - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q31, q39] - | q41 : int(1..3)]) - | q39 : int(1..3)]) - | q33 : int(1..2)]) - | q31 : int(1..2)]) - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_4_2_3-solution000001.solution b/tests/exhaustive/basic/setOfSet04/expected/model_4_2_3-solution000001.solution deleted file mode 100644 index 3ec452354e..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_4_2_3-solution000001.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {1}} -$ Visualisation for x -$ -$ 1 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_4_2_3-solution000002.solution b/tests/exhaustive/basic/setOfSet04/expected/model_4_2_3-solution000002.solution deleted file mode 100644 index c8946f3d06..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_4_2_3-solution000002.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {2}} -$ Visualisation for x -$ -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_4_2_3-solution000003.solution b/tests/exhaustive/basic/setOfSet04/expected/model_4_2_3-solution000003.solution deleted file mode 100644 index a6c0b6a43e..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_4_2_3-solution000003.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {1, 2}} -$ Visualisation for x -$ -$ 1 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_4_2_3-solution000004.solution b/tests/exhaustive/basic/setOfSet04/expected/model_4_2_3-solution000004.solution deleted file mode 100644 index af16592c51..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_4_2_3-solution000004.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1}, {2}} -$ Visualisation for x -$ 1 -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_4_2_3-solution000005.solution b/tests/exhaustive/basic/setOfSet04/expected/model_4_2_3-solution000005.solution deleted file mode 100644 index 38937c9389..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_4_2_3-solution000005.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1}, {1, 2}} -$ Visualisation for x -$ 1 -$ 1 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_4_2_3-solution000006.solution b/tests/exhaustive/basic/setOfSet04/expected/model_4_2_3-solution000006.solution deleted file mode 100644 index 9bf2af0712..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_4_2_3-solution000006.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1, 2}, {2}} -$ Visualisation for x -$ 1 2 -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_4_2_3.eprime b/tests/exhaustive/basic/setOfSet04/expected/model_4_2_3.eprime deleted file mode 100644 index ffd9fa8baf..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_4_2_3.eprime +++ /dev/null @@ -1,154 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitR4_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..2), int(1..3)] of bool -find x_ExplicitR4_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..2), int(1..3)] of int(1..2) -find x_ExplicitR6_ExplicitVarSizeWithDummy: matrix indexed by [int(1..2), int(1..3)] of int(1..3) -find x_ExplicitR5_ExplicitVarSizeWithMarker_Marker: matrix indexed by [int(1..2)] of int(0..3) -find x_ExplicitR5_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..2), int(1..3)] of int(1..2) -branching on - [x_ExplicitR5_ExplicitVarSizeWithMarker_Marker, x_ExplicitR5_ExplicitVarSizeWithMarker_Values, - x_ExplicitR4_ExplicitVarSizeWithFlags_Flags, x_ExplicitR4_ExplicitVarSizeWithFlags_Values, - x_ExplicitR6_ExplicitVarSizeWithDummy] -such that - flatten([flatten([[-toInt(x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[1, q8]); int(1)], - [x_ExplicitR4_ExplicitVarSizeWithFlags_Values[1, q8]; int(1)]; - int(1..2)]) - | q8 : int(1..3)]) - - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q2, q3] < - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q2, q3 + 1] - | q3 : int(1..2)]) - | q2 : int(1..2)]), - and([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q2, q4] = false -> - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q2, q4] = 1 - | q4 : int(1..3)]) - | q2 : int(1..2)]), - and([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q2, q5 + 1] -> - x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q2, q5] - | q5 : int(1..2)]) - | q2 : int(1..2)]), - and([sum([toInt(x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q2, q6]) | q6 : int(1..3)]) <= 3 | q2 : int(1..2)]), - [x_ExplicitR6_ExplicitVarSizeWithDummy[1, q16] | q16 : int(1..3)] - x_ExplicitR6_ExplicitVarSizeWithDummy[q11, q13 + 1] = 3 - | q13 : int(1..2)]) - | q11 : int(1..2)]), - and([sum([toInt(x_ExplicitR6_ExplicitVarSizeWithDummy[q11, q14] != 3) | q14 : int(1..3)]) <= 3 | q11 : int(1..2)]), - and([or([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q21, q23] -> - or([x_ExplicitR6_ExplicitVarSizeWithDummy[q19, q25] != 3 /\ - x_ExplicitR6_ExplicitVarSizeWithDummy[q19, q25] = - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q21, q23] - | q25 : int(1..3)]) - | q23 : int(1..3)]) - /\ - and([x_ExplicitR6_ExplicitVarSizeWithDummy[q19, q27] != 3 -> - or([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q21, q29] /\ - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q21, q29] = - x_ExplicitR6_ExplicitVarSizeWithDummy[q19, q27] - | q29 : int(1..3)]) - | q27 : int(1..3)]) - | q21 : int(1..2)]) - | q19 : int(1..2)]), - and([or([and([x_ExplicitR6_ExplicitVarSizeWithDummy[q33, q35] != 3 -> - or([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q31, q37] /\ - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q31, q37] = - x_ExplicitR6_ExplicitVarSizeWithDummy[q33, q35] - | q37 : int(1..3)]) - | q35 : int(1..3)]) - /\ - and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q31, q39] -> - or([x_ExplicitR6_ExplicitVarSizeWithDummy[q33, q41] != 3 /\ - x_ExplicitR6_ExplicitVarSizeWithDummy[q33, q41] = - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q31, q39] - | q41 : int(1..3)]) - | q39 : int(1..3)]) - | q33 : int(1..2)]) - | q31 : int(1..2)]), - flatten([[x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[1]; int(1)], - flatten([[x_ExplicitR5_ExplicitVarSizeWithMarker_Values[1, q47]; int(1)] | q47 : int(1..3)]); - int(1..2)]) - - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q43, q44] < - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q43, q44 + 1] - | q44 : int(1..2)]) - | q43 : int(1..2)]), - and([and([q45 > x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q43] -> - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q43, q45] = 1 - | q45 : int(1..3)]) - | q43 : int(1..2)]), - and([x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q43] <= 3 | q43 : int(1..2)]), - and([or([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q52, q54] -> - or([q56 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q50] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q50, q56] = - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q52, q54] - | q56 : int(1..3)]) - | q54 : int(1..3)]) - /\ - and([q58 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q50] -> - or([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q52, q60] /\ - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q52, q60] = - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q50, q58] - | q60 : int(1..3)]) - | q58 : int(1..3)]) - | q52 : int(1..2)]) - | q50 : int(1..2)]), - and([or([and([q66 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q64] -> - or([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q62, q68] /\ - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q62, q68] = - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q64, q66] - | q68 : int(1..3)]) - | q66 : int(1..3)]) - /\ - and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q62, q70] -> - or([q72 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q64] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q64, q72] = - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q62, q70] - | q72 : int(1..3)]) - | q70 : int(1..3)]) - | q64 : int(1..2)]) - | q62 : int(1..2)]), - and([or([and([x_ExplicitR6_ExplicitVarSizeWithDummy[q76, q78] != 3 -> - or([q80 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q74] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q74, q80] = - x_ExplicitR6_ExplicitVarSizeWithDummy[q76, q78] - | q80 : int(1..3)]) - | q78 : int(1..3)]) - /\ - and([q82 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q74] -> - or([x_ExplicitR6_ExplicitVarSizeWithDummy[q76, q84] != 3 /\ - x_ExplicitR6_ExplicitVarSizeWithDummy[q76, q84] = - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q74, q82] - | q84 : int(1..3)]) - | q82 : int(1..3)]) - | q76 : int(1..2)]) - | q74 : int(1..2)]), - and([or([and([q90 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q88] -> - or([x_ExplicitR6_ExplicitVarSizeWithDummy[q86, q92] != 3 /\ - x_ExplicitR6_ExplicitVarSizeWithDummy[q86, q92] = - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q88, q90] - | q92 : int(1..3)]) - | q90 : int(1..3)]) - /\ - and([x_ExplicitR6_ExplicitVarSizeWithDummy[q86, q94] != 3 -> - or([q96 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q88] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q88, q96] = - x_ExplicitR6_ExplicitVarSizeWithDummy[q86, q94] - | q96 : int(1..3)]) - | q94 : int(1..3)]) - | q88 : int(1..2)]) - | q86 : int(1..2)]) - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_4_2_4-solution000001.solution b/tests/exhaustive/basic/setOfSet04/expected/model_4_2_4-solution000001.solution deleted file mode 100644 index 38937c9389..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_4_2_4-solution000001.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1}, {1, 2}} -$ Visualisation for x -$ 1 -$ 1 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_4_2_4-solution000002.solution b/tests/exhaustive/basic/setOfSet04/expected/model_4_2_4-solution000002.solution deleted file mode 100644 index 9bf2af0712..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_4_2_4-solution000002.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1, 2}, {2}} -$ Visualisation for x -$ 1 2 -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_4_2_4-solution000003.solution b/tests/exhaustive/basic/setOfSet04/expected/model_4_2_4-solution000003.solution deleted file mode 100644 index a6c0b6a43e..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_4_2_4-solution000003.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {1, 2}} -$ Visualisation for x -$ -$ 1 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_4_2_4-solution000004.solution b/tests/exhaustive/basic/setOfSet04/expected/model_4_2_4-solution000004.solution deleted file mode 100644 index af16592c51..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_4_2_4-solution000004.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1}, {2}} -$ Visualisation for x -$ 1 -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_4_2_4-solution000005.solution b/tests/exhaustive/basic/setOfSet04/expected/model_4_2_4-solution000005.solution deleted file mode 100644 index 3ec452354e..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_4_2_4-solution000005.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {1}} -$ Visualisation for x -$ -$ 1 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_4_2_4-solution000006.solution b/tests/exhaustive/basic/setOfSet04/expected/model_4_2_4-solution000006.solution deleted file mode 100644 index c8946f3d06..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_4_2_4-solution000006.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {2}} -$ Visualisation for x -$ -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_4_2_4.eprime b/tests/exhaustive/basic/setOfSet04/expected/model_4_2_4.eprime deleted file mode 100644 index 048ac1ff0c..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_4_2_4.eprime +++ /dev/null @@ -1,74 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitR4_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..2), int(1..3)] of bool -find x_ExplicitR4_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..2), int(1..3)] of int(1..2) -find x_ExplicitR6_ExplicitVarSizeWithDummy: matrix indexed by [int(1..2), int(1..3)] of int(1..3) -branching on - [x_ExplicitR6_ExplicitVarSizeWithDummy, x_ExplicitR4_ExplicitVarSizeWithFlags_Flags, - x_ExplicitR4_ExplicitVarSizeWithFlags_Values] -such that - flatten([flatten([[-toInt(x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[1, q8]); int(1)], - [x_ExplicitR4_ExplicitVarSizeWithFlags_Values[1, q8]; int(1)]; - int(1..2)]) - | q8 : int(1..3)]) - - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q2, q3] < - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q2, q3 + 1] - | q3 : int(1..2)]) - | q2 : int(1..2)]), - and([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q2, q4] = false -> - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q2, q4] = 1 - | q4 : int(1..3)]) - | q2 : int(1..2)]), - and([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q2, q5 + 1] -> - x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q2, q5] - | q5 : int(1..2)]) - | q2 : int(1..2)]), - and([sum([toInt(x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q2, q6]) | q6 : int(1..3)]) <= 3 | q2 : int(1..2)]), - [x_ExplicitR6_ExplicitVarSizeWithDummy[1, q16] | q16 : int(1..3)] - x_ExplicitR6_ExplicitVarSizeWithDummy[q11, q13 + 1] = 3 - | q13 : int(1..2)]) - | q11 : int(1..2)]), - and([sum([toInt(x_ExplicitR6_ExplicitVarSizeWithDummy[q11, q14] != 3) | q14 : int(1..3)]) <= 3 | q11 : int(1..2)]), - and([or([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q21, q23] -> - or([x_ExplicitR6_ExplicitVarSizeWithDummy[q19, q25] != 3 /\ - x_ExplicitR6_ExplicitVarSizeWithDummy[q19, q25] = - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q21, q23] - | q25 : int(1..3)]) - | q23 : int(1..3)]) - /\ - and([x_ExplicitR6_ExplicitVarSizeWithDummy[q19, q27] != 3 -> - or([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q21, q29] /\ - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q21, q29] = - x_ExplicitR6_ExplicitVarSizeWithDummy[q19, q27] - | q29 : int(1..3)]) - | q27 : int(1..3)]) - | q21 : int(1..2)]) - | q19 : int(1..2)]), - and([or([and([x_ExplicitR6_ExplicitVarSizeWithDummy[q33, q35] != 3 -> - or([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q31, q37] /\ - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q31, q37] = - x_ExplicitR6_ExplicitVarSizeWithDummy[q33, q35] - | q37 : int(1..3)]) - | q35 : int(1..3)]) - /\ - and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q31, q39] -> - or([x_ExplicitR6_ExplicitVarSizeWithDummy[q33, q41] != 3 /\ - x_ExplicitR6_ExplicitVarSizeWithDummy[q33, q41] = - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q31, q39] - | q41 : int(1..3)]) - | q39 : int(1..3)]) - | q33 : int(1..2)]) - | q31 : int(1..2)]) - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_4_3_1-solution000001.solution b/tests/exhaustive/basic/setOfSet04/expected/model_4_3_1-solution000001.solution deleted file mode 100644 index c8946f3d06..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_4_3_1-solution000001.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {2}} -$ Visualisation for x -$ -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_4_3_1-solution000002.solution b/tests/exhaustive/basic/setOfSet04/expected/model_4_3_1-solution000002.solution deleted file mode 100644 index 3ec452354e..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_4_3_1-solution000002.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {1}} -$ Visualisation for x -$ -$ 1 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_4_3_1-solution000003.solution b/tests/exhaustive/basic/setOfSet04/expected/model_4_3_1-solution000003.solution deleted file mode 100644 index af16592c51..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_4_3_1-solution000003.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1}, {2}} -$ Visualisation for x -$ 1 -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_4_3_1-solution000004.solution b/tests/exhaustive/basic/setOfSet04/expected/model_4_3_1-solution000004.solution deleted file mode 100644 index a6c0b6a43e..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_4_3_1-solution000004.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {1, 2}} -$ Visualisation for x -$ -$ 1 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_4_3_1-solution000005.solution b/tests/exhaustive/basic/setOfSet04/expected/model_4_3_1-solution000005.solution deleted file mode 100644 index 9bf2af0712..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_4_3_1-solution000005.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1, 2}, {2}} -$ Visualisation for x -$ 1 2 -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_4_3_1-solution000006.solution b/tests/exhaustive/basic/setOfSet04/expected/model_4_3_1-solution000006.solution deleted file mode 100644 index 38937c9389..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_4_3_1-solution000006.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1}, {1, 2}} -$ Visualisation for x -$ 1 -$ 1 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_4_3_1.eprime b/tests/exhaustive/basic/setOfSet04/expected/model_4_3_1.eprime deleted file mode 100644 index 1dfcca3398..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_4_3_1.eprime +++ /dev/null @@ -1,129 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitR4_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..2), int(1..3)] of bool -find x_ExplicitR4_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..2), int(1..3)] of int(1..2) -find x_ExplicitR5_ExplicitVarSizeWithMarker_Marker: matrix indexed by [int(1..2)] of int(0..3) -find x_ExplicitR5_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..2), int(1..3)] of int(1..2) -find x_ExplicitR2_Occurrence: matrix indexed by [int(1..2), int(1..2)] of bool -branching on - [x_ExplicitR2_Occurrence, x_ExplicitR4_ExplicitVarSizeWithFlags_Flags, x_ExplicitR4_ExplicitVarSizeWithFlags_Values, - x_ExplicitR5_ExplicitVarSizeWithMarker_Marker, x_ExplicitR5_ExplicitVarSizeWithMarker_Values] -such that - flatten([flatten([[-toInt(x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[1, q8]); int(1)], - [x_ExplicitR4_ExplicitVarSizeWithFlags_Values[1, q8]; int(1)]; - int(1..2)]) - | q8 : int(1..3)]) - - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q2, q3] < - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q2, q3 + 1] - | q3 : int(1..2)]) - | q2 : int(1..2)]), - and([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q2, q4] = false -> - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q2, q4] = 1 - | q4 : int(1..3)]) - | q2 : int(1..2)]), - and([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q2, q5 + 1] -> - x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q2, q5] - | q5 : int(1..2)]) - | q2 : int(1..2)]), - and([sum([toInt(x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q2, q6]) | q6 : int(1..3)]) <= 3 | q2 : int(1..2)]), - flatten([[x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[1]; int(1)], - flatten([[x_ExplicitR5_ExplicitVarSizeWithMarker_Values[1, q15]; int(1)] | q15 : int(1..3)]); - int(1..2)]) - - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q11, q12] < - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q11, q12 + 1] - | q12 : int(1..2)]) - | q11 : int(1..2)]), - and([and([q13 > x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q11] -> - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q11, q13] = 1 - | q13 : int(1..3)]) - | q11 : int(1..2)]), - and([x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q11] <= 3 | q11 : int(1..2)]), - and([or([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q20, q22] -> - or([q24 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q18] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q18, q24] = - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q20, q22] - | q24 : int(1..3)]) - | q22 : int(1..3)]) - /\ - and([q26 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q18] -> - or([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q20, q28] /\ - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q20, q28] = - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q18, q26] - | q28 : int(1..3)]) - | q26 : int(1..3)]) - | q20 : int(1..2)]) - | q18 : int(1..2)]), - and([or([and([q34 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q32] -> - or([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q30, q36] /\ - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q30, q36] = - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q32, q34] - | q36 : int(1..3)]) - | q34 : int(1..3)]) - /\ - and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q30, q38] -> - or([q40 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q32] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q32, q40] = - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q30, q38] - | q40 : int(1..3)]) - | q38 : int(1..3)]) - | q32 : int(1..2)]) - | q30 : int(1..2)]), - [-toInt(x_ExplicitR2_Occurrence[1, q44]) | q44 : int(1..2)] - x_ExplicitR2_Occurrence[q47, x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q49, q51]] - | q51 : int(1..3)]) - /\ - and([x_ExplicitR2_Occurrence[q47, q52] -> - or([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q49, q54] /\ - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q49, q54] = q52 - | q54 : int(1..3)]) - | q52 : int(1..2)]) - | q49 : int(1..2)]) - | q47 : int(1..2)]), - and([or([and([x_ExplicitR2_Occurrence[q58, q59] -> - or([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q56, q61] /\ - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q56, q61] = q59 - | q61 : int(1..3)]) - | q59 : int(1..2)]) - /\ - and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q56, q63] -> - x_ExplicitR2_Occurrence[q58, x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q56, q63]] - | q63 : int(1..3)]) - | q58 : int(1..2)]) - | q56 : int(1..2)]), - and([or([and([q69 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q67] -> - x_ExplicitR2_Occurrence[q65, x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q67, q69]] - | q69 : int(1..3)]) - /\ - and([x_ExplicitR2_Occurrence[q65, q70] -> - or([q72 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q67] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q67, q72] = q70 - | q72 : int(1..3)]) - | q70 : int(1..2)]) - | q67 : int(1..2)]) - | q65 : int(1..2)]), - and([or([and([x_ExplicitR2_Occurrence[q76, q77] -> - or([q79 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q74] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q74, q79] = q77 - | q79 : int(1..3)]) - | q77 : int(1..2)]) - /\ - and([q81 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q74] -> - x_ExplicitR2_Occurrence[q76, x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q74, q81]] - | q81 : int(1..3)]) - | q76 : int(1..2)]) - | q74 : int(1..2)]) - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_4_3_2-solution000001.solution b/tests/exhaustive/basic/setOfSet04/expected/model_4_3_2-solution000001.solution deleted file mode 100644 index 38937c9389..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_4_3_2-solution000001.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1}, {1, 2}} -$ Visualisation for x -$ 1 -$ 1 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_4_3_2-solution000002.solution b/tests/exhaustive/basic/setOfSet04/expected/model_4_3_2-solution000002.solution deleted file mode 100644 index 9bf2af0712..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_4_3_2-solution000002.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1, 2}, {2}} -$ Visualisation for x -$ 1 2 -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_4_3_2-solution000003.solution b/tests/exhaustive/basic/setOfSet04/expected/model_4_3_2-solution000003.solution deleted file mode 100644 index a6c0b6a43e..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_4_3_2-solution000003.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {1, 2}} -$ Visualisation for x -$ -$ 1 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_4_3_2-solution000004.solution b/tests/exhaustive/basic/setOfSet04/expected/model_4_3_2-solution000004.solution deleted file mode 100644 index af16592c51..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_4_3_2-solution000004.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1}, {2}} -$ Visualisation for x -$ 1 -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_4_3_2-solution000005.solution b/tests/exhaustive/basic/setOfSet04/expected/model_4_3_2-solution000005.solution deleted file mode 100644 index 3ec452354e..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_4_3_2-solution000005.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {1}} -$ Visualisation for x -$ -$ 1 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_4_3_2-solution000006.solution b/tests/exhaustive/basic/setOfSet04/expected/model_4_3_2-solution000006.solution deleted file mode 100644 index c8946f3d06..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_4_3_2-solution000006.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {2}} -$ Visualisation for x -$ -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_4_3_2.eprime b/tests/exhaustive/basic/setOfSet04/expected/model_4_3_2.eprime deleted file mode 100644 index 3e78af1329..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_4_3_2.eprime +++ /dev/null @@ -1,154 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitR4_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..2), int(1..3)] of bool -find x_ExplicitR4_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..2), int(1..3)] of int(1..2) -find x_ExplicitR5_ExplicitVarSizeWithMarker_Marker: matrix indexed by [int(1..2)] of int(0..3) -find x_ExplicitR5_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..2), int(1..3)] of int(1..2) -find x_ExplicitR6_ExplicitVarSizeWithDummy: matrix indexed by [int(1..2), int(1..3)] of int(1..3) -branching on - [x_ExplicitR6_ExplicitVarSizeWithDummy, x_ExplicitR4_ExplicitVarSizeWithFlags_Flags, - x_ExplicitR4_ExplicitVarSizeWithFlags_Values, x_ExplicitR5_ExplicitVarSizeWithMarker_Marker, - x_ExplicitR5_ExplicitVarSizeWithMarker_Values] -such that - flatten([flatten([[-toInt(x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[1, q8]); int(1)], - [x_ExplicitR4_ExplicitVarSizeWithFlags_Values[1, q8]; int(1)]; - int(1..2)]) - | q8 : int(1..3)]) - - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q2, q3] < - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q2, q3 + 1] - | q3 : int(1..2)]) - | q2 : int(1..2)]), - and([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q2, q4] = false -> - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q2, q4] = 1 - | q4 : int(1..3)]) - | q2 : int(1..2)]), - and([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q2, q5 + 1] -> - x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q2, q5] - | q5 : int(1..2)]) - | q2 : int(1..2)]), - and([sum([toInt(x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q2, q6]) | q6 : int(1..3)]) <= 3 | q2 : int(1..2)]), - flatten([[x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[1]; int(1)], - flatten([[x_ExplicitR5_ExplicitVarSizeWithMarker_Values[1, q15]; int(1)] | q15 : int(1..3)]); - int(1..2)]) - - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q11, q12] < - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q11, q12 + 1] - | q12 : int(1..2)]) - | q11 : int(1..2)]), - and([and([q13 > x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q11] -> - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q11, q13] = 1 - | q13 : int(1..3)]) - | q11 : int(1..2)]), - and([x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q11] <= 3 | q11 : int(1..2)]), - and([or([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q20, q22] -> - or([q24 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q18] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q18, q24] = - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q20, q22] - | q24 : int(1..3)]) - | q22 : int(1..3)]) - /\ - and([q26 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q18] -> - or([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q20, q28] /\ - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q20, q28] = - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q18, q26] - | q28 : int(1..3)]) - | q26 : int(1..3)]) - | q20 : int(1..2)]) - | q18 : int(1..2)]), - and([or([and([q34 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q32] -> - or([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q30, q36] /\ - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q30, q36] = - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q32, q34] - | q36 : int(1..3)]) - | q34 : int(1..3)]) - /\ - and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q30, q38] -> - or([q40 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q32] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q32, q40] = - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q30, q38] - | q40 : int(1..3)]) - | q38 : int(1..3)]) - | q32 : int(1..2)]) - | q30 : int(1..2)]), - [x_ExplicitR6_ExplicitVarSizeWithDummy[1, q47] | q47 : int(1..3)] - x_ExplicitR6_ExplicitVarSizeWithDummy[q42, q44 + 1] = 3 - | q44 : int(1..2)]) - | q42 : int(1..2)]), - and([sum([toInt(x_ExplicitR6_ExplicitVarSizeWithDummy[q42, q45] != 3) | q45 : int(1..3)]) <= 3 | q42 : int(1..2)]), - and([or([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q52, q54] -> - or([x_ExplicitR6_ExplicitVarSizeWithDummy[q50, q56] != 3 /\ - x_ExplicitR6_ExplicitVarSizeWithDummy[q50, q56] = - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q52, q54] - | q56 : int(1..3)]) - | q54 : int(1..3)]) - /\ - and([x_ExplicitR6_ExplicitVarSizeWithDummy[q50, q58] != 3 -> - or([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q52, q60] /\ - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q52, q60] = - x_ExplicitR6_ExplicitVarSizeWithDummy[q50, q58] - | q60 : int(1..3)]) - | q58 : int(1..3)]) - | q52 : int(1..2)]) - | q50 : int(1..2)]), - and([or([and([x_ExplicitR6_ExplicitVarSizeWithDummy[q64, q66] != 3 -> - or([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q62, q68] /\ - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q62, q68] = - x_ExplicitR6_ExplicitVarSizeWithDummy[q64, q66] - | q68 : int(1..3)]) - | q66 : int(1..3)]) - /\ - and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q62, q70] -> - or([x_ExplicitR6_ExplicitVarSizeWithDummy[q64, q72] != 3 /\ - x_ExplicitR6_ExplicitVarSizeWithDummy[q64, q72] = - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q62, q70] - | q72 : int(1..3)]) - | q70 : int(1..3)]) - | q64 : int(1..2)]) - | q62 : int(1..2)]), - and([or([and([q78 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q76] -> - or([x_ExplicitR6_ExplicitVarSizeWithDummy[q74, q80] != 3 /\ - x_ExplicitR6_ExplicitVarSizeWithDummy[q74, q80] = - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q76, q78] - | q80 : int(1..3)]) - | q78 : int(1..3)]) - /\ - and([x_ExplicitR6_ExplicitVarSizeWithDummy[q74, q82] != 3 -> - or([q84 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q76] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q76, q84] = - x_ExplicitR6_ExplicitVarSizeWithDummy[q74, q82] - | q84 : int(1..3)]) - | q82 : int(1..3)]) - | q76 : int(1..2)]) - | q74 : int(1..2)]), - and([or([and([x_ExplicitR6_ExplicitVarSizeWithDummy[q88, q90] != 3 -> - or([q92 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q86] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q86, q92] = - x_ExplicitR6_ExplicitVarSizeWithDummy[q88, q90] - | q92 : int(1..3)]) - | q90 : int(1..3)]) - /\ - and([q94 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q86] -> - or([x_ExplicitR6_ExplicitVarSizeWithDummy[q88, q96] != 3 /\ - x_ExplicitR6_ExplicitVarSizeWithDummy[q88, q96] = - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q86, q94] - | q96 : int(1..3)]) - | q94 : int(1..3)]) - | q88 : int(1..2)]) - | q86 : int(1..2)]) - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_4_3_3-solution000001.solution b/tests/exhaustive/basic/setOfSet04/expected/model_4_3_3-solution000001.solution deleted file mode 100644 index 3ec452354e..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_4_3_3-solution000001.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {1}} -$ Visualisation for x -$ -$ 1 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_4_3_3-solution000002.solution b/tests/exhaustive/basic/setOfSet04/expected/model_4_3_3-solution000002.solution deleted file mode 100644 index c8946f3d06..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_4_3_3-solution000002.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {2}} -$ Visualisation for x -$ -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_4_3_3-solution000003.solution b/tests/exhaustive/basic/setOfSet04/expected/model_4_3_3-solution000003.solution deleted file mode 100644 index a6c0b6a43e..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_4_3_3-solution000003.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {1, 2}} -$ Visualisation for x -$ -$ 1 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_4_3_3-solution000004.solution b/tests/exhaustive/basic/setOfSet04/expected/model_4_3_3-solution000004.solution deleted file mode 100644 index af16592c51..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_4_3_3-solution000004.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1}, {2}} -$ Visualisation for x -$ 1 -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_4_3_3-solution000005.solution b/tests/exhaustive/basic/setOfSet04/expected/model_4_3_3-solution000005.solution deleted file mode 100644 index 38937c9389..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_4_3_3-solution000005.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1}, {1, 2}} -$ Visualisation for x -$ 1 -$ 1 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_4_3_3-solution000006.solution b/tests/exhaustive/basic/setOfSet04/expected/model_4_3_3-solution000006.solution deleted file mode 100644 index 9bf2af0712..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_4_3_3-solution000006.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1, 2}, {2}} -$ Visualisation for x -$ 1 2 -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_4_3_3.eprime b/tests/exhaustive/basic/setOfSet04/expected/model_4_3_3.eprime deleted file mode 100644 index 7052450e14..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_4_3_3.eprime +++ /dev/null @@ -1,81 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitR4_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..2), int(1..3)] of bool -find x_ExplicitR4_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..2), int(1..3)] of int(1..2) -find x_ExplicitR5_ExplicitVarSizeWithMarker_Marker: matrix indexed by [int(1..2)] of int(0..3) -find x_ExplicitR5_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..2), int(1..3)] of int(1..2) -branching on - [x_ExplicitR5_ExplicitVarSizeWithMarker_Marker, x_ExplicitR5_ExplicitVarSizeWithMarker_Values, - x_ExplicitR4_ExplicitVarSizeWithFlags_Flags, x_ExplicitR4_ExplicitVarSizeWithFlags_Values] -such that - flatten([flatten([[-toInt(x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[1, q8]); int(1)], - [x_ExplicitR4_ExplicitVarSizeWithFlags_Values[1, q8]; int(1)]; - int(1..2)]) - | q8 : int(1..3)]) - - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q2, q3] < - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q2, q3 + 1] - | q3 : int(1..2)]) - | q2 : int(1..2)]), - and([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q2, q4] = false -> - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q2, q4] = 1 - | q4 : int(1..3)]) - | q2 : int(1..2)]), - and([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q2, q5 + 1] -> - x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q2, q5] - | q5 : int(1..2)]) - | q2 : int(1..2)]), - and([sum([toInt(x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q2, q6]) | q6 : int(1..3)]) <= 3 | q2 : int(1..2)]), - flatten([[x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[1]; int(1)], - flatten([[x_ExplicitR5_ExplicitVarSizeWithMarker_Values[1, q15]; int(1)] | q15 : int(1..3)]); - int(1..2)]) - - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q11, q12] < - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q11, q12 + 1] - | q12 : int(1..2)]) - | q11 : int(1..2)]), - and([and([q13 > x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q11] -> - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q11, q13] = 1 - | q13 : int(1..3)]) - | q11 : int(1..2)]), - and([x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q11] <= 3 | q11 : int(1..2)]), - and([or([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q20, q22] -> - or([q24 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q18] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q18, q24] = - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q20, q22] - | q24 : int(1..3)]) - | q22 : int(1..3)]) - /\ - and([q26 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q18] -> - or([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q20, q28] /\ - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q20, q28] = - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q18, q26] - | q28 : int(1..3)]) - | q26 : int(1..3)]) - | q20 : int(1..2)]) - | q18 : int(1..2)]), - and([or([and([q34 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q32] -> - or([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q30, q36] /\ - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q30, q36] = - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q32, q34] - | q36 : int(1..3)]) - | q34 : int(1..3)]) - /\ - and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q30, q38] -> - or([q40 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q32] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q32, q40] = - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q30, q38] - | q40 : int(1..3)]) - | q38 : int(1..3)]) - | q32 : int(1..2)]) - | q30 : int(1..2)]) - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_4_3_4-solution000001.solution b/tests/exhaustive/basic/setOfSet04/expected/model_4_3_4-solution000001.solution deleted file mode 100644 index 3ec452354e..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_4_3_4-solution000001.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {1}} -$ Visualisation for x -$ -$ 1 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_4_3_4-solution000002.solution b/tests/exhaustive/basic/setOfSet04/expected/model_4_3_4-solution000002.solution deleted file mode 100644 index c8946f3d06..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_4_3_4-solution000002.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {2}} -$ Visualisation for x -$ -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_4_3_4-solution000003.solution b/tests/exhaustive/basic/setOfSet04/expected/model_4_3_4-solution000003.solution deleted file mode 100644 index a6c0b6a43e..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_4_3_4-solution000003.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {1, 2}} -$ Visualisation for x -$ -$ 1 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_4_3_4-solution000004.solution b/tests/exhaustive/basic/setOfSet04/expected/model_4_3_4-solution000004.solution deleted file mode 100644 index af16592c51..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_4_3_4-solution000004.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1}, {2}} -$ Visualisation for x -$ 1 -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_4_3_4-solution000005.solution b/tests/exhaustive/basic/setOfSet04/expected/model_4_3_4-solution000005.solution deleted file mode 100644 index 38937c9389..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_4_3_4-solution000005.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1}, {1, 2}} -$ Visualisation for x -$ 1 -$ 1 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_4_3_4-solution000006.solution b/tests/exhaustive/basic/setOfSet04/expected/model_4_3_4-solution000006.solution deleted file mode 100644 index 9bf2af0712..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_4_3_4-solution000006.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1, 2}, {2}} -$ Visualisation for x -$ 1 2 -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_4_3_4.eprime b/tests/exhaustive/basic/setOfSet04/expected/model_4_3_4.eprime deleted file mode 100644 index 7052450e14..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_4_3_4.eprime +++ /dev/null @@ -1,81 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitR4_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..2), int(1..3)] of bool -find x_ExplicitR4_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..2), int(1..3)] of int(1..2) -find x_ExplicitR5_ExplicitVarSizeWithMarker_Marker: matrix indexed by [int(1..2)] of int(0..3) -find x_ExplicitR5_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..2), int(1..3)] of int(1..2) -branching on - [x_ExplicitR5_ExplicitVarSizeWithMarker_Marker, x_ExplicitR5_ExplicitVarSizeWithMarker_Values, - x_ExplicitR4_ExplicitVarSizeWithFlags_Flags, x_ExplicitR4_ExplicitVarSizeWithFlags_Values] -such that - flatten([flatten([[-toInt(x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[1, q8]); int(1)], - [x_ExplicitR4_ExplicitVarSizeWithFlags_Values[1, q8]; int(1)]; - int(1..2)]) - | q8 : int(1..3)]) - - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q2, q3] < - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q2, q3 + 1] - | q3 : int(1..2)]) - | q2 : int(1..2)]), - and([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q2, q4] = false -> - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q2, q4] = 1 - | q4 : int(1..3)]) - | q2 : int(1..2)]), - and([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q2, q5 + 1] -> - x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q2, q5] - | q5 : int(1..2)]) - | q2 : int(1..2)]), - and([sum([toInt(x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q2, q6]) | q6 : int(1..3)]) <= 3 | q2 : int(1..2)]), - flatten([[x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[1]; int(1)], - flatten([[x_ExplicitR5_ExplicitVarSizeWithMarker_Values[1, q15]; int(1)] | q15 : int(1..3)]); - int(1..2)]) - - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q11, q12] < - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q11, q12 + 1] - | q12 : int(1..2)]) - | q11 : int(1..2)]), - and([and([q13 > x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q11] -> - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q11, q13] = 1 - | q13 : int(1..3)]) - | q11 : int(1..2)]), - and([x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q11] <= 3 | q11 : int(1..2)]), - and([or([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q20, q22] -> - or([q24 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q18] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q18, q24] = - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q20, q22] - | q24 : int(1..3)]) - | q22 : int(1..3)]) - /\ - and([q26 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q18] -> - or([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q20, q28] /\ - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q20, q28] = - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q18, q26] - | q28 : int(1..3)]) - | q26 : int(1..3)]) - | q20 : int(1..2)]) - | q18 : int(1..2)]), - and([or([and([q34 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q32] -> - or([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q30, q36] /\ - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q30, q36] = - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q32, q34] - | q36 : int(1..3)]) - | q34 : int(1..3)]) - /\ - and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q30, q38] -> - or([q40 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q32] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q32, q40] = - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q30, q38] - | q40 : int(1..3)]) - | q38 : int(1..3)]) - | q32 : int(1..2)]) - | q30 : int(1..2)]) - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_4_4_1-solution000001.solution b/tests/exhaustive/basic/setOfSet04/expected/model_4_4_1-solution000001.solution deleted file mode 100644 index c8946f3d06..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_4_4_1-solution000001.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {2}} -$ Visualisation for x -$ -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_4_4_1-solution000002.solution b/tests/exhaustive/basic/setOfSet04/expected/model_4_4_1-solution000002.solution deleted file mode 100644 index 3ec452354e..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_4_4_1-solution000002.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {1}} -$ Visualisation for x -$ -$ 1 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_4_4_1-solution000003.solution b/tests/exhaustive/basic/setOfSet04/expected/model_4_4_1-solution000003.solution deleted file mode 100644 index af16592c51..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_4_4_1-solution000003.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1}, {2}} -$ Visualisation for x -$ 1 -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_4_4_1-solution000004.solution b/tests/exhaustive/basic/setOfSet04/expected/model_4_4_1-solution000004.solution deleted file mode 100644 index a6c0b6a43e..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_4_4_1-solution000004.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {1, 2}} -$ Visualisation for x -$ -$ 1 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_4_4_1-solution000005.solution b/tests/exhaustive/basic/setOfSet04/expected/model_4_4_1-solution000005.solution deleted file mode 100644 index 9bf2af0712..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_4_4_1-solution000005.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1, 2}, {2}} -$ Visualisation for x -$ 1 2 -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_4_4_1-solution000006.solution b/tests/exhaustive/basic/setOfSet04/expected/model_4_4_1-solution000006.solution deleted file mode 100644 index 38937c9389..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_4_4_1-solution000006.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1}, {1, 2}} -$ Visualisation for x -$ 1 -$ 1 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_4_4_1.eprime b/tests/exhaustive/basic/setOfSet04/expected/model_4_4_1.eprime deleted file mode 100644 index c7f842826d..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_4_4_1.eprime +++ /dev/null @@ -1,57 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitR4_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..2), int(1..3)] of bool -find x_ExplicitR4_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..2), int(1..3)] of int(1..2) -find x_ExplicitR2_Occurrence: matrix indexed by [int(1..2), int(1..2)] of bool -branching on - [x_ExplicitR2_Occurrence, x_ExplicitR4_ExplicitVarSizeWithFlags_Flags, x_ExplicitR4_ExplicitVarSizeWithFlags_Values] -such that - flatten([flatten([[-toInt(x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[1, q8]); int(1)], - [x_ExplicitR4_ExplicitVarSizeWithFlags_Values[1, q8]; int(1)]; - int(1..2)]) - | q8 : int(1..3)]) - - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q2, q3] < - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q2, q3 + 1] - | q3 : int(1..2)]) - | q2 : int(1..2)]), - and([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q2, q4] = false -> - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q2, q4] = 1 - | q4 : int(1..3)]) - | q2 : int(1..2)]), - and([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q2, q5 + 1] -> - x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q2, q5] - | q5 : int(1..2)]) - | q2 : int(1..2)]), - and([sum([toInt(x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q2, q6]) | q6 : int(1..3)]) <= 3 | q2 : int(1..2)]), - [-toInt(x_ExplicitR2_Occurrence[1, q13]) | q13 : int(1..2)] - x_ExplicitR2_Occurrence[q16, x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q18, q20]] - | q20 : int(1..3)]) - /\ - and([x_ExplicitR2_Occurrence[q16, q21] -> - or([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q18, q23] /\ - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q18, q23] = q21 - | q23 : int(1..3)]) - | q21 : int(1..2)]) - | q18 : int(1..2)]) - | q16 : int(1..2)]), - and([or([and([x_ExplicitR2_Occurrence[q27, q28] -> - or([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q25, q30] /\ - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q25, q30] = q28 - | q30 : int(1..3)]) - | q28 : int(1..2)]) - /\ - and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q25, q32] -> - x_ExplicitR2_Occurrence[q27, x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q25, q32]] - | q32 : int(1..3)]) - | q27 : int(1..2)]) - | q25 : int(1..2)]) - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_4_4_2-solution000001.solution b/tests/exhaustive/basic/setOfSet04/expected/model_4_4_2-solution000001.solution deleted file mode 100644 index 38937c9389..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_4_4_2-solution000001.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1}, {1, 2}} -$ Visualisation for x -$ 1 -$ 1 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_4_4_2-solution000002.solution b/tests/exhaustive/basic/setOfSet04/expected/model_4_4_2-solution000002.solution deleted file mode 100644 index 9bf2af0712..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_4_4_2-solution000002.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1, 2}, {2}} -$ Visualisation for x -$ 1 2 -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_4_4_2-solution000003.solution b/tests/exhaustive/basic/setOfSet04/expected/model_4_4_2-solution000003.solution deleted file mode 100644 index a6c0b6a43e..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_4_4_2-solution000003.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {1, 2}} -$ Visualisation for x -$ -$ 1 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_4_4_2-solution000004.solution b/tests/exhaustive/basic/setOfSet04/expected/model_4_4_2-solution000004.solution deleted file mode 100644 index af16592c51..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_4_4_2-solution000004.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1}, {2}} -$ Visualisation for x -$ 1 -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_4_4_2-solution000005.solution b/tests/exhaustive/basic/setOfSet04/expected/model_4_4_2-solution000005.solution deleted file mode 100644 index 3ec452354e..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_4_4_2-solution000005.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {1}} -$ Visualisation for x -$ -$ 1 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_4_4_2-solution000006.solution b/tests/exhaustive/basic/setOfSet04/expected/model_4_4_2-solution000006.solution deleted file mode 100644 index c8946f3d06..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_4_4_2-solution000006.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {2}} -$ Visualisation for x -$ -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_4_4_2.eprime b/tests/exhaustive/basic/setOfSet04/expected/model_4_4_2.eprime deleted file mode 100644 index 048ac1ff0c..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_4_4_2.eprime +++ /dev/null @@ -1,74 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitR4_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..2), int(1..3)] of bool -find x_ExplicitR4_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..2), int(1..3)] of int(1..2) -find x_ExplicitR6_ExplicitVarSizeWithDummy: matrix indexed by [int(1..2), int(1..3)] of int(1..3) -branching on - [x_ExplicitR6_ExplicitVarSizeWithDummy, x_ExplicitR4_ExplicitVarSizeWithFlags_Flags, - x_ExplicitR4_ExplicitVarSizeWithFlags_Values] -such that - flatten([flatten([[-toInt(x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[1, q8]); int(1)], - [x_ExplicitR4_ExplicitVarSizeWithFlags_Values[1, q8]; int(1)]; - int(1..2)]) - | q8 : int(1..3)]) - - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q2, q3] < - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q2, q3 + 1] - | q3 : int(1..2)]) - | q2 : int(1..2)]), - and([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q2, q4] = false -> - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q2, q4] = 1 - | q4 : int(1..3)]) - | q2 : int(1..2)]), - and([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q2, q5 + 1] -> - x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q2, q5] - | q5 : int(1..2)]) - | q2 : int(1..2)]), - and([sum([toInt(x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q2, q6]) | q6 : int(1..3)]) <= 3 | q2 : int(1..2)]), - [x_ExplicitR6_ExplicitVarSizeWithDummy[1, q16] | q16 : int(1..3)] - x_ExplicitR6_ExplicitVarSizeWithDummy[q11, q13 + 1] = 3 - | q13 : int(1..2)]) - | q11 : int(1..2)]), - and([sum([toInt(x_ExplicitR6_ExplicitVarSizeWithDummy[q11, q14] != 3) | q14 : int(1..3)]) <= 3 | q11 : int(1..2)]), - and([or([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q21, q23] -> - or([x_ExplicitR6_ExplicitVarSizeWithDummy[q19, q25] != 3 /\ - x_ExplicitR6_ExplicitVarSizeWithDummy[q19, q25] = - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q21, q23] - | q25 : int(1..3)]) - | q23 : int(1..3)]) - /\ - and([x_ExplicitR6_ExplicitVarSizeWithDummy[q19, q27] != 3 -> - or([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q21, q29] /\ - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q21, q29] = - x_ExplicitR6_ExplicitVarSizeWithDummy[q19, q27] - | q29 : int(1..3)]) - | q27 : int(1..3)]) - | q21 : int(1..2)]) - | q19 : int(1..2)]), - and([or([and([x_ExplicitR6_ExplicitVarSizeWithDummy[q33, q35] != 3 -> - or([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q31, q37] /\ - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q31, q37] = - x_ExplicitR6_ExplicitVarSizeWithDummy[q33, q35] - | q37 : int(1..3)]) - | q35 : int(1..3)]) - /\ - and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q31, q39] -> - or([x_ExplicitR6_ExplicitVarSizeWithDummy[q33, q41] != 3 /\ - x_ExplicitR6_ExplicitVarSizeWithDummy[q33, q41] = - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q31, q39] - | q41 : int(1..3)]) - | q39 : int(1..3)]) - | q33 : int(1..2)]) - | q31 : int(1..2)]) - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_4_4_3-solution000001.solution b/tests/exhaustive/basic/setOfSet04/expected/model_4_4_3-solution000001.solution deleted file mode 100644 index 3ec452354e..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_4_4_3-solution000001.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {1}} -$ Visualisation for x -$ -$ 1 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_4_4_3-solution000002.solution b/tests/exhaustive/basic/setOfSet04/expected/model_4_4_3-solution000002.solution deleted file mode 100644 index c8946f3d06..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_4_4_3-solution000002.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {2}} -$ Visualisation for x -$ -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_4_4_3-solution000003.solution b/tests/exhaustive/basic/setOfSet04/expected/model_4_4_3-solution000003.solution deleted file mode 100644 index a6c0b6a43e..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_4_4_3-solution000003.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {1, 2}} -$ Visualisation for x -$ -$ 1 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_4_4_3-solution000004.solution b/tests/exhaustive/basic/setOfSet04/expected/model_4_4_3-solution000004.solution deleted file mode 100644 index af16592c51..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_4_4_3-solution000004.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1}, {2}} -$ Visualisation for x -$ 1 -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_4_4_3-solution000005.solution b/tests/exhaustive/basic/setOfSet04/expected/model_4_4_3-solution000005.solution deleted file mode 100644 index 38937c9389..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_4_4_3-solution000005.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1}, {1, 2}} -$ Visualisation for x -$ 1 -$ 1 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_4_4_3-solution000006.solution b/tests/exhaustive/basic/setOfSet04/expected/model_4_4_3-solution000006.solution deleted file mode 100644 index 9bf2af0712..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_4_4_3-solution000006.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1, 2}, {2}} -$ Visualisation for x -$ 1 2 -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_4_4_3.eprime b/tests/exhaustive/basic/setOfSet04/expected/model_4_4_3.eprime deleted file mode 100644 index 7052450e14..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_4_4_3.eprime +++ /dev/null @@ -1,81 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitR4_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..2), int(1..3)] of bool -find x_ExplicitR4_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..2), int(1..3)] of int(1..2) -find x_ExplicitR5_ExplicitVarSizeWithMarker_Marker: matrix indexed by [int(1..2)] of int(0..3) -find x_ExplicitR5_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..2), int(1..3)] of int(1..2) -branching on - [x_ExplicitR5_ExplicitVarSizeWithMarker_Marker, x_ExplicitR5_ExplicitVarSizeWithMarker_Values, - x_ExplicitR4_ExplicitVarSizeWithFlags_Flags, x_ExplicitR4_ExplicitVarSizeWithFlags_Values] -such that - flatten([flatten([[-toInt(x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[1, q8]); int(1)], - [x_ExplicitR4_ExplicitVarSizeWithFlags_Values[1, q8]; int(1)]; - int(1..2)]) - | q8 : int(1..3)]) - - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q2, q3] < - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q2, q3 + 1] - | q3 : int(1..2)]) - | q2 : int(1..2)]), - and([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q2, q4] = false -> - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q2, q4] = 1 - | q4 : int(1..3)]) - | q2 : int(1..2)]), - and([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q2, q5 + 1] -> - x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q2, q5] - | q5 : int(1..2)]) - | q2 : int(1..2)]), - and([sum([toInt(x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q2, q6]) | q6 : int(1..3)]) <= 3 | q2 : int(1..2)]), - flatten([[x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[1]; int(1)], - flatten([[x_ExplicitR5_ExplicitVarSizeWithMarker_Values[1, q15]; int(1)] | q15 : int(1..3)]); - int(1..2)]) - - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q11, q12] < - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q11, q12 + 1] - | q12 : int(1..2)]) - | q11 : int(1..2)]), - and([and([q13 > x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q11] -> - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q11, q13] = 1 - | q13 : int(1..3)]) - | q11 : int(1..2)]), - and([x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q11] <= 3 | q11 : int(1..2)]), - and([or([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q20, q22] -> - or([q24 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q18] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q18, q24] = - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q20, q22] - | q24 : int(1..3)]) - | q22 : int(1..3)]) - /\ - and([q26 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q18] -> - or([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q20, q28] /\ - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q20, q28] = - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q18, q26] - | q28 : int(1..3)]) - | q26 : int(1..3)]) - | q20 : int(1..2)]) - | q18 : int(1..2)]), - and([or([and([q34 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q32] -> - or([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q30, q36] /\ - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q30, q36] = - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q32, q34] - | q36 : int(1..3)]) - | q34 : int(1..3)]) - /\ - and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q30, q38] -> - or([q40 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q32] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q32, q40] = - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q30, q38] - | q40 : int(1..3)]) - | q38 : int(1..3)]) - | q32 : int(1..2)]) - | q30 : int(1..2)]) - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_4_4_4-solution000001.solution b/tests/exhaustive/basic/setOfSet04/expected/model_4_4_4-solution000001.solution deleted file mode 100644 index 3ec452354e..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_4_4_4-solution000001.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {1}} -$ Visualisation for x -$ -$ 1 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_4_4_4-solution000002.solution b/tests/exhaustive/basic/setOfSet04/expected/model_4_4_4-solution000002.solution deleted file mode 100644 index c8946f3d06..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_4_4_4-solution000002.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {2}} -$ Visualisation for x -$ -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_4_4_4-solution000003.solution b/tests/exhaustive/basic/setOfSet04/expected/model_4_4_4-solution000003.solution deleted file mode 100644 index af16592c51..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_4_4_4-solution000003.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1}, {2}} -$ Visualisation for x -$ 1 -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_4_4_4-solution000004.solution b/tests/exhaustive/basic/setOfSet04/expected/model_4_4_4-solution000004.solution deleted file mode 100644 index a6c0b6a43e..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_4_4_4-solution000004.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{}, {1, 2}} -$ Visualisation for x -$ -$ 1 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_4_4_4-solution000005.solution b/tests/exhaustive/basic/setOfSet04/expected/model_4_4_4-solution000005.solution deleted file mode 100644 index 38937c9389..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_4_4_4-solution000005.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1}, {1, 2}} -$ Visualisation for x -$ 1 -$ 1 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_4_4_4-solution000006.solution b/tests/exhaustive/basic/setOfSet04/expected/model_4_4_4-solution000006.solution deleted file mode 100644 index 9bf2af0712..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_4_4_4-solution000006.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting x be {{1, 2}, {2}} -$ Visualisation for x -$ 1 2 -$ 2 - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_4_4_4.eprime b/tests/exhaustive/basic/setOfSet04/expected/model_4_4_4.eprime deleted file mode 100644 index 5fc6546276..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_4_4_4.eprime +++ /dev/null @@ -1,30 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitR4_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..2), int(1..3)] of bool -find x_ExplicitR4_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..2), int(1..3)] of int(1..2) -branching on [x_ExplicitR4_ExplicitVarSizeWithFlags_Flags, x_ExplicitR4_ExplicitVarSizeWithFlags_Values] -such that - flatten([flatten([[-toInt(x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[1, q8]); int(1)], - [x_ExplicitR4_ExplicitVarSizeWithFlags_Values[1, q8]; int(1)]; - int(1..2)]) - | q8 : int(1..3)]) - - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q2, q3] < - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q2, q3 + 1] - | q3 : int(1..2)]) - | q2 : int(1..2)]), - and([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q2, q4] = false -> - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q2, q4] = 1 - | q4 : int(1..3)]) - | q2 : int(1..2)]), - and([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q2, q5 + 1] -> - x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q2, q5] - | q5 : int(1..2)]) - | q2 : int(1..2)]), - and([sum([toInt(x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q2, q6]) | q6 : int(1..3)]) <= 3 | q2 : int(1..2)]) - diff --git a/tests/exhaustive/basic/set_card_00/expected/model_1_1_1-solution000001.solution b/tests/exhaustive/basic/set_card_00/expected/model_1_1_1-solution000001.solution deleted file mode 100644 index 6c0d0fdad8..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_1_1_1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting s be {1} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_1_1_1-solution000002.solution b/tests/exhaustive/basic/set_card_00/expected/model_1_1_1-solution000002.solution deleted file mode 100644 index 2ce5f2081f..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_1_1_1-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_1_1_1.eprime b/tests/exhaustive/basic/set_card_00/expected/model_1_1_1.eprime deleted file mode 100644 index 8f7d21c6a2..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_1_1_1.eprime +++ /dev/null @@ -1,6 +0,0 @@ -language ESSENCE' 1.0 - -find s_Occurrence: matrix indexed by [int(1..2)] of bool -branching on [s_Occurrence] -such that s_Occurrence[sum([toInt(s_Occurrence[q2]) | q2 : int(1..2)])] - diff --git a/tests/exhaustive/basic/set_card_00/expected/model_1_1_2-solution000001.solution b/tests/exhaustive/basic/set_card_00/expected/model_1_1_2-solution000001.solution deleted file mode 100644 index 2ce5f2081f..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_1_1_2-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_1_1_2-solution000002.solution b/tests/exhaustive/basic/set_card_00/expected/model_1_1_2-solution000002.solution deleted file mode 100644 index 6c0d0fdad8..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_1_1_2-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting s be {1} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_1_1_2.eprime b/tests/exhaustive/basic/set_card_00/expected/model_1_1_2.eprime deleted file mode 100644 index 854db40dcb..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_1_1_2.eprime +++ /dev/null @@ -1,14 +0,0 @@ -language ESSENCE' 1.0 - -find s_Occurrence: matrix indexed by [int(1..2)] of bool -find s_ExplicitVarSizeWithDummy: matrix indexed by [int(1..2)] of int(1..3) -branching on [s_ExplicitVarSizeWithDummy, s_Occurrence] -such that - s_Occurrence[sum([toInt(s_Occurrence[q11]) | q11 : int(1..2)])], - s_ExplicitVarSizeWithDummy[1] < s_ExplicitVarSizeWithDummy[2] \/ s_ExplicitVarSizeWithDummy[1] = 3, - s_ExplicitVarSizeWithDummy[1] = 3 -> s_ExplicitVarSizeWithDummy[2] = 3, - and([s_ExplicitVarSizeWithDummy[q7] != 3 -> s_Occurrence[s_ExplicitVarSizeWithDummy[q7]] | q7 : int(1..2)]), - and([s_Occurrence[q8] -> - or([s_ExplicitVarSizeWithDummy[q10] != 3 /\ s_ExplicitVarSizeWithDummy[q10] = q8 | q10 : int(1..2)]) - | q8 : int(1..2)]) - diff --git a/tests/exhaustive/basic/set_card_00/expected/model_1_1_3-solution000001.solution b/tests/exhaustive/basic/set_card_00/expected/model_1_1_3-solution000001.solution deleted file mode 100644 index 6c0d0fdad8..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_1_1_3-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting s be {1} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_1_1_3-solution000002.solution b/tests/exhaustive/basic/set_card_00/expected/model_1_1_3-solution000002.solution deleted file mode 100644 index 2ce5f2081f..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_1_1_3-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_1_1_3.eprime b/tests/exhaustive/basic/set_card_00/expected/model_1_1_3.eprime deleted file mode 100644 index 85f5801f04..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_1_1_3.eprime +++ /dev/null @@ -1,17 +0,0 @@ -language ESSENCE' 1.0 - -find s_Occurrence: matrix indexed by [int(1..2)] of bool -find s_ExplicitVarSizeWithMarker_Marker: int(0..2) -find s_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..2)] of int(1..2) -branching on [s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithMarker_Values, s_Occurrence] -such that - s_Occurrence[sum([toInt(s_Occurrence[q10]) | q10 : int(1..2)])], - 2 <= s_ExplicitVarSizeWithMarker_Marker -> - s_ExplicitVarSizeWithMarker_Values[1] < s_ExplicitVarSizeWithMarker_Values[2], - and([q3 > s_ExplicitVarSizeWithMarker_Marker -> s_ExplicitVarSizeWithMarker_Values[q3] = 1 | q3 : int(1..2)]), - and([q6 <= s_ExplicitVarSizeWithMarker_Marker -> s_Occurrence[s_ExplicitVarSizeWithMarker_Values[q6]] - | q6 : int(1..2)]), - and([s_Occurrence[q7] -> - or([q9 <= s_ExplicitVarSizeWithMarker_Marker /\ s_ExplicitVarSizeWithMarker_Values[q9] = q7 | q9 : int(1..2)]) - | q7 : int(1..2)]) - diff --git a/tests/exhaustive/basic/set_card_00/expected/model_1_1_4-solution000001.solution b/tests/exhaustive/basic/set_card_00/expected/model_1_1_4-solution000001.solution deleted file mode 100644 index 6c0d0fdad8..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_1_1_4-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting s be {1} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_1_1_4-solution000002.solution b/tests/exhaustive/basic/set_card_00/expected/model_1_1_4-solution000002.solution deleted file mode 100644 index 2ce5f2081f..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_1_1_4-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_1_1_4.eprime b/tests/exhaustive/basic/set_card_00/expected/model_1_1_4.eprime deleted file mode 100644 index 3dd8d91baa..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_1_1_4.eprime +++ /dev/null @@ -1,16 +0,0 @@ -language ESSENCE' 1.0 - -find s_Occurrence: matrix indexed by [int(1..2)] of bool -find s_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..2)] of bool -find s_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..2)] of int(1..2) -branching on [s_ExplicitVarSizeWithFlags_Flags, s_ExplicitVarSizeWithFlags_Values, s_Occurrence] -such that - s_Occurrence[sum([toInt(s_Occurrence[q12]) | q12 : int(1..2)])], - s_ExplicitVarSizeWithFlags_Flags[2] -> s_ExplicitVarSizeWithFlags_Values[1] < s_ExplicitVarSizeWithFlags_Values[2], - and([s_ExplicitVarSizeWithFlags_Flags[q3] = false -> s_ExplicitVarSizeWithFlags_Values[q3] = 1 | q3 : int(1..2)]), - s_ExplicitVarSizeWithFlags_Flags[2] -> s_ExplicitVarSizeWithFlags_Flags[1], - and([s_ExplicitVarSizeWithFlags_Flags[q8] -> s_Occurrence[s_ExplicitVarSizeWithFlags_Values[q8]] | q8 : int(1..2)]), - and([s_Occurrence[q9] -> - or([s_ExplicitVarSizeWithFlags_Flags[q11] /\ s_ExplicitVarSizeWithFlags_Values[q11] = q9 | q11 : int(1..2)]) - | q9 : int(1..2)]) - diff --git a/tests/exhaustive/basic/set_card_00/expected/model_1_2_1-solution000001.solution b/tests/exhaustive/basic/set_card_00/expected/model_1_2_1-solution000001.solution deleted file mode 100644 index 2ce5f2081f..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_1_2_1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_1_2_1-solution000002.solution b/tests/exhaustive/basic/set_card_00/expected/model_1_2_1-solution000002.solution deleted file mode 100644 index 6c0d0fdad8..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_1_2_1-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting s be {1} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_1_2_1.eprime b/tests/exhaustive/basic/set_card_00/expected/model_1_2_1.eprime deleted file mode 100644 index ed16639077..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_1_2_1.eprime +++ /dev/null @@ -1,16 +0,0 @@ -language ESSENCE' 1.0 - -find s_Occurrence: matrix indexed by [int(1..2)] of bool -find s_ExplicitVarSizeWithDummy: matrix indexed by [int(1..2)] of int(1..3) -branching on [s_ExplicitVarSizeWithDummy, s_Occurrence] -such that - or([s_ExplicitVarSizeWithDummy[q12] != 3 /\ - s_ExplicitVarSizeWithDummy[q12] = sum([toInt(s_Occurrence[q13]) | q13 : int(1..2)]) - | q12 : int(1..2)]), - s_ExplicitVarSizeWithDummy[1] < s_ExplicitVarSizeWithDummy[2] \/ s_ExplicitVarSizeWithDummy[1] = 3, - s_ExplicitVarSizeWithDummy[1] = 3 -> s_ExplicitVarSizeWithDummy[2] = 3, - and([s_ExplicitVarSizeWithDummy[q7] != 3 -> s_Occurrence[s_ExplicitVarSizeWithDummy[q7]] | q7 : int(1..2)]), - and([s_Occurrence[q8] -> - or([s_ExplicitVarSizeWithDummy[q10] != 3 /\ s_ExplicitVarSizeWithDummy[q10] = q8 | q10 : int(1..2)]) - | q8 : int(1..2)]) - diff --git a/tests/exhaustive/basic/set_card_00/expected/model_1_2_2-solution000001.solution b/tests/exhaustive/basic/set_card_00/expected/model_1_2_2-solution000001.solution deleted file mode 100644 index 2ce5f2081f..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_1_2_2-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_1_2_2-solution000002.solution b/tests/exhaustive/basic/set_card_00/expected/model_1_2_2-solution000002.solution deleted file mode 100644 index 6c0d0fdad8..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_1_2_2-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting s be {1} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_1_2_2.eprime b/tests/exhaustive/basic/set_card_00/expected/model_1_2_2.eprime deleted file mode 100644 index ed16639077..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_1_2_2.eprime +++ /dev/null @@ -1,16 +0,0 @@ -language ESSENCE' 1.0 - -find s_Occurrence: matrix indexed by [int(1..2)] of bool -find s_ExplicitVarSizeWithDummy: matrix indexed by [int(1..2)] of int(1..3) -branching on [s_ExplicitVarSizeWithDummy, s_Occurrence] -such that - or([s_ExplicitVarSizeWithDummy[q12] != 3 /\ - s_ExplicitVarSizeWithDummy[q12] = sum([toInt(s_Occurrence[q13]) | q13 : int(1..2)]) - | q12 : int(1..2)]), - s_ExplicitVarSizeWithDummy[1] < s_ExplicitVarSizeWithDummy[2] \/ s_ExplicitVarSizeWithDummy[1] = 3, - s_ExplicitVarSizeWithDummy[1] = 3 -> s_ExplicitVarSizeWithDummy[2] = 3, - and([s_ExplicitVarSizeWithDummy[q7] != 3 -> s_Occurrence[s_ExplicitVarSizeWithDummy[q7]] | q7 : int(1..2)]), - and([s_Occurrence[q8] -> - or([s_ExplicitVarSizeWithDummy[q10] != 3 /\ s_ExplicitVarSizeWithDummy[q10] = q8 | q10 : int(1..2)]) - | q8 : int(1..2)]) - diff --git a/tests/exhaustive/basic/set_card_00/expected/model_1_2_3-solution000001.solution b/tests/exhaustive/basic/set_card_00/expected/model_1_2_3-solution000001.solution deleted file mode 100644 index 6c0d0fdad8..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_1_2_3-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting s be {1} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_1_2_3-solution000002.solution b/tests/exhaustive/basic/set_card_00/expected/model_1_2_3-solution000002.solution deleted file mode 100644 index 2ce5f2081f..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_1_2_3-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_1_2_3.eprime b/tests/exhaustive/basic/set_card_00/expected/model_1_2_3.eprime deleted file mode 100644 index aee5d0059e..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_1_2_3.eprime +++ /dev/null @@ -1,38 +0,0 @@ -language ESSENCE' 1.0 - -find s_Occurrence: matrix indexed by [int(1..2)] of bool -find s_ExplicitVarSizeWithDummy: matrix indexed by [int(1..2)] of int(1..3) -find s_ExplicitVarSizeWithMarker_Marker: int(0..2) -find s_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..2)] of int(1..2) -branching on - [s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithMarker_Values, s_Occurrence, s_ExplicitVarSizeWithDummy] -such that - or([s_ExplicitVarSizeWithDummy[q28] != 3 /\ - s_ExplicitVarSizeWithDummy[q28] = sum([toInt(s_Occurrence[q29]) | q29 : int(1..2)]) - | q28 : int(1..2)]), - s_ExplicitVarSizeWithDummy[1] < s_ExplicitVarSizeWithDummy[2] \/ s_ExplicitVarSizeWithDummy[1] = 3, - s_ExplicitVarSizeWithDummy[1] = 3 -> s_ExplicitVarSizeWithDummy[2] = 3, - and([s_ExplicitVarSizeWithDummy[q7] != 3 -> s_Occurrence[s_ExplicitVarSizeWithDummy[q7]] | q7 : int(1..2)]), - and([s_Occurrence[q8] -> - or([s_ExplicitVarSizeWithDummy[q10] != 3 /\ s_ExplicitVarSizeWithDummy[q10] = q8 | q10 : int(1..2)]) - | q8 : int(1..2)]), - 2 <= s_ExplicitVarSizeWithMarker_Marker -> - s_ExplicitVarSizeWithMarker_Values[1] < s_ExplicitVarSizeWithMarker_Values[2], - and([q12 > s_ExplicitVarSizeWithMarker_Marker -> s_ExplicitVarSizeWithMarker_Values[q12] = 1 | q12 : int(1..2)]), - and([q15 <= s_ExplicitVarSizeWithMarker_Marker -> s_Occurrence[s_ExplicitVarSizeWithMarker_Values[q15]] - | q15 : int(1..2)]), - and([s_Occurrence[q16] -> - or([q18 <= s_ExplicitVarSizeWithMarker_Marker /\ s_ExplicitVarSizeWithMarker_Values[q18] = q16 - | q18 : int(1..2)]) - | q16 : int(1..2)]), - and([q20 <= s_ExplicitVarSizeWithMarker_Marker -> - or([s_ExplicitVarSizeWithDummy[q22] != 3 /\ - s_ExplicitVarSizeWithDummy[q22] = s_ExplicitVarSizeWithMarker_Values[q20] - | q22 : int(1..2)]) - | q20 : int(1..2)]), - and([s_ExplicitVarSizeWithDummy[q24] != 3 -> - or([q26 <= s_ExplicitVarSizeWithMarker_Marker /\ - s_ExplicitVarSizeWithMarker_Values[q26] = s_ExplicitVarSizeWithDummy[q24] - | q26 : int(1..2)]) - | q24 : int(1..2)]) - diff --git a/tests/exhaustive/basic/set_card_00/expected/model_1_2_4-solution000001.solution b/tests/exhaustive/basic/set_card_00/expected/model_1_2_4-solution000001.solution deleted file mode 100644 index 6c0d0fdad8..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_1_2_4-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting s be {1} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_1_2_4-solution000002.solution b/tests/exhaustive/basic/set_card_00/expected/model_1_2_4-solution000002.solution deleted file mode 100644 index 2ce5f2081f..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_1_2_4-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_1_2_4.eprime b/tests/exhaustive/basic/set_card_00/expected/model_1_2_4.eprime deleted file mode 100644 index eb6c8281e0..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_1_2_4.eprime +++ /dev/null @@ -1,38 +0,0 @@ -language ESSENCE' 1.0 - -find s_Occurrence: matrix indexed by [int(1..2)] of bool -find s_ExplicitVarSizeWithDummy: matrix indexed by [int(1..2)] of int(1..3) -find s_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..2)] of bool -find s_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..2)] of int(1..2) -branching on - [s_ExplicitVarSizeWithFlags_Flags, s_ExplicitVarSizeWithFlags_Values, s_Occurrence, s_ExplicitVarSizeWithDummy] -such that - or([s_ExplicitVarSizeWithDummy[q30] != 3 /\ - s_ExplicitVarSizeWithDummy[q30] = sum([toInt(s_Occurrence[q31]) | q31 : int(1..2)]) - | q30 : int(1..2)]), - s_ExplicitVarSizeWithDummy[1] < s_ExplicitVarSizeWithDummy[2] \/ s_ExplicitVarSizeWithDummy[1] = 3, - s_ExplicitVarSizeWithDummy[1] = 3 -> s_ExplicitVarSizeWithDummy[2] = 3, - and([s_ExplicitVarSizeWithDummy[q7] != 3 -> s_Occurrence[s_ExplicitVarSizeWithDummy[q7]] | q7 : int(1..2)]), - and([s_Occurrence[q8] -> - or([s_ExplicitVarSizeWithDummy[q10] != 3 /\ s_ExplicitVarSizeWithDummy[q10] = q8 | q10 : int(1..2)]) - | q8 : int(1..2)]), - s_ExplicitVarSizeWithFlags_Flags[2] -> s_ExplicitVarSizeWithFlags_Values[1] < s_ExplicitVarSizeWithFlags_Values[2], - and([s_ExplicitVarSizeWithFlags_Flags[q12] = false -> s_ExplicitVarSizeWithFlags_Values[q12] = 1 - | q12 : int(1..2)]), - s_ExplicitVarSizeWithFlags_Flags[2] -> s_ExplicitVarSizeWithFlags_Flags[1], - and([s_ExplicitVarSizeWithFlags_Flags[q17] -> s_Occurrence[s_ExplicitVarSizeWithFlags_Values[q17]] - | q17 : int(1..2)]), - and([s_Occurrence[q18] -> - or([s_ExplicitVarSizeWithFlags_Flags[q20] /\ s_ExplicitVarSizeWithFlags_Values[q20] = q18 | q20 : int(1..2)]) - | q18 : int(1..2)]), - and([s_ExplicitVarSizeWithFlags_Flags[q22] -> - or([s_ExplicitVarSizeWithDummy[q24] != 3 /\ - s_ExplicitVarSizeWithDummy[q24] = s_ExplicitVarSizeWithFlags_Values[q22] - | q24 : int(1..2)]) - | q22 : int(1..2)]), - and([s_ExplicitVarSizeWithDummy[q26] != 3 -> - or([s_ExplicitVarSizeWithFlags_Flags[q28] /\ - s_ExplicitVarSizeWithFlags_Values[q28] = s_ExplicitVarSizeWithDummy[q26] - | q28 : int(1..2)]) - | q26 : int(1..2)]) - diff --git a/tests/exhaustive/basic/set_card_00/expected/model_1_3_1-solution000001.solution b/tests/exhaustive/basic/set_card_00/expected/model_1_3_1-solution000001.solution deleted file mode 100644 index 6c0d0fdad8..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_1_3_1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting s be {1} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_1_3_1-solution000002.solution b/tests/exhaustive/basic/set_card_00/expected/model_1_3_1-solution000002.solution deleted file mode 100644 index 2ce5f2081f..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_1_3_1-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_1_3_1.eprime b/tests/exhaustive/basic/set_card_00/expected/model_1_3_1.eprime deleted file mode 100644 index a11ed0ff5f..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_1_3_1.eprime +++ /dev/null @@ -1,19 +0,0 @@ -language ESSENCE' 1.0 - -find s_Occurrence: matrix indexed by [int(1..2)] of bool -find s_ExplicitVarSizeWithMarker_Marker: int(0..2) -find s_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..2)] of int(1..2) -branching on [s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithMarker_Values, s_Occurrence] -such that - or([q11 <= s_ExplicitVarSizeWithMarker_Marker /\ - s_ExplicitVarSizeWithMarker_Values[q11] = sum([toInt(s_Occurrence[q12]) | q12 : int(1..2)]) - | q11 : int(1..2)]), - 2 <= s_ExplicitVarSizeWithMarker_Marker -> - s_ExplicitVarSizeWithMarker_Values[1] < s_ExplicitVarSizeWithMarker_Values[2], - and([q3 > s_ExplicitVarSizeWithMarker_Marker -> s_ExplicitVarSizeWithMarker_Values[q3] = 1 | q3 : int(1..2)]), - and([q6 <= s_ExplicitVarSizeWithMarker_Marker -> s_Occurrence[s_ExplicitVarSizeWithMarker_Values[q6]] - | q6 : int(1..2)]), - and([s_Occurrence[q7] -> - or([q9 <= s_ExplicitVarSizeWithMarker_Marker /\ s_ExplicitVarSizeWithMarker_Values[q9] = q7 | q9 : int(1..2)]) - | q7 : int(1..2)]) - diff --git a/tests/exhaustive/basic/set_card_00/expected/model_1_3_2-solution000001.solution b/tests/exhaustive/basic/set_card_00/expected/model_1_3_2-solution000001.solution deleted file mode 100644 index 2ce5f2081f..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_1_3_2-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_1_3_2-solution000002.solution b/tests/exhaustive/basic/set_card_00/expected/model_1_3_2-solution000002.solution deleted file mode 100644 index 6c0d0fdad8..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_1_3_2-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting s be {1} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_1_3_2.eprime b/tests/exhaustive/basic/set_card_00/expected/model_1_3_2.eprime deleted file mode 100644 index d5996222eb..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_1_3_2.eprime +++ /dev/null @@ -1,37 +0,0 @@ -language ESSENCE' 1.0 - -find s_Occurrence: matrix indexed by [int(1..2)] of bool -find s_ExplicitVarSizeWithMarker_Marker: int(0..2) -find s_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..2)] of int(1..2) -find s_ExplicitVarSizeWithDummy: matrix indexed by [int(1..2)] of int(1..3) -branching on - [s_ExplicitVarSizeWithDummy, s_Occurrence, s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithMarker_Values] -such that - or([q28 <= s_ExplicitVarSizeWithMarker_Marker /\ - s_ExplicitVarSizeWithMarker_Values[q28] = sum([toInt(s_Occurrence[q29]) | q29 : int(1..2)]) - | q28 : int(1..2)]), - 2 <= s_ExplicitVarSizeWithMarker_Marker -> - s_ExplicitVarSizeWithMarker_Values[1] < s_ExplicitVarSizeWithMarker_Values[2], - and([q3 > s_ExplicitVarSizeWithMarker_Marker -> s_ExplicitVarSizeWithMarker_Values[q3] = 1 | q3 : int(1..2)]), - and([q6 <= s_ExplicitVarSizeWithMarker_Marker -> s_Occurrence[s_ExplicitVarSizeWithMarker_Values[q6]] - | q6 : int(1..2)]), - and([s_Occurrence[q7] -> - or([q9 <= s_ExplicitVarSizeWithMarker_Marker /\ s_ExplicitVarSizeWithMarker_Values[q9] = q7 | q9 : int(1..2)]) - | q7 : int(1..2)]), - s_ExplicitVarSizeWithDummy[1] < s_ExplicitVarSizeWithDummy[2] \/ s_ExplicitVarSizeWithDummy[1] = 3, - s_ExplicitVarSizeWithDummy[1] = 3 -> s_ExplicitVarSizeWithDummy[2] = 3, - and([s_ExplicitVarSizeWithDummy[q15] != 3 -> s_Occurrence[s_ExplicitVarSizeWithDummy[q15]] | q15 : int(1..2)]), - and([s_Occurrence[q16] -> - or([s_ExplicitVarSizeWithDummy[q18] != 3 /\ s_ExplicitVarSizeWithDummy[q18] = q16 | q18 : int(1..2)]) - | q16 : int(1..2)]), - and([s_ExplicitVarSizeWithDummy[q20] != 3 -> - or([q22 <= s_ExplicitVarSizeWithMarker_Marker /\ - s_ExplicitVarSizeWithMarker_Values[q22] = s_ExplicitVarSizeWithDummy[q20] - | q22 : int(1..2)]) - | q20 : int(1..2)]), - and([q24 <= s_ExplicitVarSizeWithMarker_Marker -> - or([s_ExplicitVarSizeWithDummy[q26] != 3 /\ - s_ExplicitVarSizeWithDummy[q26] = s_ExplicitVarSizeWithMarker_Values[q24] - | q26 : int(1..2)]) - | q24 : int(1..2)]) - diff --git a/tests/exhaustive/basic/set_card_00/expected/model_1_3_3-solution000001.solution b/tests/exhaustive/basic/set_card_00/expected/model_1_3_3-solution000001.solution deleted file mode 100644 index 6c0d0fdad8..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_1_3_3-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting s be {1} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_1_3_3-solution000002.solution b/tests/exhaustive/basic/set_card_00/expected/model_1_3_3-solution000002.solution deleted file mode 100644 index 2ce5f2081f..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_1_3_3-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_1_3_3.eprime b/tests/exhaustive/basic/set_card_00/expected/model_1_3_3.eprime deleted file mode 100644 index a11ed0ff5f..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_1_3_3.eprime +++ /dev/null @@ -1,19 +0,0 @@ -language ESSENCE' 1.0 - -find s_Occurrence: matrix indexed by [int(1..2)] of bool -find s_ExplicitVarSizeWithMarker_Marker: int(0..2) -find s_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..2)] of int(1..2) -branching on [s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithMarker_Values, s_Occurrence] -such that - or([q11 <= s_ExplicitVarSizeWithMarker_Marker /\ - s_ExplicitVarSizeWithMarker_Values[q11] = sum([toInt(s_Occurrence[q12]) | q12 : int(1..2)]) - | q11 : int(1..2)]), - 2 <= s_ExplicitVarSizeWithMarker_Marker -> - s_ExplicitVarSizeWithMarker_Values[1] < s_ExplicitVarSizeWithMarker_Values[2], - and([q3 > s_ExplicitVarSizeWithMarker_Marker -> s_ExplicitVarSizeWithMarker_Values[q3] = 1 | q3 : int(1..2)]), - and([q6 <= s_ExplicitVarSizeWithMarker_Marker -> s_Occurrence[s_ExplicitVarSizeWithMarker_Values[q6]] - | q6 : int(1..2)]), - and([s_Occurrence[q7] -> - or([q9 <= s_ExplicitVarSizeWithMarker_Marker /\ s_ExplicitVarSizeWithMarker_Values[q9] = q7 | q9 : int(1..2)]) - | q7 : int(1..2)]) - diff --git a/tests/exhaustive/basic/set_card_00/expected/model_1_3_4-solution000001.solution b/tests/exhaustive/basic/set_card_00/expected/model_1_3_4-solution000001.solution deleted file mode 100644 index 6c0d0fdad8..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_1_3_4-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting s be {1} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_1_3_4-solution000002.solution b/tests/exhaustive/basic/set_card_00/expected/model_1_3_4-solution000002.solution deleted file mode 100644 index 2ce5f2081f..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_1_3_4-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_1_3_4.eprime b/tests/exhaustive/basic/set_card_00/expected/model_1_3_4.eprime deleted file mode 100644 index 9de0cd975a..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_1_3_4.eprime +++ /dev/null @@ -1,42 +0,0 @@ -language ESSENCE' 1.0 - -find s_Occurrence: matrix indexed by [int(1..2)] of bool -find s_ExplicitVarSizeWithMarker_Marker: int(0..2) -find s_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..2)] of int(1..2) -find s_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..2)] of bool -find s_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..2)] of int(1..2) -branching on - [s_ExplicitVarSizeWithFlags_Flags, s_ExplicitVarSizeWithFlags_Values, s_Occurrence, - s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithMarker_Values] -such that - or([q29 <= s_ExplicitVarSizeWithMarker_Marker /\ - s_ExplicitVarSizeWithMarker_Values[q29] = sum([toInt(s_Occurrence[q30]) | q30 : int(1..2)]) - | q29 : int(1..2)]), - 2 <= s_ExplicitVarSizeWithMarker_Marker -> - s_ExplicitVarSizeWithMarker_Values[1] < s_ExplicitVarSizeWithMarker_Values[2], - and([q3 > s_ExplicitVarSizeWithMarker_Marker -> s_ExplicitVarSizeWithMarker_Values[q3] = 1 | q3 : int(1..2)]), - and([q6 <= s_ExplicitVarSizeWithMarker_Marker -> s_Occurrence[s_ExplicitVarSizeWithMarker_Values[q6]] - | q6 : int(1..2)]), - and([s_Occurrence[q7] -> - or([q9 <= s_ExplicitVarSizeWithMarker_Marker /\ s_ExplicitVarSizeWithMarker_Values[q9] = q7 | q9 : int(1..2)]) - | q7 : int(1..2)]), - s_ExplicitVarSizeWithFlags_Flags[2] -> s_ExplicitVarSizeWithFlags_Values[1] < s_ExplicitVarSizeWithFlags_Values[2], - and([s_ExplicitVarSizeWithFlags_Flags[q11] = false -> s_ExplicitVarSizeWithFlags_Values[q11] = 1 - | q11 : int(1..2)]), - s_ExplicitVarSizeWithFlags_Flags[2] -> s_ExplicitVarSizeWithFlags_Flags[1], - and([s_ExplicitVarSizeWithFlags_Flags[q16] -> s_Occurrence[s_ExplicitVarSizeWithFlags_Values[q16]] - | q16 : int(1..2)]), - and([s_Occurrence[q17] -> - or([s_ExplicitVarSizeWithFlags_Flags[q19] /\ s_ExplicitVarSizeWithFlags_Values[q19] = q17 | q19 : int(1..2)]) - | q17 : int(1..2)]), - and([s_ExplicitVarSizeWithFlags_Flags[q21] -> - or([q23 <= s_ExplicitVarSizeWithMarker_Marker /\ - s_ExplicitVarSizeWithMarker_Values[q23] = s_ExplicitVarSizeWithFlags_Values[q21] - | q23 : int(1..2)]) - | q21 : int(1..2)]), - and([q25 <= s_ExplicitVarSizeWithMarker_Marker -> - or([s_ExplicitVarSizeWithFlags_Flags[q27] /\ - s_ExplicitVarSizeWithFlags_Values[q27] = s_ExplicitVarSizeWithMarker_Values[q25] - | q27 : int(1..2)]) - | q25 : int(1..2)]) - diff --git a/tests/exhaustive/basic/set_card_00/expected/model_1_4_1-solution000001.solution b/tests/exhaustive/basic/set_card_00/expected/model_1_4_1-solution000001.solution deleted file mode 100644 index 6c0d0fdad8..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_1_4_1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting s be {1} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_1_4_1-solution000002.solution b/tests/exhaustive/basic/set_card_00/expected/model_1_4_1-solution000002.solution deleted file mode 100644 index 2ce5f2081f..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_1_4_1-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_1_4_1.eprime b/tests/exhaustive/basic/set_card_00/expected/model_1_4_1.eprime deleted file mode 100644 index c94c0a316f..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_1_4_1.eprime +++ /dev/null @@ -1,18 +0,0 @@ -language ESSENCE' 1.0 - -find s_Occurrence: matrix indexed by [int(1..2)] of bool -find s_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..2)] of bool -find s_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..2)] of int(1..2) -branching on [s_ExplicitVarSizeWithFlags_Flags, s_ExplicitVarSizeWithFlags_Values, s_Occurrence] -such that - or([s_ExplicitVarSizeWithFlags_Flags[q13] /\ - s_ExplicitVarSizeWithFlags_Values[q13] = sum([toInt(s_Occurrence[q14]) | q14 : int(1..2)]) - | q13 : int(1..2)]), - s_ExplicitVarSizeWithFlags_Flags[2] -> s_ExplicitVarSizeWithFlags_Values[1] < s_ExplicitVarSizeWithFlags_Values[2], - and([s_ExplicitVarSizeWithFlags_Flags[q3] = false -> s_ExplicitVarSizeWithFlags_Values[q3] = 1 | q3 : int(1..2)]), - s_ExplicitVarSizeWithFlags_Flags[2] -> s_ExplicitVarSizeWithFlags_Flags[1], - and([s_ExplicitVarSizeWithFlags_Flags[q8] -> s_Occurrence[s_ExplicitVarSizeWithFlags_Values[q8]] | q8 : int(1..2)]), - and([s_Occurrence[q9] -> - or([s_ExplicitVarSizeWithFlags_Flags[q11] /\ s_ExplicitVarSizeWithFlags_Values[q11] = q9 | q11 : int(1..2)]) - | q9 : int(1..2)]) - diff --git a/tests/exhaustive/basic/set_card_00/expected/model_1_4_2-solution000001.solution b/tests/exhaustive/basic/set_card_00/expected/model_1_4_2-solution000001.solution deleted file mode 100644 index 2ce5f2081f..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_1_4_2-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_1_4_2-solution000002.solution b/tests/exhaustive/basic/set_card_00/expected/model_1_4_2-solution000002.solution deleted file mode 100644 index 6c0d0fdad8..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_1_4_2-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting s be {1} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_1_4_2.eprime b/tests/exhaustive/basic/set_card_00/expected/model_1_4_2.eprime deleted file mode 100644 index 42d80e559a..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_1_4_2.eprime +++ /dev/null @@ -1,36 +0,0 @@ -language ESSENCE' 1.0 - -find s_Occurrence: matrix indexed by [int(1..2)] of bool -find s_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..2)] of bool -find s_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..2)] of int(1..2) -find s_ExplicitVarSizeWithDummy: matrix indexed by [int(1..2)] of int(1..3) -branching on - [s_ExplicitVarSizeWithDummy, s_Occurrence, s_ExplicitVarSizeWithFlags_Flags, s_ExplicitVarSizeWithFlags_Values] -such that - or([s_ExplicitVarSizeWithFlags_Flags[q30] /\ - s_ExplicitVarSizeWithFlags_Values[q30] = sum([toInt(s_Occurrence[q31]) | q31 : int(1..2)]) - | q30 : int(1..2)]), - s_ExplicitVarSizeWithFlags_Flags[2] -> s_ExplicitVarSizeWithFlags_Values[1] < s_ExplicitVarSizeWithFlags_Values[2], - and([s_ExplicitVarSizeWithFlags_Flags[q3] = false -> s_ExplicitVarSizeWithFlags_Values[q3] = 1 | q3 : int(1..2)]), - s_ExplicitVarSizeWithFlags_Flags[2] -> s_ExplicitVarSizeWithFlags_Flags[1], - and([s_ExplicitVarSizeWithFlags_Flags[q8] -> s_Occurrence[s_ExplicitVarSizeWithFlags_Values[q8]] | q8 : int(1..2)]), - and([s_Occurrence[q9] -> - or([s_ExplicitVarSizeWithFlags_Flags[q11] /\ s_ExplicitVarSizeWithFlags_Values[q11] = q9 | q11 : int(1..2)]) - | q9 : int(1..2)]), - s_ExplicitVarSizeWithDummy[1] < s_ExplicitVarSizeWithDummy[2] \/ s_ExplicitVarSizeWithDummy[1] = 3, - s_ExplicitVarSizeWithDummy[1] = 3 -> s_ExplicitVarSizeWithDummy[2] = 3, - and([s_ExplicitVarSizeWithDummy[q17] != 3 -> s_Occurrence[s_ExplicitVarSizeWithDummy[q17]] | q17 : int(1..2)]), - and([s_Occurrence[q18] -> - or([s_ExplicitVarSizeWithDummy[q20] != 3 /\ s_ExplicitVarSizeWithDummy[q20] = q18 | q20 : int(1..2)]) - | q18 : int(1..2)]), - and([s_ExplicitVarSizeWithDummy[q22] != 3 -> - or([s_ExplicitVarSizeWithFlags_Flags[q24] /\ - s_ExplicitVarSizeWithFlags_Values[q24] = s_ExplicitVarSizeWithDummy[q22] - | q24 : int(1..2)]) - | q22 : int(1..2)]), - and([s_ExplicitVarSizeWithFlags_Flags[q26] -> - or([s_ExplicitVarSizeWithDummy[q28] != 3 /\ - s_ExplicitVarSizeWithDummy[q28] = s_ExplicitVarSizeWithFlags_Values[q26] - | q28 : int(1..2)]) - | q26 : int(1..2)]) - diff --git a/tests/exhaustive/basic/set_card_00/expected/model_1_4_3-solution000001.solution b/tests/exhaustive/basic/set_card_00/expected/model_1_4_3-solution000001.solution deleted file mode 100644 index 6c0d0fdad8..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_1_4_3-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting s be {1} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_1_4_3-solution000002.solution b/tests/exhaustive/basic/set_card_00/expected/model_1_4_3-solution000002.solution deleted file mode 100644 index 2ce5f2081f..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_1_4_3-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_1_4_3.eprime b/tests/exhaustive/basic/set_card_00/expected/model_1_4_3.eprime deleted file mode 100644 index 666b249b58..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_1_4_3.eprime +++ /dev/null @@ -1,41 +0,0 @@ -language ESSENCE' 1.0 - -find s_Occurrence: matrix indexed by [int(1..2)] of bool -find s_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..2)] of bool -find s_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..2)] of int(1..2) -find s_ExplicitVarSizeWithMarker_Marker: int(0..2) -find s_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..2)] of int(1..2) -branching on - [s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithMarker_Values, s_Occurrence, - s_ExplicitVarSizeWithFlags_Flags, s_ExplicitVarSizeWithFlags_Values] -such that - or([s_ExplicitVarSizeWithFlags_Flags[q29] /\ - s_ExplicitVarSizeWithFlags_Values[q29] = sum([toInt(s_Occurrence[q30]) | q30 : int(1..2)]) - | q29 : int(1..2)]), - s_ExplicitVarSizeWithFlags_Flags[2] -> s_ExplicitVarSizeWithFlags_Values[1] < s_ExplicitVarSizeWithFlags_Values[2], - and([s_ExplicitVarSizeWithFlags_Flags[q3] = false -> s_ExplicitVarSizeWithFlags_Values[q3] = 1 | q3 : int(1..2)]), - s_ExplicitVarSizeWithFlags_Flags[2] -> s_ExplicitVarSizeWithFlags_Flags[1], - and([s_ExplicitVarSizeWithFlags_Flags[q8] -> s_Occurrence[s_ExplicitVarSizeWithFlags_Values[q8]] | q8 : int(1..2)]), - and([s_Occurrence[q9] -> - or([s_ExplicitVarSizeWithFlags_Flags[q11] /\ s_ExplicitVarSizeWithFlags_Values[q11] = q9 | q11 : int(1..2)]) - | q9 : int(1..2)]), - 2 <= s_ExplicitVarSizeWithMarker_Marker -> - s_ExplicitVarSizeWithMarker_Values[1] < s_ExplicitVarSizeWithMarker_Values[2], - and([q13 > s_ExplicitVarSizeWithMarker_Marker -> s_ExplicitVarSizeWithMarker_Values[q13] = 1 | q13 : int(1..2)]), - and([q16 <= s_ExplicitVarSizeWithMarker_Marker -> s_Occurrence[s_ExplicitVarSizeWithMarker_Values[q16]] - | q16 : int(1..2)]), - and([s_Occurrence[q17] -> - or([q19 <= s_ExplicitVarSizeWithMarker_Marker /\ s_ExplicitVarSizeWithMarker_Values[q19] = q17 - | q19 : int(1..2)]) - | q17 : int(1..2)]), - and([q21 <= s_ExplicitVarSizeWithMarker_Marker -> - or([s_ExplicitVarSizeWithFlags_Flags[q23] /\ - s_ExplicitVarSizeWithFlags_Values[q23] = s_ExplicitVarSizeWithMarker_Values[q21] - | q23 : int(1..2)]) - | q21 : int(1..2)]), - and([s_ExplicitVarSizeWithFlags_Flags[q25] -> - or([q27 <= s_ExplicitVarSizeWithMarker_Marker /\ - s_ExplicitVarSizeWithMarker_Values[q27] = s_ExplicitVarSizeWithFlags_Values[q25] - | q27 : int(1..2)]) - | q25 : int(1..2)]) - diff --git a/tests/exhaustive/basic/set_card_00/expected/model_1_4_4-solution000001.solution b/tests/exhaustive/basic/set_card_00/expected/model_1_4_4-solution000001.solution deleted file mode 100644 index 6c0d0fdad8..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_1_4_4-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting s be {1} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_1_4_4-solution000002.solution b/tests/exhaustive/basic/set_card_00/expected/model_1_4_4-solution000002.solution deleted file mode 100644 index 2ce5f2081f..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_1_4_4-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_1_4_4.eprime b/tests/exhaustive/basic/set_card_00/expected/model_1_4_4.eprime deleted file mode 100644 index c94c0a316f..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_1_4_4.eprime +++ /dev/null @@ -1,18 +0,0 @@ -language ESSENCE' 1.0 - -find s_Occurrence: matrix indexed by [int(1..2)] of bool -find s_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..2)] of bool -find s_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..2)] of int(1..2) -branching on [s_ExplicitVarSizeWithFlags_Flags, s_ExplicitVarSizeWithFlags_Values, s_Occurrence] -such that - or([s_ExplicitVarSizeWithFlags_Flags[q13] /\ - s_ExplicitVarSizeWithFlags_Values[q13] = sum([toInt(s_Occurrence[q14]) | q14 : int(1..2)]) - | q13 : int(1..2)]), - s_ExplicitVarSizeWithFlags_Flags[2] -> s_ExplicitVarSizeWithFlags_Values[1] < s_ExplicitVarSizeWithFlags_Values[2], - and([s_ExplicitVarSizeWithFlags_Flags[q3] = false -> s_ExplicitVarSizeWithFlags_Values[q3] = 1 | q3 : int(1..2)]), - s_ExplicitVarSizeWithFlags_Flags[2] -> s_ExplicitVarSizeWithFlags_Flags[1], - and([s_ExplicitVarSizeWithFlags_Flags[q8] -> s_Occurrence[s_ExplicitVarSizeWithFlags_Values[q8]] | q8 : int(1..2)]), - and([s_Occurrence[q9] -> - or([s_ExplicitVarSizeWithFlags_Flags[q11] /\ s_ExplicitVarSizeWithFlags_Values[q11] = q9 | q11 : int(1..2)]) - | q9 : int(1..2)]) - diff --git a/tests/exhaustive/basic/set_card_00/expected/model_2_1_1-solution000001.solution b/tests/exhaustive/basic/set_card_00/expected/model_2_1_1-solution000001.solution deleted file mode 100644 index 6c0d0fdad8..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_2_1_1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting s be {1} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_2_1_1-solution000002.solution b/tests/exhaustive/basic/set_card_00/expected/model_2_1_1-solution000002.solution deleted file mode 100644 index 2ce5f2081f..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_2_1_1-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_2_1_1.eprime b/tests/exhaustive/basic/set_card_00/expected/model_2_1_1.eprime deleted file mode 100644 index 776246603c..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_2_1_1.eprime +++ /dev/null @@ -1,14 +0,0 @@ -language ESSENCE' 1.0 - -find s_ExplicitVarSizeWithDummy: matrix indexed by [int(1..2)] of int(1..3) -find s_Occurrence: matrix indexed by [int(1..2)] of bool -branching on [s_Occurrence, s_ExplicitVarSizeWithDummy] -such that - s_Occurrence[sum([toInt(s_ExplicitVarSizeWithDummy[q7] != 3) | q7 : int(1..2)])], - s_ExplicitVarSizeWithDummy[1] < s_ExplicitVarSizeWithDummy[2] \/ s_ExplicitVarSizeWithDummy[1] = 3, - s_ExplicitVarSizeWithDummy[1] = 3 -> s_ExplicitVarSizeWithDummy[2] = 3, - and([s_Occurrence[q8] -> - or([s_ExplicitVarSizeWithDummy[q10] != 3 /\ s_ExplicitVarSizeWithDummy[q10] = q8 | q10 : int(1..2)]) - | q8 : int(1..2)]), - and([s_ExplicitVarSizeWithDummy[q12] != 3 -> s_Occurrence[s_ExplicitVarSizeWithDummy[q12]] | q12 : int(1..2)]) - diff --git a/tests/exhaustive/basic/set_card_00/expected/model_2_1_2-solution000001.solution b/tests/exhaustive/basic/set_card_00/expected/model_2_1_2-solution000001.solution deleted file mode 100644 index 6c0d0fdad8..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_2_1_2-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting s be {1} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_2_1_2-solution000002.solution b/tests/exhaustive/basic/set_card_00/expected/model_2_1_2-solution000002.solution deleted file mode 100644 index 2ce5f2081f..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_2_1_2-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_2_1_2.eprime b/tests/exhaustive/basic/set_card_00/expected/model_2_1_2.eprime deleted file mode 100644 index 776246603c..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_2_1_2.eprime +++ /dev/null @@ -1,14 +0,0 @@ -language ESSENCE' 1.0 - -find s_ExplicitVarSizeWithDummy: matrix indexed by [int(1..2)] of int(1..3) -find s_Occurrence: matrix indexed by [int(1..2)] of bool -branching on [s_Occurrence, s_ExplicitVarSizeWithDummy] -such that - s_Occurrence[sum([toInt(s_ExplicitVarSizeWithDummy[q7] != 3) | q7 : int(1..2)])], - s_ExplicitVarSizeWithDummy[1] < s_ExplicitVarSizeWithDummy[2] \/ s_ExplicitVarSizeWithDummy[1] = 3, - s_ExplicitVarSizeWithDummy[1] = 3 -> s_ExplicitVarSizeWithDummy[2] = 3, - and([s_Occurrence[q8] -> - or([s_ExplicitVarSizeWithDummy[q10] != 3 /\ s_ExplicitVarSizeWithDummy[q10] = q8 | q10 : int(1..2)]) - | q8 : int(1..2)]), - and([s_ExplicitVarSizeWithDummy[q12] != 3 -> s_Occurrence[s_ExplicitVarSizeWithDummy[q12]] | q12 : int(1..2)]) - diff --git a/tests/exhaustive/basic/set_card_00/expected/model_2_1_3-solution000001.solution b/tests/exhaustive/basic/set_card_00/expected/model_2_1_3-solution000001.solution deleted file mode 100644 index 6c0d0fdad8..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_2_1_3-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting s be {1} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_2_1_3-solution000002.solution b/tests/exhaustive/basic/set_card_00/expected/model_2_1_3-solution000002.solution deleted file mode 100644 index 2ce5f2081f..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_2_1_3-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_2_1_3.eprime b/tests/exhaustive/basic/set_card_00/expected/model_2_1_3.eprime deleted file mode 100644 index 58dcd8a0d9..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_2_1_3.eprime +++ /dev/null @@ -1,36 +0,0 @@ -language ESSENCE' 1.0 - -find s_ExplicitVarSizeWithDummy: matrix indexed by [int(1..2)] of int(1..3) -find s_Occurrence: matrix indexed by [int(1..2)] of bool -find s_ExplicitVarSizeWithMarker_Marker: int(0..2) -find s_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..2)] of int(1..2) -branching on - [s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithMarker_Values, s_ExplicitVarSizeWithDummy, s_Occurrence] -such that - s_Occurrence[sum([toInt(s_ExplicitVarSizeWithDummy[q23] != 3) | q23 : int(1..2)])], - s_ExplicitVarSizeWithDummy[1] < s_ExplicitVarSizeWithDummy[2] \/ s_ExplicitVarSizeWithDummy[1] = 3, - s_ExplicitVarSizeWithDummy[1] = 3 -> s_ExplicitVarSizeWithDummy[2] = 3, - and([s_Occurrence[q24] -> - or([s_ExplicitVarSizeWithDummy[q26] != 3 /\ s_ExplicitVarSizeWithDummy[q26] = q24 | q26 : int(1..2)]) - | q24 : int(1..2)]), - and([s_ExplicitVarSizeWithDummy[q28] != 3 -> s_Occurrence[s_ExplicitVarSizeWithDummy[q28]] | q28 : int(1..2)]), - 2 <= s_ExplicitVarSizeWithMarker_Marker -> - s_ExplicitVarSizeWithMarker_Values[1] < s_ExplicitVarSizeWithMarker_Values[2], - and([q7 > s_ExplicitVarSizeWithMarker_Marker -> s_ExplicitVarSizeWithMarker_Values[q7] = 1 | q7 : int(1..2)]), - and([q10 <= s_ExplicitVarSizeWithMarker_Marker -> - or([s_ExplicitVarSizeWithDummy[q12] != 3 /\ - s_ExplicitVarSizeWithDummy[q12] = s_ExplicitVarSizeWithMarker_Values[q10] - | q12 : int(1..2)]) - | q10 : int(1..2)]), - and([s_ExplicitVarSizeWithDummy[q14] != 3 -> - or([q16 <= s_ExplicitVarSizeWithMarker_Marker /\ - s_ExplicitVarSizeWithMarker_Values[q16] = s_ExplicitVarSizeWithDummy[q14] - | q16 : int(1..2)]) - | q14 : int(1..2)]), - and([q18 <= s_ExplicitVarSizeWithMarker_Marker -> s_Occurrence[s_ExplicitVarSizeWithMarker_Values[q18]] - | q18 : int(1..2)]), - and([s_Occurrence[q19] -> - or([q21 <= s_ExplicitVarSizeWithMarker_Marker /\ s_ExplicitVarSizeWithMarker_Values[q21] = q19 - | q21 : int(1..2)]) - | q19 : int(1..2)]) - diff --git a/tests/exhaustive/basic/set_card_00/expected/model_2_1_4-solution000001.solution b/tests/exhaustive/basic/set_card_00/expected/model_2_1_4-solution000001.solution deleted file mode 100644 index 6c0d0fdad8..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_2_1_4-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting s be {1} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_2_1_4-solution000002.solution b/tests/exhaustive/basic/set_card_00/expected/model_2_1_4-solution000002.solution deleted file mode 100644 index 2ce5f2081f..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_2_1_4-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_2_1_4.eprime b/tests/exhaustive/basic/set_card_00/expected/model_2_1_4.eprime deleted file mode 100644 index d91db06282..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_2_1_4.eprime +++ /dev/null @@ -1,35 +0,0 @@ -language ESSENCE' 1.0 - -find s_ExplicitVarSizeWithDummy: matrix indexed by [int(1..2)] of int(1..3) -find s_Occurrence: matrix indexed by [int(1..2)] of bool -find s_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..2)] of bool -find s_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..2)] of int(1..2) -branching on - [s_ExplicitVarSizeWithFlags_Flags, s_ExplicitVarSizeWithFlags_Values, s_ExplicitVarSizeWithDummy, s_Occurrence] -such that - s_Occurrence[sum([toInt(s_ExplicitVarSizeWithDummy[q25] != 3) | q25 : int(1..2)])], - s_ExplicitVarSizeWithDummy[1] < s_ExplicitVarSizeWithDummy[2] \/ s_ExplicitVarSizeWithDummy[1] = 3, - s_ExplicitVarSizeWithDummy[1] = 3 -> s_ExplicitVarSizeWithDummy[2] = 3, - and([s_Occurrence[q26] -> - or([s_ExplicitVarSizeWithDummy[q28] != 3 /\ s_ExplicitVarSizeWithDummy[q28] = q26 | q28 : int(1..2)]) - | q26 : int(1..2)]), - and([s_ExplicitVarSizeWithDummy[q30] != 3 -> s_Occurrence[s_ExplicitVarSizeWithDummy[q30]] | q30 : int(1..2)]), - s_ExplicitVarSizeWithFlags_Flags[2] -> s_ExplicitVarSizeWithFlags_Values[1] < s_ExplicitVarSizeWithFlags_Values[2], - and([s_ExplicitVarSizeWithFlags_Flags[q7] = false -> s_ExplicitVarSizeWithFlags_Values[q7] = 1 | q7 : int(1..2)]), - s_ExplicitVarSizeWithFlags_Flags[2] -> s_ExplicitVarSizeWithFlags_Flags[1], - and([s_ExplicitVarSizeWithFlags_Flags[q12] -> - or([s_ExplicitVarSizeWithDummy[q14] != 3 /\ - s_ExplicitVarSizeWithDummy[q14] = s_ExplicitVarSizeWithFlags_Values[q12] - | q14 : int(1..2)]) - | q12 : int(1..2)]), - and([s_ExplicitVarSizeWithDummy[q16] != 3 -> - or([s_ExplicitVarSizeWithFlags_Flags[q18] /\ - s_ExplicitVarSizeWithFlags_Values[q18] = s_ExplicitVarSizeWithDummy[q16] - | q18 : int(1..2)]) - | q16 : int(1..2)]), - and([s_ExplicitVarSizeWithFlags_Flags[q20] -> s_Occurrence[s_ExplicitVarSizeWithFlags_Values[q20]] - | q20 : int(1..2)]), - and([s_Occurrence[q21] -> - or([s_ExplicitVarSizeWithFlags_Flags[q23] /\ s_ExplicitVarSizeWithFlags_Values[q23] = q21 | q23 : int(1..2)]) - | q21 : int(1..2)]) - diff --git a/tests/exhaustive/basic/set_card_00/expected/model_2_2_1-solution000001.solution b/tests/exhaustive/basic/set_card_00/expected/model_2_2_1-solution000001.solution deleted file mode 100644 index 6c0d0fdad8..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_2_2_1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting s be {1} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_2_2_1-solution000002.solution b/tests/exhaustive/basic/set_card_00/expected/model_2_2_1-solution000002.solution deleted file mode 100644 index 2ce5f2081f..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_2_2_1-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_2_2_1.eprime b/tests/exhaustive/basic/set_card_00/expected/model_2_2_1.eprime deleted file mode 100644 index 2130ba4508..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_2_2_1.eprime +++ /dev/null @@ -1,16 +0,0 @@ -language ESSENCE' 1.0 - -find s_ExplicitVarSizeWithDummy: matrix indexed by [int(1..2)] of int(1..3) -find s_Occurrence: matrix indexed by [int(1..2)] of bool -branching on [s_Occurrence, s_ExplicitVarSizeWithDummy] -such that - or([s_ExplicitVarSizeWithDummy[q7] != 3 /\ - s_ExplicitVarSizeWithDummy[q7] = sum([toInt(s_ExplicitVarSizeWithDummy[q9] != 3) | q9 : int(1..2)]) - | q7 : int(1..2)]), - s_ExplicitVarSizeWithDummy[1] < s_ExplicitVarSizeWithDummy[2] \/ s_ExplicitVarSizeWithDummy[1] = 3, - s_ExplicitVarSizeWithDummy[1] = 3 -> s_ExplicitVarSizeWithDummy[2] = 3, - and([s_Occurrence[q10] -> - or([s_ExplicitVarSizeWithDummy[q12] != 3 /\ s_ExplicitVarSizeWithDummy[q12] = q10 | q12 : int(1..2)]) - | q10 : int(1..2)]), - and([s_ExplicitVarSizeWithDummy[q14] != 3 -> s_Occurrence[s_ExplicitVarSizeWithDummy[q14]] | q14 : int(1..2)]) - diff --git a/tests/exhaustive/basic/set_card_00/expected/model_2_2_2-solution000001.solution b/tests/exhaustive/basic/set_card_00/expected/model_2_2_2-solution000001.solution deleted file mode 100644 index 2ce5f2081f..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_2_2_2-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_2_2_2-solution000002.solution b/tests/exhaustive/basic/set_card_00/expected/model_2_2_2-solution000002.solution deleted file mode 100644 index 6c0d0fdad8..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_2_2_2-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting s be {1} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_2_2_2.eprime b/tests/exhaustive/basic/set_card_00/expected/model_2_2_2.eprime deleted file mode 100644 index de77468609..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_2_2_2.eprime +++ /dev/null @@ -1,11 +0,0 @@ -language ESSENCE' 1.0 - -find s_ExplicitVarSizeWithDummy: matrix indexed by [int(1..2)] of int(1..3) -branching on [s_ExplicitVarSizeWithDummy] -such that - or([s_ExplicitVarSizeWithDummy[q6] != 3 /\ - s_ExplicitVarSizeWithDummy[q6] = sum([toInt(s_ExplicitVarSizeWithDummy[q8] != 3) | q8 : int(1..2)]) - | q6 : int(1..2)]), - s_ExplicitVarSizeWithDummy[1] < s_ExplicitVarSizeWithDummy[2] \/ s_ExplicitVarSizeWithDummy[1] = 3, - s_ExplicitVarSizeWithDummy[1] = 3 -> s_ExplicitVarSizeWithDummy[2] = 3 - diff --git a/tests/exhaustive/basic/set_card_00/expected/model_2_2_3-solution000001.solution b/tests/exhaustive/basic/set_card_00/expected/model_2_2_3-solution000001.solution deleted file mode 100644 index 6c0d0fdad8..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_2_2_3-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting s be {1} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_2_2_3-solution000002.solution b/tests/exhaustive/basic/set_card_00/expected/model_2_2_3-solution000002.solution deleted file mode 100644 index 2ce5f2081f..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_2_2_3-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_2_2_3.eprime b/tests/exhaustive/basic/set_card_00/expected/model_2_2_3.eprime deleted file mode 100644 index d78add42d0..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_2_2_3.eprime +++ /dev/null @@ -1,26 +0,0 @@ -language ESSENCE' 1.0 - -find s_ExplicitVarSizeWithDummy: matrix indexed by [int(1..2)] of int(1..3) -find s_ExplicitVarSizeWithMarker_Marker: int(0..2) -find s_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..2)] of int(1..2) -branching on [s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithMarker_Values, s_ExplicitVarSizeWithDummy] -such that - or([s_ExplicitVarSizeWithDummy[q17] != 3 /\ - s_ExplicitVarSizeWithDummy[q17] = sum([toInt(s_ExplicitVarSizeWithDummy[q19] != 3) | q19 : int(1..2)]) - | q17 : int(1..2)]), - s_ExplicitVarSizeWithDummy[1] < s_ExplicitVarSizeWithDummy[2] \/ s_ExplicitVarSizeWithDummy[1] = 3, - s_ExplicitVarSizeWithDummy[1] = 3 -> s_ExplicitVarSizeWithDummy[2] = 3, - 2 <= s_ExplicitVarSizeWithMarker_Marker -> - s_ExplicitVarSizeWithMarker_Values[1] < s_ExplicitVarSizeWithMarker_Values[2], - and([q6 > s_ExplicitVarSizeWithMarker_Marker -> s_ExplicitVarSizeWithMarker_Values[q6] = 1 | q6 : int(1..2)]), - and([q9 <= s_ExplicitVarSizeWithMarker_Marker -> - or([s_ExplicitVarSizeWithDummy[q11] != 3 /\ - s_ExplicitVarSizeWithDummy[q11] = s_ExplicitVarSizeWithMarker_Values[q9] - | q11 : int(1..2)]) - | q9 : int(1..2)]), - and([s_ExplicitVarSizeWithDummy[q13] != 3 -> - or([q15 <= s_ExplicitVarSizeWithMarker_Marker /\ - s_ExplicitVarSizeWithMarker_Values[q15] = s_ExplicitVarSizeWithDummy[q13] - | q15 : int(1..2)]) - | q13 : int(1..2)]) - diff --git a/tests/exhaustive/basic/set_card_00/expected/model_2_2_4-solution000001.solution b/tests/exhaustive/basic/set_card_00/expected/model_2_2_4-solution000001.solution deleted file mode 100644 index 6c0d0fdad8..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_2_2_4-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting s be {1} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_2_2_4-solution000002.solution b/tests/exhaustive/basic/set_card_00/expected/model_2_2_4-solution000002.solution deleted file mode 100644 index 2ce5f2081f..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_2_2_4-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_2_2_4.eprime b/tests/exhaustive/basic/set_card_00/expected/model_2_2_4.eprime deleted file mode 100644 index e0885d30f9..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_2_2_4.eprime +++ /dev/null @@ -1,26 +0,0 @@ -language ESSENCE' 1.0 - -find s_ExplicitVarSizeWithDummy: matrix indexed by [int(1..2)] of int(1..3) -find s_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..2)] of bool -find s_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..2)] of int(1..2) -branching on [s_ExplicitVarSizeWithFlags_Flags, s_ExplicitVarSizeWithFlags_Values, s_ExplicitVarSizeWithDummy] -such that - or([s_ExplicitVarSizeWithDummy[q19] != 3 /\ - s_ExplicitVarSizeWithDummy[q19] = sum([toInt(s_ExplicitVarSizeWithDummy[q21] != 3) | q21 : int(1..2)]) - | q19 : int(1..2)]), - s_ExplicitVarSizeWithDummy[1] < s_ExplicitVarSizeWithDummy[2] \/ s_ExplicitVarSizeWithDummy[1] = 3, - s_ExplicitVarSizeWithDummy[1] = 3 -> s_ExplicitVarSizeWithDummy[2] = 3, - s_ExplicitVarSizeWithFlags_Flags[2] -> s_ExplicitVarSizeWithFlags_Values[1] < s_ExplicitVarSizeWithFlags_Values[2], - and([s_ExplicitVarSizeWithFlags_Flags[q6] = false -> s_ExplicitVarSizeWithFlags_Values[q6] = 1 | q6 : int(1..2)]), - s_ExplicitVarSizeWithFlags_Flags[2] -> s_ExplicitVarSizeWithFlags_Flags[1], - and([s_ExplicitVarSizeWithFlags_Flags[q11] -> - or([s_ExplicitVarSizeWithDummy[q13] != 3 /\ - s_ExplicitVarSizeWithDummy[q13] = s_ExplicitVarSizeWithFlags_Values[q11] - | q13 : int(1..2)]) - | q11 : int(1..2)]), - and([s_ExplicitVarSizeWithDummy[q15] != 3 -> - or([s_ExplicitVarSizeWithFlags_Flags[q17] /\ - s_ExplicitVarSizeWithFlags_Values[q17] = s_ExplicitVarSizeWithDummy[q15] - | q17 : int(1..2)]) - | q15 : int(1..2)]) - diff --git a/tests/exhaustive/basic/set_card_00/expected/model_2_3_1-solution000001.solution b/tests/exhaustive/basic/set_card_00/expected/model_2_3_1-solution000001.solution deleted file mode 100644 index 6c0d0fdad8..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_2_3_1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting s be {1} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_2_3_1-solution000002.solution b/tests/exhaustive/basic/set_card_00/expected/model_2_3_1-solution000002.solution deleted file mode 100644 index 2ce5f2081f..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_2_3_1-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_2_3_1.eprime b/tests/exhaustive/basic/set_card_00/expected/model_2_3_1.eprime deleted file mode 100644 index bb65736cc9..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_2_3_1.eprime +++ /dev/null @@ -1,38 +0,0 @@ -language ESSENCE' 1.0 - -find s_ExplicitVarSizeWithDummy: matrix indexed by [int(1..2)] of int(1..3) -find s_ExplicitVarSizeWithMarker_Marker: int(0..2) -find s_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..2)] of int(1..2) -find s_Occurrence: matrix indexed by [int(1..2)] of bool -branching on - [s_Occurrence, s_ExplicitVarSizeWithDummy, s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithMarker_Values] -such that - or([q18 <= s_ExplicitVarSizeWithMarker_Marker /\ - s_ExplicitVarSizeWithMarker_Values[q18] = sum([toInt(s_ExplicitVarSizeWithDummy[q20] != 3) | q20 : int(1..2)]) - | q18 : int(1..2)]), - s_ExplicitVarSizeWithDummy[1] < s_ExplicitVarSizeWithDummy[2] \/ s_ExplicitVarSizeWithDummy[1] = 3, - s_ExplicitVarSizeWithDummy[1] = 3 -> s_ExplicitVarSizeWithDummy[2] = 3, - 2 <= s_ExplicitVarSizeWithMarker_Marker -> - s_ExplicitVarSizeWithMarker_Values[1] < s_ExplicitVarSizeWithMarker_Values[2], - and([q6 > s_ExplicitVarSizeWithMarker_Marker -> s_ExplicitVarSizeWithMarker_Values[q6] = 1 | q6 : int(1..2)]), - and([q9 <= s_ExplicitVarSizeWithMarker_Marker -> - or([s_ExplicitVarSizeWithDummy[q11] != 3 /\ - s_ExplicitVarSizeWithDummy[q11] = s_ExplicitVarSizeWithMarker_Values[q9] - | q11 : int(1..2)]) - | q9 : int(1..2)]), - and([s_ExplicitVarSizeWithDummy[q13] != 3 -> - or([q15 <= s_ExplicitVarSizeWithMarker_Marker /\ - s_ExplicitVarSizeWithMarker_Values[q15] = s_ExplicitVarSizeWithDummy[q13] - | q15 : int(1..2)]) - | q13 : int(1..2)]), - and([s_Occurrence[q21] -> - or([s_ExplicitVarSizeWithDummy[q23] != 3 /\ s_ExplicitVarSizeWithDummy[q23] = q21 | q23 : int(1..2)]) - | q21 : int(1..2)]), - and([s_ExplicitVarSizeWithDummy[q25] != 3 -> s_Occurrence[s_ExplicitVarSizeWithDummy[q25]] | q25 : int(1..2)]), - and([s_Occurrence[q26] -> - or([q28 <= s_ExplicitVarSizeWithMarker_Marker /\ s_ExplicitVarSizeWithMarker_Values[q28] = q26 - | q28 : int(1..2)]) - | q26 : int(1..2)]), - and([q30 <= s_ExplicitVarSizeWithMarker_Marker -> s_Occurrence[s_ExplicitVarSizeWithMarker_Values[q30]] - | q30 : int(1..2)]) - diff --git a/tests/exhaustive/basic/set_card_00/expected/model_2_3_2-solution000001.solution b/tests/exhaustive/basic/set_card_00/expected/model_2_3_2-solution000001.solution deleted file mode 100644 index 6c0d0fdad8..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_2_3_2-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting s be {1} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_2_3_2-solution000002.solution b/tests/exhaustive/basic/set_card_00/expected/model_2_3_2-solution000002.solution deleted file mode 100644 index 2ce5f2081f..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_2_3_2-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_2_3_2.eprime b/tests/exhaustive/basic/set_card_00/expected/model_2_3_2.eprime deleted file mode 100644 index ab23a453ce..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_2_3_2.eprime +++ /dev/null @@ -1,26 +0,0 @@ -language ESSENCE' 1.0 - -find s_ExplicitVarSizeWithDummy: matrix indexed by [int(1..2)] of int(1..3) -find s_ExplicitVarSizeWithMarker_Marker: int(0..2) -find s_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..2)] of int(1..2) -branching on [s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithMarker_Values, s_ExplicitVarSizeWithDummy] -such that - or([q17 <= s_ExplicitVarSizeWithMarker_Marker /\ - s_ExplicitVarSizeWithMarker_Values[q17] = sum([toInt(s_ExplicitVarSizeWithDummy[q19] != 3) | q19 : int(1..2)]) - | q17 : int(1..2)]), - s_ExplicitVarSizeWithDummy[1] < s_ExplicitVarSizeWithDummy[2] \/ s_ExplicitVarSizeWithDummy[1] = 3, - s_ExplicitVarSizeWithDummy[1] = 3 -> s_ExplicitVarSizeWithDummy[2] = 3, - 2 <= s_ExplicitVarSizeWithMarker_Marker -> - s_ExplicitVarSizeWithMarker_Values[1] < s_ExplicitVarSizeWithMarker_Values[2], - and([q6 > s_ExplicitVarSizeWithMarker_Marker -> s_ExplicitVarSizeWithMarker_Values[q6] = 1 | q6 : int(1..2)]), - and([q9 <= s_ExplicitVarSizeWithMarker_Marker -> - or([s_ExplicitVarSizeWithDummy[q11] != 3 /\ - s_ExplicitVarSizeWithDummy[q11] = s_ExplicitVarSizeWithMarker_Values[q9] - | q11 : int(1..2)]) - | q9 : int(1..2)]), - and([s_ExplicitVarSizeWithDummy[q13] != 3 -> - or([q15 <= s_ExplicitVarSizeWithMarker_Marker /\ - s_ExplicitVarSizeWithMarker_Values[q15] = s_ExplicitVarSizeWithDummy[q13] - | q15 : int(1..2)]) - | q13 : int(1..2)]) - diff --git a/tests/exhaustive/basic/set_card_00/expected/model_2_3_3-solution000001.solution b/tests/exhaustive/basic/set_card_00/expected/model_2_3_3-solution000001.solution deleted file mode 100644 index 6c0d0fdad8..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_2_3_3-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting s be {1} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_2_3_3-solution000002.solution b/tests/exhaustive/basic/set_card_00/expected/model_2_3_3-solution000002.solution deleted file mode 100644 index 2ce5f2081f..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_2_3_3-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_2_3_3.eprime b/tests/exhaustive/basic/set_card_00/expected/model_2_3_3.eprime deleted file mode 100644 index ab23a453ce..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_2_3_3.eprime +++ /dev/null @@ -1,26 +0,0 @@ -language ESSENCE' 1.0 - -find s_ExplicitVarSizeWithDummy: matrix indexed by [int(1..2)] of int(1..3) -find s_ExplicitVarSizeWithMarker_Marker: int(0..2) -find s_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..2)] of int(1..2) -branching on [s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithMarker_Values, s_ExplicitVarSizeWithDummy] -such that - or([q17 <= s_ExplicitVarSizeWithMarker_Marker /\ - s_ExplicitVarSizeWithMarker_Values[q17] = sum([toInt(s_ExplicitVarSizeWithDummy[q19] != 3) | q19 : int(1..2)]) - | q17 : int(1..2)]), - s_ExplicitVarSizeWithDummy[1] < s_ExplicitVarSizeWithDummy[2] \/ s_ExplicitVarSizeWithDummy[1] = 3, - s_ExplicitVarSizeWithDummy[1] = 3 -> s_ExplicitVarSizeWithDummy[2] = 3, - 2 <= s_ExplicitVarSizeWithMarker_Marker -> - s_ExplicitVarSizeWithMarker_Values[1] < s_ExplicitVarSizeWithMarker_Values[2], - and([q6 > s_ExplicitVarSizeWithMarker_Marker -> s_ExplicitVarSizeWithMarker_Values[q6] = 1 | q6 : int(1..2)]), - and([q9 <= s_ExplicitVarSizeWithMarker_Marker -> - or([s_ExplicitVarSizeWithDummy[q11] != 3 /\ - s_ExplicitVarSizeWithDummy[q11] = s_ExplicitVarSizeWithMarker_Values[q9] - | q11 : int(1..2)]) - | q9 : int(1..2)]), - and([s_ExplicitVarSizeWithDummy[q13] != 3 -> - or([q15 <= s_ExplicitVarSizeWithMarker_Marker /\ - s_ExplicitVarSizeWithMarker_Values[q15] = s_ExplicitVarSizeWithDummy[q13] - | q15 : int(1..2)]) - | q13 : int(1..2)]) - diff --git a/tests/exhaustive/basic/set_card_00/expected/model_2_3_4-solution000001.solution b/tests/exhaustive/basic/set_card_00/expected/model_2_3_4-solution000001.solution deleted file mode 100644 index 6c0d0fdad8..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_2_3_4-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting s be {1} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_2_3_4-solution000002.solution b/tests/exhaustive/basic/set_card_00/expected/model_2_3_4-solution000002.solution deleted file mode 100644 index 2ce5f2081f..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_2_3_4-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_2_3_4.eprime b/tests/exhaustive/basic/set_card_00/expected/model_2_3_4.eprime deleted file mode 100644 index b8027d9587..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_2_3_4.eprime +++ /dev/null @@ -1,54 +0,0 @@ -language ESSENCE' 1.0 - -find s_ExplicitVarSizeWithDummy: matrix indexed by [int(1..2)] of int(1..3) -find s_ExplicitVarSizeWithMarker_Marker: int(0..2) -find s_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..2)] of int(1..2) -find s_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..2)] of bool -find s_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..2)] of int(1..2) -branching on - [s_ExplicitVarSizeWithFlags_Flags, s_ExplicitVarSizeWithFlags_Values, s_ExplicitVarSizeWithDummy, - s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithMarker_Values] -such that - or([q38 <= s_ExplicitVarSizeWithMarker_Marker /\ - s_ExplicitVarSizeWithMarker_Values[q38] = sum([toInt(s_ExplicitVarSizeWithDummy[q40] != 3) | q40 : int(1..2)]) - | q38 : int(1..2)]), - s_ExplicitVarSizeWithDummy[1] < s_ExplicitVarSizeWithDummy[2] \/ s_ExplicitVarSizeWithDummy[1] = 3, - s_ExplicitVarSizeWithDummy[1] = 3 -> s_ExplicitVarSizeWithDummy[2] = 3, - 2 <= s_ExplicitVarSizeWithMarker_Marker -> - s_ExplicitVarSizeWithMarker_Values[1] < s_ExplicitVarSizeWithMarker_Values[2], - and([q6 > s_ExplicitVarSizeWithMarker_Marker -> s_ExplicitVarSizeWithMarker_Values[q6] = 1 | q6 : int(1..2)]), - and([q9 <= s_ExplicitVarSizeWithMarker_Marker -> - or([s_ExplicitVarSizeWithDummy[q11] != 3 /\ - s_ExplicitVarSizeWithDummy[q11] = s_ExplicitVarSizeWithMarker_Values[q9] - | q11 : int(1..2)]) - | q9 : int(1..2)]), - and([s_ExplicitVarSizeWithDummy[q13] != 3 -> - or([q15 <= s_ExplicitVarSizeWithMarker_Marker /\ - s_ExplicitVarSizeWithMarker_Values[q15] = s_ExplicitVarSizeWithDummy[q13] - | q15 : int(1..2)]) - | q13 : int(1..2)]), - s_ExplicitVarSizeWithFlags_Flags[2] -> s_ExplicitVarSizeWithFlags_Values[1] < s_ExplicitVarSizeWithFlags_Values[2], - and([s_ExplicitVarSizeWithFlags_Flags[q17] = false -> s_ExplicitVarSizeWithFlags_Values[q17] = 1 - | q17 : int(1..2)]), - s_ExplicitVarSizeWithFlags_Flags[2] -> s_ExplicitVarSizeWithFlags_Flags[1], - and([s_ExplicitVarSizeWithFlags_Flags[q22] -> - or([s_ExplicitVarSizeWithDummy[q24] != 3 /\ - s_ExplicitVarSizeWithDummy[q24] = s_ExplicitVarSizeWithFlags_Values[q22] - | q24 : int(1..2)]) - | q22 : int(1..2)]), - and([s_ExplicitVarSizeWithDummy[q26] != 3 -> - or([s_ExplicitVarSizeWithFlags_Flags[q28] /\ - s_ExplicitVarSizeWithFlags_Values[q28] = s_ExplicitVarSizeWithDummy[q26] - | q28 : int(1..2)]) - | q26 : int(1..2)]), - and([s_ExplicitVarSizeWithFlags_Flags[q30] -> - or([q32 <= s_ExplicitVarSizeWithMarker_Marker /\ - s_ExplicitVarSizeWithMarker_Values[q32] = s_ExplicitVarSizeWithFlags_Values[q30] - | q32 : int(1..2)]) - | q30 : int(1..2)]), - and([q34 <= s_ExplicitVarSizeWithMarker_Marker -> - or([s_ExplicitVarSizeWithFlags_Flags[q36] /\ - s_ExplicitVarSizeWithFlags_Values[q36] = s_ExplicitVarSizeWithMarker_Values[q34] - | q36 : int(1..2)]) - | q34 : int(1..2)]) - diff --git a/tests/exhaustive/basic/set_card_00/expected/model_2_4_1-solution000001.solution b/tests/exhaustive/basic/set_card_00/expected/model_2_4_1-solution000001.solution deleted file mode 100644 index 6c0d0fdad8..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_2_4_1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting s be {1} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_2_4_1-solution000002.solution b/tests/exhaustive/basic/set_card_00/expected/model_2_4_1-solution000002.solution deleted file mode 100644 index 2ce5f2081f..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_2_4_1-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_2_4_1.eprime b/tests/exhaustive/basic/set_card_00/expected/model_2_4_1.eprime deleted file mode 100644 index 9b0944284e..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_2_4_1.eprime +++ /dev/null @@ -1,37 +0,0 @@ -language ESSENCE' 1.0 - -find s_ExplicitVarSizeWithDummy: matrix indexed by [int(1..2)] of int(1..3) -find s_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..2)] of bool -find s_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..2)] of int(1..2) -find s_Occurrence: matrix indexed by [int(1..2)] of bool -branching on - [s_Occurrence, s_ExplicitVarSizeWithDummy, s_ExplicitVarSizeWithFlags_Flags, s_ExplicitVarSizeWithFlags_Values] -such that - or([s_ExplicitVarSizeWithFlags_Flags[q30] /\ - s_ExplicitVarSizeWithFlags_Values[q30] = sum([toInt(s_ExplicitVarSizeWithDummy[q32] != 3) | q32 : int(1..2)]) - | q30 : int(1..2)]), - s_ExplicitVarSizeWithDummy[1] < s_ExplicitVarSizeWithDummy[2] \/ s_ExplicitVarSizeWithDummy[1] = 3, - s_ExplicitVarSizeWithDummy[1] = 3 -> s_ExplicitVarSizeWithDummy[2] = 3, - s_ExplicitVarSizeWithFlags_Flags[2] -> s_ExplicitVarSizeWithFlags_Values[1] < s_ExplicitVarSizeWithFlags_Values[2], - and([s_ExplicitVarSizeWithFlags_Flags[q6] = false -> s_ExplicitVarSizeWithFlags_Values[q6] = 1 | q6 : int(1..2)]), - s_ExplicitVarSizeWithFlags_Flags[2] -> s_ExplicitVarSizeWithFlags_Flags[1], - and([s_ExplicitVarSizeWithFlags_Flags[q11] -> - or([s_ExplicitVarSizeWithDummy[q13] != 3 /\ - s_ExplicitVarSizeWithDummy[q13] = s_ExplicitVarSizeWithFlags_Values[q11] - | q13 : int(1..2)]) - | q11 : int(1..2)]), - and([s_ExplicitVarSizeWithDummy[q15] != 3 -> - or([s_ExplicitVarSizeWithFlags_Flags[q17] /\ - s_ExplicitVarSizeWithFlags_Values[q17] = s_ExplicitVarSizeWithDummy[q15] - | q17 : int(1..2)]) - | q15 : int(1..2)]), - and([s_Occurrence[q19] -> - or([s_ExplicitVarSizeWithDummy[q21] != 3 /\ s_ExplicitVarSizeWithDummy[q21] = q19 | q21 : int(1..2)]) - | q19 : int(1..2)]), - and([s_ExplicitVarSizeWithDummy[q23] != 3 -> s_Occurrence[s_ExplicitVarSizeWithDummy[q23]] | q23 : int(1..2)]), - and([s_Occurrence[q24] -> - or([s_ExplicitVarSizeWithFlags_Flags[q26] /\ s_ExplicitVarSizeWithFlags_Values[q26] = q24 | q26 : int(1..2)]) - | q24 : int(1..2)]), - and([s_ExplicitVarSizeWithFlags_Flags[q28] -> s_Occurrence[s_ExplicitVarSizeWithFlags_Values[q28]] - | q28 : int(1..2)]) - diff --git a/tests/exhaustive/basic/set_card_00/expected/model_2_4_2-solution000001.solution b/tests/exhaustive/basic/set_card_00/expected/model_2_4_2-solution000001.solution deleted file mode 100644 index 6c0d0fdad8..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_2_4_2-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting s be {1} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_2_4_2-solution000002.solution b/tests/exhaustive/basic/set_card_00/expected/model_2_4_2-solution000002.solution deleted file mode 100644 index 2ce5f2081f..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_2_4_2-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_2_4_2.eprime b/tests/exhaustive/basic/set_card_00/expected/model_2_4_2.eprime deleted file mode 100644 index 52e3cd4bb4..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_2_4_2.eprime +++ /dev/null @@ -1,26 +0,0 @@ -language ESSENCE' 1.0 - -find s_ExplicitVarSizeWithDummy: matrix indexed by [int(1..2)] of int(1..3) -find s_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..2)] of bool -find s_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..2)] of int(1..2) -branching on [s_ExplicitVarSizeWithFlags_Flags, s_ExplicitVarSizeWithFlags_Values, s_ExplicitVarSizeWithDummy] -such that - or([s_ExplicitVarSizeWithFlags_Flags[q19] /\ - s_ExplicitVarSizeWithFlags_Values[q19] = sum([toInt(s_ExplicitVarSizeWithDummy[q21] != 3) | q21 : int(1..2)]) - | q19 : int(1..2)]), - s_ExplicitVarSizeWithDummy[1] < s_ExplicitVarSizeWithDummy[2] \/ s_ExplicitVarSizeWithDummy[1] = 3, - s_ExplicitVarSizeWithDummy[1] = 3 -> s_ExplicitVarSizeWithDummy[2] = 3, - s_ExplicitVarSizeWithFlags_Flags[2] -> s_ExplicitVarSizeWithFlags_Values[1] < s_ExplicitVarSizeWithFlags_Values[2], - and([s_ExplicitVarSizeWithFlags_Flags[q6] = false -> s_ExplicitVarSizeWithFlags_Values[q6] = 1 | q6 : int(1..2)]), - s_ExplicitVarSizeWithFlags_Flags[2] -> s_ExplicitVarSizeWithFlags_Flags[1], - and([s_ExplicitVarSizeWithFlags_Flags[q11] -> - or([s_ExplicitVarSizeWithDummy[q13] != 3 /\ - s_ExplicitVarSizeWithDummy[q13] = s_ExplicitVarSizeWithFlags_Values[q11] - | q13 : int(1..2)]) - | q11 : int(1..2)]), - and([s_ExplicitVarSizeWithDummy[q15] != 3 -> - or([s_ExplicitVarSizeWithFlags_Flags[q17] /\ - s_ExplicitVarSizeWithFlags_Values[q17] = s_ExplicitVarSizeWithDummy[q15] - | q17 : int(1..2)]) - | q15 : int(1..2)]) - diff --git a/tests/exhaustive/basic/set_card_00/expected/model_2_4_3-solution000001.solution b/tests/exhaustive/basic/set_card_00/expected/model_2_4_3-solution000001.solution deleted file mode 100644 index 6c0d0fdad8..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_2_4_3-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting s be {1} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_2_4_3-solution000002.solution b/tests/exhaustive/basic/set_card_00/expected/model_2_4_3-solution000002.solution deleted file mode 100644 index 2ce5f2081f..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_2_4_3-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_2_4_3.eprime b/tests/exhaustive/basic/set_card_00/expected/model_2_4_3.eprime deleted file mode 100644 index d77907f01f..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_2_4_3.eprime +++ /dev/null @@ -1,53 +0,0 @@ -language ESSENCE' 1.0 - -find s_ExplicitVarSizeWithDummy: matrix indexed by [int(1..2)] of int(1..3) -find s_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..2)] of bool -find s_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..2)] of int(1..2) -find s_ExplicitVarSizeWithMarker_Marker: int(0..2) -find s_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..2)] of int(1..2) -branching on - [s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithMarker_Values, s_ExplicitVarSizeWithDummy, - s_ExplicitVarSizeWithFlags_Flags, s_ExplicitVarSizeWithFlags_Values] -such that - or([s_ExplicitVarSizeWithFlags_Flags[q38] /\ - s_ExplicitVarSizeWithFlags_Values[q38] = sum([toInt(s_ExplicitVarSizeWithDummy[q40] != 3) | q40 : int(1..2)]) - | q38 : int(1..2)]), - s_ExplicitVarSizeWithDummy[1] < s_ExplicitVarSizeWithDummy[2] \/ s_ExplicitVarSizeWithDummy[1] = 3, - s_ExplicitVarSizeWithDummy[1] = 3 -> s_ExplicitVarSizeWithDummy[2] = 3, - s_ExplicitVarSizeWithFlags_Flags[2] -> s_ExplicitVarSizeWithFlags_Values[1] < s_ExplicitVarSizeWithFlags_Values[2], - and([s_ExplicitVarSizeWithFlags_Flags[q6] = false -> s_ExplicitVarSizeWithFlags_Values[q6] = 1 | q6 : int(1..2)]), - s_ExplicitVarSizeWithFlags_Flags[2] -> s_ExplicitVarSizeWithFlags_Flags[1], - and([s_ExplicitVarSizeWithFlags_Flags[q11] -> - or([s_ExplicitVarSizeWithDummy[q13] != 3 /\ - s_ExplicitVarSizeWithDummy[q13] = s_ExplicitVarSizeWithFlags_Values[q11] - | q13 : int(1..2)]) - | q11 : int(1..2)]), - and([s_ExplicitVarSizeWithDummy[q15] != 3 -> - or([s_ExplicitVarSizeWithFlags_Flags[q17] /\ - s_ExplicitVarSizeWithFlags_Values[q17] = s_ExplicitVarSizeWithDummy[q15] - | q17 : int(1..2)]) - | q15 : int(1..2)]), - 2 <= s_ExplicitVarSizeWithMarker_Marker -> - s_ExplicitVarSizeWithMarker_Values[1] < s_ExplicitVarSizeWithMarker_Values[2], - and([q19 > s_ExplicitVarSizeWithMarker_Marker -> s_ExplicitVarSizeWithMarker_Values[q19] = 1 | q19 : int(1..2)]), - and([q22 <= s_ExplicitVarSizeWithMarker_Marker -> - or([s_ExplicitVarSizeWithDummy[q24] != 3 /\ - s_ExplicitVarSizeWithDummy[q24] = s_ExplicitVarSizeWithMarker_Values[q22] - | q24 : int(1..2)]) - | q22 : int(1..2)]), - and([s_ExplicitVarSizeWithDummy[q26] != 3 -> - or([q28 <= s_ExplicitVarSizeWithMarker_Marker /\ - s_ExplicitVarSizeWithMarker_Values[q28] = s_ExplicitVarSizeWithDummy[q26] - | q28 : int(1..2)]) - | q26 : int(1..2)]), - and([q30 <= s_ExplicitVarSizeWithMarker_Marker -> - or([s_ExplicitVarSizeWithFlags_Flags[q32] /\ - s_ExplicitVarSizeWithFlags_Values[q32] = s_ExplicitVarSizeWithMarker_Values[q30] - | q32 : int(1..2)]) - | q30 : int(1..2)]), - and([s_ExplicitVarSizeWithFlags_Flags[q34] -> - or([q36 <= s_ExplicitVarSizeWithMarker_Marker /\ - s_ExplicitVarSizeWithMarker_Values[q36] = s_ExplicitVarSizeWithFlags_Values[q34] - | q36 : int(1..2)]) - | q34 : int(1..2)]) - diff --git a/tests/exhaustive/basic/set_card_00/expected/model_2_4_4-solution000001.solution b/tests/exhaustive/basic/set_card_00/expected/model_2_4_4-solution000001.solution deleted file mode 100644 index 6c0d0fdad8..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_2_4_4-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting s be {1} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_2_4_4-solution000002.solution b/tests/exhaustive/basic/set_card_00/expected/model_2_4_4-solution000002.solution deleted file mode 100644 index 2ce5f2081f..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_2_4_4-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_2_4_4.eprime b/tests/exhaustive/basic/set_card_00/expected/model_2_4_4.eprime deleted file mode 100644 index 52e3cd4bb4..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_2_4_4.eprime +++ /dev/null @@ -1,26 +0,0 @@ -language ESSENCE' 1.0 - -find s_ExplicitVarSizeWithDummy: matrix indexed by [int(1..2)] of int(1..3) -find s_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..2)] of bool -find s_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..2)] of int(1..2) -branching on [s_ExplicitVarSizeWithFlags_Flags, s_ExplicitVarSizeWithFlags_Values, s_ExplicitVarSizeWithDummy] -such that - or([s_ExplicitVarSizeWithFlags_Flags[q19] /\ - s_ExplicitVarSizeWithFlags_Values[q19] = sum([toInt(s_ExplicitVarSizeWithDummy[q21] != 3) | q21 : int(1..2)]) - | q19 : int(1..2)]), - s_ExplicitVarSizeWithDummy[1] < s_ExplicitVarSizeWithDummy[2] \/ s_ExplicitVarSizeWithDummy[1] = 3, - s_ExplicitVarSizeWithDummy[1] = 3 -> s_ExplicitVarSizeWithDummy[2] = 3, - s_ExplicitVarSizeWithFlags_Flags[2] -> s_ExplicitVarSizeWithFlags_Values[1] < s_ExplicitVarSizeWithFlags_Values[2], - and([s_ExplicitVarSizeWithFlags_Flags[q6] = false -> s_ExplicitVarSizeWithFlags_Values[q6] = 1 | q6 : int(1..2)]), - s_ExplicitVarSizeWithFlags_Flags[2] -> s_ExplicitVarSizeWithFlags_Flags[1], - and([s_ExplicitVarSizeWithFlags_Flags[q11] -> - or([s_ExplicitVarSizeWithDummy[q13] != 3 /\ - s_ExplicitVarSizeWithDummy[q13] = s_ExplicitVarSizeWithFlags_Values[q11] - | q13 : int(1..2)]) - | q11 : int(1..2)]), - and([s_ExplicitVarSizeWithDummy[q15] != 3 -> - or([s_ExplicitVarSizeWithFlags_Flags[q17] /\ - s_ExplicitVarSizeWithFlags_Values[q17] = s_ExplicitVarSizeWithDummy[q15] - | q17 : int(1..2)]) - | q15 : int(1..2)]) - diff --git a/tests/exhaustive/basic/set_card_00/expected/model_3_1_1-solution000001.solution b/tests/exhaustive/basic/set_card_00/expected/model_3_1_1-solution000001.solution deleted file mode 100644 index 6c0d0fdad8..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_3_1_1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting s be {1} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_3_1_1-solution000002.solution b/tests/exhaustive/basic/set_card_00/expected/model_3_1_1-solution000002.solution deleted file mode 100644 index 2ce5f2081f..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_3_1_1-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_3_1_1.eprime b/tests/exhaustive/basic/set_card_00/expected/model_3_1_1.eprime deleted file mode 100644 index e844855cfd..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_3_1_1.eprime +++ /dev/null @@ -1,17 +0,0 @@ -language ESSENCE' 1.0 - -find s_ExplicitVarSizeWithMarker_Marker: int(0..2) -find s_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..2)] of int(1..2) -find s_Occurrence: matrix indexed by [int(1..2)] of bool -branching on [s_Occurrence, s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithMarker_Values] -such that - s_Occurrence[s_ExplicitVarSizeWithMarker_Marker], - 2 <= s_ExplicitVarSizeWithMarker_Marker -> - s_ExplicitVarSizeWithMarker_Values[1] < s_ExplicitVarSizeWithMarker_Values[2], - and([q2 > s_ExplicitVarSizeWithMarker_Marker -> s_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..2)]), - and([s_Occurrence[q5] -> - or([q7 <= s_ExplicitVarSizeWithMarker_Marker /\ s_ExplicitVarSizeWithMarker_Values[q7] = q5 | q7 : int(1..2)]) - | q5 : int(1..2)]), - and([q9 <= s_ExplicitVarSizeWithMarker_Marker -> s_Occurrence[s_ExplicitVarSizeWithMarker_Values[q9]] - | q9 : int(1..2)]) - diff --git a/tests/exhaustive/basic/set_card_00/expected/model_3_1_2-solution000001.solution b/tests/exhaustive/basic/set_card_00/expected/model_3_1_2-solution000001.solution deleted file mode 100644 index 2ce5f2081f..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_3_1_2-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_3_1_2-solution000002.solution b/tests/exhaustive/basic/set_card_00/expected/model_3_1_2-solution000002.solution deleted file mode 100644 index 6c0d0fdad8..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_3_1_2-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting s be {1} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_3_1_2.eprime b/tests/exhaustive/basic/set_card_00/expected/model_3_1_2.eprime deleted file mode 100644 index 14e09f9356..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_3_1_2.eprime +++ /dev/null @@ -1,36 +0,0 @@ -language ESSENCE' 1.0 - -find s_ExplicitVarSizeWithMarker_Marker: int(0..2) -find s_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..2)] of int(1..2) -find s_Occurrence: matrix indexed by [int(1..2)] of bool -find s_ExplicitVarSizeWithDummy: matrix indexed by [int(1..2)] of int(1..3) -branching on - [s_ExplicitVarSizeWithDummy, s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithMarker_Values, s_Occurrence] -such that - s_Occurrence[s_ExplicitVarSizeWithMarker_Marker], - 2 <= s_ExplicitVarSizeWithMarker_Marker -> - s_ExplicitVarSizeWithMarker_Values[1] < s_ExplicitVarSizeWithMarker_Values[2], - and([q2 > s_ExplicitVarSizeWithMarker_Marker -> s_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..2)]), - and([s_Occurrence[q22] -> - or([q24 <= s_ExplicitVarSizeWithMarker_Marker /\ s_ExplicitVarSizeWithMarker_Values[q24] = q22 - | q24 : int(1..2)]) - | q22 : int(1..2)]), - and([q26 <= s_ExplicitVarSizeWithMarker_Marker -> s_Occurrence[s_ExplicitVarSizeWithMarker_Values[q26]] - | q26 : int(1..2)]), - s_ExplicitVarSizeWithDummy[1] < s_ExplicitVarSizeWithDummy[2] \/ s_ExplicitVarSizeWithDummy[1] = 3, - s_ExplicitVarSizeWithDummy[1] = 3 -> s_ExplicitVarSizeWithDummy[2] = 3, - and([s_ExplicitVarSizeWithDummy[q10] != 3 -> - or([q12 <= s_ExplicitVarSizeWithMarker_Marker /\ - s_ExplicitVarSizeWithMarker_Values[q12] = s_ExplicitVarSizeWithDummy[q10] - | q12 : int(1..2)]) - | q10 : int(1..2)]), - and([q14 <= s_ExplicitVarSizeWithMarker_Marker -> - or([s_ExplicitVarSizeWithDummy[q16] != 3 /\ - s_ExplicitVarSizeWithDummy[q16] = s_ExplicitVarSizeWithMarker_Values[q14] - | q16 : int(1..2)]) - | q14 : int(1..2)]), - and([s_ExplicitVarSizeWithDummy[q18] != 3 -> s_Occurrence[s_ExplicitVarSizeWithDummy[q18]] | q18 : int(1..2)]), - and([s_Occurrence[q19] -> - or([s_ExplicitVarSizeWithDummy[q21] != 3 /\ s_ExplicitVarSizeWithDummy[q21] = q19 | q21 : int(1..2)]) - | q19 : int(1..2)]) - diff --git a/tests/exhaustive/basic/set_card_00/expected/model_3_1_3-solution000001.solution b/tests/exhaustive/basic/set_card_00/expected/model_3_1_3-solution000001.solution deleted file mode 100644 index 6c0d0fdad8..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_3_1_3-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting s be {1} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_3_1_3-solution000002.solution b/tests/exhaustive/basic/set_card_00/expected/model_3_1_3-solution000002.solution deleted file mode 100644 index 2ce5f2081f..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_3_1_3-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_3_1_3.eprime b/tests/exhaustive/basic/set_card_00/expected/model_3_1_3.eprime deleted file mode 100644 index e844855cfd..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_3_1_3.eprime +++ /dev/null @@ -1,17 +0,0 @@ -language ESSENCE' 1.0 - -find s_ExplicitVarSizeWithMarker_Marker: int(0..2) -find s_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..2)] of int(1..2) -find s_Occurrence: matrix indexed by [int(1..2)] of bool -branching on [s_Occurrence, s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithMarker_Values] -such that - s_Occurrence[s_ExplicitVarSizeWithMarker_Marker], - 2 <= s_ExplicitVarSizeWithMarker_Marker -> - s_ExplicitVarSizeWithMarker_Values[1] < s_ExplicitVarSizeWithMarker_Values[2], - and([q2 > s_ExplicitVarSizeWithMarker_Marker -> s_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..2)]), - and([s_Occurrence[q5] -> - or([q7 <= s_ExplicitVarSizeWithMarker_Marker /\ s_ExplicitVarSizeWithMarker_Values[q7] = q5 | q7 : int(1..2)]) - | q5 : int(1..2)]), - and([q9 <= s_ExplicitVarSizeWithMarker_Marker -> s_Occurrence[s_ExplicitVarSizeWithMarker_Values[q9]] - | q9 : int(1..2)]) - diff --git a/tests/exhaustive/basic/set_card_00/expected/model_3_1_4-solution000001.solution b/tests/exhaustive/basic/set_card_00/expected/model_3_1_4-solution000001.solution deleted file mode 100644 index 6c0d0fdad8..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_3_1_4-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting s be {1} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_3_1_4-solution000002.solution b/tests/exhaustive/basic/set_card_00/expected/model_3_1_4-solution000002.solution deleted file mode 100644 index 2ce5f2081f..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_3_1_4-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_3_1_4.eprime b/tests/exhaustive/basic/set_card_00/expected/model_3_1_4.eprime deleted file mode 100644 index 9425709c75..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_3_1_4.eprime +++ /dev/null @@ -1,40 +0,0 @@ -language ESSENCE' 1.0 - -find s_ExplicitVarSizeWithMarker_Marker: int(0..2) -find s_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..2)] of int(1..2) -find s_Occurrence: matrix indexed by [int(1..2)] of bool -find s_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..2)] of bool -find s_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..2)] of int(1..2) -branching on - [s_ExplicitVarSizeWithFlags_Flags, s_ExplicitVarSizeWithFlags_Values, s_ExplicitVarSizeWithMarker_Marker, - s_ExplicitVarSizeWithMarker_Values, s_Occurrence] -such that - s_Occurrence[s_ExplicitVarSizeWithMarker_Marker], - 2 <= s_ExplicitVarSizeWithMarker_Marker -> - s_ExplicitVarSizeWithMarker_Values[1] < s_ExplicitVarSizeWithMarker_Values[2], - and([q2 > s_ExplicitVarSizeWithMarker_Marker -> s_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..2)]), - and([s_Occurrence[q23] -> - or([q25 <= s_ExplicitVarSizeWithMarker_Marker /\ s_ExplicitVarSizeWithMarker_Values[q25] = q23 - | q25 : int(1..2)]) - | q23 : int(1..2)]), - and([q27 <= s_ExplicitVarSizeWithMarker_Marker -> s_Occurrence[s_ExplicitVarSizeWithMarker_Values[q27]] - | q27 : int(1..2)]), - s_ExplicitVarSizeWithFlags_Flags[2] -> s_ExplicitVarSizeWithFlags_Values[1] < s_ExplicitVarSizeWithFlags_Values[2], - and([s_ExplicitVarSizeWithFlags_Flags[q6] = false -> s_ExplicitVarSizeWithFlags_Values[q6] = 1 | q6 : int(1..2)]), - s_ExplicitVarSizeWithFlags_Flags[2] -> s_ExplicitVarSizeWithFlags_Flags[1], - and([s_ExplicitVarSizeWithFlags_Flags[q11] -> - or([q13 <= s_ExplicitVarSizeWithMarker_Marker /\ - s_ExplicitVarSizeWithMarker_Values[q13] = s_ExplicitVarSizeWithFlags_Values[q11] - | q13 : int(1..2)]) - | q11 : int(1..2)]), - and([q15 <= s_ExplicitVarSizeWithMarker_Marker -> - or([s_ExplicitVarSizeWithFlags_Flags[q17] /\ - s_ExplicitVarSizeWithFlags_Values[q17] = s_ExplicitVarSizeWithMarker_Values[q15] - | q17 : int(1..2)]) - | q15 : int(1..2)]), - and([s_ExplicitVarSizeWithFlags_Flags[q19] -> s_Occurrence[s_ExplicitVarSizeWithFlags_Values[q19]] - | q19 : int(1..2)]), - and([s_Occurrence[q20] -> - or([s_ExplicitVarSizeWithFlags_Flags[q22] /\ s_ExplicitVarSizeWithFlags_Values[q22] = q20 | q22 : int(1..2)]) - | q20 : int(1..2)]) - diff --git a/tests/exhaustive/basic/set_card_00/expected/model_3_2_1-solution000001.solution b/tests/exhaustive/basic/set_card_00/expected/model_3_2_1-solution000001.solution deleted file mode 100644 index 6c0d0fdad8..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_3_2_1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting s be {1} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_3_2_1-solution000002.solution b/tests/exhaustive/basic/set_card_00/expected/model_3_2_1-solution000002.solution deleted file mode 100644 index 2ce5f2081f..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_3_2_1-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_3_2_1.eprime b/tests/exhaustive/basic/set_card_00/expected/model_3_2_1.eprime deleted file mode 100644 index 3f3dfb7cd2..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_3_2_1.eprime +++ /dev/null @@ -1,37 +0,0 @@ -language ESSENCE' 1.0 - -find s_ExplicitVarSizeWithMarker_Marker: int(0..2) -find s_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..2)] of int(1..2) -find s_ExplicitVarSizeWithDummy: matrix indexed by [int(1..2)] of int(1..3) -find s_Occurrence: matrix indexed by [int(1..2)] of bool -branching on - [s_Occurrence, s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithMarker_Values, s_ExplicitVarSizeWithDummy] -such that - or([s_ExplicitVarSizeWithDummy[q18] != 3 /\ s_ExplicitVarSizeWithDummy[q18] = s_ExplicitVarSizeWithMarker_Marker - | q18 : int(1..2)]), - 2 <= s_ExplicitVarSizeWithMarker_Marker -> - s_ExplicitVarSizeWithMarker_Values[1] < s_ExplicitVarSizeWithMarker_Values[2], - and([q2 > s_ExplicitVarSizeWithMarker_Marker -> s_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..2)]), - s_ExplicitVarSizeWithDummy[1] < s_ExplicitVarSizeWithDummy[2] \/ s_ExplicitVarSizeWithDummy[1] = 3, - s_ExplicitVarSizeWithDummy[1] = 3 -> s_ExplicitVarSizeWithDummy[2] = 3, - and([s_ExplicitVarSizeWithDummy[q9] != 3 -> - or([q11 <= s_ExplicitVarSizeWithMarker_Marker /\ - s_ExplicitVarSizeWithMarker_Values[q11] = s_ExplicitVarSizeWithDummy[q9] - | q11 : int(1..2)]) - | q9 : int(1..2)]), - and([q13 <= s_ExplicitVarSizeWithMarker_Marker -> - or([s_ExplicitVarSizeWithDummy[q15] != 3 /\ - s_ExplicitVarSizeWithDummy[q15] = s_ExplicitVarSizeWithMarker_Values[q13] - | q15 : int(1..2)]) - | q13 : int(1..2)]), - and([s_Occurrence[q19] -> - or([q21 <= s_ExplicitVarSizeWithMarker_Marker /\ s_ExplicitVarSizeWithMarker_Values[q21] = q19 - | q21 : int(1..2)]) - | q19 : int(1..2)]), - and([q23 <= s_ExplicitVarSizeWithMarker_Marker -> s_Occurrence[s_ExplicitVarSizeWithMarker_Values[q23]] - | q23 : int(1..2)]), - and([s_Occurrence[q24] -> - or([s_ExplicitVarSizeWithDummy[q26] != 3 /\ s_ExplicitVarSizeWithDummy[q26] = q24 | q26 : int(1..2)]) - | q24 : int(1..2)]), - and([s_ExplicitVarSizeWithDummy[q28] != 3 -> s_Occurrence[s_ExplicitVarSizeWithDummy[q28]] | q28 : int(1..2)]) - diff --git a/tests/exhaustive/basic/set_card_00/expected/model_3_2_2-solution000001.solution b/tests/exhaustive/basic/set_card_00/expected/model_3_2_2-solution000001.solution deleted file mode 100644 index 2ce5f2081f..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_3_2_2-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_3_2_2-solution000002.solution b/tests/exhaustive/basic/set_card_00/expected/model_3_2_2-solution000002.solution deleted file mode 100644 index 6c0d0fdad8..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_3_2_2-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting s be {1} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_3_2_2.eprime b/tests/exhaustive/basic/set_card_00/expected/model_3_2_2.eprime deleted file mode 100644 index a9af356a26..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_3_2_2.eprime +++ /dev/null @@ -1,25 +0,0 @@ -language ESSENCE' 1.0 - -find s_ExplicitVarSizeWithMarker_Marker: int(0..2) -find s_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..2)] of int(1..2) -find s_ExplicitVarSizeWithDummy: matrix indexed by [int(1..2)] of int(1..3) -branching on [s_ExplicitVarSizeWithDummy, s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithMarker_Values] -such that - or([s_ExplicitVarSizeWithDummy[q17] != 3 /\ s_ExplicitVarSizeWithDummy[q17] = s_ExplicitVarSizeWithMarker_Marker - | q17 : int(1..2)]), - 2 <= s_ExplicitVarSizeWithMarker_Marker -> - s_ExplicitVarSizeWithMarker_Values[1] < s_ExplicitVarSizeWithMarker_Values[2], - and([q2 > s_ExplicitVarSizeWithMarker_Marker -> s_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..2)]), - s_ExplicitVarSizeWithDummy[1] < s_ExplicitVarSizeWithDummy[2] \/ s_ExplicitVarSizeWithDummy[1] = 3, - s_ExplicitVarSizeWithDummy[1] = 3 -> s_ExplicitVarSizeWithDummy[2] = 3, - and([s_ExplicitVarSizeWithDummy[q9] != 3 -> - or([q11 <= s_ExplicitVarSizeWithMarker_Marker /\ - s_ExplicitVarSizeWithMarker_Values[q11] = s_ExplicitVarSizeWithDummy[q9] - | q11 : int(1..2)]) - | q9 : int(1..2)]), - and([q13 <= s_ExplicitVarSizeWithMarker_Marker -> - or([s_ExplicitVarSizeWithDummy[q15] != 3 /\ - s_ExplicitVarSizeWithDummy[q15] = s_ExplicitVarSizeWithMarker_Values[q13] - | q15 : int(1..2)]) - | q13 : int(1..2)]) - diff --git a/tests/exhaustive/basic/set_card_00/expected/model_3_2_3-solution000001.solution b/tests/exhaustive/basic/set_card_00/expected/model_3_2_3-solution000001.solution deleted file mode 100644 index 2ce5f2081f..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_3_2_3-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_3_2_3-solution000002.solution b/tests/exhaustive/basic/set_card_00/expected/model_3_2_3-solution000002.solution deleted file mode 100644 index 6c0d0fdad8..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_3_2_3-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting s be {1} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_3_2_3.eprime b/tests/exhaustive/basic/set_card_00/expected/model_3_2_3.eprime deleted file mode 100644 index a9af356a26..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_3_2_3.eprime +++ /dev/null @@ -1,25 +0,0 @@ -language ESSENCE' 1.0 - -find s_ExplicitVarSizeWithMarker_Marker: int(0..2) -find s_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..2)] of int(1..2) -find s_ExplicitVarSizeWithDummy: matrix indexed by [int(1..2)] of int(1..3) -branching on [s_ExplicitVarSizeWithDummy, s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithMarker_Values] -such that - or([s_ExplicitVarSizeWithDummy[q17] != 3 /\ s_ExplicitVarSizeWithDummy[q17] = s_ExplicitVarSizeWithMarker_Marker - | q17 : int(1..2)]), - 2 <= s_ExplicitVarSizeWithMarker_Marker -> - s_ExplicitVarSizeWithMarker_Values[1] < s_ExplicitVarSizeWithMarker_Values[2], - and([q2 > s_ExplicitVarSizeWithMarker_Marker -> s_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..2)]), - s_ExplicitVarSizeWithDummy[1] < s_ExplicitVarSizeWithDummy[2] \/ s_ExplicitVarSizeWithDummy[1] = 3, - s_ExplicitVarSizeWithDummy[1] = 3 -> s_ExplicitVarSizeWithDummy[2] = 3, - and([s_ExplicitVarSizeWithDummy[q9] != 3 -> - or([q11 <= s_ExplicitVarSizeWithMarker_Marker /\ - s_ExplicitVarSizeWithMarker_Values[q11] = s_ExplicitVarSizeWithDummy[q9] - | q11 : int(1..2)]) - | q9 : int(1..2)]), - and([q13 <= s_ExplicitVarSizeWithMarker_Marker -> - or([s_ExplicitVarSizeWithDummy[q15] != 3 /\ - s_ExplicitVarSizeWithDummy[q15] = s_ExplicitVarSizeWithMarker_Values[q13] - | q15 : int(1..2)]) - | q13 : int(1..2)]) - diff --git a/tests/exhaustive/basic/set_card_00/expected/model_3_2_4-solution000001.solution b/tests/exhaustive/basic/set_card_00/expected/model_3_2_4-solution000001.solution deleted file mode 100644 index 6c0d0fdad8..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_3_2_4-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting s be {1} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_3_2_4-solution000002.solution b/tests/exhaustive/basic/set_card_00/expected/model_3_2_4-solution000002.solution deleted file mode 100644 index 2ce5f2081f..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_3_2_4-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_3_2_4.eprime b/tests/exhaustive/basic/set_card_00/expected/model_3_2_4.eprime deleted file mode 100644 index b4d1060382..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_3_2_4.eprime +++ /dev/null @@ -1,53 +0,0 @@ -language ESSENCE' 1.0 - -find s_ExplicitVarSizeWithMarker_Marker: int(0..2) -find s_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..2)] of int(1..2) -find s_ExplicitVarSizeWithDummy: matrix indexed by [int(1..2)] of int(1..3) -find s_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..2)] of bool -find s_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..2)] of int(1..2) -branching on - [s_ExplicitVarSizeWithFlags_Flags, s_ExplicitVarSizeWithFlags_Values, s_ExplicitVarSizeWithMarker_Marker, - s_ExplicitVarSizeWithMarker_Values, s_ExplicitVarSizeWithDummy] -such that - or([s_ExplicitVarSizeWithDummy[q38] != 3 /\ s_ExplicitVarSizeWithDummy[q38] = s_ExplicitVarSizeWithMarker_Marker - | q38 : int(1..2)]), - 2 <= s_ExplicitVarSizeWithMarker_Marker -> - s_ExplicitVarSizeWithMarker_Values[1] < s_ExplicitVarSizeWithMarker_Values[2], - and([q2 > s_ExplicitVarSizeWithMarker_Marker -> s_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..2)]), - s_ExplicitVarSizeWithDummy[1] < s_ExplicitVarSizeWithDummy[2] \/ s_ExplicitVarSizeWithDummy[1] = 3, - s_ExplicitVarSizeWithDummy[1] = 3 -> s_ExplicitVarSizeWithDummy[2] = 3, - and([s_ExplicitVarSizeWithDummy[q9] != 3 -> - or([q11 <= s_ExplicitVarSizeWithMarker_Marker /\ - s_ExplicitVarSizeWithMarker_Values[q11] = s_ExplicitVarSizeWithDummy[q9] - | q11 : int(1..2)]) - | q9 : int(1..2)]), - and([q13 <= s_ExplicitVarSizeWithMarker_Marker -> - or([s_ExplicitVarSizeWithDummy[q15] != 3 /\ - s_ExplicitVarSizeWithDummy[q15] = s_ExplicitVarSizeWithMarker_Values[q13] - | q15 : int(1..2)]) - | q13 : int(1..2)]), - s_ExplicitVarSizeWithFlags_Flags[2] -> s_ExplicitVarSizeWithFlags_Values[1] < s_ExplicitVarSizeWithFlags_Values[2], - and([s_ExplicitVarSizeWithFlags_Flags[q17] = false -> s_ExplicitVarSizeWithFlags_Values[q17] = 1 - | q17 : int(1..2)]), - s_ExplicitVarSizeWithFlags_Flags[2] -> s_ExplicitVarSizeWithFlags_Flags[1], - and([s_ExplicitVarSizeWithFlags_Flags[q22] -> - or([q24 <= s_ExplicitVarSizeWithMarker_Marker /\ - s_ExplicitVarSizeWithMarker_Values[q24] = s_ExplicitVarSizeWithFlags_Values[q22] - | q24 : int(1..2)]) - | q22 : int(1..2)]), - and([q26 <= s_ExplicitVarSizeWithMarker_Marker -> - or([s_ExplicitVarSizeWithFlags_Flags[q28] /\ - s_ExplicitVarSizeWithFlags_Values[q28] = s_ExplicitVarSizeWithMarker_Values[q26] - | q28 : int(1..2)]) - | q26 : int(1..2)]), - and([s_ExplicitVarSizeWithFlags_Flags[q30] -> - or([s_ExplicitVarSizeWithDummy[q32] != 3 /\ - s_ExplicitVarSizeWithDummy[q32] = s_ExplicitVarSizeWithFlags_Values[q30] - | q32 : int(1..2)]) - | q30 : int(1..2)]), - and([s_ExplicitVarSizeWithDummy[q34] != 3 -> - or([s_ExplicitVarSizeWithFlags_Flags[q36] /\ - s_ExplicitVarSizeWithFlags_Values[q36] = s_ExplicitVarSizeWithDummy[q34] - | q36 : int(1..2)]) - | q34 : int(1..2)]) - diff --git a/tests/exhaustive/basic/set_card_00/expected/model_3_3_1-solution000001.solution b/tests/exhaustive/basic/set_card_00/expected/model_3_3_1-solution000001.solution deleted file mode 100644 index 6c0d0fdad8..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_3_3_1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting s be {1} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_3_3_1-solution000002.solution b/tests/exhaustive/basic/set_card_00/expected/model_3_3_1-solution000002.solution deleted file mode 100644 index 2ce5f2081f..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_3_3_1-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_3_3_1.eprime b/tests/exhaustive/basic/set_card_00/expected/model_3_3_1.eprime deleted file mode 100644 index 09493a4fe3..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_3_3_1.eprime +++ /dev/null @@ -1,19 +0,0 @@ -language ESSENCE' 1.0 - -find s_ExplicitVarSizeWithMarker_Marker: int(0..2) -find s_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..2)] of int(1..2) -find s_Occurrence: matrix indexed by [int(1..2)] of bool -branching on [s_Occurrence, s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithMarker_Values] -such that - or([q6 <= s_ExplicitVarSizeWithMarker_Marker /\ - s_ExplicitVarSizeWithMarker_Values[q6] = s_ExplicitVarSizeWithMarker_Marker - | q6 : int(1..2)]), - 2 <= s_ExplicitVarSizeWithMarker_Marker -> - s_ExplicitVarSizeWithMarker_Values[1] < s_ExplicitVarSizeWithMarker_Values[2], - and([q2 > s_ExplicitVarSizeWithMarker_Marker -> s_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..2)]), - and([s_Occurrence[q7] -> - or([q9 <= s_ExplicitVarSizeWithMarker_Marker /\ s_ExplicitVarSizeWithMarker_Values[q9] = q7 | q9 : int(1..2)]) - | q7 : int(1..2)]), - and([q11 <= s_ExplicitVarSizeWithMarker_Marker -> s_Occurrence[s_ExplicitVarSizeWithMarker_Values[q11]] - | q11 : int(1..2)]) - diff --git a/tests/exhaustive/basic/set_card_00/expected/model_3_3_2-solution000001.solution b/tests/exhaustive/basic/set_card_00/expected/model_3_3_2-solution000001.solution deleted file mode 100644 index 2ce5f2081f..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_3_3_2-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_3_3_2-solution000002.solution b/tests/exhaustive/basic/set_card_00/expected/model_3_3_2-solution000002.solution deleted file mode 100644 index 6c0d0fdad8..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_3_3_2-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting s be {1} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_3_3_2.eprime b/tests/exhaustive/basic/set_card_00/expected/model_3_3_2.eprime deleted file mode 100644 index 2b66d82f1b..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_3_3_2.eprime +++ /dev/null @@ -1,26 +0,0 @@ -language ESSENCE' 1.0 - -find s_ExplicitVarSizeWithMarker_Marker: int(0..2) -find s_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..2)] of int(1..2) -find s_ExplicitVarSizeWithDummy: matrix indexed by [int(1..2)] of int(1..3) -branching on [s_ExplicitVarSizeWithDummy, s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithMarker_Values] -such that - or([q17 <= s_ExplicitVarSizeWithMarker_Marker /\ - s_ExplicitVarSizeWithMarker_Values[q17] = s_ExplicitVarSizeWithMarker_Marker - | q17 : int(1..2)]), - 2 <= s_ExplicitVarSizeWithMarker_Marker -> - s_ExplicitVarSizeWithMarker_Values[1] < s_ExplicitVarSizeWithMarker_Values[2], - and([q2 > s_ExplicitVarSizeWithMarker_Marker -> s_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..2)]), - s_ExplicitVarSizeWithDummy[1] < s_ExplicitVarSizeWithDummy[2] \/ s_ExplicitVarSizeWithDummy[1] = 3, - s_ExplicitVarSizeWithDummy[1] = 3 -> s_ExplicitVarSizeWithDummy[2] = 3, - and([s_ExplicitVarSizeWithDummy[q9] != 3 -> - or([q11 <= s_ExplicitVarSizeWithMarker_Marker /\ - s_ExplicitVarSizeWithMarker_Values[q11] = s_ExplicitVarSizeWithDummy[q9] - | q11 : int(1..2)]) - | q9 : int(1..2)]), - and([q13 <= s_ExplicitVarSizeWithMarker_Marker -> - or([s_ExplicitVarSizeWithDummy[q15] != 3 /\ - s_ExplicitVarSizeWithDummy[q15] = s_ExplicitVarSizeWithMarker_Values[q13] - | q15 : int(1..2)]) - | q13 : int(1..2)]) - diff --git a/tests/exhaustive/basic/set_card_00/expected/model_3_3_3-solution000001.solution b/tests/exhaustive/basic/set_card_00/expected/model_3_3_3-solution000001.solution deleted file mode 100644 index 6c0d0fdad8..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_3_3_3-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting s be {1} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_3_3_3-solution000002.solution b/tests/exhaustive/basic/set_card_00/expected/model_3_3_3-solution000002.solution deleted file mode 100644 index 2ce5f2081f..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_3_3_3-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_3_3_3.eprime b/tests/exhaustive/basic/set_card_00/expected/model_3_3_3.eprime deleted file mode 100644 index 8abe0820c9..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_3_3_3.eprime +++ /dev/null @@ -1,13 +0,0 @@ -language ESSENCE' 1.0 - -find s_ExplicitVarSizeWithMarker_Marker: int(0..2) -find s_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..2)] of int(1..2) -branching on [s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithMarker_Values] -such that - or([q5 <= s_ExplicitVarSizeWithMarker_Marker /\ - s_ExplicitVarSizeWithMarker_Values[q5] = s_ExplicitVarSizeWithMarker_Marker - | q5 : int(1..2)]), - 2 <= s_ExplicitVarSizeWithMarker_Marker -> - s_ExplicitVarSizeWithMarker_Values[1] < s_ExplicitVarSizeWithMarker_Values[2], - and([q2 > s_ExplicitVarSizeWithMarker_Marker -> s_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..2)]) - diff --git a/tests/exhaustive/basic/set_card_00/expected/model_3_3_4-solution000001.solution b/tests/exhaustive/basic/set_card_00/expected/model_3_3_4-solution000001.solution deleted file mode 100644 index 6c0d0fdad8..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_3_3_4-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting s be {1} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_3_3_4-solution000002.solution b/tests/exhaustive/basic/set_card_00/expected/model_3_3_4-solution000002.solution deleted file mode 100644 index 2ce5f2081f..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_3_3_4-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_3_3_4.eprime b/tests/exhaustive/basic/set_card_00/expected/model_3_3_4.eprime deleted file mode 100644 index 4334952115..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_3_3_4.eprime +++ /dev/null @@ -1,30 +0,0 @@ -language ESSENCE' 1.0 - -find s_ExplicitVarSizeWithMarker_Marker: int(0..2) -find s_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..2)] of int(1..2) -find s_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..2)] of bool -find s_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..2)] of int(1..2) -branching on - [s_ExplicitVarSizeWithFlags_Flags, s_ExplicitVarSizeWithFlags_Values, s_ExplicitVarSizeWithMarker_Marker, - s_ExplicitVarSizeWithMarker_Values] -such that - or([q18 <= s_ExplicitVarSizeWithMarker_Marker /\ - s_ExplicitVarSizeWithMarker_Values[q18] = s_ExplicitVarSizeWithMarker_Marker - | q18 : int(1..2)]), - 2 <= s_ExplicitVarSizeWithMarker_Marker -> - s_ExplicitVarSizeWithMarker_Values[1] < s_ExplicitVarSizeWithMarker_Values[2], - and([q2 > s_ExplicitVarSizeWithMarker_Marker -> s_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..2)]), - s_ExplicitVarSizeWithFlags_Flags[2] -> s_ExplicitVarSizeWithFlags_Values[1] < s_ExplicitVarSizeWithFlags_Values[2], - and([s_ExplicitVarSizeWithFlags_Flags[q5] = false -> s_ExplicitVarSizeWithFlags_Values[q5] = 1 | q5 : int(1..2)]), - s_ExplicitVarSizeWithFlags_Flags[2] -> s_ExplicitVarSizeWithFlags_Flags[1], - and([s_ExplicitVarSizeWithFlags_Flags[q10] -> - or([q12 <= s_ExplicitVarSizeWithMarker_Marker /\ - s_ExplicitVarSizeWithMarker_Values[q12] = s_ExplicitVarSizeWithFlags_Values[q10] - | q12 : int(1..2)]) - | q10 : int(1..2)]), - and([q14 <= s_ExplicitVarSizeWithMarker_Marker -> - or([s_ExplicitVarSizeWithFlags_Flags[q16] /\ - s_ExplicitVarSizeWithFlags_Values[q16] = s_ExplicitVarSizeWithMarker_Values[q14] - | q16 : int(1..2)]) - | q14 : int(1..2)]) - diff --git a/tests/exhaustive/basic/set_card_00/expected/model_3_4_1-solution000001.solution b/tests/exhaustive/basic/set_card_00/expected/model_3_4_1-solution000001.solution deleted file mode 100644 index 6c0d0fdad8..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_3_4_1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting s be {1} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_3_4_1-solution000002.solution b/tests/exhaustive/basic/set_card_00/expected/model_3_4_1-solution000002.solution deleted file mode 100644 index 2ce5f2081f..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_3_4_1-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_3_4_1.eprime b/tests/exhaustive/basic/set_card_00/expected/model_3_4_1.eprime deleted file mode 100644 index e4660905d9..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_3_4_1.eprime +++ /dev/null @@ -1,42 +0,0 @@ -language ESSENCE' 1.0 - -find s_ExplicitVarSizeWithMarker_Marker: int(0..2) -find s_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..2)] of int(1..2) -find s_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..2)] of bool -find s_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..2)] of int(1..2) -find s_Occurrence: matrix indexed by [int(1..2)] of bool -branching on - [s_Occurrence, s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithMarker_Values, - s_ExplicitVarSizeWithFlags_Flags, s_ExplicitVarSizeWithFlags_Values] -such that - or([s_ExplicitVarSizeWithFlags_Flags[q29] /\ - s_ExplicitVarSizeWithFlags_Values[q29] = s_ExplicitVarSizeWithMarker_Marker - | q29 : int(1..2)]), - 2 <= s_ExplicitVarSizeWithMarker_Marker -> - s_ExplicitVarSizeWithMarker_Values[1] < s_ExplicitVarSizeWithMarker_Values[2], - and([q2 > s_ExplicitVarSizeWithMarker_Marker -> s_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..2)]), - s_ExplicitVarSizeWithFlags_Flags[2] -> s_ExplicitVarSizeWithFlags_Values[1] < s_ExplicitVarSizeWithFlags_Values[2], - and([s_ExplicitVarSizeWithFlags_Flags[q5] = false -> s_ExplicitVarSizeWithFlags_Values[q5] = 1 | q5 : int(1..2)]), - s_ExplicitVarSizeWithFlags_Flags[2] -> s_ExplicitVarSizeWithFlags_Flags[1], - and([s_ExplicitVarSizeWithFlags_Flags[q10] -> - or([q12 <= s_ExplicitVarSizeWithMarker_Marker /\ - s_ExplicitVarSizeWithMarker_Values[q12] = s_ExplicitVarSizeWithFlags_Values[q10] - | q12 : int(1..2)]) - | q10 : int(1..2)]), - and([q14 <= s_ExplicitVarSizeWithMarker_Marker -> - or([s_ExplicitVarSizeWithFlags_Flags[q16] /\ - s_ExplicitVarSizeWithFlags_Values[q16] = s_ExplicitVarSizeWithMarker_Values[q14] - | q16 : int(1..2)]) - | q14 : int(1..2)]), - and([s_Occurrence[q18] -> - or([q20 <= s_ExplicitVarSizeWithMarker_Marker /\ s_ExplicitVarSizeWithMarker_Values[q20] = q18 - | q20 : int(1..2)]) - | q18 : int(1..2)]), - and([q22 <= s_ExplicitVarSizeWithMarker_Marker -> s_Occurrence[s_ExplicitVarSizeWithMarker_Values[q22]] - | q22 : int(1..2)]), - and([s_Occurrence[q23] -> - or([s_ExplicitVarSizeWithFlags_Flags[q25] /\ s_ExplicitVarSizeWithFlags_Values[q25] = q23 | q25 : int(1..2)]) - | q23 : int(1..2)]), - and([s_ExplicitVarSizeWithFlags_Flags[q27] -> s_Occurrence[s_ExplicitVarSizeWithFlags_Values[q27]] - | q27 : int(1..2)]) - diff --git a/tests/exhaustive/basic/set_card_00/expected/model_3_4_2-solution000001.solution b/tests/exhaustive/basic/set_card_00/expected/model_3_4_2-solution000001.solution deleted file mode 100644 index 2ce5f2081f..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_3_4_2-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_3_4_2-solution000002.solution b/tests/exhaustive/basic/set_card_00/expected/model_3_4_2-solution000002.solution deleted file mode 100644 index 6c0d0fdad8..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_3_4_2-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting s be {1} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_3_4_2.eprime b/tests/exhaustive/basic/set_card_00/expected/model_3_4_2.eprime deleted file mode 100644 index 5f852ee9cb..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_3_4_2.eprime +++ /dev/null @@ -1,53 +0,0 @@ -language ESSENCE' 1.0 - -find s_ExplicitVarSizeWithMarker_Marker: int(0..2) -find s_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..2)] of int(1..2) -find s_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..2)] of bool -find s_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..2)] of int(1..2) -find s_ExplicitVarSizeWithDummy: matrix indexed by [int(1..2)] of int(1..3) -branching on - [s_ExplicitVarSizeWithDummy, s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithMarker_Values, - s_ExplicitVarSizeWithFlags_Flags, s_ExplicitVarSizeWithFlags_Values] -such that - or([s_ExplicitVarSizeWithFlags_Flags[q38] /\ - s_ExplicitVarSizeWithFlags_Values[q38] = s_ExplicitVarSizeWithMarker_Marker - | q38 : int(1..2)]), - 2 <= s_ExplicitVarSizeWithMarker_Marker -> - s_ExplicitVarSizeWithMarker_Values[1] < s_ExplicitVarSizeWithMarker_Values[2], - and([q2 > s_ExplicitVarSizeWithMarker_Marker -> s_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..2)]), - s_ExplicitVarSizeWithFlags_Flags[2] -> s_ExplicitVarSizeWithFlags_Values[1] < s_ExplicitVarSizeWithFlags_Values[2], - and([s_ExplicitVarSizeWithFlags_Flags[q5] = false -> s_ExplicitVarSizeWithFlags_Values[q5] = 1 | q5 : int(1..2)]), - s_ExplicitVarSizeWithFlags_Flags[2] -> s_ExplicitVarSizeWithFlags_Flags[1], - and([s_ExplicitVarSizeWithFlags_Flags[q10] -> - or([q12 <= s_ExplicitVarSizeWithMarker_Marker /\ - s_ExplicitVarSizeWithMarker_Values[q12] = s_ExplicitVarSizeWithFlags_Values[q10] - | q12 : int(1..2)]) - | q10 : int(1..2)]), - and([q14 <= s_ExplicitVarSizeWithMarker_Marker -> - or([s_ExplicitVarSizeWithFlags_Flags[q16] /\ - s_ExplicitVarSizeWithFlags_Values[q16] = s_ExplicitVarSizeWithMarker_Values[q14] - | q16 : int(1..2)]) - | q14 : int(1..2)]), - s_ExplicitVarSizeWithDummy[1] < s_ExplicitVarSizeWithDummy[2] \/ s_ExplicitVarSizeWithDummy[1] = 3, - s_ExplicitVarSizeWithDummy[1] = 3 -> s_ExplicitVarSizeWithDummy[2] = 3, - and([s_ExplicitVarSizeWithDummy[q22] != 3 -> - or([q24 <= s_ExplicitVarSizeWithMarker_Marker /\ - s_ExplicitVarSizeWithMarker_Values[q24] = s_ExplicitVarSizeWithDummy[q22] - | q24 : int(1..2)]) - | q22 : int(1..2)]), - and([q26 <= s_ExplicitVarSizeWithMarker_Marker -> - or([s_ExplicitVarSizeWithDummy[q28] != 3 /\ - s_ExplicitVarSizeWithDummy[q28] = s_ExplicitVarSizeWithMarker_Values[q26] - | q28 : int(1..2)]) - | q26 : int(1..2)]), - and([s_ExplicitVarSizeWithDummy[q30] != 3 -> - or([s_ExplicitVarSizeWithFlags_Flags[q32] /\ - s_ExplicitVarSizeWithFlags_Values[q32] = s_ExplicitVarSizeWithDummy[q30] - | q32 : int(1..2)]) - | q30 : int(1..2)]), - and([s_ExplicitVarSizeWithFlags_Flags[q34] -> - or([s_ExplicitVarSizeWithDummy[q36] != 3 /\ - s_ExplicitVarSizeWithDummy[q36] = s_ExplicitVarSizeWithFlags_Values[q34] - | q36 : int(1..2)]) - | q34 : int(1..2)]) - diff --git a/tests/exhaustive/basic/set_card_00/expected/model_3_4_3-solution000001.solution b/tests/exhaustive/basic/set_card_00/expected/model_3_4_3-solution000001.solution deleted file mode 100644 index 6c0d0fdad8..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_3_4_3-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting s be {1} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_3_4_3-solution000002.solution b/tests/exhaustive/basic/set_card_00/expected/model_3_4_3-solution000002.solution deleted file mode 100644 index 2ce5f2081f..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_3_4_3-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_3_4_3.eprime b/tests/exhaustive/basic/set_card_00/expected/model_3_4_3.eprime deleted file mode 100644 index 1fd723eedd..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_3_4_3.eprime +++ /dev/null @@ -1,30 +0,0 @@ -language ESSENCE' 1.0 - -find s_ExplicitVarSizeWithMarker_Marker: int(0..2) -find s_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..2)] of int(1..2) -find s_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..2)] of bool -find s_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..2)] of int(1..2) -branching on - [s_ExplicitVarSizeWithFlags_Flags, s_ExplicitVarSizeWithFlags_Values, s_ExplicitVarSizeWithMarker_Marker, - s_ExplicitVarSizeWithMarker_Values] -such that - or([s_ExplicitVarSizeWithFlags_Flags[q18] /\ - s_ExplicitVarSizeWithFlags_Values[q18] = s_ExplicitVarSizeWithMarker_Marker - | q18 : int(1..2)]), - 2 <= s_ExplicitVarSizeWithMarker_Marker -> - s_ExplicitVarSizeWithMarker_Values[1] < s_ExplicitVarSizeWithMarker_Values[2], - and([q2 > s_ExplicitVarSizeWithMarker_Marker -> s_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..2)]), - s_ExplicitVarSizeWithFlags_Flags[2] -> s_ExplicitVarSizeWithFlags_Values[1] < s_ExplicitVarSizeWithFlags_Values[2], - and([s_ExplicitVarSizeWithFlags_Flags[q5] = false -> s_ExplicitVarSizeWithFlags_Values[q5] = 1 | q5 : int(1..2)]), - s_ExplicitVarSizeWithFlags_Flags[2] -> s_ExplicitVarSizeWithFlags_Flags[1], - and([s_ExplicitVarSizeWithFlags_Flags[q10] -> - or([q12 <= s_ExplicitVarSizeWithMarker_Marker /\ - s_ExplicitVarSizeWithMarker_Values[q12] = s_ExplicitVarSizeWithFlags_Values[q10] - | q12 : int(1..2)]) - | q10 : int(1..2)]), - and([q14 <= s_ExplicitVarSizeWithMarker_Marker -> - or([s_ExplicitVarSizeWithFlags_Flags[q16] /\ - s_ExplicitVarSizeWithFlags_Values[q16] = s_ExplicitVarSizeWithMarker_Values[q14] - | q16 : int(1..2)]) - | q14 : int(1..2)]) - diff --git a/tests/exhaustive/basic/set_card_00/expected/model_3_4_4-solution000001.solution b/tests/exhaustive/basic/set_card_00/expected/model_3_4_4-solution000001.solution deleted file mode 100644 index 6c0d0fdad8..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_3_4_4-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting s be {1} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_3_4_4-solution000002.solution b/tests/exhaustive/basic/set_card_00/expected/model_3_4_4-solution000002.solution deleted file mode 100644 index 2ce5f2081f..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_3_4_4-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_3_4_4.eprime b/tests/exhaustive/basic/set_card_00/expected/model_3_4_4.eprime deleted file mode 100644 index 1fd723eedd..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_3_4_4.eprime +++ /dev/null @@ -1,30 +0,0 @@ -language ESSENCE' 1.0 - -find s_ExplicitVarSizeWithMarker_Marker: int(0..2) -find s_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..2)] of int(1..2) -find s_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..2)] of bool -find s_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..2)] of int(1..2) -branching on - [s_ExplicitVarSizeWithFlags_Flags, s_ExplicitVarSizeWithFlags_Values, s_ExplicitVarSizeWithMarker_Marker, - s_ExplicitVarSizeWithMarker_Values] -such that - or([s_ExplicitVarSizeWithFlags_Flags[q18] /\ - s_ExplicitVarSizeWithFlags_Values[q18] = s_ExplicitVarSizeWithMarker_Marker - | q18 : int(1..2)]), - 2 <= s_ExplicitVarSizeWithMarker_Marker -> - s_ExplicitVarSizeWithMarker_Values[1] < s_ExplicitVarSizeWithMarker_Values[2], - and([q2 > s_ExplicitVarSizeWithMarker_Marker -> s_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..2)]), - s_ExplicitVarSizeWithFlags_Flags[2] -> s_ExplicitVarSizeWithFlags_Values[1] < s_ExplicitVarSizeWithFlags_Values[2], - and([s_ExplicitVarSizeWithFlags_Flags[q5] = false -> s_ExplicitVarSizeWithFlags_Values[q5] = 1 | q5 : int(1..2)]), - s_ExplicitVarSizeWithFlags_Flags[2] -> s_ExplicitVarSizeWithFlags_Flags[1], - and([s_ExplicitVarSizeWithFlags_Flags[q10] -> - or([q12 <= s_ExplicitVarSizeWithMarker_Marker /\ - s_ExplicitVarSizeWithMarker_Values[q12] = s_ExplicitVarSizeWithFlags_Values[q10] - | q12 : int(1..2)]) - | q10 : int(1..2)]), - and([q14 <= s_ExplicitVarSizeWithMarker_Marker -> - or([s_ExplicitVarSizeWithFlags_Flags[q16] /\ - s_ExplicitVarSizeWithFlags_Values[q16] = s_ExplicitVarSizeWithMarker_Values[q14] - | q16 : int(1..2)]) - | q14 : int(1..2)]) - diff --git a/tests/exhaustive/basic/set_card_00/expected/model_4_1_1-solution000001.solution b/tests/exhaustive/basic/set_card_00/expected/model_4_1_1-solution000001.solution deleted file mode 100644 index 6c0d0fdad8..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_4_1_1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting s be {1} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_4_1_1-solution000002.solution b/tests/exhaustive/basic/set_card_00/expected/model_4_1_1-solution000002.solution deleted file mode 100644 index 2ce5f2081f..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_4_1_1-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_4_1_1.eprime b/tests/exhaustive/basic/set_card_00/expected/model_4_1_1.eprime deleted file mode 100644 index 0cf269a643..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_4_1_1.eprime +++ /dev/null @@ -1,17 +0,0 @@ -language ESSENCE' 1.0 - -find s_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..2)] of bool -find s_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..2)] of int(1..2) -find s_Occurrence: matrix indexed by [int(1..2)] of bool -branching on [s_Occurrence, s_ExplicitVarSizeWithFlags_Flags, s_ExplicitVarSizeWithFlags_Values] -such that - s_Occurrence[sum([toInt(s_ExplicitVarSizeWithFlags_Flags[q13]) | q13 : int(1..2)])], - s_ExplicitVarSizeWithFlags_Flags[2] -> s_ExplicitVarSizeWithFlags_Values[1] < s_ExplicitVarSizeWithFlags_Values[2], - and([s_ExplicitVarSizeWithFlags_Flags[q2] = false -> s_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..2)]), - s_ExplicitVarSizeWithFlags_Flags[2] -> s_ExplicitVarSizeWithFlags_Flags[1], - and([s_Occurrence[q7] -> - or([s_ExplicitVarSizeWithFlags_Flags[q9] /\ s_ExplicitVarSizeWithFlags_Values[q9] = q7 | q9 : int(1..2)]) - | q7 : int(1..2)]), - and([s_ExplicitVarSizeWithFlags_Flags[q11] -> s_Occurrence[s_ExplicitVarSizeWithFlags_Values[q11]] - | q11 : int(1..2)]) - diff --git a/tests/exhaustive/basic/set_card_00/expected/model_4_1_2-solution000001.solution b/tests/exhaustive/basic/set_card_00/expected/model_4_1_2-solution000001.solution deleted file mode 100644 index 2ce5f2081f..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_4_1_2-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_4_1_2-solution000002.solution b/tests/exhaustive/basic/set_card_00/expected/model_4_1_2-solution000002.solution deleted file mode 100644 index 6c0d0fdad8..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_4_1_2-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting s be {1} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_4_1_2.eprime b/tests/exhaustive/basic/set_card_00/expected/model_4_1_2.eprime deleted file mode 100644 index fe7fecdcc9..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_4_1_2.eprime +++ /dev/null @@ -1,35 +0,0 @@ -language ESSENCE' 1.0 - -find s_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..2)] of bool -find s_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..2)] of int(1..2) -find s_Occurrence: matrix indexed by [int(1..2)] of bool -find s_ExplicitVarSizeWithDummy: matrix indexed by [int(1..2)] of int(1..3) -branching on - [s_ExplicitVarSizeWithDummy, s_ExplicitVarSizeWithFlags_Flags, s_ExplicitVarSizeWithFlags_Values, s_Occurrence] -such that - s_Occurrence[sum([toInt(s_ExplicitVarSizeWithFlags_Flags[q30]) | q30 : int(1..2)])], - s_ExplicitVarSizeWithFlags_Flags[2] -> s_ExplicitVarSizeWithFlags_Values[1] < s_ExplicitVarSizeWithFlags_Values[2], - and([s_ExplicitVarSizeWithFlags_Flags[q2] = false -> s_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..2)]), - s_ExplicitVarSizeWithFlags_Flags[2] -> s_ExplicitVarSizeWithFlags_Flags[1], - and([s_Occurrence[q24] -> - or([s_ExplicitVarSizeWithFlags_Flags[q26] /\ s_ExplicitVarSizeWithFlags_Values[q26] = q24 | q26 : int(1..2)]) - | q24 : int(1..2)]), - and([s_ExplicitVarSizeWithFlags_Flags[q28] -> s_Occurrence[s_ExplicitVarSizeWithFlags_Values[q28]] - | q28 : int(1..2)]), - s_ExplicitVarSizeWithDummy[1] < s_ExplicitVarSizeWithDummy[2] \/ s_ExplicitVarSizeWithDummy[1] = 3, - s_ExplicitVarSizeWithDummy[1] = 3 -> s_ExplicitVarSizeWithDummy[2] = 3, - and([s_ExplicitVarSizeWithDummy[q12] != 3 -> - or([s_ExplicitVarSizeWithFlags_Flags[q14] /\ - s_ExplicitVarSizeWithFlags_Values[q14] = s_ExplicitVarSizeWithDummy[q12] - | q14 : int(1..2)]) - | q12 : int(1..2)]), - and([s_ExplicitVarSizeWithFlags_Flags[q16] -> - or([s_ExplicitVarSizeWithDummy[q18] != 3 /\ - s_ExplicitVarSizeWithDummy[q18] = s_ExplicitVarSizeWithFlags_Values[q16] - | q18 : int(1..2)]) - | q16 : int(1..2)]), - and([s_ExplicitVarSizeWithDummy[q20] != 3 -> s_Occurrence[s_ExplicitVarSizeWithDummy[q20]] | q20 : int(1..2)]), - and([s_Occurrence[q21] -> - or([s_ExplicitVarSizeWithDummy[q23] != 3 /\ s_ExplicitVarSizeWithDummy[q23] = q21 | q23 : int(1..2)]) - | q21 : int(1..2)]) - diff --git a/tests/exhaustive/basic/set_card_00/expected/model_4_1_3-solution000001.solution b/tests/exhaustive/basic/set_card_00/expected/model_4_1_3-solution000001.solution deleted file mode 100644 index 6c0d0fdad8..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_4_1_3-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting s be {1} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_4_1_3-solution000002.solution b/tests/exhaustive/basic/set_card_00/expected/model_4_1_3-solution000002.solution deleted file mode 100644 index 2ce5f2081f..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_4_1_3-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_4_1_3.eprime b/tests/exhaustive/basic/set_card_00/expected/model_4_1_3.eprime deleted file mode 100644 index 63b024eb56..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_4_1_3.eprime +++ /dev/null @@ -1,40 +0,0 @@ -language ESSENCE' 1.0 - -find s_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..2)] of bool -find s_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..2)] of int(1..2) -find s_Occurrence: matrix indexed by [int(1..2)] of bool -find s_ExplicitVarSizeWithMarker_Marker: int(0..2) -find s_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..2)] of int(1..2) -branching on - [s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithMarker_Values, s_ExplicitVarSizeWithFlags_Flags, - s_ExplicitVarSizeWithFlags_Values, s_Occurrence] -such that - s_Occurrence[sum([toInt(s_ExplicitVarSizeWithFlags_Flags[q29]) | q29 : int(1..2)])], - s_ExplicitVarSizeWithFlags_Flags[2] -> s_ExplicitVarSizeWithFlags_Values[1] < s_ExplicitVarSizeWithFlags_Values[2], - and([s_ExplicitVarSizeWithFlags_Flags[q2] = false -> s_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..2)]), - s_ExplicitVarSizeWithFlags_Flags[2] -> s_ExplicitVarSizeWithFlags_Flags[1], - and([s_Occurrence[q23] -> - or([s_ExplicitVarSizeWithFlags_Flags[q25] /\ s_ExplicitVarSizeWithFlags_Values[q25] = q23 | q25 : int(1..2)]) - | q23 : int(1..2)]), - and([s_ExplicitVarSizeWithFlags_Flags[q27] -> s_Occurrence[s_ExplicitVarSizeWithFlags_Values[q27]] - | q27 : int(1..2)]), - 2 <= s_ExplicitVarSizeWithMarker_Marker -> - s_ExplicitVarSizeWithMarker_Values[1] < s_ExplicitVarSizeWithMarker_Values[2], - and([q8 > s_ExplicitVarSizeWithMarker_Marker -> s_ExplicitVarSizeWithMarker_Values[q8] = 1 | q8 : int(1..2)]), - and([q11 <= s_ExplicitVarSizeWithMarker_Marker -> - or([s_ExplicitVarSizeWithFlags_Flags[q13] /\ - s_ExplicitVarSizeWithFlags_Values[q13] = s_ExplicitVarSizeWithMarker_Values[q11] - | q13 : int(1..2)]) - | q11 : int(1..2)]), - and([s_ExplicitVarSizeWithFlags_Flags[q15] -> - or([q17 <= s_ExplicitVarSizeWithMarker_Marker /\ - s_ExplicitVarSizeWithMarker_Values[q17] = s_ExplicitVarSizeWithFlags_Values[q15] - | q17 : int(1..2)]) - | q15 : int(1..2)]), - and([q19 <= s_ExplicitVarSizeWithMarker_Marker -> s_Occurrence[s_ExplicitVarSizeWithMarker_Values[q19]] - | q19 : int(1..2)]), - and([s_Occurrence[q20] -> - or([q22 <= s_ExplicitVarSizeWithMarker_Marker /\ s_ExplicitVarSizeWithMarker_Values[q22] = q20 - | q22 : int(1..2)]) - | q20 : int(1..2)]) - diff --git a/tests/exhaustive/basic/set_card_00/expected/model_4_1_4-solution000001.solution b/tests/exhaustive/basic/set_card_00/expected/model_4_1_4-solution000001.solution deleted file mode 100644 index 6c0d0fdad8..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_4_1_4-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting s be {1} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_4_1_4-solution000002.solution b/tests/exhaustive/basic/set_card_00/expected/model_4_1_4-solution000002.solution deleted file mode 100644 index 2ce5f2081f..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_4_1_4-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_4_1_4.eprime b/tests/exhaustive/basic/set_card_00/expected/model_4_1_4.eprime deleted file mode 100644 index 0cf269a643..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_4_1_4.eprime +++ /dev/null @@ -1,17 +0,0 @@ -language ESSENCE' 1.0 - -find s_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..2)] of bool -find s_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..2)] of int(1..2) -find s_Occurrence: matrix indexed by [int(1..2)] of bool -branching on [s_Occurrence, s_ExplicitVarSizeWithFlags_Flags, s_ExplicitVarSizeWithFlags_Values] -such that - s_Occurrence[sum([toInt(s_ExplicitVarSizeWithFlags_Flags[q13]) | q13 : int(1..2)])], - s_ExplicitVarSizeWithFlags_Flags[2] -> s_ExplicitVarSizeWithFlags_Values[1] < s_ExplicitVarSizeWithFlags_Values[2], - and([s_ExplicitVarSizeWithFlags_Flags[q2] = false -> s_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..2)]), - s_ExplicitVarSizeWithFlags_Flags[2] -> s_ExplicitVarSizeWithFlags_Flags[1], - and([s_Occurrence[q7] -> - or([s_ExplicitVarSizeWithFlags_Flags[q9] /\ s_ExplicitVarSizeWithFlags_Values[q9] = q7 | q9 : int(1..2)]) - | q7 : int(1..2)]), - and([s_ExplicitVarSizeWithFlags_Flags[q11] -> s_Occurrence[s_ExplicitVarSizeWithFlags_Values[q11]] - | q11 : int(1..2)]) - diff --git a/tests/exhaustive/basic/set_card_00/expected/model_4_2_1-solution000001.solution b/tests/exhaustive/basic/set_card_00/expected/model_4_2_1-solution000001.solution deleted file mode 100644 index 6c0d0fdad8..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_4_2_1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting s be {1} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_4_2_1-solution000002.solution b/tests/exhaustive/basic/set_card_00/expected/model_4_2_1-solution000002.solution deleted file mode 100644 index 2ce5f2081f..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_4_2_1-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_4_2_1.eprime b/tests/exhaustive/basic/set_card_00/expected/model_4_2_1.eprime deleted file mode 100644 index 07a85b32d6..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_4_2_1.eprime +++ /dev/null @@ -1,37 +0,0 @@ -language ESSENCE' 1.0 - -find s_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..2)] of bool -find s_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..2)] of int(1..2) -find s_ExplicitVarSizeWithDummy: matrix indexed by [int(1..2)] of int(1..3) -find s_Occurrence: matrix indexed by [int(1..2)] of bool -branching on - [s_Occurrence, s_ExplicitVarSizeWithFlags_Flags, s_ExplicitVarSizeWithFlags_Values, s_ExplicitVarSizeWithDummy] -such that - or([s_ExplicitVarSizeWithDummy[q30] != 3 /\ - s_ExplicitVarSizeWithDummy[q30] = sum([toInt(s_ExplicitVarSizeWithFlags_Flags[q32]) | q32 : int(1..2)]) - | q30 : int(1..2)]), - s_ExplicitVarSizeWithFlags_Flags[2] -> s_ExplicitVarSizeWithFlags_Values[1] < s_ExplicitVarSizeWithFlags_Values[2], - and([s_ExplicitVarSizeWithFlags_Flags[q2] = false -> s_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..2)]), - s_ExplicitVarSizeWithFlags_Flags[2] -> s_ExplicitVarSizeWithFlags_Flags[1], - s_ExplicitVarSizeWithDummy[1] < s_ExplicitVarSizeWithDummy[2] \/ s_ExplicitVarSizeWithDummy[1] = 3, - s_ExplicitVarSizeWithDummy[1] = 3 -> s_ExplicitVarSizeWithDummy[2] = 3, - and([s_ExplicitVarSizeWithDummy[q11] != 3 -> - or([s_ExplicitVarSizeWithFlags_Flags[q13] /\ - s_ExplicitVarSizeWithFlags_Values[q13] = s_ExplicitVarSizeWithDummy[q11] - | q13 : int(1..2)]) - | q11 : int(1..2)]), - and([s_ExplicitVarSizeWithFlags_Flags[q15] -> - or([s_ExplicitVarSizeWithDummy[q17] != 3 /\ - s_ExplicitVarSizeWithDummy[q17] = s_ExplicitVarSizeWithFlags_Values[q15] - | q17 : int(1..2)]) - | q15 : int(1..2)]), - and([s_Occurrence[q19] -> - or([s_ExplicitVarSizeWithFlags_Flags[q21] /\ s_ExplicitVarSizeWithFlags_Values[q21] = q19 | q21 : int(1..2)]) - | q19 : int(1..2)]), - and([s_ExplicitVarSizeWithFlags_Flags[q23] -> s_Occurrence[s_ExplicitVarSizeWithFlags_Values[q23]] - | q23 : int(1..2)]), - and([s_Occurrence[q24] -> - or([s_ExplicitVarSizeWithDummy[q26] != 3 /\ s_ExplicitVarSizeWithDummy[q26] = q24 | q26 : int(1..2)]) - | q24 : int(1..2)]), - and([s_ExplicitVarSizeWithDummy[q28] != 3 -> s_Occurrence[s_ExplicitVarSizeWithDummy[q28]] | q28 : int(1..2)]) - diff --git a/tests/exhaustive/basic/set_card_00/expected/model_4_2_2-solution000001.solution b/tests/exhaustive/basic/set_card_00/expected/model_4_2_2-solution000001.solution deleted file mode 100644 index 2ce5f2081f..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_4_2_2-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_4_2_2-solution000002.solution b/tests/exhaustive/basic/set_card_00/expected/model_4_2_2-solution000002.solution deleted file mode 100644 index 6c0d0fdad8..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_4_2_2-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting s be {1} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_4_2_2.eprime b/tests/exhaustive/basic/set_card_00/expected/model_4_2_2.eprime deleted file mode 100644 index f0da04a9ad..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_4_2_2.eprime +++ /dev/null @@ -1,26 +0,0 @@ -language ESSENCE' 1.0 - -find s_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..2)] of bool -find s_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..2)] of int(1..2) -find s_ExplicitVarSizeWithDummy: matrix indexed by [int(1..2)] of int(1..3) -branching on [s_ExplicitVarSizeWithDummy, s_ExplicitVarSizeWithFlags_Flags, s_ExplicitVarSizeWithFlags_Values] -such that - or([s_ExplicitVarSizeWithDummy[q19] != 3 /\ - s_ExplicitVarSizeWithDummy[q19] = sum([toInt(s_ExplicitVarSizeWithFlags_Flags[q21]) | q21 : int(1..2)]) - | q19 : int(1..2)]), - s_ExplicitVarSizeWithFlags_Flags[2] -> s_ExplicitVarSizeWithFlags_Values[1] < s_ExplicitVarSizeWithFlags_Values[2], - and([s_ExplicitVarSizeWithFlags_Flags[q2] = false -> s_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..2)]), - s_ExplicitVarSizeWithFlags_Flags[2] -> s_ExplicitVarSizeWithFlags_Flags[1], - s_ExplicitVarSizeWithDummy[1] < s_ExplicitVarSizeWithDummy[2] \/ s_ExplicitVarSizeWithDummy[1] = 3, - s_ExplicitVarSizeWithDummy[1] = 3 -> s_ExplicitVarSizeWithDummy[2] = 3, - and([s_ExplicitVarSizeWithDummy[q11] != 3 -> - or([s_ExplicitVarSizeWithFlags_Flags[q13] /\ - s_ExplicitVarSizeWithFlags_Values[q13] = s_ExplicitVarSizeWithDummy[q11] - | q13 : int(1..2)]) - | q11 : int(1..2)]), - and([s_ExplicitVarSizeWithFlags_Flags[q15] -> - or([s_ExplicitVarSizeWithDummy[q17] != 3 /\ - s_ExplicitVarSizeWithDummy[q17] = s_ExplicitVarSizeWithFlags_Values[q15] - | q17 : int(1..2)]) - | q15 : int(1..2)]) - diff --git a/tests/exhaustive/basic/set_card_00/expected/model_4_2_3-solution000001.solution b/tests/exhaustive/basic/set_card_00/expected/model_4_2_3-solution000001.solution deleted file mode 100644 index 6c0d0fdad8..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_4_2_3-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting s be {1} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_4_2_3-solution000002.solution b/tests/exhaustive/basic/set_card_00/expected/model_4_2_3-solution000002.solution deleted file mode 100644 index 2ce5f2081f..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_4_2_3-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_4_2_3.eprime b/tests/exhaustive/basic/set_card_00/expected/model_4_2_3.eprime deleted file mode 100644 index a8dd578091..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_4_2_3.eprime +++ /dev/null @@ -1,53 +0,0 @@ -language ESSENCE' 1.0 - -find s_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..2)] of bool -find s_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..2)] of int(1..2) -find s_ExplicitVarSizeWithDummy: matrix indexed by [int(1..2)] of int(1..3) -find s_ExplicitVarSizeWithMarker_Marker: int(0..2) -find s_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..2)] of int(1..2) -branching on - [s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithMarker_Values, s_ExplicitVarSizeWithFlags_Flags, - s_ExplicitVarSizeWithFlags_Values, s_ExplicitVarSizeWithDummy] -such that - or([s_ExplicitVarSizeWithDummy[q38] != 3 /\ - s_ExplicitVarSizeWithDummy[q38] = sum([toInt(s_ExplicitVarSizeWithFlags_Flags[q40]) | q40 : int(1..2)]) - | q38 : int(1..2)]), - s_ExplicitVarSizeWithFlags_Flags[2] -> s_ExplicitVarSizeWithFlags_Values[1] < s_ExplicitVarSizeWithFlags_Values[2], - and([s_ExplicitVarSizeWithFlags_Flags[q2] = false -> s_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..2)]), - s_ExplicitVarSizeWithFlags_Flags[2] -> s_ExplicitVarSizeWithFlags_Flags[1], - s_ExplicitVarSizeWithDummy[1] < s_ExplicitVarSizeWithDummy[2] \/ s_ExplicitVarSizeWithDummy[1] = 3, - s_ExplicitVarSizeWithDummy[1] = 3 -> s_ExplicitVarSizeWithDummy[2] = 3, - and([s_ExplicitVarSizeWithDummy[q11] != 3 -> - or([s_ExplicitVarSizeWithFlags_Flags[q13] /\ - s_ExplicitVarSizeWithFlags_Values[q13] = s_ExplicitVarSizeWithDummy[q11] - | q13 : int(1..2)]) - | q11 : int(1..2)]), - and([s_ExplicitVarSizeWithFlags_Flags[q15] -> - or([s_ExplicitVarSizeWithDummy[q17] != 3 /\ - s_ExplicitVarSizeWithDummy[q17] = s_ExplicitVarSizeWithFlags_Values[q15] - | q17 : int(1..2)]) - | q15 : int(1..2)]), - 2 <= s_ExplicitVarSizeWithMarker_Marker -> - s_ExplicitVarSizeWithMarker_Values[1] < s_ExplicitVarSizeWithMarker_Values[2], - and([q19 > s_ExplicitVarSizeWithMarker_Marker -> s_ExplicitVarSizeWithMarker_Values[q19] = 1 | q19 : int(1..2)]), - and([q22 <= s_ExplicitVarSizeWithMarker_Marker -> - or([s_ExplicitVarSizeWithFlags_Flags[q24] /\ - s_ExplicitVarSizeWithFlags_Values[q24] = s_ExplicitVarSizeWithMarker_Values[q22] - | q24 : int(1..2)]) - | q22 : int(1..2)]), - and([s_ExplicitVarSizeWithFlags_Flags[q26] -> - or([q28 <= s_ExplicitVarSizeWithMarker_Marker /\ - s_ExplicitVarSizeWithMarker_Values[q28] = s_ExplicitVarSizeWithFlags_Values[q26] - | q28 : int(1..2)]) - | q26 : int(1..2)]), - and([q30 <= s_ExplicitVarSizeWithMarker_Marker -> - or([s_ExplicitVarSizeWithDummy[q32] != 3 /\ - s_ExplicitVarSizeWithDummy[q32] = s_ExplicitVarSizeWithMarker_Values[q30] - | q32 : int(1..2)]) - | q30 : int(1..2)]), - and([s_ExplicitVarSizeWithDummy[q34] != 3 -> - or([q36 <= s_ExplicitVarSizeWithMarker_Marker /\ - s_ExplicitVarSizeWithMarker_Values[q36] = s_ExplicitVarSizeWithDummy[q34] - | q36 : int(1..2)]) - | q34 : int(1..2)]) - diff --git a/tests/exhaustive/basic/set_card_00/expected/model_4_2_4-solution000001.solution b/tests/exhaustive/basic/set_card_00/expected/model_4_2_4-solution000001.solution deleted file mode 100644 index 2ce5f2081f..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_4_2_4-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_4_2_4-solution000002.solution b/tests/exhaustive/basic/set_card_00/expected/model_4_2_4-solution000002.solution deleted file mode 100644 index 6c0d0fdad8..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_4_2_4-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting s be {1} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_4_2_4.eprime b/tests/exhaustive/basic/set_card_00/expected/model_4_2_4.eprime deleted file mode 100644 index f0da04a9ad..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_4_2_4.eprime +++ /dev/null @@ -1,26 +0,0 @@ -language ESSENCE' 1.0 - -find s_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..2)] of bool -find s_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..2)] of int(1..2) -find s_ExplicitVarSizeWithDummy: matrix indexed by [int(1..2)] of int(1..3) -branching on [s_ExplicitVarSizeWithDummy, s_ExplicitVarSizeWithFlags_Flags, s_ExplicitVarSizeWithFlags_Values] -such that - or([s_ExplicitVarSizeWithDummy[q19] != 3 /\ - s_ExplicitVarSizeWithDummy[q19] = sum([toInt(s_ExplicitVarSizeWithFlags_Flags[q21]) | q21 : int(1..2)]) - | q19 : int(1..2)]), - s_ExplicitVarSizeWithFlags_Flags[2] -> s_ExplicitVarSizeWithFlags_Values[1] < s_ExplicitVarSizeWithFlags_Values[2], - and([s_ExplicitVarSizeWithFlags_Flags[q2] = false -> s_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..2)]), - s_ExplicitVarSizeWithFlags_Flags[2] -> s_ExplicitVarSizeWithFlags_Flags[1], - s_ExplicitVarSizeWithDummy[1] < s_ExplicitVarSizeWithDummy[2] \/ s_ExplicitVarSizeWithDummy[1] = 3, - s_ExplicitVarSizeWithDummy[1] = 3 -> s_ExplicitVarSizeWithDummy[2] = 3, - and([s_ExplicitVarSizeWithDummy[q11] != 3 -> - or([s_ExplicitVarSizeWithFlags_Flags[q13] /\ - s_ExplicitVarSizeWithFlags_Values[q13] = s_ExplicitVarSizeWithDummy[q11] - | q13 : int(1..2)]) - | q11 : int(1..2)]), - and([s_ExplicitVarSizeWithFlags_Flags[q15] -> - or([s_ExplicitVarSizeWithDummy[q17] != 3 /\ - s_ExplicitVarSizeWithDummy[q17] = s_ExplicitVarSizeWithFlags_Values[q15] - | q17 : int(1..2)]) - | q15 : int(1..2)]) - diff --git a/tests/exhaustive/basic/set_card_00/expected/model_4_3_1-solution000001.solution b/tests/exhaustive/basic/set_card_00/expected/model_4_3_1-solution000001.solution deleted file mode 100644 index 6c0d0fdad8..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_4_3_1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting s be {1} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_4_3_1-solution000002.solution b/tests/exhaustive/basic/set_card_00/expected/model_4_3_1-solution000002.solution deleted file mode 100644 index 2ce5f2081f..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_4_3_1-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_4_3_1.eprime b/tests/exhaustive/basic/set_card_00/expected/model_4_3_1.eprime deleted file mode 100644 index b41daea4cc..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_4_3_1.eprime +++ /dev/null @@ -1,42 +0,0 @@ -language ESSENCE' 1.0 - -find s_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..2)] of bool -find s_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..2)] of int(1..2) -find s_ExplicitVarSizeWithMarker_Marker: int(0..2) -find s_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..2)] of int(1..2) -find s_Occurrence: matrix indexed by [int(1..2)] of bool -branching on - [s_Occurrence, s_ExplicitVarSizeWithFlags_Flags, s_ExplicitVarSizeWithFlags_Values, - s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithMarker_Values] -such that - or([q29 <= s_ExplicitVarSizeWithMarker_Marker /\ - s_ExplicitVarSizeWithMarker_Values[q29] = sum([toInt(s_ExplicitVarSizeWithFlags_Flags[q31]) | q31 : int(1..2)]) - | q29 : int(1..2)]), - s_ExplicitVarSizeWithFlags_Flags[2] -> s_ExplicitVarSizeWithFlags_Values[1] < s_ExplicitVarSizeWithFlags_Values[2], - and([s_ExplicitVarSizeWithFlags_Flags[q2] = false -> s_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..2)]), - s_ExplicitVarSizeWithFlags_Flags[2] -> s_ExplicitVarSizeWithFlags_Flags[1], - 2 <= s_ExplicitVarSizeWithMarker_Marker -> - s_ExplicitVarSizeWithMarker_Values[1] < s_ExplicitVarSizeWithMarker_Values[2], - and([q7 > s_ExplicitVarSizeWithMarker_Marker -> s_ExplicitVarSizeWithMarker_Values[q7] = 1 | q7 : int(1..2)]), - and([q10 <= s_ExplicitVarSizeWithMarker_Marker -> - or([s_ExplicitVarSizeWithFlags_Flags[q12] /\ - s_ExplicitVarSizeWithFlags_Values[q12] = s_ExplicitVarSizeWithMarker_Values[q10] - | q12 : int(1..2)]) - | q10 : int(1..2)]), - and([s_ExplicitVarSizeWithFlags_Flags[q14] -> - or([q16 <= s_ExplicitVarSizeWithMarker_Marker /\ - s_ExplicitVarSizeWithMarker_Values[q16] = s_ExplicitVarSizeWithFlags_Values[q14] - | q16 : int(1..2)]) - | q14 : int(1..2)]), - and([s_Occurrence[q18] -> - or([s_ExplicitVarSizeWithFlags_Flags[q20] /\ s_ExplicitVarSizeWithFlags_Values[q20] = q18 | q20 : int(1..2)]) - | q18 : int(1..2)]), - and([s_ExplicitVarSizeWithFlags_Flags[q22] -> s_Occurrence[s_ExplicitVarSizeWithFlags_Values[q22]] - | q22 : int(1..2)]), - and([s_Occurrence[q23] -> - or([q25 <= s_ExplicitVarSizeWithMarker_Marker /\ s_ExplicitVarSizeWithMarker_Values[q25] = q23 - | q25 : int(1..2)]) - | q23 : int(1..2)]), - and([q27 <= s_ExplicitVarSizeWithMarker_Marker -> s_Occurrence[s_ExplicitVarSizeWithMarker_Values[q27]] - | q27 : int(1..2)]) - diff --git a/tests/exhaustive/basic/set_card_00/expected/model_4_3_2-solution000001.solution b/tests/exhaustive/basic/set_card_00/expected/model_4_3_2-solution000001.solution deleted file mode 100644 index 2ce5f2081f..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_4_3_2-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_4_3_2-solution000002.solution b/tests/exhaustive/basic/set_card_00/expected/model_4_3_2-solution000002.solution deleted file mode 100644 index 6c0d0fdad8..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_4_3_2-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting s be {1} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_4_3_2.eprime b/tests/exhaustive/basic/set_card_00/expected/model_4_3_2.eprime deleted file mode 100644 index 6ad2dfa6b0..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_4_3_2.eprime +++ /dev/null @@ -1,53 +0,0 @@ -language ESSENCE' 1.0 - -find s_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..2)] of bool -find s_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..2)] of int(1..2) -find s_ExplicitVarSizeWithMarker_Marker: int(0..2) -find s_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..2)] of int(1..2) -find s_ExplicitVarSizeWithDummy: matrix indexed by [int(1..2)] of int(1..3) -branching on - [s_ExplicitVarSizeWithDummy, s_ExplicitVarSizeWithFlags_Flags, s_ExplicitVarSizeWithFlags_Values, - s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithMarker_Values] -such that - or([q38 <= s_ExplicitVarSizeWithMarker_Marker /\ - s_ExplicitVarSizeWithMarker_Values[q38] = sum([toInt(s_ExplicitVarSizeWithFlags_Flags[q40]) | q40 : int(1..2)]) - | q38 : int(1..2)]), - s_ExplicitVarSizeWithFlags_Flags[2] -> s_ExplicitVarSizeWithFlags_Values[1] < s_ExplicitVarSizeWithFlags_Values[2], - and([s_ExplicitVarSizeWithFlags_Flags[q2] = false -> s_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..2)]), - s_ExplicitVarSizeWithFlags_Flags[2] -> s_ExplicitVarSizeWithFlags_Flags[1], - 2 <= s_ExplicitVarSizeWithMarker_Marker -> - s_ExplicitVarSizeWithMarker_Values[1] < s_ExplicitVarSizeWithMarker_Values[2], - and([q7 > s_ExplicitVarSizeWithMarker_Marker -> s_ExplicitVarSizeWithMarker_Values[q7] = 1 | q7 : int(1..2)]), - and([q10 <= s_ExplicitVarSizeWithMarker_Marker -> - or([s_ExplicitVarSizeWithFlags_Flags[q12] /\ - s_ExplicitVarSizeWithFlags_Values[q12] = s_ExplicitVarSizeWithMarker_Values[q10] - | q12 : int(1..2)]) - | q10 : int(1..2)]), - and([s_ExplicitVarSizeWithFlags_Flags[q14] -> - or([q16 <= s_ExplicitVarSizeWithMarker_Marker /\ - s_ExplicitVarSizeWithMarker_Values[q16] = s_ExplicitVarSizeWithFlags_Values[q14] - | q16 : int(1..2)]) - | q14 : int(1..2)]), - s_ExplicitVarSizeWithDummy[1] < s_ExplicitVarSizeWithDummy[2] \/ s_ExplicitVarSizeWithDummy[1] = 3, - s_ExplicitVarSizeWithDummy[1] = 3 -> s_ExplicitVarSizeWithDummy[2] = 3, - and([s_ExplicitVarSizeWithDummy[q22] != 3 -> - or([s_ExplicitVarSizeWithFlags_Flags[q24] /\ - s_ExplicitVarSizeWithFlags_Values[q24] = s_ExplicitVarSizeWithDummy[q22] - | q24 : int(1..2)]) - | q22 : int(1..2)]), - and([s_ExplicitVarSizeWithFlags_Flags[q26] -> - or([s_ExplicitVarSizeWithDummy[q28] != 3 /\ - s_ExplicitVarSizeWithDummy[q28] = s_ExplicitVarSizeWithFlags_Values[q26] - | q28 : int(1..2)]) - | q26 : int(1..2)]), - and([s_ExplicitVarSizeWithDummy[q30] != 3 -> - or([q32 <= s_ExplicitVarSizeWithMarker_Marker /\ - s_ExplicitVarSizeWithMarker_Values[q32] = s_ExplicitVarSizeWithDummy[q30] - | q32 : int(1..2)]) - | q30 : int(1..2)]), - and([q34 <= s_ExplicitVarSizeWithMarker_Marker -> - or([s_ExplicitVarSizeWithDummy[q36] != 3 /\ - s_ExplicitVarSizeWithDummy[q36] = s_ExplicitVarSizeWithMarker_Values[q34] - | q36 : int(1..2)]) - | q34 : int(1..2)]) - diff --git a/tests/exhaustive/basic/set_card_00/expected/model_4_3_3-solution000001.solution b/tests/exhaustive/basic/set_card_00/expected/model_4_3_3-solution000001.solution deleted file mode 100644 index 6c0d0fdad8..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_4_3_3-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting s be {1} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_4_3_3-solution000002.solution b/tests/exhaustive/basic/set_card_00/expected/model_4_3_3-solution000002.solution deleted file mode 100644 index 2ce5f2081f..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_4_3_3-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_4_3_3.eprime b/tests/exhaustive/basic/set_card_00/expected/model_4_3_3.eprime deleted file mode 100644 index 4bf46f85b1..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_4_3_3.eprime +++ /dev/null @@ -1,30 +0,0 @@ -language ESSENCE' 1.0 - -find s_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..2)] of bool -find s_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..2)] of int(1..2) -find s_ExplicitVarSizeWithMarker_Marker: int(0..2) -find s_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..2)] of int(1..2) -branching on - [s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithMarker_Values, s_ExplicitVarSizeWithFlags_Flags, - s_ExplicitVarSizeWithFlags_Values] -such that - or([q18 <= s_ExplicitVarSizeWithMarker_Marker /\ - s_ExplicitVarSizeWithMarker_Values[q18] = sum([toInt(s_ExplicitVarSizeWithFlags_Flags[q20]) | q20 : int(1..2)]) - | q18 : int(1..2)]), - s_ExplicitVarSizeWithFlags_Flags[2] -> s_ExplicitVarSizeWithFlags_Values[1] < s_ExplicitVarSizeWithFlags_Values[2], - and([s_ExplicitVarSizeWithFlags_Flags[q2] = false -> s_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..2)]), - s_ExplicitVarSizeWithFlags_Flags[2] -> s_ExplicitVarSizeWithFlags_Flags[1], - 2 <= s_ExplicitVarSizeWithMarker_Marker -> - s_ExplicitVarSizeWithMarker_Values[1] < s_ExplicitVarSizeWithMarker_Values[2], - and([q7 > s_ExplicitVarSizeWithMarker_Marker -> s_ExplicitVarSizeWithMarker_Values[q7] = 1 | q7 : int(1..2)]), - and([q10 <= s_ExplicitVarSizeWithMarker_Marker -> - or([s_ExplicitVarSizeWithFlags_Flags[q12] /\ - s_ExplicitVarSizeWithFlags_Values[q12] = s_ExplicitVarSizeWithMarker_Values[q10] - | q12 : int(1..2)]) - | q10 : int(1..2)]), - and([s_ExplicitVarSizeWithFlags_Flags[q14] -> - or([q16 <= s_ExplicitVarSizeWithMarker_Marker /\ - s_ExplicitVarSizeWithMarker_Values[q16] = s_ExplicitVarSizeWithFlags_Values[q14] - | q16 : int(1..2)]) - | q14 : int(1..2)]) - diff --git a/tests/exhaustive/basic/set_card_00/expected/model_4_3_4-solution000001.solution b/tests/exhaustive/basic/set_card_00/expected/model_4_3_4-solution000001.solution deleted file mode 100644 index 6c0d0fdad8..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_4_3_4-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting s be {1} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_4_3_4-solution000002.solution b/tests/exhaustive/basic/set_card_00/expected/model_4_3_4-solution000002.solution deleted file mode 100644 index 2ce5f2081f..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_4_3_4-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_4_3_4.eprime b/tests/exhaustive/basic/set_card_00/expected/model_4_3_4.eprime deleted file mode 100644 index 4bf46f85b1..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_4_3_4.eprime +++ /dev/null @@ -1,30 +0,0 @@ -language ESSENCE' 1.0 - -find s_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..2)] of bool -find s_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..2)] of int(1..2) -find s_ExplicitVarSizeWithMarker_Marker: int(0..2) -find s_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..2)] of int(1..2) -branching on - [s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithMarker_Values, s_ExplicitVarSizeWithFlags_Flags, - s_ExplicitVarSizeWithFlags_Values] -such that - or([q18 <= s_ExplicitVarSizeWithMarker_Marker /\ - s_ExplicitVarSizeWithMarker_Values[q18] = sum([toInt(s_ExplicitVarSizeWithFlags_Flags[q20]) | q20 : int(1..2)]) - | q18 : int(1..2)]), - s_ExplicitVarSizeWithFlags_Flags[2] -> s_ExplicitVarSizeWithFlags_Values[1] < s_ExplicitVarSizeWithFlags_Values[2], - and([s_ExplicitVarSizeWithFlags_Flags[q2] = false -> s_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..2)]), - s_ExplicitVarSizeWithFlags_Flags[2] -> s_ExplicitVarSizeWithFlags_Flags[1], - 2 <= s_ExplicitVarSizeWithMarker_Marker -> - s_ExplicitVarSizeWithMarker_Values[1] < s_ExplicitVarSizeWithMarker_Values[2], - and([q7 > s_ExplicitVarSizeWithMarker_Marker -> s_ExplicitVarSizeWithMarker_Values[q7] = 1 | q7 : int(1..2)]), - and([q10 <= s_ExplicitVarSizeWithMarker_Marker -> - or([s_ExplicitVarSizeWithFlags_Flags[q12] /\ - s_ExplicitVarSizeWithFlags_Values[q12] = s_ExplicitVarSizeWithMarker_Values[q10] - | q12 : int(1..2)]) - | q10 : int(1..2)]), - and([s_ExplicitVarSizeWithFlags_Flags[q14] -> - or([q16 <= s_ExplicitVarSizeWithMarker_Marker /\ - s_ExplicitVarSizeWithMarker_Values[q16] = s_ExplicitVarSizeWithFlags_Values[q14] - | q16 : int(1..2)]) - | q14 : int(1..2)]) - diff --git a/tests/exhaustive/basic/set_card_00/expected/model_4_4_1-solution000001.solution b/tests/exhaustive/basic/set_card_00/expected/model_4_4_1-solution000001.solution deleted file mode 100644 index 6c0d0fdad8..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_4_4_1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting s be {1} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_4_4_1-solution000002.solution b/tests/exhaustive/basic/set_card_00/expected/model_4_4_1-solution000002.solution deleted file mode 100644 index 2ce5f2081f..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_4_4_1-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_4_4_1.eprime b/tests/exhaustive/basic/set_card_00/expected/model_4_4_1.eprime deleted file mode 100644 index 4b827d683c..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_4_4_1.eprime +++ /dev/null @@ -1,19 +0,0 @@ -language ESSENCE' 1.0 - -find s_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..2)] of bool -find s_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..2)] of int(1..2) -find s_Occurrence: matrix indexed by [int(1..2)] of bool -branching on [s_Occurrence, s_ExplicitVarSizeWithFlags_Flags, s_ExplicitVarSizeWithFlags_Values] -such that - or([s_ExplicitVarSizeWithFlags_Flags[q13] /\ - s_ExplicitVarSizeWithFlags_Values[q13] = sum([toInt(s_ExplicitVarSizeWithFlags_Flags[q15]) | q15 : int(1..2)]) - | q13 : int(1..2)]), - s_ExplicitVarSizeWithFlags_Flags[2] -> s_ExplicitVarSizeWithFlags_Values[1] < s_ExplicitVarSizeWithFlags_Values[2], - and([s_ExplicitVarSizeWithFlags_Flags[q2] = false -> s_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..2)]), - s_ExplicitVarSizeWithFlags_Flags[2] -> s_ExplicitVarSizeWithFlags_Flags[1], - and([s_Occurrence[q7] -> - or([s_ExplicitVarSizeWithFlags_Flags[q9] /\ s_ExplicitVarSizeWithFlags_Values[q9] = q7 | q9 : int(1..2)]) - | q7 : int(1..2)]), - and([s_ExplicitVarSizeWithFlags_Flags[q11] -> s_Occurrence[s_ExplicitVarSizeWithFlags_Values[q11]] - | q11 : int(1..2)]) - diff --git a/tests/exhaustive/basic/set_card_00/expected/model_4_4_2-solution000001.solution b/tests/exhaustive/basic/set_card_00/expected/model_4_4_2-solution000001.solution deleted file mode 100644 index 2ce5f2081f..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_4_4_2-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_4_4_2-solution000002.solution b/tests/exhaustive/basic/set_card_00/expected/model_4_4_2-solution000002.solution deleted file mode 100644 index 6c0d0fdad8..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_4_4_2-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting s be {1} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_4_4_2.eprime b/tests/exhaustive/basic/set_card_00/expected/model_4_4_2.eprime deleted file mode 100644 index 87dc67de4e..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_4_4_2.eprime +++ /dev/null @@ -1,26 +0,0 @@ -language ESSENCE' 1.0 - -find s_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..2)] of bool -find s_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..2)] of int(1..2) -find s_ExplicitVarSizeWithDummy: matrix indexed by [int(1..2)] of int(1..3) -branching on [s_ExplicitVarSizeWithDummy, s_ExplicitVarSizeWithFlags_Flags, s_ExplicitVarSizeWithFlags_Values] -such that - or([s_ExplicitVarSizeWithFlags_Flags[q19] /\ - s_ExplicitVarSizeWithFlags_Values[q19] = sum([toInt(s_ExplicitVarSizeWithFlags_Flags[q21]) | q21 : int(1..2)]) - | q19 : int(1..2)]), - s_ExplicitVarSizeWithFlags_Flags[2] -> s_ExplicitVarSizeWithFlags_Values[1] < s_ExplicitVarSizeWithFlags_Values[2], - and([s_ExplicitVarSizeWithFlags_Flags[q2] = false -> s_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..2)]), - s_ExplicitVarSizeWithFlags_Flags[2] -> s_ExplicitVarSizeWithFlags_Flags[1], - s_ExplicitVarSizeWithDummy[1] < s_ExplicitVarSizeWithDummy[2] \/ s_ExplicitVarSizeWithDummy[1] = 3, - s_ExplicitVarSizeWithDummy[1] = 3 -> s_ExplicitVarSizeWithDummy[2] = 3, - and([s_ExplicitVarSizeWithDummy[q11] != 3 -> - or([s_ExplicitVarSizeWithFlags_Flags[q13] /\ - s_ExplicitVarSizeWithFlags_Values[q13] = s_ExplicitVarSizeWithDummy[q11] - | q13 : int(1..2)]) - | q11 : int(1..2)]), - and([s_ExplicitVarSizeWithFlags_Flags[q15] -> - or([s_ExplicitVarSizeWithDummy[q17] != 3 /\ - s_ExplicitVarSizeWithDummy[q17] = s_ExplicitVarSizeWithFlags_Values[q15] - | q17 : int(1..2)]) - | q15 : int(1..2)]) - diff --git a/tests/exhaustive/basic/set_card_00/expected/model_4_4_3-solution000001.solution b/tests/exhaustive/basic/set_card_00/expected/model_4_4_3-solution000001.solution deleted file mode 100644 index 6c0d0fdad8..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_4_4_3-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting s be {1} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_4_4_3-solution000002.solution b/tests/exhaustive/basic/set_card_00/expected/model_4_4_3-solution000002.solution deleted file mode 100644 index 2ce5f2081f..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_4_4_3-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_4_4_3.eprime b/tests/exhaustive/basic/set_card_00/expected/model_4_4_3.eprime deleted file mode 100644 index 2634131abd..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_4_4_3.eprime +++ /dev/null @@ -1,30 +0,0 @@ -language ESSENCE' 1.0 - -find s_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..2)] of bool -find s_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..2)] of int(1..2) -find s_ExplicitVarSizeWithMarker_Marker: int(0..2) -find s_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..2)] of int(1..2) -branching on - [s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithMarker_Values, s_ExplicitVarSizeWithFlags_Flags, - s_ExplicitVarSizeWithFlags_Values] -such that - or([s_ExplicitVarSizeWithFlags_Flags[q18] /\ - s_ExplicitVarSizeWithFlags_Values[q18] = sum([toInt(s_ExplicitVarSizeWithFlags_Flags[q20]) | q20 : int(1..2)]) - | q18 : int(1..2)]), - s_ExplicitVarSizeWithFlags_Flags[2] -> s_ExplicitVarSizeWithFlags_Values[1] < s_ExplicitVarSizeWithFlags_Values[2], - and([s_ExplicitVarSizeWithFlags_Flags[q2] = false -> s_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..2)]), - s_ExplicitVarSizeWithFlags_Flags[2] -> s_ExplicitVarSizeWithFlags_Flags[1], - 2 <= s_ExplicitVarSizeWithMarker_Marker -> - s_ExplicitVarSizeWithMarker_Values[1] < s_ExplicitVarSizeWithMarker_Values[2], - and([q7 > s_ExplicitVarSizeWithMarker_Marker -> s_ExplicitVarSizeWithMarker_Values[q7] = 1 | q7 : int(1..2)]), - and([q10 <= s_ExplicitVarSizeWithMarker_Marker -> - or([s_ExplicitVarSizeWithFlags_Flags[q12] /\ - s_ExplicitVarSizeWithFlags_Values[q12] = s_ExplicitVarSizeWithMarker_Values[q10] - | q12 : int(1..2)]) - | q10 : int(1..2)]), - and([s_ExplicitVarSizeWithFlags_Flags[q14] -> - or([q16 <= s_ExplicitVarSizeWithMarker_Marker /\ - s_ExplicitVarSizeWithMarker_Values[q16] = s_ExplicitVarSizeWithFlags_Values[q14] - | q16 : int(1..2)]) - | q14 : int(1..2)]) - diff --git a/tests/exhaustive/basic/set_card_00/expected/model_4_4_4-solution000001.solution b/tests/exhaustive/basic/set_card_00/expected/model_4_4_4-solution000001.solution deleted file mode 100644 index 6c0d0fdad8..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_4_4_4-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting s be {1} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_4_4_4-solution000002.solution b/tests/exhaustive/basic/set_card_00/expected/model_4_4_4-solution000002.solution deleted file mode 100644 index 2ce5f2081f..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_4_4_4-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting s be {1, 2} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_4_4_4.eprime b/tests/exhaustive/basic/set_card_00/expected/model_4_4_4.eprime deleted file mode 100644 index f18fbe001d..0000000000 --- a/tests/exhaustive/basic/set_card_00/expected/model_4_4_4.eprime +++ /dev/null @@ -1,13 +0,0 @@ -language ESSENCE' 1.0 - -find s_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..2)] of bool -find s_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..2)] of int(1..2) -branching on [s_ExplicitVarSizeWithFlags_Flags, s_ExplicitVarSizeWithFlags_Values] -such that - or([s_ExplicitVarSizeWithFlags_Flags[q7] /\ - s_ExplicitVarSizeWithFlags_Values[q7] = sum([toInt(s_ExplicitVarSizeWithFlags_Flags[q9]) | q9 : int(1..2)]) - | q7 : int(1..2)]), - s_ExplicitVarSizeWithFlags_Flags[2] -> s_ExplicitVarSizeWithFlags_Values[1] < s_ExplicitVarSizeWithFlags_Values[2], - and([s_ExplicitVarSizeWithFlags_Flags[q2] = false -> s_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..2)]), - s_ExplicitVarSizeWithFlags_Flags[2] -> s_ExplicitVarSizeWithFlags_Flags[1] - diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_1_1_1_1-solution000001.solution b/tests/exhaustive/basic/streamline01/expected/model_1_1_1_1_1-solution000001.solution deleted file mode 100644 index cd31e1020f..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_1_1_1_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(2 --> 1) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_1_1_1_1-solution000002.solution b/tests/exhaustive/basic/streamline01/expected/model_1_1_1_1_1-solution000002.solution deleted file mode 100644 index 2646544d52..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_1_1_1_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(2 --> 2) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_1_1_1_1-solution000003.solution b/tests/exhaustive/basic/streamline01/expected/model_1_1_1_1_1-solution000003.solution deleted file mode 100644 index 6da2c362aa..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_1_1_1_1-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 1) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_1_1_1_1-solution000004.solution b/tests/exhaustive/basic/streamline01/expected/model_1_1_1_1_1-solution000004.solution deleted file mode 100644 index 9fbfa45bad..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_1_1_1_1-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 2) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_1_1_1_1-solution000005.solution b/tests/exhaustive/basic/streamline01/expected/model_1_1_1_1_1-solution000005.solution deleted file mode 100644 index e62a462994..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_1_1_1_1-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 1, 2 --> 1) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_1_1_1_1-solution000006.solution b/tests/exhaustive/basic/streamline01/expected/model_1_1_1_1_1-solution000006.solution deleted file mode 100644 index 77f032a426..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_1_1_1_1-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 1, 2 --> 1) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_1_1_1_1-solution000007.solution b/tests/exhaustive/basic/streamline01/expected/model_1_1_1_1_1-solution000007.solution deleted file mode 100644 index d2200a27b7..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_1_1_1_1-solution000007.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 1, 2 --> 2) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_1_1_1_1-solution000008.solution b/tests/exhaustive/basic/streamline01/expected/model_1_1_1_1_1-solution000008.solution deleted file mode 100644 index 57c81f730c..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_1_1_1_1-solution000008.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 1, 2 --> 2) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_1_1_1_1-solution000009.solution b/tests/exhaustive/basic/streamline01/expected/model_1_1_1_1_1-solution000009.solution deleted file mode 100644 index 03807b7fff..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_1_1_1_1-solution000009.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 2, 2 --> 1) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_1_1_1_1-solution000010.solution b/tests/exhaustive/basic/streamline01/expected/model_1_1_1_1_1-solution000010.solution deleted file mode 100644 index 50857d4142..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_1_1_1_1-solution000010.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 2, 2 --> 1) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_1_1_1_1-solution000011.solution b/tests/exhaustive/basic/streamline01/expected/model_1_1_1_1_1-solution000011.solution deleted file mode 100644 index e00a3c532c..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_1_1_1_1-solution000011.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 2, 2 --> 2) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_1_1_1_1-solution000012.solution b/tests/exhaustive/basic/streamline01/expected/model_1_1_1_1_1-solution000012.solution deleted file mode 100644 index b33ee31e23..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_1_1_1_1-solution000012.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 2, 2 --> 2) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_1_1_1_1.eprime b/tests/exhaustive/basic/streamline01/expected/model_1_1_1_1_1.eprime deleted file mode 100644 index 047ea11169..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_1_1_1_1.eprime +++ /dev/null @@ -1,34 +0,0 @@ -language ESSENCE' 1.0 - -find f_Function1DPartial_Flags: matrix indexed by [int(1..2)] of bool -find f_Function1DPartial_Values: matrix indexed by [int(1..2)] of int(1..2) -find s_Occurrence: matrix indexed by [int(1..2)] of bool -find conjure_aux3: int(1..2) -find conjure_aux1: matrix indexed by [int(1..2)] of int(1..2) -find conjure_aux2: matrix indexed by [int(1..2)] of int(1..2) -branching on [f_Function1DPartial_Flags, f_Function1DPartial_Values, s_Occurrence] -such that - and([s_Occurrence[q9] -> f_Function1DPartial_Flags[q9] | q9 : int(1..2)]), - and([s_Occurrence[q7] -> q7 >= conjure_aux3 | q7 : int(1..2)]), - sum([toInt(s_Occurrence[q7]) | q7 : int(1..2)]) > 0 -> or([s_Occurrence[q7] /\ q7 = conjure_aux3 | q7 : int(1..2)]), - sum([toInt(s_Occurrence[q7]) | q7 : int(1..2)]) = 0 -> conjure_aux3 = 1, - and([and([s_Occurrence[q5] -> q5 >= conjure_aux1[i] | q5 : int(1..2)]) | i : int(1..2)]), - and([(sum([toInt(s_Occurrence[q5]) | q5 : int(1..2)]) > 0 -> - or([s_Occurrence[q5] /\ q5 = conjure_aux1[i] | q5 : int(1..2)])) - /\ (sum([toInt(s_Occurrence[q5]) | q5 : int(1..2)]) = 0 -> conjure_aux1[i] = 1) - | i : int(1..2)]), - and([and([s_Occurrence[q6] -> q6 >= conjure_aux2[i] | q6 : int(1..2)]) | i : int(1..2)]), - and([(sum([toInt(s_Occurrence[q6]) | q6 : int(1..2)]) > 0 -> - or([s_Occurrence[q6] /\ q6 = conjure_aux2[i] | q6 : int(1..2)])) - /\ (sum([toInt(s_Occurrence[q6]) | q6 : int(1..2)]) = 0 -> conjure_aux2[i] = 1) - | i : int(1..2)]), - and([s_Occurrence[i] /\ (i != conjure_aux3 /\ sum([toInt(s_Occurrence[q7]) | q7 : int(1..2)]) > 0) -> - and([f_Function1DPartial_Values[i] > f_Function1DPartial_Values[conjure_aux1[i]] /\ - sum([toInt(s_Occurrence[q5]) | q5 : int(1..2)]) > 0, - f_Function1DPartial_Flags[i], - f_Function1DPartial_Flags[conjure_aux2[i]] /\ sum([toInt(s_Occurrence[q6]) | q6 : int(1..2)]) > 0; - int(1..3)]) - | i : int(1..2)]), - 1 = sum([toInt(s_Occurrence[q1]) | q1 : int(1..2)]), - and([f_Function1DPartial_Flags[q2] = false -> f_Function1DPartial_Values[q2] = 1 | q2 : int(1..2)]) - diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_1_1_1_2-solution000001.solution b/tests/exhaustive/basic/streamline01/expected/model_1_1_1_1_2-solution000001.solution deleted file mode 100644 index cd31e1020f..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_1_1_1_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(2 --> 1) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_1_1_1_2-solution000002.solution b/tests/exhaustive/basic/streamline01/expected/model_1_1_1_1_2-solution000002.solution deleted file mode 100644 index 2646544d52..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_1_1_1_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(2 --> 2) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_1_1_1_2-solution000003.solution b/tests/exhaustive/basic/streamline01/expected/model_1_1_1_1_2-solution000003.solution deleted file mode 100644 index 6da2c362aa..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_1_1_1_2-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 1) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_1_1_1_2-solution000004.solution b/tests/exhaustive/basic/streamline01/expected/model_1_1_1_1_2-solution000004.solution deleted file mode 100644 index 9fbfa45bad..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_1_1_1_2-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 2) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_1_1_1_2-solution000005.solution b/tests/exhaustive/basic/streamline01/expected/model_1_1_1_1_2-solution000005.solution deleted file mode 100644 index 77f032a426..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_1_1_1_2-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 1, 2 --> 1) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_1_1_1_2-solution000006.solution b/tests/exhaustive/basic/streamline01/expected/model_1_1_1_1_2-solution000006.solution deleted file mode 100644 index e62a462994..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_1_1_1_2-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 1, 2 --> 1) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_1_1_1_2-solution000007.solution b/tests/exhaustive/basic/streamline01/expected/model_1_1_1_1_2-solution000007.solution deleted file mode 100644 index 57c81f730c..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_1_1_1_2-solution000007.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 1, 2 --> 2) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_1_1_1_2-solution000008.solution b/tests/exhaustive/basic/streamline01/expected/model_1_1_1_1_2-solution000008.solution deleted file mode 100644 index d2200a27b7..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_1_1_1_2-solution000008.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 1, 2 --> 2) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_1_1_1_2-solution000009.solution b/tests/exhaustive/basic/streamline01/expected/model_1_1_1_1_2-solution000009.solution deleted file mode 100644 index 50857d4142..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_1_1_1_2-solution000009.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 2, 2 --> 1) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_1_1_1_2-solution000010.solution b/tests/exhaustive/basic/streamline01/expected/model_1_1_1_1_2-solution000010.solution deleted file mode 100644 index 03807b7fff..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_1_1_1_2-solution000010.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 2, 2 --> 1) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_1_1_1_2-solution000011.solution b/tests/exhaustive/basic/streamline01/expected/model_1_1_1_1_2-solution000011.solution deleted file mode 100644 index b33ee31e23..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_1_1_1_2-solution000011.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 2, 2 --> 2) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_1_1_1_2-solution000012.solution b/tests/exhaustive/basic/streamline01/expected/model_1_1_1_1_2-solution000012.solution deleted file mode 100644 index e00a3c532c..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_1_1_1_2-solution000012.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 2, 2 --> 2) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_1_1_1_2.eprime b/tests/exhaustive/basic/streamline01/expected/model_1_1_1_1_2.eprime deleted file mode 100644 index 468a25ece6..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_1_1_1_2.eprime +++ /dev/null @@ -1,38 +0,0 @@ -language ESSENCE' 1.0 - -find f_Function1DPartial_Flags: matrix indexed by [int(1..2)] of bool -find f_Function1DPartial_Values: matrix indexed by [int(1..2)] of int(1..2) -find s_Occurrence: matrix indexed by [int(1..2)] of bool -find s_Explicit: matrix indexed by [int(1)] of int(1..2) -find conjure_aux3: int(1..2) -find conjure_aux1: matrix indexed by [int(1..2)] of int(1..2) -find conjure_aux2: matrix indexed by [int(1..2)] of int(1..2) -branching on [f_Function1DPartial_Flags, f_Function1DPartial_Values, s_Explicit, s_Occurrence] -such that - and([s_Occurrence[q16] -> f_Function1DPartial_Flags[q16] | q16 : int(1..2)]), - and([s_Occurrence[q14] -> q14 >= conjure_aux3 | q14 : int(1..2)]), - sum([toInt(s_Occurrence[q14]) | q14 : int(1..2)]) > 0 -> - or([s_Occurrence[q14] /\ q14 = conjure_aux3 | q14 : int(1..2)]), - sum([toInt(s_Occurrence[q14]) | q14 : int(1..2)]) = 0 -> conjure_aux3 = 1, - and([and([s_Occurrence[q12] -> q12 >= conjure_aux1[i] | q12 : int(1..2)]) | i : int(1..2)]), - and([(sum([toInt(s_Occurrence[q12]) | q12 : int(1..2)]) > 0 -> - or([s_Occurrence[q12] /\ q12 = conjure_aux1[i] | q12 : int(1..2)])) - /\ (sum([toInt(s_Occurrence[q12]) | q12 : int(1..2)]) = 0 -> conjure_aux1[i] = 1) - | i : int(1..2)]), - and([and([s_Occurrence[q13] -> q13 >= conjure_aux2[i] | q13 : int(1..2)]) | i : int(1..2)]), - and([(sum([toInt(s_Occurrence[q13]) | q13 : int(1..2)]) > 0 -> - or([s_Occurrence[q13] /\ q13 = conjure_aux2[i] | q13 : int(1..2)])) - /\ (sum([toInt(s_Occurrence[q13]) | q13 : int(1..2)]) = 0 -> conjure_aux2[i] = 1) - | i : int(1..2)]), - and([s_Occurrence[i] /\ (i != conjure_aux3 /\ sum([toInt(s_Occurrence[q14]) | q14 : int(1..2)]) > 0) -> - and([f_Function1DPartial_Values[i] > f_Function1DPartial_Values[conjure_aux1[i]] /\ - sum([toInt(s_Occurrence[q12]) | q12 : int(1..2)]) > 0, - f_Function1DPartial_Flags[i], - f_Function1DPartial_Flags[conjure_aux2[i]] /\ sum([toInt(s_Occurrence[q13]) | q13 : int(1..2)]) > 0; - int(1..3)]) - | i : int(1..2)]), - 1 = sum([toInt(s_Occurrence[q1]) | q1 : int(1..2)]), - and([f_Function1DPartial_Flags[q2] = false -> f_Function1DPartial_Values[q2] = 1 | q2 : int(1..2)]), - s_Occurrence[s_Explicit[1]], - and([s_Occurrence[q9] -> s_Explicit[1] = q9 | q9 : int(1..2)]) - diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_1_1_2_1-solution000001.solution b/tests/exhaustive/basic/streamline01/expected/model_1_1_1_2_1-solution000001.solution deleted file mode 100644 index cd31e1020f..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_1_1_2_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(2 --> 1) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_1_1_2_1-solution000002.solution b/tests/exhaustive/basic/streamline01/expected/model_1_1_1_2_1-solution000002.solution deleted file mode 100644 index 2646544d52..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_1_1_2_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(2 --> 2) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_1_1_2_1-solution000003.solution b/tests/exhaustive/basic/streamline01/expected/model_1_1_1_2_1-solution000003.solution deleted file mode 100644 index 6da2c362aa..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_1_1_2_1-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 1) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_1_1_2_1-solution000004.solution b/tests/exhaustive/basic/streamline01/expected/model_1_1_1_2_1-solution000004.solution deleted file mode 100644 index 9fbfa45bad..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_1_1_2_1-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 2) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_1_1_2_1-solution000005.solution b/tests/exhaustive/basic/streamline01/expected/model_1_1_1_2_1-solution000005.solution deleted file mode 100644 index 77f032a426..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_1_1_2_1-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 1, 2 --> 1) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_1_1_2_1-solution000006.solution b/tests/exhaustive/basic/streamline01/expected/model_1_1_1_2_1-solution000006.solution deleted file mode 100644 index e62a462994..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_1_1_2_1-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 1, 2 --> 1) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_1_1_2_1-solution000007.solution b/tests/exhaustive/basic/streamline01/expected/model_1_1_1_2_1-solution000007.solution deleted file mode 100644 index 57c81f730c..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_1_1_2_1-solution000007.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 1, 2 --> 2) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_1_1_2_1-solution000008.solution b/tests/exhaustive/basic/streamline01/expected/model_1_1_1_2_1-solution000008.solution deleted file mode 100644 index d2200a27b7..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_1_1_2_1-solution000008.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 1, 2 --> 2) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_1_1_2_1-solution000009.solution b/tests/exhaustive/basic/streamline01/expected/model_1_1_1_2_1-solution000009.solution deleted file mode 100644 index 50857d4142..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_1_1_2_1-solution000009.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 2, 2 --> 1) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_1_1_2_1-solution000010.solution b/tests/exhaustive/basic/streamline01/expected/model_1_1_1_2_1-solution000010.solution deleted file mode 100644 index 03807b7fff..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_1_1_2_1-solution000010.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 2, 2 --> 1) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_1_1_2_1-solution000011.solution b/tests/exhaustive/basic/streamline01/expected/model_1_1_1_2_1-solution000011.solution deleted file mode 100644 index b33ee31e23..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_1_1_2_1-solution000011.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 2, 2 --> 2) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_1_1_2_1-solution000012.solution b/tests/exhaustive/basic/streamline01/expected/model_1_1_1_2_1-solution000012.solution deleted file mode 100644 index e00a3c532c..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_1_1_2_1-solution000012.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 2, 2 --> 2) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_1_1_2_1.eprime b/tests/exhaustive/basic/streamline01/expected/model_1_1_1_2_1.eprime deleted file mode 100644 index b202cb49d4..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_1_1_2_1.eprime +++ /dev/null @@ -1,33 +0,0 @@ -language ESSENCE' 1.0 - -find f_Function1DPartial_Flags: matrix indexed by [int(1..2)] of bool -find f_Function1DPartial_Values: matrix indexed by [int(1..2)] of int(1..2) -find s_Occurrence: matrix indexed by [int(1..2)] of bool -find s_Explicit: matrix indexed by [int(1)] of int(1..2) -find conjure_aux1: matrix indexed by [int(1..2)] of int(1..2) -find conjure_aux2: matrix indexed by [int(1..2)] of int(1..2) -branching on [f_Function1DPartial_Flags, f_Function1DPartial_Values, s_Explicit, s_Occurrence] -such that - and([s_Occurrence[q15] -> f_Function1DPartial_Flags[q15] | q15 : int(1..2)]), - and([and([s_Occurrence[q12] -> q12 >= conjure_aux1[i] | q12 : int(1..2)]) | i : int(1..2)]), - and([(sum([toInt(s_Occurrence[q12]) | q12 : int(1..2)]) > 0 -> - or([s_Occurrence[q12] /\ q12 = conjure_aux1[i] | q12 : int(1..2)])) - /\ (sum([toInt(s_Occurrence[q12]) | q12 : int(1..2)]) = 0 -> conjure_aux1[i] = 1) - | i : int(1..2)]), - and([and([s_Occurrence[q13] -> q13 >= conjure_aux2[i] | q13 : int(1..2)]) | i : int(1..2)]), - and([(sum([toInt(s_Occurrence[q13]) | q13 : int(1..2)]) > 0 -> - or([s_Occurrence[q13] /\ q13 = conjure_aux2[i] | q13 : int(1..2)])) - /\ (sum([toInt(s_Occurrence[q13]) | q13 : int(1..2)]) = 0 -> conjure_aux2[i] = 1) - | i : int(1..2)]), - and([s_Occurrence[i] /\ i != s_Explicit[1] -> - and([f_Function1DPartial_Values[i] > f_Function1DPartial_Values[conjure_aux1[i]] /\ - sum([toInt(s_Occurrence[q12]) | q12 : int(1..2)]) > 0, - f_Function1DPartial_Flags[i], - f_Function1DPartial_Flags[conjure_aux2[i]] /\ sum([toInt(s_Occurrence[q13]) | q13 : int(1..2)]) > 0; - int(1..3)]) - | i : int(1..2)]), - 1 = sum([toInt(s_Occurrence[q1]) | q1 : int(1..2)]), - and([f_Function1DPartial_Flags[q2] = false -> f_Function1DPartial_Values[q2] = 1 | q2 : int(1..2)]), - s_Occurrence[s_Explicit[1]], - and([s_Occurrence[q9] -> s_Explicit[1] = q9 | q9 : int(1..2)]) - diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_1_1_2_2-solution000001.solution b/tests/exhaustive/basic/streamline01/expected/model_1_1_1_2_2-solution000001.solution deleted file mode 100644 index cd31e1020f..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_1_1_2_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(2 --> 1) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_1_1_2_2-solution000002.solution b/tests/exhaustive/basic/streamline01/expected/model_1_1_1_2_2-solution000002.solution deleted file mode 100644 index 2646544d52..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_1_1_2_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(2 --> 2) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_1_1_2_2-solution000003.solution b/tests/exhaustive/basic/streamline01/expected/model_1_1_1_2_2-solution000003.solution deleted file mode 100644 index 6da2c362aa..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_1_1_2_2-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 1) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_1_1_2_2-solution000004.solution b/tests/exhaustive/basic/streamline01/expected/model_1_1_1_2_2-solution000004.solution deleted file mode 100644 index 9fbfa45bad..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_1_1_2_2-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 2) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_1_1_2_2-solution000005.solution b/tests/exhaustive/basic/streamline01/expected/model_1_1_1_2_2-solution000005.solution deleted file mode 100644 index 77f032a426..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_1_1_2_2-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 1, 2 --> 1) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_1_1_2_2-solution000006.solution b/tests/exhaustive/basic/streamline01/expected/model_1_1_1_2_2-solution000006.solution deleted file mode 100644 index e62a462994..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_1_1_2_2-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 1, 2 --> 1) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_1_1_2_2-solution000007.solution b/tests/exhaustive/basic/streamline01/expected/model_1_1_1_2_2-solution000007.solution deleted file mode 100644 index 57c81f730c..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_1_1_2_2-solution000007.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 1, 2 --> 2) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_1_1_2_2-solution000008.solution b/tests/exhaustive/basic/streamline01/expected/model_1_1_1_2_2-solution000008.solution deleted file mode 100644 index d2200a27b7..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_1_1_2_2-solution000008.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 1, 2 --> 2) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_1_1_2_2-solution000009.solution b/tests/exhaustive/basic/streamline01/expected/model_1_1_1_2_2-solution000009.solution deleted file mode 100644 index 50857d4142..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_1_1_2_2-solution000009.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 2, 2 --> 1) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_1_1_2_2-solution000010.solution b/tests/exhaustive/basic/streamline01/expected/model_1_1_1_2_2-solution000010.solution deleted file mode 100644 index 03807b7fff..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_1_1_2_2-solution000010.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 2, 2 --> 1) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_1_1_2_2-solution000011.solution b/tests/exhaustive/basic/streamline01/expected/model_1_1_1_2_2-solution000011.solution deleted file mode 100644 index b33ee31e23..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_1_1_2_2-solution000011.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 2, 2 --> 2) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_1_1_2_2-solution000012.solution b/tests/exhaustive/basic/streamline01/expected/model_1_1_1_2_2-solution000012.solution deleted file mode 100644 index e00a3c532c..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_1_1_2_2-solution000012.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 2, 2 --> 2) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_1_1_2_2.eprime b/tests/exhaustive/basic/streamline01/expected/model_1_1_1_2_2.eprime deleted file mode 100644 index b202cb49d4..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_1_1_2_2.eprime +++ /dev/null @@ -1,33 +0,0 @@ -language ESSENCE' 1.0 - -find f_Function1DPartial_Flags: matrix indexed by [int(1..2)] of bool -find f_Function1DPartial_Values: matrix indexed by [int(1..2)] of int(1..2) -find s_Occurrence: matrix indexed by [int(1..2)] of bool -find s_Explicit: matrix indexed by [int(1)] of int(1..2) -find conjure_aux1: matrix indexed by [int(1..2)] of int(1..2) -find conjure_aux2: matrix indexed by [int(1..2)] of int(1..2) -branching on [f_Function1DPartial_Flags, f_Function1DPartial_Values, s_Explicit, s_Occurrence] -such that - and([s_Occurrence[q15] -> f_Function1DPartial_Flags[q15] | q15 : int(1..2)]), - and([and([s_Occurrence[q12] -> q12 >= conjure_aux1[i] | q12 : int(1..2)]) | i : int(1..2)]), - and([(sum([toInt(s_Occurrence[q12]) | q12 : int(1..2)]) > 0 -> - or([s_Occurrence[q12] /\ q12 = conjure_aux1[i] | q12 : int(1..2)])) - /\ (sum([toInt(s_Occurrence[q12]) | q12 : int(1..2)]) = 0 -> conjure_aux1[i] = 1) - | i : int(1..2)]), - and([and([s_Occurrence[q13] -> q13 >= conjure_aux2[i] | q13 : int(1..2)]) | i : int(1..2)]), - and([(sum([toInt(s_Occurrence[q13]) | q13 : int(1..2)]) > 0 -> - or([s_Occurrence[q13] /\ q13 = conjure_aux2[i] | q13 : int(1..2)])) - /\ (sum([toInt(s_Occurrence[q13]) | q13 : int(1..2)]) = 0 -> conjure_aux2[i] = 1) - | i : int(1..2)]), - and([s_Occurrence[i] /\ i != s_Explicit[1] -> - and([f_Function1DPartial_Values[i] > f_Function1DPartial_Values[conjure_aux1[i]] /\ - sum([toInt(s_Occurrence[q12]) | q12 : int(1..2)]) > 0, - f_Function1DPartial_Flags[i], - f_Function1DPartial_Flags[conjure_aux2[i]] /\ sum([toInt(s_Occurrence[q13]) | q13 : int(1..2)]) > 0; - int(1..3)]) - | i : int(1..2)]), - 1 = sum([toInt(s_Occurrence[q1]) | q1 : int(1..2)]), - and([f_Function1DPartial_Flags[q2] = false -> f_Function1DPartial_Values[q2] = 1 | q2 : int(1..2)]), - s_Occurrence[s_Explicit[1]], - and([s_Occurrence[q9] -> s_Explicit[1] = q9 | q9 : int(1..2)]) - diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_1_2_1_1-solution000001.solution b/tests/exhaustive/basic/streamline01/expected/model_1_1_2_1_1-solution000001.solution deleted file mode 100644 index cd31e1020f..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_1_2_1_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(2 --> 1) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_1_2_1_1-solution000002.solution b/tests/exhaustive/basic/streamline01/expected/model_1_1_2_1_1-solution000002.solution deleted file mode 100644 index 2646544d52..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_1_2_1_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(2 --> 2) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_1_2_1_1-solution000003.solution b/tests/exhaustive/basic/streamline01/expected/model_1_1_2_1_1-solution000003.solution deleted file mode 100644 index 6da2c362aa..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_1_2_1_1-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 1) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_1_2_1_1-solution000004.solution b/tests/exhaustive/basic/streamline01/expected/model_1_1_2_1_1-solution000004.solution deleted file mode 100644 index 9fbfa45bad..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_1_2_1_1-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 2) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_1_2_1_1-solution000005.solution b/tests/exhaustive/basic/streamline01/expected/model_1_1_2_1_1-solution000005.solution deleted file mode 100644 index 77f032a426..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_1_2_1_1-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 1, 2 --> 1) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_1_2_1_1-solution000006.solution b/tests/exhaustive/basic/streamline01/expected/model_1_1_2_1_1-solution000006.solution deleted file mode 100644 index e62a462994..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_1_2_1_1-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 1, 2 --> 1) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_1_2_1_1-solution000007.solution b/tests/exhaustive/basic/streamline01/expected/model_1_1_2_1_1-solution000007.solution deleted file mode 100644 index 57c81f730c..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_1_2_1_1-solution000007.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 1, 2 --> 2) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_1_2_1_1-solution000008.solution b/tests/exhaustive/basic/streamline01/expected/model_1_1_2_1_1-solution000008.solution deleted file mode 100644 index d2200a27b7..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_1_2_1_1-solution000008.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 1, 2 --> 2) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_1_2_1_1-solution000009.solution b/tests/exhaustive/basic/streamline01/expected/model_1_1_2_1_1-solution000009.solution deleted file mode 100644 index 50857d4142..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_1_2_1_1-solution000009.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 2, 2 --> 1) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_1_2_1_1-solution000010.solution b/tests/exhaustive/basic/streamline01/expected/model_1_1_2_1_1-solution000010.solution deleted file mode 100644 index 03807b7fff..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_1_2_1_1-solution000010.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 2, 2 --> 1) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_1_2_1_1-solution000011.solution b/tests/exhaustive/basic/streamline01/expected/model_1_1_2_1_1-solution000011.solution deleted file mode 100644 index b33ee31e23..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_1_2_1_1-solution000011.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 2, 2 --> 2) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_1_2_1_1-solution000012.solution b/tests/exhaustive/basic/streamline01/expected/model_1_1_2_1_1-solution000012.solution deleted file mode 100644 index e00a3c532c..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_1_2_1_1-solution000012.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 2, 2 --> 2) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_1_2_1_1.eprime b/tests/exhaustive/basic/streamline01/expected/model_1_1_2_1_1.eprime deleted file mode 100644 index 01733c9e45..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_1_2_1_1.eprime +++ /dev/null @@ -1,35 +0,0 @@ -language ESSENCE' 1.0 - -find f_Function1DPartial_Flags: matrix indexed by [int(1..2)] of bool -find f_Function1DPartial_Values: matrix indexed by [int(1..2)] of int(1..2) -find s_Occurrence: matrix indexed by [int(1..2)] of bool -find s_Explicit: matrix indexed by [int(1)] of int(1..2) -find conjure_aux1: matrix indexed by [int(1)] of int(1..2) -find conjure_aux2: matrix indexed by [int(1)] of int(1..2) -find conjure_aux3: int(1..2) -branching on [f_Function1DPartial_Flags, f_Function1DPartial_Values, s_Explicit, s_Occurrence] -such that - and([s_Occurrence[q17] -> f_Function1DPartial_Flags[q17] | q17 : int(1..2)]), - and([s_Occurrence[q13] -> q13 >= conjure_aux1[1] | q13 : int(1..2)]), - sum([toInt(s_Occurrence[q13]) | q13 : int(1..2)]) > 0 -> - or([s_Occurrence[q13] /\ q13 = conjure_aux1[1] | q13 : int(1..2)]), - sum([toInt(s_Occurrence[q13]) | q13 : int(1..2)]) = 0 -> conjure_aux1[1] = 1, - and([s_Occurrence[q14] -> q14 >= conjure_aux2[1] | q14 : int(1..2)]), - sum([toInt(s_Occurrence[q14]) | q14 : int(1..2)]) > 0 -> - or([s_Occurrence[q14] /\ q14 = conjure_aux2[1] | q14 : int(1..2)]), - sum([toInt(s_Occurrence[q14]) | q14 : int(1..2)]) = 0 -> conjure_aux2[1] = 1, - and([s_Occurrence[q15] -> q15 >= conjure_aux3 | q15 : int(1..2)]), - sum([toInt(s_Occurrence[q15]) | q15 : int(1..2)]) > 0 -> - or([s_Occurrence[q15] /\ q15 = conjure_aux3 | q15 : int(1..2)]), - sum([toInt(s_Occurrence[q15]) | q15 : int(1..2)]) = 0 -> conjure_aux3 = 1, - s_Explicit[1] != conjure_aux3 /\ sum([toInt(s_Occurrence[q15]) | q15 : int(1..2)]) > 0 -> - and([f_Function1DPartial_Values[s_Explicit[1]] > f_Function1DPartial_Values[conjure_aux1[1]] /\ - sum([toInt(s_Occurrence[q13]) | q13 : int(1..2)]) > 0, - f_Function1DPartial_Flags[s_Explicit[1]], - f_Function1DPartial_Flags[conjure_aux2[1]] /\ sum([toInt(s_Occurrence[q14]) | q14 : int(1..2)]) > 0; - int(1..3)]), - 1 = sum([toInt(s_Occurrence[q1]) | q1 : int(1..2)]), - and([f_Function1DPartial_Flags[q2] = false -> f_Function1DPartial_Values[q2] = 1 | q2 : int(1..2)]), - s_Occurrence[s_Explicit[1]], - and([s_Occurrence[q9] -> s_Explicit[1] = q9 | q9 : int(1..2)]) - diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_1_2_1_2-solution000001.solution b/tests/exhaustive/basic/streamline01/expected/model_1_1_2_1_2-solution000001.solution deleted file mode 100644 index cd31e1020f..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_1_2_1_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(2 --> 1) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_1_2_1_2-solution000002.solution b/tests/exhaustive/basic/streamline01/expected/model_1_1_2_1_2-solution000002.solution deleted file mode 100644 index 2646544d52..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_1_2_1_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(2 --> 2) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_1_2_1_2-solution000003.solution b/tests/exhaustive/basic/streamline01/expected/model_1_1_2_1_2-solution000003.solution deleted file mode 100644 index 6da2c362aa..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_1_2_1_2-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 1) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_1_2_1_2-solution000004.solution b/tests/exhaustive/basic/streamline01/expected/model_1_1_2_1_2-solution000004.solution deleted file mode 100644 index 9fbfa45bad..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_1_2_1_2-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 2) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_1_2_1_2-solution000005.solution b/tests/exhaustive/basic/streamline01/expected/model_1_1_2_1_2-solution000005.solution deleted file mode 100644 index 77f032a426..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_1_2_1_2-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 1, 2 --> 1) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_1_2_1_2-solution000006.solution b/tests/exhaustive/basic/streamline01/expected/model_1_1_2_1_2-solution000006.solution deleted file mode 100644 index e62a462994..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_1_2_1_2-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 1, 2 --> 1) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_1_2_1_2-solution000007.solution b/tests/exhaustive/basic/streamline01/expected/model_1_1_2_1_2-solution000007.solution deleted file mode 100644 index 57c81f730c..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_1_2_1_2-solution000007.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 1, 2 --> 2) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_1_2_1_2-solution000008.solution b/tests/exhaustive/basic/streamline01/expected/model_1_1_2_1_2-solution000008.solution deleted file mode 100644 index d2200a27b7..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_1_2_1_2-solution000008.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 1, 2 --> 2) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_1_2_1_2-solution000009.solution b/tests/exhaustive/basic/streamline01/expected/model_1_1_2_1_2-solution000009.solution deleted file mode 100644 index 50857d4142..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_1_2_1_2-solution000009.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 2, 2 --> 1) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_1_2_1_2-solution000010.solution b/tests/exhaustive/basic/streamline01/expected/model_1_1_2_1_2-solution000010.solution deleted file mode 100644 index 03807b7fff..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_1_2_1_2-solution000010.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 2, 2 --> 1) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_1_2_1_2-solution000011.solution b/tests/exhaustive/basic/streamline01/expected/model_1_1_2_1_2-solution000011.solution deleted file mode 100644 index b33ee31e23..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_1_2_1_2-solution000011.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 2, 2 --> 2) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_1_2_1_2-solution000012.solution b/tests/exhaustive/basic/streamline01/expected/model_1_1_2_1_2-solution000012.solution deleted file mode 100644 index e00a3c532c..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_1_2_1_2-solution000012.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 2, 2 --> 2) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_1_2_1_2.eprime b/tests/exhaustive/basic/streamline01/expected/model_1_1_2_1_2.eprime deleted file mode 100644 index 01733c9e45..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_1_2_1_2.eprime +++ /dev/null @@ -1,35 +0,0 @@ -language ESSENCE' 1.0 - -find f_Function1DPartial_Flags: matrix indexed by [int(1..2)] of bool -find f_Function1DPartial_Values: matrix indexed by [int(1..2)] of int(1..2) -find s_Occurrence: matrix indexed by [int(1..2)] of bool -find s_Explicit: matrix indexed by [int(1)] of int(1..2) -find conjure_aux1: matrix indexed by [int(1)] of int(1..2) -find conjure_aux2: matrix indexed by [int(1)] of int(1..2) -find conjure_aux3: int(1..2) -branching on [f_Function1DPartial_Flags, f_Function1DPartial_Values, s_Explicit, s_Occurrence] -such that - and([s_Occurrence[q17] -> f_Function1DPartial_Flags[q17] | q17 : int(1..2)]), - and([s_Occurrence[q13] -> q13 >= conjure_aux1[1] | q13 : int(1..2)]), - sum([toInt(s_Occurrence[q13]) | q13 : int(1..2)]) > 0 -> - or([s_Occurrence[q13] /\ q13 = conjure_aux1[1] | q13 : int(1..2)]), - sum([toInt(s_Occurrence[q13]) | q13 : int(1..2)]) = 0 -> conjure_aux1[1] = 1, - and([s_Occurrence[q14] -> q14 >= conjure_aux2[1] | q14 : int(1..2)]), - sum([toInt(s_Occurrence[q14]) | q14 : int(1..2)]) > 0 -> - or([s_Occurrence[q14] /\ q14 = conjure_aux2[1] | q14 : int(1..2)]), - sum([toInt(s_Occurrence[q14]) | q14 : int(1..2)]) = 0 -> conjure_aux2[1] = 1, - and([s_Occurrence[q15] -> q15 >= conjure_aux3 | q15 : int(1..2)]), - sum([toInt(s_Occurrence[q15]) | q15 : int(1..2)]) > 0 -> - or([s_Occurrence[q15] /\ q15 = conjure_aux3 | q15 : int(1..2)]), - sum([toInt(s_Occurrence[q15]) | q15 : int(1..2)]) = 0 -> conjure_aux3 = 1, - s_Explicit[1] != conjure_aux3 /\ sum([toInt(s_Occurrence[q15]) | q15 : int(1..2)]) > 0 -> - and([f_Function1DPartial_Values[s_Explicit[1]] > f_Function1DPartial_Values[conjure_aux1[1]] /\ - sum([toInt(s_Occurrence[q13]) | q13 : int(1..2)]) > 0, - f_Function1DPartial_Flags[s_Explicit[1]], - f_Function1DPartial_Flags[conjure_aux2[1]] /\ sum([toInt(s_Occurrence[q14]) | q14 : int(1..2)]) > 0; - int(1..3)]), - 1 = sum([toInt(s_Occurrence[q1]) | q1 : int(1..2)]), - and([f_Function1DPartial_Flags[q2] = false -> f_Function1DPartial_Values[q2] = 1 | q2 : int(1..2)]), - s_Occurrence[s_Explicit[1]], - and([s_Occurrence[q9] -> s_Explicit[1] = q9 | q9 : int(1..2)]) - diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_1_2_2_1-solution000001.solution b/tests/exhaustive/basic/streamline01/expected/model_1_1_2_2_1-solution000001.solution deleted file mode 100644 index cd31e1020f..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_1_2_2_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(2 --> 1) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_1_2_2_1-solution000002.solution b/tests/exhaustive/basic/streamline01/expected/model_1_1_2_2_1-solution000002.solution deleted file mode 100644 index 2646544d52..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_1_2_2_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(2 --> 2) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_1_2_2_1-solution000003.solution b/tests/exhaustive/basic/streamline01/expected/model_1_1_2_2_1-solution000003.solution deleted file mode 100644 index 6da2c362aa..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_1_2_2_1-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 1) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_1_2_2_1-solution000004.solution b/tests/exhaustive/basic/streamline01/expected/model_1_1_2_2_1-solution000004.solution deleted file mode 100644 index 9fbfa45bad..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_1_2_2_1-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 2) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_1_2_2_1-solution000005.solution b/tests/exhaustive/basic/streamline01/expected/model_1_1_2_2_1-solution000005.solution deleted file mode 100644 index 77f032a426..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_1_2_2_1-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 1, 2 --> 1) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_1_2_2_1-solution000006.solution b/tests/exhaustive/basic/streamline01/expected/model_1_1_2_2_1-solution000006.solution deleted file mode 100644 index e62a462994..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_1_2_2_1-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 1, 2 --> 1) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_1_2_2_1-solution000007.solution b/tests/exhaustive/basic/streamline01/expected/model_1_1_2_2_1-solution000007.solution deleted file mode 100644 index 57c81f730c..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_1_2_2_1-solution000007.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 1, 2 --> 2) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_1_2_2_1-solution000008.solution b/tests/exhaustive/basic/streamline01/expected/model_1_1_2_2_1-solution000008.solution deleted file mode 100644 index d2200a27b7..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_1_2_2_1-solution000008.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 1, 2 --> 2) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_1_2_2_1-solution000009.solution b/tests/exhaustive/basic/streamline01/expected/model_1_1_2_2_1-solution000009.solution deleted file mode 100644 index 50857d4142..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_1_2_2_1-solution000009.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 2, 2 --> 1) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_1_2_2_1-solution000010.solution b/tests/exhaustive/basic/streamline01/expected/model_1_1_2_2_1-solution000010.solution deleted file mode 100644 index 03807b7fff..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_1_2_2_1-solution000010.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 2, 2 --> 1) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_1_2_2_1-solution000011.solution b/tests/exhaustive/basic/streamline01/expected/model_1_1_2_2_1-solution000011.solution deleted file mode 100644 index b33ee31e23..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_1_2_2_1-solution000011.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 2, 2 --> 2) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_1_2_2_1-solution000012.solution b/tests/exhaustive/basic/streamline01/expected/model_1_1_2_2_1-solution000012.solution deleted file mode 100644 index e00a3c532c..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_1_2_2_1-solution000012.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 2, 2 --> 2) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_1_2_2_1.eprime b/tests/exhaustive/basic/streamline01/expected/model_1_1_2_2_1.eprime deleted file mode 100644 index 7c6499a431..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_1_2_2_1.eprime +++ /dev/null @@ -1,30 +0,0 @@ -language ESSENCE' 1.0 - -find f_Function1DPartial_Flags: matrix indexed by [int(1..2)] of bool -find f_Function1DPartial_Values: matrix indexed by [int(1..2)] of int(1..2) -find s_Occurrence: matrix indexed by [int(1..2)] of bool -find s_Explicit: matrix indexed by [int(1)] of int(1..2) -find conjure_aux1: matrix indexed by [int(1)] of int(1..2) -find conjure_aux2: matrix indexed by [int(1)] of int(1..2) -branching on [f_Function1DPartial_Flags, f_Function1DPartial_Values, s_Explicit, s_Occurrence] -such that - and([s_Occurrence[q16] -> f_Function1DPartial_Flags[q16] | q16 : int(1..2)]), - and([s_Occurrence[q13] -> q13 >= conjure_aux1[1] | q13 : int(1..2)]), - sum([toInt(s_Occurrence[q13]) | q13 : int(1..2)]) > 0 -> - or([s_Occurrence[q13] /\ q13 = conjure_aux1[1] | q13 : int(1..2)]), - sum([toInt(s_Occurrence[q13]) | q13 : int(1..2)]) = 0 -> conjure_aux1[1] = 1, - and([s_Occurrence[q14] -> q14 >= conjure_aux2[1] | q14 : int(1..2)]), - sum([toInt(s_Occurrence[q14]) | q14 : int(1..2)]) > 0 -> - or([s_Occurrence[q14] /\ q14 = conjure_aux2[1] | q14 : int(1..2)]), - sum([toInt(s_Occurrence[q14]) | q14 : int(1..2)]) = 0 -> conjure_aux2[1] = 1, - s_Explicit[1] != s_Explicit[1] -> - and([f_Function1DPartial_Values[s_Explicit[1]] > f_Function1DPartial_Values[conjure_aux1[1]] /\ - sum([toInt(s_Occurrence[q13]) | q13 : int(1..2)]) > 0, - f_Function1DPartial_Flags[s_Explicit[1]], - f_Function1DPartial_Flags[conjure_aux2[1]] /\ sum([toInt(s_Occurrence[q14]) | q14 : int(1..2)]) > 0; - int(1..3)]), - 1 = sum([toInt(s_Occurrence[q1]) | q1 : int(1..2)]), - and([f_Function1DPartial_Flags[q2] = false -> f_Function1DPartial_Values[q2] = 1 | q2 : int(1..2)]), - s_Occurrence[s_Explicit[1]], - and([s_Occurrence[q9] -> s_Explicit[1] = q9 | q9 : int(1..2)]) - diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_1_2_2_2-solution000001.solution b/tests/exhaustive/basic/streamline01/expected/model_1_1_2_2_2-solution000001.solution deleted file mode 100644 index cd31e1020f..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_1_2_2_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(2 --> 1) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_1_2_2_2-solution000002.solution b/tests/exhaustive/basic/streamline01/expected/model_1_1_2_2_2-solution000002.solution deleted file mode 100644 index 2646544d52..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_1_2_2_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(2 --> 2) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_1_2_2_2-solution000003.solution b/tests/exhaustive/basic/streamline01/expected/model_1_1_2_2_2-solution000003.solution deleted file mode 100644 index 6da2c362aa..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_1_2_2_2-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 1) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_1_2_2_2-solution000004.solution b/tests/exhaustive/basic/streamline01/expected/model_1_1_2_2_2-solution000004.solution deleted file mode 100644 index 9fbfa45bad..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_1_2_2_2-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 2) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_1_2_2_2-solution000005.solution b/tests/exhaustive/basic/streamline01/expected/model_1_1_2_2_2-solution000005.solution deleted file mode 100644 index 77f032a426..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_1_2_2_2-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 1, 2 --> 1) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_1_2_2_2-solution000006.solution b/tests/exhaustive/basic/streamline01/expected/model_1_1_2_2_2-solution000006.solution deleted file mode 100644 index e62a462994..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_1_2_2_2-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 1, 2 --> 1) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_1_2_2_2-solution000007.solution b/tests/exhaustive/basic/streamline01/expected/model_1_1_2_2_2-solution000007.solution deleted file mode 100644 index 57c81f730c..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_1_2_2_2-solution000007.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 1, 2 --> 2) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_1_2_2_2-solution000008.solution b/tests/exhaustive/basic/streamline01/expected/model_1_1_2_2_2-solution000008.solution deleted file mode 100644 index d2200a27b7..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_1_2_2_2-solution000008.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 1, 2 --> 2) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_1_2_2_2-solution000009.solution b/tests/exhaustive/basic/streamline01/expected/model_1_1_2_2_2-solution000009.solution deleted file mode 100644 index 50857d4142..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_1_2_2_2-solution000009.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 2, 2 --> 1) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_1_2_2_2-solution000010.solution b/tests/exhaustive/basic/streamline01/expected/model_1_1_2_2_2-solution000010.solution deleted file mode 100644 index 03807b7fff..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_1_2_2_2-solution000010.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 2, 2 --> 1) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_1_2_2_2-solution000011.solution b/tests/exhaustive/basic/streamline01/expected/model_1_1_2_2_2-solution000011.solution deleted file mode 100644 index b33ee31e23..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_1_2_2_2-solution000011.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 2, 2 --> 2) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_1_2_2_2-solution000012.solution b/tests/exhaustive/basic/streamline01/expected/model_1_1_2_2_2-solution000012.solution deleted file mode 100644 index e00a3c532c..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_1_2_2_2-solution000012.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 2, 2 --> 2) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_1_2_2_2.eprime b/tests/exhaustive/basic/streamline01/expected/model_1_1_2_2_2.eprime deleted file mode 100644 index 7c6499a431..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_1_2_2_2.eprime +++ /dev/null @@ -1,30 +0,0 @@ -language ESSENCE' 1.0 - -find f_Function1DPartial_Flags: matrix indexed by [int(1..2)] of bool -find f_Function1DPartial_Values: matrix indexed by [int(1..2)] of int(1..2) -find s_Occurrence: matrix indexed by [int(1..2)] of bool -find s_Explicit: matrix indexed by [int(1)] of int(1..2) -find conjure_aux1: matrix indexed by [int(1)] of int(1..2) -find conjure_aux2: matrix indexed by [int(1)] of int(1..2) -branching on [f_Function1DPartial_Flags, f_Function1DPartial_Values, s_Explicit, s_Occurrence] -such that - and([s_Occurrence[q16] -> f_Function1DPartial_Flags[q16] | q16 : int(1..2)]), - and([s_Occurrence[q13] -> q13 >= conjure_aux1[1] | q13 : int(1..2)]), - sum([toInt(s_Occurrence[q13]) | q13 : int(1..2)]) > 0 -> - or([s_Occurrence[q13] /\ q13 = conjure_aux1[1] | q13 : int(1..2)]), - sum([toInt(s_Occurrence[q13]) | q13 : int(1..2)]) = 0 -> conjure_aux1[1] = 1, - and([s_Occurrence[q14] -> q14 >= conjure_aux2[1] | q14 : int(1..2)]), - sum([toInt(s_Occurrence[q14]) | q14 : int(1..2)]) > 0 -> - or([s_Occurrence[q14] /\ q14 = conjure_aux2[1] | q14 : int(1..2)]), - sum([toInt(s_Occurrence[q14]) | q14 : int(1..2)]) = 0 -> conjure_aux2[1] = 1, - s_Explicit[1] != s_Explicit[1] -> - and([f_Function1DPartial_Values[s_Explicit[1]] > f_Function1DPartial_Values[conjure_aux1[1]] /\ - sum([toInt(s_Occurrence[q13]) | q13 : int(1..2)]) > 0, - f_Function1DPartial_Flags[s_Explicit[1]], - f_Function1DPartial_Flags[conjure_aux2[1]] /\ sum([toInt(s_Occurrence[q14]) | q14 : int(1..2)]) > 0; - int(1..3)]), - 1 = sum([toInt(s_Occurrence[q1]) | q1 : int(1..2)]), - and([f_Function1DPartial_Flags[q2] = false -> f_Function1DPartial_Values[q2] = 1 | q2 : int(1..2)]), - s_Occurrence[s_Explicit[1]], - and([s_Occurrence[q9] -> s_Explicit[1] = q9 | q9 : int(1..2)]) - diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_2_1_1_1-solution000001.solution b/tests/exhaustive/basic/streamline01/expected/model_1_2_1_1_1-solution000001.solution deleted file mode 100644 index cd31e1020f..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_2_1_1_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(2 --> 1) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_2_1_1_1-solution000002.solution b/tests/exhaustive/basic/streamline01/expected/model_1_2_1_1_1-solution000002.solution deleted file mode 100644 index 2646544d52..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_2_1_1_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(2 --> 2) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_2_1_1_1-solution000003.solution b/tests/exhaustive/basic/streamline01/expected/model_1_2_1_1_1-solution000003.solution deleted file mode 100644 index 6da2c362aa..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_2_1_1_1-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 1) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_2_1_1_1-solution000004.solution b/tests/exhaustive/basic/streamline01/expected/model_1_2_1_1_1-solution000004.solution deleted file mode 100644 index 9fbfa45bad..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_2_1_1_1-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 2) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_2_1_1_1-solution000005.solution b/tests/exhaustive/basic/streamline01/expected/model_1_2_1_1_1-solution000005.solution deleted file mode 100644 index 77f032a426..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_2_1_1_1-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 1, 2 --> 1) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_2_1_1_1-solution000006.solution b/tests/exhaustive/basic/streamline01/expected/model_1_2_1_1_1-solution000006.solution deleted file mode 100644 index e62a462994..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_2_1_1_1-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 1, 2 --> 1) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_2_1_1_1-solution000007.solution b/tests/exhaustive/basic/streamline01/expected/model_1_2_1_1_1-solution000007.solution deleted file mode 100644 index 57c81f730c..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_2_1_1_1-solution000007.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 1, 2 --> 2) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_2_1_1_1-solution000008.solution b/tests/exhaustive/basic/streamline01/expected/model_1_2_1_1_1-solution000008.solution deleted file mode 100644 index d2200a27b7..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_2_1_1_1-solution000008.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 1, 2 --> 2) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_2_1_1_1-solution000009.solution b/tests/exhaustive/basic/streamline01/expected/model_1_2_1_1_1-solution000009.solution deleted file mode 100644 index 50857d4142..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_2_1_1_1-solution000009.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 2, 2 --> 1) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_2_1_1_1-solution000010.solution b/tests/exhaustive/basic/streamline01/expected/model_1_2_1_1_1-solution000010.solution deleted file mode 100644 index 03807b7fff..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_2_1_1_1-solution000010.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 2, 2 --> 1) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_2_1_1_1-solution000011.solution b/tests/exhaustive/basic/streamline01/expected/model_1_2_1_1_1-solution000011.solution deleted file mode 100644 index b33ee31e23..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_2_1_1_1-solution000011.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 2, 2 --> 2) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_2_1_1_1-solution000012.solution b/tests/exhaustive/basic/streamline01/expected/model_1_2_1_1_1-solution000012.solution deleted file mode 100644 index e00a3c532c..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_2_1_1_1-solution000012.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 2, 2 --> 2) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_2_1_1_1.eprime b/tests/exhaustive/basic/streamline01/expected/model_1_2_1_1_1.eprime deleted file mode 100644 index a4be78689f..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_2_1_1_1.eprime +++ /dev/null @@ -1,24 +0,0 @@ -language ESSENCE' 1.0 - -find f_Function1DPartial_Flags: matrix indexed by [int(1..2)] of bool -find f_Function1DPartial_Values: matrix indexed by [int(1..2)] of int(1..2) -find s_Occurrence: matrix indexed by [int(1..2)] of bool -find s_Explicit: matrix indexed by [int(1)] of int(1..2) -find conjure_aux1: int(1..2) -branching on [f_Function1DPartial_Flags, f_Function1DPartial_Values, s_Explicit, s_Occurrence] -such that - and([s_Occurrence[q13] -> f_Function1DPartial_Flags[q13] | q13 : int(1..2)]), - and([s_Occurrence[q12] -> q12 >= conjure_aux1 | q12 : int(1..2)]), - sum([toInt(s_Occurrence[q12]) | q12 : int(1..2)]) > 0 -> - or([s_Occurrence[q12] /\ q12 = conjure_aux1 | q12 : int(1..2)]), - sum([toInt(s_Occurrence[q12]) | q12 : int(1..2)]) = 0 -> conjure_aux1 = 1, - and([s_Occurrence[i] /\ (i != conjure_aux1 /\ sum([toInt(s_Occurrence[q12]) | q12 : int(1..2)]) > 0) -> - and([f_Function1DPartial_Values[i] > f_Function1DPartial_Values[s_Explicit[1]], f_Function1DPartial_Flags[i], - f_Function1DPartial_Flags[s_Explicit[1]]; - int(1..3)]) - | i : int(1..2)]), - 1 = sum([toInt(s_Occurrence[q1]) | q1 : int(1..2)]), - and([f_Function1DPartial_Flags[q2] = false -> f_Function1DPartial_Values[q2] = 1 | q2 : int(1..2)]), - s_Occurrence[s_Explicit[1]], - and([s_Occurrence[q9] -> s_Explicit[1] = q9 | q9 : int(1..2)]) - diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_2_1_1_2-solution000001.solution b/tests/exhaustive/basic/streamline01/expected/model_1_2_1_1_2-solution000001.solution deleted file mode 100644 index cd31e1020f..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_2_1_1_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(2 --> 1) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_2_1_1_2-solution000002.solution b/tests/exhaustive/basic/streamline01/expected/model_1_2_1_1_2-solution000002.solution deleted file mode 100644 index 2646544d52..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_2_1_1_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(2 --> 2) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_2_1_1_2-solution000003.solution b/tests/exhaustive/basic/streamline01/expected/model_1_2_1_1_2-solution000003.solution deleted file mode 100644 index 6da2c362aa..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_2_1_1_2-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 1) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_2_1_1_2-solution000004.solution b/tests/exhaustive/basic/streamline01/expected/model_1_2_1_1_2-solution000004.solution deleted file mode 100644 index 9fbfa45bad..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_2_1_1_2-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 2) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_2_1_1_2-solution000005.solution b/tests/exhaustive/basic/streamline01/expected/model_1_2_1_1_2-solution000005.solution deleted file mode 100644 index 77f032a426..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_2_1_1_2-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 1, 2 --> 1) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_2_1_1_2-solution000006.solution b/tests/exhaustive/basic/streamline01/expected/model_1_2_1_1_2-solution000006.solution deleted file mode 100644 index e62a462994..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_2_1_1_2-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 1, 2 --> 1) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_2_1_1_2-solution000007.solution b/tests/exhaustive/basic/streamline01/expected/model_1_2_1_1_2-solution000007.solution deleted file mode 100644 index 57c81f730c..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_2_1_1_2-solution000007.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 1, 2 --> 2) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_2_1_1_2-solution000008.solution b/tests/exhaustive/basic/streamline01/expected/model_1_2_1_1_2-solution000008.solution deleted file mode 100644 index d2200a27b7..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_2_1_1_2-solution000008.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 1, 2 --> 2) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_2_1_1_2-solution000009.solution b/tests/exhaustive/basic/streamline01/expected/model_1_2_1_1_2-solution000009.solution deleted file mode 100644 index 50857d4142..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_2_1_1_2-solution000009.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 2, 2 --> 1) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_2_1_1_2-solution000010.solution b/tests/exhaustive/basic/streamline01/expected/model_1_2_1_1_2-solution000010.solution deleted file mode 100644 index 03807b7fff..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_2_1_1_2-solution000010.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 2, 2 --> 1) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_2_1_1_2-solution000011.solution b/tests/exhaustive/basic/streamline01/expected/model_1_2_1_1_2-solution000011.solution deleted file mode 100644 index b33ee31e23..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_2_1_1_2-solution000011.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 2, 2 --> 2) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_2_1_1_2-solution000012.solution b/tests/exhaustive/basic/streamline01/expected/model_1_2_1_1_2-solution000012.solution deleted file mode 100644 index e00a3c532c..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_2_1_1_2-solution000012.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 2, 2 --> 2) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_2_1_1_2.eprime b/tests/exhaustive/basic/streamline01/expected/model_1_2_1_1_2.eprime deleted file mode 100644 index a4be78689f..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_2_1_1_2.eprime +++ /dev/null @@ -1,24 +0,0 @@ -language ESSENCE' 1.0 - -find f_Function1DPartial_Flags: matrix indexed by [int(1..2)] of bool -find f_Function1DPartial_Values: matrix indexed by [int(1..2)] of int(1..2) -find s_Occurrence: matrix indexed by [int(1..2)] of bool -find s_Explicit: matrix indexed by [int(1)] of int(1..2) -find conjure_aux1: int(1..2) -branching on [f_Function1DPartial_Flags, f_Function1DPartial_Values, s_Explicit, s_Occurrence] -such that - and([s_Occurrence[q13] -> f_Function1DPartial_Flags[q13] | q13 : int(1..2)]), - and([s_Occurrence[q12] -> q12 >= conjure_aux1 | q12 : int(1..2)]), - sum([toInt(s_Occurrence[q12]) | q12 : int(1..2)]) > 0 -> - or([s_Occurrence[q12] /\ q12 = conjure_aux1 | q12 : int(1..2)]), - sum([toInt(s_Occurrence[q12]) | q12 : int(1..2)]) = 0 -> conjure_aux1 = 1, - and([s_Occurrence[i] /\ (i != conjure_aux1 /\ sum([toInt(s_Occurrence[q12]) | q12 : int(1..2)]) > 0) -> - and([f_Function1DPartial_Values[i] > f_Function1DPartial_Values[s_Explicit[1]], f_Function1DPartial_Flags[i], - f_Function1DPartial_Flags[s_Explicit[1]]; - int(1..3)]) - | i : int(1..2)]), - 1 = sum([toInt(s_Occurrence[q1]) | q1 : int(1..2)]), - and([f_Function1DPartial_Flags[q2] = false -> f_Function1DPartial_Values[q2] = 1 | q2 : int(1..2)]), - s_Occurrence[s_Explicit[1]], - and([s_Occurrence[q9] -> s_Explicit[1] = q9 | q9 : int(1..2)]) - diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_2_1_2_1-solution000001.solution b/tests/exhaustive/basic/streamline01/expected/model_1_2_1_2_1-solution000001.solution deleted file mode 100644 index cd31e1020f..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_2_1_2_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(2 --> 1) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_2_1_2_1-solution000002.solution b/tests/exhaustive/basic/streamline01/expected/model_1_2_1_2_1-solution000002.solution deleted file mode 100644 index 2646544d52..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_2_1_2_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(2 --> 2) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_2_1_2_1-solution000003.solution b/tests/exhaustive/basic/streamline01/expected/model_1_2_1_2_1-solution000003.solution deleted file mode 100644 index 6da2c362aa..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_2_1_2_1-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 1) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_2_1_2_1-solution000004.solution b/tests/exhaustive/basic/streamline01/expected/model_1_2_1_2_1-solution000004.solution deleted file mode 100644 index 9fbfa45bad..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_2_1_2_1-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 2) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_2_1_2_1-solution000005.solution b/tests/exhaustive/basic/streamline01/expected/model_1_2_1_2_1-solution000005.solution deleted file mode 100644 index 77f032a426..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_2_1_2_1-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 1, 2 --> 1) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_2_1_2_1-solution000006.solution b/tests/exhaustive/basic/streamline01/expected/model_1_2_1_2_1-solution000006.solution deleted file mode 100644 index e62a462994..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_2_1_2_1-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 1, 2 --> 1) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_2_1_2_1-solution000007.solution b/tests/exhaustive/basic/streamline01/expected/model_1_2_1_2_1-solution000007.solution deleted file mode 100644 index 57c81f730c..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_2_1_2_1-solution000007.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 1, 2 --> 2) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_2_1_2_1-solution000008.solution b/tests/exhaustive/basic/streamline01/expected/model_1_2_1_2_1-solution000008.solution deleted file mode 100644 index d2200a27b7..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_2_1_2_1-solution000008.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 1, 2 --> 2) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_2_1_2_1-solution000009.solution b/tests/exhaustive/basic/streamline01/expected/model_1_2_1_2_1-solution000009.solution deleted file mode 100644 index 50857d4142..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_2_1_2_1-solution000009.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 2, 2 --> 1) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_2_1_2_1-solution000010.solution b/tests/exhaustive/basic/streamline01/expected/model_1_2_1_2_1-solution000010.solution deleted file mode 100644 index 03807b7fff..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_2_1_2_1-solution000010.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 2, 2 --> 1) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_2_1_2_1-solution000011.solution b/tests/exhaustive/basic/streamline01/expected/model_1_2_1_2_1-solution000011.solution deleted file mode 100644 index b33ee31e23..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_2_1_2_1-solution000011.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 2, 2 --> 2) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_2_1_2_1-solution000012.solution b/tests/exhaustive/basic/streamline01/expected/model_1_2_1_2_1-solution000012.solution deleted file mode 100644 index e00a3c532c..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_2_1_2_1-solution000012.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 2, 2 --> 2) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_2_1_2_1.eprime b/tests/exhaustive/basic/streamline01/expected/model_1_2_1_2_1.eprime deleted file mode 100644 index bfda3f09a1..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_2_1_2_1.eprime +++ /dev/null @@ -1,19 +0,0 @@ -language ESSENCE' 1.0 - -find f_Function1DPartial_Flags: matrix indexed by [int(1..2)] of bool -find f_Function1DPartial_Values: matrix indexed by [int(1..2)] of int(1..2) -find s_Occurrence: matrix indexed by [int(1..2)] of bool -find s_Explicit: matrix indexed by [int(1)] of int(1..2) -branching on [f_Function1DPartial_Flags, f_Function1DPartial_Values, s_Explicit, s_Occurrence] -such that - and([s_Occurrence[q12] -> f_Function1DPartial_Flags[q12] | q12 : int(1..2)]), - and([s_Occurrence[i] /\ i != s_Explicit[1] -> - and([f_Function1DPartial_Values[i] > f_Function1DPartial_Values[s_Explicit[1]], f_Function1DPartial_Flags[i], - f_Function1DPartial_Flags[s_Explicit[1]]; - int(1..3)]) - | i : int(1..2)]), - 1 = sum([toInt(s_Occurrence[q1]) | q1 : int(1..2)]), - and([f_Function1DPartial_Flags[q2] = false -> f_Function1DPartial_Values[q2] = 1 | q2 : int(1..2)]), - s_Occurrence[s_Explicit[1]], - and([s_Occurrence[q9] -> s_Explicit[1] = q9 | q9 : int(1..2)]) - diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_2_1_2_2-solution000001.solution b/tests/exhaustive/basic/streamline01/expected/model_1_2_1_2_2-solution000001.solution deleted file mode 100644 index cd31e1020f..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_2_1_2_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(2 --> 1) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_2_1_2_2-solution000002.solution b/tests/exhaustive/basic/streamline01/expected/model_1_2_1_2_2-solution000002.solution deleted file mode 100644 index 2646544d52..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_2_1_2_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(2 --> 2) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_2_1_2_2-solution000003.solution b/tests/exhaustive/basic/streamline01/expected/model_1_2_1_2_2-solution000003.solution deleted file mode 100644 index 6da2c362aa..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_2_1_2_2-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 1) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_2_1_2_2-solution000004.solution b/tests/exhaustive/basic/streamline01/expected/model_1_2_1_2_2-solution000004.solution deleted file mode 100644 index 9fbfa45bad..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_2_1_2_2-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 2) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_2_1_2_2-solution000005.solution b/tests/exhaustive/basic/streamline01/expected/model_1_2_1_2_2-solution000005.solution deleted file mode 100644 index 77f032a426..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_2_1_2_2-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 1, 2 --> 1) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_2_1_2_2-solution000006.solution b/tests/exhaustive/basic/streamline01/expected/model_1_2_1_2_2-solution000006.solution deleted file mode 100644 index e62a462994..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_2_1_2_2-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 1, 2 --> 1) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_2_1_2_2-solution000007.solution b/tests/exhaustive/basic/streamline01/expected/model_1_2_1_2_2-solution000007.solution deleted file mode 100644 index 57c81f730c..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_2_1_2_2-solution000007.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 1, 2 --> 2) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_2_1_2_2-solution000008.solution b/tests/exhaustive/basic/streamline01/expected/model_1_2_1_2_2-solution000008.solution deleted file mode 100644 index d2200a27b7..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_2_1_2_2-solution000008.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 1, 2 --> 2) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_2_1_2_2-solution000009.solution b/tests/exhaustive/basic/streamline01/expected/model_1_2_1_2_2-solution000009.solution deleted file mode 100644 index 50857d4142..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_2_1_2_2-solution000009.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 2, 2 --> 1) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_2_1_2_2-solution000010.solution b/tests/exhaustive/basic/streamline01/expected/model_1_2_1_2_2-solution000010.solution deleted file mode 100644 index 03807b7fff..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_2_1_2_2-solution000010.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 2, 2 --> 1) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_2_1_2_2-solution000011.solution b/tests/exhaustive/basic/streamline01/expected/model_1_2_1_2_2-solution000011.solution deleted file mode 100644 index b33ee31e23..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_2_1_2_2-solution000011.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 2, 2 --> 2) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_2_1_2_2-solution000012.solution b/tests/exhaustive/basic/streamline01/expected/model_1_2_1_2_2-solution000012.solution deleted file mode 100644 index e00a3c532c..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_2_1_2_2-solution000012.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 2, 2 --> 2) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_2_1_2_2.eprime b/tests/exhaustive/basic/streamline01/expected/model_1_2_1_2_2.eprime deleted file mode 100644 index bfda3f09a1..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_2_1_2_2.eprime +++ /dev/null @@ -1,19 +0,0 @@ -language ESSENCE' 1.0 - -find f_Function1DPartial_Flags: matrix indexed by [int(1..2)] of bool -find f_Function1DPartial_Values: matrix indexed by [int(1..2)] of int(1..2) -find s_Occurrence: matrix indexed by [int(1..2)] of bool -find s_Explicit: matrix indexed by [int(1)] of int(1..2) -branching on [f_Function1DPartial_Flags, f_Function1DPartial_Values, s_Explicit, s_Occurrence] -such that - and([s_Occurrence[q12] -> f_Function1DPartial_Flags[q12] | q12 : int(1..2)]), - and([s_Occurrence[i] /\ i != s_Explicit[1] -> - and([f_Function1DPartial_Values[i] > f_Function1DPartial_Values[s_Explicit[1]], f_Function1DPartial_Flags[i], - f_Function1DPartial_Flags[s_Explicit[1]]; - int(1..3)]) - | i : int(1..2)]), - 1 = sum([toInt(s_Occurrence[q1]) | q1 : int(1..2)]), - and([f_Function1DPartial_Flags[q2] = false -> f_Function1DPartial_Values[q2] = 1 | q2 : int(1..2)]), - s_Occurrence[s_Explicit[1]], - and([s_Occurrence[q9] -> s_Explicit[1] = q9 | q9 : int(1..2)]) - diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_2_2_1_1-solution000001.solution b/tests/exhaustive/basic/streamline01/expected/model_1_2_2_1_1-solution000001.solution deleted file mode 100644 index cd31e1020f..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_2_2_1_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(2 --> 1) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_2_2_1_1-solution000002.solution b/tests/exhaustive/basic/streamline01/expected/model_1_2_2_1_1-solution000002.solution deleted file mode 100644 index 2646544d52..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_2_2_1_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(2 --> 2) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_2_2_1_1-solution000003.solution b/tests/exhaustive/basic/streamline01/expected/model_1_2_2_1_1-solution000003.solution deleted file mode 100644 index 6da2c362aa..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_2_2_1_1-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 1) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_2_2_1_1-solution000004.solution b/tests/exhaustive/basic/streamline01/expected/model_1_2_2_1_1-solution000004.solution deleted file mode 100644 index 9fbfa45bad..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_2_2_1_1-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 2) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_2_2_1_1-solution000005.solution b/tests/exhaustive/basic/streamline01/expected/model_1_2_2_1_1-solution000005.solution deleted file mode 100644 index 77f032a426..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_2_2_1_1-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 1, 2 --> 1) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_2_2_1_1-solution000006.solution b/tests/exhaustive/basic/streamline01/expected/model_1_2_2_1_1-solution000006.solution deleted file mode 100644 index e62a462994..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_2_2_1_1-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 1, 2 --> 1) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_2_2_1_1-solution000007.solution b/tests/exhaustive/basic/streamline01/expected/model_1_2_2_1_1-solution000007.solution deleted file mode 100644 index 57c81f730c..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_2_2_1_1-solution000007.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 1, 2 --> 2) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_2_2_1_1-solution000008.solution b/tests/exhaustive/basic/streamline01/expected/model_1_2_2_1_1-solution000008.solution deleted file mode 100644 index d2200a27b7..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_2_2_1_1-solution000008.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 1, 2 --> 2) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_2_2_1_1-solution000009.solution b/tests/exhaustive/basic/streamline01/expected/model_1_2_2_1_1-solution000009.solution deleted file mode 100644 index 50857d4142..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_2_2_1_1-solution000009.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 2, 2 --> 1) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_2_2_1_1-solution000010.solution b/tests/exhaustive/basic/streamline01/expected/model_1_2_2_1_1-solution000010.solution deleted file mode 100644 index 03807b7fff..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_2_2_1_1-solution000010.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 2, 2 --> 1) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_2_2_1_1-solution000011.solution b/tests/exhaustive/basic/streamline01/expected/model_1_2_2_1_1-solution000011.solution deleted file mode 100644 index b33ee31e23..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_2_2_1_1-solution000011.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 2, 2 --> 2) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_2_2_1_1-solution000012.solution b/tests/exhaustive/basic/streamline01/expected/model_1_2_2_1_1-solution000012.solution deleted file mode 100644 index e00a3c532c..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_2_2_1_1-solution000012.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 2, 2 --> 2) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_2_2_1_1.eprime b/tests/exhaustive/basic/streamline01/expected/model_1_2_2_1_1.eprime deleted file mode 100644 index 709b169282..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_2_2_1_1.eprime +++ /dev/null @@ -1,23 +0,0 @@ -language ESSENCE' 1.0 - -find f_Function1DPartial_Flags: matrix indexed by [int(1..2)] of bool -find f_Function1DPartial_Values: matrix indexed by [int(1..2)] of int(1..2) -find s_Occurrence: matrix indexed by [int(1..2)] of bool -find s_Explicit: matrix indexed by [int(1)] of int(1..2) -find conjure_aux1: int(1..2) -branching on [f_Function1DPartial_Flags, f_Function1DPartial_Values, s_Explicit, s_Occurrence] -such that - and([s_Occurrence[q14] -> f_Function1DPartial_Flags[q14] | q14 : int(1..2)]), - and([s_Occurrence[q13] -> q13 >= conjure_aux1 | q13 : int(1..2)]), - sum([toInt(s_Occurrence[q13]) | q13 : int(1..2)]) > 0 -> - or([s_Occurrence[q13] /\ q13 = conjure_aux1 | q13 : int(1..2)]), - sum([toInt(s_Occurrence[q13]) | q13 : int(1..2)]) = 0 -> conjure_aux1 = 1, - s_Explicit[1] != conjure_aux1 /\ sum([toInt(s_Occurrence[q13]) | q13 : int(1..2)]) > 0 -> - and([f_Function1DPartial_Values[s_Explicit[1]] > f_Function1DPartial_Values[s_Explicit[1]], - f_Function1DPartial_Flags[s_Explicit[1]], f_Function1DPartial_Flags[s_Explicit[1]]; - int(1..3)]), - 1 = sum([toInt(s_Occurrence[q1]) | q1 : int(1..2)]), - and([f_Function1DPartial_Flags[q2] = false -> f_Function1DPartial_Values[q2] = 1 | q2 : int(1..2)]), - s_Occurrence[s_Explicit[1]], - and([s_Occurrence[q9] -> s_Explicit[1] = q9 | q9 : int(1..2)]) - diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_2_2_1_2-solution000001.solution b/tests/exhaustive/basic/streamline01/expected/model_1_2_2_1_2-solution000001.solution deleted file mode 100644 index cd31e1020f..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_2_2_1_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(2 --> 1) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_2_2_1_2-solution000002.solution b/tests/exhaustive/basic/streamline01/expected/model_1_2_2_1_2-solution000002.solution deleted file mode 100644 index 2646544d52..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_2_2_1_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(2 --> 2) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_2_2_1_2-solution000003.solution b/tests/exhaustive/basic/streamline01/expected/model_1_2_2_1_2-solution000003.solution deleted file mode 100644 index 6da2c362aa..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_2_2_1_2-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 1) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_2_2_1_2-solution000004.solution b/tests/exhaustive/basic/streamline01/expected/model_1_2_2_1_2-solution000004.solution deleted file mode 100644 index 9fbfa45bad..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_2_2_1_2-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 2) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_2_2_1_2-solution000005.solution b/tests/exhaustive/basic/streamline01/expected/model_1_2_2_1_2-solution000005.solution deleted file mode 100644 index 77f032a426..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_2_2_1_2-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 1, 2 --> 1) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_2_2_1_2-solution000006.solution b/tests/exhaustive/basic/streamline01/expected/model_1_2_2_1_2-solution000006.solution deleted file mode 100644 index e62a462994..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_2_2_1_2-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 1, 2 --> 1) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_2_2_1_2-solution000007.solution b/tests/exhaustive/basic/streamline01/expected/model_1_2_2_1_2-solution000007.solution deleted file mode 100644 index 57c81f730c..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_2_2_1_2-solution000007.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 1, 2 --> 2) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_2_2_1_2-solution000008.solution b/tests/exhaustive/basic/streamline01/expected/model_1_2_2_1_2-solution000008.solution deleted file mode 100644 index d2200a27b7..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_2_2_1_2-solution000008.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 1, 2 --> 2) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_2_2_1_2-solution000009.solution b/tests/exhaustive/basic/streamline01/expected/model_1_2_2_1_2-solution000009.solution deleted file mode 100644 index 50857d4142..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_2_2_1_2-solution000009.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 2, 2 --> 1) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_2_2_1_2-solution000010.solution b/tests/exhaustive/basic/streamline01/expected/model_1_2_2_1_2-solution000010.solution deleted file mode 100644 index 03807b7fff..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_2_2_1_2-solution000010.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 2, 2 --> 1) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_2_2_1_2-solution000011.solution b/tests/exhaustive/basic/streamline01/expected/model_1_2_2_1_2-solution000011.solution deleted file mode 100644 index b33ee31e23..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_2_2_1_2-solution000011.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 2, 2 --> 2) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_2_2_1_2-solution000012.solution b/tests/exhaustive/basic/streamline01/expected/model_1_2_2_1_2-solution000012.solution deleted file mode 100644 index e00a3c532c..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_2_2_1_2-solution000012.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 2, 2 --> 2) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_2_2_1_2.eprime b/tests/exhaustive/basic/streamline01/expected/model_1_2_2_1_2.eprime deleted file mode 100644 index 709b169282..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_2_2_1_2.eprime +++ /dev/null @@ -1,23 +0,0 @@ -language ESSENCE' 1.0 - -find f_Function1DPartial_Flags: matrix indexed by [int(1..2)] of bool -find f_Function1DPartial_Values: matrix indexed by [int(1..2)] of int(1..2) -find s_Occurrence: matrix indexed by [int(1..2)] of bool -find s_Explicit: matrix indexed by [int(1)] of int(1..2) -find conjure_aux1: int(1..2) -branching on [f_Function1DPartial_Flags, f_Function1DPartial_Values, s_Explicit, s_Occurrence] -such that - and([s_Occurrence[q14] -> f_Function1DPartial_Flags[q14] | q14 : int(1..2)]), - and([s_Occurrence[q13] -> q13 >= conjure_aux1 | q13 : int(1..2)]), - sum([toInt(s_Occurrence[q13]) | q13 : int(1..2)]) > 0 -> - or([s_Occurrence[q13] /\ q13 = conjure_aux1 | q13 : int(1..2)]), - sum([toInt(s_Occurrence[q13]) | q13 : int(1..2)]) = 0 -> conjure_aux1 = 1, - s_Explicit[1] != conjure_aux1 /\ sum([toInt(s_Occurrence[q13]) | q13 : int(1..2)]) > 0 -> - and([f_Function1DPartial_Values[s_Explicit[1]] > f_Function1DPartial_Values[s_Explicit[1]], - f_Function1DPartial_Flags[s_Explicit[1]], f_Function1DPartial_Flags[s_Explicit[1]]; - int(1..3)]), - 1 = sum([toInt(s_Occurrence[q1]) | q1 : int(1..2)]), - and([f_Function1DPartial_Flags[q2] = false -> f_Function1DPartial_Values[q2] = 1 | q2 : int(1..2)]), - s_Occurrence[s_Explicit[1]], - and([s_Occurrence[q9] -> s_Explicit[1] = q9 | q9 : int(1..2)]) - diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_2_2_2_1-solution000001.solution b/tests/exhaustive/basic/streamline01/expected/model_1_2_2_2_1-solution000001.solution deleted file mode 100644 index cd31e1020f..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_2_2_2_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(2 --> 1) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_2_2_2_1-solution000002.solution b/tests/exhaustive/basic/streamline01/expected/model_1_2_2_2_1-solution000002.solution deleted file mode 100644 index 2646544d52..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_2_2_2_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(2 --> 2) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_2_2_2_1-solution000003.solution b/tests/exhaustive/basic/streamline01/expected/model_1_2_2_2_1-solution000003.solution deleted file mode 100644 index 6da2c362aa..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_2_2_2_1-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 1) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_2_2_2_1-solution000004.solution b/tests/exhaustive/basic/streamline01/expected/model_1_2_2_2_1-solution000004.solution deleted file mode 100644 index 9fbfa45bad..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_2_2_2_1-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 2) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_2_2_2_1-solution000005.solution b/tests/exhaustive/basic/streamline01/expected/model_1_2_2_2_1-solution000005.solution deleted file mode 100644 index 77f032a426..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_2_2_2_1-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 1, 2 --> 1) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_2_2_2_1-solution000006.solution b/tests/exhaustive/basic/streamline01/expected/model_1_2_2_2_1-solution000006.solution deleted file mode 100644 index e62a462994..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_2_2_2_1-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 1, 2 --> 1) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_2_2_2_1-solution000007.solution b/tests/exhaustive/basic/streamline01/expected/model_1_2_2_2_1-solution000007.solution deleted file mode 100644 index 57c81f730c..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_2_2_2_1-solution000007.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 1, 2 --> 2) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_2_2_2_1-solution000008.solution b/tests/exhaustive/basic/streamline01/expected/model_1_2_2_2_1-solution000008.solution deleted file mode 100644 index d2200a27b7..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_2_2_2_1-solution000008.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 1, 2 --> 2) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_2_2_2_1-solution000009.solution b/tests/exhaustive/basic/streamline01/expected/model_1_2_2_2_1-solution000009.solution deleted file mode 100644 index 50857d4142..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_2_2_2_1-solution000009.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 2, 2 --> 1) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_2_2_2_1-solution000010.solution b/tests/exhaustive/basic/streamline01/expected/model_1_2_2_2_1-solution000010.solution deleted file mode 100644 index 03807b7fff..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_2_2_2_1-solution000010.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 2, 2 --> 1) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_2_2_2_1-solution000011.solution b/tests/exhaustive/basic/streamline01/expected/model_1_2_2_2_1-solution000011.solution deleted file mode 100644 index b33ee31e23..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_2_2_2_1-solution000011.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 2, 2 --> 2) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_2_2_2_1-solution000012.solution b/tests/exhaustive/basic/streamline01/expected/model_1_2_2_2_1-solution000012.solution deleted file mode 100644 index e00a3c532c..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_2_2_2_1-solution000012.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 2, 2 --> 2) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_2_2_2_1.eprime b/tests/exhaustive/basic/streamline01/expected/model_1_2_2_2_1.eprime deleted file mode 100644 index 7c7c5e7db5..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_2_2_2_1.eprime +++ /dev/null @@ -1,18 +0,0 @@ -language ESSENCE' 1.0 - -find f_Function1DPartial_Flags: matrix indexed by [int(1..2)] of bool -find f_Function1DPartial_Values: matrix indexed by [int(1..2)] of int(1..2) -find s_Occurrence: matrix indexed by [int(1..2)] of bool -find s_Explicit: matrix indexed by [int(1)] of int(1..2) -branching on [f_Function1DPartial_Flags, f_Function1DPartial_Values, s_Explicit, s_Occurrence] -such that - and([s_Occurrence[q13] -> f_Function1DPartial_Flags[q13] | q13 : int(1..2)]), - s_Explicit[1] != s_Explicit[1] -> - and([f_Function1DPartial_Values[s_Explicit[1]] > f_Function1DPartial_Values[s_Explicit[1]], - f_Function1DPartial_Flags[s_Explicit[1]], f_Function1DPartial_Flags[s_Explicit[1]]; - int(1..3)]), - 1 = sum([toInt(s_Occurrence[q1]) | q1 : int(1..2)]), - and([f_Function1DPartial_Flags[q2] = false -> f_Function1DPartial_Values[q2] = 1 | q2 : int(1..2)]), - s_Occurrence[s_Explicit[1]], - and([s_Occurrence[q9] -> s_Explicit[1] = q9 | q9 : int(1..2)]) - diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_2_2_2_2-solution000001.solution b/tests/exhaustive/basic/streamline01/expected/model_1_2_2_2_2-solution000001.solution deleted file mode 100644 index cd31e1020f..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_2_2_2_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(2 --> 1) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_2_2_2_2-solution000002.solution b/tests/exhaustive/basic/streamline01/expected/model_1_2_2_2_2-solution000002.solution deleted file mode 100644 index 2646544d52..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_2_2_2_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(2 --> 2) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_2_2_2_2-solution000003.solution b/tests/exhaustive/basic/streamline01/expected/model_1_2_2_2_2-solution000003.solution deleted file mode 100644 index 6da2c362aa..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_2_2_2_2-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 1) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_2_2_2_2-solution000004.solution b/tests/exhaustive/basic/streamline01/expected/model_1_2_2_2_2-solution000004.solution deleted file mode 100644 index 9fbfa45bad..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_2_2_2_2-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 2) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_2_2_2_2-solution000005.solution b/tests/exhaustive/basic/streamline01/expected/model_1_2_2_2_2-solution000005.solution deleted file mode 100644 index 77f032a426..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_2_2_2_2-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 1, 2 --> 1) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_2_2_2_2-solution000006.solution b/tests/exhaustive/basic/streamline01/expected/model_1_2_2_2_2-solution000006.solution deleted file mode 100644 index e62a462994..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_2_2_2_2-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 1, 2 --> 1) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_2_2_2_2-solution000007.solution b/tests/exhaustive/basic/streamline01/expected/model_1_2_2_2_2-solution000007.solution deleted file mode 100644 index 57c81f730c..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_2_2_2_2-solution000007.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 1, 2 --> 2) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_2_2_2_2-solution000008.solution b/tests/exhaustive/basic/streamline01/expected/model_1_2_2_2_2-solution000008.solution deleted file mode 100644 index d2200a27b7..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_2_2_2_2-solution000008.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 1, 2 --> 2) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_2_2_2_2-solution000009.solution b/tests/exhaustive/basic/streamline01/expected/model_1_2_2_2_2-solution000009.solution deleted file mode 100644 index 50857d4142..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_2_2_2_2-solution000009.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 2, 2 --> 1) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_2_2_2_2-solution000010.solution b/tests/exhaustive/basic/streamline01/expected/model_1_2_2_2_2-solution000010.solution deleted file mode 100644 index 03807b7fff..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_2_2_2_2-solution000010.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 2, 2 --> 1) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_2_2_2_2-solution000011.solution b/tests/exhaustive/basic/streamline01/expected/model_1_2_2_2_2-solution000011.solution deleted file mode 100644 index b33ee31e23..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_2_2_2_2-solution000011.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 2, 2 --> 2) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_2_2_2_2-solution000012.solution b/tests/exhaustive/basic/streamline01/expected/model_1_2_2_2_2-solution000012.solution deleted file mode 100644 index e00a3c532c..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_2_2_2_2-solution000012.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 2, 2 --> 2) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_1_2_2_2_2.eprime b/tests/exhaustive/basic/streamline01/expected/model_1_2_2_2_2.eprime deleted file mode 100644 index 7c7c5e7db5..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_1_2_2_2_2.eprime +++ /dev/null @@ -1,18 +0,0 @@ -language ESSENCE' 1.0 - -find f_Function1DPartial_Flags: matrix indexed by [int(1..2)] of bool -find f_Function1DPartial_Values: matrix indexed by [int(1..2)] of int(1..2) -find s_Occurrence: matrix indexed by [int(1..2)] of bool -find s_Explicit: matrix indexed by [int(1)] of int(1..2) -branching on [f_Function1DPartial_Flags, f_Function1DPartial_Values, s_Explicit, s_Occurrence] -such that - and([s_Occurrence[q13] -> f_Function1DPartial_Flags[q13] | q13 : int(1..2)]), - s_Explicit[1] != s_Explicit[1] -> - and([f_Function1DPartial_Values[s_Explicit[1]] > f_Function1DPartial_Values[s_Explicit[1]], - f_Function1DPartial_Flags[s_Explicit[1]], f_Function1DPartial_Flags[s_Explicit[1]]; - int(1..3)]), - 1 = sum([toInt(s_Occurrence[q1]) | q1 : int(1..2)]), - and([f_Function1DPartial_Flags[q2] = false -> f_Function1DPartial_Values[q2] = 1 | q2 : int(1..2)]), - s_Occurrence[s_Explicit[1]], - and([s_Occurrence[q9] -> s_Explicit[1] = q9 | q9 : int(1..2)]) - diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_1_1_1_1-solution000001.solution b/tests/exhaustive/basic/streamline01/expected/model_2_1_1_1_1-solution000001.solution deleted file mode 100644 index cd31e1020f..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_1_1_1_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(2 --> 1) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_1_1_1_1-solution000002.solution b/tests/exhaustive/basic/streamline01/expected/model_2_1_1_1_1-solution000002.solution deleted file mode 100644 index 2646544d52..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_1_1_1_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(2 --> 2) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_1_1_1_1-solution000003.solution b/tests/exhaustive/basic/streamline01/expected/model_2_1_1_1_1-solution000003.solution deleted file mode 100644 index 6da2c362aa..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_1_1_1_1-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 1) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_1_1_1_1-solution000004.solution b/tests/exhaustive/basic/streamline01/expected/model_2_1_1_1_1-solution000004.solution deleted file mode 100644 index 9fbfa45bad..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_1_1_1_1-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 2) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_1_1_1_1-solution000005.solution b/tests/exhaustive/basic/streamline01/expected/model_2_1_1_1_1-solution000005.solution deleted file mode 100644 index e62a462994..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_1_1_1_1-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 1, 2 --> 1) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_1_1_1_1-solution000006.solution b/tests/exhaustive/basic/streamline01/expected/model_2_1_1_1_1-solution000006.solution deleted file mode 100644 index 77f032a426..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_1_1_1_1-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 1, 2 --> 1) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_1_1_1_1-solution000007.solution b/tests/exhaustive/basic/streamline01/expected/model_2_1_1_1_1-solution000007.solution deleted file mode 100644 index d2200a27b7..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_1_1_1_1-solution000007.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 1, 2 --> 2) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_1_1_1_1-solution000008.solution b/tests/exhaustive/basic/streamline01/expected/model_2_1_1_1_1-solution000008.solution deleted file mode 100644 index 57c81f730c..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_1_1_1_1-solution000008.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 1, 2 --> 2) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_1_1_1_1-solution000009.solution b/tests/exhaustive/basic/streamline01/expected/model_2_1_1_1_1-solution000009.solution deleted file mode 100644 index 03807b7fff..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_1_1_1_1-solution000009.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 2, 2 --> 1) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_1_1_1_1-solution000010.solution b/tests/exhaustive/basic/streamline01/expected/model_2_1_1_1_1-solution000010.solution deleted file mode 100644 index 50857d4142..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_1_1_1_1-solution000010.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 2, 2 --> 1) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_1_1_1_1-solution000011.solution b/tests/exhaustive/basic/streamline01/expected/model_2_1_1_1_1-solution000011.solution deleted file mode 100644 index e00a3c532c..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_1_1_1_1-solution000011.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 2, 2 --> 2) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_1_1_1_1-solution000012.solution b/tests/exhaustive/basic/streamline01/expected/model_2_1_1_1_1-solution000012.solution deleted file mode 100644 index b33ee31e23..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_1_1_1_1-solution000012.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 2, 2 --> 2) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_1_1_1_1.eprime b/tests/exhaustive/basic/streamline01/expected/model_2_1_1_1_1.eprime deleted file mode 100644 index f4f46def7f..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_1_1_1_1.eprime +++ /dev/null @@ -1,39 +0,0 @@ -language ESSENCE' 1.0 - -find f_Function1DPartial_Flags: matrix indexed by [int(1..2)] of bool -find f_Function1DPartial_Values: matrix indexed by [int(1..2)] of int(1..2) -letting let1 be 1 -find s_Explicit: matrix indexed by [int(1)] of int(1..2) -find s_Occurrence: matrix indexed by [int(1..2)] of bool -find conjure_aux3: int(1..2) -find conjure_aux1: matrix indexed by [int(1..2)] of int(1..2) -find conjure_aux2: matrix indexed by [int(1..2)] of int(1..2) -branching on [f_Function1DPartial_Flags, f_Function1DPartial_Values, s_Occurrence, s_Explicit] -such that - f_Function1DPartial_Flags[s_Explicit[1]], - and([s_Occurrence[q14] -> q14 >= conjure_aux3 | q14 : int(1..2)]), - sum([toInt(s_Occurrence[q14]) | q14 : int(1..2)]) > 0 -> - or([s_Occurrence[q14] /\ q14 = conjure_aux3 | q14 : int(1..2)]), - sum([toInt(s_Occurrence[q14]) | q14 : int(1..2)]) = 0 -> conjure_aux3 = 1, - and([and([s_Occurrence[q12] -> q12 >= conjure_aux1[i] | q12 : int(1..2)]) | i : int(1..2)]), - and([(sum([toInt(s_Occurrence[q12]) | q12 : int(1..2)]) > 0 -> - or([s_Occurrence[q12] /\ q12 = conjure_aux1[i] | q12 : int(1..2)])) - /\ (sum([toInt(s_Occurrence[q12]) | q12 : int(1..2)]) = 0 -> conjure_aux1[i] = 1) - | i : int(1..2)]), - and([and([s_Occurrence[q13] -> q13 >= conjure_aux2[i] | q13 : int(1..2)]) | i : int(1..2)]), - and([(sum([toInt(s_Occurrence[q13]) | q13 : int(1..2)]) > 0 -> - or([s_Occurrence[q13] /\ q13 = conjure_aux2[i] | q13 : int(1..2)])) - /\ (sum([toInt(s_Occurrence[q13]) | q13 : int(1..2)]) = 0 -> conjure_aux2[i] = 1) - | i : int(1..2)]), - and([s_Occurrence[i] /\ (i != conjure_aux3 /\ sum([toInt(s_Occurrence[q14]) | q14 : int(1..2)]) > 0) -> - and([f_Function1DPartial_Values[i] > f_Function1DPartial_Values[conjure_aux1[i]] /\ - sum([toInt(s_Occurrence[q12]) | q12 : int(1..2)]) > 0, - f_Function1DPartial_Flags[i], - f_Function1DPartial_Flags[conjure_aux2[i]] /\ sum([toInt(s_Occurrence[q13]) | q13 : int(1..2)]) > 0; - int(1..3)]) - | i : int(1..2)]), - and([f_Function1DPartial_Flags[q3] = false -> f_Function1DPartial_Values[q3] = 1 | q3 : int(1..2)]), - 1 = sum([toInt(s_Occurrence[q6]) | q6 : int(1..2)]), - and([s_Occurrence[q7] -> s_Explicit[1] = q7 | q7 : int(1..2)]), - s_Occurrence[s_Explicit[1]] - diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_1_1_1_2-solution000001.solution b/tests/exhaustive/basic/streamline01/expected/model_2_1_1_1_2-solution000001.solution deleted file mode 100644 index cd31e1020f..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_1_1_1_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(2 --> 1) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_1_1_1_2-solution000002.solution b/tests/exhaustive/basic/streamline01/expected/model_2_1_1_1_2-solution000002.solution deleted file mode 100644 index 2646544d52..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_1_1_1_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(2 --> 2) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_1_1_1_2-solution000003.solution b/tests/exhaustive/basic/streamline01/expected/model_2_1_1_1_2-solution000003.solution deleted file mode 100644 index 6da2c362aa..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_1_1_1_2-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 1) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_1_1_1_2-solution000004.solution b/tests/exhaustive/basic/streamline01/expected/model_2_1_1_1_2-solution000004.solution deleted file mode 100644 index 9fbfa45bad..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_1_1_1_2-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 2) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_1_1_1_2-solution000005.solution b/tests/exhaustive/basic/streamline01/expected/model_2_1_1_1_2-solution000005.solution deleted file mode 100644 index e62a462994..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_1_1_1_2-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 1, 2 --> 1) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_1_1_1_2-solution000006.solution b/tests/exhaustive/basic/streamline01/expected/model_2_1_1_1_2-solution000006.solution deleted file mode 100644 index 77f032a426..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_1_1_1_2-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 1, 2 --> 1) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_1_1_1_2-solution000007.solution b/tests/exhaustive/basic/streamline01/expected/model_2_1_1_1_2-solution000007.solution deleted file mode 100644 index d2200a27b7..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_1_1_1_2-solution000007.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 1, 2 --> 2) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_1_1_1_2-solution000008.solution b/tests/exhaustive/basic/streamline01/expected/model_2_1_1_1_2-solution000008.solution deleted file mode 100644 index 57c81f730c..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_1_1_1_2-solution000008.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 1, 2 --> 2) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_1_1_1_2-solution000009.solution b/tests/exhaustive/basic/streamline01/expected/model_2_1_1_1_2-solution000009.solution deleted file mode 100644 index 03807b7fff..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_1_1_1_2-solution000009.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 2, 2 --> 1) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_1_1_1_2-solution000010.solution b/tests/exhaustive/basic/streamline01/expected/model_2_1_1_1_2-solution000010.solution deleted file mode 100644 index 50857d4142..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_1_1_1_2-solution000010.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 2, 2 --> 1) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_1_1_1_2-solution000011.solution b/tests/exhaustive/basic/streamline01/expected/model_2_1_1_1_2-solution000011.solution deleted file mode 100644 index e00a3c532c..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_1_1_1_2-solution000011.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 2, 2 --> 2) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_1_1_1_2-solution000012.solution b/tests/exhaustive/basic/streamline01/expected/model_2_1_1_1_2-solution000012.solution deleted file mode 100644 index b33ee31e23..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_1_1_1_2-solution000012.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 2, 2 --> 2) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_1_1_1_2.eprime b/tests/exhaustive/basic/streamline01/expected/model_2_1_1_1_2.eprime deleted file mode 100644 index f4f46def7f..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_1_1_1_2.eprime +++ /dev/null @@ -1,39 +0,0 @@ -language ESSENCE' 1.0 - -find f_Function1DPartial_Flags: matrix indexed by [int(1..2)] of bool -find f_Function1DPartial_Values: matrix indexed by [int(1..2)] of int(1..2) -letting let1 be 1 -find s_Explicit: matrix indexed by [int(1)] of int(1..2) -find s_Occurrence: matrix indexed by [int(1..2)] of bool -find conjure_aux3: int(1..2) -find conjure_aux1: matrix indexed by [int(1..2)] of int(1..2) -find conjure_aux2: matrix indexed by [int(1..2)] of int(1..2) -branching on [f_Function1DPartial_Flags, f_Function1DPartial_Values, s_Occurrence, s_Explicit] -such that - f_Function1DPartial_Flags[s_Explicit[1]], - and([s_Occurrence[q14] -> q14 >= conjure_aux3 | q14 : int(1..2)]), - sum([toInt(s_Occurrence[q14]) | q14 : int(1..2)]) > 0 -> - or([s_Occurrence[q14] /\ q14 = conjure_aux3 | q14 : int(1..2)]), - sum([toInt(s_Occurrence[q14]) | q14 : int(1..2)]) = 0 -> conjure_aux3 = 1, - and([and([s_Occurrence[q12] -> q12 >= conjure_aux1[i] | q12 : int(1..2)]) | i : int(1..2)]), - and([(sum([toInt(s_Occurrence[q12]) | q12 : int(1..2)]) > 0 -> - or([s_Occurrence[q12] /\ q12 = conjure_aux1[i] | q12 : int(1..2)])) - /\ (sum([toInt(s_Occurrence[q12]) | q12 : int(1..2)]) = 0 -> conjure_aux1[i] = 1) - | i : int(1..2)]), - and([and([s_Occurrence[q13] -> q13 >= conjure_aux2[i] | q13 : int(1..2)]) | i : int(1..2)]), - and([(sum([toInt(s_Occurrence[q13]) | q13 : int(1..2)]) > 0 -> - or([s_Occurrence[q13] /\ q13 = conjure_aux2[i] | q13 : int(1..2)])) - /\ (sum([toInt(s_Occurrence[q13]) | q13 : int(1..2)]) = 0 -> conjure_aux2[i] = 1) - | i : int(1..2)]), - and([s_Occurrence[i] /\ (i != conjure_aux3 /\ sum([toInt(s_Occurrence[q14]) | q14 : int(1..2)]) > 0) -> - and([f_Function1DPartial_Values[i] > f_Function1DPartial_Values[conjure_aux1[i]] /\ - sum([toInt(s_Occurrence[q12]) | q12 : int(1..2)]) > 0, - f_Function1DPartial_Flags[i], - f_Function1DPartial_Flags[conjure_aux2[i]] /\ sum([toInt(s_Occurrence[q13]) | q13 : int(1..2)]) > 0; - int(1..3)]) - | i : int(1..2)]), - and([f_Function1DPartial_Flags[q3] = false -> f_Function1DPartial_Values[q3] = 1 | q3 : int(1..2)]), - 1 = sum([toInt(s_Occurrence[q6]) | q6 : int(1..2)]), - and([s_Occurrence[q7] -> s_Explicit[1] = q7 | q7 : int(1..2)]), - s_Occurrence[s_Explicit[1]] - diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_1_1_2_1-solution000001.solution b/tests/exhaustive/basic/streamline01/expected/model_2_1_1_2_1-solution000001.solution deleted file mode 100644 index cd31e1020f..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_1_1_2_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(2 --> 1) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_1_1_2_1-solution000002.solution b/tests/exhaustive/basic/streamline01/expected/model_2_1_1_2_1-solution000002.solution deleted file mode 100644 index 2646544d52..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_1_1_2_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(2 --> 2) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_1_1_2_1-solution000003.solution b/tests/exhaustive/basic/streamline01/expected/model_2_1_1_2_1-solution000003.solution deleted file mode 100644 index 6da2c362aa..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_1_1_2_1-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 1) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_1_1_2_1-solution000004.solution b/tests/exhaustive/basic/streamline01/expected/model_2_1_1_2_1-solution000004.solution deleted file mode 100644 index 9fbfa45bad..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_1_1_2_1-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 2) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_1_1_2_1-solution000005.solution b/tests/exhaustive/basic/streamline01/expected/model_2_1_1_2_1-solution000005.solution deleted file mode 100644 index e62a462994..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_1_1_2_1-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 1, 2 --> 1) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_1_1_2_1-solution000006.solution b/tests/exhaustive/basic/streamline01/expected/model_2_1_1_2_1-solution000006.solution deleted file mode 100644 index 77f032a426..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_1_1_2_1-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 1, 2 --> 1) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_1_1_2_1-solution000007.solution b/tests/exhaustive/basic/streamline01/expected/model_2_1_1_2_1-solution000007.solution deleted file mode 100644 index d2200a27b7..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_1_1_2_1-solution000007.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 1, 2 --> 2) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_1_1_2_1-solution000008.solution b/tests/exhaustive/basic/streamline01/expected/model_2_1_1_2_1-solution000008.solution deleted file mode 100644 index 57c81f730c..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_1_1_2_1-solution000008.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 1, 2 --> 2) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_1_1_2_1-solution000009.solution b/tests/exhaustive/basic/streamline01/expected/model_2_1_1_2_1-solution000009.solution deleted file mode 100644 index 03807b7fff..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_1_1_2_1-solution000009.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 2, 2 --> 1) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_1_1_2_1-solution000010.solution b/tests/exhaustive/basic/streamline01/expected/model_2_1_1_2_1-solution000010.solution deleted file mode 100644 index 50857d4142..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_1_1_2_1-solution000010.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 2, 2 --> 1) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_1_1_2_1-solution000011.solution b/tests/exhaustive/basic/streamline01/expected/model_2_1_1_2_1-solution000011.solution deleted file mode 100644 index e00a3c532c..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_1_1_2_1-solution000011.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 2, 2 --> 2) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_1_1_2_1-solution000012.solution b/tests/exhaustive/basic/streamline01/expected/model_2_1_1_2_1-solution000012.solution deleted file mode 100644 index b33ee31e23..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_1_1_2_1-solution000012.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 2, 2 --> 2) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_1_1_2_1.eprime b/tests/exhaustive/basic/streamline01/expected/model_2_1_1_2_1.eprime deleted file mode 100644 index 5b1fbfc52a..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_1_1_2_1.eprime +++ /dev/null @@ -1,34 +0,0 @@ -language ESSENCE' 1.0 - -find f_Function1DPartial_Flags: matrix indexed by [int(1..2)] of bool -find f_Function1DPartial_Values: matrix indexed by [int(1..2)] of int(1..2) -letting let1 be 1 -find s_Explicit: matrix indexed by [int(1)] of int(1..2) -find s_Occurrence: matrix indexed by [int(1..2)] of bool -find conjure_aux1: matrix indexed by [int(1..2)] of int(1..2) -find conjure_aux2: matrix indexed by [int(1..2)] of int(1..2) -branching on [f_Function1DPartial_Flags, f_Function1DPartial_Values, s_Occurrence, s_Explicit] -such that - f_Function1DPartial_Flags[s_Explicit[1]], - and([and([s_Occurrence[q12] -> q12 >= conjure_aux1[i] | q12 : int(1..2)]) | i : int(1..2)]), - and([(sum([toInt(s_Occurrence[q12]) | q12 : int(1..2)]) > 0 -> - or([s_Occurrence[q12] /\ q12 = conjure_aux1[i] | q12 : int(1..2)])) - /\ (sum([toInt(s_Occurrence[q12]) | q12 : int(1..2)]) = 0 -> conjure_aux1[i] = 1) - | i : int(1..2)]), - and([and([s_Occurrence[q13] -> q13 >= conjure_aux2[i] | q13 : int(1..2)]) | i : int(1..2)]), - and([(sum([toInt(s_Occurrence[q13]) | q13 : int(1..2)]) > 0 -> - or([s_Occurrence[q13] /\ q13 = conjure_aux2[i] | q13 : int(1..2)])) - /\ (sum([toInt(s_Occurrence[q13]) | q13 : int(1..2)]) = 0 -> conjure_aux2[i] = 1) - | i : int(1..2)]), - and([s_Occurrence[i] /\ i != s_Explicit[1] -> - and([f_Function1DPartial_Values[i] > f_Function1DPartial_Values[conjure_aux1[i]] /\ - sum([toInt(s_Occurrence[q12]) | q12 : int(1..2)]) > 0, - f_Function1DPartial_Flags[i], - f_Function1DPartial_Flags[conjure_aux2[i]] /\ sum([toInt(s_Occurrence[q13]) | q13 : int(1..2)]) > 0; - int(1..3)]) - | i : int(1..2)]), - and([f_Function1DPartial_Flags[q3] = false -> f_Function1DPartial_Values[q3] = 1 | q3 : int(1..2)]), - 1 = sum([toInt(s_Occurrence[q6]) | q6 : int(1..2)]), - and([s_Occurrence[q7] -> s_Explicit[1] = q7 | q7 : int(1..2)]), - s_Occurrence[s_Explicit[1]] - diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_1_1_2_2-solution000001.solution b/tests/exhaustive/basic/streamline01/expected/model_2_1_1_2_2-solution000001.solution deleted file mode 100644 index cd31e1020f..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_1_1_2_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(2 --> 1) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_1_1_2_2-solution000002.solution b/tests/exhaustive/basic/streamline01/expected/model_2_1_1_2_2-solution000002.solution deleted file mode 100644 index 2646544d52..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_1_1_2_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(2 --> 2) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_1_1_2_2-solution000003.solution b/tests/exhaustive/basic/streamline01/expected/model_2_1_1_2_2-solution000003.solution deleted file mode 100644 index 6da2c362aa..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_1_1_2_2-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 1) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_1_1_2_2-solution000004.solution b/tests/exhaustive/basic/streamline01/expected/model_2_1_1_2_2-solution000004.solution deleted file mode 100644 index 9fbfa45bad..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_1_1_2_2-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 2) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_1_1_2_2-solution000005.solution b/tests/exhaustive/basic/streamline01/expected/model_2_1_1_2_2-solution000005.solution deleted file mode 100644 index e62a462994..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_1_1_2_2-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 1, 2 --> 1) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_1_1_2_2-solution000006.solution b/tests/exhaustive/basic/streamline01/expected/model_2_1_1_2_2-solution000006.solution deleted file mode 100644 index 77f032a426..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_1_1_2_2-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 1, 2 --> 1) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_1_1_2_2-solution000007.solution b/tests/exhaustive/basic/streamline01/expected/model_2_1_1_2_2-solution000007.solution deleted file mode 100644 index d2200a27b7..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_1_1_2_2-solution000007.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 1, 2 --> 2) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_1_1_2_2-solution000008.solution b/tests/exhaustive/basic/streamline01/expected/model_2_1_1_2_2-solution000008.solution deleted file mode 100644 index 57c81f730c..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_1_1_2_2-solution000008.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 1, 2 --> 2) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_1_1_2_2-solution000009.solution b/tests/exhaustive/basic/streamline01/expected/model_2_1_1_2_2-solution000009.solution deleted file mode 100644 index 03807b7fff..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_1_1_2_2-solution000009.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 2, 2 --> 1) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_1_1_2_2-solution000010.solution b/tests/exhaustive/basic/streamline01/expected/model_2_1_1_2_2-solution000010.solution deleted file mode 100644 index 50857d4142..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_1_1_2_2-solution000010.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 2, 2 --> 1) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_1_1_2_2-solution000011.solution b/tests/exhaustive/basic/streamline01/expected/model_2_1_1_2_2-solution000011.solution deleted file mode 100644 index e00a3c532c..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_1_1_2_2-solution000011.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 2, 2 --> 2) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_1_1_2_2-solution000012.solution b/tests/exhaustive/basic/streamline01/expected/model_2_1_1_2_2-solution000012.solution deleted file mode 100644 index b33ee31e23..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_1_1_2_2-solution000012.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 2, 2 --> 2) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_1_1_2_2.eprime b/tests/exhaustive/basic/streamline01/expected/model_2_1_1_2_2.eprime deleted file mode 100644 index 5b1fbfc52a..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_1_1_2_2.eprime +++ /dev/null @@ -1,34 +0,0 @@ -language ESSENCE' 1.0 - -find f_Function1DPartial_Flags: matrix indexed by [int(1..2)] of bool -find f_Function1DPartial_Values: matrix indexed by [int(1..2)] of int(1..2) -letting let1 be 1 -find s_Explicit: matrix indexed by [int(1)] of int(1..2) -find s_Occurrence: matrix indexed by [int(1..2)] of bool -find conjure_aux1: matrix indexed by [int(1..2)] of int(1..2) -find conjure_aux2: matrix indexed by [int(1..2)] of int(1..2) -branching on [f_Function1DPartial_Flags, f_Function1DPartial_Values, s_Occurrence, s_Explicit] -such that - f_Function1DPartial_Flags[s_Explicit[1]], - and([and([s_Occurrence[q12] -> q12 >= conjure_aux1[i] | q12 : int(1..2)]) | i : int(1..2)]), - and([(sum([toInt(s_Occurrence[q12]) | q12 : int(1..2)]) > 0 -> - or([s_Occurrence[q12] /\ q12 = conjure_aux1[i] | q12 : int(1..2)])) - /\ (sum([toInt(s_Occurrence[q12]) | q12 : int(1..2)]) = 0 -> conjure_aux1[i] = 1) - | i : int(1..2)]), - and([and([s_Occurrence[q13] -> q13 >= conjure_aux2[i] | q13 : int(1..2)]) | i : int(1..2)]), - and([(sum([toInt(s_Occurrence[q13]) | q13 : int(1..2)]) > 0 -> - or([s_Occurrence[q13] /\ q13 = conjure_aux2[i] | q13 : int(1..2)])) - /\ (sum([toInt(s_Occurrence[q13]) | q13 : int(1..2)]) = 0 -> conjure_aux2[i] = 1) - | i : int(1..2)]), - and([s_Occurrence[i] /\ i != s_Explicit[1] -> - and([f_Function1DPartial_Values[i] > f_Function1DPartial_Values[conjure_aux1[i]] /\ - sum([toInt(s_Occurrence[q12]) | q12 : int(1..2)]) > 0, - f_Function1DPartial_Flags[i], - f_Function1DPartial_Flags[conjure_aux2[i]] /\ sum([toInt(s_Occurrence[q13]) | q13 : int(1..2)]) > 0; - int(1..3)]) - | i : int(1..2)]), - and([f_Function1DPartial_Flags[q3] = false -> f_Function1DPartial_Values[q3] = 1 | q3 : int(1..2)]), - 1 = sum([toInt(s_Occurrence[q6]) | q6 : int(1..2)]), - and([s_Occurrence[q7] -> s_Explicit[1] = q7 | q7 : int(1..2)]), - s_Occurrence[s_Explicit[1]] - diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_1_2_1_1-solution000001.solution b/tests/exhaustive/basic/streamline01/expected/model_2_1_2_1_1-solution000001.solution deleted file mode 100644 index cd31e1020f..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_1_2_1_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(2 --> 1) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_1_2_1_1-solution000002.solution b/tests/exhaustive/basic/streamline01/expected/model_2_1_2_1_1-solution000002.solution deleted file mode 100644 index 2646544d52..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_1_2_1_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(2 --> 2) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_1_2_1_1-solution000003.solution b/tests/exhaustive/basic/streamline01/expected/model_2_1_2_1_1-solution000003.solution deleted file mode 100644 index 6da2c362aa..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_1_2_1_1-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 1) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_1_2_1_1-solution000004.solution b/tests/exhaustive/basic/streamline01/expected/model_2_1_2_1_1-solution000004.solution deleted file mode 100644 index 9fbfa45bad..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_1_2_1_1-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 2) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_1_2_1_1-solution000005.solution b/tests/exhaustive/basic/streamline01/expected/model_2_1_2_1_1-solution000005.solution deleted file mode 100644 index e62a462994..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_1_2_1_1-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 1, 2 --> 1) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_1_2_1_1-solution000006.solution b/tests/exhaustive/basic/streamline01/expected/model_2_1_2_1_1-solution000006.solution deleted file mode 100644 index 77f032a426..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_1_2_1_1-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 1, 2 --> 1) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_1_2_1_1-solution000007.solution b/tests/exhaustive/basic/streamline01/expected/model_2_1_2_1_1-solution000007.solution deleted file mode 100644 index d2200a27b7..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_1_2_1_1-solution000007.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 1, 2 --> 2) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_1_2_1_1-solution000008.solution b/tests/exhaustive/basic/streamline01/expected/model_2_1_2_1_1-solution000008.solution deleted file mode 100644 index 57c81f730c..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_1_2_1_1-solution000008.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 1, 2 --> 2) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_1_2_1_1-solution000009.solution b/tests/exhaustive/basic/streamline01/expected/model_2_1_2_1_1-solution000009.solution deleted file mode 100644 index 03807b7fff..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_1_2_1_1-solution000009.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 2, 2 --> 1) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_1_2_1_1-solution000010.solution b/tests/exhaustive/basic/streamline01/expected/model_2_1_2_1_1-solution000010.solution deleted file mode 100644 index 50857d4142..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_1_2_1_1-solution000010.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 2, 2 --> 1) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_1_2_1_1-solution000011.solution b/tests/exhaustive/basic/streamline01/expected/model_2_1_2_1_1-solution000011.solution deleted file mode 100644 index e00a3c532c..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_1_2_1_1-solution000011.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 2, 2 --> 2) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_1_2_1_1-solution000012.solution b/tests/exhaustive/basic/streamline01/expected/model_2_1_2_1_1-solution000012.solution deleted file mode 100644 index b33ee31e23..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_1_2_1_1-solution000012.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 2, 2 --> 2) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_1_2_1_1.eprime b/tests/exhaustive/basic/streamline01/expected/model_2_1_2_1_1.eprime deleted file mode 100644 index 2ceea536d4..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_1_2_1_1.eprime +++ /dev/null @@ -1,36 +0,0 @@ -language ESSENCE' 1.0 - -find f_Function1DPartial_Flags: matrix indexed by [int(1..2)] of bool -find f_Function1DPartial_Values: matrix indexed by [int(1..2)] of int(1..2) -letting let1 be 1 -find s_Explicit: matrix indexed by [int(1)] of int(1..2) -find s_Occurrence: matrix indexed by [int(1..2)] of bool -find conjure_aux1: matrix indexed by [int(1)] of int(1..2) -find conjure_aux2: matrix indexed by [int(1)] of int(1..2) -find conjure_aux3: int(1..2) -branching on [f_Function1DPartial_Flags, f_Function1DPartial_Values, s_Occurrence, s_Explicit] -such that - f_Function1DPartial_Flags[s_Explicit[1]], - and([s_Occurrence[q13] -> q13 >= conjure_aux1[1] | q13 : int(1..2)]), - sum([toInt(s_Occurrence[q13]) | q13 : int(1..2)]) > 0 -> - or([s_Occurrence[q13] /\ q13 = conjure_aux1[1] | q13 : int(1..2)]), - sum([toInt(s_Occurrence[q13]) | q13 : int(1..2)]) = 0 -> conjure_aux1[1] = 1, - and([s_Occurrence[q14] -> q14 >= conjure_aux2[1] | q14 : int(1..2)]), - sum([toInt(s_Occurrence[q14]) | q14 : int(1..2)]) > 0 -> - or([s_Occurrence[q14] /\ q14 = conjure_aux2[1] | q14 : int(1..2)]), - sum([toInt(s_Occurrence[q14]) | q14 : int(1..2)]) = 0 -> conjure_aux2[1] = 1, - and([s_Occurrence[q15] -> q15 >= conjure_aux3 | q15 : int(1..2)]), - sum([toInt(s_Occurrence[q15]) | q15 : int(1..2)]) > 0 -> - or([s_Occurrence[q15] /\ q15 = conjure_aux3 | q15 : int(1..2)]), - sum([toInt(s_Occurrence[q15]) | q15 : int(1..2)]) = 0 -> conjure_aux3 = 1, - s_Explicit[1] != conjure_aux3 /\ sum([toInt(s_Occurrence[q15]) | q15 : int(1..2)]) > 0 -> - and([f_Function1DPartial_Values[s_Explicit[1]] > f_Function1DPartial_Values[conjure_aux1[1]] /\ - sum([toInt(s_Occurrence[q13]) | q13 : int(1..2)]) > 0, - f_Function1DPartial_Flags[s_Explicit[1]], - f_Function1DPartial_Flags[conjure_aux2[1]] /\ sum([toInt(s_Occurrence[q14]) | q14 : int(1..2)]) > 0; - int(1..3)]), - and([f_Function1DPartial_Flags[q3] = false -> f_Function1DPartial_Values[q3] = 1 | q3 : int(1..2)]), - 1 = sum([toInt(s_Occurrence[q6]) | q6 : int(1..2)]), - and([s_Occurrence[q7] -> s_Explicit[1] = q7 | q7 : int(1..2)]), - s_Occurrence[s_Explicit[1]] - diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_1_2_1_2-solution000001.solution b/tests/exhaustive/basic/streamline01/expected/model_2_1_2_1_2-solution000001.solution deleted file mode 100644 index cd31e1020f..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_1_2_1_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(2 --> 1) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_1_2_1_2-solution000002.solution b/tests/exhaustive/basic/streamline01/expected/model_2_1_2_1_2-solution000002.solution deleted file mode 100644 index 2646544d52..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_1_2_1_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(2 --> 2) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_1_2_1_2-solution000003.solution b/tests/exhaustive/basic/streamline01/expected/model_2_1_2_1_2-solution000003.solution deleted file mode 100644 index 6da2c362aa..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_1_2_1_2-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 1) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_1_2_1_2-solution000004.solution b/tests/exhaustive/basic/streamline01/expected/model_2_1_2_1_2-solution000004.solution deleted file mode 100644 index 9fbfa45bad..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_1_2_1_2-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 2) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_1_2_1_2-solution000005.solution b/tests/exhaustive/basic/streamline01/expected/model_2_1_2_1_2-solution000005.solution deleted file mode 100644 index e62a462994..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_1_2_1_2-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 1, 2 --> 1) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_1_2_1_2-solution000006.solution b/tests/exhaustive/basic/streamline01/expected/model_2_1_2_1_2-solution000006.solution deleted file mode 100644 index 77f032a426..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_1_2_1_2-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 1, 2 --> 1) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_1_2_1_2-solution000007.solution b/tests/exhaustive/basic/streamline01/expected/model_2_1_2_1_2-solution000007.solution deleted file mode 100644 index d2200a27b7..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_1_2_1_2-solution000007.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 1, 2 --> 2) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_1_2_1_2-solution000008.solution b/tests/exhaustive/basic/streamline01/expected/model_2_1_2_1_2-solution000008.solution deleted file mode 100644 index 57c81f730c..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_1_2_1_2-solution000008.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 1, 2 --> 2) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_1_2_1_2-solution000009.solution b/tests/exhaustive/basic/streamline01/expected/model_2_1_2_1_2-solution000009.solution deleted file mode 100644 index 03807b7fff..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_1_2_1_2-solution000009.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 2, 2 --> 1) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_1_2_1_2-solution000010.solution b/tests/exhaustive/basic/streamline01/expected/model_2_1_2_1_2-solution000010.solution deleted file mode 100644 index 50857d4142..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_1_2_1_2-solution000010.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 2, 2 --> 1) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_1_2_1_2-solution000011.solution b/tests/exhaustive/basic/streamline01/expected/model_2_1_2_1_2-solution000011.solution deleted file mode 100644 index e00a3c532c..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_1_2_1_2-solution000011.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 2, 2 --> 2) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_1_2_1_2-solution000012.solution b/tests/exhaustive/basic/streamline01/expected/model_2_1_2_1_2-solution000012.solution deleted file mode 100644 index b33ee31e23..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_1_2_1_2-solution000012.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 2, 2 --> 2) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_1_2_1_2.eprime b/tests/exhaustive/basic/streamline01/expected/model_2_1_2_1_2.eprime deleted file mode 100644 index 2ceea536d4..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_1_2_1_2.eprime +++ /dev/null @@ -1,36 +0,0 @@ -language ESSENCE' 1.0 - -find f_Function1DPartial_Flags: matrix indexed by [int(1..2)] of bool -find f_Function1DPartial_Values: matrix indexed by [int(1..2)] of int(1..2) -letting let1 be 1 -find s_Explicit: matrix indexed by [int(1)] of int(1..2) -find s_Occurrence: matrix indexed by [int(1..2)] of bool -find conjure_aux1: matrix indexed by [int(1)] of int(1..2) -find conjure_aux2: matrix indexed by [int(1)] of int(1..2) -find conjure_aux3: int(1..2) -branching on [f_Function1DPartial_Flags, f_Function1DPartial_Values, s_Occurrence, s_Explicit] -such that - f_Function1DPartial_Flags[s_Explicit[1]], - and([s_Occurrence[q13] -> q13 >= conjure_aux1[1] | q13 : int(1..2)]), - sum([toInt(s_Occurrence[q13]) | q13 : int(1..2)]) > 0 -> - or([s_Occurrence[q13] /\ q13 = conjure_aux1[1] | q13 : int(1..2)]), - sum([toInt(s_Occurrence[q13]) | q13 : int(1..2)]) = 0 -> conjure_aux1[1] = 1, - and([s_Occurrence[q14] -> q14 >= conjure_aux2[1] | q14 : int(1..2)]), - sum([toInt(s_Occurrence[q14]) | q14 : int(1..2)]) > 0 -> - or([s_Occurrence[q14] /\ q14 = conjure_aux2[1] | q14 : int(1..2)]), - sum([toInt(s_Occurrence[q14]) | q14 : int(1..2)]) = 0 -> conjure_aux2[1] = 1, - and([s_Occurrence[q15] -> q15 >= conjure_aux3 | q15 : int(1..2)]), - sum([toInt(s_Occurrence[q15]) | q15 : int(1..2)]) > 0 -> - or([s_Occurrence[q15] /\ q15 = conjure_aux3 | q15 : int(1..2)]), - sum([toInt(s_Occurrence[q15]) | q15 : int(1..2)]) = 0 -> conjure_aux3 = 1, - s_Explicit[1] != conjure_aux3 /\ sum([toInt(s_Occurrence[q15]) | q15 : int(1..2)]) > 0 -> - and([f_Function1DPartial_Values[s_Explicit[1]] > f_Function1DPartial_Values[conjure_aux1[1]] /\ - sum([toInt(s_Occurrence[q13]) | q13 : int(1..2)]) > 0, - f_Function1DPartial_Flags[s_Explicit[1]], - f_Function1DPartial_Flags[conjure_aux2[1]] /\ sum([toInt(s_Occurrence[q14]) | q14 : int(1..2)]) > 0; - int(1..3)]), - and([f_Function1DPartial_Flags[q3] = false -> f_Function1DPartial_Values[q3] = 1 | q3 : int(1..2)]), - 1 = sum([toInt(s_Occurrence[q6]) | q6 : int(1..2)]), - and([s_Occurrence[q7] -> s_Explicit[1] = q7 | q7 : int(1..2)]), - s_Occurrence[s_Explicit[1]] - diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_1_2_2_1-solution000001.solution b/tests/exhaustive/basic/streamline01/expected/model_2_1_2_2_1-solution000001.solution deleted file mode 100644 index cd31e1020f..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_1_2_2_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(2 --> 1) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_1_2_2_1-solution000002.solution b/tests/exhaustive/basic/streamline01/expected/model_2_1_2_2_1-solution000002.solution deleted file mode 100644 index 2646544d52..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_1_2_2_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(2 --> 2) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_1_2_2_1-solution000003.solution b/tests/exhaustive/basic/streamline01/expected/model_2_1_2_2_1-solution000003.solution deleted file mode 100644 index 6da2c362aa..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_1_2_2_1-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 1) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_1_2_2_1-solution000004.solution b/tests/exhaustive/basic/streamline01/expected/model_2_1_2_2_1-solution000004.solution deleted file mode 100644 index 9fbfa45bad..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_1_2_2_1-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 2) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_1_2_2_1-solution000005.solution b/tests/exhaustive/basic/streamline01/expected/model_2_1_2_2_1-solution000005.solution deleted file mode 100644 index e62a462994..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_1_2_2_1-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 1, 2 --> 1) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_1_2_2_1-solution000006.solution b/tests/exhaustive/basic/streamline01/expected/model_2_1_2_2_1-solution000006.solution deleted file mode 100644 index 77f032a426..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_1_2_2_1-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 1, 2 --> 1) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_1_2_2_1-solution000007.solution b/tests/exhaustive/basic/streamline01/expected/model_2_1_2_2_1-solution000007.solution deleted file mode 100644 index d2200a27b7..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_1_2_2_1-solution000007.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 1, 2 --> 2) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_1_2_2_1-solution000008.solution b/tests/exhaustive/basic/streamline01/expected/model_2_1_2_2_1-solution000008.solution deleted file mode 100644 index 57c81f730c..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_1_2_2_1-solution000008.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 1, 2 --> 2) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_1_2_2_1-solution000009.solution b/tests/exhaustive/basic/streamline01/expected/model_2_1_2_2_1-solution000009.solution deleted file mode 100644 index 03807b7fff..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_1_2_2_1-solution000009.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 2, 2 --> 1) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_1_2_2_1-solution000010.solution b/tests/exhaustive/basic/streamline01/expected/model_2_1_2_2_1-solution000010.solution deleted file mode 100644 index 50857d4142..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_1_2_2_1-solution000010.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 2, 2 --> 1) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_1_2_2_1-solution000011.solution b/tests/exhaustive/basic/streamline01/expected/model_2_1_2_2_1-solution000011.solution deleted file mode 100644 index e00a3c532c..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_1_2_2_1-solution000011.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 2, 2 --> 2) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_1_2_2_1-solution000012.solution b/tests/exhaustive/basic/streamline01/expected/model_2_1_2_2_1-solution000012.solution deleted file mode 100644 index b33ee31e23..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_1_2_2_1-solution000012.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 2, 2 --> 2) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_1_2_2_1.eprime b/tests/exhaustive/basic/streamline01/expected/model_2_1_2_2_1.eprime deleted file mode 100644 index 43809fb9d0..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_1_2_2_1.eprime +++ /dev/null @@ -1,31 +0,0 @@ -language ESSENCE' 1.0 - -find f_Function1DPartial_Flags: matrix indexed by [int(1..2)] of bool -find f_Function1DPartial_Values: matrix indexed by [int(1..2)] of int(1..2) -letting let1 be 1 -find s_Explicit: matrix indexed by [int(1)] of int(1..2) -find s_Occurrence: matrix indexed by [int(1..2)] of bool -find conjure_aux1: matrix indexed by [int(1)] of int(1..2) -find conjure_aux2: matrix indexed by [int(1)] of int(1..2) -branching on [f_Function1DPartial_Flags, f_Function1DPartial_Values, s_Occurrence, s_Explicit] -such that - f_Function1DPartial_Flags[s_Explicit[1]], - and([s_Occurrence[q13] -> q13 >= conjure_aux1[1] | q13 : int(1..2)]), - sum([toInt(s_Occurrence[q13]) | q13 : int(1..2)]) > 0 -> - or([s_Occurrence[q13] /\ q13 = conjure_aux1[1] | q13 : int(1..2)]), - sum([toInt(s_Occurrence[q13]) | q13 : int(1..2)]) = 0 -> conjure_aux1[1] = 1, - and([s_Occurrence[q14] -> q14 >= conjure_aux2[1] | q14 : int(1..2)]), - sum([toInt(s_Occurrence[q14]) | q14 : int(1..2)]) > 0 -> - or([s_Occurrence[q14] /\ q14 = conjure_aux2[1] | q14 : int(1..2)]), - sum([toInt(s_Occurrence[q14]) | q14 : int(1..2)]) = 0 -> conjure_aux2[1] = 1, - s_Explicit[1] != s_Explicit[1] -> - and([f_Function1DPartial_Values[s_Explicit[1]] > f_Function1DPartial_Values[conjure_aux1[1]] /\ - sum([toInt(s_Occurrence[q13]) | q13 : int(1..2)]) > 0, - f_Function1DPartial_Flags[s_Explicit[1]], - f_Function1DPartial_Flags[conjure_aux2[1]] /\ sum([toInt(s_Occurrence[q14]) | q14 : int(1..2)]) > 0; - int(1..3)]), - and([f_Function1DPartial_Flags[q3] = false -> f_Function1DPartial_Values[q3] = 1 | q3 : int(1..2)]), - 1 = sum([toInt(s_Occurrence[q6]) | q6 : int(1..2)]), - and([s_Occurrence[q7] -> s_Explicit[1] = q7 | q7 : int(1..2)]), - s_Occurrence[s_Explicit[1]] - diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_1_2_2_2-solution000001.solution b/tests/exhaustive/basic/streamline01/expected/model_2_1_2_2_2-solution000001.solution deleted file mode 100644 index cd31e1020f..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_1_2_2_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(2 --> 1) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_1_2_2_2-solution000002.solution b/tests/exhaustive/basic/streamline01/expected/model_2_1_2_2_2-solution000002.solution deleted file mode 100644 index 2646544d52..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_1_2_2_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(2 --> 2) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_1_2_2_2-solution000003.solution b/tests/exhaustive/basic/streamline01/expected/model_2_1_2_2_2-solution000003.solution deleted file mode 100644 index 6da2c362aa..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_1_2_2_2-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 1) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_1_2_2_2-solution000004.solution b/tests/exhaustive/basic/streamline01/expected/model_2_1_2_2_2-solution000004.solution deleted file mode 100644 index 9fbfa45bad..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_1_2_2_2-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 2) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_1_2_2_2-solution000005.solution b/tests/exhaustive/basic/streamline01/expected/model_2_1_2_2_2-solution000005.solution deleted file mode 100644 index e62a462994..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_1_2_2_2-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 1, 2 --> 1) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_1_2_2_2-solution000006.solution b/tests/exhaustive/basic/streamline01/expected/model_2_1_2_2_2-solution000006.solution deleted file mode 100644 index 77f032a426..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_1_2_2_2-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 1, 2 --> 1) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_1_2_2_2-solution000007.solution b/tests/exhaustive/basic/streamline01/expected/model_2_1_2_2_2-solution000007.solution deleted file mode 100644 index d2200a27b7..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_1_2_2_2-solution000007.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 1, 2 --> 2) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_1_2_2_2-solution000008.solution b/tests/exhaustive/basic/streamline01/expected/model_2_1_2_2_2-solution000008.solution deleted file mode 100644 index 57c81f730c..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_1_2_2_2-solution000008.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 1, 2 --> 2) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_1_2_2_2-solution000009.solution b/tests/exhaustive/basic/streamline01/expected/model_2_1_2_2_2-solution000009.solution deleted file mode 100644 index 03807b7fff..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_1_2_2_2-solution000009.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 2, 2 --> 1) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_1_2_2_2-solution000010.solution b/tests/exhaustive/basic/streamline01/expected/model_2_1_2_2_2-solution000010.solution deleted file mode 100644 index 50857d4142..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_1_2_2_2-solution000010.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 2, 2 --> 1) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_1_2_2_2-solution000011.solution b/tests/exhaustive/basic/streamline01/expected/model_2_1_2_2_2-solution000011.solution deleted file mode 100644 index e00a3c532c..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_1_2_2_2-solution000011.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 2, 2 --> 2) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_1_2_2_2-solution000012.solution b/tests/exhaustive/basic/streamline01/expected/model_2_1_2_2_2-solution000012.solution deleted file mode 100644 index b33ee31e23..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_1_2_2_2-solution000012.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 2, 2 --> 2) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_1_2_2_2.eprime b/tests/exhaustive/basic/streamline01/expected/model_2_1_2_2_2.eprime deleted file mode 100644 index 43809fb9d0..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_1_2_2_2.eprime +++ /dev/null @@ -1,31 +0,0 @@ -language ESSENCE' 1.0 - -find f_Function1DPartial_Flags: matrix indexed by [int(1..2)] of bool -find f_Function1DPartial_Values: matrix indexed by [int(1..2)] of int(1..2) -letting let1 be 1 -find s_Explicit: matrix indexed by [int(1)] of int(1..2) -find s_Occurrence: matrix indexed by [int(1..2)] of bool -find conjure_aux1: matrix indexed by [int(1)] of int(1..2) -find conjure_aux2: matrix indexed by [int(1)] of int(1..2) -branching on [f_Function1DPartial_Flags, f_Function1DPartial_Values, s_Occurrence, s_Explicit] -such that - f_Function1DPartial_Flags[s_Explicit[1]], - and([s_Occurrence[q13] -> q13 >= conjure_aux1[1] | q13 : int(1..2)]), - sum([toInt(s_Occurrence[q13]) | q13 : int(1..2)]) > 0 -> - or([s_Occurrence[q13] /\ q13 = conjure_aux1[1] | q13 : int(1..2)]), - sum([toInt(s_Occurrence[q13]) | q13 : int(1..2)]) = 0 -> conjure_aux1[1] = 1, - and([s_Occurrence[q14] -> q14 >= conjure_aux2[1] | q14 : int(1..2)]), - sum([toInt(s_Occurrence[q14]) | q14 : int(1..2)]) > 0 -> - or([s_Occurrence[q14] /\ q14 = conjure_aux2[1] | q14 : int(1..2)]), - sum([toInt(s_Occurrence[q14]) | q14 : int(1..2)]) = 0 -> conjure_aux2[1] = 1, - s_Explicit[1] != s_Explicit[1] -> - and([f_Function1DPartial_Values[s_Explicit[1]] > f_Function1DPartial_Values[conjure_aux1[1]] /\ - sum([toInt(s_Occurrence[q13]) | q13 : int(1..2)]) > 0, - f_Function1DPartial_Flags[s_Explicit[1]], - f_Function1DPartial_Flags[conjure_aux2[1]] /\ sum([toInt(s_Occurrence[q14]) | q14 : int(1..2)]) > 0; - int(1..3)]), - and([f_Function1DPartial_Flags[q3] = false -> f_Function1DPartial_Values[q3] = 1 | q3 : int(1..2)]), - 1 = sum([toInt(s_Occurrence[q6]) | q6 : int(1..2)]), - and([s_Occurrence[q7] -> s_Explicit[1] = q7 | q7 : int(1..2)]), - s_Occurrence[s_Explicit[1]] - diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_2_1_1_1-solution000001.solution b/tests/exhaustive/basic/streamline01/expected/model_2_2_1_1_1-solution000001.solution deleted file mode 100644 index cd31e1020f..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_2_1_1_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(2 --> 1) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_2_1_1_1-solution000002.solution b/tests/exhaustive/basic/streamline01/expected/model_2_2_1_1_1-solution000002.solution deleted file mode 100644 index 2646544d52..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_2_1_1_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(2 --> 2) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_2_1_1_1-solution000003.solution b/tests/exhaustive/basic/streamline01/expected/model_2_2_1_1_1-solution000003.solution deleted file mode 100644 index 6da2c362aa..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_2_1_1_1-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 1) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_2_1_1_1-solution000004.solution b/tests/exhaustive/basic/streamline01/expected/model_2_2_1_1_1-solution000004.solution deleted file mode 100644 index 9fbfa45bad..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_2_1_1_1-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 2) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_2_1_1_1-solution000005.solution b/tests/exhaustive/basic/streamline01/expected/model_2_2_1_1_1-solution000005.solution deleted file mode 100644 index e62a462994..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_2_1_1_1-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 1, 2 --> 1) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_2_1_1_1-solution000006.solution b/tests/exhaustive/basic/streamline01/expected/model_2_2_1_1_1-solution000006.solution deleted file mode 100644 index 77f032a426..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_2_1_1_1-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 1, 2 --> 1) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_2_1_1_1-solution000007.solution b/tests/exhaustive/basic/streamline01/expected/model_2_2_1_1_1-solution000007.solution deleted file mode 100644 index d2200a27b7..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_2_1_1_1-solution000007.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 1, 2 --> 2) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_2_1_1_1-solution000008.solution b/tests/exhaustive/basic/streamline01/expected/model_2_2_1_1_1-solution000008.solution deleted file mode 100644 index 57c81f730c..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_2_1_1_1-solution000008.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 1, 2 --> 2) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_2_1_1_1-solution000009.solution b/tests/exhaustive/basic/streamline01/expected/model_2_2_1_1_1-solution000009.solution deleted file mode 100644 index 03807b7fff..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_2_1_1_1-solution000009.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 2, 2 --> 1) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_2_1_1_1-solution000010.solution b/tests/exhaustive/basic/streamline01/expected/model_2_2_1_1_1-solution000010.solution deleted file mode 100644 index 50857d4142..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_2_1_1_1-solution000010.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 2, 2 --> 1) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_2_1_1_1-solution000011.solution b/tests/exhaustive/basic/streamline01/expected/model_2_2_1_1_1-solution000011.solution deleted file mode 100644 index e00a3c532c..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_2_1_1_1-solution000011.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 2, 2 --> 2) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_2_1_1_1-solution000012.solution b/tests/exhaustive/basic/streamline01/expected/model_2_2_1_1_1-solution000012.solution deleted file mode 100644 index b33ee31e23..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_2_1_1_1-solution000012.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 2, 2 --> 2) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_2_1_1_1.eprime b/tests/exhaustive/basic/streamline01/expected/model_2_2_1_1_1.eprime deleted file mode 100644 index bd0fa3aa49..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_2_1_1_1.eprime +++ /dev/null @@ -1,25 +0,0 @@ -language ESSENCE' 1.0 - -find f_Function1DPartial_Flags: matrix indexed by [int(1..2)] of bool -find f_Function1DPartial_Values: matrix indexed by [int(1..2)] of int(1..2) -letting let1 be 1 -find s_Explicit: matrix indexed by [int(1)] of int(1..2) -find s_Occurrence: matrix indexed by [int(1..2)] of bool -find conjure_aux1: int(1..2) -branching on [f_Function1DPartial_Flags, f_Function1DPartial_Values, s_Occurrence, s_Explicit] -such that - f_Function1DPartial_Flags[s_Explicit[1]], - and([s_Occurrence[q12] -> q12 >= conjure_aux1 | q12 : int(1..2)]), - sum([toInt(s_Occurrence[q12]) | q12 : int(1..2)]) > 0 -> - or([s_Occurrence[q12] /\ q12 = conjure_aux1 | q12 : int(1..2)]), - sum([toInt(s_Occurrence[q12]) | q12 : int(1..2)]) = 0 -> conjure_aux1 = 1, - and([s_Occurrence[i] /\ (i != conjure_aux1 /\ sum([toInt(s_Occurrence[q12]) | q12 : int(1..2)]) > 0) -> - and([f_Function1DPartial_Values[i] > f_Function1DPartial_Values[s_Explicit[1]], f_Function1DPartial_Flags[i], - f_Function1DPartial_Flags[s_Explicit[1]]; - int(1..3)]) - | i : int(1..2)]), - and([f_Function1DPartial_Flags[q3] = false -> f_Function1DPartial_Values[q3] = 1 | q3 : int(1..2)]), - 1 = sum([toInt(s_Occurrence[q6]) | q6 : int(1..2)]), - and([s_Occurrence[q7] -> s_Explicit[1] = q7 | q7 : int(1..2)]), - s_Occurrence[s_Explicit[1]] - diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_2_1_1_2-solution000001.solution b/tests/exhaustive/basic/streamline01/expected/model_2_2_1_1_2-solution000001.solution deleted file mode 100644 index cd31e1020f..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_2_1_1_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(2 --> 1) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_2_1_1_2-solution000002.solution b/tests/exhaustive/basic/streamline01/expected/model_2_2_1_1_2-solution000002.solution deleted file mode 100644 index 2646544d52..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_2_1_1_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(2 --> 2) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_2_1_1_2-solution000003.solution b/tests/exhaustive/basic/streamline01/expected/model_2_2_1_1_2-solution000003.solution deleted file mode 100644 index 6da2c362aa..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_2_1_1_2-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 1) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_2_1_1_2-solution000004.solution b/tests/exhaustive/basic/streamline01/expected/model_2_2_1_1_2-solution000004.solution deleted file mode 100644 index 9fbfa45bad..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_2_1_1_2-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 2) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_2_1_1_2-solution000005.solution b/tests/exhaustive/basic/streamline01/expected/model_2_2_1_1_2-solution000005.solution deleted file mode 100644 index e62a462994..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_2_1_1_2-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 1, 2 --> 1) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_2_1_1_2-solution000006.solution b/tests/exhaustive/basic/streamline01/expected/model_2_2_1_1_2-solution000006.solution deleted file mode 100644 index 77f032a426..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_2_1_1_2-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 1, 2 --> 1) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_2_1_1_2-solution000007.solution b/tests/exhaustive/basic/streamline01/expected/model_2_2_1_1_2-solution000007.solution deleted file mode 100644 index d2200a27b7..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_2_1_1_2-solution000007.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 1, 2 --> 2) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_2_1_1_2-solution000008.solution b/tests/exhaustive/basic/streamline01/expected/model_2_2_1_1_2-solution000008.solution deleted file mode 100644 index 57c81f730c..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_2_1_1_2-solution000008.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 1, 2 --> 2) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_2_1_1_2-solution000009.solution b/tests/exhaustive/basic/streamline01/expected/model_2_2_1_1_2-solution000009.solution deleted file mode 100644 index 03807b7fff..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_2_1_1_2-solution000009.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 2, 2 --> 1) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_2_1_1_2-solution000010.solution b/tests/exhaustive/basic/streamline01/expected/model_2_2_1_1_2-solution000010.solution deleted file mode 100644 index 50857d4142..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_2_1_1_2-solution000010.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 2, 2 --> 1) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_2_1_1_2-solution000011.solution b/tests/exhaustive/basic/streamline01/expected/model_2_2_1_1_2-solution000011.solution deleted file mode 100644 index e00a3c532c..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_2_1_1_2-solution000011.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 2, 2 --> 2) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_2_1_1_2-solution000012.solution b/tests/exhaustive/basic/streamline01/expected/model_2_2_1_1_2-solution000012.solution deleted file mode 100644 index b33ee31e23..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_2_1_1_2-solution000012.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 2, 2 --> 2) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_2_1_1_2.eprime b/tests/exhaustive/basic/streamline01/expected/model_2_2_1_1_2.eprime deleted file mode 100644 index bd0fa3aa49..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_2_1_1_2.eprime +++ /dev/null @@ -1,25 +0,0 @@ -language ESSENCE' 1.0 - -find f_Function1DPartial_Flags: matrix indexed by [int(1..2)] of bool -find f_Function1DPartial_Values: matrix indexed by [int(1..2)] of int(1..2) -letting let1 be 1 -find s_Explicit: matrix indexed by [int(1)] of int(1..2) -find s_Occurrence: matrix indexed by [int(1..2)] of bool -find conjure_aux1: int(1..2) -branching on [f_Function1DPartial_Flags, f_Function1DPartial_Values, s_Occurrence, s_Explicit] -such that - f_Function1DPartial_Flags[s_Explicit[1]], - and([s_Occurrence[q12] -> q12 >= conjure_aux1 | q12 : int(1..2)]), - sum([toInt(s_Occurrence[q12]) | q12 : int(1..2)]) > 0 -> - or([s_Occurrence[q12] /\ q12 = conjure_aux1 | q12 : int(1..2)]), - sum([toInt(s_Occurrence[q12]) | q12 : int(1..2)]) = 0 -> conjure_aux1 = 1, - and([s_Occurrence[i] /\ (i != conjure_aux1 /\ sum([toInt(s_Occurrence[q12]) | q12 : int(1..2)]) > 0) -> - and([f_Function1DPartial_Values[i] > f_Function1DPartial_Values[s_Explicit[1]], f_Function1DPartial_Flags[i], - f_Function1DPartial_Flags[s_Explicit[1]]; - int(1..3)]) - | i : int(1..2)]), - and([f_Function1DPartial_Flags[q3] = false -> f_Function1DPartial_Values[q3] = 1 | q3 : int(1..2)]), - 1 = sum([toInt(s_Occurrence[q6]) | q6 : int(1..2)]), - and([s_Occurrence[q7] -> s_Explicit[1] = q7 | q7 : int(1..2)]), - s_Occurrence[s_Explicit[1]] - diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_2_1_2_1-solution000001.solution b/tests/exhaustive/basic/streamline01/expected/model_2_2_1_2_1-solution000001.solution deleted file mode 100644 index cd31e1020f..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_2_1_2_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(2 --> 1) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_2_1_2_1-solution000002.solution b/tests/exhaustive/basic/streamline01/expected/model_2_2_1_2_1-solution000002.solution deleted file mode 100644 index 2646544d52..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_2_1_2_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(2 --> 2) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_2_1_2_1-solution000003.solution b/tests/exhaustive/basic/streamline01/expected/model_2_2_1_2_1-solution000003.solution deleted file mode 100644 index 6da2c362aa..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_2_1_2_1-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 1) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_2_1_2_1-solution000004.solution b/tests/exhaustive/basic/streamline01/expected/model_2_2_1_2_1-solution000004.solution deleted file mode 100644 index 9fbfa45bad..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_2_1_2_1-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 2) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_2_1_2_1-solution000005.solution b/tests/exhaustive/basic/streamline01/expected/model_2_2_1_2_1-solution000005.solution deleted file mode 100644 index e62a462994..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_2_1_2_1-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 1, 2 --> 1) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_2_1_2_1-solution000006.solution b/tests/exhaustive/basic/streamline01/expected/model_2_2_1_2_1-solution000006.solution deleted file mode 100644 index 77f032a426..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_2_1_2_1-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 1, 2 --> 1) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_2_1_2_1-solution000007.solution b/tests/exhaustive/basic/streamline01/expected/model_2_2_1_2_1-solution000007.solution deleted file mode 100644 index d2200a27b7..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_2_1_2_1-solution000007.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 1, 2 --> 2) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_2_1_2_1-solution000008.solution b/tests/exhaustive/basic/streamline01/expected/model_2_2_1_2_1-solution000008.solution deleted file mode 100644 index 57c81f730c..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_2_1_2_1-solution000008.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 1, 2 --> 2) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_2_1_2_1-solution000009.solution b/tests/exhaustive/basic/streamline01/expected/model_2_2_1_2_1-solution000009.solution deleted file mode 100644 index 03807b7fff..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_2_1_2_1-solution000009.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 2, 2 --> 1) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_2_1_2_1-solution000010.solution b/tests/exhaustive/basic/streamline01/expected/model_2_2_1_2_1-solution000010.solution deleted file mode 100644 index 50857d4142..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_2_1_2_1-solution000010.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 2, 2 --> 1) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_2_1_2_1-solution000011.solution b/tests/exhaustive/basic/streamline01/expected/model_2_2_1_2_1-solution000011.solution deleted file mode 100644 index e00a3c532c..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_2_1_2_1-solution000011.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 2, 2 --> 2) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_2_1_2_1-solution000012.solution b/tests/exhaustive/basic/streamline01/expected/model_2_2_1_2_1-solution000012.solution deleted file mode 100644 index b33ee31e23..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_2_1_2_1-solution000012.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 2, 2 --> 2) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_2_1_2_1.eprime b/tests/exhaustive/basic/streamline01/expected/model_2_2_1_2_1.eprime deleted file mode 100644 index bdb507be26..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_2_1_2_1.eprime +++ /dev/null @@ -1,20 +0,0 @@ -language ESSENCE' 1.0 - -find f_Function1DPartial_Flags: matrix indexed by [int(1..2)] of bool -find f_Function1DPartial_Values: matrix indexed by [int(1..2)] of int(1..2) -letting let1 be 1 -find s_Explicit: matrix indexed by [int(1)] of int(1..2) -find s_Occurrence: matrix indexed by [int(1..2)] of bool -branching on [f_Function1DPartial_Flags, f_Function1DPartial_Values, s_Occurrence, s_Explicit] -such that - f_Function1DPartial_Flags[s_Explicit[1]], - and([s_Occurrence[i] /\ i != s_Explicit[1] -> - and([f_Function1DPartial_Values[i] > f_Function1DPartial_Values[s_Explicit[1]], f_Function1DPartial_Flags[i], - f_Function1DPartial_Flags[s_Explicit[1]]; - int(1..3)]) - | i : int(1..2)]), - and([f_Function1DPartial_Flags[q3] = false -> f_Function1DPartial_Values[q3] = 1 | q3 : int(1..2)]), - 1 = sum([toInt(s_Occurrence[q6]) | q6 : int(1..2)]), - and([s_Occurrence[q7] -> s_Explicit[1] = q7 | q7 : int(1..2)]), - s_Occurrence[s_Explicit[1]] - diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_2_1_2_2-solution000001.solution b/tests/exhaustive/basic/streamline01/expected/model_2_2_1_2_2-solution000001.solution deleted file mode 100644 index cd31e1020f..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_2_1_2_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(2 --> 1) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_2_1_2_2-solution000002.solution b/tests/exhaustive/basic/streamline01/expected/model_2_2_1_2_2-solution000002.solution deleted file mode 100644 index 2646544d52..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_2_1_2_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(2 --> 2) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_2_1_2_2-solution000003.solution b/tests/exhaustive/basic/streamline01/expected/model_2_2_1_2_2-solution000003.solution deleted file mode 100644 index 6da2c362aa..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_2_1_2_2-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 1) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_2_1_2_2-solution000004.solution b/tests/exhaustive/basic/streamline01/expected/model_2_2_1_2_2-solution000004.solution deleted file mode 100644 index 9fbfa45bad..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_2_1_2_2-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 2) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_2_1_2_2-solution000005.solution b/tests/exhaustive/basic/streamline01/expected/model_2_2_1_2_2-solution000005.solution deleted file mode 100644 index e62a462994..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_2_1_2_2-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 1, 2 --> 1) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_2_1_2_2-solution000006.solution b/tests/exhaustive/basic/streamline01/expected/model_2_2_1_2_2-solution000006.solution deleted file mode 100644 index 77f032a426..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_2_1_2_2-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 1, 2 --> 1) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_2_1_2_2-solution000007.solution b/tests/exhaustive/basic/streamline01/expected/model_2_2_1_2_2-solution000007.solution deleted file mode 100644 index d2200a27b7..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_2_1_2_2-solution000007.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 1, 2 --> 2) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_2_1_2_2-solution000008.solution b/tests/exhaustive/basic/streamline01/expected/model_2_2_1_2_2-solution000008.solution deleted file mode 100644 index 57c81f730c..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_2_1_2_2-solution000008.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 1, 2 --> 2) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_2_1_2_2-solution000009.solution b/tests/exhaustive/basic/streamline01/expected/model_2_2_1_2_2-solution000009.solution deleted file mode 100644 index 03807b7fff..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_2_1_2_2-solution000009.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 2, 2 --> 1) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_2_1_2_2-solution000010.solution b/tests/exhaustive/basic/streamline01/expected/model_2_2_1_2_2-solution000010.solution deleted file mode 100644 index 50857d4142..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_2_1_2_2-solution000010.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 2, 2 --> 1) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_2_1_2_2-solution000011.solution b/tests/exhaustive/basic/streamline01/expected/model_2_2_1_2_2-solution000011.solution deleted file mode 100644 index e00a3c532c..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_2_1_2_2-solution000011.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 2, 2 --> 2) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_2_1_2_2-solution000012.solution b/tests/exhaustive/basic/streamline01/expected/model_2_2_1_2_2-solution000012.solution deleted file mode 100644 index b33ee31e23..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_2_1_2_2-solution000012.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 2, 2 --> 2) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_2_1_2_2.eprime b/tests/exhaustive/basic/streamline01/expected/model_2_2_1_2_2.eprime deleted file mode 100644 index bdb507be26..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_2_1_2_2.eprime +++ /dev/null @@ -1,20 +0,0 @@ -language ESSENCE' 1.0 - -find f_Function1DPartial_Flags: matrix indexed by [int(1..2)] of bool -find f_Function1DPartial_Values: matrix indexed by [int(1..2)] of int(1..2) -letting let1 be 1 -find s_Explicit: matrix indexed by [int(1)] of int(1..2) -find s_Occurrence: matrix indexed by [int(1..2)] of bool -branching on [f_Function1DPartial_Flags, f_Function1DPartial_Values, s_Occurrence, s_Explicit] -such that - f_Function1DPartial_Flags[s_Explicit[1]], - and([s_Occurrence[i] /\ i != s_Explicit[1] -> - and([f_Function1DPartial_Values[i] > f_Function1DPartial_Values[s_Explicit[1]], f_Function1DPartial_Flags[i], - f_Function1DPartial_Flags[s_Explicit[1]]; - int(1..3)]) - | i : int(1..2)]), - and([f_Function1DPartial_Flags[q3] = false -> f_Function1DPartial_Values[q3] = 1 | q3 : int(1..2)]), - 1 = sum([toInt(s_Occurrence[q6]) | q6 : int(1..2)]), - and([s_Occurrence[q7] -> s_Explicit[1] = q7 | q7 : int(1..2)]), - s_Occurrence[s_Explicit[1]] - diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_2_2_1_1-solution000001.solution b/tests/exhaustive/basic/streamline01/expected/model_2_2_2_1_1-solution000001.solution deleted file mode 100644 index cd31e1020f..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_2_2_1_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(2 --> 1) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_2_2_1_1-solution000002.solution b/tests/exhaustive/basic/streamline01/expected/model_2_2_2_1_1-solution000002.solution deleted file mode 100644 index 2646544d52..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_2_2_1_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(2 --> 2) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_2_2_1_1-solution000003.solution b/tests/exhaustive/basic/streamline01/expected/model_2_2_2_1_1-solution000003.solution deleted file mode 100644 index 6da2c362aa..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_2_2_1_1-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 1) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_2_2_1_1-solution000004.solution b/tests/exhaustive/basic/streamline01/expected/model_2_2_2_1_1-solution000004.solution deleted file mode 100644 index 9fbfa45bad..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_2_2_1_1-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 2) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_2_2_1_1-solution000005.solution b/tests/exhaustive/basic/streamline01/expected/model_2_2_2_1_1-solution000005.solution deleted file mode 100644 index e62a462994..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_2_2_1_1-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 1, 2 --> 1) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_2_2_1_1-solution000006.solution b/tests/exhaustive/basic/streamline01/expected/model_2_2_2_1_1-solution000006.solution deleted file mode 100644 index 77f032a426..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_2_2_1_1-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 1, 2 --> 1) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_2_2_1_1-solution000007.solution b/tests/exhaustive/basic/streamline01/expected/model_2_2_2_1_1-solution000007.solution deleted file mode 100644 index d2200a27b7..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_2_2_1_1-solution000007.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 1, 2 --> 2) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_2_2_1_1-solution000008.solution b/tests/exhaustive/basic/streamline01/expected/model_2_2_2_1_1-solution000008.solution deleted file mode 100644 index 57c81f730c..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_2_2_1_1-solution000008.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 1, 2 --> 2) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_2_2_1_1-solution000009.solution b/tests/exhaustive/basic/streamline01/expected/model_2_2_2_1_1-solution000009.solution deleted file mode 100644 index 03807b7fff..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_2_2_1_1-solution000009.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 2, 2 --> 1) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_2_2_1_1-solution000010.solution b/tests/exhaustive/basic/streamline01/expected/model_2_2_2_1_1-solution000010.solution deleted file mode 100644 index 50857d4142..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_2_2_1_1-solution000010.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 2, 2 --> 1) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_2_2_1_1-solution000011.solution b/tests/exhaustive/basic/streamline01/expected/model_2_2_2_1_1-solution000011.solution deleted file mode 100644 index e00a3c532c..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_2_2_1_1-solution000011.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 2, 2 --> 2) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_2_2_1_1-solution000012.solution b/tests/exhaustive/basic/streamline01/expected/model_2_2_2_1_1-solution000012.solution deleted file mode 100644 index b33ee31e23..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_2_2_1_1-solution000012.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 2, 2 --> 2) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_2_2_1_1.eprime b/tests/exhaustive/basic/streamline01/expected/model_2_2_2_1_1.eprime deleted file mode 100644 index 17b512d97d..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_2_2_1_1.eprime +++ /dev/null @@ -1,24 +0,0 @@ -language ESSENCE' 1.0 - -find f_Function1DPartial_Flags: matrix indexed by [int(1..2)] of bool -find f_Function1DPartial_Values: matrix indexed by [int(1..2)] of int(1..2) -letting let1 be 1 -find s_Explicit: matrix indexed by [int(1)] of int(1..2) -find s_Occurrence: matrix indexed by [int(1..2)] of bool -find conjure_aux1: int(1..2) -branching on [f_Function1DPartial_Flags, f_Function1DPartial_Values, s_Occurrence, s_Explicit] -such that - f_Function1DPartial_Flags[s_Explicit[1]], - and([s_Occurrence[q13] -> q13 >= conjure_aux1 | q13 : int(1..2)]), - sum([toInt(s_Occurrence[q13]) | q13 : int(1..2)]) > 0 -> - or([s_Occurrence[q13] /\ q13 = conjure_aux1 | q13 : int(1..2)]), - sum([toInt(s_Occurrence[q13]) | q13 : int(1..2)]) = 0 -> conjure_aux1 = 1, - s_Explicit[1] != conjure_aux1 /\ sum([toInt(s_Occurrence[q13]) | q13 : int(1..2)]) > 0 -> - and([f_Function1DPartial_Values[s_Explicit[1]] > f_Function1DPartial_Values[s_Explicit[1]], - f_Function1DPartial_Flags[s_Explicit[1]], f_Function1DPartial_Flags[s_Explicit[1]]; - int(1..3)]), - and([f_Function1DPartial_Flags[q3] = false -> f_Function1DPartial_Values[q3] = 1 | q3 : int(1..2)]), - 1 = sum([toInt(s_Occurrence[q6]) | q6 : int(1..2)]), - and([s_Occurrence[q7] -> s_Explicit[1] = q7 | q7 : int(1..2)]), - s_Occurrence[s_Explicit[1]] - diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_2_2_1_2-solution000001.solution b/tests/exhaustive/basic/streamline01/expected/model_2_2_2_1_2-solution000001.solution deleted file mode 100644 index cd31e1020f..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_2_2_1_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(2 --> 1) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_2_2_1_2-solution000002.solution b/tests/exhaustive/basic/streamline01/expected/model_2_2_2_1_2-solution000002.solution deleted file mode 100644 index 2646544d52..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_2_2_1_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(2 --> 2) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_2_2_1_2-solution000003.solution b/tests/exhaustive/basic/streamline01/expected/model_2_2_2_1_2-solution000003.solution deleted file mode 100644 index 6da2c362aa..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_2_2_1_2-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 1) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_2_2_1_2-solution000004.solution b/tests/exhaustive/basic/streamline01/expected/model_2_2_2_1_2-solution000004.solution deleted file mode 100644 index 9fbfa45bad..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_2_2_1_2-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 2) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_2_2_1_2-solution000005.solution b/tests/exhaustive/basic/streamline01/expected/model_2_2_2_1_2-solution000005.solution deleted file mode 100644 index e62a462994..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_2_2_1_2-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 1, 2 --> 1) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_2_2_1_2-solution000006.solution b/tests/exhaustive/basic/streamline01/expected/model_2_2_2_1_2-solution000006.solution deleted file mode 100644 index 77f032a426..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_2_2_1_2-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 1, 2 --> 1) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_2_2_1_2-solution000007.solution b/tests/exhaustive/basic/streamline01/expected/model_2_2_2_1_2-solution000007.solution deleted file mode 100644 index d2200a27b7..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_2_2_1_2-solution000007.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 1, 2 --> 2) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_2_2_1_2-solution000008.solution b/tests/exhaustive/basic/streamline01/expected/model_2_2_2_1_2-solution000008.solution deleted file mode 100644 index 57c81f730c..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_2_2_1_2-solution000008.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 1, 2 --> 2) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_2_2_1_2-solution000009.solution b/tests/exhaustive/basic/streamline01/expected/model_2_2_2_1_2-solution000009.solution deleted file mode 100644 index 03807b7fff..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_2_2_1_2-solution000009.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 2, 2 --> 1) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_2_2_1_2-solution000010.solution b/tests/exhaustive/basic/streamline01/expected/model_2_2_2_1_2-solution000010.solution deleted file mode 100644 index 50857d4142..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_2_2_1_2-solution000010.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 2, 2 --> 1) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_2_2_1_2-solution000011.solution b/tests/exhaustive/basic/streamline01/expected/model_2_2_2_1_2-solution000011.solution deleted file mode 100644 index e00a3c532c..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_2_2_1_2-solution000011.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 2, 2 --> 2) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_2_2_1_2-solution000012.solution b/tests/exhaustive/basic/streamline01/expected/model_2_2_2_1_2-solution000012.solution deleted file mode 100644 index b33ee31e23..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_2_2_1_2-solution000012.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 2, 2 --> 2) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_2_2_1_2.eprime b/tests/exhaustive/basic/streamline01/expected/model_2_2_2_1_2.eprime deleted file mode 100644 index 17b512d97d..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_2_2_1_2.eprime +++ /dev/null @@ -1,24 +0,0 @@ -language ESSENCE' 1.0 - -find f_Function1DPartial_Flags: matrix indexed by [int(1..2)] of bool -find f_Function1DPartial_Values: matrix indexed by [int(1..2)] of int(1..2) -letting let1 be 1 -find s_Explicit: matrix indexed by [int(1)] of int(1..2) -find s_Occurrence: matrix indexed by [int(1..2)] of bool -find conjure_aux1: int(1..2) -branching on [f_Function1DPartial_Flags, f_Function1DPartial_Values, s_Occurrence, s_Explicit] -such that - f_Function1DPartial_Flags[s_Explicit[1]], - and([s_Occurrence[q13] -> q13 >= conjure_aux1 | q13 : int(1..2)]), - sum([toInt(s_Occurrence[q13]) | q13 : int(1..2)]) > 0 -> - or([s_Occurrence[q13] /\ q13 = conjure_aux1 | q13 : int(1..2)]), - sum([toInt(s_Occurrence[q13]) | q13 : int(1..2)]) = 0 -> conjure_aux1 = 1, - s_Explicit[1] != conjure_aux1 /\ sum([toInt(s_Occurrence[q13]) | q13 : int(1..2)]) > 0 -> - and([f_Function1DPartial_Values[s_Explicit[1]] > f_Function1DPartial_Values[s_Explicit[1]], - f_Function1DPartial_Flags[s_Explicit[1]], f_Function1DPartial_Flags[s_Explicit[1]]; - int(1..3)]), - and([f_Function1DPartial_Flags[q3] = false -> f_Function1DPartial_Values[q3] = 1 | q3 : int(1..2)]), - 1 = sum([toInt(s_Occurrence[q6]) | q6 : int(1..2)]), - and([s_Occurrence[q7] -> s_Explicit[1] = q7 | q7 : int(1..2)]), - s_Occurrence[s_Explicit[1]] - diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_2_2_2_1-solution000001.solution b/tests/exhaustive/basic/streamline01/expected/model_2_2_2_2_1-solution000001.solution deleted file mode 100644 index cd31e1020f..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_2_2_2_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(2 --> 1) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_2_2_2_1-solution000002.solution b/tests/exhaustive/basic/streamline01/expected/model_2_2_2_2_1-solution000002.solution deleted file mode 100644 index 2646544d52..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_2_2_2_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(2 --> 2) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_2_2_2_1-solution000003.solution b/tests/exhaustive/basic/streamline01/expected/model_2_2_2_2_1-solution000003.solution deleted file mode 100644 index 6da2c362aa..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_2_2_2_1-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 1) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_2_2_2_1-solution000004.solution b/tests/exhaustive/basic/streamline01/expected/model_2_2_2_2_1-solution000004.solution deleted file mode 100644 index 9fbfa45bad..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_2_2_2_1-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 2) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_2_2_2_1-solution000005.solution b/tests/exhaustive/basic/streamline01/expected/model_2_2_2_2_1-solution000005.solution deleted file mode 100644 index e62a462994..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_2_2_2_1-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 1, 2 --> 1) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_2_2_2_1-solution000006.solution b/tests/exhaustive/basic/streamline01/expected/model_2_2_2_2_1-solution000006.solution deleted file mode 100644 index 77f032a426..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_2_2_2_1-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 1, 2 --> 1) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_2_2_2_1-solution000007.solution b/tests/exhaustive/basic/streamline01/expected/model_2_2_2_2_1-solution000007.solution deleted file mode 100644 index d2200a27b7..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_2_2_2_1-solution000007.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 1, 2 --> 2) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_2_2_2_1-solution000008.solution b/tests/exhaustive/basic/streamline01/expected/model_2_2_2_2_1-solution000008.solution deleted file mode 100644 index 57c81f730c..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_2_2_2_1-solution000008.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 1, 2 --> 2) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_2_2_2_1-solution000009.solution b/tests/exhaustive/basic/streamline01/expected/model_2_2_2_2_1-solution000009.solution deleted file mode 100644 index 03807b7fff..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_2_2_2_1-solution000009.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 2, 2 --> 1) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_2_2_2_1-solution000010.solution b/tests/exhaustive/basic/streamline01/expected/model_2_2_2_2_1-solution000010.solution deleted file mode 100644 index 50857d4142..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_2_2_2_1-solution000010.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 2, 2 --> 1) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_2_2_2_1-solution000011.solution b/tests/exhaustive/basic/streamline01/expected/model_2_2_2_2_1-solution000011.solution deleted file mode 100644 index e00a3c532c..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_2_2_2_1-solution000011.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 2, 2 --> 2) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_2_2_2_1-solution000012.solution b/tests/exhaustive/basic/streamline01/expected/model_2_2_2_2_1-solution000012.solution deleted file mode 100644 index b33ee31e23..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_2_2_2_1-solution000012.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 2, 2 --> 2) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_2_2_2_1.eprime b/tests/exhaustive/basic/streamline01/expected/model_2_2_2_2_1.eprime deleted file mode 100644 index e3acdc0c7a..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_2_2_2_1.eprime +++ /dev/null @@ -1,19 +0,0 @@ -language ESSENCE' 1.0 - -find f_Function1DPartial_Flags: matrix indexed by [int(1..2)] of bool -find f_Function1DPartial_Values: matrix indexed by [int(1..2)] of int(1..2) -letting let1 be 1 -find s_Explicit: matrix indexed by [int(1)] of int(1..2) -find s_Occurrence: matrix indexed by [int(1..2)] of bool -branching on [f_Function1DPartial_Flags, f_Function1DPartial_Values, s_Occurrence, s_Explicit] -such that - f_Function1DPartial_Flags[s_Explicit[1]], - s_Explicit[1] != s_Explicit[1] -> - and([f_Function1DPartial_Values[s_Explicit[1]] > f_Function1DPartial_Values[s_Explicit[1]], - f_Function1DPartial_Flags[s_Explicit[1]], f_Function1DPartial_Flags[s_Explicit[1]]; - int(1..3)]), - and([f_Function1DPartial_Flags[q3] = false -> f_Function1DPartial_Values[q3] = 1 | q3 : int(1..2)]), - 1 = sum([toInt(s_Occurrence[q6]) | q6 : int(1..2)]), - and([s_Occurrence[q7] -> s_Explicit[1] = q7 | q7 : int(1..2)]), - s_Occurrence[s_Explicit[1]] - diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_2_2_2_2-solution000001.solution b/tests/exhaustive/basic/streamline01/expected/model_2_2_2_2_2-solution000001.solution deleted file mode 100644 index cd31e1020f..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_2_2_2_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(2 --> 1) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_2_2_2_2-solution000002.solution b/tests/exhaustive/basic/streamline01/expected/model_2_2_2_2_2-solution000002.solution deleted file mode 100644 index 2646544d52..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_2_2_2_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(2 --> 2) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_2_2_2_2-solution000003.solution b/tests/exhaustive/basic/streamline01/expected/model_2_2_2_2_2-solution000003.solution deleted file mode 100644 index 6da2c362aa..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_2_2_2_2-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 1) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_2_2_2_2-solution000004.solution b/tests/exhaustive/basic/streamline01/expected/model_2_2_2_2_2-solution000004.solution deleted file mode 100644 index 9fbfa45bad..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_2_2_2_2-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 2) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_2_2_2_2-solution000005.solution b/tests/exhaustive/basic/streamline01/expected/model_2_2_2_2_2-solution000005.solution deleted file mode 100644 index 77f032a426..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_2_2_2_2-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 1, 2 --> 1) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_2_2_2_2-solution000006.solution b/tests/exhaustive/basic/streamline01/expected/model_2_2_2_2_2-solution000006.solution deleted file mode 100644 index e62a462994..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_2_2_2_2-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 1, 2 --> 1) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_2_2_2_2-solution000007.solution b/tests/exhaustive/basic/streamline01/expected/model_2_2_2_2_2-solution000007.solution deleted file mode 100644 index 57c81f730c..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_2_2_2_2-solution000007.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 1, 2 --> 2) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_2_2_2_2-solution000008.solution b/tests/exhaustive/basic/streamline01/expected/model_2_2_2_2_2-solution000008.solution deleted file mode 100644 index d2200a27b7..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_2_2_2_2-solution000008.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 1, 2 --> 2) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_2_2_2_2-solution000009.solution b/tests/exhaustive/basic/streamline01/expected/model_2_2_2_2_2-solution000009.solution deleted file mode 100644 index 50857d4142..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_2_2_2_2-solution000009.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 2, 2 --> 1) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_2_2_2_2-solution000010.solution b/tests/exhaustive/basic/streamline01/expected/model_2_2_2_2_2-solution000010.solution deleted file mode 100644 index 03807b7fff..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_2_2_2_2-solution000010.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 2, 2 --> 1) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_2_2_2_2-solution000011.solution b/tests/exhaustive/basic/streamline01/expected/model_2_2_2_2_2-solution000011.solution deleted file mode 100644 index b33ee31e23..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_2_2_2_2-solution000011.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 2, 2 --> 2) -letting s be {1} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_2_2_2_2-solution000012.solution b/tests/exhaustive/basic/streamline01/expected/model_2_2_2_2_2-solution000012.solution deleted file mode 100644 index e00a3c532c..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_2_2_2_2-solution000012.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting f be function(1 --> 2, 2 --> 2) -letting s be {2} diff --git a/tests/exhaustive/basic/streamline01/expected/model_2_2_2_2_2.eprime b/tests/exhaustive/basic/streamline01/expected/model_2_2_2_2_2.eprime deleted file mode 100644 index 06cff1401b..0000000000 --- a/tests/exhaustive/basic/streamline01/expected/model_2_2_2_2_2.eprime +++ /dev/null @@ -1,15 +0,0 @@ -language ESSENCE' 1.0 - -find f_Function1DPartial_Flags: matrix indexed by [int(1..2)] of bool -find f_Function1DPartial_Values: matrix indexed by [int(1..2)] of int(1..2) -letting let1 be 1 -find s_Explicit: matrix indexed by [int(1)] of int(1..2) -branching on [f_Function1DPartial_Flags, f_Function1DPartial_Values, s_Explicit] -such that - f_Function1DPartial_Flags[s_Explicit[1]], - s_Explicit[1] != s_Explicit[1] -> - and([f_Function1DPartial_Values[s_Explicit[1]] > f_Function1DPartial_Values[s_Explicit[1]], - f_Function1DPartial_Flags[s_Explicit[1]], f_Function1DPartial_Flags[s_Explicit[1]]; - int(1..3)]), - and([f_Function1DPartial_Flags[q3] = false -> f_Function1DPartial_Values[q3] = 1 | q3 : int(1..2)]) - diff --git a/tests/exhaustive/basic/typed01/expected/model_1_1_1_1-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_1_1_1_1-solution000001.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_1_1_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_1_1_1-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_1_1_1_1-solution000002.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_1_1_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_1_1_1-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_1_1_1_1-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_1_1_1-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_1_1_1.eprime b/tests/exhaustive/basic/typed01/expected/model_1_1_1_1.eprime deleted file mode 100644 index 94c0d2b627..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_1_1_1.eprime +++ /dev/null @@ -1,7 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1)] of bool -find y_Occurrence: matrix indexed by [int(1)] of bool -branching on [x_Occurrence, y_Occurrence] -such that x_Occurrence[1] /\ y_Occurrence[1] -> false - diff --git a/tests/exhaustive/basic/typed01/expected/model_1_1_1_2-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_1_1_1_2-solution000001.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_1_1_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_1_1_2-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_1_1_1_2-solution000002.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_1_1_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_1_1_2-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_1_1_1_2-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_1_1_2-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_1_1_2.eprime b/tests/exhaustive/basic/typed01/expected/model_1_1_1_2.eprime deleted file mode 100644 index bdbab746fd..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_1_1_2.eprime +++ /dev/null @@ -1,11 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1)] of bool -find y_Occurrence: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -branching on [x_Occurrence, y_ExplicitVarSizeWithDummy, y_Occurrence] -such that - x_Occurrence[1] /\ y_Occurrence[1] -> false, - y_ExplicitVarSizeWithDummy[1] != 2 -> y_Occurrence[y_ExplicitVarSizeWithDummy[1]], - y_Occurrence[1] -> y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = 1 - diff --git a/tests/exhaustive/basic/typed01/expected/model_1_1_1_3-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_1_1_1_3-solution000001.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_1_1_3-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_1_1_3-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_1_1_1_3-solution000002.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_1_1_3-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_1_1_3-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_1_1_1_3-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_1_1_3-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_1_1_3.eprime b/tests/exhaustive/basic/typed01/expected/model_1_1_1_3.eprime deleted file mode 100644 index c168e1afc0..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_1_1_3.eprime +++ /dev/null @@ -1,13 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1)] of bool -find y_Occurrence: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithMarker_Marker: int(0..1) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -branching on [x_Occurrence, y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values, y_Occurrence] -such that - x_Occurrence[1] /\ y_Occurrence[1] -> false, - 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, - 1 <= y_ExplicitVarSizeWithMarker_Marker -> y_Occurrence[y_ExplicitVarSizeWithMarker_Values[1]], - y_Occurrence[1] -> 1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = 1 - diff --git a/tests/exhaustive/basic/typed01/expected/model_1_1_1_4-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_1_1_1_4-solution000001.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_1_1_4-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_1_1_4-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_1_1_1_4-solution000002.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_1_1_4-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_1_1_4-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_1_1_1_4-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_1_1_4-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_1_1_4.eprime b/tests/exhaustive/basic/typed01/expected/model_1_1_1_4.eprime deleted file mode 100644 index f0ddb80973..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_1_1_4.eprime +++ /dev/null @@ -1,13 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1)] of bool -find y_Occurrence: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -branching on [x_Occurrence, y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values, y_Occurrence] -such that - x_Occurrence[1] /\ y_Occurrence[1] -> false, - y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, - y_ExplicitVarSizeWithFlags_Flags[1] -> y_Occurrence[y_ExplicitVarSizeWithFlags_Values[1]], - y_Occurrence[1] -> y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = 1 - diff --git a/tests/exhaustive/basic/typed01/expected/model_1_1_2_1-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_1_1_2_1-solution000001.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_1_2_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_1_2_1-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_1_1_2_1-solution000002.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_1_2_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_1_2_1-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_1_1_2_1-solution000003.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_1_2_1-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_1_2_1.eprime b/tests/exhaustive/basic/typed01/expected/model_1_1_2_1.eprime deleted file mode 100644 index 0b9c355d3a..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_1_2_1.eprime +++ /dev/null @@ -1,11 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1)] of bool -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -find y_Occurrence: matrix indexed by [int(1)] of bool -branching on [x_ExplicitVarSizeWithDummy, x_Occurrence, y_Occurrence] -such that - x_Occurrence[1] /\ y_Occurrence[1] -> false, - x_ExplicitVarSizeWithDummy[1] != 2 -> x_Occurrence[x_ExplicitVarSizeWithDummy[1]], - x_Occurrence[1] -> x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = 1 - diff --git a/tests/exhaustive/basic/typed01/expected/model_1_1_2_2-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_1_1_2_2-solution000001.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_1_2_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_1_2_2-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_1_1_2_2-solution000002.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_1_2_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_1_2_2-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_1_1_2_2-solution000003.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_1_2_2-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_1_2_2.eprime b/tests/exhaustive/basic/typed01/expected/model_1_1_2_2.eprime deleted file mode 100644 index 927eca8795..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_1_2_2.eprime +++ /dev/null @@ -1,14 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1)] of bool -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -find y_Occurrence: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -branching on [x_ExplicitVarSizeWithDummy, x_Occurrence, y_ExplicitVarSizeWithDummy, y_Occurrence] -such that - x_Occurrence[1] /\ y_Occurrence[1] -> false, - x_ExplicitVarSizeWithDummy[1] != 2 -> x_Occurrence[x_ExplicitVarSizeWithDummy[1]], - x_Occurrence[1] -> x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = 1, - y_ExplicitVarSizeWithDummy[1] != 2 -> y_Occurrence[y_ExplicitVarSizeWithDummy[1]], - y_Occurrence[1] -> y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = 1 - diff --git a/tests/exhaustive/basic/typed01/expected/model_1_1_2_3-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_1_1_2_3-solution000001.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_1_2_3-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_1_2_3-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_1_1_2_3-solution000002.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_1_2_3-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_1_2_3-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_1_1_2_3-solution000003.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_1_2_3-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_1_2_3.eprime b/tests/exhaustive/basic/typed01/expected/model_1_1_2_3.eprime deleted file mode 100644 index 56aa03eb37..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_1_2_3.eprime +++ /dev/null @@ -1,18 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1)] of bool -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -find y_Occurrence: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithMarker_Marker: int(0..1) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -branching on - [x_ExplicitVarSizeWithDummy, x_Occurrence, y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values, - y_Occurrence] -such that - x_Occurrence[1] /\ y_Occurrence[1] -> false, - x_ExplicitVarSizeWithDummy[1] != 2 -> x_Occurrence[x_ExplicitVarSizeWithDummy[1]], - x_Occurrence[1] -> x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = 1, - 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, - 1 <= y_ExplicitVarSizeWithMarker_Marker -> y_Occurrence[y_ExplicitVarSizeWithMarker_Values[1]], - y_Occurrence[1] -> 1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = 1 - diff --git a/tests/exhaustive/basic/typed01/expected/model_1_1_2_4-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_1_1_2_4-solution000001.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_1_2_4-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_1_2_4-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_1_1_2_4-solution000002.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_1_2_4-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_1_2_4-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_1_1_2_4-solution000003.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_1_2_4-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_1_2_4.eprime b/tests/exhaustive/basic/typed01/expected/model_1_1_2_4.eprime deleted file mode 100644 index 2feadc3613..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_1_2_4.eprime +++ /dev/null @@ -1,18 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1)] of bool -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -find y_Occurrence: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -branching on - [x_ExplicitVarSizeWithDummy, x_Occurrence, y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values, - y_Occurrence] -such that - x_Occurrence[1] /\ y_Occurrence[1] -> false, - x_ExplicitVarSizeWithDummy[1] != 2 -> x_Occurrence[x_ExplicitVarSizeWithDummy[1]], - x_Occurrence[1] -> x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = 1, - y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, - y_ExplicitVarSizeWithFlags_Flags[1] -> y_Occurrence[y_ExplicitVarSizeWithFlags_Values[1]], - y_Occurrence[1] -> y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = 1 - diff --git a/tests/exhaustive/basic/typed01/expected/model_1_1_3_1-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_1_1_3_1-solution000001.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_1_3_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_1_3_1-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_1_1_3_1-solution000002.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_1_3_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_1_3_1-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_1_1_3_1-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_1_3_1-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_1_3_1.eprime b/tests/exhaustive/basic/typed01/expected/model_1_1_3_1.eprime deleted file mode 100644 index 2c5a058d3e..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_1_3_1.eprime +++ /dev/null @@ -1,13 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1)] of bool -find x_ExplicitVarSizeWithMarker_Marker: int(0..1) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -find y_Occurrence: matrix indexed by [int(1)] of bool -branching on [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_Occurrence, y_Occurrence] -such that - x_Occurrence[1] /\ y_Occurrence[1] -> false, - 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, - 1 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[1]], - x_Occurrence[1] -> 1 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[1] = 1 - diff --git a/tests/exhaustive/basic/typed01/expected/model_1_1_3_2-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_1_1_3_2-solution000001.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_1_3_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_1_3_2-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_1_1_3_2-solution000002.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_1_3_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_1_3_2-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_1_1_3_2-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_1_3_2-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_1_3_2.eprime b/tests/exhaustive/basic/typed01/expected/model_1_1_3_2.eprime deleted file mode 100644 index 79607aae8e..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_1_3_2.eprime +++ /dev/null @@ -1,18 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1)] of bool -find x_ExplicitVarSizeWithMarker_Marker: int(0..1) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -find y_Occurrence: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_Occurrence, y_ExplicitVarSizeWithDummy, - y_Occurrence] -such that - x_Occurrence[1] /\ y_Occurrence[1] -> false, - 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, - 1 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[1]], - x_Occurrence[1] -> 1 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[1] = 1, - y_ExplicitVarSizeWithDummy[1] != 2 -> y_Occurrence[y_ExplicitVarSizeWithDummy[1]], - y_Occurrence[1] -> y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = 1 - diff --git a/tests/exhaustive/basic/typed01/expected/model_1_1_3_3-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_1_1_3_3-solution000001.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_1_3_3-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_1_3_3-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_1_1_3_3-solution000002.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_1_3_3-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_1_3_3-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_1_1_3_3-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_1_3_3-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_1_3_3.eprime b/tests/exhaustive/basic/typed01/expected/model_1_1_3_3.eprime deleted file mode 100644 index e4c42fc2e4..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_1_3_3.eprime +++ /dev/null @@ -1,20 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1)] of bool -find x_ExplicitVarSizeWithMarker_Marker: int(0..1) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -find y_Occurrence: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithMarker_Marker: int(0..1) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_Occurrence, - y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values, y_Occurrence] -such that - x_Occurrence[1] /\ y_Occurrence[1] -> false, - 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, - 1 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[1]], - x_Occurrence[1] -> 1 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[1] = 1, - 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, - 1 <= y_ExplicitVarSizeWithMarker_Marker -> y_Occurrence[y_ExplicitVarSizeWithMarker_Values[1]], - y_Occurrence[1] -> 1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = 1 - diff --git a/tests/exhaustive/basic/typed01/expected/model_1_1_3_4-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_1_1_3_4-solution000001.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_1_3_4-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_1_3_4-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_1_1_3_4-solution000002.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_1_3_4-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_1_3_4-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_1_1_3_4-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_1_3_4-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_1_3_4.eprime b/tests/exhaustive/basic/typed01/expected/model_1_1_3_4.eprime deleted file mode 100644 index 6a78b5ae6b..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_1_3_4.eprime +++ /dev/null @@ -1,20 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1)] of bool -find x_ExplicitVarSizeWithMarker_Marker: int(0..1) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -find y_Occurrence: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_Occurrence, - y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values, y_Occurrence] -such that - x_Occurrence[1] /\ y_Occurrence[1] -> false, - 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, - 1 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[1]], - x_Occurrence[1] -> 1 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[1] = 1, - y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, - y_ExplicitVarSizeWithFlags_Flags[1] -> y_Occurrence[y_ExplicitVarSizeWithFlags_Values[1]], - y_Occurrence[1] -> y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = 1 - diff --git a/tests/exhaustive/basic/typed01/expected/model_1_1_4_1-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_1_1_4_1-solution000001.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_1_4_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_1_4_1-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_1_1_4_1-solution000002.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_1_4_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_1_4_1-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_1_1_4_1-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_1_4_1-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_1_4_1.eprime b/tests/exhaustive/basic/typed01/expected/model_1_1_4_1.eprime deleted file mode 100644 index 4e002eba26..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_1_4_1.eprime +++ /dev/null @@ -1,13 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1)] of bool -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -find y_Occurrence: matrix indexed by [int(1)] of bool -branching on [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_Occurrence, y_Occurrence] -such that - x_Occurrence[1] /\ y_Occurrence[1] -> false, - x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, - x_ExplicitVarSizeWithFlags_Flags[1] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[1]], - x_Occurrence[1] -> x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = 1 - diff --git a/tests/exhaustive/basic/typed01/expected/model_1_1_4_2-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_1_1_4_2-solution000001.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_1_4_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_1_4_2-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_1_1_4_2-solution000002.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_1_4_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_1_4_2-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_1_1_4_2-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_1_4_2-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_1_4_2.eprime b/tests/exhaustive/basic/typed01/expected/model_1_1_4_2.eprime deleted file mode 100644 index 10f0ab252c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_1_4_2.eprime +++ /dev/null @@ -1,18 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1)] of bool -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -find y_Occurrence: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_Occurrence, y_ExplicitVarSizeWithDummy, - y_Occurrence] -such that - x_Occurrence[1] /\ y_Occurrence[1] -> false, - x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, - x_ExplicitVarSizeWithFlags_Flags[1] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[1]], - x_Occurrence[1] -> x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = 1, - y_ExplicitVarSizeWithDummy[1] != 2 -> y_Occurrence[y_ExplicitVarSizeWithDummy[1]], - y_Occurrence[1] -> y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = 1 - diff --git a/tests/exhaustive/basic/typed01/expected/model_1_1_4_3-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_1_1_4_3-solution000001.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_1_4_3-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_1_4_3-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_1_1_4_3-solution000002.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_1_4_3-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_1_4_3-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_1_1_4_3-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_1_4_3-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_1_4_3.eprime b/tests/exhaustive/basic/typed01/expected/model_1_1_4_3.eprime deleted file mode 100644 index bec813d72f..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_1_4_3.eprime +++ /dev/null @@ -1,20 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1)] of bool -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -find y_Occurrence: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithMarker_Marker: int(0..1) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_Occurrence, - y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values, y_Occurrence] -such that - x_Occurrence[1] /\ y_Occurrence[1] -> false, - x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, - x_ExplicitVarSizeWithFlags_Flags[1] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[1]], - x_Occurrence[1] -> x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = 1, - 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, - 1 <= y_ExplicitVarSizeWithMarker_Marker -> y_Occurrence[y_ExplicitVarSizeWithMarker_Values[1]], - y_Occurrence[1] -> 1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = 1 - diff --git a/tests/exhaustive/basic/typed01/expected/model_1_1_4_4-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_1_1_4_4-solution000001.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_1_4_4-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_1_4_4-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_1_1_4_4-solution000002.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_1_4_4-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_1_4_4-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_1_1_4_4-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_1_4_4-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_1_4_4.eprime b/tests/exhaustive/basic/typed01/expected/model_1_1_4_4.eprime deleted file mode 100644 index 3d1696bc7d..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_1_4_4.eprime +++ /dev/null @@ -1,20 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1)] of bool -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -find y_Occurrence: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_Occurrence, - y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values, y_Occurrence] -such that - x_Occurrence[1] /\ y_Occurrence[1] -> false, - x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, - x_ExplicitVarSizeWithFlags_Flags[1] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[1]], - x_Occurrence[1] -> x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = 1, - y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, - y_ExplicitVarSizeWithFlags_Flags[1] -> y_Occurrence[y_ExplicitVarSizeWithFlags_Values[1]], - y_Occurrence[1] -> y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = 1 - diff --git a/tests/exhaustive/basic/typed01/expected/model_1_2_1_1-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_1_2_1_1-solution000001.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_2_1_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_2_1_1-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_1_2_1_1-solution000002.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_2_1_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_2_1_1-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_1_2_1_1-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_2_1_1-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_2_1_1.eprime b/tests/exhaustive/basic/typed01/expected/model_1_2_1_1.eprime deleted file mode 100644 index a11e9dfe09..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_2_1_1.eprime +++ /dev/null @@ -1,11 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -find y_Occurrence: matrix indexed by [int(1)] of bool -branching on [x_Occurrence, y_Occurrence, y_ExplicitVarSizeWithDummy] -such that - x_Occurrence[1] /\ (y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = 1) -> false, - y_Occurrence[1] -> y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = 1, - y_ExplicitVarSizeWithDummy[1] != 2 -> y_Occurrence[y_ExplicitVarSizeWithDummy[1]] - diff --git a/tests/exhaustive/basic/typed01/expected/model_1_2_1_2-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_1_2_1_2-solution000001.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_2_1_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_2_1_2-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_1_2_1_2-solution000002.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_2_1_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_2_1_2-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_1_2_1_2-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_2_1_2-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_2_1_2.eprime b/tests/exhaustive/basic/typed01/expected/model_1_2_1_2.eprime deleted file mode 100644 index f2ff753504..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_2_1_2.eprime +++ /dev/null @@ -1,7 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -branching on [x_Occurrence, y_ExplicitVarSizeWithDummy] -such that x_Occurrence[1] /\ (y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = 1) -> false - diff --git a/tests/exhaustive/basic/typed01/expected/model_1_2_1_3-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_1_2_1_3-solution000001.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_2_1_3-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_2_1_3-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_1_2_1_3-solution000002.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_2_1_3-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_2_1_3-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_1_2_1_3-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_2_1_3-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_2_1_3.eprime b/tests/exhaustive/basic/typed01/expected/model_1_2_1_3.eprime deleted file mode 100644 index 1efda9ae16..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_2_1_3.eprime +++ /dev/null @@ -1,16 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -find y_ExplicitVarSizeWithMarker_Marker: int(0..1) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -branching on - [x_Occurrence, y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithDummy] -such that - x_Occurrence[1] /\ (y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = 1) -> false, - 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, - 1 <= y_ExplicitVarSizeWithMarker_Marker -> - y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = y_ExplicitVarSizeWithMarker_Values[1], - y_ExplicitVarSizeWithDummy[1] != 2 -> - 1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = y_ExplicitVarSizeWithDummy[1] - diff --git a/tests/exhaustive/basic/typed01/expected/model_1_2_1_4-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_1_2_1_4-solution000001.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_2_1_4-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_2_1_4-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_1_2_1_4-solution000002.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_2_1_4-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_2_1_4-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_1_2_1_4-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_2_1_4-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_2_1_4.eprime b/tests/exhaustive/basic/typed01/expected/model_1_2_1_4.eprime deleted file mode 100644 index afe11ceafd..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_2_1_4.eprime +++ /dev/null @@ -1,16 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -branching on - [x_Occurrence, y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithDummy] -such that - x_Occurrence[1] /\ (y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = 1) -> false, - y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, - y_ExplicitVarSizeWithFlags_Flags[1] -> - y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = y_ExplicitVarSizeWithFlags_Values[1], - y_ExplicitVarSizeWithDummy[1] != 2 -> - y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = y_ExplicitVarSizeWithDummy[1] - diff --git a/tests/exhaustive/basic/typed01/expected/model_1_2_2_1-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_1_2_2_1-solution000001.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_2_2_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_2_2_1-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_1_2_2_1-solution000002.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_2_2_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_2_2_1-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_1_2_2_1-solution000003.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_2_2_1-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_2_2_1.eprime b/tests/exhaustive/basic/typed01/expected/model_1_2_2_1.eprime deleted file mode 100644 index 19621229d3..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_2_2_1.eprime +++ /dev/null @@ -1,14 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1)] of bool -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -find y_Occurrence: matrix indexed by [int(1)] of bool -branching on [x_ExplicitVarSizeWithDummy, x_Occurrence, y_Occurrence, y_ExplicitVarSizeWithDummy] -such that - x_Occurrence[1] /\ (y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = 1) -> false, - x_ExplicitVarSizeWithDummy[1] != 2 -> x_Occurrence[x_ExplicitVarSizeWithDummy[1]], - x_Occurrence[1] -> x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = 1, - y_Occurrence[1] -> y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = 1, - y_ExplicitVarSizeWithDummy[1] != 2 -> y_Occurrence[y_ExplicitVarSizeWithDummy[1]] - diff --git a/tests/exhaustive/basic/typed01/expected/model_1_2_2_2-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_1_2_2_2-solution000001.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_2_2_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_2_2_2-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_1_2_2_2-solution000002.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_2_2_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_2_2_2-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_1_2_2_2-solution000003.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_2_2_2-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_2_2_2.eprime b/tests/exhaustive/basic/typed01/expected/model_1_2_2_2.eprime deleted file mode 100644 index 598c4469a5..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_2_2_2.eprime +++ /dev/null @@ -1,11 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1)] of bool -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -branching on [x_ExplicitVarSizeWithDummy, x_Occurrence, y_ExplicitVarSizeWithDummy] -such that - x_Occurrence[1] /\ (y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = 1) -> false, - x_ExplicitVarSizeWithDummy[1] != 2 -> x_Occurrence[x_ExplicitVarSizeWithDummy[1]], - x_Occurrence[1] -> x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = 1 - diff --git a/tests/exhaustive/basic/typed01/expected/model_1_2_2_3-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_1_2_2_3-solution000001.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_2_2_3-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_2_2_3-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_1_2_2_3-solution000002.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_2_2_3-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_2_2_3-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_1_2_2_3-solution000003.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_2_2_3-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_2_2_3.eprime b/tests/exhaustive/basic/typed01/expected/model_1_2_2_3.eprime deleted file mode 100644 index 2778101db8..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_2_2_3.eprime +++ /dev/null @@ -1,20 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1)] of bool -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -find y_ExplicitVarSizeWithMarker_Marker: int(0..1) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -branching on - [x_ExplicitVarSizeWithDummy, x_Occurrence, y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values, - y_ExplicitVarSizeWithDummy] -such that - x_Occurrence[1] /\ (y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = 1) -> false, - x_ExplicitVarSizeWithDummy[1] != 2 -> x_Occurrence[x_ExplicitVarSizeWithDummy[1]], - x_Occurrence[1] -> x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = 1, - 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, - 1 <= y_ExplicitVarSizeWithMarker_Marker -> - y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = y_ExplicitVarSizeWithMarker_Values[1], - y_ExplicitVarSizeWithDummy[1] != 2 -> - 1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = y_ExplicitVarSizeWithDummy[1] - diff --git a/tests/exhaustive/basic/typed01/expected/model_1_2_2_4-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_1_2_2_4-solution000001.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_2_2_4-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_2_2_4-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_1_2_2_4-solution000002.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_2_2_4-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_2_2_4-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_1_2_2_4-solution000003.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_2_2_4-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_2_2_4.eprime b/tests/exhaustive/basic/typed01/expected/model_1_2_2_4.eprime deleted file mode 100644 index 7a17794ceb..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_2_2_4.eprime +++ /dev/null @@ -1,20 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1)] of bool -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -branching on - [x_ExplicitVarSizeWithDummy, x_Occurrence, y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values, - y_ExplicitVarSizeWithDummy] -such that - x_Occurrence[1] /\ (y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = 1) -> false, - x_ExplicitVarSizeWithDummy[1] != 2 -> x_Occurrence[x_ExplicitVarSizeWithDummy[1]], - x_Occurrence[1] -> x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = 1, - y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, - y_ExplicitVarSizeWithFlags_Flags[1] -> - y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = y_ExplicitVarSizeWithFlags_Values[1], - y_ExplicitVarSizeWithDummy[1] != 2 -> - y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = y_ExplicitVarSizeWithDummy[1] - diff --git a/tests/exhaustive/basic/typed01/expected/model_1_2_3_1-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_1_2_3_1-solution000001.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_2_3_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_2_3_1-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_1_2_3_1-solution000002.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_2_3_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_2_3_1-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_1_2_3_1-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_2_3_1-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_2_3_1.eprime b/tests/exhaustive/basic/typed01/expected/model_1_2_3_1.eprime deleted file mode 100644 index 740f1db56a..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_2_3_1.eprime +++ /dev/null @@ -1,18 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1)] of bool -find x_ExplicitVarSizeWithMarker_Marker: int(0..1) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -find y_Occurrence: matrix indexed by [int(1)] of bool -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_Occurrence, y_Occurrence, - y_ExplicitVarSizeWithDummy] -such that - x_Occurrence[1] /\ (y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = 1) -> false, - 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, - 1 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[1]], - x_Occurrence[1] -> 1 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[1] = 1, - y_Occurrence[1] -> y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = 1, - y_ExplicitVarSizeWithDummy[1] != 2 -> y_Occurrence[y_ExplicitVarSizeWithDummy[1]] - diff --git a/tests/exhaustive/basic/typed01/expected/model_1_2_3_2-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_1_2_3_2-solution000001.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_2_3_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_2_3_2-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_1_2_3_2-solution000002.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_2_3_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_2_3_2-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_1_2_3_2-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_2_3_2-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_2_3_2.eprime b/tests/exhaustive/basic/typed01/expected/model_1_2_3_2.eprime deleted file mode 100644 index c4faccb2d1..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_2_3_2.eprime +++ /dev/null @@ -1,14 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1)] of bool -find x_ExplicitVarSizeWithMarker_Marker: int(0..1) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_Occurrence, y_ExplicitVarSizeWithDummy] -such that - x_Occurrence[1] /\ (y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = 1) -> false, - 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, - 1 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[1]], - x_Occurrence[1] -> 1 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[1] = 1 - diff --git a/tests/exhaustive/basic/typed01/expected/model_1_2_3_3-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_1_2_3_3-solution000001.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_2_3_3-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_2_3_3-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_1_2_3_3-solution000002.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_2_3_3-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_2_3_3-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_1_2_3_3-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_2_3_3-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_2_3_3.eprime b/tests/exhaustive/basic/typed01/expected/model_1_2_3_3.eprime deleted file mode 100644 index 2c591401fc..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_2_3_3.eprime +++ /dev/null @@ -1,22 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1)] of bool -find x_ExplicitVarSizeWithMarker_Marker: int(0..1) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -find y_ExplicitVarSizeWithMarker_Marker: int(0..1) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_Occurrence, - y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithDummy] -such that - x_Occurrence[1] /\ (y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = 1) -> false, - 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, - 1 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[1]], - x_Occurrence[1] -> 1 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[1] = 1, - 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, - 1 <= y_ExplicitVarSizeWithMarker_Marker -> - y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = y_ExplicitVarSizeWithMarker_Values[1], - y_ExplicitVarSizeWithDummy[1] != 2 -> - 1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = y_ExplicitVarSizeWithDummy[1] - diff --git a/tests/exhaustive/basic/typed01/expected/model_1_2_3_4-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_1_2_3_4-solution000001.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_2_3_4-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_2_3_4-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_1_2_3_4-solution000002.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_2_3_4-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_2_3_4-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_1_2_3_4-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_2_3_4-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_2_3_4.eprime b/tests/exhaustive/basic/typed01/expected/model_1_2_3_4.eprime deleted file mode 100644 index 065b1128ba..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_2_3_4.eprime +++ /dev/null @@ -1,22 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1)] of bool -find x_ExplicitVarSizeWithMarker_Marker: int(0..1) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_Occurrence, - y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithDummy] -such that - x_Occurrence[1] /\ (y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = 1) -> false, - 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, - 1 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[1]], - x_Occurrence[1] -> 1 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[1] = 1, - y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, - y_ExplicitVarSizeWithFlags_Flags[1] -> - y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = y_ExplicitVarSizeWithFlags_Values[1], - y_ExplicitVarSizeWithDummy[1] != 2 -> - y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = y_ExplicitVarSizeWithDummy[1] - diff --git a/tests/exhaustive/basic/typed01/expected/model_1_2_4_1-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_1_2_4_1-solution000001.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_2_4_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_2_4_1-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_1_2_4_1-solution000002.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_2_4_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_2_4_1-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_1_2_4_1-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_2_4_1-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_2_4_1.eprime b/tests/exhaustive/basic/typed01/expected/model_1_2_4_1.eprime deleted file mode 100644 index 734b00c535..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_2_4_1.eprime +++ /dev/null @@ -1,18 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1)] of bool -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -find y_Occurrence: matrix indexed by [int(1)] of bool -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_Occurrence, y_Occurrence, - y_ExplicitVarSizeWithDummy] -such that - x_Occurrence[1] /\ (y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = 1) -> false, - x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, - x_ExplicitVarSizeWithFlags_Flags[1] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[1]], - x_Occurrence[1] -> x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = 1, - y_Occurrence[1] -> y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = 1, - y_ExplicitVarSizeWithDummy[1] != 2 -> y_Occurrence[y_ExplicitVarSizeWithDummy[1]] - diff --git a/tests/exhaustive/basic/typed01/expected/model_1_2_4_2-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_1_2_4_2-solution000001.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_2_4_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_2_4_2-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_1_2_4_2-solution000002.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_2_4_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_2_4_2-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_1_2_4_2-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_2_4_2-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_2_4_2.eprime b/tests/exhaustive/basic/typed01/expected/model_1_2_4_2.eprime deleted file mode 100644 index af1b4633ab..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_2_4_2.eprime +++ /dev/null @@ -1,14 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1)] of bool -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_Occurrence, y_ExplicitVarSizeWithDummy] -such that - x_Occurrence[1] /\ (y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = 1) -> false, - x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, - x_ExplicitVarSizeWithFlags_Flags[1] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[1]], - x_Occurrence[1] -> x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = 1 - diff --git a/tests/exhaustive/basic/typed01/expected/model_1_2_4_3-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_1_2_4_3-solution000001.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_2_4_3-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_2_4_3-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_1_2_4_3-solution000002.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_2_4_3-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_2_4_3-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_1_2_4_3-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_2_4_3-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_2_4_3.eprime b/tests/exhaustive/basic/typed01/expected/model_1_2_4_3.eprime deleted file mode 100644 index 5a5d396454..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_2_4_3.eprime +++ /dev/null @@ -1,22 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1)] of bool -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -find y_ExplicitVarSizeWithMarker_Marker: int(0..1) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_Occurrence, - y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithDummy] -such that - x_Occurrence[1] /\ (y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = 1) -> false, - x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, - x_ExplicitVarSizeWithFlags_Flags[1] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[1]], - x_Occurrence[1] -> x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = 1, - 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, - 1 <= y_ExplicitVarSizeWithMarker_Marker -> - y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = y_ExplicitVarSizeWithMarker_Values[1], - y_ExplicitVarSizeWithDummy[1] != 2 -> - 1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = y_ExplicitVarSizeWithDummy[1] - diff --git a/tests/exhaustive/basic/typed01/expected/model_1_2_4_4-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_1_2_4_4-solution000001.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_2_4_4-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_2_4_4-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_1_2_4_4-solution000002.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_2_4_4-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_2_4_4-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_1_2_4_4-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_2_4_4-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_2_4_4.eprime b/tests/exhaustive/basic/typed01/expected/model_1_2_4_4.eprime deleted file mode 100644 index 38426c425d..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_2_4_4.eprime +++ /dev/null @@ -1,22 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1)] of bool -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_Occurrence, - y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithDummy] -such that - x_Occurrence[1] /\ (y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = 1) -> false, - x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, - x_ExplicitVarSizeWithFlags_Flags[1] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[1]], - x_Occurrence[1] -> x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = 1, - y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, - y_ExplicitVarSizeWithFlags_Flags[1] -> - y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = y_ExplicitVarSizeWithFlags_Values[1], - y_ExplicitVarSizeWithDummy[1] != 2 -> - y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = y_ExplicitVarSizeWithDummy[1] - diff --git a/tests/exhaustive/basic/typed01/expected/model_1_3_1_1-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_1_3_1_1-solution000001.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_3_1_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_3_1_1-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_1_3_1_1-solution000002.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_3_1_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_3_1_1-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_1_3_1_1-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_3_1_1-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_3_1_1.eprime b/tests/exhaustive/basic/typed01/expected/model_1_3_1_1.eprime deleted file mode 100644 index 0e788a249a..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_3_1_1.eprime +++ /dev/null @@ -1,13 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithMarker_Marker: int(0..1) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -find y_Occurrence: matrix indexed by [int(1)] of bool -branching on [x_Occurrence, y_Occurrence, y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values] -such that - x_Occurrence[1] /\ (1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = 1) -> false, - 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, - y_Occurrence[1] -> 1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = 1, - 1 <= y_ExplicitVarSizeWithMarker_Marker -> y_Occurrence[y_ExplicitVarSizeWithMarker_Values[1]] - diff --git a/tests/exhaustive/basic/typed01/expected/model_1_3_1_2-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_1_3_1_2-solution000001.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_3_1_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_3_1_2-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_1_3_1_2-solution000002.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_3_1_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_3_1_2-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_1_3_1_2-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_3_1_2-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_3_1_2.eprime b/tests/exhaustive/basic/typed01/expected/model_1_3_1_2.eprime deleted file mode 100644 index bd9ff9b0f3..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_3_1_2.eprime +++ /dev/null @@ -1,16 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithMarker_Marker: int(0..1) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -branching on - [x_Occurrence, y_ExplicitVarSizeWithDummy, y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values] -such that - x_Occurrence[1] /\ (1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = 1) -> false, - 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, - y_ExplicitVarSizeWithDummy[1] != 2 -> - 1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = y_ExplicitVarSizeWithDummy[1], - 1 <= y_ExplicitVarSizeWithMarker_Marker -> - y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = y_ExplicitVarSizeWithMarker_Values[1] - diff --git a/tests/exhaustive/basic/typed01/expected/model_1_3_1_3-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_1_3_1_3-solution000001.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_3_1_3-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_3_1_3-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_1_3_1_3-solution000002.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_3_1_3-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_3_1_3-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_1_3_1_3-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_3_1_3-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_3_1_3.eprime b/tests/exhaustive/basic/typed01/expected/model_1_3_1_3.eprime deleted file mode 100644 index b8082395cd..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_3_1_3.eprime +++ /dev/null @@ -1,10 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithMarker_Marker: int(0..1) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -branching on [x_Occurrence, y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values] -such that - x_Occurrence[1] /\ (1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = 1) -> false, - 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1 - diff --git a/tests/exhaustive/basic/typed01/expected/model_1_3_1_4-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_1_3_1_4-solution000001.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_3_1_4-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_3_1_4-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_1_3_1_4-solution000002.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_3_1_4-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_3_1_4-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_1_3_1_4-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_3_1_4-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_3_1_4.eprime b/tests/exhaustive/basic/typed01/expected/model_1_3_1_4.eprime deleted file mode 100644 index 4def58b75c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_3_1_4.eprime +++ /dev/null @@ -1,20 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithMarker_Marker: int(0..1) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -branching on - [x_Occurrence, y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values, - y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values] -such that - x_Occurrence[1] /\ (1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = 1) -> false, - 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, - y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, - y_ExplicitVarSizeWithFlags_Flags[1] -> - 1 <= y_ExplicitVarSizeWithMarker_Marker /\ - y_ExplicitVarSizeWithMarker_Values[1] = y_ExplicitVarSizeWithFlags_Values[1], - 1 <= y_ExplicitVarSizeWithMarker_Marker -> - y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = y_ExplicitVarSizeWithMarker_Values[1] - diff --git a/tests/exhaustive/basic/typed01/expected/model_1_3_2_1-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_1_3_2_1-solution000001.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_3_2_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_3_2_1-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_1_3_2_1-solution000002.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_3_2_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_3_2_1-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_1_3_2_1-solution000003.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_3_2_1-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_3_2_1.eprime b/tests/exhaustive/basic/typed01/expected/model_1_3_2_1.eprime deleted file mode 100644 index d53864e2d5..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_3_2_1.eprime +++ /dev/null @@ -1,18 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1)] of bool -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -find y_ExplicitVarSizeWithMarker_Marker: int(0..1) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -find y_Occurrence: matrix indexed by [int(1)] of bool -branching on - [x_ExplicitVarSizeWithDummy, x_Occurrence, y_Occurrence, y_ExplicitVarSizeWithMarker_Marker, - y_ExplicitVarSizeWithMarker_Values] -such that - x_Occurrence[1] /\ (1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = 1) -> false, - 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, - x_ExplicitVarSizeWithDummy[1] != 2 -> x_Occurrence[x_ExplicitVarSizeWithDummy[1]], - x_Occurrence[1] -> x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = 1, - y_Occurrence[1] -> 1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = 1, - 1 <= y_ExplicitVarSizeWithMarker_Marker -> y_Occurrence[y_ExplicitVarSizeWithMarker_Values[1]] - diff --git a/tests/exhaustive/basic/typed01/expected/model_1_3_2_2-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_1_3_2_2-solution000001.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_3_2_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_3_2_2-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_1_3_2_2-solution000002.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_3_2_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_3_2_2-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_1_3_2_2-solution000003.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_3_2_2-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_3_2_2.eprime b/tests/exhaustive/basic/typed01/expected/model_1_3_2_2.eprime deleted file mode 100644 index 076023e23e..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_3_2_2.eprime +++ /dev/null @@ -1,20 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1)] of bool -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -find y_ExplicitVarSizeWithMarker_Marker: int(0..1) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -branching on - [x_ExplicitVarSizeWithDummy, x_Occurrence, y_ExplicitVarSizeWithDummy, y_ExplicitVarSizeWithMarker_Marker, - y_ExplicitVarSizeWithMarker_Values] -such that - x_Occurrence[1] /\ (1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = 1) -> false, - 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, - x_ExplicitVarSizeWithDummy[1] != 2 -> x_Occurrence[x_ExplicitVarSizeWithDummy[1]], - x_Occurrence[1] -> x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = 1, - y_ExplicitVarSizeWithDummy[1] != 2 -> - 1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = y_ExplicitVarSizeWithDummy[1], - 1 <= y_ExplicitVarSizeWithMarker_Marker -> - y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = y_ExplicitVarSizeWithMarker_Values[1] - diff --git a/tests/exhaustive/basic/typed01/expected/model_1_3_2_3-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_1_3_2_3-solution000001.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_3_2_3-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_3_2_3-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_1_3_2_3-solution000002.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_3_2_3-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_3_2_3-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_1_3_2_3-solution000003.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_3_2_3-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_3_2_3.eprime b/tests/exhaustive/basic/typed01/expected/model_1_3_2_3.eprime deleted file mode 100644 index b30170d39b..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_3_2_3.eprime +++ /dev/null @@ -1,14 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1)] of bool -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -find y_ExplicitVarSizeWithMarker_Marker: int(0..1) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -branching on - [x_ExplicitVarSizeWithDummy, x_Occurrence, y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values] -such that - x_Occurrence[1] /\ (1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = 1) -> false, - 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, - x_ExplicitVarSizeWithDummy[1] != 2 -> x_Occurrence[x_ExplicitVarSizeWithDummy[1]], - x_Occurrence[1] -> x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = 1 - diff --git a/tests/exhaustive/basic/typed01/expected/model_1_3_2_4-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_1_3_2_4-solution000001.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_3_2_4-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_3_2_4-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_1_3_2_4-solution000002.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_3_2_4-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_3_2_4-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_1_3_2_4-solution000003.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_3_2_4-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_3_2_4.eprime b/tests/exhaustive/basic/typed01/expected/model_1_3_2_4.eprime deleted file mode 100644 index b355a9ad86..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_3_2_4.eprime +++ /dev/null @@ -1,23 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1)] of bool -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -find y_ExplicitVarSizeWithMarker_Marker: int(0..1) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -branching on - [x_ExplicitVarSizeWithDummy, x_Occurrence, y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values, - y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values] -such that - x_Occurrence[1] /\ (1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = 1) -> false, - 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, - x_ExplicitVarSizeWithDummy[1] != 2 -> x_Occurrence[x_ExplicitVarSizeWithDummy[1]], - x_Occurrence[1] -> x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = 1, - y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, - y_ExplicitVarSizeWithFlags_Flags[1] -> - 1 <= y_ExplicitVarSizeWithMarker_Marker /\ - y_ExplicitVarSizeWithMarker_Values[1] = y_ExplicitVarSizeWithFlags_Values[1], - 1 <= y_ExplicitVarSizeWithMarker_Marker -> - y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = y_ExplicitVarSizeWithMarker_Values[1] - diff --git a/tests/exhaustive/basic/typed01/expected/model_1_3_3_1-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_1_3_3_1-solution000001.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_3_3_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_3_3_1-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_1_3_3_1-solution000002.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_3_3_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_3_3_1-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_1_3_3_1-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_3_3_1-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_3_3_1.eprime b/tests/exhaustive/basic/typed01/expected/model_1_3_3_1.eprime deleted file mode 100644 index db5c695212..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_3_3_1.eprime +++ /dev/null @@ -1,20 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1)] of bool -find x_ExplicitVarSizeWithMarker_Marker: int(0..1) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -find y_ExplicitVarSizeWithMarker_Marker: int(0..1) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -find y_Occurrence: matrix indexed by [int(1)] of bool -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_Occurrence, y_Occurrence, - y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values] -such that - x_Occurrence[1] /\ (1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = 1) -> false, - 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, - 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, - 1 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[1]], - x_Occurrence[1] -> 1 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[1] = 1, - y_Occurrence[1] -> 1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = 1, - 1 <= y_ExplicitVarSizeWithMarker_Marker -> y_Occurrence[y_ExplicitVarSizeWithMarker_Values[1]] - diff --git a/tests/exhaustive/basic/typed01/expected/model_1_3_3_2-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_1_3_3_2-solution000001.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_3_3_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_3_3_2-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_1_3_3_2-solution000002.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_3_3_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_3_3_2-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_1_3_3_2-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_3_3_2-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_3_3_2.eprime b/tests/exhaustive/basic/typed01/expected/model_1_3_3_2.eprime deleted file mode 100644 index 12bdab1c1e..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_3_3_2.eprime +++ /dev/null @@ -1,22 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1)] of bool -find x_ExplicitVarSizeWithMarker_Marker: int(0..1) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -find y_ExplicitVarSizeWithMarker_Marker: int(0..1) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_Occurrence, y_ExplicitVarSizeWithDummy, - y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values] -such that - x_Occurrence[1] /\ (1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = 1) -> false, - 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, - 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, - 1 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[1]], - x_Occurrence[1] -> 1 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[1] = 1, - y_ExplicitVarSizeWithDummy[1] != 2 -> - 1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = y_ExplicitVarSizeWithDummy[1], - 1 <= y_ExplicitVarSizeWithMarker_Marker -> - y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = y_ExplicitVarSizeWithMarker_Values[1] - diff --git a/tests/exhaustive/basic/typed01/expected/model_1_3_3_3-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_1_3_3_3-solution000001.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_3_3_3-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_3_3_3-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_1_3_3_3-solution000002.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_3_3_3-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_3_3_3-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_1_3_3_3-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_3_3_3-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_3_3_3.eprime b/tests/exhaustive/basic/typed01/expected/model_1_3_3_3.eprime deleted file mode 100644 index 797ccd6052..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_3_3_3.eprime +++ /dev/null @@ -1,17 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1)] of bool -find x_ExplicitVarSizeWithMarker_Marker: int(0..1) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -find y_ExplicitVarSizeWithMarker_Marker: int(0..1) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_Occurrence, - y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values] -such that - x_Occurrence[1] /\ (1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = 1) -> false, - 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, - 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, - 1 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[1]], - x_Occurrence[1] -> 1 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[1] = 1 - diff --git a/tests/exhaustive/basic/typed01/expected/model_1_3_3_4-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_1_3_3_4-solution000001.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_3_3_4-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_3_3_4-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_1_3_3_4-solution000002.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_3_3_4-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_3_3_4-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_1_3_3_4-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_3_3_4-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_3_3_4.eprime b/tests/exhaustive/basic/typed01/expected/model_1_3_3_4.eprime deleted file mode 100644 index 0fe2d482ea..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_3_3_4.eprime +++ /dev/null @@ -1,26 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1)] of bool -find x_ExplicitVarSizeWithMarker_Marker: int(0..1) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -find y_ExplicitVarSizeWithMarker_Marker: int(0..1) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_Occurrence, - y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithMarker_Marker, - y_ExplicitVarSizeWithMarker_Values] -such that - x_Occurrence[1] /\ (1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = 1) -> false, - 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, - 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, - 1 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[1]], - x_Occurrence[1] -> 1 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[1] = 1, - y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, - y_ExplicitVarSizeWithFlags_Flags[1] -> - 1 <= y_ExplicitVarSizeWithMarker_Marker /\ - y_ExplicitVarSizeWithMarker_Values[1] = y_ExplicitVarSizeWithFlags_Values[1], - 1 <= y_ExplicitVarSizeWithMarker_Marker -> - y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = y_ExplicitVarSizeWithMarker_Values[1] - diff --git a/tests/exhaustive/basic/typed01/expected/model_1_3_4_1-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_1_3_4_1-solution000001.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_3_4_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_3_4_1-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_1_3_4_1-solution000002.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_3_4_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_3_4_1-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_1_3_4_1-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_3_4_1-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_3_4_1.eprime b/tests/exhaustive/basic/typed01/expected/model_1_3_4_1.eprime deleted file mode 100644 index e0b90502fa..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_3_4_1.eprime +++ /dev/null @@ -1,20 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1)] of bool -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -find y_ExplicitVarSizeWithMarker_Marker: int(0..1) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -find y_Occurrence: matrix indexed by [int(1)] of bool -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_Occurrence, y_Occurrence, - y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values] -such that - x_Occurrence[1] /\ (1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = 1) -> false, - 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, - x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, - x_ExplicitVarSizeWithFlags_Flags[1] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[1]], - x_Occurrence[1] -> x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = 1, - y_Occurrence[1] -> 1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = 1, - 1 <= y_ExplicitVarSizeWithMarker_Marker -> y_Occurrence[y_ExplicitVarSizeWithMarker_Values[1]] - diff --git a/tests/exhaustive/basic/typed01/expected/model_1_3_4_2-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_1_3_4_2-solution000001.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_3_4_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_3_4_2-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_1_3_4_2-solution000002.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_3_4_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_3_4_2-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_1_3_4_2-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_3_4_2-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_3_4_2.eprime b/tests/exhaustive/basic/typed01/expected/model_1_3_4_2.eprime deleted file mode 100644 index 0ed8c94b10..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_3_4_2.eprime +++ /dev/null @@ -1,22 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1)] of bool -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -find y_ExplicitVarSizeWithMarker_Marker: int(0..1) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_Occurrence, y_ExplicitVarSizeWithDummy, - y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values] -such that - x_Occurrence[1] /\ (1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = 1) -> false, - 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, - x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, - x_ExplicitVarSizeWithFlags_Flags[1] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[1]], - x_Occurrence[1] -> x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = 1, - y_ExplicitVarSizeWithDummy[1] != 2 -> - 1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = y_ExplicitVarSizeWithDummy[1], - 1 <= y_ExplicitVarSizeWithMarker_Marker -> - y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = y_ExplicitVarSizeWithMarker_Values[1] - diff --git a/tests/exhaustive/basic/typed01/expected/model_1_3_4_3-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_1_3_4_3-solution000001.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_3_4_3-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_3_4_3-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_1_3_4_3-solution000002.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_3_4_3-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_3_4_3-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_1_3_4_3-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_3_4_3-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_3_4_3.eprime b/tests/exhaustive/basic/typed01/expected/model_1_3_4_3.eprime deleted file mode 100644 index 5b9b136e78..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_3_4_3.eprime +++ /dev/null @@ -1,17 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1)] of bool -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -find y_ExplicitVarSizeWithMarker_Marker: int(0..1) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_Occurrence, - y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values] -such that - x_Occurrence[1] /\ (1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = 1) -> false, - 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, - x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, - x_ExplicitVarSizeWithFlags_Flags[1] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[1]], - x_Occurrence[1] -> x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = 1 - diff --git a/tests/exhaustive/basic/typed01/expected/model_1_3_4_4-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_1_3_4_4-solution000001.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_3_4_4-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_3_4_4-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_1_3_4_4-solution000002.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_3_4_4-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_3_4_4-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_1_3_4_4-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_3_4_4-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_3_4_4.eprime b/tests/exhaustive/basic/typed01/expected/model_1_3_4_4.eprime deleted file mode 100644 index e7751848d5..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_3_4_4.eprime +++ /dev/null @@ -1,26 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1)] of bool -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -find y_ExplicitVarSizeWithMarker_Marker: int(0..1) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_Occurrence, - y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithMarker_Marker, - y_ExplicitVarSizeWithMarker_Values] -such that - x_Occurrence[1] /\ (1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = 1) -> false, - 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, - x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, - x_ExplicitVarSizeWithFlags_Flags[1] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[1]], - x_Occurrence[1] -> x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = 1, - y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, - y_ExplicitVarSizeWithFlags_Flags[1] -> - 1 <= y_ExplicitVarSizeWithMarker_Marker /\ - y_ExplicitVarSizeWithMarker_Values[1] = y_ExplicitVarSizeWithFlags_Values[1], - 1 <= y_ExplicitVarSizeWithMarker_Marker -> - y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = y_ExplicitVarSizeWithMarker_Values[1] - diff --git a/tests/exhaustive/basic/typed01/expected/model_1_4_1_1-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_1_4_1_1-solution000001.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_4_1_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_4_1_1-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_1_4_1_1-solution000002.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_4_1_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_4_1_1-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_1_4_1_1-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_4_1_1-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_4_1_1.eprime b/tests/exhaustive/basic/typed01/expected/model_1_4_1_1.eprime deleted file mode 100644 index aed7683e32..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_4_1_1.eprime +++ /dev/null @@ -1,13 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -find y_Occurrence: matrix indexed by [int(1)] of bool -branching on [x_Occurrence, y_Occurrence, y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values] -such that - x_Occurrence[1] /\ (y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = 1) -> false, - y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, - y_Occurrence[1] -> y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = 1, - y_ExplicitVarSizeWithFlags_Flags[1] -> y_Occurrence[y_ExplicitVarSizeWithFlags_Values[1]] - diff --git a/tests/exhaustive/basic/typed01/expected/model_1_4_1_2-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_1_4_1_2-solution000001.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_4_1_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_4_1_2-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_1_4_1_2-solution000002.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_4_1_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_4_1_2-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_1_4_1_2-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_4_1_2-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_4_1_2.eprime b/tests/exhaustive/basic/typed01/expected/model_1_4_1_2.eprime deleted file mode 100644 index e0b60b66f0..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_4_1_2.eprime +++ /dev/null @@ -1,16 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -branching on - [x_Occurrence, y_ExplicitVarSizeWithDummy, y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values] -such that - x_Occurrence[1] /\ (y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = 1) -> false, - y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, - y_ExplicitVarSizeWithDummy[1] != 2 -> - y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = y_ExplicitVarSizeWithDummy[1], - y_ExplicitVarSizeWithFlags_Flags[1] -> - y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = y_ExplicitVarSizeWithFlags_Values[1] - diff --git a/tests/exhaustive/basic/typed01/expected/model_1_4_1_3-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_1_4_1_3-solution000001.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_4_1_3-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_4_1_3-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_1_4_1_3-solution000002.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_4_1_3-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_4_1_3-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_1_4_1_3-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_4_1_3-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_4_1_3.eprime b/tests/exhaustive/basic/typed01/expected/model_1_4_1_3.eprime deleted file mode 100644 index 3deed400be..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_4_1_3.eprime +++ /dev/null @@ -1,20 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -find y_ExplicitVarSizeWithMarker_Marker: int(0..1) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -branching on - [x_Occurrence, y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values, - y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values] -such that - x_Occurrence[1] /\ (y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = 1) -> false, - y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, - 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, - 1 <= y_ExplicitVarSizeWithMarker_Marker -> - y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = y_ExplicitVarSizeWithMarker_Values[1], - y_ExplicitVarSizeWithFlags_Flags[1] -> - 1 <= y_ExplicitVarSizeWithMarker_Marker /\ - y_ExplicitVarSizeWithMarker_Values[1] = y_ExplicitVarSizeWithFlags_Values[1] - diff --git a/tests/exhaustive/basic/typed01/expected/model_1_4_1_4-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_1_4_1_4-solution000001.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_4_1_4-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_4_1_4-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_1_4_1_4-solution000002.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_4_1_4-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_4_1_4-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_1_4_1_4-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_4_1_4-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_4_1_4.eprime b/tests/exhaustive/basic/typed01/expected/model_1_4_1_4.eprime deleted file mode 100644 index 3652c914ad..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_4_1_4.eprime +++ /dev/null @@ -1,10 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -branching on [x_Occurrence, y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values] -such that - x_Occurrence[1] /\ (y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = 1) -> false, - y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1 - diff --git a/tests/exhaustive/basic/typed01/expected/model_1_4_2_1-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_1_4_2_1-solution000001.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_4_2_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_4_2_1-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_1_4_2_1-solution000002.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_4_2_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_4_2_1-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_1_4_2_1-solution000003.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_4_2_1-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_4_2_1.eprime b/tests/exhaustive/basic/typed01/expected/model_1_4_2_1.eprime deleted file mode 100644 index 486abc3cff..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_4_2_1.eprime +++ /dev/null @@ -1,18 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1)] of bool -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -find y_Occurrence: matrix indexed by [int(1)] of bool -branching on - [x_ExplicitVarSizeWithDummy, x_Occurrence, y_Occurrence, y_ExplicitVarSizeWithFlags_Flags, - y_ExplicitVarSizeWithFlags_Values] -such that - x_Occurrence[1] /\ (y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = 1) -> false, - y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, - x_ExplicitVarSizeWithDummy[1] != 2 -> x_Occurrence[x_ExplicitVarSizeWithDummy[1]], - x_Occurrence[1] -> x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = 1, - y_Occurrence[1] -> y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = 1, - y_ExplicitVarSizeWithFlags_Flags[1] -> y_Occurrence[y_ExplicitVarSizeWithFlags_Values[1]] - diff --git a/tests/exhaustive/basic/typed01/expected/model_1_4_2_2-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_1_4_2_2-solution000001.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_4_2_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_4_2_2-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_1_4_2_2-solution000002.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_4_2_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_4_2_2-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_1_4_2_2-solution000003.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_4_2_2-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_4_2_2.eprime b/tests/exhaustive/basic/typed01/expected/model_1_4_2_2.eprime deleted file mode 100644 index eb01c1c347..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_4_2_2.eprime +++ /dev/null @@ -1,20 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1)] of bool -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -branching on - [x_ExplicitVarSizeWithDummy, x_Occurrence, y_ExplicitVarSizeWithDummy, y_ExplicitVarSizeWithFlags_Flags, - y_ExplicitVarSizeWithFlags_Values] -such that - x_Occurrence[1] /\ (y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = 1) -> false, - y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, - x_ExplicitVarSizeWithDummy[1] != 2 -> x_Occurrence[x_ExplicitVarSizeWithDummy[1]], - x_Occurrence[1] -> x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = 1, - y_ExplicitVarSizeWithDummy[1] != 2 -> - y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = y_ExplicitVarSizeWithDummy[1], - y_ExplicitVarSizeWithFlags_Flags[1] -> - y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = y_ExplicitVarSizeWithFlags_Values[1] - diff --git a/tests/exhaustive/basic/typed01/expected/model_1_4_2_3-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_1_4_2_3-solution000001.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_4_2_3-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_4_2_3-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_1_4_2_3-solution000002.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_4_2_3-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_4_2_3-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_1_4_2_3-solution000003.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_4_2_3-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_4_2_3.eprime b/tests/exhaustive/basic/typed01/expected/model_1_4_2_3.eprime deleted file mode 100644 index b9db0c2490..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_4_2_3.eprime +++ /dev/null @@ -1,23 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1)] of bool -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -find y_ExplicitVarSizeWithMarker_Marker: int(0..1) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -branching on - [x_ExplicitVarSizeWithDummy, x_Occurrence, y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values, - y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values] -such that - x_Occurrence[1] /\ (y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = 1) -> false, - y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, - x_ExplicitVarSizeWithDummy[1] != 2 -> x_Occurrence[x_ExplicitVarSizeWithDummy[1]], - x_Occurrence[1] -> x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = 1, - 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, - 1 <= y_ExplicitVarSizeWithMarker_Marker -> - y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = y_ExplicitVarSizeWithMarker_Values[1], - y_ExplicitVarSizeWithFlags_Flags[1] -> - 1 <= y_ExplicitVarSizeWithMarker_Marker /\ - y_ExplicitVarSizeWithMarker_Values[1] = y_ExplicitVarSizeWithFlags_Values[1] - diff --git a/tests/exhaustive/basic/typed01/expected/model_1_4_2_4-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_1_4_2_4-solution000001.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_4_2_4-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_4_2_4-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_1_4_2_4-solution000002.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_4_2_4-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_4_2_4-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_1_4_2_4-solution000003.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_4_2_4-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_4_2_4.eprime b/tests/exhaustive/basic/typed01/expected/model_1_4_2_4.eprime deleted file mode 100644 index 8dca479233..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_4_2_4.eprime +++ /dev/null @@ -1,14 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1)] of bool -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -branching on - [x_ExplicitVarSizeWithDummy, x_Occurrence, y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values] -such that - x_Occurrence[1] /\ (y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = 1) -> false, - y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, - x_ExplicitVarSizeWithDummy[1] != 2 -> x_Occurrence[x_ExplicitVarSizeWithDummy[1]], - x_Occurrence[1] -> x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = 1 - diff --git a/tests/exhaustive/basic/typed01/expected/model_1_4_3_1-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_1_4_3_1-solution000001.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_4_3_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_4_3_1-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_1_4_3_1-solution000002.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_4_3_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_4_3_1-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_1_4_3_1-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_4_3_1-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_4_3_1.eprime b/tests/exhaustive/basic/typed01/expected/model_1_4_3_1.eprime deleted file mode 100644 index 46bbb31689..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_4_3_1.eprime +++ /dev/null @@ -1,20 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1)] of bool -find x_ExplicitVarSizeWithMarker_Marker: int(0..1) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -find y_Occurrence: matrix indexed by [int(1)] of bool -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_Occurrence, y_Occurrence, - y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values] -such that - x_Occurrence[1] /\ (y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = 1) -> false, - y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, - 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, - 1 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[1]], - x_Occurrence[1] -> 1 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[1] = 1, - y_Occurrence[1] -> y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = 1, - y_ExplicitVarSizeWithFlags_Flags[1] -> y_Occurrence[y_ExplicitVarSizeWithFlags_Values[1]] - diff --git a/tests/exhaustive/basic/typed01/expected/model_1_4_3_2-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_1_4_3_2-solution000001.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_4_3_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_4_3_2-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_1_4_3_2-solution000002.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_4_3_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_4_3_2-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_1_4_3_2-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_4_3_2-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_4_3_2.eprime b/tests/exhaustive/basic/typed01/expected/model_1_4_3_2.eprime deleted file mode 100644 index d31a6fe728..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_4_3_2.eprime +++ /dev/null @@ -1,22 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1)] of bool -find x_ExplicitVarSizeWithMarker_Marker: int(0..1) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_Occurrence, y_ExplicitVarSizeWithDummy, - y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values] -such that - x_Occurrence[1] /\ (y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = 1) -> false, - y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, - 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, - 1 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[1]], - x_Occurrence[1] -> 1 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[1] = 1, - y_ExplicitVarSizeWithDummy[1] != 2 -> - y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = y_ExplicitVarSizeWithDummy[1], - y_ExplicitVarSizeWithFlags_Flags[1] -> - y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = y_ExplicitVarSizeWithFlags_Values[1] - diff --git a/tests/exhaustive/basic/typed01/expected/model_1_4_3_3-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_1_4_3_3-solution000001.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_4_3_3-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_4_3_3-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_1_4_3_3-solution000002.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_4_3_3-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_4_3_3-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_1_4_3_3-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_4_3_3-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_4_3_3.eprime b/tests/exhaustive/basic/typed01/expected/model_1_4_3_3.eprime deleted file mode 100644 index fc3f83dcff..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_4_3_3.eprime +++ /dev/null @@ -1,26 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1)] of bool -find x_ExplicitVarSizeWithMarker_Marker: int(0..1) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -find y_ExplicitVarSizeWithMarker_Marker: int(0..1) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_Occurrence, - y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithFlags_Flags, - y_ExplicitVarSizeWithFlags_Values] -such that - x_Occurrence[1] /\ (y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = 1) -> false, - y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, - 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, - 1 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[1]], - x_Occurrence[1] -> 1 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[1] = 1, - 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, - 1 <= y_ExplicitVarSizeWithMarker_Marker -> - y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = y_ExplicitVarSizeWithMarker_Values[1], - y_ExplicitVarSizeWithFlags_Flags[1] -> - 1 <= y_ExplicitVarSizeWithMarker_Marker /\ - y_ExplicitVarSizeWithMarker_Values[1] = y_ExplicitVarSizeWithFlags_Values[1] - diff --git a/tests/exhaustive/basic/typed01/expected/model_1_4_3_4-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_1_4_3_4-solution000001.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_4_3_4-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_4_3_4-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_1_4_3_4-solution000002.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_4_3_4-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_4_3_4-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_1_4_3_4-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_4_3_4-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_4_3_4.eprime b/tests/exhaustive/basic/typed01/expected/model_1_4_3_4.eprime deleted file mode 100644 index 1ae9b4088c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_4_3_4.eprime +++ /dev/null @@ -1,17 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1)] of bool -find x_ExplicitVarSizeWithMarker_Marker: int(0..1) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_Occurrence, - y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values] -such that - x_Occurrence[1] /\ (y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = 1) -> false, - y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, - 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, - 1 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[1]], - x_Occurrence[1] -> 1 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[1] = 1 - diff --git a/tests/exhaustive/basic/typed01/expected/model_1_4_4_1-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_1_4_4_1-solution000001.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_4_4_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_4_4_1-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_1_4_4_1-solution000002.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_4_4_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_4_4_1-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_1_4_4_1-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_4_4_1-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_4_4_1.eprime b/tests/exhaustive/basic/typed01/expected/model_1_4_4_1.eprime deleted file mode 100644 index 4b0a76d2ad..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_4_4_1.eprime +++ /dev/null @@ -1,20 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1)] of bool -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -find y_Occurrence: matrix indexed by [int(1)] of bool -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_Occurrence, y_Occurrence, - y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values] -such that - x_Occurrence[1] /\ (y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = 1) -> false, - y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, - x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, - x_ExplicitVarSizeWithFlags_Flags[1] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[1]], - x_Occurrence[1] -> x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = 1, - y_Occurrence[1] -> y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = 1, - y_ExplicitVarSizeWithFlags_Flags[1] -> y_Occurrence[y_ExplicitVarSizeWithFlags_Values[1]] - diff --git a/tests/exhaustive/basic/typed01/expected/model_1_4_4_2-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_1_4_4_2-solution000001.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_4_4_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_4_4_2-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_1_4_4_2-solution000002.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_4_4_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_4_4_2-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_1_4_4_2-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_4_4_2-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_4_4_2.eprime b/tests/exhaustive/basic/typed01/expected/model_1_4_4_2.eprime deleted file mode 100644 index bc46971fe0..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_4_4_2.eprime +++ /dev/null @@ -1,22 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1)] of bool -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_Occurrence, y_ExplicitVarSizeWithDummy, - y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values] -such that - x_Occurrence[1] /\ (y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = 1) -> false, - y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, - x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, - x_ExplicitVarSizeWithFlags_Flags[1] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[1]], - x_Occurrence[1] -> x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = 1, - y_ExplicitVarSizeWithDummy[1] != 2 -> - y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = y_ExplicitVarSizeWithDummy[1], - y_ExplicitVarSizeWithFlags_Flags[1] -> - y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = y_ExplicitVarSizeWithFlags_Values[1] - diff --git a/tests/exhaustive/basic/typed01/expected/model_1_4_4_3-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_1_4_4_3-solution000001.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_4_4_3-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_4_4_3-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_1_4_4_3-solution000002.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_4_4_3-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_4_4_3-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_1_4_4_3-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_4_4_3-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_4_4_3.eprime b/tests/exhaustive/basic/typed01/expected/model_1_4_4_3.eprime deleted file mode 100644 index 9245215595..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_4_4_3.eprime +++ /dev/null @@ -1,26 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1)] of bool -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -find y_ExplicitVarSizeWithMarker_Marker: int(0..1) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_Occurrence, - y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithFlags_Flags, - y_ExplicitVarSizeWithFlags_Values] -such that - x_Occurrence[1] /\ (y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = 1) -> false, - y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, - x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, - x_ExplicitVarSizeWithFlags_Flags[1] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[1]], - x_Occurrence[1] -> x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = 1, - 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, - 1 <= y_ExplicitVarSizeWithMarker_Marker -> - y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = y_ExplicitVarSizeWithMarker_Values[1], - y_ExplicitVarSizeWithFlags_Flags[1] -> - 1 <= y_ExplicitVarSizeWithMarker_Marker /\ - y_ExplicitVarSizeWithMarker_Values[1] = y_ExplicitVarSizeWithFlags_Values[1] - diff --git a/tests/exhaustive/basic/typed01/expected/model_1_4_4_4-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_1_4_4_4-solution000001.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_4_4_4-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_4_4_4-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_1_4_4_4-solution000002.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_4_4_4-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_4_4_4-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_1_4_4_4-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_4_4_4-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_4_4_4.eprime b/tests/exhaustive/basic/typed01/expected/model_1_4_4_4.eprime deleted file mode 100644 index cccfca44a7..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_1_4_4_4.eprime +++ /dev/null @@ -1,17 +0,0 @@ -language ESSENCE' 1.0 - -find x_Occurrence: matrix indexed by [int(1)] of bool -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_Occurrence, - y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values] -such that - x_Occurrence[1] /\ (y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = 1) -> false, - y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, - x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, - x_ExplicitVarSizeWithFlags_Flags[1] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[1]], - x_Occurrence[1] -> x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = 1 - diff --git a/tests/exhaustive/basic/typed01/expected/model_2_1_1_1-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_2_1_1_1-solution000001.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_1_1_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_1_1_1-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_2_1_1_1-solution000002.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_1_1_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_1_1_1-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_2_1_1_1-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_1_1_1-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_1_1_1.eprime b/tests/exhaustive/basic/typed01/expected/model_2_1_1_1.eprime deleted file mode 100644 index dea929fb85..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_1_1_1.eprime +++ /dev/null @@ -1,11 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -find x_Occurrence: matrix indexed by [int(1)] of bool -find y_Occurrence: matrix indexed by [int(1)] of bool -branching on [x_Occurrence, x_ExplicitVarSizeWithDummy, y_Occurrence] -such that - x_ExplicitVarSizeWithDummy[1] != 2 /\ y_Occurrence[x_ExplicitVarSizeWithDummy[1]] -> false, - x_Occurrence[1] -> x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = 1, - x_ExplicitVarSizeWithDummy[1] != 2 -> x_Occurrence[x_ExplicitVarSizeWithDummy[1]] - diff --git a/tests/exhaustive/basic/typed01/expected/model_2_1_1_2-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_2_1_1_2-solution000001.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_1_1_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_1_1_2-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_2_1_1_2-solution000002.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_1_1_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_1_1_2-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_2_1_1_2-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_1_1_2-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_1_1_2.eprime b/tests/exhaustive/basic/typed01/expected/model_2_1_1_2.eprime deleted file mode 100644 index 1ebc638b04..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_1_1_2.eprime +++ /dev/null @@ -1,14 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -find x_Occurrence: matrix indexed by [int(1)] of bool -find y_Occurrence: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -branching on [x_Occurrence, x_ExplicitVarSizeWithDummy, y_ExplicitVarSizeWithDummy, y_Occurrence] -such that - x_ExplicitVarSizeWithDummy[1] != 2 /\ y_Occurrence[x_ExplicitVarSizeWithDummy[1]] -> false, - x_Occurrence[1] -> x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = 1, - x_ExplicitVarSizeWithDummy[1] != 2 -> x_Occurrence[x_ExplicitVarSizeWithDummy[1]], - y_ExplicitVarSizeWithDummy[1] != 2 -> y_Occurrence[y_ExplicitVarSizeWithDummy[1]], - y_Occurrence[1] -> y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = 1 - diff --git a/tests/exhaustive/basic/typed01/expected/model_2_1_1_3-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_2_1_1_3-solution000001.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_1_1_3-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_1_1_3-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_2_1_1_3-solution000002.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_1_1_3-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_1_1_3-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_2_1_1_3-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_1_1_3-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_1_1_3.eprime b/tests/exhaustive/basic/typed01/expected/model_2_1_1_3.eprime deleted file mode 100644 index d367ac6332..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_1_1_3.eprime +++ /dev/null @@ -1,18 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -find x_Occurrence: matrix indexed by [int(1)] of bool -find y_Occurrence: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithMarker_Marker: int(0..1) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -branching on - [x_Occurrence, x_ExplicitVarSizeWithDummy, y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values, - y_Occurrence] -such that - x_ExplicitVarSizeWithDummy[1] != 2 /\ y_Occurrence[x_ExplicitVarSizeWithDummy[1]] -> false, - x_Occurrence[1] -> x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = 1, - x_ExplicitVarSizeWithDummy[1] != 2 -> x_Occurrence[x_ExplicitVarSizeWithDummy[1]], - 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, - 1 <= y_ExplicitVarSizeWithMarker_Marker -> y_Occurrence[y_ExplicitVarSizeWithMarker_Values[1]], - y_Occurrence[1] -> 1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = 1 - diff --git a/tests/exhaustive/basic/typed01/expected/model_2_1_1_4-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_2_1_1_4-solution000001.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_1_1_4-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_1_1_4-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_2_1_1_4-solution000002.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_1_1_4-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_1_1_4-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_2_1_1_4-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_1_1_4-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_1_1_4.eprime b/tests/exhaustive/basic/typed01/expected/model_2_1_1_4.eprime deleted file mode 100644 index f956e74768..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_1_1_4.eprime +++ /dev/null @@ -1,18 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -find x_Occurrence: matrix indexed by [int(1)] of bool -find y_Occurrence: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -branching on - [x_Occurrence, x_ExplicitVarSizeWithDummy, y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values, - y_Occurrence] -such that - x_ExplicitVarSizeWithDummy[1] != 2 /\ y_Occurrence[x_ExplicitVarSizeWithDummy[1]] -> false, - x_Occurrence[1] -> x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = 1, - x_ExplicitVarSizeWithDummy[1] != 2 -> x_Occurrence[x_ExplicitVarSizeWithDummy[1]], - y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, - y_ExplicitVarSizeWithFlags_Flags[1] -> y_Occurrence[y_ExplicitVarSizeWithFlags_Values[1]], - y_Occurrence[1] -> y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = 1 - diff --git a/tests/exhaustive/basic/typed01/expected/model_2_1_2_1-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_2_1_2_1-solution000001.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_1_2_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_1_2_1-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_2_1_2_1-solution000002.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_1_2_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_1_2_1-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_2_1_2_1-solution000003.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_1_2_1-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_1_2_1.eprime b/tests/exhaustive/basic/typed01/expected/model_2_1_2_1.eprime deleted file mode 100644 index b0c1489050..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_1_2_1.eprime +++ /dev/null @@ -1,7 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -find y_Occurrence: matrix indexed by [int(1)] of bool -branching on [x_ExplicitVarSizeWithDummy, y_Occurrence] -such that x_ExplicitVarSizeWithDummy[1] != 2 /\ y_Occurrence[x_ExplicitVarSizeWithDummy[1]] -> false - diff --git a/tests/exhaustive/basic/typed01/expected/model_2_1_2_2-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_2_1_2_2-solution000001.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_1_2_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_1_2_2-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_2_1_2_2-solution000002.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_1_2_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_1_2_2-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_2_1_2_2-solution000003.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_1_2_2-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_1_2_2.eprime b/tests/exhaustive/basic/typed01/expected/model_2_1_2_2.eprime deleted file mode 100644 index 0715504126..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_1_2_2.eprime +++ /dev/null @@ -1,11 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -find y_Occurrence: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -branching on [x_ExplicitVarSizeWithDummy, y_ExplicitVarSizeWithDummy, y_Occurrence] -such that - x_ExplicitVarSizeWithDummy[1] != 2 /\ y_Occurrence[x_ExplicitVarSizeWithDummy[1]] -> false, - y_ExplicitVarSizeWithDummy[1] != 2 -> y_Occurrence[y_ExplicitVarSizeWithDummy[1]], - y_Occurrence[1] -> y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = 1 - diff --git a/tests/exhaustive/basic/typed01/expected/model_2_1_2_3-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_2_1_2_3-solution000001.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_1_2_3-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_1_2_3-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_2_1_2_3-solution000002.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_1_2_3-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_1_2_3-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_2_1_2_3-solution000003.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_1_2_3-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_1_2_3.eprime b/tests/exhaustive/basic/typed01/expected/model_2_1_2_3.eprime deleted file mode 100644 index 0e5b347379..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_1_2_3.eprime +++ /dev/null @@ -1,14 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -find y_Occurrence: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithMarker_Marker: int(0..1) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -branching on - [x_ExplicitVarSizeWithDummy, y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values, y_Occurrence] -such that - x_ExplicitVarSizeWithDummy[1] != 2 /\ y_Occurrence[x_ExplicitVarSizeWithDummy[1]] -> false, - 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, - 1 <= y_ExplicitVarSizeWithMarker_Marker -> y_Occurrence[y_ExplicitVarSizeWithMarker_Values[1]], - y_Occurrence[1] -> 1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = 1 - diff --git a/tests/exhaustive/basic/typed01/expected/model_2_1_2_4-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_2_1_2_4-solution000001.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_1_2_4-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_1_2_4-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_2_1_2_4-solution000002.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_1_2_4-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_1_2_4-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_2_1_2_4-solution000003.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_1_2_4-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_1_2_4.eprime b/tests/exhaustive/basic/typed01/expected/model_2_1_2_4.eprime deleted file mode 100644 index 92c235b315..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_1_2_4.eprime +++ /dev/null @@ -1,14 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -find y_Occurrence: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -branching on - [x_ExplicitVarSizeWithDummy, y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values, y_Occurrence] -such that - x_ExplicitVarSizeWithDummy[1] != 2 /\ y_Occurrence[x_ExplicitVarSizeWithDummy[1]] -> false, - y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, - y_ExplicitVarSizeWithFlags_Flags[1] -> y_Occurrence[y_ExplicitVarSizeWithFlags_Values[1]], - y_Occurrence[1] -> y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = 1 - diff --git a/tests/exhaustive/basic/typed01/expected/model_2_1_3_1-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_2_1_3_1-solution000001.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_1_3_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_1_3_1-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_2_1_3_1-solution000002.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_1_3_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_1_3_1-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_2_1_3_1-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_1_3_1-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_1_3_1.eprime b/tests/exhaustive/basic/typed01/expected/model_2_1_3_1.eprime deleted file mode 100644 index 5b9e809311..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_1_3_1.eprime +++ /dev/null @@ -1,16 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -find x_ExplicitVarSizeWithMarker_Marker: int(0..1) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -find y_Occurrence: matrix indexed by [int(1)] of bool -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy, y_Occurrence] -such that - x_ExplicitVarSizeWithDummy[1] != 2 /\ y_Occurrence[x_ExplicitVarSizeWithDummy[1]] -> false, - 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, - 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithMarker_Values[1], - x_ExplicitVarSizeWithDummy[1] != 2 -> - 1 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithDummy[1] - diff --git a/tests/exhaustive/basic/typed01/expected/model_2_1_3_2-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_2_1_3_2-solution000001.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_1_3_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_1_3_2-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_2_1_3_2-solution000002.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_1_3_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_1_3_2-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_2_1_3_2-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_1_3_2-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_1_3_2.eprime b/tests/exhaustive/basic/typed01/expected/model_2_1_3_2.eprime deleted file mode 100644 index 82f4c5b4a8..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_1_3_2.eprime +++ /dev/null @@ -1,20 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -find x_ExplicitVarSizeWithMarker_Marker: int(0..1) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -find y_Occurrence: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy, - y_ExplicitVarSizeWithDummy, y_Occurrence] -such that - x_ExplicitVarSizeWithDummy[1] != 2 /\ y_Occurrence[x_ExplicitVarSizeWithDummy[1]] -> false, - 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, - 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithMarker_Values[1], - x_ExplicitVarSizeWithDummy[1] != 2 -> - 1 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithDummy[1], - y_ExplicitVarSizeWithDummy[1] != 2 -> y_Occurrence[y_ExplicitVarSizeWithDummy[1]], - y_Occurrence[1] -> y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = 1 - diff --git a/tests/exhaustive/basic/typed01/expected/model_2_1_3_3-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_2_1_3_3-solution000001.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_1_3_3-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_1_3_3-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_2_1_3_3-solution000002.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_1_3_3-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_1_3_3-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_2_1_3_3-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_1_3_3-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_1_3_3.eprime b/tests/exhaustive/basic/typed01/expected/model_2_1_3_3.eprime deleted file mode 100644 index 97a807ab7e..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_1_3_3.eprime +++ /dev/null @@ -1,22 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -find x_ExplicitVarSizeWithMarker_Marker: int(0..1) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -find y_Occurrence: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithMarker_Marker: int(0..1) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy, - y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values, y_Occurrence] -such that - x_ExplicitVarSizeWithDummy[1] != 2 /\ y_Occurrence[x_ExplicitVarSizeWithDummy[1]] -> false, - 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, - 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithMarker_Values[1], - x_ExplicitVarSizeWithDummy[1] != 2 -> - 1 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithDummy[1], - 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, - 1 <= y_ExplicitVarSizeWithMarker_Marker -> y_Occurrence[y_ExplicitVarSizeWithMarker_Values[1]], - y_Occurrence[1] -> 1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = 1 - diff --git a/tests/exhaustive/basic/typed01/expected/model_2_1_3_4-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_2_1_3_4-solution000001.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_1_3_4-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_1_3_4-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_2_1_3_4-solution000002.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_1_3_4-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_1_3_4-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_2_1_3_4-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_1_3_4-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_1_3_4.eprime b/tests/exhaustive/basic/typed01/expected/model_2_1_3_4.eprime deleted file mode 100644 index 643e77b708..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_1_3_4.eprime +++ /dev/null @@ -1,22 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -find x_ExplicitVarSizeWithMarker_Marker: int(0..1) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -find y_Occurrence: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy, - y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values, y_Occurrence] -such that - x_ExplicitVarSizeWithDummy[1] != 2 /\ y_Occurrence[x_ExplicitVarSizeWithDummy[1]] -> false, - 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, - 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithMarker_Values[1], - x_ExplicitVarSizeWithDummy[1] != 2 -> - 1 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithDummy[1], - y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, - y_ExplicitVarSizeWithFlags_Flags[1] -> y_Occurrence[y_ExplicitVarSizeWithFlags_Values[1]], - y_Occurrence[1] -> y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = 1 - diff --git a/tests/exhaustive/basic/typed01/expected/model_2_1_4_1-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_2_1_4_1-solution000001.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_1_4_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_1_4_1-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_2_1_4_1-solution000002.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_1_4_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_1_4_1-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_2_1_4_1-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_1_4_1-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_1_4_1.eprime b/tests/exhaustive/basic/typed01/expected/model_2_1_4_1.eprime deleted file mode 100644 index 9824eb9893..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_1_4_1.eprime +++ /dev/null @@ -1,16 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -find y_Occurrence: matrix indexed by [int(1)] of bool -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy, y_Occurrence] -such that - x_ExplicitVarSizeWithDummy[1] != 2 /\ y_Occurrence[x_ExplicitVarSizeWithDummy[1]] -> false, - x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, - x_ExplicitVarSizeWithFlags_Flags[1] -> - x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithFlags_Values[1], - x_ExplicitVarSizeWithDummy[1] != 2 -> - x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithDummy[1] - diff --git a/tests/exhaustive/basic/typed01/expected/model_2_1_4_2-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_2_1_4_2-solution000001.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_1_4_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_1_4_2-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_2_1_4_2-solution000002.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_1_4_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_1_4_2-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_2_1_4_2-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_1_4_2-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_1_4_2.eprime b/tests/exhaustive/basic/typed01/expected/model_2_1_4_2.eprime deleted file mode 100644 index 435aee6b41..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_1_4_2.eprime +++ /dev/null @@ -1,20 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -find y_Occurrence: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy, - y_ExplicitVarSizeWithDummy, y_Occurrence] -such that - x_ExplicitVarSizeWithDummy[1] != 2 /\ y_Occurrence[x_ExplicitVarSizeWithDummy[1]] -> false, - x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, - x_ExplicitVarSizeWithFlags_Flags[1] -> - x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithFlags_Values[1], - x_ExplicitVarSizeWithDummy[1] != 2 -> - x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithDummy[1], - y_ExplicitVarSizeWithDummy[1] != 2 -> y_Occurrence[y_ExplicitVarSizeWithDummy[1]], - y_Occurrence[1] -> y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = 1 - diff --git a/tests/exhaustive/basic/typed01/expected/model_2_1_4_3-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_2_1_4_3-solution000001.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_1_4_3-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_1_4_3-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_2_1_4_3-solution000002.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_1_4_3-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_1_4_3-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_2_1_4_3-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_1_4_3-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_1_4_3.eprime b/tests/exhaustive/basic/typed01/expected/model_2_1_4_3.eprime deleted file mode 100644 index bc6ee32138..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_1_4_3.eprime +++ /dev/null @@ -1,22 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -find y_Occurrence: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithMarker_Marker: int(0..1) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy, - y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values, y_Occurrence] -such that - x_ExplicitVarSizeWithDummy[1] != 2 /\ y_Occurrence[x_ExplicitVarSizeWithDummy[1]] -> false, - x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, - x_ExplicitVarSizeWithFlags_Flags[1] -> - x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithFlags_Values[1], - x_ExplicitVarSizeWithDummy[1] != 2 -> - x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithDummy[1], - 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, - 1 <= y_ExplicitVarSizeWithMarker_Marker -> y_Occurrence[y_ExplicitVarSizeWithMarker_Values[1]], - y_Occurrence[1] -> 1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = 1 - diff --git a/tests/exhaustive/basic/typed01/expected/model_2_1_4_4-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_2_1_4_4-solution000001.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_1_4_4-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_1_4_4-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_2_1_4_4-solution000002.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_1_4_4-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_1_4_4-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_2_1_4_4-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_1_4_4-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_1_4_4.eprime b/tests/exhaustive/basic/typed01/expected/model_2_1_4_4.eprime deleted file mode 100644 index 17f79cea52..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_1_4_4.eprime +++ /dev/null @@ -1,22 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -find y_Occurrence: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy, - y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values, y_Occurrence] -such that - x_ExplicitVarSizeWithDummy[1] != 2 /\ y_Occurrence[x_ExplicitVarSizeWithDummy[1]] -> false, - x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, - x_ExplicitVarSizeWithFlags_Flags[1] -> - x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithFlags_Values[1], - x_ExplicitVarSizeWithDummy[1] != 2 -> - x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithDummy[1], - y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, - y_ExplicitVarSizeWithFlags_Flags[1] -> y_Occurrence[y_ExplicitVarSizeWithFlags_Values[1]], - y_Occurrence[1] -> y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = 1 - diff --git a/tests/exhaustive/basic/typed01/expected/model_2_2_1_1-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_2_2_1_1-solution000001.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_2_1_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_2_1_1-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_2_2_1_1-solution000002.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_2_1_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_2_1_1-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_2_2_1_1-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_2_1_1-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_2_1_1.eprime b/tests/exhaustive/basic/typed01/expected/model_2_2_1_1.eprime deleted file mode 100644 index 55ea4f98eb..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_2_1_1.eprime +++ /dev/null @@ -1,16 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -find x_Occurrence: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -find y_Occurrence: matrix indexed by [int(1)] of bool -branching on [x_Occurrence, x_ExplicitVarSizeWithDummy, y_Occurrence, y_ExplicitVarSizeWithDummy] -such that - x_ExplicitVarSizeWithDummy[1] != 2 /\ - (y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithDummy[1]) - -> false, - x_Occurrence[1] -> x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = 1, - x_ExplicitVarSizeWithDummy[1] != 2 -> x_Occurrence[x_ExplicitVarSizeWithDummy[1]], - y_Occurrence[1] -> y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = 1, - y_ExplicitVarSizeWithDummy[1] != 2 -> y_Occurrence[y_ExplicitVarSizeWithDummy[1]] - diff --git a/tests/exhaustive/basic/typed01/expected/model_2_2_1_2-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_2_2_1_2-solution000001.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_2_1_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_2_1_2-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_2_2_1_2-solution000002.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_2_1_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_2_1_2-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_2_2_1_2-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_2_1_2-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_2_1_2.eprime b/tests/exhaustive/basic/typed01/expected/model_2_2_1_2.eprime deleted file mode 100644 index 25e38b0597..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_2_1_2.eprime +++ /dev/null @@ -1,13 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -find x_Occurrence: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -branching on [x_Occurrence, x_ExplicitVarSizeWithDummy, y_ExplicitVarSizeWithDummy] -such that - x_ExplicitVarSizeWithDummy[1] != 2 /\ - (y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithDummy[1]) - -> false, - x_Occurrence[1] -> x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = 1, - x_ExplicitVarSizeWithDummy[1] != 2 -> x_Occurrence[x_ExplicitVarSizeWithDummy[1]] - diff --git a/tests/exhaustive/basic/typed01/expected/model_2_2_1_3-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_2_2_1_3-solution000001.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_2_1_3-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_2_1_3-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_2_2_1_3-solution000002.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_2_1_3-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_2_1_3-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_2_2_1_3-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_2_1_3-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_2_1_3.eprime b/tests/exhaustive/basic/typed01/expected/model_2_2_1_3.eprime deleted file mode 100644 index dfe0d93806..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_2_1_3.eprime +++ /dev/null @@ -1,22 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -find x_Occurrence: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -find y_ExplicitVarSizeWithMarker_Marker: int(0..1) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -branching on - [x_Occurrence, x_ExplicitVarSizeWithDummy, y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values, - y_ExplicitVarSizeWithDummy] -such that - x_ExplicitVarSizeWithDummy[1] != 2 /\ - (y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithDummy[1]) - -> false, - x_Occurrence[1] -> x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = 1, - x_ExplicitVarSizeWithDummy[1] != 2 -> x_Occurrence[x_ExplicitVarSizeWithDummy[1]], - 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, - 1 <= y_ExplicitVarSizeWithMarker_Marker -> - y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = y_ExplicitVarSizeWithMarker_Values[1], - y_ExplicitVarSizeWithDummy[1] != 2 -> - 1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = y_ExplicitVarSizeWithDummy[1] - diff --git a/tests/exhaustive/basic/typed01/expected/model_2_2_1_4-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_2_2_1_4-solution000001.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_2_1_4-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_2_1_4-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_2_2_1_4-solution000002.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_2_1_4-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_2_1_4-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_2_2_1_4-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_2_1_4-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_2_1_4.eprime b/tests/exhaustive/basic/typed01/expected/model_2_2_1_4.eprime deleted file mode 100644 index 53929d788b..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_2_1_4.eprime +++ /dev/null @@ -1,22 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -find x_Occurrence: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -branching on - [x_Occurrence, x_ExplicitVarSizeWithDummy, y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values, - y_ExplicitVarSizeWithDummy] -such that - x_ExplicitVarSizeWithDummy[1] != 2 /\ - (y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithDummy[1]) - -> false, - x_Occurrence[1] -> x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = 1, - x_ExplicitVarSizeWithDummy[1] != 2 -> x_Occurrence[x_ExplicitVarSizeWithDummy[1]], - y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, - y_ExplicitVarSizeWithFlags_Flags[1] -> - y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = y_ExplicitVarSizeWithFlags_Values[1], - y_ExplicitVarSizeWithDummy[1] != 2 -> - y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = y_ExplicitVarSizeWithDummy[1] - diff --git a/tests/exhaustive/basic/typed01/expected/model_2_2_2_1-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_2_2_2_1-solution000001.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_2_2_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_2_2_1-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_2_2_2_1-solution000002.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_2_2_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_2_2_1-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_2_2_2_1-solution000003.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_2_2_1-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_2_2_1.eprime b/tests/exhaustive/basic/typed01/expected/model_2_2_2_1.eprime deleted file mode 100644 index d7c4512020..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_2_2_1.eprime +++ /dev/null @@ -1,13 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -find y_Occurrence: matrix indexed by [int(1)] of bool -branching on [x_ExplicitVarSizeWithDummy, y_Occurrence, y_ExplicitVarSizeWithDummy] -such that - x_ExplicitVarSizeWithDummy[1] != 2 /\ - (y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithDummy[1]) - -> false, - y_Occurrence[1] -> y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = 1, - y_ExplicitVarSizeWithDummy[1] != 2 -> y_Occurrence[y_ExplicitVarSizeWithDummy[1]] - diff --git a/tests/exhaustive/basic/typed01/expected/model_2_2_2_2-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_2_2_2_2-solution000001.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_2_2_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_2_2_2-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_2_2_2_2-solution000002.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_2_2_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_2_2_2-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_2_2_2_2-solution000003.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_2_2_2-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_2_2_2.eprime b/tests/exhaustive/basic/typed01/expected/model_2_2_2_2.eprime deleted file mode 100644 index e0ffb03b92..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_2_2_2.eprime +++ /dev/null @@ -1,10 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -branching on [x_ExplicitVarSizeWithDummy, y_ExplicitVarSizeWithDummy] -such that - x_ExplicitVarSizeWithDummy[1] != 2 /\ - (y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithDummy[1]) - -> false - diff --git a/tests/exhaustive/basic/typed01/expected/model_2_2_2_3-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_2_2_2_3-solution000001.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_2_2_3-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_2_2_3-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_2_2_2_3-solution000002.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_2_2_3-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_2_2_3-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_2_2_2_3-solution000003.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_2_2_3-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_2_2_3.eprime b/tests/exhaustive/basic/typed01/expected/model_2_2_2_3.eprime deleted file mode 100644 index f7ad4f3285..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_2_2_3.eprime +++ /dev/null @@ -1,19 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -find y_ExplicitVarSizeWithMarker_Marker: int(0..1) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -branching on - [x_ExplicitVarSizeWithDummy, y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values, - y_ExplicitVarSizeWithDummy] -such that - x_ExplicitVarSizeWithDummy[1] != 2 /\ - (y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithDummy[1]) - -> false, - 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, - 1 <= y_ExplicitVarSizeWithMarker_Marker -> - y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = y_ExplicitVarSizeWithMarker_Values[1], - y_ExplicitVarSizeWithDummy[1] != 2 -> - 1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = y_ExplicitVarSizeWithDummy[1] - diff --git a/tests/exhaustive/basic/typed01/expected/model_2_2_2_4-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_2_2_2_4-solution000001.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_2_2_4-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_2_2_4-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_2_2_2_4-solution000002.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_2_2_4-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_2_2_4-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_2_2_2_4-solution000003.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_2_2_4-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_2_2_4.eprime b/tests/exhaustive/basic/typed01/expected/model_2_2_2_4.eprime deleted file mode 100644 index c471760f6e..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_2_2_4.eprime +++ /dev/null @@ -1,19 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -branching on - [x_ExplicitVarSizeWithDummy, y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values, - y_ExplicitVarSizeWithDummy] -such that - x_ExplicitVarSizeWithDummy[1] != 2 /\ - (y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithDummy[1]) - -> false, - y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, - y_ExplicitVarSizeWithFlags_Flags[1] -> - y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = y_ExplicitVarSizeWithFlags_Values[1], - y_ExplicitVarSizeWithDummy[1] != 2 -> - y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = y_ExplicitVarSizeWithDummy[1] - diff --git a/tests/exhaustive/basic/typed01/expected/model_2_2_3_1-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_2_2_3_1-solution000001.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_2_3_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_2_3_1-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_2_2_3_1-solution000002.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_2_3_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_2_3_1-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_2_2_3_1-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_2_3_1-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_2_3_1.eprime b/tests/exhaustive/basic/typed01/expected/model_2_2_3_1.eprime deleted file mode 100644 index 222d83cfca..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_2_3_1.eprime +++ /dev/null @@ -1,22 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -find x_ExplicitVarSizeWithMarker_Marker: int(0..1) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -find y_Occurrence: matrix indexed by [int(1)] of bool -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy, y_Occurrence, - y_ExplicitVarSizeWithDummy] -such that - x_ExplicitVarSizeWithDummy[1] != 2 /\ - (y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithDummy[1]) - -> false, - 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, - 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithMarker_Values[1], - x_ExplicitVarSizeWithDummy[1] != 2 -> - 1 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithDummy[1], - y_Occurrence[1] -> y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = 1, - y_ExplicitVarSizeWithDummy[1] != 2 -> y_Occurrence[y_ExplicitVarSizeWithDummy[1]] - diff --git a/tests/exhaustive/basic/typed01/expected/model_2_2_3_2-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_2_2_3_2-solution000001.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_2_3_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_2_3_2-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_2_2_3_2-solution000002.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_2_3_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_2_3_2-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_2_2_3_2-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_2_3_2-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_2_3_2.eprime b/tests/exhaustive/basic/typed01/expected/model_2_2_3_2.eprime deleted file mode 100644 index e9e1de7881..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_2_3_2.eprime +++ /dev/null @@ -1,19 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -find x_ExplicitVarSizeWithMarker_Marker: int(0..1) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy, - y_ExplicitVarSizeWithDummy] -such that - x_ExplicitVarSizeWithDummy[1] != 2 /\ - (y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithDummy[1]) - -> false, - 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, - 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithMarker_Values[1], - x_ExplicitVarSizeWithDummy[1] != 2 -> - 1 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithDummy[1] - diff --git a/tests/exhaustive/basic/typed01/expected/model_2_2_3_3-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_2_2_3_3-solution000001.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_2_3_3-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_2_3_3-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_2_2_3_3-solution000002.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_2_3_3-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_2_3_3-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_2_2_3_3-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_2_3_3-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_2_3_3.eprime b/tests/exhaustive/basic/typed01/expected/model_2_2_3_3.eprime deleted file mode 100644 index 648595c344..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_2_3_3.eprime +++ /dev/null @@ -1,26 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -find x_ExplicitVarSizeWithMarker_Marker: int(0..1) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -find y_ExplicitVarSizeWithMarker_Marker: int(0..1) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy, - y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithDummy] -such that - x_ExplicitVarSizeWithDummy[1] != 2 /\ - (y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithDummy[1]) - -> false, - 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, - 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithMarker_Values[1], - x_ExplicitVarSizeWithDummy[1] != 2 -> - 1 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithDummy[1], - 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, - 1 <= y_ExplicitVarSizeWithMarker_Marker -> - y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = y_ExplicitVarSizeWithMarker_Values[1], - y_ExplicitVarSizeWithDummy[1] != 2 -> - 1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = y_ExplicitVarSizeWithDummy[1] - diff --git a/tests/exhaustive/basic/typed01/expected/model_2_2_3_4-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_2_2_3_4-solution000001.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_2_3_4-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_2_3_4-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_2_2_3_4-solution000002.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_2_3_4-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_2_3_4-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_2_2_3_4-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_2_3_4-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_2_3_4.eprime b/tests/exhaustive/basic/typed01/expected/model_2_2_3_4.eprime deleted file mode 100644 index e35ba1bf82..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_2_3_4.eprime +++ /dev/null @@ -1,26 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -find x_ExplicitVarSizeWithMarker_Marker: int(0..1) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy, - y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithDummy] -such that - x_ExplicitVarSizeWithDummy[1] != 2 /\ - (y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithDummy[1]) - -> false, - 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, - 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithMarker_Values[1], - x_ExplicitVarSizeWithDummy[1] != 2 -> - 1 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithDummy[1], - y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, - y_ExplicitVarSizeWithFlags_Flags[1] -> - y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = y_ExplicitVarSizeWithFlags_Values[1], - y_ExplicitVarSizeWithDummy[1] != 2 -> - y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = y_ExplicitVarSizeWithDummy[1] - diff --git a/tests/exhaustive/basic/typed01/expected/model_2_2_4_1-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_2_2_4_1-solution000001.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_2_4_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_2_4_1-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_2_2_4_1-solution000002.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_2_4_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_2_4_1-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_2_2_4_1-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_2_4_1-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_2_4_1.eprime b/tests/exhaustive/basic/typed01/expected/model_2_2_4_1.eprime deleted file mode 100644 index 5d354a1f60..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_2_4_1.eprime +++ /dev/null @@ -1,22 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -find y_Occurrence: matrix indexed by [int(1)] of bool -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy, y_Occurrence, - y_ExplicitVarSizeWithDummy] -such that - x_ExplicitVarSizeWithDummy[1] != 2 /\ - (y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithDummy[1]) - -> false, - x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, - x_ExplicitVarSizeWithFlags_Flags[1] -> - x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithFlags_Values[1], - x_ExplicitVarSizeWithDummy[1] != 2 -> - x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithDummy[1], - y_Occurrence[1] -> y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = 1, - y_ExplicitVarSizeWithDummy[1] != 2 -> y_Occurrence[y_ExplicitVarSizeWithDummy[1]] - diff --git a/tests/exhaustive/basic/typed01/expected/model_2_2_4_2-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_2_2_4_2-solution000001.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_2_4_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_2_4_2-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_2_2_4_2-solution000002.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_2_4_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_2_4_2-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_2_2_4_2-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_2_4_2-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_2_4_2.eprime b/tests/exhaustive/basic/typed01/expected/model_2_2_4_2.eprime deleted file mode 100644 index 89bf10880d..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_2_4_2.eprime +++ /dev/null @@ -1,19 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy, - y_ExplicitVarSizeWithDummy] -such that - x_ExplicitVarSizeWithDummy[1] != 2 /\ - (y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithDummy[1]) - -> false, - x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, - x_ExplicitVarSizeWithFlags_Flags[1] -> - x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithFlags_Values[1], - x_ExplicitVarSizeWithDummy[1] != 2 -> - x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithDummy[1] - diff --git a/tests/exhaustive/basic/typed01/expected/model_2_2_4_3-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_2_2_4_3-solution000001.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_2_4_3-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_2_4_3-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_2_2_4_3-solution000002.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_2_4_3-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_2_4_3-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_2_2_4_3-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_2_4_3-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_2_4_3.eprime b/tests/exhaustive/basic/typed01/expected/model_2_2_4_3.eprime deleted file mode 100644 index 9fa68409e3..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_2_4_3.eprime +++ /dev/null @@ -1,26 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -find y_ExplicitVarSizeWithMarker_Marker: int(0..1) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy, - y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithDummy] -such that - x_ExplicitVarSizeWithDummy[1] != 2 /\ - (y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithDummy[1]) - -> false, - x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, - x_ExplicitVarSizeWithFlags_Flags[1] -> - x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithFlags_Values[1], - x_ExplicitVarSizeWithDummy[1] != 2 -> - x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithDummy[1], - 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, - 1 <= y_ExplicitVarSizeWithMarker_Marker -> - y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = y_ExplicitVarSizeWithMarker_Values[1], - y_ExplicitVarSizeWithDummy[1] != 2 -> - 1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = y_ExplicitVarSizeWithDummy[1] - diff --git a/tests/exhaustive/basic/typed01/expected/model_2_2_4_4-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_2_2_4_4-solution000001.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_2_4_4-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_2_4_4-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_2_2_4_4-solution000002.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_2_4_4-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_2_4_4-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_2_2_4_4-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_2_4_4-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_2_4_4.eprime b/tests/exhaustive/basic/typed01/expected/model_2_2_4_4.eprime deleted file mode 100644 index f394d4106f..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_2_4_4.eprime +++ /dev/null @@ -1,26 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy, - y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithDummy] -such that - x_ExplicitVarSizeWithDummy[1] != 2 /\ - (y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithDummy[1]) - -> false, - x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, - x_ExplicitVarSizeWithFlags_Flags[1] -> - x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithFlags_Values[1], - x_ExplicitVarSizeWithDummy[1] != 2 -> - x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithDummy[1], - y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, - y_ExplicitVarSizeWithFlags_Flags[1] -> - y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = y_ExplicitVarSizeWithFlags_Values[1], - y_ExplicitVarSizeWithDummy[1] != 2 -> - y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = y_ExplicitVarSizeWithDummy[1] - diff --git a/tests/exhaustive/basic/typed01/expected/model_2_3_1_1-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_2_3_1_1-solution000001.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_3_1_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_3_1_1-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_2_3_1_1-solution000002.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_3_1_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_3_1_1-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_2_3_1_1-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_3_1_1-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_3_1_1.eprime b/tests/exhaustive/basic/typed01/expected/model_2_3_1_1.eprime deleted file mode 100644 index 9bd40c6627..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_3_1_1.eprime +++ /dev/null @@ -1,20 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -find x_Occurrence: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithMarker_Marker: int(0..1) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -find y_Occurrence: matrix indexed by [int(1)] of bool -branching on - [x_Occurrence, x_ExplicitVarSizeWithDummy, y_Occurrence, y_ExplicitVarSizeWithMarker_Marker, - y_ExplicitVarSizeWithMarker_Values] -such that - x_ExplicitVarSizeWithDummy[1] != 2 /\ - (1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithDummy[1]) - -> false, - 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, - x_Occurrence[1] -> x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = 1, - x_ExplicitVarSizeWithDummy[1] != 2 -> x_Occurrence[x_ExplicitVarSizeWithDummy[1]], - y_Occurrence[1] -> 1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = 1, - 1 <= y_ExplicitVarSizeWithMarker_Marker -> y_Occurrence[y_ExplicitVarSizeWithMarker_Values[1]] - diff --git a/tests/exhaustive/basic/typed01/expected/model_2_3_1_2-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_2_3_1_2-solution000001.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_3_1_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_3_1_2-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_2_3_1_2-solution000002.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_3_1_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_3_1_2-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_2_3_1_2-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_3_1_2-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_3_1_2.eprime b/tests/exhaustive/basic/typed01/expected/model_2_3_1_2.eprime deleted file mode 100644 index 04ab19eb01..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_3_1_2.eprime +++ /dev/null @@ -1,22 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -find x_Occurrence: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithMarker_Marker: int(0..1) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -branching on - [x_Occurrence, x_ExplicitVarSizeWithDummy, y_ExplicitVarSizeWithDummy, y_ExplicitVarSizeWithMarker_Marker, - y_ExplicitVarSizeWithMarker_Values] -such that - x_ExplicitVarSizeWithDummy[1] != 2 /\ - (1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithDummy[1]) - -> false, - 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, - x_Occurrence[1] -> x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = 1, - x_ExplicitVarSizeWithDummy[1] != 2 -> x_Occurrence[x_ExplicitVarSizeWithDummy[1]], - y_ExplicitVarSizeWithDummy[1] != 2 -> - 1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = y_ExplicitVarSizeWithDummy[1], - 1 <= y_ExplicitVarSizeWithMarker_Marker -> - y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = y_ExplicitVarSizeWithMarker_Values[1] - diff --git a/tests/exhaustive/basic/typed01/expected/model_2_3_1_3-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_2_3_1_3-solution000001.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_3_1_3-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_3_1_3-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_2_3_1_3-solution000002.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_3_1_3-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_3_1_3-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_2_3_1_3-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_3_1_3-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_3_1_3.eprime b/tests/exhaustive/basic/typed01/expected/model_2_3_1_3.eprime deleted file mode 100644 index f62ac8ebf8..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_3_1_3.eprime +++ /dev/null @@ -1,16 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -find x_Occurrence: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithMarker_Marker: int(0..1) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -branching on - [x_Occurrence, x_ExplicitVarSizeWithDummy, y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values] -such that - x_ExplicitVarSizeWithDummy[1] != 2 /\ - (1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithDummy[1]) - -> false, - 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, - x_Occurrence[1] -> x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = 1, - x_ExplicitVarSizeWithDummy[1] != 2 -> x_Occurrence[x_ExplicitVarSizeWithDummy[1]] - diff --git a/tests/exhaustive/basic/typed01/expected/model_2_3_1_4-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_2_3_1_4-solution000001.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_3_1_4-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_3_1_4-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_2_3_1_4-solution000002.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_3_1_4-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_3_1_4-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_2_3_1_4-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_3_1_4-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_3_1_4.eprime b/tests/exhaustive/basic/typed01/expected/model_2_3_1_4.eprime deleted file mode 100644 index 433e7e48da..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_3_1_4.eprime +++ /dev/null @@ -1,25 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -find x_Occurrence: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithMarker_Marker: int(0..1) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -branching on - [x_Occurrence, x_ExplicitVarSizeWithDummy, y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values, - y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values] -such that - x_ExplicitVarSizeWithDummy[1] != 2 /\ - (1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithDummy[1]) - -> false, - 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, - x_Occurrence[1] -> x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = 1, - x_ExplicitVarSizeWithDummy[1] != 2 -> x_Occurrence[x_ExplicitVarSizeWithDummy[1]], - y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, - y_ExplicitVarSizeWithFlags_Flags[1] -> - 1 <= y_ExplicitVarSizeWithMarker_Marker /\ - y_ExplicitVarSizeWithMarker_Values[1] = y_ExplicitVarSizeWithFlags_Values[1], - 1 <= y_ExplicitVarSizeWithMarker_Marker -> - y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = y_ExplicitVarSizeWithMarker_Values[1] - diff --git a/tests/exhaustive/basic/typed01/expected/model_2_3_2_1-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_2_3_2_1-solution000001.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_3_2_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_3_2_1-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_2_3_2_1-solution000002.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_3_2_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_3_2_1-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_2_3_2_1-solution000003.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_3_2_1-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_3_2_1.eprime b/tests/exhaustive/basic/typed01/expected/model_2_3_2_1.eprime deleted file mode 100644 index c501d3da77..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_3_2_1.eprime +++ /dev/null @@ -1,16 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -find y_ExplicitVarSizeWithMarker_Marker: int(0..1) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -find y_Occurrence: matrix indexed by [int(1)] of bool -branching on - [x_ExplicitVarSizeWithDummy, y_Occurrence, y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values] -such that - x_ExplicitVarSizeWithDummy[1] != 2 /\ - (1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithDummy[1]) - -> false, - 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, - y_Occurrence[1] -> 1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = 1, - 1 <= y_ExplicitVarSizeWithMarker_Marker -> y_Occurrence[y_ExplicitVarSizeWithMarker_Values[1]] - diff --git a/tests/exhaustive/basic/typed01/expected/model_2_3_2_2-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_2_3_2_2-solution000001.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_3_2_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_3_2_2-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_2_3_2_2-solution000002.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_3_2_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_3_2_2-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_2_3_2_2-solution000003.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_3_2_2-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_3_2_2.eprime b/tests/exhaustive/basic/typed01/expected/model_2_3_2_2.eprime deleted file mode 100644 index eff11cdc36..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_3_2_2.eprime +++ /dev/null @@ -1,19 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -find y_ExplicitVarSizeWithMarker_Marker: int(0..1) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -branching on - [x_ExplicitVarSizeWithDummy, y_ExplicitVarSizeWithDummy, y_ExplicitVarSizeWithMarker_Marker, - y_ExplicitVarSizeWithMarker_Values] -such that - x_ExplicitVarSizeWithDummy[1] != 2 /\ - (1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithDummy[1]) - -> false, - 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, - y_ExplicitVarSizeWithDummy[1] != 2 -> - 1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = y_ExplicitVarSizeWithDummy[1], - 1 <= y_ExplicitVarSizeWithMarker_Marker -> - y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = y_ExplicitVarSizeWithMarker_Values[1] - diff --git a/tests/exhaustive/basic/typed01/expected/model_2_3_2_3-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_2_3_2_3-solution000001.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_3_2_3-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_3_2_3-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_2_3_2_3-solution000002.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_3_2_3-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_3_2_3-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_2_3_2_3-solution000003.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_3_2_3-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_3_2_3.eprime b/tests/exhaustive/basic/typed01/expected/model_2_3_2_3.eprime deleted file mode 100644 index fb495deda8..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_3_2_3.eprime +++ /dev/null @@ -1,12 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -find y_ExplicitVarSizeWithMarker_Marker: int(0..1) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -branching on [x_ExplicitVarSizeWithDummy, y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values] -such that - x_ExplicitVarSizeWithDummy[1] != 2 /\ - (1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithDummy[1]) - -> false, - 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1 - diff --git a/tests/exhaustive/basic/typed01/expected/model_2_3_2_4-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_2_3_2_4-solution000001.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_3_2_4-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_3_2_4-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_2_3_2_4-solution000002.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_3_2_4-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_3_2_4-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_2_3_2_4-solution000003.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_3_2_4-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_3_2_4.eprime b/tests/exhaustive/basic/typed01/expected/model_2_3_2_4.eprime deleted file mode 100644 index cea7c108f0..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_3_2_4.eprime +++ /dev/null @@ -1,22 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -find y_ExplicitVarSizeWithMarker_Marker: int(0..1) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -branching on - [x_ExplicitVarSizeWithDummy, y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values, - y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values] -such that - x_ExplicitVarSizeWithDummy[1] != 2 /\ - (1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithDummy[1]) - -> false, - 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, - y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, - y_ExplicitVarSizeWithFlags_Flags[1] -> - 1 <= y_ExplicitVarSizeWithMarker_Marker /\ - y_ExplicitVarSizeWithMarker_Values[1] = y_ExplicitVarSizeWithFlags_Values[1], - 1 <= y_ExplicitVarSizeWithMarker_Marker -> - y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = y_ExplicitVarSizeWithMarker_Values[1] - diff --git a/tests/exhaustive/basic/typed01/expected/model_2_3_3_1-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_2_3_3_1-solution000001.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_3_3_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_3_3_1-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_2_3_3_1-solution000002.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_3_3_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_3_3_1-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_2_3_3_1-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_3_3_1-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_3_3_1.eprime b/tests/exhaustive/basic/typed01/expected/model_2_3_3_1.eprime deleted file mode 100644 index a96e186edc..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_3_3_1.eprime +++ /dev/null @@ -1,24 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -find x_ExplicitVarSizeWithMarker_Marker: int(0..1) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -find y_ExplicitVarSizeWithMarker_Marker: int(0..1) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -find y_Occurrence: matrix indexed by [int(1)] of bool -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy, y_Occurrence, - y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values] -such that - x_ExplicitVarSizeWithDummy[1] != 2 /\ - (1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithDummy[1]) - -> false, - 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, - 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, - 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithMarker_Values[1], - x_ExplicitVarSizeWithDummy[1] != 2 -> - 1 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithDummy[1], - y_Occurrence[1] -> 1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = 1, - 1 <= y_ExplicitVarSizeWithMarker_Marker -> y_Occurrence[y_ExplicitVarSizeWithMarker_Values[1]] - diff --git a/tests/exhaustive/basic/typed01/expected/model_2_3_3_2-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_2_3_3_2-solution000001.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_3_3_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_3_3_2-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_2_3_3_2-solution000002.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_3_3_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_3_3_2-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_2_3_3_2-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_3_3_2-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_3_3_2.eprime b/tests/exhaustive/basic/typed01/expected/model_2_3_3_2.eprime deleted file mode 100644 index f0f0f557c3..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_3_3_2.eprime +++ /dev/null @@ -1,26 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -find x_ExplicitVarSizeWithMarker_Marker: int(0..1) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -find y_ExplicitVarSizeWithMarker_Marker: int(0..1) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy, - y_ExplicitVarSizeWithDummy, y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values] -such that - x_ExplicitVarSizeWithDummy[1] != 2 /\ - (1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithDummy[1]) - -> false, - 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, - 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, - 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithMarker_Values[1], - x_ExplicitVarSizeWithDummy[1] != 2 -> - 1 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithDummy[1], - y_ExplicitVarSizeWithDummy[1] != 2 -> - 1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = y_ExplicitVarSizeWithDummy[1], - 1 <= y_ExplicitVarSizeWithMarker_Marker -> - y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = y_ExplicitVarSizeWithMarker_Values[1] - diff --git a/tests/exhaustive/basic/typed01/expected/model_2_3_3_3-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_2_3_3_3-solution000001.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_3_3_3-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_3_3_3-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_2_3_3_3-solution000002.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_3_3_3-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_3_3_3-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_2_3_3_3-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_3_3_3-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_3_3_3.eprime b/tests/exhaustive/basic/typed01/expected/model_2_3_3_3.eprime deleted file mode 100644 index 455d856d44..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_3_3_3.eprime +++ /dev/null @@ -1,21 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -find x_ExplicitVarSizeWithMarker_Marker: int(0..1) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -find y_ExplicitVarSizeWithMarker_Marker: int(0..1) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy, - y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values] -such that - x_ExplicitVarSizeWithDummy[1] != 2 /\ - (1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithDummy[1]) - -> false, - 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, - 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, - 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithMarker_Values[1], - x_ExplicitVarSizeWithDummy[1] != 2 -> - 1 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithDummy[1] - diff --git a/tests/exhaustive/basic/typed01/expected/model_2_3_3_4-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_2_3_3_4-solution000001.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_3_3_4-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_3_3_4-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_2_3_3_4-solution000002.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_3_3_4-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_3_3_4-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_2_3_3_4-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_3_3_4-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_3_3_4.eprime b/tests/exhaustive/basic/typed01/expected/model_2_3_3_4.eprime deleted file mode 100644 index 4d85bf465b..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_3_3_4.eprime +++ /dev/null @@ -1,30 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -find x_ExplicitVarSizeWithMarker_Marker: int(0..1) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -find y_ExplicitVarSizeWithMarker_Marker: int(0..1) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy, - y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithMarker_Marker, - y_ExplicitVarSizeWithMarker_Values] -such that - x_ExplicitVarSizeWithDummy[1] != 2 /\ - (1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithDummy[1]) - -> false, - 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, - 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, - 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithMarker_Values[1], - x_ExplicitVarSizeWithDummy[1] != 2 -> - 1 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithDummy[1], - y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, - y_ExplicitVarSizeWithFlags_Flags[1] -> - 1 <= y_ExplicitVarSizeWithMarker_Marker /\ - y_ExplicitVarSizeWithMarker_Values[1] = y_ExplicitVarSizeWithFlags_Values[1], - 1 <= y_ExplicitVarSizeWithMarker_Marker -> - y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = y_ExplicitVarSizeWithMarker_Values[1] - diff --git a/tests/exhaustive/basic/typed01/expected/model_2_3_4_1-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_2_3_4_1-solution000001.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_3_4_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_3_4_1-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_2_3_4_1-solution000002.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_3_4_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_3_4_1-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_2_3_4_1-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_3_4_1-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_3_4_1.eprime b/tests/exhaustive/basic/typed01/expected/model_2_3_4_1.eprime deleted file mode 100644 index b51cd218eb..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_3_4_1.eprime +++ /dev/null @@ -1,24 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -find y_ExplicitVarSizeWithMarker_Marker: int(0..1) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -find y_Occurrence: matrix indexed by [int(1)] of bool -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy, y_Occurrence, - y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values] -such that - x_ExplicitVarSizeWithDummy[1] != 2 /\ - (1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithDummy[1]) - -> false, - 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, - x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, - x_ExplicitVarSizeWithFlags_Flags[1] -> - x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithFlags_Values[1], - x_ExplicitVarSizeWithDummy[1] != 2 -> - x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithDummy[1], - y_Occurrence[1] -> 1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = 1, - 1 <= y_ExplicitVarSizeWithMarker_Marker -> y_Occurrence[y_ExplicitVarSizeWithMarker_Values[1]] - diff --git a/tests/exhaustive/basic/typed01/expected/model_2_3_4_2-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_2_3_4_2-solution000001.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_3_4_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_3_4_2-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_2_3_4_2-solution000002.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_3_4_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_3_4_2-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_2_3_4_2-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_3_4_2-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_3_4_2.eprime b/tests/exhaustive/basic/typed01/expected/model_2_3_4_2.eprime deleted file mode 100644 index 9a22181e07..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_3_4_2.eprime +++ /dev/null @@ -1,26 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -find y_ExplicitVarSizeWithMarker_Marker: int(0..1) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy, - y_ExplicitVarSizeWithDummy, y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values] -such that - x_ExplicitVarSizeWithDummy[1] != 2 /\ - (1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithDummy[1]) - -> false, - 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, - x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, - x_ExplicitVarSizeWithFlags_Flags[1] -> - x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithFlags_Values[1], - x_ExplicitVarSizeWithDummy[1] != 2 -> - x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithDummy[1], - y_ExplicitVarSizeWithDummy[1] != 2 -> - 1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = y_ExplicitVarSizeWithDummy[1], - 1 <= y_ExplicitVarSizeWithMarker_Marker -> - y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = y_ExplicitVarSizeWithMarker_Values[1] - diff --git a/tests/exhaustive/basic/typed01/expected/model_2_3_4_3-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_2_3_4_3-solution000001.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_3_4_3-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_3_4_3-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_2_3_4_3-solution000002.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_3_4_3-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_3_4_3-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_2_3_4_3-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_3_4_3-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_3_4_3.eprime b/tests/exhaustive/basic/typed01/expected/model_2_3_4_3.eprime deleted file mode 100644 index 38adccfc56..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_3_4_3.eprime +++ /dev/null @@ -1,21 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -find y_ExplicitVarSizeWithMarker_Marker: int(0..1) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy, - y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values] -such that - x_ExplicitVarSizeWithDummy[1] != 2 /\ - (1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithDummy[1]) - -> false, - 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, - x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, - x_ExplicitVarSizeWithFlags_Flags[1] -> - x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithFlags_Values[1], - x_ExplicitVarSizeWithDummy[1] != 2 -> - x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithDummy[1] - diff --git a/tests/exhaustive/basic/typed01/expected/model_2_3_4_4-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_2_3_4_4-solution000001.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_3_4_4-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_3_4_4-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_2_3_4_4-solution000002.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_3_4_4-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_3_4_4-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_2_3_4_4-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_3_4_4-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_3_4_4.eprime b/tests/exhaustive/basic/typed01/expected/model_2_3_4_4.eprime deleted file mode 100644 index 4eaa9ed45c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_3_4_4.eprime +++ /dev/null @@ -1,30 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -find y_ExplicitVarSizeWithMarker_Marker: int(0..1) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy, - y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithMarker_Marker, - y_ExplicitVarSizeWithMarker_Values] -such that - x_ExplicitVarSizeWithDummy[1] != 2 /\ - (1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithDummy[1]) - -> false, - 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, - x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, - x_ExplicitVarSizeWithFlags_Flags[1] -> - x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithFlags_Values[1], - x_ExplicitVarSizeWithDummy[1] != 2 -> - x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithDummy[1], - y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, - y_ExplicitVarSizeWithFlags_Flags[1] -> - 1 <= y_ExplicitVarSizeWithMarker_Marker /\ - y_ExplicitVarSizeWithMarker_Values[1] = y_ExplicitVarSizeWithFlags_Values[1], - 1 <= y_ExplicitVarSizeWithMarker_Marker -> - y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = y_ExplicitVarSizeWithMarker_Values[1] - diff --git a/tests/exhaustive/basic/typed01/expected/model_2_4_1_1-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_2_4_1_1-solution000001.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_4_1_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_4_1_1-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_2_4_1_1-solution000002.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_4_1_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_4_1_1-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_2_4_1_1-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_4_1_1-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_4_1_1.eprime b/tests/exhaustive/basic/typed01/expected/model_2_4_1_1.eprime deleted file mode 100644 index 27384abdaa..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_4_1_1.eprime +++ /dev/null @@ -1,20 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -find x_Occurrence: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -find y_Occurrence: matrix indexed by [int(1)] of bool -branching on - [x_Occurrence, x_ExplicitVarSizeWithDummy, y_Occurrence, y_ExplicitVarSizeWithFlags_Flags, - y_ExplicitVarSizeWithFlags_Values] -such that - x_ExplicitVarSizeWithDummy[1] != 2 /\ - (y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithDummy[1]) - -> false, - y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, - x_Occurrence[1] -> x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = 1, - x_ExplicitVarSizeWithDummy[1] != 2 -> x_Occurrence[x_ExplicitVarSizeWithDummy[1]], - y_Occurrence[1] -> y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = 1, - y_ExplicitVarSizeWithFlags_Flags[1] -> y_Occurrence[y_ExplicitVarSizeWithFlags_Values[1]] - diff --git a/tests/exhaustive/basic/typed01/expected/model_2_4_1_2-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_2_4_1_2-solution000001.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_4_1_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_4_1_2-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_2_4_1_2-solution000002.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_4_1_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_4_1_2-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_2_4_1_2-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_4_1_2-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_4_1_2.eprime b/tests/exhaustive/basic/typed01/expected/model_2_4_1_2.eprime deleted file mode 100644 index 756d504a56..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_4_1_2.eprime +++ /dev/null @@ -1,22 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -find x_Occurrence: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -branching on - [x_Occurrence, x_ExplicitVarSizeWithDummy, y_ExplicitVarSizeWithDummy, y_ExplicitVarSizeWithFlags_Flags, - y_ExplicitVarSizeWithFlags_Values] -such that - x_ExplicitVarSizeWithDummy[1] != 2 /\ - (y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithDummy[1]) - -> false, - y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, - x_Occurrence[1] -> x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = 1, - x_ExplicitVarSizeWithDummy[1] != 2 -> x_Occurrence[x_ExplicitVarSizeWithDummy[1]], - y_ExplicitVarSizeWithDummy[1] != 2 -> - y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = y_ExplicitVarSizeWithDummy[1], - y_ExplicitVarSizeWithFlags_Flags[1] -> - y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = y_ExplicitVarSizeWithFlags_Values[1] - diff --git a/tests/exhaustive/basic/typed01/expected/model_2_4_1_3-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_2_4_1_3-solution000001.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_4_1_3-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_4_1_3-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_2_4_1_3-solution000002.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_4_1_3-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_4_1_3-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_2_4_1_3-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_4_1_3-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_4_1_3.eprime b/tests/exhaustive/basic/typed01/expected/model_2_4_1_3.eprime deleted file mode 100644 index 950474f419..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_4_1_3.eprime +++ /dev/null @@ -1,25 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -find x_Occurrence: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -find y_ExplicitVarSizeWithMarker_Marker: int(0..1) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -branching on - [x_Occurrence, x_ExplicitVarSizeWithDummy, y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values, - y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values] -such that - x_ExplicitVarSizeWithDummy[1] != 2 /\ - (y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithDummy[1]) - -> false, - y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, - x_Occurrence[1] -> x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = 1, - x_ExplicitVarSizeWithDummy[1] != 2 -> x_Occurrence[x_ExplicitVarSizeWithDummy[1]], - 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, - 1 <= y_ExplicitVarSizeWithMarker_Marker -> - y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = y_ExplicitVarSizeWithMarker_Values[1], - y_ExplicitVarSizeWithFlags_Flags[1] -> - 1 <= y_ExplicitVarSizeWithMarker_Marker /\ - y_ExplicitVarSizeWithMarker_Values[1] = y_ExplicitVarSizeWithFlags_Values[1] - diff --git a/tests/exhaustive/basic/typed01/expected/model_2_4_1_4-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_2_4_1_4-solution000001.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_4_1_4-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_4_1_4-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_2_4_1_4-solution000002.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_4_1_4-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_4_1_4-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_2_4_1_4-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_4_1_4-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_4_1_4.eprime b/tests/exhaustive/basic/typed01/expected/model_2_4_1_4.eprime deleted file mode 100644 index b9abdd4e8a..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_4_1_4.eprime +++ /dev/null @@ -1,16 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -find x_Occurrence: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -branching on - [x_Occurrence, x_ExplicitVarSizeWithDummy, y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values] -such that - x_ExplicitVarSizeWithDummy[1] != 2 /\ - (y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithDummy[1]) - -> false, - y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, - x_Occurrence[1] -> x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = 1, - x_ExplicitVarSizeWithDummy[1] != 2 -> x_Occurrence[x_ExplicitVarSizeWithDummy[1]] - diff --git a/tests/exhaustive/basic/typed01/expected/model_2_4_2_1-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_2_4_2_1-solution000001.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_4_2_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_4_2_1-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_2_4_2_1-solution000002.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_4_2_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_4_2_1-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_2_4_2_1-solution000003.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_4_2_1-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_4_2_1.eprime b/tests/exhaustive/basic/typed01/expected/model_2_4_2_1.eprime deleted file mode 100644 index 9305aca214..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_4_2_1.eprime +++ /dev/null @@ -1,16 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -find y_Occurrence: matrix indexed by [int(1)] of bool -branching on - [x_ExplicitVarSizeWithDummy, y_Occurrence, y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values] -such that - x_ExplicitVarSizeWithDummy[1] != 2 /\ - (y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithDummy[1]) - -> false, - y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, - y_Occurrence[1] -> y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = 1, - y_ExplicitVarSizeWithFlags_Flags[1] -> y_Occurrence[y_ExplicitVarSizeWithFlags_Values[1]] - diff --git a/tests/exhaustive/basic/typed01/expected/model_2_4_2_2-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_2_4_2_2-solution000001.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_4_2_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_4_2_2-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_2_4_2_2-solution000002.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_4_2_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_4_2_2-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_2_4_2_2-solution000003.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_4_2_2-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_4_2_2.eprime b/tests/exhaustive/basic/typed01/expected/model_2_4_2_2.eprime deleted file mode 100644 index e767d28abb..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_4_2_2.eprime +++ /dev/null @@ -1,19 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -branching on - [x_ExplicitVarSizeWithDummy, y_ExplicitVarSizeWithDummy, y_ExplicitVarSizeWithFlags_Flags, - y_ExplicitVarSizeWithFlags_Values] -such that - x_ExplicitVarSizeWithDummy[1] != 2 /\ - (y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithDummy[1]) - -> false, - y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, - y_ExplicitVarSizeWithDummy[1] != 2 -> - y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = y_ExplicitVarSizeWithDummy[1], - y_ExplicitVarSizeWithFlags_Flags[1] -> - y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = y_ExplicitVarSizeWithFlags_Values[1] - diff --git a/tests/exhaustive/basic/typed01/expected/model_2_4_2_3-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_2_4_2_3-solution000001.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_4_2_3-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_4_2_3-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_2_4_2_3-solution000002.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_4_2_3-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_4_2_3-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_2_4_2_3-solution000003.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_4_2_3-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_4_2_3.eprime b/tests/exhaustive/basic/typed01/expected/model_2_4_2_3.eprime deleted file mode 100644 index b7697fa29f..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_4_2_3.eprime +++ /dev/null @@ -1,22 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -find y_ExplicitVarSizeWithMarker_Marker: int(0..1) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -branching on - [x_ExplicitVarSizeWithDummy, y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values, - y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values] -such that - x_ExplicitVarSizeWithDummy[1] != 2 /\ - (y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithDummy[1]) - -> false, - y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, - 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, - 1 <= y_ExplicitVarSizeWithMarker_Marker -> - y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = y_ExplicitVarSizeWithMarker_Values[1], - y_ExplicitVarSizeWithFlags_Flags[1] -> - 1 <= y_ExplicitVarSizeWithMarker_Marker /\ - y_ExplicitVarSizeWithMarker_Values[1] = y_ExplicitVarSizeWithFlags_Values[1] - diff --git a/tests/exhaustive/basic/typed01/expected/model_2_4_2_4-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_2_4_2_4-solution000001.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_4_2_4-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_4_2_4-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_2_4_2_4-solution000002.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_4_2_4-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_4_2_4-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_2_4_2_4-solution000003.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_4_2_4-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_4_2_4.eprime b/tests/exhaustive/basic/typed01/expected/model_2_4_2_4.eprime deleted file mode 100644 index 81345e4ad5..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_4_2_4.eprime +++ /dev/null @@ -1,12 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -branching on [x_ExplicitVarSizeWithDummy, y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values] -such that - x_ExplicitVarSizeWithDummy[1] != 2 /\ - (y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithDummy[1]) - -> false, - y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1 - diff --git a/tests/exhaustive/basic/typed01/expected/model_2_4_3_1-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_2_4_3_1-solution000001.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_4_3_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_4_3_1-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_2_4_3_1-solution000002.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_4_3_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_4_3_1-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_2_4_3_1-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_4_3_1-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_4_3_1.eprime b/tests/exhaustive/basic/typed01/expected/model_2_4_3_1.eprime deleted file mode 100644 index 2d924bfba1..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_4_3_1.eprime +++ /dev/null @@ -1,24 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -find x_ExplicitVarSizeWithMarker_Marker: int(0..1) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -find y_Occurrence: matrix indexed by [int(1)] of bool -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy, y_Occurrence, - y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values] -such that - x_ExplicitVarSizeWithDummy[1] != 2 /\ - (y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithDummy[1]) - -> false, - y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, - 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, - 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithMarker_Values[1], - x_ExplicitVarSizeWithDummy[1] != 2 -> - 1 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithDummy[1], - y_Occurrence[1] -> y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = 1, - y_ExplicitVarSizeWithFlags_Flags[1] -> y_Occurrence[y_ExplicitVarSizeWithFlags_Values[1]] - diff --git a/tests/exhaustive/basic/typed01/expected/model_2_4_3_2-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_2_4_3_2-solution000001.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_4_3_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_4_3_2-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_2_4_3_2-solution000002.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_4_3_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_4_3_2-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_2_4_3_2-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_4_3_2-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_4_3_2.eprime b/tests/exhaustive/basic/typed01/expected/model_2_4_3_2.eprime deleted file mode 100644 index bef3b1d9e8..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_4_3_2.eprime +++ /dev/null @@ -1,26 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -find x_ExplicitVarSizeWithMarker_Marker: int(0..1) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy, - y_ExplicitVarSizeWithDummy, y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values] -such that - x_ExplicitVarSizeWithDummy[1] != 2 /\ - (y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithDummy[1]) - -> false, - y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, - 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, - 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithMarker_Values[1], - x_ExplicitVarSizeWithDummy[1] != 2 -> - 1 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithDummy[1], - y_ExplicitVarSizeWithDummy[1] != 2 -> - y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = y_ExplicitVarSizeWithDummy[1], - y_ExplicitVarSizeWithFlags_Flags[1] -> - y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = y_ExplicitVarSizeWithFlags_Values[1] - diff --git a/tests/exhaustive/basic/typed01/expected/model_2_4_3_3-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_2_4_3_3-solution000001.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_4_3_3-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_4_3_3-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_2_4_3_3-solution000002.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_4_3_3-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_4_3_3-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_2_4_3_3-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_4_3_3-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_4_3_3.eprime b/tests/exhaustive/basic/typed01/expected/model_2_4_3_3.eprime deleted file mode 100644 index b8a64e76d1..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_4_3_3.eprime +++ /dev/null @@ -1,30 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -find x_ExplicitVarSizeWithMarker_Marker: int(0..1) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -find y_ExplicitVarSizeWithMarker_Marker: int(0..1) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy, - y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithFlags_Flags, - y_ExplicitVarSizeWithFlags_Values] -such that - x_ExplicitVarSizeWithDummy[1] != 2 /\ - (y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithDummy[1]) - -> false, - y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, - 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, - 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithMarker_Values[1], - x_ExplicitVarSizeWithDummy[1] != 2 -> - 1 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithDummy[1], - 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, - 1 <= y_ExplicitVarSizeWithMarker_Marker -> - y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = y_ExplicitVarSizeWithMarker_Values[1], - y_ExplicitVarSizeWithFlags_Flags[1] -> - 1 <= y_ExplicitVarSizeWithMarker_Marker /\ - y_ExplicitVarSizeWithMarker_Values[1] = y_ExplicitVarSizeWithFlags_Values[1] - diff --git a/tests/exhaustive/basic/typed01/expected/model_2_4_3_4-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_2_4_3_4-solution000001.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_4_3_4-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_4_3_4-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_2_4_3_4-solution000002.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_4_3_4-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_4_3_4-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_2_4_3_4-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_4_3_4-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_4_3_4.eprime b/tests/exhaustive/basic/typed01/expected/model_2_4_3_4.eprime deleted file mode 100644 index 73e37546d5..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_4_3_4.eprime +++ /dev/null @@ -1,21 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -find x_ExplicitVarSizeWithMarker_Marker: int(0..1) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy, - y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values] -such that - x_ExplicitVarSizeWithDummy[1] != 2 /\ - (y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithDummy[1]) - -> false, - y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, - 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, - 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithMarker_Values[1], - x_ExplicitVarSizeWithDummy[1] != 2 -> - 1 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithDummy[1] - diff --git a/tests/exhaustive/basic/typed01/expected/model_2_4_4_1-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_2_4_4_1-solution000001.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_4_4_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_4_4_1-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_2_4_4_1-solution000002.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_4_4_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_4_4_1-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_2_4_4_1-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_4_4_1-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_4_4_1.eprime b/tests/exhaustive/basic/typed01/expected/model_2_4_4_1.eprime deleted file mode 100644 index f983f59967..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_4_4_1.eprime +++ /dev/null @@ -1,24 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -find y_Occurrence: matrix indexed by [int(1)] of bool -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy, y_Occurrence, - y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values] -such that - x_ExplicitVarSizeWithDummy[1] != 2 /\ - (y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithDummy[1]) - -> false, - y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, - x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, - x_ExplicitVarSizeWithFlags_Flags[1] -> - x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithFlags_Values[1], - x_ExplicitVarSizeWithDummy[1] != 2 -> - x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithDummy[1], - y_Occurrence[1] -> y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = 1, - y_ExplicitVarSizeWithFlags_Flags[1] -> y_Occurrence[y_ExplicitVarSizeWithFlags_Values[1]] - diff --git a/tests/exhaustive/basic/typed01/expected/model_2_4_4_2-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_2_4_4_2-solution000001.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_4_4_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_4_4_2-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_2_4_4_2-solution000002.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_4_4_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_4_4_2-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_2_4_4_2-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_4_4_2-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_4_4_2.eprime b/tests/exhaustive/basic/typed01/expected/model_2_4_4_2.eprime deleted file mode 100644 index d0265ea199..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_4_4_2.eprime +++ /dev/null @@ -1,26 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy, - y_ExplicitVarSizeWithDummy, y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values] -such that - x_ExplicitVarSizeWithDummy[1] != 2 /\ - (y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithDummy[1]) - -> false, - y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, - x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, - x_ExplicitVarSizeWithFlags_Flags[1] -> - x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithFlags_Values[1], - x_ExplicitVarSizeWithDummy[1] != 2 -> - x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithDummy[1], - y_ExplicitVarSizeWithDummy[1] != 2 -> - y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = y_ExplicitVarSizeWithDummy[1], - y_ExplicitVarSizeWithFlags_Flags[1] -> - y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = y_ExplicitVarSizeWithFlags_Values[1] - diff --git a/tests/exhaustive/basic/typed01/expected/model_2_4_4_3-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_2_4_4_3-solution000001.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_4_4_3-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_4_4_3-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_2_4_4_3-solution000002.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_4_4_3-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_4_4_3-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_2_4_4_3-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_4_4_3-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_4_4_3.eprime b/tests/exhaustive/basic/typed01/expected/model_2_4_4_3.eprime deleted file mode 100644 index 2d70798d52..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_4_4_3.eprime +++ /dev/null @@ -1,30 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -find y_ExplicitVarSizeWithMarker_Marker: int(0..1) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy, - y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithFlags_Flags, - y_ExplicitVarSizeWithFlags_Values] -such that - x_ExplicitVarSizeWithDummy[1] != 2 /\ - (y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithDummy[1]) - -> false, - y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, - x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, - x_ExplicitVarSizeWithFlags_Flags[1] -> - x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithFlags_Values[1], - x_ExplicitVarSizeWithDummy[1] != 2 -> - x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithDummy[1], - 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, - 1 <= y_ExplicitVarSizeWithMarker_Marker -> - y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = y_ExplicitVarSizeWithMarker_Values[1], - y_ExplicitVarSizeWithFlags_Flags[1] -> - 1 <= y_ExplicitVarSizeWithMarker_Marker /\ - y_ExplicitVarSizeWithMarker_Values[1] = y_ExplicitVarSizeWithFlags_Values[1] - diff --git a/tests/exhaustive/basic/typed01/expected/model_2_4_4_4-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_2_4_4_4-solution000001.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_4_4_4-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_4_4_4-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_2_4_4_4-solution000002.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_4_4_4-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_4_4_4-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_2_4_4_4-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_4_4_4-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_4_4_4.eprime b/tests/exhaustive/basic/typed01/expected/model_2_4_4_4.eprime deleted file mode 100644 index eb8ed6d4d1..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_2_4_4_4.eprime +++ /dev/null @@ -1,21 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy, - y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values] -such that - x_ExplicitVarSizeWithDummy[1] != 2 /\ - (y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithDummy[1]) - -> false, - y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, - x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, - x_ExplicitVarSizeWithFlags_Flags[1] -> - x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithFlags_Values[1], - x_ExplicitVarSizeWithDummy[1] != 2 -> - x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithDummy[1] - diff --git a/tests/exhaustive/basic/typed01/expected/model_3_1_1_1-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_3_1_1_1-solution000001.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_1_1_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_1_1_1-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_3_1_1_1-solution000002.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_1_1_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_1_1_1-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_3_1_1_1-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_1_1_1-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_1_1_1.eprime b/tests/exhaustive/basic/typed01/expected/model_3_1_1_1.eprime deleted file mode 100644 index b1f9d14f8a..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_1_1_1.eprime +++ /dev/null @@ -1,13 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..1) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -find x_Occurrence: matrix indexed by [int(1)] of bool -find y_Occurrence: matrix indexed by [int(1)] of bool -branching on [x_Occurrence, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, y_Occurrence] -such that - 1 <= x_ExplicitVarSizeWithMarker_Marker /\ y_Occurrence[x_ExplicitVarSizeWithMarker_Values[1]] -> false, - 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, - x_Occurrence[1] -> 1 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[1] = 1, - 1 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[1]] - diff --git a/tests/exhaustive/basic/typed01/expected/model_3_1_1_2-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_3_1_1_2-solution000001.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_1_1_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_1_1_2-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_3_1_1_2-solution000002.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_1_1_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_1_1_2-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_3_1_1_2-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_1_1_2-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_1_1_2.eprime b/tests/exhaustive/basic/typed01/expected/model_3_1_1_2.eprime deleted file mode 100644 index 0e577a8eac..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_1_1_2.eprime +++ /dev/null @@ -1,18 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..1) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -find x_Occurrence: matrix indexed by [int(1)] of bool -find y_Occurrence: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -branching on - [x_Occurrence, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithDummy, - y_Occurrence] -such that - 1 <= x_ExplicitVarSizeWithMarker_Marker /\ y_Occurrence[x_ExplicitVarSizeWithMarker_Values[1]] -> false, - 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, - x_Occurrence[1] -> 1 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[1] = 1, - 1 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[1]], - y_ExplicitVarSizeWithDummy[1] != 2 -> y_Occurrence[y_ExplicitVarSizeWithDummy[1]], - y_Occurrence[1] -> y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = 1 - diff --git a/tests/exhaustive/basic/typed01/expected/model_3_1_1_3-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_3_1_1_3-solution000001.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_1_1_3-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_1_1_3-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_3_1_1_3-solution000002.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_1_1_3-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_1_1_3-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_3_1_1_3-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_1_1_3-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_1_1_3.eprime b/tests/exhaustive/basic/typed01/expected/model_3_1_1_3.eprime deleted file mode 100644 index 20840fd0f7..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_1_1_3.eprime +++ /dev/null @@ -1,20 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..1) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -find x_Occurrence: matrix indexed by [int(1)] of bool -find y_Occurrence: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithMarker_Marker: int(0..1) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -branching on - [x_Occurrence, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, - y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values, y_Occurrence] -such that - 1 <= x_ExplicitVarSizeWithMarker_Marker /\ y_Occurrence[x_ExplicitVarSizeWithMarker_Values[1]] -> false, - 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, - x_Occurrence[1] -> 1 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[1] = 1, - 1 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[1]], - 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, - 1 <= y_ExplicitVarSizeWithMarker_Marker -> y_Occurrence[y_ExplicitVarSizeWithMarker_Values[1]], - y_Occurrence[1] -> 1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = 1 - diff --git a/tests/exhaustive/basic/typed01/expected/model_3_1_1_4-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_3_1_1_4-solution000001.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_1_1_4-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_1_1_4-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_3_1_1_4-solution000002.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_1_1_4-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_1_1_4-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_3_1_1_4-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_1_1_4-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_1_1_4.eprime b/tests/exhaustive/basic/typed01/expected/model_3_1_1_4.eprime deleted file mode 100644 index 15ecf4d3a3..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_1_1_4.eprime +++ /dev/null @@ -1,20 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..1) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -find x_Occurrence: matrix indexed by [int(1)] of bool -find y_Occurrence: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -branching on - [x_Occurrence, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, - y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values, y_Occurrence] -such that - 1 <= x_ExplicitVarSizeWithMarker_Marker /\ y_Occurrence[x_ExplicitVarSizeWithMarker_Values[1]] -> false, - 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, - x_Occurrence[1] -> 1 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[1] = 1, - 1 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[1]], - y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, - y_ExplicitVarSizeWithFlags_Flags[1] -> y_Occurrence[y_ExplicitVarSizeWithFlags_Values[1]], - y_Occurrence[1] -> y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = 1 - diff --git a/tests/exhaustive/basic/typed01/expected/model_3_1_2_1-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_3_1_2_1-solution000001.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_1_2_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_1_2_1-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_3_1_2_1-solution000002.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_1_2_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_1_2_1-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_3_1_2_1-solution000003.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_1_2_1-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_1_2_1.eprime b/tests/exhaustive/basic/typed01/expected/model_3_1_2_1.eprime deleted file mode 100644 index 3232164034..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_1_2_1.eprime +++ /dev/null @@ -1,16 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..1) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -find y_Occurrence: matrix indexed by [int(1)] of bool -branching on - [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, y_Occurrence] -such that - 1 <= x_ExplicitVarSizeWithMarker_Marker /\ y_Occurrence[x_ExplicitVarSizeWithMarker_Values[1]] -> false, - 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, - x_ExplicitVarSizeWithDummy[1] != 2 -> - 1 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithDummy[1], - 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithMarker_Values[1] - diff --git a/tests/exhaustive/basic/typed01/expected/model_3_1_2_2-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_3_1_2_2-solution000001.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_1_2_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_1_2_2-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_3_1_2_2-solution000002.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_1_2_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_1_2_2-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_3_1_2_2-solution000003.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_1_2_2-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_1_2_2.eprime b/tests/exhaustive/basic/typed01/expected/model_3_1_2_2.eprime deleted file mode 100644 index 8198674706..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_1_2_2.eprime +++ /dev/null @@ -1,20 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..1) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -find y_Occurrence: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -branching on - [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, - y_ExplicitVarSizeWithDummy, y_Occurrence] -such that - 1 <= x_ExplicitVarSizeWithMarker_Marker /\ y_Occurrence[x_ExplicitVarSizeWithMarker_Values[1]] -> false, - 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, - x_ExplicitVarSizeWithDummy[1] != 2 -> - 1 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithDummy[1], - 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithMarker_Values[1], - y_ExplicitVarSizeWithDummy[1] != 2 -> y_Occurrence[y_ExplicitVarSizeWithDummy[1]], - y_Occurrence[1] -> y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = 1 - diff --git a/tests/exhaustive/basic/typed01/expected/model_3_1_2_3-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_3_1_2_3-solution000001.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_1_2_3-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_1_2_3-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_3_1_2_3-solution000002.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_1_2_3-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_1_2_3-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_3_1_2_3-solution000003.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_1_2_3-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_1_2_3.eprime b/tests/exhaustive/basic/typed01/expected/model_3_1_2_3.eprime deleted file mode 100644 index d85db5cc93..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_1_2_3.eprime +++ /dev/null @@ -1,22 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..1) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -find y_Occurrence: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithMarker_Marker: int(0..1) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -branching on - [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, - y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values, y_Occurrence] -such that - 1 <= x_ExplicitVarSizeWithMarker_Marker /\ y_Occurrence[x_ExplicitVarSizeWithMarker_Values[1]] -> false, - 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, - x_ExplicitVarSizeWithDummy[1] != 2 -> - 1 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithDummy[1], - 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithMarker_Values[1], - 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, - 1 <= y_ExplicitVarSizeWithMarker_Marker -> y_Occurrence[y_ExplicitVarSizeWithMarker_Values[1]], - y_Occurrence[1] -> 1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = 1 - diff --git a/tests/exhaustive/basic/typed01/expected/model_3_1_2_4-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_3_1_2_4-solution000001.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_1_2_4-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_1_2_4-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_3_1_2_4-solution000002.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_1_2_4-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_1_2_4-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_3_1_2_4-solution000003.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_1_2_4-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_1_2_4.eprime b/tests/exhaustive/basic/typed01/expected/model_3_1_2_4.eprime deleted file mode 100644 index 6965500389..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_1_2_4.eprime +++ /dev/null @@ -1,22 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..1) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -find y_Occurrence: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -branching on - [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, - y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values, y_Occurrence] -such that - 1 <= x_ExplicitVarSizeWithMarker_Marker /\ y_Occurrence[x_ExplicitVarSizeWithMarker_Values[1]] -> false, - 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, - x_ExplicitVarSizeWithDummy[1] != 2 -> - 1 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithDummy[1], - 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithMarker_Values[1], - y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, - y_ExplicitVarSizeWithFlags_Flags[1] -> y_Occurrence[y_ExplicitVarSizeWithFlags_Values[1]], - y_Occurrence[1] -> y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = 1 - diff --git a/tests/exhaustive/basic/typed01/expected/model_3_1_3_1-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_3_1_3_1-solution000001.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_1_3_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_1_3_1-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_3_1_3_1-solution000002.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_1_3_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_1_3_1-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_3_1_3_1-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_1_3_1-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_1_3_1.eprime b/tests/exhaustive/basic/typed01/expected/model_3_1_3_1.eprime deleted file mode 100644 index f5c2cccdbc..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_1_3_1.eprime +++ /dev/null @@ -1,10 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..1) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -find y_Occurrence: matrix indexed by [int(1)] of bool -branching on [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, y_Occurrence] -such that - 1 <= x_ExplicitVarSizeWithMarker_Marker /\ y_Occurrence[x_ExplicitVarSizeWithMarker_Values[1]] -> false, - 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1 - diff --git a/tests/exhaustive/basic/typed01/expected/model_3_1_3_2-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_3_1_3_2-solution000001.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_1_3_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_1_3_2-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_3_1_3_2-solution000002.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_1_3_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_1_3_2-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_3_1_3_2-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_1_3_2-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_1_3_2.eprime b/tests/exhaustive/basic/typed01/expected/model_3_1_3_2.eprime deleted file mode 100644 index e1c3367190..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_1_3_2.eprime +++ /dev/null @@ -1,14 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..1) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -find y_Occurrence: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithDummy, y_Occurrence] -such that - 1 <= x_ExplicitVarSizeWithMarker_Marker /\ y_Occurrence[x_ExplicitVarSizeWithMarker_Values[1]] -> false, - 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, - y_ExplicitVarSizeWithDummy[1] != 2 -> y_Occurrence[y_ExplicitVarSizeWithDummy[1]], - y_Occurrence[1] -> y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = 1 - diff --git a/tests/exhaustive/basic/typed01/expected/model_3_1_3_3-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_3_1_3_3-solution000001.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_1_3_3-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_1_3_3-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_3_1_3_3-solution000002.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_1_3_3-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_1_3_3-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_3_1_3_3-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_1_3_3-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_1_3_3.eprime b/tests/exhaustive/basic/typed01/expected/model_3_1_3_3.eprime deleted file mode 100644 index 9f6c670ab3..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_1_3_3.eprime +++ /dev/null @@ -1,17 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..1) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -find y_Occurrence: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithMarker_Marker: int(0..1) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithMarker_Marker, - y_ExplicitVarSizeWithMarker_Values, y_Occurrence] -such that - 1 <= x_ExplicitVarSizeWithMarker_Marker /\ y_Occurrence[x_ExplicitVarSizeWithMarker_Values[1]] -> false, - 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, - 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, - 1 <= y_ExplicitVarSizeWithMarker_Marker -> y_Occurrence[y_ExplicitVarSizeWithMarker_Values[1]], - y_Occurrence[1] -> 1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = 1 - diff --git a/tests/exhaustive/basic/typed01/expected/model_3_1_3_4-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_3_1_3_4-solution000001.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_1_3_4-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_1_3_4-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_3_1_3_4-solution000002.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_1_3_4-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_1_3_4-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_3_1_3_4-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_1_3_4-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_1_3_4.eprime b/tests/exhaustive/basic/typed01/expected/model_3_1_3_4.eprime deleted file mode 100644 index e9cad424f2..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_1_3_4.eprime +++ /dev/null @@ -1,17 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..1) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -find y_Occurrence: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithFlags_Flags, - y_ExplicitVarSizeWithFlags_Values, y_Occurrence] -such that - 1 <= x_ExplicitVarSizeWithMarker_Marker /\ y_Occurrence[x_ExplicitVarSizeWithMarker_Values[1]] -> false, - 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, - y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, - y_ExplicitVarSizeWithFlags_Flags[1] -> y_Occurrence[y_ExplicitVarSizeWithFlags_Values[1]], - y_Occurrence[1] -> y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = 1 - diff --git a/tests/exhaustive/basic/typed01/expected/model_3_1_4_1-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_3_1_4_1-solution000001.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_1_4_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_1_4_1-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_3_1_4_1-solution000002.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_1_4_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_1_4_1-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_3_1_4_1-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_1_4_1-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_1_4_1.eprime b/tests/exhaustive/basic/typed01/expected/model_3_1_4_1.eprime deleted file mode 100644 index c9d42653f0..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_1_4_1.eprime +++ /dev/null @@ -1,20 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..1) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -find y_Occurrence: matrix indexed by [int(1)] of bool -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithMarker_Marker, - x_ExplicitVarSizeWithMarker_Values, y_Occurrence] -such that - 1 <= x_ExplicitVarSizeWithMarker_Marker /\ y_Occurrence[x_ExplicitVarSizeWithMarker_Values[1]] -> false, - 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, - x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, - x_ExplicitVarSizeWithFlags_Flags[1] -> - 1 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithFlags_Values[1], - 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithMarker_Values[1] - diff --git a/tests/exhaustive/basic/typed01/expected/model_3_1_4_2-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_3_1_4_2-solution000001.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_1_4_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_1_4_2-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_3_1_4_2-solution000002.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_1_4_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_1_4_2-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_3_1_4_2-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_1_4_2-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_1_4_2.eprime b/tests/exhaustive/basic/typed01/expected/model_3_1_4_2.eprime deleted file mode 100644 index 542fea04f9..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_1_4_2.eprime +++ /dev/null @@ -1,23 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..1) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -find y_Occurrence: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithMarker_Marker, - x_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithDummy, y_Occurrence] -such that - 1 <= x_ExplicitVarSizeWithMarker_Marker /\ y_Occurrence[x_ExplicitVarSizeWithMarker_Values[1]] -> false, - 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, - x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, - x_ExplicitVarSizeWithFlags_Flags[1] -> - 1 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithFlags_Values[1], - 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithMarker_Values[1], - y_ExplicitVarSizeWithDummy[1] != 2 -> y_Occurrence[y_ExplicitVarSizeWithDummy[1]], - y_Occurrence[1] -> y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = 1 - diff --git a/tests/exhaustive/basic/typed01/expected/model_3_1_4_3-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_3_1_4_3-solution000001.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_1_4_3-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_1_4_3-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_3_1_4_3-solution000002.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_1_4_3-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_1_4_3-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_3_1_4_3-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_1_4_3-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_1_4_3.eprime b/tests/exhaustive/basic/typed01/expected/model_3_1_4_3.eprime deleted file mode 100644 index 15763695d1..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_1_4_3.eprime +++ /dev/null @@ -1,26 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..1) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -find y_Occurrence: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithMarker_Marker: int(0..1) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithMarker_Marker, - x_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values, - y_Occurrence] -such that - 1 <= x_ExplicitVarSizeWithMarker_Marker /\ y_Occurrence[x_ExplicitVarSizeWithMarker_Values[1]] -> false, - 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, - x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, - x_ExplicitVarSizeWithFlags_Flags[1] -> - 1 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithFlags_Values[1], - 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithMarker_Values[1], - 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, - 1 <= y_ExplicitVarSizeWithMarker_Marker -> y_Occurrence[y_ExplicitVarSizeWithMarker_Values[1]], - y_Occurrence[1] -> 1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = 1 - diff --git a/tests/exhaustive/basic/typed01/expected/model_3_1_4_4-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_3_1_4_4-solution000001.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_1_4_4-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_1_4_4-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_3_1_4_4-solution000002.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_1_4_4-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_1_4_4-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_3_1_4_4-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_1_4_4-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_1_4_4.eprime b/tests/exhaustive/basic/typed01/expected/model_3_1_4_4.eprime deleted file mode 100644 index 4074e09614..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_1_4_4.eprime +++ /dev/null @@ -1,26 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..1) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -find y_Occurrence: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithMarker_Marker, - x_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values, - y_Occurrence] -such that - 1 <= x_ExplicitVarSizeWithMarker_Marker /\ y_Occurrence[x_ExplicitVarSizeWithMarker_Values[1]] -> false, - 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, - x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, - x_ExplicitVarSizeWithFlags_Flags[1] -> - 1 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithFlags_Values[1], - 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithMarker_Values[1], - y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, - y_ExplicitVarSizeWithFlags_Flags[1] -> y_Occurrence[y_ExplicitVarSizeWithFlags_Values[1]], - y_Occurrence[1] -> y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = 1 - diff --git a/tests/exhaustive/basic/typed01/expected/model_3_2_1_1-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_3_2_1_1-solution000001.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_2_1_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_2_1_1-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_3_2_1_1-solution000002.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_2_1_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_2_1_1-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_3_2_1_1-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_2_1_1-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_2_1_1.eprime b/tests/exhaustive/basic/typed01/expected/model_3_2_1_1.eprime deleted file mode 100644 index 5b779b4b38..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_2_1_1.eprime +++ /dev/null @@ -1,20 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..1) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -find x_Occurrence: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -find y_Occurrence: matrix indexed by [int(1)] of bool -branching on - [x_Occurrence, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, y_Occurrence, - y_ExplicitVarSizeWithDummy] -such that - 1 <= x_ExplicitVarSizeWithMarker_Marker /\ - (y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithMarker_Values[1]) - -> false, - 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, - x_Occurrence[1] -> 1 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[1] = 1, - 1 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[1]], - y_Occurrence[1] -> y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = 1, - y_ExplicitVarSizeWithDummy[1] != 2 -> y_Occurrence[y_ExplicitVarSizeWithDummy[1]] - diff --git a/tests/exhaustive/basic/typed01/expected/model_3_2_1_2-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_3_2_1_2-solution000001.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_2_1_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_2_1_2-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_3_2_1_2-solution000002.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_2_1_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_2_1_2-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_3_2_1_2-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_2_1_2-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_2_1_2.eprime b/tests/exhaustive/basic/typed01/expected/model_3_2_1_2.eprime deleted file mode 100644 index 3dc3f438fd..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_2_1_2.eprime +++ /dev/null @@ -1,16 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..1) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -find x_Occurrence: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -branching on - [x_Occurrence, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithDummy] -such that - 1 <= x_ExplicitVarSizeWithMarker_Marker /\ - (y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithMarker_Values[1]) - -> false, - 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, - x_Occurrence[1] -> 1 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[1] = 1, - 1 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[1]] - diff --git a/tests/exhaustive/basic/typed01/expected/model_3_2_1_3-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_3_2_1_3-solution000001.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_2_1_3-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_2_1_3-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_3_2_1_3-solution000002.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_2_1_3-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_2_1_3-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_3_2_1_3-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_2_1_3-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_2_1_3.eprime b/tests/exhaustive/basic/typed01/expected/model_3_2_1_3.eprime deleted file mode 100644 index 10e6959273..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_2_1_3.eprime +++ /dev/null @@ -1,24 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..1) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -find x_Occurrence: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -find y_ExplicitVarSizeWithMarker_Marker: int(0..1) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -branching on - [x_Occurrence, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, - y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithDummy] -such that - 1 <= x_ExplicitVarSizeWithMarker_Marker /\ - (y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithMarker_Values[1]) - -> false, - 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, - x_Occurrence[1] -> 1 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[1] = 1, - 1 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[1]], - 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, - 1 <= y_ExplicitVarSizeWithMarker_Marker -> - y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = y_ExplicitVarSizeWithMarker_Values[1], - y_ExplicitVarSizeWithDummy[1] != 2 -> - 1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = y_ExplicitVarSizeWithDummy[1] - diff --git a/tests/exhaustive/basic/typed01/expected/model_3_2_1_4-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_3_2_1_4-solution000001.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_2_1_4-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_2_1_4-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_3_2_1_4-solution000002.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_2_1_4-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_2_1_4-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_3_2_1_4-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_2_1_4-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_2_1_4.eprime b/tests/exhaustive/basic/typed01/expected/model_3_2_1_4.eprime deleted file mode 100644 index eba2cf80d9..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_2_1_4.eprime +++ /dev/null @@ -1,24 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..1) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -find x_Occurrence: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -branching on - [x_Occurrence, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, - y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithDummy] -such that - 1 <= x_ExplicitVarSizeWithMarker_Marker /\ - (y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithMarker_Values[1]) - -> false, - 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, - x_Occurrence[1] -> 1 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[1] = 1, - 1 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[1]], - y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, - y_ExplicitVarSizeWithFlags_Flags[1] -> - y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = y_ExplicitVarSizeWithFlags_Values[1], - y_ExplicitVarSizeWithDummy[1] != 2 -> - y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = y_ExplicitVarSizeWithDummy[1] - diff --git a/tests/exhaustive/basic/typed01/expected/model_3_2_2_1-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_3_2_2_1-solution000001.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_2_2_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_2_2_1-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_3_2_2_1-solution000002.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_2_2_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_2_2_1-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_3_2_2_1-solution000003.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_2_2_1-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_2_2_1.eprime b/tests/exhaustive/basic/typed01/expected/model_3_2_2_1.eprime deleted file mode 100644 index 31c98c5012..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_2_2_1.eprime +++ /dev/null @@ -1,22 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..1) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -find y_Occurrence: matrix indexed by [int(1)] of bool -branching on - [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, y_Occurrence, - y_ExplicitVarSizeWithDummy] -such that - 1 <= x_ExplicitVarSizeWithMarker_Marker /\ - (y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithMarker_Values[1]) - -> false, - 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, - x_ExplicitVarSizeWithDummy[1] != 2 -> - 1 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithDummy[1], - 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithMarker_Values[1], - y_Occurrence[1] -> y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = 1, - y_ExplicitVarSizeWithDummy[1] != 2 -> y_Occurrence[y_ExplicitVarSizeWithDummy[1]] - diff --git a/tests/exhaustive/basic/typed01/expected/model_3_2_2_2-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_3_2_2_2-solution000001.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_2_2_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_2_2_2-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_3_2_2_2-solution000002.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_2_2_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_2_2_2-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_3_2_2_2-solution000003.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_2_2_2-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_2_2_2.eprime b/tests/exhaustive/basic/typed01/expected/model_3_2_2_2.eprime deleted file mode 100644 index 6e50969662..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_2_2_2.eprime +++ /dev/null @@ -1,19 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..1) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -branching on - [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, - y_ExplicitVarSizeWithDummy] -such that - 1 <= x_ExplicitVarSizeWithMarker_Marker /\ - (y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithMarker_Values[1]) - -> false, - 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, - x_ExplicitVarSizeWithDummy[1] != 2 -> - 1 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithDummy[1], - 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithMarker_Values[1] - diff --git a/tests/exhaustive/basic/typed01/expected/model_3_2_2_3-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_3_2_2_3-solution000001.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_2_2_3-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_2_2_3-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_3_2_2_3-solution000002.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_2_2_3-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_2_2_3-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_3_2_2_3-solution000003.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_2_2_3-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_2_2_3.eprime b/tests/exhaustive/basic/typed01/expected/model_3_2_2_3.eprime deleted file mode 100644 index 23bf917fe5..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_2_2_3.eprime +++ /dev/null @@ -1,26 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..1) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -find y_ExplicitVarSizeWithMarker_Marker: int(0..1) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -branching on - [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, - y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithDummy] -such that - 1 <= x_ExplicitVarSizeWithMarker_Marker /\ - (y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithMarker_Values[1]) - -> false, - 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, - x_ExplicitVarSizeWithDummy[1] != 2 -> - 1 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithDummy[1], - 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithMarker_Values[1], - 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, - 1 <= y_ExplicitVarSizeWithMarker_Marker -> - y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = y_ExplicitVarSizeWithMarker_Values[1], - y_ExplicitVarSizeWithDummy[1] != 2 -> - 1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = y_ExplicitVarSizeWithDummy[1] - diff --git a/tests/exhaustive/basic/typed01/expected/model_3_2_2_4-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_3_2_2_4-solution000001.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_2_2_4-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_2_2_4-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_3_2_2_4-solution000002.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_2_2_4-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_2_2_4-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_3_2_2_4-solution000003.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_2_2_4-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_2_2_4.eprime b/tests/exhaustive/basic/typed01/expected/model_3_2_2_4.eprime deleted file mode 100644 index c20b43202e..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_2_2_4.eprime +++ /dev/null @@ -1,26 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..1) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -branching on - [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, - y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithDummy] -such that - 1 <= x_ExplicitVarSizeWithMarker_Marker /\ - (y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithMarker_Values[1]) - -> false, - 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, - x_ExplicitVarSizeWithDummy[1] != 2 -> - 1 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithDummy[1], - 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithMarker_Values[1], - y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, - y_ExplicitVarSizeWithFlags_Flags[1] -> - y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = y_ExplicitVarSizeWithFlags_Values[1], - y_ExplicitVarSizeWithDummy[1] != 2 -> - y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = y_ExplicitVarSizeWithDummy[1] - diff --git a/tests/exhaustive/basic/typed01/expected/model_3_2_3_1-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_3_2_3_1-solution000001.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_2_3_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_2_3_1-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_3_2_3_1-solution000002.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_2_3_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_2_3_1-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_3_2_3_1-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_2_3_1-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_2_3_1.eprime b/tests/exhaustive/basic/typed01/expected/model_3_2_3_1.eprime deleted file mode 100644 index 616ec55e21..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_2_3_1.eprime +++ /dev/null @@ -1,16 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..1) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -find y_Occurrence: matrix indexed by [int(1)] of bool -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, y_Occurrence, y_ExplicitVarSizeWithDummy] -such that - 1 <= x_ExplicitVarSizeWithMarker_Marker /\ - (y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithMarker_Values[1]) - -> false, - 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, - y_Occurrence[1] -> y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = 1, - y_ExplicitVarSizeWithDummy[1] != 2 -> y_Occurrence[y_ExplicitVarSizeWithDummy[1]] - diff --git a/tests/exhaustive/basic/typed01/expected/model_3_2_3_2-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_3_2_3_2-solution000001.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_2_3_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_2_3_2-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_3_2_3_2-solution000002.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_2_3_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_2_3_2-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_3_2_3_2-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_2_3_2-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_2_3_2.eprime b/tests/exhaustive/basic/typed01/expected/model_3_2_3_2.eprime deleted file mode 100644 index e176e88df7..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_2_3_2.eprime +++ /dev/null @@ -1,12 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..1) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -branching on [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithDummy] -such that - 1 <= x_ExplicitVarSizeWithMarker_Marker /\ - (y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithMarker_Values[1]) - -> false, - 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1 - diff --git a/tests/exhaustive/basic/typed01/expected/model_3_2_3_3-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_3_2_3_3-solution000001.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_2_3_3-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_2_3_3-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_3_2_3_3-solution000002.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_2_3_3-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_2_3_3-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_3_2_3_3-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_2_3_3-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_2_3_3.eprime b/tests/exhaustive/basic/typed01/expected/model_3_2_3_3.eprime deleted file mode 100644 index 30b4ef921e..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_2_3_3.eprime +++ /dev/null @@ -1,21 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..1) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -find y_ExplicitVarSizeWithMarker_Marker: int(0..1) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithMarker_Marker, - y_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithDummy] -such that - 1 <= x_ExplicitVarSizeWithMarker_Marker /\ - (y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithMarker_Values[1]) - -> false, - 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, - 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, - 1 <= y_ExplicitVarSizeWithMarker_Marker -> - y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = y_ExplicitVarSizeWithMarker_Values[1], - y_ExplicitVarSizeWithDummy[1] != 2 -> - 1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = y_ExplicitVarSizeWithDummy[1] - diff --git a/tests/exhaustive/basic/typed01/expected/model_3_2_3_4-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_3_2_3_4-solution000001.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_2_3_4-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_2_3_4-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_3_2_3_4-solution000002.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_2_3_4-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_2_3_4-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_3_2_3_4-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_2_3_4-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_2_3_4.eprime b/tests/exhaustive/basic/typed01/expected/model_3_2_3_4.eprime deleted file mode 100644 index f373170319..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_2_3_4.eprime +++ /dev/null @@ -1,21 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..1) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithFlags_Flags, - y_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithDummy] -such that - 1 <= x_ExplicitVarSizeWithMarker_Marker /\ - (y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithMarker_Values[1]) - -> false, - 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, - y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, - y_ExplicitVarSizeWithFlags_Flags[1] -> - y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = y_ExplicitVarSizeWithFlags_Values[1], - y_ExplicitVarSizeWithDummy[1] != 2 -> - y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = y_ExplicitVarSizeWithDummy[1] - diff --git a/tests/exhaustive/basic/typed01/expected/model_3_2_4_1-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_3_2_4_1-solution000001.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_2_4_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_2_4_1-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_3_2_4_1-solution000002.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_2_4_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_2_4_1-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_3_2_4_1-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_2_4_1-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_2_4_1.eprime b/tests/exhaustive/basic/typed01/expected/model_3_2_4_1.eprime deleted file mode 100644 index 1c3f33bddc..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_2_4_1.eprime +++ /dev/null @@ -1,25 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..1) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -find y_Occurrence: matrix indexed by [int(1)] of bool -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithMarker_Marker, - x_ExplicitVarSizeWithMarker_Values, y_Occurrence, y_ExplicitVarSizeWithDummy] -such that - 1 <= x_ExplicitVarSizeWithMarker_Marker /\ - (y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithMarker_Values[1]) - -> false, - 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, - x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, - x_ExplicitVarSizeWithFlags_Flags[1] -> - 1 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithFlags_Values[1], - 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithMarker_Values[1], - y_Occurrence[1] -> y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = 1, - y_ExplicitVarSizeWithDummy[1] != 2 -> y_Occurrence[y_ExplicitVarSizeWithDummy[1]] - diff --git a/tests/exhaustive/basic/typed01/expected/model_3_2_4_2-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_3_2_4_2-solution000001.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_2_4_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_2_4_2-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_3_2_4_2-solution000002.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_2_4_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_2_4_2-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_3_2_4_2-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_2_4_2-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_2_4_2.eprime b/tests/exhaustive/basic/typed01/expected/model_3_2_4_2.eprime deleted file mode 100644 index bfb78df1a5..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_2_4_2.eprime +++ /dev/null @@ -1,22 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..1) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithMarker_Marker, - x_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithDummy] -such that - 1 <= x_ExplicitVarSizeWithMarker_Marker /\ - (y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithMarker_Values[1]) - -> false, - 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, - x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, - x_ExplicitVarSizeWithFlags_Flags[1] -> - 1 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithFlags_Values[1], - 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithMarker_Values[1] - diff --git a/tests/exhaustive/basic/typed01/expected/model_3_2_4_3-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_3_2_4_3-solution000001.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_2_4_3-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_2_4_3-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_3_2_4_3-solution000002.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_2_4_3-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_2_4_3-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_3_2_4_3-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_2_4_3-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_2_4_3.eprime b/tests/exhaustive/basic/typed01/expected/model_3_2_4_3.eprime deleted file mode 100644 index 2516063bdd..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_2_4_3.eprime +++ /dev/null @@ -1,30 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..1) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -find y_ExplicitVarSizeWithMarker_Marker: int(0..1) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithMarker_Marker, - x_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values, - y_ExplicitVarSizeWithDummy] -such that - 1 <= x_ExplicitVarSizeWithMarker_Marker /\ - (y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithMarker_Values[1]) - -> false, - 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, - x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, - x_ExplicitVarSizeWithFlags_Flags[1] -> - 1 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithFlags_Values[1], - 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithMarker_Values[1], - 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, - 1 <= y_ExplicitVarSizeWithMarker_Marker -> - y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = y_ExplicitVarSizeWithMarker_Values[1], - y_ExplicitVarSizeWithDummy[1] != 2 -> - 1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = y_ExplicitVarSizeWithDummy[1] - diff --git a/tests/exhaustive/basic/typed01/expected/model_3_2_4_4-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_3_2_4_4-solution000001.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_2_4_4-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_2_4_4-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_3_2_4_4-solution000002.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_2_4_4-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_2_4_4-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_3_2_4_4-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_2_4_4-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_2_4_4.eprime b/tests/exhaustive/basic/typed01/expected/model_3_2_4_4.eprime deleted file mode 100644 index 3404c37403..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_2_4_4.eprime +++ /dev/null @@ -1,30 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..1) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithMarker_Marker, - x_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values, - y_ExplicitVarSizeWithDummy] -such that - 1 <= x_ExplicitVarSizeWithMarker_Marker /\ - (y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithMarker_Values[1]) - -> false, - 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, - x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, - x_ExplicitVarSizeWithFlags_Flags[1] -> - 1 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithFlags_Values[1], - 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithMarker_Values[1], - y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, - y_ExplicitVarSizeWithFlags_Flags[1] -> - y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = y_ExplicitVarSizeWithFlags_Values[1], - y_ExplicitVarSizeWithDummy[1] != 2 -> - y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = y_ExplicitVarSizeWithDummy[1] - diff --git a/tests/exhaustive/basic/typed01/expected/model_3_3_1_1-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_3_3_1_1-solution000001.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_3_1_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_3_1_1-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_3_3_1_1-solution000002.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_3_1_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_3_1_1-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_3_3_1_1-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_3_1_1-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_3_1_1.eprime b/tests/exhaustive/basic/typed01/expected/model_3_3_1_1.eprime deleted file mode 100644 index 6d3b73f10c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_3_1_1.eprime +++ /dev/null @@ -1,23 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..1) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -find x_Occurrence: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithMarker_Marker: int(0..1) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -find y_Occurrence: matrix indexed by [int(1)] of bool -branching on - [x_Occurrence, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, y_Occurrence, - y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values] -such that - 1 <= x_ExplicitVarSizeWithMarker_Marker /\ - (1 <= y_ExplicitVarSizeWithMarker_Marker /\ - y_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithMarker_Values[1]) - -> false, - 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, - 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, - x_Occurrence[1] -> 1 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[1] = 1, - 1 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[1]], - y_Occurrence[1] -> 1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = 1, - 1 <= y_ExplicitVarSizeWithMarker_Marker -> y_Occurrence[y_ExplicitVarSizeWithMarker_Values[1]] - diff --git a/tests/exhaustive/basic/typed01/expected/model_3_3_1_2-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_3_3_1_2-solution000001.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_3_1_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_3_1_2-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_3_3_1_2-solution000002.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_3_1_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_3_1_2-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_3_3_1_2-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_3_1_2-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_3_1_2.eprime b/tests/exhaustive/basic/typed01/expected/model_3_3_1_2.eprime deleted file mode 100644 index 44439955a6..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_3_1_2.eprime +++ /dev/null @@ -1,25 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..1) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -find x_Occurrence: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithMarker_Marker: int(0..1) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -branching on - [x_Occurrence, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithDummy, - y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values] -such that - 1 <= x_ExplicitVarSizeWithMarker_Marker /\ - (1 <= y_ExplicitVarSizeWithMarker_Marker /\ - y_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithMarker_Values[1]) - -> false, - 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, - 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, - x_Occurrence[1] -> 1 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[1] = 1, - 1 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[1]], - y_ExplicitVarSizeWithDummy[1] != 2 -> - 1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = y_ExplicitVarSizeWithDummy[1], - 1 <= y_ExplicitVarSizeWithMarker_Marker -> - y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = y_ExplicitVarSizeWithMarker_Values[1] - diff --git a/tests/exhaustive/basic/typed01/expected/model_3_3_1_3-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_3_3_1_3-solution000001.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_3_1_3-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_3_1_3-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_3_3_1_3-solution000002.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_3_1_3-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_3_1_3-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_3_3_1_3-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_3_1_3-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_3_1_3.eprime b/tests/exhaustive/basic/typed01/expected/model_3_3_1_3.eprime deleted file mode 100644 index 2d0516dbc1..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_3_1_3.eprime +++ /dev/null @@ -1,20 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..1) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -find x_Occurrence: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithMarker_Marker: int(0..1) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -branching on - [x_Occurrence, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, - y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values] -such that - 1 <= x_ExplicitVarSizeWithMarker_Marker /\ - (1 <= y_ExplicitVarSizeWithMarker_Marker /\ - y_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithMarker_Values[1]) - -> false, - 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, - 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, - x_Occurrence[1] -> 1 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[1] = 1, - 1 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[1]] - diff --git a/tests/exhaustive/basic/typed01/expected/model_3_3_1_4-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_3_3_1_4-solution000001.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_3_1_4-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_3_1_4-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_3_3_1_4-solution000002.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_3_1_4-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_3_1_4-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_3_3_1_4-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_3_1_4-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_3_1_4.eprime b/tests/exhaustive/basic/typed01/expected/model_3_3_1_4.eprime deleted file mode 100644 index 13374c77fe..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_3_1_4.eprime +++ /dev/null @@ -1,29 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..1) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -find x_Occurrence: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithMarker_Marker: int(0..1) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -branching on - [x_Occurrence, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, - y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithMarker_Marker, - y_ExplicitVarSizeWithMarker_Values] -such that - 1 <= x_ExplicitVarSizeWithMarker_Marker /\ - (1 <= y_ExplicitVarSizeWithMarker_Marker /\ - y_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithMarker_Values[1]) - -> false, - 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, - 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, - x_Occurrence[1] -> 1 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[1] = 1, - 1 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[1]], - y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, - y_ExplicitVarSizeWithFlags_Flags[1] -> - 1 <= y_ExplicitVarSizeWithMarker_Marker /\ - y_ExplicitVarSizeWithMarker_Values[1] = y_ExplicitVarSizeWithFlags_Values[1], - 1 <= y_ExplicitVarSizeWithMarker_Marker -> - y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = y_ExplicitVarSizeWithMarker_Values[1] - diff --git a/tests/exhaustive/basic/typed01/expected/model_3_3_2_1-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_3_3_2_1-solution000001.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_3_2_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_3_2_1-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_3_3_2_1-solution000002.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_3_2_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_3_2_1-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_3_3_2_1-solution000003.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_3_2_1-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_3_2_1.eprime b/tests/exhaustive/basic/typed01/expected/model_3_3_2_1.eprime deleted file mode 100644 index dc91372e8c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_3_2_1.eprime +++ /dev/null @@ -1,25 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..1) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -find y_ExplicitVarSizeWithMarker_Marker: int(0..1) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -find y_Occurrence: matrix indexed by [int(1)] of bool -branching on - [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, y_Occurrence, - y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values] -such that - 1 <= x_ExplicitVarSizeWithMarker_Marker /\ - (1 <= y_ExplicitVarSizeWithMarker_Marker /\ - y_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithMarker_Values[1]) - -> false, - 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, - 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, - x_ExplicitVarSizeWithDummy[1] != 2 -> - 1 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithDummy[1], - 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithMarker_Values[1], - y_Occurrence[1] -> 1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = 1, - 1 <= y_ExplicitVarSizeWithMarker_Marker -> y_Occurrence[y_ExplicitVarSizeWithMarker_Values[1]] - diff --git a/tests/exhaustive/basic/typed01/expected/model_3_3_2_2-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_3_3_2_2-solution000001.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_3_2_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_3_2_2-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_3_3_2_2-solution000002.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_3_2_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_3_2_2-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_3_3_2_2-solution000003.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_3_2_2-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_3_2_2.eprime b/tests/exhaustive/basic/typed01/expected/model_3_3_2_2.eprime deleted file mode 100644 index f5fc445a12..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_3_2_2.eprime +++ /dev/null @@ -1,27 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..1) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -find y_ExplicitVarSizeWithMarker_Marker: int(0..1) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -branching on - [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, - y_ExplicitVarSizeWithDummy, y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values] -such that - 1 <= x_ExplicitVarSizeWithMarker_Marker /\ - (1 <= y_ExplicitVarSizeWithMarker_Marker /\ - y_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithMarker_Values[1]) - -> false, - 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, - 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, - x_ExplicitVarSizeWithDummy[1] != 2 -> - 1 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithDummy[1], - 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithMarker_Values[1], - y_ExplicitVarSizeWithDummy[1] != 2 -> - 1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = y_ExplicitVarSizeWithDummy[1], - 1 <= y_ExplicitVarSizeWithMarker_Marker -> - y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = y_ExplicitVarSizeWithMarker_Values[1] - diff --git a/tests/exhaustive/basic/typed01/expected/model_3_3_2_3-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_3_3_2_3-solution000001.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_3_2_3-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_3_2_3-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_3_3_2_3-solution000002.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_3_2_3-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_3_2_3-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_3_3_2_3-solution000003.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_3_2_3-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_3_2_3.eprime b/tests/exhaustive/basic/typed01/expected/model_3_3_2_3.eprime deleted file mode 100644 index 68281a2f9a..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_3_2_3.eprime +++ /dev/null @@ -1,22 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..1) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -find y_ExplicitVarSizeWithMarker_Marker: int(0..1) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -branching on - [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, - y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values] -such that - 1 <= x_ExplicitVarSizeWithMarker_Marker /\ - (1 <= y_ExplicitVarSizeWithMarker_Marker /\ - y_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithMarker_Values[1]) - -> false, - 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, - 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, - x_ExplicitVarSizeWithDummy[1] != 2 -> - 1 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithDummy[1], - 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithMarker_Values[1] - diff --git a/tests/exhaustive/basic/typed01/expected/model_3_3_2_4-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_3_3_2_4-solution000001.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_3_2_4-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_3_2_4-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_3_3_2_4-solution000002.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_3_2_4-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_3_2_4-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_3_3_2_4-solution000003.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_3_2_4-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_3_2_4.eprime b/tests/exhaustive/basic/typed01/expected/model_3_3_2_4.eprime deleted file mode 100644 index 7d7326d650..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_3_2_4.eprime +++ /dev/null @@ -1,31 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..1) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -find y_ExplicitVarSizeWithMarker_Marker: int(0..1) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -branching on - [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, - y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithMarker_Marker, - y_ExplicitVarSizeWithMarker_Values] -such that - 1 <= x_ExplicitVarSizeWithMarker_Marker /\ - (1 <= y_ExplicitVarSizeWithMarker_Marker /\ - y_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithMarker_Values[1]) - -> false, - 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, - 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, - x_ExplicitVarSizeWithDummy[1] != 2 -> - 1 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithDummy[1], - 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithMarker_Values[1], - y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, - y_ExplicitVarSizeWithFlags_Flags[1] -> - 1 <= y_ExplicitVarSizeWithMarker_Marker /\ - y_ExplicitVarSizeWithMarker_Values[1] = y_ExplicitVarSizeWithFlags_Values[1], - 1 <= y_ExplicitVarSizeWithMarker_Marker -> - y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = y_ExplicitVarSizeWithMarker_Values[1] - diff --git a/tests/exhaustive/basic/typed01/expected/model_3_3_3_1-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_3_3_3_1-solution000001.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_3_3_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_3_3_1-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_3_3_3_1-solution000002.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_3_3_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_3_3_1-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_3_3_3_1-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_3_3_1-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_3_3_1.eprime b/tests/exhaustive/basic/typed01/expected/model_3_3_3_1.eprime deleted file mode 100644 index 8c1a3dd051..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_3_3_1.eprime +++ /dev/null @@ -1,20 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..1) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -find y_ExplicitVarSizeWithMarker_Marker: int(0..1) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -find y_Occurrence: matrix indexed by [int(1)] of bool -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, y_Occurrence, - y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values] -such that - 1 <= x_ExplicitVarSizeWithMarker_Marker /\ - (1 <= y_ExplicitVarSizeWithMarker_Marker /\ - y_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithMarker_Values[1]) - -> false, - 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, - 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, - y_Occurrence[1] -> 1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = 1, - 1 <= y_ExplicitVarSizeWithMarker_Marker -> y_Occurrence[y_ExplicitVarSizeWithMarker_Values[1]] - diff --git a/tests/exhaustive/basic/typed01/expected/model_3_3_3_2-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_3_3_3_2-solution000001.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_3_3_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_3_3_2-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_3_3_3_2-solution000002.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_3_3_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_3_3_2-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_3_3_3_2-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_3_3_2-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_3_3_2.eprime b/tests/exhaustive/basic/typed01/expected/model_3_3_3_2.eprime deleted file mode 100644 index ef312ab142..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_3_3_2.eprime +++ /dev/null @@ -1,22 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..1) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -find y_ExplicitVarSizeWithMarker_Marker: int(0..1) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithDummy, - y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values] -such that - 1 <= x_ExplicitVarSizeWithMarker_Marker /\ - (1 <= y_ExplicitVarSizeWithMarker_Marker /\ - y_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithMarker_Values[1]) - -> false, - 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, - 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, - y_ExplicitVarSizeWithDummy[1] != 2 -> - 1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = y_ExplicitVarSizeWithDummy[1], - 1 <= y_ExplicitVarSizeWithMarker_Marker -> - y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = y_ExplicitVarSizeWithMarker_Values[1] - diff --git a/tests/exhaustive/basic/typed01/expected/model_3_3_3_3-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_3_3_3_3-solution000001.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_3_3_3-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_3_3_3-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_3_3_3_3-solution000002.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_3_3_3-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_3_3_3-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_3_3_3_3-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_3_3_3-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_3_3_3.eprime b/tests/exhaustive/basic/typed01/expected/model_3_3_3_3.eprime deleted file mode 100644 index 51c528ccb0..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_3_3_3.eprime +++ /dev/null @@ -1,17 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..1) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -find y_ExplicitVarSizeWithMarker_Marker: int(0..1) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithMarker_Marker, - y_ExplicitVarSizeWithMarker_Values] -such that - 1 <= x_ExplicitVarSizeWithMarker_Marker /\ - (1 <= y_ExplicitVarSizeWithMarker_Marker /\ - y_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithMarker_Values[1]) - -> false, - 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, - 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1 - diff --git a/tests/exhaustive/basic/typed01/expected/model_3_3_3_4-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_3_3_3_4-solution000001.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_3_3_4-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_3_3_4-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_3_3_3_4-solution000002.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_3_3_4-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_3_3_4-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_3_3_3_4-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_3_3_4-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_3_3_4.eprime b/tests/exhaustive/basic/typed01/expected/model_3_3_3_4.eprime deleted file mode 100644 index 5bfbda5c04..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_3_3_4.eprime +++ /dev/null @@ -1,25 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..1) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -find y_ExplicitVarSizeWithMarker_Marker: int(0..1) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithFlags_Flags, - y_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values] -such that - 1 <= x_ExplicitVarSizeWithMarker_Marker /\ - (1 <= y_ExplicitVarSizeWithMarker_Marker /\ - y_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithMarker_Values[1]) - -> false, - 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, - 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, - y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, - y_ExplicitVarSizeWithFlags_Flags[1] -> - 1 <= y_ExplicitVarSizeWithMarker_Marker /\ - y_ExplicitVarSizeWithMarker_Values[1] = y_ExplicitVarSizeWithFlags_Values[1], - 1 <= y_ExplicitVarSizeWithMarker_Marker -> - y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = y_ExplicitVarSizeWithMarker_Values[1] - diff --git a/tests/exhaustive/basic/typed01/expected/model_3_3_4_1-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_3_3_4_1-solution000001.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_3_4_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_3_4_1-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_3_3_4_1-solution000002.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_3_4_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_3_4_1-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_3_3_4_1-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_3_4_1-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_3_4_1.eprime b/tests/exhaustive/basic/typed01/expected/model_3_3_4_1.eprime deleted file mode 100644 index 78ce007c35..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_3_4_1.eprime +++ /dev/null @@ -1,29 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..1) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -find y_ExplicitVarSizeWithMarker_Marker: int(0..1) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -find y_Occurrence: matrix indexed by [int(1)] of bool -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithMarker_Marker, - x_ExplicitVarSizeWithMarker_Values, y_Occurrence, y_ExplicitVarSizeWithMarker_Marker, - y_ExplicitVarSizeWithMarker_Values] -such that - 1 <= x_ExplicitVarSizeWithMarker_Marker /\ - (1 <= y_ExplicitVarSizeWithMarker_Marker /\ - y_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithMarker_Values[1]) - -> false, - 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, - 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, - x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, - x_ExplicitVarSizeWithFlags_Flags[1] -> - 1 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithFlags_Values[1], - 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithMarker_Values[1], - y_Occurrence[1] -> 1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = 1, - 1 <= y_ExplicitVarSizeWithMarker_Marker -> y_Occurrence[y_ExplicitVarSizeWithMarker_Values[1]] - diff --git a/tests/exhaustive/basic/typed01/expected/model_3_3_4_2-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_3_3_4_2-solution000001.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_3_4_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_3_4_2-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_3_3_4_2-solution000002.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_3_4_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_3_4_2-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_3_3_4_2-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_3_4_2-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_3_4_2.eprime b/tests/exhaustive/basic/typed01/expected/model_3_3_4_2.eprime deleted file mode 100644 index 2caba48cd3..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_3_4_2.eprime +++ /dev/null @@ -1,31 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..1) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -find y_ExplicitVarSizeWithMarker_Marker: int(0..1) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithMarker_Marker, - x_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithDummy, y_ExplicitVarSizeWithMarker_Marker, - y_ExplicitVarSizeWithMarker_Values] -such that - 1 <= x_ExplicitVarSizeWithMarker_Marker /\ - (1 <= y_ExplicitVarSizeWithMarker_Marker /\ - y_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithMarker_Values[1]) - -> false, - 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, - 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, - x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, - x_ExplicitVarSizeWithFlags_Flags[1] -> - 1 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithFlags_Values[1], - 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithMarker_Values[1], - y_ExplicitVarSizeWithDummy[1] != 2 -> - 1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = y_ExplicitVarSizeWithDummy[1], - 1 <= y_ExplicitVarSizeWithMarker_Marker -> - y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = y_ExplicitVarSizeWithMarker_Values[1] - diff --git a/tests/exhaustive/basic/typed01/expected/model_3_3_4_3-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_3_3_4_3-solution000001.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_3_4_3-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_3_4_3-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_3_3_4_3-solution000002.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_3_4_3-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_3_4_3-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_3_3_4_3-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_3_4_3-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_3_4_3.eprime b/tests/exhaustive/basic/typed01/expected/model_3_3_4_3.eprime deleted file mode 100644 index a85c4917ee..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_3_4_3.eprime +++ /dev/null @@ -1,25 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..1) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -find y_ExplicitVarSizeWithMarker_Marker: int(0..1) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithMarker_Marker, - x_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values] -such that - 1 <= x_ExplicitVarSizeWithMarker_Marker /\ - (1 <= y_ExplicitVarSizeWithMarker_Marker /\ - y_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithMarker_Values[1]) - -> false, - 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, - 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, - x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, - x_ExplicitVarSizeWithFlags_Flags[1] -> - 1 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithFlags_Values[1], - 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithMarker_Values[1] - diff --git a/tests/exhaustive/basic/typed01/expected/model_3_3_4_4-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_3_3_4_4-solution000001.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_3_4_4-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_3_4_4-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_3_3_4_4-solution000002.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_3_4_4-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_3_4_4-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_3_3_4_4-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_3_4_4-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_3_4_4.eprime b/tests/exhaustive/basic/typed01/expected/model_3_3_4_4.eprime deleted file mode 100644 index 422f3c0a9c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_3_4_4.eprime +++ /dev/null @@ -1,34 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..1) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -find y_ExplicitVarSizeWithMarker_Marker: int(0..1) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithMarker_Marker, - x_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values, - y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values] -such that - 1 <= x_ExplicitVarSizeWithMarker_Marker /\ - (1 <= y_ExplicitVarSizeWithMarker_Marker /\ - y_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithMarker_Values[1]) - -> false, - 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, - 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, - x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, - x_ExplicitVarSizeWithFlags_Flags[1] -> - 1 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithFlags_Values[1], - 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithMarker_Values[1], - y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, - y_ExplicitVarSizeWithFlags_Flags[1] -> - 1 <= y_ExplicitVarSizeWithMarker_Marker /\ - y_ExplicitVarSizeWithMarker_Values[1] = y_ExplicitVarSizeWithFlags_Values[1], - 1 <= y_ExplicitVarSizeWithMarker_Marker -> - y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = y_ExplicitVarSizeWithMarker_Values[1] - diff --git a/tests/exhaustive/basic/typed01/expected/model_3_4_1_1-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_3_4_1_1-solution000001.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_4_1_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_4_1_1-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_3_4_1_1-solution000002.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_4_1_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_4_1_1-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_3_4_1_1-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_4_1_1-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_4_1_1.eprime b/tests/exhaustive/basic/typed01/expected/model_3_4_1_1.eprime deleted file mode 100644 index e866a42f00..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_4_1_1.eprime +++ /dev/null @@ -1,23 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..1) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -find x_Occurrence: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -find y_Occurrence: matrix indexed by [int(1)] of bool -branching on - [x_Occurrence, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, y_Occurrence, - y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values] -such that - 1 <= x_ExplicitVarSizeWithMarker_Marker /\ - (y_ExplicitVarSizeWithFlags_Flags[1] /\ - y_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithMarker_Values[1]) - -> false, - 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, - y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, - x_Occurrence[1] -> 1 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[1] = 1, - 1 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[1]], - y_Occurrence[1] -> y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = 1, - y_ExplicitVarSizeWithFlags_Flags[1] -> y_Occurrence[y_ExplicitVarSizeWithFlags_Values[1]] - diff --git a/tests/exhaustive/basic/typed01/expected/model_3_4_1_2-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_3_4_1_2-solution000001.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_4_1_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_4_1_2-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_3_4_1_2-solution000002.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_4_1_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_4_1_2-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_3_4_1_2-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_4_1_2-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_4_1_2.eprime b/tests/exhaustive/basic/typed01/expected/model_3_4_1_2.eprime deleted file mode 100644 index 5eb12bb42d..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_4_1_2.eprime +++ /dev/null @@ -1,25 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..1) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -find x_Occurrence: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -branching on - [x_Occurrence, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithDummy, - y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values] -such that - 1 <= x_ExplicitVarSizeWithMarker_Marker /\ - (y_ExplicitVarSizeWithFlags_Flags[1] /\ - y_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithMarker_Values[1]) - -> false, - 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, - y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, - x_Occurrence[1] -> 1 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[1] = 1, - 1 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[1]], - y_ExplicitVarSizeWithDummy[1] != 2 -> - y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = y_ExplicitVarSizeWithDummy[1], - y_ExplicitVarSizeWithFlags_Flags[1] -> - y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = y_ExplicitVarSizeWithFlags_Values[1] - diff --git a/tests/exhaustive/basic/typed01/expected/model_3_4_1_3-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_3_4_1_3-solution000001.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_4_1_3-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_4_1_3-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_3_4_1_3-solution000002.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_4_1_3-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_4_1_3-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_3_4_1_3-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_4_1_3-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_4_1_3.eprime b/tests/exhaustive/basic/typed01/expected/model_3_4_1_3.eprime deleted file mode 100644 index 2ee31af242..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_4_1_3.eprime +++ /dev/null @@ -1,29 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..1) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -find x_Occurrence: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -find y_ExplicitVarSizeWithMarker_Marker: int(0..1) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -branching on - [x_Occurrence, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, - y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithFlags_Flags, - y_ExplicitVarSizeWithFlags_Values] -such that - 1 <= x_ExplicitVarSizeWithMarker_Marker /\ - (y_ExplicitVarSizeWithFlags_Flags[1] /\ - y_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithMarker_Values[1]) - -> false, - 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, - y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, - x_Occurrence[1] -> 1 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[1] = 1, - 1 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[1]], - 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, - 1 <= y_ExplicitVarSizeWithMarker_Marker -> - y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = y_ExplicitVarSizeWithMarker_Values[1], - y_ExplicitVarSizeWithFlags_Flags[1] -> - 1 <= y_ExplicitVarSizeWithMarker_Marker /\ - y_ExplicitVarSizeWithMarker_Values[1] = y_ExplicitVarSizeWithFlags_Values[1] - diff --git a/tests/exhaustive/basic/typed01/expected/model_3_4_1_4-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_3_4_1_4-solution000001.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_4_1_4-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_4_1_4-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_3_4_1_4-solution000002.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_4_1_4-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_4_1_4-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_3_4_1_4-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_4_1_4-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_4_1_4.eprime b/tests/exhaustive/basic/typed01/expected/model_3_4_1_4.eprime deleted file mode 100644 index 0da6db7905..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_4_1_4.eprime +++ /dev/null @@ -1,20 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..1) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -find x_Occurrence: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -branching on - [x_Occurrence, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, - y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values] -such that - 1 <= x_ExplicitVarSizeWithMarker_Marker /\ - (y_ExplicitVarSizeWithFlags_Flags[1] /\ - y_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithMarker_Values[1]) - -> false, - 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, - y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, - x_Occurrence[1] -> 1 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[1] = 1, - 1 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[1]] - diff --git a/tests/exhaustive/basic/typed01/expected/model_3_4_2_1-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_3_4_2_1-solution000001.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_4_2_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_4_2_1-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_3_4_2_1-solution000002.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_4_2_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_4_2_1-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_3_4_2_1-solution000003.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_4_2_1-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_4_2_1.eprime b/tests/exhaustive/basic/typed01/expected/model_3_4_2_1.eprime deleted file mode 100644 index 3ba13f3d49..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_4_2_1.eprime +++ /dev/null @@ -1,25 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..1) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -find y_Occurrence: matrix indexed by [int(1)] of bool -branching on - [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, y_Occurrence, - y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values] -such that - 1 <= x_ExplicitVarSizeWithMarker_Marker /\ - (y_ExplicitVarSizeWithFlags_Flags[1] /\ - y_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithMarker_Values[1]) - -> false, - 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, - y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, - x_ExplicitVarSizeWithDummy[1] != 2 -> - 1 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithDummy[1], - 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithMarker_Values[1], - y_Occurrence[1] -> y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = 1, - y_ExplicitVarSizeWithFlags_Flags[1] -> y_Occurrence[y_ExplicitVarSizeWithFlags_Values[1]] - diff --git a/tests/exhaustive/basic/typed01/expected/model_3_4_2_2-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_3_4_2_2-solution000001.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_4_2_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_4_2_2-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_3_4_2_2-solution000002.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_4_2_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_4_2_2-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_3_4_2_2-solution000003.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_4_2_2-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_4_2_2.eprime b/tests/exhaustive/basic/typed01/expected/model_3_4_2_2.eprime deleted file mode 100644 index 493690aa87..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_4_2_2.eprime +++ /dev/null @@ -1,27 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..1) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -branching on - [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, - y_ExplicitVarSizeWithDummy, y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values] -such that - 1 <= x_ExplicitVarSizeWithMarker_Marker /\ - (y_ExplicitVarSizeWithFlags_Flags[1] /\ - y_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithMarker_Values[1]) - -> false, - 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, - y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, - x_ExplicitVarSizeWithDummy[1] != 2 -> - 1 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithDummy[1], - 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithMarker_Values[1], - y_ExplicitVarSizeWithDummy[1] != 2 -> - y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = y_ExplicitVarSizeWithDummy[1], - y_ExplicitVarSizeWithFlags_Flags[1] -> - y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = y_ExplicitVarSizeWithFlags_Values[1] - diff --git a/tests/exhaustive/basic/typed01/expected/model_3_4_2_3-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_3_4_2_3-solution000001.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_4_2_3-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_4_2_3-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_3_4_2_3-solution000002.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_4_2_3-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_4_2_3-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_3_4_2_3-solution000003.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_4_2_3-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_4_2_3.eprime b/tests/exhaustive/basic/typed01/expected/model_3_4_2_3.eprime deleted file mode 100644 index 1b189dfc27..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_4_2_3.eprime +++ /dev/null @@ -1,31 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..1) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -find y_ExplicitVarSizeWithMarker_Marker: int(0..1) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -branching on - [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, - y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithFlags_Flags, - y_ExplicitVarSizeWithFlags_Values] -such that - 1 <= x_ExplicitVarSizeWithMarker_Marker /\ - (y_ExplicitVarSizeWithFlags_Flags[1] /\ - y_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithMarker_Values[1]) - -> false, - 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, - y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, - x_ExplicitVarSizeWithDummy[1] != 2 -> - 1 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithDummy[1], - 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithMarker_Values[1], - 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, - 1 <= y_ExplicitVarSizeWithMarker_Marker -> - y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = y_ExplicitVarSizeWithMarker_Values[1], - y_ExplicitVarSizeWithFlags_Flags[1] -> - 1 <= y_ExplicitVarSizeWithMarker_Marker /\ - y_ExplicitVarSizeWithMarker_Values[1] = y_ExplicitVarSizeWithFlags_Values[1] - diff --git a/tests/exhaustive/basic/typed01/expected/model_3_4_2_4-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_3_4_2_4-solution000001.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_4_2_4-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_4_2_4-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_3_4_2_4-solution000002.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_4_2_4-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_4_2_4-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_3_4_2_4-solution000003.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_4_2_4-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_4_2_4.eprime b/tests/exhaustive/basic/typed01/expected/model_3_4_2_4.eprime deleted file mode 100644 index 4a02c74755..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_4_2_4.eprime +++ /dev/null @@ -1,22 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..1) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -branching on - [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, - y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values] -such that - 1 <= x_ExplicitVarSizeWithMarker_Marker /\ - (y_ExplicitVarSizeWithFlags_Flags[1] /\ - y_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithMarker_Values[1]) - -> false, - 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, - y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, - x_ExplicitVarSizeWithDummy[1] != 2 -> - 1 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithDummy[1], - 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithMarker_Values[1] - diff --git a/tests/exhaustive/basic/typed01/expected/model_3_4_3_1-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_3_4_3_1-solution000001.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_4_3_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_4_3_1-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_3_4_3_1-solution000002.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_4_3_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_4_3_1-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_3_4_3_1-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_4_3_1-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_4_3_1.eprime b/tests/exhaustive/basic/typed01/expected/model_3_4_3_1.eprime deleted file mode 100644 index 957e3308a9..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_4_3_1.eprime +++ /dev/null @@ -1,20 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..1) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -find y_Occurrence: matrix indexed by [int(1)] of bool -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, y_Occurrence, - y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values] -such that - 1 <= x_ExplicitVarSizeWithMarker_Marker /\ - (y_ExplicitVarSizeWithFlags_Flags[1] /\ - y_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithMarker_Values[1]) - -> false, - 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, - y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, - y_Occurrence[1] -> y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = 1, - y_ExplicitVarSizeWithFlags_Flags[1] -> y_Occurrence[y_ExplicitVarSizeWithFlags_Values[1]] - diff --git a/tests/exhaustive/basic/typed01/expected/model_3_4_3_2-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_3_4_3_2-solution000001.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_4_3_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_4_3_2-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_3_4_3_2-solution000002.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_4_3_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_4_3_2-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_3_4_3_2-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_4_3_2-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_4_3_2.eprime b/tests/exhaustive/basic/typed01/expected/model_3_4_3_2.eprime deleted file mode 100644 index d785a45f2e..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_4_3_2.eprime +++ /dev/null @@ -1,22 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..1) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithDummy, - y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values] -such that - 1 <= x_ExplicitVarSizeWithMarker_Marker /\ - (y_ExplicitVarSizeWithFlags_Flags[1] /\ - y_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithMarker_Values[1]) - -> false, - 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, - y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, - y_ExplicitVarSizeWithDummy[1] != 2 -> - y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = y_ExplicitVarSizeWithDummy[1], - y_ExplicitVarSizeWithFlags_Flags[1] -> - y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = y_ExplicitVarSizeWithFlags_Values[1] - diff --git a/tests/exhaustive/basic/typed01/expected/model_3_4_3_3-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_3_4_3_3-solution000001.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_4_3_3-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_4_3_3-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_3_4_3_3-solution000002.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_4_3_3-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_4_3_3-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_3_4_3_3-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_4_3_3-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_4_3_3.eprime b/tests/exhaustive/basic/typed01/expected/model_3_4_3_3.eprime deleted file mode 100644 index d07a94b90a..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_4_3_3.eprime +++ /dev/null @@ -1,25 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..1) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -find y_ExplicitVarSizeWithMarker_Marker: int(0..1) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithMarker_Marker, - y_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values] -such that - 1 <= x_ExplicitVarSizeWithMarker_Marker /\ - (y_ExplicitVarSizeWithFlags_Flags[1] /\ - y_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithMarker_Values[1]) - -> false, - 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, - y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, - 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, - 1 <= y_ExplicitVarSizeWithMarker_Marker -> - y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = y_ExplicitVarSizeWithMarker_Values[1], - y_ExplicitVarSizeWithFlags_Flags[1] -> - 1 <= y_ExplicitVarSizeWithMarker_Marker /\ - y_ExplicitVarSizeWithMarker_Values[1] = y_ExplicitVarSizeWithFlags_Values[1] - diff --git a/tests/exhaustive/basic/typed01/expected/model_3_4_3_4-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_3_4_3_4-solution000001.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_4_3_4-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_4_3_4-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_3_4_3_4-solution000002.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_4_3_4-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_4_3_4-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_3_4_3_4-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_4_3_4-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_4_3_4.eprime b/tests/exhaustive/basic/typed01/expected/model_3_4_3_4.eprime deleted file mode 100644 index bd5f878d61..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_4_3_4.eprime +++ /dev/null @@ -1,17 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..1) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithFlags_Flags, - y_ExplicitVarSizeWithFlags_Values] -such that - 1 <= x_ExplicitVarSizeWithMarker_Marker /\ - (y_ExplicitVarSizeWithFlags_Flags[1] /\ - y_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithMarker_Values[1]) - -> false, - 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, - y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1 - diff --git a/tests/exhaustive/basic/typed01/expected/model_3_4_4_1-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_3_4_4_1-solution000001.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_4_4_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_4_4_1-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_3_4_4_1-solution000002.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_4_4_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_4_4_1-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_3_4_4_1-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_4_4_1-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_4_4_1.eprime b/tests/exhaustive/basic/typed01/expected/model_3_4_4_1.eprime deleted file mode 100644 index bd8649ff85..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_4_4_1.eprime +++ /dev/null @@ -1,29 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..1) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -find y_Occurrence: matrix indexed by [int(1)] of bool -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithMarker_Marker, - x_ExplicitVarSizeWithMarker_Values, y_Occurrence, y_ExplicitVarSizeWithFlags_Flags, - y_ExplicitVarSizeWithFlags_Values] -such that - 1 <= x_ExplicitVarSizeWithMarker_Marker /\ - (y_ExplicitVarSizeWithFlags_Flags[1] /\ - y_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithMarker_Values[1]) - -> false, - 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, - y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, - x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, - x_ExplicitVarSizeWithFlags_Flags[1] -> - 1 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithFlags_Values[1], - 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithMarker_Values[1], - y_Occurrence[1] -> y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = 1, - y_ExplicitVarSizeWithFlags_Flags[1] -> y_Occurrence[y_ExplicitVarSizeWithFlags_Values[1]] - diff --git a/tests/exhaustive/basic/typed01/expected/model_3_4_4_2-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_3_4_4_2-solution000001.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_4_4_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_4_4_2-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_3_4_4_2-solution000002.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_4_4_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_4_4_2-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_3_4_4_2-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_4_4_2-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_4_4_2.eprime b/tests/exhaustive/basic/typed01/expected/model_3_4_4_2.eprime deleted file mode 100644 index 28a0d6651c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_4_4_2.eprime +++ /dev/null @@ -1,31 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..1) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithMarker_Marker, - x_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithDummy, y_ExplicitVarSizeWithFlags_Flags, - y_ExplicitVarSizeWithFlags_Values] -such that - 1 <= x_ExplicitVarSizeWithMarker_Marker /\ - (y_ExplicitVarSizeWithFlags_Flags[1] /\ - y_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithMarker_Values[1]) - -> false, - 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, - y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, - x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, - x_ExplicitVarSizeWithFlags_Flags[1] -> - 1 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithFlags_Values[1], - 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithMarker_Values[1], - y_ExplicitVarSizeWithDummy[1] != 2 -> - y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = y_ExplicitVarSizeWithDummy[1], - y_ExplicitVarSizeWithFlags_Flags[1] -> - y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = y_ExplicitVarSizeWithFlags_Values[1] - diff --git a/tests/exhaustive/basic/typed01/expected/model_3_4_4_3-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_3_4_4_3-solution000001.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_4_4_3-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_4_4_3-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_3_4_4_3-solution000002.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_4_4_3-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_4_4_3-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_3_4_4_3-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_4_4_3-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_4_4_3.eprime b/tests/exhaustive/basic/typed01/expected/model_3_4_4_3.eprime deleted file mode 100644 index 3211485200..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_4_4_3.eprime +++ /dev/null @@ -1,34 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..1) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -find y_ExplicitVarSizeWithMarker_Marker: int(0..1) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithMarker_Marker, - x_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values, - y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values] -such that - 1 <= x_ExplicitVarSizeWithMarker_Marker /\ - (y_ExplicitVarSizeWithFlags_Flags[1] /\ - y_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithMarker_Values[1]) - -> false, - 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, - y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, - x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, - x_ExplicitVarSizeWithFlags_Flags[1] -> - 1 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithFlags_Values[1], - 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithMarker_Values[1], - 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, - 1 <= y_ExplicitVarSizeWithMarker_Marker -> - y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = y_ExplicitVarSizeWithMarker_Values[1], - y_ExplicitVarSizeWithFlags_Flags[1] -> - 1 <= y_ExplicitVarSizeWithMarker_Marker /\ - y_ExplicitVarSizeWithMarker_Values[1] = y_ExplicitVarSizeWithFlags_Values[1] - diff --git a/tests/exhaustive/basic/typed01/expected/model_3_4_4_4-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_3_4_4_4-solution000001.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_4_4_4-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_4_4_4-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_3_4_4_4-solution000002.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_4_4_4-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_4_4_4-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_3_4_4_4-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_4_4_4-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_4_4_4.eprime b/tests/exhaustive/basic/typed01/expected/model_3_4_4_4.eprime deleted file mode 100644 index 0fd26730a3..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_3_4_4_4.eprime +++ /dev/null @@ -1,25 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..1) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithMarker_Marker, - x_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values] -such that - 1 <= x_ExplicitVarSizeWithMarker_Marker /\ - (y_ExplicitVarSizeWithFlags_Flags[1] /\ - y_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithMarker_Values[1]) - -> false, - 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, - y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, - x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, - x_ExplicitVarSizeWithFlags_Flags[1] -> - 1 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithFlags_Values[1], - 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithMarker_Values[1] - diff --git a/tests/exhaustive/basic/typed01/expected/model_4_1_1_1-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_4_1_1_1-solution000001.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_1_1_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_1_1_1-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_4_1_1_1-solution000002.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_1_1_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_1_1_1-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_4_1_1_1-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_1_1_1-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_1_1_1.eprime b/tests/exhaustive/basic/typed01/expected/model_4_1_1_1.eprime deleted file mode 100644 index 146f1578b5..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_1_1_1.eprime +++ /dev/null @@ -1,13 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -find x_Occurrence: matrix indexed by [int(1)] of bool -find y_Occurrence: matrix indexed by [int(1)] of bool -branching on [x_Occurrence, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, y_Occurrence] -such that - x_ExplicitVarSizeWithFlags_Flags[1] /\ y_Occurrence[x_ExplicitVarSizeWithFlags_Values[1]] -> false, - x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, - x_Occurrence[1] -> x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = 1, - x_ExplicitVarSizeWithFlags_Flags[1] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[1]] - diff --git a/tests/exhaustive/basic/typed01/expected/model_4_1_1_2-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_4_1_1_2-solution000001.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_1_1_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_1_1_2-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_4_1_1_2-solution000002.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_1_1_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_1_1_2-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_4_1_1_2-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_1_1_2-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_1_1_2.eprime b/tests/exhaustive/basic/typed01/expected/model_4_1_1_2.eprime deleted file mode 100644 index b5a88ded3f..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_1_1_2.eprime +++ /dev/null @@ -1,18 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -find x_Occurrence: matrix indexed by [int(1)] of bool -find y_Occurrence: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -branching on - [x_Occurrence, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithDummy, - y_Occurrence] -such that - x_ExplicitVarSizeWithFlags_Flags[1] /\ y_Occurrence[x_ExplicitVarSizeWithFlags_Values[1]] -> false, - x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, - x_Occurrence[1] -> x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = 1, - x_ExplicitVarSizeWithFlags_Flags[1] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[1]], - y_ExplicitVarSizeWithDummy[1] != 2 -> y_Occurrence[y_ExplicitVarSizeWithDummy[1]], - y_Occurrence[1] -> y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = 1 - diff --git a/tests/exhaustive/basic/typed01/expected/model_4_1_1_3-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_4_1_1_3-solution000001.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_1_1_3-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_1_1_3-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_4_1_1_3-solution000002.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_1_1_3-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_1_1_3-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_4_1_1_3-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_1_1_3-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_1_1_3.eprime b/tests/exhaustive/basic/typed01/expected/model_4_1_1_3.eprime deleted file mode 100644 index 0613ec22d1..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_1_1_3.eprime +++ /dev/null @@ -1,20 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -find x_Occurrence: matrix indexed by [int(1)] of bool -find y_Occurrence: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithMarker_Marker: int(0..1) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -branching on - [x_Occurrence, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, - y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values, y_Occurrence] -such that - x_ExplicitVarSizeWithFlags_Flags[1] /\ y_Occurrence[x_ExplicitVarSizeWithFlags_Values[1]] -> false, - x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, - x_Occurrence[1] -> x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = 1, - x_ExplicitVarSizeWithFlags_Flags[1] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[1]], - 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, - 1 <= y_ExplicitVarSizeWithMarker_Marker -> y_Occurrence[y_ExplicitVarSizeWithMarker_Values[1]], - y_Occurrence[1] -> 1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = 1 - diff --git a/tests/exhaustive/basic/typed01/expected/model_4_1_1_4-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_4_1_1_4-solution000001.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_1_1_4-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_1_1_4-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_4_1_1_4-solution000002.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_1_1_4-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_1_1_4-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_4_1_1_4-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_1_1_4-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_1_1_4.eprime b/tests/exhaustive/basic/typed01/expected/model_4_1_1_4.eprime deleted file mode 100644 index 65f046be5f..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_1_1_4.eprime +++ /dev/null @@ -1,20 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -find x_Occurrence: matrix indexed by [int(1)] of bool -find y_Occurrence: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -branching on - [x_Occurrence, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, - y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values, y_Occurrence] -such that - x_ExplicitVarSizeWithFlags_Flags[1] /\ y_Occurrence[x_ExplicitVarSizeWithFlags_Values[1]] -> false, - x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, - x_Occurrence[1] -> x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = 1, - x_ExplicitVarSizeWithFlags_Flags[1] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[1]], - y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, - y_ExplicitVarSizeWithFlags_Flags[1] -> y_Occurrence[y_ExplicitVarSizeWithFlags_Values[1]], - y_Occurrence[1] -> y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = 1 - diff --git a/tests/exhaustive/basic/typed01/expected/model_4_1_2_1-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_4_1_2_1-solution000001.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_1_2_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_1_2_1-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_4_1_2_1-solution000002.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_1_2_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_1_2_1-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_4_1_2_1-solution000003.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_1_2_1-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_1_2_1.eprime b/tests/exhaustive/basic/typed01/expected/model_4_1_2_1.eprime deleted file mode 100644 index 35a3f77d73..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_1_2_1.eprime +++ /dev/null @@ -1,16 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -find y_Occurrence: matrix indexed by [int(1)] of bool -branching on - [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, y_Occurrence] -such that - x_ExplicitVarSizeWithFlags_Flags[1] /\ y_Occurrence[x_ExplicitVarSizeWithFlags_Values[1]] -> false, - x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, - x_ExplicitVarSizeWithDummy[1] != 2 -> - x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithDummy[1], - x_ExplicitVarSizeWithFlags_Flags[1] -> - x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithFlags_Values[1] - diff --git a/tests/exhaustive/basic/typed01/expected/model_4_1_2_2-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_4_1_2_2-solution000001.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_1_2_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_1_2_2-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_4_1_2_2-solution000002.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_1_2_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_1_2_2-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_4_1_2_2-solution000003.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_1_2_2-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_1_2_2.eprime b/tests/exhaustive/basic/typed01/expected/model_4_1_2_2.eprime deleted file mode 100644 index 4248fba7ca..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_1_2_2.eprime +++ /dev/null @@ -1,20 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -find y_Occurrence: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -branching on - [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, - y_ExplicitVarSizeWithDummy, y_Occurrence] -such that - x_ExplicitVarSizeWithFlags_Flags[1] /\ y_Occurrence[x_ExplicitVarSizeWithFlags_Values[1]] -> false, - x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, - x_ExplicitVarSizeWithDummy[1] != 2 -> - x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithDummy[1], - x_ExplicitVarSizeWithFlags_Flags[1] -> - x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithFlags_Values[1], - y_ExplicitVarSizeWithDummy[1] != 2 -> y_Occurrence[y_ExplicitVarSizeWithDummy[1]], - y_Occurrence[1] -> y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = 1 - diff --git a/tests/exhaustive/basic/typed01/expected/model_4_1_2_3-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_4_1_2_3-solution000001.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_1_2_3-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_1_2_3-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_4_1_2_3-solution000002.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_1_2_3-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_1_2_3-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_4_1_2_3-solution000003.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_1_2_3-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_1_2_3.eprime b/tests/exhaustive/basic/typed01/expected/model_4_1_2_3.eprime deleted file mode 100644 index b9a7ce2420..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_1_2_3.eprime +++ /dev/null @@ -1,22 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -find y_Occurrence: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithMarker_Marker: int(0..1) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -branching on - [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, - y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values, y_Occurrence] -such that - x_ExplicitVarSizeWithFlags_Flags[1] /\ y_Occurrence[x_ExplicitVarSizeWithFlags_Values[1]] -> false, - x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, - x_ExplicitVarSizeWithDummy[1] != 2 -> - x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithDummy[1], - x_ExplicitVarSizeWithFlags_Flags[1] -> - x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithFlags_Values[1], - 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, - 1 <= y_ExplicitVarSizeWithMarker_Marker -> y_Occurrence[y_ExplicitVarSizeWithMarker_Values[1]], - y_Occurrence[1] -> 1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = 1 - diff --git a/tests/exhaustive/basic/typed01/expected/model_4_1_2_4-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_4_1_2_4-solution000001.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_1_2_4-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_1_2_4-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_4_1_2_4-solution000002.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_1_2_4-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_1_2_4-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_4_1_2_4-solution000003.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_1_2_4-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_1_2_4.eprime b/tests/exhaustive/basic/typed01/expected/model_4_1_2_4.eprime deleted file mode 100644 index 22a953d049..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_1_2_4.eprime +++ /dev/null @@ -1,22 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -find y_Occurrence: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -branching on - [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, - y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values, y_Occurrence] -such that - x_ExplicitVarSizeWithFlags_Flags[1] /\ y_Occurrence[x_ExplicitVarSizeWithFlags_Values[1]] -> false, - x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, - x_ExplicitVarSizeWithDummy[1] != 2 -> - x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithDummy[1], - x_ExplicitVarSizeWithFlags_Flags[1] -> - x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithFlags_Values[1], - y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, - y_ExplicitVarSizeWithFlags_Flags[1] -> y_Occurrence[y_ExplicitVarSizeWithFlags_Values[1]], - y_Occurrence[1] -> y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = 1 - diff --git a/tests/exhaustive/basic/typed01/expected/model_4_1_3_1-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_4_1_3_1-solution000001.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_1_3_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_1_3_1-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_4_1_3_1-solution000002.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_1_3_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_1_3_1-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_4_1_3_1-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_1_3_1-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_1_3_1.eprime b/tests/exhaustive/basic/typed01/expected/model_4_1_3_1.eprime deleted file mode 100644 index b5825355dc..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_1_3_1.eprime +++ /dev/null @@ -1,20 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -find x_ExplicitVarSizeWithMarker_Marker: int(0..1) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -find y_Occurrence: matrix indexed by [int(1)] of bool -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithFlags_Flags, - x_ExplicitVarSizeWithFlags_Values, y_Occurrence] -such that - x_ExplicitVarSizeWithFlags_Flags[1] /\ y_Occurrence[x_ExplicitVarSizeWithFlags_Values[1]] -> false, - x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, - 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, - 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithMarker_Values[1], - x_ExplicitVarSizeWithFlags_Flags[1] -> - 1 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithFlags_Values[1] - diff --git a/tests/exhaustive/basic/typed01/expected/model_4_1_3_2-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_4_1_3_2-solution000001.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_1_3_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_1_3_2-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_4_1_3_2-solution000002.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_1_3_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_1_3_2-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_4_1_3_2-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_1_3_2-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_1_3_2.eprime b/tests/exhaustive/basic/typed01/expected/model_4_1_3_2.eprime deleted file mode 100644 index 8d7d07b4a2..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_1_3_2.eprime +++ /dev/null @@ -1,23 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -find x_ExplicitVarSizeWithMarker_Marker: int(0..1) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -find y_Occurrence: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithFlags_Flags, - x_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithDummy, y_Occurrence] -such that - x_ExplicitVarSizeWithFlags_Flags[1] /\ y_Occurrence[x_ExplicitVarSizeWithFlags_Values[1]] -> false, - x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, - 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, - 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithMarker_Values[1], - x_ExplicitVarSizeWithFlags_Flags[1] -> - 1 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithFlags_Values[1], - y_ExplicitVarSizeWithDummy[1] != 2 -> y_Occurrence[y_ExplicitVarSizeWithDummy[1]], - y_Occurrence[1] -> y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = 1 - diff --git a/tests/exhaustive/basic/typed01/expected/model_4_1_3_3-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_4_1_3_3-solution000001.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_1_3_3-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_1_3_3-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_4_1_3_3-solution000002.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_1_3_3-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_1_3_3-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_4_1_3_3-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_1_3_3-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_1_3_3.eprime b/tests/exhaustive/basic/typed01/expected/model_4_1_3_3.eprime deleted file mode 100644 index ff41c8db54..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_1_3_3.eprime +++ /dev/null @@ -1,26 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -find x_ExplicitVarSizeWithMarker_Marker: int(0..1) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -find y_Occurrence: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithMarker_Marker: int(0..1) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithFlags_Flags, - x_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values, - y_Occurrence] -such that - x_ExplicitVarSizeWithFlags_Flags[1] /\ y_Occurrence[x_ExplicitVarSizeWithFlags_Values[1]] -> false, - x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, - 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, - 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithMarker_Values[1], - x_ExplicitVarSizeWithFlags_Flags[1] -> - 1 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithFlags_Values[1], - 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, - 1 <= y_ExplicitVarSizeWithMarker_Marker -> y_Occurrence[y_ExplicitVarSizeWithMarker_Values[1]], - y_Occurrence[1] -> 1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = 1 - diff --git a/tests/exhaustive/basic/typed01/expected/model_4_1_3_4-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_4_1_3_4-solution000001.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_1_3_4-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_1_3_4-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_4_1_3_4-solution000002.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_1_3_4-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_1_3_4-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_4_1_3_4-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_1_3_4-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_1_3_4.eprime b/tests/exhaustive/basic/typed01/expected/model_4_1_3_4.eprime deleted file mode 100644 index 0f20e6b43f..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_1_3_4.eprime +++ /dev/null @@ -1,26 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -find x_ExplicitVarSizeWithMarker_Marker: int(0..1) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -find y_Occurrence: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithFlags_Flags, - x_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values, - y_Occurrence] -such that - x_ExplicitVarSizeWithFlags_Flags[1] /\ y_Occurrence[x_ExplicitVarSizeWithFlags_Values[1]] -> false, - x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, - 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, - 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithMarker_Values[1], - x_ExplicitVarSizeWithFlags_Flags[1] -> - 1 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithFlags_Values[1], - y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, - y_ExplicitVarSizeWithFlags_Flags[1] -> y_Occurrence[y_ExplicitVarSizeWithFlags_Values[1]], - y_Occurrence[1] -> y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = 1 - diff --git a/tests/exhaustive/basic/typed01/expected/model_4_1_4_1-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_4_1_4_1-solution000001.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_1_4_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_1_4_1-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_4_1_4_1-solution000002.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_1_4_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_1_4_1-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_4_1_4_1-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_1_4_1-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_1_4_1.eprime b/tests/exhaustive/basic/typed01/expected/model_4_1_4_1.eprime deleted file mode 100644 index a83a129f9d..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_1_4_1.eprime +++ /dev/null @@ -1,10 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -find y_Occurrence: matrix indexed by [int(1)] of bool -branching on [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, y_Occurrence] -such that - x_ExplicitVarSizeWithFlags_Flags[1] /\ y_Occurrence[x_ExplicitVarSizeWithFlags_Values[1]] -> false, - x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1 - diff --git a/tests/exhaustive/basic/typed01/expected/model_4_1_4_2-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_4_1_4_2-solution000001.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_1_4_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_1_4_2-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_4_1_4_2-solution000002.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_1_4_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_1_4_2-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_4_1_4_2-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_1_4_2-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_1_4_2.eprime b/tests/exhaustive/basic/typed01/expected/model_4_1_4_2.eprime deleted file mode 100644 index 9cba33315d..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_1_4_2.eprime +++ /dev/null @@ -1,14 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -find y_Occurrence: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithDummy, y_Occurrence] -such that - x_ExplicitVarSizeWithFlags_Flags[1] /\ y_Occurrence[x_ExplicitVarSizeWithFlags_Values[1]] -> false, - x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, - y_ExplicitVarSizeWithDummy[1] != 2 -> y_Occurrence[y_ExplicitVarSizeWithDummy[1]], - y_Occurrence[1] -> y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = 1 - diff --git a/tests/exhaustive/basic/typed01/expected/model_4_1_4_3-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_4_1_4_3-solution000001.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_1_4_3-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_1_4_3-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_4_1_4_3-solution000002.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_1_4_3-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_1_4_3-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_4_1_4_3-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_1_4_3-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_1_4_3.eprime b/tests/exhaustive/basic/typed01/expected/model_4_1_4_3.eprime deleted file mode 100644 index f0d019484b..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_1_4_3.eprime +++ /dev/null @@ -1,17 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -find y_Occurrence: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithMarker_Marker: int(0..1) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithMarker_Marker, - y_ExplicitVarSizeWithMarker_Values, y_Occurrence] -such that - x_ExplicitVarSizeWithFlags_Flags[1] /\ y_Occurrence[x_ExplicitVarSizeWithFlags_Values[1]] -> false, - x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, - 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, - 1 <= y_ExplicitVarSizeWithMarker_Marker -> y_Occurrence[y_ExplicitVarSizeWithMarker_Values[1]], - y_Occurrence[1] -> 1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = 1 - diff --git a/tests/exhaustive/basic/typed01/expected/model_4_1_4_4-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_4_1_4_4-solution000001.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_1_4_4-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_1_4_4-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_4_1_4_4-solution000002.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_1_4_4-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_1_4_4-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_4_1_4_4-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_1_4_4-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_1_4_4.eprime b/tests/exhaustive/basic/typed01/expected/model_4_1_4_4.eprime deleted file mode 100644 index 0f279552c2..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_1_4_4.eprime +++ /dev/null @@ -1,17 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -find y_Occurrence: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithFlags_Flags, - y_ExplicitVarSizeWithFlags_Values, y_Occurrence] -such that - x_ExplicitVarSizeWithFlags_Flags[1] /\ y_Occurrence[x_ExplicitVarSizeWithFlags_Values[1]] -> false, - x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, - y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, - y_ExplicitVarSizeWithFlags_Flags[1] -> y_Occurrence[y_ExplicitVarSizeWithFlags_Values[1]], - y_Occurrence[1] -> y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = 1 - diff --git a/tests/exhaustive/basic/typed01/expected/model_4_2_1_1-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_4_2_1_1-solution000001.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_2_1_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_2_1_1-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_4_2_1_1-solution000002.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_2_1_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_2_1_1-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_4_2_1_1-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_2_1_1-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_2_1_1.eprime b/tests/exhaustive/basic/typed01/expected/model_4_2_1_1.eprime deleted file mode 100644 index 7af0d950bd..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_2_1_1.eprime +++ /dev/null @@ -1,20 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -find x_Occurrence: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -find y_Occurrence: matrix indexed by [int(1)] of bool -branching on - [x_Occurrence, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, y_Occurrence, - y_ExplicitVarSizeWithDummy] -such that - x_ExplicitVarSizeWithFlags_Flags[1] /\ - (y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithFlags_Values[1]) - -> false, - x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, - x_Occurrence[1] -> x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = 1, - x_ExplicitVarSizeWithFlags_Flags[1] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[1]], - y_Occurrence[1] -> y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = 1, - y_ExplicitVarSizeWithDummy[1] != 2 -> y_Occurrence[y_ExplicitVarSizeWithDummy[1]] - diff --git a/tests/exhaustive/basic/typed01/expected/model_4_2_1_2-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_4_2_1_2-solution000001.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_2_1_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_2_1_2-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_4_2_1_2-solution000002.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_2_1_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_2_1_2-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_4_2_1_2-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_2_1_2-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_2_1_2.eprime b/tests/exhaustive/basic/typed01/expected/model_4_2_1_2.eprime deleted file mode 100644 index 7c872d9415..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_2_1_2.eprime +++ /dev/null @@ -1,16 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -find x_Occurrence: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -branching on - [x_Occurrence, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithDummy] -such that - x_ExplicitVarSizeWithFlags_Flags[1] /\ - (y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithFlags_Values[1]) - -> false, - x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, - x_Occurrence[1] -> x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = 1, - x_ExplicitVarSizeWithFlags_Flags[1] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[1]] - diff --git a/tests/exhaustive/basic/typed01/expected/model_4_2_1_3-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_4_2_1_3-solution000001.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_2_1_3-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_2_1_3-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_4_2_1_3-solution000002.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_2_1_3-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_2_1_3-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_4_2_1_3-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_2_1_3-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_2_1_3.eprime b/tests/exhaustive/basic/typed01/expected/model_4_2_1_3.eprime deleted file mode 100644 index ff225c5a29..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_2_1_3.eprime +++ /dev/null @@ -1,24 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -find x_Occurrence: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -find y_ExplicitVarSizeWithMarker_Marker: int(0..1) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -branching on - [x_Occurrence, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, - y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithDummy] -such that - x_ExplicitVarSizeWithFlags_Flags[1] /\ - (y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithFlags_Values[1]) - -> false, - x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, - x_Occurrence[1] -> x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = 1, - x_ExplicitVarSizeWithFlags_Flags[1] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[1]], - 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, - 1 <= y_ExplicitVarSizeWithMarker_Marker -> - y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = y_ExplicitVarSizeWithMarker_Values[1], - y_ExplicitVarSizeWithDummy[1] != 2 -> - 1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = y_ExplicitVarSizeWithDummy[1] - diff --git a/tests/exhaustive/basic/typed01/expected/model_4_2_1_4-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_4_2_1_4-solution000001.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_2_1_4-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_2_1_4-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_4_2_1_4-solution000002.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_2_1_4-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_2_1_4-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_4_2_1_4-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_2_1_4-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_2_1_4.eprime b/tests/exhaustive/basic/typed01/expected/model_4_2_1_4.eprime deleted file mode 100644 index 819e4e33ed..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_2_1_4.eprime +++ /dev/null @@ -1,24 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -find x_Occurrence: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -branching on - [x_Occurrence, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, - y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithDummy] -such that - x_ExplicitVarSizeWithFlags_Flags[1] /\ - (y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithFlags_Values[1]) - -> false, - x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, - x_Occurrence[1] -> x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = 1, - x_ExplicitVarSizeWithFlags_Flags[1] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[1]], - y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, - y_ExplicitVarSizeWithFlags_Flags[1] -> - y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = y_ExplicitVarSizeWithFlags_Values[1], - y_ExplicitVarSizeWithDummy[1] != 2 -> - y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = y_ExplicitVarSizeWithDummy[1] - diff --git a/tests/exhaustive/basic/typed01/expected/model_4_2_2_1-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_4_2_2_1-solution000001.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_2_2_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_2_2_1-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_4_2_2_1-solution000002.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_2_2_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_2_2_1-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_4_2_2_1-solution000003.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_2_2_1-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_2_2_1.eprime b/tests/exhaustive/basic/typed01/expected/model_4_2_2_1.eprime deleted file mode 100644 index c705186841..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_2_2_1.eprime +++ /dev/null @@ -1,22 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -find y_Occurrence: matrix indexed by [int(1)] of bool -branching on - [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, y_Occurrence, - y_ExplicitVarSizeWithDummy] -such that - x_ExplicitVarSizeWithFlags_Flags[1] /\ - (y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithFlags_Values[1]) - -> false, - x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, - x_ExplicitVarSizeWithDummy[1] != 2 -> - x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithDummy[1], - x_ExplicitVarSizeWithFlags_Flags[1] -> - x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithFlags_Values[1], - y_Occurrence[1] -> y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = 1, - y_ExplicitVarSizeWithDummy[1] != 2 -> y_Occurrence[y_ExplicitVarSizeWithDummy[1]] - diff --git a/tests/exhaustive/basic/typed01/expected/model_4_2_2_2-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_4_2_2_2-solution000001.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_2_2_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_2_2_2-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_4_2_2_2-solution000002.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_2_2_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_2_2_2-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_4_2_2_2-solution000003.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_2_2_2-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_2_2_2.eprime b/tests/exhaustive/basic/typed01/expected/model_4_2_2_2.eprime deleted file mode 100644 index 6d6bdff10b..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_2_2_2.eprime +++ /dev/null @@ -1,19 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -branching on - [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, - y_ExplicitVarSizeWithDummy] -such that - x_ExplicitVarSizeWithFlags_Flags[1] /\ - (y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithFlags_Values[1]) - -> false, - x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, - x_ExplicitVarSizeWithDummy[1] != 2 -> - x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithDummy[1], - x_ExplicitVarSizeWithFlags_Flags[1] -> - x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithFlags_Values[1] - diff --git a/tests/exhaustive/basic/typed01/expected/model_4_2_2_3-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_4_2_2_3-solution000001.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_2_2_3-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_2_2_3-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_4_2_2_3-solution000002.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_2_2_3-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_2_2_3-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_4_2_2_3-solution000003.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_2_2_3-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_2_2_3.eprime b/tests/exhaustive/basic/typed01/expected/model_4_2_2_3.eprime deleted file mode 100644 index b84dbce7a7..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_2_2_3.eprime +++ /dev/null @@ -1,26 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -find y_ExplicitVarSizeWithMarker_Marker: int(0..1) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -branching on - [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, - y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithDummy] -such that - x_ExplicitVarSizeWithFlags_Flags[1] /\ - (y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithFlags_Values[1]) - -> false, - x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, - x_ExplicitVarSizeWithDummy[1] != 2 -> - x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithDummy[1], - x_ExplicitVarSizeWithFlags_Flags[1] -> - x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithFlags_Values[1], - 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, - 1 <= y_ExplicitVarSizeWithMarker_Marker -> - y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = y_ExplicitVarSizeWithMarker_Values[1], - y_ExplicitVarSizeWithDummy[1] != 2 -> - 1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = y_ExplicitVarSizeWithDummy[1] - diff --git a/tests/exhaustive/basic/typed01/expected/model_4_2_2_4-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_4_2_2_4-solution000001.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_2_2_4-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_2_2_4-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_4_2_2_4-solution000002.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_2_2_4-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_2_2_4-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_4_2_2_4-solution000003.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_2_2_4-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_2_2_4.eprime b/tests/exhaustive/basic/typed01/expected/model_4_2_2_4.eprime deleted file mode 100644 index 9e0b55a0f7..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_2_2_4.eprime +++ /dev/null @@ -1,26 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -branching on - [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, - y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithDummy] -such that - x_ExplicitVarSizeWithFlags_Flags[1] /\ - (y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithFlags_Values[1]) - -> false, - x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, - x_ExplicitVarSizeWithDummy[1] != 2 -> - x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithDummy[1], - x_ExplicitVarSizeWithFlags_Flags[1] -> - x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithFlags_Values[1], - y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, - y_ExplicitVarSizeWithFlags_Flags[1] -> - y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = y_ExplicitVarSizeWithFlags_Values[1], - y_ExplicitVarSizeWithDummy[1] != 2 -> - y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = y_ExplicitVarSizeWithDummy[1] - diff --git a/tests/exhaustive/basic/typed01/expected/model_4_2_3_1-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_4_2_3_1-solution000001.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_2_3_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_2_3_1-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_4_2_3_1-solution000002.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_2_3_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_2_3_1-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_4_2_3_1-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_2_3_1-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_2_3_1.eprime b/tests/exhaustive/basic/typed01/expected/model_4_2_3_1.eprime deleted file mode 100644 index 6158689ebd..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_2_3_1.eprime +++ /dev/null @@ -1,25 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -find x_ExplicitVarSizeWithMarker_Marker: int(0..1) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -find y_Occurrence: matrix indexed by [int(1)] of bool -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithFlags_Flags, - x_ExplicitVarSizeWithFlags_Values, y_Occurrence, y_ExplicitVarSizeWithDummy] -such that - x_ExplicitVarSizeWithFlags_Flags[1] /\ - (y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithFlags_Values[1]) - -> false, - x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, - 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, - 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithMarker_Values[1], - x_ExplicitVarSizeWithFlags_Flags[1] -> - 1 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithFlags_Values[1], - y_Occurrence[1] -> y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = 1, - y_ExplicitVarSizeWithDummy[1] != 2 -> y_Occurrence[y_ExplicitVarSizeWithDummy[1]] - diff --git a/tests/exhaustive/basic/typed01/expected/model_4_2_3_2-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_4_2_3_2-solution000001.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_2_3_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_2_3_2-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_4_2_3_2-solution000002.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_2_3_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_2_3_2-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_4_2_3_2-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_2_3_2-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_2_3_2.eprime b/tests/exhaustive/basic/typed01/expected/model_4_2_3_2.eprime deleted file mode 100644 index af849df8be..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_2_3_2.eprime +++ /dev/null @@ -1,22 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -find x_ExplicitVarSizeWithMarker_Marker: int(0..1) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithFlags_Flags, - x_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithDummy] -such that - x_ExplicitVarSizeWithFlags_Flags[1] /\ - (y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithFlags_Values[1]) - -> false, - x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, - 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, - 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithMarker_Values[1], - x_ExplicitVarSizeWithFlags_Flags[1] -> - 1 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithFlags_Values[1] - diff --git a/tests/exhaustive/basic/typed01/expected/model_4_2_3_3-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_4_2_3_3-solution000001.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_2_3_3-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_2_3_3-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_4_2_3_3-solution000002.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_2_3_3-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_2_3_3-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_4_2_3_3-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_2_3_3-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_2_3_3.eprime b/tests/exhaustive/basic/typed01/expected/model_4_2_3_3.eprime deleted file mode 100644 index 730f8ef16d..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_2_3_3.eprime +++ /dev/null @@ -1,30 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -find x_ExplicitVarSizeWithMarker_Marker: int(0..1) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -find y_ExplicitVarSizeWithMarker_Marker: int(0..1) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithFlags_Flags, - x_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values, - y_ExplicitVarSizeWithDummy] -such that - x_ExplicitVarSizeWithFlags_Flags[1] /\ - (y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithFlags_Values[1]) - -> false, - x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, - 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, - 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithMarker_Values[1], - x_ExplicitVarSizeWithFlags_Flags[1] -> - 1 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithFlags_Values[1], - 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, - 1 <= y_ExplicitVarSizeWithMarker_Marker -> - y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = y_ExplicitVarSizeWithMarker_Values[1], - y_ExplicitVarSizeWithDummy[1] != 2 -> - 1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = y_ExplicitVarSizeWithDummy[1] - diff --git a/tests/exhaustive/basic/typed01/expected/model_4_2_3_4-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_4_2_3_4-solution000001.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_2_3_4-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_2_3_4-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_4_2_3_4-solution000002.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_2_3_4-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_2_3_4-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_4_2_3_4-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_2_3_4-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_2_3_4.eprime b/tests/exhaustive/basic/typed01/expected/model_4_2_3_4.eprime deleted file mode 100644 index ada2b923a1..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_2_3_4.eprime +++ /dev/null @@ -1,30 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -find x_ExplicitVarSizeWithMarker_Marker: int(0..1) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithFlags_Flags, - x_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values, - y_ExplicitVarSizeWithDummy] -such that - x_ExplicitVarSizeWithFlags_Flags[1] /\ - (y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithFlags_Values[1]) - -> false, - x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, - 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, - 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithMarker_Values[1], - x_ExplicitVarSizeWithFlags_Flags[1] -> - 1 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithFlags_Values[1], - y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, - y_ExplicitVarSizeWithFlags_Flags[1] -> - y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = y_ExplicitVarSizeWithFlags_Values[1], - y_ExplicitVarSizeWithDummy[1] != 2 -> - y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = y_ExplicitVarSizeWithDummy[1] - diff --git a/tests/exhaustive/basic/typed01/expected/model_4_2_4_1-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_4_2_4_1-solution000001.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_2_4_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_2_4_1-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_4_2_4_1-solution000002.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_2_4_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_2_4_1-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_4_2_4_1-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_2_4_1-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_2_4_1.eprime b/tests/exhaustive/basic/typed01/expected/model_4_2_4_1.eprime deleted file mode 100644 index dbc07862de..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_2_4_1.eprime +++ /dev/null @@ -1,16 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -find y_Occurrence: matrix indexed by [int(1)] of bool -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, y_Occurrence, y_ExplicitVarSizeWithDummy] -such that - x_ExplicitVarSizeWithFlags_Flags[1] /\ - (y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithFlags_Values[1]) - -> false, - x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, - y_Occurrence[1] -> y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = 1, - y_ExplicitVarSizeWithDummy[1] != 2 -> y_Occurrence[y_ExplicitVarSizeWithDummy[1]] - diff --git a/tests/exhaustive/basic/typed01/expected/model_4_2_4_2-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_4_2_4_2-solution000001.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_2_4_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_2_4_2-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_4_2_4_2-solution000002.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_2_4_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_2_4_2-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_4_2_4_2-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_2_4_2-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_2_4_2.eprime b/tests/exhaustive/basic/typed01/expected/model_4_2_4_2.eprime deleted file mode 100644 index 9f155130a0..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_2_4_2.eprime +++ /dev/null @@ -1,12 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -branching on [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithDummy] -such that - x_ExplicitVarSizeWithFlags_Flags[1] /\ - (y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithFlags_Values[1]) - -> false, - x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1 - diff --git a/tests/exhaustive/basic/typed01/expected/model_4_2_4_3-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_4_2_4_3-solution000001.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_2_4_3-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_2_4_3-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_4_2_4_3-solution000002.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_2_4_3-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_2_4_3-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_4_2_4_3-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_2_4_3-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_2_4_3.eprime b/tests/exhaustive/basic/typed01/expected/model_4_2_4_3.eprime deleted file mode 100644 index e1180d719b..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_2_4_3.eprime +++ /dev/null @@ -1,21 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -find y_ExplicitVarSizeWithMarker_Marker: int(0..1) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithMarker_Marker, - y_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithDummy] -such that - x_ExplicitVarSizeWithFlags_Flags[1] /\ - (y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithFlags_Values[1]) - -> false, - x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, - 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, - 1 <= y_ExplicitVarSizeWithMarker_Marker -> - y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = y_ExplicitVarSizeWithMarker_Values[1], - y_ExplicitVarSizeWithDummy[1] != 2 -> - 1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = y_ExplicitVarSizeWithDummy[1] - diff --git a/tests/exhaustive/basic/typed01/expected/model_4_2_4_4-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_4_2_4_4-solution000001.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_2_4_4-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_2_4_4-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_4_2_4_4-solution000002.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_2_4_4-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_2_4_4-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_4_2_4_4-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_2_4_4-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_2_4_4.eprime b/tests/exhaustive/basic/typed01/expected/model_4_2_4_4.eprime deleted file mode 100644 index a53eedddb0..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_2_4_4.eprime +++ /dev/null @@ -1,21 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithFlags_Flags, - y_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithDummy] -such that - x_ExplicitVarSizeWithFlags_Flags[1] /\ - (y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithFlags_Values[1]) - -> false, - x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, - y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, - y_ExplicitVarSizeWithFlags_Flags[1] -> - y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = y_ExplicitVarSizeWithFlags_Values[1], - y_ExplicitVarSizeWithDummy[1] != 2 -> - y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = y_ExplicitVarSizeWithDummy[1] - diff --git a/tests/exhaustive/basic/typed01/expected/model_4_3_1_1-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_4_3_1_1-solution000001.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_3_1_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_3_1_1-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_4_3_1_1-solution000002.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_3_1_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_3_1_1-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_4_3_1_1-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_3_1_1-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_3_1_1.eprime b/tests/exhaustive/basic/typed01/expected/model_4_3_1_1.eprime deleted file mode 100644 index dc647fb27d..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_3_1_1.eprime +++ /dev/null @@ -1,23 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -find x_Occurrence: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithMarker_Marker: int(0..1) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -find y_Occurrence: matrix indexed by [int(1)] of bool -branching on - [x_Occurrence, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, y_Occurrence, - y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values] -such that - x_ExplicitVarSizeWithFlags_Flags[1] /\ - (1 <= y_ExplicitVarSizeWithMarker_Marker /\ - y_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithFlags_Values[1]) - -> false, - x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, - 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, - x_Occurrence[1] -> x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = 1, - x_ExplicitVarSizeWithFlags_Flags[1] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[1]], - y_Occurrence[1] -> 1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = 1, - 1 <= y_ExplicitVarSizeWithMarker_Marker -> y_Occurrence[y_ExplicitVarSizeWithMarker_Values[1]] - diff --git a/tests/exhaustive/basic/typed01/expected/model_4_3_1_2-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_4_3_1_2-solution000001.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_3_1_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_3_1_2-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_4_3_1_2-solution000002.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_3_1_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_3_1_2-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_4_3_1_2-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_3_1_2-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_3_1_2.eprime b/tests/exhaustive/basic/typed01/expected/model_4_3_1_2.eprime deleted file mode 100644 index 4ec2675a1c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_3_1_2.eprime +++ /dev/null @@ -1,25 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -find x_Occurrence: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithMarker_Marker: int(0..1) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -branching on - [x_Occurrence, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithDummy, - y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values] -such that - x_ExplicitVarSizeWithFlags_Flags[1] /\ - (1 <= y_ExplicitVarSizeWithMarker_Marker /\ - y_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithFlags_Values[1]) - -> false, - x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, - 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, - x_Occurrence[1] -> x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = 1, - x_ExplicitVarSizeWithFlags_Flags[1] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[1]], - y_ExplicitVarSizeWithDummy[1] != 2 -> - 1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = y_ExplicitVarSizeWithDummy[1], - 1 <= y_ExplicitVarSizeWithMarker_Marker -> - y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = y_ExplicitVarSizeWithMarker_Values[1] - diff --git a/tests/exhaustive/basic/typed01/expected/model_4_3_1_3-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_4_3_1_3-solution000001.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_3_1_3-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_3_1_3-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_4_3_1_3-solution000002.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_3_1_3-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_3_1_3-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_4_3_1_3-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_3_1_3-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_3_1_3.eprime b/tests/exhaustive/basic/typed01/expected/model_4_3_1_3.eprime deleted file mode 100644 index 32cfd157ad..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_3_1_3.eprime +++ /dev/null @@ -1,20 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -find x_Occurrence: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithMarker_Marker: int(0..1) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -branching on - [x_Occurrence, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, - y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values] -such that - x_ExplicitVarSizeWithFlags_Flags[1] /\ - (1 <= y_ExplicitVarSizeWithMarker_Marker /\ - y_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithFlags_Values[1]) - -> false, - x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, - 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, - x_Occurrence[1] -> x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = 1, - x_ExplicitVarSizeWithFlags_Flags[1] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[1]] - diff --git a/tests/exhaustive/basic/typed01/expected/model_4_3_1_4-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_4_3_1_4-solution000001.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_3_1_4-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_3_1_4-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_4_3_1_4-solution000002.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_3_1_4-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_3_1_4-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_4_3_1_4-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_3_1_4-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_3_1_4.eprime b/tests/exhaustive/basic/typed01/expected/model_4_3_1_4.eprime deleted file mode 100644 index 27811841d5..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_3_1_4.eprime +++ /dev/null @@ -1,29 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -find x_Occurrence: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithMarker_Marker: int(0..1) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -branching on - [x_Occurrence, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, - y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithMarker_Marker, - y_ExplicitVarSizeWithMarker_Values] -such that - x_ExplicitVarSizeWithFlags_Flags[1] /\ - (1 <= y_ExplicitVarSizeWithMarker_Marker /\ - y_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithFlags_Values[1]) - -> false, - x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, - 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, - x_Occurrence[1] -> x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = 1, - x_ExplicitVarSizeWithFlags_Flags[1] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[1]], - y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, - y_ExplicitVarSizeWithFlags_Flags[1] -> - 1 <= y_ExplicitVarSizeWithMarker_Marker /\ - y_ExplicitVarSizeWithMarker_Values[1] = y_ExplicitVarSizeWithFlags_Values[1], - 1 <= y_ExplicitVarSizeWithMarker_Marker -> - y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = y_ExplicitVarSizeWithMarker_Values[1] - diff --git a/tests/exhaustive/basic/typed01/expected/model_4_3_2_1-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_4_3_2_1-solution000001.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_3_2_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_3_2_1-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_4_3_2_1-solution000002.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_3_2_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_3_2_1-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_4_3_2_1-solution000003.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_3_2_1-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_3_2_1.eprime b/tests/exhaustive/basic/typed01/expected/model_4_3_2_1.eprime deleted file mode 100644 index 14d92f563c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_3_2_1.eprime +++ /dev/null @@ -1,25 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -find y_ExplicitVarSizeWithMarker_Marker: int(0..1) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -find y_Occurrence: matrix indexed by [int(1)] of bool -branching on - [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, y_Occurrence, - y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values] -such that - x_ExplicitVarSizeWithFlags_Flags[1] /\ - (1 <= y_ExplicitVarSizeWithMarker_Marker /\ - y_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithFlags_Values[1]) - -> false, - x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, - 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, - x_ExplicitVarSizeWithDummy[1] != 2 -> - x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithDummy[1], - x_ExplicitVarSizeWithFlags_Flags[1] -> - x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithFlags_Values[1], - y_Occurrence[1] -> 1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = 1, - 1 <= y_ExplicitVarSizeWithMarker_Marker -> y_Occurrence[y_ExplicitVarSizeWithMarker_Values[1]] - diff --git a/tests/exhaustive/basic/typed01/expected/model_4_3_2_2-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_4_3_2_2-solution000001.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_3_2_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_3_2_2-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_4_3_2_2-solution000002.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_3_2_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_3_2_2-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_4_3_2_2-solution000003.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_3_2_2-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_3_2_2.eprime b/tests/exhaustive/basic/typed01/expected/model_4_3_2_2.eprime deleted file mode 100644 index 5d58c6fa0d..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_3_2_2.eprime +++ /dev/null @@ -1,27 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -find y_ExplicitVarSizeWithMarker_Marker: int(0..1) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -branching on - [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, - y_ExplicitVarSizeWithDummy, y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values] -such that - x_ExplicitVarSizeWithFlags_Flags[1] /\ - (1 <= y_ExplicitVarSizeWithMarker_Marker /\ - y_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithFlags_Values[1]) - -> false, - x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, - 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, - x_ExplicitVarSizeWithDummy[1] != 2 -> - x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithDummy[1], - x_ExplicitVarSizeWithFlags_Flags[1] -> - x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithFlags_Values[1], - y_ExplicitVarSizeWithDummy[1] != 2 -> - 1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = y_ExplicitVarSizeWithDummy[1], - 1 <= y_ExplicitVarSizeWithMarker_Marker -> - y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = y_ExplicitVarSizeWithMarker_Values[1] - diff --git a/tests/exhaustive/basic/typed01/expected/model_4_3_2_3-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_4_3_2_3-solution000001.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_3_2_3-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_3_2_3-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_4_3_2_3-solution000002.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_3_2_3-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_3_2_3-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_4_3_2_3-solution000003.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_3_2_3-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_3_2_3.eprime b/tests/exhaustive/basic/typed01/expected/model_4_3_2_3.eprime deleted file mode 100644 index 907a46b538..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_3_2_3.eprime +++ /dev/null @@ -1,22 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -find y_ExplicitVarSizeWithMarker_Marker: int(0..1) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -branching on - [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, - y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values] -such that - x_ExplicitVarSizeWithFlags_Flags[1] /\ - (1 <= y_ExplicitVarSizeWithMarker_Marker /\ - y_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithFlags_Values[1]) - -> false, - x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, - 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, - x_ExplicitVarSizeWithDummy[1] != 2 -> - x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithDummy[1], - x_ExplicitVarSizeWithFlags_Flags[1] -> - x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithFlags_Values[1] - diff --git a/tests/exhaustive/basic/typed01/expected/model_4_3_2_4-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_4_3_2_4-solution000001.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_3_2_4-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_3_2_4-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_4_3_2_4-solution000002.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_3_2_4-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_3_2_4-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_4_3_2_4-solution000003.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_3_2_4-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_3_2_4.eprime b/tests/exhaustive/basic/typed01/expected/model_4_3_2_4.eprime deleted file mode 100644 index c6f53b014c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_3_2_4.eprime +++ /dev/null @@ -1,31 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -find y_ExplicitVarSizeWithMarker_Marker: int(0..1) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -branching on - [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, - y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithMarker_Marker, - y_ExplicitVarSizeWithMarker_Values] -such that - x_ExplicitVarSizeWithFlags_Flags[1] /\ - (1 <= y_ExplicitVarSizeWithMarker_Marker /\ - y_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithFlags_Values[1]) - -> false, - x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, - 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, - x_ExplicitVarSizeWithDummy[1] != 2 -> - x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithDummy[1], - x_ExplicitVarSizeWithFlags_Flags[1] -> - x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithFlags_Values[1], - y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, - y_ExplicitVarSizeWithFlags_Flags[1] -> - 1 <= y_ExplicitVarSizeWithMarker_Marker /\ - y_ExplicitVarSizeWithMarker_Values[1] = y_ExplicitVarSizeWithFlags_Values[1], - 1 <= y_ExplicitVarSizeWithMarker_Marker -> - y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = y_ExplicitVarSizeWithMarker_Values[1] - diff --git a/tests/exhaustive/basic/typed01/expected/model_4_3_3_1-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_4_3_3_1-solution000001.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_3_3_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_3_3_1-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_4_3_3_1-solution000002.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_3_3_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_3_3_1-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_4_3_3_1-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_3_3_1-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_3_3_1.eprime b/tests/exhaustive/basic/typed01/expected/model_4_3_3_1.eprime deleted file mode 100644 index 58d00ad5ee..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_3_3_1.eprime +++ /dev/null @@ -1,29 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -find x_ExplicitVarSizeWithMarker_Marker: int(0..1) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -find y_ExplicitVarSizeWithMarker_Marker: int(0..1) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -find y_Occurrence: matrix indexed by [int(1)] of bool -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithFlags_Flags, - x_ExplicitVarSizeWithFlags_Values, y_Occurrence, y_ExplicitVarSizeWithMarker_Marker, - y_ExplicitVarSizeWithMarker_Values] -such that - x_ExplicitVarSizeWithFlags_Flags[1] /\ - (1 <= y_ExplicitVarSizeWithMarker_Marker /\ - y_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithFlags_Values[1]) - -> false, - x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, - 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, - 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, - 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithMarker_Values[1], - x_ExplicitVarSizeWithFlags_Flags[1] -> - 1 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithFlags_Values[1], - y_Occurrence[1] -> 1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = 1, - 1 <= y_ExplicitVarSizeWithMarker_Marker -> y_Occurrence[y_ExplicitVarSizeWithMarker_Values[1]] - diff --git a/tests/exhaustive/basic/typed01/expected/model_4_3_3_2-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_4_3_3_2-solution000001.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_3_3_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_3_3_2-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_4_3_3_2-solution000002.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_3_3_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_3_3_2-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_4_3_3_2-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_3_3_2-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_3_3_2.eprime b/tests/exhaustive/basic/typed01/expected/model_4_3_3_2.eprime deleted file mode 100644 index bb5e3f245d..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_3_3_2.eprime +++ /dev/null @@ -1,31 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -find x_ExplicitVarSizeWithMarker_Marker: int(0..1) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -find y_ExplicitVarSizeWithMarker_Marker: int(0..1) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithFlags_Flags, - x_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithDummy, y_ExplicitVarSizeWithMarker_Marker, - y_ExplicitVarSizeWithMarker_Values] -such that - x_ExplicitVarSizeWithFlags_Flags[1] /\ - (1 <= y_ExplicitVarSizeWithMarker_Marker /\ - y_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithFlags_Values[1]) - -> false, - x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, - 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, - 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, - 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithMarker_Values[1], - x_ExplicitVarSizeWithFlags_Flags[1] -> - 1 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithFlags_Values[1], - y_ExplicitVarSizeWithDummy[1] != 2 -> - 1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = y_ExplicitVarSizeWithDummy[1], - 1 <= y_ExplicitVarSizeWithMarker_Marker -> - y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = y_ExplicitVarSizeWithMarker_Values[1] - diff --git a/tests/exhaustive/basic/typed01/expected/model_4_3_3_3-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_4_3_3_3-solution000001.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_3_3_3-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_3_3_3-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_4_3_3_3-solution000002.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_3_3_3-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_3_3_3-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_4_3_3_3-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_3_3_3-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_3_3_3.eprime b/tests/exhaustive/basic/typed01/expected/model_4_3_3_3.eprime deleted file mode 100644 index 0943a035ed..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_3_3_3.eprime +++ /dev/null @@ -1,25 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -find x_ExplicitVarSizeWithMarker_Marker: int(0..1) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -find y_ExplicitVarSizeWithMarker_Marker: int(0..1) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithFlags_Flags, - x_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values] -such that - x_ExplicitVarSizeWithFlags_Flags[1] /\ - (1 <= y_ExplicitVarSizeWithMarker_Marker /\ - y_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithFlags_Values[1]) - -> false, - x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, - 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, - 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, - 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithMarker_Values[1], - x_ExplicitVarSizeWithFlags_Flags[1] -> - 1 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithFlags_Values[1] - diff --git a/tests/exhaustive/basic/typed01/expected/model_4_3_3_4-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_4_3_3_4-solution000001.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_3_3_4-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_3_3_4-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_4_3_3_4-solution000002.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_3_3_4-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_3_3_4-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_4_3_3_4-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_3_3_4-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_3_3_4.eprime b/tests/exhaustive/basic/typed01/expected/model_4_3_3_4.eprime deleted file mode 100644 index 14ce80e263..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_3_3_4.eprime +++ /dev/null @@ -1,34 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -find x_ExplicitVarSizeWithMarker_Marker: int(0..1) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -find y_ExplicitVarSizeWithMarker_Marker: int(0..1) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithFlags_Flags, - x_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values, - y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values] -such that - x_ExplicitVarSizeWithFlags_Flags[1] /\ - (1 <= y_ExplicitVarSizeWithMarker_Marker /\ - y_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithFlags_Values[1]) - -> false, - x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, - 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, - 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, - 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithMarker_Values[1], - x_ExplicitVarSizeWithFlags_Flags[1] -> - 1 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithFlags_Values[1], - y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, - y_ExplicitVarSizeWithFlags_Flags[1] -> - 1 <= y_ExplicitVarSizeWithMarker_Marker /\ - y_ExplicitVarSizeWithMarker_Values[1] = y_ExplicitVarSizeWithFlags_Values[1], - 1 <= y_ExplicitVarSizeWithMarker_Marker -> - y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = y_ExplicitVarSizeWithMarker_Values[1] - diff --git a/tests/exhaustive/basic/typed01/expected/model_4_3_4_1-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_4_3_4_1-solution000001.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_3_4_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_3_4_1-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_4_3_4_1-solution000002.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_3_4_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_3_4_1-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_4_3_4_1-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_3_4_1-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_3_4_1.eprime b/tests/exhaustive/basic/typed01/expected/model_4_3_4_1.eprime deleted file mode 100644 index c2e457ed45..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_3_4_1.eprime +++ /dev/null @@ -1,20 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -find y_ExplicitVarSizeWithMarker_Marker: int(0..1) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -find y_Occurrence: matrix indexed by [int(1)] of bool -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, y_Occurrence, - y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values] -such that - x_ExplicitVarSizeWithFlags_Flags[1] /\ - (1 <= y_ExplicitVarSizeWithMarker_Marker /\ - y_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithFlags_Values[1]) - -> false, - x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, - 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, - y_Occurrence[1] -> 1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = 1, - 1 <= y_ExplicitVarSizeWithMarker_Marker -> y_Occurrence[y_ExplicitVarSizeWithMarker_Values[1]] - diff --git a/tests/exhaustive/basic/typed01/expected/model_4_3_4_2-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_4_3_4_2-solution000001.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_3_4_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_3_4_2-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_4_3_4_2-solution000002.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_3_4_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_3_4_2-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_4_3_4_2-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_3_4_2-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_3_4_2.eprime b/tests/exhaustive/basic/typed01/expected/model_4_3_4_2.eprime deleted file mode 100644 index 942d4718ca..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_3_4_2.eprime +++ /dev/null @@ -1,22 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -find y_ExplicitVarSizeWithMarker_Marker: int(0..1) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithDummy, - y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values] -such that - x_ExplicitVarSizeWithFlags_Flags[1] /\ - (1 <= y_ExplicitVarSizeWithMarker_Marker /\ - y_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithFlags_Values[1]) - -> false, - x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, - 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, - y_ExplicitVarSizeWithDummy[1] != 2 -> - 1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = y_ExplicitVarSizeWithDummy[1], - 1 <= y_ExplicitVarSizeWithMarker_Marker -> - y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = y_ExplicitVarSizeWithMarker_Values[1] - diff --git a/tests/exhaustive/basic/typed01/expected/model_4_3_4_3-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_4_3_4_3-solution000001.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_3_4_3-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_3_4_3-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_4_3_4_3-solution000002.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_3_4_3-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_3_4_3-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_4_3_4_3-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_3_4_3-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_3_4_3.eprime b/tests/exhaustive/basic/typed01/expected/model_4_3_4_3.eprime deleted file mode 100644 index 9d46ed4c1c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_3_4_3.eprime +++ /dev/null @@ -1,17 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -find y_ExplicitVarSizeWithMarker_Marker: int(0..1) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithMarker_Marker, - y_ExplicitVarSizeWithMarker_Values] -such that - x_ExplicitVarSizeWithFlags_Flags[1] /\ - (1 <= y_ExplicitVarSizeWithMarker_Marker /\ - y_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithFlags_Values[1]) - -> false, - x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, - 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1 - diff --git a/tests/exhaustive/basic/typed01/expected/model_4_3_4_4-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_4_3_4_4-solution000001.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_3_4_4-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_3_4_4-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_4_3_4_4-solution000002.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_3_4_4-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_3_4_4-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_4_3_4_4-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_3_4_4-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_3_4_4.eprime b/tests/exhaustive/basic/typed01/expected/model_4_3_4_4.eprime deleted file mode 100644 index fd5e21a212..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_3_4_4.eprime +++ /dev/null @@ -1,25 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -find y_ExplicitVarSizeWithMarker_Marker: int(0..1) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithFlags_Flags, - y_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values] -such that - x_ExplicitVarSizeWithFlags_Flags[1] /\ - (1 <= y_ExplicitVarSizeWithMarker_Marker /\ - y_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithFlags_Values[1]) - -> false, - x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, - 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, - y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, - y_ExplicitVarSizeWithFlags_Flags[1] -> - 1 <= y_ExplicitVarSizeWithMarker_Marker /\ - y_ExplicitVarSizeWithMarker_Values[1] = y_ExplicitVarSizeWithFlags_Values[1], - 1 <= y_ExplicitVarSizeWithMarker_Marker -> - y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = y_ExplicitVarSizeWithMarker_Values[1] - diff --git a/tests/exhaustive/basic/typed01/expected/model_4_4_1_1-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_4_4_1_1-solution000001.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_4_1_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_4_1_1-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_4_4_1_1-solution000002.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_4_1_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_4_1_1-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_4_4_1_1-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_4_1_1-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_4_1_1.eprime b/tests/exhaustive/basic/typed01/expected/model_4_4_1_1.eprime deleted file mode 100644 index fac7863f69..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_4_1_1.eprime +++ /dev/null @@ -1,22 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -find x_Occurrence: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -find y_Occurrence: matrix indexed by [int(1)] of bool -branching on - [x_Occurrence, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, y_Occurrence, - y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values] -such that - x_ExplicitVarSizeWithFlags_Flags[1] /\ - (y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithFlags_Values[1]) - -> false, - x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, - y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, - x_Occurrence[1] -> x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = 1, - x_ExplicitVarSizeWithFlags_Flags[1] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[1]], - y_Occurrence[1] -> y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = 1, - y_ExplicitVarSizeWithFlags_Flags[1] -> y_Occurrence[y_ExplicitVarSizeWithFlags_Values[1]] - diff --git a/tests/exhaustive/basic/typed01/expected/model_4_4_1_2-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_4_4_1_2-solution000001.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_4_1_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_4_1_2-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_4_4_1_2-solution000002.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_4_1_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_4_1_2-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_4_4_1_2-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_4_1_2-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_4_1_2.eprime b/tests/exhaustive/basic/typed01/expected/model_4_4_1_2.eprime deleted file mode 100644 index 4bf7e90c1b..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_4_1_2.eprime +++ /dev/null @@ -1,24 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -find x_Occurrence: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -branching on - [x_Occurrence, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithDummy, - y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values] -such that - x_ExplicitVarSizeWithFlags_Flags[1] /\ - (y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithFlags_Values[1]) - -> false, - x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, - y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, - x_Occurrence[1] -> x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = 1, - x_ExplicitVarSizeWithFlags_Flags[1] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[1]], - y_ExplicitVarSizeWithDummy[1] != 2 -> - y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = y_ExplicitVarSizeWithDummy[1], - y_ExplicitVarSizeWithFlags_Flags[1] -> - y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = y_ExplicitVarSizeWithFlags_Values[1] - diff --git a/tests/exhaustive/basic/typed01/expected/model_4_4_1_3-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_4_4_1_3-solution000001.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_4_1_3-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_4_1_3-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_4_4_1_3-solution000002.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_4_1_3-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_4_1_3-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_4_4_1_3-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_4_1_3-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_4_1_3.eprime b/tests/exhaustive/basic/typed01/expected/model_4_4_1_3.eprime deleted file mode 100644 index 22da5be87d..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_4_1_3.eprime +++ /dev/null @@ -1,28 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -find x_Occurrence: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -find y_ExplicitVarSizeWithMarker_Marker: int(0..1) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -branching on - [x_Occurrence, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, - y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithFlags_Flags, - y_ExplicitVarSizeWithFlags_Values] -such that - x_ExplicitVarSizeWithFlags_Flags[1] /\ - (y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithFlags_Values[1]) - -> false, - x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, - y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, - x_Occurrence[1] -> x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = 1, - x_ExplicitVarSizeWithFlags_Flags[1] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[1]], - 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, - 1 <= y_ExplicitVarSizeWithMarker_Marker -> - y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = y_ExplicitVarSizeWithMarker_Values[1], - y_ExplicitVarSizeWithFlags_Flags[1] -> - 1 <= y_ExplicitVarSizeWithMarker_Marker /\ - y_ExplicitVarSizeWithMarker_Values[1] = y_ExplicitVarSizeWithFlags_Values[1] - diff --git a/tests/exhaustive/basic/typed01/expected/model_4_4_1_4-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_4_4_1_4-solution000001.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_4_1_4-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_4_1_4-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_4_4_1_4-solution000002.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_4_1_4-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_4_1_4-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_4_4_1_4-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_4_1_4-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_4_1_4.eprime b/tests/exhaustive/basic/typed01/expected/model_4_4_1_4.eprime deleted file mode 100644 index d10bd485ff..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_4_1_4.eprime +++ /dev/null @@ -1,19 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -find x_Occurrence: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -branching on - [x_Occurrence, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, - y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values] -such that - x_ExplicitVarSizeWithFlags_Flags[1] /\ - (y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithFlags_Values[1]) - -> false, - x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, - y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, - x_Occurrence[1] -> x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = 1, - x_ExplicitVarSizeWithFlags_Flags[1] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[1]] - diff --git a/tests/exhaustive/basic/typed01/expected/model_4_4_2_1-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_4_4_2_1-solution000001.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_4_2_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_4_2_1-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_4_4_2_1-solution000002.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_4_2_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_4_2_1-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_4_4_2_1-solution000003.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_4_2_1-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_4_2_1.eprime b/tests/exhaustive/basic/typed01/expected/model_4_4_2_1.eprime deleted file mode 100644 index 15f0335802..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_4_2_1.eprime +++ /dev/null @@ -1,24 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -find y_Occurrence: matrix indexed by [int(1)] of bool -branching on - [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, y_Occurrence, - y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values] -such that - x_ExplicitVarSizeWithFlags_Flags[1] /\ - (y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithFlags_Values[1]) - -> false, - x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, - y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, - x_ExplicitVarSizeWithDummy[1] != 2 -> - x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithDummy[1], - x_ExplicitVarSizeWithFlags_Flags[1] -> - x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithFlags_Values[1], - y_Occurrence[1] -> y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = 1, - y_ExplicitVarSizeWithFlags_Flags[1] -> y_Occurrence[y_ExplicitVarSizeWithFlags_Values[1]] - diff --git a/tests/exhaustive/basic/typed01/expected/model_4_4_2_2-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_4_4_2_2-solution000001.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_4_2_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_4_2_2-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_4_4_2_2-solution000002.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_4_2_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_4_2_2-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_4_4_2_2-solution000003.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_4_2_2-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_4_2_2.eprime b/tests/exhaustive/basic/typed01/expected/model_4_4_2_2.eprime deleted file mode 100644 index 58f520e750..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_4_2_2.eprime +++ /dev/null @@ -1,26 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -branching on - [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, - y_ExplicitVarSizeWithDummy, y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values] -such that - x_ExplicitVarSizeWithFlags_Flags[1] /\ - (y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithFlags_Values[1]) - -> false, - x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, - y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, - x_ExplicitVarSizeWithDummy[1] != 2 -> - x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithDummy[1], - x_ExplicitVarSizeWithFlags_Flags[1] -> - x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithFlags_Values[1], - y_ExplicitVarSizeWithDummy[1] != 2 -> - y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = y_ExplicitVarSizeWithDummy[1], - y_ExplicitVarSizeWithFlags_Flags[1] -> - y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = y_ExplicitVarSizeWithFlags_Values[1] - diff --git a/tests/exhaustive/basic/typed01/expected/model_4_4_2_3-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_4_4_2_3-solution000001.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_4_2_3-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_4_2_3-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_4_4_2_3-solution000002.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_4_2_3-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_4_2_3-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_4_4_2_3-solution000003.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_4_2_3-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_4_2_3.eprime b/tests/exhaustive/basic/typed01/expected/model_4_4_2_3.eprime deleted file mode 100644 index d112babb4a..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_4_2_3.eprime +++ /dev/null @@ -1,30 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -find y_ExplicitVarSizeWithMarker_Marker: int(0..1) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -branching on - [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, - y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithFlags_Flags, - y_ExplicitVarSizeWithFlags_Values] -such that - x_ExplicitVarSizeWithFlags_Flags[1] /\ - (y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithFlags_Values[1]) - -> false, - x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, - y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, - x_ExplicitVarSizeWithDummy[1] != 2 -> - x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithDummy[1], - x_ExplicitVarSizeWithFlags_Flags[1] -> - x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithFlags_Values[1], - 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, - 1 <= y_ExplicitVarSizeWithMarker_Marker -> - y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = y_ExplicitVarSizeWithMarker_Values[1], - y_ExplicitVarSizeWithFlags_Flags[1] -> - 1 <= y_ExplicitVarSizeWithMarker_Marker /\ - y_ExplicitVarSizeWithMarker_Values[1] = y_ExplicitVarSizeWithFlags_Values[1] - diff --git a/tests/exhaustive/basic/typed01/expected/model_4_4_2_4-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_4_4_2_4-solution000001.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_4_2_4-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_4_2_4-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_4_4_2_4-solution000002.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_4_2_4-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_4_2_4-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_4_4_2_4-solution000003.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_4_2_4-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_4_2_4.eprime b/tests/exhaustive/basic/typed01/expected/model_4_4_2_4.eprime deleted file mode 100644 index b99521dc71..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_4_2_4.eprime +++ /dev/null @@ -1,21 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -branching on - [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, - y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values] -such that - x_ExplicitVarSizeWithFlags_Flags[1] /\ - (y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithFlags_Values[1]) - -> false, - x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, - y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, - x_ExplicitVarSizeWithDummy[1] != 2 -> - x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithDummy[1], - x_ExplicitVarSizeWithFlags_Flags[1] -> - x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithFlags_Values[1] - diff --git a/tests/exhaustive/basic/typed01/expected/model_4_4_3_1-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_4_4_3_1-solution000001.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_4_3_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_4_3_1-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_4_4_3_1-solution000002.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_4_3_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_4_3_1-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_4_4_3_1-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_4_3_1-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_4_3_1.eprime b/tests/exhaustive/basic/typed01/expected/model_4_4_3_1.eprime deleted file mode 100644 index 618af31d11..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_4_3_1.eprime +++ /dev/null @@ -1,28 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -find x_ExplicitVarSizeWithMarker_Marker: int(0..1) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -find y_Occurrence: matrix indexed by [int(1)] of bool -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithFlags_Flags, - x_ExplicitVarSizeWithFlags_Values, y_Occurrence, y_ExplicitVarSizeWithFlags_Flags, - y_ExplicitVarSizeWithFlags_Values] -such that - x_ExplicitVarSizeWithFlags_Flags[1] /\ - (y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithFlags_Values[1]) - -> false, - x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, - y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, - 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, - 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithMarker_Values[1], - x_ExplicitVarSizeWithFlags_Flags[1] -> - 1 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithFlags_Values[1], - y_Occurrence[1] -> y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = 1, - y_ExplicitVarSizeWithFlags_Flags[1] -> y_Occurrence[y_ExplicitVarSizeWithFlags_Values[1]] - diff --git a/tests/exhaustive/basic/typed01/expected/model_4_4_3_2-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_4_4_3_2-solution000001.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_4_3_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_4_3_2-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_4_4_3_2-solution000002.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_4_3_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_4_3_2-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_4_4_3_2-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_4_3_2-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_4_3_2.eprime b/tests/exhaustive/basic/typed01/expected/model_4_4_3_2.eprime deleted file mode 100644 index 9e776b20fa..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_4_3_2.eprime +++ /dev/null @@ -1,30 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -find x_ExplicitVarSizeWithMarker_Marker: int(0..1) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithFlags_Flags, - x_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithDummy, y_ExplicitVarSizeWithFlags_Flags, - y_ExplicitVarSizeWithFlags_Values] -such that - x_ExplicitVarSizeWithFlags_Flags[1] /\ - (y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithFlags_Values[1]) - -> false, - x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, - y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, - 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, - 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithMarker_Values[1], - x_ExplicitVarSizeWithFlags_Flags[1] -> - 1 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithFlags_Values[1], - y_ExplicitVarSizeWithDummy[1] != 2 -> - y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = y_ExplicitVarSizeWithDummy[1], - y_ExplicitVarSizeWithFlags_Flags[1] -> - y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = y_ExplicitVarSizeWithFlags_Values[1] - diff --git a/tests/exhaustive/basic/typed01/expected/model_4_4_3_3-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_4_4_3_3-solution000001.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_4_3_3-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_4_3_3-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_4_4_3_3-solution000002.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_4_3_3-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_4_3_3-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_4_4_3_3-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_4_3_3-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_4_3_3.eprime b/tests/exhaustive/basic/typed01/expected/model_4_4_3_3.eprime deleted file mode 100644 index ed2298ccfb..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_4_3_3.eprime +++ /dev/null @@ -1,33 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -find x_ExplicitVarSizeWithMarker_Marker: int(0..1) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -find y_ExplicitVarSizeWithMarker_Marker: int(0..1) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithFlags_Flags, - x_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values, - y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values] -such that - x_ExplicitVarSizeWithFlags_Flags[1] /\ - (y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithFlags_Values[1]) - -> false, - x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, - y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, - 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, - 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithMarker_Values[1], - x_ExplicitVarSizeWithFlags_Flags[1] -> - 1 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithFlags_Values[1], - 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, - 1 <= y_ExplicitVarSizeWithMarker_Marker -> - y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = y_ExplicitVarSizeWithMarker_Values[1], - y_ExplicitVarSizeWithFlags_Flags[1] -> - 1 <= y_ExplicitVarSizeWithMarker_Marker /\ - y_ExplicitVarSizeWithMarker_Values[1] = y_ExplicitVarSizeWithFlags_Values[1] - diff --git a/tests/exhaustive/basic/typed01/expected/model_4_4_3_4-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_4_4_3_4-solution000001.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_4_3_4-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_4_3_4-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_4_4_3_4-solution000002.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_4_3_4-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_4_3_4-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_4_4_3_4-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_4_3_4-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_4_3_4.eprime b/tests/exhaustive/basic/typed01/expected/model_4_4_3_4.eprime deleted file mode 100644 index 8250b9e599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_4_3_4.eprime +++ /dev/null @@ -1,24 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -find x_ExplicitVarSizeWithMarker_Marker: int(0..1) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithFlags_Flags, - x_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values] -such that - x_ExplicitVarSizeWithFlags_Flags[1] /\ - (y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithFlags_Values[1]) - -> false, - x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, - y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, - 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, - 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithMarker_Values[1], - x_ExplicitVarSizeWithFlags_Flags[1] -> - 1 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithFlags_Values[1] - diff --git a/tests/exhaustive/basic/typed01/expected/model_4_4_4_1-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_4_4_4_1-solution000001.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_4_4_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_4_4_1-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_4_4_4_1-solution000002.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_4_4_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_4_4_1-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_4_4_4_1-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_4_4_1-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_4_4_1.eprime b/tests/exhaustive/basic/typed01/expected/model_4_4_4_1.eprime deleted file mode 100644 index dad4584015..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_4_4_1.eprime +++ /dev/null @@ -1,19 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -find y_Occurrence: matrix indexed by [int(1)] of bool -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, y_Occurrence, - y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values] -such that - x_ExplicitVarSizeWithFlags_Flags[1] /\ - (y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithFlags_Values[1]) - -> false, - x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, - y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, - y_Occurrence[1] -> y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = 1, - y_ExplicitVarSizeWithFlags_Flags[1] -> y_Occurrence[y_ExplicitVarSizeWithFlags_Values[1]] - diff --git a/tests/exhaustive/basic/typed01/expected/model_4_4_4_2-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_4_4_4_2-solution000001.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_4_4_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_4_4_2-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_4_4_4_2-solution000002.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_4_4_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_4_4_2-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_4_4_4_2-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_4_4_2-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_4_4_2.eprime b/tests/exhaustive/basic/typed01/expected/model_4_4_4_2.eprime deleted file mode 100644 index e1adf983e5..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_4_4_2.eprime +++ /dev/null @@ -1,21 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithDummy, - y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values] -such that - x_ExplicitVarSizeWithFlags_Flags[1] /\ - (y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithFlags_Values[1]) - -> false, - x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, - y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, - y_ExplicitVarSizeWithDummy[1] != 2 -> - y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = y_ExplicitVarSizeWithDummy[1], - y_ExplicitVarSizeWithFlags_Flags[1] -> - y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = y_ExplicitVarSizeWithFlags_Values[1] - diff --git a/tests/exhaustive/basic/typed01/expected/model_4_4_4_3-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_4_4_4_3-solution000001.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_4_4_3-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_4_4_3-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_4_4_4_3-solution000002.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_4_4_3-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_4_4_3-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_4_4_4_3-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_4_4_3-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_4_4_3.eprime b/tests/exhaustive/basic/typed01/expected/model_4_4_4_3.eprime deleted file mode 100644 index 6456aac8f4..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_4_4_3.eprime +++ /dev/null @@ -1,24 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -find y_ExplicitVarSizeWithMarker_Marker: int(0..1) -find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithMarker_Marker, - y_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values] -such that - x_ExplicitVarSizeWithFlags_Flags[1] /\ - (y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithFlags_Values[1]) - -> false, - x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, - y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, - 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, - 1 <= y_ExplicitVarSizeWithMarker_Marker -> - y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = y_ExplicitVarSizeWithMarker_Values[1], - y_ExplicitVarSizeWithFlags_Flags[1] -> - 1 <= y_ExplicitVarSizeWithMarker_Marker /\ - y_ExplicitVarSizeWithMarker_Values[1] = y_ExplicitVarSizeWithFlags_Values[1] - diff --git a/tests/exhaustive/basic/typed01/expected/model_4_4_4_4-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_4_4_4_4-solution000001.solution deleted file mode 100644 index a30dffc20c..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_4_4_4-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_4_4_4-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_4_4_4_4-solution000002.solution deleted file mode 100644 index 9b282fd599..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_4_4_4-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {} -letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_4_4_4-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_4_4_4_4-solution000003.solution deleted file mode 100644 index 8437ede4ce..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_4_4_4-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting x be {1} -letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_4_4_4.eprime b/tests/exhaustive/basic/typed01/expected/model_4_4_4_4.eprime deleted file mode 100644 index 137067773d..0000000000 --- a/tests/exhaustive/basic/typed01/expected/model_4_4_4_4.eprime +++ /dev/null @@ -1,16 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool -find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithFlags_Flags, - y_ExplicitVarSizeWithFlags_Values] -such that - x_ExplicitVarSizeWithFlags_Flags[1] /\ - (y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithFlags_Values[1]) - -> false, - x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, - y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1 - diff --git a/tests/exhaustive/issues/102/expected/model-solution000001.solution b/tests/exhaustive/issues/102/expected/model-solution000001.solution deleted file mode 100644 index f632708ff2..0000000000 --- a/tests/exhaustive/issues/102/expected/model-solution000001.solution +++ /dev/null @@ -1,28 +0,0 @@ -language Essence 1.3 - -letting actions be sequence((8, 5, 5), (5, 3, 3), (3, 8, 3), (5, 3, 2), (8, 5, 5), (5, 3, 1), (3, 8, 3)) -$ Visualisation for actions -$ 8 5 5 -$ 5 3 3 -$ 3 8 3 -$ 5 3 2 -$ 8 5 5 -$ 5 3 1 -$ 3 8 3 - -letting nbActions be 7 -letting states be - sequence(function(3 --> 0, 5 --> 0, 8 --> 8), function(3 --> 0, 5 --> 5, 8 --> 3), - function(3 --> 3, 5 --> 2, 8 --> 3), function(3 --> 0, 5 --> 2, 8 --> 6), - function(3 --> 2, 5 --> 0, 8 --> 6), function(3 --> 2, 5 --> 5, 8 --> 1), - function(3 --> 3, 5 --> 4, 8 --> 1), function(3 --> 0, 5 --> 4, 8 --> 4)) -$ Visualisation for states -$ 0 0 8 -$ 0 5 3 -$ 3 2 3 -$ 0 2 6 -$ 2 0 6 -$ 2 5 1 -$ 3 4 1 -$ 0 4 4 - diff --git a/tests/exhaustive/issues/102/expected/model.eprime b/tests/exhaustive/issues/102/expected/model.eprime deleted file mode 100644 index 937dd9ab75..0000000000 --- a/tests/exhaustive/issues/102/expected/model.eprime +++ /dev/null @@ -1,88 +0,0 @@ -language ESSENCE' 1.0 - -letting HORIZON be 10 -find actions_ExplicitBounded_Length: int(0..10) -find actions_ExplicitBounded_Values_1: matrix indexed by [int(1..10)] of int(3, 5, 8) -find actions_ExplicitBounded_Values_2: matrix indexed by [int(1..10)] of int(3, 5, 8) -find actions_ExplicitBounded_Values_3: matrix indexed by [int(1..10)] of int(1..8) -letting let1 be 8 -find states_ExplicitBoundedR10_Length: int(0..10) -find states_ExplicitBoundedR10_Values_Function1D: matrix indexed by [int(1..10), int(3, 5, 8)] of int(0..8) -find nbActions: int(7) -branching on - [actions_ExplicitBounded_Length, actions_ExplicitBounded_Values_1, actions_ExplicitBounded_Values_2, - actions_ExplicitBounded_Values_3, states_ExplicitBoundedR10_Length, states_ExplicitBoundedR10_Values_Function1D, - nbActions] -such that - actions_ExplicitBounded_Length = states_ExplicitBoundedR10_Length - 1, - and([q37 <= actions_ExplicitBounded_Length -> - actions_ExplicitBounded_Values_1[q37] != actions_ExplicitBounded_Values_2[q37] - | q37 : int(1..10)]), - and([q11 <= actions_ExplicitBounded_Length -> - actions_ExplicitBounded_Values_3[q11] <= - states_ExplicitBoundedR10_Values_Function1D[q11, actions_ExplicitBounded_Values_1[q11]] - /\ q11 <= states_ExplicitBoundedR10_Length - | q11 : int(1..10)]), - and([q39 <= states_ExplicitBoundedR10_Length -> - and([sum([states_ExplicitBoundedR10_Values_Function1D[q39, q40] | q40 : int(3, 5, 8), q40 = b]) <= b /\ - or([q41 = b | q41 : int(3, 5, 8)]) - | b : int(3, 5, 8)]) - | q39 : int(1..10)]), - and([q13 <= actions_ExplicitBounded_Length -> - and([states_ExplicitBoundedR10_Values_Function1D[q13, actions_ExplicitBounded_Values_1[q13]] - - actions_ExplicitBounded_Values_3[q13] - = states_ExplicitBoundedR10_Values_Function1D[q13 + 1, actions_ExplicitBounded_Values_1[q13]], - q13 <= states_ExplicitBoundedR10_Length, q13 + 1 <= states_ExplicitBoundedR10_Length; - int(1..3)]) - | q13 : int(1..10)]), - and([q15 <= actions_ExplicitBounded_Length -> - and([states_ExplicitBoundedR10_Values_Function1D[q15, actions_ExplicitBounded_Values_2[q15]] + - actions_ExplicitBounded_Values_3[q15] - = states_ExplicitBoundedR10_Values_Function1D[q15 + 1, actions_ExplicitBounded_Values_2[q15]], - q15 <= states_ExplicitBoundedR10_Length, q15 + 1 <= states_ExplicitBoundedR10_Length; - int(1..3)]) - | q15 : int(1..10)]), - and([q19 <= actions_ExplicitBounded_Length -> - and([!(actions_ExplicitBounded_Values_1[q19] = b \/ actions_ExplicitBounded_Values_2[q19] = b) -> - and([states_ExplicitBoundedR10_Values_Function1D[q19, b] = - states_ExplicitBoundedR10_Values_Function1D[q19 + 1, b], - q19 <= states_ExplicitBoundedR10_Length, q19 + 1 <= states_ExplicitBoundedR10_Length; - int(1..3)]) - | b : int(3, 5, 8)]) - | q19 : int(1..10)]), - and([q21 <= actions_ExplicitBounded_Length -> - states_ExplicitBoundedR10_Values_Function1D[q21 + 1, actions_ExplicitBounded_Values_1[q21]] = 0 /\ - q21 + 1 <= states_ExplicitBoundedR10_Length - \/ - states_ExplicitBoundedR10_Values_Function1D[q21 + 1, actions_ExplicitBounded_Values_2[q21]] = - actions_ExplicitBounded_Values_2[q21] - /\ q21 + 1 <= states_ExplicitBoundedR10_Length - | q21 : int(1..10)]), - and([sum([sum([0 | 3 = q23]), sum([0 | 5 = q23]), sum([8 | 8 = q23]); int(1..3)]) = - states_ExplicitBoundedR10_Values_Function1D[1, q23] - /\ or([3 = q23, 5 = q23, 8 = q23; int(1..3)]) - | q23 : int(3, 5, 8)]), - states_ExplicitBoundedR10_Values_Function1D[1, 3] = 0, - states_ExplicitBoundedR10_Values_Function1D[1, 5] = 0, - states_ExplicitBoundedR10_Values_Function1D[1, 8] = 8, - 1 <= states_ExplicitBoundedR10_Length, - and([sum([sum([0 | 3 = q30]), sum([4 | 5 = q30]), sum([4 | 8 = q30]); int(1..3)]) = - states_ExplicitBoundedR10_Values_Function1D[states_ExplicitBoundedR10_Length, q30] - /\ or([3 = q30, 5 = q30, 8 = q30; int(1..3)]) - | q30 : int(3, 5, 8)]), - states_ExplicitBoundedR10_Values_Function1D[states_ExplicitBoundedR10_Length, 3] = 0, - states_ExplicitBoundedR10_Values_Function1D[states_ExplicitBoundedR10_Length, 5] = 4, - states_ExplicitBoundedR10_Values_Function1D[states_ExplicitBoundedR10_Length, 8] = 4, - states_ExplicitBoundedR10_Length <= states_ExplicitBoundedR10_Length, - 7 = actions_ExplicitBounded_Length, - and([q1 > states_ExplicitBoundedR10_Length -> - and([states_ExplicitBoundedR10_Values_Function1D[q1, q4] = 0 | q4 : int(3, 5, 8)]) - | q1 : int(1..10)]), - states_ExplicitBoundedR10_Length <= 10, - and([q5 > actions_ExplicitBounded_Length -> - and([actions_ExplicitBounded_Values_1[q5] = 3, actions_ExplicitBounded_Values_2[q5] = 3, - actions_ExplicitBounded_Values_3[q5] = 1; - int(1..3)]) - | q5 : int(1..10)]), - actions_ExplicitBounded_Length <= 10 - diff --git a/tests/exhaustive/issues/166/expected/model_1_1-solution000001.solution b/tests/exhaustive/issues/166/expected/model_1_1-solution000001.solution deleted file mode 100644 index 15cf35802e..0000000000 --- a/tests/exhaustive/issues/166/expected/model_1_1-solution000001.solution +++ /dev/null @@ -1,6 +0,0 @@ -language Essence 1.3 - -letting y be - tuple ([(10, function(1 --> {1, 2}, 2 --> {1}, 3 --> {}), 33), - (11, function(1 --> {1, 2}, 2 --> {1}, 3 --> {}), 55); - int(1..2)]) diff --git a/tests/exhaustive/issues/166/expected/model_1_1.eprime b/tests/exhaustive/issues/166/expected/model_1_1.eprime deleted file mode 100644 index c87311cfea..0000000000 --- a/tests/exhaustive/issues/166/expected/model_1_1.eprime +++ /dev/null @@ -1,46 +0,0 @@ -language ESSENCE' 1.0 - -find y_1_1: matrix indexed by [int(1, 2)] of int(10, 11) -find y_1_2_Function1DR2_Occurrence: matrix indexed by [int(1, 2), int(1..3), int(1, 2)] of bool -find y_1_3: matrix indexed by [int(1, 2)] of int(33, 55) -branching on [y_1_1, y_1_2_Function1DR2_Occurrence, y_1_3] -such that - and([and([y_1_1[q4] = [10, 11; int(1..2)][q4], - and([and([y_1_2_Function1DR2_Occurrence[q4, q7, 1] | 1 = q4, 1 = q7]) /\ - and([y_1_2_Function1DR2_Occurrence[q4, q7, 2] | 1 = q4, 1 = q7]) - /\ and([y_1_2_Function1DR2_Occurrence[q4, q7, 1] | 1 = q4, 2 = q7]) - /\ - (and([y_1_2_Function1DR2_Occurrence[q4, q7, 1] | 2 = q4, 1 = q7]) /\ - and([y_1_2_Function1DR2_Occurrence[q4, q7, 2] | 2 = q4, 1 = q7]) - /\ and([y_1_2_Function1DR2_Occurrence[q4, q7, 1] | 2 = q4, 2 = q7])) - /\ - and([y_1_2_Function1DR2_Occurrence[q4, q7, q19] -> - or([1 = q19 | 1 = q4, 1 = q7]) \/ or([2 = q19 | 1 = q4, 1 = q7]) \/ - or([1 = q19 | 1 = q4, 2 = q7]) - \/ - (or([1 = q19 | 2 = q4, 1 = q7]) \/ or([2 = q19 | 2 = q4, 1 = q7]) \/ - or([1 = q19 | 2 = q4, 2 = q7])) - | q19 : int(1, 2)]) - | q7 : int(1..3)]) - /\ - (and([and([and([y_1_2_Function1DR2_Occurrence[q4, 1, q31] -> 1 = q31 \/ 2 = q31 | q31 : int(1, 2)]) /\ - (y_1_2_Function1DR2_Occurrence[q4, 1, 1] /\ y_1_2_Function1DR2_Occurrence[q4, 1, 2]) - | 1 = q4]), - and([and([y_1_2_Function1DR2_Occurrence[q4, 2, q31] -> 1 = q31 | q31 : int(1, 2)]) /\ - y_1_2_Function1DR2_Occurrence[q4, 2, 1] - | 1 = q4]), - and([and([y_1_2_Function1DR2_Occurrence[q4, 3, q31] -> false | q31 : int(1, 2)]) | 1 = q4]); - int(1..3)]) - /\ - and([and([and([y_1_2_Function1DR2_Occurrence[q4, 1, q33] -> 1 = q33 \/ 2 = q33 | q33 : int(1, 2)]) /\ - (y_1_2_Function1DR2_Occurrence[q4, 1, 1] /\ y_1_2_Function1DR2_Occurrence[q4, 1, 2]) - | 2 = q4]), - and([and([y_1_2_Function1DR2_Occurrence[q4, 2, q33] -> 1 = q33 | q33 : int(1, 2)]) /\ - y_1_2_Function1DR2_Occurrence[q4, 2, 1] - | 2 = q4]), - and([and([y_1_2_Function1DR2_Occurrence[q4, 3, q33] -> false | q33 : int(1, 2)]) | 2 = q4]); - int(1..3)])), - y_1_3[q4] = [33, 55; int(1..2)][q4]; - int(1..3)]) - | q4 : int(1, 2)]) - diff --git a/tests/exhaustive/issues/166/expected/model_1_2-solution000001.solution b/tests/exhaustive/issues/166/expected/model_1_2-solution000001.solution deleted file mode 100644 index 15cf35802e..0000000000 --- a/tests/exhaustive/issues/166/expected/model_1_2-solution000001.solution +++ /dev/null @@ -1,6 +0,0 @@ -language Essence 1.3 - -letting y be - tuple ([(10, function(1 --> {1, 2}, 2 --> {1}, 3 --> {}), 33), - (11, function(1 --> {1, 2}, 2 --> {1}, 3 --> {}), 55); - int(1..2)]) diff --git a/tests/exhaustive/issues/166/expected/model_1_2.eprime b/tests/exhaustive/issues/166/expected/model_1_2.eprime deleted file mode 100644 index 8a52736ab5..0000000000 --- a/tests/exhaustive/issues/166/expected/model_1_2.eprime +++ /dev/null @@ -1,83 +0,0 @@ -language ESSENCE' 1.0 - -find y_1_1: matrix indexed by [int(1, 2)] of int(10, 11) -find y_1_2_Function1DR2_Occurrence: matrix indexed by [int(1, 2), int(1..3), int(1, 2)] of bool -find y_1_3: matrix indexed by [int(1, 2)] of int(33, 55) -find y_1_2_Function1DR6_ExplicitVarSizeWithDummy: matrix indexed by [int(1, 2), int(1..3), int(1..2)] of int(1, 2, 3) -branching on [y_1_1, y_1_2_Function1DR6_ExplicitVarSizeWithDummy, y_1_3, y_1_2_Function1DR2_Occurrence] -such that - and([and([y_1_1[q25] = [10, 11; int(1..2)][q25], - and([and([y_1_2_Function1DR2_Occurrence[q25, q28, 1] | 1 = q25, 1 = q28]) /\ - and([y_1_2_Function1DR2_Occurrence[q25, q28, 2] | 1 = q25, 1 = q28]) - /\ and([y_1_2_Function1DR2_Occurrence[q25, q28, 1] | 1 = q25, 2 = q28]) - /\ - (and([y_1_2_Function1DR2_Occurrence[q25, q28, 1] | 2 = q25, 1 = q28]) /\ - and([y_1_2_Function1DR2_Occurrence[q25, q28, 2] | 2 = q25, 1 = q28]) - /\ and([y_1_2_Function1DR2_Occurrence[q25, q28, 1] | 2 = q25, 2 = q28])) - /\ - and([y_1_2_Function1DR2_Occurrence[q25, q28, q40] -> - or([1 = q40 | 1 = q25, 1 = q28]) \/ or([2 = q40 | 1 = q25, 1 = q28]) \/ - or([1 = q40 | 1 = q25, 2 = q28]) - \/ - (or([1 = q40 | 2 = q25, 1 = q28]) \/ or([2 = q40 | 2 = q25, 1 = q28]) \/ - or([1 = q40 | 2 = q25, 2 = q28])) - | q40 : int(1, 2)]) - | q28 : int(1..3)]) - /\ - (and([and([and([y_1_2_Function1DR2_Occurrence[q25, 1, q52] -> 1 = q52 \/ 2 = q52 | q52 : int(1, 2)]) /\ - (y_1_2_Function1DR2_Occurrence[q25, 1, 1] /\ y_1_2_Function1DR2_Occurrence[q25, 1, 2]) - | 1 = q25]), - and([and([y_1_2_Function1DR2_Occurrence[q25, 2, q52] -> 1 = q52 | q52 : int(1, 2)]) /\ - y_1_2_Function1DR2_Occurrence[q25, 2, 1] - | 1 = q25]), - and([and([y_1_2_Function1DR2_Occurrence[q25, 3, q52] -> false | q52 : int(1, 2)]) | 1 = q25]); - int(1..3)]) - /\ - and([and([and([y_1_2_Function1DR2_Occurrence[q25, 1, q54] -> 1 = q54 \/ 2 = q54 | q54 : int(1, 2)]) /\ - (y_1_2_Function1DR2_Occurrence[q25, 1, 1] /\ y_1_2_Function1DR2_Occurrence[q25, 1, 2]) - | 2 = q25]), - and([and([y_1_2_Function1DR2_Occurrence[q25, 2, q54] -> 1 = q54 | q54 : int(1, 2)]) /\ - y_1_2_Function1DR2_Occurrence[q25, 2, 1] - | 2 = q25]), - and([and([y_1_2_Function1DR2_Occurrence[q25, 3, q54] -> false | q54 : int(1, 2)]) | 2 = q25]); - int(1..3)])), - y_1_3[q25] = [33, 55; int(1..2)][q25]; - int(1..3)]) - | q25 : int(1, 2)]), - and([and([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q4, q5, 1] < - y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q4, q5, 2] - \/ y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q4, q5, 1] = 3 - | q5 : int(1..3)]) - | q4 : int(1, 2)]), - and([and([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q4, q5, 1] = 3 -> - y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q4, q5, 2] = 3 - | q5 : int(1..3)]) - | q4 : int(1, 2)]), - and([and([y_1_1[q10] = y_1_1[q10], - and([and([y_1_2_Function1DR2_Occurrence[q10, q13, q14] -> - or([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q10, q13, q16] != 3 /\ - y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q10, q13, q16] = q14 - | q16 : int(1..2)]) - | q14 : int(1, 2)]) - /\ - and([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q10, q13, q18] != 3 -> - y_1_2_Function1DR2_Occurrence - [q10, q13, y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q10, q13, q18]] - | q18 : int(1..2)]) - | q13 : int(1..3)]) - /\ - and([and([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q10, q19, q21] != 3 -> - y_1_2_Function1DR2_Occurrence - [q10, q19, y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q10, q19, q21]] - | q21 : int(1..2)]) - /\ - and([y_1_2_Function1DR2_Occurrence[q10, q19, q22] -> - or([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q10, q19, q24] != 3 /\ - y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q10, q19, q24] = q22 - | q24 : int(1..2)]) - | q22 : int(1, 2)]) - | q19 : int(1..3)]), - y_1_3[q10] = y_1_3[q10]; - int(1..3)]) - | q10 : int(1, 2)]) - diff --git a/tests/exhaustive/issues/166/expected/model_1_3-solution000001.solution b/tests/exhaustive/issues/166/expected/model_1_3-solution000001.solution deleted file mode 100644 index 15cf35802e..0000000000 --- a/tests/exhaustive/issues/166/expected/model_1_3-solution000001.solution +++ /dev/null @@ -1,6 +0,0 @@ -language Essence 1.3 - -letting y be - tuple ([(10, function(1 --> {1, 2}, 2 --> {1}, 3 --> {}), 33), - (11, function(1 --> {1, 2}, 2 --> {1}, 3 --> {}), 55); - int(1..2)]) diff --git a/tests/exhaustive/issues/166/expected/model_1_3.eprime b/tests/exhaustive/issues/166/expected/model_1_3.eprime deleted file mode 100644 index ed96319c87..0000000000 --- a/tests/exhaustive/issues/166/expected/model_1_3.eprime +++ /dev/null @@ -1,88 +0,0 @@ -language ESSENCE' 1.0 - -find y_1_1: matrix indexed by [int(1, 2)] of int(10, 11) -find y_1_2_Function1DR2_Occurrence: matrix indexed by [int(1, 2), int(1..3), int(1, 2)] of bool -find y_1_3: matrix indexed by [int(1, 2)] of int(33, 55) -find y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker: matrix indexed by [int(1, 2), int(1..3)] of int(0..2) -find y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values: - matrix indexed by [int(1, 2), int(1..3), int(1..2)] of int(1, 2) -branching on - [y_1_1, y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker, y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values, - y_1_3, y_1_2_Function1DR2_Occurrence] -such that - and([and([y_1_1[q24] = [10, 11; int(1..2)][q24], - and([and([y_1_2_Function1DR2_Occurrence[q24, q27, 1] | 1 = q24, 1 = q27]) /\ - and([y_1_2_Function1DR2_Occurrence[q24, q27, 2] | 1 = q24, 1 = q27]) - /\ and([y_1_2_Function1DR2_Occurrence[q24, q27, 1] | 1 = q24, 2 = q27]) - /\ - (and([y_1_2_Function1DR2_Occurrence[q24, q27, 1] | 2 = q24, 1 = q27]) /\ - and([y_1_2_Function1DR2_Occurrence[q24, q27, 2] | 2 = q24, 1 = q27]) - /\ and([y_1_2_Function1DR2_Occurrence[q24, q27, 1] | 2 = q24, 2 = q27])) - /\ - and([y_1_2_Function1DR2_Occurrence[q24, q27, q39] -> - or([1 = q39 | 1 = q24, 1 = q27]) \/ or([2 = q39 | 1 = q24, 1 = q27]) \/ - or([1 = q39 | 1 = q24, 2 = q27]) - \/ - (or([1 = q39 | 2 = q24, 1 = q27]) \/ or([2 = q39 | 2 = q24, 1 = q27]) \/ - or([1 = q39 | 2 = q24, 2 = q27])) - | q39 : int(1, 2)]) - | q27 : int(1..3)]) - /\ - (and([and([and([y_1_2_Function1DR2_Occurrence[q24, 1, q51] -> 1 = q51 \/ 2 = q51 | q51 : int(1, 2)]) /\ - (y_1_2_Function1DR2_Occurrence[q24, 1, 1] /\ y_1_2_Function1DR2_Occurrence[q24, 1, 2]) - | 1 = q24]), - and([and([y_1_2_Function1DR2_Occurrence[q24, 2, q51] -> 1 = q51 | q51 : int(1, 2)]) /\ - y_1_2_Function1DR2_Occurrence[q24, 2, 1] - | 1 = q24]), - and([and([y_1_2_Function1DR2_Occurrence[q24, 3, q51] -> false | q51 : int(1, 2)]) | 1 = q24]); - int(1..3)]) - /\ - and([and([and([y_1_2_Function1DR2_Occurrence[q24, 1, q53] -> 1 = q53 \/ 2 = q53 | q53 : int(1, 2)]) /\ - (y_1_2_Function1DR2_Occurrence[q24, 1, 1] /\ y_1_2_Function1DR2_Occurrence[q24, 1, 2]) - | 2 = q24]), - and([and([y_1_2_Function1DR2_Occurrence[q24, 2, q53] -> 1 = q53 | q53 : int(1, 2)]) /\ - y_1_2_Function1DR2_Occurrence[q24, 2, 1] - | 2 = q24]), - and([and([y_1_2_Function1DR2_Occurrence[q24, 3, q53] -> false | q53 : int(1, 2)]) | 2 = q24]); - int(1..3)])), - y_1_3[q24] = [33, 55; int(1..2)][q24]; - int(1..3)]) - | q24 : int(1, 2)]), - and([and([2 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q4, q5] -> - y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q4, q5, 1] < - y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q4, q5, 2] - | q5 : int(1..3)]) - | q4 : int(1, 2)]), - and([and([and([q7 > y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q4, q5] -> - y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q4, q5, q7] = 1 - | q7 : int(1..2)]) - | q5 : int(1..3)]) - | q4 : int(1, 2)]), - and([and([y_1_1[q9] = y_1_1[q9], - and([and([y_1_2_Function1DR2_Occurrence[q9, q12, q13] -> - or([q15 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q9, q12] /\ - y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q9, q12, q15] = q13 - | q15 : int(1..2)]) - | q13 : int(1, 2)]) - /\ - and([q17 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q9, q12] -> - y_1_2_Function1DR2_Occurrence - [q9, q12, y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q9, q12, q17]] - | q17 : int(1..2)]) - | q12 : int(1..3)]) - /\ - and([and([q20 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q9, q18] -> - y_1_2_Function1DR2_Occurrence - [q9, q18, y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q9, q18, q20]] - | q20 : int(1..2)]) - /\ - and([y_1_2_Function1DR2_Occurrence[q9, q18, q21] -> - or([q23 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q9, q18] /\ - y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q9, q18, q23] = q21 - | q23 : int(1..2)]) - | q21 : int(1, 2)]) - | q18 : int(1..3)]), - y_1_3[q9] = y_1_3[q9]; - int(1..3)]) - | q9 : int(1, 2)]) - diff --git a/tests/exhaustive/issues/166/expected/model_1_4-solution000001.solution b/tests/exhaustive/issues/166/expected/model_1_4-solution000001.solution deleted file mode 100644 index 15cf35802e..0000000000 --- a/tests/exhaustive/issues/166/expected/model_1_4-solution000001.solution +++ /dev/null @@ -1,6 +0,0 @@ -language Essence 1.3 - -letting y be - tuple ([(10, function(1 --> {1, 2}, 2 --> {1}, 3 --> {}), 33), - (11, function(1 --> {1, 2}, 2 --> {1}, 3 --> {}), 55); - int(1..2)]) diff --git a/tests/exhaustive/issues/166/expected/model_1_4.eprime b/tests/exhaustive/issues/166/expected/model_1_4.eprime deleted file mode 100644 index e9fe993bce..0000000000 --- a/tests/exhaustive/issues/166/expected/model_1_4.eprime +++ /dev/null @@ -1,92 +0,0 @@ -language ESSENCE' 1.0 - -find y_1_1: matrix indexed by [int(1, 2)] of int(10, 11) -find y_1_2_Function1DR2_Occurrence: matrix indexed by [int(1, 2), int(1..3), int(1, 2)] of bool -find y_1_3: matrix indexed by [int(1, 2)] of int(33, 55) -find y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1, 2), int(1..3), int(1..2)] of bool -find y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values: - matrix indexed by [int(1, 2), int(1..3), int(1..2)] of int(1, 2) -branching on - [y_1_1, y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags, y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values, - y_1_3, y_1_2_Function1DR2_Occurrence] -such that - and([and([y_1_1[q26] = [10, 11; int(1..2)][q26], - and([and([y_1_2_Function1DR2_Occurrence[q26, q29, 1] | 1 = q26, 1 = q29]) /\ - and([y_1_2_Function1DR2_Occurrence[q26, q29, 2] | 1 = q26, 1 = q29]) - /\ and([y_1_2_Function1DR2_Occurrence[q26, q29, 1] | 1 = q26, 2 = q29]) - /\ - (and([y_1_2_Function1DR2_Occurrence[q26, q29, 1] | 2 = q26, 1 = q29]) /\ - and([y_1_2_Function1DR2_Occurrence[q26, q29, 2] | 2 = q26, 1 = q29]) - /\ and([y_1_2_Function1DR2_Occurrence[q26, q29, 1] | 2 = q26, 2 = q29])) - /\ - and([y_1_2_Function1DR2_Occurrence[q26, q29, q41] -> - or([1 = q41 | 1 = q26, 1 = q29]) \/ or([2 = q41 | 1 = q26, 1 = q29]) \/ - or([1 = q41 | 1 = q26, 2 = q29]) - \/ - (or([1 = q41 | 2 = q26, 1 = q29]) \/ or([2 = q41 | 2 = q26, 1 = q29]) \/ - or([1 = q41 | 2 = q26, 2 = q29])) - | q41 : int(1, 2)]) - | q29 : int(1..3)]) - /\ - (and([and([and([y_1_2_Function1DR2_Occurrence[q26, 1, q53] -> 1 = q53 \/ 2 = q53 | q53 : int(1, 2)]) /\ - (y_1_2_Function1DR2_Occurrence[q26, 1, 1] /\ y_1_2_Function1DR2_Occurrence[q26, 1, 2]) - | 1 = q26]), - and([and([y_1_2_Function1DR2_Occurrence[q26, 2, q53] -> 1 = q53 | q53 : int(1, 2)]) /\ - y_1_2_Function1DR2_Occurrence[q26, 2, 1] - | 1 = q26]), - and([and([y_1_2_Function1DR2_Occurrence[q26, 3, q53] -> false | q53 : int(1, 2)]) | 1 = q26]); - int(1..3)]) - /\ - and([and([and([y_1_2_Function1DR2_Occurrence[q26, 1, q55] -> 1 = q55 \/ 2 = q55 | q55 : int(1, 2)]) /\ - (y_1_2_Function1DR2_Occurrence[q26, 1, 1] /\ y_1_2_Function1DR2_Occurrence[q26, 1, 2]) - | 2 = q26]), - and([and([y_1_2_Function1DR2_Occurrence[q26, 2, q55] -> 1 = q55 | q55 : int(1, 2)]) /\ - y_1_2_Function1DR2_Occurrence[q26, 2, 1] - | 2 = q26]), - and([and([y_1_2_Function1DR2_Occurrence[q26, 3, q55] -> false | q55 : int(1, 2)]) | 2 = q26]); - int(1..3)])), - y_1_3[q26] = [33, 55; int(1..2)][q26]; - int(1..3)]) - | q26 : int(1, 2)]), - and([and([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q4, q5, 2] -> - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q4, q5, 1] < - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q4, q5, 2] - | q5 : int(1..3)]) - | q4 : int(1, 2)]), - and([and([and([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q4, q5, q7] = false -> - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q4, q5, q7] = 1 - | q7 : int(1..2)]) - | q5 : int(1..3)]) - | q4 : int(1, 2)]), - and([and([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q4, q5, 2] -> - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q4, q5, 1] - | q5 : int(1..3)]) - | q4 : int(1, 2)]), - and([and([y_1_1[q11] = y_1_1[q11], - and([and([y_1_2_Function1DR2_Occurrence[q11, q14, q15] -> - or([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q11, q14, q17] /\ - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q11, q14, q17] = q15 - | q17 : int(1..2)]) - | q15 : int(1, 2)]) - /\ - and([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q11, q14, q19] -> - y_1_2_Function1DR2_Occurrence - [q11, q14, y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q11, q14, q19]] - | q19 : int(1..2)]) - | q14 : int(1..3)]) - /\ - and([and([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q11, q20, q22] -> - y_1_2_Function1DR2_Occurrence - [q11, q20, y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q11, q20, q22]] - | q22 : int(1..2)]) - /\ - and([y_1_2_Function1DR2_Occurrence[q11, q20, q23] -> - or([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q11, q20, q25] /\ - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q11, q20, q25] = q23 - | q25 : int(1..2)]) - | q23 : int(1, 2)]) - | q20 : int(1..3)]), - y_1_3[q11] = y_1_3[q11]; - int(1..3)]) - | q11 : int(1, 2)]) - diff --git a/tests/exhaustive/issues/166/expected/model_2_1-solution000001.solution b/tests/exhaustive/issues/166/expected/model_2_1-solution000001.solution deleted file mode 100644 index 15cf35802e..0000000000 --- a/tests/exhaustive/issues/166/expected/model_2_1-solution000001.solution +++ /dev/null @@ -1,6 +0,0 @@ -language Essence 1.3 - -letting y be - tuple ([(10, function(1 --> {1, 2}, 2 --> {1}, 3 --> {}), 33), - (11, function(1 --> {1, 2}, 2 --> {1}, 3 --> {}), 55); - int(1..2)]) diff --git a/tests/exhaustive/issues/166/expected/model_2_1.eprime b/tests/exhaustive/issues/166/expected/model_2_1.eprime deleted file mode 100644 index 4a6e61b210..0000000000 --- a/tests/exhaustive/issues/166/expected/model_2_1.eprime +++ /dev/null @@ -1,139 +0,0 @@ -language ESSENCE' 1.0 - -find y_1_1: matrix indexed by [int(1, 2)] of int(10, 11) -find y_1_2_Function1DR6_ExplicitVarSizeWithDummy: matrix indexed by [int(1, 2), int(1..3), int(1..2)] of int(1, 2, 3) -find y_1_3: matrix indexed by [int(1, 2)] of int(33, 55) -find y_1_2_Function1DR2_Occurrence: matrix indexed by [int(1, 2), int(1..3), int(1, 2)] of bool -branching on [y_1_1, y_1_2_Function1DR2_Occurrence, y_1_3, y_1_2_Function1DR6_ExplicitVarSizeWithDummy] -such that - and([and([y_1_1[q10] = [10, 11; int(1..2)][q10], - and([and([or([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q10, q13, q21] != 3 /\ - y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q10, q13, q21] = 1 - | q21 : int(1..2)]) - | 1 = q10, 1 = q13]) - /\ - and([or([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q10, q13, q23] != 3 /\ - y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q10, q13, q23] = 2 - | q23 : int(1..2)]) - | 1 = q10, 1 = q13]) - /\ - and([or([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q10, q13, q26] != 3 /\ - y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q10, q13, q26] = 1 - | q26 : int(1..2)]) - | 1 = q10, 2 = q13]) - /\ - (and([or([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q10, q13, q31] != 3 /\ - y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q10, q13, q31] = 1 - | q31 : int(1..2)]) - | 2 = q10, 1 = q13]) - /\ - and([or([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q10, q13, q33] != 3 /\ - y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q10, q13, q33] = 2 - | q33 : int(1..2)]) - | 2 = q10, 1 = q13]) - /\ - and([or([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q10, q13, q36] != 3 /\ - y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q10, q13, q36] = 1 - | q36 : int(1..2)]) - | 2 = q10, 2 = q13])) - /\ - and([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q10, q13, q38] != 3 -> - or([1 = y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q10, q13, q38] | 1 = q10, 1 = q13]) \/ - or([2 = y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q10, q13, q38] | 1 = q10, 1 = q13]) - \/ or([1 = y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q10, q13, q38] | 1 = q10, 2 = q13]) - \/ - (or([1 = y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q10, q13, q38] | 2 = q10, 1 = q13]) \/ - or([2 = y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q10, q13, q38] | 2 = q10, 1 = q13]) - \/ or([1 = y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q10, q13, q38] | 2 = q10, 2 = q13])) - | q38 : int(1..2)]) - | q13 : int(1..3)]) - /\ - (and([and([and([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q10, 1, q51] != 3 -> - 1 = y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q10, 1, q51] \/ - 2 = y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q10, 1, q51] - | q51 : int(1..2)]) - /\ - (or([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q10, 1, q54] != 3 /\ - y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q10, 1, q54] = 1 - | q54 : int(1..2)]) - /\ - or([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q10, 1, q54] != 3 /\ - y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q10, 1, q54] = 2 - | q54 : int(1..2)])) - | 1 = q10]), - and([and([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q10, 2, q51] != 3 -> - 1 = y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q10, 2, q51] - | q51 : int(1..2)]) - /\ - or([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q10, 2, q54] != 3 /\ - y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q10, 2, q54] = 1 - | q54 : int(1..2)]) - | 1 = q10]), - and([and([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q10, 3, q51] != 3 -> false | q51 : int(1..2)]) - | 1 = q10]); - int(1..3)]) - /\ - and([and([and([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q10, 1, q56] != 3 -> - 1 = y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q10, 1, q56] \/ - 2 = y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q10, 1, q56] - | q56 : int(1..2)]) - /\ - (or([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q10, 1, q59] != 3 /\ - y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q10, 1, q59] = 1 - | q59 : int(1..2)]) - /\ - or([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q10, 1, q59] != 3 /\ - y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q10, 1, q59] = 2 - | q59 : int(1..2)])) - | 2 = q10]), - and([and([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q10, 2, q56] != 3 -> - 1 = y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q10, 2, q56] - | q56 : int(1..2)]) - /\ - or([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q10, 2, q59] != 3 /\ - y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q10, 2, q59] = 1 - | q59 : int(1..2)]) - | 2 = q10]), - and([and([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q10, 3, q56] != 3 -> false | q56 : int(1..2)]) - | 2 = q10]); - int(1..3)])), - y_1_3[q10] = [33, 55; int(1..2)][q10]; - int(1..3)]) - | q10 : int(1, 2)]), - and([and([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q1, q2, 1] < - y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q1, q2, 2] - \/ y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q1, q2, 1] = 3 - | q2 : int(1..3)]) - | q1 : int(1, 2)]), - and([and([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q1, q2, 1] = 3 -> - y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q1, q2, 2] = 3 - | q2 : int(1..3)]) - | q1 : int(1, 2)]), - and([and([y_1_1[q76] = y_1_1[q76], - and([and([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q76, q79, q81] != 3 -> - y_1_2_Function1DR2_Occurrence - [q76, q79, y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q76, q79, q81]] - | q81 : int(1..2)]) - /\ - and([y_1_2_Function1DR2_Occurrence[q76, q79, q82] -> - or([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q76, q79, q84] != 3 /\ - y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q76, q79, q84] = q82 - | q84 : int(1..2)]) - | q82 : int(1, 2)]) - | q79 : int(1..3)]) - /\ - and([and([y_1_2_Function1DR2_Occurrence[q76, q85, q86] -> - or([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q76, q85, q88] != 3 /\ - y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q76, q85, q88] = q86 - | q88 : int(1..2)]) - | q86 : int(1, 2)]) - /\ - and([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q76, q85, q90] != 3 -> - y_1_2_Function1DR2_Occurrence - [q76, q85, y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q76, q85, q90]] - | q90 : int(1..2)]) - | q85 : int(1..3)]), - y_1_3[q76] = y_1_3[q76]; - int(1..3)]) - | q76 : int(1, 2)]) - diff --git a/tests/exhaustive/issues/166/expected/model_2_2-solution000001.solution b/tests/exhaustive/issues/166/expected/model_2_2-solution000001.solution deleted file mode 100644 index 15cf35802e..0000000000 --- a/tests/exhaustive/issues/166/expected/model_2_2-solution000001.solution +++ /dev/null @@ -1,6 +0,0 @@ -language Essence 1.3 - -letting y be - tuple ([(10, function(1 --> {1, 2}, 2 --> {1}, 3 --> {}), 33), - (11, function(1 --> {1, 2}, 2 --> {1}, 3 --> {}), 55); - int(1..2)]) diff --git a/tests/exhaustive/issues/166/expected/model_2_2.eprime b/tests/exhaustive/issues/166/expected/model_2_2.eprime deleted file mode 100644 index 01e09b171b..0000000000 --- a/tests/exhaustive/issues/166/expected/model_2_2.eprime +++ /dev/null @@ -1,111 +0,0 @@ -language ESSENCE' 1.0 - -find y_1_1: matrix indexed by [int(1, 2)] of int(10, 11) -find y_1_2_Function1DR6_ExplicitVarSizeWithDummy: matrix indexed by [int(1, 2), int(1..3), int(1..2)] of int(1, 2, 3) -find y_1_3: matrix indexed by [int(1, 2)] of int(33, 55) -branching on [y_1_1, y_1_2_Function1DR6_ExplicitVarSizeWithDummy, y_1_3] -such that - and([and([y_1_1[q7] = [10, 11; int(1..2)][q7], - and([and([or([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q7, q10, q18] != 3 /\ - y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q7, q10, q18] = 1 - | q18 : int(1..2)]) - | 1 = q7, 1 = q10]) - /\ - and([or([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q7, q10, q20] != 3 /\ - y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q7, q10, q20] = 2 - | q20 : int(1..2)]) - | 1 = q7, 1 = q10]) - /\ - and([or([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q7, q10, q23] != 3 /\ - y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q7, q10, q23] = 1 - | q23 : int(1..2)]) - | 1 = q7, 2 = q10]) - /\ - (and([or([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q7, q10, q28] != 3 /\ - y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q7, q10, q28] = 1 - | q28 : int(1..2)]) - | 2 = q7, 1 = q10]) - /\ - and([or([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q7, q10, q30] != 3 /\ - y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q7, q10, q30] = 2 - | q30 : int(1..2)]) - | 2 = q7, 1 = q10]) - /\ - and([or([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q7, q10, q33] != 3 /\ - y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q7, q10, q33] = 1 - | q33 : int(1..2)]) - | 2 = q7, 2 = q10])) - /\ - and([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q7, q10, q35] != 3 -> - or([1 = y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q7, q10, q35] | 1 = q7, 1 = q10]) \/ - or([2 = y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q7, q10, q35] | 1 = q7, 1 = q10]) - \/ or([1 = y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q7, q10, q35] | 1 = q7, 2 = q10]) - \/ - (or([1 = y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q7, q10, q35] | 2 = q7, 1 = q10]) \/ - or([2 = y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q7, q10, q35] | 2 = q7, 1 = q10]) - \/ or([1 = y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q7, q10, q35] | 2 = q7, 2 = q10])) - | q35 : int(1..2)]) - | q10 : int(1..3)]) - /\ - (and([and([and([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q7, 1, q48] != 3 -> - 1 = y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q7, 1, q48] \/ - 2 = y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q7, 1, q48] - | q48 : int(1..2)]) - /\ - (or([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q7, 1, q51] != 3 /\ - y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q7, 1, q51] = 1 - | q51 : int(1..2)]) - /\ - or([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q7, 1, q51] != 3 /\ - y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q7, 1, q51] = 2 - | q51 : int(1..2)])) - | 1 = q7]), - and([and([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q7, 2, q48] != 3 -> - 1 = y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q7, 2, q48] - | q48 : int(1..2)]) - /\ - or([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q7, 2, q51] != 3 /\ - y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q7, 2, q51] = 1 - | q51 : int(1..2)]) - | 1 = q7]), - and([and([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q7, 3, q48] != 3 -> false | q48 : int(1..2)]) - | 1 = q7]); - int(1..3)]) - /\ - and([and([and([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q7, 1, q53] != 3 -> - 1 = y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q7, 1, q53] \/ - 2 = y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q7, 1, q53] - | q53 : int(1..2)]) - /\ - (or([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q7, 1, q56] != 3 /\ - y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q7, 1, q56] = 1 - | q56 : int(1..2)]) - /\ - or([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q7, 1, q56] != 3 /\ - y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q7, 1, q56] = 2 - | q56 : int(1..2)])) - | 2 = q7]), - and([and([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q7, 2, q53] != 3 -> - 1 = y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q7, 2, q53] - | q53 : int(1..2)]) - /\ - or([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q7, 2, q56] != 3 /\ - y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q7, 2, q56] = 1 - | q56 : int(1..2)]) - | 2 = q7]), - and([and([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q7, 3, q53] != 3 -> false | q53 : int(1..2)]) - | 2 = q7]); - int(1..3)])), - y_1_3[q7] = [33, 55; int(1..2)][q7]; - int(1..3)]) - | q7 : int(1, 2)]), - and([and([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q1, q2, 1] < - y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q1, q2, 2] - \/ y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q1, q2, 1] = 3 - | q2 : int(1..3)]) - | q1 : int(1, 2)]), - and([and([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q1, q2, 1] = 3 -> - y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q1, q2, 2] = 3 - | q2 : int(1..3)]) - | q1 : int(1, 2)]) - diff --git a/tests/exhaustive/issues/166/expected/model_2_3-solution000001.solution b/tests/exhaustive/issues/166/expected/model_2_3-solution000001.solution deleted file mode 100644 index 15cf35802e..0000000000 --- a/tests/exhaustive/issues/166/expected/model_2_3-solution000001.solution +++ /dev/null @@ -1,6 +0,0 @@ -language Essence 1.3 - -letting y be - tuple ([(10, function(1 --> {1, 2}, 2 --> {1}, 3 --> {}), 33), - (11, function(1 --> {1, 2}, 2 --> {1}, 3 --> {}), 55); - int(1..2)]) diff --git a/tests/exhaustive/issues/166/expected/model_2_3.eprime b/tests/exhaustive/issues/166/expected/model_2_3.eprime deleted file mode 100644 index 5ed05bb825..0000000000 --- a/tests/exhaustive/issues/166/expected/model_2_3.eprime +++ /dev/null @@ -1,159 +0,0 @@ -language ESSENCE' 1.0 - -find y_1_1: matrix indexed by [int(1, 2)] of int(10, 11) -find y_1_2_Function1DR6_ExplicitVarSizeWithDummy: matrix indexed by [int(1, 2), int(1..3), int(1..2)] of int(1, 2, 3) -find y_1_3: matrix indexed by [int(1, 2)] of int(33, 55) -find y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker: matrix indexed by [int(1, 2), int(1..3)] of int(0..2) -find y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values: - matrix indexed by [int(1, 2), int(1..3), int(1..2)] of int(1, 2) -branching on - [y_1_1, y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker, y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values, - y_1_3, y_1_2_Function1DR6_ExplicitVarSizeWithDummy] -such that - and([and([y_1_1[q33] = [10, 11; int(1..2)][q33], - and([and([or([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q33, q36, q44] != 3 /\ - y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q33, q36, q44] = 1 - | q44 : int(1..2)]) - | 1 = q33, 1 = q36]) - /\ - and([or([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q33, q36, q46] != 3 /\ - y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q33, q36, q46] = 2 - | q46 : int(1..2)]) - | 1 = q33, 1 = q36]) - /\ - and([or([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q33, q36, q49] != 3 /\ - y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q33, q36, q49] = 1 - | q49 : int(1..2)]) - | 1 = q33, 2 = q36]) - /\ - (and([or([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q33, q36, q54] != 3 /\ - y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q33, q36, q54] = 1 - | q54 : int(1..2)]) - | 2 = q33, 1 = q36]) - /\ - and([or([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q33, q36, q56] != 3 /\ - y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q33, q36, q56] = 2 - | q56 : int(1..2)]) - | 2 = q33, 1 = q36]) - /\ - and([or([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q33, q36, q59] != 3 /\ - y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q33, q36, q59] = 1 - | q59 : int(1..2)]) - | 2 = q33, 2 = q36])) - /\ - and([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q33, q36, q61] != 3 -> - or([1 = y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q33, q36, q61] | 1 = q33, 1 = q36]) \/ - or([2 = y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q33, q36, q61] | 1 = q33, 1 = q36]) - \/ or([1 = y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q33, q36, q61] | 1 = q33, 2 = q36]) - \/ - (or([1 = y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q33, q36, q61] | 2 = q33, 1 = q36]) \/ - or([2 = y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q33, q36, q61] | 2 = q33, 1 = q36]) - \/ or([1 = y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q33, q36, q61] | 2 = q33, 2 = q36])) - | q61 : int(1..2)]) - | q36 : int(1..3)]) - /\ - (and([and([and([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q33, 1, q74] != 3 -> - 1 = y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q33, 1, q74] \/ - 2 = y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q33, 1, q74] - | q74 : int(1..2)]) - /\ - (or([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q33, 1, q77] != 3 /\ - y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q33, 1, q77] = 1 - | q77 : int(1..2)]) - /\ - or([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q33, 1, q77] != 3 /\ - y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q33, 1, q77] = 2 - | q77 : int(1..2)])) - | 1 = q33]), - and([and([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q33, 2, q74] != 3 -> - 1 = y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q33, 2, q74] - | q74 : int(1..2)]) - /\ - or([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q33, 2, q77] != 3 /\ - y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q33, 2, q77] = 1 - | q77 : int(1..2)]) - | 1 = q33]), - and([and([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q33, 3, q74] != 3 -> false | q74 : int(1..2)]) - | 1 = q33]); - int(1..3)]) - /\ - and([and([and([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q33, 1, q79] != 3 -> - 1 = y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q33, 1, q79] \/ - 2 = y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q33, 1, q79] - | q79 : int(1..2)]) - /\ - (or([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q33, 1, q82] != 3 /\ - y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q33, 1, q82] = 1 - | q82 : int(1..2)]) - /\ - or([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q33, 1, q82] != 3 /\ - y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q33, 1, q82] = 2 - | q82 : int(1..2)])) - | 2 = q33]), - and([and([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q33, 2, q79] != 3 -> - 1 = y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q33, 2, q79] - | q79 : int(1..2)]) - /\ - or([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q33, 2, q82] != 3 /\ - y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q33, 2, q82] = 1 - | q82 : int(1..2)]) - | 2 = q33]), - and([and([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q33, 3, q79] != 3 -> false | q79 : int(1..2)]) - | 2 = q33]); - int(1..3)])), - y_1_3[q33] = [33, 55; int(1..2)][q33]; - int(1..3)]) - | q33 : int(1, 2)]), - and([and([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q1, q2, 1] < - y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q1, q2, 2] - \/ y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q1, q2, 1] = 3 - | q2 : int(1..3)]) - | q1 : int(1, 2)]), - and([and([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q1, q2, 1] = 3 -> - y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q1, q2, 2] = 3 - | q2 : int(1..3)]) - | q1 : int(1, 2)]), - and([and([2 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q7, q8] -> - y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q7, q8, 1] < - y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q7, q8, 2] - | q8 : int(1..3)]) - | q7 : int(1, 2)]), - and([and([and([q10 > y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q7, q8] -> - y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q7, q8, q10] = 1 - | q10 : int(1..2)]) - | q8 : int(1..3)]) - | q7 : int(1, 2)]), - and([and([y_1_1[q12] = y_1_1[q12], - and([and([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q12, q15, q17] != 3 -> - or([q19 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q12, q15] /\ - y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q12, q15, q19] = - y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q12, q15, q17] - | q19 : int(1..2)]) - | q17 : int(1..2)]) - /\ - and([q21 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q12, q15] -> - or([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q12, q15, q23] != 3 /\ - y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q12, q15, q23] = - y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q12, q15, q21] - | q23 : int(1..2)]) - | q21 : int(1..2)]) - | q15 : int(1..3)]) - /\ - and([and([q26 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q12, q24] -> - or([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q12, q24, q28] != 3 /\ - y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q12, q24, q28] = - y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q12, q24, q26] - | q28 : int(1..2)]) - | q26 : int(1..2)]) - /\ - and([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q12, q24, q30] != 3 -> - or([q32 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q12, q24] /\ - y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q12, q24, q32] = - y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q12, q24, q30] - | q32 : int(1..2)]) - | q30 : int(1..2)]) - | q24 : int(1..3)]), - y_1_3[q12] = y_1_3[q12]; - int(1..3)]) - | q12 : int(1, 2)]) - diff --git a/tests/exhaustive/issues/166/expected/model_2_4-solution000001.solution b/tests/exhaustive/issues/166/expected/model_2_4-solution000001.solution deleted file mode 100644 index 15cf35802e..0000000000 --- a/tests/exhaustive/issues/166/expected/model_2_4-solution000001.solution +++ /dev/null @@ -1,6 +0,0 @@ -language Essence 1.3 - -letting y be - tuple ([(10, function(1 --> {1, 2}, 2 --> {1}, 3 --> {}), 33), - (11, function(1 --> {1, 2}, 2 --> {1}, 3 --> {}), 55); - int(1..2)]) diff --git a/tests/exhaustive/issues/166/expected/model_2_4.eprime b/tests/exhaustive/issues/166/expected/model_2_4.eprime deleted file mode 100644 index b870ff8076..0000000000 --- a/tests/exhaustive/issues/166/expected/model_2_4.eprime +++ /dev/null @@ -1,163 +0,0 @@ -language ESSENCE' 1.0 - -find y_1_1: matrix indexed by [int(1, 2)] of int(10, 11) -find y_1_2_Function1DR6_ExplicitVarSizeWithDummy: matrix indexed by [int(1, 2), int(1..3), int(1..2)] of int(1, 2, 3) -find y_1_3: matrix indexed by [int(1, 2)] of int(33, 55) -find y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1, 2), int(1..3), int(1..2)] of bool -find y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values: - matrix indexed by [int(1, 2), int(1..3), int(1..2)] of int(1, 2) -branching on - [y_1_1, y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags, y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values, - y_1_3, y_1_2_Function1DR6_ExplicitVarSizeWithDummy] -such that - and([and([y_1_1[q35] = [10, 11; int(1..2)][q35], - and([and([or([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q35, q38, q46] != 3 /\ - y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q35, q38, q46] = 1 - | q46 : int(1..2)]) - | 1 = q35, 1 = q38]) - /\ - and([or([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q35, q38, q48] != 3 /\ - y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q35, q38, q48] = 2 - | q48 : int(1..2)]) - | 1 = q35, 1 = q38]) - /\ - and([or([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q35, q38, q51] != 3 /\ - y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q35, q38, q51] = 1 - | q51 : int(1..2)]) - | 1 = q35, 2 = q38]) - /\ - (and([or([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q35, q38, q56] != 3 /\ - y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q35, q38, q56] = 1 - | q56 : int(1..2)]) - | 2 = q35, 1 = q38]) - /\ - and([or([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q35, q38, q58] != 3 /\ - y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q35, q38, q58] = 2 - | q58 : int(1..2)]) - | 2 = q35, 1 = q38]) - /\ - and([or([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q35, q38, q61] != 3 /\ - y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q35, q38, q61] = 1 - | q61 : int(1..2)]) - | 2 = q35, 2 = q38])) - /\ - and([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q35, q38, q63] != 3 -> - or([1 = y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q35, q38, q63] | 1 = q35, 1 = q38]) \/ - or([2 = y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q35, q38, q63] | 1 = q35, 1 = q38]) - \/ or([1 = y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q35, q38, q63] | 1 = q35, 2 = q38]) - \/ - (or([1 = y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q35, q38, q63] | 2 = q35, 1 = q38]) \/ - or([2 = y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q35, q38, q63] | 2 = q35, 1 = q38]) - \/ or([1 = y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q35, q38, q63] | 2 = q35, 2 = q38])) - | q63 : int(1..2)]) - | q38 : int(1..3)]) - /\ - (and([and([and([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q35, 1, q76] != 3 -> - 1 = y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q35, 1, q76] \/ - 2 = y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q35, 1, q76] - | q76 : int(1..2)]) - /\ - (or([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q35, 1, q79] != 3 /\ - y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q35, 1, q79] = 1 - | q79 : int(1..2)]) - /\ - or([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q35, 1, q79] != 3 /\ - y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q35, 1, q79] = 2 - | q79 : int(1..2)])) - | 1 = q35]), - and([and([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q35, 2, q76] != 3 -> - 1 = y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q35, 2, q76] - | q76 : int(1..2)]) - /\ - or([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q35, 2, q79] != 3 /\ - y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q35, 2, q79] = 1 - | q79 : int(1..2)]) - | 1 = q35]), - and([and([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q35, 3, q76] != 3 -> false | q76 : int(1..2)]) - | 1 = q35]); - int(1..3)]) - /\ - and([and([and([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q35, 1, q81] != 3 -> - 1 = y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q35, 1, q81] \/ - 2 = y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q35, 1, q81] - | q81 : int(1..2)]) - /\ - (or([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q35, 1, q84] != 3 /\ - y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q35, 1, q84] = 1 - | q84 : int(1..2)]) - /\ - or([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q35, 1, q84] != 3 /\ - y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q35, 1, q84] = 2 - | q84 : int(1..2)])) - | 2 = q35]), - and([and([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q35, 2, q81] != 3 -> - 1 = y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q35, 2, q81] - | q81 : int(1..2)]) - /\ - or([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q35, 2, q84] != 3 /\ - y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q35, 2, q84] = 1 - | q84 : int(1..2)]) - | 2 = q35]), - and([and([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q35, 3, q81] != 3 -> false | q81 : int(1..2)]) - | 2 = q35]); - int(1..3)])), - y_1_3[q35] = [33, 55; int(1..2)][q35]; - int(1..3)]) - | q35 : int(1, 2)]), - and([and([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q1, q2, 1] < - y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q1, q2, 2] - \/ y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q1, q2, 1] = 3 - | q2 : int(1..3)]) - | q1 : int(1, 2)]), - and([and([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q1, q2, 1] = 3 -> - y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q1, q2, 2] = 3 - | q2 : int(1..3)]) - | q1 : int(1, 2)]), - and([and([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q7, q8, 2] -> - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q7, q8, 1] < - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q7, q8, 2] - | q8 : int(1..3)]) - | q7 : int(1, 2)]), - and([and([and([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q7, q8, q10] = false -> - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q7, q8, q10] = 1 - | q10 : int(1..2)]) - | q8 : int(1..3)]) - | q7 : int(1, 2)]), - and([and([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q7, q8, 2] -> - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q7, q8, 1] - | q8 : int(1..3)]) - | q7 : int(1, 2)]), - and([and([y_1_1[q14] = y_1_1[q14], - and([and([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q14, q17, q19] != 3 -> - or([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q14, q17, q21] /\ - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q14, q17, q21] = - y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q14, q17, q19] - | q21 : int(1..2)]) - | q19 : int(1..2)]) - /\ - and([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q14, q17, q23] -> - or([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q14, q17, q25] != 3 /\ - y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q14, q17, q25] = - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q14, q17, q23] - | q25 : int(1..2)]) - | q23 : int(1..2)]) - | q17 : int(1..3)]) - /\ - and([and([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q14, q26, q28] -> - or([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q14, q26, q30] != 3 /\ - y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q14, q26, q30] = - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q14, q26, q28] - | q30 : int(1..2)]) - | q28 : int(1..2)]) - /\ - and([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q14, q26, q32] != 3 -> - or([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q14, q26, q34] /\ - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q14, q26, q34] = - y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q14, q26, q32] - | q34 : int(1..2)]) - | q32 : int(1..2)]) - | q26 : int(1..3)]), - y_1_3[q14] = y_1_3[q14]; - int(1..3)]) - | q14 : int(1, 2)]) - diff --git a/tests/exhaustive/issues/166/expected/model_3_1-solution000001.solution b/tests/exhaustive/issues/166/expected/model_3_1-solution000001.solution deleted file mode 100644 index 15cf35802e..0000000000 --- a/tests/exhaustive/issues/166/expected/model_3_1-solution000001.solution +++ /dev/null @@ -1,6 +0,0 @@ -language Essence 1.3 - -letting y be - tuple ([(10, function(1 --> {1, 2}, 2 --> {1}, 3 --> {}), 33), - (11, function(1 --> {1, 2}, 2 --> {1}, 3 --> {}), 55); - int(1..2)]) diff --git a/tests/exhaustive/issues/166/expected/model_3_1.eprime b/tests/exhaustive/issues/166/expected/model_3_1.eprime deleted file mode 100644 index 2cc1c16b10..0000000000 --- a/tests/exhaustive/issues/166/expected/model_3_1.eprime +++ /dev/null @@ -1,148 +0,0 @@ -language ESSENCE' 1.0 - -find y_1_1: matrix indexed by [int(1, 2)] of int(10, 11) -find y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker: matrix indexed by [int(1, 2), int(1..3)] of int(0..2) -find y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values: - matrix indexed by [int(1, 2), int(1..3), int(1..2)] of int(1, 2) -find y_1_3: matrix indexed by [int(1, 2)] of int(33, 55) -find y_1_2_Function1DR2_Occurrence: matrix indexed by [int(1, 2), int(1..3), int(1, 2)] of bool -branching on - [y_1_1, y_1_2_Function1DR2_Occurrence, y_1_3, y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker, - y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values] -such that - and([and([y_1_1[q9] = [10, 11; int(1..2)][q9], - and([and([or([q20 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q9, q12] /\ - y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q9, q12, q20] = 1 - | q20 : int(1..2)]) - | 1 = q9, 1 = q12]) - /\ - and([or([q22 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q9, q12] /\ - y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q9, q12, q22] = 2 - | q22 : int(1..2)]) - | 1 = q9, 1 = q12]) - /\ - and([or([q25 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q9, q12] /\ - y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q9, q12, q25] = 1 - | q25 : int(1..2)]) - | 1 = q9, 2 = q12]) - /\ - (and([or([q30 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q9, q12] /\ - y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q9, q12, q30] = 1 - | q30 : int(1..2)]) - | 2 = q9, 1 = q12]) - /\ - and([or([q32 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q9, q12] /\ - y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q9, q12, q32] = 2 - | q32 : int(1..2)]) - | 2 = q9, 1 = q12]) - /\ - and([or([q35 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q9, q12] /\ - y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q9, q12, q35] = 1 - | q35 : int(1..2)]) - | 2 = q9, 2 = q12])) - /\ - and([q37 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q9, q12] -> - or([1 = y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q9, q12, q37] | 1 = q9, 1 = q12]) \/ - or([2 = y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q9, q12, q37] | 1 = q9, 1 = q12]) - \/ or([1 = y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q9, q12, q37] | 1 = q9, 2 = q12]) - \/ - (or([1 = y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q9, q12, q37] | 2 = q9, 1 = q12]) - \/ - or([2 = y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q9, q12, q37] | 2 = q9, 1 = q12]) - \/ - or([1 = y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q9, q12, q37] | 2 = q9, 2 = q12])) - | q37 : int(1..2)]) - | q12 : int(1..3)]) - /\ - (and([and([and([q50 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q9, 1] -> - 1 = y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q9, 1, q50] \/ - 2 = y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q9, 1, q50] - | q50 : int(1..2)]) - /\ - (or([q53 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q9, 1] /\ - y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q9, 1, q53] = 1 - | q53 : int(1..2)]) - /\ - or([q53 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q9, 1] /\ - y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q9, 1, q53] = 2 - | q53 : int(1..2)])) - | 1 = q9]), - and([and([q50 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q9, 2] -> - 1 = y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q9, 2, q50] - | q50 : int(1..2)]) - /\ - or([q53 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q9, 2] /\ - y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q9, 2, q53] = 1 - | q53 : int(1..2)]) - | 1 = q9]), - and([and([q50 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q9, 3] -> false - | q50 : int(1..2)]) - | 1 = q9]); - int(1..3)]) - /\ - and([and([and([q55 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q9, 1] -> - 1 = y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q9, 1, q55] \/ - 2 = y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q9, 1, q55] - | q55 : int(1..2)]) - /\ - (or([q58 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q9, 1] /\ - y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q9, 1, q58] = 1 - | q58 : int(1..2)]) - /\ - or([q58 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q9, 1] /\ - y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q9, 1, q58] = 2 - | q58 : int(1..2)])) - | 2 = q9]), - and([and([q55 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q9, 2] -> - 1 = y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q9, 2, q55] - | q55 : int(1..2)]) - /\ - or([q58 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q9, 2] /\ - y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q9, 2, q58] = 1 - | q58 : int(1..2)]) - | 2 = q9]), - and([and([q55 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q9, 3] -> false - | q55 : int(1..2)]) - | 2 = q9]); - int(1..3)])), - y_1_3[q9] = [33, 55; int(1..2)][q9]; - int(1..3)]) - | q9 : int(1, 2)]), - and([and([2 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q1, q2] -> - y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q1, q2, 1] < - y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q1, q2, 2] - | q2 : int(1..3)]) - | q1 : int(1, 2)]), - and([and([and([q4 > y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q1, q2] -> - y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q1, q2, q4] = 1 - | q4 : int(1..2)]) - | q2 : int(1..3)]) - | q1 : int(1, 2)]), - and([and([y_1_1[q75] = y_1_1[q75], - and([and([q80 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q75, q78] -> - y_1_2_Function1DR2_Occurrence - [q75, q78, y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q75, q78, q80]] - | q80 : int(1..2)]) - /\ - and([y_1_2_Function1DR2_Occurrence[q75, q78, q81] -> - or([q83 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q75, q78] /\ - y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q75, q78, q83] = q81 - | q83 : int(1..2)]) - | q81 : int(1, 2)]) - | q78 : int(1..3)]) - /\ - and([and([y_1_2_Function1DR2_Occurrence[q75, q84, q85] -> - or([q87 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q75, q84] /\ - y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q75, q84, q87] = q85 - | q87 : int(1..2)]) - | q85 : int(1, 2)]) - /\ - and([q89 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q75, q84] -> - y_1_2_Function1DR2_Occurrence - [q75, q84, y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q75, q84, q89]] - | q89 : int(1..2)]) - | q84 : int(1..3)]), - y_1_3[q75] = y_1_3[q75]; - int(1..3)]) - | q75 : int(1, 2)]) - diff --git a/tests/exhaustive/issues/166/expected/model_3_2-solution000001.solution b/tests/exhaustive/issues/166/expected/model_3_2-solution000001.solution deleted file mode 100644 index 15cf35802e..0000000000 --- a/tests/exhaustive/issues/166/expected/model_3_2-solution000001.solution +++ /dev/null @@ -1,6 +0,0 @@ -language Essence 1.3 - -letting y be - tuple ([(10, function(1 --> {1, 2}, 2 --> {1}, 3 --> {}), 33), - (11, function(1 --> {1, 2}, 2 --> {1}, 3 --> {}), 55); - int(1..2)]) diff --git a/tests/exhaustive/issues/166/expected/model_3_2.eprime b/tests/exhaustive/issues/166/expected/model_3_2.eprime deleted file mode 100644 index a7db64c979..0000000000 --- a/tests/exhaustive/issues/166/expected/model_3_2.eprime +++ /dev/null @@ -1,166 +0,0 @@ -language ESSENCE' 1.0 - -find y_1_1: matrix indexed by [int(1, 2)] of int(10, 11) -find y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker: matrix indexed by [int(1, 2), int(1..3)] of int(0..2) -find y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values: - matrix indexed by [int(1, 2), int(1..3), int(1..2)] of int(1, 2) -find y_1_3: matrix indexed by [int(1, 2)] of int(33, 55) -find y_1_2_Function1DR6_ExplicitVarSizeWithDummy: matrix indexed by [int(1, 2), int(1..3), int(1..2)] of int(1, 2, 3) -branching on - [y_1_1, y_1_2_Function1DR6_ExplicitVarSizeWithDummy, y_1_3, y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker, - y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values] -such that - and([and([y_1_1[q33] = [10, 11; int(1..2)][q33], - and([and([or([q44 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q33, q36] /\ - y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q33, q36, q44] = 1 - | q44 : int(1..2)]) - | 1 = q33, 1 = q36]) - /\ - and([or([q46 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q33, q36] /\ - y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q33, q36, q46] = 2 - | q46 : int(1..2)]) - | 1 = q33, 1 = q36]) - /\ - and([or([q49 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q33, q36] /\ - y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q33, q36, q49] = 1 - | q49 : int(1..2)]) - | 1 = q33, 2 = q36]) - /\ - (and([or([q54 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q33, q36] /\ - y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q33, q36, q54] = 1 - | q54 : int(1..2)]) - | 2 = q33, 1 = q36]) - /\ - and([or([q56 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q33, q36] /\ - y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q33, q36, q56] = 2 - | q56 : int(1..2)]) - | 2 = q33, 1 = q36]) - /\ - and([or([q59 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q33, q36] /\ - y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q33, q36, q59] = 1 - | q59 : int(1..2)]) - | 2 = q33, 2 = q36])) - /\ - and([q61 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q33, q36] -> - or([1 = y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q33, q36, q61] | 1 = q33, 1 = q36]) - \/ - or([2 = y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q33, q36, q61] | 1 = q33, 1 = q36]) - \/ - or([1 = y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q33, q36, q61] | 1 = q33, 2 = q36]) - \/ - (or([1 = y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q33, q36, q61] | 2 = q33, 1 = q36]) - \/ - or([2 = y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q33, q36, q61] | 2 = q33, 1 = q36]) - \/ - or([1 = y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q33, q36, q61] - | 2 = q33, 2 = q36])) - | q61 : int(1..2)]) - | q36 : int(1..3)]) - /\ - (and([and([and([q74 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q33, 1] -> - 1 = y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q33, 1, q74] \/ - 2 = y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q33, 1, q74] - | q74 : int(1..2)]) - /\ - (or([q77 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q33, 1] /\ - y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q33, 1, q77] = 1 - | q77 : int(1..2)]) - /\ - or([q77 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q33, 1] /\ - y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q33, 1, q77] = 2 - | q77 : int(1..2)])) - | 1 = q33]), - and([and([q74 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q33, 2] -> - 1 = y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q33, 2, q74] - | q74 : int(1..2)]) - /\ - or([q77 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q33, 2] /\ - y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q33, 2, q77] = 1 - | q77 : int(1..2)]) - | 1 = q33]), - and([and([q74 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q33, 3] -> false - | q74 : int(1..2)]) - | 1 = q33]); - int(1..3)]) - /\ - and([and([and([q79 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q33, 1] -> - 1 = y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q33, 1, q79] \/ - 2 = y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q33, 1, q79] - | q79 : int(1..2)]) - /\ - (or([q82 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q33, 1] /\ - y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q33, 1, q82] = 1 - | q82 : int(1..2)]) - /\ - or([q82 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q33, 1] /\ - y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q33, 1, q82] = 2 - | q82 : int(1..2)])) - | 2 = q33]), - and([and([q79 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q33, 2] -> - 1 = y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q33, 2, q79] - | q79 : int(1..2)]) - /\ - or([q82 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q33, 2] /\ - y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q33, 2, q82] = 1 - | q82 : int(1..2)]) - | 2 = q33]), - and([and([q79 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q33, 3] -> false - | q79 : int(1..2)]) - | 2 = q33]); - int(1..3)])), - y_1_3[q33] = [33, 55; int(1..2)][q33]; - int(1..3)]) - | q33 : int(1, 2)]), - and([and([2 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q1, q2] -> - y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q1, q2, 1] < - y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q1, q2, 2] - | q2 : int(1..3)]) - | q1 : int(1, 2)]), - and([and([and([q4 > y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q1, q2] -> - y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q1, q2, q4] = 1 - | q4 : int(1..2)]) - | q2 : int(1..3)]) - | q1 : int(1, 2)]), - and([and([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q6, q7, 1] < - y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q6, q7, 2] - \/ y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q6, q7, 1] = 3 - | q7 : int(1..3)]) - | q6 : int(1, 2)]), - and([and([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q6, q7, 1] = 3 -> - y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q6, q7, 2] = 3 - | q7 : int(1..3)]) - | q6 : int(1, 2)]), - and([and([y_1_1[q12] = y_1_1[q12], - and([and([q17 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q12, q15] -> - or([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q12, q15, q19] != 3 /\ - y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q12, q15, q19] = - y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q12, q15, q17] - | q19 : int(1..2)]) - | q17 : int(1..2)]) - /\ - and([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q12, q15, q21] != 3 -> - or([q23 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q12, q15] /\ - y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q12, q15, q23] = - y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q12, q15, q21] - | q23 : int(1..2)]) - | q21 : int(1..2)]) - | q15 : int(1..3)]) - /\ - and([and([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q12, q24, q26] != 3 -> - or([q28 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q12, q24] /\ - y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q12, q24, q28] = - y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q12, q24, q26] - | q28 : int(1..2)]) - | q26 : int(1..2)]) - /\ - and([q30 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q12, q24] -> - or([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q12, q24, q32] != 3 /\ - y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q12, q24, q32] = - y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q12, q24, q30] - | q32 : int(1..2)]) - | q30 : int(1..2)]) - | q24 : int(1..3)]), - y_1_3[q12] = y_1_3[q12]; - int(1..3)]) - | q12 : int(1, 2)]) - diff --git a/tests/exhaustive/issues/166/expected/model_3_3-solution000001.solution b/tests/exhaustive/issues/166/expected/model_3_3-solution000001.solution deleted file mode 100644 index 15cf35802e..0000000000 --- a/tests/exhaustive/issues/166/expected/model_3_3-solution000001.solution +++ /dev/null @@ -1,6 +0,0 @@ -language Essence 1.3 - -letting y be - tuple ([(10, function(1 --> {1, 2}, 2 --> {1}, 3 --> {}), 33), - (11, function(1 --> {1, 2}, 2 --> {1}, 3 --> {}), 55); - int(1..2)]) diff --git a/tests/exhaustive/issues/166/expected/model_3_3.eprime b/tests/exhaustive/issues/166/expected/model_3_3.eprime deleted file mode 100644 index a2acd86800..0000000000 --- a/tests/exhaustive/issues/166/expected/model_3_3.eprime +++ /dev/null @@ -1,118 +0,0 @@ -language ESSENCE' 1.0 - -find y_1_1: matrix indexed by [int(1, 2)] of int(10, 11) -find y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker: matrix indexed by [int(1, 2), int(1..3)] of int(0..2) -find y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values: - matrix indexed by [int(1, 2), int(1..3), int(1..2)] of int(1, 2) -find y_1_3: matrix indexed by [int(1, 2)] of int(33, 55) -branching on - [y_1_1, y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker, y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values, - y_1_3] -such that - and([and([y_1_1[q6] = [10, 11; int(1..2)][q6], - and([and([or([q17 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q6, q9] /\ - y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q6, q9, q17] = 1 - | q17 : int(1..2)]) - | 1 = q6, 1 = q9]) - /\ - and([or([q19 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q6, q9] /\ - y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q6, q9, q19] = 2 - | q19 : int(1..2)]) - | 1 = q6, 1 = q9]) - /\ - and([or([q22 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q6, q9] /\ - y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q6, q9, q22] = 1 - | q22 : int(1..2)]) - | 1 = q6, 2 = q9]) - /\ - (and([or([q27 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q6, q9] /\ - y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q6, q9, q27] = 1 - | q27 : int(1..2)]) - | 2 = q6, 1 = q9]) - /\ - and([or([q29 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q6, q9] /\ - y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q6, q9, q29] = 2 - | q29 : int(1..2)]) - | 2 = q6, 1 = q9]) - /\ - and([or([q32 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q6, q9] /\ - y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q6, q9, q32] = 1 - | q32 : int(1..2)]) - | 2 = q6, 2 = q9])) - /\ - and([q34 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q6, q9] -> - or([1 = y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q6, q9, q34] | 1 = q6, 1 = q9]) \/ - or([2 = y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q6, q9, q34] | 1 = q6, 1 = q9]) - \/ or([1 = y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q6, q9, q34] | 1 = q6, 2 = q9]) - \/ - (or([1 = y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q6, q9, q34] | 2 = q6, 1 = q9]) \/ - or([2 = y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q6, q9, q34] | 2 = q6, 1 = q9]) - \/ or([1 = y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q6, q9, q34] | 2 = q6, 2 = q9])) - | q34 : int(1..2)]) - | q9 : int(1..3)]) - /\ - (and([and([and([q47 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q6, 1] -> - 1 = y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q6, 1, q47] \/ - 2 = y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q6, 1, q47] - | q47 : int(1..2)]) - /\ - (or([q50 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q6, 1] /\ - y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q6, 1, q50] = 1 - | q50 : int(1..2)]) - /\ - or([q50 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q6, 1] /\ - y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q6, 1, q50] = 2 - | q50 : int(1..2)])) - | 1 = q6]), - and([and([q47 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q6, 2] -> - 1 = y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q6, 2, q47] - | q47 : int(1..2)]) - /\ - or([q50 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q6, 2] /\ - y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q6, 2, q50] = 1 - | q50 : int(1..2)]) - | 1 = q6]), - and([and([q47 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q6, 3] -> false - | q47 : int(1..2)]) - | 1 = q6]); - int(1..3)]) - /\ - and([and([and([q52 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q6, 1] -> - 1 = y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q6, 1, q52] \/ - 2 = y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q6, 1, q52] - | q52 : int(1..2)]) - /\ - (or([q55 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q6, 1] /\ - y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q6, 1, q55] = 1 - | q55 : int(1..2)]) - /\ - or([q55 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q6, 1] /\ - y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q6, 1, q55] = 2 - | q55 : int(1..2)])) - | 2 = q6]), - and([and([q52 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q6, 2] -> - 1 = y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q6, 2, q52] - | q52 : int(1..2)]) - /\ - or([q55 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q6, 2] /\ - y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q6, 2, q55] = 1 - | q55 : int(1..2)]) - | 2 = q6]), - and([and([q52 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q6, 3] -> false - | q52 : int(1..2)]) - | 2 = q6]); - int(1..3)])), - y_1_3[q6] = [33, 55; int(1..2)][q6]; - int(1..3)]) - | q6 : int(1, 2)]), - and([and([2 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q1, q2] -> - y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q1, q2, 1] < - y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q1, q2, 2] - | q2 : int(1..3)]) - | q1 : int(1, 2)]), - and([and([and([q4 > y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q1, q2] -> - y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q1, q2, q4] = 1 - | q4 : int(1..2)]) - | q2 : int(1..3)]) - | q1 : int(1, 2)]) - diff --git a/tests/exhaustive/issues/166/expected/model_3_4-solution000001.solution b/tests/exhaustive/issues/166/expected/model_3_4-solution000001.solution deleted file mode 100644 index 15cf35802e..0000000000 --- a/tests/exhaustive/issues/166/expected/model_3_4-solution000001.solution +++ /dev/null @@ -1,6 +0,0 @@ -language Essence 1.3 - -letting y be - tuple ([(10, function(1 --> {1, 2}, 2 --> {1}, 3 --> {}), 33), - (11, function(1 --> {1, 2}, 2 --> {1}, 3 --> {}), 55); - int(1..2)]) diff --git a/tests/exhaustive/issues/166/expected/model_3_4.eprime b/tests/exhaustive/issues/166/expected/model_3_4.eprime deleted file mode 100644 index 78ca7fa00e..0000000000 --- a/tests/exhaustive/issues/166/expected/model_3_4.eprime +++ /dev/null @@ -1,173 +0,0 @@ -language ESSENCE' 1.0 - -find y_1_1: matrix indexed by [int(1, 2)] of int(10, 11) -find y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker: matrix indexed by [int(1, 2), int(1..3)] of int(0..2) -find y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values: - matrix indexed by [int(1, 2), int(1..3), int(1..2)] of int(1, 2) -find y_1_3: matrix indexed by [int(1, 2)] of int(33, 55) -find y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1, 2), int(1..3), int(1..2)] of bool -find y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values: - matrix indexed by [int(1, 2), int(1..3), int(1..2)] of int(1, 2) -branching on - [y_1_1, y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags, y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values, - y_1_3, y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker, y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values] -such that - and([and([y_1_1[q34] = [10, 11; int(1..2)][q34], - and([and([or([q45 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q34, q37] /\ - y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q34, q37, q45] = 1 - | q45 : int(1..2)]) - | 1 = q34, 1 = q37]) - /\ - and([or([q47 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q34, q37] /\ - y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q34, q37, q47] = 2 - | q47 : int(1..2)]) - | 1 = q34, 1 = q37]) - /\ - and([or([q50 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q34, q37] /\ - y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q34, q37, q50] = 1 - | q50 : int(1..2)]) - | 1 = q34, 2 = q37]) - /\ - (and([or([q55 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q34, q37] /\ - y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q34, q37, q55] = 1 - | q55 : int(1..2)]) - | 2 = q34, 1 = q37]) - /\ - and([or([q57 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q34, q37] /\ - y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q34, q37, q57] = 2 - | q57 : int(1..2)]) - | 2 = q34, 1 = q37]) - /\ - and([or([q60 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q34, q37] /\ - y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q34, q37, q60] = 1 - | q60 : int(1..2)]) - | 2 = q34, 2 = q37])) - /\ - and([q62 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q34, q37] -> - or([1 = y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q34, q37, q62] | 1 = q34, 1 = q37]) - \/ - or([2 = y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q34, q37, q62] | 1 = q34, 1 = q37]) - \/ - or([1 = y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q34, q37, q62] | 1 = q34, 2 = q37]) - \/ - (or([1 = y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q34, q37, q62] | 2 = q34, 1 = q37]) - \/ - or([2 = y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q34, q37, q62] | 2 = q34, 1 = q37]) - \/ - or([1 = y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q34, q37, q62] - | 2 = q34, 2 = q37])) - | q62 : int(1..2)]) - | q37 : int(1..3)]) - /\ - (and([and([and([q75 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q34, 1] -> - 1 = y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q34, 1, q75] \/ - 2 = y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q34, 1, q75] - | q75 : int(1..2)]) - /\ - (or([q78 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q34, 1] /\ - y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q34, 1, q78] = 1 - | q78 : int(1..2)]) - /\ - or([q78 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q34, 1] /\ - y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q34, 1, q78] = 2 - | q78 : int(1..2)])) - | 1 = q34]), - and([and([q75 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q34, 2] -> - 1 = y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q34, 2, q75] - | q75 : int(1..2)]) - /\ - or([q78 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q34, 2] /\ - y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q34, 2, q78] = 1 - | q78 : int(1..2)]) - | 1 = q34]), - and([and([q75 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q34, 3] -> false - | q75 : int(1..2)]) - | 1 = q34]); - int(1..3)]) - /\ - and([and([and([q80 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q34, 1] -> - 1 = y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q34, 1, q80] \/ - 2 = y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q34, 1, q80] - | q80 : int(1..2)]) - /\ - (or([q83 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q34, 1] /\ - y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q34, 1, q83] = 1 - | q83 : int(1..2)]) - /\ - or([q83 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q34, 1] /\ - y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q34, 1, q83] = 2 - | q83 : int(1..2)])) - | 2 = q34]), - and([and([q80 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q34, 2] -> - 1 = y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q34, 2, q80] - | q80 : int(1..2)]) - /\ - or([q83 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q34, 2] /\ - y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q34, 2, q83] = 1 - | q83 : int(1..2)]) - | 2 = q34]), - and([and([q80 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q34, 3] -> false - | q80 : int(1..2)]) - | 2 = q34]); - int(1..3)])), - y_1_3[q34] = [33, 55; int(1..2)][q34]; - int(1..3)]) - | q34 : int(1, 2)]), - and([and([2 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q1, q2] -> - y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q1, q2, 1] < - y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q1, q2, 2] - | q2 : int(1..3)]) - | q1 : int(1, 2)]), - and([and([and([q4 > y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q1, q2] -> - y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q1, q2, q4] = 1 - | q4 : int(1..2)]) - | q2 : int(1..3)]) - | q1 : int(1, 2)]), - and([and([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q6, q7, 2] -> - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q6, q7, 1] < - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q6, q7, 2] - | q7 : int(1..3)]) - | q6 : int(1, 2)]), - and([and([and([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q6, q7, q9] = false -> - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q6, q7, q9] = 1 - | q9 : int(1..2)]) - | q7 : int(1..3)]) - | q6 : int(1, 2)]), - and([and([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q6, q7, 2] -> - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q6, q7, 1] - | q7 : int(1..3)]) - | q6 : int(1, 2)]), - and([and([y_1_1[q13] = y_1_1[q13], - and([and([q18 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q13, q16] -> - or([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q13, q16, q20] /\ - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q13, q16, q20] = - y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q13, q16, q18] - | q20 : int(1..2)]) - | q18 : int(1..2)]) - /\ - and([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q13, q16, q22] -> - or([q24 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q13, q16] /\ - y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q13, q16, q24] = - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q13, q16, q22] - | q24 : int(1..2)]) - | q22 : int(1..2)]) - | q16 : int(1..3)]) - /\ - and([and([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q13, q25, q27] -> - or([q29 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q13, q25] /\ - y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q13, q25, q29] = - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q13, q25, q27] - | q29 : int(1..2)]) - | q27 : int(1..2)]) - /\ - and([q31 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q13, q25] -> - or([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q13, q25, q33] /\ - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q13, q25, q33] = - y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q13, q25, q31] - | q33 : int(1..2)]) - | q31 : int(1..2)]) - | q25 : int(1..3)]), - y_1_3[q13] = y_1_3[q13]; - int(1..3)]) - | q13 : int(1, 2)]) - diff --git a/tests/exhaustive/issues/166/expected/model_4_1-solution000001.solution b/tests/exhaustive/issues/166/expected/model_4_1-solution000001.solution deleted file mode 100644 index 15cf35802e..0000000000 --- a/tests/exhaustive/issues/166/expected/model_4_1-solution000001.solution +++ /dev/null @@ -1,6 +0,0 @@ -language Essence 1.3 - -letting y be - tuple ([(10, function(1 --> {1, 2}, 2 --> {1}, 3 --> {}), 33), - (11, function(1 --> {1, 2}, 2 --> {1}, 3 --> {}), 55); - int(1..2)]) diff --git a/tests/exhaustive/issues/166/expected/model_4_1.eprime b/tests/exhaustive/issues/166/expected/model_4_1.eprime deleted file mode 100644 index 1db6241ec8..0000000000 --- a/tests/exhaustive/issues/166/expected/model_4_1.eprime +++ /dev/null @@ -1,154 +0,0 @@ -language ESSENCE' 1.0 - -find y_1_1: matrix indexed by [int(1, 2)] of int(10, 11) -find y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1, 2), int(1..3), int(1..2)] of bool -find y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values: - matrix indexed by [int(1, 2), int(1..3), int(1..2)] of int(1, 2) -find y_1_3: matrix indexed by [int(1, 2)] of int(33, 55) -find y_1_2_Function1DR2_Occurrence: matrix indexed by [int(1, 2), int(1..3), int(1, 2)] of bool -branching on - [y_1_1, y_1_2_Function1DR2_Occurrence, y_1_3, y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags, - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values] -such that - and([and([y_1_1[q11] = [10, 11; int(1..2)][q11], - and([and([or([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q11, q14, q22] /\ - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q11, q14, q22] = 1 - | q22 : int(1..2)]) - | 1 = q11, 1 = q14]) - /\ - and([or([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q11, q14, q24] /\ - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q11, q14, q24] = 2 - | q24 : int(1..2)]) - | 1 = q11, 1 = q14]) - /\ - and([or([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q11, q14, q27] /\ - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q11, q14, q27] = 1 - | q27 : int(1..2)]) - | 1 = q11, 2 = q14]) - /\ - (and([or([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q11, q14, q32] /\ - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q11, q14, q32] = 1 - | q32 : int(1..2)]) - | 2 = q11, 1 = q14]) - /\ - and([or([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q11, q14, q34] /\ - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q11, q14, q34] = 2 - | q34 : int(1..2)]) - | 2 = q11, 1 = q14]) - /\ - and([or([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q11, q14, q37] /\ - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q11, q14, q37] = 1 - | q37 : int(1..2)]) - | 2 = q11, 2 = q14])) - /\ - and([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q11, q14, q39] -> - or([1 = y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q11, q14, q39] | 1 = q11, 1 = q14]) - \/ - or([2 = y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q11, q14, q39] | 1 = q11, 1 = q14]) - \/ - or([1 = y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q11, q14, q39] | 1 = q11, 2 = q14]) - \/ - (or([1 = y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q11, q14, q39] | 2 = q11, 1 = q14]) - \/ - or([2 = y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q11, q14, q39] | 2 = q11, 1 = q14]) - \/ - or([1 = y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q11, q14, q39] | 2 = q11, 2 = q14])) - | q39 : int(1..2)]) - | q14 : int(1..3)]) - /\ - (and([and([and([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q11, 1, q52] -> - 1 = y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q11, 1, q52] \/ - 2 = y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q11, 1, q52] - | q52 : int(1..2)]) - /\ - (or([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q11, 1, q55] /\ - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q11, 1, q55] = 1 - | q55 : int(1..2)]) - /\ - or([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q11, 1, q55] /\ - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q11, 1, q55] = 2 - | q55 : int(1..2)])) - | 1 = q11]), - and([and([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q11, 2, q52] -> - 1 = y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q11, 2, q52] - | q52 : int(1..2)]) - /\ - or([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q11, 2, q55] /\ - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q11, 2, q55] = 1 - | q55 : int(1..2)]) - | 1 = q11]), - and([and([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q11, 3, q52] -> false - | q52 : int(1..2)]) - | 1 = q11]); - int(1..3)]) - /\ - and([and([and([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q11, 1, q57] -> - 1 = y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q11, 1, q57] \/ - 2 = y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q11, 1, q57] - | q57 : int(1..2)]) - /\ - (or([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q11, 1, q60] /\ - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q11, 1, q60] = 1 - | q60 : int(1..2)]) - /\ - or([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q11, 1, q60] /\ - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q11, 1, q60] = 2 - | q60 : int(1..2)])) - | 2 = q11]), - and([and([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q11, 2, q57] -> - 1 = y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q11, 2, q57] - | q57 : int(1..2)]) - /\ - or([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q11, 2, q60] /\ - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q11, 2, q60] = 1 - | q60 : int(1..2)]) - | 2 = q11]), - and([and([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q11, 3, q57] -> false - | q57 : int(1..2)]) - | 2 = q11]); - int(1..3)])), - y_1_3[q11] = [33, 55; int(1..2)][q11]; - int(1..3)]) - | q11 : int(1, 2)]), - and([and([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q1, q2, 2] -> - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q1, q2, 1] < - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q1, q2, 2] - | q2 : int(1..3)]) - | q1 : int(1, 2)]), - and([and([and([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q1, q2, q4] = false -> - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q1, q2, q4] = 1 - | q4 : int(1..2)]) - | q2 : int(1..3)]) - | q1 : int(1, 2)]), - and([and([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q1, q2, 2] -> - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q1, q2, 1] - | q2 : int(1..3)]) - | q1 : int(1, 2)]), - and([and([y_1_1[q77] = y_1_1[q77], - and([and([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q77, q80, q82] -> - y_1_2_Function1DR2_Occurrence - [q77, q80, y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q77, q80, q82]] - | q82 : int(1..2)]) - /\ - and([y_1_2_Function1DR2_Occurrence[q77, q80, q83] -> - or([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q77, q80, q85] /\ - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q77, q80, q85] = q83 - | q85 : int(1..2)]) - | q83 : int(1, 2)]) - | q80 : int(1..3)]) - /\ - and([and([y_1_2_Function1DR2_Occurrence[q77, q86, q87] -> - or([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q77, q86, q89] /\ - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q77, q86, q89] = q87 - | q89 : int(1..2)]) - | q87 : int(1, 2)]) - /\ - and([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q77, q86, q91] -> - y_1_2_Function1DR2_Occurrence - [q77, q86, y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q77, q86, q91]] - | q91 : int(1..2)]) - | q86 : int(1..3)]), - y_1_3[q77] = y_1_3[q77]; - int(1..3)]) - | q77 : int(1, 2)]) - diff --git a/tests/exhaustive/issues/166/expected/model_4_2-solution000001.solution b/tests/exhaustive/issues/166/expected/model_4_2-solution000001.solution deleted file mode 100644 index 15cf35802e..0000000000 --- a/tests/exhaustive/issues/166/expected/model_4_2-solution000001.solution +++ /dev/null @@ -1,6 +0,0 @@ -language Essence 1.3 - -letting y be - tuple ([(10, function(1 --> {1, 2}, 2 --> {1}, 3 --> {}), 33), - (11, function(1 --> {1, 2}, 2 --> {1}, 3 --> {}), 55); - int(1..2)]) diff --git a/tests/exhaustive/issues/166/expected/model_4_2.eprime b/tests/exhaustive/issues/166/expected/model_4_2.eprime deleted file mode 100644 index e4f42b1419..0000000000 --- a/tests/exhaustive/issues/166/expected/model_4_2.eprime +++ /dev/null @@ -1,169 +0,0 @@ -language ESSENCE' 1.0 - -find y_1_1: matrix indexed by [int(1, 2)] of int(10, 11) -find y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1, 2), int(1..3), int(1..2)] of bool -find y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values: - matrix indexed by [int(1, 2), int(1..3), int(1..2)] of int(1, 2) -find y_1_3: matrix indexed by [int(1, 2)] of int(33, 55) -find y_1_2_Function1DR6_ExplicitVarSizeWithDummy: matrix indexed by [int(1, 2), int(1..3), int(1..2)] of int(1, 2, 3) -branching on - [y_1_1, y_1_2_Function1DR6_ExplicitVarSizeWithDummy, y_1_3, y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags, - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values] -such that - and([and([y_1_1[q35] = [10, 11; int(1..2)][q35], - and([and([or([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q35, q38, q46] /\ - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q35, q38, q46] = 1 - | q46 : int(1..2)]) - | 1 = q35, 1 = q38]) - /\ - and([or([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q35, q38, q48] /\ - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q35, q38, q48] = 2 - | q48 : int(1..2)]) - | 1 = q35, 1 = q38]) - /\ - and([or([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q35, q38, q51] /\ - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q35, q38, q51] = 1 - | q51 : int(1..2)]) - | 1 = q35, 2 = q38]) - /\ - (and([or([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q35, q38, q56] /\ - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q35, q38, q56] = 1 - | q56 : int(1..2)]) - | 2 = q35, 1 = q38]) - /\ - and([or([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q35, q38, q58] /\ - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q35, q38, q58] = 2 - | q58 : int(1..2)]) - | 2 = q35, 1 = q38]) - /\ - and([or([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q35, q38, q61] /\ - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q35, q38, q61] = 1 - | q61 : int(1..2)]) - | 2 = q35, 2 = q38])) - /\ - and([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q35, q38, q63] -> - or([1 = y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q35, q38, q63] | 1 = q35, 1 = q38]) - \/ - or([2 = y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q35, q38, q63] | 1 = q35, 1 = q38]) - \/ - or([1 = y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q35, q38, q63] | 1 = q35, 2 = q38]) - \/ - (or([1 = y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q35, q38, q63] | 2 = q35, 1 = q38]) - \/ - or([2 = y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q35, q38, q63] | 2 = q35, 1 = q38]) - \/ - or([1 = y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q35, q38, q63] | 2 = q35, 2 = q38])) - | q63 : int(1..2)]) - | q38 : int(1..3)]) - /\ - (and([and([and([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q35, 1, q76] -> - 1 = y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q35, 1, q76] \/ - 2 = y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q35, 1, q76] - | q76 : int(1..2)]) - /\ - (or([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q35, 1, q79] /\ - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q35, 1, q79] = 1 - | q79 : int(1..2)]) - /\ - or([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q35, 1, q79] /\ - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q35, 1, q79] = 2 - | q79 : int(1..2)])) - | 1 = q35]), - and([and([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q35, 2, q76] -> - 1 = y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q35, 2, q76] - | q76 : int(1..2)]) - /\ - or([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q35, 2, q79] /\ - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q35, 2, q79] = 1 - | q79 : int(1..2)]) - | 1 = q35]), - and([and([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q35, 3, q76] -> false - | q76 : int(1..2)]) - | 1 = q35]); - int(1..3)]) - /\ - and([and([and([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q35, 1, q81] -> - 1 = y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q35, 1, q81] \/ - 2 = y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q35, 1, q81] - | q81 : int(1..2)]) - /\ - (or([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q35, 1, q84] /\ - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q35, 1, q84] = 1 - | q84 : int(1..2)]) - /\ - or([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q35, 1, q84] /\ - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q35, 1, q84] = 2 - | q84 : int(1..2)])) - | 2 = q35]), - and([and([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q35, 2, q81] -> - 1 = y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q35, 2, q81] - | q81 : int(1..2)]) - /\ - or([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q35, 2, q84] /\ - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q35, 2, q84] = 1 - | q84 : int(1..2)]) - | 2 = q35]), - and([and([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q35, 3, q81] -> false - | q81 : int(1..2)]) - | 2 = q35]); - int(1..3)])), - y_1_3[q35] = [33, 55; int(1..2)][q35]; - int(1..3)]) - | q35 : int(1, 2)]), - and([and([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q1, q2, 2] -> - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q1, q2, 1] < - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q1, q2, 2] - | q2 : int(1..3)]) - | q1 : int(1, 2)]), - and([and([and([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q1, q2, q4] = false -> - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q1, q2, q4] = 1 - | q4 : int(1..2)]) - | q2 : int(1..3)]) - | q1 : int(1, 2)]), - and([and([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q1, q2, 2] -> - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q1, q2, 1] - | q2 : int(1..3)]) - | q1 : int(1, 2)]), - and([and([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q8, q9, 1] < - y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q8, q9, 2] - \/ y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q8, q9, 1] = 3 - | q9 : int(1..3)]) - | q8 : int(1, 2)]), - and([and([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q8, q9, 1] = 3 -> - y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q8, q9, 2] = 3 - | q9 : int(1..3)]) - | q8 : int(1, 2)]), - and([and([y_1_1[q14] = y_1_1[q14], - and([and([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q14, q17, q19] -> - or([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q14, q17, q21] != 3 /\ - y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q14, q17, q21] = - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q14, q17, q19] - | q21 : int(1..2)]) - | q19 : int(1..2)]) - /\ - and([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q14, q17, q23] != 3 -> - or([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q14, q17, q25] /\ - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q14, q17, q25] = - y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q14, q17, q23] - | q25 : int(1..2)]) - | q23 : int(1..2)]) - | q17 : int(1..3)]) - /\ - and([and([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q14, q26, q28] != 3 -> - or([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q14, q26, q30] /\ - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q14, q26, q30] = - y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q14, q26, q28] - | q30 : int(1..2)]) - | q28 : int(1..2)]) - /\ - and([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q14, q26, q32] -> - or([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q14, q26, q34] != 3 /\ - y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q14, q26, q34] = - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q14, q26, q32] - | q34 : int(1..2)]) - | q32 : int(1..2)]) - | q26 : int(1..3)]), - y_1_3[q14] = y_1_3[q14]; - int(1..3)]) - | q14 : int(1, 2)]) - diff --git a/tests/exhaustive/issues/166/expected/model_4_3-solution000001.solution b/tests/exhaustive/issues/166/expected/model_4_3-solution000001.solution deleted file mode 100644 index 15cf35802e..0000000000 --- a/tests/exhaustive/issues/166/expected/model_4_3-solution000001.solution +++ /dev/null @@ -1,6 +0,0 @@ -language Essence 1.3 - -letting y be - tuple ([(10, function(1 --> {1, 2}, 2 --> {1}, 3 --> {}), 33), - (11, function(1 --> {1, 2}, 2 --> {1}, 3 --> {}), 55); - int(1..2)]) diff --git a/tests/exhaustive/issues/166/expected/model_4_3.eprime b/tests/exhaustive/issues/166/expected/model_4_3.eprime deleted file mode 100644 index 9ac5e3f0e2..0000000000 --- a/tests/exhaustive/issues/166/expected/model_4_3.eprime +++ /dev/null @@ -1,172 +0,0 @@ -language ESSENCE' 1.0 - -find y_1_1: matrix indexed by [int(1, 2)] of int(10, 11) -find y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1, 2), int(1..3), int(1..2)] of bool -find y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values: - matrix indexed by [int(1, 2), int(1..3), int(1..2)] of int(1, 2) -find y_1_3: matrix indexed by [int(1, 2)] of int(33, 55) -find y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker: matrix indexed by [int(1, 2), int(1..3)] of int(0..2) -find y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values: - matrix indexed by [int(1, 2), int(1..3), int(1..2)] of int(1, 2) -branching on - [y_1_1, y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker, y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values, - y_1_3, y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags, y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values] -such that - and([and([y_1_1[q34] = [10, 11; int(1..2)][q34], - and([and([or([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q34, q37, q45] /\ - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q34, q37, q45] = 1 - | q45 : int(1..2)]) - | 1 = q34, 1 = q37]) - /\ - and([or([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q34, q37, q47] /\ - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q34, q37, q47] = 2 - | q47 : int(1..2)]) - | 1 = q34, 1 = q37]) - /\ - and([or([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q34, q37, q50] /\ - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q34, q37, q50] = 1 - | q50 : int(1..2)]) - | 1 = q34, 2 = q37]) - /\ - (and([or([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q34, q37, q55] /\ - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q34, q37, q55] = 1 - | q55 : int(1..2)]) - | 2 = q34, 1 = q37]) - /\ - and([or([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q34, q37, q57] /\ - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q34, q37, q57] = 2 - | q57 : int(1..2)]) - | 2 = q34, 1 = q37]) - /\ - and([or([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q34, q37, q60] /\ - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q34, q37, q60] = 1 - | q60 : int(1..2)]) - | 2 = q34, 2 = q37])) - /\ - and([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q34, q37, q62] -> - or([1 = y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q34, q37, q62] | 1 = q34, 1 = q37]) - \/ - or([2 = y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q34, q37, q62] | 1 = q34, 1 = q37]) - \/ - or([1 = y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q34, q37, q62] | 1 = q34, 2 = q37]) - \/ - (or([1 = y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q34, q37, q62] | 2 = q34, 1 = q37]) - \/ - or([2 = y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q34, q37, q62] | 2 = q34, 1 = q37]) - \/ - or([1 = y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q34, q37, q62] | 2 = q34, 2 = q37])) - | q62 : int(1..2)]) - | q37 : int(1..3)]) - /\ - (and([and([and([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q34, 1, q75] -> - 1 = y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q34, 1, q75] \/ - 2 = y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q34, 1, q75] - | q75 : int(1..2)]) - /\ - (or([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q34, 1, q78] /\ - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q34, 1, q78] = 1 - | q78 : int(1..2)]) - /\ - or([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q34, 1, q78] /\ - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q34, 1, q78] = 2 - | q78 : int(1..2)])) - | 1 = q34]), - and([and([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q34, 2, q75] -> - 1 = y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q34, 2, q75] - | q75 : int(1..2)]) - /\ - or([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q34, 2, q78] /\ - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q34, 2, q78] = 1 - | q78 : int(1..2)]) - | 1 = q34]), - and([and([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q34, 3, q75] -> false - | q75 : int(1..2)]) - | 1 = q34]); - int(1..3)]) - /\ - and([and([and([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q34, 1, q80] -> - 1 = y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q34, 1, q80] \/ - 2 = y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q34, 1, q80] - | q80 : int(1..2)]) - /\ - (or([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q34, 1, q83] /\ - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q34, 1, q83] = 1 - | q83 : int(1..2)]) - /\ - or([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q34, 1, q83] /\ - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q34, 1, q83] = 2 - | q83 : int(1..2)])) - | 2 = q34]), - and([and([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q34, 2, q80] -> - 1 = y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q34, 2, q80] - | q80 : int(1..2)]) - /\ - or([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q34, 2, q83] /\ - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q34, 2, q83] = 1 - | q83 : int(1..2)]) - | 2 = q34]), - and([and([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q34, 3, q80] -> false - | q80 : int(1..2)]) - | 2 = q34]); - int(1..3)])), - y_1_3[q34] = [33, 55; int(1..2)][q34]; - int(1..3)]) - | q34 : int(1, 2)]), - and([and([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q1, q2, 2] -> - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q1, q2, 1] < - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q1, q2, 2] - | q2 : int(1..3)]) - | q1 : int(1, 2)]), - and([and([and([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q1, q2, q4] = false -> - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q1, q2, q4] = 1 - | q4 : int(1..2)]) - | q2 : int(1..3)]) - | q1 : int(1, 2)]), - and([and([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q1, q2, 2] -> - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q1, q2, 1] - | q2 : int(1..3)]) - | q1 : int(1, 2)]), - and([and([2 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q8, q9] -> - y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q8, q9, 1] < - y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q8, q9, 2] - | q9 : int(1..3)]) - | q8 : int(1, 2)]), - and([and([and([q11 > y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q8, q9] -> - y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q8, q9, q11] = 1 - | q11 : int(1..2)]) - | q9 : int(1..3)]) - | q8 : int(1, 2)]), - and([and([y_1_1[q13] = y_1_1[q13], - and([and([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q13, q16, q18] -> - or([q20 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q13, q16] /\ - y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q13, q16, q20] = - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q13, q16, q18] - | q20 : int(1..2)]) - | q18 : int(1..2)]) - /\ - and([q22 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q13, q16] -> - or([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q13, q16, q24] /\ - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q13, q16, q24] = - y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q13, q16, q22] - | q24 : int(1..2)]) - | q22 : int(1..2)]) - | q16 : int(1..3)]) - /\ - and([and([q27 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q13, q25] -> - or([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q13, q25, q29] /\ - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q13, q25, q29] = - y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q13, q25, q27] - | q29 : int(1..2)]) - | q27 : int(1..2)]) - /\ - and([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q13, q25, q31] -> - or([q33 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q13, q25] /\ - y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q13, q25, q33] = - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q13, q25, q31] - | q33 : int(1..2)]) - | q31 : int(1..2)]) - | q25 : int(1..3)]), - y_1_3[q13] = y_1_3[q13]; - int(1..3)]) - | q13 : int(1, 2)]) - diff --git a/tests/exhaustive/issues/166/expected/model_4_4-solution000001.solution b/tests/exhaustive/issues/166/expected/model_4_4-solution000001.solution deleted file mode 100644 index 15cf35802e..0000000000 --- a/tests/exhaustive/issues/166/expected/model_4_4-solution000001.solution +++ /dev/null @@ -1,6 +0,0 @@ -language Essence 1.3 - -letting y be - tuple ([(10, function(1 --> {1, 2}, 2 --> {1}, 3 --> {}), 33), - (11, function(1 --> {1, 2}, 2 --> {1}, 3 --> {}), 55); - int(1..2)]) diff --git a/tests/exhaustive/issues/166/expected/model_4_4.eprime b/tests/exhaustive/issues/166/expected/model_4_4.eprime deleted file mode 100644 index 49fbce5a24..0000000000 --- a/tests/exhaustive/issues/166/expected/model_4_4.eprime +++ /dev/null @@ -1,121 +0,0 @@ -language ESSENCE' 1.0 - -find y_1_1: matrix indexed by [int(1, 2)] of int(10, 11) -find y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1, 2), int(1..3), int(1..2)] of bool -find y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values: - matrix indexed by [int(1, 2), int(1..3), int(1..2)] of int(1, 2) -find y_1_3: matrix indexed by [int(1, 2)] of int(33, 55) -branching on - [y_1_1, y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags, y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values, - y_1_3] -such that - and([and([y_1_1[q8] = [10, 11; int(1..2)][q8], - and([and([or([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q8, q11, q19] /\ - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q8, q11, q19] = 1 - | q19 : int(1..2)]) - | 1 = q8, 1 = q11]) - /\ - and([or([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q8, q11, q21] /\ - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q8, q11, q21] = 2 - | q21 : int(1..2)]) - | 1 = q8, 1 = q11]) - /\ - and([or([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q8, q11, q24] /\ - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q8, q11, q24] = 1 - | q24 : int(1..2)]) - | 1 = q8, 2 = q11]) - /\ - (and([or([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q8, q11, q29] /\ - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q8, q11, q29] = 1 - | q29 : int(1..2)]) - | 2 = q8, 1 = q11]) - /\ - and([or([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q8, q11, q31] /\ - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q8, q11, q31] = 2 - | q31 : int(1..2)]) - | 2 = q8, 1 = q11]) - /\ - and([or([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q8, q11, q34] /\ - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q8, q11, q34] = 1 - | q34 : int(1..2)]) - | 2 = q8, 2 = q11])) - /\ - and([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q8, q11, q36] -> - or([1 = y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q8, q11, q36] | 1 = q8, 1 = q11]) \/ - or([2 = y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q8, q11, q36] | 1 = q8, 1 = q11]) - \/ or([1 = y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q8, q11, q36] | 1 = q8, 2 = q11]) - \/ - (or([1 = y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q8, q11, q36] | 2 = q8, 1 = q11]) \/ - or([2 = y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q8, q11, q36] | 2 = q8, 1 = q11]) - \/ - or([1 = y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q8, q11, q36] | 2 = q8, 2 = q11])) - | q36 : int(1..2)]) - | q11 : int(1..3)]) - /\ - (and([and([and([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q8, 1, q49] -> - 1 = y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q8, 1, q49] \/ - 2 = y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q8, 1, q49] - | q49 : int(1..2)]) - /\ - (or([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q8, 1, q52] /\ - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q8, 1, q52] = 1 - | q52 : int(1..2)]) - /\ - or([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q8, 1, q52] /\ - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q8, 1, q52] = 2 - | q52 : int(1..2)])) - | 1 = q8]), - and([and([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q8, 2, q49] -> - 1 = y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q8, 2, q49] - | q49 : int(1..2)]) - /\ - or([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q8, 2, q52] /\ - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q8, 2, q52] = 1 - | q52 : int(1..2)]) - | 1 = q8]), - and([and([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q8, 3, q49] -> false | q49 : int(1..2)]) - | 1 = q8]); - int(1..3)]) - /\ - and([and([and([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q8, 1, q54] -> - 1 = y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q8, 1, q54] \/ - 2 = y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q8, 1, q54] - | q54 : int(1..2)]) - /\ - (or([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q8, 1, q57] /\ - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q8, 1, q57] = 1 - | q57 : int(1..2)]) - /\ - or([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q8, 1, q57] /\ - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q8, 1, q57] = 2 - | q57 : int(1..2)])) - | 2 = q8]), - and([and([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q8, 2, q54] -> - 1 = y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q8, 2, q54] - | q54 : int(1..2)]) - /\ - or([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q8, 2, q57] /\ - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q8, 2, q57] = 1 - | q57 : int(1..2)]) - | 2 = q8]), - and([and([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q8, 3, q54] -> false | q54 : int(1..2)]) - | 2 = q8]); - int(1..3)])), - y_1_3[q8] = [33, 55; int(1..2)][q8]; - int(1..3)]) - | q8 : int(1, 2)]), - and([and([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q1, q2, 2] -> - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q1, q2, 1] < - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q1, q2, 2] - | q2 : int(1..3)]) - | q1 : int(1, 2)]), - and([and([and([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q1, q2, q4] = false -> - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q1, q2, q4] = 1 - | q4 : int(1..2)]) - | q2 : int(1..3)]) - | q1 : int(1, 2)]), - and([and([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q1, q2, 2] -> - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q1, q2, 1] - | q2 : int(1..3)]) - | q1 : int(1, 2)]) - diff --git a/tests/exhaustive/issues/212/expected/model_1_1-1-solution000001.solution b/tests/exhaustive/issues/212/expected/model_1_1-1-solution000001.solution deleted file mode 100644 index de5cc861ad..0000000000 --- a/tests/exhaustive/issues/212/expected/model_1_1-1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1} diff --git a/tests/exhaustive/issues/212/expected/model_1_1-1.eprime-param b/tests/exhaustive/issues/212/expected/model_1_1-1.eprime-param deleted file mode 100644 index c50b6e81fd..0000000000 --- a/tests/exhaustive/issues/212/expected/model_1_1-1.eprime-param +++ /dev/null @@ -1,6 +0,0 @@ -language ESSENCE' 1.0 - -letting a_Explicit be [1, 2; int(1..2)] -letting b_Explicit be [1, 3; int(1..2)] -letting fin1 be 2 -letting fin2 be 2 diff --git a/tests/exhaustive/issues/212/expected/model_1_1.eprime b/tests/exhaustive/issues/212/expected/model_1_1.eprime deleted file mode 100644 index 7d498e9f22..0000000000 --- a/tests/exhaustive/issues/212/expected/model_1_1.eprime +++ /dev/null @@ -1,14 +0,0 @@ -language ESSENCE' 1.0 - -given fin1: int -given a_Explicit: matrix indexed by [int(1..fin1)] of int(0..5) -given fin2: int -given b_Explicit: matrix indexed by [int(1..fin2)] of int(0..5) -find x_Occurrence: matrix indexed by [int(0..5)] of bool -branching on [x_Occurrence] -such that - and([x_Occurrence[q2] -> - or([a_Explicit[q4] = q2 | q4 : int(1..fin1), or([b_Explicit[q6] = a_Explicit[q4] | q6 : int(1..fin2)])]) - | q2 : int(0..5)]), - and([x_Occurrence[a_Explicit[q8]] | q8 : int(1..fin1), or([b_Explicit[q10] = a_Explicit[q8] | q10 : int(1..fin2)])]) - diff --git a/tests/exhaustive/issues/212/expected/model_1_2-1-solution000001.solution b/tests/exhaustive/issues/212/expected/model_1_2-1-solution000001.solution deleted file mode 100644 index de5cc861ad..0000000000 --- a/tests/exhaustive/issues/212/expected/model_1_2-1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1} diff --git a/tests/exhaustive/issues/212/expected/model_1_2-1.eprime-param b/tests/exhaustive/issues/212/expected/model_1_2-1.eprime-param deleted file mode 100644 index c50b6e81fd..0000000000 --- a/tests/exhaustive/issues/212/expected/model_1_2-1.eprime-param +++ /dev/null @@ -1,6 +0,0 @@ -language ESSENCE' 1.0 - -letting a_Explicit be [1, 2; int(1..2)] -letting b_Explicit be [1, 3; int(1..2)] -letting fin1 be 2 -letting fin2 be 2 diff --git a/tests/exhaustive/issues/212/expected/model_1_2.eprime b/tests/exhaustive/issues/212/expected/model_1_2.eprime deleted file mode 100644 index f65c809e22..0000000000 --- a/tests/exhaustive/issues/212/expected/model_1_2.eprime +++ /dev/null @@ -1,23 +0,0 @@ -language ESSENCE' 1.0 - -given fin1: int -given a_Explicit: matrix indexed by [int(1..fin1)] of int(0..5) -given fin2: int -given b_Explicit: matrix indexed by [int(1..fin2)] of int(0..5) -find x_Occurrence: matrix indexed by [int(0..5)] of bool -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..6)] of int(0..6) -branching on [x_ExplicitVarSizeWithDummy, x_Occurrence] -such that - and([x_Occurrence[q11] -> - or([a_Explicit[q13] = q11 | q13 : int(1..fin1), or([b_Explicit[q15] = a_Explicit[q13] | q15 : int(1..fin2)])]) - | q11 : int(0..5)]), - and([x_Occurrence[a_Explicit[q17]] - | q17 : int(1..fin1), or([b_Explicit[q19] = a_Explicit[q17] | q19 : int(1..fin2)])]), - and([x_ExplicitVarSizeWithDummy[q2] < x_ExplicitVarSizeWithDummy[q2 + 1] \/ x_ExplicitVarSizeWithDummy[q2] = 6 - | q2 : int(1..5)]), - and([x_ExplicitVarSizeWithDummy[q3] = 6 -> x_ExplicitVarSizeWithDummy[q3 + 1] = 6 | q3 : int(1..5)]), - and([x_ExplicitVarSizeWithDummy[q7] != 6 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q7]] | q7 : int(1..6)]), - and([x_Occurrence[q8] -> - or([x_ExplicitVarSizeWithDummy[q10] != 6 /\ x_ExplicitVarSizeWithDummy[q10] = q8 | q10 : int(1..6)]) - | q8 : int(0..5)]) - diff --git a/tests/exhaustive/issues/212/expected/model_1_3-1-solution000001.solution b/tests/exhaustive/issues/212/expected/model_1_3-1-solution000001.solution deleted file mode 100644 index de5cc861ad..0000000000 --- a/tests/exhaustive/issues/212/expected/model_1_3-1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1} diff --git a/tests/exhaustive/issues/212/expected/model_1_3-1.eprime-param b/tests/exhaustive/issues/212/expected/model_1_3-1.eprime-param deleted file mode 100644 index c50b6e81fd..0000000000 --- a/tests/exhaustive/issues/212/expected/model_1_3-1.eprime-param +++ /dev/null @@ -1,6 +0,0 @@ -language ESSENCE' 1.0 - -letting a_Explicit be [1, 2; int(1..2)] -letting b_Explicit be [1, 3; int(1..2)] -letting fin1 be 2 -letting fin2 be 2 diff --git a/tests/exhaustive/issues/212/expected/model_1_3.eprime b/tests/exhaustive/issues/212/expected/model_1_3.eprime deleted file mode 100644 index 801bf91d9f..0000000000 --- a/tests/exhaustive/issues/212/expected/model_1_3.eprime +++ /dev/null @@ -1,26 +0,0 @@ -language ESSENCE' 1.0 - -given fin1: int -given a_Explicit: matrix indexed by [int(1..fin1)] of int(0..5) -given fin2: int -given b_Explicit: matrix indexed by [int(1..fin2)] of int(0..5) -find x_Occurrence: matrix indexed by [int(0..5)] of bool -find x_ExplicitVarSizeWithMarker_Marker: int(0..6) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..6)] of int(0..5) -branching on [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_Occurrence] -such that - and([x_Occurrence[q10] -> - or([a_Explicit[q12] = q10 | q12 : int(1..fin1), or([b_Explicit[q14] = a_Explicit[q12] | q14 : int(1..fin2)])]) - | q10 : int(0..5)]), - and([x_Occurrence[a_Explicit[q16]] - | q16 : int(1..fin1), or([b_Explicit[q18] = a_Explicit[q16] | q18 : int(1..fin2)])]), - and([q2 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q2] < x_ExplicitVarSizeWithMarker_Values[q2 + 1] - | q2 : int(1..5)]), - and([q3 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q3] = 0 | q3 : int(1..6)]), - and([q6 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q6]] - | q6 : int(1..6)]), - and([x_Occurrence[q7] -> - or([q9 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q9] = q7 | q9 : int(1..6)]) - | q7 : int(0..5)]) - diff --git a/tests/exhaustive/issues/212/expected/model_1_4-1-solution000001.solution b/tests/exhaustive/issues/212/expected/model_1_4-1-solution000001.solution deleted file mode 100644 index de5cc861ad..0000000000 --- a/tests/exhaustive/issues/212/expected/model_1_4-1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1} diff --git a/tests/exhaustive/issues/212/expected/model_1_4-1.eprime-param b/tests/exhaustive/issues/212/expected/model_1_4-1.eprime-param deleted file mode 100644 index c50b6e81fd..0000000000 --- a/tests/exhaustive/issues/212/expected/model_1_4-1.eprime-param +++ /dev/null @@ -1,6 +0,0 @@ -language ESSENCE' 1.0 - -letting a_Explicit be [1, 2; int(1..2)] -letting b_Explicit be [1, 3; int(1..2)] -letting fin1 be 2 -letting fin2 be 2 diff --git a/tests/exhaustive/issues/212/expected/model_1_4.eprime b/tests/exhaustive/issues/212/expected/model_1_4.eprime deleted file mode 100644 index ebe5228775..0000000000 --- a/tests/exhaustive/issues/212/expected/model_1_4.eprime +++ /dev/null @@ -1,26 +0,0 @@ -language ESSENCE' 1.0 - -given fin1: int -given a_Explicit: matrix indexed by [int(1..fin1)] of int(0..5) -given fin2: int -given b_Explicit: matrix indexed by [int(1..fin2)] of int(0..5) -find x_Occurrence: matrix indexed by [int(0..5)] of bool -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..6)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..6)] of int(0..5) -branching on [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_Occurrence] -such that - and([x_Occurrence[q12] -> - or([a_Explicit[q14] = q12 | q14 : int(1..fin1), or([b_Explicit[q16] = a_Explicit[q14] | q16 : int(1..fin2)])]) - | q12 : int(0..5)]), - and([x_Occurrence[a_Explicit[q18]] - | q18 : int(1..fin1), or([b_Explicit[q20] = a_Explicit[q18] | q20 : int(1..fin2)])]), - and([x_ExplicitVarSizeWithFlags_Flags[q2 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q2] < x_ExplicitVarSizeWithFlags_Values[q2 + 1] - | q2 : int(1..5)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3] = false -> x_ExplicitVarSizeWithFlags_Values[q3] = 0 | q3 : int(1..6)]), - and([x_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q4] | q4 : int(1..5)]), - and([x_ExplicitVarSizeWithFlags_Flags[q8] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q8]] | q8 : int(1..6)]), - and([x_Occurrence[q9] -> - or([x_ExplicitVarSizeWithFlags_Flags[q11] /\ x_ExplicitVarSizeWithFlags_Values[q11] = q9 | q11 : int(1..6)]) - | q9 : int(0..5)]) - diff --git a/tests/exhaustive/issues/212/expected/model_2_1-1-solution000001.solution b/tests/exhaustive/issues/212/expected/model_2_1-1-solution000001.solution deleted file mode 100644 index de5cc861ad..0000000000 --- a/tests/exhaustive/issues/212/expected/model_2_1-1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1} diff --git a/tests/exhaustive/issues/212/expected/model_2_1-1.eprime-param b/tests/exhaustive/issues/212/expected/model_2_1-1.eprime-param deleted file mode 100644 index c50b6e81fd..0000000000 --- a/tests/exhaustive/issues/212/expected/model_2_1-1.eprime-param +++ /dev/null @@ -1,6 +0,0 @@ -language ESSENCE' 1.0 - -letting a_Explicit be [1, 2; int(1..2)] -letting b_Explicit be [1, 3; int(1..2)] -letting fin1 be 2 -letting fin2 be 2 diff --git a/tests/exhaustive/issues/212/expected/model_2_1.eprime b/tests/exhaustive/issues/212/expected/model_2_1.eprime deleted file mode 100644 index 30e87e71e8..0000000000 --- a/tests/exhaustive/issues/212/expected/model_2_1.eprime +++ /dev/null @@ -1,25 +0,0 @@ -language ESSENCE' 1.0 - -given fin1: int -given a_Explicit: matrix indexed by [int(1..fin1)] of int(0..5) -given fin2: int -given b_Explicit: matrix indexed by [int(1..fin2)] of int(0..5) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..6)] of int(0..6) -find x_Occurrence: matrix indexed by [int(0..5)] of bool -branching on [x_Occurrence, x_ExplicitVarSizeWithDummy] -such that - and([x_ExplicitVarSizeWithDummy[q7] != 6 -> - or([a_Explicit[q9] = x_ExplicitVarSizeWithDummy[q7] - | q9 : int(1..fin1), or([b_Explicit[q11] = a_Explicit[q9] | q11 : int(1..fin2)])]) - | q7 : int(1..6)]), - and([or([x_ExplicitVarSizeWithDummy[q15] != 6 /\ x_ExplicitVarSizeWithDummy[q15] = a_Explicit[q13] - | q15 : int(1..6)]) - | q13 : int(1..fin1), or([b_Explicit[q17] = a_Explicit[q13] | q17 : int(1..fin2)])]), - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 6 - | q1 : int(1..5)]), - and([x_ExplicitVarSizeWithDummy[q2] = 6 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 6 | q2 : int(1..5)]), - and([x_Occurrence[q18] -> - or([x_ExplicitVarSizeWithDummy[q20] != 6 /\ x_ExplicitVarSizeWithDummy[q20] = q18 | q20 : int(1..6)]) - | q18 : int(0..5)]), - and([x_ExplicitVarSizeWithDummy[q22] != 6 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q22]] | q22 : int(1..6)]) - diff --git a/tests/exhaustive/issues/212/expected/model_2_2-1-solution000001.solution b/tests/exhaustive/issues/212/expected/model_2_2-1-solution000001.solution deleted file mode 100644 index de5cc861ad..0000000000 --- a/tests/exhaustive/issues/212/expected/model_2_2-1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1} diff --git a/tests/exhaustive/issues/212/expected/model_2_2-1.eprime-param b/tests/exhaustive/issues/212/expected/model_2_2-1.eprime-param deleted file mode 100644 index c50b6e81fd..0000000000 --- a/tests/exhaustive/issues/212/expected/model_2_2-1.eprime-param +++ /dev/null @@ -1,6 +0,0 @@ -language ESSENCE' 1.0 - -letting a_Explicit be [1, 2; int(1..2)] -letting b_Explicit be [1, 3; int(1..2)] -letting fin1 be 2 -letting fin2 be 2 diff --git a/tests/exhaustive/issues/212/expected/model_2_2.eprime b/tests/exhaustive/issues/212/expected/model_2_2.eprime deleted file mode 100644 index 2046be1123..0000000000 --- a/tests/exhaustive/issues/212/expected/model_2_2.eprime +++ /dev/null @@ -1,20 +0,0 @@ -language ESSENCE' 1.0 - -given fin1: int -given a_Explicit: matrix indexed by [int(1..fin1)] of int(0..5) -given fin2: int -given b_Explicit: matrix indexed by [int(1..fin2)] of int(0..5) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..6)] of int(0..6) -branching on [x_ExplicitVarSizeWithDummy] -such that - and([x_ExplicitVarSizeWithDummy[q6] != 6 -> - or([a_Explicit[q8] = x_ExplicitVarSizeWithDummy[q6] - | q8 : int(1..fin1), or([b_Explicit[q10] = a_Explicit[q8] | q10 : int(1..fin2)])]) - | q6 : int(1..6)]), - and([or([x_ExplicitVarSizeWithDummy[q14] != 6 /\ x_ExplicitVarSizeWithDummy[q14] = a_Explicit[q12] - | q14 : int(1..6)]) - | q12 : int(1..fin1), or([b_Explicit[q16] = a_Explicit[q12] | q16 : int(1..fin2)])]), - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 6 - | q1 : int(1..5)]), - and([x_ExplicitVarSizeWithDummy[q2] = 6 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 6 | q2 : int(1..5)]) - diff --git a/tests/exhaustive/issues/212/expected/model_2_3-1-solution000001.solution b/tests/exhaustive/issues/212/expected/model_2_3-1-solution000001.solution deleted file mode 100644 index de5cc861ad..0000000000 --- a/tests/exhaustive/issues/212/expected/model_2_3-1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1} diff --git a/tests/exhaustive/issues/212/expected/model_2_3-1.eprime-param b/tests/exhaustive/issues/212/expected/model_2_3-1.eprime-param deleted file mode 100644 index c50b6e81fd..0000000000 --- a/tests/exhaustive/issues/212/expected/model_2_3-1.eprime-param +++ /dev/null @@ -1,6 +0,0 @@ -language ESSENCE' 1.0 - -letting a_Explicit be [1, 2; int(1..2)] -letting b_Explicit be [1, 3; int(1..2)] -letting fin1 be 2 -letting fin2 be 2 diff --git a/tests/exhaustive/issues/212/expected/model_2_3.eprime b/tests/exhaustive/issues/212/expected/model_2_3.eprime deleted file mode 100644 index 93e3af90d4..0000000000 --- a/tests/exhaustive/issues/212/expected/model_2_3.eprime +++ /dev/null @@ -1,36 +0,0 @@ -language ESSENCE' 1.0 - -given fin1: int -given a_Explicit: matrix indexed by [int(1..fin1)] of int(0..5) -given fin2: int -given b_Explicit: matrix indexed by [int(1..fin2)] of int(0..5) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..6)] of int(0..6) -find x_ExplicitVarSizeWithMarker_Marker: int(0..6) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..6)] of int(0..5) -branching on [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy] -such that - and([x_ExplicitVarSizeWithDummy[q17] != 6 -> - or([a_Explicit[q19] = x_ExplicitVarSizeWithDummy[q17] - | q19 : int(1..fin1), or([b_Explicit[q21] = a_Explicit[q19] | q21 : int(1..fin2)])]) - | q17 : int(1..6)]), - and([or([x_ExplicitVarSizeWithDummy[q25] != 6 /\ x_ExplicitVarSizeWithDummy[q25] = a_Explicit[q23] - | q25 : int(1..6)]) - | q23 : int(1..fin1), or([b_Explicit[q27] = a_Explicit[q23] | q27 : int(1..fin2)])]), - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 6 - | q1 : int(1..5)]), - and([x_ExplicitVarSizeWithDummy[q2] = 6 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 6 | q2 : int(1..5)]), - and([q5 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q5] < x_ExplicitVarSizeWithMarker_Values[q5 + 1] - | q5 : int(1..5)]), - and([q6 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q6] = 0 | q6 : int(1..6)]), - and([q9 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q11] != 6 /\ - x_ExplicitVarSizeWithDummy[q11] = x_ExplicitVarSizeWithMarker_Values[q9] - | q11 : int(1..6)]) - | q9 : int(1..6)]), - and([x_ExplicitVarSizeWithDummy[q13] != 6 -> - or([q15 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q15] = x_ExplicitVarSizeWithDummy[q13] - | q15 : int(1..6)]) - | q13 : int(1..6)]) - diff --git a/tests/exhaustive/issues/212/expected/model_2_4-1-solution000001.solution b/tests/exhaustive/issues/212/expected/model_2_4-1-solution000001.solution deleted file mode 100644 index de5cc861ad..0000000000 --- a/tests/exhaustive/issues/212/expected/model_2_4-1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1} diff --git a/tests/exhaustive/issues/212/expected/model_2_4-1.eprime-param b/tests/exhaustive/issues/212/expected/model_2_4-1.eprime-param deleted file mode 100644 index c50b6e81fd..0000000000 --- a/tests/exhaustive/issues/212/expected/model_2_4-1.eprime-param +++ /dev/null @@ -1,6 +0,0 @@ -language ESSENCE' 1.0 - -letting a_Explicit be [1, 2; int(1..2)] -letting b_Explicit be [1, 3; int(1..2)] -letting fin1 be 2 -letting fin2 be 2 diff --git a/tests/exhaustive/issues/212/expected/model_2_4.eprime b/tests/exhaustive/issues/212/expected/model_2_4.eprime deleted file mode 100644 index a7493d7565..0000000000 --- a/tests/exhaustive/issues/212/expected/model_2_4.eprime +++ /dev/null @@ -1,37 +0,0 @@ -language ESSENCE' 1.0 - -given fin1: int -given a_Explicit: matrix indexed by [int(1..fin1)] of int(0..5) -given fin2: int -given b_Explicit: matrix indexed by [int(1..fin2)] of int(0..5) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..6)] of int(0..6) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..6)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..6)] of int(0..5) -branching on [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy] -such that - and([x_ExplicitVarSizeWithDummy[q19] != 6 -> - or([a_Explicit[q21] = x_ExplicitVarSizeWithDummy[q19] - | q21 : int(1..fin1), or([b_Explicit[q23] = a_Explicit[q21] | q23 : int(1..fin2)])]) - | q19 : int(1..6)]), - and([or([x_ExplicitVarSizeWithDummy[q27] != 6 /\ x_ExplicitVarSizeWithDummy[q27] = a_Explicit[q25] - | q27 : int(1..6)]) - | q25 : int(1..fin1), or([b_Explicit[q29] = a_Explicit[q25] | q29 : int(1..fin2)])]), - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 6 - | q1 : int(1..5)]), - and([x_ExplicitVarSizeWithDummy[q2] = 6 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 6 | q2 : int(1..5)]), - and([x_ExplicitVarSizeWithFlags_Flags[q5 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q5] < x_ExplicitVarSizeWithFlags_Values[q5 + 1] - | q5 : int(1..5)]), - and([x_ExplicitVarSizeWithFlags_Flags[q6] = false -> x_ExplicitVarSizeWithFlags_Values[q6] = 0 | q6 : int(1..6)]), - and([x_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q7] | q7 : int(1..5)]), - and([x_ExplicitVarSizeWithFlags_Flags[q11] -> - or([x_ExplicitVarSizeWithDummy[q13] != 6 /\ - x_ExplicitVarSizeWithDummy[q13] = x_ExplicitVarSizeWithFlags_Values[q11] - | q13 : int(1..6)]) - | q11 : int(1..6)]), - and([x_ExplicitVarSizeWithDummy[q15] != 6 -> - or([x_ExplicitVarSizeWithFlags_Flags[q17] /\ - x_ExplicitVarSizeWithFlags_Values[q17] = x_ExplicitVarSizeWithDummy[q15] - | q17 : int(1..6)]) - | q15 : int(1..6)]) - diff --git a/tests/exhaustive/issues/212/expected/model_3_1-1-solution000001.solution b/tests/exhaustive/issues/212/expected/model_3_1-1-solution000001.solution deleted file mode 100644 index de5cc861ad..0000000000 --- a/tests/exhaustive/issues/212/expected/model_3_1-1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1} diff --git a/tests/exhaustive/issues/212/expected/model_3_1-1.eprime-param b/tests/exhaustive/issues/212/expected/model_3_1-1.eprime-param deleted file mode 100644 index c50b6e81fd..0000000000 --- a/tests/exhaustive/issues/212/expected/model_3_1-1.eprime-param +++ /dev/null @@ -1,6 +0,0 @@ -language ESSENCE' 1.0 - -letting a_Explicit be [1, 2; int(1..2)] -letting b_Explicit be [1, 3; int(1..2)] -letting fin1 be 2 -letting fin2 be 2 diff --git a/tests/exhaustive/issues/212/expected/model_3_1.eprime b/tests/exhaustive/issues/212/expected/model_3_1.eprime deleted file mode 100644 index 6308f8ed0c..0000000000 --- a/tests/exhaustive/issues/212/expected/model_3_1.eprime +++ /dev/null @@ -1,29 +0,0 @@ -language ESSENCE' 1.0 - -given fin1: int -given a_Explicit: matrix indexed by [int(1..fin1)] of int(0..5) -given fin2: int -given b_Explicit: matrix indexed by [int(1..fin2)] of int(0..5) -find x_ExplicitVarSizeWithMarker_Marker: int(0..6) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..6)] of int(0..5) -find x_Occurrence: matrix indexed by [int(0..5)] of bool -branching on [x_Occurrence, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] -such that - and([q6 <= x_ExplicitVarSizeWithMarker_Marker -> - or([a_Explicit[q8] = x_ExplicitVarSizeWithMarker_Values[q6] - | q8 : int(1..fin1), or([b_Explicit[q10] = a_Explicit[q8] | q10 : int(1..fin2)])]) - | q6 : int(1..6)]), - and([or([q14 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q14] = a_Explicit[q12] - | q14 : int(1..6)]) - | q12 : int(1..fin1), or([b_Explicit[q16] = a_Explicit[q12] | q16 : int(1..fin2)])]), - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..5)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 0 | q2 : int(1..6)]), - and([x_Occurrence[q17] -> - or([q19 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q19] = q17 - | q19 : int(1..6)]) - | q17 : int(0..5)]), - and([q21 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q21]] - | q21 : int(1..6)]) - diff --git a/tests/exhaustive/issues/212/expected/model_3_2-1-solution000001.solution b/tests/exhaustive/issues/212/expected/model_3_2-1-solution000001.solution deleted file mode 100644 index de5cc861ad..0000000000 --- a/tests/exhaustive/issues/212/expected/model_3_2-1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1} diff --git a/tests/exhaustive/issues/212/expected/model_3_2-1.eprime-param b/tests/exhaustive/issues/212/expected/model_3_2-1.eprime-param deleted file mode 100644 index c50b6e81fd..0000000000 --- a/tests/exhaustive/issues/212/expected/model_3_2-1.eprime-param +++ /dev/null @@ -1,6 +0,0 @@ -language ESSENCE' 1.0 - -letting a_Explicit be [1, 2; int(1..2)] -letting b_Explicit be [1, 3; int(1..2)] -letting fin1 be 2 -letting fin2 be 2 diff --git a/tests/exhaustive/issues/212/expected/model_3_2.eprime b/tests/exhaustive/issues/212/expected/model_3_2.eprime deleted file mode 100644 index 364eb0520f..0000000000 --- a/tests/exhaustive/issues/212/expected/model_3_2.eprime +++ /dev/null @@ -1,36 +0,0 @@ -language ESSENCE' 1.0 - -given fin1: int -given a_Explicit: matrix indexed by [int(1..fin1)] of int(0..5) -given fin2: int -given b_Explicit: matrix indexed by [int(1..fin2)] of int(0..5) -find x_ExplicitVarSizeWithMarker_Marker: int(0..6) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..6)] of int(0..5) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..6)] of int(0..6) -branching on [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] -such that - and([q17 <= x_ExplicitVarSizeWithMarker_Marker -> - or([a_Explicit[q19] = x_ExplicitVarSizeWithMarker_Values[q17] - | q19 : int(1..fin1), or([b_Explicit[q21] = a_Explicit[q19] | q21 : int(1..fin2)])]) - | q17 : int(1..6)]), - and([or([q25 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q25] = a_Explicit[q23] - | q25 : int(1..6)]) - | q23 : int(1..fin1), or([b_Explicit[q27] = a_Explicit[q23] | q27 : int(1..fin2)])]), - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..5)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 0 | q2 : int(1..6)]), - and([x_ExplicitVarSizeWithDummy[q4] < x_ExplicitVarSizeWithDummy[q4 + 1] \/ x_ExplicitVarSizeWithDummy[q4] = 6 - | q4 : int(1..5)]), - and([x_ExplicitVarSizeWithDummy[q5] = 6 -> x_ExplicitVarSizeWithDummy[q5 + 1] = 6 | q5 : int(1..5)]), - and([x_ExplicitVarSizeWithDummy[q9] != 6 -> - or([q11 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q11] = x_ExplicitVarSizeWithDummy[q9] - | q11 : int(1..6)]) - | q9 : int(1..6)]), - and([q13 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q15] != 6 /\ - x_ExplicitVarSizeWithDummy[q15] = x_ExplicitVarSizeWithMarker_Values[q13] - | q15 : int(1..6)]) - | q13 : int(1..6)]) - diff --git a/tests/exhaustive/issues/212/expected/model_3_3-1-solution000001.solution b/tests/exhaustive/issues/212/expected/model_3_3-1-solution000001.solution deleted file mode 100644 index de5cc861ad..0000000000 --- a/tests/exhaustive/issues/212/expected/model_3_3-1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1} diff --git a/tests/exhaustive/issues/212/expected/model_3_3-1.eprime-param b/tests/exhaustive/issues/212/expected/model_3_3-1.eprime-param deleted file mode 100644 index c50b6e81fd..0000000000 --- a/tests/exhaustive/issues/212/expected/model_3_3-1.eprime-param +++ /dev/null @@ -1,6 +0,0 @@ -language ESSENCE' 1.0 - -letting a_Explicit be [1, 2; int(1..2)] -letting b_Explicit be [1, 3; int(1..2)] -letting fin1 be 2 -letting fin2 be 2 diff --git a/tests/exhaustive/issues/212/expected/model_3_3.eprime b/tests/exhaustive/issues/212/expected/model_3_3.eprime deleted file mode 100644 index c3326d4adb..0000000000 --- a/tests/exhaustive/issues/212/expected/model_3_3.eprime +++ /dev/null @@ -1,22 +0,0 @@ -language ESSENCE' 1.0 - -given fin1: int -given a_Explicit: matrix indexed by [int(1..fin1)] of int(0..5) -given fin2: int -given b_Explicit: matrix indexed by [int(1..fin2)] of int(0..5) -find x_ExplicitVarSizeWithMarker_Marker: int(0..6) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..6)] of int(0..5) -branching on [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] -such that - and([q5 <= x_ExplicitVarSizeWithMarker_Marker -> - or([a_Explicit[q7] = x_ExplicitVarSizeWithMarker_Values[q5] - | q7 : int(1..fin1), or([b_Explicit[q9] = a_Explicit[q7] | q9 : int(1..fin2)])]) - | q5 : int(1..6)]), - and([or([q13 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q13] = a_Explicit[q11] - | q13 : int(1..6)]) - | q11 : int(1..fin1), or([b_Explicit[q15] = a_Explicit[q11] | q15 : int(1..fin2)])]), - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..5)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 0 | q2 : int(1..6)]) - diff --git a/tests/exhaustive/issues/212/expected/model_3_4-1-solution000001.solution b/tests/exhaustive/issues/212/expected/model_3_4-1-solution000001.solution deleted file mode 100644 index de5cc861ad..0000000000 --- a/tests/exhaustive/issues/212/expected/model_3_4-1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1} diff --git a/tests/exhaustive/issues/212/expected/model_3_4-1.eprime-param b/tests/exhaustive/issues/212/expected/model_3_4-1.eprime-param deleted file mode 100644 index c50b6e81fd..0000000000 --- a/tests/exhaustive/issues/212/expected/model_3_4-1.eprime-param +++ /dev/null @@ -1,6 +0,0 @@ -language ESSENCE' 1.0 - -letting a_Explicit be [1, 2; int(1..2)] -letting b_Explicit be [1, 3; int(1..2)] -letting fin1 be 2 -letting fin2 be 2 diff --git a/tests/exhaustive/issues/212/expected/model_3_4.eprime b/tests/exhaustive/issues/212/expected/model_3_4.eprime deleted file mode 100644 index eefd4567b9..0000000000 --- a/tests/exhaustive/issues/212/expected/model_3_4.eprime +++ /dev/null @@ -1,41 +0,0 @@ -language ESSENCE' 1.0 - -given fin1: int -given a_Explicit: matrix indexed by [int(1..fin1)] of int(0..5) -given fin2: int -given b_Explicit: matrix indexed by [int(1..fin2)] of int(0..5) -find x_ExplicitVarSizeWithMarker_Marker: int(0..6) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..6)] of int(0..5) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..6)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..6)] of int(0..5) -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithMarker_Marker, - x_ExplicitVarSizeWithMarker_Values] -such that - and([q18 <= x_ExplicitVarSizeWithMarker_Marker -> - or([a_Explicit[q20] = x_ExplicitVarSizeWithMarker_Values[q18] - | q20 : int(1..fin1), or([b_Explicit[q22] = a_Explicit[q20] | q22 : int(1..fin2)])]) - | q18 : int(1..6)]), - and([or([q26 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q26] = a_Explicit[q24] - | q26 : int(1..6)]) - | q24 : int(1..fin1), or([b_Explicit[q28] = a_Explicit[q24] | q28 : int(1..fin2)])]), - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..5)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 0 | q2 : int(1..6)]), - and([x_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q4] < x_ExplicitVarSizeWithFlags_Values[q4 + 1] - | q4 : int(1..5)]), - and([x_ExplicitVarSizeWithFlags_Flags[q5] = false -> x_ExplicitVarSizeWithFlags_Values[q5] = 0 | q5 : int(1..6)]), - and([x_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q6] | q6 : int(1..5)]), - and([x_ExplicitVarSizeWithFlags_Flags[q10] -> - or([q12 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q12] = x_ExplicitVarSizeWithFlags_Values[q10] - | q12 : int(1..6)]) - | q10 : int(1..6)]), - and([q14 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q16] /\ - x_ExplicitVarSizeWithFlags_Values[q16] = x_ExplicitVarSizeWithMarker_Values[q14] - | q16 : int(1..6)]) - | q14 : int(1..6)]) - diff --git a/tests/exhaustive/issues/212/expected/model_4_1-1-solution000001.solution b/tests/exhaustive/issues/212/expected/model_4_1-1-solution000001.solution deleted file mode 100644 index de5cc861ad..0000000000 --- a/tests/exhaustive/issues/212/expected/model_4_1-1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1} diff --git a/tests/exhaustive/issues/212/expected/model_4_1-1.eprime-param b/tests/exhaustive/issues/212/expected/model_4_1-1.eprime-param deleted file mode 100644 index c50b6e81fd..0000000000 --- a/tests/exhaustive/issues/212/expected/model_4_1-1.eprime-param +++ /dev/null @@ -1,6 +0,0 @@ -language ESSENCE' 1.0 - -letting a_Explicit be [1, 2; int(1..2)] -letting b_Explicit be [1, 3; int(1..2)] -letting fin1 be 2 -letting fin2 be 2 diff --git a/tests/exhaustive/issues/212/expected/model_4_1.eprime b/tests/exhaustive/issues/212/expected/model_4_1.eprime deleted file mode 100644 index 3f9ecf24e4..0000000000 --- a/tests/exhaustive/issues/212/expected/model_4_1.eprime +++ /dev/null @@ -1,29 +0,0 @@ -language ESSENCE' 1.0 - -given fin1: int -given a_Explicit: matrix indexed by [int(1..fin1)] of int(0..5) -given fin2: int -given b_Explicit: matrix indexed by [int(1..fin2)] of int(0..5) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..6)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..6)] of int(0..5) -find x_Occurrence: matrix indexed by [int(0..5)] of bool -branching on [x_Occurrence, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] -such that - and([x_ExplicitVarSizeWithFlags_Flags[q8] -> - or([a_Explicit[q10] = x_ExplicitVarSizeWithFlags_Values[q8] - | q10 : int(1..fin1), or([b_Explicit[q12] = a_Explicit[q10] | q12 : int(1..fin2)])]) - | q8 : int(1..6)]), - and([or([x_ExplicitVarSizeWithFlags_Flags[q16] /\ x_ExplicitVarSizeWithFlags_Values[q16] = a_Explicit[q14] - | q16 : int(1..6)]) - | q14 : int(1..fin1), or([b_Explicit[q18] = a_Explicit[q14] | q18 : int(1..fin2)])]), - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..5)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 0 | q2 : int(1..6)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..5)]), - and([x_Occurrence[q19] -> - or([x_ExplicitVarSizeWithFlags_Flags[q21] /\ x_ExplicitVarSizeWithFlags_Values[q21] = q19 | q21 : int(1..6)]) - | q19 : int(0..5)]), - and([x_ExplicitVarSizeWithFlags_Flags[q23] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q23]] - | q23 : int(1..6)]) - diff --git a/tests/exhaustive/issues/212/expected/model_4_2-1-solution000001.solution b/tests/exhaustive/issues/212/expected/model_4_2-1-solution000001.solution deleted file mode 100644 index de5cc861ad..0000000000 --- a/tests/exhaustive/issues/212/expected/model_4_2-1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1} diff --git a/tests/exhaustive/issues/212/expected/model_4_2-1.eprime-param b/tests/exhaustive/issues/212/expected/model_4_2-1.eprime-param deleted file mode 100644 index c50b6e81fd..0000000000 --- a/tests/exhaustive/issues/212/expected/model_4_2-1.eprime-param +++ /dev/null @@ -1,6 +0,0 @@ -language ESSENCE' 1.0 - -letting a_Explicit be [1, 2; int(1..2)] -letting b_Explicit be [1, 3; int(1..2)] -letting fin1 be 2 -letting fin2 be 2 diff --git a/tests/exhaustive/issues/212/expected/model_4_2.eprime b/tests/exhaustive/issues/212/expected/model_4_2.eprime deleted file mode 100644 index 4d34fb6bca..0000000000 --- a/tests/exhaustive/issues/212/expected/model_4_2.eprime +++ /dev/null @@ -1,37 +0,0 @@ -language ESSENCE' 1.0 - -given fin1: int -given a_Explicit: matrix indexed by [int(1..fin1)] of int(0..5) -given fin2: int -given b_Explicit: matrix indexed by [int(1..fin2)] of int(0..5) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..6)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..6)] of int(0..5) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..6)] of int(0..6) -branching on [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] -such that - and([x_ExplicitVarSizeWithFlags_Flags[q19] -> - or([a_Explicit[q21] = x_ExplicitVarSizeWithFlags_Values[q19] - | q21 : int(1..fin1), or([b_Explicit[q23] = a_Explicit[q21] | q23 : int(1..fin2)])]) - | q19 : int(1..6)]), - and([or([x_ExplicitVarSizeWithFlags_Flags[q27] /\ x_ExplicitVarSizeWithFlags_Values[q27] = a_Explicit[q25] - | q27 : int(1..6)]) - | q25 : int(1..fin1), or([b_Explicit[q29] = a_Explicit[q25] | q29 : int(1..fin2)])]), - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..5)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 0 | q2 : int(1..6)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..5)]), - and([x_ExplicitVarSizeWithDummy[q6] < x_ExplicitVarSizeWithDummy[q6 + 1] \/ x_ExplicitVarSizeWithDummy[q6] = 6 - | q6 : int(1..5)]), - and([x_ExplicitVarSizeWithDummy[q7] = 6 -> x_ExplicitVarSizeWithDummy[q7 + 1] = 6 | q7 : int(1..5)]), - and([x_ExplicitVarSizeWithDummy[q11] != 6 -> - or([x_ExplicitVarSizeWithFlags_Flags[q13] /\ - x_ExplicitVarSizeWithFlags_Values[q13] = x_ExplicitVarSizeWithDummy[q11] - | q13 : int(1..6)]) - | q11 : int(1..6)]), - and([x_ExplicitVarSizeWithFlags_Flags[q15] -> - or([x_ExplicitVarSizeWithDummy[q17] != 6 /\ - x_ExplicitVarSizeWithDummy[q17] = x_ExplicitVarSizeWithFlags_Values[q15] - | q17 : int(1..6)]) - | q15 : int(1..6)]) - diff --git a/tests/exhaustive/issues/212/expected/model_4_3-1-solution000001.solution b/tests/exhaustive/issues/212/expected/model_4_3-1-solution000001.solution deleted file mode 100644 index de5cc861ad..0000000000 --- a/tests/exhaustive/issues/212/expected/model_4_3-1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1} diff --git a/tests/exhaustive/issues/212/expected/model_4_3-1.eprime-param b/tests/exhaustive/issues/212/expected/model_4_3-1.eprime-param deleted file mode 100644 index c50b6e81fd..0000000000 --- a/tests/exhaustive/issues/212/expected/model_4_3-1.eprime-param +++ /dev/null @@ -1,6 +0,0 @@ -language ESSENCE' 1.0 - -letting a_Explicit be [1, 2; int(1..2)] -letting b_Explicit be [1, 3; int(1..2)] -letting fin1 be 2 -letting fin2 be 2 diff --git a/tests/exhaustive/issues/212/expected/model_4_3.eprime b/tests/exhaustive/issues/212/expected/model_4_3.eprime deleted file mode 100644 index 44a997c6a7..0000000000 --- a/tests/exhaustive/issues/212/expected/model_4_3.eprime +++ /dev/null @@ -1,41 +0,0 @@ -language ESSENCE' 1.0 - -given fin1: int -given a_Explicit: matrix indexed by [int(1..fin1)] of int(0..5) -given fin2: int -given b_Explicit: matrix indexed by [int(1..fin2)] of int(0..5) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..6)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..6)] of int(0..5) -find x_ExplicitVarSizeWithMarker_Marker: int(0..6) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..6)] of int(0..5) -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithFlags_Flags, - x_ExplicitVarSizeWithFlags_Values] -such that - and([x_ExplicitVarSizeWithFlags_Flags[q18] -> - or([a_Explicit[q20] = x_ExplicitVarSizeWithFlags_Values[q18] - | q20 : int(1..fin1), or([b_Explicit[q22] = a_Explicit[q20] | q22 : int(1..fin2)])]) - | q18 : int(1..6)]), - and([or([x_ExplicitVarSizeWithFlags_Flags[q26] /\ x_ExplicitVarSizeWithFlags_Values[q26] = a_Explicit[q24] - | q26 : int(1..6)]) - | q24 : int(1..fin1), or([b_Explicit[q28] = a_Explicit[q24] | q28 : int(1..fin2)])]), - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..5)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 0 | q2 : int(1..6)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..5)]), - and([q6 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q6] < x_ExplicitVarSizeWithMarker_Values[q6 + 1] - | q6 : int(1..5)]), - and([q7 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q7] = 0 | q7 : int(1..6)]), - and([q10 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q12] /\ - x_ExplicitVarSizeWithFlags_Values[q12] = x_ExplicitVarSizeWithMarker_Values[q10] - | q12 : int(1..6)]) - | q10 : int(1..6)]), - and([x_ExplicitVarSizeWithFlags_Flags[q14] -> - or([q16 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q16] = x_ExplicitVarSizeWithFlags_Values[q14] - | q16 : int(1..6)]) - | q14 : int(1..6)]) - diff --git a/tests/exhaustive/issues/212/expected/model_4_4-1-solution000001.solution b/tests/exhaustive/issues/212/expected/model_4_4-1-solution000001.solution deleted file mode 100644 index de5cc861ad..0000000000 --- a/tests/exhaustive/issues/212/expected/model_4_4-1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {1} diff --git a/tests/exhaustive/issues/212/expected/model_4_4-1.eprime-param b/tests/exhaustive/issues/212/expected/model_4_4-1.eprime-param deleted file mode 100644 index c50b6e81fd..0000000000 --- a/tests/exhaustive/issues/212/expected/model_4_4-1.eprime-param +++ /dev/null @@ -1,6 +0,0 @@ -language ESSENCE' 1.0 - -letting a_Explicit be [1, 2; int(1..2)] -letting b_Explicit be [1, 3; int(1..2)] -letting fin1 be 2 -letting fin2 be 2 diff --git a/tests/exhaustive/issues/212/expected/model_4_4.eprime b/tests/exhaustive/issues/212/expected/model_4_4.eprime deleted file mode 100644 index fa1f37afc2..0000000000 --- a/tests/exhaustive/issues/212/expected/model_4_4.eprime +++ /dev/null @@ -1,23 +0,0 @@ -language ESSENCE' 1.0 - -given fin1: int -given a_Explicit: matrix indexed by [int(1..fin1)] of int(0..5) -given fin2: int -given b_Explicit: matrix indexed by [int(1..fin2)] of int(0..5) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..6)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..6)] of int(0..5) -branching on [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] -such that - and([x_ExplicitVarSizeWithFlags_Flags[q7] -> - or([a_Explicit[q9] = x_ExplicitVarSizeWithFlags_Values[q7] - | q9 : int(1..fin1), or([b_Explicit[q11] = a_Explicit[q9] | q11 : int(1..fin2)])]) - | q7 : int(1..6)]), - and([or([x_ExplicitVarSizeWithFlags_Flags[q15] /\ x_ExplicitVarSizeWithFlags_Values[q15] = a_Explicit[q13] - | q15 : int(1..6)]) - | q13 : int(1..fin1), or([b_Explicit[q17] = a_Explicit[q13] | q17 : int(1..fin2)])]), - and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] - | q1 : int(1..5)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 0 | q2 : int(1..6)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..5)]) - diff --git a/tests/exhaustive/issues/286/expected/model_1_1-p1-solution000001.solution b/tests/exhaustive/issues/286/expected/model_1_1-p1-solution000001.solution deleted file mode 100644 index 8f7fa48018..0000000000 --- a/tests/exhaustive/issues/286/expected/model_1_1-p1-solution000001.solution +++ /dev/null @@ -1,6 +0,0 @@ -language Essence 1.3 - -letting p be partition({1, 2, 3, 4}) -$ Visualisation for p -$ 1 2 3 4 - diff --git a/tests/exhaustive/issues/286/expected/model_1_1-p1-solution000002.solution b/tests/exhaustive/issues/286/expected/model_1_1-p1-solution000002.solution deleted file mode 100644 index cd8086fa4a..0000000000 --- a/tests/exhaustive/issues/286/expected/model_1_1-p1-solution000002.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting p be partition({1}, {2, 3, 4}) -$ Visualisation for p -$ 1 -$ 2 3 4 - diff --git a/tests/exhaustive/issues/286/expected/model_1_1-p1-solution000003.solution b/tests/exhaustive/issues/286/expected/model_1_1-p1-solution000003.solution deleted file mode 100644 index 69d6c9f6be..0000000000 --- a/tests/exhaustive/issues/286/expected/model_1_1-p1-solution000003.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting p be partition({1, 4}, {2, 3}) -$ Visualisation for p -$ 1 4 -$ 2 3 - diff --git a/tests/exhaustive/issues/286/expected/model_1_1-p1-solution000004.solution b/tests/exhaustive/issues/286/expected/model_1_1-p1-solution000004.solution deleted file mode 100644 index dafa529443..0000000000 --- a/tests/exhaustive/issues/286/expected/model_1_1-p1-solution000004.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting p be partition({1, 3}, {2, 4}) -$ Visualisation for p -$ 1 3 -$ 2 4 - diff --git a/tests/exhaustive/issues/286/expected/model_1_1-p1-solution000005.solution b/tests/exhaustive/issues/286/expected/model_1_1-p1-solution000005.solution deleted file mode 100644 index 0368fc950b..0000000000 --- a/tests/exhaustive/issues/286/expected/model_1_1-p1-solution000005.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting p be partition({1, 3, 4}, {2}) -$ Visualisation for p -$ 1 3 4 -$ 2 - diff --git a/tests/exhaustive/issues/286/expected/model_1_1-p1-solution000006.solution b/tests/exhaustive/issues/286/expected/model_1_1-p1-solution000006.solution deleted file mode 100644 index 1507fcc0c1..0000000000 --- a/tests/exhaustive/issues/286/expected/model_1_1-p1-solution000006.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting p be partition({1, 2}, {3, 4}) -$ Visualisation for p -$ 1 2 -$ 3 4 - diff --git a/tests/exhaustive/issues/286/expected/model_1_1-p1-solution000007.solution b/tests/exhaustive/issues/286/expected/model_1_1-p1-solution000007.solution deleted file mode 100644 index 7781800dc4..0000000000 --- a/tests/exhaustive/issues/286/expected/model_1_1-p1-solution000007.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting p be partition({1, 2, 4}, {3}) -$ Visualisation for p -$ 1 2 4 -$ 3 - diff --git a/tests/exhaustive/issues/286/expected/model_1_1-p1-solution000008.solution b/tests/exhaustive/issues/286/expected/model_1_1-p1-solution000008.solution deleted file mode 100644 index 556f2c0ecc..0000000000 --- a/tests/exhaustive/issues/286/expected/model_1_1-p1-solution000008.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting p be partition({1, 2, 3}, {4}) -$ Visualisation for p -$ 1 2 3 -$ 4 - diff --git a/tests/exhaustive/issues/286/expected/model_1_1-p1.eprime-param b/tests/exhaustive/issues/286/expected/model_1_1-p1.eprime-param deleted file mode 100644 index 85954307ca..0000000000 --- a/tests/exhaustive/issues/286/expected/model_1_1-p1.eprime-param +++ /dev/null @@ -1,3 +0,0 @@ -language ESSENCE' 1.0 - -letting b be 4 diff --git a/tests/exhaustive/issues/286/expected/model_1_1.eprime b/tests/exhaustive/issues/286/expected/model_1_1.eprime deleted file mode 100644 index aa35b895fb..0000000000 --- a/tests/exhaustive/issues/286/expected/model_1_1.eprime +++ /dev/null @@ -1,43 +0,0 @@ -language ESSENCE' 1.0 - -given b: int -find p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker: int(0..b) -find p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence: matrix indexed by [int(1..b), int(1..b)] of bool -branching on - [p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker, - p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence] -such that - sum([toInt(q19 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker) | q19 : int(1..b)]) <= - sum([1 | q20_ExplicitVarSizeWithDummy : matrix indexed by [int(1..b)] of int(1..b + 1), - and([q20_ExplicitVarSizeWithDummy[q21] < q20_ExplicitVarSizeWithDummy[q21 + 1] \/ - q20_ExplicitVarSizeWithDummy[q21] = b + 1 - | q21 : int(1..b - 1)]), - and([q20_ExplicitVarSizeWithDummy[q22] = b + 1 -> q20_ExplicitVarSizeWithDummy[q22 + 1] = b + 1 - | q22 : int(1..b - 1)])]) - / 8, - and([1 = - sum([toInt(q9 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ - p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q9, q1]) - | q9 : int(1..b)]) - | q1 : int(1..b)]), - and([q15 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> - sum([toInt(p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q15, q16]) | q16 : int(1..b)]) >= 1 - | q15 : int(1..b)]), - and([q4 + 1 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> - [-toInt(p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q4, q10]) | q10 : int(1..b)] p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> - and([p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q5, q12] = false | q12 : int(1..b)]) - | q5 : int(1..b)]), - p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker <= b, - and([q6 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> - sum([toInt(p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q6, q7]) | q7 : int(1..b)]) <= b - | q6 : int(1..b)]), - b = - sum([toInt(q13 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker) * - catchUndef(sum([toInt(p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q13, q14]) - | q14 : int(1..b)]), - 0) - | q13 : int(1..b)]) - diff --git a/tests/exhaustive/issues/286/expected/model_1_2-p1-solution000001.solution b/tests/exhaustive/issues/286/expected/model_1_2-p1-solution000001.solution deleted file mode 100644 index 8f7fa48018..0000000000 --- a/tests/exhaustive/issues/286/expected/model_1_2-p1-solution000001.solution +++ /dev/null @@ -1,6 +0,0 @@ -language Essence 1.3 - -letting p be partition({1, 2, 3, 4}) -$ Visualisation for p -$ 1 2 3 4 - diff --git a/tests/exhaustive/issues/286/expected/model_1_2-p1-solution000002.solution b/tests/exhaustive/issues/286/expected/model_1_2-p1-solution000002.solution deleted file mode 100644 index 556f2c0ecc..0000000000 --- a/tests/exhaustive/issues/286/expected/model_1_2-p1-solution000002.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting p be partition({1, 2, 3}, {4}) -$ Visualisation for p -$ 1 2 3 -$ 4 - diff --git a/tests/exhaustive/issues/286/expected/model_1_2-p1-solution000003.solution b/tests/exhaustive/issues/286/expected/model_1_2-p1-solution000003.solution deleted file mode 100644 index 7781800dc4..0000000000 --- a/tests/exhaustive/issues/286/expected/model_1_2-p1-solution000003.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting p be partition({1, 2, 4}, {3}) -$ Visualisation for p -$ 1 2 4 -$ 3 - diff --git a/tests/exhaustive/issues/286/expected/model_1_2-p1-solution000004.solution b/tests/exhaustive/issues/286/expected/model_1_2-p1-solution000004.solution deleted file mode 100644 index 1507fcc0c1..0000000000 --- a/tests/exhaustive/issues/286/expected/model_1_2-p1-solution000004.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting p be partition({1, 2}, {3, 4}) -$ Visualisation for p -$ 1 2 -$ 3 4 - diff --git a/tests/exhaustive/issues/286/expected/model_1_2-p1-solution000005.solution b/tests/exhaustive/issues/286/expected/model_1_2-p1-solution000005.solution deleted file mode 100644 index 0368fc950b..0000000000 --- a/tests/exhaustive/issues/286/expected/model_1_2-p1-solution000005.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting p be partition({1, 3, 4}, {2}) -$ Visualisation for p -$ 1 3 4 -$ 2 - diff --git a/tests/exhaustive/issues/286/expected/model_1_2-p1-solution000006.solution b/tests/exhaustive/issues/286/expected/model_1_2-p1-solution000006.solution deleted file mode 100644 index dafa529443..0000000000 --- a/tests/exhaustive/issues/286/expected/model_1_2-p1-solution000006.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting p be partition({1, 3}, {2, 4}) -$ Visualisation for p -$ 1 3 -$ 2 4 - diff --git a/tests/exhaustive/issues/286/expected/model_1_2-p1-solution000007.solution b/tests/exhaustive/issues/286/expected/model_1_2-p1-solution000007.solution deleted file mode 100644 index 69d6c9f6be..0000000000 --- a/tests/exhaustive/issues/286/expected/model_1_2-p1-solution000007.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting p be partition({1, 4}, {2, 3}) -$ Visualisation for p -$ 1 4 -$ 2 3 - diff --git a/tests/exhaustive/issues/286/expected/model_1_2-p1-solution000008.solution b/tests/exhaustive/issues/286/expected/model_1_2-p1-solution000008.solution deleted file mode 100644 index cd8086fa4a..0000000000 --- a/tests/exhaustive/issues/286/expected/model_1_2-p1-solution000008.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting p be partition({1}, {2, 3, 4}) -$ Visualisation for p -$ 1 -$ 2 3 4 - diff --git a/tests/exhaustive/issues/286/expected/model_1_2-p1.eprime-param b/tests/exhaustive/issues/286/expected/model_1_2-p1.eprime-param deleted file mode 100644 index 85954307ca..0000000000 --- a/tests/exhaustive/issues/286/expected/model_1_2-p1.eprime-param +++ /dev/null @@ -1,3 +0,0 @@ -language ESSENCE' 1.0 - -letting b be 4 diff --git a/tests/exhaustive/issues/286/expected/model_1_2.eprime b/tests/exhaustive/issues/286/expected/model_1_2.eprime deleted file mode 100644 index 6777d21139..0000000000 --- a/tests/exhaustive/issues/286/expected/model_1_2.eprime +++ /dev/null @@ -1,122 +0,0 @@ -language ESSENCE' 1.0 - -given b: int -find p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker: int(0..b) -find p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence: matrix indexed by [int(1..b), int(1..b)] of bool -find p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker: int(0..b) -find p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy: - matrix indexed by [int(1..b), int(1..b)] of int(1..b + 1) -branching on - [p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker, - p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy, - p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker, - p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence] -such that - sum([toInt(q63 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker) | q63 : int(1..b)]) <= - sum([1 | q64_ExplicitVarSizeWithDummy : matrix indexed by [int(1..b)] of int(1..b + 1), - and([q64_ExplicitVarSizeWithDummy[q65] < q64_ExplicitVarSizeWithDummy[q65 + 1] \/ - q64_ExplicitVarSizeWithDummy[q65] = b + 1 - | q65 : int(1..b - 1)]), - and([q64_ExplicitVarSizeWithDummy[q66] = b + 1 -> q64_ExplicitVarSizeWithDummy[q66 + 1] = b + 1 - | q66 : int(1..b - 1)])]) - / 8, - and([1 = - sum([toInt(q20 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ - p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q20, q1]) - | q20 : int(1..b)]) - | q1 : int(1..b)]), - and([q52 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> - sum([toInt(p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q52, q53]) | q53 : int(1..b)]) >= 1 - | q52 : int(1..b)]), - and([q4 + 1 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> - [-toInt(p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q4, q21]) | q21 : int(1..b)] p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> - and([p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q5, q23] = false | q23 : int(1..b)]) - | q5 : int(1..b)]), - p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker <= b, - and([q6 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> - sum([toInt(p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q6, q7]) | q7 : int(1..b)]) <= b - | q6 : int(1..b)]), - b = - sum([toInt(q54 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker) * - catchUndef(sum([toInt(p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q54, q55]) - | q55 : int(1..b)]), - 0) - | q54 : int(1..b)]), - alldifferent_except([toInt(q56 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ - p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q56, q57] != - b + 1) - * - catchUndef(p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q56, q57], - 0) - | q56 : int(1..b), q57 : int(1..b)], - 0), - and([q58 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - sum([toInt(p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q58, q60] != b + 1) - | q60 : int(1..b)]) - >= 1 - | q58 : int(1..b)]), - and([q12 + 1 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - [p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q12, q24] | q24 : int(1..b)] p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - and([p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q13, q26] = 1 - | q26 : int(1..b)]) - | q13 : int(1..b)]), - p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker <= b, - and([q14 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - and([p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q14, q15] < - p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q14, q15 + 1] - \/ p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q14, q15] = b + 1 - | q15 : int(1..b - 1)]) - | q14 : int(1..b)]), - and([q14 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - and([p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q14, q16] = b + 1 -> - p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q14, q16 + 1] = b + 1 - | q16 : int(1..b - 1)]) - | q14 : int(1..b)]), - and([q14 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - sum([toInt(p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q14, q17] != b + 1) - | q17 : int(1..b)]) - <= b - | q14 : int(1..b)]), - b = - sum([toInt(q27 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker) * - catchUndef(sum([toInt(p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q27, q29] != - b + 1) - | q29 : int(1..b)]), - 0) - | q27 : int(1..b)]), - and([q32 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - or([q35 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ - (and([p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q35, q36] -> - or([p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q32, q38] != b + 1 - /\ p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q32, q38] = q36 - | q38 : int(1..b)]) - | q36 : int(1..b)]) - /\ - and([p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q32, q40] != b + 1 -> - p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence - [q35, p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q32, q40]] - | q40 : int(1..b)])) - | q35 : int(1..b)]) - | q32 : int(1..b)]), - and([q43 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> - or([q46 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ - (and([p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q46, q48] != b + 1 -> - p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence - [q43, p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q46, q48]] - | q48 : int(1..b)]) - /\ - and([p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q43, q49] -> - or([p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q46, q51] != b + 1 - /\ p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q46, q51] = q49 - | q51 : int(1..b)]) - | q49 : int(1..b)])) - | q46 : int(1..b)]) - | q43 : int(1..b)]) - diff --git a/tests/exhaustive/issues/286/expected/model_1_3-p1-solution000001.solution b/tests/exhaustive/issues/286/expected/model_1_3-p1-solution000001.solution deleted file mode 100644 index 8f7fa48018..0000000000 --- a/tests/exhaustive/issues/286/expected/model_1_3-p1-solution000001.solution +++ /dev/null @@ -1,6 +0,0 @@ -language Essence 1.3 - -letting p be partition({1, 2, 3, 4}) -$ Visualisation for p -$ 1 2 3 4 - diff --git a/tests/exhaustive/issues/286/expected/model_1_3-p1-solution000002.solution b/tests/exhaustive/issues/286/expected/model_1_3-p1-solution000002.solution deleted file mode 100644 index cd8086fa4a..0000000000 --- a/tests/exhaustive/issues/286/expected/model_1_3-p1-solution000002.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting p be partition({1}, {2, 3, 4}) -$ Visualisation for p -$ 1 -$ 2 3 4 - diff --git a/tests/exhaustive/issues/286/expected/model_1_3-p1-solution000003.solution b/tests/exhaustive/issues/286/expected/model_1_3-p1-solution000003.solution deleted file mode 100644 index 0368fc950b..0000000000 --- a/tests/exhaustive/issues/286/expected/model_1_3-p1-solution000003.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting p be partition({1, 3, 4}, {2}) -$ Visualisation for p -$ 1 3 4 -$ 2 - diff --git a/tests/exhaustive/issues/286/expected/model_1_3-p1-solution000004.solution b/tests/exhaustive/issues/286/expected/model_1_3-p1-solution000004.solution deleted file mode 100644 index 7781800dc4..0000000000 --- a/tests/exhaustive/issues/286/expected/model_1_3-p1-solution000004.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting p be partition({1, 2, 4}, {3}) -$ Visualisation for p -$ 1 2 4 -$ 3 - diff --git a/tests/exhaustive/issues/286/expected/model_1_3-p1-solution000005.solution b/tests/exhaustive/issues/286/expected/model_1_3-p1-solution000005.solution deleted file mode 100644 index 556f2c0ecc..0000000000 --- a/tests/exhaustive/issues/286/expected/model_1_3-p1-solution000005.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting p be partition({1, 2, 3}, {4}) -$ Visualisation for p -$ 1 2 3 -$ 4 - diff --git a/tests/exhaustive/issues/286/expected/model_1_3-p1-solution000006.solution b/tests/exhaustive/issues/286/expected/model_1_3-p1-solution000006.solution deleted file mode 100644 index 1507fcc0c1..0000000000 --- a/tests/exhaustive/issues/286/expected/model_1_3-p1-solution000006.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting p be partition({1, 2}, {3, 4}) -$ Visualisation for p -$ 1 2 -$ 3 4 - diff --git a/tests/exhaustive/issues/286/expected/model_1_3-p1-solution000007.solution b/tests/exhaustive/issues/286/expected/model_1_3-p1-solution000007.solution deleted file mode 100644 index dafa529443..0000000000 --- a/tests/exhaustive/issues/286/expected/model_1_3-p1-solution000007.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting p be partition({1, 3}, {2, 4}) -$ Visualisation for p -$ 1 3 -$ 2 4 - diff --git a/tests/exhaustive/issues/286/expected/model_1_3-p1-solution000008.solution b/tests/exhaustive/issues/286/expected/model_1_3-p1-solution000008.solution deleted file mode 100644 index 69d6c9f6be..0000000000 --- a/tests/exhaustive/issues/286/expected/model_1_3-p1-solution000008.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting p be partition({1, 4}, {2, 3}) -$ Visualisation for p -$ 1 4 -$ 2 3 - diff --git a/tests/exhaustive/issues/286/expected/model_1_3-p1.eprime-param b/tests/exhaustive/issues/286/expected/model_1_3-p1.eprime-param deleted file mode 100644 index 85954307ca..0000000000 --- a/tests/exhaustive/issues/286/expected/model_1_3-p1.eprime-param +++ /dev/null @@ -1,3 +0,0 @@ -language ESSENCE' 1.0 - -letting b be 4 diff --git a/tests/exhaustive/issues/286/expected/model_1_3.eprime b/tests/exhaustive/issues/286/expected/model_1_3.eprime deleted file mode 100644 index b1d2ad1914..0000000000 --- a/tests/exhaustive/issues/286/expected/model_1_3.eprime +++ /dev/null @@ -1,136 +0,0 @@ -language ESSENCE' 1.0 - -given b: int -find p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker: int(0..b) -find p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence: matrix indexed by [int(1..b), int(1..b)] of bool -find p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker: int(0..b) -find p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker: - matrix indexed by [int(1..b)] of int(0..b) -find p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values: - matrix indexed by [int(1..b), int(1..b)] of int(1..b) -branching on - [p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker, - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker, - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values, - p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker, - p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence] -such that - sum([toInt(q58 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker) | q58 : int(1..b)]) <= - sum([1 | q59_ExplicitVarSizeWithDummy : matrix indexed by [int(1..b)] of int(1..b + 1), - and([q59_ExplicitVarSizeWithDummy[q60] < q59_ExplicitVarSizeWithDummy[q60 + 1] \/ - q59_ExplicitVarSizeWithDummy[q60] = b + 1 - | q60 : int(1..b - 1)]), - and([q59_ExplicitVarSizeWithDummy[q61] = b + 1 -> q59_ExplicitVarSizeWithDummy[q61 + 1] = b + 1 - | q61 : int(1..b - 1)])]) - / 8, - and([1 = - sum([toInt(q19 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ - p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q19, q1]) - | q19 : int(1..b)]) - | q1 : int(1..b)]), - and([q49 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> - sum([toInt(p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q49, q50]) | q50 : int(1..b)]) >= 1 - | q49 : int(1..b)]), - and([q4 + 1 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> - [-toInt(p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q4, q20]) | q20 : int(1..b)] p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> - and([p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q5, q22] = false | q22 : int(1..b)]) - | q5 : int(1..b)]), - p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker <= b, - and([q6 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> - sum([toInt(p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q6, q7]) | q7 : int(1..b)]) <= b - | q6 : int(1..b)]), - b = - sum([toInt(q51 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker) * - catchUndef(sum([toInt(p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q51, q52]) - | q52 : int(1..b)]), - 0) - | q51 : int(1..b)]), - alldifferent_except([toInt(q53 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - q54 <= - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q53]) - * - catchUndef(p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q53, q54], - 0) - | q53 : int(1..b), q54 : int(1..b)], - 0), - and([q55 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q55] >= 1 - | q55 : int(1..b)]), - and([q12 + 1 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - flatten([[p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q12]; int(1)], - flatten([[p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q12, q23]; - int(1)] - | q23 : int(1..b)]); - int(1..2)]) - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q13] = 0 /\ - and([p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q13, q25] = 1 - | q25 : int(1..b)]) - | q13 : int(1..b)]), - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker <= b, - and([q14 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - and([q15 + 1 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q14] -> - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q14, q15] < - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q14, q15 + 1] - | q15 : int(1..b - 1)]) - | q14 : int(1..b)]), - and([q14 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - and([q16 > p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q14] -> - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q14, q16] = 1 - | q16 : int(1..b)]) - | q14 : int(1..b)]), - and([q14 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q14] <= b - | q14 : int(1..b)]), - b = - sum([toInt(q26 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker) * - catchUndef(p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q26], 0) - | q26 : int(1..b)]), - and([q29 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - or([q32 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ - (and([p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q32, q33] -> - or([q35 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q29] - /\ - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q29, q35] = - q33 | q35 : int(1..b)]) - | q33 : int(1..b)]) - /\ - and([q37 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q29] -> - p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence - [q32, - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q29, q37]] - | q37 : int(1..b)])) - | q32 : int(1..b)]) - | q29 : int(1..b)]), - and([q40 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> - or([q43 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - (and([q45 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q43] -> - p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence - [q40, - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q43, q45]] - | q45 : int(1..b)]) - /\ - and([p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q40, q46] -> - or([q48 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q43] - /\ - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q43, q48] = - q46 | q48 : int(1..b)]) - | q46 : int(1..b)])) - | q43 : int(1..b)]) - | q40 : int(1..b)]) - diff --git a/tests/exhaustive/issues/286/expected/model_1_4-p1-solution000001.solution b/tests/exhaustive/issues/286/expected/model_1_4-p1-solution000001.solution deleted file mode 100644 index 8f7fa48018..0000000000 --- a/tests/exhaustive/issues/286/expected/model_1_4-p1-solution000001.solution +++ /dev/null @@ -1,6 +0,0 @@ -language Essence 1.3 - -letting p be partition({1, 2, 3, 4}) -$ Visualisation for p -$ 1 2 3 4 - diff --git a/tests/exhaustive/issues/286/expected/model_1_4-p1-solution000002.solution b/tests/exhaustive/issues/286/expected/model_1_4-p1-solution000002.solution deleted file mode 100644 index 556f2c0ecc..0000000000 --- a/tests/exhaustive/issues/286/expected/model_1_4-p1-solution000002.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting p be partition({1, 2, 3}, {4}) -$ Visualisation for p -$ 1 2 3 -$ 4 - diff --git a/tests/exhaustive/issues/286/expected/model_1_4-p1-solution000003.solution b/tests/exhaustive/issues/286/expected/model_1_4-p1-solution000003.solution deleted file mode 100644 index 7781800dc4..0000000000 --- a/tests/exhaustive/issues/286/expected/model_1_4-p1-solution000003.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting p be partition({1, 2, 4}, {3}) -$ Visualisation for p -$ 1 2 4 -$ 3 - diff --git a/tests/exhaustive/issues/286/expected/model_1_4-p1-solution000004.solution b/tests/exhaustive/issues/286/expected/model_1_4-p1-solution000004.solution deleted file mode 100644 index 1507fcc0c1..0000000000 --- a/tests/exhaustive/issues/286/expected/model_1_4-p1-solution000004.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting p be partition({1, 2}, {3, 4}) -$ Visualisation for p -$ 1 2 -$ 3 4 - diff --git a/tests/exhaustive/issues/286/expected/model_1_4-p1-solution000005.solution b/tests/exhaustive/issues/286/expected/model_1_4-p1-solution000005.solution deleted file mode 100644 index 0368fc950b..0000000000 --- a/tests/exhaustive/issues/286/expected/model_1_4-p1-solution000005.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting p be partition({1, 3, 4}, {2}) -$ Visualisation for p -$ 1 3 4 -$ 2 - diff --git a/tests/exhaustive/issues/286/expected/model_1_4-p1-solution000006.solution b/tests/exhaustive/issues/286/expected/model_1_4-p1-solution000006.solution deleted file mode 100644 index dafa529443..0000000000 --- a/tests/exhaustive/issues/286/expected/model_1_4-p1-solution000006.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting p be partition({1, 3}, {2, 4}) -$ Visualisation for p -$ 1 3 -$ 2 4 - diff --git a/tests/exhaustive/issues/286/expected/model_1_4-p1-solution000007.solution b/tests/exhaustive/issues/286/expected/model_1_4-p1-solution000007.solution deleted file mode 100644 index 69d6c9f6be..0000000000 --- a/tests/exhaustive/issues/286/expected/model_1_4-p1-solution000007.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting p be partition({1, 4}, {2, 3}) -$ Visualisation for p -$ 1 4 -$ 2 3 - diff --git a/tests/exhaustive/issues/286/expected/model_1_4-p1-solution000008.solution b/tests/exhaustive/issues/286/expected/model_1_4-p1-solution000008.solution deleted file mode 100644 index cd8086fa4a..0000000000 --- a/tests/exhaustive/issues/286/expected/model_1_4-p1-solution000008.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting p be partition({1}, {2, 3, 4}) -$ Visualisation for p -$ 1 -$ 2 3 4 - diff --git a/tests/exhaustive/issues/286/expected/model_1_4-p1.eprime-param b/tests/exhaustive/issues/286/expected/model_1_4-p1.eprime-param deleted file mode 100644 index 85954307ca..0000000000 --- a/tests/exhaustive/issues/286/expected/model_1_4-p1.eprime-param +++ /dev/null @@ -1,3 +0,0 @@ -language ESSENCE' 1.0 - -letting b be 4 diff --git a/tests/exhaustive/issues/286/expected/model_1_4.eprime b/tests/exhaustive/issues/286/expected/model_1_4.eprime deleted file mode 100644 index 263a7836c6..0000000000 --- a/tests/exhaustive/issues/286/expected/model_1_4.eprime +++ /dev/null @@ -1,91 +0,0 @@ -language ESSENCE' 1.0 - -given b: int -find p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker: int(0..b) -find p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence: matrix indexed by [int(1..b), int(1..b)] of bool -find p_PartitionOccurrence_NumParts: int(1..b) -find p_PartitionOccurrence_WhichPart: matrix indexed by [int(1..b)] of int(1..b) -find p_PartitionOccurrence_PartSizes: matrix indexed by [int(1..b)] of int(0..b) -find p_PartitionOccurrence_FirstIndex: matrix indexed by [int(1..b)] of int(1..b) -branching on - [p_PartitionOccurrence_NumParts, p_PartitionOccurrence_WhichPart, p_PartitionOccurrence_PartSizes, - p_PartitionOccurrence_FirstIndex, p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker, - p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence] -such that - sum([toInt(q51 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker) | q51 : int(1..b)]) <= - sum([1 | q52_ExplicitVarSizeWithDummy : matrix indexed by [int(1..b)] of int(1..b + 1), - and([q52_ExplicitVarSizeWithDummy[q53] < q52_ExplicitVarSizeWithDummy[q53 + 1] \/ - q52_ExplicitVarSizeWithDummy[q53] = b + 1 - | q53 : int(1..b - 1)]), - and([q52_ExplicitVarSizeWithDummy[q54] = b + 1 -> q52_ExplicitVarSizeWithDummy[q54 + 1] = b + 1 - | q54 : int(1..b - 1)])]) - / 8, - and([1 = - sum([toInt(q19 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ - p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q19, q1]) - | q19 : int(1..b)]) - | q1 : int(1..b)]), - and([q45 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> - sum([toInt(p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q45, q46]) | q46 : int(1..b)]) >= 1 - | q45 : int(1..b)]), - and([q4 + 1 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> - [-toInt(p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q4, q20]) | q20 : int(1..b)] p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> - and([p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q5, q22] = false | q22 : int(1..b)]) - | q5 : int(1..b)]), - p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker <= b, - and([q6 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> - sum([toInt(p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q6, q7]) | q7 : int(1..b)]) <= b - | q6 : int(1..b)]), - b = - sum([toInt(q47 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker) * - catchUndef(sum([toInt(p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q47, q48]) - | q48 : int(1..b)]), - 0) - | q47 : int(1..b)]), - and([q9 <= p_PartitionOccurrence_NumParts -> p_PartitionOccurrence_PartSizes[q9] <= b | q9 : int(1..b)]), - and([q9 > p_PartitionOccurrence_NumParts -> p_PartitionOccurrence_PartSizes[q9] = 0 | q9 : int(1..b)]), - p_PartitionOccurrence_NumParts <= b, - and([q10 <= p_PartitionOccurrence_NumParts -> or([p_PartitionOccurrence_WhichPart[q11] = q10 | q11 : int(1..b)]) - | q10 : int(3..b)]), - p_PartitionOccurrence_NumParts = max([p_PartitionOccurrence_WhichPart[q12] | q12 : int(1..b)]), - and([p_PartitionOccurrence_PartSizes[q13] = - sum([toInt(p_PartitionOccurrence_WhichPart[q14] = q13) | q14 : int(1..b)]) - | q13 : int(1..b)]), - and([q15 <= p_PartitionOccurrence_NumParts -> - and([p_PartitionOccurrence_WhichPart[q16] = q15 -> p_PartitionOccurrence_FirstIndex[q15] <= q16 - | q16 : int(1..b)]) - | q15 : int(1..b)]), - and([q15 <= p_PartitionOccurrence_NumParts -> - or([p_PartitionOccurrence_WhichPart[q16] = q15 /\ p_PartitionOccurrence_FirstIndex[q15] = q16 - | q16 : int(1..b)]) - | q15 : int(1..b)]), - and([q15 > p_PartitionOccurrence_NumParts -> p_PartitionOccurrence_FirstIndex[q15] = 1 | q15 : int(1..b)]), - and([q17 <= p_PartitionOccurrence_NumParts /\ q18 <= p_PartitionOccurrence_NumParts -> - (q17 < q18 <-> p_PartitionOccurrence_FirstIndex[q17] < p_PartitionOccurrence_FirstIndex[q18]) - | q17 : int(1..b), q18 : int(1..b)]), - and([q24 <= p_PartitionOccurrence_NumParts -> - or([q28 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ - (and([p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q28, q29] -> - or([p_PartitionOccurrence_WhichPart[q31] = q24 /\ q31 = q29 | q31 : int(1..b)]) - | q29 : int(1..b)]) - /\ - and([p_PartitionOccurrence_WhichPart[q33] = q24 -> - p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q28, q33] - | q33 : int(1..b)])) - | q28 : int(1..b)]) - | q24 : int(1..b)]), - and([q36 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> - or([q38 <= p_PartitionOccurrence_NumParts /\ - (and([p_PartitionOccurrence_WhichPart[q41] = q38 -> - p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q36, q41] - | q41 : int(1..b)]) - /\ - and([p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q36, q42] -> - or([p_PartitionOccurrence_WhichPart[q44] = q38 /\ q44 = q42 | q44 : int(1..b)]) - | q42 : int(1..b)])) - | q38 : int(1..b)]) - | q36 : int(1..b)]) - diff --git a/tests/exhaustive/issues/286/expected/model_2_1-p1-solution000001.solution b/tests/exhaustive/issues/286/expected/model_2_1-p1-solution000001.solution deleted file mode 100644 index 8f7fa48018..0000000000 --- a/tests/exhaustive/issues/286/expected/model_2_1-p1-solution000001.solution +++ /dev/null @@ -1,6 +0,0 @@ -language Essence 1.3 - -letting p be partition({1, 2, 3, 4}) -$ Visualisation for p -$ 1 2 3 4 - diff --git a/tests/exhaustive/issues/286/expected/model_2_1-p1-solution000002.solution b/tests/exhaustive/issues/286/expected/model_2_1-p1-solution000002.solution deleted file mode 100644 index cd8086fa4a..0000000000 --- a/tests/exhaustive/issues/286/expected/model_2_1-p1-solution000002.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting p be partition({1}, {2, 3, 4}) -$ Visualisation for p -$ 1 -$ 2 3 4 - diff --git a/tests/exhaustive/issues/286/expected/model_2_1-p1-solution000003.solution b/tests/exhaustive/issues/286/expected/model_2_1-p1-solution000003.solution deleted file mode 100644 index 69d6c9f6be..0000000000 --- a/tests/exhaustive/issues/286/expected/model_2_1-p1-solution000003.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting p be partition({1, 4}, {2, 3}) -$ Visualisation for p -$ 1 4 -$ 2 3 - diff --git a/tests/exhaustive/issues/286/expected/model_2_1-p1-solution000004.solution b/tests/exhaustive/issues/286/expected/model_2_1-p1-solution000004.solution deleted file mode 100644 index dafa529443..0000000000 --- a/tests/exhaustive/issues/286/expected/model_2_1-p1-solution000004.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting p be partition({1, 3}, {2, 4}) -$ Visualisation for p -$ 1 3 -$ 2 4 - diff --git a/tests/exhaustive/issues/286/expected/model_2_1-p1-solution000005.solution b/tests/exhaustive/issues/286/expected/model_2_1-p1-solution000005.solution deleted file mode 100644 index 0368fc950b..0000000000 --- a/tests/exhaustive/issues/286/expected/model_2_1-p1-solution000005.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting p be partition({1, 3, 4}, {2}) -$ Visualisation for p -$ 1 3 4 -$ 2 - diff --git a/tests/exhaustive/issues/286/expected/model_2_1-p1-solution000006.solution b/tests/exhaustive/issues/286/expected/model_2_1-p1-solution000006.solution deleted file mode 100644 index 1507fcc0c1..0000000000 --- a/tests/exhaustive/issues/286/expected/model_2_1-p1-solution000006.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting p be partition({1, 2}, {3, 4}) -$ Visualisation for p -$ 1 2 -$ 3 4 - diff --git a/tests/exhaustive/issues/286/expected/model_2_1-p1-solution000007.solution b/tests/exhaustive/issues/286/expected/model_2_1-p1-solution000007.solution deleted file mode 100644 index 7781800dc4..0000000000 --- a/tests/exhaustive/issues/286/expected/model_2_1-p1-solution000007.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting p be partition({1, 2, 4}, {3}) -$ Visualisation for p -$ 1 2 4 -$ 3 - diff --git a/tests/exhaustive/issues/286/expected/model_2_1-p1-solution000008.solution b/tests/exhaustive/issues/286/expected/model_2_1-p1-solution000008.solution deleted file mode 100644 index 556f2c0ecc..0000000000 --- a/tests/exhaustive/issues/286/expected/model_2_1-p1-solution000008.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting p be partition({1, 2, 3}, {4}) -$ Visualisation for p -$ 1 2 3 -$ 4 - diff --git a/tests/exhaustive/issues/286/expected/model_2_1-p1.eprime-param b/tests/exhaustive/issues/286/expected/model_2_1-p1.eprime-param deleted file mode 100644 index 85954307ca..0000000000 --- a/tests/exhaustive/issues/286/expected/model_2_1-p1.eprime-param +++ /dev/null @@ -1,3 +0,0 @@ -language ESSENCE' 1.0 - -letting b be 4 diff --git a/tests/exhaustive/issues/286/expected/model_2_1.eprime b/tests/exhaustive/issues/286/expected/model_2_1.eprime deleted file mode 100644 index cd032fe57a..0000000000 --- a/tests/exhaustive/issues/286/expected/model_2_1.eprime +++ /dev/null @@ -1,122 +0,0 @@ -language ESSENCE' 1.0 - -given b: int -find p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker: int(0..b) -find p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy: - matrix indexed by [int(1..b), int(1..b)] of int(1..b + 1) -find p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker: int(0..b) -find p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence: matrix indexed by [int(1..b), int(1..b)] of bool -branching on - [p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker, - p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence, - p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker, - p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy] -such that - sum([toInt(q63 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker) | q63 : int(1..b)]) <= - sum([1 | q64_ExplicitVarSizeWithDummy : matrix indexed by [int(1..b)] of int(1..b + 1), - and([q64_ExplicitVarSizeWithDummy[q65] < q64_ExplicitVarSizeWithDummy[q65 + 1] \/ - q64_ExplicitVarSizeWithDummy[q65] = b + 1 - | q65 : int(1..b - 1)]), - and([q64_ExplicitVarSizeWithDummy[q66] = b + 1 -> q64_ExplicitVarSizeWithDummy[q66 + 1] = b + 1 - | q66 : int(1..b - 1)])]) - / 8, - alldifferent_except([toInt(q51 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ - p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q51, q52] != - b + 1) - * - catchUndef(p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q51, q52], - 0) - | q51 : int(1..b), q52 : int(1..b)], - 0), - and([q53 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - sum([toInt(p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q53, q55] != b + 1) - | q55 : int(1..b)]) - >= 1 - | q53 : int(1..b)]), - and([q4 + 1 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - [p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q4, q20] | q20 : int(1..b)] p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - and([p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q5, q22] = 1 - | q22 : int(1..b)]) - | q5 : int(1..b)]), - p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker <= b, - and([q6 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - and([p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q6, q7] < - p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q6, q7 + 1] - \/ p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q6, q7] = b + 1 - | q7 : int(1..b - 1)]) - | q6 : int(1..b)]), - and([q6 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - and([p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q6, q8] = b + 1 -> - p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q6, q8 + 1] = b + 1 - | q8 : int(1..b - 1)]) - | q6 : int(1..b)]), - and([q6 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - sum([toInt(p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q6, q9] != b + 1) - | q9 : int(1..b)]) - <= b - | q6 : int(1..b)]), - b = - sum([toInt(q56 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker) * - catchUndef(sum([toInt(p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q56, q58] != - b + 1) - | q58 : int(1..b)]), - 0) - | q56 : int(1..b)]), - and([1 = - sum([toInt(q23 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ - p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q23, q12]) - | q23 : int(1..b)]) - | q12 : int(1..b)]), - and([q59 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> - sum([toInt(p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q59, q60]) | q60 : int(1..b)]) >= 1 - | q59 : int(1..b)]), - and([q15 + 1 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> - [-toInt(p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q15, q24]) | q24 : int(1..b)] p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> - and([p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q16, q26] = false | q26 : int(1..b)]) - | q16 : int(1..b)]), - p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker <= b, - and([q17 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> - sum([toInt(p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q17, q18]) | q18 : int(1..b)]) <= b - | q17 : int(1..b)]), - b = - sum([toInt(q27 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker) * - catchUndef(sum([toInt(p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q27, q28]) - | q28 : int(1..b)]), - 0) - | q27 : int(1..b)]), - and([q31 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> - or([q34 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ - (and([p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q34, q36] != b + 1 -> - p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence - [q31, p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q34, q36]] - | q36 : int(1..b)]) - /\ - and([p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q31, q37] -> - or([p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q34, q39] != b + 1 - /\ p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q34, q39] = q37 - | q39 : int(1..b)]) - | q37 : int(1..b)])) - | q34 : int(1..b)]) - | q31 : int(1..b)]), - and([q42 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - or([q45 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ - (and([p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q45, q46] -> - or([p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q42, q48] != b + 1 - /\ p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q42, q48] = q46 - | q48 : int(1..b)]) - | q46 : int(1..b)]) - /\ - and([p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q42, q50] != b + 1 -> - p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence - [q45, p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q42, q50]] - | q50 : int(1..b)])) - | q45 : int(1..b)]) - | q42 : int(1..b)]) - diff --git a/tests/exhaustive/issues/286/expected/model_2_2-p1-solution000001.solution b/tests/exhaustive/issues/286/expected/model_2_2-p1-solution000001.solution deleted file mode 100644 index 8f7fa48018..0000000000 --- a/tests/exhaustive/issues/286/expected/model_2_2-p1-solution000001.solution +++ /dev/null @@ -1,6 +0,0 @@ -language Essence 1.3 - -letting p be partition({1, 2, 3, 4}) -$ Visualisation for p -$ 1 2 3 4 - diff --git a/tests/exhaustive/issues/286/expected/model_2_2-p1-solution000002.solution b/tests/exhaustive/issues/286/expected/model_2_2-p1-solution000002.solution deleted file mode 100644 index 556f2c0ecc..0000000000 --- a/tests/exhaustive/issues/286/expected/model_2_2-p1-solution000002.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting p be partition({1, 2, 3}, {4}) -$ Visualisation for p -$ 1 2 3 -$ 4 - diff --git a/tests/exhaustive/issues/286/expected/model_2_2-p1-solution000003.solution b/tests/exhaustive/issues/286/expected/model_2_2-p1-solution000003.solution deleted file mode 100644 index 7781800dc4..0000000000 --- a/tests/exhaustive/issues/286/expected/model_2_2-p1-solution000003.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting p be partition({1, 2, 4}, {3}) -$ Visualisation for p -$ 1 2 4 -$ 3 - diff --git a/tests/exhaustive/issues/286/expected/model_2_2-p1-solution000004.solution b/tests/exhaustive/issues/286/expected/model_2_2-p1-solution000004.solution deleted file mode 100644 index 1507fcc0c1..0000000000 --- a/tests/exhaustive/issues/286/expected/model_2_2-p1-solution000004.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting p be partition({1, 2}, {3, 4}) -$ Visualisation for p -$ 1 2 -$ 3 4 - diff --git a/tests/exhaustive/issues/286/expected/model_2_2-p1-solution000005.solution b/tests/exhaustive/issues/286/expected/model_2_2-p1-solution000005.solution deleted file mode 100644 index 0368fc950b..0000000000 --- a/tests/exhaustive/issues/286/expected/model_2_2-p1-solution000005.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting p be partition({1, 3, 4}, {2}) -$ Visualisation for p -$ 1 3 4 -$ 2 - diff --git a/tests/exhaustive/issues/286/expected/model_2_2-p1-solution000006.solution b/tests/exhaustive/issues/286/expected/model_2_2-p1-solution000006.solution deleted file mode 100644 index dafa529443..0000000000 --- a/tests/exhaustive/issues/286/expected/model_2_2-p1-solution000006.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting p be partition({1, 3}, {2, 4}) -$ Visualisation for p -$ 1 3 -$ 2 4 - diff --git a/tests/exhaustive/issues/286/expected/model_2_2-p1-solution000007.solution b/tests/exhaustive/issues/286/expected/model_2_2-p1-solution000007.solution deleted file mode 100644 index 69d6c9f6be..0000000000 --- a/tests/exhaustive/issues/286/expected/model_2_2-p1-solution000007.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting p be partition({1, 4}, {2, 3}) -$ Visualisation for p -$ 1 4 -$ 2 3 - diff --git a/tests/exhaustive/issues/286/expected/model_2_2-p1-solution000008.solution b/tests/exhaustive/issues/286/expected/model_2_2-p1-solution000008.solution deleted file mode 100644 index cd8086fa4a..0000000000 --- a/tests/exhaustive/issues/286/expected/model_2_2-p1-solution000008.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting p be partition({1}, {2, 3, 4}) -$ Visualisation for p -$ 1 -$ 2 3 4 - diff --git a/tests/exhaustive/issues/286/expected/model_2_2-p1.eprime-param b/tests/exhaustive/issues/286/expected/model_2_2-p1.eprime-param deleted file mode 100644 index 85954307ca..0000000000 --- a/tests/exhaustive/issues/286/expected/model_2_2-p1.eprime-param +++ /dev/null @@ -1,3 +0,0 @@ -language ESSENCE' 1.0 - -letting b be 4 diff --git a/tests/exhaustive/issues/286/expected/model_2_2.eprime b/tests/exhaustive/issues/286/expected/model_2_2.eprime deleted file mode 100644 index 8d40391ff8..0000000000 --- a/tests/exhaustive/issues/286/expected/model_2_2.eprime +++ /dev/null @@ -1,65 +0,0 @@ -language ESSENCE' 1.0 - -given b: int -find p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker: int(0..b) -find p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy: - matrix indexed by [int(1..b), int(1..b)] of int(1..b + 1) -branching on - [p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker, - p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy] -such that - sum([toInt(q25 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker) | q25 : int(1..b)]) <= - sum([1 | q26_ExplicitVarSizeWithDummy : matrix indexed by [int(1..b)] of int(1..b + 1), - and([q26_ExplicitVarSizeWithDummy[q27] < q26_ExplicitVarSizeWithDummy[q27 + 1] \/ - q26_ExplicitVarSizeWithDummy[q27] = b + 1 - | q27 : int(1..b - 1)]), - and([q26_ExplicitVarSizeWithDummy[q28] = b + 1 -> q26_ExplicitVarSizeWithDummy[q28 + 1] = b + 1 - | q28 : int(1..b - 1)])]) - / 8, - alldifferent_except([toInt(q18 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ - p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q18, q19] != - b + 1) - * - catchUndef(p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q18, q19], - 0) - | q18 : int(1..b), q19 : int(1..b)], - 0), - and([q20 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - sum([toInt(p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q20, q22] != b + 1) - | q22 : int(1..b)]) - >= 1 - | q20 : int(1..b)]), - and([q4 + 1 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - [p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q4, q12] | q12 : int(1..b)] p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - and([p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q5, q14] = 1 - | q14 : int(1..b)]) - | q5 : int(1..b)]), - p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker <= b, - and([q6 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - and([p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q6, q7] < - p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q6, q7 + 1] - \/ p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q6, q7] = b + 1 - | q7 : int(1..b - 1)]) - | q6 : int(1..b)]), - and([q6 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - and([p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q6, q8] = b + 1 -> - p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q6, q8 + 1] = b + 1 - | q8 : int(1..b - 1)]) - | q6 : int(1..b)]), - and([q6 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - sum([toInt(p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q6, q9] != b + 1) - | q9 : int(1..b)]) - <= b - | q6 : int(1..b)]), - b = - sum([toInt(q15 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker) * - catchUndef(sum([toInt(p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q15, q17] != - b + 1) - | q17 : int(1..b)]), - 0) - | q15 : int(1..b)]) - diff --git a/tests/exhaustive/issues/286/expected/model_2_3-p1-solution000001.solution b/tests/exhaustive/issues/286/expected/model_2_3-p1-solution000001.solution deleted file mode 100644 index 8f7fa48018..0000000000 --- a/tests/exhaustive/issues/286/expected/model_2_3-p1-solution000001.solution +++ /dev/null @@ -1,6 +0,0 @@ -language Essence 1.3 - -letting p be partition({1, 2, 3, 4}) -$ Visualisation for p -$ 1 2 3 4 - diff --git a/tests/exhaustive/issues/286/expected/model_2_3-p1-solution000002.solution b/tests/exhaustive/issues/286/expected/model_2_3-p1-solution000002.solution deleted file mode 100644 index cd8086fa4a..0000000000 --- a/tests/exhaustive/issues/286/expected/model_2_3-p1-solution000002.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting p be partition({1}, {2, 3, 4}) -$ Visualisation for p -$ 1 -$ 2 3 4 - diff --git a/tests/exhaustive/issues/286/expected/model_2_3-p1-solution000003.solution b/tests/exhaustive/issues/286/expected/model_2_3-p1-solution000003.solution deleted file mode 100644 index 0368fc950b..0000000000 --- a/tests/exhaustive/issues/286/expected/model_2_3-p1-solution000003.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting p be partition({1, 3, 4}, {2}) -$ Visualisation for p -$ 1 3 4 -$ 2 - diff --git a/tests/exhaustive/issues/286/expected/model_2_3-p1-solution000004.solution b/tests/exhaustive/issues/286/expected/model_2_3-p1-solution000004.solution deleted file mode 100644 index 7781800dc4..0000000000 --- a/tests/exhaustive/issues/286/expected/model_2_3-p1-solution000004.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting p be partition({1, 2, 4}, {3}) -$ Visualisation for p -$ 1 2 4 -$ 3 - diff --git a/tests/exhaustive/issues/286/expected/model_2_3-p1-solution000005.solution b/tests/exhaustive/issues/286/expected/model_2_3-p1-solution000005.solution deleted file mode 100644 index 556f2c0ecc..0000000000 --- a/tests/exhaustive/issues/286/expected/model_2_3-p1-solution000005.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting p be partition({1, 2, 3}, {4}) -$ Visualisation for p -$ 1 2 3 -$ 4 - diff --git a/tests/exhaustive/issues/286/expected/model_2_3-p1-solution000006.solution b/tests/exhaustive/issues/286/expected/model_2_3-p1-solution000006.solution deleted file mode 100644 index 1507fcc0c1..0000000000 --- a/tests/exhaustive/issues/286/expected/model_2_3-p1-solution000006.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting p be partition({1, 2}, {3, 4}) -$ Visualisation for p -$ 1 2 -$ 3 4 - diff --git a/tests/exhaustive/issues/286/expected/model_2_3-p1-solution000007.solution b/tests/exhaustive/issues/286/expected/model_2_3-p1-solution000007.solution deleted file mode 100644 index dafa529443..0000000000 --- a/tests/exhaustive/issues/286/expected/model_2_3-p1-solution000007.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting p be partition({1, 3}, {2, 4}) -$ Visualisation for p -$ 1 3 -$ 2 4 - diff --git a/tests/exhaustive/issues/286/expected/model_2_3-p1-solution000008.solution b/tests/exhaustive/issues/286/expected/model_2_3-p1-solution000008.solution deleted file mode 100644 index 69d6c9f6be..0000000000 --- a/tests/exhaustive/issues/286/expected/model_2_3-p1-solution000008.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting p be partition({1, 4}, {2, 3}) -$ Visualisation for p -$ 1 4 -$ 2 3 - diff --git a/tests/exhaustive/issues/286/expected/model_2_3-p1.eprime-param b/tests/exhaustive/issues/286/expected/model_2_3-p1.eprime-param deleted file mode 100644 index 85954307ca..0000000000 --- a/tests/exhaustive/issues/286/expected/model_2_3-p1.eprime-param +++ /dev/null @@ -1,3 +0,0 @@ -language ESSENCE' 1.0 - -letting b be 4 diff --git a/tests/exhaustive/issues/286/expected/model_2_3.eprime b/tests/exhaustive/issues/286/expected/model_2_3.eprime deleted file mode 100644 index d091c5fe08..0000000000 --- a/tests/exhaustive/issues/286/expected/model_2_3.eprime +++ /dev/null @@ -1,164 +0,0 @@ -language ESSENCE' 1.0 - -given b: int -find p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker: int(0..b) -find p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy: - matrix indexed by [int(1..b), int(1..b)] of int(1..b + 1) -find p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker: int(0..b) -find p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker: - matrix indexed by [int(1..b)] of int(0..b) -find p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values: - matrix indexed by [int(1..b), int(1..b)] of int(1..b) -branching on - [p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker, - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker, - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values, - p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker, - p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy] -such that - sum([toInt(q70 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker) | q70 : int(1..b)]) <= - sum([1 | q71_ExplicitVarSizeWithDummy : matrix indexed by [int(1..b)] of int(1..b + 1), - and([q71_ExplicitVarSizeWithDummy[q72] < q71_ExplicitVarSizeWithDummy[q72 + 1] \/ - q71_ExplicitVarSizeWithDummy[q72] = b + 1 - | q72 : int(1..b - 1)]), - and([q71_ExplicitVarSizeWithDummy[q73] = b + 1 -> q71_ExplicitVarSizeWithDummy[q73 + 1] = b + 1 - | q73 : int(1..b - 1)])]) - / 8, - alldifferent_except([toInt(q57 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ - p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q57, q58] != - b + 1) - * - catchUndef(p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q57, q58], - 0) - | q57 : int(1..b), q58 : int(1..b)], - 0), - and([q59 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - sum([toInt(p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q59, q61] != b + 1) - | q61 : int(1..b)]) - >= 1 - | q59 : int(1..b)]), - and([q4 + 1 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - [p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q4, q22] | q22 : int(1..b)] p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - and([p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q5, q24] = 1 - | q24 : int(1..b)]) - | q5 : int(1..b)]), - p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker <= b, - and([q6 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - and([p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q6, q7] < - p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q6, q7 + 1] - \/ p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q6, q7] = b + 1 - | q7 : int(1..b - 1)]) - | q6 : int(1..b)]), - and([q6 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - and([p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q6, q8] = b + 1 -> - p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q6, q8 + 1] = b + 1 - | q8 : int(1..b - 1)]) - | q6 : int(1..b)]), - and([q6 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - sum([toInt(p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q6, q9] != b + 1) - | q9 : int(1..b)]) - <= b - | q6 : int(1..b)]), - b = - sum([toInt(q62 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker) * - catchUndef(sum([toInt(p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q62, q64] != - b + 1) - | q64 : int(1..b)]), - 0) - | q62 : int(1..b)]), - alldifferent_except([toInt(q65 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - q66 <= - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q65]) - * - catchUndef(p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q65, q66], - 0) - | q65 : int(1..b), q66 : int(1..b)], - 0), - and([q67 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q67] >= 1 - | q67 : int(1..b)]), - and([q15 + 1 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - flatten([[p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q15]; int(1)], - flatten([[p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q15, q25]; - int(1)] - | q25 : int(1..b)]); - int(1..2)]) - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q16] = 0 /\ - and([p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q16, q27] = 1 - | q27 : int(1..b)]) - | q16 : int(1..b)]), - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker <= b, - and([q17 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - and([q18 + 1 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q17] -> - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q17, q18] < - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q17, q18 + 1] - | q18 : int(1..b - 1)]) - | q17 : int(1..b)]), - and([q17 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - and([q19 > p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q17] -> - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q17, q19] = 1 - | q19 : int(1..b)]) - | q17 : int(1..b)]), - and([q17 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q17] <= b - | q17 : int(1..b)]), - b = - sum([toInt(q28 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker) * - catchUndef(p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q28], 0) - | q28 : int(1..b)]), - and([q31 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - or([q34 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ - (and([p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q34, q36] != b + 1 -> - or([q38 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q31] - /\ - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q31, q38] = - p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q34, q36] - | q38 : int(1..b)]) - | q36 : int(1..b)]) - /\ - and([q40 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q31] -> - or([p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q34, q42] != b + 1 - /\ - p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q34, q42] = - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q31, q40] - | q42 : int(1..b)]) - | q40 : int(1..b)])) - | q34 : int(1..b)]) - | q31 : int(1..b)]), - and([q45 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - or([q48 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - (and([q50 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q48] -> - or([p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q45, q52] != b + 1 - /\ - p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q45, q52] = - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q48, q50] - | q52 : int(1..b)]) - | q50 : int(1..b)]) - /\ - and([p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q45, q54] != b + 1 -> - or([q56 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q48] - /\ - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q48, q56] = - p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q45, q54] - | q56 : int(1..b)]) - | q54 : int(1..b)])) - | q48 : int(1..b)]) - | q45 : int(1..b)]) - diff --git a/tests/exhaustive/issues/286/expected/model_2_4-p1-solution000001.solution b/tests/exhaustive/issues/286/expected/model_2_4-p1-solution000001.solution deleted file mode 100644 index 8f7fa48018..0000000000 --- a/tests/exhaustive/issues/286/expected/model_2_4-p1-solution000001.solution +++ /dev/null @@ -1,6 +0,0 @@ -language Essence 1.3 - -letting p be partition({1, 2, 3, 4}) -$ Visualisation for p -$ 1 2 3 4 - diff --git a/tests/exhaustive/issues/286/expected/model_2_4-p1-solution000002.solution b/tests/exhaustive/issues/286/expected/model_2_4-p1-solution000002.solution deleted file mode 100644 index 556f2c0ecc..0000000000 --- a/tests/exhaustive/issues/286/expected/model_2_4-p1-solution000002.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting p be partition({1, 2, 3}, {4}) -$ Visualisation for p -$ 1 2 3 -$ 4 - diff --git a/tests/exhaustive/issues/286/expected/model_2_4-p1-solution000003.solution b/tests/exhaustive/issues/286/expected/model_2_4-p1-solution000003.solution deleted file mode 100644 index 7781800dc4..0000000000 --- a/tests/exhaustive/issues/286/expected/model_2_4-p1-solution000003.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting p be partition({1, 2, 4}, {3}) -$ Visualisation for p -$ 1 2 4 -$ 3 - diff --git a/tests/exhaustive/issues/286/expected/model_2_4-p1-solution000004.solution b/tests/exhaustive/issues/286/expected/model_2_4-p1-solution000004.solution deleted file mode 100644 index 1507fcc0c1..0000000000 --- a/tests/exhaustive/issues/286/expected/model_2_4-p1-solution000004.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting p be partition({1, 2}, {3, 4}) -$ Visualisation for p -$ 1 2 -$ 3 4 - diff --git a/tests/exhaustive/issues/286/expected/model_2_4-p1-solution000005.solution b/tests/exhaustive/issues/286/expected/model_2_4-p1-solution000005.solution deleted file mode 100644 index 0368fc950b..0000000000 --- a/tests/exhaustive/issues/286/expected/model_2_4-p1-solution000005.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting p be partition({1, 3, 4}, {2}) -$ Visualisation for p -$ 1 3 4 -$ 2 - diff --git a/tests/exhaustive/issues/286/expected/model_2_4-p1-solution000006.solution b/tests/exhaustive/issues/286/expected/model_2_4-p1-solution000006.solution deleted file mode 100644 index dafa529443..0000000000 --- a/tests/exhaustive/issues/286/expected/model_2_4-p1-solution000006.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting p be partition({1, 3}, {2, 4}) -$ Visualisation for p -$ 1 3 -$ 2 4 - diff --git a/tests/exhaustive/issues/286/expected/model_2_4-p1-solution000007.solution b/tests/exhaustive/issues/286/expected/model_2_4-p1-solution000007.solution deleted file mode 100644 index 69d6c9f6be..0000000000 --- a/tests/exhaustive/issues/286/expected/model_2_4-p1-solution000007.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting p be partition({1, 4}, {2, 3}) -$ Visualisation for p -$ 1 4 -$ 2 3 - diff --git a/tests/exhaustive/issues/286/expected/model_2_4-p1-solution000008.solution b/tests/exhaustive/issues/286/expected/model_2_4-p1-solution000008.solution deleted file mode 100644 index cd8086fa4a..0000000000 --- a/tests/exhaustive/issues/286/expected/model_2_4-p1-solution000008.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting p be partition({1}, {2, 3, 4}) -$ Visualisation for p -$ 1 -$ 2 3 4 - diff --git a/tests/exhaustive/issues/286/expected/model_2_4-p1.eprime-param b/tests/exhaustive/issues/286/expected/model_2_4-p1.eprime-param deleted file mode 100644 index 85954307ca..0000000000 --- a/tests/exhaustive/issues/286/expected/model_2_4-p1.eprime-param +++ /dev/null @@ -1,3 +0,0 @@ -language ESSENCE' 1.0 - -letting b be 4 diff --git a/tests/exhaustive/issues/286/expected/model_2_4.eprime b/tests/exhaustive/issues/286/expected/model_2_4.eprime deleted file mode 100644 index f24fc7e366..0000000000 --- a/tests/exhaustive/issues/286/expected/model_2_4.eprime +++ /dev/null @@ -1,121 +0,0 @@ -language ESSENCE' 1.0 - -given b: int -find p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker: int(0..b) -find p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy: - matrix indexed by [int(1..b), int(1..b)] of int(1..b + 1) -find p_PartitionOccurrence_NumParts: int(1..b) -find p_PartitionOccurrence_WhichPart: matrix indexed by [int(1..b)] of int(1..b) -find p_PartitionOccurrence_PartSizes: matrix indexed by [int(1..b)] of int(0..b) -find p_PartitionOccurrence_FirstIndex: matrix indexed by [int(1..b)] of int(1..b) -branching on - [p_PartitionOccurrence_NumParts, p_PartitionOccurrence_WhichPart, p_PartitionOccurrence_PartSizes, - p_PartitionOccurrence_FirstIndex, p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker, - p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy] -such that - sum([toInt(q63 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker) | q63 : int(1..b)]) <= - sum([1 | q64_ExplicitVarSizeWithDummy : matrix indexed by [int(1..b)] of int(1..b + 1), - and([q64_ExplicitVarSizeWithDummy[q65] < q64_ExplicitVarSizeWithDummy[q65 + 1] \/ - q64_ExplicitVarSizeWithDummy[q65] = b + 1 - | q65 : int(1..b - 1)]), - and([q64_ExplicitVarSizeWithDummy[q66] = b + 1 -> q64_ExplicitVarSizeWithDummy[q66 + 1] = b + 1 - | q66 : int(1..b - 1)])]) - / 8, - alldifferent_except([toInt(q53 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ - p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q53, q54] != - b + 1) - * - catchUndef(p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q53, q54], - 0) - | q53 : int(1..b), q54 : int(1..b)], - 0), - and([q55 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - sum([toInt(p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q55, q57] != b + 1) - | q57 : int(1..b)]) - >= 1 - | q55 : int(1..b)]), - and([q4 + 1 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - [p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q4, q22] | q22 : int(1..b)] p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - and([p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q5, q24] = 1 - | q24 : int(1..b)]) - | q5 : int(1..b)]), - p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker <= b, - and([q6 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - and([p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q6, q7] < - p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q6, q7 + 1] - \/ p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q6, q7] = b + 1 - | q7 : int(1..b - 1)]) - | q6 : int(1..b)]), - and([q6 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - and([p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q6, q8] = b + 1 -> - p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q6, q8 + 1] = b + 1 - | q8 : int(1..b - 1)]) - | q6 : int(1..b)]), - and([q6 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - sum([toInt(p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q6, q9] != b + 1) - | q9 : int(1..b)]) - <= b - | q6 : int(1..b)]), - b = - sum([toInt(q58 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker) * - catchUndef(sum([toInt(p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q58, q60] != - b + 1) - | q60 : int(1..b)]), - 0) - | q58 : int(1..b)]), - and([q12 <= p_PartitionOccurrence_NumParts -> p_PartitionOccurrence_PartSizes[q12] <= b | q12 : int(1..b)]), - and([q12 > p_PartitionOccurrence_NumParts -> p_PartitionOccurrence_PartSizes[q12] = 0 | q12 : int(1..b)]), - p_PartitionOccurrence_NumParts <= b, - and([q13 <= p_PartitionOccurrence_NumParts -> or([p_PartitionOccurrence_WhichPart[q14] = q13 | q14 : int(1..b)]) - | q13 : int(3..b)]), - p_PartitionOccurrence_NumParts = max([p_PartitionOccurrence_WhichPart[q15] | q15 : int(1..b)]), - and([p_PartitionOccurrence_PartSizes[q16] = - sum([toInt(p_PartitionOccurrence_WhichPart[q17] = q16) | q17 : int(1..b)]) - | q16 : int(1..b)]), - and([q18 <= p_PartitionOccurrence_NumParts -> - and([p_PartitionOccurrence_WhichPart[q19] = q18 -> p_PartitionOccurrence_FirstIndex[q18] <= q19 - | q19 : int(1..b)]) - | q18 : int(1..b)]), - and([q18 <= p_PartitionOccurrence_NumParts -> - or([p_PartitionOccurrence_WhichPart[q19] = q18 /\ p_PartitionOccurrence_FirstIndex[q18] = q19 - | q19 : int(1..b)]) - | q18 : int(1..b)]), - and([q18 > p_PartitionOccurrence_NumParts -> p_PartitionOccurrence_FirstIndex[q18] = 1 | q18 : int(1..b)]), - and([q20 <= p_PartitionOccurrence_NumParts /\ q21 <= p_PartitionOccurrence_NumParts -> - (q20 < q21 <-> p_PartitionOccurrence_FirstIndex[q20] < p_PartitionOccurrence_FirstIndex[q21]) - | q20 : int(1..b), q21 : int(1..b)]), - and([q26 <= p_PartitionOccurrence_NumParts -> - or([q30 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ - (and([p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q30, q32] != b + 1 -> - or([p_PartitionOccurrence_WhichPart[q34] = q26 /\ - q34 = p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q30, q32] - | q34 : int(1..b)]) - | q32 : int(1..b)]) - /\ - and([p_PartitionOccurrence_WhichPart[q36] = q26 -> - or([p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q30, q38] != b + 1 - /\ p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q30, q38] = q36 - | q38 : int(1..b)]) - | q36 : int(1..b)])) - | q30 : int(1..b)]) - | q26 : int(1..b)]), - and([q41 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - or([q43 <= p_PartitionOccurrence_NumParts /\ - (and([p_PartitionOccurrence_WhichPart[q46] = q43 -> - or([p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q41, q48] != b + 1 - /\ p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q41, q48] = q46 - | q48 : int(1..b)]) - | q46 : int(1..b)]) - /\ - and([p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q41, q50] != b + 1 -> - or([p_PartitionOccurrence_WhichPart[q52] = q43 /\ - q52 = p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q41, q50] - | q52 : int(1..b)]) - | q50 : int(1..b)])) - | q43 : int(1..b)]) - | q41 : int(1..b)]) - diff --git a/tests/exhaustive/issues/286/expected/model_3_1-p1-solution000001.solution b/tests/exhaustive/issues/286/expected/model_3_1-p1-solution000001.solution deleted file mode 100644 index 8f7fa48018..0000000000 --- a/tests/exhaustive/issues/286/expected/model_3_1-p1-solution000001.solution +++ /dev/null @@ -1,6 +0,0 @@ -language Essence 1.3 - -letting p be partition({1, 2, 3, 4}) -$ Visualisation for p -$ 1 2 3 4 - diff --git a/tests/exhaustive/issues/286/expected/model_3_1-p1-solution000002.solution b/tests/exhaustive/issues/286/expected/model_3_1-p1-solution000002.solution deleted file mode 100644 index cd8086fa4a..0000000000 --- a/tests/exhaustive/issues/286/expected/model_3_1-p1-solution000002.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting p be partition({1}, {2, 3, 4}) -$ Visualisation for p -$ 1 -$ 2 3 4 - diff --git a/tests/exhaustive/issues/286/expected/model_3_1-p1-solution000003.solution b/tests/exhaustive/issues/286/expected/model_3_1-p1-solution000003.solution deleted file mode 100644 index 69d6c9f6be..0000000000 --- a/tests/exhaustive/issues/286/expected/model_3_1-p1-solution000003.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting p be partition({1, 4}, {2, 3}) -$ Visualisation for p -$ 1 4 -$ 2 3 - diff --git a/tests/exhaustive/issues/286/expected/model_3_1-p1-solution000004.solution b/tests/exhaustive/issues/286/expected/model_3_1-p1-solution000004.solution deleted file mode 100644 index dafa529443..0000000000 --- a/tests/exhaustive/issues/286/expected/model_3_1-p1-solution000004.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting p be partition({1, 3}, {2, 4}) -$ Visualisation for p -$ 1 3 -$ 2 4 - diff --git a/tests/exhaustive/issues/286/expected/model_3_1-p1-solution000005.solution b/tests/exhaustive/issues/286/expected/model_3_1-p1-solution000005.solution deleted file mode 100644 index 0368fc950b..0000000000 --- a/tests/exhaustive/issues/286/expected/model_3_1-p1-solution000005.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting p be partition({1, 3, 4}, {2}) -$ Visualisation for p -$ 1 3 4 -$ 2 - diff --git a/tests/exhaustive/issues/286/expected/model_3_1-p1-solution000006.solution b/tests/exhaustive/issues/286/expected/model_3_1-p1-solution000006.solution deleted file mode 100644 index 1507fcc0c1..0000000000 --- a/tests/exhaustive/issues/286/expected/model_3_1-p1-solution000006.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting p be partition({1, 2}, {3, 4}) -$ Visualisation for p -$ 1 2 -$ 3 4 - diff --git a/tests/exhaustive/issues/286/expected/model_3_1-p1-solution000007.solution b/tests/exhaustive/issues/286/expected/model_3_1-p1-solution000007.solution deleted file mode 100644 index 7781800dc4..0000000000 --- a/tests/exhaustive/issues/286/expected/model_3_1-p1-solution000007.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting p be partition({1, 2, 4}, {3}) -$ Visualisation for p -$ 1 2 4 -$ 3 - diff --git a/tests/exhaustive/issues/286/expected/model_3_1-p1-solution000008.solution b/tests/exhaustive/issues/286/expected/model_3_1-p1-solution000008.solution deleted file mode 100644 index 556f2c0ecc..0000000000 --- a/tests/exhaustive/issues/286/expected/model_3_1-p1-solution000008.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting p be partition({1, 2, 3}, {4}) -$ Visualisation for p -$ 1 2 3 -$ 4 - diff --git a/tests/exhaustive/issues/286/expected/model_3_1-p1.eprime-param b/tests/exhaustive/issues/286/expected/model_3_1-p1.eprime-param deleted file mode 100644 index 85954307ca..0000000000 --- a/tests/exhaustive/issues/286/expected/model_3_1-p1.eprime-param +++ /dev/null @@ -1,3 +0,0 @@ -language ESSENCE' 1.0 - -letting b be 4 diff --git a/tests/exhaustive/issues/286/expected/model_3_1.eprime b/tests/exhaustive/issues/286/expected/model_3_1.eprime deleted file mode 100644 index c8d3540e60..0000000000 --- a/tests/exhaustive/issues/286/expected/model_3_1.eprime +++ /dev/null @@ -1,136 +0,0 @@ -language ESSENCE' 1.0 - -given b: int -find p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker: int(0..b) -find p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker: - matrix indexed by [int(1..b)] of int(0..b) -find p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values: - matrix indexed by [int(1..b), int(1..b)] of int(1..b) -find p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker: int(0..b) -find p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence: matrix indexed by [int(1..b), int(1..b)] of bool -branching on - [p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker, - p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence, - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker, - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker, - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values] -such that - sum([toInt(q58 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker) | q58 : int(1..b)]) <= - sum([1 | q59_ExplicitVarSizeWithDummy : matrix indexed by [int(1..b)] of int(1..b + 1), - and([q59_ExplicitVarSizeWithDummy[q60] < q59_ExplicitVarSizeWithDummy[q60 + 1] \/ - q59_ExplicitVarSizeWithDummy[q60] = b + 1 - | q60 : int(1..b - 1)]), - and([q59_ExplicitVarSizeWithDummy[q61] = b + 1 -> q59_ExplicitVarSizeWithDummy[q61 + 1] = b + 1 - | q61 : int(1..b - 1)])]) - / 8, - alldifferent_except([toInt(q50 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - q51 <= - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q50]) - * - catchUndef(p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q50, q51], - 0) - | q50 : int(1..b), q51 : int(1..b)], - 0), - and([q52 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q52] >= 1 - | q52 : int(1..b)]), - and([q4 + 1 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - flatten([[p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q4]; int(1)], - flatten([[p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q4, q19]; - int(1)] - | q19 : int(1..b)]); - int(1..2)]) - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q5] = 0 /\ - and([p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q5, q21] = 1 - | q21 : int(1..b)]) - | q5 : int(1..b)]), - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker <= b, - and([q6 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - and([q7 + 1 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q6] -> - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q6, q7] < - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q6, q7 + 1] - | q7 : int(1..b - 1)]) - | q6 : int(1..b)]), - and([q6 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - and([q8 > p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q6] -> - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q6, q8] = 1 - | q8 : int(1..b)]) - | q6 : int(1..b)]), - and([q6 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q6] <= b - | q6 : int(1..b)]), - b = - sum([toInt(q53 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker) * - catchUndef(p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q53], 0) - | q53 : int(1..b)]), - and([1 = - sum([toInt(q22 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ - p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q22, q11]) - | q22 : int(1..b)]) - | q11 : int(1..b)]), - and([q54 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> - sum([toInt(p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q54, q55]) | q55 : int(1..b)]) >= 1 - | q54 : int(1..b)]), - and([q14 + 1 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> - [-toInt(p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q14, q23]) | q23 : int(1..b)] p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> - and([p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q15, q25] = false | q25 : int(1..b)]) - | q15 : int(1..b)]), - p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker <= b, - and([q16 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> - sum([toInt(p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q16, q17]) | q17 : int(1..b)]) <= b - | q16 : int(1..b)]), - b = - sum([toInt(q26 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker) * - catchUndef(sum([toInt(p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q26, q27]) - | q27 : int(1..b)]), - 0) - | q26 : int(1..b)]), - and([q30 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> - or([q33 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - (and([q35 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q33] -> - p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence - [q30, - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q33, q35]] - | q35 : int(1..b)]) - /\ - and([p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q30, q36] -> - or([q38 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q33] - /\ - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q33, q38] = - q36 | q38 : int(1..b)]) - | q36 : int(1..b)])) - | q33 : int(1..b)]) - | q30 : int(1..b)]), - and([q41 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - or([q44 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ - (and([p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q44, q45] -> - or([q47 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q41] - /\ - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q41, q47] = - q45 | q47 : int(1..b)]) - | q45 : int(1..b)]) - /\ - and([q49 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q41] -> - p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence - [q44, - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q41, q49]] - | q49 : int(1..b)])) - | q44 : int(1..b)]) - | q41 : int(1..b)]) - diff --git a/tests/exhaustive/issues/286/expected/model_3_2-p1-solution000001.solution b/tests/exhaustive/issues/286/expected/model_3_2-p1-solution000001.solution deleted file mode 100644 index 8f7fa48018..0000000000 --- a/tests/exhaustive/issues/286/expected/model_3_2-p1-solution000001.solution +++ /dev/null @@ -1,6 +0,0 @@ -language Essence 1.3 - -letting p be partition({1, 2, 3, 4}) -$ Visualisation for p -$ 1 2 3 4 - diff --git a/tests/exhaustive/issues/286/expected/model_3_2-p1-solution000002.solution b/tests/exhaustive/issues/286/expected/model_3_2-p1-solution000002.solution deleted file mode 100644 index 556f2c0ecc..0000000000 --- a/tests/exhaustive/issues/286/expected/model_3_2-p1-solution000002.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting p be partition({1, 2, 3}, {4}) -$ Visualisation for p -$ 1 2 3 -$ 4 - diff --git a/tests/exhaustive/issues/286/expected/model_3_2-p1-solution000003.solution b/tests/exhaustive/issues/286/expected/model_3_2-p1-solution000003.solution deleted file mode 100644 index 7781800dc4..0000000000 --- a/tests/exhaustive/issues/286/expected/model_3_2-p1-solution000003.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting p be partition({1, 2, 4}, {3}) -$ Visualisation for p -$ 1 2 4 -$ 3 - diff --git a/tests/exhaustive/issues/286/expected/model_3_2-p1-solution000004.solution b/tests/exhaustive/issues/286/expected/model_3_2-p1-solution000004.solution deleted file mode 100644 index 1507fcc0c1..0000000000 --- a/tests/exhaustive/issues/286/expected/model_3_2-p1-solution000004.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting p be partition({1, 2}, {3, 4}) -$ Visualisation for p -$ 1 2 -$ 3 4 - diff --git a/tests/exhaustive/issues/286/expected/model_3_2-p1-solution000005.solution b/tests/exhaustive/issues/286/expected/model_3_2-p1-solution000005.solution deleted file mode 100644 index 0368fc950b..0000000000 --- a/tests/exhaustive/issues/286/expected/model_3_2-p1-solution000005.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting p be partition({1, 3, 4}, {2}) -$ Visualisation for p -$ 1 3 4 -$ 2 - diff --git a/tests/exhaustive/issues/286/expected/model_3_2-p1-solution000006.solution b/tests/exhaustive/issues/286/expected/model_3_2-p1-solution000006.solution deleted file mode 100644 index dafa529443..0000000000 --- a/tests/exhaustive/issues/286/expected/model_3_2-p1-solution000006.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting p be partition({1, 3}, {2, 4}) -$ Visualisation for p -$ 1 3 -$ 2 4 - diff --git a/tests/exhaustive/issues/286/expected/model_3_2-p1-solution000007.solution b/tests/exhaustive/issues/286/expected/model_3_2-p1-solution000007.solution deleted file mode 100644 index 69d6c9f6be..0000000000 --- a/tests/exhaustive/issues/286/expected/model_3_2-p1-solution000007.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting p be partition({1, 4}, {2, 3}) -$ Visualisation for p -$ 1 4 -$ 2 3 - diff --git a/tests/exhaustive/issues/286/expected/model_3_2-p1-solution000008.solution b/tests/exhaustive/issues/286/expected/model_3_2-p1-solution000008.solution deleted file mode 100644 index cd8086fa4a..0000000000 --- a/tests/exhaustive/issues/286/expected/model_3_2-p1-solution000008.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting p be partition({1}, {2, 3, 4}) -$ Visualisation for p -$ 1 -$ 2 3 4 - diff --git a/tests/exhaustive/issues/286/expected/model_3_2-p1.eprime-param b/tests/exhaustive/issues/286/expected/model_3_2-p1.eprime-param deleted file mode 100644 index 85954307ca..0000000000 --- a/tests/exhaustive/issues/286/expected/model_3_2-p1.eprime-param +++ /dev/null @@ -1,3 +0,0 @@ -language ESSENCE' 1.0 - -letting b be 4 diff --git a/tests/exhaustive/issues/286/expected/model_3_2.eprime b/tests/exhaustive/issues/286/expected/model_3_2.eprime deleted file mode 100644 index d2396ee5a7..0000000000 --- a/tests/exhaustive/issues/286/expected/model_3_2.eprime +++ /dev/null @@ -1,164 +0,0 @@ -language ESSENCE' 1.0 - -given b: int -find p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker: int(0..b) -find p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker: - matrix indexed by [int(1..b)] of int(0..b) -find p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values: - matrix indexed by [int(1..b), int(1..b)] of int(1..b) -find p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker: int(0..b) -find p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy: - matrix indexed by [int(1..b), int(1..b)] of int(1..b + 1) -branching on - [p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker, - p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy, - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker, - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker, - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values] -such that - sum([toInt(q70 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker) | q70 : int(1..b)]) <= - sum([1 | q71_ExplicitVarSizeWithDummy : matrix indexed by [int(1..b)] of int(1..b + 1), - and([q71_ExplicitVarSizeWithDummy[q72] < q71_ExplicitVarSizeWithDummy[q72 + 1] \/ - q71_ExplicitVarSizeWithDummy[q72] = b + 1 - | q72 : int(1..b - 1)]), - and([q71_ExplicitVarSizeWithDummy[q73] = b + 1 -> q71_ExplicitVarSizeWithDummy[q73 + 1] = b + 1 - | q73 : int(1..b - 1)])]) - / 8, - alldifferent_except([toInt(q59 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - q60 <= - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q59]) - * - catchUndef(p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q59, q60], - 0) - | q59 : int(1..b), q60 : int(1..b)], - 0), - and([q61 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q61] >= 1 - | q61 : int(1..b)]), - and([q4 + 1 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - flatten([[p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q4]; int(1)], - flatten([[p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q4, q22]; - int(1)] - | q22 : int(1..b)]); - int(1..2)]) - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q5] = 0 /\ - and([p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q5, q24] = 1 - | q24 : int(1..b)]) - | q5 : int(1..b)]), - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker <= b, - and([q6 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - and([q7 + 1 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q6] -> - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q6, q7] < - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q6, q7 + 1] - | q7 : int(1..b - 1)]) - | q6 : int(1..b)]), - and([q6 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - and([q8 > p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q6] -> - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q6, q8] = 1 - | q8 : int(1..b)]) - | q6 : int(1..b)]), - and([q6 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q6] <= b - | q6 : int(1..b)]), - b = - sum([toInt(q62 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker) * - catchUndef(p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q62], 0) - | q62 : int(1..b)]), - alldifferent_except([toInt(q63 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ - p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q63, q64] != - b + 1) - * - catchUndef(p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q63, q64], - 0) - | q63 : int(1..b), q64 : int(1..b)], - 0), - and([q65 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - sum([toInt(p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q65, q67] != b + 1) - | q67 : int(1..b)]) - >= 1 - | q65 : int(1..b)]), - and([q14 + 1 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - [p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q14, q25] | q25 : int(1..b)] p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - and([p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q15, q27] = 1 - | q27 : int(1..b)]) - | q15 : int(1..b)]), - p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker <= b, - and([q16 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - and([p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q16, q17] < - p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q16, q17 + 1] - \/ p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q16, q17] = b + 1 - | q17 : int(1..b - 1)]) - | q16 : int(1..b)]), - and([q16 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - and([p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q16, q18] = b + 1 -> - p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q16, q18 + 1] = b + 1 - | q18 : int(1..b - 1)]) - | q16 : int(1..b)]), - and([q16 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - sum([toInt(p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q16, q19] != b + 1) - | q19 : int(1..b)]) - <= b - | q16 : int(1..b)]), - b = - sum([toInt(q28 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker) * - catchUndef(sum([toInt(p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q28, q30] != - b + 1) - | q30 : int(1..b)]), - 0) - | q28 : int(1..b)]), - and([q33 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - or([q36 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - (and([q38 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q36] -> - or([p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q33, q40] != b + 1 - /\ - p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q33, q40] = - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q36, q38] - | q40 : int(1..b)]) - | q38 : int(1..b)]) - /\ - and([p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q33, q42] != b + 1 -> - or([q44 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q36] - /\ - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q36, q44] = - p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q33, q42] - | q44 : int(1..b)]) - | q42 : int(1..b)])) - | q36 : int(1..b)]) - | q33 : int(1..b)]), - and([q47 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - or([q50 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ - (and([p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q50, q52] != b + 1 -> - or([q54 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q47] - /\ - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q47, q54] = - p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q50, q52] - | q54 : int(1..b)]) - | q52 : int(1..b)]) - /\ - and([q56 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q47] -> - or([p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q50, q58] != b + 1 - /\ - p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q50, q58] = - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q47, q56] - | q58 : int(1..b)]) - | q56 : int(1..b)])) - | q50 : int(1..b)]) - | q47 : int(1..b)]) - diff --git a/tests/exhaustive/issues/286/expected/model_3_3-p1-solution000001.solution b/tests/exhaustive/issues/286/expected/model_3_3-p1-solution000001.solution deleted file mode 100644 index 8f7fa48018..0000000000 --- a/tests/exhaustive/issues/286/expected/model_3_3-p1-solution000001.solution +++ /dev/null @@ -1,6 +0,0 @@ -language Essence 1.3 - -letting p be partition({1, 2, 3, 4}) -$ Visualisation for p -$ 1 2 3 4 - diff --git a/tests/exhaustive/issues/286/expected/model_3_3-p1-solution000002.solution b/tests/exhaustive/issues/286/expected/model_3_3-p1-solution000002.solution deleted file mode 100644 index cd8086fa4a..0000000000 --- a/tests/exhaustive/issues/286/expected/model_3_3-p1-solution000002.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting p be partition({1}, {2, 3, 4}) -$ Visualisation for p -$ 1 -$ 2 3 4 - diff --git a/tests/exhaustive/issues/286/expected/model_3_3-p1-solution000003.solution b/tests/exhaustive/issues/286/expected/model_3_3-p1-solution000003.solution deleted file mode 100644 index 0368fc950b..0000000000 --- a/tests/exhaustive/issues/286/expected/model_3_3-p1-solution000003.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting p be partition({1, 3, 4}, {2}) -$ Visualisation for p -$ 1 3 4 -$ 2 - diff --git a/tests/exhaustive/issues/286/expected/model_3_3-p1-solution000004.solution b/tests/exhaustive/issues/286/expected/model_3_3-p1-solution000004.solution deleted file mode 100644 index 7781800dc4..0000000000 --- a/tests/exhaustive/issues/286/expected/model_3_3-p1-solution000004.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting p be partition({1, 2, 4}, {3}) -$ Visualisation for p -$ 1 2 4 -$ 3 - diff --git a/tests/exhaustive/issues/286/expected/model_3_3-p1-solution000005.solution b/tests/exhaustive/issues/286/expected/model_3_3-p1-solution000005.solution deleted file mode 100644 index 556f2c0ecc..0000000000 --- a/tests/exhaustive/issues/286/expected/model_3_3-p1-solution000005.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting p be partition({1, 2, 3}, {4}) -$ Visualisation for p -$ 1 2 3 -$ 4 - diff --git a/tests/exhaustive/issues/286/expected/model_3_3-p1-solution000006.solution b/tests/exhaustive/issues/286/expected/model_3_3-p1-solution000006.solution deleted file mode 100644 index 1507fcc0c1..0000000000 --- a/tests/exhaustive/issues/286/expected/model_3_3-p1-solution000006.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting p be partition({1, 2}, {3, 4}) -$ Visualisation for p -$ 1 2 -$ 3 4 - diff --git a/tests/exhaustive/issues/286/expected/model_3_3-p1-solution000007.solution b/tests/exhaustive/issues/286/expected/model_3_3-p1-solution000007.solution deleted file mode 100644 index dafa529443..0000000000 --- a/tests/exhaustive/issues/286/expected/model_3_3-p1-solution000007.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting p be partition({1, 3}, {2, 4}) -$ Visualisation for p -$ 1 3 -$ 2 4 - diff --git a/tests/exhaustive/issues/286/expected/model_3_3-p1-solution000008.solution b/tests/exhaustive/issues/286/expected/model_3_3-p1-solution000008.solution deleted file mode 100644 index 69d6c9f6be..0000000000 --- a/tests/exhaustive/issues/286/expected/model_3_3-p1-solution000008.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting p be partition({1, 4}, {2, 3}) -$ Visualisation for p -$ 1 4 -$ 2 3 - diff --git a/tests/exhaustive/issues/286/expected/model_3_3-p1.eprime-param b/tests/exhaustive/issues/286/expected/model_3_3-p1.eprime-param deleted file mode 100644 index 85954307ca..0000000000 --- a/tests/exhaustive/issues/286/expected/model_3_3-p1.eprime-param +++ /dev/null @@ -1,3 +0,0 @@ -language ESSENCE' 1.0 - -letting b be 4 diff --git a/tests/exhaustive/issues/286/expected/model_3_3.eprime b/tests/exhaustive/issues/286/expected/model_3_3.eprime deleted file mode 100644 index 9015f384d7..0000000000 --- a/tests/exhaustive/issues/286/expected/model_3_3.eprime +++ /dev/null @@ -1,75 +0,0 @@ -language ESSENCE' 1.0 - -given b: int -find p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker: int(0..b) -find p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker: - matrix indexed by [int(1..b)] of int(0..b) -find p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values: - matrix indexed by [int(1..b), int(1..b)] of int(1..b) -branching on - [p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker, - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker, - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values] -such that - sum([toInt(q20 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker) | q20 : int(1..b)]) <= - sum([1 | q21_ExplicitVarSizeWithDummy : matrix indexed by [int(1..b)] of int(1..b + 1), - and([q21_ExplicitVarSizeWithDummy[q22] < q21_ExplicitVarSizeWithDummy[q22 + 1] \/ - q21_ExplicitVarSizeWithDummy[q22] = b + 1 - | q22 : int(1..b - 1)]), - and([q21_ExplicitVarSizeWithDummy[q23] = b + 1 -> q21_ExplicitVarSizeWithDummy[q23 + 1] = b + 1 - | q23 : int(1..b - 1)])]) - / 8, - alldifferent_except([toInt(q15 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - q16 <= - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q15]) - * - catchUndef(p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q15, q16], - 0) - | q15 : int(1..b), q16 : int(1..b)], - 0), - and([q17 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q17] >= 1 - | q17 : int(1..b)]), - and([q4 + 1 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - flatten([[p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q4]; int(1)], - flatten([[p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q4, q11]; - int(1)] - | q11 : int(1..b)]); - int(1..2)]) - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q5] = 0 /\ - and([p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q5, q13] = 1 - | q13 : int(1..b)]) - | q5 : int(1..b)]), - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker <= b, - and([q6 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - and([q7 + 1 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q6] -> - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q6, q7] < - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q6, q7 + 1] - | q7 : int(1..b - 1)]) - | q6 : int(1..b)]), - and([q6 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - and([q8 > p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q6] -> - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q6, q8] = 1 - | q8 : int(1..b)]) - | q6 : int(1..b)]), - and([q6 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q6] <= b - | q6 : int(1..b)]), - b = - sum([toInt(q14 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker) * - catchUndef(p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q14], 0) - | q14 : int(1..b)]) - diff --git a/tests/exhaustive/issues/286/expected/model_3_4-p1-solution000001.solution b/tests/exhaustive/issues/286/expected/model_3_4-p1-solution000001.solution deleted file mode 100644 index 8f7fa48018..0000000000 --- a/tests/exhaustive/issues/286/expected/model_3_4-p1-solution000001.solution +++ /dev/null @@ -1,6 +0,0 @@ -language Essence 1.3 - -letting p be partition({1, 2, 3, 4}) -$ Visualisation for p -$ 1 2 3 4 - diff --git a/tests/exhaustive/issues/286/expected/model_3_4-p1-solution000002.solution b/tests/exhaustive/issues/286/expected/model_3_4-p1-solution000002.solution deleted file mode 100644 index 556f2c0ecc..0000000000 --- a/tests/exhaustive/issues/286/expected/model_3_4-p1-solution000002.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting p be partition({1, 2, 3}, {4}) -$ Visualisation for p -$ 1 2 3 -$ 4 - diff --git a/tests/exhaustive/issues/286/expected/model_3_4-p1-solution000003.solution b/tests/exhaustive/issues/286/expected/model_3_4-p1-solution000003.solution deleted file mode 100644 index 7781800dc4..0000000000 --- a/tests/exhaustive/issues/286/expected/model_3_4-p1-solution000003.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting p be partition({1, 2, 4}, {3}) -$ Visualisation for p -$ 1 2 4 -$ 3 - diff --git a/tests/exhaustive/issues/286/expected/model_3_4-p1-solution000004.solution b/tests/exhaustive/issues/286/expected/model_3_4-p1-solution000004.solution deleted file mode 100644 index 1507fcc0c1..0000000000 --- a/tests/exhaustive/issues/286/expected/model_3_4-p1-solution000004.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting p be partition({1, 2}, {3, 4}) -$ Visualisation for p -$ 1 2 -$ 3 4 - diff --git a/tests/exhaustive/issues/286/expected/model_3_4-p1-solution000005.solution b/tests/exhaustive/issues/286/expected/model_3_4-p1-solution000005.solution deleted file mode 100644 index 0368fc950b..0000000000 --- a/tests/exhaustive/issues/286/expected/model_3_4-p1-solution000005.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting p be partition({1, 3, 4}, {2}) -$ Visualisation for p -$ 1 3 4 -$ 2 - diff --git a/tests/exhaustive/issues/286/expected/model_3_4-p1-solution000006.solution b/tests/exhaustive/issues/286/expected/model_3_4-p1-solution000006.solution deleted file mode 100644 index dafa529443..0000000000 --- a/tests/exhaustive/issues/286/expected/model_3_4-p1-solution000006.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting p be partition({1, 3}, {2, 4}) -$ Visualisation for p -$ 1 3 -$ 2 4 - diff --git a/tests/exhaustive/issues/286/expected/model_3_4-p1-solution000007.solution b/tests/exhaustive/issues/286/expected/model_3_4-p1-solution000007.solution deleted file mode 100644 index 69d6c9f6be..0000000000 --- a/tests/exhaustive/issues/286/expected/model_3_4-p1-solution000007.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting p be partition({1, 4}, {2, 3}) -$ Visualisation for p -$ 1 4 -$ 2 3 - diff --git a/tests/exhaustive/issues/286/expected/model_3_4-p1-solution000008.solution b/tests/exhaustive/issues/286/expected/model_3_4-p1-solution000008.solution deleted file mode 100644 index cd8086fa4a..0000000000 --- a/tests/exhaustive/issues/286/expected/model_3_4-p1-solution000008.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting p be partition({1}, {2, 3, 4}) -$ Visualisation for p -$ 1 -$ 2 3 4 - diff --git a/tests/exhaustive/issues/286/expected/model_3_4-p1.eprime-param b/tests/exhaustive/issues/286/expected/model_3_4-p1.eprime-param deleted file mode 100644 index 85954307ca..0000000000 --- a/tests/exhaustive/issues/286/expected/model_3_4-p1.eprime-param +++ /dev/null @@ -1,3 +0,0 @@ -language ESSENCE' 1.0 - -letting b be 4 diff --git a/tests/exhaustive/issues/286/expected/model_3_4.eprime b/tests/exhaustive/issues/286/expected/model_3_4.eprime deleted file mode 100644 index da6cc36b99..0000000000 --- a/tests/exhaustive/issues/286/expected/model_3_4.eprime +++ /dev/null @@ -1,135 +0,0 @@ -language ESSENCE' 1.0 - -given b: int -find p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker: int(0..b) -find p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker: - matrix indexed by [int(1..b)] of int(0..b) -find p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values: - matrix indexed by [int(1..b), int(1..b)] of int(1..b) -find p_PartitionOccurrence_NumParts: int(1..b) -find p_PartitionOccurrence_WhichPart: matrix indexed by [int(1..b)] of int(1..b) -find p_PartitionOccurrence_PartSizes: matrix indexed by [int(1..b)] of int(0..b) -find p_PartitionOccurrence_FirstIndex: matrix indexed by [int(1..b)] of int(1..b) -branching on - [p_PartitionOccurrence_NumParts, p_PartitionOccurrence_WhichPart, p_PartitionOccurrence_PartSizes, - p_PartitionOccurrence_FirstIndex, p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker, - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker, - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values] -such that - sum([toInt(q58 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker) | q58 : int(1..b)]) <= - sum([1 | q59_ExplicitVarSizeWithDummy : matrix indexed by [int(1..b)] of int(1..b + 1), - and([q59_ExplicitVarSizeWithDummy[q60] < q59_ExplicitVarSizeWithDummy[q60 + 1] \/ - q59_ExplicitVarSizeWithDummy[q60] = b + 1 - | q60 : int(1..b - 1)]), - and([q59_ExplicitVarSizeWithDummy[q61] = b + 1 -> q59_ExplicitVarSizeWithDummy[q61 + 1] = b + 1 - | q61 : int(1..b - 1)])]) - / 8, - alldifferent_except([toInt(q52 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - q53 <= - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q52]) - * - catchUndef(p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q52, q53], - 0) - | q52 : int(1..b), q53 : int(1..b)], - 0), - and([q54 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q54] >= 1 - | q54 : int(1..b)]), - and([q4 + 1 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - flatten([[p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q4]; int(1)], - flatten([[p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q4, q21]; - int(1)] - | q21 : int(1..b)]); - int(1..2)]) - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q5] = 0 /\ - and([p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q5, q23] = 1 - | q23 : int(1..b)]) - | q5 : int(1..b)]), - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker <= b, - and([q6 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - and([q7 + 1 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q6] -> - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q6, q7] < - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q6, q7 + 1] - | q7 : int(1..b - 1)]) - | q6 : int(1..b)]), - and([q6 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - and([q8 > p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q6] -> - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q6, q8] = 1 - | q8 : int(1..b)]) - | q6 : int(1..b)]), - and([q6 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q6] <= b - | q6 : int(1..b)]), - b = - sum([toInt(q55 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker) * - catchUndef(p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q55], 0) - | q55 : int(1..b)]), - and([q11 <= p_PartitionOccurrence_NumParts -> p_PartitionOccurrence_PartSizes[q11] <= b | q11 : int(1..b)]), - and([q11 > p_PartitionOccurrence_NumParts -> p_PartitionOccurrence_PartSizes[q11] = 0 | q11 : int(1..b)]), - p_PartitionOccurrence_NumParts <= b, - and([q12 <= p_PartitionOccurrence_NumParts -> or([p_PartitionOccurrence_WhichPart[q13] = q12 | q13 : int(1..b)]) - | q12 : int(3..b)]), - p_PartitionOccurrence_NumParts = max([p_PartitionOccurrence_WhichPart[q14] | q14 : int(1..b)]), - and([p_PartitionOccurrence_PartSizes[q15] = - sum([toInt(p_PartitionOccurrence_WhichPart[q16] = q15) | q16 : int(1..b)]) - | q15 : int(1..b)]), - and([q17 <= p_PartitionOccurrence_NumParts -> - and([p_PartitionOccurrence_WhichPart[q18] = q17 -> p_PartitionOccurrence_FirstIndex[q17] <= q18 - | q18 : int(1..b)]) - | q17 : int(1..b)]), - and([q17 <= p_PartitionOccurrence_NumParts -> - or([p_PartitionOccurrence_WhichPart[q18] = q17 /\ p_PartitionOccurrence_FirstIndex[q17] = q18 - | q18 : int(1..b)]) - | q17 : int(1..b)]), - and([q17 > p_PartitionOccurrence_NumParts -> p_PartitionOccurrence_FirstIndex[q17] = 1 | q17 : int(1..b)]), - and([q19 <= p_PartitionOccurrence_NumParts /\ q20 <= p_PartitionOccurrence_NumParts -> - (q19 < q20 <-> p_PartitionOccurrence_FirstIndex[q19] < p_PartitionOccurrence_FirstIndex[q20]) - | q19 : int(1..b), q20 : int(1..b)]), - and([q25 <= p_PartitionOccurrence_NumParts -> - or([q29 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - (and([q31 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q29] -> - or([p_PartitionOccurrence_WhichPart[q33] = q25 /\ - q33 = - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q29, q31] - | q33 : int(1..b)]) - | q31 : int(1..b)]) - /\ - and([p_PartitionOccurrence_WhichPart[q35] = q25 -> - or([q37 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q29] - /\ - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q29, q37] = - q35 | q37 : int(1..b)]) - | q35 : int(1..b)])) - | q29 : int(1..b)]) - | q25 : int(1..b)]), - and([q40 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - or([q42 <= p_PartitionOccurrence_NumParts /\ - (and([p_PartitionOccurrence_WhichPart[q45] = q42 -> - or([q47 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q40] - /\ - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q40, q47] = - q45 | q47 : int(1..b)]) - | q45 : int(1..b)]) - /\ - and([q49 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q40] -> - or([p_PartitionOccurrence_WhichPart[q51] = q42 /\ - q51 = - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q40, q49] - | q51 : int(1..b)]) - | q49 : int(1..b)])) - | q42 : int(1..b)]) - | q40 : int(1..b)]) - diff --git a/tests/exhaustive/issues/286/expected/model_4_1-p1-solution000001.solution b/tests/exhaustive/issues/286/expected/model_4_1-p1-solution000001.solution deleted file mode 100644 index 8f7fa48018..0000000000 --- a/tests/exhaustive/issues/286/expected/model_4_1-p1-solution000001.solution +++ /dev/null @@ -1,6 +0,0 @@ -language Essence 1.3 - -letting p be partition({1, 2, 3, 4}) -$ Visualisation for p -$ 1 2 3 4 - diff --git a/tests/exhaustive/issues/286/expected/model_4_1-p1-solution000002.solution b/tests/exhaustive/issues/286/expected/model_4_1-p1-solution000002.solution deleted file mode 100644 index cd8086fa4a..0000000000 --- a/tests/exhaustive/issues/286/expected/model_4_1-p1-solution000002.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting p be partition({1}, {2, 3, 4}) -$ Visualisation for p -$ 1 -$ 2 3 4 - diff --git a/tests/exhaustive/issues/286/expected/model_4_1-p1-solution000003.solution b/tests/exhaustive/issues/286/expected/model_4_1-p1-solution000003.solution deleted file mode 100644 index 69d6c9f6be..0000000000 --- a/tests/exhaustive/issues/286/expected/model_4_1-p1-solution000003.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting p be partition({1, 4}, {2, 3}) -$ Visualisation for p -$ 1 4 -$ 2 3 - diff --git a/tests/exhaustive/issues/286/expected/model_4_1-p1-solution000004.solution b/tests/exhaustive/issues/286/expected/model_4_1-p1-solution000004.solution deleted file mode 100644 index dafa529443..0000000000 --- a/tests/exhaustive/issues/286/expected/model_4_1-p1-solution000004.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting p be partition({1, 3}, {2, 4}) -$ Visualisation for p -$ 1 3 -$ 2 4 - diff --git a/tests/exhaustive/issues/286/expected/model_4_1-p1-solution000005.solution b/tests/exhaustive/issues/286/expected/model_4_1-p1-solution000005.solution deleted file mode 100644 index 0368fc950b..0000000000 --- a/tests/exhaustive/issues/286/expected/model_4_1-p1-solution000005.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting p be partition({1, 3, 4}, {2}) -$ Visualisation for p -$ 1 3 4 -$ 2 - diff --git a/tests/exhaustive/issues/286/expected/model_4_1-p1-solution000006.solution b/tests/exhaustive/issues/286/expected/model_4_1-p1-solution000006.solution deleted file mode 100644 index 1507fcc0c1..0000000000 --- a/tests/exhaustive/issues/286/expected/model_4_1-p1-solution000006.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting p be partition({1, 2}, {3, 4}) -$ Visualisation for p -$ 1 2 -$ 3 4 - diff --git a/tests/exhaustive/issues/286/expected/model_4_1-p1-solution000007.solution b/tests/exhaustive/issues/286/expected/model_4_1-p1-solution000007.solution deleted file mode 100644 index 7781800dc4..0000000000 --- a/tests/exhaustive/issues/286/expected/model_4_1-p1-solution000007.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting p be partition({1, 2, 4}, {3}) -$ Visualisation for p -$ 1 2 4 -$ 3 - diff --git a/tests/exhaustive/issues/286/expected/model_4_1-p1-solution000008.solution b/tests/exhaustive/issues/286/expected/model_4_1-p1-solution000008.solution deleted file mode 100644 index 556f2c0ecc..0000000000 --- a/tests/exhaustive/issues/286/expected/model_4_1-p1-solution000008.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting p be partition({1, 2, 3}, {4}) -$ Visualisation for p -$ 1 2 3 -$ 4 - diff --git a/tests/exhaustive/issues/286/expected/model_4_1-p1.eprime-param b/tests/exhaustive/issues/286/expected/model_4_1-p1.eprime-param deleted file mode 100644 index 85954307ca..0000000000 --- a/tests/exhaustive/issues/286/expected/model_4_1-p1.eprime-param +++ /dev/null @@ -1,3 +0,0 @@ -language ESSENCE' 1.0 - -letting b be 4 diff --git a/tests/exhaustive/issues/286/expected/model_4_1.eprime b/tests/exhaustive/issues/286/expected/model_4_1.eprime deleted file mode 100644 index 361ef22b1b..0000000000 --- a/tests/exhaustive/issues/286/expected/model_4_1.eprime +++ /dev/null @@ -1,88 +0,0 @@ -language ESSENCE' 1.0 - -given b: int -find p_PartitionOccurrence_NumParts: int(1..b) -find p_PartitionOccurrence_WhichPart: matrix indexed by [int(1..b)] of int(1..b) -find p_PartitionOccurrence_PartSizes: matrix indexed by [int(1..b)] of int(0..b) -find p_PartitionOccurrence_FirstIndex: matrix indexed by [int(1..b)] of int(1..b) -find p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker: int(0..b) -find p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence: matrix indexed by [int(1..b), int(1..b)] of bool -branching on - [p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker, - p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence, p_PartitionOccurrence_NumParts, - p_PartitionOccurrence_WhichPart, p_PartitionOccurrence_PartSizes, p_PartitionOccurrence_FirstIndex] -such that - sum([toInt(q50 <= p_PartitionOccurrence_NumParts) | q50 : int(1..b)]) <= - sum([1 | q52_ExplicitVarSizeWithDummy : matrix indexed by [int(1..b)] of int(1..b + 1), - and([q52_ExplicitVarSizeWithDummy[q53] < q52_ExplicitVarSizeWithDummy[q53 + 1] \/ - q52_ExplicitVarSizeWithDummy[q53] = b + 1 - | q53 : int(1..b - 1)]), - and([q52_ExplicitVarSizeWithDummy[q54] = b + 1 -> q52_ExplicitVarSizeWithDummy[q54 + 1] = b + 1 - | q54 : int(1..b - 1)])]) - / 8, - and([q1 <= p_PartitionOccurrence_NumParts -> p_PartitionOccurrence_PartSizes[q1] <= b | q1 : int(1..b)]), - and([q1 > p_PartitionOccurrence_NumParts -> p_PartitionOccurrence_PartSizes[q1] = 0 | q1 : int(1..b)]), - p_PartitionOccurrence_NumParts <= b, - and([q2 <= p_PartitionOccurrence_NumParts -> or([p_PartitionOccurrence_WhichPart[q3] = q2 | q3 : int(1..b)]) - | q2 : int(3..b)]), - p_PartitionOccurrence_NumParts = max([p_PartitionOccurrence_WhichPart[q4] | q4 : int(1..b)]), - and([p_PartitionOccurrence_PartSizes[q5] = sum([toInt(p_PartitionOccurrence_WhichPart[q6] = q5) | q6 : int(1..b)]) - | q5 : int(1..b)]), - and([q7 <= p_PartitionOccurrence_NumParts -> - and([p_PartitionOccurrence_WhichPart[q8] = q7 -> p_PartitionOccurrence_FirstIndex[q7] <= q8 | q8 : int(1..b)]) - | q7 : int(1..b)]), - and([q7 <= p_PartitionOccurrence_NumParts -> - or([p_PartitionOccurrence_WhichPart[q8] = q7 /\ p_PartitionOccurrence_FirstIndex[q7] = q8 | q8 : int(1..b)]) - | q7 : int(1..b)]), - and([q7 > p_PartitionOccurrence_NumParts -> p_PartitionOccurrence_FirstIndex[q7] = 1 | q7 : int(1..b)]), - and([q9 <= p_PartitionOccurrence_NumParts /\ q10 <= p_PartitionOccurrence_NumParts -> - (q9 < q10 <-> p_PartitionOccurrence_FirstIndex[q9] < p_PartitionOccurrence_FirstIndex[q10]) - | q9 : int(1..b), q10 : int(1..b)]), - and([1 = - sum([toInt(q19 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ - p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q19, q11]) - | q19 : int(1..b)]) - | q11 : int(1..b)]), - and([q47 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> - sum([toInt(p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q47, q48]) | q48 : int(1..b)]) >= 1 - | q47 : int(1..b)]), - and([q14 + 1 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> - [-toInt(p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q14, q20]) | q20 : int(1..b)] p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> - and([p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q15, q22] = false | q22 : int(1..b)]) - | q15 : int(1..b)]), - p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker <= b, - and([q16 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> - sum([toInt(p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q16, q17]) | q17 : int(1..b)]) <= b - | q16 : int(1..b)]), - b = - sum([toInt(q23 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker) * - catchUndef(sum([toInt(p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q23, q24]) - | q24 : int(1..b)]), - 0) - | q23 : int(1..b)]), - and([q27 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> - or([q29 <= p_PartitionOccurrence_NumParts /\ - (and([p_PartitionOccurrence_WhichPart[q32] = q29 -> - p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q27, q32] - | q32 : int(1..b)]) - /\ - and([p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q27, q33] -> - or([p_PartitionOccurrence_WhichPart[q35] = q29 /\ q35 = q33 | q35 : int(1..b)]) - | q33 : int(1..b)])) - | q29 : int(1..b)]) - | q27 : int(1..b)]), - and([q37 <= p_PartitionOccurrence_NumParts -> - or([q41 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ - (and([p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q41, q42] -> - or([p_PartitionOccurrence_WhichPart[q44] = q37 /\ q44 = q42 | q44 : int(1..b)]) - | q42 : int(1..b)]) - /\ - and([p_PartitionOccurrence_WhichPart[q46] = q37 -> - p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q41, q46] - | q46 : int(1..b)])) - | q41 : int(1..b)]) - | q37 : int(1..b)]) - diff --git a/tests/exhaustive/issues/286/expected/model_4_2-p1-solution000001.solution b/tests/exhaustive/issues/286/expected/model_4_2-p1-solution000001.solution deleted file mode 100644 index 8f7fa48018..0000000000 --- a/tests/exhaustive/issues/286/expected/model_4_2-p1-solution000001.solution +++ /dev/null @@ -1,6 +0,0 @@ -language Essence 1.3 - -letting p be partition({1, 2, 3, 4}) -$ Visualisation for p -$ 1 2 3 4 - diff --git a/tests/exhaustive/issues/286/expected/model_4_2-p1-solution000002.solution b/tests/exhaustive/issues/286/expected/model_4_2-p1-solution000002.solution deleted file mode 100644 index 556f2c0ecc..0000000000 --- a/tests/exhaustive/issues/286/expected/model_4_2-p1-solution000002.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting p be partition({1, 2, 3}, {4}) -$ Visualisation for p -$ 1 2 3 -$ 4 - diff --git a/tests/exhaustive/issues/286/expected/model_4_2-p1-solution000003.solution b/tests/exhaustive/issues/286/expected/model_4_2-p1-solution000003.solution deleted file mode 100644 index 7781800dc4..0000000000 --- a/tests/exhaustive/issues/286/expected/model_4_2-p1-solution000003.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting p be partition({1, 2, 4}, {3}) -$ Visualisation for p -$ 1 2 4 -$ 3 - diff --git a/tests/exhaustive/issues/286/expected/model_4_2-p1-solution000004.solution b/tests/exhaustive/issues/286/expected/model_4_2-p1-solution000004.solution deleted file mode 100644 index 1507fcc0c1..0000000000 --- a/tests/exhaustive/issues/286/expected/model_4_2-p1-solution000004.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting p be partition({1, 2}, {3, 4}) -$ Visualisation for p -$ 1 2 -$ 3 4 - diff --git a/tests/exhaustive/issues/286/expected/model_4_2-p1-solution000005.solution b/tests/exhaustive/issues/286/expected/model_4_2-p1-solution000005.solution deleted file mode 100644 index 0368fc950b..0000000000 --- a/tests/exhaustive/issues/286/expected/model_4_2-p1-solution000005.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting p be partition({1, 3, 4}, {2}) -$ Visualisation for p -$ 1 3 4 -$ 2 - diff --git a/tests/exhaustive/issues/286/expected/model_4_2-p1-solution000006.solution b/tests/exhaustive/issues/286/expected/model_4_2-p1-solution000006.solution deleted file mode 100644 index dafa529443..0000000000 --- a/tests/exhaustive/issues/286/expected/model_4_2-p1-solution000006.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting p be partition({1, 3}, {2, 4}) -$ Visualisation for p -$ 1 3 -$ 2 4 - diff --git a/tests/exhaustive/issues/286/expected/model_4_2-p1-solution000007.solution b/tests/exhaustive/issues/286/expected/model_4_2-p1-solution000007.solution deleted file mode 100644 index 69d6c9f6be..0000000000 --- a/tests/exhaustive/issues/286/expected/model_4_2-p1-solution000007.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting p be partition({1, 4}, {2, 3}) -$ Visualisation for p -$ 1 4 -$ 2 3 - diff --git a/tests/exhaustive/issues/286/expected/model_4_2-p1-solution000008.solution b/tests/exhaustive/issues/286/expected/model_4_2-p1-solution000008.solution deleted file mode 100644 index cd8086fa4a..0000000000 --- a/tests/exhaustive/issues/286/expected/model_4_2-p1-solution000008.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting p be partition({1}, {2, 3, 4}) -$ Visualisation for p -$ 1 -$ 2 3 4 - diff --git a/tests/exhaustive/issues/286/expected/model_4_2-p1.eprime-param b/tests/exhaustive/issues/286/expected/model_4_2-p1.eprime-param deleted file mode 100644 index 85954307ca..0000000000 --- a/tests/exhaustive/issues/286/expected/model_4_2-p1.eprime-param +++ /dev/null @@ -1,3 +0,0 @@ -language ESSENCE' 1.0 - -letting b be 4 diff --git a/tests/exhaustive/issues/286/expected/model_4_2.eprime b/tests/exhaustive/issues/286/expected/model_4_2.eprime deleted file mode 100644 index 6786740b4a..0000000000 --- a/tests/exhaustive/issues/286/expected/model_4_2.eprime +++ /dev/null @@ -1,118 +0,0 @@ -language ESSENCE' 1.0 - -given b: int -find p_PartitionOccurrence_NumParts: int(1..b) -find p_PartitionOccurrence_WhichPart: matrix indexed by [int(1..b)] of int(1..b) -find p_PartitionOccurrence_PartSizes: matrix indexed by [int(1..b)] of int(0..b) -find p_PartitionOccurrence_FirstIndex: matrix indexed by [int(1..b)] of int(1..b) -find p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker: int(0..b) -find p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy: - matrix indexed by [int(1..b), int(1..b)] of int(1..b + 1) -branching on - [p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker, - p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy, p_PartitionOccurrence_NumParts, - p_PartitionOccurrence_WhichPart, p_PartitionOccurrence_PartSizes, p_PartitionOccurrence_FirstIndex] -such that - sum([toInt(q62 <= p_PartitionOccurrence_NumParts) | q62 : int(1..b)]) <= - sum([1 | q64_ExplicitVarSizeWithDummy : matrix indexed by [int(1..b)] of int(1..b + 1), - and([q64_ExplicitVarSizeWithDummy[q65] < q64_ExplicitVarSizeWithDummy[q65 + 1] \/ - q64_ExplicitVarSizeWithDummy[q65] = b + 1 - | q65 : int(1..b - 1)]), - and([q64_ExplicitVarSizeWithDummy[q66] = b + 1 -> q64_ExplicitVarSizeWithDummy[q66 + 1] = b + 1 - | q66 : int(1..b - 1)])]) - / 8, - and([q1 <= p_PartitionOccurrence_NumParts -> p_PartitionOccurrence_PartSizes[q1] <= b | q1 : int(1..b)]), - and([q1 > p_PartitionOccurrence_NumParts -> p_PartitionOccurrence_PartSizes[q1] = 0 | q1 : int(1..b)]), - p_PartitionOccurrence_NumParts <= b, - and([q2 <= p_PartitionOccurrence_NumParts -> or([p_PartitionOccurrence_WhichPart[q3] = q2 | q3 : int(1..b)]) - | q2 : int(3..b)]), - p_PartitionOccurrence_NumParts = max([p_PartitionOccurrence_WhichPart[q4] | q4 : int(1..b)]), - and([p_PartitionOccurrence_PartSizes[q5] = sum([toInt(p_PartitionOccurrence_WhichPart[q6] = q5) | q6 : int(1..b)]) - | q5 : int(1..b)]), - and([q7 <= p_PartitionOccurrence_NumParts -> - and([p_PartitionOccurrence_WhichPart[q8] = q7 -> p_PartitionOccurrence_FirstIndex[q7] <= q8 | q8 : int(1..b)]) - | q7 : int(1..b)]), - and([q7 <= p_PartitionOccurrence_NumParts -> - or([p_PartitionOccurrence_WhichPart[q8] = q7 /\ p_PartitionOccurrence_FirstIndex[q7] = q8 | q8 : int(1..b)]) - | q7 : int(1..b)]), - and([q7 > p_PartitionOccurrence_NumParts -> p_PartitionOccurrence_FirstIndex[q7] = 1 | q7 : int(1..b)]), - and([q9 <= p_PartitionOccurrence_NumParts /\ q10 <= p_PartitionOccurrence_NumParts -> - (q9 < q10 <-> p_PartitionOccurrence_FirstIndex[q9] < p_PartitionOccurrence_FirstIndex[q10]) - | q9 : int(1..b), q10 : int(1..b)]), - alldifferent_except([toInt(q56 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ - p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q56, q57] != - b + 1) - * - catchUndef(p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q56, q57], - 0) - | q56 : int(1..b), q57 : int(1..b)], - 0), - and([q58 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - sum([toInt(p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q58, q60] != b + 1) - | q60 : int(1..b)]) - >= 1 - | q58 : int(1..b)]), - and([q14 + 1 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - [p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q14, q22] | q22 : int(1..b)] p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - and([p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q15, q24] = 1 - | q24 : int(1..b)]) - | q15 : int(1..b)]), - p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker <= b, - and([q16 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - and([p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q16, q17] < - p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q16, q17 + 1] - \/ p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q16, q17] = b + 1 - | q17 : int(1..b - 1)]) - | q16 : int(1..b)]), - and([q16 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - and([p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q16, q18] = b + 1 -> - p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q16, q18 + 1] = b + 1 - | q18 : int(1..b - 1)]) - | q16 : int(1..b)]), - and([q16 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - sum([toInt(p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q16, q19] != b + 1) - | q19 : int(1..b)]) - <= b - | q16 : int(1..b)]), - b = - sum([toInt(q25 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker) * - catchUndef(sum([toInt(p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q25, q27] != - b + 1) - | q27 : int(1..b)]), - 0) - | q25 : int(1..b)]), - and([q30 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - or([q32 <= p_PartitionOccurrence_NumParts /\ - (and([p_PartitionOccurrence_WhichPart[q35] = q32 -> - or([p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q30, q37] != b + 1 - /\ p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q30, q37] = q35 - | q37 : int(1..b)]) - | q35 : int(1..b)]) - /\ - and([p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q30, q39] != b + 1 -> - or([p_PartitionOccurrence_WhichPart[q41] = q32 /\ - q41 = p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q30, q39] - | q41 : int(1..b)]) - | q39 : int(1..b)])) - | q32 : int(1..b)]) - | q30 : int(1..b)]), - and([q43 <= p_PartitionOccurrence_NumParts -> - or([q47 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ - (and([p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q47, q49] != b + 1 -> - or([p_PartitionOccurrence_WhichPart[q51] = q43 /\ - q51 = p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q47, q49] - | q51 : int(1..b)]) - | q49 : int(1..b)]) - /\ - and([p_PartitionOccurrence_WhichPart[q53] = q43 -> - or([p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q47, q55] != b + 1 - /\ p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q47, q55] = q53 - | q55 : int(1..b)]) - | q53 : int(1..b)])) - | q47 : int(1..b)]) - | q43 : int(1..b)]) - diff --git a/tests/exhaustive/issues/286/expected/model_4_3-p1-solution000001.solution b/tests/exhaustive/issues/286/expected/model_4_3-p1-solution000001.solution deleted file mode 100644 index 8f7fa48018..0000000000 --- a/tests/exhaustive/issues/286/expected/model_4_3-p1-solution000001.solution +++ /dev/null @@ -1,6 +0,0 @@ -language Essence 1.3 - -letting p be partition({1, 2, 3, 4}) -$ Visualisation for p -$ 1 2 3 4 - diff --git a/tests/exhaustive/issues/286/expected/model_4_3-p1-solution000002.solution b/tests/exhaustive/issues/286/expected/model_4_3-p1-solution000002.solution deleted file mode 100644 index cd8086fa4a..0000000000 --- a/tests/exhaustive/issues/286/expected/model_4_3-p1-solution000002.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting p be partition({1}, {2, 3, 4}) -$ Visualisation for p -$ 1 -$ 2 3 4 - diff --git a/tests/exhaustive/issues/286/expected/model_4_3-p1-solution000003.solution b/tests/exhaustive/issues/286/expected/model_4_3-p1-solution000003.solution deleted file mode 100644 index 0368fc950b..0000000000 --- a/tests/exhaustive/issues/286/expected/model_4_3-p1-solution000003.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting p be partition({1, 3, 4}, {2}) -$ Visualisation for p -$ 1 3 4 -$ 2 - diff --git a/tests/exhaustive/issues/286/expected/model_4_3-p1-solution000004.solution b/tests/exhaustive/issues/286/expected/model_4_3-p1-solution000004.solution deleted file mode 100644 index 7781800dc4..0000000000 --- a/tests/exhaustive/issues/286/expected/model_4_3-p1-solution000004.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting p be partition({1, 2, 4}, {3}) -$ Visualisation for p -$ 1 2 4 -$ 3 - diff --git a/tests/exhaustive/issues/286/expected/model_4_3-p1-solution000005.solution b/tests/exhaustive/issues/286/expected/model_4_3-p1-solution000005.solution deleted file mode 100644 index 556f2c0ecc..0000000000 --- a/tests/exhaustive/issues/286/expected/model_4_3-p1-solution000005.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting p be partition({1, 2, 3}, {4}) -$ Visualisation for p -$ 1 2 3 -$ 4 - diff --git a/tests/exhaustive/issues/286/expected/model_4_3-p1-solution000006.solution b/tests/exhaustive/issues/286/expected/model_4_3-p1-solution000006.solution deleted file mode 100644 index 1507fcc0c1..0000000000 --- a/tests/exhaustive/issues/286/expected/model_4_3-p1-solution000006.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting p be partition({1, 2}, {3, 4}) -$ Visualisation for p -$ 1 2 -$ 3 4 - diff --git a/tests/exhaustive/issues/286/expected/model_4_3-p1-solution000007.solution b/tests/exhaustive/issues/286/expected/model_4_3-p1-solution000007.solution deleted file mode 100644 index dafa529443..0000000000 --- a/tests/exhaustive/issues/286/expected/model_4_3-p1-solution000007.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting p be partition({1, 3}, {2, 4}) -$ Visualisation for p -$ 1 3 -$ 2 4 - diff --git a/tests/exhaustive/issues/286/expected/model_4_3-p1-solution000008.solution b/tests/exhaustive/issues/286/expected/model_4_3-p1-solution000008.solution deleted file mode 100644 index 69d6c9f6be..0000000000 --- a/tests/exhaustive/issues/286/expected/model_4_3-p1-solution000008.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting p be partition({1, 4}, {2, 3}) -$ Visualisation for p -$ 1 4 -$ 2 3 - diff --git a/tests/exhaustive/issues/286/expected/model_4_3-p1.eprime-param b/tests/exhaustive/issues/286/expected/model_4_3-p1.eprime-param deleted file mode 100644 index 85954307ca..0000000000 --- a/tests/exhaustive/issues/286/expected/model_4_3-p1.eprime-param +++ /dev/null @@ -1,3 +0,0 @@ -language ESSENCE' 1.0 - -letting b be 4 diff --git a/tests/exhaustive/issues/286/expected/model_4_3.eprime b/tests/exhaustive/issues/286/expected/model_4_3.eprime deleted file mode 100644 index 5916fd42ab..0000000000 --- a/tests/exhaustive/issues/286/expected/model_4_3.eprime +++ /dev/null @@ -1,133 +0,0 @@ -language ESSENCE' 1.0 - -given b: int -find p_PartitionOccurrence_NumParts: int(1..b) -find p_PartitionOccurrence_WhichPart: matrix indexed by [int(1..b)] of int(1..b) -find p_PartitionOccurrence_PartSizes: matrix indexed by [int(1..b)] of int(0..b) -find p_PartitionOccurrence_FirstIndex: matrix indexed by [int(1..b)] of int(1..b) -find p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker: int(0..b) -find p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker: - matrix indexed by [int(1..b)] of int(0..b) -find p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values: - matrix indexed by [int(1..b), int(1..b)] of int(1..b) -branching on - [p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker, - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker, - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values, - p_PartitionOccurrence_NumParts, p_PartitionOccurrence_WhichPart, p_PartitionOccurrence_PartSizes, - p_PartitionOccurrence_FirstIndex] -such that - sum([toInt(q57 <= p_PartitionOccurrence_NumParts) | q57 : int(1..b)]) <= - sum([1 | q59_ExplicitVarSizeWithDummy : matrix indexed by [int(1..b)] of int(1..b + 1), - and([q59_ExplicitVarSizeWithDummy[q60] < q59_ExplicitVarSizeWithDummy[q60 + 1] \/ - q59_ExplicitVarSizeWithDummy[q60] = b + 1 - | q60 : int(1..b - 1)]), - and([q59_ExplicitVarSizeWithDummy[q61] = b + 1 -> q59_ExplicitVarSizeWithDummy[q61 + 1] = b + 1 - | q61 : int(1..b - 1)])]) - / 8, - and([q1 <= p_PartitionOccurrence_NumParts -> p_PartitionOccurrence_PartSizes[q1] <= b | q1 : int(1..b)]), - and([q1 > p_PartitionOccurrence_NumParts -> p_PartitionOccurrence_PartSizes[q1] = 0 | q1 : int(1..b)]), - p_PartitionOccurrence_NumParts <= b, - and([q2 <= p_PartitionOccurrence_NumParts -> or([p_PartitionOccurrence_WhichPart[q3] = q2 | q3 : int(1..b)]) - | q2 : int(3..b)]), - p_PartitionOccurrence_NumParts = max([p_PartitionOccurrence_WhichPart[q4] | q4 : int(1..b)]), - and([p_PartitionOccurrence_PartSizes[q5] = sum([toInt(p_PartitionOccurrence_WhichPart[q6] = q5) | q6 : int(1..b)]) - | q5 : int(1..b)]), - and([q7 <= p_PartitionOccurrence_NumParts -> - and([p_PartitionOccurrence_WhichPart[q8] = q7 -> p_PartitionOccurrence_FirstIndex[q7] <= q8 | q8 : int(1..b)]) - | q7 : int(1..b)]), - and([q7 <= p_PartitionOccurrence_NumParts -> - or([p_PartitionOccurrence_WhichPart[q8] = q7 /\ p_PartitionOccurrence_FirstIndex[q7] = q8 | q8 : int(1..b)]) - | q7 : int(1..b)]), - and([q7 > p_PartitionOccurrence_NumParts -> p_PartitionOccurrence_FirstIndex[q7] = 1 | q7 : int(1..b)]), - and([q9 <= p_PartitionOccurrence_NumParts /\ q10 <= p_PartitionOccurrence_NumParts -> - (q9 < q10 <-> p_PartitionOccurrence_FirstIndex[q9] < p_PartitionOccurrence_FirstIndex[q10]) - | q9 : int(1..b), q10 : int(1..b)]), - alldifferent_except([toInt(q53 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - q54 <= - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q53]) - * - catchUndef(p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q53, q54], - 0) - | q53 : int(1..b), q54 : int(1..b)], - 0), - and([q55 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q55] >= 1 - | q55 : int(1..b)]), - and([q14 + 1 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - flatten([[p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q14]; int(1)], - flatten([[p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q14, q21]; - int(1)] - | q21 : int(1..b)]); - int(1..2)]) - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q15] = 0 /\ - and([p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q15, q23] = 1 - | q23 : int(1..b)]) - | q15 : int(1..b)]), - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker <= b, - and([q16 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - and([q17 + 1 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q16] -> - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q16, q17] < - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q16, q17 + 1] - | q17 : int(1..b - 1)]) - | q16 : int(1..b)]), - and([q16 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - and([q18 > p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q16] -> - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q16, q18] = 1 - | q18 : int(1..b)]) - | q16 : int(1..b)]), - and([q16 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q16] <= b - | q16 : int(1..b)]), - b = - sum([toInt(q24 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker) * - catchUndef(p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q24], 0) - | q24 : int(1..b)]), - and([q27 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - or([q29 <= p_PartitionOccurrence_NumParts /\ - (and([p_PartitionOccurrence_WhichPart[q32] = q29 -> - or([q34 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q27] - /\ - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q27, q34] = - q32 | q34 : int(1..b)]) - | q32 : int(1..b)]) - /\ - and([q36 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q27] -> - or([p_PartitionOccurrence_WhichPart[q38] = q29 /\ - q38 = - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q27, q36] - | q38 : int(1..b)]) - | q36 : int(1..b)])) - | q29 : int(1..b)]) - | q27 : int(1..b)]), - and([q40 <= p_PartitionOccurrence_NumParts -> - or([q44 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - (and([q46 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q44] -> - or([p_PartitionOccurrence_WhichPart[q48] = q40 /\ - q48 = - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q44, q46] - | q48 : int(1..b)]) - | q46 : int(1..b)]) - /\ - and([p_PartitionOccurrence_WhichPart[q50] = q40 -> - or([q52 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q44] - /\ - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q44, q52] = - q50 | q52 : int(1..b)]) - | q50 : int(1..b)])) - | q44 : int(1..b)]) - | q40 : int(1..b)]) - diff --git a/tests/exhaustive/issues/286/expected/model_4_4-p1-solution000001.solution b/tests/exhaustive/issues/286/expected/model_4_4-p1-solution000001.solution deleted file mode 100644 index 8f7fa48018..0000000000 --- a/tests/exhaustive/issues/286/expected/model_4_4-p1-solution000001.solution +++ /dev/null @@ -1,6 +0,0 @@ -language Essence 1.3 - -letting p be partition({1, 2, 3, 4}) -$ Visualisation for p -$ 1 2 3 4 - diff --git a/tests/exhaustive/issues/286/expected/model_4_4-p1-solution000002.solution b/tests/exhaustive/issues/286/expected/model_4_4-p1-solution000002.solution deleted file mode 100644 index 556f2c0ecc..0000000000 --- a/tests/exhaustive/issues/286/expected/model_4_4-p1-solution000002.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting p be partition({1, 2, 3}, {4}) -$ Visualisation for p -$ 1 2 3 -$ 4 - diff --git a/tests/exhaustive/issues/286/expected/model_4_4-p1-solution000003.solution b/tests/exhaustive/issues/286/expected/model_4_4-p1-solution000003.solution deleted file mode 100644 index 7781800dc4..0000000000 --- a/tests/exhaustive/issues/286/expected/model_4_4-p1-solution000003.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting p be partition({1, 2, 4}, {3}) -$ Visualisation for p -$ 1 2 4 -$ 3 - diff --git a/tests/exhaustive/issues/286/expected/model_4_4-p1-solution000004.solution b/tests/exhaustive/issues/286/expected/model_4_4-p1-solution000004.solution deleted file mode 100644 index 1507fcc0c1..0000000000 --- a/tests/exhaustive/issues/286/expected/model_4_4-p1-solution000004.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting p be partition({1, 2}, {3, 4}) -$ Visualisation for p -$ 1 2 -$ 3 4 - diff --git a/tests/exhaustive/issues/286/expected/model_4_4-p1-solution000005.solution b/tests/exhaustive/issues/286/expected/model_4_4-p1-solution000005.solution deleted file mode 100644 index 0368fc950b..0000000000 --- a/tests/exhaustive/issues/286/expected/model_4_4-p1-solution000005.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting p be partition({1, 3, 4}, {2}) -$ Visualisation for p -$ 1 3 4 -$ 2 - diff --git a/tests/exhaustive/issues/286/expected/model_4_4-p1-solution000006.solution b/tests/exhaustive/issues/286/expected/model_4_4-p1-solution000006.solution deleted file mode 100644 index dafa529443..0000000000 --- a/tests/exhaustive/issues/286/expected/model_4_4-p1-solution000006.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting p be partition({1, 3}, {2, 4}) -$ Visualisation for p -$ 1 3 -$ 2 4 - diff --git a/tests/exhaustive/issues/286/expected/model_4_4-p1-solution000007.solution b/tests/exhaustive/issues/286/expected/model_4_4-p1-solution000007.solution deleted file mode 100644 index 69d6c9f6be..0000000000 --- a/tests/exhaustive/issues/286/expected/model_4_4-p1-solution000007.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting p be partition({1, 4}, {2, 3}) -$ Visualisation for p -$ 1 4 -$ 2 3 - diff --git a/tests/exhaustive/issues/286/expected/model_4_4-p1-solution000008.solution b/tests/exhaustive/issues/286/expected/model_4_4-p1-solution000008.solution deleted file mode 100644 index cd8086fa4a..0000000000 --- a/tests/exhaustive/issues/286/expected/model_4_4-p1-solution000008.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting p be partition({1}, {2, 3, 4}) -$ Visualisation for p -$ 1 -$ 2 3 4 - diff --git a/tests/exhaustive/issues/286/expected/model_4_4-p1.eprime-param b/tests/exhaustive/issues/286/expected/model_4_4-p1.eprime-param deleted file mode 100644 index 85954307ca..0000000000 --- a/tests/exhaustive/issues/286/expected/model_4_4-p1.eprime-param +++ /dev/null @@ -1,3 +0,0 @@ -language ESSENCE' 1.0 - -letting b be 4 diff --git a/tests/exhaustive/issues/286/expected/model_4_4.eprime b/tests/exhaustive/issues/286/expected/model_4_4.eprime deleted file mode 100644 index 5a6173b451..0000000000 --- a/tests/exhaustive/issues/286/expected/model_4_4.eprime +++ /dev/null @@ -1,38 +0,0 @@ -language ESSENCE' 1.0 - -given b: int -find p_PartitionOccurrence_NumParts: int(1..b) -find p_PartitionOccurrence_WhichPart: matrix indexed by [int(1..b)] of int(1..b) -find p_PartitionOccurrence_PartSizes: matrix indexed by [int(1..b)] of int(0..b) -find p_PartitionOccurrence_FirstIndex: matrix indexed by [int(1..b)] of int(1..b) -branching on - [p_PartitionOccurrence_NumParts, p_PartitionOccurrence_WhichPart, p_PartitionOccurrence_PartSizes, - p_PartitionOccurrence_FirstIndex] -such that - sum([toInt(q12 <= p_PartitionOccurrence_NumParts) | q12 : int(1..b)]) <= - sum([1 | q14_ExplicitVarSizeWithDummy : matrix indexed by [int(1..b)] of int(1..b + 1), - and([q14_ExplicitVarSizeWithDummy[q15] < q14_ExplicitVarSizeWithDummy[q15 + 1] \/ - q14_ExplicitVarSizeWithDummy[q15] = b + 1 - | q15 : int(1..b - 1)]), - and([q14_ExplicitVarSizeWithDummy[q16] = b + 1 -> q14_ExplicitVarSizeWithDummy[q16 + 1] = b + 1 - | q16 : int(1..b - 1)])]) - / 8, - and([q1 <= p_PartitionOccurrence_NumParts -> p_PartitionOccurrence_PartSizes[q1] <= b | q1 : int(1..b)]), - and([q1 > p_PartitionOccurrence_NumParts -> p_PartitionOccurrence_PartSizes[q1] = 0 | q1 : int(1..b)]), - p_PartitionOccurrence_NumParts <= b, - and([q2 <= p_PartitionOccurrence_NumParts -> or([p_PartitionOccurrence_WhichPart[q3] = q2 | q3 : int(1..b)]) - | q2 : int(3..b)]), - p_PartitionOccurrence_NumParts = max([p_PartitionOccurrence_WhichPart[q4] | q4 : int(1..b)]), - and([p_PartitionOccurrence_PartSizes[q5] = sum([toInt(p_PartitionOccurrence_WhichPart[q6] = q5) | q6 : int(1..b)]) - | q5 : int(1..b)]), - and([q7 <= p_PartitionOccurrence_NumParts -> - and([p_PartitionOccurrence_WhichPart[q8] = q7 -> p_PartitionOccurrence_FirstIndex[q7] <= q8 | q8 : int(1..b)]) - | q7 : int(1..b)]), - and([q7 <= p_PartitionOccurrence_NumParts -> - or([p_PartitionOccurrence_WhichPart[q8] = q7 /\ p_PartitionOccurrence_FirstIndex[q7] = q8 | q8 : int(1..b)]) - | q7 : int(1..b)]), - and([q7 > p_PartitionOccurrence_NumParts -> p_PartitionOccurrence_FirstIndex[q7] = 1 | q7 : int(1..b)]), - and([q9 <= p_PartitionOccurrence_NumParts /\ q10 <= p_PartitionOccurrence_NumParts -> - (q9 < q10 <-> p_PartitionOccurrence_FirstIndex[q9] < p_PartitionOccurrence_FirstIndex[q10]) - | q9 : int(1..b), q10 : int(1..b)]) - diff --git a/tests/exhaustive/mildly_interesting/cyclic_graph/expected/model-cyc1.eprime-param b/tests/exhaustive/mildly_interesting/cyclic_graph/expected/model-cyc1.eprime-param deleted file mode 100644 index 3c6853085f..0000000000 --- a/tests/exhaustive/mildly_interesting/cyclic_graph/expected/model-cyc1.eprime-param +++ /dev/null @@ -1,6 +0,0 @@ -language ESSENCE' 1.0 - -letting n be 5 -letting g_RelationAsSet_Explicit_1 be [1, 2; int(1..2)] -letting g_RelationAsSet_Explicit_2 be [2, 1; int(1..2)] -letting fin1 be 2 diff --git a/tests/exhaustive/mildly_interesting/cyclic_graph/expected/model-cyc2.eprime-param b/tests/exhaustive/mildly_interesting/cyclic_graph/expected/model-cyc2.eprime-param deleted file mode 100644 index a9b1ce1d7f..0000000000 --- a/tests/exhaustive/mildly_interesting/cyclic_graph/expected/model-cyc2.eprime-param +++ /dev/null @@ -1,6 +0,0 @@ -language ESSENCE' 1.0 - -letting n be 5 -letting g_RelationAsSet_Explicit_1 be [1, 2, 3; int(1..3)] -letting g_RelationAsSet_Explicit_2 be [2, 3, 1; int(1..3)] -letting fin1 be 3 diff --git a/tests/exhaustive/mildly_interesting/cyclic_graph/expected/model-non-solution000001.solution b/tests/exhaustive/mildly_interesting/cyclic_graph/expected/model-non-solution000001.solution deleted file mode 100644 index 04a3a6738a..0000000000 --- a/tests/exhaustive/mildly_interesting/cyclic_graph/expected/model-non-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting b be 0 diff --git a/tests/exhaustive/mildly_interesting/cyclic_graph/expected/model-non.eprime-param b/tests/exhaustive/mildly_interesting/cyclic_graph/expected/model-non.eprime-param deleted file mode 100644 index 651096c47a..0000000000 --- a/tests/exhaustive/mildly_interesting/cyclic_graph/expected/model-non.eprime-param +++ /dev/null @@ -1,6 +0,0 @@ -language ESSENCE' 1.0 - -letting n be 5 -letting g_RelationAsSet_Explicit_1 be [1, 2; int(1..2)] -letting g_RelationAsSet_Explicit_2 be [2, 3; int(1..2)] -letting fin1 be 2 diff --git a/tests/exhaustive/mildly_interesting/cyclic_graph/expected/model.eprime b/tests/exhaustive/mildly_interesting/cyclic_graph/expected/model.eprime deleted file mode 100644 index 3f80fbf178..0000000000 --- a/tests/exhaustive/mildly_interesting/cyclic_graph/expected/model.eprime +++ /dev/null @@ -1,39 +0,0 @@ -language ESSENCE' 1.0 - -given n: int -given fin1: int -given g_RelationAsSet_Explicit_1: matrix indexed by [int(1..fin1)] of int(1..n) -given g_RelationAsSet_Explicit_2: matrix indexed by [int(1..fin1)] of int(1..n) -where - and([!(or([g_RelationAsSet_Explicit_1[q12] = g_RelationAsSet_Explicit_2[q14] /\ - g_RelationAsSet_Explicit_2[q12] = g_RelationAsSet_Explicit_1[q14] - | q12 : int(1..fin1)]) - \/ - or([or([g_RelationAsSet_Explicit_1[q8] = g_RelationAsSet_Explicit_2[q14] /\ - g_RelationAsSet_Explicit_2[q8] = path_ExplicitBounded_Values[1] - | q8 : int(1..fin1)]) - /\ 1 <= path_ExplicitBounded_Length - /\ - or([g_RelationAsSet_Explicit_1[q6] = path_ExplicitBounded_Values[path_ExplicitBounded_Length] /\ - g_RelationAsSet_Explicit_2[q6] = g_RelationAsSet_Explicit_1[q14] - | q6 : int(1..fin1)]) - /\ - and([and([or([g_RelationAsSet_Explicit_1[q10] = path_ExplicitBounded_Values[x] /\ - g_RelationAsSet_Explicit_2[q10] = path_ExplicitBounded_Values[x + 1] - | q10 : int(1..fin1)]), - x <= path_ExplicitBounded_Length, x + 1 <= path_ExplicitBounded_Length; - int(1..3)]) - | x : int(1..path_ExplicitBounded_Length - 1)]) - | path_ExplicitBounded_Length : int(0..n - 2), - path_ExplicitBounded_Values : matrix indexed by [int(1..n - 2)] of int(1..n), - and([q1 > path_ExplicitBounded_Length -> path_ExplicitBounded_Values[q1] = 1 - | q1 : int(1..n - 2)]), - 1 <= path_ExplicitBounded_Length, path_ExplicitBounded_Length <= n - 2, - and([path_ExplicitBounded_Values[q2] != path_ExplicitBounded_Values[q3] - | q2 : int(1..n - 2), q3 : int(1..n - 2), q2 < q3, q2 <= path_ExplicitBounded_Length, - q3 <= path_ExplicitBounded_Length])])) - | q14 : int(1..fin1)]) -find b: int(0) -branching on [b] -such that true - diff --git a/tests/exhaustive/mildly_interesting/gchq_2016/expected/model-inst-solution000001.solution b/tests/exhaustive/mildly_interesting/gchq_2016/expected/model-inst-solution000001.solution deleted file mode 100644 index 4ad15df1dd..0000000000 --- a/tests/exhaustive/mildly_interesting/gchq_2016/expected/model-inst-solution000001.solution +++ /dev/null @@ -1,182 +0,0 @@ -language Essence 1.3 - -letting bitmap be - [[true, true, true, true, true, true, true, false, true, true, true, false, false, false, true, false, true, - false, true, true, true, true, true, true, true; - int(1..25)], - [true, false, false, false, false, false, true, false, true, true, false, true, true, false, false, false, - false, false, true, false, false, false, false, false, true; - int(1..25)], - [true, false, true, true, true, false, true, false, false, false, false, false, true, true, true, false, true, - false, true, false, true, true, true, false, true; - int(1..25)], - [true, false, true, true, true, false, true, false, true, false, false, true, true, true, true, true, true, - false, true, false, true, true, true, false, true; - int(1..25)], - [true, false, true, true, true, false, true, false, false, true, true, true, true, true, false, true, true, - false, true, false, true, true, true, false, true; - int(1..25)], - [true, false, false, false, false, false, true, false, false, true, true, false, false, false, false, false, - false, false, true, false, false, false, false, false, true; - int(1..25)], - [true, true, true, true, true, true, true, false, true, false, true, false, true, false, true, false, true, - false, true, true, true, true, true, true, true; - int(1..25)], - [false, false, false, false, false, false, false, false, true, true, true, false, false, false, true, true, - true, false, false, false, false, false, false, false, false; - int(1..25)], - [true, false, true, true, false, true, true, true, false, false, true, false, true, false, true, true, true, - false, true, false, false, true, false, true, true; - int(1..25)], - [true, false, true, false, false, false, false, false, false, true, true, true, false, true, true, false, - false, false, false, true, false, false, false, true, false; - int(1..25)], - [false, true, true, true, true, false, true, false, true, true, true, true, false, true, true, false, true, - false, false, false, false, true, true, false, false; - int(1..25)], - [false, true, false, true, false, false, false, true, false, false, false, true, false, true, false, true, - true, true, true, false, true, false, true, true, true; - int(1..25)], - [false, false, true, true, false, false, true, false, true, false, true, false, false, false, false, false, - false, true, true, false, true, true, true, true, true; - int(1..25)], - [false, false, false, true, true, true, false, true, true, false, true, true, false, true, true, true, true, - true, true, false, true, true, true, false, true; - int(1..25)], - [true, false, true, true, true, true, true, true, true, true, true, false, true, false, true, false, false, - true, true, false, false, false, false, true, false; - int(1..25)], - [false, true, true, false, true, false, false, true, true, false, false, false, true, true, false, true, true, - true, false, false, false, false, false, true, false; - int(1..25)], - [true, true, true, false, true, false, true, false, true, false, false, true, false, false, false, false, true, - true, true, true, true, false, true, false, false; - int(1..25)], - [false, false, false, false, false, false, false, false, true, false, false, false, true, true, false, true, - true, false, false, false, true, true, true, true, true; - int(1..25)], - [true, true, true, true, true, true, true, false, true, false, false, true, true, false, false, false, true, - false, true, false, true, false, true, true, true; - int(1..25)], - [true, false, false, false, false, false, true, false, true, true, false, false, true, false, false, true, - true, false, false, false, true, true, false, true, false; - int(1..25)], - [true, false, true, true, true, false, true, false, false, false, true, true, true, true, false, false, true, - true, true, true, true, false, false, true, false; - int(1..25)], - [true, false, true, true, true, false, true, false, true, true, true, false, true, true, true, true, true, - true, true, true, true, true, false, true, true; - int(1..25)], - [true, false, true, true, true, false, true, false, true, false, false, true, true, true, true, true, true, - false, true, true, true, true, true, true, false; - int(1..25)], - [true, false, false, false, false, false, true, false, false, true, true, false, false, false, false, false, - false, true, false, true, false, true, true, false, false; - int(1..25)], - [true, true, true, true, true, true, true, false, true, true, false, false, false, true, false, true, true, - false, false, false, true, true, true, true, true; - int(1..25)]; - int(1..25)] -$ Visualisation for bitmap -$ T T T T T T T _ T T T _ _ _ T _ T _ T T T T T T T -$ T _ _ _ _ _ T _ T T _ T T _ _ _ _ _ T _ _ _ _ _ T -$ T _ T T T _ T _ _ _ _ _ T T T _ T _ T _ T T T _ T -$ T _ T T T _ T _ T _ _ T T T T T T _ T _ T T T _ T -$ T _ T T T _ T _ _ T T T T T _ T T _ T _ T T T _ T -$ T _ _ _ _ _ T _ _ T T _ _ _ _ _ _ _ T _ _ _ _ _ T -$ T T T T T T T _ T _ T _ T _ T _ T _ T T T T T T T -$ _ _ _ _ _ _ _ _ T T T _ _ _ T T T _ _ _ _ _ _ _ _ -$ T _ T T _ T T T _ _ T _ T _ T T T _ T _ _ T _ T T -$ T _ T _ _ _ _ _ _ T T T _ T T _ _ _ _ T _ _ _ T _ -$ _ T T T T _ T _ T T T T _ T T _ T _ _ _ _ T T _ _ -$ _ T _ T _ _ _ T _ _ _ T _ T _ T T T T _ T _ T T T -$ _ _ T T _ _ T _ T _ T _ _ _ _ _ _ T T _ T T T T T -$ _ _ _ T T T _ T T _ T T _ T T T T T T _ T T T _ T -$ T _ T T T T T T T T T _ T _ T _ _ T T _ _ _ _ T _ -$ _ T T _ T _ _ T T _ _ _ T T _ T T T _ _ _ _ _ T _ -$ T T T _ T _ T _ T _ _ T _ _ _ _ T T T T T _ T _ _ -$ _ _ _ _ _ _ _ _ T _ _ _ T T _ T T _ _ _ T T T T T -$ T T T T T T T _ T _ _ T T _ _ _ T _ T _ T _ T T T -$ T _ _ _ _ _ T _ T T _ _ T _ _ T T _ _ _ T T _ T _ -$ T _ T T T _ T _ _ _ T T T T _ _ T T T T T _ _ T _ -$ T _ T T T _ T _ T T T _ T T T T T T T T T T _ T T -$ T _ T T T _ T _ T _ _ T T T T T T _ T T T T T T _ -$ T _ _ _ _ _ T _ _ T T _ _ _ _ _ _ T _ T _ T T _ _ -$ T T T T T T T _ T T _ _ _ T _ T T _ _ _ T T T T T - -letting horizontalLocs be - [sequence(1, 9, 15, 17, 19), sequence(1, 7, 9, 12, 19, 25), sequence(1, 3, 7, 13, 17, 19, 21, 25), - sequence(1, 3, 7, 9, 12, 19, 21, 25), sequence(1, 3, 7, 10, 16, 19, 21, 25), sequence(1, 7, 10, 19, 25), - sequence(1, 9, 11, 13, 15, 17, 19), sequence(9, 15), sequence(1, 3, 6, 11, 13, 15, 19, 22, 24), - sequence(1, 3, 10, 14, 20, 24), sequence(2, 7, 9, 14, 17, 22), sequence(2, 4, 8, 12, 14, 16, 21, 23), - sequence(3, 7, 9, 11, 18, 21), sequence(4, 8, 11, 14, 21, 25), sequence(1, 3, 13, 15, 18, 24), - sequence(2, 5, 8, 13, 16, 24), sequence(1, 5, 7, 9, 12, 17, 23), sequence(9, 13, 16, 21), - sequence(1, 9, 12, 17, 19, 21, 23), sequence(1, 7, 9, 13, 16, 21, 24), sequence(1, 3, 7, 11, 17, 24), - sequence(1, 3, 7, 9, 13, 24), sequence(1, 3, 7, 9, 12, 19), sequence(1, 7, 10, 18, 20, 22), - sequence(1, 9, 14, 16, 21); - int(1..25)] -$ Visualisation for horizontalLocs -$ 1 9 15 17 19 -$ 1 7 9 12 19 25 -$ 1 3 7 13 17 19 21 25 -$ 1 3 7 9 12 19 21 25 -$ 1 3 7 10 16 19 21 25 -$ 1 7 10 19 25 -$ 1 9 11 13 15 17 19 -$ 9 15 -$ 1 3 6 11 13 15 19 22 24 -$ 1 3 10 14 20 24 -$ 2 7 9 14 17 22 -$ 2 4 8 12 14 16 21 23 -$ 3 7 9 11 18 21 -$ 4 8 11 14 21 25 -$ 1 3 13 15 18 24 -$ 2 5 8 13 16 24 -$ 1 5 7 9 12 17 23 -$ 9 13 16 21 -$ 1 9 12 17 19 21 23 -$ 1 7 9 13 16 21 24 -$ 1 3 7 11 17 24 -$ 1 3 7 9 13 24 -$ 1 3 7 9 12 19 -$ 1 7 10 18 20 22 -$ 1 9 14 16 21 - -letting verticalLocs be - [sequence(1, 9, 15, 17, 19), sequence(1, 7, 11, 16, 19, 25), sequence(1, 3, 7, 9, 13, 15, 19, 21, 25), - sequence(1, 3, 7, 9, 11, 19, 21, 25), sequence(1, 3, 7, 11, 14, 19, 21, 25), sequence(1, 7, 9, 14, 19, 25), - sequence(1, 9, 11, 13, 15, 17, 19), sequence(9, 12, 14), sequence(1, 4, 7, 11, 13, 22, 25), - sequence(1, 5, 8, 10, 15, 20, 22, 24), sequence(1, 5, 13, 21, 24), sequence(2, 4, 10, 14, 17, 19, 21, 23), - sequence(2, 7, 9, 15, 18), sequence(3, 10, 14, 16, 18, 21, 25), sequence(1, 3, 7, 14, 22), - sequence(4, 8, 12, 14, 16, 18, 20, 22, 25), sequence(1, 3, 7, 11, 14, 16, 25), sequence(12, 21, 24), - sequence(1, 9, 12, 17, 19, 21), sequence(1, 7, 10, 17, 21), sequence(1, 3, 7, 12, 17, 25), - sequence(1, 3, 7, 9, 11, 13, 18, 20, 22), sequence(1, 3, 7, 11, 17, 23), sequence(1, 7, 9, 12, 15, 18, 25), - sequence(1, 9, 12, 18, 22, 25); - int(1..25)] -$ Visualisation for verticalLocs -$ 1 9 15 17 19 -$ 1 7 11 16 19 25 -$ 1 3 7 9 13 15 19 21 25 -$ 1 3 7 9 11 19 21 25 -$ 1 3 7 11 14 19 21 25 -$ 1 7 9 14 19 25 -$ 1 9 11 13 15 17 19 -$ 9 12 14 -$ 1 4 7 11 13 22 25 -$ 1 5 8 10 15 20 22 24 -$ 1 5 13 21 24 -$ 2 4 10 14 17 19 21 23 -$ 2 7 9 15 18 -$ 3 10 14 16 18 21 25 -$ 1 3 7 14 22 -$ 4 8 12 14 16 18 20 22 25 -$ 1 3 7 11 14 16 25 -$ 12 21 24 -$ 1 9 12 17 19 21 -$ 1 7 10 17 21 -$ 1 3 7 12 17 25 -$ 1 3 7 9 11 13 18 20 22 -$ 1 3 7 11 17 23 -$ 1 7 9 12 15 18 25 -$ 1 9 12 18 22 25 - diff --git a/tests/exhaustive/mildly_interesting/gchq_2016/expected/model-inst.eprime-param b/tests/exhaustive/mildly_interesting/gchq_2016/expected/model-inst.eprime-param deleted file mode 100644 index 9712bd75a8..0000000000 --- a/tests/exhaustive/mildly_interesting/gchq_2016/expected/model-inst.eprime-param +++ /dev/null @@ -1,98 +0,0 @@ -language ESSENCE' 1.0 - -letting n be 25 -letting horizontalClues_ExplicitBounded_Length be - [5, 6, 8, 8, 8, 5, 7, 2, 9, 6, 6, 8, 6, 6, 6, 6, 7, 4, 7, 7, 6, 6, 6, 6, 5; int(1..25)] -letting horizontalClues_ExplicitBounded_Values be - [[7, 3, 1, 1, 7, 1, 1, 1, 1; int(1..9)], [1, 1, 2, 2, 1, 1, 1, 1, 1; int(1..9)], - [1, 3, 1, 3, 1, 1, 3, 1, 1; int(1..9)], [1, 3, 1, 1, 6, 1, 3, 1, 1; int(1..9)], - [1, 3, 1, 5, 2, 1, 3, 1, 1; int(1..9)], [1, 1, 2, 1, 1, 1, 1, 1, 1; int(1..9)], - [7, 1, 1, 1, 1, 1, 7, 1, 1; int(1..9)], [3, 3, 1, 1, 1, 1, 1, 1, 1; int(1..9)], - [1, 2, 3, 1, 1, 3, 1, 1, 2; int(1..9)], [1, 1, 3, 2, 1, 1, 1, 1, 1; int(1..9)], - [4, 1, 4, 2, 1, 2, 1, 1, 1; int(1..9)], [1, 1, 1, 1, 1, 4, 1, 3, 1; int(1..9)], - [2, 1, 1, 1, 2, 5, 1, 1, 1; int(1..9)], [3, 2, 2, 6, 3, 1, 1, 1, 1; int(1..9)], - [1, 9, 1, 1, 2, 1, 1, 1, 1; int(1..9)], [2, 1, 2, 2, 3, 1, 1, 1, 1; int(1..9)], - [3, 1, 1, 1, 1, 5, 1, 1, 1; int(1..9)], [1, 2, 2, 5, 1, 1, 1, 1, 1; int(1..9)], - [7, 1, 2, 1, 1, 1, 3, 1, 1; int(1..9)], [1, 1, 2, 1, 2, 2, 1, 1, 1; int(1..9)], - [1, 3, 1, 4, 5, 1, 1, 1, 1; int(1..9)], [1, 3, 1, 3, 10, 2, 1, 1, 1; int(1..9)], - [1, 3, 1, 1, 6, 6, 1, 1, 1; int(1..9)], [1, 1, 2, 1, 1, 2, 1, 1, 1; int(1..9)], - [7, 2, 1, 2, 5, 1, 1, 1, 1; int(1..9)]; - int(1..25)] -$ Visualisation for horizontalClues_ExplicitBounded_Values -$ 7 3 1 1 7 1 1 1 1 -$ 1 1 2 2 1 1 1 1 1 -$ 1 3 1 3 1 1 3 1 1 -$ 1 3 1 1 6 1 3 1 1 -$ 1 3 1 5 2 1 3 1 1 -$ 1 1 2 1 1 1 1 1 1 -$ 7 1 1 1 1 1 7 1 1 -$ 3 3 1 1 1 1 1 1 1 -$ 1 2 3 1 1 3 1 1 2 -$ 1 1 3 2 1 1 1 1 1 -$ 4 1 4 2 1 2 1 1 1 -$ 1 1 1 1 1 4 1 3 1 -$ 2 1 1 1 2 5 1 1 1 -$ 3 2 2 6 3 1 1 1 1 -$ 1 9 1 1 2 1 1 1 1 -$ 2 1 2 2 3 1 1 1 1 -$ 3 1 1 1 1 5 1 1 1 -$ 1 2 2 5 1 1 1 1 1 -$ 7 1 2 1 1 1 3 1 1 -$ 1 1 2 1 2 2 1 1 1 -$ 1 3 1 4 5 1 1 1 1 -$ 1 3 1 3 10 2 1 1 1 -$ 1 3 1 1 6 6 1 1 1 -$ 1 1 2 1 1 2 1 1 1 -$ 7 2 1 2 5 1 1 1 1 - -letting verticalClues_ExplicitBounded_Length be - [5, 6, 9, 8, 8, 6, 7, 3, 7, 8, 5, 8, 5, 7, 5, 9, 7, 3, 6, 5, 6, 9, 6, 7, 6; int(1..25)] -letting verticalClues_ExplicitBounded_Values be - [[7, 2, 1, 1, 7, 1, 1, 1, 1; int(1..9)], [1, 1, 2, 2, 1, 1, 1, 1, 1; int(1..9)], - [1, 3, 1, 3, 1, 3, 1, 3, 1; int(1..9)], [1, 3, 1, 1, 5, 1, 3, 1, 1; int(1..9)], - [1, 3, 1, 1, 4, 1, 3, 1, 1; int(1..9)], [1, 1, 1, 2, 1, 1, 1, 1, 1; int(1..9)], - [7, 1, 1, 1, 1, 1, 7, 1, 1; int(1..9)], [1, 1, 3, 1, 1, 1, 1, 1, 1; int(1..9)], - [2, 1, 2, 1, 8, 2, 1, 1, 1; int(1..9)], [2, 2, 1, 2, 1, 1, 1, 2, 1; int(1..9)], - [1, 7, 3, 2, 1, 1, 1, 1, 1; int(1..9)], [1, 2, 3, 1, 1, 1, 1, 1, 1; int(1..9)], - [4, 1, 1, 2, 6, 1, 1, 1, 1; int(1..9)], [3, 3, 1, 1, 1, 3, 1, 1, 1; int(1..9)], - [1, 2, 5, 2, 2, 1, 1, 1, 1; int(1..9)], [2, 2, 1, 1, 1, 1, 1, 2, 1; int(1..9)], - [1, 3, 3, 2, 1, 8, 1, 1, 1; int(1..9)], [6, 2, 1, 1, 1, 1, 1, 1, 1; int(1..9)], - [7, 1, 4, 1, 1, 3, 1, 1, 1; int(1..9)], [1, 1, 1, 1, 4, 1, 1, 1, 1; int(1..9)], - [1, 3, 1, 3, 7, 1, 1, 1, 1; int(1..9)], [1, 3, 1, 1, 1, 2, 1, 1, 4; int(1..9)], - [1, 3, 1, 4, 3, 3, 1, 1, 1; int(1..9)], [1, 1, 2, 2, 2, 6, 1, 1, 1; int(1..9)], - [7, 1, 3, 2, 1, 1, 1, 1, 1; int(1..9)]; - int(1..25)] -$ Visualisation for verticalClues_ExplicitBounded_Values -$ 7 2 1 1 7 1 1 1 1 -$ 1 1 2 2 1 1 1 1 1 -$ 1 3 1 3 1 3 1 3 1 -$ 1 3 1 1 5 1 3 1 1 -$ 1 3 1 1 4 1 3 1 1 -$ 1 1 1 2 1 1 1 1 1 -$ 7 1 1 1 1 1 7 1 1 -$ 1 1 3 1 1 1 1 1 1 -$ 2 1 2 1 8 2 1 1 1 -$ 2 2 1 2 1 1 1 2 1 -$ 1 7 3 2 1 1 1 1 1 -$ 1 2 3 1 1 1 1 1 1 -$ 4 1 1 2 6 1 1 1 1 -$ 3 3 1 1 1 3 1 1 1 -$ 1 2 5 2 2 1 1 1 1 -$ 2 2 1 1 1 1 1 2 1 -$ 1 3 3 2 1 8 1 1 1 -$ 6 2 1 1 1 1 1 1 1 -$ 7 1 4 1 1 3 1 1 1 -$ 1 1 1 1 4 1 1 1 1 -$ 1 3 1 3 7 1 1 1 1 -$ 1 3 1 1 1 2 1 1 4 -$ 1 3 1 4 3 3 1 1 1 -$ 1 1 2 2 2 6 1 1 1 -$ 7 1 3 2 1 1 1 1 1 - -letting prefilled_Explicit_1 be - [4, 4, 4, 4, 4, 9, 9, 9, 9, 9, 9, 17, 17, 17, 17, 22, 22, 22, 22, 22, 22, 22; int(1..22)] -letting prefilled_Explicit_2 be - [4, 5, 13, 14, 22, 7, 8, 11, 15, 16, 19, 7, 12, 17, 21, 4, 5, 10, 11, 16, 21, 22; int(1..22)] -letting fin1 be 9 -letting fin2 be 9 -letting fin3 be 22 diff --git a/tests/exhaustive/mildly_interesting/gchq_2016/expected/model.eprime b/tests/exhaustive/mildly_interesting/gchq_2016/expected/model.eprime deleted file mode 100644 index d06f46d615..0000000000 --- a/tests/exhaustive/mildly_interesting/gchq_2016/expected/model.eprime +++ /dev/null @@ -1,127 +0,0 @@ -language ESSENCE' 1.0 - -given n: int -given fin1: int -given horizontalClues_ExplicitBounded_Length: matrix indexed by [int(1..n)] of int(0..fin1) -given horizontalClues_ExplicitBounded_Values: matrix indexed by [int(1..n), int(1..fin1)] of int(1..n) -find horizontalLocs_ExplicitBounded_Length: matrix indexed by [int(1..n)] of int(0..n) -find horizontalLocs_ExplicitBounded_Values: matrix indexed by [int(1..n), int(1..n)] of int(1..n) -given fin2: int -given verticalClues_ExplicitBounded_Length: matrix indexed by [int(1..n)] of int(0..fin2) -given verticalClues_ExplicitBounded_Values: matrix indexed by [int(1..n), int(1..fin2)] of int(1..n) -find verticalLocs_ExplicitBounded_Length: matrix indexed by [int(1..n)] of int(0..n) -find verticalLocs_ExplicitBounded_Values: matrix indexed by [int(1..n), int(1..n)] of int(1..n) -find bitmap: matrix indexed by [int(1..n), int(1..n)] of bool -given fin3: int -given prefilled_Explicit_1: matrix indexed by [int(1..fin3)] of int(1..n) -given prefilled_Explicit_2: matrix indexed by [int(1..fin3)] of int(1..n) -branching on - [horizontalLocs_ExplicitBounded_Length, horizontalLocs_ExplicitBounded_Values, verticalLocs_ExplicitBounded_Length, - verticalLocs_ExplicitBounded_Values, bitmap] -such that - and([horizontalLocs_ExplicitBounded_Length[row] = horizontalClues_ExplicitBounded_Length[row] | row : int(1..n)]), - and([and([and([horizontalLocs_ExplicitBounded_Values[row, q10] > - horizontalLocs_ExplicitBounded_Values[row, q10 - 1] + - horizontalClues_ExplicitBounded_Values[row, q10 - 1], - q10 <= horizontalLocs_ExplicitBounded_Length[row], - q10 - 1 <= horizontalLocs_ExplicitBounded_Length[row], - q10 - 1 <= horizontalClues_ExplicitBounded_Length[row]; - int(1..4)]) - | q10 : int(1..fin1), q10 <= horizontalClues_ExplicitBounded_Length[row], q10 > 1]) - | row : int(1..n)]), - and([verticalLocs_ExplicitBounded_Length[col] = verticalClues_ExplicitBounded_Length[col] | col : int(1..n)]), - and([and([and([verticalLocs_ExplicitBounded_Values[col, q12] > - verticalLocs_ExplicitBounded_Values[col, q12 - 1] + - verticalClues_ExplicitBounded_Values[col, q12 - 1], - q12 <= verticalLocs_ExplicitBounded_Length[col], q12 - 1 <= verticalLocs_ExplicitBounded_Length[col], - q12 - 1 <= verticalClues_ExplicitBounded_Length[col]; - int(1..4)]) - | q12 : int(1..fin2), q12 <= verticalClues_ExplicitBounded_Length[col], q12 > 1]) - | col : int(1..n)]), - and([bitmap[prefilled_Explicit_1[q14], prefilled_Explicit_2[q14]] | q14 : int(1..fin3)]), - and([and([i >= horizontalLocs_ExplicitBounded_Values[row, index] /\ - index <= horizontalLocs_ExplicitBounded_Length[row] - /\ - and([i <= - horizontalLocs_ExplicitBounded_Values[row, index] + - horizontalClues_ExplicitBounded_Values[row, index] - - 1, - index <= horizontalLocs_ExplicitBounded_Length[row], - index <= horizontalClues_ExplicitBounded_Length[row]; - int(1..3)]) - -> bitmap[row, i] - | i : int(1..n)]) - /\ - and([i < horizontalLocs_ExplicitBounded_Values[row, index] /\ - index <= horizontalLocs_ExplicitBounded_Length[row] - -> bitmap[row, i] = false - | i : int(1..n), index = 1]) - /\ - and([and([i > - horizontalLocs_ExplicitBounded_Values[row, index] + - horizontalClues_ExplicitBounded_Values[row, index] - - 1, - index <= horizontalLocs_ExplicitBounded_Length[row], - index <= horizontalClues_ExplicitBounded_Length[row]; - int(1..3)]) - -> bitmap[row, i] = false - | i : int(1..n), index = horizontalClues_ExplicitBounded_Length[row]]) - /\ - and([and([i > - horizontalLocs_ExplicitBounded_Values[row, index] + - horizontalClues_ExplicitBounded_Values[row, index] - - 1, - index <= horizontalLocs_ExplicitBounded_Length[row], - index <= horizontalClues_ExplicitBounded_Length[row]; - int(1..3)]) - /\ - (i < horizontalLocs_ExplicitBounded_Values[row, index + 1] /\ - index + 1 <= horizontalLocs_ExplicitBounded_Length[row]) - -> bitmap[row, i] = false - | i : int(1..n), index < horizontalClues_ExplicitBounded_Length[row]]) - | row : int(1..n), index : int(1..n), index <= horizontalClues_ExplicitBounded_Length[row]]), - and([and([i >= verticalLocs_ExplicitBounded_Values[col, index] /\ index <= verticalLocs_ExplicitBounded_Length[col] - /\ - and([i <= - verticalLocs_ExplicitBounded_Values[col, index] + verticalClues_ExplicitBounded_Values[col, index] - - 1, - index <= verticalLocs_ExplicitBounded_Length[col], - index <= verticalClues_ExplicitBounded_Length[col]; - int(1..3)]) - -> bitmap[i, col] - | i : int(1..n)]) - /\ - and([i < verticalLocs_ExplicitBounded_Values[col, index] /\ index <= verticalLocs_ExplicitBounded_Length[col] - -> bitmap[i, col] = false - | i : int(1..n), index = 1]) - /\ - and([and([i > - verticalLocs_ExplicitBounded_Values[col, index] + verticalClues_ExplicitBounded_Values[col, index] - - 1, - index <= verticalLocs_ExplicitBounded_Length[col], - index <= verticalClues_ExplicitBounded_Length[col]; - int(1..3)]) - -> bitmap[i, col] = false - | i : int(1..n), index = verticalClues_ExplicitBounded_Length[col]]) - /\ - and([and([i > - verticalLocs_ExplicitBounded_Values[col, index] + verticalClues_ExplicitBounded_Values[col, index] - - 1, - index <= verticalLocs_ExplicitBounded_Length[col], - index <= verticalClues_ExplicitBounded_Length[col]; - int(1..3)]) - /\ - (i < verticalLocs_ExplicitBounded_Values[col, index + 1] /\ - index + 1 <= verticalLocs_ExplicitBounded_Length[col]) - -> bitmap[i, col] = false - | i : int(1..n), index < verticalClues_ExplicitBounded_Length[col]]) - | col : int(1..n), index : int(1..n), index <= verticalClues_ExplicitBounded_Length[col]]), - and([and([q4 > horizontalLocs_ExplicitBounded_Length[q3] -> horizontalLocs_ExplicitBounded_Values[q3, q4] = 1 - | q4 : int(1..n)]) - | q3 : int(1..n)]), - and([horizontalLocs_ExplicitBounded_Length[q3] <= n | q3 : int(1..n)]), - and([and([q7 > verticalLocs_ExplicitBounded_Length[q6] -> verticalLocs_ExplicitBounded_Values[q6, q7] = 1 - | q7 : int(1..n)]) - | q6 : int(1..n)]), - and([verticalLocs_ExplicitBounded_Length[q6] <= n | q6 : int(1..n)]) - diff --git a/tests/exhaustive/mildly_interesting/subsetSum/expected/model_1_1_1-p1-solution000001.solution b/tests/exhaustive/mildly_interesting/subsetSum/expected/model_1_1_1-p1-solution000001.solution deleted file mode 100644 index 273ab9e077..0000000000 --- a/tests/exhaustive/mildly_interesting/subsetSum/expected/model_1_1_1-p1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {-3, -2, 5} diff --git a/tests/exhaustive/mildly_interesting/subsetSum/expected/model_1_1_1-p1.eprime-param b/tests/exhaustive/mildly_interesting/subsetSum/expected/model_1_1_1-p1.eprime-param deleted file mode 100644 index b1ce145328..0000000000 --- a/tests/exhaustive/mildly_interesting/subsetSum/expected/model_1_1_1-p1.eprime-param +++ /dev/null @@ -1,7 +0,0 @@ -language ESSENCE' 1.0 - -letting nums_Explicit be [-7, -3, -2, 5, 8; int(1..5)] -letting s be 0 -letting fin1 be 5 -letting fin2 be -7 -letting fin3 be 8 diff --git a/tests/exhaustive/mildly_interesting/subsetSum/expected/model_1_1_1-p2-solution000001.solution b/tests/exhaustive/mildly_interesting/subsetSum/expected/model_1_1_1-p2-solution000001.solution deleted file mode 100644 index 102034e8e6..0000000000 --- a/tests/exhaustive/mildly_interesting/subsetSum/expected/model_1_1_1-p2-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {-5, 1, 4} diff --git a/tests/exhaustive/mildly_interesting/subsetSum/expected/model_1_1_1-p2-solution000002.solution b/tests/exhaustive/mildly_interesting/subsetSum/expected/model_1_1_1-p2-solution000002.solution deleted file mode 100644 index 3192b721eb..0000000000 --- a/tests/exhaustive/mildly_interesting/subsetSum/expected/model_1_1_1-p2-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {-5, 2, 3} diff --git a/tests/exhaustive/mildly_interesting/subsetSum/expected/model_1_1_1-p2.eprime-param b/tests/exhaustive/mildly_interesting/subsetSum/expected/model_1_1_1-p2.eprime-param deleted file mode 100644 index 2d232d7d8a..0000000000 --- a/tests/exhaustive/mildly_interesting/subsetSum/expected/model_1_1_1-p2.eprime-param +++ /dev/null @@ -1,7 +0,0 @@ -language ESSENCE' 1.0 - -letting nums_Explicit be [-5, 1, 2, 3, 4; int(1..5)] -letting s be 0 -letting fin1 be 5 -letting fin2 be -5 -letting fin3 be 4 diff --git a/tests/exhaustive/mildly_interesting/subsetSum/expected/model_1_1_1.eprime b/tests/exhaustive/mildly_interesting/subsetSum/expected/model_1_1_1.eprime deleted file mode 100644 index 0193b6f90b..0000000000 --- a/tests/exhaustive/mildly_interesting/subsetSum/expected/model_1_1_1.eprime +++ /dev/null @@ -1,27 +0,0 @@ -language ESSENCE' 1.0 - -given s: int -given fin1: int -given fin2: int -given fin3: int -given nums_Explicit: matrix indexed by [int(1..fin1)] of int(fin2..fin3) -letting let1 be fin1 -letting let2 be [nums_Explicit[q5] | q5 : int(1..fin1)] -find x_ExplicitVarSizeWithMarker_Marker: int(0..let1) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..let1)] of int(let2) -branching on [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] -such that - and([q8 <= x_ExplicitVarSizeWithMarker_Marker -> - or([nums_Explicit[q10] = x_ExplicitVarSizeWithMarker_Values[q8] | q10 : int(1..fin1)]) - | q8 : int(1..let1)]), - s = - sum([toInt(q6 <= x_ExplicitVarSizeWithMarker_Marker) * catchUndef(x_ExplicitVarSizeWithMarker_Values[q6], 0) - | q6 : int(1..let1)]), - and([q2 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q2] < x_ExplicitVarSizeWithMarker_Values[q2 + 1] - | q2 : int(1..let1 - 1)]), - and([q3 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q3] = min(let2) - | q3 : int(1..let1)]), - 1 <= x_ExplicitVarSizeWithMarker_Marker, - x_ExplicitVarSizeWithMarker_Marker <= let1 - diff --git a/tests/exhaustive/mildly_interesting/subsetSum/expected/model_1_1_2-p1-solution000001.solution b/tests/exhaustive/mildly_interesting/subsetSum/expected/model_1_1_2-p1-solution000001.solution deleted file mode 100644 index 273ab9e077..0000000000 --- a/tests/exhaustive/mildly_interesting/subsetSum/expected/model_1_1_2-p1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {-3, -2, 5} diff --git a/tests/exhaustive/mildly_interesting/subsetSum/expected/model_1_1_2-p1.eprime-param b/tests/exhaustive/mildly_interesting/subsetSum/expected/model_1_1_2-p1.eprime-param deleted file mode 100644 index b1ce145328..0000000000 --- a/tests/exhaustive/mildly_interesting/subsetSum/expected/model_1_1_2-p1.eprime-param +++ /dev/null @@ -1,7 +0,0 @@ -language ESSENCE' 1.0 - -letting nums_Explicit be [-7, -3, -2, 5, 8; int(1..5)] -letting s be 0 -letting fin1 be 5 -letting fin2 be -7 -letting fin3 be 8 diff --git a/tests/exhaustive/mildly_interesting/subsetSum/expected/model_1_1_2-p2-solution000001.solution b/tests/exhaustive/mildly_interesting/subsetSum/expected/model_1_1_2-p2-solution000001.solution deleted file mode 100644 index 102034e8e6..0000000000 --- a/tests/exhaustive/mildly_interesting/subsetSum/expected/model_1_1_2-p2-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {-5, 1, 4} diff --git a/tests/exhaustive/mildly_interesting/subsetSum/expected/model_1_1_2-p2-solution000002.solution b/tests/exhaustive/mildly_interesting/subsetSum/expected/model_1_1_2-p2-solution000002.solution deleted file mode 100644 index 3192b721eb..0000000000 --- a/tests/exhaustive/mildly_interesting/subsetSum/expected/model_1_1_2-p2-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {-5, 2, 3} diff --git a/tests/exhaustive/mildly_interesting/subsetSum/expected/model_1_1_2-p2.eprime-param b/tests/exhaustive/mildly_interesting/subsetSum/expected/model_1_1_2-p2.eprime-param deleted file mode 100644 index 2d232d7d8a..0000000000 --- a/tests/exhaustive/mildly_interesting/subsetSum/expected/model_1_1_2-p2.eprime-param +++ /dev/null @@ -1,7 +0,0 @@ -language ESSENCE' 1.0 - -letting nums_Explicit be [-5, 1, 2, 3, 4; int(1..5)] -letting s be 0 -letting fin1 be 5 -letting fin2 be -5 -letting fin3 be 4 diff --git a/tests/exhaustive/mildly_interesting/subsetSum/expected/model_1_1_2.eprime b/tests/exhaustive/mildly_interesting/subsetSum/expected/model_1_1_2.eprime deleted file mode 100644 index f7a55a9331..0000000000 --- a/tests/exhaustive/mildly_interesting/subsetSum/expected/model_1_1_2.eprime +++ /dev/null @@ -1,49 +0,0 @@ -language ESSENCE' 1.0 - -given s: int -given fin1: int -given fin2: int -given fin3: int -given nums_Explicit: matrix indexed by [int(1..fin1)] of int(fin2..fin3) -letting let1 be fin1 -letting let2 be [nums_Explicit[q18] | q18 : int(1..fin1)] -find x_ExplicitVarSizeWithMarker_Marker: int(0..let1) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..let1)] of int(let2) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..let1)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..let1)] of int(let2) -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithMarker_Marker, - x_ExplicitVarSizeWithMarker_Values] -such that - and([q21 <= x_ExplicitVarSizeWithMarker_Marker -> - or([nums_Explicit[q23] = x_ExplicitVarSizeWithMarker_Values[q21] | q23 : int(1..fin1)]) - | q21 : int(1..let1)]), - s = - sum([toInt(q19 <= x_ExplicitVarSizeWithMarker_Marker) * catchUndef(x_ExplicitVarSizeWithMarker_Values[q19], 0) - | q19 : int(1..let1)]), - and([q2 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q2] < x_ExplicitVarSizeWithMarker_Values[q2 + 1] - | q2 : int(1..let1 - 1)]), - and([q3 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q3] = min(let2) - | q3 : int(1..let1)]), - 1 <= x_ExplicitVarSizeWithMarker_Marker, - x_ExplicitVarSizeWithMarker_Marker <= let1, - and([x_ExplicitVarSizeWithFlags_Flags[q5 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q5] < x_ExplicitVarSizeWithFlags_Values[q5 + 1] - | q5 : int(1..let1 - 1)]), - and([x_ExplicitVarSizeWithFlags_Flags[q6] = false -> x_ExplicitVarSizeWithFlags_Values[q6] = min(let2) - | q6 : int(1..let1)]), - and([x_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q7] | q7 : int(1..let1 - 1)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q8]) | q8 : int(1..let1)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q8]) | q8 : int(1..let1)]) <= let1, - and([x_ExplicitVarSizeWithFlags_Flags[q11] -> - or([q13 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q13] = x_ExplicitVarSizeWithFlags_Values[q11] - | q13 : int(1..let1)]) - | q11 : int(1..let1)]), - and([q15 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q17] /\ - x_ExplicitVarSizeWithFlags_Values[q17] = x_ExplicitVarSizeWithMarker_Values[q15] - | q17 : int(1..let1)]) - | q15 : int(1..let1)]) - diff --git a/tests/exhaustive/mildly_interesting/subsetSum/expected/model_1_2_1-p1-solution000001.solution b/tests/exhaustive/mildly_interesting/subsetSum/expected/model_1_2_1-p1-solution000001.solution deleted file mode 100644 index 273ab9e077..0000000000 --- a/tests/exhaustive/mildly_interesting/subsetSum/expected/model_1_2_1-p1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {-3, -2, 5} diff --git a/tests/exhaustive/mildly_interesting/subsetSum/expected/model_1_2_1-p1.eprime-param b/tests/exhaustive/mildly_interesting/subsetSum/expected/model_1_2_1-p1.eprime-param deleted file mode 100644 index b1ce145328..0000000000 --- a/tests/exhaustive/mildly_interesting/subsetSum/expected/model_1_2_1-p1.eprime-param +++ /dev/null @@ -1,7 +0,0 @@ -language ESSENCE' 1.0 - -letting nums_Explicit be [-7, -3, -2, 5, 8; int(1..5)] -letting s be 0 -letting fin1 be 5 -letting fin2 be -7 -letting fin3 be 8 diff --git a/tests/exhaustive/mildly_interesting/subsetSum/expected/model_1_2_1-p2-solution000001.solution b/tests/exhaustive/mildly_interesting/subsetSum/expected/model_1_2_1-p2-solution000001.solution deleted file mode 100644 index 102034e8e6..0000000000 --- a/tests/exhaustive/mildly_interesting/subsetSum/expected/model_1_2_1-p2-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {-5, 1, 4} diff --git a/tests/exhaustive/mildly_interesting/subsetSum/expected/model_1_2_1-p2-solution000002.solution b/tests/exhaustive/mildly_interesting/subsetSum/expected/model_1_2_1-p2-solution000002.solution deleted file mode 100644 index 3192b721eb..0000000000 --- a/tests/exhaustive/mildly_interesting/subsetSum/expected/model_1_2_1-p2-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {-5, 2, 3} diff --git a/tests/exhaustive/mildly_interesting/subsetSum/expected/model_1_2_1-p2.eprime-param b/tests/exhaustive/mildly_interesting/subsetSum/expected/model_1_2_1-p2.eprime-param deleted file mode 100644 index 2d232d7d8a..0000000000 --- a/tests/exhaustive/mildly_interesting/subsetSum/expected/model_1_2_1-p2.eprime-param +++ /dev/null @@ -1,7 +0,0 @@ -language ESSENCE' 1.0 - -letting nums_Explicit be [-5, 1, 2, 3, 4; int(1..5)] -letting s be 0 -letting fin1 be 5 -letting fin2 be -5 -letting fin3 be 4 diff --git a/tests/exhaustive/mildly_interesting/subsetSum/expected/model_1_2_1.eprime b/tests/exhaustive/mildly_interesting/subsetSum/expected/model_1_2_1.eprime deleted file mode 100644 index 55b8aa4153..0000000000 --- a/tests/exhaustive/mildly_interesting/subsetSum/expected/model_1_2_1.eprime +++ /dev/null @@ -1,49 +0,0 @@ -language ESSENCE' 1.0 - -given s: int -given fin1: int -given fin2: int -given fin3: int -given nums_Explicit: matrix indexed by [int(1..fin1)] of int(fin2..fin3) -letting let1 be fin1 -letting let2 be [nums_Explicit[q18] | q18 : int(1..fin1)] -find x_ExplicitVarSizeWithMarker_Marker: int(0..let1) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..let1)] of int(let2) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..let1)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..let1)] of int(let2) -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithMarker_Marker, - x_ExplicitVarSizeWithMarker_Values] -such that - and([q21 <= x_ExplicitVarSizeWithMarker_Marker -> - or([nums_Explicit[q23] = x_ExplicitVarSizeWithMarker_Values[q21] | q23 : int(1..fin1)]) - | q21 : int(1..let1)]), - s = - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q19]) * catchUndef(x_ExplicitVarSizeWithFlags_Values[q19], 0) - | q19 : int(1..let1)]), - and([q2 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q2] < x_ExplicitVarSizeWithMarker_Values[q2 + 1] - | q2 : int(1..let1 - 1)]), - and([q3 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q3] = min(let2) - | q3 : int(1..let1)]), - 1 <= x_ExplicitVarSizeWithMarker_Marker, - x_ExplicitVarSizeWithMarker_Marker <= let1, - and([x_ExplicitVarSizeWithFlags_Flags[q5 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q5] < x_ExplicitVarSizeWithFlags_Values[q5 + 1] - | q5 : int(1..let1 - 1)]), - and([x_ExplicitVarSizeWithFlags_Flags[q6] = false -> x_ExplicitVarSizeWithFlags_Values[q6] = min(let2) - | q6 : int(1..let1)]), - and([x_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q7] | q7 : int(1..let1 - 1)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q8]) | q8 : int(1..let1)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q8]) | q8 : int(1..let1)]) <= let1, - and([x_ExplicitVarSizeWithFlags_Flags[q11] -> - or([q13 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q13] = x_ExplicitVarSizeWithFlags_Values[q11] - | q13 : int(1..let1)]) - | q11 : int(1..let1)]), - and([q15 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q17] /\ - x_ExplicitVarSizeWithFlags_Values[q17] = x_ExplicitVarSizeWithMarker_Values[q15] - | q17 : int(1..let1)]) - | q15 : int(1..let1)]) - diff --git a/tests/exhaustive/mildly_interesting/subsetSum/expected/model_1_2_2-p1-solution000001.solution b/tests/exhaustive/mildly_interesting/subsetSum/expected/model_1_2_2-p1-solution000001.solution deleted file mode 100644 index 273ab9e077..0000000000 --- a/tests/exhaustive/mildly_interesting/subsetSum/expected/model_1_2_2-p1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {-3, -2, 5} diff --git a/tests/exhaustive/mildly_interesting/subsetSum/expected/model_1_2_2-p1.eprime-param b/tests/exhaustive/mildly_interesting/subsetSum/expected/model_1_2_2-p1.eprime-param deleted file mode 100644 index b1ce145328..0000000000 --- a/tests/exhaustive/mildly_interesting/subsetSum/expected/model_1_2_2-p1.eprime-param +++ /dev/null @@ -1,7 +0,0 @@ -language ESSENCE' 1.0 - -letting nums_Explicit be [-7, -3, -2, 5, 8; int(1..5)] -letting s be 0 -letting fin1 be 5 -letting fin2 be -7 -letting fin3 be 8 diff --git a/tests/exhaustive/mildly_interesting/subsetSum/expected/model_1_2_2-p2-solution000001.solution b/tests/exhaustive/mildly_interesting/subsetSum/expected/model_1_2_2-p2-solution000001.solution deleted file mode 100644 index 102034e8e6..0000000000 --- a/tests/exhaustive/mildly_interesting/subsetSum/expected/model_1_2_2-p2-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {-5, 1, 4} diff --git a/tests/exhaustive/mildly_interesting/subsetSum/expected/model_1_2_2-p2-solution000002.solution b/tests/exhaustive/mildly_interesting/subsetSum/expected/model_1_2_2-p2-solution000002.solution deleted file mode 100644 index 3192b721eb..0000000000 --- a/tests/exhaustive/mildly_interesting/subsetSum/expected/model_1_2_2-p2-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {-5, 2, 3} diff --git a/tests/exhaustive/mildly_interesting/subsetSum/expected/model_1_2_2-p2.eprime-param b/tests/exhaustive/mildly_interesting/subsetSum/expected/model_1_2_2-p2.eprime-param deleted file mode 100644 index 2d232d7d8a..0000000000 --- a/tests/exhaustive/mildly_interesting/subsetSum/expected/model_1_2_2-p2.eprime-param +++ /dev/null @@ -1,7 +0,0 @@ -language ESSENCE' 1.0 - -letting nums_Explicit be [-5, 1, 2, 3, 4; int(1..5)] -letting s be 0 -letting fin1 be 5 -letting fin2 be -5 -letting fin3 be 4 diff --git a/tests/exhaustive/mildly_interesting/subsetSum/expected/model_1_2_2.eprime b/tests/exhaustive/mildly_interesting/subsetSum/expected/model_1_2_2.eprime deleted file mode 100644 index 55b8aa4153..0000000000 --- a/tests/exhaustive/mildly_interesting/subsetSum/expected/model_1_2_2.eprime +++ /dev/null @@ -1,49 +0,0 @@ -language ESSENCE' 1.0 - -given s: int -given fin1: int -given fin2: int -given fin3: int -given nums_Explicit: matrix indexed by [int(1..fin1)] of int(fin2..fin3) -letting let1 be fin1 -letting let2 be [nums_Explicit[q18] | q18 : int(1..fin1)] -find x_ExplicitVarSizeWithMarker_Marker: int(0..let1) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..let1)] of int(let2) -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..let1)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..let1)] of int(let2) -branching on - [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithMarker_Marker, - x_ExplicitVarSizeWithMarker_Values] -such that - and([q21 <= x_ExplicitVarSizeWithMarker_Marker -> - or([nums_Explicit[q23] = x_ExplicitVarSizeWithMarker_Values[q21] | q23 : int(1..fin1)]) - | q21 : int(1..let1)]), - s = - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q19]) * catchUndef(x_ExplicitVarSizeWithFlags_Values[q19], 0) - | q19 : int(1..let1)]), - and([q2 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q2] < x_ExplicitVarSizeWithMarker_Values[q2 + 1] - | q2 : int(1..let1 - 1)]), - and([q3 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q3] = min(let2) - | q3 : int(1..let1)]), - 1 <= x_ExplicitVarSizeWithMarker_Marker, - x_ExplicitVarSizeWithMarker_Marker <= let1, - and([x_ExplicitVarSizeWithFlags_Flags[q5 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q5] < x_ExplicitVarSizeWithFlags_Values[q5 + 1] - | q5 : int(1..let1 - 1)]), - and([x_ExplicitVarSizeWithFlags_Flags[q6] = false -> x_ExplicitVarSizeWithFlags_Values[q6] = min(let2) - | q6 : int(1..let1)]), - and([x_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q7] | q7 : int(1..let1 - 1)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q8]) | q8 : int(1..let1)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q8]) | q8 : int(1..let1)]) <= let1, - and([x_ExplicitVarSizeWithFlags_Flags[q11] -> - or([q13 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q13] = x_ExplicitVarSizeWithFlags_Values[q11] - | q13 : int(1..let1)]) - | q11 : int(1..let1)]), - and([q15 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q17] /\ - x_ExplicitVarSizeWithFlags_Values[q17] = x_ExplicitVarSizeWithMarker_Values[q15] - | q17 : int(1..let1)]) - | q15 : int(1..let1)]) - diff --git a/tests/exhaustive/mildly_interesting/subsetSum/expected/model_2_1_1-p1-solution000001.solution b/tests/exhaustive/mildly_interesting/subsetSum/expected/model_2_1_1-p1-solution000001.solution deleted file mode 100644 index 273ab9e077..0000000000 --- a/tests/exhaustive/mildly_interesting/subsetSum/expected/model_2_1_1-p1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {-3, -2, 5} diff --git a/tests/exhaustive/mildly_interesting/subsetSum/expected/model_2_1_1-p1.eprime-param b/tests/exhaustive/mildly_interesting/subsetSum/expected/model_2_1_1-p1.eprime-param deleted file mode 100644 index b1ce145328..0000000000 --- a/tests/exhaustive/mildly_interesting/subsetSum/expected/model_2_1_1-p1.eprime-param +++ /dev/null @@ -1,7 +0,0 @@ -language ESSENCE' 1.0 - -letting nums_Explicit be [-7, -3, -2, 5, 8; int(1..5)] -letting s be 0 -letting fin1 be 5 -letting fin2 be -7 -letting fin3 be 8 diff --git a/tests/exhaustive/mildly_interesting/subsetSum/expected/model_2_1_1-p2-solution000001.solution b/tests/exhaustive/mildly_interesting/subsetSum/expected/model_2_1_1-p2-solution000001.solution deleted file mode 100644 index 102034e8e6..0000000000 --- a/tests/exhaustive/mildly_interesting/subsetSum/expected/model_2_1_1-p2-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {-5, 1, 4} diff --git a/tests/exhaustive/mildly_interesting/subsetSum/expected/model_2_1_1-p2-solution000002.solution b/tests/exhaustive/mildly_interesting/subsetSum/expected/model_2_1_1-p2-solution000002.solution deleted file mode 100644 index 3192b721eb..0000000000 --- a/tests/exhaustive/mildly_interesting/subsetSum/expected/model_2_1_1-p2-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {-5, 2, 3} diff --git a/tests/exhaustive/mildly_interesting/subsetSum/expected/model_2_1_1-p2.eprime-param b/tests/exhaustive/mildly_interesting/subsetSum/expected/model_2_1_1-p2.eprime-param deleted file mode 100644 index 2d232d7d8a..0000000000 --- a/tests/exhaustive/mildly_interesting/subsetSum/expected/model_2_1_1-p2.eprime-param +++ /dev/null @@ -1,7 +0,0 @@ -language ESSENCE' 1.0 - -letting nums_Explicit be [-5, 1, 2, 3, 4; int(1..5)] -letting s be 0 -letting fin1 be 5 -letting fin2 be -5 -letting fin3 be 4 diff --git a/tests/exhaustive/mildly_interesting/subsetSum/expected/model_2_1_1.eprime b/tests/exhaustive/mildly_interesting/subsetSum/expected/model_2_1_1.eprime deleted file mode 100644 index b7ee7c510e..0000000000 --- a/tests/exhaustive/mildly_interesting/subsetSum/expected/model_2_1_1.eprime +++ /dev/null @@ -1,49 +0,0 @@ -language ESSENCE' 1.0 - -given s: int -given fin1: int -given fin2: int -given fin3: int -given nums_Explicit: matrix indexed by [int(1..fin1)] of int(fin2..fin3) -letting let1 be fin1 -letting let2 be [nums_Explicit[q18] | q18 : int(1..fin1)] -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..let1)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..let1)] of int(let2) -find x_ExplicitVarSizeWithMarker_Marker: int(0..let1) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..let1)] of int(let2) -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithFlags_Flags, - x_ExplicitVarSizeWithFlags_Values] -such that - and([x_ExplicitVarSizeWithFlags_Flags[q21] -> - or([nums_Explicit[q23] = x_ExplicitVarSizeWithFlags_Values[q21] | q23 : int(1..fin1)]) - | q21 : int(1..let1)]), - s = - sum([toInt(q19 <= x_ExplicitVarSizeWithMarker_Marker) * catchUndef(x_ExplicitVarSizeWithMarker_Values[q19], 0) - | q19 : int(1..let1)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q2] < x_ExplicitVarSizeWithFlags_Values[q2 + 1] - | q2 : int(1..let1 - 1)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3] = false -> x_ExplicitVarSizeWithFlags_Values[q3] = min(let2) - | q3 : int(1..let1)]), - and([x_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q4] | q4 : int(1..let1 - 1)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q5]) | q5 : int(1..let1)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q5]) | q5 : int(1..let1)]) <= let1, - and([q7 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q7] < x_ExplicitVarSizeWithMarker_Values[q7 + 1] - | q7 : int(1..let1 - 1)]), - and([q8 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q8] = min(let2) - | q8 : int(1..let1)]), - 1 <= x_ExplicitVarSizeWithMarker_Marker, - x_ExplicitVarSizeWithMarker_Marker <= let1, - and([q11 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q13] /\ - x_ExplicitVarSizeWithFlags_Values[q13] = x_ExplicitVarSizeWithMarker_Values[q11] - | q13 : int(1..let1)]) - | q11 : int(1..let1)]), - and([x_ExplicitVarSizeWithFlags_Flags[q15] -> - or([q17 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q17] = x_ExplicitVarSizeWithFlags_Values[q15] - | q17 : int(1..let1)]) - | q15 : int(1..let1)]) - diff --git a/tests/exhaustive/mildly_interesting/subsetSum/expected/model_2_1_2-p1-solution000001.solution b/tests/exhaustive/mildly_interesting/subsetSum/expected/model_2_1_2-p1-solution000001.solution deleted file mode 100644 index 273ab9e077..0000000000 --- a/tests/exhaustive/mildly_interesting/subsetSum/expected/model_2_1_2-p1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {-3, -2, 5} diff --git a/tests/exhaustive/mildly_interesting/subsetSum/expected/model_2_1_2-p1.eprime-param b/tests/exhaustive/mildly_interesting/subsetSum/expected/model_2_1_2-p1.eprime-param deleted file mode 100644 index b1ce145328..0000000000 --- a/tests/exhaustive/mildly_interesting/subsetSum/expected/model_2_1_2-p1.eprime-param +++ /dev/null @@ -1,7 +0,0 @@ -language ESSENCE' 1.0 - -letting nums_Explicit be [-7, -3, -2, 5, 8; int(1..5)] -letting s be 0 -letting fin1 be 5 -letting fin2 be -7 -letting fin3 be 8 diff --git a/tests/exhaustive/mildly_interesting/subsetSum/expected/model_2_1_2-p2-solution000001.solution b/tests/exhaustive/mildly_interesting/subsetSum/expected/model_2_1_2-p2-solution000001.solution deleted file mode 100644 index 102034e8e6..0000000000 --- a/tests/exhaustive/mildly_interesting/subsetSum/expected/model_2_1_2-p2-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {-5, 1, 4} diff --git a/tests/exhaustive/mildly_interesting/subsetSum/expected/model_2_1_2-p2-solution000002.solution b/tests/exhaustive/mildly_interesting/subsetSum/expected/model_2_1_2-p2-solution000002.solution deleted file mode 100644 index 3192b721eb..0000000000 --- a/tests/exhaustive/mildly_interesting/subsetSum/expected/model_2_1_2-p2-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {-5, 2, 3} diff --git a/tests/exhaustive/mildly_interesting/subsetSum/expected/model_2_1_2-p2.eprime-param b/tests/exhaustive/mildly_interesting/subsetSum/expected/model_2_1_2-p2.eprime-param deleted file mode 100644 index 2d232d7d8a..0000000000 --- a/tests/exhaustive/mildly_interesting/subsetSum/expected/model_2_1_2-p2.eprime-param +++ /dev/null @@ -1,7 +0,0 @@ -language ESSENCE' 1.0 - -letting nums_Explicit be [-5, 1, 2, 3, 4; int(1..5)] -letting s be 0 -letting fin1 be 5 -letting fin2 be -5 -letting fin3 be 4 diff --git a/tests/exhaustive/mildly_interesting/subsetSum/expected/model_2_1_2.eprime b/tests/exhaustive/mildly_interesting/subsetSum/expected/model_2_1_2.eprime deleted file mode 100644 index b7ee7c510e..0000000000 --- a/tests/exhaustive/mildly_interesting/subsetSum/expected/model_2_1_2.eprime +++ /dev/null @@ -1,49 +0,0 @@ -language ESSENCE' 1.0 - -given s: int -given fin1: int -given fin2: int -given fin3: int -given nums_Explicit: matrix indexed by [int(1..fin1)] of int(fin2..fin3) -letting let1 be fin1 -letting let2 be [nums_Explicit[q18] | q18 : int(1..fin1)] -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..let1)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..let1)] of int(let2) -find x_ExplicitVarSizeWithMarker_Marker: int(0..let1) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..let1)] of int(let2) -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithFlags_Flags, - x_ExplicitVarSizeWithFlags_Values] -such that - and([x_ExplicitVarSizeWithFlags_Flags[q21] -> - or([nums_Explicit[q23] = x_ExplicitVarSizeWithFlags_Values[q21] | q23 : int(1..fin1)]) - | q21 : int(1..let1)]), - s = - sum([toInt(q19 <= x_ExplicitVarSizeWithMarker_Marker) * catchUndef(x_ExplicitVarSizeWithMarker_Values[q19], 0) - | q19 : int(1..let1)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q2] < x_ExplicitVarSizeWithFlags_Values[q2 + 1] - | q2 : int(1..let1 - 1)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3] = false -> x_ExplicitVarSizeWithFlags_Values[q3] = min(let2) - | q3 : int(1..let1)]), - and([x_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q4] | q4 : int(1..let1 - 1)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q5]) | q5 : int(1..let1)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q5]) | q5 : int(1..let1)]) <= let1, - and([q7 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q7] < x_ExplicitVarSizeWithMarker_Values[q7 + 1] - | q7 : int(1..let1 - 1)]), - and([q8 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q8] = min(let2) - | q8 : int(1..let1)]), - 1 <= x_ExplicitVarSizeWithMarker_Marker, - x_ExplicitVarSizeWithMarker_Marker <= let1, - and([q11 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q13] /\ - x_ExplicitVarSizeWithFlags_Values[q13] = x_ExplicitVarSizeWithMarker_Values[q11] - | q13 : int(1..let1)]) - | q11 : int(1..let1)]), - and([x_ExplicitVarSizeWithFlags_Flags[q15] -> - or([q17 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q17] = x_ExplicitVarSizeWithFlags_Values[q15] - | q17 : int(1..let1)]) - | q15 : int(1..let1)]) - diff --git a/tests/exhaustive/mildly_interesting/subsetSum/expected/model_2_2_1-p1-solution000001.solution b/tests/exhaustive/mildly_interesting/subsetSum/expected/model_2_2_1-p1-solution000001.solution deleted file mode 100644 index 273ab9e077..0000000000 --- a/tests/exhaustive/mildly_interesting/subsetSum/expected/model_2_2_1-p1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {-3, -2, 5} diff --git a/tests/exhaustive/mildly_interesting/subsetSum/expected/model_2_2_1-p1.eprime-param b/tests/exhaustive/mildly_interesting/subsetSum/expected/model_2_2_1-p1.eprime-param deleted file mode 100644 index b1ce145328..0000000000 --- a/tests/exhaustive/mildly_interesting/subsetSum/expected/model_2_2_1-p1.eprime-param +++ /dev/null @@ -1,7 +0,0 @@ -language ESSENCE' 1.0 - -letting nums_Explicit be [-7, -3, -2, 5, 8; int(1..5)] -letting s be 0 -letting fin1 be 5 -letting fin2 be -7 -letting fin3 be 8 diff --git a/tests/exhaustive/mildly_interesting/subsetSum/expected/model_2_2_1-p2-solution000001.solution b/tests/exhaustive/mildly_interesting/subsetSum/expected/model_2_2_1-p2-solution000001.solution deleted file mode 100644 index 102034e8e6..0000000000 --- a/tests/exhaustive/mildly_interesting/subsetSum/expected/model_2_2_1-p2-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {-5, 1, 4} diff --git a/tests/exhaustive/mildly_interesting/subsetSum/expected/model_2_2_1-p2-solution000002.solution b/tests/exhaustive/mildly_interesting/subsetSum/expected/model_2_2_1-p2-solution000002.solution deleted file mode 100644 index 3192b721eb..0000000000 --- a/tests/exhaustive/mildly_interesting/subsetSum/expected/model_2_2_1-p2-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {-5, 2, 3} diff --git a/tests/exhaustive/mildly_interesting/subsetSum/expected/model_2_2_1-p2.eprime-param b/tests/exhaustive/mildly_interesting/subsetSum/expected/model_2_2_1-p2.eprime-param deleted file mode 100644 index 2d232d7d8a..0000000000 --- a/tests/exhaustive/mildly_interesting/subsetSum/expected/model_2_2_1-p2.eprime-param +++ /dev/null @@ -1,7 +0,0 @@ -language ESSENCE' 1.0 - -letting nums_Explicit be [-5, 1, 2, 3, 4; int(1..5)] -letting s be 0 -letting fin1 be 5 -letting fin2 be -5 -letting fin3 be 4 diff --git a/tests/exhaustive/mildly_interesting/subsetSum/expected/model_2_2_1.eprime b/tests/exhaustive/mildly_interesting/subsetSum/expected/model_2_2_1.eprime deleted file mode 100644 index 36c7029a44..0000000000 --- a/tests/exhaustive/mildly_interesting/subsetSum/expected/model_2_2_1.eprime +++ /dev/null @@ -1,49 +0,0 @@ -language ESSENCE' 1.0 - -given s: int -given fin1: int -given fin2: int -given fin3: int -given nums_Explicit: matrix indexed by [int(1..fin1)] of int(fin2..fin3) -letting let1 be fin1 -letting let2 be [nums_Explicit[q18] | q18 : int(1..fin1)] -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..let1)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..let1)] of int(let2) -find x_ExplicitVarSizeWithMarker_Marker: int(0..let1) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..let1)] of int(let2) -branching on - [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithFlags_Flags, - x_ExplicitVarSizeWithFlags_Values] -such that - and([x_ExplicitVarSizeWithFlags_Flags[q21] -> - or([nums_Explicit[q23] = x_ExplicitVarSizeWithFlags_Values[q21] | q23 : int(1..fin1)]) - | q21 : int(1..let1)]), - s = - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q19]) * catchUndef(x_ExplicitVarSizeWithFlags_Values[q19], 0) - | q19 : int(1..let1)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q2] < x_ExplicitVarSizeWithFlags_Values[q2 + 1] - | q2 : int(1..let1 - 1)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3] = false -> x_ExplicitVarSizeWithFlags_Values[q3] = min(let2) - | q3 : int(1..let1)]), - and([x_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q4] | q4 : int(1..let1 - 1)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q5]) | q5 : int(1..let1)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q5]) | q5 : int(1..let1)]) <= let1, - and([q7 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q7] < x_ExplicitVarSizeWithMarker_Values[q7 + 1] - | q7 : int(1..let1 - 1)]), - and([q8 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q8] = min(let2) - | q8 : int(1..let1)]), - 1 <= x_ExplicitVarSizeWithMarker_Marker, - x_ExplicitVarSizeWithMarker_Marker <= let1, - and([q11 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithFlags_Flags[q13] /\ - x_ExplicitVarSizeWithFlags_Values[q13] = x_ExplicitVarSizeWithMarker_Values[q11] - | q13 : int(1..let1)]) - | q11 : int(1..let1)]), - and([x_ExplicitVarSizeWithFlags_Flags[q15] -> - or([q17 <= x_ExplicitVarSizeWithMarker_Marker /\ - x_ExplicitVarSizeWithMarker_Values[q17] = x_ExplicitVarSizeWithFlags_Values[q15] - | q17 : int(1..let1)]) - | q15 : int(1..let1)]) - diff --git a/tests/exhaustive/mildly_interesting/subsetSum/expected/model_2_2_2-p1-solution000001.solution b/tests/exhaustive/mildly_interesting/subsetSum/expected/model_2_2_2-p1-solution000001.solution deleted file mode 100644 index 273ab9e077..0000000000 --- a/tests/exhaustive/mildly_interesting/subsetSum/expected/model_2_2_2-p1-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {-3, -2, 5} diff --git a/tests/exhaustive/mildly_interesting/subsetSum/expected/model_2_2_2-p1.eprime-param b/tests/exhaustive/mildly_interesting/subsetSum/expected/model_2_2_2-p1.eprime-param deleted file mode 100644 index b1ce145328..0000000000 --- a/tests/exhaustive/mildly_interesting/subsetSum/expected/model_2_2_2-p1.eprime-param +++ /dev/null @@ -1,7 +0,0 @@ -language ESSENCE' 1.0 - -letting nums_Explicit be [-7, -3, -2, 5, 8; int(1..5)] -letting s be 0 -letting fin1 be 5 -letting fin2 be -7 -letting fin3 be 8 diff --git a/tests/exhaustive/mildly_interesting/subsetSum/expected/model_2_2_2-p2-solution000001.solution b/tests/exhaustive/mildly_interesting/subsetSum/expected/model_2_2_2-p2-solution000001.solution deleted file mode 100644 index 102034e8e6..0000000000 --- a/tests/exhaustive/mildly_interesting/subsetSum/expected/model_2_2_2-p2-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {-5, 1, 4} diff --git a/tests/exhaustive/mildly_interesting/subsetSum/expected/model_2_2_2-p2-solution000002.solution b/tests/exhaustive/mildly_interesting/subsetSum/expected/model_2_2_2-p2-solution000002.solution deleted file mode 100644 index 3192b721eb..0000000000 --- a/tests/exhaustive/mildly_interesting/subsetSum/expected/model_2_2_2-p2-solution000002.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting x be {-5, 2, 3} diff --git a/tests/exhaustive/mildly_interesting/subsetSum/expected/model_2_2_2-p2.eprime-param b/tests/exhaustive/mildly_interesting/subsetSum/expected/model_2_2_2-p2.eprime-param deleted file mode 100644 index 2d232d7d8a..0000000000 --- a/tests/exhaustive/mildly_interesting/subsetSum/expected/model_2_2_2-p2.eprime-param +++ /dev/null @@ -1,7 +0,0 @@ -language ESSENCE' 1.0 - -letting nums_Explicit be [-5, 1, 2, 3, 4; int(1..5)] -letting s be 0 -letting fin1 be 5 -letting fin2 be -5 -letting fin3 be 4 diff --git a/tests/exhaustive/mildly_interesting/subsetSum/expected/model_2_2_2.eprime b/tests/exhaustive/mildly_interesting/subsetSum/expected/model_2_2_2.eprime deleted file mode 100644 index e242a71db7..0000000000 --- a/tests/exhaustive/mildly_interesting/subsetSum/expected/model_2_2_2.eprime +++ /dev/null @@ -1,28 +0,0 @@ -language ESSENCE' 1.0 - -given s: int -given fin1: int -given fin2: int -given fin3: int -given nums_Explicit: matrix indexed by [int(1..fin1)] of int(fin2..fin3) -letting let1 be fin1 -letting let2 be [nums_Explicit[q7] | q7 : int(1..fin1)] -find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..let1)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..let1)] of int(let2) -branching on [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] -such that - and([x_ExplicitVarSizeWithFlags_Flags[q10] -> - or([nums_Explicit[q12] = x_ExplicitVarSizeWithFlags_Values[q10] | q12 : int(1..fin1)]) - | q10 : int(1..let1)]), - s = - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q8]) * catchUndef(x_ExplicitVarSizeWithFlags_Values[q8], 0) - | q8 : int(1..let1)]), - and([x_ExplicitVarSizeWithFlags_Flags[q2 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q2] < x_ExplicitVarSizeWithFlags_Values[q2 + 1] - | q2 : int(1..let1 - 1)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3] = false -> x_ExplicitVarSizeWithFlags_Values[q3] = min(let2) - | q3 : int(1..let1)]), - and([x_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q4] | q4 : int(1..let1 - 1)]), - 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q5]) | q5 : int(1..let1)]), - sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q5]) | q5 : int(1..let1)]) <= let1 - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000001.solution deleted file mode 100644 index 534774871a..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be function() -letting b be function(2 --> false) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000002.solution b/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000002.solution deleted file mode 100644 index 9346e1754b..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be function() -letting b be function(2 --> true) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000003.solution b/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000003.solution deleted file mode 100644 index 74b1a6d481..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be function() -letting b be function(1 --> false) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000004.solution b/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000004.solution deleted file mode 100644 index 4a96af448e..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be function() -letting b be function(1 --> true) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000005.solution b/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000005.solution deleted file mode 100644 index 0e18364d45..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be function() -letting b be function(1 --> false, 2 --> false) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000006.solution b/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000006.solution deleted file mode 100644 index a342f9b86e..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be function() -letting b be function(1 --> false, 2 --> true) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000007.solution b/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000007.solution deleted file mode 100644 index 5677d2b395..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000007.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be function() -letting b be function(1 --> true, 2 --> false) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000008.solution b/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000008.solution deleted file mode 100644 index 2df313a9bf..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000008.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be function() -letting b be function(1 --> true, 2 --> true) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000009.solution b/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000009.solution deleted file mode 100644 index 58fbafa57e..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000009.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be function(2 --> false) -letting b be function(1 --> false) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000010.solution b/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000010.solution deleted file mode 100644 index 789b9c90d3..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000010.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be function(2 --> false) -letting b be function(1 --> true) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000011.solution b/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000011.solution deleted file mode 100644 index 2edff105b5..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000011.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be function(2 --> false) -letting b be function(1 --> false, 2 --> false) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000012.solution b/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000012.solution deleted file mode 100644 index 74e94168a0..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000012.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be function(2 --> false) -letting b be function(1 --> false, 2 --> true) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000013.solution b/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000013.solution deleted file mode 100644 index 093bdec177..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000013.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be function(2 --> false) -letting b be function(1 --> true, 2 --> false) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000014.solution b/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000014.solution deleted file mode 100644 index 7f91bef76e..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000014.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be function(2 --> false) -letting b be function(1 --> true, 2 --> true) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000015.solution b/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000015.solution deleted file mode 100644 index 2d31ea87c0..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000015.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be function(2 --> true) -letting b be function(2 --> false) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000016.solution b/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000016.solution deleted file mode 100644 index 39c8593d69..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000016.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be function(2 --> true) -letting b be function(1 --> false) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000017.solution b/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000017.solution deleted file mode 100644 index a0d0c36916..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000017.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be function(2 --> true) -letting b be function(1 --> true) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000018.solution b/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000018.solution deleted file mode 100644 index f9ea159aa2..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000018.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be function(2 --> true) -letting b be function(1 --> false, 2 --> false) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000019.solution b/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000019.solution deleted file mode 100644 index 957cf9fb82..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000019.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be function(2 --> true) -letting b be function(1 --> false, 2 --> true) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000020.solution b/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000020.solution deleted file mode 100644 index 3f9decd735..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000020.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be function(2 --> true) -letting b be function(1 --> true, 2 --> false) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000021.solution b/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000021.solution deleted file mode 100644 index 46ef148b20..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000021.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be function(2 --> true) -letting b be function(1 --> true, 2 --> true) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000022.solution b/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000022.solution deleted file mode 100644 index 2452e99fe4..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000022.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be function(1 --> false) -letting b be function(1 --> false, 2 --> false) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000023.solution b/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000023.solution deleted file mode 100644 index d7ded0c4b6..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000023.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be function(1 --> false) -letting b be function(1 --> false, 2 --> true) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000024.solution b/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000024.solution deleted file mode 100644 index dd8080c849..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000024.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be function(1 --> true) -letting b be function(1 --> false) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000025.solution b/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000025.solution deleted file mode 100644 index 270ba7d5b7..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000025.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be function(1 --> true) -letting b be function(1 --> false, 2 --> false) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000026.solution b/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000026.solution deleted file mode 100644 index 9081271d97..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000026.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be function(1 --> true) -letting b be function(1 --> false, 2 --> true) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000027.solution b/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000027.solution deleted file mode 100644 index 75603c59ea..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000027.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be function(1 --> true) -letting b be function(1 --> true, 2 --> false) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000028.solution b/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000028.solution deleted file mode 100644 index 3784cc005f..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000028.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be function(1 --> true) -letting b be function(1 --> true, 2 --> true) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000029.solution b/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000029.solution deleted file mode 100644 index 3e724ff0d1..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000029.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be function(1 --> false, 2 --> true) -letting b be function(1 --> false, 2 --> false) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000030.solution b/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000030.solution deleted file mode 100644 index e63fb8f776..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000030.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be function(1 --> true, 2 --> false) -letting b be function(1 --> false) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000031.solution b/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000031.solution deleted file mode 100644 index 80da5627ce..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000031.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be function(1 --> true, 2 --> false) -letting b be function(1 --> false, 2 --> false) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000032.solution b/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000032.solution deleted file mode 100644 index 6944fdbfc9..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000032.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be function(1 --> true, 2 --> false) -letting b be function(1 --> false, 2 --> true) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000033.solution b/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000033.solution deleted file mode 100644 index 2143a4e6fe..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000033.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be function(1 --> true, 2 --> true) -letting b be function(1 --> false) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000034.solution b/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000034.solution deleted file mode 100644 index e9eb65412b..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000034.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be function(1 --> true, 2 --> true) -letting b be function(1 --> false, 2 --> false) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000035.solution b/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000035.solution deleted file mode 100644 index 0e6e174af5..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000035.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be function(1 --> true, 2 --> true) -letting b be function(1 --> false, 2 --> true) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000036.solution b/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000036.solution deleted file mode 100644 index cd636fd528..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000036.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be function(1 --> true, 2 --> true) -letting b be function(1 --> true, 2 --> false) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model.eprime b/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model.eprime deleted file mode 100644 index 18f14caf88..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model.eprime +++ /dev/null @@ -1,91 +0,0 @@ -language ESSENCE' 1.0 - -find a_Function1DPartial_Flags: matrix indexed by [int(1..2)] of bool -find a_Function1DPartial_Values: matrix indexed by [int(1..2)] of bool -find b_Function1DPartial_Flags: matrix indexed by [int(1..2)] of bool -find b_Function1DPartial_Values: matrix indexed by [int(1..2)] of bool -branching on - [a_Function1DPartial_Flags, a_Function1DPartial_Values, b_Function1DPartial_Flags, b_Function1DPartial_Values] -such that - or([a_Function1DPartial_Flags[q9] /\ - (sum([toInt(a_Function1DPartial_Flags[q30]) * - catchUndef(toInt(q30 = q9 /\ a_Function1DPartial_Values[q30] = a_Function1DPartial_Values[q9]), 0) - | q30 : int(1..2)]) - < - sum([toInt(b_Function1DPartial_Flags[q32]) * - catchUndef(toInt(q32 = q9 /\ b_Function1DPartial_Values[q32] = a_Function1DPartial_Values[q9]), 0) - | q32 : int(1..2)]) - /\ - (and([a_Function1DPartial_Flags[q33] /\ - (q33 < q9 \/ q33 = q9 /\ a_Function1DPartial_Values[q33] < a_Function1DPartial_Values[q9]) - -> - sum([toInt(a_Function1DPartial_Flags[q42]) * - catchUndef(toInt(q42 = q33 /\ a_Function1DPartial_Values[q42] = a_Function1DPartial_Values[q33]), 0) - | q42 : int(1..2)]) - = - sum([toInt(b_Function1DPartial_Flags[q44]) * - catchUndef(toInt(q44 = q33 /\ b_Function1DPartial_Values[q44] = a_Function1DPartial_Values[q33]), 0) - | q44 : int(1..2)]) - | q33 : int(1..2)]) - /\ - and([and([b_Function1DPartial_Flags[q34], - !or([a_Function1DPartial_Flags[q40] /\ - (q40 = q34 /\ a_Function1DPartial_Values[q40] = b_Function1DPartial_Values[q34]) - | q40 : int(1..2)]), - q34 < q9 \/ q34 = q9 /\ b_Function1DPartial_Values[q34] < a_Function1DPartial_Values[q9]; - int(1..3)]) - -> - sum([toInt(a_Function1DPartial_Flags[q36]) * - catchUndef(toInt(q36 = q34 /\ a_Function1DPartial_Values[q36] = b_Function1DPartial_Values[q34]), 0) - | q36 : int(1..2)]) - = - sum([toInt(b_Function1DPartial_Flags[q38]) * - catchUndef(toInt(q38 = q34 /\ b_Function1DPartial_Values[q38] = b_Function1DPartial_Values[q34]), 0) - | q38 : int(1..2)]) - | q34 : int(1..2)]))) - | q9 : int(1..2)]) - \/ - or([b_Function1DPartial_Flags[q10] /\ - !or([a_Function1DPartial_Flags[q28] /\ - (q28 = q10 /\ a_Function1DPartial_Values[q28] = b_Function1DPartial_Values[q10]) - | q28 : int(1..2)]) - /\ - (sum([toInt(a_Function1DPartial_Flags[q12]) * - catchUndef(toInt(q12 = q10 /\ a_Function1DPartial_Values[q12] = b_Function1DPartial_Values[q10]), 0) - | q12 : int(1..2)]) - < - sum([toInt(b_Function1DPartial_Flags[q14]) * - catchUndef(toInt(q14 = q10 /\ b_Function1DPartial_Values[q14] = b_Function1DPartial_Values[q10]), 0) - | q14 : int(1..2)]) - /\ - (and([a_Function1DPartial_Flags[q15] /\ - (q15 < q10 \/ q15 = q10 /\ a_Function1DPartial_Values[q15] < b_Function1DPartial_Values[q10]) - -> - sum([toInt(a_Function1DPartial_Flags[q24]) * - catchUndef(toInt(q24 = q15 /\ a_Function1DPartial_Values[q24] = a_Function1DPartial_Values[q15]), 0) - | q24 : int(1..2)]) - = - sum([toInt(b_Function1DPartial_Flags[q26]) * - catchUndef(toInt(q26 = q15 /\ b_Function1DPartial_Values[q26] = a_Function1DPartial_Values[q15]), 0) - | q26 : int(1..2)]) - | q15 : int(1..2)]) - /\ - and([and([b_Function1DPartial_Flags[q16], - !or([a_Function1DPartial_Flags[q22] /\ - (q22 = q16 /\ a_Function1DPartial_Values[q22] = b_Function1DPartial_Values[q16]) - | q22 : int(1..2)]), - q16 < q10 \/ q16 = q10 /\ b_Function1DPartial_Values[q16] < b_Function1DPartial_Values[q10]; - int(1..3)]) - -> - sum([toInt(a_Function1DPartial_Flags[q18]) * - catchUndef(toInt(q18 = q16 /\ a_Function1DPartial_Values[q18] = b_Function1DPartial_Values[q16]), 0) - | q18 : int(1..2)]) - = - sum([toInt(b_Function1DPartial_Flags[q20]) * - catchUndef(toInt(q20 = q16 /\ b_Function1DPartial_Values[q20] = b_Function1DPartial_Values[q16]), 0) - | q20 : int(1..2)]) - | q16 : int(1..2)]))) - | q10 : int(1..2)]), - and([a_Function1DPartial_Flags[q1] = false -> a_Function1DPartial_Values[q1] = false | q1 : int(1..2)]), - and([b_Function1DPartial_Flags[q4] = false -> b_Function1DPartial_Values[q4] = false | q4 : int(1..2)]) - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_1_1-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_1_1-solution000001.solution deleted file mode 100644 index 5e2caa751c..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_1_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 2, 2) -letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_1_1-solution000002.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_1_1-solution000002.solution deleted file mode 100644 index 1b4b5b08a6..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_1_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 2, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_1_1-solution000003.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_1_1-solution000003.solution deleted file mode 100644 index 621d5f6edc..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_1_1-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 1, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_1_1-solution000004.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_1_1-solution000004.solution deleted file mode 100644 index 15472caf03..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_1_1-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 2, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_1_1-solution000005.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_1_1-solution000005.solution deleted file mode 100644 index ff56905e23..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_1_1-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_1_1-solution000006.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_1_1-solution000006.solution deleted file mode 100644 index d56a0bbcdc..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_1_1-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_1_1.eprime b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_1_1.eprime deleted file mode 100644 index c8ad15824b..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_1_1.eprime +++ /dev/null @@ -1,96 +0,0 @@ -language ESSENCE' 1.0 - -find a_ExplicitWithFlags_Flags: matrix indexed by [int(1..3)] of int(0..3) -find a_ExplicitWithFlags_Values: matrix indexed by [int(1..3)] of int(1..2) -find b_ExplicitWithFlags_Flags: matrix indexed by [int(1..3)] of int(0..3) -find b_ExplicitWithFlags_Values: matrix indexed by [int(1..3)] of int(1..2) -branching on - [a_ExplicitWithFlags_Flags, a_ExplicitWithFlags_Values, b_ExplicitWithFlags_Flags, b_ExplicitWithFlags_Values] -such that - or([a_ExplicitWithFlags_Flags[q25] > 0 /\ - (sum([toInt(a_ExplicitWithFlags_Values[q15] = a_ExplicitWithFlags_Values[q25]) * - catchUndef(a_ExplicitWithFlags_Flags[q15], 0) - | q15 : int(1..3)]) - < - sum([toInt(b_ExplicitWithFlags_Values[q16] = a_ExplicitWithFlags_Values[q25]) * - catchUndef(b_ExplicitWithFlags_Flags[q16], 0) - | q16 : int(1..3)]) - /\ - (and([a_ExplicitWithFlags_Flags[q21] > 0 /\ a_ExplicitWithFlags_Values[q21] < a_ExplicitWithFlags_Values[q25] - -> - sum([toInt(a_ExplicitWithFlags_Values[q17] = a_ExplicitWithFlags_Values[q21]) * - catchUndef(a_ExplicitWithFlags_Flags[q17], 0) - | q17 : int(1..3)]) - = - sum([toInt(b_ExplicitWithFlags_Values[q18] = a_ExplicitWithFlags_Values[q21]) * - catchUndef(b_ExplicitWithFlags_Flags[q18], 0) - | q18 : int(1..3)]) - | q21 : int(1..3)]) - /\ - and([and([b_ExplicitWithFlags_Flags[q22] > 0, - !or([a_ExplicitWithFlags_Flags[q20] > 0 /\ - a_ExplicitWithFlags_Values[q20] = b_ExplicitWithFlags_Values[q22] - | q20 : int(1..3)]), - b_ExplicitWithFlags_Values[q22] < a_ExplicitWithFlags_Values[q25]; - int(1..3)]) - -> - sum([toInt(a_ExplicitWithFlags_Values[q17] = b_ExplicitWithFlags_Values[q22]) * - catchUndef(a_ExplicitWithFlags_Flags[q17], 0) - | q17 : int(1..3)]) - = - sum([toInt(b_ExplicitWithFlags_Values[q18] = b_ExplicitWithFlags_Values[q22]) * - catchUndef(b_ExplicitWithFlags_Flags[q18], 0) - | q18 : int(1..3)]) - | q22 : int(1..3)]))) - | q25 : int(1..3)]) - \/ - or([b_ExplicitWithFlags_Flags[q26] > 0 /\ - !or([a_ExplicitWithFlags_Flags[q24] > 0 /\ a_ExplicitWithFlags_Values[q24] = b_ExplicitWithFlags_Values[q26] - | q24 : int(1..3)]) - /\ - (sum([toInt(a_ExplicitWithFlags_Values[q15] = b_ExplicitWithFlags_Values[q26]) * - catchUndef(a_ExplicitWithFlags_Flags[q15], 0) - | q15 : int(1..3)]) - < - sum([toInt(b_ExplicitWithFlags_Values[q16] = b_ExplicitWithFlags_Values[q26]) * - catchUndef(b_ExplicitWithFlags_Flags[q16], 0) - | q16 : int(1..3)]) - /\ - (and([a_ExplicitWithFlags_Flags[q21] > 0 /\ a_ExplicitWithFlags_Values[q21] < b_ExplicitWithFlags_Values[q26] - -> - sum([toInt(a_ExplicitWithFlags_Values[q17] = a_ExplicitWithFlags_Values[q21]) * - catchUndef(a_ExplicitWithFlags_Flags[q17], 0) - | q17 : int(1..3)]) - = - sum([toInt(b_ExplicitWithFlags_Values[q18] = a_ExplicitWithFlags_Values[q21]) * - catchUndef(b_ExplicitWithFlags_Flags[q18], 0) - | q18 : int(1..3)]) - | q21 : int(1..3)]) - /\ - and([and([b_ExplicitWithFlags_Flags[q22] > 0, - !or([a_ExplicitWithFlags_Flags[q20] > 0 /\ - a_ExplicitWithFlags_Values[q20] = b_ExplicitWithFlags_Values[q22] - | q20 : int(1..3)]), - b_ExplicitWithFlags_Values[q22] < b_ExplicitWithFlags_Values[q26]; - int(1..3)]) - -> - sum([toInt(a_ExplicitWithFlags_Values[q17] = b_ExplicitWithFlags_Values[q22]) * - catchUndef(a_ExplicitWithFlags_Flags[q17], 0) - | q17 : int(1..3)]) - = - sum([toInt(b_ExplicitWithFlags_Values[q18] = b_ExplicitWithFlags_Values[q22]) * - catchUndef(b_ExplicitWithFlags_Flags[q18], 0) - | q18 : int(1..3)]) - | q22 : int(1..3)]))) - | q26 : int(1..3)]), - and([a_ExplicitWithFlags_Flags[q1 + 1] > 0 -> a_ExplicitWithFlags_Values[q1] < a_ExplicitWithFlags_Values[q1 + 1] - | q1 : int(1..2)]), - and([a_ExplicitWithFlags_Flags[q2] = 0 -> a_ExplicitWithFlags_Values[q2] = 1 | q2 : int(1..3)]), - and([a_ExplicitWithFlags_Flags[q3 + 1] > 0 -> a_ExplicitWithFlags_Flags[q3] > 0 | q3 : int(1..2)]), - 3 = sum([a_ExplicitWithFlags_Flags[q5] | q5 : int(1..3)]), - and([b_ExplicitWithFlags_Flags[q7 + 1] > 0 -> b_ExplicitWithFlags_Values[q7] < b_ExplicitWithFlags_Values[q7 + 1] - | q7 : int(1..2)]), - and([b_ExplicitWithFlags_Flags[q8] = 0 -> b_ExplicitWithFlags_Values[q8] = 1 | q8 : int(1..3)]), - and([b_ExplicitWithFlags_Flags[q9 + 1] > 0 -> b_ExplicitWithFlags_Flags[q9] > 0 | q9 : int(1..2)]), - 3 = sum([b_ExplicitWithFlags_Flags[q11] | q11 : int(1..3)]) - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_1_2-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_1_2-solution000001.solution deleted file mode 100644 index 1b4b5b08a6..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_1_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 2, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_1_2-solution000002.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_1_2-solution000002.solution deleted file mode 100644 index 5e2caa751c..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_1_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 2, 2) -letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_1_2-solution000003.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_1_2-solution000003.solution deleted file mode 100644 index 621d5f6edc..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_1_2-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 1, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_1_2-solution000004.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_1_2-solution000004.solution deleted file mode 100644 index d56a0bbcdc..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_1_2-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_1_2-solution000005.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_1_2-solution000005.solution deleted file mode 100644 index ff56905e23..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_1_2-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_1_2-solution000006.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_1_2-solution000006.solution deleted file mode 100644 index 15472caf03..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_1_2-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 2, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_1_2.eprime b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_1_2.eprime deleted file mode 100644 index 35f7c0f260..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_1_2.eprime +++ /dev/null @@ -1,116 +0,0 @@ -language ESSENCE' 1.0 - -find a_ExplicitWithFlags_Flags: matrix indexed by [int(1..3)] of int(0..3) -find a_ExplicitWithFlags_Values: matrix indexed by [int(1..3)] of int(1..2) -find b_ExplicitWithFlags_Flags: matrix indexed by [int(1..3)] of int(0..3) -find b_ExplicitWithFlags_Values: matrix indexed by [int(1..3)] of int(1..2) -find b_ExplicitWithRepetition_Flag: int(3) -find b_ExplicitWithRepetition_Values: matrix indexed by [int(1..3)] of int(1..2) -branching on - [a_ExplicitWithFlags_Flags, a_ExplicitWithFlags_Values, b_ExplicitWithRepetition_Flag, - b_ExplicitWithRepetition_Values, b_ExplicitWithFlags_Flags, b_ExplicitWithFlags_Values] -such that - or([a_ExplicitWithFlags_Flags[q39] > 0 /\ - (sum([toInt(a_ExplicitWithFlags_Values[q29] = a_ExplicitWithFlags_Values[q39]) * - catchUndef(a_ExplicitWithFlags_Flags[q29], 0) - | q29 : int(1..3)]) - < - sum([toInt(b_ExplicitWithFlags_Values[q30] = a_ExplicitWithFlags_Values[q39]) * - catchUndef(b_ExplicitWithFlags_Flags[q30], 0) - | q30 : int(1..3)]) - /\ - (and([a_ExplicitWithFlags_Flags[q35] > 0 /\ a_ExplicitWithFlags_Values[q35] < a_ExplicitWithFlags_Values[q39] - -> - sum([toInt(a_ExplicitWithFlags_Values[q31] = a_ExplicitWithFlags_Values[q35]) * - catchUndef(a_ExplicitWithFlags_Flags[q31], 0) - | q31 : int(1..3)]) - = - sum([toInt(b_ExplicitWithFlags_Values[q32] = a_ExplicitWithFlags_Values[q35]) * - catchUndef(b_ExplicitWithFlags_Flags[q32], 0) - | q32 : int(1..3)]) - | q35 : int(1..3)]) - /\ - and([and([b_ExplicitWithFlags_Flags[q36] > 0, - !or([a_ExplicitWithFlags_Flags[q34] > 0 /\ - a_ExplicitWithFlags_Values[q34] = b_ExplicitWithFlags_Values[q36] - | q34 : int(1..3)]), - b_ExplicitWithFlags_Values[q36] < a_ExplicitWithFlags_Values[q39]; - int(1..3)]) - -> - sum([toInt(a_ExplicitWithFlags_Values[q31] = b_ExplicitWithFlags_Values[q36]) * - catchUndef(a_ExplicitWithFlags_Flags[q31], 0) - | q31 : int(1..3)]) - = - sum([toInt(b_ExplicitWithFlags_Values[q32] = b_ExplicitWithFlags_Values[q36]) * - catchUndef(b_ExplicitWithFlags_Flags[q32], 0) - | q32 : int(1..3)]) - | q36 : int(1..3)]))) - | q39 : int(1..3)]) - \/ - or([b_ExplicitWithFlags_Flags[q40] > 0 /\ - !or([a_ExplicitWithFlags_Flags[q38] > 0 /\ a_ExplicitWithFlags_Values[q38] = b_ExplicitWithFlags_Values[q40] - | q38 : int(1..3)]) - /\ - (sum([toInt(a_ExplicitWithFlags_Values[q29] = b_ExplicitWithFlags_Values[q40]) * - catchUndef(a_ExplicitWithFlags_Flags[q29], 0) - | q29 : int(1..3)]) - < - sum([toInt(b_ExplicitWithFlags_Values[q30] = b_ExplicitWithFlags_Values[q40]) * - catchUndef(b_ExplicitWithFlags_Flags[q30], 0) - | q30 : int(1..3)]) - /\ - (and([a_ExplicitWithFlags_Flags[q35] > 0 /\ a_ExplicitWithFlags_Values[q35] < b_ExplicitWithFlags_Values[q40] - -> - sum([toInt(a_ExplicitWithFlags_Values[q31] = a_ExplicitWithFlags_Values[q35]) * - catchUndef(a_ExplicitWithFlags_Flags[q31], 0) - | q31 : int(1..3)]) - = - sum([toInt(b_ExplicitWithFlags_Values[q32] = a_ExplicitWithFlags_Values[q35]) * - catchUndef(b_ExplicitWithFlags_Flags[q32], 0) - | q32 : int(1..3)]) - | q35 : int(1..3)]) - /\ - and([and([b_ExplicitWithFlags_Flags[q36] > 0, - !or([a_ExplicitWithFlags_Flags[q34] > 0 /\ - a_ExplicitWithFlags_Values[q34] = b_ExplicitWithFlags_Values[q36] - | q34 : int(1..3)]), - b_ExplicitWithFlags_Values[q36] < b_ExplicitWithFlags_Values[q40]; - int(1..3)]) - -> - sum([toInt(a_ExplicitWithFlags_Values[q31] = b_ExplicitWithFlags_Values[q36]) * - catchUndef(a_ExplicitWithFlags_Flags[q31], 0) - | q31 : int(1..3)]) - = - sum([toInt(b_ExplicitWithFlags_Values[q32] = b_ExplicitWithFlags_Values[q36]) * - catchUndef(b_ExplicitWithFlags_Flags[q32], 0) - | q32 : int(1..3)]) - | q36 : int(1..3)]))) - | q40 : int(1..3)]), - and([a_ExplicitWithFlags_Flags[q1 + 1] > 0 -> a_ExplicitWithFlags_Values[q1] < a_ExplicitWithFlags_Values[q1 + 1] - | q1 : int(1..2)]), - and([a_ExplicitWithFlags_Flags[q2] = 0 -> a_ExplicitWithFlags_Values[q2] = 1 | q2 : int(1..3)]), - and([a_ExplicitWithFlags_Flags[q3 + 1] > 0 -> a_ExplicitWithFlags_Flags[q3] > 0 | q3 : int(1..2)]), - 3 = sum([a_ExplicitWithFlags_Flags[q5] | q5 : int(1..3)]), - and([b_ExplicitWithFlags_Flags[q7 + 1] > 0 -> b_ExplicitWithFlags_Values[q7] < b_ExplicitWithFlags_Values[q7 + 1] - | q7 : int(1..2)]), - and([b_ExplicitWithFlags_Flags[q8] = 0 -> b_ExplicitWithFlags_Values[q8] = 1 | q8 : int(1..3)]), - and([b_ExplicitWithFlags_Flags[q9 + 1] > 0 -> b_ExplicitWithFlags_Flags[q9] > 0 | q9 : int(1..2)]), - 3 = sum([b_ExplicitWithFlags_Flags[q11] | q11 : int(1..3)]), - and([b_ExplicitWithRepetition_Values[q13] <= b_ExplicitWithRepetition_Values[q13 + 1] - | q13 : int(1..2), q13 + 1 <= 3]), - and([sum([toInt(b_ExplicitWithRepetition_Values[q22] = b_ExplicitWithRepetition_Values[q19]) - | q22 : int(1..3), q22 <= 3]) - = - sum([toInt(b_ExplicitWithFlags_Values[q20] = b_ExplicitWithRepetition_Values[q19]) * - catchUndef(b_ExplicitWithFlags_Flags[q20], 0) - | q20 : int(1..3)]) - | q19 : int(1..3), q19 <= 3]), - and([b_ExplicitWithFlags_Flags[q23] > 0 -> - sum([toInt(b_ExplicitWithRepetition_Values[q26] = b_ExplicitWithFlags_Values[q23]) - | q26 : int(1..3), q26 <= 3]) - = - sum([toInt(b_ExplicitWithFlags_Values[q24] = b_ExplicitWithFlags_Values[q23]) * - catchUndef(b_ExplicitWithFlags_Flags[q24], 0) - | q24 : int(1..3)]) - | q23 : int(1..3)]) - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_1_3-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_1_3-solution000001.solution deleted file mode 100644 index 5e2caa751c..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_1_3-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 2, 2) -letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_1_3-solution000002.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_1_3-solution000002.solution deleted file mode 100644 index 1b4b5b08a6..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_1_3-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 2, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_1_3-solution000003.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_1_3-solution000003.solution deleted file mode 100644 index 621d5f6edc..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_1_3-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 1, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_1_3-solution000004.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_1_3-solution000004.solution deleted file mode 100644 index 15472caf03..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_1_3-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 2, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_1_3-solution000005.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_1_3-solution000005.solution deleted file mode 100644 index ff56905e23..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_1_3-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_1_3-solution000006.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_1_3-solution000006.solution deleted file mode 100644 index d56a0bbcdc..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_1_3-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_1_3.eprime b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_1_3.eprime deleted file mode 100644 index 82b5ff5883..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_1_3.eprime +++ /dev/null @@ -1,110 +0,0 @@ -language ESSENCE' 1.0 - -find a_ExplicitWithFlags_Flags: matrix indexed by [int(1..3)] of int(0..3) -find a_ExplicitWithFlags_Values: matrix indexed by [int(1..3)] of int(1..2) -find b_ExplicitWithFlags_Flags: matrix indexed by [int(1..3)] of int(0..3) -find b_ExplicitWithFlags_Values: matrix indexed by [int(1..3)] of int(1..2) -find b_MOccurrence: matrix indexed by [int(1..2)] of int(0..3) -branching on - [a_ExplicitWithFlags_Flags, a_ExplicitWithFlags_Values, b_MOccurrence, b_ExplicitWithFlags_Flags, - b_ExplicitWithFlags_Values] -such that - or([a_ExplicitWithFlags_Flags[q31] > 0 /\ - (sum([toInt(a_ExplicitWithFlags_Values[q21] = a_ExplicitWithFlags_Values[q31]) * - catchUndef(a_ExplicitWithFlags_Flags[q21], 0) - | q21 : int(1..3)]) - < - sum([toInt(b_ExplicitWithFlags_Values[q22] = a_ExplicitWithFlags_Values[q31]) * - catchUndef(b_ExplicitWithFlags_Flags[q22], 0) - | q22 : int(1..3)]) - /\ - (and([a_ExplicitWithFlags_Flags[q27] > 0 /\ a_ExplicitWithFlags_Values[q27] < a_ExplicitWithFlags_Values[q31] - -> - sum([toInt(a_ExplicitWithFlags_Values[q23] = a_ExplicitWithFlags_Values[q27]) * - catchUndef(a_ExplicitWithFlags_Flags[q23], 0) - | q23 : int(1..3)]) - = - sum([toInt(b_ExplicitWithFlags_Values[q24] = a_ExplicitWithFlags_Values[q27]) * - catchUndef(b_ExplicitWithFlags_Flags[q24], 0) - | q24 : int(1..3)]) - | q27 : int(1..3)]) - /\ - and([and([b_ExplicitWithFlags_Flags[q28] > 0, - !or([a_ExplicitWithFlags_Flags[q26] > 0 /\ - a_ExplicitWithFlags_Values[q26] = b_ExplicitWithFlags_Values[q28] - | q26 : int(1..3)]), - b_ExplicitWithFlags_Values[q28] < a_ExplicitWithFlags_Values[q31]; - int(1..3)]) - -> - sum([toInt(a_ExplicitWithFlags_Values[q23] = b_ExplicitWithFlags_Values[q28]) * - catchUndef(a_ExplicitWithFlags_Flags[q23], 0) - | q23 : int(1..3)]) - = - sum([toInt(b_ExplicitWithFlags_Values[q24] = b_ExplicitWithFlags_Values[q28]) * - catchUndef(b_ExplicitWithFlags_Flags[q24], 0) - | q24 : int(1..3)]) - | q28 : int(1..3)]))) - | q31 : int(1..3)]) - \/ - or([b_ExplicitWithFlags_Flags[q32] > 0 /\ - !or([a_ExplicitWithFlags_Flags[q30] > 0 /\ a_ExplicitWithFlags_Values[q30] = b_ExplicitWithFlags_Values[q32] - | q30 : int(1..3)]) - /\ - (sum([toInt(a_ExplicitWithFlags_Values[q21] = b_ExplicitWithFlags_Values[q32]) * - catchUndef(a_ExplicitWithFlags_Flags[q21], 0) - | q21 : int(1..3)]) - < - sum([toInt(b_ExplicitWithFlags_Values[q22] = b_ExplicitWithFlags_Values[q32]) * - catchUndef(b_ExplicitWithFlags_Flags[q22], 0) - | q22 : int(1..3)]) - /\ - (and([a_ExplicitWithFlags_Flags[q27] > 0 /\ a_ExplicitWithFlags_Values[q27] < b_ExplicitWithFlags_Values[q32] - -> - sum([toInt(a_ExplicitWithFlags_Values[q23] = a_ExplicitWithFlags_Values[q27]) * - catchUndef(a_ExplicitWithFlags_Flags[q23], 0) - | q23 : int(1..3)]) - = - sum([toInt(b_ExplicitWithFlags_Values[q24] = a_ExplicitWithFlags_Values[q27]) * - catchUndef(b_ExplicitWithFlags_Flags[q24], 0) - | q24 : int(1..3)]) - | q27 : int(1..3)]) - /\ - and([and([b_ExplicitWithFlags_Flags[q28] > 0, - !or([a_ExplicitWithFlags_Flags[q26] > 0 /\ - a_ExplicitWithFlags_Values[q26] = b_ExplicitWithFlags_Values[q28] - | q26 : int(1..3)]), - b_ExplicitWithFlags_Values[q28] < b_ExplicitWithFlags_Values[q32]; - int(1..3)]) - -> - sum([toInt(a_ExplicitWithFlags_Values[q23] = b_ExplicitWithFlags_Values[q28]) * - catchUndef(a_ExplicitWithFlags_Flags[q23], 0) - | q23 : int(1..3)]) - = - sum([toInt(b_ExplicitWithFlags_Values[q24] = b_ExplicitWithFlags_Values[q28]) * - catchUndef(b_ExplicitWithFlags_Flags[q24], 0) - | q24 : int(1..3)]) - | q28 : int(1..3)]))) - | q32 : int(1..3)]), - and([a_ExplicitWithFlags_Flags[q1 + 1] > 0 -> a_ExplicitWithFlags_Values[q1] < a_ExplicitWithFlags_Values[q1 + 1] - | q1 : int(1..2)]), - and([a_ExplicitWithFlags_Flags[q2] = 0 -> a_ExplicitWithFlags_Values[q2] = 1 | q2 : int(1..3)]), - and([a_ExplicitWithFlags_Flags[q3 + 1] > 0 -> a_ExplicitWithFlags_Flags[q3] > 0 | q3 : int(1..2)]), - 3 = sum([a_ExplicitWithFlags_Flags[q5] | q5 : int(1..3)]), - and([b_ExplicitWithFlags_Flags[q7 + 1] > 0 -> b_ExplicitWithFlags_Values[q7] < b_ExplicitWithFlags_Values[q7 + 1] - | q7 : int(1..2)]), - and([b_ExplicitWithFlags_Flags[q8] = 0 -> b_ExplicitWithFlags_Values[q8] = 1 | q8 : int(1..3)]), - and([b_ExplicitWithFlags_Flags[q9 + 1] > 0 -> b_ExplicitWithFlags_Flags[q9] > 0 | q9 : int(1..2)]), - 3 = sum([b_ExplicitWithFlags_Flags[q11] | q11 : int(1..3)]), - 3 = sum([b_MOccurrence[q13] | q13 : int(1..2)]), - and([b_MOccurrence[q15] > 0 -> - b_MOccurrence[q15] = - sum([toInt(b_ExplicitWithFlags_Values[q16] = q15) * catchUndef(b_ExplicitWithFlags_Flags[q16], 0) - | q16 : int(1..3)]) - | q15 : int(1..2)]), - and([b_ExplicitWithFlags_Flags[q17] > 0 -> - b_MOccurrence[b_ExplicitWithFlags_Values[q17]] = - sum([toInt(b_ExplicitWithFlags_Values[q18] = b_ExplicitWithFlags_Values[q17]) * - catchUndef(b_ExplicitWithFlags_Flags[q18], 0) - | q18 : int(1..3)]) - | q17 : int(1..3)]) - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_2_1-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_2_1-solution000001.solution deleted file mode 100644 index 621d5f6edc..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_2_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 1, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_2_1-solution000002.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_2_1-solution000002.solution deleted file mode 100644 index 5e2caa751c..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_2_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 2, 2) -letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_2_1-solution000003.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_2_1-solution000003.solution deleted file mode 100644 index 1b4b5b08a6..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_2_1-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 2, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_2_1-solution000004.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_2_1-solution000004.solution deleted file mode 100644 index 15472caf03..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_2_1-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 2, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_2_1-solution000005.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_2_1-solution000005.solution deleted file mode 100644 index ff56905e23..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_2_1-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_2_1-solution000006.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_2_1-solution000006.solution deleted file mode 100644 index d56a0bbcdc..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_2_1-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_2_1.eprime b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_2_1.eprime deleted file mode 100644 index 206e9c841b..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_2_1.eprime +++ /dev/null @@ -1,116 +0,0 @@ -language ESSENCE' 1.0 - -find a_ExplicitWithFlags_Flags: matrix indexed by [int(1..3)] of int(0..3) -find a_ExplicitWithFlags_Values: matrix indexed by [int(1..3)] of int(1..2) -find a_ExplicitWithRepetition_Flag: int(3) -find a_ExplicitWithRepetition_Values: matrix indexed by [int(1..3)] of int(1..2) -find b_ExplicitWithFlags_Flags: matrix indexed by [int(1..3)] of int(0..3) -find b_ExplicitWithFlags_Values: matrix indexed by [int(1..3)] of int(1..2) -branching on - [a_ExplicitWithRepetition_Flag, a_ExplicitWithRepetition_Values, a_ExplicitWithFlags_Flags, - a_ExplicitWithFlags_Values, b_ExplicitWithFlags_Flags, b_ExplicitWithFlags_Values] -such that - or([a_ExplicitWithFlags_Flags[q39] > 0 /\ - (sum([toInt(a_ExplicitWithFlags_Values[q29] = a_ExplicitWithFlags_Values[q39]) * - catchUndef(a_ExplicitWithFlags_Flags[q29], 0) - | q29 : int(1..3)]) - < - sum([toInt(b_ExplicitWithFlags_Values[q30] = a_ExplicitWithFlags_Values[q39]) * - catchUndef(b_ExplicitWithFlags_Flags[q30], 0) - | q30 : int(1..3)]) - /\ - (and([a_ExplicitWithFlags_Flags[q35] > 0 /\ a_ExplicitWithFlags_Values[q35] < a_ExplicitWithFlags_Values[q39] - -> - sum([toInt(a_ExplicitWithFlags_Values[q31] = a_ExplicitWithFlags_Values[q35]) * - catchUndef(a_ExplicitWithFlags_Flags[q31], 0) - | q31 : int(1..3)]) - = - sum([toInt(b_ExplicitWithFlags_Values[q32] = a_ExplicitWithFlags_Values[q35]) * - catchUndef(b_ExplicitWithFlags_Flags[q32], 0) - | q32 : int(1..3)]) - | q35 : int(1..3)]) - /\ - and([and([b_ExplicitWithFlags_Flags[q36] > 0, - !or([a_ExplicitWithFlags_Flags[q34] > 0 /\ - a_ExplicitWithFlags_Values[q34] = b_ExplicitWithFlags_Values[q36] - | q34 : int(1..3)]), - b_ExplicitWithFlags_Values[q36] < a_ExplicitWithFlags_Values[q39]; - int(1..3)]) - -> - sum([toInt(a_ExplicitWithFlags_Values[q31] = b_ExplicitWithFlags_Values[q36]) * - catchUndef(a_ExplicitWithFlags_Flags[q31], 0) - | q31 : int(1..3)]) - = - sum([toInt(b_ExplicitWithFlags_Values[q32] = b_ExplicitWithFlags_Values[q36]) * - catchUndef(b_ExplicitWithFlags_Flags[q32], 0) - | q32 : int(1..3)]) - | q36 : int(1..3)]))) - | q39 : int(1..3)]) - \/ - or([b_ExplicitWithFlags_Flags[q40] > 0 /\ - !or([a_ExplicitWithFlags_Flags[q38] > 0 /\ a_ExplicitWithFlags_Values[q38] = b_ExplicitWithFlags_Values[q40] - | q38 : int(1..3)]) - /\ - (sum([toInt(a_ExplicitWithFlags_Values[q29] = b_ExplicitWithFlags_Values[q40]) * - catchUndef(a_ExplicitWithFlags_Flags[q29], 0) - | q29 : int(1..3)]) - < - sum([toInt(b_ExplicitWithFlags_Values[q30] = b_ExplicitWithFlags_Values[q40]) * - catchUndef(b_ExplicitWithFlags_Flags[q30], 0) - | q30 : int(1..3)]) - /\ - (and([a_ExplicitWithFlags_Flags[q35] > 0 /\ a_ExplicitWithFlags_Values[q35] < b_ExplicitWithFlags_Values[q40] - -> - sum([toInt(a_ExplicitWithFlags_Values[q31] = a_ExplicitWithFlags_Values[q35]) * - catchUndef(a_ExplicitWithFlags_Flags[q31], 0) - | q31 : int(1..3)]) - = - sum([toInt(b_ExplicitWithFlags_Values[q32] = a_ExplicitWithFlags_Values[q35]) * - catchUndef(b_ExplicitWithFlags_Flags[q32], 0) - | q32 : int(1..3)]) - | q35 : int(1..3)]) - /\ - and([and([b_ExplicitWithFlags_Flags[q36] > 0, - !or([a_ExplicitWithFlags_Flags[q34] > 0 /\ - a_ExplicitWithFlags_Values[q34] = b_ExplicitWithFlags_Values[q36] - | q34 : int(1..3)]), - b_ExplicitWithFlags_Values[q36] < b_ExplicitWithFlags_Values[q40]; - int(1..3)]) - -> - sum([toInt(a_ExplicitWithFlags_Values[q31] = b_ExplicitWithFlags_Values[q36]) * - catchUndef(a_ExplicitWithFlags_Flags[q31], 0) - | q31 : int(1..3)]) - = - sum([toInt(b_ExplicitWithFlags_Values[q32] = b_ExplicitWithFlags_Values[q36]) * - catchUndef(b_ExplicitWithFlags_Flags[q32], 0) - | q32 : int(1..3)]) - | q36 : int(1..3)]))) - | q40 : int(1..3)]), - and([a_ExplicitWithFlags_Flags[q1 + 1] > 0 -> a_ExplicitWithFlags_Values[q1] < a_ExplicitWithFlags_Values[q1 + 1] - | q1 : int(1..2)]), - and([a_ExplicitWithFlags_Flags[q2] = 0 -> a_ExplicitWithFlags_Values[q2] = 1 | q2 : int(1..3)]), - and([a_ExplicitWithFlags_Flags[q3 + 1] > 0 -> a_ExplicitWithFlags_Flags[q3] > 0 | q3 : int(1..2)]), - 3 = sum([a_ExplicitWithFlags_Flags[q5] | q5 : int(1..3)]), - and([b_ExplicitWithFlags_Flags[q7 + 1] > 0 -> b_ExplicitWithFlags_Values[q7] < b_ExplicitWithFlags_Values[q7 + 1] - | q7 : int(1..2)]), - and([b_ExplicitWithFlags_Flags[q8] = 0 -> b_ExplicitWithFlags_Values[q8] = 1 | q8 : int(1..3)]), - and([b_ExplicitWithFlags_Flags[q9 + 1] > 0 -> b_ExplicitWithFlags_Flags[q9] > 0 | q9 : int(1..2)]), - 3 = sum([b_ExplicitWithFlags_Flags[q11] | q11 : int(1..3)]), - and([a_ExplicitWithRepetition_Values[q13] <= a_ExplicitWithRepetition_Values[q13 + 1] - | q13 : int(1..2), q13 + 1 <= 3]), - and([sum([toInt(a_ExplicitWithRepetition_Values[q22] = a_ExplicitWithRepetition_Values[q19]) - | q22 : int(1..3), q22 <= 3]) - = - sum([toInt(a_ExplicitWithFlags_Values[q20] = a_ExplicitWithRepetition_Values[q19]) * - catchUndef(a_ExplicitWithFlags_Flags[q20], 0) - | q20 : int(1..3)]) - | q19 : int(1..3), q19 <= 3]), - and([a_ExplicitWithFlags_Flags[q23] > 0 -> - sum([toInt(a_ExplicitWithRepetition_Values[q26] = a_ExplicitWithFlags_Values[q23]) - | q26 : int(1..3), q26 <= 3]) - = - sum([toInt(a_ExplicitWithFlags_Values[q24] = a_ExplicitWithFlags_Values[q23]) * - catchUndef(a_ExplicitWithFlags_Flags[q24], 0) - | q24 : int(1..3)]) - | q23 : int(1..3)]) - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_2_2-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_2_2-solution000001.solution deleted file mode 100644 index 621d5f6edc..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_2_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 1, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_2_2-solution000002.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_2_2-solution000002.solution deleted file mode 100644 index 1b4b5b08a6..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_2_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 2, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_2_2-solution000003.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_2_2-solution000003.solution deleted file mode 100644 index 5e2caa751c..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_2_2-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 2, 2) -letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_2_2-solution000004.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_2_2-solution000004.solution deleted file mode 100644 index d56a0bbcdc..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_2_2-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_2_2-solution000005.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_2_2-solution000005.solution deleted file mode 100644 index ff56905e23..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_2_2-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_2_2-solution000006.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_2_2-solution000006.solution deleted file mode 100644 index 15472caf03..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_2_2-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 2, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_2_2.eprime b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_2_2.eprime deleted file mode 100644 index a96b6bd0a8..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_2_2.eprime +++ /dev/null @@ -1,136 +0,0 @@ -language ESSENCE' 1.0 - -find a_ExplicitWithFlags_Flags: matrix indexed by [int(1..3)] of int(0..3) -find a_ExplicitWithFlags_Values: matrix indexed by [int(1..3)] of int(1..2) -find a_ExplicitWithRepetition_Flag: int(3) -find a_ExplicitWithRepetition_Values: matrix indexed by [int(1..3)] of int(1..2) -find b_ExplicitWithFlags_Flags: matrix indexed by [int(1..3)] of int(0..3) -find b_ExplicitWithFlags_Values: matrix indexed by [int(1..3)] of int(1..2) -find b_ExplicitWithRepetition_Flag: int(3) -find b_ExplicitWithRepetition_Values: matrix indexed by [int(1..3)] of int(1..2) -branching on - [a_ExplicitWithRepetition_Flag, a_ExplicitWithRepetition_Values, a_ExplicitWithFlags_Flags, - a_ExplicitWithFlags_Values, b_ExplicitWithRepetition_Flag, b_ExplicitWithRepetition_Values, - b_ExplicitWithFlags_Flags, b_ExplicitWithFlags_Values] -such that - or([a_ExplicitWithFlags_Flags[q53] > 0 /\ - (sum([toInt(a_ExplicitWithFlags_Values[q43] = a_ExplicitWithFlags_Values[q53]) * - catchUndef(a_ExplicitWithFlags_Flags[q43], 0) - | q43 : int(1..3)]) - < - sum([toInt(b_ExplicitWithFlags_Values[q44] = a_ExplicitWithFlags_Values[q53]) * - catchUndef(b_ExplicitWithFlags_Flags[q44], 0) - | q44 : int(1..3)]) - /\ - (and([a_ExplicitWithFlags_Flags[q49] > 0 /\ a_ExplicitWithFlags_Values[q49] < a_ExplicitWithFlags_Values[q53] - -> - sum([toInt(a_ExplicitWithFlags_Values[q45] = a_ExplicitWithFlags_Values[q49]) * - catchUndef(a_ExplicitWithFlags_Flags[q45], 0) - | q45 : int(1..3)]) - = - sum([toInt(b_ExplicitWithFlags_Values[q46] = a_ExplicitWithFlags_Values[q49]) * - catchUndef(b_ExplicitWithFlags_Flags[q46], 0) - | q46 : int(1..3)]) - | q49 : int(1..3)]) - /\ - and([and([b_ExplicitWithFlags_Flags[q50] > 0, - !or([a_ExplicitWithFlags_Flags[q48] > 0 /\ - a_ExplicitWithFlags_Values[q48] = b_ExplicitWithFlags_Values[q50] - | q48 : int(1..3)]), - b_ExplicitWithFlags_Values[q50] < a_ExplicitWithFlags_Values[q53]; - int(1..3)]) - -> - sum([toInt(a_ExplicitWithFlags_Values[q45] = b_ExplicitWithFlags_Values[q50]) * - catchUndef(a_ExplicitWithFlags_Flags[q45], 0) - | q45 : int(1..3)]) - = - sum([toInt(b_ExplicitWithFlags_Values[q46] = b_ExplicitWithFlags_Values[q50]) * - catchUndef(b_ExplicitWithFlags_Flags[q46], 0) - | q46 : int(1..3)]) - | q50 : int(1..3)]))) - | q53 : int(1..3)]) - \/ - or([b_ExplicitWithFlags_Flags[q54] > 0 /\ - !or([a_ExplicitWithFlags_Flags[q52] > 0 /\ a_ExplicitWithFlags_Values[q52] = b_ExplicitWithFlags_Values[q54] - | q52 : int(1..3)]) - /\ - (sum([toInt(a_ExplicitWithFlags_Values[q43] = b_ExplicitWithFlags_Values[q54]) * - catchUndef(a_ExplicitWithFlags_Flags[q43], 0) - | q43 : int(1..3)]) - < - sum([toInt(b_ExplicitWithFlags_Values[q44] = b_ExplicitWithFlags_Values[q54]) * - catchUndef(b_ExplicitWithFlags_Flags[q44], 0) - | q44 : int(1..3)]) - /\ - (and([a_ExplicitWithFlags_Flags[q49] > 0 /\ a_ExplicitWithFlags_Values[q49] < b_ExplicitWithFlags_Values[q54] - -> - sum([toInt(a_ExplicitWithFlags_Values[q45] = a_ExplicitWithFlags_Values[q49]) * - catchUndef(a_ExplicitWithFlags_Flags[q45], 0) - | q45 : int(1..3)]) - = - sum([toInt(b_ExplicitWithFlags_Values[q46] = a_ExplicitWithFlags_Values[q49]) * - catchUndef(b_ExplicitWithFlags_Flags[q46], 0) - | q46 : int(1..3)]) - | q49 : int(1..3)]) - /\ - and([and([b_ExplicitWithFlags_Flags[q50] > 0, - !or([a_ExplicitWithFlags_Flags[q48] > 0 /\ - a_ExplicitWithFlags_Values[q48] = b_ExplicitWithFlags_Values[q50] - | q48 : int(1..3)]), - b_ExplicitWithFlags_Values[q50] < b_ExplicitWithFlags_Values[q54]; - int(1..3)]) - -> - sum([toInt(a_ExplicitWithFlags_Values[q45] = b_ExplicitWithFlags_Values[q50]) * - catchUndef(a_ExplicitWithFlags_Flags[q45], 0) - | q45 : int(1..3)]) - = - sum([toInt(b_ExplicitWithFlags_Values[q46] = b_ExplicitWithFlags_Values[q50]) * - catchUndef(b_ExplicitWithFlags_Flags[q46], 0) - | q46 : int(1..3)]) - | q50 : int(1..3)]))) - | q54 : int(1..3)]), - and([a_ExplicitWithFlags_Flags[q1 + 1] > 0 -> a_ExplicitWithFlags_Values[q1] < a_ExplicitWithFlags_Values[q1 + 1] - | q1 : int(1..2)]), - and([a_ExplicitWithFlags_Flags[q2] = 0 -> a_ExplicitWithFlags_Values[q2] = 1 | q2 : int(1..3)]), - and([a_ExplicitWithFlags_Flags[q3 + 1] > 0 -> a_ExplicitWithFlags_Flags[q3] > 0 | q3 : int(1..2)]), - 3 = sum([a_ExplicitWithFlags_Flags[q5] | q5 : int(1..3)]), - and([b_ExplicitWithFlags_Flags[q7 + 1] > 0 -> b_ExplicitWithFlags_Values[q7] < b_ExplicitWithFlags_Values[q7 + 1] - | q7 : int(1..2)]), - and([b_ExplicitWithFlags_Flags[q8] = 0 -> b_ExplicitWithFlags_Values[q8] = 1 | q8 : int(1..3)]), - and([b_ExplicitWithFlags_Flags[q9 + 1] > 0 -> b_ExplicitWithFlags_Flags[q9] > 0 | q9 : int(1..2)]), - 3 = sum([b_ExplicitWithFlags_Flags[q11] | q11 : int(1..3)]), - and([a_ExplicitWithRepetition_Values[q13] <= a_ExplicitWithRepetition_Values[q13 + 1] - | q13 : int(1..2), q13 + 1 <= 3]), - and([sum([toInt(a_ExplicitWithRepetition_Values[q22] = a_ExplicitWithRepetition_Values[q19]) - | q22 : int(1..3), q22 <= 3]) - = - sum([toInt(a_ExplicitWithFlags_Values[q20] = a_ExplicitWithRepetition_Values[q19]) * - catchUndef(a_ExplicitWithFlags_Flags[q20], 0) - | q20 : int(1..3)]) - | q19 : int(1..3), q19 <= 3]), - and([a_ExplicitWithFlags_Flags[q23] > 0 -> - sum([toInt(a_ExplicitWithRepetition_Values[q26] = a_ExplicitWithFlags_Values[q23]) - | q26 : int(1..3), q26 <= 3]) - = - sum([toInt(a_ExplicitWithFlags_Values[q24] = a_ExplicitWithFlags_Values[q23]) * - catchUndef(a_ExplicitWithFlags_Flags[q24], 0) - | q24 : int(1..3)]) - | q23 : int(1..3)]), - and([b_ExplicitWithRepetition_Values[q27] <= b_ExplicitWithRepetition_Values[q27 + 1] - | q27 : int(1..2), q27 + 1 <= 3]), - and([sum([toInt(b_ExplicitWithRepetition_Values[q36] = b_ExplicitWithRepetition_Values[q33]) - | q36 : int(1..3), q36 <= 3]) - = - sum([toInt(b_ExplicitWithFlags_Values[q34] = b_ExplicitWithRepetition_Values[q33]) * - catchUndef(b_ExplicitWithFlags_Flags[q34], 0) - | q34 : int(1..3)]) - | q33 : int(1..3), q33 <= 3]), - and([b_ExplicitWithFlags_Flags[q37] > 0 -> - sum([toInt(b_ExplicitWithRepetition_Values[q40] = b_ExplicitWithFlags_Values[q37]) - | q40 : int(1..3), q40 <= 3]) - = - sum([toInt(b_ExplicitWithFlags_Values[q38] = b_ExplicitWithFlags_Values[q37]) * - catchUndef(b_ExplicitWithFlags_Flags[q38], 0) - | q38 : int(1..3)]) - | q37 : int(1..3)]) - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_2_3-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_2_3-solution000001.solution deleted file mode 100644 index 621d5f6edc..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_2_3-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 1, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_2_3-solution000002.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_2_3-solution000002.solution deleted file mode 100644 index 5e2caa751c..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_2_3-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 2, 2) -letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_2_3-solution000003.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_2_3-solution000003.solution deleted file mode 100644 index 1b4b5b08a6..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_2_3-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 2, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_2_3-solution000004.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_2_3-solution000004.solution deleted file mode 100644 index 15472caf03..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_2_3-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 2, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_2_3-solution000005.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_2_3-solution000005.solution deleted file mode 100644 index ff56905e23..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_2_3-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_2_3-solution000006.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_2_3-solution000006.solution deleted file mode 100644 index d56a0bbcdc..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_2_3-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_2_3.eprime b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_2_3.eprime deleted file mode 100644 index f82123c4e3..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_2_3.eprime +++ /dev/null @@ -1,129 +0,0 @@ -language ESSENCE' 1.0 - -find a_ExplicitWithFlags_Flags: matrix indexed by [int(1..3)] of int(0..3) -find a_ExplicitWithFlags_Values: matrix indexed by [int(1..3)] of int(1..2) -find a_ExplicitWithRepetition_Flag: int(3) -find a_ExplicitWithRepetition_Values: matrix indexed by [int(1..3)] of int(1..2) -find b_ExplicitWithFlags_Flags: matrix indexed by [int(1..3)] of int(0..3) -find b_ExplicitWithFlags_Values: matrix indexed by [int(1..3)] of int(1..2) -find b_MOccurrence: matrix indexed by [int(1..2)] of int(0..3) -branching on - [a_ExplicitWithRepetition_Flag, a_ExplicitWithRepetition_Values, a_ExplicitWithFlags_Flags, - a_ExplicitWithFlags_Values, b_MOccurrence, b_ExplicitWithFlags_Flags, b_ExplicitWithFlags_Values] -such that - or([a_ExplicitWithFlags_Flags[q45] > 0 /\ - (sum([toInt(a_ExplicitWithFlags_Values[q35] = a_ExplicitWithFlags_Values[q45]) * - catchUndef(a_ExplicitWithFlags_Flags[q35], 0) - | q35 : int(1..3)]) - < - sum([toInt(b_ExplicitWithFlags_Values[q36] = a_ExplicitWithFlags_Values[q45]) * - catchUndef(b_ExplicitWithFlags_Flags[q36], 0) - | q36 : int(1..3)]) - /\ - (and([a_ExplicitWithFlags_Flags[q41] > 0 /\ a_ExplicitWithFlags_Values[q41] < a_ExplicitWithFlags_Values[q45] - -> - sum([toInt(a_ExplicitWithFlags_Values[q37] = a_ExplicitWithFlags_Values[q41]) * - catchUndef(a_ExplicitWithFlags_Flags[q37], 0) - | q37 : int(1..3)]) - = - sum([toInt(b_ExplicitWithFlags_Values[q38] = a_ExplicitWithFlags_Values[q41]) * - catchUndef(b_ExplicitWithFlags_Flags[q38], 0) - | q38 : int(1..3)]) - | q41 : int(1..3)]) - /\ - and([and([b_ExplicitWithFlags_Flags[q42] > 0, - !or([a_ExplicitWithFlags_Flags[q40] > 0 /\ - a_ExplicitWithFlags_Values[q40] = b_ExplicitWithFlags_Values[q42] - | q40 : int(1..3)]), - b_ExplicitWithFlags_Values[q42] < a_ExplicitWithFlags_Values[q45]; - int(1..3)]) - -> - sum([toInt(a_ExplicitWithFlags_Values[q37] = b_ExplicitWithFlags_Values[q42]) * - catchUndef(a_ExplicitWithFlags_Flags[q37], 0) - | q37 : int(1..3)]) - = - sum([toInt(b_ExplicitWithFlags_Values[q38] = b_ExplicitWithFlags_Values[q42]) * - catchUndef(b_ExplicitWithFlags_Flags[q38], 0) - | q38 : int(1..3)]) - | q42 : int(1..3)]))) - | q45 : int(1..3)]) - \/ - or([b_ExplicitWithFlags_Flags[q46] > 0 /\ - !or([a_ExplicitWithFlags_Flags[q44] > 0 /\ a_ExplicitWithFlags_Values[q44] = b_ExplicitWithFlags_Values[q46] - | q44 : int(1..3)]) - /\ - (sum([toInt(a_ExplicitWithFlags_Values[q35] = b_ExplicitWithFlags_Values[q46]) * - catchUndef(a_ExplicitWithFlags_Flags[q35], 0) - | q35 : int(1..3)]) - < - sum([toInt(b_ExplicitWithFlags_Values[q36] = b_ExplicitWithFlags_Values[q46]) * - catchUndef(b_ExplicitWithFlags_Flags[q36], 0) - | q36 : int(1..3)]) - /\ - (and([a_ExplicitWithFlags_Flags[q41] > 0 /\ a_ExplicitWithFlags_Values[q41] < b_ExplicitWithFlags_Values[q46] - -> - sum([toInt(a_ExplicitWithFlags_Values[q37] = a_ExplicitWithFlags_Values[q41]) * - catchUndef(a_ExplicitWithFlags_Flags[q37], 0) - | q37 : int(1..3)]) - = - sum([toInt(b_ExplicitWithFlags_Values[q38] = a_ExplicitWithFlags_Values[q41]) * - catchUndef(b_ExplicitWithFlags_Flags[q38], 0) - | q38 : int(1..3)]) - | q41 : int(1..3)]) - /\ - and([and([b_ExplicitWithFlags_Flags[q42] > 0, - !or([a_ExplicitWithFlags_Flags[q40] > 0 /\ - a_ExplicitWithFlags_Values[q40] = b_ExplicitWithFlags_Values[q42] - | q40 : int(1..3)]), - b_ExplicitWithFlags_Values[q42] < b_ExplicitWithFlags_Values[q46]; - int(1..3)]) - -> - sum([toInt(a_ExplicitWithFlags_Values[q37] = b_ExplicitWithFlags_Values[q42]) * - catchUndef(a_ExplicitWithFlags_Flags[q37], 0) - | q37 : int(1..3)]) - = - sum([toInt(b_ExplicitWithFlags_Values[q38] = b_ExplicitWithFlags_Values[q42]) * - catchUndef(b_ExplicitWithFlags_Flags[q38], 0) - | q38 : int(1..3)]) - | q42 : int(1..3)]))) - | q46 : int(1..3)]), - and([a_ExplicitWithFlags_Flags[q1 + 1] > 0 -> a_ExplicitWithFlags_Values[q1] < a_ExplicitWithFlags_Values[q1 + 1] - | q1 : int(1..2)]), - and([a_ExplicitWithFlags_Flags[q2] = 0 -> a_ExplicitWithFlags_Values[q2] = 1 | q2 : int(1..3)]), - and([a_ExplicitWithFlags_Flags[q3 + 1] > 0 -> a_ExplicitWithFlags_Flags[q3] > 0 | q3 : int(1..2)]), - 3 = sum([a_ExplicitWithFlags_Flags[q5] | q5 : int(1..3)]), - and([b_ExplicitWithFlags_Flags[q7 + 1] > 0 -> b_ExplicitWithFlags_Values[q7] < b_ExplicitWithFlags_Values[q7 + 1] - | q7 : int(1..2)]), - and([b_ExplicitWithFlags_Flags[q8] = 0 -> b_ExplicitWithFlags_Values[q8] = 1 | q8 : int(1..3)]), - and([b_ExplicitWithFlags_Flags[q9 + 1] > 0 -> b_ExplicitWithFlags_Flags[q9] > 0 | q9 : int(1..2)]), - 3 = sum([b_ExplicitWithFlags_Flags[q11] | q11 : int(1..3)]), - and([a_ExplicitWithRepetition_Values[q13] <= a_ExplicitWithRepetition_Values[q13 + 1] - | q13 : int(1..2), q13 + 1 <= 3]), - and([sum([toInt(a_ExplicitWithRepetition_Values[q22] = a_ExplicitWithRepetition_Values[q19]) - | q22 : int(1..3), q22 <= 3]) - = - sum([toInt(a_ExplicitWithFlags_Values[q20] = a_ExplicitWithRepetition_Values[q19]) * - catchUndef(a_ExplicitWithFlags_Flags[q20], 0) - | q20 : int(1..3)]) - | q19 : int(1..3), q19 <= 3]), - and([a_ExplicitWithFlags_Flags[q23] > 0 -> - sum([toInt(a_ExplicitWithRepetition_Values[q26] = a_ExplicitWithFlags_Values[q23]) - | q26 : int(1..3), q26 <= 3]) - = - sum([toInt(a_ExplicitWithFlags_Values[q24] = a_ExplicitWithFlags_Values[q23]) * - catchUndef(a_ExplicitWithFlags_Flags[q24], 0) - | q24 : int(1..3)]) - | q23 : int(1..3)]), - 3 = sum([b_MOccurrence[q27] | q27 : int(1..2)]), - and([b_MOccurrence[q29] > 0 -> - b_MOccurrence[q29] = - sum([toInt(b_ExplicitWithFlags_Values[q30] = q29) * catchUndef(b_ExplicitWithFlags_Flags[q30], 0) - | q30 : int(1..3)]) - | q29 : int(1..2)]), - and([b_ExplicitWithFlags_Flags[q31] > 0 -> - b_MOccurrence[b_ExplicitWithFlags_Values[q31]] = - sum([toInt(b_ExplicitWithFlags_Values[q32] = b_ExplicitWithFlags_Values[q31]) * - catchUndef(b_ExplicitWithFlags_Flags[q32], 0) - | q32 : int(1..3)]) - | q31 : int(1..3)]) - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_3_1-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_3_1-solution000001.solution deleted file mode 100644 index 15472caf03..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_3_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 2, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_3_1-solution000002.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_3_1-solution000002.solution deleted file mode 100644 index ff56905e23..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_3_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_3_1-solution000003.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_3_1-solution000003.solution deleted file mode 100644 index d56a0bbcdc..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_3_1-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_3_1-solution000004.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_3_1-solution000004.solution deleted file mode 100644 index 5e2caa751c..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_3_1-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 2, 2) -letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_3_1-solution000005.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_3_1-solution000005.solution deleted file mode 100644 index 1b4b5b08a6..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_3_1-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 2, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_3_1-solution000006.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_3_1-solution000006.solution deleted file mode 100644 index 621d5f6edc..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_3_1-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 1, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_3_1.eprime b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_3_1.eprime deleted file mode 100644 index 070e70fc88..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_3_1.eprime +++ /dev/null @@ -1,110 +0,0 @@ -language ESSENCE' 1.0 - -find a_ExplicitWithFlags_Flags: matrix indexed by [int(1..3)] of int(0..3) -find a_ExplicitWithFlags_Values: matrix indexed by [int(1..3)] of int(1..2) -find a_MOccurrence: matrix indexed by [int(1..2)] of int(0..3) -find b_ExplicitWithFlags_Flags: matrix indexed by [int(1..3)] of int(0..3) -find b_ExplicitWithFlags_Values: matrix indexed by [int(1..3)] of int(1..2) -branching on - [a_MOccurrence, a_ExplicitWithFlags_Flags, a_ExplicitWithFlags_Values, b_ExplicitWithFlags_Flags, - b_ExplicitWithFlags_Values] -such that - or([a_ExplicitWithFlags_Flags[q31] > 0 /\ - (sum([toInt(a_ExplicitWithFlags_Values[q21] = a_ExplicitWithFlags_Values[q31]) * - catchUndef(a_ExplicitWithFlags_Flags[q21], 0) - | q21 : int(1..3)]) - < - sum([toInt(b_ExplicitWithFlags_Values[q22] = a_ExplicitWithFlags_Values[q31]) * - catchUndef(b_ExplicitWithFlags_Flags[q22], 0) - | q22 : int(1..3)]) - /\ - (and([a_ExplicitWithFlags_Flags[q27] > 0 /\ a_ExplicitWithFlags_Values[q27] < a_ExplicitWithFlags_Values[q31] - -> - sum([toInt(a_ExplicitWithFlags_Values[q23] = a_ExplicitWithFlags_Values[q27]) * - catchUndef(a_ExplicitWithFlags_Flags[q23], 0) - | q23 : int(1..3)]) - = - sum([toInt(b_ExplicitWithFlags_Values[q24] = a_ExplicitWithFlags_Values[q27]) * - catchUndef(b_ExplicitWithFlags_Flags[q24], 0) - | q24 : int(1..3)]) - | q27 : int(1..3)]) - /\ - and([and([b_ExplicitWithFlags_Flags[q28] > 0, - !or([a_ExplicitWithFlags_Flags[q26] > 0 /\ - a_ExplicitWithFlags_Values[q26] = b_ExplicitWithFlags_Values[q28] - | q26 : int(1..3)]), - b_ExplicitWithFlags_Values[q28] < a_ExplicitWithFlags_Values[q31]; - int(1..3)]) - -> - sum([toInt(a_ExplicitWithFlags_Values[q23] = b_ExplicitWithFlags_Values[q28]) * - catchUndef(a_ExplicitWithFlags_Flags[q23], 0) - | q23 : int(1..3)]) - = - sum([toInt(b_ExplicitWithFlags_Values[q24] = b_ExplicitWithFlags_Values[q28]) * - catchUndef(b_ExplicitWithFlags_Flags[q24], 0) - | q24 : int(1..3)]) - | q28 : int(1..3)]))) - | q31 : int(1..3)]) - \/ - or([b_ExplicitWithFlags_Flags[q32] > 0 /\ - !or([a_ExplicitWithFlags_Flags[q30] > 0 /\ a_ExplicitWithFlags_Values[q30] = b_ExplicitWithFlags_Values[q32] - | q30 : int(1..3)]) - /\ - (sum([toInt(a_ExplicitWithFlags_Values[q21] = b_ExplicitWithFlags_Values[q32]) * - catchUndef(a_ExplicitWithFlags_Flags[q21], 0) - | q21 : int(1..3)]) - < - sum([toInt(b_ExplicitWithFlags_Values[q22] = b_ExplicitWithFlags_Values[q32]) * - catchUndef(b_ExplicitWithFlags_Flags[q22], 0) - | q22 : int(1..3)]) - /\ - (and([a_ExplicitWithFlags_Flags[q27] > 0 /\ a_ExplicitWithFlags_Values[q27] < b_ExplicitWithFlags_Values[q32] - -> - sum([toInt(a_ExplicitWithFlags_Values[q23] = a_ExplicitWithFlags_Values[q27]) * - catchUndef(a_ExplicitWithFlags_Flags[q23], 0) - | q23 : int(1..3)]) - = - sum([toInt(b_ExplicitWithFlags_Values[q24] = a_ExplicitWithFlags_Values[q27]) * - catchUndef(b_ExplicitWithFlags_Flags[q24], 0) - | q24 : int(1..3)]) - | q27 : int(1..3)]) - /\ - and([and([b_ExplicitWithFlags_Flags[q28] > 0, - !or([a_ExplicitWithFlags_Flags[q26] > 0 /\ - a_ExplicitWithFlags_Values[q26] = b_ExplicitWithFlags_Values[q28] - | q26 : int(1..3)]), - b_ExplicitWithFlags_Values[q28] < b_ExplicitWithFlags_Values[q32]; - int(1..3)]) - -> - sum([toInt(a_ExplicitWithFlags_Values[q23] = b_ExplicitWithFlags_Values[q28]) * - catchUndef(a_ExplicitWithFlags_Flags[q23], 0) - | q23 : int(1..3)]) - = - sum([toInt(b_ExplicitWithFlags_Values[q24] = b_ExplicitWithFlags_Values[q28]) * - catchUndef(b_ExplicitWithFlags_Flags[q24], 0) - | q24 : int(1..3)]) - | q28 : int(1..3)]))) - | q32 : int(1..3)]), - and([a_ExplicitWithFlags_Flags[q1 + 1] > 0 -> a_ExplicitWithFlags_Values[q1] < a_ExplicitWithFlags_Values[q1 + 1] - | q1 : int(1..2)]), - and([a_ExplicitWithFlags_Flags[q2] = 0 -> a_ExplicitWithFlags_Values[q2] = 1 | q2 : int(1..3)]), - and([a_ExplicitWithFlags_Flags[q3 + 1] > 0 -> a_ExplicitWithFlags_Flags[q3] > 0 | q3 : int(1..2)]), - 3 = sum([a_ExplicitWithFlags_Flags[q5] | q5 : int(1..3)]), - and([b_ExplicitWithFlags_Flags[q7 + 1] > 0 -> b_ExplicitWithFlags_Values[q7] < b_ExplicitWithFlags_Values[q7 + 1] - | q7 : int(1..2)]), - and([b_ExplicitWithFlags_Flags[q8] = 0 -> b_ExplicitWithFlags_Values[q8] = 1 | q8 : int(1..3)]), - and([b_ExplicitWithFlags_Flags[q9 + 1] > 0 -> b_ExplicitWithFlags_Flags[q9] > 0 | q9 : int(1..2)]), - 3 = sum([b_ExplicitWithFlags_Flags[q11] | q11 : int(1..3)]), - 3 = sum([a_MOccurrence[q13] | q13 : int(1..2)]), - and([a_MOccurrence[q15] > 0 -> - a_MOccurrence[q15] = - sum([toInt(a_ExplicitWithFlags_Values[q16] = q15) * catchUndef(a_ExplicitWithFlags_Flags[q16], 0) - | q16 : int(1..3)]) - | q15 : int(1..2)]), - and([a_ExplicitWithFlags_Flags[q17] > 0 -> - a_MOccurrence[a_ExplicitWithFlags_Values[q17]] = - sum([toInt(a_ExplicitWithFlags_Values[q18] = a_ExplicitWithFlags_Values[q17]) * - catchUndef(a_ExplicitWithFlags_Flags[q18], 0) - | q18 : int(1..3)]) - | q17 : int(1..3)]) - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_3_2-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_3_2-solution000001.solution deleted file mode 100644 index d56a0bbcdc..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_3_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_3_2-solution000002.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_3_2-solution000002.solution deleted file mode 100644 index ff56905e23..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_3_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_3_2-solution000003.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_3_2-solution000003.solution deleted file mode 100644 index 15472caf03..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_3_2-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 2, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_3_2-solution000004.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_3_2-solution000004.solution deleted file mode 100644 index 1b4b5b08a6..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_3_2-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 2, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_3_2-solution000005.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_3_2-solution000005.solution deleted file mode 100644 index 5e2caa751c..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_3_2-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 2, 2) -letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_3_2-solution000006.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_3_2-solution000006.solution deleted file mode 100644 index 621d5f6edc..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_3_2-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 1, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_3_2.eprime b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_3_2.eprime deleted file mode 100644 index f4ecda7185..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_3_2.eprime +++ /dev/null @@ -1,129 +0,0 @@ -language ESSENCE' 1.0 - -find a_ExplicitWithFlags_Flags: matrix indexed by [int(1..3)] of int(0..3) -find a_ExplicitWithFlags_Values: matrix indexed by [int(1..3)] of int(1..2) -find a_MOccurrence: matrix indexed by [int(1..2)] of int(0..3) -find b_ExplicitWithFlags_Flags: matrix indexed by [int(1..3)] of int(0..3) -find b_ExplicitWithFlags_Values: matrix indexed by [int(1..3)] of int(1..2) -find b_ExplicitWithRepetition_Flag: int(3) -find b_ExplicitWithRepetition_Values: matrix indexed by [int(1..3)] of int(1..2) -branching on - [a_MOccurrence, a_ExplicitWithFlags_Flags, a_ExplicitWithFlags_Values, b_ExplicitWithRepetition_Flag, - b_ExplicitWithRepetition_Values, b_ExplicitWithFlags_Flags, b_ExplicitWithFlags_Values] -such that - or([a_ExplicitWithFlags_Flags[q45] > 0 /\ - (sum([toInt(a_ExplicitWithFlags_Values[q35] = a_ExplicitWithFlags_Values[q45]) * - catchUndef(a_ExplicitWithFlags_Flags[q35], 0) - | q35 : int(1..3)]) - < - sum([toInt(b_ExplicitWithFlags_Values[q36] = a_ExplicitWithFlags_Values[q45]) * - catchUndef(b_ExplicitWithFlags_Flags[q36], 0) - | q36 : int(1..3)]) - /\ - (and([a_ExplicitWithFlags_Flags[q41] > 0 /\ a_ExplicitWithFlags_Values[q41] < a_ExplicitWithFlags_Values[q45] - -> - sum([toInt(a_ExplicitWithFlags_Values[q37] = a_ExplicitWithFlags_Values[q41]) * - catchUndef(a_ExplicitWithFlags_Flags[q37], 0) - | q37 : int(1..3)]) - = - sum([toInt(b_ExplicitWithFlags_Values[q38] = a_ExplicitWithFlags_Values[q41]) * - catchUndef(b_ExplicitWithFlags_Flags[q38], 0) - | q38 : int(1..3)]) - | q41 : int(1..3)]) - /\ - and([and([b_ExplicitWithFlags_Flags[q42] > 0, - !or([a_ExplicitWithFlags_Flags[q40] > 0 /\ - a_ExplicitWithFlags_Values[q40] = b_ExplicitWithFlags_Values[q42] - | q40 : int(1..3)]), - b_ExplicitWithFlags_Values[q42] < a_ExplicitWithFlags_Values[q45]; - int(1..3)]) - -> - sum([toInt(a_ExplicitWithFlags_Values[q37] = b_ExplicitWithFlags_Values[q42]) * - catchUndef(a_ExplicitWithFlags_Flags[q37], 0) - | q37 : int(1..3)]) - = - sum([toInt(b_ExplicitWithFlags_Values[q38] = b_ExplicitWithFlags_Values[q42]) * - catchUndef(b_ExplicitWithFlags_Flags[q38], 0) - | q38 : int(1..3)]) - | q42 : int(1..3)]))) - | q45 : int(1..3)]) - \/ - or([b_ExplicitWithFlags_Flags[q46] > 0 /\ - !or([a_ExplicitWithFlags_Flags[q44] > 0 /\ a_ExplicitWithFlags_Values[q44] = b_ExplicitWithFlags_Values[q46] - | q44 : int(1..3)]) - /\ - (sum([toInt(a_ExplicitWithFlags_Values[q35] = b_ExplicitWithFlags_Values[q46]) * - catchUndef(a_ExplicitWithFlags_Flags[q35], 0) - | q35 : int(1..3)]) - < - sum([toInt(b_ExplicitWithFlags_Values[q36] = b_ExplicitWithFlags_Values[q46]) * - catchUndef(b_ExplicitWithFlags_Flags[q36], 0) - | q36 : int(1..3)]) - /\ - (and([a_ExplicitWithFlags_Flags[q41] > 0 /\ a_ExplicitWithFlags_Values[q41] < b_ExplicitWithFlags_Values[q46] - -> - sum([toInt(a_ExplicitWithFlags_Values[q37] = a_ExplicitWithFlags_Values[q41]) * - catchUndef(a_ExplicitWithFlags_Flags[q37], 0) - | q37 : int(1..3)]) - = - sum([toInt(b_ExplicitWithFlags_Values[q38] = a_ExplicitWithFlags_Values[q41]) * - catchUndef(b_ExplicitWithFlags_Flags[q38], 0) - | q38 : int(1..3)]) - | q41 : int(1..3)]) - /\ - and([and([b_ExplicitWithFlags_Flags[q42] > 0, - !or([a_ExplicitWithFlags_Flags[q40] > 0 /\ - a_ExplicitWithFlags_Values[q40] = b_ExplicitWithFlags_Values[q42] - | q40 : int(1..3)]), - b_ExplicitWithFlags_Values[q42] < b_ExplicitWithFlags_Values[q46]; - int(1..3)]) - -> - sum([toInt(a_ExplicitWithFlags_Values[q37] = b_ExplicitWithFlags_Values[q42]) * - catchUndef(a_ExplicitWithFlags_Flags[q37], 0) - | q37 : int(1..3)]) - = - sum([toInt(b_ExplicitWithFlags_Values[q38] = b_ExplicitWithFlags_Values[q42]) * - catchUndef(b_ExplicitWithFlags_Flags[q38], 0) - | q38 : int(1..3)]) - | q42 : int(1..3)]))) - | q46 : int(1..3)]), - and([a_ExplicitWithFlags_Flags[q1 + 1] > 0 -> a_ExplicitWithFlags_Values[q1] < a_ExplicitWithFlags_Values[q1 + 1] - | q1 : int(1..2)]), - and([a_ExplicitWithFlags_Flags[q2] = 0 -> a_ExplicitWithFlags_Values[q2] = 1 | q2 : int(1..3)]), - and([a_ExplicitWithFlags_Flags[q3 + 1] > 0 -> a_ExplicitWithFlags_Flags[q3] > 0 | q3 : int(1..2)]), - 3 = sum([a_ExplicitWithFlags_Flags[q5] | q5 : int(1..3)]), - and([b_ExplicitWithFlags_Flags[q7 + 1] > 0 -> b_ExplicitWithFlags_Values[q7] < b_ExplicitWithFlags_Values[q7 + 1] - | q7 : int(1..2)]), - and([b_ExplicitWithFlags_Flags[q8] = 0 -> b_ExplicitWithFlags_Values[q8] = 1 | q8 : int(1..3)]), - and([b_ExplicitWithFlags_Flags[q9 + 1] > 0 -> b_ExplicitWithFlags_Flags[q9] > 0 | q9 : int(1..2)]), - 3 = sum([b_ExplicitWithFlags_Flags[q11] | q11 : int(1..3)]), - 3 = sum([a_MOccurrence[q13] | q13 : int(1..2)]), - and([a_MOccurrence[q29] > 0 -> - a_MOccurrence[q29] = - sum([toInt(a_ExplicitWithFlags_Values[q30] = q29) * catchUndef(a_ExplicitWithFlags_Flags[q30], 0) - | q30 : int(1..3)]) - | q29 : int(1..2)]), - and([a_ExplicitWithFlags_Flags[q31] > 0 -> - a_MOccurrence[a_ExplicitWithFlags_Values[q31]] = - sum([toInt(a_ExplicitWithFlags_Values[q32] = a_ExplicitWithFlags_Values[q31]) * - catchUndef(a_ExplicitWithFlags_Flags[q32], 0) - | q32 : int(1..3)]) - | q31 : int(1..3)]), - and([b_ExplicitWithRepetition_Values[q14] <= b_ExplicitWithRepetition_Values[q14 + 1] - | q14 : int(1..2), q14 + 1 <= 3]), - and([sum([toInt(b_ExplicitWithRepetition_Values[q23] = b_ExplicitWithRepetition_Values[q20]) - | q23 : int(1..3), q23 <= 3]) - = - sum([toInt(b_ExplicitWithFlags_Values[q21] = b_ExplicitWithRepetition_Values[q20]) * - catchUndef(b_ExplicitWithFlags_Flags[q21], 0) - | q21 : int(1..3)]) - | q20 : int(1..3), q20 <= 3]), - and([b_ExplicitWithFlags_Flags[q24] > 0 -> - sum([toInt(b_ExplicitWithRepetition_Values[q27] = b_ExplicitWithFlags_Values[q24]) - | q27 : int(1..3), q27 <= 3]) - = - sum([toInt(b_ExplicitWithFlags_Values[q25] = b_ExplicitWithFlags_Values[q24]) * - catchUndef(b_ExplicitWithFlags_Flags[q25], 0) - | q25 : int(1..3)]) - | q24 : int(1..3)]) - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_3_3-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_3_3-solution000001.solution deleted file mode 100644 index 15472caf03..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_3_3-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 2, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_3_3-solution000002.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_3_3-solution000002.solution deleted file mode 100644 index ff56905e23..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_3_3-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_3_3-solution000003.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_3_3-solution000003.solution deleted file mode 100644 index d56a0bbcdc..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_3_3-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_3_3-solution000004.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_3_3-solution000004.solution deleted file mode 100644 index 5e2caa751c..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_3_3-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 2, 2) -letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_3_3-solution000005.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_3_3-solution000005.solution deleted file mode 100644 index 1b4b5b08a6..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_3_3-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 2, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_3_3-solution000006.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_3_3-solution000006.solution deleted file mode 100644 index 621d5f6edc..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_3_3-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 1, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_3_3.eprime b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_3_3.eprime deleted file mode 100644 index 7bd9330a45..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_3_3.eprime +++ /dev/null @@ -1,123 +0,0 @@ -language ESSENCE' 1.0 - -find a_ExplicitWithFlags_Flags: matrix indexed by [int(1..3)] of int(0..3) -find a_ExplicitWithFlags_Values: matrix indexed by [int(1..3)] of int(1..2) -find a_MOccurrence: matrix indexed by [int(1..2)] of int(0..3) -find b_ExplicitWithFlags_Flags: matrix indexed by [int(1..3)] of int(0..3) -find b_ExplicitWithFlags_Values: matrix indexed by [int(1..3)] of int(1..2) -find b_MOccurrence: matrix indexed by [int(1..2)] of int(0..3) -branching on - [a_MOccurrence, a_ExplicitWithFlags_Flags, a_ExplicitWithFlags_Values, b_MOccurrence, b_ExplicitWithFlags_Flags, - b_ExplicitWithFlags_Values] -such that - or([a_ExplicitWithFlags_Flags[q37] > 0 /\ - (sum([toInt(a_ExplicitWithFlags_Values[q27] = a_ExplicitWithFlags_Values[q37]) * - catchUndef(a_ExplicitWithFlags_Flags[q27], 0) - | q27 : int(1..3)]) - < - sum([toInt(b_ExplicitWithFlags_Values[q28] = a_ExplicitWithFlags_Values[q37]) * - catchUndef(b_ExplicitWithFlags_Flags[q28], 0) - | q28 : int(1..3)]) - /\ - (and([a_ExplicitWithFlags_Flags[q33] > 0 /\ a_ExplicitWithFlags_Values[q33] < a_ExplicitWithFlags_Values[q37] - -> - sum([toInt(a_ExplicitWithFlags_Values[q29] = a_ExplicitWithFlags_Values[q33]) * - catchUndef(a_ExplicitWithFlags_Flags[q29], 0) - | q29 : int(1..3)]) - = - sum([toInt(b_ExplicitWithFlags_Values[q30] = a_ExplicitWithFlags_Values[q33]) * - catchUndef(b_ExplicitWithFlags_Flags[q30], 0) - | q30 : int(1..3)]) - | q33 : int(1..3)]) - /\ - and([and([b_ExplicitWithFlags_Flags[q34] > 0, - !or([a_ExplicitWithFlags_Flags[q32] > 0 /\ - a_ExplicitWithFlags_Values[q32] = b_ExplicitWithFlags_Values[q34] - | q32 : int(1..3)]), - b_ExplicitWithFlags_Values[q34] < a_ExplicitWithFlags_Values[q37]; - int(1..3)]) - -> - sum([toInt(a_ExplicitWithFlags_Values[q29] = b_ExplicitWithFlags_Values[q34]) * - catchUndef(a_ExplicitWithFlags_Flags[q29], 0) - | q29 : int(1..3)]) - = - sum([toInt(b_ExplicitWithFlags_Values[q30] = b_ExplicitWithFlags_Values[q34]) * - catchUndef(b_ExplicitWithFlags_Flags[q30], 0) - | q30 : int(1..3)]) - | q34 : int(1..3)]))) - | q37 : int(1..3)]) - \/ - or([b_ExplicitWithFlags_Flags[q38] > 0 /\ - !or([a_ExplicitWithFlags_Flags[q36] > 0 /\ a_ExplicitWithFlags_Values[q36] = b_ExplicitWithFlags_Values[q38] - | q36 : int(1..3)]) - /\ - (sum([toInt(a_ExplicitWithFlags_Values[q27] = b_ExplicitWithFlags_Values[q38]) * - catchUndef(a_ExplicitWithFlags_Flags[q27], 0) - | q27 : int(1..3)]) - < - sum([toInt(b_ExplicitWithFlags_Values[q28] = b_ExplicitWithFlags_Values[q38]) * - catchUndef(b_ExplicitWithFlags_Flags[q28], 0) - | q28 : int(1..3)]) - /\ - (and([a_ExplicitWithFlags_Flags[q33] > 0 /\ a_ExplicitWithFlags_Values[q33] < b_ExplicitWithFlags_Values[q38] - -> - sum([toInt(a_ExplicitWithFlags_Values[q29] = a_ExplicitWithFlags_Values[q33]) * - catchUndef(a_ExplicitWithFlags_Flags[q29], 0) - | q29 : int(1..3)]) - = - sum([toInt(b_ExplicitWithFlags_Values[q30] = a_ExplicitWithFlags_Values[q33]) * - catchUndef(b_ExplicitWithFlags_Flags[q30], 0) - | q30 : int(1..3)]) - | q33 : int(1..3)]) - /\ - and([and([b_ExplicitWithFlags_Flags[q34] > 0, - !or([a_ExplicitWithFlags_Flags[q32] > 0 /\ - a_ExplicitWithFlags_Values[q32] = b_ExplicitWithFlags_Values[q34] - | q32 : int(1..3)]), - b_ExplicitWithFlags_Values[q34] < b_ExplicitWithFlags_Values[q38]; - int(1..3)]) - -> - sum([toInt(a_ExplicitWithFlags_Values[q29] = b_ExplicitWithFlags_Values[q34]) * - catchUndef(a_ExplicitWithFlags_Flags[q29], 0) - | q29 : int(1..3)]) - = - sum([toInt(b_ExplicitWithFlags_Values[q30] = b_ExplicitWithFlags_Values[q34]) * - catchUndef(b_ExplicitWithFlags_Flags[q30], 0) - | q30 : int(1..3)]) - | q34 : int(1..3)]))) - | q38 : int(1..3)]), - and([a_ExplicitWithFlags_Flags[q1 + 1] > 0 -> a_ExplicitWithFlags_Values[q1] < a_ExplicitWithFlags_Values[q1 + 1] - | q1 : int(1..2)]), - and([a_ExplicitWithFlags_Flags[q2] = 0 -> a_ExplicitWithFlags_Values[q2] = 1 | q2 : int(1..3)]), - and([a_ExplicitWithFlags_Flags[q3 + 1] > 0 -> a_ExplicitWithFlags_Flags[q3] > 0 | q3 : int(1..2)]), - 3 = sum([a_ExplicitWithFlags_Flags[q5] | q5 : int(1..3)]), - and([b_ExplicitWithFlags_Flags[q7 + 1] > 0 -> b_ExplicitWithFlags_Values[q7] < b_ExplicitWithFlags_Values[q7 + 1] - | q7 : int(1..2)]), - and([b_ExplicitWithFlags_Flags[q8] = 0 -> b_ExplicitWithFlags_Values[q8] = 1 | q8 : int(1..3)]), - and([b_ExplicitWithFlags_Flags[q9 + 1] > 0 -> b_ExplicitWithFlags_Flags[q9] > 0 | q9 : int(1..2)]), - 3 = sum([b_ExplicitWithFlags_Flags[q11] | q11 : int(1..3)]), - 3 = sum([a_MOccurrence[q13] | q13 : int(1..2)]), - and([a_MOccurrence[q21] > 0 -> - a_MOccurrence[q21] = - sum([toInt(a_ExplicitWithFlags_Values[q22] = q21) * catchUndef(a_ExplicitWithFlags_Flags[q22], 0) - | q22 : int(1..3)]) - | q21 : int(1..2)]), - and([a_ExplicitWithFlags_Flags[q23] > 0 -> - a_MOccurrence[a_ExplicitWithFlags_Values[q23]] = - sum([toInt(a_ExplicitWithFlags_Values[q24] = a_ExplicitWithFlags_Values[q23]) * - catchUndef(a_ExplicitWithFlags_Flags[q24], 0) - | q24 : int(1..3)]) - | q23 : int(1..3)]), - 3 = sum([b_MOccurrence[q14] | q14 : int(1..2)]), - and([b_MOccurrence[q16] > 0 -> - b_MOccurrence[q16] = - sum([toInt(b_ExplicitWithFlags_Values[q17] = q16) * catchUndef(b_ExplicitWithFlags_Flags[q17], 0) - | q17 : int(1..3)]) - | q16 : int(1..2)]), - and([b_ExplicitWithFlags_Flags[q18] > 0 -> - b_MOccurrence[b_ExplicitWithFlags_Values[q18]] = - sum([toInt(b_ExplicitWithFlags_Values[q19] = b_ExplicitWithFlags_Values[q18]) * - catchUndef(b_ExplicitWithFlags_Flags[q19], 0) - | q19 : int(1..3)]) - | q18 : int(1..3)]) - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_1_1-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_1_1-solution000001.solution deleted file mode 100644 index 5e2caa751c..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_1_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 2, 2) -letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_1_1-solution000002.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_1_1-solution000002.solution deleted file mode 100644 index 1b4b5b08a6..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_1_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 2, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_1_1-solution000003.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_1_1-solution000003.solution deleted file mode 100644 index 621d5f6edc..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_1_1-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 1, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_1_1-solution000004.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_1_1-solution000004.solution deleted file mode 100644 index 15472caf03..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_1_1-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 2, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_1_1-solution000005.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_1_1-solution000005.solution deleted file mode 100644 index ff56905e23..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_1_1-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_1_1-solution000006.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_1_1-solution000006.solution deleted file mode 100644 index d56a0bbcdc..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_1_1-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_1_1.eprime b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_1_1.eprime deleted file mode 100644 index 16bf371f46..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_1_1.eprime +++ /dev/null @@ -1,106 +0,0 @@ -language ESSENCE' 1.0 - -find a_ExplicitWithFlags_Flags: matrix indexed by [int(1..3)] of int(0..3) -find a_ExplicitWithFlags_Values: matrix indexed by [int(1..3)] of int(1..2) -find b_ExplicitWithRepetition_Flag: int(3) -find b_ExplicitWithRepetition_Values: matrix indexed by [int(1..3)] of int(1..2) -find b_ExplicitWithFlags_Flags: matrix indexed by [int(1..3)] of int(0..3) -find b_ExplicitWithFlags_Values: matrix indexed by [int(1..3)] of int(1..2) -branching on - [a_ExplicitWithFlags_Flags, a_ExplicitWithFlags_Values, b_ExplicitWithFlags_Flags, b_ExplicitWithFlags_Values, - b_ExplicitWithRepetition_Flag, b_ExplicitWithRepetition_Values] -such that - or([a_ExplicitWithFlags_Flags[q42] > 0 /\ - (sum([toInt(a_ExplicitWithFlags_Values[q29] = a_ExplicitWithFlags_Values[q42]) * - catchUndef(a_ExplicitWithFlags_Flags[q29], 0) - | q29 : int(1..3)]) - < - sum([toInt(b_ExplicitWithRepetition_Values[q31] = a_ExplicitWithFlags_Values[q42]) - | q31 : int(1..3), q31 <= 3]) - /\ - (and([a_ExplicitWithFlags_Flags[q38] > 0 /\ a_ExplicitWithFlags_Values[q38] < a_ExplicitWithFlags_Values[q42] - -> - sum([toInt(a_ExplicitWithFlags_Values[q32] = a_ExplicitWithFlags_Values[q38]) * - catchUndef(a_ExplicitWithFlags_Flags[q32], 0) - | q32 : int(1..3)]) - = - sum([toInt(b_ExplicitWithRepetition_Values[q34] = a_ExplicitWithFlags_Values[q38]) - | q34 : int(1..3), q34 <= 3]) - | q38 : int(1..3)]) - /\ - and([!or([a_ExplicitWithFlags_Flags[q37] > 0 /\ - a_ExplicitWithFlags_Values[q37] = b_ExplicitWithRepetition_Values[q35] - | q37 : int(1..3)]) - /\ b_ExplicitWithRepetition_Values[q35] < a_ExplicitWithFlags_Values[q42] - -> - sum([toInt(a_ExplicitWithFlags_Values[q32] = b_ExplicitWithRepetition_Values[q35]) * - catchUndef(a_ExplicitWithFlags_Flags[q32], 0) - | q32 : int(1..3)]) - = - sum([toInt(b_ExplicitWithRepetition_Values[q34] = b_ExplicitWithRepetition_Values[q35]) - | q34 : int(1..3), q34 <= 3]) - | q35 : int(1..3), q35 <= 3]))) - | q42 : int(1..3)]) - \/ - or([!or([a_ExplicitWithFlags_Flags[q41] > 0 /\ - a_ExplicitWithFlags_Values[q41] = b_ExplicitWithRepetition_Values[q39] - | q41 : int(1..3)]) - /\ - (sum([toInt(a_ExplicitWithFlags_Values[q29] = b_ExplicitWithRepetition_Values[q39]) * - catchUndef(a_ExplicitWithFlags_Flags[q29], 0) - | q29 : int(1..3)]) - < - sum([toInt(b_ExplicitWithRepetition_Values[q31] = b_ExplicitWithRepetition_Values[q39]) - | q31 : int(1..3), q31 <= 3]) - /\ - (and([a_ExplicitWithFlags_Flags[q38] > 0 /\ - a_ExplicitWithFlags_Values[q38] < b_ExplicitWithRepetition_Values[q39] - -> - sum([toInt(a_ExplicitWithFlags_Values[q32] = a_ExplicitWithFlags_Values[q38]) * - catchUndef(a_ExplicitWithFlags_Flags[q32], 0) - | q32 : int(1..3)]) - = - sum([toInt(b_ExplicitWithRepetition_Values[q34] = a_ExplicitWithFlags_Values[q38]) - | q34 : int(1..3), q34 <= 3]) - | q38 : int(1..3)]) - /\ - and([!or([a_ExplicitWithFlags_Flags[q37] > 0 /\ - a_ExplicitWithFlags_Values[q37] = b_ExplicitWithRepetition_Values[q35] - | q37 : int(1..3)]) - /\ b_ExplicitWithRepetition_Values[q35] < b_ExplicitWithRepetition_Values[q39] - -> - sum([toInt(a_ExplicitWithFlags_Values[q32] = b_ExplicitWithRepetition_Values[q35]) * - catchUndef(a_ExplicitWithFlags_Flags[q32], 0) - | q32 : int(1..3)]) - = - sum([toInt(b_ExplicitWithRepetition_Values[q34] = b_ExplicitWithRepetition_Values[q35]) - | q34 : int(1..3), q34 <= 3]) - | q35 : int(1..3), q35 <= 3]))) - | q39 : int(1..3), q39 <= 3]), - and([a_ExplicitWithFlags_Flags[q1 + 1] > 0 -> a_ExplicitWithFlags_Values[q1] < a_ExplicitWithFlags_Values[q1 + 1] - | q1 : int(1..2)]), - and([a_ExplicitWithFlags_Flags[q2] = 0 -> a_ExplicitWithFlags_Values[q2] = 1 | q2 : int(1..3)]), - and([a_ExplicitWithFlags_Flags[q3 + 1] > 0 -> a_ExplicitWithFlags_Flags[q3] > 0 | q3 : int(1..2)]), - 3 = sum([a_ExplicitWithFlags_Flags[q5] | q5 : int(1..3)]), - and([b_ExplicitWithRepetition_Values[q7] <= b_ExplicitWithRepetition_Values[q7 + 1] | q7 : int(1..2), q7 + 1 <= 3]), - and([b_ExplicitWithFlags_Flags[q12 + 1] > 0 -> b_ExplicitWithFlags_Values[q12] < b_ExplicitWithFlags_Values[q12 + 1] - | q12 : int(1..2)]), - and([b_ExplicitWithFlags_Flags[q13] = 0 -> b_ExplicitWithFlags_Values[q13] = 1 | q13 : int(1..3)]), - and([b_ExplicitWithFlags_Flags[q14 + 1] > 0 -> b_ExplicitWithFlags_Flags[q14] > 0 | q14 : int(1..2)]), - 3 = sum([b_ExplicitWithFlags_Flags[q16] | q16 : int(1..3)]), - and([b_ExplicitWithFlags_Flags[q19] > 0 -> - sum([toInt(b_ExplicitWithFlags_Values[q20] = b_ExplicitWithFlags_Values[q19]) * - catchUndef(b_ExplicitWithFlags_Flags[q20], 0) - | q20 : int(1..3)]) - = - sum([toInt(b_ExplicitWithRepetition_Values[q22] = b_ExplicitWithFlags_Values[q19]) - | q22 : int(1..3), q22 <= 3]) - | q19 : int(1..3)]), - and([sum([toInt(b_ExplicitWithFlags_Values[q24] = b_ExplicitWithRepetition_Values[q23]) * - catchUndef(b_ExplicitWithFlags_Flags[q24], 0) - | q24 : int(1..3)]) - = - sum([toInt(b_ExplicitWithRepetition_Values[q26] = b_ExplicitWithRepetition_Values[q23]) - | q26 : int(1..3), q26 <= 3]) - | q23 : int(1..3), q23 <= 3]) - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_1_2-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_1_2-solution000001.solution deleted file mode 100644 index 1b4b5b08a6..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_1_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 2, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_1_2-solution000002.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_1_2-solution000002.solution deleted file mode 100644 index 5e2caa751c..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_1_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 2, 2) -letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_1_2-solution000003.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_1_2-solution000003.solution deleted file mode 100644 index 621d5f6edc..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_1_2-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 1, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_1_2-solution000004.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_1_2-solution000004.solution deleted file mode 100644 index d56a0bbcdc..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_1_2-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_1_2-solution000005.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_1_2-solution000005.solution deleted file mode 100644 index ff56905e23..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_1_2-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_1_2-solution000006.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_1_2-solution000006.solution deleted file mode 100644 index 15472caf03..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_1_2-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 2, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_1_2.eprime b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_1_2.eprime deleted file mode 100644 index 6fbb3cc8ac..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_1_2.eprime +++ /dev/null @@ -1,84 +0,0 @@ -language ESSENCE' 1.0 - -find a_ExplicitWithFlags_Flags: matrix indexed by [int(1..3)] of int(0..3) -find a_ExplicitWithFlags_Values: matrix indexed by [int(1..3)] of int(1..2) -find b_ExplicitWithRepetition_Flag: int(3) -find b_ExplicitWithRepetition_Values: matrix indexed by [int(1..3)] of int(1..2) -branching on - [a_ExplicitWithFlags_Flags, a_ExplicitWithFlags_Values, b_ExplicitWithRepetition_Flag, - b_ExplicitWithRepetition_Values] -such that - or([a_ExplicitWithFlags_Flags[q27] > 0 /\ - (sum([toInt(a_ExplicitWithFlags_Values[q14] = a_ExplicitWithFlags_Values[q27]) * - catchUndef(a_ExplicitWithFlags_Flags[q14], 0) - | q14 : int(1..3)]) - < - sum([toInt(b_ExplicitWithRepetition_Values[q16] = a_ExplicitWithFlags_Values[q27]) - | q16 : int(1..3), q16 <= 3]) - /\ - (and([a_ExplicitWithFlags_Flags[q23] > 0 /\ a_ExplicitWithFlags_Values[q23] < a_ExplicitWithFlags_Values[q27] - -> - sum([toInt(a_ExplicitWithFlags_Values[q17] = a_ExplicitWithFlags_Values[q23]) * - catchUndef(a_ExplicitWithFlags_Flags[q17], 0) - | q17 : int(1..3)]) - = - sum([toInt(b_ExplicitWithRepetition_Values[q19] = a_ExplicitWithFlags_Values[q23]) - | q19 : int(1..3), q19 <= 3]) - | q23 : int(1..3)]) - /\ - and([!or([a_ExplicitWithFlags_Flags[q22] > 0 /\ - a_ExplicitWithFlags_Values[q22] = b_ExplicitWithRepetition_Values[q20] - | q22 : int(1..3)]) - /\ b_ExplicitWithRepetition_Values[q20] < a_ExplicitWithFlags_Values[q27] - -> - sum([toInt(a_ExplicitWithFlags_Values[q17] = b_ExplicitWithRepetition_Values[q20]) * - catchUndef(a_ExplicitWithFlags_Flags[q17], 0) - | q17 : int(1..3)]) - = - sum([toInt(b_ExplicitWithRepetition_Values[q19] = b_ExplicitWithRepetition_Values[q20]) - | q19 : int(1..3), q19 <= 3]) - | q20 : int(1..3), q20 <= 3]))) - | q27 : int(1..3)]) - \/ - or([!or([a_ExplicitWithFlags_Flags[q26] > 0 /\ - a_ExplicitWithFlags_Values[q26] = b_ExplicitWithRepetition_Values[q24] - | q26 : int(1..3)]) - /\ - (sum([toInt(a_ExplicitWithFlags_Values[q14] = b_ExplicitWithRepetition_Values[q24]) * - catchUndef(a_ExplicitWithFlags_Flags[q14], 0) - | q14 : int(1..3)]) - < - sum([toInt(b_ExplicitWithRepetition_Values[q16] = b_ExplicitWithRepetition_Values[q24]) - | q16 : int(1..3), q16 <= 3]) - /\ - (and([a_ExplicitWithFlags_Flags[q23] > 0 /\ - a_ExplicitWithFlags_Values[q23] < b_ExplicitWithRepetition_Values[q24] - -> - sum([toInt(a_ExplicitWithFlags_Values[q17] = a_ExplicitWithFlags_Values[q23]) * - catchUndef(a_ExplicitWithFlags_Flags[q17], 0) - | q17 : int(1..3)]) - = - sum([toInt(b_ExplicitWithRepetition_Values[q19] = a_ExplicitWithFlags_Values[q23]) - | q19 : int(1..3), q19 <= 3]) - | q23 : int(1..3)]) - /\ - and([!or([a_ExplicitWithFlags_Flags[q22] > 0 /\ - a_ExplicitWithFlags_Values[q22] = b_ExplicitWithRepetition_Values[q20] - | q22 : int(1..3)]) - /\ b_ExplicitWithRepetition_Values[q20] < b_ExplicitWithRepetition_Values[q24] - -> - sum([toInt(a_ExplicitWithFlags_Values[q17] = b_ExplicitWithRepetition_Values[q20]) * - catchUndef(a_ExplicitWithFlags_Flags[q17], 0) - | q17 : int(1..3)]) - = - sum([toInt(b_ExplicitWithRepetition_Values[q19] = b_ExplicitWithRepetition_Values[q20]) - | q19 : int(1..3), q19 <= 3]) - | q20 : int(1..3), q20 <= 3]))) - | q24 : int(1..3), q24 <= 3]), - and([a_ExplicitWithFlags_Flags[q1 + 1] > 0 -> a_ExplicitWithFlags_Values[q1] < a_ExplicitWithFlags_Values[q1 + 1] - | q1 : int(1..2)]), - and([a_ExplicitWithFlags_Flags[q2] = 0 -> a_ExplicitWithFlags_Values[q2] = 1 | q2 : int(1..3)]), - and([a_ExplicitWithFlags_Flags[q3 + 1] > 0 -> a_ExplicitWithFlags_Flags[q3] > 0 | q3 : int(1..2)]), - 3 = sum([a_ExplicitWithFlags_Flags[q5] | q5 : int(1..3)]), - and([b_ExplicitWithRepetition_Values[q7] <= b_ExplicitWithRepetition_Values[q7 + 1] | q7 : int(1..2), q7 + 1 <= 3]) - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_1_3-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_1_3-solution000001.solution deleted file mode 100644 index 5e2caa751c..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_1_3-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 2, 2) -letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_1_3-solution000002.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_1_3-solution000002.solution deleted file mode 100644 index 1b4b5b08a6..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_1_3-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 2, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_1_3-solution000003.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_1_3-solution000003.solution deleted file mode 100644 index 621d5f6edc..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_1_3-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 1, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_1_3-solution000004.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_1_3-solution000004.solution deleted file mode 100644 index 15472caf03..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_1_3-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 2, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_1_3-solution000005.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_1_3-solution000005.solution deleted file mode 100644 index ff56905e23..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_1_3-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_1_3-solution000006.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_1_3-solution000006.solution deleted file mode 100644 index d56a0bbcdc..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_1_3-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_1_3.eprime b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_1_3.eprime deleted file mode 100644 index 4f73c0c2cb..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_1_3.eprime +++ /dev/null @@ -1,93 +0,0 @@ -language ESSENCE' 1.0 - -find a_ExplicitWithFlags_Flags: matrix indexed by [int(1..3)] of int(0..3) -find a_ExplicitWithFlags_Values: matrix indexed by [int(1..3)] of int(1..2) -find b_ExplicitWithRepetition_Flag: int(3) -find b_ExplicitWithRepetition_Values: matrix indexed by [int(1..3)] of int(1..2) -find b_MOccurrence: matrix indexed by [int(1..2)] of int(0..3) -branching on - [a_ExplicitWithFlags_Flags, a_ExplicitWithFlags_Values, b_MOccurrence, b_ExplicitWithRepetition_Flag, - b_ExplicitWithRepetition_Values] -such that - or([a_ExplicitWithFlags_Flags[q35] > 0 /\ - (sum([toInt(a_ExplicitWithFlags_Values[q22] = a_ExplicitWithFlags_Values[q35]) * - catchUndef(a_ExplicitWithFlags_Flags[q22], 0) - | q22 : int(1..3)]) - < - sum([toInt(b_ExplicitWithRepetition_Values[q24] = a_ExplicitWithFlags_Values[q35]) - | q24 : int(1..3), q24 <= 3]) - /\ - (and([a_ExplicitWithFlags_Flags[q31] > 0 /\ a_ExplicitWithFlags_Values[q31] < a_ExplicitWithFlags_Values[q35] - -> - sum([toInt(a_ExplicitWithFlags_Values[q25] = a_ExplicitWithFlags_Values[q31]) * - catchUndef(a_ExplicitWithFlags_Flags[q25], 0) - | q25 : int(1..3)]) - = - sum([toInt(b_ExplicitWithRepetition_Values[q27] = a_ExplicitWithFlags_Values[q31]) - | q27 : int(1..3), q27 <= 3]) - | q31 : int(1..3)]) - /\ - and([!or([a_ExplicitWithFlags_Flags[q30] > 0 /\ - a_ExplicitWithFlags_Values[q30] = b_ExplicitWithRepetition_Values[q28] - | q30 : int(1..3)]) - /\ b_ExplicitWithRepetition_Values[q28] < a_ExplicitWithFlags_Values[q35] - -> - sum([toInt(a_ExplicitWithFlags_Values[q25] = b_ExplicitWithRepetition_Values[q28]) * - catchUndef(a_ExplicitWithFlags_Flags[q25], 0) - | q25 : int(1..3)]) - = - sum([toInt(b_ExplicitWithRepetition_Values[q27] = b_ExplicitWithRepetition_Values[q28]) - | q27 : int(1..3), q27 <= 3]) - | q28 : int(1..3), q28 <= 3]))) - | q35 : int(1..3)]) - \/ - or([!or([a_ExplicitWithFlags_Flags[q34] > 0 /\ - a_ExplicitWithFlags_Values[q34] = b_ExplicitWithRepetition_Values[q32] - | q34 : int(1..3)]) - /\ - (sum([toInt(a_ExplicitWithFlags_Values[q22] = b_ExplicitWithRepetition_Values[q32]) * - catchUndef(a_ExplicitWithFlags_Flags[q22], 0) - | q22 : int(1..3)]) - < - sum([toInt(b_ExplicitWithRepetition_Values[q24] = b_ExplicitWithRepetition_Values[q32]) - | q24 : int(1..3), q24 <= 3]) - /\ - (and([a_ExplicitWithFlags_Flags[q31] > 0 /\ - a_ExplicitWithFlags_Values[q31] < b_ExplicitWithRepetition_Values[q32] - -> - sum([toInt(a_ExplicitWithFlags_Values[q25] = a_ExplicitWithFlags_Values[q31]) * - catchUndef(a_ExplicitWithFlags_Flags[q25], 0) - | q25 : int(1..3)]) - = - sum([toInt(b_ExplicitWithRepetition_Values[q27] = a_ExplicitWithFlags_Values[q31]) - | q27 : int(1..3), q27 <= 3]) - | q31 : int(1..3)]) - /\ - and([!or([a_ExplicitWithFlags_Flags[q30] > 0 /\ - a_ExplicitWithFlags_Values[q30] = b_ExplicitWithRepetition_Values[q28] - | q30 : int(1..3)]) - /\ b_ExplicitWithRepetition_Values[q28] < b_ExplicitWithRepetition_Values[q32] - -> - sum([toInt(a_ExplicitWithFlags_Values[q25] = b_ExplicitWithRepetition_Values[q28]) * - catchUndef(a_ExplicitWithFlags_Flags[q25], 0) - | q25 : int(1..3)]) - = - sum([toInt(b_ExplicitWithRepetition_Values[q27] = b_ExplicitWithRepetition_Values[q28]) - | q27 : int(1..3), q27 <= 3]) - | q28 : int(1..3), q28 <= 3]))) - | q32 : int(1..3), q32 <= 3]), - and([a_ExplicitWithFlags_Flags[q1 + 1] > 0 -> a_ExplicitWithFlags_Values[q1] < a_ExplicitWithFlags_Values[q1 + 1] - | q1 : int(1..2)]), - and([a_ExplicitWithFlags_Flags[q2] = 0 -> a_ExplicitWithFlags_Values[q2] = 1 | q2 : int(1..3)]), - and([a_ExplicitWithFlags_Flags[q3 + 1] > 0 -> a_ExplicitWithFlags_Flags[q3] > 0 | q3 : int(1..2)]), - 3 = sum([a_ExplicitWithFlags_Flags[q5] | q5 : int(1..3)]), - and([b_ExplicitWithRepetition_Values[q7] <= b_ExplicitWithRepetition_Values[q7 + 1] | q7 : int(1..2), q7 + 1 <= 3]), - 3 = sum([b_MOccurrence[q12] | q12 : int(1..2)]), - and([b_MOccurrence[q14] > 0 -> - b_MOccurrence[q14] = sum([toInt(b_ExplicitWithRepetition_Values[q16] = q14) | q16 : int(1..3), q16 <= 3]) - | q14 : int(1..2)]), - and([b_MOccurrence[b_ExplicitWithRepetition_Values[q17]] = - sum([toInt(b_ExplicitWithRepetition_Values[q19] = b_ExplicitWithRepetition_Values[q17]) - | q19 : int(1..3), q19 <= 3]) - | q17 : int(1..3), q17 <= 3]) - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_2_1-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_2_1-solution000001.solution deleted file mode 100644 index 621d5f6edc..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_2_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 1, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_2_1-solution000002.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_2_1-solution000002.solution deleted file mode 100644 index 5e2caa751c..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_2_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 2, 2) -letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_2_1-solution000003.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_2_1-solution000003.solution deleted file mode 100644 index 1b4b5b08a6..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_2_1-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 2, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_2_1-solution000004.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_2_1-solution000004.solution deleted file mode 100644 index 15472caf03..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_2_1-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 2, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_2_1-solution000005.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_2_1-solution000005.solution deleted file mode 100644 index ff56905e23..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_2_1-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_2_1-solution000006.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_2_1-solution000006.solution deleted file mode 100644 index d56a0bbcdc..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_2_1-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_2_1.eprime b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_2_1.eprime deleted file mode 100644 index d937c1f55c..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_2_1.eprime +++ /dev/null @@ -1,126 +0,0 @@ -language ESSENCE' 1.0 - -find a_ExplicitWithFlags_Flags: matrix indexed by [int(1..3)] of int(0..3) -find a_ExplicitWithFlags_Values: matrix indexed by [int(1..3)] of int(1..2) -find a_ExplicitWithRepetition_Flag: int(3) -find a_ExplicitWithRepetition_Values: matrix indexed by [int(1..3)] of int(1..2) -find b_ExplicitWithRepetition_Flag: int(3) -find b_ExplicitWithRepetition_Values: matrix indexed by [int(1..3)] of int(1..2) -find b_ExplicitWithFlags_Flags: matrix indexed by [int(1..3)] of int(0..3) -find b_ExplicitWithFlags_Values: matrix indexed by [int(1..3)] of int(1..2) -branching on - [a_ExplicitWithRepetition_Flag, a_ExplicitWithRepetition_Values, a_ExplicitWithFlags_Flags, - a_ExplicitWithFlags_Values, b_ExplicitWithFlags_Flags, b_ExplicitWithFlags_Values, b_ExplicitWithRepetition_Flag, - b_ExplicitWithRepetition_Values] -such that - or([a_ExplicitWithFlags_Flags[q56] > 0 /\ - (sum([toInt(a_ExplicitWithFlags_Values[q43] = a_ExplicitWithFlags_Values[q56]) * - catchUndef(a_ExplicitWithFlags_Flags[q43], 0) - | q43 : int(1..3)]) - < - sum([toInt(b_ExplicitWithRepetition_Values[q45] = a_ExplicitWithFlags_Values[q56]) - | q45 : int(1..3), q45 <= 3]) - /\ - (and([a_ExplicitWithFlags_Flags[q52] > 0 /\ a_ExplicitWithFlags_Values[q52] < a_ExplicitWithFlags_Values[q56] - -> - sum([toInt(a_ExplicitWithFlags_Values[q46] = a_ExplicitWithFlags_Values[q52]) * - catchUndef(a_ExplicitWithFlags_Flags[q46], 0) - | q46 : int(1..3)]) - = - sum([toInt(b_ExplicitWithRepetition_Values[q48] = a_ExplicitWithFlags_Values[q52]) - | q48 : int(1..3), q48 <= 3]) - | q52 : int(1..3)]) - /\ - and([!or([a_ExplicitWithFlags_Flags[q51] > 0 /\ - a_ExplicitWithFlags_Values[q51] = b_ExplicitWithRepetition_Values[q49] - | q51 : int(1..3)]) - /\ b_ExplicitWithRepetition_Values[q49] < a_ExplicitWithFlags_Values[q56] - -> - sum([toInt(a_ExplicitWithFlags_Values[q46] = b_ExplicitWithRepetition_Values[q49]) * - catchUndef(a_ExplicitWithFlags_Flags[q46], 0) - | q46 : int(1..3)]) - = - sum([toInt(b_ExplicitWithRepetition_Values[q48] = b_ExplicitWithRepetition_Values[q49]) - | q48 : int(1..3), q48 <= 3]) - | q49 : int(1..3), q49 <= 3]))) - | q56 : int(1..3)]) - \/ - or([!or([a_ExplicitWithFlags_Flags[q55] > 0 /\ - a_ExplicitWithFlags_Values[q55] = b_ExplicitWithRepetition_Values[q53] - | q55 : int(1..3)]) - /\ - (sum([toInt(a_ExplicitWithFlags_Values[q43] = b_ExplicitWithRepetition_Values[q53]) * - catchUndef(a_ExplicitWithFlags_Flags[q43], 0) - | q43 : int(1..3)]) - < - sum([toInt(b_ExplicitWithRepetition_Values[q45] = b_ExplicitWithRepetition_Values[q53]) - | q45 : int(1..3), q45 <= 3]) - /\ - (and([a_ExplicitWithFlags_Flags[q52] > 0 /\ - a_ExplicitWithFlags_Values[q52] < b_ExplicitWithRepetition_Values[q53] - -> - sum([toInt(a_ExplicitWithFlags_Values[q46] = a_ExplicitWithFlags_Values[q52]) * - catchUndef(a_ExplicitWithFlags_Flags[q46], 0) - | q46 : int(1..3)]) - = - sum([toInt(b_ExplicitWithRepetition_Values[q48] = a_ExplicitWithFlags_Values[q52]) - | q48 : int(1..3), q48 <= 3]) - | q52 : int(1..3)]) - /\ - and([!or([a_ExplicitWithFlags_Flags[q51] > 0 /\ - a_ExplicitWithFlags_Values[q51] = b_ExplicitWithRepetition_Values[q49] - | q51 : int(1..3)]) - /\ b_ExplicitWithRepetition_Values[q49] < b_ExplicitWithRepetition_Values[q53] - -> - sum([toInt(a_ExplicitWithFlags_Values[q46] = b_ExplicitWithRepetition_Values[q49]) * - catchUndef(a_ExplicitWithFlags_Flags[q46], 0) - | q46 : int(1..3)]) - = - sum([toInt(b_ExplicitWithRepetition_Values[q48] = b_ExplicitWithRepetition_Values[q49]) - | q48 : int(1..3), q48 <= 3]) - | q49 : int(1..3), q49 <= 3]))) - | q53 : int(1..3), q53 <= 3]), - and([a_ExplicitWithFlags_Flags[q1 + 1] > 0 -> a_ExplicitWithFlags_Values[q1] < a_ExplicitWithFlags_Values[q1 + 1] - | q1 : int(1..2)]), - and([a_ExplicitWithFlags_Flags[q2] = 0 -> a_ExplicitWithFlags_Values[q2] = 1 | q2 : int(1..3)]), - and([a_ExplicitWithFlags_Flags[q3 + 1] > 0 -> a_ExplicitWithFlags_Flags[q3] > 0 | q3 : int(1..2)]), - 3 = sum([a_ExplicitWithFlags_Flags[q5] | q5 : int(1..3)]), - and([b_ExplicitWithRepetition_Values[q7] <= b_ExplicitWithRepetition_Values[q7 + 1] | q7 : int(1..2), q7 + 1 <= 3]), - and([a_ExplicitWithRepetition_Values[q12] <= a_ExplicitWithRepetition_Values[q12 + 1] - | q12 : int(1..2), q12 + 1 <= 3]), - and([sum([toInt(a_ExplicitWithRepetition_Values[q21] = a_ExplicitWithRepetition_Values[q18]) - | q21 : int(1..3), q21 <= 3]) - = - sum([toInt(a_ExplicitWithFlags_Values[q19] = a_ExplicitWithRepetition_Values[q18]) * - catchUndef(a_ExplicitWithFlags_Flags[q19], 0) - | q19 : int(1..3)]) - | q18 : int(1..3), q18 <= 3]), - and([a_ExplicitWithFlags_Flags[q22] > 0 -> - sum([toInt(a_ExplicitWithRepetition_Values[q25] = a_ExplicitWithFlags_Values[q22]) - | q25 : int(1..3), q25 <= 3]) - = - sum([toInt(a_ExplicitWithFlags_Values[q23] = a_ExplicitWithFlags_Values[q22]) * - catchUndef(a_ExplicitWithFlags_Flags[q23], 0) - | q23 : int(1..3)]) - | q22 : int(1..3)]), - and([b_ExplicitWithFlags_Flags[q26 + 1] > 0 -> b_ExplicitWithFlags_Values[q26] < b_ExplicitWithFlags_Values[q26 + 1] - | q26 : int(1..2)]), - and([b_ExplicitWithFlags_Flags[q27] = 0 -> b_ExplicitWithFlags_Values[q27] = 1 | q27 : int(1..3)]), - and([b_ExplicitWithFlags_Flags[q28 + 1] > 0 -> b_ExplicitWithFlags_Flags[q28] > 0 | q28 : int(1..2)]), - 3 = sum([b_ExplicitWithFlags_Flags[q30] | q30 : int(1..3)]), - and([b_ExplicitWithFlags_Flags[q33] > 0 -> - sum([toInt(b_ExplicitWithFlags_Values[q34] = b_ExplicitWithFlags_Values[q33]) * - catchUndef(b_ExplicitWithFlags_Flags[q34], 0) - | q34 : int(1..3)]) - = - sum([toInt(b_ExplicitWithRepetition_Values[q36] = b_ExplicitWithFlags_Values[q33]) - | q36 : int(1..3), q36 <= 3]) - | q33 : int(1..3)]), - and([sum([toInt(b_ExplicitWithFlags_Values[q38] = b_ExplicitWithRepetition_Values[q37]) * - catchUndef(b_ExplicitWithFlags_Flags[q38], 0) - | q38 : int(1..3)]) - = - sum([toInt(b_ExplicitWithRepetition_Values[q40] = b_ExplicitWithRepetition_Values[q37]) - | q40 : int(1..3), q40 <= 3]) - | q37 : int(1..3), q37 <= 3]) - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_2_2-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_2_2-solution000001.solution deleted file mode 100644 index 621d5f6edc..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_2_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 1, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_2_2-solution000002.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_2_2-solution000002.solution deleted file mode 100644 index 1b4b5b08a6..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_2_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 2, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_2_2-solution000003.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_2_2-solution000003.solution deleted file mode 100644 index 5e2caa751c..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_2_2-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 2, 2) -letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_2_2-solution000004.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_2_2-solution000004.solution deleted file mode 100644 index d56a0bbcdc..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_2_2-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_2_2-solution000005.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_2_2-solution000005.solution deleted file mode 100644 index ff56905e23..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_2_2-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_2_2-solution000006.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_2_2-solution000006.solution deleted file mode 100644 index 15472caf03..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_2_2-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 2, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_2_2.eprime b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_2_2.eprime deleted file mode 100644 index 44f9ff7414..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_2_2.eprime +++ /dev/null @@ -1,103 +0,0 @@ -language ESSENCE' 1.0 - -find a_ExplicitWithFlags_Flags: matrix indexed by [int(1..3)] of int(0..3) -find a_ExplicitWithFlags_Values: matrix indexed by [int(1..3)] of int(1..2) -find a_ExplicitWithRepetition_Flag: int(3) -find a_ExplicitWithRepetition_Values: matrix indexed by [int(1..3)] of int(1..2) -find b_ExplicitWithRepetition_Flag: int(3) -find b_ExplicitWithRepetition_Values: matrix indexed by [int(1..3)] of int(1..2) -branching on - [a_ExplicitWithRepetition_Flag, a_ExplicitWithRepetition_Values, a_ExplicitWithFlags_Flags, - a_ExplicitWithFlags_Values, b_ExplicitWithRepetition_Flag, b_ExplicitWithRepetition_Values] -such that - or([a_ExplicitWithFlags_Flags[q41] > 0 /\ - (sum([toInt(a_ExplicitWithFlags_Values[q28] = a_ExplicitWithFlags_Values[q41]) * - catchUndef(a_ExplicitWithFlags_Flags[q28], 0) - | q28 : int(1..3)]) - < - sum([toInt(b_ExplicitWithRepetition_Values[q30] = a_ExplicitWithFlags_Values[q41]) - | q30 : int(1..3), q30 <= 3]) - /\ - (and([a_ExplicitWithFlags_Flags[q37] > 0 /\ a_ExplicitWithFlags_Values[q37] < a_ExplicitWithFlags_Values[q41] - -> - sum([toInt(a_ExplicitWithFlags_Values[q31] = a_ExplicitWithFlags_Values[q37]) * - catchUndef(a_ExplicitWithFlags_Flags[q31], 0) - | q31 : int(1..3)]) - = - sum([toInt(b_ExplicitWithRepetition_Values[q33] = a_ExplicitWithFlags_Values[q37]) - | q33 : int(1..3), q33 <= 3]) - | q37 : int(1..3)]) - /\ - and([!or([a_ExplicitWithFlags_Flags[q36] > 0 /\ - a_ExplicitWithFlags_Values[q36] = b_ExplicitWithRepetition_Values[q34] - | q36 : int(1..3)]) - /\ b_ExplicitWithRepetition_Values[q34] < a_ExplicitWithFlags_Values[q41] - -> - sum([toInt(a_ExplicitWithFlags_Values[q31] = b_ExplicitWithRepetition_Values[q34]) * - catchUndef(a_ExplicitWithFlags_Flags[q31], 0) - | q31 : int(1..3)]) - = - sum([toInt(b_ExplicitWithRepetition_Values[q33] = b_ExplicitWithRepetition_Values[q34]) - | q33 : int(1..3), q33 <= 3]) - | q34 : int(1..3), q34 <= 3]))) - | q41 : int(1..3)]) - \/ - or([!or([a_ExplicitWithFlags_Flags[q40] > 0 /\ - a_ExplicitWithFlags_Values[q40] = b_ExplicitWithRepetition_Values[q38] - | q40 : int(1..3)]) - /\ - (sum([toInt(a_ExplicitWithFlags_Values[q28] = b_ExplicitWithRepetition_Values[q38]) * - catchUndef(a_ExplicitWithFlags_Flags[q28], 0) - | q28 : int(1..3)]) - < - sum([toInt(b_ExplicitWithRepetition_Values[q30] = b_ExplicitWithRepetition_Values[q38]) - | q30 : int(1..3), q30 <= 3]) - /\ - (and([a_ExplicitWithFlags_Flags[q37] > 0 /\ - a_ExplicitWithFlags_Values[q37] < b_ExplicitWithRepetition_Values[q38] - -> - sum([toInt(a_ExplicitWithFlags_Values[q31] = a_ExplicitWithFlags_Values[q37]) * - catchUndef(a_ExplicitWithFlags_Flags[q31], 0) - | q31 : int(1..3)]) - = - sum([toInt(b_ExplicitWithRepetition_Values[q33] = a_ExplicitWithFlags_Values[q37]) - | q33 : int(1..3), q33 <= 3]) - | q37 : int(1..3)]) - /\ - and([!or([a_ExplicitWithFlags_Flags[q36] > 0 /\ - a_ExplicitWithFlags_Values[q36] = b_ExplicitWithRepetition_Values[q34] - | q36 : int(1..3)]) - /\ b_ExplicitWithRepetition_Values[q34] < b_ExplicitWithRepetition_Values[q38] - -> - sum([toInt(a_ExplicitWithFlags_Values[q31] = b_ExplicitWithRepetition_Values[q34]) * - catchUndef(a_ExplicitWithFlags_Flags[q31], 0) - | q31 : int(1..3)]) - = - sum([toInt(b_ExplicitWithRepetition_Values[q33] = b_ExplicitWithRepetition_Values[q34]) - | q33 : int(1..3), q33 <= 3]) - | q34 : int(1..3), q34 <= 3]))) - | q38 : int(1..3), q38 <= 3]), - and([a_ExplicitWithFlags_Flags[q1 + 1] > 0 -> a_ExplicitWithFlags_Values[q1] < a_ExplicitWithFlags_Values[q1 + 1] - | q1 : int(1..2)]), - and([a_ExplicitWithFlags_Flags[q2] = 0 -> a_ExplicitWithFlags_Values[q2] = 1 | q2 : int(1..3)]), - and([a_ExplicitWithFlags_Flags[q3 + 1] > 0 -> a_ExplicitWithFlags_Flags[q3] > 0 | q3 : int(1..2)]), - 3 = sum([a_ExplicitWithFlags_Flags[q5] | q5 : int(1..3)]), - and([b_ExplicitWithRepetition_Values[q7] <= b_ExplicitWithRepetition_Values[q7 + 1] | q7 : int(1..2), q7 + 1 <= 3]), - and([a_ExplicitWithRepetition_Values[q12] <= a_ExplicitWithRepetition_Values[q12 + 1] - | q12 : int(1..2), q12 + 1 <= 3]), - and([sum([toInt(a_ExplicitWithRepetition_Values[q21] = a_ExplicitWithRepetition_Values[q18]) - | q21 : int(1..3), q21 <= 3]) - = - sum([toInt(a_ExplicitWithFlags_Values[q19] = a_ExplicitWithRepetition_Values[q18]) * - catchUndef(a_ExplicitWithFlags_Flags[q19], 0) - | q19 : int(1..3)]) - | q18 : int(1..3), q18 <= 3]), - and([a_ExplicitWithFlags_Flags[q22] > 0 -> - sum([toInt(a_ExplicitWithRepetition_Values[q25] = a_ExplicitWithFlags_Values[q22]) - | q25 : int(1..3), q25 <= 3]) - = - sum([toInt(a_ExplicitWithFlags_Values[q23] = a_ExplicitWithFlags_Values[q22]) * - catchUndef(a_ExplicitWithFlags_Flags[q23], 0) - | q23 : int(1..3)]) - | q22 : int(1..3)]) - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_2_3-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_2_3-solution000001.solution deleted file mode 100644 index 621d5f6edc..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_2_3-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 1, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_2_3-solution000002.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_2_3-solution000002.solution deleted file mode 100644 index 5e2caa751c..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_2_3-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 2, 2) -letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_2_3-solution000003.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_2_3-solution000003.solution deleted file mode 100644 index 1b4b5b08a6..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_2_3-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 2, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_2_3-solution000004.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_2_3-solution000004.solution deleted file mode 100644 index 15472caf03..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_2_3-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 2, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_2_3-solution000005.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_2_3-solution000005.solution deleted file mode 100644 index ff56905e23..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_2_3-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_2_3-solution000006.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_2_3-solution000006.solution deleted file mode 100644 index d56a0bbcdc..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_2_3-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_2_3.eprime b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_2_3.eprime deleted file mode 100644 index 94bac3725f..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_2_3.eprime +++ /dev/null @@ -1,112 +0,0 @@ -language ESSENCE' 1.0 - -find a_ExplicitWithFlags_Flags: matrix indexed by [int(1..3)] of int(0..3) -find a_ExplicitWithFlags_Values: matrix indexed by [int(1..3)] of int(1..2) -find a_ExplicitWithRepetition_Flag: int(3) -find a_ExplicitWithRepetition_Values: matrix indexed by [int(1..3)] of int(1..2) -find b_ExplicitWithRepetition_Flag: int(3) -find b_ExplicitWithRepetition_Values: matrix indexed by [int(1..3)] of int(1..2) -find b_MOccurrence: matrix indexed by [int(1..2)] of int(0..3) -branching on - [a_ExplicitWithRepetition_Flag, a_ExplicitWithRepetition_Values, a_ExplicitWithFlags_Flags, - a_ExplicitWithFlags_Values, b_MOccurrence, b_ExplicitWithRepetition_Flag, b_ExplicitWithRepetition_Values] -such that - or([a_ExplicitWithFlags_Flags[q49] > 0 /\ - (sum([toInt(a_ExplicitWithFlags_Values[q36] = a_ExplicitWithFlags_Values[q49]) * - catchUndef(a_ExplicitWithFlags_Flags[q36], 0) - | q36 : int(1..3)]) - < - sum([toInt(b_ExplicitWithRepetition_Values[q38] = a_ExplicitWithFlags_Values[q49]) - | q38 : int(1..3), q38 <= 3]) - /\ - (and([a_ExplicitWithFlags_Flags[q45] > 0 /\ a_ExplicitWithFlags_Values[q45] < a_ExplicitWithFlags_Values[q49] - -> - sum([toInt(a_ExplicitWithFlags_Values[q39] = a_ExplicitWithFlags_Values[q45]) * - catchUndef(a_ExplicitWithFlags_Flags[q39], 0) - | q39 : int(1..3)]) - = - sum([toInt(b_ExplicitWithRepetition_Values[q41] = a_ExplicitWithFlags_Values[q45]) - | q41 : int(1..3), q41 <= 3]) - | q45 : int(1..3)]) - /\ - and([!or([a_ExplicitWithFlags_Flags[q44] > 0 /\ - a_ExplicitWithFlags_Values[q44] = b_ExplicitWithRepetition_Values[q42] - | q44 : int(1..3)]) - /\ b_ExplicitWithRepetition_Values[q42] < a_ExplicitWithFlags_Values[q49] - -> - sum([toInt(a_ExplicitWithFlags_Values[q39] = b_ExplicitWithRepetition_Values[q42]) * - catchUndef(a_ExplicitWithFlags_Flags[q39], 0) - | q39 : int(1..3)]) - = - sum([toInt(b_ExplicitWithRepetition_Values[q41] = b_ExplicitWithRepetition_Values[q42]) - | q41 : int(1..3), q41 <= 3]) - | q42 : int(1..3), q42 <= 3]))) - | q49 : int(1..3)]) - \/ - or([!or([a_ExplicitWithFlags_Flags[q48] > 0 /\ - a_ExplicitWithFlags_Values[q48] = b_ExplicitWithRepetition_Values[q46] - | q48 : int(1..3)]) - /\ - (sum([toInt(a_ExplicitWithFlags_Values[q36] = b_ExplicitWithRepetition_Values[q46]) * - catchUndef(a_ExplicitWithFlags_Flags[q36], 0) - | q36 : int(1..3)]) - < - sum([toInt(b_ExplicitWithRepetition_Values[q38] = b_ExplicitWithRepetition_Values[q46]) - | q38 : int(1..3), q38 <= 3]) - /\ - (and([a_ExplicitWithFlags_Flags[q45] > 0 /\ - a_ExplicitWithFlags_Values[q45] < b_ExplicitWithRepetition_Values[q46] - -> - sum([toInt(a_ExplicitWithFlags_Values[q39] = a_ExplicitWithFlags_Values[q45]) * - catchUndef(a_ExplicitWithFlags_Flags[q39], 0) - | q39 : int(1..3)]) - = - sum([toInt(b_ExplicitWithRepetition_Values[q41] = a_ExplicitWithFlags_Values[q45]) - | q41 : int(1..3), q41 <= 3]) - | q45 : int(1..3)]) - /\ - and([!or([a_ExplicitWithFlags_Flags[q44] > 0 /\ - a_ExplicitWithFlags_Values[q44] = b_ExplicitWithRepetition_Values[q42] - | q44 : int(1..3)]) - /\ b_ExplicitWithRepetition_Values[q42] < b_ExplicitWithRepetition_Values[q46] - -> - sum([toInt(a_ExplicitWithFlags_Values[q39] = b_ExplicitWithRepetition_Values[q42]) * - catchUndef(a_ExplicitWithFlags_Flags[q39], 0) - | q39 : int(1..3)]) - = - sum([toInt(b_ExplicitWithRepetition_Values[q41] = b_ExplicitWithRepetition_Values[q42]) - | q41 : int(1..3), q41 <= 3]) - | q42 : int(1..3), q42 <= 3]))) - | q46 : int(1..3), q46 <= 3]), - and([a_ExplicitWithFlags_Flags[q1 + 1] > 0 -> a_ExplicitWithFlags_Values[q1] < a_ExplicitWithFlags_Values[q1 + 1] - | q1 : int(1..2)]), - and([a_ExplicitWithFlags_Flags[q2] = 0 -> a_ExplicitWithFlags_Values[q2] = 1 | q2 : int(1..3)]), - and([a_ExplicitWithFlags_Flags[q3 + 1] > 0 -> a_ExplicitWithFlags_Flags[q3] > 0 | q3 : int(1..2)]), - 3 = sum([a_ExplicitWithFlags_Flags[q5] | q5 : int(1..3)]), - and([b_ExplicitWithRepetition_Values[q7] <= b_ExplicitWithRepetition_Values[q7 + 1] | q7 : int(1..2), q7 + 1 <= 3]), - and([a_ExplicitWithRepetition_Values[q12] <= a_ExplicitWithRepetition_Values[q12 + 1] - | q12 : int(1..2), q12 + 1 <= 3]), - and([sum([toInt(a_ExplicitWithRepetition_Values[q21] = a_ExplicitWithRepetition_Values[q18]) - | q21 : int(1..3), q21 <= 3]) - = - sum([toInt(a_ExplicitWithFlags_Values[q19] = a_ExplicitWithRepetition_Values[q18]) * - catchUndef(a_ExplicitWithFlags_Flags[q19], 0) - | q19 : int(1..3)]) - | q18 : int(1..3), q18 <= 3]), - and([a_ExplicitWithFlags_Flags[q22] > 0 -> - sum([toInt(a_ExplicitWithRepetition_Values[q25] = a_ExplicitWithFlags_Values[q22]) - | q25 : int(1..3), q25 <= 3]) - = - sum([toInt(a_ExplicitWithFlags_Values[q23] = a_ExplicitWithFlags_Values[q22]) * - catchUndef(a_ExplicitWithFlags_Flags[q23], 0) - | q23 : int(1..3)]) - | q22 : int(1..3)]), - 3 = sum([b_MOccurrence[q26] | q26 : int(1..2)]), - and([b_MOccurrence[q28] > 0 -> - b_MOccurrence[q28] = sum([toInt(b_ExplicitWithRepetition_Values[q30] = q28) | q30 : int(1..3), q30 <= 3]) - | q28 : int(1..2)]), - and([b_MOccurrence[b_ExplicitWithRepetition_Values[q31]] = - sum([toInt(b_ExplicitWithRepetition_Values[q33] = b_ExplicitWithRepetition_Values[q31]) - | q33 : int(1..3), q33 <= 3]) - | q31 : int(1..3), q31 <= 3]) - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_3_1-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_3_1-solution000001.solution deleted file mode 100644 index 15472caf03..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_3_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 2, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_3_1-solution000002.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_3_1-solution000002.solution deleted file mode 100644 index ff56905e23..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_3_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_3_1-solution000003.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_3_1-solution000003.solution deleted file mode 100644 index d56a0bbcdc..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_3_1-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_3_1-solution000004.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_3_1-solution000004.solution deleted file mode 100644 index 5e2caa751c..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_3_1-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 2, 2) -letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_3_1-solution000005.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_3_1-solution000005.solution deleted file mode 100644 index 1b4b5b08a6..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_3_1-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 2, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_3_1-solution000006.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_3_1-solution000006.solution deleted file mode 100644 index 621d5f6edc..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_3_1-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 1, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_3_1.eprime b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_3_1.eprime deleted file mode 100644 index 1f4a2dfef0..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_3_1.eprime +++ /dev/null @@ -1,119 +0,0 @@ -language ESSENCE' 1.0 - -find a_ExplicitWithFlags_Flags: matrix indexed by [int(1..3)] of int(0..3) -find a_ExplicitWithFlags_Values: matrix indexed by [int(1..3)] of int(1..2) -find a_MOccurrence: matrix indexed by [int(1..2)] of int(0..3) -find b_ExplicitWithRepetition_Flag: int(3) -find b_ExplicitWithRepetition_Values: matrix indexed by [int(1..3)] of int(1..2) -find b_ExplicitWithFlags_Flags: matrix indexed by [int(1..3)] of int(0..3) -find b_ExplicitWithFlags_Values: matrix indexed by [int(1..3)] of int(1..2) -branching on - [a_MOccurrence, a_ExplicitWithFlags_Flags, a_ExplicitWithFlags_Values, b_ExplicitWithFlags_Flags, - b_ExplicitWithFlags_Values, b_ExplicitWithRepetition_Flag, b_ExplicitWithRepetition_Values] -such that - or([a_ExplicitWithFlags_Flags[q48] > 0 /\ - (sum([toInt(a_ExplicitWithFlags_Values[q35] = a_ExplicitWithFlags_Values[q48]) * - catchUndef(a_ExplicitWithFlags_Flags[q35], 0) - | q35 : int(1..3)]) - < - sum([toInt(b_ExplicitWithRepetition_Values[q37] = a_ExplicitWithFlags_Values[q48]) - | q37 : int(1..3), q37 <= 3]) - /\ - (and([a_ExplicitWithFlags_Flags[q44] > 0 /\ a_ExplicitWithFlags_Values[q44] < a_ExplicitWithFlags_Values[q48] - -> - sum([toInt(a_ExplicitWithFlags_Values[q38] = a_ExplicitWithFlags_Values[q44]) * - catchUndef(a_ExplicitWithFlags_Flags[q38], 0) - | q38 : int(1..3)]) - = - sum([toInt(b_ExplicitWithRepetition_Values[q40] = a_ExplicitWithFlags_Values[q44]) - | q40 : int(1..3), q40 <= 3]) - | q44 : int(1..3)]) - /\ - and([!or([a_ExplicitWithFlags_Flags[q43] > 0 /\ - a_ExplicitWithFlags_Values[q43] = b_ExplicitWithRepetition_Values[q41] - | q43 : int(1..3)]) - /\ b_ExplicitWithRepetition_Values[q41] < a_ExplicitWithFlags_Values[q48] - -> - sum([toInt(a_ExplicitWithFlags_Values[q38] = b_ExplicitWithRepetition_Values[q41]) * - catchUndef(a_ExplicitWithFlags_Flags[q38], 0) - | q38 : int(1..3)]) - = - sum([toInt(b_ExplicitWithRepetition_Values[q40] = b_ExplicitWithRepetition_Values[q41]) - | q40 : int(1..3), q40 <= 3]) - | q41 : int(1..3), q41 <= 3]))) - | q48 : int(1..3)]) - \/ - or([!or([a_ExplicitWithFlags_Flags[q47] > 0 /\ - a_ExplicitWithFlags_Values[q47] = b_ExplicitWithRepetition_Values[q45] - | q47 : int(1..3)]) - /\ - (sum([toInt(a_ExplicitWithFlags_Values[q35] = b_ExplicitWithRepetition_Values[q45]) * - catchUndef(a_ExplicitWithFlags_Flags[q35], 0) - | q35 : int(1..3)]) - < - sum([toInt(b_ExplicitWithRepetition_Values[q37] = b_ExplicitWithRepetition_Values[q45]) - | q37 : int(1..3), q37 <= 3]) - /\ - (and([a_ExplicitWithFlags_Flags[q44] > 0 /\ - a_ExplicitWithFlags_Values[q44] < b_ExplicitWithRepetition_Values[q45] - -> - sum([toInt(a_ExplicitWithFlags_Values[q38] = a_ExplicitWithFlags_Values[q44]) * - catchUndef(a_ExplicitWithFlags_Flags[q38], 0) - | q38 : int(1..3)]) - = - sum([toInt(b_ExplicitWithRepetition_Values[q40] = a_ExplicitWithFlags_Values[q44]) - | q40 : int(1..3), q40 <= 3]) - | q44 : int(1..3)]) - /\ - and([!or([a_ExplicitWithFlags_Flags[q43] > 0 /\ - a_ExplicitWithFlags_Values[q43] = b_ExplicitWithRepetition_Values[q41] - | q43 : int(1..3)]) - /\ b_ExplicitWithRepetition_Values[q41] < b_ExplicitWithRepetition_Values[q45] - -> - sum([toInt(a_ExplicitWithFlags_Values[q38] = b_ExplicitWithRepetition_Values[q41]) * - catchUndef(a_ExplicitWithFlags_Flags[q38], 0) - | q38 : int(1..3)]) - = - sum([toInt(b_ExplicitWithRepetition_Values[q40] = b_ExplicitWithRepetition_Values[q41]) - | q40 : int(1..3), q40 <= 3]) - | q41 : int(1..3), q41 <= 3]))) - | q45 : int(1..3), q45 <= 3]), - and([a_ExplicitWithFlags_Flags[q1 + 1] > 0 -> a_ExplicitWithFlags_Values[q1] < a_ExplicitWithFlags_Values[q1 + 1] - | q1 : int(1..2)]), - and([a_ExplicitWithFlags_Flags[q2] = 0 -> a_ExplicitWithFlags_Values[q2] = 1 | q2 : int(1..3)]), - and([a_ExplicitWithFlags_Flags[q3 + 1] > 0 -> a_ExplicitWithFlags_Flags[q3] > 0 | q3 : int(1..2)]), - 3 = sum([a_ExplicitWithFlags_Flags[q5] | q5 : int(1..3)]), - and([b_ExplicitWithRepetition_Values[q7] <= b_ExplicitWithRepetition_Values[q7 + 1] | q7 : int(1..2), q7 + 1 <= 3]), - 3 = sum([a_MOccurrence[q12] | q12 : int(1..2)]), - and([a_MOccurrence[q29] > 0 -> - a_MOccurrence[q29] = - sum([toInt(a_ExplicitWithFlags_Values[q30] = q29) * catchUndef(a_ExplicitWithFlags_Flags[q30], 0) - | q30 : int(1..3)]) - | q29 : int(1..2)]), - and([a_ExplicitWithFlags_Flags[q31] > 0 -> - a_MOccurrence[a_ExplicitWithFlags_Values[q31]] = - sum([toInt(a_ExplicitWithFlags_Values[q32] = a_ExplicitWithFlags_Values[q31]) * - catchUndef(a_ExplicitWithFlags_Flags[q32], 0) - | q32 : int(1..3)]) - | q31 : int(1..3)]), - and([b_ExplicitWithFlags_Flags[q13 + 1] > 0 -> b_ExplicitWithFlags_Values[q13] < b_ExplicitWithFlags_Values[q13 + 1] - | q13 : int(1..2)]), - and([b_ExplicitWithFlags_Flags[q14] = 0 -> b_ExplicitWithFlags_Values[q14] = 1 | q14 : int(1..3)]), - and([b_ExplicitWithFlags_Flags[q15 + 1] > 0 -> b_ExplicitWithFlags_Flags[q15] > 0 | q15 : int(1..2)]), - 3 = sum([b_ExplicitWithFlags_Flags[q17] | q17 : int(1..3)]), - and([b_ExplicitWithFlags_Flags[q20] > 0 -> - sum([toInt(b_ExplicitWithFlags_Values[q21] = b_ExplicitWithFlags_Values[q20]) * - catchUndef(b_ExplicitWithFlags_Flags[q21], 0) - | q21 : int(1..3)]) - = - sum([toInt(b_ExplicitWithRepetition_Values[q23] = b_ExplicitWithFlags_Values[q20]) - | q23 : int(1..3), q23 <= 3]) - | q20 : int(1..3)]), - and([sum([toInt(b_ExplicitWithFlags_Values[q25] = b_ExplicitWithRepetition_Values[q24]) * - catchUndef(b_ExplicitWithFlags_Flags[q25], 0) - | q25 : int(1..3)]) - = - sum([toInt(b_ExplicitWithRepetition_Values[q27] = b_ExplicitWithRepetition_Values[q24]) - | q27 : int(1..3), q27 <= 3]) - | q24 : int(1..3), q24 <= 3]) - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_3_2-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_3_2-solution000001.solution deleted file mode 100644 index d56a0bbcdc..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_3_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_3_2-solution000002.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_3_2-solution000002.solution deleted file mode 100644 index ff56905e23..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_3_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_3_2-solution000003.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_3_2-solution000003.solution deleted file mode 100644 index 15472caf03..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_3_2-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 2, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_3_2-solution000004.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_3_2-solution000004.solution deleted file mode 100644 index 1b4b5b08a6..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_3_2-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 2, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_3_2-solution000005.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_3_2-solution000005.solution deleted file mode 100644 index 5e2caa751c..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_3_2-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 2, 2) -letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_3_2-solution000006.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_3_2-solution000006.solution deleted file mode 100644 index 621d5f6edc..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_3_2-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 1, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_3_2.eprime b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_3_2.eprime deleted file mode 100644 index 2bf8ae12e5..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_3_2.eprime +++ /dev/null @@ -1,97 +0,0 @@ -language ESSENCE' 1.0 - -find a_ExplicitWithFlags_Flags: matrix indexed by [int(1..3)] of int(0..3) -find a_ExplicitWithFlags_Values: matrix indexed by [int(1..3)] of int(1..2) -find a_MOccurrence: matrix indexed by [int(1..2)] of int(0..3) -find b_ExplicitWithRepetition_Flag: int(3) -find b_ExplicitWithRepetition_Values: matrix indexed by [int(1..3)] of int(1..2) -branching on - [a_MOccurrence, a_ExplicitWithFlags_Flags, a_ExplicitWithFlags_Values, b_ExplicitWithRepetition_Flag, - b_ExplicitWithRepetition_Values] -such that - or([a_ExplicitWithFlags_Flags[q33] > 0 /\ - (sum([toInt(a_ExplicitWithFlags_Values[q20] = a_ExplicitWithFlags_Values[q33]) * - catchUndef(a_ExplicitWithFlags_Flags[q20], 0) - | q20 : int(1..3)]) - < - sum([toInt(b_ExplicitWithRepetition_Values[q22] = a_ExplicitWithFlags_Values[q33]) - | q22 : int(1..3), q22 <= 3]) - /\ - (and([a_ExplicitWithFlags_Flags[q29] > 0 /\ a_ExplicitWithFlags_Values[q29] < a_ExplicitWithFlags_Values[q33] - -> - sum([toInt(a_ExplicitWithFlags_Values[q23] = a_ExplicitWithFlags_Values[q29]) * - catchUndef(a_ExplicitWithFlags_Flags[q23], 0) - | q23 : int(1..3)]) - = - sum([toInt(b_ExplicitWithRepetition_Values[q25] = a_ExplicitWithFlags_Values[q29]) - | q25 : int(1..3), q25 <= 3]) - | q29 : int(1..3)]) - /\ - and([!or([a_ExplicitWithFlags_Flags[q28] > 0 /\ - a_ExplicitWithFlags_Values[q28] = b_ExplicitWithRepetition_Values[q26] - | q28 : int(1..3)]) - /\ b_ExplicitWithRepetition_Values[q26] < a_ExplicitWithFlags_Values[q33] - -> - sum([toInt(a_ExplicitWithFlags_Values[q23] = b_ExplicitWithRepetition_Values[q26]) * - catchUndef(a_ExplicitWithFlags_Flags[q23], 0) - | q23 : int(1..3)]) - = - sum([toInt(b_ExplicitWithRepetition_Values[q25] = b_ExplicitWithRepetition_Values[q26]) - | q25 : int(1..3), q25 <= 3]) - | q26 : int(1..3), q26 <= 3]))) - | q33 : int(1..3)]) - \/ - or([!or([a_ExplicitWithFlags_Flags[q32] > 0 /\ - a_ExplicitWithFlags_Values[q32] = b_ExplicitWithRepetition_Values[q30] - | q32 : int(1..3)]) - /\ - (sum([toInt(a_ExplicitWithFlags_Values[q20] = b_ExplicitWithRepetition_Values[q30]) * - catchUndef(a_ExplicitWithFlags_Flags[q20], 0) - | q20 : int(1..3)]) - < - sum([toInt(b_ExplicitWithRepetition_Values[q22] = b_ExplicitWithRepetition_Values[q30]) - | q22 : int(1..3), q22 <= 3]) - /\ - (and([a_ExplicitWithFlags_Flags[q29] > 0 /\ - a_ExplicitWithFlags_Values[q29] < b_ExplicitWithRepetition_Values[q30] - -> - sum([toInt(a_ExplicitWithFlags_Values[q23] = a_ExplicitWithFlags_Values[q29]) * - catchUndef(a_ExplicitWithFlags_Flags[q23], 0) - | q23 : int(1..3)]) - = - sum([toInt(b_ExplicitWithRepetition_Values[q25] = a_ExplicitWithFlags_Values[q29]) - | q25 : int(1..3), q25 <= 3]) - | q29 : int(1..3)]) - /\ - and([!or([a_ExplicitWithFlags_Flags[q28] > 0 /\ - a_ExplicitWithFlags_Values[q28] = b_ExplicitWithRepetition_Values[q26] - | q28 : int(1..3)]) - /\ b_ExplicitWithRepetition_Values[q26] < b_ExplicitWithRepetition_Values[q30] - -> - sum([toInt(a_ExplicitWithFlags_Values[q23] = b_ExplicitWithRepetition_Values[q26]) * - catchUndef(a_ExplicitWithFlags_Flags[q23], 0) - | q23 : int(1..3)]) - = - sum([toInt(b_ExplicitWithRepetition_Values[q25] = b_ExplicitWithRepetition_Values[q26]) - | q25 : int(1..3), q25 <= 3]) - | q26 : int(1..3), q26 <= 3]))) - | q30 : int(1..3), q30 <= 3]), - and([a_ExplicitWithFlags_Flags[q1 + 1] > 0 -> a_ExplicitWithFlags_Values[q1] < a_ExplicitWithFlags_Values[q1 + 1] - | q1 : int(1..2)]), - and([a_ExplicitWithFlags_Flags[q2] = 0 -> a_ExplicitWithFlags_Values[q2] = 1 | q2 : int(1..3)]), - and([a_ExplicitWithFlags_Flags[q3 + 1] > 0 -> a_ExplicitWithFlags_Flags[q3] > 0 | q3 : int(1..2)]), - 3 = sum([a_ExplicitWithFlags_Flags[q5] | q5 : int(1..3)]), - and([b_ExplicitWithRepetition_Values[q7] <= b_ExplicitWithRepetition_Values[q7 + 1] | q7 : int(1..2), q7 + 1 <= 3]), - 3 = sum([a_MOccurrence[q12] | q12 : int(1..2)]), - and([a_MOccurrence[q14] > 0 -> - a_MOccurrence[q14] = - sum([toInt(a_ExplicitWithFlags_Values[q15] = q14) * catchUndef(a_ExplicitWithFlags_Flags[q15], 0) - | q15 : int(1..3)]) - | q14 : int(1..2)]), - and([a_ExplicitWithFlags_Flags[q16] > 0 -> - a_MOccurrence[a_ExplicitWithFlags_Values[q16]] = - sum([toInt(a_ExplicitWithFlags_Values[q17] = a_ExplicitWithFlags_Values[q16]) * - catchUndef(a_ExplicitWithFlags_Flags[q17], 0) - | q17 : int(1..3)]) - | q16 : int(1..3)]) - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_3_3-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_3_3-solution000001.solution deleted file mode 100644 index 15472caf03..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_3_3-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 2, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_3_3-solution000002.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_3_3-solution000002.solution deleted file mode 100644 index ff56905e23..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_3_3-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_3_3-solution000003.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_3_3-solution000003.solution deleted file mode 100644 index d56a0bbcdc..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_3_3-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_3_3-solution000004.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_3_3-solution000004.solution deleted file mode 100644 index 5e2caa751c..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_3_3-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 2, 2) -letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_3_3-solution000005.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_3_3-solution000005.solution deleted file mode 100644 index 1b4b5b08a6..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_3_3-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 2, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_3_3-solution000006.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_3_3-solution000006.solution deleted file mode 100644 index 621d5f6edc..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_3_3-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 1, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_3_3.eprime b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_3_3.eprime deleted file mode 100644 index 29ca3bbb8f..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_3_3.eprime +++ /dev/null @@ -1,106 +0,0 @@ -language ESSENCE' 1.0 - -find a_ExplicitWithFlags_Flags: matrix indexed by [int(1..3)] of int(0..3) -find a_ExplicitWithFlags_Values: matrix indexed by [int(1..3)] of int(1..2) -find a_MOccurrence: matrix indexed by [int(1..2)] of int(0..3) -find b_ExplicitWithRepetition_Flag: int(3) -find b_ExplicitWithRepetition_Values: matrix indexed by [int(1..3)] of int(1..2) -find b_MOccurrence: matrix indexed by [int(1..2)] of int(0..3) -branching on - [a_MOccurrence, a_ExplicitWithFlags_Flags, a_ExplicitWithFlags_Values, b_MOccurrence, b_ExplicitWithRepetition_Flag, - b_ExplicitWithRepetition_Values] -such that - or([a_ExplicitWithFlags_Flags[q41] > 0 /\ - (sum([toInt(a_ExplicitWithFlags_Values[q28] = a_ExplicitWithFlags_Values[q41]) * - catchUndef(a_ExplicitWithFlags_Flags[q28], 0) - | q28 : int(1..3)]) - < - sum([toInt(b_ExplicitWithRepetition_Values[q30] = a_ExplicitWithFlags_Values[q41]) - | q30 : int(1..3), q30 <= 3]) - /\ - (and([a_ExplicitWithFlags_Flags[q37] > 0 /\ a_ExplicitWithFlags_Values[q37] < a_ExplicitWithFlags_Values[q41] - -> - sum([toInt(a_ExplicitWithFlags_Values[q31] = a_ExplicitWithFlags_Values[q37]) * - catchUndef(a_ExplicitWithFlags_Flags[q31], 0) - | q31 : int(1..3)]) - = - sum([toInt(b_ExplicitWithRepetition_Values[q33] = a_ExplicitWithFlags_Values[q37]) - | q33 : int(1..3), q33 <= 3]) - | q37 : int(1..3)]) - /\ - and([!or([a_ExplicitWithFlags_Flags[q36] > 0 /\ - a_ExplicitWithFlags_Values[q36] = b_ExplicitWithRepetition_Values[q34] - | q36 : int(1..3)]) - /\ b_ExplicitWithRepetition_Values[q34] < a_ExplicitWithFlags_Values[q41] - -> - sum([toInt(a_ExplicitWithFlags_Values[q31] = b_ExplicitWithRepetition_Values[q34]) * - catchUndef(a_ExplicitWithFlags_Flags[q31], 0) - | q31 : int(1..3)]) - = - sum([toInt(b_ExplicitWithRepetition_Values[q33] = b_ExplicitWithRepetition_Values[q34]) - | q33 : int(1..3), q33 <= 3]) - | q34 : int(1..3), q34 <= 3]))) - | q41 : int(1..3)]) - \/ - or([!or([a_ExplicitWithFlags_Flags[q40] > 0 /\ - a_ExplicitWithFlags_Values[q40] = b_ExplicitWithRepetition_Values[q38] - | q40 : int(1..3)]) - /\ - (sum([toInt(a_ExplicitWithFlags_Values[q28] = b_ExplicitWithRepetition_Values[q38]) * - catchUndef(a_ExplicitWithFlags_Flags[q28], 0) - | q28 : int(1..3)]) - < - sum([toInt(b_ExplicitWithRepetition_Values[q30] = b_ExplicitWithRepetition_Values[q38]) - | q30 : int(1..3), q30 <= 3]) - /\ - (and([a_ExplicitWithFlags_Flags[q37] > 0 /\ - a_ExplicitWithFlags_Values[q37] < b_ExplicitWithRepetition_Values[q38] - -> - sum([toInt(a_ExplicitWithFlags_Values[q31] = a_ExplicitWithFlags_Values[q37]) * - catchUndef(a_ExplicitWithFlags_Flags[q31], 0) - | q31 : int(1..3)]) - = - sum([toInt(b_ExplicitWithRepetition_Values[q33] = a_ExplicitWithFlags_Values[q37]) - | q33 : int(1..3), q33 <= 3]) - | q37 : int(1..3)]) - /\ - and([!or([a_ExplicitWithFlags_Flags[q36] > 0 /\ - a_ExplicitWithFlags_Values[q36] = b_ExplicitWithRepetition_Values[q34] - | q36 : int(1..3)]) - /\ b_ExplicitWithRepetition_Values[q34] < b_ExplicitWithRepetition_Values[q38] - -> - sum([toInt(a_ExplicitWithFlags_Values[q31] = b_ExplicitWithRepetition_Values[q34]) * - catchUndef(a_ExplicitWithFlags_Flags[q31], 0) - | q31 : int(1..3)]) - = - sum([toInt(b_ExplicitWithRepetition_Values[q33] = b_ExplicitWithRepetition_Values[q34]) - | q33 : int(1..3), q33 <= 3]) - | q34 : int(1..3), q34 <= 3]))) - | q38 : int(1..3), q38 <= 3]), - and([a_ExplicitWithFlags_Flags[q1 + 1] > 0 -> a_ExplicitWithFlags_Values[q1] < a_ExplicitWithFlags_Values[q1 + 1] - | q1 : int(1..2)]), - and([a_ExplicitWithFlags_Flags[q2] = 0 -> a_ExplicitWithFlags_Values[q2] = 1 | q2 : int(1..3)]), - and([a_ExplicitWithFlags_Flags[q3 + 1] > 0 -> a_ExplicitWithFlags_Flags[q3] > 0 | q3 : int(1..2)]), - 3 = sum([a_ExplicitWithFlags_Flags[q5] | q5 : int(1..3)]), - and([b_ExplicitWithRepetition_Values[q7] <= b_ExplicitWithRepetition_Values[q7 + 1] | q7 : int(1..2), q7 + 1 <= 3]), - 3 = sum([a_MOccurrence[q12] | q12 : int(1..2)]), - and([a_MOccurrence[q22] > 0 -> - a_MOccurrence[q22] = - sum([toInt(a_ExplicitWithFlags_Values[q23] = q22) * catchUndef(a_ExplicitWithFlags_Flags[q23], 0) - | q23 : int(1..3)]) - | q22 : int(1..2)]), - and([a_ExplicitWithFlags_Flags[q24] > 0 -> - a_MOccurrence[a_ExplicitWithFlags_Values[q24]] = - sum([toInt(a_ExplicitWithFlags_Values[q25] = a_ExplicitWithFlags_Values[q24]) * - catchUndef(a_ExplicitWithFlags_Flags[q25], 0) - | q25 : int(1..3)]) - | q24 : int(1..3)]), - 3 = sum([b_MOccurrence[q13] | q13 : int(1..2)]), - and([b_MOccurrence[q15] > 0 -> - b_MOccurrence[q15] = sum([toInt(b_ExplicitWithRepetition_Values[q17] = q15) | q17 : int(1..3), q17 <= 3]) - | q15 : int(1..2)]), - and([b_MOccurrence[b_ExplicitWithRepetition_Values[q18]] = - sum([toInt(b_ExplicitWithRepetition_Values[q20] = b_ExplicitWithRepetition_Values[q18]) - | q20 : int(1..3), q20 <= 3]) - | q18 : int(1..3), q18 <= 3]) - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_1_1-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_1_1-solution000001.solution deleted file mode 100644 index 5e2caa751c..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_1_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 2, 2) -letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_1_1-solution000002.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_1_1-solution000002.solution deleted file mode 100644 index 1b4b5b08a6..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_1_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 2, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_1_1-solution000003.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_1_1-solution000003.solution deleted file mode 100644 index 621d5f6edc..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_1_1-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 1, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_1_1-solution000004.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_1_1-solution000004.solution deleted file mode 100644 index 15472caf03..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_1_1-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 2, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_1_1-solution000005.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_1_1-solution000005.solution deleted file mode 100644 index ff56905e23..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_1_1-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_1_1-solution000006.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_1_1-solution000006.solution deleted file mode 100644 index d56a0bbcdc..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_1_1-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_1_1.eprime b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_1_1.eprime deleted file mode 100644 index af150f8e96..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_1_1.eprime +++ /dev/null @@ -1,80 +0,0 @@ -language ESSENCE' 1.0 - -find a_ExplicitWithFlags_Flags: matrix indexed by [int(1..3)] of int(0..3) -find a_ExplicitWithFlags_Values: matrix indexed by [int(1..3)] of int(1..2) -find b_MOccurrence: matrix indexed by [int(1..2)] of int(0..3) -find b_ExplicitWithFlags_Flags: matrix indexed by [int(1..3)] of int(0..3) -find b_ExplicitWithFlags_Values: matrix indexed by [int(1..3)] of int(1..2) -branching on - [a_ExplicitWithFlags_Flags, a_ExplicitWithFlags_Values, b_ExplicitWithFlags_Flags, b_ExplicitWithFlags_Values, - b_MOccurrence] -such that - or([a_ExplicitWithFlags_Flags[q29] > 0 /\ - (sum([toInt(a_ExplicitWithFlags_Values[q21] = a_ExplicitWithFlags_Values[q29]) * - catchUndef(a_ExplicitWithFlags_Flags[q21], 0) - | q21 : int(1..3)]) - < b_MOccurrence[a_ExplicitWithFlags_Values[q29]] - /\ - (and([a_ExplicitWithFlags_Flags[q25] > 0 /\ a_ExplicitWithFlags_Values[q25] < a_ExplicitWithFlags_Values[q29] - -> - sum([toInt(a_ExplicitWithFlags_Values[q22] = a_ExplicitWithFlags_Values[q25]) * - catchUndef(a_ExplicitWithFlags_Flags[q22], 0) - | q22 : int(1..3)]) - = b_MOccurrence[a_ExplicitWithFlags_Values[q25]] - | q25 : int(1..3)]) - /\ - and([q26 < a_ExplicitWithFlags_Values[q29] -> - (b_MOccurrence[q26] > 0 /\ - !or([a_ExplicitWithFlags_Flags[q24] > 0 /\ a_ExplicitWithFlags_Values[q24] = q26 | q24 : int(1..3)]) - -> - sum([toInt(a_ExplicitWithFlags_Values[q22] = q26) * catchUndef(a_ExplicitWithFlags_Flags[q22], 0) - | q22 : int(1..3)]) - = b_MOccurrence[q26]) - | q26 : int(1..2)]))) - | q29 : int(1..3)]) - \/ - or([b_MOccurrence[q30] > 0 /\ - !or([a_ExplicitWithFlags_Flags[q28] > 0 /\ a_ExplicitWithFlags_Values[q28] = q30 | q28 : int(1..3)]) - /\ - (sum([toInt(a_ExplicitWithFlags_Values[q21] = q30) * catchUndef(a_ExplicitWithFlags_Flags[q21], 0) - | q21 : int(1..3)]) - < b_MOccurrence[q30] - /\ - (and([a_ExplicitWithFlags_Flags[q25] > 0 /\ a_ExplicitWithFlags_Values[q25] < q30 -> - sum([toInt(a_ExplicitWithFlags_Values[q22] = a_ExplicitWithFlags_Values[q25]) * - catchUndef(a_ExplicitWithFlags_Flags[q22], 0) - | q22 : int(1..3)]) - = b_MOccurrence[a_ExplicitWithFlags_Values[q25]] - | q25 : int(1..3)]) - /\ - and([b_MOccurrence[q26] > 0 /\ - !or([a_ExplicitWithFlags_Flags[q24] > 0 /\ a_ExplicitWithFlags_Values[q24] = q26 | q24 : int(1..3)]) - -> - sum([toInt(a_ExplicitWithFlags_Values[q22] = q26) * catchUndef(a_ExplicitWithFlags_Flags[q22], 0) - | q22 : int(1..3)]) - = b_MOccurrence[q26] - | q26 : int(1..2), q26 < q30]))) - | q30 : int(1..2)]), - and([a_ExplicitWithFlags_Flags[q1 + 1] > 0 -> a_ExplicitWithFlags_Values[q1] < a_ExplicitWithFlags_Values[q1 + 1] - | q1 : int(1..2)]), - and([a_ExplicitWithFlags_Flags[q2] = 0 -> a_ExplicitWithFlags_Values[q2] = 1 | q2 : int(1..3)]), - and([a_ExplicitWithFlags_Flags[q3 + 1] > 0 -> a_ExplicitWithFlags_Flags[q3] > 0 | q3 : int(1..2)]), - 3 = sum([a_ExplicitWithFlags_Flags[q5] | q5 : int(1..3)]), - 3 = sum([b_MOccurrence[q7] | q7 : int(1..2)]), - and([b_ExplicitWithFlags_Flags[q8 + 1] > 0 -> b_ExplicitWithFlags_Values[q8] < b_ExplicitWithFlags_Values[q8 + 1] - | q8 : int(1..2)]), - and([b_ExplicitWithFlags_Flags[q9] = 0 -> b_ExplicitWithFlags_Values[q9] = 1 | q9 : int(1..3)]), - and([b_ExplicitWithFlags_Flags[q10 + 1] > 0 -> b_ExplicitWithFlags_Flags[q10] > 0 | q10 : int(1..2)]), - 3 = sum([b_ExplicitWithFlags_Flags[q12] | q12 : int(1..3)]), - and([b_ExplicitWithFlags_Flags[q15] > 0 -> - sum([toInt(b_ExplicitWithFlags_Values[q16] = b_ExplicitWithFlags_Values[q15]) * - catchUndef(b_ExplicitWithFlags_Flags[q16], 0) - | q16 : int(1..3)]) - = b_MOccurrence[b_ExplicitWithFlags_Values[q15]] - | q15 : int(1..3)]), - and([b_MOccurrence[q17] > 0 -> - sum([toInt(b_ExplicitWithFlags_Values[q18] = q17) * catchUndef(b_ExplicitWithFlags_Flags[q18], 0) - | q18 : int(1..3)]) - = b_MOccurrence[q17] - | q17 : int(1..2)]) - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_1_2-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_1_2-solution000001.solution deleted file mode 100644 index 1b4b5b08a6..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_1_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 2, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_1_2-solution000002.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_1_2-solution000002.solution deleted file mode 100644 index 5e2caa751c..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_1_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 2, 2) -letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_1_2-solution000003.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_1_2-solution000003.solution deleted file mode 100644 index 621d5f6edc..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_1_2-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 1, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_1_2-solution000004.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_1_2-solution000004.solution deleted file mode 100644 index d56a0bbcdc..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_1_2-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_1_2-solution000005.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_1_2-solution000005.solution deleted file mode 100644 index ff56905e23..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_1_2-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_1_2-solution000006.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_1_2-solution000006.solution deleted file mode 100644 index 15472caf03..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_1_2-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 2, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_1_2.eprime b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_1_2.eprime deleted file mode 100644 index 39a9f9859a..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_1_2.eprime +++ /dev/null @@ -1,72 +0,0 @@ -language ESSENCE' 1.0 - -find a_ExplicitWithFlags_Flags: matrix indexed by [int(1..3)] of int(0..3) -find a_ExplicitWithFlags_Values: matrix indexed by [int(1..3)] of int(1..2) -find b_MOccurrence: matrix indexed by [int(1..2)] of int(0..3) -find b_ExplicitWithRepetition_Flag: int(3) -find b_ExplicitWithRepetition_Values: matrix indexed by [int(1..3)] of int(1..2) -branching on - [a_ExplicitWithFlags_Flags, a_ExplicitWithFlags_Values, b_ExplicitWithRepetition_Flag, - b_ExplicitWithRepetition_Values, b_MOccurrence] -such that - or([a_ExplicitWithFlags_Flags[q30] > 0 /\ - (sum([toInt(a_ExplicitWithFlags_Values[q22] = a_ExplicitWithFlags_Values[q30]) * - catchUndef(a_ExplicitWithFlags_Flags[q22], 0) - | q22 : int(1..3)]) - < b_MOccurrence[a_ExplicitWithFlags_Values[q30]] - /\ - (and([a_ExplicitWithFlags_Flags[q26] > 0 /\ a_ExplicitWithFlags_Values[q26] < a_ExplicitWithFlags_Values[q30] - -> - sum([toInt(a_ExplicitWithFlags_Values[q23] = a_ExplicitWithFlags_Values[q26]) * - catchUndef(a_ExplicitWithFlags_Flags[q23], 0) - | q23 : int(1..3)]) - = b_MOccurrence[a_ExplicitWithFlags_Values[q26]] - | q26 : int(1..3)]) - /\ - and([q27 < a_ExplicitWithFlags_Values[q30] -> - (b_MOccurrence[q27] > 0 /\ - !or([a_ExplicitWithFlags_Flags[q25] > 0 /\ a_ExplicitWithFlags_Values[q25] = q27 | q25 : int(1..3)]) - -> - sum([toInt(a_ExplicitWithFlags_Values[q23] = q27) * catchUndef(a_ExplicitWithFlags_Flags[q23], 0) - | q23 : int(1..3)]) - = b_MOccurrence[q27]) - | q27 : int(1..2)]))) - | q30 : int(1..3)]) - \/ - or([b_MOccurrence[q31] > 0 /\ - !or([a_ExplicitWithFlags_Flags[q29] > 0 /\ a_ExplicitWithFlags_Values[q29] = q31 | q29 : int(1..3)]) - /\ - (sum([toInt(a_ExplicitWithFlags_Values[q22] = q31) * catchUndef(a_ExplicitWithFlags_Flags[q22], 0) - | q22 : int(1..3)]) - < b_MOccurrence[q31] - /\ - (and([a_ExplicitWithFlags_Flags[q26] > 0 /\ a_ExplicitWithFlags_Values[q26] < q31 -> - sum([toInt(a_ExplicitWithFlags_Values[q23] = a_ExplicitWithFlags_Values[q26]) * - catchUndef(a_ExplicitWithFlags_Flags[q23], 0) - | q23 : int(1..3)]) - = b_MOccurrence[a_ExplicitWithFlags_Values[q26]] - | q26 : int(1..3)]) - /\ - and([b_MOccurrence[q27] > 0 /\ - !or([a_ExplicitWithFlags_Flags[q25] > 0 /\ a_ExplicitWithFlags_Values[q25] = q27 | q25 : int(1..3)]) - -> - sum([toInt(a_ExplicitWithFlags_Values[q23] = q27) * catchUndef(a_ExplicitWithFlags_Flags[q23], 0) - | q23 : int(1..3)]) - = b_MOccurrence[q27] - | q27 : int(1..2), q27 < q31]))) - | q31 : int(1..2)]), - and([a_ExplicitWithFlags_Flags[q1 + 1] > 0 -> a_ExplicitWithFlags_Values[q1] < a_ExplicitWithFlags_Values[q1 + 1] - | q1 : int(1..2)]), - and([a_ExplicitWithFlags_Flags[q2] = 0 -> a_ExplicitWithFlags_Values[q2] = 1 | q2 : int(1..3)]), - and([a_ExplicitWithFlags_Flags[q3 + 1] > 0 -> a_ExplicitWithFlags_Flags[q3] > 0 | q3 : int(1..2)]), - 3 = sum([a_ExplicitWithFlags_Flags[q5] | q5 : int(1..3)]), - 3 = sum([b_MOccurrence[q7] | q7 : int(1..2)]), - and([b_ExplicitWithRepetition_Values[q8] <= b_ExplicitWithRepetition_Values[q8 + 1] | q8 : int(1..2), q8 + 1 <= 3]), - and([sum([toInt(b_ExplicitWithRepetition_Values[q16] = b_ExplicitWithRepetition_Values[q14]) - | q16 : int(1..3), q16 <= 3]) - = b_MOccurrence[b_ExplicitWithRepetition_Values[q14]] - | q14 : int(1..3), q14 <= 3]), - and([b_MOccurrence[q17] > 0 -> - sum([toInt(b_ExplicitWithRepetition_Values[q19] = q17) | q19 : int(1..3), q19 <= 3]) = b_MOccurrence[q17] - | q17 : int(1..2)]) - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_1_3-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_1_3-solution000001.solution deleted file mode 100644 index 5e2caa751c..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_1_3-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 2, 2) -letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_1_3-solution000002.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_1_3-solution000002.solution deleted file mode 100644 index 1b4b5b08a6..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_1_3-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 2, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_1_3-solution000003.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_1_3-solution000003.solution deleted file mode 100644 index 621d5f6edc..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_1_3-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 1, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_1_3-solution000004.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_1_3-solution000004.solution deleted file mode 100644 index 15472caf03..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_1_3-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 2, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_1_3-solution000005.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_1_3-solution000005.solution deleted file mode 100644 index ff56905e23..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_1_3-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_1_3-solution000006.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_1_3-solution000006.solution deleted file mode 100644 index d56a0bbcdc..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_1_3-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_1_3.eprime b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_1_3.eprime deleted file mode 100644 index 1e385fcdf4..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_1_3.eprime +++ /dev/null @@ -1,60 +0,0 @@ -language ESSENCE' 1.0 - -find a_ExplicitWithFlags_Flags: matrix indexed by [int(1..3)] of int(0..3) -find a_ExplicitWithFlags_Values: matrix indexed by [int(1..3)] of int(1..2) -find b_MOccurrence: matrix indexed by [int(1..2)] of int(0..3) -branching on [a_ExplicitWithFlags_Flags, a_ExplicitWithFlags_Values, b_MOccurrence] -such that - or([a_ExplicitWithFlags_Flags[q18] > 0 /\ - (sum([toInt(a_ExplicitWithFlags_Values[q10] = a_ExplicitWithFlags_Values[q18]) * - catchUndef(a_ExplicitWithFlags_Flags[q10], 0) - | q10 : int(1..3)]) - < b_MOccurrence[a_ExplicitWithFlags_Values[q18]] - /\ - (and([a_ExplicitWithFlags_Flags[q14] > 0 /\ a_ExplicitWithFlags_Values[q14] < a_ExplicitWithFlags_Values[q18] - -> - sum([toInt(a_ExplicitWithFlags_Values[q11] = a_ExplicitWithFlags_Values[q14]) * - catchUndef(a_ExplicitWithFlags_Flags[q11], 0) - | q11 : int(1..3)]) - = b_MOccurrence[a_ExplicitWithFlags_Values[q14]] - | q14 : int(1..3)]) - /\ - and([q15 < a_ExplicitWithFlags_Values[q18] -> - (b_MOccurrence[q15] > 0 /\ - !or([a_ExplicitWithFlags_Flags[q13] > 0 /\ a_ExplicitWithFlags_Values[q13] = q15 | q13 : int(1..3)]) - -> - sum([toInt(a_ExplicitWithFlags_Values[q11] = q15) * catchUndef(a_ExplicitWithFlags_Flags[q11], 0) - | q11 : int(1..3)]) - = b_MOccurrence[q15]) - | q15 : int(1..2)]))) - | q18 : int(1..3)]) - \/ - or([b_MOccurrence[q19] > 0 /\ - !or([a_ExplicitWithFlags_Flags[q17] > 0 /\ a_ExplicitWithFlags_Values[q17] = q19 | q17 : int(1..3)]) - /\ - (sum([toInt(a_ExplicitWithFlags_Values[q10] = q19) * catchUndef(a_ExplicitWithFlags_Flags[q10], 0) - | q10 : int(1..3)]) - < b_MOccurrence[q19] - /\ - (and([a_ExplicitWithFlags_Flags[q14] > 0 /\ a_ExplicitWithFlags_Values[q14] < q19 -> - sum([toInt(a_ExplicitWithFlags_Values[q11] = a_ExplicitWithFlags_Values[q14]) * - catchUndef(a_ExplicitWithFlags_Flags[q11], 0) - | q11 : int(1..3)]) - = b_MOccurrence[a_ExplicitWithFlags_Values[q14]] - | q14 : int(1..3)]) - /\ - and([b_MOccurrence[q15] > 0 /\ - !or([a_ExplicitWithFlags_Flags[q13] > 0 /\ a_ExplicitWithFlags_Values[q13] = q15 | q13 : int(1..3)]) - -> - sum([toInt(a_ExplicitWithFlags_Values[q11] = q15) * catchUndef(a_ExplicitWithFlags_Flags[q11], 0) - | q11 : int(1..3)]) - = b_MOccurrence[q15] - | q15 : int(1..2), q15 < q19]))) - | q19 : int(1..2)]), - and([a_ExplicitWithFlags_Flags[q1 + 1] > 0 -> a_ExplicitWithFlags_Values[q1] < a_ExplicitWithFlags_Values[q1 + 1] - | q1 : int(1..2)]), - and([a_ExplicitWithFlags_Flags[q2] = 0 -> a_ExplicitWithFlags_Values[q2] = 1 | q2 : int(1..3)]), - and([a_ExplicitWithFlags_Flags[q3 + 1] > 0 -> a_ExplicitWithFlags_Flags[q3] > 0 | q3 : int(1..2)]), - 3 = sum([a_ExplicitWithFlags_Flags[q5] | q5 : int(1..3)]), - 3 = sum([b_MOccurrence[q7] | q7 : int(1..2)]) - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_2_1-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_2_1-solution000001.solution deleted file mode 100644 index 621d5f6edc..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_2_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 1, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_2_1-solution000002.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_2_1-solution000002.solution deleted file mode 100644 index 5e2caa751c..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_2_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 2, 2) -letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_2_1-solution000003.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_2_1-solution000003.solution deleted file mode 100644 index 1b4b5b08a6..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_2_1-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 2, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_2_1-solution000004.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_2_1-solution000004.solution deleted file mode 100644 index 15472caf03..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_2_1-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 2, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_2_1-solution000005.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_2_1-solution000005.solution deleted file mode 100644 index ff56905e23..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_2_1-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_2_1-solution000006.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_2_1-solution000006.solution deleted file mode 100644 index d56a0bbcdc..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_2_1-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_2_1.eprime b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_2_1.eprime deleted file mode 100644 index 645e205b47..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_2_1.eprime +++ /dev/null @@ -1,98 +0,0 @@ -language ESSENCE' 1.0 - -find a_ExplicitWithFlags_Flags: matrix indexed by [int(1..3)] of int(0..3) -find a_ExplicitWithFlags_Values: matrix indexed by [int(1..3)] of int(1..2) -find a_ExplicitWithRepetition_Flag: int(3) -find a_ExplicitWithRepetition_Values: matrix indexed by [int(1..3)] of int(1..2) -find b_MOccurrence: matrix indexed by [int(1..2)] of int(0..3) -find b_ExplicitWithFlags_Flags: matrix indexed by [int(1..3)] of int(0..3) -find b_ExplicitWithFlags_Values: matrix indexed by [int(1..3)] of int(1..2) -branching on - [a_ExplicitWithRepetition_Flag, a_ExplicitWithRepetition_Values, a_ExplicitWithFlags_Flags, - a_ExplicitWithFlags_Values, b_ExplicitWithFlags_Flags, b_ExplicitWithFlags_Values, b_MOccurrence] -such that - or([a_ExplicitWithFlags_Flags[q43] > 0 /\ - (sum([toInt(a_ExplicitWithFlags_Values[q35] = a_ExplicitWithFlags_Values[q43]) * - catchUndef(a_ExplicitWithFlags_Flags[q35], 0) - | q35 : int(1..3)]) - < b_MOccurrence[a_ExplicitWithFlags_Values[q43]] - /\ - (and([a_ExplicitWithFlags_Flags[q39] > 0 /\ a_ExplicitWithFlags_Values[q39] < a_ExplicitWithFlags_Values[q43] - -> - sum([toInt(a_ExplicitWithFlags_Values[q36] = a_ExplicitWithFlags_Values[q39]) * - catchUndef(a_ExplicitWithFlags_Flags[q36], 0) - | q36 : int(1..3)]) - = b_MOccurrence[a_ExplicitWithFlags_Values[q39]] - | q39 : int(1..3)]) - /\ - and([q40 < a_ExplicitWithFlags_Values[q43] -> - (b_MOccurrence[q40] > 0 /\ - !or([a_ExplicitWithFlags_Flags[q38] > 0 /\ a_ExplicitWithFlags_Values[q38] = q40 | q38 : int(1..3)]) - -> - sum([toInt(a_ExplicitWithFlags_Values[q36] = q40) * catchUndef(a_ExplicitWithFlags_Flags[q36], 0) - | q36 : int(1..3)]) - = b_MOccurrence[q40]) - | q40 : int(1..2)]))) - | q43 : int(1..3)]) - \/ - or([b_MOccurrence[q44] > 0 /\ - !or([a_ExplicitWithFlags_Flags[q42] > 0 /\ a_ExplicitWithFlags_Values[q42] = q44 | q42 : int(1..3)]) - /\ - (sum([toInt(a_ExplicitWithFlags_Values[q35] = q44) * catchUndef(a_ExplicitWithFlags_Flags[q35], 0) - | q35 : int(1..3)]) - < b_MOccurrence[q44] - /\ - (and([a_ExplicitWithFlags_Flags[q39] > 0 /\ a_ExplicitWithFlags_Values[q39] < q44 -> - sum([toInt(a_ExplicitWithFlags_Values[q36] = a_ExplicitWithFlags_Values[q39]) * - catchUndef(a_ExplicitWithFlags_Flags[q36], 0) - | q36 : int(1..3)]) - = b_MOccurrence[a_ExplicitWithFlags_Values[q39]] - | q39 : int(1..3)]) - /\ - and([b_MOccurrence[q40] > 0 /\ - !or([a_ExplicitWithFlags_Flags[q38] > 0 /\ a_ExplicitWithFlags_Values[q38] = q40 | q38 : int(1..3)]) - -> - sum([toInt(a_ExplicitWithFlags_Values[q36] = q40) * catchUndef(a_ExplicitWithFlags_Flags[q36], 0) - | q36 : int(1..3)]) - = b_MOccurrence[q40] - | q40 : int(1..2), q40 < q44]))) - | q44 : int(1..2)]), - and([a_ExplicitWithFlags_Flags[q1 + 1] > 0 -> a_ExplicitWithFlags_Values[q1] < a_ExplicitWithFlags_Values[q1 + 1] - | q1 : int(1..2)]), - and([a_ExplicitWithFlags_Flags[q2] = 0 -> a_ExplicitWithFlags_Values[q2] = 1 | q2 : int(1..3)]), - and([a_ExplicitWithFlags_Flags[q3 + 1] > 0 -> a_ExplicitWithFlags_Flags[q3] > 0 | q3 : int(1..2)]), - 3 = sum([a_ExplicitWithFlags_Flags[q5] | q5 : int(1..3)]), - 3 = sum([b_MOccurrence[q7] | q7 : int(1..2)]), - and([a_ExplicitWithRepetition_Values[q8] <= a_ExplicitWithRepetition_Values[q8 + 1] | q8 : int(1..2), q8 + 1 <= 3]), - and([sum([toInt(a_ExplicitWithRepetition_Values[q17] = a_ExplicitWithRepetition_Values[q14]) - | q17 : int(1..3), q17 <= 3]) - = - sum([toInt(a_ExplicitWithFlags_Values[q15] = a_ExplicitWithRepetition_Values[q14]) * - catchUndef(a_ExplicitWithFlags_Flags[q15], 0) - | q15 : int(1..3)]) - | q14 : int(1..3), q14 <= 3]), - and([a_ExplicitWithFlags_Flags[q18] > 0 -> - sum([toInt(a_ExplicitWithRepetition_Values[q21] = a_ExplicitWithFlags_Values[q18]) - | q21 : int(1..3), q21 <= 3]) - = - sum([toInt(a_ExplicitWithFlags_Values[q19] = a_ExplicitWithFlags_Values[q18]) * - catchUndef(a_ExplicitWithFlags_Flags[q19], 0) - | q19 : int(1..3)]) - | q18 : int(1..3)]), - and([b_ExplicitWithFlags_Flags[q22 + 1] > 0 -> b_ExplicitWithFlags_Values[q22] < b_ExplicitWithFlags_Values[q22 + 1] - | q22 : int(1..2)]), - and([b_ExplicitWithFlags_Flags[q23] = 0 -> b_ExplicitWithFlags_Values[q23] = 1 | q23 : int(1..3)]), - and([b_ExplicitWithFlags_Flags[q24 + 1] > 0 -> b_ExplicitWithFlags_Flags[q24] > 0 | q24 : int(1..2)]), - 3 = sum([b_ExplicitWithFlags_Flags[q26] | q26 : int(1..3)]), - and([b_ExplicitWithFlags_Flags[q29] > 0 -> - sum([toInt(b_ExplicitWithFlags_Values[q30] = b_ExplicitWithFlags_Values[q29]) * - catchUndef(b_ExplicitWithFlags_Flags[q30], 0) - | q30 : int(1..3)]) - = b_MOccurrence[b_ExplicitWithFlags_Values[q29]] - | q29 : int(1..3)]), - and([b_MOccurrence[q31] > 0 -> - sum([toInt(b_ExplicitWithFlags_Values[q32] = q31) * catchUndef(b_ExplicitWithFlags_Flags[q32], 0) - | q32 : int(1..3)]) - = b_MOccurrence[q31] - | q31 : int(1..2)]) - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_2_2-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_2_2-solution000001.solution deleted file mode 100644 index 621d5f6edc..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_2_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 1, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_2_2-solution000002.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_2_2-solution000002.solution deleted file mode 100644 index 1b4b5b08a6..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_2_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 2, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_2_2-solution000003.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_2_2-solution000003.solution deleted file mode 100644 index 5e2caa751c..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_2_2-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 2, 2) -letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_2_2-solution000004.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_2_2-solution000004.solution deleted file mode 100644 index d56a0bbcdc..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_2_2-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_2_2-solution000005.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_2_2-solution000005.solution deleted file mode 100644 index ff56905e23..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_2_2-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_2_2-solution000006.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_2_2-solution000006.solution deleted file mode 100644 index 15472caf03..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_2_2-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 2, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_2_2.eprime b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_2_2.eprime deleted file mode 100644 index b1c3c9c2f5..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_2_2.eprime +++ /dev/null @@ -1,91 +0,0 @@ -language ESSENCE' 1.0 - -find a_ExplicitWithFlags_Flags: matrix indexed by [int(1..3)] of int(0..3) -find a_ExplicitWithFlags_Values: matrix indexed by [int(1..3)] of int(1..2) -find a_ExplicitWithRepetition_Flag: int(3) -find a_ExplicitWithRepetition_Values: matrix indexed by [int(1..3)] of int(1..2) -find b_MOccurrence: matrix indexed by [int(1..2)] of int(0..3) -find b_ExplicitWithRepetition_Flag: int(3) -find b_ExplicitWithRepetition_Values: matrix indexed by [int(1..3)] of int(1..2) -branching on - [a_ExplicitWithRepetition_Flag, a_ExplicitWithRepetition_Values, a_ExplicitWithFlags_Flags, - a_ExplicitWithFlags_Values, b_ExplicitWithRepetition_Flag, b_ExplicitWithRepetition_Values, b_MOccurrence] -such that - or([a_ExplicitWithFlags_Flags[q44] > 0 /\ - (sum([toInt(a_ExplicitWithFlags_Values[q36] = a_ExplicitWithFlags_Values[q44]) * - catchUndef(a_ExplicitWithFlags_Flags[q36], 0) - | q36 : int(1..3)]) - < b_MOccurrence[a_ExplicitWithFlags_Values[q44]] - /\ - (and([a_ExplicitWithFlags_Flags[q40] > 0 /\ a_ExplicitWithFlags_Values[q40] < a_ExplicitWithFlags_Values[q44] - -> - sum([toInt(a_ExplicitWithFlags_Values[q37] = a_ExplicitWithFlags_Values[q40]) * - catchUndef(a_ExplicitWithFlags_Flags[q37], 0) - | q37 : int(1..3)]) - = b_MOccurrence[a_ExplicitWithFlags_Values[q40]] - | q40 : int(1..3)]) - /\ - and([q41 < a_ExplicitWithFlags_Values[q44] -> - (b_MOccurrence[q41] > 0 /\ - !or([a_ExplicitWithFlags_Flags[q39] > 0 /\ a_ExplicitWithFlags_Values[q39] = q41 | q39 : int(1..3)]) - -> - sum([toInt(a_ExplicitWithFlags_Values[q37] = q41) * catchUndef(a_ExplicitWithFlags_Flags[q37], 0) - | q37 : int(1..3)]) - = b_MOccurrence[q41]) - | q41 : int(1..2)]))) - | q44 : int(1..3)]) - \/ - or([b_MOccurrence[q45] > 0 /\ - !or([a_ExplicitWithFlags_Flags[q43] > 0 /\ a_ExplicitWithFlags_Values[q43] = q45 | q43 : int(1..3)]) - /\ - (sum([toInt(a_ExplicitWithFlags_Values[q36] = q45) * catchUndef(a_ExplicitWithFlags_Flags[q36], 0) - | q36 : int(1..3)]) - < b_MOccurrence[q45] - /\ - (and([a_ExplicitWithFlags_Flags[q40] > 0 /\ a_ExplicitWithFlags_Values[q40] < q45 -> - sum([toInt(a_ExplicitWithFlags_Values[q37] = a_ExplicitWithFlags_Values[q40]) * - catchUndef(a_ExplicitWithFlags_Flags[q37], 0) - | q37 : int(1..3)]) - = b_MOccurrence[a_ExplicitWithFlags_Values[q40]] - | q40 : int(1..3)]) - /\ - and([b_MOccurrence[q41] > 0 /\ - !or([a_ExplicitWithFlags_Flags[q39] > 0 /\ a_ExplicitWithFlags_Values[q39] = q41 | q39 : int(1..3)]) - -> - sum([toInt(a_ExplicitWithFlags_Values[q37] = q41) * catchUndef(a_ExplicitWithFlags_Flags[q37], 0) - | q37 : int(1..3)]) - = b_MOccurrence[q41] - | q41 : int(1..2), q41 < q45]))) - | q45 : int(1..2)]), - and([a_ExplicitWithFlags_Flags[q1 + 1] > 0 -> a_ExplicitWithFlags_Values[q1] < a_ExplicitWithFlags_Values[q1 + 1] - | q1 : int(1..2)]), - and([a_ExplicitWithFlags_Flags[q2] = 0 -> a_ExplicitWithFlags_Values[q2] = 1 | q2 : int(1..3)]), - and([a_ExplicitWithFlags_Flags[q3 + 1] > 0 -> a_ExplicitWithFlags_Flags[q3] > 0 | q3 : int(1..2)]), - 3 = sum([a_ExplicitWithFlags_Flags[q5] | q5 : int(1..3)]), - 3 = sum([b_MOccurrence[q7] | q7 : int(1..2)]), - and([a_ExplicitWithRepetition_Values[q8] <= a_ExplicitWithRepetition_Values[q8 + 1] | q8 : int(1..2), q8 + 1 <= 3]), - and([sum([toInt(a_ExplicitWithRepetition_Values[q17] = a_ExplicitWithRepetition_Values[q14]) - | q17 : int(1..3), q17 <= 3]) - = - sum([toInt(a_ExplicitWithFlags_Values[q15] = a_ExplicitWithRepetition_Values[q14]) * - catchUndef(a_ExplicitWithFlags_Flags[q15], 0) - | q15 : int(1..3)]) - | q14 : int(1..3), q14 <= 3]), - and([a_ExplicitWithFlags_Flags[q18] > 0 -> - sum([toInt(a_ExplicitWithRepetition_Values[q21] = a_ExplicitWithFlags_Values[q18]) - | q21 : int(1..3), q21 <= 3]) - = - sum([toInt(a_ExplicitWithFlags_Values[q19] = a_ExplicitWithFlags_Values[q18]) * - catchUndef(a_ExplicitWithFlags_Flags[q19], 0) - | q19 : int(1..3)]) - | q18 : int(1..3)]), - and([b_ExplicitWithRepetition_Values[q22] <= b_ExplicitWithRepetition_Values[q22 + 1] - | q22 : int(1..2), q22 + 1 <= 3]), - and([sum([toInt(b_ExplicitWithRepetition_Values[q30] = b_ExplicitWithRepetition_Values[q28]) - | q30 : int(1..3), q30 <= 3]) - = b_MOccurrence[b_ExplicitWithRepetition_Values[q28]] - | q28 : int(1..3), q28 <= 3]), - and([b_MOccurrence[q31] > 0 -> - sum([toInt(b_ExplicitWithRepetition_Values[q33] = q31) | q33 : int(1..3), q33 <= 3]) = b_MOccurrence[q31] - | q31 : int(1..2)]) - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_2_3-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_2_3-solution000001.solution deleted file mode 100644 index 621d5f6edc..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_2_3-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 1, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_2_3-solution000002.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_2_3-solution000002.solution deleted file mode 100644 index 5e2caa751c..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_2_3-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 2, 2) -letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_2_3-solution000003.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_2_3-solution000003.solution deleted file mode 100644 index 1b4b5b08a6..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_2_3-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 2, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_2_3-solution000004.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_2_3-solution000004.solution deleted file mode 100644 index 15472caf03..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_2_3-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 2, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_2_3-solution000005.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_2_3-solution000005.solution deleted file mode 100644 index ff56905e23..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_2_3-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_2_3-solution000006.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_2_3-solution000006.solution deleted file mode 100644 index d56a0bbcdc..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_2_3-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_2_3.eprime b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_2_3.eprime deleted file mode 100644 index 7bb777ad21..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_2_3.eprime +++ /dev/null @@ -1,80 +0,0 @@ -language ESSENCE' 1.0 - -find a_ExplicitWithFlags_Flags: matrix indexed by [int(1..3)] of int(0..3) -find a_ExplicitWithFlags_Values: matrix indexed by [int(1..3)] of int(1..2) -find a_ExplicitWithRepetition_Flag: int(3) -find a_ExplicitWithRepetition_Values: matrix indexed by [int(1..3)] of int(1..2) -find b_MOccurrence: matrix indexed by [int(1..2)] of int(0..3) -branching on - [a_ExplicitWithRepetition_Flag, a_ExplicitWithRepetition_Values, a_ExplicitWithFlags_Flags, - a_ExplicitWithFlags_Values, b_MOccurrence] -such that - or([a_ExplicitWithFlags_Flags[q32] > 0 /\ - (sum([toInt(a_ExplicitWithFlags_Values[q24] = a_ExplicitWithFlags_Values[q32]) * - catchUndef(a_ExplicitWithFlags_Flags[q24], 0) - | q24 : int(1..3)]) - < b_MOccurrence[a_ExplicitWithFlags_Values[q32]] - /\ - (and([a_ExplicitWithFlags_Flags[q28] > 0 /\ a_ExplicitWithFlags_Values[q28] < a_ExplicitWithFlags_Values[q32] - -> - sum([toInt(a_ExplicitWithFlags_Values[q25] = a_ExplicitWithFlags_Values[q28]) * - catchUndef(a_ExplicitWithFlags_Flags[q25], 0) - | q25 : int(1..3)]) - = b_MOccurrence[a_ExplicitWithFlags_Values[q28]] - | q28 : int(1..3)]) - /\ - and([q29 < a_ExplicitWithFlags_Values[q32] -> - (b_MOccurrence[q29] > 0 /\ - !or([a_ExplicitWithFlags_Flags[q27] > 0 /\ a_ExplicitWithFlags_Values[q27] = q29 | q27 : int(1..3)]) - -> - sum([toInt(a_ExplicitWithFlags_Values[q25] = q29) * catchUndef(a_ExplicitWithFlags_Flags[q25], 0) - | q25 : int(1..3)]) - = b_MOccurrence[q29]) - | q29 : int(1..2)]))) - | q32 : int(1..3)]) - \/ - or([b_MOccurrence[q33] > 0 /\ - !or([a_ExplicitWithFlags_Flags[q31] > 0 /\ a_ExplicitWithFlags_Values[q31] = q33 | q31 : int(1..3)]) - /\ - (sum([toInt(a_ExplicitWithFlags_Values[q24] = q33) * catchUndef(a_ExplicitWithFlags_Flags[q24], 0) - | q24 : int(1..3)]) - < b_MOccurrence[q33] - /\ - (and([a_ExplicitWithFlags_Flags[q28] > 0 /\ a_ExplicitWithFlags_Values[q28] < q33 -> - sum([toInt(a_ExplicitWithFlags_Values[q25] = a_ExplicitWithFlags_Values[q28]) * - catchUndef(a_ExplicitWithFlags_Flags[q25], 0) - | q25 : int(1..3)]) - = b_MOccurrence[a_ExplicitWithFlags_Values[q28]] - | q28 : int(1..3)]) - /\ - and([b_MOccurrence[q29] > 0 /\ - !or([a_ExplicitWithFlags_Flags[q27] > 0 /\ a_ExplicitWithFlags_Values[q27] = q29 | q27 : int(1..3)]) - -> - sum([toInt(a_ExplicitWithFlags_Values[q25] = q29) * catchUndef(a_ExplicitWithFlags_Flags[q25], 0) - | q25 : int(1..3)]) - = b_MOccurrence[q29] - | q29 : int(1..2), q29 < q33]))) - | q33 : int(1..2)]), - and([a_ExplicitWithFlags_Flags[q1 + 1] > 0 -> a_ExplicitWithFlags_Values[q1] < a_ExplicitWithFlags_Values[q1 + 1] - | q1 : int(1..2)]), - and([a_ExplicitWithFlags_Flags[q2] = 0 -> a_ExplicitWithFlags_Values[q2] = 1 | q2 : int(1..3)]), - and([a_ExplicitWithFlags_Flags[q3 + 1] > 0 -> a_ExplicitWithFlags_Flags[q3] > 0 | q3 : int(1..2)]), - 3 = sum([a_ExplicitWithFlags_Flags[q5] | q5 : int(1..3)]), - 3 = sum([b_MOccurrence[q7] | q7 : int(1..2)]), - and([a_ExplicitWithRepetition_Values[q8] <= a_ExplicitWithRepetition_Values[q8 + 1] | q8 : int(1..2), q8 + 1 <= 3]), - and([sum([toInt(a_ExplicitWithRepetition_Values[q17] = a_ExplicitWithRepetition_Values[q14]) - | q17 : int(1..3), q17 <= 3]) - = - sum([toInt(a_ExplicitWithFlags_Values[q15] = a_ExplicitWithRepetition_Values[q14]) * - catchUndef(a_ExplicitWithFlags_Flags[q15], 0) - | q15 : int(1..3)]) - | q14 : int(1..3), q14 <= 3]), - and([a_ExplicitWithFlags_Flags[q18] > 0 -> - sum([toInt(a_ExplicitWithRepetition_Values[q21] = a_ExplicitWithFlags_Values[q18]) - | q21 : int(1..3), q21 <= 3]) - = - sum([toInt(a_ExplicitWithFlags_Values[q19] = a_ExplicitWithFlags_Values[q18]) * - catchUndef(a_ExplicitWithFlags_Flags[q19], 0) - | q19 : int(1..3)]) - | q18 : int(1..3)]) - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_3_1-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_3_1-solution000001.solution deleted file mode 100644 index 15472caf03..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_3_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 2, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_3_1-solution000002.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_3_1-solution000002.solution deleted file mode 100644 index ff56905e23..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_3_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_3_1-solution000003.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_3_1-solution000003.solution deleted file mode 100644 index d56a0bbcdc..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_3_1-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_3_1-solution000004.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_3_1-solution000004.solution deleted file mode 100644 index 5e2caa751c..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_3_1-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 2, 2) -letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_3_1-solution000005.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_3_1-solution000005.solution deleted file mode 100644 index 1b4b5b08a6..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_3_1-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 2, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_3_1-solution000006.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_3_1-solution000006.solution deleted file mode 100644 index 621d5f6edc..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_3_1-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 1, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_3_1.eprime b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_3_1.eprime deleted file mode 100644 index 14d6fbd869..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_3_1.eprime +++ /dev/null @@ -1,93 +0,0 @@ -language ESSENCE' 1.0 - -find a_ExplicitWithFlags_Flags: matrix indexed by [int(1..3)] of int(0..3) -find a_ExplicitWithFlags_Values: matrix indexed by [int(1..3)] of int(1..2) -find a_MOccurrence: matrix indexed by [int(1..2)] of int(0..3) -find b_MOccurrence: matrix indexed by [int(1..2)] of int(0..3) -find b_ExplicitWithFlags_Flags: matrix indexed by [int(1..3)] of int(0..3) -find b_ExplicitWithFlags_Values: matrix indexed by [int(1..3)] of int(1..2) -branching on - [a_MOccurrence, a_ExplicitWithFlags_Flags, a_ExplicitWithFlags_Values, b_ExplicitWithFlags_Flags, - b_ExplicitWithFlags_Values, b_MOccurrence] -such that - or([a_ExplicitWithFlags_Flags[q35] > 0 /\ - (sum([toInt(a_ExplicitWithFlags_Values[q27] = a_ExplicitWithFlags_Values[q35]) * - catchUndef(a_ExplicitWithFlags_Flags[q27], 0) - | q27 : int(1..3)]) - < b_MOccurrence[a_ExplicitWithFlags_Values[q35]] - /\ - (and([a_ExplicitWithFlags_Flags[q31] > 0 /\ a_ExplicitWithFlags_Values[q31] < a_ExplicitWithFlags_Values[q35] - -> - sum([toInt(a_ExplicitWithFlags_Values[q28] = a_ExplicitWithFlags_Values[q31]) * - catchUndef(a_ExplicitWithFlags_Flags[q28], 0) - | q28 : int(1..3)]) - = b_MOccurrence[a_ExplicitWithFlags_Values[q31]] - | q31 : int(1..3)]) - /\ - and([q32 < a_ExplicitWithFlags_Values[q35] -> - (b_MOccurrence[q32] > 0 /\ - !or([a_ExplicitWithFlags_Flags[q30] > 0 /\ a_ExplicitWithFlags_Values[q30] = q32 | q30 : int(1..3)]) - -> - sum([toInt(a_ExplicitWithFlags_Values[q28] = q32) * catchUndef(a_ExplicitWithFlags_Flags[q28], 0) - | q28 : int(1..3)]) - = b_MOccurrence[q32]) - | q32 : int(1..2)]))) - | q35 : int(1..3)]) - \/ - or([b_MOccurrence[q36] > 0 /\ - !or([a_ExplicitWithFlags_Flags[q34] > 0 /\ a_ExplicitWithFlags_Values[q34] = q36 | q34 : int(1..3)]) - /\ - (sum([toInt(a_ExplicitWithFlags_Values[q27] = q36) * catchUndef(a_ExplicitWithFlags_Flags[q27], 0) - | q27 : int(1..3)]) - < b_MOccurrence[q36] - /\ - (and([a_ExplicitWithFlags_Flags[q31] > 0 /\ a_ExplicitWithFlags_Values[q31] < q36 -> - sum([toInt(a_ExplicitWithFlags_Values[q28] = a_ExplicitWithFlags_Values[q31]) * - catchUndef(a_ExplicitWithFlags_Flags[q28], 0) - | q28 : int(1..3)]) - = b_MOccurrence[a_ExplicitWithFlags_Values[q31]] - | q31 : int(1..3)]) - /\ - and([b_MOccurrence[q32] > 0 /\ - !or([a_ExplicitWithFlags_Flags[q30] > 0 /\ a_ExplicitWithFlags_Values[q30] = q32 | q30 : int(1..3)]) - -> - sum([toInt(a_ExplicitWithFlags_Values[q28] = q32) * catchUndef(a_ExplicitWithFlags_Flags[q28], 0) - | q28 : int(1..3)]) - = b_MOccurrence[q32] - | q32 : int(1..2), q32 < q36]))) - | q36 : int(1..2)]), - and([a_ExplicitWithFlags_Flags[q1 + 1] > 0 -> a_ExplicitWithFlags_Values[q1] < a_ExplicitWithFlags_Values[q1 + 1] - | q1 : int(1..2)]), - and([a_ExplicitWithFlags_Flags[q2] = 0 -> a_ExplicitWithFlags_Values[q2] = 1 | q2 : int(1..3)]), - and([a_ExplicitWithFlags_Flags[q3 + 1] > 0 -> a_ExplicitWithFlags_Flags[q3] > 0 | q3 : int(1..2)]), - 3 = sum([a_ExplicitWithFlags_Flags[q5] | q5 : int(1..3)]), - 3 = sum([b_MOccurrence[q7] | q7 : int(1..2)]), - 3 = sum([a_MOccurrence[q8] | q8 : int(1..2)]), - and([a_MOccurrence[q21] > 0 -> - a_MOccurrence[q21] = - sum([toInt(a_ExplicitWithFlags_Values[q22] = q21) * catchUndef(a_ExplicitWithFlags_Flags[q22], 0) - | q22 : int(1..3)]) - | q21 : int(1..2)]), - and([a_ExplicitWithFlags_Flags[q23] > 0 -> - a_MOccurrence[a_ExplicitWithFlags_Values[q23]] = - sum([toInt(a_ExplicitWithFlags_Values[q24] = a_ExplicitWithFlags_Values[q23]) * - catchUndef(a_ExplicitWithFlags_Flags[q24], 0) - | q24 : int(1..3)]) - | q23 : int(1..3)]), - and([b_ExplicitWithFlags_Flags[q9 + 1] > 0 -> b_ExplicitWithFlags_Values[q9] < b_ExplicitWithFlags_Values[q9 + 1] - | q9 : int(1..2)]), - and([b_ExplicitWithFlags_Flags[q10] = 0 -> b_ExplicitWithFlags_Values[q10] = 1 | q10 : int(1..3)]), - and([b_ExplicitWithFlags_Flags[q11 + 1] > 0 -> b_ExplicitWithFlags_Flags[q11] > 0 | q11 : int(1..2)]), - 3 = sum([b_ExplicitWithFlags_Flags[q13] | q13 : int(1..3)]), - and([b_ExplicitWithFlags_Flags[q16] > 0 -> - sum([toInt(b_ExplicitWithFlags_Values[q17] = b_ExplicitWithFlags_Values[q16]) * - catchUndef(b_ExplicitWithFlags_Flags[q17], 0) - | q17 : int(1..3)]) - = b_MOccurrence[b_ExplicitWithFlags_Values[q16]] - | q16 : int(1..3)]), - and([b_MOccurrence[q18] > 0 -> - sum([toInt(b_ExplicitWithFlags_Values[q19] = q18) * catchUndef(b_ExplicitWithFlags_Flags[q19], 0) - | q19 : int(1..3)]) - = b_MOccurrence[q18] - | q18 : int(1..2)]) - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_3_2-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_3_2-solution000001.solution deleted file mode 100644 index d56a0bbcdc..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_3_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_3_2-solution000002.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_3_2-solution000002.solution deleted file mode 100644 index ff56905e23..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_3_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_3_2-solution000003.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_3_2-solution000003.solution deleted file mode 100644 index 15472caf03..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_3_2-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 2, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_3_2-solution000004.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_3_2-solution000004.solution deleted file mode 100644 index 1b4b5b08a6..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_3_2-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 2, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_3_2-solution000005.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_3_2-solution000005.solution deleted file mode 100644 index 5e2caa751c..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_3_2-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 2, 2) -letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_3_2-solution000006.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_3_2-solution000006.solution deleted file mode 100644 index 621d5f6edc..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_3_2-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 1, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_3_2.eprime b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_3_2.eprime deleted file mode 100644 index 675e07c114..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_3_2.eprime +++ /dev/null @@ -1,85 +0,0 @@ -language ESSENCE' 1.0 - -find a_ExplicitWithFlags_Flags: matrix indexed by [int(1..3)] of int(0..3) -find a_ExplicitWithFlags_Values: matrix indexed by [int(1..3)] of int(1..2) -find a_MOccurrence: matrix indexed by [int(1..2)] of int(0..3) -find b_MOccurrence: matrix indexed by [int(1..2)] of int(0..3) -find b_ExplicitWithRepetition_Flag: int(3) -find b_ExplicitWithRepetition_Values: matrix indexed by [int(1..3)] of int(1..2) -branching on - [a_MOccurrence, a_ExplicitWithFlags_Flags, a_ExplicitWithFlags_Values, b_ExplicitWithRepetition_Flag, - b_ExplicitWithRepetition_Values, b_MOccurrence] -such that - or([a_ExplicitWithFlags_Flags[q36] > 0 /\ - (sum([toInt(a_ExplicitWithFlags_Values[q28] = a_ExplicitWithFlags_Values[q36]) * - catchUndef(a_ExplicitWithFlags_Flags[q28], 0) - | q28 : int(1..3)]) - < b_MOccurrence[a_ExplicitWithFlags_Values[q36]] - /\ - (and([a_ExplicitWithFlags_Flags[q32] > 0 /\ a_ExplicitWithFlags_Values[q32] < a_ExplicitWithFlags_Values[q36] - -> - sum([toInt(a_ExplicitWithFlags_Values[q29] = a_ExplicitWithFlags_Values[q32]) * - catchUndef(a_ExplicitWithFlags_Flags[q29], 0) - | q29 : int(1..3)]) - = b_MOccurrence[a_ExplicitWithFlags_Values[q32]] - | q32 : int(1..3)]) - /\ - and([q33 < a_ExplicitWithFlags_Values[q36] -> - (b_MOccurrence[q33] > 0 /\ - !or([a_ExplicitWithFlags_Flags[q31] > 0 /\ a_ExplicitWithFlags_Values[q31] = q33 | q31 : int(1..3)]) - -> - sum([toInt(a_ExplicitWithFlags_Values[q29] = q33) * catchUndef(a_ExplicitWithFlags_Flags[q29], 0) - | q29 : int(1..3)]) - = b_MOccurrence[q33]) - | q33 : int(1..2)]))) - | q36 : int(1..3)]) - \/ - or([b_MOccurrence[q37] > 0 /\ - !or([a_ExplicitWithFlags_Flags[q35] > 0 /\ a_ExplicitWithFlags_Values[q35] = q37 | q35 : int(1..3)]) - /\ - (sum([toInt(a_ExplicitWithFlags_Values[q28] = q37) * catchUndef(a_ExplicitWithFlags_Flags[q28], 0) - | q28 : int(1..3)]) - < b_MOccurrence[q37] - /\ - (and([a_ExplicitWithFlags_Flags[q32] > 0 /\ a_ExplicitWithFlags_Values[q32] < q37 -> - sum([toInt(a_ExplicitWithFlags_Values[q29] = a_ExplicitWithFlags_Values[q32]) * - catchUndef(a_ExplicitWithFlags_Flags[q29], 0) - | q29 : int(1..3)]) - = b_MOccurrence[a_ExplicitWithFlags_Values[q32]] - | q32 : int(1..3)]) - /\ - and([b_MOccurrence[q33] > 0 /\ - !or([a_ExplicitWithFlags_Flags[q31] > 0 /\ a_ExplicitWithFlags_Values[q31] = q33 | q31 : int(1..3)]) - -> - sum([toInt(a_ExplicitWithFlags_Values[q29] = q33) * catchUndef(a_ExplicitWithFlags_Flags[q29], 0) - | q29 : int(1..3)]) - = b_MOccurrence[q33] - | q33 : int(1..2), q33 < q37]))) - | q37 : int(1..2)]), - and([a_ExplicitWithFlags_Flags[q1 + 1] > 0 -> a_ExplicitWithFlags_Values[q1] < a_ExplicitWithFlags_Values[q1 + 1] - | q1 : int(1..2)]), - and([a_ExplicitWithFlags_Flags[q2] = 0 -> a_ExplicitWithFlags_Values[q2] = 1 | q2 : int(1..3)]), - and([a_ExplicitWithFlags_Flags[q3 + 1] > 0 -> a_ExplicitWithFlags_Flags[q3] > 0 | q3 : int(1..2)]), - 3 = sum([a_ExplicitWithFlags_Flags[q5] | q5 : int(1..3)]), - 3 = sum([b_MOccurrence[q7] | q7 : int(1..2)]), - 3 = sum([a_MOccurrence[q8] | q8 : int(1..2)]), - and([a_MOccurrence[q22] > 0 -> - a_MOccurrence[q22] = - sum([toInt(a_ExplicitWithFlags_Values[q23] = q22) * catchUndef(a_ExplicitWithFlags_Flags[q23], 0) - | q23 : int(1..3)]) - | q22 : int(1..2)]), - and([a_ExplicitWithFlags_Flags[q24] > 0 -> - a_MOccurrence[a_ExplicitWithFlags_Values[q24]] = - sum([toInt(a_ExplicitWithFlags_Values[q25] = a_ExplicitWithFlags_Values[q24]) * - catchUndef(a_ExplicitWithFlags_Flags[q25], 0) - | q25 : int(1..3)]) - | q24 : int(1..3)]), - and([b_ExplicitWithRepetition_Values[q9] <= b_ExplicitWithRepetition_Values[q9 + 1] | q9 : int(1..2), q9 + 1 <= 3]), - and([sum([toInt(b_ExplicitWithRepetition_Values[q17] = b_ExplicitWithRepetition_Values[q15]) - | q17 : int(1..3), q17 <= 3]) - = b_MOccurrence[b_ExplicitWithRepetition_Values[q15]] - | q15 : int(1..3), q15 <= 3]), - and([b_MOccurrence[q18] > 0 -> - sum([toInt(b_ExplicitWithRepetition_Values[q20] = q18) | q20 : int(1..3), q20 <= 3]) = b_MOccurrence[q18] - | q18 : int(1..2)]) - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_3_3-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_3_3-solution000001.solution deleted file mode 100644 index 15472caf03..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_3_3-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 2, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_3_3-solution000002.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_3_3-solution000002.solution deleted file mode 100644 index ff56905e23..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_3_3-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_3_3-solution000003.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_3_3-solution000003.solution deleted file mode 100644 index d56a0bbcdc..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_3_3-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_3_3-solution000004.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_3_3-solution000004.solution deleted file mode 100644 index 5e2caa751c..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_3_3-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 2, 2) -letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_3_3-solution000005.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_3_3-solution000005.solution deleted file mode 100644 index 1b4b5b08a6..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_3_3-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 2, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_3_3-solution000006.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_3_3-solution000006.solution deleted file mode 100644 index 621d5f6edc..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_3_3-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 1, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_3_3.eprime b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_3_3.eprime deleted file mode 100644 index e06edc11bc..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_3_3.eprime +++ /dev/null @@ -1,73 +0,0 @@ -language ESSENCE' 1.0 - -find a_ExplicitWithFlags_Flags: matrix indexed by [int(1..3)] of int(0..3) -find a_ExplicitWithFlags_Values: matrix indexed by [int(1..3)] of int(1..2) -find a_MOccurrence: matrix indexed by [int(1..2)] of int(0..3) -find b_MOccurrence: matrix indexed by [int(1..2)] of int(0..3) -branching on [a_MOccurrence, a_ExplicitWithFlags_Flags, a_ExplicitWithFlags_Values, b_MOccurrence] -such that - or([a_ExplicitWithFlags_Flags[q24] > 0 /\ - (sum([toInt(a_ExplicitWithFlags_Values[q16] = a_ExplicitWithFlags_Values[q24]) * - catchUndef(a_ExplicitWithFlags_Flags[q16], 0) - | q16 : int(1..3)]) - < b_MOccurrence[a_ExplicitWithFlags_Values[q24]] - /\ - (and([a_ExplicitWithFlags_Flags[q20] > 0 /\ a_ExplicitWithFlags_Values[q20] < a_ExplicitWithFlags_Values[q24] - -> - sum([toInt(a_ExplicitWithFlags_Values[q17] = a_ExplicitWithFlags_Values[q20]) * - catchUndef(a_ExplicitWithFlags_Flags[q17], 0) - | q17 : int(1..3)]) - = b_MOccurrence[a_ExplicitWithFlags_Values[q20]] - | q20 : int(1..3)]) - /\ - and([q21 < a_ExplicitWithFlags_Values[q24] -> - (b_MOccurrence[q21] > 0 /\ - !or([a_ExplicitWithFlags_Flags[q19] > 0 /\ a_ExplicitWithFlags_Values[q19] = q21 | q19 : int(1..3)]) - -> - sum([toInt(a_ExplicitWithFlags_Values[q17] = q21) * catchUndef(a_ExplicitWithFlags_Flags[q17], 0) - | q17 : int(1..3)]) - = b_MOccurrence[q21]) - | q21 : int(1..2)]))) - | q24 : int(1..3)]) - \/ - or([b_MOccurrence[q25] > 0 /\ - !or([a_ExplicitWithFlags_Flags[q23] > 0 /\ a_ExplicitWithFlags_Values[q23] = q25 | q23 : int(1..3)]) - /\ - (sum([toInt(a_ExplicitWithFlags_Values[q16] = q25) * catchUndef(a_ExplicitWithFlags_Flags[q16], 0) - | q16 : int(1..3)]) - < b_MOccurrence[q25] - /\ - (and([a_ExplicitWithFlags_Flags[q20] > 0 /\ a_ExplicitWithFlags_Values[q20] < q25 -> - sum([toInt(a_ExplicitWithFlags_Values[q17] = a_ExplicitWithFlags_Values[q20]) * - catchUndef(a_ExplicitWithFlags_Flags[q17], 0) - | q17 : int(1..3)]) - = b_MOccurrence[a_ExplicitWithFlags_Values[q20]] - | q20 : int(1..3)]) - /\ - and([b_MOccurrence[q21] > 0 /\ - !or([a_ExplicitWithFlags_Flags[q19] > 0 /\ a_ExplicitWithFlags_Values[q19] = q21 | q19 : int(1..3)]) - -> - sum([toInt(a_ExplicitWithFlags_Values[q17] = q21) * catchUndef(a_ExplicitWithFlags_Flags[q17], 0) - | q17 : int(1..3)]) - = b_MOccurrence[q21] - | q21 : int(1..2), q21 < q25]))) - | q25 : int(1..2)]), - and([a_ExplicitWithFlags_Flags[q1 + 1] > 0 -> a_ExplicitWithFlags_Values[q1] < a_ExplicitWithFlags_Values[q1 + 1] - | q1 : int(1..2)]), - and([a_ExplicitWithFlags_Flags[q2] = 0 -> a_ExplicitWithFlags_Values[q2] = 1 | q2 : int(1..3)]), - and([a_ExplicitWithFlags_Flags[q3 + 1] > 0 -> a_ExplicitWithFlags_Flags[q3] > 0 | q3 : int(1..2)]), - 3 = sum([a_ExplicitWithFlags_Flags[q5] | q5 : int(1..3)]), - 3 = sum([b_MOccurrence[q7] | q7 : int(1..2)]), - 3 = sum([a_MOccurrence[q8] | q8 : int(1..2)]), - and([a_MOccurrence[q10] > 0 -> - a_MOccurrence[q10] = - sum([toInt(a_ExplicitWithFlags_Values[q11] = q10) * catchUndef(a_ExplicitWithFlags_Flags[q11], 0) - | q11 : int(1..3)]) - | q10 : int(1..2)]), - and([a_ExplicitWithFlags_Flags[q12] > 0 -> - a_MOccurrence[a_ExplicitWithFlags_Values[q12]] = - sum([toInt(a_ExplicitWithFlags_Values[q13] = a_ExplicitWithFlags_Values[q12]) * - catchUndef(a_ExplicitWithFlags_Flags[q13], 0) - | q13 : int(1..3)]) - | q12 : int(1..3)]) - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_1_1-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_1_1-solution000001.solution deleted file mode 100644 index 5e2caa751c..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_1_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 2, 2) -letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_1_1-solution000002.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_1_1-solution000002.solution deleted file mode 100644 index 1b4b5b08a6..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_1_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 2, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_1_1-solution000003.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_1_1-solution000003.solution deleted file mode 100644 index 621d5f6edc..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_1_1-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 1, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_1_1-solution000004.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_1_1-solution000004.solution deleted file mode 100644 index 15472caf03..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_1_1-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 2, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_1_1-solution000005.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_1_1-solution000005.solution deleted file mode 100644 index ff56905e23..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_1_1-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_1_1-solution000006.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_1_1-solution000006.solution deleted file mode 100644 index d56a0bbcdc..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_1_1-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_1_1.eprime b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_1_1.eprime deleted file mode 100644 index 411ca916a0..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_1_1.eprime +++ /dev/null @@ -1,103 +0,0 @@ -language ESSENCE' 1.0 - -find a_ExplicitWithRepetition_Flag: int(3) -find a_ExplicitWithRepetition_Values: matrix indexed by [int(1..3)] of int(1..2) -find a_ExplicitWithFlags_Flags: matrix indexed by [int(1..3)] of int(0..3) -find a_ExplicitWithFlags_Values: matrix indexed by [int(1..3)] of int(1..2) -find b_ExplicitWithFlags_Flags: matrix indexed by [int(1..3)] of int(0..3) -find b_ExplicitWithFlags_Values: matrix indexed by [int(1..3)] of int(1..2) -branching on - [a_ExplicitWithFlags_Flags, a_ExplicitWithFlags_Values, a_ExplicitWithRepetition_Flag, - a_ExplicitWithRepetition_Values, b_ExplicitWithFlags_Flags, b_ExplicitWithFlags_Values] -such that - or([sum([toInt(a_ExplicitWithRepetition_Values[q38] = a_ExplicitWithRepetition_Values[q39]) - | q38 : int(1..3), q38 <= 3]) - < - sum([toInt(b_ExplicitWithFlags_Values[q29] = a_ExplicitWithRepetition_Values[q39]) * - catchUndef(b_ExplicitWithFlags_Flags[q29], 0) - | q29 : int(1..3)]) - /\ - (and([a_ExplicitWithRepetition_Values[q33] < a_ExplicitWithRepetition_Values[q39] -> - sum([toInt(a_ExplicitWithRepetition_Values[q32] = a_ExplicitWithRepetition_Values[q33]) - | q32 : int(1..3), q32 <= 3]) - = - sum([toInt(b_ExplicitWithFlags_Values[q30] = a_ExplicitWithRepetition_Values[q33]) * - catchUndef(b_ExplicitWithFlags_Flags[q30], 0) - | q30 : int(1..3)]) - | q33 : int(1..3), q33 <= 3]) - /\ - and([and([b_ExplicitWithFlags_Flags[q36] > 0, - !or([a_ExplicitWithRepetition_Values[q35] = b_ExplicitWithFlags_Values[q36] - | q35 : int(1..3), q35 <= 3]), - b_ExplicitWithFlags_Values[q36] < a_ExplicitWithRepetition_Values[q39]; - int(1..3)]) - -> - sum([toInt(a_ExplicitWithRepetition_Values[q32] = b_ExplicitWithFlags_Values[q36]) - | q32 : int(1..3), q32 <= 3]) - = - sum([toInt(b_ExplicitWithFlags_Values[q30] = b_ExplicitWithFlags_Values[q36]) * - catchUndef(b_ExplicitWithFlags_Flags[q30], 0) - | q30 : int(1..3)]) - | q36 : int(1..3)])) - | q39 : int(1..3), q39 <= 3]) - \/ - or([b_ExplicitWithFlags_Flags[q42] > 0 /\ - !or([a_ExplicitWithRepetition_Values[q41] = b_ExplicitWithFlags_Values[q42] | q41 : int(1..3), q41 <= 3]) - /\ - (sum([toInt(a_ExplicitWithRepetition_Values[q38] = b_ExplicitWithFlags_Values[q42]) - | q38 : int(1..3), q38 <= 3]) - < - sum([toInt(b_ExplicitWithFlags_Values[q29] = b_ExplicitWithFlags_Values[q42]) * - catchUndef(b_ExplicitWithFlags_Flags[q29], 0) - | q29 : int(1..3)]) - /\ - (and([a_ExplicitWithRepetition_Values[q33] < b_ExplicitWithFlags_Values[q42] -> - sum([toInt(a_ExplicitWithRepetition_Values[q32] = a_ExplicitWithRepetition_Values[q33]) - | q32 : int(1..3), q32 <= 3]) - = - sum([toInt(b_ExplicitWithFlags_Values[q30] = a_ExplicitWithRepetition_Values[q33]) * - catchUndef(b_ExplicitWithFlags_Flags[q30], 0) - | q30 : int(1..3)]) - | q33 : int(1..3), q33 <= 3]) - /\ - and([and([b_ExplicitWithFlags_Flags[q36] > 0, - !or([a_ExplicitWithRepetition_Values[q35] = b_ExplicitWithFlags_Values[q36] - | q35 : int(1..3), q35 <= 3]), - b_ExplicitWithFlags_Values[q36] < b_ExplicitWithFlags_Values[q42]; - int(1..3)]) - -> - sum([toInt(a_ExplicitWithRepetition_Values[q32] = b_ExplicitWithFlags_Values[q36]) - | q32 : int(1..3), q32 <= 3]) - = - sum([toInt(b_ExplicitWithFlags_Values[q30] = b_ExplicitWithFlags_Values[q36]) * - catchUndef(b_ExplicitWithFlags_Flags[q30], 0) - | q30 : int(1..3)]) - | q36 : int(1..3)]))) - | q42 : int(1..3)]), - and([a_ExplicitWithRepetition_Values[q1] <= a_ExplicitWithRepetition_Values[q1 + 1] | q1 : int(1..2), q1 + 1 <= 3]), - and([b_ExplicitWithFlags_Flags[q6 + 1] > 0 -> b_ExplicitWithFlags_Values[q6] < b_ExplicitWithFlags_Values[q6 + 1] - | q6 : int(1..2)]), - and([b_ExplicitWithFlags_Flags[q7] = 0 -> b_ExplicitWithFlags_Values[q7] = 1 | q7 : int(1..3)]), - and([b_ExplicitWithFlags_Flags[q8 + 1] > 0 -> b_ExplicitWithFlags_Flags[q8] > 0 | q8 : int(1..2)]), - 3 = sum([b_ExplicitWithFlags_Flags[q10] | q10 : int(1..3)]), - and([a_ExplicitWithFlags_Flags[q12 + 1] > 0 -> a_ExplicitWithFlags_Values[q12] < a_ExplicitWithFlags_Values[q12 + 1] - | q12 : int(1..2)]), - and([a_ExplicitWithFlags_Flags[q13] = 0 -> a_ExplicitWithFlags_Values[q13] = 1 | q13 : int(1..3)]), - and([a_ExplicitWithFlags_Flags[q14 + 1] > 0 -> a_ExplicitWithFlags_Flags[q14] > 0 | q14 : int(1..2)]), - 3 = sum([a_ExplicitWithFlags_Flags[q16] | q16 : int(1..3)]), - and([a_ExplicitWithFlags_Flags[q19] > 0 -> - sum([toInt(a_ExplicitWithFlags_Values[q20] = a_ExplicitWithFlags_Values[q19]) * - catchUndef(a_ExplicitWithFlags_Flags[q20], 0) - | q20 : int(1..3)]) - = - sum([toInt(a_ExplicitWithRepetition_Values[q22] = a_ExplicitWithFlags_Values[q19]) - | q22 : int(1..3), q22 <= 3]) - | q19 : int(1..3)]), - and([sum([toInt(a_ExplicitWithFlags_Values[q24] = a_ExplicitWithRepetition_Values[q23]) * - catchUndef(a_ExplicitWithFlags_Flags[q24], 0) - | q24 : int(1..3)]) - = - sum([toInt(a_ExplicitWithRepetition_Values[q26] = a_ExplicitWithRepetition_Values[q23]) - | q26 : int(1..3), q26 <= 3]) - | q23 : int(1..3), q23 <= 3]) - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_1_2-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_1_2-solution000001.solution deleted file mode 100644 index 1b4b5b08a6..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_1_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 2, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_1_2-solution000002.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_1_2-solution000002.solution deleted file mode 100644 index 5e2caa751c..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_1_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 2, 2) -letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_1_2-solution000003.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_1_2-solution000003.solution deleted file mode 100644 index 621d5f6edc..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_1_2-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 1, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_1_2-solution000004.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_1_2-solution000004.solution deleted file mode 100644 index d56a0bbcdc..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_1_2-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_1_2-solution000005.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_1_2-solution000005.solution deleted file mode 100644 index ff56905e23..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_1_2-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_1_2-solution000006.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_1_2-solution000006.solution deleted file mode 100644 index 15472caf03..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_1_2-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 2, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_1_2.eprime b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_1_2.eprime deleted file mode 100644 index b5d3afd5a7..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_1_2.eprime +++ /dev/null @@ -1,123 +0,0 @@ -language ESSENCE' 1.0 - -find a_ExplicitWithRepetition_Flag: int(3) -find a_ExplicitWithRepetition_Values: matrix indexed by [int(1..3)] of int(1..2) -find a_ExplicitWithFlags_Flags: matrix indexed by [int(1..3)] of int(0..3) -find a_ExplicitWithFlags_Values: matrix indexed by [int(1..3)] of int(1..2) -find b_ExplicitWithFlags_Flags: matrix indexed by [int(1..3)] of int(0..3) -find b_ExplicitWithFlags_Values: matrix indexed by [int(1..3)] of int(1..2) -find b_ExplicitWithRepetition_Flag: int(3) -find b_ExplicitWithRepetition_Values: matrix indexed by [int(1..3)] of int(1..2) -branching on - [a_ExplicitWithFlags_Flags, a_ExplicitWithFlags_Values, a_ExplicitWithRepetition_Flag, - a_ExplicitWithRepetition_Values, b_ExplicitWithRepetition_Flag, b_ExplicitWithRepetition_Values, - b_ExplicitWithFlags_Flags, b_ExplicitWithFlags_Values] -such that - or([sum([toInt(a_ExplicitWithRepetition_Values[q52] = a_ExplicitWithRepetition_Values[q53]) - | q52 : int(1..3), q52 <= 3]) - < - sum([toInt(b_ExplicitWithFlags_Values[q43] = a_ExplicitWithRepetition_Values[q53]) * - catchUndef(b_ExplicitWithFlags_Flags[q43], 0) - | q43 : int(1..3)]) - /\ - (and([a_ExplicitWithRepetition_Values[q47] < a_ExplicitWithRepetition_Values[q53] -> - sum([toInt(a_ExplicitWithRepetition_Values[q46] = a_ExplicitWithRepetition_Values[q47]) - | q46 : int(1..3), q46 <= 3]) - = - sum([toInt(b_ExplicitWithFlags_Values[q44] = a_ExplicitWithRepetition_Values[q47]) * - catchUndef(b_ExplicitWithFlags_Flags[q44], 0) - | q44 : int(1..3)]) - | q47 : int(1..3), q47 <= 3]) - /\ - and([and([b_ExplicitWithFlags_Flags[q50] > 0, - !or([a_ExplicitWithRepetition_Values[q49] = b_ExplicitWithFlags_Values[q50] - | q49 : int(1..3), q49 <= 3]), - b_ExplicitWithFlags_Values[q50] < a_ExplicitWithRepetition_Values[q53]; - int(1..3)]) - -> - sum([toInt(a_ExplicitWithRepetition_Values[q46] = b_ExplicitWithFlags_Values[q50]) - | q46 : int(1..3), q46 <= 3]) - = - sum([toInt(b_ExplicitWithFlags_Values[q44] = b_ExplicitWithFlags_Values[q50]) * - catchUndef(b_ExplicitWithFlags_Flags[q44], 0) - | q44 : int(1..3)]) - | q50 : int(1..3)])) - | q53 : int(1..3), q53 <= 3]) - \/ - or([b_ExplicitWithFlags_Flags[q56] > 0 /\ - !or([a_ExplicitWithRepetition_Values[q55] = b_ExplicitWithFlags_Values[q56] | q55 : int(1..3), q55 <= 3]) - /\ - (sum([toInt(a_ExplicitWithRepetition_Values[q52] = b_ExplicitWithFlags_Values[q56]) - | q52 : int(1..3), q52 <= 3]) - < - sum([toInt(b_ExplicitWithFlags_Values[q43] = b_ExplicitWithFlags_Values[q56]) * - catchUndef(b_ExplicitWithFlags_Flags[q43], 0) - | q43 : int(1..3)]) - /\ - (and([a_ExplicitWithRepetition_Values[q47] < b_ExplicitWithFlags_Values[q56] -> - sum([toInt(a_ExplicitWithRepetition_Values[q46] = a_ExplicitWithRepetition_Values[q47]) - | q46 : int(1..3), q46 <= 3]) - = - sum([toInt(b_ExplicitWithFlags_Values[q44] = a_ExplicitWithRepetition_Values[q47]) * - catchUndef(b_ExplicitWithFlags_Flags[q44], 0) - | q44 : int(1..3)]) - | q47 : int(1..3), q47 <= 3]) - /\ - and([and([b_ExplicitWithFlags_Flags[q50] > 0, - !or([a_ExplicitWithRepetition_Values[q49] = b_ExplicitWithFlags_Values[q50] - | q49 : int(1..3), q49 <= 3]), - b_ExplicitWithFlags_Values[q50] < b_ExplicitWithFlags_Values[q56]; - int(1..3)]) - -> - sum([toInt(a_ExplicitWithRepetition_Values[q46] = b_ExplicitWithFlags_Values[q50]) - | q46 : int(1..3), q46 <= 3]) - = - sum([toInt(b_ExplicitWithFlags_Values[q44] = b_ExplicitWithFlags_Values[q50]) * - catchUndef(b_ExplicitWithFlags_Flags[q44], 0) - | q44 : int(1..3)]) - | q50 : int(1..3)]))) - | q56 : int(1..3)]), - and([a_ExplicitWithRepetition_Values[q1] <= a_ExplicitWithRepetition_Values[q1 + 1] | q1 : int(1..2), q1 + 1 <= 3]), - and([b_ExplicitWithFlags_Flags[q6 + 1] > 0 -> b_ExplicitWithFlags_Values[q6] < b_ExplicitWithFlags_Values[q6 + 1] - | q6 : int(1..2)]), - and([b_ExplicitWithFlags_Flags[q7] = 0 -> b_ExplicitWithFlags_Values[q7] = 1 | q7 : int(1..3)]), - and([b_ExplicitWithFlags_Flags[q8 + 1] > 0 -> b_ExplicitWithFlags_Flags[q8] > 0 | q8 : int(1..2)]), - 3 = sum([b_ExplicitWithFlags_Flags[q10] | q10 : int(1..3)]), - and([a_ExplicitWithFlags_Flags[q12 + 1] > 0 -> a_ExplicitWithFlags_Values[q12] < a_ExplicitWithFlags_Values[q12 + 1] - | q12 : int(1..2)]), - and([a_ExplicitWithFlags_Flags[q13] = 0 -> a_ExplicitWithFlags_Values[q13] = 1 | q13 : int(1..3)]), - and([a_ExplicitWithFlags_Flags[q14 + 1] > 0 -> a_ExplicitWithFlags_Flags[q14] > 0 | q14 : int(1..2)]), - 3 = sum([a_ExplicitWithFlags_Flags[q16] | q16 : int(1..3)]), - and([a_ExplicitWithFlags_Flags[q19] > 0 -> - sum([toInt(a_ExplicitWithFlags_Values[q20] = a_ExplicitWithFlags_Values[q19]) * - catchUndef(a_ExplicitWithFlags_Flags[q20], 0) - | q20 : int(1..3)]) - = - sum([toInt(a_ExplicitWithRepetition_Values[q22] = a_ExplicitWithFlags_Values[q19]) - | q22 : int(1..3), q22 <= 3]) - | q19 : int(1..3)]), - and([sum([toInt(a_ExplicitWithFlags_Values[q24] = a_ExplicitWithRepetition_Values[q23]) * - catchUndef(a_ExplicitWithFlags_Flags[q24], 0) - | q24 : int(1..3)]) - = - sum([toInt(a_ExplicitWithRepetition_Values[q26] = a_ExplicitWithRepetition_Values[q23]) - | q26 : int(1..3), q26 <= 3]) - | q23 : int(1..3), q23 <= 3]), - and([b_ExplicitWithRepetition_Values[q27] <= b_ExplicitWithRepetition_Values[q27 + 1] - | q27 : int(1..2), q27 + 1 <= 3]), - and([sum([toInt(b_ExplicitWithRepetition_Values[q36] = b_ExplicitWithRepetition_Values[q33]) - | q36 : int(1..3), q36 <= 3]) - = - sum([toInt(b_ExplicitWithFlags_Values[q34] = b_ExplicitWithRepetition_Values[q33]) * - catchUndef(b_ExplicitWithFlags_Flags[q34], 0) - | q34 : int(1..3)]) - | q33 : int(1..3), q33 <= 3]), - and([b_ExplicitWithFlags_Flags[q37] > 0 -> - sum([toInt(b_ExplicitWithRepetition_Values[q40] = b_ExplicitWithFlags_Values[q37]) - | q40 : int(1..3), q40 <= 3]) - = - sum([toInt(b_ExplicitWithFlags_Values[q38] = b_ExplicitWithFlags_Values[q37]) * - catchUndef(b_ExplicitWithFlags_Flags[q38], 0) - | q38 : int(1..3)]) - | q37 : int(1..3)]) - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_1_3-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_1_3-solution000001.solution deleted file mode 100644 index 5e2caa751c..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_1_3-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 2, 2) -letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_1_3-solution000002.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_1_3-solution000002.solution deleted file mode 100644 index 1b4b5b08a6..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_1_3-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 2, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_1_3-solution000003.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_1_3-solution000003.solution deleted file mode 100644 index 621d5f6edc..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_1_3-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 1, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_1_3-solution000004.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_1_3-solution000004.solution deleted file mode 100644 index 15472caf03..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_1_3-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 2, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_1_3-solution000005.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_1_3-solution000005.solution deleted file mode 100644 index ff56905e23..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_1_3-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_1_3-solution000006.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_1_3-solution000006.solution deleted file mode 100644 index d56a0bbcdc..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_1_3-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_1_3.eprime b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_1_3.eprime deleted file mode 100644 index 2321c9502c..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_1_3.eprime +++ /dev/null @@ -1,116 +0,0 @@ -language ESSENCE' 1.0 - -find a_ExplicitWithRepetition_Flag: int(3) -find a_ExplicitWithRepetition_Values: matrix indexed by [int(1..3)] of int(1..2) -find a_ExplicitWithFlags_Flags: matrix indexed by [int(1..3)] of int(0..3) -find a_ExplicitWithFlags_Values: matrix indexed by [int(1..3)] of int(1..2) -find b_ExplicitWithFlags_Flags: matrix indexed by [int(1..3)] of int(0..3) -find b_ExplicitWithFlags_Values: matrix indexed by [int(1..3)] of int(1..2) -find b_MOccurrence: matrix indexed by [int(1..2)] of int(0..3) -branching on - [a_ExplicitWithFlags_Flags, a_ExplicitWithFlags_Values, a_ExplicitWithRepetition_Flag, - a_ExplicitWithRepetition_Values, b_MOccurrence, b_ExplicitWithFlags_Flags, b_ExplicitWithFlags_Values] -such that - or([sum([toInt(a_ExplicitWithRepetition_Values[q44] = a_ExplicitWithRepetition_Values[q45]) - | q44 : int(1..3), q44 <= 3]) - < - sum([toInt(b_ExplicitWithFlags_Values[q35] = a_ExplicitWithRepetition_Values[q45]) * - catchUndef(b_ExplicitWithFlags_Flags[q35], 0) - | q35 : int(1..3)]) - /\ - (and([a_ExplicitWithRepetition_Values[q39] < a_ExplicitWithRepetition_Values[q45] -> - sum([toInt(a_ExplicitWithRepetition_Values[q38] = a_ExplicitWithRepetition_Values[q39]) - | q38 : int(1..3), q38 <= 3]) - = - sum([toInt(b_ExplicitWithFlags_Values[q36] = a_ExplicitWithRepetition_Values[q39]) * - catchUndef(b_ExplicitWithFlags_Flags[q36], 0) - | q36 : int(1..3)]) - | q39 : int(1..3), q39 <= 3]) - /\ - and([and([b_ExplicitWithFlags_Flags[q42] > 0, - !or([a_ExplicitWithRepetition_Values[q41] = b_ExplicitWithFlags_Values[q42] - | q41 : int(1..3), q41 <= 3]), - b_ExplicitWithFlags_Values[q42] < a_ExplicitWithRepetition_Values[q45]; - int(1..3)]) - -> - sum([toInt(a_ExplicitWithRepetition_Values[q38] = b_ExplicitWithFlags_Values[q42]) - | q38 : int(1..3), q38 <= 3]) - = - sum([toInt(b_ExplicitWithFlags_Values[q36] = b_ExplicitWithFlags_Values[q42]) * - catchUndef(b_ExplicitWithFlags_Flags[q36], 0) - | q36 : int(1..3)]) - | q42 : int(1..3)])) - | q45 : int(1..3), q45 <= 3]) - \/ - or([b_ExplicitWithFlags_Flags[q48] > 0 /\ - !or([a_ExplicitWithRepetition_Values[q47] = b_ExplicitWithFlags_Values[q48] | q47 : int(1..3), q47 <= 3]) - /\ - (sum([toInt(a_ExplicitWithRepetition_Values[q44] = b_ExplicitWithFlags_Values[q48]) - | q44 : int(1..3), q44 <= 3]) - < - sum([toInt(b_ExplicitWithFlags_Values[q35] = b_ExplicitWithFlags_Values[q48]) * - catchUndef(b_ExplicitWithFlags_Flags[q35], 0) - | q35 : int(1..3)]) - /\ - (and([a_ExplicitWithRepetition_Values[q39] < b_ExplicitWithFlags_Values[q48] -> - sum([toInt(a_ExplicitWithRepetition_Values[q38] = a_ExplicitWithRepetition_Values[q39]) - | q38 : int(1..3), q38 <= 3]) - = - sum([toInt(b_ExplicitWithFlags_Values[q36] = a_ExplicitWithRepetition_Values[q39]) * - catchUndef(b_ExplicitWithFlags_Flags[q36], 0) - | q36 : int(1..3)]) - | q39 : int(1..3), q39 <= 3]) - /\ - and([and([b_ExplicitWithFlags_Flags[q42] > 0, - !or([a_ExplicitWithRepetition_Values[q41] = b_ExplicitWithFlags_Values[q42] - | q41 : int(1..3), q41 <= 3]), - b_ExplicitWithFlags_Values[q42] < b_ExplicitWithFlags_Values[q48]; - int(1..3)]) - -> - sum([toInt(a_ExplicitWithRepetition_Values[q38] = b_ExplicitWithFlags_Values[q42]) - | q38 : int(1..3), q38 <= 3]) - = - sum([toInt(b_ExplicitWithFlags_Values[q36] = b_ExplicitWithFlags_Values[q42]) * - catchUndef(b_ExplicitWithFlags_Flags[q36], 0) - | q36 : int(1..3)]) - | q42 : int(1..3)]))) - | q48 : int(1..3)]), - and([a_ExplicitWithRepetition_Values[q1] <= a_ExplicitWithRepetition_Values[q1 + 1] | q1 : int(1..2), q1 + 1 <= 3]), - and([b_ExplicitWithFlags_Flags[q6 + 1] > 0 -> b_ExplicitWithFlags_Values[q6] < b_ExplicitWithFlags_Values[q6 + 1] - | q6 : int(1..2)]), - and([b_ExplicitWithFlags_Flags[q7] = 0 -> b_ExplicitWithFlags_Values[q7] = 1 | q7 : int(1..3)]), - and([b_ExplicitWithFlags_Flags[q8 + 1] > 0 -> b_ExplicitWithFlags_Flags[q8] > 0 | q8 : int(1..2)]), - 3 = sum([b_ExplicitWithFlags_Flags[q10] | q10 : int(1..3)]), - and([a_ExplicitWithFlags_Flags[q12 + 1] > 0 -> a_ExplicitWithFlags_Values[q12] < a_ExplicitWithFlags_Values[q12 + 1] - | q12 : int(1..2)]), - and([a_ExplicitWithFlags_Flags[q13] = 0 -> a_ExplicitWithFlags_Values[q13] = 1 | q13 : int(1..3)]), - and([a_ExplicitWithFlags_Flags[q14 + 1] > 0 -> a_ExplicitWithFlags_Flags[q14] > 0 | q14 : int(1..2)]), - 3 = sum([a_ExplicitWithFlags_Flags[q16] | q16 : int(1..3)]), - and([a_ExplicitWithFlags_Flags[q19] > 0 -> - sum([toInt(a_ExplicitWithFlags_Values[q20] = a_ExplicitWithFlags_Values[q19]) * - catchUndef(a_ExplicitWithFlags_Flags[q20], 0) - | q20 : int(1..3)]) - = - sum([toInt(a_ExplicitWithRepetition_Values[q22] = a_ExplicitWithFlags_Values[q19]) - | q22 : int(1..3), q22 <= 3]) - | q19 : int(1..3)]), - and([sum([toInt(a_ExplicitWithFlags_Values[q24] = a_ExplicitWithRepetition_Values[q23]) * - catchUndef(a_ExplicitWithFlags_Flags[q24], 0) - | q24 : int(1..3)]) - = - sum([toInt(a_ExplicitWithRepetition_Values[q26] = a_ExplicitWithRepetition_Values[q23]) - | q26 : int(1..3), q26 <= 3]) - | q23 : int(1..3), q23 <= 3]), - 3 = sum([b_MOccurrence[q27] | q27 : int(1..2)]), - and([b_MOccurrence[q29] > 0 -> - b_MOccurrence[q29] = - sum([toInt(b_ExplicitWithFlags_Values[q30] = q29) * catchUndef(b_ExplicitWithFlags_Flags[q30], 0) - | q30 : int(1..3)]) - | q29 : int(1..2)]), - and([b_ExplicitWithFlags_Flags[q31] > 0 -> - b_MOccurrence[b_ExplicitWithFlags_Values[q31]] = - sum([toInt(b_ExplicitWithFlags_Values[q32] = b_ExplicitWithFlags_Values[q31]) * - catchUndef(b_ExplicitWithFlags_Flags[q32], 0) - | q32 : int(1..3)]) - | q31 : int(1..3)]) - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_2_1-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_2_1-solution000001.solution deleted file mode 100644 index 621d5f6edc..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_2_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 1, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_2_1-solution000002.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_2_1-solution000002.solution deleted file mode 100644 index 5e2caa751c..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_2_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 2, 2) -letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_2_1-solution000003.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_2_1-solution000003.solution deleted file mode 100644 index 1b4b5b08a6..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_2_1-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 2, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_2_1-solution000004.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_2_1-solution000004.solution deleted file mode 100644 index 15472caf03..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_2_1-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 2, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_2_1-solution000005.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_2_1-solution000005.solution deleted file mode 100644 index ff56905e23..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_2_1-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_2_1-solution000006.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_2_1-solution000006.solution deleted file mode 100644 index d56a0bbcdc..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_2_1-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_2_1.eprime b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_2_1.eprime deleted file mode 100644 index 227de3ed93..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_2_1.eprime +++ /dev/null @@ -1,81 +0,0 @@ -language ESSENCE' 1.0 - -find a_ExplicitWithRepetition_Flag: int(3) -find a_ExplicitWithRepetition_Values: matrix indexed by [int(1..3)] of int(1..2) -find b_ExplicitWithFlags_Flags: matrix indexed by [int(1..3)] of int(0..3) -find b_ExplicitWithFlags_Values: matrix indexed by [int(1..3)] of int(1..2) -branching on - [a_ExplicitWithRepetition_Flag, a_ExplicitWithRepetition_Values, b_ExplicitWithFlags_Flags, - b_ExplicitWithFlags_Values] -such that - or([sum([toInt(a_ExplicitWithRepetition_Values[q23] = a_ExplicitWithRepetition_Values[q24]) - | q23 : int(1..3), q23 <= 3]) - < - sum([toInt(b_ExplicitWithFlags_Values[q14] = a_ExplicitWithRepetition_Values[q24]) * - catchUndef(b_ExplicitWithFlags_Flags[q14], 0) - | q14 : int(1..3)]) - /\ - (and([a_ExplicitWithRepetition_Values[q18] < a_ExplicitWithRepetition_Values[q24] -> - sum([toInt(a_ExplicitWithRepetition_Values[q17] = a_ExplicitWithRepetition_Values[q18]) - | q17 : int(1..3), q17 <= 3]) - = - sum([toInt(b_ExplicitWithFlags_Values[q15] = a_ExplicitWithRepetition_Values[q18]) * - catchUndef(b_ExplicitWithFlags_Flags[q15], 0) - | q15 : int(1..3)]) - | q18 : int(1..3), q18 <= 3]) - /\ - and([and([b_ExplicitWithFlags_Flags[q21] > 0, - !or([a_ExplicitWithRepetition_Values[q20] = b_ExplicitWithFlags_Values[q21] - | q20 : int(1..3), q20 <= 3]), - b_ExplicitWithFlags_Values[q21] < a_ExplicitWithRepetition_Values[q24]; - int(1..3)]) - -> - sum([toInt(a_ExplicitWithRepetition_Values[q17] = b_ExplicitWithFlags_Values[q21]) - | q17 : int(1..3), q17 <= 3]) - = - sum([toInt(b_ExplicitWithFlags_Values[q15] = b_ExplicitWithFlags_Values[q21]) * - catchUndef(b_ExplicitWithFlags_Flags[q15], 0) - | q15 : int(1..3)]) - | q21 : int(1..3)])) - | q24 : int(1..3), q24 <= 3]) - \/ - or([b_ExplicitWithFlags_Flags[q27] > 0 /\ - !or([a_ExplicitWithRepetition_Values[q26] = b_ExplicitWithFlags_Values[q27] | q26 : int(1..3), q26 <= 3]) - /\ - (sum([toInt(a_ExplicitWithRepetition_Values[q23] = b_ExplicitWithFlags_Values[q27]) - | q23 : int(1..3), q23 <= 3]) - < - sum([toInt(b_ExplicitWithFlags_Values[q14] = b_ExplicitWithFlags_Values[q27]) * - catchUndef(b_ExplicitWithFlags_Flags[q14], 0) - | q14 : int(1..3)]) - /\ - (and([a_ExplicitWithRepetition_Values[q18] < b_ExplicitWithFlags_Values[q27] -> - sum([toInt(a_ExplicitWithRepetition_Values[q17] = a_ExplicitWithRepetition_Values[q18]) - | q17 : int(1..3), q17 <= 3]) - = - sum([toInt(b_ExplicitWithFlags_Values[q15] = a_ExplicitWithRepetition_Values[q18]) * - catchUndef(b_ExplicitWithFlags_Flags[q15], 0) - | q15 : int(1..3)]) - | q18 : int(1..3), q18 <= 3]) - /\ - and([and([b_ExplicitWithFlags_Flags[q21] > 0, - !or([a_ExplicitWithRepetition_Values[q20] = b_ExplicitWithFlags_Values[q21] - | q20 : int(1..3), q20 <= 3]), - b_ExplicitWithFlags_Values[q21] < b_ExplicitWithFlags_Values[q27]; - int(1..3)]) - -> - sum([toInt(a_ExplicitWithRepetition_Values[q17] = b_ExplicitWithFlags_Values[q21]) - | q17 : int(1..3), q17 <= 3]) - = - sum([toInt(b_ExplicitWithFlags_Values[q15] = b_ExplicitWithFlags_Values[q21]) * - catchUndef(b_ExplicitWithFlags_Flags[q15], 0) - | q15 : int(1..3)]) - | q21 : int(1..3)]))) - | q27 : int(1..3)]), - and([a_ExplicitWithRepetition_Values[q1] <= a_ExplicitWithRepetition_Values[q1 + 1] | q1 : int(1..2), q1 + 1 <= 3]), - and([b_ExplicitWithFlags_Flags[q6 + 1] > 0 -> b_ExplicitWithFlags_Values[q6] < b_ExplicitWithFlags_Values[q6 + 1] - | q6 : int(1..2)]), - and([b_ExplicitWithFlags_Flags[q7] = 0 -> b_ExplicitWithFlags_Values[q7] = 1 | q7 : int(1..3)]), - and([b_ExplicitWithFlags_Flags[q8 + 1] > 0 -> b_ExplicitWithFlags_Flags[q8] > 0 | q8 : int(1..2)]), - 3 = sum([b_ExplicitWithFlags_Flags[q10] | q10 : int(1..3)]) - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_2_2-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_2_2-solution000001.solution deleted file mode 100644 index 621d5f6edc..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_2_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 1, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_2_2-solution000002.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_2_2-solution000002.solution deleted file mode 100644 index 1b4b5b08a6..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_2_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 2, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_2_2-solution000003.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_2_2-solution000003.solution deleted file mode 100644 index 5e2caa751c..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_2_2-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 2, 2) -letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_2_2-solution000004.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_2_2-solution000004.solution deleted file mode 100644 index d56a0bbcdc..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_2_2-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_2_2-solution000005.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_2_2-solution000005.solution deleted file mode 100644 index ff56905e23..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_2_2-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_2_2-solution000006.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_2_2-solution000006.solution deleted file mode 100644 index 15472caf03..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_2_2-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 2, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_2_2.eprime b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_2_2.eprime deleted file mode 100644 index 85834943eb..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_2_2.eprime +++ /dev/null @@ -1,100 +0,0 @@ -language ESSENCE' 1.0 - -find a_ExplicitWithRepetition_Flag: int(3) -find a_ExplicitWithRepetition_Values: matrix indexed by [int(1..3)] of int(1..2) -find b_ExplicitWithFlags_Flags: matrix indexed by [int(1..3)] of int(0..3) -find b_ExplicitWithFlags_Values: matrix indexed by [int(1..3)] of int(1..2) -find b_ExplicitWithRepetition_Flag: int(3) -find b_ExplicitWithRepetition_Values: matrix indexed by [int(1..3)] of int(1..2) -branching on - [a_ExplicitWithRepetition_Flag, a_ExplicitWithRepetition_Values, b_ExplicitWithRepetition_Flag, - b_ExplicitWithRepetition_Values, b_ExplicitWithFlags_Flags, b_ExplicitWithFlags_Values] -such that - or([sum([toInt(a_ExplicitWithRepetition_Values[q37] = a_ExplicitWithRepetition_Values[q38]) - | q37 : int(1..3), q37 <= 3]) - < - sum([toInt(b_ExplicitWithFlags_Values[q28] = a_ExplicitWithRepetition_Values[q38]) * - catchUndef(b_ExplicitWithFlags_Flags[q28], 0) - | q28 : int(1..3)]) - /\ - (and([a_ExplicitWithRepetition_Values[q32] < a_ExplicitWithRepetition_Values[q38] -> - sum([toInt(a_ExplicitWithRepetition_Values[q31] = a_ExplicitWithRepetition_Values[q32]) - | q31 : int(1..3), q31 <= 3]) - = - sum([toInt(b_ExplicitWithFlags_Values[q29] = a_ExplicitWithRepetition_Values[q32]) * - catchUndef(b_ExplicitWithFlags_Flags[q29], 0) - | q29 : int(1..3)]) - | q32 : int(1..3), q32 <= 3]) - /\ - and([and([b_ExplicitWithFlags_Flags[q35] > 0, - !or([a_ExplicitWithRepetition_Values[q34] = b_ExplicitWithFlags_Values[q35] - | q34 : int(1..3), q34 <= 3]), - b_ExplicitWithFlags_Values[q35] < a_ExplicitWithRepetition_Values[q38]; - int(1..3)]) - -> - sum([toInt(a_ExplicitWithRepetition_Values[q31] = b_ExplicitWithFlags_Values[q35]) - | q31 : int(1..3), q31 <= 3]) - = - sum([toInt(b_ExplicitWithFlags_Values[q29] = b_ExplicitWithFlags_Values[q35]) * - catchUndef(b_ExplicitWithFlags_Flags[q29], 0) - | q29 : int(1..3)]) - | q35 : int(1..3)])) - | q38 : int(1..3), q38 <= 3]) - \/ - or([b_ExplicitWithFlags_Flags[q41] > 0 /\ - !or([a_ExplicitWithRepetition_Values[q40] = b_ExplicitWithFlags_Values[q41] | q40 : int(1..3), q40 <= 3]) - /\ - (sum([toInt(a_ExplicitWithRepetition_Values[q37] = b_ExplicitWithFlags_Values[q41]) - | q37 : int(1..3), q37 <= 3]) - < - sum([toInt(b_ExplicitWithFlags_Values[q28] = b_ExplicitWithFlags_Values[q41]) * - catchUndef(b_ExplicitWithFlags_Flags[q28], 0) - | q28 : int(1..3)]) - /\ - (and([a_ExplicitWithRepetition_Values[q32] < b_ExplicitWithFlags_Values[q41] -> - sum([toInt(a_ExplicitWithRepetition_Values[q31] = a_ExplicitWithRepetition_Values[q32]) - | q31 : int(1..3), q31 <= 3]) - = - sum([toInt(b_ExplicitWithFlags_Values[q29] = a_ExplicitWithRepetition_Values[q32]) * - catchUndef(b_ExplicitWithFlags_Flags[q29], 0) - | q29 : int(1..3)]) - | q32 : int(1..3), q32 <= 3]) - /\ - and([and([b_ExplicitWithFlags_Flags[q35] > 0, - !or([a_ExplicitWithRepetition_Values[q34] = b_ExplicitWithFlags_Values[q35] - | q34 : int(1..3), q34 <= 3]), - b_ExplicitWithFlags_Values[q35] < b_ExplicitWithFlags_Values[q41]; - int(1..3)]) - -> - sum([toInt(a_ExplicitWithRepetition_Values[q31] = b_ExplicitWithFlags_Values[q35]) - | q31 : int(1..3), q31 <= 3]) - = - sum([toInt(b_ExplicitWithFlags_Values[q29] = b_ExplicitWithFlags_Values[q35]) * - catchUndef(b_ExplicitWithFlags_Flags[q29], 0) - | q29 : int(1..3)]) - | q35 : int(1..3)]))) - | q41 : int(1..3)]), - and([a_ExplicitWithRepetition_Values[q1] <= a_ExplicitWithRepetition_Values[q1 + 1] | q1 : int(1..2), q1 + 1 <= 3]), - and([b_ExplicitWithFlags_Flags[q6 + 1] > 0 -> b_ExplicitWithFlags_Values[q6] < b_ExplicitWithFlags_Values[q6 + 1] - | q6 : int(1..2)]), - and([b_ExplicitWithFlags_Flags[q7] = 0 -> b_ExplicitWithFlags_Values[q7] = 1 | q7 : int(1..3)]), - and([b_ExplicitWithFlags_Flags[q8 + 1] > 0 -> b_ExplicitWithFlags_Flags[q8] > 0 | q8 : int(1..2)]), - 3 = sum([b_ExplicitWithFlags_Flags[q10] | q10 : int(1..3)]), - and([b_ExplicitWithRepetition_Values[q12] <= b_ExplicitWithRepetition_Values[q12 + 1] - | q12 : int(1..2), q12 + 1 <= 3]), - and([sum([toInt(b_ExplicitWithRepetition_Values[q21] = b_ExplicitWithRepetition_Values[q18]) - | q21 : int(1..3), q21 <= 3]) - = - sum([toInt(b_ExplicitWithFlags_Values[q19] = b_ExplicitWithRepetition_Values[q18]) * - catchUndef(b_ExplicitWithFlags_Flags[q19], 0) - | q19 : int(1..3)]) - | q18 : int(1..3), q18 <= 3]), - and([b_ExplicitWithFlags_Flags[q22] > 0 -> - sum([toInt(b_ExplicitWithRepetition_Values[q25] = b_ExplicitWithFlags_Values[q22]) - | q25 : int(1..3), q25 <= 3]) - = - sum([toInt(b_ExplicitWithFlags_Values[q23] = b_ExplicitWithFlags_Values[q22]) * - catchUndef(b_ExplicitWithFlags_Flags[q23], 0) - | q23 : int(1..3)]) - | q22 : int(1..3)]) - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_2_3-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_2_3-solution000001.solution deleted file mode 100644 index 621d5f6edc..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_2_3-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 1, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_2_3-solution000002.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_2_3-solution000002.solution deleted file mode 100644 index 5e2caa751c..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_2_3-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 2, 2) -letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_2_3-solution000003.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_2_3-solution000003.solution deleted file mode 100644 index 1b4b5b08a6..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_2_3-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 2, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_2_3-solution000004.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_2_3-solution000004.solution deleted file mode 100644 index 15472caf03..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_2_3-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 2, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_2_3-solution000005.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_2_3-solution000005.solution deleted file mode 100644 index ff56905e23..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_2_3-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_2_3-solution000006.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_2_3-solution000006.solution deleted file mode 100644 index d56a0bbcdc..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_2_3-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_2_3.eprime b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_2_3.eprime deleted file mode 100644 index 2feaeb041e..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_2_3.eprime +++ /dev/null @@ -1,94 +0,0 @@ -language ESSENCE' 1.0 - -find a_ExplicitWithRepetition_Flag: int(3) -find a_ExplicitWithRepetition_Values: matrix indexed by [int(1..3)] of int(1..2) -find b_ExplicitWithFlags_Flags: matrix indexed by [int(1..3)] of int(0..3) -find b_ExplicitWithFlags_Values: matrix indexed by [int(1..3)] of int(1..2) -find b_MOccurrence: matrix indexed by [int(1..2)] of int(0..3) -branching on - [a_ExplicitWithRepetition_Flag, a_ExplicitWithRepetition_Values, b_MOccurrence, b_ExplicitWithFlags_Flags, - b_ExplicitWithFlags_Values] -such that - or([sum([toInt(a_ExplicitWithRepetition_Values[q29] = a_ExplicitWithRepetition_Values[q30]) - | q29 : int(1..3), q29 <= 3]) - < - sum([toInt(b_ExplicitWithFlags_Values[q20] = a_ExplicitWithRepetition_Values[q30]) * - catchUndef(b_ExplicitWithFlags_Flags[q20], 0) - | q20 : int(1..3)]) - /\ - (and([a_ExplicitWithRepetition_Values[q24] < a_ExplicitWithRepetition_Values[q30] -> - sum([toInt(a_ExplicitWithRepetition_Values[q23] = a_ExplicitWithRepetition_Values[q24]) - | q23 : int(1..3), q23 <= 3]) - = - sum([toInt(b_ExplicitWithFlags_Values[q21] = a_ExplicitWithRepetition_Values[q24]) * - catchUndef(b_ExplicitWithFlags_Flags[q21], 0) - | q21 : int(1..3)]) - | q24 : int(1..3), q24 <= 3]) - /\ - and([and([b_ExplicitWithFlags_Flags[q27] > 0, - !or([a_ExplicitWithRepetition_Values[q26] = b_ExplicitWithFlags_Values[q27] - | q26 : int(1..3), q26 <= 3]), - b_ExplicitWithFlags_Values[q27] < a_ExplicitWithRepetition_Values[q30]; - int(1..3)]) - -> - sum([toInt(a_ExplicitWithRepetition_Values[q23] = b_ExplicitWithFlags_Values[q27]) - | q23 : int(1..3), q23 <= 3]) - = - sum([toInt(b_ExplicitWithFlags_Values[q21] = b_ExplicitWithFlags_Values[q27]) * - catchUndef(b_ExplicitWithFlags_Flags[q21], 0) - | q21 : int(1..3)]) - | q27 : int(1..3)])) - | q30 : int(1..3), q30 <= 3]) - \/ - or([b_ExplicitWithFlags_Flags[q33] > 0 /\ - !or([a_ExplicitWithRepetition_Values[q32] = b_ExplicitWithFlags_Values[q33] | q32 : int(1..3), q32 <= 3]) - /\ - (sum([toInt(a_ExplicitWithRepetition_Values[q29] = b_ExplicitWithFlags_Values[q33]) - | q29 : int(1..3), q29 <= 3]) - < - sum([toInt(b_ExplicitWithFlags_Values[q20] = b_ExplicitWithFlags_Values[q33]) * - catchUndef(b_ExplicitWithFlags_Flags[q20], 0) - | q20 : int(1..3)]) - /\ - (and([a_ExplicitWithRepetition_Values[q24] < b_ExplicitWithFlags_Values[q33] -> - sum([toInt(a_ExplicitWithRepetition_Values[q23] = a_ExplicitWithRepetition_Values[q24]) - | q23 : int(1..3), q23 <= 3]) - = - sum([toInt(b_ExplicitWithFlags_Values[q21] = a_ExplicitWithRepetition_Values[q24]) * - catchUndef(b_ExplicitWithFlags_Flags[q21], 0) - | q21 : int(1..3)]) - | q24 : int(1..3), q24 <= 3]) - /\ - and([and([b_ExplicitWithFlags_Flags[q27] > 0, - !or([a_ExplicitWithRepetition_Values[q26] = b_ExplicitWithFlags_Values[q27] - | q26 : int(1..3), q26 <= 3]), - b_ExplicitWithFlags_Values[q27] < b_ExplicitWithFlags_Values[q33]; - int(1..3)]) - -> - sum([toInt(a_ExplicitWithRepetition_Values[q23] = b_ExplicitWithFlags_Values[q27]) - | q23 : int(1..3), q23 <= 3]) - = - sum([toInt(b_ExplicitWithFlags_Values[q21] = b_ExplicitWithFlags_Values[q27]) * - catchUndef(b_ExplicitWithFlags_Flags[q21], 0) - | q21 : int(1..3)]) - | q27 : int(1..3)]))) - | q33 : int(1..3)]), - and([a_ExplicitWithRepetition_Values[q1] <= a_ExplicitWithRepetition_Values[q1 + 1] | q1 : int(1..2), q1 + 1 <= 3]), - and([b_ExplicitWithFlags_Flags[q6 + 1] > 0 -> b_ExplicitWithFlags_Values[q6] < b_ExplicitWithFlags_Values[q6 + 1] - | q6 : int(1..2)]), - and([b_ExplicitWithFlags_Flags[q7] = 0 -> b_ExplicitWithFlags_Values[q7] = 1 | q7 : int(1..3)]), - and([b_ExplicitWithFlags_Flags[q8 + 1] > 0 -> b_ExplicitWithFlags_Flags[q8] > 0 | q8 : int(1..2)]), - 3 = sum([b_ExplicitWithFlags_Flags[q10] | q10 : int(1..3)]), - 3 = sum([b_MOccurrence[q12] | q12 : int(1..2)]), - and([b_MOccurrence[q14] > 0 -> - b_MOccurrence[q14] = - sum([toInt(b_ExplicitWithFlags_Values[q15] = q14) * catchUndef(b_ExplicitWithFlags_Flags[q15], 0) - | q15 : int(1..3)]) - | q14 : int(1..2)]), - and([b_ExplicitWithFlags_Flags[q16] > 0 -> - b_MOccurrence[b_ExplicitWithFlags_Values[q16]] = - sum([toInt(b_ExplicitWithFlags_Values[q17] = b_ExplicitWithFlags_Values[q16]) * - catchUndef(b_ExplicitWithFlags_Flags[q17], 0) - | q17 : int(1..3)]) - | q16 : int(1..3)]) - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_3_1-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_3_1-solution000001.solution deleted file mode 100644 index 15472caf03..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_3_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 2, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_3_1-solution000002.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_3_1-solution000002.solution deleted file mode 100644 index ff56905e23..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_3_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_3_1-solution000003.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_3_1-solution000003.solution deleted file mode 100644 index d56a0bbcdc..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_3_1-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_3_1-solution000004.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_3_1-solution000004.solution deleted file mode 100644 index 5e2caa751c..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_3_1-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 2, 2) -letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_3_1-solution000005.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_3_1-solution000005.solution deleted file mode 100644 index 1b4b5b08a6..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_3_1-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 2, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_3_1-solution000006.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_3_1-solution000006.solution deleted file mode 100644 index 621d5f6edc..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_3_1-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 1, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_3_1.eprime b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_3_1.eprime deleted file mode 100644 index f5c9a18c0d..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_3_1.eprime +++ /dev/null @@ -1,90 +0,0 @@ -language ESSENCE' 1.0 - -find a_ExplicitWithRepetition_Flag: int(3) -find a_ExplicitWithRepetition_Values: matrix indexed by [int(1..3)] of int(1..2) -find a_MOccurrence: matrix indexed by [int(1..2)] of int(0..3) -find b_ExplicitWithFlags_Flags: matrix indexed by [int(1..3)] of int(0..3) -find b_ExplicitWithFlags_Values: matrix indexed by [int(1..3)] of int(1..2) -branching on - [a_MOccurrence, a_ExplicitWithRepetition_Flag, a_ExplicitWithRepetition_Values, b_ExplicitWithFlags_Flags, - b_ExplicitWithFlags_Values] -such that - or([sum([toInt(a_ExplicitWithRepetition_Values[q31] = a_ExplicitWithRepetition_Values[q32]) - | q31 : int(1..3), q31 <= 3]) - < - sum([toInt(b_ExplicitWithFlags_Values[q22] = a_ExplicitWithRepetition_Values[q32]) * - catchUndef(b_ExplicitWithFlags_Flags[q22], 0) - | q22 : int(1..3)]) - /\ - (and([a_ExplicitWithRepetition_Values[q26] < a_ExplicitWithRepetition_Values[q32] -> - sum([toInt(a_ExplicitWithRepetition_Values[q25] = a_ExplicitWithRepetition_Values[q26]) - | q25 : int(1..3), q25 <= 3]) - = - sum([toInt(b_ExplicitWithFlags_Values[q23] = a_ExplicitWithRepetition_Values[q26]) * - catchUndef(b_ExplicitWithFlags_Flags[q23], 0) - | q23 : int(1..3)]) - | q26 : int(1..3), q26 <= 3]) - /\ - and([and([b_ExplicitWithFlags_Flags[q29] > 0, - !or([a_ExplicitWithRepetition_Values[q28] = b_ExplicitWithFlags_Values[q29] - | q28 : int(1..3), q28 <= 3]), - b_ExplicitWithFlags_Values[q29] < a_ExplicitWithRepetition_Values[q32]; - int(1..3)]) - -> - sum([toInt(a_ExplicitWithRepetition_Values[q25] = b_ExplicitWithFlags_Values[q29]) - | q25 : int(1..3), q25 <= 3]) - = - sum([toInt(b_ExplicitWithFlags_Values[q23] = b_ExplicitWithFlags_Values[q29]) * - catchUndef(b_ExplicitWithFlags_Flags[q23], 0) - | q23 : int(1..3)]) - | q29 : int(1..3)])) - | q32 : int(1..3), q32 <= 3]) - \/ - or([b_ExplicitWithFlags_Flags[q35] > 0 /\ - !or([a_ExplicitWithRepetition_Values[q34] = b_ExplicitWithFlags_Values[q35] | q34 : int(1..3), q34 <= 3]) - /\ - (sum([toInt(a_ExplicitWithRepetition_Values[q31] = b_ExplicitWithFlags_Values[q35]) - | q31 : int(1..3), q31 <= 3]) - < - sum([toInt(b_ExplicitWithFlags_Values[q22] = b_ExplicitWithFlags_Values[q35]) * - catchUndef(b_ExplicitWithFlags_Flags[q22], 0) - | q22 : int(1..3)]) - /\ - (and([a_ExplicitWithRepetition_Values[q26] < b_ExplicitWithFlags_Values[q35] -> - sum([toInt(a_ExplicitWithRepetition_Values[q25] = a_ExplicitWithRepetition_Values[q26]) - | q25 : int(1..3), q25 <= 3]) - = - sum([toInt(b_ExplicitWithFlags_Values[q23] = a_ExplicitWithRepetition_Values[q26]) * - catchUndef(b_ExplicitWithFlags_Flags[q23], 0) - | q23 : int(1..3)]) - | q26 : int(1..3), q26 <= 3]) - /\ - and([and([b_ExplicitWithFlags_Flags[q29] > 0, - !or([a_ExplicitWithRepetition_Values[q28] = b_ExplicitWithFlags_Values[q29] - | q28 : int(1..3), q28 <= 3]), - b_ExplicitWithFlags_Values[q29] < b_ExplicitWithFlags_Values[q35]; - int(1..3)]) - -> - sum([toInt(a_ExplicitWithRepetition_Values[q25] = b_ExplicitWithFlags_Values[q29]) - | q25 : int(1..3), q25 <= 3]) - = - sum([toInt(b_ExplicitWithFlags_Values[q23] = b_ExplicitWithFlags_Values[q29]) * - catchUndef(b_ExplicitWithFlags_Flags[q23], 0) - | q23 : int(1..3)]) - | q29 : int(1..3)]))) - | q35 : int(1..3)]), - and([a_ExplicitWithRepetition_Values[q1] <= a_ExplicitWithRepetition_Values[q1 + 1] | q1 : int(1..2), q1 + 1 <= 3]), - and([b_ExplicitWithFlags_Flags[q6 + 1] > 0 -> b_ExplicitWithFlags_Values[q6] < b_ExplicitWithFlags_Values[q6 + 1] - | q6 : int(1..2)]), - and([b_ExplicitWithFlags_Flags[q7] = 0 -> b_ExplicitWithFlags_Values[q7] = 1 | q7 : int(1..3)]), - and([b_ExplicitWithFlags_Flags[q8 + 1] > 0 -> b_ExplicitWithFlags_Flags[q8] > 0 | q8 : int(1..2)]), - 3 = sum([b_ExplicitWithFlags_Flags[q10] | q10 : int(1..3)]), - 3 = sum([a_MOccurrence[q12] | q12 : int(1..2)]), - and([a_MOccurrence[q14] > 0 -> - a_MOccurrence[q14] = sum([toInt(a_ExplicitWithRepetition_Values[q16] = q14) | q16 : int(1..3), q16 <= 3]) - | q14 : int(1..2)]), - and([a_MOccurrence[a_ExplicitWithRepetition_Values[q17]] = - sum([toInt(a_ExplicitWithRepetition_Values[q19] = a_ExplicitWithRepetition_Values[q17]) - | q19 : int(1..3), q19 <= 3]) - | q17 : int(1..3), q17 <= 3]) - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_3_2-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_3_2-solution000001.solution deleted file mode 100644 index d56a0bbcdc..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_3_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_3_2-solution000002.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_3_2-solution000002.solution deleted file mode 100644 index ff56905e23..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_3_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_3_2-solution000003.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_3_2-solution000003.solution deleted file mode 100644 index 15472caf03..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_3_2-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 2, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_3_2-solution000004.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_3_2-solution000004.solution deleted file mode 100644 index 1b4b5b08a6..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_3_2-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 2, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_3_2-solution000005.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_3_2-solution000005.solution deleted file mode 100644 index 5e2caa751c..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_3_2-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 2, 2) -letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_3_2-solution000006.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_3_2-solution000006.solution deleted file mode 100644 index 621d5f6edc..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_3_2-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 1, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_3_2.eprime b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_3_2.eprime deleted file mode 100644 index 4638ce0096..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_3_2.eprime +++ /dev/null @@ -1,109 +0,0 @@ -language ESSENCE' 1.0 - -find a_ExplicitWithRepetition_Flag: int(3) -find a_ExplicitWithRepetition_Values: matrix indexed by [int(1..3)] of int(1..2) -find a_MOccurrence: matrix indexed by [int(1..2)] of int(0..3) -find b_ExplicitWithFlags_Flags: matrix indexed by [int(1..3)] of int(0..3) -find b_ExplicitWithFlags_Values: matrix indexed by [int(1..3)] of int(1..2) -find b_ExplicitWithRepetition_Flag: int(3) -find b_ExplicitWithRepetition_Values: matrix indexed by [int(1..3)] of int(1..2) -branching on - [a_MOccurrence, a_ExplicitWithRepetition_Flag, a_ExplicitWithRepetition_Values, b_ExplicitWithRepetition_Flag, - b_ExplicitWithRepetition_Values, b_ExplicitWithFlags_Flags, b_ExplicitWithFlags_Values] -such that - or([sum([toInt(a_ExplicitWithRepetition_Values[q45] = a_ExplicitWithRepetition_Values[q46]) - | q45 : int(1..3), q45 <= 3]) - < - sum([toInt(b_ExplicitWithFlags_Values[q36] = a_ExplicitWithRepetition_Values[q46]) * - catchUndef(b_ExplicitWithFlags_Flags[q36], 0) - | q36 : int(1..3)]) - /\ - (and([a_ExplicitWithRepetition_Values[q40] < a_ExplicitWithRepetition_Values[q46] -> - sum([toInt(a_ExplicitWithRepetition_Values[q39] = a_ExplicitWithRepetition_Values[q40]) - | q39 : int(1..3), q39 <= 3]) - = - sum([toInt(b_ExplicitWithFlags_Values[q37] = a_ExplicitWithRepetition_Values[q40]) * - catchUndef(b_ExplicitWithFlags_Flags[q37], 0) - | q37 : int(1..3)]) - | q40 : int(1..3), q40 <= 3]) - /\ - and([and([b_ExplicitWithFlags_Flags[q43] > 0, - !or([a_ExplicitWithRepetition_Values[q42] = b_ExplicitWithFlags_Values[q43] - | q42 : int(1..3), q42 <= 3]), - b_ExplicitWithFlags_Values[q43] < a_ExplicitWithRepetition_Values[q46]; - int(1..3)]) - -> - sum([toInt(a_ExplicitWithRepetition_Values[q39] = b_ExplicitWithFlags_Values[q43]) - | q39 : int(1..3), q39 <= 3]) - = - sum([toInt(b_ExplicitWithFlags_Values[q37] = b_ExplicitWithFlags_Values[q43]) * - catchUndef(b_ExplicitWithFlags_Flags[q37], 0) - | q37 : int(1..3)]) - | q43 : int(1..3)])) - | q46 : int(1..3), q46 <= 3]) - \/ - or([b_ExplicitWithFlags_Flags[q49] > 0 /\ - !or([a_ExplicitWithRepetition_Values[q48] = b_ExplicitWithFlags_Values[q49] | q48 : int(1..3), q48 <= 3]) - /\ - (sum([toInt(a_ExplicitWithRepetition_Values[q45] = b_ExplicitWithFlags_Values[q49]) - | q45 : int(1..3), q45 <= 3]) - < - sum([toInt(b_ExplicitWithFlags_Values[q36] = b_ExplicitWithFlags_Values[q49]) * - catchUndef(b_ExplicitWithFlags_Flags[q36], 0) - | q36 : int(1..3)]) - /\ - (and([a_ExplicitWithRepetition_Values[q40] < b_ExplicitWithFlags_Values[q49] -> - sum([toInt(a_ExplicitWithRepetition_Values[q39] = a_ExplicitWithRepetition_Values[q40]) - | q39 : int(1..3), q39 <= 3]) - = - sum([toInt(b_ExplicitWithFlags_Values[q37] = a_ExplicitWithRepetition_Values[q40]) * - catchUndef(b_ExplicitWithFlags_Flags[q37], 0) - | q37 : int(1..3)]) - | q40 : int(1..3), q40 <= 3]) - /\ - and([and([b_ExplicitWithFlags_Flags[q43] > 0, - !or([a_ExplicitWithRepetition_Values[q42] = b_ExplicitWithFlags_Values[q43] - | q42 : int(1..3), q42 <= 3]), - b_ExplicitWithFlags_Values[q43] < b_ExplicitWithFlags_Values[q49]; - int(1..3)]) - -> - sum([toInt(a_ExplicitWithRepetition_Values[q39] = b_ExplicitWithFlags_Values[q43]) - | q39 : int(1..3), q39 <= 3]) - = - sum([toInt(b_ExplicitWithFlags_Values[q37] = b_ExplicitWithFlags_Values[q43]) * - catchUndef(b_ExplicitWithFlags_Flags[q37], 0) - | q37 : int(1..3)]) - | q43 : int(1..3)]))) - | q49 : int(1..3)]), - and([a_ExplicitWithRepetition_Values[q1] <= a_ExplicitWithRepetition_Values[q1 + 1] | q1 : int(1..2), q1 + 1 <= 3]), - and([b_ExplicitWithFlags_Flags[q6 + 1] > 0 -> b_ExplicitWithFlags_Values[q6] < b_ExplicitWithFlags_Values[q6 + 1] - | q6 : int(1..2)]), - and([b_ExplicitWithFlags_Flags[q7] = 0 -> b_ExplicitWithFlags_Values[q7] = 1 | q7 : int(1..3)]), - and([b_ExplicitWithFlags_Flags[q8 + 1] > 0 -> b_ExplicitWithFlags_Flags[q8] > 0 | q8 : int(1..2)]), - 3 = sum([b_ExplicitWithFlags_Flags[q10] | q10 : int(1..3)]), - 3 = sum([a_MOccurrence[q12] | q12 : int(1..2)]), - and([a_MOccurrence[q28] > 0 -> - a_MOccurrence[q28] = sum([toInt(a_ExplicitWithRepetition_Values[q30] = q28) | q30 : int(1..3), q30 <= 3]) - | q28 : int(1..2)]), - and([a_MOccurrence[a_ExplicitWithRepetition_Values[q31]] = - sum([toInt(a_ExplicitWithRepetition_Values[q33] = a_ExplicitWithRepetition_Values[q31]) - | q33 : int(1..3), q33 <= 3]) - | q31 : int(1..3), q31 <= 3]), - and([b_ExplicitWithRepetition_Values[q13] <= b_ExplicitWithRepetition_Values[q13 + 1] - | q13 : int(1..2), q13 + 1 <= 3]), - and([sum([toInt(b_ExplicitWithRepetition_Values[q22] = b_ExplicitWithRepetition_Values[q19]) - | q22 : int(1..3), q22 <= 3]) - = - sum([toInt(b_ExplicitWithFlags_Values[q20] = b_ExplicitWithRepetition_Values[q19]) * - catchUndef(b_ExplicitWithFlags_Flags[q20], 0) - | q20 : int(1..3)]) - | q19 : int(1..3), q19 <= 3]), - and([b_ExplicitWithFlags_Flags[q23] > 0 -> - sum([toInt(b_ExplicitWithRepetition_Values[q26] = b_ExplicitWithFlags_Values[q23]) - | q26 : int(1..3), q26 <= 3]) - = - sum([toInt(b_ExplicitWithFlags_Values[q24] = b_ExplicitWithFlags_Values[q23]) * - catchUndef(b_ExplicitWithFlags_Flags[q24], 0) - | q24 : int(1..3)]) - | q23 : int(1..3)]) - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_3_3-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_3_3-solution000001.solution deleted file mode 100644 index 15472caf03..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_3_3-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 2, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_3_3-solution000002.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_3_3-solution000002.solution deleted file mode 100644 index ff56905e23..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_3_3-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_3_3-solution000003.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_3_3-solution000003.solution deleted file mode 100644 index d56a0bbcdc..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_3_3-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_3_3-solution000004.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_3_3-solution000004.solution deleted file mode 100644 index 5e2caa751c..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_3_3-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 2, 2) -letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_3_3-solution000005.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_3_3-solution000005.solution deleted file mode 100644 index 1b4b5b08a6..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_3_3-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 2, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_3_3-solution000006.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_3_3-solution000006.solution deleted file mode 100644 index 621d5f6edc..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_3_3-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 1, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_3_3.eprime b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_3_3.eprime deleted file mode 100644 index 614e5a2439..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_3_3.eprime +++ /dev/null @@ -1,103 +0,0 @@ -language ESSENCE' 1.0 - -find a_ExplicitWithRepetition_Flag: int(3) -find a_ExplicitWithRepetition_Values: matrix indexed by [int(1..3)] of int(1..2) -find a_MOccurrence: matrix indexed by [int(1..2)] of int(0..3) -find b_ExplicitWithFlags_Flags: matrix indexed by [int(1..3)] of int(0..3) -find b_ExplicitWithFlags_Values: matrix indexed by [int(1..3)] of int(1..2) -find b_MOccurrence: matrix indexed by [int(1..2)] of int(0..3) -branching on - [a_MOccurrence, a_ExplicitWithRepetition_Flag, a_ExplicitWithRepetition_Values, b_MOccurrence, - b_ExplicitWithFlags_Flags, b_ExplicitWithFlags_Values] -such that - or([sum([toInt(a_ExplicitWithRepetition_Values[q37] = a_ExplicitWithRepetition_Values[q38]) - | q37 : int(1..3), q37 <= 3]) - < - sum([toInt(b_ExplicitWithFlags_Values[q28] = a_ExplicitWithRepetition_Values[q38]) * - catchUndef(b_ExplicitWithFlags_Flags[q28], 0) - | q28 : int(1..3)]) - /\ - (and([a_ExplicitWithRepetition_Values[q32] < a_ExplicitWithRepetition_Values[q38] -> - sum([toInt(a_ExplicitWithRepetition_Values[q31] = a_ExplicitWithRepetition_Values[q32]) - | q31 : int(1..3), q31 <= 3]) - = - sum([toInt(b_ExplicitWithFlags_Values[q29] = a_ExplicitWithRepetition_Values[q32]) * - catchUndef(b_ExplicitWithFlags_Flags[q29], 0) - | q29 : int(1..3)]) - | q32 : int(1..3), q32 <= 3]) - /\ - and([and([b_ExplicitWithFlags_Flags[q35] > 0, - !or([a_ExplicitWithRepetition_Values[q34] = b_ExplicitWithFlags_Values[q35] - | q34 : int(1..3), q34 <= 3]), - b_ExplicitWithFlags_Values[q35] < a_ExplicitWithRepetition_Values[q38]; - int(1..3)]) - -> - sum([toInt(a_ExplicitWithRepetition_Values[q31] = b_ExplicitWithFlags_Values[q35]) - | q31 : int(1..3), q31 <= 3]) - = - sum([toInt(b_ExplicitWithFlags_Values[q29] = b_ExplicitWithFlags_Values[q35]) * - catchUndef(b_ExplicitWithFlags_Flags[q29], 0) - | q29 : int(1..3)]) - | q35 : int(1..3)])) - | q38 : int(1..3), q38 <= 3]) - \/ - or([b_ExplicitWithFlags_Flags[q41] > 0 /\ - !or([a_ExplicitWithRepetition_Values[q40] = b_ExplicitWithFlags_Values[q41] | q40 : int(1..3), q40 <= 3]) - /\ - (sum([toInt(a_ExplicitWithRepetition_Values[q37] = b_ExplicitWithFlags_Values[q41]) - | q37 : int(1..3), q37 <= 3]) - < - sum([toInt(b_ExplicitWithFlags_Values[q28] = b_ExplicitWithFlags_Values[q41]) * - catchUndef(b_ExplicitWithFlags_Flags[q28], 0) - | q28 : int(1..3)]) - /\ - (and([a_ExplicitWithRepetition_Values[q32] < b_ExplicitWithFlags_Values[q41] -> - sum([toInt(a_ExplicitWithRepetition_Values[q31] = a_ExplicitWithRepetition_Values[q32]) - | q31 : int(1..3), q31 <= 3]) - = - sum([toInt(b_ExplicitWithFlags_Values[q29] = a_ExplicitWithRepetition_Values[q32]) * - catchUndef(b_ExplicitWithFlags_Flags[q29], 0) - | q29 : int(1..3)]) - | q32 : int(1..3), q32 <= 3]) - /\ - and([and([b_ExplicitWithFlags_Flags[q35] > 0, - !or([a_ExplicitWithRepetition_Values[q34] = b_ExplicitWithFlags_Values[q35] - | q34 : int(1..3), q34 <= 3]), - b_ExplicitWithFlags_Values[q35] < b_ExplicitWithFlags_Values[q41]; - int(1..3)]) - -> - sum([toInt(a_ExplicitWithRepetition_Values[q31] = b_ExplicitWithFlags_Values[q35]) - | q31 : int(1..3), q31 <= 3]) - = - sum([toInt(b_ExplicitWithFlags_Values[q29] = b_ExplicitWithFlags_Values[q35]) * - catchUndef(b_ExplicitWithFlags_Flags[q29], 0) - | q29 : int(1..3)]) - | q35 : int(1..3)]))) - | q41 : int(1..3)]), - and([a_ExplicitWithRepetition_Values[q1] <= a_ExplicitWithRepetition_Values[q1 + 1] | q1 : int(1..2), q1 + 1 <= 3]), - and([b_ExplicitWithFlags_Flags[q6 + 1] > 0 -> b_ExplicitWithFlags_Values[q6] < b_ExplicitWithFlags_Values[q6 + 1] - | q6 : int(1..2)]), - and([b_ExplicitWithFlags_Flags[q7] = 0 -> b_ExplicitWithFlags_Values[q7] = 1 | q7 : int(1..3)]), - and([b_ExplicitWithFlags_Flags[q8 + 1] > 0 -> b_ExplicitWithFlags_Flags[q8] > 0 | q8 : int(1..2)]), - 3 = sum([b_ExplicitWithFlags_Flags[q10] | q10 : int(1..3)]), - 3 = sum([a_MOccurrence[q12] | q12 : int(1..2)]), - and([a_MOccurrence[q20] > 0 -> - a_MOccurrence[q20] = sum([toInt(a_ExplicitWithRepetition_Values[q22] = q20) | q22 : int(1..3), q22 <= 3]) - | q20 : int(1..2)]), - and([a_MOccurrence[a_ExplicitWithRepetition_Values[q23]] = - sum([toInt(a_ExplicitWithRepetition_Values[q25] = a_ExplicitWithRepetition_Values[q23]) - | q25 : int(1..3), q25 <= 3]) - | q23 : int(1..3), q23 <= 3]), - 3 = sum([b_MOccurrence[q13] | q13 : int(1..2)]), - and([b_MOccurrence[q15] > 0 -> - b_MOccurrence[q15] = - sum([toInt(b_ExplicitWithFlags_Values[q16] = q15) * catchUndef(b_ExplicitWithFlags_Flags[q16], 0) - | q16 : int(1..3)]) - | q15 : int(1..2)]), - and([b_ExplicitWithFlags_Flags[q17] > 0 -> - b_MOccurrence[b_ExplicitWithFlags_Values[q17]] = - sum([toInt(b_ExplicitWithFlags_Values[q18] = b_ExplicitWithFlags_Values[q17]) * - catchUndef(b_ExplicitWithFlags_Flags[q18], 0) - | q18 : int(1..3)]) - | q17 : int(1..3)]) - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_1_1-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_1_1-solution000001.solution deleted file mode 100644 index 5e2caa751c..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_1_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 2, 2) -letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_1_1-solution000002.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_1_1-solution000002.solution deleted file mode 100644 index 1b4b5b08a6..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_1_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 2, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_1_1-solution000003.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_1_1-solution000003.solution deleted file mode 100644 index 621d5f6edc..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_1_1-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 1, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_1_1-solution000004.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_1_1-solution000004.solution deleted file mode 100644 index 15472caf03..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_1_1-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 2, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_1_1-solution000005.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_1_1-solution000005.solution deleted file mode 100644 index ff56905e23..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_1_1-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_1_1-solution000006.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_1_1-solution000006.solution deleted file mode 100644 index d56a0bbcdc..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_1_1-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_1_1.eprime b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_1_1.eprime deleted file mode 100644 index cb60481286..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_1_1.eprime +++ /dev/null @@ -1,111 +0,0 @@ -language ESSENCE' 1.0 - -find a_ExplicitWithRepetition_Flag: int(3) -find a_ExplicitWithRepetition_Values: matrix indexed by [int(1..3)] of int(1..2) -find a_ExplicitWithFlags_Flags: matrix indexed by [int(1..3)] of int(0..3) -find a_ExplicitWithFlags_Values: matrix indexed by [int(1..3)] of int(1..2) -find b_ExplicitWithRepetition_Flag: int(3) -find b_ExplicitWithRepetition_Values: matrix indexed by [int(1..3)] of int(1..2) -find b_ExplicitWithFlags_Flags: matrix indexed by [int(1..3)] of int(0..3) -find b_ExplicitWithFlags_Values: matrix indexed by [int(1..3)] of int(1..2) -branching on - [a_ExplicitWithFlags_Flags, a_ExplicitWithFlags_Values, a_ExplicitWithRepetition_Flag, - a_ExplicitWithRepetition_Values, b_ExplicitWithFlags_Flags, b_ExplicitWithFlags_Values, - b_ExplicitWithRepetition_Flag, b_ExplicitWithRepetition_Values] -such that - or([sum([toInt(a_ExplicitWithRepetition_Values[q64] = a_ExplicitWithRepetition_Values[q43]) - | q64 : int(1..3), q64 <= 3]) - < - sum([toInt(b_ExplicitWithRepetition_Values[q66] = a_ExplicitWithRepetition_Values[q43]) - | q66 : int(1..3), q66 <= 3]) - /\ - (and([a_ExplicitWithRepetition_Values[q67] < a_ExplicitWithRepetition_Values[q43] -> - sum([toInt(a_ExplicitWithRepetition_Values[q76] = a_ExplicitWithRepetition_Values[q67]) - | q76 : int(1..3), q76 <= 3]) - = - sum([toInt(b_ExplicitWithRepetition_Values[q78] = a_ExplicitWithRepetition_Values[q67]) - | q78 : int(1..3), q78 <= 3]) - | q67 : int(1..3), q67 <= 3]) - /\ - and([!or([a_ExplicitWithRepetition_Values[q70] = b_ExplicitWithRepetition_Values[q68] - | q70 : int(1..3), q70 <= 3]) - /\ b_ExplicitWithRepetition_Values[q68] < a_ExplicitWithRepetition_Values[q43] - -> - sum([toInt(a_ExplicitWithRepetition_Values[q72] = b_ExplicitWithRepetition_Values[q68]) - | q72 : int(1..3), q72 <= 3]) - = - sum([toInt(b_ExplicitWithRepetition_Values[q74] = b_ExplicitWithRepetition_Values[q68]) - | q74 : int(1..3), q74 <= 3]) - | q68 : int(1..3), q68 <= 3])) - | q43 : int(1..3), q43 <= 3]) - \/ - or([!or([a_ExplicitWithRepetition_Values[q46] = b_ExplicitWithRepetition_Values[q44] | q46 : int(1..3), q46 <= 3]) - /\ - (sum([toInt(a_ExplicitWithRepetition_Values[q48] = b_ExplicitWithRepetition_Values[q44]) - | q48 : int(1..3), q48 <= 3]) - < - sum([toInt(b_ExplicitWithRepetition_Values[q50] = b_ExplicitWithRepetition_Values[q44]) - | q50 : int(1..3), q50 <= 3]) - /\ - (and([a_ExplicitWithRepetition_Values[q51] < b_ExplicitWithRepetition_Values[q44] -> - sum([toInt(a_ExplicitWithRepetition_Values[q60] = a_ExplicitWithRepetition_Values[q51]) - | q60 : int(1..3), q60 <= 3]) - = - sum([toInt(b_ExplicitWithRepetition_Values[q62] = a_ExplicitWithRepetition_Values[q51]) - | q62 : int(1..3), q62 <= 3]) - | q51 : int(1..3), q51 <= 3]) - /\ - and([!or([a_ExplicitWithRepetition_Values[q54] = b_ExplicitWithRepetition_Values[q52] - | q54 : int(1..3), q54 <= 3]) - /\ b_ExplicitWithRepetition_Values[q52] < b_ExplicitWithRepetition_Values[q44] - -> - sum([toInt(a_ExplicitWithRepetition_Values[q56] = b_ExplicitWithRepetition_Values[q52]) - | q56 : int(1..3), q56 <= 3]) - = - sum([toInt(b_ExplicitWithRepetition_Values[q58] = b_ExplicitWithRepetition_Values[q52]) - | q58 : int(1..3), q58 <= 3]) - | q52 : int(1..3), q52 <= 3]))) - | q44 : int(1..3), q44 <= 3]), - and([a_ExplicitWithRepetition_Values[q1] <= a_ExplicitWithRepetition_Values[q1 + 1] | q1 : int(1..2), q1 + 1 <= 3]), - and([b_ExplicitWithRepetition_Values[q6] <= b_ExplicitWithRepetition_Values[q6 + 1] | q6 : int(1..2), q6 + 1 <= 3]), - and([a_ExplicitWithFlags_Flags[q11 + 1] > 0 -> a_ExplicitWithFlags_Values[q11] < a_ExplicitWithFlags_Values[q11 + 1] - | q11 : int(1..2)]), - and([a_ExplicitWithFlags_Flags[q12] = 0 -> a_ExplicitWithFlags_Values[q12] = 1 | q12 : int(1..3)]), - and([a_ExplicitWithFlags_Flags[q13 + 1] > 0 -> a_ExplicitWithFlags_Flags[q13] > 0 | q13 : int(1..2)]), - 3 = sum([a_ExplicitWithFlags_Flags[q15] | q15 : int(1..3)]), - and([a_ExplicitWithFlags_Flags[q18] > 0 -> - sum([toInt(a_ExplicitWithFlags_Values[q19] = a_ExplicitWithFlags_Values[q18]) * - catchUndef(a_ExplicitWithFlags_Flags[q19], 0) - | q19 : int(1..3)]) - = - sum([toInt(a_ExplicitWithRepetition_Values[q21] = a_ExplicitWithFlags_Values[q18]) - | q21 : int(1..3), q21 <= 3]) - | q18 : int(1..3)]), - and([sum([toInt(a_ExplicitWithFlags_Values[q23] = a_ExplicitWithRepetition_Values[q22]) * - catchUndef(a_ExplicitWithFlags_Flags[q23], 0) - | q23 : int(1..3)]) - = - sum([toInt(a_ExplicitWithRepetition_Values[q25] = a_ExplicitWithRepetition_Values[q22]) - | q25 : int(1..3), q25 <= 3]) - | q22 : int(1..3), q22 <= 3]), - and([b_ExplicitWithFlags_Flags[q26 + 1] > 0 -> b_ExplicitWithFlags_Values[q26] < b_ExplicitWithFlags_Values[q26 + 1] - | q26 : int(1..2)]), - and([b_ExplicitWithFlags_Flags[q27] = 0 -> b_ExplicitWithFlags_Values[q27] = 1 | q27 : int(1..3)]), - and([b_ExplicitWithFlags_Flags[q28 + 1] > 0 -> b_ExplicitWithFlags_Flags[q28] > 0 | q28 : int(1..2)]), - 3 = sum([b_ExplicitWithFlags_Flags[q30] | q30 : int(1..3)]), - and([b_ExplicitWithFlags_Flags[q33] > 0 -> - sum([toInt(b_ExplicitWithFlags_Values[q34] = b_ExplicitWithFlags_Values[q33]) * - catchUndef(b_ExplicitWithFlags_Flags[q34], 0) - | q34 : int(1..3)]) - = - sum([toInt(b_ExplicitWithRepetition_Values[q36] = b_ExplicitWithFlags_Values[q33]) - | q36 : int(1..3), q36 <= 3]) - | q33 : int(1..3)]), - and([sum([toInt(b_ExplicitWithFlags_Values[q38] = b_ExplicitWithRepetition_Values[q37]) * - catchUndef(b_ExplicitWithFlags_Flags[q38], 0) - | q38 : int(1..3)]) - = - sum([toInt(b_ExplicitWithRepetition_Values[q40] = b_ExplicitWithRepetition_Values[q37]) - | q40 : int(1..3), q40 <= 3]) - | q37 : int(1..3), q37 <= 3]) - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_1_2-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_1_2-solution000001.solution deleted file mode 100644 index 1b4b5b08a6..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_1_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 2, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_1_2-solution000002.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_1_2-solution000002.solution deleted file mode 100644 index 5e2caa751c..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_1_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 2, 2) -letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_1_2-solution000003.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_1_2-solution000003.solution deleted file mode 100644 index 621d5f6edc..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_1_2-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 1, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_1_2-solution000004.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_1_2-solution000004.solution deleted file mode 100644 index d56a0bbcdc..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_1_2-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_1_2-solution000005.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_1_2-solution000005.solution deleted file mode 100644 index ff56905e23..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_1_2-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_1_2-solution000006.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_1_2-solution000006.solution deleted file mode 100644 index 15472caf03..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_1_2-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 2, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_1_2.eprime b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_1_2.eprime deleted file mode 100644 index 01cead4da0..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_1_2.eprime +++ /dev/null @@ -1,88 +0,0 @@ -language ESSENCE' 1.0 - -find a_ExplicitWithRepetition_Flag: int(3) -find a_ExplicitWithRepetition_Values: matrix indexed by [int(1..3)] of int(1..2) -find a_ExplicitWithFlags_Flags: matrix indexed by [int(1..3)] of int(0..3) -find a_ExplicitWithFlags_Values: matrix indexed by [int(1..3)] of int(1..2) -find b_ExplicitWithRepetition_Flag: int(3) -find b_ExplicitWithRepetition_Values: matrix indexed by [int(1..3)] of int(1..2) -branching on - [a_ExplicitWithFlags_Flags, a_ExplicitWithFlags_Values, a_ExplicitWithRepetition_Flag, - a_ExplicitWithRepetition_Values, b_ExplicitWithRepetition_Flag, b_ExplicitWithRepetition_Values] -such that - or([sum([toInt(a_ExplicitWithRepetition_Values[q49] = a_ExplicitWithRepetition_Values[q28]) - | q49 : int(1..3), q49 <= 3]) - < - sum([toInt(b_ExplicitWithRepetition_Values[q51] = a_ExplicitWithRepetition_Values[q28]) - | q51 : int(1..3), q51 <= 3]) - /\ - (and([a_ExplicitWithRepetition_Values[q52] < a_ExplicitWithRepetition_Values[q28] -> - sum([toInt(a_ExplicitWithRepetition_Values[q61] = a_ExplicitWithRepetition_Values[q52]) - | q61 : int(1..3), q61 <= 3]) - = - sum([toInt(b_ExplicitWithRepetition_Values[q63] = a_ExplicitWithRepetition_Values[q52]) - | q63 : int(1..3), q63 <= 3]) - | q52 : int(1..3), q52 <= 3]) - /\ - and([!or([a_ExplicitWithRepetition_Values[q55] = b_ExplicitWithRepetition_Values[q53] - | q55 : int(1..3), q55 <= 3]) - /\ b_ExplicitWithRepetition_Values[q53] < a_ExplicitWithRepetition_Values[q28] - -> - sum([toInt(a_ExplicitWithRepetition_Values[q57] = b_ExplicitWithRepetition_Values[q53]) - | q57 : int(1..3), q57 <= 3]) - = - sum([toInt(b_ExplicitWithRepetition_Values[q59] = b_ExplicitWithRepetition_Values[q53]) - | q59 : int(1..3), q59 <= 3]) - | q53 : int(1..3), q53 <= 3])) - | q28 : int(1..3), q28 <= 3]) - \/ - or([!or([a_ExplicitWithRepetition_Values[q31] = b_ExplicitWithRepetition_Values[q29] | q31 : int(1..3), q31 <= 3]) - /\ - (sum([toInt(a_ExplicitWithRepetition_Values[q33] = b_ExplicitWithRepetition_Values[q29]) - | q33 : int(1..3), q33 <= 3]) - < - sum([toInt(b_ExplicitWithRepetition_Values[q35] = b_ExplicitWithRepetition_Values[q29]) - | q35 : int(1..3), q35 <= 3]) - /\ - (and([a_ExplicitWithRepetition_Values[q36] < b_ExplicitWithRepetition_Values[q29] -> - sum([toInt(a_ExplicitWithRepetition_Values[q45] = a_ExplicitWithRepetition_Values[q36]) - | q45 : int(1..3), q45 <= 3]) - = - sum([toInt(b_ExplicitWithRepetition_Values[q47] = a_ExplicitWithRepetition_Values[q36]) - | q47 : int(1..3), q47 <= 3]) - | q36 : int(1..3), q36 <= 3]) - /\ - and([!or([a_ExplicitWithRepetition_Values[q39] = b_ExplicitWithRepetition_Values[q37] - | q39 : int(1..3), q39 <= 3]) - /\ b_ExplicitWithRepetition_Values[q37] < b_ExplicitWithRepetition_Values[q29] - -> - sum([toInt(a_ExplicitWithRepetition_Values[q41] = b_ExplicitWithRepetition_Values[q37]) - | q41 : int(1..3), q41 <= 3]) - = - sum([toInt(b_ExplicitWithRepetition_Values[q43] = b_ExplicitWithRepetition_Values[q37]) - | q43 : int(1..3), q43 <= 3]) - | q37 : int(1..3), q37 <= 3]))) - | q29 : int(1..3), q29 <= 3]), - and([a_ExplicitWithRepetition_Values[q1] <= a_ExplicitWithRepetition_Values[q1 + 1] | q1 : int(1..2), q1 + 1 <= 3]), - and([b_ExplicitWithRepetition_Values[q6] <= b_ExplicitWithRepetition_Values[q6 + 1] | q6 : int(1..2), q6 + 1 <= 3]), - and([a_ExplicitWithFlags_Flags[q11 + 1] > 0 -> a_ExplicitWithFlags_Values[q11] < a_ExplicitWithFlags_Values[q11 + 1] - | q11 : int(1..2)]), - and([a_ExplicitWithFlags_Flags[q12] = 0 -> a_ExplicitWithFlags_Values[q12] = 1 | q12 : int(1..3)]), - and([a_ExplicitWithFlags_Flags[q13 + 1] > 0 -> a_ExplicitWithFlags_Flags[q13] > 0 | q13 : int(1..2)]), - 3 = sum([a_ExplicitWithFlags_Flags[q15] | q15 : int(1..3)]), - and([a_ExplicitWithFlags_Flags[q18] > 0 -> - sum([toInt(a_ExplicitWithFlags_Values[q19] = a_ExplicitWithFlags_Values[q18]) * - catchUndef(a_ExplicitWithFlags_Flags[q19], 0) - | q19 : int(1..3)]) - = - sum([toInt(a_ExplicitWithRepetition_Values[q21] = a_ExplicitWithFlags_Values[q18]) - | q21 : int(1..3), q21 <= 3]) - | q18 : int(1..3)]), - and([sum([toInt(a_ExplicitWithFlags_Values[q23] = a_ExplicitWithRepetition_Values[q22]) * - catchUndef(a_ExplicitWithFlags_Flags[q23], 0) - | q23 : int(1..3)]) - = - sum([toInt(a_ExplicitWithRepetition_Values[q25] = a_ExplicitWithRepetition_Values[q22]) - | q25 : int(1..3), q25 <= 3]) - | q22 : int(1..3), q22 <= 3]) - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_1_3-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_1_3-solution000001.solution deleted file mode 100644 index 5e2caa751c..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_1_3-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 2, 2) -letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_1_3-solution000002.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_1_3-solution000002.solution deleted file mode 100644 index 1b4b5b08a6..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_1_3-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 2, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_1_3-solution000003.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_1_3-solution000003.solution deleted file mode 100644 index 621d5f6edc..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_1_3-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 1, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_1_3-solution000004.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_1_3-solution000004.solution deleted file mode 100644 index 15472caf03..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_1_3-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 2, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_1_3-solution000005.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_1_3-solution000005.solution deleted file mode 100644 index ff56905e23..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_1_3-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_1_3-solution000006.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_1_3-solution000006.solution deleted file mode 100644 index d56a0bbcdc..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_1_3-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_1_3.eprime b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_1_3.eprime deleted file mode 100644 index d04ff5dce7..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_1_3.eprime +++ /dev/null @@ -1,97 +0,0 @@ -language ESSENCE' 1.0 - -find a_ExplicitWithRepetition_Flag: int(3) -find a_ExplicitWithRepetition_Values: matrix indexed by [int(1..3)] of int(1..2) -find a_ExplicitWithFlags_Flags: matrix indexed by [int(1..3)] of int(0..3) -find a_ExplicitWithFlags_Values: matrix indexed by [int(1..3)] of int(1..2) -find b_ExplicitWithRepetition_Flag: int(3) -find b_ExplicitWithRepetition_Values: matrix indexed by [int(1..3)] of int(1..2) -find b_MOccurrence: matrix indexed by [int(1..2)] of int(0..3) -branching on - [a_ExplicitWithFlags_Flags, a_ExplicitWithFlags_Values, a_ExplicitWithRepetition_Flag, - a_ExplicitWithRepetition_Values, b_MOccurrence, b_ExplicitWithRepetition_Flag, b_ExplicitWithRepetition_Values] -such that - or([sum([toInt(a_ExplicitWithRepetition_Values[q57] = a_ExplicitWithRepetition_Values[q36]) - | q57 : int(1..3), q57 <= 3]) - < - sum([toInt(b_ExplicitWithRepetition_Values[q59] = a_ExplicitWithRepetition_Values[q36]) - | q59 : int(1..3), q59 <= 3]) - /\ - (and([a_ExplicitWithRepetition_Values[q60] < a_ExplicitWithRepetition_Values[q36] -> - sum([toInt(a_ExplicitWithRepetition_Values[q69] = a_ExplicitWithRepetition_Values[q60]) - | q69 : int(1..3), q69 <= 3]) - = - sum([toInt(b_ExplicitWithRepetition_Values[q71] = a_ExplicitWithRepetition_Values[q60]) - | q71 : int(1..3), q71 <= 3]) - | q60 : int(1..3), q60 <= 3]) - /\ - and([!or([a_ExplicitWithRepetition_Values[q63] = b_ExplicitWithRepetition_Values[q61] - | q63 : int(1..3), q63 <= 3]) - /\ b_ExplicitWithRepetition_Values[q61] < a_ExplicitWithRepetition_Values[q36] - -> - sum([toInt(a_ExplicitWithRepetition_Values[q65] = b_ExplicitWithRepetition_Values[q61]) - | q65 : int(1..3), q65 <= 3]) - = - sum([toInt(b_ExplicitWithRepetition_Values[q67] = b_ExplicitWithRepetition_Values[q61]) - | q67 : int(1..3), q67 <= 3]) - | q61 : int(1..3), q61 <= 3])) - | q36 : int(1..3), q36 <= 3]) - \/ - or([!or([a_ExplicitWithRepetition_Values[q39] = b_ExplicitWithRepetition_Values[q37] | q39 : int(1..3), q39 <= 3]) - /\ - (sum([toInt(a_ExplicitWithRepetition_Values[q41] = b_ExplicitWithRepetition_Values[q37]) - | q41 : int(1..3), q41 <= 3]) - < - sum([toInt(b_ExplicitWithRepetition_Values[q43] = b_ExplicitWithRepetition_Values[q37]) - | q43 : int(1..3), q43 <= 3]) - /\ - (and([a_ExplicitWithRepetition_Values[q44] < b_ExplicitWithRepetition_Values[q37] -> - sum([toInt(a_ExplicitWithRepetition_Values[q53] = a_ExplicitWithRepetition_Values[q44]) - | q53 : int(1..3), q53 <= 3]) - = - sum([toInt(b_ExplicitWithRepetition_Values[q55] = a_ExplicitWithRepetition_Values[q44]) - | q55 : int(1..3), q55 <= 3]) - | q44 : int(1..3), q44 <= 3]) - /\ - and([!or([a_ExplicitWithRepetition_Values[q47] = b_ExplicitWithRepetition_Values[q45] - | q47 : int(1..3), q47 <= 3]) - /\ b_ExplicitWithRepetition_Values[q45] < b_ExplicitWithRepetition_Values[q37] - -> - sum([toInt(a_ExplicitWithRepetition_Values[q49] = b_ExplicitWithRepetition_Values[q45]) - | q49 : int(1..3), q49 <= 3]) - = - sum([toInt(b_ExplicitWithRepetition_Values[q51] = b_ExplicitWithRepetition_Values[q45]) - | q51 : int(1..3), q51 <= 3]) - | q45 : int(1..3), q45 <= 3]))) - | q37 : int(1..3), q37 <= 3]), - and([a_ExplicitWithRepetition_Values[q1] <= a_ExplicitWithRepetition_Values[q1 + 1] | q1 : int(1..2), q1 + 1 <= 3]), - and([b_ExplicitWithRepetition_Values[q6] <= b_ExplicitWithRepetition_Values[q6 + 1] | q6 : int(1..2), q6 + 1 <= 3]), - and([a_ExplicitWithFlags_Flags[q11 + 1] > 0 -> a_ExplicitWithFlags_Values[q11] < a_ExplicitWithFlags_Values[q11 + 1] - | q11 : int(1..2)]), - and([a_ExplicitWithFlags_Flags[q12] = 0 -> a_ExplicitWithFlags_Values[q12] = 1 | q12 : int(1..3)]), - and([a_ExplicitWithFlags_Flags[q13 + 1] > 0 -> a_ExplicitWithFlags_Flags[q13] > 0 | q13 : int(1..2)]), - 3 = sum([a_ExplicitWithFlags_Flags[q15] | q15 : int(1..3)]), - and([a_ExplicitWithFlags_Flags[q18] > 0 -> - sum([toInt(a_ExplicitWithFlags_Values[q19] = a_ExplicitWithFlags_Values[q18]) * - catchUndef(a_ExplicitWithFlags_Flags[q19], 0) - | q19 : int(1..3)]) - = - sum([toInt(a_ExplicitWithRepetition_Values[q21] = a_ExplicitWithFlags_Values[q18]) - | q21 : int(1..3), q21 <= 3]) - | q18 : int(1..3)]), - and([sum([toInt(a_ExplicitWithFlags_Values[q23] = a_ExplicitWithRepetition_Values[q22]) * - catchUndef(a_ExplicitWithFlags_Flags[q23], 0) - | q23 : int(1..3)]) - = - sum([toInt(a_ExplicitWithRepetition_Values[q25] = a_ExplicitWithRepetition_Values[q22]) - | q25 : int(1..3), q25 <= 3]) - | q22 : int(1..3), q22 <= 3]), - 3 = sum([b_MOccurrence[q26] | q26 : int(1..2)]), - and([b_MOccurrence[q28] > 0 -> - b_MOccurrence[q28] = sum([toInt(b_ExplicitWithRepetition_Values[q30] = q28) | q30 : int(1..3), q30 <= 3]) - | q28 : int(1..2)]), - and([b_MOccurrence[b_ExplicitWithRepetition_Values[q31]] = - sum([toInt(b_ExplicitWithRepetition_Values[q33] = b_ExplicitWithRepetition_Values[q31]) - | q33 : int(1..3), q33 <= 3]) - | q31 : int(1..3), q31 <= 3]) - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_2_1-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_2_1-solution000001.solution deleted file mode 100644 index 621d5f6edc..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_2_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 1, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_2_1-solution000002.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_2_1-solution000002.solution deleted file mode 100644 index 5e2caa751c..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_2_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 2, 2) -letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_2_1-solution000003.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_2_1-solution000003.solution deleted file mode 100644 index 1b4b5b08a6..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_2_1-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 2, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_2_1-solution000004.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_2_1-solution000004.solution deleted file mode 100644 index 15472caf03..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_2_1-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 2, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_2_1-solution000005.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_2_1-solution000005.solution deleted file mode 100644 index ff56905e23..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_2_1-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_2_1-solution000006.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_2_1-solution000006.solution deleted file mode 100644 index d56a0bbcdc..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_2_1-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_2_1.eprime b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_2_1.eprime deleted file mode 100644 index bf0481ee67..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_2_1.eprime +++ /dev/null @@ -1,88 +0,0 @@ -language ESSENCE' 1.0 - -find a_ExplicitWithRepetition_Flag: int(3) -find a_ExplicitWithRepetition_Values: matrix indexed by [int(1..3)] of int(1..2) -find b_ExplicitWithRepetition_Flag: int(3) -find b_ExplicitWithRepetition_Values: matrix indexed by [int(1..3)] of int(1..2) -find b_ExplicitWithFlags_Flags: matrix indexed by [int(1..3)] of int(0..3) -find b_ExplicitWithFlags_Values: matrix indexed by [int(1..3)] of int(1..2) -branching on - [a_ExplicitWithRepetition_Flag, a_ExplicitWithRepetition_Values, b_ExplicitWithFlags_Flags, - b_ExplicitWithFlags_Values, b_ExplicitWithRepetition_Flag, b_ExplicitWithRepetition_Values] -such that - or([sum([toInt(a_ExplicitWithRepetition_Values[q49] = a_ExplicitWithRepetition_Values[q28]) - | q49 : int(1..3), q49 <= 3]) - < - sum([toInt(b_ExplicitWithRepetition_Values[q51] = a_ExplicitWithRepetition_Values[q28]) - | q51 : int(1..3), q51 <= 3]) - /\ - (and([a_ExplicitWithRepetition_Values[q52] < a_ExplicitWithRepetition_Values[q28] -> - sum([toInt(a_ExplicitWithRepetition_Values[q61] = a_ExplicitWithRepetition_Values[q52]) - | q61 : int(1..3), q61 <= 3]) - = - sum([toInt(b_ExplicitWithRepetition_Values[q63] = a_ExplicitWithRepetition_Values[q52]) - | q63 : int(1..3), q63 <= 3]) - | q52 : int(1..3), q52 <= 3]) - /\ - and([!or([a_ExplicitWithRepetition_Values[q55] = b_ExplicitWithRepetition_Values[q53] - | q55 : int(1..3), q55 <= 3]) - /\ b_ExplicitWithRepetition_Values[q53] < a_ExplicitWithRepetition_Values[q28] - -> - sum([toInt(a_ExplicitWithRepetition_Values[q57] = b_ExplicitWithRepetition_Values[q53]) - | q57 : int(1..3), q57 <= 3]) - = - sum([toInt(b_ExplicitWithRepetition_Values[q59] = b_ExplicitWithRepetition_Values[q53]) - | q59 : int(1..3), q59 <= 3]) - | q53 : int(1..3), q53 <= 3])) - | q28 : int(1..3), q28 <= 3]) - \/ - or([!or([a_ExplicitWithRepetition_Values[q31] = b_ExplicitWithRepetition_Values[q29] | q31 : int(1..3), q31 <= 3]) - /\ - (sum([toInt(a_ExplicitWithRepetition_Values[q33] = b_ExplicitWithRepetition_Values[q29]) - | q33 : int(1..3), q33 <= 3]) - < - sum([toInt(b_ExplicitWithRepetition_Values[q35] = b_ExplicitWithRepetition_Values[q29]) - | q35 : int(1..3), q35 <= 3]) - /\ - (and([a_ExplicitWithRepetition_Values[q36] < b_ExplicitWithRepetition_Values[q29] -> - sum([toInt(a_ExplicitWithRepetition_Values[q45] = a_ExplicitWithRepetition_Values[q36]) - | q45 : int(1..3), q45 <= 3]) - = - sum([toInt(b_ExplicitWithRepetition_Values[q47] = a_ExplicitWithRepetition_Values[q36]) - | q47 : int(1..3), q47 <= 3]) - | q36 : int(1..3), q36 <= 3]) - /\ - and([!or([a_ExplicitWithRepetition_Values[q39] = b_ExplicitWithRepetition_Values[q37] - | q39 : int(1..3), q39 <= 3]) - /\ b_ExplicitWithRepetition_Values[q37] < b_ExplicitWithRepetition_Values[q29] - -> - sum([toInt(a_ExplicitWithRepetition_Values[q41] = b_ExplicitWithRepetition_Values[q37]) - | q41 : int(1..3), q41 <= 3]) - = - sum([toInt(b_ExplicitWithRepetition_Values[q43] = b_ExplicitWithRepetition_Values[q37]) - | q43 : int(1..3), q43 <= 3]) - | q37 : int(1..3), q37 <= 3]))) - | q29 : int(1..3), q29 <= 3]), - and([a_ExplicitWithRepetition_Values[q1] <= a_ExplicitWithRepetition_Values[q1 + 1] | q1 : int(1..2), q1 + 1 <= 3]), - and([b_ExplicitWithRepetition_Values[q6] <= b_ExplicitWithRepetition_Values[q6 + 1] | q6 : int(1..2), q6 + 1 <= 3]), - and([b_ExplicitWithFlags_Flags[q11 + 1] > 0 -> b_ExplicitWithFlags_Values[q11] < b_ExplicitWithFlags_Values[q11 + 1] - | q11 : int(1..2)]), - and([b_ExplicitWithFlags_Flags[q12] = 0 -> b_ExplicitWithFlags_Values[q12] = 1 | q12 : int(1..3)]), - and([b_ExplicitWithFlags_Flags[q13 + 1] > 0 -> b_ExplicitWithFlags_Flags[q13] > 0 | q13 : int(1..2)]), - 3 = sum([b_ExplicitWithFlags_Flags[q15] | q15 : int(1..3)]), - and([b_ExplicitWithFlags_Flags[q18] > 0 -> - sum([toInt(b_ExplicitWithFlags_Values[q19] = b_ExplicitWithFlags_Values[q18]) * - catchUndef(b_ExplicitWithFlags_Flags[q19], 0) - | q19 : int(1..3)]) - = - sum([toInt(b_ExplicitWithRepetition_Values[q21] = b_ExplicitWithFlags_Values[q18]) - | q21 : int(1..3), q21 <= 3]) - | q18 : int(1..3)]), - and([sum([toInt(b_ExplicitWithFlags_Values[q23] = b_ExplicitWithRepetition_Values[q22]) * - catchUndef(b_ExplicitWithFlags_Flags[q23], 0) - | q23 : int(1..3)]) - = - sum([toInt(b_ExplicitWithRepetition_Values[q25] = b_ExplicitWithRepetition_Values[q22]) - | q25 : int(1..3), q25 <= 3]) - | q22 : int(1..3), q22 <= 3]) - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_2_2-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_2_2-solution000001.solution deleted file mode 100644 index 621d5f6edc..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_2_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 1, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_2_2-solution000002.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_2_2-solution000002.solution deleted file mode 100644 index 1b4b5b08a6..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_2_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 2, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_2_2-solution000003.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_2_2-solution000003.solution deleted file mode 100644 index 5e2caa751c..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_2_2-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 2, 2) -letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_2_2-solution000004.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_2_2-solution000004.solution deleted file mode 100644 index d56a0bbcdc..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_2_2-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_2_2-solution000005.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_2_2-solution000005.solution deleted file mode 100644 index ff56905e23..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_2_2-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_2_2-solution000006.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_2_2-solution000006.solution deleted file mode 100644 index 15472caf03..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_2_2-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 2, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_2_2.eprime b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_2_2.eprime deleted file mode 100644 index 24067a2f5e..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_2_2.eprime +++ /dev/null @@ -1,66 +0,0 @@ -language ESSENCE' 1.0 - -find a_ExplicitWithRepetition_Flag: int(3) -find a_ExplicitWithRepetition_Values: matrix indexed by [int(1..3)] of int(1..2) -find b_ExplicitWithRepetition_Flag: int(3) -find b_ExplicitWithRepetition_Values: matrix indexed by [int(1..3)] of int(1..2) -branching on - [a_ExplicitWithRepetition_Flag, a_ExplicitWithRepetition_Values, b_ExplicitWithRepetition_Flag, - b_ExplicitWithRepetition_Values] -such that - or([sum([toInt(a_ExplicitWithRepetition_Values[q34] = a_ExplicitWithRepetition_Values[q13]) - | q34 : int(1..3), q34 <= 3]) - < - sum([toInt(b_ExplicitWithRepetition_Values[q36] = a_ExplicitWithRepetition_Values[q13]) - | q36 : int(1..3), q36 <= 3]) - /\ - (and([a_ExplicitWithRepetition_Values[q37] < a_ExplicitWithRepetition_Values[q13] -> - sum([toInt(a_ExplicitWithRepetition_Values[q46] = a_ExplicitWithRepetition_Values[q37]) - | q46 : int(1..3), q46 <= 3]) - = - sum([toInt(b_ExplicitWithRepetition_Values[q48] = a_ExplicitWithRepetition_Values[q37]) - | q48 : int(1..3), q48 <= 3]) - | q37 : int(1..3), q37 <= 3]) - /\ - and([!or([a_ExplicitWithRepetition_Values[q40] = b_ExplicitWithRepetition_Values[q38] - | q40 : int(1..3), q40 <= 3]) - /\ b_ExplicitWithRepetition_Values[q38] < a_ExplicitWithRepetition_Values[q13] - -> - sum([toInt(a_ExplicitWithRepetition_Values[q42] = b_ExplicitWithRepetition_Values[q38]) - | q42 : int(1..3), q42 <= 3]) - = - sum([toInt(b_ExplicitWithRepetition_Values[q44] = b_ExplicitWithRepetition_Values[q38]) - | q44 : int(1..3), q44 <= 3]) - | q38 : int(1..3), q38 <= 3])) - | q13 : int(1..3), q13 <= 3]) - \/ - or([!or([a_ExplicitWithRepetition_Values[q16] = b_ExplicitWithRepetition_Values[q14] | q16 : int(1..3), q16 <= 3]) - /\ - (sum([toInt(a_ExplicitWithRepetition_Values[q18] = b_ExplicitWithRepetition_Values[q14]) - | q18 : int(1..3), q18 <= 3]) - < - sum([toInt(b_ExplicitWithRepetition_Values[q20] = b_ExplicitWithRepetition_Values[q14]) - | q20 : int(1..3), q20 <= 3]) - /\ - (and([a_ExplicitWithRepetition_Values[q21] < b_ExplicitWithRepetition_Values[q14] -> - sum([toInt(a_ExplicitWithRepetition_Values[q30] = a_ExplicitWithRepetition_Values[q21]) - | q30 : int(1..3), q30 <= 3]) - = - sum([toInt(b_ExplicitWithRepetition_Values[q32] = a_ExplicitWithRepetition_Values[q21]) - | q32 : int(1..3), q32 <= 3]) - | q21 : int(1..3), q21 <= 3]) - /\ - and([!or([a_ExplicitWithRepetition_Values[q24] = b_ExplicitWithRepetition_Values[q22] - | q24 : int(1..3), q24 <= 3]) - /\ b_ExplicitWithRepetition_Values[q22] < b_ExplicitWithRepetition_Values[q14] - -> - sum([toInt(a_ExplicitWithRepetition_Values[q26] = b_ExplicitWithRepetition_Values[q22]) - | q26 : int(1..3), q26 <= 3]) - = - sum([toInt(b_ExplicitWithRepetition_Values[q28] = b_ExplicitWithRepetition_Values[q22]) - | q28 : int(1..3), q28 <= 3]) - | q22 : int(1..3), q22 <= 3]))) - | q14 : int(1..3), q14 <= 3]), - and([a_ExplicitWithRepetition_Values[q1] <= a_ExplicitWithRepetition_Values[q1 + 1] | q1 : int(1..2), q1 + 1 <= 3]), - and([b_ExplicitWithRepetition_Values[q6] <= b_ExplicitWithRepetition_Values[q6 + 1] | q6 : int(1..2), q6 + 1 <= 3]) - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_2_3-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_2_3-solution000001.solution deleted file mode 100644 index 621d5f6edc..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_2_3-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 1, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_2_3-solution000002.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_2_3-solution000002.solution deleted file mode 100644 index 5e2caa751c..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_2_3-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 2, 2) -letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_2_3-solution000003.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_2_3-solution000003.solution deleted file mode 100644 index 1b4b5b08a6..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_2_3-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 2, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_2_3-solution000004.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_2_3-solution000004.solution deleted file mode 100644 index 15472caf03..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_2_3-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 2, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_2_3-solution000005.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_2_3-solution000005.solution deleted file mode 100644 index ff56905e23..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_2_3-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_2_3-solution000006.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_2_3-solution000006.solution deleted file mode 100644 index d56a0bbcdc..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_2_3-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_2_3.eprime b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_2_3.eprime deleted file mode 100644 index 3c8a938e45..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_2_3.eprime +++ /dev/null @@ -1,75 +0,0 @@ -language ESSENCE' 1.0 - -find a_ExplicitWithRepetition_Flag: int(3) -find a_ExplicitWithRepetition_Values: matrix indexed by [int(1..3)] of int(1..2) -find b_ExplicitWithRepetition_Flag: int(3) -find b_ExplicitWithRepetition_Values: matrix indexed by [int(1..3)] of int(1..2) -find b_MOccurrence: matrix indexed by [int(1..2)] of int(0..3) -branching on - [a_ExplicitWithRepetition_Flag, a_ExplicitWithRepetition_Values, b_MOccurrence, b_ExplicitWithRepetition_Flag, - b_ExplicitWithRepetition_Values] -such that - or([sum([toInt(a_ExplicitWithRepetition_Values[q42] = a_ExplicitWithRepetition_Values[q21]) - | q42 : int(1..3), q42 <= 3]) - < - sum([toInt(b_ExplicitWithRepetition_Values[q44] = a_ExplicitWithRepetition_Values[q21]) - | q44 : int(1..3), q44 <= 3]) - /\ - (and([a_ExplicitWithRepetition_Values[q45] < a_ExplicitWithRepetition_Values[q21] -> - sum([toInt(a_ExplicitWithRepetition_Values[q54] = a_ExplicitWithRepetition_Values[q45]) - | q54 : int(1..3), q54 <= 3]) - = - sum([toInt(b_ExplicitWithRepetition_Values[q56] = a_ExplicitWithRepetition_Values[q45]) - | q56 : int(1..3), q56 <= 3]) - | q45 : int(1..3), q45 <= 3]) - /\ - and([!or([a_ExplicitWithRepetition_Values[q48] = b_ExplicitWithRepetition_Values[q46] - | q48 : int(1..3), q48 <= 3]) - /\ b_ExplicitWithRepetition_Values[q46] < a_ExplicitWithRepetition_Values[q21] - -> - sum([toInt(a_ExplicitWithRepetition_Values[q50] = b_ExplicitWithRepetition_Values[q46]) - | q50 : int(1..3), q50 <= 3]) - = - sum([toInt(b_ExplicitWithRepetition_Values[q52] = b_ExplicitWithRepetition_Values[q46]) - | q52 : int(1..3), q52 <= 3]) - | q46 : int(1..3), q46 <= 3])) - | q21 : int(1..3), q21 <= 3]) - \/ - or([!or([a_ExplicitWithRepetition_Values[q24] = b_ExplicitWithRepetition_Values[q22] | q24 : int(1..3), q24 <= 3]) - /\ - (sum([toInt(a_ExplicitWithRepetition_Values[q26] = b_ExplicitWithRepetition_Values[q22]) - | q26 : int(1..3), q26 <= 3]) - < - sum([toInt(b_ExplicitWithRepetition_Values[q28] = b_ExplicitWithRepetition_Values[q22]) - | q28 : int(1..3), q28 <= 3]) - /\ - (and([a_ExplicitWithRepetition_Values[q29] < b_ExplicitWithRepetition_Values[q22] -> - sum([toInt(a_ExplicitWithRepetition_Values[q38] = a_ExplicitWithRepetition_Values[q29]) - | q38 : int(1..3), q38 <= 3]) - = - sum([toInt(b_ExplicitWithRepetition_Values[q40] = a_ExplicitWithRepetition_Values[q29]) - | q40 : int(1..3), q40 <= 3]) - | q29 : int(1..3), q29 <= 3]) - /\ - and([!or([a_ExplicitWithRepetition_Values[q32] = b_ExplicitWithRepetition_Values[q30] - | q32 : int(1..3), q32 <= 3]) - /\ b_ExplicitWithRepetition_Values[q30] < b_ExplicitWithRepetition_Values[q22] - -> - sum([toInt(a_ExplicitWithRepetition_Values[q34] = b_ExplicitWithRepetition_Values[q30]) - | q34 : int(1..3), q34 <= 3]) - = - sum([toInt(b_ExplicitWithRepetition_Values[q36] = b_ExplicitWithRepetition_Values[q30]) - | q36 : int(1..3), q36 <= 3]) - | q30 : int(1..3), q30 <= 3]))) - | q22 : int(1..3), q22 <= 3]), - and([a_ExplicitWithRepetition_Values[q1] <= a_ExplicitWithRepetition_Values[q1 + 1] | q1 : int(1..2), q1 + 1 <= 3]), - and([b_ExplicitWithRepetition_Values[q6] <= b_ExplicitWithRepetition_Values[q6 + 1] | q6 : int(1..2), q6 + 1 <= 3]), - 3 = sum([b_MOccurrence[q11] | q11 : int(1..2)]), - and([b_MOccurrence[q13] > 0 -> - b_MOccurrence[q13] = sum([toInt(b_ExplicitWithRepetition_Values[q15] = q13) | q15 : int(1..3), q15 <= 3]) - | q13 : int(1..2)]), - and([b_MOccurrence[b_ExplicitWithRepetition_Values[q16]] = - sum([toInt(b_ExplicitWithRepetition_Values[q18] = b_ExplicitWithRepetition_Values[q16]) - | q18 : int(1..3), q18 <= 3]) - | q16 : int(1..3), q16 <= 3]) - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_3_1-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_3_1-solution000001.solution deleted file mode 100644 index 15472caf03..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_3_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 2, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_3_1-solution000002.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_3_1-solution000002.solution deleted file mode 100644 index ff56905e23..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_3_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_3_1-solution000003.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_3_1-solution000003.solution deleted file mode 100644 index d56a0bbcdc..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_3_1-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_3_1-solution000004.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_3_1-solution000004.solution deleted file mode 100644 index 5e2caa751c..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_3_1-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 2, 2) -letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_3_1-solution000005.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_3_1-solution000005.solution deleted file mode 100644 index 1b4b5b08a6..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_3_1-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 2, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_3_1-solution000006.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_3_1-solution000006.solution deleted file mode 100644 index 621d5f6edc..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_3_1-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 1, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_3_1.eprime b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_3_1.eprime deleted file mode 100644 index b030f86ef4..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_3_1.eprime +++ /dev/null @@ -1,97 +0,0 @@ -language ESSENCE' 1.0 - -find a_ExplicitWithRepetition_Flag: int(3) -find a_ExplicitWithRepetition_Values: matrix indexed by [int(1..3)] of int(1..2) -find a_MOccurrence: matrix indexed by [int(1..2)] of int(0..3) -find b_ExplicitWithRepetition_Flag: int(3) -find b_ExplicitWithRepetition_Values: matrix indexed by [int(1..3)] of int(1..2) -find b_ExplicitWithFlags_Flags: matrix indexed by [int(1..3)] of int(0..3) -find b_ExplicitWithFlags_Values: matrix indexed by [int(1..3)] of int(1..2) -branching on - [a_MOccurrence, a_ExplicitWithRepetition_Flag, a_ExplicitWithRepetition_Values, b_ExplicitWithFlags_Flags, - b_ExplicitWithFlags_Values, b_ExplicitWithRepetition_Flag, b_ExplicitWithRepetition_Values] -such that - or([sum([toInt(a_ExplicitWithRepetition_Values[q57] = a_ExplicitWithRepetition_Values[q36]) - | q57 : int(1..3), q57 <= 3]) - < - sum([toInt(b_ExplicitWithRepetition_Values[q59] = a_ExplicitWithRepetition_Values[q36]) - | q59 : int(1..3), q59 <= 3]) - /\ - (and([a_ExplicitWithRepetition_Values[q60] < a_ExplicitWithRepetition_Values[q36] -> - sum([toInt(a_ExplicitWithRepetition_Values[q69] = a_ExplicitWithRepetition_Values[q60]) - | q69 : int(1..3), q69 <= 3]) - = - sum([toInt(b_ExplicitWithRepetition_Values[q71] = a_ExplicitWithRepetition_Values[q60]) - | q71 : int(1..3), q71 <= 3]) - | q60 : int(1..3), q60 <= 3]) - /\ - and([!or([a_ExplicitWithRepetition_Values[q63] = b_ExplicitWithRepetition_Values[q61] - | q63 : int(1..3), q63 <= 3]) - /\ b_ExplicitWithRepetition_Values[q61] < a_ExplicitWithRepetition_Values[q36] - -> - sum([toInt(a_ExplicitWithRepetition_Values[q65] = b_ExplicitWithRepetition_Values[q61]) - | q65 : int(1..3), q65 <= 3]) - = - sum([toInt(b_ExplicitWithRepetition_Values[q67] = b_ExplicitWithRepetition_Values[q61]) - | q67 : int(1..3), q67 <= 3]) - | q61 : int(1..3), q61 <= 3])) - | q36 : int(1..3), q36 <= 3]) - \/ - or([!or([a_ExplicitWithRepetition_Values[q39] = b_ExplicitWithRepetition_Values[q37] | q39 : int(1..3), q39 <= 3]) - /\ - (sum([toInt(a_ExplicitWithRepetition_Values[q41] = b_ExplicitWithRepetition_Values[q37]) - | q41 : int(1..3), q41 <= 3]) - < - sum([toInt(b_ExplicitWithRepetition_Values[q43] = b_ExplicitWithRepetition_Values[q37]) - | q43 : int(1..3), q43 <= 3]) - /\ - (and([a_ExplicitWithRepetition_Values[q44] < b_ExplicitWithRepetition_Values[q37] -> - sum([toInt(a_ExplicitWithRepetition_Values[q53] = a_ExplicitWithRepetition_Values[q44]) - | q53 : int(1..3), q53 <= 3]) - = - sum([toInt(b_ExplicitWithRepetition_Values[q55] = a_ExplicitWithRepetition_Values[q44]) - | q55 : int(1..3), q55 <= 3]) - | q44 : int(1..3), q44 <= 3]) - /\ - and([!or([a_ExplicitWithRepetition_Values[q47] = b_ExplicitWithRepetition_Values[q45] - | q47 : int(1..3), q47 <= 3]) - /\ b_ExplicitWithRepetition_Values[q45] < b_ExplicitWithRepetition_Values[q37] - -> - sum([toInt(a_ExplicitWithRepetition_Values[q49] = b_ExplicitWithRepetition_Values[q45]) - | q49 : int(1..3), q49 <= 3]) - = - sum([toInt(b_ExplicitWithRepetition_Values[q51] = b_ExplicitWithRepetition_Values[q45]) - | q51 : int(1..3), q51 <= 3]) - | q45 : int(1..3), q45 <= 3]))) - | q37 : int(1..3), q37 <= 3]), - and([a_ExplicitWithRepetition_Values[q1] <= a_ExplicitWithRepetition_Values[q1 + 1] | q1 : int(1..2), q1 + 1 <= 3]), - and([b_ExplicitWithRepetition_Values[q6] <= b_ExplicitWithRepetition_Values[q6 + 1] | q6 : int(1..2), q6 + 1 <= 3]), - 3 = sum([a_MOccurrence[q11] | q11 : int(1..2)]), - and([a_MOccurrence[q28] > 0 -> - a_MOccurrence[q28] = sum([toInt(a_ExplicitWithRepetition_Values[q30] = q28) | q30 : int(1..3), q30 <= 3]) - | q28 : int(1..2)]), - and([a_MOccurrence[a_ExplicitWithRepetition_Values[q31]] = - sum([toInt(a_ExplicitWithRepetition_Values[q33] = a_ExplicitWithRepetition_Values[q31]) - | q33 : int(1..3), q33 <= 3]) - | q31 : int(1..3), q31 <= 3]), - and([b_ExplicitWithFlags_Flags[q12 + 1] > 0 -> b_ExplicitWithFlags_Values[q12] < b_ExplicitWithFlags_Values[q12 + 1] - | q12 : int(1..2)]), - and([b_ExplicitWithFlags_Flags[q13] = 0 -> b_ExplicitWithFlags_Values[q13] = 1 | q13 : int(1..3)]), - and([b_ExplicitWithFlags_Flags[q14 + 1] > 0 -> b_ExplicitWithFlags_Flags[q14] > 0 | q14 : int(1..2)]), - 3 = sum([b_ExplicitWithFlags_Flags[q16] | q16 : int(1..3)]), - and([b_ExplicitWithFlags_Flags[q19] > 0 -> - sum([toInt(b_ExplicitWithFlags_Values[q20] = b_ExplicitWithFlags_Values[q19]) * - catchUndef(b_ExplicitWithFlags_Flags[q20], 0) - | q20 : int(1..3)]) - = - sum([toInt(b_ExplicitWithRepetition_Values[q22] = b_ExplicitWithFlags_Values[q19]) - | q22 : int(1..3), q22 <= 3]) - | q19 : int(1..3)]), - and([sum([toInt(b_ExplicitWithFlags_Values[q24] = b_ExplicitWithRepetition_Values[q23]) * - catchUndef(b_ExplicitWithFlags_Flags[q24], 0) - | q24 : int(1..3)]) - = - sum([toInt(b_ExplicitWithRepetition_Values[q26] = b_ExplicitWithRepetition_Values[q23]) - | q26 : int(1..3), q26 <= 3]) - | q23 : int(1..3), q23 <= 3]) - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_3_2-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_3_2-solution000001.solution deleted file mode 100644 index d56a0bbcdc..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_3_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_3_2-solution000002.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_3_2-solution000002.solution deleted file mode 100644 index ff56905e23..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_3_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_3_2-solution000003.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_3_2-solution000003.solution deleted file mode 100644 index 15472caf03..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_3_2-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 2, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_3_2-solution000004.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_3_2-solution000004.solution deleted file mode 100644 index 1b4b5b08a6..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_3_2-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 2, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_3_2-solution000005.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_3_2-solution000005.solution deleted file mode 100644 index 5e2caa751c..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_3_2-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 2, 2) -letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_3_2-solution000006.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_3_2-solution000006.solution deleted file mode 100644 index 621d5f6edc..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_3_2-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 1, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_3_2.eprime b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_3_2.eprime deleted file mode 100644 index f152965fd1..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_3_2.eprime +++ /dev/null @@ -1,75 +0,0 @@ -language ESSENCE' 1.0 - -find a_ExplicitWithRepetition_Flag: int(3) -find a_ExplicitWithRepetition_Values: matrix indexed by [int(1..3)] of int(1..2) -find a_MOccurrence: matrix indexed by [int(1..2)] of int(0..3) -find b_ExplicitWithRepetition_Flag: int(3) -find b_ExplicitWithRepetition_Values: matrix indexed by [int(1..3)] of int(1..2) -branching on - [a_MOccurrence, a_ExplicitWithRepetition_Flag, a_ExplicitWithRepetition_Values, b_ExplicitWithRepetition_Flag, - b_ExplicitWithRepetition_Values] -such that - or([sum([toInt(a_ExplicitWithRepetition_Values[q42] = a_ExplicitWithRepetition_Values[q21]) - | q42 : int(1..3), q42 <= 3]) - < - sum([toInt(b_ExplicitWithRepetition_Values[q44] = a_ExplicitWithRepetition_Values[q21]) - | q44 : int(1..3), q44 <= 3]) - /\ - (and([a_ExplicitWithRepetition_Values[q45] < a_ExplicitWithRepetition_Values[q21] -> - sum([toInt(a_ExplicitWithRepetition_Values[q54] = a_ExplicitWithRepetition_Values[q45]) - | q54 : int(1..3), q54 <= 3]) - = - sum([toInt(b_ExplicitWithRepetition_Values[q56] = a_ExplicitWithRepetition_Values[q45]) - | q56 : int(1..3), q56 <= 3]) - | q45 : int(1..3), q45 <= 3]) - /\ - and([!or([a_ExplicitWithRepetition_Values[q48] = b_ExplicitWithRepetition_Values[q46] - | q48 : int(1..3), q48 <= 3]) - /\ b_ExplicitWithRepetition_Values[q46] < a_ExplicitWithRepetition_Values[q21] - -> - sum([toInt(a_ExplicitWithRepetition_Values[q50] = b_ExplicitWithRepetition_Values[q46]) - | q50 : int(1..3), q50 <= 3]) - = - sum([toInt(b_ExplicitWithRepetition_Values[q52] = b_ExplicitWithRepetition_Values[q46]) - | q52 : int(1..3), q52 <= 3]) - | q46 : int(1..3), q46 <= 3])) - | q21 : int(1..3), q21 <= 3]) - \/ - or([!or([a_ExplicitWithRepetition_Values[q24] = b_ExplicitWithRepetition_Values[q22] | q24 : int(1..3), q24 <= 3]) - /\ - (sum([toInt(a_ExplicitWithRepetition_Values[q26] = b_ExplicitWithRepetition_Values[q22]) - | q26 : int(1..3), q26 <= 3]) - < - sum([toInt(b_ExplicitWithRepetition_Values[q28] = b_ExplicitWithRepetition_Values[q22]) - | q28 : int(1..3), q28 <= 3]) - /\ - (and([a_ExplicitWithRepetition_Values[q29] < b_ExplicitWithRepetition_Values[q22] -> - sum([toInt(a_ExplicitWithRepetition_Values[q38] = a_ExplicitWithRepetition_Values[q29]) - | q38 : int(1..3), q38 <= 3]) - = - sum([toInt(b_ExplicitWithRepetition_Values[q40] = a_ExplicitWithRepetition_Values[q29]) - | q40 : int(1..3), q40 <= 3]) - | q29 : int(1..3), q29 <= 3]) - /\ - and([!or([a_ExplicitWithRepetition_Values[q32] = b_ExplicitWithRepetition_Values[q30] - | q32 : int(1..3), q32 <= 3]) - /\ b_ExplicitWithRepetition_Values[q30] < b_ExplicitWithRepetition_Values[q22] - -> - sum([toInt(a_ExplicitWithRepetition_Values[q34] = b_ExplicitWithRepetition_Values[q30]) - | q34 : int(1..3), q34 <= 3]) - = - sum([toInt(b_ExplicitWithRepetition_Values[q36] = b_ExplicitWithRepetition_Values[q30]) - | q36 : int(1..3), q36 <= 3]) - | q30 : int(1..3), q30 <= 3]))) - | q22 : int(1..3), q22 <= 3]), - and([a_ExplicitWithRepetition_Values[q1] <= a_ExplicitWithRepetition_Values[q1 + 1] | q1 : int(1..2), q1 + 1 <= 3]), - and([b_ExplicitWithRepetition_Values[q6] <= b_ExplicitWithRepetition_Values[q6 + 1] | q6 : int(1..2), q6 + 1 <= 3]), - 3 = sum([a_MOccurrence[q11] | q11 : int(1..2)]), - and([a_MOccurrence[q13] > 0 -> - a_MOccurrence[q13] = sum([toInt(a_ExplicitWithRepetition_Values[q15] = q13) | q15 : int(1..3), q15 <= 3]) - | q13 : int(1..2)]), - and([a_MOccurrence[a_ExplicitWithRepetition_Values[q16]] = - sum([toInt(a_ExplicitWithRepetition_Values[q18] = a_ExplicitWithRepetition_Values[q16]) - | q18 : int(1..3), q18 <= 3]) - | q16 : int(1..3), q16 <= 3]) - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_3_3-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_3_3-solution000001.solution deleted file mode 100644 index 15472caf03..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_3_3-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 2, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_3_3-solution000002.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_3_3-solution000002.solution deleted file mode 100644 index ff56905e23..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_3_3-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_3_3-solution000003.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_3_3-solution000003.solution deleted file mode 100644 index d56a0bbcdc..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_3_3-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_3_3-solution000004.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_3_3-solution000004.solution deleted file mode 100644 index 5e2caa751c..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_3_3-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 2, 2) -letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_3_3-solution000005.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_3_3-solution000005.solution deleted file mode 100644 index 1b4b5b08a6..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_3_3-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 2, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_3_3-solution000006.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_3_3-solution000006.solution deleted file mode 100644 index 621d5f6edc..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_3_3-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 1, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_3_3.eprime b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_3_3.eprime deleted file mode 100644 index bc2ecdfcfe..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_3_3.eprime +++ /dev/null @@ -1,84 +0,0 @@ -language ESSENCE' 1.0 - -find a_ExplicitWithRepetition_Flag: int(3) -find a_ExplicitWithRepetition_Values: matrix indexed by [int(1..3)] of int(1..2) -find a_MOccurrence: matrix indexed by [int(1..2)] of int(0..3) -find b_ExplicitWithRepetition_Flag: int(3) -find b_ExplicitWithRepetition_Values: matrix indexed by [int(1..3)] of int(1..2) -find b_MOccurrence: matrix indexed by [int(1..2)] of int(0..3) -branching on - [a_MOccurrence, a_ExplicitWithRepetition_Flag, a_ExplicitWithRepetition_Values, b_MOccurrence, - b_ExplicitWithRepetition_Flag, b_ExplicitWithRepetition_Values] -such that - or([sum([toInt(a_ExplicitWithRepetition_Values[q50] = a_ExplicitWithRepetition_Values[q29]) - | q50 : int(1..3), q50 <= 3]) - < - sum([toInt(b_ExplicitWithRepetition_Values[q52] = a_ExplicitWithRepetition_Values[q29]) - | q52 : int(1..3), q52 <= 3]) - /\ - (and([a_ExplicitWithRepetition_Values[q53] < a_ExplicitWithRepetition_Values[q29] -> - sum([toInt(a_ExplicitWithRepetition_Values[q62] = a_ExplicitWithRepetition_Values[q53]) - | q62 : int(1..3), q62 <= 3]) - = - sum([toInt(b_ExplicitWithRepetition_Values[q64] = a_ExplicitWithRepetition_Values[q53]) - | q64 : int(1..3), q64 <= 3]) - | q53 : int(1..3), q53 <= 3]) - /\ - and([!or([a_ExplicitWithRepetition_Values[q56] = b_ExplicitWithRepetition_Values[q54] - | q56 : int(1..3), q56 <= 3]) - /\ b_ExplicitWithRepetition_Values[q54] < a_ExplicitWithRepetition_Values[q29] - -> - sum([toInt(a_ExplicitWithRepetition_Values[q58] = b_ExplicitWithRepetition_Values[q54]) - | q58 : int(1..3), q58 <= 3]) - = - sum([toInt(b_ExplicitWithRepetition_Values[q60] = b_ExplicitWithRepetition_Values[q54]) - | q60 : int(1..3), q60 <= 3]) - | q54 : int(1..3), q54 <= 3])) - | q29 : int(1..3), q29 <= 3]) - \/ - or([!or([a_ExplicitWithRepetition_Values[q32] = b_ExplicitWithRepetition_Values[q30] | q32 : int(1..3), q32 <= 3]) - /\ - (sum([toInt(a_ExplicitWithRepetition_Values[q34] = b_ExplicitWithRepetition_Values[q30]) - | q34 : int(1..3), q34 <= 3]) - < - sum([toInt(b_ExplicitWithRepetition_Values[q36] = b_ExplicitWithRepetition_Values[q30]) - | q36 : int(1..3), q36 <= 3]) - /\ - (and([a_ExplicitWithRepetition_Values[q37] < b_ExplicitWithRepetition_Values[q30] -> - sum([toInt(a_ExplicitWithRepetition_Values[q46] = a_ExplicitWithRepetition_Values[q37]) - | q46 : int(1..3), q46 <= 3]) - = - sum([toInt(b_ExplicitWithRepetition_Values[q48] = a_ExplicitWithRepetition_Values[q37]) - | q48 : int(1..3), q48 <= 3]) - | q37 : int(1..3), q37 <= 3]) - /\ - and([!or([a_ExplicitWithRepetition_Values[q40] = b_ExplicitWithRepetition_Values[q38] - | q40 : int(1..3), q40 <= 3]) - /\ b_ExplicitWithRepetition_Values[q38] < b_ExplicitWithRepetition_Values[q30] - -> - sum([toInt(a_ExplicitWithRepetition_Values[q42] = b_ExplicitWithRepetition_Values[q38]) - | q42 : int(1..3), q42 <= 3]) - = - sum([toInt(b_ExplicitWithRepetition_Values[q44] = b_ExplicitWithRepetition_Values[q38]) - | q44 : int(1..3), q44 <= 3]) - | q38 : int(1..3), q38 <= 3]))) - | q30 : int(1..3), q30 <= 3]), - and([a_ExplicitWithRepetition_Values[q1] <= a_ExplicitWithRepetition_Values[q1 + 1] | q1 : int(1..2), q1 + 1 <= 3]), - and([b_ExplicitWithRepetition_Values[q6] <= b_ExplicitWithRepetition_Values[q6 + 1] | q6 : int(1..2), q6 + 1 <= 3]), - 3 = sum([a_MOccurrence[q11] | q11 : int(1..2)]), - and([a_MOccurrence[q21] > 0 -> - a_MOccurrence[q21] = sum([toInt(a_ExplicitWithRepetition_Values[q23] = q21) | q23 : int(1..3), q23 <= 3]) - | q21 : int(1..2)]), - and([a_MOccurrence[a_ExplicitWithRepetition_Values[q24]] = - sum([toInt(a_ExplicitWithRepetition_Values[q26] = a_ExplicitWithRepetition_Values[q24]) - | q26 : int(1..3), q26 <= 3]) - | q24 : int(1..3), q24 <= 3]), - 3 = sum([b_MOccurrence[q12] | q12 : int(1..2)]), - and([b_MOccurrence[q14] > 0 -> - b_MOccurrence[q14] = sum([toInt(b_ExplicitWithRepetition_Values[q16] = q14) | q16 : int(1..3), q16 <= 3]) - | q14 : int(1..2)]), - and([b_MOccurrence[b_ExplicitWithRepetition_Values[q17]] = - sum([toInt(b_ExplicitWithRepetition_Values[q19] = b_ExplicitWithRepetition_Values[q17]) - | q19 : int(1..3), q19 <= 3]) - | q17 : int(1..3), q17 <= 3]) - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_1_1-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_1_1-solution000001.solution deleted file mode 100644 index 5e2caa751c..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_1_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 2, 2) -letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_1_1-solution000002.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_1_1-solution000002.solution deleted file mode 100644 index 1b4b5b08a6..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_1_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 2, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_1_1-solution000003.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_1_1-solution000003.solution deleted file mode 100644 index 621d5f6edc..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_1_1-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 1, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_1_1-solution000004.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_1_1-solution000004.solution deleted file mode 100644 index 15472caf03..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_1_1-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 2, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_1_1-solution000005.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_1_1-solution000005.solution deleted file mode 100644 index ff56905e23..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_1_1-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_1_1-solution000006.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_1_1-solution000006.solution deleted file mode 100644 index d56a0bbcdc..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_1_1-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_1_1.eprime b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_1_1.eprime deleted file mode 100644 index 738bb5fb14..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_1_1.eprime +++ /dev/null @@ -1,83 +0,0 @@ -language ESSENCE' 1.0 - -find a_ExplicitWithRepetition_Flag: int(3) -find a_ExplicitWithRepetition_Values: matrix indexed by [int(1..3)] of int(1..2) -find a_ExplicitWithFlags_Flags: matrix indexed by [int(1..3)] of int(0..3) -find a_ExplicitWithFlags_Values: matrix indexed by [int(1..3)] of int(1..2) -find b_MOccurrence: matrix indexed by [int(1..2)] of int(0..3) -find b_ExplicitWithFlags_Flags: matrix indexed by [int(1..3)] of int(0..3) -find b_ExplicitWithFlags_Values: matrix indexed by [int(1..3)] of int(1..2) -branching on - [a_ExplicitWithFlags_Flags, a_ExplicitWithFlags_Values, a_ExplicitWithRepetition_Flag, - a_ExplicitWithRepetition_Values, b_ExplicitWithFlags_Flags, b_ExplicitWithFlags_Values, b_MOccurrence] -such that - or([sum([toInt(a_ExplicitWithRepetition_Values[q42] = a_ExplicitWithRepetition_Values[q43]) - | q42 : int(1..3), q42 <= 3]) - < b_MOccurrence[a_ExplicitWithRepetition_Values[q43]] - /\ - (and([a_ExplicitWithRepetition_Values[q37] < a_ExplicitWithRepetition_Values[q43] -> - sum([toInt(a_ExplicitWithRepetition_Values[q36] = a_ExplicitWithRepetition_Values[q37]) - | q36 : int(1..3), q36 <= 3]) - = b_MOccurrence[a_ExplicitWithRepetition_Values[q37]] - | q37 : int(1..3), q37 <= 3]) - /\ - and([q40 < a_ExplicitWithRepetition_Values[q43] -> - (b_MOccurrence[q40] > 0 /\ !or([a_ExplicitWithRepetition_Values[q39] = q40 | q39 : int(1..3), q39 <= 3]) - -> - sum([toInt(a_ExplicitWithRepetition_Values[q36] = q40) | q36 : int(1..3), q36 <= 3]) = - b_MOccurrence[q40]) - | q40 : int(1..2)])) - | q43 : int(1..3), q43 <= 3]) - \/ - or([b_MOccurrence[q46] > 0 /\ !or([a_ExplicitWithRepetition_Values[q45] = q46 | q45 : int(1..3), q45 <= 3]) /\ - (sum([toInt(a_ExplicitWithRepetition_Values[q42] = q46) | q42 : int(1..3), q42 <= 3]) < b_MOccurrence[q46] /\ - (and([a_ExplicitWithRepetition_Values[q37] < q46 -> - sum([toInt(a_ExplicitWithRepetition_Values[q36] = a_ExplicitWithRepetition_Values[q37]) - | q36 : int(1..3), q36 <= 3]) - = b_MOccurrence[a_ExplicitWithRepetition_Values[q37]] - | q37 : int(1..3), q37 <= 3]) - /\ - and([b_MOccurrence[q40] > 0 /\ !or([a_ExplicitWithRepetition_Values[q39] = q40 | q39 : int(1..3), q39 <= 3]) - -> - sum([toInt(a_ExplicitWithRepetition_Values[q36] = q40) | q36 : int(1..3), q36 <= 3]) = b_MOccurrence[q40] - | q40 : int(1..2), q40 < q46]))) - | q46 : int(1..2)]), - and([a_ExplicitWithRepetition_Values[q1] <= a_ExplicitWithRepetition_Values[q1 + 1] | q1 : int(1..2), q1 + 1 <= 3]), - 3 = sum([b_MOccurrence[q6] | q6 : int(1..2)]), - and([a_ExplicitWithFlags_Flags[q7 + 1] > 0 -> a_ExplicitWithFlags_Values[q7] < a_ExplicitWithFlags_Values[q7 + 1] - | q7 : int(1..2)]), - and([a_ExplicitWithFlags_Flags[q8] = 0 -> a_ExplicitWithFlags_Values[q8] = 1 | q8 : int(1..3)]), - and([a_ExplicitWithFlags_Flags[q9 + 1] > 0 -> a_ExplicitWithFlags_Flags[q9] > 0 | q9 : int(1..2)]), - 3 = sum([a_ExplicitWithFlags_Flags[q11] | q11 : int(1..3)]), - and([a_ExplicitWithFlags_Flags[q14] > 0 -> - sum([toInt(a_ExplicitWithFlags_Values[q15] = a_ExplicitWithFlags_Values[q14]) * - catchUndef(a_ExplicitWithFlags_Flags[q15], 0) - | q15 : int(1..3)]) - = - sum([toInt(a_ExplicitWithRepetition_Values[q17] = a_ExplicitWithFlags_Values[q14]) - | q17 : int(1..3), q17 <= 3]) - | q14 : int(1..3)]), - and([sum([toInt(a_ExplicitWithFlags_Values[q19] = a_ExplicitWithRepetition_Values[q18]) * - catchUndef(a_ExplicitWithFlags_Flags[q19], 0) - | q19 : int(1..3)]) - = - sum([toInt(a_ExplicitWithRepetition_Values[q21] = a_ExplicitWithRepetition_Values[q18]) - | q21 : int(1..3), q21 <= 3]) - | q18 : int(1..3), q18 <= 3]), - and([b_ExplicitWithFlags_Flags[q22 + 1] > 0 -> b_ExplicitWithFlags_Values[q22] < b_ExplicitWithFlags_Values[q22 + 1] - | q22 : int(1..2)]), - and([b_ExplicitWithFlags_Flags[q23] = 0 -> b_ExplicitWithFlags_Values[q23] = 1 | q23 : int(1..3)]), - and([b_ExplicitWithFlags_Flags[q24 + 1] > 0 -> b_ExplicitWithFlags_Flags[q24] > 0 | q24 : int(1..2)]), - 3 = sum([b_ExplicitWithFlags_Flags[q26] | q26 : int(1..3)]), - and([b_ExplicitWithFlags_Flags[q29] > 0 -> - sum([toInt(b_ExplicitWithFlags_Values[q30] = b_ExplicitWithFlags_Values[q29]) * - catchUndef(b_ExplicitWithFlags_Flags[q30], 0) - | q30 : int(1..3)]) - = b_MOccurrence[b_ExplicitWithFlags_Values[q29]] - | q29 : int(1..3)]), - and([b_MOccurrence[q31] > 0 -> - sum([toInt(b_ExplicitWithFlags_Values[q32] = q31) * catchUndef(b_ExplicitWithFlags_Flags[q32], 0) - | q32 : int(1..3)]) - = b_MOccurrence[q31] - | q31 : int(1..2)]) - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_1_2-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_1_2-solution000001.solution deleted file mode 100644 index 1b4b5b08a6..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_1_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 2, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_1_2-solution000002.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_1_2-solution000002.solution deleted file mode 100644 index 5e2caa751c..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_1_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 2, 2) -letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_1_2-solution000003.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_1_2-solution000003.solution deleted file mode 100644 index 621d5f6edc..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_1_2-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 1, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_1_2-solution000004.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_1_2-solution000004.solution deleted file mode 100644 index d56a0bbcdc..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_1_2-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_1_2-solution000005.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_1_2-solution000005.solution deleted file mode 100644 index ff56905e23..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_1_2-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_1_2-solution000006.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_1_2-solution000006.solution deleted file mode 100644 index 15472caf03..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_1_2-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 2, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_1_2.eprime b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_1_2.eprime deleted file mode 100644 index c0d6342a0e..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_1_2.eprime +++ /dev/null @@ -1,76 +0,0 @@ -language ESSENCE' 1.0 - -find a_ExplicitWithRepetition_Flag: int(3) -find a_ExplicitWithRepetition_Values: matrix indexed by [int(1..3)] of int(1..2) -find a_ExplicitWithFlags_Flags: matrix indexed by [int(1..3)] of int(0..3) -find a_ExplicitWithFlags_Values: matrix indexed by [int(1..3)] of int(1..2) -find b_MOccurrence: matrix indexed by [int(1..2)] of int(0..3) -find b_ExplicitWithRepetition_Flag: int(3) -find b_ExplicitWithRepetition_Values: matrix indexed by [int(1..3)] of int(1..2) -branching on - [a_ExplicitWithFlags_Flags, a_ExplicitWithFlags_Values, a_ExplicitWithRepetition_Flag, - a_ExplicitWithRepetition_Values, b_ExplicitWithRepetition_Flag, b_ExplicitWithRepetition_Values, b_MOccurrence] -such that - or([sum([toInt(a_ExplicitWithRepetition_Values[q43] = a_ExplicitWithRepetition_Values[q44]) - | q43 : int(1..3), q43 <= 3]) - < b_MOccurrence[a_ExplicitWithRepetition_Values[q44]] - /\ - (and([a_ExplicitWithRepetition_Values[q38] < a_ExplicitWithRepetition_Values[q44] -> - sum([toInt(a_ExplicitWithRepetition_Values[q37] = a_ExplicitWithRepetition_Values[q38]) - | q37 : int(1..3), q37 <= 3]) - = b_MOccurrence[a_ExplicitWithRepetition_Values[q38]] - | q38 : int(1..3), q38 <= 3]) - /\ - and([q41 < a_ExplicitWithRepetition_Values[q44] -> - (b_MOccurrence[q41] > 0 /\ !or([a_ExplicitWithRepetition_Values[q40] = q41 | q40 : int(1..3), q40 <= 3]) - -> - sum([toInt(a_ExplicitWithRepetition_Values[q37] = q41) | q37 : int(1..3), q37 <= 3]) = - b_MOccurrence[q41]) - | q41 : int(1..2)])) - | q44 : int(1..3), q44 <= 3]) - \/ - or([b_MOccurrence[q47] > 0 /\ !or([a_ExplicitWithRepetition_Values[q46] = q47 | q46 : int(1..3), q46 <= 3]) /\ - (sum([toInt(a_ExplicitWithRepetition_Values[q43] = q47) | q43 : int(1..3), q43 <= 3]) < b_MOccurrence[q47] /\ - (and([a_ExplicitWithRepetition_Values[q38] < q47 -> - sum([toInt(a_ExplicitWithRepetition_Values[q37] = a_ExplicitWithRepetition_Values[q38]) - | q37 : int(1..3), q37 <= 3]) - = b_MOccurrence[a_ExplicitWithRepetition_Values[q38]] - | q38 : int(1..3), q38 <= 3]) - /\ - and([b_MOccurrence[q41] > 0 /\ !or([a_ExplicitWithRepetition_Values[q40] = q41 | q40 : int(1..3), q40 <= 3]) - -> - sum([toInt(a_ExplicitWithRepetition_Values[q37] = q41) | q37 : int(1..3), q37 <= 3]) = b_MOccurrence[q41] - | q41 : int(1..2), q41 < q47]))) - | q47 : int(1..2)]), - and([a_ExplicitWithRepetition_Values[q1] <= a_ExplicitWithRepetition_Values[q1 + 1] | q1 : int(1..2), q1 + 1 <= 3]), - 3 = sum([b_MOccurrence[q6] | q6 : int(1..2)]), - and([a_ExplicitWithFlags_Flags[q7 + 1] > 0 -> a_ExplicitWithFlags_Values[q7] < a_ExplicitWithFlags_Values[q7 + 1] - | q7 : int(1..2)]), - and([a_ExplicitWithFlags_Flags[q8] = 0 -> a_ExplicitWithFlags_Values[q8] = 1 | q8 : int(1..3)]), - and([a_ExplicitWithFlags_Flags[q9 + 1] > 0 -> a_ExplicitWithFlags_Flags[q9] > 0 | q9 : int(1..2)]), - 3 = sum([a_ExplicitWithFlags_Flags[q11] | q11 : int(1..3)]), - and([a_ExplicitWithFlags_Flags[q14] > 0 -> - sum([toInt(a_ExplicitWithFlags_Values[q15] = a_ExplicitWithFlags_Values[q14]) * - catchUndef(a_ExplicitWithFlags_Flags[q15], 0) - | q15 : int(1..3)]) - = - sum([toInt(a_ExplicitWithRepetition_Values[q17] = a_ExplicitWithFlags_Values[q14]) - | q17 : int(1..3), q17 <= 3]) - | q14 : int(1..3)]), - and([sum([toInt(a_ExplicitWithFlags_Values[q19] = a_ExplicitWithRepetition_Values[q18]) * - catchUndef(a_ExplicitWithFlags_Flags[q19], 0) - | q19 : int(1..3)]) - = - sum([toInt(a_ExplicitWithRepetition_Values[q21] = a_ExplicitWithRepetition_Values[q18]) - | q21 : int(1..3), q21 <= 3]) - | q18 : int(1..3), q18 <= 3]), - and([b_ExplicitWithRepetition_Values[q22] <= b_ExplicitWithRepetition_Values[q22 + 1] - | q22 : int(1..2), q22 + 1 <= 3]), - and([sum([toInt(b_ExplicitWithRepetition_Values[q30] = b_ExplicitWithRepetition_Values[q28]) - | q30 : int(1..3), q30 <= 3]) - = b_MOccurrence[b_ExplicitWithRepetition_Values[q28]] - | q28 : int(1..3), q28 <= 3]), - and([b_MOccurrence[q31] > 0 -> - sum([toInt(b_ExplicitWithRepetition_Values[q33] = q31) | q33 : int(1..3), q33 <= 3]) = b_MOccurrence[q31] - | q31 : int(1..2)]) - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_1_3-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_1_3-solution000001.solution deleted file mode 100644 index 5e2caa751c..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_1_3-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 2, 2) -letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_1_3-solution000002.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_1_3-solution000002.solution deleted file mode 100644 index 1b4b5b08a6..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_1_3-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 2, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_1_3-solution000003.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_1_3-solution000003.solution deleted file mode 100644 index 621d5f6edc..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_1_3-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 1, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_1_3-solution000004.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_1_3-solution000004.solution deleted file mode 100644 index 15472caf03..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_1_3-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 2, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_1_3-solution000005.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_1_3-solution000005.solution deleted file mode 100644 index ff56905e23..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_1_3-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_1_3-solution000006.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_1_3-solution000006.solution deleted file mode 100644 index d56a0bbcdc..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_1_3-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_1_3.eprime b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_1_3.eprime deleted file mode 100644 index 908f0c60b9..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_1_3.eprime +++ /dev/null @@ -1,65 +0,0 @@ -language ESSENCE' 1.0 - -find a_ExplicitWithRepetition_Flag: int(3) -find a_ExplicitWithRepetition_Values: matrix indexed by [int(1..3)] of int(1..2) -find a_ExplicitWithFlags_Flags: matrix indexed by [int(1..3)] of int(0..3) -find a_ExplicitWithFlags_Values: matrix indexed by [int(1..3)] of int(1..2) -find b_MOccurrence: matrix indexed by [int(1..2)] of int(0..3) -branching on - [a_ExplicitWithFlags_Flags, a_ExplicitWithFlags_Values, a_ExplicitWithRepetition_Flag, - a_ExplicitWithRepetition_Values, b_MOccurrence] -such that - or([sum([toInt(a_ExplicitWithRepetition_Values[q31] = a_ExplicitWithRepetition_Values[q32]) - | q31 : int(1..3), q31 <= 3]) - < b_MOccurrence[a_ExplicitWithRepetition_Values[q32]] - /\ - (and([a_ExplicitWithRepetition_Values[q26] < a_ExplicitWithRepetition_Values[q32] -> - sum([toInt(a_ExplicitWithRepetition_Values[q25] = a_ExplicitWithRepetition_Values[q26]) - | q25 : int(1..3), q25 <= 3]) - = b_MOccurrence[a_ExplicitWithRepetition_Values[q26]] - | q26 : int(1..3), q26 <= 3]) - /\ - and([q29 < a_ExplicitWithRepetition_Values[q32] -> - (b_MOccurrence[q29] > 0 /\ !or([a_ExplicitWithRepetition_Values[q28] = q29 | q28 : int(1..3), q28 <= 3]) - -> - sum([toInt(a_ExplicitWithRepetition_Values[q25] = q29) | q25 : int(1..3), q25 <= 3]) = - b_MOccurrence[q29]) - | q29 : int(1..2)])) - | q32 : int(1..3), q32 <= 3]) - \/ - or([b_MOccurrence[q35] > 0 /\ !or([a_ExplicitWithRepetition_Values[q34] = q35 | q34 : int(1..3), q34 <= 3]) /\ - (sum([toInt(a_ExplicitWithRepetition_Values[q31] = q35) | q31 : int(1..3), q31 <= 3]) < b_MOccurrence[q35] /\ - (and([a_ExplicitWithRepetition_Values[q26] < q35 -> - sum([toInt(a_ExplicitWithRepetition_Values[q25] = a_ExplicitWithRepetition_Values[q26]) - | q25 : int(1..3), q25 <= 3]) - = b_MOccurrence[a_ExplicitWithRepetition_Values[q26]] - | q26 : int(1..3), q26 <= 3]) - /\ - and([b_MOccurrence[q29] > 0 /\ !or([a_ExplicitWithRepetition_Values[q28] = q29 | q28 : int(1..3), q28 <= 3]) - -> - sum([toInt(a_ExplicitWithRepetition_Values[q25] = q29) | q25 : int(1..3), q25 <= 3]) = b_MOccurrence[q29] - | q29 : int(1..2), q29 < q35]))) - | q35 : int(1..2)]), - and([a_ExplicitWithRepetition_Values[q1] <= a_ExplicitWithRepetition_Values[q1 + 1] | q1 : int(1..2), q1 + 1 <= 3]), - 3 = sum([b_MOccurrence[q6] | q6 : int(1..2)]), - and([a_ExplicitWithFlags_Flags[q7 + 1] > 0 -> a_ExplicitWithFlags_Values[q7] < a_ExplicitWithFlags_Values[q7 + 1] - | q7 : int(1..2)]), - and([a_ExplicitWithFlags_Flags[q8] = 0 -> a_ExplicitWithFlags_Values[q8] = 1 | q8 : int(1..3)]), - and([a_ExplicitWithFlags_Flags[q9 + 1] > 0 -> a_ExplicitWithFlags_Flags[q9] > 0 | q9 : int(1..2)]), - 3 = sum([a_ExplicitWithFlags_Flags[q11] | q11 : int(1..3)]), - and([a_ExplicitWithFlags_Flags[q14] > 0 -> - sum([toInt(a_ExplicitWithFlags_Values[q15] = a_ExplicitWithFlags_Values[q14]) * - catchUndef(a_ExplicitWithFlags_Flags[q15], 0) - | q15 : int(1..3)]) - = - sum([toInt(a_ExplicitWithRepetition_Values[q17] = a_ExplicitWithFlags_Values[q14]) - | q17 : int(1..3), q17 <= 3]) - | q14 : int(1..3)]), - and([sum([toInt(a_ExplicitWithFlags_Values[q19] = a_ExplicitWithRepetition_Values[q18]) * - catchUndef(a_ExplicitWithFlags_Flags[q19], 0) - | q19 : int(1..3)]) - = - sum([toInt(a_ExplicitWithRepetition_Values[q21] = a_ExplicitWithRepetition_Values[q18]) - | q21 : int(1..3), q21 <= 3]) - | q18 : int(1..3), q18 <= 3]) - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_2_1-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_2_1-solution000001.solution deleted file mode 100644 index 621d5f6edc..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_2_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 1, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_2_1-solution000002.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_2_1-solution000002.solution deleted file mode 100644 index 5e2caa751c..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_2_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 2, 2) -letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_2_1-solution000003.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_2_1-solution000003.solution deleted file mode 100644 index 1b4b5b08a6..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_2_1-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 2, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_2_1-solution000004.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_2_1-solution000004.solution deleted file mode 100644 index 15472caf03..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_2_1-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 2, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_2_1-solution000005.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_2_1-solution000005.solution deleted file mode 100644 index ff56905e23..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_2_1-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_2_1-solution000006.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_2_1-solution000006.solution deleted file mode 100644 index d56a0bbcdc..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_2_1-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_2_1.eprime b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_2_1.eprime deleted file mode 100644 index 3596eb2d74..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_2_1.eprime +++ /dev/null @@ -1,61 +0,0 @@ -language ESSENCE' 1.0 - -find a_ExplicitWithRepetition_Flag: int(3) -find a_ExplicitWithRepetition_Values: matrix indexed by [int(1..3)] of int(1..2) -find b_MOccurrence: matrix indexed by [int(1..2)] of int(0..3) -find b_ExplicitWithFlags_Flags: matrix indexed by [int(1..3)] of int(0..3) -find b_ExplicitWithFlags_Values: matrix indexed by [int(1..3)] of int(1..2) -branching on - [a_ExplicitWithRepetition_Flag, a_ExplicitWithRepetition_Values, b_ExplicitWithFlags_Flags, - b_ExplicitWithFlags_Values, b_MOccurrence] -such that - or([sum([toInt(a_ExplicitWithRepetition_Values[q27] = a_ExplicitWithRepetition_Values[q28]) - | q27 : int(1..3), q27 <= 3]) - < b_MOccurrence[a_ExplicitWithRepetition_Values[q28]] - /\ - (and([a_ExplicitWithRepetition_Values[q22] < a_ExplicitWithRepetition_Values[q28] -> - sum([toInt(a_ExplicitWithRepetition_Values[q21] = a_ExplicitWithRepetition_Values[q22]) - | q21 : int(1..3), q21 <= 3]) - = b_MOccurrence[a_ExplicitWithRepetition_Values[q22]] - | q22 : int(1..3), q22 <= 3]) - /\ - and([q25 < a_ExplicitWithRepetition_Values[q28] -> - (b_MOccurrence[q25] > 0 /\ !or([a_ExplicitWithRepetition_Values[q24] = q25 | q24 : int(1..3), q24 <= 3]) - -> - sum([toInt(a_ExplicitWithRepetition_Values[q21] = q25) | q21 : int(1..3), q21 <= 3]) = - b_MOccurrence[q25]) - | q25 : int(1..2)])) - | q28 : int(1..3), q28 <= 3]) - \/ - or([b_MOccurrence[q31] > 0 /\ !or([a_ExplicitWithRepetition_Values[q30] = q31 | q30 : int(1..3), q30 <= 3]) /\ - (sum([toInt(a_ExplicitWithRepetition_Values[q27] = q31) | q27 : int(1..3), q27 <= 3]) < b_MOccurrence[q31] /\ - (and([a_ExplicitWithRepetition_Values[q22] < q31 -> - sum([toInt(a_ExplicitWithRepetition_Values[q21] = a_ExplicitWithRepetition_Values[q22]) - | q21 : int(1..3), q21 <= 3]) - = b_MOccurrence[a_ExplicitWithRepetition_Values[q22]] - | q22 : int(1..3), q22 <= 3]) - /\ - and([b_MOccurrence[q25] > 0 /\ !or([a_ExplicitWithRepetition_Values[q24] = q25 | q24 : int(1..3), q24 <= 3]) - -> - sum([toInt(a_ExplicitWithRepetition_Values[q21] = q25) | q21 : int(1..3), q21 <= 3]) = b_MOccurrence[q25] - | q25 : int(1..2), q25 < q31]))) - | q31 : int(1..2)]), - and([a_ExplicitWithRepetition_Values[q1] <= a_ExplicitWithRepetition_Values[q1 + 1] | q1 : int(1..2), q1 + 1 <= 3]), - 3 = sum([b_MOccurrence[q6] | q6 : int(1..2)]), - and([b_ExplicitWithFlags_Flags[q7 + 1] > 0 -> b_ExplicitWithFlags_Values[q7] < b_ExplicitWithFlags_Values[q7 + 1] - | q7 : int(1..2)]), - and([b_ExplicitWithFlags_Flags[q8] = 0 -> b_ExplicitWithFlags_Values[q8] = 1 | q8 : int(1..3)]), - and([b_ExplicitWithFlags_Flags[q9 + 1] > 0 -> b_ExplicitWithFlags_Flags[q9] > 0 | q9 : int(1..2)]), - 3 = sum([b_ExplicitWithFlags_Flags[q11] | q11 : int(1..3)]), - and([b_ExplicitWithFlags_Flags[q14] > 0 -> - sum([toInt(b_ExplicitWithFlags_Values[q15] = b_ExplicitWithFlags_Values[q14]) * - catchUndef(b_ExplicitWithFlags_Flags[q15], 0) - | q15 : int(1..3)]) - = b_MOccurrence[b_ExplicitWithFlags_Values[q14]] - | q14 : int(1..3)]), - and([b_MOccurrence[q16] > 0 -> - sum([toInt(b_ExplicitWithFlags_Values[q17] = q16) * catchUndef(b_ExplicitWithFlags_Flags[q17], 0) - | q17 : int(1..3)]) - = b_MOccurrence[q16] - | q16 : int(1..2)]) - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_2_2-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_2_2-solution000001.solution deleted file mode 100644 index 621d5f6edc..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_2_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 1, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_2_2-solution000002.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_2_2-solution000002.solution deleted file mode 100644 index 1b4b5b08a6..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_2_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 2, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_2_2-solution000003.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_2_2-solution000003.solution deleted file mode 100644 index 5e2caa751c..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_2_2-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 2, 2) -letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_2_2-solution000004.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_2_2-solution000004.solution deleted file mode 100644 index d56a0bbcdc..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_2_2-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_2_2-solution000005.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_2_2-solution000005.solution deleted file mode 100644 index ff56905e23..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_2_2-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_2_2-solution000006.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_2_2-solution000006.solution deleted file mode 100644 index 15472caf03..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_2_2-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 2, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_2_2.eprime b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_2_2.eprime deleted file mode 100644 index d9e532d5b0..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_2_2.eprime +++ /dev/null @@ -1,53 +0,0 @@ -language ESSENCE' 1.0 - -find a_ExplicitWithRepetition_Flag: int(3) -find a_ExplicitWithRepetition_Values: matrix indexed by [int(1..3)] of int(1..2) -find b_MOccurrence: matrix indexed by [int(1..2)] of int(0..3) -find b_ExplicitWithRepetition_Flag: int(3) -find b_ExplicitWithRepetition_Values: matrix indexed by [int(1..3)] of int(1..2) -branching on - [a_ExplicitWithRepetition_Flag, a_ExplicitWithRepetition_Values, b_ExplicitWithRepetition_Flag, - b_ExplicitWithRepetition_Values, b_MOccurrence] -such that - or([sum([toInt(a_ExplicitWithRepetition_Values[q28] = a_ExplicitWithRepetition_Values[q29]) - | q28 : int(1..3), q28 <= 3]) - < b_MOccurrence[a_ExplicitWithRepetition_Values[q29]] - /\ - (and([a_ExplicitWithRepetition_Values[q23] < a_ExplicitWithRepetition_Values[q29] -> - sum([toInt(a_ExplicitWithRepetition_Values[q22] = a_ExplicitWithRepetition_Values[q23]) - | q22 : int(1..3), q22 <= 3]) - = b_MOccurrence[a_ExplicitWithRepetition_Values[q23]] - | q23 : int(1..3), q23 <= 3]) - /\ - and([q26 < a_ExplicitWithRepetition_Values[q29] -> - (b_MOccurrence[q26] > 0 /\ !or([a_ExplicitWithRepetition_Values[q25] = q26 | q25 : int(1..3), q25 <= 3]) - -> - sum([toInt(a_ExplicitWithRepetition_Values[q22] = q26) | q22 : int(1..3), q22 <= 3]) = - b_MOccurrence[q26]) - | q26 : int(1..2)])) - | q29 : int(1..3), q29 <= 3]) - \/ - or([b_MOccurrence[q32] > 0 /\ !or([a_ExplicitWithRepetition_Values[q31] = q32 | q31 : int(1..3), q31 <= 3]) /\ - (sum([toInt(a_ExplicitWithRepetition_Values[q28] = q32) | q28 : int(1..3), q28 <= 3]) < b_MOccurrence[q32] /\ - (and([a_ExplicitWithRepetition_Values[q23] < q32 -> - sum([toInt(a_ExplicitWithRepetition_Values[q22] = a_ExplicitWithRepetition_Values[q23]) - | q22 : int(1..3), q22 <= 3]) - = b_MOccurrence[a_ExplicitWithRepetition_Values[q23]] - | q23 : int(1..3), q23 <= 3]) - /\ - and([b_MOccurrence[q26] > 0 /\ !or([a_ExplicitWithRepetition_Values[q25] = q26 | q25 : int(1..3), q25 <= 3]) - -> - sum([toInt(a_ExplicitWithRepetition_Values[q22] = q26) | q22 : int(1..3), q22 <= 3]) = b_MOccurrence[q26] - | q26 : int(1..2), q26 < q32]))) - | q32 : int(1..2)]), - and([a_ExplicitWithRepetition_Values[q1] <= a_ExplicitWithRepetition_Values[q1 + 1] | q1 : int(1..2), q1 + 1 <= 3]), - 3 = sum([b_MOccurrence[q6] | q6 : int(1..2)]), - and([b_ExplicitWithRepetition_Values[q7] <= b_ExplicitWithRepetition_Values[q7 + 1] | q7 : int(1..2), q7 + 1 <= 3]), - and([sum([toInt(b_ExplicitWithRepetition_Values[q15] = b_ExplicitWithRepetition_Values[q13]) - | q15 : int(1..3), q15 <= 3]) - = b_MOccurrence[b_ExplicitWithRepetition_Values[q13]] - | q13 : int(1..3), q13 <= 3]), - and([b_MOccurrence[q16] > 0 -> - sum([toInt(b_ExplicitWithRepetition_Values[q18] = q16) | q18 : int(1..3), q18 <= 3]) = b_MOccurrence[q16] - | q16 : int(1..2)]) - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_2_3-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_2_3-solution000001.solution deleted file mode 100644 index 621d5f6edc..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_2_3-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 1, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_2_3-solution000002.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_2_3-solution000002.solution deleted file mode 100644 index 5e2caa751c..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_2_3-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 2, 2) -letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_2_3-solution000003.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_2_3-solution000003.solution deleted file mode 100644 index 1b4b5b08a6..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_2_3-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 2, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_2_3-solution000004.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_2_3-solution000004.solution deleted file mode 100644 index 15472caf03..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_2_3-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 2, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_2_3-solution000005.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_2_3-solution000005.solution deleted file mode 100644 index ff56905e23..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_2_3-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_2_3-solution000006.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_2_3-solution000006.solution deleted file mode 100644 index d56a0bbcdc..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_2_3-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_2_3.eprime b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_2_3.eprime deleted file mode 100644 index 3857dbf52e..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_2_3.eprime +++ /dev/null @@ -1,41 +0,0 @@ -language ESSENCE' 1.0 - -find a_ExplicitWithRepetition_Flag: int(3) -find a_ExplicitWithRepetition_Values: matrix indexed by [int(1..3)] of int(1..2) -find b_MOccurrence: matrix indexed by [int(1..2)] of int(0..3) -branching on [a_ExplicitWithRepetition_Flag, a_ExplicitWithRepetition_Values, b_MOccurrence] -such that - or([sum([toInt(a_ExplicitWithRepetition_Values[q16] = a_ExplicitWithRepetition_Values[q17]) - | q16 : int(1..3), q16 <= 3]) - < b_MOccurrence[a_ExplicitWithRepetition_Values[q17]] - /\ - (and([a_ExplicitWithRepetition_Values[q11] < a_ExplicitWithRepetition_Values[q17] -> - sum([toInt(a_ExplicitWithRepetition_Values[q10] = a_ExplicitWithRepetition_Values[q11]) - | q10 : int(1..3), q10 <= 3]) - = b_MOccurrence[a_ExplicitWithRepetition_Values[q11]] - | q11 : int(1..3), q11 <= 3]) - /\ - and([q14 < a_ExplicitWithRepetition_Values[q17] -> - (b_MOccurrence[q14] > 0 /\ !or([a_ExplicitWithRepetition_Values[q13] = q14 | q13 : int(1..3), q13 <= 3]) - -> - sum([toInt(a_ExplicitWithRepetition_Values[q10] = q14) | q10 : int(1..3), q10 <= 3]) = - b_MOccurrence[q14]) - | q14 : int(1..2)])) - | q17 : int(1..3), q17 <= 3]) - \/ - or([b_MOccurrence[q20] > 0 /\ !or([a_ExplicitWithRepetition_Values[q19] = q20 | q19 : int(1..3), q19 <= 3]) /\ - (sum([toInt(a_ExplicitWithRepetition_Values[q16] = q20) | q16 : int(1..3), q16 <= 3]) < b_MOccurrence[q20] /\ - (and([a_ExplicitWithRepetition_Values[q11] < q20 -> - sum([toInt(a_ExplicitWithRepetition_Values[q10] = a_ExplicitWithRepetition_Values[q11]) - | q10 : int(1..3), q10 <= 3]) - = b_MOccurrence[a_ExplicitWithRepetition_Values[q11]] - | q11 : int(1..3), q11 <= 3]) - /\ - and([b_MOccurrence[q14] > 0 /\ !or([a_ExplicitWithRepetition_Values[q13] = q14 | q13 : int(1..3), q13 <= 3]) - -> - sum([toInt(a_ExplicitWithRepetition_Values[q10] = q14) | q10 : int(1..3), q10 <= 3]) = b_MOccurrence[q14] - | q14 : int(1..2), q14 < q20]))) - | q20 : int(1..2)]), - and([a_ExplicitWithRepetition_Values[q1] <= a_ExplicitWithRepetition_Values[q1 + 1] | q1 : int(1..2), q1 + 1 <= 3]), - 3 = sum([b_MOccurrence[q6] | q6 : int(1..2)]) - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_3_1-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_3_1-solution000001.solution deleted file mode 100644 index 15472caf03..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_3_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 2, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_3_1-solution000002.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_3_1-solution000002.solution deleted file mode 100644 index ff56905e23..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_3_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_3_1-solution000003.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_3_1-solution000003.solution deleted file mode 100644 index d56a0bbcdc..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_3_1-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_3_1-solution000004.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_3_1-solution000004.solution deleted file mode 100644 index 5e2caa751c..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_3_1-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 2, 2) -letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_3_1-solution000005.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_3_1-solution000005.solution deleted file mode 100644 index 1b4b5b08a6..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_3_1-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 2, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_3_1-solution000006.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_3_1-solution000006.solution deleted file mode 100644 index 621d5f6edc..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_3_1-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 1, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_3_1.eprime b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_3_1.eprime deleted file mode 100644 index 2dab8e6ab7..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_3_1.eprime +++ /dev/null @@ -1,70 +0,0 @@ -language ESSENCE' 1.0 - -find a_ExplicitWithRepetition_Flag: int(3) -find a_ExplicitWithRepetition_Values: matrix indexed by [int(1..3)] of int(1..2) -find a_MOccurrence: matrix indexed by [int(1..2)] of int(0..3) -find b_MOccurrence: matrix indexed by [int(1..2)] of int(0..3) -find b_ExplicitWithFlags_Flags: matrix indexed by [int(1..3)] of int(0..3) -find b_ExplicitWithFlags_Values: matrix indexed by [int(1..3)] of int(1..2) -branching on - [a_MOccurrence, a_ExplicitWithRepetition_Flag, a_ExplicitWithRepetition_Values, b_ExplicitWithFlags_Flags, - b_ExplicitWithFlags_Values, b_MOccurrence] -such that - or([sum([toInt(a_ExplicitWithRepetition_Values[q35] = a_ExplicitWithRepetition_Values[q36]) - | q35 : int(1..3), q35 <= 3]) - < b_MOccurrence[a_ExplicitWithRepetition_Values[q36]] - /\ - (and([a_ExplicitWithRepetition_Values[q30] < a_ExplicitWithRepetition_Values[q36] -> - sum([toInt(a_ExplicitWithRepetition_Values[q29] = a_ExplicitWithRepetition_Values[q30]) - | q29 : int(1..3), q29 <= 3]) - = b_MOccurrence[a_ExplicitWithRepetition_Values[q30]] - | q30 : int(1..3), q30 <= 3]) - /\ - and([q33 < a_ExplicitWithRepetition_Values[q36] -> - (b_MOccurrence[q33] > 0 /\ !or([a_ExplicitWithRepetition_Values[q32] = q33 | q32 : int(1..3), q32 <= 3]) - -> - sum([toInt(a_ExplicitWithRepetition_Values[q29] = q33) | q29 : int(1..3), q29 <= 3]) = - b_MOccurrence[q33]) - | q33 : int(1..2)])) - | q36 : int(1..3), q36 <= 3]) - \/ - or([b_MOccurrence[q39] > 0 /\ !or([a_ExplicitWithRepetition_Values[q38] = q39 | q38 : int(1..3), q38 <= 3]) /\ - (sum([toInt(a_ExplicitWithRepetition_Values[q35] = q39) | q35 : int(1..3), q35 <= 3]) < b_MOccurrence[q39] /\ - (and([a_ExplicitWithRepetition_Values[q30] < q39 -> - sum([toInt(a_ExplicitWithRepetition_Values[q29] = a_ExplicitWithRepetition_Values[q30]) - | q29 : int(1..3), q29 <= 3]) - = b_MOccurrence[a_ExplicitWithRepetition_Values[q30]] - | q30 : int(1..3), q30 <= 3]) - /\ - and([b_MOccurrence[q33] > 0 /\ !or([a_ExplicitWithRepetition_Values[q32] = q33 | q32 : int(1..3), q32 <= 3]) - -> - sum([toInt(a_ExplicitWithRepetition_Values[q29] = q33) | q29 : int(1..3), q29 <= 3]) = b_MOccurrence[q33] - | q33 : int(1..2), q33 < q39]))) - | q39 : int(1..2)]), - and([a_ExplicitWithRepetition_Values[q1] <= a_ExplicitWithRepetition_Values[q1 + 1] | q1 : int(1..2), q1 + 1 <= 3]), - 3 = sum([b_MOccurrence[q6] | q6 : int(1..2)]), - 3 = sum([a_MOccurrence[q7] | q7 : int(1..2)]), - and([a_MOccurrence[q20] > 0 -> - a_MOccurrence[q20] = sum([toInt(a_ExplicitWithRepetition_Values[q22] = q20) | q22 : int(1..3), q22 <= 3]) - | q20 : int(1..2)]), - and([a_MOccurrence[a_ExplicitWithRepetition_Values[q23]] = - sum([toInt(a_ExplicitWithRepetition_Values[q25] = a_ExplicitWithRepetition_Values[q23]) - | q25 : int(1..3), q25 <= 3]) - | q23 : int(1..3), q23 <= 3]), - and([b_ExplicitWithFlags_Flags[q8 + 1] > 0 -> b_ExplicitWithFlags_Values[q8] < b_ExplicitWithFlags_Values[q8 + 1] - | q8 : int(1..2)]), - and([b_ExplicitWithFlags_Flags[q9] = 0 -> b_ExplicitWithFlags_Values[q9] = 1 | q9 : int(1..3)]), - and([b_ExplicitWithFlags_Flags[q10 + 1] > 0 -> b_ExplicitWithFlags_Flags[q10] > 0 | q10 : int(1..2)]), - 3 = sum([b_ExplicitWithFlags_Flags[q12] | q12 : int(1..3)]), - and([b_ExplicitWithFlags_Flags[q15] > 0 -> - sum([toInt(b_ExplicitWithFlags_Values[q16] = b_ExplicitWithFlags_Values[q15]) * - catchUndef(b_ExplicitWithFlags_Flags[q16], 0) - | q16 : int(1..3)]) - = b_MOccurrence[b_ExplicitWithFlags_Values[q15]] - | q15 : int(1..3)]), - and([b_MOccurrence[q17] > 0 -> - sum([toInt(b_ExplicitWithFlags_Values[q18] = q17) * catchUndef(b_ExplicitWithFlags_Flags[q18], 0) - | q18 : int(1..3)]) - = b_MOccurrence[q17] - | q17 : int(1..2)]) - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_3_2-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_3_2-solution000001.solution deleted file mode 100644 index d56a0bbcdc..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_3_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_3_2-solution000002.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_3_2-solution000002.solution deleted file mode 100644 index ff56905e23..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_3_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_3_2-solution000003.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_3_2-solution000003.solution deleted file mode 100644 index 15472caf03..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_3_2-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 2, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_3_2-solution000004.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_3_2-solution000004.solution deleted file mode 100644 index 1b4b5b08a6..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_3_2-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 2, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_3_2-solution000005.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_3_2-solution000005.solution deleted file mode 100644 index 5e2caa751c..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_3_2-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 2, 2) -letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_3_2-solution000006.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_3_2-solution000006.solution deleted file mode 100644 index 621d5f6edc..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_3_2-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 1, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_3_2.eprime b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_3_2.eprime deleted file mode 100644 index f5bfe69d73..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_3_2.eprime +++ /dev/null @@ -1,62 +0,0 @@ -language ESSENCE' 1.0 - -find a_ExplicitWithRepetition_Flag: int(3) -find a_ExplicitWithRepetition_Values: matrix indexed by [int(1..3)] of int(1..2) -find a_MOccurrence: matrix indexed by [int(1..2)] of int(0..3) -find b_MOccurrence: matrix indexed by [int(1..2)] of int(0..3) -find b_ExplicitWithRepetition_Flag: int(3) -find b_ExplicitWithRepetition_Values: matrix indexed by [int(1..3)] of int(1..2) -branching on - [a_MOccurrence, a_ExplicitWithRepetition_Flag, a_ExplicitWithRepetition_Values, b_ExplicitWithRepetition_Flag, - b_ExplicitWithRepetition_Values, b_MOccurrence] -such that - or([sum([toInt(a_ExplicitWithRepetition_Values[q36] = a_ExplicitWithRepetition_Values[q37]) - | q36 : int(1..3), q36 <= 3]) - < b_MOccurrence[a_ExplicitWithRepetition_Values[q37]] - /\ - (and([a_ExplicitWithRepetition_Values[q31] < a_ExplicitWithRepetition_Values[q37] -> - sum([toInt(a_ExplicitWithRepetition_Values[q30] = a_ExplicitWithRepetition_Values[q31]) - | q30 : int(1..3), q30 <= 3]) - = b_MOccurrence[a_ExplicitWithRepetition_Values[q31]] - | q31 : int(1..3), q31 <= 3]) - /\ - and([q34 < a_ExplicitWithRepetition_Values[q37] -> - (b_MOccurrence[q34] > 0 /\ !or([a_ExplicitWithRepetition_Values[q33] = q34 | q33 : int(1..3), q33 <= 3]) - -> - sum([toInt(a_ExplicitWithRepetition_Values[q30] = q34) | q30 : int(1..3), q30 <= 3]) = - b_MOccurrence[q34]) - | q34 : int(1..2)])) - | q37 : int(1..3), q37 <= 3]) - \/ - or([b_MOccurrence[q40] > 0 /\ !or([a_ExplicitWithRepetition_Values[q39] = q40 | q39 : int(1..3), q39 <= 3]) /\ - (sum([toInt(a_ExplicitWithRepetition_Values[q36] = q40) | q36 : int(1..3), q36 <= 3]) < b_MOccurrence[q40] /\ - (and([a_ExplicitWithRepetition_Values[q31] < q40 -> - sum([toInt(a_ExplicitWithRepetition_Values[q30] = a_ExplicitWithRepetition_Values[q31]) - | q30 : int(1..3), q30 <= 3]) - = b_MOccurrence[a_ExplicitWithRepetition_Values[q31]] - | q31 : int(1..3), q31 <= 3]) - /\ - and([b_MOccurrence[q34] > 0 /\ !or([a_ExplicitWithRepetition_Values[q33] = q34 | q33 : int(1..3), q33 <= 3]) - -> - sum([toInt(a_ExplicitWithRepetition_Values[q30] = q34) | q30 : int(1..3), q30 <= 3]) = b_MOccurrence[q34] - | q34 : int(1..2), q34 < q40]))) - | q40 : int(1..2)]), - and([a_ExplicitWithRepetition_Values[q1] <= a_ExplicitWithRepetition_Values[q1 + 1] | q1 : int(1..2), q1 + 1 <= 3]), - 3 = sum([b_MOccurrence[q6] | q6 : int(1..2)]), - 3 = sum([a_MOccurrence[q7] | q7 : int(1..2)]), - and([a_MOccurrence[q21] > 0 -> - a_MOccurrence[q21] = sum([toInt(a_ExplicitWithRepetition_Values[q23] = q21) | q23 : int(1..3), q23 <= 3]) - | q21 : int(1..2)]), - and([a_MOccurrence[a_ExplicitWithRepetition_Values[q24]] = - sum([toInt(a_ExplicitWithRepetition_Values[q26] = a_ExplicitWithRepetition_Values[q24]) - | q26 : int(1..3), q26 <= 3]) - | q24 : int(1..3), q24 <= 3]), - and([b_ExplicitWithRepetition_Values[q8] <= b_ExplicitWithRepetition_Values[q8 + 1] | q8 : int(1..2), q8 + 1 <= 3]), - and([sum([toInt(b_ExplicitWithRepetition_Values[q16] = b_ExplicitWithRepetition_Values[q14]) - | q16 : int(1..3), q16 <= 3]) - = b_MOccurrence[b_ExplicitWithRepetition_Values[q14]] - | q14 : int(1..3), q14 <= 3]), - and([b_MOccurrence[q17] > 0 -> - sum([toInt(b_ExplicitWithRepetition_Values[q19] = q17) | q19 : int(1..3), q19 <= 3]) = b_MOccurrence[q17] - | q17 : int(1..2)]) - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_3_3-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_3_3-solution000001.solution deleted file mode 100644 index 15472caf03..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_3_3-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 2, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_3_3-solution000002.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_3_3-solution000002.solution deleted file mode 100644 index ff56905e23..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_3_3-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_3_3-solution000003.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_3_3-solution000003.solution deleted file mode 100644 index d56a0bbcdc..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_3_3-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_3_3-solution000004.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_3_3-solution000004.solution deleted file mode 100644 index 5e2caa751c..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_3_3-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 2, 2) -letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_3_3-solution000005.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_3_3-solution000005.solution deleted file mode 100644 index 1b4b5b08a6..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_3_3-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 2, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_3_3-solution000006.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_3_3-solution000006.solution deleted file mode 100644 index 621d5f6edc..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_3_3-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 1, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_3_3.eprime b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_3_3.eprime deleted file mode 100644 index f51cd8c9ab..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_3_3.eprime +++ /dev/null @@ -1,50 +0,0 @@ -language ESSENCE' 1.0 - -find a_ExplicitWithRepetition_Flag: int(3) -find a_ExplicitWithRepetition_Values: matrix indexed by [int(1..3)] of int(1..2) -find a_MOccurrence: matrix indexed by [int(1..2)] of int(0..3) -find b_MOccurrence: matrix indexed by [int(1..2)] of int(0..3) -branching on [a_MOccurrence, a_ExplicitWithRepetition_Flag, a_ExplicitWithRepetition_Values, b_MOccurrence] -such that - or([sum([toInt(a_ExplicitWithRepetition_Values[q24] = a_ExplicitWithRepetition_Values[q25]) - | q24 : int(1..3), q24 <= 3]) - < b_MOccurrence[a_ExplicitWithRepetition_Values[q25]] - /\ - (and([a_ExplicitWithRepetition_Values[q19] < a_ExplicitWithRepetition_Values[q25] -> - sum([toInt(a_ExplicitWithRepetition_Values[q18] = a_ExplicitWithRepetition_Values[q19]) - | q18 : int(1..3), q18 <= 3]) - = b_MOccurrence[a_ExplicitWithRepetition_Values[q19]] - | q19 : int(1..3), q19 <= 3]) - /\ - and([q22 < a_ExplicitWithRepetition_Values[q25] -> - (b_MOccurrence[q22] > 0 /\ !or([a_ExplicitWithRepetition_Values[q21] = q22 | q21 : int(1..3), q21 <= 3]) - -> - sum([toInt(a_ExplicitWithRepetition_Values[q18] = q22) | q18 : int(1..3), q18 <= 3]) = - b_MOccurrence[q22]) - | q22 : int(1..2)])) - | q25 : int(1..3), q25 <= 3]) - \/ - or([b_MOccurrence[q28] > 0 /\ !or([a_ExplicitWithRepetition_Values[q27] = q28 | q27 : int(1..3), q27 <= 3]) /\ - (sum([toInt(a_ExplicitWithRepetition_Values[q24] = q28) | q24 : int(1..3), q24 <= 3]) < b_MOccurrence[q28] /\ - (and([a_ExplicitWithRepetition_Values[q19] < q28 -> - sum([toInt(a_ExplicitWithRepetition_Values[q18] = a_ExplicitWithRepetition_Values[q19]) - | q18 : int(1..3), q18 <= 3]) - = b_MOccurrence[a_ExplicitWithRepetition_Values[q19]] - | q19 : int(1..3), q19 <= 3]) - /\ - and([b_MOccurrence[q22] > 0 /\ !or([a_ExplicitWithRepetition_Values[q21] = q22 | q21 : int(1..3), q21 <= 3]) - -> - sum([toInt(a_ExplicitWithRepetition_Values[q18] = q22) | q18 : int(1..3), q18 <= 3]) = b_MOccurrence[q22] - | q22 : int(1..2), q22 < q28]))) - | q28 : int(1..2)]), - and([a_ExplicitWithRepetition_Values[q1] <= a_ExplicitWithRepetition_Values[q1 + 1] | q1 : int(1..2), q1 + 1 <= 3]), - 3 = sum([b_MOccurrence[q6] | q6 : int(1..2)]), - 3 = sum([a_MOccurrence[q7] | q7 : int(1..2)]), - and([a_MOccurrence[q9] > 0 -> - a_MOccurrence[q9] = sum([toInt(a_ExplicitWithRepetition_Values[q11] = q9) | q11 : int(1..3), q11 <= 3]) - | q9 : int(1..2)]), - and([a_MOccurrence[a_ExplicitWithRepetition_Values[q12]] = - sum([toInt(a_ExplicitWithRepetition_Values[q14] = a_ExplicitWithRepetition_Values[q12]) - | q14 : int(1..3), q14 <= 3]) - | q12 : int(1..3), q12 <= 3]) - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_1_1-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_1_1-solution000001.solution deleted file mode 100644 index 5e2caa751c..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_1_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 2, 2) -letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_1_1-solution000002.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_1_1-solution000002.solution deleted file mode 100644 index 1b4b5b08a6..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_1_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 2, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_1_1-solution000003.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_1_1-solution000003.solution deleted file mode 100644 index 621d5f6edc..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_1_1-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 1, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_1_1-solution000004.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_1_1-solution000004.solution deleted file mode 100644 index 15472caf03..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_1_1-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 2, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_1_1-solution000005.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_1_1-solution000005.solution deleted file mode 100644 index ff56905e23..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_1_1-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_1_1-solution000006.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_1_1-solution000006.solution deleted file mode 100644 index d56a0bbcdc..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_1_1-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_1_1.eprime b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_1_1.eprime deleted file mode 100644 index 39a657e8e7..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_1_1.eprime +++ /dev/null @@ -1,83 +0,0 @@ -language ESSENCE' 1.0 - -find a_MOccurrence: matrix indexed by [int(1..2)] of int(0..3) -find a_ExplicitWithFlags_Flags: matrix indexed by [int(1..3)] of int(0..3) -find a_ExplicitWithFlags_Values: matrix indexed by [int(1..3)] of int(1..2) -find b_ExplicitWithFlags_Flags: matrix indexed by [int(1..3)] of int(0..3) -find b_ExplicitWithFlags_Values: matrix indexed by [int(1..3)] of int(1..2) -branching on - [a_ExplicitWithFlags_Flags, a_ExplicitWithFlags_Values, a_MOccurrence, b_ExplicitWithFlags_Flags, - b_ExplicitWithFlags_Values] -such that - or([a_MOccurrence[q29] > 0 /\ - (a_MOccurrence[q29] < - sum([toInt(b_ExplicitWithFlags_Values[q21] = q29) * catchUndef(b_ExplicitWithFlags_Flags[q21], 0) - | q21 : int(1..3)]) - /\ - (and([a_MOccurrence[q25] > 0 -> - a_MOccurrence[q25] = - sum([toInt(b_ExplicitWithFlags_Values[q22] = q25) * catchUndef(b_ExplicitWithFlags_Flags[q22], 0) - | q22 : int(1..3)]) - | q25 : int(1..2), q25 < q29]) - /\ - and([and([b_ExplicitWithFlags_Flags[q26] > 0, - !or([a_MOccurrence[q24] > 0 /\ q24 = b_ExplicitWithFlags_Values[q26] | q24 : int(1..2)]), - b_ExplicitWithFlags_Values[q26] < q29; - int(1..3)]) - -> - a_MOccurrence[b_ExplicitWithFlags_Values[q26]] = - sum([toInt(b_ExplicitWithFlags_Values[q22] = b_ExplicitWithFlags_Values[q26]) * - catchUndef(b_ExplicitWithFlags_Flags[q22], 0) - | q22 : int(1..3)]) - | q26 : int(1..3)]))) - | q29 : int(1..2)]) - \/ - or([b_ExplicitWithFlags_Flags[q30] > 0 /\ - !or([a_MOccurrence[q28] > 0 /\ q28 = b_ExplicitWithFlags_Values[q30] | q28 : int(1..2)]) - /\ - (a_MOccurrence[b_ExplicitWithFlags_Values[q30]] < - sum([toInt(b_ExplicitWithFlags_Values[q21] = b_ExplicitWithFlags_Values[q30]) * - catchUndef(b_ExplicitWithFlags_Flags[q21], 0) - | q21 : int(1..3)]) - /\ - (and([q25 < b_ExplicitWithFlags_Values[q30] -> - (a_MOccurrence[q25] > 0 -> - a_MOccurrence[q25] = - sum([toInt(b_ExplicitWithFlags_Values[q22] = q25) * catchUndef(b_ExplicitWithFlags_Flags[q22], 0) - | q22 : int(1..3)])) - | q25 : int(1..2)]) - /\ - and([and([b_ExplicitWithFlags_Flags[q26] > 0, - !or([a_MOccurrence[q24] > 0 /\ q24 = b_ExplicitWithFlags_Values[q26] | q24 : int(1..2)]), - b_ExplicitWithFlags_Values[q26] < b_ExplicitWithFlags_Values[q30]; - int(1..3)]) - -> - a_MOccurrence[b_ExplicitWithFlags_Values[q26]] = - sum([toInt(b_ExplicitWithFlags_Values[q22] = b_ExplicitWithFlags_Values[q26]) * - catchUndef(b_ExplicitWithFlags_Flags[q22], 0) - | q22 : int(1..3)]) - | q26 : int(1..3)]))) - | q30 : int(1..3)]), - 3 = sum([a_MOccurrence[q1] | q1 : int(1..2)]), - and([b_ExplicitWithFlags_Flags[q2 + 1] > 0 -> b_ExplicitWithFlags_Values[q2] < b_ExplicitWithFlags_Values[q2 + 1] - | q2 : int(1..2)]), - and([b_ExplicitWithFlags_Flags[q3] = 0 -> b_ExplicitWithFlags_Values[q3] = 1 | q3 : int(1..3)]), - and([b_ExplicitWithFlags_Flags[q4 + 1] > 0 -> b_ExplicitWithFlags_Flags[q4] > 0 | q4 : int(1..2)]), - 3 = sum([b_ExplicitWithFlags_Flags[q6] | q6 : int(1..3)]), - and([a_ExplicitWithFlags_Flags[q8 + 1] > 0 -> a_ExplicitWithFlags_Values[q8] < a_ExplicitWithFlags_Values[q8 + 1] - | q8 : int(1..2)]), - and([a_ExplicitWithFlags_Flags[q9] = 0 -> a_ExplicitWithFlags_Values[q9] = 1 | q9 : int(1..3)]), - and([a_ExplicitWithFlags_Flags[q10 + 1] > 0 -> a_ExplicitWithFlags_Flags[q10] > 0 | q10 : int(1..2)]), - 3 = sum([a_ExplicitWithFlags_Flags[q12] | q12 : int(1..3)]), - and([a_ExplicitWithFlags_Flags[q15] > 0 -> - sum([toInt(a_ExplicitWithFlags_Values[q16] = a_ExplicitWithFlags_Values[q15]) * - catchUndef(a_ExplicitWithFlags_Flags[q16], 0) - | q16 : int(1..3)]) - = a_MOccurrence[a_ExplicitWithFlags_Values[q15]] - | q15 : int(1..3)]), - and([a_MOccurrence[q17] > 0 -> - sum([toInt(a_ExplicitWithFlags_Values[q18] = q17) * catchUndef(a_ExplicitWithFlags_Flags[q18], 0) - | q18 : int(1..3)]) - = a_MOccurrence[q17] - | q17 : int(1..2)]) - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_1_2-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_1_2-solution000001.solution deleted file mode 100644 index 1b4b5b08a6..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_1_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 2, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_1_2-solution000002.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_1_2-solution000002.solution deleted file mode 100644 index 5e2caa751c..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_1_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 2, 2) -letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_1_2-solution000003.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_1_2-solution000003.solution deleted file mode 100644 index 621d5f6edc..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_1_2-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 1, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_1_2-solution000004.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_1_2-solution000004.solution deleted file mode 100644 index d56a0bbcdc..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_1_2-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_1_2-solution000005.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_1_2-solution000005.solution deleted file mode 100644 index ff56905e23..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_1_2-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_1_2-solution000006.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_1_2-solution000006.solution deleted file mode 100644 index 15472caf03..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_1_2-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 2, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_1_2.eprime b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_1_2.eprime deleted file mode 100644 index 69fb1a7c7e..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_1_2.eprime +++ /dev/null @@ -1,102 +0,0 @@ -language ESSENCE' 1.0 - -find a_MOccurrence: matrix indexed by [int(1..2)] of int(0..3) -find a_ExplicitWithFlags_Flags: matrix indexed by [int(1..3)] of int(0..3) -find a_ExplicitWithFlags_Values: matrix indexed by [int(1..3)] of int(1..2) -find b_ExplicitWithFlags_Flags: matrix indexed by [int(1..3)] of int(0..3) -find b_ExplicitWithFlags_Values: matrix indexed by [int(1..3)] of int(1..2) -find b_ExplicitWithRepetition_Flag: int(3) -find b_ExplicitWithRepetition_Values: matrix indexed by [int(1..3)] of int(1..2) -branching on - [a_ExplicitWithFlags_Flags, a_ExplicitWithFlags_Values, a_MOccurrence, b_ExplicitWithRepetition_Flag, - b_ExplicitWithRepetition_Values, b_ExplicitWithFlags_Flags, b_ExplicitWithFlags_Values] -such that - or([a_MOccurrence[q43] > 0 /\ - (a_MOccurrence[q43] < - sum([toInt(b_ExplicitWithFlags_Values[q35] = q43) * catchUndef(b_ExplicitWithFlags_Flags[q35], 0) - | q35 : int(1..3)]) - /\ - (and([a_MOccurrence[q39] > 0 -> - a_MOccurrence[q39] = - sum([toInt(b_ExplicitWithFlags_Values[q36] = q39) * catchUndef(b_ExplicitWithFlags_Flags[q36], 0) - | q36 : int(1..3)]) - | q39 : int(1..2), q39 < q43]) - /\ - and([and([b_ExplicitWithFlags_Flags[q40] > 0, - !or([a_MOccurrence[q38] > 0 /\ q38 = b_ExplicitWithFlags_Values[q40] | q38 : int(1..2)]), - b_ExplicitWithFlags_Values[q40] < q43; - int(1..3)]) - -> - a_MOccurrence[b_ExplicitWithFlags_Values[q40]] = - sum([toInt(b_ExplicitWithFlags_Values[q36] = b_ExplicitWithFlags_Values[q40]) * - catchUndef(b_ExplicitWithFlags_Flags[q36], 0) - | q36 : int(1..3)]) - | q40 : int(1..3)]))) - | q43 : int(1..2)]) - \/ - or([b_ExplicitWithFlags_Flags[q44] > 0 /\ - !or([a_MOccurrence[q42] > 0 /\ q42 = b_ExplicitWithFlags_Values[q44] | q42 : int(1..2)]) - /\ - (a_MOccurrence[b_ExplicitWithFlags_Values[q44]] < - sum([toInt(b_ExplicitWithFlags_Values[q35] = b_ExplicitWithFlags_Values[q44]) * - catchUndef(b_ExplicitWithFlags_Flags[q35], 0) - | q35 : int(1..3)]) - /\ - (and([q39 < b_ExplicitWithFlags_Values[q44] -> - (a_MOccurrence[q39] > 0 -> - a_MOccurrence[q39] = - sum([toInt(b_ExplicitWithFlags_Values[q36] = q39) * catchUndef(b_ExplicitWithFlags_Flags[q36], 0) - | q36 : int(1..3)])) - | q39 : int(1..2)]) - /\ - and([and([b_ExplicitWithFlags_Flags[q40] > 0, - !or([a_MOccurrence[q38] > 0 /\ q38 = b_ExplicitWithFlags_Values[q40] | q38 : int(1..2)]), - b_ExplicitWithFlags_Values[q40] < b_ExplicitWithFlags_Values[q44]; - int(1..3)]) - -> - a_MOccurrence[b_ExplicitWithFlags_Values[q40]] = - sum([toInt(b_ExplicitWithFlags_Values[q36] = b_ExplicitWithFlags_Values[q40]) * - catchUndef(b_ExplicitWithFlags_Flags[q36], 0) - | q36 : int(1..3)]) - | q40 : int(1..3)]))) - | q44 : int(1..3)]), - 3 = sum([a_MOccurrence[q1] | q1 : int(1..2)]), - and([b_ExplicitWithFlags_Flags[q2 + 1] > 0 -> b_ExplicitWithFlags_Values[q2] < b_ExplicitWithFlags_Values[q2 + 1] - | q2 : int(1..2)]), - and([b_ExplicitWithFlags_Flags[q3] = 0 -> b_ExplicitWithFlags_Values[q3] = 1 | q3 : int(1..3)]), - and([b_ExplicitWithFlags_Flags[q4 + 1] > 0 -> b_ExplicitWithFlags_Flags[q4] > 0 | q4 : int(1..2)]), - 3 = sum([b_ExplicitWithFlags_Flags[q6] | q6 : int(1..3)]), - and([a_ExplicitWithFlags_Flags[q8 + 1] > 0 -> a_ExplicitWithFlags_Values[q8] < a_ExplicitWithFlags_Values[q8 + 1] - | q8 : int(1..2)]), - and([a_ExplicitWithFlags_Flags[q9] = 0 -> a_ExplicitWithFlags_Values[q9] = 1 | q9 : int(1..3)]), - and([a_ExplicitWithFlags_Flags[q10 + 1] > 0 -> a_ExplicitWithFlags_Flags[q10] > 0 | q10 : int(1..2)]), - 3 = sum([a_ExplicitWithFlags_Flags[q12] | q12 : int(1..3)]), - and([a_ExplicitWithFlags_Flags[q15] > 0 -> - sum([toInt(a_ExplicitWithFlags_Values[q16] = a_ExplicitWithFlags_Values[q15]) * - catchUndef(a_ExplicitWithFlags_Flags[q16], 0) - | q16 : int(1..3)]) - = a_MOccurrence[a_ExplicitWithFlags_Values[q15]] - | q15 : int(1..3)]), - and([a_MOccurrence[q17] > 0 -> - sum([toInt(a_ExplicitWithFlags_Values[q18] = q17) * catchUndef(a_ExplicitWithFlags_Flags[q18], 0) - | q18 : int(1..3)]) - = a_MOccurrence[q17] - | q17 : int(1..2)]), - and([b_ExplicitWithRepetition_Values[q19] <= b_ExplicitWithRepetition_Values[q19 + 1] - | q19 : int(1..2), q19 + 1 <= 3]), - and([sum([toInt(b_ExplicitWithRepetition_Values[q28] = b_ExplicitWithRepetition_Values[q25]) - | q28 : int(1..3), q28 <= 3]) - = - sum([toInt(b_ExplicitWithFlags_Values[q26] = b_ExplicitWithRepetition_Values[q25]) * - catchUndef(b_ExplicitWithFlags_Flags[q26], 0) - | q26 : int(1..3)]) - | q25 : int(1..3), q25 <= 3]), - and([b_ExplicitWithFlags_Flags[q29] > 0 -> - sum([toInt(b_ExplicitWithRepetition_Values[q32] = b_ExplicitWithFlags_Values[q29]) - | q32 : int(1..3), q32 <= 3]) - = - sum([toInt(b_ExplicitWithFlags_Values[q30] = b_ExplicitWithFlags_Values[q29]) * - catchUndef(b_ExplicitWithFlags_Flags[q30], 0) - | q30 : int(1..3)]) - | q29 : int(1..3)]) - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_1_3-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_1_3-solution000001.solution deleted file mode 100644 index 5e2caa751c..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_1_3-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 2, 2) -letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_1_3-solution000002.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_1_3-solution000002.solution deleted file mode 100644 index 1b4b5b08a6..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_1_3-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 2, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_1_3-solution000003.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_1_3-solution000003.solution deleted file mode 100644 index 621d5f6edc..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_1_3-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 1, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_1_3-solution000004.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_1_3-solution000004.solution deleted file mode 100644 index 15472caf03..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_1_3-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 2, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_1_3-solution000005.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_1_3-solution000005.solution deleted file mode 100644 index ff56905e23..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_1_3-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_1_3-solution000006.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_1_3-solution000006.solution deleted file mode 100644 index d56a0bbcdc..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_1_3-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_1_3.eprime b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_1_3.eprime deleted file mode 100644 index 845b529dc6..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_1_3.eprime +++ /dev/null @@ -1,96 +0,0 @@ -language ESSENCE' 1.0 - -find a_MOccurrence: matrix indexed by [int(1..2)] of int(0..3) -find a_ExplicitWithFlags_Flags: matrix indexed by [int(1..3)] of int(0..3) -find a_ExplicitWithFlags_Values: matrix indexed by [int(1..3)] of int(1..2) -find b_ExplicitWithFlags_Flags: matrix indexed by [int(1..3)] of int(0..3) -find b_ExplicitWithFlags_Values: matrix indexed by [int(1..3)] of int(1..2) -find b_MOccurrence: matrix indexed by [int(1..2)] of int(0..3) -branching on - [a_ExplicitWithFlags_Flags, a_ExplicitWithFlags_Values, a_MOccurrence, b_MOccurrence, b_ExplicitWithFlags_Flags, - b_ExplicitWithFlags_Values] -such that - or([a_MOccurrence[q35] > 0 /\ - (a_MOccurrence[q35] < - sum([toInt(b_ExplicitWithFlags_Values[q27] = q35) * catchUndef(b_ExplicitWithFlags_Flags[q27], 0) - | q27 : int(1..3)]) - /\ - (and([a_MOccurrence[q31] > 0 -> - a_MOccurrence[q31] = - sum([toInt(b_ExplicitWithFlags_Values[q28] = q31) * catchUndef(b_ExplicitWithFlags_Flags[q28], 0) - | q28 : int(1..3)]) - | q31 : int(1..2), q31 < q35]) - /\ - and([and([b_ExplicitWithFlags_Flags[q32] > 0, - !or([a_MOccurrence[q30] > 0 /\ q30 = b_ExplicitWithFlags_Values[q32] | q30 : int(1..2)]), - b_ExplicitWithFlags_Values[q32] < q35; - int(1..3)]) - -> - a_MOccurrence[b_ExplicitWithFlags_Values[q32]] = - sum([toInt(b_ExplicitWithFlags_Values[q28] = b_ExplicitWithFlags_Values[q32]) * - catchUndef(b_ExplicitWithFlags_Flags[q28], 0) - | q28 : int(1..3)]) - | q32 : int(1..3)]))) - | q35 : int(1..2)]) - \/ - or([b_ExplicitWithFlags_Flags[q36] > 0 /\ - !or([a_MOccurrence[q34] > 0 /\ q34 = b_ExplicitWithFlags_Values[q36] | q34 : int(1..2)]) - /\ - (a_MOccurrence[b_ExplicitWithFlags_Values[q36]] < - sum([toInt(b_ExplicitWithFlags_Values[q27] = b_ExplicitWithFlags_Values[q36]) * - catchUndef(b_ExplicitWithFlags_Flags[q27], 0) - | q27 : int(1..3)]) - /\ - (and([q31 < b_ExplicitWithFlags_Values[q36] -> - (a_MOccurrence[q31] > 0 -> - a_MOccurrence[q31] = - sum([toInt(b_ExplicitWithFlags_Values[q28] = q31) * catchUndef(b_ExplicitWithFlags_Flags[q28], 0) - | q28 : int(1..3)])) - | q31 : int(1..2)]) - /\ - and([and([b_ExplicitWithFlags_Flags[q32] > 0, - !or([a_MOccurrence[q30] > 0 /\ q30 = b_ExplicitWithFlags_Values[q32] | q30 : int(1..2)]), - b_ExplicitWithFlags_Values[q32] < b_ExplicitWithFlags_Values[q36]; - int(1..3)]) - -> - a_MOccurrence[b_ExplicitWithFlags_Values[q32]] = - sum([toInt(b_ExplicitWithFlags_Values[q28] = b_ExplicitWithFlags_Values[q32]) * - catchUndef(b_ExplicitWithFlags_Flags[q28], 0) - | q28 : int(1..3)]) - | q32 : int(1..3)]))) - | q36 : int(1..3)]), - 3 = sum([a_MOccurrence[q1] | q1 : int(1..2)]), - and([b_ExplicitWithFlags_Flags[q2 + 1] > 0 -> b_ExplicitWithFlags_Values[q2] < b_ExplicitWithFlags_Values[q2 + 1] - | q2 : int(1..2)]), - and([b_ExplicitWithFlags_Flags[q3] = 0 -> b_ExplicitWithFlags_Values[q3] = 1 | q3 : int(1..3)]), - and([b_ExplicitWithFlags_Flags[q4 + 1] > 0 -> b_ExplicitWithFlags_Flags[q4] > 0 | q4 : int(1..2)]), - 3 = sum([b_ExplicitWithFlags_Flags[q6] | q6 : int(1..3)]), - and([a_ExplicitWithFlags_Flags[q8 + 1] > 0 -> a_ExplicitWithFlags_Values[q8] < a_ExplicitWithFlags_Values[q8 + 1] - | q8 : int(1..2)]), - and([a_ExplicitWithFlags_Flags[q9] = 0 -> a_ExplicitWithFlags_Values[q9] = 1 | q9 : int(1..3)]), - and([a_ExplicitWithFlags_Flags[q10 + 1] > 0 -> a_ExplicitWithFlags_Flags[q10] > 0 | q10 : int(1..2)]), - 3 = sum([a_ExplicitWithFlags_Flags[q12] | q12 : int(1..3)]), - and([a_ExplicitWithFlags_Flags[q15] > 0 -> - sum([toInt(a_ExplicitWithFlags_Values[q16] = a_ExplicitWithFlags_Values[q15]) * - catchUndef(a_ExplicitWithFlags_Flags[q16], 0) - | q16 : int(1..3)]) - = a_MOccurrence[a_ExplicitWithFlags_Values[q15]] - | q15 : int(1..3)]), - and([a_MOccurrence[q17] > 0 -> - sum([toInt(a_ExplicitWithFlags_Values[q18] = q17) * catchUndef(a_ExplicitWithFlags_Flags[q18], 0) - | q18 : int(1..3)]) - = a_MOccurrence[q17] - | q17 : int(1..2)]), - 3 = sum([b_MOccurrence[q19] | q19 : int(1..2)]), - and([b_MOccurrence[q21] > 0 -> - b_MOccurrence[q21] = - sum([toInt(b_ExplicitWithFlags_Values[q22] = q21) * catchUndef(b_ExplicitWithFlags_Flags[q22], 0) - | q22 : int(1..3)]) - | q21 : int(1..2)]), - and([b_ExplicitWithFlags_Flags[q23] > 0 -> - b_MOccurrence[b_ExplicitWithFlags_Values[q23]] = - sum([toInt(b_ExplicitWithFlags_Values[q24] = b_ExplicitWithFlags_Values[q23]) * - catchUndef(b_ExplicitWithFlags_Flags[q24], 0) - | q24 : int(1..3)]) - | q23 : int(1..3)]) - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_2_1-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_2_1-solution000001.solution deleted file mode 100644 index 621d5f6edc..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_2_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 1, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_2_1-solution000002.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_2_1-solution000002.solution deleted file mode 100644 index 5e2caa751c..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_2_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 2, 2) -letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_2_1-solution000003.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_2_1-solution000003.solution deleted file mode 100644 index 1b4b5b08a6..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_2_1-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 2, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_2_1-solution000004.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_2_1-solution000004.solution deleted file mode 100644 index 15472caf03..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_2_1-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 2, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_2_1-solution000005.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_2_1-solution000005.solution deleted file mode 100644 index ff56905e23..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_2_1-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_2_1-solution000006.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_2_1-solution000006.solution deleted file mode 100644 index d56a0bbcdc..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_2_1-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_2_1.eprime b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_2_1.eprime deleted file mode 100644 index 9f822488d7..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_2_1.eprime +++ /dev/null @@ -1,75 +0,0 @@ -language ESSENCE' 1.0 - -find a_MOccurrence: matrix indexed by [int(1..2)] of int(0..3) -find a_ExplicitWithRepetition_Flag: int(3) -find a_ExplicitWithRepetition_Values: matrix indexed by [int(1..3)] of int(1..2) -find b_ExplicitWithFlags_Flags: matrix indexed by [int(1..3)] of int(0..3) -find b_ExplicitWithFlags_Values: matrix indexed by [int(1..3)] of int(1..2) -branching on - [a_ExplicitWithRepetition_Flag, a_ExplicitWithRepetition_Values, a_MOccurrence, b_ExplicitWithFlags_Flags, - b_ExplicitWithFlags_Values] -such that - or([a_MOccurrence[q30] > 0 /\ - (a_MOccurrence[q30] < - sum([toInt(b_ExplicitWithFlags_Values[q22] = q30) * catchUndef(b_ExplicitWithFlags_Flags[q22], 0) - | q22 : int(1..3)]) - /\ - (and([a_MOccurrence[q26] > 0 -> - a_MOccurrence[q26] = - sum([toInt(b_ExplicitWithFlags_Values[q23] = q26) * catchUndef(b_ExplicitWithFlags_Flags[q23], 0) - | q23 : int(1..3)]) - | q26 : int(1..2), q26 < q30]) - /\ - and([and([b_ExplicitWithFlags_Flags[q27] > 0, - !or([a_MOccurrence[q25] > 0 /\ q25 = b_ExplicitWithFlags_Values[q27] | q25 : int(1..2)]), - b_ExplicitWithFlags_Values[q27] < q30; - int(1..3)]) - -> - a_MOccurrence[b_ExplicitWithFlags_Values[q27]] = - sum([toInt(b_ExplicitWithFlags_Values[q23] = b_ExplicitWithFlags_Values[q27]) * - catchUndef(b_ExplicitWithFlags_Flags[q23], 0) - | q23 : int(1..3)]) - | q27 : int(1..3)]))) - | q30 : int(1..2)]) - \/ - or([b_ExplicitWithFlags_Flags[q31] > 0 /\ - !or([a_MOccurrence[q29] > 0 /\ q29 = b_ExplicitWithFlags_Values[q31] | q29 : int(1..2)]) - /\ - (a_MOccurrence[b_ExplicitWithFlags_Values[q31]] < - sum([toInt(b_ExplicitWithFlags_Values[q22] = b_ExplicitWithFlags_Values[q31]) * - catchUndef(b_ExplicitWithFlags_Flags[q22], 0) - | q22 : int(1..3)]) - /\ - (and([q26 < b_ExplicitWithFlags_Values[q31] -> - (a_MOccurrence[q26] > 0 -> - a_MOccurrence[q26] = - sum([toInt(b_ExplicitWithFlags_Values[q23] = q26) * catchUndef(b_ExplicitWithFlags_Flags[q23], 0) - | q23 : int(1..3)])) - | q26 : int(1..2)]) - /\ - and([and([b_ExplicitWithFlags_Flags[q27] > 0, - !or([a_MOccurrence[q25] > 0 /\ q25 = b_ExplicitWithFlags_Values[q27] | q25 : int(1..2)]), - b_ExplicitWithFlags_Values[q27] < b_ExplicitWithFlags_Values[q31]; - int(1..3)]) - -> - a_MOccurrence[b_ExplicitWithFlags_Values[q27]] = - sum([toInt(b_ExplicitWithFlags_Values[q23] = b_ExplicitWithFlags_Values[q27]) * - catchUndef(b_ExplicitWithFlags_Flags[q23], 0) - | q23 : int(1..3)]) - | q27 : int(1..3)]))) - | q31 : int(1..3)]), - 3 = sum([a_MOccurrence[q1] | q1 : int(1..2)]), - and([b_ExplicitWithFlags_Flags[q2 + 1] > 0 -> b_ExplicitWithFlags_Values[q2] < b_ExplicitWithFlags_Values[q2 + 1] - | q2 : int(1..2)]), - and([b_ExplicitWithFlags_Flags[q3] = 0 -> b_ExplicitWithFlags_Values[q3] = 1 | q3 : int(1..3)]), - and([b_ExplicitWithFlags_Flags[q4 + 1] > 0 -> b_ExplicitWithFlags_Flags[q4] > 0 | q4 : int(1..2)]), - 3 = sum([b_ExplicitWithFlags_Flags[q6] | q6 : int(1..3)]), - and([a_ExplicitWithRepetition_Values[q8] <= a_ExplicitWithRepetition_Values[q8 + 1] | q8 : int(1..2), q8 + 1 <= 3]), - and([sum([toInt(a_ExplicitWithRepetition_Values[q16] = a_ExplicitWithRepetition_Values[q14]) - | q16 : int(1..3), q16 <= 3]) - = a_MOccurrence[a_ExplicitWithRepetition_Values[q14]] - | q14 : int(1..3), q14 <= 3]), - and([a_MOccurrence[q17] > 0 -> - sum([toInt(a_ExplicitWithRepetition_Values[q19] = q17) | q19 : int(1..3), q19 <= 3]) = a_MOccurrence[q17] - | q17 : int(1..2)]) - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_2_2-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_2_2-solution000001.solution deleted file mode 100644 index 621d5f6edc..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_2_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 1, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_2_2-solution000002.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_2_2-solution000002.solution deleted file mode 100644 index 1b4b5b08a6..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_2_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 2, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_2_2-solution000003.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_2_2-solution000003.solution deleted file mode 100644 index 5e2caa751c..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_2_2-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 2, 2) -letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_2_2-solution000004.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_2_2-solution000004.solution deleted file mode 100644 index d56a0bbcdc..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_2_2-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_2_2-solution000005.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_2_2-solution000005.solution deleted file mode 100644 index ff56905e23..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_2_2-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_2_2-solution000006.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_2_2-solution000006.solution deleted file mode 100644 index 15472caf03..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_2_2-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 2, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_2_2.eprime b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_2_2.eprime deleted file mode 100644 index c806744113..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_2_2.eprime +++ /dev/null @@ -1,94 +0,0 @@ -language ESSENCE' 1.0 - -find a_MOccurrence: matrix indexed by [int(1..2)] of int(0..3) -find a_ExplicitWithRepetition_Flag: int(3) -find a_ExplicitWithRepetition_Values: matrix indexed by [int(1..3)] of int(1..2) -find b_ExplicitWithFlags_Flags: matrix indexed by [int(1..3)] of int(0..3) -find b_ExplicitWithFlags_Values: matrix indexed by [int(1..3)] of int(1..2) -find b_ExplicitWithRepetition_Flag: int(3) -find b_ExplicitWithRepetition_Values: matrix indexed by [int(1..3)] of int(1..2) -branching on - [a_ExplicitWithRepetition_Flag, a_ExplicitWithRepetition_Values, a_MOccurrence, b_ExplicitWithRepetition_Flag, - b_ExplicitWithRepetition_Values, b_ExplicitWithFlags_Flags, b_ExplicitWithFlags_Values] -such that - or([a_MOccurrence[q44] > 0 /\ - (a_MOccurrence[q44] < - sum([toInt(b_ExplicitWithFlags_Values[q36] = q44) * catchUndef(b_ExplicitWithFlags_Flags[q36], 0) - | q36 : int(1..3)]) - /\ - (and([a_MOccurrence[q40] > 0 -> - a_MOccurrence[q40] = - sum([toInt(b_ExplicitWithFlags_Values[q37] = q40) * catchUndef(b_ExplicitWithFlags_Flags[q37], 0) - | q37 : int(1..3)]) - | q40 : int(1..2), q40 < q44]) - /\ - and([and([b_ExplicitWithFlags_Flags[q41] > 0, - !or([a_MOccurrence[q39] > 0 /\ q39 = b_ExplicitWithFlags_Values[q41] | q39 : int(1..2)]), - b_ExplicitWithFlags_Values[q41] < q44; - int(1..3)]) - -> - a_MOccurrence[b_ExplicitWithFlags_Values[q41]] = - sum([toInt(b_ExplicitWithFlags_Values[q37] = b_ExplicitWithFlags_Values[q41]) * - catchUndef(b_ExplicitWithFlags_Flags[q37], 0) - | q37 : int(1..3)]) - | q41 : int(1..3)]))) - | q44 : int(1..2)]) - \/ - or([b_ExplicitWithFlags_Flags[q45] > 0 /\ - !or([a_MOccurrence[q43] > 0 /\ q43 = b_ExplicitWithFlags_Values[q45] | q43 : int(1..2)]) - /\ - (a_MOccurrence[b_ExplicitWithFlags_Values[q45]] < - sum([toInt(b_ExplicitWithFlags_Values[q36] = b_ExplicitWithFlags_Values[q45]) * - catchUndef(b_ExplicitWithFlags_Flags[q36], 0) - | q36 : int(1..3)]) - /\ - (and([q40 < b_ExplicitWithFlags_Values[q45] -> - (a_MOccurrence[q40] > 0 -> - a_MOccurrence[q40] = - sum([toInt(b_ExplicitWithFlags_Values[q37] = q40) * catchUndef(b_ExplicitWithFlags_Flags[q37], 0) - | q37 : int(1..3)])) - | q40 : int(1..2)]) - /\ - and([and([b_ExplicitWithFlags_Flags[q41] > 0, - !or([a_MOccurrence[q39] > 0 /\ q39 = b_ExplicitWithFlags_Values[q41] | q39 : int(1..2)]), - b_ExplicitWithFlags_Values[q41] < b_ExplicitWithFlags_Values[q45]; - int(1..3)]) - -> - a_MOccurrence[b_ExplicitWithFlags_Values[q41]] = - sum([toInt(b_ExplicitWithFlags_Values[q37] = b_ExplicitWithFlags_Values[q41]) * - catchUndef(b_ExplicitWithFlags_Flags[q37], 0) - | q37 : int(1..3)]) - | q41 : int(1..3)]))) - | q45 : int(1..3)]), - 3 = sum([a_MOccurrence[q1] | q1 : int(1..2)]), - and([b_ExplicitWithFlags_Flags[q2 + 1] > 0 -> b_ExplicitWithFlags_Values[q2] < b_ExplicitWithFlags_Values[q2 + 1] - | q2 : int(1..2)]), - and([b_ExplicitWithFlags_Flags[q3] = 0 -> b_ExplicitWithFlags_Values[q3] = 1 | q3 : int(1..3)]), - and([b_ExplicitWithFlags_Flags[q4 + 1] > 0 -> b_ExplicitWithFlags_Flags[q4] > 0 | q4 : int(1..2)]), - 3 = sum([b_ExplicitWithFlags_Flags[q6] | q6 : int(1..3)]), - and([a_ExplicitWithRepetition_Values[q8] <= a_ExplicitWithRepetition_Values[q8 + 1] | q8 : int(1..2), q8 + 1 <= 3]), - and([sum([toInt(a_ExplicitWithRepetition_Values[q16] = a_ExplicitWithRepetition_Values[q14]) - | q16 : int(1..3), q16 <= 3]) - = a_MOccurrence[a_ExplicitWithRepetition_Values[q14]] - | q14 : int(1..3), q14 <= 3]), - and([a_MOccurrence[q17] > 0 -> - sum([toInt(a_ExplicitWithRepetition_Values[q19] = q17) | q19 : int(1..3), q19 <= 3]) = a_MOccurrence[q17] - | q17 : int(1..2)]), - and([b_ExplicitWithRepetition_Values[q20] <= b_ExplicitWithRepetition_Values[q20 + 1] - | q20 : int(1..2), q20 + 1 <= 3]), - and([sum([toInt(b_ExplicitWithRepetition_Values[q29] = b_ExplicitWithRepetition_Values[q26]) - | q29 : int(1..3), q29 <= 3]) - = - sum([toInt(b_ExplicitWithFlags_Values[q27] = b_ExplicitWithRepetition_Values[q26]) * - catchUndef(b_ExplicitWithFlags_Flags[q27], 0) - | q27 : int(1..3)]) - | q26 : int(1..3), q26 <= 3]), - and([b_ExplicitWithFlags_Flags[q30] > 0 -> - sum([toInt(b_ExplicitWithRepetition_Values[q33] = b_ExplicitWithFlags_Values[q30]) - | q33 : int(1..3), q33 <= 3]) - = - sum([toInt(b_ExplicitWithFlags_Values[q31] = b_ExplicitWithFlags_Values[q30]) * - catchUndef(b_ExplicitWithFlags_Flags[q31], 0) - | q31 : int(1..3)]) - | q30 : int(1..3)]) - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_2_3-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_2_3-solution000001.solution deleted file mode 100644 index 621d5f6edc..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_2_3-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 1, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_2_3-solution000002.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_2_3-solution000002.solution deleted file mode 100644 index 5e2caa751c..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_2_3-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 2, 2) -letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_2_3-solution000003.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_2_3-solution000003.solution deleted file mode 100644 index 1b4b5b08a6..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_2_3-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 2, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_2_3-solution000004.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_2_3-solution000004.solution deleted file mode 100644 index 15472caf03..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_2_3-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 2, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_2_3-solution000005.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_2_3-solution000005.solution deleted file mode 100644 index ff56905e23..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_2_3-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_2_3-solution000006.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_2_3-solution000006.solution deleted file mode 100644 index d56a0bbcdc..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_2_3-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_2_3.eprime b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_2_3.eprime deleted file mode 100644 index f61c556af3..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_2_3.eprime +++ /dev/null @@ -1,88 +0,0 @@ -language ESSENCE' 1.0 - -find a_MOccurrence: matrix indexed by [int(1..2)] of int(0..3) -find a_ExplicitWithRepetition_Flag: int(3) -find a_ExplicitWithRepetition_Values: matrix indexed by [int(1..3)] of int(1..2) -find b_ExplicitWithFlags_Flags: matrix indexed by [int(1..3)] of int(0..3) -find b_ExplicitWithFlags_Values: matrix indexed by [int(1..3)] of int(1..2) -find b_MOccurrence: matrix indexed by [int(1..2)] of int(0..3) -branching on - [a_ExplicitWithRepetition_Flag, a_ExplicitWithRepetition_Values, a_MOccurrence, b_MOccurrence, - b_ExplicitWithFlags_Flags, b_ExplicitWithFlags_Values] -such that - or([a_MOccurrence[q36] > 0 /\ - (a_MOccurrence[q36] < - sum([toInt(b_ExplicitWithFlags_Values[q28] = q36) * catchUndef(b_ExplicitWithFlags_Flags[q28], 0) - | q28 : int(1..3)]) - /\ - (and([a_MOccurrence[q32] > 0 -> - a_MOccurrence[q32] = - sum([toInt(b_ExplicitWithFlags_Values[q29] = q32) * catchUndef(b_ExplicitWithFlags_Flags[q29], 0) - | q29 : int(1..3)]) - | q32 : int(1..2), q32 < q36]) - /\ - and([and([b_ExplicitWithFlags_Flags[q33] > 0, - !or([a_MOccurrence[q31] > 0 /\ q31 = b_ExplicitWithFlags_Values[q33] | q31 : int(1..2)]), - b_ExplicitWithFlags_Values[q33] < q36; - int(1..3)]) - -> - a_MOccurrence[b_ExplicitWithFlags_Values[q33]] = - sum([toInt(b_ExplicitWithFlags_Values[q29] = b_ExplicitWithFlags_Values[q33]) * - catchUndef(b_ExplicitWithFlags_Flags[q29], 0) - | q29 : int(1..3)]) - | q33 : int(1..3)]))) - | q36 : int(1..2)]) - \/ - or([b_ExplicitWithFlags_Flags[q37] > 0 /\ - !or([a_MOccurrence[q35] > 0 /\ q35 = b_ExplicitWithFlags_Values[q37] | q35 : int(1..2)]) - /\ - (a_MOccurrence[b_ExplicitWithFlags_Values[q37]] < - sum([toInt(b_ExplicitWithFlags_Values[q28] = b_ExplicitWithFlags_Values[q37]) * - catchUndef(b_ExplicitWithFlags_Flags[q28], 0) - | q28 : int(1..3)]) - /\ - (and([q32 < b_ExplicitWithFlags_Values[q37] -> - (a_MOccurrence[q32] > 0 -> - a_MOccurrence[q32] = - sum([toInt(b_ExplicitWithFlags_Values[q29] = q32) * catchUndef(b_ExplicitWithFlags_Flags[q29], 0) - | q29 : int(1..3)])) - | q32 : int(1..2)]) - /\ - and([and([b_ExplicitWithFlags_Flags[q33] > 0, - !or([a_MOccurrence[q31] > 0 /\ q31 = b_ExplicitWithFlags_Values[q33] | q31 : int(1..2)]), - b_ExplicitWithFlags_Values[q33] < b_ExplicitWithFlags_Values[q37]; - int(1..3)]) - -> - a_MOccurrence[b_ExplicitWithFlags_Values[q33]] = - sum([toInt(b_ExplicitWithFlags_Values[q29] = b_ExplicitWithFlags_Values[q33]) * - catchUndef(b_ExplicitWithFlags_Flags[q29], 0) - | q29 : int(1..3)]) - | q33 : int(1..3)]))) - | q37 : int(1..3)]), - 3 = sum([a_MOccurrence[q1] | q1 : int(1..2)]), - and([b_ExplicitWithFlags_Flags[q2 + 1] > 0 -> b_ExplicitWithFlags_Values[q2] < b_ExplicitWithFlags_Values[q2 + 1] - | q2 : int(1..2)]), - and([b_ExplicitWithFlags_Flags[q3] = 0 -> b_ExplicitWithFlags_Values[q3] = 1 | q3 : int(1..3)]), - and([b_ExplicitWithFlags_Flags[q4 + 1] > 0 -> b_ExplicitWithFlags_Flags[q4] > 0 | q4 : int(1..2)]), - 3 = sum([b_ExplicitWithFlags_Flags[q6] | q6 : int(1..3)]), - and([a_ExplicitWithRepetition_Values[q8] <= a_ExplicitWithRepetition_Values[q8 + 1] | q8 : int(1..2), q8 + 1 <= 3]), - and([sum([toInt(a_ExplicitWithRepetition_Values[q16] = a_ExplicitWithRepetition_Values[q14]) - | q16 : int(1..3), q16 <= 3]) - = a_MOccurrence[a_ExplicitWithRepetition_Values[q14]] - | q14 : int(1..3), q14 <= 3]), - and([a_MOccurrence[q17] > 0 -> - sum([toInt(a_ExplicitWithRepetition_Values[q19] = q17) | q19 : int(1..3), q19 <= 3]) = a_MOccurrence[q17] - | q17 : int(1..2)]), - 3 = sum([b_MOccurrence[q20] | q20 : int(1..2)]), - and([b_MOccurrence[q22] > 0 -> - b_MOccurrence[q22] = - sum([toInt(b_ExplicitWithFlags_Values[q23] = q22) * catchUndef(b_ExplicitWithFlags_Flags[q23], 0) - | q23 : int(1..3)]) - | q22 : int(1..2)]), - and([b_ExplicitWithFlags_Flags[q24] > 0 -> - b_MOccurrence[b_ExplicitWithFlags_Values[q24]] = - sum([toInt(b_ExplicitWithFlags_Values[q25] = b_ExplicitWithFlags_Values[q24]) * - catchUndef(b_ExplicitWithFlags_Flags[q25], 0) - | q25 : int(1..3)]) - | q24 : int(1..3)]) - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_3_1-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_3_1-solution000001.solution deleted file mode 100644 index 15472caf03..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_3_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 2, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_3_1-solution000002.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_3_1-solution000002.solution deleted file mode 100644 index ff56905e23..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_3_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_3_1-solution000003.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_3_1-solution000003.solution deleted file mode 100644 index d56a0bbcdc..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_3_1-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_3_1-solution000004.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_3_1-solution000004.solution deleted file mode 100644 index 5e2caa751c..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_3_1-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 2, 2) -letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_3_1-solution000005.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_3_1-solution000005.solution deleted file mode 100644 index 1b4b5b08a6..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_3_1-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 2, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_3_1-solution000006.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_3_1-solution000006.solution deleted file mode 100644 index 621d5f6edc..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_3_1-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 1, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_3_1.eprime b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_3_1.eprime deleted file mode 100644 index 6d0283ebf5..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_3_1.eprime +++ /dev/null @@ -1,63 +0,0 @@ -language ESSENCE' 1.0 - -find a_MOccurrence: matrix indexed by [int(1..2)] of int(0..3) -find b_ExplicitWithFlags_Flags: matrix indexed by [int(1..3)] of int(0..3) -find b_ExplicitWithFlags_Values: matrix indexed by [int(1..3)] of int(1..2) -branching on [a_MOccurrence, b_ExplicitWithFlags_Flags, b_ExplicitWithFlags_Values] -such that - or([a_MOccurrence[q18] > 0 /\ - (a_MOccurrence[q18] < - sum([toInt(b_ExplicitWithFlags_Values[q10] = q18) * catchUndef(b_ExplicitWithFlags_Flags[q10], 0) - | q10 : int(1..3)]) - /\ - (and([a_MOccurrence[q14] > 0 -> - a_MOccurrence[q14] = - sum([toInt(b_ExplicitWithFlags_Values[q11] = q14) * catchUndef(b_ExplicitWithFlags_Flags[q11], 0) - | q11 : int(1..3)]) - | q14 : int(1..2), q14 < q18]) - /\ - and([and([b_ExplicitWithFlags_Flags[q15] > 0, - !or([a_MOccurrence[q13] > 0 /\ q13 = b_ExplicitWithFlags_Values[q15] | q13 : int(1..2)]), - b_ExplicitWithFlags_Values[q15] < q18; - int(1..3)]) - -> - a_MOccurrence[b_ExplicitWithFlags_Values[q15]] = - sum([toInt(b_ExplicitWithFlags_Values[q11] = b_ExplicitWithFlags_Values[q15]) * - catchUndef(b_ExplicitWithFlags_Flags[q11], 0) - | q11 : int(1..3)]) - | q15 : int(1..3)]))) - | q18 : int(1..2)]) - \/ - or([b_ExplicitWithFlags_Flags[q19] > 0 /\ - !or([a_MOccurrence[q17] > 0 /\ q17 = b_ExplicitWithFlags_Values[q19] | q17 : int(1..2)]) - /\ - (a_MOccurrence[b_ExplicitWithFlags_Values[q19]] < - sum([toInt(b_ExplicitWithFlags_Values[q10] = b_ExplicitWithFlags_Values[q19]) * - catchUndef(b_ExplicitWithFlags_Flags[q10], 0) - | q10 : int(1..3)]) - /\ - (and([q14 < b_ExplicitWithFlags_Values[q19] -> - (a_MOccurrence[q14] > 0 -> - a_MOccurrence[q14] = - sum([toInt(b_ExplicitWithFlags_Values[q11] = q14) * catchUndef(b_ExplicitWithFlags_Flags[q11], 0) - | q11 : int(1..3)])) - | q14 : int(1..2)]) - /\ - and([and([b_ExplicitWithFlags_Flags[q15] > 0, - !or([a_MOccurrence[q13] > 0 /\ q13 = b_ExplicitWithFlags_Values[q15] | q13 : int(1..2)]), - b_ExplicitWithFlags_Values[q15] < b_ExplicitWithFlags_Values[q19]; - int(1..3)]) - -> - a_MOccurrence[b_ExplicitWithFlags_Values[q15]] = - sum([toInt(b_ExplicitWithFlags_Values[q11] = b_ExplicitWithFlags_Values[q15]) * - catchUndef(b_ExplicitWithFlags_Flags[q11], 0) - | q11 : int(1..3)]) - | q15 : int(1..3)]))) - | q19 : int(1..3)]), - 3 = sum([a_MOccurrence[q1] | q1 : int(1..2)]), - and([b_ExplicitWithFlags_Flags[q2 + 1] > 0 -> b_ExplicitWithFlags_Values[q2] < b_ExplicitWithFlags_Values[q2 + 1] - | q2 : int(1..2)]), - and([b_ExplicitWithFlags_Flags[q3] = 0 -> b_ExplicitWithFlags_Values[q3] = 1 | q3 : int(1..3)]), - and([b_ExplicitWithFlags_Flags[q4 + 1] > 0 -> b_ExplicitWithFlags_Flags[q4] > 0 | q4 : int(1..2)]), - 3 = sum([b_ExplicitWithFlags_Flags[q6] | q6 : int(1..3)]) - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_3_2-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_3_2-solution000001.solution deleted file mode 100644 index d56a0bbcdc..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_3_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_3_2-solution000002.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_3_2-solution000002.solution deleted file mode 100644 index ff56905e23..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_3_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_3_2-solution000003.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_3_2-solution000003.solution deleted file mode 100644 index 15472caf03..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_3_2-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 2, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_3_2-solution000004.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_3_2-solution000004.solution deleted file mode 100644 index 1b4b5b08a6..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_3_2-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 2, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_3_2-solution000005.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_3_2-solution000005.solution deleted file mode 100644 index 5e2caa751c..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_3_2-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 2, 2) -letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_3_2-solution000006.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_3_2-solution000006.solution deleted file mode 100644 index 621d5f6edc..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_3_2-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 1, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_3_2.eprime b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_3_2.eprime deleted file mode 100644 index 514daf5d9b..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_3_2.eprime +++ /dev/null @@ -1,83 +0,0 @@ -language ESSENCE' 1.0 - -find a_MOccurrence: matrix indexed by [int(1..2)] of int(0..3) -find b_ExplicitWithFlags_Flags: matrix indexed by [int(1..3)] of int(0..3) -find b_ExplicitWithFlags_Values: matrix indexed by [int(1..3)] of int(1..2) -find b_ExplicitWithRepetition_Flag: int(3) -find b_ExplicitWithRepetition_Values: matrix indexed by [int(1..3)] of int(1..2) -branching on - [a_MOccurrence, b_ExplicitWithRepetition_Flag, b_ExplicitWithRepetition_Values, b_ExplicitWithFlags_Flags, - b_ExplicitWithFlags_Values] -such that - or([a_MOccurrence[q32] > 0 /\ - (a_MOccurrence[q32] < - sum([toInt(b_ExplicitWithFlags_Values[q24] = q32) * catchUndef(b_ExplicitWithFlags_Flags[q24], 0) - | q24 : int(1..3)]) - /\ - (and([a_MOccurrence[q28] > 0 -> - a_MOccurrence[q28] = - sum([toInt(b_ExplicitWithFlags_Values[q25] = q28) * catchUndef(b_ExplicitWithFlags_Flags[q25], 0) - | q25 : int(1..3)]) - | q28 : int(1..2), q28 < q32]) - /\ - and([and([b_ExplicitWithFlags_Flags[q29] > 0, - !or([a_MOccurrence[q27] > 0 /\ q27 = b_ExplicitWithFlags_Values[q29] | q27 : int(1..2)]), - b_ExplicitWithFlags_Values[q29] < q32; - int(1..3)]) - -> - a_MOccurrence[b_ExplicitWithFlags_Values[q29]] = - sum([toInt(b_ExplicitWithFlags_Values[q25] = b_ExplicitWithFlags_Values[q29]) * - catchUndef(b_ExplicitWithFlags_Flags[q25], 0) - | q25 : int(1..3)]) - | q29 : int(1..3)]))) - | q32 : int(1..2)]) - \/ - or([b_ExplicitWithFlags_Flags[q33] > 0 /\ - !or([a_MOccurrence[q31] > 0 /\ q31 = b_ExplicitWithFlags_Values[q33] | q31 : int(1..2)]) - /\ - (a_MOccurrence[b_ExplicitWithFlags_Values[q33]] < - sum([toInt(b_ExplicitWithFlags_Values[q24] = b_ExplicitWithFlags_Values[q33]) * - catchUndef(b_ExplicitWithFlags_Flags[q24], 0) - | q24 : int(1..3)]) - /\ - (and([q28 < b_ExplicitWithFlags_Values[q33] -> - (a_MOccurrence[q28] > 0 -> - a_MOccurrence[q28] = - sum([toInt(b_ExplicitWithFlags_Values[q25] = q28) * catchUndef(b_ExplicitWithFlags_Flags[q25], 0) - | q25 : int(1..3)])) - | q28 : int(1..2)]) - /\ - and([and([b_ExplicitWithFlags_Flags[q29] > 0, - !or([a_MOccurrence[q27] > 0 /\ q27 = b_ExplicitWithFlags_Values[q29] | q27 : int(1..2)]), - b_ExplicitWithFlags_Values[q29] < b_ExplicitWithFlags_Values[q33]; - int(1..3)]) - -> - a_MOccurrence[b_ExplicitWithFlags_Values[q29]] = - sum([toInt(b_ExplicitWithFlags_Values[q25] = b_ExplicitWithFlags_Values[q29]) * - catchUndef(b_ExplicitWithFlags_Flags[q25], 0) - | q25 : int(1..3)]) - | q29 : int(1..3)]))) - | q33 : int(1..3)]), - 3 = sum([a_MOccurrence[q1] | q1 : int(1..2)]), - and([b_ExplicitWithFlags_Flags[q2 + 1] > 0 -> b_ExplicitWithFlags_Values[q2] < b_ExplicitWithFlags_Values[q2 + 1] - | q2 : int(1..2)]), - and([b_ExplicitWithFlags_Flags[q3] = 0 -> b_ExplicitWithFlags_Values[q3] = 1 | q3 : int(1..3)]), - and([b_ExplicitWithFlags_Flags[q4 + 1] > 0 -> b_ExplicitWithFlags_Flags[q4] > 0 | q4 : int(1..2)]), - 3 = sum([b_ExplicitWithFlags_Flags[q6] | q6 : int(1..3)]), - and([b_ExplicitWithRepetition_Values[q8] <= b_ExplicitWithRepetition_Values[q8 + 1] | q8 : int(1..2), q8 + 1 <= 3]), - and([sum([toInt(b_ExplicitWithRepetition_Values[q17] = b_ExplicitWithRepetition_Values[q14]) - | q17 : int(1..3), q17 <= 3]) - = - sum([toInt(b_ExplicitWithFlags_Values[q15] = b_ExplicitWithRepetition_Values[q14]) * - catchUndef(b_ExplicitWithFlags_Flags[q15], 0) - | q15 : int(1..3)]) - | q14 : int(1..3), q14 <= 3]), - and([b_ExplicitWithFlags_Flags[q18] > 0 -> - sum([toInt(b_ExplicitWithRepetition_Values[q21] = b_ExplicitWithFlags_Values[q18]) - | q21 : int(1..3), q21 <= 3]) - = - sum([toInt(b_ExplicitWithFlags_Values[q19] = b_ExplicitWithFlags_Values[q18]) * - catchUndef(b_ExplicitWithFlags_Flags[q19], 0) - | q19 : int(1..3)]) - | q18 : int(1..3)]) - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_3_3-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_3_3-solution000001.solution deleted file mode 100644 index 15472caf03..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_3_3-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 2, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_3_3-solution000002.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_3_3-solution000002.solution deleted file mode 100644 index ff56905e23..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_3_3-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_3_3-solution000003.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_3_3-solution000003.solution deleted file mode 100644 index d56a0bbcdc..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_3_3-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_3_3-solution000004.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_3_3-solution000004.solution deleted file mode 100644 index 5e2caa751c..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_3_3-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 2, 2) -letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_3_3-solution000005.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_3_3-solution000005.solution deleted file mode 100644 index 1b4b5b08a6..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_3_3-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 2, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_3_3-solution000006.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_3_3-solution000006.solution deleted file mode 100644 index 621d5f6edc..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_3_3-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 1, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_3_3.eprime b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_3_3.eprime deleted file mode 100644 index 2aa2b2f5cc..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_3_3.eprime +++ /dev/null @@ -1,76 +0,0 @@ -language ESSENCE' 1.0 - -find a_MOccurrence: matrix indexed by [int(1..2)] of int(0..3) -find b_ExplicitWithFlags_Flags: matrix indexed by [int(1..3)] of int(0..3) -find b_ExplicitWithFlags_Values: matrix indexed by [int(1..3)] of int(1..2) -find b_MOccurrence: matrix indexed by [int(1..2)] of int(0..3) -branching on [a_MOccurrence, b_MOccurrence, b_ExplicitWithFlags_Flags, b_ExplicitWithFlags_Values] -such that - or([a_MOccurrence[q24] > 0 /\ - (a_MOccurrence[q24] < - sum([toInt(b_ExplicitWithFlags_Values[q16] = q24) * catchUndef(b_ExplicitWithFlags_Flags[q16], 0) - | q16 : int(1..3)]) - /\ - (and([a_MOccurrence[q20] > 0 -> - a_MOccurrence[q20] = - sum([toInt(b_ExplicitWithFlags_Values[q17] = q20) * catchUndef(b_ExplicitWithFlags_Flags[q17], 0) - | q17 : int(1..3)]) - | q20 : int(1..2), q20 < q24]) - /\ - and([and([b_ExplicitWithFlags_Flags[q21] > 0, - !or([a_MOccurrence[q19] > 0 /\ q19 = b_ExplicitWithFlags_Values[q21] | q19 : int(1..2)]), - b_ExplicitWithFlags_Values[q21] < q24; - int(1..3)]) - -> - a_MOccurrence[b_ExplicitWithFlags_Values[q21]] = - sum([toInt(b_ExplicitWithFlags_Values[q17] = b_ExplicitWithFlags_Values[q21]) * - catchUndef(b_ExplicitWithFlags_Flags[q17], 0) - | q17 : int(1..3)]) - | q21 : int(1..3)]))) - | q24 : int(1..2)]) - \/ - or([b_ExplicitWithFlags_Flags[q25] > 0 /\ - !or([a_MOccurrence[q23] > 0 /\ q23 = b_ExplicitWithFlags_Values[q25] | q23 : int(1..2)]) - /\ - (a_MOccurrence[b_ExplicitWithFlags_Values[q25]] < - sum([toInt(b_ExplicitWithFlags_Values[q16] = b_ExplicitWithFlags_Values[q25]) * - catchUndef(b_ExplicitWithFlags_Flags[q16], 0) - | q16 : int(1..3)]) - /\ - (and([q20 < b_ExplicitWithFlags_Values[q25] -> - (a_MOccurrence[q20] > 0 -> - a_MOccurrence[q20] = - sum([toInt(b_ExplicitWithFlags_Values[q17] = q20) * catchUndef(b_ExplicitWithFlags_Flags[q17], 0) - | q17 : int(1..3)])) - | q20 : int(1..2)]) - /\ - and([and([b_ExplicitWithFlags_Flags[q21] > 0, - !or([a_MOccurrence[q19] > 0 /\ q19 = b_ExplicitWithFlags_Values[q21] | q19 : int(1..2)]), - b_ExplicitWithFlags_Values[q21] < b_ExplicitWithFlags_Values[q25]; - int(1..3)]) - -> - a_MOccurrence[b_ExplicitWithFlags_Values[q21]] = - sum([toInt(b_ExplicitWithFlags_Values[q17] = b_ExplicitWithFlags_Values[q21]) * - catchUndef(b_ExplicitWithFlags_Flags[q17], 0) - | q17 : int(1..3)]) - | q21 : int(1..3)]))) - | q25 : int(1..3)]), - 3 = sum([a_MOccurrence[q1] | q1 : int(1..2)]), - and([b_ExplicitWithFlags_Flags[q2 + 1] > 0 -> b_ExplicitWithFlags_Values[q2] < b_ExplicitWithFlags_Values[q2 + 1] - | q2 : int(1..2)]), - and([b_ExplicitWithFlags_Flags[q3] = 0 -> b_ExplicitWithFlags_Values[q3] = 1 | q3 : int(1..3)]), - and([b_ExplicitWithFlags_Flags[q4 + 1] > 0 -> b_ExplicitWithFlags_Flags[q4] > 0 | q4 : int(1..2)]), - 3 = sum([b_ExplicitWithFlags_Flags[q6] | q6 : int(1..3)]), - 3 = sum([b_MOccurrence[q8] | q8 : int(1..2)]), - and([b_MOccurrence[q10] > 0 -> - b_MOccurrence[q10] = - sum([toInt(b_ExplicitWithFlags_Values[q11] = q10) * catchUndef(b_ExplicitWithFlags_Flags[q11], 0) - | q11 : int(1..3)]) - | q10 : int(1..2)]), - and([b_ExplicitWithFlags_Flags[q12] > 0 -> - b_MOccurrence[b_ExplicitWithFlags_Values[q12]] = - sum([toInt(b_ExplicitWithFlags_Values[q13] = b_ExplicitWithFlags_Values[q12]) * - catchUndef(b_ExplicitWithFlags_Flags[q13], 0) - | q13 : int(1..3)]) - | q12 : int(1..3)]) - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_1_1-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_1_1-solution000001.solution deleted file mode 100644 index 5e2caa751c..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_1_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 2, 2) -letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_1_1-solution000002.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_1_1-solution000002.solution deleted file mode 100644 index 1b4b5b08a6..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_1_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 2, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_1_1-solution000003.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_1_1-solution000003.solution deleted file mode 100644 index 621d5f6edc..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_1_1-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 1, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_1_1-solution000004.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_1_1-solution000004.solution deleted file mode 100644 index 15472caf03..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_1_1-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 2, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_1_1-solution000005.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_1_1-solution000005.solution deleted file mode 100644 index ff56905e23..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_1_1-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_1_1-solution000006.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_1_1-solution000006.solution deleted file mode 100644 index d56a0bbcdc..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_1_1-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_1_1.eprime b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_1_1.eprime deleted file mode 100644 index 6027415255..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_1_1.eprime +++ /dev/null @@ -1,86 +0,0 @@ -language ESSENCE' 1.0 - -find a_MOccurrence: matrix indexed by [int(1..2)] of int(0..3) -find a_ExplicitWithFlags_Flags: matrix indexed by [int(1..3)] of int(0..3) -find a_ExplicitWithFlags_Values: matrix indexed by [int(1..3)] of int(1..2) -find b_ExplicitWithRepetition_Flag: int(3) -find b_ExplicitWithRepetition_Values: matrix indexed by [int(1..3)] of int(1..2) -find b_ExplicitWithFlags_Flags: matrix indexed by [int(1..3)] of int(0..3) -find b_ExplicitWithFlags_Values: matrix indexed by [int(1..3)] of int(1..2) -branching on - [a_ExplicitWithFlags_Flags, a_ExplicitWithFlags_Values, a_MOccurrence, b_ExplicitWithFlags_Flags, - b_ExplicitWithFlags_Values, b_ExplicitWithRepetition_Flag, b_ExplicitWithRepetition_Values] -such that - or([a_MOccurrence[q46] > 0 /\ - (a_MOccurrence[q46] < sum([toInt(b_ExplicitWithRepetition_Values[q36] = q46) | q36 : int(1..3), q36 <= 3]) /\ - (and([a_MOccurrence[q42] > 0 -> - a_MOccurrence[q42] = sum([toInt(b_ExplicitWithRepetition_Values[q38] = q42) | q38 : int(1..3), q38 <= 3]) - | q42 : int(1..2), q42 < q46]) - /\ - and([!or([a_MOccurrence[q41] > 0 /\ q41 = b_ExplicitWithRepetition_Values[q39] | q41 : int(1..2)]) /\ - b_ExplicitWithRepetition_Values[q39] < q46 - -> - a_MOccurrence[b_ExplicitWithRepetition_Values[q39]] = - sum([toInt(b_ExplicitWithRepetition_Values[q38] = b_ExplicitWithRepetition_Values[q39]) - | q38 : int(1..3), q38 <= 3]) - | q39 : int(1..3), q39 <= 3]))) - | q46 : int(1..2)]) - \/ - or([!or([a_MOccurrence[q45] > 0 /\ q45 = b_ExplicitWithRepetition_Values[q43] | q45 : int(1..2)]) /\ - (a_MOccurrence[b_ExplicitWithRepetition_Values[q43]] < - sum([toInt(b_ExplicitWithRepetition_Values[q36] = b_ExplicitWithRepetition_Values[q43]) - | q36 : int(1..3), q36 <= 3]) - /\ - (and([q42 < b_ExplicitWithRepetition_Values[q43] -> - (a_MOccurrence[q42] > 0 -> - a_MOccurrence[q42] = - sum([toInt(b_ExplicitWithRepetition_Values[q38] = q42) | q38 : int(1..3), q38 <= 3])) - | q42 : int(1..2)]) - /\ - and([!or([a_MOccurrence[q41] > 0 /\ q41 = b_ExplicitWithRepetition_Values[q39] | q41 : int(1..2)]) /\ - b_ExplicitWithRepetition_Values[q39] < b_ExplicitWithRepetition_Values[q43] - -> - a_MOccurrence[b_ExplicitWithRepetition_Values[q39]] = - sum([toInt(b_ExplicitWithRepetition_Values[q38] = b_ExplicitWithRepetition_Values[q39]) - | q38 : int(1..3), q38 <= 3]) - | q39 : int(1..3), q39 <= 3]))) - | q43 : int(1..3), q43 <= 3]), - 3 = sum([a_MOccurrence[q1] | q1 : int(1..2)]), - and([b_ExplicitWithRepetition_Values[q2] <= b_ExplicitWithRepetition_Values[q2 + 1] | q2 : int(1..2), q2 + 1 <= 3]), - and([a_ExplicitWithFlags_Flags[q7 + 1] > 0 -> a_ExplicitWithFlags_Values[q7] < a_ExplicitWithFlags_Values[q7 + 1] - | q7 : int(1..2)]), - and([a_ExplicitWithFlags_Flags[q8] = 0 -> a_ExplicitWithFlags_Values[q8] = 1 | q8 : int(1..3)]), - and([a_ExplicitWithFlags_Flags[q9 + 1] > 0 -> a_ExplicitWithFlags_Flags[q9] > 0 | q9 : int(1..2)]), - 3 = sum([a_ExplicitWithFlags_Flags[q11] | q11 : int(1..3)]), - and([a_ExplicitWithFlags_Flags[q14] > 0 -> - sum([toInt(a_ExplicitWithFlags_Values[q15] = a_ExplicitWithFlags_Values[q14]) * - catchUndef(a_ExplicitWithFlags_Flags[q15], 0) - | q15 : int(1..3)]) - = a_MOccurrence[a_ExplicitWithFlags_Values[q14]] - | q14 : int(1..3)]), - and([a_MOccurrence[q16] > 0 -> - sum([toInt(a_ExplicitWithFlags_Values[q17] = q16) * catchUndef(a_ExplicitWithFlags_Flags[q17], 0) - | q17 : int(1..3)]) - = a_MOccurrence[q16] - | q16 : int(1..2)]), - and([b_ExplicitWithFlags_Flags[q18 + 1] > 0 -> b_ExplicitWithFlags_Values[q18] < b_ExplicitWithFlags_Values[q18 + 1] - | q18 : int(1..2)]), - and([b_ExplicitWithFlags_Flags[q19] = 0 -> b_ExplicitWithFlags_Values[q19] = 1 | q19 : int(1..3)]), - and([b_ExplicitWithFlags_Flags[q20 + 1] > 0 -> b_ExplicitWithFlags_Flags[q20] > 0 | q20 : int(1..2)]), - 3 = sum([b_ExplicitWithFlags_Flags[q22] | q22 : int(1..3)]), - and([b_ExplicitWithFlags_Flags[q25] > 0 -> - sum([toInt(b_ExplicitWithFlags_Values[q26] = b_ExplicitWithFlags_Values[q25]) * - catchUndef(b_ExplicitWithFlags_Flags[q26], 0) - | q26 : int(1..3)]) - = - sum([toInt(b_ExplicitWithRepetition_Values[q28] = b_ExplicitWithFlags_Values[q25]) - | q28 : int(1..3), q28 <= 3]) - | q25 : int(1..3)]), - and([sum([toInt(b_ExplicitWithFlags_Values[q30] = b_ExplicitWithRepetition_Values[q29]) * - catchUndef(b_ExplicitWithFlags_Flags[q30], 0) - | q30 : int(1..3)]) - = - sum([toInt(b_ExplicitWithRepetition_Values[q32] = b_ExplicitWithRepetition_Values[q29]) - | q32 : int(1..3), q32 <= 3]) - | q29 : int(1..3), q29 <= 3]) - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_1_2-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_1_2-solution000001.solution deleted file mode 100644 index 1b4b5b08a6..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_1_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 2, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_1_2-solution000002.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_1_2-solution000002.solution deleted file mode 100644 index 5e2caa751c..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_1_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 2, 2) -letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_1_2-solution000003.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_1_2-solution000003.solution deleted file mode 100644 index 621d5f6edc..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_1_2-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 1, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_1_2-solution000004.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_1_2-solution000004.solution deleted file mode 100644 index d56a0bbcdc..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_1_2-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_1_2-solution000005.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_1_2-solution000005.solution deleted file mode 100644 index ff56905e23..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_1_2-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_1_2-solution000006.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_1_2-solution000006.solution deleted file mode 100644 index 15472caf03..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_1_2-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 2, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_1_2.eprime b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_1_2.eprime deleted file mode 100644 index 4ecc886d5c..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_1_2.eprime +++ /dev/null @@ -1,64 +0,0 @@ -language ESSENCE' 1.0 - -find a_MOccurrence: matrix indexed by [int(1..2)] of int(0..3) -find a_ExplicitWithFlags_Flags: matrix indexed by [int(1..3)] of int(0..3) -find a_ExplicitWithFlags_Values: matrix indexed by [int(1..3)] of int(1..2) -find b_ExplicitWithRepetition_Flag: int(3) -find b_ExplicitWithRepetition_Values: matrix indexed by [int(1..3)] of int(1..2) -branching on - [a_ExplicitWithFlags_Flags, a_ExplicitWithFlags_Values, a_MOccurrence, b_ExplicitWithRepetition_Flag, - b_ExplicitWithRepetition_Values] -such that - or([a_MOccurrence[q31] > 0 /\ - (a_MOccurrence[q31] < sum([toInt(b_ExplicitWithRepetition_Values[q21] = q31) | q21 : int(1..3), q21 <= 3]) /\ - (and([a_MOccurrence[q27] > 0 -> - a_MOccurrence[q27] = sum([toInt(b_ExplicitWithRepetition_Values[q23] = q27) | q23 : int(1..3), q23 <= 3]) - | q27 : int(1..2), q27 < q31]) - /\ - and([!or([a_MOccurrence[q26] > 0 /\ q26 = b_ExplicitWithRepetition_Values[q24] | q26 : int(1..2)]) /\ - b_ExplicitWithRepetition_Values[q24] < q31 - -> - a_MOccurrence[b_ExplicitWithRepetition_Values[q24]] = - sum([toInt(b_ExplicitWithRepetition_Values[q23] = b_ExplicitWithRepetition_Values[q24]) - | q23 : int(1..3), q23 <= 3]) - | q24 : int(1..3), q24 <= 3]))) - | q31 : int(1..2)]) - \/ - or([!or([a_MOccurrence[q30] > 0 /\ q30 = b_ExplicitWithRepetition_Values[q28] | q30 : int(1..2)]) /\ - (a_MOccurrence[b_ExplicitWithRepetition_Values[q28]] < - sum([toInt(b_ExplicitWithRepetition_Values[q21] = b_ExplicitWithRepetition_Values[q28]) - | q21 : int(1..3), q21 <= 3]) - /\ - (and([q27 < b_ExplicitWithRepetition_Values[q28] -> - (a_MOccurrence[q27] > 0 -> - a_MOccurrence[q27] = - sum([toInt(b_ExplicitWithRepetition_Values[q23] = q27) | q23 : int(1..3), q23 <= 3])) - | q27 : int(1..2)]) - /\ - and([!or([a_MOccurrence[q26] > 0 /\ q26 = b_ExplicitWithRepetition_Values[q24] | q26 : int(1..2)]) /\ - b_ExplicitWithRepetition_Values[q24] < b_ExplicitWithRepetition_Values[q28] - -> - a_MOccurrence[b_ExplicitWithRepetition_Values[q24]] = - sum([toInt(b_ExplicitWithRepetition_Values[q23] = b_ExplicitWithRepetition_Values[q24]) - | q23 : int(1..3), q23 <= 3]) - | q24 : int(1..3), q24 <= 3]))) - | q28 : int(1..3), q28 <= 3]), - 3 = sum([a_MOccurrence[q1] | q1 : int(1..2)]), - and([b_ExplicitWithRepetition_Values[q2] <= b_ExplicitWithRepetition_Values[q2 + 1] | q2 : int(1..2), q2 + 1 <= 3]), - and([a_ExplicitWithFlags_Flags[q7 + 1] > 0 -> a_ExplicitWithFlags_Values[q7] < a_ExplicitWithFlags_Values[q7 + 1] - | q7 : int(1..2)]), - and([a_ExplicitWithFlags_Flags[q8] = 0 -> a_ExplicitWithFlags_Values[q8] = 1 | q8 : int(1..3)]), - and([a_ExplicitWithFlags_Flags[q9 + 1] > 0 -> a_ExplicitWithFlags_Flags[q9] > 0 | q9 : int(1..2)]), - 3 = sum([a_ExplicitWithFlags_Flags[q11] | q11 : int(1..3)]), - and([a_ExplicitWithFlags_Flags[q14] > 0 -> - sum([toInt(a_ExplicitWithFlags_Values[q15] = a_ExplicitWithFlags_Values[q14]) * - catchUndef(a_ExplicitWithFlags_Flags[q15], 0) - | q15 : int(1..3)]) - = a_MOccurrence[a_ExplicitWithFlags_Values[q14]] - | q14 : int(1..3)]), - and([a_MOccurrence[q16] > 0 -> - sum([toInt(a_ExplicitWithFlags_Values[q17] = q16) * catchUndef(a_ExplicitWithFlags_Flags[q17], 0) - | q17 : int(1..3)]) - = a_MOccurrence[q16] - | q16 : int(1..2)]) - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_1_3-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_1_3-solution000001.solution deleted file mode 100644 index 5e2caa751c..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_1_3-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 2, 2) -letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_1_3-solution000002.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_1_3-solution000002.solution deleted file mode 100644 index 1b4b5b08a6..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_1_3-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 2, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_1_3-solution000003.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_1_3-solution000003.solution deleted file mode 100644 index 621d5f6edc..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_1_3-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 1, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_1_3-solution000004.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_1_3-solution000004.solution deleted file mode 100644 index 15472caf03..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_1_3-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 2, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_1_3-solution000005.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_1_3-solution000005.solution deleted file mode 100644 index ff56905e23..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_1_3-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_1_3-solution000006.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_1_3-solution000006.solution deleted file mode 100644 index d56a0bbcdc..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_1_3-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_1_3.eprime b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_1_3.eprime deleted file mode 100644 index e34d5f0e2e..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_1_3.eprime +++ /dev/null @@ -1,73 +0,0 @@ -language ESSENCE' 1.0 - -find a_MOccurrence: matrix indexed by [int(1..2)] of int(0..3) -find a_ExplicitWithFlags_Flags: matrix indexed by [int(1..3)] of int(0..3) -find a_ExplicitWithFlags_Values: matrix indexed by [int(1..3)] of int(1..2) -find b_ExplicitWithRepetition_Flag: int(3) -find b_ExplicitWithRepetition_Values: matrix indexed by [int(1..3)] of int(1..2) -find b_MOccurrence: matrix indexed by [int(1..2)] of int(0..3) -branching on - [a_ExplicitWithFlags_Flags, a_ExplicitWithFlags_Values, a_MOccurrence, b_MOccurrence, b_ExplicitWithRepetition_Flag, - b_ExplicitWithRepetition_Values] -such that - or([a_MOccurrence[q39] > 0 /\ - (a_MOccurrence[q39] < sum([toInt(b_ExplicitWithRepetition_Values[q29] = q39) | q29 : int(1..3), q29 <= 3]) /\ - (and([a_MOccurrence[q35] > 0 -> - a_MOccurrence[q35] = sum([toInt(b_ExplicitWithRepetition_Values[q31] = q35) | q31 : int(1..3), q31 <= 3]) - | q35 : int(1..2), q35 < q39]) - /\ - and([!or([a_MOccurrence[q34] > 0 /\ q34 = b_ExplicitWithRepetition_Values[q32] | q34 : int(1..2)]) /\ - b_ExplicitWithRepetition_Values[q32] < q39 - -> - a_MOccurrence[b_ExplicitWithRepetition_Values[q32]] = - sum([toInt(b_ExplicitWithRepetition_Values[q31] = b_ExplicitWithRepetition_Values[q32]) - | q31 : int(1..3), q31 <= 3]) - | q32 : int(1..3), q32 <= 3]))) - | q39 : int(1..2)]) - \/ - or([!or([a_MOccurrence[q38] > 0 /\ q38 = b_ExplicitWithRepetition_Values[q36] | q38 : int(1..2)]) /\ - (a_MOccurrence[b_ExplicitWithRepetition_Values[q36]] < - sum([toInt(b_ExplicitWithRepetition_Values[q29] = b_ExplicitWithRepetition_Values[q36]) - | q29 : int(1..3), q29 <= 3]) - /\ - (and([q35 < b_ExplicitWithRepetition_Values[q36] -> - (a_MOccurrence[q35] > 0 -> - a_MOccurrence[q35] = - sum([toInt(b_ExplicitWithRepetition_Values[q31] = q35) | q31 : int(1..3), q31 <= 3])) - | q35 : int(1..2)]) - /\ - and([!or([a_MOccurrence[q34] > 0 /\ q34 = b_ExplicitWithRepetition_Values[q32] | q34 : int(1..2)]) /\ - b_ExplicitWithRepetition_Values[q32] < b_ExplicitWithRepetition_Values[q36] - -> - a_MOccurrence[b_ExplicitWithRepetition_Values[q32]] = - sum([toInt(b_ExplicitWithRepetition_Values[q31] = b_ExplicitWithRepetition_Values[q32]) - | q31 : int(1..3), q31 <= 3]) - | q32 : int(1..3), q32 <= 3]))) - | q36 : int(1..3), q36 <= 3]), - 3 = sum([a_MOccurrence[q1] | q1 : int(1..2)]), - and([b_ExplicitWithRepetition_Values[q2] <= b_ExplicitWithRepetition_Values[q2 + 1] | q2 : int(1..2), q2 + 1 <= 3]), - and([a_ExplicitWithFlags_Flags[q7 + 1] > 0 -> a_ExplicitWithFlags_Values[q7] < a_ExplicitWithFlags_Values[q7 + 1] - | q7 : int(1..2)]), - and([a_ExplicitWithFlags_Flags[q8] = 0 -> a_ExplicitWithFlags_Values[q8] = 1 | q8 : int(1..3)]), - and([a_ExplicitWithFlags_Flags[q9 + 1] > 0 -> a_ExplicitWithFlags_Flags[q9] > 0 | q9 : int(1..2)]), - 3 = sum([a_ExplicitWithFlags_Flags[q11] | q11 : int(1..3)]), - and([a_ExplicitWithFlags_Flags[q14] > 0 -> - sum([toInt(a_ExplicitWithFlags_Values[q15] = a_ExplicitWithFlags_Values[q14]) * - catchUndef(a_ExplicitWithFlags_Flags[q15], 0) - | q15 : int(1..3)]) - = a_MOccurrence[a_ExplicitWithFlags_Values[q14]] - | q14 : int(1..3)]), - and([a_MOccurrence[q16] > 0 -> - sum([toInt(a_ExplicitWithFlags_Values[q17] = q16) * catchUndef(a_ExplicitWithFlags_Flags[q17], 0) - | q17 : int(1..3)]) - = a_MOccurrence[q16] - | q16 : int(1..2)]), - 3 = sum([b_MOccurrence[q18] | q18 : int(1..2)]), - and([b_MOccurrence[q20] > 0 -> - b_MOccurrence[q20] = sum([toInt(b_ExplicitWithRepetition_Values[q22] = q20) | q22 : int(1..3), q22 <= 3]) - | q20 : int(1..2)]), - and([b_MOccurrence[b_ExplicitWithRepetition_Values[q23]] = - sum([toInt(b_ExplicitWithRepetition_Values[q25] = b_ExplicitWithRepetition_Values[q23]) - | q25 : int(1..3), q25 <= 3]) - | q23 : int(1..3), q23 <= 3]) - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_2_1-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_2_1-solution000001.solution deleted file mode 100644 index 621d5f6edc..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_2_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 1, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_2_1-solution000002.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_2_1-solution000002.solution deleted file mode 100644 index 5e2caa751c..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_2_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 2, 2) -letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_2_1-solution000003.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_2_1-solution000003.solution deleted file mode 100644 index 1b4b5b08a6..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_2_1-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 2, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_2_1-solution000004.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_2_1-solution000004.solution deleted file mode 100644 index 15472caf03..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_2_1-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 2, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_2_1-solution000005.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_2_1-solution000005.solution deleted file mode 100644 index ff56905e23..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_2_1-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_2_1-solution000006.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_2_1-solution000006.solution deleted file mode 100644 index d56a0bbcdc..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_2_1-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_2_1.eprime b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_2_1.eprime deleted file mode 100644 index 580229d971..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_2_1.eprime +++ /dev/null @@ -1,78 +0,0 @@ -language ESSENCE' 1.0 - -find a_MOccurrence: matrix indexed by [int(1..2)] of int(0..3) -find a_ExplicitWithRepetition_Flag: int(3) -find a_ExplicitWithRepetition_Values: matrix indexed by [int(1..3)] of int(1..2) -find b_ExplicitWithRepetition_Flag: int(3) -find b_ExplicitWithRepetition_Values: matrix indexed by [int(1..3)] of int(1..2) -find b_ExplicitWithFlags_Flags: matrix indexed by [int(1..3)] of int(0..3) -find b_ExplicitWithFlags_Values: matrix indexed by [int(1..3)] of int(1..2) -branching on - [a_ExplicitWithRepetition_Flag, a_ExplicitWithRepetition_Values, a_MOccurrence, b_ExplicitWithFlags_Flags, - b_ExplicitWithFlags_Values, b_ExplicitWithRepetition_Flag, b_ExplicitWithRepetition_Values] -such that - or([a_MOccurrence[q47] > 0 /\ - (a_MOccurrence[q47] < sum([toInt(b_ExplicitWithRepetition_Values[q37] = q47) | q37 : int(1..3), q37 <= 3]) /\ - (and([a_MOccurrence[q43] > 0 -> - a_MOccurrence[q43] = sum([toInt(b_ExplicitWithRepetition_Values[q39] = q43) | q39 : int(1..3), q39 <= 3]) - | q43 : int(1..2), q43 < q47]) - /\ - and([!or([a_MOccurrence[q42] > 0 /\ q42 = b_ExplicitWithRepetition_Values[q40] | q42 : int(1..2)]) /\ - b_ExplicitWithRepetition_Values[q40] < q47 - -> - a_MOccurrence[b_ExplicitWithRepetition_Values[q40]] = - sum([toInt(b_ExplicitWithRepetition_Values[q39] = b_ExplicitWithRepetition_Values[q40]) - | q39 : int(1..3), q39 <= 3]) - | q40 : int(1..3), q40 <= 3]))) - | q47 : int(1..2)]) - \/ - or([!or([a_MOccurrence[q46] > 0 /\ q46 = b_ExplicitWithRepetition_Values[q44] | q46 : int(1..2)]) /\ - (a_MOccurrence[b_ExplicitWithRepetition_Values[q44]] < - sum([toInt(b_ExplicitWithRepetition_Values[q37] = b_ExplicitWithRepetition_Values[q44]) - | q37 : int(1..3), q37 <= 3]) - /\ - (and([q43 < b_ExplicitWithRepetition_Values[q44] -> - (a_MOccurrence[q43] > 0 -> - a_MOccurrence[q43] = - sum([toInt(b_ExplicitWithRepetition_Values[q39] = q43) | q39 : int(1..3), q39 <= 3])) - | q43 : int(1..2)]) - /\ - and([!or([a_MOccurrence[q42] > 0 /\ q42 = b_ExplicitWithRepetition_Values[q40] | q42 : int(1..2)]) /\ - b_ExplicitWithRepetition_Values[q40] < b_ExplicitWithRepetition_Values[q44] - -> - a_MOccurrence[b_ExplicitWithRepetition_Values[q40]] = - sum([toInt(b_ExplicitWithRepetition_Values[q39] = b_ExplicitWithRepetition_Values[q40]) - | q39 : int(1..3), q39 <= 3]) - | q40 : int(1..3), q40 <= 3]))) - | q44 : int(1..3), q44 <= 3]), - 3 = sum([a_MOccurrence[q1] | q1 : int(1..2)]), - and([b_ExplicitWithRepetition_Values[q2] <= b_ExplicitWithRepetition_Values[q2 + 1] | q2 : int(1..2), q2 + 1 <= 3]), - and([a_ExplicitWithRepetition_Values[q7] <= a_ExplicitWithRepetition_Values[q7 + 1] | q7 : int(1..2), q7 + 1 <= 3]), - and([sum([toInt(a_ExplicitWithRepetition_Values[q15] = a_ExplicitWithRepetition_Values[q13]) - | q15 : int(1..3), q15 <= 3]) - = a_MOccurrence[a_ExplicitWithRepetition_Values[q13]] - | q13 : int(1..3), q13 <= 3]), - and([a_MOccurrence[q16] > 0 -> - sum([toInt(a_ExplicitWithRepetition_Values[q18] = q16) | q18 : int(1..3), q18 <= 3]) = a_MOccurrence[q16] - | q16 : int(1..2)]), - and([b_ExplicitWithFlags_Flags[q19 + 1] > 0 -> b_ExplicitWithFlags_Values[q19] < b_ExplicitWithFlags_Values[q19 + 1] - | q19 : int(1..2)]), - and([b_ExplicitWithFlags_Flags[q20] = 0 -> b_ExplicitWithFlags_Values[q20] = 1 | q20 : int(1..3)]), - and([b_ExplicitWithFlags_Flags[q21 + 1] > 0 -> b_ExplicitWithFlags_Flags[q21] > 0 | q21 : int(1..2)]), - 3 = sum([b_ExplicitWithFlags_Flags[q23] | q23 : int(1..3)]), - and([b_ExplicitWithFlags_Flags[q26] > 0 -> - sum([toInt(b_ExplicitWithFlags_Values[q27] = b_ExplicitWithFlags_Values[q26]) * - catchUndef(b_ExplicitWithFlags_Flags[q27], 0) - | q27 : int(1..3)]) - = - sum([toInt(b_ExplicitWithRepetition_Values[q29] = b_ExplicitWithFlags_Values[q26]) - | q29 : int(1..3), q29 <= 3]) - | q26 : int(1..3)]), - and([sum([toInt(b_ExplicitWithFlags_Values[q31] = b_ExplicitWithRepetition_Values[q30]) * - catchUndef(b_ExplicitWithFlags_Flags[q31], 0) - | q31 : int(1..3)]) - = - sum([toInt(b_ExplicitWithRepetition_Values[q33] = b_ExplicitWithRepetition_Values[q30]) - | q33 : int(1..3), q33 <= 3]) - | q30 : int(1..3), q30 <= 3]) - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_2_2-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_2_2-solution000001.solution deleted file mode 100644 index 621d5f6edc..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_2_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 1, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_2_2-solution000002.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_2_2-solution000002.solution deleted file mode 100644 index 1b4b5b08a6..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_2_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 2, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_2_2-solution000003.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_2_2-solution000003.solution deleted file mode 100644 index 5e2caa751c..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_2_2-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 2, 2) -letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_2_2-solution000004.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_2_2-solution000004.solution deleted file mode 100644 index d56a0bbcdc..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_2_2-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_2_2-solution000005.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_2_2-solution000005.solution deleted file mode 100644 index ff56905e23..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_2_2-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_2_2-solution000006.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_2_2-solution000006.solution deleted file mode 100644 index 15472caf03..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_2_2-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 2, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_2_2.eprime b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_2_2.eprime deleted file mode 100644 index 559348a46a..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_2_2.eprime +++ /dev/null @@ -1,56 +0,0 @@ -language ESSENCE' 1.0 - -find a_MOccurrence: matrix indexed by [int(1..2)] of int(0..3) -find a_ExplicitWithRepetition_Flag: int(3) -find a_ExplicitWithRepetition_Values: matrix indexed by [int(1..3)] of int(1..2) -find b_ExplicitWithRepetition_Flag: int(3) -find b_ExplicitWithRepetition_Values: matrix indexed by [int(1..3)] of int(1..2) -branching on - [a_ExplicitWithRepetition_Flag, a_ExplicitWithRepetition_Values, a_MOccurrence, b_ExplicitWithRepetition_Flag, - b_ExplicitWithRepetition_Values] -such that - or([a_MOccurrence[q32] > 0 /\ - (a_MOccurrence[q32] < sum([toInt(b_ExplicitWithRepetition_Values[q22] = q32) | q22 : int(1..3), q22 <= 3]) /\ - (and([a_MOccurrence[q28] > 0 -> - a_MOccurrence[q28] = sum([toInt(b_ExplicitWithRepetition_Values[q24] = q28) | q24 : int(1..3), q24 <= 3]) - | q28 : int(1..2), q28 < q32]) - /\ - and([!or([a_MOccurrence[q27] > 0 /\ q27 = b_ExplicitWithRepetition_Values[q25] | q27 : int(1..2)]) /\ - b_ExplicitWithRepetition_Values[q25] < q32 - -> - a_MOccurrence[b_ExplicitWithRepetition_Values[q25]] = - sum([toInt(b_ExplicitWithRepetition_Values[q24] = b_ExplicitWithRepetition_Values[q25]) - | q24 : int(1..3), q24 <= 3]) - | q25 : int(1..3), q25 <= 3]))) - | q32 : int(1..2)]) - \/ - or([!or([a_MOccurrence[q31] > 0 /\ q31 = b_ExplicitWithRepetition_Values[q29] | q31 : int(1..2)]) /\ - (a_MOccurrence[b_ExplicitWithRepetition_Values[q29]] < - sum([toInt(b_ExplicitWithRepetition_Values[q22] = b_ExplicitWithRepetition_Values[q29]) - | q22 : int(1..3), q22 <= 3]) - /\ - (and([q28 < b_ExplicitWithRepetition_Values[q29] -> - (a_MOccurrence[q28] > 0 -> - a_MOccurrence[q28] = - sum([toInt(b_ExplicitWithRepetition_Values[q24] = q28) | q24 : int(1..3), q24 <= 3])) - | q28 : int(1..2)]) - /\ - and([!or([a_MOccurrence[q27] > 0 /\ q27 = b_ExplicitWithRepetition_Values[q25] | q27 : int(1..2)]) /\ - b_ExplicitWithRepetition_Values[q25] < b_ExplicitWithRepetition_Values[q29] - -> - a_MOccurrence[b_ExplicitWithRepetition_Values[q25]] = - sum([toInt(b_ExplicitWithRepetition_Values[q24] = b_ExplicitWithRepetition_Values[q25]) - | q24 : int(1..3), q24 <= 3]) - | q25 : int(1..3), q25 <= 3]))) - | q29 : int(1..3), q29 <= 3]), - 3 = sum([a_MOccurrence[q1] | q1 : int(1..2)]), - and([b_ExplicitWithRepetition_Values[q2] <= b_ExplicitWithRepetition_Values[q2 + 1] | q2 : int(1..2), q2 + 1 <= 3]), - and([a_ExplicitWithRepetition_Values[q7] <= a_ExplicitWithRepetition_Values[q7 + 1] | q7 : int(1..2), q7 + 1 <= 3]), - and([sum([toInt(a_ExplicitWithRepetition_Values[q15] = a_ExplicitWithRepetition_Values[q13]) - | q15 : int(1..3), q15 <= 3]) - = a_MOccurrence[a_ExplicitWithRepetition_Values[q13]] - | q13 : int(1..3), q13 <= 3]), - and([a_MOccurrence[q16] > 0 -> - sum([toInt(a_ExplicitWithRepetition_Values[q18] = q16) | q18 : int(1..3), q18 <= 3]) = a_MOccurrence[q16] - | q16 : int(1..2)]) - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_2_3-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_2_3-solution000001.solution deleted file mode 100644 index 621d5f6edc..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_2_3-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 1, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_2_3-solution000002.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_2_3-solution000002.solution deleted file mode 100644 index 5e2caa751c..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_2_3-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 2, 2) -letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_2_3-solution000003.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_2_3-solution000003.solution deleted file mode 100644 index 1b4b5b08a6..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_2_3-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 2, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_2_3-solution000004.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_2_3-solution000004.solution deleted file mode 100644 index 15472caf03..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_2_3-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 2, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_2_3-solution000005.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_2_3-solution000005.solution deleted file mode 100644 index ff56905e23..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_2_3-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_2_3-solution000006.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_2_3-solution000006.solution deleted file mode 100644 index d56a0bbcdc..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_2_3-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_2_3.eprime b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_2_3.eprime deleted file mode 100644 index 86fe846f2a..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_2_3.eprime +++ /dev/null @@ -1,65 +0,0 @@ -language ESSENCE' 1.0 - -find a_MOccurrence: matrix indexed by [int(1..2)] of int(0..3) -find a_ExplicitWithRepetition_Flag: int(3) -find a_ExplicitWithRepetition_Values: matrix indexed by [int(1..3)] of int(1..2) -find b_ExplicitWithRepetition_Flag: int(3) -find b_ExplicitWithRepetition_Values: matrix indexed by [int(1..3)] of int(1..2) -find b_MOccurrence: matrix indexed by [int(1..2)] of int(0..3) -branching on - [a_ExplicitWithRepetition_Flag, a_ExplicitWithRepetition_Values, a_MOccurrence, b_MOccurrence, - b_ExplicitWithRepetition_Flag, b_ExplicitWithRepetition_Values] -such that - or([a_MOccurrence[q40] > 0 /\ - (a_MOccurrence[q40] < sum([toInt(b_ExplicitWithRepetition_Values[q30] = q40) | q30 : int(1..3), q30 <= 3]) /\ - (and([a_MOccurrence[q36] > 0 -> - a_MOccurrence[q36] = sum([toInt(b_ExplicitWithRepetition_Values[q32] = q36) | q32 : int(1..3), q32 <= 3]) - | q36 : int(1..2), q36 < q40]) - /\ - and([!or([a_MOccurrence[q35] > 0 /\ q35 = b_ExplicitWithRepetition_Values[q33] | q35 : int(1..2)]) /\ - b_ExplicitWithRepetition_Values[q33] < q40 - -> - a_MOccurrence[b_ExplicitWithRepetition_Values[q33]] = - sum([toInt(b_ExplicitWithRepetition_Values[q32] = b_ExplicitWithRepetition_Values[q33]) - | q32 : int(1..3), q32 <= 3]) - | q33 : int(1..3), q33 <= 3]))) - | q40 : int(1..2)]) - \/ - or([!or([a_MOccurrence[q39] > 0 /\ q39 = b_ExplicitWithRepetition_Values[q37] | q39 : int(1..2)]) /\ - (a_MOccurrence[b_ExplicitWithRepetition_Values[q37]] < - sum([toInt(b_ExplicitWithRepetition_Values[q30] = b_ExplicitWithRepetition_Values[q37]) - | q30 : int(1..3), q30 <= 3]) - /\ - (and([q36 < b_ExplicitWithRepetition_Values[q37] -> - (a_MOccurrence[q36] > 0 -> - a_MOccurrence[q36] = - sum([toInt(b_ExplicitWithRepetition_Values[q32] = q36) | q32 : int(1..3), q32 <= 3])) - | q36 : int(1..2)]) - /\ - and([!or([a_MOccurrence[q35] > 0 /\ q35 = b_ExplicitWithRepetition_Values[q33] | q35 : int(1..2)]) /\ - b_ExplicitWithRepetition_Values[q33] < b_ExplicitWithRepetition_Values[q37] - -> - a_MOccurrence[b_ExplicitWithRepetition_Values[q33]] = - sum([toInt(b_ExplicitWithRepetition_Values[q32] = b_ExplicitWithRepetition_Values[q33]) - | q32 : int(1..3), q32 <= 3]) - | q33 : int(1..3), q33 <= 3]))) - | q37 : int(1..3), q37 <= 3]), - 3 = sum([a_MOccurrence[q1] | q1 : int(1..2)]), - and([b_ExplicitWithRepetition_Values[q2] <= b_ExplicitWithRepetition_Values[q2 + 1] | q2 : int(1..2), q2 + 1 <= 3]), - and([a_ExplicitWithRepetition_Values[q7] <= a_ExplicitWithRepetition_Values[q7 + 1] | q7 : int(1..2), q7 + 1 <= 3]), - and([sum([toInt(a_ExplicitWithRepetition_Values[q15] = a_ExplicitWithRepetition_Values[q13]) - | q15 : int(1..3), q15 <= 3]) - = a_MOccurrence[a_ExplicitWithRepetition_Values[q13]] - | q13 : int(1..3), q13 <= 3]), - and([a_MOccurrence[q16] > 0 -> - sum([toInt(a_ExplicitWithRepetition_Values[q18] = q16) | q18 : int(1..3), q18 <= 3]) = a_MOccurrence[q16] - | q16 : int(1..2)]), - 3 = sum([b_MOccurrence[q19] | q19 : int(1..2)]), - and([b_MOccurrence[q21] > 0 -> - b_MOccurrence[q21] = sum([toInt(b_ExplicitWithRepetition_Values[q23] = q21) | q23 : int(1..3), q23 <= 3]) - | q21 : int(1..2)]), - and([b_MOccurrence[b_ExplicitWithRepetition_Values[q24]] = - sum([toInt(b_ExplicitWithRepetition_Values[q26] = b_ExplicitWithRepetition_Values[q24]) - | q26 : int(1..3), q26 <= 3]) - | q24 : int(1..3), q24 <= 3]) - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_3_1-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_3_1-solution000001.solution deleted file mode 100644 index 15472caf03..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_3_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 2, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_3_1-solution000002.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_3_1-solution000002.solution deleted file mode 100644 index ff56905e23..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_3_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_3_1-solution000003.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_3_1-solution000003.solution deleted file mode 100644 index d56a0bbcdc..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_3_1-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_3_1-solution000004.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_3_1-solution000004.solution deleted file mode 100644 index 5e2caa751c..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_3_1-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 2, 2) -letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_3_1-solution000005.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_3_1-solution000005.solution deleted file mode 100644 index 1b4b5b08a6..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_3_1-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 2, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_3_1-solution000006.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_3_1-solution000006.solution deleted file mode 100644 index 621d5f6edc..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_3_1-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 1, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_3_1.eprime b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_3_1.eprime deleted file mode 100644 index 4acc79a15c..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_3_1.eprime +++ /dev/null @@ -1,68 +0,0 @@ -language ESSENCE' 1.0 - -find a_MOccurrence: matrix indexed by [int(1..2)] of int(0..3) -find b_ExplicitWithRepetition_Flag: int(3) -find b_ExplicitWithRepetition_Values: matrix indexed by [int(1..3)] of int(1..2) -find b_ExplicitWithFlags_Flags: matrix indexed by [int(1..3)] of int(0..3) -find b_ExplicitWithFlags_Values: matrix indexed by [int(1..3)] of int(1..2) -branching on - [a_MOccurrence, b_ExplicitWithFlags_Flags, b_ExplicitWithFlags_Values, b_ExplicitWithRepetition_Flag, - b_ExplicitWithRepetition_Values] -such that - or([a_MOccurrence[q35] > 0 /\ - (a_MOccurrence[q35] < sum([toInt(b_ExplicitWithRepetition_Values[q25] = q35) | q25 : int(1..3), q25 <= 3]) /\ - (and([a_MOccurrence[q31] > 0 -> - a_MOccurrence[q31] = sum([toInt(b_ExplicitWithRepetition_Values[q27] = q31) | q27 : int(1..3), q27 <= 3]) - | q31 : int(1..2), q31 < q35]) - /\ - and([!or([a_MOccurrence[q30] > 0 /\ q30 = b_ExplicitWithRepetition_Values[q28] | q30 : int(1..2)]) /\ - b_ExplicitWithRepetition_Values[q28] < q35 - -> - a_MOccurrence[b_ExplicitWithRepetition_Values[q28]] = - sum([toInt(b_ExplicitWithRepetition_Values[q27] = b_ExplicitWithRepetition_Values[q28]) - | q27 : int(1..3), q27 <= 3]) - | q28 : int(1..3), q28 <= 3]))) - | q35 : int(1..2)]) - \/ - or([!or([a_MOccurrence[q34] > 0 /\ q34 = b_ExplicitWithRepetition_Values[q32] | q34 : int(1..2)]) /\ - (a_MOccurrence[b_ExplicitWithRepetition_Values[q32]] < - sum([toInt(b_ExplicitWithRepetition_Values[q25] = b_ExplicitWithRepetition_Values[q32]) - | q25 : int(1..3), q25 <= 3]) - /\ - (and([q31 < b_ExplicitWithRepetition_Values[q32] -> - (a_MOccurrence[q31] > 0 -> - a_MOccurrence[q31] = - sum([toInt(b_ExplicitWithRepetition_Values[q27] = q31) | q27 : int(1..3), q27 <= 3])) - | q31 : int(1..2)]) - /\ - and([!or([a_MOccurrence[q30] > 0 /\ q30 = b_ExplicitWithRepetition_Values[q28] | q30 : int(1..2)]) /\ - b_ExplicitWithRepetition_Values[q28] < b_ExplicitWithRepetition_Values[q32] - -> - a_MOccurrence[b_ExplicitWithRepetition_Values[q28]] = - sum([toInt(b_ExplicitWithRepetition_Values[q27] = b_ExplicitWithRepetition_Values[q28]) - | q27 : int(1..3), q27 <= 3]) - | q28 : int(1..3), q28 <= 3]))) - | q32 : int(1..3), q32 <= 3]), - 3 = sum([a_MOccurrence[q1] | q1 : int(1..2)]), - and([b_ExplicitWithRepetition_Values[q2] <= b_ExplicitWithRepetition_Values[q2 + 1] | q2 : int(1..2), q2 + 1 <= 3]), - and([b_ExplicitWithFlags_Flags[q7 + 1] > 0 -> b_ExplicitWithFlags_Values[q7] < b_ExplicitWithFlags_Values[q7 + 1] - | q7 : int(1..2)]), - and([b_ExplicitWithFlags_Flags[q8] = 0 -> b_ExplicitWithFlags_Values[q8] = 1 | q8 : int(1..3)]), - and([b_ExplicitWithFlags_Flags[q9 + 1] > 0 -> b_ExplicitWithFlags_Flags[q9] > 0 | q9 : int(1..2)]), - 3 = sum([b_ExplicitWithFlags_Flags[q11] | q11 : int(1..3)]), - and([b_ExplicitWithFlags_Flags[q14] > 0 -> - sum([toInt(b_ExplicitWithFlags_Values[q15] = b_ExplicitWithFlags_Values[q14]) * - catchUndef(b_ExplicitWithFlags_Flags[q15], 0) - | q15 : int(1..3)]) - = - sum([toInt(b_ExplicitWithRepetition_Values[q17] = b_ExplicitWithFlags_Values[q14]) - | q17 : int(1..3), q17 <= 3]) - | q14 : int(1..3)]), - and([sum([toInt(b_ExplicitWithFlags_Values[q19] = b_ExplicitWithRepetition_Values[q18]) * - catchUndef(b_ExplicitWithFlags_Flags[q19], 0) - | q19 : int(1..3)]) - = - sum([toInt(b_ExplicitWithRepetition_Values[q21] = b_ExplicitWithRepetition_Values[q18]) - | q21 : int(1..3), q21 <= 3]) - | q18 : int(1..3), q18 <= 3]) - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_3_2-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_3_2-solution000001.solution deleted file mode 100644 index d56a0bbcdc..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_3_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_3_2-solution000002.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_3_2-solution000002.solution deleted file mode 100644 index ff56905e23..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_3_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_3_2-solution000003.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_3_2-solution000003.solution deleted file mode 100644 index 15472caf03..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_3_2-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 2, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_3_2-solution000004.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_3_2-solution000004.solution deleted file mode 100644 index 1b4b5b08a6..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_3_2-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 2, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_3_2-solution000005.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_3_2-solution000005.solution deleted file mode 100644 index 5e2caa751c..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_3_2-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 2, 2) -letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_3_2-solution000006.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_3_2-solution000006.solution deleted file mode 100644 index 621d5f6edc..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_3_2-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 1, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_3_2.eprime b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_3_2.eprime deleted file mode 100644 index 5fd762ddea..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_3_2.eprime +++ /dev/null @@ -1,44 +0,0 @@ -language ESSENCE' 1.0 - -find a_MOccurrence: matrix indexed by [int(1..2)] of int(0..3) -find b_ExplicitWithRepetition_Flag: int(3) -find b_ExplicitWithRepetition_Values: matrix indexed by [int(1..3)] of int(1..2) -branching on [a_MOccurrence, b_ExplicitWithRepetition_Flag, b_ExplicitWithRepetition_Values] -such that - or([a_MOccurrence[q20] > 0 /\ - (a_MOccurrence[q20] < sum([toInt(b_ExplicitWithRepetition_Values[q10] = q20) | q10 : int(1..3), q10 <= 3]) /\ - (and([a_MOccurrence[q16] > 0 -> - a_MOccurrence[q16] = sum([toInt(b_ExplicitWithRepetition_Values[q12] = q16) | q12 : int(1..3), q12 <= 3]) - | q16 : int(1..2), q16 < q20]) - /\ - and([!or([a_MOccurrence[q15] > 0 /\ q15 = b_ExplicitWithRepetition_Values[q13] | q15 : int(1..2)]) /\ - b_ExplicitWithRepetition_Values[q13] < q20 - -> - a_MOccurrence[b_ExplicitWithRepetition_Values[q13]] = - sum([toInt(b_ExplicitWithRepetition_Values[q12] = b_ExplicitWithRepetition_Values[q13]) - | q12 : int(1..3), q12 <= 3]) - | q13 : int(1..3), q13 <= 3]))) - | q20 : int(1..2)]) - \/ - or([!or([a_MOccurrence[q19] > 0 /\ q19 = b_ExplicitWithRepetition_Values[q17] | q19 : int(1..2)]) /\ - (a_MOccurrence[b_ExplicitWithRepetition_Values[q17]] < - sum([toInt(b_ExplicitWithRepetition_Values[q10] = b_ExplicitWithRepetition_Values[q17]) - | q10 : int(1..3), q10 <= 3]) - /\ - (and([q16 < b_ExplicitWithRepetition_Values[q17] -> - (a_MOccurrence[q16] > 0 -> - a_MOccurrence[q16] = - sum([toInt(b_ExplicitWithRepetition_Values[q12] = q16) | q12 : int(1..3), q12 <= 3])) - | q16 : int(1..2)]) - /\ - and([!or([a_MOccurrence[q15] > 0 /\ q15 = b_ExplicitWithRepetition_Values[q13] | q15 : int(1..2)]) /\ - b_ExplicitWithRepetition_Values[q13] < b_ExplicitWithRepetition_Values[q17] - -> - a_MOccurrence[b_ExplicitWithRepetition_Values[q13]] = - sum([toInt(b_ExplicitWithRepetition_Values[q12] = b_ExplicitWithRepetition_Values[q13]) - | q12 : int(1..3), q12 <= 3]) - | q13 : int(1..3), q13 <= 3]))) - | q17 : int(1..3), q17 <= 3]), - 3 = sum([a_MOccurrence[q1] | q1 : int(1..2)]), - and([b_ExplicitWithRepetition_Values[q2] <= b_ExplicitWithRepetition_Values[q2 + 1] | q2 : int(1..2), q2 + 1 <= 3]) - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_3_3-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_3_3-solution000001.solution deleted file mode 100644 index 15472caf03..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_3_3-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 2, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_3_3-solution000002.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_3_3-solution000002.solution deleted file mode 100644 index ff56905e23..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_3_3-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_3_3-solution000003.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_3_3-solution000003.solution deleted file mode 100644 index d56a0bbcdc..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_3_3-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_3_3-solution000004.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_3_3-solution000004.solution deleted file mode 100644 index 5e2caa751c..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_3_3-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 2, 2) -letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_3_3-solution000005.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_3_3-solution000005.solution deleted file mode 100644 index 1b4b5b08a6..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_3_3-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 2, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_3_3-solution000006.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_3_3-solution000006.solution deleted file mode 100644 index 621d5f6edc..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_3_3-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 1, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_3_3.eprime b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_3_3.eprime deleted file mode 100644 index 58c3cfbb72..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_3_3.eprime +++ /dev/null @@ -1,53 +0,0 @@ -language ESSENCE' 1.0 - -find a_MOccurrence: matrix indexed by [int(1..2)] of int(0..3) -find b_ExplicitWithRepetition_Flag: int(3) -find b_ExplicitWithRepetition_Values: matrix indexed by [int(1..3)] of int(1..2) -find b_MOccurrence: matrix indexed by [int(1..2)] of int(0..3) -branching on [a_MOccurrence, b_MOccurrence, b_ExplicitWithRepetition_Flag, b_ExplicitWithRepetition_Values] -such that - or([a_MOccurrence[q28] > 0 /\ - (a_MOccurrence[q28] < sum([toInt(b_ExplicitWithRepetition_Values[q18] = q28) | q18 : int(1..3), q18 <= 3]) /\ - (and([a_MOccurrence[q24] > 0 -> - a_MOccurrence[q24] = sum([toInt(b_ExplicitWithRepetition_Values[q20] = q24) | q20 : int(1..3), q20 <= 3]) - | q24 : int(1..2), q24 < q28]) - /\ - and([!or([a_MOccurrence[q23] > 0 /\ q23 = b_ExplicitWithRepetition_Values[q21] | q23 : int(1..2)]) /\ - b_ExplicitWithRepetition_Values[q21] < q28 - -> - a_MOccurrence[b_ExplicitWithRepetition_Values[q21]] = - sum([toInt(b_ExplicitWithRepetition_Values[q20] = b_ExplicitWithRepetition_Values[q21]) - | q20 : int(1..3), q20 <= 3]) - | q21 : int(1..3), q21 <= 3]))) - | q28 : int(1..2)]) - \/ - or([!or([a_MOccurrence[q27] > 0 /\ q27 = b_ExplicitWithRepetition_Values[q25] | q27 : int(1..2)]) /\ - (a_MOccurrence[b_ExplicitWithRepetition_Values[q25]] < - sum([toInt(b_ExplicitWithRepetition_Values[q18] = b_ExplicitWithRepetition_Values[q25]) - | q18 : int(1..3), q18 <= 3]) - /\ - (and([q24 < b_ExplicitWithRepetition_Values[q25] -> - (a_MOccurrence[q24] > 0 -> - a_MOccurrence[q24] = - sum([toInt(b_ExplicitWithRepetition_Values[q20] = q24) | q20 : int(1..3), q20 <= 3])) - | q24 : int(1..2)]) - /\ - and([!or([a_MOccurrence[q23] > 0 /\ q23 = b_ExplicitWithRepetition_Values[q21] | q23 : int(1..2)]) /\ - b_ExplicitWithRepetition_Values[q21] < b_ExplicitWithRepetition_Values[q25] - -> - a_MOccurrence[b_ExplicitWithRepetition_Values[q21]] = - sum([toInt(b_ExplicitWithRepetition_Values[q20] = b_ExplicitWithRepetition_Values[q21]) - | q20 : int(1..3), q20 <= 3]) - | q21 : int(1..3), q21 <= 3]))) - | q25 : int(1..3), q25 <= 3]), - 3 = sum([a_MOccurrence[q1] | q1 : int(1..2)]), - and([b_ExplicitWithRepetition_Values[q2] <= b_ExplicitWithRepetition_Values[q2 + 1] | q2 : int(1..2), q2 + 1 <= 3]), - 3 = sum([b_MOccurrence[q7] | q7 : int(1..2)]), - and([b_MOccurrence[q9] > 0 -> - b_MOccurrence[q9] = sum([toInt(b_ExplicitWithRepetition_Values[q11] = q9) | q11 : int(1..3), q11 <= 3]) - | q9 : int(1..2)]), - and([b_MOccurrence[b_ExplicitWithRepetition_Values[q12]] = - sum([toInt(b_ExplicitWithRepetition_Values[q14] = b_ExplicitWithRepetition_Values[q12]) - | q14 : int(1..3), q14 <= 3]) - | q12 : int(1..3), q12 <= 3]) - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_1_1-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_1_1-solution000001.solution deleted file mode 100644 index 5e2caa751c..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_1_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 2, 2) -letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_1_1-solution000002.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_1_1-solution000002.solution deleted file mode 100644 index 1b4b5b08a6..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_1_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 2, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_1_1-solution000003.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_1_1-solution000003.solution deleted file mode 100644 index 621d5f6edc..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_1_1-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 1, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_1_1-solution000004.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_1_1-solution000004.solution deleted file mode 100644 index 15472caf03..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_1_1-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 2, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_1_1-solution000005.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_1_1-solution000005.solution deleted file mode 100644 index ff56905e23..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_1_1-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_1_1-solution000006.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_1_1-solution000006.solution deleted file mode 100644 index d56a0bbcdc..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_1_1-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_1_1.eprime b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_1_1.eprime deleted file mode 100644 index f27369aa00..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_1_1.eprime +++ /dev/null @@ -1,62 +0,0 @@ -language ESSENCE' 1.0 - -find a_MOccurrence: matrix indexed by [int(1..2)] of int(0..3) -find a_ExplicitWithFlags_Flags: matrix indexed by [int(1..3)] of int(0..3) -find a_ExplicitWithFlags_Values: matrix indexed by [int(1..3)] of int(1..2) -find b_MOccurrence: matrix indexed by [int(1..2)] of int(0..3) -find b_ExplicitWithFlags_Flags: matrix indexed by [int(1..3)] of int(0..3) -find b_ExplicitWithFlags_Values: matrix indexed by [int(1..3)] of int(1..2) -branching on - [a_ExplicitWithFlags_Flags, a_ExplicitWithFlags_Values, a_MOccurrence, b_ExplicitWithFlags_Flags, - b_ExplicitWithFlags_Values, b_MOccurrence] -such that - or([a_MOccurrence[q33] > 0 /\ - (a_MOccurrence[q33] < b_MOccurrence[q33] /\ - (and([a_MOccurrence[q29] > 0 -> a_MOccurrence[q29] = b_MOccurrence[q29] | q29 : int(1..2), q29 < q33]) /\ - and([b_MOccurrence[q30] > 0 /\ !or([a_MOccurrence[q28] > 0 /\ q28 = q30 | q28 : int(1..2)]) -> - a_MOccurrence[q30] = b_MOccurrence[q30] - | q30 : int(1..2), q30 < q33]))) - | q33 : int(1..2)]) - \/ - or([b_MOccurrence[q34] > 0 /\ !or([a_MOccurrence[q32] > 0 /\ q32 = q34 | q32 : int(1..2)]) /\ - (a_MOccurrence[q34] < b_MOccurrence[q34] /\ - (and([a_MOccurrence[q29] > 0 -> a_MOccurrence[q29] = b_MOccurrence[q29] | q29 : int(1..2), q29 < q34]) /\ - and([b_MOccurrence[q30] > 0 /\ !or([a_MOccurrence[q28] > 0 /\ q28 = q30 | q28 : int(1..2)]) -> - a_MOccurrence[q30] = b_MOccurrence[q30] - | q30 : int(1..2), q30 < q34]))) - | q34 : int(1..2)]), - 3 = sum([a_MOccurrence[q1] | q1 : int(1..2)]), - 3 = sum([b_MOccurrence[q2] | q2 : int(1..2)]), - and([a_ExplicitWithFlags_Flags[q3 + 1] > 0 -> a_ExplicitWithFlags_Values[q3] < a_ExplicitWithFlags_Values[q3 + 1] - | q3 : int(1..2)]), - and([a_ExplicitWithFlags_Flags[q4] = 0 -> a_ExplicitWithFlags_Values[q4] = 1 | q4 : int(1..3)]), - and([a_ExplicitWithFlags_Flags[q5 + 1] > 0 -> a_ExplicitWithFlags_Flags[q5] > 0 | q5 : int(1..2)]), - 3 = sum([a_ExplicitWithFlags_Flags[q7] | q7 : int(1..3)]), - and([a_ExplicitWithFlags_Flags[q10] > 0 -> - sum([toInt(a_ExplicitWithFlags_Values[q11] = a_ExplicitWithFlags_Values[q10]) * - catchUndef(a_ExplicitWithFlags_Flags[q11], 0) - | q11 : int(1..3)]) - = a_MOccurrence[a_ExplicitWithFlags_Values[q10]] - | q10 : int(1..3)]), - and([a_MOccurrence[q12] > 0 -> - sum([toInt(a_ExplicitWithFlags_Values[q13] = q12) * catchUndef(a_ExplicitWithFlags_Flags[q13], 0) - | q13 : int(1..3)]) - = a_MOccurrence[q12] - | q12 : int(1..2)]), - and([b_ExplicitWithFlags_Flags[q14 + 1] > 0 -> b_ExplicitWithFlags_Values[q14] < b_ExplicitWithFlags_Values[q14 + 1] - | q14 : int(1..2)]), - and([b_ExplicitWithFlags_Flags[q15] = 0 -> b_ExplicitWithFlags_Values[q15] = 1 | q15 : int(1..3)]), - and([b_ExplicitWithFlags_Flags[q16 + 1] > 0 -> b_ExplicitWithFlags_Flags[q16] > 0 | q16 : int(1..2)]), - 3 = sum([b_ExplicitWithFlags_Flags[q18] | q18 : int(1..3)]), - and([b_ExplicitWithFlags_Flags[q21] > 0 -> - sum([toInt(b_ExplicitWithFlags_Values[q22] = b_ExplicitWithFlags_Values[q21]) * - catchUndef(b_ExplicitWithFlags_Flags[q22], 0) - | q22 : int(1..3)]) - = b_MOccurrence[b_ExplicitWithFlags_Values[q21]] - | q21 : int(1..3)]), - and([b_MOccurrence[q23] > 0 -> - sum([toInt(b_ExplicitWithFlags_Values[q24] = q23) * catchUndef(b_ExplicitWithFlags_Flags[q24], 0) - | q24 : int(1..3)]) - = b_MOccurrence[q23] - | q23 : int(1..2)]) - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_1_2-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_1_2-solution000001.solution deleted file mode 100644 index 1b4b5b08a6..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_1_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 2, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_1_2-solution000002.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_1_2-solution000002.solution deleted file mode 100644 index 5e2caa751c..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_1_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 2, 2) -letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_1_2-solution000003.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_1_2-solution000003.solution deleted file mode 100644 index 621d5f6edc..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_1_2-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 1, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_1_2-solution000004.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_1_2-solution000004.solution deleted file mode 100644 index d56a0bbcdc..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_1_2-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_1_2-solution000005.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_1_2-solution000005.solution deleted file mode 100644 index ff56905e23..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_1_2-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_1_2-solution000006.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_1_2-solution000006.solution deleted file mode 100644 index 15472caf03..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_1_2-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 2, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_1_2.eprime b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_1_2.eprime deleted file mode 100644 index b1d9dd3640..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_1_2.eprime +++ /dev/null @@ -1,55 +0,0 @@ -language ESSENCE' 1.0 - -find a_MOccurrence: matrix indexed by [int(1..2)] of int(0..3) -find a_ExplicitWithFlags_Flags: matrix indexed by [int(1..3)] of int(0..3) -find a_ExplicitWithFlags_Values: matrix indexed by [int(1..3)] of int(1..2) -find b_MOccurrence: matrix indexed by [int(1..2)] of int(0..3) -find b_ExplicitWithRepetition_Flag: int(3) -find b_ExplicitWithRepetition_Values: matrix indexed by [int(1..3)] of int(1..2) -branching on - [a_ExplicitWithFlags_Flags, a_ExplicitWithFlags_Values, a_MOccurrence, b_ExplicitWithRepetition_Flag, - b_ExplicitWithRepetition_Values, b_MOccurrence] -such that - or([a_MOccurrence[q34] > 0 /\ - (a_MOccurrence[q34] < b_MOccurrence[q34] /\ - (and([a_MOccurrence[q30] > 0 -> a_MOccurrence[q30] = b_MOccurrence[q30] | q30 : int(1..2), q30 < q34]) /\ - and([b_MOccurrence[q31] > 0 /\ !or([a_MOccurrence[q29] > 0 /\ q29 = q31 | q29 : int(1..2)]) -> - a_MOccurrence[q31] = b_MOccurrence[q31] - | q31 : int(1..2), q31 < q34]))) - | q34 : int(1..2)]) - \/ - or([b_MOccurrence[q35] > 0 /\ !or([a_MOccurrence[q33] > 0 /\ q33 = q35 | q33 : int(1..2)]) /\ - (a_MOccurrence[q35] < b_MOccurrence[q35] /\ - (and([a_MOccurrence[q30] > 0 -> a_MOccurrence[q30] = b_MOccurrence[q30] | q30 : int(1..2), q30 < q35]) /\ - and([b_MOccurrence[q31] > 0 /\ !or([a_MOccurrence[q29] > 0 /\ q29 = q31 | q29 : int(1..2)]) -> - a_MOccurrence[q31] = b_MOccurrence[q31] - | q31 : int(1..2), q31 < q35]))) - | q35 : int(1..2)]), - 3 = sum([a_MOccurrence[q1] | q1 : int(1..2)]), - 3 = sum([b_MOccurrence[q2] | q2 : int(1..2)]), - and([a_ExplicitWithFlags_Flags[q3 + 1] > 0 -> a_ExplicitWithFlags_Values[q3] < a_ExplicitWithFlags_Values[q3 + 1] - | q3 : int(1..2)]), - and([a_ExplicitWithFlags_Flags[q4] = 0 -> a_ExplicitWithFlags_Values[q4] = 1 | q4 : int(1..3)]), - and([a_ExplicitWithFlags_Flags[q5 + 1] > 0 -> a_ExplicitWithFlags_Flags[q5] > 0 | q5 : int(1..2)]), - 3 = sum([a_ExplicitWithFlags_Flags[q7] | q7 : int(1..3)]), - and([a_ExplicitWithFlags_Flags[q10] > 0 -> - sum([toInt(a_ExplicitWithFlags_Values[q11] = a_ExplicitWithFlags_Values[q10]) * - catchUndef(a_ExplicitWithFlags_Flags[q11], 0) - | q11 : int(1..3)]) - = a_MOccurrence[a_ExplicitWithFlags_Values[q10]] - | q10 : int(1..3)]), - and([a_MOccurrence[q12] > 0 -> - sum([toInt(a_ExplicitWithFlags_Values[q13] = q12) * catchUndef(a_ExplicitWithFlags_Flags[q13], 0) - | q13 : int(1..3)]) - = a_MOccurrence[q12] - | q12 : int(1..2)]), - and([b_ExplicitWithRepetition_Values[q14] <= b_ExplicitWithRepetition_Values[q14 + 1] - | q14 : int(1..2), q14 + 1 <= 3]), - and([sum([toInt(b_ExplicitWithRepetition_Values[q22] = b_ExplicitWithRepetition_Values[q20]) - | q22 : int(1..3), q22 <= 3]) - = b_MOccurrence[b_ExplicitWithRepetition_Values[q20]] - | q20 : int(1..3), q20 <= 3]), - and([b_MOccurrence[q23] > 0 -> - sum([toInt(b_ExplicitWithRepetition_Values[q25] = q23) | q25 : int(1..3), q25 <= 3]) = b_MOccurrence[q23] - | q23 : int(1..2)]) - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_1_3-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_1_3-solution000001.solution deleted file mode 100644 index 5e2caa751c..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_1_3-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 2, 2) -letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_1_3-solution000002.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_1_3-solution000002.solution deleted file mode 100644 index 1b4b5b08a6..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_1_3-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 2, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_1_3-solution000003.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_1_3-solution000003.solution deleted file mode 100644 index 621d5f6edc..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_1_3-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 1, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_1_3-solution000004.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_1_3-solution000004.solution deleted file mode 100644 index 15472caf03..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_1_3-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 2, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_1_3-solution000005.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_1_3-solution000005.solution deleted file mode 100644 index ff56905e23..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_1_3-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_1_3-solution000006.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_1_3-solution000006.solution deleted file mode 100644 index d56a0bbcdc..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_1_3-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_1_3.eprime b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_1_3.eprime deleted file mode 100644 index f2643ff7c9..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_1_3.eprime +++ /dev/null @@ -1,42 +0,0 @@ -language ESSENCE' 1.0 - -find a_MOccurrence: matrix indexed by [int(1..2)] of int(0..3) -find a_ExplicitWithFlags_Flags: matrix indexed by [int(1..3)] of int(0..3) -find a_ExplicitWithFlags_Values: matrix indexed by [int(1..3)] of int(1..2) -find b_MOccurrence: matrix indexed by [int(1..2)] of int(0..3) -branching on [a_ExplicitWithFlags_Flags, a_ExplicitWithFlags_Values, a_MOccurrence, b_MOccurrence] -such that - or([a_MOccurrence[q22] > 0 /\ - (a_MOccurrence[q22] < b_MOccurrence[q22] /\ - (and([a_MOccurrence[q18] > 0 -> a_MOccurrence[q18] = b_MOccurrence[q18] | q18 : int(1..2), q18 < q22]) /\ - and([b_MOccurrence[q19] > 0 /\ !or([a_MOccurrence[q17] > 0 /\ q17 = q19 | q17 : int(1..2)]) -> - a_MOccurrence[q19] = b_MOccurrence[q19] - | q19 : int(1..2), q19 < q22]))) - | q22 : int(1..2)]) - \/ - or([b_MOccurrence[q23] > 0 /\ !or([a_MOccurrence[q21] > 0 /\ q21 = q23 | q21 : int(1..2)]) /\ - (a_MOccurrence[q23] < b_MOccurrence[q23] /\ - (and([a_MOccurrence[q18] > 0 -> a_MOccurrence[q18] = b_MOccurrence[q18] | q18 : int(1..2), q18 < q23]) /\ - and([b_MOccurrence[q19] > 0 /\ !or([a_MOccurrence[q17] > 0 /\ q17 = q19 | q17 : int(1..2)]) -> - a_MOccurrence[q19] = b_MOccurrence[q19] - | q19 : int(1..2), q19 < q23]))) - | q23 : int(1..2)]), - 3 = sum([a_MOccurrence[q1] | q1 : int(1..2)]), - 3 = sum([b_MOccurrence[q2] | q2 : int(1..2)]), - and([a_ExplicitWithFlags_Flags[q3 + 1] > 0 -> a_ExplicitWithFlags_Values[q3] < a_ExplicitWithFlags_Values[q3 + 1] - | q3 : int(1..2)]), - and([a_ExplicitWithFlags_Flags[q4] = 0 -> a_ExplicitWithFlags_Values[q4] = 1 | q4 : int(1..3)]), - and([a_ExplicitWithFlags_Flags[q5 + 1] > 0 -> a_ExplicitWithFlags_Flags[q5] > 0 | q5 : int(1..2)]), - 3 = sum([a_ExplicitWithFlags_Flags[q7] | q7 : int(1..3)]), - and([a_ExplicitWithFlags_Flags[q10] > 0 -> - sum([toInt(a_ExplicitWithFlags_Values[q11] = a_ExplicitWithFlags_Values[q10]) * - catchUndef(a_ExplicitWithFlags_Flags[q11], 0) - | q11 : int(1..3)]) - = a_MOccurrence[a_ExplicitWithFlags_Values[q10]] - | q10 : int(1..3)]), - and([a_MOccurrence[q12] > 0 -> - sum([toInt(a_ExplicitWithFlags_Values[q13] = q12) * catchUndef(a_ExplicitWithFlags_Flags[q13], 0) - | q13 : int(1..3)]) - = a_MOccurrence[q12] - | q12 : int(1..2)]) - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_2_1-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_2_1-solution000001.solution deleted file mode 100644 index 621d5f6edc..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_2_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 1, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_2_1-solution000002.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_2_1-solution000002.solution deleted file mode 100644 index 5e2caa751c..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_2_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 2, 2) -letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_2_1-solution000003.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_2_1-solution000003.solution deleted file mode 100644 index 1b4b5b08a6..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_2_1-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 2, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_2_1-solution000004.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_2_1-solution000004.solution deleted file mode 100644 index 15472caf03..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_2_1-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 2, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_2_1-solution000005.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_2_1-solution000005.solution deleted file mode 100644 index ff56905e23..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_2_1-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_2_1-solution000006.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_2_1-solution000006.solution deleted file mode 100644 index d56a0bbcdc..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_2_1-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_2_1.eprime b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_2_1.eprime deleted file mode 100644 index f6db853769..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_2_1.eprime +++ /dev/null @@ -1,54 +0,0 @@ -language ESSENCE' 1.0 - -find a_MOccurrence: matrix indexed by [int(1..2)] of int(0..3) -find a_ExplicitWithRepetition_Flag: int(3) -find a_ExplicitWithRepetition_Values: matrix indexed by [int(1..3)] of int(1..2) -find b_MOccurrence: matrix indexed by [int(1..2)] of int(0..3) -find b_ExplicitWithFlags_Flags: matrix indexed by [int(1..3)] of int(0..3) -find b_ExplicitWithFlags_Values: matrix indexed by [int(1..3)] of int(1..2) -branching on - [a_ExplicitWithRepetition_Flag, a_ExplicitWithRepetition_Values, a_MOccurrence, b_ExplicitWithFlags_Flags, - b_ExplicitWithFlags_Values, b_MOccurrence] -such that - or([a_MOccurrence[q34] > 0 /\ - (a_MOccurrence[q34] < b_MOccurrence[q34] /\ - (and([a_MOccurrence[q30] > 0 -> a_MOccurrence[q30] = b_MOccurrence[q30] | q30 : int(1..2), q30 < q34]) /\ - and([b_MOccurrence[q31] > 0 /\ !or([a_MOccurrence[q29] > 0 /\ q29 = q31 | q29 : int(1..2)]) -> - a_MOccurrence[q31] = b_MOccurrence[q31] - | q31 : int(1..2), q31 < q34]))) - | q34 : int(1..2)]) - \/ - or([b_MOccurrence[q35] > 0 /\ !or([a_MOccurrence[q33] > 0 /\ q33 = q35 | q33 : int(1..2)]) /\ - (a_MOccurrence[q35] < b_MOccurrence[q35] /\ - (and([a_MOccurrence[q30] > 0 -> a_MOccurrence[q30] = b_MOccurrence[q30] | q30 : int(1..2), q30 < q35]) /\ - and([b_MOccurrence[q31] > 0 /\ !or([a_MOccurrence[q29] > 0 /\ q29 = q31 | q29 : int(1..2)]) -> - a_MOccurrence[q31] = b_MOccurrence[q31] - | q31 : int(1..2), q31 < q35]))) - | q35 : int(1..2)]), - 3 = sum([a_MOccurrence[q1] | q1 : int(1..2)]), - 3 = sum([b_MOccurrence[q2] | q2 : int(1..2)]), - and([a_ExplicitWithRepetition_Values[q3] <= a_ExplicitWithRepetition_Values[q3 + 1] | q3 : int(1..2), q3 + 1 <= 3]), - and([sum([toInt(a_ExplicitWithRepetition_Values[q11] = a_ExplicitWithRepetition_Values[q9]) - | q11 : int(1..3), q11 <= 3]) - = a_MOccurrence[a_ExplicitWithRepetition_Values[q9]] - | q9 : int(1..3), q9 <= 3]), - and([a_MOccurrence[q12] > 0 -> - sum([toInt(a_ExplicitWithRepetition_Values[q14] = q12) | q14 : int(1..3), q14 <= 3]) = a_MOccurrence[q12] - | q12 : int(1..2)]), - and([b_ExplicitWithFlags_Flags[q15 + 1] > 0 -> b_ExplicitWithFlags_Values[q15] < b_ExplicitWithFlags_Values[q15 + 1] - | q15 : int(1..2)]), - and([b_ExplicitWithFlags_Flags[q16] = 0 -> b_ExplicitWithFlags_Values[q16] = 1 | q16 : int(1..3)]), - and([b_ExplicitWithFlags_Flags[q17 + 1] > 0 -> b_ExplicitWithFlags_Flags[q17] > 0 | q17 : int(1..2)]), - 3 = sum([b_ExplicitWithFlags_Flags[q19] | q19 : int(1..3)]), - and([b_ExplicitWithFlags_Flags[q22] > 0 -> - sum([toInt(b_ExplicitWithFlags_Values[q23] = b_ExplicitWithFlags_Values[q22]) * - catchUndef(b_ExplicitWithFlags_Flags[q23], 0) - | q23 : int(1..3)]) - = b_MOccurrence[b_ExplicitWithFlags_Values[q22]] - | q22 : int(1..3)]), - and([b_MOccurrence[q24] > 0 -> - sum([toInt(b_ExplicitWithFlags_Values[q25] = q24) * catchUndef(b_ExplicitWithFlags_Flags[q25], 0) - | q25 : int(1..3)]) - = b_MOccurrence[q24] - | q24 : int(1..2)]) - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_2_2-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_2_2-solution000001.solution deleted file mode 100644 index 621d5f6edc..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_2_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 1, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_2_2-solution000002.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_2_2-solution000002.solution deleted file mode 100644 index 1b4b5b08a6..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_2_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 2, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_2_2-solution000003.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_2_2-solution000003.solution deleted file mode 100644 index 5e2caa751c..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_2_2-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 2, 2) -letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_2_2-solution000004.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_2_2-solution000004.solution deleted file mode 100644 index d56a0bbcdc..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_2_2-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_2_2-solution000005.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_2_2-solution000005.solution deleted file mode 100644 index ff56905e23..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_2_2-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_2_2-solution000006.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_2_2-solution000006.solution deleted file mode 100644 index 15472caf03..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_2_2-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 2, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_2_2.eprime b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_2_2.eprime deleted file mode 100644 index 3433c44d83..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_2_2.eprime +++ /dev/null @@ -1,47 +0,0 @@ -language ESSENCE' 1.0 - -find a_MOccurrence: matrix indexed by [int(1..2)] of int(0..3) -find a_ExplicitWithRepetition_Flag: int(3) -find a_ExplicitWithRepetition_Values: matrix indexed by [int(1..3)] of int(1..2) -find b_MOccurrence: matrix indexed by [int(1..2)] of int(0..3) -find b_ExplicitWithRepetition_Flag: int(3) -find b_ExplicitWithRepetition_Values: matrix indexed by [int(1..3)] of int(1..2) -branching on - [a_ExplicitWithRepetition_Flag, a_ExplicitWithRepetition_Values, a_MOccurrence, b_ExplicitWithRepetition_Flag, - b_ExplicitWithRepetition_Values, b_MOccurrence] -such that - or([a_MOccurrence[q35] > 0 /\ - (a_MOccurrence[q35] < b_MOccurrence[q35] /\ - (and([a_MOccurrence[q31] > 0 -> a_MOccurrence[q31] = b_MOccurrence[q31] | q31 : int(1..2), q31 < q35]) /\ - and([b_MOccurrence[q32] > 0 /\ !or([a_MOccurrence[q30] > 0 /\ q30 = q32 | q30 : int(1..2)]) -> - a_MOccurrence[q32] = b_MOccurrence[q32] - | q32 : int(1..2), q32 < q35]))) - | q35 : int(1..2)]) - \/ - or([b_MOccurrence[q36] > 0 /\ !or([a_MOccurrence[q34] > 0 /\ q34 = q36 | q34 : int(1..2)]) /\ - (a_MOccurrence[q36] < b_MOccurrence[q36] /\ - (and([a_MOccurrence[q31] > 0 -> a_MOccurrence[q31] = b_MOccurrence[q31] | q31 : int(1..2), q31 < q36]) /\ - and([b_MOccurrence[q32] > 0 /\ !or([a_MOccurrence[q30] > 0 /\ q30 = q32 | q30 : int(1..2)]) -> - a_MOccurrence[q32] = b_MOccurrence[q32] - | q32 : int(1..2), q32 < q36]))) - | q36 : int(1..2)]), - 3 = sum([a_MOccurrence[q1] | q1 : int(1..2)]), - 3 = sum([b_MOccurrence[q2] | q2 : int(1..2)]), - and([a_ExplicitWithRepetition_Values[q3] <= a_ExplicitWithRepetition_Values[q3 + 1] | q3 : int(1..2), q3 + 1 <= 3]), - and([sum([toInt(a_ExplicitWithRepetition_Values[q11] = a_ExplicitWithRepetition_Values[q9]) - | q11 : int(1..3), q11 <= 3]) - = a_MOccurrence[a_ExplicitWithRepetition_Values[q9]] - | q9 : int(1..3), q9 <= 3]), - and([a_MOccurrence[q12] > 0 -> - sum([toInt(a_ExplicitWithRepetition_Values[q14] = q12) | q14 : int(1..3), q14 <= 3]) = a_MOccurrence[q12] - | q12 : int(1..2)]), - and([b_ExplicitWithRepetition_Values[q15] <= b_ExplicitWithRepetition_Values[q15 + 1] - | q15 : int(1..2), q15 + 1 <= 3]), - and([sum([toInt(b_ExplicitWithRepetition_Values[q23] = b_ExplicitWithRepetition_Values[q21]) - | q23 : int(1..3), q23 <= 3]) - = b_MOccurrence[b_ExplicitWithRepetition_Values[q21]] - | q21 : int(1..3), q21 <= 3]), - and([b_MOccurrence[q24] > 0 -> - sum([toInt(b_ExplicitWithRepetition_Values[q26] = q24) | q26 : int(1..3), q26 <= 3]) = b_MOccurrence[q24] - | q24 : int(1..2)]) - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_2_3-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_2_3-solution000001.solution deleted file mode 100644 index 621d5f6edc..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_2_3-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 1, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_2_3-solution000002.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_2_3-solution000002.solution deleted file mode 100644 index 5e2caa751c..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_2_3-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 2, 2) -letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_2_3-solution000003.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_2_3-solution000003.solution deleted file mode 100644 index 1b4b5b08a6..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_2_3-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 2, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_2_3-solution000004.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_2_3-solution000004.solution deleted file mode 100644 index 15472caf03..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_2_3-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 2, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_2_3-solution000005.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_2_3-solution000005.solution deleted file mode 100644 index ff56905e23..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_2_3-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_2_3-solution000006.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_2_3-solution000006.solution deleted file mode 100644 index d56a0bbcdc..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_2_3-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_2_3.eprime b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_2_3.eprime deleted file mode 100644 index fe7f6d1d79..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_2_3.eprime +++ /dev/null @@ -1,34 +0,0 @@ -language ESSENCE' 1.0 - -find a_MOccurrence: matrix indexed by [int(1..2)] of int(0..3) -find a_ExplicitWithRepetition_Flag: int(3) -find a_ExplicitWithRepetition_Values: matrix indexed by [int(1..3)] of int(1..2) -find b_MOccurrence: matrix indexed by [int(1..2)] of int(0..3) -branching on [a_ExplicitWithRepetition_Flag, a_ExplicitWithRepetition_Values, a_MOccurrence, b_MOccurrence] -such that - or([a_MOccurrence[q23] > 0 /\ - (a_MOccurrence[q23] < b_MOccurrence[q23] /\ - (and([a_MOccurrence[q19] > 0 -> a_MOccurrence[q19] = b_MOccurrence[q19] | q19 : int(1..2), q19 < q23]) /\ - and([b_MOccurrence[q20] > 0 /\ !or([a_MOccurrence[q18] > 0 /\ q18 = q20 | q18 : int(1..2)]) -> - a_MOccurrence[q20] = b_MOccurrence[q20] - | q20 : int(1..2), q20 < q23]))) - | q23 : int(1..2)]) - \/ - or([b_MOccurrence[q24] > 0 /\ !or([a_MOccurrence[q22] > 0 /\ q22 = q24 | q22 : int(1..2)]) /\ - (a_MOccurrence[q24] < b_MOccurrence[q24] /\ - (and([a_MOccurrence[q19] > 0 -> a_MOccurrence[q19] = b_MOccurrence[q19] | q19 : int(1..2), q19 < q24]) /\ - and([b_MOccurrence[q20] > 0 /\ !or([a_MOccurrence[q18] > 0 /\ q18 = q20 | q18 : int(1..2)]) -> - a_MOccurrence[q20] = b_MOccurrence[q20] - | q20 : int(1..2), q20 < q24]))) - | q24 : int(1..2)]), - 3 = sum([a_MOccurrence[q1] | q1 : int(1..2)]), - 3 = sum([b_MOccurrence[q2] | q2 : int(1..2)]), - and([a_ExplicitWithRepetition_Values[q3] <= a_ExplicitWithRepetition_Values[q3 + 1] | q3 : int(1..2), q3 + 1 <= 3]), - and([sum([toInt(a_ExplicitWithRepetition_Values[q11] = a_ExplicitWithRepetition_Values[q9]) - | q11 : int(1..3), q11 <= 3]) - = a_MOccurrence[a_ExplicitWithRepetition_Values[q9]] - | q9 : int(1..3), q9 <= 3]), - and([a_MOccurrence[q12] > 0 -> - sum([toInt(a_ExplicitWithRepetition_Values[q14] = q12) | q14 : int(1..3), q14 <= 3]) = a_MOccurrence[q12] - | q12 : int(1..2)]) - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_3_1-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_3_1-solution000001.solution deleted file mode 100644 index 15472caf03..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_3_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 2, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_3_1-solution000002.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_3_1-solution000002.solution deleted file mode 100644 index ff56905e23..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_3_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_3_1-solution000003.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_3_1-solution000003.solution deleted file mode 100644 index d56a0bbcdc..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_3_1-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_3_1-solution000004.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_3_1-solution000004.solution deleted file mode 100644 index 5e2caa751c..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_3_1-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 2, 2) -letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_3_1-solution000005.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_3_1-solution000005.solution deleted file mode 100644 index 1b4b5b08a6..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_3_1-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 2, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_3_1-solution000006.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_3_1-solution000006.solution deleted file mode 100644 index 621d5f6edc..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_3_1-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 1, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_3_1.eprime b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_3_1.eprime deleted file mode 100644 index 5c108dd064..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_3_1.eprime +++ /dev/null @@ -1,42 +0,0 @@ -language ESSENCE' 1.0 - -find a_MOccurrence: matrix indexed by [int(1..2)] of int(0..3) -find b_MOccurrence: matrix indexed by [int(1..2)] of int(0..3) -find b_ExplicitWithFlags_Flags: matrix indexed by [int(1..3)] of int(0..3) -find b_ExplicitWithFlags_Values: matrix indexed by [int(1..3)] of int(1..2) -branching on [a_MOccurrence, b_ExplicitWithFlags_Flags, b_ExplicitWithFlags_Values, b_MOccurrence] -such that - or([a_MOccurrence[q22] > 0 /\ - (a_MOccurrence[q22] < b_MOccurrence[q22] /\ - (and([a_MOccurrence[q18] > 0 -> a_MOccurrence[q18] = b_MOccurrence[q18] | q18 : int(1..2), q18 < q22]) /\ - and([b_MOccurrence[q19] > 0 /\ !or([a_MOccurrence[q17] > 0 /\ q17 = q19 | q17 : int(1..2)]) -> - a_MOccurrence[q19] = b_MOccurrence[q19] - | q19 : int(1..2), q19 < q22]))) - | q22 : int(1..2)]) - \/ - or([b_MOccurrence[q23] > 0 /\ !or([a_MOccurrence[q21] > 0 /\ q21 = q23 | q21 : int(1..2)]) /\ - (a_MOccurrence[q23] < b_MOccurrence[q23] /\ - (and([a_MOccurrence[q18] > 0 -> a_MOccurrence[q18] = b_MOccurrence[q18] | q18 : int(1..2), q18 < q23]) /\ - and([b_MOccurrence[q19] > 0 /\ !or([a_MOccurrence[q17] > 0 /\ q17 = q19 | q17 : int(1..2)]) -> - a_MOccurrence[q19] = b_MOccurrence[q19] - | q19 : int(1..2), q19 < q23]))) - | q23 : int(1..2)]), - 3 = sum([a_MOccurrence[q1] | q1 : int(1..2)]), - 3 = sum([b_MOccurrence[q2] | q2 : int(1..2)]), - and([b_ExplicitWithFlags_Flags[q3 + 1] > 0 -> b_ExplicitWithFlags_Values[q3] < b_ExplicitWithFlags_Values[q3 + 1] - | q3 : int(1..2)]), - and([b_ExplicitWithFlags_Flags[q4] = 0 -> b_ExplicitWithFlags_Values[q4] = 1 | q4 : int(1..3)]), - and([b_ExplicitWithFlags_Flags[q5 + 1] > 0 -> b_ExplicitWithFlags_Flags[q5] > 0 | q5 : int(1..2)]), - 3 = sum([b_ExplicitWithFlags_Flags[q7] | q7 : int(1..3)]), - and([b_ExplicitWithFlags_Flags[q10] > 0 -> - sum([toInt(b_ExplicitWithFlags_Values[q11] = b_ExplicitWithFlags_Values[q10]) * - catchUndef(b_ExplicitWithFlags_Flags[q11], 0) - | q11 : int(1..3)]) - = b_MOccurrence[b_ExplicitWithFlags_Values[q10]] - | q10 : int(1..3)]), - and([b_MOccurrence[q12] > 0 -> - sum([toInt(b_ExplicitWithFlags_Values[q13] = q12) * catchUndef(b_ExplicitWithFlags_Flags[q13], 0) - | q13 : int(1..3)]) - = b_MOccurrence[q12] - | q12 : int(1..2)]) - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_3_2-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_3_2-solution000001.solution deleted file mode 100644 index d56a0bbcdc..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_3_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_3_2-solution000002.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_3_2-solution000002.solution deleted file mode 100644 index ff56905e23..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_3_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_3_2-solution000003.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_3_2-solution000003.solution deleted file mode 100644 index 15472caf03..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_3_2-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 2, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_3_2-solution000004.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_3_2-solution000004.solution deleted file mode 100644 index 1b4b5b08a6..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_3_2-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 2, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_3_2-solution000005.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_3_2-solution000005.solution deleted file mode 100644 index 5e2caa751c..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_3_2-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 2, 2) -letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_3_2-solution000006.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_3_2-solution000006.solution deleted file mode 100644 index 621d5f6edc..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_3_2-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 1, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_3_2.eprime b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_3_2.eprime deleted file mode 100644 index fbd4f2c5d9..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_3_2.eprime +++ /dev/null @@ -1,34 +0,0 @@ -language ESSENCE' 1.0 - -find a_MOccurrence: matrix indexed by [int(1..2)] of int(0..3) -find b_MOccurrence: matrix indexed by [int(1..2)] of int(0..3) -find b_ExplicitWithRepetition_Flag: int(3) -find b_ExplicitWithRepetition_Values: matrix indexed by [int(1..3)] of int(1..2) -branching on [a_MOccurrence, b_ExplicitWithRepetition_Flag, b_ExplicitWithRepetition_Values, b_MOccurrence] -such that - or([a_MOccurrence[q23] > 0 /\ - (a_MOccurrence[q23] < b_MOccurrence[q23] /\ - (and([a_MOccurrence[q19] > 0 -> a_MOccurrence[q19] = b_MOccurrence[q19] | q19 : int(1..2), q19 < q23]) /\ - and([b_MOccurrence[q20] > 0 /\ !or([a_MOccurrence[q18] > 0 /\ q18 = q20 | q18 : int(1..2)]) -> - a_MOccurrence[q20] = b_MOccurrence[q20] - | q20 : int(1..2), q20 < q23]))) - | q23 : int(1..2)]) - \/ - or([b_MOccurrence[q24] > 0 /\ !or([a_MOccurrence[q22] > 0 /\ q22 = q24 | q22 : int(1..2)]) /\ - (a_MOccurrence[q24] < b_MOccurrence[q24] /\ - (and([a_MOccurrence[q19] > 0 -> a_MOccurrence[q19] = b_MOccurrence[q19] | q19 : int(1..2), q19 < q24]) /\ - and([b_MOccurrence[q20] > 0 /\ !or([a_MOccurrence[q18] > 0 /\ q18 = q20 | q18 : int(1..2)]) -> - a_MOccurrence[q20] = b_MOccurrence[q20] - | q20 : int(1..2), q20 < q24]))) - | q24 : int(1..2)]), - 3 = sum([a_MOccurrence[q1] | q1 : int(1..2)]), - 3 = sum([b_MOccurrence[q2] | q2 : int(1..2)]), - and([b_ExplicitWithRepetition_Values[q3] <= b_ExplicitWithRepetition_Values[q3 + 1] | q3 : int(1..2), q3 + 1 <= 3]), - and([sum([toInt(b_ExplicitWithRepetition_Values[q11] = b_ExplicitWithRepetition_Values[q9]) - | q11 : int(1..3), q11 <= 3]) - = b_MOccurrence[b_ExplicitWithRepetition_Values[q9]] - | q9 : int(1..3), q9 <= 3]), - and([b_MOccurrence[q12] > 0 -> - sum([toInt(b_ExplicitWithRepetition_Values[q14] = q12) | q14 : int(1..3), q14 <= 3]) = b_MOccurrence[q12] - | q12 : int(1..2)]) - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_3_3-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_3_3-solution000001.solution deleted file mode 100644 index 15472caf03..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_3_3-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 2, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_3_3-solution000002.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_3_3-solution000002.solution deleted file mode 100644 index ff56905e23..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_3_3-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_3_3-solution000003.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_3_3-solution000003.solution deleted file mode 100644 index d56a0bbcdc..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_3_3-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(2, 2, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_3_3-solution000004.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_3_3-solution000004.solution deleted file mode 100644 index 5e2caa751c..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_3_3-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 2, 2) -letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_3_3-solution000005.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_3_3-solution000005.solution deleted file mode 100644 index 1b4b5b08a6..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_3_3-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 2, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_3_3-solution000006.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_3_3-solution000006.solution deleted file mode 100644 index 621d5f6edc..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_3_3-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be mset(1, 1, 2) -letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_3_3.eprime b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_3_3.eprime deleted file mode 100644 index 735a032370..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_3_3.eprime +++ /dev/null @@ -1,24 +0,0 @@ -language ESSENCE' 1.0 - -find a_MOccurrence: matrix indexed by [int(1..2)] of int(0..3) -find b_MOccurrence: matrix indexed by [int(1..2)] of int(0..3) -branching on [a_MOccurrence, b_MOccurrence] -such that - or([a_MOccurrence[q11] > 0 /\ - (a_MOccurrence[q11] < b_MOccurrence[q11] /\ - (and([a_MOccurrence[q7] > 0 -> a_MOccurrence[q7] = b_MOccurrence[q7] | q7 : int(1..2), q7 < q11]) /\ - and([b_MOccurrence[q8] > 0 /\ !or([a_MOccurrence[q6] > 0 /\ q6 = q8 | q6 : int(1..2)]) -> - a_MOccurrence[q8] = b_MOccurrence[q8] - | q8 : int(1..2), q8 < q11]))) - | q11 : int(1..2)]) - \/ - or([b_MOccurrence[q12] > 0 /\ !or([a_MOccurrence[q10] > 0 /\ q10 = q12 | q10 : int(1..2)]) /\ - (a_MOccurrence[q12] < b_MOccurrence[q12] /\ - (and([a_MOccurrence[q7] > 0 -> a_MOccurrence[q7] = b_MOccurrence[q7] | q7 : int(1..2), q7 < q12]) /\ - and([b_MOccurrence[q8] > 0 /\ !or([a_MOccurrence[q6] > 0 /\ q6 = q8 | q6 : int(1..2)]) -> - a_MOccurrence[q8] = b_MOccurrence[q8] - | q8 : int(1..2), q8 < q12]))) - | q12 : int(1..2)]), - 3 = sum([a_MOccurrence[q1] | q1 : int(1..2)]), - 3 = sum([b_MOccurrence[q2] | q2 : int(1..2)]) - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_1_1-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_1_1-solution000001.solution deleted file mode 100644 index cde05d5274..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_1_1-solution000001.solution +++ /dev/null @@ -1,11 +0,0 @@ -language Essence 1.3 - -letting a be partition({1, 2}) -$ Visualisation for a -$ 1 2 - -letting b be partition({1}, {2}) -$ Visualisation for b -$ 1 -$ 2 - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_1_1.eprime b/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_1_1.eprime deleted file mode 100644 index 5999cb42ac..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_1_1.eprime +++ /dev/null @@ -1,324 +0,0 @@ -language ESSENCE' 1.0 - -find a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker: int(0..2) -find a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence: matrix indexed by [int(1..2), int(1..2)] of bool -find b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker: int(0..2) -find b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence: matrix indexed by [int(1..2), int(1..2)] of bool -branching on - [a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker, - a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence, - b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker, - b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence] -such that - or([q36 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ - (toInt(or([q95 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ - and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q95, q96] = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q36, q96] - | q96 : int(1..2)]) - | q95 : int(1..2)])) - < - toInt(or([q100 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ - and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q100, q101] = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q36, q101] - | q101 : int(1..2)]) - | q100 : int(1..2)])) - /\ - (and([q104 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ - (or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q104, q137] /\ - (toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q104, q137]) < - toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q36, q137]) - /\ - (and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q104, q138] -> - toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q104, q138]) = - toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q36, q138]) - | q138 : int(1..2), q138 < q137]) - /\ - and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q36, q138] /\ - !or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q104, q141] /\ - q141 = q138 - | q141 : int(1..2)]) - -> - toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q104, q138]) = - toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q36, q138]) - | q138 : int(1..2), q138 < q137]))) - | q137 : int(1..2)]) - \/ - or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q36, q137] /\ - !or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q104, q140] /\ q140 = q137 - | q140 : int(1..2)]) - /\ - (toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q104, q137]) < - toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q36, q137]) - /\ - (and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q104, q138] -> - toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q104, q138]) = - toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q36, q138]) - | q138 : int(1..2), q138 < q137]) - /\ - and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q36, q138] /\ - !or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q104, q139] /\ - q139 = q138 - | q139 : int(1..2)]) - -> - toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q104, q138]) = - toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q36, q138]) - | q138 : int(1..2), q138 < q137]))) - | q137 : int(1..2)])) - -> - toInt(or([q129 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ - and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q129, q130] = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q104, q130] - | q130 : int(1..2)]) - | q129 : int(1..2)])) - = - toInt(or([q134 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ - and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q134, q135] = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q104, q135] - | q135 : int(1..2)]) - | q134 : int(1..2)])) - | q104 : int(1..2)]) - /\ - and([and([q106 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker, - !or([q119 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ - and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q119, q120] = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q106, q120] - | q120 : int(1..2)]) - | q119 : int(1..2)]), - or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q106, q122] /\ - (toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q106, q122]) < - toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q36, q122]) - /\ - (and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q106, q123] -> - toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q106, q123]) = - toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q36, q123]) - | q123 : int(1..2), q123 < q122]) - /\ - and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q36, q123] /\ - !or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q106, q126] /\ - q126 = q123 - | q126 : int(1..2)]) - -> - toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q106, q123]) = - toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q36, q123]) - | q123 : int(1..2), q123 < q122]))) - | q122 : int(1..2)]) - \/ - or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q36, q122] /\ - !or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q106, q125] /\ q125 = q122 - | q125 : int(1..2)]) - /\ - (toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q106, q122]) < - toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q36, q122]) - /\ - (and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q106, q123] -> - toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q106, q123]) = - toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q36, q123]) - | q123 : int(1..2), q123 < q122]) - /\ - and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q36, q123] /\ - !or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q106, q124] /\ - q124 = q123 - | q124 : int(1..2)]) - -> - toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q106, q123]) = - toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q36, q123]) - | q123 : int(1..2), q123 < q122]))) - | q122 : int(1..2)]); - int(1..3)]) - -> - toInt(or([q109 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ - and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q109, q110] = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q106, q110] - | q110 : int(1..2)]) - | q109 : int(1..2)])) - = - toInt(or([q114 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ - and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q114, q115] = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q106, q115] - | q115 : int(1..2)]) - | q114 : int(1..2)])) - | q106 : int(1..2)]))) - | q36 : int(1..2)]) - \/ - or([q38 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ - !or([q90 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ - and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q90, q91] = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q38, q91] - | q91 : int(1..2)]) - | q90 : int(1..2)]) - /\ - (toInt(or([q41 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ - and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q41, q42] = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q38, q42] - | q42 : int(1..2)]) - | q41 : int(1..2)])) - < - toInt(or([q46 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ - and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q46, q47] = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q38, q47] - | q47 : int(1..2)]) - | q46 : int(1..2)])) - /\ - (and([q50 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ - (or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q50, q83] /\ - (toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q50, q83]) < - toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q38, q83]) - /\ - (and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q50, q84] -> - toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q50, q84]) = - toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q38, q84]) - | q84 : int(1..2), q84 < q83]) - /\ - and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q38, q84] /\ - !or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q50, q87] /\ q87 = q84 - | q87 : int(1..2)]) - -> - toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q50, q84]) = - toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q38, q84]) - | q84 : int(1..2), q84 < q83]))) - | q83 : int(1..2)]) - \/ - or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q38, q83] /\ - !or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q50, q86] /\ q86 = q83 - | q86 : int(1..2)]) - /\ - (toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q50, q83]) < - toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q38, q83]) - /\ - (and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q50, q84] -> - toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q50, q84]) = - toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q38, q84]) - | q84 : int(1..2), q84 < q83]) - /\ - and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q38, q84] /\ - !or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q50, q85] /\ q85 = q84 - | q85 : int(1..2)]) - -> - toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q50, q84]) = - toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q38, q84]) - | q84 : int(1..2), q84 < q83]))) - | q83 : int(1..2)])) - -> - toInt(or([q75 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ - and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q75, q76] = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q50, q76] - | q76 : int(1..2)]) - | q75 : int(1..2)])) - = - toInt(or([q80 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ - and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q80, q81] = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q50, q81] - | q81 : int(1..2)]) - | q80 : int(1..2)])) - | q50 : int(1..2)]) - /\ - and([and([q52 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker, - !or([q65 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ - and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q65, q66] = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q52, q66] - | q66 : int(1..2)]) - | q65 : int(1..2)]), - or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q52, q68] /\ - (toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q52, q68]) < - toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q38, q68]) - /\ - (and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q52, q69] -> - toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q52, q69]) = - toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q38, q69]) - | q69 : int(1..2), q69 < q68]) - /\ - and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q38, q69] /\ - !or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q52, q72] /\ - q72 = q69 - | q72 : int(1..2)]) - -> - toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q52, q69]) = - toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q38, q69]) - | q69 : int(1..2), q69 < q68]))) - | q68 : int(1..2)]) - \/ - or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q38, q68] /\ - !or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q52, q71] /\ q71 = q68 - | q71 : int(1..2)]) - /\ - (toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q52, q68]) < - toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q38, q68]) - /\ - (and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q52, q69] -> - toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q52, q69]) = - toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q38, q69]) - | q69 : int(1..2), q69 < q68]) - /\ - and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q38, q69] /\ - !or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q52, q70] /\ - q70 = q69 - | q70 : int(1..2)]) - -> - toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q52, q69]) = - toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q38, q69]) - | q69 : int(1..2), q69 < q68]))) - | q68 : int(1..2)]); - int(1..3)]) - -> - toInt(or([q55 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ - and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q55, q56] = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q52, q56] - | q56 : int(1..2)]) - | q55 : int(1..2)])) - = - toInt(or([q60 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ - and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q60, q61] = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q52, q61] - | q61 : int(1..2)]) - | q60 : int(1..2)])) - | q52 : int(1..2)]))) - | q38 : int(1..2)]), - and([1 = - sum([toInt(q27 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q27, q1]) - | q27 : int(1..2)]) - | q1 : int(1..2)]), - and([q31 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> - sum([toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q31, q32]) | q32 : int(1..2)]) >= 1 - | q31 : int(1..2)]), - 2 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> - [-toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[1, q9]) | q9 : int(1..2)] a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> - and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q5, q11] = false | q11 : int(1..2)]) - | q5 : int(1..2)]), - a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker <= 2, - and([q6 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> - sum([toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q6, q7]) | q7 : int(1..2)]) <= 2 - | q6 : int(1..2)]), - 2 = - sum([toInt(q12 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker) * - catchUndef(sum([toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q12, q13]) - | q13 : int(1..2)]), - 0) - | q12 : int(1..2)]), - and([1 = - sum([toInt(q28 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q28, q14]) - | q28 : int(1..2)]) - | q14 : int(1..2)]), - and([q29 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> - sum([toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q29, q30]) | q30 : int(1..2)]) >= 1 - | q29 : int(1..2)]), - 2 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> - [-toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[1, q22]) | q22 : int(1..2)] b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> - and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q18, q24] = false | q24 : int(1..2)]) - | q18 : int(1..2)]), - b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker <= 2, - and([q19 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> - sum([toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q19, q20]) | q20 : int(1..2)]) <= 2 - | q19 : int(1..2)]), - 2 = - sum([toInt(q25 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker) * - catchUndef(sum([toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q25, q26]) - | q26 : int(1..2)]), - 0) - | q25 : int(1..2)]) - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_1_2-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_1_2-solution000001.solution deleted file mode 100644 index cde05d5274..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_1_2-solution000001.solution +++ /dev/null @@ -1,11 +0,0 @@ -language Essence 1.3 - -letting a be partition({1, 2}) -$ Visualisation for a -$ 1 2 - -letting b be partition({1}, {2}) -$ Visualisation for b -$ 1 -$ 2 - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_1_2.eprime b/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_1_2.eprime deleted file mode 100644 index 6ac5a9636a..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_1_2.eprime +++ /dev/null @@ -1,787 +0,0 @@ -language ESSENCE' 1.0 - -find a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker: int(0..2) -find a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence: matrix indexed by [int(1..2), int(1..2)] of bool -find b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker: int(0..2) -find b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy: - matrix indexed by [int(1..2), int(1..2)] of int(1..3) -branching on - [a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker, - a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence, - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker, - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy] -such that - or([q42 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ - (toInt(or([q164 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ - and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q164, q165] = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q42, q165] - | q165 : int(1..2)]) - | q164 : int(1..2)])) - < - toInt(or([q169 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ - (and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q169, q171] != 3 - -> - a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence - [q42, - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q169, q171]] - | q171 : int(1..2)]) - /\ - and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q42, q172] -> - or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q169, q174] != - 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q169, q174] = - q172 - | q174 : int(1..2)]) - | q172 : int(1..2)])) - | q169 : int(1..2)])) - /\ - (and([q176 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ - (or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q176, q236] /\ - (toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q176, q236]) < - toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q42, q236]) - /\ - (and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q176, q237] -> - toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q176, q237]) = - toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q42, q237]) - | q237 : int(1..2), q237 < q236]) - /\ - and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q42, q237] /\ - !or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q176, q240] /\ - q240 = q237 - | q240 : int(1..2)]) - -> - toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q176, q237]) = - toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q42, q237]) - | q237 : int(1..2), q237 < q236]))) - | q236 : int(1..2)]) - \/ - or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q42, q236] /\ - !or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q176, q239] /\ q239 = q236 - | q239 : int(1..2)]) - /\ - (toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q176, q236]) < - toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q42, q236]) - /\ - (and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q176, q237] -> - toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q176, q237]) = - toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q42, q237]) - | q237 : int(1..2), q237 < q236]) - /\ - and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q42, q237] /\ - !or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q176, q238] /\ - q238 = q237 - | q238 : int(1..2)]) - -> - toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q176, q237]) = - toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q42, q237]) - | q237 : int(1..2), q237 < q236]))) - | q236 : int(1..2)])) - -> - toInt(or([q225 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ - and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q225, q226] = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q176, q226] - | q226 : int(1..2)]) - | q225 : int(1..2)])) - = - toInt(or([q230 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ - (and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q230, q232] - != 3 - -> - a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence - [q176, - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q230, q232]] - | q232 : int(1..2)]) - /\ - and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q176, q233] -> - or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q230, q235] - != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q230, q235] - = q233 - | q235 : int(1..2)]) - | q233 : int(1..2)])) - | q230 : int(1..2)])) - | q176 : int(1..2)]) - /\ - and([and([q178 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker, - !or([q194 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ - (and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q194, q195] -> - or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q178, q197] - != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q178, q197] - = q195 - | q197 : int(1..2)]) - | q195 : int(1..2)]) - /\ - and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q178, q199] - != 3 - -> - a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence - [q194, - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q178, q199]] - | q199 : int(1..2)])) - | q194 : int(1..2)]), - or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q178, q202] != 3 /\ - (toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q178, q215] - != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q178, q215] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q178, q202] - | q215 : int(1..2)])) - < - toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence - [q42, - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q178, q202]]) - /\ - (and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q178, q216] - != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q178, q216] - < - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q178, q202] - -> - toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q178, q222] - != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q178, q222] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q178, q216] - | q222 : int(1..2)])) - = - toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence - [q42, - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q178, q216]]) - | q216 : int(1..2)]) - /\ - and([and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q42, q201], - !or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q178, q220] - != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q178, q220] - = q201 - | q220 : int(1..2)]), - q201 < - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q178, q202]; - int(1..3)]) - -> - toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q178, q218] - != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q178, q218] - = q201 - | q218 : int(1..2)])) - = toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q42, q201]) - | q201 : int(1..2)]))) - | q202 : int(1..2)]) - \/ - or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q42, q200] /\ - !or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q178, q213] != - 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q178, q213] = - q200 - | q213 : int(1..2)]) - /\ - (toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q178, q204] - != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q178, q204] - = q200 - | q204 : int(1..2)])) - < toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q42, q200]) - /\ - (and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q178, q205] - != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q178, q205] - < q200 - -> - toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q178, q211] - != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q178, q211] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q178, q205] - | q211 : int(1..2)])) - = - toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence - [q42, - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q178, q205]]) - | q205 : int(1..2)]) - /\ - and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q42, q201] /\ - !or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q178, q209] - != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q178, q209] - = q201 - | q209 : int(1..2)]) - -> - toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q178, q207] - != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q178, q207] - = q201 - | q207 : int(1..2)])) - = toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q42, q201]) - | q201 : int(1..2), q201 < q200]))) - | q200 : int(1..2)]); - int(1..3)]) - -> - toInt(or([q181 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ - (and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q181, q182] -> - or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q178, q184] - != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q178, q184] - = q182 - | q184 : int(1..2)]) - | q182 : int(1..2)]) - /\ - and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q178, q186] - != 3 - -> - a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence - [q181, - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q178, q186]] - | q186 : int(1..2)])) - | q181 : int(1..2)])) - = - toInt(or([q189 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ - and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q189, q190] = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q178, q190] - | q190 : int(1..2)]) - | q189 : int(1..2)])) - | q178 : int(1..2)]))) - | q42 : int(1..2)]) - \/ - or([q44 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ - !or([q156 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ - (and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q156, q157] -> - or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q44, q159] != 3 /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q44, q159] = q157 - | q159 : int(1..2)]) - | q157 : int(1..2)]) - /\ - and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q44, q161] != 3 -> - a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence - [q156, b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q44, q161]] - | q161 : int(1..2)])) - | q156 : int(1..2)]) - /\ - (toInt(or([q47 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ - (and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q47, q48] -> - or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q44, q50] != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q44, q50] = - q48 | q50 : int(1..2)]) - | q48 : int(1..2)]) - /\ - and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q44, q52] != 3 -> - a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence - [q47, - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q44, q52]] - | q52 : int(1..2)])) - | q47 : int(1..2)])) - < - toInt(or([q55 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ - and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q55, q56] = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q44, q56] - | q56 : int(1..2)]) - | q55 : int(1..2)])) - /\ - (and([q59 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ - (or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q59, q134] /\ - (toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q59, q134]) < - toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q44, q147] - != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q44, q147] = - q134 - | q147 : int(1..2)])) - /\ - (and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q59, q135] -> - toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q59, q135]) = - toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q44, q153] - != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q44, q153] - = q135 - | q153 : int(1..2)])) - | q135 : int(1..2), q135 < q134]) - /\ - and([and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q44, q148] - != 3, - !or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q59, q149] /\ - q149 = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q44, q148] - | q149 : int(1..2)]), - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q44, q148] - < q134; - int(1..3)]) - -> - toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence - [q59, - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q44, q148]]) - = - toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q44, q151] - != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q44, q151] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q44, q148] - | q151 : int(1..2)])) - | q148 : int(1..2)]))) - | q134 : int(1..2)]) - \/ - or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q44, q136] != 3 /\ - !or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q59, q137] /\ - q137 = b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q44, q136] - | q137 : int(1..2)]) - /\ - (toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence - [q59, - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q44, q136]]) - < - toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q44, q139] - != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q44, q139] = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q44, q136] - | q139 : int(1..2)])) - /\ - (and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q59, q135] /\ - q135 < - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q44, q136] - -> - toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q59, q135]) = - toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q44, q145] - != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q44, q145] - = q135 - | q145 : int(1..2)])) - | q135 : int(1..2)]) - /\ - and([and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q44, q140] - != 3, - !or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q59, q141] /\ - q141 = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q44, q140] - | q141 : int(1..2)]), - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q44, q140] - < - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q44, q136]; - int(1..3)]) - -> - toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence - [q59, - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q44, q140]]) - = - toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q44, q143] - != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q44, q143] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q44, q140] - | q143 : int(1..2)])) - | q140 : int(1..2)]))) - | q136 : int(1..2)])) - -> - toInt(or([q123 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ - and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q123, q124] = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q59, q124] - | q124 : int(1..2)]) - | q123 : int(1..2)])) - = - toInt(or([q128 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ - (and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q128, q130] - != 3 - -> - a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence - [q59, - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q128, q130]] - | q130 : int(1..2)]) - /\ - and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q59, q131] -> - or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q128, q133] - != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q128, q133] - = q131 - | q133 : int(1..2)]) - | q131 : int(1..2)])) - | q128 : int(1..2)])) - | q59 : int(1..2)]) - /\ - and([and([q61 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker, - !or([q77 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ - (and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q77, q78] -> - or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q61, q80] - != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q61, q80] - = q78 - | q80 : int(1..2)]) - | q78 : int(1..2)]) - /\ - and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q61, q82] != - 3 - -> - a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence - [q77, - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q61, q82]] - | q82 : int(1..2)])) - | q77 : int(1..2)]), - or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q61, q85] != 3 /\ - (toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q61, q106] - != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q61, q106] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q61, q85] - | q106 : int(1..2)])) - < - toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q44, q108] - != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q44, q108] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q61, q85] - | q108 : int(1..2)])) - /\ - (and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q61, q109] - != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q61, q109] < - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q61, q85] - -> - toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q61, q118] - != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q61, q118] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q61, q109] - | q118 : int(1..2)])) - = - toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q44, q120] - != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q44, q120] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q61, q109] - | q120 : int(1..2)])) - | q109 : int(1..2)]) - /\ - and([and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q44, q110] - != 3, - !or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q61, q112] - != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q61, q112] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q44, q110] - | q112 : int(1..2)]), - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q44, q110] - < - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q61, q85]; - int(1..3)]) - -> - toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q61, q114] - != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q61, q114] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q44, q110] - | q114 : int(1..2)])) - = - toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q44, q116] - != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q44, q116] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q44, q110] - | q116 : int(1..2)])) - | q110 : int(1..2)]))) - | q85 : int(1..2)]) - \/ - or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q44, q86] != 3 /\ - !or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q61, q88] != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q61, q88] = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q44, q86] - | q88 : int(1..2)]) - /\ - (toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q61, q90] - != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q61, q90] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q44, q86] - | q90 : int(1..2)])) - < - toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q44, q92] - != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q44, q92] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q44, q86] - | q92 : int(1..2)])) - /\ - (and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q61, q93] != - 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q61, q93] < - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q44, q86] - -> - toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q61, q102] - != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q61, q102] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q61, q93] - | q102 : int(1..2)])) - = - toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q44, q104] - != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q44, q104] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q61, q93] - | q104 : int(1..2)])) - | q93 : int(1..2)]) - /\ - and([and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q44, q94] - != 3, - !or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q61, q96] - != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q61, q96] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q44, q94] - | q96 : int(1..2)]), - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q44, q94] - < - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q44, q86]; - int(1..3)]) - -> - toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q61, q98] - != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q61, q98] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q44, q94] - | q98 : int(1..2)])) - = - toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q44, q100] - != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q44, q100] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q44, q94] - | q100 : int(1..2)])) - | q94 : int(1..2)]))) - | q86 : int(1..2)]); - int(1..3)]) - -> - toInt(or([q64 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ - (and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q64, q65] -> - or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q61, q67] - != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q61, q67] - = q65 - | q67 : int(1..2)]) - | q65 : int(1..2)]) - /\ - and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q61, q69] != - 3 - -> - a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence - [q64, - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q61, q69]] - | q69 : int(1..2)])) - | q64 : int(1..2)])) - = - toInt(or([q72 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ - and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q72, q73] = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q61, q73] - | q73 : int(1..2)]) - | q72 : int(1..2)])) - | q61 : int(1..2)]))) - | q44 : int(1..2)]), - and([1 = - sum([toInt(q30 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q30, q1]) - | q30 : int(1..2)]) - | q1 : int(1..2)]), - and([q32 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> - sum([toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q32, q33]) | q33 : int(1..2)]) >= 1 - | q32 : int(1..2)]), - 2 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> - [-toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[1, q9]) | q9 : int(1..2)] a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> - and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q5, q11] = false | q11 : int(1..2)]) - | q5 : int(1..2)]), - a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker <= 2, - and([q6 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> - sum([toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q6, q7]) | q7 : int(1..2)]) <= 2 - | q6 : int(1..2)]), - 2 = - sum([toInt(q12 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker) * - catchUndef(sum([toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q12, q13]) - | q13 : int(1..2)]), - 0) - | q12 : int(1..2)]), - alldifferent_except([toInt(q34 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q34, q35] != - 3) - * - catchUndef(b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q34, q35], - 0) - | q34 : int(1..2), q35 : int(1..2)], - 0), - and([q36 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - sum([toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q36, q38] != 3) - | q38 : int(1..2)]) - >= 1 - | q36 : int(1..2)]), - 2 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - [b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[1, q25] | q25 : int(1..2)] b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q18, q31] = 1 - | q31 : int(1..2)]) - | q18 : int(1..2)]), - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker <= 2, - and([q19 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q19, 1] < - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q19, 2] - \/ b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q19, 1] = 3 - | q19 : int(1..2)]), - and([q19 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - (b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q19, 1] = 3 -> - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q19, 2] = 3) - | q19 : int(1..2)]), - and([q19 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - sum([toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q19, q22] != 3) - | q22 : int(1..2)]) - <= 2 - | q19 : int(1..2)]), - 2 = - sum([toInt(q27 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker) * - catchUndef(sum([toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q27, q29] != - 3) - | q29 : int(1..2)]), - 0) - | q27 : int(1..2)]) - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_1_3-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_1_3-solution000001.solution deleted file mode 100644 index cde05d5274..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_1_3-solution000001.solution +++ /dev/null @@ -1,11 +0,0 @@ -language Essence 1.3 - -letting a be partition({1, 2}) -$ Visualisation for a -$ 1 2 - -letting b be partition({1}, {2}) -$ Visualisation for b -$ 1 -$ 2 - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_1_3.eprime b/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_1_3.eprime deleted file mode 100644 index cc87f64f5e..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_1_3.eprime +++ /dev/null @@ -1,858 +0,0 @@ -language ESSENCE' 1.0 - -find a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker: int(0..2) -find a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence: matrix indexed by [int(1..2), int(1..2)] of bool -find b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker: int(0..2) -find b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker: - matrix indexed by [int(1..2)] of int(0..2) -find b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values: - matrix indexed by [int(1..2), int(1..2)] of int(1..2) -branching on - [a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker, - a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence, - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker, - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker, - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values] -such that - or([q37 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ - (toInt(or([q159 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ - and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q159, q160] = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q37, q160] - | q160 : int(1..2)]) - | q159 : int(1..2)])) - < - toInt(or([q164 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - (and([q166 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q164] - -> - a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence - [q37, - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q164, q166]] - | q166 : int(1..2)]) - /\ - and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q37, q167] -> - or([q169 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q164] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q164, q169] - = q167 - | q169 : int(1..2)]) - | q167 : int(1..2)])) - | q164 : int(1..2)])) - /\ - (and([q171 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ - (or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q171, q231] /\ - (toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q171, q231]) < - toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q37, q231]) - /\ - (and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q171, q232] -> - toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q171, q232]) = - toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q37, q232]) - | q232 : int(1..2), q232 < q231]) - /\ - and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q37, q232] /\ - !or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q171, q235] /\ - q235 = q232 - | q235 : int(1..2)]) - -> - toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q171, q232]) = - toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q37, q232]) - | q232 : int(1..2), q232 < q231]))) - | q231 : int(1..2)]) - \/ - or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q37, q231] /\ - !or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q171, q234] /\ q234 = q231 - | q234 : int(1..2)]) - /\ - (toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q171, q231]) < - toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q37, q231]) - /\ - (and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q171, q232] -> - toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q171, q232]) = - toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q37, q232]) - | q232 : int(1..2), q232 < q231]) - /\ - and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q37, q232] /\ - !or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q171, q233] /\ - q233 = q232 - | q233 : int(1..2)]) - -> - toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q171, q232]) = - toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q37, q232]) - | q232 : int(1..2), q232 < q231]))) - | q231 : int(1..2)])) - -> - toInt(or([q220 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ - and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q220, q221] = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q171, q221] - | q221 : int(1..2)]) - | q220 : int(1..2)])) - = - toInt(or([q225 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - (and([q227 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q225] - -> - a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence - [q171, - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q225, q227]] - | q227 : int(1..2)]) - /\ - and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q171, q228] -> - or([q230 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q225] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q225, q230] - = q228 - | q230 : int(1..2)]) - | q228 : int(1..2)])) - | q225 : int(1..2)])) - | q171 : int(1..2)]) - /\ - and([and([q173 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker, - !or([q189 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ - (and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q189, q190] -> - or([q192 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q173] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q173, q192] - = q190 - | q192 : int(1..2)]) - | q190 : int(1..2)]) - /\ - and([q194 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q173] - -> - a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence - [q189, - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q173, q194]] - | q194 : int(1..2)])) - | q189 : int(1..2)]), - or([q197 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q173] - /\ - (toInt(or([q210 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q173] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q173, q210] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q173, q197] - | q210 : int(1..2)])) - < - toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence - [q37, - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q173, q197]]) - /\ - (and([q211 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q173] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q173, q211] - < - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q173, q197] - -> - toInt(or([q217 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q173] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q173, q217] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q173, q211] - | q217 : int(1..2)])) - = - toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence - [q37, - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q173, q211]]) - | q211 : int(1..2)]) - /\ - and([and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q37, q196], - !or([q215 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q173] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q173, q215] - = q196 - | q215 : int(1..2)]), - q196 < - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q173, q197]; - int(1..3)]) - -> - toInt(or([q213 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q173] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q173, q213] - = q196 - | q213 : int(1..2)])) - = toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q37, q196]) - | q196 : int(1..2)]))) - | q197 : int(1..2)]) - \/ - or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q37, q195] /\ - !or([q208 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q173] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q173, q208] - = q195 - | q208 : int(1..2)]) - /\ - (toInt(or([q199 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q173] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q173, q199] - = q195 - | q199 : int(1..2)])) - < toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q37, q195]) - /\ - (and([q200 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q173] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q173, q200] - < q195 - -> - toInt(or([q206 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q173] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q173, q206] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q173, q200] - | q206 : int(1..2)])) - = - toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence - [q37, - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q173, q200]]) - | q200 : int(1..2)]) - /\ - and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q37, q196] /\ - !or([q204 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q173] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q173, q204] - = q196 - | q204 : int(1..2)]) - -> - toInt(or([q202 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q173] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q173, q202] - = q196 - | q202 : int(1..2)])) - = toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q37, q196]) - | q196 : int(1..2), q196 < q195]))) - | q195 : int(1..2)]); - int(1..3)]) - -> - toInt(or([q176 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ - (and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q176, q177] -> - or([q179 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q173] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q173, q179] - = q177 - | q179 : int(1..2)]) - | q177 : int(1..2)]) - /\ - and([q181 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q173] - -> - a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence - [q176, - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q173, q181]] - | q181 : int(1..2)])) - | q176 : int(1..2)])) - = - toInt(or([q184 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - (b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q184] = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q173] - /\ - and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q184, q185] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q173, q185] - | q185 : int(1..2)])) - | q184 : int(1..2)])) - | q173 : int(1..2)]))) - | q37 : int(1..2)]) - \/ - or([q39 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - !or([q151 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ - (and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q151, q152] -> - or([q154 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q39] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q39, q154] = - q152 - | q154 : int(1..2)]) - | q152 : int(1..2)]) - /\ - and([q156 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q39] -> - a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence - [q151, - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q39, q156]] - | q156 : int(1..2)])) - | q151 : int(1..2)]) - /\ - (toInt(or([q42 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ - (and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q42, q43] -> - or([q45 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q39] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q39, q45] - = q43 - | q45 : int(1..2)]) - | q43 : int(1..2)]) - /\ - and([q47 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q39] - -> - a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence - [q42, - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q39, q47]] - | q47 : int(1..2)])) - | q42 : int(1..2)])) - < - toInt(or([q50 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - (b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q50] = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q39] - /\ - and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q50, q51] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q39, q51] - | q51 : int(1..2)])) - | q50 : int(1..2)])) - /\ - (and([q54 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ - (or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q54, q129] /\ - (toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q54, q129]) < - toInt(or([q142 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q39] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q39, q142] - = q129 - | q142 : int(1..2)])) - /\ - (and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q54, q130] -> - toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q54, q130]) = - toInt(or([q148 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q39] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q39, q148] - = q130 - | q148 : int(1..2)])) - | q130 : int(1..2), q130 < q129]) - /\ - and([and([q143 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q39], - !or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q54, q146] /\ - q146 = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q39, q143] - | q146 : int(1..2)]), - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q39, q143] - < q129; - int(1..3)]) - -> - toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence - [q54, - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q39, q143]]) - = - toInt(or([q145 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q39] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q39, q145] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q39, q143] - | q145 : int(1..2)])) - | q143 : int(1..2)]))) - | q129 : int(1..2)]) - \/ - or([q131 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q39] /\ - !or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q54, q140] /\ - q140 = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q39, q131] - | q140 : int(1..2)]) - /\ - (toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence - [q54, - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q39, q131]]) - < - toInt(or([q133 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q39] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q39, q133] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q39, q131] - | q133 : int(1..2)])) - /\ - (and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q54, q130] /\ - q130 < - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q39, q131] - -> - toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q54, q130]) = - toInt(or([q139 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q39] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q39, q139] - = q130 - | q139 : int(1..2)])) - | q130 : int(1..2)]) - /\ - and([and([q134 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q39], - !or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q54, q137] /\ - q137 = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q39, q134] - | q137 : int(1..2)]), - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q39, q134] - < - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q39, q131]; - int(1..3)]) - -> - toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence - [q54, - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q39, q134]]) - = - toInt(or([q136 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q39] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q39, q136] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q39, q134] - | q136 : int(1..2)])) - | q134 : int(1..2)]))) - | q131 : int(1..2)])) - -> - toInt(or([q118 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ - and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q118, q119] = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q54, q119] - | q119 : int(1..2)]) - | q118 : int(1..2)])) - = - toInt(or([q123 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - (and([q125 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q123] - -> - a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence - [q54, - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q123, q125]] - | q125 : int(1..2)]) - /\ - and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q54, q126] -> - or([q128 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q123] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q123, q128] - = q126 - | q128 : int(1..2)]) - | q126 : int(1..2)])) - | q123 : int(1..2)])) - | q54 : int(1..2)]) - /\ - and([and([q56 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker, - !or([q72 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ - (and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q72, q73] -> - or([q75 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q56] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q56, q75] - = q73 - | q75 : int(1..2)]) - | q73 : int(1..2)]) - /\ - and([q77 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q56] - -> - a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence - [q72, - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q56, q77]] - | q77 : int(1..2)])) - | q72 : int(1..2)]), - or([q80 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q56] - /\ - (toInt(or([q101 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q56] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q56, q101] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q56, q80] - | q101 : int(1..2)])) - < - toInt(or([q103 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q39] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q39, q103] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q56, q80] - | q103 : int(1..2)])) - /\ - (and([q104 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q56] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q56, q104] - < - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q56, q80] - -> - toInt(or([q113 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q56] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q56, q113] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q56, q104] - | q113 : int(1..2)])) - = - toInt(or([q115 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q39] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q39, q115] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q56, q104] - | q115 : int(1..2)])) - | q104 : int(1..2)]) - /\ - and([and([q105 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q39], - !or([q111 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q56] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q56, q111] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q39, q105] - | q111 : int(1..2)]), - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q39, q105] - < - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q56, q80]; - int(1..3)]) - -> - toInt(or([q107 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q56] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q56, q107] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q39, q105] - | q107 : int(1..2)])) - = - toInt(or([q109 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q39] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q39, q109] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q39, q105] - | q109 : int(1..2)])) - | q105 : int(1..2)]))) - | q80 : int(1..2)]) - \/ - or([q81 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q39] - /\ - !or([q99 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q56] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q56, q99] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q39, q81] - | q99 : int(1..2)]) - /\ - (toInt(or([q83 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q56] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q56, q83] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q39, q81] - | q83 : int(1..2)])) - < - toInt(or([q85 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q39] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q39, q85] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q39, q81] - | q85 : int(1..2)])) - /\ - (and([q86 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q56] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q56, q86] - < - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q39, q81] - -> - toInt(or([q95 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q56] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q56, q95] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q56, q86] - | q95 : int(1..2)])) - = - toInt(or([q97 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q39] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q39, q97] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q56, q86] - | q97 : int(1..2)])) - | q86 : int(1..2)]) - /\ - and([and([q87 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q39], - !or([q93 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q56] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q56, q93] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q39, q87] - | q93 : int(1..2)]), - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q39, q87] - < - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q39, q81]; - int(1..3)]) - -> - toInt(or([q89 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q56] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q56, q89] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q39, q87] - | q89 : int(1..2)])) - = - toInt(or([q91 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q39] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q39, q91] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q39, q87] - | q91 : int(1..2)])) - | q87 : int(1..2)]))) - | q81 : int(1..2)]); - int(1..3)]) - -> - toInt(or([q59 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ - (and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q59, q60] -> - or([q62 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q56] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q56, q62] - = q60 - | q62 : int(1..2)]) - | q60 : int(1..2)]) - /\ - and([q64 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q56] - -> - a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence - [q59, - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q56, q64]] - | q64 : int(1..2)])) - | q59 : int(1..2)])) - = - toInt(or([q67 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - (b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q67] = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q56] - /\ - and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q67, q68] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q56, q68] - | q68 : int(1..2)])) - | q67 : int(1..2)])) - | q56 : int(1..2)]))) - | q39 : int(1..2)]), - and([1 = - sum([toInt(q27 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q27, q1]) - | q27 : int(1..2)]) - | q1 : int(1..2)]), - and([q29 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> - sum([toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q29, q30]) | q30 : int(1..2)]) >= 1 - | q29 : int(1..2)]), - 2 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> - [-toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[1, q9]) | q9 : int(1..2)] a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> - and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q5, q11] = false | q11 : int(1..2)]) - | q5 : int(1..2)]), - a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker <= 2, - and([q6 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> - sum([toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q6, q7]) | q7 : int(1..2)]) <= 2 - | q6 : int(1..2)]), - 2 = - sum([toInt(q12 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker) * - catchUndef(sum([toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q12, q13]) - | q13 : int(1..2)]), - 0) - | q12 : int(1..2)]), - alldifferent_except([toInt(q31 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - q32 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q31]) - * - catchUndef(b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q31, q32], - 0) - | q31 : int(1..2), q32 : int(1..2)], - 0), - and([q33 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q33] >= 1 - | q33 : int(1..2)]), - 2 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - flatten([[b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[1]; int(1)], - flatten([[b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[1, q24]; - int(1)] - | q24 : int(1..2)]); - int(1..2)]) - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q18] = 0 /\ - and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q18, q28] = 1 - | q28 : int(1..2)]) - | q18 : int(1..2)]), - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker <= 2, - and([q19 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - (2 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q19] -> - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q19, 1] < - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q19, 2]) - | q19 : int(1..2)]), - and([q19 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - and([q21 > b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q19] -> - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q19, q21] = 1 - | q21 : int(1..2)]) - | q19 : int(1..2)]), - and([q19 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q19] <= 2 - | q19 : int(1..2)]), - 2 = - sum([toInt(q26 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker) * - catchUndef(b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q26], 0) - | q26 : int(1..2)]) - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_1_4-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_1_4-solution000001.solution deleted file mode 100644 index cde05d5274..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_1_4-solution000001.solution +++ /dev/null @@ -1,11 +0,0 @@ -language Essence 1.3 - -letting a be partition({1, 2}) -$ Visualisation for a -$ 1 2 - -letting b be partition({1}, {2}) -$ Visualisation for b -$ 1 -$ 2 - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_1_4.eprime b/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_1_4.eprime deleted file mode 100644 index 5e65b4ba3b..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_1_4.eprime +++ /dev/null @@ -1,382 +0,0 @@ -language ESSENCE' 1.0 - -find a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker: int(0..2) -find a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence: matrix indexed by [int(1..2), int(1..2)] of bool -find b_PartitionOccurrence_NumParts: int(1..2) -find b_PartitionOccurrence_WhichPart: matrix indexed by [int(1..2)] of int(1..2) -find b_PartitionOccurrence_PartSizes: matrix indexed by [int(1..2)] of int(0..2) -find b_PartitionOccurrence_FirstIndex: matrix indexed by [int(1..2)] of int(1..2) -branching on - [a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker, - a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence, b_PartitionOccurrence_NumParts, - b_PartitionOccurrence_WhichPart, b_PartitionOccurrence_PartSizes, b_PartitionOccurrence_FirstIndex] -such that - or([q30 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ - (toInt(or([q144 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ - and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q144, q145] = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q30, q145] - | q145 : int(1..2)]) - | q144 : int(1..2)])) - < - toInt(or([q148 <= b_PartitionOccurrence_NumParts /\ - (and([b_PartitionOccurrence_WhichPart[q151] = q148 -> - a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q30, q151] - | q151 : int(1..2)]) - /\ - and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q30, q152] -> - or([b_PartitionOccurrence_WhichPart[q154] = q148 /\ q154 = q152 | q154 : int(1..2)]) - | q152 : int(1..2)])) - | q148 : int(1..2)])) - /\ - (and([q156 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ - (or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q156, q222] /\ - (toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q156, q222]) < - toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q30, q222]) - /\ - (and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q156, q223] -> - toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q156, q223]) = - toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q30, q223]) - | q223 : int(1..2), q223 < q222]) - /\ - and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q30, q223] /\ - !or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q156, q226] /\ - q226 = q223 - | q226 : int(1..2)]) - -> - toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q156, q223]) = - toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q30, q223]) - | q223 : int(1..2), q223 < q222]))) - | q222 : int(1..2)]) - \/ - or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q30, q222] /\ - !or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q156, q225] /\ q225 = q222 - | q225 : int(1..2)]) - /\ - (toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q156, q222]) < - toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q30, q222]) - /\ - (and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q156, q223] -> - toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q156, q223]) = - toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q30, q223]) - | q223 : int(1..2), q223 < q222]) - /\ - and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q30, q223] /\ - !or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q156, q224] /\ - q224 = q223 - | q224 : int(1..2)]) - -> - toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q156, q223]) = - toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q30, q223]) - | q223 : int(1..2), q223 < q222]))) - | q222 : int(1..2)])) - -> - toInt(or([q211 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ - and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q211, q212] = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q156, q212] - | q212 : int(1..2)]) - | q211 : int(1..2)])) - = - toInt(or([q215 <= b_PartitionOccurrence_NumParts /\ - (and([b_PartitionOccurrence_WhichPart[q218] = q215 -> - a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q156, q218] - | q218 : int(1..2)]) - /\ - and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q156, q219] -> - or([b_PartitionOccurrence_WhichPart[q221] = q215 /\ q221 = q219 | q221 : int(1..2)]) - | q219 : int(1..2)])) - | q215 : int(1..2)])) - | q156 : int(1..2)]) - /\ - and([and([q157 <= b_PartitionOccurrence_NumParts, - !or([q172 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ - (and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q172, q173] -> - or([b_PartitionOccurrence_WhichPart[q175] = q157 /\ q175 = q173 | q175 : int(1..2)]) - | q173 : int(1..2)]) - /\ - and([b_PartitionOccurrence_WhichPart[q177] = q157 -> - a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q172, q177] - | q177 : int(1..2)])) - | q172 : int(1..2)]), - or([b_PartitionOccurrence_WhichPart[q180] = q157 /\ - (sum([toInt(b_PartitionOccurrence_WhichPart[q193] = q157) * catchUndef(toInt(q193 = q180), 0) - | q193 : int(1..2)]) - < toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q30, q180]) - /\ - (and([b_PartitionOccurrence_WhichPart[q194] = q157 -> - sum([toInt(b_PartitionOccurrence_WhichPart[q200] = q157) * - catchUndef(toInt(q200 = q194), 0) - | q200 : int(1..2)]) - = toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q30, q194]) - | q194 : int(1..2), q194 < q180]) - /\ - and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q30, q179] /\ - !or([b_PartitionOccurrence_WhichPart[q198] = q157 /\ q198 = q179 | q198 : int(1..2)]) - -> - sum([toInt(b_PartitionOccurrence_WhichPart[q196] = q157) * - catchUndef(toInt(q196 = q179), 0) - | q196 : int(1..2)]) - = toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q30, q179]) - | q179 : int(1..2), q179 < q180]))) - | q180 : int(1..2)]) - \/ - or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q30, q178] /\ - !or([b_PartitionOccurrence_WhichPart[q191] = q157 /\ q191 = q178 | q191 : int(1..2)]) - /\ - (sum([toInt(b_PartitionOccurrence_WhichPart[q182] = q157) * catchUndef(toInt(q182 = q178), 0) - | q182 : int(1..2)]) - < toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q30, q178]) - /\ - (and([b_PartitionOccurrence_WhichPart[q183] = q157 -> - sum([toInt(b_PartitionOccurrence_WhichPart[q189] = q157) * - catchUndef(toInt(q189 = q183), 0) - | q189 : int(1..2)]) - = toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q30, q183]) - | q183 : int(1..2), q183 < q178]) - /\ - and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q30, q179] /\ - !or([b_PartitionOccurrence_WhichPart[q187] = q157 /\ q187 = q179 | q187 : int(1..2)]) - -> - sum([toInt(b_PartitionOccurrence_WhichPart[q185] = q157) * - catchUndef(toInt(q185 = q179), 0) - | q185 : int(1..2)]) - = toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q30, q179]) - | q179 : int(1..2), q179 < q178]))) - | q178 : int(1..2)]); - int(1..3)]) - -> - toInt(or([q203 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ - (and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q203, q204] -> - or([b_PartitionOccurrence_WhichPart[q206] = q157 /\ q206 = q204 | q206 : int(1..2)]) - | q204 : int(1..2)]) - /\ - and([b_PartitionOccurrence_WhichPart[q208] = q157 -> - a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q203, q208] - | q208 : int(1..2)])) - | q203 : int(1..2)])) - = - toInt(or([q160 <= b_PartitionOccurrence_NumParts /\ - (and([b_PartitionOccurrence_WhichPart[q163] = q160 -> - or([b_PartitionOccurrence_WhichPart[q165] = q157 /\ q165 = q163 | q165 : int(1..2)]) - | q163 : int(1..2)]) - /\ - and([b_PartitionOccurrence_WhichPart[q167] = q157 -> - or([b_PartitionOccurrence_WhichPart[q169] = q160 /\ q169 = q167 | q169 : int(1..2)]) - | q167 : int(1..2)])) - | q160 : int(1..2)])) - | q157 : int(1..2)]))) - | q30 : int(1..2)]) - \/ - or([q31 <= b_PartitionOccurrence_NumParts /\ - !or([q136 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ - (and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q136, q137] -> - or([b_PartitionOccurrence_WhichPart[q139] = q31 /\ q139 = q137 | q139 : int(1..2)]) - | q137 : int(1..2)]) - /\ - and([b_PartitionOccurrence_WhichPart[q141] = q31 -> - a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q136, q141] - | q141 : int(1..2)])) - | q136 : int(1..2)]) - /\ - (toInt(or([q128 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ - (and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q128, q129] -> - or([b_PartitionOccurrence_WhichPart[q131] = q31 /\ q131 = q129 | q131 : int(1..2)]) - | q129 : int(1..2)]) - /\ - and([b_PartitionOccurrence_WhichPart[q133] = q31 -> - a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q128, q133] - | q133 : int(1..2)])) - | q128 : int(1..2)])) - < - toInt(or([q34 <= b_PartitionOccurrence_NumParts /\ - (and([b_PartitionOccurrence_WhichPart[q37] = q34 -> - or([b_PartitionOccurrence_WhichPart[q39] = q31 /\ q39 = q37 | q39 : int(1..2)]) - | q37 : int(1..2)]) - /\ - and([b_PartitionOccurrence_WhichPart[q41] = q31 -> - or([b_PartitionOccurrence_WhichPart[q43] = q34 /\ q43 = q41 | q43 : int(1..2)]) - | q41 : int(1..2)])) - | q34 : int(1..2)])) - /\ - (and([q65 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ - (or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q65, q44] /\ - (toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q65, q44]) < - sum([toInt(b_PartitionOccurrence_WhichPart[q57] = q31) * catchUndef(toInt(q57 = q44), 0) - | q57 : int(1..2)]) - /\ - (and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q65, q45] -> - toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q65, q45]) = - sum([toInt(b_PartitionOccurrence_WhichPart[q63] = q31) * catchUndef(toInt(q63 = q45), 0) - | q63 : int(1..2)]) - | q45 : int(1..2), q45 < q44]) - /\ - and([!or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q65, q61] /\ q61 = q58 - | q61 : int(1..2)]) - -> - (b_PartitionOccurrence_WhichPart[q58] = q31 -> - toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q65, q58]) = - sum([toInt(b_PartitionOccurrence_WhichPart[q60] = q31) * catchUndef(toInt(q60 = q58), 0) - | q60 : int(1..2)])) - | q58 : int(1..2), q58 < q44]))) - | q44 : int(1..2)]) - \/ - or([!or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q65, q55] /\ q55 = q46 - | q55 : int(1..2)]) - /\ - (b_PartitionOccurrence_WhichPart[q46] = q31 /\ - (toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q65, q46]) < - sum([toInt(b_PartitionOccurrence_WhichPart[q48] = q31) * catchUndef(toInt(q48 = q46), 0) - | q48 : int(1..2)]) - /\ - (and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q65, q45] -> - toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q65, q45]) = - sum([toInt(b_PartitionOccurrence_WhichPart[q54] = q31) * catchUndef(toInt(q54 = q45), 0) - | q54 : int(1..2)]) - | q45 : int(1..2), q45 < q46]) - /\ - and([!or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q65, q52] /\ q52 = q49 - | q52 : int(1..2)]) - -> - (b_PartitionOccurrence_WhichPart[q49] = q31 -> - toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q65, q49]) = - sum([toInt(b_PartitionOccurrence_WhichPart[q51] = q31) * catchUndef(toInt(q51 = q49), 0) - | q51 : int(1..2)])) - | q49 : int(1..2), q49 < q46])))) - | q46 : int(1..2)])) - -> - toInt(or([q115 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ - and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q115, q116] = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q65, q116] - | q116 : int(1..2)]) - | q115 : int(1..2)])) - = - toInt(or([q119 <= b_PartitionOccurrence_NumParts /\ - (and([b_PartitionOccurrence_WhichPart[q122] = q119 -> - a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q65, q122] - | q122 : int(1..2)]) - /\ - and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q65, q123] -> - or([b_PartitionOccurrence_WhichPart[q125] = q119 /\ q125 = q123 | q125 : int(1..2)]) - | q123 : int(1..2)])) - | q119 : int(1..2)])) - | q65 : int(1..2)]) - /\ - and([and([q66 <= b_PartitionOccurrence_NumParts, - !or([q81 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ - (and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q81, q82] -> - or([b_PartitionOccurrence_WhichPart[q84] = q66 /\ q84 = q82 | q84 : int(1..2)]) - | q82 : int(1..2)]) - /\ - and([b_PartitionOccurrence_WhichPart[q86] = q66 -> - a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q81, q86] - | q86 : int(1..2)])) - | q81 : int(1..2)]), - or([b_PartitionOccurrence_WhichPart[q95] = q66 /\ - (toInt(or([b_PartitionOccurrence_WhichPart[q88] = q66 /\ q88 = q95 | q88 : int(1..2)])) < - sum([toInt(b_PartitionOccurrence_WhichPart[q57] = q31) * catchUndef(toInt(q57 = q95), 0) - | q57 : int(1..2)]) - /\ - (and([b_PartitionOccurrence_WhichPart[q91] = q66 -> - toInt(or([b_PartitionOccurrence_WhichPart[q90] = q66 /\ q90 = q91 | q90 : int(1..2)])) = - sum([toInt(b_PartitionOccurrence_WhichPart[q63] = q31) * catchUndef(toInt(q63 = q91), 0) - | q63 : int(1..2)]) - | q91 : int(1..2), q91 < q95]) - /\ - and([!or([b_PartitionOccurrence_WhichPart[q94] = q66 /\ q94 = q58 | q94 : int(1..2)]) -> - (b_PartitionOccurrence_WhichPart[q58] = q31 -> - toInt(or([b_PartitionOccurrence_WhichPart[q93] = q66 /\ q93 = q58 | q93 : int(1..2)])) = - sum([toInt(b_PartitionOccurrence_WhichPart[q60] = q31) * catchUndef(toInt(q60 = q58), 0) - | q60 : int(1..2)])) - | q58 : int(1..2), q58 < q95]))) - | q95 : int(1..2)]) - \/ - or([!or([b_PartitionOccurrence_WhichPart[q104] = q66 /\ q104 = q46 | q104 : int(1..2)]) /\ - (b_PartitionOccurrence_WhichPart[q46] = q31 /\ - (toInt(or([b_PartitionOccurrence_WhichPart[q97] = q66 /\ q97 = q46 | q97 : int(1..2)])) < - sum([toInt(b_PartitionOccurrence_WhichPart[q48] = q31) * catchUndef(toInt(q48 = q46), 0) - | q48 : int(1..2)]) - /\ - (and([b_PartitionOccurrence_WhichPart[q100] = q66 -> - toInt(or([b_PartitionOccurrence_WhichPart[q99] = q66 /\ q99 = q100 | q99 : int(1..2)])) - = - sum([toInt(b_PartitionOccurrence_WhichPart[q54] = q31) * - catchUndef(toInt(q54 = q100), 0) - | q54 : int(1..2)]) - | q100 : int(1..2), q100 < q46]) - /\ - and([!or([b_PartitionOccurrence_WhichPart[q103] = q66 /\ q103 = q49 | q103 : int(1..2)]) -> - (b_PartitionOccurrence_WhichPart[q49] = q31 -> - toInt(or([b_PartitionOccurrence_WhichPart[q102] = q66 /\ q102 = q49 - | q102 : int(1..2)])) - = - sum([toInt(b_PartitionOccurrence_WhichPart[q51] = q31) * - catchUndef(toInt(q51 = q49), 0) - | q51 : int(1..2)])) - | q49 : int(1..2), q49 < q46])))) - | q46 : int(1..2)]); - int(1..3)]) - -> - toInt(or([q107 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ - (and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q107, q108] -> - or([b_PartitionOccurrence_WhichPart[q110] = q66 /\ q110 = q108 | q110 : int(1..2)]) - | q108 : int(1..2)]) - /\ - and([b_PartitionOccurrence_WhichPart[q112] = q66 -> - a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q107, q112] - | q112 : int(1..2)])) - | q107 : int(1..2)])) - = - toInt(or([q69 <= b_PartitionOccurrence_NumParts /\ - (and([b_PartitionOccurrence_WhichPart[q72] = q69 -> - or([b_PartitionOccurrence_WhichPart[q74] = q66 /\ q74 = q72 | q74 : int(1..2)]) - | q72 : int(1..2)]) - /\ - and([b_PartitionOccurrence_WhichPart[q76] = q66 -> - or([b_PartitionOccurrence_WhichPart[q78] = q69 /\ q78 = q76 | q78 : int(1..2)]) - | q76 : int(1..2)])) - | q69 : int(1..2)])) - | q66 : int(1..2)]))) - | q31 : int(1..2)]), - and([1 = - sum([toInt(q24 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q24, q1]) - | q24 : int(1..2)]) - | q1 : int(1..2)]), - and([q25 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> - sum([toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q25, q26]) | q26 : int(1..2)]) >= 1 - | q25 : int(1..2)]), - 2 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> - [-toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[1, q9]) | q9 : int(1..2)] a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> - and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q5, q11] = false | q11 : int(1..2)]) - | q5 : int(1..2)]), - a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker <= 2, - and([q6 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> - sum([toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q6, q7]) | q7 : int(1..2)]) <= 2 - | q6 : int(1..2)]), - 2 = - sum([toInt(q12 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker) * - catchUndef(sum([toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q12, q13]) - | q13 : int(1..2)]), - 0) - | q12 : int(1..2)]), - and([q14 <= b_PartitionOccurrence_NumParts -> b_PartitionOccurrence_PartSizes[q14] <= 2 | q14 : int(1..2)]), - and([q14 > b_PartitionOccurrence_NumParts -> b_PartitionOccurrence_PartSizes[q14] = 0 | q14 : int(1..2)]), - b_PartitionOccurrence_NumParts <= 2, - b_PartitionOccurrence_NumParts = max([b_PartitionOccurrence_WhichPart[q17] | q17 : int(1..2)]), - and([b_PartitionOccurrence_PartSizes[q18] = - sum([toInt(b_PartitionOccurrence_WhichPart[q19] = q18) | q19 : int(1..2)]) - | q18 : int(1..2)]), - and([q20 <= b_PartitionOccurrence_NumParts -> - and([b_PartitionOccurrence_WhichPart[q21] = q20 -> b_PartitionOccurrence_FirstIndex[q20] <= q21 - | q21 : int(1..2)]) - | q20 : int(1..2)]), - and([q20 <= b_PartitionOccurrence_NumParts -> - or([b_PartitionOccurrence_WhichPart[q21] = q20 /\ b_PartitionOccurrence_FirstIndex[q20] = q21 - | q21 : int(1..2)]) - | q20 : int(1..2)]), - and([q20 > b_PartitionOccurrence_NumParts -> b_PartitionOccurrence_FirstIndex[q20] = 1 | q20 : int(1..2)]), - and([q22 <= b_PartitionOccurrence_NumParts /\ q23 <= b_PartitionOccurrence_NumParts -> - (q22 < q23 <-> b_PartitionOccurrence_FirstIndex[q22] < b_PartitionOccurrence_FirstIndex[q23]) - | q22 : int(1..2), q23 : int(1..2)]) - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_2_1-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_2_1-solution000001.solution deleted file mode 100644 index cde05d5274..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_2_1-solution000001.solution +++ /dev/null @@ -1,11 +0,0 @@ -language Essence 1.3 - -letting a be partition({1, 2}) -$ Visualisation for a -$ 1 2 - -letting b be partition({1}, {2}) -$ Visualisation for b -$ 1 -$ 2 - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_2_1.eprime b/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_2_1.eprime deleted file mode 100644 index 917ebeb2c9..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_2_1.eprime +++ /dev/null @@ -1,761 +0,0 @@ -language ESSENCE' 1.0 - -find a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker: int(0..2) -find a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy: - matrix indexed by [int(1..2), int(1..2)] of int(1..3) -find b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker: int(0..2) -find b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence: matrix indexed by [int(1..2), int(1..2)] of bool -branching on - [a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker, - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy, - b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker, - b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence] -such that - or([q42 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ - (toInt(or([q134 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ - and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q134, q135] = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q42, q135] - | q135 : int(1..2)]) - | q134 : int(1..2)])) - < - toInt(or([q139 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ - (and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q139, q140] -> - or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q42, q142] != - 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q42, q142] = - q140 - | q142 : int(1..2)]) - | q140 : int(1..2)]) - /\ - and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q42, q144] != 3 -> - b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence - [q139, - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q42, q144]] - | q144 : int(1..2)])) - | q139 : int(1..2)])) - /\ - (and([q146 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ - (or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q146, q205] != 3 /\ - (toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q146, q226] - != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q146, q226] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q146, q205] - | q226 : int(1..2)])) - < - toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q42, q228] - != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q42, q228] = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q146, q205] - | q228 : int(1..2)])) - /\ - (and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q146, q229] != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q146, q229] < - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q146, q205] - -> - toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q146, q238] - != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q146, q238] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q146, q229] - | q238 : int(1..2)])) - = - toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q42, q240] - != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q42, q240] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q146, q229] - | q240 : int(1..2)])) - | q229 : int(1..2)]) - /\ - and([and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q42, q230] - != 3, - !or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q146, q232] - != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q146, q232] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q42, q230] - | q232 : int(1..2)]), - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q42, q230] - < - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q146, q205]; - int(1..3)]) - -> - toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q146, q234] - != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q146, q234] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q42, q230] - | q234 : int(1..2)])) - = - toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q42, q236] - != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q42, q236] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q42, q230] - | q236 : int(1..2)])) - | q230 : int(1..2)]))) - | q205 : int(1..2)]) - \/ - or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q42, q206] != 3 /\ - !or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q146, q208] != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q146, q208] = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q42, q206] - | q208 : int(1..2)]) - /\ - (toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q146, q210] - != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q146, q210] - = a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q42, q206] - | q210 : int(1..2)])) - < - toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q42, q212] - != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q42, q212] = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q42, q206] - | q212 : int(1..2)])) - /\ - (and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q146, q213] != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q146, q213] < - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q42, q206] - -> - toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q146, q222] - != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q146, q222] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q146, q213] - | q222 : int(1..2)])) - = - toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q42, q224] - != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q42, q224] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q146, q213] - | q224 : int(1..2)])) - | q213 : int(1..2)]) - /\ - and([and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q42, q214] - != 3, - !or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q146, q216] - != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q146, q216] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q42, q214] - | q216 : int(1..2)]), - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q42, q214] - < - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q42, q206]; - int(1..3)]) - -> - toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q146, q218] - != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q146, q218] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q42, q214] - | q218 : int(1..2)])) - = - toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q42, q220] - != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q42, q220] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q42, q214] - | q220 : int(1..2)])) - | q214 : int(1..2)]))) - | q206 : int(1..2)])) - -> - toInt(or([q192 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ - and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q192, q193] = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q146, q193] - | q193 : int(1..2)]) - | q192 : int(1..2)])) - = - toInt(or([q197 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ - (and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q197, q198] -> - or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q146, q200] - != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q146, q200] - = q198 - | q200 : int(1..2)]) - | q198 : int(1..2)]) - /\ - and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q146, q202] - != 3 - -> - b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence - [q197, - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q146, q202]] - | q202 : int(1..2)])) - | q197 : int(1..2)])) - | q146 : int(1..2)]) - /\ - and([and([q148 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker, - !or([q164 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ - (and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q164, q166] - != 3 - -> - b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence - [q148, - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q164, q166]] - | q166 : int(1..2)]) - /\ - and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q148, q167] -> - or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q164, q169] - != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q164, q169] - = q167 - | q169 : int(1..2)]) - | q167 : int(1..2)])) - | q164 : int(1..2)]), - or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q148, q170] /\ - (toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q148, q170]) < - toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q42, q183] - != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q42, q183] - = q170 - | q183 : int(1..2)])) - /\ - (and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q148, q171] -> - toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q148, q171]) = - toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q42, q189] - != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q42, q189] - = q171 - | q189 : int(1..2)])) - | q171 : int(1..2), q171 < q170]) - /\ - and([and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q42, q184] - != 3, - !or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q148, q185] /\ - q185 = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q42, q184] - | q185 : int(1..2)]), - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q42, q184] - < q170; - int(1..3)]) - -> - toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence - [q148, - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q42, q184]]) - = - toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q42, q187] - != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q42, q187] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q42, q184] - | q187 : int(1..2)])) - | q184 : int(1..2)]))) - | q170 : int(1..2)]) - \/ - or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q42, q172] != 3 /\ - !or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q148, q173] /\ - q173 = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q42, q172] - | q173 : int(1..2)]) - /\ - (toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence - [q148, - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q42, q172]]) - < - toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q42, q175] - != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q42, q175] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q42, q172] - | q175 : int(1..2)])) - /\ - (and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q148, q171] /\ - q171 < - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q42, q172] - -> - toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q148, q171]) = - toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q42, q181] - != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q42, q181] - = q171 - | q181 : int(1..2)])) - | q171 : int(1..2)]) - /\ - and([and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q42, q176] - != 3, - !or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q148, q177] /\ - q177 = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q42, q176] - | q177 : int(1..2)]), - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q42, q176] - < - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q42, q172]; - int(1..3)]) - -> - toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence - [q148, - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q42, q176]]) - = - toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q42, q179] - != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q42, q179] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q42, q176] - | q179 : int(1..2)])) - | q176 : int(1..2)]))) - | q172 : int(1..2)]); - int(1..3)]) - -> - toInt(or([q151 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ - (and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q151, q153] - != 3 - -> - b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence - [q148, - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q151, q153]] - | q153 : int(1..2)]) - /\ - and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q148, q154] -> - or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q151, q156] - != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q151, q156] - = q154 - | q156 : int(1..2)]) - | q154 : int(1..2)])) - | q151 : int(1..2)])) - = - toInt(or([q159 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ - and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q159, q160] = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q148, q160] - | q160 : int(1..2)]) - | q159 : int(1..2)])) - | q148 : int(1..2)]))) - | q42 : int(1..2)]) - \/ - or([q44 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ - !or([q126 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ - (and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q126, q128] != 3 -> - b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence - [q44, a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q126, q128]] - | q128 : int(1..2)]) - /\ - and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q44, q129] -> - or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q126, q131] != 3 /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q126, q131] = q129 - | q131 : int(1..2)]) - | q129 : int(1..2)])) - | q126 : int(1..2)]) - /\ - (toInt(or([q47 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ - (and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q47, q49] != 3 -> - b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence - [q44, - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q47, q49]] - | q49 : int(1..2)]) - /\ - and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q44, q50] -> - or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q47, q52] != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q47, q52] = - q50 | q52 : int(1..2)]) - | q50 : int(1..2)])) - | q47 : int(1..2)])) - < - toInt(or([q55 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ - and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q55, q56] = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q44, q56] - | q56 : int(1..2)]) - | q55 : int(1..2)])) - /\ - (and([q59 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ - (or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q59, q103] != 3 /\ - (toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q59, q116] - != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q59, q116] = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q59, q103] - | q116 : int(1..2)])) - < - toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence - [q44, - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q59, q103]]) - /\ - (and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q59, q117] != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q59, q117] < - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q59, q103] - -> - toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q59, q123] - != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q59, q123] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q59, q117] - | q123 : int(1..2)])) - = - toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence - [q44, - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q59, q117]]) - | q117 : int(1..2)]) - /\ - and([and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q44, q102], - !or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q59, q121] - != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q59, q121] - = q102 - | q121 : int(1..2)]), - q102 < - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q59, q103]; - int(1..3)]) - -> - toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q59, q119] - != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q59, q119] - = q102 - | q119 : int(1..2)])) - = toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q44, q102]) - | q102 : int(1..2)]))) - | q103 : int(1..2)]) - \/ - or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q44, q101] /\ - !or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q59, q114] != 3 /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q59, q114] = q101 - | q114 : int(1..2)]) - /\ - (toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q59, q105] - != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q59, q105] = - q101 - | q105 : int(1..2)])) - < toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q44, q101]) - /\ - (and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q59, q106] != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q59, q106] < - q101 - -> - toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q59, q112] - != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q59, q112] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q59, q106] - | q112 : int(1..2)])) - = - toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence - [q44, - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q59, q106]]) - | q106 : int(1..2)]) - /\ - and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q44, q102] /\ - !or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q59, q110] - != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q59, q110] - = q102 - | q110 : int(1..2)]) - -> - toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q59, q108] - != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q59, q108] - = q102 - | q108 : int(1..2)])) - = toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q44, q102]) - | q102 : int(1..2), q102 < q101]))) - | q101 : int(1..2)])) - -> - toInt(or([q90 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ - and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q90, q91] = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q59, q91] - | q91 : int(1..2)]) - | q90 : int(1..2)])) - = - toInt(or([q95 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ - (and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q95, q96] -> - or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q59, q98] - != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q59, q98] - = q96 - | q98 : int(1..2)]) - | q96 : int(1..2)]) - /\ - and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q59, q100] - != 3 - -> - b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence - [q95, - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q59, q100]] - | q100 : int(1..2)])) - | q95 : int(1..2)])) - | q59 : int(1..2)]) - /\ - and([and([q61 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker, - !or([q77 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ - (and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q77, q79] != - 3 - -> - b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence - [q61, - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q77, q79]] - | q79 : int(1..2)]) - /\ - and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q61, q80] -> - or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q77, q82] - != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q77, q82] - = q80 - | q82 : int(1..2)]) - | q80 : int(1..2)])) - | q77 : int(1..2)]), - or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q61, q83] /\ - (toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q61, q83]) < - toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q44, q83]) - /\ - (and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q61, q84] -> - toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q61, q84]) = - toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q44, q84]) - | q84 : int(1..2), q84 < q83]) - /\ - and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q44, q84] /\ - !or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q61, q87] /\ - q87 = q84 - | q87 : int(1..2)]) - -> - toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q61, q84]) = - toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q44, q84]) - | q84 : int(1..2), q84 < q83]))) - | q83 : int(1..2)]) - \/ - or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q44, q83] /\ - !or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q61, q86] /\ q86 = q83 - | q86 : int(1..2)]) - /\ - (toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q61, q83]) < - toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q44, q83]) - /\ - (and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q61, q84] -> - toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q61, q84]) = - toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q44, q84]) - | q84 : int(1..2), q84 < q83]) - /\ - and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q44, q84] /\ - !or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q61, q85] /\ - q85 = q84 - | q85 : int(1..2)]) - -> - toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q61, q84]) = - toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q44, q84]) - | q84 : int(1..2), q84 < q83]))) - | q83 : int(1..2)]); - int(1..3)]) - -> - toInt(or([q64 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ - (and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q64, q66] != - 3 - -> - b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence - [q61, - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q64, q66]] - | q66 : int(1..2)]) - /\ - and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q61, q67] -> - or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q64, q69] - != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q64, q69] - = q67 - | q69 : int(1..2)]) - | q67 : int(1..2)])) - | q64 : int(1..2)])) - = - toInt(or([q72 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ - and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q72, q73] = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q61, q73] - | q73 : int(1..2)]) - | q72 : int(1..2)])) - | q61 : int(1..2)]))) - | q44 : int(1..2)]), - alldifferent_except([toInt(q34 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q34, q35] != - 3) - * - catchUndef(a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q34, q35], - 0) - | q34 : int(1..2), q35 : int(1..2)], - 0), - and([q36 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - sum([toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q36, q38] != 3) - | q38 : int(1..2)]) - >= 1 - | q36 : int(1..2)]), - 2 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - [a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[1, q12] | q12 : int(1..2)] a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q5, q30] = 1 - | q30 : int(1..2)]) - | q5 : int(1..2)]), - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker <= 2, - and([q6 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q6, 1] < - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q6, 2] - \/ a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q6, 1] = 3 - | q6 : int(1..2)]), - and([q6 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - (a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q6, 1] = 3 -> - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q6, 2] = 3) - | q6 : int(1..2)]), - and([q6 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - sum([toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q6, q9] != 3) - | q9 : int(1..2)]) - <= 2 - | q6 : int(1..2)]), - 2 = - sum([toInt(q14 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker) * - catchUndef(sum([toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q14, q16] != - 3) - | q16 : int(1..2)]), - 0) - | q14 : int(1..2)]), - and([1 = - sum([toInt(q31 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q31, q17]) - | q31 : int(1..2)]) - | q17 : int(1..2)]), - and([q32 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> - sum([toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q32, q33]) | q33 : int(1..2)]) >= 1 - | q32 : int(1..2)]), - 2 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> - [-toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[1, q25]) | q25 : int(1..2)] b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> - and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q21, q27] = false | q27 : int(1..2)]) - | q21 : int(1..2)]), - b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker <= 2, - and([q22 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> - sum([toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q22, q23]) | q23 : int(1..2)]) <= 2 - | q22 : int(1..2)]), - 2 = - sum([toInt(q28 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker) * - catchUndef(sum([toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q28, q29]) - | q29 : int(1..2)]), - 0) - | q28 : int(1..2)]) - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_2_2-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_2_2-solution000001.solution deleted file mode 100644 index cde05d5274..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_2_2-solution000001.solution +++ /dev/null @@ -1,11 +0,0 @@ -language Essence 1.3 - -letting a be partition({1, 2}) -$ Visualisation for a -$ 1 2 - -letting b be partition({1}, {2}) -$ Visualisation for b -$ 1 -$ 2 - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_2_2.eprime b/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_2_2.eprime deleted file mode 100644 index 2f788f30c5..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_2_2.eprime +++ /dev/null @@ -1,949 +0,0 @@ -language ESSENCE' 1.0 - -find a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker: int(0..2) -find a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy: - matrix indexed by [int(1..2), int(1..2)] of int(1..3) -find b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker: int(0..2) -find b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy: - matrix indexed by [int(1..2), int(1..2)] of int(1..3) -branching on - [a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker, - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy, - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker, - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy] -such that - or([q48 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ - (toInt(or([q173 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ - and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q173, q174] = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q48, q174] - | q174 : int(1..2)]) - | q173 : int(1..2)])) - < - toInt(or([q178 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ - and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q178, q179] = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q48, q179] - | q179 : int(1..2)]) - | q178 : int(1..2)])) - /\ - (and([q182 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ - (or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q182, q250] != 3 /\ - (toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q182, q271] - != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q182, q271] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q182, q250] - | q271 : int(1..2)])) - < - toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q48, q273] - != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q48, q273] = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q182, q250] - | q273 : int(1..2)])) - /\ - (and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q182, q274] != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q182, q274] < - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q182, q250] - -> - toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q182, q283] - != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q182, q283] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q182, q274] - | q283 : int(1..2)])) - = - toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q48, q285] - != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q48, q285] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q182, q274] - | q285 : int(1..2)])) - | q274 : int(1..2)]) - /\ - and([and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q48, q275] - != 3, - !or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q182, q277] - != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q182, q277] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q48, q275] - | q277 : int(1..2)]), - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q48, q275] - < - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q182, q250]; - int(1..3)]) - -> - toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q182, q279] - != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q182, q279] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q48, q275] - | q279 : int(1..2)])) - = - toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q48, q281] - != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q48, q281] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q48, q275] - | q281 : int(1..2)])) - | q275 : int(1..2)]))) - | q250 : int(1..2)]) - \/ - or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q48, q251] != 3 /\ - !or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q182, q253] != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q182, q253] = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q48, q251] - | q253 : int(1..2)]) - /\ - (toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q182, q255] - != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q182, q255] - = a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q48, q251] - | q255 : int(1..2)])) - < - toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q48, q257] - != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q48, q257] = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q48, q251] - | q257 : int(1..2)])) - /\ - (and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q182, q258] != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q182, q258] < - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q48, q251] - -> - toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q182, q267] - != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q182, q267] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q182, q258] - | q267 : int(1..2)])) - = - toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q48, q269] - != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q48, q269] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q182, q258] - | q269 : int(1..2)])) - | q258 : int(1..2)]) - /\ - and([and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q48, q259] - != 3, - !or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q182, q261] - != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q182, q261] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q48, q259] - | q261 : int(1..2)]), - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q48, q259] - < - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q48, q251]; - int(1..3)]) - -> - toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q182, q263] - != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q182, q263] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q48, q259] - | q263 : int(1..2)])) - = - toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q48, q265] - != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q48, q265] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q48, q259] - | q265 : int(1..2)])) - | q259 : int(1..2)]))) - | q251 : int(1..2)])) - -> - toInt(or([q240 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ - and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q240, q241] = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q182, q241] - | q241 : int(1..2)]) - | q240 : int(1..2)])) - = - toInt(or([q245 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ - and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q245, q246] = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q182, q246] - | q246 : int(1..2)]) - | q245 : int(1..2)])) - | q182 : int(1..2)]) - /\ - and([and([q184 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker, - !or([q197 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ - and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q197, q198] = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q184, q198] - | q198 : int(1..2)]) - | q197 : int(1..2)]), - or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q184, q202] != 3 /\ - (toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q184, q223] - != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q184, q223] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q184, q202] - | q223 : int(1..2)])) - < - toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q48, q225] - != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q48, q225] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q184, q202] - | q225 : int(1..2)])) - /\ - (and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q184, q226] - != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q184, q226] - < - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q184, q202] - -> - toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q184, q235] - != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q184, q235] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q184, q226] - | q235 : int(1..2)])) - = - toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q48, q237] - != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q48, q237] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q184, q226] - | q237 : int(1..2)])) - | q226 : int(1..2)]) - /\ - and([and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q48, q227] - != 3, - !or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q184, q229] - != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q184, q229] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q48, q227] - | q229 : int(1..2)]), - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q48, q227] - < - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q184, q202]; - int(1..3)]) - -> - toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q184, q231] - != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q184, q231] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q48, q227] - | q231 : int(1..2)])) - = - toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q48, q233] - != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q48, q233] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q48, q227] - | q233 : int(1..2)])) - | q227 : int(1..2)]))) - | q202 : int(1..2)]) - \/ - or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q48, q203] != 3 /\ - !or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q184, q205] != - 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q184, q205] = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q48, q203] - | q205 : int(1..2)]) - /\ - (toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q184, q207] - != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q184, q207] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q48, q203] - | q207 : int(1..2)])) - < - toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q48, q209] - != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q48, q209] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q48, q203] - | q209 : int(1..2)])) - /\ - (and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q184, q210] - != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q184, q210] - < a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q48, q203] - -> - toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q184, q219] - != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q184, q219] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q184, q210] - | q219 : int(1..2)])) - = - toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q48, q221] - != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q48, q221] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q184, q210] - | q221 : int(1..2)])) - | q210 : int(1..2)]) - /\ - and([and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q48, q211] - != 3, - !or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q184, q213] - != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q184, q213] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q48, q211] - | q213 : int(1..2)]), - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q48, q211] - < - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q48, q203]; - int(1..3)]) - -> - toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q184, q215] - != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q184, q215] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q48, q211] - | q215 : int(1..2)])) - = - toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q48, q217] - != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q48, q217] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q48, q211] - | q217 : int(1..2)])) - | q211 : int(1..2)]))) - | q203 : int(1..2)]); - int(1..3)]) - -> - toInt(or([q187 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ - and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q187, q188] = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q184, q188] - | q188 : int(1..2)]) - | q187 : int(1..2)])) - = - toInt(or([q192 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ - and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q192, q193] = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q184, q193] - | q193 : int(1..2)]) - | q192 : int(1..2)])) - | q184 : int(1..2)]))) - | q48 : int(1..2)]) - \/ - or([q50 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ - !or([q168 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ - and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q168, q169] = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q50, q169] - | q169 : int(1..2)]) - | q168 : int(1..2)]) - /\ - (toInt(or([q53 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ - and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q53, q54] = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q50, q54] - | q54 : int(1..2)]) - | q53 : int(1..2)])) - < - toInt(or([q58 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ - and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q58, q59] = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q50, q59] - | q59 : int(1..2)]) - | q58 : int(1..2)])) - /\ - (and([q62 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ - (or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q62, q130] != 3 /\ - (toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q62, q151] - != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q62, q151] = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q62, q130] - | q151 : int(1..2)])) - < - toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q50, q153] - != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q50, q153] = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q62, q130] - | q153 : int(1..2)])) - /\ - (and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q62, q154] != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q62, q154] < - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q62, q130] - -> - toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q62, q163] - != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q62, q163] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q62, q154] - | q163 : int(1..2)])) - = - toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q50, q165] - != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q50, q165] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q62, q154] - | q165 : int(1..2)])) - | q154 : int(1..2)]) - /\ - and([and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q50, q155] - != 3, - !or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q62, q157] - != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q62, q157] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q50, q155] - | q157 : int(1..2)]), - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q50, q155] - < - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q62, q130]; - int(1..3)]) - -> - toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q62, q159] - != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q62, q159] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q50, q155] - | q159 : int(1..2)])) - = - toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q50, q161] - != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q50, q161] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q50, q155] - | q161 : int(1..2)])) - | q155 : int(1..2)]))) - | q130 : int(1..2)]) - \/ - or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q50, q131] != 3 /\ - !or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q62, q133] != 3 /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q62, q133] = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q50, q131] - | q133 : int(1..2)]) - /\ - (toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q62, q135] - != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q62, q135] = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q50, q131] - | q135 : int(1..2)])) - < - toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q50, q137] - != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q50, q137] = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q50, q131] - | q137 : int(1..2)])) - /\ - (and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q62, q138] != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q62, q138] < - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q50, q131] - -> - toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q62, q147] - != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q62, q147] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q62, q138] - | q147 : int(1..2)])) - = - toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q50, q149] - != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q50, q149] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q62, q138] - | q149 : int(1..2)])) - | q138 : int(1..2)]) - /\ - and([and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q50, q139] - != 3, - !or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q62, q141] - != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q62, q141] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q50, q139] - | q141 : int(1..2)]), - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q50, q139] - < - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q50, q131]; - int(1..3)]) - -> - toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q62, q143] - != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q62, q143] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q50, q139] - | q143 : int(1..2)])) - = - toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q50, q145] - != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q50, q145] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q50, q139] - | q145 : int(1..2)])) - | q139 : int(1..2)]))) - | q131 : int(1..2)])) - -> - toInt(or([q120 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ - and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q120, q121] = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q62, q121] - | q121 : int(1..2)]) - | q120 : int(1..2)])) - = - toInt(or([q125 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ - and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q125, q126] = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q62, q126] - | q126 : int(1..2)]) - | q125 : int(1..2)])) - | q62 : int(1..2)]) - /\ - and([and([q64 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker, - !or([q77 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ - and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q77, q78] = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q64, q78] - | q78 : int(1..2)]) - | q77 : int(1..2)]), - or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q64, q82] != 3 /\ - (toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q64, q103] - != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q64, q103] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q64, q82] - | q103 : int(1..2)])) - < - toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q50, q105] - != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q50, q105] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q64, q82] - | q105 : int(1..2)])) - /\ - (and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q64, q106] - != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q64, q106] < - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q64, q82] - -> - toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q64, q115] - != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q64, q115] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q64, q106] - | q115 : int(1..2)])) - = - toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q50, q117] - != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q50, q117] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q64, q106] - | q117 : int(1..2)])) - | q106 : int(1..2)]) - /\ - and([and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q50, q107] - != 3, - !or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q64, q109] - != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q64, q109] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q50, q107] - | q109 : int(1..2)]), - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q50, q107] - < - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q64, q82]; - int(1..3)]) - -> - toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q64, q111] - != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q64, q111] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q50, q107] - | q111 : int(1..2)])) - = - toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q50, q113] - != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q50, q113] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q50, q107] - | q113 : int(1..2)])) - | q107 : int(1..2)]))) - | q82 : int(1..2)]) - \/ - or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q50, q83] != 3 /\ - !or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q64, q85] != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q64, q85] = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q50, q83] - | q85 : int(1..2)]) - /\ - (toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q64, q87] - != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q64, q87] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q50, q83] - | q87 : int(1..2)])) - < - toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q50, q89] - != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q50, q89] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q50, q83] - | q89 : int(1..2)])) - /\ - (and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q64, q90] != - 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q64, q90] < - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q50, q83] - -> - toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q64, q99] - != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q64, q99] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q64, q90] - | q99 : int(1..2)])) - = - toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q50, q101] - != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q50, q101] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q64, q90] - | q101 : int(1..2)])) - | q90 : int(1..2)]) - /\ - and([and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q50, q91] - != 3, - !or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q64, q93] - != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q64, q93] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q50, q91] - | q93 : int(1..2)]), - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q50, q91] - < - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q50, q83]; - int(1..3)]) - -> - toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q64, q95] - != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q64, q95] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q50, q91] - | q95 : int(1..2)])) - = - toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q50, q97] - != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q50, q97] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q50, q91] - | q97 : int(1..2)])) - | q91 : int(1..2)]))) - | q83 : int(1..2)]); - int(1..3)]) - -> - toInt(or([q67 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ - and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q67, q68] = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q64, q68] - | q68 : int(1..2)]) - | q67 : int(1..2)])) - = - toInt(or([q72 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ - and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q72, q73] = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q64, q73] - | q73 : int(1..2)]) - | q72 : int(1..2)])) - | q64 : int(1..2)]))) - | q50 : int(1..2)]), - alldifferent_except([toInt(q35 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q35, q36] != - 3) - * - catchUndef(a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q35, q36], - 0) - | q35 : int(1..2), q36 : int(1..2)], - 0), - and([q37 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - sum([toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q37, q39] != 3) - | q39 : int(1..2)]) - >= 1 - | q37 : int(1..2)]), - 2 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - [a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[1, q12] | q12 : int(1..2)] a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q5, q33] = 1 - | q33 : int(1..2)]) - | q5 : int(1..2)]), - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker <= 2, - and([q6 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q6, 1] < - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q6, 2] - \/ a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q6, 1] = 3 - | q6 : int(1..2)]), - and([q6 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - (a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q6, 1] = 3 -> - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q6, 2] = 3) - | q6 : int(1..2)]), - and([q6 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - sum([toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q6, q9] != 3) - | q9 : int(1..2)]) - <= 2 - | q6 : int(1..2)]), - 2 = - sum([toInt(q14 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker) * - catchUndef(sum([toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q14, q16] != - 3) - | q16 : int(1..2)]), - 0) - | q14 : int(1..2)]), - alldifferent_except([toInt(q40 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q40, q41] != - 3) - * - catchUndef(b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q40, q41], - 0) - | q40 : int(1..2), q41 : int(1..2)], - 0), - and([q42 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - sum([toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q42, q44] != 3) - | q44 : int(1..2)]) - >= 1 - | q42 : int(1..2)]), - 2 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - [b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[1, q28] | q28 : int(1..2)] b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q21, q34] = 1 - | q34 : int(1..2)]) - | q21 : int(1..2)]), - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker <= 2, - and([q22 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q22, 1] < - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q22, 2] - \/ b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q22, 1] = 3 - | q22 : int(1..2)]), - and([q22 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - (b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q22, 1] = 3 -> - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q22, 2] = 3) - | q22 : int(1..2)]), - and([q22 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - sum([toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q22, q25] != 3) - | q25 : int(1..2)]) - <= 2 - | q22 : int(1..2)]), - 2 = - sum([toInt(q30 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker) * - catchUndef(sum([toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q30, q32] != - 3) - | q32 : int(1..2)]), - 0) - | q30 : int(1..2)]) - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_2_3-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_2_3-solution000001.solution deleted file mode 100644 index cde05d5274..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_2_3-solution000001.solution +++ /dev/null @@ -1,11 +0,0 @@ -language Essence 1.3 - -letting a be partition({1, 2}) -$ Visualisation for a -$ 1 2 - -letting b be partition({1}, {2}) -$ Visualisation for b -$ 1 -$ 2 - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_2_3.eprime b/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_2_3.eprime deleted file mode 100644 index 191e70b297..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_2_3.eprime +++ /dev/null @@ -1,1210 +0,0 @@ -language ESSENCE' 1.0 - -find a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker: int(0..2) -find a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy: - matrix indexed by [int(1..2), int(1..2)] of int(1..3) -find b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker: int(0..2) -find b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker: - matrix indexed by [int(1..2)] of int(0..2) -find b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values: - matrix indexed by [int(1..2), int(1..2)] of int(1..2) -branching on - [a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker, - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy, - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker, - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker, - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values] -such that - or([q43 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ - (toInt(or([q198 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ - and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q198, q199] = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q43, q199] - | q199 : int(1..2)]) - | q198 : int(1..2)])) - < - toInt(or([q203 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - (and([q205 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q203] - -> - or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q43, q207] != - 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q43, q207] = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q203, q205] - | q207 : int(1..2)]) - | q205 : int(1..2)]) - /\ - and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q43, q209] != 3 -> - or([q211 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q203] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q203, q211] - = a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q43, q209] - | q211 : int(1..2)]) - | q209 : int(1..2)])) - | q203 : int(1..2)])) - /\ - (and([q213 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ - (or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q213, q299] != 3 /\ - (toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q213, q320] - != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q213, q320] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q213, q299] - | q320 : int(1..2)])) - < - toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q43, q322] - != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q43, q322] = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q213, q299] - | q322 : int(1..2)])) - /\ - (and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q213, q323] != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q213, q323] < - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q213, q299] - -> - toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q213, q332] - != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q213, q332] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q213, q323] - | q332 : int(1..2)])) - = - toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q43, q334] - != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q43, q334] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q213, q323] - | q334 : int(1..2)])) - | q323 : int(1..2)]) - /\ - and([and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q43, q324] - != 3, - !or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q213, q326] - != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q213, q326] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q43, q324] - | q326 : int(1..2)]), - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q43, q324] - < - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q213, q299]; - int(1..3)]) - -> - toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q213, q328] - != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q213, q328] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q43, q324] - | q328 : int(1..2)])) - = - toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q43, q330] - != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q43, q330] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q43, q324] - | q330 : int(1..2)])) - | q324 : int(1..2)]))) - | q299 : int(1..2)]) - \/ - or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q43, q300] != 3 /\ - !or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q213, q302] != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q213, q302] = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q43, q300] - | q302 : int(1..2)]) - /\ - (toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q213, q304] - != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q213, q304] - = a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q43, q300] - | q304 : int(1..2)])) - < - toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q43, q306] - != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q43, q306] = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q43, q300] - | q306 : int(1..2)])) - /\ - (and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q213, q307] != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q213, q307] < - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q43, q300] - -> - toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q213, q316] - != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q213, q316] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q213, q307] - | q316 : int(1..2)])) - = - toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q43, q318] - != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q43, q318] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q213, q307] - | q318 : int(1..2)])) - | q307 : int(1..2)]) - /\ - and([and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q43, q308] - != 3, - !or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q213, q310] - != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q213, q310] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q43, q308] - | q310 : int(1..2)]), - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q43, q308] - < - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q43, q300]; - int(1..3)]) - -> - toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q213, q312] - != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q213, q312] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q43, q308] - | q312 : int(1..2)])) - = - toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q43, q314] - != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q43, q314] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q43, q308] - | q314 : int(1..2)])) - | q308 : int(1..2)]))) - | q300 : int(1..2)])) - -> - toInt(or([q283 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ - and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q283, q284] = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q213, q284] - | q284 : int(1..2)]) - | q283 : int(1..2)])) - = - toInt(or([q288 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - (and([q290 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q288] - -> - or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q213, q292] - != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q213, q292] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q288, q290] - | q292 : int(1..2)]) - | q290 : int(1..2)]) - /\ - and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q213, q294] - != 3 - -> - or([q296 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q288] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q288, q296] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q213, q294] - | q296 : int(1..2)]) - | q294 : int(1..2)])) - | q288 : int(1..2)])) - | q213 : int(1..2)]) - /\ - and([and([q215 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker, - !or([q234 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ - (and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q234, q236] - != 3 - -> - or([q238 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q215] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q215, q238] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q234, q236] - | q238 : int(1..2)]) - | q236 : int(1..2)]) - /\ - and([q240 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q215] - -> - or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q234, q242] - != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q234, q242] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q215, q240] - | q242 : int(1..2)]) - | q240 : int(1..2)])) - | q234 : int(1..2)]), - or([q245 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q215] - /\ - (toInt(or([q266 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q215] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q215, q266] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q215, q245] - | q266 : int(1..2)])) - < - toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q43, q268] - != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q43, q268] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q215, q245] - | q268 : int(1..2)])) - /\ - (and([q269 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q215] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q215, q269] - < - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q215, q245] - -> - toInt(or([q278 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q215] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q215, q278] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q215, q269] - | q278 : int(1..2)])) - = - toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q43, q280] - != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q43, q280] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q215, q269] - | q280 : int(1..2)])) - | q269 : int(1..2)]) - /\ - and([and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q43, q270] - != 3, - !or([q272 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q215] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q215, q272] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q43, q270] - | q272 : int(1..2)]), - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q43, q270] - < - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q215, q245]; - int(1..3)]) - -> - toInt(or([q274 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q215] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q215, q274] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q43, q270] - | q274 : int(1..2)])) - = - toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q43, q276] - != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q43, q276] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q43, q270] - | q276 : int(1..2)])) - | q270 : int(1..2)]))) - | q245 : int(1..2)]) - \/ - or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q43, q246] != 3 /\ - !or([q248 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q215] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q215, q248] - = a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q43, q246] - | q248 : int(1..2)]) - /\ - (toInt(or([q250 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q215] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q215, q250] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q43, q246] - | q250 : int(1..2)])) - < - toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q43, q252] - != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q43, q252] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q43, q246] - | q252 : int(1..2)])) - /\ - (and([q253 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q215] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q215, q253] - < a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q43, q246] - -> - toInt(or([q262 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q215] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q215, q262] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q215, q253] - | q262 : int(1..2)])) - = - toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q43, q264] - != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q43, q264] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q215, q253] - | q264 : int(1..2)])) - | q253 : int(1..2)]) - /\ - and([and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q43, q254] - != 3, - !or([q256 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q215] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q215, q256] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q43, q254] - | q256 : int(1..2)]), - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q43, q254] - < - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q43, q246]; - int(1..3)]) - -> - toInt(or([q258 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q215] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q215, q258] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q43, q254] - | q258 : int(1..2)])) - = - toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q43, q260] - != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q43, q260] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q43, q254] - | q260 : int(1..2)])) - | q254 : int(1..2)]))) - | q246 : int(1..2)]); - int(1..3)]) - -> - toInt(or([q218 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ - (and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q218, q220] - != 3 - -> - or([q222 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q215] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q215, q222] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q218, q220] - | q222 : int(1..2)]) - | q220 : int(1..2)]) - /\ - and([q224 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q215] - -> - or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q218, q226] - != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q218, q226] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q215, q224] - | q226 : int(1..2)]) - | q224 : int(1..2)])) - | q218 : int(1..2)])) - = - toInt(or([q229 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - (b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q229] = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q215] - /\ - and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q229, q230] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q215, q230] - | q230 : int(1..2)])) - | q229 : int(1..2)])) - | q215 : int(1..2)]))) - | q43 : int(1..2)]) - \/ - or([q45 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - !or([q187 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ - (and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q187, q189] != 3 -> - or([q191 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q45] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q45, q191] = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q187, q189] - | q191 : int(1..2)]) - | q189 : int(1..2)]) - /\ - and([q193 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q45] -> - or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q187, q195] != 3 /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q187, q195] = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q45, q193] - | q195 : int(1..2)]) - | q193 : int(1..2)])) - | q187 : int(1..2)]) - /\ - (toInt(or([q48 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ - (and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q48, q50] != 3 -> - or([q52 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q45] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q45, q52] - = a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q48, q50] - | q52 : int(1..2)]) - | q50 : int(1..2)]) - /\ - and([q54 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q45] - -> - or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q48, q56] != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q48, q56] = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q45, q54] - | q56 : int(1..2)]) - | q54 : int(1..2)])) - | q48 : int(1..2)])) - < - toInt(or([q59 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - (b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q59] = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q45] - /\ - and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q59, q60] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q45, q60] - | q60 : int(1..2)])) - | q59 : int(1..2)])) - /\ - (and([q63 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ - (or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q63, q149] != 3 /\ - (toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q63, q170] - != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q63, q170] = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q63, q149] - | q170 : int(1..2)])) - < - toInt(or([q172 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q45] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q45, q172] - = a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q63, q149] - | q172 : int(1..2)])) - /\ - (and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q63, q173] != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q63, q173] < - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q63, q149] - -> - toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q63, q182] - != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q63, q182] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q63, q173] - | q182 : int(1..2)])) - = - toInt(or([q184 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q45] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q45, q184] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q63, q173] - | q184 : int(1..2)])) - | q173 : int(1..2)]) - /\ - and([and([q174 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q45], - !or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q63, q180] - != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q63, q180] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q45, q174] - | q180 : int(1..2)]), - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q45, q174] - < - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q63, q149]; - int(1..3)]) - -> - toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q63, q176] - != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q63, q176] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q45, q174] - | q176 : int(1..2)])) - = - toInt(or([q178 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q45] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q45, q178] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q45, q174] - | q178 : int(1..2)])) - | q174 : int(1..2)]))) - | q149 : int(1..2)]) - \/ - or([q150 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q45] /\ - !or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q63, q168] != 3 /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q63, q168] = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q45, q150] - | q168 : int(1..2)]) - /\ - (toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q63, q152] - != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q63, q152] = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q45, q150] - | q152 : int(1..2)])) - < - toInt(or([q154 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q45] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q45, q154] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q45, q150] - | q154 : int(1..2)])) - /\ - (and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q63, q155] != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q63, q155] < - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q45, q150] - -> - toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q63, q164] - != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q63, q164] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q63, q155] - | q164 : int(1..2)])) - = - toInt(or([q166 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q45] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q45, q166] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q63, q155] - | q166 : int(1..2)])) - | q155 : int(1..2)]) - /\ - and([and([q156 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q45], - !or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q63, q162] - != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q63, q162] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q45, q156] - | q162 : int(1..2)]), - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q45, q156] - < - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q45, q150]; - int(1..3)]) - -> - toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q63, q158] - != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q63, q158] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q45, q156] - | q158 : int(1..2)])) - = - toInt(or([q160 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q45] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q45, q160] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q45, q156] - | q160 : int(1..2)])) - | q156 : int(1..2)]))) - | q150 : int(1..2)])) - -> - toInt(or([q133 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ - and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q133, q134] = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q63, q134] - | q134 : int(1..2)]) - | q133 : int(1..2)])) - = - toInt(or([q138 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - (and([q140 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q138] - -> - or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q63, q142] - != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q63, q142] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q138, q140] - | q142 : int(1..2)]) - | q140 : int(1..2)]) - /\ - and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q63, q144] - != 3 - -> - or([q146 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q138] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q138, q146] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q63, q144] - | q146 : int(1..2)]) - | q144 : int(1..2)])) - | q138 : int(1..2)])) - | q63 : int(1..2)]) - /\ - and([and([q65 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker, - !or([q84 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ - (and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q84, q86] != - 3 - -> - or([q88 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q65] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q65, q88] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q84, q86] - | q88 : int(1..2)]) - | q86 : int(1..2)]) - /\ - and([q90 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q65] - -> - or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q84, q92] - != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q84, q92] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q65, q90] - | q92 : int(1..2)]) - | q90 : int(1..2)])) - | q84 : int(1..2)]), - or([q95 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q65] - /\ - (toInt(or([q116 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q65] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q65, q116] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q65, q95] - | q116 : int(1..2)])) - < - toInt(or([q118 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q45] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q45, q118] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q65, q95] - | q118 : int(1..2)])) - /\ - (and([q119 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q65] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q65, q119] - < - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q65, q95] - -> - toInt(or([q128 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q65] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q65, q128] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q65, q119] - | q128 : int(1..2)])) - = - toInt(or([q130 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q45] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q45, q130] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q65, q119] - | q130 : int(1..2)])) - | q119 : int(1..2)]) - /\ - and([and([q120 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q45], - !or([q126 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q65] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q65, q126] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q45, q120] - | q126 : int(1..2)]), - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q45, q120] - < - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q65, q95]; - int(1..3)]) - -> - toInt(or([q122 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q65] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q65, q122] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q45, q120] - | q122 : int(1..2)])) - = - toInt(or([q124 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q45] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q45, q124] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q45, q120] - | q124 : int(1..2)])) - | q120 : int(1..2)]))) - | q95 : int(1..2)]) - \/ - or([q96 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q45] - /\ - !or([q114 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q65] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q65, q114] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q45, q96] - | q114 : int(1..2)]) - /\ - (toInt(or([q98 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q65] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q65, q98] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q45, q96] - | q98 : int(1..2)])) - < - toInt(or([q100 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q45] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q45, q100] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q45, q96] - | q100 : int(1..2)])) - /\ - (and([q101 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q65] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q65, q101] - < - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q45, q96] - -> - toInt(or([q110 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q65] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q65, q110] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q65, q101] - | q110 : int(1..2)])) - = - toInt(or([q112 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q45] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q45, q112] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q65, q101] - | q112 : int(1..2)])) - | q101 : int(1..2)]) - /\ - and([and([q102 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q45], - !or([q108 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q65] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q65, q108] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q45, q102] - | q108 : int(1..2)]), - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q45, q102] - < - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q45, q96]; - int(1..3)]) - -> - toInt(or([q104 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q65] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q65, q104] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q45, q102] - | q104 : int(1..2)])) - = - toInt(or([q106 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q45] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q45, q106] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q45, q102] - | q106 : int(1..2)])) - | q102 : int(1..2)]))) - | q96 : int(1..2)]); - int(1..3)]) - -> - toInt(or([q68 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ - (and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q68, q70] != - 3 - -> - or([q72 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q65] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q65, q72] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q68, q70] - | q72 : int(1..2)]) - | q70 : int(1..2)]) - /\ - and([q74 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q65] - -> - or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q68, q76] - != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q68, q76] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q65, q74] - | q76 : int(1..2)]) - | q74 : int(1..2)])) - | q68 : int(1..2)])) - = - toInt(or([q79 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - (b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q79] = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q65] - /\ - and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q79, q80] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q65, q80] - | q80 : int(1..2)])) - | q79 : int(1..2)])) - | q65 : int(1..2)]))) - | q45 : int(1..2)]), - alldifferent_except([toInt(q32 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q32, q33] != - 3) - * - catchUndef(a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q32, q33], - 0) - | q32 : int(1..2), q33 : int(1..2)], - 0), - and([q34 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - sum([toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q34, q36] != 3) - | q36 : int(1..2)]) - >= 1 - | q34 : int(1..2)]), - 2 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - [a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[1, q12] | q12 : int(1..2)] a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q5, q30] = 1 - | q30 : int(1..2)]) - | q5 : int(1..2)]), - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker <= 2, - and([q6 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q6, 1] < - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q6, 2] - \/ a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q6, 1] = 3 - | q6 : int(1..2)]), - and([q6 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - (a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q6, 1] = 3 -> - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q6, 2] = 3) - | q6 : int(1..2)]), - and([q6 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - sum([toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q6, q9] != 3) - | q9 : int(1..2)]) - <= 2 - | q6 : int(1..2)]), - 2 = - sum([toInt(q14 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker) * - catchUndef(sum([toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q14, q16] != - 3) - | q16 : int(1..2)]), - 0) - | q14 : int(1..2)]), - alldifferent_except([toInt(q37 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - q38 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q37]) - * - catchUndef(b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q37, q38], - 0) - | q37 : int(1..2), q38 : int(1..2)], - 0), - and([q39 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q39] >= 1 - | q39 : int(1..2)]), - 2 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - flatten([[b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[1]; int(1)], - flatten([[b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[1, q27]; - int(1)] - | q27 : int(1..2)]); - int(1..2)]) - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q21] = 0 /\ - and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q21, q31] = 1 - | q31 : int(1..2)]) - | q21 : int(1..2)]), - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker <= 2, - and([q22 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - (2 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q22] -> - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q22, 1] < - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q22, 2]) - | q22 : int(1..2)]), - and([q22 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - and([q24 > b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q22] -> - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q22, q24] = 1 - | q24 : int(1..2)]) - | q22 : int(1..2)]), - and([q22 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q22] <= 2 - | q22 : int(1..2)]), - 2 = - sum([toInt(q29 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker) * - catchUndef(b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q29], 0) - | q29 : int(1..2)]) - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_2_4-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_2_4-solution000001.solution deleted file mode 100644 index cde05d5274..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_2_4-solution000001.solution +++ /dev/null @@ -1,11 +0,0 @@ -language Essence 1.3 - -letting a be partition({1, 2}) -$ Visualisation for a -$ 1 2 - -letting b be partition({1}, {2}) -$ Visualisation for b -$ 1 -$ 2 - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_2_4.eprime b/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_2_4.eprime deleted file mode 100644 index 99d329b649..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_2_4.eprime +++ /dev/null @@ -1,809 +0,0 @@ -language ESSENCE' 1.0 - -find a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker: int(0..2) -find a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy: - matrix indexed by [int(1..2), int(1..2)] of int(1..3) -find b_PartitionOccurrence_NumParts: int(1..2) -find b_PartitionOccurrence_WhichPart: matrix indexed by [int(1..2)] of int(1..2) -find b_PartitionOccurrence_PartSizes: matrix indexed by [int(1..2)] of int(0..2) -find b_PartitionOccurrence_FirstIndex: matrix indexed by [int(1..2)] of int(1..2) -branching on - [a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker, - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy, b_PartitionOccurrence_NumParts, - b_PartitionOccurrence_WhichPart, b_PartitionOccurrence_PartSizes, b_PartitionOccurrence_FirstIndex] -such that - or([q36 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ - (toInt(or([q183 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ - and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q183, q184] = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q36, q184] - | q184 : int(1..2)]) - | q183 : int(1..2)])) - < - toInt(or([q187 <= b_PartitionOccurrence_NumParts /\ - (and([b_PartitionOccurrence_WhichPart[q190] = q187 -> - or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q36, q192] != - 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q36, q192] = - q190 - | q192 : int(1..2)]) - | q190 : int(1..2)]) - /\ - and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q36, q194] != 3 -> - or([b_PartitionOccurrence_WhichPart[q196] = q187 /\ - q196 = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q36, q194] - | q196 : int(1..2)]) - | q194 : int(1..2)])) - | q187 : int(1..2)])) - /\ - (and([q198 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ - (or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q198, q290] != 3 /\ - (toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q198, q311] - != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q198, q311] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q198, q290] - | q311 : int(1..2)])) - < - toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q36, q313] - != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q36, q313] = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q198, q290] - | q313 : int(1..2)])) - /\ - (and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q198, q314] != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q198, q314] < - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q198, q290] - -> - toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q198, q323] - != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q198, q323] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q198, q314] - | q323 : int(1..2)])) - = - toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q36, q325] - != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q36, q325] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q198, q314] - | q325 : int(1..2)])) - | q314 : int(1..2)]) - /\ - and([and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q36, q315] - != 3, - !or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q198, q317] - != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q198, q317] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q36, q315] - | q317 : int(1..2)]), - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q36, q315] - < - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q198, q290]; - int(1..3)]) - -> - toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q198, q319] - != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q198, q319] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q36, q315] - | q319 : int(1..2)])) - = - toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q36, q321] - != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q36, q321] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q36, q315] - | q321 : int(1..2)])) - | q315 : int(1..2)]))) - | q290 : int(1..2)]) - \/ - or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q36, q291] != 3 /\ - !or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q198, q293] != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q198, q293] = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q36, q291] - | q293 : int(1..2)]) - /\ - (toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q198, q295] - != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q198, q295] - = a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q36, q291] - | q295 : int(1..2)])) - < - toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q36, q297] - != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q36, q297] = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q36, q291] - | q297 : int(1..2)])) - /\ - (and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q198, q298] != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q198, q298] < - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q36, q291] - -> - toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q198, q307] - != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q198, q307] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q198, q298] - | q307 : int(1..2)])) - = - toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q36, q309] - != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q36, q309] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q198, q298] - | q309 : int(1..2)])) - | q298 : int(1..2)]) - /\ - and([and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q36, q299] - != 3, - !or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q198, q301] - != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q198, q301] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q36, q299] - | q301 : int(1..2)]), - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q36, q299] - < - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q36, q291]; - int(1..3)]) - -> - toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q198, q303] - != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q198, q303] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q36, q299] - | q303 : int(1..2)])) - = - toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q36, q305] - != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q36, q305] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q36, q299] - | q305 : int(1..2)])) - | q299 : int(1..2)]))) - | q291 : int(1..2)])) - -> - toInt(or([q274 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ - and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q274, q275] = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q198, q275] - | q275 : int(1..2)]) - | q274 : int(1..2)])) - = - toInt(or([q278 <= b_PartitionOccurrence_NumParts /\ - (and([b_PartitionOccurrence_WhichPart[q281] = q278 -> - or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q198, q283] - != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q198, q283] - = q281 - | q283 : int(1..2)]) - | q281 : int(1..2)]) - /\ - and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q198, q285] - != 3 - -> - or([b_PartitionOccurrence_WhichPart[q287] = q278 /\ - q287 = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q198, q285] - | q287 : int(1..2)]) - | q285 : int(1..2)])) - | q278 : int(1..2)])) - | q198 : int(1..2)]) - /\ - and([and([q199 <= b_PartitionOccurrence_NumParts, - !or([q214 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ - (and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q214, q216] - != 3 - -> - or([b_PartitionOccurrence_WhichPart[q218] = q199 /\ - q218 = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q214, q216] - | q218 : int(1..2)]) - | q216 : int(1..2)]) - /\ - and([b_PartitionOccurrence_WhichPart[q220] = q199 -> - or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q214, q222] - != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q214, q222] - = q220 - | q222 : int(1..2)]) - | q220 : int(1..2)])) - | q214 : int(1..2)]), - or([b_PartitionOccurrence_WhichPart[q225] = q199 /\ - (sum([toInt(b_PartitionOccurrence_WhichPart[q246] = q199) * catchUndef(toInt(q246 = q225), 0) - | q246 : int(1..2)]) - < - toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q36, q248] - != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q36, q248] - = q225 - | q248 : int(1..2)])) - /\ - (and([b_PartitionOccurrence_WhichPart[q249] = q199 -> - sum([toInt(b_PartitionOccurrence_WhichPart[q258] = q199) * - catchUndef(toInt(q258 = q249), 0) - | q258 : int(1..2)]) - = - toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q36, q260] - != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q36, q260] - = q249 - | q260 : int(1..2)])) - | q249 : int(1..2), q249 < q225]) - /\ - and([and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q36, q250] - != 3, - !or([b_PartitionOccurrence_WhichPart[q252] = q199 /\ - q252 = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q36, q250] - | q252 : int(1..2)]), - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q36, q250] - < q225; - int(1..3)]) - -> - sum([toInt(b_PartitionOccurrence_WhichPart[q254] = q199) * - catchUndef(toInt(q254 = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q36, q250]), - 0) - | q254 : int(1..2)]) - = - toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q36, q256] - != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q36, q256] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q36, q250] - | q256 : int(1..2)])) - | q250 : int(1..2)]))) - | q225 : int(1..2)]) - \/ - or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q36, q226] != 3 /\ - !or([b_PartitionOccurrence_WhichPart[q228] = q199 /\ - q228 = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q36, q226] - | q228 : int(1..2)]) - /\ - (sum([toInt(b_PartitionOccurrence_WhichPart[q230] = q199) * - catchUndef(toInt(q230 = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q36, q226]), - 0) - | q230 : int(1..2)]) - < - toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q36, q232] - != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q36, q232] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q36, q226] - | q232 : int(1..2)])) - /\ - (and([b_PartitionOccurrence_WhichPart[q233] = q199 /\ - q233 < - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q36, q226] - -> - sum([toInt(b_PartitionOccurrence_WhichPart[q242] = q199) * - catchUndef(toInt(q242 = q233), 0) - | q242 : int(1..2)]) - = - toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q36, q244] - != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q36, q244] - = q233 - | q244 : int(1..2)])) - | q233 : int(1..2)]) - /\ - and([and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q36, q234] - != 3, - !or([b_PartitionOccurrence_WhichPart[q236] = q199 /\ - q236 = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q36, q234] - | q236 : int(1..2)]), - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q36, q234] - < - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q36, q226]; - int(1..3)]) - -> - sum([toInt(b_PartitionOccurrence_WhichPart[q238] = q199) * - catchUndef(toInt(q238 = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q36, q234]), - 0) - | q238 : int(1..2)]) - = - toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q36, q240] - != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q36, q240] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q36, q234] - | q240 : int(1..2)])) - | q234 : int(1..2)]))) - | q226 : int(1..2)]); - int(1..3)]) - -> - toInt(or([q263 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ - (and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q263, q265] - != 3 - -> - or([b_PartitionOccurrence_WhichPart[q267] = q199 /\ - q267 = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q263, q265] - | q267 : int(1..2)]) - | q265 : int(1..2)]) - /\ - and([b_PartitionOccurrence_WhichPart[q269] = q199 -> - or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q263, q271] - != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q263, q271] - = q269 - | q271 : int(1..2)]) - | q269 : int(1..2)])) - | q263 : int(1..2)])) - = - toInt(or([q202 <= b_PartitionOccurrence_NumParts /\ - (and([b_PartitionOccurrence_WhichPart[q205] = q202 -> - or([b_PartitionOccurrence_WhichPart[q207] = q199 /\ q207 = q205 | q207 : int(1..2)]) - | q205 : int(1..2)]) - /\ - and([b_PartitionOccurrence_WhichPart[q209] = q199 -> - or([b_PartitionOccurrence_WhichPart[q211] = q202 /\ q211 = q209 | q211 : int(1..2)]) - | q209 : int(1..2)])) - | q202 : int(1..2)])) - | q199 : int(1..2)]))) - | q36 : int(1..2)]) - \/ - or([q37 <= b_PartitionOccurrence_NumParts /\ - !or([q172 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ - (and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q172, q174] != 3 -> - or([b_PartitionOccurrence_WhichPart[q176] = q37 /\ - q176 = a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q172, q174] - | q176 : int(1..2)]) - | q174 : int(1..2)]) - /\ - and([b_PartitionOccurrence_WhichPart[q178] = q37 -> - or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q172, q180] != 3 /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q172, q180] = q178 - | q180 : int(1..2)]) - | q178 : int(1..2)])) - | q172 : int(1..2)]) - /\ - (toInt(or([q161 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ - (and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q161, q163] != 3 - -> - or([b_PartitionOccurrence_WhichPart[q165] = q37 /\ - q165 = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q161, q163] - | q165 : int(1..2)]) - | q163 : int(1..2)]) - /\ - and([b_PartitionOccurrence_WhichPart[q167] = q37 -> - or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q161, q169] != - 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q161, q169] = - q167 - | q169 : int(1..2)]) - | q167 : int(1..2)])) - | q161 : int(1..2)])) - < - toInt(or([q40 <= b_PartitionOccurrence_NumParts /\ - (and([b_PartitionOccurrence_WhichPart[q43] = q40 -> - or([b_PartitionOccurrence_WhichPart[q45] = q37 /\ q45 = q43 | q45 : int(1..2)]) - | q43 : int(1..2)]) - /\ - and([b_PartitionOccurrence_WhichPart[q47] = q37 -> - or([b_PartitionOccurrence_WhichPart[q49] = q40 /\ q49 = q47 | q49 : int(1..2)]) - | q47 : int(1..2)])) - | q40 : int(1..2)])) - /\ - (and([q71 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ - (or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q71, q72] != 3 /\ - (toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q71, q80] != - 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q71, q80] = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q71, q72] - | q80 : int(1..2)])) - < - sum([toInt(b_PartitionOccurrence_WhichPart[q63] = q37) * - catchUndef(toInt(q63 = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q71, q72]), - 0) - | q63 : int(1..2)]) - /\ - (and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q71, q73] != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q71, q73] < - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q71, q72] - -> - toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q71, q75] - != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q71, q75] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q71, q73] - | q75 : int(1..2)])) - = - sum([toInt(b_PartitionOccurrence_WhichPart[q69] = q37) * - catchUndef(toInt(q69 = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q71, q73]), - 0) - | q69 : int(1..2)]) - | q73 : int(1..2)]) - /\ - and([!or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q71, q76] - != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q71, q76] = - q64 | q76 : int(1..2)]) - /\ - q64 < a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q71, q72] - -> - (b_PartitionOccurrence_WhichPart[q64] = q37 -> - toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q71, q78] - != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q71, q78] - = q64 - | q78 : int(1..2)])) - = - sum([toInt(b_PartitionOccurrence_WhichPart[q66] = q37) * catchUndef(toInt(q66 = q64), 0) - | q66 : int(1..2)])) - | q64 : int(1..2)]))) - | q72 : int(1..2)]) - \/ - or([!or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q71, q89] != 3 /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q71, q89] = q52 - | q89 : int(1..2)]) - /\ - (b_PartitionOccurrence_WhichPart[q52] = q37 /\ - (toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q71, q88] - != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q71, q88] = - q52 | q88 : int(1..2)])) - < - sum([toInt(b_PartitionOccurrence_WhichPart[q54] = q37) * catchUndef(toInt(q54 = q52), 0) - | q54 : int(1..2)]) - /\ - (and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q71, q81] != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q71, q81] < q52 - -> - toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q71, q83] - != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q71, q83] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q71, q81] - | q83 : int(1..2)])) - = - sum([toInt(b_PartitionOccurrence_WhichPart[q60] = q37) * - catchUndef(toInt(q60 = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q71, q81]), - 0) - | q60 : int(1..2)]) - | q81 : int(1..2)]) - /\ - and([!or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q71, q84] - != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q71, q84] - = q55 - | q84 : int(1..2)]) - -> - (b_PartitionOccurrence_WhichPart[q55] = q37 -> - toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q71, q86] - != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q71, q86] - = q55 - | q86 : int(1..2)])) - = - sum([toInt(b_PartitionOccurrence_WhichPart[q57] = q37) * catchUndef(toInt(q57 = q55), 0) - | q57 : int(1..2)])) - | q55 : int(1..2), q55 < q52])))) - | q52 : int(1..2)])) - -> - toInt(or([q145 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ - and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q145, q146] = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q71, q146] - | q146 : int(1..2)]) - | q145 : int(1..2)])) - = - toInt(or([q149 <= b_PartitionOccurrence_NumParts /\ - (and([b_PartitionOccurrence_WhichPart[q152] = q149 -> - or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q71, q154] - != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q71, q154] - = q152 - | q154 : int(1..2)]) - | q152 : int(1..2)]) - /\ - and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q71, q156] - != 3 - -> - or([b_PartitionOccurrence_WhichPart[q158] = q149 /\ - q158 = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q71, q156] - | q158 : int(1..2)]) - | q156 : int(1..2)])) - | q149 : int(1..2)])) - | q71 : int(1..2)]) - /\ - and([and([q90 <= b_PartitionOccurrence_NumParts, - !or([q105 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ - (and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q105, q107] - != 3 - -> - or([b_PartitionOccurrence_WhichPart[q109] = q90 /\ - q109 = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q105, q107] - | q109 : int(1..2)]) - | q107 : int(1..2)]) - /\ - and([b_PartitionOccurrence_WhichPart[q111] = q90 -> - or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q105, q113] - != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q105, q113] - = q111 - | q113 : int(1..2)]) - | q111 : int(1..2)])) - | q105 : int(1..2)]), - or([b_PartitionOccurrence_WhichPart[q122] = q90 /\ - (toInt(or([b_PartitionOccurrence_WhichPart[q115] = q90 /\ q115 = q122 | q115 : int(1..2)])) < - sum([toInt(b_PartitionOccurrence_WhichPart[q63] = q37) * catchUndef(toInt(q63 = q122), 0) - | q63 : int(1..2)]) - /\ - (and([b_PartitionOccurrence_WhichPart[q118] = q90 -> - toInt(or([b_PartitionOccurrence_WhichPart[q117] = q90 /\ q117 = q118 - | q117 : int(1..2)])) - = - sum([toInt(b_PartitionOccurrence_WhichPart[q69] = q37) * catchUndef(toInt(q69 = q118), 0) - | q69 : int(1..2)]) - | q118 : int(1..2), q118 < q122]) - /\ - and([!or([b_PartitionOccurrence_WhichPart[q121] = q90 /\ q121 = q64 | q121 : int(1..2)]) -> - (b_PartitionOccurrence_WhichPart[q64] = q37 -> - toInt(or([b_PartitionOccurrence_WhichPart[q120] = q90 /\ q120 = q64 - | q120 : int(1..2)])) - = - sum([toInt(b_PartitionOccurrence_WhichPart[q66] = q37) * catchUndef(toInt(q66 = q64), 0) - | q66 : int(1..2)])) - | q64 : int(1..2), q64 < q122]))) - | q122 : int(1..2)]) - \/ - or([!or([b_PartitionOccurrence_WhichPart[q131] = q90 /\ q131 = q52 | q131 : int(1..2)]) /\ - (b_PartitionOccurrence_WhichPart[q52] = q37 /\ - (toInt(or([b_PartitionOccurrence_WhichPart[q124] = q90 /\ q124 = q52 | q124 : int(1..2)])) < - sum([toInt(b_PartitionOccurrence_WhichPart[q54] = q37) * catchUndef(toInt(q54 = q52), 0) - | q54 : int(1..2)]) - /\ - (and([b_PartitionOccurrence_WhichPart[q127] = q90 -> - toInt(or([b_PartitionOccurrence_WhichPart[q126] = q90 /\ q126 = q127 - | q126 : int(1..2)])) - = - sum([toInt(b_PartitionOccurrence_WhichPart[q60] = q37) * - catchUndef(toInt(q60 = q127), 0) - | q60 : int(1..2)]) - | q127 : int(1..2), q127 < q52]) - /\ - and([!or([b_PartitionOccurrence_WhichPart[q130] = q90 /\ q130 = q55 | q130 : int(1..2)]) -> - (b_PartitionOccurrence_WhichPart[q55] = q37 -> - toInt(or([b_PartitionOccurrence_WhichPart[q129] = q90 /\ q129 = q55 - | q129 : int(1..2)])) - = - sum([toInt(b_PartitionOccurrence_WhichPart[q57] = q37) * - catchUndef(toInt(q57 = q55), 0) - | q57 : int(1..2)])) - | q55 : int(1..2), q55 < q52])))) - | q52 : int(1..2)]); - int(1..3)]) - -> - toInt(or([q134 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ - (and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q134, q136] - != 3 - -> - or([b_PartitionOccurrence_WhichPart[q138] = q90 /\ - q138 = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q134, q136] - | q138 : int(1..2)]) - | q136 : int(1..2)]) - /\ - and([b_PartitionOccurrence_WhichPart[q140] = q90 -> - or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q134, q142] - != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q134, q142] - = q140 - | q142 : int(1..2)]) - | q140 : int(1..2)])) - | q134 : int(1..2)])) - = - toInt(or([q93 <= b_PartitionOccurrence_NumParts /\ - (and([b_PartitionOccurrence_WhichPart[q96] = q93 -> - or([b_PartitionOccurrence_WhichPart[q98] = q90 /\ q98 = q96 | q98 : int(1..2)]) - | q96 : int(1..2)]) - /\ - and([b_PartitionOccurrence_WhichPart[q100] = q90 -> - or([b_PartitionOccurrence_WhichPart[q102] = q93 /\ q102 = q100 | q102 : int(1..2)]) - | q100 : int(1..2)])) - | q93 : int(1..2)])) - | q90 : int(1..2)]))) - | q37 : int(1..2)]), - alldifferent_except([toInt(q28 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q28, q29] != - 3) - * - catchUndef(a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q28, q29], - 0) - | q28 : int(1..2), q29 : int(1..2)], - 0), - and([q30 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - sum([toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q30, q32] != 3) - | q32 : int(1..2)]) - >= 1 - | q30 : int(1..2)]), - 2 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - [a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[1, q12] | q12 : int(1..2)] a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q5, q27] = 1 - | q27 : int(1..2)]) - | q5 : int(1..2)]), - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker <= 2, - and([q6 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q6, 1] < - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q6, 2] - \/ a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q6, 1] = 3 - | q6 : int(1..2)]), - and([q6 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - (a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q6, 1] = 3 -> - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q6, 2] = 3) - | q6 : int(1..2)]), - and([q6 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - sum([toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q6, q9] != 3) - | q9 : int(1..2)]) - <= 2 - | q6 : int(1..2)]), - 2 = - sum([toInt(q14 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker) * - catchUndef(sum([toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q14, q16] != - 3) - | q16 : int(1..2)]), - 0) - | q14 : int(1..2)]), - and([q17 <= b_PartitionOccurrence_NumParts -> b_PartitionOccurrence_PartSizes[q17] <= 2 | q17 : int(1..2)]), - and([q17 > b_PartitionOccurrence_NumParts -> b_PartitionOccurrence_PartSizes[q17] = 0 | q17 : int(1..2)]), - b_PartitionOccurrence_NumParts <= 2, - b_PartitionOccurrence_NumParts = max([b_PartitionOccurrence_WhichPart[q20] | q20 : int(1..2)]), - and([b_PartitionOccurrence_PartSizes[q21] = - sum([toInt(b_PartitionOccurrence_WhichPart[q22] = q21) | q22 : int(1..2)]) - | q21 : int(1..2)]), - and([q23 <= b_PartitionOccurrence_NumParts -> - and([b_PartitionOccurrence_WhichPart[q24] = q23 -> b_PartitionOccurrence_FirstIndex[q23] <= q24 - | q24 : int(1..2)]) - | q23 : int(1..2)]), - and([q23 <= b_PartitionOccurrence_NumParts -> - or([b_PartitionOccurrence_WhichPart[q24] = q23 /\ b_PartitionOccurrence_FirstIndex[q23] = q24 - | q24 : int(1..2)]) - | q23 : int(1..2)]), - and([q23 > b_PartitionOccurrence_NumParts -> b_PartitionOccurrence_FirstIndex[q23] = 1 | q23 : int(1..2)]), - and([q25 <= b_PartitionOccurrence_NumParts /\ q26 <= b_PartitionOccurrence_NumParts -> - (q25 < q26 <-> b_PartitionOccurrence_FirstIndex[q25] < b_PartitionOccurrence_FirstIndex[q26]) - | q25 : int(1..2), q26 : int(1..2)]) - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_3_1-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_3_1-solution000001.solution deleted file mode 100644 index cde05d5274..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_3_1-solution000001.solution +++ /dev/null @@ -1,11 +0,0 @@ -language Essence 1.3 - -letting a be partition({1, 2}) -$ Visualisation for a -$ 1 2 - -letting b be partition({1}, {2}) -$ Visualisation for b -$ 1 -$ 2 - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_3_1.eprime b/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_3_1.eprime deleted file mode 100644 index 203aa27995..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_3_1.eprime +++ /dev/null @@ -1,854 +0,0 @@ -language ESSENCE' 1.0 - -find a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker: int(0..2) -find a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker: - matrix indexed by [int(1..2)] of int(0..2) -find a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values: - matrix indexed by [int(1..2), int(1..2)] of int(1..2) -find b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker: int(0..2) -find b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence: matrix indexed by [int(1..2), int(1..2)] of bool -branching on - [a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker, - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker, - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values, - b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker, - b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence] -such that - or([q37 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - (toInt(or([q129 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - (a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q129] = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q37] - /\ - and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q129, q130] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q37, q130] - | q130 : int(1..2)])) - | q129 : int(1..2)])) - < - toInt(or([q134 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ - (and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q134, q135] -> - or([q137 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q37] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q37, q137] - = q135 - | q137 : int(1..2)]) - | q135 : int(1..2)]) - /\ - and([q139 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q37] - -> - b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence - [q134, - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q37, q139]] - | q139 : int(1..2)])) - | q134 : int(1..2)])) - /\ - (and([q141 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - (or([q200 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q141] - /\ - (toInt(or([q221 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q141] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q141, q221] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q141, q200] - | q221 : int(1..2)])) - < - toInt(or([q223 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q37] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q37, q223] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q141, q200] - | q223 : int(1..2)])) - /\ - (and([q224 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q141] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q141, q224] - < - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q141, q200] - -> - toInt(or([q233 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q141] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q141, q233] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q141, q224] - | q233 : int(1..2)])) - = - toInt(or([q235 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q37] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q37, q235] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q141, q224] - | q235 : int(1..2)])) - | q224 : int(1..2)]) - /\ - and([and([q225 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q37], - !or([q231 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q141] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q141, q231] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q37, q225] - | q231 : int(1..2)]), - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q37, q225] - < - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q141, q200]; - int(1..3)]) - -> - toInt(or([q227 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q141] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q141, q227] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q37, q225] - | q227 : int(1..2)])) - = - toInt(or([q229 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q37] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q37, q229] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q37, q225] - | q229 : int(1..2)])) - | q225 : int(1..2)]))) - | q200 : int(1..2)]) - \/ - or([q201 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q37] /\ - !or([q219 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q141] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q141, q219] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q37, q201] - | q219 : int(1..2)]) - /\ - (toInt(or([q203 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q141] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q141, q203] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q37, q201] - | q203 : int(1..2)])) - < - toInt(or([q205 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q37] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q37, q205] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q37, q201] - | q205 : int(1..2)])) - /\ - (and([q206 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q141] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q141, q206] - < - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q37, q201] - -> - toInt(or([q215 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q141] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q141, q215] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q141, q206] - | q215 : int(1..2)])) - = - toInt(or([q217 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q37] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q37, q217] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q141, q206] - | q217 : int(1..2)])) - | q206 : int(1..2)]) - /\ - and([and([q207 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q37], - !or([q213 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q141] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q141, q213] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q37, q207] - | q213 : int(1..2)]), - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q37, q207] - < - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q37, q201]; - int(1..3)]) - -> - toInt(or([q209 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q141] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q141, q209] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q37, q207] - | q209 : int(1..2)])) - = - toInt(or([q211 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q37] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q37, q211] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q37, q207] - | q211 : int(1..2)])) - | q207 : int(1..2)]))) - | q201 : int(1..2)])) - -> - toInt(or([q187 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - (a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q187] = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q141] - /\ - and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q187, q188] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q141, q188] - | q188 : int(1..2)])) - | q187 : int(1..2)])) - = - toInt(or([q192 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ - (and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q192, q193] -> - or([q195 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q141] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q141, q195] - = q193 - | q195 : int(1..2)]) - | q193 : int(1..2)]) - /\ - and([q197 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q141] - -> - b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence - [q192, - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q141, q197]] - | q197 : int(1..2)])) - | q192 : int(1..2)])) - | q141 : int(1..2)]) - /\ - and([and([q143 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker, - !or([q159 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - (and([q161 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q159] - -> - b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence - [q143, - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q159, q161]] - | q161 : int(1..2)]) - /\ - and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q143, q162] -> - or([q164 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q159] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q159, q164] - = q162 - | q164 : int(1..2)]) - | q162 : int(1..2)])) - | q159 : int(1..2)]), - or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q143, q165] /\ - (toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q143, q165]) < - toInt(or([q178 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q37] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q37, q178] - = q165 - | q178 : int(1..2)])) - /\ - (and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q143, q166] -> - toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q143, q166]) = - toInt(or([q184 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q37] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q37, q184] - = q166 - | q184 : int(1..2)])) - | q166 : int(1..2), q166 < q165]) - /\ - and([and([q179 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q37], - !or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q143, q182] /\ - q182 = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q37, q179] - | q182 : int(1..2)]), - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q37, q179] - < q165; - int(1..3)]) - -> - toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence - [q143, - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q37, q179]]) - = - toInt(or([q181 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q37] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q37, q181] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q37, q179] - | q181 : int(1..2)])) - | q179 : int(1..2)]))) - | q165 : int(1..2)]) - \/ - or([q167 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q37] - /\ - !or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q143, q176] /\ - q176 = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q37, q167] - | q176 : int(1..2)]) - /\ - (toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence - [q143, - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q37, q167]]) - < - toInt(or([q169 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q37] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q37, q169] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q37, q167] - | q169 : int(1..2)])) - /\ - (and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q143, q166] /\ - q166 < - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q37, q167] - -> - toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q143, q166]) = - toInt(or([q175 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q37] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q37, q175] - = q166 - | q175 : int(1..2)])) - | q166 : int(1..2)]) - /\ - and([and([q170 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q37], - !or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q143, q173] /\ - q173 = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q37, q170] - | q173 : int(1..2)]), - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q37, q170] - < - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q37, q167]; - int(1..3)]) - -> - toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence - [q143, - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q37, q170]]) - = - toInt(or([q172 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q37] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q37, q172] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q37, q170] - | q172 : int(1..2)])) - | q170 : int(1..2)]))) - | q167 : int(1..2)]); - int(1..3)]) - -> - toInt(or([q146 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - (and([q148 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q146] - -> - b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence - [q143, - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q146, q148]] - | q148 : int(1..2)]) - /\ - and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q143, q149] -> - or([q151 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q146] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q146, q151] - = q149 - | q151 : int(1..2)]) - | q149 : int(1..2)])) - | q146 : int(1..2)])) - = - toInt(or([q154 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ - and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q154, q155] = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q143, q155] - | q155 : int(1..2)]) - | q154 : int(1..2)])) - | q143 : int(1..2)]))) - | q37 : int(1..2)]) - \/ - or([q39 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ - !or([q121 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - (and([q123 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q121] -> - b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence - [q39, - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q121, q123]] - | q123 : int(1..2)]) - /\ - and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q39, q124] -> - or([q126 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q121] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q121, q126] - = q124 - | q126 : int(1..2)]) - | q124 : int(1..2)])) - | q121 : int(1..2)]) - /\ - (toInt(or([q42 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - (and([q44 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q42] - -> - b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence - [q39, - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q42, q44]] - | q44 : int(1..2)]) - /\ - and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q39, q45] -> - or([q47 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q42] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q42, q47] - = q45 - | q47 : int(1..2)]) - | q45 : int(1..2)])) - | q42 : int(1..2)])) - < - toInt(or([q50 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ - and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q50, q51] = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q39, q51] - | q51 : int(1..2)]) - | q50 : int(1..2)])) - /\ - (and([q54 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - (or([q98 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q54] /\ - (toInt(or([q111 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q54] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q54, q111] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q54, q98] - | q111 : int(1..2)])) - < - toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence - [q39, - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q54, q98]]) - /\ - (and([q112 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q54] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q54, q112] - < - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q54, q98] - -> - toInt(or([q118 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q54] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q54, q118] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q54, q112] - | q118 : int(1..2)])) - = - toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence - [q39, - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q54, q112]]) - | q112 : int(1..2)]) - /\ - and([and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q39, q97], - !or([q116 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q54] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q54, q116] - = q97 - | q116 : int(1..2)]), - q97 < - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q54, q98]; - int(1..3)]) - -> - toInt(or([q114 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q54] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q54, q114] - = q97 - | q114 : int(1..2)])) - = toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q39, q97]) - | q97 : int(1..2)]))) - | q98 : int(1..2)]) - \/ - or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q39, q96] /\ - !or([q109 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q54] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q54, q109] - = q96 - | q109 : int(1..2)]) - /\ - (toInt(or([q100 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q54] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q54, q100] - = q96 - | q100 : int(1..2)])) - < toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q39, q96]) - /\ - (and([q101 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q54] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q54, q101] - < q96 - -> - toInt(or([q107 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q54] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q54, q107] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q54, q101] - | q107 : int(1..2)])) - = - toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence - [q39, - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q54, q101]]) - | q101 : int(1..2)]) - /\ - and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q39, q97] /\ - !or([q105 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q54] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q54, q105] - = q97 - | q105 : int(1..2)]) - -> - toInt(or([q103 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q54] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q54, q103] - = q97 - | q103 : int(1..2)])) - = toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q39, q97]) - | q97 : int(1..2), q97 < q96]))) - | q96 : int(1..2)])) - -> - toInt(or([q85 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - (a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q85] = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q54] - /\ - and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q85, q86] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q54, q86] - | q86 : int(1..2)])) - | q85 : int(1..2)])) - = - toInt(or([q90 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ - (and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q90, q91] -> - or([q93 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q54] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q54, q93] - = q91 - | q93 : int(1..2)]) - | q91 : int(1..2)]) - /\ - and([q95 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q54] - -> - b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence - [q90, - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q54, q95]] - | q95 : int(1..2)])) - | q90 : int(1..2)])) - | q54 : int(1..2)]) - /\ - and([and([q56 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker, - !or([q72 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - (and([q74 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q72] - -> - b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence - [q56, - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q72, q74]] - | q74 : int(1..2)]) - /\ - and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q56, q75] -> - or([q77 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q72] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q72, q77] - = q75 - | q77 : int(1..2)]) - | q75 : int(1..2)])) - | q72 : int(1..2)]), - or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q56, q78] /\ - (toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q56, q78]) < - toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q39, q78]) - /\ - (and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q56, q79] -> - toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q56, q79]) = - toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q39, q79]) - | q79 : int(1..2), q79 < q78]) - /\ - and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q39, q79] /\ - !or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q56, q82] /\ - q82 = q79 - | q82 : int(1..2)]) - -> - toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q56, q79]) = - toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q39, q79]) - | q79 : int(1..2), q79 < q78]))) - | q78 : int(1..2)]) - \/ - or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q39, q78] /\ - !or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q56, q81] /\ q81 = q78 - | q81 : int(1..2)]) - /\ - (toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q56, q78]) < - toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q39, q78]) - /\ - (and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q56, q79] -> - toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q56, q79]) = - toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q39, q79]) - | q79 : int(1..2), q79 < q78]) - /\ - and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q39, q79] /\ - !or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q56, q80] /\ - q80 = q79 - | q80 : int(1..2)]) - -> - toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q56, q79]) = - toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q39, q79]) - | q79 : int(1..2), q79 < q78]))) - | q78 : int(1..2)]); - int(1..3)]) - -> - toInt(or([q59 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - (and([q61 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q59] - -> - b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence - [q56, - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q59, q61]] - | q61 : int(1..2)]) - /\ - and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q56, q62] -> - or([q64 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q59] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q59, q64] - = q62 - | q64 : int(1..2)]) - | q62 : int(1..2)])) - | q59 : int(1..2)])) - = - toInt(or([q67 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ - and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q67, q68] = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q56, q68] - | q68 : int(1..2)]) - | q67 : int(1..2)])) - | q56 : int(1..2)]))) - | q39 : int(1..2)]), - alldifferent_except([toInt(q31 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - q32 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q31]) - * - catchUndef(a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q31, q32], - 0) - | q31 : int(1..2), q32 : int(1..2)], - 0), - and([q33 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q33] >= 1 - | q33 : int(1..2)]), - 2 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - flatten([[a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[1]; int(1)], - flatten([[a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[1, q11]; - int(1)] - | q11 : int(1..2)]); - int(1..2)]) - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q5] = 0 /\ - and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q5, q27] = 1 - | q27 : int(1..2)]) - | q5 : int(1..2)]), - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker <= 2, - and([q6 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - (2 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q6] -> - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q6, 1] < - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q6, 2]) - | q6 : int(1..2)]), - and([q6 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - and([q8 > a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q6] -> - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q6, q8] = 1 - | q8 : int(1..2)]) - | q6 : int(1..2)]), - and([q6 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q6] <= 2 - | q6 : int(1..2)]), - 2 = - sum([toInt(q13 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker) * - catchUndef(a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q13], 0) - | q13 : int(1..2)]), - and([1 = - sum([toInt(q28 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q28, q14]) - | q28 : int(1..2)]) - | q14 : int(1..2)]), - and([q29 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> - sum([toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q29, q30]) | q30 : int(1..2)]) >= 1 - | q29 : int(1..2)]), - 2 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> - [-toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[1, q22]) | q22 : int(1..2)] b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> - and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q18, q24] = false | q24 : int(1..2)]) - | q18 : int(1..2)]), - b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker <= 2, - and([q19 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> - sum([toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q19, q20]) | q20 : int(1..2)]) <= 2 - | q19 : int(1..2)]), - 2 = - sum([toInt(q25 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker) * - catchUndef(sum([toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q25, q26]) - | q26 : int(1..2)]), - 0) - | q25 : int(1..2)]) - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_3_2-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_3_2-solution000001.solution deleted file mode 100644 index cde05d5274..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_3_2-solution000001.solution +++ /dev/null @@ -1,11 +0,0 @@ -language Essence 1.3 - -letting a be partition({1, 2}) -$ Visualisation for a -$ 1 2 - -letting b be partition({1}, {2}) -$ Visualisation for b -$ 1 -$ 2 - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_3_2.eprime b/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_3_2.eprime deleted file mode 100644 index 7151e6d98f..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_3_2.eprime +++ /dev/null @@ -1,1230 +0,0 @@ -language ESSENCE' 1.0 - -find a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker: int(0..2) -find a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker: - matrix indexed by [int(1..2)] of int(0..2) -find a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values: - matrix indexed by [int(1..2), int(1..2)] of int(1..2) -find b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker: int(0..2) -find b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy: - matrix indexed by [int(1..2), int(1..2)] of int(1..3) -branching on - [a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker, - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker, - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values, - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker, - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy] -such that - or([q43 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - (toInt(or([q198 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - (a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q198] = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q43] - /\ - and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q198, q199] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q43, q199] - | q199 : int(1..2)])) - | q198 : int(1..2)])) - < - toInt(or([q203 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ - (and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q203, q205] != 3 - -> - or([q207 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q43] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q43, q207] - = b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q203, q205] - | q207 : int(1..2)]) - | q205 : int(1..2)]) - /\ - and([q209 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q43] - -> - or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q203, q211] != - 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q203, q211] = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q43, q209] - | q211 : int(1..2)]) - | q209 : int(1..2)])) - | q203 : int(1..2)])) - /\ - (and([q213 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - (or([q299 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q213] - /\ - (toInt(or([q320 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q213] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q213, q320] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q213, q299] - | q320 : int(1..2)])) - < - toInt(or([q322 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q43] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q43, q322] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q213, q299] - | q322 : int(1..2)])) - /\ - (and([q323 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q213] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q213, q323] - < - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q213, q299] - -> - toInt(or([q332 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q213] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q213, q332] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q213, q323] - | q332 : int(1..2)])) - = - toInt(or([q334 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q43] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q43, q334] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q213, q323] - | q334 : int(1..2)])) - | q323 : int(1..2)]) - /\ - and([and([q324 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q43], - !or([q330 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q213] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q213, q330] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q43, q324] - | q330 : int(1..2)]), - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q43, q324] - < - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q213, q299]; - int(1..3)]) - -> - toInt(or([q326 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q213] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q213, q326] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q43, q324] - | q326 : int(1..2)])) - = - toInt(or([q328 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q43] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q43, q328] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q43, q324] - | q328 : int(1..2)])) - | q324 : int(1..2)]))) - | q299 : int(1..2)]) - \/ - or([q300 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q43] /\ - !or([q318 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q213] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q213, q318] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q43, q300] - | q318 : int(1..2)]) - /\ - (toInt(or([q302 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q213] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q213, q302] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q43, q300] - | q302 : int(1..2)])) - < - toInt(or([q304 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q43] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q43, q304] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q43, q300] - | q304 : int(1..2)])) - /\ - (and([q305 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q213] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q213, q305] - < - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q43, q300] - -> - toInt(or([q314 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q213] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q213, q314] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q213, q305] - | q314 : int(1..2)])) - = - toInt(or([q316 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q43] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q43, q316] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q213, q305] - | q316 : int(1..2)])) - | q305 : int(1..2)]) - /\ - and([and([q306 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q43], - !or([q312 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q213] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q213, q312] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q43, q306] - | q312 : int(1..2)]), - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q43, q306] - < - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q43, q300]; - int(1..3)]) - -> - toInt(or([q308 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q213] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q213, q308] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q43, q306] - | q308 : int(1..2)])) - = - toInt(or([q310 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q43] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q43, q310] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q43, q306] - | q310 : int(1..2)])) - | q306 : int(1..2)]))) - | q300 : int(1..2)])) - -> - toInt(or([q283 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - (a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q283] = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q213] - /\ - and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q283, q284] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q213, q284] - | q284 : int(1..2)])) - | q283 : int(1..2)])) - = - toInt(or([q288 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ - (and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q288, q290] - != 3 - -> - or([q292 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q213] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q213, q292] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q288, q290] - | q292 : int(1..2)]) - | q290 : int(1..2)]) - /\ - and([q294 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q213] - -> - or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q288, q296] - != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q288, q296] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q213, q294] - | q296 : int(1..2)]) - | q294 : int(1..2)])) - | q288 : int(1..2)])) - | q213 : int(1..2)]) - /\ - and([and([q215 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker, - !or([q234 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - (and([q236 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q234] - -> - or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q215, q238] - != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q215, q238] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q234, q236] - | q238 : int(1..2)]) - | q236 : int(1..2)]) - /\ - and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q215, q240] - != 3 - -> - or([q242 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q234] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q234, q242] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q215, q240] - | q242 : int(1..2)]) - | q240 : int(1..2)])) - | q234 : int(1..2)]), - or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q215, q245] != 3 /\ - (toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q215, q266] - != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q215, q266] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q215, q245] - | q266 : int(1..2)])) - < - toInt(or([q268 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q43] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q43, q268] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q215, q245] - | q268 : int(1..2)])) - /\ - (and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q215, q269] - != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q215, q269] - < - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q215, q245] - -> - toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q215, q278] - != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q215, q278] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q215, q269] - | q278 : int(1..2)])) - = - toInt(or([q280 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q43] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q43, q280] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q215, q269] - | q280 : int(1..2)])) - | q269 : int(1..2)]) - /\ - and([and([q270 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q43], - !or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q215, q276] - != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q215, q276] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q43, q270] - | q276 : int(1..2)]), - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q43, q270] - < - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q215, q245]; - int(1..3)]) - -> - toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q215, q272] - != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q215, q272] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q43, q270] - | q272 : int(1..2)])) - = - toInt(or([q274 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q43] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q43, q274] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q43, q270] - | q274 : int(1..2)])) - | q270 : int(1..2)]))) - | q245 : int(1..2)]) - \/ - or([q246 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q43] - /\ - !or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q215, q264] != - 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q215, q264] = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q43, q246] - | q264 : int(1..2)]) - /\ - (toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q215, q248] - != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q215, q248] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q43, q246] - | q248 : int(1..2)])) - < - toInt(or([q250 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q43] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q43, q250] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q43, q246] - | q250 : int(1..2)])) - /\ - (and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q215, q251] - != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q215, q251] - < - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q43, q246] - -> - toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q215, q260] - != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q215, q260] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q215, q251] - | q260 : int(1..2)])) - = - toInt(or([q262 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q43] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q43, q262] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q215, q251] - | q262 : int(1..2)])) - | q251 : int(1..2)]) - /\ - and([and([q252 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q43], - !or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q215, q258] - != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q215, q258] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q43, q252] - | q258 : int(1..2)]), - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q43, q252] - < - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q43, q246]; - int(1..3)]) - -> - toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q215, q254] - != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q215, q254] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q43, q252] - | q254 : int(1..2)])) - = - toInt(or([q256 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q43] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q43, q256] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q43, q252] - | q256 : int(1..2)])) - | q252 : int(1..2)]))) - | q246 : int(1..2)]); - int(1..3)]) - -> - toInt(or([q218 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - (and([q220 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q218] - -> - or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q215, q222] - != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q215, q222] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q218, q220] - | q222 : int(1..2)]) - | q220 : int(1..2)]) - /\ - and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q215, q224] - != 3 - -> - or([q226 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q218] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q218, q226] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q215, q224] - | q226 : int(1..2)]) - | q224 : int(1..2)])) - | q218 : int(1..2)])) - = - toInt(or([q229 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ - and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q229, q230] = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q215, q230] - | q230 : int(1..2)]) - | q229 : int(1..2)])) - | q215 : int(1..2)]))) - | q43 : int(1..2)]) - \/ - or([q45 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ - !or([q187 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - (and([q189 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q187] -> - or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q45, q191] != 3 /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q45, q191] = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q187, q189] - | q191 : int(1..2)]) - | q189 : int(1..2)]) - /\ - and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q45, q193] != 3 -> - or([q195 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q187] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q187, q195] - = b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q45, q193] - | q195 : int(1..2)]) - | q193 : int(1..2)])) - | q187 : int(1..2)]) - /\ - (toInt(or([q48 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - (and([q50 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q48] - -> - or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q45, q52] != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q45, q52] = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q48, q50] - | q52 : int(1..2)]) - | q50 : int(1..2)]) - /\ - and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q45, q54] != 3 -> - or([q56 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q48] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q48, q56] - = b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q45, q54] - | q56 : int(1..2)]) - | q54 : int(1..2)])) - | q48 : int(1..2)])) - < - toInt(or([q59 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ - and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q59, q60] = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q45, q60] - | q60 : int(1..2)]) - | q59 : int(1..2)])) - /\ - (and([q63 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - (or([q149 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q63] /\ - (toInt(or([q170 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q63] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q63, q170] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q63, q149] - | q170 : int(1..2)])) - < - toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q45, q172] - != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q45, q172] = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q63, q149] - | q172 : int(1..2)])) - /\ - (and([q173 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q63] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q63, q173] - < - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q63, q149] - -> - toInt(or([q182 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q63] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q63, q182] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q63, q173] - | q182 : int(1..2)])) - = - toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q45, q184] - != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q45, q184] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q63, q173] - | q184 : int(1..2)])) - | q173 : int(1..2)]) - /\ - and([and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q45, q174] - != 3, - !or([q176 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q63] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q63, q176] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q45, q174] - | q176 : int(1..2)]), - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q45, q174] - < - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q63, q149]; - int(1..3)]) - -> - toInt(or([q178 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q63] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q63, q178] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q45, q174] - | q178 : int(1..2)])) - = - toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q45, q180] - != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q45, q180] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q45, q174] - | q180 : int(1..2)])) - | q174 : int(1..2)]))) - | q149 : int(1..2)]) - \/ - or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q45, q150] != 3 /\ - !or([q152 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q63] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q63, q152] - = b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q45, q150] - | q152 : int(1..2)]) - /\ - (toInt(or([q154 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q63] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q63, q154] - = b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q45, q150] - | q154 : int(1..2)])) - < - toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q45, q156] - != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q45, q156] = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q45, q150] - | q156 : int(1..2)])) - /\ - (and([q157 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q63] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q63, q157] - < b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q45, q150] - -> - toInt(or([q166 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q63] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q63, q166] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q63, q157] - | q166 : int(1..2)])) - = - toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q45, q168] - != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q45, q168] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q63, q157] - | q168 : int(1..2)])) - | q157 : int(1..2)]) - /\ - and([and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q45, q158] - != 3, - !or([q160 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q63] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q63, q160] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q45, q158] - | q160 : int(1..2)]), - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q45, q158] - < - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q45, q150]; - int(1..3)]) - -> - toInt(or([q162 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q63] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q63, q162] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q45, q158] - | q162 : int(1..2)])) - = - toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q45, q164] - != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q45, q164] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q45, q158] - | q164 : int(1..2)])) - | q158 : int(1..2)]))) - | q150 : int(1..2)])) - -> - toInt(or([q133 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - (a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q133] = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q63] - /\ - and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q133, q134] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q63, q134] - | q134 : int(1..2)])) - | q133 : int(1..2)])) - = - toInt(or([q138 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ - (and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q138, q140] - != 3 - -> - or([q142 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q63] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q63, q142] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q138, q140] - | q142 : int(1..2)]) - | q140 : int(1..2)]) - /\ - and([q144 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q63] - -> - or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q138, q146] - != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q138, q146] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q63, q144] - | q146 : int(1..2)]) - | q144 : int(1..2)])) - | q138 : int(1..2)])) - | q63 : int(1..2)]) - /\ - and([and([q65 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker, - !or([q84 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - (and([q86 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q84] - -> - or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q65, q88] - != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q65, q88] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q84, q86] - | q88 : int(1..2)]) - | q86 : int(1..2)]) - /\ - and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q65, q90] != - 3 - -> - or([q92 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q84] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q84, q92] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q65, q90] - | q92 : int(1..2)]) - | q90 : int(1..2)])) - | q84 : int(1..2)]), - or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q65, q95] != 3 /\ - (toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q65, q116] - != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q65, q116] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q65, q95] - | q116 : int(1..2)])) - < - toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q45, q118] - != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q45, q118] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q65, q95] - | q118 : int(1..2)])) - /\ - (and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q65, q119] - != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q65, q119] < - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q65, q95] - -> - toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q65, q128] - != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q65, q128] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q65, q119] - | q128 : int(1..2)])) - = - toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q45, q130] - != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q45, q130] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q65, q119] - | q130 : int(1..2)])) - | q119 : int(1..2)]) - /\ - and([and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q45, q120] - != 3, - !or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q65, q122] - != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q65, q122] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q45, q120] - | q122 : int(1..2)]), - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q45, q120] - < - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q65, q95]; - int(1..3)]) - -> - toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q65, q124] - != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q65, q124] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q45, q120] - | q124 : int(1..2)])) - = - toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q45, q126] - != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q45, q126] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q45, q120] - | q126 : int(1..2)])) - | q120 : int(1..2)]))) - | q95 : int(1..2)]) - \/ - or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q45, q96] != 3 /\ - !or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q65, q98] != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q65, q98] = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q45, q96] - | q98 : int(1..2)]) - /\ - (toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q65, q100] - != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q65, q100] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q45, q96] - | q100 : int(1..2)])) - < - toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q45, q102] - != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q45, q102] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q45, q96] - | q102 : int(1..2)])) - /\ - (and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q65, q103] - != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q65, q103] < - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q45, q96] - -> - toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q65, q112] - != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q65, q112] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q65, q103] - | q112 : int(1..2)])) - = - toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q45, q114] - != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q45, q114] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q65, q103] - | q114 : int(1..2)])) - | q103 : int(1..2)]) - /\ - and([and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q45, q104] - != 3, - !or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q65, q106] - != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q65, q106] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q45, q104] - | q106 : int(1..2)]), - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q45, q104] - < - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q45, q96]; - int(1..3)]) - -> - toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q65, q108] - != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q65, q108] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q45, q104] - | q108 : int(1..2)])) - = - toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q45, q110] - != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q45, q110] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q45, q104] - | q110 : int(1..2)])) - | q104 : int(1..2)]))) - | q96 : int(1..2)]); - int(1..3)]) - -> - toInt(or([q68 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - (and([q70 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q68] - -> - or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q65, q72] - != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q65, q72] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q68, q70] - | q72 : int(1..2)]) - | q70 : int(1..2)]) - /\ - and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q65, q74] != - 3 - -> - or([q76 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q68] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q68, q76] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q65, q74] - | q76 : int(1..2)]) - | q74 : int(1..2)])) - | q68 : int(1..2)])) - = - toInt(or([q79 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ - and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q79, q80] = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q65, q80] - | q80 : int(1..2)]) - | q79 : int(1..2)])) - | q65 : int(1..2)]))) - | q45 : int(1..2)]), - alldifferent_except([toInt(q32 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - q33 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q32]) - * - catchUndef(a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q32, q33], - 0) - | q32 : int(1..2), q33 : int(1..2)], - 0), - and([q34 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q34] >= 1 - | q34 : int(1..2)]), - 2 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - flatten([[a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[1]; int(1)], - flatten([[a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[1, q11]; - int(1)] - | q11 : int(1..2)]); - int(1..2)]) - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q5] = 0 /\ - and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q5, q30] = 1 - | q30 : int(1..2)]) - | q5 : int(1..2)]), - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker <= 2, - and([q6 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - (2 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q6] -> - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q6, 1] < - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q6, 2]) - | q6 : int(1..2)]), - and([q6 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - and([q8 > a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q6] -> - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q6, q8] = 1 - | q8 : int(1..2)]) - | q6 : int(1..2)]), - and([q6 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q6] <= 2 - | q6 : int(1..2)]), - 2 = - sum([toInt(q13 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker) * - catchUndef(a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q13], 0) - | q13 : int(1..2)]), - alldifferent_except([toInt(q35 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q35, q36] != - 3) - * - catchUndef(b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q35, q36], - 0) - | q35 : int(1..2), q36 : int(1..2)], - 0), - and([q37 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - sum([toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q37, q39] != 3) - | q39 : int(1..2)]) - >= 1 - | q37 : int(1..2)]), - 2 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - [b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[1, q25] | q25 : int(1..2)] b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q18, q31] = 1 - | q31 : int(1..2)]) - | q18 : int(1..2)]), - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker <= 2, - and([q19 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q19, 1] < - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q19, 2] - \/ b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q19, 1] = 3 - | q19 : int(1..2)]), - and([q19 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - (b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q19, 1] = 3 -> - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q19, 2] = 3) - | q19 : int(1..2)]), - and([q19 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - sum([toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q19, q22] != 3) - | q22 : int(1..2)]) - <= 2 - | q19 : int(1..2)]), - 2 = - sum([toInt(q27 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker) * - catchUndef(sum([toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q27, q29] != - 3) - | q29 : int(1..2)]), - 0) - | q27 : int(1..2)]) - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_3_3-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_3_3-solution000001.solution deleted file mode 100644 index cde05d5274..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_3_3-solution000001.solution +++ /dev/null @@ -1,11 +0,0 @@ -language Essence 1.3 - -letting a be partition({1, 2}) -$ Visualisation for a -$ 1 2 - -letting b be partition({1}, {2}) -$ Visualisation for b -$ 1 -$ 2 - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_3_3.eprime b/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_3_3.eprime deleted file mode 100644 index 2be8a0e387..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_3_3.eprime +++ /dev/null @@ -1,1131 +0,0 @@ -language ESSENCE' 1.0 - -find a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker: int(0..2) -find a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker: - matrix indexed by [int(1..2)] of int(0..2) -find a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values: - matrix indexed by [int(1..2), int(1..2)] of int(1..2) -find b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker: int(0..2) -find b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker: - matrix indexed by [int(1..2)] of int(0..2) -find b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values: - matrix indexed by [int(1..2), int(1..2)] of int(1..2) -branching on - [a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker, - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker, - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values, - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker, - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker, - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values] -such that - or([q38 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - (toInt(or([q163 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - (a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q163] = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q38] - /\ - and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q163, q164] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q38, q164] - | q164 : int(1..2)])) - | q163 : int(1..2)])) - < - toInt(or([q168 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - (b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q168] = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q38] - /\ - and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q168, q169] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q38, q169] - | q169 : int(1..2)])) - | q168 : int(1..2)])) - /\ - (and([q172 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - (or([q240 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q172] - /\ - (toInt(or([q261 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q172] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q172, q261] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q172, q240] - | q261 : int(1..2)])) - < - toInt(or([q263 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q38] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q38, q263] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q172, q240] - | q263 : int(1..2)])) - /\ - (and([q264 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q172] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q172, q264] - < - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q172, q240] - -> - toInt(or([q273 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q172] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q172, q273] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q172, q264] - | q273 : int(1..2)])) - = - toInt(or([q275 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q38] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q38, q275] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q172, q264] - | q275 : int(1..2)])) - | q264 : int(1..2)]) - /\ - and([and([q265 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q38], - !or([q271 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q172] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q172, q271] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q38, q265] - | q271 : int(1..2)]), - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q38, q265] - < - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q172, q240]; - int(1..3)]) - -> - toInt(or([q267 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q172] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q172, q267] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q38, q265] - | q267 : int(1..2)])) - = - toInt(or([q269 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q38] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q38, q269] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q38, q265] - | q269 : int(1..2)])) - | q265 : int(1..2)]))) - | q240 : int(1..2)]) - \/ - or([q241 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q38] /\ - !or([q259 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q172] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q172, q259] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q38, q241] - | q259 : int(1..2)]) - /\ - (toInt(or([q243 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q172] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q172, q243] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q38, q241] - | q243 : int(1..2)])) - < - toInt(or([q245 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q38] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q38, q245] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q38, q241] - | q245 : int(1..2)])) - /\ - (and([q246 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q172] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q172, q246] - < - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q38, q241] - -> - toInt(or([q255 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q172] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q172, q255] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q172, q246] - | q255 : int(1..2)])) - = - toInt(or([q257 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q38] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q38, q257] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q172, q246] - | q257 : int(1..2)])) - | q246 : int(1..2)]) - /\ - and([and([q247 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q38], - !or([q253 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q172] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q172, q253] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q38, q247] - | q253 : int(1..2)]), - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q38, q247] - < - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q38, q241]; - int(1..3)]) - -> - toInt(or([q249 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q172] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q172, q249] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q38, q247] - | q249 : int(1..2)])) - = - toInt(or([q251 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q38] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q38, q251] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q38, q247] - | q251 : int(1..2)])) - | q247 : int(1..2)]))) - | q241 : int(1..2)])) - -> - toInt(or([q230 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - (a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q230] = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q172] - /\ - and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q230, q231] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q172, q231] - | q231 : int(1..2)])) - | q230 : int(1..2)])) - = - toInt(or([q235 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - (b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q235] = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q172] - /\ - and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q235, q236] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q172, q236] - | q236 : int(1..2)])) - | q235 : int(1..2)])) - | q172 : int(1..2)]) - /\ - and([and([q174 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker, - !or([q187 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - (a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q187] = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q174] - /\ - and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q187, q188] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q174, q188] - | q188 : int(1..2)])) - | q187 : int(1..2)]), - or([q192 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q174] - /\ - (toInt(or([q213 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q174] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q174, q213] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q174, q192] - | q213 : int(1..2)])) - < - toInt(or([q215 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q38] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q38, q215] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q174, q192] - | q215 : int(1..2)])) - /\ - (and([q216 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q174] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q174, q216] - < - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q174, q192] - -> - toInt(or([q225 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q174] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q174, q225] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q174, q216] - | q225 : int(1..2)])) - = - toInt(or([q227 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q38] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q38, q227] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q174, q216] - | q227 : int(1..2)])) - | q216 : int(1..2)]) - /\ - and([and([q217 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q38], - !or([q223 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q174] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q174, q223] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q38, q217] - | q223 : int(1..2)]), - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q38, q217] - < - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q174, q192]; - int(1..3)]) - -> - toInt(or([q219 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q174] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q174, q219] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q38, q217] - | q219 : int(1..2)])) - = - toInt(or([q221 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q38] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q38, q221] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q38, q217] - | q221 : int(1..2)])) - | q217 : int(1..2)]))) - | q192 : int(1..2)]) - \/ - or([q193 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q38] - /\ - !or([q211 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q174] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q174, q211] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q38, q193] - | q211 : int(1..2)]) - /\ - (toInt(or([q195 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q174] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q174, q195] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q38, q193] - | q195 : int(1..2)])) - < - toInt(or([q197 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q38] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q38, q197] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q38, q193] - | q197 : int(1..2)])) - /\ - (and([q198 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q174] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q174, q198] - < - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q38, q193] - -> - toInt(or([q207 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q174] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q174, q207] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q174, q198] - | q207 : int(1..2)])) - = - toInt(or([q209 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q38] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q38, q209] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q174, q198] - | q209 : int(1..2)])) - | q198 : int(1..2)]) - /\ - and([and([q199 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q38], - !or([q205 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q174] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q174, q205] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q38, q199] - | q205 : int(1..2)]), - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q38, q199] - < - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q38, q193]; - int(1..3)]) - -> - toInt(or([q201 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q174] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q174, q201] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q38, q199] - | q201 : int(1..2)])) - = - toInt(or([q203 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q38] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q38, q203] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q38, q199] - | q203 : int(1..2)])) - | q199 : int(1..2)]))) - | q193 : int(1..2)]); - int(1..3)]) - -> - toInt(or([q177 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - (a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q177] = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q174] - /\ - and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q177, q178] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q174, q178] - | q178 : int(1..2)])) - | q177 : int(1..2)])) - = - toInt(or([q182 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - (b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q182] = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q174] - /\ - and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q182, q183] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q174, q183] - | q183 : int(1..2)])) - | q182 : int(1..2)])) - | q174 : int(1..2)]))) - | q38 : int(1..2)]) - \/ - or([q40 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - !or([q158 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - (a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q158] = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q40] - /\ - and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q158, q159] = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q40, q159] - | q159 : int(1..2)])) - | q158 : int(1..2)]) - /\ - (toInt(or([q43 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - (a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q43] = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q40] - /\ - and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q43, q44] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q40, q44] - | q44 : int(1..2)])) - | q43 : int(1..2)])) - < - toInt(or([q48 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - (b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q48] = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q40] - /\ - and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q48, q49] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q40, q49] - | q49 : int(1..2)])) - | q48 : int(1..2)])) - /\ - (and([q52 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - (or([q120 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q52] /\ - (toInt(or([q141 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q52] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q52, q141] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q52, q120] - | q141 : int(1..2)])) - < - toInt(or([q143 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q40] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q40, q143] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q52, q120] - | q143 : int(1..2)])) - /\ - (and([q144 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q52] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q52, q144] - < - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q52, q120] - -> - toInt(or([q153 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q52] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q52, q153] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q52, q144] - | q153 : int(1..2)])) - = - toInt(or([q155 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q40] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q40, q155] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q52, q144] - | q155 : int(1..2)])) - | q144 : int(1..2)]) - /\ - and([and([q145 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q40], - !or([q151 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q52] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q52, q151] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q40, q145] - | q151 : int(1..2)]), - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q40, q145] - < - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q52, q120]; - int(1..3)]) - -> - toInt(or([q147 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q52] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q52, q147] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q40, q145] - | q147 : int(1..2)])) - = - toInt(or([q149 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q40] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q40, q149] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q40, q145] - | q149 : int(1..2)])) - | q145 : int(1..2)]))) - | q120 : int(1..2)]) - \/ - or([q121 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q40] /\ - !or([q139 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q52] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q52, q139] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q40, q121] - | q139 : int(1..2)]) - /\ - (toInt(or([q123 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q52] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q52, q123] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q40, q121] - | q123 : int(1..2)])) - < - toInt(or([q125 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q40] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q40, q125] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q40, q121] - | q125 : int(1..2)])) - /\ - (and([q126 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q52] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q52, q126] - < - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q40, q121] - -> - toInt(or([q135 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q52] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q52, q135] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q52, q126] - | q135 : int(1..2)])) - = - toInt(or([q137 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q40] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q40, q137] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q52, q126] - | q137 : int(1..2)])) - | q126 : int(1..2)]) - /\ - and([and([q127 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q40], - !or([q133 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q52] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q52, q133] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q40, q127] - | q133 : int(1..2)]), - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q40, q127] - < - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q40, q121]; - int(1..3)]) - -> - toInt(or([q129 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q52] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q52, q129] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q40, q127] - | q129 : int(1..2)])) - = - toInt(or([q131 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q40] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q40, q131] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q40, q127] - | q131 : int(1..2)])) - | q127 : int(1..2)]))) - | q121 : int(1..2)])) - -> - toInt(or([q110 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - (a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q110] = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q52] - /\ - and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q110, q111] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q52, q111] - | q111 : int(1..2)])) - | q110 : int(1..2)])) - = - toInt(or([q115 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - (b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q115] = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q52] - /\ - and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q115, q116] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q52, q116] - | q116 : int(1..2)])) - | q115 : int(1..2)])) - | q52 : int(1..2)]) - /\ - and([and([q54 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker, - !or([q67 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - (a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q67] = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q54] - /\ - and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q67, q68] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q54, q68] - | q68 : int(1..2)])) - | q67 : int(1..2)]), - or([q72 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q54] - /\ - (toInt(or([q93 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q54] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q54, q93] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q54, q72] - | q93 : int(1..2)])) - < - toInt(or([q95 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q40] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q40, q95] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q54, q72] - | q95 : int(1..2)])) - /\ - (and([q96 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q54] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q54, q96] - < - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q54, q72] - -> - toInt(or([q105 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q54] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q54, q105] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q54, q96] - | q105 : int(1..2)])) - = - toInt(or([q107 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q40] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q40, q107] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q54, q96] - | q107 : int(1..2)])) - | q96 : int(1..2)]) - /\ - and([and([q97 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q40], - !or([q103 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q54] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q54, q103] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q40, q97] - | q103 : int(1..2)]), - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q40, q97] - < - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q54, q72]; - int(1..3)]) - -> - toInt(or([q99 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q54] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q54, q99] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q40, q97] - | q99 : int(1..2)])) - = - toInt(or([q101 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q40] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q40, q101] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q40, q97] - | q101 : int(1..2)])) - | q97 : int(1..2)]))) - | q72 : int(1..2)]) - \/ - or([q73 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q40] - /\ - !or([q91 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q54] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q54, q91] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q40, q73] - | q91 : int(1..2)]) - /\ - (toInt(or([q75 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q54] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q54, q75] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q40, q73] - | q75 : int(1..2)])) - < - toInt(or([q77 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q40] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q40, q77] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q40, q73] - | q77 : int(1..2)])) - /\ - (and([q78 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q54] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q54, q78] - < - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q40, q73] - -> - toInt(or([q87 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q54] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q54, q87] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q54, q78] - | q87 : int(1..2)])) - = - toInt(or([q89 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q40] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q40, q89] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q54, q78] - | q89 : int(1..2)])) - | q78 : int(1..2)]) - /\ - and([and([q79 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q40], - !or([q85 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q54] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q54, q85] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q40, q79] - | q85 : int(1..2)]), - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q40, q79] - < - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q40, q73]; - int(1..3)]) - -> - toInt(or([q81 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q54] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q54, q81] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q40, q79] - | q81 : int(1..2)])) - = - toInt(or([q83 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q40] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q40, q83] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q40, q79] - | q83 : int(1..2)])) - | q79 : int(1..2)]))) - | q73 : int(1..2)]); - int(1..3)]) - -> - toInt(or([q57 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - (a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q57] = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q54] - /\ - and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q57, q58] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q54, q58] - | q58 : int(1..2)])) - | q57 : int(1..2)])) - = - toInt(or([q62 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - (b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q62] = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q54] - /\ - and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q62, q63] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q54, q63] - | q63 : int(1..2)])) - | q62 : int(1..2)])) - | q54 : int(1..2)]))) - | q40 : int(1..2)]), - alldifferent_except([toInt(q29 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - q30 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q29]) - * - catchUndef(a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q29, q30], - 0) - | q29 : int(1..2), q30 : int(1..2)], - 0), - and([q31 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q31] >= 1 - | q31 : int(1..2)]), - 2 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - flatten([[a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[1]; int(1)], - flatten([[a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[1, q11]; - int(1)] - | q11 : int(1..2)]); - int(1..2)]) - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q5] = 0 /\ - and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q5, q27] = 1 - | q27 : int(1..2)]) - | q5 : int(1..2)]), - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker <= 2, - and([q6 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - (2 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q6] -> - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q6, 1] < - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q6, 2]) - | q6 : int(1..2)]), - and([q6 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - and([q8 > a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q6] -> - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q6, q8] = 1 - | q8 : int(1..2)]) - | q6 : int(1..2)]), - and([q6 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q6] <= 2 - | q6 : int(1..2)]), - 2 = - sum([toInt(q13 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker) * - catchUndef(a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q13], 0) - | q13 : int(1..2)]), - alldifferent_except([toInt(q32 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - q33 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q32]) - * - catchUndef(b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q32, q33], - 0) - | q32 : int(1..2), q33 : int(1..2)], - 0), - and([q34 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q34] >= 1 - | q34 : int(1..2)]), - 2 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - flatten([[b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[1]; int(1)], - flatten([[b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[1, q24]; - int(1)] - | q24 : int(1..2)]); - int(1..2)]) - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q18] = 0 /\ - and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q18, q28] = 1 - | q28 : int(1..2)]) - | q18 : int(1..2)]), - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker <= 2, - and([q19 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - (2 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q19] -> - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q19, 1] < - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q19, 2]) - | q19 : int(1..2)]), - and([q19 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - and([q21 > b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q19] -> - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q19, q21] = 1 - | q21 : int(1..2)]) - | q19 : int(1..2)]), - and([q19 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q19] <= 2 - | q19 : int(1..2)]), - 2 = - sum([toInt(q26 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker) * - catchUndef(b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q26], 0) - | q26 : int(1..2)]) - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_3_4-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_3_4-solution000001.solution deleted file mode 100644 index cde05d5274..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_3_4-solution000001.solution +++ /dev/null @@ -1,11 +0,0 @@ -language Essence 1.3 - -letting a be partition({1, 2}) -$ Visualisation for a -$ 1 2 - -letting b be partition({1}, {2}) -$ Visualisation for b -$ 1 -$ 2 - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_3_4.eprime b/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_3_4.eprime deleted file mode 100644 index ba95f02e68..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_3_4.eprime +++ /dev/null @@ -1,908 +0,0 @@ -language ESSENCE' 1.0 - -find a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker: int(0..2) -find a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker: - matrix indexed by [int(1..2)] of int(0..2) -find a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values: - matrix indexed by [int(1..2), int(1..2)] of int(1..2) -find b_PartitionOccurrence_NumParts: int(1..2) -find b_PartitionOccurrence_WhichPart: matrix indexed by [int(1..2)] of int(1..2) -find b_PartitionOccurrence_PartSizes: matrix indexed by [int(1..2)] of int(0..2) -find b_PartitionOccurrence_FirstIndex: matrix indexed by [int(1..2)] of int(1..2) -branching on - [a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker, - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker, - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values, - b_PartitionOccurrence_NumParts, b_PartitionOccurrence_WhichPart, b_PartitionOccurrence_PartSizes, - b_PartitionOccurrence_FirstIndex] -such that - or([q31 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - (toInt(or([q178 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - (a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q178] = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q31] - /\ - and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q178, q179] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q31, q179] - | q179 : int(1..2)])) - | q178 : int(1..2)])) - < - toInt(or([q182 <= b_PartitionOccurrence_NumParts /\ - (and([b_PartitionOccurrence_WhichPart[q185] = q182 -> - or([q187 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q31] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q31, q187] - = q185 - | q187 : int(1..2)]) - | q185 : int(1..2)]) - /\ - and([q189 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q31] - -> - or([b_PartitionOccurrence_WhichPart[q191] = q182 /\ - q191 = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q31, q189] - | q191 : int(1..2)]) - | q189 : int(1..2)])) - | q182 : int(1..2)])) - /\ - (and([q193 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - (or([q285 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q193] - /\ - (toInt(or([q306 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q193] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q193, q306] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q193, q285] - | q306 : int(1..2)])) - < - toInt(or([q308 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q31] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q31, q308] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q193, q285] - | q308 : int(1..2)])) - /\ - (and([q309 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q193] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q193, q309] - < - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q193, q285] - -> - toInt(or([q318 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q193] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q193, q318] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q193, q309] - | q318 : int(1..2)])) - = - toInt(or([q320 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q31] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q31, q320] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q193, q309] - | q320 : int(1..2)])) - | q309 : int(1..2)]) - /\ - and([and([q310 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q31], - !or([q316 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q193] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q193, q316] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q31, q310] - | q316 : int(1..2)]), - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q31, q310] - < - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q193, q285]; - int(1..3)]) - -> - toInt(or([q312 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q193] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q193, q312] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q31, q310] - | q312 : int(1..2)])) - = - toInt(or([q314 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q31] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q31, q314] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q31, q310] - | q314 : int(1..2)])) - | q310 : int(1..2)]))) - | q285 : int(1..2)]) - \/ - or([q286 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q31] /\ - !or([q304 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q193] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q193, q304] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q31, q286] - | q304 : int(1..2)]) - /\ - (toInt(or([q288 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q193] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q193, q288] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q31, q286] - | q288 : int(1..2)])) - < - toInt(or([q290 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q31] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q31, q290] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q31, q286] - | q290 : int(1..2)])) - /\ - (and([q291 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q193] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q193, q291] - < - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q31, q286] - -> - toInt(or([q300 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q193] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q193, q300] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q193, q291] - | q300 : int(1..2)])) - = - toInt(or([q302 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q31] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q31, q302] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q193, q291] - | q302 : int(1..2)])) - | q291 : int(1..2)]) - /\ - and([and([q292 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q31], - !or([q298 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q193] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q193, q298] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q31, q292] - | q298 : int(1..2)]), - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q31, q292] - < - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q31, q286]; - int(1..3)]) - -> - toInt(or([q294 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q193] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q193, q294] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q31, q292] - | q294 : int(1..2)])) - = - toInt(or([q296 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q31] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q31, q296] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q31, q292] - | q296 : int(1..2)])) - | q292 : int(1..2)]))) - | q286 : int(1..2)])) - -> - toInt(or([q269 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - (a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q269] = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q193] - /\ - and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q269, q270] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q193, q270] - | q270 : int(1..2)])) - | q269 : int(1..2)])) - = - toInt(or([q273 <= b_PartitionOccurrence_NumParts /\ - (and([b_PartitionOccurrence_WhichPart[q276] = q273 -> - or([q278 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q193] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q193, q278] - = q276 - | q278 : int(1..2)]) - | q276 : int(1..2)]) - /\ - and([q280 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q193] - -> - or([b_PartitionOccurrence_WhichPart[q282] = q273 /\ - q282 = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q193, q280] - | q282 : int(1..2)]) - | q280 : int(1..2)])) - | q273 : int(1..2)])) - | q193 : int(1..2)]) - /\ - and([and([q194 <= b_PartitionOccurrence_NumParts, - !or([q209 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - (and([q211 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q209] - -> - or([b_PartitionOccurrence_WhichPart[q213] = q194 /\ - q213 = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q209, q211] - | q213 : int(1..2)]) - | q211 : int(1..2)]) - /\ - and([b_PartitionOccurrence_WhichPart[q215] = q194 -> - or([q217 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q209] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q209, q217] - = q215 - | q217 : int(1..2)]) - | q215 : int(1..2)])) - | q209 : int(1..2)]), - or([b_PartitionOccurrence_WhichPart[q220] = q194 /\ - (sum([toInt(b_PartitionOccurrence_WhichPart[q241] = q194) * catchUndef(toInt(q241 = q220), 0) - | q241 : int(1..2)]) - < - toInt(or([q243 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q31] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q31, q243] - = q220 - | q243 : int(1..2)])) - /\ - (and([b_PartitionOccurrence_WhichPart[q244] = q194 -> - sum([toInt(b_PartitionOccurrence_WhichPart[q253] = q194) * - catchUndef(toInt(q253 = q244), 0) - | q253 : int(1..2)]) - = - toInt(or([q255 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q31] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q31, q255] - = q244 - | q255 : int(1..2)])) - | q244 : int(1..2), q244 < q220]) - /\ - and([and([q245 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q31], - !or([b_PartitionOccurrence_WhichPart[q251] = q194 /\ - q251 = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q31, q245] - | q251 : int(1..2)]), - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q31, q245] - < q220; - int(1..3)]) - -> - sum([toInt(b_PartitionOccurrence_WhichPart[q247] = q194) * - catchUndef(toInt(q247 = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q31, q245]), - 0) - | q247 : int(1..2)]) - = - toInt(or([q249 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q31] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q31, q249] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q31, q245] - | q249 : int(1..2)])) - | q245 : int(1..2)]))) - | q220 : int(1..2)]) - \/ - or([q221 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q31] - /\ - !or([b_PartitionOccurrence_WhichPart[q239] = q194 /\ - q239 = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q31, q221] - | q239 : int(1..2)]) - /\ - (sum([toInt(b_PartitionOccurrence_WhichPart[q223] = q194) * - catchUndef(toInt(q223 = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q31, q221]), - 0) - | q223 : int(1..2)]) - < - toInt(or([q225 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q31] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q31, q225] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q31, q221] - | q225 : int(1..2)])) - /\ - (and([b_PartitionOccurrence_WhichPart[q226] = q194 /\ - q226 < - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q31, q221] - -> - sum([toInt(b_PartitionOccurrence_WhichPart[q235] = q194) * - catchUndef(toInt(q235 = q226), 0) - | q235 : int(1..2)]) - = - toInt(or([q237 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q31] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q31, q237] - = q226 - | q237 : int(1..2)])) - | q226 : int(1..2)]) - /\ - and([and([q227 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q31], - !or([b_PartitionOccurrence_WhichPart[q233] = q194 /\ - q233 = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q31, q227] - | q233 : int(1..2)]), - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q31, q227] - < - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q31, q221]; - int(1..3)]) - -> - sum([toInt(b_PartitionOccurrence_WhichPart[q229] = q194) * - catchUndef(toInt(q229 = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q31, q227]), - 0) - | q229 : int(1..2)]) - = - toInt(or([q231 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q31] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q31, q231] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q31, q227] - | q231 : int(1..2)])) - | q227 : int(1..2)]))) - | q221 : int(1..2)]); - int(1..3)]) - -> - toInt(or([q258 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - (and([q260 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q258] - -> - or([b_PartitionOccurrence_WhichPart[q262] = q194 /\ - q262 = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q258, q260] - | q262 : int(1..2)]) - | q260 : int(1..2)]) - /\ - and([b_PartitionOccurrence_WhichPart[q264] = q194 -> - or([q266 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q258] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q258, q266] - = q264 - | q266 : int(1..2)]) - | q264 : int(1..2)])) - | q258 : int(1..2)])) - = - toInt(or([q197 <= b_PartitionOccurrence_NumParts /\ - (and([b_PartitionOccurrence_WhichPart[q200] = q197 -> - or([b_PartitionOccurrence_WhichPart[q202] = q194 /\ q202 = q200 | q202 : int(1..2)]) - | q200 : int(1..2)]) - /\ - and([b_PartitionOccurrence_WhichPart[q204] = q194 -> - or([b_PartitionOccurrence_WhichPart[q206] = q197 /\ q206 = q204 | q206 : int(1..2)]) - | q204 : int(1..2)])) - | q197 : int(1..2)])) - | q194 : int(1..2)]))) - | q31 : int(1..2)]) - \/ - or([q32 <= b_PartitionOccurrence_NumParts /\ - !or([q167 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - (and([q169 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q167] -> - or([b_PartitionOccurrence_WhichPart[q171] = q32 /\ - q171 = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q167, q169] - | q171 : int(1..2)]) - | q169 : int(1..2)]) - /\ - and([b_PartitionOccurrence_WhichPart[q173] = q32 -> - or([q175 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q167] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q167, q175] - = q173 - | q175 : int(1..2)]) - | q173 : int(1..2)])) - | q167 : int(1..2)]) - /\ - (toInt(or([q156 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - (and([q158 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q156] - -> - or([b_PartitionOccurrence_WhichPart[q160] = q32 /\ - q160 = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q156, q158] - | q160 : int(1..2)]) - | q158 : int(1..2)]) - /\ - and([b_PartitionOccurrence_WhichPart[q162] = q32 -> - or([q164 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q156] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q156, q164] - = q162 - | q164 : int(1..2)]) - | q162 : int(1..2)])) - | q156 : int(1..2)])) - < - toInt(or([q35 <= b_PartitionOccurrence_NumParts /\ - (and([b_PartitionOccurrence_WhichPart[q38] = q35 -> - or([b_PartitionOccurrence_WhichPart[q40] = q32 /\ q40 = q38 | q40 : int(1..2)]) - | q38 : int(1..2)]) - /\ - and([b_PartitionOccurrence_WhichPart[q42] = q32 -> - or([b_PartitionOccurrence_WhichPart[q44] = q35 /\ q44 = q42 | q44 : int(1..2)]) - | q42 : int(1..2)])) - | q35 : int(1..2)])) - /\ - (and([q66 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - (or([q67 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q66] /\ - (toInt(or([q75 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q66] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q66, q75] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q66, q67] - | q75 : int(1..2)])) - < - sum([toInt(b_PartitionOccurrence_WhichPart[q58] = q32) * - catchUndef(toInt(q58 = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q66, q67]), - 0) - | q58 : int(1..2)]) - /\ - (and([q68 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q66] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q66, q68] - < - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q66, q67] - -> - toInt(or([q70 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q66] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q66, q70] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q66, q68] - | q70 : int(1..2)])) - = - sum([toInt(b_PartitionOccurrence_WhichPart[q64] = q32) * - catchUndef(toInt(q64 = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q66, q68]), - 0) - | q64 : int(1..2)]) - | q68 : int(1..2)]) - /\ - and([!or([q71 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q66] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q66, q71] - = q59 - | q71 : int(1..2)]) - /\ - q59 < - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q66, q67] - -> - (b_PartitionOccurrence_WhichPart[q59] = q32 -> - toInt(or([q73 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q66] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q66, q73] - = q59 - | q73 : int(1..2)])) - = - sum([toInt(b_PartitionOccurrence_WhichPart[q61] = q32) * catchUndef(toInt(q61 = q59), 0) - | q61 : int(1..2)])) - | q59 : int(1..2)]))) - | q67 : int(1..2)]) - \/ - or([!or([q84 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q66] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q66, q84] - = q47 - | q84 : int(1..2)]) - /\ - (b_PartitionOccurrence_WhichPart[q47] = q32 /\ - (toInt(or([q83 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q66] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q66, q83] - = q47 - | q83 : int(1..2)])) - < - sum([toInt(b_PartitionOccurrence_WhichPart[q49] = q32) * catchUndef(toInt(q49 = q47), 0) - | q49 : int(1..2)]) - /\ - (and([q76 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q66] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q66, q76] - < q47 - -> - toInt(or([q78 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q66] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q66, q78] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q66, q76] - | q78 : int(1..2)])) - = - sum([toInt(b_PartitionOccurrence_WhichPart[q55] = q32) * - catchUndef(toInt(q55 = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q66, q76]), - 0) - | q55 : int(1..2)]) - | q76 : int(1..2)]) - /\ - and([!or([q79 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q66] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q66, q79] - = q50 - | q79 : int(1..2)]) - -> - (b_PartitionOccurrence_WhichPart[q50] = q32 -> - toInt(or([q81 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q66] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q66, q81] - = q50 - | q81 : int(1..2)])) - = - sum([toInt(b_PartitionOccurrence_WhichPart[q52] = q32) * catchUndef(toInt(q52 = q50), 0) - | q52 : int(1..2)])) - | q50 : int(1..2), q50 < q47])))) - | q47 : int(1..2)])) - -> - toInt(or([q140 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - (a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q140] = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q66] - /\ - and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q140, q141] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q66, q141] - | q141 : int(1..2)])) - | q140 : int(1..2)])) - = - toInt(or([q144 <= b_PartitionOccurrence_NumParts /\ - (and([b_PartitionOccurrence_WhichPart[q147] = q144 -> - or([q149 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q66] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q66, q149] - = q147 - | q149 : int(1..2)]) - | q147 : int(1..2)]) - /\ - and([q151 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q66] - -> - or([b_PartitionOccurrence_WhichPart[q153] = q144 /\ - q153 = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q66, q151] - | q153 : int(1..2)]) - | q151 : int(1..2)])) - | q144 : int(1..2)])) - | q66 : int(1..2)]) - /\ - and([and([q85 <= b_PartitionOccurrence_NumParts, - !or([q100 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - (and([q102 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q100] - -> - or([b_PartitionOccurrence_WhichPart[q104] = q85 /\ - q104 = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q100, q102] - | q104 : int(1..2)]) - | q102 : int(1..2)]) - /\ - and([b_PartitionOccurrence_WhichPart[q106] = q85 -> - or([q108 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q100] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q100, q108] - = q106 - | q108 : int(1..2)]) - | q106 : int(1..2)])) - | q100 : int(1..2)]), - or([b_PartitionOccurrence_WhichPart[q117] = q85 /\ - (toInt(or([b_PartitionOccurrence_WhichPart[q110] = q85 /\ q110 = q117 | q110 : int(1..2)])) < - sum([toInt(b_PartitionOccurrence_WhichPart[q58] = q32) * catchUndef(toInt(q58 = q117), 0) - | q58 : int(1..2)]) - /\ - (and([b_PartitionOccurrence_WhichPart[q113] = q85 -> - toInt(or([b_PartitionOccurrence_WhichPart[q112] = q85 /\ q112 = q113 - | q112 : int(1..2)])) - = - sum([toInt(b_PartitionOccurrence_WhichPart[q64] = q32) * catchUndef(toInt(q64 = q113), 0) - | q64 : int(1..2)]) - | q113 : int(1..2), q113 < q117]) - /\ - and([!or([b_PartitionOccurrence_WhichPart[q116] = q85 /\ q116 = q59 | q116 : int(1..2)]) -> - (b_PartitionOccurrence_WhichPart[q59] = q32 -> - toInt(or([b_PartitionOccurrence_WhichPart[q115] = q85 /\ q115 = q59 - | q115 : int(1..2)])) - = - sum([toInt(b_PartitionOccurrence_WhichPart[q61] = q32) * catchUndef(toInt(q61 = q59), 0) - | q61 : int(1..2)])) - | q59 : int(1..2), q59 < q117]))) - | q117 : int(1..2)]) - \/ - or([!or([b_PartitionOccurrence_WhichPart[q126] = q85 /\ q126 = q47 | q126 : int(1..2)]) /\ - (b_PartitionOccurrence_WhichPart[q47] = q32 /\ - (toInt(or([b_PartitionOccurrence_WhichPart[q119] = q85 /\ q119 = q47 | q119 : int(1..2)])) < - sum([toInt(b_PartitionOccurrence_WhichPart[q49] = q32) * catchUndef(toInt(q49 = q47), 0) - | q49 : int(1..2)]) - /\ - (and([b_PartitionOccurrence_WhichPart[q122] = q85 -> - toInt(or([b_PartitionOccurrence_WhichPart[q121] = q85 /\ q121 = q122 - | q121 : int(1..2)])) - = - sum([toInt(b_PartitionOccurrence_WhichPart[q55] = q32) * - catchUndef(toInt(q55 = q122), 0) - | q55 : int(1..2)]) - | q122 : int(1..2), q122 < q47]) - /\ - and([!or([b_PartitionOccurrence_WhichPart[q125] = q85 /\ q125 = q50 | q125 : int(1..2)]) -> - (b_PartitionOccurrence_WhichPart[q50] = q32 -> - toInt(or([b_PartitionOccurrence_WhichPart[q124] = q85 /\ q124 = q50 - | q124 : int(1..2)])) - = - sum([toInt(b_PartitionOccurrence_WhichPart[q52] = q32) * - catchUndef(toInt(q52 = q50), 0) - | q52 : int(1..2)])) - | q50 : int(1..2), q50 < q47])))) - | q47 : int(1..2)]); - int(1..3)]) - -> - toInt(or([q129 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - (and([q131 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q129] - -> - or([b_PartitionOccurrence_WhichPart[q133] = q85 /\ - q133 = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q129, q131] - | q133 : int(1..2)]) - | q131 : int(1..2)]) - /\ - and([b_PartitionOccurrence_WhichPart[q135] = q85 -> - or([q137 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q129] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q129, q137] - = q135 - | q137 : int(1..2)]) - | q135 : int(1..2)])) - | q129 : int(1..2)])) - = - toInt(or([q88 <= b_PartitionOccurrence_NumParts /\ - (and([b_PartitionOccurrence_WhichPart[q91] = q88 -> - or([b_PartitionOccurrence_WhichPart[q93] = q85 /\ q93 = q91 | q93 : int(1..2)]) - | q91 : int(1..2)]) - /\ - and([b_PartitionOccurrence_WhichPart[q95] = q85 -> - or([b_PartitionOccurrence_WhichPart[q97] = q88 /\ q97 = q95 | q97 : int(1..2)]) - | q95 : int(1..2)])) - | q88 : int(1..2)])) - | q85 : int(1..2)]))) - | q32 : int(1..2)]), - alldifferent_except([toInt(q25 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - q26 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q25]) - * - catchUndef(a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q25, q26], - 0) - | q25 : int(1..2), q26 : int(1..2)], - 0), - and([q27 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q27] >= 1 - | q27 : int(1..2)]), - 2 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - flatten([[a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[1]; int(1)], - flatten([[a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[1, q11]; - int(1)] - | q11 : int(1..2)]); - int(1..2)]) - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q5] = 0 /\ - and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q5, q24] = 1 - | q24 : int(1..2)]) - | q5 : int(1..2)]), - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker <= 2, - and([q6 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - (2 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q6] -> - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q6, 1] < - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q6, 2]) - | q6 : int(1..2)]), - and([q6 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - and([q8 > a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q6] -> - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q6, q8] = 1 - | q8 : int(1..2)]) - | q6 : int(1..2)]), - and([q6 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q6] <= 2 - | q6 : int(1..2)]), - 2 = - sum([toInt(q13 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker) * - catchUndef(a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q13], 0) - | q13 : int(1..2)]), - and([q14 <= b_PartitionOccurrence_NumParts -> b_PartitionOccurrence_PartSizes[q14] <= 2 | q14 : int(1..2)]), - and([q14 > b_PartitionOccurrence_NumParts -> b_PartitionOccurrence_PartSizes[q14] = 0 | q14 : int(1..2)]), - b_PartitionOccurrence_NumParts <= 2, - b_PartitionOccurrence_NumParts = max([b_PartitionOccurrence_WhichPart[q17] | q17 : int(1..2)]), - and([b_PartitionOccurrence_PartSizes[q18] = - sum([toInt(b_PartitionOccurrence_WhichPart[q19] = q18) | q19 : int(1..2)]) - | q18 : int(1..2)]), - and([q20 <= b_PartitionOccurrence_NumParts -> - and([b_PartitionOccurrence_WhichPart[q21] = q20 -> b_PartitionOccurrence_FirstIndex[q20] <= q21 - | q21 : int(1..2)]) - | q20 : int(1..2)]), - and([q20 <= b_PartitionOccurrence_NumParts -> - or([b_PartitionOccurrence_WhichPart[q21] = q20 /\ b_PartitionOccurrence_FirstIndex[q20] = q21 - | q21 : int(1..2)]) - | q20 : int(1..2)]), - and([q20 > b_PartitionOccurrence_NumParts -> b_PartitionOccurrence_FirstIndex[q20] = 1 | q20 : int(1..2)]), - and([q22 <= b_PartitionOccurrence_NumParts /\ q23 <= b_PartitionOccurrence_NumParts -> - (q22 < q23 <-> b_PartitionOccurrence_FirstIndex[q22] < b_PartitionOccurrence_FirstIndex[q23]) - | q22 : int(1..2), q23 : int(1..2)]) - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_4_1-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_4_1-solution000001.solution deleted file mode 100644 index cde05d5274..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_4_1-solution000001.solution +++ /dev/null @@ -1,11 +0,0 @@ -language Essence 1.3 - -letting a be partition({1, 2}) -$ Visualisation for a -$ 1 2 - -letting b be partition({1}, {2}) -$ Visualisation for b -$ 1 -$ 2 - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_4_1.eprime b/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_4_1.eprime deleted file mode 100644 index 5216e84b83..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_4_1.eprime +++ /dev/null @@ -1,373 +0,0 @@ -language ESSENCE' 1.0 - -find a_PartitionOccurrence_NumParts: int(1..2) -find a_PartitionOccurrence_WhichPart: matrix indexed by [int(1..2)] of int(1..2) -find a_PartitionOccurrence_PartSizes: matrix indexed by [int(1..2)] of int(0..2) -find a_PartitionOccurrence_FirstIndex: matrix indexed by [int(1..2)] of int(1..2) -find b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker: int(0..2) -find b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence: matrix indexed by [int(1..2), int(1..2)] of bool -branching on - [a_PartitionOccurrence_NumParts, a_PartitionOccurrence_WhichPart, a_PartitionOccurrence_PartSizes, - a_PartitionOccurrence_FirstIndex, b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker, - b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence] -such that - or([q29 <= a_PartitionOccurrence_NumParts /\ - (toInt(or([q122 <= a_PartitionOccurrence_NumParts /\ - (and([a_PartitionOccurrence_WhichPart[q125] = q122 -> - or([a_PartitionOccurrence_WhichPart[q127] = q29 /\ q127 = q125 | q127 : int(1..2)]) - | q125 : int(1..2)]) - /\ - and([a_PartitionOccurrence_WhichPart[q129] = q29 -> - or([a_PartitionOccurrence_WhichPart[q131] = q122 /\ q131 = q129 | q131 : int(1..2)]) - | q129 : int(1..2)])) - | q122 : int(1..2)])) - < - toInt(or([q33 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ - (and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q33, q34] -> - or([a_PartitionOccurrence_WhichPart[q36] = q29 /\ q36 = q34 | q36 : int(1..2)]) - | q34 : int(1..2)]) - /\ - and([a_PartitionOccurrence_WhichPart[q38] = q29 -> - b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q33, q38] - | q38 : int(1..2)])) - | q33 : int(1..2)])) - /\ - (and([q59 <= a_PartitionOccurrence_NumParts /\ - (or([a_PartitionOccurrence_WhichPart[q77] = q59 /\ - (toInt(or([a_PartitionOccurrence_WhichPart[q70] = q59 /\ q70 = q77 | q70 : int(1..2)])) < - sum([toInt(a_PartitionOccurrence_WhichPart[q52] = q29) * catchUndef(toInt(q52 = q77), 0) - | q52 : int(1..2)]) - /\ - (and([a_PartitionOccurrence_WhichPart[q73] = q59 -> - toInt(or([a_PartitionOccurrence_WhichPart[q72] = q59 /\ q72 = q73 | q72 : int(1..2)])) = - sum([toInt(a_PartitionOccurrence_WhichPart[q58] = q29) * catchUndef(toInt(q58 = q73), 0) - | q58 : int(1..2)]) - | q73 : int(1..2), q73 < q77]) - /\ - and([!or([a_PartitionOccurrence_WhichPart[q76] = q59 /\ q76 = q53 | q76 : int(1..2)]) -> - (a_PartitionOccurrence_WhichPart[q53] = q29 -> - toInt(or([a_PartitionOccurrence_WhichPart[q75] = q59 /\ q75 = q53 | q75 : int(1..2)])) = - sum([toInt(a_PartitionOccurrence_WhichPart[q55] = q29) * catchUndef(toInt(q55 = q53), 0) - | q55 : int(1..2)])) - | q53 : int(1..2), q53 < q77]))) - | q77 : int(1..2)]) - \/ - or([!or([a_PartitionOccurrence_WhichPart[q86] = q59 /\ q86 = q41 | q86 : int(1..2)]) /\ - (a_PartitionOccurrence_WhichPart[q41] = q29 /\ - (toInt(or([a_PartitionOccurrence_WhichPart[q79] = q59 /\ q79 = q41 | q79 : int(1..2)])) < - sum([toInt(a_PartitionOccurrence_WhichPart[q43] = q29) * catchUndef(toInt(q43 = q41), 0) - | q43 : int(1..2)]) - /\ - (and([a_PartitionOccurrence_WhichPart[q82] = q59 -> - toInt(or([a_PartitionOccurrence_WhichPart[q81] = q59 /\ q81 = q82 | q81 : int(1..2)])) = - sum([toInt(a_PartitionOccurrence_WhichPart[q49] = q29) * catchUndef(toInt(q49 = q82), 0) - | q49 : int(1..2)]) - | q82 : int(1..2), q82 < q41]) - /\ - and([!or([a_PartitionOccurrence_WhichPart[q85] = q59 /\ q85 = q44 | q85 : int(1..2)]) -> - (a_PartitionOccurrence_WhichPart[q44] = q29 -> - toInt(or([a_PartitionOccurrence_WhichPart[q84] = q59 /\ q84 = q44 | q84 : int(1..2)])) = - sum([toInt(a_PartitionOccurrence_WhichPart[q46] = q29) * catchUndef(toInt(q46 = q44), 0) - | q46 : int(1..2)])) - | q44 : int(1..2), q44 < q41])))) - | q41 : int(1..2)])) - -> - toInt(or([q111 <= a_PartitionOccurrence_NumParts /\ - (and([a_PartitionOccurrence_WhichPart[q114] = q111 -> - or([a_PartitionOccurrence_WhichPart[q116] = q59 /\ q116 = q114 | q116 : int(1..2)]) - | q114 : int(1..2)]) - /\ - and([a_PartitionOccurrence_WhichPart[q118] = q59 -> - or([a_PartitionOccurrence_WhichPart[q120] = q111 /\ q120 = q118 | q120 : int(1..2)]) - | q118 : int(1..2)])) - | q111 : int(1..2)])) - = - toInt(or([q63 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ - (and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q63, q64] -> - or([a_PartitionOccurrence_WhichPart[q66] = q59 /\ q66 = q64 | q66 : int(1..2)]) - | q64 : int(1..2)]) - /\ - and([a_PartitionOccurrence_WhichPart[q68] = q59 -> - b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q63, q68] - | q68 : int(1..2)])) - | q63 : int(1..2)])) - | q59 : int(1..2)]) - /\ - and([and([q88 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker, - !or([q103 <= a_PartitionOccurrence_NumParts /\ - (and([a_PartitionOccurrence_WhichPart[q106] = q103 -> - b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q88, q106] - | q106 : int(1..2)]) - /\ - and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q88, q107] -> - or([a_PartitionOccurrence_WhichPart[q109] = q103 /\ q109 = q107 | q109 : int(1..2)]) - | q107 : int(1..2)])) - | q103 : int(1..2)]), - or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q88, q39] /\ - (toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q88, q39]) < - sum([toInt(a_PartitionOccurrence_WhichPart[q52] = q29) * catchUndef(toInt(q52 = q39), 0) - | q52 : int(1..2)]) - /\ - (and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q88, q40] -> - toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q88, q40]) = - sum([toInt(a_PartitionOccurrence_WhichPart[q58] = q29) * catchUndef(toInt(q58 = q40), 0) - | q58 : int(1..2)]) - | q40 : int(1..2), q40 < q39]) - /\ - and([!or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q88, q56] /\ - q56 = q53 - | q56 : int(1..2)]) - -> - (a_PartitionOccurrence_WhichPart[q53] = q29 -> - toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q88, q53]) = - sum([toInt(a_PartitionOccurrence_WhichPart[q55] = q29) * catchUndef(toInt(q55 = q53), 0) - | q55 : int(1..2)])) - | q53 : int(1..2), q53 < q39]))) - | q39 : int(1..2)]) - \/ - or([!or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q88, q50] /\ q50 = q41 - | q50 : int(1..2)]) - /\ - (a_PartitionOccurrence_WhichPart[q41] = q29 /\ - (toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q88, q41]) < - sum([toInt(a_PartitionOccurrence_WhichPart[q43] = q29) * catchUndef(toInt(q43 = q41), 0) - | q43 : int(1..2)]) - /\ - (and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q88, q40] -> - toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q88, q40]) = - sum([toInt(a_PartitionOccurrence_WhichPart[q49] = q29) * catchUndef(toInt(q49 = q40), 0) - | q49 : int(1..2)]) - | q40 : int(1..2), q40 < q41]) - /\ - and([!or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q88, q47] /\ - q47 = q44 - | q47 : int(1..2)]) - -> - (a_PartitionOccurrence_WhichPart[q44] = q29 -> - toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q88, q44]) = - sum([toInt(a_PartitionOccurrence_WhichPart[q46] = q29) * - catchUndef(toInt(q46 = q44), 0) - | q46 : int(1..2)])) - | q44 : int(1..2), q44 < q41])))) - | q41 : int(1..2)]); - int(1..3)]) - -> - toInt(or([q90 <= a_PartitionOccurrence_NumParts /\ - (and([a_PartitionOccurrence_WhichPart[q93] = q90 -> - b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q88, q93] - | q93 : int(1..2)]) - /\ - and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q88, q94] -> - or([a_PartitionOccurrence_WhichPart[q96] = q90 /\ q96 = q94 | q96 : int(1..2)]) - | q94 : int(1..2)])) - | q90 : int(1..2)])) - = - toInt(or([q99 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ - and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q99, q100] = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q88, q100] - | q100 : int(1..2)]) - | q99 : int(1..2)])) - | q88 : int(1..2)]))) - | q29 : int(1..2)]) - \/ - or([q133 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ - !or([q220 <= a_PartitionOccurrence_NumParts /\ - (and([a_PartitionOccurrence_WhichPart[q223] = q220 -> - b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q133, q223] - | q223 : int(1..2)]) - /\ - and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q133, q224] -> - or([a_PartitionOccurrence_WhichPart[q226] = q220 /\ q226 = q224 | q226 : int(1..2)]) - | q224 : int(1..2)])) - | q220 : int(1..2)]) - /\ - (toInt(or([q135 <= a_PartitionOccurrence_NumParts /\ - (and([a_PartitionOccurrence_WhichPart[q138] = q135 -> - b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q133, q138] - | q138 : int(1..2)]) - /\ - and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q133, q139] -> - or([a_PartitionOccurrence_WhichPart[q141] = q135 /\ q141 = q139 | q141 : int(1..2)]) - | q139 : int(1..2)])) - | q135 : int(1..2)])) - < - toInt(or([q144 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ - and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q144, q145] = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q133, q145] - | q145 : int(1..2)]) - | q144 : int(1..2)])) - /\ - (and([q147 <= a_PartitionOccurrence_NumParts /\ - (or([a_PartitionOccurrence_WhichPart[q159] = q147 /\ - (sum([toInt(a_PartitionOccurrence_WhichPart[q172] = q147) * catchUndef(toInt(q172 = q159), 0) - | q172 : int(1..2)]) - < toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q133, q159]) - /\ - (and([a_PartitionOccurrence_WhichPart[q173] = q147 -> - sum([toInt(a_PartitionOccurrence_WhichPart[q179] = q147) * catchUndef(toInt(q179 = q173), 0) - | q179 : int(1..2)]) - = toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q133, q173]) - | q173 : int(1..2), q173 < q159]) - /\ - and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q133, q158] /\ - !or([a_PartitionOccurrence_WhichPart[q177] = q147 /\ q177 = q158 | q177 : int(1..2)]) - -> - sum([toInt(a_PartitionOccurrence_WhichPart[q175] = q147) * catchUndef(toInt(q175 = q158), 0) - | q175 : int(1..2)]) - = toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q133, q158]) - | q158 : int(1..2), q158 < q159]))) - | q159 : int(1..2)]) - \/ - or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q133, q157] /\ - !or([a_PartitionOccurrence_WhichPart[q170] = q147 /\ q170 = q157 | q170 : int(1..2)]) - /\ - (sum([toInt(a_PartitionOccurrence_WhichPart[q161] = q147) * catchUndef(toInt(q161 = q157), 0) - | q161 : int(1..2)]) - < toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q133, q157]) - /\ - (and([a_PartitionOccurrence_WhichPart[q162] = q147 -> - sum([toInt(a_PartitionOccurrence_WhichPart[q168] = q147) * catchUndef(toInt(q168 = q162), 0) - | q168 : int(1..2)]) - = toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q133, q162]) - | q162 : int(1..2), q162 < q157]) - /\ - and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q133, q158] /\ - !or([a_PartitionOccurrence_WhichPart[q166] = q147 /\ q166 = q158 | q166 : int(1..2)]) - -> - sum([toInt(a_PartitionOccurrence_WhichPart[q164] = q147) * catchUndef(toInt(q164 = q158), 0) - | q164 : int(1..2)]) - = toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q133, q158]) - | q158 : int(1..2), q158 < q157]))) - | q157 : int(1..2)])) - -> - toInt(or([q209 <= a_PartitionOccurrence_NumParts /\ - (and([a_PartitionOccurrence_WhichPart[q212] = q209 -> - or([a_PartitionOccurrence_WhichPart[q214] = q147 /\ q214 = q212 | q214 : int(1..2)]) - | q212 : int(1..2)]) - /\ - and([a_PartitionOccurrence_WhichPart[q216] = q147 -> - or([a_PartitionOccurrence_WhichPart[q218] = q209 /\ q218 = q216 | q218 : int(1..2)]) - | q216 : int(1..2)])) - | q209 : int(1..2)])) - = - toInt(or([q151 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ - (and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q151, q152] -> - or([a_PartitionOccurrence_WhichPart[q154] = q147 /\ q154 = q152 | q154 : int(1..2)]) - | q152 : int(1..2)]) - /\ - and([a_PartitionOccurrence_WhichPart[q156] = q147 -> - b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q151, q156] - | q156 : int(1..2)])) - | q151 : int(1..2)])) - | q147 : int(1..2)]) - /\ - and([and([q181 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker, - !or([q196 <= a_PartitionOccurrence_NumParts /\ - (and([a_PartitionOccurrence_WhichPart[q199] = q196 -> - b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q181, q199] - | q199 : int(1..2)]) - /\ - and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q181, q200] -> - or([a_PartitionOccurrence_WhichPart[q202] = q196 /\ q202 = q200 | q202 : int(1..2)]) - | q200 : int(1..2)])) - | q196 : int(1..2)]), - or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q181, q203] /\ - (toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q181, q203]) < - toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q133, q203]) - /\ - (and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q181, q204] -> - toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q181, q204]) = - toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q133, q204]) - | q204 : int(1..2), q204 < q203]) - /\ - and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q133, q204] /\ - !or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q181, q207] /\ - q207 = q204 - | q207 : int(1..2)]) - -> - toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q181, q204]) = - toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q133, q204]) - | q204 : int(1..2), q204 < q203]))) - | q203 : int(1..2)]) - \/ - or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q133, q203] /\ - !or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q181, q206] /\ q206 = q203 - | q206 : int(1..2)]) - /\ - (toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q181, q203]) < - toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q133, q203]) - /\ - (and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q181, q204] -> - toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q181, q204]) = - toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q133, q204]) - | q204 : int(1..2), q204 < q203]) - /\ - and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q133, q204] /\ - !or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q181, q205] /\ - q205 = q204 - | q205 : int(1..2)]) - -> - toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q181, q204]) = - toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q133, q204]) - | q204 : int(1..2), q204 < q203]))) - | q203 : int(1..2)]); - int(1..3)]) - -> - toInt(or([q183 <= a_PartitionOccurrence_NumParts /\ - (and([a_PartitionOccurrence_WhichPart[q186] = q183 -> - b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q181, q186] - | q186 : int(1..2)]) - /\ - and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q181, q187] -> - or([a_PartitionOccurrence_WhichPart[q189] = q183 /\ q189 = q187 | q189 : int(1..2)]) - | q187 : int(1..2)])) - | q183 : int(1..2)])) - = - toInt(or([q192 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ - and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q192, q193] = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q181, q193] - | q193 : int(1..2)]) - | q192 : int(1..2)])) - | q181 : int(1..2)]))) - | q133 : int(1..2)]), - and([q1 <= a_PartitionOccurrence_NumParts -> a_PartitionOccurrence_PartSizes[q1] <= 2 | q1 : int(1..2)]), - and([q1 > a_PartitionOccurrence_NumParts -> a_PartitionOccurrence_PartSizes[q1] = 0 | q1 : int(1..2)]), - a_PartitionOccurrence_NumParts <= 2, - a_PartitionOccurrence_NumParts = max([a_PartitionOccurrence_WhichPart[q4] | q4 : int(1..2)]), - and([a_PartitionOccurrence_PartSizes[q5] = sum([toInt(a_PartitionOccurrence_WhichPart[q6] = q5) | q6 : int(1..2)]) - | q5 : int(1..2)]), - and([q7 <= a_PartitionOccurrence_NumParts -> - and([a_PartitionOccurrence_WhichPart[q8] = q7 -> a_PartitionOccurrence_FirstIndex[q7] <= q8 | q8 : int(1..2)]) - | q7 : int(1..2)]), - and([q7 <= a_PartitionOccurrence_NumParts -> - or([a_PartitionOccurrence_WhichPart[q8] = q7 /\ a_PartitionOccurrence_FirstIndex[q7] = q8 | q8 : int(1..2)]) - | q7 : int(1..2)]), - and([q7 > a_PartitionOccurrence_NumParts -> a_PartitionOccurrence_FirstIndex[q7] = 1 | q7 : int(1..2)]), - and([q9 <= a_PartitionOccurrence_NumParts /\ q10 <= a_PartitionOccurrence_NumParts -> - (q9 < q10 <-> a_PartitionOccurrence_FirstIndex[q9] < a_PartitionOccurrence_FirstIndex[q10]) - | q9 : int(1..2), q10 : int(1..2)]), - and([1 = - sum([toInt(q24 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q24, q11]) - | q24 : int(1..2)]) - | q11 : int(1..2)]), - and([q25 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> - sum([toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q25, q26]) | q26 : int(1..2)]) >= 1 - | q25 : int(1..2)]), - 2 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> - [-toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[1, q19]) | q19 : int(1..2)] b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> - and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q15, q21] = false | q21 : int(1..2)]) - | q15 : int(1..2)]), - b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker <= 2, - and([q16 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> - sum([toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q16, q17]) | q17 : int(1..2)]) <= 2 - | q16 : int(1..2)]), - 2 = - sum([toInt(q22 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker) * - catchUndef(sum([toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q22, q23]) - | q23 : int(1..2)]), - 0) - | q22 : int(1..2)]) - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_4_2-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_4_2-solution000001.solution deleted file mode 100644 index cde05d5274..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_4_2-solution000001.solution +++ /dev/null @@ -1,11 +0,0 @@ -language Essence 1.3 - -letting a be partition({1, 2}) -$ Visualisation for a -$ 1 2 - -letting b be partition({1}, {2}) -$ Visualisation for b -$ 1 -$ 2 - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_4_2.eprime b/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_4_2.eprime deleted file mode 100644 index 4fdad05487..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_4_2.eprime +++ /dev/null @@ -1,827 +0,0 @@ -language ESSENCE' 1.0 - -find a_PartitionOccurrence_NumParts: int(1..2) -find a_PartitionOccurrence_WhichPart: matrix indexed by [int(1..2)] of int(1..2) -find a_PartitionOccurrence_PartSizes: matrix indexed by [int(1..2)] of int(0..2) -find a_PartitionOccurrence_FirstIndex: matrix indexed by [int(1..2)] of int(1..2) -find b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker: int(0..2) -find b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy: - matrix indexed by [int(1..2), int(1..2)] of int(1..3) -branching on - [a_PartitionOccurrence_NumParts, a_PartitionOccurrence_WhichPart, a_PartitionOccurrence_PartSizes, - a_PartitionOccurrence_FirstIndex, b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker, - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy] -such that - or([q35 <= a_PartitionOccurrence_NumParts /\ - (toInt(or([q158 <= a_PartitionOccurrence_NumParts /\ - (and([a_PartitionOccurrence_WhichPart[q161] = q158 -> - or([a_PartitionOccurrence_WhichPart[q163] = q35 /\ q163 = q161 | q163 : int(1..2)]) - | q161 : int(1..2)]) - /\ - and([a_PartitionOccurrence_WhichPart[q165] = q35 -> - or([a_PartitionOccurrence_WhichPart[q167] = q158 /\ q167 = q165 | q167 : int(1..2)]) - | q165 : int(1..2)])) - | q158 : int(1..2)])) - < - toInt(or([q39 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ - (and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q39, q41] != 3 -> - or([a_PartitionOccurrence_WhichPart[q43] = q35 /\ - q43 = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q39, q41] - | q43 : int(1..2)]) - | q41 : int(1..2)]) - /\ - and([a_PartitionOccurrence_WhichPart[q45] = q35 -> - or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q39, q47] != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q39, q47] = - q45 | q47 : int(1..2)]) - | q45 : int(1..2)])) - | q39 : int(1..2)])) - /\ - (and([q68 <= a_PartitionOccurrence_NumParts /\ - (or([a_PartitionOccurrence_WhichPart[q89] = q68 /\ - (toInt(or([a_PartitionOccurrence_WhichPart[q82] = q68 /\ q82 = q89 | q82 : int(1..2)])) < - sum([toInt(a_PartitionOccurrence_WhichPart[q61] = q35) * catchUndef(toInt(q61 = q89), 0) - | q61 : int(1..2)]) - /\ - (and([a_PartitionOccurrence_WhichPart[q85] = q68 -> - toInt(or([a_PartitionOccurrence_WhichPart[q84] = q68 /\ q84 = q85 | q84 : int(1..2)])) = - sum([toInt(a_PartitionOccurrence_WhichPart[q67] = q35) * catchUndef(toInt(q67 = q85), 0) - | q67 : int(1..2)]) - | q85 : int(1..2), q85 < q89]) - /\ - and([!or([a_PartitionOccurrence_WhichPart[q88] = q68 /\ q88 = q62 | q88 : int(1..2)]) -> - (a_PartitionOccurrence_WhichPart[q62] = q35 -> - toInt(or([a_PartitionOccurrence_WhichPart[q87] = q68 /\ q87 = q62 | q87 : int(1..2)])) = - sum([toInt(a_PartitionOccurrence_WhichPart[q64] = q35) * catchUndef(toInt(q64 = q62), 0) - | q64 : int(1..2)])) - | q62 : int(1..2), q62 < q89]))) - | q89 : int(1..2)]) - \/ - or([!or([a_PartitionOccurrence_WhichPart[q98] = q68 /\ q98 = q50 | q98 : int(1..2)]) /\ - (a_PartitionOccurrence_WhichPart[q50] = q35 /\ - (toInt(or([a_PartitionOccurrence_WhichPart[q91] = q68 /\ q91 = q50 | q91 : int(1..2)])) < - sum([toInt(a_PartitionOccurrence_WhichPart[q52] = q35) * catchUndef(toInt(q52 = q50), 0) - | q52 : int(1..2)]) - /\ - (and([a_PartitionOccurrence_WhichPart[q94] = q68 -> - toInt(or([a_PartitionOccurrence_WhichPart[q93] = q68 /\ q93 = q94 | q93 : int(1..2)])) = - sum([toInt(a_PartitionOccurrence_WhichPart[q58] = q35) * catchUndef(toInt(q58 = q94), 0) - | q58 : int(1..2)]) - | q94 : int(1..2), q94 < q50]) - /\ - and([!or([a_PartitionOccurrence_WhichPart[q97] = q68 /\ q97 = q53 | q97 : int(1..2)]) -> - (a_PartitionOccurrence_WhichPart[q53] = q35 -> - toInt(or([a_PartitionOccurrence_WhichPart[q96] = q68 /\ q96 = q53 | q96 : int(1..2)])) = - sum([toInt(a_PartitionOccurrence_WhichPart[q55] = q35) * catchUndef(toInt(q55 = q53), 0) - | q55 : int(1..2)])) - | q53 : int(1..2), q53 < q50])))) - | q50 : int(1..2)])) - -> - toInt(or([q147 <= a_PartitionOccurrence_NumParts /\ - (and([a_PartitionOccurrence_WhichPart[q150] = q147 -> - or([a_PartitionOccurrence_WhichPart[q152] = q68 /\ q152 = q150 | q152 : int(1..2)]) - | q150 : int(1..2)]) - /\ - and([a_PartitionOccurrence_WhichPart[q154] = q68 -> - or([a_PartitionOccurrence_WhichPart[q156] = q147 /\ q156 = q154 | q156 : int(1..2)]) - | q154 : int(1..2)])) - | q147 : int(1..2)])) - = - toInt(or([q72 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ - (and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q72, q74] != - 3 - -> - or([a_PartitionOccurrence_WhichPart[q76] = q68 /\ - q76 = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q72, q74] - | q76 : int(1..2)]) - | q74 : int(1..2)]) - /\ - and([a_PartitionOccurrence_WhichPart[q78] = q68 -> - or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q72, q80] - != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q72, q80] - = q78 - | q80 : int(1..2)]) - | q78 : int(1..2)])) - | q72 : int(1..2)])) - | q68 : int(1..2)]) - /\ - and([and([q100 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker, - !or([q136 <= a_PartitionOccurrence_NumParts /\ - (and([a_PartitionOccurrence_WhichPart[q139] = q136 -> - or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q100, q141] - != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q100, q141] - = q139 - | q141 : int(1..2)]) - | q139 : int(1..2)]) - /\ - and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q100, q143] - != 3 - -> - or([a_PartitionOccurrence_WhichPart[q145] = q136 /\ - q145 = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q100, q143] - | q145 : int(1..2)]) - | q143 : int(1..2)])) - | q136 : int(1..2)]), - or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q100, q101] != 3 /\ - (toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q100, q109] - != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q100, q109] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q100, q101] - | q109 : int(1..2)])) - < - sum([toInt(a_PartitionOccurrence_WhichPart[q61] = q35) * - catchUndef(toInt(q61 = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q100, q101]), - 0) - | q61 : int(1..2)]) - /\ - (and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q100, q102] - != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q100, q102] - < - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q100, q101] - -> - toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q100, q104] - != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q100, q104] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q100, q102] - | q104 : int(1..2)])) - = - sum([toInt(a_PartitionOccurrence_WhichPart[q67] = q35) * - catchUndef(toInt(q67 = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q100, q102]), - 0) - | q67 : int(1..2)]) - | q102 : int(1..2)]) - /\ - and([!or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q100, q105] - != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q100, q105] - = q62 - | q105 : int(1..2)]) - /\ - q62 < - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q100, q101] - -> - (a_PartitionOccurrence_WhichPart[q62] = q35 -> - toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q100, q107] - != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q100, q107] - = q62 - | q107 : int(1..2)])) - = - sum([toInt(a_PartitionOccurrence_WhichPart[q64] = q35) * catchUndef(toInt(q64 = q62), 0) - | q64 : int(1..2)])) - | q62 : int(1..2)]))) - | q101 : int(1..2)]) - \/ - or([!or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q100, q118] != - 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q100, q118] = - q50 | q118 : int(1..2)]) - /\ - (a_PartitionOccurrence_WhichPart[q50] = q35 /\ - (toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q100, q117] - != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q100, q117] - = q50 - | q117 : int(1..2)])) - < - sum([toInt(a_PartitionOccurrence_WhichPart[q52] = q35) * catchUndef(toInt(q52 = q50), 0) - | q52 : int(1..2)]) - /\ - (and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q100, q110] - != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q100, q110] - < q50 - -> - toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q100, q112] - != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q100, q112] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q100, q110] - | q112 : int(1..2)])) - = - sum([toInt(a_PartitionOccurrence_WhichPart[q58] = q35) * - catchUndef(toInt(q58 = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q100, q110]), - 0) - | q58 : int(1..2)]) - | q110 : int(1..2)]) - /\ - and([!or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q100, q113] - != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q100, q113] - = q53 - | q113 : int(1..2)]) - -> - (a_PartitionOccurrence_WhichPart[q53] = q35 -> - toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q100, q115] - != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q100, q115] - = q53 - | q115 : int(1..2)])) - = - sum([toInt(a_PartitionOccurrence_WhichPart[q55] = q35) * - catchUndef(toInt(q55 = q53), 0) - | q55 : int(1..2)])) - | q53 : int(1..2), q53 < q50])))) - | q50 : int(1..2)]); - int(1..3)]) - -> - toInt(or([q120 <= a_PartitionOccurrence_NumParts /\ - (and([a_PartitionOccurrence_WhichPart[q123] = q120 -> - or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q100, q125] - != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q100, q125] - = q123 - | q125 : int(1..2)]) - | q123 : int(1..2)]) - /\ - and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q100, q127] - != 3 - -> - or([a_PartitionOccurrence_WhichPart[q129] = q120 /\ - q129 = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q100, q127] - | q129 : int(1..2)]) - | q127 : int(1..2)])) - | q120 : int(1..2)])) - = - toInt(or([q132 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ - and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q132, q133] = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q100, q133] - | q133 : int(1..2)]) - | q132 : int(1..2)])) - | q100 : int(1..2)]))) - | q35 : int(1..2)]) - \/ - or([q169 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ - !or([q316 <= a_PartitionOccurrence_NumParts /\ - (and([a_PartitionOccurrence_WhichPart[q319] = q316 -> - or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q169, q321] != 3 /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q169, q321] = q319 - | q321 : int(1..2)]) - | q319 : int(1..2)]) - /\ - and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q169, q323] != 3 -> - or([a_PartitionOccurrence_WhichPart[q325] = q316 /\ - q325 = b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q169, q323] - | q325 : int(1..2)]) - | q323 : int(1..2)])) - | q316 : int(1..2)]) - /\ - (toInt(or([q171 <= a_PartitionOccurrence_NumParts /\ - (and([a_PartitionOccurrence_WhichPart[q174] = q171 -> - or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q169, q176] != - 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q169, q176] = - q174 - | q176 : int(1..2)]) - | q174 : int(1..2)]) - /\ - and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q169, q178] != 3 - -> - or([a_PartitionOccurrence_WhichPart[q180] = q171 /\ - q180 = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q169, q178] - | q180 : int(1..2)]) - | q178 : int(1..2)])) - | q171 : int(1..2)])) - < - toInt(or([q183 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ - and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q183, q184] = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q169, q184] - | q184 : int(1..2)]) - | q183 : int(1..2)])) - /\ - (and([q186 <= a_PartitionOccurrence_NumParts /\ - (or([a_PartitionOccurrence_WhichPart[q201] = q186 /\ - (sum([toInt(a_PartitionOccurrence_WhichPart[q222] = q186) * catchUndef(toInt(q222 = q201), 0) - | q222 : int(1..2)]) - < - toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q169, q224] - != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q169, q224] - = q201 - | q224 : int(1..2)])) - /\ - (and([a_PartitionOccurrence_WhichPart[q225] = q186 -> - sum([toInt(a_PartitionOccurrence_WhichPart[q234] = q186) * catchUndef(toInt(q234 = q225), 0) - | q234 : int(1..2)]) - = - toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q169, q236] - != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q169, q236] - = q225 - | q236 : int(1..2)])) - | q225 : int(1..2), q225 < q201]) - /\ - and([and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q169, q226] - != 3, - !or([a_PartitionOccurrence_WhichPart[q228] = q186 /\ - q228 = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q169, q226] - | q228 : int(1..2)]), - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q169, q226] - < q201; - int(1..3)]) - -> - sum([toInt(a_PartitionOccurrence_WhichPart[q230] = q186) * - catchUndef(toInt(q230 = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q169, q226]), - 0) - | q230 : int(1..2)]) - = - toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q169, q232] - != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q169, q232] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q169, q226] - | q232 : int(1..2)])) - | q226 : int(1..2)]))) - | q201 : int(1..2)]) - \/ - or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q169, q202] != 3 /\ - !or([a_PartitionOccurrence_WhichPart[q204] = q186 /\ - q204 = b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q169, q202] - | q204 : int(1..2)]) - /\ - (sum([toInt(a_PartitionOccurrence_WhichPart[q206] = q186) * - catchUndef(toInt(q206 = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q169, q202]), - 0) - | q206 : int(1..2)]) - < - toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q169, q208] - != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q169, q208] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q169, q202] - | q208 : int(1..2)])) - /\ - (and([a_PartitionOccurrence_WhichPart[q209] = q186 /\ - q209 < - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q169, q202] - -> - sum([toInt(a_PartitionOccurrence_WhichPart[q218] = q186) * catchUndef(toInt(q218 = q209), 0) - | q218 : int(1..2)]) - = - toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q169, q220] - != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q169, q220] - = q209 - | q220 : int(1..2)])) - | q209 : int(1..2)]) - /\ - and([and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q169, q210] - != 3, - !or([a_PartitionOccurrence_WhichPart[q212] = q186 /\ - q212 = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q169, q210] - | q212 : int(1..2)]), - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q169, q210] - < - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q169, q202]; - int(1..3)]) - -> - sum([toInt(a_PartitionOccurrence_WhichPart[q214] = q186) * - catchUndef(toInt(q214 = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q169, q210]), - 0) - | q214 : int(1..2)]) - = - toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q169, q216] - != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q169, q216] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q169, q210] - | q216 : int(1..2)])) - | q210 : int(1..2)]))) - | q202 : int(1..2)])) - -> - toInt(or([q305 <= a_PartitionOccurrence_NumParts /\ - (and([a_PartitionOccurrence_WhichPart[q308] = q305 -> - or([a_PartitionOccurrence_WhichPart[q310] = q186 /\ q310 = q308 | q310 : int(1..2)]) - | q308 : int(1..2)]) - /\ - and([a_PartitionOccurrence_WhichPart[q312] = q186 -> - or([a_PartitionOccurrence_WhichPart[q314] = q305 /\ q314 = q312 | q314 : int(1..2)]) - | q312 : int(1..2)])) - | q305 : int(1..2)])) - = - toInt(or([q190 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ - (and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q190, q192] - != 3 - -> - or([a_PartitionOccurrence_WhichPart[q194] = q186 /\ - q194 = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q190, q192] - | q194 : int(1..2)]) - | q192 : int(1..2)]) - /\ - and([a_PartitionOccurrence_WhichPart[q196] = q186 -> - or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q190, q198] - != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q190, q198] - = q196 - | q198 : int(1..2)]) - | q196 : int(1..2)])) - | q190 : int(1..2)])) - | q186 : int(1..2)]) - /\ - and([and([q238 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker, - !or([q256 <= a_PartitionOccurrence_NumParts /\ - (and([a_PartitionOccurrence_WhichPart[q259] = q256 -> - or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q238, q261] - != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q238, q261] - = q259 - | q261 : int(1..2)]) - | q259 : int(1..2)]) - /\ - and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q238, q263] - != 3 - -> - or([a_PartitionOccurrence_WhichPart[q265] = q256 /\ - q265 = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q238, q263] - | q265 : int(1..2)]) - | q263 : int(1..2)])) - | q256 : int(1..2)]), - or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q238, q268] != 3 /\ - (toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q238, q289] - != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q238, q289] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q238, q268] - | q289 : int(1..2)])) - < - toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q169, q291] - != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q169, q291] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q238, q268] - | q291 : int(1..2)])) - /\ - (and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q238, q292] - != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q238, q292] - < - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q238, q268] - -> - toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q238, q301] - != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q238, q301] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q238, q292] - | q301 : int(1..2)])) - = - toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q169, q303] - != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q169, q303] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q238, q292] - | q303 : int(1..2)])) - | q292 : int(1..2)]) - /\ - and([and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q169, q293] - != 3, - !or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q238, q295] - != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q238, q295] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q169, q293] - | q295 : int(1..2)]), - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q169, q293] - < - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q238, q268]; - int(1..3)]) - -> - toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q238, q297] - != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q238, q297] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q169, q293] - | q297 : int(1..2)])) - = - toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q169, q299] - != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q169, q299] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q169, q293] - | q299 : int(1..2)])) - | q293 : int(1..2)]))) - | q268 : int(1..2)]) - \/ - or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q169, q269] != 3 /\ - !or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q238, q271] != - 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q238, q271] = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q169, q269] - | q271 : int(1..2)]) - /\ - (toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q238, q273] - != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q238, q273] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q169, q269] - | q273 : int(1..2)])) - < - toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q169, q275] - != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q169, q275] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q169, q269] - | q275 : int(1..2)])) - /\ - (and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q238, q276] - != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q238, q276] - < - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q169, q269] - -> - toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q238, q285] - != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q238, q285] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q238, q276] - | q285 : int(1..2)])) - = - toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q169, q287] - != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q169, q287] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q238, q276] - | q287 : int(1..2)])) - | q276 : int(1..2)]) - /\ - and([and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q169, q277] - != 3, - !or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q238, q279] - != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q238, q279] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q169, q277] - | q279 : int(1..2)]), - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q169, q277] - < - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q169, q269]; - int(1..3)]) - -> - toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q238, q281] - != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q238, q281] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q169, q277] - | q281 : int(1..2)])) - = - toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q169, q283] - != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q169, q283] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q169, q277] - | q283 : int(1..2)])) - | q277 : int(1..2)]))) - | q269 : int(1..2)]); - int(1..3)]) - -> - toInt(or([q240 <= a_PartitionOccurrence_NumParts /\ - (and([a_PartitionOccurrence_WhichPart[q243] = q240 -> - or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q238, q245] - != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q238, q245] - = q243 - | q245 : int(1..2)]) - | q243 : int(1..2)]) - /\ - and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q238, q247] - != 3 - -> - or([a_PartitionOccurrence_WhichPart[q249] = q240 /\ - q249 = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q238, q247] - | q249 : int(1..2)]) - | q247 : int(1..2)])) - | q240 : int(1..2)])) - = - toInt(or([q252 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ - and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q252, q253] = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q238, q253] - | q253 : int(1..2)]) - | q252 : int(1..2)])) - | q238 : int(1..2)]))) - | q169 : int(1..2)]), - and([q1 <= a_PartitionOccurrence_NumParts -> a_PartitionOccurrence_PartSizes[q1] <= 2 | q1 : int(1..2)]), - and([q1 > a_PartitionOccurrence_NumParts -> a_PartitionOccurrence_PartSizes[q1] = 0 | q1 : int(1..2)]), - a_PartitionOccurrence_NumParts <= 2, - a_PartitionOccurrence_NumParts = max([a_PartitionOccurrence_WhichPart[q4] | q4 : int(1..2)]), - and([a_PartitionOccurrence_PartSizes[q5] = sum([toInt(a_PartitionOccurrence_WhichPart[q6] = q5) | q6 : int(1..2)]) - | q5 : int(1..2)]), - and([q7 <= a_PartitionOccurrence_NumParts -> - and([a_PartitionOccurrence_WhichPart[q8] = q7 -> a_PartitionOccurrence_FirstIndex[q7] <= q8 | q8 : int(1..2)]) - | q7 : int(1..2)]), - and([q7 <= a_PartitionOccurrence_NumParts -> - or([a_PartitionOccurrence_WhichPart[q8] = q7 /\ a_PartitionOccurrence_FirstIndex[q7] = q8 | q8 : int(1..2)]) - | q7 : int(1..2)]), - and([q7 > a_PartitionOccurrence_NumParts -> a_PartitionOccurrence_FirstIndex[q7] = 1 | q7 : int(1..2)]), - and([q9 <= a_PartitionOccurrence_NumParts /\ q10 <= a_PartitionOccurrence_NumParts -> - (q9 < q10 <-> a_PartitionOccurrence_FirstIndex[q9] < a_PartitionOccurrence_FirstIndex[q10]) - | q9 : int(1..2), q10 : int(1..2)]), - alldifferent_except([toInt(q28 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q28, q29] != - 3) - * - catchUndef(b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q28, q29], - 0) - | q28 : int(1..2), q29 : int(1..2)], - 0), - and([q30 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - sum([toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q30, q32] != 3) - | q32 : int(1..2)]) - >= 1 - | q30 : int(1..2)]), - 2 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - [b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[1, q22] | q22 : int(1..2)] b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q15, q27] = 1 - | q27 : int(1..2)]) - | q15 : int(1..2)]), - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker <= 2, - and([q16 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q16, 1] < - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q16, 2] - \/ b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q16, 1] = 3 - | q16 : int(1..2)]), - and([q16 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - (b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q16, 1] = 3 -> - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q16, 2] = 3) - | q16 : int(1..2)]), - and([q16 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - sum([toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q16, q19] != 3) - | q19 : int(1..2)]) - <= 2 - | q16 : int(1..2)]), - 2 = - sum([toInt(q24 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker) * - catchUndef(sum([toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q24, q26] != - 3) - | q26 : int(1..2)]), - 0) - | q24 : int(1..2)]) - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_4_3-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_4_3-solution000001.solution deleted file mode 100644 index cde05d5274..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_4_3-solution000001.solution +++ /dev/null @@ -1,11 +0,0 @@ -language Essence 1.3 - -letting a be partition({1, 2}) -$ Visualisation for a -$ 1 2 - -letting b be partition({1}, {2}) -$ Visualisation for b -$ 1 -$ 2 - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_4_3.eprime b/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_4_3.eprime deleted file mode 100644 index 61840c1142..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_4_3.eprime +++ /dev/null @@ -1,903 +0,0 @@ -language ESSENCE' 1.0 - -find a_PartitionOccurrence_NumParts: int(1..2) -find a_PartitionOccurrence_WhichPart: matrix indexed by [int(1..2)] of int(1..2) -find a_PartitionOccurrence_PartSizes: matrix indexed by [int(1..2)] of int(0..2) -find a_PartitionOccurrence_FirstIndex: matrix indexed by [int(1..2)] of int(1..2) -find b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker: int(0..2) -find b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker: - matrix indexed by [int(1..2)] of int(0..2) -find b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values: - matrix indexed by [int(1..2), int(1..2)] of int(1..2) -branching on - [a_PartitionOccurrence_NumParts, a_PartitionOccurrence_WhichPart, a_PartitionOccurrence_PartSizes, - a_PartitionOccurrence_FirstIndex, b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker, - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker, - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values] -such that - or([q30 <= a_PartitionOccurrence_NumParts /\ - (toInt(or([q153 <= a_PartitionOccurrence_NumParts /\ - (and([a_PartitionOccurrence_WhichPart[q156] = q153 -> - or([a_PartitionOccurrence_WhichPart[q158] = q30 /\ q158 = q156 | q158 : int(1..2)]) - | q156 : int(1..2)]) - /\ - and([a_PartitionOccurrence_WhichPart[q160] = q30 -> - or([a_PartitionOccurrence_WhichPart[q162] = q153 /\ q162 = q160 | q162 : int(1..2)]) - | q160 : int(1..2)])) - | q153 : int(1..2)])) - < - toInt(or([q34 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - (and([q36 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q34] - -> - or([a_PartitionOccurrence_WhichPart[q38] = q30 /\ - q38 = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q34, q36] - | q38 : int(1..2)]) - | q36 : int(1..2)]) - /\ - and([a_PartitionOccurrence_WhichPart[q40] = q30 -> - or([q42 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q34] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q34, q42] - = q40 - | q42 : int(1..2)]) - | q40 : int(1..2)])) - | q34 : int(1..2)])) - /\ - (and([q63 <= a_PartitionOccurrence_NumParts /\ - (or([a_PartitionOccurrence_WhichPart[q84] = q63 /\ - (toInt(or([a_PartitionOccurrence_WhichPart[q77] = q63 /\ q77 = q84 | q77 : int(1..2)])) < - sum([toInt(a_PartitionOccurrence_WhichPart[q56] = q30) * catchUndef(toInt(q56 = q84), 0) - | q56 : int(1..2)]) - /\ - (and([a_PartitionOccurrence_WhichPart[q80] = q63 -> - toInt(or([a_PartitionOccurrence_WhichPart[q79] = q63 /\ q79 = q80 | q79 : int(1..2)])) = - sum([toInt(a_PartitionOccurrence_WhichPart[q62] = q30) * catchUndef(toInt(q62 = q80), 0) - | q62 : int(1..2)]) - | q80 : int(1..2), q80 < q84]) - /\ - and([!or([a_PartitionOccurrence_WhichPart[q83] = q63 /\ q83 = q57 | q83 : int(1..2)]) -> - (a_PartitionOccurrence_WhichPart[q57] = q30 -> - toInt(or([a_PartitionOccurrence_WhichPart[q82] = q63 /\ q82 = q57 | q82 : int(1..2)])) = - sum([toInt(a_PartitionOccurrence_WhichPart[q59] = q30) * catchUndef(toInt(q59 = q57), 0) - | q59 : int(1..2)])) - | q57 : int(1..2), q57 < q84]))) - | q84 : int(1..2)]) - \/ - or([!or([a_PartitionOccurrence_WhichPart[q93] = q63 /\ q93 = q45 | q93 : int(1..2)]) /\ - (a_PartitionOccurrence_WhichPart[q45] = q30 /\ - (toInt(or([a_PartitionOccurrence_WhichPart[q86] = q63 /\ q86 = q45 | q86 : int(1..2)])) < - sum([toInt(a_PartitionOccurrence_WhichPart[q47] = q30) * catchUndef(toInt(q47 = q45), 0) - | q47 : int(1..2)]) - /\ - (and([a_PartitionOccurrence_WhichPart[q89] = q63 -> - toInt(or([a_PartitionOccurrence_WhichPart[q88] = q63 /\ q88 = q89 | q88 : int(1..2)])) = - sum([toInt(a_PartitionOccurrence_WhichPart[q53] = q30) * catchUndef(toInt(q53 = q89), 0) - | q53 : int(1..2)]) - | q89 : int(1..2), q89 < q45]) - /\ - and([!or([a_PartitionOccurrence_WhichPart[q92] = q63 /\ q92 = q48 | q92 : int(1..2)]) -> - (a_PartitionOccurrence_WhichPart[q48] = q30 -> - toInt(or([a_PartitionOccurrence_WhichPart[q91] = q63 /\ q91 = q48 | q91 : int(1..2)])) = - sum([toInt(a_PartitionOccurrence_WhichPart[q50] = q30) * catchUndef(toInt(q50 = q48), 0) - | q50 : int(1..2)])) - | q48 : int(1..2), q48 < q45])))) - | q45 : int(1..2)])) - -> - toInt(or([q142 <= a_PartitionOccurrence_NumParts /\ - (and([a_PartitionOccurrence_WhichPart[q145] = q142 -> - or([a_PartitionOccurrence_WhichPart[q147] = q63 /\ q147 = q145 | q147 : int(1..2)]) - | q145 : int(1..2)]) - /\ - and([a_PartitionOccurrence_WhichPart[q149] = q63 -> - or([a_PartitionOccurrence_WhichPart[q151] = q142 /\ q151 = q149 | q151 : int(1..2)]) - | q149 : int(1..2)])) - | q142 : int(1..2)])) - = - toInt(or([q67 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - (and([q69 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q67] - -> - or([a_PartitionOccurrence_WhichPart[q71] = q63 /\ - q71 = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q67, q69] - | q71 : int(1..2)]) - | q69 : int(1..2)]) - /\ - and([a_PartitionOccurrence_WhichPart[q73] = q63 -> - or([q75 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q67] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q67, q75] - = q73 - | q75 : int(1..2)]) - | q73 : int(1..2)])) - | q67 : int(1..2)])) - | q63 : int(1..2)]) - /\ - and([and([q95 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker, - !or([q131 <= a_PartitionOccurrence_NumParts /\ - (and([a_PartitionOccurrence_WhichPart[q134] = q131 -> - or([q136 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q95] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q95, q136] - = q134 - | q136 : int(1..2)]) - | q134 : int(1..2)]) - /\ - and([q138 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q95] - -> - or([a_PartitionOccurrence_WhichPart[q140] = q131 /\ - q140 = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q95, q138] - | q140 : int(1..2)]) - | q138 : int(1..2)])) - | q131 : int(1..2)]), - or([q96 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q95] - /\ - (toInt(or([q104 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q95] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q95, q104] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q95, q96] - | q104 : int(1..2)])) - < - sum([toInt(a_PartitionOccurrence_WhichPart[q56] = q30) * - catchUndef(toInt(q56 = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q95, q96]), - 0) - | q56 : int(1..2)]) - /\ - (and([q97 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q95] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q95, q97] - < - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q95, q96] - -> - toInt(or([q99 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q95] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q95, q99] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q95, q97] - | q99 : int(1..2)])) - = - sum([toInt(a_PartitionOccurrence_WhichPart[q62] = q30) * - catchUndef(toInt(q62 = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q95, q97]), - 0) - | q62 : int(1..2)]) - | q97 : int(1..2)]) - /\ - and([!or([q100 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q95] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q95, q100] - = q57 - | q100 : int(1..2)]) - /\ - q57 < - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q95, q96] - -> - (a_PartitionOccurrence_WhichPart[q57] = q30 -> - toInt(or([q102 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q95] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q95, q102] - = q57 - | q102 : int(1..2)])) - = - sum([toInt(a_PartitionOccurrence_WhichPart[q59] = q30) * catchUndef(toInt(q59 = q57), 0) - | q59 : int(1..2)])) - | q57 : int(1..2)]))) - | q96 : int(1..2)]) - \/ - or([!or([q113 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q95] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q95, q113] - = q45 - | q113 : int(1..2)]) - /\ - (a_PartitionOccurrence_WhichPart[q45] = q30 /\ - (toInt(or([q112 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q95] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q95, q112] - = q45 - | q112 : int(1..2)])) - < - sum([toInt(a_PartitionOccurrence_WhichPart[q47] = q30) * catchUndef(toInt(q47 = q45), 0) - | q47 : int(1..2)]) - /\ - (and([q105 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q95] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q95, q105] - < q45 - -> - toInt(or([q107 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q95] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q95, q107] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q95, q105] - | q107 : int(1..2)])) - = - sum([toInt(a_PartitionOccurrence_WhichPart[q53] = q30) * - catchUndef(toInt(q53 = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q95, q105]), - 0) - | q53 : int(1..2)]) - | q105 : int(1..2)]) - /\ - and([!or([q108 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q95] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q95, q108] - = q48 - | q108 : int(1..2)]) - -> - (a_PartitionOccurrence_WhichPart[q48] = q30 -> - toInt(or([q110 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q95] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q95, q110] - = q48 - | q110 : int(1..2)])) - = - sum([toInt(a_PartitionOccurrence_WhichPart[q50] = q30) * - catchUndef(toInt(q50 = q48), 0) - | q50 : int(1..2)])) - | q48 : int(1..2), q48 < q45])))) - | q45 : int(1..2)]); - int(1..3)]) - -> - toInt(or([q115 <= a_PartitionOccurrence_NumParts /\ - (and([a_PartitionOccurrence_WhichPart[q118] = q115 -> - or([q120 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q95] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q95, q120] - = q118 - | q120 : int(1..2)]) - | q118 : int(1..2)]) - /\ - and([q122 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q95] - -> - or([a_PartitionOccurrence_WhichPart[q124] = q115 /\ - q124 = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q95, q122] - | q124 : int(1..2)]) - | q122 : int(1..2)])) - | q115 : int(1..2)])) - = - toInt(or([q127 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - (b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q127] = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q95] - /\ - and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q127, q128] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q95, q128] - | q128 : int(1..2)])) - | q127 : int(1..2)])) - | q95 : int(1..2)]))) - | q30 : int(1..2)]) - \/ - or([q164 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - !or([q311 <= a_PartitionOccurrence_NumParts /\ - (and([a_PartitionOccurrence_WhichPart[q314] = q311 -> - or([q316 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q164] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q164, q316] - = q314 - | q316 : int(1..2)]) - | q314 : int(1..2)]) - /\ - and([q318 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q164] -> - or([a_PartitionOccurrence_WhichPart[q320] = q311 /\ - q320 = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q164, q318] - | q320 : int(1..2)]) - | q318 : int(1..2)])) - | q311 : int(1..2)]) - /\ - (toInt(or([q166 <= a_PartitionOccurrence_NumParts /\ - (and([a_PartitionOccurrence_WhichPart[q169] = q166 -> - or([q171 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q164] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q164, q171] - = q169 - | q171 : int(1..2)]) - | q169 : int(1..2)]) - /\ - and([q173 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q164] - -> - or([a_PartitionOccurrence_WhichPart[q175] = q166 /\ - q175 = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q164, q173] - | q175 : int(1..2)]) - | q173 : int(1..2)])) - | q166 : int(1..2)])) - < - toInt(or([q178 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - (b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q178] = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q164] - /\ - and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q178, q179] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q164, q179] - | q179 : int(1..2)])) - | q178 : int(1..2)])) - /\ - (and([q181 <= a_PartitionOccurrence_NumParts /\ - (or([a_PartitionOccurrence_WhichPart[q196] = q181 /\ - (sum([toInt(a_PartitionOccurrence_WhichPart[q217] = q181) * catchUndef(toInt(q217 = q196), 0) - | q217 : int(1..2)]) - < - toInt(or([q219 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q164] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q164, q219] - = q196 - | q219 : int(1..2)])) - /\ - (and([a_PartitionOccurrence_WhichPart[q220] = q181 -> - sum([toInt(a_PartitionOccurrence_WhichPart[q229] = q181) * catchUndef(toInt(q229 = q220), 0) - | q229 : int(1..2)]) - = - toInt(or([q231 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q164] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q164, q231] - = q220 - | q231 : int(1..2)])) - | q220 : int(1..2), q220 < q196]) - /\ - and([and([q221 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q164], - !or([a_PartitionOccurrence_WhichPart[q227] = q181 /\ - q227 = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q164, q221] - | q227 : int(1..2)]), - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q164, q221] - < q196; - int(1..3)]) - -> - sum([toInt(a_PartitionOccurrence_WhichPart[q223] = q181) * - catchUndef(toInt(q223 = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q164, q221]), - 0) - | q223 : int(1..2)]) - = - toInt(or([q225 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q164] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q164, q225] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q164, q221] - | q225 : int(1..2)])) - | q221 : int(1..2)]))) - | q196 : int(1..2)]) - \/ - or([q197 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q164] - /\ - !or([a_PartitionOccurrence_WhichPart[q215] = q181 /\ - q215 = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q164, q197] - | q215 : int(1..2)]) - /\ - (sum([toInt(a_PartitionOccurrence_WhichPart[q199] = q181) * - catchUndef(toInt(q199 = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q164, q197]), - 0) - | q199 : int(1..2)]) - < - toInt(or([q201 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q164] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q164, q201] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q164, q197] - | q201 : int(1..2)])) - /\ - (and([a_PartitionOccurrence_WhichPart[q202] = q181 /\ - q202 < - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q164, q197] - -> - sum([toInt(a_PartitionOccurrence_WhichPart[q211] = q181) * catchUndef(toInt(q211 = q202), 0) - | q211 : int(1..2)]) - = - toInt(or([q213 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q164] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q164, q213] - = q202 - | q213 : int(1..2)])) - | q202 : int(1..2)]) - /\ - and([and([q203 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q164], - !or([a_PartitionOccurrence_WhichPart[q209] = q181 /\ - q209 = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q164, q203] - | q209 : int(1..2)]), - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q164, q203] - < - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q164, q197]; - int(1..3)]) - -> - sum([toInt(a_PartitionOccurrence_WhichPart[q205] = q181) * - catchUndef(toInt(q205 = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q164, q203]), - 0) - | q205 : int(1..2)]) - = - toInt(or([q207 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q164] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q164, q207] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q164, q203] - | q207 : int(1..2)])) - | q203 : int(1..2)]))) - | q197 : int(1..2)])) - -> - toInt(or([q300 <= a_PartitionOccurrence_NumParts /\ - (and([a_PartitionOccurrence_WhichPart[q303] = q300 -> - or([a_PartitionOccurrence_WhichPart[q305] = q181 /\ q305 = q303 | q305 : int(1..2)]) - | q303 : int(1..2)]) - /\ - and([a_PartitionOccurrence_WhichPart[q307] = q181 -> - or([a_PartitionOccurrence_WhichPart[q309] = q300 /\ q309 = q307 | q309 : int(1..2)]) - | q307 : int(1..2)])) - | q300 : int(1..2)])) - = - toInt(or([q185 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - (and([q187 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q185] - -> - or([a_PartitionOccurrence_WhichPart[q189] = q181 /\ - q189 = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q185, q187] - | q189 : int(1..2)]) - | q187 : int(1..2)]) - /\ - and([a_PartitionOccurrence_WhichPart[q191] = q181 -> - or([q193 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q185] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q185, q193] - = q191 - | q193 : int(1..2)]) - | q191 : int(1..2)])) - | q185 : int(1..2)])) - | q181 : int(1..2)]) - /\ - and([and([q233 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker, - !or([q251 <= a_PartitionOccurrence_NumParts /\ - (and([a_PartitionOccurrence_WhichPart[q254] = q251 -> - or([q256 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q233] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q233, q256] - = q254 - | q256 : int(1..2)]) - | q254 : int(1..2)]) - /\ - and([q258 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q233] - -> - or([a_PartitionOccurrence_WhichPart[q260] = q251 /\ - q260 = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q233, q258] - | q260 : int(1..2)]) - | q258 : int(1..2)])) - | q251 : int(1..2)]), - or([q263 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q233] - /\ - (toInt(or([q284 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q233] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q233, q284] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q233, q263] - | q284 : int(1..2)])) - < - toInt(or([q286 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q164] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q164, q286] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q233, q263] - | q286 : int(1..2)])) - /\ - (and([q287 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q233] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q233, q287] - < - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q233, q263] - -> - toInt(or([q296 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q233] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q233, q296] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q233, q287] - | q296 : int(1..2)])) - = - toInt(or([q298 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q164] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q164, q298] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q233, q287] - | q298 : int(1..2)])) - | q287 : int(1..2)]) - /\ - and([and([q288 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q164], - !or([q294 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q233] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q233, q294] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q164, q288] - | q294 : int(1..2)]), - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q164, q288] - < - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q233, q263]; - int(1..3)]) - -> - toInt(or([q290 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q233] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q233, q290] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q164, q288] - | q290 : int(1..2)])) - = - toInt(or([q292 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q164] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q164, q292] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q164, q288] - | q292 : int(1..2)])) - | q288 : int(1..2)]))) - | q263 : int(1..2)]) - \/ - or([q264 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q164] - /\ - !or([q282 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q233] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q233, q282] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q164, q264] - | q282 : int(1..2)]) - /\ - (toInt(or([q266 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q233] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q233, q266] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q164, q264] - | q266 : int(1..2)])) - < - toInt(or([q268 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q164] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q164, q268] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q164, q264] - | q268 : int(1..2)])) - /\ - (and([q269 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q233] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q233, q269] - < - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q164, q264] - -> - toInt(or([q278 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q233] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q233, q278] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q233, q269] - | q278 : int(1..2)])) - = - toInt(or([q280 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q164] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q164, q280] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q233, q269] - | q280 : int(1..2)])) - | q269 : int(1..2)]) - /\ - and([and([q270 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q164], - !or([q276 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q233] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q233, q276] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q164, q270] - | q276 : int(1..2)]), - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q164, q270] - < - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q164, q264]; - int(1..3)]) - -> - toInt(or([q272 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q233] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q233, q272] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q164, q270] - | q272 : int(1..2)])) - = - toInt(or([q274 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q164] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q164, q274] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q164, q270] - | q274 : int(1..2)])) - | q270 : int(1..2)]))) - | q264 : int(1..2)]); - int(1..3)]) - -> - toInt(or([q235 <= a_PartitionOccurrence_NumParts /\ - (and([a_PartitionOccurrence_WhichPart[q238] = q235 -> - or([q240 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q233] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q233, q240] - = q238 - | q240 : int(1..2)]) - | q238 : int(1..2)]) - /\ - and([q242 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q233] - -> - or([a_PartitionOccurrence_WhichPart[q244] = q235 /\ - q244 = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q233, q242] - | q244 : int(1..2)]) - | q242 : int(1..2)])) - | q235 : int(1..2)])) - = - toInt(or([q247 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - (b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q247] = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q233] - /\ - and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q247, q248] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q233, q248] - | q248 : int(1..2)])) - | q247 : int(1..2)])) - | q233 : int(1..2)]))) - | q164 : int(1..2)]), - and([q1 <= a_PartitionOccurrence_NumParts -> a_PartitionOccurrence_PartSizes[q1] <= 2 | q1 : int(1..2)]), - and([q1 > a_PartitionOccurrence_NumParts -> a_PartitionOccurrence_PartSizes[q1] = 0 | q1 : int(1..2)]), - a_PartitionOccurrence_NumParts <= 2, - a_PartitionOccurrence_NumParts = max([a_PartitionOccurrence_WhichPart[q4] | q4 : int(1..2)]), - and([a_PartitionOccurrence_PartSizes[q5] = sum([toInt(a_PartitionOccurrence_WhichPart[q6] = q5) | q6 : int(1..2)]) - | q5 : int(1..2)]), - and([q7 <= a_PartitionOccurrence_NumParts -> - and([a_PartitionOccurrence_WhichPart[q8] = q7 -> a_PartitionOccurrence_FirstIndex[q7] <= q8 | q8 : int(1..2)]) - | q7 : int(1..2)]), - and([q7 <= a_PartitionOccurrence_NumParts -> - or([a_PartitionOccurrence_WhichPart[q8] = q7 /\ a_PartitionOccurrence_FirstIndex[q7] = q8 | q8 : int(1..2)]) - | q7 : int(1..2)]), - and([q7 > a_PartitionOccurrence_NumParts -> a_PartitionOccurrence_FirstIndex[q7] = 1 | q7 : int(1..2)]), - and([q9 <= a_PartitionOccurrence_NumParts /\ q10 <= a_PartitionOccurrence_NumParts -> - (q9 < q10 <-> a_PartitionOccurrence_FirstIndex[q9] < a_PartitionOccurrence_FirstIndex[q10]) - | q9 : int(1..2), q10 : int(1..2)]), - alldifferent_except([toInt(q25 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - q26 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q25]) - * - catchUndef(b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q25, q26], - 0) - | q25 : int(1..2), q26 : int(1..2)], - 0), - and([q27 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q27] >= 1 - | q27 : int(1..2)]), - 2 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - flatten([[b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[1]; int(1)], - flatten([[b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[1, q21]; - int(1)] - | q21 : int(1..2)]); - int(1..2)]) - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q15] = 0 /\ - and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q15, q24] = 1 - | q24 : int(1..2)]) - | q15 : int(1..2)]), - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker <= 2, - and([q16 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - (2 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q16] -> - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q16, 1] < - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q16, 2]) - | q16 : int(1..2)]), - and([q16 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - and([q18 > b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q16] -> - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q16, q18] = 1 - | q18 : int(1..2)]) - | q16 : int(1..2)]), - and([q16 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q16] <= 2 - | q16 : int(1..2)]), - 2 = - sum([toInt(q23 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker) * - catchUndef(b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q23], 0) - | q23 : int(1..2)]) - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_4_4-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_4_4-solution000001.solution deleted file mode 100644 index cde05d5274..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_4_4-solution000001.solution +++ /dev/null @@ -1,11 +0,0 @@ -language Essence 1.3 - -letting a be partition({1, 2}) -$ Visualisation for a -$ 1 2 - -letting b be partition({1}, {2}) -$ Visualisation for b -$ 1 -$ 2 - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_4_4.eprime b/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_4_4.eprime deleted file mode 100644 index c027a58750..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_4_4.eprime +++ /dev/null @@ -1,394 +0,0 @@ -language ESSENCE' 1.0 - -find a_PartitionOccurrence_NumParts: int(1..2) -find a_PartitionOccurrence_WhichPart: matrix indexed by [int(1..2)] of int(1..2) -find a_PartitionOccurrence_PartSizes: matrix indexed by [int(1..2)] of int(0..2) -find a_PartitionOccurrence_FirstIndex: matrix indexed by [int(1..2)] of int(1..2) -find b_PartitionOccurrence_NumParts: int(1..2) -find b_PartitionOccurrence_WhichPart: matrix indexed by [int(1..2)] of int(1..2) -find b_PartitionOccurrence_PartSizes: matrix indexed by [int(1..2)] of int(0..2) -find b_PartitionOccurrence_FirstIndex: matrix indexed by [int(1..2)] of int(1..2) -branching on - [a_PartitionOccurrence_NumParts, a_PartitionOccurrence_WhichPart, a_PartitionOccurrence_PartSizes, - a_PartitionOccurrence_FirstIndex, b_PartitionOccurrence_NumParts, b_PartitionOccurrence_WhichPart, - b_PartitionOccurrence_PartSizes, b_PartitionOccurrence_FirstIndex] -such that - or([q23 <= a_PartitionOccurrence_NumParts /\ - (toInt(or([q152 <= a_PartitionOccurrence_NumParts /\ - (and([a_PartitionOccurrence_WhichPart[q155] = q152 -> - or([a_PartitionOccurrence_WhichPart[q157] = q23 /\ q157 = q155 | q157 : int(1..2)]) - | q155 : int(1..2)]) - /\ - and([a_PartitionOccurrence_WhichPart[q159] = q23 -> - or([a_PartitionOccurrence_WhichPart[q161] = q152 /\ q161 = q159 | q161 : int(1..2)]) - | q159 : int(1..2)])) - | q152 : int(1..2)])) - < - toInt(or([q26 <= b_PartitionOccurrence_NumParts /\ - (and([b_PartitionOccurrence_WhichPart[q29] = q26 -> - or([a_PartitionOccurrence_WhichPart[q31] = q23 /\ q31 = q29 | q31 : int(1..2)]) - | q29 : int(1..2)]) - /\ - and([a_PartitionOccurrence_WhichPart[q33] = q23 -> - or([b_PartitionOccurrence_WhichPart[q35] = q26 /\ q35 = q33 | q35 : int(1..2)]) - | q33 : int(1..2)])) - | q26 : int(1..2)])) - /\ - (and([q56 <= a_PartitionOccurrence_NumParts /\ - (or([a_PartitionOccurrence_WhichPart[q77] = q56 /\ - (toInt(or([a_PartitionOccurrence_WhichPart[q70] = q56 /\ q70 = q77 | q70 : int(1..2)])) < - sum([toInt(a_PartitionOccurrence_WhichPart[q49] = q23) * catchUndef(toInt(q49 = q77), 0) - | q49 : int(1..2)]) - /\ - (and([a_PartitionOccurrence_WhichPart[q73] = q56 -> - toInt(or([a_PartitionOccurrence_WhichPart[q72] = q56 /\ q72 = q73 | q72 : int(1..2)])) = - sum([toInt(a_PartitionOccurrence_WhichPart[q55] = q23) * catchUndef(toInt(q55 = q73), 0) - | q55 : int(1..2)]) - | q73 : int(1..2), q73 < q77]) - /\ - and([!or([a_PartitionOccurrence_WhichPart[q76] = q56 /\ q76 = q50 | q76 : int(1..2)]) -> - (a_PartitionOccurrence_WhichPart[q50] = q23 -> - toInt(or([a_PartitionOccurrence_WhichPart[q75] = q56 /\ q75 = q50 | q75 : int(1..2)])) = - sum([toInt(a_PartitionOccurrence_WhichPart[q52] = q23) * catchUndef(toInt(q52 = q50), 0) - | q52 : int(1..2)])) - | q50 : int(1..2), q50 < q77]))) - | q77 : int(1..2)]) - \/ - or([!or([a_PartitionOccurrence_WhichPart[q86] = q56 /\ q86 = q38 | q86 : int(1..2)]) /\ - (a_PartitionOccurrence_WhichPart[q38] = q23 /\ - (toInt(or([a_PartitionOccurrence_WhichPart[q79] = q56 /\ q79 = q38 | q79 : int(1..2)])) < - sum([toInt(a_PartitionOccurrence_WhichPart[q40] = q23) * catchUndef(toInt(q40 = q38), 0) - | q40 : int(1..2)]) - /\ - (and([a_PartitionOccurrence_WhichPart[q82] = q56 -> - toInt(or([a_PartitionOccurrence_WhichPart[q81] = q56 /\ q81 = q82 | q81 : int(1..2)])) = - sum([toInt(a_PartitionOccurrence_WhichPart[q46] = q23) * catchUndef(toInt(q46 = q82), 0) - | q46 : int(1..2)]) - | q82 : int(1..2), q82 < q38]) - /\ - and([!or([a_PartitionOccurrence_WhichPart[q85] = q56 /\ q85 = q41 | q85 : int(1..2)]) -> - (a_PartitionOccurrence_WhichPart[q41] = q23 -> - toInt(or([a_PartitionOccurrence_WhichPart[q84] = q56 /\ q84 = q41 | q84 : int(1..2)])) = - sum([toInt(a_PartitionOccurrence_WhichPart[q43] = q23) * catchUndef(toInt(q43 = q41), 0) - | q43 : int(1..2)])) - | q41 : int(1..2), q41 < q38])))) - | q38 : int(1..2)])) - -> - toInt(or([q141 <= a_PartitionOccurrence_NumParts /\ - (and([a_PartitionOccurrence_WhichPart[q144] = q141 -> - or([a_PartitionOccurrence_WhichPart[q146] = q56 /\ q146 = q144 | q146 : int(1..2)]) - | q144 : int(1..2)]) - /\ - and([a_PartitionOccurrence_WhichPart[q148] = q56 -> - or([a_PartitionOccurrence_WhichPart[q150] = q141 /\ q150 = q148 | q150 : int(1..2)]) - | q148 : int(1..2)])) - | q141 : int(1..2)])) - = - toInt(or([q59 <= b_PartitionOccurrence_NumParts /\ - (and([b_PartitionOccurrence_WhichPart[q62] = q59 -> - or([a_PartitionOccurrence_WhichPart[q64] = q56 /\ q64 = q62 | q64 : int(1..2)]) - | q62 : int(1..2)]) - /\ - and([a_PartitionOccurrence_WhichPart[q66] = q56 -> - or([b_PartitionOccurrence_WhichPart[q68] = q59 /\ q68 = q66 | q68 : int(1..2)]) - | q66 : int(1..2)])) - | q59 : int(1..2)])) - | q56 : int(1..2)]) - /\ - and([and([q87 <= b_PartitionOccurrence_NumParts, - !or([q101 <= a_PartitionOccurrence_NumParts /\ - (and([a_PartitionOccurrence_WhichPart[q104] = q101 -> - or([b_PartitionOccurrence_WhichPart[q106] = q87 /\ q106 = q104 | q106 : int(1..2)]) - | q104 : int(1..2)]) - /\ - and([b_PartitionOccurrence_WhichPart[q108] = q87 -> - or([a_PartitionOccurrence_WhichPart[q110] = q101 /\ q110 = q108 | q110 : int(1..2)]) - | q108 : int(1..2)])) - | q101 : int(1..2)]), - or([b_PartitionOccurrence_WhichPart[q119] = q87 /\ - (toInt(or([b_PartitionOccurrence_WhichPart[q112] = q87 /\ q112 = q119 | q112 : int(1..2)])) < - sum([toInt(a_PartitionOccurrence_WhichPart[q49] = q23) * catchUndef(toInt(q49 = q119), 0) - | q49 : int(1..2)]) - /\ - (and([b_PartitionOccurrence_WhichPart[q115] = q87 -> - toInt(or([b_PartitionOccurrence_WhichPart[q114] = q87 /\ q114 = q115 - | q114 : int(1..2)])) - = - sum([toInt(a_PartitionOccurrence_WhichPart[q55] = q23) * catchUndef(toInt(q55 = q115), 0) - | q55 : int(1..2)]) - | q115 : int(1..2), q115 < q119]) - /\ - and([!or([b_PartitionOccurrence_WhichPart[q118] = q87 /\ q118 = q50 | q118 : int(1..2)]) -> - (a_PartitionOccurrence_WhichPart[q50] = q23 -> - toInt(or([b_PartitionOccurrence_WhichPart[q117] = q87 /\ q117 = q50 - | q117 : int(1..2)])) - = - sum([toInt(a_PartitionOccurrence_WhichPart[q52] = q23) * catchUndef(toInt(q52 = q50), 0) - | q52 : int(1..2)])) - | q50 : int(1..2), q50 < q119]))) - | q119 : int(1..2)]) - \/ - or([!or([b_PartitionOccurrence_WhichPart[q128] = q87 /\ q128 = q38 | q128 : int(1..2)]) /\ - (a_PartitionOccurrence_WhichPart[q38] = q23 /\ - (toInt(or([b_PartitionOccurrence_WhichPart[q121] = q87 /\ q121 = q38 | q121 : int(1..2)])) < - sum([toInt(a_PartitionOccurrence_WhichPart[q40] = q23) * catchUndef(toInt(q40 = q38), 0) - | q40 : int(1..2)]) - /\ - (and([b_PartitionOccurrence_WhichPart[q124] = q87 -> - toInt(or([b_PartitionOccurrence_WhichPart[q123] = q87 /\ q123 = q124 - | q123 : int(1..2)])) - = - sum([toInt(a_PartitionOccurrence_WhichPart[q46] = q23) * - catchUndef(toInt(q46 = q124), 0) - | q46 : int(1..2)]) - | q124 : int(1..2), q124 < q38]) - /\ - and([!or([b_PartitionOccurrence_WhichPart[q127] = q87 /\ q127 = q41 | q127 : int(1..2)]) -> - (a_PartitionOccurrence_WhichPart[q41] = q23 -> - toInt(or([b_PartitionOccurrence_WhichPart[q126] = q87 /\ q126 = q41 - | q126 : int(1..2)])) - = - sum([toInt(a_PartitionOccurrence_WhichPart[q43] = q23) * - catchUndef(toInt(q43 = q41), 0) - | q43 : int(1..2)])) - | q41 : int(1..2), q41 < q38])))) - | q38 : int(1..2)]); - int(1..3)]) - -> - toInt(or([q130 <= a_PartitionOccurrence_NumParts /\ - (and([a_PartitionOccurrence_WhichPart[q133] = q130 -> - or([b_PartitionOccurrence_WhichPart[q135] = q87 /\ q135 = q133 | q135 : int(1..2)]) - | q133 : int(1..2)]) - /\ - and([b_PartitionOccurrence_WhichPart[q137] = q87 -> - or([a_PartitionOccurrence_WhichPart[q139] = q130 /\ q139 = q137 | q139 : int(1..2)]) - | q137 : int(1..2)])) - | q130 : int(1..2)])) - = - toInt(or([q90 <= b_PartitionOccurrence_NumParts /\ - (and([b_PartitionOccurrence_WhichPart[q93] = q90 -> - or([b_PartitionOccurrence_WhichPart[q95] = q87 /\ q95 = q93 | q95 : int(1..2)]) - | q93 : int(1..2)]) - /\ - and([b_PartitionOccurrence_WhichPart[q97] = q87 -> - or([b_PartitionOccurrence_WhichPart[q99] = q90 /\ q99 = q97 | q99 : int(1..2)]) - | q97 : int(1..2)])) - | q90 : int(1..2)])) - | q87 : int(1..2)]))) - | q23 : int(1..2)]) - \/ - or([q162 <= b_PartitionOccurrence_NumParts /\ - !or([q302 <= a_PartitionOccurrence_NumParts /\ - (and([a_PartitionOccurrence_WhichPart[q305] = q302 -> - or([b_PartitionOccurrence_WhichPart[q307] = q162 /\ q307 = q305 | q307 : int(1..2)]) - | q305 : int(1..2)]) - /\ - and([b_PartitionOccurrence_WhichPart[q309] = q162 -> - or([a_PartitionOccurrence_WhichPart[q311] = q302 /\ q311 = q309 | q311 : int(1..2)]) - | q309 : int(1..2)])) - | q302 : int(1..2)]) - /\ - (toInt(or([q291 <= a_PartitionOccurrence_NumParts /\ - (and([a_PartitionOccurrence_WhichPart[q294] = q291 -> - or([b_PartitionOccurrence_WhichPart[q296] = q162 /\ q296 = q294 | q296 : int(1..2)]) - | q294 : int(1..2)]) - /\ - and([b_PartitionOccurrence_WhichPart[q298] = q162 -> - or([a_PartitionOccurrence_WhichPart[q300] = q291 /\ q300 = q298 | q300 : int(1..2)]) - | q298 : int(1..2)])) - | q291 : int(1..2)])) - < - toInt(or([q165 <= b_PartitionOccurrence_NumParts /\ - (and([b_PartitionOccurrence_WhichPart[q168] = q165 -> - or([b_PartitionOccurrence_WhichPart[q170] = q162 /\ q170 = q168 | q170 : int(1..2)]) - | q168 : int(1..2)]) - /\ - and([b_PartitionOccurrence_WhichPart[q172] = q162 -> - or([b_PartitionOccurrence_WhichPart[q174] = q165 /\ q174 = q172 | q174 : int(1..2)]) - | q172 : int(1..2)])) - | q165 : int(1..2)])) - /\ - (and([q195 <= a_PartitionOccurrence_NumParts /\ - (or([a_PartitionOccurrence_WhichPart[q216] = q195 /\ - (toInt(or([a_PartitionOccurrence_WhichPart[q209] = q195 /\ q209 = q216 | q209 : int(1..2)])) < - sum([toInt(b_PartitionOccurrence_WhichPart[q188] = q162) * catchUndef(toInt(q188 = q216), 0) - | q188 : int(1..2)]) - /\ - (and([a_PartitionOccurrence_WhichPart[q212] = q195 -> - toInt(or([a_PartitionOccurrence_WhichPart[q211] = q195 /\ q211 = q212 | q211 : int(1..2)])) = - sum([toInt(b_PartitionOccurrence_WhichPart[q194] = q162) * catchUndef(toInt(q194 = q212), 0) - | q194 : int(1..2)]) - | q212 : int(1..2), q212 < q216]) - /\ - and([!or([a_PartitionOccurrence_WhichPart[q215] = q195 /\ q215 = q189 | q215 : int(1..2)]) -> - (b_PartitionOccurrence_WhichPart[q189] = q162 -> - toInt(or([a_PartitionOccurrence_WhichPart[q214] = q195 /\ q214 = q189 | q214 : int(1..2)])) - = - sum([toInt(b_PartitionOccurrence_WhichPart[q191] = q162) * catchUndef(toInt(q191 = q189), 0) - | q191 : int(1..2)])) - | q189 : int(1..2), q189 < q216]))) - | q216 : int(1..2)]) - \/ - or([!or([a_PartitionOccurrence_WhichPart[q225] = q195 /\ q225 = q177 | q225 : int(1..2)]) /\ - (b_PartitionOccurrence_WhichPart[q177] = q162 /\ - (toInt(or([a_PartitionOccurrence_WhichPart[q218] = q195 /\ q218 = q177 | q218 : int(1..2)])) < - sum([toInt(b_PartitionOccurrence_WhichPart[q179] = q162) * catchUndef(toInt(q179 = q177), 0) - | q179 : int(1..2)]) - /\ - (and([a_PartitionOccurrence_WhichPart[q221] = q195 -> - toInt(or([a_PartitionOccurrence_WhichPart[q220] = q195 /\ q220 = q221 | q220 : int(1..2)])) - = - sum([toInt(b_PartitionOccurrence_WhichPart[q185] = q162) * catchUndef(toInt(q185 = q221), 0) - | q185 : int(1..2)]) - | q221 : int(1..2), q221 < q177]) - /\ - and([!or([a_PartitionOccurrence_WhichPart[q224] = q195 /\ q224 = q180 | q224 : int(1..2)]) -> - (b_PartitionOccurrence_WhichPart[q180] = q162 -> - toInt(or([a_PartitionOccurrence_WhichPart[q223] = q195 /\ q223 = q180 | q223 : int(1..2)])) - = - sum([toInt(b_PartitionOccurrence_WhichPart[q182] = q162) * - catchUndef(toInt(q182 = q180), 0) - | q182 : int(1..2)])) - | q180 : int(1..2), q180 < q177])))) - | q177 : int(1..2)])) - -> - toInt(or([q280 <= a_PartitionOccurrence_NumParts /\ - (and([a_PartitionOccurrence_WhichPart[q283] = q280 -> - or([a_PartitionOccurrence_WhichPart[q285] = q195 /\ q285 = q283 | q285 : int(1..2)]) - | q283 : int(1..2)]) - /\ - and([a_PartitionOccurrence_WhichPart[q287] = q195 -> - or([a_PartitionOccurrence_WhichPart[q289] = q280 /\ q289 = q287 | q289 : int(1..2)]) - | q287 : int(1..2)])) - | q280 : int(1..2)])) - = - toInt(or([q198 <= b_PartitionOccurrence_NumParts /\ - (and([b_PartitionOccurrence_WhichPart[q201] = q198 -> - or([a_PartitionOccurrence_WhichPart[q203] = q195 /\ q203 = q201 | q203 : int(1..2)]) - | q201 : int(1..2)]) - /\ - and([a_PartitionOccurrence_WhichPart[q205] = q195 -> - or([b_PartitionOccurrence_WhichPart[q207] = q198 /\ q207 = q205 | q207 : int(1..2)]) - | q205 : int(1..2)])) - | q198 : int(1..2)])) - | q195 : int(1..2)]) - /\ - and([and([q226 <= b_PartitionOccurrence_NumParts, - !or([q240 <= a_PartitionOccurrence_NumParts /\ - (and([a_PartitionOccurrence_WhichPart[q243] = q240 -> - or([b_PartitionOccurrence_WhichPart[q245] = q226 /\ q245 = q243 | q245 : int(1..2)]) - | q243 : int(1..2)]) - /\ - and([b_PartitionOccurrence_WhichPart[q247] = q226 -> - or([a_PartitionOccurrence_WhichPart[q249] = q240 /\ q249 = q247 | q249 : int(1..2)]) - | q247 : int(1..2)])) - | q240 : int(1..2)]), - or([b_PartitionOccurrence_WhichPart[q258] = q226 /\ - (toInt(or([b_PartitionOccurrence_WhichPart[q251] = q226 /\ q251 = q258 | q251 : int(1..2)])) < - sum([toInt(b_PartitionOccurrence_WhichPart[q188] = q162) * catchUndef(toInt(q188 = q258), 0) - | q188 : int(1..2)]) - /\ - (and([b_PartitionOccurrence_WhichPart[q254] = q226 -> - toInt(or([b_PartitionOccurrence_WhichPart[q253] = q226 /\ q253 = q254 - | q253 : int(1..2)])) - = - sum([toInt(b_PartitionOccurrence_WhichPart[q194] = q162) * - catchUndef(toInt(q194 = q254), 0) - | q194 : int(1..2)]) - | q254 : int(1..2), q254 < q258]) - /\ - and([!or([b_PartitionOccurrence_WhichPart[q257] = q226 /\ q257 = q189 | q257 : int(1..2)]) -> - (b_PartitionOccurrence_WhichPart[q189] = q162 -> - toInt(or([b_PartitionOccurrence_WhichPart[q256] = q226 /\ q256 = q189 - | q256 : int(1..2)])) - = - sum([toInt(b_PartitionOccurrence_WhichPart[q191] = q162) * - catchUndef(toInt(q191 = q189), 0) - | q191 : int(1..2)])) - | q189 : int(1..2), q189 < q258]))) - | q258 : int(1..2)]) - \/ - or([!or([b_PartitionOccurrence_WhichPart[q267] = q226 /\ q267 = q177 | q267 : int(1..2)]) /\ - (b_PartitionOccurrence_WhichPart[q177] = q162 /\ - (toInt(or([b_PartitionOccurrence_WhichPart[q260] = q226 /\ q260 = q177 | q260 : int(1..2)])) < - sum([toInt(b_PartitionOccurrence_WhichPart[q179] = q162) * catchUndef(toInt(q179 = q177), 0) - | q179 : int(1..2)]) - /\ - (and([b_PartitionOccurrence_WhichPart[q263] = q226 -> - toInt(or([b_PartitionOccurrence_WhichPart[q262] = q226 /\ q262 = q263 - | q262 : int(1..2)])) - = - sum([toInt(b_PartitionOccurrence_WhichPart[q185] = q162) * - catchUndef(toInt(q185 = q263), 0) - | q185 : int(1..2)]) - | q263 : int(1..2), q263 < q177]) - /\ - and([!or([b_PartitionOccurrence_WhichPart[q266] = q226 /\ q266 = q180 | q266 : int(1..2)]) -> - (b_PartitionOccurrence_WhichPart[q180] = q162 -> - toInt(or([b_PartitionOccurrence_WhichPart[q265] = q226 /\ q265 = q180 - | q265 : int(1..2)])) - = - sum([toInt(b_PartitionOccurrence_WhichPart[q182] = q162) * - catchUndef(toInt(q182 = q180), 0) - | q182 : int(1..2)])) - | q180 : int(1..2), q180 < q177])))) - | q177 : int(1..2)]); - int(1..3)]) - -> - toInt(or([q269 <= a_PartitionOccurrence_NumParts /\ - (and([a_PartitionOccurrence_WhichPart[q272] = q269 -> - or([b_PartitionOccurrence_WhichPart[q274] = q226 /\ q274 = q272 | q274 : int(1..2)]) - | q272 : int(1..2)]) - /\ - and([b_PartitionOccurrence_WhichPart[q276] = q226 -> - or([a_PartitionOccurrence_WhichPart[q278] = q269 /\ q278 = q276 | q278 : int(1..2)]) - | q276 : int(1..2)])) - | q269 : int(1..2)])) - = - toInt(or([q229 <= b_PartitionOccurrence_NumParts /\ - (and([b_PartitionOccurrence_WhichPart[q232] = q229 -> - or([b_PartitionOccurrence_WhichPart[q234] = q226 /\ q234 = q232 | q234 : int(1..2)]) - | q232 : int(1..2)]) - /\ - and([b_PartitionOccurrence_WhichPart[q236] = q226 -> - or([b_PartitionOccurrence_WhichPart[q238] = q229 /\ q238 = q236 | q238 : int(1..2)]) - | q236 : int(1..2)])) - | q229 : int(1..2)])) - | q226 : int(1..2)]))) - | q162 : int(1..2)]), - and([q1 <= a_PartitionOccurrence_NumParts -> a_PartitionOccurrence_PartSizes[q1] <= 2 | q1 : int(1..2)]), - and([q1 > a_PartitionOccurrence_NumParts -> a_PartitionOccurrence_PartSizes[q1] = 0 | q1 : int(1..2)]), - a_PartitionOccurrence_NumParts <= 2, - a_PartitionOccurrence_NumParts = max([a_PartitionOccurrence_WhichPart[q4] | q4 : int(1..2)]), - and([a_PartitionOccurrence_PartSizes[q5] = sum([toInt(a_PartitionOccurrence_WhichPart[q6] = q5) | q6 : int(1..2)]) - | q5 : int(1..2)]), - and([q7 <= a_PartitionOccurrence_NumParts -> - and([a_PartitionOccurrence_WhichPart[q8] = q7 -> a_PartitionOccurrence_FirstIndex[q7] <= q8 | q8 : int(1..2)]) - | q7 : int(1..2)]), - and([q7 <= a_PartitionOccurrence_NumParts -> - or([a_PartitionOccurrence_WhichPart[q8] = q7 /\ a_PartitionOccurrence_FirstIndex[q7] = q8 | q8 : int(1..2)]) - | q7 : int(1..2)]), - and([q7 > a_PartitionOccurrence_NumParts -> a_PartitionOccurrence_FirstIndex[q7] = 1 | q7 : int(1..2)]), - and([q9 <= a_PartitionOccurrence_NumParts /\ q10 <= a_PartitionOccurrence_NumParts -> - (q9 < q10 <-> a_PartitionOccurrence_FirstIndex[q9] < a_PartitionOccurrence_FirstIndex[q10]) - | q9 : int(1..2), q10 : int(1..2)]), - and([q11 <= b_PartitionOccurrence_NumParts -> b_PartitionOccurrence_PartSizes[q11] <= 2 | q11 : int(1..2)]), - and([q11 > b_PartitionOccurrence_NumParts -> b_PartitionOccurrence_PartSizes[q11] = 0 | q11 : int(1..2)]), - b_PartitionOccurrence_NumParts <= 2, - b_PartitionOccurrence_NumParts = max([b_PartitionOccurrence_WhichPart[q14] | q14 : int(1..2)]), - and([b_PartitionOccurrence_PartSizes[q15] = - sum([toInt(b_PartitionOccurrence_WhichPart[q16] = q15) | q16 : int(1..2)]) - | q15 : int(1..2)]), - and([q17 <= b_PartitionOccurrence_NumParts -> - and([b_PartitionOccurrence_WhichPart[q18] = q17 -> b_PartitionOccurrence_FirstIndex[q17] <= q18 - | q18 : int(1..2)]) - | q17 : int(1..2)]), - and([q17 <= b_PartitionOccurrence_NumParts -> - or([b_PartitionOccurrence_WhichPart[q18] = q17 /\ b_PartitionOccurrence_FirstIndex[q17] = q18 - | q18 : int(1..2)]) - | q17 : int(1..2)]), - and([q17 > b_PartitionOccurrence_NumParts -> b_PartitionOccurrence_FirstIndex[q17] = 1 | q17 : int(1..2)]), - and([q19 <= b_PartitionOccurrence_NumParts /\ q20 <= b_PartitionOccurrence_NumParts -> - (q19 < q20 <-> b_PartitionOccurrence_FirstIndex[q19] < b_PartitionOccurrence_FirstIndex[q20]) - | q19 : int(1..2), q20 : int(1..2)]) - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000001.solution deleted file mode 100644 index 9b50bb2ed2..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000001.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting a be relation() -letting b be relation((2, true)) -$ Visualisation for b -$ 2 T - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000002.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000002.solution deleted file mode 100644 index e05e181325..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000002.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting a be relation() -letting b be relation((2, false)) -$ Visualisation for b -$ 2 _ - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000003.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000003.solution deleted file mode 100644 index a14764841f..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000003.solution +++ /dev/null @@ -1,8 +0,0 @@ -language Essence 1.3 - -letting a be relation() -letting b be relation((2, false), (2, true)) -$ Visualisation for b -$ 2 _ -$ 2 T - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000004.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000004.solution deleted file mode 100644 index 2d2025d4dc..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000004.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting a be relation() -letting b be relation((1, true)) -$ Visualisation for b -$ 1 T - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000005.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000005.solution deleted file mode 100644 index 9e94a7fc99..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000005.solution +++ /dev/null @@ -1,8 +0,0 @@ -language Essence 1.3 - -letting a be relation() -letting b be relation((1, true), (2, true)) -$ Visualisation for b -$ 1 T -$ 2 T - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000006.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000006.solution deleted file mode 100644 index a23fdb9592..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000006.solution +++ /dev/null @@ -1,8 +0,0 @@ -language Essence 1.3 - -letting a be relation() -letting b be relation((1, true), (2, false)) -$ Visualisation for b -$ 1 T -$ 2 _ - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000007.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000007.solution deleted file mode 100644 index c6e284fe39..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000007.solution +++ /dev/null @@ -1,9 +0,0 @@ -language Essence 1.3 - -letting a be relation() -letting b be relation((1, true), (2, false), (2, true)) -$ Visualisation for b -$ 1 T -$ 2 _ -$ 2 T - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000008.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000008.solution deleted file mode 100644 index b9ac1ab260..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000008.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -letting a be relation() -letting b be relation((1, false)) -$ Visualisation for b -$ 1 _ - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000009.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000009.solution deleted file mode 100644 index 4c3b9b516b..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000009.solution +++ /dev/null @@ -1,8 +0,0 @@ -language Essence 1.3 - -letting a be relation() -letting b be relation((1, false), (2, true)) -$ Visualisation for b -$ 1 _ -$ 2 T - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000010.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000010.solution deleted file mode 100644 index 390eb51d64..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000010.solution +++ /dev/null @@ -1,8 +0,0 @@ -language Essence 1.3 - -letting a be relation() -letting b be relation((1, false), (2, false)) -$ Visualisation for b -$ 1 _ -$ 2 _ - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000011.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000011.solution deleted file mode 100644 index 5f6b5bb3eb..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000011.solution +++ /dev/null @@ -1,9 +0,0 @@ -language Essence 1.3 - -letting a be relation() -letting b be relation((1, false), (2, false), (2, true)) -$ Visualisation for b -$ 1 _ -$ 2 _ -$ 2 T - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000012.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000012.solution deleted file mode 100644 index 96b3f7a61d..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000012.solution +++ /dev/null @@ -1,8 +0,0 @@ -language Essence 1.3 - -letting a be relation() -letting b be relation((1, false), (1, true)) -$ Visualisation for b -$ 1 _ -$ 1 T - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000013.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000013.solution deleted file mode 100644 index 7c1b31979c..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000013.solution +++ /dev/null @@ -1,9 +0,0 @@ -language Essence 1.3 - -letting a be relation() -letting b be relation((1, false), (1, true), (2, true)) -$ Visualisation for b -$ 1 _ -$ 1 T -$ 2 T - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000014.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000014.solution deleted file mode 100644 index df3bcc7d19..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000014.solution +++ /dev/null @@ -1,9 +0,0 @@ -language Essence 1.3 - -letting a be relation() -letting b be relation((1, false), (1, true), (2, false)) -$ Visualisation for b -$ 1 _ -$ 1 T -$ 2 _ - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000015.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000015.solution deleted file mode 100644 index 57c4c4d4cc..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000015.solution +++ /dev/null @@ -1,10 +0,0 @@ -language Essence 1.3 - -letting a be relation() -letting b be relation((1, false), (1, true), (2, false), (2, true)) -$ Visualisation for b -$ 1 _ -$ 1 T -$ 2 _ -$ 2 T - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000016.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000016.solution deleted file mode 100644 index d6c83fac87..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000016.solution +++ /dev/null @@ -1,10 +0,0 @@ -language Essence 1.3 - -letting a be relation((2, true)) -$ Visualisation for a -$ 2 T - -letting b be relation((2, false)) -$ Visualisation for b -$ 2 _ - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000017.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000017.solution deleted file mode 100644 index 2e03b77f68..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000017.solution +++ /dev/null @@ -1,11 +0,0 @@ -language Essence 1.3 - -letting a be relation((2, true)) -$ Visualisation for a -$ 2 T - -letting b be relation((2, false), (2, true)) -$ Visualisation for b -$ 2 _ -$ 2 T - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000018.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000018.solution deleted file mode 100644 index 5a8a614393..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000018.solution +++ /dev/null @@ -1,10 +0,0 @@ -language Essence 1.3 - -letting a be relation((2, true)) -$ Visualisation for a -$ 2 T - -letting b be relation((1, true)) -$ Visualisation for b -$ 1 T - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000019.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000019.solution deleted file mode 100644 index 827334e801..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000019.solution +++ /dev/null @@ -1,11 +0,0 @@ -language Essence 1.3 - -letting a be relation((2, true)) -$ Visualisation for a -$ 2 T - -letting b be relation((1, true), (2, true)) -$ Visualisation for b -$ 1 T -$ 2 T - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000020.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000020.solution deleted file mode 100644 index ff0da926b6..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000020.solution +++ /dev/null @@ -1,11 +0,0 @@ -language Essence 1.3 - -letting a be relation((2, true)) -$ Visualisation for a -$ 2 T - -letting b be relation((1, true), (2, false)) -$ Visualisation for b -$ 1 T -$ 2 _ - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000021.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000021.solution deleted file mode 100644 index 6e71bd9351..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000021.solution +++ /dev/null @@ -1,12 +0,0 @@ -language Essence 1.3 - -letting a be relation((2, true)) -$ Visualisation for a -$ 2 T - -letting b be relation((1, true), (2, false), (2, true)) -$ Visualisation for b -$ 1 T -$ 2 _ -$ 2 T - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000022.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000022.solution deleted file mode 100644 index 632f76f414..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000022.solution +++ /dev/null @@ -1,10 +0,0 @@ -language Essence 1.3 - -letting a be relation((2, true)) -$ Visualisation for a -$ 2 T - -letting b be relation((1, false)) -$ Visualisation for b -$ 1 _ - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000023.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000023.solution deleted file mode 100644 index 59e96b0a9d..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000023.solution +++ /dev/null @@ -1,11 +0,0 @@ -language Essence 1.3 - -letting a be relation((2, true)) -$ Visualisation for a -$ 2 T - -letting b be relation((1, false), (2, true)) -$ Visualisation for b -$ 1 _ -$ 2 T - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000024.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000024.solution deleted file mode 100644 index cb604edb99..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000024.solution +++ /dev/null @@ -1,11 +0,0 @@ -language Essence 1.3 - -letting a be relation((2, true)) -$ Visualisation for a -$ 2 T - -letting b be relation((1, false), (2, false)) -$ Visualisation for b -$ 1 _ -$ 2 _ - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000025.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000025.solution deleted file mode 100644 index b5fdc4c3d5..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000025.solution +++ /dev/null @@ -1,12 +0,0 @@ -language Essence 1.3 - -letting a be relation((2, true)) -$ Visualisation for a -$ 2 T - -letting b be relation((1, false), (2, false), (2, true)) -$ Visualisation for b -$ 1 _ -$ 2 _ -$ 2 T - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000026.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000026.solution deleted file mode 100644 index 73274c8b53..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000026.solution +++ /dev/null @@ -1,11 +0,0 @@ -language Essence 1.3 - -letting a be relation((2, true)) -$ Visualisation for a -$ 2 T - -letting b be relation((1, false), (1, true)) -$ Visualisation for b -$ 1 _ -$ 1 T - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000027.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000027.solution deleted file mode 100644 index 740843554e..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000027.solution +++ /dev/null @@ -1,12 +0,0 @@ -language Essence 1.3 - -letting a be relation((2, true)) -$ Visualisation for a -$ 2 T - -letting b be relation((1, false), (1, true), (2, true)) -$ Visualisation for b -$ 1 _ -$ 1 T -$ 2 T - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000028.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000028.solution deleted file mode 100644 index 29f3289516..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000028.solution +++ /dev/null @@ -1,12 +0,0 @@ -language Essence 1.3 - -letting a be relation((2, true)) -$ Visualisation for a -$ 2 T - -letting b be relation((1, false), (1, true), (2, false)) -$ Visualisation for b -$ 1 _ -$ 1 T -$ 2 _ - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000029.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000029.solution deleted file mode 100644 index fdeebbf013..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000029.solution +++ /dev/null @@ -1,13 +0,0 @@ -language Essence 1.3 - -letting a be relation((2, true)) -$ Visualisation for a -$ 2 T - -letting b be relation((1, false), (1, true), (2, false), (2, true)) -$ Visualisation for b -$ 1 _ -$ 1 T -$ 2 _ -$ 2 T - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000030.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000030.solution deleted file mode 100644 index eaccbb5373..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000030.solution +++ /dev/null @@ -1,11 +0,0 @@ -language Essence 1.3 - -letting a be relation((2, false)) -$ Visualisation for a -$ 2 _ - -letting b be relation((2, false), (2, true)) -$ Visualisation for b -$ 2 _ -$ 2 T - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000031.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000031.solution deleted file mode 100644 index 3eaa95be98..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000031.solution +++ /dev/null @@ -1,10 +0,0 @@ -language Essence 1.3 - -letting a be relation((2, false)) -$ Visualisation for a -$ 2 _ - -letting b be relation((1, true)) -$ Visualisation for b -$ 1 T - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000032.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000032.solution deleted file mode 100644 index d5abbfe57c..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000032.solution +++ /dev/null @@ -1,11 +0,0 @@ -language Essence 1.3 - -letting a be relation((2, false)) -$ Visualisation for a -$ 2 _ - -letting b be relation((1, true), (2, true)) -$ Visualisation for b -$ 1 T -$ 2 T - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000033.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000033.solution deleted file mode 100644 index d9f72172e5..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000033.solution +++ /dev/null @@ -1,11 +0,0 @@ -language Essence 1.3 - -letting a be relation((2, false)) -$ Visualisation for a -$ 2 _ - -letting b be relation((1, true), (2, false)) -$ Visualisation for b -$ 1 T -$ 2 _ - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000034.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000034.solution deleted file mode 100644 index 57c910c0e2..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000034.solution +++ /dev/null @@ -1,12 +0,0 @@ -language Essence 1.3 - -letting a be relation((2, false)) -$ Visualisation for a -$ 2 _ - -letting b be relation((1, true), (2, false), (2, true)) -$ Visualisation for b -$ 1 T -$ 2 _ -$ 2 T - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000035.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000035.solution deleted file mode 100644 index 24b2054619..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000035.solution +++ /dev/null @@ -1,10 +0,0 @@ -language Essence 1.3 - -letting a be relation((2, false)) -$ Visualisation for a -$ 2 _ - -letting b be relation((1, false)) -$ Visualisation for b -$ 1 _ - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000036.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000036.solution deleted file mode 100644 index bef7f6af5e..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000036.solution +++ /dev/null @@ -1,11 +0,0 @@ -language Essence 1.3 - -letting a be relation((2, false)) -$ Visualisation for a -$ 2 _ - -letting b be relation((1, false), (2, true)) -$ Visualisation for b -$ 1 _ -$ 2 T - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000037.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000037.solution deleted file mode 100644 index 03d588c94a..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000037.solution +++ /dev/null @@ -1,11 +0,0 @@ -language Essence 1.3 - -letting a be relation((2, false)) -$ Visualisation for a -$ 2 _ - -letting b be relation((1, false), (2, false)) -$ Visualisation for b -$ 1 _ -$ 2 _ - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000038.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000038.solution deleted file mode 100644 index 0cee2c9e7b..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000038.solution +++ /dev/null @@ -1,12 +0,0 @@ -language Essence 1.3 - -letting a be relation((2, false)) -$ Visualisation for a -$ 2 _ - -letting b be relation((1, false), (2, false), (2, true)) -$ Visualisation for b -$ 1 _ -$ 2 _ -$ 2 T - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000039.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000039.solution deleted file mode 100644 index 886c2f905b..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000039.solution +++ /dev/null @@ -1,11 +0,0 @@ -language Essence 1.3 - -letting a be relation((2, false)) -$ Visualisation for a -$ 2 _ - -letting b be relation((1, false), (1, true)) -$ Visualisation for b -$ 1 _ -$ 1 T - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000040.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000040.solution deleted file mode 100644 index 769d0184ce..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000040.solution +++ /dev/null @@ -1,12 +0,0 @@ -language Essence 1.3 - -letting a be relation((2, false)) -$ Visualisation for a -$ 2 _ - -letting b be relation((1, false), (1, true), (2, true)) -$ Visualisation for b -$ 1 _ -$ 1 T -$ 2 T - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000041.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000041.solution deleted file mode 100644 index 5f5262aec4..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000041.solution +++ /dev/null @@ -1,12 +0,0 @@ -language Essence 1.3 - -letting a be relation((2, false)) -$ Visualisation for a -$ 2 _ - -letting b be relation((1, false), (1, true), (2, false)) -$ Visualisation for b -$ 1 _ -$ 1 T -$ 2 _ - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000042.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000042.solution deleted file mode 100644 index 11990b806d..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000042.solution +++ /dev/null @@ -1,13 +0,0 @@ -language Essence 1.3 - -letting a be relation((2, false)) -$ Visualisation for a -$ 2 _ - -letting b be relation((1, false), (1, true), (2, false), (2, true)) -$ Visualisation for b -$ 1 _ -$ 1 T -$ 2 _ -$ 2 T - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000043.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000043.solution deleted file mode 100644 index aacbe14a36..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000043.solution +++ /dev/null @@ -1,11 +0,0 @@ -language Essence 1.3 - -letting a be relation((2, false), (2, true)) -$ Visualisation for a -$ 2 _ -$ 2 T - -letting b be relation((1, true)) -$ Visualisation for b -$ 1 T - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000044.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000044.solution deleted file mode 100644 index b15348099a..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000044.solution +++ /dev/null @@ -1,12 +0,0 @@ -language Essence 1.3 - -letting a be relation((2, false), (2, true)) -$ Visualisation for a -$ 2 _ -$ 2 T - -letting b be relation((1, true), (2, true)) -$ Visualisation for b -$ 1 T -$ 2 T - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000045.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000045.solution deleted file mode 100644 index 3b8561efe4..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000045.solution +++ /dev/null @@ -1,12 +0,0 @@ -language Essence 1.3 - -letting a be relation((2, false), (2, true)) -$ Visualisation for a -$ 2 _ -$ 2 T - -letting b be relation((1, true), (2, false)) -$ Visualisation for b -$ 1 T -$ 2 _ - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000046.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000046.solution deleted file mode 100644 index c8c72a43bf..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000046.solution +++ /dev/null @@ -1,13 +0,0 @@ -language Essence 1.3 - -letting a be relation((2, false), (2, true)) -$ Visualisation for a -$ 2 _ -$ 2 T - -letting b be relation((1, true), (2, false), (2, true)) -$ Visualisation for b -$ 1 T -$ 2 _ -$ 2 T - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000047.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000047.solution deleted file mode 100644 index 1e024d6569..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000047.solution +++ /dev/null @@ -1,11 +0,0 @@ -language Essence 1.3 - -letting a be relation((2, false), (2, true)) -$ Visualisation for a -$ 2 _ -$ 2 T - -letting b be relation((1, false)) -$ Visualisation for b -$ 1 _ - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000048.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000048.solution deleted file mode 100644 index 689794b9e5..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000048.solution +++ /dev/null @@ -1,12 +0,0 @@ -language Essence 1.3 - -letting a be relation((2, false), (2, true)) -$ Visualisation for a -$ 2 _ -$ 2 T - -letting b be relation((1, false), (2, true)) -$ Visualisation for b -$ 1 _ -$ 2 T - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000049.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000049.solution deleted file mode 100644 index d53edacbed..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000049.solution +++ /dev/null @@ -1,12 +0,0 @@ -language Essence 1.3 - -letting a be relation((2, false), (2, true)) -$ Visualisation for a -$ 2 _ -$ 2 T - -letting b be relation((1, false), (2, false)) -$ Visualisation for b -$ 1 _ -$ 2 _ - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000050.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000050.solution deleted file mode 100644 index 2ffb1e0713..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000050.solution +++ /dev/null @@ -1,13 +0,0 @@ -language Essence 1.3 - -letting a be relation((2, false), (2, true)) -$ Visualisation for a -$ 2 _ -$ 2 T - -letting b be relation((1, false), (2, false), (2, true)) -$ Visualisation for b -$ 1 _ -$ 2 _ -$ 2 T - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000051.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000051.solution deleted file mode 100644 index 45ae15ca2f..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000051.solution +++ /dev/null @@ -1,12 +0,0 @@ -language Essence 1.3 - -letting a be relation((2, false), (2, true)) -$ Visualisation for a -$ 2 _ -$ 2 T - -letting b be relation((1, false), (1, true)) -$ Visualisation for b -$ 1 _ -$ 1 T - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000052.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000052.solution deleted file mode 100644 index e34aca5265..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000052.solution +++ /dev/null @@ -1,13 +0,0 @@ -language Essence 1.3 - -letting a be relation((2, false), (2, true)) -$ Visualisation for a -$ 2 _ -$ 2 T - -letting b be relation((1, false), (1, true), (2, true)) -$ Visualisation for b -$ 1 _ -$ 1 T -$ 2 T - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000053.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000053.solution deleted file mode 100644 index 0650195dfa..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000053.solution +++ /dev/null @@ -1,13 +0,0 @@ -language Essence 1.3 - -letting a be relation((2, false), (2, true)) -$ Visualisation for a -$ 2 _ -$ 2 T - -letting b be relation((1, false), (1, true), (2, false)) -$ Visualisation for b -$ 1 _ -$ 1 T -$ 2 _ - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000054.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000054.solution deleted file mode 100644 index d005ee72f3..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000054.solution +++ /dev/null @@ -1,14 +0,0 @@ -language Essence 1.3 - -letting a be relation((2, false), (2, true)) -$ Visualisation for a -$ 2 _ -$ 2 T - -letting b be relation((1, false), (1, true), (2, false), (2, true)) -$ Visualisation for b -$ 1 _ -$ 1 T -$ 2 _ -$ 2 T - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000055.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000055.solution deleted file mode 100644 index b97e565a71..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000055.solution +++ /dev/null @@ -1,11 +0,0 @@ -language Essence 1.3 - -letting a be relation((1, true)) -$ Visualisation for a -$ 1 T - -letting b be relation((1, true), (2, true)) -$ Visualisation for b -$ 1 T -$ 2 T - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000056.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000056.solution deleted file mode 100644 index 1c2c273c2b..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000056.solution +++ /dev/null @@ -1,11 +0,0 @@ -language Essence 1.3 - -letting a be relation((1, true)) -$ Visualisation for a -$ 1 T - -letting b be relation((1, true), (2, false)) -$ Visualisation for b -$ 1 T -$ 2 _ - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000057.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000057.solution deleted file mode 100644 index d22929e033..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000057.solution +++ /dev/null @@ -1,12 +0,0 @@ -language Essence 1.3 - -letting a be relation((1, true)) -$ Visualisation for a -$ 1 T - -letting b be relation((1, true), (2, false), (2, true)) -$ Visualisation for b -$ 1 T -$ 2 _ -$ 2 T - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000058.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000058.solution deleted file mode 100644 index 131f4ca60d..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000058.solution +++ /dev/null @@ -1,10 +0,0 @@ -language Essence 1.3 - -letting a be relation((1, true)) -$ Visualisation for a -$ 1 T - -letting b be relation((1, false)) -$ Visualisation for b -$ 1 _ - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000059.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000059.solution deleted file mode 100644 index cdc3c8c342..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000059.solution +++ /dev/null @@ -1,11 +0,0 @@ -language Essence 1.3 - -letting a be relation((1, true)) -$ Visualisation for a -$ 1 T - -letting b be relation((1, false), (2, true)) -$ Visualisation for b -$ 1 _ -$ 2 T - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000060.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000060.solution deleted file mode 100644 index e96d5802a8..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000060.solution +++ /dev/null @@ -1,11 +0,0 @@ -language Essence 1.3 - -letting a be relation((1, true)) -$ Visualisation for a -$ 1 T - -letting b be relation((1, false), (2, false)) -$ Visualisation for b -$ 1 _ -$ 2 _ - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000061.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000061.solution deleted file mode 100644 index bef89da48c..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000061.solution +++ /dev/null @@ -1,12 +0,0 @@ -language Essence 1.3 - -letting a be relation((1, true)) -$ Visualisation for a -$ 1 T - -letting b be relation((1, false), (2, false), (2, true)) -$ Visualisation for b -$ 1 _ -$ 2 _ -$ 2 T - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000062.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000062.solution deleted file mode 100644 index ea0c4dbf09..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000062.solution +++ /dev/null @@ -1,11 +0,0 @@ -language Essence 1.3 - -letting a be relation((1, true)) -$ Visualisation for a -$ 1 T - -letting b be relation((1, false), (1, true)) -$ Visualisation for b -$ 1 _ -$ 1 T - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000063.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000063.solution deleted file mode 100644 index ffe8162de3..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000063.solution +++ /dev/null @@ -1,12 +0,0 @@ -language Essence 1.3 - -letting a be relation((1, true)) -$ Visualisation for a -$ 1 T - -letting b be relation((1, false), (1, true), (2, true)) -$ Visualisation for b -$ 1 _ -$ 1 T -$ 2 T - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000064.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000064.solution deleted file mode 100644 index 40a475eb0a..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000064.solution +++ /dev/null @@ -1,12 +0,0 @@ -language Essence 1.3 - -letting a be relation((1, true)) -$ Visualisation for a -$ 1 T - -letting b be relation((1, false), (1, true), (2, false)) -$ Visualisation for b -$ 1 _ -$ 1 T -$ 2 _ - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000065.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000065.solution deleted file mode 100644 index bb4a540328..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000065.solution +++ /dev/null @@ -1,13 +0,0 @@ -language Essence 1.3 - -letting a be relation((1, true)) -$ Visualisation for a -$ 1 T - -letting b be relation((1, false), (1, true), (2, false), (2, true)) -$ Visualisation for b -$ 1 _ -$ 1 T -$ 2 _ -$ 2 T - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000066.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000066.solution deleted file mode 100644 index a6d6d0a1d9..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000066.solution +++ /dev/null @@ -1,12 +0,0 @@ -language Essence 1.3 - -letting a be relation((1, true), (2, true)) -$ Visualisation for a -$ 1 T -$ 2 T - -letting b be relation((1, true), (2, false)) -$ Visualisation for b -$ 1 T -$ 2 _ - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000067.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000067.solution deleted file mode 100644 index 30730a76db..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000067.solution +++ /dev/null @@ -1,13 +0,0 @@ -language Essence 1.3 - -letting a be relation((1, true), (2, true)) -$ Visualisation for a -$ 1 T -$ 2 T - -letting b be relation((1, true), (2, false), (2, true)) -$ Visualisation for b -$ 1 T -$ 2 _ -$ 2 T - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000068.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000068.solution deleted file mode 100644 index 2bda2ef994..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000068.solution +++ /dev/null @@ -1,11 +0,0 @@ -language Essence 1.3 - -letting a be relation((1, true), (2, true)) -$ Visualisation for a -$ 1 T -$ 2 T - -letting b be relation((1, false)) -$ Visualisation for b -$ 1 _ - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000069.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000069.solution deleted file mode 100644 index edaea295f4..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000069.solution +++ /dev/null @@ -1,12 +0,0 @@ -language Essence 1.3 - -letting a be relation((1, true), (2, true)) -$ Visualisation for a -$ 1 T -$ 2 T - -letting b be relation((1, false), (2, true)) -$ Visualisation for b -$ 1 _ -$ 2 T - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000070.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000070.solution deleted file mode 100644 index e7e730d42e..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000070.solution +++ /dev/null @@ -1,12 +0,0 @@ -language Essence 1.3 - -letting a be relation((1, true), (2, true)) -$ Visualisation for a -$ 1 T -$ 2 T - -letting b be relation((1, false), (2, false)) -$ Visualisation for b -$ 1 _ -$ 2 _ - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000071.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000071.solution deleted file mode 100644 index d35c2856a3..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000071.solution +++ /dev/null @@ -1,13 +0,0 @@ -language Essence 1.3 - -letting a be relation((1, true), (2, true)) -$ Visualisation for a -$ 1 T -$ 2 T - -letting b be relation((1, false), (2, false), (2, true)) -$ Visualisation for b -$ 1 _ -$ 2 _ -$ 2 T - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000072.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000072.solution deleted file mode 100644 index 2cafa9ec51..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000072.solution +++ /dev/null @@ -1,12 +0,0 @@ -language Essence 1.3 - -letting a be relation((1, true), (2, true)) -$ Visualisation for a -$ 1 T -$ 2 T - -letting b be relation((1, false), (1, true)) -$ Visualisation for b -$ 1 _ -$ 1 T - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000073.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000073.solution deleted file mode 100644 index c6c6295627..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000073.solution +++ /dev/null @@ -1,13 +0,0 @@ -language Essence 1.3 - -letting a be relation((1, true), (2, true)) -$ Visualisation for a -$ 1 T -$ 2 T - -letting b be relation((1, false), (1, true), (2, true)) -$ Visualisation for b -$ 1 _ -$ 1 T -$ 2 T - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000074.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000074.solution deleted file mode 100644 index 15d97d4729..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000074.solution +++ /dev/null @@ -1,13 +0,0 @@ -language Essence 1.3 - -letting a be relation((1, true), (2, true)) -$ Visualisation for a -$ 1 T -$ 2 T - -letting b be relation((1, false), (1, true), (2, false)) -$ Visualisation for b -$ 1 _ -$ 1 T -$ 2 _ - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000075.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000075.solution deleted file mode 100644 index 0697674c24..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000075.solution +++ /dev/null @@ -1,14 +0,0 @@ -language Essence 1.3 - -letting a be relation((1, true), (2, true)) -$ Visualisation for a -$ 1 T -$ 2 T - -letting b be relation((1, false), (1, true), (2, false), (2, true)) -$ Visualisation for b -$ 1 _ -$ 1 T -$ 2 _ -$ 2 T - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000076.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000076.solution deleted file mode 100644 index 296759f9b3..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000076.solution +++ /dev/null @@ -1,13 +0,0 @@ -language Essence 1.3 - -letting a be relation((1, true), (2, false)) -$ Visualisation for a -$ 1 T -$ 2 _ - -letting b be relation((1, true), (2, false), (2, true)) -$ Visualisation for b -$ 1 T -$ 2 _ -$ 2 T - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000077.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000077.solution deleted file mode 100644 index 4ea598db58..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000077.solution +++ /dev/null @@ -1,11 +0,0 @@ -language Essence 1.3 - -letting a be relation((1, true), (2, false)) -$ Visualisation for a -$ 1 T -$ 2 _ - -letting b be relation((1, false)) -$ Visualisation for b -$ 1 _ - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000078.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000078.solution deleted file mode 100644 index 0537b5fb9e..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000078.solution +++ /dev/null @@ -1,12 +0,0 @@ -language Essence 1.3 - -letting a be relation((1, true), (2, false)) -$ Visualisation for a -$ 1 T -$ 2 _ - -letting b be relation((1, false), (2, true)) -$ Visualisation for b -$ 1 _ -$ 2 T - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000079.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000079.solution deleted file mode 100644 index cb0d5e93ae..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000079.solution +++ /dev/null @@ -1,12 +0,0 @@ -language Essence 1.3 - -letting a be relation((1, true), (2, false)) -$ Visualisation for a -$ 1 T -$ 2 _ - -letting b be relation((1, false), (2, false)) -$ Visualisation for b -$ 1 _ -$ 2 _ - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000080.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000080.solution deleted file mode 100644 index 71bf1f4226..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000080.solution +++ /dev/null @@ -1,13 +0,0 @@ -language Essence 1.3 - -letting a be relation((1, true), (2, false)) -$ Visualisation for a -$ 1 T -$ 2 _ - -letting b be relation((1, false), (2, false), (2, true)) -$ Visualisation for b -$ 1 _ -$ 2 _ -$ 2 T - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000081.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000081.solution deleted file mode 100644 index 4a56054133..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000081.solution +++ /dev/null @@ -1,12 +0,0 @@ -language Essence 1.3 - -letting a be relation((1, true), (2, false)) -$ Visualisation for a -$ 1 T -$ 2 _ - -letting b be relation((1, false), (1, true)) -$ Visualisation for b -$ 1 _ -$ 1 T - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000082.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000082.solution deleted file mode 100644 index 0afa181179..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000082.solution +++ /dev/null @@ -1,13 +0,0 @@ -language Essence 1.3 - -letting a be relation((1, true), (2, false)) -$ Visualisation for a -$ 1 T -$ 2 _ - -letting b be relation((1, false), (1, true), (2, true)) -$ Visualisation for b -$ 1 _ -$ 1 T -$ 2 T - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000083.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000083.solution deleted file mode 100644 index a556323487..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000083.solution +++ /dev/null @@ -1,13 +0,0 @@ -language Essence 1.3 - -letting a be relation((1, true), (2, false)) -$ Visualisation for a -$ 1 T -$ 2 _ - -letting b be relation((1, false), (1, true), (2, false)) -$ Visualisation for b -$ 1 _ -$ 1 T -$ 2 _ - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000084.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000084.solution deleted file mode 100644 index 847e586971..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000084.solution +++ /dev/null @@ -1,14 +0,0 @@ -language Essence 1.3 - -letting a be relation((1, true), (2, false)) -$ Visualisation for a -$ 1 T -$ 2 _ - -letting b be relation((1, false), (1, true), (2, false), (2, true)) -$ Visualisation for b -$ 1 _ -$ 1 T -$ 2 _ -$ 2 T - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000085.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000085.solution deleted file mode 100644 index 8b71d47ea9..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000085.solution +++ /dev/null @@ -1,12 +0,0 @@ -language Essence 1.3 - -letting a be relation((1, true), (2, false), (2, true)) -$ Visualisation for a -$ 1 T -$ 2 _ -$ 2 T - -letting b be relation((1, false)) -$ Visualisation for b -$ 1 _ - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000086.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000086.solution deleted file mode 100644 index 918b7b8edd..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000086.solution +++ /dev/null @@ -1,13 +0,0 @@ -language Essence 1.3 - -letting a be relation((1, true), (2, false), (2, true)) -$ Visualisation for a -$ 1 T -$ 2 _ -$ 2 T - -letting b be relation((1, false), (2, true)) -$ Visualisation for b -$ 1 _ -$ 2 T - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000087.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000087.solution deleted file mode 100644 index ca6ddd39f8..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000087.solution +++ /dev/null @@ -1,13 +0,0 @@ -language Essence 1.3 - -letting a be relation((1, true), (2, false), (2, true)) -$ Visualisation for a -$ 1 T -$ 2 _ -$ 2 T - -letting b be relation((1, false), (2, false)) -$ Visualisation for b -$ 1 _ -$ 2 _ - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000088.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000088.solution deleted file mode 100644 index dca6353d9f..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000088.solution +++ /dev/null @@ -1,14 +0,0 @@ -language Essence 1.3 - -letting a be relation((1, true), (2, false), (2, true)) -$ Visualisation for a -$ 1 T -$ 2 _ -$ 2 T - -letting b be relation((1, false), (2, false), (2, true)) -$ Visualisation for b -$ 1 _ -$ 2 _ -$ 2 T - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000089.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000089.solution deleted file mode 100644 index 984e3636be..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000089.solution +++ /dev/null @@ -1,13 +0,0 @@ -language Essence 1.3 - -letting a be relation((1, true), (2, false), (2, true)) -$ Visualisation for a -$ 1 T -$ 2 _ -$ 2 T - -letting b be relation((1, false), (1, true)) -$ Visualisation for b -$ 1 _ -$ 1 T - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000090.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000090.solution deleted file mode 100644 index 5b5350f84d..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000090.solution +++ /dev/null @@ -1,14 +0,0 @@ -language Essence 1.3 - -letting a be relation((1, true), (2, false), (2, true)) -$ Visualisation for a -$ 1 T -$ 2 _ -$ 2 T - -letting b be relation((1, false), (1, true), (2, true)) -$ Visualisation for b -$ 1 _ -$ 1 T -$ 2 T - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000091.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000091.solution deleted file mode 100644 index 8c4f2ec1d5..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000091.solution +++ /dev/null @@ -1,14 +0,0 @@ -language Essence 1.3 - -letting a be relation((1, true), (2, false), (2, true)) -$ Visualisation for a -$ 1 T -$ 2 _ -$ 2 T - -letting b be relation((1, false), (1, true), (2, false)) -$ Visualisation for b -$ 1 _ -$ 1 T -$ 2 _ - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000092.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000092.solution deleted file mode 100644 index 3d9f447820..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000092.solution +++ /dev/null @@ -1,15 +0,0 @@ -language Essence 1.3 - -letting a be relation((1, true), (2, false), (2, true)) -$ Visualisation for a -$ 1 T -$ 2 _ -$ 2 T - -letting b be relation((1, false), (1, true), (2, false), (2, true)) -$ Visualisation for b -$ 1 _ -$ 1 T -$ 2 _ -$ 2 T - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000093.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000093.solution deleted file mode 100644 index 20ba97a49b..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000093.solution +++ /dev/null @@ -1,11 +0,0 @@ -language Essence 1.3 - -letting a be relation((1, false)) -$ Visualisation for a -$ 1 _ - -letting b be relation((1, false), (2, true)) -$ Visualisation for b -$ 1 _ -$ 2 T - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000094.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000094.solution deleted file mode 100644 index a6299cb56e..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000094.solution +++ /dev/null @@ -1,11 +0,0 @@ -language Essence 1.3 - -letting a be relation((1, false)) -$ Visualisation for a -$ 1 _ - -letting b be relation((1, false), (2, false)) -$ Visualisation for b -$ 1 _ -$ 2 _ - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000095.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000095.solution deleted file mode 100644 index 68ef4a2d32..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000095.solution +++ /dev/null @@ -1,12 +0,0 @@ -language Essence 1.3 - -letting a be relation((1, false)) -$ Visualisation for a -$ 1 _ - -letting b be relation((1, false), (2, false), (2, true)) -$ Visualisation for b -$ 1 _ -$ 2 _ -$ 2 T - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000096.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000096.solution deleted file mode 100644 index 9191690a29..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000096.solution +++ /dev/null @@ -1,11 +0,0 @@ -language Essence 1.3 - -letting a be relation((1, false)) -$ Visualisation for a -$ 1 _ - -letting b be relation((1, false), (1, true)) -$ Visualisation for b -$ 1 _ -$ 1 T - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000097.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000097.solution deleted file mode 100644 index be125318a4..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000097.solution +++ /dev/null @@ -1,12 +0,0 @@ -language Essence 1.3 - -letting a be relation((1, false)) -$ Visualisation for a -$ 1 _ - -letting b be relation((1, false), (1, true), (2, true)) -$ Visualisation for b -$ 1 _ -$ 1 T -$ 2 T - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000098.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000098.solution deleted file mode 100644 index 3ee2e652e1..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000098.solution +++ /dev/null @@ -1,12 +0,0 @@ -language Essence 1.3 - -letting a be relation((1, false)) -$ Visualisation for a -$ 1 _ - -letting b be relation((1, false), (1, true), (2, false)) -$ Visualisation for b -$ 1 _ -$ 1 T -$ 2 _ - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000099.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000099.solution deleted file mode 100644 index 100fb99ae9..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000099.solution +++ /dev/null @@ -1,13 +0,0 @@ -language Essence 1.3 - -letting a be relation((1, false)) -$ Visualisation for a -$ 1 _ - -letting b be relation((1, false), (1, true), (2, false), (2, true)) -$ Visualisation for b -$ 1 _ -$ 1 T -$ 2 _ -$ 2 T - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000100.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000100.solution deleted file mode 100644 index fe1c124d6b..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000100.solution +++ /dev/null @@ -1,12 +0,0 @@ -language Essence 1.3 - -letting a be relation((1, false), (2, true)) -$ Visualisation for a -$ 1 _ -$ 2 T - -letting b be relation((1, false), (2, false)) -$ Visualisation for b -$ 1 _ -$ 2 _ - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000101.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000101.solution deleted file mode 100644 index 45605841d1..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000101.solution +++ /dev/null @@ -1,13 +0,0 @@ -language Essence 1.3 - -letting a be relation((1, false), (2, true)) -$ Visualisation for a -$ 1 _ -$ 2 T - -letting b be relation((1, false), (2, false), (2, true)) -$ Visualisation for b -$ 1 _ -$ 2 _ -$ 2 T - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000102.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000102.solution deleted file mode 100644 index 5b09524f76..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000102.solution +++ /dev/null @@ -1,12 +0,0 @@ -language Essence 1.3 - -letting a be relation((1, false), (2, true)) -$ Visualisation for a -$ 1 _ -$ 2 T - -letting b be relation((1, false), (1, true)) -$ Visualisation for b -$ 1 _ -$ 1 T - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000103.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000103.solution deleted file mode 100644 index 289bf90bb7..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000103.solution +++ /dev/null @@ -1,13 +0,0 @@ -language Essence 1.3 - -letting a be relation((1, false), (2, true)) -$ Visualisation for a -$ 1 _ -$ 2 T - -letting b be relation((1, false), (1, true), (2, true)) -$ Visualisation for b -$ 1 _ -$ 1 T -$ 2 T - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000104.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000104.solution deleted file mode 100644 index acdc5ef598..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000104.solution +++ /dev/null @@ -1,13 +0,0 @@ -language Essence 1.3 - -letting a be relation((1, false), (2, true)) -$ Visualisation for a -$ 1 _ -$ 2 T - -letting b be relation((1, false), (1, true), (2, false)) -$ Visualisation for b -$ 1 _ -$ 1 T -$ 2 _ - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000105.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000105.solution deleted file mode 100644 index c38106e519..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000105.solution +++ /dev/null @@ -1,14 +0,0 @@ -language Essence 1.3 - -letting a be relation((1, false), (2, true)) -$ Visualisation for a -$ 1 _ -$ 2 T - -letting b be relation((1, false), (1, true), (2, false), (2, true)) -$ Visualisation for b -$ 1 _ -$ 1 T -$ 2 _ -$ 2 T - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000106.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000106.solution deleted file mode 100644 index 4a64f01e99..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000106.solution +++ /dev/null @@ -1,13 +0,0 @@ -language Essence 1.3 - -letting a be relation((1, false), (2, false)) -$ Visualisation for a -$ 1 _ -$ 2 _ - -letting b be relation((1, false), (2, false), (2, true)) -$ Visualisation for b -$ 1 _ -$ 2 _ -$ 2 T - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000107.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000107.solution deleted file mode 100644 index 9ec48a3bc7..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000107.solution +++ /dev/null @@ -1,12 +0,0 @@ -language Essence 1.3 - -letting a be relation((1, false), (2, false)) -$ Visualisation for a -$ 1 _ -$ 2 _ - -letting b be relation((1, false), (1, true)) -$ Visualisation for b -$ 1 _ -$ 1 T - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000108.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000108.solution deleted file mode 100644 index 8531b893a9..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000108.solution +++ /dev/null @@ -1,13 +0,0 @@ -language Essence 1.3 - -letting a be relation((1, false), (2, false)) -$ Visualisation for a -$ 1 _ -$ 2 _ - -letting b be relation((1, false), (1, true), (2, true)) -$ Visualisation for b -$ 1 _ -$ 1 T -$ 2 T - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000109.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000109.solution deleted file mode 100644 index e41a986c0c..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000109.solution +++ /dev/null @@ -1,13 +0,0 @@ -language Essence 1.3 - -letting a be relation((1, false), (2, false)) -$ Visualisation for a -$ 1 _ -$ 2 _ - -letting b be relation((1, false), (1, true), (2, false)) -$ Visualisation for b -$ 1 _ -$ 1 T -$ 2 _ - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000110.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000110.solution deleted file mode 100644 index f39c9292d8..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000110.solution +++ /dev/null @@ -1,14 +0,0 @@ -language Essence 1.3 - -letting a be relation((1, false), (2, false)) -$ Visualisation for a -$ 1 _ -$ 2 _ - -letting b be relation((1, false), (1, true), (2, false), (2, true)) -$ Visualisation for b -$ 1 _ -$ 1 T -$ 2 _ -$ 2 T - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000111.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000111.solution deleted file mode 100644 index 0801593375..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000111.solution +++ /dev/null @@ -1,13 +0,0 @@ -language Essence 1.3 - -letting a be relation((1, false), (2, false), (2, true)) -$ Visualisation for a -$ 1 _ -$ 2 _ -$ 2 T - -letting b be relation((1, false), (1, true)) -$ Visualisation for b -$ 1 _ -$ 1 T - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000112.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000112.solution deleted file mode 100644 index 8604ea0029..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000112.solution +++ /dev/null @@ -1,14 +0,0 @@ -language Essence 1.3 - -letting a be relation((1, false), (2, false), (2, true)) -$ Visualisation for a -$ 1 _ -$ 2 _ -$ 2 T - -letting b be relation((1, false), (1, true), (2, true)) -$ Visualisation for b -$ 1 _ -$ 1 T -$ 2 T - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000113.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000113.solution deleted file mode 100644 index 13ec11e78c..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000113.solution +++ /dev/null @@ -1,14 +0,0 @@ -language Essence 1.3 - -letting a be relation((1, false), (2, false), (2, true)) -$ Visualisation for a -$ 1 _ -$ 2 _ -$ 2 T - -letting b be relation((1, false), (1, true), (2, false)) -$ Visualisation for b -$ 1 _ -$ 1 T -$ 2 _ - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000114.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000114.solution deleted file mode 100644 index 5df1f52cfb..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000114.solution +++ /dev/null @@ -1,15 +0,0 @@ -language Essence 1.3 - -letting a be relation((1, false), (2, false), (2, true)) -$ Visualisation for a -$ 1 _ -$ 2 _ -$ 2 T - -letting b be relation((1, false), (1, true), (2, false), (2, true)) -$ Visualisation for b -$ 1 _ -$ 1 T -$ 2 _ -$ 2 T - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000115.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000115.solution deleted file mode 100644 index 08d44b1cbc..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000115.solution +++ /dev/null @@ -1,13 +0,0 @@ -language Essence 1.3 - -letting a be relation((1, false), (1, true)) -$ Visualisation for a -$ 1 _ -$ 1 T - -letting b be relation((1, false), (1, true), (2, true)) -$ Visualisation for b -$ 1 _ -$ 1 T -$ 2 T - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000116.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000116.solution deleted file mode 100644 index 61c43b3425..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000116.solution +++ /dev/null @@ -1,13 +0,0 @@ -language Essence 1.3 - -letting a be relation((1, false), (1, true)) -$ Visualisation for a -$ 1 _ -$ 1 T - -letting b be relation((1, false), (1, true), (2, false)) -$ Visualisation for b -$ 1 _ -$ 1 T -$ 2 _ - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000117.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000117.solution deleted file mode 100644 index 53b30afee2..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000117.solution +++ /dev/null @@ -1,14 +0,0 @@ -language Essence 1.3 - -letting a be relation((1, false), (1, true)) -$ Visualisation for a -$ 1 _ -$ 1 T - -letting b be relation((1, false), (1, true), (2, false), (2, true)) -$ Visualisation for b -$ 1 _ -$ 1 T -$ 2 _ -$ 2 T - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000118.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000118.solution deleted file mode 100644 index f9f326b9b0..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000118.solution +++ /dev/null @@ -1,14 +0,0 @@ -language Essence 1.3 - -letting a be relation((1, false), (1, true), (2, true)) -$ Visualisation for a -$ 1 _ -$ 1 T -$ 2 T - -letting b be relation((1, false), (1, true), (2, false)) -$ Visualisation for b -$ 1 _ -$ 1 T -$ 2 _ - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000119.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000119.solution deleted file mode 100644 index 1bbce78897..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000119.solution +++ /dev/null @@ -1,15 +0,0 @@ -language Essence 1.3 - -letting a be relation((1, false), (1, true), (2, true)) -$ Visualisation for a -$ 1 _ -$ 1 T -$ 2 T - -letting b be relation((1, false), (1, true), (2, false), (2, true)) -$ Visualisation for b -$ 1 _ -$ 1 T -$ 2 _ -$ 2 T - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000120.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000120.solution deleted file mode 100644 index 0e39505c9e..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000120.solution +++ /dev/null @@ -1,15 +0,0 @@ -language Essence 1.3 - -letting a be relation((1, false), (1, true), (2, false)) -$ Visualisation for a -$ 1 _ -$ 1 T -$ 2 _ - -letting b be relation((1, false), (1, true), (2, false), (2, true)) -$ Visualisation for b -$ 1 _ -$ 1 T -$ 2 _ -$ 2 T - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model.eprime b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model.eprime deleted file mode 100644 index 02a8b92b47..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model.eprime +++ /dev/null @@ -1,62 +0,0 @@ -language ESSENCE' 1.0 - -find a_RelationAsMatrix: matrix indexed by [int(1..2), bool] of bool -find b_RelationAsMatrix: matrix indexed by [int(1..2), bool] of bool -branching on [a_RelationAsMatrix, b_RelationAsMatrix] -such that - or([a_RelationAsMatrix[q7_1, q7_2] /\ - (sum([toInt(a_RelationAsMatrix[q23_1, q23_2]) * catchUndef(toInt(q23_1 = q7_1 /\ q23_2 = q7_2), 0) - | q23_1 : int(1..2), q23_2 : bool]) - < - sum([toInt(b_RelationAsMatrix[q9_1, q9_2]) * catchUndef(toInt(q9_1 = q7_1 /\ q9_2 = q7_2), 0) - | q9_1 : int(1..2), q9_2 : bool]) - /\ - (and([a_RelationAsMatrix[q10_1, q10_2] -> - sum([toInt(a_RelationAsMatrix[q21_1, q21_2]) * catchUndef(toInt(q21_1 = q10_1 /\ q21_2 = q10_2), 0) - | q21_1 : int(1..2), q21_2 : bool]) - = - sum([toInt(b_RelationAsMatrix[q12_1, q12_2]) * catchUndef(toInt(q12_1 = q10_1 /\ q12_2 = q10_2), 0) - | q12_1 : int(1..2), q12_2 : bool]) - | q10_1 : int(1..2), q10_2 : bool, q10_1 < q7_1 \/ q10_1 = q7_1 /\ q10_2 < q7_2]) - /\ - and([b_RelationAsMatrix[q13_1, q13_2] /\ - !or([a_RelationAsMatrix[q17_1, q17_2] /\ (q17_1 = q13_1 /\ q17_2 = q13_2) - | q17_1 : int(1..2), q17_2 : bool]) - -> - sum([toInt(a_RelationAsMatrix[q19_1, q19_2]) * catchUndef(toInt(q19_1 = q13_1 /\ q19_2 = q13_2), 0) - | q19_1 : int(1..2), q19_2 : bool]) - = - sum([toInt(b_RelationAsMatrix[q15_1, q15_2]) * catchUndef(toInt(q15_1 = q13_1 /\ q15_2 = q13_2), 0) - | q15_1 : int(1..2), q15_2 : bool]) - | q13_1 : int(1..2), q13_2 : bool, q13_1 < q7_1 \/ q13_1 = q7_1 /\ q13_2 < q7_2]))) - | q7_1 : int(1..2), q7_2 : bool]) - \/ - or([b_RelationAsMatrix[q24_1, q24_2] /\ - !or([a_RelationAsMatrix[q42_1, q42_2] /\ (q42_1 = q24_1 /\ q42_2 = q24_2) | q42_1 : int(1..2), q42_2 : bool]) - /\ - (sum([toInt(a_RelationAsMatrix[q40_1, q40_2]) * catchUndef(toInt(q40_1 = q24_1 /\ q40_2 = q24_2), 0) - | q40_1 : int(1..2), q40_2 : bool]) - < - sum([toInt(b_RelationAsMatrix[q26_1, q26_2]) * catchUndef(toInt(q26_1 = q24_1 /\ q26_2 = q24_2), 0) - | q26_1 : int(1..2), q26_2 : bool]) - /\ - (and([a_RelationAsMatrix[q27_1, q27_2] -> - sum([toInt(a_RelationAsMatrix[q38_1, q38_2]) * catchUndef(toInt(q38_1 = q27_1 /\ q38_2 = q27_2), 0) - | q38_1 : int(1..2), q38_2 : bool]) - = - sum([toInt(b_RelationAsMatrix[q29_1, q29_2]) * catchUndef(toInt(q29_1 = q27_1 /\ q29_2 = q27_2), 0) - | q29_1 : int(1..2), q29_2 : bool]) - | q27_1 : int(1..2), q27_2 : bool, q27_1 < q24_1 \/ q27_1 = q24_1 /\ q27_2 < q24_2]) - /\ - and([b_RelationAsMatrix[q30_1, q30_2] /\ - !or([a_RelationAsMatrix[q34_1, q34_2] /\ (q34_1 = q30_1 /\ q34_2 = q30_2) - | q34_1 : int(1..2), q34_2 : bool]) - -> - sum([toInt(a_RelationAsMatrix[q36_1, q36_2]) * catchUndef(toInt(q36_1 = q30_1 /\ q36_2 = q30_2), 0) - | q36_1 : int(1..2), q36_2 : bool]) - = - sum([toInt(b_RelationAsMatrix[q32_1, q32_2]) * catchUndef(toInt(q32_1 = q30_1 /\ q32_2 = q30_2), 0) - | q32_1 : int(1..2), q32_2 : bool]) - | q30_1 : int(1..2), q30_2 : bool, q30_1 < q24_1 \/ q30_1 = q24_1 /\ q30_2 < q24_2]))) - | q24_1 : int(1..2), q24_2 : bool]) - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_1_1_1-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_1_1_1-solution000001.solution deleted file mode 100644 index ce716c9ad7..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_1_1_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be {2, 3, 4} -letting b be {1, 3, 4} diff --git a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_1_1_1-solution000002.solution b/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_1_1_1-solution000002.solution deleted file mode 100644 index 28f008dddf..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_1_1_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be {2, 3, 4} -letting b be {1, 2, 4} diff --git a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_1_1_1-solution000003.solution b/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_1_1_1-solution000003.solution deleted file mode 100644 index 872d8190b1..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_1_1_1-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be {2, 3, 4} -letting b be {1, 2, 3} diff --git a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_1_1_1-solution000004.solution b/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_1_1_1-solution000004.solution deleted file mode 100644 index 294f34ef4b..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_1_1_1-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be {1, 3, 4} -letting b be {1, 2, 4} diff --git a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_1_1_1-solution000005.solution b/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_1_1_1-solution000005.solution deleted file mode 100644 index 590062f44f..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_1_1_1-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be {1, 3, 4} -letting b be {1, 2, 3} diff --git a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_1_1_1-solution000006.solution b/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_1_1_1-solution000006.solution deleted file mode 100644 index 1b7dfb6b12..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_1_1_1-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be {1, 2, 4} -letting b be {1, 2, 3} diff --git a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_1_1_1.eprime b/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_1_1_1.eprime deleted file mode 100644 index 15588dcf6b..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_1_1_1.eprime +++ /dev/null @@ -1,24 +0,0 @@ -language ESSENCE' 1.0 - -find a_Occurrence: matrix indexed by [int(1..4)] of bool -find b_Occurrence: matrix indexed by [int(1..4)] of bool -branching on [a_Occurrence, b_Occurrence] -such that - or([a_Occurrence[q3] /\ - (toInt(a_Occurrence[q3]) < toInt(b_Occurrence[q3]) /\ - (and([a_Occurrence[q4] -> toInt(a_Occurrence[q4]) = toInt(b_Occurrence[q4]) | q4 : int(1..4), q4 < q3]) /\ - and([b_Occurrence[q4] /\ !or([a_Occurrence[q7] /\ q7 = q4 | q7 : int(1..4)]) -> - toInt(a_Occurrence[q4]) = toInt(b_Occurrence[q4]) - | q4 : int(1..4), q4 < q3]))) - | q3 : int(1..4)]) - \/ - or([b_Occurrence[q3] /\ !or([a_Occurrence[q6] /\ q6 = q3 | q6 : int(1..4)]) /\ - (toInt(a_Occurrence[q3]) < toInt(b_Occurrence[q3]) /\ - (and([a_Occurrence[q4] -> toInt(a_Occurrence[q4]) = toInt(b_Occurrence[q4]) | q4 : int(1..4), q4 < q3]) /\ - and([b_Occurrence[q4] /\ !or([a_Occurrence[q5] /\ q5 = q4 | q5 : int(1..4)]) -> - toInt(a_Occurrence[q4]) = toInt(b_Occurrence[q4]) - | q4 : int(1..4), q4 < q3]))) - | q3 : int(1..4)]), - 3 = sum([toInt(a_Occurrence[q1]) | q1 : int(1..4)]), - 3 = sum([toInt(b_Occurrence[q2]) | q2 : int(1..4)]) - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_1_1_2-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_1_1_2-solution000001.solution deleted file mode 100644 index 872d8190b1..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_1_1_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be {2, 3, 4} -letting b be {1, 2, 3} diff --git a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_1_1_2-solution000002.solution b/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_1_1_2-solution000002.solution deleted file mode 100644 index 28f008dddf..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_1_1_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be {2, 3, 4} -letting b be {1, 2, 4} diff --git a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_1_1_2-solution000003.solution b/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_1_1_2-solution000003.solution deleted file mode 100644 index ce716c9ad7..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_1_1_2-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be {2, 3, 4} -letting b be {1, 3, 4} diff --git a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_1_1_2-solution000004.solution b/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_1_1_2-solution000004.solution deleted file mode 100644 index 590062f44f..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_1_1_2-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be {1, 3, 4} -letting b be {1, 2, 3} diff --git a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_1_1_2-solution000005.solution b/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_1_1_2-solution000005.solution deleted file mode 100644 index 294f34ef4b..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_1_1_2-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be {1, 3, 4} -letting b be {1, 2, 4} diff --git a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_1_1_2-solution000006.solution b/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_1_1_2-solution000006.solution deleted file mode 100644 index 1b7dfb6b12..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_1_1_2-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be {1, 2, 4} -letting b be {1, 2, 3} diff --git a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_1_1_2.eprime b/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_1_1_2.eprime deleted file mode 100644 index 01bc5ae7fb..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_1_1_2.eprime +++ /dev/null @@ -1,30 +0,0 @@ -language ESSENCE' 1.0 - -find a_Occurrence: matrix indexed by [int(1..4)] of bool -find b_Occurrence: matrix indexed by [int(1..4)] of bool -find b_Explicit: matrix indexed by [int(1..3)] of int(1..4) -branching on [a_Occurrence, b_Explicit, b_Occurrence] -such that - or([a_Occurrence[q10] /\ - (toInt(a_Occurrence[q10]) < toInt(b_Occurrence[q10]) /\ - (and([a_Occurrence[q11] -> toInt(a_Occurrence[q11]) = toInt(b_Occurrence[q11]) | q11 : int(1..4), q11 < q10]) - /\ - and([b_Occurrence[q11] /\ !or([a_Occurrence[q14] /\ q14 = q11 | q14 : int(1..4)]) -> - toInt(a_Occurrence[q11]) = toInt(b_Occurrence[q11]) - | q11 : int(1..4), q11 < q10]))) - | q10 : int(1..4)]) - \/ - or([b_Occurrence[q10] /\ !or([a_Occurrence[q13] /\ q13 = q10 | q13 : int(1..4)]) /\ - (toInt(a_Occurrence[q10]) < toInt(b_Occurrence[q10]) /\ - (and([a_Occurrence[q11] -> toInt(a_Occurrence[q11]) = toInt(b_Occurrence[q11]) | q11 : int(1..4), q11 < q10]) - /\ - and([b_Occurrence[q11] /\ !or([a_Occurrence[q12] /\ q12 = q11 | q12 : int(1..4)]) -> - toInt(a_Occurrence[q11]) = toInt(b_Occurrence[q11]) - | q11 : int(1..4), q11 < q10]))) - | q10 : int(1..4)]), - 3 = sum([toInt(a_Occurrence[q1]) | q1 : int(1..4)]), - 3 = sum([toInt(b_Occurrence[q2]) | q2 : int(1..4)]), - and([b_Explicit[q3] < b_Explicit[q3 + 1] | q3 : int(1..2)]), - and([b_Occurrence[b_Explicit[q6]] | q6 : int(1..3)]), - and([b_Occurrence[q7] -> or([b_Explicit[q9] = q7 | q9 : int(1..3)]) | q7 : int(1..4)]) - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_1_2_1-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_1_2_1-solution000001.solution deleted file mode 100644 index 1b7dfb6b12..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_1_2_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be {1, 2, 4} -letting b be {1, 2, 3} diff --git a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_1_2_1-solution000002.solution b/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_1_2_1-solution000002.solution deleted file mode 100644 index 294f34ef4b..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_1_2_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be {1, 3, 4} -letting b be {1, 2, 4} diff --git a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_1_2_1-solution000003.solution b/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_1_2_1-solution000003.solution deleted file mode 100644 index 590062f44f..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_1_2_1-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be {1, 3, 4} -letting b be {1, 2, 3} diff --git a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_1_2_1-solution000004.solution b/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_1_2_1-solution000004.solution deleted file mode 100644 index ce716c9ad7..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_1_2_1-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be {2, 3, 4} -letting b be {1, 3, 4} diff --git a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_1_2_1-solution000005.solution b/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_1_2_1-solution000005.solution deleted file mode 100644 index 28f008dddf..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_1_2_1-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be {2, 3, 4} -letting b be {1, 2, 4} diff --git a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_1_2_1-solution000006.solution b/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_1_2_1-solution000006.solution deleted file mode 100644 index 872d8190b1..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_1_2_1-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be {2, 3, 4} -letting b be {1, 2, 3} diff --git a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_1_2_1.eprime b/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_1_2_1.eprime deleted file mode 100644 index 508ad476f3..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_1_2_1.eprime +++ /dev/null @@ -1,30 +0,0 @@ -language ESSENCE' 1.0 - -find a_Occurrence: matrix indexed by [int(1..4)] of bool -find a_Explicit: matrix indexed by [int(1..3)] of int(1..4) -find b_Occurrence: matrix indexed by [int(1..4)] of bool -branching on [a_Explicit, a_Occurrence, b_Occurrence] -such that - or([a_Occurrence[q10] /\ - (toInt(a_Occurrence[q10]) < toInt(b_Occurrence[q10]) /\ - (and([a_Occurrence[q11] -> toInt(a_Occurrence[q11]) = toInt(b_Occurrence[q11]) | q11 : int(1..4), q11 < q10]) - /\ - and([b_Occurrence[q11] /\ !or([a_Occurrence[q14] /\ q14 = q11 | q14 : int(1..4)]) -> - toInt(a_Occurrence[q11]) = toInt(b_Occurrence[q11]) - | q11 : int(1..4), q11 < q10]))) - | q10 : int(1..4)]) - \/ - or([b_Occurrence[q10] /\ !or([a_Occurrence[q13] /\ q13 = q10 | q13 : int(1..4)]) /\ - (toInt(a_Occurrence[q10]) < toInt(b_Occurrence[q10]) /\ - (and([a_Occurrence[q11] -> toInt(a_Occurrence[q11]) = toInt(b_Occurrence[q11]) | q11 : int(1..4), q11 < q10]) - /\ - and([b_Occurrence[q11] /\ !or([a_Occurrence[q12] /\ q12 = q11 | q12 : int(1..4)]) -> - toInt(a_Occurrence[q11]) = toInt(b_Occurrence[q11]) - | q11 : int(1..4), q11 < q10]))) - | q10 : int(1..4)]), - 3 = sum([toInt(a_Occurrence[q1]) | q1 : int(1..4)]), - 3 = sum([toInt(b_Occurrence[q2]) | q2 : int(1..4)]), - and([a_Explicit[q3] < a_Explicit[q3 + 1] | q3 : int(1..2)]), - and([a_Occurrence[a_Explicit[q6]] | q6 : int(1..3)]), - and([a_Occurrence[q7] -> or([a_Explicit[q9] = q7 | q9 : int(1..3)]) | q7 : int(1..4)]) - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_1_2_2-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_1_2_2-solution000001.solution deleted file mode 100644 index 1b7dfb6b12..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_1_2_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be {1, 2, 4} -letting b be {1, 2, 3} diff --git a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_1_2_2-solution000002.solution b/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_1_2_2-solution000002.solution deleted file mode 100644 index 590062f44f..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_1_2_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be {1, 3, 4} -letting b be {1, 2, 3} diff --git a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_1_2_2-solution000003.solution b/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_1_2_2-solution000003.solution deleted file mode 100644 index 294f34ef4b..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_1_2_2-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be {1, 3, 4} -letting b be {1, 2, 4} diff --git a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_1_2_2-solution000004.solution b/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_1_2_2-solution000004.solution deleted file mode 100644 index 872d8190b1..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_1_2_2-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be {2, 3, 4} -letting b be {1, 2, 3} diff --git a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_1_2_2-solution000005.solution b/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_1_2_2-solution000005.solution deleted file mode 100644 index 28f008dddf..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_1_2_2-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be {2, 3, 4} -letting b be {1, 2, 4} diff --git a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_1_2_2-solution000006.solution b/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_1_2_2-solution000006.solution deleted file mode 100644 index ce716c9ad7..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_1_2_2-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be {2, 3, 4} -letting b be {1, 3, 4} diff --git a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_1_2_2.eprime b/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_1_2_2.eprime deleted file mode 100644 index ea4530ca06..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_1_2_2.eprime +++ /dev/null @@ -1,34 +0,0 @@ -language ESSENCE' 1.0 - -find a_Occurrence: matrix indexed by [int(1..4)] of bool -find a_Explicit: matrix indexed by [int(1..3)] of int(1..4) -find b_Occurrence: matrix indexed by [int(1..4)] of bool -find b_Explicit: matrix indexed by [int(1..3)] of int(1..4) -branching on [a_Explicit, a_Occurrence, b_Explicit, b_Occurrence] -such that - or([a_Occurrence[q17] /\ - (toInt(a_Occurrence[q17]) < toInt(b_Occurrence[q17]) /\ - (and([a_Occurrence[q18] -> toInt(a_Occurrence[q18]) = toInt(b_Occurrence[q18]) | q18 : int(1..4), q18 < q17]) - /\ - and([b_Occurrence[q18] /\ !or([a_Occurrence[q21] /\ q21 = q18 | q21 : int(1..4)]) -> - toInt(a_Occurrence[q18]) = toInt(b_Occurrence[q18]) - | q18 : int(1..4), q18 < q17]))) - | q17 : int(1..4)]) - \/ - or([b_Occurrence[q17] /\ !or([a_Occurrence[q20] /\ q20 = q17 | q20 : int(1..4)]) /\ - (toInt(a_Occurrence[q17]) < toInt(b_Occurrence[q17]) /\ - (and([a_Occurrence[q18] -> toInt(a_Occurrence[q18]) = toInt(b_Occurrence[q18]) | q18 : int(1..4), q18 < q17]) - /\ - and([b_Occurrence[q18] /\ !or([a_Occurrence[q19] /\ q19 = q18 | q19 : int(1..4)]) -> - toInt(a_Occurrence[q18]) = toInt(b_Occurrence[q18]) - | q18 : int(1..4), q18 < q17]))) - | q17 : int(1..4)]), - 3 = sum([toInt(a_Occurrence[q1]) | q1 : int(1..4)]), - 3 = sum([toInt(b_Occurrence[q2]) | q2 : int(1..4)]), - and([a_Explicit[q3] < a_Explicit[q3 + 1] | q3 : int(1..2)]), - and([a_Occurrence[a_Explicit[q6]] | q6 : int(1..3)]), - and([a_Occurrence[q7] -> or([a_Explicit[q9] = q7 | q9 : int(1..3)]) | q7 : int(1..4)]), - and([b_Explicit[q10] < b_Explicit[q10 + 1] | q10 : int(1..2)]), - and([b_Occurrence[b_Explicit[q13]] | q13 : int(1..3)]), - and([b_Occurrence[q14] -> or([b_Explicit[q16] = q14 | q16 : int(1..3)]) | q14 : int(1..4)]) - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_2_1_1-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_2_1_1-solution000001.solution deleted file mode 100644 index ce716c9ad7..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_2_1_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be {2, 3, 4} -letting b be {1, 3, 4} diff --git a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_2_1_1-solution000002.solution b/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_2_1_1-solution000002.solution deleted file mode 100644 index 28f008dddf..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_2_1_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be {2, 3, 4} -letting b be {1, 2, 4} diff --git a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_2_1_1-solution000003.solution b/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_2_1_1-solution000003.solution deleted file mode 100644 index 872d8190b1..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_2_1_1-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be {2, 3, 4} -letting b be {1, 2, 3} diff --git a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_2_1_1-solution000004.solution b/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_2_1_1-solution000004.solution deleted file mode 100644 index 294f34ef4b..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_2_1_1-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be {1, 3, 4} -letting b be {1, 2, 4} diff --git a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_2_1_1-solution000005.solution b/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_2_1_1-solution000005.solution deleted file mode 100644 index 590062f44f..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_2_1_1-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be {1, 3, 4} -letting b be {1, 2, 3} diff --git a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_2_1_1-solution000006.solution b/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_2_1_1-solution000006.solution deleted file mode 100644 index 1b7dfb6b12..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_2_1_1-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be {1, 2, 4} -letting b be {1, 2, 3} diff --git a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_2_1_1.eprime b/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_2_1_1.eprime deleted file mode 100644 index ec352b6f14..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_2_1_1.eprime +++ /dev/null @@ -1,34 +0,0 @@ -language ESSENCE' 1.0 - -find a_Occurrence: matrix indexed by [int(1..4)] of bool -find b_Explicit: matrix indexed by [int(1..3)] of int(1..4) -find b_Occurrence: matrix indexed by [int(1..4)] of bool -branching on [a_Occurrence, b_Occurrence, b_Explicit] -such that - or([a_Occurrence[q10] /\ - (toInt(a_Occurrence[q10]) < toInt(or([b_Explicit[q23] = q10 | q23 : int(1..3)])) /\ - (and([a_Occurrence[q11] -> toInt(a_Occurrence[q11]) = toInt(or([b_Explicit[q29] = q11 | q29 : int(1..3)])) - | q11 : int(1..4), q11 < q10]) - /\ - and([!or([a_Occurrence[q27] /\ q27 = b_Explicit[q24] | q27 : int(1..4)]) /\ b_Explicit[q24] < q10 -> - toInt(a_Occurrence[b_Explicit[q24]]) = toInt(or([b_Explicit[q26] = b_Explicit[q24] | q26 : int(1..3)])) - | q24 : int(1..3)]))) - | q10 : int(1..4)]) - \/ - or([!or([a_Occurrence[q21] /\ q21 = b_Explicit[q12] | q21 : int(1..4)]) /\ - (toInt(a_Occurrence[b_Explicit[q12]]) < toInt(or([b_Explicit[q14] = b_Explicit[q12] | q14 : int(1..3)])) /\ - (and([a_Occurrence[q11] /\ q11 < b_Explicit[q12] -> - toInt(a_Occurrence[q11]) = toInt(or([b_Explicit[q20] = q11 | q20 : int(1..3)])) - | q11 : int(1..4)]) - /\ - and([!or([a_Occurrence[q18] /\ q18 = b_Explicit[q15] | q18 : int(1..4)]) /\ b_Explicit[q15] < b_Explicit[q12] - -> - toInt(a_Occurrence[b_Explicit[q15]]) = toInt(or([b_Explicit[q17] = b_Explicit[q15] | q17 : int(1..3)])) - | q15 : int(1..3)]))) - | q12 : int(1..3)]), - 3 = sum([toInt(a_Occurrence[q1]) | q1 : int(1..4)]), - and([b_Explicit[q2] < b_Explicit[q2 + 1] | q2 : int(1..2)]), - 3 = sum([toInt(b_Occurrence[q4]) | q4 : int(1..4)]), - and([b_Occurrence[q5] -> or([b_Explicit[q7] = q5 | q7 : int(1..3)]) | q5 : int(1..4)]), - and([b_Occurrence[b_Explicit[q9]] | q9 : int(1..3)]) - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_2_1_2-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_2_1_2-solution000001.solution deleted file mode 100644 index 872d8190b1..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_2_1_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be {2, 3, 4} -letting b be {1, 2, 3} diff --git a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_2_1_2-solution000002.solution b/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_2_1_2-solution000002.solution deleted file mode 100644 index 28f008dddf..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_2_1_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be {2, 3, 4} -letting b be {1, 2, 4} diff --git a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_2_1_2-solution000003.solution b/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_2_1_2-solution000003.solution deleted file mode 100644 index ce716c9ad7..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_2_1_2-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be {2, 3, 4} -letting b be {1, 3, 4} diff --git a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_2_1_2-solution000004.solution b/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_2_1_2-solution000004.solution deleted file mode 100644 index 590062f44f..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_2_1_2-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be {1, 3, 4} -letting b be {1, 2, 3} diff --git a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_2_1_2-solution000005.solution b/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_2_1_2-solution000005.solution deleted file mode 100644 index 294f34ef4b..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_2_1_2-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be {1, 3, 4} -letting b be {1, 2, 4} diff --git a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_2_1_2-solution000006.solution b/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_2_1_2-solution000006.solution deleted file mode 100644 index 1b7dfb6b12..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_2_1_2-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be {1, 2, 4} -letting b be {1, 2, 3} diff --git a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_2_1_2.eprime b/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_2_1_2.eprime deleted file mode 100644 index 2942c4a4d0..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_2_1_2.eprime +++ /dev/null @@ -1,29 +0,0 @@ -language ESSENCE' 1.0 - -find a_Occurrence: matrix indexed by [int(1..4)] of bool -find b_Explicit: matrix indexed by [int(1..3)] of int(1..4) -branching on [a_Occurrence, b_Explicit] -such that - or([a_Occurrence[q4] /\ - (toInt(a_Occurrence[q4]) < toInt(or([b_Explicit[q17] = q4 | q17 : int(1..3)])) /\ - (and([a_Occurrence[q5] -> toInt(a_Occurrence[q5]) = toInt(or([b_Explicit[q23] = q5 | q23 : int(1..3)])) - | q5 : int(1..4), q5 < q4]) - /\ - and([!or([a_Occurrence[q21] /\ q21 = b_Explicit[q18] | q21 : int(1..4)]) /\ b_Explicit[q18] < q4 -> - toInt(a_Occurrence[b_Explicit[q18]]) = toInt(or([b_Explicit[q20] = b_Explicit[q18] | q20 : int(1..3)])) - | q18 : int(1..3)]))) - | q4 : int(1..4)]) - \/ - or([!or([a_Occurrence[q15] /\ q15 = b_Explicit[q6] | q15 : int(1..4)]) /\ - (toInt(a_Occurrence[b_Explicit[q6]]) < toInt(or([b_Explicit[q8] = b_Explicit[q6] | q8 : int(1..3)])) /\ - (and([a_Occurrence[q5] /\ q5 < b_Explicit[q6] -> - toInt(a_Occurrence[q5]) = toInt(or([b_Explicit[q14] = q5 | q14 : int(1..3)])) - | q5 : int(1..4)]) - /\ - and([!or([a_Occurrence[q12] /\ q12 = b_Explicit[q9] | q12 : int(1..4)]) /\ b_Explicit[q9] < b_Explicit[q6] -> - toInt(a_Occurrence[b_Explicit[q9]]) = toInt(or([b_Explicit[q11] = b_Explicit[q9] | q11 : int(1..3)])) - | q9 : int(1..3)]))) - | q6 : int(1..3)]), - 3 = sum([toInt(a_Occurrence[q1]) | q1 : int(1..4)]), - and([b_Explicit[q2] < b_Explicit[q2 + 1] | q2 : int(1..2)]) - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_2_2_1-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_2_2_1-solution000001.solution deleted file mode 100644 index 1b7dfb6b12..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_2_2_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be {1, 2, 4} -letting b be {1, 2, 3} diff --git a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_2_2_1-solution000002.solution b/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_2_2_1-solution000002.solution deleted file mode 100644 index 294f34ef4b..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_2_2_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be {1, 3, 4} -letting b be {1, 2, 4} diff --git a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_2_2_1-solution000003.solution b/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_2_2_1-solution000003.solution deleted file mode 100644 index 590062f44f..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_2_2_1-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be {1, 3, 4} -letting b be {1, 2, 3} diff --git a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_2_2_1-solution000004.solution b/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_2_2_1-solution000004.solution deleted file mode 100644 index ce716c9ad7..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_2_2_1-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be {2, 3, 4} -letting b be {1, 3, 4} diff --git a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_2_2_1-solution000005.solution b/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_2_2_1-solution000005.solution deleted file mode 100644 index 28f008dddf..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_2_2_1-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be {2, 3, 4} -letting b be {1, 2, 4} diff --git a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_2_2_1-solution000006.solution b/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_2_2_1-solution000006.solution deleted file mode 100644 index 872d8190b1..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_2_2_1-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be {2, 3, 4} -letting b be {1, 2, 3} diff --git a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_2_2_1.eprime b/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_2_2_1.eprime deleted file mode 100644 index ed0a2c30f1..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_2_2_1.eprime +++ /dev/null @@ -1,38 +0,0 @@ -language ESSENCE' 1.0 - -find a_Occurrence: matrix indexed by [int(1..4)] of bool -find a_Explicit: matrix indexed by [int(1..3)] of int(1..4) -find b_Explicit: matrix indexed by [int(1..3)] of int(1..4) -find b_Occurrence: matrix indexed by [int(1..4)] of bool -branching on [a_Explicit, a_Occurrence, b_Occurrence, b_Explicit] -such that - or([a_Occurrence[q17] /\ - (toInt(a_Occurrence[q17]) < toInt(or([b_Explicit[q30] = q17 | q30 : int(1..3)])) /\ - (and([a_Occurrence[q18] -> toInt(a_Occurrence[q18]) = toInt(or([b_Explicit[q36] = q18 | q36 : int(1..3)])) - | q18 : int(1..4), q18 < q17]) - /\ - and([!or([a_Occurrence[q34] /\ q34 = b_Explicit[q31] | q34 : int(1..4)]) /\ b_Explicit[q31] < q17 -> - toInt(a_Occurrence[b_Explicit[q31]]) = toInt(or([b_Explicit[q33] = b_Explicit[q31] | q33 : int(1..3)])) - | q31 : int(1..3)]))) - | q17 : int(1..4)]) - \/ - or([!or([a_Occurrence[q28] /\ q28 = b_Explicit[q19] | q28 : int(1..4)]) /\ - (toInt(a_Occurrence[b_Explicit[q19]]) < toInt(or([b_Explicit[q21] = b_Explicit[q19] | q21 : int(1..3)])) /\ - (and([a_Occurrence[q18] /\ q18 < b_Explicit[q19] -> - toInt(a_Occurrence[q18]) = toInt(or([b_Explicit[q27] = q18 | q27 : int(1..3)])) - | q18 : int(1..4)]) - /\ - and([!or([a_Occurrence[q25] /\ q25 = b_Explicit[q22] | q25 : int(1..4)]) /\ b_Explicit[q22] < b_Explicit[q19] - -> - toInt(a_Occurrence[b_Explicit[q22]]) = toInt(or([b_Explicit[q24] = b_Explicit[q22] | q24 : int(1..3)])) - | q22 : int(1..3)]))) - | q19 : int(1..3)]), - 3 = sum([toInt(a_Occurrence[q1]) | q1 : int(1..4)]), - and([b_Explicit[q2] < b_Explicit[q2 + 1] | q2 : int(1..2)]), - and([a_Explicit[q4] < a_Explicit[q4 + 1] | q4 : int(1..2)]), - and([a_Occurrence[a_Explicit[q7]] | q7 : int(1..3)]), - and([a_Occurrence[q8] -> or([a_Explicit[q10] = q8 | q10 : int(1..3)]) | q8 : int(1..4)]), - 3 = sum([toInt(b_Occurrence[q11]) | q11 : int(1..4)]), - and([b_Occurrence[q12] -> or([b_Explicit[q14] = q12 | q14 : int(1..3)]) | q12 : int(1..4)]), - and([b_Occurrence[b_Explicit[q16]] | q16 : int(1..3)]) - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_2_2_2-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_2_2_2-solution000001.solution deleted file mode 100644 index 1b7dfb6b12..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_2_2_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be {1, 2, 4} -letting b be {1, 2, 3} diff --git a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_2_2_2-solution000002.solution b/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_2_2_2-solution000002.solution deleted file mode 100644 index 590062f44f..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_2_2_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be {1, 3, 4} -letting b be {1, 2, 3} diff --git a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_2_2_2-solution000003.solution b/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_2_2_2-solution000003.solution deleted file mode 100644 index 294f34ef4b..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_2_2_2-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be {1, 3, 4} -letting b be {1, 2, 4} diff --git a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_2_2_2-solution000004.solution b/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_2_2_2-solution000004.solution deleted file mode 100644 index 872d8190b1..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_2_2_2-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be {2, 3, 4} -letting b be {1, 2, 3} diff --git a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_2_2_2-solution000005.solution b/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_2_2_2-solution000005.solution deleted file mode 100644 index 28f008dddf..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_2_2_2-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be {2, 3, 4} -letting b be {1, 2, 4} diff --git a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_2_2_2-solution000006.solution b/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_2_2_2-solution000006.solution deleted file mode 100644 index ce716c9ad7..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_2_2_2-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be {2, 3, 4} -letting b be {1, 3, 4} diff --git a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_2_2_2.eprime b/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_2_2_2.eprime deleted file mode 100644 index 5d23683092..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_1_2_2_2.eprime +++ /dev/null @@ -1,34 +0,0 @@ -language ESSENCE' 1.0 - -find a_Occurrence: matrix indexed by [int(1..4)] of bool -find a_Explicit: matrix indexed by [int(1..3)] of int(1..4) -find b_Explicit: matrix indexed by [int(1..3)] of int(1..4) -branching on [a_Explicit, a_Occurrence, b_Explicit] -such that - or([a_Occurrence[q11] /\ - (toInt(a_Occurrence[q11]) < toInt(or([b_Explicit[q24] = q11 | q24 : int(1..3)])) /\ - (and([a_Occurrence[q12] -> toInt(a_Occurrence[q12]) = toInt(or([b_Explicit[q30] = q12 | q30 : int(1..3)])) - | q12 : int(1..4), q12 < q11]) - /\ - and([!or([a_Occurrence[q28] /\ q28 = b_Explicit[q25] | q28 : int(1..4)]) /\ b_Explicit[q25] < q11 -> - toInt(a_Occurrence[b_Explicit[q25]]) = toInt(or([b_Explicit[q27] = b_Explicit[q25] | q27 : int(1..3)])) - | q25 : int(1..3)]))) - | q11 : int(1..4)]) - \/ - or([!or([a_Occurrence[q22] /\ q22 = b_Explicit[q13] | q22 : int(1..4)]) /\ - (toInt(a_Occurrence[b_Explicit[q13]]) < toInt(or([b_Explicit[q15] = b_Explicit[q13] | q15 : int(1..3)])) /\ - (and([a_Occurrence[q12] /\ q12 < b_Explicit[q13] -> - toInt(a_Occurrence[q12]) = toInt(or([b_Explicit[q21] = q12 | q21 : int(1..3)])) - | q12 : int(1..4)]) - /\ - and([!or([a_Occurrence[q19] /\ q19 = b_Explicit[q16] | q19 : int(1..4)]) /\ b_Explicit[q16] < b_Explicit[q13] - -> - toInt(a_Occurrence[b_Explicit[q16]]) = toInt(or([b_Explicit[q18] = b_Explicit[q16] | q18 : int(1..3)])) - | q16 : int(1..3)]))) - | q13 : int(1..3)]), - 3 = sum([toInt(a_Occurrence[q1]) | q1 : int(1..4)]), - and([b_Explicit[q2] < b_Explicit[q2 + 1] | q2 : int(1..2)]), - and([a_Explicit[q4] < a_Explicit[q4 + 1] | q4 : int(1..2)]), - and([a_Occurrence[a_Explicit[q7]] | q7 : int(1..3)]), - and([a_Occurrence[q8] -> or([a_Explicit[q10] = q8 | q10 : int(1..3)]) | q8 : int(1..4)]) - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_1_1_1-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_1_1_1-solution000001.solution deleted file mode 100644 index ce716c9ad7..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_1_1_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be {2, 3, 4} -letting b be {1, 3, 4} diff --git a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_1_1_1-solution000002.solution b/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_1_1_1-solution000002.solution deleted file mode 100644 index 28f008dddf..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_1_1_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be {2, 3, 4} -letting b be {1, 2, 4} diff --git a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_1_1_1-solution000003.solution b/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_1_1_1-solution000003.solution deleted file mode 100644 index 872d8190b1..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_1_1_1-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be {2, 3, 4} -letting b be {1, 2, 3} diff --git a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_1_1_1-solution000004.solution b/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_1_1_1-solution000004.solution deleted file mode 100644 index 294f34ef4b..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_1_1_1-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be {1, 3, 4} -letting b be {1, 2, 4} diff --git a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_1_1_1-solution000005.solution b/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_1_1_1-solution000005.solution deleted file mode 100644 index 590062f44f..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_1_1_1-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be {1, 3, 4} -letting b be {1, 2, 3} diff --git a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_1_1_1-solution000006.solution b/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_1_1_1-solution000006.solution deleted file mode 100644 index 1b7dfb6b12..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_1_1_1-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be {1, 2, 4} -letting b be {1, 2, 3} diff --git a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_1_1_1.eprime b/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_1_1_1.eprime deleted file mode 100644 index 774d98f0ee..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_1_1_1.eprime +++ /dev/null @@ -1,33 +0,0 @@ -language ESSENCE' 1.0 - -find a_Explicit: matrix indexed by [int(1..3)] of int(1..4) -find a_Occurrence: matrix indexed by [int(1..4)] of bool -find b_Occurrence: matrix indexed by [int(1..4)] of bool -branching on [a_Occurrence, a_Explicit, b_Occurrence] -such that - or([toInt(or([a_Explicit[q25] = a_Explicit[q12] | q25 : int(1..3)])) < toInt(b_Occurrence[a_Explicit[q12]]) /\ - (and([a_Explicit[q26] < a_Explicit[q12] -> - toInt(or([a_Explicit[q32] = a_Explicit[q26] | q32 : int(1..3)])) = toInt(b_Occurrence[a_Explicit[q26]]) - | q26 : int(1..3)]) - /\ - and([and([b_Occurrence[q11], !or([a_Explicit[q30] = q11 | q30 : int(1..3)]), q11 < a_Explicit[q12]; int(1..3)]) - -> toInt(or([a_Explicit[q28] = q11 | q28 : int(1..3)])) = toInt(b_Occurrence[q11]) - | q11 : int(1..4)])) - | q12 : int(1..3)]) - \/ - or([b_Occurrence[q10] /\ !or([a_Explicit[q23] = q10 | q23 : int(1..3)]) /\ - (toInt(or([a_Explicit[q14] = q10 | q14 : int(1..3)])) < toInt(b_Occurrence[q10]) /\ - (and([a_Explicit[q15] < q10 -> - toInt(or([a_Explicit[q21] = a_Explicit[q15] | q21 : int(1..3)])) = toInt(b_Occurrence[a_Explicit[q15]]) - | q15 : int(1..3)]) - /\ - and([b_Occurrence[q11] /\ !or([a_Explicit[q19] = q11 | q19 : int(1..3)]) -> - toInt(or([a_Explicit[q17] = q11 | q17 : int(1..3)])) = toInt(b_Occurrence[q11]) - | q11 : int(1..4), q11 < q10]))) - | q10 : int(1..4)]), - and([a_Explicit[q1] < a_Explicit[q1 + 1] | q1 : int(1..2)]), - 3 = sum([toInt(b_Occurrence[q3]) | q3 : int(1..4)]), - 3 = sum([toInt(a_Occurrence[q4]) | q4 : int(1..4)]), - and([a_Occurrence[q5] -> or([a_Explicit[q7] = q5 | q7 : int(1..3)]) | q5 : int(1..4)]), - and([a_Occurrence[a_Explicit[q9]] | q9 : int(1..3)]) - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_1_1_2-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_1_1_2-solution000001.solution deleted file mode 100644 index 872d8190b1..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_1_1_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be {2, 3, 4} -letting b be {1, 2, 3} diff --git a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_1_1_2-solution000002.solution b/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_1_1_2-solution000002.solution deleted file mode 100644 index 28f008dddf..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_1_1_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be {2, 3, 4} -letting b be {1, 2, 4} diff --git a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_1_1_2-solution000003.solution b/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_1_1_2-solution000003.solution deleted file mode 100644 index ce716c9ad7..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_1_1_2-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be {2, 3, 4} -letting b be {1, 3, 4} diff --git a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_1_1_2-solution000004.solution b/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_1_1_2-solution000004.solution deleted file mode 100644 index 590062f44f..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_1_1_2-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be {1, 3, 4} -letting b be {1, 2, 3} diff --git a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_1_1_2-solution000005.solution b/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_1_1_2-solution000005.solution deleted file mode 100644 index 294f34ef4b..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_1_1_2-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be {1, 3, 4} -letting b be {1, 2, 4} diff --git a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_1_1_2-solution000006.solution b/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_1_1_2-solution000006.solution deleted file mode 100644 index 1b7dfb6b12..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_1_1_2-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be {1, 2, 4} -letting b be {1, 2, 3} diff --git a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_1_1_2.eprime b/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_1_1_2.eprime deleted file mode 100644 index 83c896bcc7..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_1_1_2.eprime +++ /dev/null @@ -1,37 +0,0 @@ -language ESSENCE' 1.0 - -find a_Explicit: matrix indexed by [int(1..3)] of int(1..4) -find a_Occurrence: matrix indexed by [int(1..4)] of bool -find b_Occurrence: matrix indexed by [int(1..4)] of bool -find b_Explicit: matrix indexed by [int(1..3)] of int(1..4) -branching on [a_Occurrence, a_Explicit, b_Explicit, b_Occurrence] -such that - or([toInt(or([a_Explicit[q32] = a_Explicit[q19] | q32 : int(1..3)])) < toInt(b_Occurrence[a_Explicit[q19]]) /\ - (and([a_Explicit[q33] < a_Explicit[q19] -> - toInt(or([a_Explicit[q39] = a_Explicit[q33] | q39 : int(1..3)])) = toInt(b_Occurrence[a_Explicit[q33]]) - | q33 : int(1..3)]) - /\ - and([and([b_Occurrence[q18], !or([a_Explicit[q37] = q18 | q37 : int(1..3)]), q18 < a_Explicit[q19]; int(1..3)]) - -> toInt(or([a_Explicit[q35] = q18 | q35 : int(1..3)])) = toInt(b_Occurrence[q18]) - | q18 : int(1..4)])) - | q19 : int(1..3)]) - \/ - or([b_Occurrence[q17] /\ !or([a_Explicit[q30] = q17 | q30 : int(1..3)]) /\ - (toInt(or([a_Explicit[q21] = q17 | q21 : int(1..3)])) < toInt(b_Occurrence[q17]) /\ - (and([a_Explicit[q22] < q17 -> - toInt(or([a_Explicit[q28] = a_Explicit[q22] | q28 : int(1..3)])) = toInt(b_Occurrence[a_Explicit[q22]]) - | q22 : int(1..3)]) - /\ - and([b_Occurrence[q18] /\ !or([a_Explicit[q26] = q18 | q26 : int(1..3)]) -> - toInt(or([a_Explicit[q24] = q18 | q24 : int(1..3)])) = toInt(b_Occurrence[q18]) - | q18 : int(1..4), q18 < q17]))) - | q17 : int(1..4)]), - and([a_Explicit[q1] < a_Explicit[q1 + 1] | q1 : int(1..2)]), - 3 = sum([toInt(b_Occurrence[q3]) | q3 : int(1..4)]), - 3 = sum([toInt(a_Occurrence[q4]) | q4 : int(1..4)]), - and([a_Occurrence[q12] -> or([a_Explicit[q14] = q12 | q14 : int(1..3)]) | q12 : int(1..4)]), - and([a_Occurrence[a_Explicit[q16]] | q16 : int(1..3)]), - and([b_Explicit[q5] < b_Explicit[q5 + 1] | q5 : int(1..2)]), - and([b_Occurrence[b_Explicit[q8]] | q8 : int(1..3)]), - and([b_Occurrence[q9] -> or([b_Explicit[q11] = q9 | q11 : int(1..3)]) | q9 : int(1..4)]) - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_1_2_1-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_1_2_1-solution000001.solution deleted file mode 100644 index 1b7dfb6b12..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_1_2_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be {1, 2, 4} -letting b be {1, 2, 3} diff --git a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_1_2_1-solution000002.solution b/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_1_2_1-solution000002.solution deleted file mode 100644 index 294f34ef4b..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_1_2_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be {1, 3, 4} -letting b be {1, 2, 4} diff --git a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_1_2_1-solution000003.solution b/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_1_2_1-solution000003.solution deleted file mode 100644 index 590062f44f..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_1_2_1-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be {1, 3, 4} -letting b be {1, 2, 3} diff --git a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_1_2_1-solution000004.solution b/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_1_2_1-solution000004.solution deleted file mode 100644 index ce716c9ad7..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_1_2_1-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be {2, 3, 4} -letting b be {1, 3, 4} diff --git a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_1_2_1-solution000005.solution b/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_1_2_1-solution000005.solution deleted file mode 100644 index 28f008dddf..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_1_2_1-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be {2, 3, 4} -letting b be {1, 2, 4} diff --git a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_1_2_1-solution000006.solution b/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_1_2_1-solution000006.solution deleted file mode 100644 index 872d8190b1..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_1_2_1-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be {2, 3, 4} -letting b be {1, 2, 3} diff --git a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_1_2_1.eprime b/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_1_2_1.eprime deleted file mode 100644 index 6da0ecd855..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_1_2_1.eprime +++ /dev/null @@ -1,29 +0,0 @@ -language ESSENCE' 1.0 - -find a_Explicit: matrix indexed by [int(1..3)] of int(1..4) -find b_Occurrence: matrix indexed by [int(1..4)] of bool -branching on [a_Explicit, b_Occurrence] -such that - or([toInt(or([a_Explicit[q19] = a_Explicit[q6] | q19 : int(1..3)])) < toInt(b_Occurrence[a_Explicit[q6]]) /\ - (and([a_Explicit[q20] < a_Explicit[q6] -> - toInt(or([a_Explicit[q26] = a_Explicit[q20] | q26 : int(1..3)])) = toInt(b_Occurrence[a_Explicit[q20]]) - | q20 : int(1..3)]) - /\ - and([and([b_Occurrence[q5], !or([a_Explicit[q24] = q5 | q24 : int(1..3)]), q5 < a_Explicit[q6]; int(1..3)]) -> - toInt(or([a_Explicit[q22] = q5 | q22 : int(1..3)])) = toInt(b_Occurrence[q5]) - | q5 : int(1..4)])) - | q6 : int(1..3)]) - \/ - or([b_Occurrence[q4] /\ !or([a_Explicit[q17] = q4 | q17 : int(1..3)]) /\ - (toInt(or([a_Explicit[q8] = q4 | q8 : int(1..3)])) < toInt(b_Occurrence[q4]) /\ - (and([a_Explicit[q9] < q4 -> - toInt(or([a_Explicit[q15] = a_Explicit[q9] | q15 : int(1..3)])) = toInt(b_Occurrence[a_Explicit[q9]]) - | q9 : int(1..3)]) - /\ - and([b_Occurrence[q5] /\ !or([a_Explicit[q13] = q5 | q13 : int(1..3)]) -> - toInt(or([a_Explicit[q11] = q5 | q11 : int(1..3)])) = toInt(b_Occurrence[q5]) - | q5 : int(1..4), q5 < q4]))) - | q4 : int(1..4)]), - and([a_Explicit[q1] < a_Explicit[q1 + 1] | q1 : int(1..2)]), - 3 = sum([toInt(b_Occurrence[q3]) | q3 : int(1..4)]) - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_1_2_2-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_1_2_2-solution000001.solution deleted file mode 100644 index 1b7dfb6b12..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_1_2_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be {1, 2, 4} -letting b be {1, 2, 3} diff --git a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_1_2_2-solution000002.solution b/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_1_2_2-solution000002.solution deleted file mode 100644 index 590062f44f..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_1_2_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be {1, 3, 4} -letting b be {1, 2, 3} diff --git a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_1_2_2-solution000003.solution b/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_1_2_2-solution000003.solution deleted file mode 100644 index 294f34ef4b..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_1_2_2-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be {1, 3, 4} -letting b be {1, 2, 4} diff --git a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_1_2_2-solution000004.solution b/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_1_2_2-solution000004.solution deleted file mode 100644 index 872d8190b1..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_1_2_2-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be {2, 3, 4} -letting b be {1, 2, 3} diff --git a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_1_2_2-solution000005.solution b/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_1_2_2-solution000005.solution deleted file mode 100644 index 28f008dddf..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_1_2_2-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be {2, 3, 4} -letting b be {1, 2, 4} diff --git a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_1_2_2-solution000006.solution b/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_1_2_2-solution000006.solution deleted file mode 100644 index ce716c9ad7..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_1_2_2-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be {2, 3, 4} -letting b be {1, 3, 4} diff --git a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_1_2_2.eprime b/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_1_2_2.eprime deleted file mode 100644 index ff74c33383..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_1_2_2.eprime +++ /dev/null @@ -1,33 +0,0 @@ -language ESSENCE' 1.0 - -find a_Explicit: matrix indexed by [int(1..3)] of int(1..4) -find b_Occurrence: matrix indexed by [int(1..4)] of bool -find b_Explicit: matrix indexed by [int(1..3)] of int(1..4) -branching on [a_Explicit, b_Explicit, b_Occurrence] -such that - or([toInt(or([a_Explicit[q26] = a_Explicit[q13] | q26 : int(1..3)])) < toInt(b_Occurrence[a_Explicit[q13]]) /\ - (and([a_Explicit[q27] < a_Explicit[q13] -> - toInt(or([a_Explicit[q33] = a_Explicit[q27] | q33 : int(1..3)])) = toInt(b_Occurrence[a_Explicit[q27]]) - | q27 : int(1..3)]) - /\ - and([and([b_Occurrence[q12], !or([a_Explicit[q31] = q12 | q31 : int(1..3)]), q12 < a_Explicit[q13]; int(1..3)]) - -> toInt(or([a_Explicit[q29] = q12 | q29 : int(1..3)])) = toInt(b_Occurrence[q12]) - | q12 : int(1..4)])) - | q13 : int(1..3)]) - \/ - or([b_Occurrence[q11] /\ !or([a_Explicit[q24] = q11 | q24 : int(1..3)]) /\ - (toInt(or([a_Explicit[q15] = q11 | q15 : int(1..3)])) < toInt(b_Occurrence[q11]) /\ - (and([a_Explicit[q16] < q11 -> - toInt(or([a_Explicit[q22] = a_Explicit[q16] | q22 : int(1..3)])) = toInt(b_Occurrence[a_Explicit[q16]]) - | q16 : int(1..3)]) - /\ - and([b_Occurrence[q12] /\ !or([a_Explicit[q20] = q12 | q20 : int(1..3)]) -> - toInt(or([a_Explicit[q18] = q12 | q18 : int(1..3)])) = toInt(b_Occurrence[q12]) - | q12 : int(1..4), q12 < q11]))) - | q11 : int(1..4)]), - and([a_Explicit[q1] < a_Explicit[q1 + 1] | q1 : int(1..2)]), - 3 = sum([toInt(b_Occurrence[q3]) | q3 : int(1..4)]), - and([b_Explicit[q4] < b_Explicit[q4 + 1] | q4 : int(1..2)]), - and([b_Occurrence[b_Explicit[q7]] | q7 : int(1..3)]), - and([b_Occurrence[q8] -> or([b_Explicit[q10] = q8 | q10 : int(1..3)]) | q8 : int(1..4)]) - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_2_1_1-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_2_1_1-solution000001.solution deleted file mode 100644 index ce716c9ad7..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_2_1_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be {2, 3, 4} -letting b be {1, 3, 4} diff --git a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_2_1_1-solution000002.solution b/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_2_1_1-solution000002.solution deleted file mode 100644 index 28f008dddf..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_2_1_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be {2, 3, 4} -letting b be {1, 2, 4} diff --git a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_2_1_1-solution000003.solution b/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_2_1_1-solution000003.solution deleted file mode 100644 index 872d8190b1..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_2_1_1-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be {2, 3, 4} -letting b be {1, 2, 3} diff --git a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_2_1_1-solution000004.solution b/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_2_1_1-solution000004.solution deleted file mode 100644 index 294f34ef4b..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_2_1_1-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be {1, 3, 4} -letting b be {1, 2, 4} diff --git a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_2_1_1-solution000005.solution b/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_2_1_1-solution000005.solution deleted file mode 100644 index 590062f44f..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_2_1_1-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be {1, 3, 4} -letting b be {1, 2, 3} diff --git a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_2_1_1-solution000006.solution b/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_2_1_1-solution000006.solution deleted file mode 100644 index 1b7dfb6b12..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_2_1_1-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be {1, 2, 4} -letting b be {1, 2, 3} diff --git a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_2_1_1.eprime b/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_2_1_1.eprime deleted file mode 100644 index dea148eacf..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_2_1_1.eprime +++ /dev/null @@ -1,45 +0,0 @@ -language ESSENCE' 1.0 - -find a_Explicit: matrix indexed by [int(1..3)] of int(1..4) -find a_Occurrence: matrix indexed by [int(1..4)] of bool -find b_Explicit: matrix indexed by [int(1..3)] of int(1..4) -find b_Occurrence: matrix indexed by [int(1..4)] of bool -branching on [a_Occurrence, a_Explicit, b_Occurrence, b_Explicit] -such that - or([toInt(or([a_Explicit[q40] = a_Explicit[q19] | q40 : int(1..3)])) < - toInt(or([b_Explicit[q42] = a_Explicit[q19] | q42 : int(1..3)])) - /\ - (and([a_Explicit[q43] < a_Explicit[q19] -> - toInt(or([a_Explicit[q52] = a_Explicit[q43] | q52 : int(1..3)])) = - toInt(or([b_Explicit[q54] = a_Explicit[q43] | q54 : int(1..3)])) - | q43 : int(1..3)]) - /\ - and([!or([a_Explicit[q50] = b_Explicit[q44] | q50 : int(1..3)]) /\ b_Explicit[q44] < a_Explicit[q19] -> - toInt(or([a_Explicit[q46] = b_Explicit[q44] | q46 : int(1..3)])) = - toInt(or([b_Explicit[q48] = b_Explicit[q44] | q48 : int(1..3)])) - | q44 : int(1..3)])) - | q19 : int(1..3)]) - \/ - or([!or([a_Explicit[q38] = b_Explicit[q20] | q38 : int(1..3)]) /\ - (toInt(or([a_Explicit[q22] = b_Explicit[q20] | q22 : int(1..3)])) < - toInt(or([b_Explicit[q24] = b_Explicit[q20] | q24 : int(1..3)])) - /\ - (and([a_Explicit[q25] < b_Explicit[q20] -> - toInt(or([a_Explicit[q34] = a_Explicit[q25] | q34 : int(1..3)])) = - toInt(or([b_Explicit[q36] = a_Explicit[q25] | q36 : int(1..3)])) - | q25 : int(1..3)]) - /\ - and([!or([a_Explicit[q32] = b_Explicit[q26] | q32 : int(1..3)]) /\ b_Explicit[q26] < b_Explicit[q20] -> - toInt(or([a_Explicit[q28] = b_Explicit[q26] | q28 : int(1..3)])) = - toInt(or([b_Explicit[q30] = b_Explicit[q26] | q30 : int(1..3)])) - | q26 : int(1..3)]))) - | q20 : int(1..3)]), - and([a_Explicit[q1] < a_Explicit[q1 + 1] | q1 : int(1..2)]), - and([b_Explicit[q3] < b_Explicit[q3 + 1] | q3 : int(1..2)]), - 3 = sum([toInt(a_Occurrence[q5]) | q5 : int(1..4)]), - and([a_Occurrence[q12] -> or([a_Explicit[q14] = q12 | q14 : int(1..3)]) | q12 : int(1..4)]), - and([a_Occurrence[a_Explicit[q16]] | q16 : int(1..3)]), - 3 = sum([toInt(b_Occurrence[q6]) | q6 : int(1..4)]), - and([b_Occurrence[q7] -> or([b_Explicit[q9] = q7 | q9 : int(1..3)]) | q7 : int(1..4)]), - and([b_Occurrence[b_Explicit[q11]] | q11 : int(1..3)]) - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_2_1_2-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_2_1_2-solution000001.solution deleted file mode 100644 index 872d8190b1..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_2_1_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be {2, 3, 4} -letting b be {1, 2, 3} diff --git a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_2_1_2-solution000002.solution b/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_2_1_2-solution000002.solution deleted file mode 100644 index 28f008dddf..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_2_1_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be {2, 3, 4} -letting b be {1, 2, 4} diff --git a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_2_1_2-solution000003.solution b/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_2_1_2-solution000003.solution deleted file mode 100644 index ce716c9ad7..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_2_1_2-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be {2, 3, 4} -letting b be {1, 3, 4} diff --git a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_2_1_2-solution000004.solution b/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_2_1_2-solution000004.solution deleted file mode 100644 index 590062f44f..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_2_1_2-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be {1, 3, 4} -letting b be {1, 2, 3} diff --git a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_2_1_2-solution000005.solution b/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_2_1_2-solution000005.solution deleted file mode 100644 index 294f34ef4b..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_2_1_2-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be {1, 3, 4} -letting b be {1, 2, 4} diff --git a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_2_1_2-solution000006.solution b/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_2_1_2-solution000006.solution deleted file mode 100644 index 1b7dfb6b12..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_2_1_2-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be {1, 2, 4} -letting b be {1, 2, 3} diff --git a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_2_1_2.eprime b/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_2_1_2.eprime deleted file mode 100644 index a0324dd6ff..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_2_1_2.eprime +++ /dev/null @@ -1,41 +0,0 @@ -language ESSENCE' 1.0 - -find a_Explicit: matrix indexed by [int(1..3)] of int(1..4) -find a_Occurrence: matrix indexed by [int(1..4)] of bool -find b_Explicit: matrix indexed by [int(1..3)] of int(1..4) -branching on [a_Occurrence, a_Explicit, b_Explicit] -such that - or([toInt(or([a_Explicit[q34] = a_Explicit[q13] | q34 : int(1..3)])) < - toInt(or([b_Explicit[q36] = a_Explicit[q13] | q36 : int(1..3)])) - /\ - (and([a_Explicit[q37] < a_Explicit[q13] -> - toInt(or([a_Explicit[q46] = a_Explicit[q37] | q46 : int(1..3)])) = - toInt(or([b_Explicit[q48] = a_Explicit[q37] | q48 : int(1..3)])) - | q37 : int(1..3)]) - /\ - and([!or([a_Explicit[q44] = b_Explicit[q38] | q44 : int(1..3)]) /\ b_Explicit[q38] < a_Explicit[q13] -> - toInt(or([a_Explicit[q40] = b_Explicit[q38] | q40 : int(1..3)])) = - toInt(or([b_Explicit[q42] = b_Explicit[q38] | q42 : int(1..3)])) - | q38 : int(1..3)])) - | q13 : int(1..3)]) - \/ - or([!or([a_Explicit[q32] = b_Explicit[q14] | q32 : int(1..3)]) /\ - (toInt(or([a_Explicit[q16] = b_Explicit[q14] | q16 : int(1..3)])) < - toInt(or([b_Explicit[q18] = b_Explicit[q14] | q18 : int(1..3)])) - /\ - (and([a_Explicit[q19] < b_Explicit[q14] -> - toInt(or([a_Explicit[q28] = a_Explicit[q19] | q28 : int(1..3)])) = - toInt(or([b_Explicit[q30] = a_Explicit[q19] | q30 : int(1..3)])) - | q19 : int(1..3)]) - /\ - and([!or([a_Explicit[q26] = b_Explicit[q20] | q26 : int(1..3)]) /\ b_Explicit[q20] < b_Explicit[q14] -> - toInt(or([a_Explicit[q22] = b_Explicit[q20] | q22 : int(1..3)])) = - toInt(or([b_Explicit[q24] = b_Explicit[q20] | q24 : int(1..3)])) - | q20 : int(1..3)]))) - | q14 : int(1..3)]), - and([a_Explicit[q1] < a_Explicit[q1 + 1] | q1 : int(1..2)]), - and([b_Explicit[q3] < b_Explicit[q3 + 1] | q3 : int(1..2)]), - 3 = sum([toInt(a_Occurrence[q5]) | q5 : int(1..4)]), - and([a_Occurrence[q6] -> or([a_Explicit[q8] = q6 | q8 : int(1..3)]) | q6 : int(1..4)]), - and([a_Occurrence[a_Explicit[q10]] | q10 : int(1..3)]) - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_2_2_1-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_2_2_1-solution000001.solution deleted file mode 100644 index 1b7dfb6b12..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_2_2_1-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be {1, 2, 4} -letting b be {1, 2, 3} diff --git a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_2_2_1-solution000002.solution b/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_2_2_1-solution000002.solution deleted file mode 100644 index 294f34ef4b..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_2_2_1-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be {1, 3, 4} -letting b be {1, 2, 4} diff --git a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_2_2_1-solution000003.solution b/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_2_2_1-solution000003.solution deleted file mode 100644 index 590062f44f..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_2_2_1-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be {1, 3, 4} -letting b be {1, 2, 3} diff --git a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_2_2_1-solution000004.solution b/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_2_2_1-solution000004.solution deleted file mode 100644 index ce716c9ad7..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_2_2_1-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be {2, 3, 4} -letting b be {1, 3, 4} diff --git a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_2_2_1-solution000005.solution b/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_2_2_1-solution000005.solution deleted file mode 100644 index 28f008dddf..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_2_2_1-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be {2, 3, 4} -letting b be {1, 2, 4} diff --git a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_2_2_1-solution000006.solution b/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_2_2_1-solution000006.solution deleted file mode 100644 index 872d8190b1..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_2_2_1-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be {2, 3, 4} -letting b be {1, 2, 3} diff --git a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_2_2_1.eprime b/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_2_2_1.eprime deleted file mode 100644 index 5360883616..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_2_2_1.eprime +++ /dev/null @@ -1,41 +0,0 @@ -language ESSENCE' 1.0 - -find a_Explicit: matrix indexed by [int(1..3)] of int(1..4) -find b_Explicit: matrix indexed by [int(1..3)] of int(1..4) -find b_Occurrence: matrix indexed by [int(1..4)] of bool -branching on [a_Explicit, b_Occurrence, b_Explicit] -such that - or([toInt(or([a_Explicit[q34] = a_Explicit[q13] | q34 : int(1..3)])) < - toInt(or([b_Explicit[q36] = a_Explicit[q13] | q36 : int(1..3)])) - /\ - (and([a_Explicit[q37] < a_Explicit[q13] -> - toInt(or([a_Explicit[q46] = a_Explicit[q37] | q46 : int(1..3)])) = - toInt(or([b_Explicit[q48] = a_Explicit[q37] | q48 : int(1..3)])) - | q37 : int(1..3)]) - /\ - and([!or([a_Explicit[q44] = b_Explicit[q38] | q44 : int(1..3)]) /\ b_Explicit[q38] < a_Explicit[q13] -> - toInt(or([a_Explicit[q40] = b_Explicit[q38] | q40 : int(1..3)])) = - toInt(or([b_Explicit[q42] = b_Explicit[q38] | q42 : int(1..3)])) - | q38 : int(1..3)])) - | q13 : int(1..3)]) - \/ - or([!or([a_Explicit[q32] = b_Explicit[q14] | q32 : int(1..3)]) /\ - (toInt(or([a_Explicit[q16] = b_Explicit[q14] | q16 : int(1..3)])) < - toInt(or([b_Explicit[q18] = b_Explicit[q14] | q18 : int(1..3)])) - /\ - (and([a_Explicit[q19] < b_Explicit[q14] -> - toInt(or([a_Explicit[q28] = a_Explicit[q19] | q28 : int(1..3)])) = - toInt(or([b_Explicit[q30] = a_Explicit[q19] | q30 : int(1..3)])) - | q19 : int(1..3)]) - /\ - and([!or([a_Explicit[q26] = b_Explicit[q20] | q26 : int(1..3)]) /\ b_Explicit[q20] < b_Explicit[q14] -> - toInt(or([a_Explicit[q22] = b_Explicit[q20] | q22 : int(1..3)])) = - toInt(or([b_Explicit[q24] = b_Explicit[q20] | q24 : int(1..3)])) - | q20 : int(1..3)]))) - | q14 : int(1..3)]), - and([a_Explicit[q1] < a_Explicit[q1 + 1] | q1 : int(1..2)]), - and([b_Explicit[q3] < b_Explicit[q3 + 1] | q3 : int(1..2)]), - 3 = sum([toInt(b_Occurrence[q5]) | q5 : int(1..4)]), - and([b_Occurrence[q6] -> or([b_Explicit[q8] = q6 | q8 : int(1..3)]) | q6 : int(1..4)]), - and([b_Occurrence[b_Explicit[q10]] | q10 : int(1..3)]) - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_2_2_2-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_2_2_2-solution000001.solution deleted file mode 100644 index 1b7dfb6b12..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_2_2_2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be {1, 2, 4} -letting b be {1, 2, 3} diff --git a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_2_2_2-solution000002.solution b/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_2_2_2-solution000002.solution deleted file mode 100644 index 590062f44f..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_2_2_2-solution000002.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be {1, 3, 4} -letting b be {1, 2, 3} diff --git a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_2_2_2-solution000003.solution b/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_2_2_2-solution000003.solution deleted file mode 100644 index 294f34ef4b..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_2_2_2-solution000003.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be {1, 3, 4} -letting b be {1, 2, 4} diff --git a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_2_2_2-solution000004.solution b/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_2_2_2-solution000004.solution deleted file mode 100644 index 872d8190b1..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_2_2_2-solution000004.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be {2, 3, 4} -letting b be {1, 2, 3} diff --git a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_2_2_2-solution000005.solution b/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_2_2_2-solution000005.solution deleted file mode 100644 index 28f008dddf..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_2_2_2-solution000005.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be {2, 3, 4} -letting b be {1, 2, 4} diff --git a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_2_2_2-solution000006.solution b/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_2_2_2-solution000006.solution deleted file mode 100644 index ce716c9ad7..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_2_2_2-solution000006.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting a be {2, 3, 4} -letting b be {1, 3, 4} diff --git a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_2_2_2.eprime b/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_2_2_2.eprime deleted file mode 100644 index 6bff46d3d4..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_set_01/expected/model_2_2_2_2.eprime +++ /dev/null @@ -1,37 +0,0 @@ -language ESSENCE' 1.0 - -find a_Explicit: matrix indexed by [int(1..3)] of int(1..4) -find b_Explicit: matrix indexed by [int(1..3)] of int(1..4) -branching on [a_Explicit, b_Explicit] -such that - or([toInt(or([a_Explicit[q28] = a_Explicit[q7] | q28 : int(1..3)])) < - toInt(or([b_Explicit[q30] = a_Explicit[q7] | q30 : int(1..3)])) - /\ - (and([a_Explicit[q31] < a_Explicit[q7] -> - toInt(or([a_Explicit[q40] = a_Explicit[q31] | q40 : int(1..3)])) = - toInt(or([b_Explicit[q42] = a_Explicit[q31] | q42 : int(1..3)])) - | q31 : int(1..3)]) - /\ - and([!or([a_Explicit[q38] = b_Explicit[q32] | q38 : int(1..3)]) /\ b_Explicit[q32] < a_Explicit[q7] -> - toInt(or([a_Explicit[q34] = b_Explicit[q32] | q34 : int(1..3)])) = - toInt(or([b_Explicit[q36] = b_Explicit[q32] | q36 : int(1..3)])) - | q32 : int(1..3)])) - | q7 : int(1..3)]) - \/ - or([!or([a_Explicit[q26] = b_Explicit[q8] | q26 : int(1..3)]) /\ - (toInt(or([a_Explicit[q10] = b_Explicit[q8] | q10 : int(1..3)])) < - toInt(or([b_Explicit[q12] = b_Explicit[q8] | q12 : int(1..3)])) - /\ - (and([a_Explicit[q13] < b_Explicit[q8] -> - toInt(or([a_Explicit[q22] = a_Explicit[q13] | q22 : int(1..3)])) = - toInt(or([b_Explicit[q24] = a_Explicit[q13] | q24 : int(1..3)])) - | q13 : int(1..3)]) - /\ - and([!or([a_Explicit[q20] = b_Explicit[q14] | q20 : int(1..3)]) /\ b_Explicit[q14] < b_Explicit[q8] -> - toInt(or([a_Explicit[q16] = b_Explicit[q14] | q16 : int(1..3)])) = - toInt(or([b_Explicit[q18] = b_Explicit[q14] | q18 : int(1..3)])) - | q14 : int(1..3)]))) - | q8 : int(1..3)]), - and([a_Explicit[q1] < a_Explicit[q1 + 1] | q1 : int(1..2)]), - and([b_Explicit[q3] < b_Explicit[q3 + 1] | q3 : int(1..2)]) - From 141d70b6d07e990b1d77255d703f97568368bf76 Mon Sep 17 00:00:00 2001 From: Fraser Dunlop Date: Wed, 3 Apr 2019 08:12:51 +0100 Subject: [PATCH 073/229] symmetry ordering not working for permutation image --- src/Conjure/Representations.hs | 10 ++- src/Conjure/Rules/Horizontal/Permutation.hs | 13 ++++ src/Conjure/Rules/Vertical/Permutation.hs | 1 + src/Conjure/Rules/Vertical/Tuple.hs | 15 +++++ src/Conjure/UI/Model.hs | 4 +- .../permutation.essence | 7 ++ .../int/0010_find_perm_find_set/run.sh | 3 + .../0010_find_perm_find_set/stdout.expected | 64 +++++++++++++++++++ .../23_image_set_dotlt/runthese.sh | 1 + 9 files changed, 116 insertions(+), 2 deletions(-) create mode 100644 tests/custom/permutations/23_image_set_dotlt/int/0010_find_perm_find_set/permutation.essence create mode 100755 tests/custom/permutations/23_image_set_dotlt/int/0010_find_perm_find_set/run.sh create mode 100644 tests/custom/permutations/23_image_set_dotlt/int/0010_find_perm_find_set/stdout.expected create mode 100644 tests/custom/permutations/23_image_set_dotlt/runthese.sh diff --git a/src/Conjure/Representations.hs b/src/Conjure/Representations.hs index 54d2b70c1c..d928a0228a 100644 --- a/src/Conjure/Representations.hs +++ b/src/Conjure/Representations.hs @@ -138,6 +138,14 @@ symmetryOrdering inp = case inp of -- Constant x -> so_onConstant x -- AbstractLiteral x +-- AbstractLiteral x -> do +-- case x of +-- AbsLitTuple xs -> do +-- soVals <- sequence (symmetryOrdering <$> xs) +-- return $ make opFlatten (fromList soVals) +-- _ -> bug ("symmetryOrdering: AbstractLiteral:" <++> pretty (show inp) <++> pretty (inp)) +-- + Reference _ (Just refTo) -> do case refTo of Alias x -> symmetryOrdering x @@ -162,5 +170,5 @@ symmetryOrdering inp = xs <- symmetryOrdering body return $ make opFlatten $ Comprehension xs stmts -- x@WithLocals{} -> bug ("downX1:" <++> pretty (show x)) - _ -> bug ("symmetryOrdering:" <++> pretty (show inp)) + _ -> bug ("symmetryOrdering:" <++> pretty (show inp) <++> pretty (inp)) diff --git a/src/Conjure/Rules/Horizontal/Permutation.hs b/src/Conjure/Rules/Horizontal/Permutation.hs index e762bf663d..d260179ac0 100644 --- a/src/Conjure/Rules/Horizontal/Permutation.hs +++ b/src/Conjure/Rules/Horizontal/Permutation.hs @@ -18,6 +18,19 @@ rule_Cardinality_Literal = "permutation-cardinality-literal" `namedRule` theRule return [essence| &i |] ) +rule_Image_DotLt :: Rule +rule_Image_DotLt = "permutation-image-dotlt{AsFunction}" `namedRule` theRule where + theRule [essence| image(&p, &i) .< &q |] = do + TypePermutation inner <- typeOf p + return ( "Horizontal rule for image of permutation DotLt" + , do + (piPat, pi) <- quantifiedVar + (qiPat, qi) <- quantifiedVar + return [essence| [&pi | &piPat <- image(&p, &i)] .< [&qi | &qiPat <- &q] |] + ) + theRule _ = na "rule_Image_DotLt" + + rule_Equality :: Rule rule_Equality = "permutation-equality" `namedRule` theRule where theRule e = do diff --git a/src/Conjure/Rules/Vertical/Permutation.hs b/src/Conjure/Rules/Vertical/Permutation.hs index 71e752e6f0..ed9ba4a87b 100644 --- a/src/Conjure/Rules/Vertical/Permutation.hs +++ b/src/Conjure/Rules/Vertical/Permutation.hs @@ -59,6 +59,7 @@ rule_Comprehension = "permutation-comprehension-tuples{AsFunction}" `namedRule` theRule _ = na "rule_Comprehension" + rule_Image :: Rule rule_Image = "permutation-image{AsFunction}" `namedRule` theRule where theRule [essence| image(&p, &i) |] = do diff --git a/src/Conjure/Rules/Vertical/Tuple.hs b/src/Conjure/Rules/Vertical/Tuple.hs index 3fa6d7c263..3682deed89 100644 --- a/src/Conjure/Rules/Vertical/Tuple.hs +++ b/src/Conjure/Rules/Vertical/Tuple.hs @@ -89,6 +89,21 @@ rule_Tuple_TildeLeq = "tuple-TildeLeq" `namedRule` theRule where ) +rule_Tuple_DotLt :: Rule +rule_Tuple_DotLt = "tuple-DotLt" `namedRule` theRule where + theRule p = do + (x,y) <- match opDotLt p + TypeTuple{} <- typeOf x -- TODO: check if x and y have the same arity + TypeTuple{} <- typeOf y + xs <- downX1 x + ys <- downX1 y + return + ( "Horizontal rule for tuple .<" + , return $ decomposeLexDotLt p xs ys + ) + + + decomposeLexLt :: Expression -> [Expression] -> [Expression] -> Expression decomposeLexLt p = unroll where diff --git a/src/Conjure/UI/Model.hs b/src/Conjure/UI/Model.hs index e763dc5e80..1c95648ac0 100644 --- a/src/Conjure/UI/Model.hs +++ b/src/Conjure/UI/Model.hs @@ -1181,7 +1181,7 @@ verticalRules = , Vertical.Permutation.rule_Cardinality , Vertical.Permutation.rule_Defined , Vertical.Permutation.rule_Comprehension - , Vertical.Permutation.rule_Permutation_DotLt +-- , Vertical.Permutation.rule_Permutation_DotLt , Vertical.Tuple.rule_Tuple_Eq @@ -1191,6 +1191,7 @@ verticalRules = , Vertical.Tuple.rule_Tuple_TildeLeq , Vertical.Tuple.rule_Tuple_TildeLt , Vertical.Tuple.rule_Tuple_Index +-- , Vertical.Tuple.rule_Tuple_DotLt , Vertical.Record.rule_Record_Eq , Vertical.Record.rule_Record_Neq @@ -1292,6 +1293,7 @@ horizontalRules = [ Horizontal.Permutation.rule_Cardinality_Literal , Horizontal.Permutation.rule_Equality , Horizontal.Permutation.rule_Comprehension +-- , Horizontal.Permutation.rule_Image_DotLt , Horizontal.Permutation.rule_Compose_Image , Horizontal.Permutation.rule_Image_Matrix_Indexing , Horizontal.Permutation.rule_Image_Sequence_Literal diff --git a/tests/custom/permutations/23_image_set_dotlt/int/0010_find_perm_find_set/permutation.essence b/tests/custom/permutations/23_image_set_dotlt/int/0010_find_perm_find_set/permutation.essence new file mode 100644 index 0000000000..9344576a9b --- /dev/null +++ b/tests/custom/permutations/23_image_set_dotlt/int/0010_find_perm_find_set/permutation.essence @@ -0,0 +1,7 @@ +find p : permutation of int(1..4) + +find s : set of int(1..4) + + +such that image(p,s) .< s + diff --git a/tests/custom/permutations/23_image_set_dotlt/int/0010_find_perm_find_set/run.sh b/tests/custom/permutations/23_image_set_dotlt/int/0010_find_perm_find_set/run.sh new file mode 100755 index 0000000000..03373df6cb --- /dev/null +++ b/tests/custom/permutations/23_image_set_dotlt/int/0010_find_perm_find_set/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence --number-of-solutions=10 +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/23_image_set_dotlt/int/0010_find_perm_find_set/stdout.expected b/tests/custom/permutations/23_image_set_dotlt/int/0010_find_perm_find_set/stdout.expected new file mode 100644 index 0000000000..42291b8573 --- /dev/null +++ b/tests/custom/permutations/23_image_set_dotlt/int/0010_find_perm_find_set/stdout.expected @@ -0,0 +1,64 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Copying solution to: permutation-000001.solution +Copying solution to: permutation-000002.solution +Copying solution to: permutation-000003.solution +Copying solution to: permutation-000004.solution +Copying solution to: permutation-000005.solution +Copying solution to: permutation-000006.solution +Copying solution to: permutation-000007.solution +Copying solution to: permutation-000008.solution +Copying solution to: permutation-000009.solution +Copying solution to: permutation-000010.solution +language Essence 1.3 + +letting p be permutation((2, 3, 4)) +letting s be {} +letting sn be {} +language Essence 1.3 + +letting p be permutation((2, 3, 4)) +letting s be {4} +letting sn be {2} +language Essence 1.3 + +letting p be permutation((2, 3, 4)) +letting s be {3} +letting sn be {4} +language Essence 1.3 + +letting p be permutation((2, 3, 4)) +letting s be {3, 4} +letting sn be {2, 4} +language Essence 1.3 + +letting p be permutation((2, 3, 4)) +letting s be {2} +letting sn be {3} +language Essence 1.3 + +letting p be permutation((2, 3, 4)) +letting s be {2, 4} +letting sn be {2, 3} +language Essence 1.3 + +letting p be permutation((2, 3, 4)) +letting s be {2, 3} +letting sn be {3, 4} +language Essence 1.3 + +letting p be permutation((2, 3, 4)) +letting s be {2, 3, 4} +letting sn be {2, 3, 4} +language Essence 1.3 + +letting p be permutation((2, 3, 4)) +letting s be {1} +letting sn be {1} +language Essence 1.3 + +letting p be permutation((2, 3, 4)) +letting s be {1, 4} +letting sn be {1, 2} diff --git a/tests/custom/permutations/23_image_set_dotlt/runthese.sh b/tests/custom/permutations/23_image_set_dotlt/runthese.sh new file mode 100644 index 0000000000..19a4d4fbd4 --- /dev/null +++ b/tests/custom/permutations/23_image_set_dotlt/runthese.sh @@ -0,0 +1 @@ +stack build --copy-bins --test --test-arguments "-p custom.permutations.23" From c1c022797d50ce4b36448a79115f242f66c4309e Mon Sep 17 00:00:00 2001 From: Fraser Dunlop Date: Thu, 25 Apr 2019 12:15:13 +0100 Subject: [PATCH 074/229] record implementation for permutation image --- src/Conjure/Rules/Horizontal/Permutation.hs | 21 ++++++++++++++------- 1 file changed, 14 insertions(+), 7 deletions(-) diff --git a/src/Conjure/Rules/Horizontal/Permutation.hs b/src/Conjure/Rules/Horizontal/Permutation.hs index d260179ac0..b03e1a6b6d 100644 --- a/src/Conjure/Rules/Horizontal/Permutation.hs +++ b/src/Conjure/Rules/Horizontal/Permutation.hs @@ -21,7 +21,7 @@ rule_Cardinality_Literal = "permutation-cardinality-literal" `namedRule` theRule rule_Image_DotLt :: Rule rule_Image_DotLt = "permutation-image-dotlt{AsFunction}" `namedRule` theRule where theRule [essence| image(&p, &i) .< &q |] = do - TypePermutation inner <- typeOf p + TypePermutation _ <- typeOf p return ( "Horizontal rule for image of permutation DotLt" , do (piPat, pi) <- quantifiedVar @@ -181,14 +181,13 @@ rule_Image_Sequence_Literal :: Rule rule_Image_Sequence_Literal = "image-permutation-sequence-literal" `namedRule` theRule where theRule expr = do (perm,seq) <- match opImage expr - (TypeSequence t, elems) <- match sequenceLiteral seq - (TypePermutation inn) <- typeOf perm + (TypeSequence _, elems) <- match sequenceLiteral seq + (TypePermutation _) <- typeOf perm let outLiteral = AbstractLiteral $ AbsLitSequence [ [essence| image(&perm,&e) |] | e <- elems ] return ( "Comprehension on permutation image of sequence literals" , return [essence| &outLiteral |] ) - theRule _ = na "rule_Image_Sequence_Literal" @@ -289,11 +288,19 @@ rule_Image_Incomprehendable = "comprehendable-image" `namedRule` theRule where tupleExpression = AbstractLiteral $ AbsLitTuple $ (tupleIndexImage <$> [1..(fromIntegral $ length tint)]) return - ( "Horizontal rule for image of incomprehendable under permutation" + ( "Horizontal rule for image of tuple under permutation" , return tupleExpression ) - (TypeRecord _) -> - bug "rule_Image_Incomprehendable not implemented for Record" + (TypeRecord namet) -> do + let names = fst <$> namet + recordIndexImage indx = let indexexpr = patternToExpr $ Single indx + in (indx, [essence| image(&p, &i[&indexexpr]) |]) + recordExpression = AbstractLiteral $ AbsLitRecord + $ (recordIndexImage <$> names) + return + ( "Horizontal rule for image of record under permutation" + , return recordExpression + ) (TypeVariant _) -> bug "rule_Image_Incomprehendable not implemented for Variant" _ -> bug "rule_Image_Incomprehendable this is a bug" From 0283cabcfe87f2f9fda51c5c759efdd29dee1378 Mon Sep 17 00:00:00 2001 From: Fraser Dunlop Date: Thu, 2 May 2019 13:01:59 +0100 Subject: [PATCH 075/229] remove flatten from symmetryOrdering for Matrix --- src/Conjure/Representations/Matrix.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Conjure/Representations/Matrix.hs b/src/Conjure/Representations/Matrix.hs index 33f73d1745..2aa444e0d0 100644 --- a/src/Conjure/Representations/Matrix.hs +++ b/src/Conjure/Representations/Matrix.hs @@ -202,5 +202,5 @@ matrix downD1 downC1 up1 = Representation chck matrixDownD structuralCons matrix (iPat, i) <- quantifiedVarOverDomain indexDom let mi = [essence| &inp[&i] |] res <- innerSO downX1 mi innerDom - return [essence| flatten([ &res | &iPat : &indexDom ]) |] + return [essence| [ &res | &iPat : &indexDom ] |] _ -> bug $ "symmetryOrdering matrix" <+> pretty inp <+> pretty domain From 29a9d43fd9de668441d703e8b14d474d8fcaf7b7 Mon Sep 17 00:00:00 2001 From: Fraser Dunlop Date: Thu, 2 May 2019 13:04:35 +0100 Subject: [PATCH 076/229] remove flatten on set explicit --- src/Conjure/Representations/Set/Explicit.hs | 6 +++--- 1 file changed, 3 insertions(+), 3 deletions(-) diff --git a/src/Conjure/Representations/Set/Explicit.hs b/src/Conjure/Representations/Set/Explicit.hs index a45af68965..ee5efa1f9e 100644 --- a/src/Conjure/Representations/Set/Explicit.hs +++ b/src/Conjure/Representations/Set/Explicit.hs @@ -114,7 +114,7 @@ setExplicit = Representation chck downD structuralCons downC up symmetryOrdering soValues <- innerSO downX1 [essence| &values[&i] |] inner return [essence| - flatten([ &soValues - | &iPat : &index - ]) + [ &soValues + | &iPat : &index + ] |] From 54386ea9a8734ac4657e6fe520b58ad28a9bdb1b Mon Sep 17 00:00:00 2001 From: Fraser Dunlop Date: Thu, 2 May 2019 13:25:48 +0100 Subject: [PATCH 077/229] explicit var size with flags symmetry now tuple --- .../Representations/Set/ExplicitVarSizeWithFlags.hs | 8 +++----- 1 file changed, 3 insertions(+), 5 deletions(-) diff --git a/src/Conjure/Representations/Set/ExplicitVarSizeWithFlags.hs b/src/Conjure/Representations/Set/ExplicitVarSizeWithFlags.hs index 5e5bc22f9f..e308094539 100644 --- a/src/Conjure/Representations/Set/ExplicitVarSizeWithFlags.hs +++ b/src/Conjure/Representations/Set/ExplicitVarSizeWithFlags.hs @@ -193,9 +193,7 @@ setExplicitVarSizeWithFlags = Representation chck downD structuralCons downC up soValues <- innerSO downX1 [essence| &values[&i] |] inner return [essence| - flatten([ flatten([ [-toInt(&flags[&i])] - , &soValues - ]) - | &iPat : &index - ]) + (&flags + ,[&soValues | &iPat : &index] + ) |] From 214c2ac83bc674ca966ce9fc4f41245a7ada8031 Mon Sep 17 00:00:00 2001 From: Fraser Dunlop Date: Fri, 3 May 2019 13:26:33 +0100 Subject: [PATCH 078/229] a handful of changes in the name of symmetryOrder --- src/Conjure/Language/Expression/Op/LexLeq.hs | 2 +- src/Conjure/Language/Expression/Op/LexLt.hs | 2 +- .../Representations/Function/Function1D.hs | 6 +- .../Function/Function1DPartial.hs | 12 ++-- .../Representations/Function/FunctionND.hs | 2 +- .../Function/FunctionNDPartial.hs | 8 +-- .../Representations/MSet/ExplicitWithFlags.hs | 10 +-- .../MSet/ExplicitWithRepetition.hs | 10 +-- .../Representations/Partition/Occurrence.hs | 2 +- src/Conjure/Representations/Primitive.hs | 4 +- src/Conjure/Representations/Record.hs | 2 +- .../Sequence/ExplicitBounded.hs | 10 +-- .../Set/ExplicitVarSizeWithDummy.hs | 12 +++- .../Set/ExplicitVarSizeWithFlags.hs | 4 +- .../Set/ExplicitVarSizeWithMarker.hs | 10 +-- src/Conjure/Representations/Tuple.hs | 2 +- src/Conjure/Representations/Variant.hs | 2 +- src/Conjure/Rules/Vertical/Tuple.hs | 61 +++++++++++++++++++ src/Conjure/UI/Model.hs | 24 +++++++- 19 files changed, 136 insertions(+), 49 deletions(-) diff --git a/src/Conjure/Language/Expression/Op/LexLeq.hs b/src/Conjure/Language/Expression/Op/LexLeq.hs index 56ec40104b..78b3f61b90 100644 --- a/src/Conjure/Language/Expression/Op/LexLeq.hs +++ b/src/Conjure/Language/Expression/Op/LexLeq.hs @@ -25,7 +25,7 @@ instance (TypeOf x, Pretty x) => TypeOf (OpLexLeq x) where typeOf p@(OpLexLeq a b) = do tyA <- typeOf a tyB <- typeOf b - if typesUnify [TypeList TypeAny, tyA, tyB] + if typesUnify [tyA, tyB] then return TypeBool else raiseTypeError $ vcat [ pretty p , "LHS has type:" <+> pretty tyA diff --git a/src/Conjure/Language/Expression/Op/LexLt.hs b/src/Conjure/Language/Expression/Op/LexLt.hs index 8c264f7797..fc84591e26 100644 --- a/src/Conjure/Language/Expression/Op/LexLt.hs +++ b/src/Conjure/Language/Expression/Op/LexLt.hs @@ -25,7 +25,7 @@ instance (TypeOf x, Pretty x) => TypeOf (OpLexLt x) where typeOf p@(OpLexLt a b) = do tyA <- typeOf a tyB <- typeOf b - if typesUnify [TypeList TypeAny, tyA, tyB] + if typesUnify [tyA, tyB] then return TypeBool else raiseTypeError $ vcat [ pretty p , "LHS has type:" <+> pretty tyA diff --git a/src/Conjure/Representations/Function/Function1D.hs b/src/Conjure/Representations/Function/Function1D.hs index 72292053f9..50c81d9273 100644 --- a/src/Conjure/Representations/Function/Function1D.hs +++ b/src/Conjure/Representations/Function/Function1D.hs @@ -186,9 +186,9 @@ function1D = Representation chck downD structuralCons downC up symmetryOrdering soValues <- innerSO downX1 [essence| &values[&i] |] innerDomainTo return [essence| - flatten([ &soValues - | &iPat : &innerDomainFr - ]) + [ &soValues + | &iPat : &innerDomainFr + ] |] diff --git a/src/Conjure/Representations/Function/Function1DPartial.hs b/src/Conjure/Representations/Function/Function1DPartial.hs index 99a95b62fe..485b08d1fa 100644 --- a/src/Conjure/Representations/Function/Function1DPartial.hs +++ b/src/Conjure/Representations/Function/Function1DPartial.hs @@ -213,9 +213,9 @@ function1DPartial = Representation chck downD structuralCons downC up symmetryOr soValues <- innerSO downX1 [essence| &values[&i] |] innerDomainTo return [essence| - flatten([ flatten([ [-toInt(&flags[&i])] - , &soValues - ]) - | &iPat : &innerDomainFr - ]) - |] \ No newline at end of file + [ ( -toInt(&flags[&i]) + , &soValues + ) + | &iPat : &innerDomainFr + ] + |] diff --git a/src/Conjure/Representations/Function/FunctionND.hs b/src/Conjure/Representations/Function/FunctionND.hs index 375ab90921..64553d4574 100644 --- a/src/Conjure/Representations/Function/FunctionND.hs +++ b/src/Conjure/Representations/Function/FunctionND.hs @@ -250,7 +250,7 @@ functionND = Representation chck downD structuralCons downC up symmetryOrdering soValues <- innerSO downX1 valuesIndexed innerDomainTo - return $ make opFlatten $ + return $ Comprehension soValues [Generator (GenDomainNoRepr iPat (forgetRepr innerDomainFr))] diff --git a/src/Conjure/Representations/Function/FunctionNDPartial.hs b/src/Conjure/Representations/Function/FunctionNDPartial.hs index c3b4db06b1..f5c483d806 100644 --- a/src/Conjure/Representations/Function/FunctionNDPartial.hs +++ b/src/Conjure/Representations/Function/FunctionNDPartial.hs @@ -296,10 +296,10 @@ functionNDPartial = Representation chck downD structuralCons downC up symmetryOr soValues <- innerSO downX1 valuesIndexed innerDomainTo - return $ make opFlatten $ + return $ Comprehension - [essence| flatten([ [-&flagsIndexed] - , &soValues - ]) + [essence| ( -&flagsIndexed + , &soValues + ) |] [Generator (GenDomainNoRepr iPat (forgetRepr innerDomainFr))] diff --git a/src/Conjure/Representations/MSet/ExplicitWithFlags.hs b/src/Conjure/Representations/MSet/ExplicitWithFlags.hs index 8363b63b8b..b6debf9f01 100644 --- a/src/Conjure/Representations/MSet/ExplicitWithFlags.hs +++ b/src/Conjure/Representations/MSet/ExplicitWithFlags.hs @@ -211,9 +211,9 @@ msetExplicitWithFlags = Representation chck downD structuralCons downC up symmet soValues <- innerSO downX1 [essence| &values[&i] |] inner return [essence| - flatten([ flatten([ [-&flags[&i]] - , &soValues - ]) - | &iPat : &index - ]) + [ [ -&flags[&i] + , &soValues + ] + | &iPat : &index + ] |] diff --git a/src/Conjure/Representations/MSet/ExplicitWithRepetition.hs b/src/Conjure/Representations/MSet/ExplicitWithRepetition.hs index 36521907e8..73ce9a0fc3 100644 --- a/src/Conjure/Representations/MSet/ExplicitWithRepetition.hs +++ b/src/Conjure/Representations/MSet/ExplicitWithRepetition.hs @@ -228,9 +228,9 @@ msetExplicitWithRepetition = Representation chck downD structuralCons downC up s soValues <- innerSO downX1 [essence| &values[&i] |] inner return [essence| - flatten([ [ &marker ] - , flatten([ &soValues - | &iPat : &index - ]) - ]) + ( &marker + , [ &soValues + | &iPat : &index + ] + ) |] diff --git a/src/Conjure/Representations/Partition/Occurrence.hs b/src/Conjure/Representations/Partition/Occurrence.hs index 3b369d18a5..6c715a52d5 100644 --- a/src/Conjure/Representations/Partition/Occurrence.hs +++ b/src/Conjure/Representations/Partition/Occurrence.hs @@ -323,4 +323,4 @@ partitionOccurrence = Representation chck downD structuralCons downC up symmetry Just xsDoms' <- downD ("SO", domain) let xsDoms = map snd xsDoms' soValues <- sequence [ innerSO downX1 x xDom | (x, xDom) <- zip xs xsDoms ] - return $ make opFlatten (fromList soValues) + return (fromList soValues) diff --git a/src/Conjure/Representations/Primitive.hs b/src/Conjure/Representations/Primitive.hs index 49642c4fcc..68cc1b8a9c 100644 --- a/src/Conjure/Representations/Primitive.hs +++ b/src/Conjure/Representations/Primitive.hs @@ -30,7 +30,7 @@ primitive = Representation Just c -> return (name, c) , rSymmetryOrdering = \ _innerSO _downX1 inp domain -> return $ case domain of - DomainBool -> [essence| [-toInt(&inp)] |] - _ -> [essence| [&inp] |] + DomainBool -> [essence| -toInt(&inp) |] + _ -> [essence| &inp |] } diff --git a/src/Conjure/Representations/Record.hs b/src/Conjure/Representations/Record.hs index 6dd888065e..4394916e45 100644 --- a/src/Conjure/Representations/Record.hs +++ b/src/Conjure/Representations/Record.hs @@ -83,4 +83,4 @@ record = Representation chck downD structuralCons downC up symmetryOrdering Just xsDoms' <- downD ("SO", domain) let xsDoms = map snd xsDoms' soValues <- sequence [ innerSO downX1 x xDom | (x, xDom) <- zip xs xsDoms ] - return $ make opFlatten (fromList soValues) + return (fromList soValues) diff --git a/src/Conjure/Representations/Sequence/ExplicitBounded.hs b/src/Conjure/Representations/Sequence/ExplicitBounded.hs index 4d0f3a2a54..b67b54829d 100644 --- a/src/Conjure/Representations/Sequence/ExplicitBounded.hs +++ b/src/Conjure/Representations/Sequence/ExplicitBounded.hs @@ -289,9 +289,9 @@ sequenceExplicitBounded = Representation chck downD structuralCons downC up symm soValues <- innerSO downX1 [essence| &values[&i] |] inner return [essence| - flatten([ [ &marker ] - , flatten([ &soValues - | &iPat : &index - ]) - ]) + ( &marker + , [ &soValues + | &iPat : &index + ] + ) |] diff --git a/src/Conjure/Representations/Set/ExplicitVarSizeWithDummy.hs b/src/Conjure/Representations/Set/ExplicitVarSizeWithDummy.hs index 085c14bbed..c8b3efac58 100644 --- a/src/Conjure/Representations/Set/ExplicitVarSizeWithDummy.hs +++ b/src/Conjure/Representations/Set/ExplicitVarSizeWithDummy.hs @@ -168,8 +168,14 @@ setExplicitVarSizeWithDummy = Representation chck downD structuralCons downC up up _ _ = na "{up} ExplicitVarSizeWithDummy" symmetryOrdering :: TypeOf_SymmetryOrdering m - symmetryOrdering _innerSO downX1 inp domain = do + symmetryOrdering innerSO downX1 inp domain = do [values] <- downX1 inp - Just [(_, DomainMatrix index _inner)] <- downD ("SO", domain) + Just [(_, DomainMatrix index inner)] <- downD ("SO", domain) (iPat, i) <- quantifiedVar - return [essence| [ &values[&i] | &iPat : &index ] |] + soValues <- innerSO downX1 [essence| &values[&i] |] inner + return + [essence| + [ &soValues + | &iPat : &index + ] + |] diff --git a/src/Conjure/Representations/Set/ExplicitVarSizeWithFlags.hs b/src/Conjure/Representations/Set/ExplicitVarSizeWithFlags.hs index e308094539..6923712e79 100644 --- a/src/Conjure/Representations/Set/ExplicitVarSizeWithFlags.hs +++ b/src/Conjure/Representations/Set/ExplicitVarSizeWithFlags.hs @@ -193,7 +193,5 @@ setExplicitVarSizeWithFlags = Representation chck downD structuralCons downC up soValues <- innerSO downX1 [essence| &values[&i] |] inner return [essence| - (&flags - ,[&soValues | &iPat : &index] - ) + [ (&flags[&i], &soValues) | &iPat : &index] |] diff --git a/src/Conjure/Representations/Set/ExplicitVarSizeWithMarker.hs b/src/Conjure/Representations/Set/ExplicitVarSizeWithMarker.hs index 4f2e75b69b..726fb2d000 100644 --- a/src/Conjure/Representations/Set/ExplicitVarSizeWithMarker.hs +++ b/src/Conjure/Representations/Set/ExplicitVarSizeWithMarker.hs @@ -166,9 +166,9 @@ setExplicitVarSizeWithMarker = Representation chck downD structuralCons downC up soValues <- innerSO downX1 [essence| &values[&i] |] inner return [essence| - flatten([ [ &marker ] - , flatten([ &soValues - | &iPat : &index - ]) - ]) + ( &marker + ,[ &soValues + | &iPat : &index + ] + ) |] diff --git a/src/Conjure/Representations/Tuple.hs b/src/Conjure/Representations/Tuple.hs index 235f3181ee..aaca054cd3 100644 --- a/src/Conjure/Representations/Tuple.hs +++ b/src/Conjure/Representations/Tuple.hs @@ -83,4 +83,4 @@ tuple = Representation chck downD structuralCons downC up symmetryOrdering Just xsDoms' <- downD ("SO", domain) let xsDoms = map snd xsDoms' soValues <- sequence [ innerSO downX1 x xDom | (x, xDom) <- zip xs xsDoms ] - return $ make opFlatten (fromList soValues) + return (fromList soValues) diff --git a/src/Conjure/Representations/Variant.hs b/src/Conjure/Representations/Variant.hs index b898404603..3cd839b741 100644 --- a/src/Conjure/Representations/Variant.hs +++ b/src/Conjure/Representations/Variant.hs @@ -121,4 +121,4 @@ variant = Representation chck downD structuralCons downC up symmetryOrdering Just xsDoms' <- downD ("SO", domain) let xsDoms = map snd xsDoms' soValues <- sequence [ innerSO downX1 x xDom | (x, xDom) <- zip xs xsDoms ] - return $ make opFlatten (fromList soValues) + return (fromList soValues) diff --git a/src/Conjure/Rules/Vertical/Tuple.hs b/src/Conjure/Rules/Vertical/Tuple.hs index 3682deed89..ca74ee51cb 100644 --- a/src/Conjure/Rules/Vertical/Tuple.hs +++ b/src/Conjure/Rules/Vertical/Tuple.hs @@ -103,6 +103,67 @@ rule_Tuple_DotLt = "tuple-DotLt" `namedRule` theRule where ) +rule_Tuple_DotLeq :: Rule +rule_Tuple_DotLeq = "tuple-DotLeq" `namedRule` theRule where + theRule p = do + (x,y) <- match opDotLeq p + TypeTuple{} <- typeOf x -- TODO: check if x and y have the same arity + TypeTuple{} <- typeOf y + xs <- downX1 x + ys <- downX1 y + return + ( "Horizontal rule for tuple .<=" + , return $ decomposeLexDotLeq p xs ys + ) + + +rule_Tuple_LexLt :: Rule +rule_Tuple_LexLt = "tuple-LexLt" `namedRule` theRule where + theRule [essence| &x [Expression] -> [Expression] -> Expression +decomposeLexLexLt p = unroll + where + unroll [a] [b] = [essence| &a pretty p) + +decomposeLexLexLeq :: Expression -> [Expression] -> [Expression] -> Expression +decomposeLexLexLeq p = unroll + where + unroll [a] [b] = [essence| &a <=lex &b |] + unroll (a:as) (b:bs) = let rest = unroll as bs + in [essence| (&a <=lex &b) /\ &rest |] + unroll _ _ = bug ("arity mismatch in:" <+> pretty p) + + decomposeLexLt :: Expression -> [Expression] -> [Expression] -> Expression decomposeLexLt p = unroll diff --git a/src/Conjure/UI/Model.hs b/src/Conjure/UI/Model.hs index 1c95648ac0..1c6488e41a 100644 --- a/src/Conjure/UI/Model.hs +++ b/src/Conjure/UI/Model.hs @@ -1191,7 +1191,12 @@ verticalRules = , Vertical.Tuple.rule_Tuple_TildeLeq , Vertical.Tuple.rule_Tuple_TildeLt , Vertical.Tuple.rule_Tuple_Index --- , Vertical.Tuple.rule_Tuple_DotLt + , Vertical.Tuple.rule_Tuple_DotLt + , Vertical.Tuple.rule_Tuple_DotLeq + , Vertical.Tuple.rule_Tuple_LexLt + , Vertical.Tuple.rule_Tuple_LexLeq + + , Vertical.Record.rule_Record_Eq , Vertical.Record.rule_Record_Neq @@ -1497,6 +1502,7 @@ delayedRules = , [ rule_ReducerToComprehension ] , [ rule_DotLtLeq + , rule_DotLtLeqLexPrim ] ] @@ -1848,6 +1854,22 @@ rule_Neq = "identical-domain-neq" `namedRule` theRule where , return $ make opOr $ fromList $ zipWith (\ i j -> [essence| &i != &j |] ) xs ys ) +rule_DotLtLeqLexPrim :: Rule +rule_DotLtLeqLexPrim = "int-DotLtLeq" `namedRule` theRule where + theRule p = do + (a,b,mk) <- case p of + [essence| &a return (a,b,\i j -> [essence| [&i] return (a,b,\i j -> [essence| [&i] <=lex [&j] |]) + _ -> na "rule_DotLtLeqLexPrim" + t <- typeOf a + case t of + TypeInt{} -> return () + TypeBool -> return () + _ -> na "rule_DotLtLeqLexPrim" + return ( "Rule for dotLt and dotLeq on primitives:" <+> pretty p + , return $ mk a b + ) + rule_DotLtLeq :: Rule rule_DotLtLeq = "generic-DotLtLeq" `namedRule` theRule where From ba0377d8359f2aa35b4ee6b6005366269fefc1c2 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?O=CC=88zgu=CC=88r=20Akgu=CC=88n?= Date: Fri, 3 May 2019 15:26:51 +0100 Subject: [PATCH 079/229] We now handle symmetryOrder on image(perm,x) - image(perm, [comprehension]) doesn't seem to work at the moment --- src/Conjure/Representations.hs | 3 ++ src/Conjure/Rules/Horizontal/Function.hs | 2 + src/Conjure/Rules/Vertical/Tuple.hs | 58 ------------------------ src/Conjure/UI/Model.hs | 25 +--------- 4 files changed, 6 insertions(+), 82 deletions(-) diff --git a/src/Conjure/Representations.hs b/src/Conjure/Representations.hs index d928a0228a..e15916561a 100644 --- a/src/Conjure/Representations.hs +++ b/src/Conjure/Representations.hs @@ -165,6 +165,9 @@ symmetryOrdering inp = case mDom of DomainMatrix _ domainInner -> symmetryOrderingDispatch downX1 inp domainInner _ -> bug ("symmetryOrdering, not DomainMatrix:" <++> pretty (show op)) + MkOpImage (OpImage p x) -> do + so <- symmetryOrdering x + return [essence| image(&p, &so) |] _ -> bug ("symmetryOrdering, no OpIndexing:" <++> pretty (show op)) Comprehension body stmts -> do xs <- symmetryOrdering body diff --git a/src/Conjure/Rules/Horizontal/Function.hs b/src/Conjure/Rules/Horizontal/Function.hs index deb9781c43..f8ab546832 100644 --- a/src/Conjure/Rules/Horizontal/Function.hs +++ b/src/Conjure/Rules/Horizontal/Function.hs @@ -690,6 +690,7 @@ rule_Image_Matrix_LexLhs = "function-image-matrix-lexlhs" `namedRule` theRule wh theRule p = do (mkLex, (lhs,rhs)) <- match opLex p (func, arg) <- match opImage lhs + TypeFunction{} <- typeOf func return ( "Function image, matrix as an argument to a lex operator." , do @@ -709,6 +710,7 @@ rule_Image_Matrix_LexRhs = "function-image-matrix-lexrhs" `namedRule` theRule wh theRule p = do (mkLex, (lhs,rhs)) <- match opLex p (func, arg) <- match opImage rhs + TypeFunction{} <- typeOf func return ( "Function image, matrix as an argument to a lex operator." , do diff --git a/src/Conjure/Rules/Vertical/Tuple.hs b/src/Conjure/Rules/Vertical/Tuple.hs index ca74ee51cb..c18edce74a 100644 --- a/src/Conjure/Rules/Vertical/Tuple.hs +++ b/src/Conjure/Rules/Vertical/Tuple.hs @@ -89,64 +89,6 @@ rule_Tuple_TildeLeq = "tuple-TildeLeq" `namedRule` theRule where ) -rule_Tuple_DotLt :: Rule -rule_Tuple_DotLt = "tuple-DotLt" `namedRule` theRule where - theRule p = do - (x,y) <- match opDotLt p - TypeTuple{} <- typeOf x -- TODO: check if x and y have the same arity - TypeTuple{} <- typeOf y - xs <- downX1 x - ys <- downX1 y - return - ( "Horizontal rule for tuple .<" - , return $ decomposeLexDotLt p xs ys - ) - - -rule_Tuple_DotLeq :: Rule -rule_Tuple_DotLeq = "tuple-DotLeq" `namedRule` theRule where - theRule p = do - (x,y) <- match opDotLeq p - TypeTuple{} <- typeOf x -- TODO: check if x and y have the same arity - TypeTuple{} <- typeOf y - xs <- downX1 x - ys <- downX1 y - return - ( "Horizontal rule for tuple .<=" - , return $ decomposeLexDotLeq p xs ys - ) - - -rule_Tuple_LexLt :: Rule -rule_Tuple_LexLt = "tuple-LexLt" `namedRule` theRule where - theRule [essence| &x [Expression] -> [Expression] -> Expression decomposeLexLexLt p = unroll where diff --git a/src/Conjure/UI/Model.hs b/src/Conjure/UI/Model.hs index 1c6488e41a..62da0a80bc 100644 --- a/src/Conjure/UI/Model.hs +++ b/src/Conjure/UI/Model.hs @@ -1181,7 +1181,7 @@ verticalRules = , Vertical.Permutation.rule_Cardinality , Vertical.Permutation.rule_Defined , Vertical.Permutation.rule_Comprehension --- , Vertical.Permutation.rule_Permutation_DotLt + -- , Vertical.Permutation.rule_Permutation_DotLt , Vertical.Tuple.rule_Tuple_Eq @@ -1191,10 +1191,6 @@ verticalRules = , Vertical.Tuple.rule_Tuple_TildeLeq , Vertical.Tuple.rule_Tuple_TildeLt , Vertical.Tuple.rule_Tuple_Index - , Vertical.Tuple.rule_Tuple_DotLt - , Vertical.Tuple.rule_Tuple_DotLeq - , Vertical.Tuple.rule_Tuple_LexLt - , Vertical.Tuple.rule_Tuple_LexLeq @@ -1298,10 +1294,8 @@ horizontalRules = [ Horizontal.Permutation.rule_Cardinality_Literal , Horizontal.Permutation.rule_Equality , Horizontal.Permutation.rule_Comprehension --- , Horizontal.Permutation.rule_Image_DotLt , Horizontal.Permutation.rule_Compose_Image , Horizontal.Permutation.rule_Image_Matrix_Indexing - , Horizontal.Permutation.rule_Image_Sequence_Literal -- , Horizontal.Permutation.rule_Image_Matrix_Indexing_Comprehension -- , Horizontal.Permutation.rule_Compose , Horizontal.Permutation.rule_Image_Literal @@ -1502,7 +1496,6 @@ delayedRules = , [ rule_ReducerToComprehension ] , [ rule_DotLtLeq - , rule_DotLtLeqLexPrim ] ] @@ -1854,22 +1847,6 @@ rule_Neq = "identical-domain-neq" `namedRule` theRule where , return $ make opOr $ fromList $ zipWith (\ i j -> [essence| &i != &j |] ) xs ys ) -rule_DotLtLeqLexPrim :: Rule -rule_DotLtLeqLexPrim = "int-DotLtLeq" `namedRule` theRule where - theRule p = do - (a,b,mk) <- case p of - [essence| &a return (a,b,\i j -> [essence| [&i] return (a,b,\i j -> [essence| [&i] <=lex [&j] |]) - _ -> na "rule_DotLtLeqLexPrim" - t <- typeOf a - case t of - TypeInt{} -> return () - TypeBool -> return () - _ -> na "rule_DotLtLeqLexPrim" - return ( "Rule for dotLt and dotLeq on primitives:" <+> pretty p - , return $ mk a b - ) - rule_DotLtLeq :: Rule rule_DotLtLeq = "generic-DotLtLeq" `namedRule` theRule where From 38cd76b202318becec24ba01a8b23ea24915ead8 Mon Sep 17 00:00:00 2001 From: Fraser Dunlop Date: Fri, 3 May 2019 18:24:13 +0100 Subject: [PATCH 080/229] Rule for permutation image of comprehension --- src/Conjure/Rules/Horizontal/Permutation.hs | 40 ++++++++++++++++++++- src/Conjure/UI/Model.hs | 1 + 2 files changed, 40 insertions(+), 1 deletion(-) diff --git a/src/Conjure/Rules/Horizontal/Permutation.hs b/src/Conjure/Rules/Horizontal/Permutation.hs index b03e1a6b6d..71a80ab0a7 100644 --- a/src/Conjure/Rules/Horizontal/Permutation.hs +++ b/src/Conjure/Rules/Horizontal/Permutation.hs @@ -3,7 +3,6 @@ module Conjure.Rules.Horizontal.Permutation where import Conjure.Rules.Import import Data.Permutation (size, fromCycles, toFunction) - rule_Cardinality_Literal :: Rule rule_Cardinality_Literal = "permutation-cardinality-literal" `namedRule` theRule where theRule p' = do @@ -149,6 +148,45 @@ rule_Compose_Image = "permutation-compose-image" `namedRule` theRule where else na "rule_Compose_Image" theRule _ = na "rule_Compose_Image" +rule_Image_Comprehension :: Rule +rule_Image_Comprehension = "comprehension-image" `namedRule` theRule where + theRule x = do + (perm, Comprehension body gensOrConds) <- match opImage x + TypePermutation{} <- typeOf perm + return ( "Horizontal rule for image of comprehension" + , do + gox <- sequence (permutationOverGenOrCond perm <$> gensOrConds) + return $ Comprehension [essence| image(&perm, &body) |] (join gox) + ) + -- permutationOverGenOrCond :: Expression + -- -> GeneratorOrCondition + -- -> m [GeneratorOrCondition] + permutationOverGenOrCond p (Generator g) = permutationOverGenerator p g + permutationOverGenOrCond p (Condition e) = return [Condition [essence| image(&p,&e) |]] + permutationOverGenOrCond p (ComprehensionLetting n e) = + return [ComprehensionLetting n [essence| image(&p,&e) |]] +-- permutationOverGenerator :: Expression +-- -> Generator +-- -> m [GeneratorOrCondition] + permutationOverGenerator p (GenDomainNoRepr (Single a) d) = do + (nPat, n) <- quantifiedVar + return [Generator (GenDomainNoRepr nPat d) + ,ComprehensionLetting a [essence| image(&p, &n) |] + ] + permutationOverGenerator _ (GenDomainNoRepr _ _) = do + na "permutationOverGenerator: absPat" + --TODO not sure what to do with the other absPats + permutationOverGenerator p (GenDomainHasRepr a d) = do + (Single nm, n) <- quantifiedVar + return [Generator (GenDomainHasRepr nm d) + ,ComprehensionLetting a [essence| image(&p, &n) |] + ] + permutationOverGenerator p (GenInExpr a e) = + return [Generator (GenInExpr a [essence| image(&p,&e) |])] + + + + rule_Image_Comprehendable :: Rule rule_Image_Comprehendable = "comprehendable-image" `namedRule` theRule where diff --git a/src/Conjure/UI/Model.hs b/src/Conjure/UI/Model.hs index 62da0a80bc..c6d443c9b8 100644 --- a/src/Conjure/UI/Model.hs +++ b/src/Conjure/UI/Model.hs @@ -1296,6 +1296,7 @@ horizontalRules = , Horizontal.Permutation.rule_Comprehension , Horizontal.Permutation.rule_Compose_Image , Horizontal.Permutation.rule_Image_Matrix_Indexing + , Horizontal.Permutation.rule_Image_Comprehension -- , Horizontal.Permutation.rule_Image_Matrix_Indexing_Comprehension -- , Horizontal.Permutation.rule_Compose , Horizontal.Permutation.rule_Image_Literal From f55dc62f43317d437c09c54a76dab1354b9d134d Mon Sep 17 00:00:00 2001 From: Fraser Dunlop Date: Sat, 4 May 2019 15:35:22 +0100 Subject: [PATCH 081/229] support abstract patterns in comprehension permutation image --- src/Conjure/Rules/Horizontal/Permutation.hs | 39 +++++++++++++---- .../permutation.essence | 2 +- .../0010_find_perm_find_set/stdout.expected | 42 +++++++------------ 3 files changed, 48 insertions(+), 35 deletions(-) diff --git a/src/Conjure/Rules/Horizontal/Permutation.hs b/src/Conjure/Rules/Horizontal/Permutation.hs index 71a80ab0a7..3ba6afb468 100644 --- a/src/Conjure/Rules/Horizontal/Permutation.hs +++ b/src/Conjure/Rules/Horizontal/Permutation.hs @@ -158,6 +158,7 @@ rule_Image_Comprehension = "comprehension-image" `namedRule` theRule where gox <- sequence (permutationOverGenOrCond perm <$> gensOrConds) return $ Comprehension [essence| image(&perm, &body) |] (join gox) ) + -- permutationOverGenOrCond :: Expression -- -> GeneratorOrCondition -- -> m [GeneratorOrCondition] @@ -165,17 +166,10 @@ rule_Image_Comprehension = "comprehension-image" `namedRule` theRule where permutationOverGenOrCond p (Condition e) = return [Condition [essence| image(&p,&e) |]] permutationOverGenOrCond p (ComprehensionLetting n e) = return [ComprehensionLetting n [essence| image(&p,&e) |]] + -- permutationOverGenerator :: Expression -- -> Generator -- -> m [GeneratorOrCondition] - permutationOverGenerator p (GenDomainNoRepr (Single a) d) = do - (nPat, n) <- quantifiedVar - return [Generator (GenDomainNoRepr nPat d) - ,ComprehensionLetting a [essence| image(&p, &n) |] - ] - permutationOverGenerator _ (GenDomainNoRepr _ _) = do - na "permutationOverGenerator: absPat" - --TODO not sure what to do with the other absPats permutationOverGenerator p (GenDomainHasRepr a d) = do (Single nm, n) <- quantifiedVar return [Generator (GenDomainHasRepr nm d) @@ -183,6 +177,35 @@ rule_Image_Comprehension = "comprehension-image" `namedRule` theRule where ] permutationOverGenerator p (GenInExpr a e) = return [Generator (GenInExpr a [essence| image(&p,&e) |])] + permutationOverGenerator p (GenDomainNoRepr absPat d) = do + (rPat, ns) <- clonePattern absPat + return $ [Generator (GenDomainNoRepr rPat d)] + ++ ((\(pat,exp) -> + ComprehensionLetting pat [essence| image(&p,&exp) |] + ) <$> ns) + +-- clonePattern :: AbstractPattern +-- -> m (AbstractPattern, [(Namr, Expression)]) + clonePattern (Single name) = do + (nPat, n) <- quantifiedVar + return (nPat,[(name, n)]) + clonePattern (AbsPatTuple pats) = do + rec <- sequence (clonePattern <$> pats) + return ( AbsPatTuple $ fst <$> rec + , join $ snd <$> rec) + clonePattern (AbsPatMatrix pats) = do + rec <- sequence (clonePattern <$> pats) + return ( AbsPatMatrix $ fst <$> rec + , join $ snd <$> rec) + clonePattern (AbsPatSet pats) = do + rec <- sequence (clonePattern <$> pats) + return ( AbsPatSet $ fst <$> rec + , join $ snd <$> rec) + clonePattern _ = + bug "rule_Image_Comprehension: clonePattern: unsupported Abstract Pattern" + + + diff --git a/tests/custom/permutations/23_image_set_dotlt/int/0010_find_perm_find_set/permutation.essence b/tests/custom/permutations/23_image_set_dotlt/int/0010_find_perm_find_set/permutation.essence index 9344576a9b..3068703308 100644 --- a/tests/custom/permutations/23_image_set_dotlt/int/0010_find_perm_find_set/permutation.essence +++ b/tests/custom/permutations/23_image_set_dotlt/int/0010_find_perm_find_set/permutation.essence @@ -3,5 +3,5 @@ find p : permutation of int(1..4) find s : set of int(1..4) -such that image(p,s) .< s +such that s .< image(p,s) diff --git a/tests/custom/permutations/23_image_set_dotlt/int/0010_find_perm_find_set/stdout.expected b/tests/custom/permutations/23_image_set_dotlt/int/0010_find_perm_find_set/stdout.expected index 42291b8573..abda9428df 100644 --- a/tests/custom/permutations/23_image_set_dotlt/int/0010_find_perm_find_set/stdout.expected +++ b/tests/custom/permutations/23_image_set_dotlt/int/0010_find_perm_find_set/stdout.expected @@ -14,51 +14,41 @@ Copying solution to: permutation-000009.solution Copying solution to: permutation-000010.solution language Essence 1.3 -letting p be permutation((2, 3, 4)) -letting s be {} -letting sn be {} +letting p be permutation((3, 4)) +letting s be {3} language Essence 1.3 -letting p be permutation((2, 3, 4)) -letting s be {4} -letting sn be {2} +letting p be permutation((3, 4)) +letting s be {2, 3} language Essence 1.3 -letting p be permutation((2, 3, 4)) -letting s be {3} -letting sn be {4} +letting p be permutation((3, 4)) +letting s be {1, 3} language Essence 1.3 -letting p be permutation((2, 3, 4)) -letting s be {3, 4} -letting sn be {2, 4} +letting p be permutation((3, 4)) +letting s be {1, 2, 3} language Essence 1.3 -letting p be permutation((2, 3, 4)) +letting p be permutation((2, 3)) letting s be {2} -letting sn be {3} language Essence 1.3 -letting p be permutation((2, 3, 4)) +letting p be permutation((2, 3)) letting s be {2, 4} -letting sn be {2, 3} language Essence 1.3 -letting p be permutation((2, 3, 4)) -letting s be {2, 3} -letting sn be {3, 4} +letting p be permutation((2, 3)) +letting s be {1, 2} language Essence 1.3 -letting p be permutation((2, 3, 4)) -letting s be {2, 3, 4} -letting sn be {2, 3, 4} +letting p be permutation((2, 3)) +letting s be {1, 2, 4} language Essence 1.3 letting p be permutation((2, 3, 4)) -letting s be {1} -letting sn be {1} +letting s be {2} language Essence 1.3 letting p be permutation((2, 3, 4)) -letting s be {1, 4} -letting sn be {1, 2} +letting s be {2, 4} From defe09cb0d129da1fdc9c4b713036bcea5387a9c Mon Sep 17 00:00:00 2001 From: Fraser Dunlop Date: Sat, 4 May 2019 15:53:04 +0100 Subject: [PATCH 082/229] abstract pattern tuple test --- .../permutation.essence | 7 ++ .../int/0010_find_perm_find_set/run.sh | 3 + .../0010_find_perm_find_set/stdout.expected | 84 +++++++++++++++++++ .../24_image_comprehension_dotlt/runthese.sh | 1 + 4 files changed, 95 insertions(+) create mode 100644 tests/custom/permutations/24_image_comprehension_dotlt/int/0010_find_perm_find_set/permutation.essence create mode 100755 tests/custom/permutations/24_image_comprehension_dotlt/int/0010_find_perm_find_set/run.sh create mode 100644 tests/custom/permutations/24_image_comprehension_dotlt/int/0010_find_perm_find_set/stdout.expected create mode 100644 tests/custom/permutations/24_image_comprehension_dotlt/runthese.sh diff --git a/tests/custom/permutations/24_image_comprehension_dotlt/int/0010_find_perm_find_set/permutation.essence b/tests/custom/permutations/24_image_comprehension_dotlt/int/0010_find_perm_find_set/permutation.essence new file mode 100644 index 0000000000..4fbf4f54e5 --- /dev/null +++ b/tests/custom/permutations/24_image_comprehension_dotlt/int/0010_find_perm_find_set/permutation.essence @@ -0,0 +1,7 @@ +find p : permutation of int(1..4) + +find s : set of (int(1..4),int(1..4)) + +such that p(4) != 4 +such that and(image(p,[sj > si | (si,sj) <- s])) + diff --git a/tests/custom/permutations/24_image_comprehension_dotlt/int/0010_find_perm_find_set/run.sh b/tests/custom/permutations/24_image_comprehension_dotlt/int/0010_find_perm_find_set/run.sh new file mode 100755 index 0000000000..03373df6cb --- /dev/null +++ b/tests/custom/permutations/24_image_comprehension_dotlt/int/0010_find_perm_find_set/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence --number-of-solutions=10 +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/24_image_comprehension_dotlt/int/0010_find_perm_find_set/stdout.expected b/tests/custom/permutations/24_image_comprehension_dotlt/int/0010_find_perm_find_set/stdout.expected new file mode 100644 index 0000000000..ffa9483c61 --- /dev/null +++ b/tests/custom/permutations/24_image_comprehension_dotlt/int/0010_find_perm_find_set/stdout.expected @@ -0,0 +1,84 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Copying solution to: permutation-000001.solution +Copying solution to: permutation-000002.solution +Copying solution to: permutation-000003.solution +Copying solution to: permutation-000004.solution +Copying solution to: permutation-000005.solution +Copying solution to: permutation-000006.solution +Copying solution to: permutation-000007.solution +Copying solution to: permutation-000008.solution +Copying solution to: permutation-000009.solution +Copying solution to: permutation-000010.solution +language Essence 1.3 + +letting p be permutation((3, 4)) +letting s be {} +language Essence 1.3 + +letting p be permutation((3, 4)) +letting s be {(1, 2)} +$ Visualisation for s +$ 1 2 + +language Essence 1.3 + +letting p be permutation((3, 4)) +letting s be {(1, 3)} +$ Visualisation for s +$ 1 3 + +language Essence 1.3 + +letting p be permutation((3, 4)) +letting s be {(1, 4)} +$ Visualisation for s +$ 1 4 + +language Essence 1.3 + +letting p be permutation((3, 4)) +letting s be {(2, 3)} +$ Visualisation for s +$ 2 3 + +language Essence 1.3 + +letting p be permutation((3, 4)) +letting s be {(2, 4)} +$ Visualisation for s +$ 2 4 + +language Essence 1.3 + +letting p be permutation((3, 4)) +letting s be {(3, 4)} +$ Visualisation for s +$ 3 4 + +language Essence 1.3 + +letting p be permutation((3, 4)) +letting s be {(1, 2), (1, 3)} +$ Visualisation for s +$ 1 2 +$ 1 3 + +language Essence 1.3 + +letting p be permutation((3, 4)) +letting s be {(1, 2), (1, 4)} +$ Visualisation for s +$ 1 2 +$ 1 4 + +language Essence 1.3 + +letting p be permutation((3, 4)) +letting s be {(1, 3), (1, 4)} +$ Visualisation for s +$ 1 3 +$ 1 4 + diff --git a/tests/custom/permutations/24_image_comprehension_dotlt/runthese.sh b/tests/custom/permutations/24_image_comprehension_dotlt/runthese.sh new file mode 100644 index 0000000000..9b679c9d7d --- /dev/null +++ b/tests/custom/permutations/24_image_comprehension_dotlt/runthese.sh @@ -0,0 +1 @@ +stack build --copy-bins --test --test-arguments "-p custom.permutations.24" From 704397e1b47573e909aea9b0b5a93de6e280cae0 Mon Sep 17 00:00:00 2001 From: Fraser Dunlop Date: Sun, 5 May 2019 17:49:48 +0100 Subject: [PATCH 083/229] flattenLex (incomplete definition but works for BIBD) --- src/Conjure/UI/Model.hs | 26 ++++++++++++++++++++++++++ 1 file changed, 26 insertions(+) diff --git a/src/Conjure/UI/Model.hs b/src/Conjure/UI/Model.hs index c6d443c9b8..f552259ad4 100644 --- a/src/Conjure/UI/Model.hs +++ b/src/Conjure/UI/Model.hs @@ -705,6 +705,31 @@ inlineDecVarLettings model = in model { mStatements = statements } +flattenLex :: MonadFail m + => NameGen m + => (?typeCheckerMode :: TypeCheckerMode) + => Model -> m Model +flattenLex m = do + let + flatten a = do + ta <- typeOf a + case ta of + TypeList (TypeList{}) -> do + flatten [essence| flatten(&a) |] + TypeList (TypeInt{}) -> return [essence| &a |] + _ -> bug "flattenLex: hasn't been defined for this structure yet..." + flattener [essence| &a @@ -1058,6 +1083,7 @@ epilogue :: Model -> m Model epilogue model = return model >>= logDebugIdModel "[epilogue]" + >>= flattenLex >>= logDebugIdModel "[flattenLex]" >>= dropTagForSR >>= logDebugIdModel "[dropTagForSR]" >>= updateDeclarations >>= logDebugIdModel "[updateDeclarations]" >>= return . inlineDecVarLettings >>= logDebugIdModel "[inlineDecVarLettings]" From bc7480e066abb6ed542e424b1c2102a54f229f0c Mon Sep 17 00:00:00 2001 From: Fraser Dunlop Date: Mon, 6 May 2019 11:16:41 +0100 Subject: [PATCH 084/229] reject List in permutation-image-literal Literal lists should be handled by permutatuin-image-comprehension This is where we were losing the permutation in BIBD --- src/Conjure/Rules/Horizontal/Permutation.hs | 4 +++- 1 file changed, 3 insertions(+), 1 deletion(-) diff --git a/src/Conjure/Rules/Horizontal/Permutation.hs b/src/Conjure/Rules/Horizontal/Permutation.hs index 3ba6afb468..9caca5536b 100644 --- a/src/Conjure/Rules/Horizontal/Permutation.hs +++ b/src/Conjure/Rules/Horizontal/Permutation.hs @@ -74,11 +74,12 @@ rule_Image_Literal :: Rule rule_Image_Literal = "permutation-image-literal" `namedRule` theRule where theRule [essence| image(&p, &i) |] = do (TypePermutation inner, elems) <- match permutationLiteral p + typeI <- typeOf i + case typeI of TypeList{} -> na "list is a special case" ; _ -> return () let f' = toFunction <$> fromCycles elems case f' of Left er -> fail $ "Permutation literal invalid." <++> stringToDoc (show er) Right f -> do - typeI <- typeOf i if let ?typeCheckerMode = StronglyTyped in typesUnify [inner, typeI] then do let srtdel = sortBy compare (join elems) @@ -221,6 +222,7 @@ rule_Image_Comprehendable = "comprehendable-image" `namedRule` theRule where ty <- typeOf y case ty of TypeSequence{} -> na "sequence is a special case" ; _ -> return () case ty of TypePartition{} -> na "partition is a special case" ; _ -> return () + case ty of TypeList{} -> na "list is a special case" ; _ -> return () (TypePermutation inn) <- typeOf perm if let ?typeCheckerMode = StronglyTyped in ty `containsTypeComprehendable` inn then do From 68d852681b2b621612667c55a0414ca3cad8129f Mon Sep 17 00:00:00 2001 From: Fraser Dunlop Date: Mon, 6 May 2019 14:46:52 +0100 Subject: [PATCH 085/229] Matrix Lt & Leq update + symmetryOrdering fixes --- src/Conjure/Representations.hs | 18 +++++++-------- .../Representations/Function/Function1D.hs | 14 +++-------- .../Function/FunctionAsRelation.hs | 4 ++-- .../Representations/Function/FunctionND.hs | 23 ++++--------------- .../Representations/MSet/ExplicitWithFlags.hs | 4 ++-- src/Conjure/Representations/Set/Explicit.hs | 14 ++++------- .../Set/ExplicitVarSizeWithDummy.hs | 13 +++-------- src/Conjure/Representations/Tuple.hs | 2 +- src/Conjure/Rules/Vertical/Matrix.hs | 18 +++++++-------- src/Conjure/UI/Model.hs | 15 ++++++++---- 10 files changed, 47 insertions(+), 78 deletions(-) diff --git a/src/Conjure/Representations.hs b/src/Conjure/Representations.hs index e15916561a..6d1af3c80e 100644 --- a/src/Conjure/Representations.hs +++ b/src/Conjure/Representations.hs @@ -134,17 +134,17 @@ symmetryOrdering :: EnumerateDomain m => (?typeCheckerMode :: TypeCheckerMode) => Expression -> m Expression -symmetryOrdering inp = +symmetryOrdering inp = do case inp of -- Constant x -> so_onConstant x - -- AbstractLiteral x --- AbstractLiteral x -> do --- case x of --- AbsLitTuple xs -> do --- soVals <- sequence (symmetryOrdering <$> xs) --- return $ make opFlatten (fromList soVals) --- _ -> bug ("symmetryOrdering: AbstractLiteral:" <++> pretty (show inp) <++> pretty (inp)) --- +-- AbstractLiteral _ -> return inp + AbstractLiteral x -> do + case x of + AbsLitTuple xs -> do + soVals <- sequence (symmetryOrdering <$> xs) + return $ AbstractLiteral $ AbsLitTuple soVals --make opFlatten (fromList soVals) + _ -> bug ("symmetryOrdering: AbstractLiteral:" <++> pretty (show inp) <++> pretty (inp)) + Reference _ (Just refTo) -> do case refTo of diff --git a/src/Conjure/Representations/Function/Function1D.hs b/src/Conjure/Representations/Function/Function1D.hs index 50c81d9273..c23383ff09 100644 --- a/src/Conjure/Representations/Function/Function1D.hs +++ b/src/Conjure/Representations/Function/Function1D.hs @@ -180,17 +180,9 @@ function1D = Representation chck downD structuralCons downC up symmetryOrdering symmetryOrdering :: TypeOf_SymmetryOrdering m symmetryOrdering innerSO downX1 inp domain = do - [values] <- downX1 inp - Just [(_, DomainMatrix innerDomainFr innerDomainTo)] <- downD ("SO", domain) - (iPat, i) <- quantifiedVar - soValues <- innerSO downX1 [essence| &values[&i] |] innerDomainTo - return - [essence| - [ &soValues - | &iPat : &innerDomainFr - ] - |] - + [inner] <- downX1 inp + Just [(_, innerDomain)] <- downD ("SO", domain) + innerSO downX1 inner innerDomain domainValues :: (MonadFail m, Pretty r) => Domain r Constant -> m [Constant] domainValues dom = diff --git a/src/Conjure/Representations/Function/FunctionAsRelation.hs b/src/Conjure/Representations/Function/FunctionAsRelation.hs index 1be3bf2fd2..fd72e3f345 100644 --- a/src/Conjure/Representations/Function/FunctionAsRelation.hs +++ b/src/Conjure/Representations/Function/FunctionAsRelation.hs @@ -181,5 +181,5 @@ functionAsRelation dispatch reprOptions = Representation chck downD structuralCo symmetryOrdering innerSO downX1 inp domain = do [rel] <- downX1 inp Just [(_, relDomain)] <- downD ("SO", domain) - soValues <- innerSO downX1 rel relDomain - return soValues + innerSO downX1 rel relDomain + diff --git a/src/Conjure/Representations/Function/FunctionND.hs b/src/Conjure/Representations/Function/FunctionND.hs index 64553d4574..46cf7d2c93 100644 --- a/src/Conjure/Representations/Function/FunctionND.hs +++ b/src/Conjure/Representations/Function/FunctionND.hs @@ -234,25 +234,10 @@ functionND = Representation chck downD structuralCons downC up symmetryOrdering symmetryOrdering :: TypeOf_SymmetryOrdering m symmetryOrdering innerSO downX1 inp domain = do - [values] <- downX1 inp - Just [(_, DomainMatrix innerDomainFr innerDomainTo)] <- downD ("SO", domain) - (iPat, i) <- quantifiedVar - - -- setting up the quantification - let kRange = case innerDomainFr of - DomainTuple ts -> map fromInt [1 .. genericLength ts] - DomainRecord rs -> map (fromName . fst) rs - _ -> bug $ vcat [ "FunctionND.rule_Comprehension" - , "indexDomain:" <+> pretty innerDomainFr - ] - toIndex = [ [essence| &i[&k] |] | k <- kRange ] - valuesIndexed = make opMatrixIndexing values toIndex - - soValues <- innerSO downX1 valuesIndexed innerDomainTo - - return $ - Comprehension soValues - [Generator (GenDomainNoRepr iPat (forgetRepr innerDomainFr))] + [inner] <- downX1 inp + Just [(_, innerDomain)] <- downD ("SO", domain) + innerSO downX1 inner innerDomain + viewAsDomainTuple :: Domain r x -> Maybe [Domain r x] diff --git a/src/Conjure/Representations/MSet/ExplicitWithFlags.hs b/src/Conjure/Representations/MSet/ExplicitWithFlags.hs index b6debf9f01..d11984de6b 100644 --- a/src/Conjure/Representations/MSet/ExplicitWithFlags.hs +++ b/src/Conjure/Representations/MSet/ExplicitWithFlags.hs @@ -211,9 +211,9 @@ msetExplicitWithFlags = Representation chck downD structuralCons downC up symmet soValues <- innerSO downX1 [essence| &values[&i] |] inner return [essence| - [ [ -&flags[&i] + [ ( -&flags[&i] , &soValues - ] + ) | &iPat : &index ] |] diff --git a/src/Conjure/Representations/Set/Explicit.hs b/src/Conjure/Representations/Set/Explicit.hs index ee5efa1f9e..4695cbef8d 100644 --- a/src/Conjure/Representations/Set/Explicit.hs +++ b/src/Conjure/Representations/Set/Explicit.hs @@ -108,13 +108,7 @@ setExplicit = Representation chck downD structuralCons downC up symmetryOrdering symmetryOrdering :: TypeOf_SymmetryOrdering m symmetryOrdering innerSO downX1 inp domain = do - [values] <- downX1 inp - Just [(_, DomainMatrix index inner)] <- downD ("SO", domain) - (iPat, i) <- quantifiedVar - soValues <- innerSO downX1 [essence| &values[&i] |] inner - return - [essence| - [ &soValues - | &iPat : &index - ] - |] + [inner] <- downX1 inp + Just [(_, innerDomain)] <- downD ("SO", domain) + innerSO downX1 inner innerDomain + diff --git a/src/Conjure/Representations/Set/ExplicitVarSizeWithDummy.hs b/src/Conjure/Representations/Set/ExplicitVarSizeWithDummy.hs index c8b3efac58..d2c5d2b290 100644 --- a/src/Conjure/Representations/Set/ExplicitVarSizeWithDummy.hs +++ b/src/Conjure/Representations/Set/ExplicitVarSizeWithDummy.hs @@ -169,13 +169,6 @@ setExplicitVarSizeWithDummy = Representation chck downD structuralCons downC up symmetryOrdering :: TypeOf_SymmetryOrdering m symmetryOrdering innerSO downX1 inp domain = do - [values] <- downX1 inp - Just [(_, DomainMatrix index inner)] <- downD ("SO", domain) - (iPat, i) <- quantifiedVar - soValues <- innerSO downX1 [essence| &values[&i] |] inner - return - [essence| - [ &soValues - | &iPat : &index - ] - |] + [inner] <- downX1 inp + Just [(_, innerDomain)] <- downD ("SO", domain) + innerSO downX1 inner innerDomain diff --git a/src/Conjure/Representations/Tuple.hs b/src/Conjure/Representations/Tuple.hs index aaca054cd3..bb2c814d37 100644 --- a/src/Conjure/Representations/Tuple.hs +++ b/src/Conjure/Representations/Tuple.hs @@ -83,4 +83,4 @@ tuple = Representation chck downD structuralCons downC up symmetryOrdering Just xsDoms' <- downD ("SO", domain) let xsDoms = map snd xsDoms' soValues <- sequence [ innerSO downX1 x xDom | (x, xDom) <- zip xs xsDoms ] - return (fromList soValues) + return $ AbstractLiteral $ AbsLitTuple soValues diff --git a/src/Conjure/Rules/Vertical/Matrix.hs b/src/Conjure/Rules/Vertical/Matrix.hs index 2e4ee583d8..d7f0cadc9f 100644 --- a/src/Conjure/Rules/Vertical/Matrix.hs +++ b/src/Conjure/Rules/Vertical/Matrix.hs @@ -350,10 +350,9 @@ rule_Matrix_Neq = "matrix-neq" `namedRule` theRule where rule_Matrix_Lt_Primitive :: Rule rule_Matrix_Lt_Primitive = "matrix-Lt-primitive" `namedRule` theRule where theRule p = do - (x,y) <- case (match opLt p, match opDotLt p, match opTildeLt p) of - (Just a, _, _) -> return a - (_, Just a, _) -> return a - (_, _, Just a) -> return a + (x,y) <- case (match opLt p, match opTildeLt p) of + (Just a, _) -> return a + (_, Just a) -> return a _ -> na "rule_Matrix_Lt_Primitive" tx <- typeOf x -- TODO: check if x and y have the same arity ty <- typeOf y @@ -363,17 +362,16 @@ rule_Matrix_Lt_Primitive = "matrix-Lt-primitive" `namedRule` theRule where let y' = flattenIfNeeded (matrixNumDims ty) y return ( "Horizontal rule for matrix <" - , return [essence| &x' return a - (_, Just a, _) -> return a - (_, _, Just a) -> return a + (x,y) <- case (match opLeq p, match opTildeLeq p) of + (Just a, _) -> return a + (_, Just a) -> return a _ -> na "rule_Matrix_Leq_Primitive" tx <- typeOf x -- TODO: check if x and y have the same arity ty <- typeOf y @@ -383,7 +381,7 @@ rule_Matrix_Leq_Primitive = "matrix-Leq-primitive" `namedRule` theRule where let y' = flattenIfNeeded (matrixNumDims ty) y return ( "Horizontal rule for matrix <=" - , return [essence| &x' <=lex &y' |] + , return [essence| &x' .<= &y' |] ) diff --git a/src/Conjure/UI/Model.hs b/src/Conjure/UI/Model.hs index f552259ad4..09866edbfd 100644 --- a/src/Conjure/UI/Model.hs +++ b/src/Conjure/UI/Model.hs @@ -714,10 +714,17 @@ flattenLex m = do flatten a = do ta <- typeOf a case ta of - TypeList (TypeList{}) -> do - flatten [essence| flatten(&a) |] - TypeList (TypeInt{}) -> return [essence| &a |] - _ -> bug "flattenLex: hasn't been defined for this structure yet..." + TypeList (TypeInt{}) -> return [essence| &a |] + TypeInt{} -> return [essence| [&a] |] + TypeList{} -> flatten [essence| flatten(&a) |] + TypeMatrix{} -> flatten [essence| flatten(&a) |] + TypeTuple{} -> do + case a of + AbstractLiteral (AbsLitTuple exprs) -> do + is <- sequence (flatten <$> exprs) + flatten $ fromList is + _ -> bug $ "epilogue: flattenLex: expected AbsLitTuple..." <+> vcat [pretty ta, pretty a] + _ -> bug $ "epilogue: flattenLex: isn't defined for this structure..." <+> vcat [pretty ta, pretty a] flattener [essence| &a Date: Mon, 6 May 2019 23:59:29 +0100 Subject: [PATCH 086/229] fixed flattenLex infinite recursion --- .../Representations/MSet/Occurrence.hs | 9 ++++--- src/Conjure/Representations/Permutation.hs | 3 +-- src/Conjure/Representations/Record.hs | 2 +- src/Conjure/UI/Model.hs | 24 +++++++++++++------ 4 files changed, 23 insertions(+), 15 deletions(-) diff --git a/src/Conjure/Representations/MSet/Occurrence.hs b/src/Conjure/Representations/MSet/Occurrence.hs index 8de91a3fdd..6f93b646f2 100644 --- a/src/Conjure/Representations/MSet/Occurrence.hs +++ b/src/Conjure/Representations/MSet/Occurrence.hs @@ -112,8 +112,7 @@ msetOccurrence = Representation chck downD structuralCons downC up symmetryOrder up _ _ = na "{up} Occurrence" symmetryOrdering :: TypeOf_SymmetryOrdering m - symmetryOrdering _innerSO downX1 inp (DomainSet MSet_Occurrence _attrs innerDomain) = do - [m] <- downX1 inp - (iPat, i) <- quantifiedVar - return [essence| [ -&m[&i] | &iPat : &innerDomain ] |] - symmetryOrdering _ _ _ _ = na "{symmetryOrdering} Occurrence" + symmetryOrdering innerSO downX1 inp domain = do + [inner] <- downX1 inp + Just [(_, innerDomain)] <- downD ("SO", domain) + innerSO downX1 inner innerDomain diff --git a/src/Conjure/Representations/Permutation.hs b/src/Conjure/Representations/Permutation.hs index c0095b3ca0..a4fe17af94 100644 --- a/src/Conjure/Representations/Permutation.hs +++ b/src/Conjure/Representations/Permutation.hs @@ -133,5 +133,4 @@ permutationAsFunction dispatch = Representation chck downD structuralCons downC symmetryOrdering innerSO downX1 inp domain = do [x] <- downX1 inp Just [(_, xDomain)] <- downD ("SO", domain) - soValues <- innerSO downX1 x xDomain - return soValues + innerSO downX1 x xDomain diff --git a/src/Conjure/Representations/Record.hs b/src/Conjure/Representations/Record.hs index 4394916e45..75904744b6 100644 --- a/src/Conjure/Representations/Record.hs +++ b/src/Conjure/Representations/Record.hs @@ -83,4 +83,4 @@ record = Representation chck downD structuralCons downC up symmetryOrdering Just xsDoms' <- downD ("SO", domain) let xsDoms = map snd xsDoms' soValues <- sequence [ innerSO downX1 x xDom | (x, xDom) <- zip xs xsDoms ] - return (fromList soValues) + return $ AbstractLiteral $ AbsLitTuple soValues diff --git a/src/Conjure/UI/Model.hs b/src/Conjure/UI/Model.hs index 09866edbfd..ae36c11b26 100644 --- a/src/Conjure/UI/Model.hs +++ b/src/Conjure/UI/Model.hs @@ -711,13 +711,25 @@ flattenLex :: MonadFail m => Model -> m Model flattenLex m = do let + deshell (Op (MkOpFlatten (OpFlatten Nothing crab))) = do + (reshell, hermit) <- deshell crab + return (\r -> (Op (MkOpFlatten (OpFlatten Nothing (reshell r)))), hermit) + deshell e = return (id, e) flatten a = do ta <- typeOf a case ta of - TypeList (TypeInt{}) -> return [essence| &a |] - TypeInt{} -> return [essence| [&a] |] - TypeList{} -> flatten [essence| flatten(&a) |] - TypeMatrix{} -> flatten [essence| flatten(&a) |] + TypeList (TypeInt{}) -> return [essence| &a |] + TypeInt{} -> return [essence| [&a] |] + TypeList (TypeList{}) -> flatten [essence| flatten(&a) |] + TypeList (TypeMatrix{}) -> flatten [essence| flatten(&a) |] + TypeList{} -> do + (resh, desh) <- deshell a + case desh of + Comprehension exp goc -> do + nexp <- flatten exp + flatten $ resh $ Comprehension nexp goc + _ -> bug $ "epilogue: flattenLex: isn't defined for this structure...." <+> vcat [pretty ta, pretty a, stringToDoc $ show a] + TypeMatrix{} -> flatten [essence| flatten(&a) |] TypeTuple{} -> do case a of AbstractLiteral (AbsLitTuple exprs) -> do @@ -1332,7 +1344,6 @@ horizontalRules = , Horizontal.Permutation.rule_Image_Comprehension -- , Horizontal.Permutation.rule_Image_Matrix_Indexing_Comprehension -- , Horizontal.Permutation.rule_Compose - , Horizontal.Permutation.rule_Image_Literal , Horizontal.Permutation.rule_Image_Partition , Horizontal.Permutation.rule_Image_Sequence , Horizontal.Permutation.rule_Image_Sequence_Defined @@ -1340,7 +1351,7 @@ horizontalRules = , Horizontal.Permutation.rule_Permutation_Inverse , Horizontal.Permutation.rule_Image_Comprehendable , Horizontal.Permutation.rule_Image_Incomprehendable - + , Horizontal.Permutation.rule_Image_Literal , Horizontal.Set.rule_Comprehension_Literal @@ -1901,7 +1912,6 @@ rule_DotLtLeq = "generic-DotLtLeq" `namedRule` theRule where -- TypePartition{} -> return () -- _ -> na "rule_DotLtLeq" -- sameRepresentationTree a b - ma <- symmetryOrdering a mb <- symmetryOrdering b return From 3471a29364e17743fd56e9a5251792fd77424fb1 Mon Sep 17 00:00:00 2001 From: Fraser Dunlop Date: Wed, 8 May 2019 11:52:07 +0100 Subject: [PATCH 087/229] rollback domain pretty --- src/Conjure/Prelude.hs | 4 ++++ src/Conjure/UI/Model.hs | 27 +++++++++++++++++++++++---- 2 files changed, 27 insertions(+), 4 deletions(-) diff --git a/src/Conjure/Prelude.hs b/src/Conjure/Prelude.hs index 32645ace2b..953f3fdf10 100644 --- a/src/Conjure/Prelude.hs +++ b/src/Conjure/Prelude.hs @@ -7,6 +7,7 @@ module Conjure.Prelude ( module X , stringToDoc + , textToDoc , padRight, padLeft, padCenter , pairWithContents , withRest, withAfter, withBefore @@ -220,6 +221,9 @@ textToString = T.unpack stringToDoc :: String -> Doc stringToDoc = Pr.text +textToDoc :: T.Text -> Doc +textToDoc = stringToDoc . textToString + padRight :: Int -> Char -> String -> String padRight n ch s = s ++ replicate (n - length s) ch diff --git a/src/Conjure/UI/Model.hs b/src/Conjure/UI/Model.hs index ae36c11b26..cb3f29dd02 100644 --- a/src/Conjure/UI/Model.hs +++ b/src/Conjure/UI/Model.hs @@ -722,21 +722,40 @@ flattenLex m = do TypeInt{} -> return [essence| [&a] |] TypeList (TypeList{}) -> flatten [essence| flatten(&a) |] TypeList (TypeMatrix{}) -> flatten [essence| flatten(&a) |] + TypeMatrix{} -> do -- flatten [essence| flatten(&a) |] + case a of + AbstractLiteral (AbsLitMatrix indxDom _) -> do + (iPat,i) <- quantifiedVarOverDomain indxDom + flatten $ Comprehension [essence| &a[&i] |] + [Generator (GenDomainNoRepr iPat indxDom)] + _ -> bug $ "epilogue: flattenLex: isn't defined for this structure.." + <+> vcat [pretty ta, pretty a, stringToDoc $ show a] TypeList{} -> do (resh, desh) <- deshell a case desh of Comprehension exp goc -> do nexp <- flatten exp flatten $ resh $ Comprehension nexp goc - _ -> bug $ "epilogue: flattenLex: isn't defined for this structure...." <+> vcat [pretty ta, pretty a, stringToDoc $ show a] - TypeMatrix{} -> flatten [essence| flatten(&a) |] + _ -> bug $ "epilogue: flattenLex: isn't defined for this structure..." + <+> vcat [pretty ta, pretty a, stringToDoc $ show a] +-- TypeMatrix{} -> do +-- (resh, desh) <- deshell a +-- deshd <- domainOf desh +-- case deshd of +-- DomainMatrix indxDom _ -> do +-- (iPat,i) <- quantifiedVarOverDomain indxDom +-- flatten $ resh [essence| [ &desh[&i] | &iPat : &indxDom ] |] +-- _ -> bug $ "epilogue: flattenLex: isn't defined for this structure...." +-- <+> vcat [pretty ta, pretty a, stringToDoc $ show a] TypeTuple{} -> do case a of AbstractLiteral (AbsLitTuple exprs) -> do is <- sequence (flatten <$> exprs) flatten $ fromList is - _ -> bug $ "epilogue: flattenLex: expected AbsLitTuple..." <+> vcat [pretty ta, pretty a] - _ -> bug $ "epilogue: flattenLex: isn't defined for this structure..." <+> vcat [pretty ta, pretty a] + _ -> bug $ "epilogue: flattenLex: expected AbsLitTuple...." + <+> vcat [pretty ta, pretty a] + _ -> bug $ "epilogue: flattenLex: isn't defined for this structure....." + <+> vcat [pretty ta, pretty a] flattener [essence| &a Date: Fri, 10 May 2019 14:23:40 +0100 Subject: [PATCH 088/229] enforce tag consistency + permutation literal image of tuple --- src/Conjure/Language/Constant.hs | 8 +++ src/Conjure/Language/Domain.hs | 1 + src/Conjure/Language/Expression.hs | 8 +++ src/Conjure/Language/NameResolution.hs | 7 ++- src/Conjure/Prelude.hs | 1 + src/Conjure/Rules/Horizontal/Permutation.hs | 55 ++++++++++++--------- src/Conjure/UI/Model.hs | 12 ++++- 7 files changed, 66 insertions(+), 26 deletions(-) diff --git a/src/Conjure/Language/Constant.hs b/src/Conjure/Language/Constant.hs index 3716a9b36d..2fcf67e975 100644 --- a/src/Conjure/Language/Constant.hs +++ b/src/Conjure/Language/Constant.hs @@ -21,6 +21,7 @@ module Conjure.Language.Constant , viewConstantRelation , viewConstantPartition , viewConstantPermutation + , reDomConst ) where -- conjure @@ -524,3 +525,10 @@ viewConstantPermutation :: MonadFail m => Constant -> m [[Constant]] viewConstantPermutation (ConstantAbstract (AbsLitPermutation xs)) = return xs viewConstantPermutation (TypedConstant c _) = viewConstantPermutation c viewConstantPermutation constant = fail ("Expecting a permutation, but got:" <++> pretty constant) + + +reDomConst :: Domain () Constant -> Domain () Constant +reDomConst cns = case cns of + DomainInt t _ -> reTag t cns + _ -> cns + diff --git a/src/Conjure/Language/Domain.hs b/src/Conjure/Language/Domain.hs index 33f379dedf..d5cfb8d6c9 100644 --- a/src/Conjure/Language/Domain.hs +++ b/src/Conjure/Language/Domain.hs @@ -1041,3 +1041,4 @@ singletonDomainInt _ = Nothing matrixNumDimsD :: Domain r x -> Int matrixNumDimsD (DomainMatrix _ t) = 1 + matrixNumDimsD t matrixNumDimsD _ = 0 + diff --git a/src/Conjure/Language/Expression.hs b/src/Conjure/Language/Expression.hs index 53cc0cbdc1..04f1f469c0 100644 --- a/src/Conjure/Language/Expression.hs +++ b/src/Conjure/Language/Expression.hs @@ -16,6 +16,7 @@ module Conjure.Language.Expression , patternToExpr , emptyCollectionX , nbUses + , reDomExp ) where -- conjure @@ -857,3 +858,10 @@ emptyCollectionX (Constant x) = emptyCollection x emptyCollectionX (AbstractLiteral x) = emptyCollectionAbsLit x emptyCollectionX (Typed x _) = emptyCollectionX x emptyCollectionX _ = False + + +reDomExp :: Domain () Expression -> Domain () Expression +reDomExp exp = case exp of + DomainInt t _ -> reTag t exp + _ -> exp + diff --git a/src/Conjure/Language/NameResolution.hs b/src/Conjure/Language/NameResolution.hs index 741b3dff99..1498a7f930 100644 --- a/src/Conjure/Language/NameResolution.hs +++ b/src/Conjure/Language/NameResolution.hs @@ -15,6 +15,8 @@ import Conjure.Language.Domain import Conjure.Language.Type import Conjure.Language.TypeOf import Conjure.Language.Pretty +import Conjure.Language.Expression ( reDomExp ) +import Conjure.Language.Constant ( reDomConst ) resolveNamesMulti @@ -115,11 +117,11 @@ resolveStatement st = Letting nm x -> do x' <- resolveX x modify ((nm, Alias x') :) - return (Declaration (Letting nm x')) + return (Declaration (Letting nm x')) LettingDomainDefnUnnamed nm x -> do x' <- resolveX x modify ((nm, Alias (Domain (DomainUnnamed nm x'))) :) - return (Declaration (LettingDomainDefnUnnamed nm x')) + return (Declaration (LettingDomainDefnUnnamed nm x')) LettingDomainDefnEnum (Name ename) nms -> do modify ( [ (nm, Alias (Constant (ConstantInt (TagEnum ename) i))) | (nm, i) <- zip nms [1..] @@ -140,6 +142,7 @@ resolveStatement st = SuchThat xs -> SuchThat <$> mapM resolveX xs + resolveSearchOrder :: ( MonadFail m , MonadUserError m diff --git a/src/Conjure/Prelude.hs b/src/Conjure/Prelude.hs index 953f3fdf10..a81b8d1162 100644 --- a/src/Conjure/Prelude.hs +++ b/src/Conjure/Prelude.hs @@ -169,6 +169,7 @@ import Data.Generics.Uniplate.Data as X , transformM, transformBiM , descend, descendM , descendBi, descendBiM + , rewriteBi , universe, universeBi , children, childrenBi , uniplate diff --git a/src/Conjure/Rules/Horizontal/Permutation.hs b/src/Conjure/Rules/Horizontal/Permutation.hs index 9caca5536b..dac520270e 100644 --- a/src/Conjure/Rules/Horizontal/Permutation.hs +++ b/src/Conjure/Rules/Horizontal/Permutation.hs @@ -76,27 +76,38 @@ rule_Image_Literal = "permutation-image-literal" `namedRule` theRule where (TypePermutation inner, elems) <- match permutationLiteral p typeI <- typeOf i case typeI of TypeList{} -> na "list is a special case" ; _ -> return () - let f' = toFunction <$> fromCycles elems - case f' of - Left er -> fail $ "Permutation literal invalid." <++> stringToDoc (show er) - Right f -> do - if let ?typeCheckerMode = StronglyTyped in typesUnify [inner, typeI] - then do - let srtdel = sortBy compare (join elems) - domIndx = mkDomainInt (RangeSingle <$> srtdel) - matLit = make matrixLiteral (TypeMatrix inner inner) domIndx ( f <$> srtdel) - return - ( "Horizontal rule for permutation literal application to a single value (image), AsFunction representation" - , do - return [essence| [&i, catchUndef(&matLit[&i],0)][toInt(&i in toSet(&matLit))+1] |] - - ) - else if let ?typeCheckerMode = StronglyTyped in typeI `containsType` inner - then na "rule_Image_Literal" - else return ( "Horizontal rule for permutation application to a type the permutation doesn't care about" - , do - return [essence| &i |] - ) + case typeI of + TypeTuple tint -> do + let tupleIndexImage indx = let indexexpr = Constant (ConstantInt TagInt indx) + in [essence| image(&p, &i[&indexexpr]) |] + tupleExpression = AbstractLiteral $ AbsLitTuple + $ (tupleIndexImage <$> [1..(fromIntegral $ length tint)]) + return + ( "Horizontal rule for image of tuple under permutation" + , return tupleExpression + ) + _ -> do + let f' = toFunction <$> fromCycles elems + case f' of + Left er -> fail $ "Permutation literal invalid." <++> stringToDoc (show er) + Right f -> do + if let ?typeCheckerMode = StronglyTyped in typesUnify [inner, typeI] + then do + let srtdel = sortBy compare (join elems) + domIndx = mkDomainInt (RangeSingle <$> srtdel) + matLit = make matrixLiteral (TypeMatrix inner inner) domIndx ( f <$> srtdel) + return + ( "Horizontal rule for permutation literal application to a single value (image), AsFunction representation" + , do + return [essence| [&i, catchUndef(&matLit[&i],0)][toInt(&i in toSet(&matLit))+1] |] + + ) + else if let ?typeCheckerMode = StronglyTyped in typeI `containsType` inner + then na "rule_Image_Literal" + else return ( "Horizontal rule for permutation application to a type the permutation doesn't care about" + , do + return [essence| &i |] + ) theRule _ = na "rule_Image_Literal" @@ -172,7 +183,7 @@ rule_Image_Comprehension = "comprehension-image" `namedRule` theRule where -- -> Generator -- -> m [GeneratorOrCondition] permutationOverGenerator p (GenDomainHasRepr a d) = do - (Single nm, n) <- quantifiedVar + (Single nm, n) <- quantifiedVarOverDomain $ forgetRepr d return [Generator (GenDomainHasRepr nm d) ,ComprehensionLetting a [essence| image(&p, &n) |] ] diff --git a/src/Conjure/UI/Model.hs b/src/Conjure/UI/Model.hs index cb3f29dd02..95e9624deb 100644 --- a/src/Conjure/UI/Model.hs +++ b/src/Conjure/UI/Model.hs @@ -23,6 +23,8 @@ import Conjure.Language.TypeOf import Conjure.Compute.DomainOf import Conjure.Language.Lenses import Conjure.Language.TH ( essence ) +import Conjure.Language.Expression ( reDomExp ) +import Conjure.Language.Constant ( reDomConst ) import Conjure.Language.Expression.Op import Conjure.Language.ModelStats ( modelInfo ) import Conjure.Language.Instantiate ( instantiateExpression, trySimplify ) @@ -1091,6 +1093,7 @@ prologue :: prologue model = do void $ typeCheckModel_StandAlone model return model >>= logDebugIdModel "[input]" + >>= enforceTagConsistency >>= logDebugIdModel "[enforceTagConsistency]" >>= return . addSearchOrder >>= logDebugIdModel "[addSearchOrder]" >>= attributeAsConstraints >>= logDebugIdModel "[attributeAsConstraints]" >>= inferAttributes >>= logDebugIdModel "[inferAttributes]" @@ -1110,7 +1113,12 @@ prologue model = do >>= dealWithCuts >>= logDebugIdModel "[dealWithCuts]" >>= removeExtraSlices >>= logDebugIdModel "[removeExtraSlices]" >>= return . addTrueConstraints >>= logDebugIdModel "[addTrueConstraints]" + >>= enforceTagConsistency >>= logDebugIdModel "[enforceTagConsistency]" +enforceTagConsistency :: MonadFail m => Model -> m Model +enforceTagConsistency model = do + let statements' = transformBi reDomExp $ transformBi reDomConst (mStatements model) + return model { mStatements = statements' } epilogue :: MonadFail m => @@ -1931,8 +1939,8 @@ rule_DotLtLeq = "generic-DotLtLeq" `namedRule` theRule where -- TypePartition{} -> return () -- _ -> na "rule_DotLtLeq" -- sameRepresentationTree a b - ma <- symmetryOrdering a - mb <- symmetryOrdering b + ma <- symmetryOrdering $ transformBi reDomExp $ transformBi reDomConst a + mb <- symmetryOrdering $ transformBi reDomExp $ transformBi reDomConst b return ( "Generic vertical rule for dotLt and dotLeq:" <+> pretty p , return $ mk ma mb From cd709d74708f19e3f37e339dcdf7cdee098487b1 Mon Sep 17 00:00:00 2001 From: Fraser Dunlop Date: Sun, 12 May 2019 00:28:40 +0100 Subject: [PATCH 089/229] correct image for permutation literal --- src/Conjure/Rules/Horizontal/Permutation.hs | 14 +++++++++++--- 1 file changed, 11 insertions(+), 3 deletions(-) diff --git a/src/Conjure/Rules/Horizontal/Permutation.hs b/src/Conjure/Rules/Horizontal/Permutation.hs index dac520270e..b949cf734e 100644 --- a/src/Conjure/Rules/Horizontal/Permutation.hs +++ b/src/Conjure/Rules/Horizontal/Permutation.hs @@ -94,12 +94,20 @@ rule_Image_Literal = "permutation-image-literal" `namedRule` theRule where if let ?typeCheckerMode = StronglyTyped in typesUnify [inner, typeI] then do let srtdel = sortBy compare (join elems) - domIndx = mkDomainInt (RangeSingle <$> srtdel) - matLit = make matrixLiteral (TypeMatrix inner inner) domIndx ( f <$> srtdel) + inperm = (\x -> [essence| toInt(&x) + 1 |]) + ((\o -> [essence| or(&o) |]) + ((fromList ((\q -> [essence| &q = &i |]) <$> srtdel)))) + indexr = (\x -> [essence| sum(&x) |]) + (fromList ((\(n,q) -> [essence| toInt(&q = &i) * &n |]) + <$> (zip [1..] srtdel))) + matIdx = mkDomainIntB (fromInt 1) + (fromInt (fromIntegral (length srtdel))) + matLit = make matrixLiteral (TypeMatrix (TypeInt TagInt) inner) + matIdx (f <$> srtdel) return ( "Horizontal rule for permutation literal application to a single value (image), AsFunction representation" , do - return [essence| [&i, catchUndef(&matLit[&i],0)][toInt(&i in toSet(&matLit))+1] |] + return [essence| [&i, catchUndef(&matLit[&indexr],0)][&inperm] |] ) else if let ?typeCheckerMode = StronglyTyped in typeI `containsType` inner From 75b2d54bc8ba1a29ef5ed17467c930f5df87b6e9 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?O=CC=88zgu=CC=88r=20Akgu=CC=88n?= Date: Mon, 13 May 2019 15:20:21 +0100 Subject: [PATCH 090/229] Add --unnamed-symmetry-breaking as a command line option --- docs/conjure-help.html | 2 ++ docs/conjure-help.txt | 8 ++++++++ src/Conjure/Rules/Definition.hs | 11 +++++++++++ src/Conjure/UI.hs | 18 ++++++++++++++++++ src/Conjure/UI/MainHelper.hs | 16 +++++++++++++++- 5 files changed, 54 insertions(+), 1 deletion(-) diff --git a/docs/conjure-help.html b/docs/conjure-help.html index f7f8816264..969ffd49d2 100644 --- a/docs/conjure-help.html +++ b/docs/conjure-help.html @@ -38,6 +38,7 @@  --representations-cuts=STRATEGYStrategy for choosing a representation for cuts in 'branching on'.
Default value: same as --representations  --channellingWhether to produce channelled models (true by default).
 --representation-levelsWhether to use built-in precedence levels when choosing representations. Used to cut down the number of generated models.
Default: true + --unnamed-symmetry-breaking=ITEMLevel to use for breaking symmetries arising from unnamed types. Options: none / fast-consecutive / fast-allpairs / complete-independently / complete.
Default: none  --seed=INTRandom number generator seed.  --limit-models=INTMaximum number of models to generate.  --choices=FILEChoices to use for -al, either an eprime file (created by --log-choices), or a json file. @@ -121,6 +122,7 @@  --representations-cuts=STRATEGYStrategy for choosing a representation for cuts in 'branching on'.
Default value: same as --representations  --channellingWhether to produce channelled models (true by default).
 --representation-levelsWhether to use built-in precedence levels when choosing representations. Used to cut down the number of generated models.
Default: true + --unnamed-symmetry-breaking=ITEMLevel to use for breaking symmetries arising from unnamed types. Options: none / fast-consecutive / fast-allpairs / complete-independently / complete.
Default: none  --seed=INTRandom number generator seed.  --limit-models=INTMaximum number of models to generate.  --use-existing-models=FILEFile names of Essence' models generated beforehand.
If given, Conjure skips the modelling phase and uses the existing models for solving.
The models should be inside the output directory (See -o). diff --git a/docs/conjure-help.txt b/docs/conjure-help.txt index 459636c4a5..01b787449f 100644 --- a/docs/conjure-help.txt +++ b/docs/conjure-help.txt @@ -69,6 +69,10 @@ --representation-levels Whether to use built-in precedence levels when choosing representations. Used to cut down the number of generated models. Default: true + --unnamed-symmetry-breaking=ITEM Level to use for breaking symmetries arising from unnamed types. + Options: none / fast-consecutive / fast-allpairs / complete-independently + / complete. + Default: none --seed=INT Random number generator seed. --limit-models=INT Maximum number of models to generate. --choices=FILE Choices to use for -al, either an eprime file (created by @@ -204,6 +208,10 @@ --representation-levels Whether to use built-in precedence levels when choosing representations. Used to cut down the number of generated models. Default: true + --unnamed-symmetry-breaking=ITEM Level to use for breaking symmetries arising from unnamed types. + Options: none / fast-consecutive / fast-allpairs / complete-independently + / complete. + Default: none --seed=INT Random number generator seed. --limit-models=INT Maximum number of models to generate. --use-existing-models=FILE File names of Essence' models generated beforehand. diff --git a/src/Conjure/Rules/Definition.hs b/src/Conjure/Rules/Definition.hs index 4180316c75..6875b047ac 100644 --- a/src/Conjure/Rules/Definition.hs +++ b/src/Conjure/Rules/Definition.hs @@ -7,6 +7,7 @@ module Conjure.Rules.Definition , LogOrModel, LogOr , Driver, Strategy(..), viewAuto, parseStrategy , Config(..) + , UnnamedSymmetryBreaking(..) , ModelZipper, mkModelZipper, fromModelZipper , ModelWIP(..), modelWIPOut, updateModelWIPInfo , isAtomic @@ -100,6 +101,7 @@ data Config = Config , outputDirectory :: FilePath , channelling :: Bool , representationLevels :: Bool + , unnamedSymmetryBreaking :: UnnamedSymmetryBreaking , limitModels :: Maybe Int , numberingStart :: Int , smartFilenames :: Bool @@ -129,6 +131,7 @@ instance Default Config where , outputDirectory = "conjure-output" , channelling = True , representationLevels = True + , unnamedSymmetryBreaking = None , limitModels = Nothing , numberingStart = 1 , smartFilenames = False @@ -137,6 +140,14 @@ instance Default Config where , estimateNumberOfModels = False } +data UnnamedSymmetryBreaking + = None + | FastConsecutive + | FastAllpairs + | CompleteIndependently + | Complete + deriving (Eq, Ord, Show, Read, Data, Typeable) + data RuleResult m = RuleResult { ruleResultDescr :: Doc -- describe this transformation , ruleResultType :: QuestionType diff --git a/src/Conjure/UI.hs b/src/Conjure/UI.hs index 802a618781..d5437a4828 100644 --- a/src/Conjure/UI.hs +++ b/src/Conjure/UI.hs @@ -45,6 +45,7 @@ data UI , representationsCuts :: Maybe String -- (def: representations) , channelling :: Bool , representationLevels :: Bool -- (def: True) + , unnamedSymmetryBreaking :: String , seed :: Maybe Int , limitModels :: Maybe Int , limitTime :: Maybe Int @@ -112,6 +113,7 @@ data UI , representationsCuts :: Maybe String , channelling :: Bool , representationLevels :: Bool -- (def: True) + , unnamedSymmetryBreaking :: String , seed :: Maybe Int , limitModels :: Maybe Int , limitTime :: Maybe Int @@ -379,6 +381,14 @@ ui = modes &= help "Whether to use built-in precedence levels when choosing representations. \ \Used to cut down the number of generated models.\n\ \Default: true" + , unnamedSymmetryBreaking + = "none" + &= name "unnamed-symmetry-breaking" + &= groupname "Model generation" + &= explicit + &= help "Level to use for breaking symmetries arising from unnamed types. \ + \Options: none / fast-consecutive / fast-allpairs / complete-independently / complete.\n\ + \Default: none" , seed = Nothing &= name "seed" @@ -777,6 +787,14 @@ ui = modes &= help "Whether to use built-in precedence levels when choosing representations. \ \Used to cut down the number of generated models.\n\ \Default: true" + , unnamedSymmetryBreaking + = "none" + &= name "unnamed-symmetry-breaking" + &= groupname "Model generation" + &= explicit + &= help "Level to use for breaking symmetries arising from unnamed types. \ + \Options: none / fast-consecutive / fast-allpairs / complete-independently / complete.\n\ + \Default: none" , seed = Nothing &= name "seed" diff --git a/src/Conjure/UI/MainHelper.hs b/src/Conjure/UI/MainHelper.hs index beeae88f7f..2b695f83d4 100644 --- a/src/Conjure/UI/MainHelper.hs +++ b/src/Conjure/UI/MainHelper.hs @@ -26,7 +26,7 @@ import Conjure.Language.NameGen ( NameGenM, runNameGen ) import Conjure.Language.Pretty ( pretty, prettyList, renderNormal, render ) import qualified Conjure.Language.ParserC as ParserC ( parseModel ) import Conjure.Language.ModelDiff ( modelDiffIO ) -import Conjure.Rules.Definition ( viewAuto, Strategy(..) ) +import Conjure.Rules.Definition ( viewAuto, Strategy(..), UnnamedSymmetryBreaking(..) ) import Conjure.Process.Enumerate ( EnumerateDomain ) import Conjure.Process.ModelStrengthening ( strengthenModel ) import Conjure.Language.NameResolution ( resolveNamesMulti ) @@ -104,6 +104,19 @@ mainWithArgs Modelling{..} = do , "But got:" <+> pretty responses ] + unnamedSymmetryBreakingParsed <- + case unnamedSymmetryBreaking of + "none" -> return None + "fast-consecutive" -> return FastConsecutive + "fast-allpairs" -> return FastAllpairs + "complete-independently" -> return CompleteIndependently + "complete" -> return Complete + _ -> userErr1 $ vcat + [ "Unrecognised value for --unnamed-symmetry-breaking" + , "Expected one of: none/fast-consecutive/fast-allpairs/complete-independently/complete" + , "But got:" <+> pretty unnamedSymmetryBreaking + ] + return Config.Config { Config.outputDirectory = outputDirectory , Config.logLevel = logLevel @@ -123,6 +136,7 @@ mainWithArgs Modelling{..} = do , Config.representationsCuts = representationsCuts' , Config.channelling = channelling , Config.representationLevels = representationLevels + , Config.unnamedSymmetryBreaking = unnamedSymmetryBreakingParsed , Config.limitModels = if limitModels == Just 0 then Nothing else limitModels , Config.numberingStart = numberingStart , Config.smartFilenames = smartFilenames From f0d067a5a7728ec351baa879c04dd94cbd10cc5b Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?O=CC=88zgu=CC=88r=20Akgu=CC=88n?= Date: Mon, 13 May 2019 16:30:10 +0100 Subject: [PATCH 091/229] fast-consecutive and fast-allpairs should both work --- src/Conjure/UI/Model.hs | 102 ++++++++++++++++++++++++++++++++++++---- 1 file changed, 94 insertions(+), 8 deletions(-) diff --git a/src/Conjure/UI/Model.hs b/src/Conjure/UI/Model.hs index 95e9624deb..713f72490e 100644 --- a/src/Conjure/UI/Model.hs +++ b/src/Conjure/UI/Model.hs @@ -219,7 +219,7 @@ toCompletion :: forall m . Model -> Producer LogOrModel m () toCompletion config m = do - m2 <- let ?typeCheckerMode = StronglyTyped in prologue m + m2 <- let ?typeCheckerMode = StronglyTyped in prologue config m namegenst <- exportNameGenState let m2Info = mInfo m2 let m3 = m2 { mInfo = m2Info { miStrategyQ = strategyQ config @@ -1089,8 +1089,10 @@ prologue :: NameGen m => EnumerateDomain m => (?typeCheckerMode :: TypeCheckerMode) => - Model -> m Model -prologue model = do + Config -> + Model -> + m Model +prologue config model = do void $ typeCheckModel_StandAlone model return model >>= logDebugIdModel "[input]" >>= enforceTagConsistency >>= logDebugIdModel "[enforceTagConsistency]" @@ -1101,13 +1103,16 @@ prologue model = do >>= lettingsForComplexInDoms >>= logDebugIdModel "[lettingsForComplexInDoms]" >>= distinctQuantifiedVars >>= logDebugIdModel "[distinctQuantifiedVars]" >>= return . initInfo >>= logDebugIdModel "[initInfo]" + >>= addUnnamedSymmetryBreaking (unnamedSymmetryBreaking config ) + >>= logDebugIdModel "[addUnnamedSymmetryBreaking]" >>= removeUnnamedsFromModel >>= logDebugIdModel "[removeUnnamedsFromModel]" >>= removeEnumsFromModel >>= logDebugIdModel "[removeEnumsFromModel]" >>= finiteGivens >>= logDebugIdModel "[finiteGivens]" >>= resolveNames >>= logDebugIdModel "[resolveNames]" >>= return . initInfo_Lettings >>= logDebugIdModel "[initInfo_Lettings]" >>= removeDomainLettings >>= logDebugIdModel "[removeDomainLettings]" - >>= typeCheckModel >>= logDebugIdModel "[typeCheckModel]" + >>= (let ?typeCheckerMode = RelaxedIntegerTags in typeCheckModel) + >>= logDebugIdModel "[typeCheckModel]" >>= categoryChecking >>= logDebugIdModel "[categoryChecking]" >>= sanityChecks >>= logDebugIdModel "[sanityChecks]" >>= dealWithCuts >>= logDebugIdModel "[dealWithCuts]" @@ -1115,10 +1120,6 @@ prologue model = do >>= return . addTrueConstraints >>= logDebugIdModel "[addTrueConstraints]" >>= enforceTagConsistency >>= logDebugIdModel "[enforceTagConsistency]" -enforceTagConsistency :: MonadFail m => Model -> m Model -enforceTagConsistency model = do - let statements' = transformBi reDomExp $ transformBi reDomConst (mStatements model) - return model { mStatements = statements' } epilogue :: MonadFail m => @@ -2439,3 +2440,88 @@ rule_Xor_To_Sum = "xor-to-sum" `namedRule` theRule where , return [essence| 1 = sum([ toInt(&i) | &iPat <- &arg ]) |] ) theRule _ = na "rule_Xor_To_Sum" + + +enforceTagConsistency :: MonadFail m => Model -> m Model +enforceTagConsistency model = do + let statements' = transformBi reDomExp $ transformBi reDomConst (mStatements model) + return model { mStatements = statements' } + + +addUnnamedSymmetryBreaking :: + NameGen m => + UnnamedSymmetryBreaking -> + Model -> + m Model +addUnnamedSymmetryBreaking mode model = do + + let + allUnnamedTypes :: [(Domain () Expression, Expression)] + allUnnamedTypes = + [ (DomainReference nm Nothing, x) + | Declaration (LettingDomainDefnUnnamed nm x) <- mStatements model + ] + + allDecVars = + [ Reference nm Nothing + | Declaration (FindOrGiven Find nm _ ) <- mStatements model + ] + + varsTuple = AbstractLiteral $ AbsLitTuple allDecVars + + traceM $ show $ "Unnamed types in this model:" <+> prettyList id "," allUnnamedTypes + traceM $ show $ "Unnamed decision variables in this model:" <+> prettyList id "," allDecVars + + case mode of + None -> return model + FastConsecutive -> do + -- independently for each unnamed type + -- for pairs of (i, i+1) : U + -- add a .<= on a tuple of all decision variables + stmts <- sequence + [ do + (iPat, i) <- quantifiedVar + return [essence| + and([ &varsTuple .<= image(permutation((&i, &i+1)), &varsTuple) + | &iPat : &u + , &i < &uSize + ]) + |] + | (u, uSize) <- allUnnamedTypes + ] + traceM $ show $ vcat $ "Adding the following unnamed symmetry breaking constraints:" + : map (nest 4 . pretty) stmts + return model { mStatements = mStatements model ++ [SuchThat stmts] } + FastAllpairs -> do + -- independently for each unnamed type + -- for pairs of (i, j) : U i < j + -- add a .<= + stmts <- sequence + [ do + (iPat, i) <- quantifiedVar + (jPat, j) <- quantifiedVar + return [essence| + and([ &varsTuple .<= image(permutation((&i, &j)), &varsTuple) + | &iPat : &u + , &jPat : &u + , &i < &j + ]) + |] + | (u, _uSize) <- allUnnamedTypes + ] + traceM $ show $ vcat $ "Adding the following unnamed symmetry breaking constraints:" + : map (nest 4 . pretty) stmts + return model { mStatements = mStatements model ++ [SuchThat stmts] } + CompleteIndependently -> do + -- independently for each unnamed type + -- introduce an aux for each top level decision variable + -- aux_x = image(perm, x) + -- add a .<= on x and aux_x + return model + Complete -> do + -- introduce an aux for each top level decision variable + -- aux_x = image(perm_U, image(perm_T, x)) + -- add a .<= on x and aux_x + return model + + From cd33bdf7b330df350e4777e5db9f690c64a4b5ba Mon Sep 17 00:00:00 2001 From: Fraser Dunlop Date: Mon, 13 May 2019 16:59:48 +0100 Subject: [PATCH 092/229] remove dead code --- src/Conjure/Rules/Horizontal/Permutation.hs | 13 ------------- src/Conjure/Rules/Vertical/Permutation.hs | 16 ---------------- src/Conjure/UI/Model.hs | 1 - 3 files changed, 30 deletions(-) diff --git a/src/Conjure/Rules/Horizontal/Permutation.hs b/src/Conjure/Rules/Horizontal/Permutation.hs index b949cf734e..7dcb9b6dc6 100644 --- a/src/Conjure/Rules/Horizontal/Permutation.hs +++ b/src/Conjure/Rules/Horizontal/Permutation.hs @@ -17,19 +17,6 @@ rule_Cardinality_Literal = "permutation-cardinality-literal" `namedRule` theRule return [essence| &i |] ) -rule_Image_DotLt :: Rule -rule_Image_DotLt = "permutation-image-dotlt{AsFunction}" `namedRule` theRule where - theRule [essence| image(&p, &i) .< &q |] = do - TypePermutation _ <- typeOf p - return ( "Horizontal rule for image of permutation DotLt" - , do - (piPat, pi) <- quantifiedVar - (qiPat, qi) <- quantifiedVar - return [essence| [&pi | &piPat <- image(&p, &i)] .< [&qi | &qiPat <- &q] |] - ) - theRule _ = na "rule_Image_DotLt" - - rule_Equality :: Rule rule_Equality = "permutation-equality" `namedRule` theRule where theRule e = do diff --git a/src/Conjure/Rules/Vertical/Permutation.hs b/src/Conjure/Rules/Vertical/Permutation.hs index ed9ba4a87b..53644662ec 100644 --- a/src/Conjure/Rules/Vertical/Permutation.hs +++ b/src/Conjure/Rules/Vertical/Permutation.hs @@ -83,22 +83,6 @@ rule_Image = "permutation-image{AsFunction}" `namedRule` theRule where _ -> na "rule_Image" theRule _ = na "rule_Image" - -rule_Permutation_DotLt :: Rule -rule_Permutation_DotLt = "permuation-dotlt" `namedRule` theRule where - theRule [essence| &lhs .< &rhs |] = do - TypePermutation _ <- typeOf lhs - TypePermutation _ <- typeOf rhs - [fl] <- downX1 lhs - [fr] <- downX1 rhs - return - ( "Vertical rule for permutation dot less." - , return [essence| &fl .< &fr |] - ) - theRule _ = na "rule_Permutation_DotLt" - - - rule_Matrix_Image :: Rule rule_Matrix_Image = "matrix-image" `namedRule` theRule where theRule [essence| image(&perm, &y) |] = do diff --git a/src/Conjure/UI/Model.hs b/src/Conjure/UI/Model.hs index 95e9624deb..972ab37e93 100644 --- a/src/Conjure/UI/Model.hs +++ b/src/Conjure/UI/Model.hs @@ -1253,7 +1253,6 @@ verticalRules = , Vertical.Permutation.rule_Cardinality , Vertical.Permutation.rule_Defined , Vertical.Permutation.rule_Comprehension - -- , Vertical.Permutation.rule_Permutation_DotLt , Vertical.Tuple.rule_Tuple_Eq From bf8a9c139015a1aa276035dc3c7d2a85722a1a5a Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?O=CC=88zgu=CC=88r=20Akgu=CC=88n?= Date: Mon, 13 May 2019 17:11:15 +0100 Subject: [PATCH 093/229] add FastAllPermutations as well --- src/Conjure/Rules/Definition.hs | 1 + src/Conjure/UI/MainHelper.hs | 5 ++-- src/Conjure/UI/Model.hs | 50 ++++++++++++++++++++++++--------- 3 files changed, 40 insertions(+), 16 deletions(-) diff --git a/src/Conjure/Rules/Definition.hs b/src/Conjure/Rules/Definition.hs index 6875b047ac..fe76d23536 100644 --- a/src/Conjure/Rules/Definition.hs +++ b/src/Conjure/Rules/Definition.hs @@ -144,6 +144,7 @@ data UnnamedSymmetryBreaking = None | FastConsecutive | FastAllpairs + | FastAllPermutations | CompleteIndependently | Complete deriving (Eq, Ord, Show, Read, Data, Typeable) diff --git a/src/Conjure/UI/MainHelper.hs b/src/Conjure/UI/MainHelper.hs index 2b695f83d4..6b472dda84 100644 --- a/src/Conjure/UI/MainHelper.hs +++ b/src/Conjure/UI/MainHelper.hs @@ -107,8 +107,9 @@ mainWithArgs Modelling{..} = do unnamedSymmetryBreakingParsed <- case unnamedSymmetryBreaking of "none" -> return None - "fast-consecutive" -> return FastConsecutive - "fast-allpairs" -> return FastAllpairs + "fast-consecutive" -> return FastConsecutive -- quick, consecutive, independently + "fast-allpairs" -> return FastAllpairs -- quick, allpairs, independently + "fast-allpermutations" -> return FastAllPermutations -- quick, allperms, independently "complete-independently" -> return CompleteIndependently "complete" -> return Complete _ -> userErr1 $ vcat diff --git a/src/Conjure/UI/Model.hs b/src/Conjure/UI/Model.hs index 713f72490e..c4a9416397 100644 --- a/src/Conjure/UI/Model.hs +++ b/src/Conjure/UI/Model.hs @@ -2463,22 +2463,30 @@ addUnnamedSymmetryBreaking mode model = do ] allDecVars = - [ Reference nm Nothing - | Declaration (FindOrGiven Find nm _ ) <- mStatements model + [ (Reference nm Nothing, domain) + | Declaration (FindOrGiven Find nm domain) <- mStatements model ] - varsTuple = AbstractLiteral $ AbsLitTuple allDecVars + varsTuple = AbstractLiteral $ AbsLitTuple $ map fst allDecVars traceM $ show $ "Unnamed types in this model:" <+> prettyList id "," allUnnamedTypes traceM $ show $ "Unnamed decision variables in this model:" <+> prettyList id "," allDecVars - case mode of + -- 3 axis of doom + -- 1. quick/complete. quick is x .<= p(x) + -- complete is x .<= y /\ y = p(x) + -- 2. scope. consecutive + -- all-pairs + -- all-permutations + -- 3. independently/altogether + + stmts <- case mode of None -> return model FastConsecutive -> do -- independently for each unnamed type -- for pairs of (i, i+1) : U -- add a .<= on a tuple of all decision variables - stmts <- sequence + sequence [ do (iPat, i) <- quantifiedVar return [essence| @@ -2489,14 +2497,11 @@ addUnnamedSymmetryBreaking mode model = do |] | (u, uSize) <- allUnnamedTypes ] - traceM $ show $ vcat $ "Adding the following unnamed symmetry breaking constraints:" - : map (nest 4 . pretty) stmts - return model { mStatements = mStatements model ++ [SuchThat stmts] } FastAllpairs -> do -- independently for each unnamed type -- for pairs of (i, j) : U i < j -- add a .<= - stmts <- sequence + sequence [ do (iPat, i) <- quantifiedVar (jPat, j) <- quantifiedVar @@ -2509,19 +2514,36 @@ addUnnamedSymmetryBreaking mode model = do |] | (u, _uSize) <- allUnnamedTypes ] - traceM $ show $ vcat $ "Adding the following unnamed symmetry breaking constraints:" - : map (nest 4 . pretty) stmts - return model { mStatements = mStatements model ++ [SuchThat stmts] } + FastAllPermutations -> do + -- independently for each unnamed type + -- for all p : permutation of U + -- add a .<= + sequence + [ do + (iPat, i) <- quantifiedVar + return [essence| + and([ &varsTuple .<= image(&i, &varsTuple) + | &iPat : permutation of &u + ]) + |] + | (u, _uSize) <- allUnnamedTypes + ] CompleteIndependently -> do -- independently for each unnamed type -- introduce an aux for each top level decision variable -- aux_x = image(perm, x) -- add a .<= on x and aux_x - return model + return [] Complete -> do -- introduce an aux for each top level decision variable -- aux_x = image(perm_U, image(perm_T, x)) -- add a .<= on x and aux_x - return model + return [] + + traceM $ show $ vcat $ "Adding the following unnamed symmetry breaking constraints:" + : map (nest 4 . pretty) stmts + return model { mStatements = mStatements model ++ [SuchThat stmts] } + + From 51567311d0d15c0182a4a707abdf59e8e333bb46 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?O=CC=88zgu=CC=88r=20Akgu=CC=88n?= Date: Tue, 14 May 2019 11:48:31 +0100 Subject: [PATCH 094/229] Finished --unnamed-symmetry-breaking command line flag and the generators --- src/Conjure/Process/Enumerate.hs | 1 + src/Conjure/Rules/Definition.hs | 36 +++++-- src/Conjure/UI/MainHelper.hs | 61 ++++++++--- src/Conjure/UI/Model.hs | 175 +++++++++++++++++++++---------- 4 files changed, 194 insertions(+), 79 deletions(-) diff --git a/src/Conjure/Process/Enumerate.hs b/src/Conjure/Process/Enumerate.hs index a74c22dcf0..bd24afae4f 100644 --- a/src/Conjure/Process/Enumerate.hs +++ b/src/Conjure/Process/Enumerate.hs @@ -154,6 +154,7 @@ enumerateDomain d = liftIO' $ withSystemTempDirectory ("conjure-enumerateDomain- , representationsCuts = Nothing , channelling = False , representationLevels = True + , unnamedSymmetryBreaking = "none" , useExistingModels = [] , seed = Nothing , limitModels = Nothing diff --git a/src/Conjure/Rules/Definition.hs b/src/Conjure/Rules/Definition.hs index fe76d23536..fbba43fbe4 100644 --- a/src/Conjure/Rules/Definition.hs +++ b/src/Conjure/Rules/Definition.hs @@ -7,7 +7,7 @@ module Conjure.Rules.Definition , LogOrModel, LogOr , Driver, Strategy(..), viewAuto, parseStrategy , Config(..) - , UnnamedSymmetryBreaking(..) + , UnnamedSymmetryBreaking(..), USBQuickOrComplete(..), USBScope(..), USBIndependentlyOrAltogether(..) , ModelZipper, mkModelZipper, fromModelZipper , ModelWIP(..), modelWIPOut, updateModelWIPInfo , isAtomic @@ -101,7 +101,7 @@ data Config = Config , outputDirectory :: FilePath , channelling :: Bool , representationLevels :: Bool - , unnamedSymmetryBreaking :: UnnamedSymmetryBreaking + , unnamedSymmetryBreaking :: Maybe UnnamedSymmetryBreaking , limitModels :: Maybe Int , numberingStart :: Int , smartFilenames :: Bool @@ -131,7 +131,7 @@ instance Default Config where , outputDirectory = "conjure-output" , channelling = True , representationLevels = True - , unnamedSymmetryBreaking = None + , unnamedSymmetryBreaking = Nothing , limitModels = Nothing , numberingStart = 1 , smartFilenames = False @@ -140,14 +140,30 @@ instance Default Config where , estimateNumberOfModels = False } -data UnnamedSymmetryBreaking - = None - | FastConsecutive - | FastAllpairs - | FastAllPermutations - | CompleteIndependently - | Complete + +-- 1. Quick/Complete. Quick is x .<= p(x) +-- Complete is x .<= y /\ y = p(x) +-- 2. Scope. Consecutive +-- AllPairs +-- AllPermutations +-- 3. Independently/Altogether +-- in addition, we have +-- none +-- fast: Quick-Consecutive-Independently +-- full: Complete-AllPermutations-Altogether +data UnnamedSymmetryBreaking = + UnnamedSymmetryBreaking + USBQuickOrComplete + USBScope + USBIndependentlyOrAltogether + deriving (Eq, Ord, Show, Read, Data, Typeable) +data USBQuickOrComplete = USBQuick | USBComplete + deriving (Eq, Ord, Show, Read, Data, Typeable) +data USBScope = USBConsecutive | USBAllPairs | USBAllPermutations deriving (Eq, Ord, Show, Read, Data, Typeable) +data USBIndependentlyOrAltogether = USBIndependently | USBAltogether + deriving (Eq, Ord, Show, Read, Data, Typeable) + data RuleResult m = RuleResult { ruleResultDescr :: Doc -- describe this transformation diff --git a/src/Conjure/UI/MainHelper.hs b/src/Conjure/UI/MainHelper.hs index 6b472dda84..aabaece279 100644 --- a/src/Conjure/UI/MainHelper.hs +++ b/src/Conjure/UI/MainHelper.hs @@ -26,7 +26,10 @@ import Conjure.Language.NameGen ( NameGenM, runNameGen ) import Conjure.Language.Pretty ( pretty, prettyList, renderNormal, render ) import qualified Conjure.Language.ParserC as ParserC ( parseModel ) import Conjure.Language.ModelDiff ( modelDiffIO ) -import Conjure.Rules.Definition ( viewAuto, Strategy(..), UnnamedSymmetryBreaking(..) ) +import Conjure.Rules.Definition ( viewAuto, Strategy(..) + , UnnamedSymmetryBreaking(..) + , USBQuickOrComplete(..), USBScope(..), USBIndependentlyOrAltogether(..) + ) import Conjure.Process.Enumerate ( EnumerateDomain ) import Conjure.Process.ModelStrengthening ( strengthenModel ) import Conjure.Language.NameResolution ( resolveNamesMulti ) @@ -105,18 +108,52 @@ mainWithArgs Modelling{..} = do ] unnamedSymmetryBreakingParsed <- - case unnamedSymmetryBreaking of - "none" -> return None - "fast-consecutive" -> return FastConsecutive -- quick, consecutive, independently - "fast-allpairs" -> return FastAllpairs -- quick, allpairs, independently - "fast-allpermutations" -> return FastAllPermutations -- quick, allperms, independently - "complete-independently" -> return CompleteIndependently - "complete" -> return Complete + -- 1. Quick/Complete. Quick is x .<= p(x) + -- Complete is x .<= y /\ y = p(x) + -- 2. Scope. Consecutive + -- AllPairs + -- AllPermutations + -- 3. Independently/Altogether + -- in addition, we have + -- none + -- fast: Quick-Consecutive-Independently + -- full: Complete-AllPermutations-Altogether + case (unnamedSymmetryBreaking, splitOn "-" unnamedSymmetryBreaking) of + ("none", _) -> return Nothing + ("fast", _) -> return $ Just $ UnnamedSymmetryBreaking USBQuick USBConsecutive USBIndependently + ("full", _) -> return $ Just $ UnnamedSymmetryBreaking USBComplete USBAllPermutations USBAltogether + (_, [a,b,c]) -> do + a' <- case a of + "Quick" -> return USBQuick + "Complete" -> return USBComplete + _ -> userErr1 $ vcat + [ "Unrecognised value for the first component of --unnamed-symmetry-breaking" + , "Expected one of: Quick / Complete" + , "But got:" <+> pretty a + ] + b' <- case b of + "Consecutive" -> return USBConsecutive + "AllPairs" -> return USBAllPairs + "AllPermutations" -> return USBAllPermutations + _ -> userErr1 $ vcat + [ "Unrecognised value for the second component of --unnamed-symmetry-breaking" + , "Expected one of: Consecutive / AllPairs / AllPermutations" + , "But got:" <+> pretty b + ] + c' <- case c of + "Independently" -> return USBIndependently + "Altogether" -> return USBAltogether + _ -> userErr1 $ vcat + [ "Unrecognised value for the third component of --unnamed-symmetry-breaking" + , "Expected one of: Independently / Altogether" + , "But got:" <+> pretty c + ] + return $ Just $ UnnamedSymmetryBreaking a' b' c' _ -> userErr1 $ vcat - [ "Unrecognised value for --unnamed-symmetry-breaking" - , "Expected one of: none/fast-consecutive/fast-allpairs/complete-independently/complete" - , "But got:" <+> pretty unnamedSymmetryBreaking - ] + [ "Unrecognised value for --unnamed-symmetry-breaking" + , "Maybe try one of: none / fast / full" + , "Got:" <+> pretty unnamedSymmetryBreaking + ] return Config.Config { Config.outputDirectory = outputDirectory diff --git a/src/Conjure/UI/Model.hs b/src/Conjure/UI/Model.hs index c4a9416397..230368e806 100644 --- a/src/Conjure/UI/Model.hs +++ b/src/Conjure/UI/Model.hs @@ -1103,7 +1103,7 @@ prologue config model = do >>= lettingsForComplexInDoms >>= logDebugIdModel "[lettingsForComplexInDoms]" >>= distinctQuantifiedVars >>= logDebugIdModel "[distinctQuantifiedVars]" >>= return . initInfo >>= logDebugIdModel "[initInfo]" - >>= addUnnamedSymmetryBreaking (unnamedSymmetryBreaking config ) + >>= addUnnamedSymmetryBreaking (unnamedSymmetryBreaking config) >>= logDebugIdModel "[addUnnamedSymmetryBreaking]" >>= removeUnnamedsFromModel >>= logDebugIdModel "[removeUnnamedsFromModel]" >>= removeEnumsFromModel >>= logDebugIdModel "[removeEnumsFromModel]" @@ -2450,7 +2450,7 @@ enforceTagConsistency model = do addUnnamedSymmetryBreaking :: NameGen m => - UnnamedSymmetryBreaking -> + Maybe UnnamedSymmetryBreaking -> Model -> m Model addUnnamedSymmetryBreaking mode model = do @@ -2467,83 +2467,144 @@ addUnnamedSymmetryBreaking mode model = do | Declaration (FindOrGiven Find nm domain) <- mStatements model ] + allDecVarsAux = + [ (Reference (mconcat [nm, "_aux"]) Nothing, domain) + | Declaration (FindOrGiven Find nm domain) <- mStatements model + ] + varsTuple = AbstractLiteral $ AbsLitTuple $ map fst allDecVars + auxsTuple = AbstractLiteral $ AbsLitTuple $ map fst allDecVarsAux traceM $ show $ "Unnamed types in this model:" <+> prettyList id "," allUnnamedTypes traceM $ show $ "Unnamed decision variables in this model:" <+> prettyList id "," allDecVars -- 3 axis of doom - -- 1. quick/complete. quick is x .<= p(x) - -- complete is x .<= y /\ y = p(x) - -- 2. scope. consecutive - -- all-pairs - -- all-permutations - -- 3. independently/altogether - - stmts <- case mode of - None -> return model - FastConsecutive -> do - -- independently for each unnamed type - -- for pairs of (i, i+1) : U - -- add a .<= on a tuple of all decision variables - sequence - [ do + -- 1. Quick/Complete. Quick is x .<= p(x) + -- Complete is x .<= y /\ y = p(x) + -- 2. Scope. Consecutive + -- AllPairs + -- AllPermutations + -- 3. Independently/Altogether + + case mode of + Nothing -> return model + Just (UnnamedSymmetryBreaking quickOrComplete usbScope independentlyOrAltogether) -> do + + let + + buildPermutationChain [] vars = vars + buildPermutationChain (p:ps) vars = + let applied = buildPermutationChain ps vars + in [essence| image(&p, &applied) |] + + combinedPermApply perms = + case quickOrComplete of + USBQuick -> + let applied = buildPermutationChain perms varsTuple + in [essence| &varsTuple .<= &applied |] + USBComplete -> + let applied = buildPermutationChain perms auxsTuple + in [essence| &varsTuple .<= &applied |] + + + mkGenerator_Consecutive _ [] = bug "must have at least one unnamed type" + mkGenerator_Consecutive perms [(u, uSize)] = do (iPat, i) <- quantifiedVar + let perm = [essence| permutation((&i, &i+1)) |] + let applied = combinedPermApply (perm:perms) return [essence| - and([ &varsTuple .<= image(permutation((&i, &i+1)), &varsTuple) + and([ &applied | &iPat : &u , &i < &uSize ]) - |] - | (u, uSize) <- allUnnamedTypes - ] - FastAllpairs -> do - -- independently for each unnamed type - -- for pairs of (i, j) : U i < j - -- add a .<= - sequence - [ do + |] + mkGenerator_Consecutive perms ((u, uSize):us) = do + (iPat, i) <- quantifiedVar + let perm = [essence| permutation((&i, &i+1)) |] + applied <- mkGenerator_Consecutive (perm:perms) us + return [essence| + and([ &applied + | &iPat : &u + , &i < &uSize + ]) + |] + + + mkGenerator_AllPairs _ [] = bug "must have at least one unnamed type" + mkGenerator_AllPairs perms [(u, _uSize)] = do (iPat, i) <- quantifiedVar (jPat, j) <- quantifiedVar + let perm = [essence| permutation((&i, &j)) |] + let applied = combinedPermApply (perm:perms) return [essence| - and([ &varsTuple .<= image(permutation((&i, &j)), &varsTuple) + and([ &applied | &iPat : &u , &jPat : &u , &i < &j ]) - |] - | (u, _uSize) <- allUnnamedTypes - ] - FastAllPermutations -> do - -- independently for each unnamed type - -- for all p : permutation of U - -- add a .<= - sequence - [ do + |] + mkGenerator_AllPairs perms ((u, _uSize):us) = do (iPat, i) <- quantifiedVar + (jPat, j) <- quantifiedVar + let perm = [essence| permutation((&i, &j)) |] + applied <- mkGenerator_AllPairs (perm:perms) us return [essence| - and([ &varsTuple .<= image(&i, &varsTuple) - | &iPat : permutation of &u + and([ &applied + | &iPat : &u + , &jPat : &u + , &i < &j ]) - |] - | (u, _uSize) <- allUnnamedTypes - ] - CompleteIndependently -> do - -- independently for each unnamed type - -- introduce an aux for each top level decision variable - -- aux_x = image(perm, x) - -- add a .<= on x and aux_x - return [] - Complete -> do - -- introduce an aux for each top level decision variable - -- aux_x = image(perm_U, image(perm_T, x)) - -- add a .<= on x and aux_x - return [] - - traceM $ show $ vcat $ "Adding the following unnamed symmetry breaking constraints:" - : map (nest 4 . pretty) stmts - return model { mStatements = mStatements model ++ [SuchThat stmts] } + |] + mkGenerator_AllPermutations _ [] = bug "must have at least one unnamed type" + mkGenerator_AllPermutations perms [(u, _uSize)] = do + (iPat, i) <- quantifiedVar + let perm = i + let applied = combinedPermApply (perm:perms) + return [essence| + and([ &applied + | &iPat : permutation of &u + ]) + |] + mkGenerator_AllPermutations perms ((u, _uSize):us) = do + (iPat, i) <- quantifiedVar + let perm = i + applied <- mkGenerator_AllPermutations (perm:perms) us + return [essence| + and([ &applied + | &iPat : permutation of &u + ]) + |] + + mkGenerator perms us = + case usbScope of + USBConsecutive -> mkGenerator_Consecutive perms us + USBAllPairs -> mkGenerator_AllPairs perms us + USBAllPermutations -> mkGenerator_AllPermutations perms us + + newCons <- + case independentlyOrAltogether of + USBIndependently -> + sequence + [ mkGenerator [] [(u, uSize)] + | (u, uSize) <- allUnnamedTypes + ] + USBAltogether -> do + cons <- mkGenerator [] allUnnamedTypes + return [cons] + + let newDecls = + case quickOrComplete of + USBQuick -> [] + USBComplete -> + [ Declaration (FindOrGiven Find nm' domain) + | Declaration (FindOrGiven Find nm domain) <- mStatements model + , let nm' = mconcat [nm, "_aux"] + ] + let stmts = newDecls ++ [SuchThat newCons] + traceM $ show $ vcat $ "Adding the following unnamed symmetry breaking constraints:" + : map (nest 4 . pretty) stmts + return model { mStatements = mStatements model ++ stmts } From f53402e19c25445f95fdc06c1c8a152f37a03527 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?O=CC=88zgu=CC=88r=20Akgu=CC=88n?= Date: Tue, 14 May 2019 11:51:21 +0100 Subject: [PATCH 095/229] fiddle with the trace statements --- src/Conjure/UI/Model.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/src/Conjure/UI/Model.hs b/src/Conjure/UI/Model.hs index 5790d3f2e2..1768cb2a02 100644 --- a/src/Conjure/UI/Model.hs +++ b/src/Conjure/UI/Model.hs @@ -2474,8 +2474,8 @@ addUnnamedSymmetryBreaking mode model = do varsTuple = AbstractLiteral $ AbsLitTuple $ map fst allDecVars auxsTuple = AbstractLiteral $ AbsLitTuple $ map fst allDecVarsAux - traceM $ show $ "Unnamed types in this model:" <+> prettyList id "," allUnnamedTypes - traceM $ show $ "Unnamed decision variables in this model:" <+> prettyList id "," allDecVars + traceM $ show $ "Unnamed types in this model:" <++> prettyList id "," allUnnamedTypes + traceM $ show $ "Unnamed decision variables in this model:" <++> prettyList id "," allDecVars -- 3 axis of doom -- 1. Quick/Complete. Quick is x .<= p(x) From 52d1ebadbef46e561d9484314dc77bc8839354c7 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?O=CC=88zgu=CC=88r=20Akgu=CC=88n?= Date: Tue, 14 May 2019 12:03:52 +0100 Subject: [PATCH 096/229] fix the complete flavours --- src/Conjure/UI/Model.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/src/Conjure/UI/Model.hs b/src/Conjure/UI/Model.hs index 1768cb2a02..a6046634e2 100644 --- a/src/Conjure/UI/Model.hs +++ b/src/Conjure/UI/Model.hs @@ -2502,8 +2502,8 @@ addUnnamedSymmetryBreaking mode model = do let applied = buildPermutationChain perms varsTuple in [essence| &varsTuple .<= &applied |] USBComplete -> - let applied = buildPermutationChain perms auxsTuple - in [essence| &varsTuple .<= &applied |] + let applied = buildPermutationChain perms varsTuple + in [essence| &varsTuple .<= &auxsTuple /\ &auxsTuple = &applied |] mkGenerator_Consecutive _ [] = bug "must have at least one unnamed type" From afd04ccaed23e624e9cac0e01701a147ce5f76ac Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?O=CC=88zgu=CC=88r=20Akgu=CC=88n?= Date: Tue, 14 May 2019 12:17:44 +0100 Subject: [PATCH 097/229] One aux variable per unnamed type when doing Complete-*-Altogether --- src/Conjure/UI/Model.hs | 71 +++++++++++++++++++++++------------------ 1 file changed, 40 insertions(+), 31 deletions(-) diff --git a/src/Conjure/UI/Model.hs b/src/Conjure/UI/Model.hs index a6046634e2..2cc1312e4b 100644 --- a/src/Conjure/UI/Model.hs +++ b/src/Conjure/UI/Model.hs @@ -2466,13 +2466,13 @@ addUnnamedSymmetryBreaking mode model = do | Declaration (FindOrGiven Find nm domain) <- mStatements model ] - allDecVarsAux = - [ (Reference (mconcat [nm, "_aux"]) Nothing, domain) + allDecVarsAux auxSuffix = + [ (Reference (mconcat [nm, "_auxFor_", auxSuffix]) Nothing, domain) | Declaration (FindOrGiven Find nm domain) <- mStatements model ] varsTuple = AbstractLiteral $ AbsLitTuple $ map fst allDecVars - auxsTuple = AbstractLiteral $ AbsLitTuple $ map fst allDecVarsAux + mkAuxTuple auxSuffix = AbstractLiteral $ AbsLitTuple $ map fst (allDecVarsAux auxSuffix) traceM $ show $ "Unnamed types in this model:" <++> prettyList id "," allUnnamedTypes traceM $ show $ "Unnamed decision variables in this model:" <++> prettyList id "," allDecVars @@ -2496,31 +2496,32 @@ addUnnamedSymmetryBreaking mode model = do let applied = buildPermutationChain ps vars in [essence| image(&p, &applied) |] - combinedPermApply perms = + combinedPermApply auxSuffix perms = case quickOrComplete of USBQuick -> let applied = buildPermutationChain perms varsTuple in [essence| &varsTuple .<= &applied |] USBComplete -> let applied = buildPermutationChain perms varsTuple - in [essence| &varsTuple .<= &auxsTuple /\ &auxsTuple = &applied |] + thisAuxTuple = mkAuxTuple auxSuffix + in [essence| &varsTuple .<= &thisAuxTuple /\ &thisAuxTuple = &applied |] - mkGenerator_Consecutive _ [] = bug "must have at least one unnamed type" - mkGenerator_Consecutive perms [(u, uSize)] = do + mkGenerator_Consecutive _ _ [] = bug "must have at least one unnamed type" + mkGenerator_Consecutive auxSuffix perms [(u, uSize)] = do (iPat, i) <- quantifiedVar let perm = [essence| permutation((&i, &i+1)) |] - let applied = combinedPermApply (perm:perms) + let applied = combinedPermApply auxSuffix (perm:perms) return [essence| and([ &applied | &iPat : &u , &i < &uSize ]) |] - mkGenerator_Consecutive perms ((u, uSize):us) = do + mkGenerator_Consecutive auxSuffix perms ((u, uSize):us) = do (iPat, i) <- quantifiedVar let perm = [essence| permutation((&i, &i+1)) |] - applied <- mkGenerator_Consecutive (perm:perms) us + applied <- mkGenerator_Consecutive auxSuffix (perm:perms) us return [essence| and([ &applied | &iPat : &u @@ -2529,12 +2530,12 @@ addUnnamedSymmetryBreaking mode model = do |] - mkGenerator_AllPairs _ [] = bug "must have at least one unnamed type" - mkGenerator_AllPairs perms [(u, _uSize)] = do + mkGenerator_AllPairs _ _ [] = bug "must have at least one unnamed type" + mkGenerator_AllPairs auxSuffix perms [(u, _uSize)] = do (iPat, i) <- quantifiedVar (jPat, j) <- quantifiedVar let perm = [essence| permutation((&i, &j)) |] - let applied = combinedPermApply (perm:perms) + let applied = combinedPermApply auxSuffix (perm:perms) return [essence| and([ &applied | &iPat : &u @@ -2542,11 +2543,11 @@ addUnnamedSymmetryBreaking mode model = do , &i < &j ]) |] - mkGenerator_AllPairs perms ((u, _uSize):us) = do + mkGenerator_AllPairs auxSuffix perms ((u, _uSize):us) = do (iPat, i) <- quantifiedVar (jPat, j) <- quantifiedVar let perm = [essence| permutation((&i, &j)) |] - applied <- mkGenerator_AllPairs (perm:perms) us + applied <- mkGenerator_AllPairs auxSuffix (perm:perms) us return [essence| and([ &applied | &iPat : &u @@ -2555,51 +2556,59 @@ addUnnamedSymmetryBreaking mode model = do ]) |] - mkGenerator_AllPermutations _ [] = bug "must have at least one unnamed type" - mkGenerator_AllPermutations perms [(u, _uSize)] = do + mkGenerator_AllPermutations _ _ [] = bug "must have at least one unnamed type" + mkGenerator_AllPermutations auxSuffix perms [(u, _uSize)] = do (iPat, i) <- quantifiedVar let perm = i - let applied = combinedPermApply (perm:perms) + let applied = combinedPermApply auxSuffix (perm:perms) return [essence| and([ &applied | &iPat : permutation of &u ]) |] - mkGenerator_AllPermutations perms ((u, _uSize):us) = do + mkGenerator_AllPermutations auxSuffix perms ((u, _uSize):us) = do (iPat, i) <- quantifiedVar let perm = i - applied <- mkGenerator_AllPermutations (perm:perms) us + applied <- mkGenerator_AllPermutations auxSuffix (perm:perms) us return [essence| and([ &applied | &iPat : permutation of &u ]) |] - mkGenerator perms us = + mkGenerator auxSuffix perms us = case usbScope of - USBConsecutive -> mkGenerator_Consecutive perms us - USBAllPairs -> mkGenerator_AllPairs perms us - USBAllPermutations -> mkGenerator_AllPermutations perms us + USBConsecutive -> mkGenerator_Consecutive auxSuffix perms us + USBAllPairs -> mkGenerator_AllPairs auxSuffix perms us + USBAllPermutations -> mkGenerator_AllPermutations auxSuffix perms us newCons <- case independentlyOrAltogether of USBIndependently -> sequence - [ mkGenerator [] [(u, uSize)] - | (u, uSize) <- allUnnamedTypes + [ mkGenerator uName [] [(u, uSize)] + | (u@(DomainReference uName _), uSize) <- allUnnamedTypes ] USBAltogether -> do - cons <- mkGenerator [] allUnnamedTypes + cons <- mkGenerator "all" [] allUnnamedTypes return [cons] let newDecls = case quickOrComplete of USBQuick -> [] USBComplete -> - [ Declaration (FindOrGiven Find nm' domain) - | Declaration (FindOrGiven Find nm domain) <- mStatements model - , let nm' = mconcat [nm, "_aux"] - ] + case independentlyOrAltogether of + USBIndependently -> + [ Declaration (FindOrGiven Find nm' domain) + | Declaration (FindOrGiven Find nm domain) <- mStatements model + , (DomainReference uName _, _) <- allUnnamedTypes + , let nm' = mconcat [nm, "_auxFor_", uName] + ] + USBAltogether -> + [ Declaration (FindOrGiven Find nm' domain) + | Declaration (FindOrGiven Find nm domain) <- mStatements model + , let nm' = mconcat [nm, "_auxFor_all"] + ] let stmts = newDecls ++ [SuchThat newCons] From 5579326696fc505f99e6d7e32bd9b1e332b120ea Mon Sep 17 00:00:00 2001 From: Fraser Dunlop Date: Tue, 14 May 2019 16:15:24 +0100 Subject: [PATCH 098/229] rewrite flattenLex and acceptAllOutputs --- src/Conjure/Representations.hs | 3 + src/Conjure/UI/Model.hs | 85 +++++++++---------- .../stderr.expected | 2 +- .../0020_size_3/stderr.expected | 35 ++++++++ .../0020_size_3/stdout.expected | 7 -- .../autogen/gen17/expected/model_1.eprime | 3 +- .../autogen/gen17/expected/model_2.eprime | 3 +- .../autogen/gen25/expected/model_1.eprime | 3 +- .../autogen/gen25/expected/model_2.eprime | 3 +- .../autogen/gen35/expected/model_1.eprime | 18 ++-- .../autogen/gen35/expected/model_2.eprime | 14 ++- .../autogen/gen37/expected/model_1.eprime | 18 ++-- .../autogen/gen37/expected/model_2.eprime | 14 ++- .../autogen/gen37/expected/model_3.eprime | 8 +- .../autogen/gen37/expected/model_4.eprime | 4 +- .../comprehension_01_2/expected/model.eprime | 3 +- .../comprehension_02_2/expected/model.eprime | 3 +- .../comprehension_03_2/expected/model.eprime | 3 +- .../basic/cut_01_off/expected/model_2.eprime | 3 +- .../basic/cut_01_off/expected/model_3.eprime | 2 +- .../basic/cut_01_off/expected/model_4.eprime | 2 +- .../enum05-unnamed/expected/model_2.eprime | 3 +- .../enum05-unnamed/expected/model_3.eprime | 2 +- .../enum05-unnamed/expected/model_4.eprime | 3 +- .../basic/enum05/expected/model_1_2.eprime | 3 +- .../basic/enum05/expected/model_1_3.eprime | 2 +- .../basic/enum05/expected/model_1_4.eprime | 3 +- .../basic/enum05/expected/model_2_1.eprime | 3 +- .../basic/enum05/expected/model_2_2.eprime | 3 +- .../basic/enum05/expected/model_2_3.eprime | 5 +- .../basic/enum05/expected/model_2_4.eprime | 6 +- .../basic/enum05/expected/model_3_1.eprime | 2 +- .../basic/enum05/expected/model_3_2.eprime | 5 +- .../basic/enum05/expected/model_3_3.eprime | 2 +- .../basic/enum05/expected/model_3_4.eprime | 5 +- .../basic/enum05/expected/model_4_1.eprime | 3 +- .../basic/enum05/expected/model_4_2.eprime | 6 +- .../basic/enum05/expected/model_4_3.eprime | 5 +- .../basic/enum05/expected/model_4_4.eprime | 3 +- .../basic/enum06/expected/model_1_1.eprime | 3 +- .../basic/enum06/expected/model_1_2.eprime | 5 +- .../basic/enum06/expected/model_1_3.eprime | 3 +- .../basic/enum06/expected/model_2_1.eprime | 5 +- .../basic/enum06/expected/model_2_2.eprime | 2 +- .../basic/enum06/expected/model_2_3.eprime | 2 +- .../basic/enum06/expected/model_3_1.eprime | 3 +- .../basic/enum06/expected/model_3_2.eprime | 2 +- .../function_card_02/expected/model.eprime | 2 +- .../expected/model.eprime | 2 +- .../expected/model.eprime | 2 +- .../expected/model.eprime | 2 +- .../expected/model.eprime | 2 +- .../expected/model.eprime | 2 +- .../expected/model_1.eprime | 2 +- .../expected/model_2.eprime | 4 +- .../basic/mset01_find/expected/model_1.eprime | 3 +- .../basic/mset01_find/expected/model_2.eprime | 2 +- .../basic/mset02/expected/model_1.eprime | 3 +- .../basic/mset02/expected/model_2.eprime | 2 +- .../basic/mset03_1/expected/model_1.eprime | 3 +- .../basic/mset03_1/expected/model_2.eprime | 2 +- .../basic/mset03_2/expected/model_1.eprime | 3 +- .../basic/mset03_2/expected/model_2.eprime | 2 +- .../basic/mset04/expected/model_1.eprime | 3 +- .../basic/mset04/expected/model_2.eprime | 3 +- .../basic/mset05/expected/model_1.eprime | 3 +- .../basic/mset05/expected/model_2.eprime | 2 +- .../basic/mset06_1/expected/model_1.eprime | 3 +- .../basic/mset06_1/expected/model_2.eprime | 2 +- .../basic/mset06_2/expected/model_1.eprime | 3 +- .../basic/mset06_2/expected/model_2.eprime | 2 +- .../basic/mset07/expected/model_1.eprime | 3 +- .../basic/mset07/expected/model_2.eprime | 2 +- .../partition_01/expected/model_2.eprime | 7 +- .../partition_02/expected/model_2.eprime | 4 +- .../partition_02/expected/model_3.eprime | 10 +-- .../partition_03/expected/model_2.eprime | 10 +-- .../expected/model_2.eprime | 7 +- .../expected/model_2.eprime | 10 +-- .../expected/model_2.eprime | 10 +-- .../expected/model_2.eprime | 7 +- .../expected/model_4.eprime | 7 +- .../basic/restricted03/expected/model.eprime | 2 +- .../expected/model.eprime | 2 +- .../expected/model.eprime | 2 +- .../basic/set01_1/expected/model_2.eprime | 2 +- .../basic/set01_2/expected/model_1_2.eprime | 2 +- .../basic/set01_2/expected/model_2_1.eprime | 2 +- .../basic/set01_2/expected/model_2_2.eprime | 2 +- .../basic/set01_3/expected/model_1_2.eprime | 2 +- .../basic/set01_3/expected/model_2_1.eprime | 2 +- .../basic/set01_3/expected/model_2_2.eprime | 2 +- .../basic/set02/expected/model_1_2.eprime | 2 +- .../basic/set02/expected/model_2_1.eprime | 2 +- .../basic/set02/expected/model_2_2.eprime | 2 +- .../basic/setOfSet03/expected/model_2.eprime | 7 +- .../set_card_02/expected/model_1_1_2.eprime | 2 +- .../set_card_02/expected/model_1_2_1.eprime | 2 +- .../set_card_02/expected/model_1_2_2.eprime | 2 +- .../set_card_02/expected/model_2_1_1.eprime | 2 +- .../set_card_02/expected/model_2_1_2.eprime | 2 +- .../set_card_02/expected/model_2_2_1.eprime | 2 +- .../set_card_02/expected/model_2_2_2.eprime | 2 +- .../expected/model_2.eprime | 5 +- .../expected/model_3.eprime | 3 +- .../expected/model_4.eprime | 3 +- .../basic/variant01/expected/model_1.eprime | 14 ++- .../basic/variant01/expected/model_2.eprime | 14 ++- .../issues/182/expected/model.eprime | 51 +++++------ .../issues/200/expected/model_1_2.eprime | 2 +- .../issues/200/expected/model_2_1.eprime | 2 +- .../issues/200/expected/model_2_2.eprime | 2 +- .../issues/261/expected/model.eprime | 2 +- .../expected/model-p2-solution000001.solution | 4 - .../issues/263/expected/model-p2.eprime-param | 3 - .../issues/284/expected/model_1_2.eprime | 2 +- .../issues/284/expected/model_2_1.eprime | 2 +- .../issues/284/expected/model_2_2.eprime | 4 +- .../expected/model-solution000001.solution | 3 - .../issues/309/expected/model.eprime | 8 -- 120 files changed, 335 insertions(+), 297 deletions(-) create mode 100644 tests/custom/permutations/21_superpermutations/0020_size_3/stderr.expected delete mode 100644 tests/exhaustive/issues/263/expected/model-p2-solution000001.solution delete mode 100644 tests/exhaustive/issues/263/expected/model-p2.eprime-param delete mode 100644 tests/exhaustive/issues/309/expected/model-solution000001.solution delete mode 100644 tests/exhaustive/issues/309/expected/model.eprime diff --git a/src/Conjure/Representations.hs b/src/Conjure/Representations.hs index 6d1af3c80e..80c78b5420 100644 --- a/src/Conjure/Representations.hs +++ b/src/Conjure/Representations.hs @@ -143,6 +143,9 @@ symmetryOrdering inp = do AbsLitTuple xs -> do soVals <- sequence (symmetryOrdering <$> xs) return $ AbstractLiteral $ AbsLitTuple soVals --make opFlatten (fromList soVals) + AbsLitMatrix d xs -> do + soVals <- sequence (symmetryOrdering <$> xs) + return $ AbstractLiteral $ AbsLitMatrix d soVals _ -> bug ("symmetryOrdering: AbstractLiteral:" <++> pretty (show inp) <++> pretty (inp)) diff --git a/src/Conjure/UI/Model.hs b/src/Conjure/UI/Model.hs index 2cc1312e4b..037ac2edc6 100644 --- a/src/Conjure/UI/Model.hs +++ b/src/Conjure/UI/Model.hs @@ -713,51 +713,50 @@ flattenLex :: MonadFail m => Model -> m Model flattenLex m = do let - deshell (Op (MkOpFlatten (OpFlatten Nothing crab))) = do - (reshell, hermit) <- deshell crab - return (\r -> (Op (MkOpFlatten (OpFlatten Nothing (reshell r)))), hermit) - deshell e = return (id, e) flatten a = do ta <- typeOf a case ta of - TypeList (TypeInt{}) -> return [essence| &a |] - TypeInt{} -> return [essence| [&a] |] - TypeList (TypeList{}) -> flatten [essence| flatten(&a) |] - TypeList (TypeMatrix{}) -> flatten [essence| flatten(&a) |] - TypeMatrix{} -> do -- flatten [essence| flatten(&a) |] + TypeBool -> return [essence| [-toInt(&a)] |] + TypeInt{} -> return [essence| [&a] |] + TypeList TypeInt{} -> return a + TypeMatrix TypeInt{} TypeInt{} -> return a + _ -> case a of - AbstractLiteral (AbsLitMatrix indxDom _) -> do - (iPat,i) <- quantifiedVarOverDomain indxDom - flatten $ Comprehension [essence| &a[&i] |] - [Generator (GenDomainNoRepr iPat indxDom)] - _ -> bug $ "epilogue: flattenLex: isn't defined for this structure.." - <+> vcat [pretty ta, pretty a, stringToDoc $ show a] - TypeList{} -> do - (resh, desh) <- deshell a - case desh of - Comprehension exp goc -> do - nexp <- flatten exp - flatten $ resh $ Comprehension nexp goc - _ -> bug $ "epilogue: flattenLex: isn't defined for this structure..." - <+> vcat [pretty ta, pretty a, stringToDoc $ show a] --- TypeMatrix{} -> do --- (resh, desh) <- deshell a --- deshd <- domainOf desh --- case deshd of --- DomainMatrix indxDom _ -> do --- (iPat,i) <- quantifiedVarOverDomain indxDom --- flatten $ resh [essence| [ &desh[&i] | &iPat : &indxDom ] |] --- _ -> bug $ "epilogue: flattenLex: isn't defined for this structure...." --- <+> vcat [pretty ta, pretty a, stringToDoc $ show a] - TypeTuple{} -> do - case a of - AbstractLiteral (AbsLitTuple exprs) -> do - is <- sequence (flatten <$> exprs) - flatten $ fromList is - _ -> bug $ "epilogue: flattenLex: expected AbsLitTuple...." - <+> vcat [pretty ta, pretty a] - _ -> bug $ "epilogue: flattenLex: isn't defined for this structure....." - <+> vcat [pretty ta, pretty a] + AbstractLiteral x -> do + case x of + AbsLitTuple xs -> do + fxs <- sequence (flatten <$> xs) + let flatxs = fromList fxs + return [essence| flatten(&flatxs) |] + AbsLitMatrix _ xs -> do + fxs <- sequence (flatten <$> xs) + let flatxs = fromList fxs + return [essence| flatten(&flatxs) |] + _ -> bug $ "epilogue: flattenLex: isn't defined for this abslit fellow..." + <+> vcat [pretty a, pretty ta, stringToDoc $ show a] + Constant c -> + case c of + ConstantAbstract ca -> + case ca of + AbsLitTuple xs -> do + fxs <- sequence (flatten <$> (Constant <$> xs)) + let flatxs = fromList fxs + return [essence| flatten(&flatxs) |] + AbsLitMatrix _ xs -> do + fxs <- sequence (flatten <$> (Constant <$> xs)) + let flatxs = fromList fxs + return [essence| flatten(&flatxs) |] + _ -> bug $ "epilogue: flattenLex: isn't defined for this fellow..." + <+> vcat [pretty a, pretty ta, stringToDoc $ show a] + TypedConstant tc _ -> flatten (Constant tc) + _ -> bug $ "epilogue: flattenLex: isn't defined for this constant fellow." + <+> vcat [pretty a, pretty ta, stringToDoc $ show a] + Comprehension body gocs -> do + fbody <- flatten body + let comp = Comprehension fbody gocs + return [essence| flatten(&comp) |] + _ -> bug $ "epilogue: flattenLex: isn't defined for this expression fellow..." + <+> vcat [pretty a, pretty ta, stringToDoc $ show a] flattener [essence| &a prettyList id "," allUnnamedTypes - traceM $ show $ "Unnamed decision variables in this model:" <++> prettyList id "," allDecVars +-- traceM $ show $ "Unnamed types in this model:" <++> prettyList id "," allUnnamedTypes +-- traceM $ show $ "Unnamed decision variables in this model:" <++> prettyList id "," allDecVars -- 3 axis of doom -- 1. Quick/Complete. Quick is x .<= p(x) diff --git a/tests/custom/permutations/17_image_partition/enum/0010_given_partition_of_enum_BUG/stderr.expected b/tests/custom/permutations/17_image_partition/enum/0010_given_partition_of_enum_BUG/stderr.expected index 8d9e3b4c34..31143a8512 100644 --- a/tests/custom/permutations/17_image_partition/enum/0010_given_partition_of_enum_BUG/stderr.expected +++ b/tests/custom/permutations/17_image_partition/enum/0010_given_partition_of_enum_BUG/stderr.expected @@ -8,7 +8,7 @@ However, it did happen, so it must be a bug. Please report it to us! Conjure is actively maintained, we will get back to you as soon as possible. You can help us by providing a minimal failing example. -Also include the repository version for this build: 4a9d4ca08 (2019-02-26 14:02:10 +0000) +Also include the repository version for this build: 3471a2936 (2019-05-08 11:52:07 +0100) Issue tracker: http://github.com/conjure-cp/conjure/issues diff --git a/tests/custom/permutations/21_superpermutations/0020_size_3/stderr.expected b/tests/custom/permutations/21_superpermutations/0020_size_3/stderr.expected new file mode 100644 index 0000000000..50dc7cdffd --- /dev/null +++ b/tests/custom/permutations/21_superpermutations/0020_size_3/stderr.expected @@ -0,0 +1,35 @@ +conjure: This should never happen, sorry! + +However, it did happen, so it must be a bug. Please report it to us! + +Conjure is actively maintained, we will get back to you as soon as possible. +You can help us by providing a minimal failing example. + +Also include the repository version for this build: 3471a2936 (2019-05-08 11:52:07 +0100) + +Issue tracker: http://github.com/conjure-cp/conjure/issues + + + +Not refined: s_ExplicitR20 +Domain : matrix indexed by [int(1..fin1)] of permutation {PermutationAsFunction} of int(1..3) + Context #1: s_ExplicitR20[q3] + Context #2: image(s_ExplicitR20[q3], sequence(1, 2, 3)) + Context #3: image(s_ExplicitR20[q3], sequence(1, 2, 3)) substring superperm + Context #4: [image(s_ExplicitR20[q3], sequence(1, 2, 3)) substring superperm | q3 : int(1..fin1)] + Context #5: and([image(s_ExplicitR20[q3], sequence(1, 2, 3)) substring superperm | q3 : int(1..fin1)]) +Not refined: sequence(1, 2, 3) + Context #1: image(s_ExplicitR20[q3], sequence(1, 2, 3)) + Context #2: image(s_ExplicitR20[q3], sequence(1, 2, 3)) substring superperm + Context #3: [image(s_ExplicitR20[q3], sequence(1, 2, 3)) substring superperm | q3 : int(1..fin1)] + Context #4: and([image(s_ExplicitR20[q3], sequence(1, 2, 3)) substring superperm | q3 : int(1..fin1)]) +Not refined: superperm +Domain : sequence {ExplicitBounded} (maxSize 100) of int(1..3) + Context #1: image(s_ExplicitR20[q3], sequence(1, 2, 3)) substring superperm + Context #2: [image(s_ExplicitR20[q3], sequence(1, 2, 3)) substring superperm | q3 : int(1..fin1)] + Context #3: and([image(s_ExplicitR20[q3], sequence(1, 2, 3)) substring superperm | q3 : int(1..fin1)]) + +CallStack (from HasCallStack): + error, called at src/Conjure/Bug.hs:21:15 in conjure-cp-2.2.0-71NFmy1yFuTKzqIQD5mEC7:Conjure.Bug + bug, called at src/Conjure/UI/Model.hs:936:26 in conjure-cp-2.2.0-71NFmy1yFuTKzqIQD5mEC7:Conjure.UI.Model +cat: conjure-output/*.solution: No such file or directory diff --git a/tests/custom/permutations/21_superpermutations/0020_size_3/stdout.expected b/tests/custom/permutations/21_superpermutations/0020_size_3/stdout.expected index 6d17d75323..d10ebe7b59 100644 --- a/tests/custom/permutations/21_superpermutations/0020_size_3/stdout.expected +++ b/tests/custom/permutations/21_superpermutations/0020_size_3/stdout.expected @@ -1,8 +1 @@ Generating models for permutation.essence -Generated models: model000001.eprime -Saved under: conjure-output -Savile Row: model000001.eprime permutation.param -Copying solution to: permutation-permutation.solution -language Essence 1.3 - -letting superperm be sequence(1, 2, 3, 1, 2, 1, 3, 2, 1) diff --git a/tests/exhaustive/autogen/gen17/expected/model_1.eprime b/tests/exhaustive/autogen/gen17/expected/model_1.eprime index b7c8b7620b..f2c7967cf9 100644 --- a/tests/exhaustive/autogen/gen17/expected/model_1.eprime +++ b/tests/exhaustive/autogen/gen17/expected/model_1.eprime @@ -6,7 +6,8 @@ branching on [var1_ExplicitVarSizeWithMarker_Marker, var1_ExplicitVarSizeWithMar such that false, 2 <= var1_ExplicitVarSizeWithMarker_Marker -> - -toInt(var1_ExplicitVarSizeWithMarker_Values[1]) < -toInt(var1_ExplicitVarSizeWithMarker_Values[2]), + [-toInt(var1_ExplicitVarSizeWithMarker_Values[1]); int(1)] var1_ExplicitVarSizeWithMarker_Marker -> var1_ExplicitVarSizeWithMarker_Values[q2] = false | q2 : int(1..2)]) diff --git a/tests/exhaustive/autogen/gen17/expected/model_2.eprime b/tests/exhaustive/autogen/gen17/expected/model_2.eprime index b7d0c50001..be44a8c757 100644 --- a/tests/exhaustive/autogen/gen17/expected/model_2.eprime +++ b/tests/exhaustive/autogen/gen17/expected/model_2.eprime @@ -6,7 +6,8 @@ branching on [var1_ExplicitVarSizeWithFlags_Flags, var1_ExplicitVarSizeWithFlags such that false, var1_ExplicitVarSizeWithFlags_Flags[2] -> - -toInt(var1_ExplicitVarSizeWithFlags_Values[1]) < -toInt(var1_ExplicitVarSizeWithFlags_Values[2]), + [-toInt(var1_ExplicitVarSizeWithFlags_Values[1]); int(1)] var1_ExplicitVarSizeWithFlags_Values[q2] = false | q2 : int(1..2)]), var1_ExplicitVarSizeWithFlags_Flags[2] -> var1_ExplicitVarSizeWithFlags_Flags[1] diff --git a/tests/exhaustive/autogen/gen25/expected/model_1.eprime b/tests/exhaustive/autogen/gen25/expected/model_1.eprime index b1b11d3b44..7a7abed767 100644 --- a/tests/exhaustive/autogen/gen25/expected/model_1.eprime +++ b/tests/exhaustive/autogen/gen25/expected/model_1.eprime @@ -6,7 +6,8 @@ find var3_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..5)] of boo branching on [var3_ExplicitVarSizeWithMarker_Marker, var3_ExplicitVarSizeWithMarker_Values] such that and([q1 + 1 <= var3_ExplicitVarSizeWithMarker_Marker -> - -toInt(var3_ExplicitVarSizeWithMarker_Values[q1]) < -toInt(var3_ExplicitVarSizeWithMarker_Values[q1 + 1]) + [-toInt(var3_ExplicitVarSizeWithMarker_Values[q1]); int(1)] var3_ExplicitVarSizeWithMarker_Marker -> var3_ExplicitVarSizeWithMarker_Values[q2] = false | q2 : int(1..5)]), diff --git a/tests/exhaustive/autogen/gen25/expected/model_2.eprime b/tests/exhaustive/autogen/gen25/expected/model_2.eprime index daa108ae03..2f3be37f18 100644 --- a/tests/exhaustive/autogen/gen25/expected/model_2.eprime +++ b/tests/exhaustive/autogen/gen25/expected/model_2.eprime @@ -6,7 +6,8 @@ find var3_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..5)] of bool branching on [var3_ExplicitVarSizeWithFlags_Flags, var3_ExplicitVarSizeWithFlags_Values] such that and([var3_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - -toInt(var3_ExplicitVarSizeWithFlags_Values[q1]) < -toInt(var3_ExplicitVarSizeWithFlags_Values[q1 + 1]) + [-toInt(var3_ExplicitVarSizeWithFlags_Values[q1]); int(1)] var3_ExplicitVarSizeWithFlags_Values[q2] = false | q2 : int(1..5)]), diff --git a/tests/exhaustive/autogen/gen35/expected/model_1.eprime b/tests/exhaustive/autogen/gen35/expected/model_1.eprime index ff5aa922c1..46823920d8 100644 --- a/tests/exhaustive/autogen/gen35/expected/model_1.eprime +++ b/tests/exhaustive/autogen/gen35/expected/model_1.eprime @@ -14,19 +14,17 @@ branching on var2_FunctionAsRelationR8R16_RelationAsSetR8R16_ExplicitVarSizeWithMarkerR8R16_Values_2_RelationAsMatrix] such that and([q1 + 1 <= var2_FunctionAsRelationR8R16_RelationAsSetR8R16_ExplicitVarSizeWithMarkerR8R16_Marker -> - flatten([([] : `matrix indexed by [int()] of int`), - flatten([flatten([[-toInt(var2_FunctionAsRelationR8R16_RelationAsSetR8R16_ExplicitVarSizeWithMarkerR8R16_Values_2_RelationAsMatrix - [q1, q15, q16]); - int(1)] - | q16 : bool]) + flatten([flatten([]), + flatten([[-toInt(var2_FunctionAsRelationR8R16_RelationAsSetR8R16_ExplicitVarSizeWithMarkerR8R16_Values_2_RelationAsMatrix + [q1, q15, q16]) + | q16 : bool] | q15 : bool]); int(1..2)]) - -toInt(var1_RelationAsSetR5R8_ExplicitR5R8_1_ExplicitVarSizeWithMarker_Values[q2, 1]) < - -toInt(var1_RelationAsSetR5R8_ExplicitR5R8_1_ExplicitVarSizeWithMarker_Values[q2, 2]) + [-toInt(var1_RelationAsSetR5R8_ExplicitR5R8_1_ExplicitVarSizeWithMarker_Values[q2, 1]); int(1)] var1_RelationAsSetR5R8_ExplicitR5R8_1_ExplicitVarSizeWithMarker_Marker[q2] -> var1_RelationAsSetR5R8_ExplicitR5R8_1_ExplicitVarSizeWithMarker_Values[q2, q4] = false diff --git a/tests/exhaustive/autogen/gen37/expected/model_2.eprime b/tests/exhaustive/autogen/gen37/expected/model_2.eprime index fde9545d3c..d1376c97f6 100644 --- a/tests/exhaustive/autogen/gen37/expected/model_2.eprime +++ b/tests/exhaustive/autogen/gen37/expected/model_2.eprime @@ -13,9 +13,8 @@ branching on var1_RelationAsSetR5R9_ExplicitR5R9_2_ExplicitWithRepetition_Values] such that flatten([flatten([[var1_RelationAsSetR5R9_ExplicitR5R9_1_ExplicitVarSizeWithMarker_Marker[1]; int(1)], - flatten([[-toInt(var1_RelationAsSetR5R9_ExplicitR5R9_1_ExplicitVarSizeWithMarker_Values[1, q11]); - int(1)] - | q11 : int(1..2)]); + [-toInt(var1_RelationAsSetR5R9_ExplicitR5R9_1_ExplicitVarSizeWithMarker_Values[1, q11]) + | q11 : int(1..2)]; int(1..2)]), flatten([[var1_RelationAsSetR5R9_ExplicitR5R9_2_ExplicitWithRepetition_Flag[1]; int(1)], ([] : `matrix indexed by [int()] of int`); @@ -23,17 +22,16 @@ such that int(1..2)]) - -toInt(var1_RelationAsSetR5R9_ExplicitR5R9_1_ExplicitVarSizeWithMarker_Values[q2, 1]) < - -toInt(var1_RelationAsSetR5R9_ExplicitR5R9_1_ExplicitVarSizeWithMarker_Values[q2, 2]) + [-toInt(var1_RelationAsSetR5R9_ExplicitR5R9_1_ExplicitVarSizeWithMarker_Values[q2, 1]); int(1)] var1_RelationAsSetR5R9_ExplicitR5R9_1_ExplicitVarSizeWithMarker_Marker[q2] -> var1_RelationAsSetR5R9_ExplicitR5R9_1_ExplicitVarSizeWithMarker_Values[q2, q4] = false diff --git a/tests/exhaustive/autogen/gen37/expected/model_3.eprime b/tests/exhaustive/autogen/gen37/expected/model_3.eprime index 0c9d2495be..26614fbb51 100644 --- a/tests/exhaustive/autogen/gen37/expected/model_3.eprime +++ b/tests/exhaustive/autogen/gen37/expected/model_3.eprime @@ -18,7 +18,7 @@ such that int(1)]; int(1..2)]) | q14 : int(1..2)]), - ([] : `matrix indexed by [int()] of int`); + flatten([]); int(1..2)]) - -toInt(var1_RelationAsSetR4R8_ExplicitR4R8_1_ExplicitVarSizeWithFlags_Values[q2, 1]) < - -toInt(var1_RelationAsSetR4R8_ExplicitR4R8_1_ExplicitVarSizeWithFlags_Values[q2, 2]) + [-toInt(var1_RelationAsSetR4R8_ExplicitR4R8_1_ExplicitVarSizeWithFlags_Values[q2, 1]); int(1)] var1_RelationAsSetR4R8_ExplicitR4R8_1_ExplicitVarSizeWithFlags_Values[q2, q4] = false diff --git a/tests/exhaustive/autogen/gen37/expected/model_4.eprime b/tests/exhaustive/autogen/gen37/expected/model_4.eprime index e7002c317f..356fa5a41a 100644 --- a/tests/exhaustive/autogen/gen37/expected/model_4.eprime +++ b/tests/exhaustive/autogen/gen37/expected/model_4.eprime @@ -35,8 +35,8 @@ such that int(1..2)]); int(1..2)]), and([var1_RelationAsSetR4R9_ExplicitR4R9_1_ExplicitVarSizeWithFlags_Flags[q2, 2] -> - -toInt(var1_RelationAsSetR4R9_ExplicitR4R9_1_ExplicitVarSizeWithFlags_Values[q2, 1]) < - -toInt(var1_RelationAsSetR4R9_ExplicitR4R9_1_ExplicitVarSizeWithFlags_Values[q2, 2]) + [-toInt(var1_RelationAsSetR4R9_ExplicitR4R9_1_ExplicitVarSizeWithFlags_Values[q2, 1]); int(1)] var1_RelationAsSetR4R9_ExplicitR4R9_1_ExplicitVarSizeWithFlags_Values[q2, q4] = false diff --git a/tests/exhaustive/basic/comprehension_01_2/expected/model.eprime b/tests/exhaustive/basic/comprehension_01_2/expected/model.eprime index 5928bc4873..8607f86a85 100644 --- a/tests/exhaustive/basic/comprehension_01_2/expected/model.eprime +++ b/tests/exhaustive/basic/comprehension_01_2/expected/model.eprime @@ -6,5 +6,6 @@ branching on [x, y] such that x = sum([toInt(or([i_Explicit[q4] = y | q4 : int(1..2)])) - | i_Explicit : matrix indexed by [int(1..2)] of int(7..9), i_Explicit[1] < i_Explicit[2]]) + | i_Explicit : matrix indexed by [int(1..2)] of int(7..9), + [i_Explicit[1]; int(1)] i_ExplicitVarSizeWithDummy[2] = 9, 1 <= sum([toInt(i_ExplicitVarSizeWithDummy[q3] != 9) | q3 : int(1..2)]), sum([toInt(i_ExplicitVarSizeWithDummy[q3] != 9) | q3 : int(1..2)]) <= 2, diff --git a/tests/exhaustive/basic/comprehension_03_2/expected/model.eprime b/tests/exhaustive/basic/comprehension_03_2/expected/model.eprime index 52b5ee4f84..71f6ae576f 100644 --- a/tests/exhaustive/basic/comprehension_03_2/expected/model.eprime +++ b/tests/exhaustive/basic/comprehension_03_2/expected/model.eprime @@ -7,7 +7,8 @@ such that x = sum([toInt(or([i_ExplicitVarSizeWithDummy[q6] = y | q6 : int(1..2), i_ExplicitVarSizeWithDummy[q6] != 10])) | i_ExplicitVarSizeWithDummy : matrix indexed by [int(1..2)] of int(7..10), - i_ExplicitVarSizeWithDummy[1] < i_ExplicitVarSizeWithDummy[2] \/ i_ExplicitVarSizeWithDummy[1] = 10, + [i_ExplicitVarSizeWithDummy[1]; int(1)] i_ExplicitVarSizeWithDummy[2] = 10, 1 <= sum([toInt(i_ExplicitVarSizeWithDummy[q3] != 10) | q3 : int(1..2)]), sum([toInt(i_ExplicitVarSizeWithDummy[q3] != 10) | q3 : int(1..2)]) <= 2]) diff --git a/tests/exhaustive/basic/cut_01_off/expected/model_2.eprime b/tests/exhaustive/basic/cut_01_off/expected/model_2.eprime index 3d1fd14c52..37164ea2c4 100644 --- a/tests/exhaustive/basic/cut_01_off/expected/model_2.eprime +++ b/tests/exhaustive/basic/cut_01_off/expected/model_2.eprime @@ -3,7 +3,8 @@ language ESSENCE' 1.0 find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..3)] of int(1..4) branching on [x_ExplicitVarSizeWithDummy] such that - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 4 + and([[x_ExplicitVarSizeWithDummy[q1]; int(1)] x_ExplicitVarSizeWithDummy[q2 + 1] = 4 | q2 : int(1..2)]) diff --git a/tests/exhaustive/basic/cut_01_off/expected/model_3.eprime b/tests/exhaustive/basic/cut_01_off/expected/model_3.eprime index d729b76811..2450f96648 100644 --- a/tests/exhaustive/basic/cut_01_off/expected/model_3.eprime +++ b/tests/exhaustive/basic/cut_01_off/expected/model_3.eprime @@ -5,7 +5,7 @@ find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3)] of int(1. branching on [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] such that and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] + [x_ExplicitVarSizeWithMarker_Values[q1]; int(1)] x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..3)]) diff --git a/tests/exhaustive/basic/cut_01_off/expected/model_4.eprime b/tests/exhaustive/basic/cut_01_off/expected/model_4.eprime index 1f10b1c798..d0b0cedea3 100644 --- a/tests/exhaustive/basic/cut_01_off/expected/model_4.eprime +++ b/tests/exhaustive/basic/cut_01_off/expected/model_4.eprime @@ -5,7 +5,7 @@ find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3)] of int(1.. branching on [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] such that and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] + [x_ExplicitVarSizeWithFlags_Values[q1]; int(1)] x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..3)]), and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..2)]) diff --git a/tests/exhaustive/basic/enum05-unnamed/expected/model_2.eprime b/tests/exhaustive/basic/enum05-unnamed/expected/model_2.eprime index dd1644147e..32c39e4747 100644 --- a/tests/exhaustive/basic/enum05-unnamed/expected/model_2.eprime +++ b/tests/exhaustive/basic/enum05-unnamed/expected/model_2.eprime @@ -3,6 +3,7 @@ language ESSENCE' 1.0 find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..2)] of int(1..3) branching on [x_ExplicitVarSizeWithDummy] such that - x_ExplicitVarSizeWithDummy[1] < x_ExplicitVarSizeWithDummy[2] \/ x_ExplicitVarSizeWithDummy[1] = 3, + [x_ExplicitVarSizeWithDummy[1]; int(1)] x_ExplicitVarSizeWithDummy[2] = 3 diff --git a/tests/exhaustive/basic/enum05-unnamed/expected/model_3.eprime b/tests/exhaustive/basic/enum05-unnamed/expected/model_3.eprime index 9baf5521b0..4846bb6513 100644 --- a/tests/exhaustive/basic/enum05-unnamed/expected/model_3.eprime +++ b/tests/exhaustive/basic/enum05-unnamed/expected/model_3.eprime @@ -5,6 +5,6 @@ find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..2)] of int(1. branching on [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] such that 2 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[1] < x_ExplicitVarSizeWithMarker_Values[2], + [x_ExplicitVarSizeWithMarker_Values[1]; int(1)] x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..2)]) diff --git a/tests/exhaustive/basic/enum05-unnamed/expected/model_4.eprime b/tests/exhaustive/basic/enum05-unnamed/expected/model_4.eprime index 8c652122fc..b922e0b97b 100644 --- a/tests/exhaustive/basic/enum05-unnamed/expected/model_4.eprime +++ b/tests/exhaustive/basic/enum05-unnamed/expected/model_4.eprime @@ -4,7 +4,8 @@ find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..2)] of bool find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..2)] of int(1..2) branching on [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] such that - x_ExplicitVarSizeWithFlags_Flags[2] -> x_ExplicitVarSizeWithFlags_Values[1] < x_ExplicitVarSizeWithFlags_Values[2], + x_ExplicitVarSizeWithFlags_Flags[2] -> + [x_ExplicitVarSizeWithFlags_Values[1]; int(1)] x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..2)]), x_ExplicitVarSizeWithFlags_Flags[2] -> x_ExplicitVarSizeWithFlags_Flags[1] diff --git a/tests/exhaustive/basic/enum05/expected/model_1_2.eprime b/tests/exhaustive/basic/enum05/expected/model_1_2.eprime index 3c466a4bfb..5e1ac67e4f 100644 --- a/tests/exhaustive/basic/enum05/expected/model_1_2.eprime +++ b/tests/exhaustive/basic/enum05/expected/model_1_2.eprime @@ -5,7 +5,8 @@ find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..2)] of int(1..3) branching on [x_ExplicitVarSizeWithDummy, x_Occurrence] such that x_Occurrence[1], - x_ExplicitVarSizeWithDummy[1] < x_ExplicitVarSizeWithDummy[2] \/ x_ExplicitVarSizeWithDummy[1] = 3, + [x_ExplicitVarSizeWithDummy[1]; int(1)] x_ExplicitVarSizeWithDummy[2] = 3, and([x_ExplicitVarSizeWithDummy[q7] != 3 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q7]] | q7 : int(1..2)]), and([x_Occurrence[q8] -> diff --git a/tests/exhaustive/basic/enum05/expected/model_1_3.eprime b/tests/exhaustive/basic/enum05/expected/model_1_3.eprime index caa450f69d..1c517b2f64 100644 --- a/tests/exhaustive/basic/enum05/expected/model_1_3.eprime +++ b/tests/exhaustive/basic/enum05/expected/model_1_3.eprime @@ -7,7 +7,7 @@ branching on [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Va such that x_Occurrence[1], 2 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[1] < x_ExplicitVarSizeWithMarker_Values[2], + [x_ExplicitVarSizeWithMarker_Values[1]; int(1)] x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q3] = 1 | q3 : int(1..2)]), and([q6 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q6]] | q6 : int(1..2)]), diff --git a/tests/exhaustive/basic/enum05/expected/model_1_4.eprime b/tests/exhaustive/basic/enum05/expected/model_1_4.eprime index 65b54149be..b0a108ce36 100644 --- a/tests/exhaustive/basic/enum05/expected/model_1_4.eprime +++ b/tests/exhaustive/basic/enum05/expected/model_1_4.eprime @@ -6,7 +6,8 @@ find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..2)] of int(1.. branching on [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_Occurrence] such that x_Occurrence[1], - x_ExplicitVarSizeWithFlags_Flags[2] -> x_ExplicitVarSizeWithFlags_Values[1] < x_ExplicitVarSizeWithFlags_Values[2], + x_ExplicitVarSizeWithFlags_Flags[2] -> + [x_ExplicitVarSizeWithFlags_Values[1]; int(1)] x_ExplicitVarSizeWithFlags_Values[q3] = 1 | q3 : int(1..2)]), x_ExplicitVarSizeWithFlags_Flags[2] -> x_ExplicitVarSizeWithFlags_Flags[1], and([x_ExplicitVarSizeWithFlags_Flags[q8] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q8]] | q8 : int(1..2)]), diff --git a/tests/exhaustive/basic/enum05/expected/model_2_1.eprime b/tests/exhaustive/basic/enum05/expected/model_2_1.eprime index 06dba1716a..19b55ab58a 100644 --- a/tests/exhaustive/basic/enum05/expected/model_2_1.eprime +++ b/tests/exhaustive/basic/enum05/expected/model_2_1.eprime @@ -5,7 +5,8 @@ find x_Occurrence: matrix indexed by [int(1..2)] of bool branching on [x_Occurrence, x_ExplicitVarSizeWithDummy] such that or([x_ExplicitVarSizeWithDummy[q7] != 3 /\ x_ExplicitVarSizeWithDummy[q7] = 1 | q7 : int(1..2)]), - x_ExplicitVarSizeWithDummy[1] < x_ExplicitVarSizeWithDummy[2] \/ x_ExplicitVarSizeWithDummy[1] = 3, + [x_ExplicitVarSizeWithDummy[1]; int(1)] x_ExplicitVarSizeWithDummy[2] = 3, and([x_Occurrence[q8] -> or([x_ExplicitVarSizeWithDummy[q10] != 3 /\ x_ExplicitVarSizeWithDummy[q10] = q8 | q10 : int(1..2)]) diff --git a/tests/exhaustive/basic/enum05/expected/model_2_2.eprime b/tests/exhaustive/basic/enum05/expected/model_2_2.eprime index 3cbe9f04b3..3cd005c946 100644 --- a/tests/exhaustive/basic/enum05/expected/model_2_2.eprime +++ b/tests/exhaustive/basic/enum05/expected/model_2_2.eprime @@ -4,6 +4,7 @@ find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..2)] of int(1..3) branching on [x_ExplicitVarSizeWithDummy] such that or([x_ExplicitVarSizeWithDummy[q6] != 3 /\ x_ExplicitVarSizeWithDummy[q6] = 1 | q6 : int(1..2)]), - x_ExplicitVarSizeWithDummy[1] < x_ExplicitVarSizeWithDummy[2] \/ x_ExplicitVarSizeWithDummy[1] = 3, + [x_ExplicitVarSizeWithDummy[1]; int(1)] x_ExplicitVarSizeWithDummy[2] = 3 diff --git a/tests/exhaustive/basic/enum05/expected/model_2_3.eprime b/tests/exhaustive/basic/enum05/expected/model_2_3.eprime index 15b24ddce9..affa05405a 100644 --- a/tests/exhaustive/basic/enum05/expected/model_2_3.eprime +++ b/tests/exhaustive/basic/enum05/expected/model_2_3.eprime @@ -6,10 +6,11 @@ find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..2)] of int(1. branching on [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy] such that or([x_ExplicitVarSizeWithDummy[q17] != 3 /\ x_ExplicitVarSizeWithDummy[q17] = 1 | q17 : int(1..2)]), - x_ExplicitVarSizeWithDummy[1] < x_ExplicitVarSizeWithDummy[2] \/ x_ExplicitVarSizeWithDummy[1] = 3, + [x_ExplicitVarSizeWithDummy[1]; int(1)] x_ExplicitVarSizeWithDummy[2] = 3, 2 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[1] < x_ExplicitVarSizeWithMarker_Values[2], + [x_ExplicitVarSizeWithMarker_Values[1]; int(1)] x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q6] = 1 | q6 : int(1..2)]), and([q9 <= x_ExplicitVarSizeWithMarker_Marker -> or([x_ExplicitVarSizeWithDummy[q11] != 3 /\ diff --git a/tests/exhaustive/basic/enum05/expected/model_2_4.eprime b/tests/exhaustive/basic/enum05/expected/model_2_4.eprime index e6286e36dc..20ee576a7b 100644 --- a/tests/exhaustive/basic/enum05/expected/model_2_4.eprime +++ b/tests/exhaustive/basic/enum05/expected/model_2_4.eprime @@ -6,9 +6,11 @@ find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..2)] of int(1.. branching on [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy] such that or([x_ExplicitVarSizeWithDummy[q19] != 3 /\ x_ExplicitVarSizeWithDummy[q19] = 1 | q19 : int(1..2)]), - x_ExplicitVarSizeWithDummy[1] < x_ExplicitVarSizeWithDummy[2] \/ x_ExplicitVarSizeWithDummy[1] = 3, + [x_ExplicitVarSizeWithDummy[1]; int(1)] x_ExplicitVarSizeWithDummy[2] = 3, - x_ExplicitVarSizeWithFlags_Flags[2] -> x_ExplicitVarSizeWithFlags_Values[1] < x_ExplicitVarSizeWithFlags_Values[2], + x_ExplicitVarSizeWithFlags_Flags[2] -> + [x_ExplicitVarSizeWithFlags_Values[1]; int(1)] x_ExplicitVarSizeWithFlags_Values[q6] = 1 | q6 : int(1..2)]), x_ExplicitVarSizeWithFlags_Flags[2] -> x_ExplicitVarSizeWithFlags_Flags[1], and([x_ExplicitVarSizeWithFlags_Flags[q11] -> diff --git a/tests/exhaustive/basic/enum05/expected/model_3_1.eprime b/tests/exhaustive/basic/enum05/expected/model_3_1.eprime index 53b78284b9..305e95e154 100644 --- a/tests/exhaustive/basic/enum05/expected/model_3_1.eprime +++ b/tests/exhaustive/basic/enum05/expected/model_3_1.eprime @@ -7,7 +7,7 @@ branching on [x_Occurrence, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSiz such that or([q6 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q6] = 1 | q6 : int(1..2)]), 2 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[1] < x_ExplicitVarSizeWithMarker_Values[2], + [x_ExplicitVarSizeWithMarker_Values[1]; int(1)] x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..2)]), and([x_Occurrence[q7] -> or([q9 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q9] = q7 | q9 : int(1..2)]) diff --git a/tests/exhaustive/basic/enum05/expected/model_3_2.eprime b/tests/exhaustive/basic/enum05/expected/model_3_2.eprime index 9955c46684..289392ed4b 100644 --- a/tests/exhaustive/basic/enum05/expected/model_3_2.eprime +++ b/tests/exhaustive/basic/enum05/expected/model_3_2.eprime @@ -7,9 +7,10 @@ branching on [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithMarker_Marker, x_ such that or([q17 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q17] = 1 | q17 : int(1..2)]), 2 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[1] < x_ExplicitVarSizeWithMarker_Values[2], + [x_ExplicitVarSizeWithMarker_Values[1]; int(1)] x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..2)]), - x_ExplicitVarSizeWithDummy[1] < x_ExplicitVarSizeWithDummy[2] \/ x_ExplicitVarSizeWithDummy[1] = 3, + [x_ExplicitVarSizeWithDummy[1]; int(1)] x_ExplicitVarSizeWithDummy[2] = 3, and([x_ExplicitVarSizeWithDummy[q9] != 3 -> or([q11 <= x_ExplicitVarSizeWithMarker_Marker /\ diff --git a/tests/exhaustive/basic/enum05/expected/model_3_3.eprime b/tests/exhaustive/basic/enum05/expected/model_3_3.eprime index 6bf0fbc245..cafd3e03b9 100644 --- a/tests/exhaustive/basic/enum05/expected/model_3_3.eprime +++ b/tests/exhaustive/basic/enum05/expected/model_3_3.eprime @@ -6,6 +6,6 @@ branching on [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Va such that or([q5 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q5] = 1 | q5 : int(1..2)]), 2 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[1] < x_ExplicitVarSizeWithMarker_Values[2], + [x_ExplicitVarSizeWithMarker_Values[1]; int(1)] x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..2)]) diff --git a/tests/exhaustive/basic/enum05/expected/model_3_4.eprime b/tests/exhaustive/basic/enum05/expected/model_3_4.eprime index 30b752c34b..e0e163e423 100644 --- a/tests/exhaustive/basic/enum05/expected/model_3_4.eprime +++ b/tests/exhaustive/basic/enum05/expected/model_3_4.eprime @@ -10,9 +10,10 @@ branching on such that or([q18 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q18] = 1 | q18 : int(1..2)]), 2 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[1] < x_ExplicitVarSizeWithMarker_Values[2], + [x_ExplicitVarSizeWithMarker_Values[1]; int(1)] x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..2)]), - x_ExplicitVarSizeWithFlags_Flags[2] -> x_ExplicitVarSizeWithFlags_Values[1] < x_ExplicitVarSizeWithFlags_Values[2], + x_ExplicitVarSizeWithFlags_Flags[2] -> + [x_ExplicitVarSizeWithFlags_Values[1]; int(1)] x_ExplicitVarSizeWithFlags_Values[q5] = 1 | q5 : int(1..2)]), x_ExplicitVarSizeWithFlags_Flags[2] -> x_ExplicitVarSizeWithFlags_Flags[1], and([x_ExplicitVarSizeWithFlags_Flags[q10] -> diff --git a/tests/exhaustive/basic/enum05/expected/model_4_1.eprime b/tests/exhaustive/basic/enum05/expected/model_4_1.eprime index d357287c6d..8d42b90c9e 100644 --- a/tests/exhaustive/basic/enum05/expected/model_4_1.eprime +++ b/tests/exhaustive/basic/enum05/expected/model_4_1.eprime @@ -6,7 +6,8 @@ find x_Occurrence: matrix indexed by [int(1..2)] of bool branching on [x_Occurrence, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] such that or([x_ExplicitVarSizeWithFlags_Flags[q13] /\ x_ExplicitVarSizeWithFlags_Values[q13] = 1 | q13 : int(1..2)]), - x_ExplicitVarSizeWithFlags_Flags[2] -> x_ExplicitVarSizeWithFlags_Values[1] < x_ExplicitVarSizeWithFlags_Values[2], + x_ExplicitVarSizeWithFlags_Flags[2] -> + [x_ExplicitVarSizeWithFlags_Values[1]; int(1)] x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..2)]), x_ExplicitVarSizeWithFlags_Flags[2] -> x_ExplicitVarSizeWithFlags_Flags[1], and([x_Occurrence[q7] -> diff --git a/tests/exhaustive/basic/enum05/expected/model_4_2.eprime b/tests/exhaustive/basic/enum05/expected/model_4_2.eprime index 7845f87b0a..fa7a9b3cfb 100644 --- a/tests/exhaustive/basic/enum05/expected/model_4_2.eprime +++ b/tests/exhaustive/basic/enum05/expected/model_4_2.eprime @@ -6,10 +6,12 @@ find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..2)] of int(1..3) branching on [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] such that or([x_ExplicitVarSizeWithFlags_Flags[q19] /\ x_ExplicitVarSizeWithFlags_Values[q19] = 1 | q19 : int(1..2)]), - x_ExplicitVarSizeWithFlags_Flags[2] -> x_ExplicitVarSizeWithFlags_Values[1] < x_ExplicitVarSizeWithFlags_Values[2], + x_ExplicitVarSizeWithFlags_Flags[2] -> + [x_ExplicitVarSizeWithFlags_Values[1]; int(1)] x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..2)]), x_ExplicitVarSizeWithFlags_Flags[2] -> x_ExplicitVarSizeWithFlags_Flags[1], - x_ExplicitVarSizeWithDummy[1] < x_ExplicitVarSizeWithDummy[2] \/ x_ExplicitVarSizeWithDummy[1] = 3, + [x_ExplicitVarSizeWithDummy[1]; int(1)] x_ExplicitVarSizeWithDummy[2] = 3, and([x_ExplicitVarSizeWithDummy[q11] != 3 -> or([x_ExplicitVarSizeWithFlags_Flags[q13] /\ diff --git a/tests/exhaustive/basic/enum05/expected/model_4_3.eprime b/tests/exhaustive/basic/enum05/expected/model_4_3.eprime index 681490ebe2..9339754f19 100644 --- a/tests/exhaustive/basic/enum05/expected/model_4_3.eprime +++ b/tests/exhaustive/basic/enum05/expected/model_4_3.eprime @@ -9,11 +9,12 @@ branching on x_ExplicitVarSizeWithFlags_Values] such that or([x_ExplicitVarSizeWithFlags_Flags[q18] /\ x_ExplicitVarSizeWithFlags_Values[q18] = 1 | q18 : int(1..2)]), - x_ExplicitVarSizeWithFlags_Flags[2] -> x_ExplicitVarSizeWithFlags_Values[1] < x_ExplicitVarSizeWithFlags_Values[2], + x_ExplicitVarSizeWithFlags_Flags[2] -> + [x_ExplicitVarSizeWithFlags_Values[1]; int(1)] x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..2)]), x_ExplicitVarSizeWithFlags_Flags[2] -> x_ExplicitVarSizeWithFlags_Flags[1], 2 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[1] < x_ExplicitVarSizeWithMarker_Values[2], + [x_ExplicitVarSizeWithMarker_Values[1]; int(1)] x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q7] = 1 | q7 : int(1..2)]), and([q10 <= x_ExplicitVarSizeWithMarker_Marker -> or([x_ExplicitVarSizeWithFlags_Flags[q12] /\ diff --git a/tests/exhaustive/basic/enum05/expected/model_4_4.eprime b/tests/exhaustive/basic/enum05/expected/model_4_4.eprime index 5045c01422..4488d3c825 100644 --- a/tests/exhaustive/basic/enum05/expected/model_4_4.eprime +++ b/tests/exhaustive/basic/enum05/expected/model_4_4.eprime @@ -5,7 +5,8 @@ find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..2)] of int(1.. branching on [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] such that or([x_ExplicitVarSizeWithFlags_Flags[q7] /\ x_ExplicitVarSizeWithFlags_Values[q7] = 1 | q7 : int(1..2)]), - x_ExplicitVarSizeWithFlags_Flags[2] -> x_ExplicitVarSizeWithFlags_Values[1] < x_ExplicitVarSizeWithFlags_Values[2], + x_ExplicitVarSizeWithFlags_Flags[2] -> + [x_ExplicitVarSizeWithFlags_Values[1]; int(1)] x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..2)]), x_ExplicitVarSizeWithFlags_Flags[2] -> x_ExplicitVarSizeWithFlags_Flags[1] diff --git a/tests/exhaustive/basic/enum06/expected/model_1_1.eprime b/tests/exhaustive/basic/enum06/expected/model_1_1.eprime index 261c385226..96c933def5 100644 --- a/tests/exhaustive/basic/enum06/expected/model_1_1.eprime +++ b/tests/exhaustive/basic/enum06/expected/model_1_1.eprime @@ -5,7 +5,8 @@ find x_ExplicitWithFlags_Values: matrix indexed by [int(1..4)] of int(1..2) branching on [x_ExplicitWithFlags_Flags, x_ExplicitWithFlags_Values] such that or([x_ExplicitWithFlags_Flags[q8] > 0 /\ x_ExplicitWithFlags_Values[q8] = 1 | q8 : int(1..4)]), - and([x_ExplicitWithFlags_Flags[q1 + 1] > 0 -> x_ExplicitWithFlags_Values[q1] < x_ExplicitWithFlags_Values[q1 + 1] + and([x_ExplicitWithFlags_Flags[q1 + 1] > 0 -> + [x_ExplicitWithFlags_Values[q1]; int(1)] x_ExplicitWithFlags_Values[q2] = 1 | q2 : int(1..4)]), and([x_ExplicitWithFlags_Flags[q3 + 1] > 0 -> x_ExplicitWithFlags_Flags[q3] > 0 | q3 : int(1..3)]), diff --git a/tests/exhaustive/basic/enum06/expected/model_1_2.eprime b/tests/exhaustive/basic/enum06/expected/model_1_2.eprime index d49d817883..9e376f91a6 100644 --- a/tests/exhaustive/basic/enum06/expected/model_1_2.eprime +++ b/tests/exhaustive/basic/enum06/expected/model_1_2.eprime @@ -9,13 +9,14 @@ branching on x_ExplicitWithFlags_Values] such that or([x_ExplicitWithFlags_Flags[q22] > 0 /\ x_ExplicitWithFlags_Values[q22] = 1 | q22 : int(1..4)]), - and([x_ExplicitWithFlags_Flags[q1 + 1] > 0 -> x_ExplicitWithFlags_Values[q1] < x_ExplicitWithFlags_Values[q1 + 1] + and([x_ExplicitWithFlags_Flags[q1 + 1] > 0 -> + [x_ExplicitWithFlags_Values[q1]; int(1)] x_ExplicitWithFlags_Values[q2] = 1 | q2 : int(1..4)]), and([x_ExplicitWithFlags_Flags[q3 + 1] > 0 -> x_ExplicitWithFlags_Flags[q3] > 0 | q3 : int(1..3)]), sum([x_ExplicitWithFlags_Flags[q5] | q5 : int(1..4)]) <= 4, and([q7 + 1 <= x_ExplicitWithRepetition_Flag -> - x_ExplicitWithRepetition_Values[q7] <= x_ExplicitWithRepetition_Values[q7 + 1] + [x_ExplicitWithRepetition_Values[q7]; int(1)] <=lex [x_ExplicitWithRepetition_Values[q7 + 1]; int(1)] | q7 : int(1..3)]), and([q8 > x_ExplicitWithRepetition_Flag -> x_ExplicitWithRepetition_Values[q8] = 1 | q8 : int(1..4)]), x_ExplicitWithRepetition_Flag <= 4, diff --git a/tests/exhaustive/basic/enum06/expected/model_1_3.eprime b/tests/exhaustive/basic/enum06/expected/model_1_3.eprime index 1e2675abc2..aa6985e35d 100644 --- a/tests/exhaustive/basic/enum06/expected/model_1_3.eprime +++ b/tests/exhaustive/basic/enum06/expected/model_1_3.eprime @@ -6,7 +6,8 @@ find x_MOccurrence: matrix indexed by [int(1..2)] of int(0..4) branching on [x_MOccurrence, x_ExplicitWithFlags_Flags, x_ExplicitWithFlags_Values] such that or([x_ExplicitWithFlags_Flags[q14] > 0 /\ x_ExplicitWithFlags_Values[q14] = 1 | q14 : int(1..4)]), - and([x_ExplicitWithFlags_Flags[q1 + 1] > 0 -> x_ExplicitWithFlags_Values[q1] < x_ExplicitWithFlags_Values[q1 + 1] + and([x_ExplicitWithFlags_Flags[q1 + 1] > 0 -> + [x_ExplicitWithFlags_Values[q1]; int(1)] x_ExplicitWithFlags_Values[q2] = 1 | q2 : int(1..4)]), and([x_ExplicitWithFlags_Flags[q3 + 1] > 0 -> x_ExplicitWithFlags_Flags[q3] > 0 | q3 : int(1..3)]), diff --git a/tests/exhaustive/basic/enum06/expected/model_2_1.eprime b/tests/exhaustive/basic/enum06/expected/model_2_1.eprime index 22430fd8eb..12d1f22400 100644 --- a/tests/exhaustive/basic/enum06/expected/model_2_1.eprime +++ b/tests/exhaustive/basic/enum06/expected/model_2_1.eprime @@ -10,11 +10,12 @@ branching on such that or([q22 <= x_ExplicitWithRepetition_Flag /\ x_ExplicitWithRepetition_Values[q22] = 1 | q22 : int(1..4)]), and([q1 + 1 <= x_ExplicitWithRepetition_Flag -> - x_ExplicitWithRepetition_Values[q1] <= x_ExplicitWithRepetition_Values[q1 + 1] + [x_ExplicitWithRepetition_Values[q1]; int(1)] <=lex [x_ExplicitWithRepetition_Values[q1 + 1]; int(1)] | q1 : int(1..3)]), and([q2 > x_ExplicitWithRepetition_Flag -> x_ExplicitWithRepetition_Values[q2] = 1 | q2 : int(1..4)]), x_ExplicitWithRepetition_Flag <= 4, - and([x_ExplicitWithFlags_Flags[q6 + 1] > 0 -> x_ExplicitWithFlags_Values[q6] < x_ExplicitWithFlags_Values[q6 + 1] + and([x_ExplicitWithFlags_Flags[q6 + 1] > 0 -> + [x_ExplicitWithFlags_Values[q6]; int(1)] x_ExplicitWithFlags_Values[q7] = 1 | q7 : int(1..4)]), and([x_ExplicitWithFlags_Flags[q8 + 1] > 0 -> x_ExplicitWithFlags_Flags[q8] > 0 | q8 : int(1..3)]), diff --git a/tests/exhaustive/basic/enum06/expected/model_2_2.eprime b/tests/exhaustive/basic/enum06/expected/model_2_2.eprime index 83a4f59f8c..ae8798327d 100644 --- a/tests/exhaustive/basic/enum06/expected/model_2_2.eprime +++ b/tests/exhaustive/basic/enum06/expected/model_2_2.eprime @@ -6,7 +6,7 @@ branching on [x_ExplicitWithRepetition_Flag, x_ExplicitWithRepetition_Values] such that or([q7 <= x_ExplicitWithRepetition_Flag /\ x_ExplicitWithRepetition_Values[q7] = 1 | q7 : int(1..4)]), and([q1 + 1 <= x_ExplicitWithRepetition_Flag -> - x_ExplicitWithRepetition_Values[q1] <= x_ExplicitWithRepetition_Values[q1 + 1] + [x_ExplicitWithRepetition_Values[q1]; int(1)] <=lex [x_ExplicitWithRepetition_Values[q1 + 1]; int(1)] | q1 : int(1..3)]), and([q2 > x_ExplicitWithRepetition_Flag -> x_ExplicitWithRepetition_Values[q2] = 1 | q2 : int(1..4)]), x_ExplicitWithRepetition_Flag <= 4 diff --git a/tests/exhaustive/basic/enum06/expected/model_2_3.eprime b/tests/exhaustive/basic/enum06/expected/model_2_3.eprime index 14637dd1da..c53f6a7689 100644 --- a/tests/exhaustive/basic/enum06/expected/model_2_3.eprime +++ b/tests/exhaustive/basic/enum06/expected/model_2_3.eprime @@ -7,7 +7,7 @@ branching on [x_MOccurrence, x_ExplicitWithRepetition_Flag, x_ExplicitWithRepeti such that or([q15 <= x_ExplicitWithRepetition_Flag /\ x_ExplicitWithRepetition_Values[q15] = 1 | q15 : int(1..4)]), and([q1 + 1 <= x_ExplicitWithRepetition_Flag -> - x_ExplicitWithRepetition_Values[q1] <= x_ExplicitWithRepetition_Values[q1 + 1] + [x_ExplicitWithRepetition_Values[q1]; int(1)] <=lex [x_ExplicitWithRepetition_Values[q1 + 1]; int(1)] | q1 : int(1..3)]), and([q2 > x_ExplicitWithRepetition_Flag -> x_ExplicitWithRepetition_Values[q2] = 1 | q2 : int(1..4)]), x_ExplicitWithRepetition_Flag <= 4, diff --git a/tests/exhaustive/basic/enum06/expected/model_3_1.eprime b/tests/exhaustive/basic/enum06/expected/model_3_1.eprime index d4e1fb79c3..997c73f250 100644 --- a/tests/exhaustive/basic/enum06/expected/model_3_1.eprime +++ b/tests/exhaustive/basic/enum06/expected/model_3_1.eprime @@ -7,7 +7,8 @@ branching on [x_ExplicitWithFlags_Flags, x_ExplicitWithFlags_Values, x_MOccurren such that or([x_MOccurrence[q14] > 0 /\ q14 = 1 | q14 : int(1..2)]), sum([x_MOccurrence[q1] | q1 : int(1..2)]) <= 4, - and([x_ExplicitWithFlags_Flags[q2 + 1] > 0 -> x_ExplicitWithFlags_Values[q2] < x_ExplicitWithFlags_Values[q2 + 1] + and([x_ExplicitWithFlags_Flags[q2 + 1] > 0 -> + [x_ExplicitWithFlags_Values[q2]; int(1)] x_ExplicitWithFlags_Values[q3] = 1 | q3 : int(1..4)]), and([x_ExplicitWithFlags_Flags[q4 + 1] > 0 -> x_ExplicitWithFlags_Flags[q4] > 0 | q4 : int(1..3)]), diff --git a/tests/exhaustive/basic/enum06/expected/model_3_2.eprime b/tests/exhaustive/basic/enum06/expected/model_3_2.eprime index 4309aabff6..ec9ac25a79 100644 --- a/tests/exhaustive/basic/enum06/expected/model_3_2.eprime +++ b/tests/exhaustive/basic/enum06/expected/model_3_2.eprime @@ -8,7 +8,7 @@ such that or([x_MOccurrence[q15] > 0 /\ q15 = 1 | q15 : int(1..2)]), sum([x_MOccurrence[q1] | q1 : int(1..2)]) <= 4, and([q2 + 1 <= x_ExplicitWithRepetition_Flag -> - x_ExplicitWithRepetition_Values[q2] <= x_ExplicitWithRepetition_Values[q2 + 1] + [x_ExplicitWithRepetition_Values[q2]; int(1)] <=lex [x_ExplicitWithRepetition_Values[q2 + 1]; int(1)] | q2 : int(1..3)]), and([q3 > x_ExplicitWithRepetition_Flag -> x_ExplicitWithRepetition_Values[q3] = 1 | q3 : int(1..4)]), x_ExplicitWithRepetition_Flag <= 4, diff --git a/tests/exhaustive/basic/function_card_02/expected/model.eprime b/tests/exhaustive/basic/function_card_02/expected/model.eprime index 2ce3241b3c..c9723e37b7 100644 --- a/tests/exhaustive/basic/function_card_02/expected/model.eprime +++ b/tests/exhaustive/basic/function_card_02/expected/model.eprime @@ -9,6 +9,6 @@ such that x_Function1DPartial_Flags[sum([toInt(x_Function1DPartial_Flags[q9]) | q9 : int(1..3)])], and([x_Function1DPartial_Flags[q1] /\ x_Function1DPartial_Flags[q2] -> x_Function1DPartial_Values[q1] != x_Function1DPartial_Values[q2] - | q1 : int(1..3), q2 : int(1..3), q1 < q2]), + | q1 : int(1..3), q2 : int(1..3), [q1; int(1)] x_Function1DPartial_Values[q3] = 1 | q3 : int(1..3)]) diff --git a/tests/exhaustive/basic/function_partial_int_03/expected/model.eprime b/tests/exhaustive/basic/function_partial_int_03/expected/model.eprime index a49ff07d06..155203f66d 100644 --- a/tests/exhaustive/basic/function_partial_int_03/expected/model.eprime +++ b/tests/exhaustive/basic/function_partial_int_03/expected/model.eprime @@ -6,6 +6,6 @@ branching on [x_Function1DPartial_Flags, x_Function1DPartial_Values] such that and([x_Function1DPartial_Flags[q1] /\ x_Function1DPartial_Flags[q2] -> x_Function1DPartial_Values[q1] != x_Function1DPartial_Values[q2] - | q1 : int(1..3), q2 : int(1..3), q1 < q2]), + | q1 : int(1..3), q2 : int(1..3), [q1; int(1)] x_Function1DPartial_Values[q3] = 13 | q3 : int(1..3)]) diff --git a/tests/exhaustive/basic/function_partial_int_04/expected/model.eprime b/tests/exhaustive/basic/function_partial_int_04/expected/model.eprime index 81d5dd9bd1..4731e78ca6 100644 --- a/tests/exhaustive/basic/function_partial_int_04/expected/model.eprime +++ b/tests/exhaustive/basic/function_partial_int_04/expected/model.eprime @@ -6,6 +6,6 @@ branching on [x_Function1DPartial_Flags, x_Function1DPartial_Values] such that and([x_Function1DPartial_Flags[q1] /\ x_Function1DPartial_Flags[q2] -> x_Function1DPartial_Values[q1] != x_Function1DPartial_Values[q2] - | q1 : int(1..3), q2 : int(1..3), q1 < q2]), + | q1 : int(1..3), q2 : int(1..3), [q1; int(1)] x_Function1DPartial_Values[q3] = 13 | q3 : int(1..3)]) diff --git a/tests/exhaustive/basic/function_partial_int_05/expected/model.eprime b/tests/exhaustive/basic/function_partial_int_05/expected/model.eprime index 29e442b4af..2fe5942b34 100644 --- a/tests/exhaustive/basic/function_partial_int_05/expected/model.eprime +++ b/tests/exhaustive/basic/function_partial_int_05/expected/model.eprime @@ -6,7 +6,7 @@ branching on [x_Function1DPartial_Flags, x_Function1DPartial_Values] such that and([x_Function1DPartial_Flags[q1] /\ x_Function1DPartial_Flags[q2] -> x_Function1DPartial_Values[q1] != x_Function1DPartial_Values[q2] - | q1 : int(1..3), q2 : int(1..3), q1 < q2]), + | q1 : int(1..3), q2 : int(1..3), [q1; int(1)] x_Function1DPartial_Values[q5] = 13 | q5 : int(1..3)]) diff --git a/tests/exhaustive/basic/function_partial_int_06/expected/model.eprime b/tests/exhaustive/basic/function_partial_int_06/expected/model.eprime index b9caf89dae..036bb12744 100644 --- a/tests/exhaustive/basic/function_partial_int_06/expected/model.eprime +++ b/tests/exhaustive/basic/function_partial_int_06/expected/model.eprime @@ -6,7 +6,7 @@ branching on [x_Function1DPartial_Flags, x_Function1DPartial_Values] such that and([x_Function1DPartial_Flags[q1] /\ x_Function1DPartial_Flags[q2] -> x_Function1DPartial_Values[q1] != x_Function1DPartial_Values[q2] - | q1 : int(1..3), q2 : int(1..3), q1 < q2]), + | q1 : int(1..3), q2 : int(1..3), [q1; int(1)] x_Function1DPartial_Values[q5] = 13 | q5 : int(1..3)]) diff --git a/tests/exhaustive/basic/function_partial_int_param/expected/model.eprime b/tests/exhaustive/basic/function_partial_int_param/expected/model.eprime index 691faf6f88..51f6b3884a 100644 --- a/tests/exhaustive/basic/function_partial_int_param/expected/model.eprime +++ b/tests/exhaustive/basic/function_partial_int_param/expected/model.eprime @@ -18,6 +18,6 @@ such that | q8 : int(1..3)]), and([x_Function1DPartial_Flags[q1] /\ x_Function1DPartial_Flags[q2] -> x_Function1DPartial_Values[q1] != x_Function1DPartial_Values[q2] - | q1 : int(1..3), q2 : int(1..3), q1 < q2]), + | q1 : int(1..3), q2 : int(1..3), [q1; int(1)] x_Function1DPartial_Values[q3] = 13 | q3 : int(1..3)]) diff --git a/tests/exhaustive/basic/function_total_int_set_01/expected/model_1.eprime b/tests/exhaustive/basic/function_total_int_set_01/expected/model_1.eprime index ee147a457c..9495e416f1 100644 --- a/tests/exhaustive/basic/function_total_int_set_01/expected/model_1.eprime +++ b/tests/exhaustive/basic/function_total_int_set_01/expected/model_1.eprime @@ -3,7 +3,7 @@ language ESSENCE' 1.0 find f_Function1DR2_Occurrence: matrix indexed by [int(1..3), int(1..3)] of bool branching on [f_Function1DR2_Occurrence] such that - and([q1 < q2 -> + and([[q1; int(1)] or([f_Function1DR2_Occurrence[q1, q5] != f_Function1DR2_Occurrence[q2, q5] | q5 : int(1..3)]) \/ or([f_Function1DR2_Occurrence[q1, q5] != f_Function1DR2_Occurrence[q2, q5] | q5 : int(1..3)]) | q1 : int(1..3), q2 : int(1..3)]), diff --git a/tests/exhaustive/basic/function_total_int_set_01/expected/model_2.eprime b/tests/exhaustive/basic/function_total_int_set_01/expected/model_2.eprime index 4de8f61bbe..baad69006d 100644 --- a/tests/exhaustive/basic/function_total_int_set_01/expected/model_2.eprime +++ b/tests/exhaustive/basic/function_total_int_set_01/expected/model_2.eprime @@ -3,9 +3,9 @@ language ESSENCE' 1.0 find f_Function1DR3_Explicit: matrix indexed by [int(1..3), int(1..2)] of int(1..3) branching on [f_Function1DR3_Explicit] such that - and([q1 < q2 -> + and([[q1; int(1)] or([f_Function1DR3_Explicit[q1, q6] != f_Function1DR3_Explicit[q2, q6] | q6 : int(1..2)]) \/ or([f_Function1DR3_Explicit[q1, q6] != f_Function1DR3_Explicit[q2, q6] | q6 : int(1..2)]) | q1 : int(1..3), q2 : int(1..3)]), - and([f_Function1DR3_Explicit[q3, 1] < f_Function1DR3_Explicit[q3, 2] | q3 : int(1..3)]) + and([[f_Function1DR3_Explicit[q3, 1]; int(1)] 0 -> x_ExplicitWithFlags_Values[q1] < x_ExplicitWithFlags_Values[q1 + 1] + and([x_ExplicitWithFlags_Flags[q1 + 1] > 0 -> + [x_ExplicitWithFlags_Values[q1]; int(1)] x_ExplicitWithFlags_Values[q2] = 1 | q2 : int(1..4)]), and([x_ExplicitWithFlags_Flags[q3 + 1] > 0 -> x_ExplicitWithFlags_Flags[q3] > 0 | q3 : int(1..3)]), diff --git a/tests/exhaustive/basic/mset01_find/expected/model_2.eprime b/tests/exhaustive/basic/mset01_find/expected/model_2.eprime index 622b9c2da2..49768a43b8 100644 --- a/tests/exhaustive/basic/mset01_find/expected/model_2.eprime +++ b/tests/exhaustive/basic/mset01_find/expected/model_2.eprime @@ -5,7 +5,7 @@ find x_ExplicitWithRepetition_Values: matrix indexed by [int(1..4)] of int(1..2) branching on [x_ExplicitWithRepetition_Flag, x_ExplicitWithRepetition_Values] such that and([q1 + 1 <= x_ExplicitWithRepetition_Flag -> - x_ExplicitWithRepetition_Values[q1] <= x_ExplicitWithRepetition_Values[q1 + 1] + [x_ExplicitWithRepetition_Values[q1]; int(1)] <=lex [x_ExplicitWithRepetition_Values[q1 + 1]; int(1)] | q1 : int(1..3)]), and([q2 > x_ExplicitWithRepetition_Flag -> x_ExplicitWithRepetition_Values[q2] = 1 | q2 : int(1..4)]), and([q4 <= x_ExplicitWithRepetition_Flag -> diff --git a/tests/exhaustive/basic/mset02/expected/model_1.eprime b/tests/exhaustive/basic/mset02/expected/model_1.eprime index b5e036ab59..9cab090d1c 100644 --- a/tests/exhaustive/basic/mset02/expected/model_1.eprime +++ b/tests/exhaustive/basic/mset02/expected/model_1.eprime @@ -4,7 +4,8 @@ find x_ExplicitWithFlags_Flags: matrix indexed by [int(1..4)] of int(0..4) find x_ExplicitWithFlags_Values: matrix indexed by [int(1..4)] of int(1..2) branching on [x_ExplicitWithFlags_Flags, x_ExplicitWithFlags_Values] such that - and([x_ExplicitWithFlags_Flags[q1 + 1] > 0 -> x_ExplicitWithFlags_Values[q1] < x_ExplicitWithFlags_Values[q1 + 1] + and([x_ExplicitWithFlags_Flags[q1 + 1] > 0 -> + [x_ExplicitWithFlags_Values[q1]; int(1)] x_ExplicitWithFlags_Values[q2] = 1 | q2 : int(1..4)]), and([x_ExplicitWithFlags_Flags[q3 + 1] > 0 -> x_ExplicitWithFlags_Flags[q3] > 0 | q3 : int(1..3)]), diff --git a/tests/exhaustive/basic/mset02/expected/model_2.eprime b/tests/exhaustive/basic/mset02/expected/model_2.eprime index cc0afc5588..239b853358 100644 --- a/tests/exhaustive/basic/mset02/expected/model_2.eprime +++ b/tests/exhaustive/basic/mset02/expected/model_2.eprime @@ -5,7 +5,7 @@ find x_ExplicitWithRepetition_Values: matrix indexed by [int(1..4)] of int(1..2) branching on [x_ExplicitWithRepetition_Flag, x_ExplicitWithRepetition_Values] such that and([q1 + 1 <= x_ExplicitWithRepetition_Flag -> - x_ExplicitWithRepetition_Values[q1] <= x_ExplicitWithRepetition_Values[q1 + 1] + [x_ExplicitWithRepetition_Values[q1]; int(1)] <=lex [x_ExplicitWithRepetition_Values[q1 + 1]; int(1)] | q1 : int(1..3)]), and([q2 > x_ExplicitWithRepetition_Flag -> x_ExplicitWithRepetition_Values[q2] = 1 | q2 : int(1..4)]), x_ExplicitWithRepetition_Flag <= 4 diff --git a/tests/exhaustive/basic/mset03_1/expected/model_1.eprime b/tests/exhaustive/basic/mset03_1/expected/model_1.eprime index c1f542f07a..4c87dce0a5 100644 --- a/tests/exhaustive/basic/mset03_1/expected/model_1.eprime +++ b/tests/exhaustive/basic/mset03_1/expected/model_1.eprime @@ -4,7 +4,8 @@ find x_ExplicitWithFlags_Flags: matrix indexed by [int(1..4)] of int(0..2) find x_ExplicitWithFlags_Values: matrix indexed by [int(1..4)] of int(1..2) branching on [x_ExplicitWithFlags_Flags, x_ExplicitWithFlags_Values] such that - and([x_ExplicitWithFlags_Flags[q1 + 1] > 0 -> x_ExplicitWithFlags_Values[q1] < x_ExplicitWithFlags_Values[q1 + 1] + and([x_ExplicitWithFlags_Flags[q1 + 1] > 0 -> + [x_ExplicitWithFlags_Values[q1]; int(1)] x_ExplicitWithFlags_Values[q2] = 1 | q2 : int(1..4)]), and([x_ExplicitWithFlags_Flags[q3 + 1] > 0 -> x_ExplicitWithFlags_Flags[q3] > 0 | q3 : int(1..3)]) diff --git a/tests/exhaustive/basic/mset03_1/expected/model_2.eprime b/tests/exhaustive/basic/mset03_1/expected/model_2.eprime index 44cf254dca..31ae843509 100644 --- a/tests/exhaustive/basic/mset03_1/expected/model_2.eprime +++ b/tests/exhaustive/basic/mset03_1/expected/model_2.eprime @@ -5,7 +5,7 @@ find x_ExplicitWithRepetition_Values: matrix indexed by [int(1..4)] of int(1..2) branching on [x_ExplicitWithRepetition_Flag, x_ExplicitWithRepetition_Values] such that and([q1 + 1 <= x_ExplicitWithRepetition_Flag -> - x_ExplicitWithRepetition_Values[q1] <= x_ExplicitWithRepetition_Values[q1 + 1] + [x_ExplicitWithRepetition_Values[q1]; int(1)] <=lex [x_ExplicitWithRepetition_Values[q1 + 1]; int(1)] | q1 : int(1..3)]), and([q2 > x_ExplicitWithRepetition_Flag -> x_ExplicitWithRepetition_Values[q2] = 1 | q2 : int(1..4)]), and([q4 <= x_ExplicitWithRepetition_Flag -> diff --git a/tests/exhaustive/basic/mset03_2/expected/model_1.eprime b/tests/exhaustive/basic/mset03_2/expected/model_1.eprime index 53f85ab769..246464053e 100644 --- a/tests/exhaustive/basic/mset03_2/expected/model_1.eprime +++ b/tests/exhaustive/basic/mset03_2/expected/model_1.eprime @@ -4,7 +4,8 @@ find x_ExplicitWithFlags_Flags: matrix indexed by [int(1..6)] of int(0..2) find x_ExplicitWithFlags_Values: matrix indexed by [int(1..6)] of int(1..3) branching on [x_ExplicitWithFlags_Flags, x_ExplicitWithFlags_Values] such that - and([x_ExplicitWithFlags_Flags[q1 + 1] > 0 -> x_ExplicitWithFlags_Values[q1] < x_ExplicitWithFlags_Values[q1 + 1] + and([x_ExplicitWithFlags_Flags[q1 + 1] > 0 -> + [x_ExplicitWithFlags_Values[q1]; int(1)] x_ExplicitWithFlags_Values[q2] = 1 | q2 : int(1..6)]), and([x_ExplicitWithFlags_Flags[q3 + 1] > 0 -> x_ExplicitWithFlags_Flags[q3] > 0 | q3 : int(1..5)]) diff --git a/tests/exhaustive/basic/mset03_2/expected/model_2.eprime b/tests/exhaustive/basic/mset03_2/expected/model_2.eprime index 55d05e3479..bc7fd246d0 100644 --- a/tests/exhaustive/basic/mset03_2/expected/model_2.eprime +++ b/tests/exhaustive/basic/mset03_2/expected/model_2.eprime @@ -5,7 +5,7 @@ find x_ExplicitWithRepetition_Values: matrix indexed by [int(1..6)] of int(1..3) branching on [x_ExplicitWithRepetition_Flag, x_ExplicitWithRepetition_Values] such that and([q1 + 1 <= x_ExplicitWithRepetition_Flag -> - x_ExplicitWithRepetition_Values[q1] <= x_ExplicitWithRepetition_Values[q1 + 1] + [x_ExplicitWithRepetition_Values[q1]; int(1)] <=lex [x_ExplicitWithRepetition_Values[q1 + 1]; int(1)] | q1 : int(1..5)]), and([q2 > x_ExplicitWithRepetition_Flag -> x_ExplicitWithRepetition_Values[q2] = 1 | q2 : int(1..6)]), and([q4 <= x_ExplicitWithRepetition_Flag -> diff --git a/tests/exhaustive/basic/mset04/expected/model_1.eprime b/tests/exhaustive/basic/mset04/expected/model_1.eprime index 48c4b21a23..fe688fcaf4 100644 --- a/tests/exhaustive/basic/mset04/expected/model_1.eprime +++ b/tests/exhaustive/basic/mset04/expected/model_1.eprime @@ -4,7 +4,8 @@ find x_ExplicitWithFlags_Flags: matrix indexed by [int(1..4)] of int(0..2) find x_ExplicitWithFlags_Values: matrix indexed by [int(1..4)] of int(1..2) branching on [x_ExplicitWithFlags_Flags, x_ExplicitWithFlags_Values] such that - and([x_ExplicitWithFlags_Flags[q1 + 1] > 0 -> x_ExplicitWithFlags_Values[q1] < x_ExplicitWithFlags_Values[q1 + 1] + and([x_ExplicitWithFlags_Flags[q1 + 1] > 0 -> + [x_ExplicitWithFlags_Values[q1]; int(1)] x_ExplicitWithFlags_Values[q2] = 1 | q2 : int(1..4)]), and([x_ExplicitWithFlags_Flags[q3 + 1] > 0 -> x_ExplicitWithFlags_Flags[q3] > 0 | q3 : int(1..3)]), diff --git a/tests/exhaustive/basic/mset04/expected/model_2.eprime b/tests/exhaustive/basic/mset04/expected/model_2.eprime index 3c59a6b6a4..bd0c3f362b 100644 --- a/tests/exhaustive/basic/mset04/expected/model_2.eprime +++ b/tests/exhaustive/basic/mset04/expected/model_2.eprime @@ -4,7 +4,8 @@ find x_ExplicitWithRepetition_Flag: int(4) find x_ExplicitWithRepetition_Values: matrix indexed by [int(1..4)] of int(1..2) branching on [x_ExplicitWithRepetition_Flag, x_ExplicitWithRepetition_Values] such that - and([x_ExplicitWithRepetition_Values[q1] <= x_ExplicitWithRepetition_Values[q1 + 1] | q1 : int(1..3), q1 + 1 <= 4]), + and([[x_ExplicitWithRepetition_Values[q1]; int(1)] <=lex [x_ExplicitWithRepetition_Values[q1 + 1]; int(1)] + | q1 : int(1..3), q1 + 1 <= 4]), and([sum([toInt(x_ExplicitWithRepetition_Values[q7] = x_ExplicitWithRepetition_Values[q4]) | q7 : int(1..4), q7 <= 4]) <= 2 diff --git a/tests/exhaustive/basic/mset05/expected/model_1.eprime b/tests/exhaustive/basic/mset05/expected/model_1.eprime index 5f08b65d88..2d1f4d30fd 100644 --- a/tests/exhaustive/basic/mset05/expected/model_1.eprime +++ b/tests/exhaustive/basic/mset05/expected/model_1.eprime @@ -4,7 +4,8 @@ find x_ExplicitWithFlags_Flags: matrix indexed by [int(1..4)] of int(0..2) find x_ExplicitWithFlags_Values: matrix indexed by [int(1..4)] of int(1..2) branching on [x_ExplicitWithFlags_Flags, x_ExplicitWithFlags_Values] such that - and([x_ExplicitWithFlags_Flags[q1 + 1] > 0 -> x_ExplicitWithFlags_Values[q1] < x_ExplicitWithFlags_Values[q1 + 1] + and([x_ExplicitWithFlags_Flags[q1 + 1] > 0 -> + [x_ExplicitWithFlags_Values[q1]; int(1)] x_ExplicitWithFlags_Values[q2] = 1 | q2 : int(1..4)]), and([x_ExplicitWithFlags_Flags[q3 + 1] > 0 -> x_ExplicitWithFlags_Flags[q3] > 0 | q3 : int(1..3)]), diff --git a/tests/exhaustive/basic/mset05/expected/model_2.eprime b/tests/exhaustive/basic/mset05/expected/model_2.eprime index f1a0aec2a6..1ecab17108 100644 --- a/tests/exhaustive/basic/mset05/expected/model_2.eprime +++ b/tests/exhaustive/basic/mset05/expected/model_2.eprime @@ -5,7 +5,7 @@ find x_ExplicitWithRepetition_Values: matrix indexed by [int(1..4)] of int(1..2) branching on [x_ExplicitWithRepetition_Flag, x_ExplicitWithRepetition_Values] such that and([q1 + 1 <= x_ExplicitWithRepetition_Flag -> - x_ExplicitWithRepetition_Values[q1] <= x_ExplicitWithRepetition_Values[q1 + 1] + [x_ExplicitWithRepetition_Values[q1]; int(1)] <=lex [x_ExplicitWithRepetition_Values[q1 + 1]; int(1)] | q1 : int(1..3)]), and([q2 > x_ExplicitWithRepetition_Flag -> x_ExplicitWithRepetition_Values[q2] = 1 | q2 : int(1..4)]), and([q4 <= x_ExplicitWithRepetition_Flag -> diff --git a/tests/exhaustive/basic/mset06_1/expected/model_1.eprime b/tests/exhaustive/basic/mset06_1/expected/model_1.eprime index 6ec6346fe8..a349dc8262 100644 --- a/tests/exhaustive/basic/mset06_1/expected/model_1.eprime +++ b/tests/exhaustive/basic/mset06_1/expected/model_1.eprime @@ -4,7 +4,8 @@ find x_ExplicitWithFlags_Flags: matrix indexed by [int(1..4)] of int(0..2) find x_ExplicitWithFlags_Values: matrix indexed by [int(1..4)] of int(1..2) branching on [x_ExplicitWithFlags_Flags, x_ExplicitWithFlags_Values] such that - and([x_ExplicitWithFlags_Flags[q1 + 1] > 0 -> x_ExplicitWithFlags_Values[q1] < x_ExplicitWithFlags_Values[q1 + 1] + and([x_ExplicitWithFlags_Flags[q1 + 1] > 0 -> + [x_ExplicitWithFlags_Values[q1]; int(1)] x_ExplicitWithFlags_Values[q2] = 1 | q2 : int(1..4)]), and([x_ExplicitWithFlags_Flags[q3 + 1] > 0 -> x_ExplicitWithFlags_Flags[q3] > 0 | q3 : int(1..3)]), diff --git a/tests/exhaustive/basic/mset06_1/expected/model_2.eprime b/tests/exhaustive/basic/mset06_1/expected/model_2.eprime index 3585b9ef40..bd86afafbe 100644 --- a/tests/exhaustive/basic/mset06_1/expected/model_2.eprime +++ b/tests/exhaustive/basic/mset06_1/expected/model_2.eprime @@ -5,7 +5,7 @@ find x_ExplicitWithRepetition_Values: matrix indexed by [int(1..4)] of int(1..2) branching on [x_ExplicitWithRepetition_Flag, x_ExplicitWithRepetition_Values] such that and([q1 + 1 <= x_ExplicitWithRepetition_Flag -> - x_ExplicitWithRepetition_Values[q1] <= x_ExplicitWithRepetition_Values[q1 + 1] + [x_ExplicitWithRepetition_Values[q1]; int(1)] <=lex [x_ExplicitWithRepetition_Values[q1 + 1]; int(1)] | q1 : int(1..3)]), and([q2 > x_ExplicitWithRepetition_Flag -> x_ExplicitWithRepetition_Values[q2] = 1 | q2 : int(1..4)]), and([q3 <= x_ExplicitWithRepetition_Flag -> diff --git a/tests/exhaustive/basic/mset06_2/expected/model_1.eprime b/tests/exhaustive/basic/mset06_2/expected/model_1.eprime index b91d3259b3..b7ee0a2d34 100644 --- a/tests/exhaustive/basic/mset06_2/expected/model_1.eprime +++ b/tests/exhaustive/basic/mset06_2/expected/model_1.eprime @@ -4,7 +4,8 @@ find x_ExplicitWithFlags_Flags: matrix indexed by [int(1..12)] of int(0..3) find x_ExplicitWithFlags_Values: matrix indexed by [int(1..12)] of int(1..4) branching on [x_ExplicitWithFlags_Flags, x_ExplicitWithFlags_Values] such that - and([x_ExplicitWithFlags_Flags[q1 + 1] > 0 -> x_ExplicitWithFlags_Values[q1] < x_ExplicitWithFlags_Values[q1 + 1] + and([x_ExplicitWithFlags_Flags[q1 + 1] > 0 -> + [x_ExplicitWithFlags_Values[q1]; int(1)] x_ExplicitWithFlags_Values[q2] = 1 | q2 : int(1..12)]), and([x_ExplicitWithFlags_Flags[q3 + 1] > 0 -> x_ExplicitWithFlags_Flags[q3] > 0 | q3 : int(1..11)]), diff --git a/tests/exhaustive/basic/mset06_2/expected/model_2.eprime b/tests/exhaustive/basic/mset06_2/expected/model_2.eprime index d37d09ad82..ab5801043c 100644 --- a/tests/exhaustive/basic/mset06_2/expected/model_2.eprime +++ b/tests/exhaustive/basic/mset06_2/expected/model_2.eprime @@ -5,7 +5,7 @@ find x_ExplicitWithRepetition_Values: matrix indexed by [int(1..12)] of int(1..4 branching on [x_ExplicitWithRepetition_Flag, x_ExplicitWithRepetition_Values] such that and([q1 + 1 <= x_ExplicitWithRepetition_Flag -> - x_ExplicitWithRepetition_Values[q1] <= x_ExplicitWithRepetition_Values[q1 + 1] + [x_ExplicitWithRepetition_Values[q1]; int(1)] <=lex [x_ExplicitWithRepetition_Values[q1 + 1]; int(1)] | q1 : int(1..11)]), and([q2 > x_ExplicitWithRepetition_Flag -> x_ExplicitWithRepetition_Values[q2] = 1 | q2 : int(1..12)]), and([q3 <= x_ExplicitWithRepetition_Flag -> diff --git a/tests/exhaustive/basic/mset07/expected/model_1.eprime b/tests/exhaustive/basic/mset07/expected/model_1.eprime index 51dfdd641d..b2c953a865 100644 --- a/tests/exhaustive/basic/mset07/expected/model_1.eprime +++ b/tests/exhaustive/basic/mset07/expected/model_1.eprime @@ -5,7 +5,8 @@ find x_ExplicitWithFlags_Flags: matrix indexed by [int(1..2)] of int(0..2) find x_ExplicitWithFlags_Values: matrix indexed by [int(1..2)] of int(1..a) branching on [x_ExplicitWithFlags_Flags, x_ExplicitWithFlags_Values] such that - x_ExplicitWithFlags_Flags[2] > 0 -> x_ExplicitWithFlags_Values[1] < x_ExplicitWithFlags_Values[2], + x_ExplicitWithFlags_Flags[2] > 0 -> + [x_ExplicitWithFlags_Values[1]; int(1)] x_ExplicitWithFlags_Values[q2] = 1 | q2 : int(1..2)]), x_ExplicitWithFlags_Flags[2] > 0 -> x_ExplicitWithFlags_Flags[1] > 0, 2 = sum([x_ExplicitWithFlags_Flags[q5] | q5 : int(1..2)]) diff --git a/tests/exhaustive/basic/mset07/expected/model_2.eprime b/tests/exhaustive/basic/mset07/expected/model_2.eprime index 0c20d756ee..c2b0c8db50 100644 --- a/tests/exhaustive/basic/mset07/expected/model_2.eprime +++ b/tests/exhaustive/basic/mset07/expected/model_2.eprime @@ -4,5 +4,5 @@ given a: int find x_ExplicitWithRepetition_Flag: int(2) find x_ExplicitWithRepetition_Values: matrix indexed by [int(1..2)] of int(1..a) branching on [x_ExplicitWithRepetition_Flag, x_ExplicitWithRepetition_Values] -such that x_ExplicitWithRepetition_Values[1] <= x_ExplicitWithRepetition_Values[2] +such that [x_ExplicitWithRepetition_Values[1]; int(1)] <=lex [x_ExplicitWithRepetition_Values[2]; int(1)] diff --git a/tests/exhaustive/basic/partition_01/expected/model_2.eprime b/tests/exhaustive/basic/partition_01/expected/model_2.eprime index 51f140cc38..5cba4c66a3 100644 --- a/tests/exhaustive/basic/partition_01/expected/model_2.eprime +++ b/tests/exhaustive/basic/partition_01/expected/model_2.eprime @@ -4,9 +4,10 @@ find x_PartitionAsSet_ExplicitR3_Explicit: matrix indexed by [int(1..2), int(1.. branching on [x_PartitionAsSet_ExplicitR3_Explicit] such that allDiff([x_PartitionAsSet_ExplicitR3_Explicit[q12, q13] | q12 : int(1..2), q13 : int(1..3)]), - flatten([[x_PartitionAsSet_ExplicitR3_Explicit[1, q9]; int(1)] | q9 : int(1..3)]) = 1 | q19 : int(1..2)]), flatten([[x_PartitionAsSet_ExplicitR5_ExplicitVarSizeWithMarker_Marker[1]; int(1)], - flatten([[x_PartitionAsSet_ExplicitR5_ExplicitVarSizeWithMarker_Values[1, q12]; int(1)] - | q12 : int(1..6)]); + [x_PartitionAsSet_ExplicitR5_ExplicitVarSizeWithMarker_Values[1, q12] | q12 : int(1..6)]; int(1..2)]) - x_PartitionAsSet_ExplicitR5_ExplicitVarSizeWithMarker_Values[q7, q8] < - x_PartitionAsSet_ExplicitR5_ExplicitVarSizeWithMarker_Values[q7, q8 + 1] + [x_PartitionAsSet_ExplicitR5_ExplicitVarSizeWithMarker_Values[q7, q8]; int(1)] x_PartitionAsSet_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q7] -> diff --git a/tests/exhaustive/basic/partition_03/expected/model_2.eprime b/tests/exhaustive/basic/partition_03/expected/model_2.eprime index f4fefc5668..e89b097ee9 100644 --- a/tests/exhaustive/basic/partition_03/expected/model_2.eprime +++ b/tests/exhaustive/basic/partition_03/expected/model_2.eprime @@ -10,18 +10,16 @@ such that | q14 : int(1..6), q15 : int(1..3)], 0), and([q4 + 1 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR3_Marker -> - flatten([[x_PartitionAsSet_ExplicitVarSizeWithMarkerR3_Values_Explicit[q4, q10]; int(1)] | q10 : int(1..3)]) - x_PartitionAsSet_ExplicitVarSizeWithMarkerR3_Marker -> and([x_PartitionAsSet_ExplicitVarSizeWithMarkerR3_Values_Explicit[q5, q13] = 1 | q13 : int(1..3)]) | q5 : int(1..6)]), x_PartitionAsSet_ExplicitVarSizeWithMarkerR3_Marker <= 6, and([q6 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR3_Marker -> - and([x_PartitionAsSet_ExplicitVarSizeWithMarkerR3_Values_Explicit[q6, q7] < - x_PartitionAsSet_ExplicitVarSizeWithMarkerR3_Values_Explicit[q6, q7 + 1] + and([[x_PartitionAsSet_ExplicitVarSizeWithMarkerR3_Values_Explicit[q6, q7]; int(1)] flatten([[x_RelationAsSetR3_ExplicitVarSizeWithMarkerR3_Values_1[q1]; int(1)], - flatten([[x_RelationAsSetR3_ExplicitVarSizeWithMarkerR3_Values_2_Explicit[q1, q6]; int(1)] - | q6 : int(1..2)]); + [x_RelationAsSetR3_ExplicitVarSizeWithMarkerR3_Values_2_Explicit[q1, q6] | q6 : int(1..2)]; int(1..2)]) x_RelationAsSetR3_ExplicitVarSizeWithMarkerR3_Marker -> @@ -26,7 +24,7 @@ such that 2 <= x_RelationAsSetR3_ExplicitVarSizeWithMarkerR3_Marker, x_RelationAsSetR3_ExplicitVarSizeWithMarkerR3_Marker <= 3, and([q3 <= x_RelationAsSetR3_ExplicitVarSizeWithMarkerR3_Marker -> - x_RelationAsSetR3_ExplicitVarSizeWithMarkerR3_Values_2_Explicit[q3, 1] < - x_RelationAsSetR3_ExplicitVarSizeWithMarkerR3_Values_2_Explicit[q3, 2] + [x_RelationAsSetR3_ExplicitVarSizeWithMarkerR3_Values_2_Explicit[q3, 1]; int(1)] flatten([[x_ExplicitVarSizeWithMarkerR3_Values_1[q1]; int(1)], - flatten([[x_ExplicitVarSizeWithMarkerR3_Values_2_Explicit[q1, q6]; int(1)] | q6 : int(1..2)]); + [x_ExplicitVarSizeWithMarkerR3_Values_2_Explicit[q1, q6] | q6 : int(1..2)]; int(1..2)]) x_ExplicitVarSizeWithMarkerR3_Marker -> @@ -23,6 +23,7 @@ such that 2 <= x_ExplicitVarSizeWithMarkerR3_Marker, x_ExplicitVarSizeWithMarkerR3_Marker <= 3, and([q3 <= x_ExplicitVarSizeWithMarkerR3_Marker -> - x_ExplicitVarSizeWithMarkerR3_Values_2_Explicit[q3, 1] < x_ExplicitVarSizeWithMarkerR3_Values_2_Explicit[q3, 2] + [x_ExplicitVarSizeWithMarkerR3_Values_2_Explicit[q3, 1]; int(1)] flatten([[x_ExplicitVarSizeWithFlagsR3_Values_1[q1]; int(1)], - flatten([[x_ExplicitVarSizeWithFlagsR3_Values_2_Explicit[q1, q8]; int(1)] | q8 : int(1..2)]); + [x_ExplicitVarSizeWithFlagsR3_Values_2_Explicit[q1, q8] | q8 : int(1..2)]; int(1..2)]) @@ -24,6 +24,7 @@ such that 2 <= sum([toInt(x_ExplicitVarSizeWithFlagsR3_Flags[q4]) | q4 : int(1..3)]), sum([toInt(x_ExplicitVarSizeWithFlagsR3_Flags[q4]) | q4 : int(1..3)]) <= 3, and([x_ExplicitVarSizeWithFlagsR3_Flags[q5] -> - x_ExplicitVarSizeWithFlagsR3_Values_2_Explicit[q5, 1] < x_ExplicitVarSizeWithFlagsR3_Values_2_Explicit[q5, 2] + [x_ExplicitVarSizeWithFlagsR3_Values_2_Explicit[q5, 1]; int(1)] x_Function1DPartial_Values[q1] != x_Function1DPartial_Values[q2] - | q1 : int(1..4), q2 : int(1..4), q1 < q2]), + | q1 : int(1..4), q2 : int(1..4), [q1; int(1)] x_Function1DPartial_Values[q3] = 1 | q3 : int(1..4)]) diff --git a/tests/exhaustive/basic/sequence_injective_01/expected/model.eprime b/tests/exhaustive/basic/sequence_injective_01/expected/model.eprime index 6b789c1341..c8d80819ad 100644 --- a/tests/exhaustive/basic/sequence_injective_01/expected/model.eprime +++ b/tests/exhaustive/basic/sequence_injective_01/expected/model.eprime @@ -7,5 +7,5 @@ branching on [f_ExplicitBounded_Length, f_ExplicitBounded_Values_1, f_ExplicitBo such that and([f_ExplicitBounded_Values_1[q1] != f_ExplicitBounded_Values_1[q2] \/ f_ExplicitBounded_Values_2[q1] != f_ExplicitBounded_Values_2[q2] - | q1 : int(1..2), q2 : int(1..2), q1 < q2]) + | q1 : int(1..2), q2 : int(1..2), [q1; int(1)] f_ExplicitBounded_Values_1[q2] != f_ExplicitBounded_Values_1[q3] \/ f_ExplicitBounded_Values_2[q2] != f_ExplicitBounded_Values_2[q3] - | q2 : int(1..2), q3 : int(1..2), q2 < q3]) + | q2 : int(1..2), q3 : int(1..2), [q2; int(1)] or([x_Explicit[q8] = q6 | q8 : int(1..2)]) | q6 : int(1..3)]) diff --git a/tests/exhaustive/basic/set01_2/expected/model_2_1.eprime b/tests/exhaustive/basic/set01_2/expected/model_2_1.eprime index 560304aacd..1e5c6c8989 100644 --- a/tests/exhaustive/basic/set01_2/expected/model_2_1.eprime +++ b/tests/exhaustive/basic/set01_2/expected/model_2_1.eprime @@ -5,7 +5,7 @@ find x_Occurrence: matrix indexed by [int(1..3)] of bool branching on [x_Occurrence, x_Explicit] such that and([or([x_Explicit[q10] = i | q10 : int(1..2)]) | i : int(1..2)]), - x_Explicit[1] < x_Explicit[2], + [x_Explicit[1]; int(1)] or([x_Explicit[q6] = q4 | q6 : int(1..2)]) | q4 : int(1..3)]), and([x_Occurrence[x_Explicit[q8]] | q8 : int(1..2)]) diff --git a/tests/exhaustive/basic/set01_2/expected/model_2_2.eprime b/tests/exhaustive/basic/set01_2/expected/model_2_2.eprime index 6ad71d263d..173f498e8c 100644 --- a/tests/exhaustive/basic/set01_2/expected/model_2_2.eprime +++ b/tests/exhaustive/basic/set01_2/expected/model_2_2.eprime @@ -4,5 +4,5 @@ find x_Explicit: matrix indexed by [int(1..2)] of int(1..3) branching on [x_Explicit] such that and([or([x_Explicit[q4] = i | q4 : int(1..2)]) | i : int(1..2)]), - x_Explicit[1] < x_Explicit[2] + [x_Explicit[1]; int(1)] or([x_Explicit[q8] = q6 | q8 : int(1..2)]) | q6 : int(1..3)]) diff --git a/tests/exhaustive/basic/set01_3/expected/model_2_1.eprime b/tests/exhaustive/basic/set01_3/expected/model_2_1.eprime index 560304aacd..1e5c6c8989 100644 --- a/tests/exhaustive/basic/set01_3/expected/model_2_1.eprime +++ b/tests/exhaustive/basic/set01_3/expected/model_2_1.eprime @@ -5,7 +5,7 @@ find x_Occurrence: matrix indexed by [int(1..3)] of bool branching on [x_Occurrence, x_Explicit] such that and([or([x_Explicit[q10] = i | q10 : int(1..2)]) | i : int(1..2)]), - x_Explicit[1] < x_Explicit[2], + [x_Explicit[1]; int(1)] or([x_Explicit[q6] = q4 | q6 : int(1..2)]) | q4 : int(1..3)]), and([x_Occurrence[x_Explicit[q8]] | q8 : int(1..2)]) diff --git a/tests/exhaustive/basic/set01_3/expected/model_2_2.eprime b/tests/exhaustive/basic/set01_3/expected/model_2_2.eprime index 6ad71d263d..173f498e8c 100644 --- a/tests/exhaustive/basic/set01_3/expected/model_2_2.eprime +++ b/tests/exhaustive/basic/set01_3/expected/model_2_2.eprime @@ -4,5 +4,5 @@ find x_Explicit: matrix indexed by [int(1..2)] of int(1..3) branching on [x_Explicit] such that and([or([x_Explicit[q4] = i | q4 : int(1..2)]) | i : int(1..2)]), - x_Explicit[1] < x_Explicit[2] + [x_Explicit[1]; int(1)] or([x_Explicit[q8] = q6 | q8 : int(1..2)]) | q6 : int(1..3)]) diff --git a/tests/exhaustive/basic/set02/expected/model_2_1.eprime b/tests/exhaustive/basic/set02/expected/model_2_1.eprime index 0434a4ad13..d98f6cbc26 100644 --- a/tests/exhaustive/basic/set02/expected/model_2_1.eprime +++ b/tests/exhaustive/basic/set02/expected/model_2_1.eprime @@ -5,7 +5,7 @@ find x_Occurrence: matrix indexed by [int(1..3)] of bool branching on [x_Occurrence, x_Explicit] such that or([x_Explicit[q10] = 1 | q10 : int(1..2)]), - x_Explicit[1] < x_Explicit[2], + [x_Explicit[1]; int(1)] or([x_Explicit[q6] = q4 | q6 : int(1..2)]) | q4 : int(1..3)]), and([x_Occurrence[x_Explicit[q8]] | q8 : int(1..2)]) diff --git a/tests/exhaustive/basic/set02/expected/model_2_2.eprime b/tests/exhaustive/basic/set02/expected/model_2_2.eprime index eb58084260..35b23902c2 100644 --- a/tests/exhaustive/basic/set02/expected/model_2_2.eprime +++ b/tests/exhaustive/basic/set02/expected/model_2_2.eprime @@ -4,5 +4,5 @@ find x_Explicit: matrix indexed by [int(1..2)] of int(1..3) branching on [x_Explicit] such that or([x_Explicit[q4] = 1 | q4 : int(1..2)]), - x_Explicit[1] < x_Explicit[2] + [x_Explicit[1]; int(1)] or([s_Explicit[q8] = q6 | q8 : int(1..2)]) | q6 : int(1..2)]) diff --git a/tests/exhaustive/basic/set_card_02/expected/model_1_2_1.eprime b/tests/exhaustive/basic/set_card_02/expected/model_1_2_1.eprime index a433443261..5a2b11db7d 100644 --- a/tests/exhaustive/basic/set_card_02/expected/model_1_2_1.eprime +++ b/tests/exhaustive/basic/set_card_02/expected/model_1_2_1.eprime @@ -6,7 +6,7 @@ branching on [s_Explicit, s_Occurrence] such that or([s_Explicit[q10] = 2 | q10 : int(1..2)]), 2 = sum([toInt(s_Occurrence[q1]) | q1 : int(1..2)]), - s_Explicit[1] < s_Explicit[2], + [s_Explicit[1]; int(1)] or([s_Explicit[q8] = q6 | q8 : int(1..2)]) | q6 : int(1..2)]) diff --git a/tests/exhaustive/basic/set_card_02/expected/model_1_2_2.eprime b/tests/exhaustive/basic/set_card_02/expected/model_1_2_2.eprime index a433443261..5a2b11db7d 100644 --- a/tests/exhaustive/basic/set_card_02/expected/model_1_2_2.eprime +++ b/tests/exhaustive/basic/set_card_02/expected/model_1_2_2.eprime @@ -6,7 +6,7 @@ branching on [s_Explicit, s_Occurrence] such that or([s_Explicit[q10] = 2 | q10 : int(1..2)]), 2 = sum([toInt(s_Occurrence[q1]) | q1 : int(1..2)]), - s_Explicit[1] < s_Explicit[2], + [s_Explicit[1]; int(1)] or([s_Explicit[q8] = q6 | q8 : int(1..2)]) | q6 : int(1..2)]) diff --git a/tests/exhaustive/basic/set_card_02/expected/model_2_1_1.eprime b/tests/exhaustive/basic/set_card_02/expected/model_2_1_1.eprime index d14af629f8..e61dce3c88 100644 --- a/tests/exhaustive/basic/set_card_02/expected/model_2_1_1.eprime +++ b/tests/exhaustive/basic/set_card_02/expected/model_2_1_1.eprime @@ -5,7 +5,7 @@ find s_Occurrence: matrix indexed by [int(1..2)] of bool branching on [s_Occurrence, s_Explicit] such that s_Occurrence[2], - s_Explicit[1] < s_Explicit[2], + [s_Explicit[1]; int(1)] or([s_Explicit[q6] = q4 | q6 : int(1..2)]) | q4 : int(1..2)]), and([s_Occurrence[s_Explicit[q8]] | q8 : int(1..2)]) diff --git a/tests/exhaustive/basic/set_card_02/expected/model_2_1_2.eprime b/tests/exhaustive/basic/set_card_02/expected/model_2_1_2.eprime index d14af629f8..e61dce3c88 100644 --- a/tests/exhaustive/basic/set_card_02/expected/model_2_1_2.eprime +++ b/tests/exhaustive/basic/set_card_02/expected/model_2_1_2.eprime @@ -5,7 +5,7 @@ find s_Occurrence: matrix indexed by [int(1..2)] of bool branching on [s_Occurrence, s_Explicit] such that s_Occurrence[2], - s_Explicit[1] < s_Explicit[2], + [s_Explicit[1]; int(1)] or([s_Explicit[q6] = q4 | q6 : int(1..2)]) | q4 : int(1..2)]), and([s_Occurrence[s_Explicit[q8]] | q8 : int(1..2)]) diff --git a/tests/exhaustive/basic/set_card_02/expected/model_2_2_1.eprime b/tests/exhaustive/basic/set_card_02/expected/model_2_2_1.eprime index 4983889ed3..f53e382156 100644 --- a/tests/exhaustive/basic/set_card_02/expected/model_2_2_1.eprime +++ b/tests/exhaustive/basic/set_card_02/expected/model_2_2_1.eprime @@ -5,7 +5,7 @@ find s_Occurrence: matrix indexed by [int(1..2)] of bool branching on [s_Occurrence, s_Explicit] such that or([s_Explicit[q10] = 2 | q10 : int(1..2)]), - s_Explicit[1] < s_Explicit[2], + [s_Explicit[1]; int(1)] or([s_Explicit[q6] = q4 | q6 : int(1..2)]) | q4 : int(1..2)]), and([s_Occurrence[s_Explicit[q8]] | q8 : int(1..2)]) diff --git a/tests/exhaustive/basic/set_card_02/expected/model_2_2_2.eprime b/tests/exhaustive/basic/set_card_02/expected/model_2_2_2.eprime index bcb32077c4..f060f183a1 100644 --- a/tests/exhaustive/basic/set_card_02/expected/model_2_2_2.eprime +++ b/tests/exhaustive/basic/set_card_02/expected/model_2_2_2.eprime @@ -4,5 +4,5 @@ find s_Explicit: matrix indexed by [int(1..2)] of int(1..2) branching on [s_Explicit] such that or([s_Explicit[q4] = 2 | q4 : int(1..2)]), - s_Explicit[1] < s_Explicit[2] + [s_Explicit[1]; int(1)] conjure_aux1_ExplicitVarSizeWithDummy[q5 + 1] = 4 | q5 : int(1..2)]), diff --git a/tests/exhaustive/basic/toSet_comprehension/expected/model_3.eprime b/tests/exhaustive/basic/toSet_comprehension/expected/model_3.eprime index aa55c84836..1124f64f1b 100644 --- a/tests/exhaustive/basic/toSet_comprehension/expected/model_3.eprime +++ b/tests/exhaustive/basic/toSet_comprehension/expected/model_3.eprime @@ -9,7 +9,8 @@ find conjure_aux1_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3) branching on [flags, val, x] such that and([q4 + 1 <= conjure_aux1_ExplicitVarSizeWithMarker_Marker -> - conjure_aux1_ExplicitVarSizeWithMarker_Values[q4] < conjure_aux1_ExplicitVarSizeWithMarker_Values[q4 + 1] + [conjure_aux1_ExplicitVarSizeWithMarker_Values[q4]; int(1)] conjure_aux1_ExplicitVarSizeWithMarker_Marker -> conjure_aux1_ExplicitVarSizeWithMarker_Values[q5] = 1 | q5 : int(1..3)]), diff --git a/tests/exhaustive/basic/toSet_comprehension/expected/model_4.eprime b/tests/exhaustive/basic/toSet_comprehension/expected/model_4.eprime index 9672c4965c..4114f93599 100644 --- a/tests/exhaustive/basic/toSet_comprehension/expected/model_4.eprime +++ b/tests/exhaustive/basic/toSet_comprehension/expected/model_4.eprime @@ -9,7 +9,8 @@ find conjure_aux1_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3)] branching on [flags, val, x] such that and([conjure_aux1_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> - conjure_aux1_ExplicitVarSizeWithFlags_Values[q4] < conjure_aux1_ExplicitVarSizeWithFlags_Values[q4 + 1] + [conjure_aux1_ExplicitVarSizeWithFlags_Values[q4]; int(1)] conjure_aux1_ExplicitVarSizeWithFlags_Values[q5] = 1 | q5 : int(1..3)]), diff --git a/tests/exhaustive/basic/variant01/expected/model_1.eprime b/tests/exhaustive/basic/variant01/expected/model_1.eprime index 95ae6d56dc..b35c0c35a1 100644 --- a/tests/exhaustive/basic/variant01/expected/model_1.eprime +++ b/tests/exhaustive/basic/variant01/expected/model_1.eprime @@ -9,15 +9,13 @@ branching on x_ExplicitVarSizeWithMarker_Values_theBool, x_ExplicitVarSizeWithMarker_Values_theInt] such that and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - flatten([[x_ExplicitVarSizeWithMarker_Values__tag[q1]; int(1)], - [-toInt(x_ExplicitVarSizeWithMarker_Values_theBool[q1]); int(1)], - [x_ExplicitVarSizeWithMarker_Values_theInt[q1]; int(1)]; - int(1..3)]) + [x_ExplicitVarSizeWithMarker_Values__tag[q1], -toInt(x_ExplicitVarSizeWithMarker_Values_theBool[q1]), + x_ExplicitVarSizeWithMarker_Values_theInt[q1]; + int(1..3)] x_ExplicitVarSizeWithMarker_Marker -> and([x_ExplicitVarSizeWithMarker_Values__tag[q2] = 1, x_ExplicitVarSizeWithMarker_Values_theBool[q2] = false, diff --git a/tests/exhaustive/basic/variant01/expected/model_2.eprime b/tests/exhaustive/basic/variant01/expected/model_2.eprime index 93484568b2..7723511ff7 100644 --- a/tests/exhaustive/basic/variant01/expected/model_2.eprime +++ b/tests/exhaustive/basic/variant01/expected/model_2.eprime @@ -9,15 +9,13 @@ branching on x_ExplicitVarSizeWithFlags_Values_theBool, x_ExplicitVarSizeWithFlags_Values_theInt] such that and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - flatten([[x_ExplicitVarSizeWithFlags_Values__tag[q1]; int(1)], - [-toInt(x_ExplicitVarSizeWithFlags_Values_theBool[q1]); int(1)], - [x_ExplicitVarSizeWithFlags_Values_theInt[q1]; int(1)]; - int(1..3)]) + [x_ExplicitVarSizeWithFlags_Values__tag[q1], -toInt(x_ExplicitVarSizeWithFlags_Values_theBool[q1]), + x_ExplicitVarSizeWithFlags_Values_theInt[q1]; + int(1..3)] and([x_ExplicitVarSizeWithFlags_Values__tag[q2] = 1, x_ExplicitVarSizeWithFlags_Values_theBool[q2] = false, diff --git a/tests/exhaustive/issues/182/expected/model.eprime b/tests/exhaustive/issues/182/expected/model.eprime index c51a6815c8..42f89e0671 100644 --- a/tests/exhaustive/issues/182/expected/model.eprime +++ b/tests/exhaustive/issues/182/expected/model.eprime @@ -13,34 +13,32 @@ branching on p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values] such that and([1 = - sum([toInt(q21 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - or([q23 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q21] + sum([toInt(q23 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ + or([q25 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q23] /\ and([p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q21, q23, q24] - = q1[q24] - | q24 : int(1..2)]) - | q23 : int(1..4)])) - | q21 : int(1..4)]) + [q23, q25, q26] + = q1[q26] + | q26 : int(1..2)]) + | q25 : int(1..4)])) + | q23 : int(1..4)]) | q1 : matrix indexed by [int(1..2)] of int(1..2)]), - and([q26 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q26] >= 1 - | q26 : int(1..4)]), + and([q28 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> + p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q28] >= 1 + | q28 : int(1..4)]), and([q4 + 1 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> flatten([[p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q4]; int(1)], - flatten([flatten([[p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q4, q12, q13]; - int(1)] - | q13 : int(1..2)]) + flatten([[p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values + [q4, q12, q13] + | q13 : int(1..2)] | q12 : int(1..4)]); int(1..2)]) and([q7 + 1 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q6] -> - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q6, q7, ..] and([q8 > p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q6] -> - and([p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q6, q8, q18] = 1 - | q18 : int(1..2)]) + and([p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q6, q8, q20] = 1 + | q20 : int(1..2)]) | q8 : int(1..4)]) | q6 : int(1..4)]), and([q6 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q6] <= 4 | q6 : int(1..4)]), 4 = - sum([toInt(q19 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker) * - catchUndef(p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q19], 0) - | q19 : int(1..4)]) + sum([toInt(q21 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker) * + catchUndef(p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q21], 0) + | q21 : int(1..4)]) diff --git a/tests/exhaustive/issues/200/expected/model_1_2.eprime b/tests/exhaustive/issues/200/expected/model_1_2.eprime index 698b9815ac..49a92913f7 100644 --- a/tests/exhaustive/issues/200/expected/model_1_2.eprime +++ b/tests/exhaustive/issues/200/expected/model_1_2.eprime @@ -9,7 +9,7 @@ such that and([quasigroup_Occurrence[a] /\ quasigroup_Occurrence[b] -> a * b * (b * a) = a | a : int(0..4), b : int(0..4), b > a]), 5 = sum([toInt(quasigroup_Occurrence[q1]) | q1 : int(0..4)]), - and([quasigroup_Explicit[q2] < quasigroup_Explicit[q2 + 1] | q2 : int(1..4)]), + and([[quasigroup_Explicit[q2]; int(1)] or([quasigroup_Explicit[q8] = q6 | q8 : int(1..5)]) | q6 : int(0..4)]) diff --git a/tests/exhaustive/issues/200/expected/model_2_1.eprime b/tests/exhaustive/issues/200/expected/model_2_1.eprime index 681dbb21e1..53ba03c244 100644 --- a/tests/exhaustive/issues/200/expected/model_2_1.eprime +++ b/tests/exhaustive/issues/200/expected/model_2_1.eprime @@ -9,7 +9,7 @@ such that and([quasigroup_Explicit[q11] * quasigroup_Explicit[q12] * (quasigroup_Explicit[q12] * quasigroup_Explicit[q11]) = quasigroup_Explicit[q11] | q11 : int(1..5), q12 : int(1..5), q12 > q11]), - and([quasigroup_Explicit[q1] < quasigroup_Explicit[q1 + 1] | q1 : int(1..4)]), + and([[quasigroup_Explicit[q1]; int(1)] or([quasigroup_Explicit[q6] = q4 | q6 : int(1..5)]) | q4 : int(0..4)]), and([quasigroup_Occurrence[quasigroup_Explicit[q8]] | q8 : int(1..5)]) diff --git a/tests/exhaustive/issues/200/expected/model_2_2.eprime b/tests/exhaustive/issues/200/expected/model_2_2.eprime index 618aea87ae..027f5a520e 100644 --- a/tests/exhaustive/issues/200/expected/model_2_2.eprime +++ b/tests/exhaustive/issues/200/expected/model_2_2.eprime @@ -8,5 +8,5 @@ such that and([quasigroup_Explicit[q5] * quasigroup_Explicit[q6] * (quasigroup_Explicit[q6] * quasigroup_Explicit[q5]) = quasigroup_Explicit[q5] | q5 : int(1..5), q6 : int(1..5), q6 > q5]), - and([quasigroup_Explicit[q1] < quasigroup_Explicit[q1 + 1] | q1 : int(1..4)]) + and([[quasigroup_Explicit[q1]; int(1)] a_Function1DPartial_Values[q1] != a_Function1DPartial_Values[q2] - | q1 : int(0..let1), q2 : int(0..let1), q1 < q2]), + | q1 : int(0..let1), q2 : int(0..let1), [q1; int(1)] a_Function1DPartial_Values[q5] = 1 | q5 : int(0..let1)]) diff --git a/tests/exhaustive/issues/263/expected/model-p2-solution000001.solution b/tests/exhaustive/issues/263/expected/model-p2-solution000001.solution deleted file mode 100644 index ac8c733f23..0000000000 --- a/tests/exhaustive/issues/263/expected/model-p2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting O be new type enum {O_1, O_2} -letting f be function(O_1 --> O_1, O_2 --> O_2) diff --git a/tests/exhaustive/issues/263/expected/model-p2.eprime-param b/tests/exhaustive/issues/263/expected/model-p2.eprime-param deleted file mode 100644 index 15cca3e147..0000000000 --- a/tests/exhaustive/issues/263/expected/model-p2.eprime-param +++ /dev/null @@ -1,3 +0,0 @@ -language ESSENCE' 1.0 - -letting v be 2 diff --git a/tests/exhaustive/issues/284/expected/model_1_2.eprime b/tests/exhaustive/issues/284/expected/model_1_2.eprime index f9f4ca9536..54a4db5a0a 100644 --- a/tests/exhaustive/issues/284/expected/model_1_2.eprime +++ b/tests/exhaustive/issues/284/expected/model_1_2.eprime @@ -11,7 +11,7 @@ such that and([conjure_aux1_Occurrence[q4] -> or([f_Function1DPartial_Flags[q8] /\ f_Function1DPartial_Values[q8] = q4 | q8 : int(1..3)]) | q4 : int(1..3)]), - and([conjure_aux2_Explicit[q11] < conjure_aux2_Explicit[q11 + 1] | q11 : int(1..2)]), + and([[conjure_aux2_Explicit[q11]; int(1)] or([conjure_aux2_Explicit[q15] = q13 | q15 : int(1..3)]) | q13 : int(1..3)]), and([or([f_Function1DPartial_Flags[q17] /\ q17 = conjure_aux2_Explicit[q16] | q17 : int(1..3)]) | q16 : int(1..3)]), and([f_Function1DPartial_Flags[q1] = false -> f_Function1DPartial_Values[q1] = 1 | q1 : int(1..3)]) diff --git a/tests/exhaustive/issues/284/expected/model_2_1.eprime b/tests/exhaustive/issues/284/expected/model_2_1.eprime index 4f72e0091f..c41e2b5a97 100644 --- a/tests/exhaustive/issues/284/expected/model_2_1.eprime +++ b/tests/exhaustive/issues/284/expected/model_2_1.eprime @@ -6,7 +6,7 @@ find conjure_aux1_Explicit: matrix indexed by [int(1..2)] of int(1..3) find conjure_aux2_Occurrence: matrix indexed by [int(1..3)] of bool branching on [f_Function1DPartial_Flags, f_Function1DPartial_Values] such that - conjure_aux1_Explicit[1] < conjure_aux1_Explicit[2], + [conjure_aux1_Explicit[1]; int(1)] or([conjure_aux1_Explicit[q10] = f_Function1DPartial_Values[q8] | q10 : int(1..2)]) | q8 : int(1..3)]), diff --git a/tests/exhaustive/issues/284/expected/model_2_2.eprime b/tests/exhaustive/issues/284/expected/model_2_2.eprime index c5ba643d69..aabab47d39 100644 --- a/tests/exhaustive/issues/284/expected/model_2_2.eprime +++ b/tests/exhaustive/issues/284/expected/model_2_2.eprime @@ -6,14 +6,14 @@ find conjure_aux1_Explicit: matrix indexed by [int(1..2)] of int(1..3) find conjure_aux2_Explicit: matrix indexed by [int(1..3)] of int(1..3) branching on [f_Function1DPartial_Flags, f_Function1DPartial_Values] such that - conjure_aux1_Explicit[1] < conjure_aux1_Explicit[2], + [conjure_aux1_Explicit[1]; int(1)] or([conjure_aux1_Explicit[q10] = f_Function1DPartial_Values[q8] | q10 : int(1..2)]) | q8 : int(1..3)]), and([or([f_Function1DPartial_Flags[q12] /\ f_Function1DPartial_Values[q12] = conjure_aux1_Explicit[q11] | q12 : int(1..3)]) | q11 : int(1..2)]), - and([conjure_aux2_Explicit[q15] < conjure_aux2_Explicit[q15 + 1] | q15 : int(1..2)]), + and([[conjure_aux2_Explicit[q15]; int(1)] or([conjure_aux2_Explicit[q19] = q17 | q19 : int(1..3)]) | q17 : int(1..3)]), and([or([f_Function1DPartial_Flags[q21] /\ q21 = conjure_aux2_Explicit[q20] | q21 : int(1..3)]) | q20 : int(1..3)]), and([f_Function1DPartial_Flags[q1] = false -> f_Function1DPartial_Values[q1] = 1 | q1 : int(1..3)]) diff --git a/tests/exhaustive/issues/309/expected/model-solution000001.solution b/tests/exhaustive/issues/309/expected/model-solution000001.solution deleted file mode 100644 index 58b54d127a..0000000000 --- a/tests/exhaustive/issues/309/expected/model-solution000001.solution +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting var1 be 2 diff --git a/tests/exhaustive/issues/309/expected/model.eprime b/tests/exhaustive/issues/309/expected/model.eprime deleted file mode 100644 index 9c9983f4d7..0000000000 --- a/tests/exhaustive/issues/309/expected/model.eprime +++ /dev/null @@ -1,8 +0,0 @@ -language ESSENCE' 1.0 - -find var1: int(1..2) -branching on [var1] -such that - [true, true, true, true; int(1..4)] <=lex - [[true, false, false, true; int(1..4)], [true, true, true, true; int(1..4)]; int(1..2)][var1, ..] - From 194fb806323627c6ff7358a2d20b925b1813e019 Mon Sep 17 00:00:00 2001 From: Fraser Dunlop Date: Wed, 15 May 2019 12:16:53 +0100 Subject: [PATCH 099/229] more symmetry ordering cases --- src/Conjure/Representations.hs | 108 +++++++++++------- src/Conjure/UI/Model.hs | 21 +++- tests/exhaustive/issues/309/_issue_38.essence | 2 +- .../expected/model-solution000001.solution | 3 + .../issues/309/expected/model.eprime | 6 + 5 files changed, 93 insertions(+), 47 deletions(-) create mode 100644 tests/exhaustive/issues/309/expected/model-solution000001.solution create mode 100644 tests/exhaustive/issues/309/expected/model.eprime diff --git a/src/Conjure/Representations.hs b/src/Conjure/Representations.hs index 80c78b5420..392b3a52db 100644 --- a/src/Conjure/Representations.hs +++ b/src/Conjure/Representations.hs @@ -134,47 +134,69 @@ symmetryOrdering :: EnumerateDomain m => (?typeCheckerMode :: TypeCheckerMode) => Expression -> m Expression -symmetryOrdering inp = do - case inp of - -- Constant x -> so_onConstant x --- AbstractLiteral _ -> return inp - AbstractLiteral x -> do - case x of - AbsLitTuple xs -> do - soVals <- sequence (symmetryOrdering <$> xs) - return $ AbstractLiteral $ AbsLitTuple soVals --make opFlatten (fromList soVals) - AbsLitMatrix d xs -> do - soVals <- sequence (symmetryOrdering <$> xs) - return $ AbstractLiteral $ AbsLitMatrix d soVals - _ -> bug ("symmetryOrdering: AbstractLiteral:" <++> pretty (show inp) <++> pretty (inp)) - - - Reference _ (Just refTo) -> do - case refTo of - Alias x -> symmetryOrdering x - InComprehension{} -> bug ("symmetryOrdering.InComprehension:" <++> pretty (show inp)) - DeclNoRepr{} -> bug ("symmetryOrdering.DeclNoRepr:" <++> pretty (show inp)) - DeclHasRepr _forg _name domain -> symmetryOrderingDispatch downX1 inp domain - RecordField{} -> bug ("symmetryOrdering.RecordField:" <++> pretty (show inp)) - VariantField{} -> bug ("symmetryOrdering.VariantField:" <++> pretty (show inp)) - Op op -> case op of - MkOpIndexing (OpIndexing m _) -> do - ty <- typeOf m - case ty of - TypeMatrix{} -> return () - TypeList{} -> return () - _ -> bug $ "[symmetryOrdering.onOp, not a TypeMatrix or TypeList]" <+> vcat [pretty ty, pretty op] - mDom <- domainOfR m - case mDom of - DomainMatrix _ domainInner -> symmetryOrderingDispatch downX1 inp domainInner - _ -> bug ("symmetryOrdering, not DomainMatrix:" <++> pretty (show op)) - MkOpImage (OpImage p x) -> do - so <- symmetryOrdering x - return [essence| image(&p, &so) |] - _ -> bug ("symmetryOrdering, no OpIndexing:" <++> pretty (show op)) - Comprehension body stmts -> do - xs <- symmetryOrdering body - return $ make opFlatten $ Comprehension xs stmts - -- x@WithLocals{} -> bug ("downX1:" <++> pretty (show x)) - _ -> bug ("symmetryOrdering:" <++> pretty (show inp) <++> pretty (inp)) +symmetryOrdering inp' = do + let constBool (ConstantBool True) = ConstantInt TagInt 1 + constBool (ConstantBool False) = ConstantInt TagInt 0 + constBool x = x + inp = transformBi constBool inp' + ta <- typeOf inp + case ta of + TypeBool -> return [essence| [-toInt(&inp)] |] + TypeInt{} -> return [essence| [&inp] |] + TypeList TypeInt{} -> return inp + TypeMatrix TypeInt{} TypeInt{} -> return inp + _ -> do + case inp of + -- Constant x -> so_onConstant x + -- AbstractLiteral _ -> return inp + Constant (ConstantAbstract x) -> do + case x of + AbsLitTuple xs -> do + soVals <- sequence (symmetryOrdering <$> (Constant <$> xs)) + return $ fromList soVals + AbsLitMatrix _ xs -> do + soVals <- sequence (symmetryOrdering <$> (Constant <$> xs)) + return $ fromList soVals + _ -> bug ("symmetryOrdering: AbstractLiteral:" <++> pretty (show inp) <++> pretty (inp)) + Constant (ConstantBool b) -> return [essence| -toInt(&inp) |] + AbstractLiteral x -> do + case x of + AbsLitTuple xs -> do + soVals <- sequence (symmetryOrdering <$> xs) + return $ AbstractLiteral $ AbsLitTuple soVals + AbsLitMatrix d xs -> do + soVals <- sequence (symmetryOrdering <$> xs) + return $ AbstractLiteral $ AbsLitMatrix d soVals + _ -> bug ("symmetryOrdering: AbstractLiteral:" <++> pretty (show inp) <++> pretty (inp)) + + + Reference _ (Just refTo) -> do + case refTo of + Alias x -> symmetryOrdering x + InComprehension{} -> bug ("symmetryOrdering.InComprehension:" <++> pretty (show inp)) + DeclNoRepr{} -> bug ("symmetryOrdering.DeclNoRepr:" <++> pretty (show inp)) + DeclHasRepr _forg _name domain -> symmetryOrderingDispatch downX1 inp domain + RecordField{} -> bug ("symmetryOrdering.RecordField:" <++> pretty (show inp)) + VariantField{} -> bug ("symmetryOrdering.VariantField:" <++> pretty (show inp)) + Op op -> case op of + MkOpIndexing (OpIndexing m _) -> do + + ty <- typeOf m + case ty of + TypeMatrix{} -> return () + TypeList{} -> return () + _ -> bug $ "[symmetryOrdering.onOp, not a TypeMatrix or TypeList]" <+> vcat [pretty ty, pretty op] + mDom <- domainOfR m + case mDom of + DomainMatrix _ domainInner -> symmetryOrderingDispatch downX1 inp domainInner + _ -> bug ("symmetryOrdering, not DomainMatrix:" <++> pretty (show op)) + MkOpImage (OpImage p x) -> do + so <- symmetryOrdering x + return [essence| image(&p, &so) |] + _ -> bug ("symmetryOrdering, no OpIndexing:" <++> pretty (show op)) + Comprehension body stmts -> do + xs <- symmetryOrdering body + return $ make opFlatten $ Comprehension xs stmts + -- x@WithLocals{} -> bug ("downX1:" <++> pretty (show x)) + _ -> bug ("symmetryOrdering:" <++> pretty (show inp) <++> pretty (inp)) diff --git a/src/Conjure/UI/Model.hs b/src/Conjure/UI/Model.hs index 037ac2edc6..c68a11453b 100644 --- a/src/Conjure/UI/Model.hs +++ b/src/Conjure/UI/Model.hs @@ -751,12 +751,27 @@ flattenLex m = do TypedConstant tc _ -> flatten (Constant tc) _ -> bug $ "epilogue: flattenLex: isn't defined for this constant fellow." <+> vcat [pretty a, pretty ta, stringToDoc $ show a] +-- Op op -> do +-- case op of +-- MkOpIndexing (OpIndexing m i) -> +-- bug $ "epilogue: flattenLex: flatten not defined for this indexed fellow." +-- <+> vcat [stringToDoc (show a) +-- ,"fellow:" <+> stringToDoc (show m) +-- ,"index:" <+> stringToDoc (show i)] + Reference nm ex -> + bug $ "epilogue: flattenLex: flatten not defined for this referenced fellow." + <+> vcat [stringToDoc (show a) + ,"reference:" <+> stringToDoc (show nm) + ,"fellow:" <+> stringToDoc (show ex)] Comprehension body gocs -> do fbody <- flatten body let comp = Comprehension fbody gocs - return [essence| flatten(&comp) |] +-- return [essence| flatten(&comp) |] + return [essence| &comp |] _ -> bug $ "epilogue: flattenLex: isn't defined for this expression fellow..." <+> vcat [pretty a, pretty ta, stringToDoc $ show a] + + flattener [essence| &a return () -- _ -> na "rule_DotLtLeq" -- sameRepresentationTree a b - ma <- symmetryOrdering $ transformBi reDomExp $ transformBi reDomConst a - mb <- symmetryOrdering $ transformBi reDomExp $ transformBi reDomConst b + ma <- symmetryOrdering a + mb <- symmetryOrdering b return ( "Generic vertical rule for dotLt and dotLeq:" <+> pretty p , return $ mk ma mb diff --git a/tests/exhaustive/issues/309/_issue_38.essence b/tests/exhaustive/issues/309/_issue_38.essence index 7734ea37f5..520f5bc562 100644 --- a/tests/exhaustive/issues/309/_issue_38.essence +++ b/tests/exhaustive/issues/309/_issue_38.essence @@ -5,5 +5,5 @@ such that [ [true , false, false, true; int(1..4)] , [true , true , true , true; int(1..4)] ; int(1..2) - ][var1, ..] >=lex + ][var1, ..] .>= [true , true , true , true ; int(1..4)] diff --git a/tests/exhaustive/issues/309/expected/model-solution000001.solution b/tests/exhaustive/issues/309/expected/model-solution000001.solution new file mode 100644 index 0000000000..58b54d127a --- /dev/null +++ b/tests/exhaustive/issues/309/expected/model-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting var1 be 2 diff --git a/tests/exhaustive/issues/309/expected/model.eprime b/tests/exhaustive/issues/309/expected/model.eprime new file mode 100644 index 0000000000..73da0b937c --- /dev/null +++ b/tests/exhaustive/issues/309/expected/model.eprime @@ -0,0 +1,6 @@ +language ESSENCE' 1.0 + +find var1: int(1..2) +branching on [var1] +such that [1, 1, 1, 1; int(1..4)] <=lex [[1, 0, 0, 1; int(1..4)], [1, 1, 1, 1; int(1..4)]; int(1..2)][var1, ..] + From 3f68a5f1a6ee01bf9bb8bce5a431080dfa064bc8 Mon Sep 17 00:00:00 2001 From: Fraser Dunlop Date: Wed, 15 May 2019 15:36:57 +0100 Subject: [PATCH 100/229] replace <=lex in test files with .<= --- .MINIONSOLS_1557920204186_7093 | 0 .MINIONSTATS_1557920204186_7093 | 2 ++ etc/testdata/specs/matrixes.essence | 2 +- etc/testdata/specs/matrixes2.essence | 2 +- etc/testdata/specs/n3.essence | 2 +- etc/testdata/specs/set-of-lettings.essence | 2 +- etc/upTests/___simple/matrixes_of_tuples.essence | 2 +- etc/upTests/_matrix_of_tuples/different.essence | 2 +- etc/upTests/matrixes2.essence | 2 +- tests/custom/basic/solutionsInOneFile/test.essence | 2 +- .../21_set_comprehension/set_comprehension.essence | 2 +- tests/exhaustive/autogen/gen02/gen02.essence | 2 +- tests/exhaustive/autogen/gen38/gen38.essence | 2 +- tests/exhaustive/issues/236/langfords.essence | 2 +- ...00f3f6e00d6aaa0c44f7a7bfaeabf301.eprime.essence | 8 ++++---- .../0155ed23298044f98c24b049e9f674d5.essence | 2 +- ...016e7609f3aa273a2a9d8f851cda23b0.eprime.essence | 6 +++--- ...03336ac6e1e3f3c00e3feb6957358811.eprime.essence | 6 +++--- ...039a29d0d4631598657b8b2611a05cf6.eprime.essence | 2 +- ...03fa5e0fb1010e34c88e5d085c726276.eprime.essence | 8 ++++---- ...0632e804c201340757931f64f9587edb.eprime.essence | 2 +- ...06af2d456d70394d86a8f427da584a37.eprime.essence | 8 ++++---- .../074ea9fbacd659cc463b376a2772bf13.essence | 2 +- ...075527221a657e78d6f1c0a6a335371f.eprime.essence | 2 +- ...084959e428c16c5485c7775b20480e40.eprime.essence | 6 +++--- ...089427b807ae2e05bb8e2512153035ee.eprime.essence | 10 +++++----- ...0896777a9c9ec7a2944d17b0f832af27.eprime.essence | 10 +++++----- .../09ac2051b1e1a54e1b7a3b051b78bcd3.essence | 2 +- ...0a4c5d1f2a6f82e1a72b0732362906b6.eprime.essence | 4 ++-- ...0b621881d60dee823364b01fd40f9769.eprime.essence | 2 +- ...0d57246ca2b2deb63c1aa6a5fc286fa2.eprime.essence | 8 ++++---- ...0d757bbc1bf600cc00cccc23dd0dbabb.eprime.essence | 6 +++--- ...0ed115e4ee3afb7cae4c8f89695c5fdd.eprime.essence | 6 +++--- ...10c99281fb90ea99297131629d79951b.eprime.essence | 8 ++++---- ...10ee9f7ba50dfd3e0bdcc8ad341640d3.eprime.essence | 2 +- ...1191a8fe91feb6b1ae455420e223bf6e.eprime.essence | 8 ++++---- ...1291155001a2b89117838f7032c4ab5e.eprime.essence | 6 +++--- ...13700d10e259531c00b3ea61a5a5222e.eprime.essence | 10 +++++----- ...139f9520357e237c8f0d1489daa512e8.eprime.essence | 4 ++-- .../13eda547bb0b8ccccb4b8cc348f66d91.essence | 2 +- ...15916e89942607cd189f87dbe1a6552b.eprime.essence | 4 ++-- ...16fd8e97c063710963e8c810fe6d2065.eprime.essence | 4 ++-- ...176498a86f4f6aa56d13e84f835917e5.eprime.essence | 4 ++-- .../183ea55a9258e18d69a7b15d4f823c67.essence | 2 +- ...18bf9a38ee59e4bcaebd478b9f980662.eprime.essence | 4 ++-- .../1a4f723156644e60a38ec0e325765e17.essence | 2 +- ...1abb07c9ef975b96bf575bfbe8f442b5.eprime.essence | 2 +- ...1b6c1179b1a92bd88edaeed5c5bfb398.eprime.essence | 2 +- ...1cc14f70f3fd8130affee799d5120a35.eprime.essence | 6 +++--- ...1e3c2ea5eb1b0a1eb092e59c73e21e65.eprime.essence | 6 +++--- ...200d78834a42ebeb6f12a80d41000004.eprime.essence | 4 ++-- ...208ec24add8f7b331f0829f7296b04c7.eprime.essence | 8 ++++---- .../20a87ed854619dfbc1f01b026e5db67b.essence | 2 +- .../21be920dffbaacd7e2b6b06b72cb75c0.essence | 2 +- ...22477309ce0401a8d76f05db531a8477.eprime.essence | 8 ++++---- ...23bad3eae7b82e1742600d53802770fd.eprime.essence | 4 ++-- ...23f59fd02b1d9c3816b417a8727e418c.eprime.essence | 2 +- ...256afa47464e2a7d839a0636d335714b.eprime.essence | 4 ++-- .../25c731b81cdfba9a1930f6d921e9fc53.essence | 2 +- .../27751403de10fefc991154fbb6c3f49a.essence | 2 +- ...282fe3e111717af84f27689693c94ac4.eprime.essence | 4 ++-- .../2835cf8d0df29e21336c9c33319cc86f.essence | 2 +- ...2910579caa938519c953fccd48611fee.eprime.essence | 6 +++--- ...2abab26b761b711b383086f57689adc5.eprime.essence | 4 ++-- ...2c66ae20ba104065bc0b14b9b0eb8e2c.eprime.essence | 4 ++-- ...2cb879c833748cef779f84df872b0d71.eprime.essence | 8 ++++---- ...2e2ad8fe1fae6676863edda2c078d2f2.eprime.essence | 8 ++++---- ...3092be0de62c362cd1c49042c585105f.eprime.essence | 6 +++--- ...31f683d305b86f1023d4853cf84d6901.eprime.essence | 2 +- ...32ba15f900d2899e277de2884b82db33.eprime.essence | 2 +- ...32f8563c6daa93f905b86ab15f412aa7.eprime.essence | 2 +- ...34552e2be8dd2ea63930ffe4b5a015aa.eprime.essence | 4 ++-- ...34efe399d190ea2b129f8a3c0e7a0e52.eprime.essence | 6 +++--- ...35a9b9aabd733bd1da92dcfbbafbb0e0.eprime.essence | 4 ++-- ...35aec2a8434e0ae0a0041beca9f1d91e.eprime.essence | 4 ++-- ...35bd3096c398059a5f4e2e9de6159866.eprime.essence | 6 +++--- ...360166fcf3210cf2cc730698c7561f1a.eprime.essence | 8 ++++---- ...3620a44b9d1882d1b8d68ebb7c2e267b.eprime.essence | 8 ++++---- ...36adf65748e3aabfd49290654b8b9ec2.eprime.essence | 4 ++-- ...37b6d848c391d03c123e6e8c55e6b822.eprime.essence | 8 ++++---- ...39936b90fd0cf508557865456d964b8b.eprime.essence | 10 +++++----- ...39a705752a0c5e219408facaeb5079d9.eprime.essence | 6 +++--- .../39fc0816e0aea89208c87fa4d39edf4d.essence | 2 +- ...3b5e1803eab57ae500a891f3bfadce58.eprime.essence | 6 +++--- ...3cc911ee89eb40d0d5e49b63286e8f7f.eprime.essence | 6 +++--- ...3d535f0ac7272986482b759dae43c292.eprime.essence | 4 ++-- ...3ec03da1ddc427cf36261757e735114e.eprime.essence | 2 +- ...3f487c8189ea7cd34b26c9482423c22f.eprime.essence | 8 ++++---- ...406db1c9f1d0b024a8ba6de04ada1fa2.eprime.essence | 4 ++-- .../40c777188c96f06f23b379634df5be19.essence | 2 +- ...40ce6cdb722c1098a95e3150cf28137a.eprime.essence | 4 ++-- ...4280cfb278486b51961b41fb8309b68d.eprime.essence | 10 +++++----- ...42c5a23fafc955d441461af4184f86f2.eprime.essence | 8 ++++---- ...434c784a35b841f5f825ff3ec5fbff68.eprime.essence | 8 ++++---- ...444f84074522a17b89cf4e24e859558a.eprime.essence | 14 +++++++------- ...44dd846c20ee4eb39d7cc4a19408a0ae.eprime.essence | 6 +++--- ...461bdf3c29b2f09b541034b080952550.eprime.essence | 4 ++-- .../463c263b7ca3948dadc72aac12f03675.essence | 2 +- ...48929a67dab909763280169f5d4632b9.eprime.essence | 4 ++-- ...48faac38ade4e0680ba7f0e26fc7d315.eprime.essence | 4 ++-- ...499e079eb49364e5f37956fbd5635887.eprime.essence | 4 ++-- ...49c4bb2084ae145c951d6e363a90ea9f.eprime.essence | 4 ++-- ...49c6df33edfc97e3f0f7b81aa6940880.eprime.essence | 6 +++--- ...4a598ea5ec7744cc20c3a53601371daf.eprime.essence | 8 ++++---- ...4aba79f85e75b7880783738a0de5456f.eprime.essence | 4 ++-- ...4b23607e697a7b33b7855bb9e6d8e164.eprime.essence | 6 +++--- ...4be21fd12a8819847cbd51dea1e370a3.eprime.essence | 6 +++--- .../4ea83cdfbcaf661ef1707eb376d12dcb.essence | 2 +- ...4f9ae4ffb009a3b226c8414061bd362f.eprime.essence | 4 ++-- ...5066c398855444982cf41c9d767fd995.eprime.essence | 4 ++-- .../5068bddda9fe656697ec6de2579580db.essence | 2 +- ...5389d8ae83d9b2260e7c5697c481970a.eprime.essence | 4 ++-- ...54c995d240bca20d3853847acef38f4b.eprime.essence | 4 ++-- ...5537b34a9991a0fb4580102062c0b795.eprime.essence | 6 +++--- ...5730851ebaf12a1212be46cc5a31235d.eprime.essence | 8 ++++---- ...5b7f553219b00b0d37cfc5bec0f2eaf6.eprime.essence | 4 ++-- ...5c05f9d9fdff466f29cbe3e931304e9a.eprime.essence | 2 +- ...5cfc3c0f1cdd912aca8ac526cf3a7102.eprime.essence | 8 ++++---- ...5df0ac9ae39fb7bfbf5f990f89cd23d5.eprime.essence | 4 ++-- ...5f8abcfb913c155e5fcf9aad1689ee48.eprime.essence | 4 ++-- ...603465a931823cf8433459de2d015883.eprime.essence | 6 +++--- .../612a3b4f1e02d37d3c58b3ade9b248ef.essence | 2 +- ...62efe6787e7be32b6775a9054b5e7a90.eprime.essence | 4 ++-- ...635d068c0ed6bbf9ed532bcb7160ca5b.eprime.essence | 6 +++--- ...67856b9617d62beaf659a45708f21210.eprime.essence | 2 +- ...6816e93188da042831d6849d9fc88b51.eprime.essence | 2 +- ...688d9c5f26c404975d660fcdd262858c.eprime.essence | 4 ++-- ...6aca6588ab888f9c3965cb703a7ffa87.eprime.essence | 10 +++++----- ...6d234926de4bf3efc85ef76d53a68827.eprime.essence | 6 +++--- ...6e78775adcfd98bd61ddfa72523d20d7.eprime.essence | 6 +++--- ...6f115e6ceb931de245d1914a7238a5e1.eprime.essence | 2 +- ...70707c28efe6141f1c5f70cb86a86ffa.eprime.essence | 8 ++++---- ...70729b148e4e70ab38cb319e8c952730.eprime.essence | 6 +++--- ...73472b413e1c687c0430a8719e4f016b.eprime.essence | 4 ++-- ...73595304cbda134ee926997219f68122.eprime.essence | 8 ++++---- ...76e95ca7345ad8108828e20d9116d317.eprime.essence | 8 ++++---- ...77bf93b23c2e5269471d3e07d2d0eff3.eprime.essence | 8 ++++---- ...7813ae28e21e6cf03109291d165d4647.eprime.essence | 8 ++++---- ...7842b5f4c7ad574e4dd5e285a6512004.eprime.essence | 6 +++--- ...788102a4292eb30458166a213f53d06b.eprime.essence | 6 +++--- ...7916e2376c2f7a027a1836f83d31e41f.eprime.essence | 2 +- ...7b0c8abe457f0fb2a4ff0e27c5acc7ef.eprime.essence | 4 ++-- ...7b43b4a26dc012bc58edd762a212c306.eprime.essence | 6 +++--- ...7b5e1f92bb5d4a7807d1d23d112cd92d.eprime.essence | 8 ++++---- .../7c756ce0724280ed59c97a84dd82e7c0.essence | 2 +- ...7c9328a9df7d3971ebc02d3a5d032831.eprime.essence | 6 +++--- ...7cc8838035af5627767687a2a0dd2023.eprime.essence | 6 +++--- ...7eeaf2347f1bf8b83db5d0b7c15483e6.eprime.essence | 8 ++++---- ...7fe2fcf2a860ff56a8cce5c04d1de189.eprime.essence | 8 ++++---- ...818ec086c054d27d412fd647960ada42.eprime.essence | 6 +++--- .../820969cf7025c19eb6a8b65584b5c7ec.essence | 4 ++-- ...827f1d4ebd57ab718caa032cc8b297fc.eprime.essence | 6 +++--- ...8367e8de71de185d6acf3e859e23a37b.eprime.essence | 10 +++++----- ...83e79dafff20cf8bb9bbf4e0e4da6ed2.eprime.essence | 4 ++-- ...851192d3d7c1ec86c1869bb52c0f6640.eprime.essence | 8 ++++---- ...85b8db7be2f6abe894214a12a3d2b71d.eprime.essence | 4 ++-- ...86302603127c6befda9307b173096b8d.eprime.essence | 2 +- ...877d629f542f55f0f97157cd8c1654fe.eprime.essence | 4 ++-- .../87d64817d9031ce1ce57748338fd3be3.essence | 2 +- ...88fb8c6b9616da911eaa4532629f05d7.eprime.essence | 4 ++-- .../890bfc7260b9693bee3681fdd772c9d9.essence | 4 ++-- ...8b18b9af68196441a501019b9212cb97.eprime.essence | 2 +- ...8c6249e4d3029b23653b7f2c74259b87.eprime.essence | 8 ++++---- ...8d24bbf635ac91ecf06f51548f733735.eprime.essence | 8 ++++---- ...8d47dfa1129d0d9a0970aa6e38e36998.eprime.essence | 2 +- ...8e57797389036cafd59682f3b212615f.eprime.essence | 6 +++--- ...8e7aea1c1a683206e6a897c6ad5d8bd3.eprime.essence | 2 +- .../8e93ce71508f064beff9a26d88d989ce.essence | 2 +- ...8f501dda2021fc3c7c4e001157f1e6e6.eprime.essence | 6 +++--- ...90320206b02563fde63fe692179aedbe.eprime.essence | 10 +++++----- ...90955ca420084f220878f52c9a1671bc.eprime.essence | 8 ++++---- ...92e662998492b98daa5a6a0332603ea2.eprime.essence | 2 +- ...93284da4a4bcb0b65f9af4e148349956.eprime.essence | 6 +++--- ...950926788ae00620bf3eefe8cfa83b48.eprime.essence | 6 +++--- ...951d3c18901f9994c032518bb08cd59c.eprime.essence | 4 ++-- ...95673ede51a7abf39744fbcc1b3524b5.eprime.essence | 6 +++--- ...961d1c03df4f6fdf5a4b8bfa8fb85d14.eprime.essence | 12 ++++++------ .../9766d2cb8dbc532f788d40e27b2a738f.essence | 2 +- ...979854a979c1d69c3dc6653f5b2db319.eprime.essence | 2 +- ...9a0d61ffdcb4d471c71fcb70f6ff1232.eprime.essence | 2 +- ...9a180dd7ae58ead0dd9e267df03321f7.eprime.essence | 6 +++--- .../9abdea7380788d3969dc2640d22d213c.essence | 4 ++-- ...9ac3f75c1e13c0710509398532042647.eprime.essence | 4 ++-- ...9b469468a3b10432c0ce1da021333952.eprime.essence | 2 +- ...9c55294c0d3d31ba76c9c8253bef3ef8.eprime.essence | 8 ++++---- ...9cc3198933cb09006cb5dbb960f49f95.eprime.essence | 10 +++++----- ...9d9440d946dd0a2494f8ad0ef44d90e4.eprime.essence | 4 ++-- ...9f0da0c4289dcd010e92c8ab6d50b07a.eprime.essence | 10 +++++----- ...a03ddc28b5f272001ba23db986726a9f.eprime.essence | 4 ++-- ...a09b27e60c42a3e4ab0c27e3826dfc25.eprime.essence | 4 ++-- ...a10653f603b57480444e59a7f67a1eea.eprime.essence | 4 ++-- ...a278490eff4c7aaa3efb73ab7cb5a355.eprime.essence | 4 ++-- ...a29843ebaa6b51bea21d033d0410646e.eprime.essence | 4 ++-- ...a2d859e9768309b9821313f15f257203.eprime.essence | 4 ++-- ...a2d869e1257b1c53d062dbc8e2d442fd.eprime.essence | 2 +- ...a34c8275c1d9524a08d2ec1d329ed35a.eprime.essence | 4 ++-- ...a363b2628f65efb0290c8d10d2a18ac4.eprime.essence | 6 +++--- ...a370966830e4e6e3d5c258cbed1908e2.eprime.essence | 8 ++++---- ...a39552e9ed1bd8481c8c6a692b9a507c.eprime.essence | 6 +++--- ...a569624863aa273c01c6312a624723f1.eprime.essence | 4 ++-- ...a5da41200401440fbed34793aaf4a1f9.eprime.essence | 8 ++++---- ...a5f89c8745074bbbd432690c47cee7e7.eprime.essence | 10 +++++----- ...a5f97387c646309f28161687f8ce5e52.eprime.essence | 4 ++-- ...a6e121cacb3fcfc3686d158963d59199.eprime.essence | 4 ++-- ...a747a06b8ce4f18eaabdc79af95c005f.eprime.essence | 10 +++++----- ...ab828d5a7f3d31d42bf66810cab3da9b.eprime.essence | 6 +++--- ...ac72aae66b512a833a3ec00755c2084d.eprime.essence | 4 ++-- ...ad58de7a6f4b8961d21962c5c1339af3.eprime.essence | 4 ++-- ...ad613a17f3cee2196b552d3d7248765d.eprime.essence | 6 +++--- ...addd14e8dfc91037ec8c416bcefe5a6f.eprime.essence | 6 +++--- ...ae18a4a435dc69d385d04a00db890160.eprime.essence | 8 ++++---- ...af8b7ba49f3da7b43601534cea6c9a52.eprime.essence | 6 +++--- .../aff37a614c45b7cbfad99c7e884ab813.essence | 2 +- ...b0a86f8190115820c0473cbe11e9d73b.eprime.essence | 8 ++++---- ...b0c22716eda56b873b42d632dd725701.eprime.essence | 8 ++++---- ...b20a88a48ca68397fb84abb1ffdfbb20.eprime.essence | 12 ++++++------ .../b38ec6d36aff0c916226635561cbd1a6.essence | 2 +- ...b3e5efec04851a6556b23a0d4a9f50d0.eprime.essence | 4 ++-- ...b427cac47c65e49ff32c22d2b3e8c19b.eprime.essence | 2 +- ...b6716decf75eddda33df3ec06f7cc400.eprime.essence | 4 ++-- ...b68ea8a7e4351cdfc4b3b75bb6582893.eprime.essence | 6 +++--- ...b7ca13696cd34ed7006ef9dfac6d66ff.eprime.essence | 6 +++--- ...b7eff6ada58015f7994346e5ca41950c.eprime.essence | 2 +- ...b97231328d01c59346c93171844928df.eprime.essence | 8 ++++---- ...bbe3f66a50742afbb33589d94d014b78.eprime.essence | 6 +++--- ...be5b5a644521be5b55c6a12c503cad3a.eprime.essence | 10 +++++----- ...bfd00aba95070795c7a808361a3c495d.eprime.essence | 6 +++--- ...c012b856025e2c580aa6d09abc8a939b.eprime.essence | 14 +++++++------- ...c0929bb90fee827dde819c6dacffe4c0.eprime.essence | 8 ++++---- ...c23f30dfa58f7135e9c61ff93975c98d.eprime.essence | 6 +++--- ...c3841e1877c34e8e5bfd1c1837d307e1.eprime.essence | 2 +- ...c423e819384eec3bed63a038add27ca6.eprime.essence | 6 +++--- ...c5272f0460d36d154f10770be9088fa4.eprime.essence | 6 +++--- ...c539dc840839e54f8d3d5ca53104102f.eprime.essence | 2 +- ...c6f07fc1b59d5295892164e99ab6b192.eprime.essence | 8 ++++---- ...c7a05c6406dc0bf72a24b7344bf05115.eprime.essence | 4 ++-- ...c7bab02871b463a4b24d6530e2009c74.eprime.essence | 8 ++++---- ...c863e1aefc22489efd92991f527ae5a2.eprime.essence | 4 ++-- ...c89bdec4acf5b8c9aaaa53cb0cb59f7d.eprime.essence | 8 ++++---- ...c8cbbeb91436bc3cbb6db533e1de1c9f.eprime.essence | 4 ++-- .../c8cc670b809293626467998d149a92ca.essence | 2 +- ...c96d788458c4c7e3247f608a018776aa.eprime.essence | 6 +++--- ...c9e1cd7a71dc9c900ce717378a2e7326.eprime.essence | 2 +- ...cad537c995fb03554a83b3fb49b715bc.eprime.essence | 2 +- .../cc2192ed7f68debf33abcbf2de08eff2.essence | 2 +- ...d1f9f5646ad02f51e81ccd962c936011.eprime.essence | 6 +++--- ...d1ffc6dc30ae73ba44e3f9c55d3e1636.eprime.essence | 6 +++--- ...d20ff5e630ee919f1fcc726ea14f1e21.eprime.essence | 8 ++++---- ...d2d4b6dd1eb76f25c117fe82249925fb.eprime.essence | 6 +++--- ...d3909eeb253333c473b61058dd67f690.eprime.essence | 6 +++--- ...d548102740c166c94c1585976df85834.eprime.essence | 8 ++++---- ...d563cbf2c040240a470a21faf1f336cb.eprime.essence | 4 ++-- ...d6b3494aaacb9f588de0875051f0040c.eprime.essence | 2 +- ...d75b01e01b11eb07e4bc4fbd71ce3b5e.eprime.essence | 2 +- ...d7d816b10a6f459ed78f1bd604bca06f.eprime.essence | 4 ++-- ...d89a06ed8f4ec8185046a435ad85ca8c.eprime.essence | 4 ++-- ...d92076e69308eb50f5eb562d89a97d2e.eprime.essence | 4 ++-- ...da2dd87b9830b0d92b6148601757e71f.eprime.essence | 8 ++++---- ...dad7b9b0bdd9e288f1dc3b19ec96c213.eprime.essence | 10 +++++----- ...dbc08914b7c5505e1136cc21ac9d5125.eprime.essence | 6 +++--- ...de9716a7ff65a1574f48f0b1858be3bd.eprime.essence | 4 ++-- ...de98c56929c67f420c29fa2f74d46c69.eprime.essence | 2 +- ...dec056eee47fd05a251225b16b62ab64.eprime.essence | 8 ++++---- ...e02f77cea3324e91d885d1f3fe504cd4.eprime.essence | 4 ++-- ...e0bb089c7844a06fba3ed1abd7cb6608.eprime.essence | 4 ++-- ...e1aecd4c14589221e87e2ec00b232d51.eprime.essence | 2 +- ...e21cd7b0f710515a79d787945d809a81.eprime.essence | 6 +++--- ...e31e8258961a4a8fa32e4eb491491bdc.eprime.essence | 6 +++--- .../e33c5a4b1eca296873386a312774d872.essence | 2 +- ...e5c113460990fde26723d11aa27cbea5.eprime.essence | 8 ++++---- ...e5ef686faac39c34b542eec223509aa8.eprime.essence | 4 ++-- ...e65878a75f8a723504c5189d62b6f391.eprime.essence | 4 ++-- ...e6d35b55e35082d3fa2dd4068f7ebfdf.eprime.essence | 6 +++--- ...e7a6d29d4285dcfdd7daddc00be2c882.eprime.essence | 6 +++--- ...e7f89fcbcdbd0a79caefef0e87678c8d.eprime.essence | 8 ++++---- .../e8b367599a5f7fcb2e355134b78bc13f.essence | 4 ++-- ...e94042e71ae4aca4b2dcbe6a1c03eeb5.eprime.essence | 2 +- ...e94f81e31dce6a8efb7cdffe25cc7a9a.eprime.essence | 8 ++++---- ...eaa45321fa09e5ac7b722523a615feba.eprime.essence | 6 +++--- .../eb0e88cd958943e2e87a5ade86710827.essence | 2 +- ...eb22d7172ced999f8568dccf4a1a3d94.eprime.essence | 6 +++--- ...eb5e229a3045349ef118229f11ede50b.eprime.essence | 4 ++-- ...ec9aed752e5eeb363b644516fc85dd8f.eprime.essence | 2 +- ...ed0e6ab88e79cb8c6c179357811e4b33.eprime.essence | 4 ++-- ...ed529213e4789b79a6929c96d89b6eb2.eprime.essence | 2 +- ...ed6e2ac3457110fd811f7f6066338883.eprime.essence | 4 ++-- ...edeee104245da0f75d4b86e7146e073f.eprime.essence | 6 +++--- ...ee0f4f29b6fcae0b8a1a80540fff7469.eprime.essence | 4 ++-- ...eebf57c0e408c9d7b113317d714541bf.eprime.essence | 6 +++--- ...eee79bab97319cb6a1cfb2a945bcc1a6.eprime.essence | 6 +++--- ...ef336eba26eb0a9a90de40b18d840b84.eprime.essence | 4 ++-- .../ef47512eb208c3dc333c0f019cdd3b41.essence | 4 ++-- .../f0da1b32d64901550697edd2a56acbb1.essence | 2 +- ...f0fc2fcf48b2784adbc82bebe8debe1d.eprime.essence | 4 ++-- .../f11a6d1a6b6ea819dc5ab8227c9c909d.essence | 2 +- .../f17b4b0018354dbb3657f42a48ff8c38.essence | 2 +- ...f1fd537fecc6c852b01a571e701d7e59.eprime.essence | 4 ++-- .../f243bccb3b210797782c1c047cbf7643.essence | 2 +- ...f2d8a670b4c34d59079378000ca2e898.eprime.essence | 6 +++--- ...f2f725a26126338e19e3f08ef990f1da.eprime.essence | 10 +++++----- ...f3b4b055e266a994218c9c7c4772d7db.eprime.essence | 8 ++++---- ...f41a286594c108909b183b37074c3e76.eprime.essence | 6 +++--- ...f42851729ee7b455bb9015d9c3e76513.eprime.essence | 8 ++++---- .../f5650f709d784157b7cac1ee24385d89.essence | 2 +- ...f57b3d11bf42b1452c009a9c008864fd.eprime.essence | 2 +- ...f5e0dd3dd1ecaf45dc4127467fcbd4dd.eprime.essence | 6 +++--- ...f6f3227d62d29091577943cbcc8b7b7f.eprime.essence | 4 ++-- ...f7faf3149f0cc222402ea4da0e2865f1.eprime.essence | 8 ++++---- ...f82a4527f67eca4c2d17cab8c2c8925c.eprime.essence | 2 +- .../f8551d2ded7dfbb7f4fc2fefcfe32146.essence | 2 +- ...fbfe220f5450d8f205a3e3e9ec02f054.eprime.essence | 2 +- ...fe7777e1ad2badafc794d13da8eddcf4.eprime.essence | 10 +++++----- ...ff226931c79ca27e68e71f211b4aa84e.eprime.essence | 8 ++++---- .../autogen/319~1435138340_66/spec.essence | 2 +- .../autogen/321~1435140010_44/spec.essence | 2 +- .../autogen/447~1435213364_36/spec.essence | 2 +- .../autogen/605~1436581770_45/spec.essence | 2 +- .../autogen/613~1436580506_52/spec.essence | 2 +- 318 files changed, 783 insertions(+), 781 deletions(-) create mode 100644 .MINIONSOLS_1557920204186_7093 create mode 100644 .MINIONSTATS_1557920204186_7093 diff --git a/.MINIONSOLS_1557920204186_7093 b/.MINIONSOLS_1557920204186_7093 new file mode 100644 index 0000000000..e69de29bb2 diff --git a/.MINIONSTATS_1557920204186_7093 b/.MINIONSTATS_1557920204186_7093 new file mode 100644 index 0000000000..c41c1cd0f3 --- /dev/null +++ b/.MINIONSTATS_1557920204186_7093 @@ -0,0 +1,2 @@ +#"CommandLineArguments" "Filename" "InitialPropagate" "MinionVersion" "Nodes" "ParsingTime" "Preprocess" "PreprocessTime" "RandomSeed" "Satisfiable" "SearchOrderTime" "SetupTime" "SolutionsFound" "SolveTime" "TimeOut" "TotalTime" +tests/exhaustive/autogen/gen38/outputs/model.eprime-minion,-printsolsonly,-preprocess,None,-tableout,.MINIONSTATS_1557920204186_7093,-solsout,.MINIONSOLS_1557920204186_7093,-noprintsols,-findallsols tests/exhaustive/autogen/gen38/outputs/model.eprime-minion 9e-06 -1 0 0.000424 none 4e-06 1557914234 0 4.9e-05 5.8e-05 0 5e-06 0 0.000548 diff --git a/etc/testdata/specs/matrixes.essence b/etc/testdata/specs/matrixes.essence index 7ae361b641..2d433e2ae0 100644 --- a/etc/testdata/specs/matrixes.essence +++ b/etc/testdata/specs/matrixes.essence @@ -4,4 +4,4 @@ find x : matrix indexed by [int(1..2)] of (int(3,5), int(6,7)) such that x[1][1] = 3, x[2] = (5,7), - x[1][2] = 6, \ No newline at end of file + x[1][2] = 6, diff --git a/etc/testdata/specs/matrixes2.essence b/etc/testdata/specs/matrixes2.essence index fa83aa006c..2ea6902ce2 100644 --- a/etc/testdata/specs/matrixes2.essence +++ b/etc/testdata/specs/matrixes2.essence @@ -3,4 +3,4 @@ language Essence 2.0 find x : matrix indexed by [int(1..2)] of set(minSize 1) of int(6..8) such that x[1] = {6}, - x[2] = {7,8} \ No newline at end of file + x[2] = {7,8} diff --git a/etc/testdata/specs/n3.essence b/etc/testdata/specs/n3.essence index dae22b183b..88c40e7399 100644 --- a/etc/testdata/specs/n3.essence +++ b/etc/testdata/specs/n3.essence @@ -4,4 +4,4 @@ find x : set (minSize 1) of set (minSize 1) of int(1..1) find n : int(1..1) such that - forAll i in x . forAll j in i . j =1 \ No newline at end of file + forAll i in x . forAll j in i . j =1 diff --git a/etc/testdata/specs/set-of-lettings.essence b/etc/testdata/specs/set-of-lettings.essence index 3e070ae571..fffc4e0feb 100644 --- a/etc/testdata/specs/set-of-lettings.essence +++ b/etc/testdata/specs/set-of-lettings.essence @@ -10,4 +10,4 @@ find y : CC such that (2,3,4) in x, - (1,{3}) in y \ No newline at end of file + (1,{3}) in y diff --git a/etc/upTests/___simple/matrixes_of_tuples.essence b/etc/upTests/___simple/matrixes_of_tuples.essence index 7ae361b641..2d433e2ae0 100644 --- a/etc/upTests/___simple/matrixes_of_tuples.essence +++ b/etc/upTests/___simple/matrixes_of_tuples.essence @@ -4,4 +4,4 @@ find x : matrix indexed by [int(1..2)] of (int(3,5), int(6,7)) such that x[1][1] = 3, x[2] = (5,7), - x[1][2] = 6, \ No newline at end of file + x[1][2] = 6, diff --git a/etc/upTests/_matrix_of_tuples/different.essence b/etc/upTests/_matrix_of_tuples/different.essence index c6da947ecb..874dc75ebf 100644 --- a/etc/upTests/_matrix_of_tuples/different.essence +++ b/etc/upTests/_matrix_of_tuples/different.essence @@ -4,4 +4,4 @@ find x : matrix indexed by [int(1..2)] of (int(3,5), int(6,7)) such that x[1][1] = 3, x[2] = (5,7), - x[1][2] = 6, \ No newline at end of file + x[1][2] = 6, diff --git a/etc/upTests/matrixes2.essence b/etc/upTests/matrixes2.essence index fa83aa006c..2ea6902ce2 100644 --- a/etc/upTests/matrixes2.essence +++ b/etc/upTests/matrixes2.essence @@ -3,4 +3,4 @@ language Essence 2.0 find x : matrix indexed by [int(1..2)] of set(minSize 1) of int(6..8) such that x[1] = {6}, - x[2] = {7,8} \ No newline at end of file + x[2] = {7,8} diff --git a/tests/custom/basic/solutionsInOneFile/test.essence b/tests/custom/basic/solutionsInOneFile/test.essence index 37e14b9b5a..fd9ed31c1e 100644 --- a/tests/custom/basic/solutionsInOneFile/test.essence +++ b/tests/custom/basic/solutionsInOneFile/test.essence @@ -1 +1 @@ -find s : set of int(1..3) \ No newline at end of file +find s : set of int(1..3) diff --git a/tests/custom/permutations/21_set_comprehension/set_comprehension.essence b/tests/custom/permutations/21_set_comprehension/set_comprehension.essence index 72947ffaa9..00aa724da1 100644 --- a/tests/custom/permutations/21_set_comprehension/set_comprehension.essence +++ b/tests/custom/permutations/21_set_comprehension/set_comprehension.essence @@ -1,4 +1,4 @@ find s : set (minSize 2) of set (minSize 2) of int(1..3) letting p be permutation((1,2,3)) such that - [i | i <- s] .<= [i | i <- s] \ No newline at end of file + [i | i <- s] .<= [i | i <- s] diff --git a/tests/exhaustive/autogen/gen02/gen02.essence b/tests/exhaustive/autogen/gen02/gen02.essence index 1246a5e92a..c76cbb51e1 100644 --- a/tests/exhaustive/autogen/gen02/gen02.essence +++ b/tests/exhaustive/autogen/gen02/gen02.essence @@ -1,4 +1,4 @@ language Essence 1.3 find var2: set of set of bool -such that exists q_4 in var2 , |q_4| >= -7 . true \ No newline at end of file +such that exists q_4 in var2 , |q_4| >= -7 . true diff --git a/tests/exhaustive/autogen/gen38/gen38.essence b/tests/exhaustive/autogen/gen38/gen38.essence index 129cf433d7..6446f40a61 100644 --- a/tests/exhaustive/autogen/gen38/gen38.essence +++ b/tests/exhaustive/autogen/gen38/gen38.essence @@ -13,4 +13,4 @@ or([{ 5 = aux9 or([x[q47] > 0 /\ y[q47] = aux9 | q47 : int(1..15)]) - } | true]) \ No newline at end of file + } | true]) diff --git a/tests/exhaustive/issues/236/langfords.essence b/tests/exhaustive/issues/236/langfords.essence index 095a426f39..650996dc6e 100644 --- a/tests/exhaustive/issues/236/langfords.essence +++ b/tests/exhaustive/issues/236/langfords.essence @@ -13,4 +13,4 @@ find seq : function (total, surjective) seqIndex --> int(1..n) such that forAll i,j : seqIndex , i < j . seq(i) = seq(j) -> seq(i) = j - i - 1 - \ No newline at end of file + diff --git a/tests/parse_print/autogen-bilals-fixed/00f3f6e00d6aaa0c44f7a7bfaeabf301/00f3f6e00d6aaa0c44f7a7bfaeabf301.eprime.essence b/tests/parse_print/autogen-bilals-fixed/00f3f6e00d6aaa0c44f7a7bfaeabf301/00f3f6e00d6aaa0c44f7a7bfaeabf301.eprime.essence index 8fde15690a..3a47ad6b98 100644 --- a/tests/parse_print/autogen-bilals-fixed/00f3f6e00d6aaa0c44f7a7bfaeabf301/00f3f6e00d6aaa0c44f7a7bfaeabf301.eprime.essence +++ b/tests/parse_print/autogen-bilals-fixed/00f3f6e00d6aaa0c44f7a7bfaeabf301/00f3f6e00d6aaa0c44f7a7bfaeabf301.eprime.essence @@ -98,7 +98,7 @@ such that (flatten(var1_PartitionAsSet_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMarker_Values_Function1DPartial_Flags[q5, .., ..]) - matrix indexed by [int] of int`), mset(false)) diff --git a/tests/parse_print/autogen-bilals-fixed/075527221a657e78d6f1c0a6a335371f/075527221a657e78d6f1c0a6a335371f.eprime.essence b/tests/parse_print/autogen-bilals-fixed/075527221a657e78d6f1c0a6a335371f/075527221a657e78d6f1c0a6a335371f.eprime.essence index 5a725961aa..fb4cfc5624 100644 --- a/tests/parse_print/autogen-bilals-fixed/075527221a657e78d6f1c0a6a335371f/075527221a657e78d6f1c0a6a335371f.eprime.essence +++ b/tests/parse_print/autogen-bilals-fixed/075527221a657e78d6f1c0a6a335371f/075527221a657e78d6f1c0a6a335371f.eprime.essence @@ -12,7 +12,7 @@ such that -> var1_FunctionAsRelation_RelationAsSet_ExplicitVarSizeWithMarker_Values_1_Occurrence[q1, ..] - - var1_ExplicitVarSizeWithMarker_Values_Function1D[q1, ..] var1_ExplicitVarSizeWithMarker_Marker -> @@ -64,7 +64,7 @@ such that and([q10 + 1 <= var2_PartitionAsSet_ExplicitVarSizeWithMarker_Marker -> flatten(var2_PartitionAsSet_ExplicitVarSizeWithMarker_Values_Explicit_ExplicitVarSizeWithFlags_Flags[q10, .., ..]) - - q_4_ExplicitVarSizeWithMarker_Values_Function1DPartial_Flags[q1, ..] q_4_ExplicitVarSizeWithMarker_Marker -> @@ -71,7 +71,7 @@ such that /\ var1_PartitionAsSet_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMarker_Values[q3, ..] - - var2_ExplicitVarSizeWithFlags_Values_Function1DPartial_Flags[q5, ..] diff --git a/tests/parse_print/autogen-bilals-fixed/0896777a9c9ec7a2944d17b0f832af27/0896777a9c9ec7a2944d17b0f832af27.eprime.essence b/tests/parse_print/autogen-bilals-fixed/0896777a9c9ec7a2944d17b0f832af27/0896777a9c9ec7a2944d17b0f832af27.eprime.essence index edd2e65dab..e1f8897550 100644 --- a/tests/parse_print/autogen-bilals-fixed/0896777a9c9ec7a2944d17b0f832af27/0896777a9c9ec7a2944d17b0f832af27.eprime.essence +++ b/tests/parse_print/autogen-bilals-fixed/0896777a9c9ec7a2944d17b0f832af27/0896777a9c9ec7a2944d17b0f832af27.eprime.essence @@ -109,7 +109,7 @@ such that (flatten(var4_PartitionAsSet_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMarker_Values_Function1DPartial_Flags[q8, .., ..]) - = 1 | q31 : int(1..2)]), 2 <= var6_PartitionAsSet_ExplicitVarSizeWithMarker_Marker -> - var6_PartitionAsSet_ExplicitVarSizeWithMarker_Values_Occurrence[1, ..] var6_PartitionAsSet_ExplicitVarSizeWithMarker_Marker -> var6_PartitionAsSet_ExplicitVarSizeWithMarker_Values_Occurrence[q22, 2] = false diff --git a/tests/parse_print/autogen-bilals-fixed/09ac2051b1e1a54e1b7a3b051b78bcd3/09ac2051b1e1a54e1b7a3b051b78bcd3.essence b/tests/parse_print/autogen-bilals-fixed/09ac2051b1e1a54e1b7a3b051b78bcd3/09ac2051b1e1a54e1b7a3b051b78bcd3.essence index 110e08a9da..7637faaa7d 100644 --- a/tests/parse_print/autogen-bilals-fixed/09ac2051b1e1a54e1b7a3b051b78bcd3/09ac2051b1e1a54e1b7a3b051b78bcd3.essence +++ b/tests/parse_print/autogen-bilals-fixed/09ac2051b1e1a54e1b7a3b051b78bcd3/09ac2051b1e1a54e1b7a3b051b78bcd3.essence @@ -3,4 +3,4 @@ language Essence 1.3 find var1: bool such that [var1, var1, true, var1, false; int(10, 2..5)][toInt(var1)], - [false, false, true; int(1..3)] <=lex [var1, var1, false; int(9, 7, 5..5)] + [false, false, true; int(1..3)] .<= [var1, var1, false; int(9, 7, 5..5)] diff --git a/tests/parse_print/autogen-bilals-fixed/0a4c5d1f2a6f82e1a72b0732362906b6/0a4c5d1f2a6f82e1a72b0732362906b6.eprime.essence b/tests/parse_print/autogen-bilals-fixed/0a4c5d1f2a6f82e1a72b0732362906b6/0a4c5d1f2a6f82e1a72b0732362906b6.eprime.essence index 3a952ac73f..d3d9816c06 100644 --- a/tests/parse_print/autogen-bilals-fixed/0a4c5d1f2a6f82e1a72b0732362906b6/0a4c5d1f2a6f82e1a72b0732362906b6.eprime.essence +++ b/tests/parse_print/autogen-bilals-fixed/0a4c5d1f2a6f82e1a72b0732362906b6/0a4c5d1f2a6f82e1a72b0732362906b6.eprime.essence @@ -47,7 +47,7 @@ such that and([q4 + 1 <= var2_PartitionAsSet_ExplicitVarSizeWithMarker_Marker -> flatten(var2_PartitionAsSet_ExplicitVarSizeWithMarker_Values_Explicit_ExplicitVarSizeWithFlags_Flags[q4, .., ..]) - @@ -33,10 +33,10 @@ such that | q23 : int(1..2)]) | q21 : int(1..2)]) /\ - (var1_RelationAsSet_Explicit_2_ExplicitVarSizeWithFlags_Flags[1, ..] var1_RelationAsSet_Explicit_1_ExplicitVarSizeWithFlags_Values[q2, 1] < diff --git a/tests/parse_print/autogen-bilals-fixed/0d757bbc1bf600cc00cccc23dd0dbabb/0d757bbc1bf600cc00cccc23dd0dbabb.eprime.essence b/tests/parse_print/autogen-bilals-fixed/0d757bbc1bf600cc00cccc23dd0dbabb/0d757bbc1bf600cc00cccc23dd0dbabb.eprime.essence index 8446df43f6..82d66376cb 100644 --- a/tests/parse_print/autogen-bilals-fixed/0d757bbc1bf600cc00cccc23dd0dbabb/0d757bbc1bf600cc00cccc23dd0dbabb.eprime.essence +++ b/tests/parse_print/autogen-bilals-fixed/0d757bbc1bf600cc00cccc23dd0dbabb/0d757bbc1bf600cc00cccc23dd0dbabb.eprime.essence @@ -14,21 +14,21 @@ such that -> var2_FunctionAsRelation_RelationAsSet_ExplicitVarSizeWithMarker_Values_1_ExplicitVarSizeWithFlags_Flags[q1, ..] - var1_FunctionAsRelation_RelationAsSet_ExplicitVarSizeWithMarker_Values_1_ExplicitVarSizeWithFlags_Flags[q1, ..] - flatten(var1_ExplicitVarSizeWithFlags_Values_RelationAsSet_Explicit_1_RelationAsSet_Explicit_1[q1, .., ..]) - and([var1_ExplicitVarSizeWithFlags_Values_RelationAsSet_Explicit_1_RelationAsSet_Explicit_1[q5, q6, ..] - = 1, and([q8 + 1 <= var1_PartitionAsSet_ExplicitR5_ExplicitVarSizeWithMarker_Marker[1] -> - var1_PartitionAsSet_ExplicitR5_ExplicitVarSizeWithMarker_Values[1, q8, ..] var1_PartitionAsSet_ExplicitR5_ExplicitVarSizeWithMarker_Marker[1] -> @@ -36,14 +36,14 @@ such that | q9 : int(1..24)]), var1_PartitionAsSet_ExplicitR5_ExplicitVarSizeWithMarker_Marker[1] <= 24, and([q13 + 1 <= var2_ExplicitVarSizeWithMarkerR10_Marker -> - var2_ExplicitVarSizeWithMarkerR10_Values_Function1DPartial_Flags[q13, ..] var2_ExplicitVarSizeWithMarkerR10_Marker -> @@ -85,7 +85,7 @@ such that var4_1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q34] = var4_1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q34 + 1] /\ - var4_1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q34, ..] var4_1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> diff --git a/tests/parse_print/autogen-bilals-fixed/1291155001a2b89117838f7032c4ab5e/1291155001a2b89117838f7032c4ab5e.eprime.essence b/tests/parse_print/autogen-bilals-fixed/1291155001a2b89117838f7032c4ab5e/1291155001a2b89117838f7032c4ab5e.eprime.essence index 4bd26a7b2c..944640e5a3 100644 --- a/tests/parse_print/autogen-bilals-fixed/1291155001a2b89117838f7032c4ab5e/1291155001a2b89117838f7032c4ab5e.eprime.essence +++ b/tests/parse_print/autogen-bilals-fixed/1291155001a2b89117838f7032c4ab5e/1291155001a2b89117838f7032c4ab5e.eprime.essence @@ -94,7 +94,7 @@ such that var2_1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q7] = var2_1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q7 + 1] /\ - var2_1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q7, ..] var2_1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> @@ -123,14 +123,14 @@ such that and([var4_1_ExplicitWithFlags_Flags[q17] = 0 \/ var4_1_ExplicitWithFlags_Flags[q17] >= 0 | q17 : int(1..3)]), 3 = sum([var4_1_ExplicitWithFlags_Flags[q18] | q18 : int(1..3)]), and([var5_ExplicitWithFlagsR10_Flags[q20 + 1] > 0 -> - var5_ExplicitWithFlagsR10_Values_Function1DPartial_Flags[q20, ..] diff --git a/tests/parse_print/autogen-bilals-fixed/13700d10e259531c00b3ea61a5a5222e/13700d10e259531c00b3ea61a5a5222e.eprime.essence b/tests/parse_print/autogen-bilals-fixed/13700d10e259531c00b3ea61a5a5222e/13700d10e259531c00b3ea61a5a5222e.eprime.essence index 5294a94159..9d657c18e0 100644 --- a/tests/parse_print/autogen-bilals-fixed/13700d10e259531c00b3ea61a5a5222e/13700d10e259531c00b3ea61a5a5222e.eprime.essence +++ b/tests/parse_print/autogen-bilals-fixed/13700d10e259531c00b3ea61a5a5222e/13700d10e259531c00b3ea61a5a5222e.eprime.essence @@ -27,7 +27,7 @@ find var5_PartitionAsSet_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMar find var6: int(-1..1) such that and([q1 + 1 <= var2_RelationAsSet_ExplicitVarSizeWithMarker_Marker -> - var2_RelationAsSet_ExplicitVarSizeWithMarker_Values_1_Occurrence[q1, ..] var1_FunctionAsRelation_RelationAsSet_ExplicitVarSizeWithMarker_Values_1_Occurrence[q1, ..] - var1_FunctionAsRelation_RelationAsSet_ExplicitVarSizeWithMarker_Values_1_Function1DPartial_Flags[q1, ..] - var5_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Marker[q10] < @@ -24,7 +24,7 @@ such that var5_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Marker[q10] = var5_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Marker[q10 + 1] /\ - var5_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Values[q10, ..] diff --git a/tests/parse_print/autogen-bilals-fixed/176498a86f4f6aa56d13e84f835917e5/176498a86f4f6aa56d13e84f835917e5.eprime.essence b/tests/parse_print/autogen-bilals-fixed/176498a86f4f6aa56d13e84f835917e5/176498a86f4f6aa56d13e84f835917e5.eprime.essence index d0ca28d2d0..3c9c987ec3 100644 --- a/tests/parse_print/autogen-bilals-fixed/176498a86f4f6aa56d13e84f835917e5/176498a86f4f6aa56d13e84f835917e5.eprime.essence +++ b/tests/parse_print/autogen-bilals-fixed/176498a86f4f6aa56d13e84f835917e5/176498a86f4f6aa56d13e84f835917e5.eprime.essence @@ -25,7 +25,7 @@ such that /\ var1_FunctionAsRelation_RelationAsSet_ExplicitVarSizeWithMarker_Values_1_ExplicitVarSizeWithMarker_Values[q1, ..] - [0, 3, 1; int(4, 3, 6..6)], mset(true) --> [3; int(2..2)], mset(false, false, false) --> [5, 2, 0; int(1, 7..8)]), (mset() : `mset of bool`)) - <=lex + .<= image(function(relation((true, 2), (false, 2), (false, 3)) --> [3, 2, 2, 0, 4; int(11, 2, 5..7)], relation((true, 0), (false, 4)) --> [0; int(0..0)], diff --git a/tests/parse_print/autogen-bilals-fixed/18bf9a38ee59e4bcaebd478b9f980662/18bf9a38ee59e4bcaebd478b9f980662.eprime.essence b/tests/parse_print/autogen-bilals-fixed/18bf9a38ee59e4bcaebd478b9f980662/18bf9a38ee59e4bcaebd478b9f980662.eprime.essence index c364f271cd..2baa1c7dbd 100644 --- a/tests/parse_print/autogen-bilals-fixed/18bf9a38ee59e4bcaebd478b9f980662/18bf9a38ee59e4bcaebd478b9f980662.eprime.essence +++ b/tests/parse_print/autogen-bilals-fixed/18bf9a38ee59e4bcaebd478b9f980662/18bf9a38ee59e4bcaebd478b9f980662.eprime.essence @@ -25,7 +25,7 @@ such that /\ var1_FunctionAsRelation_RelationAsSet_ExplicitVarSizeWithMarker_Values_1_ExplicitVarSizeWithMarker_Values[q1, ..] - [0, 1, 0; int(3, 5, 1..1)], (mset() : `mset of int`) --> [1, 4; int(5, 0..0)], mset(1, 5, 2) --> [4, 4, 2, 4, 1; int(8..10, 4, 14..14)]), toMSet({0, 1})) - <=lex [l_3 | l_2 : int(0..3, 5), l_3 : int(5..5, 4)], + .<= [l_3 | l_2 : int(0..3, 5), l_3 : int(5..5, 4)], true, or([l_4 | l_4 : bool, l_5 : bool, l_4]), mset(mset([2, 1, 3, 5, 4; int(0, 2..3, 15, 4..4)], [1, 1, 5, 1, 4; int(2..6)], diff --git a/tests/parse_print/autogen-bilals-fixed/1abb07c9ef975b96bf575bfbe8f442b5/1abb07c9ef975b96bf575bfbe8f442b5.eprime.essence b/tests/parse_print/autogen-bilals-fixed/1abb07c9ef975b96bf575bfbe8f442b5/1abb07c9ef975b96bf575bfbe8f442b5.eprime.essence index ad92e53ff7..e925596a4b 100644 --- a/tests/parse_print/autogen-bilals-fixed/1abb07c9ef975b96bf575bfbe8f442b5/1abb07c9ef975b96bf575bfbe8f442b5.eprime.essence +++ b/tests/parse_print/autogen-bilals-fixed/1abb07c9ef975b96bf575bfbe8f442b5/1abb07c9ef975b96bf575bfbe8f442b5.eprime.essence @@ -21,7 +21,7 @@ such that >= 1 | q19 : int(1..16)]), and([q9 + 1 <= var3_PartitionAsSet_ExplicitVarSizeWithMarker_Marker -> - var3_PartitionAsSet_ExplicitVarSizeWithMarker_Values_Occurrence[q9, ..] var3_PartitionAsSet_ExplicitVarSizeWithMarker_Marker -> diff --git a/tests/parse_print/autogen-bilals-fixed/1b6c1179b1a92bd88edaeed5c5bfb398/1b6c1179b1a92bd88edaeed5c5bfb398.eprime.essence b/tests/parse_print/autogen-bilals-fixed/1b6c1179b1a92bd88edaeed5c5bfb398/1b6c1179b1a92bd88edaeed5c5bfb398.eprime.essence index 4e5600d550..cac510ffa2 100644 --- a/tests/parse_print/autogen-bilals-fixed/1b6c1179b1a92bd88edaeed5c5bfb398/1b6c1179b1a92bd88edaeed5c5bfb398.eprime.essence +++ b/tests/parse_print/autogen-bilals-fixed/1b6c1179b1a92bd88edaeed5c5bfb398/1b6c1179b1a92bd88edaeed5c5bfb398.eprime.essence @@ -28,7 +28,7 @@ such that /\ flatten(var2_PartitionAsSetR6_ExplicitVarSizeWithMarkerR5R6_Values_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy [q4, .., ..]) - = 1 | q53 : int(1..4)]), and([q7 + 1 <= var2_1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - var2_1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q7, ..] var2_1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> @@ -114,14 +114,14 @@ such that and([var4_1_ExplicitWithFlags_Flags[q18] = 0 \/ var4_1_ExplicitWithFlags_Flags[q18] >= 0 | q18 : int(1..3)]), 3 = sum([var4_1_ExplicitWithFlags_Flags[q19] | q19 : int(1..3)]), and([q21 + 1 <= var5_ExplicitWithRepetitionR10_Flag -> - var5_ExplicitWithRepetitionR10_Values_Function1DPartial_Flags[q21, ..] var5_ExplicitWithRepetitionR10_Flag -> diff --git a/tests/parse_print/autogen-bilals-fixed/1e3c2ea5eb1b0a1eb092e59c73e21e65/1e3c2ea5eb1b0a1eb092e59c73e21e65.eprime.essence b/tests/parse_print/autogen-bilals-fixed/1e3c2ea5eb1b0a1eb092e59c73e21e65/1e3c2ea5eb1b0a1eb092e59c73e21e65.eprime.essence index 7a5041412f..c1d0a9e67d 100644 --- a/tests/parse_print/autogen-bilals-fixed/1e3c2ea5eb1b0a1eb092e59c73e21e65/1e3c2ea5eb1b0a1eb092e59c73e21e65.eprime.essence +++ b/tests/parse_print/autogen-bilals-fixed/1e3c2ea5eb1b0a1eb092e59c73e21e65/1e3c2ea5eb1b0a1eb092e59c73e21e65.eprime.essence @@ -27,7 +27,7 @@ such that var1_PartitionAsSet_ExplicitR5_ExplicitVarSizeWithMarker_Marker[1], var1_PartitionAsSet_ExplicitR5_ExplicitVarSizeWithMarker_Marker[1] >= 1, and([q8 + 1 <= var1_PartitionAsSet_ExplicitR5_ExplicitVarSizeWithMarker_Marker[1] -> - var1_PartitionAsSet_ExplicitR5_ExplicitVarSizeWithMarker_Values[1, q8, ..] var1_PartitionAsSet_ExplicitR5_ExplicitVarSizeWithMarker_Marker[1] -> @@ -35,14 +35,14 @@ such that | q9 : int(1..24)]), var1_PartitionAsSet_ExplicitR5_ExplicitVarSizeWithMarker_Marker[1] <= 24, and([var2_ExplicitVarSizeWithFlagsR10_Flags[q13 + 1] -> - var2_ExplicitVarSizeWithFlagsR10_Values_Function1DPartial_Flags[q13, ..] diff --git a/tests/parse_print/autogen-bilals-fixed/200d78834a42ebeb6f12a80d41000004/200d78834a42ebeb6f12a80d41000004.eprime.essence b/tests/parse_print/autogen-bilals-fixed/200d78834a42ebeb6f12a80d41000004/200d78834a42ebeb6f12a80d41000004.eprime.essence index 641d404193..bb36f9f85f 100644 --- a/tests/parse_print/autogen-bilals-fixed/200d78834a42ebeb6f12a80d41000004/200d78834a42ebeb6f12a80d41000004.eprime.essence +++ b/tests/parse_print/autogen-bilals-fixed/200d78834a42ebeb6f12a80d41000004/200d78834a42ebeb6f12a80d41000004.eprime.essence @@ -75,7 +75,7 @@ such that 1 <= var1_PartitionAsSet_ExplicitVarSizeWithMarker_Marker -> and([var1_PartitionAsSet_ExplicitVarSizeWithMarker_Values_Explicit_ExplicitVarSizeWithFlags_Flags[1, q9, ..] - = 0 | l_4 : bool, l_5 : bool], ([] : `matrix indexed by [int] of relation of (matrix indexed by [int] of bool * partition from bool * mset of bool)`)), diff --git a/tests/parse_print/autogen-bilals-fixed/21be920dffbaacd7e2b6b06b72cb75c0/21be920dffbaacd7e2b6b06b72cb75c0.essence b/tests/parse_print/autogen-bilals-fixed/21be920dffbaacd7e2b6b06b72cb75c0/21be920dffbaacd7e2b6b06b72cb75c0.essence index 36a95c6de1..ec01a524ef 100644 --- a/tests/parse_print/autogen-bilals-fixed/21be920dffbaacd7e2b6b06b72cb75c0/21be920dffbaacd7e2b6b06b72cb75c0.essence +++ b/tests/parse_print/autogen-bilals-fixed/21be920dffbaacd7e2b6b06b72cb75c0/21be920dffbaacd7e2b6b06b72cb75c0.essence @@ -80,6 +80,6 @@ such that (0, false, 5, 5) --> mset(2, 0, 4), (2, true, 0, 1) --> (mset() : `mset of int`)))), or([l_2 | l_1 : bool, l_2 : bool, l_2, l_2]), - [l_4 | l_3 : int(3..3, 5..5), l_4 : int(1..2, 3..3)] and([var1_PartitionAsSet_ExplicitVarSizeWithMarker_Values_Explicit_ExplicitVarSizeWithFlags_Flags[1, q9, ..] - flatten(var2_PartitionAsSet_ExplicitVarSizeWithMarker_Values_Explicit_Occurrence[q4, .., ..]) - var1_FunctionAsRelation_RelationAsSet_ExplicitVarSizeWithMarker_Values_1_Occurrence[q1, ..] - var1_PartitionAsSet_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMarker_Values_Occurrence[q8, q9, ..] - [0; int(1..1)]), relation((false, 4))) diff --git a/tests/parse_print/autogen-bilals-fixed/2910579caa938519c953fccd48611fee/2910579caa938519c953fccd48611fee.eprime.essence b/tests/parse_print/autogen-bilals-fixed/2910579caa938519c953fccd48611fee/2910579caa938519c953fccd48611fee.eprime.essence index d8018b9dad..6ddfc59ea6 100644 --- a/tests/parse_print/autogen-bilals-fixed/2910579caa938519c953fccd48611fee/2910579caa938519c953fccd48611fee.eprime.essence +++ b/tests/parse_print/autogen-bilals-fixed/2910579caa938519c953fccd48611fee/2910579caa938519c953fccd48611fee.eprime.essence @@ -11,7 +11,7 @@ find var1_FunctionAsRelation_RelationAsSet_ExplicitVarSizeWithMarker_Values_2_Ex such that 2 <= var1_FunctionAsRelation_RelationAsSet_ExplicitVarSizeWithMarker_Marker -> var1_FunctionAsRelation_RelationAsSet_ExplicitVarSizeWithMarker_Values_1[1, ..] - var1_FunctionAsRelation_RelationAsSet_ExplicitVarSizeWithMarker_Marker diff --git a/tests/parse_print/autogen-bilals-fixed/2abab26b761b711b383086f57689adc5/2abab26b761b711b383086f57689adc5.eprime.essence b/tests/parse_print/autogen-bilals-fixed/2abab26b761b711b383086f57689adc5/2abab26b761b711b383086f57689adc5.eprime.essence index 61199e85b7..8f31bc1650 100644 --- a/tests/parse_print/autogen-bilals-fixed/2abab26b761b711b383086f57689adc5/2abab26b761b711b383086f57689adc5.eprime.essence +++ b/tests/parse_print/autogen-bilals-fixed/2abab26b761b711b383086f57689adc5/2abab26b761b711b383086f57689adc5.eprime.essence @@ -55,7 +55,7 @@ such that -> var1_FunctionAsRelation_RelationAsSet_ExplicitVarSizeWithMarker_Values_1_Function1DPartial_Flags[q1, ..] - var1_PartitionAsSet_Explicit_ExplicitVarSizeWithMarker_Values_Function1D[1, q6, ..] - flatten(var3_ExplicitVarSizeWithMarker_Values_RelationAsMatrix[1, .., .., .., ..]) - var3_ExplicitVarSizeWithMarker_Marker -> diff --git a/tests/parse_print/autogen-bilals-fixed/2cb879c833748cef779f84df872b0d71/2cb879c833748cef779f84df872b0d71.eprime.essence b/tests/parse_print/autogen-bilals-fixed/2cb879c833748cef779f84df872b0d71/2cb879c833748cef779f84df872b0d71.eprime.essence index 9a2b71cab4..d1f5295c50 100644 --- a/tests/parse_print/autogen-bilals-fixed/2cb879c833748cef779f84df872b0d71/2cb879c833748cef779f84df872b0d71.eprime.essence +++ b/tests/parse_print/autogen-bilals-fixed/2cb879c833748cef779f84df872b0d71/2cb879c833748cef779f84df872b0d71.eprime.essence @@ -159,7 +159,7 @@ such that (flatten(var1_PartitionAsSet_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMarker_Values_Function1DPartial_Flags[q1, .., ..]) - - var1_FunctionAsRelationR2R4_RelationAsSetR2R4_ExplicitVarSizeWithMarkerR2R4_Values_1_Occurrence[q6, ..] - (var1_FunctionAsRelationR2R4_RelationAsSetR2R4_ExplicitVarSizeWithMarkerR2R4_Values_1_Occurrence[q30, ..] or([var1_FunctionAsRelationR2R4_RelationAsSetR2R4_ExplicitVarSizeWithMarkerR2R4_Values_2_ExplicitVarSizeWithFlags_Flags diff --git a/tests/parse_print/autogen-bilals-fixed/3092be0de62c362cd1c49042c585105f/3092be0de62c362cd1c49042c585105f.eprime.essence b/tests/parse_print/autogen-bilals-fixed/3092be0de62c362cd1c49042c585105f/3092be0de62c362cd1c49042c585105f.eprime.essence index 6dffdecd73..ebfc20ef23 100644 --- a/tests/parse_print/autogen-bilals-fixed/3092be0de62c362cd1c49042c585105f/3092be0de62c362cd1c49042c585105f.eprime.essence +++ b/tests/parse_print/autogen-bilals-fixed/3092be0de62c362cd1c49042c585105f/3092be0de62c362cd1c49042c585105f.eprime.essence @@ -23,7 +23,7 @@ such that /\ (var1_ExplicitVarSizeWithFlags_Values_PartitionAsSet_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMarker_Marker[q1, ..] - diff --git a/tests/parse_print/autogen-bilals-fixed/32ba15f900d2899e277de2884b82db33/32ba15f900d2899e277de2884b82db33.eprime.essence b/tests/parse_print/autogen-bilals-fixed/32ba15f900d2899e277de2884b82db33/32ba15f900d2899e277de2884b82db33.eprime.essence index 375d7f3641..2f71ad5d39 100644 --- a/tests/parse_print/autogen-bilals-fixed/32ba15f900d2899e277de2884b82db33/32ba15f900d2899e277de2884b82db33.eprime.essence +++ b/tests/parse_print/autogen-bilals-fixed/32ba15f900d2899e277de2884b82db33/32ba15f900d2899e277de2884b82db33.eprime.essence @@ -2,5 +2,5 @@ language ESSENCE' 1.0 find unused: bool such that - [[false; int(1..1)]; int(1..1)][0, ..] var1_PartitionAsSet_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMarker_Values_Occurrence[q7, q8, ..] - var1_FunctionAsRelation_RelationAsSet_ExplicitVarSizeWithMarker_Values_1_Function1DPartial_Flags[q1, ..] - var1_FunctionAsRelation_RelationAsSet_ExplicitVarSizeWithMarker_Values_1_Occurrence[q1, ..] - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> diff --git a/tests/parse_print/autogen-bilals-fixed/360166fcf3210cf2cc730698c7561f1a/360166fcf3210cf2cc730698c7561f1a.eprime.essence b/tests/parse_print/autogen-bilals-fixed/360166fcf3210cf2cc730698c7561f1a/360166fcf3210cf2cc730698c7561f1a.eprime.essence index dff39ee084..b469082e31 100644 --- a/tests/parse_print/autogen-bilals-fixed/360166fcf3210cf2cc730698c7561f1a/360166fcf3210cf2cc730698c7561f1a.eprime.essence +++ b/tests/parse_print/autogen-bilals-fixed/360166fcf3210cf2cc730698c7561f1a/360166fcf3210cf2cc730698c7561f1a.eprime.essence @@ -128,7 +128,7 @@ such that (flatten(var1_PartitionAsSet_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMarker_Values_Function1DPartial_Flags[q1, .., ..]) - - var1_FunctionAsRelationR2R4_RelationAsSetR2R4_ExplicitVarSizeWithMarkerR2R4_Values_1_Occurrence[q6, ..] - (var1_FunctionAsRelationR2R4_RelationAsSetR2R4_ExplicitVarSizeWithMarkerR2R4_Values_1_Occurrence[q34, ..] or([var1_FunctionAsRelationR2R4_RelationAsSetR2R4_ExplicitVarSizeWithMarkerR2R4_Values_2_ExplicitVarSizeWithFlags_Flags diff --git a/tests/parse_print/autogen-bilals-fixed/36adf65748e3aabfd49290654b8b9ec2/36adf65748e3aabfd49290654b8b9ec2.eprime.essence b/tests/parse_print/autogen-bilals-fixed/36adf65748e3aabfd49290654b8b9ec2/36adf65748e3aabfd49290654b8b9ec2.eprime.essence index be34a43bb8..41527b55e7 100644 --- a/tests/parse_print/autogen-bilals-fixed/36adf65748e3aabfd49290654b8b9ec2/36adf65748e3aabfd49290654b8b9ec2.eprime.essence +++ b/tests/parse_print/autogen-bilals-fixed/36adf65748e3aabfd49290654b8b9ec2/36adf65748e3aabfd49290654b8b9ec2.eprime.essence @@ -71,7 +71,7 @@ such that -> var1_FunctionAsRelation_RelationAsSet_ExplicitVarSizeWithMarker_Values_1_Function1DPartial_Flags[q1, ..] - - var1_ExplicitVarSizeWithFlags_Values_ExplicitVarSizeWithFlags_Flags[q1, ..] @@ -125,7 +125,7 @@ such that .., .., ..]) - var2_1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> @@ -132,14 +132,14 @@ such that | q16 : int(1..9)]), 3 = var4_1_ExplicitWithRepetition_Flag, and([q23 + 1 <= var5_ExplicitWithRepetitionR10_Flag -> - var5_ExplicitWithRepetitionR10_Values_Function1DPartial_Flags[q23, ..] var5_ExplicitWithRepetitionR10_Flag -> diff --git a/tests/parse_print/autogen-bilals-fixed/39fc0816e0aea89208c87fa4d39edf4d/39fc0816e0aea89208c87fa4d39edf4d.essence b/tests/parse_print/autogen-bilals-fixed/39fc0816e0aea89208c87fa4d39edf4d/39fc0816e0aea89208c87fa4d39edf4d.essence index 56b00d2989..4535f7fea9 100644 --- a/tests/parse_print/autogen-bilals-fixed/39fc0816e0aea89208c87fa4d39edf4d/39fc0816e0aea89208c87fa4d39edf4d.essence +++ b/tests/parse_print/autogen-bilals-fixed/39fc0816e0aea89208c87fa4d39edf4d/39fc0816e0aea89208c87fa4d39edf4d.essence @@ -21,7 +21,7 @@ such that (mset() : `mset of mset of int`) --> mset(true)), image(function([1, 0; int(3, 0..0)] --> [false, true, false, false, false; int(3, 15, 0, 4, 2..2)]), [5, 2 - 5; int(2, 5..5)]) - <=lex [l_2 | l_1 : bool, l_2 : bool, and(([] : `matrix indexed by [int] of bool`)), l_2], + .<= [l_2 | l_1 : bool, l_2 : bool, and(([] : `matrix indexed by [int] of bool`)), l_2], image(function((tuple (0), false, false, partition({true}, {false})) --> true, (tuple (4), true = false, true, partition({false, true, true})) --> true > false, (tuple (1), false, false, diff --git a/tests/parse_print/autogen-bilals-fixed/3b5e1803eab57ae500a891f3bfadce58/3b5e1803eab57ae500a891f3bfadce58.eprime.essence b/tests/parse_print/autogen-bilals-fixed/3b5e1803eab57ae500a891f3bfadce58/3b5e1803eab57ae500a891f3bfadce58.eprime.essence index f58632e6d7..fdecf2c6a5 100644 --- a/tests/parse_print/autogen-bilals-fixed/3b5e1803eab57ae500a891f3bfadce58/3b5e1803eab57ae500a891f3bfadce58.eprime.essence +++ b/tests/parse_print/autogen-bilals-fixed/3b5e1803eab57ae500a891f3bfadce58/3b5e1803eab57ae500a891f3bfadce58.eprime.essence @@ -30,7 +30,7 @@ such that /\ (var1_ExplicitVarSizeWithFlags_Values_PartitionAsSet_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMarker_Marker[q1, ..] - var2_PartitionAsSet_ExplicitVarSizeWithMarker_Values_Explicit_ExplicitVarSizeWithMarker_Marker[q4, ..] - = 1 | q17 : int(1..16)]), and([q6 + 1 <= var2_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> - var2_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q6, ..] var2_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> diff --git a/tests/parse_print/autogen-bilals-fixed/3f487c8189ea7cd34b26c9482423c22f/3f487c8189ea7cd34b26c9482423c22f.eprime.essence b/tests/parse_print/autogen-bilals-fixed/3f487c8189ea7cd34b26c9482423c22f/3f487c8189ea7cd34b26c9482423c22f.eprime.essence index 927389ae07..184105042e 100644 --- a/tests/parse_print/autogen-bilals-fixed/3f487c8189ea7cd34b26c9482423c22f/3f487c8189ea7cd34b26c9482423c22f.eprime.essence +++ b/tests/parse_print/autogen-bilals-fixed/3f487c8189ea7cd34b26c9482423c22f/3f487c8189ea7cd34b26c9482423c22f.eprime.essence @@ -156,7 +156,7 @@ such that (flatten(var1_PartitionAsSet_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMarker_Values_Function1DPartial_Flags[q1, .., ..]) - @@ -77,7 +77,7 @@ such that var3_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q20] = var3_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q20 + 1] /\ - var3_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values_1[q20, ..] var3_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> diff --git a/tests/parse_print/autogen-bilals-fixed/40c777188c96f06f23b379634df5be19/40c777188c96f06f23b379634df5be19.essence b/tests/parse_print/autogen-bilals-fixed/40c777188c96f06f23b379634df5be19/40c777188c96f06f23b379634df5be19.essence index da86918288..cfff9bb54f 100644 --- a/tests/parse_print/autogen-bilals-fixed/40c777188c96f06f23b379634df5be19/40c777188c96f06f23b379634df5be19.essence +++ b/tests/parse_print/autogen-bilals-fixed/40c777188c96f06f23b379634df5be19/40c777188c96f06f23b379634df5be19.essence @@ -4,4 +4,4 @@ find var1: set (maxSize -0) of partition (numParts 5, partSize 3) from bool such that {true, false} = {false, true, true}, true, - [false, false, true, false; int(6..9)] = 0 | q17 : int(1..3)]), 3 = sum([var4_1_ExplicitWithFlags_Flags[q18] | q18 : int(1..3)]), and([q20 + 1 <= var5_ExplicitWithRepetitionR10_Flag -> - var5_ExplicitWithRepetitionR10_Values_Function1DPartial_Flags[q20, ..] var5_ExplicitWithRepetitionR10_Flag -> diff --git a/tests/parse_print/autogen-bilals-fixed/4280cfb278486b51961b41fb8309b68d/4280cfb278486b51961b41fb8309b68d.eprime.essence b/tests/parse_print/autogen-bilals-fixed/4280cfb278486b51961b41fb8309b68d/4280cfb278486b51961b41fb8309b68d.eprime.essence index c3f42d0423..6f5a02d570 100644 --- a/tests/parse_print/autogen-bilals-fixed/4280cfb278486b51961b41fb8309b68d/4280cfb278486b51961b41fb8309b68d.eprime.essence +++ b/tests/parse_print/autogen-bilals-fixed/4280cfb278486b51961b41fb8309b68d/4280cfb278486b51961b41fb8309b68d.eprime.essence @@ -19,14 +19,14 @@ such that q_4_ExplicitVarSizeWithFlags_Values_Function1DPartial_Values : matrix indexed by [int(1..4), bool] of int(5..5), and([q_4_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - q_4_ExplicitVarSizeWithFlags_Values_Function1DPartial_Flags[q1, ..] @@ -73,7 +73,7 @@ such that /\ var1_PartitionAsSet_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMarker_Values[q3, ..] - - var2_ExplicitVarSizeWithMarker_Values_Function1DPartial_Flags[q5, ..] var2_ExplicitVarSizeWithMarker_Marker -> diff --git a/tests/parse_print/autogen-bilals-fixed/42c5a23fafc955d441461af4184f86f2/42c5a23fafc955d441461af4184f86f2.eprime.essence b/tests/parse_print/autogen-bilals-fixed/42c5a23fafc955d441461af4184f86f2/42c5a23fafc955d441461af4184f86f2.eprime.essence index 359723c10c..d21c58d7f8 100644 --- a/tests/parse_print/autogen-bilals-fixed/42c5a23fafc955d441461af4184f86f2/42c5a23fafc955d441461af4184f86f2.eprime.essence +++ b/tests/parse_print/autogen-bilals-fixed/42c5a23fafc955d441461af4184f86f2/42c5a23fafc955d441461af4184f86f2.eprime.essence @@ -135,7 +135,7 @@ such that (flatten(var1_PartitionAsSet_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMarker_Values_Function1DPartial_Flags[q5, .., ..]) - var5_PartitionAsSet_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMarker_Values_Occurrence[q23, q24, ..] - var2_RelationAsSet_ExplicitVarSizeWithMarker_Values_1_ExplicitVarSizeWithFlags_Flags[q1, ..] - var4_ExplicitVarSizeWithMarkerR18_Marker -> diff --git a/tests/parse_print/autogen-bilals-fixed/461bdf3c29b2f09b541034b080952550/461bdf3c29b2f09b541034b080952550.eprime.essence b/tests/parse_print/autogen-bilals-fixed/461bdf3c29b2f09b541034b080952550/461bdf3c29b2f09b541034b080952550.eprime.essence index 857fd67c94..c1cdaecc70 100644 --- a/tests/parse_print/autogen-bilals-fixed/461bdf3c29b2f09b541034b080952550/461bdf3c29b2f09b541034b080952550.eprime.essence +++ b/tests/parse_print/autogen-bilals-fixed/461bdf3c29b2f09b541034b080952550/461bdf3c29b2f09b541034b080952550.eprime.essence @@ -21,7 +21,7 @@ find var6_ExplicitVarSizeWithFlags_Values: such that var4, and([var2_ExplicitVarSizeWithFlags_Flags[q10 + 1] -> - var2_ExplicitVarSizeWithFlags_Values[q10, ..] @@ -38,7 +38,7 @@ such that var5_ExplicitVarSizeWithFlags_Flags[1] >= -4, 1 = var5_ExplicitVarSizeWithFlags_Flags[1], and([var6_ExplicitVarSizeWithFlags_Flags[q25 + 1] -> - var6_ExplicitVarSizeWithFlags_Values[q25, ..] diff --git a/tests/parse_print/autogen-bilals-fixed/463c263b7ca3948dadc72aac12f03675/463c263b7ca3948dadc72aac12f03675.essence b/tests/parse_print/autogen-bilals-fixed/463c263b7ca3948dadc72aac12f03675/463c263b7ca3948dadc72aac12f03675.essence index 5e0b8145c6..ab77ff929a 100644 --- a/tests/parse_print/autogen-bilals-fixed/463c263b7ca3948dadc72aac12f03675/463c263b7ca3948dadc72aac12f03675.essence +++ b/tests/parse_print/autogen-bilals-fixed/463c263b7ca3948dadc72aac12f03675/463c263b7ca3948dadc72aac12f03675.essence @@ -1,4 +1,4 @@ language Essence 1.3 find unused: bool -such that [false; int(1..1)] [true; int(1..1)]), [false; int(1..1)]) +such that [false; int(1..1)] .< image(function([true; int(1..1)] --> [true; int(1..1)]), [false; int(1..1)]) diff --git a/tests/parse_print/autogen-bilals-fixed/48929a67dab909763280169f5d4632b9/48929a67dab909763280169f5d4632b9.eprime.essence b/tests/parse_print/autogen-bilals-fixed/48929a67dab909763280169f5d4632b9/48929a67dab909763280169f5d4632b9.eprime.essence index e2c7003263..7230b3fdc5 100644 --- a/tests/parse_print/autogen-bilals-fixed/48929a67dab909763280169f5d4632b9/48929a67dab909763280169f5d4632b9.eprime.essence +++ b/tests/parse_print/autogen-bilals-fixed/48929a67dab909763280169f5d4632b9/48929a67dab909763280169f5d4632b9.eprime.essence @@ -21,7 +21,7 @@ such that /\ (var1_ExplicitVarSizeWithFlags_Values_PartitionAsSet_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMarker_Marker[q1, ..] - var1_FunctionAsRelation_RelationAsSet_ExplicitVarSizeWithMarker_Values_1_Function1DPartial_Flags[q1, ..] - @@ -32,10 +32,10 @@ such that | q19 : int(1..2)]) | q17 : int(1..2)]) /\ - (var1_RelationAsSet_Explicit_2_ExplicitVarSizeWithFlags_Flags[1, ..] var1_RelationAsSet_Explicit_1_ExplicitVarSizeWithMarker_Values[q2, 1] < diff --git a/tests/parse_print/autogen-bilals-fixed/4a598ea5ec7744cc20c3a53601371daf/4a598ea5ec7744cc20c3a53601371daf.eprime.essence b/tests/parse_print/autogen-bilals-fixed/4a598ea5ec7744cc20c3a53601371daf/4a598ea5ec7744cc20c3a53601371daf.eprime.essence index 8f8259e415..f17eed1156 100644 --- a/tests/parse_print/autogen-bilals-fixed/4a598ea5ec7744cc20c3a53601371daf/4a598ea5ec7744cc20c3a53601371daf.eprime.essence +++ b/tests/parse_print/autogen-bilals-fixed/4a598ea5ec7744cc20c3a53601371daf/4a598ea5ec7744cc20c3a53601371daf.eprime.essence @@ -120,7 +120,7 @@ such that (flatten(var1_PartitionAsSet_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMarker_Values_Function1DPartial_Flags[q5, .., ..]) - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> diff --git a/tests/parse_print/autogen-bilals-fixed/4be21fd12a8819847cbd51dea1e370a3/4be21fd12a8819847cbd51dea1e370a3.eprime.essence b/tests/parse_print/autogen-bilals-fixed/4be21fd12a8819847cbd51dea1e370a3/4be21fd12a8819847cbd51dea1e370a3.eprime.essence index 700beccb1b..6e1ad0bbd1 100644 --- a/tests/parse_print/autogen-bilals-fixed/4be21fd12a8819847cbd51dea1e370a3/4be21fd12a8819847cbd51dea1e370a3.eprime.essence +++ b/tests/parse_print/autogen-bilals-fixed/4be21fd12a8819847cbd51dea1e370a3/4be21fd12a8819847cbd51dea1e370a3.eprime.essence @@ -21,21 +21,21 @@ such that -> var2_FunctionAsRelation_RelationAsSet_ExplicitVarSizeWithMarker_Values_1_ExplicitVarSizeWithFlags_Flags[q4, ..] - false), var1 <=lex [true; int(1..1)]) +such that image(function(true --> false), var1 .<= [true; int(1..1)]) diff --git a/tests/parse_print/autogen-bilals-fixed/4f9ae4ffb009a3b226c8414061bd362f/4f9ae4ffb009a3b226c8414061bd362f.eprime.essence b/tests/parse_print/autogen-bilals-fixed/4f9ae4ffb009a3b226c8414061bd362f/4f9ae4ffb009a3b226c8414061bd362f.eprime.essence index 9381407992..45e2a8a251 100644 --- a/tests/parse_print/autogen-bilals-fixed/4f9ae4ffb009a3b226c8414061bd362f/4f9ae4ffb009a3b226c8414061bd362f.eprime.essence +++ b/tests/parse_print/autogen-bilals-fixed/4f9ae4ffb009a3b226c8414061bd362f/4f9ae4ffb009a3b226c8414061bd362f.eprime.essence @@ -49,7 +49,7 @@ such that -> var1_FunctionAsRelation_RelationAsSet_ExplicitVarSizeWithMarker_Values_1_Function1DPartial_Flags[q1, ..] - @@ -79,7 +79,7 @@ such that var3_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q19] = var3_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q19 + 1] /\ - var3_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values_1[q19, ..] var3_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> diff --git a/tests/parse_print/autogen-bilals-fixed/54c995d240bca20d3853847acef38f4b/54c995d240bca20d3853847acef38f4b.eprime.essence b/tests/parse_print/autogen-bilals-fixed/54c995d240bca20d3853847acef38f4b/54c995d240bca20d3853847acef38f4b.eprime.essence index 5845d300d8..9468627669 100644 --- a/tests/parse_print/autogen-bilals-fixed/54c995d240bca20d3853847acef38f4b/54c995d240bca20d3853847acef38f4b.eprime.essence +++ b/tests/parse_print/autogen-bilals-fixed/54c995d240bca20d3853847acef38f4b/54c995d240bca20d3853847acef38f4b.eprime.essence @@ -91,7 +91,7 @@ such that -> var1_FunctionAsRelation_RelationAsSet_ExplicitVarSizeWithMarker_Values_1_Function1DPartial_Flags[q1, ..] - - var1_ExplicitWithRepetitionR4_Values_ExplicitVarSizeWithFlags_Flags[q1, ..] var1_ExplicitWithRepetitionR4_Flag -> @@ -82,7 +82,7 @@ such that var2_RelationAsSetR9_ExplicitVarSizeWithMarkerR9_Values_1[q25, q26] = var2_RelationAsSetR9_ExplicitVarSizeWithMarkerR9_Values_1[q25, q26 + 1] /\ - var2_RelationAsSetR9_ExplicitVarSizeWithMarkerR9_Values_2_Function1D[q25, q26, ..] - var2_ExplicitVarSizeWithMarker_Values[q10, ..] var2_ExplicitVarSizeWithMarker_Marker -> @@ -35,7 +35,7 @@ such that var5_ExplicitVarSizeWithFlags_Flags[1] >= -4, 1 = var5_ExplicitVarSizeWithFlags_Flags[1], and([q23 + 1 <= var6_ExplicitVarSizeWithMarker_Marker -> - var6_ExplicitVarSizeWithMarker_Values[q23, ..] var6_ExplicitVarSizeWithMarker_Marker -> diff --git a/tests/parse_print/autogen-bilals-fixed/5f8abcfb913c155e5fcf9aad1689ee48/5f8abcfb913c155e5fcf9aad1689ee48.eprime.essence b/tests/parse_print/autogen-bilals-fixed/5f8abcfb913c155e5fcf9aad1689ee48/5f8abcfb913c155e5fcf9aad1689ee48.eprime.essence index 76f2ee0dcb..d635873d95 100644 --- a/tests/parse_print/autogen-bilals-fixed/5f8abcfb913c155e5fcf9aad1689ee48/5f8abcfb913c155e5fcf9aad1689ee48.eprime.essence +++ b/tests/parse_print/autogen-bilals-fixed/5f8abcfb913c155e5fcf9aad1689ee48/5f8abcfb913c155e5fcf9aad1689ee48.eprime.essence @@ -33,7 +33,7 @@ such that var1_ExplicitVarSizeWithMarkerR8_Values_ExplicitWithRepetition_Flag[q1] = var1_ExplicitVarSizeWithMarkerR8_Values_ExplicitWithRepetition_Flag[q1 + 1] /\ - var1_ExplicitVarSizeWithMarkerR8_Values_ExplicitWithRepetition_Values[q1, ..] var1_ExplicitVarSizeWithMarkerR8_Marker -> @@ -78,7 +78,7 @@ such that var3_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q17] = var3_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q17 + 1] /\ - var3_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values_1[q17, ..] var3_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> diff --git a/tests/parse_print/autogen-bilals-fixed/603465a931823cf8433459de2d015883/603465a931823cf8433459de2d015883.eprime.essence b/tests/parse_print/autogen-bilals-fixed/603465a931823cf8433459de2d015883/603465a931823cf8433459de2d015883.eprime.essence index 3b91ee5a2c..60dec1b2a0 100644 --- a/tests/parse_print/autogen-bilals-fixed/603465a931823cf8433459de2d015883/603465a931823cf8433459de2d015883.eprime.essence +++ b/tests/parse_print/autogen-bilals-fixed/603465a931823cf8433459de2d015883/603465a931823cf8433459de2d015883.eprime.essence @@ -68,21 +68,21 @@ such that var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q4] = var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q4 + 1] /\ - (var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values_1[q4, ..] var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> diff --git a/tests/parse_print/autogen-bilals-fixed/612a3b4f1e02d37d3c58b3ade9b248ef/612a3b4f1e02d37d3c58b3ade9b248ef.essence b/tests/parse_print/autogen-bilals-fixed/612a3b4f1e02d37d3c58b3ade9b248ef/612a3b4f1e02d37d3c58b3ade9b248ef.essence index 51a85aced1..5e20cc46ec 100644 --- a/tests/parse_print/autogen-bilals-fixed/612a3b4f1e02d37d3c58b3ade9b248ef/612a3b4f1e02d37d3c58b3ade9b248ef.essence +++ b/tests/parse_print/autogen-bilals-fixed/612a3b4f1e02d37d3c58b3ade9b248ef/612a3b4f1e02d37d3c58b3ade9b248ef.essence @@ -6,7 +6,7 @@ such that false, (function() : `function bool --> int`) = function(true --> 0, true --> 4, true --> 0), - [false, true, true, false; int(6..9)] <=lex + [false, true, true, false; int(6..9)] .<= [true, true, false, false, false; int(10..11, 1..3)], image(function(5 --> true), 3 / var1), true in mset(false), diff --git a/tests/parse_print/autogen-bilals-fixed/62efe6787e7be32b6775a9054b5e7a90/62efe6787e7be32b6775a9054b5e7a90.eprime.essence b/tests/parse_print/autogen-bilals-fixed/62efe6787e7be32b6775a9054b5e7a90/62efe6787e7be32b6775a9054b5e7a90.eprime.essence index ecb2edcfba..f2e33b4e53 100644 --- a/tests/parse_print/autogen-bilals-fixed/62efe6787e7be32b6775a9054b5e7a90/62efe6787e7be32b6775a9054b5e7a90.eprime.essence +++ b/tests/parse_print/autogen-bilals-fixed/62efe6787e7be32b6775a9054b5e7a90/62efe6787e7be32b6775a9054b5e7a90.eprime.essence @@ -33,7 +33,7 @@ such that and([q13 + 1 <= var2_PartitionAsSet_ExplicitVarSizeWithMarker_Marker -> flatten(var2_PartitionAsSet_ExplicitVarSizeWithMarker_Values_Explicit_ExplicitVarSizeWithFlags_Flags[q13, .., ..]) - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> diff --git a/tests/parse_print/autogen-bilals-fixed/67856b9617d62beaf659a45708f21210/67856b9617d62beaf659a45708f21210.eprime.essence b/tests/parse_print/autogen-bilals-fixed/67856b9617d62beaf659a45708f21210/67856b9617d62beaf659a45708f21210.eprime.essence index 8d96840444..6465b61481 100644 --- a/tests/parse_print/autogen-bilals-fixed/67856b9617d62beaf659a45708f21210/67856b9617d62beaf659a45708f21210.eprime.essence +++ b/tests/parse_print/autogen-bilals-fixed/67856b9617d62beaf659a45708f21210/67856b9617d62beaf659a45708f21210.eprime.essence @@ -28,7 +28,7 @@ such that /\ flatten(var2_PartitionAsSetR6_ExplicitVarSizeWithMarkerR5R6_Values_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy [q4, .., ..]) - - flatten(var2_ExplicitVarSizeWithFlags_Values_RelationAsMatrix[q8, .., ..]) diff --git a/tests/parse_print/autogen-bilals-fixed/688d9c5f26c404975d660fcdd262858c/688d9c5f26c404975d660fcdd262858c.eprime.essence b/tests/parse_print/autogen-bilals-fixed/688d9c5f26c404975d660fcdd262858c/688d9c5f26c404975d660fcdd262858c.eprime.essence index cf295fd551..17eb576482 100644 --- a/tests/parse_print/autogen-bilals-fixed/688d9c5f26c404975d660fcdd262858c/688d9c5f26c404975d660fcdd262858c.eprime.essence +++ b/tests/parse_print/autogen-bilals-fixed/688d9c5f26c404975d660fcdd262858c/688d9c5f26c404975d660fcdd262858c.eprime.essence @@ -66,7 +66,7 @@ such that -> var1_FunctionAsRelation_RelationAsSet_ExplicitVarSizeWithMarker_Values_1_Function1DPartial_Flags[q1, ..] - - q_4_ExplicitVarSizeWithMarker_Values_Function1DPartial_Flags[q1, ..] q_4_ExplicitVarSizeWithMarker_Marker -> @@ -71,7 +71,7 @@ such that /\ var1_PartitionAsSet_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMarker_Values[q3, ..] - - var2_ExplicitVarSizeWithMarker_Values_Function1DPartial_Flags[q5, ..] var2_ExplicitVarSizeWithMarker_Marker -> diff --git a/tests/parse_print/autogen-bilals-fixed/6d234926de4bf3efc85ef76d53a68827/6d234926de4bf3efc85ef76d53a68827.eprime.essence b/tests/parse_print/autogen-bilals-fixed/6d234926de4bf3efc85ef76d53a68827/6d234926de4bf3efc85ef76d53a68827.eprime.essence index d5e8c626e3..d06510ed3c 100644 --- a/tests/parse_print/autogen-bilals-fixed/6d234926de4bf3efc85ef76d53a68827/6d234926de4bf3efc85ef76d53a68827.eprime.essence +++ b/tests/parse_print/autogen-bilals-fixed/6d234926de4bf3efc85ef76d53a68827/6d234926de4bf3efc85ef76d53a68827.eprime.essence @@ -60,21 +60,21 @@ such that var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q4] = var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q4 + 1] /\ - (var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values_1[q4, ..] var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> diff --git a/tests/parse_print/autogen-bilals-fixed/6e78775adcfd98bd61ddfa72523d20d7/6e78775adcfd98bd61ddfa72523d20d7.eprime.essence b/tests/parse_print/autogen-bilals-fixed/6e78775adcfd98bd61ddfa72523d20d7/6e78775adcfd98bd61ddfa72523d20d7.eprime.essence index f6f488e8d1..3f36f05a53 100644 --- a/tests/parse_print/autogen-bilals-fixed/6e78775adcfd98bd61ddfa72523d20d7/6e78775adcfd98bd61ddfa72523d20d7.eprime.essence +++ b/tests/parse_print/autogen-bilals-fixed/6e78775adcfd98bd61ddfa72523d20d7/6e78775adcfd98bd61ddfa72523d20d7.eprime.essence @@ -64,21 +64,21 @@ such that var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q4] = var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q4 + 1] /\ - (var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values_1[q4, ..] var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> diff --git a/tests/parse_print/autogen-bilals-fixed/6f115e6ceb931de245d1914a7238a5e1/6f115e6ceb931de245d1914a7238a5e1.eprime.essence b/tests/parse_print/autogen-bilals-fixed/6f115e6ceb931de245d1914a7238a5e1/6f115e6ceb931de245d1914a7238a5e1.eprime.essence index 2fc416e344..0661cb713b 100644 --- a/tests/parse_print/autogen-bilals-fixed/6f115e6ceb931de245d1914a7238a5e1/6f115e6ceb931de245d1914a7238a5e1.eprime.essence +++ b/tests/parse_print/autogen-bilals-fixed/6f115e6ceb931de245d1914a7238a5e1/6f115e6ceb931de245d1914a7238a5e1.eprime.essence @@ -28,7 +28,7 @@ such that /\ flatten(var2_PartitionAsSetR6_ExplicitVarSizeWithMarkerR5R6_Values_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy [q4, .., ..]) - - var1_ExplicitVarSizeWithFlagsR7_Values_ExplicitWithFlags_Flags[q1, ..] @@ -85,7 +85,7 @@ such that var3_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q22] = var3_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q22 + 1] /\ - var3_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values_1[q22, ..] var3_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> diff --git a/tests/parse_print/autogen-bilals-fixed/73472b413e1c687c0430a8719e4f016b/73472b413e1c687c0430a8719e4f016b.eprime.essence b/tests/parse_print/autogen-bilals-fixed/73472b413e1c687c0430a8719e4f016b/73472b413e1c687c0430a8719e4f016b.eprime.essence index 6413675181..75317635de 100644 --- a/tests/parse_print/autogen-bilals-fixed/73472b413e1c687c0430a8719e4f016b/73472b413e1c687c0430a8719e4f016b.eprime.essence +++ b/tests/parse_print/autogen-bilals-fixed/73472b413e1c687c0430a8719e4f016b/73472b413e1c687c0430a8719e4f016b.eprime.essence @@ -17,7 +17,7 @@ such that /\ flatten(var6_ExplicitVarSizeWithFlags_Values_PartitionAsSet_ExplicitVarSizeWithMarker_Values_Explicit[1, .., ..]) - @@ -38,7 +38,7 @@ such that -> var6_ExplicitVarSizeWithFlags_Values_PartitionAsSet_ExplicitVarSizeWithMarker_Values_Explicit[q5, q9, ..] - var1_RelationAsSet_ExplicitVarSizeWithMarker_Values_1_ExplicitVarSizeWithFlags_Flags[q1, ..] - - var1_FunctionAsRelationR3R5_RelationAsSetR3R5_ExplicitVarSizeWithMarkerR3R5_Values_1_Explicit[q6, ..] - (var1_FunctionAsRelationR3R5_RelationAsSetR3R5_ExplicitVarSizeWithMarkerR3R5_Values_1_Explicit[q31, ..] or([q34 <= diff --git a/tests/parse_print/autogen-bilals-fixed/788102a4292eb30458166a213f53d06b/788102a4292eb30458166a213f53d06b.eprime.essence b/tests/parse_print/autogen-bilals-fixed/788102a4292eb30458166a213f53d06b/788102a4292eb30458166a213f53d06b.eprime.essence index 9601ed7970..7963b7b968 100644 --- a/tests/parse_print/autogen-bilals-fixed/788102a4292eb30458166a213f53d06b/788102a4292eb30458166a213f53d06b.eprime.essence +++ b/tests/parse_print/autogen-bilals-fixed/788102a4292eb30458166a213f53d06b/788102a4292eb30458166a213f53d06b.eprime.essence @@ -64,21 +64,21 @@ such that var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q4] = var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q4 + 1] /\ - (var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values_1[q4, ..] var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> diff --git a/tests/parse_print/autogen-bilals-fixed/7916e2376c2f7a027a1836f83d31e41f/7916e2376c2f7a027a1836f83d31e41f.eprime.essence b/tests/parse_print/autogen-bilals-fixed/7916e2376c2f7a027a1836f83d31e41f/7916e2376c2f7a027a1836f83d31e41f.eprime.essence index e211819970..8a826ab758 100644 --- a/tests/parse_print/autogen-bilals-fixed/7916e2376c2f7a027a1836f83d31e41f/7916e2376c2f7a027a1836f83d31e41f.eprime.essence +++ b/tests/parse_print/autogen-bilals-fixed/7916e2376c2f7a027a1836f83d31e41f/7916e2376c2f7a027a1836f83d31e41f.eprime.essence @@ -24,7 +24,7 @@ such that -> var1_PartitionAsSet_Explicit_ExplicitVarSizeWithMarker_Values_Function1D[1, q6, ..] - var1_PartitionAsSet_Explicit_ExplicitVarSizeWithMarker_Values_Function1D[q5, q6, ..] - - var1_FunctionAsRelationR3R4_RelationAsSetR3R4_ExplicitVarSizeWithMarkerR3R4_Values_1_Explicit[q6, ..] - (var1_FunctionAsRelationR3R4_RelationAsSetR3R4_ExplicitVarSizeWithMarkerR3R4_Values_1_Explicit[q36, ..] or([var1_FunctionAsRelationR3R4_RelationAsSetR3R4_ExplicitVarSizeWithMarkerR3R4_Values_2_ExplicitVarSizeWithFlags_Flags diff --git a/tests/parse_print/autogen-bilals-fixed/7c756ce0724280ed59c97a84dd82e7c0/7c756ce0724280ed59c97a84dd82e7c0.essence b/tests/parse_print/autogen-bilals-fixed/7c756ce0724280ed59c97a84dd82e7c0/7c756ce0724280ed59c97a84dd82e7c0.essence index 2afa71e4c4..1560815a31 100644 --- a/tests/parse_print/autogen-bilals-fixed/7c756ce0724280ed59c97a84dd82e7c0/7c756ce0724280ed59c97a84dd82e7c0.essence +++ b/tests/parse_print/autogen-bilals-fixed/7c756ce0724280ed59c97a84dd82e7c0/7c756ce0724280ed59c97a84dd82e7c0.essence @@ -14,5 +14,5 @@ find var4: find var5: set (minSize 5 , maxSize 5) of tuple (int(2, 4)) such that tuple (false)[1] > - ([l_2 | l_1 : int(4, 2), l_2 : int(2, 5..5), true] = 1 | q56 : int(1..4)]), and([q7 + 1 <= var2_1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - var2_1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q7, ..] var2_1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> @@ -119,14 +119,14 @@ such that | q17 : int(1..9)]), 3 = var4_1_ExplicitWithRepetition_Flag, and([q24 + 1 <= var5_ExplicitWithRepetitionR10_Flag -> - var5_ExplicitWithRepetitionR10_Values_Function1DPartial_Flags[q24, ..] var5_ExplicitWithRepetitionR10_Flag -> diff --git a/tests/parse_print/autogen-bilals-fixed/7cc8838035af5627767687a2a0dd2023/7cc8838035af5627767687a2a0dd2023.eprime.essence b/tests/parse_print/autogen-bilals-fixed/7cc8838035af5627767687a2a0dd2023/7cc8838035af5627767687a2a0dd2023.eprime.essence index 69e309d01b..7115d2533c 100644 --- a/tests/parse_print/autogen-bilals-fixed/7cc8838035af5627767687a2a0dd2023/7cc8838035af5627767687a2a0dd2023.eprime.essence +++ b/tests/parse_print/autogen-bilals-fixed/7cc8838035af5627767687a2a0dd2023/7cc8838035af5627767687a2a0dd2023.eprime.essence @@ -27,14 +27,14 @@ such that given2, given1, and([var1_ExplicitVarSizeWithFlagsR7_Flags[q1 + 1] -> - var1_ExplicitVarSizeWithFlagsR7_Values_ExplicitWithFlags_Flags[q1, ..] @@ -83,7 +83,7 @@ such that var3_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q23] = var3_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q23 + 1] /\ - var3_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values_1[q23, ..] var3_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> diff --git a/tests/parse_print/autogen-bilals-fixed/7eeaf2347f1bf8b83db5d0b7c15483e6/7eeaf2347f1bf8b83db5d0b7c15483e6.eprime.essence b/tests/parse_print/autogen-bilals-fixed/7eeaf2347f1bf8b83db5d0b7c15483e6/7eeaf2347f1bf8b83db5d0b7c15483e6.eprime.essence index 9f4a05fa5f..c843e5d614 100644 --- a/tests/parse_print/autogen-bilals-fixed/7eeaf2347f1bf8b83db5d0b7c15483e6/7eeaf2347f1bf8b83db5d0b7c15483e6.eprime.essence +++ b/tests/parse_print/autogen-bilals-fixed/7eeaf2347f1bf8b83db5d0b7c15483e6/7eeaf2347f1bf8b83db5d0b7c15483e6.eprime.essence @@ -156,7 +156,7 @@ such that (flatten(var3_PartitionAsSet_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMarker_Values_Function1DPartial_Flags[q1, .., ..]) - - var1_FunctionAsRelationR3R5_RelationAsSetR3R5_ExplicitVarSizeWithMarkerR3R5_Values_1_Explicit[q6, ..] - (var1_FunctionAsRelationR3R5_RelationAsSetR3R5_ExplicitVarSizeWithMarkerR3R5_Values_1_Explicit[q31, ..] or([q34 <= diff --git a/tests/parse_print/autogen-bilals-fixed/820969cf7025c19eb6a8b65584b5c7ec/820969cf7025c19eb6a8b65584b5c7ec.essence b/tests/parse_print/autogen-bilals-fixed/820969cf7025c19eb6a8b65584b5c7ec/820969cf7025c19eb6a8b65584b5c7ec.essence index bda27f5fe5..7450ef5c6e 100644 --- a/tests/parse_print/autogen-bilals-fixed/820969cf7025c19eb6a8b65584b5c7ec/820969cf7025c19eb6a8b65584b5c7ec.essence +++ b/tests/parse_print/autogen-bilals-fixed/820969cf7025c19eb6a8b65584b5c7ec/820969cf7025c19eb6a8b65584b5c7ec.essence @@ -127,7 +127,7 @@ such that relation((false, 5, 4), (true, 4, 3), (false, 5, 4), (true, 4, 3), (true, 5, 2))))} --> ((2, 3, false, 5), mset(0, 1, 3), (true, true), false >= true)[2]), - [l_1 | l_1 : int(5, 2..5)] <=lex + [l_1 | l_1 : int(5, 2..5)] .<= [l_2 | l_2 : int(1..2, 2), and(([] : `matrix indexed by [int] of bool`))], allDiff([partition({(mset() : `mset of partition from bool`), mset(partition({true}, {true, false, true, true, false}, {true, true, false}, @@ -157,7 +157,7 @@ such that {false, false, false}, {true, true, false, false}, {true, true}), partition({true, true, true}, {true, false, false, true}))}), (partition() : `partition from mset of partition from bool`); int(3, 4, 2..2)]), - [l_3 | l_3 : int(2, 0), false] !true, relation((false, l_5, l_5, true), (false, l_5, l_5, true)) --> true = true, diff --git a/tests/parse_print/autogen-bilals-fixed/827f1d4ebd57ab718caa032cc8b297fc/827f1d4ebd57ab718caa032cc8b297fc.eprime.essence b/tests/parse_print/autogen-bilals-fixed/827f1d4ebd57ab718caa032cc8b297fc/827f1d4ebd57ab718caa032cc8b297fc.eprime.essence index 72efb10dee..8fb617a3ee 100644 --- a/tests/parse_print/autogen-bilals-fixed/827f1d4ebd57ab718caa032cc8b297fc/827f1d4ebd57ab718caa032cc8b297fc.eprime.essence +++ b/tests/parse_print/autogen-bilals-fixed/827f1d4ebd57ab718caa032cc8b297fc/827f1d4ebd57ab718caa032cc8b297fc.eprime.essence @@ -15,7 +15,7 @@ such that -> var1_FunctionAsRelation_RelationAsSet_ExplicitVarSizeWithMarker_Values_1_ExplicitVarSizeWithFlags_Flags[q1, ..] - var1_ExplicitVarSizeWithMarker_Values_PartitionAsSet_ExplicitVarSizeWithMarker_Values_Occurrence[1, q9, ..] - - var3_ExplicitVarSizeWithFlags_Values_Function1DPartial_Flags[q32, ..] @@ -150,14 +150,14 @@ such that | q40 : bool]) | q36 : int(1..3)]), and([var4_ExplicitVarSizeWithFlags_Flags[q42 + 1] -> - var4_ExplicitVarSizeWithFlags_Values_Function1DPartial_Flags[q42, ..] diff --git a/tests/parse_print/autogen-bilals-fixed/83e79dafff20cf8bb9bbf4e0e4da6ed2/83e79dafff20cf8bb9bbf4e0e4da6ed2.eprime.essence b/tests/parse_print/autogen-bilals-fixed/83e79dafff20cf8bb9bbf4e0e4da6ed2/83e79dafff20cf8bb9bbf4e0e4da6ed2.eprime.essence index 66852001cf..8c8a2eb5f9 100644 --- a/tests/parse_print/autogen-bilals-fixed/83e79dafff20cf8bb9bbf4e0e4da6ed2/83e79dafff20cf8bb9bbf4e0e4da6ed2.eprime.essence +++ b/tests/parse_print/autogen-bilals-fixed/83e79dafff20cf8bb9bbf4e0e4da6ed2/83e79dafff20cf8bb9bbf4e0e4da6ed2.eprime.essence @@ -82,7 +82,7 @@ such that -> var1_FunctionAsRelation_RelationAsSet_ExplicitVarSizeWithMarker_Values_1_Function1DPartial_Flags[q1, ..] - - var2_ExplicitVarSizeWithMarker_Values[q10, ..] var2_ExplicitVarSizeWithMarker_Marker -> @@ -35,7 +35,7 @@ such that var5_ExplicitVarSizeWithFlags_Flags[1] >= -4, 1 = var5_ExplicitVarSizeWithFlags_Flags[1], and([var6_ExplicitVarSizeWithFlags_Flags[q23 + 1] -> - var6_ExplicitVarSizeWithFlags_Values[q23, ..] diff --git a/tests/parse_print/autogen-bilals-fixed/86302603127c6befda9307b173096b8d/86302603127c6befda9307b173096b8d.eprime.essence b/tests/parse_print/autogen-bilals-fixed/86302603127c6befda9307b173096b8d/86302603127c6befda9307b173096b8d.eprime.essence index 6acb8f4739..c4f0d1d43e 100644 --- a/tests/parse_print/autogen-bilals-fixed/86302603127c6befda9307b173096b8d/86302603127c6befda9307b173096b8d.eprime.essence +++ b/tests/parse_print/autogen-bilals-fixed/86302603127c6befda9307b173096b8d/86302603127c6befda9307b173096b8d.eprime.essence @@ -48,7 +48,7 @@ such that var3_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q10] = var3_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q10 + 1] /\ - var3_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q10, ..] var3_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> diff --git a/tests/parse_print/autogen-bilals-fixed/877d629f542f55f0f97157cd8c1654fe/877d629f542f55f0f97157cd8c1654fe.eprime.essence b/tests/parse_print/autogen-bilals-fixed/877d629f542f55f0f97157cd8c1654fe/877d629f542f55f0f97157cd8c1654fe.eprime.essence index a32347fb99..026652ffd5 100644 --- a/tests/parse_print/autogen-bilals-fixed/877d629f542f55f0f97157cd8c1654fe/877d629f542f55f0f97157cd8c1654fe.eprime.essence +++ b/tests/parse_print/autogen-bilals-fixed/877d629f542f55f0f97157cd8c1654fe/877d629f542f55f0f97157cd8c1654fe.eprime.essence @@ -82,7 +82,7 @@ such that -> var1_FunctionAsRelation_RelationAsSet_ExplicitVarSizeWithMarker_Values_1_Function1DPartial_Flags[q1, ..] - [5; int(1..1)]), (false, 1)) <=lex [0; int(1..1)] +such that image(function((true, 2) --> [5; int(1..1)]), (false, 1)) .<= [0; int(1..1)] diff --git a/tests/parse_print/autogen-bilals-fixed/88fb8c6b9616da911eaa4532629f05d7/88fb8c6b9616da911eaa4532629f05d7.eprime.essence b/tests/parse_print/autogen-bilals-fixed/88fb8c6b9616da911eaa4532629f05d7/88fb8c6b9616da911eaa4532629f05d7.eprime.essence index ec2955112a..b8527bd63b 100644 --- a/tests/parse_print/autogen-bilals-fixed/88fb8c6b9616da911eaa4532629f05d7/88fb8c6b9616da911eaa4532629f05d7.eprime.essence +++ b/tests/parse_print/autogen-bilals-fixed/88fb8c6b9616da911eaa4532629f05d7/88fb8c6b9616da911eaa4532629f05d7.eprime.essence @@ -35,7 +35,7 @@ such that /\ flatten(var2_PartitionAsSet_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMarker_Values[q4, .., ..]) - var2_PartitionAsSet_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMarker_Values[q6, q7, ..] - [false, false, true, false; int(2, 4..6)] <=lex + image(function({{true}} --> [false, false, true, false; int(2, 4..6)] .<= [true, false, true; int(2..3, 8..8)], ({} : `set of set of bool`) --> apart({false}, partition({true, false})), {({} : `set of bool`), {true}} --> {false, false} subset {true, false}), @@ -23,7 +23,7 @@ such that function(mset(3, 3, 1) --> (mset() : `mset of int`), (mset() : `mset of int`) --> mset(1, 2, 2))) < - (flatten([true, false, true, false; int(3..6)]) <=lex + (flatten([true, false, true, false; int(3..6)]) .<= [false < true, true <= true; int(4..5)]), [tuple (false), tuple (true), tuple (false), tuple (true); int(4, 10, 11, 9..9)][([] : `matrix indexed by [int] of int`)[factorial(4)], diff --git a/tests/parse_print/autogen-bilals-fixed/8b18b9af68196441a501019b9212cb97/8b18b9af68196441a501019b9212cb97.eprime.essence b/tests/parse_print/autogen-bilals-fixed/8b18b9af68196441a501019b9212cb97/8b18b9af68196441a501019b9212cb97.eprime.essence index cb8743c778..00294eae6b 100644 --- a/tests/parse_print/autogen-bilals-fixed/8b18b9af68196441a501019b9212cb97/8b18b9af68196441a501019b9212cb97.eprime.essence +++ b/tests/parse_print/autogen-bilals-fixed/8b18b9af68196441a501019b9212cb97/8b18b9af68196441a501019b9212cb97.eprime.essence @@ -1,5 +1,5 @@ language ESSENCE' 1.0 find unused: bool -such that [false, false; int(1..2)] = 1 | q26 : int(1..2)]), 2 <= var2_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - var2_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[1, ..] var2_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> and([var2_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q10, q19] = 2 diff --git a/tests/parse_print/autogen-bilals-fixed/8e57797389036cafd59682f3b212615f/8e57797389036cafd59682f3b212615f.eprime.essence b/tests/parse_print/autogen-bilals-fixed/8e57797389036cafd59682f3b212615f/8e57797389036cafd59682f3b212615f.eprime.essence index 5b44d223e6..7f7165322e 100644 --- a/tests/parse_print/autogen-bilals-fixed/8e57797389036cafd59682f3b212615f/8e57797389036cafd59682f3b212615f.eprime.essence +++ b/tests/parse_print/autogen-bilals-fixed/8e57797389036cafd59682f3b212615f/8e57797389036cafd59682f3b212615f.eprime.essence @@ -22,7 +22,7 @@ such that -> var1_FunctionAsRelation_RelationAsSet_ExplicitVarSizeWithMarker_Values_1_ExplicitVarSizeWithFlags_Flags[q1, ..] - true, false --> false, true --> false, true --> false, true --> true)), (partition({3}, {3, 4, 3, 5, 3}, {1, 4, 5, 1, 3}, {2, 2}, {1, 1}), tuple (true), ({} : `set of bool`), function(true --> false, false --> true, false --> true, false --> false)))), - flatten(flatten([false, false, false, false, true; int(3, 6, 2, 10, 1..1)])) ([] : `matrix indexed by [int] of bool`), [false; int(1..1)] --> [false, false; int(3, 0..0)], [true, false, true; int(6..8)] --> [true, false, false, false; int(2..3, 0, 11..11)], diff --git a/tests/parse_print/autogen-bilals-fixed/8f501dda2021fc3c7c4e001157f1e6e6/8f501dda2021fc3c7c4e001157f1e6e6.eprime.essence b/tests/parse_print/autogen-bilals-fixed/8f501dda2021fc3c7c4e001157f1e6e6/8f501dda2021fc3c7c4e001157f1e6e6.eprime.essence index 2b68ab80ef..032bc06452 100644 --- a/tests/parse_print/autogen-bilals-fixed/8f501dda2021fc3c7c4e001157f1e6e6/8f501dda2021fc3c7c4e001157f1e6e6.eprime.essence +++ b/tests/parse_print/autogen-bilals-fixed/8f501dda2021fc3c7c4e001157f1e6e6/8f501dda2021fc3c7c4e001157f1e6e6.eprime.essence @@ -18,7 +18,7 @@ maximising var4 such that and([q1 + 1 <= var1_ExplicitVarSizeWithMarker_Marker -> var1_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithFlags_Flags[q1, ..] - - flatten(var2_ExplicitVarSizeWithFlags_Values_RelationAsMatrix[q10, .., ..]) diff --git a/tests/parse_print/autogen-bilals-fixed/90320206b02563fde63fe692179aedbe/90320206b02563fde63fe692179aedbe.eprime.essence b/tests/parse_print/autogen-bilals-fixed/90320206b02563fde63fe692179aedbe/90320206b02563fde63fe692179aedbe.eprime.essence index c10ec2aaf4..ea7b525337 100644 --- a/tests/parse_print/autogen-bilals-fixed/90320206b02563fde63fe692179aedbe/90320206b02563fde63fe692179aedbe.eprime.essence +++ b/tests/parse_print/autogen-bilals-fixed/90320206b02563fde63fe692179aedbe/90320206b02563fde63fe692179aedbe.eprime.essence @@ -17,14 +17,14 @@ such that q_4_ExplicitVarSizeWithMarker_Values_Function1DPartial_Values : matrix indexed by [int(1..4), bool] of int(5..5), and([q1 + 1 <= q_4_ExplicitVarSizeWithMarker_Marker -> - q_4_ExplicitVarSizeWithMarker_Values_Function1DPartial_Flags[q1, ..] q_4_ExplicitVarSizeWithMarker_Marker -> @@ -53,7 +53,7 @@ such that >= 1 | q21 : int(1..8)]), and([q10 + 1 <= var1_PartitionAsSet_ExplicitVarSizeWithMarker_Marker -> - var1_PartitionAsSet_ExplicitVarSizeWithMarker_Values_Occurrence[q10, ..] var1_PartitionAsSet_ExplicitVarSizeWithMarker_Marker -> @@ -62,14 +62,14 @@ such that | q29 : int(0..2)]) | q11 : int(1..8)]), and([q14 + 1 <= var2_ExplicitVarSizeWithMarker_Marker -> - var2_ExplicitVarSizeWithMarker_Values_Function1DPartial_Flags[q14, ..] var2_ExplicitVarSizeWithMarker_Marker -> diff --git a/tests/parse_print/autogen-bilals-fixed/90955ca420084f220878f52c9a1671bc/90955ca420084f220878f52c9a1671bc.eprime.essence b/tests/parse_print/autogen-bilals-fixed/90955ca420084f220878f52c9a1671bc/90955ca420084f220878f52c9a1671bc.eprime.essence index 2a1cbc71af..636a4d1e79 100644 --- a/tests/parse_print/autogen-bilals-fixed/90955ca420084f220878f52c9a1671bc/90955ca420084f220878f52c9a1671bc.eprime.essence +++ b/tests/parse_print/autogen-bilals-fixed/90955ca420084f220878f52c9a1671bc/90955ca420084f220878f52c9a1671bc.eprime.essence @@ -158,7 +158,7 @@ such that (flatten(var2_PartitionAsSet_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMarker_Values_Function1DPartial_Flags[q1, .., ..]) - var2_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> diff --git a/tests/parse_print/autogen-bilals-fixed/93284da4a4bcb0b65f9af4e148349956/93284da4a4bcb0b65f9af4e148349956.eprime.essence b/tests/parse_print/autogen-bilals-fixed/93284da4a4bcb0b65f9af4e148349956/93284da4a4bcb0b65f9af4e148349956.eprime.essence index 139247214b..c499c2ff7a 100644 --- a/tests/parse_print/autogen-bilals-fixed/93284da4a4bcb0b65f9af4e148349956/93284da4a4bcb0b65f9af4e148349956.eprime.essence +++ b/tests/parse_print/autogen-bilals-fixed/93284da4a4bcb0b65f9af4e148349956/93284da4a4bcb0b65f9af4e148349956.eprime.essence @@ -34,7 +34,7 @@ such that /\ (var4_ExplicitVarSizeWithFlagsR17R5R5_Values_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker [q3, ..] - - var5_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Flags[q12, ..] var5_ExplicitVarSizeWithMarkerR4_Marker -> diff --git a/tests/parse_print/autogen-bilals-fixed/951d3c18901f9994c032518bb08cd59c/951d3c18901f9994c032518bb08cd59c.eprime.essence b/tests/parse_print/autogen-bilals-fixed/951d3c18901f9994c032518bb08cd59c/951d3c18901f9994c032518bb08cd59c.eprime.essence index f7ba19e35f..7d5c2dedc9 100644 --- a/tests/parse_print/autogen-bilals-fixed/951d3c18901f9994c032518bb08cd59c/951d3c18901f9994c032518bb08cd59c.eprime.essence +++ b/tests/parse_print/autogen-bilals-fixed/951d3c18901f9994c032518bb08cd59c/951d3c18901f9994c032518bb08cd59c.eprime.essence @@ -13,7 +13,7 @@ such that -> var1_FunctionAsRelation_RelationAsSet_ExplicitVarSizeWithMarker_Values_1_Occurrence[q1, ..] - = 1 | q34 : int(1..4)]), and([q7 + 1 <= var2_1_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> - var2_1_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q7, ..] var2_1_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> @@ -95,14 +95,14 @@ such that and([var4_1_ExplicitWithFlags_Flags[q15] = 0 \/ var4_1_ExplicitWithFlags_Flags[q15] >= 0 | q15 : int(1..3)]), 3 = sum([var4_1_ExplicitWithFlags_Flags[q16] | q16 : int(1..3)]), and([var5_ExplicitWithFlagsR10_Flags[q18 + 1] > 0 -> - var5_ExplicitWithFlagsR10_Values_Function1DPartial_Flags[q18, ..] diff --git a/tests/parse_print/autogen-bilals-fixed/961d1c03df4f6fdf5a4b8bfa8fb85d14/961d1c03df4f6fdf5a4b8bfa8fb85d14.eprime.essence b/tests/parse_print/autogen-bilals-fixed/961d1c03df4f6fdf5a4b8bfa8fb85d14/961d1c03df4f6fdf5a4b8bfa8fb85d14.eprime.essence index 7542b9cd75..e63311912c 100644 --- a/tests/parse_print/autogen-bilals-fixed/961d1c03df4f6fdf5a4b8bfa8fb85d14/961d1c03df4f6fdf5a4b8bfa8fb85d14.eprime.essence +++ b/tests/parse_print/autogen-bilals-fixed/961d1c03df4f6fdf5a4b8bfa8fb85d14/961d1c03df4f6fdf5a4b8bfa8fb85d14.eprime.essence @@ -43,7 +43,7 @@ such that 2 <= sum([var2_FunctionNDPartial_Flags[q22_1] | q22_1 : bool]), and([var3_ExplicitVarSizeWithFlags_Flags[q24 + 1] > 0 -> var3_ExplicitVarSizeWithFlags_Values_ExplicitVarSizeWithFlags_Flags[q24, ..] - true) <-> false <= false) -> - [true; int(2..2)] <=lex + [true; int(2..2)] .<= [false, true, false, true, false; int(11..12, 7, 13, 14..14)] diff --git a/tests/parse_print/autogen-bilals-fixed/979854a979c1d69c3dc6653f5b2db319/979854a979c1d69c3dc6653f5b2db319.eprime.essence b/tests/parse_print/autogen-bilals-fixed/979854a979c1d69c3dc6653f5b2db319/979854a979c1d69c3dc6653f5b2db319.eprime.essence index 45e865db79..fd919e8cf9 100644 --- a/tests/parse_print/autogen-bilals-fixed/979854a979c1d69c3dc6653f5b2db319/979854a979c1d69c3dc6653f5b2db319.eprime.essence +++ b/tests/parse_print/autogen-bilals-fixed/979854a979c1d69c3dc6653f5b2db319/979854a979c1d69c3dc6653f5b2db319.eprime.essence @@ -24,7 +24,7 @@ such that /\ var1_FunctionAsRelation_RelationAsSet_ExplicitVarSizeWithMarker_Values_1_ExplicitVarSizeWithMarker_Values[q1, ..] - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> diff --git a/tests/parse_print/autogen-bilals-fixed/9abdea7380788d3969dc2640d22d213c/9abdea7380788d3969dc2640d22d213c.essence b/tests/parse_print/autogen-bilals-fixed/9abdea7380788d3969dc2640d22d213c/9abdea7380788d3969dc2640d22d213c.essence index 68c7e158f7..d43b98aa8f 100644 --- a/tests/parse_print/autogen-bilals-fixed/9abdea7380788d3969dc2640d22d213c/9abdea7380788d3969dc2640d22d213c.essence +++ b/tests/parse_print/autogen-bilals-fixed/9abdea7380788d3969dc2640d22d213c/9abdea7380788d3969dc2640d22d213c.essence @@ -7,7 +7,7 @@ such that (partition() : `partition from int`)) != (relation((false, false, true, false)), mset(true), partition({5, 2, 1, 2}))) != - (([true, false; int(5, 4..4)] relation((true, false, true), @@ -42,7 +42,7 @@ such that true, [[true, true; int(0..1)], [true, true, true; int(1..2, 8..8)], [true; int(1..1)]; int(2, 4..5)][freq(mset(false), false <= true)] - var1_FunctionAsRelation_RelationAsSet_ExplicitVarSizeWithMarker_Values_1_Function1DPartial_Flags[q1, ..] - = 1 | q24 : int(1..16)]), and([q6 + 1 <= var2_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - var2_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q6, ..] var2_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> diff --git a/tests/parse_print/autogen-bilals-fixed/9c55294c0d3d31ba76c9c8253bef3ef8/9c55294c0d3d31ba76c9c8253bef3ef8.eprime.essence b/tests/parse_print/autogen-bilals-fixed/9c55294c0d3d31ba76c9c8253bef3ef8/9c55294c0d3d31ba76c9c8253bef3ef8.eprime.essence index 4c451aad65..fa92a66410 100644 --- a/tests/parse_print/autogen-bilals-fixed/9c55294c0d3d31ba76c9c8253bef3ef8/9c55294c0d3d31ba76c9c8253bef3ef8.eprime.essence +++ b/tests/parse_print/autogen-bilals-fixed/9c55294c0d3d31ba76c9c8253bef3ef8/9c55294c0d3d31ba76c9c8253bef3ef8.eprime.essence @@ -28,7 +28,7 @@ such that var1_PartitionAsSet_ExplicitR5_ExplicitVarSizeWithMarker_Marker[1], var1_PartitionAsSet_ExplicitR5_ExplicitVarSizeWithMarker_Marker[1] >= 1, and([q8 + 1 <= var1_PartitionAsSet_ExplicitR5_ExplicitVarSizeWithMarker_Marker[1] -> - var1_PartitionAsSet_ExplicitR5_ExplicitVarSizeWithMarker_Values[1, q8, ..] var1_PartitionAsSet_ExplicitR5_ExplicitVarSizeWithMarker_Marker[1] -> @@ -36,14 +36,14 @@ such that | q9 : int(1..24)]), var1_PartitionAsSet_ExplicitR5_ExplicitVarSizeWithMarker_Marker[1] <= 24, and([q13 + 1 <= var2_ExplicitVarSizeWithMarkerR10_Marker -> - var2_ExplicitVarSizeWithMarkerR10_Values_Function1DPartial_Flags[q13, ..] var2_ExplicitVarSizeWithMarkerR10_Marker -> @@ -85,7 +85,7 @@ such that var4_1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q36] = var4_1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q36 + 1] /\ - var4_1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q36, ..] var4_1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> diff --git a/tests/parse_print/autogen-bilals-fixed/9cc3198933cb09006cb5dbb960f49f95/9cc3198933cb09006cb5dbb960f49f95.eprime.essence b/tests/parse_print/autogen-bilals-fixed/9cc3198933cb09006cb5dbb960f49f95/9cc3198933cb09006cb5dbb960f49f95.eprime.essence index 276eea6765..6afdd61c3d 100644 --- a/tests/parse_print/autogen-bilals-fixed/9cc3198933cb09006cb5dbb960f49f95/9cc3198933cb09006cb5dbb960f49f95.eprime.essence +++ b/tests/parse_print/autogen-bilals-fixed/9cc3198933cb09006cb5dbb960f49f95/9cc3198933cb09006cb5dbb960f49f95.eprime.essence @@ -35,7 +35,7 @@ such that var1_FunctionAsRelation_RelationAsSet_ExplicitVarSizeWithMarker_Marker -> var1_FunctionAsRelation_RelationAsSet_ExplicitVarSizeWithMarker_Values_1[q1, ..] - var1_ExplicitVarSizeWithMarkerR8_Marker -> @@ -76,7 +76,7 @@ such that var3_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q18] = var3_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q18 + 1] /\ - var3_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values_1[q18, ..] var3_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> diff --git a/tests/parse_print/autogen-bilals-fixed/9f0da0c4289dcd010e92c8ab6d50b07a/9f0da0c4289dcd010e92c8ab6d50b07a.eprime.essence b/tests/parse_print/autogen-bilals-fixed/9f0da0c4289dcd010e92c8ab6d50b07a/9f0da0c4289dcd010e92c8ab6d50b07a.eprime.essence index c0600ad25f..21b7a9701b 100644 --- a/tests/parse_print/autogen-bilals-fixed/9f0da0c4289dcd010e92c8ab6d50b07a/9f0da0c4289dcd010e92c8ab6d50b07a.eprime.essence +++ b/tests/parse_print/autogen-bilals-fixed/9f0da0c4289dcd010e92c8ab6d50b07a/9f0da0c4289dcd010e92c8ab6d50b07a.eprime.essence @@ -9,7 +9,7 @@ find var1_ExplicitVarSizeWithFlags_Values_ExplicitVarSizeWithFlags_Values_Explic matrix indexed by [int(1..3), int(1..5), int(1..1)] of bool such that and([var1_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - var1_ExplicitVarSizeWithFlags_Values_ExplicitVarSizeWithFlags_Flags[q1, ..] var1_FunctionAsRelation_RelationAsSet_ExplicitVarSizeWithMarker_Values_1_Function1DPartial_Flags[q1, ..] - var1_1_PartitionAsSet_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMarker_Values_Function1D[q6, q7, ..] - - flatten(var1_RelationAsSetR15_ExplicitVarSizeWithMarkerR15_Values_1_RelationAsMatrix[q1, .., ..]) var1_RelationAsSetR15_ExplicitVarSizeWithMarkerR15_Marker -> @@ -54,7 +54,7 @@ such that var2_RelationAsSet_ExplicitVarSizeWithMarker_Values_2[q8] = var2_RelationAsSet_ExplicitVarSizeWithMarker_Values_2[q8 + 1] /\ - var2_RelationAsSet_ExplicitVarSizeWithMarker_Values_3[q8, ..] var2_RelationAsSet_ExplicitVarSizeWithMarker_Marker -> diff --git a/tests/parse_print/autogen-bilals-fixed/a278490eff4c7aaa3efb73ab7cb5a355/a278490eff4c7aaa3efb73ab7cb5a355.eprime.essence b/tests/parse_print/autogen-bilals-fixed/a278490eff4c7aaa3efb73ab7cb5a355/a278490eff4c7aaa3efb73ab7cb5a355.eprime.essence index 1bd6b1e635..c7375bb8d3 100644 --- a/tests/parse_print/autogen-bilals-fixed/a278490eff4c7aaa3efb73ab7cb5a355/a278490eff4c7aaa3efb73ab7cb5a355.eprime.essence +++ b/tests/parse_print/autogen-bilals-fixed/a278490eff4c7aaa3efb73ab7cb5a355/a278490eff4c7aaa3efb73ab7cb5a355.eprime.essence @@ -32,14 +32,14 @@ such that | q10 : int(1..9)]), 3 <= sum([var3_2_ExplicitVarSizeWithFlags_Flags[q12] | q12 : int(1..10)]), and([q14 + 1 <= var4_RelationAsSet_ExplicitVarSizeWithMarker_Marker -> - var4_RelationAsSet_ExplicitVarSizeWithMarker_Values_1[q14, ..] flatten(var2_PartitionAsSet_ExplicitVarSizeWithMarker_Values_Explicit_ExplicitVarSizeWithFlags_Flags[q13, .., ..]) - var1_FunctionAsRelation_RelationAsSet_ExplicitVarSizeWithMarker_Values_1_ExplicitVarSizeWithFlags_Flags[q1, ..] - - flatten(var2_ExplicitVarSizeWithMarker_Values_RelationAsMatrix[q8, .., ..]) var2_ExplicitVarSizeWithMarker_Marker -> diff --git a/tests/parse_print/autogen-bilals-fixed/a34c8275c1d9524a08d2ec1d329ed35a/a34c8275c1d9524a08d2ec1d329ed35a.eprime.essence b/tests/parse_print/autogen-bilals-fixed/a34c8275c1d9524a08d2ec1d329ed35a/a34c8275c1d9524a08d2ec1d329ed35a.eprime.essence index 17d67128e8..3865376345 100644 --- a/tests/parse_print/autogen-bilals-fixed/a34c8275c1d9524a08d2ec1d329ed35a/a34c8275c1d9524a08d2ec1d329ed35a.eprime.essence +++ b/tests/parse_print/autogen-bilals-fixed/a34c8275c1d9524a08d2ec1d329ed35a/a34c8275c1d9524a08d2ec1d329ed35a.eprime.essence @@ -83,7 +83,7 @@ such that -> var1_FunctionAsRelation_RelationAsSet_ExplicitVarSizeWithMarker_Values_1_Function1DPartial_Flags[q1, ..] - = 1 | q56 : int(1..4)]), and([q7 + 1 <= var2_1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - var2_1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q7, ..] var2_1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> @@ -123,14 +123,14 @@ such that | q17 : int(1..9)]), 3 = var4_1_ExplicitWithRepetition_Flag, and([q24 + 1 <= var5_ExplicitWithRepetitionR10_Flag -> - var5_ExplicitWithRepetitionR10_Values_Function1DPartial_Flags[q24, ..] var5_ExplicitWithRepetitionR10_Flag -> diff --git a/tests/parse_print/autogen-bilals-fixed/a370966830e4e6e3d5c258cbed1908e2/a370966830e4e6e3d5c258cbed1908e2.eprime.essence b/tests/parse_print/autogen-bilals-fixed/a370966830e4e6e3d5c258cbed1908e2/a370966830e4e6e3d5c258cbed1908e2.eprime.essence index d124421881..69f2d36e65 100644 --- a/tests/parse_print/autogen-bilals-fixed/a370966830e4e6e3d5c258cbed1908e2/a370966830e4e6e3d5c258cbed1908e2.eprime.essence +++ b/tests/parse_print/autogen-bilals-fixed/a370966830e4e6e3d5c258cbed1908e2/a370966830e4e6e3d5c258cbed1908e2.eprime.essence @@ -157,7 +157,7 @@ such that (flatten(var1_PartitionAsSet_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMarker_Values_Function1DPartial_Flags[q1, .., ..]) - = 1 | q37 : int(1..4)]), and([q7 + 1 <= var2_1_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> - var2_1_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q7, ..] var2_1_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> @@ -108,14 +108,14 @@ such that | q14 : int(1..9)]), 3 = var4_1_ExplicitWithRepetition_Flag, and([var5_ExplicitWithFlagsR10_Flags[q21 + 1] > 0 -> - var5_ExplicitWithFlagsR10_Values_Function1DPartial_Flags[q21, ..] diff --git a/tests/parse_print/autogen-bilals-fixed/a569624863aa273c01c6312a624723f1/a569624863aa273c01c6312a624723f1.eprime.essence b/tests/parse_print/autogen-bilals-fixed/a569624863aa273c01c6312a624723f1/a569624863aa273c01c6312a624723f1.eprime.essence index 70dd846378..0d13abef49 100644 --- a/tests/parse_print/autogen-bilals-fixed/a569624863aa273c01c6312a624723f1/a569624863aa273c01c6312a624723f1.eprime.essence +++ b/tests/parse_print/autogen-bilals-fixed/a569624863aa273c01c6312a624723f1/a569624863aa273c01c6312a624723f1.eprime.essence @@ -66,7 +66,7 @@ such that /\ var3_2_PartitionAsSet_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMarker_Values[q3, ..] - var2_PartitionAsSet_ExplicitVarSizeWithMarker_Values_Explicit_ExplicitVarSizeWithMarker_Marker[q4, ..] - var1_FunctionAsRelation_RelationAsSet_ExplicitVarSizeWithMarker_Values_1_Function1DPartial_Flags[q1, ..] - var5_RelationAsSet_ExplicitVarSizeWithMarker_Marker -> @@ -69,7 +69,7 @@ such that /\ flatten(var6_ExplicitVarSizeWithFlags_Values_PartitionAsSet_ExplicitVarSizeWithMarker_Values_Explicit[1, .., ..]) - @@ -90,7 +90,7 @@ such that -> var6_ExplicitVarSizeWithFlags_Values_PartitionAsSet_ExplicitVarSizeWithMarker_Values_Explicit[q11, q15, ..] - var1_PartitionAsSet_Explicit_ExplicitVarSizeWithMarker_Values_Explicit[1, q8, ..] - 0 -> flatten(var2_ExplicitVarSizeWithFlags_Values_RelationAsMatrix[q13, .., .., .., ..]) - var2_FunctionAsRelation_RelationAsSet_ExplicitVarSizeWithMarker_Values_1_ExplicitVarSizeWithFlags_Flags[q1, ..] - var1_PartitionAsSet_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMarker_Values_Occurrence[q7, q8, ..] - - var1_ExplicitVarSizeWithMarker_Values_Function1D[q1, ..] var1_ExplicitVarSizeWithMarker_Marker -> @@ -67,7 +67,7 @@ such that and([q10 + 1 <= var2_PartitionAsSet_ExplicitVarSizeWithMarker_Marker -> flatten(var2_PartitionAsSet_ExplicitVarSizeWithMarker_Values_Explicit_ExplicitVarSizeWithFlags_Flags[q10, .., ..]) - - var2_RelationAsSet_ExplicitVarSizeWithMarker_Values_1_Occurrence[q1, ..] tuple (mset(false, false)), false --> tuple (mset(true, false, false))), - [4 | l_1 : int(5..5, 3), l_2 : int(3, 4)] <=lex [3, 4, 1, 0; int(1, 6..8)])[1] + [4 | l_1 : int(5..5, 3), l_2 : int(3, 4)] .<= [3, 4, 1, 0; int(1, 6..8)])[1] supsetEq mset(true), (function() : `function relation of (mset of bool * matrix indexed by [int] of relation of (bool * function bool --> int * bool) * diff --git a/tests/parse_print/autogen-bilals-fixed/b3e5efec04851a6556b23a0d4a9f50d0/b3e5efec04851a6556b23a0d4a9f50d0.eprime.essence b/tests/parse_print/autogen-bilals-fixed/b3e5efec04851a6556b23a0d4a9f50d0/b3e5efec04851a6556b23a0d4a9f50d0.eprime.essence index cfce4a54e4..7ca8130a98 100644 --- a/tests/parse_print/autogen-bilals-fixed/b3e5efec04851a6556b23a0d4a9f50d0/b3e5efec04851a6556b23a0d4a9f50d0.eprime.essence +++ b/tests/parse_print/autogen-bilals-fixed/b3e5efec04851a6556b23a0d4a9f50d0/b3e5efec04851a6556b23a0d4a9f50d0.eprime.essence @@ -32,7 +32,7 @@ such that -> var1_PartitionAsSet_Explicit_ExplicitVarSizeWithMarker_Values_Function1D[1, q6, ..] - flatten(var3_ExplicitVarSizeWithFlags_Values_RelationAsMatrix[1, .., .., .., ..]) - diff --git a/tests/parse_print/autogen-bilals-fixed/b427cac47c65e49ff32c22d2b3e8c19b/b427cac47c65e49ff32c22d2b3e8c19b.eprime.essence b/tests/parse_print/autogen-bilals-fixed/b427cac47c65e49ff32c22d2b3e8c19b/b427cac47c65e49ff32c22d2b3e8c19b.eprime.essence index f0a1803bda..97675baa7a 100644 --- a/tests/parse_print/autogen-bilals-fixed/b427cac47c65e49ff32c22d2b3e8c19b/b427cac47c65e49ff32c22d2b3e8c19b.eprime.essence +++ b/tests/parse_print/autogen-bilals-fixed/b427cac47c65e49ff32c22d2b3e8c19b/b427cac47c65e49ff32c22d2b3e8c19b.eprime.essence @@ -4,5 +4,5 @@ find var1: int(2, 3..5) such that [[true, false, false, true; int(1..1, 3..3, 9..9, 11..11)], [true, true; int(0..0, 5..5)]; int(1..2)][var1, ..] - <=lex [true; int(1..1)] + .<= [true; int(1..1)] diff --git a/tests/parse_print/autogen-bilals-fixed/b6716decf75eddda33df3ec06f7cc400/b6716decf75eddda33df3ec06f7cc400.eprime.essence b/tests/parse_print/autogen-bilals-fixed/b6716decf75eddda33df3ec06f7cc400/b6716decf75eddda33df3ec06f7cc400.eprime.essence index cffd5b42d2..6e83b0addd 100644 --- a/tests/parse_print/autogen-bilals-fixed/b6716decf75eddda33df3ec06f7cc400/b6716decf75eddda33df3ec06f7cc400.eprime.essence +++ b/tests/parse_print/autogen-bilals-fixed/b6716decf75eddda33df3ec06f7cc400/b6716decf75eddda33df3ec06f7cc400.eprime.essence @@ -16,7 +16,7 @@ find var5_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker: find var5_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4), int(1..5)] of bool such that - [var3; int(0..0)] var5_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q10] < @@ -25,7 +25,7 @@ such that var5_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q10] = var5_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q10 + 1] /\ - var5_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q10, ..] var5_ExplicitVarSizeWithMarkerR5_Marker -> diff --git a/tests/parse_print/autogen-bilals-fixed/b68ea8a7e4351cdfc4b3b75bb6582893/b68ea8a7e4351cdfc4b3b75bb6582893.eprime.essence b/tests/parse_print/autogen-bilals-fixed/b68ea8a7e4351cdfc4b3b75bb6582893/b68ea8a7e4351cdfc4b3b75bb6582893.eprime.essence index e4f8633b2b..4129ea3b7e 100644 --- a/tests/parse_print/autogen-bilals-fixed/b68ea8a7e4351cdfc4b3b75bb6582893/b68ea8a7e4351cdfc4b3b75bb6582893.eprime.essence +++ b/tests/parse_print/autogen-bilals-fixed/b68ea8a7e4351cdfc4b3b75bb6582893/b68ea8a7e4351cdfc4b3b75bb6582893.eprime.essence @@ -17,7 +17,7 @@ find var6: int(1..4, 4..5) maximising var4 such that and([var1_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - var1_ExplicitVarSizeWithFlags_Values_ExplicitVarSizeWithFlags_Flags[q1, ..] @@ -81,7 +81,7 @@ such that | q10 : int(1..4)]) | q5 : int(1..81)]), and([var2_ExplicitVarSizeWithFlags_Flags[q12 + 1] -> - flatten(var2_ExplicitVarSizeWithFlags_Values_RelationAsMatrix[q12, .., ..]) diff --git a/tests/parse_print/autogen-bilals-fixed/b7ca13696cd34ed7006ef9dfac6d66ff/b7ca13696cd34ed7006ef9dfac6d66ff.eprime.essence b/tests/parse_print/autogen-bilals-fixed/b7ca13696cd34ed7006ef9dfac6d66ff/b7ca13696cd34ed7006ef9dfac6d66ff.eprime.essence index edfcbad9cc..12436243a8 100644 --- a/tests/parse_print/autogen-bilals-fixed/b7ca13696cd34ed7006ef9dfac6d66ff/b7ca13696cd34ed7006ef9dfac6d66ff.eprime.essence +++ b/tests/parse_print/autogen-bilals-fixed/b7ca13696cd34ed7006ef9dfac6d66ff/b7ca13696cd34ed7006ef9dfac6d66ff.eprime.essence @@ -60,21 +60,21 @@ such that var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q4] = var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q4 + 1] /\ - (var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values_1[q4, ..] var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> diff --git a/tests/parse_print/autogen-bilals-fixed/b7eff6ada58015f7994346e5ca41950c/b7eff6ada58015f7994346e5ca41950c.eprime.essence b/tests/parse_print/autogen-bilals-fixed/b7eff6ada58015f7994346e5ca41950c/b7eff6ada58015f7994346e5ca41950c.eprime.essence index cd19c972eb..4bab004604 100644 --- a/tests/parse_print/autogen-bilals-fixed/b7eff6ada58015f7994346e5ca41950c/b7eff6ada58015f7994346e5ca41950c.eprime.essence +++ b/tests/parse_print/autogen-bilals-fixed/b7eff6ada58015f7994346e5ca41950c/b7eff6ada58015f7994346e5ca41950c.eprime.essence @@ -28,7 +28,7 @@ such that /\ flatten(var2_PartitionAsSetR2_ExplicitVarSizeWithMarkerR5R2_Values_ExplicitVarSizeWithMarkerR2_Values_Occurrence [q4, .., ..]) - - var1_ExplicitVarSizeWithFlags_Values_ExplicitVarSizeWithFlags_Flags[q1, ..] @@ -82,7 +82,7 @@ such that | q5 : int(1..81)]), and([q12 + 1 <= var2_ExplicitVarSizeWithMarker_Marker -> flatten(var2_ExplicitVarSizeWithMarker_Values_RelationAsMatrix[q12, .., ..]) - var2_ExplicitVarSizeWithMarker_Marker -> diff --git a/tests/parse_print/autogen-bilals-fixed/be5b5a644521be5b55c6a12c503cad3a/be5b5a644521be5b55c6a12c503cad3a.eprime.essence b/tests/parse_print/autogen-bilals-fixed/be5b5a644521be5b55c6a12c503cad3a/be5b5a644521be5b55c6a12c503cad3a.eprime.essence index e8d09cdeae..33b174a4b8 100644 --- a/tests/parse_print/autogen-bilals-fixed/be5b5a644521be5b55c6a12c503cad3a/be5b5a644521be5b55c6a12c503cad3a.eprime.essence +++ b/tests/parse_print/autogen-bilals-fixed/be5b5a644521be5b55c6a12c503cad3a/be5b5a644521be5b55c6a12c503cad3a.eprime.essence @@ -172,7 +172,7 @@ such that (flatten(var4_PartitionAsSet_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMarker_Values_Function1DPartial_Flags[q8, .., ..]) - = 1 | q31 : int(1..2)]), 2 <= var6_PartitionAsSet_ExplicitVarSizeWithMarker_Marker -> - var6_PartitionAsSet_ExplicitVarSizeWithMarker_Values_Occurrence[1, ..] var6_PartitionAsSet_ExplicitVarSizeWithMarker_Marker -> var6_PartitionAsSet_ExplicitVarSizeWithMarker_Values_Occurrence[q22, 2] = false diff --git a/tests/parse_print/autogen-bilals-fixed/bfd00aba95070795c7a808361a3c495d/bfd00aba95070795c7a808361a3c495d.eprime.essence b/tests/parse_print/autogen-bilals-fixed/bfd00aba95070795c7a808361a3c495d/bfd00aba95070795c7a808361a3c495d.eprime.essence index 61bd3df424..7e29b3e0b4 100644 --- a/tests/parse_print/autogen-bilals-fixed/bfd00aba95070795c7a808361a3c495d/bfd00aba95070795c7a808361a3c495d.eprime.essence +++ b/tests/parse_print/autogen-bilals-fixed/bfd00aba95070795c7a808361a3c495d/bfd00aba95070795c7a808361a3c495d.eprime.essence @@ -11,7 +11,7 @@ find var2_PartitionAsSet_ExplicitVarSizeWithMarker_Values_Explicit_ExplicitVarSi such that false, and([var1_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - var1_ExplicitVarSizeWithFlags_Values_Function1D[q1, ..] @@ -71,7 +71,7 @@ such that and([q12 + 1 <= var2_PartitionAsSet_ExplicitVarSizeWithMarker_Marker -> var2_PartitionAsSet_ExplicitVarSizeWithMarker_Values_Explicit_ExplicitVarSizeWithMarker_Marker[q12, ..] - var2_RelationAsSet_ExplicitVarSizeWithMarker_Values_1_ExplicitVarSizeWithFlags_Flags[q1, ..] - var1_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithFlags_Flags[q1, ..] - flatten(var2_ExplicitVarSizeWithMarker_Values_RelationAsMatrix[q10, .., ..]) - var2_ExplicitVarSizeWithMarker_Marker -> diff --git a/tests/parse_print/autogen-bilals-fixed/c3841e1877c34e8e5bfd1c1837d307e1/c3841e1877c34e8e5bfd1c1837d307e1.eprime.essence b/tests/parse_print/autogen-bilals-fixed/c3841e1877c34e8e5bfd1c1837d307e1/c3841e1877c34e8e5bfd1c1837d307e1.eprime.essence index 6242404d83..d10dd17984 100644 --- a/tests/parse_print/autogen-bilals-fixed/c3841e1877c34e8e5bfd1c1837d307e1/c3841e1877c34e8e5bfd1c1837d307e1.eprime.essence +++ b/tests/parse_print/autogen-bilals-fixed/c3841e1877c34e8e5bfd1c1837d307e1/c3841e1877c34e8e5bfd1c1837d307e1.eprime.essence @@ -55,7 +55,7 @@ such that /\ var3_PartitionAsSet_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMarker_Values[q17, ..] - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> diff --git a/tests/parse_print/autogen-bilals-fixed/c5272f0460d36d154f10770be9088fa4/c5272f0460d36d154f10770be9088fa4.eprime.essence b/tests/parse_print/autogen-bilals-fixed/c5272f0460d36d154f10770be9088fa4/c5272f0460d36d154f10770be9088fa4.eprime.essence index 72feda5a4c..eca4fe72a3 100644 --- a/tests/parse_print/autogen-bilals-fixed/c5272f0460d36d154f10770be9088fa4/c5272f0460d36d154f10770be9088fa4.eprime.essence +++ b/tests/parse_print/autogen-bilals-fixed/c5272f0460d36d154f10770be9088fa4/c5272f0460d36d154f10770be9088fa4.eprime.essence @@ -60,21 +60,21 @@ such that var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q4] = var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q4 + 1] /\ - (var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values_1[q4, ..] var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> diff --git a/tests/parse_print/autogen-bilals-fixed/c539dc840839e54f8d3d5ca53104102f/c539dc840839e54f8d3d5ca53104102f.eprime.essence b/tests/parse_print/autogen-bilals-fixed/c539dc840839e54f8d3d5ca53104102f/c539dc840839e54f8d3d5ca53104102f.eprime.essence index 567d2164ee..d431d4789b 100644 --- a/tests/parse_print/autogen-bilals-fixed/c539dc840839e54f8d3d5ca53104102f/c539dc840839e54f8d3d5ca53104102f.eprime.essence +++ b/tests/parse_print/autogen-bilals-fixed/c539dc840839e54f8d3d5ca53104102f/c539dc840839e54f8d3d5ca53104102f.eprime.essence @@ -33,7 +33,7 @@ such that and([q4 + 1 <= var2_PartitionAsSet_ExplicitVarSizeWithMarker_Marker -> flatten(var2_PartitionAsSet_ExplicitVarSizeWithMarker_Values_Explicit_Occurrence[q4, .., ..]) - - var1_FunctionAsRelationR3R4_RelationAsSetR3R4_ExplicitVarSizeWithMarkerR3R4_Values_1_Explicit[q6, ..] - (var1_FunctionAsRelationR3R4_RelationAsSetR3R4_ExplicitVarSizeWithMarkerR3R4_Values_1_Explicit[q36, ..] or([var1_FunctionAsRelationR3R4_RelationAsSetR3R4_ExplicitVarSizeWithMarkerR3R4_Values_2_ExplicitVarSizeWithFlags_Flags diff --git a/tests/parse_print/autogen-bilals-fixed/c7a05c6406dc0bf72a24b7344bf05115/c7a05c6406dc0bf72a24b7344bf05115.eprime.essence b/tests/parse_print/autogen-bilals-fixed/c7a05c6406dc0bf72a24b7344bf05115/c7a05c6406dc0bf72a24b7344bf05115.eprime.essence index 2a6fd61057..65ab4a4526 100644 --- a/tests/parse_print/autogen-bilals-fixed/c7a05c6406dc0bf72a24b7344bf05115/c7a05c6406dc0bf72a24b7344bf05115.eprime.essence +++ b/tests/parse_print/autogen-bilals-fixed/c7a05c6406dc0bf72a24b7344bf05115/c7a05c6406dc0bf72a24b7344bf05115.eprime.essence @@ -9,14 +9,14 @@ such that q_4_ExplicitVarSizeWithMarker_Values_Function1DPartial_Values : matrix indexed by [int(1..4), bool] of int(5..5), and([q1 + 1 <= q_4_ExplicitVarSizeWithMarker_Marker -> - q_4_ExplicitVarSizeWithMarker_Values_Function1DPartial_Flags[q1, ..] q_4_ExplicitVarSizeWithMarker_Marker -> diff --git a/tests/parse_print/autogen-bilals-fixed/c7bab02871b463a4b24d6530e2009c74/c7bab02871b463a4b24d6530e2009c74.eprime.essence b/tests/parse_print/autogen-bilals-fixed/c7bab02871b463a4b24d6530e2009c74/c7bab02871b463a4b24d6530e2009c74.eprime.essence index c698ee6ccd..a6ce2c44e6 100644 --- a/tests/parse_print/autogen-bilals-fixed/c7bab02871b463a4b24d6530e2009c74/c7bab02871b463a4b24d6530e2009c74.eprime.essence +++ b/tests/parse_print/autogen-bilals-fixed/c7bab02871b463a4b24d6530e2009c74/c7bab02871b463a4b24d6530e2009c74.eprime.essence @@ -81,7 +81,7 @@ such that /\ (var1_PartitionAsSet_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMarker_Marker[q5, ..] - var1_FunctionAsRelation_RelationAsSet_ExplicitVarSizeWithMarker_Values_1_Function1DPartial_Flags[q1, ..] - - var1_ExplicitVarSizeWithMarker_Values_Function1D[q1, ..] var1_ExplicitVarSizeWithMarker_Marker -> @@ -56,7 +56,7 @@ such that and([q10 + 1 <= var2_PartitionAsSet_ExplicitVarSizeWithMarker_Marker -> flatten(var2_PartitionAsSet_ExplicitVarSizeWithMarker_Values_Explicit_Occurrence[q10, .., ..]) - var2_1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> @@ -128,14 +128,14 @@ such that | q16 : int(1..9)]), 3 = var4_1_ExplicitWithRepetition_Flag, and([var5_ExplicitWithFlagsR10_Flags[q23 + 1] > 0 -> - var5_ExplicitWithFlagsR10_Values_Function1DPartial_Flags[q23, ..] diff --git a/tests/parse_print/autogen-bilals-fixed/c9e1cd7a71dc9c900ce717378a2e7326/c9e1cd7a71dc9c900ce717378a2e7326.eprime.essence b/tests/parse_print/autogen-bilals-fixed/c9e1cd7a71dc9c900ce717378a2e7326/c9e1cd7a71dc9c900ce717378a2e7326.eprime.essence index c5696d3331..378c7fca76 100644 --- a/tests/parse_print/autogen-bilals-fixed/c9e1cd7a71dc9c900ce717378a2e7326/c9e1cd7a71dc9c900ce717378a2e7326.eprime.essence +++ b/tests/parse_print/autogen-bilals-fixed/c9e1cd7a71dc9c900ce717378a2e7326/c9e1cd7a71dc9c900ce717378a2e7326.eprime.essence @@ -36,7 +36,7 @@ such that and([q4 + 1 <= var2_PartitionAsSet_ExplicitVarSizeWithMarker_Marker -> flatten(var2_PartitionAsSet_ExplicitVarSizeWithMarker_Values_Explicit_Occurrence[q4, .., ..]) - false), var1 <=lex [true, true, true; int(2, 4, 0..0)]), + image(function(true --> false), var1 .<= [true, true, true; int(2, 4, 0..0)]), image(function({true} --> false, {true} --> false), {true <-> false}), together({relation((true, true))}, partition({relation((true, false), (false, true), (false, false), diff --git a/tests/parse_print/autogen-bilals-fixed/d1f9f5646ad02f51e81ccd962c936011/d1f9f5646ad02f51e81ccd962c936011.eprime.essence b/tests/parse_print/autogen-bilals-fixed/d1f9f5646ad02f51e81ccd962c936011/d1f9f5646ad02f51e81ccd962c936011.eprime.essence index 632fbd6152..0479a8b30c 100644 --- a/tests/parse_print/autogen-bilals-fixed/d1f9f5646ad02f51e81ccd962c936011/d1f9f5646ad02f51e81ccd962c936011.eprime.essence +++ b/tests/parse_print/autogen-bilals-fixed/d1f9f5646ad02f51e81ccd962c936011/d1f9f5646ad02f51e81ccd962c936011.eprime.essence @@ -27,14 +27,14 @@ such that given2, given1, and([q1 + 1 <= var1_ExplicitVarSizeWithMarkerR7_Marker -> - var1_ExplicitVarSizeWithMarkerR7_Values_ExplicitWithFlags_Flags[q1, ..] var1_ExplicitVarSizeWithMarkerR7_Marker -> @@ -84,7 +84,7 @@ such that var3_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q20] = var3_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q20 + 1] /\ - var3_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values_1[q20, ..] var3_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> diff --git a/tests/parse_print/autogen-bilals-fixed/d1ffc6dc30ae73ba44e3f9c55d3e1636/d1ffc6dc30ae73ba44e3f9c55d3e1636.eprime.essence b/tests/parse_print/autogen-bilals-fixed/d1ffc6dc30ae73ba44e3f9c55d3e1636/d1ffc6dc30ae73ba44e3f9c55d3e1636.eprime.essence index 672e145261..820ef65c2a 100644 --- a/tests/parse_print/autogen-bilals-fixed/d1ffc6dc30ae73ba44e3f9c55d3e1636/d1ffc6dc30ae73ba44e3f9c55d3e1636.eprime.essence +++ b/tests/parse_print/autogen-bilals-fixed/d1ffc6dc30ae73ba44e3f9c55d3e1636/d1ffc6dc30ae73ba44e3f9c55d3e1636.eprime.essence @@ -60,21 +60,21 @@ such that var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q4] = var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q4 + 1] /\ - (var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values_1[q4, ..] var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> diff --git a/tests/parse_print/autogen-bilals-fixed/d20ff5e630ee919f1fcc726ea14f1e21/d20ff5e630ee919f1fcc726ea14f1e21.eprime.essence b/tests/parse_print/autogen-bilals-fixed/d20ff5e630ee919f1fcc726ea14f1e21/d20ff5e630ee919f1fcc726ea14f1e21.eprime.essence index 0eb5c681ce..f9a4a90442 100644 --- a/tests/parse_print/autogen-bilals-fixed/d20ff5e630ee919f1fcc726ea14f1e21/d20ff5e630ee919f1fcc726ea14f1e21.eprime.essence +++ b/tests/parse_print/autogen-bilals-fixed/d20ff5e630ee919f1fcc726ea14f1e21/d20ff5e630ee919f1fcc726ea14f1e21.eprime.essence @@ -100,7 +100,7 @@ such that (flatten(var1_PartitionAsSet_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMarker_Values_Function1DPartial_Flags[q5, .., ..]) - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> diff --git a/tests/parse_print/autogen-bilals-fixed/d3909eeb253333c473b61058dd67f690/d3909eeb253333c473b61058dd67f690.eprime.essence b/tests/parse_print/autogen-bilals-fixed/d3909eeb253333c473b61058dd67f690/d3909eeb253333c473b61058dd67f690.eprime.essence index fa63fdbaef..2c82e2986e 100644 --- a/tests/parse_print/autogen-bilals-fixed/d3909eeb253333c473b61058dd67f690/d3909eeb253333c473b61058dd67f690.eprime.essence +++ b/tests/parse_print/autogen-bilals-fixed/d3909eeb253333c473b61058dd67f690/d3909eeb253333c473b61058dd67f690.eprime.essence @@ -90,7 +90,7 @@ such that var2_1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q7] = var2_1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q7 + 1] /\ - var2_1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q7, ..] var2_1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> @@ -119,14 +119,14 @@ such that and([var4_1_ExplicitWithFlags_Flags[q17] = 0 \/ var4_1_ExplicitWithFlags_Flags[q17] >= 0 | q17 : int(1..3)]), 3 = sum([var4_1_ExplicitWithFlags_Flags[q18] | q18 : int(1..3)]), and([var5_ExplicitWithFlagsR10_Flags[q20 + 1] > 0 -> - var5_ExplicitWithFlagsR10_Values_Function1DPartial_Flags[q20, ..] diff --git a/tests/parse_print/autogen-bilals-fixed/d548102740c166c94c1585976df85834/d548102740c166c94c1585976df85834.eprime.essence b/tests/parse_print/autogen-bilals-fixed/d548102740c166c94c1585976df85834/d548102740c166c94c1585976df85834.eprime.essence index cde47c805e..efc37a2dcb 100644 --- a/tests/parse_print/autogen-bilals-fixed/d548102740c166c94c1585976df85834/d548102740c166c94c1585976df85834.eprime.essence +++ b/tests/parse_print/autogen-bilals-fixed/d548102740c166c94c1585976df85834/d548102740c166c94c1585976df85834.eprime.essence @@ -118,7 +118,7 @@ such that (flatten(var1_PartitionAsSet_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMarker_Values_Function1DPartial_Flags[q5, .., ..]) - and([var1_PartitionAsSet_ExplicitVarSizeWithMarker_Values_Explicit_ExplicitVarSizeWithFlags_Flags[1, q9, ..] - var1_FunctionAsRelation_RelationAsSet_ExplicitVarSizeWithMarker_Values_1_Occurrence[q1, ..] - var2_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> diff --git a/tests/parse_print/autogen-bilals-fixed/d7d816b10a6f459ed78f1bd604bca06f/d7d816b10a6f459ed78f1bd604bca06f.eprime.essence b/tests/parse_print/autogen-bilals-fixed/d7d816b10a6f459ed78f1bd604bca06f/d7d816b10a6f459ed78f1bd604bca06f.eprime.essence index 4222e8f2d6..03a8106cb5 100644 --- a/tests/parse_print/autogen-bilals-fixed/d7d816b10a6f459ed78f1bd604bca06f/d7d816b10a6f459ed78f1bd604bca06f.eprime.essence +++ b/tests/parse_print/autogen-bilals-fixed/d7d816b10a6f459ed78f1bd604bca06f/d7d816b10a6f459ed78f1bd604bca06f.eprime.essence @@ -45,7 +45,7 @@ such that and([q4 + 1 <= var2_PartitionAsSet_ExplicitVarSizeWithMarker_Marker -> var2_PartitionAsSet_ExplicitVarSizeWithMarker_Values_Explicit_ExplicitVarSizeWithMarker_Marker[q4, ..] - var1_FunctionAsRelation_RelationAsSet_ExplicitVarSizeWithMarker_Values_1_Function1DPartial_Flags[q1, ..] - = 1, and([q8 + 1 <= var1_PartitionAsSet_ExplicitR5_ExplicitVarSizeWithMarker_Marker[1] -> - var1_PartitionAsSet_ExplicitR5_ExplicitVarSizeWithMarker_Values[1, q8, ..] var1_PartitionAsSet_ExplicitR5_ExplicitVarSizeWithMarker_Marker[1] -> @@ -36,14 +36,14 @@ such that | q9 : int(1..24)]), var1_PartitionAsSet_ExplicitR5_ExplicitVarSizeWithMarker_Marker[1] <= 24, and([var2_ExplicitVarSizeWithFlagsR10_Flags[q13 + 1] -> - var2_ExplicitVarSizeWithFlagsR10_Values_Function1DPartial_Flags[q13, ..] @@ -87,7 +87,7 @@ such that var4_1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q36] = var4_1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q36 + 1] /\ - var4_1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q36, ..] var4_1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> diff --git a/tests/parse_print/autogen-bilals-fixed/dad7b9b0bdd9e288f1dc3b19ec96c213/dad7b9b0bdd9e288f1dc3b19ec96c213.eprime.essence b/tests/parse_print/autogen-bilals-fixed/dad7b9b0bdd9e288f1dc3b19ec96c213/dad7b9b0bdd9e288f1dc3b19ec96c213.eprime.essence index 85a89cc588..5bf980191b 100644 --- a/tests/parse_print/autogen-bilals-fixed/dad7b9b0bdd9e288f1dc3b19ec96c213/dad7b9b0bdd9e288f1dc3b19ec96c213.eprime.essence +++ b/tests/parse_print/autogen-bilals-fixed/dad7b9b0bdd9e288f1dc3b19ec96c213/dad7b9b0bdd9e288f1dc3b19ec96c213.eprime.essence @@ -82,7 +82,7 @@ such that (flatten(var1_PartitionAsSet_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithFlags_Flags[q5, .., ..]) - = 1 | q51 : int(1..4)]), and([q7 + 1 <= var2_1_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> - var2_1_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q7, ..] var2_1_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> @@ -104,14 +104,14 @@ such that | q14 : int(1..9)]), 3 = var4_1_ExplicitWithRepetition_Flag, and([q21 + 1 <= var5_ExplicitWithRepetitionR10_Flag -> - var5_ExplicitWithRepetitionR10_Values_Function1DPartial_Flags[q21, ..] var5_ExplicitWithRepetitionR10_Flag -> diff --git a/tests/parse_print/autogen-bilals-fixed/de9716a7ff65a1574f48f0b1858be3bd/de9716a7ff65a1574f48f0b1858be3bd.eprime.essence b/tests/parse_print/autogen-bilals-fixed/de9716a7ff65a1574f48f0b1858be3bd/de9716a7ff65a1574f48f0b1858be3bd.eprime.essence index 9727c9c642..2ee0ee8d82 100644 --- a/tests/parse_print/autogen-bilals-fixed/de9716a7ff65a1574f48f0b1858be3bd/de9716a7ff65a1574f48f0b1858be3bd.eprime.essence +++ b/tests/parse_print/autogen-bilals-fixed/de9716a7ff65a1574f48f0b1858be3bd/de9716a7ff65a1574f48f0b1858be3bd.eprime.essence @@ -86,7 +86,7 @@ such that -> var1_FunctionAsRelation_RelationAsSet_ExplicitVarSizeWithMarker_Values_1_Function1DPartial_Flags[q1, ..] - var2_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> diff --git a/tests/parse_print/autogen-bilals-fixed/dec056eee47fd05a251225b16b62ab64/dec056eee47fd05a251225b16b62ab64.eprime.essence b/tests/parse_print/autogen-bilals-fixed/dec056eee47fd05a251225b16b62ab64/dec056eee47fd05a251225b16b62ab64.eprime.essence index fe81e3feef..9147748567 100644 --- a/tests/parse_print/autogen-bilals-fixed/dec056eee47fd05a251225b16b62ab64/dec056eee47fd05a251225b16b62ab64.eprime.essence +++ b/tests/parse_print/autogen-bilals-fixed/dec056eee47fd05a251225b16b62ab64/dec056eee47fd05a251225b16b62ab64.eprime.essence @@ -51,7 +51,7 @@ such that /\ flatten(var1_PartitionAsSet_Explicit_ExplicitVarSizeWithMarker_Values_Function1D[q4, .., ..]) - var1_PartitionAsSet_Explicit_ExplicitVarSizeWithMarker_Values_Function1D[q5, q6, ..] - - var4_2_PartitionAsSet_ExplicitVarSizeWithMarker_Values_Explicit[q35, ..] var4_2_PartitionAsSet_ExplicitVarSizeWithMarker_Marker -> @@ -112,7 +112,7 @@ such that var4_3_PartitionAsSet_Explicit_ExplicitVarSizeWithMarker_Marker[q43] = var4_3_PartitionAsSet_Explicit_ExplicitVarSizeWithMarker_Marker[q43 + 1] /\ - var4_3_PartitionAsSet_Explicit_ExplicitVarSizeWithMarker_Values[q43, ..] var4_3_PartitionAsSet_Explicit_ExplicitVarSizeWithMarker_Marker[q44] -> diff --git a/tests/parse_print/autogen-bilals-fixed/e02f77cea3324e91d885d1f3fe504cd4/e02f77cea3324e91d885d1f3fe504cd4.eprime.essence b/tests/parse_print/autogen-bilals-fixed/e02f77cea3324e91d885d1f3fe504cd4/e02f77cea3324e91d885d1f3fe504cd4.eprime.essence index 613729e30b..7d2f1906c5 100644 --- a/tests/parse_print/autogen-bilals-fixed/e02f77cea3324e91d885d1f3fe504cd4/e02f77cea3324e91d885d1f3fe504cd4.eprime.essence +++ b/tests/parse_print/autogen-bilals-fixed/e02f77cea3324e91d885d1f3fe504cd4/e02f77cea3324e91d885d1f3fe504cd4.eprime.essence @@ -14,7 +14,7 @@ such that -> var1_FunctionAsRelation_RelationAsSet_ExplicitVarSizeWithMarker_Values_1_ExplicitVarSizeWithFlags_Flags[q1, ..] - var1_FunctionAsRelation_RelationAsSet_ExplicitVarSizeWithMarker_Values_1_Function1DPartial_Flags[q1, ..] - and([q7 + 1 <= var2_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[1] -> - var2_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[1, q7, ..] diff --git a/tests/parse_print/autogen-bilals-fixed/e21cd7b0f710515a79d787945d809a81/e21cd7b0f710515a79d787945d809a81.eprime.essence b/tests/parse_print/autogen-bilals-fixed/e21cd7b0f710515a79d787945d809a81/e21cd7b0f710515a79d787945d809a81.eprime.essence index fe6b7b4f24..ab22647c58 100644 --- a/tests/parse_print/autogen-bilals-fixed/e21cd7b0f710515a79d787945d809a81/e21cd7b0f710515a79d787945d809a81.eprime.essence +++ b/tests/parse_print/autogen-bilals-fixed/e21cd7b0f710515a79d787945d809a81/e21cd7b0f710515a79d787945d809a81.eprime.essence @@ -27,14 +27,14 @@ such that given2, given1, and([q1 + 1 <= var1_ExplicitVarSizeWithMarkerR7_Marker -> - var1_ExplicitVarSizeWithMarkerR7_Values_ExplicitWithFlags_Flags[q1, ..] var1_ExplicitVarSizeWithMarkerR7_Marker -> @@ -84,7 +84,7 @@ such that var3_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q20] = var3_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q20 + 1] /\ - var3_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values_1[q20, ..] var3_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> diff --git a/tests/parse_print/autogen-bilals-fixed/e31e8258961a4a8fa32e4eb491491bdc/e31e8258961a4a8fa32e4eb491491bdc.eprime.essence b/tests/parse_print/autogen-bilals-fixed/e31e8258961a4a8fa32e4eb491491bdc/e31e8258961a4a8fa32e4eb491491bdc.eprime.essence index e1f553cd89..d77f8ba693 100644 --- a/tests/parse_print/autogen-bilals-fixed/e31e8258961a4a8fa32e4eb491491bdc/e31e8258961a4a8fa32e4eb491491bdc.eprime.essence +++ b/tests/parse_print/autogen-bilals-fixed/e31e8258961a4a8fa32e4eb491491bdc/e31e8258961a4a8fa32e4eb491491bdc.eprime.essence @@ -13,7 +13,7 @@ find var2_RelationAsMatrix: such that 2 <= var1_FunctionAsRelation_RelationAsSet_ExplicitVarSizeWithMarker_Marker -> var1_FunctionAsRelation_RelationAsSet_ExplicitVarSizeWithMarker_Values_1[1, ..] - var1_FunctionAsRelation_RelationAsSet_ExplicitVarSizeWithMarker_Marker diff --git a/tests/parse_print/autogen-bilals-fixed/e33c5a4b1eca296873386a312774d872/e33c5a4b1eca296873386a312774d872.essence b/tests/parse_print/autogen-bilals-fixed/e33c5a4b1eca296873386a312774d872/e33c5a4b1eca296873386a312774d872.essence index 7a61c28416..8bafd83d85 100644 --- a/tests/parse_print/autogen-bilals-fixed/e33c5a4b1eca296873386a312774d872/e33c5a4b1eca296873386a312774d872.essence +++ b/tests/parse_print/autogen-bilals-fixed/e33c5a4b1eca296873386a312774d872/e33c5a4b1eca296873386a312774d872.essence @@ -7,5 +7,5 @@ find var2: partition (maxNumParts 2, minPartSize 4 , maxPartSize 5, regular) from matrix indexed by [int(2..2, 5..5)] of int(5..5, 5..5) such that - [l_1 | l_1 : bool] var1_1_PartitionAsSet_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMarker_Values_Function1D[q6, q7, ..] - 0 -> - var1_2_ExplicitVarSizeWithFlags_Values_Function1DPartial_Flags[q11, ..] diff --git a/tests/parse_print/autogen-bilals-fixed/e5ef686faac39c34b542eec223509aa8/e5ef686faac39c34b542eec223509aa8.eprime.essence b/tests/parse_print/autogen-bilals-fixed/e5ef686faac39c34b542eec223509aa8/e5ef686faac39c34b542eec223509aa8.eprime.essence index 9cf2bf804a..ae82d71b72 100644 --- a/tests/parse_print/autogen-bilals-fixed/e5ef686faac39c34b542eec223509aa8/e5ef686faac39c34b542eec223509aa8.eprime.essence +++ b/tests/parse_print/autogen-bilals-fixed/e5ef686faac39c34b542eec223509aa8/e5ef686faac39c34b542eec223509aa8.eprime.essence @@ -68,7 +68,7 @@ such that -> var1_FunctionAsRelation_RelationAsSet_ExplicitVarSizeWithMarker_Values_1_Function1DPartial_Flags[q1, ..] - - var1_ExplicitVarSizeWithMarkerR7_Values_ExplicitWithFlags_Flags[q1, ..] var1_ExplicitVarSizeWithMarkerR7_Marker -> @@ -82,7 +82,7 @@ such that var3_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q21] = var3_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q21 + 1] /\ - var3_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values_1[q21, ..] var3_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> diff --git a/tests/parse_print/autogen-bilals-fixed/e7a6d29d4285dcfdd7daddc00be2c882/e7a6d29d4285dcfdd7daddc00be2c882.eprime.essence b/tests/parse_print/autogen-bilals-fixed/e7a6d29d4285dcfdd7daddc00be2c882/e7a6d29d4285dcfdd7daddc00be2c882.eprime.essence index fd163cab36..60ccc54ca7 100644 --- a/tests/parse_print/autogen-bilals-fixed/e7a6d29d4285dcfdd7daddc00be2c882/e7a6d29d4285dcfdd7daddc00be2c882.eprime.essence +++ b/tests/parse_print/autogen-bilals-fixed/e7a6d29d4285dcfdd7daddc00be2c882/e7a6d29d4285dcfdd7daddc00be2c882.eprime.essence @@ -27,7 +27,7 @@ find var3_RelationAsSetR15_ExplicitVarSizeWithMarkerR15_Values_1_RelationAsMatri such that false, and([q6 + 1 <= var1_FunctionAsRelationR2R5_RelationAsSetR2R5_ExplicitVarSizeWithMarkerR2R5_Marker -> - var1_FunctionAsRelationR2R5_RelationAsSetR2R5_ExplicitVarSizeWithMarkerR2R5_Values_1_Occurrence[q6, ..] - (var1_FunctionAsRelationR2R5_RelationAsSetR2R5_ExplicitVarSizeWithMarkerR2R5_Values_1_Occurrence[q29, ..] or([q32 <= diff --git a/tests/parse_print/autogen-bilals-fixed/e7f89fcbcdbd0a79caefef0e87678c8d/e7f89fcbcdbd0a79caefef0e87678c8d.eprime.essence b/tests/parse_print/autogen-bilals-fixed/e7f89fcbcdbd0a79caefef0e87678c8d/e7f89fcbcdbd0a79caefef0e87678c8d.eprime.essence index 3ebb75e445..c48c7ff048 100644 --- a/tests/parse_print/autogen-bilals-fixed/e7f89fcbcdbd0a79caefef0e87678c8d/e7f89fcbcdbd0a79caefef0e87678c8d.eprime.essence +++ b/tests/parse_print/autogen-bilals-fixed/e7f89fcbcdbd0a79caefef0e87678c8d/e7f89fcbcdbd0a79caefef0e87678c8d.eprime.essence @@ -167,7 +167,7 @@ such that (flatten(var3_PartitionAsSet_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMarker_Values_Function1DPartial_Flags[q1, .., ..]) - or([false, false, false, true, false; int(11..12, 3, 0, 8..8)]), - flatten([0, 2, 0, 2, 1; int(12..13, 7, 6, 8..8)]) + flatten([0, 2, 0, 2, 1; int(12..13, 7, 6, 8..8)]) .< [2 % 2, 3 ** 0, -2; int(0..2)], + [false; int(0..0)] .< [false; int(1..1)] -> together({false, true, false}, partition({false}, {true}, {false, true, false}, {false, false, true, false, true})) diff --git a/tests/parse_print/autogen-bilals-fixed/e94042e71ae4aca4b2dcbe6a1c03eeb5/e94042e71ae4aca4b2dcbe6a1c03eeb5.eprime.essence b/tests/parse_print/autogen-bilals-fixed/e94042e71ae4aca4b2dcbe6a1c03eeb5/e94042e71ae4aca4b2dcbe6a1c03eeb5.eprime.essence index df24c8cf46..cd8563eddd 100644 --- a/tests/parse_print/autogen-bilals-fixed/e94042e71ae4aca4b2dcbe6a1c03eeb5/e94042e71ae4aca4b2dcbe6a1c03eeb5.eprime.essence +++ b/tests/parse_print/autogen-bilals-fixed/e94042e71ae4aca4b2dcbe6a1c03eeb5/e94042e71ae4aca4b2dcbe6a1c03eeb5.eprime.essence @@ -22,7 +22,7 @@ such that | q12 : int(1..nrings)]) | q11 : int(1..fin1)]), and([network_ExplicitWithFlagsR2_Flags[q1 + 1] > 0 -> - network_ExplicitWithFlagsR2_Values_Occurrence[q1, ..] diff --git a/tests/parse_print/autogen-bilals-fixed/e94f81e31dce6a8efb7cdffe25cc7a9a/e94f81e31dce6a8efb7cdffe25cc7a9a.eprime.essence b/tests/parse_print/autogen-bilals-fixed/e94f81e31dce6a8efb7cdffe25cc7a9a/e94f81e31dce6a8efb7cdffe25cc7a9a.eprime.essence index f1efc14803..259e9c1af4 100644 --- a/tests/parse_print/autogen-bilals-fixed/e94f81e31dce6a8efb7cdffe25cc7a9a/e94f81e31dce6a8efb7cdffe25cc7a9a.eprime.essence +++ b/tests/parse_print/autogen-bilals-fixed/e94f81e31dce6a8efb7cdffe25cc7a9a/e94f81e31dce6a8efb7cdffe25cc7a9a.eprime.essence @@ -14,11 +14,11 @@ find var2_PartitionAsSet_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMar such that false, and([var1_ExplicitVarSizeWithFlags_Flags[q1 + 1] > 0 -> - var1_ExplicitVarSizeWithFlags_Values_ExplicitVarSizeWithFlags_Flags[q1, ..] 0 -> @@ -59,7 +59,7 @@ such that /\ flatten(var2_PartitionAsSet_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMarker_Values[1, .., ..]) - var2_PartitionAsSet_ExplicitVarSizeWithMarker_Marker -> @@ -78,7 +78,7 @@ such that -> var2_PartitionAsSet_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMarker_Values[q20, q21, ..] - = 1 | q42 : int(1..4)]), and([q7 + 1 <= var2_1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - var2_1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q7, ..] var2_1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> @@ -123,14 +123,14 @@ such that | q17 : int(1..9)]), 3 = var4_1_ExplicitWithRepetition_Flag, and([var5_ExplicitWithFlagsR10_Flags[q24 + 1] > 0 -> - var5_ExplicitWithFlagsR10_Values_Function1DPartial_Flags[q24, ..] diff --git a/tests/parse_print/autogen-bilals-fixed/eb0e88cd958943e2e87a5ade86710827/eb0e88cd958943e2e87a5ade86710827.essence b/tests/parse_print/autogen-bilals-fixed/eb0e88cd958943e2e87a5ade86710827/eb0e88cd958943e2e87a5ade86710827.essence index 63505c4c50..65e7ddc7be 100644 --- a/tests/parse_print/autogen-bilals-fixed/eb0e88cd958943e2e87a5ade86710827/eb0e88cd958943e2e87a5ade86710827.essence +++ b/tests/parse_print/autogen-bilals-fixed/eb0e88cd958943e2e87a5ade86710827/eb0e88cd958943e2e87a5ade86710827.essence @@ -83,7 +83,7 @@ such that flatten([mset(true), mset(true), mset(false); int(2..3, 6..6)]) --> relation(([false, true, false, false, true; int(3, 7..10)] - <=lex [false; int(2..2)], + .<= [false; int(2..2)], partition({relation(tuple (false), tuple (false), tuple (true)), diff --git a/tests/parse_print/autogen-bilals-fixed/eb22d7172ced999f8568dccf4a1a3d94/eb22d7172ced999f8568dccf4a1a3d94.eprime.essence b/tests/parse_print/autogen-bilals-fixed/eb22d7172ced999f8568dccf4a1a3d94/eb22d7172ced999f8568dccf4a1a3d94.eprime.essence index 0e5059373f..011f9c5631 100644 --- a/tests/parse_print/autogen-bilals-fixed/eb22d7172ced999f8568dccf4a1a3d94/eb22d7172ced999f8568dccf4a1a3d94.eprime.essence +++ b/tests/parse_print/autogen-bilals-fixed/eb22d7172ced999f8568dccf4a1a3d94/eb22d7172ced999f8568dccf4a1a3d94.eprime.essence @@ -30,7 +30,7 @@ such that /\ (var1_ExplicitVarSizeWithFlags_Values_PartitionAsSet_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMarker_Marker[q1, ..] - - var5_ExplicitWithRepetitionR10_Values_Function1DPartial_Flags[q23, ..] var5_ExplicitWithRepetitionR10_Flag -> diff --git a/tests/parse_print/autogen-bilals-fixed/ec9aed752e5eeb363b644516fc85dd8f/ec9aed752e5eeb363b644516fc85dd8f.eprime.essence b/tests/parse_print/autogen-bilals-fixed/ec9aed752e5eeb363b644516fc85dd8f/ec9aed752e5eeb363b644516fc85dd8f.eprime.essence index 9b340fb7f8..d6754e09d5 100644 --- a/tests/parse_print/autogen-bilals-fixed/ec9aed752e5eeb363b644516fc85dd8f/ec9aed752e5eeb363b644516fc85dd8f.eprime.essence +++ b/tests/parse_print/autogen-bilals-fixed/ec9aed752e5eeb363b644516fc85dd8f/ec9aed752e5eeb363b644516fc85dd8f.eprime.essence @@ -28,7 +28,7 @@ such that /\ flatten(var2_PartitionAsSetR2_ExplicitVarSizeWithMarkerR5R2_Values_ExplicitVarSizeWithMarkerR2_Values_Occurrence [q4, .., ..]) - var1_FunctionAsRelation_RelationAsSet_ExplicitVarSizeWithMarker_Values_1[q1, ..] - = 1 | q17 : int(1..16)]), and([q7 + 1 <= var3_PartitionAsSet_ExplicitVarSizeWithMarker_Marker -> - var3_PartitionAsSet_ExplicitVarSizeWithMarker_Values_Occurrence[q7, ..] var3_PartitionAsSet_ExplicitVarSizeWithMarker_Marker -> diff --git a/tests/parse_print/autogen-bilals-fixed/ed6e2ac3457110fd811f7f6066338883/ed6e2ac3457110fd811f7f6066338883.eprime.essence b/tests/parse_print/autogen-bilals-fixed/ed6e2ac3457110fd811f7f6066338883/ed6e2ac3457110fd811f7f6066338883.eprime.essence index e9c2d5eb7c..ebe38dd8a4 100644 --- a/tests/parse_print/autogen-bilals-fixed/ed6e2ac3457110fd811f7f6066338883/ed6e2ac3457110fd811f7f6066338883.eprime.essence +++ b/tests/parse_print/autogen-bilals-fixed/ed6e2ac3457110fd811f7f6066338883/ed6e2ac3457110fd811f7f6066338883.eprime.essence @@ -33,7 +33,7 @@ such that and([q4 + 1 <= var2_PartitionAsSet_ExplicitVarSizeWithMarker_Marker -> flatten(var2_PartitionAsSet_ExplicitVarSizeWithMarker_Values_Explicit_ExplicitVarSizeWithFlags_Flags[q4, .., ..]) - - var1_ExplicitVarSizeWithFlags_Values_Function1D[q1, ..] @@ -68,7 +68,7 @@ such that and([q12 + 1 <= var2_PartitionAsSet_ExplicitVarSizeWithMarker_Marker -> var2_PartitionAsSet_ExplicitVarSizeWithMarker_Values_Explicit_ExplicitVarSizeWithMarker_Marker[q12, ..] - flatten(var2_PartitionAsSet_ExplicitVarSizeWithMarker_Values_Explicit_ExplicitVarSizeWithFlags_Flags[q4, .., ..]) - var1_FunctionAsRelation_RelationAsSet_ExplicitVarSizeWithMarker_Values_1_ExplicitVarSizeWithFlags_Flags[q1, ..] - - var1_FunctionAsRelationR2R5_RelationAsSetR2R5_ExplicitVarSizeWithMarkerR2R5_Values_1_Occurrence[q6, ..] - (var1_FunctionAsRelationR2R5_RelationAsSetR2R5_ExplicitVarSizeWithMarkerR2R5_Values_1_Occurrence[q25, ..] or([q28 <= diff --git a/tests/parse_print/autogen-bilals-fixed/ef336eba26eb0a9a90de40b18d840b84/ef336eba26eb0a9a90de40b18d840b84.eprime.essence b/tests/parse_print/autogen-bilals-fixed/ef336eba26eb0a9a90de40b18d840b84/ef336eba26eb0a9a90de40b18d840b84.eprime.essence index 5bcaa78cce..e7428015ff 100644 --- a/tests/parse_print/autogen-bilals-fixed/ef336eba26eb0a9a90de40b18d840b84/ef336eba26eb0a9a90de40b18d840b84.eprime.essence +++ b/tests/parse_print/autogen-bilals-fixed/ef336eba26eb0a9a90de40b18d840b84/ef336eba26eb0a9a90de40b18d840b84.eprime.essence @@ -7,14 +7,14 @@ find var3_ExplicitVarSizeWithFlags_Values_Function1DPartial_Values: matrix indexed by [int(1..3), bool] of bool such that and([var3_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - var3_ExplicitVarSizeWithFlags_Values_Function1DPartial_Flags[q1, ..] diff --git a/tests/parse_print/autogen-bilals-fixed/ef47512eb208c3dc333c0f019cdd3b41/ef47512eb208c3dc333c0f019cdd3b41.essence b/tests/parse_print/autogen-bilals-fixed/ef47512eb208c3dc333c0f019cdd3b41/ef47512eb208c3dc333c0f019cdd3b41.essence index d15b066d15..691a3115a3 100644 --- a/tests/parse_print/autogen-bilals-fixed/ef47512eb208c3dc333c0f019cdd3b41/ef47512eb208c3dc333c0f019cdd3b41.essence +++ b/tests/parse_print/autogen-bilals-fixed/ef47512eb208c3dc333c0f019cdd3b41/ef47512eb208c3dc333c0f019cdd3b41.essence @@ -12,7 +12,7 @@ such that true, ([false; int(0..0)], (false, 1), {5, 3}, [true, false; int(0..1)]) in (mset() : `mset of (matrix indexed by [int] of bool, (bool, int), set of int, matrix indexed by [int] of bool)`), - [true; int(2..2)] matrix indexed by [int] of int`), mset(false)) diff --git a/tests/parse_print/autogen-bilals-fixed/f0da1b32d64901550697edd2a56acbb1/f0da1b32d64901550697edd2a56acbb1.essence b/tests/parse_print/autogen-bilals-fixed/f0da1b32d64901550697edd2a56acbb1/f0da1b32d64901550697edd2a56acbb1.essence index a8f6171875..cf8266eeb2 100644 --- a/tests/parse_print/autogen-bilals-fixed/f0da1b32d64901550697edd2a56acbb1/f0da1b32d64901550697edd2a56acbb1.essence +++ b/tests/parse_print/autogen-bilals-fixed/f0da1b32d64901550697edd2a56acbb1/f0da1b32d64901550697edd2a56acbb1.essence @@ -1,4 +1,4 @@ language Essence 1.3 find unused: bool -such that image(function(mset(4) --> [2; int(1..1)]), mset(3)) <=lex [l_3 | l_3 : int(5..5, 4)] +such that image(function(mset(4) --> [2; int(1..1)]), mset(3)) .<= [l_3 | l_3 : int(5..5, 4)] diff --git a/tests/parse_print/autogen-bilals-fixed/f0fc2fcf48b2784adbc82bebe8debe1d/f0fc2fcf48b2784adbc82bebe8debe1d.eprime.essence b/tests/parse_print/autogen-bilals-fixed/f0fc2fcf48b2784adbc82bebe8debe1d/f0fc2fcf48b2784adbc82bebe8debe1d.eprime.essence index 053b248d31..287d842350 100644 --- a/tests/parse_print/autogen-bilals-fixed/f0fc2fcf48b2784adbc82bebe8debe1d/f0fc2fcf48b2784adbc82bebe8debe1d.eprime.essence +++ b/tests/parse_print/autogen-bilals-fixed/f0fc2fcf48b2784adbc82bebe8debe1d/f0fc2fcf48b2784adbc82bebe8debe1d.eprime.essence @@ -30,13 +30,13 @@ such that /\ (var2_PartitionAsSetR5_ExplicitVarSizeWithMarkerR5R5_Values_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker [q4, ..] - false, var2 --> true, var2 --> false, var1 --> true, diff --git a/tests/parse_print/autogen-bilals-fixed/f1fd537fecc6c852b01a571e701d7e59/f1fd537fecc6c852b01a571e701d7e59.eprime.essence b/tests/parse_print/autogen-bilals-fixed/f1fd537fecc6c852b01a571e701d7e59/f1fd537fecc6c852b01a571e701d7e59.eprime.essence index fcfbff417b..fbb3d386b7 100644 --- a/tests/parse_print/autogen-bilals-fixed/f1fd537fecc6c852b01a571e701d7e59/f1fd537fecc6c852b01a571e701d7e59.eprime.essence +++ b/tests/parse_print/autogen-bilals-fixed/f1fd537fecc6c852b01a571e701d7e59/f1fd537fecc6c852b01a571e701d7e59.eprime.essence @@ -17,7 +17,7 @@ such that /\ flatten(var6_ExplicitVarSizeWithMarker_Values_PartitionAsSet_ExplicitVarSizeWithMarker_Values_Explicit[1, .., ..]) - var6_ExplicitVarSizeWithMarker_Marker -> @@ -36,7 +36,7 @@ such that -> var6_ExplicitVarSizeWithMarker_Values_PartitionAsSet_ExplicitVarSizeWithMarker_Values_Explicit[q3, q7, ..] - [false, true, false, false, false; int(3, 15, 0, 4, 2..2)]), [5; int(1..1)]) - <=lex [false | l_1 : bool] + .<= [false | l_1 : bool] diff --git a/tests/parse_print/autogen-bilals-fixed/f2d8a670b4c34d59079378000ca2e898/f2d8a670b4c34d59079378000ca2e898.eprime.essence b/tests/parse_print/autogen-bilals-fixed/f2d8a670b4c34d59079378000ca2e898/f2d8a670b4c34d59079378000ca2e898.eprime.essence index bce60edb10..6dee3b7c8b 100644 --- a/tests/parse_print/autogen-bilals-fixed/f2d8a670b4c34d59079378000ca2e898/f2d8a670b4c34d59079378000ca2e898.eprime.essence +++ b/tests/parse_print/autogen-bilals-fixed/f2d8a670b4c34d59079378000ca2e898/f2d8a670b4c34d59079378000ca2e898.eprime.essence @@ -56,7 +56,7 @@ such that /\ (var2_ExplicitVarSizeWithFlags_Values_PartitionAsSet_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMarker_Marker[q7, ..] - = 1 | q31 : int(1..2)]), 2 <= var6_PartitionAsSet_ExplicitVarSizeWithMarker_Marker -> - var6_PartitionAsSet_ExplicitVarSizeWithMarker_Values_Occurrence[1, ..] var6_PartitionAsSet_ExplicitVarSizeWithMarker_Marker -> var6_PartitionAsSet_ExplicitVarSizeWithMarker_Values_Occurrence[q22, 2] = false diff --git a/tests/parse_print/autogen-bilals-fixed/f3b4b055e266a994218c9c7c4772d7db/f3b4b055e266a994218c9c7c4772d7db.eprime.essence b/tests/parse_print/autogen-bilals-fixed/f3b4b055e266a994218c9c7c4772d7db/f3b4b055e266a994218c9c7c4772d7db.eprime.essence index 1e58b7f123..cc74920837 100644 --- a/tests/parse_print/autogen-bilals-fixed/f3b4b055e266a994218c9c7c4772d7db/f3b4b055e266a994218c9c7c4772d7db.eprime.essence +++ b/tests/parse_print/autogen-bilals-fixed/f3b4b055e266a994218c9c7c4772d7db/f3b4b055e266a994218c9c7c4772d7db.eprime.essence @@ -9,7 +9,7 @@ such that and([var1_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> flatten(var1_ExplicitVarSizeWithFlags_Values_RelationAsSet_Explicit_1_RelationAsSet_Explicit_1[q1, .., ..]) - and([var1_ExplicitVarSizeWithFlags_Values_RelationAsSet_Explicit_1_RelationAsSet_Explicit_1[q5, q6, ..] - var5_RelationAsSet_ExplicitVarSizeWithMarker_Marker -> @@ -69,7 +69,7 @@ such that /\ flatten(var6_ExplicitVarSizeWithMarker_Values_PartitionAsSet_ExplicitVarSizeWithMarker_Values_Explicit[1, .., ..]) - var6_ExplicitVarSizeWithMarker_Marker -> @@ -88,7 +88,7 @@ such that -> var6_ExplicitVarSizeWithMarker_Values_PartitionAsSet_ExplicitVarSizeWithMarker_Values_Explicit[q9, q13, ..] - = false, true > false], false diff --git a/tests/parse_print/autogen-bilals-fixed/f57b3d11bf42b1452c009a9c008864fd/f57b3d11bf42b1452c009a9c008864fd.eprime.essence b/tests/parse_print/autogen-bilals-fixed/f57b3d11bf42b1452c009a9c008864fd/f57b3d11bf42b1452c009a9c008864fd.eprime.essence index 66dadd4cfa..5ba037ac2b 100644 --- a/tests/parse_print/autogen-bilals-fixed/f57b3d11bf42b1452c009a9c008864fd/f57b3d11bf42b1452c009a9c008864fd.eprime.essence +++ b/tests/parse_print/autogen-bilals-fixed/f57b3d11bf42b1452c009a9c008864fd/f57b3d11bf42b1452c009a9c008864fd.eprime.essence @@ -28,7 +28,7 @@ such that /\ flatten(var2_PartitionAsSetR6_ExplicitVarSizeWithMarkerR5R6_Values_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy [q4, .., ..]) - = 1 | q34 : int(1..4)]), and([q7 + 1 <= var2_1_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> - var2_1_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q7, ..] var2_1_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> @@ -99,14 +99,14 @@ such that and([var4_1_ExplicitWithFlags_Flags[q15] = 0 \/ var4_1_ExplicitWithFlags_Flags[q15] >= 0 | q15 : int(1..3)]), 3 = sum([var4_1_ExplicitWithFlags_Flags[q16] | q16 : int(1..3)]), and([var5_ExplicitWithFlagsR10_Flags[q18 + 1] > 0 -> - var5_ExplicitWithFlagsR10_Values_Function1DPartial_Flags[q18, ..] diff --git a/tests/parse_print/autogen-bilals-fixed/f6f3227d62d29091577943cbcc8b7b7f/f6f3227d62d29091577943cbcc8b7b7f.eprime.essence b/tests/parse_print/autogen-bilals-fixed/f6f3227d62d29091577943cbcc8b7b7f/f6f3227d62d29091577943cbcc8b7b7f.eprime.essence index aded023c8f..35edeae49b 100644 --- a/tests/parse_print/autogen-bilals-fixed/f6f3227d62d29091577943cbcc8b7b7f/f6f3227d62d29091577943cbcc8b7b7f.eprime.essence +++ b/tests/parse_print/autogen-bilals-fixed/f6f3227d62d29091577943cbcc8b7b7f/f6f3227d62d29091577943cbcc8b7b7f.eprime.essence @@ -9,7 +9,7 @@ find var2_PartitionAsSet_ExplicitVarSizeWithMarker_Values_Explicit_Occurrence: such that false, and([q1 + 1 <= var1_ExplicitVarSizeWithMarker_Marker -> - var1_ExplicitVarSizeWithMarker_Values_Function1D[q1, ..] var1_ExplicitVarSizeWithMarker_Marker -> @@ -53,7 +53,7 @@ such that and([q10 + 1 <= var2_PartitionAsSet_ExplicitVarSizeWithMarker_Marker -> flatten(var2_PartitionAsSet_ExplicitVarSizeWithMarker_Values_Explicit_Occurrence[q10, .., ..]) - var2_PartitionAsSet_ExplicitVarSizeWithMarker_Marker -> diff --git a/tests/parse_print/autogen-bilals-fixed/f8551d2ded7dfbb7f4fc2fefcfe32146/f8551d2ded7dfbb7f4fc2fefcfe32146.essence b/tests/parse_print/autogen-bilals-fixed/f8551d2ded7dfbb7f4fc2fefcfe32146/f8551d2ded7dfbb7f4fc2fefcfe32146.essence index 190a7c32e5..0069599864 100644 --- a/tests/parse_print/autogen-bilals-fixed/f8551d2ded7dfbb7f4fc2fefcfe32146/f8551d2ded7dfbb7f4fc2fefcfe32146.essence +++ b/tests/parse_print/autogen-bilals-fixed/f8551d2ded7dfbb7f4fc2fefcfe32146/f8551d2ded7dfbb7f4fc2fefcfe32146.essence @@ -9,6 +9,6 @@ such that (true, 4) --> [0, 2, 4, 3; int(11, 6, 8, 2..2)], (true, 5) --> ([] : `matrix indexed by [int] of int`)), (false <-> false, factorial(1))) - <=lex [4, 0, 4, 4; int(7, 2..3, 8..8)], + .<= [4, 0, 4, 4; int(7, 2..3, 8..8)], false maximising var1 diff --git a/tests/parse_print/autogen-bilals-fixed/fbfe220f5450d8f205a3e3e9ec02f054/fbfe220f5450d8f205a3e3e9ec02f054.eprime.essence b/tests/parse_print/autogen-bilals-fixed/fbfe220f5450d8f205a3e3e9ec02f054/fbfe220f5450d8f205a3e3e9ec02f054.eprime.essence index aa5811342b..2ea2bff2ad 100644 --- a/tests/parse_print/autogen-bilals-fixed/fbfe220f5450d8f205a3e3e9ec02f054/fbfe220f5450d8f205a3e3e9ec02f054.eprime.essence +++ b/tests/parse_print/autogen-bilals-fixed/fbfe220f5450d8f205a3e3e9ec02f054/fbfe220f5450d8f205a3e3e9ec02f054.eprime.essence @@ -2,6 +2,6 @@ language ESSENCE' 1.0 find unused: bool such that - [[true; int(1..1)]; int(1..1)][2, ..] - q_4_ExplicitVarSizeWithFlags_Values_Function1DPartial_Flags[q1, ..] @@ -73,7 +73,7 @@ such that /\ var1_PartitionAsSet_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMarker_Values[q3, ..] - - var2_ExplicitVarSizeWithFlags_Values_Function1DPartial_Flags[q5, ..] diff --git a/tests/parse_print/autogen-bilals-fixed/ff226931c79ca27e68e71f211b4aa84e/ff226931c79ca27e68e71f211b4aa84e.eprime.essence b/tests/parse_print/autogen-bilals-fixed/ff226931c79ca27e68e71f211b4aa84e/ff226931c79ca27e68e71f211b4aa84e.eprime.essence index 85ad15e4c7..ab175ad442 100644 --- a/tests/parse_print/autogen-bilals-fixed/ff226931c79ca27e68e71f211b4aa84e/ff226931c79ca27e68e71f211b4aa84e.eprime.essence +++ b/tests/parse_print/autogen-bilals-fixed/ff226931c79ca27e68e71f211b4aa84e/ff226931c79ca27e68e71f211b4aa84e.eprime.essence @@ -9,7 +9,7 @@ such that and([var1_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> flatten(var1_ExplicitVarSizeWithFlags_Values_RelationAsSet_Explicit_1_RelationAsSet_Explicit_1[q1, .., ..]) - and([var1_ExplicitVarSizeWithFlags_Values_RelationAsSet_Explicit_1_RelationAsSet_Explicit_1[q5, q6, ..] - bool find var2: (bool, bool, bool) such that - [false; int(0..0)] <=lex [false, false; int(0..1)] <-> + [false; int(0..0)] .<= [false, false; int(0..1)] <-> ({} : `set of bool`) subsetEq {false, false, true}, (mset(true, false, false) supset (mset() : `mset of bool`)) > !(true < false), (partition() : `partition from bool`) - diff --git a/tests/parse_print/autogen/321~1435140010_44/spec.essence b/tests/parse_print/autogen/321~1435140010_44/spec.essence index 0dc96fcce0..a59709521d 100644 --- a/tests/parse_print/autogen/321~1435140010_44/spec.essence +++ b/tests/parse_print/autogen/321~1435140010_44/spec.essence @@ -71,4 +71,4 @@ such that [false, false, false, true; int(7..10)], [false, false, false, false, true; int(1..3, 10..11)], [false, false, true, true, true; int(2, 10, 0, 12, 7..7)]; int(9..10, 3, 7..7)]) - <=lex ([] : `matrix indexed by [int] of bool`) + .<= ([] : `matrix indexed by [int] of bool`) diff --git a/tests/parse_print/autogen/447~1435213364_36/spec.essence b/tests/parse_print/autogen/447~1435213364_36/spec.essence index 451c59fda6..1b7248cd24 100644 --- a/tests/parse_print/autogen/447~1435213364_36/spec.essence +++ b/tests/parse_print/autogen/447~1435213364_36/spec.essence @@ -2,7 +2,7 @@ language Essence 1.3 find var1: bool such that - [l_2 | l_1 : bool, l_2 : bool, l_2] = var1, true, diff --git a/tests/parse_print/autogen/613~1436580506_52/spec.essence b/tests/parse_print/autogen/613~1436580506_52/spec.essence index e69dcc0c68..64ef7bc42a 100644 --- a/tests/parse_print/autogen/613~1436580506_52/spec.essence +++ b/tests/parse_print/autogen/613~1436580506_52/spec.essence @@ -7,7 +7,7 @@ such that function(false --> false, false --> true, false --> true, true --> false) supset (function() : `function bool --> bool`), var2, - [1, 3 / 5; int(4, 0..0)] = l_2, false <= false], apart({false}, From 2194e19b3a007ddf31d084eb94c26bd73985c323 Mon Sep 17 00:00:00 2001 From: Fraser Dunlop Date: Thu, 5 Sep 2019 09:38:27 +0100 Subject: [PATCH 101/229] fixed bug in Consecutive generation caused by mismatched tags --- src/Conjure/Language/Expression/Op/Succ.hs | 1 + src/Conjure/UI/Model.hs | 8 ++-- stack.yaml.lock | 47 ++++++++++++++++++++++ 3 files changed, 52 insertions(+), 4 deletions(-) create mode 100644 stack.yaml.lock diff --git a/src/Conjure/Language/Expression/Op/Succ.hs b/src/Conjure/Language/Expression/Op/Succ.hs index 7c69624118..c620f57402 100644 --- a/src/Conjure/Language/Expression/Op/Succ.hs +++ b/src/Conjure/Language/Expression/Op/Succ.hs @@ -26,6 +26,7 @@ instance (TypeOf x, Pretty x) => TypeOf (OpSucc x) where TypeInt TagInt -> return ty TypeInt TaggedInt{} -> return ty TypeInt (TagEnum _) -> return ty + TypeInt t | ?typeCheckerMode == RelaxedIntegerTags -> return (TypeInt t) TypeEnum{} -> return ty _ -> raiseTypeError p diff --git a/src/Conjure/UI/Model.hs b/src/Conjure/UI/Model.hs index c68a11453b..2733b61c19 100644 --- a/src/Conjure/UI/Model.hs +++ b/src/Conjure/UI/Model.hs @@ -2471,8 +2471,8 @@ addUnnamedSymmetryBreaking mode model = do let allUnnamedTypes :: [(Domain () Expression, Expression)] allUnnamedTypes = - [ (DomainReference nm Nothing, x) - | Declaration (LettingDomainDefnUnnamed nm x) <- mStatements model + [ reTag (TagUnnamed nm') (DomainReference nm Nothing, x) --x is a TagInt at this point so we must reTag it + | Declaration (LettingDomainDefnUnnamed nm@(Name nm') x) <- mStatements model ] allDecVars = @@ -2524,7 +2524,7 @@ addUnnamedSymmetryBreaking mode model = do mkGenerator_Consecutive _ _ [] = bug "must have at least one unnamed type" mkGenerator_Consecutive auxSuffix perms [(u, uSize)] = do (iPat, i) <- quantifiedVar - let perm = [essence| permutation((&i, &i+1)) |] + let perm = [essence| permutation((&i, succ(&i))) |] let applied = combinedPermApply auxSuffix (perm:perms) return [essence| and([ &applied @@ -2534,7 +2534,7 @@ addUnnamedSymmetryBreaking mode model = do |] mkGenerator_Consecutive auxSuffix perms ((u, uSize):us) = do (iPat, i) <- quantifiedVar - let perm = [essence| permutation((&i, &i+1)) |] + let perm = [essence| permutation((&i, succ(&i))) |] applied <- mkGenerator_Consecutive auxSuffix (perm:perms) us return [essence| and([ &applied diff --git a/stack.yaml.lock b/stack.yaml.lock new file mode 100644 index 0000000000..db355fe1e1 --- /dev/null +++ b/stack.yaml.lock @@ -0,0 +1,47 @@ +# This file was autogenerated by Stack. +# You should not edit this file by hand. +# For more information, please see the documentation at: +# https://docs.haskellstack.org/en/stable/lock_files + +packages: +- completed: + hackage: megaparsec-4.4.0@sha256:aa17fa6f41e825466e085f5fcaa3ce7c2558b330a324f3638533d1a7fcd1210d,6603 + pantry-tree: + size: 2394 + sha256: 97b6b17183ce020355f1354304d7fbe4b225d7af390da656ae4f801659c98329 + original: + hackage: megaparsec-4.4.0 +- completed: + hackage: tasty-1.1.0.1@sha256:7ae59ecb6550b91a73e23791d3c78b9d852b075cb519c3694e0790c0abd22d72,2449 + pantry-tree: + size: 1723 + sha256: 6e1e6d9fe9c854115b6a834f91bacb782e8dcbf3562485dd696cfad166ffc71b + original: + hackage: tasty-1.1.0.1 +- completed: + hackage: tasty-ant-xml-1.1.4@sha256:b9ac0e8912b138e944d5ee94660cbfee500dbbf143d82607d7518a62f0925a68,917 + pantry-tree: + size: 278 + sha256: f6b5a9486e3207bea4a69880cc0bc609e21099d49806a607f310fa7034e1c0bf + original: + hackage: tasty-ant-xml-1.1.4 +- completed: + cabal-file: + size: 1547 + sha256: b47802ab3bc3c44ccebdca3fa962dd0ef4e6e64aed77d82bb17f5a60aa270cd8 + name: permutation-safe + version: 0.1.0.0 + git: https://github.com/fraser-dunlop/permutation-safe.git + pantry-tree: + size: 537 + sha256: 8c37e47c2a8009cbf06f4c864fad018f848fe322f8309e52164892ec9af4a6bb + commit: 52b577751f6ebb55e333471829fff4dc1b44fc98 + original: + git: https://github.com/fraser-dunlop/permutation-safe.git + commit: 52b577751f6ebb55e333471829fff4dc1b44fc98 +snapshots: +- completed: + size: 509471 + url: https://raw.githubusercontent.com/commercialhaskell/stackage-snapshots/master/lts/12/26.yaml + sha256: 95f014df58d0679b1c4a2b7bf2b652b61da8d30de5f571abb0d59015ef678646 + original: lts-12.26 From fa250bbd272f9980a540448bc292ce18056c08aa Mon Sep 17 00:00:00 2001 From: Fraser Dunlop Date: Tue, 8 Oct 2019 11:36:05 +0100 Subject: [PATCH 102/229] bubbling issue for --unnamed-symmetry-breaking=full --- src/Conjure/UI/Model.hs | 69 ++++++++++++++++++++++++----------------- 1 file changed, 40 insertions(+), 29 deletions(-) diff --git a/src/Conjure/UI/Model.hs b/src/Conjure/UI/Model.hs index 2733b61c19..665f775119 100644 --- a/src/Conjure/UI/Model.hs +++ b/src/Conjure/UI/Model.hs @@ -894,6 +894,7 @@ checkIfAllRefined m | Just modelZipper <- mkModelZipper m = do -- we let returnMsg x = return $ "" : ("Not refined:" <+> pretty (hole x)) + <+> stringToDoc(show (hole x)) : [ nest 4 ("Context #" <> pretty i <> ":" <+> pretty c) | (i, c) <- zip allNats (tail (ascendants x)) ] @@ -904,6 +905,7 @@ checkIfAllRefined m | Just modelZipper <- mkModelZipper m = do -- we | not (isPrimitiveDomain dom) -> return $ "" : ("Not refined:" <+> pretty (hole x)) + <+> stringToDoc(show (hole x)) : ("Domain :" <+> pretty dom) : [ nest 4 ("Context #" <> pretty i <> ":" <+> pretty c) | (i, c) <- zip allNats (tail (ascendants x)) @@ -944,9 +946,11 @@ checkIfAllRefined m | Just modelZipper <- mkModelZipper m = do -- we | (i, c) <- zip allNats (tail (ascendants x)) ] [essence| &_ .< &_ |] -> - return ["", ("Not refined:" <+> pretty (hole x))] + return ["", ("Not refined:" <+> pretty (hole x)) + <+> stringToDoc(show (hole x))] [essence| &_ .<= &_ |] -> - return ["", ("Not refined:" <+> pretty (hole x))] + return ["", ("Not refined:" <+> pretty (hole x)) + <+> stringToDoc(show (hole x))] _ -> return [] unless (null fails) (bug (vcat fails)) return m @@ -2502,6 +2506,22 @@ addUnnamedSymmetryBreaking mode model = do case mode of Nothing -> return model Just (UnnamedSymmetryBreaking quickOrComplete usbScope independentlyOrAltogether) -> do + let newDecls = + case quickOrComplete of + USBQuick -> [] + USBComplete -> + case independentlyOrAltogether of + USBIndependently -> + [ Declaration (FindOrGiven LocalFind nm' domain) + | Declaration (FindOrGiven Find nm domain) <- mStatements model + , (DomainReference uName _, _) <- allUnnamedTypes + , let nm' = mconcat [nm, "_auxFor_", uName] + ] + USBAltogether -> + [ Declaration (FindOrGiven LocalFind nm' domain) + | Declaration (FindOrGiven Find nm domain) <- mStatements model + , let nm' = mconcat [nm, "_auxFor_all"] + ] let @@ -2510,6 +2530,13 @@ addUnnamedSymmetryBreaking mode model = do let applied = buildPermutationChain ps vars in [essence| image(&p, &applied) |] + nestInBubbles :: Expression -> Int -> [(Expression,Statement)] -> Expression -> Expression + nestInBubbles _ _ [] expr = expr + nestInBubbles modl i (fv:auxVars) expr = + let v = fst fv + ii = fromInt (fromIntegral i) + in WithLocals [essence| &modl[&ii] .<= &v |] (AuxiliaryVars ((snd fv):[SuchThat [nestInBubbles modl (i + 1) auxVars expr]])) + combinedPermApply auxSuffix perms = case quickOrComplete of USBQuick -> @@ -2518,8 +2545,10 @@ addUnnamedSymmetryBreaking mode model = do USBComplete -> let applied = buildPermutationChain perms varsTuple thisAuxTuple = mkAuxTuple auxSuffix - in [essence| &varsTuple .<= &thisAuxTuple /\ &thisAuxTuple = &applied |] - + + dVars = map fst (allDecVarsAux auxSuffix) + in nestInBubbles varsTuple 1 (zip dVars newDecls) + [essence| &thisAuxTuple = &applied |] mkGenerator_Consecutive _ _ [] = bug "must have at least one unnamed type" mkGenerator_Consecutive auxSuffix perms [(u, uSize)] = do @@ -2595,38 +2624,20 @@ addUnnamedSymmetryBreaking mode model = do USBConsecutive -> mkGenerator_Consecutive auxSuffix perms us USBAllPairs -> mkGenerator_AllPairs auxSuffix perms us USBAllPermutations -> mkGenerator_AllPermutations auxSuffix perms us - newCons <- case independentlyOrAltogether of - USBIndependently -> - sequence + USBIndependently -> do + xs <- (sequence [ mkGenerator uName [] [(u, uSize)] | (u@(DomainReference uName _), uSize) <- allUnnamedTypes - ] + ]) + return [SuchThat xs] USBAltogether -> do cons <- mkGenerator "all" [] allUnnamedTypes - return [cons] - - let newDecls = - case quickOrComplete of - USBQuick -> [] - USBComplete -> - case independentlyOrAltogether of - USBIndependently -> - [ Declaration (FindOrGiven Find nm' domain) - | Declaration (FindOrGiven Find nm domain) <- mStatements model - , (DomainReference uName _, _) <- allUnnamedTypes - , let nm' = mconcat [nm, "_auxFor_", uName] - ] - USBAltogether -> - [ Declaration (FindOrGiven Find nm' domain) - | Declaration (FindOrGiven Find nm domain) <- mStatements model - , let nm' = mconcat [nm, "_auxFor_all"] - ] - - let stmts = newDecls ++ [SuchThat newCons] + return [SuchThat [cons]] + let stmts = newCons traceM $ show $ vcat $ "Adding the following unnamed symmetry breaking constraints:" : map (nest 4 . pretty) stmts - return model { mStatements = mStatements model ++ stmts } + return model { mStatements = mStatements model ++ stmts} From 107adce2dd97ce6be78bacbb80123c0102d1a5a2 Mon Sep 17 00:00:00 2001 From: Fraser Dunlop Date: Fri, 11 Oct 2019 13:57:29 +0100 Subject: [PATCH 103/229] fixing up some permutation tests --- .../permutations/04_image/accept_these.sh | 42 +++++++++++++++++++ .../stdout.expected | 12 ++++-- .../stdout.expected | 2 + .../stdout.expected | 2 + .../stdout.expected | 12 ++++-- .../stdout.expected | 12 ++++-- .../stdout.expected | 2 + .../stdout.expected | 12 ++++-- .../stdout.expected | 2 + .../stdout.expected | 2 + .../permutation.essence | 3 +- .../stdout.expected | 12 ++++-- .../stdout.expected | 12 ++++-- .../stdout.expected | 2 + .../stdout.expected | 2 + .../permutations/05_equality/accept_these.sh | 15 +++++++ .../stdout.expected | 2 + .../stdout.expected | 2 + .../0003_given_equal_letting/stdout.expected | 2 + .../0004_letting_equal_given/stdout.expected | 2 + .../enum/0005_find_eq_find/stdout.expected | 2 + .../0006_in_comprehension/stdout.expected | 2 + .../stdout.expected | 2 + .../stdout.expected | 2 + .../0003_given_equal_letting/stdout.expected | 2 + .../0004_letting_equal_given/stdout.expected | 2 + .../int/0005_find_eq_find/stdout.expected | 2 + .../int/0006_in_comprehension/stdout.expected | 2 + .../stdout.expected | 2 + .../unnamed/0005_find_eq_find/stdout.expected | 2 + .../0006_in_comprehension/stdout.expected | 2 + .../permutations/06_inverse/accept_these.sh | 25 +++++++++++ .../stdout.expected | 12 ++++-- .../stdout.expected | 12 ++++-- .../0004_letting_equal_given/stdout.expected | 12 ++++-- .../enum/0005_find_eq_find/stdout.expected | 2 + .../stdout.expected | 2 + .../stdout.expected | 2 + .../0003_given_equal_letting/stdout.expected | 2 + .../0004_letting_equal_given/stdout.expected | 12 ++++-- .../int/0005_find_eq_find/stdout.expected | 2 + .../0005_find_inverse_find/stdout.expected | 2 + 42 files changed, 220 insertions(+), 41 deletions(-) create mode 100644 tests/custom/permutations/04_image/accept_these.sh create mode 100644 tests/custom/permutations/05_equality/accept_these.sh create mode 100644 tests/custom/permutations/06_inverse/accept_these.sh diff --git a/tests/custom/permutations/04_image/accept_these.sh b/tests/custom/permutations/04_image/accept_these.sh new file mode 100644 index 0000000000..cce6c030cc --- /dev/null +++ b/tests/custom/permutations/04_image/accept_these.sh @@ -0,0 +1,42 @@ +sh ../../acceptOutput.sh enum/0001_given_permutation_given_enum +sh ../../acceptOutput.sh enum/0007_find_permutation_find_enums +sh ../../acceptOutput.sh enum/0006_letting_permutation_given_enum +sh ../../acceptOutput.sh enum/0002_given_permutation_letting_enum +# sh ../../acceptOutput.sh enum/0004_given_permutation_find_enum ) +# TODO - why this error when run.sh appears to work fine?! +# Running +# Checking stderr +# src/test/Conjure/Custom/hs86 +# unexpected stderr +# Error +# permutation/essence31 +# unexpected find +# expecting end of input or letting statement +# find i n +# ^ +# cat conjure-output/*/solution No such file or directory +# was expecting +sh ../../acceptOutput.sh enum/0003_given_permutation_letting_enum +sh ../../acceptOutput.sh enum/0005_find_permutation_given_enums +sh ../../acceptOutput.sh int/0002_given_permutation_letting_int +sh ../../acceptOutput.sh int/0007_find_permutation_find_ints +# sh ../../acceptOutput.sh int/0004_given_permutation_find_int ) +# TODO - why this error when run.sh appears to work fine?! +# Running +# Checking stderr +# src/test/Conjure/Custom/hs86 +# unexpected stderr +# Error +# permutation/essence11 +# unexpected find +# expecting end of input, language, or letting statement +# find i int(0//10) +# ^ +# cat conjure-output/*/solution No such file or directory +# was expecting +sh ../../acceptOutput.sh int/0005_find_permutation_given_ints +sh ../../acceptOutput.sh int/0003_given_permutation_letting_int +sh ../../acceptOutput.sh int/0006_letting_permutation_given_int +sh ../../acceptOutput.sh int/0001_given_permutation_given_int +sh ../../acceptOutput.sh unnamed/0007_find_permutation_find_unnameds + diff --git a/tests/custom/permutations/04_image/enum/0001_given_permutation_given_enum/stdout.expected b/tests/custom/permutations/04_image/enum/0001_given_permutation_given_enum/stdout.expected index 41fd1f1fbe..bd9c885558 100644 --- a/tests/custom/permutations/04_image/enum/0001_given_permutation_given_enum/stdout.expected +++ b/tests/custom/permutations/04_image/enum/0001_given_permutation_given_enum/stdout.expected @@ -1,13 +1,17 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime permutation.param Savile Row: model000001.eprime permutation2.param -Copying solution to: permutation-permutation.solution +Running minion for domain filtering. +Running solver: minion +Savile Row: model000001.eprime permutation.param +Running minion for domain filtering. +Running solver: minion Copying solution to: permutation-permutation2.solution +Copying solution to: permutation-permutation.solution language Essence 1.3 -letting j be E3 +letting j be E6 language Essence 1.3 -letting j be E6 +letting j be E3 diff --git a/tests/custom/permutations/04_image/enum/0002_given_permutation_letting_enum/stdout.expected b/tests/custom/permutations/04_image/enum/0002_given_permutation_letting_enum/stdout.expected index f512b33cb4..4176f65d0c 100644 --- a/tests/custom/permutations/04_image/enum/0002_given_permutation_letting_enum/stdout.expected +++ b/tests/custom/permutations/04_image/enum/0002_given_permutation_letting_enum/stdout.expected @@ -2,6 +2,8 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output Savile Row: model000001.eprime permutation.param +Running minion for domain filtering. +Running solver: minion Copying solution to: permutation-permutation.solution language Essence 1.3 diff --git a/tests/custom/permutations/04_image/enum/0003_given_permutation_letting_enum/stdout.expected b/tests/custom/permutations/04_image/enum/0003_given_permutation_letting_enum/stdout.expected index fa4fe849ea..905052aa12 100644 --- a/tests/custom/permutations/04_image/enum/0003_given_permutation_letting_enum/stdout.expected +++ b/tests/custom/permutations/04_image/enum/0003_given_permutation_letting_enum/stdout.expected @@ -2,6 +2,8 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output Savile Row: model000001.eprime permutation.param +Running minion for domain filtering. +Running solver: minion Copying solution to: permutation-permutation.solution language Essence 1.3 diff --git a/tests/custom/permutations/04_image/enum/0005_find_permutation_given_enums/stdout.expected b/tests/custom/permutations/04_image/enum/0005_find_permutation_given_enums/stdout.expected index 8b5ff8e97e..c98e25b9b7 100644 --- a/tests/custom/permutations/04_image/enum/0005_find_permutation_given_enums/stdout.expected +++ b/tests/custom/permutations/04_image/enum/0005_find_permutation_given_enums/stdout.expected @@ -1,13 +1,17 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime permutation.param Savile Row: model000001.eprime permutation2.param -Copying solution to: permutation-permutation.solution +Running minion for domain filtering. +Running solver: minion +Savile Row: model000001.eprime permutation.param +Running minion for domain filtering. +Running solver: minion Copying solution to: permutation-permutation2.solution +Copying solution to: permutation-permutation.solution language Essence 1.3 -letting p be permutation((E3, E5, E4)) +letting p be permutation((E4, E5, E6)) language Essence 1.3 -letting p be permutation((E4, E5, E6)) +letting p be permutation((E3, E5, E4)) diff --git a/tests/custom/permutations/04_image/enum/0006_letting_permutation_given_enum/stdout.expected b/tests/custom/permutations/04_image/enum/0006_letting_permutation_given_enum/stdout.expected index 41fd1f1fbe..bd9c885558 100644 --- a/tests/custom/permutations/04_image/enum/0006_letting_permutation_given_enum/stdout.expected +++ b/tests/custom/permutations/04_image/enum/0006_letting_permutation_given_enum/stdout.expected @@ -1,13 +1,17 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime permutation.param Savile Row: model000001.eprime permutation2.param -Copying solution to: permutation-permutation.solution +Running minion for domain filtering. +Running solver: minion +Savile Row: model000001.eprime permutation.param +Running minion for domain filtering. +Running solver: minion Copying solution to: permutation-permutation2.solution +Copying solution to: permutation-permutation.solution language Essence 1.3 -letting j be E3 +letting j be E6 language Essence 1.3 -letting j be E6 +letting j be E3 diff --git a/tests/custom/permutations/04_image/enum/0007_find_permutation_find_enums/stdout.expected b/tests/custom/permutations/04_image/enum/0007_find_permutation_find_enums/stdout.expected index 3531be6272..d5fca1e209 100644 --- a/tests/custom/permutations/04_image/enum/0007_find_permutation_find_enums/stdout.expected +++ b/tests/custom/permutations/04_image/enum/0007_find_permutation_find_enums/stdout.expected @@ -2,6 +2,8 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output Savile Row: model000001.eprime +Running minion for domain filtering. +Running solver: minion Copying solution to: permutation.solution language Essence 1.3 diff --git a/tests/custom/permutations/04_image/int/0001_given_permutation_given_int/stdout.expected b/tests/custom/permutations/04_image/int/0001_given_permutation_given_int/stdout.expected index 0342fd6429..e104d62518 100644 --- a/tests/custom/permutations/04_image/int/0001_given_permutation_given_int/stdout.expected +++ b/tests/custom/permutations/04_image/int/0001_given_permutation_given_int/stdout.expected @@ -1,13 +1,17 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime permutation.param Savile Row: model000001.eprime permutation2.param -Copying solution to: permutation-permutation.solution +Running minion for domain filtering. +Running solver: minion +Savile Row: model000001.eprime permutation.param +Running minion for domain filtering. +Running solver: minion Copying solution to: permutation-permutation2.solution +Copying solution to: permutation-permutation.solution language Essence 1.3 -letting j be 3 +letting j be 6 language Essence 1.3 -letting j be 6 +letting j be 3 diff --git a/tests/custom/permutations/04_image/int/0002_given_permutation_letting_int/stdout.expected b/tests/custom/permutations/04_image/int/0002_given_permutation_letting_int/stdout.expected index 5cd5a59686..71a75b7bc2 100644 --- a/tests/custom/permutations/04_image/int/0002_given_permutation_letting_int/stdout.expected +++ b/tests/custom/permutations/04_image/int/0002_given_permutation_letting_int/stdout.expected @@ -2,6 +2,8 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output Savile Row: model000001.eprime permutation.param +Running minion for domain filtering. +Running solver: minion Copying solution to: permutation-permutation.solution language Essence 1.3 diff --git a/tests/custom/permutations/04_image/int/0003_given_permutation_letting_int/stdout.expected b/tests/custom/permutations/04_image/int/0003_given_permutation_letting_int/stdout.expected index cc1cb62951..f95ce6dc3a 100644 --- a/tests/custom/permutations/04_image/int/0003_given_permutation_letting_int/stdout.expected +++ b/tests/custom/permutations/04_image/int/0003_given_permutation_letting_int/stdout.expected @@ -2,6 +2,8 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output Savile Row: model000001.eprime permutation.param +Running minion for domain filtering. +Running solver: minion Copying solution to: permutation-permutation.solution language Essence 1.3 diff --git a/tests/custom/permutations/04_image/int/0004_given_permutation_find_int/permutation.essence b/tests/custom/permutations/04_image/int/0004_given_permutation_find_int/permutation.essence index 0d83139a52..3b48f881fb 100644 --- a/tests/custom/permutations/04_image/int/0004_given_permutation_find_int/permutation.essence +++ b/tests/custom/permutations/04_image/int/0004_given_permutation_find_int/permutation.essence @@ -1,9 +1,10 @@ -find i : int(0..10) given p : permutation of int(1..4) given j : int(0..10) + +find i : int(0..10) such that j = image(p, i) diff --git a/tests/custom/permutations/04_image/int/0005_find_permutation_given_ints/stdout.expected b/tests/custom/permutations/04_image/int/0005_find_permutation_given_ints/stdout.expected index 4ed8b97ac7..6ed590db5c 100644 --- a/tests/custom/permutations/04_image/int/0005_find_permutation_given_ints/stdout.expected +++ b/tests/custom/permutations/04_image/int/0005_find_permutation_given_ints/stdout.expected @@ -1,13 +1,17 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime permutation.param Savile Row: model000001.eprime permutation2.param -Copying solution to: permutation-permutation.solution +Running minion for domain filtering. +Running solver: minion +Savile Row: model000001.eprime permutation.param +Running minion for domain filtering. +Running solver: minion Copying solution to: permutation-permutation2.solution +Copying solution to: permutation-permutation.solution language Essence 1.3 -letting p be permutation((2, 4, 3)) +letting p be permutation((1, 2, 4)) language Essence 1.3 -letting p be permutation((1, 2, 4)) +letting p be permutation((2, 4, 3)) diff --git a/tests/custom/permutations/04_image/int/0006_letting_permutation_given_int/stdout.expected b/tests/custom/permutations/04_image/int/0006_letting_permutation_given_int/stdout.expected index 0342fd6429..e104d62518 100644 --- a/tests/custom/permutations/04_image/int/0006_letting_permutation_given_int/stdout.expected +++ b/tests/custom/permutations/04_image/int/0006_letting_permutation_given_int/stdout.expected @@ -1,13 +1,17 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime permutation.param Savile Row: model000001.eprime permutation2.param -Copying solution to: permutation-permutation.solution +Running minion for domain filtering. +Running solver: minion +Savile Row: model000001.eprime permutation.param +Running minion for domain filtering. +Running solver: minion Copying solution to: permutation-permutation2.solution +Copying solution to: permutation-permutation.solution language Essence 1.3 -letting j be 3 +letting j be 6 language Essence 1.3 -letting j be 6 +letting j be 3 diff --git a/tests/custom/permutations/04_image/int/0007_find_permutation_find_ints/stdout.expected b/tests/custom/permutations/04_image/int/0007_find_permutation_find_ints/stdout.expected index 236f65e8da..f794d92540 100644 --- a/tests/custom/permutations/04_image/int/0007_find_permutation_find_ints/stdout.expected +++ b/tests/custom/permutations/04_image/int/0007_find_permutation_find_ints/stdout.expected @@ -2,6 +2,8 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output Savile Row: model000001.eprime +Running minion for domain filtering. +Running solver: minion Copying solution to: permutation.solution language Essence 1.3 diff --git a/tests/custom/permutations/04_image/unnamed/0007_find_permutation_find_unnameds/stdout.expected b/tests/custom/permutations/04_image/unnamed/0007_find_permutation_find_unnameds/stdout.expected index 3f0b9a4848..35ff4abb03 100644 --- a/tests/custom/permutations/04_image/unnamed/0007_find_permutation_find_unnameds/stdout.expected +++ b/tests/custom/permutations/04_image/unnamed/0007_find_permutation_find_unnameds/stdout.expected @@ -2,6 +2,8 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output Savile Row: model000001.eprime +Running minion for domain filtering. +Running solver: minion Copying solution to: permutation.solution language Essence 1.3 diff --git a/tests/custom/permutations/05_equality/accept_these.sh b/tests/custom/permutations/05_equality/accept_these.sh new file mode 100644 index 0000000000..18aea096a3 --- /dev/null +++ b/tests/custom/permutations/05_equality/accept_these.sh @@ -0,0 +1,15 @@ +sh ../../acceptOutput.sh enum/0002_given_permutations_in_param +sh ../../acceptOutput.sh enum/0004_letting_equal_given +sh ../../acceptOutput.sh enum/0003_given_equal_letting +sh ../../acceptOutput.sh enum/0005_find_eq_find +sh ../../acceptOutput.sh enum/0006_in_comprehension +sh ../../acceptOutput.sh enum/0001_given_permutations_in_param +sh ../../acceptOutput.sh int/0002_given_permutations_in_param +sh ../../acceptOutput.sh int/0007_letting_equal_letting +sh ../../acceptOutput.sh int/0004_letting_equal_given +sh ../../acceptOutput.sh int/0003_given_equal_letting +sh ../../acceptOutput.sh int/0005_find_eq_find +sh ../../acceptOutput.sh int/0006_in_comprehension +sh ../../acceptOutput.sh int/0001_given_permutations_in_param +sh ../../acceptOutput.sh unnamed/0005_find_eq_find +sh ../../acceptOutput.sh unnamed/0006_in_comprehension diff --git a/tests/custom/permutations/05_equality/enum/0001_given_permutations_in_param/stdout.expected b/tests/custom/permutations/05_equality/enum/0001_given_permutations_in_param/stdout.expected index 901f2ae574..8a78c0058b 100644 --- a/tests/custom/permutations/05_equality/enum/0001_given_permutations_in_param/stdout.expected +++ b/tests/custom/permutations/05_equality/enum/0001_given_permutations_in_param/stdout.expected @@ -2,6 +2,8 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output Savile Row: model000001.eprime permutation.param +Running minion for domain filtering. +Running solver: minion Copying solution to: permutation-permutation.solution language Essence 1.3 diff --git a/tests/custom/permutations/05_equality/enum/0002_given_permutations_in_param/stdout.expected b/tests/custom/permutations/05_equality/enum/0002_given_permutations_in_param/stdout.expected index 1cc90d46bc..da9c2d6b8a 100644 --- a/tests/custom/permutations/05_equality/enum/0002_given_permutations_in_param/stdout.expected +++ b/tests/custom/permutations/05_equality/enum/0002_given_permutations_in_param/stdout.expected @@ -2,6 +2,8 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output Savile Row: model000001.eprime permutation.param +Running minion for domain filtering. +Running solver: minion Copying solution to: permutation-permutation.solution language Essence 1.3 diff --git a/tests/custom/permutations/05_equality/enum/0003_given_equal_letting/stdout.expected b/tests/custom/permutations/05_equality/enum/0003_given_equal_letting/stdout.expected index 1cc90d46bc..da9c2d6b8a 100644 --- a/tests/custom/permutations/05_equality/enum/0003_given_equal_letting/stdout.expected +++ b/tests/custom/permutations/05_equality/enum/0003_given_equal_letting/stdout.expected @@ -2,6 +2,8 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output Savile Row: model000001.eprime permutation.param +Running minion for domain filtering. +Running solver: minion Copying solution to: permutation-permutation.solution language Essence 1.3 diff --git a/tests/custom/permutations/05_equality/enum/0004_letting_equal_given/stdout.expected b/tests/custom/permutations/05_equality/enum/0004_letting_equal_given/stdout.expected index 1cc90d46bc..da9c2d6b8a 100644 --- a/tests/custom/permutations/05_equality/enum/0004_letting_equal_given/stdout.expected +++ b/tests/custom/permutations/05_equality/enum/0004_letting_equal_given/stdout.expected @@ -2,6 +2,8 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output Savile Row: model000001.eprime permutation.param +Running minion for domain filtering. +Running solver: minion Copying solution to: permutation-permutation.solution language Essence 1.3 diff --git a/tests/custom/permutations/05_equality/enum/0005_find_eq_find/stdout.expected b/tests/custom/permutations/05_equality/enum/0005_find_eq_find/stdout.expected index 16efae085b..e89e1c34ab 100644 --- a/tests/custom/permutations/05_equality/enum/0005_find_eq_find/stdout.expected +++ b/tests/custom/permutations/05_equality/enum/0005_find_eq_find/stdout.expected @@ -2,6 +2,8 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output Savile Row: model000001.eprime +Running minion for domain filtering. +Running solver: minion Copying solution to: permutation-000001.solution Copying solution to: permutation-000002.solution Copying solution to: permutation-000003.solution diff --git a/tests/custom/permutations/05_equality/enum/0006_in_comprehension/stdout.expected b/tests/custom/permutations/05_equality/enum/0006_in_comprehension/stdout.expected index 61af88efe6..8f60251025 100644 --- a/tests/custom/permutations/05_equality/enum/0006_in_comprehension/stdout.expected +++ b/tests/custom/permutations/05_equality/enum/0006_in_comprehension/stdout.expected @@ -2,6 +2,8 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output Savile Row: model000001.eprime +Running minion for domain filtering. +Running solver: minion Copying solution to: permutation-000001.solution Copying solution to: permutation-000002.solution Copying solution to: permutation-000003.solution diff --git a/tests/custom/permutations/05_equality/int/0001_given_permutations_in_param/stdout.expected b/tests/custom/permutations/05_equality/int/0001_given_permutations_in_param/stdout.expected index 901f2ae574..8a78c0058b 100644 --- a/tests/custom/permutations/05_equality/int/0001_given_permutations_in_param/stdout.expected +++ b/tests/custom/permutations/05_equality/int/0001_given_permutations_in_param/stdout.expected @@ -2,6 +2,8 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output Savile Row: model000001.eprime permutation.param +Running minion for domain filtering. +Running solver: minion Copying solution to: permutation-permutation.solution language Essence 1.3 diff --git a/tests/custom/permutations/05_equality/int/0002_given_permutations_in_param/stdout.expected b/tests/custom/permutations/05_equality/int/0002_given_permutations_in_param/stdout.expected index 1cc90d46bc..da9c2d6b8a 100644 --- a/tests/custom/permutations/05_equality/int/0002_given_permutations_in_param/stdout.expected +++ b/tests/custom/permutations/05_equality/int/0002_given_permutations_in_param/stdout.expected @@ -2,6 +2,8 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output Savile Row: model000001.eprime permutation.param +Running minion for domain filtering. +Running solver: minion Copying solution to: permutation-permutation.solution language Essence 1.3 diff --git a/tests/custom/permutations/05_equality/int/0003_given_equal_letting/stdout.expected b/tests/custom/permutations/05_equality/int/0003_given_equal_letting/stdout.expected index 1cc90d46bc..da9c2d6b8a 100644 --- a/tests/custom/permutations/05_equality/int/0003_given_equal_letting/stdout.expected +++ b/tests/custom/permutations/05_equality/int/0003_given_equal_letting/stdout.expected @@ -2,6 +2,8 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output Savile Row: model000001.eprime permutation.param +Running minion for domain filtering. +Running solver: minion Copying solution to: permutation-permutation.solution language Essence 1.3 diff --git a/tests/custom/permutations/05_equality/int/0004_letting_equal_given/stdout.expected b/tests/custom/permutations/05_equality/int/0004_letting_equal_given/stdout.expected index 1cc90d46bc..da9c2d6b8a 100644 --- a/tests/custom/permutations/05_equality/int/0004_letting_equal_given/stdout.expected +++ b/tests/custom/permutations/05_equality/int/0004_letting_equal_given/stdout.expected @@ -2,6 +2,8 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output Savile Row: model000001.eprime permutation.param +Running minion for domain filtering. +Running solver: minion Copying solution to: permutation-permutation.solution language Essence 1.3 diff --git a/tests/custom/permutations/05_equality/int/0005_find_eq_find/stdout.expected b/tests/custom/permutations/05_equality/int/0005_find_eq_find/stdout.expected index f8eaaf4a36..9961ea40fb 100644 --- a/tests/custom/permutations/05_equality/int/0005_find_eq_find/stdout.expected +++ b/tests/custom/permutations/05_equality/int/0005_find_eq_find/stdout.expected @@ -2,6 +2,8 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output Savile Row: model000001.eprime +Running minion for domain filtering. +Running solver: minion Copying solution to: permutation-000001.solution Copying solution to: permutation-000002.solution Copying solution to: permutation-000003.solution diff --git a/tests/custom/permutations/05_equality/int/0006_in_comprehension/stdout.expected b/tests/custom/permutations/05_equality/int/0006_in_comprehension/stdout.expected index 351d543e1e..6d6696bcce 100644 --- a/tests/custom/permutations/05_equality/int/0006_in_comprehension/stdout.expected +++ b/tests/custom/permutations/05_equality/int/0006_in_comprehension/stdout.expected @@ -2,6 +2,8 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output Savile Row: model000001.eprime +Running minion for domain filtering. +Running solver: minion Copying solution to: permutation-000001.solution Copying solution to: permutation-000002.solution Copying solution to: permutation-000003.solution diff --git a/tests/custom/permutations/05_equality/int/0007_letting_equal_letting/stdout.expected b/tests/custom/permutations/05_equality/int/0007_letting_equal_letting/stdout.expected index 587753f3d2..bcb4922cff 100644 --- a/tests/custom/permutations/05_equality/int/0007_letting_equal_letting/stdout.expected +++ b/tests/custom/permutations/05_equality/int/0007_letting_equal_letting/stdout.expected @@ -2,6 +2,8 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output Savile Row: model000001.eprime +Running minion for domain filtering. +Running solver: minion Copying solution to: permutation.solution language Essence 1.3 diff --git a/tests/custom/permutations/05_equality/unnamed/0005_find_eq_find/stdout.expected b/tests/custom/permutations/05_equality/unnamed/0005_find_eq_find/stdout.expected index 6446ec12f7..cd78de8134 100644 --- a/tests/custom/permutations/05_equality/unnamed/0005_find_eq_find/stdout.expected +++ b/tests/custom/permutations/05_equality/unnamed/0005_find_eq_find/stdout.expected @@ -2,6 +2,8 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output Savile Row: model000001.eprime +Running minion for domain filtering. +Running solver: minion Copying solution to: permutation-000001.solution Copying solution to: permutation-000002.solution Copying solution to: permutation-000003.solution diff --git a/tests/custom/permutations/05_equality/unnamed/0006_in_comprehension/stdout.expected b/tests/custom/permutations/05_equality/unnamed/0006_in_comprehension/stdout.expected index d02cb834ce..e971cd91ea 100644 --- a/tests/custom/permutations/05_equality/unnamed/0006_in_comprehension/stdout.expected +++ b/tests/custom/permutations/05_equality/unnamed/0006_in_comprehension/stdout.expected @@ -2,6 +2,8 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output Savile Row: model000001.eprime +Running minion for domain filtering. +Running solver: minion Copying solution to: permutation-000001.solution Copying solution to: permutation-000002.solution Copying solution to: permutation-000003.solution diff --git a/tests/custom/permutations/06_inverse/accept_these.sh b/tests/custom/permutations/06_inverse/accept_these.sh new file mode 100644 index 0000000000..2ec1ca0ecd --- /dev/null +++ b/tests/custom/permutations/06_inverse/accept_these.sh @@ -0,0 +1,25 @@ +sh ../../acceptOutput.sh enum/0002_given_permutations_in_param +sh ../../acceptOutput.sh enum/0004_letting_equal_given +sh ../../acceptOutput.sh enum/0005_find_eq_find +sh ../../acceptOutput.sh enum/0001_given_permutations_in_param +sh ../../acceptOutput.sh int/0002_given_permutations_in_param +sh ../../acceptOutput.sh int/0004_letting_equal_given +sh ../../acceptOutput.sh int/0003_given_equal_letting +sh ../../acceptOutput.sh int/0005_find_eq_find +sh ../../acceptOutput.sh int/0001_given_permutations_in_param +sh ../../acceptOutput.sh unnamed/0005_find_inverse_find +# permutations.06_inverse.enum.0003_given_equal_letting: FAIL (0.38s) +# TODO - what's wrong here? +# Running +# Checking stderr +# src/test/Conjure/Custom.hs:86: +# unexpected stderr: +# Error: +# permutation.essence:3:1: +# unexpected given +# expecting end of input or letting statement +# given p : permutation of n +# ^ +# cat: conjure-output/*.solution: No such file or directory +# was expecting: + diff --git a/tests/custom/permutations/06_inverse/enum/0001_given_permutations_in_param/stdout.expected b/tests/custom/permutations/06_inverse/enum/0001_given_permutations_in_param/stdout.expected index 8ca07a3941..5628c4ea9d 100644 --- a/tests/custom/permutations/06_inverse/enum/0001_given_permutations_in_param/stdout.expected +++ b/tests/custom/permutations/06_inverse/enum/0001_given_permutations_in_param/stdout.expected @@ -1,13 +1,17 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime permutation.param Savile Row: model000001.eprime permutation2.param -Copying solution to: permutation-permutation.solution +Running minion for domain filtering. +Running solver: minion +Savile Row: model000001.eprime permutation.param +Running minion for domain filtering. +Running solver: minion Copying solution to: permutation-permutation2.solution +Copying solution to: permutation-permutation.solution language Essence 1.3 -letting b be false +letting b be true language Essence 1.3 -letting b be true +letting b be false diff --git a/tests/custom/permutations/06_inverse/enum/0002_given_permutations_in_param/stdout.expected b/tests/custom/permutations/06_inverse/enum/0002_given_permutations_in_param/stdout.expected index 8ca07a3941..5628c4ea9d 100644 --- a/tests/custom/permutations/06_inverse/enum/0002_given_permutations_in_param/stdout.expected +++ b/tests/custom/permutations/06_inverse/enum/0002_given_permutations_in_param/stdout.expected @@ -1,13 +1,17 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime permutation.param Savile Row: model000001.eprime permutation2.param -Copying solution to: permutation-permutation.solution +Running minion for domain filtering. +Running solver: minion +Savile Row: model000001.eprime permutation.param +Running minion for domain filtering. +Running solver: minion Copying solution to: permutation-permutation2.solution +Copying solution to: permutation-permutation.solution language Essence 1.3 -letting b be false +letting b be true language Essence 1.3 -letting b be true +letting b be false diff --git a/tests/custom/permutations/06_inverse/enum/0004_letting_equal_given/stdout.expected b/tests/custom/permutations/06_inverse/enum/0004_letting_equal_given/stdout.expected index 8ca07a3941..5628c4ea9d 100644 --- a/tests/custom/permutations/06_inverse/enum/0004_letting_equal_given/stdout.expected +++ b/tests/custom/permutations/06_inverse/enum/0004_letting_equal_given/stdout.expected @@ -1,13 +1,17 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime permutation.param Savile Row: model000001.eprime permutation2.param -Copying solution to: permutation-permutation.solution +Running minion for domain filtering. +Running solver: minion +Savile Row: model000001.eprime permutation.param +Running minion for domain filtering. +Running solver: minion Copying solution to: permutation-permutation2.solution +Copying solution to: permutation-permutation.solution language Essence 1.3 -letting b be false +letting b be true language Essence 1.3 -letting b be true +letting b be false diff --git a/tests/custom/permutations/06_inverse/enum/0005_find_eq_find/stdout.expected b/tests/custom/permutations/06_inverse/enum/0005_find_eq_find/stdout.expected index f18ecd5016..8e8d28c8fb 100644 --- a/tests/custom/permutations/06_inverse/enum/0005_find_eq_find/stdout.expected +++ b/tests/custom/permutations/06_inverse/enum/0005_find_eq_find/stdout.expected @@ -2,6 +2,8 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output Savile Row: model000001.eprime +Running minion for domain filtering. +Running solver: minion Copying solution to: permutation-000001.solution Copying solution to: permutation-000002.solution Copying solution to: permutation-000003.solution diff --git a/tests/custom/permutations/06_inverse/int/0001_given_permutations_in_param/stdout.expected b/tests/custom/permutations/06_inverse/int/0001_given_permutations_in_param/stdout.expected index 1cc90d46bc..da9c2d6b8a 100644 --- a/tests/custom/permutations/06_inverse/int/0001_given_permutations_in_param/stdout.expected +++ b/tests/custom/permutations/06_inverse/int/0001_given_permutations_in_param/stdout.expected @@ -2,6 +2,8 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output Savile Row: model000001.eprime permutation.param +Running minion for domain filtering. +Running solver: minion Copying solution to: permutation-permutation.solution language Essence 1.3 diff --git a/tests/custom/permutations/06_inverse/int/0002_given_permutations_in_param/stdout.expected b/tests/custom/permutations/06_inverse/int/0002_given_permutations_in_param/stdout.expected index 1cc90d46bc..da9c2d6b8a 100644 --- a/tests/custom/permutations/06_inverse/int/0002_given_permutations_in_param/stdout.expected +++ b/tests/custom/permutations/06_inverse/int/0002_given_permutations_in_param/stdout.expected @@ -2,6 +2,8 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output Savile Row: model000001.eprime permutation.param +Running minion for domain filtering. +Running solver: minion Copying solution to: permutation-permutation.solution language Essence 1.3 diff --git a/tests/custom/permutations/06_inverse/int/0003_given_equal_letting/stdout.expected b/tests/custom/permutations/06_inverse/int/0003_given_equal_letting/stdout.expected index 1cc90d46bc..da9c2d6b8a 100644 --- a/tests/custom/permutations/06_inverse/int/0003_given_equal_letting/stdout.expected +++ b/tests/custom/permutations/06_inverse/int/0003_given_equal_letting/stdout.expected @@ -2,6 +2,8 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output Savile Row: model000001.eprime permutation.param +Running minion for domain filtering. +Running solver: minion Copying solution to: permutation-permutation.solution language Essence 1.3 diff --git a/tests/custom/permutations/06_inverse/int/0004_letting_equal_given/stdout.expected b/tests/custom/permutations/06_inverse/int/0004_letting_equal_given/stdout.expected index 8ca07a3941..5628c4ea9d 100644 --- a/tests/custom/permutations/06_inverse/int/0004_letting_equal_given/stdout.expected +++ b/tests/custom/permutations/06_inverse/int/0004_letting_equal_given/stdout.expected @@ -1,13 +1,17 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime permutation.param Savile Row: model000001.eprime permutation2.param -Copying solution to: permutation-permutation.solution +Running minion for domain filtering. +Running solver: minion +Savile Row: model000001.eprime permutation.param +Running minion for domain filtering. +Running solver: minion Copying solution to: permutation-permutation2.solution +Copying solution to: permutation-permutation.solution language Essence 1.3 -letting b be false +letting b be true language Essence 1.3 -letting b be true +letting b be false diff --git a/tests/custom/permutations/06_inverse/int/0005_find_eq_find/stdout.expected b/tests/custom/permutations/06_inverse/int/0005_find_eq_find/stdout.expected index a1b5092b13..c58698e36d 100644 --- a/tests/custom/permutations/06_inverse/int/0005_find_eq_find/stdout.expected +++ b/tests/custom/permutations/06_inverse/int/0005_find_eq_find/stdout.expected @@ -2,6 +2,8 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output Savile Row: model000001.eprime +Running minion for domain filtering. +Running solver: minion Copying solution to: permutation-000001.solution Copying solution to: permutation-000002.solution Copying solution to: permutation-000003.solution diff --git a/tests/custom/permutations/06_inverse/unnamed/0005_find_inverse_find/stdout.expected b/tests/custom/permutations/06_inverse/unnamed/0005_find_inverse_find/stdout.expected index 453e3e80ef..de9cceb95e 100644 --- a/tests/custom/permutations/06_inverse/unnamed/0005_find_inverse_find/stdout.expected +++ b/tests/custom/permutations/06_inverse/unnamed/0005_find_inverse_find/stdout.expected @@ -2,6 +2,8 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output Savile Row: model000001.eprime +Running minion for domain filtering. +Running solver: minion Copying solution to: permutation-000001.solution Copying solution to: permutation-000002.solution Copying solution to: permutation-000003.solution From 6a3e5efa03adcd4ed392bc0e935a309ef3208e21 Mon Sep 17 00:00:00 2001 From: Fraser Dunlop Date: Fri, 11 Oct 2019 14:15:48 +0100 Subject: [PATCH 104/229] fixing some permutation tests --- etc/hs-deps/stack-8.0.yaml | 3 +- etc/hs-deps/stack-8.2.yaml | 1 + etc/hs-deps/stack-8.4.yaml | 3 +- etc/hs-deps/stack-8.6.yaml | 3 ++ src/Conjure/Compute/DomainOf.hs | 2 +- src/Conjure/Language/Expression/Op/Image.hs | 3 -- src/Conjure/Language/Expression/Op/Inverse.hs | 2 +- src/Conjure/Language/Expression/Op/ToSet.hs | 2 +- src/Conjure/Rules/Horizontal/Permutation.hs | 31 +++++++++++++++ src/Conjure/UI/Model.hs | 2 +- .../permutations/07_compose/accept_these.sh | 38 +++++++++++++++++++ .../0002_given_and_letting/stdout.expected | 2 + .../0003_letting_and_find/stdout.expected | 12 ++++-- .../enum/0004_find_and_find/stdout.expected | 2 + .../0002_given_and_letting/stdout.expected | 2 + .../0002_letting_and_given/stdout.expected | 2 + .../int/0003_letting_and_find/stdout.expected | 12 ++++-- .../int/0004_find_and_find/stdout.expected | 2 + .../int/0005_find_composition/stdout.expected | 2 + .../int/0006_find_composition/stdout.expected | 2 + .../0004_find_and_find/stdout.expected | 2 + 21 files changed, 112 insertions(+), 18 deletions(-) create mode 100644 tests/custom/permutations/07_compose/accept_these.sh diff --git a/etc/hs-deps/stack-8.0.yaml b/etc/hs-deps/stack-8.0.yaml index 980ab29ab9..9a5b1f6432 100644 --- a/etc/hs-deps/stack-8.0.yaml +++ b/etc/hs-deps/stack-8.0.yaml @@ -13,5 +13,4 @@ extra-deps: - tasty-ant-xml-1.1.4 - optparse-applicative-0.14.2.0 - git: https://github.com/fraser-dunlop/permutation-safe.git - commit: 52b577751f6ebb55e333471829fff4dc1b44fc98 - + commit: 98b176dcd2acdfcab23bed8f4c5121df7661f343 diff --git a/etc/hs-deps/stack-8.2.yaml b/etc/hs-deps/stack-8.2.yaml index 1c15aee3dc..a0f6d9a6c1 100644 --- a/etc/hs-deps/stack-8.2.yaml +++ b/etc/hs-deps/stack-8.2.yaml @@ -10,3 +10,4 @@ extra-deps: - tasty-ant-xml-1.1.4 - git: https://github.com/fraser-dunlop/permutation-safe.git commit: 52b577751f6ebb55e333471829fff4dc1b44fc98 + diff --git a/etc/hs-deps/stack-8.4.yaml b/etc/hs-deps/stack-8.4.yaml index c628bcdfa3..ec54a4b3d5 100644 --- a/etc/hs-deps/stack-8.4.yaml +++ b/etc/hs-deps/stack-8.4.yaml @@ -7,5 +7,6 @@ extra-deps: - megaparsec-4.4.0 - tasty-1.1.0.1 - tasty-ant-xml-1.1.4 + - git: https://github.com/fraser-dunlop/permutation-safe.git - commit: 52b577751f6ebb55e333471829fff4dc1b44fc98 + commit: 98b176dcd2acdfcab23bed8f4c5121df7661f343 diff --git a/etc/hs-deps/stack-8.6.yaml b/etc/hs-deps/stack-8.6.yaml index 0f90965ce6..40376f77cb 100644 --- a/etc/hs-deps/stack-8.6.yaml +++ b/etc/hs-deps/stack-8.6.yaml @@ -5,3 +5,6 @@ system-ghc: true install-ghc: true extra-deps: - megaparsec-4.4.0 + +- git: https://github.com/fraser-dunlop/permutation-safe.git + commit: 98b176dcd2acdfcab23bed8f4c5121df7661f343 diff --git a/src/Conjure/Compute/DomainOf.hs b/src/Conjure/Compute/DomainOf.hs index 52caa84fef..ce1eec18e9 100644 --- a/src/Conjure/Compute/DomainOf.hs +++ b/src/Conjure/Compute/DomainOf.hs @@ -413,7 +413,7 @@ instance (Pretty x, TypeOf x, DomainOf x) => DomainOf (OpImage x) where case fDomain of DomainFunction _ _ _ to -> return to DomainSequence _ _ to -> return to - DomainPermutation _ _ on -> return on + DomainPermutation _ _ ov -> return ov _ -> fail "domainOf, OpImage, not a function or sequence" instance (Pretty x, TypeOf x) => DomainOf (OpImageSet x) where diff --git a/src/Conjure/Language/Expression/Op/Image.hs b/src/Conjure/Language/Expression/Op/Image.hs index b4b5a7dc9c..abb9bfacc9 100644 --- a/src/Conjure/Language/Expression/Op/Image.hs +++ b/src/Conjure/Language/Expression/Op/Image.hs @@ -4,14 +4,11 @@ module Conjure.Language.Expression.Op.Image where import Conjure.Prelude import Conjure.Language.Expression.Op.Internal.Common -import Conjure.Bug import qualified Data.Aeson as JSON -- aeson import qualified Data.HashMap.Strict as M -- unordered-containers import qualified Data.Vector as V -- vector -import Data.List (cycle) - data OpImage x = OpImage x x deriving (Eq, Ord, Show, Data, Functor, Traversable, Foldable, Typeable, Generic) diff --git a/src/Conjure/Language/Expression/Op/Inverse.hs b/src/Conjure/Language/Expression/Op/Inverse.hs index c0694459df..7babaacf3f 100644 --- a/src/Conjure/Language/Expression/Op/Inverse.hs +++ b/src/Conjure/Language/Expression/Op/Inverse.hs @@ -9,7 +9,7 @@ import qualified Data.Aeson as JSON -- aeson import qualified Data.HashMap.Strict as M -- unordered-containers import qualified Data.Vector as V -- vector -import Data.Permutation + data OpInverse x = OpInverse x x diff --git a/src/Conjure/Language/Expression/Op/ToSet.hs b/src/Conjure/Language/Expression/Op/ToSet.hs index 83740e0629..6ca641c7e1 100644 --- a/src/Conjure/Language/Expression/Op/ToSet.hs +++ b/src/Conjure/Language/Expression/Op/ToSet.hs @@ -9,7 +9,7 @@ import qualified Data.Aeson as JSON -- aeson import qualified Data.HashMap.Strict as M -- unordered-containers import qualified Data.Vector as V -- vector -import Data.Permutation +--import Data.Permutation data OpToSet x = OpToSet diff --git a/src/Conjure/Rules/Horizontal/Permutation.hs b/src/Conjure/Rules/Horizontal/Permutation.hs index 70fca541ae..0127da793e 100644 --- a/src/Conjure/Rules/Horizontal/Permutation.hs +++ b/src/Conjure/Rules/Horizontal/Permutation.hs @@ -108,3 +108,34 @@ rule_Compose_Image = "permutation-compose-image" `namedRule` theRule where theRule _ = na "rule_Compose_Image" +rule_Image_Literal :: Rule +rule_Image_Literal = "permutation-image-literal" `namedRule` theRule where + theRule [essence| image(&p, &i) |] = do + (TypePermutation inner, elems) <- match permutationLiteral p + typeI <- typeOf i + let f' = toFunction <$> fromCycles elems + case f' of + Left er -> fail $ "Permutation literal invalid." <++> stringToDoc (show er) + Right f -> do + if let ?typeCheckerMode = StronglyTyped in typesUnify [inner, typeI] + then do + let srtdel = sortBy compare (join elems) + inperm = (\x -> [essence| toInt(&x) + 1 |]) + ((\o -> [essence| or(&o) |]) + ((fromList ((\q -> [essence| &q = &i |]) <$> srtdel)))) + indexr = (\x -> [essence| sum(&x) |]) + (fromList ((\(n,q) -> [essence| toInt(&q = &i) * &n |]) + <$> (zip [1..] srtdel))) + matIdx = mkDomainIntB (fromInt 1) + (fromInt (fromIntegral (length srtdel))) + matLit = make matrixLiteral (TypeMatrix (TypeInt TagInt) inner) + matIdx (f <$> srtdel) + return + ( "Horizontal rule for permutation literal application to a single value (image), AsFunction representation" + , do + return [essence| [&i, catchUndef(&matLit[&indexr],0)][&inperm] |] + + ) + else fail $ "Permutation applied to a type its inner does not unify with" + theRule _ = na "rule_Image_Literal" + diff --git a/src/Conjure/UI/Model.hs b/src/Conjure/UI/Model.hs index a9b625a7a3..f49d828c8b 100644 --- a/src/Conjure/UI/Model.hs +++ b/src/Conjure/UI/Model.hs @@ -1506,7 +1506,7 @@ horizontalRules = - + , Horizontal.Permutation.rule_Image_Literal , Horizontal.Permutation.rule_In , Horizontal.Permutation.rule_Permutation_Inverse diff --git a/tests/custom/permutations/07_compose/accept_these.sh b/tests/custom/permutations/07_compose/accept_these.sh new file mode 100644 index 0000000000..a140956cdb --- /dev/null +++ b/tests/custom/permutations/07_compose/accept_these.sh @@ -0,0 +1,38 @@ + sh ../../acceptOutput.sh enum/0002_given_and_letting + sh ../../acceptOutput.sh enum/0003_letting_and_find + sh ../../acceptOutput.sh enum/0004_find_and_find + sh ../../acceptOutput.sh int/0002_given_and_letting + sh ../../acceptOutput.sh int/0005_find_composition + sh ../../acceptOutput.sh int/0003_letting_and_find + sh ../../acceptOutput.sh int/0004_find_and_find + sh ../../acceptOutput.sh int/0002_letting_and_given + sh ../../acceptOutput.sh int/0006_find_composition + sh ../../acceptOutput.sh unnamed/0004_find_and_find + +# TODO what's wrong here? +# permutations.07_compose.enum.0001_given_permutations_in_param: +# Running +# Checking stderr +# src/test/Conjure/Custom.hs:86: +# unexpected stderr: +# Error: +# permutation.essence:3:1: +# unexpected given +# expecting end of input or letting statement +# given p : permutation of n +# ^ +# cat: conjure-output/*.solution: No such file or directory +# was expecting: +# permutations.07_compose.int.0001_given_permutations_in_param: FAIL (0.31s) +# Running +# Checking stderr +# src/test/Conjure/Custom.hs:86: +# unexpected stderr: +# Error: +# permutation.essence:3:1: +# unexpected given +# expecting end of input, letting statement, or rest of letting statement +# given p : permutation of int(1..n) +# ^ +# cat: conjure-output/*.solution: No such file or directory +# was expecting: diff --git a/tests/custom/permutations/07_compose/enum/0002_given_and_letting/stdout.expected b/tests/custom/permutations/07_compose/enum/0002_given_and_letting/stdout.expected index 901f2ae574..8a78c0058b 100644 --- a/tests/custom/permutations/07_compose/enum/0002_given_and_letting/stdout.expected +++ b/tests/custom/permutations/07_compose/enum/0002_given_and_letting/stdout.expected @@ -2,6 +2,8 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output Savile Row: model000001.eprime permutation.param +Running minion for domain filtering. +Running solver: minion Copying solution to: permutation-permutation.solution language Essence 1.3 diff --git a/tests/custom/permutations/07_compose/enum/0003_letting_and_find/stdout.expected b/tests/custom/permutations/07_compose/enum/0003_letting_and_find/stdout.expected index 5c93b5fa44..0b64fe4a88 100644 --- a/tests/custom/permutations/07_compose/enum/0003_letting_and_find/stdout.expected +++ b/tests/custom/permutations/07_compose/enum/0003_letting_and_find/stdout.expected @@ -1,13 +1,17 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime permutation.param Savile Row: model000001.eprime permutation2.param -Copying solution to: permutation-permutation.solution +Running minion for domain filtering. +Running solver: minion +Savile Row: model000001.eprime permutation.param +Running minion for domain filtering. +Running solver: minion Copying solution to: permutation-permutation2.solution +Copying solution to: permutation-permutation.solution language Essence 1.3 -letting p be permutation((E2, E4, E3)) +letting p be permutation((E2, E3)) language Essence 1.3 -letting p be permutation((E2, E3)) +letting p be permutation((E2, E4, E3)) diff --git a/tests/custom/permutations/07_compose/enum/0004_find_and_find/stdout.expected b/tests/custom/permutations/07_compose/enum/0004_find_and_find/stdout.expected index 01b2419221..37a8ddc8d1 100644 --- a/tests/custom/permutations/07_compose/enum/0004_find_and_find/stdout.expected +++ b/tests/custom/permutations/07_compose/enum/0004_find_and_find/stdout.expected @@ -2,6 +2,8 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output Savile Row: model000001.eprime permutation.param +Running minion for domain filtering. +Running solver: minion Copying solution to: permutation-permutation-000001.solution Copying solution to: permutation-permutation-000002.solution Copying solution to: permutation-permutation-000003.solution diff --git a/tests/custom/permutations/07_compose/int/0002_given_and_letting/stdout.expected b/tests/custom/permutations/07_compose/int/0002_given_and_letting/stdout.expected index 901f2ae574..8a78c0058b 100644 --- a/tests/custom/permutations/07_compose/int/0002_given_and_letting/stdout.expected +++ b/tests/custom/permutations/07_compose/int/0002_given_and_letting/stdout.expected @@ -2,6 +2,8 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output Savile Row: model000001.eprime permutation.param +Running minion for domain filtering. +Running solver: minion Copying solution to: permutation-permutation.solution language Essence 1.3 diff --git a/tests/custom/permutations/07_compose/int/0002_letting_and_given/stdout.expected b/tests/custom/permutations/07_compose/int/0002_letting_and_given/stdout.expected index 1cc90d46bc..da9c2d6b8a 100644 --- a/tests/custom/permutations/07_compose/int/0002_letting_and_given/stdout.expected +++ b/tests/custom/permutations/07_compose/int/0002_letting_and_given/stdout.expected @@ -2,6 +2,8 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output Savile Row: model000001.eprime permutation.param +Running minion for domain filtering. +Running solver: minion Copying solution to: permutation-permutation.solution language Essence 1.3 diff --git a/tests/custom/permutations/07_compose/int/0003_letting_and_find/stdout.expected b/tests/custom/permutations/07_compose/int/0003_letting_and_find/stdout.expected index 2d74f851e9..024ae71ed2 100644 --- a/tests/custom/permutations/07_compose/int/0003_letting_and_find/stdout.expected +++ b/tests/custom/permutations/07_compose/int/0003_letting_and_find/stdout.expected @@ -1,13 +1,17 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime permutation.param Savile Row: model000001.eprime permutation2.param -Copying solution to: permutation-permutation.solution +Running minion for domain filtering. +Running solver: minion +Savile Row: model000001.eprime permutation.param +Running minion for domain filtering. +Running solver: minion Copying solution to: permutation-permutation2.solution +Copying solution to: permutation-permutation.solution language Essence 1.3 -letting p be permutation((2, 4, 3)) +letting p be permutation((2, 3)) language Essence 1.3 -letting p be permutation((2, 3)) +letting p be permutation((2, 4, 3)) diff --git a/tests/custom/permutations/07_compose/int/0004_find_and_find/stdout.expected b/tests/custom/permutations/07_compose/int/0004_find_and_find/stdout.expected index 313f185cec..63e01673f7 100644 --- a/tests/custom/permutations/07_compose/int/0004_find_and_find/stdout.expected +++ b/tests/custom/permutations/07_compose/int/0004_find_and_find/stdout.expected @@ -2,6 +2,8 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output Savile Row: model000001.eprime permutation.param +Running minion for domain filtering. +Running solver: minion Copying solution to: permutation-permutation-000001.solution Copying solution to: permutation-permutation-000002.solution Copying solution to: permutation-permutation-000003.solution diff --git a/tests/custom/permutations/07_compose/int/0005_find_composition/stdout.expected b/tests/custom/permutations/07_compose/int/0005_find_composition/stdout.expected index d041d90c1a..fa2c7dec5e 100644 --- a/tests/custom/permutations/07_compose/int/0005_find_composition/stdout.expected +++ b/tests/custom/permutations/07_compose/int/0005_find_composition/stdout.expected @@ -2,6 +2,8 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output Savile Row: model000001.eprime +Running minion for domain filtering. +Running solver: minion Copying solution to: permutation.solution language Essence 1.3 diff --git a/tests/custom/permutations/07_compose/int/0006_find_composition/stdout.expected b/tests/custom/permutations/07_compose/int/0006_find_composition/stdout.expected index 496da0634a..3d95995ea1 100644 --- a/tests/custom/permutations/07_compose/int/0006_find_composition/stdout.expected +++ b/tests/custom/permutations/07_compose/int/0006_find_composition/stdout.expected @@ -2,6 +2,8 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output Savile Row: model000001.eprime +Running minion for domain filtering. +Running solver: minion Copying solution to: permutation.solution language Essence 1.3 diff --git a/tests/custom/permutations/07_compose/unnamed/0004_find_and_find/stdout.expected b/tests/custom/permutations/07_compose/unnamed/0004_find_and_find/stdout.expected index ba284f1627..8c12f73901 100644 --- a/tests/custom/permutations/07_compose/unnamed/0004_find_and_find/stdout.expected +++ b/tests/custom/permutations/07_compose/unnamed/0004_find_and_find/stdout.expected @@ -2,6 +2,8 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output Savile Row: model000001.eprime +Running minion for domain filtering. +Running solver: minion Copying solution to: permutation-000001.solution Copying solution to: permutation-000002.solution Copying solution to: permutation-000003.solution From ff0d11f4f4e712bb7d9c4fe7008862199c76d323 Mon Sep 17 00:00:00 2001 From: Fraser Dunlop Date: Fri, 11 Oct 2019 15:33:04 +0100 Subject: [PATCH 105/229] add defined for permutation const & fix some tests --- src/Conjure/Language/Type.hs | 1 + src/Conjure/Rules/Horizontal/Permutation.hs | 16 +++++++++++++++- src/Conjure/UI/Model.hs | 3 +-- .../08_transform_set/accept_output.sh | 12 ++++++++++++ .../permutation.essence | 0 .../permutation.param | 0 .../0001_given_permutation_letting_set/run.sh | 0 .../stdout.expected | 2 ++ .../permutation.essence | 2 +- .../permutation.param | 0 .../enum/0002_given_permutation_find_sets/run.sh | 0 .../stdout.expected | 2 ++ .../permutation.essence | 2 +- .../0003_letting_permutation_find_sets/run.sh | 0 .../stdout.expected | 2 ++ .../permutation.essence | 2 +- .../enum/0004_find_permutation_find_sets/run.sh | 0 .../stdout.expected | 2 ++ .../permutation.essence | 2 +- .../permutation.param | 0 .../run.sh | 0 .../stdout.expected | 2 ++ .../permutation.essence | 2 +- .../permutation.param | 0 .../0001_given_permutation_letting_set/run.sh | 0 .../stdout.expected | 2 ++ .../permutation.essence | 2 +- .../permutation.param | 0 .../int/0002_given_permutation_find_sets/run.sh | 0 .../stdout.expected | 2 ++ .../permutation.essence | 0 .../0003_letting_permutation_find_sets/run.sh | 0 .../stdout.expected | 2 ++ .../permutation.essence | 2 +- .../int/0004_find_permutation_find_sets/run.sh | 0 .../stdout.expected | 2 ++ .../permutation.essence | 2 +- .../permutation.param | 0 .../run.sh | 0 .../stdout.expected | 2 ++ .../runthese.sh | 2 +- .../permutation.essence | 2 +- .../0004_find_permutation_find_sets/run.sh | 0 .../stdout.expected | 2 ++ .../permutations/09_defined/accept_these.sh | 12 ++++++++++++ .../0001_letting_permutation/stdout.expected | 2 ++ .../0002_letting_permutation/stdout.expected | 2 ++ .../enum/0003_given_permutation/stdout.expected | 2 ++ .../enum/0004_given_permutation/stdout.expected | 2 ++ .../enum/0005_find_permutation/stdout.expected | 2 ++ .../int/0001_letting_permutation/stdout.expected | 2 ++ .../int/0002_letting_permutation/stdout.expected | 2 ++ .../int/0003_given_permutation/stdout.expected | 2 ++ .../int/0004_given_permutation/stdout.expected | 2 ++ .../int/0005_find_permutation/stdout.expected | 2 ++ .../0005_find_permutation/stdout.expected | 2 ++ .../10_transform_tuple/accept_these.sh | 12 ++++++++++++ .../permutation.essence | 2 +- .../permutation.param | 0 .../run.sh | 0 .../stdout.expected | 2 ++ .../permutation.essence | 2 +- .../permutation.param | 0 .../run.sh | 0 .../stdout.expected | 2 ++ .../permutation.essence | 2 +- .../permutation.param | 0 .../run.sh | 0 .../stdout.expected | 2 ++ .../permutation.essence | 2 +- .../permutation.param | 0 .../run.sh | 0 .../stdout.expected | 2 ++ .../permutation.essence | 2 +- .../run.sh | 0 .../stdout.expected | 2 ++ .../permutation.essence | 2 +- .../permutation.param | 0 .../run.sh | 0 .../stdout.expected | 2 ++ .../permutation.essence | 2 +- .../permutation.param | 0 .../run.sh | 0 .../stdout.expected | 2 ++ .../permutation.essence | 2 +- .../permutation.param | 0 .../run.sh | 0 .../stdout.expected | 2 ++ .../permutation.essence | 2 +- .../permutation.param | 0 .../run.sh | 0 .../stdout.expected | 2 ++ .../permutation.essence | 2 +- .../run.sh | 0 .../stdout.expected | 2 ++ .../runthese.sh | 2 +- .../permutation.essence | 2 +- .../run.sh | 0 .../stdout.expected | 2 ++ 99 files changed, 141 insertions(+), 25 deletions(-) create mode 100644 tests/custom/permutations/08_transform_set/accept_output.sh rename tests/custom/permutations/{08_image_set => 08_transform_set}/enum/0001_given_permutation_letting_set/permutation.essence (100%) rename tests/custom/permutations/{08_image_set => 08_transform_set}/enum/0001_given_permutation_letting_set/permutation.param (100%) rename tests/custom/permutations/{08_image_set => 08_transform_set}/enum/0001_given_permutation_letting_set/run.sh (100%) rename tests/custom/permutations/{08_image_set => 08_transform_set}/enum/0001_given_permutation_letting_set/stdout.expected (80%) rename tests/custom/permutations/{08_image_set => 08_transform_set}/enum/0002_given_permutation_find_sets/permutation.essence (78%) rename tests/custom/permutations/{08_image_set => 08_transform_set}/enum/0002_given_permutation_find_sets/permutation.param (100%) rename tests/custom/permutations/{08_image_set => 08_transform_set}/enum/0002_given_permutation_find_sets/run.sh (100%) rename tests/custom/permutations/{08_image_set => 08_transform_set}/enum/0002_given_permutation_find_sets/stdout.expected (95%) rename tests/custom/permutations/{08_image_set => 08_transform_set}/enum/0003_letting_permutation_find_sets/permutation.essence (80%) rename tests/custom/permutations/{08_image_set => 08_transform_set}/enum/0003_letting_permutation_find_sets/run.sh (100%) rename tests/custom/permutations/{08_image_set => 08_transform_set}/enum/0003_letting_permutation_find_sets/stdout.expected (95%) rename tests/custom/permutations/{08_image_set => 08_transform_set}/enum/0004_find_permutation_find_sets/permutation.essence (60%) rename tests/custom/permutations/{08_image_set => 08_transform_set}/enum/0004_find_permutation_find_sets/run.sh (100%) rename tests/custom/permutations/{08_image_set => 08_transform_set}/enum/0004_find_permutation_find_sets/stdout.expected (96%) rename tests/custom/permutations/{08_image_set => 08_transform_set}/enum/0005_find_permutation_given_set_find_set/permutation.essence (60%) rename tests/custom/permutations/{08_image_set => 08_transform_set}/enum/0005_find_permutation_given_set_find_set/permutation.param (100%) rename tests/custom/permutations/{08_image_set => 08_transform_set}/enum/0005_find_permutation_given_set_find_set/run.sh (100%) rename tests/custom/permutations/{08_image_set => 08_transform_set}/enum/0005_find_permutation_given_set_find_set/stdout.expected (95%) rename tests/custom/permutations/{08_image_set => 08_transform_set}/int/0001_given_permutation_letting_set/permutation.essence (77%) rename tests/custom/permutations/{08_image_set => 08_transform_set}/int/0001_given_permutation_letting_set/permutation.param (100%) rename tests/custom/permutations/{08_image_set => 08_transform_set}/int/0001_given_permutation_letting_set/run.sh (100%) rename tests/custom/permutations/{08_image_set => 08_transform_set}/int/0001_given_permutation_letting_set/stdout.expected (80%) rename tests/custom/permutations/{08_image_set => 08_transform_set}/int/0002_given_permutation_find_sets/permutation.essence (77%) rename tests/custom/permutations/{08_image_set => 08_transform_set}/int/0002_given_permutation_find_sets/permutation.param (100%) rename tests/custom/permutations/{08_image_set => 08_transform_set}/int/0002_given_permutation_find_sets/run.sh (100%) rename tests/custom/permutations/{08_image_set => 08_transform_set}/int/0002_given_permutation_find_sets/stdout.expected (95%) rename tests/custom/permutations/{08_image_set => 08_transform_set}/int/0003_letting_permutation_find_sets/permutation.essence (100%) rename tests/custom/permutations/{08_image_set => 08_transform_set}/int/0003_letting_permutation_find_sets/run.sh (100%) rename tests/custom/permutations/{08_image_set => 08_transform_set}/int/0003_letting_permutation_find_sets/stdout.expected (95%) rename tests/custom/permutations/{08_image_set => 08_transform_set}/int/0004_find_permutation_find_sets/permutation.essence (58%) rename tests/custom/permutations/{08_image_set => 08_transform_set}/int/0004_find_permutation_find_sets/run.sh (100%) rename tests/custom/permutations/{08_image_set => 08_transform_set}/int/0004_find_permutation_find_sets/stdout.expected (96%) rename tests/custom/permutations/{08_image_set => 08_transform_set}/int/0005_find_permutation_given_set_find_set/permutation.essence (58%) rename tests/custom/permutations/{08_image_set => 08_transform_set}/int/0005_find_permutation_given_set_find_set/permutation.param (100%) rename tests/custom/permutations/{08_image_set => 08_transform_set}/int/0005_find_permutation_given_set_find_set/run.sh (100%) rename tests/custom/permutations/{08_image_set => 08_transform_set}/int/0005_find_permutation_given_set_find_set/stdout.expected (95%) rename tests/custom/permutations/{08_image_set => 08_transform_set}/runthese.sh (71%) rename tests/custom/permutations/{08_image_set => 08_transform_set}/unnamed/0004_find_permutation_find_sets/permutation.essence (58%) rename tests/custom/permutations/{08_image_set => 08_transform_set}/unnamed/0004_find_permutation_find_sets/run.sh (100%) rename tests/custom/permutations/{08_image_set => 08_transform_set}/unnamed/0004_find_permutation_find_sets/stdout.expected (97%) create mode 100644 tests/custom/permutations/09_defined/accept_these.sh create mode 100644 tests/custom/permutations/10_transform_tuple/accept_these.sh rename tests/custom/permutations/{10_image_tuple => 10_transform_tuple}/enum/0001_letting_permutation_given_tuple_find_tuple/permutation.essence (80%) rename tests/custom/permutations/{10_image_tuple => 10_transform_tuple}/enum/0001_letting_permutation_given_tuple_find_tuple/permutation.param (100%) rename tests/custom/permutations/{10_image_tuple => 10_transform_tuple}/enum/0001_letting_permutation_given_tuple_find_tuple/run.sh (100%) rename tests/custom/permutations/{10_image_tuple/enum/0003_given_permutation_given_tuple_find_tuple => 10_transform_tuple/enum/0001_letting_permutation_given_tuple_find_tuple}/stdout.expected (81%) rename tests/custom/permutations/{10_image_tuple => 10_transform_tuple}/enum/0002_letting_permutation_given_tuple_find_tuple/permutation.essence (80%) rename tests/custom/permutations/{10_image_tuple => 10_transform_tuple}/enum/0002_letting_permutation_given_tuple_find_tuple/permutation.param (100%) rename tests/custom/permutations/{10_image_tuple => 10_transform_tuple}/enum/0002_letting_permutation_given_tuple_find_tuple/run.sh (100%) rename tests/custom/permutations/{10_image_tuple => 10_transform_tuple}/enum/0002_letting_permutation_given_tuple_find_tuple/stdout.expected (81%) rename tests/custom/permutations/{10_image_tuple => 10_transform_tuple}/enum/0003_given_permutation_given_tuple_find_tuple/permutation.essence (78%) rename tests/custom/permutations/{10_image_tuple => 10_transform_tuple}/enum/0003_given_permutation_given_tuple_find_tuple/permutation.param (100%) rename tests/custom/permutations/{10_image_tuple => 10_transform_tuple}/enum/0003_given_permutation_given_tuple_find_tuple/run.sh (100%) rename tests/custom/permutations/{10_image_tuple/enum/0001_letting_permutation_given_tuple_find_tuple => 10_transform_tuple/enum/0003_given_permutation_given_tuple_find_tuple}/stdout.expected (81%) rename tests/custom/permutations/{10_image_tuple => 10_transform_tuple}/enum/0004_given_permutation_find_tuple_find_tuple/permutation.essence (78%) rename tests/custom/permutations/{10_image_tuple => 10_transform_tuple}/enum/0004_given_permutation_find_tuple_find_tuple/permutation.param (100%) rename tests/custom/permutations/{10_image_tuple => 10_transform_tuple}/enum/0004_given_permutation_find_tuple_find_tuple/run.sh (100%) rename tests/custom/permutations/{10_image_tuple => 10_transform_tuple}/enum/0004_given_permutation_find_tuple_find_tuple/stdout.expected (96%) rename tests/custom/permutations/{10_image_tuple => 10_transform_tuple}/enum/0005_find_permutation_find_tuple_find_tuple/permutation.essence (59%) rename tests/custom/permutations/{10_image_tuple => 10_transform_tuple}/enum/0005_find_permutation_find_tuple_find_tuple/run.sh (100%) rename tests/custom/permutations/{10_image_tuple => 10_transform_tuple}/enum/0005_find_permutation_find_tuple_find_tuple/stdout.expected (96%) rename tests/custom/permutations/{10_image_tuple => 10_transform_tuple}/int/0001_letting_permutation_given_tuple_find_tuple/permutation.essence (82%) rename tests/custom/permutations/{10_image_tuple => 10_transform_tuple}/int/0001_letting_permutation_given_tuple_find_tuple/permutation.param (100%) rename tests/custom/permutations/{10_image_tuple => 10_transform_tuple}/int/0001_letting_permutation_given_tuple_find_tuple/run.sh (100%) rename tests/custom/permutations/{10_image_tuple => 10_transform_tuple}/int/0001_letting_permutation_given_tuple_find_tuple/stdout.expected (80%) rename tests/custom/permutations/{10_image_tuple => 10_transform_tuple}/int/0002_letting_permutation_given_tuple_find_tuple/permutation.essence (84%) rename tests/custom/permutations/{10_image_tuple => 10_transform_tuple}/int/0002_letting_permutation_given_tuple_find_tuple/permutation.param (100%) rename tests/custom/permutations/{10_image_tuple => 10_transform_tuple}/int/0002_letting_permutation_given_tuple_find_tuple/run.sh (100%) rename tests/custom/permutations/{10_image_tuple => 10_transform_tuple}/int/0002_letting_permutation_given_tuple_find_tuple/stdout.expected (81%) rename tests/custom/permutations/{10_image_tuple => 10_transform_tuple}/int/0003_given_permutation_given_tuple_find_tuple/permutation.essence (82%) rename tests/custom/permutations/{10_image_tuple => 10_transform_tuple}/int/0003_given_permutation_given_tuple_find_tuple/permutation.param (100%) rename tests/custom/permutations/{10_image_tuple => 10_transform_tuple}/int/0003_given_permutation_given_tuple_find_tuple/run.sh (100%) rename tests/custom/permutations/{10_image_tuple => 10_transform_tuple}/int/0003_given_permutation_given_tuple_find_tuple/stdout.expected (80%) rename tests/custom/permutations/{10_image_tuple => 10_transform_tuple}/int/0004_given_permutation_find_tuple_find_tuple/permutation.essence (82%) rename tests/custom/permutations/{10_image_tuple => 10_transform_tuple}/int/0004_given_permutation_find_tuple_find_tuple/permutation.param (100%) rename tests/custom/permutations/{10_image_tuple => 10_transform_tuple}/int/0004_given_permutation_find_tuple_find_tuple/run.sh (100%) rename tests/custom/permutations/{10_image_tuple => 10_transform_tuple}/int/0004_given_permutation_find_tuple_find_tuple/stdout.expected (96%) rename tests/custom/permutations/{10_image_tuple => 10_transform_tuple}/int/0005_find_permutation_find_tuple_find_tuple/permutation.essence (65%) rename tests/custom/permutations/{10_image_tuple => 10_transform_tuple}/int/0005_find_permutation_find_tuple_find_tuple/run.sh (100%) rename tests/custom/permutations/{10_image_tuple => 10_transform_tuple}/int/0005_find_permutation_find_tuple_find_tuple/stdout.expected (96%) rename tests/custom/permutations/{10_image_tuple => 10_transform_tuple}/runthese.sh (69%) rename tests/custom/permutations/{10_image_tuple => 10_transform_tuple}/unnamed/0005_find_permutation_find_tuple_find_tuple/permutation.essence (56%) rename tests/custom/permutations/{10_image_tuple => 10_transform_tuple}/unnamed/0005_find_permutation_find_tuple_find_tuple/run.sh (100%) rename tests/custom/permutations/{10_image_tuple => 10_transform_tuple}/unnamed/0005_find_permutation_find_tuple_find_tuple/stdout.expected (97%) diff --git a/src/Conjure/Language/Type.hs b/src/Conjure/Language/Type.hs index 6e9edf802e..48f73f72dd 100644 --- a/src/Conjure/Language/Type.hs +++ b/src/Conjure/Language/Type.hs @@ -298,5 +298,6 @@ morphing :: (?typeCheckerMode :: TypeCheckerMode) => Type -> m Type morphing (TypeFunction a _) = return a morphing (TypeSequence a) = return a +morphing (TypePermutation a) = return a morphing t = fail ("morphing:" <+> pretty (show t)) diff --git a/src/Conjure/Rules/Horizontal/Permutation.hs b/src/Conjure/Rules/Horizontal/Permutation.hs index 0127da793e..6f4dc7e591 100644 --- a/src/Conjure/Rules/Horizontal/Permutation.hs +++ b/src/Conjure/Rules/Horizontal/Permutation.hs @@ -1,7 +1,7 @@ {-# LANGUAGE QuasiQuotes #-} module Conjure.Rules.Horizontal.Permutation where import Conjure.Rules.Import -import Data.Permutation (size, fromCycles, toFunction) +import Data.Permutation (size, toCycles, fromCycles, toFunction) rule_Cardinality_Literal :: Rule rule_Cardinality_Literal = "permutation-cardinality-literal" `namedRule` theRule where @@ -17,6 +17,20 @@ rule_Cardinality_Literal = "permutation-cardinality-literal" `namedRule` theRule return [essence| &i |] ) +rule_Defined_Literal :: Rule +rule_Defined_Literal = "permutation-defined-literal" `namedRule` theRule where + theRule p' = do + p <- match opDefined p' + (TypePermutation _, elems) <- match permutationLiteral p + let i' = (AbstractLiteral . AbsLitSet . nub . join . toCycles) <$> fromCycles elems + case i' of + Left er -> fail $ "Permutation literal invalid." <++> stringToDoc (show er) + Right i -> return + ( "Vertical rule for permutation defined, AsFunction representation." + , do + return [essence| &i |] + ) + rule_Equality :: Rule rule_Equality = "permutation-equality" `namedRule` theRule where theRule e = do diff --git a/src/Conjure/UI/Model.hs b/src/Conjure/UI/Model.hs index f49d828c8b..4988efc932 100644 --- a/src/Conjure/UI/Model.hs +++ b/src/Conjure/UI/Model.hs @@ -1504,8 +1504,7 @@ horizontalRules = - - + , Horizontal.Permutation.rule_Defined_Literal , Horizontal.Permutation.rule_Image_Literal , Horizontal.Permutation.rule_In , Horizontal.Permutation.rule_Permutation_Inverse diff --git a/tests/custom/permutations/08_transform_set/accept_output.sh b/tests/custom/permutations/08_transform_set/accept_output.sh new file mode 100644 index 0000000000..c5d2ba3ff8 --- /dev/null +++ b/tests/custom/permutations/08_transform_set/accept_output.sh @@ -0,0 +1,12 @@ +sh ../../acceptOutput.sh enum/0003_letting_permutation_find_sets +sh ../../acceptOutput.sh enum/0004_find_permutation_find_sets +sh ../../acceptOutput.sh enum/0005_find_permutation_given_set_find_set +sh ../../acceptOutput.sh enum/0001_given_permutation_letting_set +sh ../../acceptOutput.sh enum/0002_given_permutation_find_sets +sh ../../acceptOutput.sh int/0003_letting_permutation_find_sets +sh ../../acceptOutput.sh int/0004_find_permutation_find_sets +sh ../../acceptOutput.sh int/0005_find_permutation_given_set_find_set +sh ../../acceptOutput.sh int/0001_given_permutation_letting_set +sh ../../acceptOutput.sh int/0002_given_permutation_find_sets +sh ../../acceptOutput.sh unnamed/0004_find_permutation_find_sets + diff --git a/tests/custom/permutations/08_image_set/enum/0001_given_permutation_letting_set/permutation.essence b/tests/custom/permutations/08_transform_set/enum/0001_given_permutation_letting_set/permutation.essence similarity index 100% rename from tests/custom/permutations/08_image_set/enum/0001_given_permutation_letting_set/permutation.essence rename to tests/custom/permutations/08_transform_set/enum/0001_given_permutation_letting_set/permutation.essence diff --git a/tests/custom/permutations/08_image_set/enum/0001_given_permutation_letting_set/permutation.param b/tests/custom/permutations/08_transform_set/enum/0001_given_permutation_letting_set/permutation.param similarity index 100% rename from tests/custom/permutations/08_image_set/enum/0001_given_permutation_letting_set/permutation.param rename to tests/custom/permutations/08_transform_set/enum/0001_given_permutation_letting_set/permutation.param diff --git a/tests/custom/permutations/08_image_set/enum/0001_given_permutation_letting_set/run.sh b/tests/custom/permutations/08_transform_set/enum/0001_given_permutation_letting_set/run.sh similarity index 100% rename from tests/custom/permutations/08_image_set/enum/0001_given_permutation_letting_set/run.sh rename to tests/custom/permutations/08_transform_set/enum/0001_given_permutation_letting_set/run.sh diff --git a/tests/custom/permutations/08_image_set/enum/0001_given_permutation_letting_set/stdout.expected b/tests/custom/permutations/08_transform_set/enum/0001_given_permutation_letting_set/stdout.expected similarity index 80% rename from tests/custom/permutations/08_image_set/enum/0001_given_permutation_letting_set/stdout.expected rename to tests/custom/permutations/08_transform_set/enum/0001_given_permutation_letting_set/stdout.expected index c19e017a09..7f6a2f48ee 100644 --- a/tests/custom/permutations/08_image_set/enum/0001_given_permutation_letting_set/stdout.expected +++ b/tests/custom/permutations/08_transform_set/enum/0001_given_permutation_letting_set/stdout.expected @@ -2,6 +2,8 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output Savile Row: model000001.eprime permutation.param +Running minion for domain filtering. +Running solver: minion Copying solution to: permutation-permutation.solution language Essence 1.3 diff --git a/tests/custom/permutations/08_image_set/enum/0002_given_permutation_find_sets/permutation.essence b/tests/custom/permutations/08_transform_set/enum/0002_given_permutation_find_sets/permutation.essence similarity index 78% rename from tests/custom/permutations/08_image_set/enum/0002_given_permutation_find_sets/permutation.essence rename to tests/custom/permutations/08_transform_set/enum/0002_given_permutation_find_sets/permutation.essence index bb435e5de5..13f4aa6091 100644 --- a/tests/custom/permutations/08_image_set/enum/0002_given_permutation_find_sets/permutation.essence +++ b/tests/custom/permutations/08_transform_set/enum/0002_given_permutation_find_sets/permutation.essence @@ -7,5 +7,5 @@ find s : set of n find sn : set of n -such that sn = image(p,s) +such that sn = transform(p,s) diff --git a/tests/custom/permutations/08_image_set/enum/0002_given_permutation_find_sets/permutation.param b/tests/custom/permutations/08_transform_set/enum/0002_given_permutation_find_sets/permutation.param similarity index 100% rename from tests/custom/permutations/08_image_set/enum/0002_given_permutation_find_sets/permutation.param rename to tests/custom/permutations/08_transform_set/enum/0002_given_permutation_find_sets/permutation.param diff --git a/tests/custom/permutations/08_image_set/enum/0002_given_permutation_find_sets/run.sh b/tests/custom/permutations/08_transform_set/enum/0002_given_permutation_find_sets/run.sh similarity index 100% rename from tests/custom/permutations/08_image_set/enum/0002_given_permutation_find_sets/run.sh rename to tests/custom/permutations/08_transform_set/enum/0002_given_permutation_find_sets/run.sh diff --git a/tests/custom/permutations/08_image_set/enum/0002_given_permutation_find_sets/stdout.expected b/tests/custom/permutations/08_transform_set/enum/0002_given_permutation_find_sets/stdout.expected similarity index 95% rename from tests/custom/permutations/08_image_set/enum/0002_given_permutation_find_sets/stdout.expected rename to tests/custom/permutations/08_transform_set/enum/0002_given_permutation_find_sets/stdout.expected index f8250f03d3..a7f4317f04 100644 --- a/tests/custom/permutations/08_image_set/enum/0002_given_permutation_find_sets/stdout.expected +++ b/tests/custom/permutations/08_transform_set/enum/0002_given_permutation_find_sets/stdout.expected @@ -2,6 +2,8 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output Savile Row: model000001.eprime permutation.param +Running minion for domain filtering. +Running solver: minion Copying solution to: permutation-permutation-000001.solution Copying solution to: permutation-permutation-000002.solution Copying solution to: permutation-permutation-000003.solution diff --git a/tests/custom/permutations/08_image_set/enum/0003_letting_permutation_find_sets/permutation.essence b/tests/custom/permutations/08_transform_set/enum/0003_letting_permutation_find_sets/permutation.essence similarity index 80% rename from tests/custom/permutations/08_image_set/enum/0003_letting_permutation_find_sets/permutation.essence rename to tests/custom/permutations/08_transform_set/enum/0003_letting_permutation_find_sets/permutation.essence index 9a3fcb1eff..7e6f33026e 100644 --- a/tests/custom/permutations/08_image_set/enum/0003_letting_permutation_find_sets/permutation.essence +++ b/tests/custom/permutations/08_transform_set/enum/0003_letting_permutation_find_sets/permutation.essence @@ -7,5 +7,5 @@ find s : set of n find sn : set of n -such that sn = image(p,s) +such that sn = transform(p,s) diff --git a/tests/custom/permutations/08_image_set/enum/0003_letting_permutation_find_sets/run.sh b/tests/custom/permutations/08_transform_set/enum/0003_letting_permutation_find_sets/run.sh similarity index 100% rename from tests/custom/permutations/08_image_set/enum/0003_letting_permutation_find_sets/run.sh rename to tests/custom/permutations/08_transform_set/enum/0003_letting_permutation_find_sets/run.sh diff --git a/tests/custom/permutations/08_image_set/enum/0003_letting_permutation_find_sets/stdout.expected b/tests/custom/permutations/08_transform_set/enum/0003_letting_permutation_find_sets/stdout.expected similarity index 95% rename from tests/custom/permutations/08_image_set/enum/0003_letting_permutation_find_sets/stdout.expected rename to tests/custom/permutations/08_transform_set/enum/0003_letting_permutation_find_sets/stdout.expected index a0ba996c55..2005a71b93 100644 --- a/tests/custom/permutations/08_image_set/enum/0003_letting_permutation_find_sets/stdout.expected +++ b/tests/custom/permutations/08_transform_set/enum/0003_letting_permutation_find_sets/stdout.expected @@ -2,6 +2,8 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output Savile Row: model000001.eprime +Running minion for domain filtering. +Running solver: minion Copying solution to: permutation-000001.solution Copying solution to: permutation-000002.solution Copying solution to: permutation-000003.solution diff --git a/tests/custom/permutations/08_image_set/enum/0004_find_permutation_find_sets/permutation.essence b/tests/custom/permutations/08_transform_set/enum/0004_find_permutation_find_sets/permutation.essence similarity index 60% rename from tests/custom/permutations/08_image_set/enum/0004_find_permutation_find_sets/permutation.essence rename to tests/custom/permutations/08_transform_set/enum/0004_find_permutation_find_sets/permutation.essence index 7f494c25f4..0a841a421b 100644 --- a/tests/custom/permutations/08_image_set/enum/0004_find_permutation_find_sets/permutation.essence +++ b/tests/custom/permutations/08_transform_set/enum/0004_find_permutation_find_sets/permutation.essence @@ -7,5 +7,5 @@ find s : set of n find sn : set of n -such that sn = image(p,s) /\ (3 = sum([ toInt(l != r) | (l, r) <- p])) +such that sn = transform(p,s) /\ (3 = sum([ toInt(l != r) | (l, r) <- p])) diff --git a/tests/custom/permutations/08_image_set/enum/0004_find_permutation_find_sets/run.sh b/tests/custom/permutations/08_transform_set/enum/0004_find_permutation_find_sets/run.sh similarity index 100% rename from tests/custom/permutations/08_image_set/enum/0004_find_permutation_find_sets/run.sh rename to tests/custom/permutations/08_transform_set/enum/0004_find_permutation_find_sets/run.sh diff --git a/tests/custom/permutations/08_image_set/enum/0004_find_permutation_find_sets/stdout.expected b/tests/custom/permutations/08_transform_set/enum/0004_find_permutation_find_sets/stdout.expected similarity index 96% rename from tests/custom/permutations/08_image_set/enum/0004_find_permutation_find_sets/stdout.expected rename to tests/custom/permutations/08_transform_set/enum/0004_find_permutation_find_sets/stdout.expected index e0dee52381..5923ac139d 100644 --- a/tests/custom/permutations/08_image_set/enum/0004_find_permutation_find_sets/stdout.expected +++ b/tests/custom/permutations/08_transform_set/enum/0004_find_permutation_find_sets/stdout.expected @@ -2,6 +2,8 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output Savile Row: model000001.eprime +Running minion for domain filtering. +Running solver: minion Copying solution to: permutation-000001.solution Copying solution to: permutation-000002.solution Copying solution to: permutation-000003.solution diff --git a/tests/custom/permutations/08_image_set/enum/0005_find_permutation_given_set_find_set/permutation.essence b/tests/custom/permutations/08_transform_set/enum/0005_find_permutation_given_set_find_set/permutation.essence similarity index 60% rename from tests/custom/permutations/08_image_set/enum/0005_find_permutation_given_set_find_set/permutation.essence rename to tests/custom/permutations/08_transform_set/enum/0005_find_permutation_given_set_find_set/permutation.essence index 1d550e041f..45367de855 100644 --- a/tests/custom/permutations/08_image_set/enum/0005_find_permutation_given_set_find_set/permutation.essence +++ b/tests/custom/permutations/08_transform_set/enum/0005_find_permutation_given_set_find_set/permutation.essence @@ -7,5 +7,5 @@ given s : set of n find sn : set of n -such that sn = image(p,s) /\ (3 = sum([ toInt(l != r) | (l, r) <- p])) +such that sn = transform(p,s) /\ (3 = sum([ toInt(l != r) | (l, r) <- p])) diff --git a/tests/custom/permutations/08_image_set/enum/0005_find_permutation_given_set_find_set/permutation.param b/tests/custom/permutations/08_transform_set/enum/0005_find_permutation_given_set_find_set/permutation.param similarity index 100% rename from tests/custom/permutations/08_image_set/enum/0005_find_permutation_given_set_find_set/permutation.param rename to tests/custom/permutations/08_transform_set/enum/0005_find_permutation_given_set_find_set/permutation.param diff --git a/tests/custom/permutations/08_image_set/enum/0005_find_permutation_given_set_find_set/run.sh b/tests/custom/permutations/08_transform_set/enum/0005_find_permutation_given_set_find_set/run.sh similarity index 100% rename from tests/custom/permutations/08_image_set/enum/0005_find_permutation_given_set_find_set/run.sh rename to tests/custom/permutations/08_transform_set/enum/0005_find_permutation_given_set_find_set/run.sh diff --git a/tests/custom/permutations/08_image_set/enum/0005_find_permutation_given_set_find_set/stdout.expected b/tests/custom/permutations/08_transform_set/enum/0005_find_permutation_given_set_find_set/stdout.expected similarity index 95% rename from tests/custom/permutations/08_image_set/enum/0005_find_permutation_given_set_find_set/stdout.expected rename to tests/custom/permutations/08_transform_set/enum/0005_find_permutation_given_set_find_set/stdout.expected index dcbaec3952..d7aefd2589 100644 --- a/tests/custom/permutations/08_image_set/enum/0005_find_permutation_given_set_find_set/stdout.expected +++ b/tests/custom/permutations/08_transform_set/enum/0005_find_permutation_given_set_find_set/stdout.expected @@ -2,6 +2,8 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output Savile Row: model000001.eprime permutation.param +Running minion for domain filtering. +Running solver: minion Copying solution to: permutation-permutation-000001.solution Copying solution to: permutation-permutation-000002.solution Copying solution to: permutation-permutation-000003.solution diff --git a/tests/custom/permutations/08_image_set/int/0001_given_permutation_letting_set/permutation.essence b/tests/custom/permutations/08_transform_set/int/0001_given_permutation_letting_set/permutation.essence similarity index 77% rename from tests/custom/permutations/08_image_set/int/0001_given_permutation_letting_set/permutation.essence rename to tests/custom/permutations/08_transform_set/int/0001_given_permutation_letting_set/permutation.essence index d503098c60..c2c60a059c 100644 --- a/tests/custom/permutations/08_image_set/int/0001_given_permutation_letting_set/permutation.essence +++ b/tests/custom/permutations/08_transform_set/int/0001_given_permutation_letting_set/permutation.essence @@ -6,5 +6,5 @@ given s : set of int(1..n) find sn : set of int(1..n) -such that sn = image(p,s) +such that sn = transform(p,s) diff --git a/tests/custom/permutations/08_image_set/int/0001_given_permutation_letting_set/permutation.param b/tests/custom/permutations/08_transform_set/int/0001_given_permutation_letting_set/permutation.param similarity index 100% rename from tests/custom/permutations/08_image_set/int/0001_given_permutation_letting_set/permutation.param rename to tests/custom/permutations/08_transform_set/int/0001_given_permutation_letting_set/permutation.param diff --git a/tests/custom/permutations/08_image_set/int/0001_given_permutation_letting_set/run.sh b/tests/custom/permutations/08_transform_set/int/0001_given_permutation_letting_set/run.sh similarity index 100% rename from tests/custom/permutations/08_image_set/int/0001_given_permutation_letting_set/run.sh rename to tests/custom/permutations/08_transform_set/int/0001_given_permutation_letting_set/run.sh diff --git a/tests/custom/permutations/08_image_set/int/0001_given_permutation_letting_set/stdout.expected b/tests/custom/permutations/08_transform_set/int/0001_given_permutation_letting_set/stdout.expected similarity index 80% rename from tests/custom/permutations/08_image_set/int/0001_given_permutation_letting_set/stdout.expected rename to tests/custom/permutations/08_transform_set/int/0001_given_permutation_letting_set/stdout.expected index 3d0b07b4fc..faac5ab4a1 100644 --- a/tests/custom/permutations/08_image_set/int/0001_given_permutation_letting_set/stdout.expected +++ b/tests/custom/permutations/08_transform_set/int/0001_given_permutation_letting_set/stdout.expected @@ -2,6 +2,8 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output Savile Row: model000001.eprime permutation.param +Running minion for domain filtering. +Running solver: minion Copying solution to: permutation-permutation.solution language Essence 1.3 diff --git a/tests/custom/permutations/08_image_set/int/0002_given_permutation_find_sets/permutation.essence b/tests/custom/permutations/08_transform_set/int/0002_given_permutation_find_sets/permutation.essence similarity index 77% rename from tests/custom/permutations/08_image_set/int/0002_given_permutation_find_sets/permutation.essence rename to tests/custom/permutations/08_transform_set/int/0002_given_permutation_find_sets/permutation.essence index 421b59bd2a..6d0865db30 100644 --- a/tests/custom/permutations/08_image_set/int/0002_given_permutation_find_sets/permutation.essence +++ b/tests/custom/permutations/08_transform_set/int/0002_given_permutation_find_sets/permutation.essence @@ -7,5 +7,5 @@ find s : set of int(1..n) find sn : set of int(1..n) -such that sn = image(p,s) +such that sn = transform(p,s) diff --git a/tests/custom/permutations/08_image_set/int/0002_given_permutation_find_sets/permutation.param b/tests/custom/permutations/08_transform_set/int/0002_given_permutation_find_sets/permutation.param similarity index 100% rename from tests/custom/permutations/08_image_set/int/0002_given_permutation_find_sets/permutation.param rename to tests/custom/permutations/08_transform_set/int/0002_given_permutation_find_sets/permutation.param diff --git a/tests/custom/permutations/08_image_set/int/0002_given_permutation_find_sets/run.sh b/tests/custom/permutations/08_transform_set/int/0002_given_permutation_find_sets/run.sh similarity index 100% rename from tests/custom/permutations/08_image_set/int/0002_given_permutation_find_sets/run.sh rename to tests/custom/permutations/08_transform_set/int/0002_given_permutation_find_sets/run.sh diff --git a/tests/custom/permutations/08_image_set/int/0002_given_permutation_find_sets/stdout.expected b/tests/custom/permutations/08_transform_set/int/0002_given_permutation_find_sets/stdout.expected similarity index 95% rename from tests/custom/permutations/08_image_set/int/0002_given_permutation_find_sets/stdout.expected rename to tests/custom/permutations/08_transform_set/int/0002_given_permutation_find_sets/stdout.expected index e408f884c6..ed0335f3bd 100644 --- a/tests/custom/permutations/08_image_set/int/0002_given_permutation_find_sets/stdout.expected +++ b/tests/custom/permutations/08_transform_set/int/0002_given_permutation_find_sets/stdout.expected @@ -2,6 +2,8 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output Savile Row: model000001.eprime permutation.param +Running minion for domain filtering. +Running solver: minion Copying solution to: permutation-permutation-000001.solution Copying solution to: permutation-permutation-000002.solution Copying solution to: permutation-permutation-000003.solution diff --git a/tests/custom/permutations/08_image_set/int/0003_letting_permutation_find_sets/permutation.essence b/tests/custom/permutations/08_transform_set/int/0003_letting_permutation_find_sets/permutation.essence similarity index 100% rename from tests/custom/permutations/08_image_set/int/0003_letting_permutation_find_sets/permutation.essence rename to tests/custom/permutations/08_transform_set/int/0003_letting_permutation_find_sets/permutation.essence diff --git a/tests/custom/permutations/08_image_set/int/0003_letting_permutation_find_sets/run.sh b/tests/custom/permutations/08_transform_set/int/0003_letting_permutation_find_sets/run.sh similarity index 100% rename from tests/custom/permutations/08_image_set/int/0003_letting_permutation_find_sets/run.sh rename to tests/custom/permutations/08_transform_set/int/0003_letting_permutation_find_sets/run.sh diff --git a/tests/custom/permutations/08_image_set/int/0003_letting_permutation_find_sets/stdout.expected b/tests/custom/permutations/08_transform_set/int/0003_letting_permutation_find_sets/stdout.expected similarity index 95% rename from tests/custom/permutations/08_image_set/int/0003_letting_permutation_find_sets/stdout.expected rename to tests/custom/permutations/08_transform_set/int/0003_letting_permutation_find_sets/stdout.expected index e436325718..855a415b46 100644 --- a/tests/custom/permutations/08_image_set/int/0003_letting_permutation_find_sets/stdout.expected +++ b/tests/custom/permutations/08_transform_set/int/0003_letting_permutation_find_sets/stdout.expected @@ -2,6 +2,8 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output Savile Row: model000001.eprime +Running minion for domain filtering. +Running solver: minion Copying solution to: permutation-000001.solution Copying solution to: permutation-000002.solution Copying solution to: permutation-000003.solution diff --git a/tests/custom/permutations/08_image_set/int/0004_find_permutation_find_sets/permutation.essence b/tests/custom/permutations/08_transform_set/int/0004_find_permutation_find_sets/permutation.essence similarity index 58% rename from tests/custom/permutations/08_image_set/int/0004_find_permutation_find_sets/permutation.essence rename to tests/custom/permutations/08_transform_set/int/0004_find_permutation_find_sets/permutation.essence index c281ffe0c7..67d8a4436e 100644 --- a/tests/custom/permutations/08_image_set/int/0004_find_permutation_find_sets/permutation.essence +++ b/tests/custom/permutations/08_transform_set/int/0004_find_permutation_find_sets/permutation.essence @@ -7,5 +7,5 @@ find s : set of int(1..n) find sn : set of int(1..n) -such that sn = image(p,s) /\ (3 = sum([ toInt(l != r) | (l, r) <- p])) +such that sn = transform(p,s) /\ (3 = sum([ toInt(l != r) | (l, r) <- p])) diff --git a/tests/custom/permutations/08_image_set/int/0004_find_permutation_find_sets/run.sh b/tests/custom/permutations/08_transform_set/int/0004_find_permutation_find_sets/run.sh similarity index 100% rename from tests/custom/permutations/08_image_set/int/0004_find_permutation_find_sets/run.sh rename to tests/custom/permutations/08_transform_set/int/0004_find_permutation_find_sets/run.sh diff --git a/tests/custom/permutations/08_image_set/int/0004_find_permutation_find_sets/stdout.expected b/tests/custom/permutations/08_transform_set/int/0004_find_permutation_find_sets/stdout.expected similarity index 96% rename from tests/custom/permutations/08_image_set/int/0004_find_permutation_find_sets/stdout.expected rename to tests/custom/permutations/08_transform_set/int/0004_find_permutation_find_sets/stdout.expected index 42291b8573..2ff7ab2c06 100644 --- a/tests/custom/permutations/08_image_set/int/0004_find_permutation_find_sets/stdout.expected +++ b/tests/custom/permutations/08_transform_set/int/0004_find_permutation_find_sets/stdout.expected @@ -2,6 +2,8 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output Savile Row: model000001.eprime +Running minion for domain filtering. +Running solver: minion Copying solution to: permutation-000001.solution Copying solution to: permutation-000002.solution Copying solution to: permutation-000003.solution diff --git a/tests/custom/permutations/08_image_set/int/0005_find_permutation_given_set_find_set/permutation.essence b/tests/custom/permutations/08_transform_set/int/0005_find_permutation_given_set_find_set/permutation.essence similarity index 58% rename from tests/custom/permutations/08_image_set/int/0005_find_permutation_given_set_find_set/permutation.essence rename to tests/custom/permutations/08_transform_set/int/0005_find_permutation_given_set_find_set/permutation.essence index bc2e8b55e4..31bb9bbd17 100644 --- a/tests/custom/permutations/08_image_set/int/0005_find_permutation_given_set_find_set/permutation.essence +++ b/tests/custom/permutations/08_transform_set/int/0005_find_permutation_given_set_find_set/permutation.essence @@ -7,5 +7,5 @@ given s : set of int(1..n) find sn : set of int(1..n) -such that sn = image(p,s) /\ (3 = sum([ toInt(l != r) | (l, r) <- p])) +such that sn = transform(p,s) /\ (3 = sum([ toInt(l != r) | (l, r) <- p])) diff --git a/tests/custom/permutations/08_image_set/int/0005_find_permutation_given_set_find_set/permutation.param b/tests/custom/permutations/08_transform_set/int/0005_find_permutation_given_set_find_set/permutation.param similarity index 100% rename from tests/custom/permutations/08_image_set/int/0005_find_permutation_given_set_find_set/permutation.param rename to tests/custom/permutations/08_transform_set/int/0005_find_permutation_given_set_find_set/permutation.param diff --git a/tests/custom/permutations/08_image_set/int/0005_find_permutation_given_set_find_set/run.sh b/tests/custom/permutations/08_transform_set/int/0005_find_permutation_given_set_find_set/run.sh similarity index 100% rename from tests/custom/permutations/08_image_set/int/0005_find_permutation_given_set_find_set/run.sh rename to tests/custom/permutations/08_transform_set/int/0005_find_permutation_given_set_find_set/run.sh diff --git a/tests/custom/permutations/08_image_set/int/0005_find_permutation_given_set_find_set/stdout.expected b/tests/custom/permutations/08_transform_set/int/0005_find_permutation_given_set_find_set/stdout.expected similarity index 95% rename from tests/custom/permutations/08_image_set/int/0005_find_permutation_given_set_find_set/stdout.expected rename to tests/custom/permutations/08_transform_set/int/0005_find_permutation_given_set_find_set/stdout.expected index a76cb5cf7f..a43fe606e4 100644 --- a/tests/custom/permutations/08_image_set/int/0005_find_permutation_given_set_find_set/stdout.expected +++ b/tests/custom/permutations/08_transform_set/int/0005_find_permutation_given_set_find_set/stdout.expected @@ -2,6 +2,8 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output Savile Row: model000001.eprime permutation.param +Running minion for domain filtering. +Running solver: minion Copying solution to: permutation-permutation-000001.solution Copying solution to: permutation-permutation-000002.solution Copying solution to: permutation-permutation-000003.solution diff --git a/tests/custom/permutations/08_image_set/runthese.sh b/tests/custom/permutations/08_transform_set/runthese.sh similarity index 71% rename from tests/custom/permutations/08_image_set/runthese.sh rename to tests/custom/permutations/08_transform_set/runthese.sh index ca3f96bc20..91bb9cd7a2 100644 --- a/tests/custom/permutations/08_image_set/runthese.sh +++ b/tests/custom/permutations/08_transform_set/runthese.sh @@ -1 +1 @@ -stack build --copy-bins --test --test-arguments "-p custom.permutations.08_image_set" +stack build --copy-bins --test --test-arguments "-p custom.permutations.08_transform_set" diff --git a/tests/custom/permutations/08_image_set/unnamed/0004_find_permutation_find_sets/permutation.essence b/tests/custom/permutations/08_transform_set/unnamed/0004_find_permutation_find_sets/permutation.essence similarity index 58% rename from tests/custom/permutations/08_image_set/unnamed/0004_find_permutation_find_sets/permutation.essence rename to tests/custom/permutations/08_transform_set/unnamed/0004_find_permutation_find_sets/permutation.essence index 4405140cad..805aba3bb4 100644 --- a/tests/custom/permutations/08_image_set/unnamed/0004_find_permutation_find_sets/permutation.essence +++ b/tests/custom/permutations/08_transform_set/unnamed/0004_find_permutation_find_sets/permutation.essence @@ -7,5 +7,5 @@ find s : set of n find sn : set of n -such that sn = image(p,s) /\ (3 = sum([ toInt(l != r) | (l, r) <- p])) +such that sn = transform(p,s) /\ (3 = sum([ toInt(l != r) | (l, r) <- p])) diff --git a/tests/custom/permutations/08_image_set/unnamed/0004_find_permutation_find_sets/run.sh b/tests/custom/permutations/08_transform_set/unnamed/0004_find_permutation_find_sets/run.sh similarity index 100% rename from tests/custom/permutations/08_image_set/unnamed/0004_find_permutation_find_sets/run.sh rename to tests/custom/permutations/08_transform_set/unnamed/0004_find_permutation_find_sets/run.sh diff --git a/tests/custom/permutations/08_image_set/unnamed/0004_find_permutation_find_sets/stdout.expected b/tests/custom/permutations/08_transform_set/unnamed/0004_find_permutation_find_sets/stdout.expected similarity index 97% rename from tests/custom/permutations/08_image_set/unnamed/0004_find_permutation_find_sets/stdout.expected rename to tests/custom/permutations/08_transform_set/unnamed/0004_find_permutation_find_sets/stdout.expected index 412c71035c..22c85d8fee 100644 --- a/tests/custom/permutations/08_image_set/unnamed/0004_find_permutation_find_sets/stdout.expected +++ b/tests/custom/permutations/08_transform_set/unnamed/0004_find_permutation_find_sets/stdout.expected @@ -2,6 +2,8 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output Savile Row: model000001.eprime +Running minion for domain filtering. +Running solver: minion Copying solution to: permutation-000001.solution Copying solution to: permutation-000002.solution Copying solution to: permutation-000003.solution diff --git a/tests/custom/permutations/09_defined/accept_these.sh b/tests/custom/permutations/09_defined/accept_these.sh new file mode 100644 index 0000000000..379ca74a6a --- /dev/null +++ b/tests/custom/permutations/09_defined/accept_these.sh @@ -0,0 +1,12 @@ +sh ../../acceptOutput.sh enum/0005_find_permutation +sh ../../acceptOutput.sh enum/0003_given_permutation +sh ../../acceptOutput.sh enum/0004_given_permutation +sh ../../acceptOutput.sh enum/0002_letting_permutation +sh ../../acceptOutput.sh enum/0001_letting_permutation +sh ../../acceptOutput.sh int/0005_find_permutation +sh ../../acceptOutput.sh int/0003_given_permutation +sh ../../acceptOutput.sh int/0004_given_permutation +sh ../../acceptOutput.sh int/0002_letting_permutation +sh ../../acceptOutput.sh int/0001_letting_permutation +sh ../../acceptOutput.sh unnamed/0005_find_permutation + diff --git a/tests/custom/permutations/09_defined/enum/0001_letting_permutation/stdout.expected b/tests/custom/permutations/09_defined/enum/0001_letting_permutation/stdout.expected index 901f2ae574..8a78c0058b 100644 --- a/tests/custom/permutations/09_defined/enum/0001_letting_permutation/stdout.expected +++ b/tests/custom/permutations/09_defined/enum/0001_letting_permutation/stdout.expected @@ -2,6 +2,8 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output Savile Row: model000001.eprime permutation.param +Running minion for domain filtering. +Running solver: minion Copying solution to: permutation-permutation.solution language Essence 1.3 diff --git a/tests/custom/permutations/09_defined/enum/0002_letting_permutation/stdout.expected b/tests/custom/permutations/09_defined/enum/0002_letting_permutation/stdout.expected index 1cc90d46bc..da9c2d6b8a 100644 --- a/tests/custom/permutations/09_defined/enum/0002_letting_permutation/stdout.expected +++ b/tests/custom/permutations/09_defined/enum/0002_letting_permutation/stdout.expected @@ -2,6 +2,8 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output Savile Row: model000001.eprime permutation.param +Running minion for domain filtering. +Running solver: minion Copying solution to: permutation-permutation.solution language Essence 1.3 diff --git a/tests/custom/permutations/09_defined/enum/0003_given_permutation/stdout.expected b/tests/custom/permutations/09_defined/enum/0003_given_permutation/stdout.expected index 901f2ae574..8a78c0058b 100644 --- a/tests/custom/permutations/09_defined/enum/0003_given_permutation/stdout.expected +++ b/tests/custom/permutations/09_defined/enum/0003_given_permutation/stdout.expected @@ -2,6 +2,8 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output Savile Row: model000001.eprime permutation.param +Running minion for domain filtering. +Running solver: minion Copying solution to: permutation-permutation.solution language Essence 1.3 diff --git a/tests/custom/permutations/09_defined/enum/0004_given_permutation/stdout.expected b/tests/custom/permutations/09_defined/enum/0004_given_permutation/stdout.expected index 64aacd0ddd..01505e3c4c 100644 --- a/tests/custom/permutations/09_defined/enum/0004_given_permutation/stdout.expected +++ b/tests/custom/permutations/09_defined/enum/0004_given_permutation/stdout.expected @@ -2,6 +2,8 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output Savile Row: model000001.eprime permutation.param +Running minion for domain filtering. +Running solver: minion Copying solution to: permutation-permutation.solution language Essence 1.3 diff --git a/tests/custom/permutations/09_defined/enum/0005_find_permutation/stdout.expected b/tests/custom/permutations/09_defined/enum/0005_find_permutation/stdout.expected index 7f88621554..e0c1eb1477 100644 --- a/tests/custom/permutations/09_defined/enum/0005_find_permutation/stdout.expected +++ b/tests/custom/permutations/09_defined/enum/0005_find_permutation/stdout.expected @@ -2,6 +2,8 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output Savile Row: model000001.eprime +Running minion for domain filtering. +Running solver: minion Copying solution to: permutation.solution language Essence 1.3 diff --git a/tests/custom/permutations/09_defined/int/0001_letting_permutation/stdout.expected b/tests/custom/permutations/09_defined/int/0001_letting_permutation/stdout.expected index 901f2ae574..8a78c0058b 100644 --- a/tests/custom/permutations/09_defined/int/0001_letting_permutation/stdout.expected +++ b/tests/custom/permutations/09_defined/int/0001_letting_permutation/stdout.expected @@ -2,6 +2,8 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output Savile Row: model000001.eprime permutation.param +Running minion for domain filtering. +Running solver: minion Copying solution to: permutation-permutation.solution language Essence 1.3 diff --git a/tests/custom/permutations/09_defined/int/0002_letting_permutation/stdout.expected b/tests/custom/permutations/09_defined/int/0002_letting_permutation/stdout.expected index 1cc90d46bc..da9c2d6b8a 100644 --- a/tests/custom/permutations/09_defined/int/0002_letting_permutation/stdout.expected +++ b/tests/custom/permutations/09_defined/int/0002_letting_permutation/stdout.expected @@ -2,6 +2,8 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output Savile Row: model000001.eprime permutation.param +Running minion for domain filtering. +Running solver: minion Copying solution to: permutation-permutation.solution language Essence 1.3 diff --git a/tests/custom/permutations/09_defined/int/0003_given_permutation/stdout.expected b/tests/custom/permutations/09_defined/int/0003_given_permutation/stdout.expected index 901f2ae574..8a78c0058b 100644 --- a/tests/custom/permutations/09_defined/int/0003_given_permutation/stdout.expected +++ b/tests/custom/permutations/09_defined/int/0003_given_permutation/stdout.expected @@ -2,6 +2,8 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output Savile Row: model000001.eprime permutation.param +Running minion for domain filtering. +Running solver: minion Copying solution to: permutation-permutation.solution language Essence 1.3 diff --git a/tests/custom/permutations/09_defined/int/0004_given_permutation/stdout.expected b/tests/custom/permutations/09_defined/int/0004_given_permutation/stdout.expected index 43cefee272..5b87dbb8c8 100644 --- a/tests/custom/permutations/09_defined/int/0004_given_permutation/stdout.expected +++ b/tests/custom/permutations/09_defined/int/0004_given_permutation/stdout.expected @@ -2,6 +2,8 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output Savile Row: model000001.eprime permutation.param +Running minion for domain filtering. +Running solver: minion Copying solution to: permutation-permutation.solution language Essence 1.3 diff --git a/tests/custom/permutations/09_defined/int/0005_find_permutation/stdout.expected b/tests/custom/permutations/09_defined/int/0005_find_permutation/stdout.expected index ddece56758..0650091188 100644 --- a/tests/custom/permutations/09_defined/int/0005_find_permutation/stdout.expected +++ b/tests/custom/permutations/09_defined/int/0005_find_permutation/stdout.expected @@ -2,6 +2,8 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output Savile Row: model000001.eprime +Running minion for domain filtering. +Running solver: minion Copying solution to: permutation.solution language Essence 1.3 diff --git a/tests/custom/permutations/09_defined/unnamed/0005_find_permutation/stdout.expected b/tests/custom/permutations/09_defined/unnamed/0005_find_permutation/stdout.expected index ab113b5a06..a03d43f7e0 100644 --- a/tests/custom/permutations/09_defined/unnamed/0005_find_permutation/stdout.expected +++ b/tests/custom/permutations/09_defined/unnamed/0005_find_permutation/stdout.expected @@ -2,6 +2,8 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output Savile Row: model000001.eprime +Running minion for domain filtering. +Running solver: minion Copying solution to: permutation.solution language Essence 1.3 diff --git a/tests/custom/permutations/10_transform_tuple/accept_these.sh b/tests/custom/permutations/10_transform_tuple/accept_these.sh new file mode 100644 index 0000000000..7c343ae8f8 --- /dev/null +++ b/tests/custom/permutations/10_transform_tuple/accept_these.sh @@ -0,0 +1,12 @@ +sh ../../acceptOutput.sh enum/0004_given_permutation_find_tuple_find_tuple +sh ../../acceptOutput.sh enum/0005_find_permutation_find_tuple_find_tuple +sh ../../acceptOutput.sh enum/0003_given_permutation_given_tuple_find_tuple +sh ../../acceptOutput.sh enum/0001_letting_permutation_given_tuple_find_tuple +sh ../../acceptOutput.sh enum/0002_letting_permutation_given_tuple_find_tuple +sh ../../acceptOutput.sh int/0004_given_permutation_find_tuple_find_tuple +sh ../../acceptOutput.sh int/0005_find_permutation_find_tuple_find_tuple +sh ../../acceptOutput.sh int/0003_given_permutation_given_tuple_find_tuple +sh ../../acceptOutput.sh int/0001_letting_permutation_given_tuple_find_tuple +sh ../../acceptOutput.sh int/0002_letting_permutation_given_tuple_find_tuple +sh ../../acceptOutput.sh unnamed/0005_find_permutation_find_tuple_find_tuple + diff --git a/tests/custom/permutations/10_image_tuple/enum/0001_letting_permutation_given_tuple_find_tuple/permutation.essence b/tests/custom/permutations/10_transform_tuple/enum/0001_letting_permutation_given_tuple_find_tuple/permutation.essence similarity index 80% rename from tests/custom/permutations/10_image_tuple/enum/0001_letting_permutation_given_tuple_find_tuple/permutation.essence rename to tests/custom/permutations/10_transform_tuple/enum/0001_letting_permutation_given_tuple_find_tuple/permutation.essence index f64f66cc18..809e9ce2fc 100644 --- a/tests/custom/permutations/10_image_tuple/enum/0001_letting_permutation_given_tuple_find_tuple/permutation.essence +++ b/tests/custom/permutations/10_transform_tuple/enum/0001_letting_permutation_given_tuple_find_tuple/permutation.essence @@ -5,5 +5,5 @@ given t : (n,n,n) find q : (n,n,n) -such that q = image(p,t) +such that q = transform(p,t) diff --git a/tests/custom/permutations/10_image_tuple/enum/0001_letting_permutation_given_tuple_find_tuple/permutation.param b/tests/custom/permutations/10_transform_tuple/enum/0001_letting_permutation_given_tuple_find_tuple/permutation.param similarity index 100% rename from tests/custom/permutations/10_image_tuple/enum/0001_letting_permutation_given_tuple_find_tuple/permutation.param rename to tests/custom/permutations/10_transform_tuple/enum/0001_letting_permutation_given_tuple_find_tuple/permutation.param diff --git a/tests/custom/permutations/10_image_tuple/enum/0001_letting_permutation_given_tuple_find_tuple/run.sh b/tests/custom/permutations/10_transform_tuple/enum/0001_letting_permutation_given_tuple_find_tuple/run.sh similarity index 100% rename from tests/custom/permutations/10_image_tuple/enum/0001_letting_permutation_given_tuple_find_tuple/run.sh rename to tests/custom/permutations/10_transform_tuple/enum/0001_letting_permutation_given_tuple_find_tuple/run.sh diff --git a/tests/custom/permutations/10_image_tuple/enum/0003_given_permutation_given_tuple_find_tuple/stdout.expected b/tests/custom/permutations/10_transform_tuple/enum/0001_letting_permutation_given_tuple_find_tuple/stdout.expected similarity index 81% rename from tests/custom/permutations/10_image_tuple/enum/0003_given_permutation_given_tuple_find_tuple/stdout.expected rename to tests/custom/permutations/10_transform_tuple/enum/0001_letting_permutation_given_tuple_find_tuple/stdout.expected index d069522cd4..119078ab0f 100644 --- a/tests/custom/permutations/10_image_tuple/enum/0003_given_permutation_given_tuple_find_tuple/stdout.expected +++ b/tests/custom/permutations/10_transform_tuple/enum/0001_letting_permutation_given_tuple_find_tuple/stdout.expected @@ -2,6 +2,8 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output Savile Row: model000001.eprime permutation.param +Running minion for domain filtering. +Running solver: minion Copying solution to: permutation-permutation.solution language Essence 1.3 diff --git a/tests/custom/permutations/10_image_tuple/enum/0002_letting_permutation_given_tuple_find_tuple/permutation.essence b/tests/custom/permutations/10_transform_tuple/enum/0002_letting_permutation_given_tuple_find_tuple/permutation.essence similarity index 80% rename from tests/custom/permutations/10_image_tuple/enum/0002_letting_permutation_given_tuple_find_tuple/permutation.essence rename to tests/custom/permutations/10_transform_tuple/enum/0002_letting_permutation_given_tuple_find_tuple/permutation.essence index cd8ec560a8..5380b03bc9 100644 --- a/tests/custom/permutations/10_image_tuple/enum/0002_letting_permutation_given_tuple_find_tuple/permutation.essence +++ b/tests/custom/permutations/10_transform_tuple/enum/0002_letting_permutation_given_tuple_find_tuple/permutation.essence @@ -5,5 +5,5 @@ given t : (n,n,n,n) find q : (n,n,n,n) -such that q = image(p,t) +such that q = transform(p,t) diff --git a/tests/custom/permutations/10_image_tuple/enum/0002_letting_permutation_given_tuple_find_tuple/permutation.param b/tests/custom/permutations/10_transform_tuple/enum/0002_letting_permutation_given_tuple_find_tuple/permutation.param similarity index 100% rename from tests/custom/permutations/10_image_tuple/enum/0002_letting_permutation_given_tuple_find_tuple/permutation.param rename to tests/custom/permutations/10_transform_tuple/enum/0002_letting_permutation_given_tuple_find_tuple/permutation.param diff --git a/tests/custom/permutations/10_image_tuple/enum/0002_letting_permutation_given_tuple_find_tuple/run.sh b/tests/custom/permutations/10_transform_tuple/enum/0002_letting_permutation_given_tuple_find_tuple/run.sh similarity index 100% rename from tests/custom/permutations/10_image_tuple/enum/0002_letting_permutation_given_tuple_find_tuple/run.sh rename to tests/custom/permutations/10_transform_tuple/enum/0002_letting_permutation_given_tuple_find_tuple/run.sh diff --git a/tests/custom/permutations/10_image_tuple/enum/0002_letting_permutation_given_tuple_find_tuple/stdout.expected b/tests/custom/permutations/10_transform_tuple/enum/0002_letting_permutation_given_tuple_find_tuple/stdout.expected similarity index 81% rename from tests/custom/permutations/10_image_tuple/enum/0002_letting_permutation_given_tuple_find_tuple/stdout.expected rename to tests/custom/permutations/10_transform_tuple/enum/0002_letting_permutation_given_tuple_find_tuple/stdout.expected index 087a53e1a2..0c60bd23b1 100644 --- a/tests/custom/permutations/10_image_tuple/enum/0002_letting_permutation_given_tuple_find_tuple/stdout.expected +++ b/tests/custom/permutations/10_transform_tuple/enum/0002_letting_permutation_given_tuple_find_tuple/stdout.expected @@ -2,6 +2,8 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output Savile Row: model000001.eprime permutation.param +Running minion for domain filtering. +Running solver: minion Copying solution to: permutation-permutation.solution language Essence 1.3 diff --git a/tests/custom/permutations/10_image_tuple/enum/0003_given_permutation_given_tuple_find_tuple/permutation.essence b/tests/custom/permutations/10_transform_tuple/enum/0003_given_permutation_given_tuple_find_tuple/permutation.essence similarity index 78% rename from tests/custom/permutations/10_image_tuple/enum/0003_given_permutation_given_tuple_find_tuple/permutation.essence rename to tests/custom/permutations/10_transform_tuple/enum/0003_given_permutation_given_tuple_find_tuple/permutation.essence index 5877cf2311..7335248377 100644 --- a/tests/custom/permutations/10_image_tuple/enum/0003_given_permutation_given_tuple_find_tuple/permutation.essence +++ b/tests/custom/permutations/10_transform_tuple/enum/0003_given_permutation_given_tuple_find_tuple/permutation.essence @@ -6,5 +6,5 @@ find q : (n,n,n) -such that q = image(p, t) +such that q = transform(p, t) diff --git a/tests/custom/permutations/10_image_tuple/enum/0003_given_permutation_given_tuple_find_tuple/permutation.param b/tests/custom/permutations/10_transform_tuple/enum/0003_given_permutation_given_tuple_find_tuple/permutation.param similarity index 100% rename from tests/custom/permutations/10_image_tuple/enum/0003_given_permutation_given_tuple_find_tuple/permutation.param rename to tests/custom/permutations/10_transform_tuple/enum/0003_given_permutation_given_tuple_find_tuple/permutation.param diff --git a/tests/custom/permutations/10_image_tuple/enum/0003_given_permutation_given_tuple_find_tuple/run.sh b/tests/custom/permutations/10_transform_tuple/enum/0003_given_permutation_given_tuple_find_tuple/run.sh similarity index 100% rename from tests/custom/permutations/10_image_tuple/enum/0003_given_permutation_given_tuple_find_tuple/run.sh rename to tests/custom/permutations/10_transform_tuple/enum/0003_given_permutation_given_tuple_find_tuple/run.sh diff --git a/tests/custom/permutations/10_image_tuple/enum/0001_letting_permutation_given_tuple_find_tuple/stdout.expected b/tests/custom/permutations/10_transform_tuple/enum/0003_given_permutation_given_tuple_find_tuple/stdout.expected similarity index 81% rename from tests/custom/permutations/10_image_tuple/enum/0001_letting_permutation_given_tuple_find_tuple/stdout.expected rename to tests/custom/permutations/10_transform_tuple/enum/0003_given_permutation_given_tuple_find_tuple/stdout.expected index d069522cd4..119078ab0f 100644 --- a/tests/custom/permutations/10_image_tuple/enum/0001_letting_permutation_given_tuple_find_tuple/stdout.expected +++ b/tests/custom/permutations/10_transform_tuple/enum/0003_given_permutation_given_tuple_find_tuple/stdout.expected @@ -2,6 +2,8 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output Savile Row: model000001.eprime permutation.param +Running minion for domain filtering. +Running solver: minion Copying solution to: permutation-permutation.solution language Essence 1.3 diff --git a/tests/custom/permutations/10_image_tuple/enum/0004_given_permutation_find_tuple_find_tuple/permutation.essence b/tests/custom/permutations/10_transform_tuple/enum/0004_given_permutation_find_tuple_find_tuple/permutation.essence similarity index 78% rename from tests/custom/permutations/10_image_tuple/enum/0004_given_permutation_find_tuple_find_tuple/permutation.essence rename to tests/custom/permutations/10_transform_tuple/enum/0004_given_permutation_find_tuple_find_tuple/permutation.essence index 0b5ba8f9f6..9b77826d33 100644 --- a/tests/custom/permutations/10_image_tuple/enum/0004_given_permutation_find_tuple_find_tuple/permutation.essence +++ b/tests/custom/permutations/10_transform_tuple/enum/0004_given_permutation_find_tuple_find_tuple/permutation.essence @@ -6,5 +6,5 @@ find q : (n,n,n) -such that q = image(p, t) +such that q = transform(p, t) diff --git a/tests/custom/permutations/10_image_tuple/enum/0004_given_permutation_find_tuple_find_tuple/permutation.param b/tests/custom/permutations/10_transform_tuple/enum/0004_given_permutation_find_tuple_find_tuple/permutation.param similarity index 100% rename from tests/custom/permutations/10_image_tuple/enum/0004_given_permutation_find_tuple_find_tuple/permutation.param rename to tests/custom/permutations/10_transform_tuple/enum/0004_given_permutation_find_tuple_find_tuple/permutation.param diff --git a/tests/custom/permutations/10_image_tuple/enum/0004_given_permutation_find_tuple_find_tuple/run.sh b/tests/custom/permutations/10_transform_tuple/enum/0004_given_permutation_find_tuple_find_tuple/run.sh similarity index 100% rename from tests/custom/permutations/10_image_tuple/enum/0004_given_permutation_find_tuple_find_tuple/run.sh rename to tests/custom/permutations/10_transform_tuple/enum/0004_given_permutation_find_tuple_find_tuple/run.sh diff --git a/tests/custom/permutations/10_image_tuple/enum/0004_given_permutation_find_tuple_find_tuple/stdout.expected b/tests/custom/permutations/10_transform_tuple/enum/0004_given_permutation_find_tuple_find_tuple/stdout.expected similarity index 96% rename from tests/custom/permutations/10_image_tuple/enum/0004_given_permutation_find_tuple_find_tuple/stdout.expected rename to tests/custom/permutations/10_transform_tuple/enum/0004_given_permutation_find_tuple_find_tuple/stdout.expected index e0cbb59c9f..fada2bec18 100644 --- a/tests/custom/permutations/10_image_tuple/enum/0004_given_permutation_find_tuple_find_tuple/stdout.expected +++ b/tests/custom/permutations/10_transform_tuple/enum/0004_given_permutation_find_tuple_find_tuple/stdout.expected @@ -2,6 +2,8 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output Savile Row: model000001.eprime permutation.param +Running minion for domain filtering. +Running solver: minion Copying solution to: permutation-permutation-000001.solution Copying solution to: permutation-permutation-000002.solution Copying solution to: permutation-permutation-000003.solution diff --git a/tests/custom/permutations/10_image_tuple/enum/0005_find_permutation_find_tuple_find_tuple/permutation.essence b/tests/custom/permutations/10_transform_tuple/enum/0005_find_permutation_find_tuple_find_tuple/permutation.essence similarity index 59% rename from tests/custom/permutations/10_image_tuple/enum/0005_find_permutation_find_tuple_find_tuple/permutation.essence rename to tests/custom/permutations/10_transform_tuple/enum/0005_find_permutation_find_tuple_find_tuple/permutation.essence index 29011a21a1..571ca969ed 100644 --- a/tests/custom/permutations/10_image_tuple/enum/0005_find_permutation_find_tuple_find_tuple/permutation.essence +++ b/tests/custom/permutations/10_transform_tuple/enum/0005_find_permutation_find_tuple_find_tuple/permutation.essence @@ -5,5 +5,5 @@ find t : (n,n,n) find q : (n,n,n) -such that (q = image(p, t)) /\ (4 = sum([toInt(l != r) | (l,r) <- p])) +such that (q = transform(p, t)) /\ (4 = sum([toInt(l != r) | (l,r) <- p])) diff --git a/tests/custom/permutations/10_image_tuple/enum/0005_find_permutation_find_tuple_find_tuple/run.sh b/tests/custom/permutations/10_transform_tuple/enum/0005_find_permutation_find_tuple_find_tuple/run.sh similarity index 100% rename from tests/custom/permutations/10_image_tuple/enum/0005_find_permutation_find_tuple_find_tuple/run.sh rename to tests/custom/permutations/10_transform_tuple/enum/0005_find_permutation_find_tuple_find_tuple/run.sh diff --git a/tests/custom/permutations/10_image_tuple/enum/0005_find_permutation_find_tuple_find_tuple/stdout.expected b/tests/custom/permutations/10_transform_tuple/enum/0005_find_permutation_find_tuple_find_tuple/stdout.expected similarity index 96% rename from tests/custom/permutations/10_image_tuple/enum/0005_find_permutation_find_tuple_find_tuple/stdout.expected rename to tests/custom/permutations/10_transform_tuple/enum/0005_find_permutation_find_tuple_find_tuple/stdout.expected index 9540e6c30c..cf25cc15d1 100644 --- a/tests/custom/permutations/10_image_tuple/enum/0005_find_permutation_find_tuple_find_tuple/stdout.expected +++ b/tests/custom/permutations/10_transform_tuple/enum/0005_find_permutation_find_tuple_find_tuple/stdout.expected @@ -2,6 +2,8 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output Savile Row: model000001.eprime +Running minion for domain filtering. +Running solver: minion Copying solution to: permutation-000001.solution Copying solution to: permutation-000002.solution Copying solution to: permutation-000003.solution diff --git a/tests/custom/permutations/10_image_tuple/int/0001_letting_permutation_given_tuple_find_tuple/permutation.essence b/tests/custom/permutations/10_transform_tuple/int/0001_letting_permutation_given_tuple_find_tuple/permutation.essence similarity index 82% rename from tests/custom/permutations/10_image_tuple/int/0001_letting_permutation_given_tuple_find_tuple/permutation.essence rename to tests/custom/permutations/10_transform_tuple/int/0001_letting_permutation_given_tuple_find_tuple/permutation.essence index 8ff47ec02b..79c73e43c8 100644 --- a/tests/custom/permutations/10_image_tuple/int/0001_letting_permutation_given_tuple_find_tuple/permutation.essence +++ b/tests/custom/permutations/10_transform_tuple/int/0001_letting_permutation_given_tuple_find_tuple/permutation.essence @@ -4,5 +4,5 @@ letting p be permutation((1,3,4)) given t : (int(1..5), int(1..5), int(1..5)) find q : (int(1..5), int(1..5), int(1..5)) -such that q = image(p,t) +such that q = transform(p,t) diff --git a/tests/custom/permutations/10_image_tuple/int/0001_letting_permutation_given_tuple_find_tuple/permutation.param b/tests/custom/permutations/10_transform_tuple/int/0001_letting_permutation_given_tuple_find_tuple/permutation.param similarity index 100% rename from tests/custom/permutations/10_image_tuple/int/0001_letting_permutation_given_tuple_find_tuple/permutation.param rename to tests/custom/permutations/10_transform_tuple/int/0001_letting_permutation_given_tuple_find_tuple/permutation.param diff --git a/tests/custom/permutations/10_image_tuple/int/0001_letting_permutation_given_tuple_find_tuple/run.sh b/tests/custom/permutations/10_transform_tuple/int/0001_letting_permutation_given_tuple_find_tuple/run.sh similarity index 100% rename from tests/custom/permutations/10_image_tuple/int/0001_letting_permutation_given_tuple_find_tuple/run.sh rename to tests/custom/permutations/10_transform_tuple/int/0001_letting_permutation_given_tuple_find_tuple/run.sh diff --git a/tests/custom/permutations/10_image_tuple/int/0001_letting_permutation_given_tuple_find_tuple/stdout.expected b/tests/custom/permutations/10_transform_tuple/int/0001_letting_permutation_given_tuple_find_tuple/stdout.expected similarity index 80% rename from tests/custom/permutations/10_image_tuple/int/0001_letting_permutation_given_tuple_find_tuple/stdout.expected rename to tests/custom/permutations/10_transform_tuple/int/0001_letting_permutation_given_tuple_find_tuple/stdout.expected index 719e5b7b9c..e4d0d07195 100644 --- a/tests/custom/permutations/10_image_tuple/int/0001_letting_permutation_given_tuple_find_tuple/stdout.expected +++ b/tests/custom/permutations/10_transform_tuple/int/0001_letting_permutation_given_tuple_find_tuple/stdout.expected @@ -2,6 +2,8 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output Savile Row: model000001.eprime permutation.param +Running minion for domain filtering. +Running solver: minion Copying solution to: permutation-permutation.solution language Essence 1.3 diff --git a/tests/custom/permutations/10_image_tuple/int/0002_letting_permutation_given_tuple_find_tuple/permutation.essence b/tests/custom/permutations/10_transform_tuple/int/0002_letting_permutation_given_tuple_find_tuple/permutation.essence similarity index 84% rename from tests/custom/permutations/10_image_tuple/int/0002_letting_permutation_given_tuple_find_tuple/permutation.essence rename to tests/custom/permutations/10_transform_tuple/int/0002_letting_permutation_given_tuple_find_tuple/permutation.essence index dbdc925827..0258b0fed0 100644 --- a/tests/custom/permutations/10_image_tuple/int/0002_letting_permutation_given_tuple_find_tuple/permutation.essence +++ b/tests/custom/permutations/10_transform_tuple/int/0002_letting_permutation_given_tuple_find_tuple/permutation.essence @@ -4,5 +4,5 @@ letting p be permutation((1,3,4)) given t : (int(1..5), int(1..5), int(1..5), int(1..5)) find q : (int(1..5), int(1..5), int(1..5), int(1..5)) -such that q = image(p,t) +such that q = transform(p,t) diff --git a/tests/custom/permutations/10_image_tuple/int/0002_letting_permutation_given_tuple_find_tuple/permutation.param b/tests/custom/permutations/10_transform_tuple/int/0002_letting_permutation_given_tuple_find_tuple/permutation.param similarity index 100% rename from tests/custom/permutations/10_image_tuple/int/0002_letting_permutation_given_tuple_find_tuple/permutation.param rename to tests/custom/permutations/10_transform_tuple/int/0002_letting_permutation_given_tuple_find_tuple/permutation.param diff --git a/tests/custom/permutations/10_image_tuple/int/0002_letting_permutation_given_tuple_find_tuple/run.sh b/tests/custom/permutations/10_transform_tuple/int/0002_letting_permutation_given_tuple_find_tuple/run.sh similarity index 100% rename from tests/custom/permutations/10_image_tuple/int/0002_letting_permutation_given_tuple_find_tuple/run.sh rename to tests/custom/permutations/10_transform_tuple/int/0002_letting_permutation_given_tuple_find_tuple/run.sh diff --git a/tests/custom/permutations/10_image_tuple/int/0002_letting_permutation_given_tuple_find_tuple/stdout.expected b/tests/custom/permutations/10_transform_tuple/int/0002_letting_permutation_given_tuple_find_tuple/stdout.expected similarity index 81% rename from tests/custom/permutations/10_image_tuple/int/0002_letting_permutation_given_tuple_find_tuple/stdout.expected rename to tests/custom/permutations/10_transform_tuple/int/0002_letting_permutation_given_tuple_find_tuple/stdout.expected index f0593a67be..8acee4491e 100644 --- a/tests/custom/permutations/10_image_tuple/int/0002_letting_permutation_given_tuple_find_tuple/stdout.expected +++ b/tests/custom/permutations/10_transform_tuple/int/0002_letting_permutation_given_tuple_find_tuple/stdout.expected @@ -2,6 +2,8 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output Savile Row: model000001.eprime permutation.param +Running minion for domain filtering. +Running solver: minion Copying solution to: permutation-permutation.solution language Essence 1.3 diff --git a/tests/custom/permutations/10_image_tuple/int/0003_given_permutation_given_tuple_find_tuple/permutation.essence b/tests/custom/permutations/10_transform_tuple/int/0003_given_permutation_given_tuple_find_tuple/permutation.essence similarity index 82% rename from tests/custom/permutations/10_image_tuple/int/0003_given_permutation_given_tuple_find_tuple/permutation.essence rename to tests/custom/permutations/10_transform_tuple/int/0003_given_permutation_given_tuple_find_tuple/permutation.essence index ed4d8c10a4..64c3e549c8 100644 --- a/tests/custom/permutations/10_image_tuple/int/0003_given_permutation_given_tuple_find_tuple/permutation.essence +++ b/tests/custom/permutations/10_transform_tuple/int/0003_given_permutation_given_tuple_find_tuple/permutation.essence @@ -6,5 +6,5 @@ find q : (int(1..n), int(1..n), int(1..n)) -such that q = image(p, t) +such that q = transform(p, t) diff --git a/tests/custom/permutations/10_image_tuple/int/0003_given_permutation_given_tuple_find_tuple/permutation.param b/tests/custom/permutations/10_transform_tuple/int/0003_given_permutation_given_tuple_find_tuple/permutation.param similarity index 100% rename from tests/custom/permutations/10_image_tuple/int/0003_given_permutation_given_tuple_find_tuple/permutation.param rename to tests/custom/permutations/10_transform_tuple/int/0003_given_permutation_given_tuple_find_tuple/permutation.param diff --git a/tests/custom/permutations/10_image_tuple/int/0003_given_permutation_given_tuple_find_tuple/run.sh b/tests/custom/permutations/10_transform_tuple/int/0003_given_permutation_given_tuple_find_tuple/run.sh similarity index 100% rename from tests/custom/permutations/10_image_tuple/int/0003_given_permutation_given_tuple_find_tuple/run.sh rename to tests/custom/permutations/10_transform_tuple/int/0003_given_permutation_given_tuple_find_tuple/run.sh diff --git a/tests/custom/permutations/10_image_tuple/int/0003_given_permutation_given_tuple_find_tuple/stdout.expected b/tests/custom/permutations/10_transform_tuple/int/0003_given_permutation_given_tuple_find_tuple/stdout.expected similarity index 80% rename from tests/custom/permutations/10_image_tuple/int/0003_given_permutation_given_tuple_find_tuple/stdout.expected rename to tests/custom/permutations/10_transform_tuple/int/0003_given_permutation_given_tuple_find_tuple/stdout.expected index 719e5b7b9c..e4d0d07195 100644 --- a/tests/custom/permutations/10_image_tuple/int/0003_given_permutation_given_tuple_find_tuple/stdout.expected +++ b/tests/custom/permutations/10_transform_tuple/int/0003_given_permutation_given_tuple_find_tuple/stdout.expected @@ -2,6 +2,8 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output Savile Row: model000001.eprime permutation.param +Running minion for domain filtering. +Running solver: minion Copying solution to: permutation-permutation.solution language Essence 1.3 diff --git a/tests/custom/permutations/10_image_tuple/int/0004_given_permutation_find_tuple_find_tuple/permutation.essence b/tests/custom/permutations/10_transform_tuple/int/0004_given_permutation_find_tuple_find_tuple/permutation.essence similarity index 82% rename from tests/custom/permutations/10_image_tuple/int/0004_given_permutation_find_tuple_find_tuple/permutation.essence rename to tests/custom/permutations/10_transform_tuple/int/0004_given_permutation_find_tuple_find_tuple/permutation.essence index 688cb2c963..233e718845 100644 --- a/tests/custom/permutations/10_image_tuple/int/0004_given_permutation_find_tuple_find_tuple/permutation.essence +++ b/tests/custom/permutations/10_transform_tuple/int/0004_given_permutation_find_tuple_find_tuple/permutation.essence @@ -6,5 +6,5 @@ find q : (int(1..n), int(1..n), int(1..n)) -such that q = image(p, t) +such that q = transform(p, t) diff --git a/tests/custom/permutations/10_image_tuple/int/0004_given_permutation_find_tuple_find_tuple/permutation.param b/tests/custom/permutations/10_transform_tuple/int/0004_given_permutation_find_tuple_find_tuple/permutation.param similarity index 100% rename from tests/custom/permutations/10_image_tuple/int/0004_given_permutation_find_tuple_find_tuple/permutation.param rename to tests/custom/permutations/10_transform_tuple/int/0004_given_permutation_find_tuple_find_tuple/permutation.param diff --git a/tests/custom/permutations/10_image_tuple/int/0004_given_permutation_find_tuple_find_tuple/run.sh b/tests/custom/permutations/10_transform_tuple/int/0004_given_permutation_find_tuple_find_tuple/run.sh similarity index 100% rename from tests/custom/permutations/10_image_tuple/int/0004_given_permutation_find_tuple_find_tuple/run.sh rename to tests/custom/permutations/10_transform_tuple/int/0004_given_permutation_find_tuple_find_tuple/run.sh diff --git a/tests/custom/permutations/10_image_tuple/int/0004_given_permutation_find_tuple_find_tuple/stdout.expected b/tests/custom/permutations/10_transform_tuple/int/0004_given_permutation_find_tuple_find_tuple/stdout.expected similarity index 96% rename from tests/custom/permutations/10_image_tuple/int/0004_given_permutation_find_tuple_find_tuple/stdout.expected rename to tests/custom/permutations/10_transform_tuple/int/0004_given_permutation_find_tuple_find_tuple/stdout.expected index 88540848fd..343b8187b5 100644 --- a/tests/custom/permutations/10_image_tuple/int/0004_given_permutation_find_tuple_find_tuple/stdout.expected +++ b/tests/custom/permutations/10_transform_tuple/int/0004_given_permutation_find_tuple_find_tuple/stdout.expected @@ -2,6 +2,8 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output Savile Row: model000001.eprime permutation.param +Running minion for domain filtering. +Running solver: minion Copying solution to: permutation-permutation-000001.solution Copying solution to: permutation-permutation-000002.solution Copying solution to: permutation-permutation-000003.solution diff --git a/tests/custom/permutations/10_image_tuple/int/0005_find_permutation_find_tuple_find_tuple/permutation.essence b/tests/custom/permutations/10_transform_tuple/int/0005_find_permutation_find_tuple_find_tuple/permutation.essence similarity index 65% rename from tests/custom/permutations/10_image_tuple/int/0005_find_permutation_find_tuple_find_tuple/permutation.essence rename to tests/custom/permutations/10_transform_tuple/int/0005_find_permutation_find_tuple_find_tuple/permutation.essence index e06c7ffc0d..8550cdb22e 100644 --- a/tests/custom/permutations/10_image_tuple/int/0005_find_permutation_find_tuple_find_tuple/permutation.essence +++ b/tests/custom/permutations/10_transform_tuple/int/0005_find_permutation_find_tuple_find_tuple/permutation.essence @@ -6,5 +6,5 @@ find q : (int(1..n), int(1..n), int(1..n)) -such that (q = image(p, t)) /\ (4 = sum([toInt(l != r) | (l,r) <- p])) +such that (q = transform(p, t)) /\ (4 = sum([toInt(l != r) | (l,r) <- p])) diff --git a/tests/custom/permutations/10_image_tuple/int/0005_find_permutation_find_tuple_find_tuple/run.sh b/tests/custom/permutations/10_transform_tuple/int/0005_find_permutation_find_tuple_find_tuple/run.sh similarity index 100% rename from tests/custom/permutations/10_image_tuple/int/0005_find_permutation_find_tuple_find_tuple/run.sh rename to tests/custom/permutations/10_transform_tuple/int/0005_find_permutation_find_tuple_find_tuple/run.sh diff --git a/tests/custom/permutations/10_image_tuple/int/0005_find_permutation_find_tuple_find_tuple/stdout.expected b/tests/custom/permutations/10_transform_tuple/int/0005_find_permutation_find_tuple_find_tuple/stdout.expected similarity index 96% rename from tests/custom/permutations/10_image_tuple/int/0005_find_permutation_find_tuple_find_tuple/stdout.expected rename to tests/custom/permutations/10_transform_tuple/int/0005_find_permutation_find_tuple_find_tuple/stdout.expected index 4413c9de83..98113abbf7 100644 --- a/tests/custom/permutations/10_image_tuple/int/0005_find_permutation_find_tuple_find_tuple/stdout.expected +++ b/tests/custom/permutations/10_transform_tuple/int/0005_find_permutation_find_tuple_find_tuple/stdout.expected @@ -2,6 +2,8 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output Savile Row: model000001.eprime +Running minion for domain filtering. +Running solver: minion Copying solution to: permutation-000001.solution Copying solution to: permutation-000002.solution Copying solution to: permutation-000003.solution diff --git a/tests/custom/permutations/10_image_tuple/runthese.sh b/tests/custom/permutations/10_transform_tuple/runthese.sh similarity index 69% rename from tests/custom/permutations/10_image_tuple/runthese.sh rename to tests/custom/permutations/10_transform_tuple/runthese.sh index 47ef7cdc6b..20a2d14ad1 100644 --- a/tests/custom/permutations/10_image_tuple/runthese.sh +++ b/tests/custom/permutations/10_transform_tuple/runthese.sh @@ -1 +1 @@ -stack build --copy-bins --test --test-arguments "-p custom.permutations.10_image_tuple" +stack build --copy-bins --test --test-arguments "-p custom.permutations.10_transform_tuple" diff --git a/tests/custom/permutations/10_image_tuple/unnamed/0005_find_permutation_find_tuple_find_tuple/permutation.essence b/tests/custom/permutations/10_transform_tuple/unnamed/0005_find_permutation_find_tuple_find_tuple/permutation.essence similarity index 56% rename from tests/custom/permutations/10_image_tuple/unnamed/0005_find_permutation_find_tuple_find_tuple/permutation.essence rename to tests/custom/permutations/10_transform_tuple/unnamed/0005_find_permutation_find_tuple_find_tuple/permutation.essence index dade0a1bf6..c5a863cb53 100644 --- a/tests/custom/permutations/10_image_tuple/unnamed/0005_find_permutation_find_tuple_find_tuple/permutation.essence +++ b/tests/custom/permutations/10_transform_tuple/unnamed/0005_find_permutation_find_tuple_find_tuple/permutation.essence @@ -5,5 +5,5 @@ find t : (n,n,n) find q : (n,n,n) -such that (q = image(p, t)) /\ (4 = sum([toInt(l != r) | (l,r) <- p])) +such that (q = transform(p, t)) /\ (4 = sum([toInt(l != r) | (l,r) <- p])) diff --git a/tests/custom/permutations/10_image_tuple/unnamed/0005_find_permutation_find_tuple_find_tuple/run.sh b/tests/custom/permutations/10_transform_tuple/unnamed/0005_find_permutation_find_tuple_find_tuple/run.sh similarity index 100% rename from tests/custom/permutations/10_image_tuple/unnamed/0005_find_permutation_find_tuple_find_tuple/run.sh rename to tests/custom/permutations/10_transform_tuple/unnamed/0005_find_permutation_find_tuple_find_tuple/run.sh diff --git a/tests/custom/permutations/10_image_tuple/unnamed/0005_find_permutation_find_tuple_find_tuple/stdout.expected b/tests/custom/permutations/10_transform_tuple/unnamed/0005_find_permutation_find_tuple_find_tuple/stdout.expected similarity index 97% rename from tests/custom/permutations/10_image_tuple/unnamed/0005_find_permutation_find_tuple_find_tuple/stdout.expected rename to tests/custom/permutations/10_transform_tuple/unnamed/0005_find_permutation_find_tuple_find_tuple/stdout.expected index 8ed90d7f24..1548177d90 100644 --- a/tests/custom/permutations/10_image_tuple/unnamed/0005_find_permutation_find_tuple_find_tuple/stdout.expected +++ b/tests/custom/permutations/10_transform_tuple/unnamed/0005_find_permutation_find_tuple_find_tuple/stdout.expected @@ -2,6 +2,8 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output Savile Row: model000001.eprime +Running minion for domain filtering. +Running solver: minion Copying solution to: permutation-000001.solution Copying solution to: permutation-000002.solution Copying solution to: permutation-000003.solution From 08a4b30a38d7ef2e61a5953605d50f2f34b553ee Mon Sep 17 00:00:00 2001 From: Fraser Dunlop Date: Fri, 11 Oct 2019 17:04:54 +0100 Subject: [PATCH 106/229] fixed some permutation tests --- .../11_transform_relation/accept_these.sh | 9 +++++++ .../permutation.essence | 2 +- .../permutation.param | 0 .../run.sh | 0 .../stdout.expected | 2 ++ .../permutation.essence | 2 +- .../permutation.param | 0 .../run.sh | 0 .../stdout.expected | 2 ++ .../permutation.essence | 2 +- .../permutation.param | 0 .../run.sh | 0 .../stdout.expected | 2 ++ .../permutation.essence | 2 +- .../run.sh | 0 .../stdout.expected | 2 ++ .../permutation.essence | 2 +- .../permutation.param | 0 .../run.sh | 0 .../stdout.expected | 2 ++ .../permutation.essence | 2 +- .../permutation.param | 0 .../run.sh | 0 .../stdout.expected | 2 ++ .../permutation.essence | 2 +- .../permutation.param | 0 .../run.sh | 0 .../stdout.expected | 2 ++ .../permutation.essence | 2 +- .../run.sh | 0 .../stdout.expected | 2 ++ .../runthese.sh | 2 +- .../permutation.essence | 2 +- .../run.sh | 0 .../stdout.expected | 2 ++ .../0030_find_permutation/permutation.essence | 6 ----- .../12_transform_list/accept_these.sh | 8 ++++++ .../permutation.essence | 2 +- .../0010_given_permutation/permutation.param | 0 .../enum/0010_given_permutation/run.sh | 0 .../0010_given_permutation/stdout.expected | 2 ++ .../permutation.essence | 2 +- .../enum/0020_letting_permutation/run.sh | 0 .../0020_letting_permutation/stdout.expected | 2 ++ .../0030_find_permutation/permutation.essence | 2 +- .../enum/0030_find_permutation/run.sh | 0 .../0030_find_permutation/stdout.expected | 2 ++ .../permutation.essence | 2 +- .../0010_given_permutation/permutation.param | 0 .../int/0010_given_permutation/run.sh | 0 .../0010_given_permutation/stdout.expected | 2 ++ .../permutation.essence | 2 +- .../int/0020_letting_permutation/run.sh | 0 .../0020_letting_permutation/stdout.expected | 2 ++ .../0030_find_permutation/permutation.essence | 6 +++++ .../int/0030_find_permutation/run.sh | 0 .../int/0030_find_permutation/stdout.expected | 2 ++ .../runthese.sh | 2 +- .../0030_find_permutation/permutation.essence | 2 +- .../unnamed/0030_find_permutation/run.sh | 0 .../0030_find_permutation/stdout.expected | 2 ++ .../13_transform_function/accept_these.sh | 7 ++++++ .../permutation.essence | 2 +- .../0010_given_permutation/permutation.param | 0 .../enum/0010_given_permutation/run.sh | 0 .../0010_given_permutation/stdout.expected | 2 ++ .../permutation.essence | 2 +- .../enum/0020_letting_permutation/run.sh | 0 .../0020_letting_permutation/stdout.expected | 2 ++ .../0030_find_permutation/permutation.essence | 2 +- .../enum/0030_find_permutation/run.sh | 0 .../0030_find_permutation/stdout.expected | 2 ++ .../permutation.essence | 2 +- .../0010_given_permutation/permutation.param | 0 .../int/0010_given_permutation/run.sh | 0 .../0010_given_permutation/stdout.expected | 2 ++ .../permutation.essence | 2 +- .../int/0020_letting_permutation/run.sh | 0 .../0020_letting_permutation/stdout.expected | 2 ++ .../0030_find_permutation/permutation.essence | 2 +- .../int/0030_find_permutation/run.sh | 0 .../int/0030_find_permutation/stdout.expected | 2 ++ .../13_transform_function/runthese.sh | 1 + .../0030_find_permutation/permutation.essence | 2 +- .../unnamed/0030_find_permutation/run.sh | 0 .../0030_find_permutation/stdout.expected | 2 ++ .../14_transform_sequence/accept_these.sh | 7 ++++++ .../permutation.essence | 2 +- .../0010_given_permutation/permutation.param | 0 .../enum/0010_given_permutation/run.sh | 0 .../0010_given_permutation/stdout.expected | 2 ++ .../permutation.essence | 2 +- .../enum/0020_letting_permutation/run.sh | 0 .../0020_letting_permutation/stdout.expected | 2 ++ .../0030_find_permutation/permutation.essence | 2 +- .../enum/0030_find_permutation/run.sh | 0 .../0030_find_permutation/stdout.expected | 2 ++ .../permutation.essence | 2 +- .../0010_given_permutation/permutation.param | 0 .../int/0010_given_permutation/run.sh | 0 .../0010_given_permutation/stdout.expected | 2 ++ .../permutation.essence | 2 +- .../int/0020_letting_permutation/run.sh | 0 .../0020_letting_permutation/stdout.expected | 2 ++ .../0030_find_permutation/permutation.essence | 2 +- .../int/0030_find_permutation/run.sh | 0 .../int/0030_find_permutation/stdout.expected | 2 ++ .../14_transform_sequence/runthese.sh | 1 + .../0030_find_permutation/permutation.essence | 2 +- .../unnamed/0030_find_permutation/run.sh | 0 .../0030_find_permutation/stdout.expected | 2 ++ .../permutations/15_image_mset/runthese.sh | 1 - .../15_transform_mset/accept_these.sh | 11 ++++++++ .../permutation.essence | 2 +- .../permutation.param | 0 .../run.sh | 0 .../stdout.expected | 2 ++ .../permutation.essence | 2 +- .../permutation.param | 0 .../0020_given_permutation_find_msets/run.sh | 0 .../stdout.expected | 2 ++ .../permutation.essence | 2 +- .../run.sh | 0 .../stdout.expected | 2 ++ .../permutation.essence | 2 +- .../0040_find_permutation_find_msets/run.sh | 0 .../stdout.expected | 2 ++ .../permutation.essence | 2 +- .../permutation.param | 0 .../run.sh | 0 .../stdout.expected | 2 ++ .../permutation.essence | 2 +- .../permutation.param | 0 .../run.sh | 0 .../stdout.expected | 2 ++ .../permutation.essence | 2 +- .../permutation.param | 0 .../0020_given_permutation_find_msets/run.sh | 0 .../stdout.expected | 2 ++ .../permutation.essence | 2 +- .../run.sh | 0 .../stdout.expected | 2 ++ .../permutation.essence | 2 +- .../0040_find_permutation_find_msets/run.sh | 0 .../stdout.expected | 2 ++ .../permutation.essence | 2 +- .../permutation.param | 0 .../run.sh | 0 .../stdout.expected | 2 ++ .../runthese.sh | 2 +- .../permutation.essence | 2 +- .../0004_find_permutation_find_msets/run.sh | 0 .../stdout.expected | 2 ++ .../16_image_permutation/runthese.sh | 1 - .../16_transform_permutation/accept_these.sh | 11 ++++++++ .../permutation.essence | 2 +- .../permutation.param | 0 .../run.sh | 0 .../stdout.expected | 2 ++ .../permutation.essence | 2 +- .../permutation.param | 0 .../run.sh | 0 .../stdout.expected | 2 ++ .../permutation.essence | 2 +- .../run.sh | 0 .../stdout.expected | 2 ++ .../permutation.essence | 2 +- .../run.sh | 0 .../stdout.expected | 2 ++ .../permutation.essence | 2 +- .../permutation.param | 0 .../run.sh | 0 .../stdout.expected | 2 ++ .../permutation.essence | 2 +- .../permutation.param | 0 .../run.sh | 0 .../stdout.expected | 2 ++ .../permutation.essence | 2 +- .../permutation.param | 0 .../run.sh | 0 .../stdout.expected | 2 ++ .../permutation.essence | 2 +- .../run.sh | 0 .../stdout.expected | 2 ++ .../permutation.essence | 2 +- .../run.sh | 0 .../stdout.expected | 2 ++ .../permutation.essence | 2 +- .../permutation.param | 0 .../run.sh | 0 .../stdout.expected | 2 ++ .../16_transform_permutation/runthese.sh | 1 + .../permutation.essence | 2 +- .../run.sh | 0 .../stdout.expected | 2 ++ .../stderr.expected | 25 ------------------- .../17_image_partition/runthese.sh | 1 - .../BUGS.md | 0 .../17_transform_partition/accept_these.sh | 7 ++++++ .../permutation.essence | 0 .../permutation.param | 0 .../0010_given_partition_of_enum_BUG/run.sh | 0 .../stderr.expected | 6 +++++ .../stdout.expected | 0 .../permutation.essence | 0 .../0020_find_partition_of_enum_BUG/run.sh | 0 .../stderr.expected | 0 .../stdout.expected | 0 .../permutation.essence | 2 +- .../permutation.param | 0 .../run.sh | 0 .../stdout.expected | 2 ++ .../permutation.essence | 2 +- .../permutation.param | 0 .../run.sh | 0 .../stdout.expected | 2 ++ .../permutation.essence | 2 +- .../run.sh | 0 .../stdout.expected | 2 ++ .../permutation.essence | 2 +- .../run.sh | 0 .../stdout.expected | 2 ++ .../permutation.essence | 2 +- .../permutation.param | 0 .../run.sh | 0 .../stdout.expected | 2 ++ .../17_transform_partition/runthese.sh | 1 + .../permutation.essence | 2 +- .../0010_find_partition_of_unnamed/run.sh | 0 .../stdout.expected | 2 ++ .../permutations/18_image_matrix/runthese.sh | 1 - .../permutation.essence | 2 +- .../permutation.param | 0 .../run.sh | 0 .../stdout.expected | 0 .../permutation.essence | 2 +- .../run.sh | 0 .../stdout.expected | 0 .../permutation.essence | 2 +- .../permutation.param | 0 .../run.sh | 0 .../stdout.expected | 0 .../permutation.essence | 2 +- .../permutation.param | 0 .../run.sh | 0 .../stdout.expected | 0 .../permutation.essence | 2 +- .../run.sh | 0 .../stdout.expected | 0 .../permutation.essence | 2 +- .../permutation.param | 0 .../run.sh | 0 .../stdout.expected | 0 .../permutation.essence | 2 +- .../run.sh | 0 .../stdout.expected | 0 .../permutation.essence | 2 +- .../permutation.param | 0 .../run.sh | 0 .../stdout.expected | 0 .../permutation.essence | 2 +- .../permutation.param | 0 .../run.sh | 0 .../stdout.expected | 0 .../runthese.sh | 2 +- .../permutation.essence | 2 +- .../run.sh | 0 .../stdout.expected | 0 268 files changed, 263 insertions(+), 106 deletions(-) create mode 100644 tests/custom/permutations/11_transform_relation/accept_these.sh rename tests/custom/permutations/{11_image_relation => 11_transform_relation}/enum/0010_given_permutation_letting_relation/permutation.essence (81%) rename tests/custom/permutations/{11_image_relation => 11_transform_relation}/enum/0010_given_permutation_letting_relation/permutation.param (100%) rename tests/custom/permutations/{11_image_relation => 11_transform_relation}/enum/0010_given_permutation_letting_relation/run.sh (100%) rename tests/custom/permutations/{11_image_relation => 11_transform_relation}/enum/0010_given_permutation_letting_relation/stdout.expected (84%) rename tests/custom/permutations/{11_image_relation => 11_transform_relation}/enum/0020_letting_permutation_letting_relation/permutation.essence (82%) rename tests/custom/permutations/{11_image_relation => 11_transform_relation}/enum/0020_letting_permutation_letting_relation/permutation.param (100%) rename tests/custom/permutations/{11_image_relation => 11_transform_relation}/enum/0020_letting_permutation_letting_relation/run.sh (100%) rename tests/custom/permutations/{11_image_relation => 11_transform_relation}/enum/0020_letting_permutation_letting_relation/stdout.expected (84%) rename tests/custom/permutations/{11_image_relation => 11_transform_relation}/enum/0030_find_permutation_given_relation/permutation.essence (65%) rename tests/custom/permutations/{11_image_relation => 11_transform_relation}/enum/0030_find_permutation_given_relation/permutation.param (100%) rename tests/custom/permutations/{11_image_relation => 11_transform_relation}/enum/0030_find_permutation_given_relation/run.sh (100%) rename tests/custom/permutations/{11_image_relation => 11_transform_relation}/enum/0030_find_permutation_given_relation/stdout.expected (85%) rename tests/custom/permutations/{11_image_relation => 11_transform_relation}/enum/0040_find_permutation_find_relation/permutation.essence (61%) rename tests/custom/permutations/{11_image_relation => 11_transform_relation}/enum/0040_find_permutation_find_relation/run.sh (100%) rename tests/custom/permutations/{11_image_relation => 11_transform_relation}/enum/0040_find_permutation_find_relation/stdout.expected (88%) rename tests/custom/permutations/{11_image_relation => 11_transform_relation}/int/0010_given_permutation_letting_relation/permutation.essence (82%) rename tests/custom/permutations/{11_image_relation => 11_transform_relation}/int/0010_given_permutation_letting_relation/permutation.param (100%) rename tests/custom/permutations/{11_image_relation => 11_transform_relation}/int/0010_given_permutation_letting_relation/run.sh (100%) rename tests/custom/permutations/{11_image_relation => 11_transform_relation}/int/0010_given_permutation_letting_relation/stdout.expected (83%) rename tests/custom/permutations/{11_image_relation => 11_transform_relation}/int/0020_letting_permutation_letting_relation/permutation.essence (82%) rename tests/custom/permutations/{11_image_relation => 11_transform_relation}/int/0020_letting_permutation_letting_relation/permutation.param (100%) rename tests/custom/permutations/{11_image_relation => 11_transform_relation}/int/0020_letting_permutation_letting_relation/run.sh (100%) rename tests/custom/permutations/{11_image_relation => 11_transform_relation}/int/0020_letting_permutation_letting_relation/stdout.expected (83%) rename tests/custom/permutations/{11_image_relation => 11_transform_relation}/int/0030_find_permutation_given_relation/permutation.essence (67%) rename tests/custom/permutations/{11_image_relation => 11_transform_relation}/int/0030_find_permutation_given_relation/permutation.param (100%) rename tests/custom/permutations/{11_image_relation => 11_transform_relation}/int/0030_find_permutation_given_relation/run.sh (100%) rename tests/custom/permutations/{11_image_relation => 11_transform_relation}/int/0030_find_permutation_given_relation/stdout.expected (85%) rename tests/custom/permutations/{11_image_relation => 11_transform_relation}/int/0040_find_permutation_find_relation/permutation.essence (63%) rename tests/custom/permutations/{11_image_relation => 11_transform_relation}/int/0040_find_permutation_find_relation/run.sh (100%) rename tests/custom/permutations/{11_image_relation => 11_transform_relation}/int/0040_find_permutation_find_relation/stdout.expected (88%) rename tests/custom/permutations/{14_image_sequence => 11_transform_relation}/runthese.sh (67%) rename tests/custom/permutations/{11_image_relation => 11_transform_relation}/unnamed/0040_find_permutation_find_relation/permutation.essence (59%) rename tests/custom/permutations/{11_image_relation => 11_transform_relation}/unnamed/0040_find_permutation_find_relation/run.sh (100%) rename tests/custom/permutations/{11_image_relation => 11_transform_relation}/unnamed/0040_find_permutation_find_relation/stdout.expected (90%) delete mode 100644 tests/custom/permutations/12_image_list/int/0030_find_permutation/permutation.essence create mode 100644 tests/custom/permutations/12_transform_list/accept_these.sh rename tests/custom/permutations/{12_image_list => 12_transform_list}/enum/0010_given_permutation/permutation.essence (59%) rename tests/custom/permutations/{12_image_list => 12_transform_list}/enum/0010_given_permutation/permutation.param (100%) rename tests/custom/permutations/{12_image_list => 12_transform_list}/enum/0010_given_permutation/run.sh (100%) rename tests/custom/permutations/{12_image_list => 12_transform_list}/enum/0010_given_permutation/stdout.expected (80%) rename tests/custom/permutations/{12_image_list => 12_transform_list}/enum/0020_letting_permutation/permutation.essence (61%) rename tests/custom/permutations/{12_image_list => 12_transform_list}/enum/0020_letting_permutation/run.sh (100%) rename tests/custom/permutations/{12_image_list => 12_transform_list}/enum/0020_letting_permutation/stdout.expected (78%) rename tests/custom/permutations/{12_image_list => 12_transform_list}/enum/0030_find_permutation/permutation.essence (54%) rename tests/custom/permutations/{12_image_list => 12_transform_list}/enum/0030_find_permutation/run.sh (100%) rename tests/custom/permutations/{12_image_list => 12_transform_list}/enum/0030_find_permutation/stdout.expected (80%) rename tests/custom/permutations/{12_image_list => 12_transform_list}/int/0010_given_permutation/permutation.essence (58%) rename tests/custom/permutations/{12_image_list => 12_transform_list}/int/0010_given_permutation/permutation.param (100%) rename tests/custom/permutations/{12_image_list => 12_transform_list}/int/0010_given_permutation/run.sh (100%) rename tests/custom/permutations/{12_image_list => 12_transform_list}/int/0010_given_permutation/stdout.expected (80%) rename tests/custom/permutations/{12_image_list => 12_transform_list}/int/0020_letting_permutation/permutation.essence (57%) rename tests/custom/permutations/{12_image_list => 12_transform_list}/int/0020_letting_permutation/run.sh (100%) rename tests/custom/permutations/{12_image_list => 12_transform_list}/int/0020_letting_permutation/stdout.expected (78%) create mode 100644 tests/custom/permutations/12_transform_list/int/0030_find_permutation/permutation.essence rename tests/custom/permutations/{12_image_list => 12_transform_list}/int/0030_find_permutation/run.sh (100%) rename tests/custom/permutations/{12_image_list => 12_transform_list}/int/0030_find_permutation/stdout.expected (80%) rename tests/custom/permutations/{11_image_relation => 12_transform_list}/runthese.sh (70%) rename tests/custom/permutations/{12_image_list => 12_transform_list}/unnamed/0030_find_permutation/permutation.essence (56%) rename tests/custom/permutations/{12_image_list => 12_transform_list}/unnamed/0030_find_permutation/run.sh (100%) rename tests/custom/permutations/{12_image_list => 12_transform_list}/unnamed/0030_find_permutation/stdout.expected (84%) create mode 100644 tests/custom/permutations/13_transform_function/accept_these.sh rename tests/custom/permutations/{13_image_function => 13_transform_function}/enum/0010_given_permutation/permutation.essence (82%) rename tests/custom/permutations/{13_image_function => 13_transform_function}/enum/0010_given_permutation/permutation.param (100%) rename tests/custom/permutations/{13_image_function => 13_transform_function}/enum/0010_given_permutation/run.sh (100%) rename tests/custom/permutations/{13_image_function => 13_transform_function}/enum/0010_given_permutation/stdout.expected (82%) rename tests/custom/permutations/{13_image_function => 13_transform_function}/enum/0020_letting_permutation/permutation.essence (82%) rename tests/custom/permutations/{13_image_function => 13_transform_function}/enum/0020_letting_permutation/run.sh (100%) rename tests/custom/permutations/{13_image_function => 13_transform_function}/enum/0020_letting_permutation/stdout.expected (80%) rename tests/custom/permutations/{13_image_function => 13_transform_function}/enum/0030_find_permutation/permutation.essence (83%) rename tests/custom/permutations/{13_image_function => 13_transform_function}/enum/0030_find_permutation/run.sh (100%) rename tests/custom/permutations/{13_image_function => 13_transform_function}/enum/0030_find_permutation/stdout.expected (79%) rename tests/custom/permutations/{13_image_function => 13_transform_function}/int/0010_given_permutation/permutation.essence (81%) rename tests/custom/permutations/{13_image_function => 13_transform_function}/int/0010_given_permutation/permutation.param (100%) rename tests/custom/permutations/{13_image_function => 13_transform_function}/int/0010_given_permutation/run.sh (100%) rename tests/custom/permutations/{13_image_function => 13_transform_function}/int/0010_given_permutation/stdout.expected (81%) rename tests/custom/permutations/{13_image_function => 13_transform_function}/int/0020_letting_permutation/permutation.essence (81%) rename tests/custom/permutations/{13_image_function => 13_transform_function}/int/0020_letting_permutation/run.sh (100%) rename tests/custom/permutations/{13_image_function => 13_transform_function}/int/0020_letting_permutation/stdout.expected (80%) rename tests/custom/permutations/{13_image_function => 13_transform_function}/int/0030_find_permutation/permutation.essence (80%) rename tests/custom/permutations/{13_image_function => 13_transform_function}/int/0030_find_permutation/run.sh (100%) rename tests/custom/permutations/{13_image_function => 13_transform_function}/int/0030_find_permutation/stdout.expected (79%) create mode 100644 tests/custom/permutations/13_transform_function/runthese.sh rename tests/custom/permutations/{13_image_function => 13_transform_function}/unnamed/0030_find_permutation/permutation.essence (69%) rename tests/custom/permutations/{13_image_function => 13_transform_function}/unnamed/0030_find_permutation/run.sh (100%) rename tests/custom/permutations/{13_image_function => 13_transform_function}/unnamed/0030_find_permutation/stdout.expected (85%) create mode 100644 tests/custom/permutations/14_transform_sequence/accept_these.sh rename tests/custom/permutations/{14_image_sequence => 14_transform_sequence}/enum/0010_given_permutation/permutation.essence (82%) rename tests/custom/permutations/{14_image_sequence => 14_transform_sequence}/enum/0010_given_permutation/permutation.param (100%) rename tests/custom/permutations/{14_image_sequence => 14_transform_sequence}/enum/0010_given_permutation/run.sh (100%) rename tests/custom/permutations/{14_image_sequence => 14_transform_sequence}/enum/0010_given_permutation/stdout.expected (81%) rename tests/custom/permutations/{14_image_sequence => 14_transform_sequence}/enum/0020_letting_permutation/permutation.essence (83%) rename tests/custom/permutations/{14_image_sequence => 14_transform_sequence}/enum/0020_letting_permutation/run.sh (100%) rename tests/custom/permutations/{14_image_sequence => 14_transform_sequence}/enum/0020_letting_permutation/stdout.expected (80%) rename tests/custom/permutations/{14_image_sequence => 14_transform_sequence}/enum/0030_find_permutation/permutation.essence (82%) rename tests/custom/permutations/{14_image_sequence => 14_transform_sequence}/enum/0030_find_permutation/run.sh (100%) rename tests/custom/permutations/{14_image_sequence => 14_transform_sequence}/enum/0030_find_permutation/stdout.expected (80%) rename tests/custom/permutations/{14_image_sequence => 14_transform_sequence}/int/0010_given_permutation/permutation.essence (80%) rename tests/custom/permutations/{14_image_sequence => 14_transform_sequence}/int/0010_given_permutation/permutation.param (100%) rename tests/custom/permutations/{14_image_sequence => 14_transform_sequence}/int/0010_given_permutation/run.sh (100%) rename tests/custom/permutations/{14_image_sequence => 14_transform_sequence}/int/0010_given_permutation/stdout.expected (81%) rename tests/custom/permutations/{14_image_sequence => 14_transform_sequence}/int/0020_letting_permutation/permutation.essence (80%) rename tests/custom/permutations/{14_image_sequence => 14_transform_sequence}/int/0020_letting_permutation/run.sh (100%) rename tests/custom/permutations/{14_image_sequence => 14_transform_sequence}/int/0020_letting_permutation/stdout.expected (79%) rename tests/custom/permutations/{14_image_sequence => 14_transform_sequence}/int/0030_find_permutation/permutation.essence (79%) rename tests/custom/permutations/{14_image_sequence => 14_transform_sequence}/int/0030_find_permutation/run.sh (100%) rename tests/custom/permutations/{14_image_sequence => 14_transform_sequence}/int/0030_find_permutation/stdout.expected (80%) create mode 100644 tests/custom/permutations/14_transform_sequence/runthese.sh rename tests/custom/permutations/{14_image_sequence => 14_transform_sequence}/unnamed/0030_find_permutation/permutation.essence (76%) rename tests/custom/permutations/{14_image_sequence => 14_transform_sequence}/unnamed/0030_find_permutation/run.sh (100%) rename tests/custom/permutations/{14_image_sequence => 14_transform_sequence}/unnamed/0030_find_permutation/stdout.expected (86%) delete mode 100644 tests/custom/permutations/15_image_mset/runthese.sh create mode 100644 tests/custom/permutations/15_transform_mset/accept_these.sh rename tests/custom/permutations/{15_image_mset => 15_transform_mset}/enum/0010_given_permutation_letting_mset/permutation.essence (81%) rename tests/custom/permutations/{15_image_mset => 15_transform_mset}/enum/0010_given_permutation_letting_mset/permutation.param (100%) rename tests/custom/permutations/{15_image_mset => 15_transform_mset}/enum/0010_given_permutation_letting_mset/run.sh (100%) rename tests/custom/permutations/{15_image_mset => 15_transform_mset}/enum/0010_given_permutation_letting_mset/stdout.expected (81%) rename tests/custom/permutations/{15_image_mset => 15_transform_mset}/enum/0020_given_permutation_find_msets/permutation.essence (81%) rename tests/custom/permutations/{15_image_mset => 15_transform_mset}/enum/0020_given_permutation_find_msets/permutation.param (100%) rename tests/custom/permutations/{15_image_mset => 15_transform_mset}/enum/0020_given_permutation_find_msets/run.sh (100%) rename tests/custom/permutations/{15_image_mset => 15_transform_mset}/enum/0020_given_permutation_find_msets/stdout.expected (96%) rename tests/custom/permutations/{15_image_mset => 15_transform_mset}/enum/0030_letting_permutation_find_msets/permutation.essence (82%) rename tests/custom/permutations/{15_image_mset => 15_transform_mset}/enum/0030_letting_permutation_find_msets/run.sh (100%) rename tests/custom/permutations/{15_image_mset => 15_transform_mset}/enum/0030_letting_permutation_find_msets/stdout.expected (95%) rename tests/custom/permutations/{15_image_mset => 15_transform_mset}/enum/0040_find_permutation_find_msets/permutation.essence (63%) rename tests/custom/permutations/{15_image_mset => 15_transform_mset}/enum/0040_find_permutation_find_msets/run.sh (100%) rename tests/custom/permutations/{15_image_mset => 15_transform_mset}/enum/0040_find_permutation_find_msets/stdout.expected (97%) rename tests/custom/permutations/{15_image_mset => 15_transform_mset}/enum/0050_find_permutation_given_mset_find_mset/permutation.essence (62%) rename tests/custom/permutations/{15_image_mset => 15_transform_mset}/enum/0050_find_permutation_given_mset_find_mset/permutation.param (100%) rename tests/custom/permutations/{15_image_mset => 15_transform_mset}/enum/0050_find_permutation_given_mset_find_mset/run.sh (100%) rename tests/custom/permutations/{15_image_mset => 15_transform_mset}/enum/0050_find_permutation_given_mset_find_mset/stdout.expected (95%) rename tests/custom/permutations/{15_image_mset => 15_transform_mset}/int/0010_given_permutation_letting_mset/permutation.essence (80%) rename tests/custom/permutations/{15_image_mset => 15_transform_mset}/int/0010_given_permutation_letting_mset/permutation.param (100%) rename tests/custom/permutations/{15_image_mset => 15_transform_mset}/int/0010_given_permutation_letting_mset/run.sh (100%) rename tests/custom/permutations/{15_image_mset => 15_transform_mset}/int/0010_given_permutation_letting_mset/stdout.expected (81%) rename tests/custom/permutations/{15_image_mset => 15_transform_mset}/int/0020_given_permutation_find_msets/permutation.essence (80%) rename tests/custom/permutations/{15_image_mset => 15_transform_mset}/int/0020_given_permutation_find_msets/permutation.param (100%) rename tests/custom/permutations/{15_image_mset => 15_transform_mset}/int/0020_given_permutation_find_msets/run.sh (100%) rename tests/custom/permutations/{15_image_mset => 15_transform_mset}/int/0020_given_permutation_find_msets/stdout.expected (96%) rename tests/custom/permutations/{15_image_mset => 15_transform_mset}/int/0030_letting_permutation_find_msets/permutation.essence (80%) rename tests/custom/permutations/{15_image_mset => 15_transform_mset}/int/0030_letting_permutation_find_msets/run.sh (100%) rename tests/custom/permutations/{15_image_mset => 15_transform_mset}/int/0030_letting_permutation_find_msets/stdout.expected (96%) rename tests/custom/permutations/{15_image_mset => 15_transform_mset}/int/0040_find_permutation_find_msets/permutation.essence (75%) rename tests/custom/permutations/{15_image_mset => 15_transform_mset}/int/0040_find_permutation_find_msets/run.sh (100%) rename tests/custom/permutations/{15_image_mset => 15_transform_mset}/int/0040_find_permutation_find_msets/stdout.expected (96%) rename tests/custom/permutations/{15_image_mset => 15_transform_mset}/int/0050_find_permutation_given_mset_find_mset/permutation.essence (62%) rename tests/custom/permutations/{15_image_mset => 15_transform_mset}/int/0050_find_permutation_given_mset_find_mset/permutation.param (100%) rename tests/custom/permutations/{15_image_mset => 15_transform_mset}/int/0050_find_permutation_given_mset_find_mset/run.sh (100%) rename tests/custom/permutations/{15_image_mset => 15_transform_mset}/int/0050_find_permutation_given_mset_find_mset/stdout.expected (95%) rename tests/custom/permutations/{12_image_list => 15_transform_mset}/runthese.sh (70%) rename tests/custom/permutations/{15_image_mset => 15_transform_mset}/unnamed/0004_find_permutation_find_msets/permutation.essence (62%) rename tests/custom/permutations/{15_image_mset => 15_transform_mset}/unnamed/0004_find_permutation_find_msets/run.sh (100%) rename tests/custom/permutations/{15_image_mset => 15_transform_mset}/unnamed/0004_find_permutation_find_msets/stdout.expected (97%) delete mode 100644 tests/custom/permutations/16_image_permutation/runthese.sh create mode 100644 tests/custom/permutations/16_transform_permutation/accept_these.sh rename tests/custom/permutations/{16_image_permutation => 16_transform_permutation}/enum/0010_given_permutation_letting_permutation/permutation.essence (80%) rename tests/custom/permutations/{16_image_permutation => 16_transform_permutation}/enum/0010_given_permutation_letting_permutation/permutation.param (100%) rename tests/custom/permutations/{16_image_permutation => 16_transform_permutation}/enum/0010_given_permutation_letting_permutation/run.sh (100%) rename tests/custom/permutations/{16_image_permutation => 16_transform_permutation}/enum/0010_given_permutation_letting_permutation/stdout.expected (82%) rename tests/custom/permutations/{16_image_permutation => 16_transform_permutation}/enum/0020_given_permutation_find_permutations/permutation.essence (71%) rename tests/custom/permutations/{16_image_permutation => 16_transform_permutation}/enum/0020_given_permutation_find_permutations/permutation.param (100%) rename tests/custom/permutations/{16_image_permutation => 16_transform_permutation}/enum/0020_given_permutation_find_permutations/run.sh (100%) rename tests/custom/permutations/{16_image_permutation => 16_transform_permutation}/enum/0020_given_permutation_find_permutations/stdout.expected (96%) rename tests/custom/permutations/{16_image_permutation => 16_transform_permutation}/enum/0030_letting_permutation_find_permutations/permutation.essence (81%) rename tests/custom/permutations/{16_image_permutation => 16_transform_permutation}/enum/0030_letting_permutation_find_permutations/run.sh (100%) rename tests/custom/permutations/{16_image_permutation => 16_transform_permutation}/enum/0030_letting_permutation_find_permutations/stdout.expected (96%) rename tests/custom/permutations/{16_image_permutation => 16_transform_permutation}/enum/0040_find_permutation_find_permutations/permutation.essence (75%) rename tests/custom/permutations/{16_image_permutation => 16_transform_permutation}/enum/0040_find_permutation_find_permutations/run.sh (100%) rename tests/custom/permutations/{16_image_permutation => 16_transform_permutation}/enum/0040_find_permutation_find_permutations/stdout.expected (97%) rename tests/custom/permutations/{16_image_permutation => 16_transform_permutation}/enum/0050_find_permutation_given_permutation_find_permutation/permutation.essence (81%) rename tests/custom/permutations/{16_image_permutation => 16_transform_permutation}/enum/0050_find_permutation_given_permutation_find_permutation/permutation.param (100%) rename tests/custom/permutations/{16_image_permutation => 16_transform_permutation}/enum/0050_find_permutation_given_permutation_find_permutation/run.sh (100%) rename tests/custom/permutations/{16_image_permutation => 16_transform_permutation}/enum/0050_find_permutation_given_permutation_find_permutation/stdout.expected (96%) rename tests/custom/permutations/{16_image_permutation => 16_transform_permutation}/int/0010_given_permutation_letting_permutation/permutation.essence (80%) rename tests/custom/permutations/{16_image_permutation => 16_transform_permutation}/int/0010_given_permutation_letting_permutation/permutation.param (100%) rename tests/custom/permutations/{16_image_permutation => 16_transform_permutation}/int/0010_given_permutation_letting_permutation/run.sh (100%) rename tests/custom/permutations/{16_image_permutation => 16_transform_permutation}/int/0010_given_permutation_letting_permutation/stdout.expected (82%) rename tests/custom/permutations/{16_image_permutation => 16_transform_permutation}/int/0020_given_permutation_find_permutations/permutation.essence (70%) rename tests/custom/permutations/{16_image_permutation => 16_transform_permutation}/int/0020_given_permutation_find_permutations/permutation.param (100%) rename tests/custom/permutations/{16_image_permutation => 16_transform_permutation}/int/0020_given_permutation_find_permutations/run.sh (100%) rename tests/custom/permutations/{16_image_permutation => 16_transform_permutation}/int/0020_given_permutation_find_permutations/stdout.expected (96%) rename tests/custom/permutations/{16_image_permutation => 16_transform_permutation}/int/0030_letting_permutation_find_permutations/permutation.essence (80%) rename tests/custom/permutations/{16_image_permutation => 16_transform_permutation}/int/0030_letting_permutation_find_permutations/run.sh (100%) rename tests/custom/permutations/{16_image_permutation => 16_transform_permutation}/int/0030_letting_permutation_find_permutations/stdout.expected (96%) rename tests/custom/permutations/{16_image_permutation => 16_transform_permutation}/int/0040_find_permutation_find_permutations/permutation.essence (74%) rename tests/custom/permutations/{16_image_permutation => 16_transform_permutation}/int/0040_find_permutation_find_permutations/run.sh (100%) rename tests/custom/permutations/{16_image_permutation => 16_transform_permutation}/int/0040_find_permutation_find_permutations/stdout.expected (96%) rename tests/custom/permutations/{16_image_permutation => 16_transform_permutation}/int/0050_find_permutation_given_permutation_find_permutation/permutation.essence (80%) rename tests/custom/permutations/{16_image_permutation => 16_transform_permutation}/int/0050_find_permutation_given_permutation_find_permutation/permutation.param (100%) rename tests/custom/permutations/{16_image_permutation => 16_transform_permutation}/int/0050_find_permutation_given_permutation_find_permutation/run.sh (100%) rename tests/custom/permutations/{16_image_permutation => 16_transform_permutation}/int/0050_find_permutation_given_permutation_find_permutation/stdout.expected (96%) create mode 100644 tests/custom/permutations/16_transform_permutation/runthese.sh rename tests/custom/permutations/{16_image_permutation => 16_transform_permutation}/unnamed/0004_find_permutation_find_permutations/permutation.essence (74%) rename tests/custom/permutations/{16_image_permutation => 16_transform_permutation}/unnamed/0004_find_permutation_find_permutations/run.sh (100%) rename tests/custom/permutations/{16_image_permutation => 16_transform_permutation}/unnamed/0004_find_permutation_find_permutations/stdout.expected (97%) delete mode 100644 tests/custom/permutations/17_image_partition/enum/0010_given_partition_of_enum_BUG/stderr.expected delete mode 100644 tests/custom/permutations/17_image_partition/runthese.sh rename tests/custom/permutations/{17_image_partition => 17_transform_partition}/BUGS.md (100%) create mode 100644 tests/custom/permutations/17_transform_partition/accept_these.sh rename tests/custom/permutations/{17_image_partition => 17_transform_partition}/enum/0010_given_partition_of_enum_BUG/permutation.essence (100%) rename tests/custom/permutations/{17_image_partition => 17_transform_partition}/enum/0010_given_partition_of_enum_BUG/permutation.param (100%) rename tests/custom/permutations/{17_image_partition => 17_transform_partition}/enum/0010_given_partition_of_enum_BUG/run.sh (100%) create mode 100644 tests/custom/permutations/17_transform_partition/enum/0010_given_partition_of_enum_BUG/stderr.expected rename tests/custom/permutations/{17_image_partition => 17_transform_partition}/enum/0010_given_partition_of_enum_BUG/stdout.expected (100%) rename tests/custom/permutations/{17_image_partition => 17_transform_partition}/enum/0020_find_partition_of_enum_BUG/permutation.essence (100%) rename tests/custom/permutations/{17_image_partition => 17_transform_partition}/enum/0020_find_partition_of_enum_BUG/run.sh (100%) rename tests/custom/permutations/{17_image_partition => 17_transform_partition}/enum/0020_find_partition_of_enum_BUG/stderr.expected (100%) rename tests/custom/permutations/{17_image_partition => 17_transform_partition}/enum/0020_find_partition_of_enum_BUG/stdout.expected (100%) rename tests/custom/permutations/{17_image_partition => 17_transform_partition}/int/0010_given_permutation_partition_find_partition/permutation.essence (80%) rename tests/custom/permutations/{17_image_partition => 17_transform_partition}/int/0010_given_permutation_partition_find_partition/permutation.param (100%) rename tests/custom/permutations/{17_image_partition => 17_transform_partition}/int/0010_given_permutation_partition_find_partition/run.sh (100%) rename tests/custom/permutations/{17_image_partition => 17_transform_partition}/int/0010_given_permutation_partition_find_partition/stdout.expected (83%) rename tests/custom/permutations/{17_image_partition => 17_transform_partition}/int/0020_given_permutation_find_partitions/permutation.essence (70%) rename tests/custom/permutations/{17_image_partition => 17_transform_partition}/int/0020_given_permutation_find_partitions/permutation.param (100%) rename tests/custom/permutations/{17_image_partition => 17_transform_partition}/int/0020_given_permutation_find_partitions/run.sh (100%) rename tests/custom/permutations/{17_image_partition => 17_transform_partition}/int/0020_given_permutation_find_partitions/stdout.expected (97%) rename tests/custom/permutations/{17_image_partition => 17_transform_partition}/int/0030_letting_permutation_find_partitions/permutation.essence (80%) rename tests/custom/permutations/{17_image_partition => 17_transform_partition}/int/0030_letting_permutation_find_partitions/run.sh (100%) rename tests/custom/permutations/{17_image_partition => 17_transform_partition}/int/0030_letting_permutation_find_partitions/stdout.expected (97%) rename tests/custom/permutations/{17_image_partition => 17_transform_partition}/int/0040_find_permutation_find_partitions/permutation.essence (74%) rename tests/custom/permutations/{17_image_partition => 17_transform_partition}/int/0040_find_permutation_find_partitions/run.sh (100%) rename tests/custom/permutations/{17_image_partition => 17_transform_partition}/int/0040_find_permutation_find_partitions/stdout.expected (97%) rename tests/custom/permutations/{17_image_partition => 17_transform_partition}/int/0050_find_permutation_given_partition_find_partition/permutation.essence (80%) rename tests/custom/permutations/{17_image_partition => 17_transform_partition}/int/0050_find_permutation_given_partition_find_partition/permutation.param (100%) rename tests/custom/permutations/{17_image_partition => 17_transform_partition}/int/0050_find_permutation_given_partition_find_partition/run.sh (100%) rename tests/custom/permutations/{17_image_partition => 17_transform_partition}/int/0050_find_permutation_given_partition_find_partition/stdout.expected (97%) create mode 100644 tests/custom/permutations/17_transform_partition/runthese.sh rename tests/custom/permutations/{17_image_partition => 17_transform_partition}/unnamed/0010_find_partition_of_unnamed/permutation.essence (75%) rename tests/custom/permutations/{17_image_partition => 17_transform_partition}/unnamed/0010_find_partition_of_unnamed/run.sh (100%) rename tests/custom/permutations/{17_image_partition => 17_transform_partition}/unnamed/0010_find_partition_of_unnamed/stdout.expected (98%) delete mode 100644 tests/custom/permutations/18_image_matrix/runthese.sh rename tests/custom/permutations/{18_image_matrix => 18_transform_matrix}/enum/0010_find_permutation_indexing_given_matrix/permutation.essence (75%) rename tests/custom/permutations/{18_image_matrix => 18_transform_matrix}/enum/0010_find_permutation_indexing_given_matrix/permutation.param (100%) rename tests/custom/permutations/{18_image_matrix => 18_transform_matrix}/enum/0010_find_permutation_indexing_given_matrix/run.sh (100%) rename tests/custom/permutations/{18_image_matrix => 18_transform_matrix}/enum/0010_find_permutation_indexing_given_matrix/stdout.expected (100%) rename tests/custom/permutations/{18_image_matrix => 18_transform_matrix}/enum/0015_find_permutation_indexing_given_matrix/permutation.essence (75%) rename tests/custom/permutations/{18_image_matrix => 18_transform_matrix}/enum/0015_find_permutation_indexing_given_matrix/run.sh (100%) rename tests/custom/permutations/{18_image_matrix => 18_transform_matrix}/enum/0015_find_permutation_indexing_given_matrix/stdout.expected (100%) rename tests/custom/permutations/{18_image_matrix => 18_transform_matrix}/enum/0020_given_permutation_and_matrix_find_matrix/permutation.essence (85%) rename tests/custom/permutations/{18_image_matrix => 18_transform_matrix}/enum/0020_given_permutation_and_matrix_find_matrix/permutation.param (100%) rename tests/custom/permutations/{18_image_matrix => 18_transform_matrix}/enum/0020_given_permutation_and_matrix_find_matrix/run.sh (100%) rename tests/custom/permutations/{18_image_matrix => 18_transform_matrix}/enum/0020_given_permutation_and_matrix_find_matrix/stdout.expected (100%) rename tests/custom/permutations/{18_image_matrix => 18_transform_matrix}/enum/0030_letting_permutation_given_matrix_find_matrix/permutation.essence (85%) rename tests/custom/permutations/{18_image_matrix => 18_transform_matrix}/enum/0030_letting_permutation_given_matrix_find_matrix/permutation.param (100%) rename tests/custom/permutations/{18_image_matrix => 18_transform_matrix}/enum/0030_letting_permutation_given_matrix_find_matrix/run.sh (100%) rename tests/custom/permutations/{18_image_matrix => 18_transform_matrix}/enum/0030_letting_permutation_given_matrix_find_matrix/stdout.expected (100%) rename tests/custom/permutations/{18_image_matrix => 18_transform_matrix}/enum/0040_find_permutation_find_matrices/permutation.essence (80%) rename tests/custom/permutations/{18_image_matrix => 18_transform_matrix}/enum/0040_find_permutation_find_matrices/run.sh (100%) rename tests/custom/permutations/{18_image_matrix => 18_transform_matrix}/enum/0040_find_permutation_find_matrices/stdout.expected (100%) rename tests/custom/permutations/{18_image_matrix => 18_transform_matrix}/int/0010_find_permutation_indexing_given_matrix/permutation.essence (76%) rename tests/custom/permutations/{18_image_matrix => 18_transform_matrix}/int/0010_find_permutation_indexing_given_matrix/permutation.param (100%) rename tests/custom/permutations/{18_image_matrix => 18_transform_matrix}/int/0010_find_permutation_indexing_given_matrix/run.sh (100%) rename tests/custom/permutations/{18_image_matrix => 18_transform_matrix}/int/0010_find_permutation_indexing_given_matrix/stdout.expected (100%) rename tests/custom/permutations/{18_image_matrix => 18_transform_matrix}/int/0015_find_permutation_indexing_given_matrix/permutation.essence (70%) rename tests/custom/permutations/{18_image_matrix => 18_transform_matrix}/int/0015_find_permutation_indexing_given_matrix/run.sh (100%) rename tests/custom/permutations/{18_image_matrix => 18_transform_matrix}/int/0015_find_permutation_indexing_given_matrix/stdout.expected (100%) rename tests/custom/permutations/{18_image_matrix => 18_transform_matrix}/int/0020_given_permutation_and_matrix_find_matrix/permutation.essence (84%) rename tests/custom/permutations/{18_image_matrix => 18_transform_matrix}/int/0020_given_permutation_and_matrix_find_matrix/permutation.param (100%) rename tests/custom/permutations/{18_image_matrix => 18_transform_matrix}/int/0020_given_permutation_and_matrix_find_matrix/run.sh (100%) rename tests/custom/permutations/{18_image_matrix => 18_transform_matrix}/int/0020_given_permutation_and_matrix_find_matrix/stdout.expected (100%) rename tests/custom/permutations/{18_image_matrix => 18_transform_matrix}/int/0030_letting_permutation_given_matrix_find_matrix/permutation.essence (84%) rename tests/custom/permutations/{18_image_matrix => 18_transform_matrix}/int/0030_letting_permutation_given_matrix_find_matrix/permutation.param (100%) rename tests/custom/permutations/{18_image_matrix => 18_transform_matrix}/int/0030_letting_permutation_given_matrix_find_matrix/run.sh (100%) rename tests/custom/permutations/{18_image_matrix => 18_transform_matrix}/int/0030_letting_permutation_given_matrix_find_matrix/stdout.expected (100%) rename tests/custom/permutations/{13_image_function => 18_transform_matrix}/runthese.sh (68%) rename tests/custom/permutations/{18_image_matrix => 18_transform_matrix}/unnamed/0040_find_permutation_find_matrices/permutation.essence (78%) rename tests/custom/permutations/{18_image_matrix => 18_transform_matrix}/unnamed/0040_find_permutation_find_matrices/run.sh (100%) rename tests/custom/permutations/{18_image_matrix => 18_transform_matrix}/unnamed/0040_find_permutation_find_matrices/stdout.expected (100%) diff --git a/tests/custom/permutations/11_transform_relation/accept_these.sh b/tests/custom/permutations/11_transform_relation/accept_these.sh new file mode 100644 index 0000000000..c1260104cd --- /dev/null +++ b/tests/custom/permutations/11_transform_relation/accept_these.sh @@ -0,0 +1,9 @@ +sh ../../acceptOutput.sh enum/0040_find_permutation_find_relation +sh ../../acceptOutput.sh enum/0010_given_permutation_letting_relation +sh ../../acceptOutput.sh enum/0030_find_permutation_given_relation +sh ../../acceptOutput.sh enum/0020_letting_permutation_letting_relation +sh ../../acceptOutput.sh int/0040_find_permutation_find_relation +sh ../../acceptOutput.sh int/0010_given_permutation_letting_relation +sh ../../acceptOutput.sh int/0030_find_permutation_given_relation +sh ../../acceptOutput.sh int/0020_letting_permutation_letting_relation +sh ../../acceptOutput.sh unnamed/0040_find_permutation_find_relation diff --git a/tests/custom/permutations/11_image_relation/enum/0010_given_permutation_letting_relation/permutation.essence b/tests/custom/permutations/11_transform_relation/enum/0010_given_permutation_letting_relation/permutation.essence similarity index 81% rename from tests/custom/permutations/11_image_relation/enum/0010_given_permutation_letting_relation/permutation.essence rename to tests/custom/permutations/11_transform_relation/enum/0010_given_permutation_letting_relation/permutation.essence index 5ccea8a6b8..6cd61c8ad9 100644 --- a/tests/custom/permutations/11_image_relation/enum/0010_given_permutation_letting_relation/permutation.essence +++ b/tests/custom/permutations/11_transform_relation/enum/0010_given_permutation_letting_relation/permutation.essence @@ -7,5 +7,5 @@ find sn : relation of (n * n) -such that sn = image(p,s) +such that sn = transform(p,s) diff --git a/tests/custom/permutations/11_image_relation/enum/0010_given_permutation_letting_relation/permutation.param b/tests/custom/permutations/11_transform_relation/enum/0010_given_permutation_letting_relation/permutation.param similarity index 100% rename from tests/custom/permutations/11_image_relation/enum/0010_given_permutation_letting_relation/permutation.param rename to tests/custom/permutations/11_transform_relation/enum/0010_given_permutation_letting_relation/permutation.param diff --git a/tests/custom/permutations/11_image_relation/enum/0010_given_permutation_letting_relation/run.sh b/tests/custom/permutations/11_transform_relation/enum/0010_given_permutation_letting_relation/run.sh similarity index 100% rename from tests/custom/permutations/11_image_relation/enum/0010_given_permutation_letting_relation/run.sh rename to tests/custom/permutations/11_transform_relation/enum/0010_given_permutation_letting_relation/run.sh diff --git a/tests/custom/permutations/11_image_relation/enum/0010_given_permutation_letting_relation/stdout.expected b/tests/custom/permutations/11_transform_relation/enum/0010_given_permutation_letting_relation/stdout.expected similarity index 84% rename from tests/custom/permutations/11_image_relation/enum/0010_given_permutation_letting_relation/stdout.expected rename to tests/custom/permutations/11_transform_relation/enum/0010_given_permutation_letting_relation/stdout.expected index 0958f891d2..b53a3621a3 100644 --- a/tests/custom/permutations/11_image_relation/enum/0010_given_permutation_letting_relation/stdout.expected +++ b/tests/custom/permutations/11_transform_relation/enum/0010_given_permutation_letting_relation/stdout.expected @@ -2,6 +2,8 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output Savile Row: model000001.eprime permutation.param +Running minion for domain filtering. +Running solver: minion Copying solution to: permutation-permutation.solution language Essence 1.3 diff --git a/tests/custom/permutations/11_image_relation/enum/0020_letting_permutation_letting_relation/permutation.essence b/tests/custom/permutations/11_transform_relation/enum/0020_letting_permutation_letting_relation/permutation.essence similarity index 82% rename from tests/custom/permutations/11_image_relation/enum/0020_letting_permutation_letting_relation/permutation.essence rename to tests/custom/permutations/11_transform_relation/enum/0020_letting_permutation_letting_relation/permutation.essence index 02e9f6473d..3a4dfe80e1 100644 --- a/tests/custom/permutations/11_image_relation/enum/0020_letting_permutation_letting_relation/permutation.essence +++ b/tests/custom/permutations/11_transform_relation/enum/0020_letting_permutation_letting_relation/permutation.essence @@ -7,5 +7,5 @@ find sn : relation of (n * n) -such that sn = image(p,s) +such that sn = transform(p,s) diff --git a/tests/custom/permutations/11_image_relation/enum/0020_letting_permutation_letting_relation/permutation.param b/tests/custom/permutations/11_transform_relation/enum/0020_letting_permutation_letting_relation/permutation.param similarity index 100% rename from tests/custom/permutations/11_image_relation/enum/0020_letting_permutation_letting_relation/permutation.param rename to tests/custom/permutations/11_transform_relation/enum/0020_letting_permutation_letting_relation/permutation.param diff --git a/tests/custom/permutations/11_image_relation/enum/0020_letting_permutation_letting_relation/run.sh b/tests/custom/permutations/11_transform_relation/enum/0020_letting_permutation_letting_relation/run.sh similarity index 100% rename from tests/custom/permutations/11_image_relation/enum/0020_letting_permutation_letting_relation/run.sh rename to tests/custom/permutations/11_transform_relation/enum/0020_letting_permutation_letting_relation/run.sh diff --git a/tests/custom/permutations/11_image_relation/enum/0020_letting_permutation_letting_relation/stdout.expected b/tests/custom/permutations/11_transform_relation/enum/0020_letting_permutation_letting_relation/stdout.expected similarity index 84% rename from tests/custom/permutations/11_image_relation/enum/0020_letting_permutation_letting_relation/stdout.expected rename to tests/custom/permutations/11_transform_relation/enum/0020_letting_permutation_letting_relation/stdout.expected index 0958f891d2..b53a3621a3 100644 --- a/tests/custom/permutations/11_image_relation/enum/0020_letting_permutation_letting_relation/stdout.expected +++ b/tests/custom/permutations/11_transform_relation/enum/0020_letting_permutation_letting_relation/stdout.expected @@ -2,6 +2,8 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output Savile Row: model000001.eprime permutation.param +Running minion for domain filtering. +Running solver: minion Copying solution to: permutation-permutation.solution language Essence 1.3 diff --git a/tests/custom/permutations/11_image_relation/enum/0030_find_permutation_given_relation/permutation.essence b/tests/custom/permutations/11_transform_relation/enum/0030_find_permutation_given_relation/permutation.essence similarity index 65% rename from tests/custom/permutations/11_image_relation/enum/0030_find_permutation_given_relation/permutation.essence rename to tests/custom/permutations/11_transform_relation/enum/0030_find_permutation_given_relation/permutation.essence index 3e30e185cb..c6196d1228 100644 --- a/tests/custom/permutations/11_image_relation/enum/0030_find_permutation_given_relation/permutation.essence +++ b/tests/custom/permutations/11_transform_relation/enum/0030_find_permutation_given_relation/permutation.essence @@ -7,4 +7,4 @@ find sn : relation of (n * n) -such that sn = image(p,s) /\ (3 = sum([ toInt(l!=r) | (l,r) <- p])) +such that sn = transform(p,s) /\ (3 = sum([ toInt(l!=r) | (l,r) <- p])) diff --git a/tests/custom/permutations/11_image_relation/enum/0030_find_permutation_given_relation/permutation.param b/tests/custom/permutations/11_transform_relation/enum/0030_find_permutation_given_relation/permutation.param similarity index 100% rename from tests/custom/permutations/11_image_relation/enum/0030_find_permutation_given_relation/permutation.param rename to tests/custom/permutations/11_transform_relation/enum/0030_find_permutation_given_relation/permutation.param diff --git a/tests/custom/permutations/11_image_relation/enum/0030_find_permutation_given_relation/run.sh b/tests/custom/permutations/11_transform_relation/enum/0030_find_permutation_given_relation/run.sh similarity index 100% rename from tests/custom/permutations/11_image_relation/enum/0030_find_permutation_given_relation/run.sh rename to tests/custom/permutations/11_transform_relation/enum/0030_find_permutation_given_relation/run.sh diff --git a/tests/custom/permutations/11_image_relation/enum/0030_find_permutation_given_relation/stdout.expected b/tests/custom/permutations/11_transform_relation/enum/0030_find_permutation_given_relation/stdout.expected similarity index 85% rename from tests/custom/permutations/11_image_relation/enum/0030_find_permutation_given_relation/stdout.expected rename to tests/custom/permutations/11_transform_relation/enum/0030_find_permutation_given_relation/stdout.expected index 6274febb02..fcf16cbaba 100644 --- a/tests/custom/permutations/11_image_relation/enum/0030_find_permutation_given_relation/stdout.expected +++ b/tests/custom/permutations/11_transform_relation/enum/0030_find_permutation_given_relation/stdout.expected @@ -2,6 +2,8 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output Savile Row: model000001.eprime permutation.param +Running minion for domain filtering. +Running solver: minion Copying solution to: permutation-permutation.solution language Essence 1.3 diff --git a/tests/custom/permutations/11_image_relation/enum/0040_find_permutation_find_relation/permutation.essence b/tests/custom/permutations/11_transform_relation/enum/0040_find_permutation_find_relation/permutation.essence similarity index 61% rename from tests/custom/permutations/11_image_relation/enum/0040_find_permutation_find_relation/permutation.essence rename to tests/custom/permutations/11_transform_relation/enum/0040_find_permutation_find_relation/permutation.essence index 3c7b761179..be7a9f3968 100644 --- a/tests/custom/permutations/11_image_relation/enum/0040_find_permutation_find_relation/permutation.essence +++ b/tests/custom/permutations/11_transform_relation/enum/0040_find_permutation_find_relation/permutation.essence @@ -7,4 +7,4 @@ find sn : relation of (n * n) -such that sn = image(p,s) /\ (3 = sum([ toInt(l!=r) | (l,r) <- p]) /\ |s| = 4) +such that sn = transform(p,s) /\ (3 = sum([ toInt(l!=r) | (l,r) <- p]) /\ |s| = 4) diff --git a/tests/custom/permutations/11_image_relation/enum/0040_find_permutation_find_relation/run.sh b/tests/custom/permutations/11_transform_relation/enum/0040_find_permutation_find_relation/run.sh similarity index 100% rename from tests/custom/permutations/11_image_relation/enum/0040_find_permutation_find_relation/run.sh rename to tests/custom/permutations/11_transform_relation/enum/0040_find_permutation_find_relation/run.sh diff --git a/tests/custom/permutations/11_image_relation/enum/0040_find_permutation_find_relation/stdout.expected b/tests/custom/permutations/11_transform_relation/enum/0040_find_permutation_find_relation/stdout.expected similarity index 88% rename from tests/custom/permutations/11_image_relation/enum/0040_find_permutation_find_relation/stdout.expected rename to tests/custom/permutations/11_transform_relation/enum/0040_find_permutation_find_relation/stdout.expected index f7f0905d56..624839f190 100644 --- a/tests/custom/permutations/11_image_relation/enum/0040_find_permutation_find_relation/stdout.expected +++ b/tests/custom/permutations/11_transform_relation/enum/0040_find_permutation_find_relation/stdout.expected @@ -2,6 +2,8 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output Savile Row: model000001.eprime +Running minion for domain filtering. +Running solver: minion Copying solution to: permutation.solution language Essence 1.3 diff --git a/tests/custom/permutations/11_image_relation/int/0010_given_permutation_letting_relation/permutation.essence b/tests/custom/permutations/11_transform_relation/int/0010_given_permutation_letting_relation/permutation.essence similarity index 82% rename from tests/custom/permutations/11_image_relation/int/0010_given_permutation_letting_relation/permutation.essence rename to tests/custom/permutations/11_transform_relation/int/0010_given_permutation_letting_relation/permutation.essence index 8245be0083..c350aea3ea 100644 --- a/tests/custom/permutations/11_image_relation/int/0010_given_permutation_letting_relation/permutation.essence +++ b/tests/custom/permutations/11_transform_relation/int/0010_given_permutation_letting_relation/permutation.essence @@ -7,5 +7,5 @@ find sn : relation of (int(1..n) * int(1..n)) -such that sn = image(p,s) +such that sn = transform(p,s) diff --git a/tests/custom/permutations/11_image_relation/int/0010_given_permutation_letting_relation/permutation.param b/tests/custom/permutations/11_transform_relation/int/0010_given_permutation_letting_relation/permutation.param similarity index 100% rename from tests/custom/permutations/11_image_relation/int/0010_given_permutation_letting_relation/permutation.param rename to tests/custom/permutations/11_transform_relation/int/0010_given_permutation_letting_relation/permutation.param diff --git a/tests/custom/permutations/11_image_relation/int/0010_given_permutation_letting_relation/run.sh b/tests/custom/permutations/11_transform_relation/int/0010_given_permutation_letting_relation/run.sh similarity index 100% rename from tests/custom/permutations/11_image_relation/int/0010_given_permutation_letting_relation/run.sh rename to tests/custom/permutations/11_transform_relation/int/0010_given_permutation_letting_relation/run.sh diff --git a/tests/custom/permutations/11_image_relation/int/0010_given_permutation_letting_relation/stdout.expected b/tests/custom/permutations/11_transform_relation/int/0010_given_permutation_letting_relation/stdout.expected similarity index 83% rename from tests/custom/permutations/11_image_relation/int/0010_given_permutation_letting_relation/stdout.expected rename to tests/custom/permutations/11_transform_relation/int/0010_given_permutation_letting_relation/stdout.expected index 672239ad4e..7f5c20f6ae 100644 --- a/tests/custom/permutations/11_image_relation/int/0010_given_permutation_letting_relation/stdout.expected +++ b/tests/custom/permutations/11_transform_relation/int/0010_given_permutation_letting_relation/stdout.expected @@ -2,6 +2,8 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output Savile Row: model000001.eprime permutation.param +Running minion for domain filtering. +Running solver: minion Copying solution to: permutation-permutation.solution language Essence 1.3 diff --git a/tests/custom/permutations/11_image_relation/int/0020_letting_permutation_letting_relation/permutation.essence b/tests/custom/permutations/11_transform_relation/int/0020_letting_permutation_letting_relation/permutation.essence similarity index 82% rename from tests/custom/permutations/11_image_relation/int/0020_letting_permutation_letting_relation/permutation.essence rename to tests/custom/permutations/11_transform_relation/int/0020_letting_permutation_letting_relation/permutation.essence index b013d8138c..df44f769ee 100644 --- a/tests/custom/permutations/11_image_relation/int/0020_letting_permutation_letting_relation/permutation.essence +++ b/tests/custom/permutations/11_transform_relation/int/0020_letting_permutation_letting_relation/permutation.essence @@ -7,5 +7,5 @@ find sn : relation of (int(1..n) * int(1..n)) -such that sn = image(p,s) +such that sn = transform(p,s) diff --git a/tests/custom/permutations/11_image_relation/int/0020_letting_permutation_letting_relation/permutation.param b/tests/custom/permutations/11_transform_relation/int/0020_letting_permutation_letting_relation/permutation.param similarity index 100% rename from tests/custom/permutations/11_image_relation/int/0020_letting_permutation_letting_relation/permutation.param rename to tests/custom/permutations/11_transform_relation/int/0020_letting_permutation_letting_relation/permutation.param diff --git a/tests/custom/permutations/11_image_relation/int/0020_letting_permutation_letting_relation/run.sh b/tests/custom/permutations/11_transform_relation/int/0020_letting_permutation_letting_relation/run.sh similarity index 100% rename from tests/custom/permutations/11_image_relation/int/0020_letting_permutation_letting_relation/run.sh rename to tests/custom/permutations/11_transform_relation/int/0020_letting_permutation_letting_relation/run.sh diff --git a/tests/custom/permutations/11_image_relation/int/0020_letting_permutation_letting_relation/stdout.expected b/tests/custom/permutations/11_transform_relation/int/0020_letting_permutation_letting_relation/stdout.expected similarity index 83% rename from tests/custom/permutations/11_image_relation/int/0020_letting_permutation_letting_relation/stdout.expected rename to tests/custom/permutations/11_transform_relation/int/0020_letting_permutation_letting_relation/stdout.expected index 672239ad4e..7f5c20f6ae 100644 --- a/tests/custom/permutations/11_image_relation/int/0020_letting_permutation_letting_relation/stdout.expected +++ b/tests/custom/permutations/11_transform_relation/int/0020_letting_permutation_letting_relation/stdout.expected @@ -2,6 +2,8 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output Savile Row: model000001.eprime permutation.param +Running minion for domain filtering. +Running solver: minion Copying solution to: permutation-permutation.solution language Essence 1.3 diff --git a/tests/custom/permutations/11_image_relation/int/0030_find_permutation_given_relation/permutation.essence b/tests/custom/permutations/11_transform_relation/int/0030_find_permutation_given_relation/permutation.essence similarity index 67% rename from tests/custom/permutations/11_image_relation/int/0030_find_permutation_given_relation/permutation.essence rename to tests/custom/permutations/11_transform_relation/int/0030_find_permutation_given_relation/permutation.essence index 0e05c005db..1e99ec59d5 100644 --- a/tests/custom/permutations/11_image_relation/int/0030_find_permutation_given_relation/permutation.essence +++ b/tests/custom/permutations/11_transform_relation/int/0030_find_permutation_given_relation/permutation.essence @@ -7,4 +7,4 @@ find sn : relation of (int(1..n) * int(1..n)) -such that sn = image(p,s) /\ (3 = sum([ toInt(l!=r) | (l,r) <- p])) +such that sn = transform(p,s) /\ (3 = sum([ toInt(l!=r) | (l,r) <- p])) diff --git a/tests/custom/permutations/11_image_relation/int/0030_find_permutation_given_relation/permutation.param b/tests/custom/permutations/11_transform_relation/int/0030_find_permutation_given_relation/permutation.param similarity index 100% rename from tests/custom/permutations/11_image_relation/int/0030_find_permutation_given_relation/permutation.param rename to tests/custom/permutations/11_transform_relation/int/0030_find_permutation_given_relation/permutation.param diff --git a/tests/custom/permutations/11_image_relation/int/0030_find_permutation_given_relation/run.sh b/tests/custom/permutations/11_transform_relation/int/0030_find_permutation_given_relation/run.sh similarity index 100% rename from tests/custom/permutations/11_image_relation/int/0030_find_permutation_given_relation/run.sh rename to tests/custom/permutations/11_transform_relation/int/0030_find_permutation_given_relation/run.sh diff --git a/tests/custom/permutations/11_image_relation/int/0030_find_permutation_given_relation/stdout.expected b/tests/custom/permutations/11_transform_relation/int/0030_find_permutation_given_relation/stdout.expected similarity index 85% rename from tests/custom/permutations/11_image_relation/int/0030_find_permutation_given_relation/stdout.expected rename to tests/custom/permutations/11_transform_relation/int/0030_find_permutation_given_relation/stdout.expected index ba78bdf1b6..4c5045b4f4 100644 --- a/tests/custom/permutations/11_image_relation/int/0030_find_permutation_given_relation/stdout.expected +++ b/tests/custom/permutations/11_transform_relation/int/0030_find_permutation_given_relation/stdout.expected @@ -2,6 +2,8 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output Savile Row: model000001.eprime permutation.param +Running minion for domain filtering. +Running solver: minion Copying solution to: permutation-permutation.solution language Essence 1.3 diff --git a/tests/custom/permutations/11_image_relation/int/0040_find_permutation_find_relation/permutation.essence b/tests/custom/permutations/11_transform_relation/int/0040_find_permutation_find_relation/permutation.essence similarity index 63% rename from tests/custom/permutations/11_image_relation/int/0040_find_permutation_find_relation/permutation.essence rename to tests/custom/permutations/11_transform_relation/int/0040_find_permutation_find_relation/permutation.essence index ef68f9ff7a..abbf9c0ba4 100644 --- a/tests/custom/permutations/11_image_relation/int/0040_find_permutation_find_relation/permutation.essence +++ b/tests/custom/permutations/11_transform_relation/int/0040_find_permutation_find_relation/permutation.essence @@ -7,4 +7,4 @@ find sn : relation of (int(1..n) * int(1..n)) -such that sn = image(p,s) /\ (3 = sum([ toInt(l!=r) | (l,r) <- p]) /\ |s| = 4) +such that sn = transform(p,s) /\ (3 = sum([ toInt(l!=r) | (l,r) <- p]) /\ |s| = 4) diff --git a/tests/custom/permutations/11_image_relation/int/0040_find_permutation_find_relation/run.sh b/tests/custom/permutations/11_transform_relation/int/0040_find_permutation_find_relation/run.sh similarity index 100% rename from tests/custom/permutations/11_image_relation/int/0040_find_permutation_find_relation/run.sh rename to tests/custom/permutations/11_transform_relation/int/0040_find_permutation_find_relation/run.sh diff --git a/tests/custom/permutations/11_image_relation/int/0040_find_permutation_find_relation/stdout.expected b/tests/custom/permutations/11_transform_relation/int/0040_find_permutation_find_relation/stdout.expected similarity index 88% rename from tests/custom/permutations/11_image_relation/int/0040_find_permutation_find_relation/stdout.expected rename to tests/custom/permutations/11_transform_relation/int/0040_find_permutation_find_relation/stdout.expected index 4b7742790e..59214a4f3f 100644 --- a/tests/custom/permutations/11_image_relation/int/0040_find_permutation_find_relation/stdout.expected +++ b/tests/custom/permutations/11_transform_relation/int/0040_find_permutation_find_relation/stdout.expected @@ -2,6 +2,8 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output Savile Row: model000001.eprime +Running minion for domain filtering. +Running solver: minion Copying solution to: permutation.solution language Essence 1.3 diff --git a/tests/custom/permutations/14_image_sequence/runthese.sh b/tests/custom/permutations/11_transform_relation/runthese.sh similarity index 67% rename from tests/custom/permutations/14_image_sequence/runthese.sh rename to tests/custom/permutations/11_transform_relation/runthese.sh index f4ba4c79fb..f3c89d1cfc 100644 --- a/tests/custom/permutations/14_image_sequence/runthese.sh +++ b/tests/custom/permutations/11_transform_relation/runthese.sh @@ -1 +1 @@ -stack build --copy-bins --test --test-arguments "-p custom.permutations.14_image_sequence" +stack build --copy-bins --test --test-arguments "-p custom.permutations.11_transform_relation" diff --git a/tests/custom/permutations/11_image_relation/unnamed/0040_find_permutation_find_relation/permutation.essence b/tests/custom/permutations/11_transform_relation/unnamed/0040_find_permutation_find_relation/permutation.essence similarity index 59% rename from tests/custom/permutations/11_image_relation/unnamed/0040_find_permutation_find_relation/permutation.essence rename to tests/custom/permutations/11_transform_relation/unnamed/0040_find_permutation_find_relation/permutation.essence index f8cf709877..71c3e75925 100644 --- a/tests/custom/permutations/11_image_relation/unnamed/0040_find_permutation_find_relation/permutation.essence +++ b/tests/custom/permutations/11_transform_relation/unnamed/0040_find_permutation_find_relation/permutation.essence @@ -7,4 +7,4 @@ find sn : relation of (n * n) -such that sn = image(p,s) /\ (3 = sum([ toInt(l!=r) | (l,r) <- p]) /\ |s| = 4) +such that sn = transform(p,s) /\ (3 = sum([ toInt(l!=r) | (l,r) <- p]) /\ |s| = 4) diff --git a/tests/custom/permutations/11_image_relation/unnamed/0040_find_permutation_find_relation/run.sh b/tests/custom/permutations/11_transform_relation/unnamed/0040_find_permutation_find_relation/run.sh similarity index 100% rename from tests/custom/permutations/11_image_relation/unnamed/0040_find_permutation_find_relation/run.sh rename to tests/custom/permutations/11_transform_relation/unnamed/0040_find_permutation_find_relation/run.sh diff --git a/tests/custom/permutations/11_image_relation/unnamed/0040_find_permutation_find_relation/stdout.expected b/tests/custom/permutations/11_transform_relation/unnamed/0040_find_permutation_find_relation/stdout.expected similarity index 90% rename from tests/custom/permutations/11_image_relation/unnamed/0040_find_permutation_find_relation/stdout.expected rename to tests/custom/permutations/11_transform_relation/unnamed/0040_find_permutation_find_relation/stdout.expected index 8096cfe173..f306f9cfe8 100644 --- a/tests/custom/permutations/11_image_relation/unnamed/0040_find_permutation_find_relation/stdout.expected +++ b/tests/custom/permutations/11_transform_relation/unnamed/0040_find_permutation_find_relation/stdout.expected @@ -2,6 +2,8 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output Savile Row: model000001.eprime +Running minion for domain filtering. +Running solver: minion Copying solution to: permutation.solution language Essence 1.3 diff --git a/tests/custom/permutations/12_image_list/int/0030_find_permutation/permutation.essence b/tests/custom/permutations/12_image_list/int/0030_find_permutation/permutation.essence deleted file mode 100644 index 50bd7450a8..0000000000 --- a/tests/custom/permutations/12_image_list/int/0030_find_permutation/permutation.essence +++ /dev/null @@ -1,6 +0,0 @@ -letting n be 4 - -find p : permutation of int(1..4) - -such that 4 = sum([i | i <- image(p, [4,4,4,4])]) - diff --git a/tests/custom/permutations/12_transform_list/accept_these.sh b/tests/custom/permutations/12_transform_list/accept_these.sh new file mode 100644 index 0000000000..12b0d9c7bb --- /dev/null +++ b/tests/custom/permutations/12_transform_list/accept_these.sh @@ -0,0 +1,8 @@ +sh ../../acceptOutput.sh enum/0010_given_permutation +sh ../../acceptOutput.sh enum/0030_find_permutation +sh ../../acceptOutput.sh enum/0020_letting_permutation +sh ../../acceptOutput.sh int/0010_given_permutation +sh ../../acceptOutput.sh int/0030_find_permutation +sh ../../acceptOutput.sh int/0020_letting_permutation +sh ../../acceptOutput.sh unnamed/0030_find_permutation + diff --git a/tests/custom/permutations/12_image_list/enum/0010_given_permutation/permutation.essence b/tests/custom/permutations/12_transform_list/enum/0010_given_permutation/permutation.essence similarity index 59% rename from tests/custom/permutations/12_image_list/enum/0010_given_permutation/permutation.essence rename to tests/custom/permutations/12_transform_list/enum/0010_given_permutation/permutation.essence index 2fc7eb726b..a6bcc3b66c 100644 --- a/tests/custom/permutations/12_image_list/enum/0010_given_permutation/permutation.essence +++ b/tests/custom/permutations/12_transform_list/enum/0010_given_permutation/permutation.essence @@ -4,5 +4,5 @@ given p : permutation of n find b : n -such that and([ i = b | i <- image(p,[E4,E4,E4,E4])]) +such that and([ i = b | i <- transform(p,[E4,E4,E4,E4])]) diff --git a/tests/custom/permutations/12_image_list/enum/0010_given_permutation/permutation.param b/tests/custom/permutations/12_transform_list/enum/0010_given_permutation/permutation.param similarity index 100% rename from tests/custom/permutations/12_image_list/enum/0010_given_permutation/permutation.param rename to tests/custom/permutations/12_transform_list/enum/0010_given_permutation/permutation.param diff --git a/tests/custom/permutations/12_image_list/enum/0010_given_permutation/run.sh b/tests/custom/permutations/12_transform_list/enum/0010_given_permutation/run.sh similarity index 100% rename from tests/custom/permutations/12_image_list/enum/0010_given_permutation/run.sh rename to tests/custom/permutations/12_transform_list/enum/0010_given_permutation/run.sh diff --git a/tests/custom/permutations/12_image_list/enum/0010_given_permutation/stdout.expected b/tests/custom/permutations/12_transform_list/enum/0010_given_permutation/stdout.expected similarity index 80% rename from tests/custom/permutations/12_image_list/enum/0010_given_permutation/stdout.expected rename to tests/custom/permutations/12_transform_list/enum/0010_given_permutation/stdout.expected index 506b046403..71fe3e137a 100644 --- a/tests/custom/permutations/12_image_list/enum/0010_given_permutation/stdout.expected +++ b/tests/custom/permutations/12_transform_list/enum/0010_given_permutation/stdout.expected @@ -2,6 +2,8 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output Savile Row: model000001.eprime permutation.param +Running minion for domain filtering. +Running solver: minion Copying solution to: permutation-permutation.solution language Essence 1.3 diff --git a/tests/custom/permutations/12_image_list/enum/0020_letting_permutation/permutation.essence b/tests/custom/permutations/12_transform_list/enum/0020_letting_permutation/permutation.essence similarity index 61% rename from tests/custom/permutations/12_image_list/enum/0020_letting_permutation/permutation.essence rename to tests/custom/permutations/12_transform_list/enum/0020_letting_permutation/permutation.essence index ad1e442938..f71faf62a6 100644 --- a/tests/custom/permutations/12_image_list/enum/0020_letting_permutation/permutation.essence +++ b/tests/custom/permutations/12_transform_list/enum/0020_letting_permutation/permutation.essence @@ -3,5 +3,5 @@ letting n be new type enum {E1,E2,E3,E4} letting p be permutation((E1,E3,E4)) find b : n -such that and([i = b | i <- image(p, [E4,E4,E4,E4])]) +such that and([i = b | i <- transform(p, [E4,E4,E4,E4])]) diff --git a/tests/custom/permutations/12_image_list/enum/0020_letting_permutation/run.sh b/tests/custom/permutations/12_transform_list/enum/0020_letting_permutation/run.sh similarity index 100% rename from tests/custom/permutations/12_image_list/enum/0020_letting_permutation/run.sh rename to tests/custom/permutations/12_transform_list/enum/0020_letting_permutation/run.sh diff --git a/tests/custom/permutations/12_image_list/enum/0020_letting_permutation/stdout.expected b/tests/custom/permutations/12_transform_list/enum/0020_letting_permutation/stdout.expected similarity index 78% rename from tests/custom/permutations/12_image_list/enum/0020_letting_permutation/stdout.expected rename to tests/custom/permutations/12_transform_list/enum/0020_letting_permutation/stdout.expected index 7e742d02ef..53fe5f0484 100644 --- a/tests/custom/permutations/12_image_list/enum/0020_letting_permutation/stdout.expected +++ b/tests/custom/permutations/12_transform_list/enum/0020_letting_permutation/stdout.expected @@ -2,6 +2,8 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output Savile Row: model000001.eprime +Running minion for domain filtering. +Running solver: minion Copying solution to: permutation.solution language Essence 1.3 diff --git a/tests/custom/permutations/12_image_list/enum/0030_find_permutation/permutation.essence b/tests/custom/permutations/12_transform_list/enum/0030_find_permutation/permutation.essence similarity index 54% rename from tests/custom/permutations/12_image_list/enum/0030_find_permutation/permutation.essence rename to tests/custom/permutations/12_transform_list/enum/0030_find_permutation/permutation.essence index f2003d2684..a9099fa425 100644 --- a/tests/custom/permutations/12_image_list/enum/0030_find_permutation/permutation.essence +++ b/tests/custom/permutations/12_transform_list/enum/0030_find_permutation/permutation.essence @@ -3,5 +3,5 @@ letting n be new type enum {E1,E2,E3,E4} find p : permutation of n find b : n -such that and([i = b | i <- image(p, [E4,E4,E4,E4])]) /\ b != E4 +such that and([i = b | i <- transform(p, [E4,E4,E4,E4])]) /\ b != E4 diff --git a/tests/custom/permutations/12_image_list/enum/0030_find_permutation/run.sh b/tests/custom/permutations/12_transform_list/enum/0030_find_permutation/run.sh similarity index 100% rename from tests/custom/permutations/12_image_list/enum/0030_find_permutation/run.sh rename to tests/custom/permutations/12_transform_list/enum/0030_find_permutation/run.sh diff --git a/tests/custom/permutations/12_image_list/enum/0030_find_permutation/stdout.expected b/tests/custom/permutations/12_transform_list/enum/0030_find_permutation/stdout.expected similarity index 80% rename from tests/custom/permutations/12_image_list/enum/0030_find_permutation/stdout.expected rename to tests/custom/permutations/12_transform_list/enum/0030_find_permutation/stdout.expected index b8d3197660..78d5b42fe0 100644 --- a/tests/custom/permutations/12_image_list/enum/0030_find_permutation/stdout.expected +++ b/tests/custom/permutations/12_transform_list/enum/0030_find_permutation/stdout.expected @@ -2,6 +2,8 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output Savile Row: model000001.eprime +Running minion for domain filtering. +Running solver: minion Copying solution to: permutation.solution language Essence 1.3 diff --git a/tests/custom/permutations/12_image_list/int/0010_given_permutation/permutation.essence b/tests/custom/permutations/12_transform_list/int/0010_given_permutation/permutation.essence similarity index 58% rename from tests/custom/permutations/12_image_list/int/0010_given_permutation/permutation.essence rename to tests/custom/permutations/12_transform_list/int/0010_given_permutation/permutation.essence index 603a3a6d80..874f8ff957 100644 --- a/tests/custom/permutations/12_image_list/int/0010_given_permutation/permutation.essence +++ b/tests/custom/permutations/12_transform_list/int/0010_given_permutation/permutation.essence @@ -4,5 +4,5 @@ given p : permutation of int(1..n) find b : int(1..50) -such that b = sum([ i | i <- image(p,[4,4,4,4])]) +such that b = sum([ i | i <- transform(p,[4,4,4,4])]) diff --git a/tests/custom/permutations/12_image_list/int/0010_given_permutation/permutation.param b/tests/custom/permutations/12_transform_list/int/0010_given_permutation/permutation.param similarity index 100% rename from tests/custom/permutations/12_image_list/int/0010_given_permutation/permutation.param rename to tests/custom/permutations/12_transform_list/int/0010_given_permutation/permutation.param diff --git a/tests/custom/permutations/12_image_list/int/0010_given_permutation/run.sh b/tests/custom/permutations/12_transform_list/int/0010_given_permutation/run.sh similarity index 100% rename from tests/custom/permutations/12_image_list/int/0010_given_permutation/run.sh rename to tests/custom/permutations/12_transform_list/int/0010_given_permutation/run.sh diff --git a/tests/custom/permutations/12_image_list/int/0010_given_permutation/stdout.expected b/tests/custom/permutations/12_transform_list/int/0010_given_permutation/stdout.expected similarity index 80% rename from tests/custom/permutations/12_image_list/int/0010_given_permutation/stdout.expected rename to tests/custom/permutations/12_transform_list/int/0010_given_permutation/stdout.expected index b149f7b32e..307441720d 100644 --- a/tests/custom/permutations/12_image_list/int/0010_given_permutation/stdout.expected +++ b/tests/custom/permutations/12_transform_list/int/0010_given_permutation/stdout.expected @@ -2,6 +2,8 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output Savile Row: model000001.eprime permutation.param +Running minion for domain filtering. +Running solver: minion Copying solution to: permutation-permutation.solution language Essence 1.3 diff --git a/tests/custom/permutations/12_image_list/int/0020_letting_permutation/permutation.essence b/tests/custom/permutations/12_transform_list/int/0020_letting_permutation/permutation.essence similarity index 57% rename from tests/custom/permutations/12_image_list/int/0020_letting_permutation/permutation.essence rename to tests/custom/permutations/12_transform_list/int/0020_letting_permutation/permutation.essence index 7ccc16aff8..c0c056a3f1 100644 --- a/tests/custom/permutations/12_image_list/int/0020_letting_permutation/permutation.essence +++ b/tests/custom/permutations/12_transform_list/int/0020_letting_permutation/permutation.essence @@ -3,5 +3,5 @@ letting n be 4 letting p be permutation((1,3,4)) find b : int(1..50) -such that b = sum([i | i <- image(p, [4,4,4,4])]) +such that b = sum([i | i <- transform(p, [4,4,4,4])]) diff --git a/tests/custom/permutations/12_image_list/int/0020_letting_permutation/run.sh b/tests/custom/permutations/12_transform_list/int/0020_letting_permutation/run.sh similarity index 100% rename from tests/custom/permutations/12_image_list/int/0020_letting_permutation/run.sh rename to tests/custom/permutations/12_transform_list/int/0020_letting_permutation/run.sh diff --git a/tests/custom/permutations/12_image_list/int/0020_letting_permutation/stdout.expected b/tests/custom/permutations/12_transform_list/int/0020_letting_permutation/stdout.expected similarity index 78% rename from tests/custom/permutations/12_image_list/int/0020_letting_permutation/stdout.expected rename to tests/custom/permutations/12_transform_list/int/0020_letting_permutation/stdout.expected index 12a21c3a0e..b0ec1acad6 100644 --- a/tests/custom/permutations/12_image_list/int/0020_letting_permutation/stdout.expected +++ b/tests/custom/permutations/12_transform_list/int/0020_letting_permutation/stdout.expected @@ -2,6 +2,8 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output Savile Row: model000001.eprime +Running minion for domain filtering. +Running solver: minion Copying solution to: permutation.solution language Essence 1.3 diff --git a/tests/custom/permutations/12_transform_list/int/0030_find_permutation/permutation.essence b/tests/custom/permutations/12_transform_list/int/0030_find_permutation/permutation.essence new file mode 100644 index 0000000000..4a2844917b --- /dev/null +++ b/tests/custom/permutations/12_transform_list/int/0030_find_permutation/permutation.essence @@ -0,0 +1,6 @@ +letting n be 4 + +find p : permutation of int(1..4) + +such that 4 = sum([i | i <- transform(p, [4,4,4,4])]) + diff --git a/tests/custom/permutations/12_image_list/int/0030_find_permutation/run.sh b/tests/custom/permutations/12_transform_list/int/0030_find_permutation/run.sh similarity index 100% rename from tests/custom/permutations/12_image_list/int/0030_find_permutation/run.sh rename to tests/custom/permutations/12_transform_list/int/0030_find_permutation/run.sh diff --git a/tests/custom/permutations/12_image_list/int/0030_find_permutation/stdout.expected b/tests/custom/permutations/12_transform_list/int/0030_find_permutation/stdout.expected similarity index 80% rename from tests/custom/permutations/12_image_list/int/0030_find_permutation/stdout.expected rename to tests/custom/permutations/12_transform_list/int/0030_find_permutation/stdout.expected index 1fc3c0fa55..81d6c93cb0 100644 --- a/tests/custom/permutations/12_image_list/int/0030_find_permutation/stdout.expected +++ b/tests/custom/permutations/12_transform_list/int/0030_find_permutation/stdout.expected @@ -2,6 +2,8 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output Savile Row: model000001.eprime +Running minion for domain filtering. +Running solver: minion Copying solution to: permutation.solution language Essence 1.3 diff --git a/tests/custom/permutations/11_image_relation/runthese.sh b/tests/custom/permutations/12_transform_list/runthese.sh similarity index 70% rename from tests/custom/permutations/11_image_relation/runthese.sh rename to tests/custom/permutations/12_transform_list/runthese.sh index 26a4fa606f..307bef7089 100644 --- a/tests/custom/permutations/11_image_relation/runthese.sh +++ b/tests/custom/permutations/12_transform_list/runthese.sh @@ -1 +1 @@ -stack build --copy-bins --test --test-arguments "-p custom.permutations.11_image_relation" +stack build --copy-bins --test --test-arguments "-p custom.permutations.12_transform_list" diff --git a/tests/custom/permutations/12_image_list/unnamed/0030_find_permutation/permutation.essence b/tests/custom/permutations/12_transform_list/unnamed/0030_find_permutation/permutation.essence similarity index 56% rename from tests/custom/permutations/12_image_list/unnamed/0030_find_permutation/permutation.essence rename to tests/custom/permutations/12_transform_list/unnamed/0030_find_permutation/permutation.essence index b3570ccf42..4d303d007d 100644 --- a/tests/custom/permutations/12_image_list/unnamed/0030_find_permutation/permutation.essence +++ b/tests/custom/permutations/12_transform_list/unnamed/0030_find_permutation/permutation.essence @@ -4,5 +4,5 @@ find p : permutation of n find b : n find c : n -such that and([i = b | i <- image(p, [c,c,c,c])]) /\ b != c +such that and([i = b | i <- transform(p, [c,c,c,c])]) /\ b != c diff --git a/tests/custom/permutations/12_image_list/unnamed/0030_find_permutation/run.sh b/tests/custom/permutations/12_transform_list/unnamed/0030_find_permutation/run.sh similarity index 100% rename from tests/custom/permutations/12_image_list/unnamed/0030_find_permutation/run.sh rename to tests/custom/permutations/12_transform_list/unnamed/0030_find_permutation/run.sh diff --git a/tests/custom/permutations/12_image_list/unnamed/0030_find_permutation/stdout.expected b/tests/custom/permutations/12_transform_list/unnamed/0030_find_permutation/stdout.expected similarity index 84% rename from tests/custom/permutations/12_image_list/unnamed/0030_find_permutation/stdout.expected rename to tests/custom/permutations/12_transform_list/unnamed/0030_find_permutation/stdout.expected index dd091051e6..51e1357f41 100644 --- a/tests/custom/permutations/12_image_list/unnamed/0030_find_permutation/stdout.expected +++ b/tests/custom/permutations/12_transform_list/unnamed/0030_find_permutation/stdout.expected @@ -2,6 +2,8 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output Savile Row: model000001.eprime +Running minion for domain filtering. +Running solver: minion Copying solution to: permutation.solution language Essence 1.3 diff --git a/tests/custom/permutations/13_transform_function/accept_these.sh b/tests/custom/permutations/13_transform_function/accept_these.sh new file mode 100644 index 0000000000..c3e2a349fe --- /dev/null +++ b/tests/custom/permutations/13_transform_function/accept_these.sh @@ -0,0 +1,7 @@ +sh ../../acceptOutput.sh enum/0010_given_permutation +sh ../../acceptOutput.sh enum/0030_find_permutation +sh ../../acceptOutput.sh enum/0020_letting_permutation +sh ../../acceptOutput.sh int/0010_given_permutation +sh ../../acceptOutput.sh int/0030_find_permutation +sh ../../acceptOutput.sh int/0020_letting_permutation +sh ../../acceptOutput.sh unnamed/0030_find_permutation diff --git a/tests/custom/permutations/13_image_function/enum/0010_given_permutation/permutation.essence b/tests/custom/permutations/13_transform_function/enum/0010_given_permutation/permutation.essence similarity index 82% rename from tests/custom/permutations/13_image_function/enum/0010_given_permutation/permutation.essence rename to tests/custom/permutations/13_transform_function/enum/0010_given_permutation/permutation.essence index c0e5a90e9d..55f76ef90a 100644 --- a/tests/custom/permutations/13_image_function/enum/0010_given_permutation/permutation.essence +++ b/tests/custom/permutations/13_transform_function/enum/0010_given_permutation/permutation.essence @@ -4,5 +4,5 @@ given p : permutation of n letting f be function(E1-->E2, E2-->E3) find g : function n --> n -such that g = image(p,f) +such that g = transform(p,f) diff --git a/tests/custom/permutations/13_image_function/enum/0010_given_permutation/permutation.param b/tests/custom/permutations/13_transform_function/enum/0010_given_permutation/permutation.param similarity index 100% rename from tests/custom/permutations/13_image_function/enum/0010_given_permutation/permutation.param rename to tests/custom/permutations/13_transform_function/enum/0010_given_permutation/permutation.param diff --git a/tests/custom/permutations/13_image_function/enum/0010_given_permutation/run.sh b/tests/custom/permutations/13_transform_function/enum/0010_given_permutation/run.sh similarity index 100% rename from tests/custom/permutations/13_image_function/enum/0010_given_permutation/run.sh rename to tests/custom/permutations/13_transform_function/enum/0010_given_permutation/run.sh diff --git a/tests/custom/permutations/13_image_function/enum/0010_given_permutation/stdout.expected b/tests/custom/permutations/13_transform_function/enum/0010_given_permutation/stdout.expected similarity index 82% rename from tests/custom/permutations/13_image_function/enum/0010_given_permutation/stdout.expected rename to tests/custom/permutations/13_transform_function/enum/0010_given_permutation/stdout.expected index a37bad006e..0b3df54caf 100644 --- a/tests/custom/permutations/13_image_function/enum/0010_given_permutation/stdout.expected +++ b/tests/custom/permutations/13_transform_function/enum/0010_given_permutation/stdout.expected @@ -2,6 +2,8 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output Savile Row: model000001.eprime permutation.param +Running minion for domain filtering. +Running solver: minion Copying solution to: permutation-permutation.solution language Essence 1.3 diff --git a/tests/custom/permutations/13_image_function/enum/0020_letting_permutation/permutation.essence b/tests/custom/permutations/13_transform_function/enum/0020_letting_permutation/permutation.essence similarity index 82% rename from tests/custom/permutations/13_image_function/enum/0020_letting_permutation/permutation.essence rename to tests/custom/permutations/13_transform_function/enum/0020_letting_permutation/permutation.essence index f92e6054c6..014a56fd47 100644 --- a/tests/custom/permutations/13_image_function/enum/0020_letting_permutation/permutation.essence +++ b/tests/custom/permutations/13_transform_function/enum/0020_letting_permutation/permutation.essence @@ -4,5 +4,5 @@ letting p be permutation((E2,E3)) letting f be function(E1-->E2, E2-->E4) find g : function n --> n -such that g = image(p,f) +such that g = transform(p,f) diff --git a/tests/custom/permutations/13_image_function/enum/0020_letting_permutation/run.sh b/tests/custom/permutations/13_transform_function/enum/0020_letting_permutation/run.sh similarity index 100% rename from tests/custom/permutations/13_image_function/enum/0020_letting_permutation/run.sh rename to tests/custom/permutations/13_transform_function/enum/0020_letting_permutation/run.sh diff --git a/tests/custom/permutations/13_image_function/enum/0020_letting_permutation/stdout.expected b/tests/custom/permutations/13_transform_function/enum/0020_letting_permutation/stdout.expected similarity index 80% rename from tests/custom/permutations/13_image_function/enum/0020_letting_permutation/stdout.expected rename to tests/custom/permutations/13_transform_function/enum/0020_letting_permutation/stdout.expected index 9910fdd1d7..d107362fc0 100644 --- a/tests/custom/permutations/13_image_function/enum/0020_letting_permutation/stdout.expected +++ b/tests/custom/permutations/13_transform_function/enum/0020_letting_permutation/stdout.expected @@ -2,6 +2,8 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output Savile Row: model000001.eprime +Running minion for domain filtering. +Running solver: minion Copying solution to: permutation.solution language Essence 1.3 diff --git a/tests/custom/permutations/13_image_function/enum/0030_find_permutation/permutation.essence b/tests/custom/permutations/13_transform_function/enum/0030_find_permutation/permutation.essence similarity index 83% rename from tests/custom/permutations/13_image_function/enum/0030_find_permutation/permutation.essence rename to tests/custom/permutations/13_transform_function/enum/0030_find_permutation/permutation.essence index 7e7c9c3dc6..503b4b66d2 100644 --- a/tests/custom/permutations/13_image_function/enum/0030_find_permutation/permutation.essence +++ b/tests/custom/permutations/13_transform_function/enum/0030_find_permutation/permutation.essence @@ -4,5 +4,5 @@ find p : permutation of n letting f be function(E1-->E2,E2-->E4) letting g be function(E1-->E3,E3-->E4) -such that g = image(p,f) +such that g = transform(p,f) diff --git a/tests/custom/permutations/13_image_function/enum/0030_find_permutation/run.sh b/tests/custom/permutations/13_transform_function/enum/0030_find_permutation/run.sh similarity index 100% rename from tests/custom/permutations/13_image_function/enum/0030_find_permutation/run.sh rename to tests/custom/permutations/13_transform_function/enum/0030_find_permutation/run.sh diff --git a/tests/custom/permutations/13_image_function/enum/0030_find_permutation/stdout.expected b/tests/custom/permutations/13_transform_function/enum/0030_find_permutation/stdout.expected similarity index 79% rename from tests/custom/permutations/13_image_function/enum/0030_find_permutation/stdout.expected rename to tests/custom/permutations/13_transform_function/enum/0030_find_permutation/stdout.expected index 066eb575ff..b71343efb7 100644 --- a/tests/custom/permutations/13_image_function/enum/0030_find_permutation/stdout.expected +++ b/tests/custom/permutations/13_transform_function/enum/0030_find_permutation/stdout.expected @@ -2,6 +2,8 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output Savile Row: model000001.eprime +Running minion for domain filtering. +Running solver: minion Copying solution to: permutation.solution language Essence 1.3 diff --git a/tests/custom/permutations/13_image_function/int/0010_given_permutation/permutation.essence b/tests/custom/permutations/13_transform_function/int/0010_given_permutation/permutation.essence similarity index 81% rename from tests/custom/permutations/13_image_function/int/0010_given_permutation/permutation.essence rename to tests/custom/permutations/13_transform_function/int/0010_given_permutation/permutation.essence index a89c13ead8..4574cdf6b9 100644 --- a/tests/custom/permutations/13_image_function/int/0010_given_permutation/permutation.essence +++ b/tests/custom/permutations/13_transform_function/int/0010_given_permutation/permutation.essence @@ -4,5 +4,5 @@ given p : permutation of int(1..n) letting f be function(1-->2, 2-->3) find g : function int(1..4) --> int(1..4) -such that g = image(p,f) +such that g = transform(p,f) diff --git a/tests/custom/permutations/13_image_function/int/0010_given_permutation/permutation.param b/tests/custom/permutations/13_transform_function/int/0010_given_permutation/permutation.param similarity index 100% rename from tests/custom/permutations/13_image_function/int/0010_given_permutation/permutation.param rename to tests/custom/permutations/13_transform_function/int/0010_given_permutation/permutation.param diff --git a/tests/custom/permutations/13_image_function/int/0010_given_permutation/run.sh b/tests/custom/permutations/13_transform_function/int/0010_given_permutation/run.sh similarity index 100% rename from tests/custom/permutations/13_image_function/int/0010_given_permutation/run.sh rename to tests/custom/permutations/13_transform_function/int/0010_given_permutation/run.sh diff --git a/tests/custom/permutations/13_image_function/int/0010_given_permutation/stdout.expected b/tests/custom/permutations/13_transform_function/int/0010_given_permutation/stdout.expected similarity index 81% rename from tests/custom/permutations/13_image_function/int/0010_given_permutation/stdout.expected rename to tests/custom/permutations/13_transform_function/int/0010_given_permutation/stdout.expected index 07cf3d6c18..7f23926d57 100644 --- a/tests/custom/permutations/13_image_function/int/0010_given_permutation/stdout.expected +++ b/tests/custom/permutations/13_transform_function/int/0010_given_permutation/stdout.expected @@ -2,6 +2,8 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output Savile Row: model000001.eprime permutation.param +Running minion for domain filtering. +Running solver: minion Copying solution to: permutation-permutation.solution language Essence 1.3 diff --git a/tests/custom/permutations/13_image_function/int/0020_letting_permutation/permutation.essence b/tests/custom/permutations/13_transform_function/int/0020_letting_permutation/permutation.essence similarity index 81% rename from tests/custom/permutations/13_image_function/int/0020_letting_permutation/permutation.essence rename to tests/custom/permutations/13_transform_function/int/0020_letting_permutation/permutation.essence index 7c72c3dfa6..c67d3ada08 100644 --- a/tests/custom/permutations/13_image_function/int/0020_letting_permutation/permutation.essence +++ b/tests/custom/permutations/13_transform_function/int/0020_letting_permutation/permutation.essence @@ -4,5 +4,5 @@ letting p be permutation((2,3)) letting f be function(1-->2, 2-->4) find g : function int(1..4) --> int(1..4) -such that g = image(p,f) +such that g = transform(p,f) diff --git a/tests/custom/permutations/13_image_function/int/0020_letting_permutation/run.sh b/tests/custom/permutations/13_transform_function/int/0020_letting_permutation/run.sh similarity index 100% rename from tests/custom/permutations/13_image_function/int/0020_letting_permutation/run.sh rename to tests/custom/permutations/13_transform_function/int/0020_letting_permutation/run.sh diff --git a/tests/custom/permutations/13_image_function/int/0020_letting_permutation/stdout.expected b/tests/custom/permutations/13_transform_function/int/0020_letting_permutation/stdout.expected similarity index 80% rename from tests/custom/permutations/13_image_function/int/0020_letting_permutation/stdout.expected rename to tests/custom/permutations/13_transform_function/int/0020_letting_permutation/stdout.expected index 400f44ca55..a29a803f56 100644 --- a/tests/custom/permutations/13_image_function/int/0020_letting_permutation/stdout.expected +++ b/tests/custom/permutations/13_transform_function/int/0020_letting_permutation/stdout.expected @@ -2,6 +2,8 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output Savile Row: model000001.eprime +Running minion for domain filtering. +Running solver: minion Copying solution to: permutation.solution language Essence 1.3 diff --git a/tests/custom/permutations/13_image_function/int/0030_find_permutation/permutation.essence b/tests/custom/permutations/13_transform_function/int/0030_find_permutation/permutation.essence similarity index 80% rename from tests/custom/permutations/13_image_function/int/0030_find_permutation/permutation.essence rename to tests/custom/permutations/13_transform_function/int/0030_find_permutation/permutation.essence index 67e8890930..6508464448 100644 --- a/tests/custom/permutations/13_image_function/int/0030_find_permutation/permutation.essence +++ b/tests/custom/permutations/13_transform_function/int/0030_find_permutation/permutation.essence @@ -4,5 +4,5 @@ find p : permutation of int(1..4) letting f be function(1-->2,2-->4) letting g be function(1-->3,3-->4) -such that g = image(p,f) +such that g = transform(p,f) diff --git a/tests/custom/permutations/13_image_function/int/0030_find_permutation/run.sh b/tests/custom/permutations/13_transform_function/int/0030_find_permutation/run.sh similarity index 100% rename from tests/custom/permutations/13_image_function/int/0030_find_permutation/run.sh rename to tests/custom/permutations/13_transform_function/int/0030_find_permutation/run.sh diff --git a/tests/custom/permutations/13_image_function/int/0030_find_permutation/stdout.expected b/tests/custom/permutations/13_transform_function/int/0030_find_permutation/stdout.expected similarity index 79% rename from tests/custom/permutations/13_image_function/int/0030_find_permutation/stdout.expected rename to tests/custom/permutations/13_transform_function/int/0030_find_permutation/stdout.expected index 4e07c3be70..187ae23c55 100644 --- a/tests/custom/permutations/13_image_function/int/0030_find_permutation/stdout.expected +++ b/tests/custom/permutations/13_transform_function/int/0030_find_permutation/stdout.expected @@ -2,6 +2,8 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output Savile Row: model000001.eprime +Running minion for domain filtering. +Running solver: minion Copying solution to: permutation.solution language Essence 1.3 diff --git a/tests/custom/permutations/13_transform_function/runthese.sh b/tests/custom/permutations/13_transform_function/runthese.sh new file mode 100644 index 0000000000..5b2f8993b8 --- /dev/null +++ b/tests/custom/permutations/13_transform_function/runthese.sh @@ -0,0 +1 @@ +stack build --copy-bins --test --test-arguments "-p custom.permutations.13_transform_function" diff --git a/tests/custom/permutations/13_image_function/unnamed/0030_find_permutation/permutation.essence b/tests/custom/permutations/13_transform_function/unnamed/0030_find_permutation/permutation.essence similarity index 69% rename from tests/custom/permutations/13_image_function/unnamed/0030_find_permutation/permutation.essence rename to tests/custom/permutations/13_transform_function/unnamed/0030_find_permutation/permutation.essence index adf1db82c6..a0c212ecdf 100644 --- a/tests/custom/permutations/13_image_function/unnamed/0030_find_permutation/permutation.essence +++ b/tests/custom/permutations/13_transform_function/unnamed/0030_find_permutation/permutation.essence @@ -5,5 +5,5 @@ find f : function n --> n find g : function n --> n -such that g = image(p,f) /\ |p| > 0 /\ |f| > 0 +such that g = transform(p,f) /\ |p| > 0 /\ |f| > 0 diff --git a/tests/custom/permutations/13_image_function/unnamed/0030_find_permutation/run.sh b/tests/custom/permutations/13_transform_function/unnamed/0030_find_permutation/run.sh similarity index 100% rename from tests/custom/permutations/13_image_function/unnamed/0030_find_permutation/run.sh rename to tests/custom/permutations/13_transform_function/unnamed/0030_find_permutation/run.sh diff --git a/tests/custom/permutations/13_image_function/unnamed/0030_find_permutation/stdout.expected b/tests/custom/permutations/13_transform_function/unnamed/0030_find_permutation/stdout.expected similarity index 85% rename from tests/custom/permutations/13_image_function/unnamed/0030_find_permutation/stdout.expected rename to tests/custom/permutations/13_transform_function/unnamed/0030_find_permutation/stdout.expected index 8631753f0f..75a8251b11 100644 --- a/tests/custom/permutations/13_image_function/unnamed/0030_find_permutation/stdout.expected +++ b/tests/custom/permutations/13_transform_function/unnamed/0030_find_permutation/stdout.expected @@ -2,6 +2,8 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output Savile Row: model000001.eprime +Running minion for domain filtering. +Running solver: minion Copying solution to: permutation.solution language Essence 1.3 diff --git a/tests/custom/permutations/14_transform_sequence/accept_these.sh b/tests/custom/permutations/14_transform_sequence/accept_these.sh new file mode 100644 index 0000000000..c3e2a349fe --- /dev/null +++ b/tests/custom/permutations/14_transform_sequence/accept_these.sh @@ -0,0 +1,7 @@ +sh ../../acceptOutput.sh enum/0010_given_permutation +sh ../../acceptOutput.sh enum/0030_find_permutation +sh ../../acceptOutput.sh enum/0020_letting_permutation +sh ../../acceptOutput.sh int/0010_given_permutation +sh ../../acceptOutput.sh int/0030_find_permutation +sh ../../acceptOutput.sh int/0020_letting_permutation +sh ../../acceptOutput.sh unnamed/0030_find_permutation diff --git a/tests/custom/permutations/14_image_sequence/enum/0010_given_permutation/permutation.essence b/tests/custom/permutations/14_transform_sequence/enum/0010_given_permutation/permutation.essence similarity index 82% rename from tests/custom/permutations/14_image_sequence/enum/0010_given_permutation/permutation.essence rename to tests/custom/permutations/14_transform_sequence/enum/0010_given_permutation/permutation.essence index a48b6809f9..5d7dd79626 100644 --- a/tests/custom/permutations/14_image_sequence/enum/0010_given_permutation/permutation.essence +++ b/tests/custom/permutations/14_transform_sequence/enum/0010_given_permutation/permutation.essence @@ -4,5 +4,5 @@ given p : permutation of n letting f be sequence(E1,E2,E3,E4) find g : sequence (size 4) of n -such that g = image(p,f) +such that g = transform(p,f) diff --git a/tests/custom/permutations/14_image_sequence/enum/0010_given_permutation/permutation.param b/tests/custom/permutations/14_transform_sequence/enum/0010_given_permutation/permutation.param similarity index 100% rename from tests/custom/permutations/14_image_sequence/enum/0010_given_permutation/permutation.param rename to tests/custom/permutations/14_transform_sequence/enum/0010_given_permutation/permutation.param diff --git a/tests/custom/permutations/14_image_sequence/enum/0010_given_permutation/run.sh b/tests/custom/permutations/14_transform_sequence/enum/0010_given_permutation/run.sh similarity index 100% rename from tests/custom/permutations/14_image_sequence/enum/0010_given_permutation/run.sh rename to tests/custom/permutations/14_transform_sequence/enum/0010_given_permutation/run.sh diff --git a/tests/custom/permutations/14_image_sequence/enum/0010_given_permutation/stdout.expected b/tests/custom/permutations/14_transform_sequence/enum/0010_given_permutation/stdout.expected similarity index 81% rename from tests/custom/permutations/14_image_sequence/enum/0010_given_permutation/stdout.expected rename to tests/custom/permutations/14_transform_sequence/enum/0010_given_permutation/stdout.expected index 5793310569..89938f5e8d 100644 --- a/tests/custom/permutations/14_image_sequence/enum/0010_given_permutation/stdout.expected +++ b/tests/custom/permutations/14_transform_sequence/enum/0010_given_permutation/stdout.expected @@ -2,6 +2,8 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output Savile Row: model000001.eprime permutation.param +Running minion for domain filtering. +Running solver: minion Copying solution to: permutation-permutation.solution language Essence 1.3 diff --git a/tests/custom/permutations/14_image_sequence/enum/0020_letting_permutation/permutation.essence b/tests/custom/permutations/14_transform_sequence/enum/0020_letting_permutation/permutation.essence similarity index 83% rename from tests/custom/permutations/14_image_sequence/enum/0020_letting_permutation/permutation.essence rename to tests/custom/permutations/14_transform_sequence/enum/0020_letting_permutation/permutation.essence index 446537c410..46eaa3aa2b 100644 --- a/tests/custom/permutations/14_image_sequence/enum/0020_letting_permutation/permutation.essence +++ b/tests/custom/permutations/14_transform_sequence/enum/0020_letting_permutation/permutation.essence @@ -4,5 +4,5 @@ letting p be permutation((E2,E3)) letting f be sequence(E1,E2,E3,E4) find g : sequence (size 4) of n -such that g = image(p,f) +such that g = transform(p,f) diff --git a/tests/custom/permutations/14_image_sequence/enum/0020_letting_permutation/run.sh b/tests/custom/permutations/14_transform_sequence/enum/0020_letting_permutation/run.sh similarity index 100% rename from tests/custom/permutations/14_image_sequence/enum/0020_letting_permutation/run.sh rename to tests/custom/permutations/14_transform_sequence/enum/0020_letting_permutation/run.sh diff --git a/tests/custom/permutations/14_image_sequence/enum/0020_letting_permutation/stdout.expected b/tests/custom/permutations/14_transform_sequence/enum/0020_letting_permutation/stdout.expected similarity index 80% rename from tests/custom/permutations/14_image_sequence/enum/0020_letting_permutation/stdout.expected rename to tests/custom/permutations/14_transform_sequence/enum/0020_letting_permutation/stdout.expected index e4b9bb364e..d9d8d82c01 100644 --- a/tests/custom/permutations/14_image_sequence/enum/0020_letting_permutation/stdout.expected +++ b/tests/custom/permutations/14_transform_sequence/enum/0020_letting_permutation/stdout.expected @@ -2,6 +2,8 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output Savile Row: model000001.eprime +Running minion for domain filtering. +Running solver: minion Copying solution to: permutation.solution language Essence 1.3 diff --git a/tests/custom/permutations/14_image_sequence/enum/0030_find_permutation/permutation.essence b/tests/custom/permutations/14_transform_sequence/enum/0030_find_permutation/permutation.essence similarity index 82% rename from tests/custom/permutations/14_image_sequence/enum/0030_find_permutation/permutation.essence rename to tests/custom/permutations/14_transform_sequence/enum/0030_find_permutation/permutation.essence index 2861b8d4a5..5fb8a185b4 100644 --- a/tests/custom/permutations/14_image_sequence/enum/0030_find_permutation/permutation.essence +++ b/tests/custom/permutations/14_transform_sequence/enum/0030_find_permutation/permutation.essence @@ -4,5 +4,5 @@ find p : permutation of n letting f be sequence(E1,E2,E3,E4) letting g be sequence (E4,E3,E2,E1) -such that g = image(p,f) +such that g = transform(p,f) diff --git a/tests/custom/permutations/14_image_sequence/enum/0030_find_permutation/run.sh b/tests/custom/permutations/14_transform_sequence/enum/0030_find_permutation/run.sh similarity index 100% rename from tests/custom/permutations/14_image_sequence/enum/0030_find_permutation/run.sh rename to tests/custom/permutations/14_transform_sequence/enum/0030_find_permutation/run.sh diff --git a/tests/custom/permutations/14_image_sequence/enum/0030_find_permutation/stdout.expected b/tests/custom/permutations/14_transform_sequence/enum/0030_find_permutation/stdout.expected similarity index 80% rename from tests/custom/permutations/14_image_sequence/enum/0030_find_permutation/stdout.expected rename to tests/custom/permutations/14_transform_sequence/enum/0030_find_permutation/stdout.expected index 75c9c50761..2ab14eb1b5 100644 --- a/tests/custom/permutations/14_image_sequence/enum/0030_find_permutation/stdout.expected +++ b/tests/custom/permutations/14_transform_sequence/enum/0030_find_permutation/stdout.expected @@ -2,6 +2,8 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output Savile Row: model000001.eprime +Running minion for domain filtering. +Running solver: minion Copying solution to: permutation.solution language Essence 1.3 diff --git a/tests/custom/permutations/14_image_sequence/int/0010_given_permutation/permutation.essence b/tests/custom/permutations/14_transform_sequence/int/0010_given_permutation/permutation.essence similarity index 80% rename from tests/custom/permutations/14_image_sequence/int/0010_given_permutation/permutation.essence rename to tests/custom/permutations/14_transform_sequence/int/0010_given_permutation/permutation.essence index d313a62827..77bdd73ab4 100644 --- a/tests/custom/permutations/14_image_sequence/int/0010_given_permutation/permutation.essence +++ b/tests/custom/permutations/14_transform_sequence/int/0010_given_permutation/permutation.essence @@ -4,5 +4,5 @@ given p : permutation of int(1..n) letting f be sequence(1,2,3,4) find g : sequence (size 4) of int(1..4) -such that g = image(p,f) +such that g = transform(p,f) diff --git a/tests/custom/permutations/14_image_sequence/int/0010_given_permutation/permutation.param b/tests/custom/permutations/14_transform_sequence/int/0010_given_permutation/permutation.param similarity index 100% rename from tests/custom/permutations/14_image_sequence/int/0010_given_permutation/permutation.param rename to tests/custom/permutations/14_transform_sequence/int/0010_given_permutation/permutation.param diff --git a/tests/custom/permutations/14_image_sequence/int/0010_given_permutation/run.sh b/tests/custom/permutations/14_transform_sequence/int/0010_given_permutation/run.sh similarity index 100% rename from tests/custom/permutations/14_image_sequence/int/0010_given_permutation/run.sh rename to tests/custom/permutations/14_transform_sequence/int/0010_given_permutation/run.sh diff --git a/tests/custom/permutations/14_image_sequence/int/0010_given_permutation/stdout.expected b/tests/custom/permutations/14_transform_sequence/int/0010_given_permutation/stdout.expected similarity index 81% rename from tests/custom/permutations/14_image_sequence/int/0010_given_permutation/stdout.expected rename to tests/custom/permutations/14_transform_sequence/int/0010_given_permutation/stdout.expected index 57d6d03ae4..15e22b1224 100644 --- a/tests/custom/permutations/14_image_sequence/int/0010_given_permutation/stdout.expected +++ b/tests/custom/permutations/14_transform_sequence/int/0010_given_permutation/stdout.expected @@ -2,6 +2,8 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output Savile Row: model000001.eprime permutation.param +Running minion for domain filtering. +Running solver: minion Copying solution to: permutation-permutation.solution language Essence 1.3 diff --git a/tests/custom/permutations/14_image_sequence/int/0020_letting_permutation/permutation.essence b/tests/custom/permutations/14_transform_sequence/int/0020_letting_permutation/permutation.essence similarity index 80% rename from tests/custom/permutations/14_image_sequence/int/0020_letting_permutation/permutation.essence rename to tests/custom/permutations/14_transform_sequence/int/0020_letting_permutation/permutation.essence index 1dce97d86d..7d607fad85 100644 --- a/tests/custom/permutations/14_image_sequence/int/0020_letting_permutation/permutation.essence +++ b/tests/custom/permutations/14_transform_sequence/int/0020_letting_permutation/permutation.essence @@ -4,5 +4,5 @@ letting p be permutation((2,3)) letting f be sequence(1,2,3,4) find g : sequence (size 4) of int(1..4) -such that g = image(p,f) +such that g = transform(p,f) diff --git a/tests/custom/permutations/14_image_sequence/int/0020_letting_permutation/run.sh b/tests/custom/permutations/14_transform_sequence/int/0020_letting_permutation/run.sh similarity index 100% rename from tests/custom/permutations/14_image_sequence/int/0020_letting_permutation/run.sh rename to tests/custom/permutations/14_transform_sequence/int/0020_letting_permutation/run.sh diff --git a/tests/custom/permutations/14_image_sequence/int/0020_letting_permutation/stdout.expected b/tests/custom/permutations/14_transform_sequence/int/0020_letting_permutation/stdout.expected similarity index 79% rename from tests/custom/permutations/14_image_sequence/int/0020_letting_permutation/stdout.expected rename to tests/custom/permutations/14_transform_sequence/int/0020_letting_permutation/stdout.expected index d93cbb4075..27f4dd5561 100644 --- a/tests/custom/permutations/14_image_sequence/int/0020_letting_permutation/stdout.expected +++ b/tests/custom/permutations/14_transform_sequence/int/0020_letting_permutation/stdout.expected @@ -2,6 +2,8 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output Savile Row: model000001.eprime +Running minion for domain filtering. +Running solver: minion Copying solution to: permutation.solution language Essence 1.3 diff --git a/tests/custom/permutations/14_image_sequence/int/0030_find_permutation/permutation.essence b/tests/custom/permutations/14_transform_sequence/int/0030_find_permutation/permutation.essence similarity index 79% rename from tests/custom/permutations/14_image_sequence/int/0030_find_permutation/permutation.essence rename to tests/custom/permutations/14_transform_sequence/int/0030_find_permutation/permutation.essence index 419cd05ff9..150ba14c00 100644 --- a/tests/custom/permutations/14_image_sequence/int/0030_find_permutation/permutation.essence +++ b/tests/custom/permutations/14_transform_sequence/int/0030_find_permutation/permutation.essence @@ -4,5 +4,5 @@ find p : permutation of int(1..4) letting f be sequence(1,2,3,4) letting g be sequence (4,3,2,1) -such that g = image(p,f) +such that g = transform(p,f) diff --git a/tests/custom/permutations/14_image_sequence/int/0030_find_permutation/run.sh b/tests/custom/permutations/14_transform_sequence/int/0030_find_permutation/run.sh similarity index 100% rename from tests/custom/permutations/14_image_sequence/int/0030_find_permutation/run.sh rename to tests/custom/permutations/14_transform_sequence/int/0030_find_permutation/run.sh diff --git a/tests/custom/permutations/14_image_sequence/int/0030_find_permutation/stdout.expected b/tests/custom/permutations/14_transform_sequence/int/0030_find_permutation/stdout.expected similarity index 80% rename from tests/custom/permutations/14_image_sequence/int/0030_find_permutation/stdout.expected rename to tests/custom/permutations/14_transform_sequence/int/0030_find_permutation/stdout.expected index df2d4d38af..f18eb4d299 100644 --- a/tests/custom/permutations/14_image_sequence/int/0030_find_permutation/stdout.expected +++ b/tests/custom/permutations/14_transform_sequence/int/0030_find_permutation/stdout.expected @@ -2,6 +2,8 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output Savile Row: model000001.eprime +Running minion for domain filtering. +Running solver: minion Copying solution to: permutation.solution language Essence 1.3 diff --git a/tests/custom/permutations/14_transform_sequence/runthese.sh b/tests/custom/permutations/14_transform_sequence/runthese.sh new file mode 100644 index 0000000000..ae75fa1461 --- /dev/null +++ b/tests/custom/permutations/14_transform_sequence/runthese.sh @@ -0,0 +1 @@ +stack build --copy-bins --test --test-arguments "-p custom.permutations.14_transform_sequence" diff --git a/tests/custom/permutations/14_image_sequence/unnamed/0030_find_permutation/permutation.essence b/tests/custom/permutations/14_transform_sequence/unnamed/0030_find_permutation/permutation.essence similarity index 76% rename from tests/custom/permutations/14_image_sequence/unnamed/0030_find_permutation/permutation.essence rename to tests/custom/permutations/14_transform_sequence/unnamed/0030_find_permutation/permutation.essence index a6e601898b..b2a953d10b 100644 --- a/tests/custom/permutations/14_image_sequence/unnamed/0030_find_permutation/permutation.essence +++ b/tests/custom/permutations/14_transform_sequence/unnamed/0030_find_permutation/permutation.essence @@ -4,5 +4,5 @@ find p : permutation of n find f : sequence (size 4) of n find g : sequence (size 4) of n -such that g = image(p,f) /\ f != g +such that g = transform(p,f) /\ f != g diff --git a/tests/custom/permutations/14_image_sequence/unnamed/0030_find_permutation/run.sh b/tests/custom/permutations/14_transform_sequence/unnamed/0030_find_permutation/run.sh similarity index 100% rename from tests/custom/permutations/14_image_sequence/unnamed/0030_find_permutation/run.sh rename to tests/custom/permutations/14_transform_sequence/unnamed/0030_find_permutation/run.sh diff --git a/tests/custom/permutations/14_image_sequence/unnamed/0030_find_permutation/stdout.expected b/tests/custom/permutations/14_transform_sequence/unnamed/0030_find_permutation/stdout.expected similarity index 86% rename from tests/custom/permutations/14_image_sequence/unnamed/0030_find_permutation/stdout.expected rename to tests/custom/permutations/14_transform_sequence/unnamed/0030_find_permutation/stdout.expected index 87cc818944..fc6c276596 100644 --- a/tests/custom/permutations/14_image_sequence/unnamed/0030_find_permutation/stdout.expected +++ b/tests/custom/permutations/14_transform_sequence/unnamed/0030_find_permutation/stdout.expected @@ -2,6 +2,8 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output Savile Row: model000001.eprime +Running minion for domain filtering. +Running solver: minion Copying solution to: permutation.solution language Essence 1.3 diff --git a/tests/custom/permutations/15_image_mset/runthese.sh b/tests/custom/permutations/15_image_mset/runthese.sh deleted file mode 100644 index a816234e2e..0000000000 --- a/tests/custom/permutations/15_image_mset/runthese.sh +++ /dev/null @@ -1 +0,0 @@ -stack build --copy-bins --test --test-arguments "-p custom.permutations.15_image_mset" diff --git a/tests/custom/permutations/15_transform_mset/accept_these.sh b/tests/custom/permutations/15_transform_mset/accept_these.sh new file mode 100644 index 0000000000..417ffb1e43 --- /dev/null +++ b/tests/custom/permutations/15_transform_mset/accept_these.sh @@ -0,0 +1,11 @@ +sh ../../acceptOutput.sh enum/0050_find_permutation_given_mset_find_mset +sh ../../acceptOutput.sh enum/0030_letting_permutation_find_msets +sh ../../acceptOutput.sh enum/0040_find_permutation_find_msets +sh ../../acceptOutput.sh enum/0020_given_permutation_find_msets +sh ../../acceptOutput.sh enum/0010_given_permutation_letting_mset +sh ../../acceptOutput.sh int/0050_find_permutation_given_mset_find_mset +sh ../../acceptOutput.sh int/0030_letting_permutation_find_msets +sh ../../acceptOutput.sh int/0040_find_permutation_find_msets +sh ../../acceptOutput.sh int/0020_given_permutation_find_msets +sh ../../acceptOutput.sh int/0010_given_permutation_letting_mset +sh ../../acceptOutput.sh unnamed/0004_find_permutation_find_msets diff --git a/tests/custom/permutations/15_image_mset/enum/0010_given_permutation_letting_mset/permutation.essence b/tests/custom/permutations/15_transform_mset/enum/0010_given_permutation_letting_mset/permutation.essence similarity index 81% rename from tests/custom/permutations/15_image_mset/enum/0010_given_permutation_letting_mset/permutation.essence rename to tests/custom/permutations/15_transform_mset/enum/0010_given_permutation_letting_mset/permutation.essence index 4ed5ea678e..101f26d76e 100644 --- a/tests/custom/permutations/15_image_mset/enum/0010_given_permutation_letting_mset/permutation.essence +++ b/tests/custom/permutations/15_transform_mset/enum/0010_given_permutation_letting_mset/permutation.essence @@ -6,5 +6,5 @@ given s : mset (size 3) of n find sn : mset (size 3) of n -such that sn = image(p,s) +such that sn = transform(p,s) diff --git a/tests/custom/permutations/15_image_mset/enum/0010_given_permutation_letting_mset/permutation.param b/tests/custom/permutations/15_transform_mset/enum/0010_given_permutation_letting_mset/permutation.param similarity index 100% rename from tests/custom/permutations/15_image_mset/enum/0010_given_permutation_letting_mset/permutation.param rename to tests/custom/permutations/15_transform_mset/enum/0010_given_permutation_letting_mset/permutation.param diff --git a/tests/custom/permutations/15_image_mset/enum/0010_given_permutation_letting_mset/run.sh b/tests/custom/permutations/15_transform_mset/enum/0010_given_permutation_letting_mset/run.sh similarity index 100% rename from tests/custom/permutations/15_image_mset/enum/0010_given_permutation_letting_mset/run.sh rename to tests/custom/permutations/15_transform_mset/enum/0010_given_permutation_letting_mset/run.sh diff --git a/tests/custom/permutations/15_image_mset/enum/0010_given_permutation_letting_mset/stdout.expected b/tests/custom/permutations/15_transform_mset/enum/0010_given_permutation_letting_mset/stdout.expected similarity index 81% rename from tests/custom/permutations/15_image_mset/enum/0010_given_permutation_letting_mset/stdout.expected rename to tests/custom/permutations/15_transform_mset/enum/0010_given_permutation_letting_mset/stdout.expected index 7d29cdcc0b..c9028d85e7 100644 --- a/tests/custom/permutations/15_image_mset/enum/0010_given_permutation_letting_mset/stdout.expected +++ b/tests/custom/permutations/15_transform_mset/enum/0010_given_permutation_letting_mset/stdout.expected @@ -2,6 +2,8 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output Savile Row: model000001.eprime permutation.param +Running minion for domain filtering. +Running solver: minion Copying solution to: permutation-permutation.solution language Essence 1.3 diff --git a/tests/custom/permutations/15_image_mset/enum/0020_given_permutation_find_msets/permutation.essence b/tests/custom/permutations/15_transform_mset/enum/0020_given_permutation_find_msets/permutation.essence similarity index 81% rename from tests/custom/permutations/15_image_mset/enum/0020_given_permutation_find_msets/permutation.essence rename to tests/custom/permutations/15_transform_mset/enum/0020_given_permutation_find_msets/permutation.essence index a3dedca402..84d66091b6 100644 --- a/tests/custom/permutations/15_image_mset/enum/0020_given_permutation_find_msets/permutation.essence +++ b/tests/custom/permutations/15_transform_mset/enum/0020_given_permutation_find_msets/permutation.essence @@ -7,5 +7,5 @@ find s : mset (maxSize 3) of n find sn : mset (maxSize 3) of n -such that sn = image(p,s) +such that sn = transform(p,s) diff --git a/tests/custom/permutations/15_image_mset/enum/0020_given_permutation_find_msets/permutation.param b/tests/custom/permutations/15_transform_mset/enum/0020_given_permutation_find_msets/permutation.param similarity index 100% rename from tests/custom/permutations/15_image_mset/enum/0020_given_permutation_find_msets/permutation.param rename to tests/custom/permutations/15_transform_mset/enum/0020_given_permutation_find_msets/permutation.param diff --git a/tests/custom/permutations/15_image_mset/enum/0020_given_permutation_find_msets/run.sh b/tests/custom/permutations/15_transform_mset/enum/0020_given_permutation_find_msets/run.sh similarity index 100% rename from tests/custom/permutations/15_image_mset/enum/0020_given_permutation_find_msets/run.sh rename to tests/custom/permutations/15_transform_mset/enum/0020_given_permutation_find_msets/run.sh diff --git a/tests/custom/permutations/15_image_mset/enum/0020_given_permutation_find_msets/stdout.expected b/tests/custom/permutations/15_transform_mset/enum/0020_given_permutation_find_msets/stdout.expected similarity index 96% rename from tests/custom/permutations/15_image_mset/enum/0020_given_permutation_find_msets/stdout.expected rename to tests/custom/permutations/15_transform_mset/enum/0020_given_permutation_find_msets/stdout.expected index 94ae70cf3d..969181b0df 100644 --- a/tests/custom/permutations/15_image_mset/enum/0020_given_permutation_find_msets/stdout.expected +++ b/tests/custom/permutations/15_transform_mset/enum/0020_given_permutation_find_msets/stdout.expected @@ -2,6 +2,8 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output Savile Row: model000001.eprime permutation.param +Running minion for domain filtering. +Running solver: minion Copying solution to: permutation-permutation-000001.solution Copying solution to: permutation-permutation-000002.solution Copying solution to: permutation-permutation-000003.solution diff --git a/tests/custom/permutations/15_image_mset/enum/0030_letting_permutation_find_msets/permutation.essence b/tests/custom/permutations/15_transform_mset/enum/0030_letting_permutation_find_msets/permutation.essence similarity index 82% rename from tests/custom/permutations/15_image_mset/enum/0030_letting_permutation_find_msets/permutation.essence rename to tests/custom/permutations/15_transform_mset/enum/0030_letting_permutation_find_msets/permutation.essence index c9f6d9f4d4..74d18edb30 100644 --- a/tests/custom/permutations/15_image_mset/enum/0030_letting_permutation_find_msets/permutation.essence +++ b/tests/custom/permutations/15_transform_mset/enum/0030_letting_permutation_find_msets/permutation.essence @@ -7,5 +7,5 @@ find s : mset (maxSize 3) of n find sn : mset (maxSize 3) of n -such that sn = image(p,s) +such that sn = transform(p,s) diff --git a/tests/custom/permutations/15_image_mset/enum/0030_letting_permutation_find_msets/run.sh b/tests/custom/permutations/15_transform_mset/enum/0030_letting_permutation_find_msets/run.sh similarity index 100% rename from tests/custom/permutations/15_image_mset/enum/0030_letting_permutation_find_msets/run.sh rename to tests/custom/permutations/15_transform_mset/enum/0030_letting_permutation_find_msets/run.sh diff --git a/tests/custom/permutations/15_image_mset/enum/0030_letting_permutation_find_msets/stdout.expected b/tests/custom/permutations/15_transform_mset/enum/0030_letting_permutation_find_msets/stdout.expected similarity index 95% rename from tests/custom/permutations/15_image_mset/enum/0030_letting_permutation_find_msets/stdout.expected rename to tests/custom/permutations/15_transform_mset/enum/0030_letting_permutation_find_msets/stdout.expected index 269d8404f3..172f9e30e9 100644 --- a/tests/custom/permutations/15_image_mset/enum/0030_letting_permutation_find_msets/stdout.expected +++ b/tests/custom/permutations/15_transform_mset/enum/0030_letting_permutation_find_msets/stdout.expected @@ -2,6 +2,8 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output Savile Row: model000001.eprime +Running minion for domain filtering. +Running solver: minion Copying solution to: permutation-000001.solution Copying solution to: permutation-000002.solution Copying solution to: permutation-000003.solution diff --git a/tests/custom/permutations/15_image_mset/enum/0040_find_permutation_find_msets/permutation.essence b/tests/custom/permutations/15_transform_mset/enum/0040_find_permutation_find_msets/permutation.essence similarity index 63% rename from tests/custom/permutations/15_image_mset/enum/0040_find_permutation_find_msets/permutation.essence rename to tests/custom/permutations/15_transform_mset/enum/0040_find_permutation_find_msets/permutation.essence index 7b9ce98cbf..1007c7c4c6 100644 --- a/tests/custom/permutations/15_image_mset/enum/0040_find_permutation_find_msets/permutation.essence +++ b/tests/custom/permutations/15_transform_mset/enum/0040_find_permutation_find_msets/permutation.essence @@ -7,5 +7,5 @@ find s : mset (size 6) of n find sn : mset (size 6) of n -such that sn = image(p,s) /\ (3 = sum([ toInt(l != r) | (l, r) <- p])) +such that sn = transform(p,s) /\ (3 = sum([ toInt(l != r) | (l, r) <- p])) diff --git a/tests/custom/permutations/15_image_mset/enum/0040_find_permutation_find_msets/run.sh b/tests/custom/permutations/15_transform_mset/enum/0040_find_permutation_find_msets/run.sh similarity index 100% rename from tests/custom/permutations/15_image_mset/enum/0040_find_permutation_find_msets/run.sh rename to tests/custom/permutations/15_transform_mset/enum/0040_find_permutation_find_msets/run.sh diff --git a/tests/custom/permutations/15_image_mset/enum/0040_find_permutation_find_msets/stdout.expected b/tests/custom/permutations/15_transform_mset/enum/0040_find_permutation_find_msets/stdout.expected similarity index 97% rename from tests/custom/permutations/15_image_mset/enum/0040_find_permutation_find_msets/stdout.expected rename to tests/custom/permutations/15_transform_mset/enum/0040_find_permutation_find_msets/stdout.expected index 5c6f660314..888f7406b2 100644 --- a/tests/custom/permutations/15_image_mset/enum/0040_find_permutation_find_msets/stdout.expected +++ b/tests/custom/permutations/15_transform_mset/enum/0040_find_permutation_find_msets/stdout.expected @@ -2,6 +2,8 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output Savile Row: model000001.eprime +Running minion for domain filtering. +Running solver: minion Copying solution to: permutation-000001.solution Copying solution to: permutation-000002.solution Copying solution to: permutation-000003.solution diff --git a/tests/custom/permutations/15_image_mset/enum/0050_find_permutation_given_mset_find_mset/permutation.essence b/tests/custom/permutations/15_transform_mset/enum/0050_find_permutation_given_mset_find_mset/permutation.essence similarity index 62% rename from tests/custom/permutations/15_image_mset/enum/0050_find_permutation_given_mset_find_mset/permutation.essence rename to tests/custom/permutations/15_transform_mset/enum/0050_find_permutation_given_mset_find_mset/permutation.essence index 682a284254..9c72ef2e9e 100644 --- a/tests/custom/permutations/15_image_mset/enum/0050_find_permutation_given_mset_find_mset/permutation.essence +++ b/tests/custom/permutations/15_transform_mset/enum/0050_find_permutation_given_mset_find_mset/permutation.essence @@ -7,5 +7,5 @@ given s : mset of n find sn : mset (maxSize 5) of n -such that sn = image(p,s) /\ (3 = sum([ toInt(l != r) | (l, r) <- p])) +such that sn = transform(p,s) /\ (3 = sum([ toInt(l != r) | (l, r) <- p])) diff --git a/tests/custom/permutations/15_image_mset/enum/0050_find_permutation_given_mset_find_mset/permutation.param b/tests/custom/permutations/15_transform_mset/enum/0050_find_permutation_given_mset_find_mset/permutation.param similarity index 100% rename from tests/custom/permutations/15_image_mset/enum/0050_find_permutation_given_mset_find_mset/permutation.param rename to tests/custom/permutations/15_transform_mset/enum/0050_find_permutation_given_mset_find_mset/permutation.param diff --git a/tests/custom/permutations/15_image_mset/enum/0050_find_permutation_given_mset_find_mset/run.sh b/tests/custom/permutations/15_transform_mset/enum/0050_find_permutation_given_mset_find_mset/run.sh similarity index 100% rename from tests/custom/permutations/15_image_mset/enum/0050_find_permutation_given_mset_find_mset/run.sh rename to tests/custom/permutations/15_transform_mset/enum/0050_find_permutation_given_mset_find_mset/run.sh diff --git a/tests/custom/permutations/15_image_mset/enum/0050_find_permutation_given_mset_find_mset/stdout.expected b/tests/custom/permutations/15_transform_mset/enum/0050_find_permutation_given_mset_find_mset/stdout.expected similarity index 95% rename from tests/custom/permutations/15_image_mset/enum/0050_find_permutation_given_mset_find_mset/stdout.expected rename to tests/custom/permutations/15_transform_mset/enum/0050_find_permutation_given_mset_find_mset/stdout.expected index 14465059ff..67d1d70414 100644 --- a/tests/custom/permutations/15_image_mset/enum/0050_find_permutation_given_mset_find_mset/stdout.expected +++ b/tests/custom/permutations/15_transform_mset/enum/0050_find_permutation_given_mset_find_mset/stdout.expected @@ -2,6 +2,8 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output Savile Row: model000001.eprime permutation.param +Running minion for domain filtering. +Running solver: minion Copying solution to: permutation-permutation-000001.solution Copying solution to: permutation-permutation-000002.solution Copying solution to: permutation-permutation-000003.solution diff --git a/tests/custom/permutations/15_image_mset/int/0010_given_permutation_letting_mset/permutation.essence b/tests/custom/permutations/15_transform_mset/int/0010_given_permutation_letting_mset/permutation.essence similarity index 80% rename from tests/custom/permutations/15_image_mset/int/0010_given_permutation_letting_mset/permutation.essence rename to tests/custom/permutations/15_transform_mset/int/0010_given_permutation_letting_mset/permutation.essence index f39709e521..436e7f366a 100644 --- a/tests/custom/permutations/15_image_mset/int/0010_given_permutation_letting_mset/permutation.essence +++ b/tests/custom/permutations/15_transform_mset/int/0010_given_permutation_letting_mset/permutation.essence @@ -6,5 +6,5 @@ given s : mset (size 4) of int(1..n) find sn : mset (size 4) of int(1..n) -such that sn = image(p,s) +such that sn = transform(p,s) diff --git a/tests/custom/permutations/15_image_mset/int/0010_given_permutation_letting_mset/permutation.param b/tests/custom/permutations/15_transform_mset/int/0010_given_permutation_letting_mset/permutation.param similarity index 100% rename from tests/custom/permutations/15_image_mset/int/0010_given_permutation_letting_mset/permutation.param rename to tests/custom/permutations/15_transform_mset/int/0010_given_permutation_letting_mset/permutation.param diff --git a/tests/custom/permutations/15_image_mset/int/0010_given_permutation_letting_mset/run.sh b/tests/custom/permutations/15_transform_mset/int/0010_given_permutation_letting_mset/run.sh similarity index 100% rename from tests/custom/permutations/15_image_mset/int/0010_given_permutation_letting_mset/run.sh rename to tests/custom/permutations/15_transform_mset/int/0010_given_permutation_letting_mset/run.sh diff --git a/tests/custom/permutations/15_image_mset/int/0010_given_permutation_letting_mset/stdout.expected b/tests/custom/permutations/15_transform_mset/int/0010_given_permutation_letting_mset/stdout.expected similarity index 81% rename from tests/custom/permutations/15_image_mset/int/0010_given_permutation_letting_mset/stdout.expected rename to tests/custom/permutations/15_transform_mset/int/0010_given_permutation_letting_mset/stdout.expected index 116746b7a3..c741d96b56 100644 --- a/tests/custom/permutations/15_image_mset/int/0010_given_permutation_letting_mset/stdout.expected +++ b/tests/custom/permutations/15_transform_mset/int/0010_given_permutation_letting_mset/stdout.expected @@ -2,6 +2,8 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output Savile Row: model000001.eprime permutation.param +Running minion for domain filtering. +Running solver: minion Copying solution to: permutation-permutation.solution language Essence 1.3 diff --git a/tests/custom/permutations/15_image_mset/int/0020_given_permutation_find_msets/permutation.essence b/tests/custom/permutations/15_transform_mset/int/0020_given_permutation_find_msets/permutation.essence similarity index 80% rename from tests/custom/permutations/15_image_mset/int/0020_given_permutation_find_msets/permutation.essence rename to tests/custom/permutations/15_transform_mset/int/0020_given_permutation_find_msets/permutation.essence index 512a928f0f..b397857ddb 100644 --- a/tests/custom/permutations/15_image_mset/int/0020_given_permutation_find_msets/permutation.essence +++ b/tests/custom/permutations/15_transform_mset/int/0020_given_permutation_find_msets/permutation.essence @@ -7,5 +7,5 @@ find s : mset (size 4) of int(1..n) find sn : mset (size 4) of int(1..n) -such that sn = image(p,s) +such that sn = transform(p,s) diff --git a/tests/custom/permutations/15_image_mset/int/0020_given_permutation_find_msets/permutation.param b/tests/custom/permutations/15_transform_mset/int/0020_given_permutation_find_msets/permutation.param similarity index 100% rename from tests/custom/permutations/15_image_mset/int/0020_given_permutation_find_msets/permutation.param rename to tests/custom/permutations/15_transform_mset/int/0020_given_permutation_find_msets/permutation.param diff --git a/tests/custom/permutations/15_image_mset/int/0020_given_permutation_find_msets/run.sh b/tests/custom/permutations/15_transform_mset/int/0020_given_permutation_find_msets/run.sh similarity index 100% rename from tests/custom/permutations/15_image_mset/int/0020_given_permutation_find_msets/run.sh rename to tests/custom/permutations/15_transform_mset/int/0020_given_permutation_find_msets/run.sh diff --git a/tests/custom/permutations/15_image_mset/int/0020_given_permutation_find_msets/stdout.expected b/tests/custom/permutations/15_transform_mset/int/0020_given_permutation_find_msets/stdout.expected similarity index 96% rename from tests/custom/permutations/15_image_mset/int/0020_given_permutation_find_msets/stdout.expected rename to tests/custom/permutations/15_transform_mset/int/0020_given_permutation_find_msets/stdout.expected index f6d27c0865..70f822e9cc 100644 --- a/tests/custom/permutations/15_image_mset/int/0020_given_permutation_find_msets/stdout.expected +++ b/tests/custom/permutations/15_transform_mset/int/0020_given_permutation_find_msets/stdout.expected @@ -2,6 +2,8 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output Savile Row: model000001.eprime permutation.param +Running minion for domain filtering. +Running solver: minion Copying solution to: permutation-permutation-000001.solution Copying solution to: permutation-permutation-000002.solution Copying solution to: permutation-permutation-000003.solution diff --git a/tests/custom/permutations/15_image_mset/int/0030_letting_permutation_find_msets/permutation.essence b/tests/custom/permutations/15_transform_mset/int/0030_letting_permutation_find_msets/permutation.essence similarity index 80% rename from tests/custom/permutations/15_image_mset/int/0030_letting_permutation_find_msets/permutation.essence rename to tests/custom/permutations/15_transform_mset/int/0030_letting_permutation_find_msets/permutation.essence index d69b86aa03..83b264ba00 100644 --- a/tests/custom/permutations/15_image_mset/int/0030_letting_permutation_find_msets/permutation.essence +++ b/tests/custom/permutations/15_transform_mset/int/0030_letting_permutation_find_msets/permutation.essence @@ -7,5 +7,5 @@ find s : mset (size 4) of int(1..n) find sn : mset (size 4) of int(1..n) -such that sn = image(p,s) +such that sn = transform(p,s) diff --git a/tests/custom/permutations/15_image_mset/int/0030_letting_permutation_find_msets/run.sh b/tests/custom/permutations/15_transform_mset/int/0030_letting_permutation_find_msets/run.sh similarity index 100% rename from tests/custom/permutations/15_image_mset/int/0030_letting_permutation_find_msets/run.sh rename to tests/custom/permutations/15_transform_mset/int/0030_letting_permutation_find_msets/run.sh diff --git a/tests/custom/permutations/15_image_mset/int/0030_letting_permutation_find_msets/stdout.expected b/tests/custom/permutations/15_transform_mset/int/0030_letting_permutation_find_msets/stdout.expected similarity index 96% rename from tests/custom/permutations/15_image_mset/int/0030_letting_permutation_find_msets/stdout.expected rename to tests/custom/permutations/15_transform_mset/int/0030_letting_permutation_find_msets/stdout.expected index 87171190e1..24a82edaf3 100644 --- a/tests/custom/permutations/15_image_mset/int/0030_letting_permutation_find_msets/stdout.expected +++ b/tests/custom/permutations/15_transform_mset/int/0030_letting_permutation_find_msets/stdout.expected @@ -2,6 +2,8 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output Savile Row: model000001.eprime +Running minion for domain filtering. +Running solver: minion Copying solution to: permutation-000001.solution Copying solution to: permutation-000002.solution Copying solution to: permutation-000003.solution diff --git a/tests/custom/permutations/15_image_mset/int/0040_find_permutation_find_msets/permutation.essence b/tests/custom/permutations/15_transform_mset/int/0040_find_permutation_find_msets/permutation.essence similarity index 75% rename from tests/custom/permutations/15_image_mset/int/0040_find_permutation_find_msets/permutation.essence rename to tests/custom/permutations/15_transform_mset/int/0040_find_permutation_find_msets/permutation.essence index 930c052961..65384aebb1 100644 --- a/tests/custom/permutations/15_image_mset/int/0040_find_permutation_find_msets/permutation.essence +++ b/tests/custom/permutations/15_transform_mset/int/0040_find_permutation_find_msets/permutation.essence @@ -7,5 +7,5 @@ find s : mset (size 4) of int(1..n) find sn : mset (size 4) of int(1..n) -such that sn = image(p,s) /\ 3 = |p| +such that sn = transform(p,s) /\ 3 = |p| diff --git a/tests/custom/permutations/15_image_mset/int/0040_find_permutation_find_msets/run.sh b/tests/custom/permutations/15_transform_mset/int/0040_find_permutation_find_msets/run.sh similarity index 100% rename from tests/custom/permutations/15_image_mset/int/0040_find_permutation_find_msets/run.sh rename to tests/custom/permutations/15_transform_mset/int/0040_find_permutation_find_msets/run.sh diff --git a/tests/custom/permutations/15_image_mset/int/0040_find_permutation_find_msets/stdout.expected b/tests/custom/permutations/15_transform_mset/int/0040_find_permutation_find_msets/stdout.expected similarity index 96% rename from tests/custom/permutations/15_image_mset/int/0040_find_permutation_find_msets/stdout.expected rename to tests/custom/permutations/15_transform_mset/int/0040_find_permutation_find_msets/stdout.expected index c68ae1dd2d..a00f1ae67d 100644 --- a/tests/custom/permutations/15_image_mset/int/0040_find_permutation_find_msets/stdout.expected +++ b/tests/custom/permutations/15_transform_mset/int/0040_find_permutation_find_msets/stdout.expected @@ -2,6 +2,8 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output Savile Row: model000001.eprime +Running minion for domain filtering. +Running solver: minion Copying solution to: permutation-000001.solution Copying solution to: permutation-000002.solution Copying solution to: permutation-000003.solution diff --git a/tests/custom/permutations/15_image_mset/int/0050_find_permutation_given_mset_find_mset/permutation.essence b/tests/custom/permutations/15_transform_mset/int/0050_find_permutation_given_mset_find_mset/permutation.essence similarity index 62% rename from tests/custom/permutations/15_image_mset/int/0050_find_permutation_given_mset_find_mset/permutation.essence rename to tests/custom/permutations/15_transform_mset/int/0050_find_permutation_given_mset_find_mset/permutation.essence index 58d3abf762..ce6faf384c 100644 --- a/tests/custom/permutations/15_image_mset/int/0050_find_permutation_given_mset_find_mset/permutation.essence +++ b/tests/custom/permutations/15_transform_mset/int/0050_find_permutation_given_mset_find_mset/permutation.essence @@ -7,5 +7,5 @@ given s : mset (size 3) of int(1..n) find sn : mset (size 3) of int(1..n) -such that sn = image(p,s) /\ (3 = sum([ toInt(l != r) | (l, r) <- p])) +such that sn = transform(p,s) /\ (3 = sum([ toInt(l != r) | (l, r) <- p])) diff --git a/tests/custom/permutations/15_image_mset/int/0050_find_permutation_given_mset_find_mset/permutation.param b/tests/custom/permutations/15_transform_mset/int/0050_find_permutation_given_mset_find_mset/permutation.param similarity index 100% rename from tests/custom/permutations/15_image_mset/int/0050_find_permutation_given_mset_find_mset/permutation.param rename to tests/custom/permutations/15_transform_mset/int/0050_find_permutation_given_mset_find_mset/permutation.param diff --git a/tests/custom/permutations/15_image_mset/int/0050_find_permutation_given_mset_find_mset/run.sh b/tests/custom/permutations/15_transform_mset/int/0050_find_permutation_given_mset_find_mset/run.sh similarity index 100% rename from tests/custom/permutations/15_image_mset/int/0050_find_permutation_given_mset_find_mset/run.sh rename to tests/custom/permutations/15_transform_mset/int/0050_find_permutation_given_mset_find_mset/run.sh diff --git a/tests/custom/permutations/15_image_mset/int/0050_find_permutation_given_mset_find_mset/stdout.expected b/tests/custom/permutations/15_transform_mset/int/0050_find_permutation_given_mset_find_mset/stdout.expected similarity index 95% rename from tests/custom/permutations/15_image_mset/int/0050_find_permutation_given_mset_find_mset/stdout.expected rename to tests/custom/permutations/15_transform_mset/int/0050_find_permutation_given_mset_find_mset/stdout.expected index 3419c537e4..24ef48b19d 100644 --- a/tests/custom/permutations/15_image_mset/int/0050_find_permutation_given_mset_find_mset/stdout.expected +++ b/tests/custom/permutations/15_transform_mset/int/0050_find_permutation_given_mset_find_mset/stdout.expected @@ -2,6 +2,8 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output Savile Row: model000001.eprime permutation.param +Running minion for domain filtering. +Running solver: minion Copying solution to: permutation-permutation-000001.solution Copying solution to: permutation-permutation-000002.solution Copying solution to: permutation-permutation-000003.solution diff --git a/tests/custom/permutations/12_image_list/runthese.sh b/tests/custom/permutations/15_transform_mset/runthese.sh similarity index 70% rename from tests/custom/permutations/12_image_list/runthese.sh rename to tests/custom/permutations/15_transform_mset/runthese.sh index 3a0e2a9392..2448831e35 100644 --- a/tests/custom/permutations/12_image_list/runthese.sh +++ b/tests/custom/permutations/15_transform_mset/runthese.sh @@ -1 +1 @@ -stack build --copy-bins --test --test-arguments "-p custom.permutations.12_image_list" +stack build --copy-bins --test --test-arguments "-p custom.permutations.15_transform_mset" diff --git a/tests/custom/permutations/15_image_mset/unnamed/0004_find_permutation_find_msets/permutation.essence b/tests/custom/permutations/15_transform_mset/unnamed/0004_find_permutation_find_msets/permutation.essence similarity index 62% rename from tests/custom/permutations/15_image_mset/unnamed/0004_find_permutation_find_msets/permutation.essence rename to tests/custom/permutations/15_transform_mset/unnamed/0004_find_permutation_find_msets/permutation.essence index afba9a0bae..2a9902ecaa 100644 --- a/tests/custom/permutations/15_image_mset/unnamed/0004_find_permutation_find_msets/permutation.essence +++ b/tests/custom/permutations/15_transform_mset/unnamed/0004_find_permutation_find_msets/permutation.essence @@ -7,5 +7,5 @@ find s : mset (size 4) of n find sn : mset (size 4) of n -such that sn = image(p,s) /\ (3 = sum([ toInt(l != r) | (l, r) <- p])) +such that sn = transform(p,s) /\ (3 = sum([ toInt(l != r) | (l, r) <- p])) diff --git a/tests/custom/permutations/15_image_mset/unnamed/0004_find_permutation_find_msets/run.sh b/tests/custom/permutations/15_transform_mset/unnamed/0004_find_permutation_find_msets/run.sh similarity index 100% rename from tests/custom/permutations/15_image_mset/unnamed/0004_find_permutation_find_msets/run.sh rename to tests/custom/permutations/15_transform_mset/unnamed/0004_find_permutation_find_msets/run.sh diff --git a/tests/custom/permutations/15_image_mset/unnamed/0004_find_permutation_find_msets/stdout.expected b/tests/custom/permutations/15_transform_mset/unnamed/0004_find_permutation_find_msets/stdout.expected similarity index 97% rename from tests/custom/permutations/15_image_mset/unnamed/0004_find_permutation_find_msets/stdout.expected rename to tests/custom/permutations/15_transform_mset/unnamed/0004_find_permutation_find_msets/stdout.expected index 1309113e68..f68af1bc0a 100644 --- a/tests/custom/permutations/15_image_mset/unnamed/0004_find_permutation_find_msets/stdout.expected +++ b/tests/custom/permutations/15_transform_mset/unnamed/0004_find_permutation_find_msets/stdout.expected @@ -2,6 +2,8 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output Savile Row: model000001.eprime +Running minion for domain filtering. +Running solver: minion Copying solution to: permutation-000001.solution Copying solution to: permutation-000002.solution Copying solution to: permutation-000003.solution diff --git a/tests/custom/permutations/16_image_permutation/runthese.sh b/tests/custom/permutations/16_image_permutation/runthese.sh deleted file mode 100644 index 2c9f64b312..0000000000 --- a/tests/custom/permutations/16_image_permutation/runthese.sh +++ /dev/null @@ -1 +0,0 @@ -stack build --copy-bins --test --test-arguments "-p custom.permutations.16_image_permutation" diff --git a/tests/custom/permutations/16_transform_permutation/accept_these.sh b/tests/custom/permutations/16_transform_permutation/accept_these.sh new file mode 100644 index 0000000000..94e622f20b --- /dev/null +++ b/tests/custom/permutations/16_transform_permutation/accept_these.sh @@ -0,0 +1,11 @@ +sh ../../acceptOutput.sh enum/0040_find_permutation_find_permutations +sh ../../acceptOutput.sh enum/0050_find_permutation_given_permutation_find_permutation +sh ../../acceptOutput.sh enum/0010_given_permutation_letting_permutation +sh ../../acceptOutput.sh enum/0020_given_permutation_find_permutations +sh ../../acceptOutput.sh enum/0030_letting_permutation_find_permutations +sh ../../acceptOutput.sh int/0040_find_permutation_find_permutations +sh ../../acceptOutput.sh int/0050_find_permutation_given_permutation_find_permutation +sh ../../acceptOutput.sh int/0010_given_permutation_letting_permutation +sh ../../acceptOutput.sh int/0020_given_permutation_find_permutations +sh ../../acceptOutput.sh int/0030_letting_permutation_find_permutations +sh ../../acceptOutput.sh unnamed/0004_find_permutation_find_permutations diff --git a/tests/custom/permutations/16_image_permutation/enum/0010_given_permutation_letting_permutation/permutation.essence b/tests/custom/permutations/16_transform_permutation/enum/0010_given_permutation_letting_permutation/permutation.essence similarity index 80% rename from tests/custom/permutations/16_image_permutation/enum/0010_given_permutation_letting_permutation/permutation.essence rename to tests/custom/permutations/16_transform_permutation/enum/0010_given_permutation_letting_permutation/permutation.essence index a3081ab099..093189b861 100644 --- a/tests/custom/permutations/16_image_permutation/enum/0010_given_permutation_letting_permutation/permutation.essence +++ b/tests/custom/permutations/16_transform_permutation/enum/0010_given_permutation_letting_permutation/permutation.essence @@ -5,5 +5,5 @@ given s : permutation of n find sn : permutation of n -such that sn = image(p,s) +such that sn = transform(p,s) diff --git a/tests/custom/permutations/16_image_permutation/enum/0010_given_permutation_letting_permutation/permutation.param b/tests/custom/permutations/16_transform_permutation/enum/0010_given_permutation_letting_permutation/permutation.param similarity index 100% rename from tests/custom/permutations/16_image_permutation/enum/0010_given_permutation_letting_permutation/permutation.param rename to tests/custom/permutations/16_transform_permutation/enum/0010_given_permutation_letting_permutation/permutation.param diff --git a/tests/custom/permutations/16_image_permutation/enum/0010_given_permutation_letting_permutation/run.sh b/tests/custom/permutations/16_transform_permutation/enum/0010_given_permutation_letting_permutation/run.sh similarity index 100% rename from tests/custom/permutations/16_image_permutation/enum/0010_given_permutation_letting_permutation/run.sh rename to tests/custom/permutations/16_transform_permutation/enum/0010_given_permutation_letting_permutation/run.sh diff --git a/tests/custom/permutations/16_image_permutation/enum/0010_given_permutation_letting_permutation/stdout.expected b/tests/custom/permutations/16_transform_permutation/enum/0010_given_permutation_letting_permutation/stdout.expected similarity index 82% rename from tests/custom/permutations/16_image_permutation/enum/0010_given_permutation_letting_permutation/stdout.expected rename to tests/custom/permutations/16_transform_permutation/enum/0010_given_permutation_letting_permutation/stdout.expected index 1ae9c33dae..f177ed54f9 100644 --- a/tests/custom/permutations/16_image_permutation/enum/0010_given_permutation_letting_permutation/stdout.expected +++ b/tests/custom/permutations/16_transform_permutation/enum/0010_given_permutation_letting_permutation/stdout.expected @@ -2,6 +2,8 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output Savile Row: model000001.eprime permutation.param +Running minion for domain filtering. +Running solver: minion Copying solution to: permutation-permutation.solution language Essence 1.3 diff --git a/tests/custom/permutations/16_image_permutation/enum/0020_given_permutation_find_permutations/permutation.essence b/tests/custom/permutations/16_transform_permutation/enum/0020_given_permutation_find_permutations/permutation.essence similarity index 71% rename from tests/custom/permutations/16_image_permutation/enum/0020_given_permutation_find_permutations/permutation.essence rename to tests/custom/permutations/16_transform_permutation/enum/0020_given_permutation_find_permutations/permutation.essence index 48bac35241..991443ec79 100644 --- a/tests/custom/permutations/16_image_permutation/enum/0020_given_permutation_find_permutations/permutation.essence +++ b/tests/custom/permutations/16_transform_permutation/enum/0020_given_permutation_find_permutations/permutation.essence @@ -7,5 +7,5 @@ find s : permutation of n find sn : permutation of n -such that sn = image(p,s) /\ sn != s /\ |s| > 0 +such that sn = transform(p,s) /\ sn != s /\ |s| > 0 diff --git a/tests/custom/permutations/16_image_permutation/enum/0020_given_permutation_find_permutations/permutation.param b/tests/custom/permutations/16_transform_permutation/enum/0020_given_permutation_find_permutations/permutation.param similarity index 100% rename from tests/custom/permutations/16_image_permutation/enum/0020_given_permutation_find_permutations/permutation.param rename to tests/custom/permutations/16_transform_permutation/enum/0020_given_permutation_find_permutations/permutation.param diff --git a/tests/custom/permutations/16_image_permutation/enum/0020_given_permutation_find_permutations/run.sh b/tests/custom/permutations/16_transform_permutation/enum/0020_given_permutation_find_permutations/run.sh similarity index 100% rename from tests/custom/permutations/16_image_permutation/enum/0020_given_permutation_find_permutations/run.sh rename to tests/custom/permutations/16_transform_permutation/enum/0020_given_permutation_find_permutations/run.sh diff --git a/tests/custom/permutations/16_image_permutation/enum/0020_given_permutation_find_permutations/stdout.expected b/tests/custom/permutations/16_transform_permutation/enum/0020_given_permutation_find_permutations/stdout.expected similarity index 96% rename from tests/custom/permutations/16_image_permutation/enum/0020_given_permutation_find_permutations/stdout.expected rename to tests/custom/permutations/16_transform_permutation/enum/0020_given_permutation_find_permutations/stdout.expected index bf0321c3a7..a659cab5c2 100644 --- a/tests/custom/permutations/16_image_permutation/enum/0020_given_permutation_find_permutations/stdout.expected +++ b/tests/custom/permutations/16_transform_permutation/enum/0020_given_permutation_find_permutations/stdout.expected @@ -2,6 +2,8 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output Savile Row: model000001.eprime permutation.param +Running minion for domain filtering. +Running solver: minion Copying solution to: permutation-permutation-000001.solution Copying solution to: permutation-permutation-000002.solution Copying solution to: permutation-permutation-000003.solution diff --git a/tests/custom/permutations/16_image_permutation/enum/0030_letting_permutation_find_permutations/permutation.essence b/tests/custom/permutations/16_transform_permutation/enum/0030_letting_permutation_find_permutations/permutation.essence similarity index 81% rename from tests/custom/permutations/16_image_permutation/enum/0030_letting_permutation_find_permutations/permutation.essence rename to tests/custom/permutations/16_transform_permutation/enum/0030_letting_permutation_find_permutations/permutation.essence index f91391eafd..72451e09ed 100644 --- a/tests/custom/permutations/16_image_permutation/enum/0030_letting_permutation_find_permutations/permutation.essence +++ b/tests/custom/permutations/16_transform_permutation/enum/0030_letting_permutation_find_permutations/permutation.essence @@ -7,5 +7,5 @@ find s : permutation of n find sn : permutation of n -such that sn = image(p,s) +such that sn = transform(p,s) diff --git a/tests/custom/permutations/16_image_permutation/enum/0030_letting_permutation_find_permutations/run.sh b/tests/custom/permutations/16_transform_permutation/enum/0030_letting_permutation_find_permutations/run.sh similarity index 100% rename from tests/custom/permutations/16_image_permutation/enum/0030_letting_permutation_find_permutations/run.sh rename to tests/custom/permutations/16_transform_permutation/enum/0030_letting_permutation_find_permutations/run.sh diff --git a/tests/custom/permutations/16_image_permutation/enum/0030_letting_permutation_find_permutations/stdout.expected b/tests/custom/permutations/16_transform_permutation/enum/0030_letting_permutation_find_permutations/stdout.expected similarity index 96% rename from tests/custom/permutations/16_image_permutation/enum/0030_letting_permutation_find_permutations/stdout.expected rename to tests/custom/permutations/16_transform_permutation/enum/0030_letting_permutation_find_permutations/stdout.expected index 2058ad9727..c6ebb65424 100644 --- a/tests/custom/permutations/16_image_permutation/enum/0030_letting_permutation_find_permutations/stdout.expected +++ b/tests/custom/permutations/16_transform_permutation/enum/0030_letting_permutation_find_permutations/stdout.expected @@ -2,6 +2,8 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output Savile Row: model000001.eprime +Running minion for domain filtering. +Running solver: minion Copying solution to: permutation-000001.solution Copying solution to: permutation-000002.solution Copying solution to: permutation-000003.solution diff --git a/tests/custom/permutations/16_image_permutation/enum/0040_find_permutation_find_permutations/permutation.essence b/tests/custom/permutations/16_transform_permutation/enum/0040_find_permutation_find_permutations/permutation.essence similarity index 75% rename from tests/custom/permutations/16_image_permutation/enum/0040_find_permutation_find_permutations/permutation.essence rename to tests/custom/permutations/16_transform_permutation/enum/0040_find_permutation_find_permutations/permutation.essence index 0541d6385b..731b5f81cb 100644 --- a/tests/custom/permutations/16_image_permutation/enum/0040_find_permutation_find_permutations/permutation.essence +++ b/tests/custom/permutations/16_transform_permutation/enum/0040_find_permutation_find_permutations/permutation.essence @@ -7,5 +7,5 @@ find s : permutation of n find sn : permutation of n -such that sn = image(p,s) /\ 3 = |p| +such that sn = transform(p,s) /\ 3 = |p| diff --git a/tests/custom/permutations/16_image_permutation/enum/0040_find_permutation_find_permutations/run.sh b/tests/custom/permutations/16_transform_permutation/enum/0040_find_permutation_find_permutations/run.sh similarity index 100% rename from tests/custom/permutations/16_image_permutation/enum/0040_find_permutation_find_permutations/run.sh rename to tests/custom/permutations/16_transform_permutation/enum/0040_find_permutation_find_permutations/run.sh diff --git a/tests/custom/permutations/16_image_permutation/enum/0040_find_permutation_find_permutations/stdout.expected b/tests/custom/permutations/16_transform_permutation/enum/0040_find_permutation_find_permutations/stdout.expected similarity index 97% rename from tests/custom/permutations/16_image_permutation/enum/0040_find_permutation_find_permutations/stdout.expected rename to tests/custom/permutations/16_transform_permutation/enum/0040_find_permutation_find_permutations/stdout.expected index b738675525..8d1e719bc3 100644 --- a/tests/custom/permutations/16_image_permutation/enum/0040_find_permutation_find_permutations/stdout.expected +++ b/tests/custom/permutations/16_transform_permutation/enum/0040_find_permutation_find_permutations/stdout.expected @@ -2,6 +2,8 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output Savile Row: model000001.eprime +Running minion for domain filtering. +Running solver: minion Copying solution to: permutation-000001.solution Copying solution to: permutation-000002.solution Copying solution to: permutation-000003.solution diff --git a/tests/custom/permutations/16_image_permutation/enum/0050_find_permutation_given_permutation_find_permutation/permutation.essence b/tests/custom/permutations/16_transform_permutation/enum/0050_find_permutation_given_permutation_find_permutation/permutation.essence similarity index 81% rename from tests/custom/permutations/16_image_permutation/enum/0050_find_permutation_given_permutation_find_permutation/permutation.essence rename to tests/custom/permutations/16_transform_permutation/enum/0050_find_permutation_given_permutation_find_permutation/permutation.essence index 29240f3a0c..c0161fd378 100644 --- a/tests/custom/permutations/16_image_permutation/enum/0050_find_permutation_given_permutation_find_permutation/permutation.essence +++ b/tests/custom/permutations/16_transform_permutation/enum/0050_find_permutation_given_permutation_find_permutation/permutation.essence @@ -7,5 +7,5 @@ given s : permutation of n find sn : permutation of n -such that sn = image(p,s) +such that sn = transform(p,s) diff --git a/tests/custom/permutations/16_image_permutation/enum/0050_find_permutation_given_permutation_find_permutation/permutation.param b/tests/custom/permutations/16_transform_permutation/enum/0050_find_permutation_given_permutation_find_permutation/permutation.param similarity index 100% rename from tests/custom/permutations/16_image_permutation/enum/0050_find_permutation_given_permutation_find_permutation/permutation.param rename to tests/custom/permutations/16_transform_permutation/enum/0050_find_permutation_given_permutation_find_permutation/permutation.param diff --git a/tests/custom/permutations/16_image_permutation/enum/0050_find_permutation_given_permutation_find_permutation/run.sh b/tests/custom/permutations/16_transform_permutation/enum/0050_find_permutation_given_permutation_find_permutation/run.sh similarity index 100% rename from tests/custom/permutations/16_image_permutation/enum/0050_find_permutation_given_permutation_find_permutation/run.sh rename to tests/custom/permutations/16_transform_permutation/enum/0050_find_permutation_given_permutation_find_permutation/run.sh diff --git a/tests/custom/permutations/16_image_permutation/enum/0050_find_permutation_given_permutation_find_permutation/stdout.expected b/tests/custom/permutations/16_transform_permutation/enum/0050_find_permutation_given_permutation_find_permutation/stdout.expected similarity index 96% rename from tests/custom/permutations/16_image_permutation/enum/0050_find_permutation_given_permutation_find_permutation/stdout.expected rename to tests/custom/permutations/16_transform_permutation/enum/0050_find_permutation_given_permutation_find_permutation/stdout.expected index dfa9602299..bbd361990c 100644 --- a/tests/custom/permutations/16_image_permutation/enum/0050_find_permutation_given_permutation_find_permutation/stdout.expected +++ b/tests/custom/permutations/16_transform_permutation/enum/0050_find_permutation_given_permutation_find_permutation/stdout.expected @@ -2,6 +2,8 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output Savile Row: model000001.eprime permutation.param +Running minion for domain filtering. +Running solver: minion Copying solution to: permutation-permutation-000001.solution Copying solution to: permutation-permutation-000002.solution Copying solution to: permutation-permutation-000003.solution diff --git a/tests/custom/permutations/16_image_permutation/int/0010_given_permutation_letting_permutation/permutation.essence b/tests/custom/permutations/16_transform_permutation/int/0010_given_permutation_letting_permutation/permutation.essence similarity index 80% rename from tests/custom/permutations/16_image_permutation/int/0010_given_permutation_letting_permutation/permutation.essence rename to tests/custom/permutations/16_transform_permutation/int/0010_given_permutation_letting_permutation/permutation.essence index ebd5b402fc..ef8dc79096 100644 --- a/tests/custom/permutations/16_image_permutation/int/0010_given_permutation_letting_permutation/permutation.essence +++ b/tests/custom/permutations/16_transform_permutation/int/0010_given_permutation_letting_permutation/permutation.essence @@ -6,5 +6,5 @@ given s : permutation of int(1..n) find sn : permutation of int(1..n) -such that sn = image(p,s) +such that sn = transform(p,s) diff --git a/tests/custom/permutations/16_image_permutation/int/0010_given_permutation_letting_permutation/permutation.param b/tests/custom/permutations/16_transform_permutation/int/0010_given_permutation_letting_permutation/permutation.param similarity index 100% rename from tests/custom/permutations/16_image_permutation/int/0010_given_permutation_letting_permutation/permutation.param rename to tests/custom/permutations/16_transform_permutation/int/0010_given_permutation_letting_permutation/permutation.param diff --git a/tests/custom/permutations/16_image_permutation/int/0010_given_permutation_letting_permutation/run.sh b/tests/custom/permutations/16_transform_permutation/int/0010_given_permutation_letting_permutation/run.sh similarity index 100% rename from tests/custom/permutations/16_image_permutation/int/0010_given_permutation_letting_permutation/run.sh rename to tests/custom/permutations/16_transform_permutation/int/0010_given_permutation_letting_permutation/run.sh diff --git a/tests/custom/permutations/16_image_permutation/int/0010_given_permutation_letting_permutation/stdout.expected b/tests/custom/permutations/16_transform_permutation/int/0010_given_permutation_letting_permutation/stdout.expected similarity index 82% rename from tests/custom/permutations/16_image_permutation/int/0010_given_permutation_letting_permutation/stdout.expected rename to tests/custom/permutations/16_transform_permutation/int/0010_given_permutation_letting_permutation/stdout.expected index c56184dc94..f2041ec176 100644 --- a/tests/custom/permutations/16_image_permutation/int/0010_given_permutation_letting_permutation/stdout.expected +++ b/tests/custom/permutations/16_transform_permutation/int/0010_given_permutation_letting_permutation/stdout.expected @@ -2,6 +2,8 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output Savile Row: model000001.eprime permutation.param +Running minion for domain filtering. +Running solver: minion Copying solution to: permutation-permutation.solution language Essence 1.3 diff --git a/tests/custom/permutations/16_image_permutation/int/0020_given_permutation_find_permutations/permutation.essence b/tests/custom/permutations/16_transform_permutation/int/0020_given_permutation_find_permutations/permutation.essence similarity index 70% rename from tests/custom/permutations/16_image_permutation/int/0020_given_permutation_find_permutations/permutation.essence rename to tests/custom/permutations/16_transform_permutation/int/0020_given_permutation_find_permutations/permutation.essence index c29d51a9dd..6cedf3e6e3 100644 --- a/tests/custom/permutations/16_image_permutation/int/0020_given_permutation_find_permutations/permutation.essence +++ b/tests/custom/permutations/16_transform_permutation/int/0020_given_permutation_find_permutations/permutation.essence @@ -7,5 +7,5 @@ find s : permutation of int(1..n) find sn : permutation of int(1..n) -such that sn = image(p,s) /\ sn != s /\ |s| > 0 +such that sn = transform(p,s) /\ sn != s /\ |s| > 0 diff --git a/tests/custom/permutations/16_image_permutation/int/0020_given_permutation_find_permutations/permutation.param b/tests/custom/permutations/16_transform_permutation/int/0020_given_permutation_find_permutations/permutation.param similarity index 100% rename from tests/custom/permutations/16_image_permutation/int/0020_given_permutation_find_permutations/permutation.param rename to tests/custom/permutations/16_transform_permutation/int/0020_given_permutation_find_permutations/permutation.param diff --git a/tests/custom/permutations/16_image_permutation/int/0020_given_permutation_find_permutations/run.sh b/tests/custom/permutations/16_transform_permutation/int/0020_given_permutation_find_permutations/run.sh similarity index 100% rename from tests/custom/permutations/16_image_permutation/int/0020_given_permutation_find_permutations/run.sh rename to tests/custom/permutations/16_transform_permutation/int/0020_given_permutation_find_permutations/run.sh diff --git a/tests/custom/permutations/16_image_permutation/int/0020_given_permutation_find_permutations/stdout.expected b/tests/custom/permutations/16_transform_permutation/int/0020_given_permutation_find_permutations/stdout.expected similarity index 96% rename from tests/custom/permutations/16_image_permutation/int/0020_given_permutation_find_permutations/stdout.expected rename to tests/custom/permutations/16_transform_permutation/int/0020_given_permutation_find_permutations/stdout.expected index 4a4c1a1fe9..c447fefe90 100644 --- a/tests/custom/permutations/16_image_permutation/int/0020_given_permutation_find_permutations/stdout.expected +++ b/tests/custom/permutations/16_transform_permutation/int/0020_given_permutation_find_permutations/stdout.expected @@ -2,6 +2,8 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output Savile Row: model000001.eprime permutation.param +Running minion for domain filtering. +Running solver: minion Copying solution to: permutation-permutation-000001.solution Copying solution to: permutation-permutation-000002.solution Copying solution to: permutation-permutation-000003.solution diff --git a/tests/custom/permutations/16_image_permutation/int/0030_letting_permutation_find_permutations/permutation.essence b/tests/custom/permutations/16_transform_permutation/int/0030_letting_permutation_find_permutations/permutation.essence similarity index 80% rename from tests/custom/permutations/16_image_permutation/int/0030_letting_permutation_find_permutations/permutation.essence rename to tests/custom/permutations/16_transform_permutation/int/0030_letting_permutation_find_permutations/permutation.essence index db27179e9c..b509b4340c 100644 --- a/tests/custom/permutations/16_image_permutation/int/0030_letting_permutation_find_permutations/permutation.essence +++ b/tests/custom/permutations/16_transform_permutation/int/0030_letting_permutation_find_permutations/permutation.essence @@ -7,5 +7,5 @@ find s : permutation of int(1..n) find sn : permutation of int(1..n) -such that sn = image(p,s) +such that sn = transform(p,s) diff --git a/tests/custom/permutations/16_image_permutation/int/0030_letting_permutation_find_permutations/run.sh b/tests/custom/permutations/16_transform_permutation/int/0030_letting_permutation_find_permutations/run.sh similarity index 100% rename from tests/custom/permutations/16_image_permutation/int/0030_letting_permutation_find_permutations/run.sh rename to tests/custom/permutations/16_transform_permutation/int/0030_letting_permutation_find_permutations/run.sh diff --git a/tests/custom/permutations/16_image_permutation/int/0030_letting_permutation_find_permutations/stdout.expected b/tests/custom/permutations/16_transform_permutation/int/0030_letting_permutation_find_permutations/stdout.expected similarity index 96% rename from tests/custom/permutations/16_image_permutation/int/0030_letting_permutation_find_permutations/stdout.expected rename to tests/custom/permutations/16_transform_permutation/int/0030_letting_permutation_find_permutations/stdout.expected index 640c74ecb2..f5135a83c0 100644 --- a/tests/custom/permutations/16_image_permutation/int/0030_letting_permutation_find_permutations/stdout.expected +++ b/tests/custom/permutations/16_transform_permutation/int/0030_letting_permutation_find_permutations/stdout.expected @@ -2,6 +2,8 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output Savile Row: model000001.eprime +Running minion for domain filtering. +Running solver: minion Copying solution to: permutation-000001.solution Copying solution to: permutation-000002.solution Copying solution to: permutation-000003.solution diff --git a/tests/custom/permutations/16_image_permutation/int/0040_find_permutation_find_permutations/permutation.essence b/tests/custom/permutations/16_transform_permutation/int/0040_find_permutation_find_permutations/permutation.essence similarity index 74% rename from tests/custom/permutations/16_image_permutation/int/0040_find_permutation_find_permutations/permutation.essence rename to tests/custom/permutations/16_transform_permutation/int/0040_find_permutation_find_permutations/permutation.essence index 15ea636aef..d1013736a7 100644 --- a/tests/custom/permutations/16_image_permutation/int/0040_find_permutation_find_permutations/permutation.essence +++ b/tests/custom/permutations/16_transform_permutation/int/0040_find_permutation_find_permutations/permutation.essence @@ -7,5 +7,5 @@ find s : permutation of int(1..n) find sn : permutation of int(1..n) -such that sn = image(p,s) /\ 3 = |p| +such that sn = transform(p,s) /\ 3 = |p| diff --git a/tests/custom/permutations/16_image_permutation/int/0040_find_permutation_find_permutations/run.sh b/tests/custom/permutations/16_transform_permutation/int/0040_find_permutation_find_permutations/run.sh similarity index 100% rename from tests/custom/permutations/16_image_permutation/int/0040_find_permutation_find_permutations/run.sh rename to tests/custom/permutations/16_transform_permutation/int/0040_find_permutation_find_permutations/run.sh diff --git a/tests/custom/permutations/16_image_permutation/int/0040_find_permutation_find_permutations/stdout.expected b/tests/custom/permutations/16_transform_permutation/int/0040_find_permutation_find_permutations/stdout.expected similarity index 96% rename from tests/custom/permutations/16_image_permutation/int/0040_find_permutation_find_permutations/stdout.expected rename to tests/custom/permutations/16_transform_permutation/int/0040_find_permutation_find_permutations/stdout.expected index 820e928dce..615c9a835f 100644 --- a/tests/custom/permutations/16_image_permutation/int/0040_find_permutation_find_permutations/stdout.expected +++ b/tests/custom/permutations/16_transform_permutation/int/0040_find_permutation_find_permutations/stdout.expected @@ -2,6 +2,8 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output Savile Row: model000001.eprime +Running minion for domain filtering. +Running solver: minion Copying solution to: permutation-000001.solution Copying solution to: permutation-000002.solution Copying solution to: permutation-000003.solution diff --git a/tests/custom/permutations/16_image_permutation/int/0050_find_permutation_given_permutation_find_permutation/permutation.essence b/tests/custom/permutations/16_transform_permutation/int/0050_find_permutation_given_permutation_find_permutation/permutation.essence similarity index 80% rename from tests/custom/permutations/16_image_permutation/int/0050_find_permutation_given_permutation_find_permutation/permutation.essence rename to tests/custom/permutations/16_transform_permutation/int/0050_find_permutation_given_permutation_find_permutation/permutation.essence index df9daf9b35..b2d77ac49e 100644 --- a/tests/custom/permutations/16_image_permutation/int/0050_find_permutation_given_permutation_find_permutation/permutation.essence +++ b/tests/custom/permutations/16_transform_permutation/int/0050_find_permutation_given_permutation_find_permutation/permutation.essence @@ -7,5 +7,5 @@ given s : permutation of int(1..n) find sn : permutation of int(1..n) -such that sn = image(p,s) +such that sn = transform(p,s) diff --git a/tests/custom/permutations/16_image_permutation/int/0050_find_permutation_given_permutation_find_permutation/permutation.param b/tests/custom/permutations/16_transform_permutation/int/0050_find_permutation_given_permutation_find_permutation/permutation.param similarity index 100% rename from tests/custom/permutations/16_image_permutation/int/0050_find_permutation_given_permutation_find_permutation/permutation.param rename to tests/custom/permutations/16_transform_permutation/int/0050_find_permutation_given_permutation_find_permutation/permutation.param diff --git a/tests/custom/permutations/16_image_permutation/int/0050_find_permutation_given_permutation_find_permutation/run.sh b/tests/custom/permutations/16_transform_permutation/int/0050_find_permutation_given_permutation_find_permutation/run.sh similarity index 100% rename from tests/custom/permutations/16_image_permutation/int/0050_find_permutation_given_permutation_find_permutation/run.sh rename to tests/custom/permutations/16_transform_permutation/int/0050_find_permutation_given_permutation_find_permutation/run.sh diff --git a/tests/custom/permutations/16_image_permutation/int/0050_find_permutation_given_permutation_find_permutation/stdout.expected b/tests/custom/permutations/16_transform_permutation/int/0050_find_permutation_given_permutation_find_permutation/stdout.expected similarity index 96% rename from tests/custom/permutations/16_image_permutation/int/0050_find_permutation_given_permutation_find_permutation/stdout.expected rename to tests/custom/permutations/16_transform_permutation/int/0050_find_permutation_given_permutation_find_permutation/stdout.expected index c03dbfd631..cdd0426367 100644 --- a/tests/custom/permutations/16_image_permutation/int/0050_find_permutation_given_permutation_find_permutation/stdout.expected +++ b/tests/custom/permutations/16_transform_permutation/int/0050_find_permutation_given_permutation_find_permutation/stdout.expected @@ -2,6 +2,8 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output Savile Row: model000001.eprime permutation.param +Running minion for domain filtering. +Running solver: minion Copying solution to: permutation-permutation-000001.solution Copying solution to: permutation-permutation-000002.solution Copying solution to: permutation-permutation-000003.solution diff --git a/tests/custom/permutations/16_transform_permutation/runthese.sh b/tests/custom/permutations/16_transform_permutation/runthese.sh new file mode 100644 index 0000000000..5b0a16dc53 --- /dev/null +++ b/tests/custom/permutations/16_transform_permutation/runthese.sh @@ -0,0 +1 @@ +stack build --copy-bins --test --test-arguments "-p custom.permutations.16_transform_permutation" diff --git a/tests/custom/permutations/16_image_permutation/unnamed/0004_find_permutation_find_permutations/permutation.essence b/tests/custom/permutations/16_transform_permutation/unnamed/0004_find_permutation_find_permutations/permutation.essence similarity index 74% rename from tests/custom/permutations/16_image_permutation/unnamed/0004_find_permutation_find_permutations/permutation.essence rename to tests/custom/permutations/16_transform_permutation/unnamed/0004_find_permutation_find_permutations/permutation.essence index 41ef1b0e1c..c29addc20c 100644 --- a/tests/custom/permutations/16_image_permutation/unnamed/0004_find_permutation_find_permutations/permutation.essence +++ b/tests/custom/permutations/16_transform_permutation/unnamed/0004_find_permutation_find_permutations/permutation.essence @@ -7,5 +7,5 @@ find s : permutation of n find sn : permutation of n -such that sn = image(p,s) /\ |p| > 0 +such that sn = transform(p,s) /\ |p| > 0 diff --git a/tests/custom/permutations/16_image_permutation/unnamed/0004_find_permutation_find_permutations/run.sh b/tests/custom/permutations/16_transform_permutation/unnamed/0004_find_permutation_find_permutations/run.sh similarity index 100% rename from tests/custom/permutations/16_image_permutation/unnamed/0004_find_permutation_find_permutations/run.sh rename to tests/custom/permutations/16_transform_permutation/unnamed/0004_find_permutation_find_permutations/run.sh diff --git a/tests/custom/permutations/16_image_permutation/unnamed/0004_find_permutation_find_permutations/stdout.expected b/tests/custom/permutations/16_transform_permutation/unnamed/0004_find_permutation_find_permutations/stdout.expected similarity index 97% rename from tests/custom/permutations/16_image_permutation/unnamed/0004_find_permutation_find_permutations/stdout.expected rename to tests/custom/permutations/16_transform_permutation/unnamed/0004_find_permutation_find_permutations/stdout.expected index 7426c7dd7b..77f97629e9 100644 --- a/tests/custom/permutations/16_image_permutation/unnamed/0004_find_permutation_find_permutations/stdout.expected +++ b/tests/custom/permutations/16_transform_permutation/unnamed/0004_find_permutation_find_permutations/stdout.expected @@ -2,6 +2,8 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output Savile Row: model000001.eprime +Running minion for domain filtering. +Running solver: minion Copying solution to: permutation-000001.solution Copying solution to: permutation-000002.solution Copying solution to: permutation-000003.solution diff --git a/tests/custom/permutations/17_image_partition/enum/0010_given_partition_of_enum_BUG/stderr.expected b/tests/custom/permutations/17_image_partition/enum/0010_given_partition_of_enum_BUG/stderr.expected deleted file mode 100644 index 31143a8512..0000000000 --- a/tests/custom/permutations/17_image_partition/enum/0010_given_partition_of_enum_BUG/stderr.expected +++ /dev/null @@ -1,25 +0,0 @@ -conjure: -Ran commands: - -Exception: This should never happen, sorry! - -However, it did happen, so it must be a bug. Please report it to us! - -Conjure is actively maintained, we will get back to you as soon as possible. -You can help us by providing a minimal failing example. - -Also include the repository version for this build: 3471a2936 (2019-05-08 11:52:07 +0100) - -Issue tracker: http://github.com/conjure-cp/conjure/issues - - -IO Error -No value for: n_EnumSize -Bindings in context: - s: partition({1, 2}, {3, 4}) - n: `int(1..4)` - -CallStack (from HasCallStack): - error, called at src/Conjure/Bug.hs:21:15 in conjure-cp-2.2.0-71NFmy1yFuTKzqIQD5mEC7:Conjure.Bug - bug, called at src/Conjure/Bug.hs:47:16 in conjure-cp-2.2.0-71NFmy1yFuTKzqIQD5mEC7:Conjure.Bug -cat: conjure-output/*.solution: No such file or directory diff --git a/tests/custom/permutations/17_image_partition/runthese.sh b/tests/custom/permutations/17_image_partition/runthese.sh deleted file mode 100644 index f7d9c58994..0000000000 --- a/tests/custom/permutations/17_image_partition/runthese.sh +++ /dev/null @@ -1 +0,0 @@ -stack build --copy-bins --test --test-arguments "-p custom.permutations.17_image_partition" diff --git a/tests/custom/permutations/17_image_partition/BUGS.md b/tests/custom/permutations/17_transform_partition/BUGS.md similarity index 100% rename from tests/custom/permutations/17_image_partition/BUGS.md rename to tests/custom/permutations/17_transform_partition/BUGS.md diff --git a/tests/custom/permutations/17_transform_partition/accept_these.sh b/tests/custom/permutations/17_transform_partition/accept_these.sh new file mode 100644 index 0000000000..9ce41ef5fb --- /dev/null +++ b/tests/custom/permutations/17_transform_partition/accept_these.sh @@ -0,0 +1,7 @@ +sh ../../acceptOutput.sh enum/0010_given_partition_of_enum_BUG +sh ../../acceptOutput.sh int/0020_given_permutation_find_partitions +sh ../../acceptOutput.sh int/0040_find_permutation_find_partitions +sh ../../acceptOutput.sh int/0030_letting_permutation_find_partitions +sh ../../acceptOutput.sh int/0010_given_permutation_partition_find_partition +sh ../../acceptOutput.sh int/0050_find_permutation_given_partition_find_partition +sh ../../acceptOutput.sh unnamed/0010_find_partition_of_unnamed diff --git a/tests/custom/permutations/17_image_partition/enum/0010_given_partition_of_enum_BUG/permutation.essence b/tests/custom/permutations/17_transform_partition/enum/0010_given_partition_of_enum_BUG/permutation.essence similarity index 100% rename from tests/custom/permutations/17_image_partition/enum/0010_given_partition_of_enum_BUG/permutation.essence rename to tests/custom/permutations/17_transform_partition/enum/0010_given_partition_of_enum_BUG/permutation.essence diff --git a/tests/custom/permutations/17_image_partition/enum/0010_given_partition_of_enum_BUG/permutation.param b/tests/custom/permutations/17_transform_partition/enum/0010_given_partition_of_enum_BUG/permutation.param similarity index 100% rename from tests/custom/permutations/17_image_partition/enum/0010_given_partition_of_enum_BUG/permutation.param rename to tests/custom/permutations/17_transform_partition/enum/0010_given_partition_of_enum_BUG/permutation.param diff --git a/tests/custom/permutations/17_image_partition/enum/0010_given_partition_of_enum_BUG/run.sh b/tests/custom/permutations/17_transform_partition/enum/0010_given_partition_of_enum_BUG/run.sh similarity index 100% rename from tests/custom/permutations/17_image_partition/enum/0010_given_partition_of_enum_BUG/run.sh rename to tests/custom/permutations/17_transform_partition/enum/0010_given_partition_of_enum_BUG/run.sh diff --git a/tests/custom/permutations/17_transform_partition/enum/0010_given_partition_of_enum_BUG/stderr.expected b/tests/custom/permutations/17_transform_partition/enum/0010_given_partition_of_enum_BUG/stderr.expected new file mode 100644 index 0000000000..3ebb6892ff --- /dev/null +++ b/tests/custom/permutations/17_transform_partition/enum/0010_given_partition_of_enum_BUG/stderr.expected @@ -0,0 +1,6 @@ +Error: + No value for: n_EnumSize + Bindings in context: + s: partition({1, 2}, {3, 4}) + n: `n` +cat: conjure-output/*.solution: No such file or directory diff --git a/tests/custom/permutations/17_image_partition/enum/0010_given_partition_of_enum_BUG/stdout.expected b/tests/custom/permutations/17_transform_partition/enum/0010_given_partition_of_enum_BUG/stdout.expected similarity index 100% rename from tests/custom/permutations/17_image_partition/enum/0010_given_partition_of_enum_BUG/stdout.expected rename to tests/custom/permutations/17_transform_partition/enum/0010_given_partition_of_enum_BUG/stdout.expected diff --git a/tests/custom/permutations/17_image_partition/enum/0020_find_partition_of_enum_BUG/permutation.essence b/tests/custom/permutations/17_transform_partition/enum/0020_find_partition_of_enum_BUG/permutation.essence similarity index 100% rename from tests/custom/permutations/17_image_partition/enum/0020_find_partition_of_enum_BUG/permutation.essence rename to tests/custom/permutations/17_transform_partition/enum/0020_find_partition_of_enum_BUG/permutation.essence diff --git a/tests/custom/permutations/17_image_partition/enum/0020_find_partition_of_enum_BUG/run.sh b/tests/custom/permutations/17_transform_partition/enum/0020_find_partition_of_enum_BUG/run.sh similarity index 100% rename from tests/custom/permutations/17_image_partition/enum/0020_find_partition_of_enum_BUG/run.sh rename to tests/custom/permutations/17_transform_partition/enum/0020_find_partition_of_enum_BUG/run.sh diff --git a/tests/custom/permutations/17_image_partition/enum/0020_find_partition_of_enum_BUG/stderr.expected b/tests/custom/permutations/17_transform_partition/enum/0020_find_partition_of_enum_BUG/stderr.expected similarity index 100% rename from tests/custom/permutations/17_image_partition/enum/0020_find_partition_of_enum_BUG/stderr.expected rename to tests/custom/permutations/17_transform_partition/enum/0020_find_partition_of_enum_BUG/stderr.expected diff --git a/tests/custom/permutations/17_image_partition/enum/0020_find_partition_of_enum_BUG/stdout.expected b/tests/custom/permutations/17_transform_partition/enum/0020_find_partition_of_enum_BUG/stdout.expected similarity index 100% rename from tests/custom/permutations/17_image_partition/enum/0020_find_partition_of_enum_BUG/stdout.expected rename to tests/custom/permutations/17_transform_partition/enum/0020_find_partition_of_enum_BUG/stdout.expected diff --git a/tests/custom/permutations/17_image_partition/int/0010_given_permutation_partition_find_partition/permutation.essence b/tests/custom/permutations/17_transform_partition/int/0010_given_permutation_partition_find_partition/permutation.essence similarity index 80% rename from tests/custom/permutations/17_image_partition/int/0010_given_permutation_partition_find_partition/permutation.essence rename to tests/custom/permutations/17_transform_partition/int/0010_given_permutation_partition_find_partition/permutation.essence index 655db58eee..362296528c 100644 --- a/tests/custom/permutations/17_image_partition/int/0010_given_permutation_partition_find_partition/permutation.essence +++ b/tests/custom/permutations/17_transform_partition/int/0010_given_permutation_partition_find_partition/permutation.essence @@ -6,5 +6,5 @@ given s : partition from int(1..n) find sn : partition from int(1..n) -such that sn = image(p,s) +such that sn = transform(p,s) diff --git a/tests/custom/permutations/17_image_partition/int/0010_given_permutation_partition_find_partition/permutation.param b/tests/custom/permutations/17_transform_partition/int/0010_given_permutation_partition_find_partition/permutation.param similarity index 100% rename from tests/custom/permutations/17_image_partition/int/0010_given_permutation_partition_find_partition/permutation.param rename to tests/custom/permutations/17_transform_partition/int/0010_given_permutation_partition_find_partition/permutation.param diff --git a/tests/custom/permutations/17_image_partition/int/0010_given_permutation_partition_find_partition/run.sh b/tests/custom/permutations/17_transform_partition/int/0010_given_permutation_partition_find_partition/run.sh similarity index 100% rename from tests/custom/permutations/17_image_partition/int/0010_given_permutation_partition_find_partition/run.sh rename to tests/custom/permutations/17_transform_partition/int/0010_given_permutation_partition_find_partition/run.sh diff --git a/tests/custom/permutations/17_image_partition/int/0010_given_permutation_partition_find_partition/stdout.expected b/tests/custom/permutations/17_transform_partition/int/0010_given_permutation_partition_find_partition/stdout.expected similarity index 83% rename from tests/custom/permutations/17_image_partition/int/0010_given_permutation_partition_find_partition/stdout.expected rename to tests/custom/permutations/17_transform_partition/int/0010_given_permutation_partition_find_partition/stdout.expected index 75fa929da5..1ef30ea1bc 100644 --- a/tests/custom/permutations/17_image_partition/int/0010_given_permutation_partition_find_partition/stdout.expected +++ b/tests/custom/permutations/17_transform_partition/int/0010_given_permutation_partition_find_partition/stdout.expected @@ -2,6 +2,8 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output Savile Row: model000001.eprime permutation.param +Running minion for domain filtering. +Running solver: minion Copying solution to: permutation-permutation.solution language Essence 1.3 diff --git a/tests/custom/permutations/17_image_partition/int/0020_given_permutation_find_partitions/permutation.essence b/tests/custom/permutations/17_transform_partition/int/0020_given_permutation_find_partitions/permutation.essence similarity index 70% rename from tests/custom/permutations/17_image_partition/int/0020_given_permutation_find_partitions/permutation.essence rename to tests/custom/permutations/17_transform_partition/int/0020_given_permutation_find_partitions/permutation.essence index 0dae580e91..a351d7b830 100644 --- a/tests/custom/permutations/17_image_partition/int/0020_given_permutation_find_partitions/permutation.essence +++ b/tests/custom/permutations/17_transform_partition/int/0020_given_permutation_find_partitions/permutation.essence @@ -7,5 +7,5 @@ find s : partition from int(1..n) find sn : partition from int(1..n) -such that sn = image(p,s) /\ sn != s /\ |s| > 0 +such that sn = transform(p,s) /\ sn != s /\ |s| > 0 diff --git a/tests/custom/permutations/17_image_partition/int/0020_given_permutation_find_partitions/permutation.param b/tests/custom/permutations/17_transform_partition/int/0020_given_permutation_find_partitions/permutation.param similarity index 100% rename from tests/custom/permutations/17_image_partition/int/0020_given_permutation_find_partitions/permutation.param rename to tests/custom/permutations/17_transform_partition/int/0020_given_permutation_find_partitions/permutation.param diff --git a/tests/custom/permutations/17_image_partition/int/0020_given_permutation_find_partitions/run.sh b/tests/custom/permutations/17_transform_partition/int/0020_given_permutation_find_partitions/run.sh similarity index 100% rename from tests/custom/permutations/17_image_partition/int/0020_given_permutation_find_partitions/run.sh rename to tests/custom/permutations/17_transform_partition/int/0020_given_permutation_find_partitions/run.sh diff --git a/tests/custom/permutations/17_image_partition/int/0020_given_permutation_find_partitions/stdout.expected b/tests/custom/permutations/17_transform_partition/int/0020_given_permutation_find_partitions/stdout.expected similarity index 97% rename from tests/custom/permutations/17_image_partition/int/0020_given_permutation_find_partitions/stdout.expected rename to tests/custom/permutations/17_transform_partition/int/0020_given_permutation_find_partitions/stdout.expected index cdb26da296..22c01e1f33 100644 --- a/tests/custom/permutations/17_image_partition/int/0020_given_permutation_find_partitions/stdout.expected +++ b/tests/custom/permutations/17_transform_partition/int/0020_given_permutation_find_partitions/stdout.expected @@ -2,6 +2,8 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output Savile Row: model000001.eprime permutation.param +Running minion for domain filtering. +Running solver: minion Copying solution to: permutation-permutation-000001.solution Copying solution to: permutation-permutation-000002.solution Copying solution to: permutation-permutation-000003.solution diff --git a/tests/custom/permutations/17_image_partition/int/0030_letting_permutation_find_partitions/permutation.essence b/tests/custom/permutations/17_transform_partition/int/0030_letting_permutation_find_partitions/permutation.essence similarity index 80% rename from tests/custom/permutations/17_image_partition/int/0030_letting_permutation_find_partitions/permutation.essence rename to tests/custom/permutations/17_transform_partition/int/0030_letting_permutation_find_partitions/permutation.essence index bc3c7c232a..044aa742d6 100644 --- a/tests/custom/permutations/17_image_partition/int/0030_letting_permutation_find_partitions/permutation.essence +++ b/tests/custom/permutations/17_transform_partition/int/0030_letting_permutation_find_partitions/permutation.essence @@ -7,5 +7,5 @@ find s : partition from int(1..n) find sn : partition from int(1..n) -such that sn = image(p,s) +such that sn = transform(p,s) diff --git a/tests/custom/permutations/17_image_partition/int/0030_letting_permutation_find_partitions/run.sh b/tests/custom/permutations/17_transform_partition/int/0030_letting_permutation_find_partitions/run.sh similarity index 100% rename from tests/custom/permutations/17_image_partition/int/0030_letting_permutation_find_partitions/run.sh rename to tests/custom/permutations/17_transform_partition/int/0030_letting_permutation_find_partitions/run.sh diff --git a/tests/custom/permutations/17_image_partition/int/0030_letting_permutation_find_partitions/stdout.expected b/tests/custom/permutations/17_transform_partition/int/0030_letting_permutation_find_partitions/stdout.expected similarity index 97% rename from tests/custom/permutations/17_image_partition/int/0030_letting_permutation_find_partitions/stdout.expected rename to tests/custom/permutations/17_transform_partition/int/0030_letting_permutation_find_partitions/stdout.expected index 0a5cc47ad3..e83b516d73 100644 --- a/tests/custom/permutations/17_image_partition/int/0030_letting_permutation_find_partitions/stdout.expected +++ b/tests/custom/permutations/17_transform_partition/int/0030_letting_permutation_find_partitions/stdout.expected @@ -2,6 +2,8 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output Savile Row: model000001.eprime +Running minion for domain filtering. +Running solver: minion Copying solution to: permutation-000001.solution Copying solution to: permutation-000002.solution Copying solution to: permutation-000003.solution diff --git a/tests/custom/permutations/17_image_partition/int/0040_find_permutation_find_partitions/permutation.essence b/tests/custom/permutations/17_transform_partition/int/0040_find_permutation_find_partitions/permutation.essence similarity index 74% rename from tests/custom/permutations/17_image_partition/int/0040_find_permutation_find_partitions/permutation.essence rename to tests/custom/permutations/17_transform_partition/int/0040_find_permutation_find_partitions/permutation.essence index 947d6ec00f..9a3e54913d 100644 --- a/tests/custom/permutations/17_image_partition/int/0040_find_permutation_find_partitions/permutation.essence +++ b/tests/custom/permutations/17_transform_partition/int/0040_find_permutation_find_partitions/permutation.essence @@ -7,5 +7,5 @@ find s : partition from int(1..n) find sn : partition from int(1..n) -such that sn = image(p,s) /\ 3 = |p| +such that sn = transform(p,s) /\ 3 = |p| diff --git a/tests/custom/permutations/17_image_partition/int/0040_find_permutation_find_partitions/run.sh b/tests/custom/permutations/17_transform_partition/int/0040_find_permutation_find_partitions/run.sh similarity index 100% rename from tests/custom/permutations/17_image_partition/int/0040_find_permutation_find_partitions/run.sh rename to tests/custom/permutations/17_transform_partition/int/0040_find_permutation_find_partitions/run.sh diff --git a/tests/custom/permutations/17_image_partition/int/0040_find_permutation_find_partitions/stdout.expected b/tests/custom/permutations/17_transform_partition/int/0040_find_permutation_find_partitions/stdout.expected similarity index 97% rename from tests/custom/permutations/17_image_partition/int/0040_find_permutation_find_partitions/stdout.expected rename to tests/custom/permutations/17_transform_partition/int/0040_find_permutation_find_partitions/stdout.expected index f4b377f97d..2ecd83b341 100644 --- a/tests/custom/permutations/17_image_partition/int/0040_find_permutation_find_partitions/stdout.expected +++ b/tests/custom/permutations/17_transform_partition/int/0040_find_permutation_find_partitions/stdout.expected @@ -2,6 +2,8 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output Savile Row: model000001.eprime +Running minion for domain filtering. +Running solver: minion Copying solution to: permutation-000001.solution Copying solution to: permutation-000002.solution Copying solution to: permutation-000003.solution diff --git a/tests/custom/permutations/17_image_partition/int/0050_find_permutation_given_partition_find_partition/permutation.essence b/tests/custom/permutations/17_transform_partition/int/0050_find_permutation_given_partition_find_partition/permutation.essence similarity index 80% rename from tests/custom/permutations/17_image_partition/int/0050_find_permutation_given_partition_find_partition/permutation.essence rename to tests/custom/permutations/17_transform_partition/int/0050_find_permutation_given_partition_find_partition/permutation.essence index 5e04cbe8ed..b615b9813e 100644 --- a/tests/custom/permutations/17_image_partition/int/0050_find_permutation_given_partition_find_partition/permutation.essence +++ b/tests/custom/permutations/17_transform_partition/int/0050_find_permutation_given_partition_find_partition/permutation.essence @@ -7,5 +7,5 @@ given s : partition from int(1..n) find sn : partition from int(1..n) -such that sn = image(p,s) +such that sn = transform(p,s) diff --git a/tests/custom/permutations/17_image_partition/int/0050_find_permutation_given_partition_find_partition/permutation.param b/tests/custom/permutations/17_transform_partition/int/0050_find_permutation_given_partition_find_partition/permutation.param similarity index 100% rename from tests/custom/permutations/17_image_partition/int/0050_find_permutation_given_partition_find_partition/permutation.param rename to tests/custom/permutations/17_transform_partition/int/0050_find_permutation_given_partition_find_partition/permutation.param diff --git a/tests/custom/permutations/17_image_partition/int/0050_find_permutation_given_partition_find_partition/run.sh b/tests/custom/permutations/17_transform_partition/int/0050_find_permutation_given_partition_find_partition/run.sh similarity index 100% rename from tests/custom/permutations/17_image_partition/int/0050_find_permutation_given_partition_find_partition/run.sh rename to tests/custom/permutations/17_transform_partition/int/0050_find_permutation_given_partition_find_partition/run.sh diff --git a/tests/custom/permutations/17_image_partition/int/0050_find_permutation_given_partition_find_partition/stdout.expected b/tests/custom/permutations/17_transform_partition/int/0050_find_permutation_given_partition_find_partition/stdout.expected similarity index 97% rename from tests/custom/permutations/17_image_partition/int/0050_find_permutation_given_partition_find_partition/stdout.expected rename to tests/custom/permutations/17_transform_partition/int/0050_find_permutation_given_partition_find_partition/stdout.expected index 7eb68a2281..105650bc2c 100644 --- a/tests/custom/permutations/17_image_partition/int/0050_find_permutation_given_partition_find_partition/stdout.expected +++ b/tests/custom/permutations/17_transform_partition/int/0050_find_permutation_given_partition_find_partition/stdout.expected @@ -2,6 +2,8 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output Savile Row: model000001.eprime permutation.param +Running minion for domain filtering. +Running solver: minion Copying solution to: permutation-permutation-000001.solution Copying solution to: permutation-permutation-000002.solution Copying solution to: permutation-permutation-000003.solution diff --git a/tests/custom/permutations/17_transform_partition/runthese.sh b/tests/custom/permutations/17_transform_partition/runthese.sh new file mode 100644 index 0000000000..43b2e440cb --- /dev/null +++ b/tests/custom/permutations/17_transform_partition/runthese.sh @@ -0,0 +1 @@ +stack build --copy-bins --test --test-arguments "-p custom.permutations.17_transform_partition" diff --git a/tests/custom/permutations/17_image_partition/unnamed/0010_find_partition_of_unnamed/permutation.essence b/tests/custom/permutations/17_transform_partition/unnamed/0010_find_partition_of_unnamed/permutation.essence similarity index 75% rename from tests/custom/permutations/17_image_partition/unnamed/0010_find_partition_of_unnamed/permutation.essence rename to tests/custom/permutations/17_transform_partition/unnamed/0010_find_partition_of_unnamed/permutation.essence index 7db072527e..325b1db590 100644 --- a/tests/custom/permutations/17_image_partition/unnamed/0010_find_partition_of_unnamed/permutation.essence +++ b/tests/custom/permutations/17_transform_partition/unnamed/0010_find_partition_of_unnamed/permutation.essence @@ -2,4 +2,4 @@ letting n be new type of size 4 find a : partition from n find b : partition from n find p : permutation (size 3) of n -such that b = image(p,a) /\ a != b +such that b = transform(p,a) /\ a != b diff --git a/tests/custom/permutations/17_image_partition/unnamed/0010_find_partition_of_unnamed/run.sh b/tests/custom/permutations/17_transform_partition/unnamed/0010_find_partition_of_unnamed/run.sh similarity index 100% rename from tests/custom/permutations/17_image_partition/unnamed/0010_find_partition_of_unnamed/run.sh rename to tests/custom/permutations/17_transform_partition/unnamed/0010_find_partition_of_unnamed/run.sh diff --git a/tests/custom/permutations/17_image_partition/unnamed/0010_find_partition_of_unnamed/stdout.expected b/tests/custom/permutations/17_transform_partition/unnamed/0010_find_partition_of_unnamed/stdout.expected similarity index 98% rename from tests/custom/permutations/17_image_partition/unnamed/0010_find_partition_of_unnamed/stdout.expected rename to tests/custom/permutations/17_transform_partition/unnamed/0010_find_partition_of_unnamed/stdout.expected index 76423dba25..75a4cba9a1 100644 --- a/tests/custom/permutations/17_image_partition/unnamed/0010_find_partition_of_unnamed/stdout.expected +++ b/tests/custom/permutations/17_transform_partition/unnamed/0010_find_partition_of_unnamed/stdout.expected @@ -2,6 +2,8 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output Savile Row: model000001.eprime +Running minion for domain filtering. +Running solver: minion Copying solution to: permutation-000001.solution Copying solution to: permutation-000002.solution Copying solution to: permutation-000003.solution diff --git a/tests/custom/permutations/18_image_matrix/runthese.sh b/tests/custom/permutations/18_image_matrix/runthese.sh deleted file mode 100644 index fbd0b51ebd..0000000000 --- a/tests/custom/permutations/18_image_matrix/runthese.sh +++ /dev/null @@ -1 +0,0 @@ -stack build --copy-bins --test --test-arguments "-p custom.permutations.18_image_matrix" diff --git a/tests/custom/permutations/18_image_matrix/enum/0010_find_permutation_indexing_given_matrix/permutation.essence b/tests/custom/permutations/18_transform_matrix/enum/0010_find_permutation_indexing_given_matrix/permutation.essence similarity index 75% rename from tests/custom/permutations/18_image_matrix/enum/0010_find_permutation_indexing_given_matrix/permutation.essence rename to tests/custom/permutations/18_transform_matrix/enum/0010_find_permutation_indexing_given_matrix/permutation.essence index 53aa282871..5431ec54d7 100644 --- a/tests/custom/permutations/18_image_matrix/enum/0010_find_permutation_indexing_given_matrix/permutation.essence +++ b/tests/custom/permutations/18_transform_matrix/enum/0010_find_permutation_indexing_given_matrix/permutation.essence @@ -4,5 +4,5 @@ find p : permutation of n given s : matrix indexed by [int(1..4)] of n find t : matrix indexed by [int(1..4)] of n -such that e_8 = image(p,s)[2] /\ t = image(p,s) +such that e_8 = transform(p,s)[2] /\ t = image(p,s) diff --git a/tests/custom/permutations/18_image_matrix/enum/0010_find_permutation_indexing_given_matrix/permutation.param b/tests/custom/permutations/18_transform_matrix/enum/0010_find_permutation_indexing_given_matrix/permutation.param similarity index 100% rename from tests/custom/permutations/18_image_matrix/enum/0010_find_permutation_indexing_given_matrix/permutation.param rename to tests/custom/permutations/18_transform_matrix/enum/0010_find_permutation_indexing_given_matrix/permutation.param diff --git a/tests/custom/permutations/18_image_matrix/enum/0010_find_permutation_indexing_given_matrix/run.sh b/tests/custom/permutations/18_transform_matrix/enum/0010_find_permutation_indexing_given_matrix/run.sh similarity index 100% rename from tests/custom/permutations/18_image_matrix/enum/0010_find_permutation_indexing_given_matrix/run.sh rename to tests/custom/permutations/18_transform_matrix/enum/0010_find_permutation_indexing_given_matrix/run.sh diff --git a/tests/custom/permutations/18_image_matrix/enum/0010_find_permutation_indexing_given_matrix/stdout.expected b/tests/custom/permutations/18_transform_matrix/enum/0010_find_permutation_indexing_given_matrix/stdout.expected similarity index 100% rename from tests/custom/permutations/18_image_matrix/enum/0010_find_permutation_indexing_given_matrix/stdout.expected rename to tests/custom/permutations/18_transform_matrix/enum/0010_find_permutation_indexing_given_matrix/stdout.expected diff --git a/tests/custom/permutations/18_image_matrix/enum/0015_find_permutation_indexing_given_matrix/permutation.essence b/tests/custom/permutations/18_transform_matrix/enum/0015_find_permutation_indexing_given_matrix/permutation.essence similarity index 75% rename from tests/custom/permutations/18_image_matrix/enum/0015_find_permutation_indexing_given_matrix/permutation.essence rename to tests/custom/permutations/18_transform_matrix/enum/0015_find_permutation_indexing_given_matrix/permutation.essence index 81c6159239..2d592b4f06 100644 --- a/tests/custom/permutations/18_image_matrix/enum/0015_find_permutation_indexing_given_matrix/permutation.essence +++ b/tests/custom/permutations/18_transform_matrix/enum/0015_find_permutation_indexing_given_matrix/permutation.essence @@ -3,5 +3,5 @@ letting n be new type enum {e_5,e_6,e_7,e_8} find p : permutation of n letting s be [e_5,e_6,e_7,e_8] -such that e_8 = image(p,s)[2] +such that e_8 = transform(p,s)[2] diff --git a/tests/custom/permutations/18_image_matrix/enum/0015_find_permutation_indexing_given_matrix/run.sh b/tests/custom/permutations/18_transform_matrix/enum/0015_find_permutation_indexing_given_matrix/run.sh similarity index 100% rename from tests/custom/permutations/18_image_matrix/enum/0015_find_permutation_indexing_given_matrix/run.sh rename to tests/custom/permutations/18_transform_matrix/enum/0015_find_permutation_indexing_given_matrix/run.sh diff --git a/tests/custom/permutations/18_image_matrix/enum/0015_find_permutation_indexing_given_matrix/stdout.expected b/tests/custom/permutations/18_transform_matrix/enum/0015_find_permutation_indexing_given_matrix/stdout.expected similarity index 100% rename from tests/custom/permutations/18_image_matrix/enum/0015_find_permutation_indexing_given_matrix/stdout.expected rename to tests/custom/permutations/18_transform_matrix/enum/0015_find_permutation_indexing_given_matrix/stdout.expected diff --git a/tests/custom/permutations/18_image_matrix/enum/0020_given_permutation_and_matrix_find_matrix/permutation.essence b/tests/custom/permutations/18_transform_matrix/enum/0020_given_permutation_and_matrix_find_matrix/permutation.essence similarity index 85% rename from tests/custom/permutations/18_image_matrix/enum/0020_given_permutation_and_matrix_find_matrix/permutation.essence rename to tests/custom/permutations/18_transform_matrix/enum/0020_given_permutation_and_matrix_find_matrix/permutation.essence index c6cbd22bcb..6334331928 100644 --- a/tests/custom/permutations/18_image_matrix/enum/0020_given_permutation_and_matrix_find_matrix/permutation.essence +++ b/tests/custom/permutations/18_transform_matrix/enum/0020_given_permutation_and_matrix_find_matrix/permutation.essence @@ -5,5 +5,5 @@ given s : matrix indexed by [int(11..14)] of n find sn : matrix indexed by [int(11..14)] of n -such that sn = image(p,s) +such that sn = transform(p,s) diff --git a/tests/custom/permutations/18_image_matrix/enum/0020_given_permutation_and_matrix_find_matrix/permutation.param b/tests/custom/permutations/18_transform_matrix/enum/0020_given_permutation_and_matrix_find_matrix/permutation.param similarity index 100% rename from tests/custom/permutations/18_image_matrix/enum/0020_given_permutation_and_matrix_find_matrix/permutation.param rename to tests/custom/permutations/18_transform_matrix/enum/0020_given_permutation_and_matrix_find_matrix/permutation.param diff --git a/tests/custom/permutations/18_image_matrix/enum/0020_given_permutation_and_matrix_find_matrix/run.sh b/tests/custom/permutations/18_transform_matrix/enum/0020_given_permutation_and_matrix_find_matrix/run.sh similarity index 100% rename from tests/custom/permutations/18_image_matrix/enum/0020_given_permutation_and_matrix_find_matrix/run.sh rename to tests/custom/permutations/18_transform_matrix/enum/0020_given_permutation_and_matrix_find_matrix/run.sh diff --git a/tests/custom/permutations/18_image_matrix/enum/0020_given_permutation_and_matrix_find_matrix/stdout.expected b/tests/custom/permutations/18_transform_matrix/enum/0020_given_permutation_and_matrix_find_matrix/stdout.expected similarity index 100% rename from tests/custom/permutations/18_image_matrix/enum/0020_given_permutation_and_matrix_find_matrix/stdout.expected rename to tests/custom/permutations/18_transform_matrix/enum/0020_given_permutation_and_matrix_find_matrix/stdout.expected diff --git a/tests/custom/permutations/18_image_matrix/enum/0030_letting_permutation_given_matrix_find_matrix/permutation.essence b/tests/custom/permutations/18_transform_matrix/enum/0030_letting_permutation_given_matrix_find_matrix/permutation.essence similarity index 85% rename from tests/custom/permutations/18_image_matrix/enum/0030_letting_permutation_given_matrix_find_matrix/permutation.essence rename to tests/custom/permutations/18_transform_matrix/enum/0030_letting_permutation_given_matrix_find_matrix/permutation.essence index e62573ab31..cf493e7d21 100644 --- a/tests/custom/permutations/18_image_matrix/enum/0030_letting_permutation_given_matrix_find_matrix/permutation.essence +++ b/tests/custom/permutations/18_transform_matrix/enum/0030_letting_permutation_given_matrix_find_matrix/permutation.essence @@ -5,5 +5,5 @@ given s : matrix indexed by [int(1..4)] of n find sn : matrix indexed by [int(1..4)] of n -such that sn = image(p,s) +such that sn = transform(p,s) diff --git a/tests/custom/permutations/18_image_matrix/enum/0030_letting_permutation_given_matrix_find_matrix/permutation.param b/tests/custom/permutations/18_transform_matrix/enum/0030_letting_permutation_given_matrix_find_matrix/permutation.param similarity index 100% rename from tests/custom/permutations/18_image_matrix/enum/0030_letting_permutation_given_matrix_find_matrix/permutation.param rename to tests/custom/permutations/18_transform_matrix/enum/0030_letting_permutation_given_matrix_find_matrix/permutation.param diff --git a/tests/custom/permutations/18_image_matrix/enum/0030_letting_permutation_given_matrix_find_matrix/run.sh b/tests/custom/permutations/18_transform_matrix/enum/0030_letting_permutation_given_matrix_find_matrix/run.sh similarity index 100% rename from tests/custom/permutations/18_image_matrix/enum/0030_letting_permutation_given_matrix_find_matrix/run.sh rename to tests/custom/permutations/18_transform_matrix/enum/0030_letting_permutation_given_matrix_find_matrix/run.sh diff --git a/tests/custom/permutations/18_image_matrix/enum/0030_letting_permutation_given_matrix_find_matrix/stdout.expected b/tests/custom/permutations/18_transform_matrix/enum/0030_letting_permutation_given_matrix_find_matrix/stdout.expected similarity index 100% rename from tests/custom/permutations/18_image_matrix/enum/0030_letting_permutation_given_matrix_find_matrix/stdout.expected rename to tests/custom/permutations/18_transform_matrix/enum/0030_letting_permutation_given_matrix_find_matrix/stdout.expected diff --git a/tests/custom/permutations/18_image_matrix/enum/0040_find_permutation_find_matrices/permutation.essence b/tests/custom/permutations/18_transform_matrix/enum/0040_find_permutation_find_matrices/permutation.essence similarity index 80% rename from tests/custom/permutations/18_image_matrix/enum/0040_find_permutation_find_matrices/permutation.essence rename to tests/custom/permutations/18_transform_matrix/enum/0040_find_permutation_find_matrices/permutation.essence index 74ffe44ee5..2806ade22a 100644 --- a/tests/custom/permutations/18_image_matrix/enum/0040_find_permutation_find_matrices/permutation.essence +++ b/tests/custom/permutations/18_transform_matrix/enum/0040_find_permutation_find_matrices/permutation.essence @@ -5,5 +5,5 @@ find s : matrix indexed by [int(1..4)] of n find t : matrix indexed by [int(1..4)] of n -such that t = image(p,s) /\ allDiff(s) +such that t = transform(p,s) /\ allDiff(s) diff --git a/tests/custom/permutations/18_image_matrix/enum/0040_find_permutation_find_matrices/run.sh b/tests/custom/permutations/18_transform_matrix/enum/0040_find_permutation_find_matrices/run.sh similarity index 100% rename from tests/custom/permutations/18_image_matrix/enum/0040_find_permutation_find_matrices/run.sh rename to tests/custom/permutations/18_transform_matrix/enum/0040_find_permutation_find_matrices/run.sh diff --git a/tests/custom/permutations/18_image_matrix/enum/0040_find_permutation_find_matrices/stdout.expected b/tests/custom/permutations/18_transform_matrix/enum/0040_find_permutation_find_matrices/stdout.expected similarity index 100% rename from tests/custom/permutations/18_image_matrix/enum/0040_find_permutation_find_matrices/stdout.expected rename to tests/custom/permutations/18_transform_matrix/enum/0040_find_permutation_find_matrices/stdout.expected diff --git a/tests/custom/permutations/18_image_matrix/int/0010_find_permutation_indexing_given_matrix/permutation.essence b/tests/custom/permutations/18_transform_matrix/int/0010_find_permutation_indexing_given_matrix/permutation.essence similarity index 76% rename from tests/custom/permutations/18_image_matrix/int/0010_find_permutation_indexing_given_matrix/permutation.essence rename to tests/custom/permutations/18_transform_matrix/int/0010_find_permutation_indexing_given_matrix/permutation.essence index c91bce7e79..20508b3545 100644 --- a/tests/custom/permutations/18_image_matrix/int/0010_find_permutation_indexing_given_matrix/permutation.essence +++ b/tests/custom/permutations/18_transform_matrix/int/0010_find_permutation_indexing_given_matrix/permutation.essence @@ -3,5 +3,5 @@ letting n be 4 find p : permutation of int(1..n) given s : matrix indexed by [int(1..4)] of int(5..8) -such that 8 = image(p,s)[2] +such that 8 = transform(p,s)[2] diff --git a/tests/custom/permutations/18_image_matrix/int/0010_find_permutation_indexing_given_matrix/permutation.param b/tests/custom/permutations/18_transform_matrix/int/0010_find_permutation_indexing_given_matrix/permutation.param similarity index 100% rename from tests/custom/permutations/18_image_matrix/int/0010_find_permutation_indexing_given_matrix/permutation.param rename to tests/custom/permutations/18_transform_matrix/int/0010_find_permutation_indexing_given_matrix/permutation.param diff --git a/tests/custom/permutations/18_image_matrix/int/0010_find_permutation_indexing_given_matrix/run.sh b/tests/custom/permutations/18_transform_matrix/int/0010_find_permutation_indexing_given_matrix/run.sh similarity index 100% rename from tests/custom/permutations/18_image_matrix/int/0010_find_permutation_indexing_given_matrix/run.sh rename to tests/custom/permutations/18_transform_matrix/int/0010_find_permutation_indexing_given_matrix/run.sh diff --git a/tests/custom/permutations/18_image_matrix/int/0010_find_permutation_indexing_given_matrix/stdout.expected b/tests/custom/permutations/18_transform_matrix/int/0010_find_permutation_indexing_given_matrix/stdout.expected similarity index 100% rename from tests/custom/permutations/18_image_matrix/int/0010_find_permutation_indexing_given_matrix/stdout.expected rename to tests/custom/permutations/18_transform_matrix/int/0010_find_permutation_indexing_given_matrix/stdout.expected diff --git a/tests/custom/permutations/18_image_matrix/int/0015_find_permutation_indexing_given_matrix/permutation.essence b/tests/custom/permutations/18_transform_matrix/int/0015_find_permutation_indexing_given_matrix/permutation.essence similarity index 70% rename from tests/custom/permutations/18_image_matrix/int/0015_find_permutation_indexing_given_matrix/permutation.essence rename to tests/custom/permutations/18_transform_matrix/int/0015_find_permutation_indexing_given_matrix/permutation.essence index de2e14a788..95ffb595d0 100644 --- a/tests/custom/permutations/18_image_matrix/int/0015_find_permutation_indexing_given_matrix/permutation.essence +++ b/tests/custom/permutations/18_transform_matrix/int/0015_find_permutation_indexing_given_matrix/permutation.essence @@ -3,5 +3,5 @@ letting n be 4 find p : permutation of int(1..n) letting s be [5,6,7,8] -such that 8 = image(p,s)[2] +such that 8 = transform(p,s)[2] diff --git a/tests/custom/permutations/18_image_matrix/int/0015_find_permutation_indexing_given_matrix/run.sh b/tests/custom/permutations/18_transform_matrix/int/0015_find_permutation_indexing_given_matrix/run.sh similarity index 100% rename from tests/custom/permutations/18_image_matrix/int/0015_find_permutation_indexing_given_matrix/run.sh rename to tests/custom/permutations/18_transform_matrix/int/0015_find_permutation_indexing_given_matrix/run.sh diff --git a/tests/custom/permutations/18_image_matrix/int/0015_find_permutation_indexing_given_matrix/stdout.expected b/tests/custom/permutations/18_transform_matrix/int/0015_find_permutation_indexing_given_matrix/stdout.expected similarity index 100% rename from tests/custom/permutations/18_image_matrix/int/0015_find_permutation_indexing_given_matrix/stdout.expected rename to tests/custom/permutations/18_transform_matrix/int/0015_find_permutation_indexing_given_matrix/stdout.expected diff --git a/tests/custom/permutations/18_image_matrix/int/0020_given_permutation_and_matrix_find_matrix/permutation.essence b/tests/custom/permutations/18_transform_matrix/int/0020_given_permutation_and_matrix_find_matrix/permutation.essence similarity index 84% rename from tests/custom/permutations/18_image_matrix/int/0020_given_permutation_and_matrix_find_matrix/permutation.essence rename to tests/custom/permutations/18_transform_matrix/int/0020_given_permutation_and_matrix_find_matrix/permutation.essence index fcf2b326c7..d716c4f430 100644 --- a/tests/custom/permutations/18_image_matrix/int/0020_given_permutation_and_matrix_find_matrix/permutation.essence +++ b/tests/custom/permutations/18_transform_matrix/int/0020_given_permutation_and_matrix_find_matrix/permutation.essence @@ -5,5 +5,5 @@ given s : matrix indexed by [int(1..4)] of int(5..8) find sn : matrix indexed by [int(1..4)] of int(5..8) -such that sn = image(p,s) +such that sn = transform(p,s) diff --git a/tests/custom/permutations/18_image_matrix/int/0020_given_permutation_and_matrix_find_matrix/permutation.param b/tests/custom/permutations/18_transform_matrix/int/0020_given_permutation_and_matrix_find_matrix/permutation.param similarity index 100% rename from tests/custom/permutations/18_image_matrix/int/0020_given_permutation_and_matrix_find_matrix/permutation.param rename to tests/custom/permutations/18_transform_matrix/int/0020_given_permutation_and_matrix_find_matrix/permutation.param diff --git a/tests/custom/permutations/18_image_matrix/int/0020_given_permutation_and_matrix_find_matrix/run.sh b/tests/custom/permutations/18_transform_matrix/int/0020_given_permutation_and_matrix_find_matrix/run.sh similarity index 100% rename from tests/custom/permutations/18_image_matrix/int/0020_given_permutation_and_matrix_find_matrix/run.sh rename to tests/custom/permutations/18_transform_matrix/int/0020_given_permutation_and_matrix_find_matrix/run.sh diff --git a/tests/custom/permutations/18_image_matrix/int/0020_given_permutation_and_matrix_find_matrix/stdout.expected b/tests/custom/permutations/18_transform_matrix/int/0020_given_permutation_and_matrix_find_matrix/stdout.expected similarity index 100% rename from tests/custom/permutations/18_image_matrix/int/0020_given_permutation_and_matrix_find_matrix/stdout.expected rename to tests/custom/permutations/18_transform_matrix/int/0020_given_permutation_and_matrix_find_matrix/stdout.expected diff --git a/tests/custom/permutations/18_image_matrix/int/0030_letting_permutation_given_matrix_find_matrix/permutation.essence b/tests/custom/permutations/18_transform_matrix/int/0030_letting_permutation_given_matrix_find_matrix/permutation.essence similarity index 84% rename from tests/custom/permutations/18_image_matrix/int/0030_letting_permutation_given_matrix_find_matrix/permutation.essence rename to tests/custom/permutations/18_transform_matrix/int/0030_letting_permutation_given_matrix_find_matrix/permutation.essence index f4b9b4f76f..651988fbae 100644 --- a/tests/custom/permutations/18_image_matrix/int/0030_letting_permutation_given_matrix_find_matrix/permutation.essence +++ b/tests/custom/permutations/18_transform_matrix/int/0030_letting_permutation_given_matrix_find_matrix/permutation.essence @@ -5,5 +5,5 @@ given s : matrix indexed by [int(1..4)] of int(5..8) find sn : matrix indexed by [int(1..4)] of int(5..8) -such that sn = image(p,s) +such that sn = transform(p,s) diff --git a/tests/custom/permutations/18_image_matrix/int/0030_letting_permutation_given_matrix_find_matrix/permutation.param b/tests/custom/permutations/18_transform_matrix/int/0030_letting_permutation_given_matrix_find_matrix/permutation.param similarity index 100% rename from tests/custom/permutations/18_image_matrix/int/0030_letting_permutation_given_matrix_find_matrix/permutation.param rename to tests/custom/permutations/18_transform_matrix/int/0030_letting_permutation_given_matrix_find_matrix/permutation.param diff --git a/tests/custom/permutations/18_image_matrix/int/0030_letting_permutation_given_matrix_find_matrix/run.sh b/tests/custom/permutations/18_transform_matrix/int/0030_letting_permutation_given_matrix_find_matrix/run.sh similarity index 100% rename from tests/custom/permutations/18_image_matrix/int/0030_letting_permutation_given_matrix_find_matrix/run.sh rename to tests/custom/permutations/18_transform_matrix/int/0030_letting_permutation_given_matrix_find_matrix/run.sh diff --git a/tests/custom/permutations/18_image_matrix/int/0030_letting_permutation_given_matrix_find_matrix/stdout.expected b/tests/custom/permutations/18_transform_matrix/int/0030_letting_permutation_given_matrix_find_matrix/stdout.expected similarity index 100% rename from tests/custom/permutations/18_image_matrix/int/0030_letting_permutation_given_matrix_find_matrix/stdout.expected rename to tests/custom/permutations/18_transform_matrix/int/0030_letting_permutation_given_matrix_find_matrix/stdout.expected diff --git a/tests/custom/permutations/13_image_function/runthese.sh b/tests/custom/permutations/18_transform_matrix/runthese.sh similarity index 68% rename from tests/custom/permutations/13_image_function/runthese.sh rename to tests/custom/permutations/18_transform_matrix/runthese.sh index ac3509a9ce..97ae7aac12 100644 --- a/tests/custom/permutations/13_image_function/runthese.sh +++ b/tests/custom/permutations/18_transform_matrix/runthese.sh @@ -1 +1 @@ -stack build --copy-bins --test --test-arguments "-p custom.permutations.13_image_function" +stack build --copy-bins --test --test-arguments "-p custom.permutations.18_transform_matrix" diff --git a/tests/custom/permutations/18_image_matrix/unnamed/0040_find_permutation_find_matrices/permutation.essence b/tests/custom/permutations/18_transform_matrix/unnamed/0040_find_permutation_find_matrices/permutation.essence similarity index 78% rename from tests/custom/permutations/18_image_matrix/unnamed/0040_find_permutation_find_matrices/permutation.essence rename to tests/custom/permutations/18_transform_matrix/unnamed/0040_find_permutation_find_matrices/permutation.essence index 958708e9a7..d2239aa3da 100644 --- a/tests/custom/permutations/18_image_matrix/unnamed/0040_find_permutation_find_matrices/permutation.essence +++ b/tests/custom/permutations/18_transform_matrix/unnamed/0040_find_permutation_find_matrices/permutation.essence @@ -5,5 +5,5 @@ find s : matrix indexed by [int(1..4)] of n find t : matrix indexed by [int(1..4)] of n -such that t = image(p,s) /\ allDiff(s) +such that t = transform(p,s) /\ allDiff(s) diff --git a/tests/custom/permutations/18_image_matrix/unnamed/0040_find_permutation_find_matrices/run.sh b/tests/custom/permutations/18_transform_matrix/unnamed/0040_find_permutation_find_matrices/run.sh similarity index 100% rename from tests/custom/permutations/18_image_matrix/unnamed/0040_find_permutation_find_matrices/run.sh rename to tests/custom/permutations/18_transform_matrix/unnamed/0040_find_permutation_find_matrices/run.sh diff --git a/tests/custom/permutations/18_image_matrix/unnamed/0040_find_permutation_find_matrices/stdout.expected b/tests/custom/permutations/18_transform_matrix/unnamed/0040_find_permutation_find_matrices/stdout.expected similarity index 100% rename from tests/custom/permutations/18_image_matrix/unnamed/0040_find_permutation_find_matrices/stdout.expected rename to tests/custom/permutations/18_transform_matrix/unnamed/0040_find_permutation_find_matrices/stdout.expected From 41f77599ed7e4b57a1966c2ca854039a88e70abf Mon Sep 17 00:00:00 2001 From: Fraser Dunlop Date: Mon, 14 Oct 2019 10:23:27 +0100 Subject: [PATCH 107/229] fixed some permutation tests --- .../0010_set_of_tuples/permutation.essence | 2 +- .../0010_set_of_tuples/stdout.expected | 2 ++ .../stdout.expected | 2 ++ .../stdout.expected | 2 ++ .../0010_size_3/permutation.essence | 2 +- .../0010_size_3/stdout.expected | 18 +++++----- .../0020_size_3/permutation.essence | 2 +- .../0020_size_3/stderr.expected | 35 ------------------- .../0020_size_3/stdout.expected | 9 +++++ .../22_tagged_ints/accept_these.sh | 25 +++++++++++++ .../0001_permute_untagged/permutation.essence | 2 +- .../int/0001_permute_untagged/stdout.expected | 2 ++ .../0002_permute_tagged/permutation.essence | 2 +- .../int/0002_permute_tagged/stdout.expected | 2 ++ .../permutation.essence | 2 +- .../0003_tagged_lits_in_param/stdout.expected | 2 ++ .../div/0001_same_tags_works/stdout.expected | 2 ++ .../0003_const_tagged_works/stdout.expected | 2 ++ .../0003_const_tagged_works/stdout.expected | 2 ++ .../0003_const_tagged_works/stdout.expected | 2 ++ .../0003_const_tagged_works/stdout.expected | 2 ++ .../0003_const_tagged_works/stdout.expected | 2 ++ .../max/0001_same_tags_work/stdout.expected | 2 ++ .../0003_const_tagged_works/stdout.expected | 2 ++ .../min/0001_same_tags_work/stdout.expected | 2 ++ .../0003_const_tagged_works/stdout.expected | 2 ++ .../0001_same_tags_works/stdout.expected | 2 ++ .../0003_const_tagged_works/stdout.expected | 2 ++ .../mod/0001_same_tags_works/stdout.expected | 2 ++ .../0003_const_tagged_works/stdout.expected | 2 ++ .../neg/0001_same_tags_works/stdout.expected | 2 ++ .../0003_const_tagged_works/stdout.expected | 2 ++ .../0003_const_tagged_works/stdout.expected | 2 ++ .../prod/0001_same_tags_works/stdout.expected | 2 ++ .../0003_const_tagged_works/stdout.expected | 2 ++ .../0003_const_tagged_works/stdout.expected | 2 ++ .../sum/0001_same_tags_works/stdout.expected | 2 ++ .../0003_const_tagged_works/stdout.expected | 2 ++ .../permutation.essence | 2 +- .../permutation.essence | 2 +- .../0010_find_perm_find_set/stdout.expected | 2 ++ 41 files changed, 110 insertions(+), 51 deletions(-) delete mode 100644 tests/custom/permutations/21_superpermutations/0020_size_3/stderr.expected create mode 100644 tests/custom/permutations/22_tagged_ints/accept_these.sh diff --git a/tests/custom/permutations/19_complications/multiple_enums/0010_set_of_tuples/permutation.essence b/tests/custom/permutations/19_complications/multiple_enums/0010_set_of_tuples/permutation.essence index 1dd7a44872..0d85a6ad7a 100644 --- a/tests/custom/permutations/19_complications/multiple_enums/0010_set_of_tuples/permutation.essence +++ b/tests/custom/permutations/19_complications/multiple_enums/0010_set_of_tuples/permutation.essence @@ -6,5 +6,5 @@ letting s be {(e_1,n_3),(e_2,n_4)} find t : set of (e,n) -such that t = image(p,s) +such that t = transform(p,s) diff --git a/tests/custom/permutations/19_complications/multiple_enums/0010_set_of_tuples/stdout.expected b/tests/custom/permutations/19_complications/multiple_enums/0010_set_of_tuples/stdout.expected index d35fec6a2a..81c53ebfd0 100644 --- a/tests/custom/permutations/19_complications/multiple_enums/0010_set_of_tuples/stdout.expected +++ b/tests/custom/permutations/19_complications/multiple_enums/0010_set_of_tuples/stdout.expected @@ -2,6 +2,8 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output Savile Row: model000001.eprime +Running minion for domain filtering. +Running solver: minion Copying solution to: permutation.solution language Essence 1.3 diff --git a/tests/custom/permutations/20_counting/0010_set_of_permutations_size_3/stdout.expected b/tests/custom/permutations/20_counting/0010_set_of_permutations_size_3/stdout.expected index 3b1723c783..eedac71a60 100644 --- a/tests/custom/permutations/20_counting/0010_set_of_permutations_size_3/stdout.expected +++ b/tests/custom/permutations/20_counting/0010_set_of_permutations_size_3/stdout.expected @@ -2,6 +2,8 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output Savile Row: model000001.eprime +Running minion for domain filtering. +Running solver: minion Copying solution to: permutation.solution language Essence 1.3 diff --git a/tests/custom/permutations/20_counting/0020_set_of_permutations_size_4/stdout.expected b/tests/custom/permutations/20_counting/0020_set_of_permutations_size_4/stdout.expected index 6faf256466..212b20776e 100644 --- a/tests/custom/permutations/20_counting/0020_set_of_permutations_size_4/stdout.expected +++ b/tests/custom/permutations/20_counting/0020_set_of_permutations_size_4/stdout.expected @@ -2,6 +2,8 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output Savile Row: model000001.eprime +Running minion for domain filtering. +Running solver: minion Copying solution to: permutation.solution language Essence 1.3 diff --git a/tests/custom/permutations/21_superpermutations/0010_size_3/permutation.essence b/tests/custom/permutations/21_superpermutations/0010_size_3/permutation.essence index 7aecd27844..7a27b0e9e7 100644 --- a/tests/custom/permutations/21_superpermutations/0010_size_3/permutation.essence +++ b/tests/custom/permutations/21_superpermutations/0010_size_3/permutation.essence @@ -2,7 +2,7 @@ given s : set of permutation of int(1..3) given q : sequence (size 3) of int(1..3) find qs : set of sequence (size 3) of int(1..3) -such that |qs| = |s| /\ and([ image(p,q) in qs | p <- s]) +such that |qs| = |s| /\ and([ transform(p,q) in qs | p <- s]) find superperm : sequence (maxSize 100) of int(1..3) diff --git a/tests/custom/permutations/21_superpermutations/0010_size_3/stdout.expected b/tests/custom/permutations/21_superpermutations/0010_size_3/stdout.expected index 9d8a5471bf..3d1ad910f5 100644 --- a/tests/custom/permutations/21_superpermutations/0010_size_3/stdout.expected +++ b/tests/custom/permutations/21_superpermutations/0010_size_3/stdout.expected @@ -2,18 +2,20 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output Savile Row: model000001.eprime permutation.param +Running minion for domain filtering. +Running solver: minion Copying solution to: permutation-permutation.solution language Essence 1.3 letting qs be - {sequence(1, 2, 3), sequence(1, 3, 2), sequence(2, 1, 3), sequence(2, 3, 1), sequence(3, 1, 2), - sequence(3, 2, 1)} + {sequence(1, 1, 1), sequence(1, 1, 2), sequence(1, 1, 3), sequence(1, 2, 3), sequence(1, 3, 1), + sequence(3, 1, 1)} $ Visualisation for qs +$ 1 1 1 +$ 1 1 2 +$ 1 1 3 $ 1 2 3 -$ 1 3 2 -$ 2 1 3 -$ 2 3 1 -$ 3 1 2 -$ 3 2 1 +$ 1 3 1 +$ 3 1 1 -letting superperm be sequence(1, 2, 3, 1, 2, 1, 3, 2, 1) +letting superperm be sequence(1, 1, 1, 3, 1, 1, 2, 3) diff --git a/tests/custom/permutations/21_superpermutations/0020_size_3/permutation.essence b/tests/custom/permutations/21_superpermutations/0020_size_3/permutation.essence index c08d28953f..c758655ecc 100644 --- a/tests/custom/permutations/21_superpermutations/0020_size_3/permutation.essence +++ b/tests/custom/permutations/21_superpermutations/0020_size_3/permutation.essence @@ -2,7 +2,7 @@ given s : set of permutation of int(1..3) find superperm : sequence (maxSize 100) of int(1..3) such that - and([ image(z,sequence(1,2,3)) substring superperm | z <- s ]) + and([ transform(z,sequence(1,2,3)) substring superperm | z <- s ]) minimising |superperm| diff --git a/tests/custom/permutations/21_superpermutations/0020_size_3/stderr.expected b/tests/custom/permutations/21_superpermutations/0020_size_3/stderr.expected deleted file mode 100644 index 50dc7cdffd..0000000000 --- a/tests/custom/permutations/21_superpermutations/0020_size_3/stderr.expected +++ /dev/null @@ -1,35 +0,0 @@ -conjure: This should never happen, sorry! - -However, it did happen, so it must be a bug. Please report it to us! - -Conjure is actively maintained, we will get back to you as soon as possible. -You can help us by providing a minimal failing example. - -Also include the repository version for this build: 3471a2936 (2019-05-08 11:52:07 +0100) - -Issue tracker: http://github.com/conjure-cp/conjure/issues - - - -Not refined: s_ExplicitR20 -Domain : matrix indexed by [int(1..fin1)] of permutation {PermutationAsFunction} of int(1..3) - Context #1: s_ExplicitR20[q3] - Context #2: image(s_ExplicitR20[q3], sequence(1, 2, 3)) - Context #3: image(s_ExplicitR20[q3], sequence(1, 2, 3)) substring superperm - Context #4: [image(s_ExplicitR20[q3], sequence(1, 2, 3)) substring superperm | q3 : int(1..fin1)] - Context #5: and([image(s_ExplicitR20[q3], sequence(1, 2, 3)) substring superperm | q3 : int(1..fin1)]) -Not refined: sequence(1, 2, 3) - Context #1: image(s_ExplicitR20[q3], sequence(1, 2, 3)) - Context #2: image(s_ExplicitR20[q3], sequence(1, 2, 3)) substring superperm - Context #3: [image(s_ExplicitR20[q3], sequence(1, 2, 3)) substring superperm | q3 : int(1..fin1)] - Context #4: and([image(s_ExplicitR20[q3], sequence(1, 2, 3)) substring superperm | q3 : int(1..fin1)]) -Not refined: superperm -Domain : sequence {ExplicitBounded} (maxSize 100) of int(1..3) - Context #1: image(s_ExplicitR20[q3], sequence(1, 2, 3)) substring superperm - Context #2: [image(s_ExplicitR20[q3], sequence(1, 2, 3)) substring superperm | q3 : int(1..fin1)] - Context #3: and([image(s_ExplicitR20[q3], sequence(1, 2, 3)) substring superperm | q3 : int(1..fin1)]) - -CallStack (from HasCallStack): - error, called at src/Conjure/Bug.hs:21:15 in conjure-cp-2.2.0-71NFmy1yFuTKzqIQD5mEC7:Conjure.Bug - bug, called at src/Conjure/UI/Model.hs:936:26 in conjure-cp-2.2.0-71NFmy1yFuTKzqIQD5mEC7:Conjure.UI.Model -cat: conjure-output/*.solution: No such file or directory diff --git a/tests/custom/permutations/21_superpermutations/0020_size_3/stdout.expected b/tests/custom/permutations/21_superpermutations/0020_size_3/stdout.expected index d10ebe7b59..78e7a506c7 100644 --- a/tests/custom/permutations/21_superpermutations/0020_size_3/stdout.expected +++ b/tests/custom/permutations/21_superpermutations/0020_size_3/stdout.expected @@ -1 +1,10 @@ Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime permutation.param +Running minion for domain filtering. +Running solver: minion +Copying solution to: permutation-permutation.solution +language Essence 1.3 + +letting superperm be sequence(1, 2, 3, 1, 2, 1, 3, 2, 1) diff --git a/tests/custom/permutations/22_tagged_ints/accept_these.sh b/tests/custom/permutations/22_tagged_ints/accept_these.sh new file mode 100644 index 0000000000..3de55fa726 --- /dev/null +++ b/tests/custom/permutations/22_tagged_ints/accept_these.sh @@ -0,0 +1,25 @@ +sh ../../acceptOutput.sh int/prod/0001_same_tags_works +sh ../../acceptOutput.sh int/prod/0003_const_tagged_works +sh ../../acceptOutput.sh int/pred/0003_const_tagged_works +sh ../../acceptOutput.sh int/div/0001_same_tags_works +sh ../../acceptOutput.sh int/div/0003_const_tagged_works +sh ../../acceptOutput.sh int/succ/0003_const_tagged_works +sh ../../acceptOutput.sh int/minus/0001_same_tags_works +sh ../../acceptOutput.sh int/minus/0003_const_tagged_works +sh ../../acceptOutput.sh int/leq/0003_const_tagged_works +sh ../../acceptOutput.sh int/neg/0001_same_tags_works +sh ../../acceptOutput.sh int/neg/0003_const_tagged_works +sh ../../acceptOutput.sh int/factorial/0003_const_tagged_works +sh ../../acceptOutput.sh int/0002_permute_tagged +sh ../../acceptOutput.sh int/max/0003_const_tagged_works +sh ../../acceptOutput.sh int/max/0001_same_tags_work +sh ../../acceptOutput.sh int/sum/0001_same_tags_works +sh ../../acceptOutput.sh int/sum/0003_const_tagged_works +sh ../../acceptOutput.sh int/lt/0003_const_tagged_works +sh ../../acceptOutput.sh int/0003_tagged_lits_in_param +sh ../../acceptOutput.sh int/0001_permute_untagged +sh ../../acceptOutput.sh int/min/0003_const_tagged_works +sh ../../acceptOutput.sh int/min/0001_same_tags_work +sh ../../acceptOutput.sh int/mod/0001_same_tags_works +sh ../../acceptOutput.sh int/mod/0003_const_tagged_works +sh ../../acceptOutput.sh int/geq/0003_const_tagged_works diff --git a/tests/custom/permutations/22_tagged_ints/int/0001_permute_untagged/permutation.essence b/tests/custom/permutations/22_tagged_ints/int/0001_permute_untagged/permutation.essence index 1ce852f79e..1f152d58d5 100644 --- a/tests/custom/permutations/22_tagged_ints/int/0001_permute_untagged/permutation.essence +++ b/tests/custom/permutations/22_tagged_ints/int/0001_permute_untagged/permutation.essence @@ -1,5 +1,5 @@ find t : (int:A(1..6), int(1..6)) find x : (int:A(1..6), int(1..6)) -such that x = image(permutation((1,2,3,4,5,6)),t) +such that x = transform(permutation((1,2,3,4,5,6)),t) diff --git a/tests/custom/permutations/22_tagged_ints/int/0001_permute_untagged/stdout.expected b/tests/custom/permutations/22_tagged_ints/int/0001_permute_untagged/stdout.expected index d8e77ec23e..c40fe7c84e 100644 --- a/tests/custom/permutations/22_tagged_ints/int/0001_permute_untagged/stdout.expected +++ b/tests/custom/permutations/22_tagged_ints/int/0001_permute_untagged/stdout.expected @@ -2,6 +2,8 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output Savile Row: model000001.eprime +Running minion for domain filtering. +Running solver: minion Copying solution to: permutation.solution language Essence 1.3 diff --git a/tests/custom/permutations/22_tagged_ints/int/0002_permute_tagged/permutation.essence b/tests/custom/permutations/22_tagged_ints/int/0002_permute_tagged/permutation.essence index 86b76d4f2d..1b9c3cadf6 100644 --- a/tests/custom/permutations/22_tagged_ints/int/0002_permute_tagged/permutation.essence +++ b/tests/custom/permutations/22_tagged_ints/int/0002_permute_tagged/permutation.essence @@ -1,5 +1,5 @@ find t : (int:A(1..6), int(1..6)) find x : (int:A(1..6), int(1..6)) -such that x = image(permutation((1:A,2:A,3:A,4:A,5:A,6:A)),t) +such that x = transform(permutation((1:A,2:A,3:A,4:A,5:A,6:A)),t) diff --git a/tests/custom/permutations/22_tagged_ints/int/0002_permute_tagged/stdout.expected b/tests/custom/permutations/22_tagged_ints/int/0002_permute_tagged/stdout.expected index 4aa68baef7..2073bb1d22 100644 --- a/tests/custom/permutations/22_tagged_ints/int/0002_permute_tagged/stdout.expected +++ b/tests/custom/permutations/22_tagged_ints/int/0002_permute_tagged/stdout.expected @@ -2,6 +2,8 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output Savile Row: model000001.eprime +Running minion for domain filtering. +Running solver: minion Copying solution to: permutation.solution language Essence 1.3 diff --git a/tests/custom/permutations/22_tagged_ints/int/0003_tagged_lits_in_param/permutation.essence b/tests/custom/permutations/22_tagged_ints/int/0003_tagged_lits_in_param/permutation.essence index 6910c5ae6a..a45cda7741 100644 --- a/tests/custom/permutations/22_tagged_ints/int/0003_tagged_lits_in_param/permutation.essence +++ b/tests/custom/permutations/22_tagged_ints/int/0003_tagged_lits_in_param/permutation.essence @@ -1,6 +1,6 @@ find t : (int:A(1..6), int(1..6)) find x : (int:A(1..6), int(1..6)) given p : permutation of int:A(1..6) -such that x = image(p,t) +such that x = transform(p,t) diff --git a/tests/custom/permutations/22_tagged_ints/int/0003_tagged_lits_in_param/stdout.expected b/tests/custom/permutations/22_tagged_ints/int/0003_tagged_lits_in_param/stdout.expected index b4bc08fe98..b40e0f6a2a 100644 --- a/tests/custom/permutations/22_tagged_ints/int/0003_tagged_lits_in_param/stdout.expected +++ b/tests/custom/permutations/22_tagged_ints/int/0003_tagged_lits_in_param/stdout.expected @@ -2,6 +2,8 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output Savile Row: model000001.eprime permutation.param +Running minion for domain filtering. +Running solver: minion Copying solution to: permutation-permutation.solution language Essence 1.3 diff --git a/tests/custom/permutations/22_tagged_ints/int/div/0001_same_tags_works/stdout.expected b/tests/custom/permutations/22_tagged_ints/int/div/0001_same_tags_works/stdout.expected index 4805b4c772..3699f5924f 100644 --- a/tests/custom/permutations/22_tagged_ints/int/div/0001_same_tags_works/stdout.expected +++ b/tests/custom/permutations/22_tagged_ints/int/div/0001_same_tags_works/stdout.expected @@ -2,6 +2,8 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output Savile Row: model000001.eprime +Running minion for domain filtering. +Running solver: minion Copying solution to: permutation.solution language Essence 1.3 diff --git a/tests/custom/permutations/22_tagged_ints/int/div/0003_const_tagged_works/stdout.expected b/tests/custom/permutations/22_tagged_ints/int/div/0003_const_tagged_works/stdout.expected index ce08534589..efeeb71a08 100644 --- a/tests/custom/permutations/22_tagged_ints/int/div/0003_const_tagged_works/stdout.expected +++ b/tests/custom/permutations/22_tagged_ints/int/div/0003_const_tagged_works/stdout.expected @@ -2,6 +2,8 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output Savile Row: model000001.eprime +Running minion for domain filtering. +Running solver: minion Copying solution to: permutation.solution language Essence 1.3 diff --git a/tests/custom/permutations/22_tagged_ints/int/factorial/0003_const_tagged_works/stdout.expected b/tests/custom/permutations/22_tagged_ints/int/factorial/0003_const_tagged_works/stdout.expected index 79e05ead18..53d1ddf9b0 100644 --- a/tests/custom/permutations/22_tagged_ints/int/factorial/0003_const_tagged_works/stdout.expected +++ b/tests/custom/permutations/22_tagged_ints/int/factorial/0003_const_tagged_works/stdout.expected @@ -2,6 +2,8 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output Savile Row: model000001.eprime +Running minion for domain filtering. +Running solver: minion Copying solution to: permutation.solution language Essence 1.3 diff --git a/tests/custom/permutations/22_tagged_ints/int/geq/0003_const_tagged_works/stdout.expected b/tests/custom/permutations/22_tagged_ints/int/geq/0003_const_tagged_works/stdout.expected index 25665ca6ca..72487280db 100644 --- a/tests/custom/permutations/22_tagged_ints/int/geq/0003_const_tagged_works/stdout.expected +++ b/tests/custom/permutations/22_tagged_ints/int/geq/0003_const_tagged_works/stdout.expected @@ -2,6 +2,8 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output Savile Row: model000001.eprime +Running minion for domain filtering. +Running solver: minion Copying solution to: permutation.solution language Essence 1.3 diff --git a/tests/custom/permutations/22_tagged_ints/int/leq/0003_const_tagged_works/stdout.expected b/tests/custom/permutations/22_tagged_ints/int/leq/0003_const_tagged_works/stdout.expected index 25665ca6ca..72487280db 100644 --- a/tests/custom/permutations/22_tagged_ints/int/leq/0003_const_tagged_works/stdout.expected +++ b/tests/custom/permutations/22_tagged_ints/int/leq/0003_const_tagged_works/stdout.expected @@ -2,6 +2,8 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output Savile Row: model000001.eprime +Running minion for domain filtering. +Running solver: minion Copying solution to: permutation.solution language Essence 1.3 diff --git a/tests/custom/permutations/22_tagged_ints/int/lt/0003_const_tagged_works/stdout.expected b/tests/custom/permutations/22_tagged_ints/int/lt/0003_const_tagged_works/stdout.expected index b241021976..b6829caf1f 100644 --- a/tests/custom/permutations/22_tagged_ints/int/lt/0003_const_tagged_works/stdout.expected +++ b/tests/custom/permutations/22_tagged_ints/int/lt/0003_const_tagged_works/stdout.expected @@ -2,6 +2,8 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output Savile Row: model000001.eprime +Running minion for domain filtering. +Running solver: minion Copying solution to: permutation.solution language Essence 1.3 diff --git a/tests/custom/permutations/22_tagged_ints/int/max/0001_same_tags_work/stdout.expected b/tests/custom/permutations/22_tagged_ints/int/max/0001_same_tags_work/stdout.expected index bf44838b4f..52afb68fe6 100644 --- a/tests/custom/permutations/22_tagged_ints/int/max/0001_same_tags_work/stdout.expected +++ b/tests/custom/permutations/22_tagged_ints/int/max/0001_same_tags_work/stdout.expected @@ -2,6 +2,8 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output Savile Row: model000001.eprime +Running minion for domain filtering. +Running solver: minion Copying solution to: permutation.solution language Essence 1.3 diff --git a/tests/custom/permutations/22_tagged_ints/int/max/0003_const_tagged_works/stdout.expected b/tests/custom/permutations/22_tagged_ints/int/max/0003_const_tagged_works/stdout.expected index df7b739bcd..a3c1446354 100644 --- a/tests/custom/permutations/22_tagged_ints/int/max/0003_const_tagged_works/stdout.expected +++ b/tests/custom/permutations/22_tagged_ints/int/max/0003_const_tagged_works/stdout.expected @@ -2,6 +2,8 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output Savile Row: model000001.eprime +Running minion for domain filtering. +Running solver: minion Copying solution to: permutation.solution language Essence 1.3 diff --git a/tests/custom/permutations/22_tagged_ints/int/min/0001_same_tags_work/stdout.expected b/tests/custom/permutations/22_tagged_ints/int/min/0001_same_tags_work/stdout.expected index bf44838b4f..52afb68fe6 100644 --- a/tests/custom/permutations/22_tagged_ints/int/min/0001_same_tags_work/stdout.expected +++ b/tests/custom/permutations/22_tagged_ints/int/min/0001_same_tags_work/stdout.expected @@ -2,6 +2,8 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output Savile Row: model000001.eprime +Running minion for domain filtering. +Running solver: minion Copying solution to: permutation.solution language Essence 1.3 diff --git a/tests/custom/permutations/22_tagged_ints/int/min/0003_const_tagged_works/stdout.expected b/tests/custom/permutations/22_tagged_ints/int/min/0003_const_tagged_works/stdout.expected index df7b739bcd..a3c1446354 100644 --- a/tests/custom/permutations/22_tagged_ints/int/min/0003_const_tagged_works/stdout.expected +++ b/tests/custom/permutations/22_tagged_ints/int/min/0003_const_tagged_works/stdout.expected @@ -2,6 +2,8 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output Savile Row: model000001.eprime +Running minion for domain filtering. +Running solver: minion Copying solution to: permutation.solution language Essence 1.3 diff --git a/tests/custom/permutations/22_tagged_ints/int/minus/0001_same_tags_works/stdout.expected b/tests/custom/permutations/22_tagged_ints/int/minus/0001_same_tags_works/stdout.expected index 592ae071db..da8f18aa8e 100644 --- a/tests/custom/permutations/22_tagged_ints/int/minus/0001_same_tags_works/stdout.expected +++ b/tests/custom/permutations/22_tagged_ints/int/minus/0001_same_tags_works/stdout.expected @@ -2,6 +2,8 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output Savile Row: model000001.eprime +Running minion for domain filtering. +Running solver: minion Copying solution to: permutation.solution language Essence 1.3 diff --git a/tests/custom/permutations/22_tagged_ints/int/minus/0003_const_tagged_works/stdout.expected b/tests/custom/permutations/22_tagged_ints/int/minus/0003_const_tagged_works/stdout.expected index ce08534589..efeeb71a08 100644 --- a/tests/custom/permutations/22_tagged_ints/int/minus/0003_const_tagged_works/stdout.expected +++ b/tests/custom/permutations/22_tagged_ints/int/minus/0003_const_tagged_works/stdout.expected @@ -2,6 +2,8 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output Savile Row: model000001.eprime +Running minion for domain filtering. +Running solver: minion Copying solution to: permutation.solution language Essence 1.3 diff --git a/tests/custom/permutations/22_tagged_ints/int/mod/0001_same_tags_works/stdout.expected b/tests/custom/permutations/22_tagged_ints/int/mod/0001_same_tags_works/stdout.expected index bbc23f8d00..6f7ccdf470 100644 --- a/tests/custom/permutations/22_tagged_ints/int/mod/0001_same_tags_works/stdout.expected +++ b/tests/custom/permutations/22_tagged_ints/int/mod/0001_same_tags_works/stdout.expected @@ -2,6 +2,8 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output Savile Row: model000001.eprime +Running minion for domain filtering. +Running solver: minion Copying solution to: permutation.solution language Essence 1.3 diff --git a/tests/custom/permutations/22_tagged_ints/int/mod/0003_const_tagged_works/stdout.expected b/tests/custom/permutations/22_tagged_ints/int/mod/0003_const_tagged_works/stdout.expected index ce08534589..efeeb71a08 100644 --- a/tests/custom/permutations/22_tagged_ints/int/mod/0003_const_tagged_works/stdout.expected +++ b/tests/custom/permutations/22_tagged_ints/int/mod/0003_const_tagged_works/stdout.expected @@ -2,6 +2,8 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output Savile Row: model000001.eprime +Running minion for domain filtering. +Running solver: minion Copying solution to: permutation.solution language Essence 1.3 diff --git a/tests/custom/permutations/22_tagged_ints/int/neg/0001_same_tags_works/stdout.expected b/tests/custom/permutations/22_tagged_ints/int/neg/0001_same_tags_works/stdout.expected index 2239389f44..97a4627bd0 100644 --- a/tests/custom/permutations/22_tagged_ints/int/neg/0001_same_tags_works/stdout.expected +++ b/tests/custom/permutations/22_tagged_ints/int/neg/0001_same_tags_works/stdout.expected @@ -2,6 +2,8 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output Savile Row: model000001.eprime +Running minion for domain filtering. +Running solver: minion Copying solution to: permutation.solution language Essence 1.3 diff --git a/tests/custom/permutations/22_tagged_ints/int/neg/0003_const_tagged_works/stdout.expected b/tests/custom/permutations/22_tagged_ints/int/neg/0003_const_tagged_works/stdout.expected index 3484829aca..20c939f655 100644 --- a/tests/custom/permutations/22_tagged_ints/int/neg/0003_const_tagged_works/stdout.expected +++ b/tests/custom/permutations/22_tagged_ints/int/neg/0003_const_tagged_works/stdout.expected @@ -2,6 +2,8 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output Savile Row: model000001.eprime +Running minion for domain filtering. +Running solver: minion Copying solution to: permutation.solution language Essence 1.3 diff --git a/tests/custom/permutations/22_tagged_ints/int/pred/0003_const_tagged_works/stdout.expected b/tests/custom/permutations/22_tagged_ints/int/pred/0003_const_tagged_works/stdout.expected index b241021976..b6829caf1f 100644 --- a/tests/custom/permutations/22_tagged_ints/int/pred/0003_const_tagged_works/stdout.expected +++ b/tests/custom/permutations/22_tagged_ints/int/pred/0003_const_tagged_works/stdout.expected @@ -2,6 +2,8 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output Savile Row: model000001.eprime +Running minion for domain filtering. +Running solver: minion Copying solution to: permutation.solution language Essence 1.3 diff --git a/tests/custom/permutations/22_tagged_ints/int/prod/0001_same_tags_works/stdout.expected b/tests/custom/permutations/22_tagged_ints/int/prod/0001_same_tags_works/stdout.expected index eee4b0542b..9b47e4135d 100644 --- a/tests/custom/permutations/22_tagged_ints/int/prod/0001_same_tags_works/stdout.expected +++ b/tests/custom/permutations/22_tagged_ints/int/prod/0001_same_tags_works/stdout.expected @@ -2,6 +2,8 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output Savile Row: model000001.eprime +Running minion for domain filtering. +Running solver: minion Copying solution to: permutation.solution language Essence 1.3 diff --git a/tests/custom/permutations/22_tagged_ints/int/prod/0003_const_tagged_works/stdout.expected b/tests/custom/permutations/22_tagged_ints/int/prod/0003_const_tagged_works/stdout.expected index 79e05ead18..53d1ddf9b0 100644 --- a/tests/custom/permutations/22_tagged_ints/int/prod/0003_const_tagged_works/stdout.expected +++ b/tests/custom/permutations/22_tagged_ints/int/prod/0003_const_tagged_works/stdout.expected @@ -2,6 +2,8 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output Savile Row: model000001.eprime +Running minion for domain filtering. +Running solver: minion Copying solution to: permutation.solution language Essence 1.3 diff --git a/tests/custom/permutations/22_tagged_ints/int/succ/0003_const_tagged_works/stdout.expected b/tests/custom/permutations/22_tagged_ints/int/succ/0003_const_tagged_works/stdout.expected index 746139963a..44089a9b87 100644 --- a/tests/custom/permutations/22_tagged_ints/int/succ/0003_const_tagged_works/stdout.expected +++ b/tests/custom/permutations/22_tagged_ints/int/succ/0003_const_tagged_works/stdout.expected @@ -2,6 +2,8 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output Savile Row: model000001.eprime +Running minion for domain filtering. +Running solver: minion Copying solution to: permutation.solution language Essence 1.3 diff --git a/tests/custom/permutations/22_tagged_ints/int/sum/0001_same_tags_works/stdout.expected b/tests/custom/permutations/22_tagged_ints/int/sum/0001_same_tags_works/stdout.expected index 4bdc225570..f5d65a4dec 100644 --- a/tests/custom/permutations/22_tagged_ints/int/sum/0001_same_tags_works/stdout.expected +++ b/tests/custom/permutations/22_tagged_ints/int/sum/0001_same_tags_works/stdout.expected @@ -2,6 +2,8 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output Savile Row: model000001.eprime +Running minion for domain filtering. +Running solver: minion Copying solution to: permutation.solution language Essence 1.3 diff --git a/tests/custom/permutations/22_tagged_ints/int/sum/0003_const_tagged_works/stdout.expected b/tests/custom/permutations/22_tagged_ints/int/sum/0003_const_tagged_works/stdout.expected index 79e05ead18..53d1ddf9b0 100644 --- a/tests/custom/permutations/22_tagged_ints/int/sum/0003_const_tagged_works/stdout.expected +++ b/tests/custom/permutations/22_tagged_ints/int/sum/0003_const_tagged_works/stdout.expected @@ -2,6 +2,8 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output Savile Row: model000001.eprime +Running minion for domain filtering. +Running solver: minion Copying solution to: permutation.solution language Essence 1.3 diff --git a/tests/custom/permutations/23_image_set_dotlt/int/0010_find_perm_find_set/permutation.essence b/tests/custom/permutations/23_image_set_dotlt/int/0010_find_perm_find_set/permutation.essence index 3068703308..5f4f842f08 100644 --- a/tests/custom/permutations/23_image_set_dotlt/int/0010_find_perm_find_set/permutation.essence +++ b/tests/custom/permutations/23_image_set_dotlt/int/0010_find_perm_find_set/permutation.essence @@ -3,5 +3,5 @@ find p : permutation of int(1..4) find s : set of int(1..4) -such that s .< image(p,s) +such that s .< transform(p,s) diff --git a/tests/custom/permutations/24_image_comprehension_dotlt/int/0010_find_perm_find_set/permutation.essence b/tests/custom/permutations/24_image_comprehension_dotlt/int/0010_find_perm_find_set/permutation.essence index 4fbf4f54e5..012b29421b 100644 --- a/tests/custom/permutations/24_image_comprehension_dotlt/int/0010_find_perm_find_set/permutation.essence +++ b/tests/custom/permutations/24_image_comprehension_dotlt/int/0010_find_perm_find_set/permutation.essence @@ -3,5 +3,5 @@ find p : permutation of int(1..4) find s : set of (int(1..4),int(1..4)) such that p(4) != 4 -such that and(image(p,[sj > si | (si,sj) <- s])) +such that and(transform(p,[sj > si | (si,sj) <- s])) diff --git a/tests/custom/permutations/24_image_comprehension_dotlt/int/0010_find_perm_find_set/stdout.expected b/tests/custom/permutations/24_image_comprehension_dotlt/int/0010_find_perm_find_set/stdout.expected index ffa9483c61..5272e4573d 100644 --- a/tests/custom/permutations/24_image_comprehension_dotlt/int/0010_find_perm_find_set/stdout.expected +++ b/tests/custom/permutations/24_image_comprehension_dotlt/int/0010_find_perm_find_set/stdout.expected @@ -2,6 +2,8 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output Savile Row: model000001.eprime +Running minion for domain filtering. +Running solver: minion Copying solution to: permutation-000001.solution Copying solution to: permutation-000002.solution Copying solution to: permutation-000003.solution From 11d49196c696c8d4cb49c32dbbe1f8b8f008236c Mon Sep 17 00:00:00 2001 From: Fraser Dunlop Date: Mon, 14 Oct 2019 14:30:07 +0100 Subject: [PATCH 108/229] removing dead code --- src/Conjure/UI/Model.hs | 79 ----------------------------------------- 1 file changed, 79 deletions(-) diff --git a/src/Conjure/UI/Model.hs b/src/Conjure/UI/Model.hs index 4988efc932..ca3adf11c1 100644 --- a/src/Conjure/UI/Model.hs +++ b/src/Conjure/UI/Model.hs @@ -789,84 +789,6 @@ inlineDecVarLettings model = in model { mStatements = statements } -flattenLex :: MonadFail m - => NameGen m - => (?typeCheckerMode :: TypeCheckerMode) - => Model -> m Model -flattenLex m = do - let - flatten a = do - ta <- typeOf a - case ta of - TypeBool -> return [essence| [-toInt(&a)] |] - TypeInt{} -> return [essence| [&a] |] - TypeList TypeInt{} -> return a - TypeMatrix TypeInt{} TypeInt{} -> return a - _ -> - case a of - AbstractLiteral x -> do - case x of - AbsLitTuple xs -> do - fxs <- sequence (flatten <$> xs) - let flatxs = fromList fxs - return [essence| flatten(&flatxs) |] - AbsLitMatrix _ xs -> do - fxs <- sequence (flatten <$> xs) - let flatxs = fromList fxs - return [essence| flatten(&flatxs) |] - _ -> bug $ "epilogue: flattenLex: isn't defined for this abslit fellow..." - <+> vcat [pretty a, pretty ta, stringToDoc $ show a] - Constant c -> - case c of - ConstantAbstract ca -> - case ca of - AbsLitTuple xs -> do - fxs <- sequence (flatten <$> (Constant <$> xs)) - let flatxs = fromList fxs - return [essence| flatten(&flatxs) |] - AbsLitMatrix _ xs -> do - fxs <- sequence (flatten <$> (Constant <$> xs)) - let flatxs = fromList fxs - return [essence| flatten(&flatxs) |] - _ -> bug $ "epilogue: flattenLex: isn't defined for this fellow..." - <+> vcat [pretty a, pretty ta, stringToDoc $ show a] - TypedConstant tc _ -> flatten (Constant tc) - _ -> bug $ "epilogue: flattenLex: isn't defined for this constant fellow." - <+> vcat [pretty a, pretty ta, stringToDoc $ show a] --- Op op -> do --- case op of --- MkOpIndexing (OpIndexing m i) -> --- bug $ "epilogue: flattenLex: flatten not defined for this indexed fellow." --- <+> vcat [stringToDoc (show a) --- ,"fellow:" <+> stringToDoc (show m) --- ,"index:" <+> stringToDoc (show i)] - Reference nm ex -> - bug $ "epilogue: flattenLex: flatten not defined for this referenced fellow." - <+> vcat [stringToDoc (show a) - ,"reference:" <+> stringToDoc (show nm) - ,"fellow:" <+> stringToDoc (show ex)] - Comprehension body gocs -> do - fbody <- flatten body - let comp = Comprehension fbody gocs --- return [essence| flatten(&comp) |] - return [essence| &comp |] - _ -> bug $ "epilogue: flattenLex: isn't defined for this expression fellow..." - <+> vcat [pretty a, pretty ta, stringToDoc $ show a] - - - flattener [essence| &a (?typeCheckerMode :: TypeCheckerMode) => @@ -1257,7 +1179,6 @@ epilogue :: Model -> m Model epilogue model = return model >>= logDebugIdModel "[epilogue]" - >>= flattenLex >>= logDebugIdModel "[flattenLex]" >>= lexSingletons >>= logDebugIdModel "[lexSingletons]" >>= updateDeclarations >>= logDebugIdModel "[updateDeclarations]" >>= return . inlineDecVarLettings >>= logDebugIdModel "[inlineDecVarLettings]" From ebc32a4a67a023c54f8952e695f6d1154f4118f2 Mon Sep 17 00:00:00 2001 From: Chris Jefferson Date: Mon, 10 Aug 2020 17:28:10 +0100 Subject: [PATCH 109/229] Add EvaluateOp OpTwoBars for Permutation --- src/Conjure/Language/EvaluateOp.hs | 1 + 1 file changed, 1 insertion(+) diff --git a/src/Conjure/Language/EvaluateOp.hs b/src/Conjure/Language/EvaluateOp.hs index 56c5a1851a..2d43b450ff 100644 --- a/src/Conjure/Language/EvaluateOp.hs +++ b/src/Conjure/Language/EvaluateOp.hs @@ -752,6 +752,7 @@ instance EvaluateOp OpTwoBars where (viewConstantSequence -> Just xs) -> return $ ConstantInt TagInt $ genericLength xs (viewConstantRelation -> Just xs) -> return $ ConstantInt TagInt $ genericLength $ sortNub xs (viewConstantPartition -> Just xs) -> return $ ConstantInt TagInt $ genericLength $ sortNub $ concat xs + (viewConstantPermutation -> Just xs) -> return $ ConstantInt TagInt $ genericLength $ sortNub $ concat xs -- cardinality of a domain DomainInConstant (DomainInt _ rs) -> ConstantInt TagInt . genericLength <$> rangesInts rs From 760e70216acec4913bc2242e0a5a314cf1f6886d Mon Sep 17 00:00:00 2001 From: Chris Jefferson Date: Mon, 10 Aug 2020 17:28:29 +0100 Subject: [PATCH 110/229] Make applying permutations more efficient --- src/Conjure/Rules/Horizontal/Permutation.hs | 9 +++------ 1 file changed, 3 insertions(+), 6 deletions(-) diff --git a/src/Conjure/Rules/Horizontal/Permutation.hs b/src/Conjure/Rules/Horizontal/Permutation.hs index 6f4dc7e591..cf080e87bf 100644 --- a/src/Conjure/Rules/Horizontal/Permutation.hs +++ b/src/Conjure/Rules/Horizontal/Permutation.hs @@ -134,20 +134,17 @@ rule_Image_Literal = "permutation-image-literal" `namedRule` theRule where if let ?typeCheckerMode = StronglyTyped in typesUnify [inner, typeI] then do let srtdel = sortBy compare (join elems) - inperm = (\x -> [essence| toInt(&x) + 1 |]) - ((\o -> [essence| or(&o) |]) - ((fromList ((\q -> [essence| &q = &i |]) <$> srtdel)))) indexr = (\x -> [essence| sum(&x) |]) (fromList ((\(n,q) -> [essence| toInt(&q = &i) * &n |]) <$> (zip [1..] srtdel))) - matIdx = mkDomainIntB (fromInt 1) + matIdx = mkDomainIntB (fromInt 0) (fromInt (fromIntegral (length srtdel))) matLit = make matrixLiteral (TypeMatrix (TypeInt TagInt) inner) - matIdx (f <$> srtdel) + matIdx ([ [essence| &i |] ] ++ (f <$> srtdel)) return ( "Horizontal rule for permutation literal application to a single value (image), AsFunction representation" , do - return [essence| [&i, catchUndef(&matLit[&indexr],0)][&inperm] |] + return [essence| &matLit[&indexr] |] ) else fail $ "Permutation applied to a type its inner does not unify with" From ea4c7ca403d7851e07cad728bf3b807a54747eaf Mon Sep 17 00:00:00 2001 From: Chris Jefferson Date: Mon, 10 Aug 2020 17:29:13 +0100 Subject: [PATCH 111/229] Add exhaustive permutation tests - part 1 --- .../basic/perms/01_representation/README.md | 4 ++++ .../model-permutation-solution000001.solution | 2 ++ .../expected/model-permutation.eprime-param | 3 +++ .../expected/model.eprime | 6 ++++++ .../permutation.essence | 9 +++++++++ .../0001_given_permutation_in_param/permutation.param | 1 + .../model-permutation-solution000001.solution | 2 ++ .../expected/model-permutation.eprime-param | 3 +++ .../expected/model.eprime | 6 ++++++ .../permutation.essence | 5 +++++ .../0002_given_permutation_in_param/permutation.param | 1 + .../model-permutation-solution000001.solution | 2 ++ .../expected/model-permutation.eprime-param | 3 +++ .../expected/model.eprime | 6 ++++++ .../permutation.essence | 5 +++++ .../permutation.param | 1 + .../model-permutation-solution000001.solution | 2 ++ .../expected/model-permutation.eprime-param | 3 +++ .../expected/model.eprime | 6 ++++++ .../permutation.essence | 5 +++++ .../permutation.param | 1 + .../expected/model-solution000001.solution | 3 +++ .../expected/model-solution000002.solution | 3 +++ .../expected/model-solution000003.solution | 3 +++ .../expected/model-solution000004.solution | 3 +++ .../expected/model-solution000005.solution | 3 +++ .../expected/model-solution000006.solution | 3 +++ .../expected/model-solution000007.solution | 3 +++ .../expected/model-solution000008.solution | 3 +++ .../expected/model-solution000009.solution | 3 +++ .../expected/model.eprime | 9 +++++++++ .../permutation.essence | 5 +++++ .../expected/model-solution000001.solution | 3 +++ .../expected/model.eprime | 9 +++++++++ .../permutation.essence | 5 +++++ .../expected/model-solution000001.solution | 2 ++ .../expected/model.eprime | 5 +++++ .../permutation.essence | 3 +++ .../expected/model-solution000001.solution | 3 +++ .../expected/model-solution000002.solution | 3 +++ .../expected/model-solution000003.solution | 3 +++ .../expected/model-solution000004.solution | 3 +++ .../expected/model-solution000005.solution | 3 +++ .../expected/model-solution000006.solution | 3 +++ .../expected/model-solution000007.solution | 3 +++ .../expected/model-solution000008.solution | 3 +++ .../expected/model-solution000009.solution | 3 +++ .../expected/model-solution000010.solution | 3 +++ .../expected/model-solution000011.solution | 3 +++ .../expected/model-solution000012.solution | 3 +++ .../expected/model-solution000013.solution | 3 +++ .../expected/model-solution000014.solution | 3 +++ .../expected/model-solution000015.solution | 3 +++ .../expected/model-solution000016.solution | 3 +++ .../expected/model-solution000017.solution | 3 +++ .../expected/model-solution000018.solution | 3 +++ .../expected/model-solution000019.solution | 3 +++ .../expected/model-solution000020.solution | 3 +++ .../expected/model-solution000021.solution | 3 +++ .../expected/model-solution000022.solution | 3 +++ .../expected/model-solution000023.solution | 3 +++ .../expected/model-solution000024.solution | 3 +++ .../expected/model.eprime | 8 ++++++++ .../permutation.essence | 5 +++++ .../expected/model-solution000001.solution | 2 ++ .../expected/model.eprime | 5 +++++ .../permutation.essence | 4 ++++ .../expected/model-solution000001.solution | 3 +++ .../expected/model-solution000002.solution | 3 +++ .../expected/model-solution000003.solution | 3 +++ .../expected/model-solution000004.solution | 3 +++ .../expected/model.eprime | 9 +++++++++ .../permutation.essence | 5 +++++ .../expected/model-solution000001.solution | 3 +++ .../expected/model-solution000002.solution | 3 +++ .../expected/model-solution000003.solution | 3 +++ .../expected/model-solution000004.solution | 3 +++ .../expected/model-solution000005.solution | 3 +++ .../expected/model.eprime | 9 +++++++++ .../permutation.essence | 5 +++++ .../expected/model-solution000001.solution | 3 +++ .../expected/model-solution000002.solution | 3 +++ .../expected/model-solution000003.solution | 3 +++ .../expected/model-solution000004.solution | 3 +++ .../expected/model-solution000005.solution | 3 +++ .../expected/model-solution000006.solution | 3 +++ .../expected/model-solution000007.solution | 3 +++ .../expected/model-solution000008.solution | 3 +++ .../expected/model-solution000009.solution | 3 +++ .../expected/model-solution000010.solution | 3 +++ .../expected/model-solution000011.solution | 3 +++ .../expected/model-solution000012.solution | 3 +++ .../expected/model-solution000013.solution | 3 +++ .../expected/model-solution000014.solution | 3 +++ .../expected/model.eprime | 10 ++++++++++ .../permutation.essence | 5 +++++ .../model-permutation-solution000001.solution | 2 ++ .../expected/model-permutation.eprime-param | 3 +++ .../expected/model.eprime | 6 ++++++ .../permutation.essence | 9 +++++++++ .../0001_given_permutation_in_param/permutation.param | 1 + .../model-permutation-solution000001.solution | 2 ++ .../expected/model-permutation.eprime-param | 3 +++ .../expected/model.eprime | 6 ++++++ .../permutation.essence | 5 +++++ .../0002_given_permutation_in_param/permutation.param | 1 + .../model-permutation-solution000001.solution | 2 ++ .../expected/model-permutation.eprime-param | 3 +++ .../expected/model.eprime | 6 ++++++ .../permutation.essence | 5 +++++ .../permutation.param | 1 + .../model-permutation-solution000001.solution | 2 ++ .../expected/model-permutation.eprime-param | 3 +++ .../expected/model.eprime | 6 ++++++ .../permutation.essence | 5 +++++ .../permutation.param | 1 + .../expected/model-solution000001.solution | 3 +++ .../expected/model-solution000002.solution | 3 +++ .../expected/model-solution000003.solution | 3 +++ .../expected/model-solution000004.solution | 3 +++ .../expected/model-solution000005.solution | 3 +++ .../expected/model-solution000006.solution | 3 +++ .../expected/model-solution000007.solution | 3 +++ .../expected/model-solution000008.solution | 3 +++ .../expected/model-solution000009.solution | 3 +++ .../expected/model.eprime | 10 ++++++++++ .../permutation.essence | 5 +++++ .../expected/model-solution000001.solution | 3 +++ .../expected/model.eprime | 10 ++++++++++ .../permutation.essence | 5 +++++ .../expected/model-solution000001.solution | 2 ++ .../expected/model.eprime | 5 +++++ .../permutation.essence | 3 +++ .../expected/model-solution000001.solution | 3 +++ .../expected/model-solution000002.solution | 3 +++ .../expected/model-solution000003.solution | 3 +++ .../expected/model-solution000004.solution | 3 +++ .../expected/model-solution000005.solution | 3 +++ .../expected/model-solution000006.solution | 3 +++ .../expected/model-solution000007.solution | 3 +++ .../expected/model-solution000008.solution | 3 +++ .../expected/model-solution000009.solution | 3 +++ .../expected/model-solution000010.solution | 3 +++ .../expected/model-solution000011.solution | 3 +++ .../expected/model-solution000012.solution | 3 +++ .../expected/model-solution000013.solution | 3 +++ .../expected/model-solution000014.solution | 3 +++ .../expected/model-solution000015.solution | 3 +++ .../expected/model-solution000016.solution | 3 +++ .../expected/model-solution000017.solution | 3 +++ .../expected/model-solution000018.solution | 3 +++ .../expected/model-solution000019.solution | 3 +++ .../expected/model-solution000020.solution | 3 +++ .../expected/model-solution000021.solution | 3 +++ .../expected/model-solution000022.solution | 3 +++ .../expected/model-solution000023.solution | 3 +++ .../expected/model-solution000024.solution | 3 +++ .../expected/model.eprime | 9 +++++++++ .../permutation.essence | 5 +++++ .../expected/model-solution000001.solution | 2 ++ .../expected/model.eprime | 5 +++++ .../permutation.essence | 3 +++ .../expected/model-solution000001.solution | 3 +++ .../expected/model-solution000002.solution | 3 +++ .../expected/model-solution000003.solution | 3 +++ .../expected/model-solution000004.solution | 3 +++ .../expected/model.eprime | 10 ++++++++++ .../permutation.essence | 5 +++++ .../expected/model-solution000001.solution | 3 +++ .../expected/model-solution000002.solution | 3 +++ .../expected/model-solution000003.solution | 3 +++ .../expected/model-solution000004.solution | 3 +++ .../expected/model-solution000005.solution | 3 +++ .../expected/model.eprime | 10 ++++++++++ .../permutation.essence | 5 +++++ .../expected/model-solution000001.solution | 3 +++ .../expected/model-solution000002.solution | 3 +++ .../expected/model-solution000003.solution | 3 +++ .../expected/model-solution000004.solution | 3 +++ .../expected/model-solution000005.solution | 3 +++ .../expected/model-solution000006.solution | 3 +++ .../expected/model-solution000007.solution | 3 +++ .../expected/model-solution000008.solution | 3 +++ .../expected/model-solution000009.solution | 3 +++ .../expected/model-solution000010.solution | 3 +++ .../expected/model-solution000011.solution | 3 +++ .../expected/model-solution000012.solution | 3 +++ .../expected/model-solution000013.solution | 3 +++ .../expected/model-solution000014.solution | 3 +++ .../expected/model.eprime | 11 +++++++++++ .../permutation.essence | 5 +++++ .../expected/model-solution000001.solution | 4 ++++ .../expected/model-solution000002.solution | 4 ++++ .../expected/model-solution000003.solution | 4 ++++ .../expected/model-solution000004.solution | 4 ++++ .../expected/model-solution000005.solution | 4 ++++ .../expected/model-solution000006.solution | 4 ++++ .../expected/model-solution000007.solution | 4 ++++ .../expected/model-solution000008.solution | 4 ++++ .../expected/model-solution000009.solution | 4 ++++ .../expected/model.eprime | 9 +++++++++ .../permutation.essence | 5 +++++ .../expected/model-solution000001.solution | 4 ++++ .../expected/model.eprime | 9 +++++++++ .../permutation.essence | 5 +++++ .../expected/model-solution000001.solution | 2 ++ .../expected/model.eprime | 5 +++++ .../permutation.essence | 3 +++ .../expected/model-solution000001.solution | 4 ++++ .../expected/model-solution000002.solution | 4 ++++ .../expected/model-solution000003.solution | 4 ++++ .../expected/model-solution000004.solution | 4 ++++ .../expected/model-solution000005.solution | 4 ++++ .../expected/model-solution000006.solution | 4 ++++ .../expected/model-solution000007.solution | 4 ++++ .../expected/model-solution000008.solution | 4 ++++ .../expected/model-solution000009.solution | 4 ++++ .../expected/model-solution000010.solution | 4 ++++ .../expected/model-solution000011.solution | 4 ++++ .../expected/model-solution000012.solution | 4 ++++ .../expected/model-solution000013.solution | 4 ++++ .../expected/model-solution000014.solution | 4 ++++ .../expected/model-solution000015.solution | 4 ++++ .../expected/model-solution000016.solution | 4 ++++ .../expected/model-solution000017.solution | 4 ++++ .../expected/model-solution000018.solution | 4 ++++ .../expected/model-solution000019.solution | 4 ++++ .../expected/model-solution000020.solution | 4 ++++ .../expected/model-solution000021.solution | 4 ++++ .../expected/model-solution000022.solution | 4 ++++ .../expected/model-solution000023.solution | 4 ++++ .../expected/model-solution000024.solution | 4 ++++ .../expected/model.eprime | 8 ++++++++ .../permutation.essence | 5 +++++ .../expected/model-solution000001.solution | 4 ++++ .../expected/model-solution000002.solution | 4 ++++ .../expected/model-solution000003.solution | 4 ++++ .../expected/model-solution000004.solution | 4 ++++ .../expected/model.eprime | 9 +++++++++ .../permutation.essence | 5 +++++ .../expected/model-solution000001.solution | 4 ++++ .../expected/model-solution000002.solution | 4 ++++ .../expected/model-solution000003.solution | 4 ++++ .../expected/model-solution000004.solution | 4 ++++ .../expected/model-solution000005.solution | 4 ++++ .../expected/model.eprime | 9 +++++++++ .../permutation.essence | 5 +++++ .../expected/model-solution000001.solution | 4 ++++ .../expected/model-solution000002.solution | 4 ++++ .../expected/model-solution000003.solution | 4 ++++ .../expected/model-solution000004.solution | 4 ++++ .../expected/model-solution000005.solution | 4 ++++ .../expected/model-solution000006.solution | 4 ++++ .../expected/model-solution000007.solution | 4 ++++ .../expected/model-solution000008.solution | 4 ++++ .../expected/model-solution000009.solution | 4 ++++ .../expected/model-solution000010.solution | 4 ++++ .../expected/model-solution000011.solution | 4 ++++ .../expected/model-solution000012.solution | 4 ++++ .../expected/model-solution000013.solution | 4 ++++ .../expected/model-solution000014.solution | 4 ++++ .../expected/model.eprime | 10 ++++++++++ .../permutation.essence | 5 +++++ 263 files changed, 1027 insertions(+) create mode 100644 tests/exhaustive/basic/perms/01_representation/README.md create mode 100644 tests/exhaustive/basic/perms/01_representation/enum/0001_given_permutation_in_param/expected/model-permutation-solution000001.solution create mode 100644 tests/exhaustive/basic/perms/01_representation/enum/0001_given_permutation_in_param/expected/model-permutation.eprime-param create mode 100644 tests/exhaustive/basic/perms/01_representation/enum/0001_given_permutation_in_param/expected/model.eprime create mode 100644 tests/exhaustive/basic/perms/01_representation/enum/0001_given_permutation_in_param/permutation.essence create mode 100644 tests/exhaustive/basic/perms/01_representation/enum/0001_given_permutation_in_param/permutation.param create mode 100644 tests/exhaustive/basic/perms/01_representation/enum/0002_given_permutation_in_param/expected/model-permutation-solution000001.solution create mode 100644 tests/exhaustive/basic/perms/01_representation/enum/0002_given_permutation_in_param/expected/model-permutation.eprime-param create mode 100644 tests/exhaustive/basic/perms/01_representation/enum/0002_given_permutation_in_param/expected/model.eprime create mode 100644 tests/exhaustive/basic/perms/01_representation/enum/0002_given_permutation_in_param/permutation.essence create mode 100644 tests/exhaustive/basic/perms/01_representation/enum/0002_given_permutation_in_param/permutation.param create mode 100644 tests/exhaustive/basic/perms/01_representation/enum/0003_given_permutation_in_param_2_cycle/expected/model-permutation-solution000001.solution create mode 100644 tests/exhaustive/basic/perms/01_representation/enum/0003_given_permutation_in_param_2_cycle/expected/model-permutation.eprime-param create mode 100644 tests/exhaustive/basic/perms/01_representation/enum/0003_given_permutation_in_param_2_cycle/expected/model.eprime create mode 100644 tests/exhaustive/basic/perms/01_representation/enum/0003_given_permutation_in_param_2_cycle/permutation.essence create mode 100644 tests/exhaustive/basic/perms/01_representation/enum/0003_given_permutation_in_param_2_cycle/permutation.param create mode 100644 tests/exhaustive/basic/perms/01_representation/enum/0004_given_permutation_in_param_2_cycle/expected/model-permutation-solution000001.solution create mode 100644 tests/exhaustive/basic/perms/01_representation/enum/0004_given_permutation_in_param_2_cycle/expected/model-permutation.eprime-param create mode 100644 tests/exhaustive/basic/perms/01_representation/enum/0004_given_permutation_in_param_2_cycle/expected/model.eprime create mode 100644 tests/exhaustive/basic/perms/01_representation/enum/0004_given_permutation_in_param_2_cycle/permutation.essence create mode 100644 tests/exhaustive/basic/perms/01_representation/enum/0004_given_permutation_in_param_2_cycle/permutation.param create mode 100644 tests/exhaustive/basic/perms/01_representation/enum/0005_find_permutation_size_4_of_int1_4/expected/model-solution000001.solution create mode 100644 tests/exhaustive/basic/perms/01_representation/enum/0005_find_permutation_size_4_of_int1_4/expected/model-solution000002.solution create mode 100644 tests/exhaustive/basic/perms/01_representation/enum/0005_find_permutation_size_4_of_int1_4/expected/model-solution000003.solution create mode 100644 tests/exhaustive/basic/perms/01_representation/enum/0005_find_permutation_size_4_of_int1_4/expected/model-solution000004.solution create mode 100644 tests/exhaustive/basic/perms/01_representation/enum/0005_find_permutation_size_4_of_int1_4/expected/model-solution000005.solution create mode 100644 tests/exhaustive/basic/perms/01_representation/enum/0005_find_permutation_size_4_of_int1_4/expected/model-solution000006.solution create mode 100644 tests/exhaustive/basic/perms/01_representation/enum/0005_find_permutation_size_4_of_int1_4/expected/model-solution000007.solution create mode 100644 tests/exhaustive/basic/perms/01_representation/enum/0005_find_permutation_size_4_of_int1_4/expected/model-solution000008.solution create mode 100644 tests/exhaustive/basic/perms/01_representation/enum/0005_find_permutation_size_4_of_int1_4/expected/model-solution000009.solution create mode 100644 tests/exhaustive/basic/perms/01_representation/enum/0005_find_permutation_size_4_of_int1_4/expected/model.eprime create mode 100644 tests/exhaustive/basic/perms/01_representation/enum/0005_find_permutation_size_4_of_int1_4/permutation.essence create mode 100644 tests/exhaustive/basic/perms/01_representation/enum/0006_find_permutation_size_0_of_int1_4/expected/model-solution000001.solution create mode 100644 tests/exhaustive/basic/perms/01_representation/enum/0006_find_permutation_size_0_of_int1_4/expected/model.eprime create mode 100644 tests/exhaustive/basic/perms/01_representation/enum/0006_find_permutation_size_0_of_int1_4/permutation.essence create mode 100644 tests/exhaustive/basic/perms/01_representation/enum/0007_letting_permutation_be_empty/expected/model-solution000001.solution create mode 100644 tests/exhaustive/basic/perms/01_representation/enum/0007_letting_permutation_be_empty/expected/model.eprime create mode 100644 tests/exhaustive/basic/perms/01_representation/enum/0007_letting_permutation_be_empty/permutation.essence create mode 100644 tests/exhaustive/basic/perms/01_representation/enum/0008_find_permutation_of_int1_4/expected/model-solution000001.solution create mode 100644 tests/exhaustive/basic/perms/01_representation/enum/0008_find_permutation_of_int1_4/expected/model-solution000002.solution create mode 100644 tests/exhaustive/basic/perms/01_representation/enum/0008_find_permutation_of_int1_4/expected/model-solution000003.solution create mode 100644 tests/exhaustive/basic/perms/01_representation/enum/0008_find_permutation_of_int1_4/expected/model-solution000004.solution create mode 100644 tests/exhaustive/basic/perms/01_representation/enum/0008_find_permutation_of_int1_4/expected/model-solution000005.solution create mode 100644 tests/exhaustive/basic/perms/01_representation/enum/0008_find_permutation_of_int1_4/expected/model-solution000006.solution create mode 100644 tests/exhaustive/basic/perms/01_representation/enum/0008_find_permutation_of_int1_4/expected/model-solution000007.solution create mode 100644 tests/exhaustive/basic/perms/01_representation/enum/0008_find_permutation_of_int1_4/expected/model-solution000008.solution create mode 100644 tests/exhaustive/basic/perms/01_representation/enum/0008_find_permutation_of_int1_4/expected/model-solution000009.solution create mode 100644 tests/exhaustive/basic/perms/01_representation/enum/0008_find_permutation_of_int1_4/expected/model-solution000010.solution create mode 100644 tests/exhaustive/basic/perms/01_representation/enum/0008_find_permutation_of_int1_4/expected/model-solution000011.solution create mode 100644 tests/exhaustive/basic/perms/01_representation/enum/0008_find_permutation_of_int1_4/expected/model-solution000012.solution create mode 100644 tests/exhaustive/basic/perms/01_representation/enum/0008_find_permutation_of_int1_4/expected/model-solution000013.solution create mode 100644 tests/exhaustive/basic/perms/01_representation/enum/0008_find_permutation_of_int1_4/expected/model-solution000014.solution create mode 100644 tests/exhaustive/basic/perms/01_representation/enum/0008_find_permutation_of_int1_4/expected/model-solution000015.solution create mode 100644 tests/exhaustive/basic/perms/01_representation/enum/0008_find_permutation_of_int1_4/expected/model-solution000016.solution create mode 100644 tests/exhaustive/basic/perms/01_representation/enum/0008_find_permutation_of_int1_4/expected/model-solution000017.solution create mode 100644 tests/exhaustive/basic/perms/01_representation/enum/0008_find_permutation_of_int1_4/expected/model-solution000018.solution create mode 100644 tests/exhaustive/basic/perms/01_representation/enum/0008_find_permutation_of_int1_4/expected/model-solution000019.solution create mode 100644 tests/exhaustive/basic/perms/01_representation/enum/0008_find_permutation_of_int1_4/expected/model-solution000020.solution create mode 100644 tests/exhaustive/basic/perms/01_representation/enum/0008_find_permutation_of_int1_4/expected/model-solution000021.solution create mode 100644 tests/exhaustive/basic/perms/01_representation/enum/0008_find_permutation_of_int1_4/expected/model-solution000022.solution create mode 100644 tests/exhaustive/basic/perms/01_representation/enum/0008_find_permutation_of_int1_4/expected/model-solution000023.solution create mode 100644 tests/exhaustive/basic/perms/01_representation/enum/0008_find_permutation_of_int1_4/expected/model-solution000024.solution create mode 100644 tests/exhaustive/basic/perms/01_representation/enum/0008_find_permutation_of_int1_4/expected/model.eprime create mode 100644 tests/exhaustive/basic/perms/01_representation/enum/0008_find_permutation_of_int1_4/permutation.essence create mode 100644 tests/exhaustive/basic/perms/01_representation/enum/0009_letting_permutation_in_model/expected/model-solution000001.solution create mode 100644 tests/exhaustive/basic/perms/01_representation/enum/0009_letting_permutation_in_model/expected/model.eprime create mode 100644 tests/exhaustive/basic/perms/01_representation/enum/0009_letting_permutation_in_model/permutation.essence create mode 100644 tests/exhaustive/basic/perms/01_representation/enum/0010_find_permutation_maxSize_2_of_int1_3/expected/model-solution000001.solution create mode 100644 tests/exhaustive/basic/perms/01_representation/enum/0010_find_permutation_maxSize_2_of_int1_3/expected/model-solution000002.solution create mode 100644 tests/exhaustive/basic/perms/01_representation/enum/0010_find_permutation_maxSize_2_of_int1_3/expected/model-solution000003.solution create mode 100644 tests/exhaustive/basic/perms/01_representation/enum/0010_find_permutation_maxSize_2_of_int1_3/expected/model-solution000004.solution create mode 100644 tests/exhaustive/basic/perms/01_representation/enum/0010_find_permutation_maxSize_2_of_int1_3/expected/model.eprime create mode 100644 tests/exhaustive/basic/perms/01_representation/enum/0010_find_permutation_maxSize_2_of_int1_3/permutation.essence create mode 100644 tests/exhaustive/basic/perms/01_representation/enum/0011_find_permutation_minSize_2_of_int1_3/expected/model-solution000001.solution create mode 100644 tests/exhaustive/basic/perms/01_representation/enum/0011_find_permutation_minSize_2_of_int1_3/expected/model-solution000002.solution create mode 100644 tests/exhaustive/basic/perms/01_representation/enum/0011_find_permutation_minSize_2_of_int1_3/expected/model-solution000003.solution create mode 100644 tests/exhaustive/basic/perms/01_representation/enum/0011_find_permutation_minSize_2_of_int1_3/expected/model-solution000004.solution create mode 100644 tests/exhaustive/basic/perms/01_representation/enum/0011_find_permutation_minSize_2_of_int1_3/expected/model-solution000005.solution create mode 100644 tests/exhaustive/basic/perms/01_representation/enum/0011_find_permutation_minSize_2_of_int1_3/expected/model.eprime create mode 100644 tests/exhaustive/basic/perms/01_representation/enum/0011_find_permutation_minSize_2_of_int1_3/permutation.essence create mode 100644 tests/exhaustive/basic/perms/01_representation/enum/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model-solution000001.solution create mode 100644 tests/exhaustive/basic/perms/01_representation/enum/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model-solution000002.solution create mode 100644 tests/exhaustive/basic/perms/01_representation/enum/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model-solution000003.solution create mode 100644 tests/exhaustive/basic/perms/01_representation/enum/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model-solution000004.solution create mode 100644 tests/exhaustive/basic/perms/01_representation/enum/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model-solution000005.solution create mode 100644 tests/exhaustive/basic/perms/01_representation/enum/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model-solution000006.solution create mode 100644 tests/exhaustive/basic/perms/01_representation/enum/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model-solution000007.solution create mode 100644 tests/exhaustive/basic/perms/01_representation/enum/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model-solution000008.solution create mode 100644 tests/exhaustive/basic/perms/01_representation/enum/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model-solution000009.solution create mode 100644 tests/exhaustive/basic/perms/01_representation/enum/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model-solution000010.solution create mode 100644 tests/exhaustive/basic/perms/01_representation/enum/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model-solution000011.solution create mode 100644 tests/exhaustive/basic/perms/01_representation/enum/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model-solution000012.solution create mode 100644 tests/exhaustive/basic/perms/01_representation/enum/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model-solution000013.solution create mode 100644 tests/exhaustive/basic/perms/01_representation/enum/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model-solution000014.solution create mode 100644 tests/exhaustive/basic/perms/01_representation/enum/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model.eprime create mode 100644 tests/exhaustive/basic/perms/01_representation/enum/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/permutation.essence create mode 100644 tests/exhaustive/basic/perms/01_representation/int/0001_given_permutation_in_param/expected/model-permutation-solution000001.solution create mode 100644 tests/exhaustive/basic/perms/01_representation/int/0001_given_permutation_in_param/expected/model-permutation.eprime-param create mode 100644 tests/exhaustive/basic/perms/01_representation/int/0001_given_permutation_in_param/expected/model.eprime create mode 100644 tests/exhaustive/basic/perms/01_representation/int/0001_given_permutation_in_param/permutation.essence create mode 100644 tests/exhaustive/basic/perms/01_representation/int/0001_given_permutation_in_param/permutation.param create mode 100644 tests/exhaustive/basic/perms/01_representation/int/0002_given_permutation_in_param/expected/model-permutation-solution000001.solution create mode 100644 tests/exhaustive/basic/perms/01_representation/int/0002_given_permutation_in_param/expected/model-permutation.eprime-param create mode 100644 tests/exhaustive/basic/perms/01_representation/int/0002_given_permutation_in_param/expected/model.eprime create mode 100644 tests/exhaustive/basic/perms/01_representation/int/0002_given_permutation_in_param/permutation.essence create mode 100644 tests/exhaustive/basic/perms/01_representation/int/0002_given_permutation_in_param/permutation.param create mode 100644 tests/exhaustive/basic/perms/01_representation/int/0003_given_permutation_in_param_2_cycle/expected/model-permutation-solution000001.solution create mode 100644 tests/exhaustive/basic/perms/01_representation/int/0003_given_permutation_in_param_2_cycle/expected/model-permutation.eprime-param create mode 100644 tests/exhaustive/basic/perms/01_representation/int/0003_given_permutation_in_param_2_cycle/expected/model.eprime create mode 100644 tests/exhaustive/basic/perms/01_representation/int/0003_given_permutation_in_param_2_cycle/permutation.essence create mode 100644 tests/exhaustive/basic/perms/01_representation/int/0003_given_permutation_in_param_2_cycle/permutation.param create mode 100644 tests/exhaustive/basic/perms/01_representation/int/0004_given_permutation_in_param_2_cycle/expected/model-permutation-solution000001.solution create mode 100644 tests/exhaustive/basic/perms/01_representation/int/0004_given_permutation_in_param_2_cycle/expected/model-permutation.eprime-param create mode 100644 tests/exhaustive/basic/perms/01_representation/int/0004_given_permutation_in_param_2_cycle/expected/model.eprime create mode 100644 tests/exhaustive/basic/perms/01_representation/int/0004_given_permutation_in_param_2_cycle/permutation.essence create mode 100644 tests/exhaustive/basic/perms/01_representation/int/0004_given_permutation_in_param_2_cycle/permutation.param create mode 100644 tests/exhaustive/basic/perms/01_representation/int/0005_find_permutation_size_4_of_int1_4/expected/model-solution000001.solution create mode 100644 tests/exhaustive/basic/perms/01_representation/int/0005_find_permutation_size_4_of_int1_4/expected/model-solution000002.solution create mode 100644 tests/exhaustive/basic/perms/01_representation/int/0005_find_permutation_size_4_of_int1_4/expected/model-solution000003.solution create mode 100644 tests/exhaustive/basic/perms/01_representation/int/0005_find_permutation_size_4_of_int1_4/expected/model-solution000004.solution create mode 100644 tests/exhaustive/basic/perms/01_representation/int/0005_find_permutation_size_4_of_int1_4/expected/model-solution000005.solution create mode 100644 tests/exhaustive/basic/perms/01_representation/int/0005_find_permutation_size_4_of_int1_4/expected/model-solution000006.solution create mode 100644 tests/exhaustive/basic/perms/01_representation/int/0005_find_permutation_size_4_of_int1_4/expected/model-solution000007.solution create mode 100644 tests/exhaustive/basic/perms/01_representation/int/0005_find_permutation_size_4_of_int1_4/expected/model-solution000008.solution create mode 100644 tests/exhaustive/basic/perms/01_representation/int/0005_find_permutation_size_4_of_int1_4/expected/model-solution000009.solution create mode 100644 tests/exhaustive/basic/perms/01_representation/int/0005_find_permutation_size_4_of_int1_4/expected/model.eprime create mode 100644 tests/exhaustive/basic/perms/01_representation/int/0005_find_permutation_size_4_of_int1_4/permutation.essence create mode 100644 tests/exhaustive/basic/perms/01_representation/int/0006_find_permutation_size_0_of_int1_4/expected/model-solution000001.solution create mode 100644 tests/exhaustive/basic/perms/01_representation/int/0006_find_permutation_size_0_of_int1_4/expected/model.eprime create mode 100644 tests/exhaustive/basic/perms/01_representation/int/0006_find_permutation_size_0_of_int1_4/permutation.essence create mode 100644 tests/exhaustive/basic/perms/01_representation/int/0007_letting_permutation_be_empty/expected/model-solution000001.solution create mode 100644 tests/exhaustive/basic/perms/01_representation/int/0007_letting_permutation_be_empty/expected/model.eprime create mode 100644 tests/exhaustive/basic/perms/01_representation/int/0007_letting_permutation_be_empty/permutation.essence create mode 100644 tests/exhaustive/basic/perms/01_representation/int/0008_find_permutation_of_int1_4/expected/model-solution000001.solution create mode 100644 tests/exhaustive/basic/perms/01_representation/int/0008_find_permutation_of_int1_4/expected/model-solution000002.solution create mode 100644 tests/exhaustive/basic/perms/01_representation/int/0008_find_permutation_of_int1_4/expected/model-solution000003.solution create mode 100644 tests/exhaustive/basic/perms/01_representation/int/0008_find_permutation_of_int1_4/expected/model-solution000004.solution create mode 100644 tests/exhaustive/basic/perms/01_representation/int/0008_find_permutation_of_int1_4/expected/model-solution000005.solution create mode 100644 tests/exhaustive/basic/perms/01_representation/int/0008_find_permutation_of_int1_4/expected/model-solution000006.solution create mode 100644 tests/exhaustive/basic/perms/01_representation/int/0008_find_permutation_of_int1_4/expected/model-solution000007.solution create mode 100644 tests/exhaustive/basic/perms/01_representation/int/0008_find_permutation_of_int1_4/expected/model-solution000008.solution create mode 100644 tests/exhaustive/basic/perms/01_representation/int/0008_find_permutation_of_int1_4/expected/model-solution000009.solution create mode 100644 tests/exhaustive/basic/perms/01_representation/int/0008_find_permutation_of_int1_4/expected/model-solution000010.solution create mode 100644 tests/exhaustive/basic/perms/01_representation/int/0008_find_permutation_of_int1_4/expected/model-solution000011.solution create mode 100644 tests/exhaustive/basic/perms/01_representation/int/0008_find_permutation_of_int1_4/expected/model-solution000012.solution create mode 100644 tests/exhaustive/basic/perms/01_representation/int/0008_find_permutation_of_int1_4/expected/model-solution000013.solution create mode 100644 tests/exhaustive/basic/perms/01_representation/int/0008_find_permutation_of_int1_4/expected/model-solution000014.solution create mode 100644 tests/exhaustive/basic/perms/01_representation/int/0008_find_permutation_of_int1_4/expected/model-solution000015.solution create mode 100644 tests/exhaustive/basic/perms/01_representation/int/0008_find_permutation_of_int1_4/expected/model-solution000016.solution create mode 100644 tests/exhaustive/basic/perms/01_representation/int/0008_find_permutation_of_int1_4/expected/model-solution000017.solution create mode 100644 tests/exhaustive/basic/perms/01_representation/int/0008_find_permutation_of_int1_4/expected/model-solution000018.solution create mode 100644 tests/exhaustive/basic/perms/01_representation/int/0008_find_permutation_of_int1_4/expected/model-solution000019.solution create mode 100644 tests/exhaustive/basic/perms/01_representation/int/0008_find_permutation_of_int1_4/expected/model-solution000020.solution create mode 100644 tests/exhaustive/basic/perms/01_representation/int/0008_find_permutation_of_int1_4/expected/model-solution000021.solution create mode 100644 tests/exhaustive/basic/perms/01_representation/int/0008_find_permutation_of_int1_4/expected/model-solution000022.solution create mode 100644 tests/exhaustive/basic/perms/01_representation/int/0008_find_permutation_of_int1_4/expected/model-solution000023.solution create mode 100644 tests/exhaustive/basic/perms/01_representation/int/0008_find_permutation_of_int1_4/expected/model-solution000024.solution create mode 100644 tests/exhaustive/basic/perms/01_representation/int/0008_find_permutation_of_int1_4/expected/model.eprime create mode 100644 tests/exhaustive/basic/perms/01_representation/int/0008_find_permutation_of_int1_4/permutation.essence create mode 100644 tests/exhaustive/basic/perms/01_representation/int/0009_letting_permutation_in_model/expected/model-solution000001.solution create mode 100644 tests/exhaustive/basic/perms/01_representation/int/0009_letting_permutation_in_model/expected/model.eprime create mode 100644 tests/exhaustive/basic/perms/01_representation/int/0009_letting_permutation_in_model/permutation.essence create mode 100644 tests/exhaustive/basic/perms/01_representation/int/0010_find_permutation_maxSize_2_of_int1_3/expected/model-solution000001.solution create mode 100644 tests/exhaustive/basic/perms/01_representation/int/0010_find_permutation_maxSize_2_of_int1_3/expected/model-solution000002.solution create mode 100644 tests/exhaustive/basic/perms/01_representation/int/0010_find_permutation_maxSize_2_of_int1_3/expected/model-solution000003.solution create mode 100644 tests/exhaustive/basic/perms/01_representation/int/0010_find_permutation_maxSize_2_of_int1_3/expected/model-solution000004.solution create mode 100644 tests/exhaustive/basic/perms/01_representation/int/0010_find_permutation_maxSize_2_of_int1_3/expected/model.eprime create mode 100644 tests/exhaustive/basic/perms/01_representation/int/0010_find_permutation_maxSize_2_of_int1_3/permutation.essence create mode 100644 tests/exhaustive/basic/perms/01_representation/int/0011_find_permutation_minSize_2_of_int1_3/expected/model-solution000001.solution create mode 100644 tests/exhaustive/basic/perms/01_representation/int/0011_find_permutation_minSize_2_of_int1_3/expected/model-solution000002.solution create mode 100644 tests/exhaustive/basic/perms/01_representation/int/0011_find_permutation_minSize_2_of_int1_3/expected/model-solution000003.solution create mode 100644 tests/exhaustive/basic/perms/01_representation/int/0011_find_permutation_minSize_2_of_int1_3/expected/model-solution000004.solution create mode 100644 tests/exhaustive/basic/perms/01_representation/int/0011_find_permutation_minSize_2_of_int1_3/expected/model-solution000005.solution create mode 100644 tests/exhaustive/basic/perms/01_representation/int/0011_find_permutation_minSize_2_of_int1_3/expected/model.eprime create mode 100644 tests/exhaustive/basic/perms/01_representation/int/0011_find_permutation_minSize_2_of_int1_3/permutation.essence create mode 100644 tests/exhaustive/basic/perms/01_representation/int/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model-solution000001.solution create mode 100644 tests/exhaustive/basic/perms/01_representation/int/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model-solution000002.solution create mode 100644 tests/exhaustive/basic/perms/01_representation/int/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model-solution000003.solution create mode 100644 tests/exhaustive/basic/perms/01_representation/int/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model-solution000004.solution create mode 100644 tests/exhaustive/basic/perms/01_representation/int/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model-solution000005.solution create mode 100644 tests/exhaustive/basic/perms/01_representation/int/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model-solution000006.solution create mode 100644 tests/exhaustive/basic/perms/01_representation/int/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model-solution000007.solution create mode 100644 tests/exhaustive/basic/perms/01_representation/int/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model-solution000008.solution create mode 100644 tests/exhaustive/basic/perms/01_representation/int/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model-solution000009.solution create mode 100644 tests/exhaustive/basic/perms/01_representation/int/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model-solution000010.solution create mode 100644 tests/exhaustive/basic/perms/01_representation/int/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model-solution000011.solution create mode 100644 tests/exhaustive/basic/perms/01_representation/int/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model-solution000012.solution create mode 100644 tests/exhaustive/basic/perms/01_representation/int/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model-solution000013.solution create mode 100644 tests/exhaustive/basic/perms/01_representation/int/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model-solution000014.solution create mode 100644 tests/exhaustive/basic/perms/01_representation/int/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model.eprime create mode 100644 tests/exhaustive/basic/perms/01_representation/int/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/permutation.essence create mode 100644 tests/exhaustive/basic/perms/01_representation/unnamed/0005_find_permutation_size_4_of_int1_4/expected/model-solution000001.solution create mode 100644 tests/exhaustive/basic/perms/01_representation/unnamed/0005_find_permutation_size_4_of_int1_4/expected/model-solution000002.solution create mode 100644 tests/exhaustive/basic/perms/01_representation/unnamed/0005_find_permutation_size_4_of_int1_4/expected/model-solution000003.solution create mode 100644 tests/exhaustive/basic/perms/01_representation/unnamed/0005_find_permutation_size_4_of_int1_4/expected/model-solution000004.solution create mode 100644 tests/exhaustive/basic/perms/01_representation/unnamed/0005_find_permutation_size_4_of_int1_4/expected/model-solution000005.solution create mode 100644 tests/exhaustive/basic/perms/01_representation/unnamed/0005_find_permutation_size_4_of_int1_4/expected/model-solution000006.solution create mode 100644 tests/exhaustive/basic/perms/01_representation/unnamed/0005_find_permutation_size_4_of_int1_4/expected/model-solution000007.solution create mode 100644 tests/exhaustive/basic/perms/01_representation/unnamed/0005_find_permutation_size_4_of_int1_4/expected/model-solution000008.solution create mode 100644 tests/exhaustive/basic/perms/01_representation/unnamed/0005_find_permutation_size_4_of_int1_4/expected/model-solution000009.solution create mode 100644 tests/exhaustive/basic/perms/01_representation/unnamed/0005_find_permutation_size_4_of_int1_4/expected/model.eprime create mode 100644 tests/exhaustive/basic/perms/01_representation/unnamed/0005_find_permutation_size_4_of_int1_4/permutation.essence create mode 100644 tests/exhaustive/basic/perms/01_representation/unnamed/0006_find_permutation_size_0_of_int1_4/expected/model-solution000001.solution create mode 100644 tests/exhaustive/basic/perms/01_representation/unnamed/0006_find_permutation_size_0_of_int1_4/expected/model.eprime create mode 100644 tests/exhaustive/basic/perms/01_representation/unnamed/0006_find_permutation_size_0_of_int1_4/permutation.essence create mode 100644 tests/exhaustive/basic/perms/01_representation/unnamed/0007_letting_permutation_be_empty/expected/model-solution000001.solution create mode 100644 tests/exhaustive/basic/perms/01_representation/unnamed/0007_letting_permutation_be_empty/expected/model.eprime create mode 100644 tests/exhaustive/basic/perms/01_representation/unnamed/0007_letting_permutation_be_empty/permutation.essence create mode 100644 tests/exhaustive/basic/perms/01_representation/unnamed/0008_find_permutation_of_int1_4/expected/model-solution000001.solution create mode 100644 tests/exhaustive/basic/perms/01_representation/unnamed/0008_find_permutation_of_int1_4/expected/model-solution000002.solution create mode 100644 tests/exhaustive/basic/perms/01_representation/unnamed/0008_find_permutation_of_int1_4/expected/model-solution000003.solution create mode 100644 tests/exhaustive/basic/perms/01_representation/unnamed/0008_find_permutation_of_int1_4/expected/model-solution000004.solution create mode 100644 tests/exhaustive/basic/perms/01_representation/unnamed/0008_find_permutation_of_int1_4/expected/model-solution000005.solution create mode 100644 tests/exhaustive/basic/perms/01_representation/unnamed/0008_find_permutation_of_int1_4/expected/model-solution000006.solution create mode 100644 tests/exhaustive/basic/perms/01_representation/unnamed/0008_find_permutation_of_int1_4/expected/model-solution000007.solution create mode 100644 tests/exhaustive/basic/perms/01_representation/unnamed/0008_find_permutation_of_int1_4/expected/model-solution000008.solution create mode 100644 tests/exhaustive/basic/perms/01_representation/unnamed/0008_find_permutation_of_int1_4/expected/model-solution000009.solution create mode 100644 tests/exhaustive/basic/perms/01_representation/unnamed/0008_find_permutation_of_int1_4/expected/model-solution000010.solution create mode 100644 tests/exhaustive/basic/perms/01_representation/unnamed/0008_find_permutation_of_int1_4/expected/model-solution000011.solution create mode 100644 tests/exhaustive/basic/perms/01_representation/unnamed/0008_find_permutation_of_int1_4/expected/model-solution000012.solution create mode 100644 tests/exhaustive/basic/perms/01_representation/unnamed/0008_find_permutation_of_int1_4/expected/model-solution000013.solution create mode 100644 tests/exhaustive/basic/perms/01_representation/unnamed/0008_find_permutation_of_int1_4/expected/model-solution000014.solution create mode 100644 tests/exhaustive/basic/perms/01_representation/unnamed/0008_find_permutation_of_int1_4/expected/model-solution000015.solution create mode 100644 tests/exhaustive/basic/perms/01_representation/unnamed/0008_find_permutation_of_int1_4/expected/model-solution000016.solution create mode 100644 tests/exhaustive/basic/perms/01_representation/unnamed/0008_find_permutation_of_int1_4/expected/model-solution000017.solution create mode 100644 tests/exhaustive/basic/perms/01_representation/unnamed/0008_find_permutation_of_int1_4/expected/model-solution000018.solution create mode 100644 tests/exhaustive/basic/perms/01_representation/unnamed/0008_find_permutation_of_int1_4/expected/model-solution000019.solution create mode 100644 tests/exhaustive/basic/perms/01_representation/unnamed/0008_find_permutation_of_int1_4/expected/model-solution000020.solution create mode 100644 tests/exhaustive/basic/perms/01_representation/unnamed/0008_find_permutation_of_int1_4/expected/model-solution000021.solution create mode 100644 tests/exhaustive/basic/perms/01_representation/unnamed/0008_find_permutation_of_int1_4/expected/model-solution000022.solution create mode 100644 tests/exhaustive/basic/perms/01_representation/unnamed/0008_find_permutation_of_int1_4/expected/model-solution000023.solution create mode 100644 tests/exhaustive/basic/perms/01_representation/unnamed/0008_find_permutation_of_int1_4/expected/model-solution000024.solution create mode 100644 tests/exhaustive/basic/perms/01_representation/unnamed/0008_find_permutation_of_int1_4/expected/model.eprime create mode 100644 tests/exhaustive/basic/perms/01_representation/unnamed/0008_find_permutation_of_int1_4/permutation.essence create mode 100644 tests/exhaustive/basic/perms/01_representation/unnamed/0010_find_permutation_maxSize_2_of_int1_3/expected/model-solution000001.solution create mode 100644 tests/exhaustive/basic/perms/01_representation/unnamed/0010_find_permutation_maxSize_2_of_int1_3/expected/model-solution000002.solution create mode 100644 tests/exhaustive/basic/perms/01_representation/unnamed/0010_find_permutation_maxSize_2_of_int1_3/expected/model-solution000003.solution create mode 100644 tests/exhaustive/basic/perms/01_representation/unnamed/0010_find_permutation_maxSize_2_of_int1_3/expected/model-solution000004.solution create mode 100644 tests/exhaustive/basic/perms/01_representation/unnamed/0010_find_permutation_maxSize_2_of_int1_3/expected/model.eprime create mode 100644 tests/exhaustive/basic/perms/01_representation/unnamed/0010_find_permutation_maxSize_2_of_int1_3/permutation.essence create mode 100644 tests/exhaustive/basic/perms/01_representation/unnamed/0011_find_permutation_minSize_2_of_int1_3/expected/model-solution000001.solution create mode 100644 tests/exhaustive/basic/perms/01_representation/unnamed/0011_find_permutation_minSize_2_of_int1_3/expected/model-solution000002.solution create mode 100644 tests/exhaustive/basic/perms/01_representation/unnamed/0011_find_permutation_minSize_2_of_int1_3/expected/model-solution000003.solution create mode 100644 tests/exhaustive/basic/perms/01_representation/unnamed/0011_find_permutation_minSize_2_of_int1_3/expected/model-solution000004.solution create mode 100644 tests/exhaustive/basic/perms/01_representation/unnamed/0011_find_permutation_minSize_2_of_int1_3/expected/model-solution000005.solution create mode 100644 tests/exhaustive/basic/perms/01_representation/unnamed/0011_find_permutation_minSize_2_of_int1_3/expected/model.eprime create mode 100644 tests/exhaustive/basic/perms/01_representation/unnamed/0011_find_permutation_minSize_2_of_int1_3/permutation.essence create mode 100644 tests/exhaustive/basic/perms/01_representation/unnamed/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model-solution000001.solution create mode 100644 tests/exhaustive/basic/perms/01_representation/unnamed/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model-solution000002.solution create mode 100644 tests/exhaustive/basic/perms/01_representation/unnamed/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model-solution000003.solution create mode 100644 tests/exhaustive/basic/perms/01_representation/unnamed/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model-solution000004.solution create mode 100644 tests/exhaustive/basic/perms/01_representation/unnamed/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model-solution000005.solution create mode 100644 tests/exhaustive/basic/perms/01_representation/unnamed/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model-solution000006.solution create mode 100644 tests/exhaustive/basic/perms/01_representation/unnamed/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model-solution000007.solution create mode 100644 tests/exhaustive/basic/perms/01_representation/unnamed/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model-solution000008.solution create mode 100644 tests/exhaustive/basic/perms/01_representation/unnamed/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model-solution000009.solution create mode 100644 tests/exhaustive/basic/perms/01_representation/unnamed/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model-solution000010.solution create mode 100644 tests/exhaustive/basic/perms/01_representation/unnamed/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model-solution000011.solution create mode 100644 tests/exhaustive/basic/perms/01_representation/unnamed/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model-solution000012.solution create mode 100644 tests/exhaustive/basic/perms/01_representation/unnamed/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model-solution000013.solution create mode 100644 tests/exhaustive/basic/perms/01_representation/unnamed/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model-solution000014.solution create mode 100644 tests/exhaustive/basic/perms/01_representation/unnamed/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model.eprime create mode 100644 tests/exhaustive/basic/perms/01_representation/unnamed/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/permutation.essence diff --git a/tests/exhaustive/basic/perms/01_representation/README.md b/tests/exhaustive/basic/perms/01_representation/README.md new file mode 100644 index 0000000000..7edafd9c69 --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/README.md @@ -0,0 +1,4 @@ +# Minimal permutation test set +These tests should work without any vertical or horizontal permutation rules. + +They rely only on the permutation type and representation rules. diff --git a/tests/exhaustive/basic/perms/01_representation/enum/0001_given_permutation_in_param/expected/model-permutation-solution000001.solution b/tests/exhaustive/basic/perms/01_representation/enum/0001_given_permutation_in_param/expected/model-permutation-solution000001.solution new file mode 100644 index 0000000000..fa3c1c5e86 --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/enum/0001_given_permutation_in_param/expected/model-permutation-solution000001.solution @@ -0,0 +1,2 @@ +language Essence 1.3 + diff --git a/tests/exhaustive/basic/perms/01_representation/enum/0001_given_permutation_in_param/expected/model-permutation.eprime-param b/tests/exhaustive/basic/perms/01_representation/enum/0001_given_permutation_in_param/expected/model-permutation.eprime-param new file mode 100644 index 0000000000..c2bddee0e8 --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/enum/0001_given_permutation_in_param/expected/model-permutation.eprime-param @@ -0,0 +1,3 @@ +language ESSENCE' 1.0 + +letting p_PermutationAsFunction_PermutationFunction_Function1D be [3, 2, 4, 1; int(1..4)] diff --git a/tests/exhaustive/basic/perms/01_representation/enum/0001_given_permutation_in_param/expected/model.eprime b/tests/exhaustive/basic/perms/01_representation/enum/0001_given_permutation_in_param/expected/model.eprime new file mode 100644 index 0000000000..cc4c1dfa5f --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/enum/0001_given_permutation_in_param/expected/model.eprime @@ -0,0 +1,6 @@ +language ESSENCE' 1.0 + +given p_PermutationAsFunction_PermutationFunction_Function1D: matrix indexed by [int(1..4)] of int(1..4) +branching on [] +such that true + diff --git a/tests/exhaustive/basic/perms/01_representation/enum/0001_given_permutation_in_param/permutation.essence b/tests/exhaustive/basic/perms/01_representation/enum/0001_given_permutation_in_param/permutation.essence new file mode 100644 index 0000000000..cfb90df3cc --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/enum/0001_given_permutation_in_param/permutation.essence @@ -0,0 +1,9 @@ +letting n be new type enum {E1,E2,E3,E4} + +given p : permutation of n + +such that true + + + + diff --git a/tests/exhaustive/basic/perms/01_representation/enum/0001_given_permutation_in_param/permutation.param b/tests/exhaustive/basic/perms/01_representation/enum/0001_given_permutation_in_param/permutation.param new file mode 100644 index 0000000000..19349bb872 --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/enum/0001_given_permutation_in_param/permutation.param @@ -0,0 +1 @@ +letting p be permutation((E1,E3,E4)) diff --git a/tests/exhaustive/basic/perms/01_representation/enum/0002_given_permutation_in_param/expected/model-permutation-solution000001.solution b/tests/exhaustive/basic/perms/01_representation/enum/0002_given_permutation_in_param/expected/model-permutation-solution000001.solution new file mode 100644 index 0000000000..fa3c1c5e86 --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/enum/0002_given_permutation_in_param/expected/model-permutation-solution000001.solution @@ -0,0 +1,2 @@ +language Essence 1.3 + diff --git a/tests/exhaustive/basic/perms/01_representation/enum/0002_given_permutation_in_param/expected/model-permutation.eprime-param b/tests/exhaustive/basic/perms/01_representation/enum/0002_given_permutation_in_param/expected/model-permutation.eprime-param new file mode 100644 index 0000000000..7e9e727085 --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/enum/0002_given_permutation_in_param/expected/model-permutation.eprime-param @@ -0,0 +1,3 @@ +language ESSENCE' 1.0 + +letting p_PermutationAsFunction_PermutationFunction_Function1D be [3, 1, 2; int(1..3)] diff --git a/tests/exhaustive/basic/perms/01_representation/enum/0002_given_permutation_in_param/expected/model.eprime b/tests/exhaustive/basic/perms/01_representation/enum/0002_given_permutation_in_param/expected/model.eprime new file mode 100644 index 0000000000..b1234f8b14 --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/enum/0002_given_permutation_in_param/expected/model.eprime @@ -0,0 +1,6 @@ +language ESSENCE' 1.0 + +given p_PermutationAsFunction_PermutationFunction_Function1D: matrix indexed by [int(1..3)] of int(1..3) +branching on [] +such that true + diff --git a/tests/exhaustive/basic/perms/01_representation/enum/0002_given_permutation_in_param/permutation.essence b/tests/exhaustive/basic/perms/01_representation/enum/0002_given_permutation_in_param/permutation.essence new file mode 100644 index 0000000000..b02f26c6a6 --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/enum/0002_given_permutation_in_param/permutation.essence @@ -0,0 +1,5 @@ +letting n be new type enum {E1,E2,E3} + +given p : permutation of n + +such that true diff --git a/tests/exhaustive/basic/perms/01_representation/enum/0002_given_permutation_in_param/permutation.param b/tests/exhaustive/basic/perms/01_representation/enum/0002_given_permutation_in_param/permutation.param new file mode 100644 index 0000000000..95a86975a7 --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/enum/0002_given_permutation_in_param/permutation.param @@ -0,0 +1 @@ +letting p be permutation((E1,E3,E2)) diff --git a/tests/exhaustive/basic/perms/01_representation/enum/0003_given_permutation_in_param_2_cycle/expected/model-permutation-solution000001.solution b/tests/exhaustive/basic/perms/01_representation/enum/0003_given_permutation_in_param_2_cycle/expected/model-permutation-solution000001.solution new file mode 100644 index 0000000000..fa3c1c5e86 --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/enum/0003_given_permutation_in_param_2_cycle/expected/model-permutation-solution000001.solution @@ -0,0 +1,2 @@ +language Essence 1.3 + diff --git a/tests/exhaustive/basic/perms/01_representation/enum/0003_given_permutation_in_param_2_cycle/expected/model-permutation.eprime-param b/tests/exhaustive/basic/perms/01_representation/enum/0003_given_permutation_in_param_2_cycle/expected/model-permutation.eprime-param new file mode 100644 index 0000000000..3cc48acd18 --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/enum/0003_given_permutation_in_param_2_cycle/expected/model-permutation.eprime-param @@ -0,0 +1,3 @@ +language ESSENCE' 1.0 + +letting p_PermutationAsFunction_PermutationFunction_Function1D be [3, 4, 1, 2; int(1..4)] diff --git a/tests/exhaustive/basic/perms/01_representation/enum/0003_given_permutation_in_param_2_cycle/expected/model.eprime b/tests/exhaustive/basic/perms/01_representation/enum/0003_given_permutation_in_param_2_cycle/expected/model.eprime new file mode 100644 index 0000000000..cc4c1dfa5f --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/enum/0003_given_permutation_in_param_2_cycle/expected/model.eprime @@ -0,0 +1,6 @@ +language ESSENCE' 1.0 + +given p_PermutationAsFunction_PermutationFunction_Function1D: matrix indexed by [int(1..4)] of int(1..4) +branching on [] +such that true + diff --git a/tests/exhaustive/basic/perms/01_representation/enum/0003_given_permutation_in_param_2_cycle/permutation.essence b/tests/exhaustive/basic/perms/01_representation/enum/0003_given_permutation_in_param_2_cycle/permutation.essence new file mode 100644 index 0000000000..35d81d7264 --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/enum/0003_given_permutation_in_param_2_cycle/permutation.essence @@ -0,0 +1,5 @@ +letting n be new type enum {E1,E2,E3,E4} + +given p : permutation of n + +such that true diff --git a/tests/exhaustive/basic/perms/01_representation/enum/0003_given_permutation_in_param_2_cycle/permutation.param b/tests/exhaustive/basic/perms/01_representation/enum/0003_given_permutation_in_param_2_cycle/permutation.param new file mode 100644 index 0000000000..34ca085d38 --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/enum/0003_given_permutation_in_param_2_cycle/permutation.param @@ -0,0 +1 @@ +letting p be permutation((E1,E3),(E2,E4)) diff --git a/tests/exhaustive/basic/perms/01_representation/enum/0004_given_permutation_in_param_2_cycle/expected/model-permutation-solution000001.solution b/tests/exhaustive/basic/perms/01_representation/enum/0004_given_permutation_in_param_2_cycle/expected/model-permutation-solution000001.solution new file mode 100644 index 0000000000..fa3c1c5e86 --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/enum/0004_given_permutation_in_param_2_cycle/expected/model-permutation-solution000001.solution @@ -0,0 +1,2 @@ +language Essence 1.3 + diff --git a/tests/exhaustive/basic/perms/01_representation/enum/0004_given_permutation_in_param_2_cycle/expected/model-permutation.eprime-param b/tests/exhaustive/basic/perms/01_representation/enum/0004_given_permutation_in_param_2_cycle/expected/model-permutation.eprime-param new file mode 100644 index 0000000000..3cc48acd18 --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/enum/0004_given_permutation_in_param_2_cycle/expected/model-permutation.eprime-param @@ -0,0 +1,3 @@ +language ESSENCE' 1.0 + +letting p_PermutationAsFunction_PermutationFunction_Function1D be [3, 4, 1, 2; int(1..4)] diff --git a/tests/exhaustive/basic/perms/01_representation/enum/0004_given_permutation_in_param_2_cycle/expected/model.eprime b/tests/exhaustive/basic/perms/01_representation/enum/0004_given_permutation_in_param_2_cycle/expected/model.eprime new file mode 100644 index 0000000000..cc4c1dfa5f --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/enum/0004_given_permutation_in_param_2_cycle/expected/model.eprime @@ -0,0 +1,6 @@ +language ESSENCE' 1.0 + +given p_PermutationAsFunction_PermutationFunction_Function1D: matrix indexed by [int(1..4)] of int(1..4) +branching on [] +such that true + diff --git a/tests/exhaustive/basic/perms/01_representation/enum/0004_given_permutation_in_param_2_cycle/permutation.essence b/tests/exhaustive/basic/perms/01_representation/enum/0004_given_permutation_in_param_2_cycle/permutation.essence new file mode 100644 index 0000000000..35d81d7264 --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/enum/0004_given_permutation_in_param_2_cycle/permutation.essence @@ -0,0 +1,5 @@ +letting n be new type enum {E1,E2,E3,E4} + +given p : permutation of n + +such that true diff --git a/tests/exhaustive/basic/perms/01_representation/enum/0004_given_permutation_in_param_2_cycle/permutation.param b/tests/exhaustive/basic/perms/01_representation/enum/0004_given_permutation_in_param_2_cycle/permutation.param new file mode 100644 index 0000000000..34ca085d38 --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/enum/0004_given_permutation_in_param_2_cycle/permutation.param @@ -0,0 +1 @@ +letting p be permutation((E1,E3),(E2,E4)) diff --git a/tests/exhaustive/basic/perms/01_representation/enum/0005_find_permutation_size_4_of_int1_4/expected/model-solution000001.solution b/tests/exhaustive/basic/perms/01_representation/enum/0005_find_permutation_size_4_of_int1_4/expected/model-solution000001.solution new file mode 100644 index 0000000000..c26b24e96c --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/enum/0005_find_permutation_size_4_of_int1_4/expected/model-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting p be permutation((E1, E2), (E3, E4)) diff --git a/tests/exhaustive/basic/perms/01_representation/enum/0005_find_permutation_size_4_of_int1_4/expected/model-solution000002.solution b/tests/exhaustive/basic/perms/01_representation/enum/0005_find_permutation_size_4_of_int1_4/expected/model-solution000002.solution new file mode 100644 index 0000000000..302a1d753f --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/enum/0005_find_permutation_size_4_of_int1_4/expected/model-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting p be permutation((E1, E2, E3, E4)) diff --git a/tests/exhaustive/basic/perms/01_representation/enum/0005_find_permutation_size_4_of_int1_4/expected/model-solution000003.solution b/tests/exhaustive/basic/perms/01_representation/enum/0005_find_permutation_size_4_of_int1_4/expected/model-solution000003.solution new file mode 100644 index 0000000000..16c9c55d9d --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/enum/0005_find_permutation_size_4_of_int1_4/expected/model-solution000003.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting p be permutation((E1, E2, E4, E3)) diff --git a/tests/exhaustive/basic/perms/01_representation/enum/0005_find_permutation_size_4_of_int1_4/expected/model-solution000004.solution b/tests/exhaustive/basic/perms/01_representation/enum/0005_find_permutation_size_4_of_int1_4/expected/model-solution000004.solution new file mode 100644 index 0000000000..fbce064674 --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/enum/0005_find_permutation_size_4_of_int1_4/expected/model-solution000004.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting p be permutation((E1, E3, E4, E2)) diff --git a/tests/exhaustive/basic/perms/01_representation/enum/0005_find_permutation_size_4_of_int1_4/expected/model-solution000005.solution b/tests/exhaustive/basic/perms/01_representation/enum/0005_find_permutation_size_4_of_int1_4/expected/model-solution000005.solution new file mode 100644 index 0000000000..5460f2a118 --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/enum/0005_find_permutation_size_4_of_int1_4/expected/model-solution000005.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting p be permutation((E1, E3), (E2, E4)) diff --git a/tests/exhaustive/basic/perms/01_representation/enum/0005_find_permutation_size_4_of_int1_4/expected/model-solution000006.solution b/tests/exhaustive/basic/perms/01_representation/enum/0005_find_permutation_size_4_of_int1_4/expected/model-solution000006.solution new file mode 100644 index 0000000000..ce90f13c1d --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/enum/0005_find_permutation_size_4_of_int1_4/expected/model-solution000006.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting p be permutation((E1, E3, E2, E4)) diff --git a/tests/exhaustive/basic/perms/01_representation/enum/0005_find_permutation_size_4_of_int1_4/expected/model-solution000007.solution b/tests/exhaustive/basic/perms/01_representation/enum/0005_find_permutation_size_4_of_int1_4/expected/model-solution000007.solution new file mode 100644 index 0000000000..56f4d68c62 --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/enum/0005_find_permutation_size_4_of_int1_4/expected/model-solution000007.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting p be permutation((E1, E4, E3, E2)) diff --git a/tests/exhaustive/basic/perms/01_representation/enum/0005_find_permutation_size_4_of_int1_4/expected/model-solution000008.solution b/tests/exhaustive/basic/perms/01_representation/enum/0005_find_permutation_size_4_of_int1_4/expected/model-solution000008.solution new file mode 100644 index 0000000000..69dc5a4176 --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/enum/0005_find_permutation_size_4_of_int1_4/expected/model-solution000008.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting p be permutation((E1, E4, E2, E3)) diff --git a/tests/exhaustive/basic/perms/01_representation/enum/0005_find_permutation_size_4_of_int1_4/expected/model-solution000009.solution b/tests/exhaustive/basic/perms/01_representation/enum/0005_find_permutation_size_4_of_int1_4/expected/model-solution000009.solution new file mode 100644 index 0000000000..170719569e --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/enum/0005_find_permutation_size_4_of_int1_4/expected/model-solution000009.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting p be permutation((E1, E4), (E2, E3)) diff --git a/tests/exhaustive/basic/perms/01_representation/enum/0005_find_permutation_size_4_of_int1_4/expected/model.eprime b/tests/exhaustive/basic/perms/01_representation/enum/0005_find_permutation_size_4_of_int1_4/expected/model.eprime new file mode 100644 index 0000000000..134950077a --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/enum/0005_find_permutation_size_4_of_int1_4/expected/model.eprime @@ -0,0 +1,9 @@ +language ESSENCE' 1.0 + +find p_PermutationAsFunction_PermutationFunction_Function1D: matrix indexed by [int(1..4)] of int(1..4) +branching on [p_PermutationAsFunction_PermutationFunction_Function1D] +such that + allDiff(p_PermutationAsFunction_PermutationFunction_Function1D), + and([or([p_PermutationAsFunction_PermutationFunction_Function1D[q3] = q2 | q3 : int(1..4)]) | q2 : int(1..4)]), + 4 = sum([toInt(q1 != p_PermutationAsFunction_PermutationFunction_Function1D[q1]) | q1 : int(1..4)]) + diff --git a/tests/exhaustive/basic/perms/01_representation/enum/0005_find_permutation_size_4_of_int1_4/permutation.essence b/tests/exhaustive/basic/perms/01_representation/enum/0005_find_permutation_size_4_of_int1_4/permutation.essence new file mode 100644 index 0000000000..26786093fd --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/enum/0005_find_permutation_size_4_of_int1_4/permutation.essence @@ -0,0 +1,5 @@ +letting n be new type enum {E1,E2,E3,E4} + +find p : permutation (size 4) of n + +such that true diff --git a/tests/exhaustive/basic/perms/01_representation/enum/0006_find_permutation_size_0_of_int1_4/expected/model-solution000001.solution b/tests/exhaustive/basic/perms/01_representation/enum/0006_find_permutation_size_0_of_int1_4/expected/model-solution000001.solution new file mode 100644 index 0000000000..dec1e69413 --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/enum/0006_find_permutation_size_0_of_int1_4/expected/model-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting p be permutation() diff --git a/tests/exhaustive/basic/perms/01_representation/enum/0006_find_permutation_size_0_of_int1_4/expected/model.eprime b/tests/exhaustive/basic/perms/01_representation/enum/0006_find_permutation_size_0_of_int1_4/expected/model.eprime new file mode 100644 index 0000000000..a03a5e86e3 --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/enum/0006_find_permutation_size_0_of_int1_4/expected/model.eprime @@ -0,0 +1,9 @@ +language ESSENCE' 1.0 + +find p_PermutationAsFunction_PermutationFunction_Function1D: matrix indexed by [int(1..4)] of int(1..4) +branching on [p_PermutationAsFunction_PermutationFunction_Function1D] +such that + allDiff(p_PermutationAsFunction_PermutationFunction_Function1D), + and([or([p_PermutationAsFunction_PermutationFunction_Function1D[q3] = q2 | q3 : int(1..4)]) | q2 : int(1..4)]), + 0 = sum([toInt(q1 != p_PermutationAsFunction_PermutationFunction_Function1D[q1]) | q1 : int(1..4)]) + diff --git a/tests/exhaustive/basic/perms/01_representation/enum/0006_find_permutation_size_0_of_int1_4/permutation.essence b/tests/exhaustive/basic/perms/01_representation/enum/0006_find_permutation_size_0_of_int1_4/permutation.essence new file mode 100644 index 0000000000..9a91f2f8d1 --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/enum/0006_find_permutation_size_0_of_int1_4/permutation.essence @@ -0,0 +1,5 @@ +letting n be new type enum {E1,E2,E3,E4} + +find p : permutation (size 0) of n + +such that true diff --git a/tests/exhaustive/basic/perms/01_representation/enum/0007_letting_permutation_be_empty/expected/model-solution000001.solution b/tests/exhaustive/basic/perms/01_representation/enum/0007_letting_permutation_be_empty/expected/model-solution000001.solution new file mode 100644 index 0000000000..fa3c1c5e86 --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/enum/0007_letting_permutation_be_empty/expected/model-solution000001.solution @@ -0,0 +1,2 @@ +language Essence 1.3 + diff --git a/tests/exhaustive/basic/perms/01_representation/enum/0007_letting_permutation_be_empty/expected/model.eprime b/tests/exhaustive/basic/perms/01_representation/enum/0007_letting_permutation_be_empty/expected/model.eprime new file mode 100644 index 0000000000..c64108a295 --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/enum/0007_letting_permutation_be_empty/expected/model.eprime @@ -0,0 +1,5 @@ +language ESSENCE' 1.0 + +branching on [] +such that true + diff --git a/tests/exhaustive/basic/perms/01_representation/enum/0007_letting_permutation_be_empty/permutation.essence b/tests/exhaustive/basic/perms/01_representation/enum/0007_letting_permutation_be_empty/permutation.essence new file mode 100644 index 0000000000..a39f3ae0b1 --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/enum/0007_letting_permutation_be_empty/permutation.essence @@ -0,0 +1,3 @@ +letting p be permutation() + +such that true diff --git a/tests/exhaustive/basic/perms/01_representation/enum/0008_find_permutation_of_int1_4/expected/model-solution000001.solution b/tests/exhaustive/basic/perms/01_representation/enum/0008_find_permutation_of_int1_4/expected/model-solution000001.solution new file mode 100644 index 0000000000..dec1e69413 --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/enum/0008_find_permutation_of_int1_4/expected/model-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting p be permutation() diff --git a/tests/exhaustive/basic/perms/01_representation/enum/0008_find_permutation_of_int1_4/expected/model-solution000002.solution b/tests/exhaustive/basic/perms/01_representation/enum/0008_find_permutation_of_int1_4/expected/model-solution000002.solution new file mode 100644 index 0000000000..e84be5d054 --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/enum/0008_find_permutation_of_int1_4/expected/model-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting p be permutation((E3, E4)) diff --git a/tests/exhaustive/basic/perms/01_representation/enum/0008_find_permutation_of_int1_4/expected/model-solution000003.solution b/tests/exhaustive/basic/perms/01_representation/enum/0008_find_permutation_of_int1_4/expected/model-solution000003.solution new file mode 100644 index 0000000000..075d779af1 --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/enum/0008_find_permutation_of_int1_4/expected/model-solution000003.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting p be permutation((E2, E3)) diff --git a/tests/exhaustive/basic/perms/01_representation/enum/0008_find_permutation_of_int1_4/expected/model-solution000004.solution b/tests/exhaustive/basic/perms/01_representation/enum/0008_find_permutation_of_int1_4/expected/model-solution000004.solution new file mode 100644 index 0000000000..10f28984f9 --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/enum/0008_find_permutation_of_int1_4/expected/model-solution000004.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting p be permutation((E2, E3, E4)) diff --git a/tests/exhaustive/basic/perms/01_representation/enum/0008_find_permutation_of_int1_4/expected/model-solution000005.solution b/tests/exhaustive/basic/perms/01_representation/enum/0008_find_permutation_of_int1_4/expected/model-solution000005.solution new file mode 100644 index 0000000000..629ad61397 --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/enum/0008_find_permutation_of_int1_4/expected/model-solution000005.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting p be permutation((E2, E4, E3)) diff --git a/tests/exhaustive/basic/perms/01_representation/enum/0008_find_permutation_of_int1_4/expected/model-solution000006.solution b/tests/exhaustive/basic/perms/01_representation/enum/0008_find_permutation_of_int1_4/expected/model-solution000006.solution new file mode 100644 index 0000000000..bf4b6b916a --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/enum/0008_find_permutation_of_int1_4/expected/model-solution000006.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting p be permutation((E2, E4)) diff --git a/tests/exhaustive/basic/perms/01_representation/enum/0008_find_permutation_of_int1_4/expected/model-solution000007.solution b/tests/exhaustive/basic/perms/01_representation/enum/0008_find_permutation_of_int1_4/expected/model-solution000007.solution new file mode 100644 index 0000000000..3aee0eea27 --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/enum/0008_find_permutation_of_int1_4/expected/model-solution000007.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting p be permutation((E1, E2)) diff --git a/tests/exhaustive/basic/perms/01_representation/enum/0008_find_permutation_of_int1_4/expected/model-solution000008.solution b/tests/exhaustive/basic/perms/01_representation/enum/0008_find_permutation_of_int1_4/expected/model-solution000008.solution new file mode 100644 index 0000000000..c26b24e96c --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/enum/0008_find_permutation_of_int1_4/expected/model-solution000008.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting p be permutation((E1, E2), (E3, E4)) diff --git a/tests/exhaustive/basic/perms/01_representation/enum/0008_find_permutation_of_int1_4/expected/model-solution000009.solution b/tests/exhaustive/basic/perms/01_representation/enum/0008_find_permutation_of_int1_4/expected/model-solution000009.solution new file mode 100644 index 0000000000..c0472072bd --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/enum/0008_find_permutation_of_int1_4/expected/model-solution000009.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting p be permutation((E1, E2, E3)) diff --git a/tests/exhaustive/basic/perms/01_representation/enum/0008_find_permutation_of_int1_4/expected/model-solution000010.solution b/tests/exhaustive/basic/perms/01_representation/enum/0008_find_permutation_of_int1_4/expected/model-solution000010.solution new file mode 100644 index 0000000000..302a1d753f --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/enum/0008_find_permutation_of_int1_4/expected/model-solution000010.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting p be permutation((E1, E2, E3, E4)) diff --git a/tests/exhaustive/basic/perms/01_representation/enum/0008_find_permutation_of_int1_4/expected/model-solution000011.solution b/tests/exhaustive/basic/perms/01_representation/enum/0008_find_permutation_of_int1_4/expected/model-solution000011.solution new file mode 100644 index 0000000000..16c9c55d9d --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/enum/0008_find_permutation_of_int1_4/expected/model-solution000011.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting p be permutation((E1, E2, E4, E3)) diff --git a/tests/exhaustive/basic/perms/01_representation/enum/0008_find_permutation_of_int1_4/expected/model-solution000012.solution b/tests/exhaustive/basic/perms/01_representation/enum/0008_find_permutation_of_int1_4/expected/model-solution000012.solution new file mode 100644 index 0000000000..33947cf4e2 --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/enum/0008_find_permutation_of_int1_4/expected/model-solution000012.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting p be permutation((E1, E2, E4)) diff --git a/tests/exhaustive/basic/perms/01_representation/enum/0008_find_permutation_of_int1_4/expected/model-solution000013.solution b/tests/exhaustive/basic/perms/01_representation/enum/0008_find_permutation_of_int1_4/expected/model-solution000013.solution new file mode 100644 index 0000000000..57f20ee7a2 --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/enum/0008_find_permutation_of_int1_4/expected/model-solution000013.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting p be permutation((E1, E3, E2)) diff --git a/tests/exhaustive/basic/perms/01_representation/enum/0008_find_permutation_of_int1_4/expected/model-solution000014.solution b/tests/exhaustive/basic/perms/01_representation/enum/0008_find_permutation_of_int1_4/expected/model-solution000014.solution new file mode 100644 index 0000000000..fbce064674 --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/enum/0008_find_permutation_of_int1_4/expected/model-solution000014.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting p be permutation((E1, E3, E4, E2)) diff --git a/tests/exhaustive/basic/perms/01_representation/enum/0008_find_permutation_of_int1_4/expected/model-solution000015.solution b/tests/exhaustive/basic/perms/01_representation/enum/0008_find_permutation_of_int1_4/expected/model-solution000015.solution new file mode 100644 index 0000000000..bf590b8050 --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/enum/0008_find_permutation_of_int1_4/expected/model-solution000015.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting p be permutation((E1, E3)) diff --git a/tests/exhaustive/basic/perms/01_representation/enum/0008_find_permutation_of_int1_4/expected/model-solution000016.solution b/tests/exhaustive/basic/perms/01_representation/enum/0008_find_permutation_of_int1_4/expected/model-solution000016.solution new file mode 100644 index 0000000000..1652358d75 --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/enum/0008_find_permutation_of_int1_4/expected/model-solution000016.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting p be permutation((E1, E3, E4)) diff --git a/tests/exhaustive/basic/perms/01_representation/enum/0008_find_permutation_of_int1_4/expected/model-solution000017.solution b/tests/exhaustive/basic/perms/01_representation/enum/0008_find_permutation_of_int1_4/expected/model-solution000017.solution new file mode 100644 index 0000000000..5460f2a118 --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/enum/0008_find_permutation_of_int1_4/expected/model-solution000017.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting p be permutation((E1, E3), (E2, E4)) diff --git a/tests/exhaustive/basic/perms/01_representation/enum/0008_find_permutation_of_int1_4/expected/model-solution000018.solution b/tests/exhaustive/basic/perms/01_representation/enum/0008_find_permutation_of_int1_4/expected/model-solution000018.solution new file mode 100644 index 0000000000..ce90f13c1d --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/enum/0008_find_permutation_of_int1_4/expected/model-solution000018.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting p be permutation((E1, E3, E2, E4)) diff --git a/tests/exhaustive/basic/perms/01_representation/enum/0008_find_permutation_of_int1_4/expected/model-solution000019.solution b/tests/exhaustive/basic/perms/01_representation/enum/0008_find_permutation_of_int1_4/expected/model-solution000019.solution new file mode 100644 index 0000000000..56f4d68c62 --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/enum/0008_find_permutation_of_int1_4/expected/model-solution000019.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting p be permutation((E1, E4, E3, E2)) diff --git a/tests/exhaustive/basic/perms/01_representation/enum/0008_find_permutation_of_int1_4/expected/model-solution000020.solution b/tests/exhaustive/basic/perms/01_representation/enum/0008_find_permutation_of_int1_4/expected/model-solution000020.solution new file mode 100644 index 0000000000..75881b0769 --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/enum/0008_find_permutation_of_int1_4/expected/model-solution000020.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting p be permutation((E1, E4, E2)) diff --git a/tests/exhaustive/basic/perms/01_representation/enum/0008_find_permutation_of_int1_4/expected/model-solution000021.solution b/tests/exhaustive/basic/perms/01_representation/enum/0008_find_permutation_of_int1_4/expected/model-solution000021.solution new file mode 100644 index 0000000000..b58f30a6d5 --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/enum/0008_find_permutation_of_int1_4/expected/model-solution000021.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting p be permutation((E1, E4, E3)) diff --git a/tests/exhaustive/basic/perms/01_representation/enum/0008_find_permutation_of_int1_4/expected/model-solution000022.solution b/tests/exhaustive/basic/perms/01_representation/enum/0008_find_permutation_of_int1_4/expected/model-solution000022.solution new file mode 100644 index 0000000000..51581e1b9f --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/enum/0008_find_permutation_of_int1_4/expected/model-solution000022.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting p be permutation((E1, E4)) diff --git a/tests/exhaustive/basic/perms/01_representation/enum/0008_find_permutation_of_int1_4/expected/model-solution000023.solution b/tests/exhaustive/basic/perms/01_representation/enum/0008_find_permutation_of_int1_4/expected/model-solution000023.solution new file mode 100644 index 0000000000..69dc5a4176 --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/enum/0008_find_permutation_of_int1_4/expected/model-solution000023.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting p be permutation((E1, E4, E2, E3)) diff --git a/tests/exhaustive/basic/perms/01_representation/enum/0008_find_permutation_of_int1_4/expected/model-solution000024.solution b/tests/exhaustive/basic/perms/01_representation/enum/0008_find_permutation_of_int1_4/expected/model-solution000024.solution new file mode 100644 index 0000000000..170719569e --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/enum/0008_find_permutation_of_int1_4/expected/model-solution000024.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting p be permutation((E1, E4), (E2, E3)) diff --git a/tests/exhaustive/basic/perms/01_representation/enum/0008_find_permutation_of_int1_4/expected/model.eprime b/tests/exhaustive/basic/perms/01_representation/enum/0008_find_permutation_of_int1_4/expected/model.eprime new file mode 100644 index 0000000000..ac93d552d6 --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/enum/0008_find_permutation_of_int1_4/expected/model.eprime @@ -0,0 +1,8 @@ +language ESSENCE' 1.0 + +find p_PermutationAsFunction_PermutationFunction_Function1D: matrix indexed by [int(1..4)] of int(1..4) +branching on [p_PermutationAsFunction_PermutationFunction_Function1D] +such that + allDiff(p_PermutationAsFunction_PermutationFunction_Function1D), + and([or([p_PermutationAsFunction_PermutationFunction_Function1D[q3] = q2 | q3 : int(1..4)]) | q2 : int(1..4)]) + diff --git a/tests/exhaustive/basic/perms/01_representation/enum/0008_find_permutation_of_int1_4/permutation.essence b/tests/exhaustive/basic/perms/01_representation/enum/0008_find_permutation_of_int1_4/permutation.essence new file mode 100644 index 0000000000..87e671ee38 --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/enum/0008_find_permutation_of_int1_4/permutation.essence @@ -0,0 +1,5 @@ +letting n be new type enum {E1,E2,E3,E4} + +find p : permutation of n + +such that true diff --git a/tests/exhaustive/basic/perms/01_representation/enum/0009_letting_permutation_in_model/expected/model-solution000001.solution b/tests/exhaustive/basic/perms/01_representation/enum/0009_letting_permutation_in_model/expected/model-solution000001.solution new file mode 100644 index 0000000000..fa3c1c5e86 --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/enum/0009_letting_permutation_in_model/expected/model-solution000001.solution @@ -0,0 +1,2 @@ +language Essence 1.3 + diff --git a/tests/exhaustive/basic/perms/01_representation/enum/0009_letting_permutation_in_model/expected/model.eprime b/tests/exhaustive/basic/perms/01_representation/enum/0009_letting_permutation_in_model/expected/model.eprime new file mode 100644 index 0000000000..c64108a295 --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/enum/0009_letting_permutation_in_model/expected/model.eprime @@ -0,0 +1,5 @@ +language ESSENCE' 1.0 + +branching on [] +such that true + diff --git a/tests/exhaustive/basic/perms/01_representation/enum/0009_letting_permutation_in_model/permutation.essence b/tests/exhaustive/basic/perms/01_representation/enum/0009_letting_permutation_in_model/permutation.essence new file mode 100644 index 0000000000..93739e5f4e --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/enum/0009_letting_permutation_in_model/permutation.essence @@ -0,0 +1,4 @@ +letting n be new type enum {E1,E2,E3,E4} +letting p be permutation((E1,E3),(E2,E4)) + +such that true diff --git a/tests/exhaustive/basic/perms/01_representation/enum/0010_find_permutation_maxSize_2_of_int1_3/expected/model-solution000001.solution b/tests/exhaustive/basic/perms/01_representation/enum/0010_find_permutation_maxSize_2_of_int1_3/expected/model-solution000001.solution new file mode 100644 index 0000000000..dec1e69413 --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/enum/0010_find_permutation_maxSize_2_of_int1_3/expected/model-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting p be permutation() diff --git a/tests/exhaustive/basic/perms/01_representation/enum/0010_find_permutation_maxSize_2_of_int1_3/expected/model-solution000002.solution b/tests/exhaustive/basic/perms/01_representation/enum/0010_find_permutation_maxSize_2_of_int1_3/expected/model-solution000002.solution new file mode 100644 index 0000000000..075d779af1 --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/enum/0010_find_permutation_maxSize_2_of_int1_3/expected/model-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting p be permutation((E2, E3)) diff --git a/tests/exhaustive/basic/perms/01_representation/enum/0010_find_permutation_maxSize_2_of_int1_3/expected/model-solution000003.solution b/tests/exhaustive/basic/perms/01_representation/enum/0010_find_permutation_maxSize_2_of_int1_3/expected/model-solution000003.solution new file mode 100644 index 0000000000..3aee0eea27 --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/enum/0010_find_permutation_maxSize_2_of_int1_3/expected/model-solution000003.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting p be permutation((E1, E2)) diff --git a/tests/exhaustive/basic/perms/01_representation/enum/0010_find_permutation_maxSize_2_of_int1_3/expected/model-solution000004.solution b/tests/exhaustive/basic/perms/01_representation/enum/0010_find_permutation_maxSize_2_of_int1_3/expected/model-solution000004.solution new file mode 100644 index 0000000000..bf590b8050 --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/enum/0010_find_permutation_maxSize_2_of_int1_3/expected/model-solution000004.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting p be permutation((E1, E3)) diff --git a/tests/exhaustive/basic/perms/01_representation/enum/0010_find_permutation_maxSize_2_of_int1_3/expected/model.eprime b/tests/exhaustive/basic/perms/01_representation/enum/0010_find_permutation_maxSize_2_of_int1_3/expected/model.eprime new file mode 100644 index 0000000000..95837c9498 --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/enum/0010_find_permutation_maxSize_2_of_int1_3/expected/model.eprime @@ -0,0 +1,9 @@ +language ESSENCE' 1.0 + +find p_PermutationAsFunction_PermutationFunction_Function1D: matrix indexed by [int(1..3)] of int(1..3) +branching on [p_PermutationAsFunction_PermutationFunction_Function1D] +such that + allDiff(p_PermutationAsFunction_PermutationFunction_Function1D), + and([or([p_PermutationAsFunction_PermutationFunction_Function1D[q3] = q2 | q3 : int(1..3)]) | q2 : int(1..3)]), + sum([toInt(q1 != p_PermutationAsFunction_PermutationFunction_Function1D[q1]) | q1 : int(1..3)]) <= 2 + diff --git a/tests/exhaustive/basic/perms/01_representation/enum/0010_find_permutation_maxSize_2_of_int1_3/permutation.essence b/tests/exhaustive/basic/perms/01_representation/enum/0010_find_permutation_maxSize_2_of_int1_3/permutation.essence new file mode 100644 index 0000000000..5e23322970 --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/enum/0010_find_permutation_maxSize_2_of_int1_3/permutation.essence @@ -0,0 +1,5 @@ +letting n be new type enum {E1,E2,E3} + +find p : permutation (maxSize 2) of n + +such that true diff --git a/tests/exhaustive/basic/perms/01_representation/enum/0011_find_permutation_minSize_2_of_int1_3/expected/model-solution000001.solution b/tests/exhaustive/basic/perms/01_representation/enum/0011_find_permutation_minSize_2_of_int1_3/expected/model-solution000001.solution new file mode 100644 index 0000000000..075d779af1 --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/enum/0011_find_permutation_minSize_2_of_int1_3/expected/model-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting p be permutation((E2, E3)) diff --git a/tests/exhaustive/basic/perms/01_representation/enum/0011_find_permutation_minSize_2_of_int1_3/expected/model-solution000002.solution b/tests/exhaustive/basic/perms/01_representation/enum/0011_find_permutation_minSize_2_of_int1_3/expected/model-solution000002.solution new file mode 100644 index 0000000000..3aee0eea27 --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/enum/0011_find_permutation_minSize_2_of_int1_3/expected/model-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting p be permutation((E1, E2)) diff --git a/tests/exhaustive/basic/perms/01_representation/enum/0011_find_permutation_minSize_2_of_int1_3/expected/model-solution000003.solution b/tests/exhaustive/basic/perms/01_representation/enum/0011_find_permutation_minSize_2_of_int1_3/expected/model-solution000003.solution new file mode 100644 index 0000000000..c0472072bd --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/enum/0011_find_permutation_minSize_2_of_int1_3/expected/model-solution000003.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting p be permutation((E1, E2, E3)) diff --git a/tests/exhaustive/basic/perms/01_representation/enum/0011_find_permutation_minSize_2_of_int1_3/expected/model-solution000004.solution b/tests/exhaustive/basic/perms/01_representation/enum/0011_find_permutation_minSize_2_of_int1_3/expected/model-solution000004.solution new file mode 100644 index 0000000000..57f20ee7a2 --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/enum/0011_find_permutation_minSize_2_of_int1_3/expected/model-solution000004.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting p be permutation((E1, E3, E2)) diff --git a/tests/exhaustive/basic/perms/01_representation/enum/0011_find_permutation_minSize_2_of_int1_3/expected/model-solution000005.solution b/tests/exhaustive/basic/perms/01_representation/enum/0011_find_permutation_minSize_2_of_int1_3/expected/model-solution000005.solution new file mode 100644 index 0000000000..bf590b8050 --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/enum/0011_find_permutation_minSize_2_of_int1_3/expected/model-solution000005.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting p be permutation((E1, E3)) diff --git a/tests/exhaustive/basic/perms/01_representation/enum/0011_find_permutation_minSize_2_of_int1_3/expected/model.eprime b/tests/exhaustive/basic/perms/01_representation/enum/0011_find_permutation_minSize_2_of_int1_3/expected/model.eprime new file mode 100644 index 0000000000..7854912481 --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/enum/0011_find_permutation_minSize_2_of_int1_3/expected/model.eprime @@ -0,0 +1,9 @@ +language ESSENCE' 1.0 + +find p_PermutationAsFunction_PermutationFunction_Function1D: matrix indexed by [int(1..3)] of int(1..3) +branching on [p_PermutationAsFunction_PermutationFunction_Function1D] +such that + allDiff(p_PermutationAsFunction_PermutationFunction_Function1D), + and([or([p_PermutationAsFunction_PermutationFunction_Function1D[q3] = q2 | q3 : int(1..3)]) | q2 : int(1..3)]), + 2 <= sum([toInt(q1 != p_PermutationAsFunction_PermutationFunction_Function1D[q1]) | q1 : int(1..3)]) + diff --git a/tests/exhaustive/basic/perms/01_representation/enum/0011_find_permutation_minSize_2_of_int1_3/permutation.essence b/tests/exhaustive/basic/perms/01_representation/enum/0011_find_permutation_minSize_2_of_int1_3/permutation.essence new file mode 100644 index 0000000000..3da37a3987 --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/enum/0011_find_permutation_minSize_2_of_int1_3/permutation.essence @@ -0,0 +1,5 @@ +letting n be new type enum {E1,E2,E3} + +find p : permutation (minSize 2) of n + +such that true diff --git a/tests/exhaustive/basic/perms/01_representation/enum/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model-solution000001.solution b/tests/exhaustive/basic/perms/01_representation/enum/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model-solution000001.solution new file mode 100644 index 0000000000..e84be5d054 --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/enum/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting p be permutation((E3, E4)) diff --git a/tests/exhaustive/basic/perms/01_representation/enum/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model-solution000002.solution b/tests/exhaustive/basic/perms/01_representation/enum/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model-solution000002.solution new file mode 100644 index 0000000000..075d779af1 --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/enum/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting p be permutation((E2, E3)) diff --git a/tests/exhaustive/basic/perms/01_representation/enum/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model-solution000003.solution b/tests/exhaustive/basic/perms/01_representation/enum/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model-solution000003.solution new file mode 100644 index 0000000000..10f28984f9 --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/enum/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model-solution000003.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting p be permutation((E2, E3, E4)) diff --git a/tests/exhaustive/basic/perms/01_representation/enum/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model-solution000004.solution b/tests/exhaustive/basic/perms/01_representation/enum/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model-solution000004.solution new file mode 100644 index 0000000000..629ad61397 --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/enum/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model-solution000004.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting p be permutation((E2, E4, E3)) diff --git a/tests/exhaustive/basic/perms/01_representation/enum/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model-solution000005.solution b/tests/exhaustive/basic/perms/01_representation/enum/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model-solution000005.solution new file mode 100644 index 0000000000..bf4b6b916a --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/enum/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model-solution000005.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting p be permutation((E2, E4)) diff --git a/tests/exhaustive/basic/perms/01_representation/enum/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model-solution000006.solution b/tests/exhaustive/basic/perms/01_representation/enum/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model-solution000006.solution new file mode 100644 index 0000000000..3aee0eea27 --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/enum/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model-solution000006.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting p be permutation((E1, E2)) diff --git a/tests/exhaustive/basic/perms/01_representation/enum/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model-solution000007.solution b/tests/exhaustive/basic/perms/01_representation/enum/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model-solution000007.solution new file mode 100644 index 0000000000..c0472072bd --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/enum/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model-solution000007.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting p be permutation((E1, E2, E3)) diff --git a/tests/exhaustive/basic/perms/01_representation/enum/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model-solution000008.solution b/tests/exhaustive/basic/perms/01_representation/enum/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model-solution000008.solution new file mode 100644 index 0000000000..33947cf4e2 --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/enum/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model-solution000008.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting p be permutation((E1, E2, E4)) diff --git a/tests/exhaustive/basic/perms/01_representation/enum/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model-solution000009.solution b/tests/exhaustive/basic/perms/01_representation/enum/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model-solution000009.solution new file mode 100644 index 0000000000..57f20ee7a2 --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/enum/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model-solution000009.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting p be permutation((E1, E3, E2)) diff --git a/tests/exhaustive/basic/perms/01_representation/enum/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model-solution000010.solution b/tests/exhaustive/basic/perms/01_representation/enum/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model-solution000010.solution new file mode 100644 index 0000000000..bf590b8050 --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/enum/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model-solution000010.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting p be permutation((E1, E3)) diff --git a/tests/exhaustive/basic/perms/01_representation/enum/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model-solution000011.solution b/tests/exhaustive/basic/perms/01_representation/enum/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model-solution000011.solution new file mode 100644 index 0000000000..1652358d75 --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/enum/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model-solution000011.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting p be permutation((E1, E3, E4)) diff --git a/tests/exhaustive/basic/perms/01_representation/enum/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model-solution000012.solution b/tests/exhaustive/basic/perms/01_representation/enum/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model-solution000012.solution new file mode 100644 index 0000000000..75881b0769 --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/enum/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model-solution000012.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting p be permutation((E1, E4, E2)) diff --git a/tests/exhaustive/basic/perms/01_representation/enum/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model-solution000013.solution b/tests/exhaustive/basic/perms/01_representation/enum/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model-solution000013.solution new file mode 100644 index 0000000000..b58f30a6d5 --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/enum/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model-solution000013.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting p be permutation((E1, E4, E3)) diff --git a/tests/exhaustive/basic/perms/01_representation/enum/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model-solution000014.solution b/tests/exhaustive/basic/perms/01_representation/enum/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model-solution000014.solution new file mode 100644 index 0000000000..51581e1b9f --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/enum/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model-solution000014.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting p be permutation((E1, E4)) diff --git a/tests/exhaustive/basic/perms/01_representation/enum/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model.eprime b/tests/exhaustive/basic/perms/01_representation/enum/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model.eprime new file mode 100644 index 0000000000..4292a59345 --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/enum/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model.eprime @@ -0,0 +1,10 @@ +language ESSENCE' 1.0 + +find p_PermutationAsFunction_PermutationFunction_Function1D: matrix indexed by [int(1..4)] of int(1..4) +branching on [p_PermutationAsFunction_PermutationFunction_Function1D] +such that + allDiff(p_PermutationAsFunction_PermutationFunction_Function1D), + and([or([p_PermutationAsFunction_PermutationFunction_Function1D[q3] = q2 | q3 : int(1..4)]) | q2 : int(1..4)]), + 2 <= sum([toInt(q1 != p_PermutationAsFunction_PermutationFunction_Function1D[q1]) | q1 : int(1..4)]), + sum([toInt(q1 != p_PermutationAsFunction_PermutationFunction_Function1D[q1]) | q1 : int(1..4)]) <= 3 + diff --git a/tests/exhaustive/basic/perms/01_representation/enum/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/permutation.essence b/tests/exhaustive/basic/perms/01_representation/enum/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/permutation.essence new file mode 100644 index 0000000000..6fc7ffd73a --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/enum/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/permutation.essence @@ -0,0 +1,5 @@ +letting n be new type enum {E1,E2,E3,E4} + +find p : permutation (minSize 2, maxSize 3) of n + +such that true diff --git a/tests/exhaustive/basic/perms/01_representation/int/0001_given_permutation_in_param/expected/model-permutation-solution000001.solution b/tests/exhaustive/basic/perms/01_representation/int/0001_given_permutation_in_param/expected/model-permutation-solution000001.solution new file mode 100644 index 0000000000..fa3c1c5e86 --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/int/0001_given_permutation_in_param/expected/model-permutation-solution000001.solution @@ -0,0 +1,2 @@ +language Essence 1.3 + diff --git a/tests/exhaustive/basic/perms/01_representation/int/0001_given_permutation_in_param/expected/model-permutation.eprime-param b/tests/exhaustive/basic/perms/01_representation/int/0001_given_permutation_in_param/expected/model-permutation.eprime-param new file mode 100644 index 0000000000..c2bddee0e8 --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/int/0001_given_permutation_in_param/expected/model-permutation.eprime-param @@ -0,0 +1,3 @@ +language ESSENCE' 1.0 + +letting p_PermutationAsFunction_PermutationFunction_Function1D be [3, 2, 4, 1; int(1..4)] diff --git a/tests/exhaustive/basic/perms/01_representation/int/0001_given_permutation_in_param/expected/model.eprime b/tests/exhaustive/basic/perms/01_representation/int/0001_given_permutation_in_param/expected/model.eprime new file mode 100644 index 0000000000..cc4c1dfa5f --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/int/0001_given_permutation_in_param/expected/model.eprime @@ -0,0 +1,6 @@ +language ESSENCE' 1.0 + +given p_PermutationAsFunction_PermutationFunction_Function1D: matrix indexed by [int(1..4)] of int(1..4) +branching on [] +such that true + diff --git a/tests/exhaustive/basic/perms/01_representation/int/0001_given_permutation_in_param/permutation.essence b/tests/exhaustive/basic/perms/01_representation/int/0001_given_permutation_in_param/permutation.essence new file mode 100644 index 0000000000..ec84d3ae7d --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/int/0001_given_permutation_in_param/permutation.essence @@ -0,0 +1,9 @@ +letting n be 4 + +given p : permutation of int(1..n) + +such that true + + + + diff --git a/tests/exhaustive/basic/perms/01_representation/int/0001_given_permutation_in_param/permutation.param b/tests/exhaustive/basic/perms/01_representation/int/0001_given_permutation_in_param/permutation.param new file mode 100644 index 0000000000..8a8c516801 --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/int/0001_given_permutation_in_param/permutation.param @@ -0,0 +1 @@ +letting p be permutation((1,3,4)) diff --git a/tests/exhaustive/basic/perms/01_representation/int/0002_given_permutation_in_param/expected/model-permutation-solution000001.solution b/tests/exhaustive/basic/perms/01_representation/int/0002_given_permutation_in_param/expected/model-permutation-solution000001.solution new file mode 100644 index 0000000000..fa3c1c5e86 --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/int/0002_given_permutation_in_param/expected/model-permutation-solution000001.solution @@ -0,0 +1,2 @@ +language Essence 1.3 + diff --git a/tests/exhaustive/basic/perms/01_representation/int/0002_given_permutation_in_param/expected/model-permutation.eprime-param b/tests/exhaustive/basic/perms/01_representation/int/0002_given_permutation_in_param/expected/model-permutation.eprime-param new file mode 100644 index 0000000000..7e9e727085 --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/int/0002_given_permutation_in_param/expected/model-permutation.eprime-param @@ -0,0 +1,3 @@ +language ESSENCE' 1.0 + +letting p_PermutationAsFunction_PermutationFunction_Function1D be [3, 1, 2; int(1..3)] diff --git a/tests/exhaustive/basic/perms/01_representation/int/0002_given_permutation_in_param/expected/model.eprime b/tests/exhaustive/basic/perms/01_representation/int/0002_given_permutation_in_param/expected/model.eprime new file mode 100644 index 0000000000..b1234f8b14 --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/int/0002_given_permutation_in_param/expected/model.eprime @@ -0,0 +1,6 @@ +language ESSENCE' 1.0 + +given p_PermutationAsFunction_PermutationFunction_Function1D: matrix indexed by [int(1..3)] of int(1..3) +branching on [] +such that true + diff --git a/tests/exhaustive/basic/perms/01_representation/int/0002_given_permutation_in_param/permutation.essence b/tests/exhaustive/basic/perms/01_representation/int/0002_given_permutation_in_param/permutation.essence new file mode 100644 index 0000000000..4d613e1dc6 --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/int/0002_given_permutation_in_param/permutation.essence @@ -0,0 +1,5 @@ +letting n be 3 + +given p : permutation of int(1..n) + +such that true diff --git a/tests/exhaustive/basic/perms/01_representation/int/0002_given_permutation_in_param/permutation.param b/tests/exhaustive/basic/perms/01_representation/int/0002_given_permutation_in_param/permutation.param new file mode 100644 index 0000000000..2099896d75 --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/int/0002_given_permutation_in_param/permutation.param @@ -0,0 +1 @@ +letting p be permutation((1,3,2)) diff --git a/tests/exhaustive/basic/perms/01_representation/int/0003_given_permutation_in_param_2_cycle/expected/model-permutation-solution000001.solution b/tests/exhaustive/basic/perms/01_representation/int/0003_given_permutation_in_param_2_cycle/expected/model-permutation-solution000001.solution new file mode 100644 index 0000000000..fa3c1c5e86 --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/int/0003_given_permutation_in_param_2_cycle/expected/model-permutation-solution000001.solution @@ -0,0 +1,2 @@ +language Essence 1.3 + diff --git a/tests/exhaustive/basic/perms/01_representation/int/0003_given_permutation_in_param_2_cycle/expected/model-permutation.eprime-param b/tests/exhaustive/basic/perms/01_representation/int/0003_given_permutation_in_param_2_cycle/expected/model-permutation.eprime-param new file mode 100644 index 0000000000..3cc48acd18 --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/int/0003_given_permutation_in_param_2_cycle/expected/model-permutation.eprime-param @@ -0,0 +1,3 @@ +language ESSENCE' 1.0 + +letting p_PermutationAsFunction_PermutationFunction_Function1D be [3, 4, 1, 2; int(1..4)] diff --git a/tests/exhaustive/basic/perms/01_representation/int/0003_given_permutation_in_param_2_cycle/expected/model.eprime b/tests/exhaustive/basic/perms/01_representation/int/0003_given_permutation_in_param_2_cycle/expected/model.eprime new file mode 100644 index 0000000000..cc4c1dfa5f --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/int/0003_given_permutation_in_param_2_cycle/expected/model.eprime @@ -0,0 +1,6 @@ +language ESSENCE' 1.0 + +given p_PermutationAsFunction_PermutationFunction_Function1D: matrix indexed by [int(1..4)] of int(1..4) +branching on [] +such that true + diff --git a/tests/exhaustive/basic/perms/01_representation/int/0003_given_permutation_in_param_2_cycle/permutation.essence b/tests/exhaustive/basic/perms/01_representation/int/0003_given_permutation_in_param_2_cycle/permutation.essence new file mode 100644 index 0000000000..fff346c07e --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/int/0003_given_permutation_in_param_2_cycle/permutation.essence @@ -0,0 +1,5 @@ +letting n be 4 + +given p : permutation of int(1..n) + +such that true diff --git a/tests/exhaustive/basic/perms/01_representation/int/0003_given_permutation_in_param_2_cycle/permutation.param b/tests/exhaustive/basic/perms/01_representation/int/0003_given_permutation_in_param_2_cycle/permutation.param new file mode 100644 index 0000000000..a862179e25 --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/int/0003_given_permutation_in_param_2_cycle/permutation.param @@ -0,0 +1 @@ +letting p be permutation((1,3),(2,4)) diff --git a/tests/exhaustive/basic/perms/01_representation/int/0004_given_permutation_in_param_2_cycle/expected/model-permutation-solution000001.solution b/tests/exhaustive/basic/perms/01_representation/int/0004_given_permutation_in_param_2_cycle/expected/model-permutation-solution000001.solution new file mode 100644 index 0000000000..fa3c1c5e86 --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/int/0004_given_permutation_in_param_2_cycle/expected/model-permutation-solution000001.solution @@ -0,0 +1,2 @@ +language Essence 1.3 + diff --git a/tests/exhaustive/basic/perms/01_representation/int/0004_given_permutation_in_param_2_cycle/expected/model-permutation.eprime-param b/tests/exhaustive/basic/perms/01_representation/int/0004_given_permutation_in_param_2_cycle/expected/model-permutation.eprime-param new file mode 100644 index 0000000000..3cc48acd18 --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/int/0004_given_permutation_in_param_2_cycle/expected/model-permutation.eprime-param @@ -0,0 +1,3 @@ +language ESSENCE' 1.0 + +letting p_PermutationAsFunction_PermutationFunction_Function1D be [3, 4, 1, 2; int(1..4)] diff --git a/tests/exhaustive/basic/perms/01_representation/int/0004_given_permutation_in_param_2_cycle/expected/model.eprime b/tests/exhaustive/basic/perms/01_representation/int/0004_given_permutation_in_param_2_cycle/expected/model.eprime new file mode 100644 index 0000000000..cc4c1dfa5f --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/int/0004_given_permutation_in_param_2_cycle/expected/model.eprime @@ -0,0 +1,6 @@ +language ESSENCE' 1.0 + +given p_PermutationAsFunction_PermutationFunction_Function1D: matrix indexed by [int(1..4)] of int(1..4) +branching on [] +such that true + diff --git a/tests/exhaustive/basic/perms/01_representation/int/0004_given_permutation_in_param_2_cycle/permutation.essence b/tests/exhaustive/basic/perms/01_representation/int/0004_given_permutation_in_param_2_cycle/permutation.essence new file mode 100644 index 0000000000..fff346c07e --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/int/0004_given_permutation_in_param_2_cycle/permutation.essence @@ -0,0 +1,5 @@ +letting n be 4 + +given p : permutation of int(1..n) + +such that true diff --git a/tests/exhaustive/basic/perms/01_representation/int/0004_given_permutation_in_param_2_cycle/permutation.param b/tests/exhaustive/basic/perms/01_representation/int/0004_given_permutation_in_param_2_cycle/permutation.param new file mode 100644 index 0000000000..a862179e25 --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/int/0004_given_permutation_in_param_2_cycle/permutation.param @@ -0,0 +1 @@ +letting p be permutation((1,3),(2,4)) diff --git a/tests/exhaustive/basic/perms/01_representation/int/0005_find_permutation_size_4_of_int1_4/expected/model-solution000001.solution b/tests/exhaustive/basic/perms/01_representation/int/0005_find_permutation_size_4_of_int1_4/expected/model-solution000001.solution new file mode 100644 index 0000000000..e34d3d53fa --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/int/0005_find_permutation_size_4_of_int1_4/expected/model-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4)) diff --git a/tests/exhaustive/basic/perms/01_representation/int/0005_find_permutation_size_4_of_int1_4/expected/model-solution000002.solution b/tests/exhaustive/basic/perms/01_representation/int/0005_find_permutation_size_4_of_int1_4/expected/model-solution000002.solution new file mode 100644 index 0000000000..34d90c14ce --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/int/0005_find_permutation_size_4_of_int1_4/expected/model-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting p be permutation((1, 2, 3, 4)) diff --git a/tests/exhaustive/basic/perms/01_representation/int/0005_find_permutation_size_4_of_int1_4/expected/model-solution000003.solution b/tests/exhaustive/basic/perms/01_representation/int/0005_find_permutation_size_4_of_int1_4/expected/model-solution000003.solution new file mode 100644 index 0000000000..eb85686411 --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/int/0005_find_permutation_size_4_of_int1_4/expected/model-solution000003.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting p be permutation((1, 2, 4, 3)) diff --git a/tests/exhaustive/basic/perms/01_representation/int/0005_find_permutation_size_4_of_int1_4/expected/model-solution000004.solution b/tests/exhaustive/basic/perms/01_representation/int/0005_find_permutation_size_4_of_int1_4/expected/model-solution000004.solution new file mode 100644 index 0000000000..73c67f18ea --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/int/0005_find_permutation_size_4_of_int1_4/expected/model-solution000004.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting p be permutation((1, 3, 4, 2)) diff --git a/tests/exhaustive/basic/perms/01_representation/int/0005_find_permutation_size_4_of_int1_4/expected/model-solution000005.solution b/tests/exhaustive/basic/perms/01_representation/int/0005_find_permutation_size_4_of_int1_4/expected/model-solution000005.solution new file mode 100644 index 0000000000..3076e7fd39 --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/int/0005_find_permutation_size_4_of_int1_4/expected/model-solution000005.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting p be permutation((1, 3), (2, 4)) diff --git a/tests/exhaustive/basic/perms/01_representation/int/0005_find_permutation_size_4_of_int1_4/expected/model-solution000006.solution b/tests/exhaustive/basic/perms/01_representation/int/0005_find_permutation_size_4_of_int1_4/expected/model-solution000006.solution new file mode 100644 index 0000000000..cc91ad3bcf --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/int/0005_find_permutation_size_4_of_int1_4/expected/model-solution000006.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting p be permutation((1, 3, 2, 4)) diff --git a/tests/exhaustive/basic/perms/01_representation/int/0005_find_permutation_size_4_of_int1_4/expected/model-solution000007.solution b/tests/exhaustive/basic/perms/01_representation/int/0005_find_permutation_size_4_of_int1_4/expected/model-solution000007.solution new file mode 100644 index 0000000000..8d38e068ea --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/int/0005_find_permutation_size_4_of_int1_4/expected/model-solution000007.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting p be permutation((1, 4, 3, 2)) diff --git a/tests/exhaustive/basic/perms/01_representation/int/0005_find_permutation_size_4_of_int1_4/expected/model-solution000008.solution b/tests/exhaustive/basic/perms/01_representation/int/0005_find_permutation_size_4_of_int1_4/expected/model-solution000008.solution new file mode 100644 index 0000000000..232587b457 --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/int/0005_find_permutation_size_4_of_int1_4/expected/model-solution000008.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting p be permutation((1, 4, 2, 3)) diff --git a/tests/exhaustive/basic/perms/01_representation/int/0005_find_permutation_size_4_of_int1_4/expected/model-solution000009.solution b/tests/exhaustive/basic/perms/01_representation/int/0005_find_permutation_size_4_of_int1_4/expected/model-solution000009.solution new file mode 100644 index 0000000000..03e66bf271 --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/int/0005_find_permutation_size_4_of_int1_4/expected/model-solution000009.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting p be permutation((1, 4), (2, 3)) diff --git a/tests/exhaustive/basic/perms/01_representation/int/0005_find_permutation_size_4_of_int1_4/expected/model.eprime b/tests/exhaustive/basic/perms/01_representation/int/0005_find_permutation_size_4_of_int1_4/expected/model.eprime new file mode 100644 index 0000000000..661a61e88f --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/int/0005_find_permutation_size_4_of_int1_4/expected/model.eprime @@ -0,0 +1,10 @@ +language ESSENCE' 1.0 + +letting n be 4 +find p_PermutationAsFunction_PermutationFunction_Function1D: matrix indexed by [int(1..4)] of int(1..4) +branching on [p_PermutationAsFunction_PermutationFunction_Function1D] +such that + allDiff(p_PermutationAsFunction_PermutationFunction_Function1D), + and([or([p_PermutationAsFunction_PermutationFunction_Function1D[q3] = q2 | q3 : int(1..4)]) | q2 : int(1..4)]), + 4 = sum([toInt(q1 != p_PermutationAsFunction_PermutationFunction_Function1D[q1]) | q1 : int(1..4)]) + diff --git a/tests/exhaustive/basic/perms/01_representation/int/0005_find_permutation_size_4_of_int1_4/permutation.essence b/tests/exhaustive/basic/perms/01_representation/int/0005_find_permutation_size_4_of_int1_4/permutation.essence new file mode 100644 index 0000000000..63899fe581 --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/int/0005_find_permutation_size_4_of_int1_4/permutation.essence @@ -0,0 +1,5 @@ +letting n be 4 + +find p : permutation (size n) of int(1..n) + +such that true diff --git a/tests/exhaustive/basic/perms/01_representation/int/0006_find_permutation_size_0_of_int1_4/expected/model-solution000001.solution b/tests/exhaustive/basic/perms/01_representation/int/0006_find_permutation_size_0_of_int1_4/expected/model-solution000001.solution new file mode 100644 index 0000000000..dec1e69413 --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/int/0006_find_permutation_size_0_of_int1_4/expected/model-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting p be permutation() diff --git a/tests/exhaustive/basic/perms/01_representation/int/0006_find_permutation_size_0_of_int1_4/expected/model.eprime b/tests/exhaustive/basic/perms/01_representation/int/0006_find_permutation_size_0_of_int1_4/expected/model.eprime new file mode 100644 index 0000000000..e95d7701bd --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/int/0006_find_permutation_size_0_of_int1_4/expected/model.eprime @@ -0,0 +1,10 @@ +language ESSENCE' 1.0 + +letting n be 4 +find p_PermutationAsFunction_PermutationFunction_Function1D: matrix indexed by [int(1..4)] of int(1..4) +branching on [p_PermutationAsFunction_PermutationFunction_Function1D] +such that + allDiff(p_PermutationAsFunction_PermutationFunction_Function1D), + and([or([p_PermutationAsFunction_PermutationFunction_Function1D[q3] = q2 | q3 : int(1..4)]) | q2 : int(1..4)]), + 0 = sum([toInt(q1 != p_PermutationAsFunction_PermutationFunction_Function1D[q1]) | q1 : int(1..4)]) + diff --git a/tests/exhaustive/basic/perms/01_representation/int/0006_find_permutation_size_0_of_int1_4/permutation.essence b/tests/exhaustive/basic/perms/01_representation/int/0006_find_permutation_size_0_of_int1_4/permutation.essence new file mode 100644 index 0000000000..8c60c7b839 --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/int/0006_find_permutation_size_0_of_int1_4/permutation.essence @@ -0,0 +1,5 @@ +letting n be 4 + +find p : permutation (size 0) of int(1..n) + +such that true diff --git a/tests/exhaustive/basic/perms/01_representation/int/0007_letting_permutation_be_empty/expected/model-solution000001.solution b/tests/exhaustive/basic/perms/01_representation/int/0007_letting_permutation_be_empty/expected/model-solution000001.solution new file mode 100644 index 0000000000..fa3c1c5e86 --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/int/0007_letting_permutation_be_empty/expected/model-solution000001.solution @@ -0,0 +1,2 @@ +language Essence 1.3 + diff --git a/tests/exhaustive/basic/perms/01_representation/int/0007_letting_permutation_be_empty/expected/model.eprime b/tests/exhaustive/basic/perms/01_representation/int/0007_letting_permutation_be_empty/expected/model.eprime new file mode 100644 index 0000000000..c64108a295 --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/int/0007_letting_permutation_be_empty/expected/model.eprime @@ -0,0 +1,5 @@ +language ESSENCE' 1.0 + +branching on [] +such that true + diff --git a/tests/exhaustive/basic/perms/01_representation/int/0007_letting_permutation_be_empty/permutation.essence b/tests/exhaustive/basic/perms/01_representation/int/0007_letting_permutation_be_empty/permutation.essence new file mode 100644 index 0000000000..a39f3ae0b1 --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/int/0007_letting_permutation_be_empty/permutation.essence @@ -0,0 +1,3 @@ +letting p be permutation() + +such that true diff --git a/tests/exhaustive/basic/perms/01_representation/int/0008_find_permutation_of_int1_4/expected/model-solution000001.solution b/tests/exhaustive/basic/perms/01_representation/int/0008_find_permutation_of_int1_4/expected/model-solution000001.solution new file mode 100644 index 0000000000..dec1e69413 --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/int/0008_find_permutation_of_int1_4/expected/model-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting p be permutation() diff --git a/tests/exhaustive/basic/perms/01_representation/int/0008_find_permutation_of_int1_4/expected/model-solution000002.solution b/tests/exhaustive/basic/perms/01_representation/int/0008_find_permutation_of_int1_4/expected/model-solution000002.solution new file mode 100644 index 0000000000..c191faffa1 --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/int/0008_find_permutation_of_int1_4/expected/model-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting p be permutation((3, 4)) diff --git a/tests/exhaustive/basic/perms/01_representation/int/0008_find_permutation_of_int1_4/expected/model-solution000003.solution b/tests/exhaustive/basic/perms/01_representation/int/0008_find_permutation_of_int1_4/expected/model-solution000003.solution new file mode 100644 index 0000000000..605f7ec490 --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/int/0008_find_permutation_of_int1_4/expected/model-solution000003.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting p be permutation((2, 3)) diff --git a/tests/exhaustive/basic/perms/01_representation/int/0008_find_permutation_of_int1_4/expected/model-solution000004.solution b/tests/exhaustive/basic/perms/01_representation/int/0008_find_permutation_of_int1_4/expected/model-solution000004.solution new file mode 100644 index 0000000000..0349e8bfc1 --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/int/0008_find_permutation_of_int1_4/expected/model-solution000004.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting p be permutation((2, 3, 4)) diff --git a/tests/exhaustive/basic/perms/01_representation/int/0008_find_permutation_of_int1_4/expected/model-solution000005.solution b/tests/exhaustive/basic/perms/01_representation/int/0008_find_permutation_of_int1_4/expected/model-solution000005.solution new file mode 100644 index 0000000000..7f3ffab396 --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/int/0008_find_permutation_of_int1_4/expected/model-solution000005.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting p be permutation((2, 4, 3)) diff --git a/tests/exhaustive/basic/perms/01_representation/int/0008_find_permutation_of_int1_4/expected/model-solution000006.solution b/tests/exhaustive/basic/perms/01_representation/int/0008_find_permutation_of_int1_4/expected/model-solution000006.solution new file mode 100644 index 0000000000..4aa2acf568 --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/int/0008_find_permutation_of_int1_4/expected/model-solution000006.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting p be permutation((2, 4)) diff --git a/tests/exhaustive/basic/perms/01_representation/int/0008_find_permutation_of_int1_4/expected/model-solution000007.solution b/tests/exhaustive/basic/perms/01_representation/int/0008_find_permutation_of_int1_4/expected/model-solution000007.solution new file mode 100644 index 0000000000..bce4d1fc90 --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/int/0008_find_permutation_of_int1_4/expected/model-solution000007.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting p be permutation((1, 2)) diff --git a/tests/exhaustive/basic/perms/01_representation/int/0008_find_permutation_of_int1_4/expected/model-solution000008.solution b/tests/exhaustive/basic/perms/01_representation/int/0008_find_permutation_of_int1_4/expected/model-solution000008.solution new file mode 100644 index 0000000000..e34d3d53fa --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/int/0008_find_permutation_of_int1_4/expected/model-solution000008.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4)) diff --git a/tests/exhaustive/basic/perms/01_representation/int/0008_find_permutation_of_int1_4/expected/model-solution000009.solution b/tests/exhaustive/basic/perms/01_representation/int/0008_find_permutation_of_int1_4/expected/model-solution000009.solution new file mode 100644 index 0000000000..ae8af1a204 --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/int/0008_find_permutation_of_int1_4/expected/model-solution000009.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting p be permutation((1, 2, 3)) diff --git a/tests/exhaustive/basic/perms/01_representation/int/0008_find_permutation_of_int1_4/expected/model-solution000010.solution b/tests/exhaustive/basic/perms/01_representation/int/0008_find_permutation_of_int1_4/expected/model-solution000010.solution new file mode 100644 index 0000000000..34d90c14ce --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/int/0008_find_permutation_of_int1_4/expected/model-solution000010.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting p be permutation((1, 2, 3, 4)) diff --git a/tests/exhaustive/basic/perms/01_representation/int/0008_find_permutation_of_int1_4/expected/model-solution000011.solution b/tests/exhaustive/basic/perms/01_representation/int/0008_find_permutation_of_int1_4/expected/model-solution000011.solution new file mode 100644 index 0000000000..eb85686411 --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/int/0008_find_permutation_of_int1_4/expected/model-solution000011.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting p be permutation((1, 2, 4, 3)) diff --git a/tests/exhaustive/basic/perms/01_representation/int/0008_find_permutation_of_int1_4/expected/model-solution000012.solution b/tests/exhaustive/basic/perms/01_representation/int/0008_find_permutation_of_int1_4/expected/model-solution000012.solution new file mode 100644 index 0000000000..3fba79788b --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/int/0008_find_permutation_of_int1_4/expected/model-solution000012.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting p be permutation((1, 2, 4)) diff --git a/tests/exhaustive/basic/perms/01_representation/int/0008_find_permutation_of_int1_4/expected/model-solution000013.solution b/tests/exhaustive/basic/perms/01_representation/int/0008_find_permutation_of_int1_4/expected/model-solution000013.solution new file mode 100644 index 0000000000..899856556b --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/int/0008_find_permutation_of_int1_4/expected/model-solution000013.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting p be permutation((1, 3, 2)) diff --git a/tests/exhaustive/basic/perms/01_representation/int/0008_find_permutation_of_int1_4/expected/model-solution000014.solution b/tests/exhaustive/basic/perms/01_representation/int/0008_find_permutation_of_int1_4/expected/model-solution000014.solution new file mode 100644 index 0000000000..73c67f18ea --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/int/0008_find_permutation_of_int1_4/expected/model-solution000014.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting p be permutation((1, 3, 4, 2)) diff --git a/tests/exhaustive/basic/perms/01_representation/int/0008_find_permutation_of_int1_4/expected/model-solution000015.solution b/tests/exhaustive/basic/perms/01_representation/int/0008_find_permutation_of_int1_4/expected/model-solution000015.solution new file mode 100644 index 0000000000..12c2330c06 --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/int/0008_find_permutation_of_int1_4/expected/model-solution000015.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting p be permutation((1, 3)) diff --git a/tests/exhaustive/basic/perms/01_representation/int/0008_find_permutation_of_int1_4/expected/model-solution000016.solution b/tests/exhaustive/basic/perms/01_representation/int/0008_find_permutation_of_int1_4/expected/model-solution000016.solution new file mode 100644 index 0000000000..8710a5d0ae --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/int/0008_find_permutation_of_int1_4/expected/model-solution000016.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting p be permutation((1, 3, 4)) diff --git a/tests/exhaustive/basic/perms/01_representation/int/0008_find_permutation_of_int1_4/expected/model-solution000017.solution b/tests/exhaustive/basic/perms/01_representation/int/0008_find_permutation_of_int1_4/expected/model-solution000017.solution new file mode 100644 index 0000000000..3076e7fd39 --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/int/0008_find_permutation_of_int1_4/expected/model-solution000017.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting p be permutation((1, 3), (2, 4)) diff --git a/tests/exhaustive/basic/perms/01_representation/int/0008_find_permutation_of_int1_4/expected/model-solution000018.solution b/tests/exhaustive/basic/perms/01_representation/int/0008_find_permutation_of_int1_4/expected/model-solution000018.solution new file mode 100644 index 0000000000..cc91ad3bcf --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/int/0008_find_permutation_of_int1_4/expected/model-solution000018.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting p be permutation((1, 3, 2, 4)) diff --git a/tests/exhaustive/basic/perms/01_representation/int/0008_find_permutation_of_int1_4/expected/model-solution000019.solution b/tests/exhaustive/basic/perms/01_representation/int/0008_find_permutation_of_int1_4/expected/model-solution000019.solution new file mode 100644 index 0000000000..8d38e068ea --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/int/0008_find_permutation_of_int1_4/expected/model-solution000019.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting p be permutation((1, 4, 3, 2)) diff --git a/tests/exhaustive/basic/perms/01_representation/int/0008_find_permutation_of_int1_4/expected/model-solution000020.solution b/tests/exhaustive/basic/perms/01_representation/int/0008_find_permutation_of_int1_4/expected/model-solution000020.solution new file mode 100644 index 0000000000..72a96ad1f9 --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/int/0008_find_permutation_of_int1_4/expected/model-solution000020.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting p be permutation((1, 4, 2)) diff --git a/tests/exhaustive/basic/perms/01_representation/int/0008_find_permutation_of_int1_4/expected/model-solution000021.solution b/tests/exhaustive/basic/perms/01_representation/int/0008_find_permutation_of_int1_4/expected/model-solution000021.solution new file mode 100644 index 0000000000..23fcbc89f7 --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/int/0008_find_permutation_of_int1_4/expected/model-solution000021.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting p be permutation((1, 4, 3)) diff --git a/tests/exhaustive/basic/perms/01_representation/int/0008_find_permutation_of_int1_4/expected/model-solution000022.solution b/tests/exhaustive/basic/perms/01_representation/int/0008_find_permutation_of_int1_4/expected/model-solution000022.solution new file mode 100644 index 0000000000..829b355a1f --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/int/0008_find_permutation_of_int1_4/expected/model-solution000022.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting p be permutation((1, 4)) diff --git a/tests/exhaustive/basic/perms/01_representation/int/0008_find_permutation_of_int1_4/expected/model-solution000023.solution b/tests/exhaustive/basic/perms/01_representation/int/0008_find_permutation_of_int1_4/expected/model-solution000023.solution new file mode 100644 index 0000000000..232587b457 --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/int/0008_find_permutation_of_int1_4/expected/model-solution000023.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting p be permutation((1, 4, 2, 3)) diff --git a/tests/exhaustive/basic/perms/01_representation/int/0008_find_permutation_of_int1_4/expected/model-solution000024.solution b/tests/exhaustive/basic/perms/01_representation/int/0008_find_permutation_of_int1_4/expected/model-solution000024.solution new file mode 100644 index 0000000000..03e66bf271 --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/int/0008_find_permutation_of_int1_4/expected/model-solution000024.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting p be permutation((1, 4), (2, 3)) diff --git a/tests/exhaustive/basic/perms/01_representation/int/0008_find_permutation_of_int1_4/expected/model.eprime b/tests/exhaustive/basic/perms/01_representation/int/0008_find_permutation_of_int1_4/expected/model.eprime new file mode 100644 index 0000000000..baf4941d10 --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/int/0008_find_permutation_of_int1_4/expected/model.eprime @@ -0,0 +1,9 @@ +language ESSENCE' 1.0 + +letting n be 4 +find p_PermutationAsFunction_PermutationFunction_Function1D: matrix indexed by [int(1..4)] of int(1..4) +branching on [p_PermutationAsFunction_PermutationFunction_Function1D] +such that + allDiff(p_PermutationAsFunction_PermutationFunction_Function1D), + and([or([p_PermutationAsFunction_PermutationFunction_Function1D[q3] = q2 | q3 : int(1..4)]) | q2 : int(1..4)]) + diff --git a/tests/exhaustive/basic/perms/01_representation/int/0008_find_permutation_of_int1_4/permutation.essence b/tests/exhaustive/basic/perms/01_representation/int/0008_find_permutation_of_int1_4/permutation.essence new file mode 100644 index 0000000000..cf835570bd --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/int/0008_find_permutation_of_int1_4/permutation.essence @@ -0,0 +1,5 @@ +letting n be 4 + +find p : permutation of int(1..n) + +such that true diff --git a/tests/exhaustive/basic/perms/01_representation/int/0009_letting_permutation_in_model/expected/model-solution000001.solution b/tests/exhaustive/basic/perms/01_representation/int/0009_letting_permutation_in_model/expected/model-solution000001.solution new file mode 100644 index 0000000000..fa3c1c5e86 --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/int/0009_letting_permutation_in_model/expected/model-solution000001.solution @@ -0,0 +1,2 @@ +language Essence 1.3 + diff --git a/tests/exhaustive/basic/perms/01_representation/int/0009_letting_permutation_in_model/expected/model.eprime b/tests/exhaustive/basic/perms/01_representation/int/0009_letting_permutation_in_model/expected/model.eprime new file mode 100644 index 0000000000..c64108a295 --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/int/0009_letting_permutation_in_model/expected/model.eprime @@ -0,0 +1,5 @@ +language ESSENCE' 1.0 + +branching on [] +such that true + diff --git a/tests/exhaustive/basic/perms/01_representation/int/0009_letting_permutation_in_model/permutation.essence b/tests/exhaustive/basic/perms/01_representation/int/0009_letting_permutation_in_model/permutation.essence new file mode 100644 index 0000000000..ab8ecc292d --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/int/0009_letting_permutation_in_model/permutation.essence @@ -0,0 +1,3 @@ +letting p be permutation((1,3),(2,4)) + +such that true diff --git a/tests/exhaustive/basic/perms/01_representation/int/0010_find_permutation_maxSize_2_of_int1_3/expected/model-solution000001.solution b/tests/exhaustive/basic/perms/01_representation/int/0010_find_permutation_maxSize_2_of_int1_3/expected/model-solution000001.solution new file mode 100644 index 0000000000..dec1e69413 --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/int/0010_find_permutation_maxSize_2_of_int1_3/expected/model-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting p be permutation() diff --git a/tests/exhaustive/basic/perms/01_representation/int/0010_find_permutation_maxSize_2_of_int1_3/expected/model-solution000002.solution b/tests/exhaustive/basic/perms/01_representation/int/0010_find_permutation_maxSize_2_of_int1_3/expected/model-solution000002.solution new file mode 100644 index 0000000000..605f7ec490 --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/int/0010_find_permutation_maxSize_2_of_int1_3/expected/model-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting p be permutation((2, 3)) diff --git a/tests/exhaustive/basic/perms/01_representation/int/0010_find_permutation_maxSize_2_of_int1_3/expected/model-solution000003.solution b/tests/exhaustive/basic/perms/01_representation/int/0010_find_permutation_maxSize_2_of_int1_3/expected/model-solution000003.solution new file mode 100644 index 0000000000..bce4d1fc90 --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/int/0010_find_permutation_maxSize_2_of_int1_3/expected/model-solution000003.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting p be permutation((1, 2)) diff --git a/tests/exhaustive/basic/perms/01_representation/int/0010_find_permutation_maxSize_2_of_int1_3/expected/model-solution000004.solution b/tests/exhaustive/basic/perms/01_representation/int/0010_find_permutation_maxSize_2_of_int1_3/expected/model-solution000004.solution new file mode 100644 index 0000000000..12c2330c06 --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/int/0010_find_permutation_maxSize_2_of_int1_3/expected/model-solution000004.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting p be permutation((1, 3)) diff --git a/tests/exhaustive/basic/perms/01_representation/int/0010_find_permutation_maxSize_2_of_int1_3/expected/model.eprime b/tests/exhaustive/basic/perms/01_representation/int/0010_find_permutation_maxSize_2_of_int1_3/expected/model.eprime new file mode 100644 index 0000000000..3bd6e097fb --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/int/0010_find_permutation_maxSize_2_of_int1_3/expected/model.eprime @@ -0,0 +1,10 @@ +language ESSENCE' 1.0 + +letting n be 3 +find p_PermutationAsFunction_PermutationFunction_Function1D: matrix indexed by [int(1..3)] of int(1..3) +branching on [p_PermutationAsFunction_PermutationFunction_Function1D] +such that + allDiff(p_PermutationAsFunction_PermutationFunction_Function1D), + and([or([p_PermutationAsFunction_PermutationFunction_Function1D[q3] = q2 | q3 : int(1..3)]) | q2 : int(1..3)]), + sum([toInt(q1 != p_PermutationAsFunction_PermutationFunction_Function1D[q1]) | q1 : int(1..3)]) <= 2 + diff --git a/tests/exhaustive/basic/perms/01_representation/int/0010_find_permutation_maxSize_2_of_int1_3/permutation.essence b/tests/exhaustive/basic/perms/01_representation/int/0010_find_permutation_maxSize_2_of_int1_3/permutation.essence new file mode 100644 index 0000000000..c5f650a6ea --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/int/0010_find_permutation_maxSize_2_of_int1_3/permutation.essence @@ -0,0 +1,5 @@ +letting n be 3 + +find p : permutation (maxSize 2) of int(1..n) + +such that true diff --git a/tests/exhaustive/basic/perms/01_representation/int/0011_find_permutation_minSize_2_of_int1_3/expected/model-solution000001.solution b/tests/exhaustive/basic/perms/01_representation/int/0011_find_permutation_minSize_2_of_int1_3/expected/model-solution000001.solution new file mode 100644 index 0000000000..605f7ec490 --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/int/0011_find_permutation_minSize_2_of_int1_3/expected/model-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting p be permutation((2, 3)) diff --git a/tests/exhaustive/basic/perms/01_representation/int/0011_find_permutation_minSize_2_of_int1_3/expected/model-solution000002.solution b/tests/exhaustive/basic/perms/01_representation/int/0011_find_permutation_minSize_2_of_int1_3/expected/model-solution000002.solution new file mode 100644 index 0000000000..bce4d1fc90 --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/int/0011_find_permutation_minSize_2_of_int1_3/expected/model-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting p be permutation((1, 2)) diff --git a/tests/exhaustive/basic/perms/01_representation/int/0011_find_permutation_minSize_2_of_int1_3/expected/model-solution000003.solution b/tests/exhaustive/basic/perms/01_representation/int/0011_find_permutation_minSize_2_of_int1_3/expected/model-solution000003.solution new file mode 100644 index 0000000000..ae8af1a204 --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/int/0011_find_permutation_minSize_2_of_int1_3/expected/model-solution000003.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting p be permutation((1, 2, 3)) diff --git a/tests/exhaustive/basic/perms/01_representation/int/0011_find_permutation_minSize_2_of_int1_3/expected/model-solution000004.solution b/tests/exhaustive/basic/perms/01_representation/int/0011_find_permutation_minSize_2_of_int1_3/expected/model-solution000004.solution new file mode 100644 index 0000000000..899856556b --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/int/0011_find_permutation_minSize_2_of_int1_3/expected/model-solution000004.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting p be permutation((1, 3, 2)) diff --git a/tests/exhaustive/basic/perms/01_representation/int/0011_find_permutation_minSize_2_of_int1_3/expected/model-solution000005.solution b/tests/exhaustive/basic/perms/01_representation/int/0011_find_permutation_minSize_2_of_int1_3/expected/model-solution000005.solution new file mode 100644 index 0000000000..12c2330c06 --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/int/0011_find_permutation_minSize_2_of_int1_3/expected/model-solution000005.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting p be permutation((1, 3)) diff --git a/tests/exhaustive/basic/perms/01_representation/int/0011_find_permutation_minSize_2_of_int1_3/expected/model.eprime b/tests/exhaustive/basic/perms/01_representation/int/0011_find_permutation_minSize_2_of_int1_3/expected/model.eprime new file mode 100644 index 0000000000..6029393e7f --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/int/0011_find_permutation_minSize_2_of_int1_3/expected/model.eprime @@ -0,0 +1,10 @@ +language ESSENCE' 1.0 + +letting n be 3 +find p_PermutationAsFunction_PermutationFunction_Function1D: matrix indexed by [int(1..3)] of int(1..3) +branching on [p_PermutationAsFunction_PermutationFunction_Function1D] +such that + allDiff(p_PermutationAsFunction_PermutationFunction_Function1D), + and([or([p_PermutationAsFunction_PermutationFunction_Function1D[q3] = q2 | q3 : int(1..3)]) | q2 : int(1..3)]), + 2 <= sum([toInt(q1 != p_PermutationAsFunction_PermutationFunction_Function1D[q1]) | q1 : int(1..3)]) + diff --git a/tests/exhaustive/basic/perms/01_representation/int/0011_find_permutation_minSize_2_of_int1_3/permutation.essence b/tests/exhaustive/basic/perms/01_representation/int/0011_find_permutation_minSize_2_of_int1_3/permutation.essence new file mode 100644 index 0000000000..73007c1924 --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/int/0011_find_permutation_minSize_2_of_int1_3/permutation.essence @@ -0,0 +1,5 @@ +letting n be 3 + +find p : permutation (minSize 2) of int(1..n) + +such that true diff --git a/tests/exhaustive/basic/perms/01_representation/int/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model-solution000001.solution b/tests/exhaustive/basic/perms/01_representation/int/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model-solution000001.solution new file mode 100644 index 0000000000..c191faffa1 --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/int/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting p be permutation((3, 4)) diff --git a/tests/exhaustive/basic/perms/01_representation/int/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model-solution000002.solution b/tests/exhaustive/basic/perms/01_representation/int/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model-solution000002.solution new file mode 100644 index 0000000000..605f7ec490 --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/int/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting p be permutation((2, 3)) diff --git a/tests/exhaustive/basic/perms/01_representation/int/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model-solution000003.solution b/tests/exhaustive/basic/perms/01_representation/int/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model-solution000003.solution new file mode 100644 index 0000000000..0349e8bfc1 --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/int/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model-solution000003.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting p be permutation((2, 3, 4)) diff --git a/tests/exhaustive/basic/perms/01_representation/int/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model-solution000004.solution b/tests/exhaustive/basic/perms/01_representation/int/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model-solution000004.solution new file mode 100644 index 0000000000..7f3ffab396 --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/int/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model-solution000004.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting p be permutation((2, 4, 3)) diff --git a/tests/exhaustive/basic/perms/01_representation/int/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model-solution000005.solution b/tests/exhaustive/basic/perms/01_representation/int/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model-solution000005.solution new file mode 100644 index 0000000000..4aa2acf568 --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/int/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model-solution000005.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting p be permutation((2, 4)) diff --git a/tests/exhaustive/basic/perms/01_representation/int/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model-solution000006.solution b/tests/exhaustive/basic/perms/01_representation/int/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model-solution000006.solution new file mode 100644 index 0000000000..bce4d1fc90 --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/int/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model-solution000006.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting p be permutation((1, 2)) diff --git a/tests/exhaustive/basic/perms/01_representation/int/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model-solution000007.solution b/tests/exhaustive/basic/perms/01_representation/int/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model-solution000007.solution new file mode 100644 index 0000000000..ae8af1a204 --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/int/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model-solution000007.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting p be permutation((1, 2, 3)) diff --git a/tests/exhaustive/basic/perms/01_representation/int/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model-solution000008.solution b/tests/exhaustive/basic/perms/01_representation/int/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model-solution000008.solution new file mode 100644 index 0000000000..3fba79788b --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/int/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model-solution000008.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting p be permutation((1, 2, 4)) diff --git a/tests/exhaustive/basic/perms/01_representation/int/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model-solution000009.solution b/tests/exhaustive/basic/perms/01_representation/int/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model-solution000009.solution new file mode 100644 index 0000000000..899856556b --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/int/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model-solution000009.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting p be permutation((1, 3, 2)) diff --git a/tests/exhaustive/basic/perms/01_representation/int/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model-solution000010.solution b/tests/exhaustive/basic/perms/01_representation/int/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model-solution000010.solution new file mode 100644 index 0000000000..12c2330c06 --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/int/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model-solution000010.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting p be permutation((1, 3)) diff --git a/tests/exhaustive/basic/perms/01_representation/int/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model-solution000011.solution b/tests/exhaustive/basic/perms/01_representation/int/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model-solution000011.solution new file mode 100644 index 0000000000..8710a5d0ae --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/int/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model-solution000011.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting p be permutation((1, 3, 4)) diff --git a/tests/exhaustive/basic/perms/01_representation/int/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model-solution000012.solution b/tests/exhaustive/basic/perms/01_representation/int/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model-solution000012.solution new file mode 100644 index 0000000000..72a96ad1f9 --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/int/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model-solution000012.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting p be permutation((1, 4, 2)) diff --git a/tests/exhaustive/basic/perms/01_representation/int/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model-solution000013.solution b/tests/exhaustive/basic/perms/01_representation/int/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model-solution000013.solution new file mode 100644 index 0000000000..23fcbc89f7 --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/int/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model-solution000013.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting p be permutation((1, 4, 3)) diff --git a/tests/exhaustive/basic/perms/01_representation/int/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model-solution000014.solution b/tests/exhaustive/basic/perms/01_representation/int/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model-solution000014.solution new file mode 100644 index 0000000000..829b355a1f --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/int/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model-solution000014.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting p be permutation((1, 4)) diff --git a/tests/exhaustive/basic/perms/01_representation/int/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model.eprime b/tests/exhaustive/basic/perms/01_representation/int/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model.eprime new file mode 100644 index 0000000000..43f442968f --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/int/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model.eprime @@ -0,0 +1,11 @@ +language ESSENCE' 1.0 + +letting n be 4 +find p_PermutationAsFunction_PermutationFunction_Function1D: matrix indexed by [int(1..4)] of int(1..4) +branching on [p_PermutationAsFunction_PermutationFunction_Function1D] +such that + allDiff(p_PermutationAsFunction_PermutationFunction_Function1D), + and([or([p_PermutationAsFunction_PermutationFunction_Function1D[q3] = q2 | q3 : int(1..4)]) | q2 : int(1..4)]), + 2 <= sum([toInt(q1 != p_PermutationAsFunction_PermutationFunction_Function1D[q1]) | q1 : int(1..4)]), + sum([toInt(q1 != p_PermutationAsFunction_PermutationFunction_Function1D[q1]) | q1 : int(1..4)]) <= 3 + diff --git a/tests/exhaustive/basic/perms/01_representation/int/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/permutation.essence b/tests/exhaustive/basic/perms/01_representation/int/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/permutation.essence new file mode 100644 index 0000000000..4460f93ee0 --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/int/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/permutation.essence @@ -0,0 +1,5 @@ +letting n be 4 + +find p : permutation (minSize 2, maxSize 3) of int(1..n) + +such that true diff --git a/tests/exhaustive/basic/perms/01_representation/unnamed/0005_find_permutation_size_4_of_int1_4/expected/model-solution000001.solution b/tests/exhaustive/basic/perms/01_representation/unnamed/0005_find_permutation_size_4_of_int1_4/expected/model-solution000001.solution new file mode 100644 index 0000000000..bddabf9ef1 --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/unnamed/0005_find_permutation_size_4_of_int1_4/expected/model-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_1, n_2), (n_3, n_4)) diff --git a/tests/exhaustive/basic/perms/01_representation/unnamed/0005_find_permutation_size_4_of_int1_4/expected/model-solution000002.solution b/tests/exhaustive/basic/perms/01_representation/unnamed/0005_find_permutation_size_4_of_int1_4/expected/model-solution000002.solution new file mode 100644 index 0000000000..ab1f215231 --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/unnamed/0005_find_permutation_size_4_of_int1_4/expected/model-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_1, n_2, n_3, n_4)) diff --git a/tests/exhaustive/basic/perms/01_representation/unnamed/0005_find_permutation_size_4_of_int1_4/expected/model-solution000003.solution b/tests/exhaustive/basic/perms/01_representation/unnamed/0005_find_permutation_size_4_of_int1_4/expected/model-solution000003.solution new file mode 100644 index 0000000000..44dfd72b13 --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/unnamed/0005_find_permutation_size_4_of_int1_4/expected/model-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_1, n_2, n_4, n_3)) diff --git a/tests/exhaustive/basic/perms/01_representation/unnamed/0005_find_permutation_size_4_of_int1_4/expected/model-solution000004.solution b/tests/exhaustive/basic/perms/01_representation/unnamed/0005_find_permutation_size_4_of_int1_4/expected/model-solution000004.solution new file mode 100644 index 0000000000..8cce2a9dc1 --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/unnamed/0005_find_permutation_size_4_of_int1_4/expected/model-solution000004.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_1, n_3, n_4, n_2)) diff --git a/tests/exhaustive/basic/perms/01_representation/unnamed/0005_find_permutation_size_4_of_int1_4/expected/model-solution000005.solution b/tests/exhaustive/basic/perms/01_representation/unnamed/0005_find_permutation_size_4_of_int1_4/expected/model-solution000005.solution new file mode 100644 index 0000000000..77d7abd43f --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/unnamed/0005_find_permutation_size_4_of_int1_4/expected/model-solution000005.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_1, n_3), (n_2, n_4)) diff --git a/tests/exhaustive/basic/perms/01_representation/unnamed/0005_find_permutation_size_4_of_int1_4/expected/model-solution000006.solution b/tests/exhaustive/basic/perms/01_representation/unnamed/0005_find_permutation_size_4_of_int1_4/expected/model-solution000006.solution new file mode 100644 index 0000000000..313bbe8778 --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/unnamed/0005_find_permutation_size_4_of_int1_4/expected/model-solution000006.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_1, n_3, n_2, n_4)) diff --git a/tests/exhaustive/basic/perms/01_representation/unnamed/0005_find_permutation_size_4_of_int1_4/expected/model-solution000007.solution b/tests/exhaustive/basic/perms/01_representation/unnamed/0005_find_permutation_size_4_of_int1_4/expected/model-solution000007.solution new file mode 100644 index 0000000000..10b0bd6eb3 --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/unnamed/0005_find_permutation_size_4_of_int1_4/expected/model-solution000007.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_1, n_4, n_3, n_2)) diff --git a/tests/exhaustive/basic/perms/01_representation/unnamed/0005_find_permutation_size_4_of_int1_4/expected/model-solution000008.solution b/tests/exhaustive/basic/perms/01_representation/unnamed/0005_find_permutation_size_4_of_int1_4/expected/model-solution000008.solution new file mode 100644 index 0000000000..a6698d00e9 --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/unnamed/0005_find_permutation_size_4_of_int1_4/expected/model-solution000008.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_1, n_4, n_2, n_3)) diff --git a/tests/exhaustive/basic/perms/01_representation/unnamed/0005_find_permutation_size_4_of_int1_4/expected/model-solution000009.solution b/tests/exhaustive/basic/perms/01_representation/unnamed/0005_find_permutation_size_4_of_int1_4/expected/model-solution000009.solution new file mode 100644 index 0000000000..8fb143974a --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/unnamed/0005_find_permutation_size_4_of_int1_4/expected/model-solution000009.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_1, n_4), (n_2, n_3)) diff --git a/tests/exhaustive/basic/perms/01_representation/unnamed/0005_find_permutation_size_4_of_int1_4/expected/model.eprime b/tests/exhaustive/basic/perms/01_representation/unnamed/0005_find_permutation_size_4_of_int1_4/expected/model.eprime new file mode 100644 index 0000000000..134950077a --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/unnamed/0005_find_permutation_size_4_of_int1_4/expected/model.eprime @@ -0,0 +1,9 @@ +language ESSENCE' 1.0 + +find p_PermutationAsFunction_PermutationFunction_Function1D: matrix indexed by [int(1..4)] of int(1..4) +branching on [p_PermutationAsFunction_PermutationFunction_Function1D] +such that + allDiff(p_PermutationAsFunction_PermutationFunction_Function1D), + and([or([p_PermutationAsFunction_PermutationFunction_Function1D[q3] = q2 | q3 : int(1..4)]) | q2 : int(1..4)]), + 4 = sum([toInt(q1 != p_PermutationAsFunction_PermutationFunction_Function1D[q1]) | q1 : int(1..4)]) + diff --git a/tests/exhaustive/basic/perms/01_representation/unnamed/0005_find_permutation_size_4_of_int1_4/permutation.essence b/tests/exhaustive/basic/perms/01_representation/unnamed/0005_find_permutation_size_4_of_int1_4/permutation.essence new file mode 100644 index 0000000000..355a19fd10 --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/unnamed/0005_find_permutation_size_4_of_int1_4/permutation.essence @@ -0,0 +1,5 @@ +letting n be new type of size 4 + +find p : permutation (size 4) of n + +such that true diff --git a/tests/exhaustive/basic/perms/01_representation/unnamed/0006_find_permutation_size_0_of_int1_4/expected/model-solution000001.solution b/tests/exhaustive/basic/perms/01_representation/unnamed/0006_find_permutation_size_0_of_int1_4/expected/model-solution000001.solution new file mode 100644 index 0000000000..48aee04d80 --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/unnamed/0006_find_permutation_size_0_of_int1_4/expected/model-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation() diff --git a/tests/exhaustive/basic/perms/01_representation/unnamed/0006_find_permutation_size_0_of_int1_4/expected/model.eprime b/tests/exhaustive/basic/perms/01_representation/unnamed/0006_find_permutation_size_0_of_int1_4/expected/model.eprime new file mode 100644 index 0000000000..a03a5e86e3 --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/unnamed/0006_find_permutation_size_0_of_int1_4/expected/model.eprime @@ -0,0 +1,9 @@ +language ESSENCE' 1.0 + +find p_PermutationAsFunction_PermutationFunction_Function1D: matrix indexed by [int(1..4)] of int(1..4) +branching on [p_PermutationAsFunction_PermutationFunction_Function1D] +such that + allDiff(p_PermutationAsFunction_PermutationFunction_Function1D), + and([or([p_PermutationAsFunction_PermutationFunction_Function1D[q3] = q2 | q3 : int(1..4)]) | q2 : int(1..4)]), + 0 = sum([toInt(q1 != p_PermutationAsFunction_PermutationFunction_Function1D[q1]) | q1 : int(1..4)]) + diff --git a/tests/exhaustive/basic/perms/01_representation/unnamed/0006_find_permutation_size_0_of_int1_4/permutation.essence b/tests/exhaustive/basic/perms/01_representation/unnamed/0006_find_permutation_size_0_of_int1_4/permutation.essence new file mode 100644 index 0000000000..264e52e6b7 --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/unnamed/0006_find_permutation_size_0_of_int1_4/permutation.essence @@ -0,0 +1,5 @@ +letting n be new type of size 4 + +find p : permutation (size 0) of n + +such that true diff --git a/tests/exhaustive/basic/perms/01_representation/unnamed/0007_letting_permutation_be_empty/expected/model-solution000001.solution b/tests/exhaustive/basic/perms/01_representation/unnamed/0007_letting_permutation_be_empty/expected/model-solution000001.solution new file mode 100644 index 0000000000..fa3c1c5e86 --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/unnamed/0007_letting_permutation_be_empty/expected/model-solution000001.solution @@ -0,0 +1,2 @@ +language Essence 1.3 + diff --git a/tests/exhaustive/basic/perms/01_representation/unnamed/0007_letting_permutation_be_empty/expected/model.eprime b/tests/exhaustive/basic/perms/01_representation/unnamed/0007_letting_permutation_be_empty/expected/model.eprime new file mode 100644 index 0000000000..c64108a295 --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/unnamed/0007_letting_permutation_be_empty/expected/model.eprime @@ -0,0 +1,5 @@ +language ESSENCE' 1.0 + +branching on [] +such that true + diff --git a/tests/exhaustive/basic/perms/01_representation/unnamed/0007_letting_permutation_be_empty/permutation.essence b/tests/exhaustive/basic/perms/01_representation/unnamed/0007_letting_permutation_be_empty/permutation.essence new file mode 100644 index 0000000000..a39f3ae0b1 --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/unnamed/0007_letting_permutation_be_empty/permutation.essence @@ -0,0 +1,3 @@ +letting p be permutation() + +such that true diff --git a/tests/exhaustive/basic/perms/01_representation/unnamed/0008_find_permutation_of_int1_4/expected/model-solution000001.solution b/tests/exhaustive/basic/perms/01_representation/unnamed/0008_find_permutation_of_int1_4/expected/model-solution000001.solution new file mode 100644 index 0000000000..48aee04d80 --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/unnamed/0008_find_permutation_of_int1_4/expected/model-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation() diff --git a/tests/exhaustive/basic/perms/01_representation/unnamed/0008_find_permutation_of_int1_4/expected/model-solution000002.solution b/tests/exhaustive/basic/perms/01_representation/unnamed/0008_find_permutation_of_int1_4/expected/model-solution000002.solution new file mode 100644 index 0000000000..92d4b6859f --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/unnamed/0008_find_permutation_of_int1_4/expected/model-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_3, n_4)) diff --git a/tests/exhaustive/basic/perms/01_representation/unnamed/0008_find_permutation_of_int1_4/expected/model-solution000003.solution b/tests/exhaustive/basic/perms/01_representation/unnamed/0008_find_permutation_of_int1_4/expected/model-solution000003.solution new file mode 100644 index 0000000000..9e6535551a --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/unnamed/0008_find_permutation_of_int1_4/expected/model-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_2, n_3)) diff --git a/tests/exhaustive/basic/perms/01_representation/unnamed/0008_find_permutation_of_int1_4/expected/model-solution000004.solution b/tests/exhaustive/basic/perms/01_representation/unnamed/0008_find_permutation_of_int1_4/expected/model-solution000004.solution new file mode 100644 index 0000000000..dbde96e6cd --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/unnamed/0008_find_permutation_of_int1_4/expected/model-solution000004.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_2, n_3, n_4)) diff --git a/tests/exhaustive/basic/perms/01_representation/unnamed/0008_find_permutation_of_int1_4/expected/model-solution000005.solution b/tests/exhaustive/basic/perms/01_representation/unnamed/0008_find_permutation_of_int1_4/expected/model-solution000005.solution new file mode 100644 index 0000000000..26cf179956 --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/unnamed/0008_find_permutation_of_int1_4/expected/model-solution000005.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_2, n_4, n_3)) diff --git a/tests/exhaustive/basic/perms/01_representation/unnamed/0008_find_permutation_of_int1_4/expected/model-solution000006.solution b/tests/exhaustive/basic/perms/01_representation/unnamed/0008_find_permutation_of_int1_4/expected/model-solution000006.solution new file mode 100644 index 0000000000..f037c8c0fe --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/unnamed/0008_find_permutation_of_int1_4/expected/model-solution000006.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_2, n_4)) diff --git a/tests/exhaustive/basic/perms/01_representation/unnamed/0008_find_permutation_of_int1_4/expected/model-solution000007.solution b/tests/exhaustive/basic/perms/01_representation/unnamed/0008_find_permutation_of_int1_4/expected/model-solution000007.solution new file mode 100644 index 0000000000..797cb1cd45 --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/unnamed/0008_find_permutation_of_int1_4/expected/model-solution000007.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_1, n_2)) diff --git a/tests/exhaustive/basic/perms/01_representation/unnamed/0008_find_permutation_of_int1_4/expected/model-solution000008.solution b/tests/exhaustive/basic/perms/01_representation/unnamed/0008_find_permutation_of_int1_4/expected/model-solution000008.solution new file mode 100644 index 0000000000..bddabf9ef1 --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/unnamed/0008_find_permutation_of_int1_4/expected/model-solution000008.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_1, n_2), (n_3, n_4)) diff --git a/tests/exhaustive/basic/perms/01_representation/unnamed/0008_find_permutation_of_int1_4/expected/model-solution000009.solution b/tests/exhaustive/basic/perms/01_representation/unnamed/0008_find_permutation_of_int1_4/expected/model-solution000009.solution new file mode 100644 index 0000000000..3d15c52429 --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/unnamed/0008_find_permutation_of_int1_4/expected/model-solution000009.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_1, n_2, n_3)) diff --git a/tests/exhaustive/basic/perms/01_representation/unnamed/0008_find_permutation_of_int1_4/expected/model-solution000010.solution b/tests/exhaustive/basic/perms/01_representation/unnamed/0008_find_permutation_of_int1_4/expected/model-solution000010.solution new file mode 100644 index 0000000000..ab1f215231 --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/unnamed/0008_find_permutation_of_int1_4/expected/model-solution000010.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_1, n_2, n_3, n_4)) diff --git a/tests/exhaustive/basic/perms/01_representation/unnamed/0008_find_permutation_of_int1_4/expected/model-solution000011.solution b/tests/exhaustive/basic/perms/01_representation/unnamed/0008_find_permutation_of_int1_4/expected/model-solution000011.solution new file mode 100644 index 0000000000..44dfd72b13 --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/unnamed/0008_find_permutation_of_int1_4/expected/model-solution000011.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_1, n_2, n_4, n_3)) diff --git a/tests/exhaustive/basic/perms/01_representation/unnamed/0008_find_permutation_of_int1_4/expected/model-solution000012.solution b/tests/exhaustive/basic/perms/01_representation/unnamed/0008_find_permutation_of_int1_4/expected/model-solution000012.solution new file mode 100644 index 0000000000..42c251ee5e --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/unnamed/0008_find_permutation_of_int1_4/expected/model-solution000012.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_1, n_2, n_4)) diff --git a/tests/exhaustive/basic/perms/01_representation/unnamed/0008_find_permutation_of_int1_4/expected/model-solution000013.solution b/tests/exhaustive/basic/perms/01_representation/unnamed/0008_find_permutation_of_int1_4/expected/model-solution000013.solution new file mode 100644 index 0000000000..fc62614b72 --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/unnamed/0008_find_permutation_of_int1_4/expected/model-solution000013.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_1, n_3, n_2)) diff --git a/tests/exhaustive/basic/perms/01_representation/unnamed/0008_find_permutation_of_int1_4/expected/model-solution000014.solution b/tests/exhaustive/basic/perms/01_representation/unnamed/0008_find_permutation_of_int1_4/expected/model-solution000014.solution new file mode 100644 index 0000000000..8cce2a9dc1 --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/unnamed/0008_find_permutation_of_int1_4/expected/model-solution000014.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_1, n_3, n_4, n_2)) diff --git a/tests/exhaustive/basic/perms/01_representation/unnamed/0008_find_permutation_of_int1_4/expected/model-solution000015.solution b/tests/exhaustive/basic/perms/01_representation/unnamed/0008_find_permutation_of_int1_4/expected/model-solution000015.solution new file mode 100644 index 0000000000..b142877457 --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/unnamed/0008_find_permutation_of_int1_4/expected/model-solution000015.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_1, n_3)) diff --git a/tests/exhaustive/basic/perms/01_representation/unnamed/0008_find_permutation_of_int1_4/expected/model-solution000016.solution b/tests/exhaustive/basic/perms/01_representation/unnamed/0008_find_permutation_of_int1_4/expected/model-solution000016.solution new file mode 100644 index 0000000000..e344e99dd8 --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/unnamed/0008_find_permutation_of_int1_4/expected/model-solution000016.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_1, n_3, n_4)) diff --git a/tests/exhaustive/basic/perms/01_representation/unnamed/0008_find_permutation_of_int1_4/expected/model-solution000017.solution b/tests/exhaustive/basic/perms/01_representation/unnamed/0008_find_permutation_of_int1_4/expected/model-solution000017.solution new file mode 100644 index 0000000000..77d7abd43f --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/unnamed/0008_find_permutation_of_int1_4/expected/model-solution000017.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_1, n_3), (n_2, n_4)) diff --git a/tests/exhaustive/basic/perms/01_representation/unnamed/0008_find_permutation_of_int1_4/expected/model-solution000018.solution b/tests/exhaustive/basic/perms/01_representation/unnamed/0008_find_permutation_of_int1_4/expected/model-solution000018.solution new file mode 100644 index 0000000000..313bbe8778 --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/unnamed/0008_find_permutation_of_int1_4/expected/model-solution000018.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_1, n_3, n_2, n_4)) diff --git a/tests/exhaustive/basic/perms/01_representation/unnamed/0008_find_permutation_of_int1_4/expected/model-solution000019.solution b/tests/exhaustive/basic/perms/01_representation/unnamed/0008_find_permutation_of_int1_4/expected/model-solution000019.solution new file mode 100644 index 0000000000..10b0bd6eb3 --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/unnamed/0008_find_permutation_of_int1_4/expected/model-solution000019.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_1, n_4, n_3, n_2)) diff --git a/tests/exhaustive/basic/perms/01_representation/unnamed/0008_find_permutation_of_int1_4/expected/model-solution000020.solution b/tests/exhaustive/basic/perms/01_representation/unnamed/0008_find_permutation_of_int1_4/expected/model-solution000020.solution new file mode 100644 index 0000000000..e0282c3b4d --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/unnamed/0008_find_permutation_of_int1_4/expected/model-solution000020.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_1, n_4, n_2)) diff --git a/tests/exhaustive/basic/perms/01_representation/unnamed/0008_find_permutation_of_int1_4/expected/model-solution000021.solution b/tests/exhaustive/basic/perms/01_representation/unnamed/0008_find_permutation_of_int1_4/expected/model-solution000021.solution new file mode 100644 index 0000000000..44e4a74dff --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/unnamed/0008_find_permutation_of_int1_4/expected/model-solution000021.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_1, n_4, n_3)) diff --git a/tests/exhaustive/basic/perms/01_representation/unnamed/0008_find_permutation_of_int1_4/expected/model-solution000022.solution b/tests/exhaustive/basic/perms/01_representation/unnamed/0008_find_permutation_of_int1_4/expected/model-solution000022.solution new file mode 100644 index 0000000000..89dd3cde3c --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/unnamed/0008_find_permutation_of_int1_4/expected/model-solution000022.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_1, n_4)) diff --git a/tests/exhaustive/basic/perms/01_representation/unnamed/0008_find_permutation_of_int1_4/expected/model-solution000023.solution b/tests/exhaustive/basic/perms/01_representation/unnamed/0008_find_permutation_of_int1_4/expected/model-solution000023.solution new file mode 100644 index 0000000000..a6698d00e9 --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/unnamed/0008_find_permutation_of_int1_4/expected/model-solution000023.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_1, n_4, n_2, n_3)) diff --git a/tests/exhaustive/basic/perms/01_representation/unnamed/0008_find_permutation_of_int1_4/expected/model-solution000024.solution b/tests/exhaustive/basic/perms/01_representation/unnamed/0008_find_permutation_of_int1_4/expected/model-solution000024.solution new file mode 100644 index 0000000000..8fb143974a --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/unnamed/0008_find_permutation_of_int1_4/expected/model-solution000024.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_1, n_4), (n_2, n_3)) diff --git a/tests/exhaustive/basic/perms/01_representation/unnamed/0008_find_permutation_of_int1_4/expected/model.eprime b/tests/exhaustive/basic/perms/01_representation/unnamed/0008_find_permutation_of_int1_4/expected/model.eprime new file mode 100644 index 0000000000..ac93d552d6 --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/unnamed/0008_find_permutation_of_int1_4/expected/model.eprime @@ -0,0 +1,8 @@ +language ESSENCE' 1.0 + +find p_PermutationAsFunction_PermutationFunction_Function1D: matrix indexed by [int(1..4)] of int(1..4) +branching on [p_PermutationAsFunction_PermutationFunction_Function1D] +such that + allDiff(p_PermutationAsFunction_PermutationFunction_Function1D), + and([or([p_PermutationAsFunction_PermutationFunction_Function1D[q3] = q2 | q3 : int(1..4)]) | q2 : int(1..4)]) + diff --git a/tests/exhaustive/basic/perms/01_representation/unnamed/0008_find_permutation_of_int1_4/permutation.essence b/tests/exhaustive/basic/perms/01_representation/unnamed/0008_find_permutation_of_int1_4/permutation.essence new file mode 100644 index 0000000000..a3348d0d12 --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/unnamed/0008_find_permutation_of_int1_4/permutation.essence @@ -0,0 +1,5 @@ +letting n be new type of size 4 + +find p : permutation of n + +such that true diff --git a/tests/exhaustive/basic/perms/01_representation/unnamed/0010_find_permutation_maxSize_2_of_int1_3/expected/model-solution000001.solution b/tests/exhaustive/basic/perms/01_representation/unnamed/0010_find_permutation_maxSize_2_of_int1_3/expected/model-solution000001.solution new file mode 100644 index 0000000000..eb4b07c580 --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/unnamed/0010_find_permutation_maxSize_2_of_int1_3/expected/model-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3} +letting p be permutation() diff --git a/tests/exhaustive/basic/perms/01_representation/unnamed/0010_find_permutation_maxSize_2_of_int1_3/expected/model-solution000002.solution b/tests/exhaustive/basic/perms/01_representation/unnamed/0010_find_permutation_maxSize_2_of_int1_3/expected/model-solution000002.solution new file mode 100644 index 0000000000..976a7f2977 --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/unnamed/0010_find_permutation_maxSize_2_of_int1_3/expected/model-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3} +letting p be permutation((n_2, n_3)) diff --git a/tests/exhaustive/basic/perms/01_representation/unnamed/0010_find_permutation_maxSize_2_of_int1_3/expected/model-solution000003.solution b/tests/exhaustive/basic/perms/01_representation/unnamed/0010_find_permutation_maxSize_2_of_int1_3/expected/model-solution000003.solution new file mode 100644 index 0000000000..03e77d66f1 --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/unnamed/0010_find_permutation_maxSize_2_of_int1_3/expected/model-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3} +letting p be permutation((n_1, n_2)) diff --git a/tests/exhaustive/basic/perms/01_representation/unnamed/0010_find_permutation_maxSize_2_of_int1_3/expected/model-solution000004.solution b/tests/exhaustive/basic/perms/01_representation/unnamed/0010_find_permutation_maxSize_2_of_int1_3/expected/model-solution000004.solution new file mode 100644 index 0000000000..9121fde110 --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/unnamed/0010_find_permutation_maxSize_2_of_int1_3/expected/model-solution000004.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3} +letting p be permutation((n_1, n_3)) diff --git a/tests/exhaustive/basic/perms/01_representation/unnamed/0010_find_permutation_maxSize_2_of_int1_3/expected/model.eprime b/tests/exhaustive/basic/perms/01_representation/unnamed/0010_find_permutation_maxSize_2_of_int1_3/expected/model.eprime new file mode 100644 index 0000000000..95837c9498 --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/unnamed/0010_find_permutation_maxSize_2_of_int1_3/expected/model.eprime @@ -0,0 +1,9 @@ +language ESSENCE' 1.0 + +find p_PermutationAsFunction_PermutationFunction_Function1D: matrix indexed by [int(1..3)] of int(1..3) +branching on [p_PermutationAsFunction_PermutationFunction_Function1D] +such that + allDiff(p_PermutationAsFunction_PermutationFunction_Function1D), + and([or([p_PermutationAsFunction_PermutationFunction_Function1D[q3] = q2 | q3 : int(1..3)]) | q2 : int(1..3)]), + sum([toInt(q1 != p_PermutationAsFunction_PermutationFunction_Function1D[q1]) | q1 : int(1..3)]) <= 2 + diff --git a/tests/exhaustive/basic/perms/01_representation/unnamed/0010_find_permutation_maxSize_2_of_int1_3/permutation.essence b/tests/exhaustive/basic/perms/01_representation/unnamed/0010_find_permutation_maxSize_2_of_int1_3/permutation.essence new file mode 100644 index 0000000000..7e78359040 --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/unnamed/0010_find_permutation_maxSize_2_of_int1_3/permutation.essence @@ -0,0 +1,5 @@ +letting n be new type of size 3 + +find p : permutation (maxSize 2) of n + +such that true diff --git a/tests/exhaustive/basic/perms/01_representation/unnamed/0011_find_permutation_minSize_2_of_int1_3/expected/model-solution000001.solution b/tests/exhaustive/basic/perms/01_representation/unnamed/0011_find_permutation_minSize_2_of_int1_3/expected/model-solution000001.solution new file mode 100644 index 0000000000..976a7f2977 --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/unnamed/0011_find_permutation_minSize_2_of_int1_3/expected/model-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3} +letting p be permutation((n_2, n_3)) diff --git a/tests/exhaustive/basic/perms/01_representation/unnamed/0011_find_permutation_minSize_2_of_int1_3/expected/model-solution000002.solution b/tests/exhaustive/basic/perms/01_representation/unnamed/0011_find_permutation_minSize_2_of_int1_3/expected/model-solution000002.solution new file mode 100644 index 0000000000..03e77d66f1 --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/unnamed/0011_find_permutation_minSize_2_of_int1_3/expected/model-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3} +letting p be permutation((n_1, n_2)) diff --git a/tests/exhaustive/basic/perms/01_representation/unnamed/0011_find_permutation_minSize_2_of_int1_3/expected/model-solution000003.solution b/tests/exhaustive/basic/perms/01_representation/unnamed/0011_find_permutation_minSize_2_of_int1_3/expected/model-solution000003.solution new file mode 100644 index 0000000000..221dcaf11d --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/unnamed/0011_find_permutation_minSize_2_of_int1_3/expected/model-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3} +letting p be permutation((n_1, n_2, n_3)) diff --git a/tests/exhaustive/basic/perms/01_representation/unnamed/0011_find_permutation_minSize_2_of_int1_3/expected/model-solution000004.solution b/tests/exhaustive/basic/perms/01_representation/unnamed/0011_find_permutation_minSize_2_of_int1_3/expected/model-solution000004.solution new file mode 100644 index 0000000000..66c52edc04 --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/unnamed/0011_find_permutation_minSize_2_of_int1_3/expected/model-solution000004.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3} +letting p be permutation((n_1, n_3, n_2)) diff --git a/tests/exhaustive/basic/perms/01_representation/unnamed/0011_find_permutation_minSize_2_of_int1_3/expected/model-solution000005.solution b/tests/exhaustive/basic/perms/01_representation/unnamed/0011_find_permutation_minSize_2_of_int1_3/expected/model-solution000005.solution new file mode 100644 index 0000000000..9121fde110 --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/unnamed/0011_find_permutation_minSize_2_of_int1_3/expected/model-solution000005.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3} +letting p be permutation((n_1, n_3)) diff --git a/tests/exhaustive/basic/perms/01_representation/unnamed/0011_find_permutation_minSize_2_of_int1_3/expected/model.eprime b/tests/exhaustive/basic/perms/01_representation/unnamed/0011_find_permutation_minSize_2_of_int1_3/expected/model.eprime new file mode 100644 index 0000000000..7854912481 --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/unnamed/0011_find_permutation_minSize_2_of_int1_3/expected/model.eprime @@ -0,0 +1,9 @@ +language ESSENCE' 1.0 + +find p_PermutationAsFunction_PermutationFunction_Function1D: matrix indexed by [int(1..3)] of int(1..3) +branching on [p_PermutationAsFunction_PermutationFunction_Function1D] +such that + allDiff(p_PermutationAsFunction_PermutationFunction_Function1D), + and([or([p_PermutationAsFunction_PermutationFunction_Function1D[q3] = q2 | q3 : int(1..3)]) | q2 : int(1..3)]), + 2 <= sum([toInt(q1 != p_PermutationAsFunction_PermutationFunction_Function1D[q1]) | q1 : int(1..3)]) + diff --git a/tests/exhaustive/basic/perms/01_representation/unnamed/0011_find_permutation_minSize_2_of_int1_3/permutation.essence b/tests/exhaustive/basic/perms/01_representation/unnamed/0011_find_permutation_minSize_2_of_int1_3/permutation.essence new file mode 100644 index 0000000000..b2a3c523d4 --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/unnamed/0011_find_permutation_minSize_2_of_int1_3/permutation.essence @@ -0,0 +1,5 @@ +letting n be new type of size 3 + +find p : permutation (minSize 2) of n + +such that true diff --git a/tests/exhaustive/basic/perms/01_representation/unnamed/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model-solution000001.solution b/tests/exhaustive/basic/perms/01_representation/unnamed/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model-solution000001.solution new file mode 100644 index 0000000000..92d4b6859f --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/unnamed/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_3, n_4)) diff --git a/tests/exhaustive/basic/perms/01_representation/unnamed/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model-solution000002.solution b/tests/exhaustive/basic/perms/01_representation/unnamed/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model-solution000002.solution new file mode 100644 index 0000000000..9e6535551a --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/unnamed/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_2, n_3)) diff --git a/tests/exhaustive/basic/perms/01_representation/unnamed/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model-solution000003.solution b/tests/exhaustive/basic/perms/01_representation/unnamed/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model-solution000003.solution new file mode 100644 index 0000000000..dbde96e6cd --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/unnamed/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_2, n_3, n_4)) diff --git a/tests/exhaustive/basic/perms/01_representation/unnamed/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model-solution000004.solution b/tests/exhaustive/basic/perms/01_representation/unnamed/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model-solution000004.solution new file mode 100644 index 0000000000..26cf179956 --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/unnamed/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model-solution000004.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_2, n_4, n_3)) diff --git a/tests/exhaustive/basic/perms/01_representation/unnamed/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model-solution000005.solution b/tests/exhaustive/basic/perms/01_representation/unnamed/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model-solution000005.solution new file mode 100644 index 0000000000..f037c8c0fe --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/unnamed/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model-solution000005.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_2, n_4)) diff --git a/tests/exhaustive/basic/perms/01_representation/unnamed/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model-solution000006.solution b/tests/exhaustive/basic/perms/01_representation/unnamed/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model-solution000006.solution new file mode 100644 index 0000000000..797cb1cd45 --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/unnamed/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model-solution000006.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_1, n_2)) diff --git a/tests/exhaustive/basic/perms/01_representation/unnamed/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model-solution000007.solution b/tests/exhaustive/basic/perms/01_representation/unnamed/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model-solution000007.solution new file mode 100644 index 0000000000..3d15c52429 --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/unnamed/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model-solution000007.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_1, n_2, n_3)) diff --git a/tests/exhaustive/basic/perms/01_representation/unnamed/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model-solution000008.solution b/tests/exhaustive/basic/perms/01_representation/unnamed/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model-solution000008.solution new file mode 100644 index 0000000000..42c251ee5e --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/unnamed/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model-solution000008.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_1, n_2, n_4)) diff --git a/tests/exhaustive/basic/perms/01_representation/unnamed/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model-solution000009.solution b/tests/exhaustive/basic/perms/01_representation/unnamed/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model-solution000009.solution new file mode 100644 index 0000000000..fc62614b72 --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/unnamed/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model-solution000009.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_1, n_3, n_2)) diff --git a/tests/exhaustive/basic/perms/01_representation/unnamed/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model-solution000010.solution b/tests/exhaustive/basic/perms/01_representation/unnamed/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model-solution000010.solution new file mode 100644 index 0000000000..b142877457 --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/unnamed/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model-solution000010.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_1, n_3)) diff --git a/tests/exhaustive/basic/perms/01_representation/unnamed/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model-solution000011.solution b/tests/exhaustive/basic/perms/01_representation/unnamed/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model-solution000011.solution new file mode 100644 index 0000000000..e344e99dd8 --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/unnamed/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model-solution000011.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_1, n_3, n_4)) diff --git a/tests/exhaustive/basic/perms/01_representation/unnamed/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model-solution000012.solution b/tests/exhaustive/basic/perms/01_representation/unnamed/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model-solution000012.solution new file mode 100644 index 0000000000..e0282c3b4d --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/unnamed/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model-solution000012.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_1, n_4, n_2)) diff --git a/tests/exhaustive/basic/perms/01_representation/unnamed/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model-solution000013.solution b/tests/exhaustive/basic/perms/01_representation/unnamed/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model-solution000013.solution new file mode 100644 index 0000000000..44e4a74dff --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/unnamed/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model-solution000013.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_1, n_4, n_3)) diff --git a/tests/exhaustive/basic/perms/01_representation/unnamed/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model-solution000014.solution b/tests/exhaustive/basic/perms/01_representation/unnamed/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model-solution000014.solution new file mode 100644 index 0000000000..89dd3cde3c --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/unnamed/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model-solution000014.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_1, n_4)) diff --git a/tests/exhaustive/basic/perms/01_representation/unnamed/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model.eprime b/tests/exhaustive/basic/perms/01_representation/unnamed/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model.eprime new file mode 100644 index 0000000000..4292a59345 --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/unnamed/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model.eprime @@ -0,0 +1,10 @@ +language ESSENCE' 1.0 + +find p_PermutationAsFunction_PermutationFunction_Function1D: matrix indexed by [int(1..4)] of int(1..4) +branching on [p_PermutationAsFunction_PermutationFunction_Function1D] +such that + allDiff(p_PermutationAsFunction_PermutationFunction_Function1D), + and([or([p_PermutationAsFunction_PermutationFunction_Function1D[q3] = q2 | q3 : int(1..4)]) | q2 : int(1..4)]), + 2 <= sum([toInt(q1 != p_PermutationAsFunction_PermutationFunction_Function1D[q1]) | q1 : int(1..4)]), + sum([toInt(q1 != p_PermutationAsFunction_PermutationFunction_Function1D[q1]) | q1 : int(1..4)]) <= 3 + diff --git a/tests/exhaustive/basic/perms/01_representation/unnamed/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/permutation.essence b/tests/exhaustive/basic/perms/01_representation/unnamed/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/permutation.essence new file mode 100644 index 0000000000..5083fed5ca --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/unnamed/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/permutation.essence @@ -0,0 +1,5 @@ +letting n be new type of size 4 + +find p : permutation (minSize 2, maxSize 3) of n + +such that true From 8172ad164d415c5747c77c84d51caa045fad20b4 Mon Sep 17 00:00:00 2001 From: Chris Jefferson Date: Mon, 10 Aug 2020 17:29:31 +0100 Subject: [PATCH 112/229] Add exhaustive permutation tests - part 2 --- .../model-permutation-solution000001.solution | 3 +++ .../expected/model-permutation.eprime-param | 3 +++ .../expected/model.eprime | 7 +++++++ .../permutation.essence | 11 +++++++++++ .../0001_given_permutation_in_param/permutation.param | 1 + .../expected/model-solution000001.solution | 3 +++ .../expected/model.eprime | 6 ++++++ .../permutation.essence | 10 ++++++++++ .../expected/model-solution000001.solution | 4 ++++ .../expected/model-solution000002.solution | 4 ++++ .../expected/model-solution000003.solution | 4 ++++ .../expected/model-solution000004.solution | 4 ++++ .../expected/model-solution000005.solution | 4 ++++ .../expected/model-solution000006.solution | 4 ++++ .../expected/model-solution000007.solution | 4 ++++ .../expected/model-solution000008.solution | 4 ++++ .../expected/model-solution000009.solution | 4 ++++ .../expected/model-solution000010.solution | 4 ++++ .../expected/model-solution000011.solution | 4 ++++ .../expected/model-solution000012.solution | 4 ++++ .../expected/model-solution000013.solution | 4 ++++ .../expected/model-solution000014.solution | 4 ++++ .../expected/model-solution000015.solution | 4 ++++ .../expected/model-solution000016.solution | 4 ++++ .../expected/model-solution000017.solution | 4 ++++ .../expected/model-solution000018.solution | 4 ++++ .../expected/model-solution000019.solution | 4 ++++ .../expected/model-solution000020.solution | 4 ++++ .../expected/model-solution000021.solution | 4 ++++ .../expected/model-solution000022.solution | 4 ++++ .../expected/model-solution000023.solution | 4 ++++ .../expected/model-solution000024.solution | 4 ++++ .../expected/model-solution000025.solution | 4 ++++ .../expected/model-solution000026.solution | 4 ++++ .../expected/model-solution000027.solution | 4 ++++ .../expected/model-solution000028.solution | 4 ++++ .../expected/model-solution000029.solution | 4 ++++ .../expected/model-solution000030.solution | 4 ++++ .../expected/model-solution000031.solution | 4 ++++ .../expected/model-solution000032.solution | 4 ++++ .../expected/model-solution000033.solution | 4 ++++ .../expected/model-solution000034.solution | 4 ++++ .../expected/model-solution000035.solution | 4 ++++ .../expected/model-solution000036.solution | 4 ++++ .../expected/model-solution000037.solution | 4 ++++ .../expected/model-solution000038.solution | 4 ++++ .../expected/model-solution000039.solution | 4 ++++ .../expected/model-solution000040.solution | 4 ++++ .../expected/model-solution000041.solution | 4 ++++ .../expected/model-solution000042.solution | 4 ++++ .../expected/model-solution000043.solution | 4 ++++ .../expected/model-solution000044.solution | 4 ++++ .../expected/model-solution000045.solution | 4 ++++ .../expected/model-solution000046.solution | 4 ++++ .../expected/model-solution000047.solution | 4 ++++ .../expected/model-solution000048.solution | 4 ++++ .../expected/model-solution000049.solution | 4 ++++ .../expected/model-solution000050.solution | 4 ++++ .../expected/model-solution000051.solution | 4 ++++ .../expected/model-solution000052.solution | 4 ++++ .../expected/model-solution000053.solution | 4 ++++ .../expected/model-solution000054.solution | 4 ++++ .../expected/model-solution000055.solution | 4 ++++ .../expected/model-solution000056.solution | 4 ++++ .../expected/model-solution000057.solution | 4 ++++ .../expected/model-solution000058.solution | 4 ++++ .../expected/model-solution000059.solution | 4 ++++ .../expected/model-solution000060.solution | 4 ++++ .../expected/model-solution000061.solution | 4 ++++ .../expected/model-solution000062.solution | 4 ++++ .../expected/model-solution000063.solution | 4 ++++ .../expected/model-solution000064.solution | 4 ++++ .../expected/model-solution000065.solution | 4 ++++ .../expected/model-solution000066.solution | 4 ++++ .../expected/model-solution000067.solution | 4 ++++ .../expected/model-solution000068.solution | 4 ++++ .../expected/model-solution000069.solution | 4 ++++ .../expected/model-solution000070.solution | 4 ++++ .../expected/model-solution000071.solution | 4 ++++ .../expected/model-solution000072.solution | 4 ++++ .../expected/model-solution000073.solution | 4 ++++ .../expected/model-solution000074.solution | 4 ++++ .../expected/model-solution000075.solution | 4 ++++ .../expected/model-solution000076.solution | 4 ++++ .../expected/model-solution000077.solution | 4 ++++ .../expected/model-solution000078.solution | 4 ++++ .../expected/model-solution000079.solution | 4 ++++ .../expected/model-solution000080.solution | 4 ++++ .../expected/model-solution000081.solution | 4 ++++ .../expected/model-solution000082.solution | 4 ++++ .../expected/model-solution000083.solution | 4 ++++ .../expected/model-solution000084.solution | 4 ++++ .../expected/model-solution000085.solution | 4 ++++ .../expected/model-solution000086.solution | 4 ++++ .../expected/model-solution000087.solution | 4 ++++ .../expected/model-solution000088.solution | 4 ++++ .../expected/model-solution000089.solution | 4 ++++ .../expected/model-solution000090.solution | 4 ++++ .../expected/model-solution000091.solution | 4 ++++ .../expected/model-solution000092.solution | 4 ++++ .../expected/model-solution000093.solution | 4 ++++ .../expected/model-solution000094.solution | 4 ++++ .../expected/model-solution000095.solution | 4 ++++ .../expected/model-solution000096.solution | 4 ++++ .../expected/model-solution000097.solution | 4 ++++ .../expected/model-solution000098.solution | 4 ++++ .../expected/model-solution000099.solution | 4 ++++ .../expected/model-solution000100.solution | 4 ++++ .../expected/model-solution000101.solution | 4 ++++ .../expected/model-solution000102.solution | 4 ++++ .../expected/model-solution000103.solution | 4 ++++ .../expected/model-solution000104.solution | 4 ++++ .../expected/model-solution000105.solution | 4 ++++ .../expected/model-solution000106.solution | 4 ++++ .../expected/model-solution000107.solution | 4 ++++ .../expected/model-solution000108.solution | 4 ++++ .../expected/model-solution000109.solution | 4 ++++ .../expected/model-solution000110.solution | 4 ++++ .../expected/model-solution000111.solution | 4 ++++ .../expected/model-solution000112.solution | 4 ++++ .../expected/model-solution000113.solution | 4 ++++ .../expected/model-solution000114.solution | 4 ++++ .../expected/model-solution000115.solution | 4 ++++ .../expected/model-solution000116.solution | 4 ++++ .../expected/model-solution000117.solution | 4 ++++ .../expected/model-solution000118.solution | 4 ++++ .../expected/model-solution000119.solution | 4 ++++ .../expected/model-solution000120.solution | 4 ++++ .../expected/model-solution000121.solution | 4 ++++ .../expected/model-solution000122.solution | 4 ++++ .../expected/model-solution000123.solution | 4 ++++ .../expected/model-solution000124.solution | 4 ++++ .../expected/model-solution000125.solution | 4 ++++ .../expected/model-solution000126.solution | 4 ++++ .../expected/model-solution000127.solution | 4 ++++ .../expected/model-solution000128.solution | 4 ++++ .../expected/model-solution000129.solution | 4 ++++ .../expected/model-solution000130.solution | 4 ++++ .../expected/model-solution000131.solution | 4 ++++ .../expected/model-solution000132.solution | 4 ++++ .../expected/model-solution000133.solution | 4 ++++ .../expected/model-solution000134.solution | 4 ++++ .../expected/model-solution000135.solution | 4 ++++ .../enum/0003_find_permutation/expected/model.eprime | 11 +++++++++++ .../enum/0003_find_permutation/permutation.essence | 10 ++++++++++ .../model-permutation-solution000001.solution | 3 +++ .../expected/model-permutation.eprime-param | 3 +++ .../expected/model.eprime | 7 +++++++ .../permutation.essence | 11 +++++++++++ .../0001_given_permutation_in_param/permutation.param | 1 + .../expected/model-solution000001.solution | 3 +++ .../expected/model.eprime | 6 ++++++ .../permutation.essence | 9 +++++++++ .../expected/model-solution000001.solution | 4 ++++ .../expected/model-solution000002.solution | 4 ++++ .../expected/model-solution000003.solution | 4 ++++ .../expected/model-solution000004.solution | 4 ++++ .../expected/model-solution000005.solution | 4 ++++ .../expected/model-solution000006.solution | 4 ++++ .../expected/model-solution000007.solution | 4 ++++ .../expected/model-solution000008.solution | 4 ++++ .../expected/model-solution000009.solution | 4 ++++ .../expected/model-solution000010.solution | 4 ++++ .../expected/model-solution000011.solution | 4 ++++ .../expected/model-solution000012.solution | 4 ++++ .../expected/model-solution000013.solution | 4 ++++ .../expected/model-solution000014.solution | 4 ++++ .../expected/model-solution000015.solution | 4 ++++ .../expected/model-solution000016.solution | 4 ++++ .../expected/model-solution000017.solution | 4 ++++ .../expected/model-solution000018.solution | 4 ++++ .../expected/model-solution000019.solution | 4 ++++ .../expected/model-solution000020.solution | 4 ++++ .../expected/model-solution000021.solution | 4 ++++ .../expected/model-solution000022.solution | 4 ++++ .../expected/model-solution000023.solution | 4 ++++ .../expected/model-solution000024.solution | 4 ++++ .../expected/model-solution000025.solution | 4 ++++ .../expected/model-solution000026.solution | 4 ++++ .../expected/model-solution000027.solution | 4 ++++ .../expected/model-solution000028.solution | 4 ++++ .../expected/model-solution000029.solution | 4 ++++ .../expected/model-solution000030.solution | 4 ++++ .../expected/model-solution000031.solution | 4 ++++ .../expected/model-solution000032.solution | 4 ++++ .../expected/model-solution000033.solution | 4 ++++ .../expected/model-solution000034.solution | 4 ++++ .../expected/model-solution000035.solution | 4 ++++ .../expected/model-solution000036.solution | 4 ++++ .../expected/model-solution000037.solution | 4 ++++ .../expected/model-solution000038.solution | 4 ++++ .../expected/model-solution000039.solution | 4 ++++ .../expected/model-solution000040.solution | 4 ++++ .../expected/model-solution000041.solution | 4 ++++ .../expected/model-solution000042.solution | 4 ++++ .../expected/model-solution000043.solution | 4 ++++ .../expected/model-solution000044.solution | 4 ++++ .../expected/model-solution000045.solution | 4 ++++ .../expected/model-solution000046.solution | 4 ++++ .../expected/model-solution000047.solution | 4 ++++ .../expected/model-solution000048.solution | 4 ++++ .../expected/model-solution000049.solution | 4 ++++ .../expected/model-solution000050.solution | 4 ++++ .../expected/model-solution000051.solution | 4 ++++ .../expected/model-solution000052.solution | 4 ++++ .../expected/model-solution000053.solution | 4 ++++ .../expected/model-solution000054.solution | 4 ++++ .../expected/model-solution000055.solution | 4 ++++ .../expected/model-solution000056.solution | 4 ++++ .../expected/model-solution000057.solution | 4 ++++ .../expected/model-solution000058.solution | 4 ++++ .../expected/model-solution000059.solution | 4 ++++ .../expected/model-solution000060.solution | 4 ++++ .../expected/model-solution000061.solution | 4 ++++ .../expected/model-solution000062.solution | 4 ++++ .../expected/model-solution000063.solution | 4 ++++ .../expected/model-solution000064.solution | 4 ++++ .../expected/model-solution000065.solution | 4 ++++ .../expected/model-solution000066.solution | 4 ++++ .../expected/model-solution000067.solution | 4 ++++ .../expected/model-solution000068.solution | 4 ++++ .../expected/model-solution000069.solution | 4 ++++ .../expected/model-solution000070.solution | 4 ++++ .../expected/model-solution000071.solution | 4 ++++ .../expected/model-solution000072.solution | 4 ++++ .../expected/model-solution000073.solution | 4 ++++ .../expected/model-solution000074.solution | 4 ++++ .../expected/model-solution000075.solution | 4 ++++ .../expected/model-solution000076.solution | 4 ++++ .../expected/model-solution000077.solution | 4 ++++ .../expected/model-solution000078.solution | 4 ++++ .../expected/model-solution000079.solution | 4 ++++ .../expected/model-solution000080.solution | 4 ++++ .../expected/model-solution000081.solution | 4 ++++ .../expected/model-solution000082.solution | 4 ++++ .../expected/model-solution000083.solution | 4 ++++ .../expected/model-solution000084.solution | 4 ++++ .../expected/model-solution000085.solution | 4 ++++ .../expected/model-solution000086.solution | 4 ++++ .../expected/model-solution000087.solution | 4 ++++ .../expected/model-solution000088.solution | 4 ++++ .../expected/model-solution000089.solution | 4 ++++ .../expected/model-solution000090.solution | 4 ++++ .../expected/model-solution000091.solution | 4 ++++ .../expected/model-solution000092.solution | 4 ++++ .../expected/model-solution000093.solution | 4 ++++ .../expected/model-solution000094.solution | 4 ++++ .../expected/model-solution000095.solution | 4 ++++ .../expected/model-solution000096.solution | 4 ++++ .../expected/model-solution000097.solution | 4 ++++ .../expected/model-solution000098.solution | 4 ++++ .../expected/model-solution000099.solution | 4 ++++ .../expected/model-solution000100.solution | 4 ++++ .../expected/model-solution000101.solution | 4 ++++ .../expected/model-solution000102.solution | 4 ++++ .../expected/model-solution000103.solution | 4 ++++ .../expected/model-solution000104.solution | 4 ++++ .../expected/model-solution000105.solution | 4 ++++ .../expected/model-solution000106.solution | 4 ++++ .../expected/model-solution000107.solution | 4 ++++ .../expected/model-solution000108.solution | 4 ++++ .../expected/model-solution000109.solution | 4 ++++ .../expected/model-solution000110.solution | 4 ++++ .../expected/model-solution000111.solution | 4 ++++ .../expected/model-solution000112.solution | 4 ++++ .../expected/model-solution000113.solution | 4 ++++ .../expected/model-solution000114.solution | 4 ++++ .../expected/model-solution000115.solution | 4 ++++ .../expected/model-solution000116.solution | 4 ++++ .../expected/model-solution000117.solution | 4 ++++ .../expected/model-solution000118.solution | 4 ++++ .../expected/model-solution000119.solution | 4 ++++ .../expected/model-solution000120.solution | 4 ++++ .../expected/model-solution000121.solution | 4 ++++ .../expected/model-solution000122.solution | 4 ++++ .../expected/model-solution000123.solution | 4 ++++ .../expected/model-solution000124.solution | 4 ++++ .../expected/model-solution000125.solution | 4 ++++ .../expected/model-solution000126.solution | 4 ++++ .../expected/model-solution000127.solution | 4 ++++ .../expected/model-solution000128.solution | 4 ++++ .../expected/model-solution000129.solution | 4 ++++ .../expected/model-solution000130.solution | 4 ++++ .../expected/model-solution000131.solution | 4 ++++ .../expected/model-solution000132.solution | 4 ++++ .../expected/model-solution000133.solution | 4 ++++ .../expected/model-solution000134.solution | 4 ++++ .../expected/model-solution000135.solution | 4 ++++ .../int/0003_find_permutation/expected/model.eprime | 11 +++++++++++ .../int/0003_find_permutation/permutation.essence | 9 +++++++++ .../expected/model-solution000001.solution | 5 +++++ .../expected/model-solution000002.solution | 5 +++++ .../expected/model-solution000003.solution | 5 +++++ .../expected/model-solution000004.solution | 5 +++++ .../expected/model-solution000005.solution | 5 +++++ .../expected/model-solution000006.solution | 5 +++++ .../expected/model-solution000007.solution | 5 +++++ .../expected/model-solution000008.solution | 5 +++++ .../expected/model-solution000009.solution | 5 +++++ .../expected/model-solution000010.solution | 5 +++++ .../expected/model-solution000011.solution | 5 +++++ .../expected/model-solution000012.solution | 5 +++++ .../expected/model-solution000013.solution | 5 +++++ .../expected/model-solution000014.solution | 5 +++++ .../expected/model-solution000015.solution | 5 +++++ .../expected/model-solution000016.solution | 5 +++++ .../expected/model-solution000017.solution | 5 +++++ .../expected/model-solution000018.solution | 5 +++++ .../expected/model-solution000019.solution | 5 +++++ .../expected/model-solution000020.solution | 5 +++++ .../expected/model-solution000021.solution | 5 +++++ .../expected/model-solution000022.solution | 5 +++++ .../expected/model-solution000023.solution | 5 +++++ .../expected/model-solution000024.solution | 5 +++++ .../expected/model-solution000025.solution | 5 +++++ .../expected/model-solution000026.solution | 5 +++++ .../expected/model-solution000027.solution | 5 +++++ .../expected/model-solution000028.solution | 5 +++++ .../expected/model-solution000029.solution | 5 +++++ .../expected/model-solution000030.solution | 5 +++++ .../expected/model-solution000031.solution | 5 +++++ .../expected/model-solution000032.solution | 5 +++++ .../expected/model-solution000033.solution | 5 +++++ .../expected/model-solution000034.solution | 5 +++++ .../expected/model-solution000035.solution | 5 +++++ .../expected/model-solution000036.solution | 5 +++++ .../expected/model-solution000037.solution | 5 +++++ .../expected/model-solution000038.solution | 5 +++++ .../expected/model-solution000039.solution | 5 +++++ .../expected/model-solution000040.solution | 5 +++++ .../expected/model-solution000041.solution | 5 +++++ .../expected/model-solution000042.solution | 5 +++++ .../expected/model-solution000043.solution | 5 +++++ .../expected/model-solution000044.solution | 5 +++++ .../expected/model-solution000045.solution | 5 +++++ .../expected/model-solution000046.solution | 5 +++++ .../expected/model-solution000047.solution | 5 +++++ .../expected/model-solution000048.solution | 5 +++++ .../expected/model-solution000049.solution | 5 +++++ .../expected/model-solution000050.solution | 5 +++++ .../expected/model-solution000051.solution | 5 +++++ .../expected/model-solution000052.solution | 5 +++++ .../expected/model-solution000053.solution | 5 +++++ .../expected/model-solution000054.solution | 5 +++++ .../expected/model-solution000055.solution | 5 +++++ .../expected/model-solution000056.solution | 5 +++++ .../expected/model-solution000057.solution | 5 +++++ .../expected/model-solution000058.solution | 5 +++++ .../expected/model-solution000059.solution | 5 +++++ .../expected/model-solution000060.solution | 5 +++++ .../expected/model-solution000061.solution | 5 +++++ .../expected/model-solution000062.solution | 5 +++++ .../expected/model-solution000063.solution | 5 +++++ .../expected/model-solution000064.solution | 5 +++++ .../expected/model-solution000065.solution | 5 +++++ .../expected/model-solution000066.solution | 5 +++++ .../expected/model-solution000067.solution | 5 +++++ .../expected/model-solution000068.solution | 5 +++++ .../expected/model-solution000069.solution | 5 +++++ .../expected/model-solution000070.solution | 5 +++++ .../expected/model-solution000071.solution | 5 +++++ .../expected/model-solution000072.solution | 5 +++++ .../expected/model-solution000073.solution | 5 +++++ .../expected/model-solution000074.solution | 5 +++++ .../expected/model-solution000075.solution | 5 +++++ .../expected/model-solution000076.solution | 5 +++++ .../expected/model-solution000077.solution | 5 +++++ .../expected/model-solution000078.solution | 5 +++++ .../expected/model-solution000079.solution | 5 +++++ .../expected/model-solution000080.solution | 5 +++++ .../expected/model-solution000081.solution | 5 +++++ .../expected/model-solution000082.solution | 5 +++++ .../expected/model-solution000083.solution | 5 +++++ .../expected/model-solution000084.solution | 5 +++++ .../expected/model-solution000085.solution | 5 +++++ .../expected/model-solution000086.solution | 5 +++++ .../expected/model-solution000087.solution | 5 +++++ .../expected/model-solution000088.solution | 5 +++++ .../expected/model-solution000089.solution | 5 +++++ .../expected/model-solution000090.solution | 5 +++++ .../expected/model-solution000091.solution | 5 +++++ .../expected/model-solution000092.solution | 5 +++++ .../expected/model-solution000093.solution | 5 +++++ .../expected/model-solution000094.solution | 5 +++++ .../expected/model-solution000095.solution | 5 +++++ .../expected/model-solution000096.solution | 5 +++++ .../expected/model-solution000097.solution | 5 +++++ .../expected/model-solution000098.solution | 5 +++++ .../expected/model-solution000099.solution | 5 +++++ .../expected/model-solution000100.solution | 5 +++++ .../expected/model-solution000101.solution | 5 +++++ .../expected/model-solution000102.solution | 5 +++++ .../expected/model-solution000103.solution | 5 +++++ .../expected/model-solution000104.solution | 5 +++++ .../expected/model-solution000105.solution | 5 +++++ .../expected/model-solution000106.solution | 5 +++++ .../expected/model-solution000107.solution | 5 +++++ .../expected/model-solution000108.solution | 5 +++++ .../expected/model-solution000109.solution | 5 +++++ .../expected/model-solution000110.solution | 5 +++++ .../expected/model-solution000111.solution | 5 +++++ .../expected/model-solution000112.solution | 5 +++++ .../expected/model-solution000113.solution | 5 +++++ .../expected/model-solution000114.solution | 5 +++++ .../expected/model-solution000115.solution | 5 +++++ .../expected/model-solution000116.solution | 5 +++++ .../expected/model-solution000117.solution | 5 +++++ .../expected/model-solution000118.solution | 5 +++++ .../expected/model-solution000119.solution | 5 +++++ .../expected/model-solution000120.solution | 5 +++++ .../expected/model-solution000121.solution | 5 +++++ .../expected/model-solution000122.solution | 5 +++++ .../expected/model-solution000123.solution | 5 +++++ .../expected/model-solution000124.solution | 5 +++++ .../expected/model-solution000125.solution | 5 +++++ .../expected/model-solution000126.solution | 5 +++++ .../expected/model-solution000127.solution | 5 +++++ .../expected/model-solution000128.solution | 5 +++++ .../expected/model-solution000129.solution | 5 +++++ .../expected/model-solution000130.solution | 5 +++++ .../expected/model-solution000131.solution | 5 +++++ .../expected/model-solution000132.solution | 5 +++++ .../expected/model-solution000133.solution | 5 +++++ .../expected/model-solution000134.solution | 5 +++++ .../expected/model-solution000135.solution | 5 +++++ .../0003_find_permutation/expected/model.eprime | 11 +++++++++++ .../unnamed/0003_find_permutation/permutation.essence | 10 ++++++++++ .../0003_find_permutation/permutation.solution | 5 +++++ 428 files changed, 1909 insertions(+) create mode 100644 tests/exhaustive/basic/perms/02_cardinality/enum/0001_given_permutation_in_param/expected/model-permutation-solution000001.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/enum/0001_given_permutation_in_param/expected/model-permutation.eprime-param create mode 100644 tests/exhaustive/basic/perms/02_cardinality/enum/0001_given_permutation_in_param/expected/model.eprime create mode 100644 tests/exhaustive/basic/perms/02_cardinality/enum/0001_given_permutation_in_param/permutation.essence create mode 100644 tests/exhaustive/basic/perms/02_cardinality/enum/0001_given_permutation_in_param/permutation.param create mode 100644 tests/exhaustive/basic/perms/02_cardinality/enum/0002_letting_permutation_in_model/expected/model-solution000001.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/enum/0002_letting_permutation_in_model/expected/model.eprime create mode 100644 tests/exhaustive/basic/perms/02_cardinality/enum/0002_letting_permutation_in_model/permutation.essence create mode 100644 tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000001.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000002.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000003.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000004.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000005.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000006.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000007.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000008.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000009.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000010.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000011.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000012.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000013.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000014.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000015.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000016.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000017.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000018.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000019.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000020.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000021.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000022.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000023.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000024.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000025.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000026.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000027.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000028.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000029.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000030.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000031.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000032.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000033.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000034.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000035.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000036.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000037.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000038.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000039.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000040.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000041.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000042.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000043.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000044.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000045.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000046.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000047.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000048.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000049.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000050.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000051.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000052.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000053.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000054.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000055.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000056.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000057.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000058.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000059.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000060.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000061.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000062.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000063.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000064.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000065.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000066.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000067.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000068.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000069.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000070.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000071.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000072.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000073.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000074.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000075.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000076.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000077.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000078.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000079.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000080.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000081.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000082.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000083.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000084.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000085.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000086.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000087.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000088.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000089.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000090.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000091.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000092.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000093.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000094.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000095.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000096.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000097.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000098.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000099.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000100.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000101.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000102.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000103.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000104.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000105.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000106.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000107.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000108.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000109.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000110.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000111.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000112.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000113.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000114.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000115.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000116.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000117.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000118.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000119.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000120.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000121.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000122.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000123.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000124.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000125.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000126.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000127.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000128.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000129.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000130.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000131.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000132.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000133.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000134.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000135.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model.eprime create mode 100644 tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/permutation.essence create mode 100644 tests/exhaustive/basic/perms/02_cardinality/int/0001_given_permutation_in_param/expected/model-permutation-solution000001.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/int/0001_given_permutation_in_param/expected/model-permutation.eprime-param create mode 100644 tests/exhaustive/basic/perms/02_cardinality/int/0001_given_permutation_in_param/expected/model.eprime create mode 100644 tests/exhaustive/basic/perms/02_cardinality/int/0001_given_permutation_in_param/permutation.essence create mode 100644 tests/exhaustive/basic/perms/02_cardinality/int/0001_given_permutation_in_param/permutation.param create mode 100644 tests/exhaustive/basic/perms/02_cardinality/int/0002_letting_permutation_in_model/expected/model-solution000001.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/int/0002_letting_permutation_in_model/expected/model.eprime create mode 100644 tests/exhaustive/basic/perms/02_cardinality/int/0002_letting_permutation_in_model/permutation.essence create mode 100644 tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000001.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000002.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000003.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000004.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000005.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000006.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000007.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000008.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000009.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000010.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000011.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000012.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000013.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000014.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000015.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000016.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000017.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000018.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000019.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000020.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000021.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000022.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000023.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000024.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000025.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000026.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000027.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000028.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000029.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000030.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000031.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000032.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000033.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000034.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000035.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000036.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000037.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000038.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000039.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000040.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000041.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000042.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000043.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000044.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000045.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000046.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000047.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000048.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000049.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000050.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000051.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000052.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000053.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000054.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000055.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000056.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000057.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000058.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000059.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000060.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000061.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000062.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000063.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000064.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000065.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000066.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000067.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000068.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000069.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000070.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000071.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000072.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000073.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000074.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000075.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000076.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000077.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000078.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000079.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000080.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000081.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000082.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000083.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000084.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000085.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000086.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000087.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000088.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000089.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000090.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000091.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000092.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000093.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000094.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000095.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000096.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000097.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000098.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000099.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000100.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000101.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000102.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000103.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000104.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000105.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000106.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000107.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000108.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000109.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000110.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000111.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000112.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000113.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000114.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000115.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000116.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000117.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000118.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000119.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000120.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000121.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000122.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000123.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000124.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000125.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000126.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000127.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000128.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000129.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000130.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000131.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000132.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000133.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000134.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000135.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model.eprime create mode 100644 tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/permutation.essence create mode 100644 tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000001.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000002.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000003.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000004.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000005.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000006.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000007.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000008.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000009.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000010.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000011.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000012.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000013.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000014.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000015.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000016.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000017.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000018.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000019.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000020.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000021.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000022.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000023.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000024.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000025.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000026.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000027.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000028.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000029.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000030.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000031.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000032.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000033.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000034.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000035.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000036.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000037.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000038.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000039.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000040.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000041.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000042.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000043.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000044.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000045.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000046.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000047.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000048.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000049.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000050.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000051.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000052.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000053.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000054.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000055.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000056.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000057.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000058.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000059.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000060.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000061.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000062.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000063.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000064.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000065.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000066.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000067.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000068.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000069.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000070.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000071.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000072.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000073.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000074.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000075.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000076.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000077.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000078.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000079.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000080.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000081.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000082.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000083.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000084.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000085.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000086.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000087.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000088.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000089.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000090.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000091.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000092.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000093.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000094.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000095.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000096.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000097.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000098.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000099.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000100.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000101.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000102.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000103.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000104.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000105.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000106.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000107.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000108.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000109.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000110.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000111.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000112.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000113.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000114.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000115.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000116.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000117.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000118.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000119.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000120.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000121.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000122.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000123.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000124.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000125.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000126.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000127.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000128.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000129.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000130.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000131.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000132.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000133.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000134.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000135.solution create mode 100644 tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model.eprime create mode 100644 tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/permutation.essence create mode 100644 tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/permutation.solution diff --git a/tests/exhaustive/basic/perms/02_cardinality/enum/0001_given_permutation_in_param/expected/model-permutation-solution000001.solution b/tests/exhaustive/basic/perms/02_cardinality/enum/0001_given_permutation_in_param/expected/model-permutation-solution000001.solution new file mode 100644 index 0000000000..96980679cc --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/enum/0001_given_permutation_in_param/expected/model-permutation-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting i be 3 diff --git a/tests/exhaustive/basic/perms/02_cardinality/enum/0001_given_permutation_in_param/expected/model-permutation.eprime-param b/tests/exhaustive/basic/perms/02_cardinality/enum/0001_given_permutation_in_param/expected/model-permutation.eprime-param new file mode 100644 index 0000000000..c2bddee0e8 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/enum/0001_given_permutation_in_param/expected/model-permutation.eprime-param @@ -0,0 +1,3 @@ +language ESSENCE' 1.0 + +letting p_PermutationAsFunction_PermutationFunction_Function1D be [3, 2, 4, 1; int(1..4)] diff --git a/tests/exhaustive/basic/perms/02_cardinality/enum/0001_given_permutation_in_param/expected/model.eprime b/tests/exhaustive/basic/perms/02_cardinality/enum/0001_given_permutation_in_param/expected/model.eprime new file mode 100644 index 0000000000..e05a7bb583 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/enum/0001_given_permutation_in_param/expected/model.eprime @@ -0,0 +1,7 @@ +language ESSENCE' 1.0 + +given p_PermutationAsFunction_PermutationFunction_Function1D: matrix indexed by [int(1..4)] of int(1..4) +find i: int(0..10) +branching on [i] +such that i = sum([toInt(q1 != p_PermutationAsFunction_PermutationFunction_Function1D[q1]) | q1 : int(1..4)]) + diff --git a/tests/exhaustive/basic/perms/02_cardinality/enum/0001_given_permutation_in_param/permutation.essence b/tests/exhaustive/basic/perms/02_cardinality/enum/0001_given_permutation_in_param/permutation.essence new file mode 100644 index 0000000000..115d51f9b8 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/enum/0001_given_permutation_in_param/permutation.essence @@ -0,0 +1,11 @@ +letting n be new type enum {E1,E2,E3,E4} + +given p : permutation of n + +find i : int(0..10) + +such that i = |p| + + + + diff --git a/tests/exhaustive/basic/perms/02_cardinality/enum/0001_given_permutation_in_param/permutation.param b/tests/exhaustive/basic/perms/02_cardinality/enum/0001_given_permutation_in_param/permutation.param new file mode 100644 index 0000000000..19349bb872 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/enum/0001_given_permutation_in_param/permutation.param @@ -0,0 +1 @@ +letting p be permutation((E1,E3,E4)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/enum/0002_letting_permutation_in_model/expected/model-solution000001.solution b/tests/exhaustive/basic/perms/02_cardinality/enum/0002_letting_permutation_in_model/expected/model-solution000001.solution new file mode 100644 index 0000000000..96980679cc --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/enum/0002_letting_permutation_in_model/expected/model-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting i be 3 diff --git a/tests/exhaustive/basic/perms/02_cardinality/enum/0002_letting_permutation_in_model/expected/model.eprime b/tests/exhaustive/basic/perms/02_cardinality/enum/0002_letting_permutation_in_model/expected/model.eprime new file mode 100644 index 0000000000..95deebf783 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/enum/0002_letting_permutation_in_model/expected/model.eprime @@ -0,0 +1,6 @@ +language ESSENCE' 1.0 + +find i: int(0..10) +branching on [i] +such that i = 3 + diff --git a/tests/exhaustive/basic/perms/02_cardinality/enum/0002_letting_permutation_in_model/permutation.essence b/tests/exhaustive/basic/perms/02_cardinality/enum/0002_letting_permutation_in_model/permutation.essence new file mode 100644 index 0000000000..91903a1aa5 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/enum/0002_letting_permutation_in_model/permutation.essence @@ -0,0 +1,10 @@ +letting n be new type enum {E1,E2,E3,E4} +letting p be permutation((E1,E3,E4)) + +find i : int(0..10) + +such that i = |p| + + + + diff --git a/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000001.solution b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000001.solution new file mode 100644 index 0000000000..dec34f7fde --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((E3, E4), (E5, E6)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000002.solution b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000002.solution new file mode 100644 index 0000000000..2568382f9c --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((E3, E4, E5, E6)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000003.solution b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000003.solution new file mode 100644 index 0000000000..b9c7e60549 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((E3, E4, E6, E5)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000004.solution b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000004.solution new file mode 100644 index 0000000000..086f159d67 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000004.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((E3, E5, E6, E4)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000005.solution b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000005.solution new file mode 100644 index 0000000000..9f7186e8db --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000005.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((E3, E5), (E4, E6)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000006.solution b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000006.solution new file mode 100644 index 0000000000..ff88494e86 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000006.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((E3, E5, E4, E6)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000007.solution b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000007.solution new file mode 100644 index 0000000000..0553f6a6ab --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000007.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((E3, E6, E5, E4)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000008.solution b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000008.solution new file mode 100644 index 0000000000..b89f60e083 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000008.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((E3, E6, E4, E5)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000009.solution b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000009.solution new file mode 100644 index 0000000000..361544be6f --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000009.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((E3, E6), (E4, E5)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000010.solution b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000010.solution new file mode 100644 index 0000000000..8da343f92b --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000010.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((E2, E3), (E5, E6)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000011.solution b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000011.solution new file mode 100644 index 0000000000..aa47f20fb9 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000011.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((E2, E3), (E4, E5)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000012.solution b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000012.solution new file mode 100644 index 0000000000..871fb07564 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000012.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((E2, E3), (E4, E6)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000013.solution b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000013.solution new file mode 100644 index 0000000000..d9bc1050b7 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000013.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((E2, E3, E4, E5)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000014.solution b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000014.solution new file mode 100644 index 0000000000..df693ea586 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000014.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((E2, E3, E4, E6)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000015.solution b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000015.solution new file mode 100644 index 0000000000..af418a914b --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000015.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((E2, E3, E5, E4)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000016.solution b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000016.solution new file mode 100644 index 0000000000..e6544f34b4 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000016.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((E2, E3, E5, E6)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000017.solution b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000017.solution new file mode 100644 index 0000000000..e3e118f066 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000017.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((E2, E3, E6, E4)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000018.solution b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000018.solution new file mode 100644 index 0000000000..8d93922e2d --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000018.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((E2, E3, E6, E5)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000019.solution b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000019.solution new file mode 100644 index 0000000000..3042d92d85 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000019.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((E2, E4, E5, E3)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000020.solution b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000020.solution new file mode 100644 index 0000000000..e8506ff63d --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000020.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((E2, E4, E6, E3)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000021.solution b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000021.solution new file mode 100644 index 0000000000..464210eb6f --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000021.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((E2, E4), (E5, E6)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000022.solution b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000022.solution new file mode 100644 index 0000000000..ff6afb8904 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000022.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((E2, E4, E5, E6)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000023.solution b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000023.solution new file mode 100644 index 0000000000..8ab7f38ada --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000023.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((E2, E4, E6, E5)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000024.solution b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000024.solution new file mode 100644 index 0000000000..9122e744ca --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000024.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((E2, E4), (E3, E5)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000025.solution b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000025.solution new file mode 100644 index 0000000000..288c8073eb --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000025.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((E2, E4, E3, E5)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000026.solution b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000026.solution new file mode 100644 index 0000000000..59efe2aa24 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000026.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((E2, E4), (E3, E6)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000027.solution b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000027.solution new file mode 100644 index 0000000000..311081f627 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000027.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((E2, E4, E3, E6)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000028.solution b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000028.solution new file mode 100644 index 0000000000..f211362336 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000028.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((E2, E5, E4, E3)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000029.solution b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000029.solution new file mode 100644 index 0000000000..5766877eec --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000029.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((E2, E5, E6, E3)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000030.solution b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000030.solution new file mode 100644 index 0000000000..4a5d833017 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000030.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((E2, E5, E6, E4)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000031.solution b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000031.solution new file mode 100644 index 0000000000..8c94d656f5 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000031.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((E2, E5), (E4, E6)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000032.solution b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000032.solution new file mode 100644 index 0000000000..7fa40f90ee --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000032.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((E2, E5, E4, E6)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000033.solution b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000033.solution new file mode 100644 index 0000000000..a2f9a0b4ef --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000033.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((E2, E5, E3, E4)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000034.solution b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000034.solution new file mode 100644 index 0000000000..7cbfa28abc --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000034.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((E2, E5), (E3, E4)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000035.solution b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000035.solution new file mode 100644 index 0000000000..b0adddaa8a --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000035.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((E2, E5), (E3, E6)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000036.solution b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000036.solution new file mode 100644 index 0000000000..1d34e24b39 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000036.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((E2, E5, E3, E6)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000037.solution b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000037.solution new file mode 100644 index 0000000000..7e7fbcd1a6 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000037.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((E2, E6, E4, E3)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000038.solution b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000038.solution new file mode 100644 index 0000000000..614c783606 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000038.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((E2, E6, E5, E3)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000039.solution b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000039.solution new file mode 100644 index 0000000000..ecd405c25a --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000039.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((E2, E6, E5, E4)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000040.solution b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000040.solution new file mode 100644 index 0000000000..8935991620 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000040.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((E2, E6, E4, E5)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000041.solution b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000041.solution new file mode 100644 index 0000000000..a4a46a0e97 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000041.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((E2, E6), (E4, E5)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000042.solution b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000042.solution new file mode 100644 index 0000000000..a1a29222ee --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000042.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((E2, E6, E3, E4)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000043.solution b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000043.solution new file mode 100644 index 0000000000..0fbf8652ac --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000043.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((E2, E6), (E3, E4)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000044.solution b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000044.solution new file mode 100644 index 0000000000..d9bfad72d3 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000044.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((E2, E6, E3, E5)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000045.solution b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000045.solution new file mode 100644 index 0000000000..3eb7321098 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000045.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((E2, E6), (E3, E5)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000046.solution b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000046.solution new file mode 100644 index 0000000000..086c1201c2 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000046.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((E1, E2), (E5, E6)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000047.solution b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000047.solution new file mode 100644 index 0000000000..b156e99206 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000047.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((E1, E2), (E4, E5)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000048.solution b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000048.solution new file mode 100644 index 0000000000..47e35bbfdc --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000048.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((E1, E2), (E4, E6)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000049.solution b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000049.solution new file mode 100644 index 0000000000..f323cb7969 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000049.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((E1, E2), (E3, E4)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000050.solution b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000050.solution new file mode 100644 index 0000000000..27b7bd01dc --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000050.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((E1, E2), (E3, E5)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000051.solution b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000051.solution new file mode 100644 index 0000000000..7fa98ac017 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000051.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((E1, E2), (E3, E6)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000052.solution b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000052.solution new file mode 100644 index 0000000000..60322c54ac --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000052.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((E1, E2, E3, E4)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000053.solution b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000053.solution new file mode 100644 index 0000000000..decfba4136 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000053.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((E1, E2, E3, E5)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000054.solution b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000054.solution new file mode 100644 index 0000000000..d6e1004ec2 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000054.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((E1, E2, E3, E6)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000055.solution b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000055.solution new file mode 100644 index 0000000000..fe72250a1b --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000055.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((E1, E2, E4, E3)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000056.solution b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000056.solution new file mode 100644 index 0000000000..601654ac81 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000056.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((E1, E2, E4, E5)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000057.solution b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000057.solution new file mode 100644 index 0000000000..9fbe31eab1 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000057.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((E1, E2, E4, E6)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000058.solution b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000058.solution new file mode 100644 index 0000000000..4048fdb542 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000058.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((E1, E2, E5, E3)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000059.solution b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000059.solution new file mode 100644 index 0000000000..8fa0290765 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000059.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((E1, E2, E5, E4)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000060.solution b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000060.solution new file mode 100644 index 0000000000..50efac802e --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000060.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((E1, E2, E5, E6)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000061.solution b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000061.solution new file mode 100644 index 0000000000..276ea0e18a --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000061.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((E1, E2, E6, E3)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000062.solution b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000062.solution new file mode 100644 index 0000000000..374c1e82e8 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000062.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((E1, E2, E6, E4)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000063.solution b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000063.solution new file mode 100644 index 0000000000..2d1b3d4a34 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000063.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((E1, E2, E6, E5)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000064.solution b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000064.solution new file mode 100644 index 0000000000..c99411e65b --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000064.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((E1, E3, E4, E2)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000065.solution b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000065.solution new file mode 100644 index 0000000000..d9f7f67b54 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000065.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((E1, E3, E5, E2)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000066.solution b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000066.solution new file mode 100644 index 0000000000..c3438187ac --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000066.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((E1, E3, E6, E2)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000067.solution b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000067.solution new file mode 100644 index 0000000000..8aadeff655 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000067.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((E1, E3), (E5, E6)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000068.solution b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000068.solution new file mode 100644 index 0000000000..1142d0c000 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000068.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((E1, E3), (E4, E5)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000069.solution b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000069.solution new file mode 100644 index 0000000000..ed67076f9b --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000069.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((E1, E3), (E4, E6)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000070.solution b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000070.solution new file mode 100644 index 0000000000..fc6437105b --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000070.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((E1, E3, E4, E5)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000071.solution b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000071.solution new file mode 100644 index 0000000000..c3ceb20b57 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000071.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((E1, E3, E4, E6)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000072.solution b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000072.solution new file mode 100644 index 0000000000..2e1973a6b9 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000072.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((E1, E3, E5, E4)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000073.solution b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000073.solution new file mode 100644 index 0000000000..4cbd3e5610 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000073.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((E1, E3, E5, E6)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000074.solution b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000074.solution new file mode 100644 index 0000000000..bc04a8a152 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000074.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((E1, E3, E6, E4)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000075.solution b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000075.solution new file mode 100644 index 0000000000..57062fcb7c --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000075.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((E1, E3, E6, E5)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000076.solution b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000076.solution new file mode 100644 index 0000000000..91e8153cfa --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000076.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((E1, E3), (E2, E4)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000077.solution b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000077.solution new file mode 100644 index 0000000000..f5975cebdb --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000077.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((E1, E3, E2, E4)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000078.solution b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000078.solution new file mode 100644 index 0000000000..d22a14ddd9 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000078.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((E1, E3), (E2, E5)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000079.solution b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000079.solution new file mode 100644 index 0000000000..fe09e06140 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000079.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((E1, E3, E2, E5)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000080.solution b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000080.solution new file mode 100644 index 0000000000..1ab274d37d --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000080.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((E1, E3), (E2, E6)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000081.solution b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000081.solution new file mode 100644 index 0000000000..96e274c772 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000081.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((E1, E3, E2, E6)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000082.solution b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000082.solution new file mode 100644 index 0000000000..5b0aa3af71 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000082.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((E1, E4, E3, E2)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000083.solution b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000083.solution new file mode 100644 index 0000000000..284f0fa3d7 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000083.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((E1, E4, E5, E2)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000084.solution b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000084.solution new file mode 100644 index 0000000000..f852438ce2 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000084.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((E1, E4, E6, E2)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000085.solution b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000085.solution new file mode 100644 index 0000000000..7aed860e57 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000085.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((E1, E4, E5, E3)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000086.solution b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000086.solution new file mode 100644 index 0000000000..d01273fe29 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000086.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((E1, E4, E6, E3)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000087.solution b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000087.solution new file mode 100644 index 0000000000..074fb5db10 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000087.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((E1, E4), (E5, E6)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000088.solution b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000088.solution new file mode 100644 index 0000000000..f2c7e637cc --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000088.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((E1, E4, E5, E6)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000089.solution b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000089.solution new file mode 100644 index 0000000000..794ae44696 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000089.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((E1, E4, E6, E5)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000090.solution b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000090.solution new file mode 100644 index 0000000000..c46a5df3f4 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000090.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((E1, E4), (E3, E5)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000091.solution b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000091.solution new file mode 100644 index 0000000000..2646f3ca89 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000091.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((E1, E4, E3, E5)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000092.solution b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000092.solution new file mode 100644 index 0000000000..9d8d5a1016 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000092.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((E1, E4), (E3, E6)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000093.solution b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000093.solution new file mode 100644 index 0000000000..ae3b5500c8 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000093.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((E1, E4, E3, E6)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000094.solution b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000094.solution new file mode 100644 index 0000000000..2a032e7c16 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000094.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((E1, E4, E2, E3)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000095.solution b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000095.solution new file mode 100644 index 0000000000..e569bf4581 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000095.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((E1, E4), (E2, E3)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000096.solution b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000096.solution new file mode 100644 index 0000000000..d8dff4ea4b --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000096.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((E1, E4), (E2, E5)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000097.solution b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000097.solution new file mode 100644 index 0000000000..a9c87d8d72 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000097.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((E1, E4, E2, E5)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000098.solution b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000098.solution new file mode 100644 index 0000000000..a727c0c033 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000098.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((E1, E4), (E2, E6)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000099.solution b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000099.solution new file mode 100644 index 0000000000..cadd33607c --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000099.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((E1, E4, E2, E6)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000100.solution b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000100.solution new file mode 100644 index 0000000000..35e203a0e0 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000100.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((E1, E5, E3, E2)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000101.solution b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000101.solution new file mode 100644 index 0000000000..4d79679f10 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000101.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((E1, E5, E4, E2)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000102.solution b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000102.solution new file mode 100644 index 0000000000..6e595a0b29 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000102.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((E1, E5, E6, E2)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000103.solution b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000103.solution new file mode 100644 index 0000000000..f0c14f00b3 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000103.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((E1, E5, E4, E3)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000104.solution b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000104.solution new file mode 100644 index 0000000000..0c324feb32 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000104.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((E1, E5, E6, E3)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000105.solution b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000105.solution new file mode 100644 index 0000000000..57f7d36a4b --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000105.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((E1, E5, E6, E4)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000106.solution b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000106.solution new file mode 100644 index 0000000000..27bff0de95 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000106.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((E1, E5), (E4, E6)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000107.solution b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000107.solution new file mode 100644 index 0000000000..7881c5cc1f --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000107.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((E1, E5, E4, E6)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000108.solution b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000108.solution new file mode 100644 index 0000000000..518a871f9a --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000108.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((E1, E5, E3, E4)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000109.solution b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000109.solution new file mode 100644 index 0000000000..efa53e69ff --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000109.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((E1, E5), (E3, E4)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000110.solution b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000110.solution new file mode 100644 index 0000000000..be4607035a --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000110.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((E1, E5), (E3, E6)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000111.solution b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000111.solution new file mode 100644 index 0000000000..845009387b --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000111.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((E1, E5, E3, E6)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000112.solution b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000112.solution new file mode 100644 index 0000000000..d27f1d1aea --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000112.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((E1, E5, E2, E3)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000113.solution b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000113.solution new file mode 100644 index 0000000000..3cf8abb69e --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000113.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((E1, E5), (E2, E3)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000114.solution b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000114.solution new file mode 100644 index 0000000000..6c2c4ab06a --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000114.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((E1, E5, E2, E4)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000115.solution b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000115.solution new file mode 100644 index 0000000000..2825c5b824 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000115.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((E1, E5), (E2, E4)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000116.solution b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000116.solution new file mode 100644 index 0000000000..bd1565b2df --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000116.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((E1, E5), (E2, E6)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000117.solution b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000117.solution new file mode 100644 index 0000000000..d15fc278b0 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000117.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((E1, E5, E2, E6)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000118.solution b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000118.solution new file mode 100644 index 0000000000..7bc999d7aa --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000118.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((E1, E6, E3, E2)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000119.solution b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000119.solution new file mode 100644 index 0000000000..19fda1c638 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000119.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((E1, E6, E4, E2)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000120.solution b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000120.solution new file mode 100644 index 0000000000..71b4c99b4b --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000120.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((E1, E6, E5, E2)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000121.solution b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000121.solution new file mode 100644 index 0000000000..93417bd13e --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000121.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((E1, E6, E4, E3)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000122.solution b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000122.solution new file mode 100644 index 0000000000..c3bfaac83a --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000122.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((E1, E6, E5, E3)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000123.solution b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000123.solution new file mode 100644 index 0000000000..668880c1e2 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000123.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((E1, E6, E5, E4)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000124.solution b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000124.solution new file mode 100644 index 0000000000..dec983baff --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000124.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((E1, E6, E4, E5)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000125.solution b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000125.solution new file mode 100644 index 0000000000..50ac88bc64 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000125.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((E1, E6), (E4, E5)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000126.solution b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000126.solution new file mode 100644 index 0000000000..2f8d730dfc --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000126.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((E1, E6, E3, E4)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000127.solution b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000127.solution new file mode 100644 index 0000000000..a5b338900f --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000127.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((E1, E6), (E3, E4)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000128.solution b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000128.solution new file mode 100644 index 0000000000..c96216accc --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000128.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((E1, E6, E3, E5)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000129.solution b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000129.solution new file mode 100644 index 0000000000..377806e6b6 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000129.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((E1, E6), (E3, E5)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000130.solution b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000130.solution new file mode 100644 index 0000000000..c1e24f697d --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000130.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((E1, E6, E2, E3)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000131.solution b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000131.solution new file mode 100644 index 0000000000..d6c5d9fe07 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000131.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((E1, E6), (E2, E3)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000132.solution b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000132.solution new file mode 100644 index 0000000000..2d96df2d28 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000132.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((E1, E6, E2, E4)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000133.solution b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000133.solution new file mode 100644 index 0000000000..fc08467569 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000133.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((E1, E6), (E2, E4)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000134.solution b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000134.solution new file mode 100644 index 0000000000..4e45d37a4c --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000134.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((E1, E6, E2, E5)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000135.solution b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000135.solution new file mode 100644 index 0000000000..d580dfc612 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model-solution000135.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((E1, E6), (E2, E5)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model.eprime b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model.eprime new file mode 100644 index 0000000000..27f6b498e7 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model.eprime @@ -0,0 +1,11 @@ +language ESSENCE' 1.0 + +find p_PermutationAsFunction_PermutationFunction_Function1D: matrix indexed by [int(1..6)] of int(1..6) +find i: int(0..10) +branching on [p_PermutationAsFunction_PermutationFunction_Function1D, i] +such that + i = sum([toInt(q5 != p_PermutationAsFunction_PermutationFunction_Function1D[q5]) | q5 : int(1..6)]), + allDiff(p_PermutationAsFunction_PermutationFunction_Function1D), + and([or([p_PermutationAsFunction_PermutationFunction_Function1D[q3] = q2 | q3 : int(1..6)]) | q2 : int(1..6)]), + 4 = sum([toInt(q1 != p_PermutationAsFunction_PermutationFunction_Function1D[q1]) | q1 : int(1..6)]) + diff --git a/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/permutation.essence b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/permutation.essence new file mode 100644 index 0000000000..663987f4f6 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/permutation.essence @@ -0,0 +1,10 @@ +letting n be new type enum {E1,E2,E3,E4,E5,E6} +find p : permutation (size 4) of n + +find i : int(0..10) + +such that i = |p| + + + + diff --git a/tests/exhaustive/basic/perms/02_cardinality/int/0001_given_permutation_in_param/expected/model-permutation-solution000001.solution b/tests/exhaustive/basic/perms/02_cardinality/int/0001_given_permutation_in_param/expected/model-permutation-solution000001.solution new file mode 100644 index 0000000000..96980679cc --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/int/0001_given_permutation_in_param/expected/model-permutation-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting i be 3 diff --git a/tests/exhaustive/basic/perms/02_cardinality/int/0001_given_permutation_in_param/expected/model-permutation.eprime-param b/tests/exhaustive/basic/perms/02_cardinality/int/0001_given_permutation_in_param/expected/model-permutation.eprime-param new file mode 100644 index 0000000000..c2bddee0e8 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/int/0001_given_permutation_in_param/expected/model-permutation.eprime-param @@ -0,0 +1,3 @@ +language ESSENCE' 1.0 + +letting p_PermutationAsFunction_PermutationFunction_Function1D be [3, 2, 4, 1; int(1..4)] diff --git a/tests/exhaustive/basic/perms/02_cardinality/int/0001_given_permutation_in_param/expected/model.eprime b/tests/exhaustive/basic/perms/02_cardinality/int/0001_given_permutation_in_param/expected/model.eprime new file mode 100644 index 0000000000..e05a7bb583 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/int/0001_given_permutation_in_param/expected/model.eprime @@ -0,0 +1,7 @@ +language ESSENCE' 1.0 + +given p_PermutationAsFunction_PermutationFunction_Function1D: matrix indexed by [int(1..4)] of int(1..4) +find i: int(0..10) +branching on [i] +such that i = sum([toInt(q1 != p_PermutationAsFunction_PermutationFunction_Function1D[q1]) | q1 : int(1..4)]) + diff --git a/tests/exhaustive/basic/perms/02_cardinality/int/0001_given_permutation_in_param/permutation.essence b/tests/exhaustive/basic/perms/02_cardinality/int/0001_given_permutation_in_param/permutation.essence new file mode 100644 index 0000000000..f69bae145b --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/int/0001_given_permutation_in_param/permutation.essence @@ -0,0 +1,11 @@ +letting n be 4 + +given p : permutation of int(1..n) + +find i : int(0..10) + +such that i = |p| + + + + diff --git a/tests/exhaustive/basic/perms/02_cardinality/int/0001_given_permutation_in_param/permutation.param b/tests/exhaustive/basic/perms/02_cardinality/int/0001_given_permutation_in_param/permutation.param new file mode 100644 index 0000000000..8a8c516801 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/int/0001_given_permutation_in_param/permutation.param @@ -0,0 +1 @@ +letting p be permutation((1,3,4)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/int/0002_letting_permutation_in_model/expected/model-solution000001.solution b/tests/exhaustive/basic/perms/02_cardinality/int/0002_letting_permutation_in_model/expected/model-solution000001.solution new file mode 100644 index 0000000000..96980679cc --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/int/0002_letting_permutation_in_model/expected/model-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting i be 3 diff --git a/tests/exhaustive/basic/perms/02_cardinality/int/0002_letting_permutation_in_model/expected/model.eprime b/tests/exhaustive/basic/perms/02_cardinality/int/0002_letting_permutation_in_model/expected/model.eprime new file mode 100644 index 0000000000..95deebf783 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/int/0002_letting_permutation_in_model/expected/model.eprime @@ -0,0 +1,6 @@ +language ESSENCE' 1.0 + +find i: int(0..10) +branching on [i] +such that i = 3 + diff --git a/tests/exhaustive/basic/perms/02_cardinality/int/0002_letting_permutation_in_model/permutation.essence b/tests/exhaustive/basic/perms/02_cardinality/int/0002_letting_permutation_in_model/permutation.essence new file mode 100644 index 0000000000..4f1c879426 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/int/0002_letting_permutation_in_model/permutation.essence @@ -0,0 +1,9 @@ +letting p be permutation((1,3,4)) + +find i : int(0..10) + +such that i = |p| + + + + diff --git a/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000001.solution b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000001.solution new file mode 100644 index 0000000000..b5c955fc33 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((3, 4), (5, 6)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000002.solution b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000002.solution new file mode 100644 index 0000000000..1fcb8b8e77 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((3, 4, 5, 6)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000003.solution b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000003.solution new file mode 100644 index 0000000000..d53c4d8c27 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((3, 4, 6, 5)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000004.solution b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000004.solution new file mode 100644 index 0000000000..4095a95868 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000004.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((3, 5, 6, 4)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000005.solution b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000005.solution new file mode 100644 index 0000000000..5872d937ff --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000005.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((3, 5), (4, 6)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000006.solution b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000006.solution new file mode 100644 index 0000000000..62b5072a68 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000006.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((3, 5, 4, 6)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000007.solution b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000007.solution new file mode 100644 index 0000000000..5962bbb578 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000007.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((3, 6, 5, 4)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000008.solution b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000008.solution new file mode 100644 index 0000000000..7d0dc8dfad --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000008.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((3, 6, 4, 5)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000009.solution b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000009.solution new file mode 100644 index 0000000000..8a35f38196 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000009.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((3, 6), (4, 5)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000010.solution b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000010.solution new file mode 100644 index 0000000000..7fdb689562 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000010.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((2, 3), (5, 6)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000011.solution b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000011.solution new file mode 100644 index 0000000000..248dc59619 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000011.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((2, 3), (4, 5)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000012.solution b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000012.solution new file mode 100644 index 0000000000..c22b2400d7 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000012.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((2, 3), (4, 6)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000013.solution b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000013.solution new file mode 100644 index 0000000000..500ff2cf16 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000013.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((2, 3, 4, 5)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000014.solution b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000014.solution new file mode 100644 index 0000000000..fd9c2b7139 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000014.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((2, 3, 4, 6)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000015.solution b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000015.solution new file mode 100644 index 0000000000..933574ba37 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000015.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((2, 3, 5, 4)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000016.solution b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000016.solution new file mode 100644 index 0000000000..f1236e4b7b --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000016.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((2, 3, 5, 6)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000017.solution b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000017.solution new file mode 100644 index 0000000000..1c83e6ce92 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000017.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((2, 3, 6, 4)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000018.solution b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000018.solution new file mode 100644 index 0000000000..2f213bc263 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000018.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((2, 3, 6, 5)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000019.solution b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000019.solution new file mode 100644 index 0000000000..724653f688 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000019.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((2, 4, 5, 3)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000020.solution b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000020.solution new file mode 100644 index 0000000000..a4f0d953a9 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000020.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((2, 4, 6, 3)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000021.solution b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000021.solution new file mode 100644 index 0000000000..bbdc7a8720 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000021.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((2, 4), (5, 6)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000022.solution b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000022.solution new file mode 100644 index 0000000000..7b55ed5ee0 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000022.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((2, 4, 5, 6)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000023.solution b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000023.solution new file mode 100644 index 0000000000..d30c55e6d1 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000023.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((2, 4, 6, 5)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000024.solution b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000024.solution new file mode 100644 index 0000000000..e8857f570f --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000024.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((2, 4), (3, 5)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000025.solution b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000025.solution new file mode 100644 index 0000000000..c708df0c2b --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000025.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((2, 4, 3, 5)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000026.solution b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000026.solution new file mode 100644 index 0000000000..1d51aae600 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000026.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((2, 4), (3, 6)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000027.solution b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000027.solution new file mode 100644 index 0000000000..1c7c054912 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000027.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((2, 4, 3, 6)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000028.solution b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000028.solution new file mode 100644 index 0000000000..6e7fd7d8c6 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000028.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((2, 5, 4, 3)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000029.solution b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000029.solution new file mode 100644 index 0000000000..56a2ede4bb --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000029.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((2, 5, 6, 3)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000030.solution b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000030.solution new file mode 100644 index 0000000000..b869f8b46f --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000030.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((2, 5, 6, 4)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000031.solution b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000031.solution new file mode 100644 index 0000000000..68fc4c41d3 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000031.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((2, 5), (4, 6)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000032.solution b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000032.solution new file mode 100644 index 0000000000..4a7dbe5a34 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000032.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((2, 5, 4, 6)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000033.solution b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000033.solution new file mode 100644 index 0000000000..63a64dc2bc --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000033.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((2, 5, 3, 4)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000034.solution b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000034.solution new file mode 100644 index 0000000000..006851aa2b --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000034.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((2, 5), (3, 4)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000035.solution b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000035.solution new file mode 100644 index 0000000000..472ab2f404 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000035.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((2, 5), (3, 6)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000036.solution b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000036.solution new file mode 100644 index 0000000000..77a2c683a1 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000036.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((2, 5, 3, 6)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000037.solution b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000037.solution new file mode 100644 index 0000000000..de8f712d9b --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000037.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((2, 6, 4, 3)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000038.solution b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000038.solution new file mode 100644 index 0000000000..5ca9a7596c --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000038.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((2, 6, 5, 3)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000039.solution b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000039.solution new file mode 100644 index 0000000000..9672bc8989 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000039.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((2, 6, 5, 4)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000040.solution b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000040.solution new file mode 100644 index 0000000000..148b2a723c --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000040.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((2, 6, 4, 5)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000041.solution b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000041.solution new file mode 100644 index 0000000000..5c9b1950b3 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000041.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((2, 6), (4, 5)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000042.solution b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000042.solution new file mode 100644 index 0000000000..82cf11f180 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000042.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((2, 6, 3, 4)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000043.solution b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000043.solution new file mode 100644 index 0000000000..17af11aca4 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000043.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((2, 6), (3, 4)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000044.solution b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000044.solution new file mode 100644 index 0000000000..1f88859022 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000044.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((2, 6, 3, 5)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000045.solution b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000045.solution new file mode 100644 index 0000000000..3bf5d7517f --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000045.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((2, 6), (3, 5)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000046.solution b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000046.solution new file mode 100644 index 0000000000..188289646f --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000046.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((1, 2), (5, 6)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000047.solution b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000047.solution new file mode 100644 index 0000000000..9273382814 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000047.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((1, 2), (4, 5)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000048.solution b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000048.solution new file mode 100644 index 0000000000..46be273586 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000048.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((1, 2), (4, 6)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000049.solution b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000049.solution new file mode 100644 index 0000000000..d6740ec5ed --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000049.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((1, 2), (3, 4)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000050.solution b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000050.solution new file mode 100644 index 0000000000..7c5e0c496d --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000050.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((1, 2), (3, 5)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000051.solution b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000051.solution new file mode 100644 index 0000000000..5a647b1d1c --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000051.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((1, 2), (3, 6)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000052.solution b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000052.solution new file mode 100644 index 0000000000..4801d4cee4 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000052.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((1, 2, 3, 4)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000053.solution b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000053.solution new file mode 100644 index 0000000000..b704ebe16d --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000053.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((1, 2, 3, 5)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000054.solution b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000054.solution new file mode 100644 index 0000000000..992ece90f7 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000054.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((1, 2, 3, 6)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000055.solution b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000055.solution new file mode 100644 index 0000000000..2223d530bd --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000055.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((1, 2, 4, 3)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000056.solution b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000056.solution new file mode 100644 index 0000000000..d8cce611bc --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000056.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((1, 2, 4, 5)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000057.solution b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000057.solution new file mode 100644 index 0000000000..d095a92b93 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000057.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((1, 2, 4, 6)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000058.solution b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000058.solution new file mode 100644 index 0000000000..54eaabe8a3 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000058.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((1, 2, 5, 3)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000059.solution b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000059.solution new file mode 100644 index 0000000000..22a8c3babf --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000059.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((1, 2, 5, 4)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000060.solution b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000060.solution new file mode 100644 index 0000000000..c95efbe387 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000060.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((1, 2, 5, 6)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000061.solution b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000061.solution new file mode 100644 index 0000000000..4b4246e673 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000061.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((1, 2, 6, 3)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000062.solution b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000062.solution new file mode 100644 index 0000000000..3decdbed84 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000062.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((1, 2, 6, 4)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000063.solution b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000063.solution new file mode 100644 index 0000000000..4bdc639049 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000063.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((1, 2, 6, 5)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000064.solution b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000064.solution new file mode 100644 index 0000000000..cf2b44ddd9 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000064.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((1, 3, 4, 2)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000065.solution b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000065.solution new file mode 100644 index 0000000000..1713378db6 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000065.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((1, 3, 5, 2)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000066.solution b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000066.solution new file mode 100644 index 0000000000..a356a0c16c --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000066.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((1, 3, 6, 2)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000067.solution b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000067.solution new file mode 100644 index 0000000000..e4454bdd11 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000067.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((1, 3), (5, 6)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000068.solution b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000068.solution new file mode 100644 index 0000000000..bef0aa6ae9 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000068.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((1, 3), (4, 5)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000069.solution b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000069.solution new file mode 100644 index 0000000000..87dc50857f --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000069.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((1, 3), (4, 6)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000070.solution b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000070.solution new file mode 100644 index 0000000000..6425522364 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000070.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((1, 3, 4, 5)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000071.solution b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000071.solution new file mode 100644 index 0000000000..a689b1d77f --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000071.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((1, 3, 4, 6)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000072.solution b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000072.solution new file mode 100644 index 0000000000..e19e96f693 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000072.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((1, 3, 5, 4)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000073.solution b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000073.solution new file mode 100644 index 0000000000..a4c30d49a1 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000073.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((1, 3, 5, 6)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000074.solution b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000074.solution new file mode 100644 index 0000000000..12b163d173 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000074.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((1, 3, 6, 4)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000075.solution b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000075.solution new file mode 100644 index 0000000000..32e7a7cdc2 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000075.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((1, 3, 6, 5)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000076.solution b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000076.solution new file mode 100644 index 0000000000..1ae7b3c96e --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000076.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((1, 3), (2, 4)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000077.solution b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000077.solution new file mode 100644 index 0000000000..3e25adc31a --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000077.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((1, 3, 2, 4)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000078.solution b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000078.solution new file mode 100644 index 0000000000..9bfe84cb36 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000078.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((1, 3), (2, 5)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000079.solution b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000079.solution new file mode 100644 index 0000000000..4f7d90a697 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000079.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((1, 3, 2, 5)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000080.solution b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000080.solution new file mode 100644 index 0000000000..b9a44f1707 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000080.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((1, 3), (2, 6)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000081.solution b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000081.solution new file mode 100644 index 0000000000..07516e43d9 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000081.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((1, 3, 2, 6)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000082.solution b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000082.solution new file mode 100644 index 0000000000..8d10c7e3a4 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000082.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((1, 4, 3, 2)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000083.solution b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000083.solution new file mode 100644 index 0000000000..54c82473dd --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000083.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((1, 4, 5, 2)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000084.solution b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000084.solution new file mode 100644 index 0000000000..2057eb53ba --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000084.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((1, 4, 6, 2)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000085.solution b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000085.solution new file mode 100644 index 0000000000..0874b3eda5 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000085.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((1, 4, 5, 3)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000086.solution b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000086.solution new file mode 100644 index 0000000000..f25e517e43 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000086.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((1, 4, 6, 3)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000087.solution b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000087.solution new file mode 100644 index 0000000000..9cb6395e01 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000087.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((1, 4), (5, 6)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000088.solution b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000088.solution new file mode 100644 index 0000000000..2fe50d11a8 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000088.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((1, 4, 5, 6)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000089.solution b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000089.solution new file mode 100644 index 0000000000..d4bff66d3e --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000089.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((1, 4, 6, 5)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000090.solution b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000090.solution new file mode 100644 index 0000000000..f471600eba --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000090.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((1, 4), (3, 5)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000091.solution b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000091.solution new file mode 100644 index 0000000000..4d0f9612d0 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000091.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((1, 4, 3, 5)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000092.solution b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000092.solution new file mode 100644 index 0000000000..9e98de44da --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000092.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((1, 4), (3, 6)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000093.solution b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000093.solution new file mode 100644 index 0000000000..4a434be2cf --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000093.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((1, 4, 3, 6)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000094.solution b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000094.solution new file mode 100644 index 0000000000..2d3202bde3 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000094.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((1, 4, 2, 3)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000095.solution b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000095.solution new file mode 100644 index 0000000000..b0e972b6e1 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000095.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((1, 4), (2, 3)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000096.solution b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000096.solution new file mode 100644 index 0000000000..27bfda880c --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000096.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((1, 4), (2, 5)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000097.solution b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000097.solution new file mode 100644 index 0000000000..ade36d524e --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000097.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((1, 4, 2, 5)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000098.solution b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000098.solution new file mode 100644 index 0000000000..5627d01138 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000098.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((1, 4), (2, 6)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000099.solution b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000099.solution new file mode 100644 index 0000000000..7319573bea --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000099.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((1, 4, 2, 6)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000100.solution b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000100.solution new file mode 100644 index 0000000000..d4218a9d95 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000100.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((1, 5, 3, 2)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000101.solution b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000101.solution new file mode 100644 index 0000000000..f6cf558b97 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000101.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((1, 5, 4, 2)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000102.solution b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000102.solution new file mode 100644 index 0000000000..048e897f7d --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000102.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((1, 5, 6, 2)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000103.solution b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000103.solution new file mode 100644 index 0000000000..a9729ada90 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000103.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((1, 5, 4, 3)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000104.solution b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000104.solution new file mode 100644 index 0000000000..340822f726 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000104.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((1, 5, 6, 3)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000105.solution b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000105.solution new file mode 100644 index 0000000000..cabf526647 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000105.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((1, 5, 6, 4)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000106.solution b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000106.solution new file mode 100644 index 0000000000..f5195e5f9e --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000106.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((1, 5), (4, 6)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000107.solution b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000107.solution new file mode 100644 index 0000000000..8054d5660c --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000107.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((1, 5, 4, 6)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000108.solution b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000108.solution new file mode 100644 index 0000000000..8f00646a5d --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000108.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((1, 5, 3, 4)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000109.solution b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000109.solution new file mode 100644 index 0000000000..d330e98fd1 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000109.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((1, 5), (3, 4)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000110.solution b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000110.solution new file mode 100644 index 0000000000..023788faf7 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000110.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((1, 5), (3, 6)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000111.solution b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000111.solution new file mode 100644 index 0000000000..b4e92ba3cb --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000111.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((1, 5, 3, 6)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000112.solution b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000112.solution new file mode 100644 index 0000000000..7c35b42d64 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000112.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((1, 5, 2, 3)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000113.solution b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000113.solution new file mode 100644 index 0000000000..d509cece8f --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000113.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((1, 5), (2, 3)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000114.solution b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000114.solution new file mode 100644 index 0000000000..477c9ec9f4 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000114.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((1, 5, 2, 4)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000115.solution b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000115.solution new file mode 100644 index 0000000000..b41ec00a65 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000115.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((1, 5), (2, 4)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000116.solution b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000116.solution new file mode 100644 index 0000000000..baff48ec3a --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000116.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((1, 5), (2, 6)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000117.solution b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000117.solution new file mode 100644 index 0000000000..f863fc1389 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000117.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((1, 5, 2, 6)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000118.solution b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000118.solution new file mode 100644 index 0000000000..46999a747f --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000118.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((1, 6, 3, 2)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000119.solution b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000119.solution new file mode 100644 index 0000000000..08c12c5701 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000119.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((1, 6, 4, 2)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000120.solution b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000120.solution new file mode 100644 index 0000000000..43cb218f90 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000120.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((1, 6, 5, 2)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000121.solution b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000121.solution new file mode 100644 index 0000000000..6977d417e5 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000121.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((1, 6, 4, 3)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000122.solution b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000122.solution new file mode 100644 index 0000000000..6ba5031ed1 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000122.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((1, 6, 5, 3)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000123.solution b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000123.solution new file mode 100644 index 0000000000..66fd4b0422 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000123.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((1, 6, 5, 4)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000124.solution b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000124.solution new file mode 100644 index 0000000000..9db9be795c --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000124.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((1, 6, 4, 5)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000125.solution b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000125.solution new file mode 100644 index 0000000000..d36939a291 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000125.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((1, 6), (4, 5)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000126.solution b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000126.solution new file mode 100644 index 0000000000..f03a35bab9 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000126.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((1, 6, 3, 4)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000127.solution b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000127.solution new file mode 100644 index 0000000000..201575f940 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000127.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((1, 6), (3, 4)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000128.solution b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000128.solution new file mode 100644 index 0000000000..25ae36e558 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000128.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((1, 6, 3, 5)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000129.solution b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000129.solution new file mode 100644 index 0000000000..db646a5c0d --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000129.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((1, 6), (3, 5)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000130.solution b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000130.solution new file mode 100644 index 0000000000..6db3905910 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000130.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((1, 6, 2, 3)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000131.solution b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000131.solution new file mode 100644 index 0000000000..533db695d8 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000131.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((1, 6), (2, 3)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000132.solution b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000132.solution new file mode 100644 index 0000000000..6bc1bed0e3 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000132.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((1, 6, 2, 4)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000133.solution b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000133.solution new file mode 100644 index 0000000000..70f9f53c74 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000133.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((1, 6), (2, 4)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000134.solution b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000134.solution new file mode 100644 index 0000000000..9c36492577 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000134.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((1, 6, 2, 5)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000135.solution b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000135.solution new file mode 100644 index 0000000000..59da82efa6 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model-solution000135.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting i be 4 +letting p be permutation((1, 6), (2, 5)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model.eprime b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model.eprime new file mode 100644 index 0000000000..27f6b498e7 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model.eprime @@ -0,0 +1,11 @@ +language ESSENCE' 1.0 + +find p_PermutationAsFunction_PermutationFunction_Function1D: matrix indexed by [int(1..6)] of int(1..6) +find i: int(0..10) +branching on [p_PermutationAsFunction_PermutationFunction_Function1D, i] +such that + i = sum([toInt(q5 != p_PermutationAsFunction_PermutationFunction_Function1D[q5]) | q5 : int(1..6)]), + allDiff(p_PermutationAsFunction_PermutationFunction_Function1D), + and([or([p_PermutationAsFunction_PermutationFunction_Function1D[q3] = q2 | q3 : int(1..6)]) | q2 : int(1..6)]), + 4 = sum([toInt(q1 != p_PermutationAsFunction_PermutationFunction_Function1D[q1]) | q1 : int(1..6)]) + diff --git a/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/permutation.essence b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/permutation.essence new file mode 100644 index 0000000000..59127b82f2 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/permutation.essence @@ -0,0 +1,9 @@ +find p : permutation (size 4) of int(1..6) + +find i : int(0..10) + +such that i = |p| + + + + diff --git a/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000001.solution b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000001.solution new file mode 100644 index 0000000000..1d4f90ede1 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000001.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6} +letting i be 4 +letting p be permutation((n_3, n_4), (n_5, n_6)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000002.solution b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000002.solution new file mode 100644 index 0000000000..3e3bb16e9d --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000002.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6} +letting i be 4 +letting p be permutation((n_3, n_4, n_5, n_6)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000003.solution b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000003.solution new file mode 100644 index 0000000000..5ef04c1d04 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000003.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6} +letting i be 4 +letting p be permutation((n_3, n_4, n_6, n_5)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000004.solution b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000004.solution new file mode 100644 index 0000000000..a571fbe93a --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000004.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6} +letting i be 4 +letting p be permutation((n_3, n_5, n_6, n_4)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000005.solution b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000005.solution new file mode 100644 index 0000000000..481824cd94 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000005.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6} +letting i be 4 +letting p be permutation((n_3, n_5), (n_4, n_6)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000006.solution b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000006.solution new file mode 100644 index 0000000000..24c99a1030 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000006.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6} +letting i be 4 +letting p be permutation((n_3, n_5, n_4, n_6)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000007.solution b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000007.solution new file mode 100644 index 0000000000..2252fdb1e4 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000007.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6} +letting i be 4 +letting p be permutation((n_3, n_6, n_5, n_4)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000008.solution b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000008.solution new file mode 100644 index 0000000000..a2f1be5bfc --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000008.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6} +letting i be 4 +letting p be permutation((n_3, n_6, n_4, n_5)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000009.solution b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000009.solution new file mode 100644 index 0000000000..6d226f8893 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000009.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6} +letting i be 4 +letting p be permutation((n_3, n_6), (n_4, n_5)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000010.solution b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000010.solution new file mode 100644 index 0000000000..a74b734cba --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000010.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6} +letting i be 4 +letting p be permutation((n_2, n_3), (n_5, n_6)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000011.solution b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000011.solution new file mode 100644 index 0000000000..5c2e302273 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000011.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6} +letting i be 4 +letting p be permutation((n_2, n_3), (n_4, n_5)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000012.solution b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000012.solution new file mode 100644 index 0000000000..c0ac7148da --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000012.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6} +letting i be 4 +letting p be permutation((n_2, n_3), (n_4, n_6)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000013.solution b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000013.solution new file mode 100644 index 0000000000..74bfc03415 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000013.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6} +letting i be 4 +letting p be permutation((n_2, n_3, n_4, n_5)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000014.solution b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000014.solution new file mode 100644 index 0000000000..cdffd1b5a1 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000014.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6} +letting i be 4 +letting p be permutation((n_2, n_3, n_4, n_6)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000015.solution b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000015.solution new file mode 100644 index 0000000000..f93ca5b4e5 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000015.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6} +letting i be 4 +letting p be permutation((n_2, n_3, n_5, n_4)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000016.solution b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000016.solution new file mode 100644 index 0000000000..49360f42ff --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000016.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6} +letting i be 4 +letting p be permutation((n_2, n_3, n_5, n_6)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000017.solution b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000017.solution new file mode 100644 index 0000000000..82e1797f81 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000017.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6} +letting i be 4 +letting p be permutation((n_2, n_3, n_6, n_4)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000018.solution b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000018.solution new file mode 100644 index 0000000000..9a309bc238 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000018.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6} +letting i be 4 +letting p be permutation((n_2, n_3, n_6, n_5)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000019.solution b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000019.solution new file mode 100644 index 0000000000..b6c87c524d --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000019.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6} +letting i be 4 +letting p be permutation((n_2, n_4, n_5, n_3)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000020.solution b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000020.solution new file mode 100644 index 0000000000..e6834bf6c9 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000020.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6} +letting i be 4 +letting p be permutation((n_2, n_4, n_6, n_3)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000021.solution b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000021.solution new file mode 100644 index 0000000000..8efe85f8c4 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000021.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6} +letting i be 4 +letting p be permutation((n_2, n_4), (n_5, n_6)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000022.solution b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000022.solution new file mode 100644 index 0000000000..c3ae2c9025 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000022.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6} +letting i be 4 +letting p be permutation((n_2, n_4, n_5, n_6)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000023.solution b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000023.solution new file mode 100644 index 0000000000..d21f0104b2 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000023.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6} +letting i be 4 +letting p be permutation((n_2, n_4, n_6, n_5)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000024.solution b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000024.solution new file mode 100644 index 0000000000..1f5e46ffe3 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000024.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6} +letting i be 4 +letting p be permutation((n_2, n_4), (n_3, n_5)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000025.solution b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000025.solution new file mode 100644 index 0000000000..db43eb87a2 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000025.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6} +letting i be 4 +letting p be permutation((n_2, n_4, n_3, n_5)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000026.solution b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000026.solution new file mode 100644 index 0000000000..ac132366ae --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000026.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6} +letting i be 4 +letting p be permutation((n_2, n_4), (n_3, n_6)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000027.solution b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000027.solution new file mode 100644 index 0000000000..00cf16dc94 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000027.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6} +letting i be 4 +letting p be permutation((n_2, n_4, n_3, n_6)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000028.solution b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000028.solution new file mode 100644 index 0000000000..b5af3d14bd --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000028.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6} +letting i be 4 +letting p be permutation((n_2, n_5, n_4, n_3)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000029.solution b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000029.solution new file mode 100644 index 0000000000..abe48adfde --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000029.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6} +letting i be 4 +letting p be permutation((n_2, n_5, n_6, n_3)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000030.solution b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000030.solution new file mode 100644 index 0000000000..cf4f9c4371 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000030.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6} +letting i be 4 +letting p be permutation((n_2, n_5, n_6, n_4)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000031.solution b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000031.solution new file mode 100644 index 0000000000..97ee44b415 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000031.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6} +letting i be 4 +letting p be permutation((n_2, n_5), (n_4, n_6)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000032.solution b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000032.solution new file mode 100644 index 0000000000..e13a06a446 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000032.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6} +letting i be 4 +letting p be permutation((n_2, n_5, n_4, n_6)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000033.solution b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000033.solution new file mode 100644 index 0000000000..cc79dcf5d6 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000033.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6} +letting i be 4 +letting p be permutation((n_2, n_5, n_3, n_4)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000034.solution b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000034.solution new file mode 100644 index 0000000000..d2ec7df9c8 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000034.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6} +letting i be 4 +letting p be permutation((n_2, n_5), (n_3, n_4)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000035.solution b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000035.solution new file mode 100644 index 0000000000..27e18d2ef7 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000035.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6} +letting i be 4 +letting p be permutation((n_2, n_5), (n_3, n_6)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000036.solution b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000036.solution new file mode 100644 index 0000000000..885e37f392 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000036.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6} +letting i be 4 +letting p be permutation((n_2, n_5, n_3, n_6)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000037.solution b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000037.solution new file mode 100644 index 0000000000..8ac58de954 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000037.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6} +letting i be 4 +letting p be permutation((n_2, n_6, n_4, n_3)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000038.solution b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000038.solution new file mode 100644 index 0000000000..cb8699239a --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000038.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6} +letting i be 4 +letting p be permutation((n_2, n_6, n_5, n_3)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000039.solution b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000039.solution new file mode 100644 index 0000000000..88406b6de1 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000039.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6} +letting i be 4 +letting p be permutation((n_2, n_6, n_5, n_4)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000040.solution b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000040.solution new file mode 100644 index 0000000000..2ec9bbf396 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000040.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6} +letting i be 4 +letting p be permutation((n_2, n_6, n_4, n_5)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000041.solution b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000041.solution new file mode 100644 index 0000000000..1d3dcbfbb8 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000041.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6} +letting i be 4 +letting p be permutation((n_2, n_6), (n_4, n_5)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000042.solution b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000042.solution new file mode 100644 index 0000000000..c5c26222b8 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000042.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6} +letting i be 4 +letting p be permutation((n_2, n_6, n_3, n_4)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000043.solution b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000043.solution new file mode 100644 index 0000000000..e49e11aa83 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000043.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6} +letting i be 4 +letting p be permutation((n_2, n_6), (n_3, n_4)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000044.solution b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000044.solution new file mode 100644 index 0000000000..d8ea451b88 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000044.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6} +letting i be 4 +letting p be permutation((n_2, n_6, n_3, n_5)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000045.solution b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000045.solution new file mode 100644 index 0000000000..d0a7bc36f3 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000045.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6} +letting i be 4 +letting p be permutation((n_2, n_6), (n_3, n_5)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000046.solution b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000046.solution new file mode 100644 index 0000000000..a21fc6205b --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000046.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6} +letting i be 4 +letting p be permutation((n_1, n_2), (n_5, n_6)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000047.solution b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000047.solution new file mode 100644 index 0000000000..66e8dffe5a --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000047.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6} +letting i be 4 +letting p be permutation((n_1, n_2), (n_4, n_5)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000048.solution b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000048.solution new file mode 100644 index 0000000000..5530a42abf --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000048.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6} +letting i be 4 +letting p be permutation((n_1, n_2), (n_4, n_6)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000049.solution b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000049.solution new file mode 100644 index 0000000000..277137616e --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000049.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6} +letting i be 4 +letting p be permutation((n_1, n_2), (n_3, n_4)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000050.solution b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000050.solution new file mode 100644 index 0000000000..489fe18271 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000050.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6} +letting i be 4 +letting p be permutation((n_1, n_2), (n_3, n_5)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000051.solution b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000051.solution new file mode 100644 index 0000000000..e2d18e503a --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000051.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6} +letting i be 4 +letting p be permutation((n_1, n_2), (n_3, n_6)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000052.solution b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000052.solution new file mode 100644 index 0000000000..f7ee4b7ccc --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000052.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6} +letting i be 4 +letting p be permutation((n_1, n_2, n_3, n_4)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000053.solution b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000053.solution new file mode 100644 index 0000000000..e5031d77d4 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000053.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6} +letting i be 4 +letting p be permutation((n_1, n_2, n_3, n_5)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000054.solution b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000054.solution new file mode 100644 index 0000000000..99b862031d --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000054.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6} +letting i be 4 +letting p be permutation((n_1, n_2, n_3, n_6)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000055.solution b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000055.solution new file mode 100644 index 0000000000..4fa92e3542 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000055.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6} +letting i be 4 +letting p be permutation((n_1, n_2, n_4, n_3)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000056.solution b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000056.solution new file mode 100644 index 0000000000..338f0f1a2a --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000056.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6} +letting i be 4 +letting p be permutation((n_1, n_2, n_4, n_5)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000057.solution b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000057.solution new file mode 100644 index 0000000000..2517ba7118 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000057.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6} +letting i be 4 +letting p be permutation((n_1, n_2, n_4, n_6)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000058.solution b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000058.solution new file mode 100644 index 0000000000..a22d99be6c --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000058.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6} +letting i be 4 +letting p be permutation((n_1, n_2, n_5, n_3)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000059.solution b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000059.solution new file mode 100644 index 0000000000..87d21ee74a --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000059.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6} +letting i be 4 +letting p be permutation((n_1, n_2, n_5, n_4)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000060.solution b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000060.solution new file mode 100644 index 0000000000..325bacfaec --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000060.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6} +letting i be 4 +letting p be permutation((n_1, n_2, n_5, n_6)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000061.solution b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000061.solution new file mode 100644 index 0000000000..87259e62c8 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000061.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6} +letting i be 4 +letting p be permutation((n_1, n_2, n_6, n_3)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000062.solution b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000062.solution new file mode 100644 index 0000000000..e58a595000 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000062.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6} +letting i be 4 +letting p be permutation((n_1, n_2, n_6, n_4)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000063.solution b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000063.solution new file mode 100644 index 0000000000..db32ddd470 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000063.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6} +letting i be 4 +letting p be permutation((n_1, n_2, n_6, n_5)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000064.solution b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000064.solution new file mode 100644 index 0000000000..b321435371 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000064.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6} +letting i be 4 +letting p be permutation((n_1, n_3, n_4, n_2)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000065.solution b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000065.solution new file mode 100644 index 0000000000..ea98df2c73 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000065.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6} +letting i be 4 +letting p be permutation((n_1, n_3, n_5, n_2)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000066.solution b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000066.solution new file mode 100644 index 0000000000..8ab10602ec --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000066.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6} +letting i be 4 +letting p be permutation((n_1, n_3, n_6, n_2)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000067.solution b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000067.solution new file mode 100644 index 0000000000..0da3b18dbb --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000067.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6} +letting i be 4 +letting p be permutation((n_1, n_3), (n_5, n_6)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000068.solution b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000068.solution new file mode 100644 index 0000000000..a16b5197f1 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000068.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6} +letting i be 4 +letting p be permutation((n_1, n_3), (n_4, n_5)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000069.solution b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000069.solution new file mode 100644 index 0000000000..6002c4e2ba --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000069.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6} +letting i be 4 +letting p be permutation((n_1, n_3), (n_4, n_6)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000070.solution b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000070.solution new file mode 100644 index 0000000000..163b09f83f --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000070.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6} +letting i be 4 +letting p be permutation((n_1, n_3, n_4, n_5)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000071.solution b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000071.solution new file mode 100644 index 0000000000..703da5a236 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000071.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6} +letting i be 4 +letting p be permutation((n_1, n_3, n_4, n_6)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000072.solution b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000072.solution new file mode 100644 index 0000000000..62199256d0 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000072.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6} +letting i be 4 +letting p be permutation((n_1, n_3, n_5, n_4)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000073.solution b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000073.solution new file mode 100644 index 0000000000..d949a49a5c --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000073.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6} +letting i be 4 +letting p be permutation((n_1, n_3, n_5, n_6)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000074.solution b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000074.solution new file mode 100644 index 0000000000..f8bbba5ecb --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000074.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6} +letting i be 4 +letting p be permutation((n_1, n_3, n_6, n_4)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000075.solution b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000075.solution new file mode 100644 index 0000000000..cd28639064 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000075.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6} +letting i be 4 +letting p be permutation((n_1, n_3, n_6, n_5)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000076.solution b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000076.solution new file mode 100644 index 0000000000..7961dfd876 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000076.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6} +letting i be 4 +letting p be permutation((n_1, n_3), (n_2, n_4)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000077.solution b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000077.solution new file mode 100644 index 0000000000..80b57cc70b --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000077.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6} +letting i be 4 +letting p be permutation((n_1, n_3, n_2, n_4)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000078.solution b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000078.solution new file mode 100644 index 0000000000..4ec7971278 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000078.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6} +letting i be 4 +letting p be permutation((n_1, n_3), (n_2, n_5)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000079.solution b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000079.solution new file mode 100644 index 0000000000..cdb2d2c941 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000079.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6} +letting i be 4 +letting p be permutation((n_1, n_3, n_2, n_5)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000080.solution b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000080.solution new file mode 100644 index 0000000000..0788933504 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000080.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6} +letting i be 4 +letting p be permutation((n_1, n_3), (n_2, n_6)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000081.solution b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000081.solution new file mode 100644 index 0000000000..1cadafbcd6 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000081.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6} +letting i be 4 +letting p be permutation((n_1, n_3, n_2, n_6)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000082.solution b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000082.solution new file mode 100644 index 0000000000..b56a5c3d09 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000082.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6} +letting i be 4 +letting p be permutation((n_1, n_4, n_3, n_2)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000083.solution b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000083.solution new file mode 100644 index 0000000000..297bfcd2d2 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000083.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6} +letting i be 4 +letting p be permutation((n_1, n_4, n_5, n_2)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000084.solution b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000084.solution new file mode 100644 index 0000000000..d0cc4476f6 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000084.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6} +letting i be 4 +letting p be permutation((n_1, n_4, n_6, n_2)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000085.solution b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000085.solution new file mode 100644 index 0000000000..114357f70d --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000085.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6} +letting i be 4 +letting p be permutation((n_1, n_4, n_5, n_3)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000086.solution b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000086.solution new file mode 100644 index 0000000000..ac2f0fec2b --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000086.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6} +letting i be 4 +letting p be permutation((n_1, n_4, n_6, n_3)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000087.solution b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000087.solution new file mode 100644 index 0000000000..74d0c1d184 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000087.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6} +letting i be 4 +letting p be permutation((n_1, n_4), (n_5, n_6)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000088.solution b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000088.solution new file mode 100644 index 0000000000..a01e77d366 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000088.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6} +letting i be 4 +letting p be permutation((n_1, n_4, n_5, n_6)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000089.solution b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000089.solution new file mode 100644 index 0000000000..b8eeff705b --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000089.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6} +letting i be 4 +letting p be permutation((n_1, n_4, n_6, n_5)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000090.solution b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000090.solution new file mode 100644 index 0000000000..189ec5161c --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000090.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6} +letting i be 4 +letting p be permutation((n_1, n_4), (n_3, n_5)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000091.solution b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000091.solution new file mode 100644 index 0000000000..1c06d7229c --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000091.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6} +letting i be 4 +letting p be permutation((n_1, n_4, n_3, n_5)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000092.solution b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000092.solution new file mode 100644 index 0000000000..e0e796db84 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000092.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6} +letting i be 4 +letting p be permutation((n_1, n_4), (n_3, n_6)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000093.solution b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000093.solution new file mode 100644 index 0000000000..cc13b63e49 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000093.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6} +letting i be 4 +letting p be permutation((n_1, n_4, n_3, n_6)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000094.solution b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000094.solution new file mode 100644 index 0000000000..390118be0e --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000094.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6} +letting i be 4 +letting p be permutation((n_1, n_4, n_2, n_3)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000095.solution b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000095.solution new file mode 100644 index 0000000000..7a663cf0ec --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000095.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6} +letting i be 4 +letting p be permutation((n_1, n_4), (n_2, n_3)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000096.solution b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000096.solution new file mode 100644 index 0000000000..2714537e5c --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000096.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6} +letting i be 4 +letting p be permutation((n_1, n_4), (n_2, n_5)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000097.solution b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000097.solution new file mode 100644 index 0000000000..f1bf47c6fb --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000097.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6} +letting i be 4 +letting p be permutation((n_1, n_4, n_2, n_5)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000098.solution b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000098.solution new file mode 100644 index 0000000000..6dc29133e2 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000098.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6} +letting i be 4 +letting p be permutation((n_1, n_4), (n_2, n_6)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000099.solution b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000099.solution new file mode 100644 index 0000000000..ebcf1f0f8a --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000099.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6} +letting i be 4 +letting p be permutation((n_1, n_4, n_2, n_6)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000100.solution b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000100.solution new file mode 100644 index 0000000000..f674ea8f7e --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000100.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6} +letting i be 4 +letting p be permutation((n_1, n_5, n_3, n_2)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000101.solution b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000101.solution new file mode 100644 index 0000000000..d6529c391a --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000101.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6} +letting i be 4 +letting p be permutation((n_1, n_5, n_4, n_2)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000102.solution b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000102.solution new file mode 100644 index 0000000000..16382b60b4 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000102.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6} +letting i be 4 +letting p be permutation((n_1, n_5, n_6, n_2)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000103.solution b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000103.solution new file mode 100644 index 0000000000..c0d5fa7d6d --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000103.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6} +letting i be 4 +letting p be permutation((n_1, n_5, n_4, n_3)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000104.solution b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000104.solution new file mode 100644 index 0000000000..09f719f2d8 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000104.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6} +letting i be 4 +letting p be permutation((n_1, n_5, n_6, n_3)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000105.solution b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000105.solution new file mode 100644 index 0000000000..6b73345064 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000105.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6} +letting i be 4 +letting p be permutation((n_1, n_5, n_6, n_4)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000106.solution b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000106.solution new file mode 100644 index 0000000000..c536eaa3cd --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000106.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6} +letting i be 4 +letting p be permutation((n_1, n_5), (n_4, n_6)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000107.solution b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000107.solution new file mode 100644 index 0000000000..db5a2eea9d --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000107.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6} +letting i be 4 +letting p be permutation((n_1, n_5, n_4, n_6)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000108.solution b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000108.solution new file mode 100644 index 0000000000..6ea6293b99 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000108.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6} +letting i be 4 +letting p be permutation((n_1, n_5, n_3, n_4)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000109.solution b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000109.solution new file mode 100644 index 0000000000..a5903e3f19 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000109.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6} +letting i be 4 +letting p be permutation((n_1, n_5), (n_3, n_4)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000110.solution b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000110.solution new file mode 100644 index 0000000000..9da81801c2 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000110.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6} +letting i be 4 +letting p be permutation((n_1, n_5), (n_3, n_6)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000111.solution b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000111.solution new file mode 100644 index 0000000000..efc2b2d6f6 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000111.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6} +letting i be 4 +letting p be permutation((n_1, n_5, n_3, n_6)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000112.solution b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000112.solution new file mode 100644 index 0000000000..fffb547eb7 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000112.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6} +letting i be 4 +letting p be permutation((n_1, n_5, n_2, n_3)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000113.solution b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000113.solution new file mode 100644 index 0000000000..d38d283344 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000113.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6} +letting i be 4 +letting p be permutation((n_1, n_5), (n_2, n_3)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000114.solution b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000114.solution new file mode 100644 index 0000000000..23f55c7b25 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000114.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6} +letting i be 4 +letting p be permutation((n_1, n_5, n_2, n_4)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000115.solution b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000115.solution new file mode 100644 index 0000000000..b9ca8d50da --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000115.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6} +letting i be 4 +letting p be permutation((n_1, n_5), (n_2, n_4)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000116.solution b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000116.solution new file mode 100644 index 0000000000..626601dc76 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000116.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6} +letting i be 4 +letting p be permutation((n_1, n_5), (n_2, n_6)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000117.solution b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000117.solution new file mode 100644 index 0000000000..b0bb66ce6a --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000117.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6} +letting i be 4 +letting p be permutation((n_1, n_5, n_2, n_6)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000118.solution b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000118.solution new file mode 100644 index 0000000000..21a3ab8cfa --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000118.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6} +letting i be 4 +letting p be permutation((n_1, n_6, n_3, n_2)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000119.solution b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000119.solution new file mode 100644 index 0000000000..348f58230e --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000119.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6} +letting i be 4 +letting p be permutation((n_1, n_6, n_4, n_2)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000120.solution b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000120.solution new file mode 100644 index 0000000000..4cb81f29aa --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000120.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6} +letting i be 4 +letting p be permutation((n_1, n_6, n_5, n_2)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000121.solution b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000121.solution new file mode 100644 index 0000000000..1c648fb373 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000121.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6} +letting i be 4 +letting p be permutation((n_1, n_6, n_4, n_3)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000122.solution b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000122.solution new file mode 100644 index 0000000000..d2ad5ba814 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000122.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6} +letting i be 4 +letting p be permutation((n_1, n_6, n_5, n_3)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000123.solution b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000123.solution new file mode 100644 index 0000000000..ebf42a8211 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000123.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6} +letting i be 4 +letting p be permutation((n_1, n_6, n_5, n_4)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000124.solution b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000124.solution new file mode 100644 index 0000000000..23258e27a8 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000124.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6} +letting i be 4 +letting p be permutation((n_1, n_6, n_4, n_5)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000125.solution b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000125.solution new file mode 100644 index 0000000000..b2912f63a3 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000125.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6} +letting i be 4 +letting p be permutation((n_1, n_6), (n_4, n_5)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000126.solution b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000126.solution new file mode 100644 index 0000000000..7ba9dd9ada --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000126.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6} +letting i be 4 +letting p be permutation((n_1, n_6, n_3, n_4)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000127.solution b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000127.solution new file mode 100644 index 0000000000..cf16769e49 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000127.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6} +letting i be 4 +letting p be permutation((n_1, n_6), (n_3, n_4)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000128.solution b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000128.solution new file mode 100644 index 0000000000..11121f58d7 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000128.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6} +letting i be 4 +letting p be permutation((n_1, n_6, n_3, n_5)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000129.solution b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000129.solution new file mode 100644 index 0000000000..a8aa8d2b47 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000129.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6} +letting i be 4 +letting p be permutation((n_1, n_6), (n_3, n_5)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000130.solution b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000130.solution new file mode 100644 index 0000000000..c2f5d5f34a --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000130.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6} +letting i be 4 +letting p be permutation((n_1, n_6, n_2, n_3)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000131.solution b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000131.solution new file mode 100644 index 0000000000..4717457d60 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000131.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6} +letting i be 4 +letting p be permutation((n_1, n_6), (n_2, n_3)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000132.solution b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000132.solution new file mode 100644 index 0000000000..6d3ba40b0a --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000132.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6} +letting i be 4 +letting p be permutation((n_1, n_6, n_2, n_4)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000133.solution b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000133.solution new file mode 100644 index 0000000000..ec23144f19 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000133.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6} +letting i be 4 +letting p be permutation((n_1, n_6), (n_2, n_4)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000134.solution b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000134.solution new file mode 100644 index 0000000000..0fedefb883 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000134.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6} +letting i be 4 +letting p be permutation((n_1, n_6, n_2, n_5)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000135.solution b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000135.solution new file mode 100644 index 0000000000..0d32cd8763 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model-solution000135.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6} +letting i be 4 +letting p be permutation((n_1, n_6), (n_2, n_5)) diff --git a/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model.eprime b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model.eprime new file mode 100644 index 0000000000..27f6b498e7 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model.eprime @@ -0,0 +1,11 @@ +language ESSENCE' 1.0 + +find p_PermutationAsFunction_PermutationFunction_Function1D: matrix indexed by [int(1..6)] of int(1..6) +find i: int(0..10) +branching on [p_PermutationAsFunction_PermutationFunction_Function1D, i] +such that + i = sum([toInt(q5 != p_PermutationAsFunction_PermutationFunction_Function1D[q5]) | q5 : int(1..6)]), + allDiff(p_PermutationAsFunction_PermutationFunction_Function1D), + and([or([p_PermutationAsFunction_PermutationFunction_Function1D[q3] = q2 | q3 : int(1..6)]) | q2 : int(1..6)]), + 4 = sum([toInt(q1 != p_PermutationAsFunction_PermutationFunction_Function1D[q1]) | q1 : int(1..6)]) + diff --git a/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/permutation.essence b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/permutation.essence new file mode 100644 index 0000000000..05bc8e04fa --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/permutation.essence @@ -0,0 +1,10 @@ +letting n be new type of size 6 +find p : permutation (size 4) of n + +find i : int(0..10) + +such that i = |p| + + + + diff --git a/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/permutation.solution b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/permutation.solution new file mode 100644 index 0000000000..1d4f90ede1 --- /dev/null +++ b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/permutation.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6} +letting i be 4 +letting p be permutation((n_3, n_4), (n_5, n_6)) From 68193d65700db14b42d82c6f6b0873afac2ea998 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?O=CC=88zgu=CC=88r=20Akgu=CC=88n?= Date: Tue, 11 Aug 2020 15:45:21 +0300 Subject: [PATCH 113/229] Add support for enumerating permutation values --- src/Conjure/Language/EvaluateOp.hs | 6 ++++-- src/Conjure/Process/Enumerate.hs | 7 +++++++ 2 files changed, 11 insertions(+), 2 deletions(-) diff --git a/src/Conjure/Language/EvaluateOp.hs b/src/Conjure/Language/EvaluateOp.hs index 2d43b450ff..37eaf94d22 100644 --- a/src/Conjure/Language/EvaluateOp.hs +++ b/src/Conjure/Language/EvaluateOp.hs @@ -5,7 +5,7 @@ module Conjure.Language.EvaluateOp ( EvaluateOp(..) ) where import Conjure.Prelude import Conjure.Bug import Conjure.Language -import Conjure.Process.Enumerate ( EnumerateDomain ) +import Conjure.Process.Enumerate ( EnumerateDomain, enumerateInConstant ) import Conjure.Compute.DomainOf ( domainOf ) import Conjure.Language.DomainSizeOf ( domainSizeOf ) import Conjure.Process.AttributeAsConstraints ( mkAttributeToConstraint ) @@ -211,7 +211,9 @@ instance EvaluateOp OpIn where return $ ConstantBool $ elem c $ map (\ (i,j) -> ConstantAbstract $ AbsLitTuple [i,j] ) cs evaluateOp (OpIn c (viewConstantRelation -> Just cs)) = return $ ConstantBool $ elem c $ map (ConstantAbstract . AbsLitTuple) cs - evaluateOp op = na $ "evaluateOp{OpIn}:" <++> pretty (show op) + evaluateOp (OpIn c coll) = do + vals <- enumerateInConstant coll + return $ ConstantBool $ elem c vals instance EvaluateOp OpIndexing where evaluateOp p@(OpIndexing m i) | isUndef i = do diff --git a/src/Conjure/Process/Enumerate.hs b/src/Conjure/Process/Enumerate.hs index bf51718e64..49cb0e34ca 100644 --- a/src/Conjure/Process/Enumerate.hs +++ b/src/Conjure/Process/Enumerate.hs @@ -215,6 +215,13 @@ enumerateInConstant constant = case constant of ] ConstantAbstract (AbsLitRelation xs) -> return $ map (ConstantAbstract . AbsLitTuple) xs ConstantAbstract (AbsLitPartition xs) -> return $ map (ConstantAbstract . AbsLitSet) xs + ConstantAbstract (AbsLitPermutation xss) -> + let + enumPerm [] = [] + enumPerm xs = [ ConstantAbstract (AbsLitTuple [i,j]) | (i,j) <- zip xs (tail xs) ] ++ + [ ConstantAbstract (AbsLitTuple [last xs, head xs]) ] + in + return $ concatMap enumPerm xss TypedConstant c _ -> enumerateInConstant c _ -> fail $ vcat [ "enumerateInConstant" , "constant:" <+> pretty constant From ff46470c26a6037208b987fdd2a1e2803950b83d Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?O=CC=88zgu=CC=88r=20Akgu=CC=88n?= Date: Tue, 11 Aug 2020 16:08:28 +0300 Subject: [PATCH 114/229] evaluating permutation image --- src/Conjure/Language/EvaluateOp.hs | 11 +++++++++++ src/Conjure/Language/Expression/Op/Image.hs | 1 + 2 files changed, 12 insertions(+) diff --git a/src/Conjure/Language/EvaluateOp.hs b/src/Conjure/Language/EvaluateOp.hs index 37eaf94d22..dffc2a5ee3 100644 --- a/src/Conjure/Language/EvaluateOp.hs +++ b/src/Conjure/Language/EvaluateOp.hs @@ -186,6 +186,17 @@ instance EvaluateOp OpImage where [ "Sequence is multiply defined at this point:" <+> pretty a , "Sequence value:" <+> pretty f ] + evaluateOp (OpImage f@(viewConstantPermutation -> Just _) a) = do + permVals <- enumerateInConstant f + case [ y | ConstantAbstract (AbsLitTuple [x,y]) <- permVals, a == x ] of + [y] -> return y + [] -> return a -- permutations map things to themselves by default + _ -> do + TypePermutation tyTo <- typeOf f + return $ mkUndef tyTo $ vcat + [ "Permutation is multiply defined at this point:" <+> pretty a + , "Permutation value:" <+> pretty f + ] evaluateOp op = na $ "evaluateOp{OpImage}:" <++> pretty (show op) instance EvaluateOp OpImageSet where diff --git a/src/Conjure/Language/Expression/Op/Image.hs b/src/Conjure/Language/Expression/Op/Image.hs index abb9bfacc9..1e194a528f 100644 --- a/src/Conjure/Language/Expression/Op/Image.hs +++ b/src/Conjure/Language/Expression/Op/Image.hs @@ -36,6 +36,7 @@ instance (TypeOf x, Pretty x) => TypeOf (OpImage x) where , "argument :" <+> pretty x , "argument type:" <+> pretty tyX ] + instance SimplifyOp OpImage x where simplifyOp _ = na "simplifyOp{OpImage}" From 343509b4234b0b9c2ff33da6d0f4efef0dda8f21 Mon Sep 17 00:00:00 2001 From: Chris Jefferson Date: Tue, 11 Aug 2020 13:54:56 +0100 Subject: [PATCH 115/229] Add more perm tests - part 3 --- .../model-permutation-solution000001.solution | 8 ++++++++ .../expected/model-permutation.eprime-param | 3 +++ .../expected/model.eprime | 14 ++++++++++++++ .../permutation-permutation.solution | 8 ++++++++ .../permutation.essence | 11 +++++++++++ .../permutation.param | 1 + .../expected/model-solution000001.solution | 8 ++++++++ .../expected/model.eprime | 13 +++++++++++++ .../permutation.essence | 11 +++++++++++ .../expected/model-solution000001.solution | 9 +++++++++ .../expected/model-solution000002.solution | 9 +++++++++ .../expected/model-solution000003.solution | 9 +++++++++ .../expected/model-solution000004.solution | 9 +++++++++ .../expected/model-solution000005.solution | 9 +++++++++ .../expected/model-solution000006.solution | 9 +++++++++ .../expected/model-solution000007.solution | 9 +++++++++ .../expected/model-solution000008.solution | 9 +++++++++ .../expected/model.eprime | 18 ++++++++++++++++++ .../permutation.essence | 10 ++++++++++ .../expected/model-solution000001.solution | 3 +++ .../expected/model-solution000002.solution | 3 +++ .../expected/model-solution000003.solution | 3 +++ .../expected/model-solution000004.solution | 3 +++ .../expected/model-solution000005.solution | 3 +++ .../expected/model-solution000006.solution | 3 +++ .../expected/model-solution000007.solution | 3 +++ .../expected/model-solution000008.solution | 3 +++ .../expected/model.eprime | 12 ++++++++++++ .../permutation.essence | 10 ++++++++++ .../model-permutation-solution000001.solution | 8 ++++++++ .../expected/model-permutation.eprime-param | 3 +++ .../expected/model.eprime | 14 ++++++++++++++ .../permutation.essence | 11 +++++++++++ .../permutation.param | 1 + .../expected/model-solution000001.solution | 8 ++++++++ .../expected/model.eprime | 13 +++++++++++++ .../permutation.essence | 11 +++++++++++ .../expected/model-solution000001.solution | 9 +++++++++ .../expected/model-solution000002.solution | 9 +++++++++ .../expected/model-solution000003.solution | 9 +++++++++ .../expected/model-solution000004.solution | 9 +++++++++ .../expected/model-solution000005.solution | 9 +++++++++ .../expected/model-solution000006.solution | 9 +++++++++ .../expected/model-solution000007.solution | 9 +++++++++ .../expected/model-solution000008.solution | 9 +++++++++ .../expected/model.eprime | 18 ++++++++++++++++++ .../permutation.essence | 9 +++++++++ .../expected/model-solution000001.solution | 9 +++++++++ .../expected/model-solution000002.solution | 9 +++++++++ .../expected/model-solution000003.solution | 9 +++++++++ .../expected/model-solution000004.solution | 9 +++++++++ .../expected/model-solution000005.solution | 9 +++++++++ .../expected/model-solution000006.solution | 9 +++++++++ .../expected/model-solution000007.solution | 9 +++++++++ .../expected/model-solution000008.solution | 9 +++++++++ .../expected/model.eprime | 18 ++++++++++++++++++ .../permutation.essence | 7 +++++++ .../expected/model-solution000001.solution | 9 +++++++++ .../expected/model-solution000002.solution | 9 +++++++++ .../expected/model-solution000003.solution | 9 +++++++++ .../expected/model-solution000004.solution | 9 +++++++++ .../expected/model-solution000005.solution | 9 +++++++++ .../expected/model-solution000006.solution | 9 +++++++++ .../expected/model-solution000007.solution | 9 +++++++++ .../expected/model-solution000008.solution | 9 +++++++++ .../expected/model.eprime | 18 ++++++++++++++++++ .../permutation.essence | 7 +++++++ .../expected/model-solution000001.solution | 10 ++++++++++ .../expected/model-solution000002.solution | 10 ++++++++++ .../expected/model-solution000003.solution | 10 ++++++++++ .../expected/model-solution000004.solution | 10 ++++++++++ .../expected/model-solution000005.solution | 10 ++++++++++ .../expected/model-solution000006.solution | 10 ++++++++++ .../expected/model-solution000007.solution | 10 ++++++++++ .../expected/model-solution000008.solution | 10 ++++++++++ .../expected/model.eprime | 18 ++++++++++++++++++ .../permutation.essence | 10 ++++++++++ 77 files changed, 693 insertions(+) create mode 100644 tests/exhaustive/basic/perms/03_generators/enum/0001_given_permutation_in_generator/expected/model-permutation-solution000001.solution create mode 100644 tests/exhaustive/basic/perms/03_generators/enum/0001_given_permutation_in_generator/expected/model-permutation.eprime-param create mode 100644 tests/exhaustive/basic/perms/03_generators/enum/0001_given_permutation_in_generator/expected/model.eprime create mode 100644 tests/exhaustive/basic/perms/03_generators/enum/0001_given_permutation_in_generator/permutation-permutation.solution create mode 100644 tests/exhaustive/basic/perms/03_generators/enum/0001_given_permutation_in_generator/permutation.essence create mode 100644 tests/exhaustive/basic/perms/03_generators/enum/0001_given_permutation_in_generator/permutation.param create mode 100644 tests/exhaustive/basic/perms/03_generators/enum/0002_letting_permutation_in_generator/expected/model-solution000001.solution create mode 100644 tests/exhaustive/basic/perms/03_generators/enum/0002_letting_permutation_in_generator/expected/model.eprime create mode 100644 tests/exhaustive/basic/perms/03_generators/enum/0002_letting_permutation_in_generator/permutation.essence create mode 100644 tests/exhaustive/basic/perms/03_generators/enum/0003_find_permutation_in_generator/expected/model-solution000001.solution create mode 100644 tests/exhaustive/basic/perms/03_generators/enum/0003_find_permutation_in_generator/expected/model-solution000002.solution create mode 100644 tests/exhaustive/basic/perms/03_generators/enum/0003_find_permutation_in_generator/expected/model-solution000003.solution create mode 100644 tests/exhaustive/basic/perms/03_generators/enum/0003_find_permutation_in_generator/expected/model-solution000004.solution create mode 100644 tests/exhaustive/basic/perms/03_generators/enum/0003_find_permutation_in_generator/expected/model-solution000005.solution create mode 100644 tests/exhaustive/basic/perms/03_generators/enum/0003_find_permutation_in_generator/expected/model-solution000006.solution create mode 100644 tests/exhaustive/basic/perms/03_generators/enum/0003_find_permutation_in_generator/expected/model-solution000007.solution create mode 100644 tests/exhaustive/basic/perms/03_generators/enum/0003_find_permutation_in_generator/expected/model-solution000008.solution create mode 100644 tests/exhaustive/basic/perms/03_generators/enum/0003_find_permutation_in_generator/expected/model.eprime create mode 100644 tests/exhaustive/basic/perms/03_generators/enum/0003_find_permutation_in_generator/permutation.essence create mode 100644 tests/exhaustive/basic/perms/03_generators/enum/0004_find_permutation_in_generator/expected/model-solution000001.solution create mode 100644 tests/exhaustive/basic/perms/03_generators/enum/0004_find_permutation_in_generator/expected/model-solution000002.solution create mode 100644 tests/exhaustive/basic/perms/03_generators/enum/0004_find_permutation_in_generator/expected/model-solution000003.solution create mode 100644 tests/exhaustive/basic/perms/03_generators/enum/0004_find_permutation_in_generator/expected/model-solution000004.solution create mode 100644 tests/exhaustive/basic/perms/03_generators/enum/0004_find_permutation_in_generator/expected/model-solution000005.solution create mode 100644 tests/exhaustive/basic/perms/03_generators/enum/0004_find_permutation_in_generator/expected/model-solution000006.solution create mode 100644 tests/exhaustive/basic/perms/03_generators/enum/0004_find_permutation_in_generator/expected/model-solution000007.solution create mode 100644 tests/exhaustive/basic/perms/03_generators/enum/0004_find_permutation_in_generator/expected/model-solution000008.solution create mode 100644 tests/exhaustive/basic/perms/03_generators/enum/0004_find_permutation_in_generator/expected/model.eprime create mode 100644 tests/exhaustive/basic/perms/03_generators/enum/0004_find_permutation_in_generator/permutation.essence create mode 100644 tests/exhaustive/basic/perms/03_generators/int/0001_given_permutation_in_generator/expected/model-permutation-solution000001.solution create mode 100644 tests/exhaustive/basic/perms/03_generators/int/0001_given_permutation_in_generator/expected/model-permutation.eprime-param create mode 100644 tests/exhaustive/basic/perms/03_generators/int/0001_given_permutation_in_generator/expected/model.eprime create mode 100644 tests/exhaustive/basic/perms/03_generators/int/0001_given_permutation_in_generator/permutation.essence create mode 100644 tests/exhaustive/basic/perms/03_generators/int/0001_given_permutation_in_generator/permutation.param create mode 100644 tests/exhaustive/basic/perms/03_generators/int/0002_letting_permutation_in_generator/expected/model-solution000001.solution create mode 100644 tests/exhaustive/basic/perms/03_generators/int/0002_letting_permutation_in_generator/expected/model.eprime create mode 100644 tests/exhaustive/basic/perms/03_generators/int/0002_letting_permutation_in_generator/permutation.essence create mode 100644 tests/exhaustive/basic/perms/03_generators/int/0003_find_permutation_in_generator/expected/model-solution000001.solution create mode 100644 tests/exhaustive/basic/perms/03_generators/int/0003_find_permutation_in_generator/expected/model-solution000002.solution create mode 100644 tests/exhaustive/basic/perms/03_generators/int/0003_find_permutation_in_generator/expected/model-solution000003.solution create mode 100644 tests/exhaustive/basic/perms/03_generators/int/0003_find_permutation_in_generator/expected/model-solution000004.solution create mode 100644 tests/exhaustive/basic/perms/03_generators/int/0003_find_permutation_in_generator/expected/model-solution000005.solution create mode 100644 tests/exhaustive/basic/perms/03_generators/int/0003_find_permutation_in_generator/expected/model-solution000006.solution create mode 100644 tests/exhaustive/basic/perms/03_generators/int/0003_find_permutation_in_generator/expected/model-solution000007.solution create mode 100644 tests/exhaustive/basic/perms/03_generators/int/0003_find_permutation_in_generator/expected/model-solution000008.solution create mode 100644 tests/exhaustive/basic/perms/03_generators/int/0003_find_permutation_in_generator/expected/model.eprime create mode 100644 tests/exhaustive/basic/perms/03_generators/int/0003_find_permutation_in_generator/permutation.essence create mode 100644 tests/exhaustive/basic/perms/03_generators/int/0004_find_permutation_in_forall/expected/model-solution000001.solution create mode 100644 tests/exhaustive/basic/perms/03_generators/int/0004_find_permutation_in_forall/expected/model-solution000002.solution create mode 100644 tests/exhaustive/basic/perms/03_generators/int/0004_find_permutation_in_forall/expected/model-solution000003.solution create mode 100644 tests/exhaustive/basic/perms/03_generators/int/0004_find_permutation_in_forall/expected/model-solution000004.solution create mode 100644 tests/exhaustive/basic/perms/03_generators/int/0004_find_permutation_in_forall/expected/model-solution000005.solution create mode 100644 tests/exhaustive/basic/perms/03_generators/int/0004_find_permutation_in_forall/expected/model-solution000006.solution create mode 100644 tests/exhaustive/basic/perms/03_generators/int/0004_find_permutation_in_forall/expected/model-solution000007.solution create mode 100644 tests/exhaustive/basic/perms/03_generators/int/0004_find_permutation_in_forall/expected/model-solution000008.solution create mode 100644 tests/exhaustive/basic/perms/03_generators/int/0004_find_permutation_in_forall/expected/model.eprime create mode 100644 tests/exhaustive/basic/perms/03_generators/int/0004_find_permutation_in_forall/permutation.essence create mode 100644 tests/exhaustive/basic/perms/03_generators/int/0005_find_permutation_in_forall/expected/model-solution000001.solution create mode 100644 tests/exhaustive/basic/perms/03_generators/int/0005_find_permutation_in_forall/expected/model-solution000002.solution create mode 100644 tests/exhaustive/basic/perms/03_generators/int/0005_find_permutation_in_forall/expected/model-solution000003.solution create mode 100644 tests/exhaustive/basic/perms/03_generators/int/0005_find_permutation_in_forall/expected/model-solution000004.solution create mode 100644 tests/exhaustive/basic/perms/03_generators/int/0005_find_permutation_in_forall/expected/model-solution000005.solution create mode 100644 tests/exhaustive/basic/perms/03_generators/int/0005_find_permutation_in_forall/expected/model-solution000006.solution create mode 100644 tests/exhaustive/basic/perms/03_generators/int/0005_find_permutation_in_forall/expected/model-solution000007.solution create mode 100644 tests/exhaustive/basic/perms/03_generators/int/0005_find_permutation_in_forall/expected/model-solution000008.solution create mode 100644 tests/exhaustive/basic/perms/03_generators/int/0005_find_permutation_in_forall/expected/model.eprime create mode 100644 tests/exhaustive/basic/perms/03_generators/int/0005_find_permutation_in_forall/permutation.essence create mode 100644 tests/exhaustive/basic/perms/03_generators/unnamed/0003_find_permutation_in_generator/expected/model-solution000001.solution create mode 100644 tests/exhaustive/basic/perms/03_generators/unnamed/0003_find_permutation_in_generator/expected/model-solution000002.solution create mode 100644 tests/exhaustive/basic/perms/03_generators/unnamed/0003_find_permutation_in_generator/expected/model-solution000003.solution create mode 100644 tests/exhaustive/basic/perms/03_generators/unnamed/0003_find_permutation_in_generator/expected/model-solution000004.solution create mode 100644 tests/exhaustive/basic/perms/03_generators/unnamed/0003_find_permutation_in_generator/expected/model-solution000005.solution create mode 100644 tests/exhaustive/basic/perms/03_generators/unnamed/0003_find_permutation_in_generator/expected/model-solution000006.solution create mode 100644 tests/exhaustive/basic/perms/03_generators/unnamed/0003_find_permutation_in_generator/expected/model-solution000007.solution create mode 100644 tests/exhaustive/basic/perms/03_generators/unnamed/0003_find_permutation_in_generator/expected/model-solution000008.solution create mode 100644 tests/exhaustive/basic/perms/03_generators/unnamed/0003_find_permutation_in_generator/expected/model.eprime create mode 100644 tests/exhaustive/basic/perms/03_generators/unnamed/0003_find_permutation_in_generator/permutation.essence diff --git a/tests/exhaustive/basic/perms/03_generators/enum/0001_given_permutation_in_generator/expected/model-permutation-solution000001.solution b/tests/exhaustive/basic/perms/03_generators/enum/0001_given_permutation_in_generator/expected/model-permutation-solution000001.solution new file mode 100644 index 0000000000..a808317703 --- /dev/null +++ b/tests/exhaustive/basic/perms/03_generators/enum/0001_given_permutation_in_generator/expected/model-permutation-solution000001.solution @@ -0,0 +1,8 @@ +language Essence 1.3 + +letting s be {(E1, E3), (E3, E4), (E4, E1)} +$ Visualisation for s +$ E1 E3 +$ E3 E4 +$ E4 E1 + diff --git a/tests/exhaustive/basic/perms/03_generators/enum/0001_given_permutation_in_generator/expected/model-permutation.eprime-param b/tests/exhaustive/basic/perms/03_generators/enum/0001_given_permutation_in_generator/expected/model-permutation.eprime-param new file mode 100644 index 0000000000..c2bddee0e8 --- /dev/null +++ b/tests/exhaustive/basic/perms/03_generators/enum/0001_given_permutation_in_generator/expected/model-permutation.eprime-param @@ -0,0 +1,3 @@ +language ESSENCE' 1.0 + +letting p_PermutationAsFunction_PermutationFunction_Function1D be [3, 2, 4, 1; int(1..4)] diff --git a/tests/exhaustive/basic/perms/03_generators/enum/0001_given_permutation_in_generator/expected/model.eprime b/tests/exhaustive/basic/perms/03_generators/enum/0001_given_permutation_in_generator/expected/model.eprime new file mode 100644 index 0000000000..2637d263cd --- /dev/null +++ b/tests/exhaustive/basic/perms/03_generators/enum/0001_given_permutation_in_generator/expected/model.eprime @@ -0,0 +1,14 @@ +language ESSENCE' 1.0 + +given p_PermutationAsFunction_PermutationFunction_Function1D: matrix indexed by [int(1..4)] of int(1..4) +find s_Explicit_1: matrix indexed by [int(1..3)] of int(1..4) +find s_Explicit_2: matrix indexed by [int(1..3)] of int(1..4) +branching on [s_Explicit_1, s_Explicit_2] +such that + and([or([s_Explicit_1[q8] = q10 /\ s_Explicit_2[q8] = p_PermutationAsFunction_PermutationFunction_Function1D[q10] + | q8 : int(1..3)]) + | q10 : int(1..4), q10 != p_PermutationAsFunction_PermutationFunction_Function1D[q10]]), + and([flatten([[s_Explicit_1[q1]; int(1)], [s_Explicit_2[q1]; int(1)]; int(1..2)]) + or([s_Explicit_1[q12] = q14 /\ s_Explicit_2[q12] = p_PermutationAsFunction_PermutationFunction_Function1D[q14] + | q12 : int(1..3)]) + | q14 : int(1..4)]), + and([flatten([[s_Explicit_1[q1]; int(1)], [s_Explicit_2[q1]; int(1)]; int(1..2)]) + q11 != p_PermutationAsFunction_PermutationFunction_Function1D[q11] + | q11 : int(1..4)]), + allDiff(p_PermutationAsFunction_PermutationFunction_Function1D), + and([or([p_PermutationAsFunction_PermutationFunction_Function1D[q3] = q2 | q3 : int(1..4)]) | q2 : int(1..4)]), + 3 = sum([toInt(q1 != p_PermutationAsFunction_PermutationFunction_Function1D[q1]) | q1 : int(1..4)]) + diff --git a/tests/exhaustive/basic/perms/03_generators/enum/0004_find_permutation_in_generator/permutation.essence b/tests/exhaustive/basic/perms/03_generators/enum/0004_find_permutation_in_generator/permutation.essence new file mode 100644 index 0000000000..80c1a9b4e3 --- /dev/null +++ b/tests/exhaustive/basic/perms/03_generators/enum/0004_find_permutation_in_generator/permutation.essence @@ -0,0 +1,10 @@ +letting n be new type enum {E1,E2,E3,E4} +find p : permutation (size 3) of n + + +such that + and([l != r | (l,r) <- p]) + + + + diff --git a/tests/exhaustive/basic/perms/03_generators/int/0001_given_permutation_in_generator/expected/model-permutation-solution000001.solution b/tests/exhaustive/basic/perms/03_generators/int/0001_given_permutation_in_generator/expected/model-permutation-solution000001.solution new file mode 100644 index 0000000000..23d4dc482a --- /dev/null +++ b/tests/exhaustive/basic/perms/03_generators/int/0001_given_permutation_in_generator/expected/model-permutation-solution000001.solution @@ -0,0 +1,8 @@ +language Essence 1.3 + +letting s be {(1, 3), (3, 4), (4, 1)} +$ Visualisation for s +$ 1 3 +$ 3 4 +$ 4 1 + diff --git a/tests/exhaustive/basic/perms/03_generators/int/0001_given_permutation_in_generator/expected/model-permutation.eprime-param b/tests/exhaustive/basic/perms/03_generators/int/0001_given_permutation_in_generator/expected/model-permutation.eprime-param new file mode 100644 index 0000000000..c2bddee0e8 --- /dev/null +++ b/tests/exhaustive/basic/perms/03_generators/int/0001_given_permutation_in_generator/expected/model-permutation.eprime-param @@ -0,0 +1,3 @@ +language ESSENCE' 1.0 + +letting p_PermutationAsFunction_PermutationFunction_Function1D be [3, 2, 4, 1; int(1..4)] diff --git a/tests/exhaustive/basic/perms/03_generators/int/0001_given_permutation_in_generator/expected/model.eprime b/tests/exhaustive/basic/perms/03_generators/int/0001_given_permutation_in_generator/expected/model.eprime new file mode 100644 index 0000000000..2637d263cd --- /dev/null +++ b/tests/exhaustive/basic/perms/03_generators/int/0001_given_permutation_in_generator/expected/model.eprime @@ -0,0 +1,14 @@ +language ESSENCE' 1.0 + +given p_PermutationAsFunction_PermutationFunction_Function1D: matrix indexed by [int(1..4)] of int(1..4) +find s_Explicit_1: matrix indexed by [int(1..3)] of int(1..4) +find s_Explicit_2: matrix indexed by [int(1..3)] of int(1..4) +branching on [s_Explicit_1, s_Explicit_2] +such that + and([or([s_Explicit_1[q8] = q10 /\ s_Explicit_2[q8] = p_PermutationAsFunction_PermutationFunction_Function1D[q10] + | q8 : int(1..3)]) + | q10 : int(1..4), q10 != p_PermutationAsFunction_PermutationFunction_Function1D[q10]]), + and([flatten([[s_Explicit_1[q1]; int(1)], [s_Explicit_2[q1]; int(1)]; int(1..2)]) + or([s_Explicit_1[q12] = q14 /\ s_Explicit_2[q12] = p_PermutationAsFunction_PermutationFunction_Function1D[q14] + | q12 : int(1..3)]) + | q14 : int(1..4)]), + and([flatten([[s_Explicit_1[q1]; int(1)], [s_Explicit_2[q1]; int(1)]; int(1..2)]) + or([s_Explicit_1[q12] = q14 /\ s_Explicit_2[q12] = p_PermutationAsFunction_PermutationFunction_Function1D[q14] + | q12 : int(1..3)]) + | q14 : int(1..4)]), + and([flatten([[s_Explicit_1[q1]; int(1)], [s_Explicit_2[q1]; int(1)]; int(1..2)]) + or([s_Explicit_1[q12] = q14 /\ s_Explicit_2[q12] = p_PermutationAsFunction_PermutationFunction_Function1D[q14] + | q12 : int(1..3)]) + | q14 : int(1..4)]), + and([flatten([[s_Explicit_1[q1]; int(1)], [s_Explicit_2[q1]; int(1)]; int(1..2)]) Date: Tue, 11 Aug 2020 14:34:38 +0100 Subject: [PATCH 116/229] Add broken permutation image test --- .../model-permutation-solution000001.solution | 3 +++ .../expected/model-permutation.eprime-param | 3 +++ .../model-permutation2-solution000001.solution | 3 +++ .../expected/model-permutation2.eprime-param | 3 +++ .../expected/model.eprime | 7 +++++++ .../permutation.essence | 11 +++++++++++ .../permutation.param | 1 + .../permutation2.param | 1 + 8 files changed, 32 insertions(+) create mode 100644 tests/exhaustive/basic/perms/04_image/int/0006_letting_permutation_given_int/expected/model-permutation-solution000001.solution create mode 100644 tests/exhaustive/basic/perms/04_image/int/0006_letting_permutation_given_int/expected/model-permutation.eprime-param create mode 100644 tests/exhaustive/basic/perms/04_image/int/0006_letting_permutation_given_int/expected/model-permutation2-solution000001.solution create mode 100644 tests/exhaustive/basic/perms/04_image/int/0006_letting_permutation_given_int/expected/model-permutation2.eprime-param create mode 100644 tests/exhaustive/basic/perms/04_image/int/0006_letting_permutation_given_int/expected/model.eprime create mode 100644 tests/exhaustive/basic/perms/04_image/int/0006_letting_permutation_given_int/permutation.essence create mode 100644 tests/exhaustive/basic/perms/04_image/int/0006_letting_permutation_given_int/permutation.param create mode 100644 tests/exhaustive/basic/perms/04_image/int/0006_letting_permutation_given_int/permutation2.param diff --git a/tests/exhaustive/basic/perms/04_image/int/0006_letting_permutation_given_int/expected/model-permutation-solution000001.solution b/tests/exhaustive/basic/perms/04_image/int/0006_letting_permutation_given_int/expected/model-permutation-solution000001.solution new file mode 100644 index 0000000000..215f7d0a92 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/int/0006_letting_permutation_given_int/expected/model-permutation-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting j be 3 diff --git a/tests/exhaustive/basic/perms/04_image/int/0006_letting_permutation_given_int/expected/model-permutation.eprime-param b/tests/exhaustive/basic/perms/04_image/int/0006_letting_permutation_given_int/expected/model-permutation.eprime-param new file mode 100644 index 0000000000..a8a9ac3b6a --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/int/0006_letting_permutation_given_int/expected/model-permutation.eprime-param @@ -0,0 +1,3 @@ +language ESSENCE' 1.0 + +letting i be 1 diff --git a/tests/exhaustive/basic/perms/04_image/int/0006_letting_permutation_given_int/expected/model-permutation2-solution000001.solution b/tests/exhaustive/basic/perms/04_image/int/0006_letting_permutation_given_int/expected/model-permutation2-solution000001.solution new file mode 100644 index 0000000000..3585952da3 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/int/0006_letting_permutation_given_int/expected/model-permutation2-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting j be 6 diff --git a/tests/exhaustive/basic/perms/04_image/int/0006_letting_permutation_given_int/expected/model-permutation2.eprime-param b/tests/exhaustive/basic/perms/04_image/int/0006_letting_permutation_given_int/expected/model-permutation2.eprime-param new file mode 100644 index 0000000000..3fabd39da4 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/int/0006_letting_permutation_given_int/expected/model-permutation2.eprime-param @@ -0,0 +1,3 @@ +language ESSENCE' 1.0 + +letting i be 6 diff --git a/tests/exhaustive/basic/perms/04_image/int/0006_letting_permutation_given_int/expected/model.eprime b/tests/exhaustive/basic/perms/04_image/int/0006_letting_permutation_given_int/expected/model.eprime new file mode 100644 index 0000000000..7a650bbdd9 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/int/0006_letting_permutation_given_int/expected/model.eprime @@ -0,0 +1,7 @@ +language ESSENCE' 1.0 + +given i: int(0..10) +find j: int(0..10) +branching on [j] +such that j = [i, 3, 4, 1; int(0..3)][sum([toInt(1 = i), toInt(3 = i) * 2, toInt(4 = i) * 3; int(1..3)])] + diff --git a/tests/exhaustive/basic/perms/04_image/int/0006_letting_permutation_given_int/permutation.essence b/tests/exhaustive/basic/perms/04_image/int/0006_letting_permutation_given_int/permutation.essence new file mode 100644 index 0000000000..a32d539c49 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/int/0006_letting_permutation_given_int/permutation.essence @@ -0,0 +1,11 @@ +given i : int(0..10) +letting p be permutation((1,3,4)) + + +find j : int(0..10) + +such that j = image(p, i) + + + + diff --git a/tests/exhaustive/basic/perms/04_image/int/0006_letting_permutation_given_int/permutation.param b/tests/exhaustive/basic/perms/04_image/int/0006_letting_permutation_given_int/permutation.param new file mode 100644 index 0000000000..d185471560 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/int/0006_letting_permutation_given_int/permutation.param @@ -0,0 +1 @@ +letting i be 1 diff --git a/tests/exhaustive/basic/perms/04_image/int/0006_letting_permutation_given_int/permutation2.param b/tests/exhaustive/basic/perms/04_image/int/0006_letting_permutation_given_int/permutation2.param new file mode 100644 index 0000000000..4f045e546c --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/int/0006_letting_permutation_given_int/permutation2.param @@ -0,0 +1 @@ +letting i be 6 From 36e854c64d20941b23b7a0914004f4fc568e29fd Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?O=CC=88zgu=CC=88r=20Akgu=CC=88n?= Date: Tue, 11 Aug 2020 16:48:41 +0300 Subject: [PATCH 117/229] Fix confusion in the tester about multiple param files --- src/test/Conjure/ModelAllSolveAll.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/test/Conjure/ModelAllSolveAll.hs b/src/test/Conjure/ModelAllSolveAll.hs index e440f9b045..8c47a6c292 100644 --- a/src/test/Conjure/ModelAllSolveAll.hs +++ b/src/test/Conjure/ModelAllSolveAll.hs @@ -192,7 +192,7 @@ testSingleDir (TestTimeLimit timeLimitMin timeLimitMax) srOptions t@TestDirFiles then validateSolutionNoParam step t expectedSols else validateSolutionWithParams step t [ ( p , [ s | s <- expectedSols - , dropExtension p `isInfixOf` dropExtension s + , (dropExtension p ++ "-solution") `isInfixOf` dropExtension s ] ) | p <- paramFiles From 37200261ae16eeb3d5da8725b71ea7e5ea497ae5 Mon Sep 17 00:00:00 2001 From: Chris Jefferson Date: Tue, 11 Aug 2020 15:25:50 +0100 Subject: [PATCH 118/229] Add permutation tests - part 4 --- .../model-permutation-solution000001.solution | 3 +++ .../expected/model-permutation.eprime-param | 4 ++++ .../model-permutation2-solution000001.solution | 3 +++ .../expected/model-permutation2.eprime-param | 4 ++++ .../expected/model.eprime | 11 +++++++++++ .../permutation.essence | 13 +++++++++++++ .../permutation.param | 2 ++ .../permutation2.param | 2 ++ .../model-permutation-solution000001.solution | 3 +++ .../expected/model-permutation.eprime-param | 3 +++ .../expected/model.eprime | 7 +++++++ .../permutation.essence | 12 ++++++++++++ .../permutation.param | 1 + .../model-permutation-solution000001.solution | 3 +++ .../expected/model-permutation.eprime-param | 3 +++ .../expected/model.eprime | 7 +++++++ .../permutation.essence | 12 ++++++++++++ .../permutation.param | 1 + .../model-permutation-solution000001.solution | 3 +++ .../model-permutation-solution000002.solution | 3 +++ .../model-permutation-solution000003.solution | 3 +++ .../model-permutation-solution000004.solution | 3 +++ .../model-permutation-solution000005.solution | 3 +++ .../expected/model-permutation.eprime-param | 4 ++++ .../model-permutation2-solution000001.solution | 3 +++ .../model-permutation2-solution000002.solution | 3 +++ .../model-permutation2-solution000003.solution | 3 +++ .../model-permutation2-solution000004.solution | 3 +++ .../model-permutation2-solution000005.solution | 3 +++ .../model-permutation2-solution000006.solution | 3 +++ .../model-permutation2-solution000007.solution | 3 +++ .../model-permutation2-solution000008.solution | 3 +++ .../model-permutation2-solution000009.solution | 3 +++ .../model-permutation2-solution000010.solution | 3 +++ .../model-permutation2-solution000011.solution | 3 +++ .../model-permutation2-solution000012.solution | 3 +++ .../model-permutation2-solution000013.solution | 3 +++ .../model-permutation2-solution000014.solution | 3 +++ .../model-permutation2-solution000015.solution | 3 +++ .../model-permutation2-solution000016.solution | 3 +++ .../model-permutation2-solution000017.solution | 3 +++ .../model-permutation2-solution000018.solution | 3 +++ .../model-permutation2-solution000019.solution | 3 +++ .../model-permutation2-solution000020.solution | 3 +++ .../model-permutation2-solution000021.solution | 3 +++ .../model-permutation2-solution000022.solution | 3 +++ .../model-permutation2-solution000023.solution | 3 +++ .../model-permutation2-solution000024.solution | 3 +++ .../model-permutation2-solution000025.solution | 3 +++ .../model-permutation2-solution000026.solution | 3 +++ .../model-permutation2-solution000027.solution | 3 +++ .../model-permutation2-solution000028.solution | 3 +++ .../model-permutation2-solution000029.solution | 3 +++ .../model-permutation2-solution000030.solution | 3 +++ .../model-permutation2-solution000031.solution | 3 +++ .../model-permutation2-solution000032.solution | 3 +++ .../model-permutation2-solution000033.solution | 3 +++ .../model-permutation2-solution000034.solution | 3 +++ .../model-permutation2-solution000035.solution | 3 +++ .../model-permutation2-solution000036.solution | 3 +++ .../model-permutation2-solution000037.solution | 3 +++ .../model-permutation2-solution000038.solution | 3 +++ .../model-permutation2-solution000039.solution | 3 +++ .../model-permutation2-solution000040.solution | 3 +++ .../expected/model-permutation2.eprime-param | 4 ++++ .../expected/model.eprime | 17 +++++++++++++++++ .../permutation.essence | 14 ++++++++++++++ .../permutation.param | 2 ++ .../permutation2.param | 2 ++ .../model-permutation-solution000001.solution | 3 +++ .../expected/model-permutation.eprime-param | 3 +++ .../model-permutation2-solution000001.solution | 3 +++ .../expected/model-permutation2.eprime-param | 3 +++ .../expected/model.eprime | 7 +++++++ .../permutation.essence | 12 ++++++++++++ .../permutation.param | 1 + .../permutation2.param | 1 + .../expected/model-solution000001.solution | 5 +++++ .../expected/model-solution000002.solution | 5 +++++ .../expected/model-solution000003.solution | 5 +++++ .../expected/model-solution000004.solution | 5 +++++ .../expected/model-solution000005.solution | 5 +++++ .../expected/model-solution000006.solution | 5 +++++ .../expected/model-solution000007.solution | 5 +++++ .../expected/model-solution000008.solution | 5 +++++ .../expected/model-solution000009.solution | 5 +++++ .../expected/model-solution000010.solution | 5 +++++ .../expected/model-solution000011.solution | 5 +++++ .../expected/model-solution000012.solution | 5 +++++ .../expected/model-solution000013.solution | 5 +++++ .../expected/model-solution000014.solution | 5 +++++ .../expected/model-solution000015.solution | 5 +++++ .../expected/model-solution000016.solution | 5 +++++ .../expected/model-solution000017.solution | 5 +++++ .../expected/model-solution000018.solution | 5 +++++ .../expected/model-solution000019.solution | 5 +++++ .../expected/model-solution000020.solution | 5 +++++ .../expected/model-solution000021.solution | 5 +++++ .../expected/model-solution000022.solution | 5 +++++ .../expected/model-solution000023.solution | 5 +++++ .../expected/model-solution000024.solution | 5 +++++ .../expected/model-solution000025.solution | 5 +++++ .../expected/model-solution000026.solution | 5 +++++ .../expected/model-solution000027.solution | 5 +++++ .../expected/model-solution000028.solution | 5 +++++ .../expected/model-solution000029.solution | 5 +++++ .../expected/model-solution000030.solution | 5 +++++ .../expected/model-solution000031.solution | 5 +++++ .../expected/model-solution000032.solution | 5 +++++ .../expected/model-solution000033.solution | 5 +++++ .../expected/model-solution000034.solution | 5 +++++ .../expected/model-solution000035.solution | 5 +++++ .../expected/model-solution000036.solution | 5 +++++ .../expected/model-solution000037.solution | 5 +++++ .../expected/model-solution000038.solution | 5 +++++ .../expected/model-solution000039.solution | 5 +++++ .../expected/model-solution000040.solution | 5 +++++ .../expected/model-solution000041.solution | 5 +++++ .../expected/model-solution000042.solution | 5 +++++ .../expected/model-solution000043.solution | 5 +++++ .../expected/model-solution000044.solution | 5 +++++ .../expected/model-solution000045.solution | 5 +++++ .../expected/model-solution000046.solution | 5 +++++ .../expected/model-solution000047.solution | 5 +++++ .../expected/model-solution000048.solution | 5 +++++ .../expected/model-solution000049.solution | 5 +++++ .../expected/model-solution000050.solution | 5 +++++ .../expected/model-solution000051.solution | 5 +++++ .../expected/model-solution000052.solution | 5 +++++ .../expected/model-solution000053.solution | 5 +++++ .../expected/model-solution000054.solution | 5 +++++ .../expected/model-solution000055.solution | 5 +++++ .../expected/model-solution000056.solution | 5 +++++ .../expected/model-solution000057.solution | 5 +++++ .../expected/model-solution000058.solution | 5 +++++ .../expected/model-solution000059.solution | 5 +++++ .../expected/model-solution000060.solution | 5 +++++ .../expected/model-solution000061.solution | 5 +++++ .../expected/model-solution000062.solution | 5 +++++ .../expected/model-solution000063.solution | 5 +++++ .../expected/model-solution000064.solution | 5 +++++ .../expected/model-solution000065.solution | 5 +++++ .../expected/model-solution000066.solution | 5 +++++ .../expected/model-solution000067.solution | 5 +++++ .../expected/model-solution000068.solution | 5 +++++ .../expected/model-solution000069.solution | 5 +++++ .../expected/model-solution000070.solution | 5 +++++ .../expected/model-solution000071.solution | 5 +++++ .../expected/model-solution000072.solution | 5 +++++ .../expected/model-solution000073.solution | 5 +++++ .../expected/model-solution000074.solution | 5 +++++ .../expected/model-solution000075.solution | 5 +++++ .../expected/model-solution000076.solution | 5 +++++ .../expected/model-solution000077.solution | 5 +++++ .../expected/model-solution000078.solution | 5 +++++ .../expected/model-solution000079.solution | 5 +++++ .../expected/model-solution000080.solution | 5 +++++ .../expected/model-solution000081.solution | 5 +++++ .../expected/model-solution000082.solution | 5 +++++ .../expected/model-solution000083.solution | 5 +++++ .../expected/model-solution000084.solution | 5 +++++ .../expected/model-solution000085.solution | 5 +++++ .../expected/model-solution000086.solution | 5 +++++ .../expected/model-solution000087.solution | 5 +++++ .../expected/model-solution000088.solution | 5 +++++ .../expected/model-solution000089.solution | 5 +++++ .../expected/model-solution000090.solution | 5 +++++ .../expected/model-solution000091.solution | 5 +++++ .../expected/model-solution000092.solution | 5 +++++ .../expected/model-solution000093.solution | 5 +++++ .../expected/model-solution000094.solution | 5 +++++ .../expected/model-solution000095.solution | 5 +++++ .../expected/model-solution000096.solution | 5 +++++ .../expected/model-solution000097.solution | 5 +++++ .../expected/model-solution000098.solution | 5 +++++ .../expected/model-solution000099.solution | 5 +++++ .../expected/model-solution000100.solution | 5 +++++ .../expected/model.eprime | 17 +++++++++++++++++ .../permutation.essence | 14 ++++++++++++++ .../model-permutation-solution000001.solution | 3 +++ .../expected/model-permutation.eprime-param | 4 ++++ .../model-permutation2-solution000001.solution | 3 +++ .../expected/model-permutation2.eprime-param | 4 ++++ .../expected/model.eprime | 11 +++++++++++ .../permutation.essence | 11 +++++++++++ .../permutation.param | 2 ++ .../permutation2.param | 2 ++ .../model-permutation-solution000001.solution | 3 +++ .../expected/model-permutation.eprime-param | 3 +++ .../expected/model.eprime | 7 +++++++ .../permutation.essence | 11 +++++++++++ .../permutation.param | 1 + .../model-permutation-solution000001.solution | 3 +++ .../expected/model-permutation.eprime-param | 3 +++ .../expected/model.eprime | 7 +++++++ .../permutation.essence | 11 +++++++++++ .../permutation.param | 1 + .../permutation.essence | 12 ++++++++++++ .../permutation.param | 2 ++ .../permutation2.essence | 2 ++ .../model-permutation-solution000001.solution | 3 +++ .../model-permutation-solution000002.solution | 3 +++ .../expected/model-permutation.eprime-param | 4 ++++ .../model-permutation2-solution000001.solution | 3 +++ .../model-permutation2-solution000002.solution | 3 +++ .../expected/model-permutation2.eprime-param | 4 ++++ .../expected/model.eprime | 17 +++++++++++++++++ .../permutation.essence | 12 ++++++++++++ .../permutation.param | 2 ++ .../permutation2.param | 2 ++ .../expected/model-solution000001.solution | 5 +++++ .../expected/model-solution000002.solution | 5 +++++ .../expected/model-solution000003.solution | 5 +++++ .../expected/model-solution000004.solution | 5 +++++ .../expected/model-solution000005.solution | 5 +++++ .../expected/model-solution000006.solution | 5 +++++ .../expected/model-solution000007.solution | 5 +++++ .../expected/model-solution000008.solution | 5 +++++ .../expected/model-solution000009.solution | 5 +++++ .../expected/model-solution000010.solution | 5 +++++ .../expected/model-solution000011.solution | 5 +++++ .../expected/model-solution000012.solution | 5 +++++ .../expected/model-solution000013.solution | 5 +++++ .../expected/model-solution000014.solution | 5 +++++ .../expected/model-solution000015.solution | 5 +++++ .../expected/model-solution000016.solution | 5 +++++ .../expected/model-solution000017.solution | 5 +++++ .../expected/model-solution000018.solution | 5 +++++ .../expected/model-solution000019.solution | 5 +++++ .../expected/model-solution000020.solution | 5 +++++ .../expected/model-solution000021.solution | 5 +++++ .../expected/model-solution000022.solution | 5 +++++ .../expected/model-solution000023.solution | 5 +++++ .../expected/model-solution000024.solution | 5 +++++ .../expected/model.eprime | 17 +++++++++++++++++ .../permutation.essence | 16 ++++++++++++++++ .../expected/model-solution000001.solution | 6 ++++++ .../expected/model-solution000002.solution | 6 ++++++ .../expected/model-solution000003.solution | 6 ++++++ .../expected/model-solution000004.solution | 6 ++++++ .../expected/model-solution000005.solution | 6 ++++++ .../expected/model-solution000006.solution | 6 ++++++ .../expected/model-solution000007.solution | 6 ++++++ .../expected/model-solution000008.solution | 6 ++++++ .../expected/model-solution000009.solution | 6 ++++++ .../expected/model-solution000010.solution | 6 ++++++ .../expected/model-solution000011.solution | 6 ++++++ .../expected/model-solution000012.solution | 6 ++++++ .../expected/model-solution000013.solution | 6 ++++++ .../expected/model-solution000014.solution | 6 ++++++ .../expected/model-solution000015.solution | 6 ++++++ .../expected/model-solution000016.solution | 6 ++++++ .../expected/model-solution000017.solution | 6 ++++++ .../expected/model-solution000018.solution | 6 ++++++ .../expected/model-solution000019.solution | 6 ++++++ .../expected/model-solution000020.solution | 6 ++++++ .../expected/model-solution000021.solution | 6 ++++++ .../expected/model-solution000022.solution | 6 ++++++ .../expected/model-solution000023.solution | 6 ++++++ .../expected/model-solution000024.solution | 6 ++++++ .../expected/model-solution000025.solution | 6 ++++++ .../expected/model-solution000026.solution | 6 ++++++ .../expected/model-solution000027.solution | 6 ++++++ .../expected/model-solution000028.solution | 6 ++++++ .../expected/model-solution000029.solution | 6 ++++++ .../expected/model-solution000030.solution | 6 ++++++ .../expected/model-solution000031.solution | 6 ++++++ .../expected/model-solution000032.solution | 6 ++++++ .../expected/model-solution000033.solution | 6 ++++++ .../expected/model-solution000034.solution | 6 ++++++ .../expected/model-solution000035.solution | 6 ++++++ .../expected/model-solution000036.solution | 6 ++++++ .../expected/model-solution000037.solution | 6 ++++++ .../expected/model-solution000038.solution | 6 ++++++ .../expected/model-solution000039.solution | 6 ++++++ .../expected/model-solution000040.solution | 6 ++++++ .../expected/model-solution000041.solution | 6 ++++++ .../expected/model-solution000042.solution | 6 ++++++ .../expected/model-solution000043.solution | 6 ++++++ .../expected/model-solution000044.solution | 6 ++++++ .../expected/model-solution000045.solution | 6 ++++++ .../expected/model-solution000046.solution | 6 ++++++ .../expected/model-solution000047.solution | 6 ++++++ .../expected/model-solution000048.solution | 6 ++++++ .../expected/model-solution000049.solution | 6 ++++++ .../expected/model-solution000050.solution | 6 ++++++ .../expected/model-solution000051.solution | 6 ++++++ .../expected/model-solution000052.solution | 6 ++++++ .../expected/model-solution000053.solution | 6 ++++++ .../expected/model-solution000054.solution | 6 ++++++ .../expected/model-solution000055.solution | 6 ++++++ .../expected/model-solution000056.solution | 6 ++++++ .../expected/model-solution000057.solution | 6 ++++++ .../expected/model-solution000058.solution | 6 ++++++ .../expected/model-solution000059.solution | 6 ++++++ .../expected/model-solution000060.solution | 6 ++++++ .../expected/model-solution000061.solution | 6 ++++++ .../expected/model-solution000062.solution | 6 ++++++ .../expected/model-solution000063.solution | 6 ++++++ .../expected/model-solution000064.solution | 6 ++++++ .../expected/model-solution000065.solution | 6 ++++++ .../expected/model-solution000066.solution | 6 ++++++ .../expected/model-solution000067.solution | 6 ++++++ .../expected/model-solution000068.solution | 6 ++++++ .../expected/model-solution000069.solution | 6 ++++++ .../expected/model-solution000070.solution | 6 ++++++ .../expected/model-solution000071.solution | 6 ++++++ .../expected/model-solution000072.solution | 6 ++++++ .../expected/model-solution000073.solution | 6 ++++++ .../expected/model-solution000074.solution | 6 ++++++ .../expected/model-solution000075.solution | 6 ++++++ .../expected/model-solution000076.solution | 6 ++++++ .../expected/model-solution000077.solution | 6 ++++++ .../expected/model-solution000078.solution | 6 ++++++ .../expected/model-solution000079.solution | 6 ++++++ .../expected/model-solution000080.solution | 6 ++++++ .../expected/model-solution000081.solution | 6 ++++++ .../expected/model-solution000082.solution | 6 ++++++ .../expected/model-solution000083.solution | 6 ++++++ .../expected/model-solution000084.solution | 6 ++++++ .../expected/model-solution000085.solution | 6 ++++++ .../expected/model-solution000086.solution | 6 ++++++ .../expected/model-solution000087.solution | 6 ++++++ .../expected/model-solution000088.solution | 6 ++++++ .../expected/model-solution000089.solution | 6 ++++++ .../expected/model-solution000090.solution | 6 ++++++ .../expected/model-solution000091.solution | 6 ++++++ .../expected/model-solution000092.solution | 6 ++++++ .../expected/model-solution000093.solution | 6 ++++++ .../expected/model-solution000094.solution | 6 ++++++ .../expected/model-solution000095.solution | 6 ++++++ .../expected/model-solution000096.solution | 6 ++++++ .../expected/model-solution000097.solution | 6 ++++++ .../expected/model-solution000098.solution | 6 ++++++ .../expected/model-solution000099.solution | 6 ++++++ .../expected/model-solution000100.solution | 6 ++++++ .../expected/model-solution000101.solution | 6 ++++++ .../expected/model-solution000102.solution | 6 ++++++ .../expected/model-solution000103.solution | 6 ++++++ .../expected/model-solution000104.solution | 6 ++++++ .../expected/model-solution000105.solution | 6 ++++++ .../expected/model-solution000106.solution | 6 ++++++ .../expected/model-solution000107.solution | 6 ++++++ .../expected/model-solution000108.solution | 6 ++++++ .../expected/model-solution000109.solution | 6 ++++++ .../expected/model-solution000110.solution | 6 ++++++ .../expected/model-solution000111.solution | 6 ++++++ .../expected/model-solution000112.solution | 6 ++++++ .../expected/model-solution000113.solution | 6 ++++++ .../expected/model-solution000114.solution | 6 ++++++ .../expected/model-solution000115.solution | 6 ++++++ .../expected/model-solution000116.solution | 6 ++++++ .../expected/model-solution000117.solution | 6 ++++++ .../expected/model-solution000118.solution | 6 ++++++ .../expected/model-solution000119.solution | 6 ++++++ .../expected/model-solution000120.solution | 6 ++++++ .../expected/model-solution000121.solution | 6 ++++++ .../expected/model-solution000122.solution | 6 ++++++ .../expected/model-solution000123.solution | 6 ++++++ .../expected/model-solution000124.solution | 6 ++++++ .../expected/model-solution000125.solution | 6 ++++++ .../expected/model-solution000126.solution | 6 ++++++ .../expected/model-solution000127.solution | 6 ++++++ .../expected/model-solution000128.solution | 6 ++++++ .../expected/model-solution000129.solution | 6 ++++++ .../expected/model-solution000130.solution | 6 ++++++ .../expected/model-solution000131.solution | 6 ++++++ .../expected/model-solution000132.solution | 6 ++++++ .../expected/model-solution000133.solution | 6 ++++++ .../expected/model-solution000134.solution | 6 ++++++ .../expected/model-solution000135.solution | 6 ++++++ .../expected/model-solution000136.solution | 6 ++++++ .../expected/model-solution000137.solution | 6 ++++++ .../expected/model-solution000138.solution | 6 ++++++ .../expected/model-solution000139.solution | 6 ++++++ .../expected/model-solution000140.solution | 6 ++++++ .../expected/model-solution000141.solution | 6 ++++++ .../expected/model-solution000142.solution | 6 ++++++ .../expected/model-solution000143.solution | 6 ++++++ .../expected/model-solution000144.solution | 6 ++++++ .../expected/model-solution000145.solution | 6 ++++++ .../expected/model-solution000146.solution | 6 ++++++ .../expected/model-solution000147.solution | 6 ++++++ .../expected/model-solution000148.solution | 6 ++++++ .../expected/model-solution000149.solution | 6 ++++++ .../expected/model-solution000150.solution | 6 ++++++ .../expected/model-solution000151.solution | 6 ++++++ .../expected/model-solution000152.solution | 6 ++++++ .../expected/model-solution000153.solution | 6 ++++++ .../expected/model-solution000154.solution | 6 ++++++ .../expected/model-solution000155.solution | 6 ++++++ .../expected/model-solution000156.solution | 6 ++++++ .../expected/model-solution000157.solution | 6 ++++++ .../expected/model-solution000158.solution | 6 ++++++ .../expected/model-solution000159.solution | 6 ++++++ .../expected/model-solution000160.solution | 6 ++++++ .../expected/model-solution000161.solution | 6 ++++++ .../expected/model-solution000162.solution | 6 ++++++ .../expected/model-solution000163.solution | 6 ++++++ .../expected/model-solution000164.solution | 6 ++++++ .../expected/model-solution000165.solution | 6 ++++++ .../expected/model-solution000166.solution | 6 ++++++ .../expected/model-solution000167.solution | 6 ++++++ .../expected/model-solution000168.solution | 6 ++++++ .../expected/model-solution000169.solution | 6 ++++++ .../expected/model-solution000170.solution | 6 ++++++ .../expected/model-solution000171.solution | 6 ++++++ .../expected/model-solution000172.solution | 6 ++++++ .../expected/model-solution000173.solution | 6 ++++++ .../expected/model-solution000174.solution | 6 ++++++ .../expected/model-solution000175.solution | 6 ++++++ .../expected/model-solution000176.solution | 6 ++++++ .../expected/model-solution000177.solution | 6 ++++++ .../expected/model-solution000178.solution | 6 ++++++ .../expected/model-solution000179.solution | 6 ++++++ .../expected/model-solution000180.solution | 6 ++++++ .../expected/model-solution000181.solution | 6 ++++++ .../expected/model-solution000182.solution | 6 ++++++ .../expected/model-solution000183.solution | 6 ++++++ .../expected/model-solution000184.solution | 6 ++++++ .../expected/model-solution000185.solution | 6 ++++++ .../expected/model-solution000186.solution | 6 ++++++ .../expected/model-solution000187.solution | 6 ++++++ .../expected/model-solution000188.solution | 6 ++++++ .../expected/model-solution000189.solution | 6 ++++++ .../expected/model-solution000190.solution | 6 ++++++ .../expected/model-solution000191.solution | 6 ++++++ .../expected/model-solution000192.solution | 6 ++++++ .../expected/model-solution000193.solution | 6 ++++++ .../expected/model-solution000194.solution | 6 ++++++ .../expected/model-solution000195.solution | 6 ++++++ .../expected/model-solution000196.solution | 6 ++++++ .../expected/model-solution000197.solution | 6 ++++++ .../expected/model-solution000198.solution | 6 ++++++ .../expected/model-solution000199.solution | 6 ++++++ .../expected/model-solution000200.solution | 6 ++++++ .../expected/model-solution000201.solution | 6 ++++++ .../expected/model-solution000202.solution | 6 ++++++ .../expected/model-solution000203.solution | 6 ++++++ .../expected/model-solution000204.solution | 6 ++++++ .../expected/model-solution000205.solution | 6 ++++++ .../expected/model-solution000206.solution | 6 ++++++ .../expected/model-solution000207.solution | 6 ++++++ .../expected/model-solution000208.solution | 6 ++++++ .../expected/model-solution000209.solution | 6 ++++++ .../expected/model-solution000210.solution | 6 ++++++ .../expected/model-solution000211.solution | 6 ++++++ .../expected/model-solution000212.solution | 6 ++++++ .../expected/model-solution000213.solution | 6 ++++++ .../expected/model-solution000214.solution | 6 ++++++ .../expected/model-solution000215.solution | 6 ++++++ .../expected/model-solution000216.solution | 6 ++++++ .../expected/model-solution000217.solution | 6 ++++++ .../expected/model-solution000218.solution | 6 ++++++ .../expected/model-solution000219.solution | 6 ++++++ .../expected/model-solution000220.solution | 6 ++++++ .../expected/model-solution000221.solution | 6 ++++++ .../expected/model-solution000222.solution | 6 ++++++ .../expected/model-solution000223.solution | 6 ++++++ .../expected/model-solution000224.solution | 6 ++++++ .../expected/model-solution000225.solution | 6 ++++++ .../expected/model-solution000226.solution | 6 ++++++ .../expected/model-solution000227.solution | 6 ++++++ .../expected/model-solution000228.solution | 6 ++++++ .../expected/model-solution000229.solution | 6 ++++++ .../expected/model-solution000230.solution | 6 ++++++ .../expected/model-solution000231.solution | 6 ++++++ .../expected/model-solution000232.solution | 6 ++++++ .../expected/model-solution000233.solution | 6 ++++++ .../expected/model-solution000234.solution | 6 ++++++ .../expected/model-solution000235.solution | 6 ++++++ .../expected/model-solution000236.solution | 6 ++++++ .../expected/model-solution000237.solution | 6 ++++++ .../expected/model-solution000238.solution | 6 ++++++ .../expected/model-solution000239.solution | 6 ++++++ .../expected/model-solution000240.solution | 6 ++++++ .../expected/model-solution000241.solution | 6 ++++++ .../expected/model-solution000242.solution | 6 ++++++ .../expected/model-solution000243.solution | 6 ++++++ .../expected/model-solution000244.solution | 6 ++++++ .../expected/model-solution000245.solution | 6 ++++++ .../expected/model-solution000246.solution | 6 ++++++ .../expected/model-solution000247.solution | 6 ++++++ .../expected/model-solution000248.solution | 6 ++++++ .../expected/model-solution000249.solution | 6 ++++++ .../expected/model-solution000250.solution | 6 ++++++ .../expected/model-solution000251.solution | 6 ++++++ .../expected/model-solution000252.solution | 6 ++++++ .../expected/model-solution000253.solution | 6 ++++++ .../expected/model-solution000254.solution | 6 ++++++ .../expected/model-solution000255.solution | 6 ++++++ .../expected/model-solution000256.solution | 6 ++++++ .../expected/model-solution000257.solution | 6 ++++++ .../expected/model-solution000258.solution | 6 ++++++ .../expected/model-solution000259.solution | 6 ++++++ .../expected/model-solution000260.solution | 6 ++++++ .../expected/model-solution000261.solution | 6 ++++++ .../expected/model-solution000262.solution | 6 ++++++ .../expected/model-solution000263.solution | 6 ++++++ .../expected/model-solution000264.solution | 6 ++++++ .../expected/model-solution000265.solution | 6 ++++++ .../expected/model-solution000266.solution | 6 ++++++ .../expected/model-solution000267.solution | 6 ++++++ .../expected/model-solution000268.solution | 6 ++++++ .../expected/model-solution000269.solution | 6 ++++++ .../expected/model-solution000270.solution | 6 ++++++ .../expected/model-solution000271.solution | 6 ++++++ .../expected/model-solution000272.solution | 6 ++++++ .../expected/model-solution000273.solution | 6 ++++++ .../expected/model-solution000274.solution | 6 ++++++ .../expected/model-solution000275.solution | 6 ++++++ .../expected/model-solution000276.solution | 6 ++++++ .../expected/model-solution000277.solution | 6 ++++++ .../expected/model-solution000278.solution | 6 ++++++ .../expected/model-solution000279.solution | 6 ++++++ .../expected/model-solution000280.solution | 6 ++++++ .../expected/model-solution000281.solution | 6 ++++++ .../expected/model-solution000282.solution | 6 ++++++ .../expected/model-solution000283.solution | 6 ++++++ .../expected/model-solution000284.solution | 6 ++++++ .../expected/model-solution000285.solution | 6 ++++++ .../expected/model-solution000286.solution | 6 ++++++ .../expected/model-solution000287.solution | 6 ++++++ .../expected/model-solution000288.solution | 6 ++++++ .../expected/model-solution000289.solution | 6 ++++++ .../expected/model-solution000290.solution | 6 ++++++ .../expected/model-solution000291.solution | 6 ++++++ .../expected/model-solution000292.solution | 6 ++++++ .../expected/model-solution000293.solution | 6 ++++++ .../expected/model-solution000294.solution | 6 ++++++ .../expected/model-solution000295.solution | 6 ++++++ .../expected/model-solution000296.solution | 6 ++++++ .../expected/model-solution000297.solution | 6 ++++++ .../expected/model-solution000298.solution | 6 ++++++ .../expected/model-solution000299.solution | 6 ++++++ .../expected/model-solution000300.solution | 6 ++++++ .../expected/model-solution000301.solution | 6 ++++++ .../expected/model-solution000302.solution | 6 ++++++ .../expected/model-solution000303.solution | 6 ++++++ .../expected/model-solution000304.solution | 6 ++++++ .../expected/model-solution000305.solution | 6 ++++++ .../expected/model-solution000306.solution | 6 ++++++ .../expected/model-solution000307.solution | 6 ++++++ .../expected/model-solution000308.solution | 6 ++++++ .../expected/model-solution000309.solution | 6 ++++++ .../expected/model-solution000310.solution | 6 ++++++ .../expected/model-solution000311.solution | 6 ++++++ .../expected/model-solution000312.solution | 6 ++++++ .../expected/model-solution000313.solution | 6 ++++++ .../expected/model-solution000314.solution | 6 ++++++ .../expected/model-solution000315.solution | 6 ++++++ .../expected/model-solution000316.solution | 6 ++++++ .../expected/model-solution000317.solution | 6 ++++++ .../expected/model-solution000318.solution | 6 ++++++ .../expected/model-solution000319.solution | 6 ++++++ .../expected/model-solution000320.solution | 6 ++++++ .../expected/model-solution000321.solution | 6 ++++++ .../expected/model-solution000322.solution | 6 ++++++ .../expected/model-solution000323.solution | 6 ++++++ .../expected/model-solution000324.solution | 6 ++++++ .../expected/model-solution000325.solution | 6 ++++++ .../expected/model-solution000326.solution | 6 ++++++ .../expected/model-solution000327.solution | 6 ++++++ .../expected/model-solution000328.solution | 6 ++++++ .../expected/model-solution000329.solution | 6 ++++++ .../expected/model-solution000330.solution | 6 ++++++ .../expected/model-solution000331.solution | 6 ++++++ .../expected/model-solution000332.solution | 6 ++++++ .../expected/model-solution000333.solution | 6 ++++++ .../expected/model-solution000334.solution | 6 ++++++ .../expected/model-solution000335.solution | 6 ++++++ .../expected/model-solution000336.solution | 6 ++++++ .../expected/model-solution000337.solution | 6 ++++++ .../expected/model-solution000338.solution | 6 ++++++ .../expected/model-solution000339.solution | 6 ++++++ .../expected/model-solution000340.solution | 6 ++++++ .../expected/model-solution000341.solution | 6 ++++++ .../expected/model-solution000342.solution | 6 ++++++ .../expected/model-solution000343.solution | 6 ++++++ .../expected/model-solution000344.solution | 6 ++++++ .../expected/model-solution000345.solution | 6 ++++++ .../expected/model-solution000346.solution | 6 ++++++ .../expected/model-solution000347.solution | 6 ++++++ .../expected/model-solution000348.solution | 6 ++++++ .../expected/model-solution000349.solution | 6 ++++++ .../expected/model-solution000350.solution | 6 ++++++ .../expected/model-solution000351.solution | 6 ++++++ .../expected/model-solution000352.solution | 6 ++++++ .../expected/model-solution000353.solution | 6 ++++++ .../expected/model-solution000354.solution | 6 ++++++ .../expected/model-solution000355.solution | 6 ++++++ .../expected/model-solution000356.solution | 6 ++++++ .../expected/model-solution000357.solution | 6 ++++++ .../expected/model-solution000358.solution | 6 ++++++ .../expected/model-solution000359.solution | 6 ++++++ .../expected/model-solution000360.solution | 6 ++++++ .../expected/model-solution000361.solution | 6 ++++++ .../expected/model-solution000362.solution | 6 ++++++ .../expected/model-solution000363.solution | 6 ++++++ .../expected/model-solution000364.solution | 6 ++++++ .../expected/model-solution000365.solution | 6 ++++++ .../expected/model-solution000366.solution | 6 ++++++ .../expected/model-solution000367.solution | 6 ++++++ .../expected/model-solution000368.solution | 6 ++++++ .../expected/model-solution000369.solution | 6 ++++++ .../expected/model-solution000370.solution | 6 ++++++ .../expected/model-solution000371.solution | 6 ++++++ .../expected/model-solution000372.solution | 6 ++++++ .../expected/model-solution000373.solution | 6 ++++++ .../expected/model-solution000374.solution | 6 ++++++ .../expected/model-solution000375.solution | 6 ++++++ .../expected/model-solution000376.solution | 6 ++++++ .../expected/model-solution000377.solution | 6 ++++++ .../expected/model-solution000378.solution | 6 ++++++ .../expected/model-solution000379.solution | 6 ++++++ .../expected/model-solution000380.solution | 6 ++++++ .../expected/model-solution000381.solution | 6 ++++++ .../expected/model-solution000382.solution | 6 ++++++ .../expected/model-solution000383.solution | 6 ++++++ .../expected/model-solution000384.solution | 6 ++++++ .../expected/model-solution000385.solution | 6 ++++++ .../expected/model-solution000386.solution | 6 ++++++ .../expected/model-solution000387.solution | 6 ++++++ .../expected/model-solution000388.solution | 6 ++++++ .../expected/model-solution000389.solution | 6 ++++++ .../expected/model-solution000390.solution | 6 ++++++ .../expected/model-solution000391.solution | 6 ++++++ .../expected/model-solution000392.solution | 6 ++++++ .../expected/model-solution000393.solution | 6 ++++++ .../expected/model-solution000394.solution | 6 ++++++ .../expected/model-solution000395.solution | 6 ++++++ .../expected/model-solution000396.solution | 6 ++++++ .../expected/model-solution000397.solution | 6 ++++++ .../expected/model-solution000398.solution | 6 ++++++ .../expected/model-solution000399.solution | 6 ++++++ .../expected/model-solution000400.solution | 6 ++++++ .../expected/model-solution000401.solution | 6 ++++++ .../expected/model-solution000402.solution | 6 ++++++ .../expected/model-solution000403.solution | 6 ++++++ .../expected/model-solution000404.solution | 6 ++++++ .../expected/model-solution000405.solution | 6 ++++++ .../expected/model-solution000406.solution | 6 ++++++ .../expected/model-solution000407.solution | 6 ++++++ .../expected/model-solution000408.solution | 6 ++++++ .../expected/model-solution000409.solution | 6 ++++++ .../expected/model-solution000410.solution | 6 ++++++ .../expected/model-solution000411.solution | 6 ++++++ .../expected/model-solution000412.solution | 6 ++++++ .../expected/model-solution000413.solution | 6 ++++++ .../expected/model-solution000414.solution | 6 ++++++ .../expected/model-solution000415.solution | 6 ++++++ .../expected/model-solution000416.solution | 6 ++++++ .../expected/model-solution000417.solution | 6 ++++++ .../expected/model-solution000418.solution | 6 ++++++ .../expected/model-solution000419.solution | 6 ++++++ .../expected/model-solution000420.solution | 6 ++++++ .../expected/model-solution000421.solution | 6 ++++++ .../expected/model-solution000422.solution | 6 ++++++ .../expected/model-solution000423.solution | 6 ++++++ .../expected/model-solution000424.solution | 6 ++++++ .../expected/model-solution000425.solution | 6 ++++++ .../expected/model-solution000426.solution | 6 ++++++ .../expected/model-solution000427.solution | 6 ++++++ .../expected/model-solution000428.solution | 6 ++++++ .../expected/model-solution000429.solution | 6 ++++++ .../expected/model-solution000430.solution | 6 ++++++ .../expected/model-solution000431.solution | 6 ++++++ .../expected/model-solution000432.solution | 6 ++++++ .../expected/model-solution000433.solution | 6 ++++++ .../expected/model-solution000434.solution | 6 ++++++ .../expected/model-solution000435.solution | 6 ++++++ .../expected/model-solution000436.solution | 6 ++++++ .../expected/model-solution000437.solution | 6 ++++++ .../expected/model-solution000438.solution | 6 ++++++ .../expected/model-solution000439.solution | 6 ++++++ .../expected/model-solution000440.solution | 6 ++++++ .../expected/model-solution000441.solution | 6 ++++++ .../expected/model-solution000442.solution | 6 ++++++ .../expected/model-solution000443.solution | 6 ++++++ .../expected/model-solution000444.solution | 6 ++++++ .../expected/model-solution000445.solution | 6 ++++++ .../expected/model-solution000446.solution | 6 ++++++ .../expected/model-solution000447.solution | 6 ++++++ .../expected/model-solution000448.solution | 6 ++++++ .../expected/model-solution000449.solution | 6 ++++++ .../expected/model-solution000450.solution | 6 ++++++ .../expected/model-solution000451.solution | 6 ++++++ .../expected/model-solution000452.solution | 6 ++++++ .../expected/model-solution000453.solution | 6 ++++++ .../expected/model-solution000454.solution | 6 ++++++ .../expected/model-solution000455.solution | 6 ++++++ .../expected/model-solution000456.solution | 6 ++++++ .../expected/model-solution000457.solution | 6 ++++++ .../expected/model-solution000458.solution | 6 ++++++ .../expected/model-solution000459.solution | 6 ++++++ .../expected/model-solution000460.solution | 6 ++++++ .../expected/model-solution000461.solution | 6 ++++++ .../expected/model-solution000462.solution | 6 ++++++ .../expected/model-solution000463.solution | 6 ++++++ .../expected/model-solution000464.solution | 6 ++++++ .../expected/model-solution000465.solution | 6 ++++++ .../expected/model-solution000466.solution | 6 ++++++ .../expected/model-solution000467.solution | 6 ++++++ .../expected/model-solution000468.solution | 6 ++++++ .../expected/model-solution000469.solution | 6 ++++++ .../expected/model-solution000470.solution | 6 ++++++ .../expected/model-solution000471.solution | 6 ++++++ .../expected/model-solution000472.solution | 6 ++++++ .../expected/model-solution000473.solution | 6 ++++++ .../expected/model-solution000474.solution | 6 ++++++ .../expected/model-solution000475.solution | 6 ++++++ .../expected/model-solution000476.solution | 6 ++++++ .../expected/model-solution000477.solution | 6 ++++++ .../expected/model-solution000478.solution | 6 ++++++ .../expected/model-solution000479.solution | 6 ++++++ .../expected/model-solution000480.solution | 6 ++++++ .../expected/model-solution000481.solution | 6 ++++++ .../expected/model-solution000482.solution | 6 ++++++ .../expected/model-solution000483.solution | 6 ++++++ .../expected/model-solution000484.solution | 6 ++++++ .../expected/model-solution000485.solution | 6 ++++++ .../expected/model-solution000486.solution | 6 ++++++ .../expected/model-solution000487.solution | 6 ++++++ .../expected/model-solution000488.solution | 6 ++++++ .../expected/model-solution000489.solution | 6 ++++++ .../expected/model-solution000490.solution | 6 ++++++ .../expected/model.eprime | 17 +++++++++++++++++ .../permutation.essence | 14 ++++++++++++++ 728 files changed, 4119 insertions(+) create mode 100644 tests/exhaustive/basic/perms/04_image/enum/0001_given_permutation_given_enum/expected/model-permutation-solution000001.solution create mode 100644 tests/exhaustive/basic/perms/04_image/enum/0001_given_permutation_given_enum/expected/model-permutation.eprime-param create mode 100644 tests/exhaustive/basic/perms/04_image/enum/0001_given_permutation_given_enum/expected/model-permutation2-solution000001.solution create mode 100644 tests/exhaustive/basic/perms/04_image/enum/0001_given_permutation_given_enum/expected/model-permutation2.eprime-param create mode 100644 tests/exhaustive/basic/perms/04_image/enum/0001_given_permutation_given_enum/expected/model.eprime create mode 100644 tests/exhaustive/basic/perms/04_image/enum/0001_given_permutation_given_enum/permutation.essence create mode 100644 tests/exhaustive/basic/perms/04_image/enum/0001_given_permutation_given_enum/permutation.param create mode 100644 tests/exhaustive/basic/perms/04_image/enum/0001_given_permutation_given_enum/permutation2.param create mode 100644 tests/exhaustive/basic/perms/04_image/enum/0002_given_permutation_letting_enum/expected/model-permutation-solution000001.solution create mode 100644 tests/exhaustive/basic/perms/04_image/enum/0002_given_permutation_letting_enum/expected/model-permutation.eprime-param create mode 100644 tests/exhaustive/basic/perms/04_image/enum/0002_given_permutation_letting_enum/expected/model.eprime create mode 100644 tests/exhaustive/basic/perms/04_image/enum/0002_given_permutation_letting_enum/permutation.essence create mode 100644 tests/exhaustive/basic/perms/04_image/enum/0002_given_permutation_letting_enum/permutation.param create mode 100644 tests/exhaustive/basic/perms/04_image/enum/0003_given_permutation_letting_enum/expected/model-permutation-solution000001.solution create mode 100644 tests/exhaustive/basic/perms/04_image/enum/0003_given_permutation_letting_enum/expected/model-permutation.eprime-param create mode 100644 tests/exhaustive/basic/perms/04_image/enum/0003_given_permutation_letting_enum/expected/model.eprime create mode 100644 tests/exhaustive/basic/perms/04_image/enum/0003_given_permutation_letting_enum/permutation.essence create mode 100644 tests/exhaustive/basic/perms/04_image/enum/0003_given_permutation_letting_enum/permutation.param create mode 100644 tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model-permutation-solution000001.solution create mode 100644 tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model-permutation-solution000002.solution create mode 100644 tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model-permutation-solution000003.solution create mode 100644 tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model-permutation-solution000004.solution create mode 100644 tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model-permutation-solution000005.solution create mode 100644 tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model-permutation.eprime-param create mode 100644 tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model-permutation2-solution000001.solution create mode 100644 tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model-permutation2-solution000002.solution create mode 100644 tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model-permutation2-solution000003.solution create mode 100644 tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model-permutation2-solution000004.solution create mode 100644 tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model-permutation2-solution000005.solution create mode 100644 tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model-permutation2-solution000006.solution create mode 100644 tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model-permutation2-solution000007.solution create mode 100644 tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model-permutation2-solution000008.solution create mode 100644 tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model-permutation2-solution000009.solution create mode 100644 tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model-permutation2-solution000010.solution create mode 100644 tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model-permutation2-solution000011.solution create mode 100644 tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model-permutation2-solution000012.solution create mode 100644 tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model-permutation2-solution000013.solution create mode 100644 tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model-permutation2-solution000014.solution create mode 100644 tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model-permutation2-solution000015.solution create mode 100644 tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model-permutation2-solution000016.solution create mode 100644 tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model-permutation2-solution000017.solution create mode 100644 tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model-permutation2-solution000018.solution create mode 100644 tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model-permutation2-solution000019.solution create mode 100644 tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model-permutation2-solution000020.solution create mode 100644 tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model-permutation2-solution000021.solution create mode 100644 tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model-permutation2-solution000022.solution create mode 100644 tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model-permutation2-solution000023.solution create mode 100644 tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model-permutation2-solution000024.solution create mode 100644 tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model-permutation2-solution000025.solution create mode 100644 tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model-permutation2-solution000026.solution create mode 100644 tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model-permutation2-solution000027.solution create mode 100644 tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model-permutation2-solution000028.solution create mode 100644 tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model-permutation2-solution000029.solution create mode 100644 tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model-permutation2-solution000030.solution create mode 100644 tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model-permutation2-solution000031.solution create mode 100644 tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model-permutation2-solution000032.solution create mode 100644 tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model-permutation2-solution000033.solution create mode 100644 tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model-permutation2-solution000034.solution create mode 100644 tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model-permutation2-solution000035.solution create mode 100644 tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model-permutation2-solution000036.solution create mode 100644 tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model-permutation2-solution000037.solution create mode 100644 tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model-permutation2-solution000038.solution create mode 100644 tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model-permutation2-solution000039.solution create mode 100644 tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model-permutation2-solution000040.solution create mode 100644 tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model-permutation2.eprime-param create mode 100644 tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model.eprime create mode 100644 tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/permutation.essence create mode 100644 tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/permutation.param create mode 100644 tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/permutation2.param create mode 100644 tests/exhaustive/basic/perms/04_image/enum/0006_letting_permutation_given_enum/expected/model-permutation-solution000001.solution create mode 100644 tests/exhaustive/basic/perms/04_image/enum/0006_letting_permutation_given_enum/expected/model-permutation.eprime-param create mode 100644 tests/exhaustive/basic/perms/04_image/enum/0006_letting_permutation_given_enum/expected/model-permutation2-solution000001.solution create mode 100644 tests/exhaustive/basic/perms/04_image/enum/0006_letting_permutation_given_enum/expected/model-permutation2.eprime-param create mode 100644 tests/exhaustive/basic/perms/04_image/enum/0006_letting_permutation_given_enum/expected/model.eprime create mode 100644 tests/exhaustive/basic/perms/04_image/enum/0006_letting_permutation_given_enum/permutation.essence create mode 100644 tests/exhaustive/basic/perms/04_image/enum/0006_letting_permutation_given_enum/permutation.param create mode 100644 tests/exhaustive/basic/perms/04_image/enum/0006_letting_permutation_given_enum/permutation2.param create mode 100644 tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000001.solution create mode 100644 tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000002.solution create mode 100644 tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000003.solution create mode 100644 tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000004.solution create mode 100644 tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000005.solution create mode 100644 tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000006.solution create mode 100644 tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000007.solution create mode 100644 tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000008.solution create mode 100644 tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000009.solution create mode 100644 tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000010.solution create mode 100644 tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000011.solution create mode 100644 tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000012.solution create mode 100644 tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000013.solution create mode 100644 tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000014.solution create mode 100644 tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000015.solution create mode 100644 tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000016.solution create mode 100644 tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000017.solution create mode 100644 tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000018.solution create mode 100644 tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000019.solution create mode 100644 tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000020.solution create mode 100644 tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000021.solution create mode 100644 tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000022.solution create mode 100644 tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000023.solution create mode 100644 tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000024.solution create mode 100644 tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000025.solution create mode 100644 tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000026.solution create mode 100644 tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000027.solution create mode 100644 tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000028.solution create mode 100644 tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000029.solution create mode 100644 tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000030.solution create mode 100644 tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000031.solution create mode 100644 tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000032.solution create mode 100644 tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000033.solution create mode 100644 tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000034.solution create mode 100644 tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000035.solution create mode 100644 tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000036.solution create mode 100644 tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000037.solution create mode 100644 tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000038.solution create mode 100644 tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000039.solution create mode 100644 tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000040.solution create mode 100644 tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000041.solution create mode 100644 tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000042.solution create mode 100644 tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000043.solution create mode 100644 tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000044.solution create mode 100644 tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000045.solution create mode 100644 tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000046.solution create mode 100644 tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000047.solution create mode 100644 tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000048.solution create mode 100644 tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000049.solution create mode 100644 tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000050.solution create mode 100644 tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000051.solution create mode 100644 tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000052.solution create mode 100644 tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000053.solution create mode 100644 tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000054.solution create mode 100644 tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000055.solution create mode 100644 tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000056.solution create mode 100644 tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000057.solution create mode 100644 tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000058.solution create mode 100644 tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000059.solution create mode 100644 tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000060.solution create mode 100644 tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000061.solution create mode 100644 tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000062.solution create mode 100644 tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000063.solution create mode 100644 tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000064.solution create mode 100644 tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000065.solution create mode 100644 tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000066.solution create mode 100644 tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000067.solution create mode 100644 tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000068.solution create mode 100644 tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000069.solution create mode 100644 tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000070.solution create mode 100644 tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000071.solution create mode 100644 tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000072.solution create mode 100644 tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000073.solution create mode 100644 tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000074.solution create mode 100644 tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000075.solution create mode 100644 tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000076.solution create mode 100644 tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000077.solution create mode 100644 tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000078.solution create mode 100644 tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000079.solution create mode 100644 tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000080.solution create mode 100644 tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000081.solution create mode 100644 tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000082.solution create mode 100644 tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000083.solution create mode 100644 tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000084.solution create mode 100644 tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000085.solution create mode 100644 tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000086.solution create mode 100644 tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000087.solution create mode 100644 tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000088.solution create mode 100644 tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000089.solution create mode 100644 tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000090.solution create mode 100644 tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000091.solution create mode 100644 tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000092.solution create mode 100644 tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000093.solution create mode 100644 tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000094.solution create mode 100644 tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000095.solution create mode 100644 tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000096.solution create mode 100644 tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000097.solution create mode 100644 tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000098.solution create mode 100644 tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000099.solution create mode 100644 tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000100.solution create mode 100644 tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model.eprime create mode 100644 tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/permutation.essence create mode 100644 tests/exhaustive/basic/perms/04_image/int/0001_given_permutation_given_int/expected/model-permutation-solution000001.solution create mode 100644 tests/exhaustive/basic/perms/04_image/int/0001_given_permutation_given_int/expected/model-permutation.eprime-param create mode 100644 tests/exhaustive/basic/perms/04_image/int/0001_given_permutation_given_int/expected/model-permutation2-solution000001.solution create mode 100644 tests/exhaustive/basic/perms/04_image/int/0001_given_permutation_given_int/expected/model-permutation2.eprime-param create mode 100644 tests/exhaustive/basic/perms/04_image/int/0001_given_permutation_given_int/expected/model.eprime create mode 100644 tests/exhaustive/basic/perms/04_image/int/0001_given_permutation_given_int/permutation.essence create mode 100644 tests/exhaustive/basic/perms/04_image/int/0001_given_permutation_given_int/permutation.param create mode 100644 tests/exhaustive/basic/perms/04_image/int/0001_given_permutation_given_int/permutation2.param create mode 100644 tests/exhaustive/basic/perms/04_image/int/0002_given_permutation_letting_int/expected/model-permutation-solution000001.solution create mode 100644 tests/exhaustive/basic/perms/04_image/int/0002_given_permutation_letting_int/expected/model-permutation.eprime-param create mode 100644 tests/exhaustive/basic/perms/04_image/int/0002_given_permutation_letting_int/expected/model.eprime create mode 100644 tests/exhaustive/basic/perms/04_image/int/0002_given_permutation_letting_int/permutation.essence create mode 100644 tests/exhaustive/basic/perms/04_image/int/0002_given_permutation_letting_int/permutation.param create mode 100644 tests/exhaustive/basic/perms/04_image/int/0003_given_permutation_letting_int/expected/model-permutation-solution000001.solution create mode 100644 tests/exhaustive/basic/perms/04_image/int/0003_given_permutation_letting_int/expected/model-permutation.eprime-param create mode 100644 tests/exhaustive/basic/perms/04_image/int/0003_given_permutation_letting_int/expected/model.eprime create mode 100644 tests/exhaustive/basic/perms/04_image/int/0003_given_permutation_letting_int/permutation.essence create mode 100644 tests/exhaustive/basic/perms/04_image/int/0003_given_permutation_letting_int/permutation.param create mode 100644 tests/exhaustive/basic/perms/04_image/int/0004_given_permutation_find_int/permutation.essence create mode 100644 tests/exhaustive/basic/perms/04_image/int/0004_given_permutation_find_int/permutation.param create mode 100644 tests/exhaustive/basic/perms/04_image/int/0004_given_permutation_find_int/permutation2.essence create mode 100644 tests/exhaustive/basic/perms/04_image/int/0005_find_permutation_given_ints/expected/model-permutation-solution000001.solution create mode 100644 tests/exhaustive/basic/perms/04_image/int/0005_find_permutation_given_ints/expected/model-permutation-solution000002.solution create mode 100644 tests/exhaustive/basic/perms/04_image/int/0005_find_permutation_given_ints/expected/model-permutation.eprime-param create mode 100644 tests/exhaustive/basic/perms/04_image/int/0005_find_permutation_given_ints/expected/model-permutation2-solution000001.solution create mode 100644 tests/exhaustive/basic/perms/04_image/int/0005_find_permutation_given_ints/expected/model-permutation2-solution000002.solution create mode 100644 tests/exhaustive/basic/perms/04_image/int/0005_find_permutation_given_ints/expected/model-permutation2.eprime-param create mode 100644 tests/exhaustive/basic/perms/04_image/int/0005_find_permutation_given_ints/expected/model.eprime create mode 100644 tests/exhaustive/basic/perms/04_image/int/0005_find_permutation_given_ints/permutation.essence create mode 100644 tests/exhaustive/basic/perms/04_image/int/0005_find_permutation_given_ints/permutation.param create mode 100644 tests/exhaustive/basic/perms/04_image/int/0005_find_permutation_given_ints/permutation2.param create mode 100644 tests/exhaustive/basic/perms/04_image/int/0007_find_permutation_find_ints/expected/model-solution000001.solution create mode 100644 tests/exhaustive/basic/perms/04_image/int/0007_find_permutation_find_ints/expected/model-solution000002.solution create mode 100644 tests/exhaustive/basic/perms/04_image/int/0007_find_permutation_find_ints/expected/model-solution000003.solution create mode 100644 tests/exhaustive/basic/perms/04_image/int/0007_find_permutation_find_ints/expected/model-solution000004.solution create mode 100644 tests/exhaustive/basic/perms/04_image/int/0007_find_permutation_find_ints/expected/model-solution000005.solution create mode 100644 tests/exhaustive/basic/perms/04_image/int/0007_find_permutation_find_ints/expected/model-solution000006.solution create mode 100644 tests/exhaustive/basic/perms/04_image/int/0007_find_permutation_find_ints/expected/model-solution000007.solution create mode 100644 tests/exhaustive/basic/perms/04_image/int/0007_find_permutation_find_ints/expected/model-solution000008.solution create mode 100644 tests/exhaustive/basic/perms/04_image/int/0007_find_permutation_find_ints/expected/model-solution000009.solution create mode 100644 tests/exhaustive/basic/perms/04_image/int/0007_find_permutation_find_ints/expected/model-solution000010.solution create mode 100644 tests/exhaustive/basic/perms/04_image/int/0007_find_permutation_find_ints/expected/model-solution000011.solution create mode 100644 tests/exhaustive/basic/perms/04_image/int/0007_find_permutation_find_ints/expected/model-solution000012.solution create mode 100644 tests/exhaustive/basic/perms/04_image/int/0007_find_permutation_find_ints/expected/model-solution000013.solution create mode 100644 tests/exhaustive/basic/perms/04_image/int/0007_find_permutation_find_ints/expected/model-solution000014.solution create mode 100644 tests/exhaustive/basic/perms/04_image/int/0007_find_permutation_find_ints/expected/model-solution000015.solution create mode 100644 tests/exhaustive/basic/perms/04_image/int/0007_find_permutation_find_ints/expected/model-solution000016.solution create mode 100644 tests/exhaustive/basic/perms/04_image/int/0007_find_permutation_find_ints/expected/model-solution000017.solution create mode 100644 tests/exhaustive/basic/perms/04_image/int/0007_find_permutation_find_ints/expected/model-solution000018.solution create mode 100644 tests/exhaustive/basic/perms/04_image/int/0007_find_permutation_find_ints/expected/model-solution000019.solution create mode 100644 tests/exhaustive/basic/perms/04_image/int/0007_find_permutation_find_ints/expected/model-solution000020.solution create mode 100644 tests/exhaustive/basic/perms/04_image/int/0007_find_permutation_find_ints/expected/model-solution000021.solution create mode 100644 tests/exhaustive/basic/perms/04_image/int/0007_find_permutation_find_ints/expected/model-solution000022.solution create mode 100644 tests/exhaustive/basic/perms/04_image/int/0007_find_permutation_find_ints/expected/model-solution000023.solution create mode 100644 tests/exhaustive/basic/perms/04_image/int/0007_find_permutation_find_ints/expected/model-solution000024.solution create mode 100644 tests/exhaustive/basic/perms/04_image/int/0007_find_permutation_find_ints/expected/model.eprime create mode 100644 tests/exhaustive/basic/perms/04_image/int/0007_find_permutation_find_ints/permutation.essence create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000001.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000002.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000003.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000004.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000005.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000006.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000007.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000008.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000009.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000010.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000011.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000012.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000013.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000014.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000015.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000016.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000017.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000018.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000019.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000020.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000021.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000022.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000023.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000024.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000025.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000026.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000027.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000028.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000029.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000030.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000031.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000032.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000033.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000034.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000035.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000036.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000037.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000038.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000039.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000040.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000041.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000042.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000043.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000044.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000045.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000046.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000047.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000048.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000049.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000050.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000051.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000052.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000053.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000054.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000055.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000056.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000057.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000058.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000059.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000060.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000061.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000062.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000063.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000064.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000065.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000066.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000067.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000068.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000069.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000070.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000071.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000072.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000073.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000074.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000075.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000076.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000077.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000078.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000079.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000080.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000081.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000082.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000083.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000084.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000085.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000086.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000087.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000088.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000089.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000090.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000091.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000092.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000093.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000094.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000095.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000096.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000097.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000098.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000099.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000100.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000101.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000102.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000103.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000104.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000105.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000106.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000107.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000108.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000109.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000110.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000111.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000112.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000113.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000114.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000115.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000116.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000117.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000118.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000119.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000120.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000121.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000122.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000123.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000124.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000125.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000126.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000127.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000128.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000129.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000130.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000131.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000132.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000133.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000134.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000135.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000136.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000137.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000138.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000139.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000140.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000141.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000142.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000143.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000144.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000145.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000146.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000147.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000148.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000149.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000150.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000151.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000152.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000153.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000154.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000155.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000156.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000157.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000158.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000159.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000160.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000161.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000162.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000163.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000164.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000165.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000166.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000167.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000168.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000169.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000170.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000171.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000172.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000173.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000174.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000175.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000176.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000177.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000178.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000179.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000180.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000181.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000182.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000183.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000184.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000185.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000186.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000187.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000188.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000189.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000190.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000191.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000192.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000193.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000194.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000195.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000196.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000197.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000198.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000199.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000200.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000201.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000202.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000203.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000204.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000205.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000206.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000207.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000208.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000209.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000210.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000211.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000212.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000213.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000214.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000215.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000216.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000217.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000218.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000219.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000220.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000221.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000222.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000223.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000224.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000225.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000226.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000227.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000228.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000229.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000230.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000231.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000232.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000233.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000234.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000235.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000236.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000237.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000238.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000239.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000240.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000241.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000242.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000243.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000244.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000245.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000246.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000247.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000248.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000249.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000250.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000251.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000252.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000253.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000254.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000255.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000256.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000257.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000258.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000259.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000260.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000261.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000262.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000263.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000264.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000265.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000266.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000267.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000268.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000269.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000270.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000271.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000272.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000273.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000274.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000275.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000276.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000277.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000278.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000279.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000280.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000281.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000282.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000283.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000284.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000285.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000286.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000287.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000288.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000289.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000290.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000291.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000292.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000293.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000294.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000295.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000296.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000297.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000298.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000299.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000300.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000301.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000302.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000303.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000304.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000305.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000306.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000307.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000308.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000309.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000310.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000311.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000312.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000313.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000314.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000315.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000316.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000317.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000318.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000319.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000320.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000321.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000322.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000323.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000324.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000325.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000326.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000327.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000328.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000329.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000330.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000331.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000332.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000333.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000334.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000335.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000336.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000337.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000338.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000339.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000340.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000341.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000342.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000343.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000344.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000345.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000346.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000347.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000348.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000349.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000350.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000351.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000352.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000353.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000354.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000355.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000356.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000357.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000358.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000359.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000360.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000361.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000362.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000363.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000364.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000365.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000366.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000367.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000368.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000369.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000370.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000371.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000372.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000373.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000374.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000375.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000376.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000377.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000378.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000379.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000380.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000381.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000382.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000383.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000384.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000385.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000386.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000387.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000388.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000389.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000390.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000391.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000392.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000393.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000394.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000395.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000396.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000397.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000398.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000399.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000400.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000401.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000402.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000403.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000404.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000405.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000406.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000407.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000408.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000409.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000410.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000411.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000412.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000413.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000414.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000415.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000416.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000417.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000418.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000419.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000420.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000421.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000422.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000423.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000424.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000425.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000426.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000427.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000428.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000429.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000430.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000431.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000432.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000433.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000434.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000435.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000436.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000437.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000438.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000439.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000440.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000441.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000442.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000443.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000444.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000445.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000446.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000447.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000448.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000449.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000450.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000451.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000452.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000453.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000454.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000455.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000456.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000457.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000458.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000459.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000460.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000461.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000462.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000463.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000464.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000465.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000466.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000467.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000468.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000469.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000470.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000471.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000472.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000473.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000474.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000475.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000476.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000477.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000478.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000479.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000480.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000481.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000482.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000483.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000484.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000485.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000486.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000487.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000488.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000489.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000490.solution create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model.eprime create mode 100644 tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/permutation.essence diff --git a/tests/exhaustive/basic/perms/04_image/enum/0001_given_permutation_given_enum/expected/model-permutation-solution000001.solution b/tests/exhaustive/basic/perms/04_image/enum/0001_given_permutation_given_enum/expected/model-permutation-solution000001.solution new file mode 100644 index 0000000000..23c353363e --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/enum/0001_given_permutation_given_enum/expected/model-permutation-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting j be E3 diff --git a/tests/exhaustive/basic/perms/04_image/enum/0001_given_permutation_given_enum/expected/model-permutation.eprime-param b/tests/exhaustive/basic/perms/04_image/enum/0001_given_permutation_given_enum/expected/model-permutation.eprime-param new file mode 100644 index 0000000000..14ab17b4ee --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/enum/0001_given_permutation_given_enum/expected/model-permutation.eprime-param @@ -0,0 +1,4 @@ +language ESSENCE' 1.0 + +letting p_PermutationAsFunction_PermutationFunction_Function1D be [1, 4, 3, 5, 2, 6, 7; int(1..7)] +letting i be 2 diff --git a/tests/exhaustive/basic/perms/04_image/enum/0001_given_permutation_given_enum/expected/model-permutation2-solution000001.solution b/tests/exhaustive/basic/perms/04_image/enum/0001_given_permutation_given_enum/expected/model-permutation2-solution000001.solution new file mode 100644 index 0000000000..818b6919ed --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/enum/0001_given_permutation_given_enum/expected/model-permutation2-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting j be E6 diff --git a/tests/exhaustive/basic/perms/04_image/enum/0001_given_permutation_given_enum/expected/model-permutation2.eprime-param b/tests/exhaustive/basic/perms/04_image/enum/0001_given_permutation_given_enum/expected/model-permutation2.eprime-param new file mode 100644 index 0000000000..54120b9c64 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/enum/0001_given_permutation_given_enum/expected/model-permutation2.eprime-param @@ -0,0 +1,4 @@ +language ESSENCE' 1.0 + +letting p_PermutationAsFunction_PermutationFunction_Function1D be [1, 4, 3, 5, 2, 6, 7; int(1..7)] +letting i be 7 diff --git a/tests/exhaustive/basic/perms/04_image/enum/0001_given_permutation_given_enum/expected/model.eprime b/tests/exhaustive/basic/perms/04_image/enum/0001_given_permutation_given_enum/expected/model.eprime new file mode 100644 index 0000000000..547ef36d70 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/enum/0001_given_permutation_given_enum/expected/model.eprime @@ -0,0 +1,11 @@ +language ESSENCE' 1.0 + +given i: int(1..7) +given p_PermutationAsFunction_PermutationFunction_Function1D: matrix indexed by [int(1..7)] of int(1..7) +find j: int(1..7) +branching on [j] +such that + j = + [i, catchUndef(p_PermutationAsFunction_PermutationFunction_Function1D[i], 0); int(1..2)] + [toInt(or([q2 = i | q2 : int(1..7)])) + 1] + diff --git a/tests/exhaustive/basic/perms/04_image/enum/0001_given_permutation_given_enum/permutation.essence b/tests/exhaustive/basic/perms/04_image/enum/0001_given_permutation_given_enum/permutation.essence new file mode 100644 index 0000000000..d72ee5d644 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/enum/0001_given_permutation_given_enum/permutation.essence @@ -0,0 +1,13 @@ +letting n be new type enum {E0, E1, E2, E3, E4, E5, E6} + +given i : n + +given p : permutation of n + +find j : n + +such that j = image(p, i) + + + + diff --git a/tests/exhaustive/basic/perms/04_image/enum/0001_given_permutation_given_enum/permutation.param b/tests/exhaustive/basic/perms/04_image/enum/0001_given_permutation_given_enum/permutation.param new file mode 100644 index 0000000000..b09ac9d45d --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/enum/0001_given_permutation_given_enum/permutation.param @@ -0,0 +1,2 @@ +letting p be permutation((E1,E3,E4)) +letting i be E1 diff --git a/tests/exhaustive/basic/perms/04_image/enum/0001_given_permutation_given_enum/permutation2.param b/tests/exhaustive/basic/perms/04_image/enum/0001_given_permutation_given_enum/permutation2.param new file mode 100644 index 0000000000..c02623b95d --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/enum/0001_given_permutation_given_enum/permutation2.param @@ -0,0 +1,2 @@ +letting p be permutation((E1,E3,E4)) +letting i be E6 diff --git a/tests/exhaustive/basic/perms/04_image/enum/0002_given_permutation_letting_enum/expected/model-permutation-solution000001.solution b/tests/exhaustive/basic/perms/04_image/enum/0002_given_permutation_letting_enum/expected/model-permutation-solution000001.solution new file mode 100644 index 0000000000..23c353363e --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/enum/0002_given_permutation_letting_enum/expected/model-permutation-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting j be E3 diff --git a/tests/exhaustive/basic/perms/04_image/enum/0002_given_permutation_letting_enum/expected/model-permutation.eprime-param b/tests/exhaustive/basic/perms/04_image/enum/0002_given_permutation_letting_enum/expected/model-permutation.eprime-param new file mode 100644 index 0000000000..057f35e97d --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/enum/0002_given_permutation_letting_enum/expected/model-permutation.eprime-param @@ -0,0 +1,3 @@ +language ESSENCE' 1.0 + +letting p_PermutationAsFunction_PermutationFunction_Function1D be [1, 4, 3, 5, 2, 6, 7; int(1..7)] diff --git a/tests/exhaustive/basic/perms/04_image/enum/0002_given_permutation_letting_enum/expected/model.eprime b/tests/exhaustive/basic/perms/04_image/enum/0002_given_permutation_letting_enum/expected/model.eprime new file mode 100644 index 0000000000..e52723fd4a --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/enum/0002_given_permutation_letting_enum/expected/model.eprime @@ -0,0 +1,7 @@ +language ESSENCE' 1.0 + +given p_PermutationAsFunction_PermutationFunction_Function1D: matrix indexed by [int(1..7)] of int(1..7) +find j: int(1..7) +branching on [j] +such that j = catchUndef(p_PermutationAsFunction_PermutationFunction_Function1D[2], 0) + diff --git a/tests/exhaustive/basic/perms/04_image/enum/0002_given_permutation_letting_enum/permutation.essence b/tests/exhaustive/basic/perms/04_image/enum/0002_given_permutation_letting_enum/permutation.essence new file mode 100644 index 0000000000..61a292a552 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/enum/0002_given_permutation_letting_enum/permutation.essence @@ -0,0 +1,12 @@ +letting n be new type enum {E0,E1,E2,E3,E4,E5,E6} +letting i be E1 + +given p : permutation of n + +find j : n + +such that j = image(p, i) + + + + diff --git a/tests/exhaustive/basic/perms/04_image/enum/0002_given_permutation_letting_enum/permutation.param b/tests/exhaustive/basic/perms/04_image/enum/0002_given_permutation_letting_enum/permutation.param new file mode 100644 index 0000000000..19349bb872 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/enum/0002_given_permutation_letting_enum/permutation.param @@ -0,0 +1 @@ +letting p be permutation((E1,E3,E4)) diff --git a/tests/exhaustive/basic/perms/04_image/enum/0003_given_permutation_letting_enum/expected/model-permutation-solution000001.solution b/tests/exhaustive/basic/perms/04_image/enum/0003_given_permutation_letting_enum/expected/model-permutation-solution000001.solution new file mode 100644 index 0000000000..818b6919ed --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/enum/0003_given_permutation_letting_enum/expected/model-permutation-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting j be E6 diff --git a/tests/exhaustive/basic/perms/04_image/enum/0003_given_permutation_letting_enum/expected/model-permutation.eprime-param b/tests/exhaustive/basic/perms/04_image/enum/0003_given_permutation_letting_enum/expected/model-permutation.eprime-param new file mode 100644 index 0000000000..057f35e97d --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/enum/0003_given_permutation_letting_enum/expected/model-permutation.eprime-param @@ -0,0 +1,3 @@ +language ESSENCE' 1.0 + +letting p_PermutationAsFunction_PermutationFunction_Function1D be [1, 4, 3, 5, 2, 6, 7; int(1..7)] diff --git a/tests/exhaustive/basic/perms/04_image/enum/0003_given_permutation_letting_enum/expected/model.eprime b/tests/exhaustive/basic/perms/04_image/enum/0003_given_permutation_letting_enum/expected/model.eprime new file mode 100644 index 0000000000..3927221550 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/enum/0003_given_permutation_letting_enum/expected/model.eprime @@ -0,0 +1,7 @@ +language ESSENCE' 1.0 + +given p_PermutationAsFunction_PermutationFunction_Function1D: matrix indexed by [int(1..7)] of int(1..7) +find j: int(1..7) +branching on [j] +such that j = catchUndef(p_PermutationAsFunction_PermutationFunction_Function1D[7], 0) + diff --git a/tests/exhaustive/basic/perms/04_image/enum/0003_given_permutation_letting_enum/permutation.essence b/tests/exhaustive/basic/perms/04_image/enum/0003_given_permutation_letting_enum/permutation.essence new file mode 100644 index 0000000000..a136a2c21d --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/enum/0003_given_permutation_letting_enum/permutation.essence @@ -0,0 +1,12 @@ +letting n be new type enum {E0,E1,E2,E3,E4,E5,E6} +letting i be E6 + +given p : permutation of n + +find j : n + +such that j = image(p, i) + + + + diff --git a/tests/exhaustive/basic/perms/04_image/enum/0003_given_permutation_letting_enum/permutation.param b/tests/exhaustive/basic/perms/04_image/enum/0003_given_permutation_letting_enum/permutation.param new file mode 100644 index 0000000000..19349bb872 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/enum/0003_given_permutation_letting_enum/permutation.param @@ -0,0 +1 @@ +letting p be permutation((E1,E3,E4)) diff --git a/tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model-permutation-solution000001.solution b/tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model-permutation-solution000001.solution new file mode 100644 index 0000000000..3fef8d9264 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model-permutation-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting p be permutation((E3, E5, E4)) diff --git a/tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model-permutation-solution000002.solution b/tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model-permutation-solution000002.solution new file mode 100644 index 0000000000..ee70696ec2 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model-permutation-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting p be permutation((E3, E6, E4)) diff --git a/tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model-permutation-solution000003.solution b/tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model-permutation-solution000003.solution new file mode 100644 index 0000000000..629ad61397 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model-permutation-solution000003.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting p be permutation((E2, E4, E3)) diff --git a/tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model-permutation-solution000004.solution b/tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model-permutation-solution000004.solution new file mode 100644 index 0000000000..b58f30a6d5 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model-permutation-solution000004.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting p be permutation((E1, E4, E3)) diff --git a/tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model-permutation-solution000005.solution b/tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model-permutation-solution000005.solution new file mode 100644 index 0000000000..4accd87fcb --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model-permutation-solution000005.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting p be permutation((E0, E4, E3)) diff --git a/tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model-permutation.eprime-param b/tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model-permutation.eprime-param new file mode 100644 index 0000000000..8b87a55bcc --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model-permutation.eprime-param @@ -0,0 +1,4 @@ +language ESSENCE' 1.0 + +letting j be 4 +letting i be 5 diff --git a/tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model-permutation2-solution000001.solution b/tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model-permutation2-solution000001.solution new file mode 100644 index 0000000000..a0be6cb425 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model-permutation2-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting p be permutation((E4, E5, E6)) diff --git a/tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model-permutation2-solution000002.solution b/tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model-permutation2-solution000002.solution new file mode 100644 index 0000000000..f9abe77afc --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model-permutation2-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting p be permutation((E4, E6, E5)) diff --git a/tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model-permutation2-solution000003.solution b/tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model-permutation2-solution000003.solution new file mode 100644 index 0000000000..46ed8e6db1 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model-permutation2-solution000003.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting p be permutation((E2, E4, E5)) diff --git a/tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model-permutation2-solution000004.solution b/tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model-permutation2-solution000004.solution new file mode 100644 index 0000000000..e337f88ba4 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model-permutation2-solution000004.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting p be permutation((E2, E4, E6)) diff --git a/tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model-permutation2-solution000005.solution b/tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model-permutation2-solution000005.solution new file mode 100644 index 0000000000..452599788a --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model-permutation2-solution000005.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting p be permutation((E2, E5, E4)) diff --git a/tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model-permutation2-solution000006.solution b/tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model-permutation2-solution000006.solution new file mode 100644 index 0000000000..bd81cc117a --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model-permutation2-solution000006.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting p be permutation((E2, E5, E6)) diff --git a/tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model-permutation2-solution000007.solution b/tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model-permutation2-solution000007.solution new file mode 100644 index 0000000000..ac307ecc3f --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model-permutation2-solution000007.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting p be permutation((E2, E6, E4)) diff --git a/tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model-permutation2-solution000008.solution b/tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model-permutation2-solution000008.solution new file mode 100644 index 0000000000..5eb1db5a66 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model-permutation2-solution000008.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting p be permutation((E2, E6, E5)) diff --git a/tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model-permutation2-solution000009.solution b/tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model-permutation2-solution000009.solution new file mode 100644 index 0000000000..33947cf4e2 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model-permutation2-solution000009.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting p be permutation((E1, E2, E4)) diff --git a/tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model-permutation2-solution000010.solution b/tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model-permutation2-solution000010.solution new file mode 100644 index 0000000000..bcd9f854c5 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model-permutation2-solution000010.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting p be permutation((E1, E2, E5)) diff --git a/tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model-permutation2-solution000011.solution b/tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model-permutation2-solution000011.solution new file mode 100644 index 0000000000..7bec9d3af2 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model-permutation2-solution000011.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting p be permutation((E1, E2, E6)) diff --git a/tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model-permutation2-solution000012.solution b/tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model-permutation2-solution000012.solution new file mode 100644 index 0000000000..75881b0769 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model-permutation2-solution000012.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting p be permutation((E1, E4, E2)) diff --git a/tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model-permutation2-solution000013.solution b/tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model-permutation2-solution000013.solution new file mode 100644 index 0000000000..c2913f88ef --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model-permutation2-solution000013.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting p be permutation((E1, E4, E5)) diff --git a/tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model-permutation2-solution000014.solution b/tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model-permutation2-solution000014.solution new file mode 100644 index 0000000000..3b04ac97d8 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model-permutation2-solution000014.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting p be permutation((E1, E4, E6)) diff --git a/tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model-permutation2-solution000015.solution b/tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model-permutation2-solution000015.solution new file mode 100644 index 0000000000..0e42d076da --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model-permutation2-solution000015.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting p be permutation((E1, E5, E2)) diff --git a/tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model-permutation2-solution000016.solution b/tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model-permutation2-solution000016.solution new file mode 100644 index 0000000000..40f0baca23 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model-permutation2-solution000016.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting p be permutation((E1, E5, E4)) diff --git a/tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model-permutation2-solution000017.solution b/tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model-permutation2-solution000017.solution new file mode 100644 index 0000000000..7c5d2b6846 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model-permutation2-solution000017.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting p be permutation((E1, E5, E6)) diff --git a/tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model-permutation2-solution000018.solution b/tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model-permutation2-solution000018.solution new file mode 100644 index 0000000000..be8e5a66e4 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model-permutation2-solution000018.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting p be permutation((E1, E6, E2)) diff --git a/tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model-permutation2-solution000019.solution b/tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model-permutation2-solution000019.solution new file mode 100644 index 0000000000..681f1e8f84 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model-permutation2-solution000019.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting p be permutation((E1, E6, E4)) diff --git a/tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model-permutation2-solution000020.solution b/tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model-permutation2-solution000020.solution new file mode 100644 index 0000000000..15af4d73d6 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model-permutation2-solution000020.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting p be permutation((E1, E6, E5)) diff --git a/tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model-permutation2-solution000021.solution b/tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model-permutation2-solution000021.solution new file mode 100644 index 0000000000..4fb795c956 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model-permutation2-solution000021.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting p be permutation((E0, E1, E2)) diff --git a/tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model-permutation2-solution000022.solution b/tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model-permutation2-solution000022.solution new file mode 100644 index 0000000000..234942d580 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model-permutation2-solution000022.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting p be permutation((E0, E1, E4)) diff --git a/tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model-permutation2-solution000023.solution b/tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model-permutation2-solution000023.solution new file mode 100644 index 0000000000..058e188824 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model-permutation2-solution000023.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting p be permutation((E0, E1, E5)) diff --git a/tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model-permutation2-solution000024.solution b/tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model-permutation2-solution000024.solution new file mode 100644 index 0000000000..5f085793b0 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model-permutation2-solution000024.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting p be permutation((E0, E1, E6)) diff --git a/tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model-permutation2-solution000025.solution b/tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model-permutation2-solution000025.solution new file mode 100644 index 0000000000..e61a20208c --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model-permutation2-solution000025.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting p be permutation((E0, E2, E1)) diff --git a/tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model-permutation2-solution000026.solution b/tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model-permutation2-solution000026.solution new file mode 100644 index 0000000000..a73119ea78 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model-permutation2-solution000026.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting p be permutation((E0, E2, E4)) diff --git a/tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model-permutation2-solution000027.solution b/tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model-permutation2-solution000027.solution new file mode 100644 index 0000000000..bec0b72f04 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model-permutation2-solution000027.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting p be permutation((E0, E2, E5)) diff --git a/tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model-permutation2-solution000028.solution b/tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model-permutation2-solution000028.solution new file mode 100644 index 0000000000..a4775ca05d --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model-permutation2-solution000028.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting p be permutation((E0, E2, E6)) diff --git a/tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model-permutation2-solution000029.solution b/tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model-permutation2-solution000029.solution new file mode 100644 index 0000000000..5bb000a543 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model-permutation2-solution000029.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting p be permutation((E0, E4, E1)) diff --git a/tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model-permutation2-solution000030.solution b/tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model-permutation2-solution000030.solution new file mode 100644 index 0000000000..592d20d512 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model-permutation2-solution000030.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting p be permutation((E0, E4, E2)) diff --git a/tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model-permutation2-solution000031.solution b/tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model-permutation2-solution000031.solution new file mode 100644 index 0000000000..3fe8e281e8 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model-permutation2-solution000031.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting p be permutation((E0, E4, E5)) diff --git a/tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model-permutation2-solution000032.solution b/tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model-permutation2-solution000032.solution new file mode 100644 index 0000000000..9dd0003c85 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model-permutation2-solution000032.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting p be permutation((E0, E4, E6)) diff --git a/tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model-permutation2-solution000033.solution b/tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model-permutation2-solution000033.solution new file mode 100644 index 0000000000..c7ed58b1d3 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model-permutation2-solution000033.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting p be permutation((E0, E5, E1)) diff --git a/tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model-permutation2-solution000034.solution b/tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model-permutation2-solution000034.solution new file mode 100644 index 0000000000..23d73d25a7 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model-permutation2-solution000034.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting p be permutation((E0, E5, E2)) diff --git a/tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model-permutation2-solution000035.solution b/tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model-permutation2-solution000035.solution new file mode 100644 index 0000000000..8c377d4b1b --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model-permutation2-solution000035.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting p be permutation((E0, E5, E4)) diff --git a/tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model-permutation2-solution000036.solution b/tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model-permutation2-solution000036.solution new file mode 100644 index 0000000000..721a8c38a8 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model-permutation2-solution000036.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting p be permutation((E0, E5, E6)) diff --git a/tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model-permutation2-solution000037.solution b/tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model-permutation2-solution000037.solution new file mode 100644 index 0000000000..5d00ffd7e2 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model-permutation2-solution000037.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting p be permutation((E0, E6, E1)) diff --git a/tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model-permutation2-solution000038.solution b/tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model-permutation2-solution000038.solution new file mode 100644 index 0000000000..a66c134769 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model-permutation2-solution000038.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting p be permutation((E0, E6, E2)) diff --git a/tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model-permutation2-solution000039.solution b/tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model-permutation2-solution000039.solution new file mode 100644 index 0000000000..98ce364b90 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model-permutation2-solution000039.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting p be permutation((E0, E6, E4)) diff --git a/tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model-permutation2-solution000040.solution b/tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model-permutation2-solution000040.solution new file mode 100644 index 0000000000..c9cd9c7cf9 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model-permutation2-solution000040.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting p be permutation((E0, E6, E5)) diff --git a/tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model-permutation2.eprime-param b/tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model-permutation2.eprime-param new file mode 100644 index 0000000000..bfaab18ca2 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model-permutation2.eprime-param @@ -0,0 +1,4 @@ +language ESSENCE' 1.0 + +letting j be 4 +letting i be 4 diff --git a/tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model.eprime b/tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model.eprime new file mode 100644 index 0000000000..63c21511a2 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/expected/model.eprime @@ -0,0 +1,17 @@ +language ESSENCE' 1.0 + +given i: int(1..7) +find p_PermutationAsFunction_PermutationFunction_Function1D: matrix indexed by [int(1..7)] of int(1..7) +given j: int(1..7) +branching on [p_PermutationAsFunction_PermutationFunction_Function1D] +such that + j = + [i, catchUndef(p_PermutationAsFunction_PermutationFunction_Function1D[i], 0); int(1..2)] + [toInt(or([q6 = i | q6 : int(1..7)])) + 1], + sum([toInt(q13 != p_PermutationAsFunction_PermutationFunction_Function1D[q13]) * + catchUndef(toInt(q13 != p_PermutationAsFunction_PermutationFunction_Function1D[q13]), 0) + | q13 : int(1..7)]) + = 3, + allDiff(p_PermutationAsFunction_PermutationFunction_Function1D), + and([or([p_PermutationAsFunction_PermutationFunction_Function1D[q3] = q2 | q3 : int(1..7)]) | q2 : int(1..7)]) + diff --git a/tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/permutation.essence b/tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/permutation.essence new file mode 100644 index 0000000000..04775d022f --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/permutation.essence @@ -0,0 +1,14 @@ +letting n be new type enum {E0,E1,E2,E3,E4,E5,E6} + +given i : n + +find p : permutation of n + +given j : n + +such that + j = image(p, i) /\ sum([toInt(l!=r)|(l,r)<-p]) = 3 + + + + diff --git a/tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/permutation.param b/tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/permutation.param new file mode 100644 index 0000000000..4298bddeda --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/permutation.param @@ -0,0 +1,2 @@ +letting i be E4 +letting j be E3 diff --git a/tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/permutation2.param b/tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/permutation2.param new file mode 100644 index 0000000000..ad96fe5ec5 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/enum/0005_find_permutation_given_enums/permutation2.param @@ -0,0 +1,2 @@ +letting i be E3 +letting j be E3 diff --git a/tests/exhaustive/basic/perms/04_image/enum/0006_letting_permutation_given_enum/expected/model-permutation-solution000001.solution b/tests/exhaustive/basic/perms/04_image/enum/0006_letting_permutation_given_enum/expected/model-permutation-solution000001.solution new file mode 100644 index 0000000000..23c353363e --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/enum/0006_letting_permutation_given_enum/expected/model-permutation-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting j be E3 diff --git a/tests/exhaustive/basic/perms/04_image/enum/0006_letting_permutation_given_enum/expected/model-permutation.eprime-param b/tests/exhaustive/basic/perms/04_image/enum/0006_letting_permutation_given_enum/expected/model-permutation.eprime-param new file mode 100644 index 0000000000..2ff3de0f01 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/enum/0006_letting_permutation_given_enum/expected/model-permutation.eprime-param @@ -0,0 +1,3 @@ +language ESSENCE' 1.0 + +letting i be 2 diff --git a/tests/exhaustive/basic/perms/04_image/enum/0006_letting_permutation_given_enum/expected/model-permutation2-solution000001.solution b/tests/exhaustive/basic/perms/04_image/enum/0006_letting_permutation_given_enum/expected/model-permutation2-solution000001.solution new file mode 100644 index 0000000000..818b6919ed --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/enum/0006_letting_permutation_given_enum/expected/model-permutation2-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting j be E6 diff --git a/tests/exhaustive/basic/perms/04_image/enum/0006_letting_permutation_given_enum/expected/model-permutation2.eprime-param b/tests/exhaustive/basic/perms/04_image/enum/0006_letting_permutation_given_enum/expected/model-permutation2.eprime-param new file mode 100644 index 0000000000..0309e1995f --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/enum/0006_letting_permutation_given_enum/expected/model-permutation2.eprime-param @@ -0,0 +1,3 @@ +language ESSENCE' 1.0 + +letting i be 7 diff --git a/tests/exhaustive/basic/perms/04_image/enum/0006_letting_permutation_given_enum/expected/model.eprime b/tests/exhaustive/basic/perms/04_image/enum/0006_letting_permutation_given_enum/expected/model.eprime new file mode 100644 index 0000000000..2518317ee9 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/enum/0006_letting_permutation_given_enum/expected/model.eprime @@ -0,0 +1,7 @@ +language ESSENCE' 1.0 + +given i: int(1..7) +find j: int(1..7) +branching on [j] +such that j = [i, 4, 5, 2; int(0..3)][sum([toInt(2 = i), toInt(4 = i) * 2, toInt(5 = i) * 3; int(1..3)])] + diff --git a/tests/exhaustive/basic/perms/04_image/enum/0006_letting_permutation_given_enum/permutation.essence b/tests/exhaustive/basic/perms/04_image/enum/0006_letting_permutation_given_enum/permutation.essence new file mode 100644 index 0000000000..b6f45bdb6d --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/enum/0006_letting_permutation_given_enum/permutation.essence @@ -0,0 +1,12 @@ +letting n be new type enum {E0,E1,E2,E3,E4,E5,E6} +given i : n +letting p be permutation((E1,E3,E4)) + + +find j : n + +such that j = image(p, i) + + + + diff --git a/tests/exhaustive/basic/perms/04_image/enum/0006_letting_permutation_given_enum/permutation.param b/tests/exhaustive/basic/perms/04_image/enum/0006_letting_permutation_given_enum/permutation.param new file mode 100644 index 0000000000..78d957a607 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/enum/0006_letting_permutation_given_enum/permutation.param @@ -0,0 +1 @@ +letting i be E1 diff --git a/tests/exhaustive/basic/perms/04_image/enum/0006_letting_permutation_given_enum/permutation2.param b/tests/exhaustive/basic/perms/04_image/enum/0006_letting_permutation_given_enum/permutation2.param new file mode 100644 index 0000000000..4a531ef986 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/enum/0006_letting_permutation_given_enum/permutation2.param @@ -0,0 +1 @@ +letting i be E6 diff --git a/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000001.solution b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000001.solution new file mode 100644 index 0000000000..e4265ec87f --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000001.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting i be E0 +letting j be E0 +letting p be permutation((E2, E3, E4)) diff --git a/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000002.solution b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000002.solution new file mode 100644 index 0000000000..bebf9ece9c --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000002.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting i be E0 +letting j be E0 +letting p be permutation((E2, E4, E3)) diff --git a/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000003.solution b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000003.solution new file mode 100644 index 0000000000..c2a4cbf862 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000003.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting i be E0 +letting j be E0 +letting p be permutation((E1, E2, E3)) diff --git a/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000004.solution b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000004.solution new file mode 100644 index 0000000000..e93ab19efb --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000004.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting i be E0 +letting j be E0 +letting p be permutation((E1, E2, E4)) diff --git a/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000005.solution b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000005.solution new file mode 100644 index 0000000000..9e056eba80 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000005.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting i be E0 +letting j be E0 +letting p be permutation((E1, E3, E2)) diff --git a/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000006.solution b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000006.solution new file mode 100644 index 0000000000..5ca7dbd854 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000006.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting i be E0 +letting j be E0 +letting p be permutation((E1, E3, E4)) diff --git a/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000007.solution b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000007.solution new file mode 100644 index 0000000000..57ebb61030 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000007.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting i be E0 +letting j be E0 +letting p be permutation((E1, E4, E2)) diff --git a/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000008.solution b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000008.solution new file mode 100644 index 0000000000..d3e6e799f3 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000008.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting i be E0 +letting j be E0 +letting p be permutation((E1, E4, E3)) diff --git a/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000009.solution b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000009.solution new file mode 100644 index 0000000000..41ba4db18a --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000009.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting i be E0 +letting j be E1 +letting p be permutation((E0, E1, E2)) diff --git a/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000010.solution b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000010.solution new file mode 100644 index 0000000000..84225db8e2 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000010.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting i be E0 +letting j be E1 +letting p be permutation((E0, E1, E3)) diff --git a/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000011.solution b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000011.solution new file mode 100644 index 0000000000..89068c8072 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000011.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting i be E0 +letting j be E1 +letting p be permutation((E0, E1, E4)) diff --git a/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000012.solution b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000012.solution new file mode 100644 index 0000000000..bf2e0df702 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000012.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting i be E0 +letting j be E2 +letting p be permutation((E0, E2, E1)) diff --git a/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000013.solution b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000013.solution new file mode 100644 index 0000000000..bee22346b4 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000013.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting i be E0 +letting j be E2 +letting p be permutation((E0, E2, E3)) diff --git a/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000014.solution b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000014.solution new file mode 100644 index 0000000000..70111cd0c1 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000014.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting i be E0 +letting j be E2 +letting p be permutation((E0, E2, E4)) diff --git a/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000015.solution b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000015.solution new file mode 100644 index 0000000000..b31b59f85b --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000015.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting i be E0 +letting j be E3 +letting p be permutation((E0, E3, E1)) diff --git a/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000016.solution b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000016.solution new file mode 100644 index 0000000000..9186a31ad4 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000016.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting i be E0 +letting j be E3 +letting p be permutation((E0, E3, E2)) diff --git a/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000017.solution b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000017.solution new file mode 100644 index 0000000000..b2d78ba27c --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000017.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting i be E0 +letting j be E3 +letting p be permutation((E0, E3, E4)) diff --git a/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000018.solution b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000018.solution new file mode 100644 index 0000000000..5c23e64251 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000018.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting i be E0 +letting j be E4 +letting p be permutation((E0, E4, E1)) diff --git a/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000019.solution b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000019.solution new file mode 100644 index 0000000000..755a43b754 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000019.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting i be E0 +letting j be E4 +letting p be permutation((E0, E4, E2)) diff --git a/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000020.solution b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000020.solution new file mode 100644 index 0000000000..14e97e301a --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000020.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting i be E0 +letting j be E4 +letting p be permutation((E0, E4, E3)) diff --git a/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000021.solution b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000021.solution new file mode 100644 index 0000000000..abf8f74cc2 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000021.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting i be E1 +letting j be E1 +letting p be permutation((E2, E3, E4)) diff --git a/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000022.solution b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000022.solution new file mode 100644 index 0000000000..4685adb99a --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000022.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting i be E1 +letting j be E1 +letting p be permutation((E2, E4, E3)) diff --git a/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000023.solution b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000023.solution new file mode 100644 index 0000000000..e41ca44ab8 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000023.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting i be E1 +letting j be E2 +letting p be permutation((E1, E2, E3)) diff --git a/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000024.solution b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000024.solution new file mode 100644 index 0000000000..9462c3d143 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000024.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting i be E1 +letting j be E2 +letting p be permutation((E1, E2, E4)) diff --git a/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000025.solution b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000025.solution new file mode 100644 index 0000000000..b058d434dc --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000025.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting i be E1 +letting j be E3 +letting p be permutation((E1, E3, E2)) diff --git a/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000026.solution b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000026.solution new file mode 100644 index 0000000000..34bfc36daa --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000026.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting i be E1 +letting j be E3 +letting p be permutation((E1, E3, E4)) diff --git a/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000027.solution b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000027.solution new file mode 100644 index 0000000000..8b6bc65afd --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000027.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting i be E1 +letting j be E4 +letting p be permutation((E1, E4, E2)) diff --git a/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000028.solution b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000028.solution new file mode 100644 index 0000000000..47577004c2 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000028.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting i be E1 +letting j be E4 +letting p be permutation((E1, E4, E3)) diff --git a/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000029.solution b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000029.solution new file mode 100644 index 0000000000..85a6253c01 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000029.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting i be E1 +letting j be E2 +letting p be permutation((E0, E1, E2)) diff --git a/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000030.solution b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000030.solution new file mode 100644 index 0000000000..6179c0ff68 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000030.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting i be E1 +letting j be E3 +letting p be permutation((E0, E1, E3)) diff --git a/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000031.solution b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000031.solution new file mode 100644 index 0000000000..7303f2a178 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000031.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting i be E1 +letting j be E4 +letting p be permutation((E0, E1, E4)) diff --git a/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000032.solution b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000032.solution new file mode 100644 index 0000000000..cd0896c790 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000032.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting i be E1 +letting j be E0 +letting p be permutation((E0, E2, E1)) diff --git a/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000033.solution b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000033.solution new file mode 100644 index 0000000000..3101d42636 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000033.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting i be E1 +letting j be E1 +letting p be permutation((E0, E2, E3)) diff --git a/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000034.solution b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000034.solution new file mode 100644 index 0000000000..e1ab0c1f0a --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000034.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting i be E1 +letting j be E1 +letting p be permutation((E0, E2, E4)) diff --git a/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000035.solution b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000035.solution new file mode 100644 index 0000000000..0f67e1ca0e --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000035.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting i be E1 +letting j be E0 +letting p be permutation((E0, E3, E1)) diff --git a/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000036.solution b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000036.solution new file mode 100644 index 0000000000..c4e7ea61ab --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000036.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting i be E1 +letting j be E1 +letting p be permutation((E0, E3, E2)) diff --git a/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000037.solution b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000037.solution new file mode 100644 index 0000000000..e0cadd8966 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000037.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting i be E1 +letting j be E1 +letting p be permutation((E0, E3, E4)) diff --git a/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000038.solution b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000038.solution new file mode 100644 index 0000000000..6ada7a7917 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000038.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting i be E1 +letting j be E0 +letting p be permutation((E0, E4, E1)) diff --git a/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000039.solution b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000039.solution new file mode 100644 index 0000000000..134eb91a3a --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000039.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting i be E1 +letting j be E1 +letting p be permutation((E0, E4, E2)) diff --git a/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000040.solution b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000040.solution new file mode 100644 index 0000000000..c744d8ce7f --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000040.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting i be E1 +letting j be E1 +letting p be permutation((E0, E4, E3)) diff --git a/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000041.solution b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000041.solution new file mode 100644 index 0000000000..92ef6730bb --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000041.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting i be E2 +letting j be E3 +letting p be permutation((E2, E3, E4)) diff --git a/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000042.solution b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000042.solution new file mode 100644 index 0000000000..60168854b1 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000042.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting i be E2 +letting j be E4 +letting p be permutation((E2, E4, E3)) diff --git a/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000043.solution b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000043.solution new file mode 100644 index 0000000000..1d8151e621 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000043.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting i be E2 +letting j be E3 +letting p be permutation((E1, E2, E3)) diff --git a/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000044.solution b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000044.solution new file mode 100644 index 0000000000..733d1bac65 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000044.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting i be E2 +letting j be E4 +letting p be permutation((E1, E2, E4)) diff --git a/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000045.solution b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000045.solution new file mode 100644 index 0000000000..b9a77828f4 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000045.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting i be E2 +letting j be E1 +letting p be permutation((E1, E3, E2)) diff --git a/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000046.solution b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000046.solution new file mode 100644 index 0000000000..6ebc6f7044 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000046.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting i be E2 +letting j be E2 +letting p be permutation((E1, E3, E4)) diff --git a/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000047.solution b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000047.solution new file mode 100644 index 0000000000..c13ccbf499 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000047.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting i be E2 +letting j be E1 +letting p be permutation((E1, E4, E2)) diff --git a/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000048.solution b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000048.solution new file mode 100644 index 0000000000..018175b8bb --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000048.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting i be E2 +letting j be E2 +letting p be permutation((E1, E4, E3)) diff --git a/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000049.solution b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000049.solution new file mode 100644 index 0000000000..db43b7799f --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000049.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting i be E2 +letting j be E0 +letting p be permutation((E0, E1, E2)) diff --git a/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000050.solution b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000050.solution new file mode 100644 index 0000000000..90d98a4b55 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000050.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting i be E2 +letting j be E2 +letting p be permutation((E0, E1, E3)) diff --git a/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000051.solution b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000051.solution new file mode 100644 index 0000000000..b7ec7c94c3 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000051.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting i be E2 +letting j be E2 +letting p be permutation((E0, E1, E4)) diff --git a/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000052.solution b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000052.solution new file mode 100644 index 0000000000..8d2fb87a12 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000052.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting i be E2 +letting j be E1 +letting p be permutation((E0, E2, E1)) diff --git a/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000053.solution b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000053.solution new file mode 100644 index 0000000000..02ffdba8d9 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000053.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting i be E2 +letting j be E3 +letting p be permutation((E0, E2, E3)) diff --git a/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000054.solution b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000054.solution new file mode 100644 index 0000000000..5e1c28ef28 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000054.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting i be E2 +letting j be E4 +letting p be permutation((E0, E2, E4)) diff --git a/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000055.solution b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000055.solution new file mode 100644 index 0000000000..f3ed237eb0 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000055.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting i be E2 +letting j be E2 +letting p be permutation((E0, E3, E1)) diff --git a/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000056.solution b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000056.solution new file mode 100644 index 0000000000..08eceabab9 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000056.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting i be E2 +letting j be E0 +letting p be permutation((E0, E3, E2)) diff --git a/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000057.solution b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000057.solution new file mode 100644 index 0000000000..5fd5b2fcc0 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000057.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting i be E2 +letting j be E2 +letting p be permutation((E0, E3, E4)) diff --git a/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000058.solution b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000058.solution new file mode 100644 index 0000000000..591fdd04f5 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000058.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting i be E2 +letting j be E2 +letting p be permutation((E0, E4, E1)) diff --git a/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000059.solution b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000059.solution new file mode 100644 index 0000000000..6389a68277 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000059.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting i be E2 +letting j be E0 +letting p be permutation((E0, E4, E2)) diff --git a/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000060.solution b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000060.solution new file mode 100644 index 0000000000..78d701bbae --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000060.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting i be E2 +letting j be E2 +letting p be permutation((E0, E4, E3)) diff --git a/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000061.solution b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000061.solution new file mode 100644 index 0000000000..c46f8cd271 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000061.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting i be E3 +letting j be E4 +letting p be permutation((E2, E3, E4)) diff --git a/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000062.solution b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000062.solution new file mode 100644 index 0000000000..dcc8b0a2e1 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000062.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting i be E3 +letting j be E2 +letting p be permutation((E2, E4, E3)) diff --git a/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000063.solution b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000063.solution new file mode 100644 index 0000000000..fab4241c26 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000063.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting i be E3 +letting j be E1 +letting p be permutation((E1, E2, E3)) diff --git a/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000064.solution b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000064.solution new file mode 100644 index 0000000000..aab27bee33 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000064.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting i be E3 +letting j be E3 +letting p be permutation((E1, E2, E4)) diff --git a/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000065.solution b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000065.solution new file mode 100644 index 0000000000..f5d9ff42fe --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000065.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting i be E3 +letting j be E2 +letting p be permutation((E1, E3, E2)) diff --git a/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000066.solution b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000066.solution new file mode 100644 index 0000000000..e63ebff77e --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000066.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting i be E3 +letting j be E4 +letting p be permutation((E1, E3, E4)) diff --git a/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000067.solution b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000067.solution new file mode 100644 index 0000000000..7ac35967b9 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000067.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting i be E3 +letting j be E3 +letting p be permutation((E1, E4, E2)) diff --git a/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000068.solution b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000068.solution new file mode 100644 index 0000000000..29be661bc0 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000068.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting i be E3 +letting j be E1 +letting p be permutation((E1, E4, E3)) diff --git a/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000069.solution b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000069.solution new file mode 100644 index 0000000000..48f3c38f29 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000069.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting i be E3 +letting j be E3 +letting p be permutation((E0, E1, E2)) diff --git a/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000070.solution b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000070.solution new file mode 100644 index 0000000000..c3d0aebd0d --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000070.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting i be E3 +letting j be E0 +letting p be permutation((E0, E1, E3)) diff --git a/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000071.solution b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000071.solution new file mode 100644 index 0000000000..6c06e36e04 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000071.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting i be E3 +letting j be E3 +letting p be permutation((E0, E1, E4)) diff --git a/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000072.solution b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000072.solution new file mode 100644 index 0000000000..8838f9806a --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000072.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting i be E3 +letting j be E3 +letting p be permutation((E0, E2, E1)) diff --git a/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000073.solution b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000073.solution new file mode 100644 index 0000000000..cba3c11d20 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000073.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting i be E3 +letting j be E0 +letting p be permutation((E0, E2, E3)) diff --git a/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000074.solution b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000074.solution new file mode 100644 index 0000000000..5730b991de --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000074.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting i be E3 +letting j be E3 +letting p be permutation((E0, E2, E4)) diff --git a/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000075.solution b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000075.solution new file mode 100644 index 0000000000..45bb479392 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000075.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting i be E3 +letting j be E1 +letting p be permutation((E0, E3, E1)) diff --git a/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000076.solution b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000076.solution new file mode 100644 index 0000000000..baa5ee3879 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000076.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting i be E3 +letting j be E2 +letting p be permutation((E0, E3, E2)) diff --git a/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000077.solution b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000077.solution new file mode 100644 index 0000000000..42e10e580d --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000077.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting i be E3 +letting j be E4 +letting p be permutation((E0, E3, E4)) diff --git a/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000078.solution b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000078.solution new file mode 100644 index 0000000000..7aeed4a6da --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000078.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting i be E3 +letting j be E3 +letting p be permutation((E0, E4, E1)) diff --git a/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000079.solution b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000079.solution new file mode 100644 index 0000000000..26424a9f72 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000079.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting i be E3 +letting j be E3 +letting p be permutation((E0, E4, E2)) diff --git a/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000080.solution b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000080.solution new file mode 100644 index 0000000000..d1efa56314 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000080.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting i be E3 +letting j be E0 +letting p be permutation((E0, E4, E3)) diff --git a/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000081.solution b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000081.solution new file mode 100644 index 0000000000..4984244444 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000081.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting i be E4 +letting j be E2 +letting p be permutation((E2, E3, E4)) diff --git a/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000082.solution b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000082.solution new file mode 100644 index 0000000000..9b7a152e79 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000082.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting i be E4 +letting j be E3 +letting p be permutation((E2, E4, E3)) diff --git a/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000083.solution b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000083.solution new file mode 100644 index 0000000000..c329723886 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000083.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting i be E4 +letting j be E4 +letting p be permutation((E1, E2, E3)) diff --git a/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000084.solution b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000084.solution new file mode 100644 index 0000000000..c616dd3069 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000084.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting i be E4 +letting j be E1 +letting p be permutation((E1, E2, E4)) diff --git a/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000085.solution b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000085.solution new file mode 100644 index 0000000000..0e40faf1fc --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000085.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting i be E4 +letting j be E4 +letting p be permutation((E1, E3, E2)) diff --git a/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000086.solution b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000086.solution new file mode 100644 index 0000000000..3f2adc3115 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000086.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting i be E4 +letting j be E1 +letting p be permutation((E1, E3, E4)) diff --git a/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000087.solution b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000087.solution new file mode 100644 index 0000000000..8d4ed8a469 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000087.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting i be E4 +letting j be E2 +letting p be permutation((E1, E4, E2)) diff --git a/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000088.solution b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000088.solution new file mode 100644 index 0000000000..6dd49b562c --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000088.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting i be E4 +letting j be E3 +letting p be permutation((E1, E4, E3)) diff --git a/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000089.solution b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000089.solution new file mode 100644 index 0000000000..58cd8b0155 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000089.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting i be E4 +letting j be E4 +letting p be permutation((E0, E1, E2)) diff --git a/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000090.solution b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000090.solution new file mode 100644 index 0000000000..1407496a43 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000090.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting i be E4 +letting j be E4 +letting p be permutation((E0, E1, E3)) diff --git a/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000091.solution b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000091.solution new file mode 100644 index 0000000000..c87499dc9b --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000091.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting i be E4 +letting j be E0 +letting p be permutation((E0, E1, E4)) diff --git a/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000092.solution b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000092.solution new file mode 100644 index 0000000000..ad589d574e --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000092.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting i be E4 +letting j be E4 +letting p be permutation((E0, E2, E1)) diff --git a/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000093.solution b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000093.solution new file mode 100644 index 0000000000..6839a3bdba --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000093.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting i be E4 +letting j be E4 +letting p be permutation((E0, E2, E3)) diff --git a/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000094.solution b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000094.solution new file mode 100644 index 0000000000..07c1365b9f --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000094.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting i be E4 +letting j be E0 +letting p be permutation((E0, E2, E4)) diff --git a/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000095.solution b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000095.solution new file mode 100644 index 0000000000..33bdf5ab5d --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000095.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting i be E4 +letting j be E4 +letting p be permutation((E0, E3, E1)) diff --git a/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000096.solution b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000096.solution new file mode 100644 index 0000000000..eb4e6e19da --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000096.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting i be E4 +letting j be E4 +letting p be permutation((E0, E3, E2)) diff --git a/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000097.solution b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000097.solution new file mode 100644 index 0000000000..5bf6f994ec --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000097.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting i be E4 +letting j be E0 +letting p be permutation((E0, E3, E4)) diff --git a/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000098.solution b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000098.solution new file mode 100644 index 0000000000..b983f84174 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000098.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting i be E4 +letting j be E1 +letting p be permutation((E0, E4, E1)) diff --git a/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000099.solution b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000099.solution new file mode 100644 index 0000000000..f3b1b3c394 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000099.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting i be E4 +letting j be E2 +letting p be permutation((E0, E4, E2)) diff --git a/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000100.solution b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000100.solution new file mode 100644 index 0000000000..2ba6312faa --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model-solution000100.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting i be E4 +letting j be E3 +letting p be permutation((E0, E4, E3)) diff --git a/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model.eprime b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model.eprime new file mode 100644 index 0000000000..381cf3354b --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/expected/model.eprime @@ -0,0 +1,17 @@ +language ESSENCE' 1.0 + +find i: int(1..5) +find p_PermutationAsFunction_PermutationFunction_Function1D: matrix indexed by [int(1..5)] of int(1..5) +find j: int(1..5) +branching on [i, p_PermutationAsFunction_PermutationFunction_Function1D, j] +such that + j = + [i, catchUndef(p_PermutationAsFunction_PermutationFunction_Function1D[i], 0); int(1..2)] + [toInt(or([q6 = i | q6 : int(1..5)])) + 1], + sum([toInt(q13 != p_PermutationAsFunction_PermutationFunction_Function1D[q13]) * + catchUndef(toInt(q13 != p_PermutationAsFunction_PermutationFunction_Function1D[q13]), 0) + | q13 : int(1..5)]) + = 3, + allDiff(p_PermutationAsFunction_PermutationFunction_Function1D), + and([or([p_PermutationAsFunction_PermutationFunction_Function1D[q3] = q2 | q3 : int(1..5)]) | q2 : int(1..5)]) + diff --git a/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/permutation.essence b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/permutation.essence new file mode 100644 index 0000000000..530076abc4 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/enum/0007_find_permutation_find_enums/permutation.essence @@ -0,0 +1,14 @@ +letting n be new type enum {E0,E1,E2,E3,E4} + +find i : n + +find p : permutation of n + +find j : n + +such that + j = image(p, i) /\ sum([toInt(l!=r)|(l,r)<-p]) = 3 + + + + diff --git a/tests/exhaustive/basic/perms/04_image/int/0001_given_permutation_given_int/expected/model-permutation-solution000001.solution b/tests/exhaustive/basic/perms/04_image/int/0001_given_permutation_given_int/expected/model-permutation-solution000001.solution new file mode 100644 index 0000000000..215f7d0a92 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/int/0001_given_permutation_given_int/expected/model-permutation-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting j be 3 diff --git a/tests/exhaustive/basic/perms/04_image/int/0001_given_permutation_given_int/expected/model-permutation.eprime-param b/tests/exhaustive/basic/perms/04_image/int/0001_given_permutation_given_int/expected/model-permutation.eprime-param new file mode 100644 index 0000000000..7ec57d0c4c --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/int/0001_given_permutation_given_int/expected/model-permutation.eprime-param @@ -0,0 +1,4 @@ +language ESSENCE' 1.0 + +letting p_PermutationAsFunction_PermutationFunction_Function1D be [3, 2, 4, 1; int(1..4)] +letting i be 1 diff --git a/tests/exhaustive/basic/perms/04_image/int/0001_given_permutation_given_int/expected/model-permutation2-solution000001.solution b/tests/exhaustive/basic/perms/04_image/int/0001_given_permutation_given_int/expected/model-permutation2-solution000001.solution new file mode 100644 index 0000000000..3585952da3 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/int/0001_given_permutation_given_int/expected/model-permutation2-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting j be 6 diff --git a/tests/exhaustive/basic/perms/04_image/int/0001_given_permutation_given_int/expected/model-permutation2.eprime-param b/tests/exhaustive/basic/perms/04_image/int/0001_given_permutation_given_int/expected/model-permutation2.eprime-param new file mode 100644 index 0000000000..dbf2ea0e96 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/int/0001_given_permutation_given_int/expected/model-permutation2.eprime-param @@ -0,0 +1,4 @@ +language ESSENCE' 1.0 + +letting p_PermutationAsFunction_PermutationFunction_Function1D be [3, 2, 4, 1; int(1..4)] +letting i be 6 diff --git a/tests/exhaustive/basic/perms/04_image/int/0001_given_permutation_given_int/expected/model.eprime b/tests/exhaustive/basic/perms/04_image/int/0001_given_permutation_given_int/expected/model.eprime new file mode 100644 index 0000000000..c91ed7f053 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/int/0001_given_permutation_given_int/expected/model.eprime @@ -0,0 +1,11 @@ +language ESSENCE' 1.0 + +given i: int(0..10) +given p_PermutationAsFunction_PermutationFunction_Function1D: matrix indexed by [int(1..4)] of int(1..4) +find j: int(0..10) +branching on [j] +such that + j = + [i, catchUndef(p_PermutationAsFunction_PermutationFunction_Function1D[i], 0); int(1..2)] + [toInt(or([q2 = i | q2 : int(1..4)])) + 1] + diff --git a/tests/exhaustive/basic/perms/04_image/int/0001_given_permutation_given_int/permutation.essence b/tests/exhaustive/basic/perms/04_image/int/0001_given_permutation_given_int/permutation.essence new file mode 100644 index 0000000000..38e2624e94 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/int/0001_given_permutation_given_int/permutation.essence @@ -0,0 +1,11 @@ +given i : int(0..10) + +given p : permutation of int(1..4) + +find j : int(0..10) + +such that j = image(p, i) + + + + diff --git a/tests/exhaustive/basic/perms/04_image/int/0001_given_permutation_given_int/permutation.param b/tests/exhaustive/basic/perms/04_image/int/0001_given_permutation_given_int/permutation.param new file mode 100644 index 0000000000..600438bb4b --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/int/0001_given_permutation_given_int/permutation.param @@ -0,0 +1,2 @@ +letting p be permutation((1,3,4)) +letting i be 1 diff --git a/tests/exhaustive/basic/perms/04_image/int/0001_given_permutation_given_int/permutation2.param b/tests/exhaustive/basic/perms/04_image/int/0001_given_permutation_given_int/permutation2.param new file mode 100644 index 0000000000..96f2fdd075 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/int/0001_given_permutation_given_int/permutation2.param @@ -0,0 +1,2 @@ +letting p be permutation((1,3,4)) +letting i be 6 diff --git a/tests/exhaustive/basic/perms/04_image/int/0002_given_permutation_letting_int/expected/model-permutation-solution000001.solution b/tests/exhaustive/basic/perms/04_image/int/0002_given_permutation_letting_int/expected/model-permutation-solution000001.solution new file mode 100644 index 0000000000..215f7d0a92 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/int/0002_given_permutation_letting_int/expected/model-permutation-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting j be 3 diff --git a/tests/exhaustive/basic/perms/04_image/int/0002_given_permutation_letting_int/expected/model-permutation.eprime-param b/tests/exhaustive/basic/perms/04_image/int/0002_given_permutation_letting_int/expected/model-permutation.eprime-param new file mode 100644 index 0000000000..c2bddee0e8 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/int/0002_given_permutation_letting_int/expected/model-permutation.eprime-param @@ -0,0 +1,3 @@ +language ESSENCE' 1.0 + +letting p_PermutationAsFunction_PermutationFunction_Function1D be [3, 2, 4, 1; int(1..4)] diff --git a/tests/exhaustive/basic/perms/04_image/int/0002_given_permutation_letting_int/expected/model.eprime b/tests/exhaustive/basic/perms/04_image/int/0002_given_permutation_letting_int/expected/model.eprime new file mode 100644 index 0000000000..406aaecebe --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/int/0002_given_permutation_letting_int/expected/model.eprime @@ -0,0 +1,7 @@ +language ESSENCE' 1.0 + +given p_PermutationAsFunction_PermutationFunction_Function1D: matrix indexed by [int(1..4)] of int(1..4) +find j: int(0..10) +branching on [j] +such that j = catchUndef(p_PermutationAsFunction_PermutationFunction_Function1D[1], 0) + diff --git a/tests/exhaustive/basic/perms/04_image/int/0002_given_permutation_letting_int/permutation.essence b/tests/exhaustive/basic/perms/04_image/int/0002_given_permutation_letting_int/permutation.essence new file mode 100644 index 0000000000..8ac5f78cc5 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/int/0002_given_permutation_letting_int/permutation.essence @@ -0,0 +1,11 @@ +letting i be 1 + +given p : permutation of int(1..4) + +find j : int(0..10) + +such that j = image(p, i) + + + + diff --git a/tests/exhaustive/basic/perms/04_image/int/0002_given_permutation_letting_int/permutation.param b/tests/exhaustive/basic/perms/04_image/int/0002_given_permutation_letting_int/permutation.param new file mode 100644 index 0000000000..8a8c516801 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/int/0002_given_permutation_letting_int/permutation.param @@ -0,0 +1 @@ +letting p be permutation((1,3,4)) diff --git a/tests/exhaustive/basic/perms/04_image/int/0003_given_permutation_letting_int/expected/model-permutation-solution000001.solution b/tests/exhaustive/basic/perms/04_image/int/0003_given_permutation_letting_int/expected/model-permutation-solution000001.solution new file mode 100644 index 0000000000..3585952da3 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/int/0003_given_permutation_letting_int/expected/model-permutation-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting j be 6 diff --git a/tests/exhaustive/basic/perms/04_image/int/0003_given_permutation_letting_int/expected/model-permutation.eprime-param b/tests/exhaustive/basic/perms/04_image/int/0003_given_permutation_letting_int/expected/model-permutation.eprime-param new file mode 100644 index 0000000000..c2bddee0e8 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/int/0003_given_permutation_letting_int/expected/model-permutation.eprime-param @@ -0,0 +1,3 @@ +language ESSENCE' 1.0 + +letting p_PermutationAsFunction_PermutationFunction_Function1D be [3, 2, 4, 1; int(1..4)] diff --git a/tests/exhaustive/basic/perms/04_image/int/0003_given_permutation_letting_int/expected/model.eprime b/tests/exhaustive/basic/perms/04_image/int/0003_given_permutation_letting_int/expected/model.eprime new file mode 100644 index 0000000000..b4001266d7 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/int/0003_given_permutation_letting_int/expected/model.eprime @@ -0,0 +1,7 @@ +language ESSENCE' 1.0 + +given p_PermutationAsFunction_PermutationFunction_Function1D: matrix indexed by [int(1..4)] of int(1..4) +find j: int(0..10) +branching on [j] +such that j = 6 + diff --git a/tests/exhaustive/basic/perms/04_image/int/0003_given_permutation_letting_int/permutation.essence b/tests/exhaustive/basic/perms/04_image/int/0003_given_permutation_letting_int/permutation.essence new file mode 100644 index 0000000000..786c6b7c52 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/int/0003_given_permutation_letting_int/permutation.essence @@ -0,0 +1,11 @@ +letting i be 6 + +given p : permutation of int(1..4) + +find j : int(0..10) + +such that j = image(p, i) + + + + diff --git a/tests/exhaustive/basic/perms/04_image/int/0003_given_permutation_letting_int/permutation.param b/tests/exhaustive/basic/perms/04_image/int/0003_given_permutation_letting_int/permutation.param new file mode 100644 index 0000000000..8a8c516801 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/int/0003_given_permutation_letting_int/permutation.param @@ -0,0 +1 @@ +letting p be permutation((1,3,4)) diff --git a/tests/exhaustive/basic/perms/04_image/int/0004_given_permutation_find_int/permutation.essence b/tests/exhaustive/basic/perms/04_image/int/0004_given_permutation_find_int/permutation.essence new file mode 100644 index 0000000000..3b48f881fb --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/int/0004_given_permutation_find_int/permutation.essence @@ -0,0 +1,12 @@ + +given p : permutation of int(1..4) + +given j : int(0..10) + + +find i : int(0..10) +such that j = image(p, i) + + + + diff --git a/tests/exhaustive/basic/perms/04_image/int/0004_given_permutation_find_int/permutation.param b/tests/exhaustive/basic/perms/04_image/int/0004_given_permutation_find_int/permutation.param new file mode 100644 index 0000000000..417c2de221 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/int/0004_given_permutation_find_int/permutation.param @@ -0,0 +1,2 @@ +letting p be permutation((1,3,4)) +letting j be 3 diff --git a/tests/exhaustive/basic/perms/04_image/int/0004_given_permutation_find_int/permutation2.essence b/tests/exhaustive/basic/perms/04_image/int/0004_given_permutation_find_int/permutation2.essence new file mode 100644 index 0000000000..d9758bd4b1 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/int/0004_given_permutation_find_int/permutation2.essence @@ -0,0 +1,2 @@ +letting p be permutation((1,3,4)) +letting j be 6 diff --git a/tests/exhaustive/basic/perms/04_image/int/0005_find_permutation_given_ints/expected/model-permutation-solution000001.solution b/tests/exhaustive/basic/perms/04_image/int/0005_find_permutation_given_ints/expected/model-permutation-solution000001.solution new file mode 100644 index 0000000000..7f3ffab396 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/int/0005_find_permutation_given_ints/expected/model-permutation-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting p be permutation((2, 4, 3)) diff --git a/tests/exhaustive/basic/perms/04_image/int/0005_find_permutation_given_ints/expected/model-permutation-solution000002.solution b/tests/exhaustive/basic/perms/04_image/int/0005_find_permutation_given_ints/expected/model-permutation-solution000002.solution new file mode 100644 index 0000000000..23fcbc89f7 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/int/0005_find_permutation_given_ints/expected/model-permutation-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting p be permutation((1, 4, 3)) diff --git a/tests/exhaustive/basic/perms/04_image/int/0005_find_permutation_given_ints/expected/model-permutation.eprime-param b/tests/exhaustive/basic/perms/04_image/int/0005_find_permutation_given_ints/expected/model-permutation.eprime-param new file mode 100644 index 0000000000..766b0c6f9c --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/int/0005_find_permutation_given_ints/expected/model-permutation.eprime-param @@ -0,0 +1,4 @@ +language ESSENCE' 1.0 + +letting j be 3 +letting i be 4 diff --git a/tests/exhaustive/basic/perms/04_image/int/0005_find_permutation_given_ints/expected/model-permutation2-solution000001.solution b/tests/exhaustive/basic/perms/04_image/int/0005_find_permutation_given_ints/expected/model-permutation2-solution000001.solution new file mode 100644 index 0000000000..3fba79788b --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/int/0005_find_permutation_given_ints/expected/model-permutation2-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting p be permutation((1, 2, 4)) diff --git a/tests/exhaustive/basic/perms/04_image/int/0005_find_permutation_given_ints/expected/model-permutation2-solution000002.solution b/tests/exhaustive/basic/perms/04_image/int/0005_find_permutation_given_ints/expected/model-permutation2-solution000002.solution new file mode 100644 index 0000000000..72a96ad1f9 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/int/0005_find_permutation_given_ints/expected/model-permutation2-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting p be permutation((1, 4, 2)) diff --git a/tests/exhaustive/basic/perms/04_image/int/0005_find_permutation_given_ints/expected/model-permutation2.eprime-param b/tests/exhaustive/basic/perms/04_image/int/0005_find_permutation_given_ints/expected/model-permutation2.eprime-param new file mode 100644 index 0000000000..4cd8b02202 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/int/0005_find_permutation_given_ints/expected/model-permutation2.eprime-param @@ -0,0 +1,4 @@ +language ESSENCE' 1.0 + +letting j be 3 +letting i be 3 diff --git a/tests/exhaustive/basic/perms/04_image/int/0005_find_permutation_given_ints/expected/model.eprime b/tests/exhaustive/basic/perms/04_image/int/0005_find_permutation_given_ints/expected/model.eprime new file mode 100644 index 0000000000..141b7abaef --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/int/0005_find_permutation_given_ints/expected/model.eprime @@ -0,0 +1,17 @@ +language ESSENCE' 1.0 + +given i: int(0..10) +find p_PermutationAsFunction_PermutationFunction_Function1D: matrix indexed by [int(1..4)] of int(1..4) +given j: int(0..10) +branching on [p_PermutationAsFunction_PermutationFunction_Function1D] +such that + j = + [i, catchUndef(p_PermutationAsFunction_PermutationFunction_Function1D[i], 0); int(1..2)] + [toInt(or([q6 = i | q6 : int(1..4)])) + 1], + sum([toInt(q13 != p_PermutationAsFunction_PermutationFunction_Function1D[q13]) * + catchUndef(toInt(q13 != p_PermutationAsFunction_PermutationFunction_Function1D[q13]), 0) + | q13 : int(1..4)]) + = 3, + allDiff(p_PermutationAsFunction_PermutationFunction_Function1D), + and([or([p_PermutationAsFunction_PermutationFunction_Function1D[q3] = q2 | q3 : int(1..4)]) | q2 : int(1..4)]) + diff --git a/tests/exhaustive/basic/perms/04_image/int/0005_find_permutation_given_ints/permutation.essence b/tests/exhaustive/basic/perms/04_image/int/0005_find_permutation_given_ints/permutation.essence new file mode 100644 index 0000000000..fb725c1838 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/int/0005_find_permutation_given_ints/permutation.essence @@ -0,0 +1,12 @@ +given i : int(0..10) + +find p : permutation of int(1..4) + +given j : int(0..10) + +such that + j = image(p, i) /\ sum([toInt(l!=r)|(l,r)<-p])= 3 + + + + diff --git a/tests/exhaustive/basic/perms/04_image/int/0005_find_permutation_given_ints/permutation.param b/tests/exhaustive/basic/perms/04_image/int/0005_find_permutation_given_ints/permutation.param new file mode 100644 index 0000000000..4e680d5b1b --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/int/0005_find_permutation_given_ints/permutation.param @@ -0,0 +1,2 @@ +letting i be 4 +letting j be 3 diff --git a/tests/exhaustive/basic/perms/04_image/int/0005_find_permutation_given_ints/permutation2.param b/tests/exhaustive/basic/perms/04_image/int/0005_find_permutation_given_ints/permutation2.param new file mode 100644 index 0000000000..0ff59e0909 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/int/0005_find_permutation_given_ints/permutation2.param @@ -0,0 +1,2 @@ +letting i be 3 +letting j be 3 diff --git a/tests/exhaustive/basic/perms/04_image/int/0007_find_permutation_find_ints/expected/model-solution000001.solution b/tests/exhaustive/basic/perms/04_image/int/0007_find_permutation_find_ints/expected/model-solution000001.solution new file mode 100644 index 0000000000..0a2c9233c3 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/int/0007_find_permutation_find_ints/expected/model-solution000001.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting i be 2 +letting j be 3 +letting p be permutation((2, 3)) diff --git a/tests/exhaustive/basic/perms/04_image/int/0007_find_permutation_find_ints/expected/model-solution000002.solution b/tests/exhaustive/basic/perms/04_image/int/0007_find_permutation_find_ints/expected/model-solution000002.solution new file mode 100644 index 0000000000..0694bc7cb6 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/int/0007_find_permutation_find_ints/expected/model-solution000002.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting i be 2 +letting j be 3 +letting p be permutation((2, 3, 4)) diff --git a/tests/exhaustive/basic/perms/04_image/int/0007_find_permutation_find_ints/expected/model-solution000003.solution b/tests/exhaustive/basic/perms/04_image/int/0007_find_permutation_find_ints/expected/model-solution000003.solution new file mode 100644 index 0000000000..b730d1b200 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/int/0007_find_permutation_find_ints/expected/model-solution000003.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting i be 2 +letting j be 4 +letting p be permutation((2, 4, 3)) diff --git a/tests/exhaustive/basic/perms/04_image/int/0007_find_permutation_find_ints/expected/model-solution000004.solution b/tests/exhaustive/basic/perms/04_image/int/0007_find_permutation_find_ints/expected/model-solution000004.solution new file mode 100644 index 0000000000..08b51c99ec --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/int/0007_find_permutation_find_ints/expected/model-solution000004.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting i be 2 +letting j be 4 +letting p be permutation((2, 4)) diff --git a/tests/exhaustive/basic/perms/04_image/int/0007_find_permutation_find_ints/expected/model-solution000005.solution b/tests/exhaustive/basic/perms/04_image/int/0007_find_permutation_find_ints/expected/model-solution000005.solution new file mode 100644 index 0000000000..2f2fed0198 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/int/0007_find_permutation_find_ints/expected/model-solution000005.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting i be 2 +letting j be 3 +letting p be permutation((1, 2, 3)) diff --git a/tests/exhaustive/basic/perms/04_image/int/0007_find_permutation_find_ints/expected/model-solution000006.solution b/tests/exhaustive/basic/perms/04_image/int/0007_find_permutation_find_ints/expected/model-solution000006.solution new file mode 100644 index 0000000000..553383dd79 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/int/0007_find_permutation_find_ints/expected/model-solution000006.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting i be 2 +letting j be 3 +letting p be permutation((1, 2, 3, 4)) diff --git a/tests/exhaustive/basic/perms/04_image/int/0007_find_permutation_find_ints/expected/model-solution000007.solution b/tests/exhaustive/basic/perms/04_image/int/0007_find_permutation_find_ints/expected/model-solution000007.solution new file mode 100644 index 0000000000..6476d6cd1d --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/int/0007_find_permutation_find_ints/expected/model-solution000007.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting i be 2 +letting j be 4 +letting p be permutation((1, 2, 4, 3)) diff --git a/tests/exhaustive/basic/perms/04_image/int/0007_find_permutation_find_ints/expected/model-solution000008.solution b/tests/exhaustive/basic/perms/04_image/int/0007_find_permutation_find_ints/expected/model-solution000008.solution new file mode 100644 index 0000000000..b34bd7aa83 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/int/0007_find_permutation_find_ints/expected/model-solution000008.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting i be 2 +letting j be 4 +letting p be permutation((1, 2, 4)) diff --git a/tests/exhaustive/basic/perms/04_image/int/0007_find_permutation_find_ints/expected/model-solution000009.solution b/tests/exhaustive/basic/perms/04_image/int/0007_find_permutation_find_ints/expected/model-solution000009.solution new file mode 100644 index 0000000000..789c8c3a45 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/int/0007_find_permutation_find_ints/expected/model-solution000009.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting i be 2 +letting j be 4 +letting p be permutation((1, 3), (2, 4)) diff --git a/tests/exhaustive/basic/perms/04_image/int/0007_find_permutation_find_ints/expected/model-solution000010.solution b/tests/exhaustive/basic/perms/04_image/int/0007_find_permutation_find_ints/expected/model-solution000010.solution new file mode 100644 index 0000000000..d2ae8c6b5d --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/int/0007_find_permutation_find_ints/expected/model-solution000010.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting i be 2 +letting j be 4 +letting p be permutation((1, 3, 2, 4)) diff --git a/tests/exhaustive/basic/perms/04_image/int/0007_find_permutation_find_ints/expected/model-solution000011.solution b/tests/exhaustive/basic/perms/04_image/int/0007_find_permutation_find_ints/expected/model-solution000011.solution new file mode 100644 index 0000000000..a3c11fe316 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/int/0007_find_permutation_find_ints/expected/model-solution000011.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting i be 2 +letting j be 3 +letting p be permutation((1, 4, 2, 3)) diff --git a/tests/exhaustive/basic/perms/04_image/int/0007_find_permutation_find_ints/expected/model-solution000012.solution b/tests/exhaustive/basic/perms/04_image/int/0007_find_permutation_find_ints/expected/model-solution000012.solution new file mode 100644 index 0000000000..a92768ab5d --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/int/0007_find_permutation_find_ints/expected/model-solution000012.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting i be 2 +letting j be 3 +letting p be permutation((1, 4), (2, 3)) diff --git a/tests/exhaustive/basic/perms/04_image/int/0007_find_permutation_find_ints/expected/model-solution000013.solution b/tests/exhaustive/basic/perms/04_image/int/0007_find_permutation_find_ints/expected/model-solution000013.solution new file mode 100644 index 0000000000..6f1090bd74 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/int/0007_find_permutation_find_ints/expected/model-solution000013.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting i be 3 +letting j be 3 +letting p be permutation() diff --git a/tests/exhaustive/basic/perms/04_image/int/0007_find_permutation_find_ints/expected/model-solution000014.solution b/tests/exhaustive/basic/perms/04_image/int/0007_find_permutation_find_ints/expected/model-solution000014.solution new file mode 100644 index 0000000000..e1966f7dde --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/int/0007_find_permutation_find_ints/expected/model-solution000014.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting i be 3 +letting j be 4 +letting p be permutation((3, 4)) diff --git a/tests/exhaustive/basic/perms/04_image/int/0007_find_permutation_find_ints/expected/model-solution000015.solution b/tests/exhaustive/basic/perms/04_image/int/0007_find_permutation_find_ints/expected/model-solution000015.solution new file mode 100644 index 0000000000..f6dd5d0796 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/int/0007_find_permutation_find_ints/expected/model-solution000015.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting i be 3 +letting j be 4 +letting p be permutation((2, 3, 4)) diff --git a/tests/exhaustive/basic/perms/04_image/int/0007_find_permutation_find_ints/expected/model-solution000016.solution b/tests/exhaustive/basic/perms/04_image/int/0007_find_permutation_find_ints/expected/model-solution000016.solution new file mode 100644 index 0000000000..60ddfbbb88 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/int/0007_find_permutation_find_ints/expected/model-solution000016.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting i be 3 +letting j be 3 +letting p be permutation((2, 4)) diff --git a/tests/exhaustive/basic/perms/04_image/int/0007_find_permutation_find_ints/expected/model-solution000017.solution b/tests/exhaustive/basic/perms/04_image/int/0007_find_permutation_find_ints/expected/model-solution000017.solution new file mode 100644 index 0000000000..f9ad3a2caa --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/int/0007_find_permutation_find_ints/expected/model-solution000017.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting i be 3 +letting j be 3 +letting p be permutation((1, 2)) diff --git a/tests/exhaustive/basic/perms/04_image/int/0007_find_permutation_find_ints/expected/model-solution000018.solution b/tests/exhaustive/basic/perms/04_image/int/0007_find_permutation_find_ints/expected/model-solution000018.solution new file mode 100644 index 0000000000..59c7128348 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/int/0007_find_permutation_find_ints/expected/model-solution000018.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting i be 3 +letting j be 4 +letting p be permutation((1, 2), (3, 4)) diff --git a/tests/exhaustive/basic/perms/04_image/int/0007_find_permutation_find_ints/expected/model-solution000019.solution b/tests/exhaustive/basic/perms/04_image/int/0007_find_permutation_find_ints/expected/model-solution000019.solution new file mode 100644 index 0000000000..ee31fdde28 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/int/0007_find_permutation_find_ints/expected/model-solution000019.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting i be 3 +letting j be 4 +letting p be permutation((1, 2, 3, 4)) diff --git a/tests/exhaustive/basic/perms/04_image/int/0007_find_permutation_find_ints/expected/model-solution000020.solution b/tests/exhaustive/basic/perms/04_image/int/0007_find_permutation_find_ints/expected/model-solution000020.solution new file mode 100644 index 0000000000..820d2610df --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/int/0007_find_permutation_find_ints/expected/model-solution000020.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting i be 3 +letting j be 3 +letting p be permutation((1, 2, 4)) diff --git a/tests/exhaustive/basic/perms/04_image/int/0007_find_permutation_find_ints/expected/model-solution000021.solution b/tests/exhaustive/basic/perms/04_image/int/0007_find_permutation_find_ints/expected/model-solution000021.solution new file mode 100644 index 0000000000..d21e731546 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/int/0007_find_permutation_find_ints/expected/model-solution000021.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting i be 3 +letting j be 4 +letting p be permutation((1, 3, 4, 2)) diff --git a/tests/exhaustive/basic/perms/04_image/int/0007_find_permutation_find_ints/expected/model-solution000022.solution b/tests/exhaustive/basic/perms/04_image/int/0007_find_permutation_find_ints/expected/model-solution000022.solution new file mode 100644 index 0000000000..178dc4f8df --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/int/0007_find_permutation_find_ints/expected/model-solution000022.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting i be 3 +letting j be 4 +letting p be permutation((1, 3, 4)) diff --git a/tests/exhaustive/basic/perms/04_image/int/0007_find_permutation_find_ints/expected/model-solution000023.solution b/tests/exhaustive/basic/perms/04_image/int/0007_find_permutation_find_ints/expected/model-solution000023.solution new file mode 100644 index 0000000000..f92facc713 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/int/0007_find_permutation_find_ints/expected/model-solution000023.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting i be 3 +letting j be 3 +letting p be permutation((1, 4, 2)) diff --git a/tests/exhaustive/basic/perms/04_image/int/0007_find_permutation_find_ints/expected/model-solution000024.solution b/tests/exhaustive/basic/perms/04_image/int/0007_find_permutation_find_ints/expected/model-solution000024.solution new file mode 100644 index 0000000000..102406023f --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/int/0007_find_permutation_find_ints/expected/model-solution000024.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting i be 3 +letting j be 3 +letting p be permutation((1, 4)) diff --git a/tests/exhaustive/basic/perms/04_image/int/0007_find_permutation_find_ints/expected/model.eprime b/tests/exhaustive/basic/perms/04_image/int/0007_find_permutation_find_ints/expected/model.eprime new file mode 100644 index 0000000000..0f9d2f7a25 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/int/0007_find_permutation_find_ints/expected/model.eprime @@ -0,0 +1,17 @@ +language ESSENCE' 1.0 + +find i: int(1..4) +find p_PermutationAsFunction_PermutationFunction_Function1D: matrix indexed by [int(1..4)] of int(1..4) +find j: int(1..4) +branching on [i, p_PermutationAsFunction_PermutationFunction_Function1D, j] +such that + i >= 2, + i <= 3, + j >= 3, + j <= 4, + j = + [i, catchUndef(p_PermutationAsFunction_PermutationFunction_Function1D[i], 0); int(1..2)] + [toInt(or([q6 = i | q6 : int(1..4)])) + 1], + allDiff(p_PermutationAsFunction_PermutationFunction_Function1D), + and([or([p_PermutationAsFunction_PermutationFunction_Function1D[q3] = q2 | q3 : int(1..4)]) | q2 : int(1..4)]) + diff --git a/tests/exhaustive/basic/perms/04_image/int/0007_find_permutation_find_ints/permutation.essence b/tests/exhaustive/basic/perms/04_image/int/0007_find_permutation_find_ints/permutation.essence new file mode 100644 index 0000000000..c1c164c3e2 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/int/0007_find_permutation_find_ints/permutation.essence @@ -0,0 +1,16 @@ +letting n be domain int(1..4) + +find i : n + +find p : permutation of n + +find j : n + +such that + i >= 2 /\ i <= 3, + j >= 3 /\ j <= 4, + j = image(p, i) + + + + diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000001.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000001.solution new file mode 100644 index 0000000000..0c7a6a5528 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000001.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_1 +letting j be n_1 +letting p be permutation((n_5, n_6, n_7)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000002.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000002.solution new file mode 100644 index 0000000000..9f751644be --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000002.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_1 +letting j be n_1 +letting p be permutation((n_5, n_7, n_6)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000003.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000003.solution new file mode 100644 index 0000000000..16a346c791 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000003.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_1 +letting j be n_1 +letting p be permutation((n_4, n_5, n_6)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000004.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000004.solution new file mode 100644 index 0000000000..e0f40074c2 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000004.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_1 +letting j be n_1 +letting p be permutation((n_4, n_5, n_7)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000005.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000005.solution new file mode 100644 index 0000000000..c2e4e5ea41 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000005.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_1 +letting j be n_1 +letting p be permutation((n_4, n_6, n_5)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000006.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000006.solution new file mode 100644 index 0000000000..22c4554194 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000006.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_1 +letting j be n_1 +letting p be permutation((n_4, n_6, n_7)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000007.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000007.solution new file mode 100644 index 0000000000..440aa69aba --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000007.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_1 +letting j be n_1 +letting p be permutation((n_4, n_7, n_5)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000008.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000008.solution new file mode 100644 index 0000000000..c6c0744379 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000008.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_1 +letting j be n_1 +letting p be permutation((n_4, n_7, n_6)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000009.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000009.solution new file mode 100644 index 0000000000..7558d5baf1 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000009.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_1 +letting j be n_1 +letting p be permutation((n_3, n_4, n_5)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000010.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000010.solution new file mode 100644 index 0000000000..e2df3c0f27 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000010.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_1 +letting j be n_1 +letting p be permutation((n_3, n_4, n_6)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000011.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000011.solution new file mode 100644 index 0000000000..27fdb198b8 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000011.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_1 +letting j be n_1 +letting p be permutation((n_3, n_4, n_7)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000012.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000012.solution new file mode 100644 index 0000000000..b49a222d43 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000012.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_1 +letting j be n_1 +letting p be permutation((n_3, n_5, n_4)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000013.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000013.solution new file mode 100644 index 0000000000..e6b7165850 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000013.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_1 +letting j be n_1 +letting p be permutation((n_3, n_5, n_6)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000014.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000014.solution new file mode 100644 index 0000000000..2b0fb0cf21 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000014.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_1 +letting j be n_1 +letting p be permutation((n_3, n_5, n_7)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000015.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000015.solution new file mode 100644 index 0000000000..dcc7219eaf --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000015.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_1 +letting j be n_1 +letting p be permutation((n_3, n_6, n_4)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000016.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000016.solution new file mode 100644 index 0000000000..c0dbc008d4 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000016.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_1 +letting j be n_1 +letting p be permutation((n_3, n_6, n_5)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000017.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000017.solution new file mode 100644 index 0000000000..39ff4b5e81 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000017.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_1 +letting j be n_1 +letting p be permutation((n_3, n_6, n_7)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000018.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000018.solution new file mode 100644 index 0000000000..112fdbf415 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000018.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_1 +letting j be n_1 +letting p be permutation((n_3, n_7, n_4)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000019.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000019.solution new file mode 100644 index 0000000000..af96cd3497 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000019.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_1 +letting j be n_1 +letting p be permutation((n_3, n_7, n_5)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000020.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000020.solution new file mode 100644 index 0000000000..ccd6e96951 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000020.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_1 +letting j be n_1 +letting p be permutation((n_3, n_7, n_6)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000021.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000021.solution new file mode 100644 index 0000000000..769beb4c0a --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000021.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_1 +letting j be n_1 +letting p be permutation((n_2, n_3, n_4)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000022.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000022.solution new file mode 100644 index 0000000000..617a3f6fbc --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000022.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_1 +letting j be n_1 +letting p be permutation((n_2, n_3, n_5)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000023.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000023.solution new file mode 100644 index 0000000000..91d81acc10 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000023.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_1 +letting j be n_1 +letting p be permutation((n_2, n_3, n_6)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000024.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000024.solution new file mode 100644 index 0000000000..f6042d9f3a --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000024.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_1 +letting j be n_1 +letting p be permutation((n_2, n_3, n_7)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000025.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000025.solution new file mode 100644 index 0000000000..2a8bfcc0f4 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000025.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_1 +letting j be n_1 +letting p be permutation((n_2, n_4, n_3)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000026.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000026.solution new file mode 100644 index 0000000000..0cee2f236c --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000026.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_1 +letting j be n_1 +letting p be permutation((n_2, n_4, n_5)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000027.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000027.solution new file mode 100644 index 0000000000..04b67ef053 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000027.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_1 +letting j be n_1 +letting p be permutation((n_2, n_4, n_6)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000028.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000028.solution new file mode 100644 index 0000000000..d10753bd51 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000028.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_1 +letting j be n_1 +letting p be permutation((n_2, n_4, n_7)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000029.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000029.solution new file mode 100644 index 0000000000..d4e638332d --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000029.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_1 +letting j be n_1 +letting p be permutation((n_2, n_5, n_3)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000030.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000030.solution new file mode 100644 index 0000000000..7d2224da1d --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000030.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_1 +letting j be n_1 +letting p be permutation((n_2, n_5, n_4)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000031.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000031.solution new file mode 100644 index 0000000000..e8d58debf4 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000031.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_1 +letting j be n_1 +letting p be permutation((n_2, n_5, n_6)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000032.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000032.solution new file mode 100644 index 0000000000..200d9b612f --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000032.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_1 +letting j be n_1 +letting p be permutation((n_2, n_5, n_7)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000033.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000033.solution new file mode 100644 index 0000000000..ac2eda8355 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000033.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_1 +letting j be n_1 +letting p be permutation((n_2, n_6, n_3)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000034.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000034.solution new file mode 100644 index 0000000000..f6a44ca463 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000034.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_1 +letting j be n_1 +letting p be permutation((n_2, n_6, n_4)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000035.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000035.solution new file mode 100644 index 0000000000..69c12e92ac --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000035.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_1 +letting j be n_1 +letting p be permutation((n_2, n_6, n_5)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000036.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000036.solution new file mode 100644 index 0000000000..fc2bd5261a --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000036.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_1 +letting j be n_1 +letting p be permutation((n_2, n_6, n_7)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000037.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000037.solution new file mode 100644 index 0000000000..cf3cf921ba --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000037.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_1 +letting j be n_1 +letting p be permutation((n_2, n_7, n_3)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000038.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000038.solution new file mode 100644 index 0000000000..f1bfe86dac --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000038.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_1 +letting j be n_1 +letting p be permutation((n_2, n_7, n_4)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000039.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000039.solution new file mode 100644 index 0000000000..9820300e95 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000039.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_1 +letting j be n_1 +letting p be permutation((n_2, n_7, n_5)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000040.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000040.solution new file mode 100644 index 0000000000..cbcc16b43c --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000040.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_1 +letting j be n_1 +letting p be permutation((n_2, n_7, n_6)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000041.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000041.solution new file mode 100644 index 0000000000..cab486c4f4 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000041.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_1 +letting j be n_2 +letting p be permutation((n_1, n_2, n_3)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000042.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000042.solution new file mode 100644 index 0000000000..00336874aa --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000042.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_1 +letting j be n_2 +letting p be permutation((n_1, n_2, n_4)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000043.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000043.solution new file mode 100644 index 0000000000..19cd6c0dd7 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000043.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_1 +letting j be n_2 +letting p be permutation((n_1, n_2, n_5)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000044.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000044.solution new file mode 100644 index 0000000000..24cf0dcaa4 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000044.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_1 +letting j be n_2 +letting p be permutation((n_1, n_2, n_6)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000045.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000045.solution new file mode 100644 index 0000000000..358d5903c1 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000045.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_1 +letting j be n_2 +letting p be permutation((n_1, n_2, n_7)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000046.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000046.solution new file mode 100644 index 0000000000..67266a14fc --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000046.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_1 +letting j be n_3 +letting p be permutation((n_1, n_3, n_2)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000047.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000047.solution new file mode 100644 index 0000000000..469af45687 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000047.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_1 +letting j be n_3 +letting p be permutation((n_1, n_3, n_4)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000048.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000048.solution new file mode 100644 index 0000000000..fc413f1f9d --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000048.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_1 +letting j be n_3 +letting p be permutation((n_1, n_3, n_5)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000049.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000049.solution new file mode 100644 index 0000000000..7e8d8ef19d --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000049.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_1 +letting j be n_3 +letting p be permutation((n_1, n_3, n_6)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000050.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000050.solution new file mode 100644 index 0000000000..07ef83600f --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000050.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_1 +letting j be n_3 +letting p be permutation((n_1, n_3, n_7)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000051.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000051.solution new file mode 100644 index 0000000000..c760fecbb1 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000051.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_1 +letting j be n_4 +letting p be permutation((n_1, n_4, n_2)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000052.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000052.solution new file mode 100644 index 0000000000..fa2bca9e62 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000052.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_1 +letting j be n_4 +letting p be permutation((n_1, n_4, n_3)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000053.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000053.solution new file mode 100644 index 0000000000..befa8181e0 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000053.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_1 +letting j be n_4 +letting p be permutation((n_1, n_4, n_5)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000054.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000054.solution new file mode 100644 index 0000000000..4762de53db --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000054.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_1 +letting j be n_4 +letting p be permutation((n_1, n_4, n_6)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000055.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000055.solution new file mode 100644 index 0000000000..fa036c23ea --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000055.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_1 +letting j be n_4 +letting p be permutation((n_1, n_4, n_7)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000056.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000056.solution new file mode 100644 index 0000000000..f7726e431c --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000056.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_1 +letting j be n_5 +letting p be permutation((n_1, n_5, n_2)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000057.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000057.solution new file mode 100644 index 0000000000..228549e15d --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000057.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_1 +letting j be n_5 +letting p be permutation((n_1, n_5, n_3)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000058.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000058.solution new file mode 100644 index 0000000000..496d9a8fd9 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000058.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_1 +letting j be n_5 +letting p be permutation((n_1, n_5, n_4)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000059.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000059.solution new file mode 100644 index 0000000000..c271e211f2 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000059.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_1 +letting j be n_5 +letting p be permutation((n_1, n_5, n_6)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000060.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000060.solution new file mode 100644 index 0000000000..b4f4ecf313 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000060.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_1 +letting j be n_5 +letting p be permutation((n_1, n_5, n_7)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000061.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000061.solution new file mode 100644 index 0000000000..c7d2e53921 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000061.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_1 +letting j be n_6 +letting p be permutation((n_1, n_6, n_2)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000062.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000062.solution new file mode 100644 index 0000000000..7ed4a6ae68 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000062.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_1 +letting j be n_6 +letting p be permutation((n_1, n_6, n_3)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000063.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000063.solution new file mode 100644 index 0000000000..3f9ad21db6 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000063.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_1 +letting j be n_6 +letting p be permutation((n_1, n_6, n_4)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000064.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000064.solution new file mode 100644 index 0000000000..2c07cfe859 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000064.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_1 +letting j be n_6 +letting p be permutation((n_1, n_6, n_5)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000065.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000065.solution new file mode 100644 index 0000000000..5fbdeaed78 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000065.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_1 +letting j be n_6 +letting p be permutation((n_1, n_6, n_7)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000066.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000066.solution new file mode 100644 index 0000000000..5b6edaf142 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000066.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_1 +letting j be n_7 +letting p be permutation((n_1, n_7, n_2)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000067.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000067.solution new file mode 100644 index 0000000000..627d38ea84 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000067.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_1 +letting j be n_7 +letting p be permutation((n_1, n_7, n_3)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000068.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000068.solution new file mode 100644 index 0000000000..84581d1440 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000068.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_1 +letting j be n_7 +letting p be permutation((n_1, n_7, n_4)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000069.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000069.solution new file mode 100644 index 0000000000..95209f23d0 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000069.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_1 +letting j be n_7 +letting p be permutation((n_1, n_7, n_5)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000070.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000070.solution new file mode 100644 index 0000000000..24e16795cb --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000070.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_1 +letting j be n_7 +letting p be permutation((n_1, n_7, n_6)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000071.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000071.solution new file mode 100644 index 0000000000..b8cd8b1ab7 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000071.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_2 +letting j be n_2 +letting p be permutation((n_5, n_6, n_7)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000072.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000072.solution new file mode 100644 index 0000000000..374b3b63be --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000072.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_2 +letting j be n_2 +letting p be permutation((n_5, n_7, n_6)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000073.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000073.solution new file mode 100644 index 0000000000..d590aa7120 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000073.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_2 +letting j be n_2 +letting p be permutation((n_4, n_5, n_6)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000074.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000074.solution new file mode 100644 index 0000000000..29c576968a --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000074.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_2 +letting j be n_2 +letting p be permutation((n_4, n_5, n_7)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000075.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000075.solution new file mode 100644 index 0000000000..dae17e70f8 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000075.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_2 +letting j be n_2 +letting p be permutation((n_4, n_6, n_5)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000076.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000076.solution new file mode 100644 index 0000000000..5ddc2bc11d --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000076.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_2 +letting j be n_2 +letting p be permutation((n_4, n_6, n_7)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000077.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000077.solution new file mode 100644 index 0000000000..688cc6dc93 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000077.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_2 +letting j be n_2 +letting p be permutation((n_4, n_7, n_5)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000078.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000078.solution new file mode 100644 index 0000000000..d46b040327 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000078.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_2 +letting j be n_2 +letting p be permutation((n_4, n_7, n_6)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000079.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000079.solution new file mode 100644 index 0000000000..751b474195 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000079.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_2 +letting j be n_2 +letting p be permutation((n_3, n_4, n_5)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000080.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000080.solution new file mode 100644 index 0000000000..7c399dd847 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000080.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_2 +letting j be n_2 +letting p be permutation((n_3, n_4, n_6)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000081.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000081.solution new file mode 100644 index 0000000000..d883260ade --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000081.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_2 +letting j be n_2 +letting p be permutation((n_3, n_4, n_7)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000082.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000082.solution new file mode 100644 index 0000000000..9fe084bc2d --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000082.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_2 +letting j be n_2 +letting p be permutation((n_3, n_5, n_4)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000083.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000083.solution new file mode 100644 index 0000000000..213553c9b1 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000083.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_2 +letting j be n_2 +letting p be permutation((n_3, n_5, n_6)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000084.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000084.solution new file mode 100644 index 0000000000..527b1ca902 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000084.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_2 +letting j be n_2 +letting p be permutation((n_3, n_5, n_7)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000085.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000085.solution new file mode 100644 index 0000000000..1ad1725cd0 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000085.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_2 +letting j be n_2 +letting p be permutation((n_3, n_6, n_4)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000086.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000086.solution new file mode 100644 index 0000000000..0a91c90eae --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000086.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_2 +letting j be n_2 +letting p be permutation((n_3, n_6, n_5)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000087.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000087.solution new file mode 100644 index 0000000000..0540569ad5 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000087.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_2 +letting j be n_2 +letting p be permutation((n_3, n_6, n_7)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000088.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000088.solution new file mode 100644 index 0000000000..7183bc9893 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000088.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_2 +letting j be n_2 +letting p be permutation((n_3, n_7, n_4)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000089.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000089.solution new file mode 100644 index 0000000000..22029b7a14 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000089.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_2 +letting j be n_2 +letting p be permutation((n_3, n_7, n_5)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000090.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000090.solution new file mode 100644 index 0000000000..4c256e3605 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000090.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_2 +letting j be n_2 +letting p be permutation((n_3, n_7, n_6)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000091.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000091.solution new file mode 100644 index 0000000000..e714060eb9 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000091.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_2 +letting j be n_3 +letting p be permutation((n_2, n_3, n_4)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000092.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000092.solution new file mode 100644 index 0000000000..c00923f053 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000092.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_2 +letting j be n_3 +letting p be permutation((n_2, n_3, n_5)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000093.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000093.solution new file mode 100644 index 0000000000..a4b6d3c73a --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000093.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_2 +letting j be n_3 +letting p be permutation((n_2, n_3, n_6)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000094.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000094.solution new file mode 100644 index 0000000000..d3eb36f042 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000094.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_2 +letting j be n_3 +letting p be permutation((n_2, n_3, n_7)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000095.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000095.solution new file mode 100644 index 0000000000..56a4c3da98 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000095.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_2 +letting j be n_4 +letting p be permutation((n_2, n_4, n_3)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000096.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000096.solution new file mode 100644 index 0000000000..514ca01c87 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000096.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_2 +letting j be n_4 +letting p be permutation((n_2, n_4, n_5)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000097.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000097.solution new file mode 100644 index 0000000000..27c6ed5f9d --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000097.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_2 +letting j be n_4 +letting p be permutation((n_2, n_4, n_6)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000098.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000098.solution new file mode 100644 index 0000000000..98a2045a15 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000098.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_2 +letting j be n_4 +letting p be permutation((n_2, n_4, n_7)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000099.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000099.solution new file mode 100644 index 0000000000..fadf6a747f --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000099.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_2 +letting j be n_5 +letting p be permutation((n_2, n_5, n_3)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000100.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000100.solution new file mode 100644 index 0000000000..058bc12d76 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000100.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_2 +letting j be n_5 +letting p be permutation((n_2, n_5, n_4)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000101.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000101.solution new file mode 100644 index 0000000000..adb507129e --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000101.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_2 +letting j be n_5 +letting p be permutation((n_2, n_5, n_6)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000102.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000102.solution new file mode 100644 index 0000000000..91974b8940 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000102.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_2 +letting j be n_5 +letting p be permutation((n_2, n_5, n_7)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000103.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000103.solution new file mode 100644 index 0000000000..1e06693e0d --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000103.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_2 +letting j be n_6 +letting p be permutation((n_2, n_6, n_3)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000104.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000104.solution new file mode 100644 index 0000000000..40cb150657 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000104.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_2 +letting j be n_6 +letting p be permutation((n_2, n_6, n_4)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000105.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000105.solution new file mode 100644 index 0000000000..701089f493 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000105.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_2 +letting j be n_6 +letting p be permutation((n_2, n_6, n_5)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000106.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000106.solution new file mode 100644 index 0000000000..70a0c5e461 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000106.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_2 +letting j be n_6 +letting p be permutation((n_2, n_6, n_7)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000107.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000107.solution new file mode 100644 index 0000000000..64a831cf65 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000107.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_2 +letting j be n_7 +letting p be permutation((n_2, n_7, n_3)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000108.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000108.solution new file mode 100644 index 0000000000..77b84b9e63 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000108.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_2 +letting j be n_7 +letting p be permutation((n_2, n_7, n_4)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000109.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000109.solution new file mode 100644 index 0000000000..6bbbee3b74 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000109.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_2 +letting j be n_7 +letting p be permutation((n_2, n_7, n_5)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000110.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000110.solution new file mode 100644 index 0000000000..15a84d0fd0 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000110.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_2 +letting j be n_7 +letting p be permutation((n_2, n_7, n_6)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000111.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000111.solution new file mode 100644 index 0000000000..714be34d29 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000111.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_2 +letting j be n_3 +letting p be permutation((n_1, n_2, n_3)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000112.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000112.solution new file mode 100644 index 0000000000..3f7c71532e --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000112.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_2 +letting j be n_4 +letting p be permutation((n_1, n_2, n_4)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000113.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000113.solution new file mode 100644 index 0000000000..23a4137987 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000113.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_2 +letting j be n_5 +letting p be permutation((n_1, n_2, n_5)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000114.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000114.solution new file mode 100644 index 0000000000..0ee6effc91 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000114.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_2 +letting j be n_6 +letting p be permutation((n_1, n_2, n_6)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000115.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000115.solution new file mode 100644 index 0000000000..973597b328 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000115.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_2 +letting j be n_7 +letting p be permutation((n_1, n_2, n_7)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000116.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000116.solution new file mode 100644 index 0000000000..519809beef --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000116.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_2 +letting j be n_1 +letting p be permutation((n_1, n_3, n_2)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000117.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000117.solution new file mode 100644 index 0000000000..395e867a31 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000117.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_2 +letting j be n_2 +letting p be permutation((n_1, n_3, n_4)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000118.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000118.solution new file mode 100644 index 0000000000..885458780f --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000118.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_2 +letting j be n_2 +letting p be permutation((n_1, n_3, n_5)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000119.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000119.solution new file mode 100644 index 0000000000..f70e6e250f --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000119.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_2 +letting j be n_2 +letting p be permutation((n_1, n_3, n_6)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000120.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000120.solution new file mode 100644 index 0000000000..b04c410245 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000120.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_2 +letting j be n_2 +letting p be permutation((n_1, n_3, n_7)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000121.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000121.solution new file mode 100644 index 0000000000..9aa97fccc6 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000121.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_2 +letting j be n_1 +letting p be permutation((n_1, n_4, n_2)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000122.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000122.solution new file mode 100644 index 0000000000..2f00773b43 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000122.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_2 +letting j be n_2 +letting p be permutation((n_1, n_4, n_3)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000123.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000123.solution new file mode 100644 index 0000000000..da7dd28288 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000123.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_2 +letting j be n_2 +letting p be permutation((n_1, n_4, n_5)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000124.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000124.solution new file mode 100644 index 0000000000..29bd54c675 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000124.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_2 +letting j be n_2 +letting p be permutation((n_1, n_4, n_6)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000125.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000125.solution new file mode 100644 index 0000000000..b5cf2b4571 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000125.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_2 +letting j be n_2 +letting p be permutation((n_1, n_4, n_7)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000126.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000126.solution new file mode 100644 index 0000000000..0ccc6930a8 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000126.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_2 +letting j be n_1 +letting p be permutation((n_1, n_5, n_2)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000127.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000127.solution new file mode 100644 index 0000000000..de9a11848b --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000127.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_2 +letting j be n_2 +letting p be permutation((n_1, n_5, n_3)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000128.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000128.solution new file mode 100644 index 0000000000..5c25a7e35b --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000128.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_2 +letting j be n_2 +letting p be permutation((n_1, n_5, n_4)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000129.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000129.solution new file mode 100644 index 0000000000..37b1ec7837 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000129.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_2 +letting j be n_2 +letting p be permutation((n_1, n_5, n_6)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000130.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000130.solution new file mode 100644 index 0000000000..d927205654 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000130.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_2 +letting j be n_2 +letting p be permutation((n_1, n_5, n_7)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000131.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000131.solution new file mode 100644 index 0000000000..0374925b0c --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000131.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_2 +letting j be n_1 +letting p be permutation((n_1, n_6, n_2)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000132.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000132.solution new file mode 100644 index 0000000000..d7db4b79ba --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000132.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_2 +letting j be n_2 +letting p be permutation((n_1, n_6, n_3)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000133.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000133.solution new file mode 100644 index 0000000000..cb0b376b4b --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000133.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_2 +letting j be n_2 +letting p be permutation((n_1, n_6, n_4)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000134.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000134.solution new file mode 100644 index 0000000000..e940ef07a3 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000134.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_2 +letting j be n_2 +letting p be permutation((n_1, n_6, n_5)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000135.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000135.solution new file mode 100644 index 0000000000..ac7df51382 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000135.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_2 +letting j be n_2 +letting p be permutation((n_1, n_6, n_7)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000136.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000136.solution new file mode 100644 index 0000000000..6c07821d58 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000136.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_2 +letting j be n_1 +letting p be permutation((n_1, n_7, n_2)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000137.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000137.solution new file mode 100644 index 0000000000..b3df39f6e9 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000137.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_2 +letting j be n_2 +letting p be permutation((n_1, n_7, n_3)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000138.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000138.solution new file mode 100644 index 0000000000..63b3de8658 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000138.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_2 +letting j be n_2 +letting p be permutation((n_1, n_7, n_4)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000139.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000139.solution new file mode 100644 index 0000000000..b42eafbe72 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000139.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_2 +letting j be n_2 +letting p be permutation((n_1, n_7, n_5)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000140.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000140.solution new file mode 100644 index 0000000000..c71915bb59 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000140.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_2 +letting j be n_2 +letting p be permutation((n_1, n_7, n_6)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000141.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000141.solution new file mode 100644 index 0000000000..53105c6095 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000141.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_3 +letting j be n_3 +letting p be permutation((n_5, n_6, n_7)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000142.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000142.solution new file mode 100644 index 0000000000..1a45179405 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000142.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_3 +letting j be n_3 +letting p be permutation((n_5, n_7, n_6)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000143.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000143.solution new file mode 100644 index 0000000000..07a1ec4c6f --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000143.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_3 +letting j be n_3 +letting p be permutation((n_4, n_5, n_6)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000144.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000144.solution new file mode 100644 index 0000000000..1ecefee51a --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000144.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_3 +letting j be n_3 +letting p be permutation((n_4, n_5, n_7)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000145.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000145.solution new file mode 100644 index 0000000000..40f4def324 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000145.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_3 +letting j be n_3 +letting p be permutation((n_4, n_6, n_5)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000146.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000146.solution new file mode 100644 index 0000000000..9d90f029ac --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000146.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_3 +letting j be n_3 +letting p be permutation((n_4, n_6, n_7)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000147.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000147.solution new file mode 100644 index 0000000000..51307cc9fb --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000147.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_3 +letting j be n_3 +letting p be permutation((n_4, n_7, n_5)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000148.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000148.solution new file mode 100644 index 0000000000..a8bd2840e1 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000148.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_3 +letting j be n_3 +letting p be permutation((n_4, n_7, n_6)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000149.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000149.solution new file mode 100644 index 0000000000..17b2ad0a8a --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000149.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_3 +letting j be n_4 +letting p be permutation((n_3, n_4, n_5)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000150.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000150.solution new file mode 100644 index 0000000000..5fe529b3a5 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000150.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_3 +letting j be n_4 +letting p be permutation((n_3, n_4, n_6)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000151.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000151.solution new file mode 100644 index 0000000000..4d84bff2d1 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000151.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_3 +letting j be n_4 +letting p be permutation((n_3, n_4, n_7)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000152.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000152.solution new file mode 100644 index 0000000000..c5b635eadb --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000152.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_3 +letting j be n_5 +letting p be permutation((n_3, n_5, n_4)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000153.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000153.solution new file mode 100644 index 0000000000..3023d3497d --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000153.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_3 +letting j be n_5 +letting p be permutation((n_3, n_5, n_6)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000154.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000154.solution new file mode 100644 index 0000000000..8b6b45d167 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000154.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_3 +letting j be n_5 +letting p be permutation((n_3, n_5, n_7)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000155.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000155.solution new file mode 100644 index 0000000000..58fde6c23c --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000155.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_3 +letting j be n_6 +letting p be permutation((n_3, n_6, n_4)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000156.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000156.solution new file mode 100644 index 0000000000..644ae1ecbe --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000156.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_3 +letting j be n_6 +letting p be permutation((n_3, n_6, n_5)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000157.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000157.solution new file mode 100644 index 0000000000..3908bf1a54 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000157.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_3 +letting j be n_6 +letting p be permutation((n_3, n_6, n_7)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000158.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000158.solution new file mode 100644 index 0000000000..32351a43ea --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000158.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_3 +letting j be n_7 +letting p be permutation((n_3, n_7, n_4)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000159.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000159.solution new file mode 100644 index 0000000000..4dd4a4f58d --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000159.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_3 +letting j be n_7 +letting p be permutation((n_3, n_7, n_5)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000160.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000160.solution new file mode 100644 index 0000000000..16837d9848 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000160.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_3 +letting j be n_7 +letting p be permutation((n_3, n_7, n_6)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000161.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000161.solution new file mode 100644 index 0000000000..aeedc5b8f6 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000161.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_3 +letting j be n_4 +letting p be permutation((n_2, n_3, n_4)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000162.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000162.solution new file mode 100644 index 0000000000..64e3168f3e --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000162.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_3 +letting j be n_5 +letting p be permutation((n_2, n_3, n_5)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000163.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000163.solution new file mode 100644 index 0000000000..005d796d41 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000163.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_3 +letting j be n_6 +letting p be permutation((n_2, n_3, n_6)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000164.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000164.solution new file mode 100644 index 0000000000..6b0b8baeab --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000164.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_3 +letting j be n_7 +letting p be permutation((n_2, n_3, n_7)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000165.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000165.solution new file mode 100644 index 0000000000..84e632bd76 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000165.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_3 +letting j be n_2 +letting p be permutation((n_2, n_4, n_3)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000166.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000166.solution new file mode 100644 index 0000000000..f3c66d6ee0 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000166.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_3 +letting j be n_3 +letting p be permutation((n_2, n_4, n_5)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000167.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000167.solution new file mode 100644 index 0000000000..5892068f17 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000167.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_3 +letting j be n_3 +letting p be permutation((n_2, n_4, n_6)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000168.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000168.solution new file mode 100644 index 0000000000..ead98c0cdc --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000168.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_3 +letting j be n_3 +letting p be permutation((n_2, n_4, n_7)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000169.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000169.solution new file mode 100644 index 0000000000..e6afac2a46 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000169.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_3 +letting j be n_2 +letting p be permutation((n_2, n_5, n_3)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000170.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000170.solution new file mode 100644 index 0000000000..87a81dffe0 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000170.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_3 +letting j be n_3 +letting p be permutation((n_2, n_5, n_4)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000171.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000171.solution new file mode 100644 index 0000000000..a90b9dc803 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000171.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_3 +letting j be n_3 +letting p be permutation((n_2, n_5, n_6)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000172.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000172.solution new file mode 100644 index 0000000000..ad94c1e84d --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000172.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_3 +letting j be n_3 +letting p be permutation((n_2, n_5, n_7)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000173.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000173.solution new file mode 100644 index 0000000000..7f90c18e7f --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000173.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_3 +letting j be n_2 +letting p be permutation((n_2, n_6, n_3)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000174.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000174.solution new file mode 100644 index 0000000000..b898dcdbb3 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000174.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_3 +letting j be n_3 +letting p be permutation((n_2, n_6, n_4)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000175.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000175.solution new file mode 100644 index 0000000000..6dc673ed57 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000175.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_3 +letting j be n_3 +letting p be permutation((n_2, n_6, n_5)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000176.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000176.solution new file mode 100644 index 0000000000..0cf5e0e39b --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000176.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_3 +letting j be n_3 +letting p be permutation((n_2, n_6, n_7)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000177.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000177.solution new file mode 100644 index 0000000000..d110ac23b4 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000177.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_3 +letting j be n_2 +letting p be permutation((n_2, n_7, n_3)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000178.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000178.solution new file mode 100644 index 0000000000..f2c635f27a --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000178.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_3 +letting j be n_3 +letting p be permutation((n_2, n_7, n_4)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000179.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000179.solution new file mode 100644 index 0000000000..e7053c1b25 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000179.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_3 +letting j be n_3 +letting p be permutation((n_2, n_7, n_5)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000180.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000180.solution new file mode 100644 index 0000000000..da2c3a76e6 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000180.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_3 +letting j be n_3 +letting p be permutation((n_2, n_7, n_6)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000181.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000181.solution new file mode 100644 index 0000000000..e35eb1a886 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000181.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_3 +letting j be n_1 +letting p be permutation((n_1, n_2, n_3)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000182.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000182.solution new file mode 100644 index 0000000000..0d13ec4581 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000182.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_3 +letting j be n_3 +letting p be permutation((n_1, n_2, n_4)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000183.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000183.solution new file mode 100644 index 0000000000..bcc350334f --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000183.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_3 +letting j be n_3 +letting p be permutation((n_1, n_2, n_5)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000184.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000184.solution new file mode 100644 index 0000000000..c803aa222a --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000184.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_3 +letting j be n_3 +letting p be permutation((n_1, n_2, n_6)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000185.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000185.solution new file mode 100644 index 0000000000..dda552398b --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000185.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_3 +letting j be n_3 +letting p be permutation((n_1, n_2, n_7)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000186.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000186.solution new file mode 100644 index 0000000000..3c4556c608 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000186.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_3 +letting j be n_2 +letting p be permutation((n_1, n_3, n_2)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000187.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000187.solution new file mode 100644 index 0000000000..5913fa0e7a --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000187.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_3 +letting j be n_4 +letting p be permutation((n_1, n_3, n_4)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000188.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000188.solution new file mode 100644 index 0000000000..b0d1f7fbde --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000188.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_3 +letting j be n_5 +letting p be permutation((n_1, n_3, n_5)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000189.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000189.solution new file mode 100644 index 0000000000..0e0c916d71 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000189.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_3 +letting j be n_6 +letting p be permutation((n_1, n_3, n_6)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000190.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000190.solution new file mode 100644 index 0000000000..cb837c3e68 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000190.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_3 +letting j be n_7 +letting p be permutation((n_1, n_3, n_7)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000191.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000191.solution new file mode 100644 index 0000000000..8fbbba6f71 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000191.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_3 +letting j be n_3 +letting p be permutation((n_1, n_4, n_2)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000192.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000192.solution new file mode 100644 index 0000000000..13a1869de6 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000192.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_3 +letting j be n_1 +letting p be permutation((n_1, n_4, n_3)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000193.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000193.solution new file mode 100644 index 0000000000..eb09b5665c --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000193.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_3 +letting j be n_3 +letting p be permutation((n_1, n_4, n_5)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000194.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000194.solution new file mode 100644 index 0000000000..6b7eeee4d9 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000194.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_3 +letting j be n_3 +letting p be permutation((n_1, n_4, n_6)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000195.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000195.solution new file mode 100644 index 0000000000..42ad76650d --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000195.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_3 +letting j be n_3 +letting p be permutation((n_1, n_4, n_7)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000196.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000196.solution new file mode 100644 index 0000000000..c0c9238597 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000196.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_3 +letting j be n_3 +letting p be permutation((n_1, n_5, n_2)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000197.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000197.solution new file mode 100644 index 0000000000..06f3bf8b3b --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000197.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_3 +letting j be n_1 +letting p be permutation((n_1, n_5, n_3)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000198.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000198.solution new file mode 100644 index 0000000000..42103948bb --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000198.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_3 +letting j be n_3 +letting p be permutation((n_1, n_5, n_4)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000199.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000199.solution new file mode 100644 index 0000000000..815cde2f7e --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000199.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_3 +letting j be n_3 +letting p be permutation((n_1, n_5, n_6)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000200.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000200.solution new file mode 100644 index 0000000000..7f4ab45e1f --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000200.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_3 +letting j be n_3 +letting p be permutation((n_1, n_5, n_7)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000201.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000201.solution new file mode 100644 index 0000000000..2187fb6e6b --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000201.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_3 +letting j be n_3 +letting p be permutation((n_1, n_6, n_2)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000202.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000202.solution new file mode 100644 index 0000000000..bffae7a95b --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000202.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_3 +letting j be n_1 +letting p be permutation((n_1, n_6, n_3)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000203.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000203.solution new file mode 100644 index 0000000000..4db2ee937d --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000203.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_3 +letting j be n_3 +letting p be permutation((n_1, n_6, n_4)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000204.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000204.solution new file mode 100644 index 0000000000..7222f5d72f --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000204.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_3 +letting j be n_3 +letting p be permutation((n_1, n_6, n_5)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000205.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000205.solution new file mode 100644 index 0000000000..51e1f42375 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000205.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_3 +letting j be n_3 +letting p be permutation((n_1, n_6, n_7)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000206.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000206.solution new file mode 100644 index 0000000000..b1f689433a --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000206.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_3 +letting j be n_3 +letting p be permutation((n_1, n_7, n_2)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000207.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000207.solution new file mode 100644 index 0000000000..792e3f7c06 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000207.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_3 +letting j be n_1 +letting p be permutation((n_1, n_7, n_3)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000208.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000208.solution new file mode 100644 index 0000000000..37367f5ee0 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000208.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_3 +letting j be n_3 +letting p be permutation((n_1, n_7, n_4)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000209.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000209.solution new file mode 100644 index 0000000000..9bb443788a --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000209.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_3 +letting j be n_3 +letting p be permutation((n_1, n_7, n_5)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000210.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000210.solution new file mode 100644 index 0000000000..0f1ae3bc70 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000210.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_3 +letting j be n_3 +letting p be permutation((n_1, n_7, n_6)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000211.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000211.solution new file mode 100644 index 0000000000..b5f96ecf55 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000211.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_4 +letting j be n_4 +letting p be permutation((n_5, n_6, n_7)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000212.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000212.solution new file mode 100644 index 0000000000..7ecc0e8e29 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000212.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_4 +letting j be n_4 +letting p be permutation((n_5, n_7, n_6)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000213.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000213.solution new file mode 100644 index 0000000000..7446193488 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000213.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_4 +letting j be n_5 +letting p be permutation((n_4, n_5, n_6)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000214.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000214.solution new file mode 100644 index 0000000000..7b1dc0935c --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000214.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_4 +letting j be n_5 +letting p be permutation((n_4, n_5, n_7)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000215.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000215.solution new file mode 100644 index 0000000000..d2dedaa2dc --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000215.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_4 +letting j be n_6 +letting p be permutation((n_4, n_6, n_5)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000216.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000216.solution new file mode 100644 index 0000000000..7ce8b69c0c --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000216.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_4 +letting j be n_6 +letting p be permutation((n_4, n_6, n_7)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000217.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000217.solution new file mode 100644 index 0000000000..3dbcef6b85 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000217.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_4 +letting j be n_7 +letting p be permutation((n_4, n_7, n_5)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000218.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000218.solution new file mode 100644 index 0000000000..5cf2420cc9 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000218.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_4 +letting j be n_7 +letting p be permutation((n_4, n_7, n_6)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000219.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000219.solution new file mode 100644 index 0000000000..08a0034b41 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000219.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_4 +letting j be n_5 +letting p be permutation((n_3, n_4, n_5)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000220.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000220.solution new file mode 100644 index 0000000000..ddf77b7ff7 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000220.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_4 +letting j be n_6 +letting p be permutation((n_3, n_4, n_6)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000221.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000221.solution new file mode 100644 index 0000000000..93ad9a3ae6 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000221.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_4 +letting j be n_7 +letting p be permutation((n_3, n_4, n_7)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000222.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000222.solution new file mode 100644 index 0000000000..f4de44e07b --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000222.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_4 +letting j be n_3 +letting p be permutation((n_3, n_5, n_4)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000223.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000223.solution new file mode 100644 index 0000000000..bde8210cfa --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000223.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_4 +letting j be n_4 +letting p be permutation((n_3, n_5, n_6)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000224.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000224.solution new file mode 100644 index 0000000000..60001c49af --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000224.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_4 +letting j be n_4 +letting p be permutation((n_3, n_5, n_7)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000225.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000225.solution new file mode 100644 index 0000000000..1a49f54f93 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000225.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_4 +letting j be n_3 +letting p be permutation((n_3, n_6, n_4)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000226.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000226.solution new file mode 100644 index 0000000000..b732486873 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000226.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_4 +letting j be n_4 +letting p be permutation((n_3, n_6, n_5)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000227.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000227.solution new file mode 100644 index 0000000000..ae6b4387ce --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000227.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_4 +letting j be n_4 +letting p be permutation((n_3, n_6, n_7)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000228.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000228.solution new file mode 100644 index 0000000000..2fd08a2130 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000228.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_4 +letting j be n_3 +letting p be permutation((n_3, n_7, n_4)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000229.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000229.solution new file mode 100644 index 0000000000..ccae877702 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000229.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_4 +letting j be n_4 +letting p be permutation((n_3, n_7, n_5)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000230.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000230.solution new file mode 100644 index 0000000000..ad73c3d3c3 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000230.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_4 +letting j be n_4 +letting p be permutation((n_3, n_7, n_6)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000231.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000231.solution new file mode 100644 index 0000000000..029bc49325 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000231.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_4 +letting j be n_2 +letting p be permutation((n_2, n_3, n_4)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000232.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000232.solution new file mode 100644 index 0000000000..3966eb048d --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000232.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_4 +letting j be n_4 +letting p be permutation((n_2, n_3, n_5)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000233.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000233.solution new file mode 100644 index 0000000000..0069029c64 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000233.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_4 +letting j be n_4 +letting p be permutation((n_2, n_3, n_6)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000234.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000234.solution new file mode 100644 index 0000000000..236159f04f --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000234.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_4 +letting j be n_4 +letting p be permutation((n_2, n_3, n_7)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000235.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000235.solution new file mode 100644 index 0000000000..4fa1f8c32f --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000235.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_4 +letting j be n_3 +letting p be permutation((n_2, n_4, n_3)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000236.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000236.solution new file mode 100644 index 0000000000..96330c731f --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000236.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_4 +letting j be n_5 +letting p be permutation((n_2, n_4, n_5)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000237.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000237.solution new file mode 100644 index 0000000000..eca4792789 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000237.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_4 +letting j be n_6 +letting p be permutation((n_2, n_4, n_6)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000238.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000238.solution new file mode 100644 index 0000000000..de059872fb --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000238.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_4 +letting j be n_7 +letting p be permutation((n_2, n_4, n_7)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000239.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000239.solution new file mode 100644 index 0000000000..1d13679ca0 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000239.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_4 +letting j be n_4 +letting p be permutation((n_2, n_5, n_3)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000240.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000240.solution new file mode 100644 index 0000000000..4013b4c3c2 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000240.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_4 +letting j be n_2 +letting p be permutation((n_2, n_5, n_4)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000241.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000241.solution new file mode 100644 index 0000000000..7f325656bc --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000241.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_4 +letting j be n_4 +letting p be permutation((n_2, n_5, n_6)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000242.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000242.solution new file mode 100644 index 0000000000..5bdf9e2c6b --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000242.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_4 +letting j be n_4 +letting p be permutation((n_2, n_5, n_7)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000243.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000243.solution new file mode 100644 index 0000000000..619bc69a31 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000243.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_4 +letting j be n_4 +letting p be permutation((n_2, n_6, n_3)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000244.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000244.solution new file mode 100644 index 0000000000..0d29f5f604 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000244.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_4 +letting j be n_2 +letting p be permutation((n_2, n_6, n_4)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000245.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000245.solution new file mode 100644 index 0000000000..e042f15878 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000245.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_4 +letting j be n_4 +letting p be permutation((n_2, n_6, n_5)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000246.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000246.solution new file mode 100644 index 0000000000..11e7c73d07 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000246.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_4 +letting j be n_4 +letting p be permutation((n_2, n_6, n_7)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000247.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000247.solution new file mode 100644 index 0000000000..370b1b921c --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000247.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_4 +letting j be n_4 +letting p be permutation((n_2, n_7, n_3)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000248.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000248.solution new file mode 100644 index 0000000000..f279b0dfaa --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000248.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_4 +letting j be n_2 +letting p be permutation((n_2, n_7, n_4)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000249.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000249.solution new file mode 100644 index 0000000000..92e1950c2b --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000249.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_4 +letting j be n_4 +letting p be permutation((n_2, n_7, n_5)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000250.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000250.solution new file mode 100644 index 0000000000..5c6dac277a --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000250.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_4 +letting j be n_4 +letting p be permutation((n_2, n_7, n_6)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000251.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000251.solution new file mode 100644 index 0000000000..331f5ee784 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000251.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_4 +letting j be n_4 +letting p be permutation((n_1, n_2, n_3)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000252.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000252.solution new file mode 100644 index 0000000000..32f571a591 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000252.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_4 +letting j be n_1 +letting p be permutation((n_1, n_2, n_4)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000253.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000253.solution new file mode 100644 index 0000000000..d37d742dab --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000253.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_4 +letting j be n_4 +letting p be permutation((n_1, n_2, n_5)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000254.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000254.solution new file mode 100644 index 0000000000..bc85f9cb2f --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000254.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_4 +letting j be n_4 +letting p be permutation((n_1, n_2, n_6)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000255.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000255.solution new file mode 100644 index 0000000000..d5eb887e9d --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000255.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_4 +letting j be n_4 +letting p be permutation((n_1, n_2, n_7)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000256.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000256.solution new file mode 100644 index 0000000000..b9b78c4571 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000256.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_4 +letting j be n_4 +letting p be permutation((n_1, n_3, n_2)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000257.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000257.solution new file mode 100644 index 0000000000..203b421ebf --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000257.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_4 +letting j be n_1 +letting p be permutation((n_1, n_3, n_4)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000258.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000258.solution new file mode 100644 index 0000000000..daf558a01d --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000258.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_4 +letting j be n_4 +letting p be permutation((n_1, n_3, n_5)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000259.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000259.solution new file mode 100644 index 0000000000..a7e4ad1896 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000259.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_4 +letting j be n_4 +letting p be permutation((n_1, n_3, n_6)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000260.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000260.solution new file mode 100644 index 0000000000..2c7a81e95b --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000260.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_4 +letting j be n_4 +letting p be permutation((n_1, n_3, n_7)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000261.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000261.solution new file mode 100644 index 0000000000..454cccc371 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000261.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_4 +letting j be n_2 +letting p be permutation((n_1, n_4, n_2)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000262.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000262.solution new file mode 100644 index 0000000000..5b6bb5c46d --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000262.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_4 +letting j be n_3 +letting p be permutation((n_1, n_4, n_3)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000263.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000263.solution new file mode 100644 index 0000000000..be71ef7795 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000263.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_4 +letting j be n_5 +letting p be permutation((n_1, n_4, n_5)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000264.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000264.solution new file mode 100644 index 0000000000..5f0a316996 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000264.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_4 +letting j be n_6 +letting p be permutation((n_1, n_4, n_6)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000265.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000265.solution new file mode 100644 index 0000000000..837c20abf2 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000265.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_4 +letting j be n_7 +letting p be permutation((n_1, n_4, n_7)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000266.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000266.solution new file mode 100644 index 0000000000..8326144d93 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000266.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_4 +letting j be n_4 +letting p be permutation((n_1, n_5, n_2)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000267.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000267.solution new file mode 100644 index 0000000000..5ad59ad76f --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000267.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_4 +letting j be n_4 +letting p be permutation((n_1, n_5, n_3)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000268.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000268.solution new file mode 100644 index 0000000000..f92cf64131 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000268.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_4 +letting j be n_1 +letting p be permutation((n_1, n_5, n_4)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000269.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000269.solution new file mode 100644 index 0000000000..90e28dfbb7 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000269.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_4 +letting j be n_4 +letting p be permutation((n_1, n_5, n_6)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000270.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000270.solution new file mode 100644 index 0000000000..ee3297a14d --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000270.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_4 +letting j be n_4 +letting p be permutation((n_1, n_5, n_7)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000271.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000271.solution new file mode 100644 index 0000000000..cb9e4c0e04 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000271.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_4 +letting j be n_4 +letting p be permutation((n_1, n_6, n_2)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000272.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000272.solution new file mode 100644 index 0000000000..6710ec48eb --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000272.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_4 +letting j be n_4 +letting p be permutation((n_1, n_6, n_3)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000273.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000273.solution new file mode 100644 index 0000000000..938e2e73d9 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000273.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_4 +letting j be n_1 +letting p be permutation((n_1, n_6, n_4)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000274.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000274.solution new file mode 100644 index 0000000000..b7e25038b7 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000274.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_4 +letting j be n_4 +letting p be permutation((n_1, n_6, n_5)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000275.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000275.solution new file mode 100644 index 0000000000..ae26588517 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000275.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_4 +letting j be n_4 +letting p be permutation((n_1, n_6, n_7)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000276.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000276.solution new file mode 100644 index 0000000000..9cf6b5607d --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000276.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_4 +letting j be n_4 +letting p be permutation((n_1, n_7, n_2)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000277.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000277.solution new file mode 100644 index 0000000000..e38467e19e --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000277.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_4 +letting j be n_4 +letting p be permutation((n_1, n_7, n_3)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000278.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000278.solution new file mode 100644 index 0000000000..03ef4d1280 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000278.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_4 +letting j be n_1 +letting p be permutation((n_1, n_7, n_4)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000279.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000279.solution new file mode 100644 index 0000000000..371618d9d0 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000279.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_4 +letting j be n_4 +letting p be permutation((n_1, n_7, n_5)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000280.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000280.solution new file mode 100644 index 0000000000..6a5e2cb49a --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000280.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_4 +letting j be n_4 +letting p be permutation((n_1, n_7, n_6)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000281.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000281.solution new file mode 100644 index 0000000000..34dce7c805 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000281.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_5 +letting j be n_6 +letting p be permutation((n_5, n_6, n_7)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000282.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000282.solution new file mode 100644 index 0000000000..66775dade2 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000282.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_5 +letting j be n_7 +letting p be permutation((n_5, n_7, n_6)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000283.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000283.solution new file mode 100644 index 0000000000..a0506596b2 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000283.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_5 +letting j be n_6 +letting p be permutation((n_4, n_5, n_6)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000284.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000284.solution new file mode 100644 index 0000000000..10ac50c9d4 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000284.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_5 +letting j be n_7 +letting p be permutation((n_4, n_5, n_7)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000285.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000285.solution new file mode 100644 index 0000000000..df1be0aebf --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000285.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_5 +letting j be n_4 +letting p be permutation((n_4, n_6, n_5)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000286.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000286.solution new file mode 100644 index 0000000000..ae784cc500 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000286.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_5 +letting j be n_5 +letting p be permutation((n_4, n_6, n_7)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000287.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000287.solution new file mode 100644 index 0000000000..6c877ef370 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000287.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_5 +letting j be n_4 +letting p be permutation((n_4, n_7, n_5)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000288.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000288.solution new file mode 100644 index 0000000000..80e623c98f --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000288.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_5 +letting j be n_5 +letting p be permutation((n_4, n_7, n_6)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000289.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000289.solution new file mode 100644 index 0000000000..7bb8fa4fe6 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000289.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_5 +letting j be n_3 +letting p be permutation((n_3, n_4, n_5)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000290.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000290.solution new file mode 100644 index 0000000000..a545063f07 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000290.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_5 +letting j be n_5 +letting p be permutation((n_3, n_4, n_6)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000291.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000291.solution new file mode 100644 index 0000000000..1728e8709e --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000291.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_5 +letting j be n_5 +letting p be permutation((n_3, n_4, n_7)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000292.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000292.solution new file mode 100644 index 0000000000..8f0117a4e6 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000292.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_5 +letting j be n_4 +letting p be permutation((n_3, n_5, n_4)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000293.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000293.solution new file mode 100644 index 0000000000..f711df4402 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000293.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_5 +letting j be n_6 +letting p be permutation((n_3, n_5, n_6)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000294.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000294.solution new file mode 100644 index 0000000000..58f8edb996 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000294.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_5 +letting j be n_7 +letting p be permutation((n_3, n_5, n_7)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000295.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000295.solution new file mode 100644 index 0000000000..4142f6bd21 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000295.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_5 +letting j be n_5 +letting p be permutation((n_3, n_6, n_4)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000296.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000296.solution new file mode 100644 index 0000000000..f4bd157aef --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000296.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_5 +letting j be n_3 +letting p be permutation((n_3, n_6, n_5)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000297.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000297.solution new file mode 100644 index 0000000000..2d696c60ab --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000297.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_5 +letting j be n_5 +letting p be permutation((n_3, n_6, n_7)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000298.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000298.solution new file mode 100644 index 0000000000..19f5874ca2 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000298.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_5 +letting j be n_5 +letting p be permutation((n_3, n_7, n_4)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000299.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000299.solution new file mode 100644 index 0000000000..a5d94eb2e2 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000299.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_5 +letting j be n_3 +letting p be permutation((n_3, n_7, n_5)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000300.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000300.solution new file mode 100644 index 0000000000..911ae849a9 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000300.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_5 +letting j be n_5 +letting p be permutation((n_3, n_7, n_6)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000301.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000301.solution new file mode 100644 index 0000000000..b2f5481ab2 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000301.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_5 +letting j be n_5 +letting p be permutation((n_2, n_3, n_4)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000302.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000302.solution new file mode 100644 index 0000000000..884521180d --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000302.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_5 +letting j be n_2 +letting p be permutation((n_2, n_3, n_5)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000303.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000303.solution new file mode 100644 index 0000000000..7b0d8aa96f --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000303.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_5 +letting j be n_5 +letting p be permutation((n_2, n_3, n_6)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000304.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000304.solution new file mode 100644 index 0000000000..3fea301528 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000304.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_5 +letting j be n_5 +letting p be permutation((n_2, n_3, n_7)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000305.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000305.solution new file mode 100644 index 0000000000..684bee90ef --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000305.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_5 +letting j be n_5 +letting p be permutation((n_2, n_4, n_3)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000306.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000306.solution new file mode 100644 index 0000000000..39b38ebcfa --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000306.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_5 +letting j be n_2 +letting p be permutation((n_2, n_4, n_5)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000307.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000307.solution new file mode 100644 index 0000000000..b4a85c8756 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000307.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_5 +letting j be n_5 +letting p be permutation((n_2, n_4, n_6)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000308.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000308.solution new file mode 100644 index 0000000000..6c833e3466 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000308.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_5 +letting j be n_5 +letting p be permutation((n_2, n_4, n_7)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000309.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000309.solution new file mode 100644 index 0000000000..326dfd393b --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000309.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_5 +letting j be n_3 +letting p be permutation((n_2, n_5, n_3)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000310.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000310.solution new file mode 100644 index 0000000000..431e58f27e --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000310.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_5 +letting j be n_4 +letting p be permutation((n_2, n_5, n_4)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000311.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000311.solution new file mode 100644 index 0000000000..3b84bd7b39 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000311.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_5 +letting j be n_6 +letting p be permutation((n_2, n_5, n_6)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000312.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000312.solution new file mode 100644 index 0000000000..774e3741f2 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000312.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_5 +letting j be n_7 +letting p be permutation((n_2, n_5, n_7)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000313.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000313.solution new file mode 100644 index 0000000000..1f0f400f40 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000313.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_5 +letting j be n_5 +letting p be permutation((n_2, n_6, n_3)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000314.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000314.solution new file mode 100644 index 0000000000..fa66214892 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000314.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_5 +letting j be n_5 +letting p be permutation((n_2, n_6, n_4)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000315.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000315.solution new file mode 100644 index 0000000000..fb0434d702 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000315.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_5 +letting j be n_2 +letting p be permutation((n_2, n_6, n_5)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000316.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000316.solution new file mode 100644 index 0000000000..2a70b292f9 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000316.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_5 +letting j be n_5 +letting p be permutation((n_2, n_6, n_7)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000317.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000317.solution new file mode 100644 index 0000000000..636c3df91f --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000317.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_5 +letting j be n_5 +letting p be permutation((n_2, n_7, n_3)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000318.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000318.solution new file mode 100644 index 0000000000..8385d5951c --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000318.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_5 +letting j be n_5 +letting p be permutation((n_2, n_7, n_4)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000319.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000319.solution new file mode 100644 index 0000000000..02dfb2ce7d --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000319.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_5 +letting j be n_2 +letting p be permutation((n_2, n_7, n_5)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000320.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000320.solution new file mode 100644 index 0000000000..61292cf914 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000320.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_5 +letting j be n_5 +letting p be permutation((n_2, n_7, n_6)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000321.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000321.solution new file mode 100644 index 0000000000..ffdb97f234 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000321.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_5 +letting j be n_5 +letting p be permutation((n_1, n_2, n_3)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000322.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000322.solution new file mode 100644 index 0000000000..ea4e0e8fa0 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000322.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_5 +letting j be n_5 +letting p be permutation((n_1, n_2, n_4)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000323.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000323.solution new file mode 100644 index 0000000000..cd55c5120c --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000323.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_5 +letting j be n_1 +letting p be permutation((n_1, n_2, n_5)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000324.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000324.solution new file mode 100644 index 0000000000..5c6a2d2a9b --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000324.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_5 +letting j be n_5 +letting p be permutation((n_1, n_2, n_6)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000325.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000325.solution new file mode 100644 index 0000000000..3032bcd7d0 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000325.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_5 +letting j be n_5 +letting p be permutation((n_1, n_2, n_7)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000326.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000326.solution new file mode 100644 index 0000000000..2e2ca4c002 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000326.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_5 +letting j be n_5 +letting p be permutation((n_1, n_3, n_2)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000327.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000327.solution new file mode 100644 index 0000000000..47d1906ec9 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000327.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_5 +letting j be n_5 +letting p be permutation((n_1, n_3, n_4)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000328.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000328.solution new file mode 100644 index 0000000000..ff3569c248 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000328.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_5 +letting j be n_1 +letting p be permutation((n_1, n_3, n_5)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000329.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000329.solution new file mode 100644 index 0000000000..d1f176ec48 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000329.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_5 +letting j be n_5 +letting p be permutation((n_1, n_3, n_6)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000330.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000330.solution new file mode 100644 index 0000000000..20f2030c41 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000330.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_5 +letting j be n_5 +letting p be permutation((n_1, n_3, n_7)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000331.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000331.solution new file mode 100644 index 0000000000..44688d5209 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000331.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_5 +letting j be n_5 +letting p be permutation((n_1, n_4, n_2)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000332.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000332.solution new file mode 100644 index 0000000000..bc3625b0af --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000332.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_5 +letting j be n_5 +letting p be permutation((n_1, n_4, n_3)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000333.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000333.solution new file mode 100644 index 0000000000..fe410e211d --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000333.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_5 +letting j be n_1 +letting p be permutation((n_1, n_4, n_5)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000334.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000334.solution new file mode 100644 index 0000000000..02e8e84b2c --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000334.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_5 +letting j be n_5 +letting p be permutation((n_1, n_4, n_6)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000335.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000335.solution new file mode 100644 index 0000000000..9ae3266106 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000335.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_5 +letting j be n_5 +letting p be permutation((n_1, n_4, n_7)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000336.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000336.solution new file mode 100644 index 0000000000..4faccb05b7 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000336.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_5 +letting j be n_2 +letting p be permutation((n_1, n_5, n_2)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000337.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000337.solution new file mode 100644 index 0000000000..d8a71a5cf7 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000337.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_5 +letting j be n_3 +letting p be permutation((n_1, n_5, n_3)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000338.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000338.solution new file mode 100644 index 0000000000..93e20bf878 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000338.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_5 +letting j be n_4 +letting p be permutation((n_1, n_5, n_4)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000339.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000339.solution new file mode 100644 index 0000000000..a2fbc53646 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000339.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_5 +letting j be n_6 +letting p be permutation((n_1, n_5, n_6)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000340.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000340.solution new file mode 100644 index 0000000000..4a7b8d74d5 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000340.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_5 +letting j be n_7 +letting p be permutation((n_1, n_5, n_7)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000341.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000341.solution new file mode 100644 index 0000000000..4c87919ecc --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000341.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_5 +letting j be n_5 +letting p be permutation((n_1, n_6, n_2)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000342.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000342.solution new file mode 100644 index 0000000000..ecc8e7c3d4 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000342.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_5 +letting j be n_5 +letting p be permutation((n_1, n_6, n_3)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000343.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000343.solution new file mode 100644 index 0000000000..3cdac07da4 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000343.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_5 +letting j be n_5 +letting p be permutation((n_1, n_6, n_4)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000344.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000344.solution new file mode 100644 index 0000000000..98dadd1aac --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000344.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_5 +letting j be n_1 +letting p be permutation((n_1, n_6, n_5)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000345.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000345.solution new file mode 100644 index 0000000000..eaa497c329 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000345.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_5 +letting j be n_5 +letting p be permutation((n_1, n_6, n_7)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000346.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000346.solution new file mode 100644 index 0000000000..41e6f5dc38 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000346.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_5 +letting j be n_5 +letting p be permutation((n_1, n_7, n_2)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000347.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000347.solution new file mode 100644 index 0000000000..87f774f2ef --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000347.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_5 +letting j be n_5 +letting p be permutation((n_1, n_7, n_3)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000348.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000348.solution new file mode 100644 index 0000000000..f4b2ccd663 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000348.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_5 +letting j be n_5 +letting p be permutation((n_1, n_7, n_4)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000349.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000349.solution new file mode 100644 index 0000000000..2ce3715eea --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000349.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_5 +letting j be n_1 +letting p be permutation((n_1, n_7, n_5)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000350.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000350.solution new file mode 100644 index 0000000000..5f862615a8 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000350.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_5 +letting j be n_5 +letting p be permutation((n_1, n_7, n_6)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000351.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000351.solution new file mode 100644 index 0000000000..ab8eb9676c --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000351.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_6 +letting j be n_7 +letting p be permutation((n_5, n_6, n_7)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000352.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000352.solution new file mode 100644 index 0000000000..4225102ee0 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000352.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_6 +letting j be n_5 +letting p be permutation((n_5, n_7, n_6)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000353.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000353.solution new file mode 100644 index 0000000000..778eaccca5 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000353.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_6 +letting j be n_4 +letting p be permutation((n_4, n_5, n_6)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000354.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000354.solution new file mode 100644 index 0000000000..1930c88935 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000354.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_6 +letting j be n_6 +letting p be permutation((n_4, n_5, n_7)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000355.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000355.solution new file mode 100644 index 0000000000..ecdc2feb4c --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000355.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_6 +letting j be n_5 +letting p be permutation((n_4, n_6, n_5)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000356.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000356.solution new file mode 100644 index 0000000000..6f47717723 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000356.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_6 +letting j be n_7 +letting p be permutation((n_4, n_6, n_7)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000357.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000357.solution new file mode 100644 index 0000000000..14bc3e6556 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000357.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_6 +letting j be n_6 +letting p be permutation((n_4, n_7, n_5)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000358.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000358.solution new file mode 100644 index 0000000000..4046f8f508 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000358.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_6 +letting j be n_4 +letting p be permutation((n_4, n_7, n_6)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000359.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000359.solution new file mode 100644 index 0000000000..ddd05e7052 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000359.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_6 +letting j be n_6 +letting p be permutation((n_3, n_4, n_5)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000360.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000360.solution new file mode 100644 index 0000000000..bd1ee12726 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000360.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_6 +letting j be n_3 +letting p be permutation((n_3, n_4, n_6)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000361.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000361.solution new file mode 100644 index 0000000000..2cec909221 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000361.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_6 +letting j be n_6 +letting p be permutation((n_3, n_4, n_7)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000362.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000362.solution new file mode 100644 index 0000000000..8db4a88ef1 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000362.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_6 +letting j be n_6 +letting p be permutation((n_3, n_5, n_4)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000363.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000363.solution new file mode 100644 index 0000000000..bfee9fd242 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000363.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_6 +letting j be n_3 +letting p be permutation((n_3, n_5, n_6)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000364.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000364.solution new file mode 100644 index 0000000000..364e3e3628 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000364.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_6 +letting j be n_6 +letting p be permutation((n_3, n_5, n_7)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000365.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000365.solution new file mode 100644 index 0000000000..4f2386d100 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000365.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_6 +letting j be n_4 +letting p be permutation((n_3, n_6, n_4)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000366.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000366.solution new file mode 100644 index 0000000000..7dd9e1e7e0 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000366.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_6 +letting j be n_5 +letting p be permutation((n_3, n_6, n_5)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000367.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000367.solution new file mode 100644 index 0000000000..d00b3197d0 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000367.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_6 +letting j be n_7 +letting p be permutation((n_3, n_6, n_7)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000368.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000368.solution new file mode 100644 index 0000000000..afab028ce0 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000368.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_6 +letting j be n_6 +letting p be permutation((n_3, n_7, n_4)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000369.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000369.solution new file mode 100644 index 0000000000..dd98453ffb --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000369.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_6 +letting j be n_6 +letting p be permutation((n_3, n_7, n_5)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000370.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000370.solution new file mode 100644 index 0000000000..298b4e1ed3 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000370.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_6 +letting j be n_3 +letting p be permutation((n_3, n_7, n_6)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000371.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000371.solution new file mode 100644 index 0000000000..2243791f60 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000371.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_6 +letting j be n_6 +letting p be permutation((n_2, n_3, n_4)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000372.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000372.solution new file mode 100644 index 0000000000..693e519679 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000372.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_6 +letting j be n_6 +letting p be permutation((n_2, n_3, n_5)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000373.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000373.solution new file mode 100644 index 0000000000..3686f6b045 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000373.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_6 +letting j be n_2 +letting p be permutation((n_2, n_3, n_6)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000374.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000374.solution new file mode 100644 index 0000000000..7a094c0d2e --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000374.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_6 +letting j be n_6 +letting p be permutation((n_2, n_3, n_7)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000375.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000375.solution new file mode 100644 index 0000000000..4a87236542 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000375.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_6 +letting j be n_6 +letting p be permutation((n_2, n_4, n_3)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000376.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000376.solution new file mode 100644 index 0000000000..ebe2f9c301 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000376.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_6 +letting j be n_6 +letting p be permutation((n_2, n_4, n_5)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000377.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000377.solution new file mode 100644 index 0000000000..ae44a43055 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000377.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_6 +letting j be n_2 +letting p be permutation((n_2, n_4, n_6)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000378.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000378.solution new file mode 100644 index 0000000000..dff18f5d7e --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000378.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_6 +letting j be n_6 +letting p be permutation((n_2, n_4, n_7)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000379.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000379.solution new file mode 100644 index 0000000000..4130f1daf4 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000379.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_6 +letting j be n_6 +letting p be permutation((n_2, n_5, n_3)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000380.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000380.solution new file mode 100644 index 0000000000..6b774194d3 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000380.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_6 +letting j be n_6 +letting p be permutation((n_2, n_5, n_4)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000381.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000381.solution new file mode 100644 index 0000000000..729d4e6581 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000381.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_6 +letting j be n_2 +letting p be permutation((n_2, n_5, n_6)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000382.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000382.solution new file mode 100644 index 0000000000..9d78627c8b --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000382.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_6 +letting j be n_6 +letting p be permutation((n_2, n_5, n_7)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000383.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000383.solution new file mode 100644 index 0000000000..f6a97aa660 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000383.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_6 +letting j be n_3 +letting p be permutation((n_2, n_6, n_3)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000384.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000384.solution new file mode 100644 index 0000000000..f3ee39dcdc --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000384.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_6 +letting j be n_4 +letting p be permutation((n_2, n_6, n_4)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000385.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000385.solution new file mode 100644 index 0000000000..3d20e74b7c --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000385.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_6 +letting j be n_5 +letting p be permutation((n_2, n_6, n_5)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000386.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000386.solution new file mode 100644 index 0000000000..4ff719a21b --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000386.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_6 +letting j be n_7 +letting p be permutation((n_2, n_6, n_7)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000387.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000387.solution new file mode 100644 index 0000000000..82a58ca26c --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000387.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_6 +letting j be n_6 +letting p be permutation((n_2, n_7, n_3)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000388.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000388.solution new file mode 100644 index 0000000000..bbc3b22665 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000388.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_6 +letting j be n_6 +letting p be permutation((n_2, n_7, n_4)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000389.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000389.solution new file mode 100644 index 0000000000..3148ad40ab --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000389.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_6 +letting j be n_6 +letting p be permutation((n_2, n_7, n_5)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000390.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000390.solution new file mode 100644 index 0000000000..bf1034c271 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000390.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_6 +letting j be n_2 +letting p be permutation((n_2, n_7, n_6)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000391.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000391.solution new file mode 100644 index 0000000000..b9d0261916 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000391.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_6 +letting j be n_6 +letting p be permutation((n_1, n_2, n_3)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000392.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000392.solution new file mode 100644 index 0000000000..e2a2101319 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000392.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_6 +letting j be n_6 +letting p be permutation((n_1, n_2, n_4)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000393.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000393.solution new file mode 100644 index 0000000000..b0dd0b9d79 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000393.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_6 +letting j be n_6 +letting p be permutation((n_1, n_2, n_5)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000394.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000394.solution new file mode 100644 index 0000000000..081e2edbcb --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000394.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_6 +letting j be n_1 +letting p be permutation((n_1, n_2, n_6)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000395.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000395.solution new file mode 100644 index 0000000000..473a2ad2da --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000395.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_6 +letting j be n_6 +letting p be permutation((n_1, n_2, n_7)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000396.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000396.solution new file mode 100644 index 0000000000..2f8a9ffa93 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000396.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_6 +letting j be n_6 +letting p be permutation((n_1, n_3, n_2)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000397.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000397.solution new file mode 100644 index 0000000000..e1b017a6d1 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000397.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_6 +letting j be n_6 +letting p be permutation((n_1, n_3, n_4)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000398.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000398.solution new file mode 100644 index 0000000000..fd77dd2abe --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000398.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_6 +letting j be n_6 +letting p be permutation((n_1, n_3, n_5)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000399.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000399.solution new file mode 100644 index 0000000000..add2a6d721 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000399.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_6 +letting j be n_1 +letting p be permutation((n_1, n_3, n_6)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000400.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000400.solution new file mode 100644 index 0000000000..b3c5709d65 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000400.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_6 +letting j be n_6 +letting p be permutation((n_1, n_3, n_7)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000401.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000401.solution new file mode 100644 index 0000000000..f1e7d09bac --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000401.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_6 +letting j be n_6 +letting p be permutation((n_1, n_4, n_2)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000402.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000402.solution new file mode 100644 index 0000000000..6a5d264cd9 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000402.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_6 +letting j be n_6 +letting p be permutation((n_1, n_4, n_3)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000403.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000403.solution new file mode 100644 index 0000000000..67bfeec694 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000403.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_6 +letting j be n_6 +letting p be permutation((n_1, n_4, n_5)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000404.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000404.solution new file mode 100644 index 0000000000..096065a1a4 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000404.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_6 +letting j be n_1 +letting p be permutation((n_1, n_4, n_6)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000405.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000405.solution new file mode 100644 index 0000000000..95af0f3e8c --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000405.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_6 +letting j be n_6 +letting p be permutation((n_1, n_4, n_7)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000406.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000406.solution new file mode 100644 index 0000000000..51e68389b6 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000406.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_6 +letting j be n_6 +letting p be permutation((n_1, n_5, n_2)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000407.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000407.solution new file mode 100644 index 0000000000..36b699f540 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000407.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_6 +letting j be n_6 +letting p be permutation((n_1, n_5, n_3)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000408.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000408.solution new file mode 100644 index 0000000000..21ebc6ead9 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000408.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_6 +letting j be n_6 +letting p be permutation((n_1, n_5, n_4)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000409.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000409.solution new file mode 100644 index 0000000000..e41a818214 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000409.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_6 +letting j be n_1 +letting p be permutation((n_1, n_5, n_6)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000410.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000410.solution new file mode 100644 index 0000000000..c7f623c069 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000410.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_6 +letting j be n_6 +letting p be permutation((n_1, n_5, n_7)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000411.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000411.solution new file mode 100644 index 0000000000..4fd685be5c --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000411.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_6 +letting j be n_2 +letting p be permutation((n_1, n_6, n_2)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000412.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000412.solution new file mode 100644 index 0000000000..cd9a2832a1 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000412.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_6 +letting j be n_3 +letting p be permutation((n_1, n_6, n_3)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000413.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000413.solution new file mode 100644 index 0000000000..9e26465901 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000413.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_6 +letting j be n_4 +letting p be permutation((n_1, n_6, n_4)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000414.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000414.solution new file mode 100644 index 0000000000..19b13802d0 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000414.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_6 +letting j be n_5 +letting p be permutation((n_1, n_6, n_5)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000415.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000415.solution new file mode 100644 index 0000000000..637d4b2b8e --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000415.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_6 +letting j be n_7 +letting p be permutation((n_1, n_6, n_7)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000416.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000416.solution new file mode 100644 index 0000000000..1e02d59900 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000416.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_6 +letting j be n_6 +letting p be permutation((n_1, n_7, n_2)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000417.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000417.solution new file mode 100644 index 0000000000..c282fac0e1 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000417.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_6 +letting j be n_6 +letting p be permutation((n_1, n_7, n_3)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000418.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000418.solution new file mode 100644 index 0000000000..07d94df0f5 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000418.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_6 +letting j be n_6 +letting p be permutation((n_1, n_7, n_4)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000419.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000419.solution new file mode 100644 index 0000000000..a7b0923a62 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000419.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_6 +letting j be n_6 +letting p be permutation((n_1, n_7, n_5)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000420.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000420.solution new file mode 100644 index 0000000000..2993be52c3 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000420.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_6 +letting j be n_1 +letting p be permutation((n_1, n_7, n_6)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000421.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000421.solution new file mode 100644 index 0000000000..a86df812a9 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000421.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_7 +letting j be n_5 +letting p be permutation((n_5, n_6, n_7)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000422.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000422.solution new file mode 100644 index 0000000000..885b913028 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000422.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_7 +letting j be n_6 +letting p be permutation((n_5, n_7, n_6)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000423.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000423.solution new file mode 100644 index 0000000000..5b5e3aeb7b --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000423.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_7 +letting j be n_7 +letting p be permutation((n_4, n_5, n_6)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000424.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000424.solution new file mode 100644 index 0000000000..1f947fea93 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000424.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_7 +letting j be n_4 +letting p be permutation((n_4, n_5, n_7)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000425.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000425.solution new file mode 100644 index 0000000000..5b3683a20d --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000425.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_7 +letting j be n_7 +letting p be permutation((n_4, n_6, n_5)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000426.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000426.solution new file mode 100644 index 0000000000..2902ca455d --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000426.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_7 +letting j be n_4 +letting p be permutation((n_4, n_6, n_7)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000427.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000427.solution new file mode 100644 index 0000000000..487493052a --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000427.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_7 +letting j be n_5 +letting p be permutation((n_4, n_7, n_5)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000428.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000428.solution new file mode 100644 index 0000000000..aa253691ad --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000428.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_7 +letting j be n_6 +letting p be permutation((n_4, n_7, n_6)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000429.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000429.solution new file mode 100644 index 0000000000..ddbefc0756 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000429.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_7 +letting j be n_7 +letting p be permutation((n_3, n_4, n_5)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000430.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000430.solution new file mode 100644 index 0000000000..32699822ed --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000430.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_7 +letting j be n_7 +letting p be permutation((n_3, n_4, n_6)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000431.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000431.solution new file mode 100644 index 0000000000..2d15364df7 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000431.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_7 +letting j be n_3 +letting p be permutation((n_3, n_4, n_7)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000432.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000432.solution new file mode 100644 index 0000000000..5441228c4d --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000432.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_7 +letting j be n_7 +letting p be permutation((n_3, n_5, n_4)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000433.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000433.solution new file mode 100644 index 0000000000..f1ee9de6f1 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000433.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_7 +letting j be n_7 +letting p be permutation((n_3, n_5, n_6)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000434.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000434.solution new file mode 100644 index 0000000000..bf36ff07ea --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000434.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_7 +letting j be n_3 +letting p be permutation((n_3, n_5, n_7)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000435.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000435.solution new file mode 100644 index 0000000000..df29790154 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000435.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_7 +letting j be n_7 +letting p be permutation((n_3, n_6, n_4)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000436.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000436.solution new file mode 100644 index 0000000000..db90731636 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000436.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_7 +letting j be n_7 +letting p be permutation((n_3, n_6, n_5)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000437.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000437.solution new file mode 100644 index 0000000000..1ea5e8e414 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000437.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_7 +letting j be n_3 +letting p be permutation((n_3, n_6, n_7)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000438.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000438.solution new file mode 100644 index 0000000000..baf4ecef7d --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000438.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_7 +letting j be n_4 +letting p be permutation((n_3, n_7, n_4)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000439.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000439.solution new file mode 100644 index 0000000000..8409145272 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000439.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_7 +letting j be n_5 +letting p be permutation((n_3, n_7, n_5)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000440.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000440.solution new file mode 100644 index 0000000000..e41cd97cd1 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000440.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_7 +letting j be n_6 +letting p be permutation((n_3, n_7, n_6)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000441.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000441.solution new file mode 100644 index 0000000000..9e58c2bc0f --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000441.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_7 +letting j be n_7 +letting p be permutation((n_2, n_3, n_4)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000442.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000442.solution new file mode 100644 index 0000000000..c4908edfda --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000442.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_7 +letting j be n_7 +letting p be permutation((n_2, n_3, n_5)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000443.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000443.solution new file mode 100644 index 0000000000..bfcf196883 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000443.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_7 +letting j be n_7 +letting p be permutation((n_2, n_3, n_6)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000444.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000444.solution new file mode 100644 index 0000000000..43556ada3f --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000444.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_7 +letting j be n_2 +letting p be permutation((n_2, n_3, n_7)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000445.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000445.solution new file mode 100644 index 0000000000..aae4c3549a --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000445.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_7 +letting j be n_7 +letting p be permutation((n_2, n_4, n_3)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000446.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000446.solution new file mode 100644 index 0000000000..3bc01b24c1 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000446.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_7 +letting j be n_7 +letting p be permutation((n_2, n_4, n_5)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000447.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000447.solution new file mode 100644 index 0000000000..37f44d93d7 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000447.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_7 +letting j be n_7 +letting p be permutation((n_2, n_4, n_6)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000448.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000448.solution new file mode 100644 index 0000000000..41d079e76f --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000448.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_7 +letting j be n_2 +letting p be permutation((n_2, n_4, n_7)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000449.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000449.solution new file mode 100644 index 0000000000..20f1a380ee --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000449.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_7 +letting j be n_7 +letting p be permutation((n_2, n_5, n_3)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000450.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000450.solution new file mode 100644 index 0000000000..0192485a06 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000450.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_7 +letting j be n_7 +letting p be permutation((n_2, n_5, n_4)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000451.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000451.solution new file mode 100644 index 0000000000..0faabeba7c --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000451.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_7 +letting j be n_7 +letting p be permutation((n_2, n_5, n_6)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000452.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000452.solution new file mode 100644 index 0000000000..b4c49e4a50 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000452.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_7 +letting j be n_2 +letting p be permutation((n_2, n_5, n_7)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000453.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000453.solution new file mode 100644 index 0000000000..956c1e1c3c --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000453.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_7 +letting j be n_7 +letting p be permutation((n_2, n_6, n_3)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000454.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000454.solution new file mode 100644 index 0000000000..eb42ae9909 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000454.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_7 +letting j be n_7 +letting p be permutation((n_2, n_6, n_4)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000455.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000455.solution new file mode 100644 index 0000000000..2bf907c354 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000455.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_7 +letting j be n_7 +letting p be permutation((n_2, n_6, n_5)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000456.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000456.solution new file mode 100644 index 0000000000..f426acbbf2 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000456.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_7 +letting j be n_2 +letting p be permutation((n_2, n_6, n_7)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000457.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000457.solution new file mode 100644 index 0000000000..f3f94d39d2 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000457.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_7 +letting j be n_3 +letting p be permutation((n_2, n_7, n_3)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000458.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000458.solution new file mode 100644 index 0000000000..2f2a150cb4 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000458.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_7 +letting j be n_4 +letting p be permutation((n_2, n_7, n_4)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000459.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000459.solution new file mode 100644 index 0000000000..f66d3eaa21 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000459.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_7 +letting j be n_5 +letting p be permutation((n_2, n_7, n_5)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000460.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000460.solution new file mode 100644 index 0000000000..b8cf6e0c75 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000460.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_7 +letting j be n_6 +letting p be permutation((n_2, n_7, n_6)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000461.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000461.solution new file mode 100644 index 0000000000..445dc76460 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000461.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_7 +letting j be n_7 +letting p be permutation((n_1, n_2, n_3)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000462.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000462.solution new file mode 100644 index 0000000000..1b24a83489 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000462.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_7 +letting j be n_7 +letting p be permutation((n_1, n_2, n_4)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000463.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000463.solution new file mode 100644 index 0000000000..533f28f0f2 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000463.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_7 +letting j be n_7 +letting p be permutation((n_1, n_2, n_5)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000464.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000464.solution new file mode 100644 index 0000000000..d35f671bc2 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000464.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_7 +letting j be n_7 +letting p be permutation((n_1, n_2, n_6)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000465.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000465.solution new file mode 100644 index 0000000000..8d854d60dd --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000465.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_7 +letting j be n_1 +letting p be permutation((n_1, n_2, n_7)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000466.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000466.solution new file mode 100644 index 0000000000..b18b70f537 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000466.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_7 +letting j be n_7 +letting p be permutation((n_1, n_3, n_2)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000467.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000467.solution new file mode 100644 index 0000000000..990e838f31 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000467.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_7 +letting j be n_7 +letting p be permutation((n_1, n_3, n_4)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000468.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000468.solution new file mode 100644 index 0000000000..a3d8a47efb --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000468.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_7 +letting j be n_7 +letting p be permutation((n_1, n_3, n_5)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000469.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000469.solution new file mode 100644 index 0000000000..b10496956d --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000469.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_7 +letting j be n_7 +letting p be permutation((n_1, n_3, n_6)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000470.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000470.solution new file mode 100644 index 0000000000..f011f9222f --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000470.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_7 +letting j be n_1 +letting p be permutation((n_1, n_3, n_7)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000471.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000471.solution new file mode 100644 index 0000000000..4abb9c6f5d --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000471.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_7 +letting j be n_7 +letting p be permutation((n_1, n_4, n_2)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000472.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000472.solution new file mode 100644 index 0000000000..70f8da69c4 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000472.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_7 +letting j be n_7 +letting p be permutation((n_1, n_4, n_3)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000473.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000473.solution new file mode 100644 index 0000000000..a199e367e8 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000473.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_7 +letting j be n_7 +letting p be permutation((n_1, n_4, n_5)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000474.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000474.solution new file mode 100644 index 0000000000..c4dd1a9436 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000474.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_7 +letting j be n_7 +letting p be permutation((n_1, n_4, n_6)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000475.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000475.solution new file mode 100644 index 0000000000..32edffbc2f --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000475.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_7 +letting j be n_1 +letting p be permutation((n_1, n_4, n_7)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000476.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000476.solution new file mode 100644 index 0000000000..70626165fa --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000476.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_7 +letting j be n_7 +letting p be permutation((n_1, n_5, n_2)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000477.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000477.solution new file mode 100644 index 0000000000..4e0ac72aeb --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000477.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_7 +letting j be n_7 +letting p be permutation((n_1, n_5, n_3)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000478.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000478.solution new file mode 100644 index 0000000000..b5c7be313d --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000478.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_7 +letting j be n_7 +letting p be permutation((n_1, n_5, n_4)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000479.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000479.solution new file mode 100644 index 0000000000..21f3b1fe6f --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000479.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_7 +letting j be n_7 +letting p be permutation((n_1, n_5, n_6)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000480.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000480.solution new file mode 100644 index 0000000000..241e8449c0 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000480.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_7 +letting j be n_1 +letting p be permutation((n_1, n_5, n_7)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000481.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000481.solution new file mode 100644 index 0000000000..a8b7dd8632 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000481.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_7 +letting j be n_7 +letting p be permutation((n_1, n_6, n_2)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000482.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000482.solution new file mode 100644 index 0000000000..c70419115c --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000482.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_7 +letting j be n_7 +letting p be permutation((n_1, n_6, n_3)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000483.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000483.solution new file mode 100644 index 0000000000..94c19774fd --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000483.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_7 +letting j be n_7 +letting p be permutation((n_1, n_6, n_4)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000484.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000484.solution new file mode 100644 index 0000000000..0ecb242af5 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000484.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_7 +letting j be n_7 +letting p be permutation((n_1, n_6, n_5)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000485.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000485.solution new file mode 100644 index 0000000000..5ab43a337f --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000485.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_7 +letting j be n_1 +letting p be permutation((n_1, n_6, n_7)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000486.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000486.solution new file mode 100644 index 0000000000..4722c285a7 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000486.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_7 +letting j be n_2 +letting p be permutation((n_1, n_7, n_2)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000487.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000487.solution new file mode 100644 index 0000000000..3cbeef6524 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000487.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_7 +letting j be n_3 +letting p be permutation((n_1, n_7, n_3)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000488.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000488.solution new file mode 100644 index 0000000000..48762327de --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000488.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_7 +letting j be n_4 +letting p be permutation((n_1, n_7, n_4)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000489.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000489.solution new file mode 100644 index 0000000000..a32b06707e --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000489.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_7 +letting j be n_5 +letting p be permutation((n_1, n_7, n_5)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000490.solution b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000490.solution new file mode 100644 index 0000000000..752a4db8ab --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model-solution000490.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4, n_5, n_6, n_7} +letting i be n_7 +letting j be n_6 +letting p be permutation((n_1, n_7, n_6)) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model.eprime b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model.eprime new file mode 100644 index 0000000000..d74675d6b2 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model.eprime @@ -0,0 +1,17 @@ +language ESSENCE' 1.0 + +find i: int(1..7) +find p_PermutationAsFunction_PermutationFunction_Function1D: matrix indexed by [int(1..7)] of int(1..7) +find j: int(1..7) +branching on [i, p_PermutationAsFunction_PermutationFunction_Function1D, j] +such that + j = + [i, catchUndef(p_PermutationAsFunction_PermutationFunction_Function1D[i], 0); int(1..2)] + [toInt(or([q6 = i | q6 : int(1..7)])) + 1], + sum([toInt(q13 != p_PermutationAsFunction_PermutationFunction_Function1D[q13]) * + catchUndef(toInt(q13 != p_PermutationAsFunction_PermutationFunction_Function1D[q13]), 0) + | q13 : int(1..7)]) + = 3, + allDiff(p_PermutationAsFunction_PermutationFunction_Function1D), + and([or([p_PermutationAsFunction_PermutationFunction_Function1D[q3] = q2 | q3 : int(1..7)]) | q2 : int(1..7)]) + diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/permutation.essence b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/permutation.essence new file mode 100644 index 0000000000..62aca160b0 --- /dev/null +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/permutation.essence @@ -0,0 +1,14 @@ +letting n be new type of size 7 + +find i : n + +find p : permutation of n + +find j : n + +such that + j = image(p, i) /\ sum([toInt(l!=r)|(l,r)<-p]) = 3 + + + + From ba3507d0631badf66099fd1611f5876d8516ddf7 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?O=CC=88zgu=CC=88r=20Akgu=CC=88n?= Date: Tue, 11 Aug 2020 17:38:13 +0300 Subject: [PATCH 119/229] handling top level list of bools in the solution validator --- src/Conjure/UI/ValidateSolution.hs | 11 +++++++---- 1 file changed, 7 insertions(+), 4 deletions(-) diff --git a/src/Conjure/UI/ValidateSolution.hs b/src/Conjure/UI/ValidateSolution.hs index 07791d1717..37f574ab50 100644 --- a/src/Conjure/UI/ValidateSolution.hs +++ b/src/Conjure/UI/ValidateSolution.hs @@ -5,6 +5,7 @@ import Conjure.Bug import Conjure.Prelude import Conjure.UserError import Conjure.Language.Definition +import Conjure.Language.Constant import Conjure.Language.Domain import Conjure.Language.Pretty import Conjure.Language.Type @@ -128,8 +129,9 @@ validateSolution essenceModel essenceParam essenceSolution = flip evalStateT [] vals <- gets id forM_ xs $ \ x -> do constant <- instantiateExpression vals x - case constant of - ConstantBool True -> return () + case (constant, viewConstantMatrix constant) of + (ConstantBool True, _) -> return () + (_, Just (_, bools)) | all (== ConstantBool True) bools -> return () _ -> userErr1 $ "Invalid." <++> vcat [ "Statement evaluates to:" <+> pretty constant , "Original statement was:" <+> pretty x , "Relevant values:" <++> vcat @@ -143,8 +145,9 @@ validateSolution essenceModel essenceParam essenceSolution = flip evalStateT [] vals <- gets id forM_ xs $ \ x -> do constant <- instantiateExpression vals x - case constant of - ConstantBool True -> return () + case (constant, viewConstantMatrix constant) of + (ConstantBool True, _) -> return () + (_, Just (_, bools)) | all (== ConstantBool True) bools -> return () _ -> userErr1 $ "Invalid." <++> vcat [ "Statement evaluates to:" <+> pretty constant , "Original statement was:" <+> pretty x , "Relevant values:" <++> vcat From f4c7fa12d21ddf0c7c81aa65928e0a518c4c7316 Mon Sep 17 00:00:00 2001 From: Chris Jefferson Date: Tue, 11 Aug 2020 15:34:28 +0100 Subject: [PATCH 120/229] Permutation tests - part 5 --- .../model-permutation-solution000001.solution | 3 +++ .../expected/model-permutation.eprime-param | 4 ++++ .../expected/model.eprime | 12 ++++++++++ .../permutation.essence | 12 ++++++++++ .../permutation.param | 2 ++ .../model-permutation-solution000001.solution | 3 +++ .../expected/model-permutation.eprime-param | 4 ++++ .../expected/model.eprime | 12 ++++++++++ .../permutation.essence | 12 ++++++++++ .../permutation.param | 2 ++ .../model-permutation-solution000001.solution | 3 +++ .../expected/model-permutation.eprime-param | 3 +++ .../expected/model.eprime | 21 ++++++++++++++++++ .../permutation.essence | 12 ++++++++++ .../permutation.param | 1 + .../model-permutation-solution000001.solution | 3 +++ .../expected/model-permutation.eprime-param | 3 +++ .../expected/model.eprime | 21 ++++++++++++++++++ .../permutation.essence | 12 ++++++++++ .../permutation.param | 1 + .../expected/model-solution000001.solution | 4 ++++ .../expected/model-solution000002.solution | 4 ++++ .../expected/model-solution000003.solution | 4 ++++ .../expected/model-solution000004.solution | 4 ++++ .../expected/model-solution000005.solution | 4 ++++ .../expected/model-solution000006.solution | 4 ++++ .../expected/model-solution000007.solution | 4 ++++ .../expected/model-solution000008.solution | 4 ++++ .../expected/model-solution000009.solution | 4 ++++ .../expected/model-solution000010.solution | 4 ++++ .../expected/model-solution000011.solution | 4 ++++ .../expected/model-solution000012.solution | 4 ++++ .../expected/model-solution000013.solution | 4 ++++ .../expected/model-solution000014.solution | 4 ++++ .../expected/model-solution000015.solution | 4 ++++ .../expected/model-solution000016.solution | 4 ++++ .../expected/model-solution000017.solution | 4 ++++ .../expected/model-solution000018.solution | 4 ++++ .../expected/model-solution000019.solution | 4 ++++ .../expected/model-solution000020.solution | 4 ++++ .../expected/model-solution000021.solution | 4 ++++ .../expected/model-solution000022.solution | 4 ++++ .../expected/model-solution000023.solution | 4 ++++ .../expected/model-solution000024.solution | 4 ++++ .../0005_find_eq_find/expected/model.eprime | 15 +++++++++++++ .../0005_find_eq_find/permutation.essence | 10 +++++++++ .../expected/model-solution000001.solution | 4 ++++ .../expected/model-solution000002.solution | 4 ++++ .../expected/model-solution000003.solution | 4 ++++ .../expected/model-solution000004.solution | 4 ++++ .../expected/model-solution000005.solution | 4 ++++ .../expected/model-solution000006.solution | 4 ++++ .../expected/model-solution000007.solution | 4 ++++ .../expected/model-solution000008.solution | 4 ++++ .../expected/model-solution000009.solution | 4 ++++ .../expected/model-solution000010.solution | 4 ++++ .../expected/model-solution000011.solution | 4 ++++ .../expected/model-solution000012.solution | 4 ++++ .../expected/model-solution000013.solution | 4 ++++ .../expected/model-solution000014.solution | 4 ++++ .../expected/model-solution000015.solution | 4 ++++ .../expected/model-solution000016.solution | 4 ++++ .../expected/model-solution000017.solution | 4 ++++ .../expected/model-solution000018.solution | 4 ++++ .../expected/model-solution000019.solution | 4 ++++ .../expected/model-solution000020.solution | 4 ++++ .../expected/model-solution000021.solution | 4 ++++ .../expected/model-solution000022.solution | 4 ++++ .../expected/model-solution000023.solution | 4 ++++ .../expected/model-solution000024.solution | 4 ++++ .../expected/model.eprime | 21 ++++++++++++++++++ .../0006_in_comprehension/permutation.essence | 7 ++++++ .../model-permutation-solution000001.solution | 3 +++ .../expected/model-permutation.eprime-param | 4 ++++ .../expected/model.eprime | 12 ++++++++++ .../permutation.essence | 12 ++++++++++ .../permutation.param | 2 ++ .../model-permutation-solution000001.solution | 3 +++ .../expected/model-permutation.eprime-param | 4 ++++ .../expected/model.eprime | 12 ++++++++++ .../permutation.essence | 12 ++++++++++ .../permutation.param | 2 ++ .../model-permutation-solution000001.solution | 3 +++ .../expected/model-permutation.eprime-param | 3 +++ .../expected/model.eprime | 22 +++++++++++++++++++ .../permutation.essence | 12 ++++++++++ .../permutation.param | 1 + .../model-permutation-solution000001.solution | 3 +++ .../expected/model-permutation.eprime-param | 3 +++ .../expected/model.eprime | 22 +++++++++++++++++++ .../permutation.essence | 12 ++++++++++ .../permutation.param | 1 + .../expected/model-solution000001.solution | 4 ++++ .../expected/model-solution000002.solution | 4 ++++ .../expected/model-solution000003.solution | 4 ++++ .../expected/model-solution000004.solution | 4 ++++ .../expected/model-solution000005.solution | 4 ++++ .../expected/model-solution000006.solution | 4 ++++ .../expected/model-solution000007.solution | 4 ++++ .../expected/model-solution000008.solution | 4 ++++ .../expected/model-solution000009.solution | 4 ++++ .../expected/model-solution000010.solution | 4 ++++ .../expected/model-solution000011.solution | 4 ++++ .../expected/model-solution000012.solution | 4 ++++ .../expected/model-solution000013.solution | 4 ++++ .../expected/model-solution000014.solution | 4 ++++ .../expected/model-solution000015.solution | 4 ++++ .../expected/model-solution000016.solution | 4 ++++ .../expected/model-solution000017.solution | 4 ++++ .../expected/model-solution000018.solution | 4 ++++ .../expected/model-solution000019.solution | 4 ++++ .../expected/model-solution000020.solution | 4 ++++ .../expected/model-solution000021.solution | 4 ++++ .../expected/model-solution000022.solution | 4 ++++ .../expected/model-solution000023.solution | 4 ++++ .../expected/model-solution000024.solution | 4 ++++ .../0005_find_eq_find/expected/model.eprime | 15 +++++++++++++ .../int/0005_find_eq_find/permutation.essence | 8 +++++++ .../expected/model-solution000001.solution | 4 ++++ .../expected/model-solution000002.solution | 4 ++++ .../expected/model-solution000003.solution | 4 ++++ .../expected/model-solution000004.solution | 4 ++++ .../expected/model-solution000005.solution | 4 ++++ .../expected/model-solution000006.solution | 4 ++++ .../expected/model-solution000007.solution | 4 ++++ .../expected/model-solution000008.solution | 4 ++++ .../expected/model-solution000009.solution | 4 ++++ .../expected/model-solution000010.solution | 4 ++++ .../expected/model-solution000011.solution | 4 ++++ .../expected/model-solution000012.solution | 4 ++++ .../expected/model-solution000013.solution | 4 ++++ .../expected/model-solution000014.solution | 4 ++++ .../expected/model-solution000015.solution | 4 ++++ .../expected/model-solution000016.solution | 4 ++++ .../expected/model-solution000017.solution | 4 ++++ .../expected/model-solution000018.solution | 4 ++++ .../expected/model-solution000019.solution | 4 ++++ .../expected/model-solution000020.solution | 4 ++++ .../expected/model-solution000021.solution | 4 ++++ .../expected/model-solution000022.solution | 4 ++++ .../expected/model-solution000023.solution | 4 ++++ .../expected/model-solution000024.solution | 4 ++++ .../expected/model.eprime | 21 ++++++++++++++++++ .../0006_in_comprehension/permutation.essence | 6 +++++ .../expected/model-solution000001.solution | 3 +++ .../expected/model.eprime | 6 +++++ .../permutation.essence | 4 ++++ .../expected/model-solution000001.solution | 3 +++ .../05_equality/int/expected/model.eprime | 6 +++++ .../basic/perms/05_equality/int/new.essence | 4 ++++ .../expected/model-solution000001.solution | 5 +++++ .../expected/model-solution000002.solution | 5 +++++ .../expected/model-solution000003.solution | 5 +++++ .../expected/model-solution000004.solution | 5 +++++ .../expected/model-solution000005.solution | 5 +++++ .../expected/model-solution000006.solution | 5 +++++ .../expected/model-solution000007.solution | 5 +++++ .../expected/model-solution000008.solution | 5 +++++ .../expected/model-solution000009.solution | 5 +++++ .../expected/model-solution000010.solution | 5 +++++ .../expected/model-solution000011.solution | 5 +++++ .../expected/model-solution000012.solution | 5 +++++ .../expected/model-solution000013.solution | 5 +++++ .../expected/model-solution000014.solution | 5 +++++ .../expected/model-solution000015.solution | 5 +++++ .../expected/model-solution000016.solution | 5 +++++ .../expected/model-solution000017.solution | 5 +++++ .../expected/model-solution000018.solution | 5 +++++ .../expected/model-solution000019.solution | 5 +++++ .../expected/model-solution000020.solution | 5 +++++ .../expected/model-solution000021.solution | 5 +++++ .../expected/model-solution000022.solution | 5 +++++ .../expected/model-solution000023.solution | 5 +++++ .../expected/model-solution000024.solution | 5 +++++ .../0005_find_eq_find/expected/model.eprime | 15 +++++++++++++ .../0005_find_eq_find/permutation.essence | 10 +++++++++ .../expected/model-solution000001.solution | 5 +++++ .../expected/model-solution000002.solution | 5 +++++ .../expected/model-solution000003.solution | 5 +++++ .../expected/model-solution000004.solution | 5 +++++ .../expected/model-solution000005.solution | 5 +++++ .../expected/model-solution000006.solution | 5 +++++ .../expected/model-solution000007.solution | 5 +++++ .../expected/model-solution000008.solution | 5 +++++ .../expected/model-solution000009.solution | 5 +++++ .../expected/model-solution000010.solution | 5 +++++ .../expected/model-solution000011.solution | 5 +++++ .../expected/model-solution000012.solution | 5 +++++ .../expected/model-solution000013.solution | 5 +++++ .../expected/model-solution000014.solution | 5 +++++ .../expected/model-solution000015.solution | 5 +++++ .../expected/model-solution000016.solution | 5 +++++ .../expected/model-solution000017.solution | 5 +++++ .../expected/model-solution000018.solution | 5 +++++ .../expected/model-solution000019.solution | 5 +++++ .../expected/model-solution000020.solution | 5 +++++ .../expected/model-solution000021.solution | 5 +++++ .../expected/model-solution000022.solution | 5 +++++ .../expected/model-solution000023.solution | 5 +++++ .../expected/model-solution000024.solution | 5 +++++ .../expected/model.eprime | 21 ++++++++++++++++++ .../0006_in_comprehension/permutation.essence | 7 ++++++ 202 files changed, 1100 insertions(+) create mode 100644 tests/exhaustive/basic/perms/05_equality/enum/0001_given_permutations_in_param/expected/model-permutation-solution000001.solution create mode 100644 tests/exhaustive/basic/perms/05_equality/enum/0001_given_permutations_in_param/expected/model-permutation.eprime-param create mode 100644 tests/exhaustive/basic/perms/05_equality/enum/0001_given_permutations_in_param/expected/model.eprime create mode 100644 tests/exhaustive/basic/perms/05_equality/enum/0001_given_permutations_in_param/permutation.essence create mode 100644 tests/exhaustive/basic/perms/05_equality/enum/0001_given_permutations_in_param/permutation.param create mode 100644 tests/exhaustive/basic/perms/05_equality/enum/0002_given_permutations_in_param/expected/model-permutation-solution000001.solution create mode 100644 tests/exhaustive/basic/perms/05_equality/enum/0002_given_permutations_in_param/expected/model-permutation.eprime-param create mode 100644 tests/exhaustive/basic/perms/05_equality/enum/0002_given_permutations_in_param/expected/model.eprime create mode 100644 tests/exhaustive/basic/perms/05_equality/enum/0002_given_permutations_in_param/permutation.essence create mode 100644 tests/exhaustive/basic/perms/05_equality/enum/0002_given_permutations_in_param/permutation.param create mode 100644 tests/exhaustive/basic/perms/05_equality/enum/0003_given_equal_letting/expected/model-permutation-solution000001.solution create mode 100644 tests/exhaustive/basic/perms/05_equality/enum/0003_given_equal_letting/expected/model-permutation.eprime-param create mode 100644 tests/exhaustive/basic/perms/05_equality/enum/0003_given_equal_letting/expected/model.eprime create mode 100644 tests/exhaustive/basic/perms/05_equality/enum/0003_given_equal_letting/permutation.essence create mode 100644 tests/exhaustive/basic/perms/05_equality/enum/0003_given_equal_letting/permutation.param create mode 100644 tests/exhaustive/basic/perms/05_equality/enum/0004_letting_equal_given/expected/model-permutation-solution000001.solution create mode 100644 tests/exhaustive/basic/perms/05_equality/enum/0004_letting_equal_given/expected/model-permutation.eprime-param create mode 100644 tests/exhaustive/basic/perms/05_equality/enum/0004_letting_equal_given/expected/model.eprime create mode 100644 tests/exhaustive/basic/perms/05_equality/enum/0004_letting_equal_given/permutation.essence create mode 100644 tests/exhaustive/basic/perms/05_equality/enum/0004_letting_equal_given/permutation.param create mode 100644 tests/exhaustive/basic/perms/05_equality/enum/0005_find_eq_find/expected/model-solution000001.solution create mode 100644 tests/exhaustive/basic/perms/05_equality/enum/0005_find_eq_find/expected/model-solution000002.solution create mode 100644 tests/exhaustive/basic/perms/05_equality/enum/0005_find_eq_find/expected/model-solution000003.solution create mode 100644 tests/exhaustive/basic/perms/05_equality/enum/0005_find_eq_find/expected/model-solution000004.solution create mode 100644 tests/exhaustive/basic/perms/05_equality/enum/0005_find_eq_find/expected/model-solution000005.solution create mode 100644 tests/exhaustive/basic/perms/05_equality/enum/0005_find_eq_find/expected/model-solution000006.solution create mode 100644 tests/exhaustive/basic/perms/05_equality/enum/0005_find_eq_find/expected/model-solution000007.solution create mode 100644 tests/exhaustive/basic/perms/05_equality/enum/0005_find_eq_find/expected/model-solution000008.solution create mode 100644 tests/exhaustive/basic/perms/05_equality/enum/0005_find_eq_find/expected/model-solution000009.solution create mode 100644 tests/exhaustive/basic/perms/05_equality/enum/0005_find_eq_find/expected/model-solution000010.solution create mode 100644 tests/exhaustive/basic/perms/05_equality/enum/0005_find_eq_find/expected/model-solution000011.solution create mode 100644 tests/exhaustive/basic/perms/05_equality/enum/0005_find_eq_find/expected/model-solution000012.solution create mode 100644 tests/exhaustive/basic/perms/05_equality/enum/0005_find_eq_find/expected/model-solution000013.solution create mode 100644 tests/exhaustive/basic/perms/05_equality/enum/0005_find_eq_find/expected/model-solution000014.solution create mode 100644 tests/exhaustive/basic/perms/05_equality/enum/0005_find_eq_find/expected/model-solution000015.solution create mode 100644 tests/exhaustive/basic/perms/05_equality/enum/0005_find_eq_find/expected/model-solution000016.solution create mode 100644 tests/exhaustive/basic/perms/05_equality/enum/0005_find_eq_find/expected/model-solution000017.solution create mode 100644 tests/exhaustive/basic/perms/05_equality/enum/0005_find_eq_find/expected/model-solution000018.solution create mode 100644 tests/exhaustive/basic/perms/05_equality/enum/0005_find_eq_find/expected/model-solution000019.solution create mode 100644 tests/exhaustive/basic/perms/05_equality/enum/0005_find_eq_find/expected/model-solution000020.solution create mode 100644 tests/exhaustive/basic/perms/05_equality/enum/0005_find_eq_find/expected/model-solution000021.solution create mode 100644 tests/exhaustive/basic/perms/05_equality/enum/0005_find_eq_find/expected/model-solution000022.solution create mode 100644 tests/exhaustive/basic/perms/05_equality/enum/0005_find_eq_find/expected/model-solution000023.solution create mode 100644 tests/exhaustive/basic/perms/05_equality/enum/0005_find_eq_find/expected/model-solution000024.solution create mode 100644 tests/exhaustive/basic/perms/05_equality/enum/0005_find_eq_find/expected/model.eprime create mode 100644 tests/exhaustive/basic/perms/05_equality/enum/0005_find_eq_find/permutation.essence create mode 100644 tests/exhaustive/basic/perms/05_equality/enum/0006_in_comprehension/expected/model-solution000001.solution create mode 100644 tests/exhaustive/basic/perms/05_equality/enum/0006_in_comprehension/expected/model-solution000002.solution create mode 100644 tests/exhaustive/basic/perms/05_equality/enum/0006_in_comprehension/expected/model-solution000003.solution create mode 100644 tests/exhaustive/basic/perms/05_equality/enum/0006_in_comprehension/expected/model-solution000004.solution create mode 100644 tests/exhaustive/basic/perms/05_equality/enum/0006_in_comprehension/expected/model-solution000005.solution create mode 100644 tests/exhaustive/basic/perms/05_equality/enum/0006_in_comprehension/expected/model-solution000006.solution create mode 100644 tests/exhaustive/basic/perms/05_equality/enum/0006_in_comprehension/expected/model-solution000007.solution create mode 100644 tests/exhaustive/basic/perms/05_equality/enum/0006_in_comprehension/expected/model-solution000008.solution create mode 100644 tests/exhaustive/basic/perms/05_equality/enum/0006_in_comprehension/expected/model-solution000009.solution create mode 100644 tests/exhaustive/basic/perms/05_equality/enum/0006_in_comprehension/expected/model-solution000010.solution create mode 100644 tests/exhaustive/basic/perms/05_equality/enum/0006_in_comprehension/expected/model-solution000011.solution create mode 100644 tests/exhaustive/basic/perms/05_equality/enum/0006_in_comprehension/expected/model-solution000012.solution create mode 100644 tests/exhaustive/basic/perms/05_equality/enum/0006_in_comprehension/expected/model-solution000013.solution create mode 100644 tests/exhaustive/basic/perms/05_equality/enum/0006_in_comprehension/expected/model-solution000014.solution create mode 100644 tests/exhaustive/basic/perms/05_equality/enum/0006_in_comprehension/expected/model-solution000015.solution create mode 100644 tests/exhaustive/basic/perms/05_equality/enum/0006_in_comprehension/expected/model-solution000016.solution create mode 100644 tests/exhaustive/basic/perms/05_equality/enum/0006_in_comprehension/expected/model-solution000017.solution create mode 100644 tests/exhaustive/basic/perms/05_equality/enum/0006_in_comprehension/expected/model-solution000018.solution create mode 100644 tests/exhaustive/basic/perms/05_equality/enum/0006_in_comprehension/expected/model-solution000019.solution create mode 100644 tests/exhaustive/basic/perms/05_equality/enum/0006_in_comprehension/expected/model-solution000020.solution create mode 100644 tests/exhaustive/basic/perms/05_equality/enum/0006_in_comprehension/expected/model-solution000021.solution create mode 100644 tests/exhaustive/basic/perms/05_equality/enum/0006_in_comprehension/expected/model-solution000022.solution create mode 100644 tests/exhaustive/basic/perms/05_equality/enum/0006_in_comprehension/expected/model-solution000023.solution create mode 100644 tests/exhaustive/basic/perms/05_equality/enum/0006_in_comprehension/expected/model-solution000024.solution create mode 100644 tests/exhaustive/basic/perms/05_equality/enum/0006_in_comprehension/expected/model.eprime create mode 100644 tests/exhaustive/basic/perms/05_equality/enum/0006_in_comprehension/permutation.essence create mode 100644 tests/exhaustive/basic/perms/05_equality/int/0001_given_permutations_in_param/expected/model-permutation-solution000001.solution create mode 100644 tests/exhaustive/basic/perms/05_equality/int/0001_given_permutations_in_param/expected/model-permutation.eprime-param create mode 100644 tests/exhaustive/basic/perms/05_equality/int/0001_given_permutations_in_param/expected/model.eprime create mode 100644 tests/exhaustive/basic/perms/05_equality/int/0001_given_permutations_in_param/permutation.essence create mode 100644 tests/exhaustive/basic/perms/05_equality/int/0001_given_permutations_in_param/permutation.param create mode 100644 tests/exhaustive/basic/perms/05_equality/int/0002_given_permutations_in_param/expected/model-permutation-solution000001.solution create mode 100644 tests/exhaustive/basic/perms/05_equality/int/0002_given_permutations_in_param/expected/model-permutation.eprime-param create mode 100644 tests/exhaustive/basic/perms/05_equality/int/0002_given_permutations_in_param/expected/model.eprime create mode 100644 tests/exhaustive/basic/perms/05_equality/int/0002_given_permutations_in_param/permutation.essence create mode 100644 tests/exhaustive/basic/perms/05_equality/int/0002_given_permutations_in_param/permutation.param create mode 100644 tests/exhaustive/basic/perms/05_equality/int/0003_given_equal_letting/expected/model-permutation-solution000001.solution create mode 100644 tests/exhaustive/basic/perms/05_equality/int/0003_given_equal_letting/expected/model-permutation.eprime-param create mode 100644 tests/exhaustive/basic/perms/05_equality/int/0003_given_equal_letting/expected/model.eprime create mode 100644 tests/exhaustive/basic/perms/05_equality/int/0003_given_equal_letting/permutation.essence create mode 100644 tests/exhaustive/basic/perms/05_equality/int/0003_given_equal_letting/permutation.param create mode 100644 tests/exhaustive/basic/perms/05_equality/int/0004_letting_equal_given/expected/model-permutation-solution000001.solution create mode 100644 tests/exhaustive/basic/perms/05_equality/int/0004_letting_equal_given/expected/model-permutation.eprime-param create mode 100644 tests/exhaustive/basic/perms/05_equality/int/0004_letting_equal_given/expected/model.eprime create mode 100644 tests/exhaustive/basic/perms/05_equality/int/0004_letting_equal_given/permutation.essence create mode 100644 tests/exhaustive/basic/perms/05_equality/int/0004_letting_equal_given/permutation.param create mode 100644 tests/exhaustive/basic/perms/05_equality/int/0005_find_eq_find/expected/model-solution000001.solution create mode 100644 tests/exhaustive/basic/perms/05_equality/int/0005_find_eq_find/expected/model-solution000002.solution create mode 100644 tests/exhaustive/basic/perms/05_equality/int/0005_find_eq_find/expected/model-solution000003.solution create mode 100644 tests/exhaustive/basic/perms/05_equality/int/0005_find_eq_find/expected/model-solution000004.solution create mode 100644 tests/exhaustive/basic/perms/05_equality/int/0005_find_eq_find/expected/model-solution000005.solution create mode 100644 tests/exhaustive/basic/perms/05_equality/int/0005_find_eq_find/expected/model-solution000006.solution create mode 100644 tests/exhaustive/basic/perms/05_equality/int/0005_find_eq_find/expected/model-solution000007.solution create mode 100644 tests/exhaustive/basic/perms/05_equality/int/0005_find_eq_find/expected/model-solution000008.solution create mode 100644 tests/exhaustive/basic/perms/05_equality/int/0005_find_eq_find/expected/model-solution000009.solution create mode 100644 tests/exhaustive/basic/perms/05_equality/int/0005_find_eq_find/expected/model-solution000010.solution create mode 100644 tests/exhaustive/basic/perms/05_equality/int/0005_find_eq_find/expected/model-solution000011.solution create mode 100644 tests/exhaustive/basic/perms/05_equality/int/0005_find_eq_find/expected/model-solution000012.solution create mode 100644 tests/exhaustive/basic/perms/05_equality/int/0005_find_eq_find/expected/model-solution000013.solution create mode 100644 tests/exhaustive/basic/perms/05_equality/int/0005_find_eq_find/expected/model-solution000014.solution create mode 100644 tests/exhaustive/basic/perms/05_equality/int/0005_find_eq_find/expected/model-solution000015.solution create mode 100644 tests/exhaustive/basic/perms/05_equality/int/0005_find_eq_find/expected/model-solution000016.solution create mode 100644 tests/exhaustive/basic/perms/05_equality/int/0005_find_eq_find/expected/model-solution000017.solution create mode 100644 tests/exhaustive/basic/perms/05_equality/int/0005_find_eq_find/expected/model-solution000018.solution create mode 100644 tests/exhaustive/basic/perms/05_equality/int/0005_find_eq_find/expected/model-solution000019.solution create mode 100644 tests/exhaustive/basic/perms/05_equality/int/0005_find_eq_find/expected/model-solution000020.solution create mode 100644 tests/exhaustive/basic/perms/05_equality/int/0005_find_eq_find/expected/model-solution000021.solution create mode 100644 tests/exhaustive/basic/perms/05_equality/int/0005_find_eq_find/expected/model-solution000022.solution create mode 100644 tests/exhaustive/basic/perms/05_equality/int/0005_find_eq_find/expected/model-solution000023.solution create mode 100644 tests/exhaustive/basic/perms/05_equality/int/0005_find_eq_find/expected/model-solution000024.solution create mode 100644 tests/exhaustive/basic/perms/05_equality/int/0005_find_eq_find/expected/model.eprime create mode 100644 tests/exhaustive/basic/perms/05_equality/int/0005_find_eq_find/permutation.essence create mode 100644 tests/exhaustive/basic/perms/05_equality/int/0006_in_comprehension/expected/model-solution000001.solution create mode 100644 tests/exhaustive/basic/perms/05_equality/int/0006_in_comprehension/expected/model-solution000002.solution create mode 100644 tests/exhaustive/basic/perms/05_equality/int/0006_in_comprehension/expected/model-solution000003.solution create mode 100644 tests/exhaustive/basic/perms/05_equality/int/0006_in_comprehension/expected/model-solution000004.solution create mode 100644 tests/exhaustive/basic/perms/05_equality/int/0006_in_comprehension/expected/model-solution000005.solution create mode 100644 tests/exhaustive/basic/perms/05_equality/int/0006_in_comprehension/expected/model-solution000006.solution create mode 100644 tests/exhaustive/basic/perms/05_equality/int/0006_in_comprehension/expected/model-solution000007.solution create mode 100644 tests/exhaustive/basic/perms/05_equality/int/0006_in_comprehension/expected/model-solution000008.solution create mode 100644 tests/exhaustive/basic/perms/05_equality/int/0006_in_comprehension/expected/model-solution000009.solution create mode 100644 tests/exhaustive/basic/perms/05_equality/int/0006_in_comprehension/expected/model-solution000010.solution create mode 100644 tests/exhaustive/basic/perms/05_equality/int/0006_in_comprehension/expected/model-solution000011.solution create mode 100644 tests/exhaustive/basic/perms/05_equality/int/0006_in_comprehension/expected/model-solution000012.solution create mode 100644 tests/exhaustive/basic/perms/05_equality/int/0006_in_comprehension/expected/model-solution000013.solution create mode 100644 tests/exhaustive/basic/perms/05_equality/int/0006_in_comprehension/expected/model-solution000014.solution create mode 100644 tests/exhaustive/basic/perms/05_equality/int/0006_in_comprehension/expected/model-solution000015.solution create mode 100644 tests/exhaustive/basic/perms/05_equality/int/0006_in_comprehension/expected/model-solution000016.solution create mode 100644 tests/exhaustive/basic/perms/05_equality/int/0006_in_comprehension/expected/model-solution000017.solution create mode 100644 tests/exhaustive/basic/perms/05_equality/int/0006_in_comprehension/expected/model-solution000018.solution create mode 100644 tests/exhaustive/basic/perms/05_equality/int/0006_in_comprehension/expected/model-solution000019.solution create mode 100644 tests/exhaustive/basic/perms/05_equality/int/0006_in_comprehension/expected/model-solution000020.solution create mode 100644 tests/exhaustive/basic/perms/05_equality/int/0006_in_comprehension/expected/model-solution000021.solution create mode 100644 tests/exhaustive/basic/perms/05_equality/int/0006_in_comprehension/expected/model-solution000022.solution create mode 100644 tests/exhaustive/basic/perms/05_equality/int/0006_in_comprehension/expected/model-solution000023.solution create mode 100644 tests/exhaustive/basic/perms/05_equality/int/0006_in_comprehension/expected/model-solution000024.solution create mode 100644 tests/exhaustive/basic/perms/05_equality/int/0006_in_comprehension/expected/model.eprime create mode 100644 tests/exhaustive/basic/perms/05_equality/int/0006_in_comprehension/permutation.essence create mode 100644 tests/exhaustive/basic/perms/05_equality/int/0007_letting_equal_letting/expected/model-solution000001.solution create mode 100644 tests/exhaustive/basic/perms/05_equality/int/0007_letting_equal_letting/expected/model.eprime create mode 100644 tests/exhaustive/basic/perms/05_equality/int/0007_letting_equal_letting/permutation.essence create mode 100644 tests/exhaustive/basic/perms/05_equality/int/expected/model-solution000001.solution create mode 100644 tests/exhaustive/basic/perms/05_equality/int/expected/model.eprime create mode 100644 tests/exhaustive/basic/perms/05_equality/int/new.essence create mode 100644 tests/exhaustive/basic/perms/05_equality/unnamed/0005_find_eq_find/expected/model-solution000001.solution create mode 100644 tests/exhaustive/basic/perms/05_equality/unnamed/0005_find_eq_find/expected/model-solution000002.solution create mode 100644 tests/exhaustive/basic/perms/05_equality/unnamed/0005_find_eq_find/expected/model-solution000003.solution create mode 100644 tests/exhaustive/basic/perms/05_equality/unnamed/0005_find_eq_find/expected/model-solution000004.solution create mode 100644 tests/exhaustive/basic/perms/05_equality/unnamed/0005_find_eq_find/expected/model-solution000005.solution create mode 100644 tests/exhaustive/basic/perms/05_equality/unnamed/0005_find_eq_find/expected/model-solution000006.solution create mode 100644 tests/exhaustive/basic/perms/05_equality/unnamed/0005_find_eq_find/expected/model-solution000007.solution create mode 100644 tests/exhaustive/basic/perms/05_equality/unnamed/0005_find_eq_find/expected/model-solution000008.solution create mode 100644 tests/exhaustive/basic/perms/05_equality/unnamed/0005_find_eq_find/expected/model-solution000009.solution create mode 100644 tests/exhaustive/basic/perms/05_equality/unnamed/0005_find_eq_find/expected/model-solution000010.solution create mode 100644 tests/exhaustive/basic/perms/05_equality/unnamed/0005_find_eq_find/expected/model-solution000011.solution create mode 100644 tests/exhaustive/basic/perms/05_equality/unnamed/0005_find_eq_find/expected/model-solution000012.solution create mode 100644 tests/exhaustive/basic/perms/05_equality/unnamed/0005_find_eq_find/expected/model-solution000013.solution create mode 100644 tests/exhaustive/basic/perms/05_equality/unnamed/0005_find_eq_find/expected/model-solution000014.solution create mode 100644 tests/exhaustive/basic/perms/05_equality/unnamed/0005_find_eq_find/expected/model-solution000015.solution create mode 100644 tests/exhaustive/basic/perms/05_equality/unnamed/0005_find_eq_find/expected/model-solution000016.solution create mode 100644 tests/exhaustive/basic/perms/05_equality/unnamed/0005_find_eq_find/expected/model-solution000017.solution create mode 100644 tests/exhaustive/basic/perms/05_equality/unnamed/0005_find_eq_find/expected/model-solution000018.solution create mode 100644 tests/exhaustive/basic/perms/05_equality/unnamed/0005_find_eq_find/expected/model-solution000019.solution create mode 100644 tests/exhaustive/basic/perms/05_equality/unnamed/0005_find_eq_find/expected/model-solution000020.solution create mode 100644 tests/exhaustive/basic/perms/05_equality/unnamed/0005_find_eq_find/expected/model-solution000021.solution create mode 100644 tests/exhaustive/basic/perms/05_equality/unnamed/0005_find_eq_find/expected/model-solution000022.solution create mode 100644 tests/exhaustive/basic/perms/05_equality/unnamed/0005_find_eq_find/expected/model-solution000023.solution create mode 100644 tests/exhaustive/basic/perms/05_equality/unnamed/0005_find_eq_find/expected/model-solution000024.solution create mode 100644 tests/exhaustive/basic/perms/05_equality/unnamed/0005_find_eq_find/expected/model.eprime create mode 100644 tests/exhaustive/basic/perms/05_equality/unnamed/0005_find_eq_find/permutation.essence create mode 100644 tests/exhaustive/basic/perms/05_equality/unnamed/0006_in_comprehension/expected/model-solution000001.solution create mode 100644 tests/exhaustive/basic/perms/05_equality/unnamed/0006_in_comprehension/expected/model-solution000002.solution create mode 100644 tests/exhaustive/basic/perms/05_equality/unnamed/0006_in_comprehension/expected/model-solution000003.solution create mode 100644 tests/exhaustive/basic/perms/05_equality/unnamed/0006_in_comprehension/expected/model-solution000004.solution create mode 100644 tests/exhaustive/basic/perms/05_equality/unnamed/0006_in_comprehension/expected/model-solution000005.solution create mode 100644 tests/exhaustive/basic/perms/05_equality/unnamed/0006_in_comprehension/expected/model-solution000006.solution create mode 100644 tests/exhaustive/basic/perms/05_equality/unnamed/0006_in_comprehension/expected/model-solution000007.solution create mode 100644 tests/exhaustive/basic/perms/05_equality/unnamed/0006_in_comprehension/expected/model-solution000008.solution create mode 100644 tests/exhaustive/basic/perms/05_equality/unnamed/0006_in_comprehension/expected/model-solution000009.solution create mode 100644 tests/exhaustive/basic/perms/05_equality/unnamed/0006_in_comprehension/expected/model-solution000010.solution create mode 100644 tests/exhaustive/basic/perms/05_equality/unnamed/0006_in_comprehension/expected/model-solution000011.solution create mode 100644 tests/exhaustive/basic/perms/05_equality/unnamed/0006_in_comprehension/expected/model-solution000012.solution create mode 100644 tests/exhaustive/basic/perms/05_equality/unnamed/0006_in_comprehension/expected/model-solution000013.solution create mode 100644 tests/exhaustive/basic/perms/05_equality/unnamed/0006_in_comprehension/expected/model-solution000014.solution create mode 100644 tests/exhaustive/basic/perms/05_equality/unnamed/0006_in_comprehension/expected/model-solution000015.solution create mode 100644 tests/exhaustive/basic/perms/05_equality/unnamed/0006_in_comprehension/expected/model-solution000016.solution create mode 100644 tests/exhaustive/basic/perms/05_equality/unnamed/0006_in_comprehension/expected/model-solution000017.solution create mode 100644 tests/exhaustive/basic/perms/05_equality/unnamed/0006_in_comprehension/expected/model-solution000018.solution create mode 100644 tests/exhaustive/basic/perms/05_equality/unnamed/0006_in_comprehension/expected/model-solution000019.solution create mode 100644 tests/exhaustive/basic/perms/05_equality/unnamed/0006_in_comprehension/expected/model-solution000020.solution create mode 100644 tests/exhaustive/basic/perms/05_equality/unnamed/0006_in_comprehension/expected/model-solution000021.solution create mode 100644 tests/exhaustive/basic/perms/05_equality/unnamed/0006_in_comprehension/expected/model-solution000022.solution create mode 100644 tests/exhaustive/basic/perms/05_equality/unnamed/0006_in_comprehension/expected/model-solution000023.solution create mode 100644 tests/exhaustive/basic/perms/05_equality/unnamed/0006_in_comprehension/expected/model-solution000024.solution create mode 100644 tests/exhaustive/basic/perms/05_equality/unnamed/0006_in_comprehension/expected/model.eprime create mode 100644 tests/exhaustive/basic/perms/05_equality/unnamed/0006_in_comprehension/permutation.essence diff --git a/tests/exhaustive/basic/perms/05_equality/enum/0001_given_permutations_in_param/expected/model-permutation-solution000001.solution b/tests/exhaustive/basic/perms/05_equality/enum/0001_given_permutations_in_param/expected/model-permutation-solution000001.solution new file mode 100644 index 0000000000..6d3576ecbf --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/enum/0001_given_permutations_in_param/expected/model-permutation-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting b be true diff --git a/tests/exhaustive/basic/perms/05_equality/enum/0001_given_permutations_in_param/expected/model-permutation.eprime-param b/tests/exhaustive/basic/perms/05_equality/enum/0001_given_permutations_in_param/expected/model-permutation.eprime-param new file mode 100644 index 0000000000..5a448d7146 --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/enum/0001_given_permutations_in_param/expected/model-permutation.eprime-param @@ -0,0 +1,4 @@ +language ESSENCE' 1.0 + +letting p_PermutationAsFunction_PermutationFunction_Function1D be [3, 2, 4, 1; int(1..4)] +letting q_PermutationAsFunction_PermutationFunction_Function1D be [3, 2, 4, 1; int(1..4)] diff --git a/tests/exhaustive/basic/perms/05_equality/enum/0001_given_permutations_in_param/expected/model.eprime b/tests/exhaustive/basic/perms/05_equality/enum/0001_given_permutations_in_param/expected/model.eprime new file mode 100644 index 0000000000..167dc8f366 --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/enum/0001_given_permutations_in_param/expected/model.eprime @@ -0,0 +1,12 @@ +language ESSENCE' 1.0 + +given p_PermutationAsFunction_PermutationFunction_Function1D: matrix indexed by [int(1..4)] of int(1..4) +given q_PermutationAsFunction_PermutationFunction_Function1D: matrix indexed by [int(1..4)] of int(1..4) +find b: bool +branching on [b] +such that + b = + and([p_PermutationAsFunction_PermutationFunction_Function1D[q1] = + q_PermutationAsFunction_PermutationFunction_Function1D[q1] + | q1 : int(1..4)]) + diff --git a/tests/exhaustive/basic/perms/05_equality/enum/0001_given_permutations_in_param/permutation.essence b/tests/exhaustive/basic/perms/05_equality/enum/0001_given_permutations_in_param/permutation.essence new file mode 100644 index 0000000000..1d734d0227 --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/enum/0001_given_permutations_in_param/permutation.essence @@ -0,0 +1,12 @@ +letting n be new type enum {E1,E2,E3,E4} + +given p : permutation of n +given q : permutation of n + +find b : bool + +such that b = (p = q) + + + + diff --git a/tests/exhaustive/basic/perms/05_equality/enum/0001_given_permutations_in_param/permutation.param b/tests/exhaustive/basic/perms/05_equality/enum/0001_given_permutations_in_param/permutation.param new file mode 100644 index 0000000000..d15978a724 --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/enum/0001_given_permutations_in_param/permutation.param @@ -0,0 +1,2 @@ +letting p be permutation((E1,E3,E4)) +letting q be permutation((E1,E3,E4)) diff --git a/tests/exhaustive/basic/perms/05_equality/enum/0002_given_permutations_in_param/expected/model-permutation-solution000001.solution b/tests/exhaustive/basic/perms/05_equality/enum/0002_given_permutations_in_param/expected/model-permutation-solution000001.solution new file mode 100644 index 0000000000..97ec002915 --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/enum/0002_given_permutations_in_param/expected/model-permutation-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting b be false diff --git a/tests/exhaustive/basic/perms/05_equality/enum/0002_given_permutations_in_param/expected/model-permutation.eprime-param b/tests/exhaustive/basic/perms/05_equality/enum/0002_given_permutations_in_param/expected/model-permutation.eprime-param new file mode 100644 index 0000000000..fea0f3fb24 --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/enum/0002_given_permutations_in_param/expected/model-permutation.eprime-param @@ -0,0 +1,4 @@ +language ESSENCE' 1.0 + +letting p_PermutationAsFunction_PermutationFunction_Function1D be [3, 2, 4, 1; int(1..4)] +letting q_PermutationAsFunction_PermutationFunction_Function1D be [2, 4, 3, 1; int(1..4)] diff --git a/tests/exhaustive/basic/perms/05_equality/enum/0002_given_permutations_in_param/expected/model.eprime b/tests/exhaustive/basic/perms/05_equality/enum/0002_given_permutations_in_param/expected/model.eprime new file mode 100644 index 0000000000..167dc8f366 --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/enum/0002_given_permutations_in_param/expected/model.eprime @@ -0,0 +1,12 @@ +language ESSENCE' 1.0 + +given p_PermutationAsFunction_PermutationFunction_Function1D: matrix indexed by [int(1..4)] of int(1..4) +given q_PermutationAsFunction_PermutationFunction_Function1D: matrix indexed by [int(1..4)] of int(1..4) +find b: bool +branching on [b] +such that + b = + and([p_PermutationAsFunction_PermutationFunction_Function1D[q1] = + q_PermutationAsFunction_PermutationFunction_Function1D[q1] + | q1 : int(1..4)]) + diff --git a/tests/exhaustive/basic/perms/05_equality/enum/0002_given_permutations_in_param/permutation.essence b/tests/exhaustive/basic/perms/05_equality/enum/0002_given_permutations_in_param/permutation.essence new file mode 100644 index 0000000000..f50a7f5ec1 --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/enum/0002_given_permutations_in_param/permutation.essence @@ -0,0 +1,12 @@ +letting n be new type enum {E1,E2,E3,E4} + +given p : permutation of n +given q : permutation of n + +find b : bool + +such that b = (p = q) + + + + diff --git a/tests/exhaustive/basic/perms/05_equality/enum/0002_given_permutations_in_param/permutation.param b/tests/exhaustive/basic/perms/05_equality/enum/0002_given_permutations_in_param/permutation.param new file mode 100644 index 0000000000..9fe9e7a421 --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/enum/0002_given_permutations_in_param/permutation.param @@ -0,0 +1,2 @@ +letting p be permutation((E1,E3,E4)) +letting q be permutation((E1,E2,E4)) diff --git a/tests/exhaustive/basic/perms/05_equality/enum/0003_given_equal_letting/expected/model-permutation-solution000001.solution b/tests/exhaustive/basic/perms/05_equality/enum/0003_given_equal_letting/expected/model-permutation-solution000001.solution new file mode 100644 index 0000000000..97ec002915 --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/enum/0003_given_equal_letting/expected/model-permutation-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting b be false diff --git a/tests/exhaustive/basic/perms/05_equality/enum/0003_given_equal_letting/expected/model-permutation.eprime-param b/tests/exhaustive/basic/perms/05_equality/enum/0003_given_equal_letting/expected/model-permutation.eprime-param new file mode 100644 index 0000000000..c2bddee0e8 --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/enum/0003_given_equal_letting/expected/model-permutation.eprime-param @@ -0,0 +1,3 @@ +language ESSENCE' 1.0 + +letting p_PermutationAsFunction_PermutationFunction_Function1D be [3, 2, 4, 1; int(1..4)] diff --git a/tests/exhaustive/basic/perms/05_equality/enum/0003_given_equal_letting/expected/model.eprime b/tests/exhaustive/basic/perms/05_equality/enum/0003_given_equal_letting/expected/model.eprime new file mode 100644 index 0000000000..4047fc6e95 --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/enum/0003_given_equal_letting/expected/model.eprime @@ -0,0 +1,21 @@ +language ESSENCE' 1.0 + +given p_PermutationAsFunction_PermutationFunction_Function1D: matrix indexed by [int(1..4)] of int(1..4) +find b: bool +branching on [b] +such that + b = + (and([or([1 = q8 /\ 2 = p_PermutationAsFunction_PermutationFunction_Function1D[q8], + 2 = q8 /\ 4 = p_PermutationAsFunction_PermutationFunction_Function1D[q8], + 4 = q8 /\ 1 = p_PermutationAsFunction_PermutationFunction_Function1D[q8]; + int(1..3)]) + | q8 : int(1..4), q8 != p_PermutationAsFunction_PermutationFunction_Function1D[q8]]) + /\ + and([or([q16 = 1 /\ p_PermutationAsFunction_PermutationFunction_Function1D[q16] = 2 + | q16 : int(1..4), q16 != p_PermutationAsFunction_PermutationFunction_Function1D[q16]]), + or([q23 = 2 /\ p_PermutationAsFunction_PermutationFunction_Function1D[q23] = 4 + | q23 : int(1..4), q23 != p_PermutationAsFunction_PermutationFunction_Function1D[q23]]), + or([q30 = 4 /\ p_PermutationAsFunction_PermutationFunction_Function1D[q30] = 1 + | q30 : int(1..4), q30 != p_PermutationAsFunction_PermutationFunction_Function1D[q30]]); + int(1..3)])) + diff --git a/tests/exhaustive/basic/perms/05_equality/enum/0003_given_equal_letting/permutation.essence b/tests/exhaustive/basic/perms/05_equality/enum/0003_given_equal_letting/permutation.essence new file mode 100644 index 0000000000..70fee7073d --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/enum/0003_given_equal_letting/permutation.essence @@ -0,0 +1,12 @@ +letting n be new type enum {E1,E2,E3,E4} + +given p : permutation of n +letting q be permutation((E1,E2,E4)) + +find b : bool + +such that b = (p = q) + + + + diff --git a/tests/exhaustive/basic/perms/05_equality/enum/0003_given_equal_letting/permutation.param b/tests/exhaustive/basic/perms/05_equality/enum/0003_given_equal_letting/permutation.param new file mode 100644 index 0000000000..19349bb872 --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/enum/0003_given_equal_letting/permutation.param @@ -0,0 +1 @@ +letting p be permutation((E1,E3,E4)) diff --git a/tests/exhaustive/basic/perms/05_equality/enum/0004_letting_equal_given/expected/model-permutation-solution000001.solution b/tests/exhaustive/basic/perms/05_equality/enum/0004_letting_equal_given/expected/model-permutation-solution000001.solution new file mode 100644 index 0000000000..97ec002915 --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/enum/0004_letting_equal_given/expected/model-permutation-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting b be false diff --git a/tests/exhaustive/basic/perms/05_equality/enum/0004_letting_equal_given/expected/model-permutation.eprime-param b/tests/exhaustive/basic/perms/05_equality/enum/0004_letting_equal_given/expected/model-permutation.eprime-param new file mode 100644 index 0000000000..c2bddee0e8 --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/enum/0004_letting_equal_given/expected/model-permutation.eprime-param @@ -0,0 +1,3 @@ +language ESSENCE' 1.0 + +letting p_PermutationAsFunction_PermutationFunction_Function1D be [3, 2, 4, 1; int(1..4)] diff --git a/tests/exhaustive/basic/perms/05_equality/enum/0004_letting_equal_given/expected/model.eprime b/tests/exhaustive/basic/perms/05_equality/enum/0004_letting_equal_given/expected/model.eprime new file mode 100644 index 0000000000..e8d100615a --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/enum/0004_letting_equal_given/expected/model.eprime @@ -0,0 +1,21 @@ +language ESSENCE' 1.0 + +given p_PermutationAsFunction_PermutationFunction_Function1D: matrix indexed by [int(1..4)] of int(1..4) +find b: bool +branching on [b] +such that + b = + (and([or([q8 = 1 /\ p_PermutationAsFunction_PermutationFunction_Function1D[q8] = 2 + | q8 : int(1..4), q8 != p_PermutationAsFunction_PermutationFunction_Function1D[q8]]), + or([q15 = 2 /\ p_PermutationAsFunction_PermutationFunction_Function1D[q15] = 4 + | q15 : int(1..4), q15 != p_PermutationAsFunction_PermutationFunction_Function1D[q15]]), + or([q22 = 4 /\ p_PermutationAsFunction_PermutationFunction_Function1D[q22] = 1 + | q22 : int(1..4), q22 != p_PermutationAsFunction_PermutationFunction_Function1D[q22]]); + int(1..3)]) + /\ + and([or([1 = q30 /\ 2 = p_PermutationAsFunction_PermutationFunction_Function1D[q30], + 2 = q30 /\ 4 = p_PermutationAsFunction_PermutationFunction_Function1D[q30], + 4 = q30 /\ 1 = p_PermutationAsFunction_PermutationFunction_Function1D[q30]; + int(1..3)]) + | q30 : int(1..4), q30 != p_PermutationAsFunction_PermutationFunction_Function1D[q30]])) + diff --git a/tests/exhaustive/basic/perms/05_equality/enum/0004_letting_equal_given/permutation.essence b/tests/exhaustive/basic/perms/05_equality/enum/0004_letting_equal_given/permutation.essence new file mode 100644 index 0000000000..ec7bacb28f --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/enum/0004_letting_equal_given/permutation.essence @@ -0,0 +1,12 @@ +letting n be new type enum {E1,E2,E3,E4} + +given p : permutation of n +letting q be permutation((E1,E2,E4)) + +find b : bool + +such that b = (q = p) + + + + diff --git a/tests/exhaustive/basic/perms/05_equality/enum/0004_letting_equal_given/permutation.param b/tests/exhaustive/basic/perms/05_equality/enum/0004_letting_equal_given/permutation.param new file mode 100644 index 0000000000..19349bb872 --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/enum/0004_letting_equal_given/permutation.param @@ -0,0 +1 @@ +letting p be permutation((E1,E3,E4)) diff --git a/tests/exhaustive/basic/perms/05_equality/enum/0005_find_eq_find/expected/model-solution000001.solution b/tests/exhaustive/basic/perms/05_equality/enum/0005_find_eq_find/expected/model-solution000001.solution new file mode 100644 index 0000000000..5e99ad7a05 --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/enum/0005_find_eq_find/expected/model-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting p be permutation() +letting q be permutation() diff --git a/tests/exhaustive/basic/perms/05_equality/enum/0005_find_eq_find/expected/model-solution000002.solution b/tests/exhaustive/basic/perms/05_equality/enum/0005_find_eq_find/expected/model-solution000002.solution new file mode 100644 index 0000000000..cc107b6078 --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/enum/0005_find_eq_find/expected/model-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting p be permutation((E3, E4)) +letting q be permutation((E3, E4)) diff --git a/tests/exhaustive/basic/perms/05_equality/enum/0005_find_eq_find/expected/model-solution000003.solution b/tests/exhaustive/basic/perms/05_equality/enum/0005_find_eq_find/expected/model-solution000003.solution new file mode 100644 index 0000000000..b815b7f2b7 --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/enum/0005_find_eq_find/expected/model-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting p be permutation((E2, E3)) +letting q be permutation((E2, E3)) diff --git a/tests/exhaustive/basic/perms/05_equality/enum/0005_find_eq_find/expected/model-solution000004.solution b/tests/exhaustive/basic/perms/05_equality/enum/0005_find_eq_find/expected/model-solution000004.solution new file mode 100644 index 0000000000..60e770117c --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/enum/0005_find_eq_find/expected/model-solution000004.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting p be permutation((E2, E3, E4)) +letting q be permutation((E2, E3, E4)) diff --git a/tests/exhaustive/basic/perms/05_equality/enum/0005_find_eq_find/expected/model-solution000005.solution b/tests/exhaustive/basic/perms/05_equality/enum/0005_find_eq_find/expected/model-solution000005.solution new file mode 100644 index 0000000000..a56d373880 --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/enum/0005_find_eq_find/expected/model-solution000005.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting p be permutation((E2, E4, E3)) +letting q be permutation((E2, E4, E3)) diff --git a/tests/exhaustive/basic/perms/05_equality/enum/0005_find_eq_find/expected/model-solution000006.solution b/tests/exhaustive/basic/perms/05_equality/enum/0005_find_eq_find/expected/model-solution000006.solution new file mode 100644 index 0000000000..779e12630b --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/enum/0005_find_eq_find/expected/model-solution000006.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting p be permutation((E2, E4)) +letting q be permutation((E2, E4)) diff --git a/tests/exhaustive/basic/perms/05_equality/enum/0005_find_eq_find/expected/model-solution000007.solution b/tests/exhaustive/basic/perms/05_equality/enum/0005_find_eq_find/expected/model-solution000007.solution new file mode 100644 index 0000000000..a5c0a46619 --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/enum/0005_find_eq_find/expected/model-solution000007.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting p be permutation((E1, E2)) +letting q be permutation((E1, E2)) diff --git a/tests/exhaustive/basic/perms/05_equality/enum/0005_find_eq_find/expected/model-solution000008.solution b/tests/exhaustive/basic/perms/05_equality/enum/0005_find_eq_find/expected/model-solution000008.solution new file mode 100644 index 0000000000..cefa10df0b --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/enum/0005_find_eq_find/expected/model-solution000008.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting p be permutation((E1, E2), (E3, E4)) +letting q be permutation((E1, E2), (E3, E4)) diff --git a/tests/exhaustive/basic/perms/05_equality/enum/0005_find_eq_find/expected/model-solution000009.solution b/tests/exhaustive/basic/perms/05_equality/enum/0005_find_eq_find/expected/model-solution000009.solution new file mode 100644 index 0000000000..8f6f6da946 --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/enum/0005_find_eq_find/expected/model-solution000009.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting p be permutation((E1, E2, E3)) +letting q be permutation((E1, E2, E3)) diff --git a/tests/exhaustive/basic/perms/05_equality/enum/0005_find_eq_find/expected/model-solution000010.solution b/tests/exhaustive/basic/perms/05_equality/enum/0005_find_eq_find/expected/model-solution000010.solution new file mode 100644 index 0000000000..a68e0b7ea8 --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/enum/0005_find_eq_find/expected/model-solution000010.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting p be permutation((E1, E2, E3, E4)) +letting q be permutation((E1, E2, E3, E4)) diff --git a/tests/exhaustive/basic/perms/05_equality/enum/0005_find_eq_find/expected/model-solution000011.solution b/tests/exhaustive/basic/perms/05_equality/enum/0005_find_eq_find/expected/model-solution000011.solution new file mode 100644 index 0000000000..eccd486441 --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/enum/0005_find_eq_find/expected/model-solution000011.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting p be permutation((E1, E2, E4, E3)) +letting q be permutation((E1, E2, E4, E3)) diff --git a/tests/exhaustive/basic/perms/05_equality/enum/0005_find_eq_find/expected/model-solution000012.solution b/tests/exhaustive/basic/perms/05_equality/enum/0005_find_eq_find/expected/model-solution000012.solution new file mode 100644 index 0000000000..de9602f9c4 --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/enum/0005_find_eq_find/expected/model-solution000012.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting p be permutation((E1, E2, E4)) +letting q be permutation((E1, E2, E4)) diff --git a/tests/exhaustive/basic/perms/05_equality/enum/0005_find_eq_find/expected/model-solution000013.solution b/tests/exhaustive/basic/perms/05_equality/enum/0005_find_eq_find/expected/model-solution000013.solution new file mode 100644 index 0000000000..273a92fdfa --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/enum/0005_find_eq_find/expected/model-solution000013.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting p be permutation((E1, E3, E2)) +letting q be permutation((E1, E3, E2)) diff --git a/tests/exhaustive/basic/perms/05_equality/enum/0005_find_eq_find/expected/model-solution000014.solution b/tests/exhaustive/basic/perms/05_equality/enum/0005_find_eq_find/expected/model-solution000014.solution new file mode 100644 index 0000000000..434c24d783 --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/enum/0005_find_eq_find/expected/model-solution000014.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting p be permutation((E1, E3, E4, E2)) +letting q be permutation((E1, E3, E4, E2)) diff --git a/tests/exhaustive/basic/perms/05_equality/enum/0005_find_eq_find/expected/model-solution000015.solution b/tests/exhaustive/basic/perms/05_equality/enum/0005_find_eq_find/expected/model-solution000015.solution new file mode 100644 index 0000000000..ec7fcc2333 --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/enum/0005_find_eq_find/expected/model-solution000015.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting p be permutation((E1, E3)) +letting q be permutation((E1, E3)) diff --git a/tests/exhaustive/basic/perms/05_equality/enum/0005_find_eq_find/expected/model-solution000016.solution b/tests/exhaustive/basic/perms/05_equality/enum/0005_find_eq_find/expected/model-solution000016.solution new file mode 100644 index 0000000000..74936596c2 --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/enum/0005_find_eq_find/expected/model-solution000016.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting p be permutation((E1, E3, E4)) +letting q be permutation((E1, E3, E4)) diff --git a/tests/exhaustive/basic/perms/05_equality/enum/0005_find_eq_find/expected/model-solution000017.solution b/tests/exhaustive/basic/perms/05_equality/enum/0005_find_eq_find/expected/model-solution000017.solution new file mode 100644 index 0000000000..4498016bb4 --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/enum/0005_find_eq_find/expected/model-solution000017.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting p be permutation((E1, E3), (E2, E4)) +letting q be permutation((E1, E3), (E2, E4)) diff --git a/tests/exhaustive/basic/perms/05_equality/enum/0005_find_eq_find/expected/model-solution000018.solution b/tests/exhaustive/basic/perms/05_equality/enum/0005_find_eq_find/expected/model-solution000018.solution new file mode 100644 index 0000000000..ce14251333 --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/enum/0005_find_eq_find/expected/model-solution000018.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting p be permutation((E1, E3, E2, E4)) +letting q be permutation((E1, E3, E2, E4)) diff --git a/tests/exhaustive/basic/perms/05_equality/enum/0005_find_eq_find/expected/model-solution000019.solution b/tests/exhaustive/basic/perms/05_equality/enum/0005_find_eq_find/expected/model-solution000019.solution new file mode 100644 index 0000000000..ae3fad4f99 --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/enum/0005_find_eq_find/expected/model-solution000019.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting p be permutation((E1, E4, E3, E2)) +letting q be permutation((E1, E4, E3, E2)) diff --git a/tests/exhaustive/basic/perms/05_equality/enum/0005_find_eq_find/expected/model-solution000020.solution b/tests/exhaustive/basic/perms/05_equality/enum/0005_find_eq_find/expected/model-solution000020.solution new file mode 100644 index 0000000000..fdfd9fac96 --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/enum/0005_find_eq_find/expected/model-solution000020.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting p be permutation((E1, E4, E2)) +letting q be permutation((E1, E4, E2)) diff --git a/tests/exhaustive/basic/perms/05_equality/enum/0005_find_eq_find/expected/model-solution000021.solution b/tests/exhaustive/basic/perms/05_equality/enum/0005_find_eq_find/expected/model-solution000021.solution new file mode 100644 index 0000000000..79899a33b1 --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/enum/0005_find_eq_find/expected/model-solution000021.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting p be permutation((E1, E4, E3)) +letting q be permutation((E1, E4, E3)) diff --git a/tests/exhaustive/basic/perms/05_equality/enum/0005_find_eq_find/expected/model-solution000022.solution b/tests/exhaustive/basic/perms/05_equality/enum/0005_find_eq_find/expected/model-solution000022.solution new file mode 100644 index 0000000000..b7c2138520 --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/enum/0005_find_eq_find/expected/model-solution000022.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting p be permutation((E1, E4)) +letting q be permutation((E1, E4)) diff --git a/tests/exhaustive/basic/perms/05_equality/enum/0005_find_eq_find/expected/model-solution000023.solution b/tests/exhaustive/basic/perms/05_equality/enum/0005_find_eq_find/expected/model-solution000023.solution new file mode 100644 index 0000000000..20a254310b --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/enum/0005_find_eq_find/expected/model-solution000023.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting p be permutation((E1, E4, E2, E3)) +letting q be permutation((E1, E4, E2, E3)) diff --git a/tests/exhaustive/basic/perms/05_equality/enum/0005_find_eq_find/expected/model-solution000024.solution b/tests/exhaustive/basic/perms/05_equality/enum/0005_find_eq_find/expected/model-solution000024.solution new file mode 100644 index 0000000000..ed56bbf672 --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/enum/0005_find_eq_find/expected/model-solution000024.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting p be permutation((E1, E4), (E2, E3)) +letting q be permutation((E1, E4), (E2, E3)) diff --git a/tests/exhaustive/basic/perms/05_equality/enum/0005_find_eq_find/expected/model.eprime b/tests/exhaustive/basic/perms/05_equality/enum/0005_find_eq_find/expected/model.eprime new file mode 100644 index 0000000000..f1a2530c1a --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/enum/0005_find_eq_find/expected/model.eprime @@ -0,0 +1,15 @@ +language ESSENCE' 1.0 + +find p_PermutationAsFunction_PermutationFunction_Function1D: matrix indexed by [int(1..4)] of int(1..4) +find q_PermutationAsFunction_PermutationFunction_Function1D: matrix indexed by [int(1..4)] of int(1..4) +branching on + [p_PermutationAsFunction_PermutationFunction_Function1D, q_PermutationAsFunction_PermutationFunction_Function1D] +such that + and([q_PermutationAsFunction_PermutationFunction_Function1D[q9] = + p_PermutationAsFunction_PermutationFunction_Function1D[q9] + | q9 : int(1..4)]), + allDiff(q_PermutationAsFunction_PermutationFunction_Function1D), + and([or([q_PermutationAsFunction_PermutationFunction_Function1D[q3] = q2 | q3 : int(1..4)]) | q2 : int(1..4)]), + allDiff(p_PermutationAsFunction_PermutationFunction_Function1D), + and([or([p_PermutationAsFunction_PermutationFunction_Function1D[q7] = q6 | q7 : int(1..4)]) | q6 : int(1..4)]) + diff --git a/tests/exhaustive/basic/perms/05_equality/enum/0005_find_eq_find/permutation.essence b/tests/exhaustive/basic/perms/05_equality/enum/0005_find_eq_find/permutation.essence new file mode 100644 index 0000000000..55b8c1f1e4 --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/enum/0005_find_eq_find/permutation.essence @@ -0,0 +1,10 @@ +letting n be new type enum {E1,E2,E3,E4} + +find p : permutation of n +find q : permutation of n + +such that q = p + + + + diff --git a/tests/exhaustive/basic/perms/05_equality/enum/0006_in_comprehension/expected/model-solution000001.solution b/tests/exhaustive/basic/perms/05_equality/enum/0006_in_comprehension/expected/model-solution000001.solution new file mode 100644 index 0000000000..1bf17c8510 --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/enum/0006_in_comprehension/expected/model-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting p be permutation((E1, E2), (E3, E4)) +letting q be permutation((E1, E3), (E2, E4)) diff --git a/tests/exhaustive/basic/perms/05_equality/enum/0006_in_comprehension/expected/model-solution000002.solution b/tests/exhaustive/basic/perms/05_equality/enum/0006_in_comprehension/expected/model-solution000002.solution new file mode 100644 index 0000000000..c65dc9df09 --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/enum/0006_in_comprehension/expected/model-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting p be permutation((E1, E2), (E3, E4)) +letting q be permutation((E1, E3, E2, E4)) diff --git a/tests/exhaustive/basic/perms/05_equality/enum/0006_in_comprehension/expected/model-solution000003.solution b/tests/exhaustive/basic/perms/05_equality/enum/0006_in_comprehension/expected/model-solution000003.solution new file mode 100644 index 0000000000..0a0e9b3c85 --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/enum/0006_in_comprehension/expected/model-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting p be permutation((E1, E2), (E3, E4)) +letting q be permutation((E1, E4, E2, E3)) diff --git a/tests/exhaustive/basic/perms/05_equality/enum/0006_in_comprehension/expected/model-solution000004.solution b/tests/exhaustive/basic/perms/05_equality/enum/0006_in_comprehension/expected/model-solution000004.solution new file mode 100644 index 0000000000..2694192b46 --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/enum/0006_in_comprehension/expected/model-solution000004.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting p be permutation((E1, E2), (E3, E4)) +letting q be permutation((E1, E4), (E2, E3)) diff --git a/tests/exhaustive/basic/perms/05_equality/enum/0006_in_comprehension/expected/model-solution000005.solution b/tests/exhaustive/basic/perms/05_equality/enum/0006_in_comprehension/expected/model-solution000005.solution new file mode 100644 index 0000000000..b01cbea006 --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/enum/0006_in_comprehension/expected/model-solution000005.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting p be permutation((E1, E2, E3, E4)) +letting q be permutation((E1, E3), (E2, E4)) diff --git a/tests/exhaustive/basic/perms/05_equality/enum/0006_in_comprehension/expected/model-solution000006.solution b/tests/exhaustive/basic/perms/05_equality/enum/0006_in_comprehension/expected/model-solution000006.solution new file mode 100644 index 0000000000..e52e292e71 --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/enum/0006_in_comprehension/expected/model-solution000006.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting p be permutation((E1, E2, E3, E4)) +letting q be permutation((E1, E4, E3, E2)) diff --git a/tests/exhaustive/basic/perms/05_equality/enum/0006_in_comprehension/expected/model-solution000007.solution b/tests/exhaustive/basic/perms/05_equality/enum/0006_in_comprehension/expected/model-solution000007.solution new file mode 100644 index 0000000000..ee75cbbf7a --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/enum/0006_in_comprehension/expected/model-solution000007.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting p be permutation((E1, E2, E4, E3)) +letting q be permutation((E1, E3, E4, E2)) diff --git a/tests/exhaustive/basic/perms/05_equality/enum/0006_in_comprehension/expected/model-solution000008.solution b/tests/exhaustive/basic/perms/05_equality/enum/0006_in_comprehension/expected/model-solution000008.solution new file mode 100644 index 0000000000..d40bfc43f9 --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/enum/0006_in_comprehension/expected/model-solution000008.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting p be permutation((E1, E2, E4, E3)) +letting q be permutation((E1, E4), (E2, E3)) diff --git a/tests/exhaustive/basic/perms/05_equality/enum/0006_in_comprehension/expected/model-solution000009.solution b/tests/exhaustive/basic/perms/05_equality/enum/0006_in_comprehension/expected/model-solution000009.solution new file mode 100644 index 0000000000..80ccc2c325 --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/enum/0006_in_comprehension/expected/model-solution000009.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting p be permutation((E1, E3, E4, E2)) +letting q be permutation((E1, E2, E4, E3)) diff --git a/tests/exhaustive/basic/perms/05_equality/enum/0006_in_comprehension/expected/model-solution000010.solution b/tests/exhaustive/basic/perms/05_equality/enum/0006_in_comprehension/expected/model-solution000010.solution new file mode 100644 index 0000000000..e39f6ae04c --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/enum/0006_in_comprehension/expected/model-solution000010.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting p be permutation((E1, E3, E4, E2)) +letting q be permutation((E1, E4), (E2, E3)) diff --git a/tests/exhaustive/basic/perms/05_equality/enum/0006_in_comprehension/expected/model-solution000011.solution b/tests/exhaustive/basic/perms/05_equality/enum/0006_in_comprehension/expected/model-solution000011.solution new file mode 100644 index 0000000000..2a8faaf7ce --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/enum/0006_in_comprehension/expected/model-solution000011.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting p be permutation((E1, E3), (E2, E4)) +letting q be permutation((E1, E2), (E3, E4)) diff --git a/tests/exhaustive/basic/perms/05_equality/enum/0006_in_comprehension/expected/model-solution000012.solution b/tests/exhaustive/basic/perms/05_equality/enum/0006_in_comprehension/expected/model-solution000012.solution new file mode 100644 index 0000000000..414787bbfc --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/enum/0006_in_comprehension/expected/model-solution000012.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting p be permutation((E1, E3), (E2, E4)) +letting q be permutation((E1, E2, E3, E4)) diff --git a/tests/exhaustive/basic/perms/05_equality/enum/0006_in_comprehension/expected/model-solution000013.solution b/tests/exhaustive/basic/perms/05_equality/enum/0006_in_comprehension/expected/model-solution000013.solution new file mode 100644 index 0000000000..403f3a3c09 --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/enum/0006_in_comprehension/expected/model-solution000013.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting p be permutation((E1, E3), (E2, E4)) +letting q be permutation((E1, E4, E3, E2)) diff --git a/tests/exhaustive/basic/perms/05_equality/enum/0006_in_comprehension/expected/model-solution000014.solution b/tests/exhaustive/basic/perms/05_equality/enum/0006_in_comprehension/expected/model-solution000014.solution new file mode 100644 index 0000000000..4c0372103c --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/enum/0006_in_comprehension/expected/model-solution000014.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting p be permutation((E1, E3), (E2, E4)) +letting q be permutation((E1, E4), (E2, E3)) diff --git a/tests/exhaustive/basic/perms/05_equality/enum/0006_in_comprehension/expected/model-solution000015.solution b/tests/exhaustive/basic/perms/05_equality/enum/0006_in_comprehension/expected/model-solution000015.solution new file mode 100644 index 0000000000..ce87b9b8ae --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/enum/0006_in_comprehension/expected/model-solution000015.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting p be permutation((E1, E3, E2, E4)) +letting q be permutation((E1, E2), (E3, E4)) diff --git a/tests/exhaustive/basic/perms/05_equality/enum/0006_in_comprehension/expected/model-solution000016.solution b/tests/exhaustive/basic/perms/05_equality/enum/0006_in_comprehension/expected/model-solution000016.solution new file mode 100644 index 0000000000..95ddec76ce --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/enum/0006_in_comprehension/expected/model-solution000016.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting p be permutation((E1, E3, E2, E4)) +letting q be permutation((E1, E4, E2, E3)) diff --git a/tests/exhaustive/basic/perms/05_equality/enum/0006_in_comprehension/expected/model-solution000017.solution b/tests/exhaustive/basic/perms/05_equality/enum/0006_in_comprehension/expected/model-solution000017.solution new file mode 100644 index 0000000000..08879149f9 --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/enum/0006_in_comprehension/expected/model-solution000017.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting p be permutation((E1, E4, E3, E2)) +letting q be permutation((E1, E2, E3, E4)) diff --git a/tests/exhaustive/basic/perms/05_equality/enum/0006_in_comprehension/expected/model-solution000018.solution b/tests/exhaustive/basic/perms/05_equality/enum/0006_in_comprehension/expected/model-solution000018.solution new file mode 100644 index 0000000000..a767ed693c --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/enum/0006_in_comprehension/expected/model-solution000018.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting p be permutation((E1, E4, E3, E2)) +letting q be permutation((E1, E3), (E2, E4)) diff --git a/tests/exhaustive/basic/perms/05_equality/enum/0006_in_comprehension/expected/model-solution000019.solution b/tests/exhaustive/basic/perms/05_equality/enum/0006_in_comprehension/expected/model-solution000019.solution new file mode 100644 index 0000000000..50b0d5a2e6 --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/enum/0006_in_comprehension/expected/model-solution000019.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting p be permutation((E1, E4, E2, E3)) +letting q be permutation((E1, E2), (E3, E4)) diff --git a/tests/exhaustive/basic/perms/05_equality/enum/0006_in_comprehension/expected/model-solution000020.solution b/tests/exhaustive/basic/perms/05_equality/enum/0006_in_comprehension/expected/model-solution000020.solution new file mode 100644 index 0000000000..1e84b585a8 --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/enum/0006_in_comprehension/expected/model-solution000020.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting p be permutation((E1, E4, E2, E3)) +letting q be permutation((E1, E3, E2, E4)) diff --git a/tests/exhaustive/basic/perms/05_equality/enum/0006_in_comprehension/expected/model-solution000021.solution b/tests/exhaustive/basic/perms/05_equality/enum/0006_in_comprehension/expected/model-solution000021.solution new file mode 100644 index 0000000000..c07bea3885 --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/enum/0006_in_comprehension/expected/model-solution000021.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting p be permutation((E1, E4), (E2, E3)) +letting q be permutation((E1, E2), (E3, E4)) diff --git a/tests/exhaustive/basic/perms/05_equality/enum/0006_in_comprehension/expected/model-solution000022.solution b/tests/exhaustive/basic/perms/05_equality/enum/0006_in_comprehension/expected/model-solution000022.solution new file mode 100644 index 0000000000..41f0ccd1fd --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/enum/0006_in_comprehension/expected/model-solution000022.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting p be permutation((E1, E4), (E2, E3)) +letting q be permutation((E1, E2, E4, E3)) diff --git a/tests/exhaustive/basic/perms/05_equality/enum/0006_in_comprehension/expected/model-solution000023.solution b/tests/exhaustive/basic/perms/05_equality/enum/0006_in_comprehension/expected/model-solution000023.solution new file mode 100644 index 0000000000..77106d3078 --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/enum/0006_in_comprehension/expected/model-solution000023.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting p be permutation((E1, E4), (E2, E3)) +letting q be permutation((E1, E3, E4, E2)) diff --git a/tests/exhaustive/basic/perms/05_equality/enum/0006_in_comprehension/expected/model-solution000024.solution b/tests/exhaustive/basic/perms/05_equality/enum/0006_in_comprehension/expected/model-solution000024.solution new file mode 100644 index 0000000000..670c351fbb --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/enum/0006_in_comprehension/expected/model-solution000024.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting p be permutation((E1, E4), (E2, E3)) +letting q be permutation((E1, E3), (E2, E4)) diff --git a/tests/exhaustive/basic/perms/05_equality/enum/0006_in_comprehension/expected/model.eprime b/tests/exhaustive/basic/perms/05_equality/enum/0006_in_comprehension/expected/model.eprime new file mode 100644 index 0000000000..b06a4e1b4e --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/enum/0006_in_comprehension/expected/model.eprime @@ -0,0 +1,21 @@ +language ESSENCE' 1.0 + +find p_PermutationAsFunction_PermutationFunction_Function1D: matrix indexed by [int(1..4)] of int(1..4) +find q_PermutationAsFunction_PermutationFunction_Function1D: matrix indexed by [int(1..4)] of int(1..4) +branching on + [p_PermutationAsFunction_PermutationFunction_Function1D, q_PermutationAsFunction_PermutationFunction_Function1D] +such that + and([q20 != q_PermutationAsFunction_PermutationFunction_Function1D[q20] /\ + q14 != p_PermutationAsFunction_PermutationFunction_Function1D[q14] + -> + !(q14 = q20 /\ + p_PermutationAsFunction_PermutationFunction_Function1D[q14] = + q_PermutationAsFunction_PermutationFunction_Function1D[q20]) + | q14 : int(1..4), q20 : int(1..4)]), + allDiff(p_PermutationAsFunction_PermutationFunction_Function1D), + and([or([p_PermutationAsFunction_PermutationFunction_Function1D[q3] = q2 | q3 : int(1..4)]) | q2 : int(1..4)]), + 4 = sum([toInt(q1 != p_PermutationAsFunction_PermutationFunction_Function1D[q1]) | q1 : int(1..4)]), + allDiff(q_PermutationAsFunction_PermutationFunction_Function1D), + and([or([q_PermutationAsFunction_PermutationFunction_Function1D[q7] = q6 | q7 : int(1..4)]) | q6 : int(1..4)]), + 4 = sum([toInt(q5 != q_PermutationAsFunction_PermutationFunction_Function1D[q5]) | q5 : int(1..4)]) + diff --git a/tests/exhaustive/basic/perms/05_equality/enum/0006_in_comprehension/permutation.essence b/tests/exhaustive/basic/perms/05_equality/enum/0006_in_comprehension/permutation.essence new file mode 100644 index 0000000000..cc47c67c6e --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/enum/0006_in_comprehension/permutation.essence @@ -0,0 +1,7 @@ +letting n be new type enum {E1,E2,E3,E4} +find p : permutation (size 4) of n +find q : permutation (size 4) of n + +such that + and([pt != qt | pt <- p, qt <- q]) + diff --git a/tests/exhaustive/basic/perms/05_equality/int/0001_given_permutations_in_param/expected/model-permutation-solution000001.solution b/tests/exhaustive/basic/perms/05_equality/int/0001_given_permutations_in_param/expected/model-permutation-solution000001.solution new file mode 100644 index 0000000000..6d3576ecbf --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/int/0001_given_permutations_in_param/expected/model-permutation-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting b be true diff --git a/tests/exhaustive/basic/perms/05_equality/int/0001_given_permutations_in_param/expected/model-permutation.eprime-param b/tests/exhaustive/basic/perms/05_equality/int/0001_given_permutations_in_param/expected/model-permutation.eprime-param new file mode 100644 index 0000000000..5a448d7146 --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/int/0001_given_permutations_in_param/expected/model-permutation.eprime-param @@ -0,0 +1,4 @@ +language ESSENCE' 1.0 + +letting p_PermutationAsFunction_PermutationFunction_Function1D be [3, 2, 4, 1; int(1..4)] +letting q_PermutationAsFunction_PermutationFunction_Function1D be [3, 2, 4, 1; int(1..4)] diff --git a/tests/exhaustive/basic/perms/05_equality/int/0001_given_permutations_in_param/expected/model.eprime b/tests/exhaustive/basic/perms/05_equality/int/0001_given_permutations_in_param/expected/model.eprime new file mode 100644 index 0000000000..167dc8f366 --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/int/0001_given_permutations_in_param/expected/model.eprime @@ -0,0 +1,12 @@ +language ESSENCE' 1.0 + +given p_PermutationAsFunction_PermutationFunction_Function1D: matrix indexed by [int(1..4)] of int(1..4) +given q_PermutationAsFunction_PermutationFunction_Function1D: matrix indexed by [int(1..4)] of int(1..4) +find b: bool +branching on [b] +such that + b = + and([p_PermutationAsFunction_PermutationFunction_Function1D[q1] = + q_PermutationAsFunction_PermutationFunction_Function1D[q1] + | q1 : int(1..4)]) + diff --git a/tests/exhaustive/basic/perms/05_equality/int/0001_given_permutations_in_param/permutation.essence b/tests/exhaustive/basic/perms/05_equality/int/0001_given_permutations_in_param/permutation.essence new file mode 100644 index 0000000000..759f7dfacc --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/int/0001_given_permutations_in_param/permutation.essence @@ -0,0 +1,12 @@ +letting n be 4 + +given p : permutation of int(1..n) +given q : permutation of int(1..n) + +find b : bool + +such that b = (p = q) + + + + diff --git a/tests/exhaustive/basic/perms/05_equality/int/0001_given_permutations_in_param/permutation.param b/tests/exhaustive/basic/perms/05_equality/int/0001_given_permutations_in_param/permutation.param new file mode 100644 index 0000000000..98b582712a --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/int/0001_given_permutations_in_param/permutation.param @@ -0,0 +1,2 @@ +letting p be permutation((1,3,4)) +letting q be permutation((1,3,4)) diff --git a/tests/exhaustive/basic/perms/05_equality/int/0002_given_permutations_in_param/expected/model-permutation-solution000001.solution b/tests/exhaustive/basic/perms/05_equality/int/0002_given_permutations_in_param/expected/model-permutation-solution000001.solution new file mode 100644 index 0000000000..97ec002915 --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/int/0002_given_permutations_in_param/expected/model-permutation-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting b be false diff --git a/tests/exhaustive/basic/perms/05_equality/int/0002_given_permutations_in_param/expected/model-permutation.eprime-param b/tests/exhaustive/basic/perms/05_equality/int/0002_given_permutations_in_param/expected/model-permutation.eprime-param new file mode 100644 index 0000000000..fea0f3fb24 --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/int/0002_given_permutations_in_param/expected/model-permutation.eprime-param @@ -0,0 +1,4 @@ +language ESSENCE' 1.0 + +letting p_PermutationAsFunction_PermutationFunction_Function1D be [3, 2, 4, 1; int(1..4)] +letting q_PermutationAsFunction_PermutationFunction_Function1D be [2, 4, 3, 1; int(1..4)] diff --git a/tests/exhaustive/basic/perms/05_equality/int/0002_given_permutations_in_param/expected/model.eprime b/tests/exhaustive/basic/perms/05_equality/int/0002_given_permutations_in_param/expected/model.eprime new file mode 100644 index 0000000000..167dc8f366 --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/int/0002_given_permutations_in_param/expected/model.eprime @@ -0,0 +1,12 @@ +language ESSENCE' 1.0 + +given p_PermutationAsFunction_PermutationFunction_Function1D: matrix indexed by [int(1..4)] of int(1..4) +given q_PermutationAsFunction_PermutationFunction_Function1D: matrix indexed by [int(1..4)] of int(1..4) +find b: bool +branching on [b] +such that + b = + and([p_PermutationAsFunction_PermutationFunction_Function1D[q1] = + q_PermutationAsFunction_PermutationFunction_Function1D[q1] + | q1 : int(1..4)]) + diff --git a/tests/exhaustive/basic/perms/05_equality/int/0002_given_permutations_in_param/permutation.essence b/tests/exhaustive/basic/perms/05_equality/int/0002_given_permutations_in_param/permutation.essence new file mode 100644 index 0000000000..759f7dfacc --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/int/0002_given_permutations_in_param/permutation.essence @@ -0,0 +1,12 @@ +letting n be 4 + +given p : permutation of int(1..n) +given q : permutation of int(1..n) + +find b : bool + +such that b = (p = q) + + + + diff --git a/tests/exhaustive/basic/perms/05_equality/int/0002_given_permutations_in_param/permutation.param b/tests/exhaustive/basic/perms/05_equality/int/0002_given_permutations_in_param/permutation.param new file mode 100644 index 0000000000..a58ae460a2 --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/int/0002_given_permutations_in_param/permutation.param @@ -0,0 +1,2 @@ +letting p be permutation((1,3,4)) +letting q be permutation((1,2,4)) diff --git a/tests/exhaustive/basic/perms/05_equality/int/0003_given_equal_letting/expected/model-permutation-solution000001.solution b/tests/exhaustive/basic/perms/05_equality/int/0003_given_equal_letting/expected/model-permutation-solution000001.solution new file mode 100644 index 0000000000..97ec002915 --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/int/0003_given_equal_letting/expected/model-permutation-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting b be false diff --git a/tests/exhaustive/basic/perms/05_equality/int/0003_given_equal_letting/expected/model-permutation.eprime-param b/tests/exhaustive/basic/perms/05_equality/int/0003_given_equal_letting/expected/model-permutation.eprime-param new file mode 100644 index 0000000000..c2bddee0e8 --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/int/0003_given_equal_letting/expected/model-permutation.eprime-param @@ -0,0 +1,3 @@ +language ESSENCE' 1.0 + +letting p_PermutationAsFunction_PermutationFunction_Function1D be [3, 2, 4, 1; int(1..4)] diff --git a/tests/exhaustive/basic/perms/05_equality/int/0003_given_equal_letting/expected/model.eprime b/tests/exhaustive/basic/perms/05_equality/int/0003_given_equal_letting/expected/model.eprime new file mode 100644 index 0000000000..09965ef373 --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/int/0003_given_equal_letting/expected/model.eprime @@ -0,0 +1,22 @@ +language ESSENCE' 1.0 + +letting n be 4 +given p_PermutationAsFunction_PermutationFunction_Function1D: matrix indexed by [int(1..4)] of int(1..4) +find b: bool +branching on [b] +such that + b = + (and([or([1 = q8 /\ 2 = p_PermutationAsFunction_PermutationFunction_Function1D[q8], + 2 = q8 /\ 4 = p_PermutationAsFunction_PermutationFunction_Function1D[q8], + 4 = q8 /\ 1 = p_PermutationAsFunction_PermutationFunction_Function1D[q8]; + int(1..3)]) + | q8 : int(1..4), q8 != p_PermutationAsFunction_PermutationFunction_Function1D[q8]]) + /\ + and([or([q16 = 1 /\ p_PermutationAsFunction_PermutationFunction_Function1D[q16] = 2 + | q16 : int(1..4), q16 != p_PermutationAsFunction_PermutationFunction_Function1D[q16]]), + or([q23 = 2 /\ p_PermutationAsFunction_PermutationFunction_Function1D[q23] = 4 + | q23 : int(1..4), q23 != p_PermutationAsFunction_PermutationFunction_Function1D[q23]]), + or([q30 = 4 /\ p_PermutationAsFunction_PermutationFunction_Function1D[q30] = 1 + | q30 : int(1..4), q30 != p_PermutationAsFunction_PermutationFunction_Function1D[q30]]); + int(1..3)])) + diff --git a/tests/exhaustive/basic/perms/05_equality/int/0003_given_equal_letting/permutation.essence b/tests/exhaustive/basic/perms/05_equality/int/0003_given_equal_letting/permutation.essence new file mode 100644 index 0000000000..699aa4ffc8 --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/int/0003_given_equal_letting/permutation.essence @@ -0,0 +1,12 @@ +letting n be 4 + +given p : permutation of int(1..n) +letting q be permutation((1,2,4)) + +find b : bool + +such that b = (p = q) + + + + diff --git a/tests/exhaustive/basic/perms/05_equality/int/0003_given_equal_letting/permutation.param b/tests/exhaustive/basic/perms/05_equality/int/0003_given_equal_letting/permutation.param new file mode 100644 index 0000000000..8a8c516801 --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/int/0003_given_equal_letting/permutation.param @@ -0,0 +1 @@ +letting p be permutation((1,3,4)) diff --git a/tests/exhaustive/basic/perms/05_equality/int/0004_letting_equal_given/expected/model-permutation-solution000001.solution b/tests/exhaustive/basic/perms/05_equality/int/0004_letting_equal_given/expected/model-permutation-solution000001.solution new file mode 100644 index 0000000000..97ec002915 --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/int/0004_letting_equal_given/expected/model-permutation-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting b be false diff --git a/tests/exhaustive/basic/perms/05_equality/int/0004_letting_equal_given/expected/model-permutation.eprime-param b/tests/exhaustive/basic/perms/05_equality/int/0004_letting_equal_given/expected/model-permutation.eprime-param new file mode 100644 index 0000000000..c2bddee0e8 --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/int/0004_letting_equal_given/expected/model-permutation.eprime-param @@ -0,0 +1,3 @@ +language ESSENCE' 1.0 + +letting p_PermutationAsFunction_PermutationFunction_Function1D be [3, 2, 4, 1; int(1..4)] diff --git a/tests/exhaustive/basic/perms/05_equality/int/0004_letting_equal_given/expected/model.eprime b/tests/exhaustive/basic/perms/05_equality/int/0004_letting_equal_given/expected/model.eprime new file mode 100644 index 0000000000..e58dfc930a --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/int/0004_letting_equal_given/expected/model.eprime @@ -0,0 +1,22 @@ +language ESSENCE' 1.0 + +letting n be 4 +given p_PermutationAsFunction_PermutationFunction_Function1D: matrix indexed by [int(1..4)] of int(1..4) +find b: bool +branching on [b] +such that + b = + (and([or([q8 = 1 /\ p_PermutationAsFunction_PermutationFunction_Function1D[q8] = 2 + | q8 : int(1..4), q8 != p_PermutationAsFunction_PermutationFunction_Function1D[q8]]), + or([q15 = 2 /\ p_PermutationAsFunction_PermutationFunction_Function1D[q15] = 4 + | q15 : int(1..4), q15 != p_PermutationAsFunction_PermutationFunction_Function1D[q15]]), + or([q22 = 4 /\ p_PermutationAsFunction_PermutationFunction_Function1D[q22] = 1 + | q22 : int(1..4), q22 != p_PermutationAsFunction_PermutationFunction_Function1D[q22]]); + int(1..3)]) + /\ + and([or([1 = q30 /\ 2 = p_PermutationAsFunction_PermutationFunction_Function1D[q30], + 2 = q30 /\ 4 = p_PermutationAsFunction_PermutationFunction_Function1D[q30], + 4 = q30 /\ 1 = p_PermutationAsFunction_PermutationFunction_Function1D[q30]; + int(1..3)]) + | q30 : int(1..4), q30 != p_PermutationAsFunction_PermutationFunction_Function1D[q30]])) + diff --git a/tests/exhaustive/basic/perms/05_equality/int/0004_letting_equal_given/permutation.essence b/tests/exhaustive/basic/perms/05_equality/int/0004_letting_equal_given/permutation.essence new file mode 100644 index 0000000000..400d6fdcf4 --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/int/0004_letting_equal_given/permutation.essence @@ -0,0 +1,12 @@ +letting n be 4 + +given p : permutation of int(1..n) +letting q be permutation((1,2,4)) + +find b : bool + +such that b = (q = p) + + + + diff --git a/tests/exhaustive/basic/perms/05_equality/int/0004_letting_equal_given/permutation.param b/tests/exhaustive/basic/perms/05_equality/int/0004_letting_equal_given/permutation.param new file mode 100644 index 0000000000..8a8c516801 --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/int/0004_letting_equal_given/permutation.param @@ -0,0 +1 @@ +letting p be permutation((1,3,4)) diff --git a/tests/exhaustive/basic/perms/05_equality/int/0005_find_eq_find/expected/model-solution000001.solution b/tests/exhaustive/basic/perms/05_equality/int/0005_find_eq_find/expected/model-solution000001.solution new file mode 100644 index 0000000000..5e99ad7a05 --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/int/0005_find_eq_find/expected/model-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting p be permutation() +letting q be permutation() diff --git a/tests/exhaustive/basic/perms/05_equality/int/0005_find_eq_find/expected/model-solution000002.solution b/tests/exhaustive/basic/perms/05_equality/int/0005_find_eq_find/expected/model-solution000002.solution new file mode 100644 index 0000000000..d51a2f2ed6 --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/int/0005_find_eq_find/expected/model-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting p be permutation((3, 4)) +letting q be permutation((3, 4)) diff --git a/tests/exhaustive/basic/perms/05_equality/int/0005_find_eq_find/expected/model-solution000003.solution b/tests/exhaustive/basic/perms/05_equality/int/0005_find_eq_find/expected/model-solution000003.solution new file mode 100644 index 0000000000..5c3302f8db --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/int/0005_find_eq_find/expected/model-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting p be permutation((2, 3)) +letting q be permutation((2, 3)) diff --git a/tests/exhaustive/basic/perms/05_equality/int/0005_find_eq_find/expected/model-solution000004.solution b/tests/exhaustive/basic/perms/05_equality/int/0005_find_eq_find/expected/model-solution000004.solution new file mode 100644 index 0000000000..5ab435779d --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/int/0005_find_eq_find/expected/model-solution000004.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting p be permutation((2, 3, 4)) +letting q be permutation((2, 3, 4)) diff --git a/tests/exhaustive/basic/perms/05_equality/int/0005_find_eq_find/expected/model-solution000005.solution b/tests/exhaustive/basic/perms/05_equality/int/0005_find_eq_find/expected/model-solution000005.solution new file mode 100644 index 0000000000..d650d878e0 --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/int/0005_find_eq_find/expected/model-solution000005.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting p be permutation((2, 4, 3)) +letting q be permutation((2, 4, 3)) diff --git a/tests/exhaustive/basic/perms/05_equality/int/0005_find_eq_find/expected/model-solution000006.solution b/tests/exhaustive/basic/perms/05_equality/int/0005_find_eq_find/expected/model-solution000006.solution new file mode 100644 index 0000000000..9aed2f67de --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/int/0005_find_eq_find/expected/model-solution000006.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting p be permutation((2, 4)) +letting q be permutation((2, 4)) diff --git a/tests/exhaustive/basic/perms/05_equality/int/0005_find_eq_find/expected/model-solution000007.solution b/tests/exhaustive/basic/perms/05_equality/int/0005_find_eq_find/expected/model-solution000007.solution new file mode 100644 index 0000000000..5760f6393a --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/int/0005_find_eq_find/expected/model-solution000007.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting p be permutation((1, 2)) +letting q be permutation((1, 2)) diff --git a/tests/exhaustive/basic/perms/05_equality/int/0005_find_eq_find/expected/model-solution000008.solution b/tests/exhaustive/basic/perms/05_equality/int/0005_find_eq_find/expected/model-solution000008.solution new file mode 100644 index 0000000000..57925fc124 --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/int/0005_find_eq_find/expected/model-solution000008.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4)) +letting q be permutation((1, 2), (3, 4)) diff --git a/tests/exhaustive/basic/perms/05_equality/int/0005_find_eq_find/expected/model-solution000009.solution b/tests/exhaustive/basic/perms/05_equality/int/0005_find_eq_find/expected/model-solution000009.solution new file mode 100644 index 0000000000..461ebbb082 --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/int/0005_find_eq_find/expected/model-solution000009.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting p be permutation((1, 2, 3)) +letting q be permutation((1, 2, 3)) diff --git a/tests/exhaustive/basic/perms/05_equality/int/0005_find_eq_find/expected/model-solution000010.solution b/tests/exhaustive/basic/perms/05_equality/int/0005_find_eq_find/expected/model-solution000010.solution new file mode 100644 index 0000000000..1c6903f54c --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/int/0005_find_eq_find/expected/model-solution000010.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting p be permutation((1, 2, 3, 4)) +letting q be permutation((1, 2, 3, 4)) diff --git a/tests/exhaustive/basic/perms/05_equality/int/0005_find_eq_find/expected/model-solution000011.solution b/tests/exhaustive/basic/perms/05_equality/int/0005_find_eq_find/expected/model-solution000011.solution new file mode 100644 index 0000000000..1ca62c257c --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/int/0005_find_eq_find/expected/model-solution000011.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting p be permutation((1, 2, 4, 3)) +letting q be permutation((1, 2, 4, 3)) diff --git a/tests/exhaustive/basic/perms/05_equality/int/0005_find_eq_find/expected/model-solution000012.solution b/tests/exhaustive/basic/perms/05_equality/int/0005_find_eq_find/expected/model-solution000012.solution new file mode 100644 index 0000000000..18776adc7a --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/int/0005_find_eq_find/expected/model-solution000012.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting p be permutation((1, 2, 4)) +letting q be permutation((1, 2, 4)) diff --git a/tests/exhaustive/basic/perms/05_equality/int/0005_find_eq_find/expected/model-solution000013.solution b/tests/exhaustive/basic/perms/05_equality/int/0005_find_eq_find/expected/model-solution000013.solution new file mode 100644 index 0000000000..b9765f1249 --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/int/0005_find_eq_find/expected/model-solution000013.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting p be permutation((1, 3, 2)) +letting q be permutation((1, 3, 2)) diff --git a/tests/exhaustive/basic/perms/05_equality/int/0005_find_eq_find/expected/model-solution000014.solution b/tests/exhaustive/basic/perms/05_equality/int/0005_find_eq_find/expected/model-solution000014.solution new file mode 100644 index 0000000000..13a4a44ffa --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/int/0005_find_eq_find/expected/model-solution000014.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting p be permutation((1, 3, 4, 2)) +letting q be permutation((1, 3, 4, 2)) diff --git a/tests/exhaustive/basic/perms/05_equality/int/0005_find_eq_find/expected/model-solution000015.solution b/tests/exhaustive/basic/perms/05_equality/int/0005_find_eq_find/expected/model-solution000015.solution new file mode 100644 index 0000000000..e622738f3b --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/int/0005_find_eq_find/expected/model-solution000015.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting p be permutation((1, 3)) +letting q be permutation((1, 3)) diff --git a/tests/exhaustive/basic/perms/05_equality/int/0005_find_eq_find/expected/model-solution000016.solution b/tests/exhaustive/basic/perms/05_equality/int/0005_find_eq_find/expected/model-solution000016.solution new file mode 100644 index 0000000000..118e4eae87 --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/int/0005_find_eq_find/expected/model-solution000016.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting p be permutation((1, 3, 4)) +letting q be permutation((1, 3, 4)) diff --git a/tests/exhaustive/basic/perms/05_equality/int/0005_find_eq_find/expected/model-solution000017.solution b/tests/exhaustive/basic/perms/05_equality/int/0005_find_eq_find/expected/model-solution000017.solution new file mode 100644 index 0000000000..ed94b069c6 --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/int/0005_find_eq_find/expected/model-solution000017.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting p be permutation((1, 3), (2, 4)) +letting q be permutation((1, 3), (2, 4)) diff --git a/tests/exhaustive/basic/perms/05_equality/int/0005_find_eq_find/expected/model-solution000018.solution b/tests/exhaustive/basic/perms/05_equality/int/0005_find_eq_find/expected/model-solution000018.solution new file mode 100644 index 0000000000..fbaf3222e9 --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/int/0005_find_eq_find/expected/model-solution000018.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting p be permutation((1, 3, 2, 4)) +letting q be permutation((1, 3, 2, 4)) diff --git a/tests/exhaustive/basic/perms/05_equality/int/0005_find_eq_find/expected/model-solution000019.solution b/tests/exhaustive/basic/perms/05_equality/int/0005_find_eq_find/expected/model-solution000019.solution new file mode 100644 index 0000000000..d8c5b666b5 --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/int/0005_find_eq_find/expected/model-solution000019.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting p be permutation((1, 4, 3, 2)) +letting q be permutation((1, 4, 3, 2)) diff --git a/tests/exhaustive/basic/perms/05_equality/int/0005_find_eq_find/expected/model-solution000020.solution b/tests/exhaustive/basic/perms/05_equality/int/0005_find_eq_find/expected/model-solution000020.solution new file mode 100644 index 0000000000..b6e0a953f8 --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/int/0005_find_eq_find/expected/model-solution000020.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting p be permutation((1, 4, 2)) +letting q be permutation((1, 4, 2)) diff --git a/tests/exhaustive/basic/perms/05_equality/int/0005_find_eq_find/expected/model-solution000021.solution b/tests/exhaustive/basic/perms/05_equality/int/0005_find_eq_find/expected/model-solution000021.solution new file mode 100644 index 0000000000..8b898f5f36 --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/int/0005_find_eq_find/expected/model-solution000021.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting p be permutation((1, 4, 3)) +letting q be permutation((1, 4, 3)) diff --git a/tests/exhaustive/basic/perms/05_equality/int/0005_find_eq_find/expected/model-solution000022.solution b/tests/exhaustive/basic/perms/05_equality/int/0005_find_eq_find/expected/model-solution000022.solution new file mode 100644 index 0000000000..a9675be6a3 --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/int/0005_find_eq_find/expected/model-solution000022.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting p be permutation((1, 4)) +letting q be permutation((1, 4)) diff --git a/tests/exhaustive/basic/perms/05_equality/int/0005_find_eq_find/expected/model-solution000023.solution b/tests/exhaustive/basic/perms/05_equality/int/0005_find_eq_find/expected/model-solution000023.solution new file mode 100644 index 0000000000..3cf43d6c47 --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/int/0005_find_eq_find/expected/model-solution000023.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting p be permutation((1, 4, 2, 3)) +letting q be permutation((1, 4, 2, 3)) diff --git a/tests/exhaustive/basic/perms/05_equality/int/0005_find_eq_find/expected/model-solution000024.solution b/tests/exhaustive/basic/perms/05_equality/int/0005_find_eq_find/expected/model-solution000024.solution new file mode 100644 index 0000000000..fa74c1f6bc --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/int/0005_find_eq_find/expected/model-solution000024.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting p be permutation((1, 4), (2, 3)) +letting q be permutation((1, 4), (2, 3)) diff --git a/tests/exhaustive/basic/perms/05_equality/int/0005_find_eq_find/expected/model.eprime b/tests/exhaustive/basic/perms/05_equality/int/0005_find_eq_find/expected/model.eprime new file mode 100644 index 0000000000..f1a2530c1a --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/int/0005_find_eq_find/expected/model.eprime @@ -0,0 +1,15 @@ +language ESSENCE' 1.0 + +find p_PermutationAsFunction_PermutationFunction_Function1D: matrix indexed by [int(1..4)] of int(1..4) +find q_PermutationAsFunction_PermutationFunction_Function1D: matrix indexed by [int(1..4)] of int(1..4) +branching on + [p_PermutationAsFunction_PermutationFunction_Function1D, q_PermutationAsFunction_PermutationFunction_Function1D] +such that + and([q_PermutationAsFunction_PermutationFunction_Function1D[q9] = + p_PermutationAsFunction_PermutationFunction_Function1D[q9] + | q9 : int(1..4)]), + allDiff(q_PermutationAsFunction_PermutationFunction_Function1D), + and([or([q_PermutationAsFunction_PermutationFunction_Function1D[q3] = q2 | q3 : int(1..4)]) | q2 : int(1..4)]), + allDiff(p_PermutationAsFunction_PermutationFunction_Function1D), + and([or([p_PermutationAsFunction_PermutationFunction_Function1D[q7] = q6 | q7 : int(1..4)]) | q6 : int(1..4)]) + diff --git a/tests/exhaustive/basic/perms/05_equality/int/0005_find_eq_find/permutation.essence b/tests/exhaustive/basic/perms/05_equality/int/0005_find_eq_find/permutation.essence new file mode 100644 index 0000000000..cd79b60584 --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/int/0005_find_eq_find/permutation.essence @@ -0,0 +1,8 @@ +find p : permutation of int(1..4) +find q : permutation of int(1..4) + +such that q = p + + + + diff --git a/tests/exhaustive/basic/perms/05_equality/int/0006_in_comprehension/expected/model-solution000001.solution b/tests/exhaustive/basic/perms/05_equality/int/0006_in_comprehension/expected/model-solution000001.solution new file mode 100644 index 0000000000..f79cb5a645 --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/int/0006_in_comprehension/expected/model-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4)) +letting q be permutation((1, 3), (2, 4)) diff --git a/tests/exhaustive/basic/perms/05_equality/int/0006_in_comprehension/expected/model-solution000002.solution b/tests/exhaustive/basic/perms/05_equality/int/0006_in_comprehension/expected/model-solution000002.solution new file mode 100644 index 0000000000..8f51d44e59 --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/int/0006_in_comprehension/expected/model-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4)) +letting q be permutation((1, 3, 2, 4)) diff --git a/tests/exhaustive/basic/perms/05_equality/int/0006_in_comprehension/expected/model-solution000003.solution b/tests/exhaustive/basic/perms/05_equality/int/0006_in_comprehension/expected/model-solution000003.solution new file mode 100644 index 0000000000..8e0e10c83f --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/int/0006_in_comprehension/expected/model-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4)) +letting q be permutation((1, 4, 2, 3)) diff --git a/tests/exhaustive/basic/perms/05_equality/int/0006_in_comprehension/expected/model-solution000004.solution b/tests/exhaustive/basic/perms/05_equality/int/0006_in_comprehension/expected/model-solution000004.solution new file mode 100644 index 0000000000..5c03976813 --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/int/0006_in_comprehension/expected/model-solution000004.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4)) +letting q be permutation((1, 4), (2, 3)) diff --git a/tests/exhaustive/basic/perms/05_equality/int/0006_in_comprehension/expected/model-solution000005.solution b/tests/exhaustive/basic/perms/05_equality/int/0006_in_comprehension/expected/model-solution000005.solution new file mode 100644 index 0000000000..460c8b5512 --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/int/0006_in_comprehension/expected/model-solution000005.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting p be permutation((1, 2, 3, 4)) +letting q be permutation((1, 3), (2, 4)) diff --git a/tests/exhaustive/basic/perms/05_equality/int/0006_in_comprehension/expected/model-solution000006.solution b/tests/exhaustive/basic/perms/05_equality/int/0006_in_comprehension/expected/model-solution000006.solution new file mode 100644 index 0000000000..a4cbf995e9 --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/int/0006_in_comprehension/expected/model-solution000006.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting p be permutation((1, 2, 3, 4)) +letting q be permutation((1, 4, 3, 2)) diff --git a/tests/exhaustive/basic/perms/05_equality/int/0006_in_comprehension/expected/model-solution000007.solution b/tests/exhaustive/basic/perms/05_equality/int/0006_in_comprehension/expected/model-solution000007.solution new file mode 100644 index 0000000000..66a2f1e65b --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/int/0006_in_comprehension/expected/model-solution000007.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting p be permutation((1, 2, 4, 3)) +letting q be permutation((1, 3, 4, 2)) diff --git a/tests/exhaustive/basic/perms/05_equality/int/0006_in_comprehension/expected/model-solution000008.solution b/tests/exhaustive/basic/perms/05_equality/int/0006_in_comprehension/expected/model-solution000008.solution new file mode 100644 index 0000000000..f514c4c68c --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/int/0006_in_comprehension/expected/model-solution000008.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting p be permutation((1, 2, 4, 3)) +letting q be permutation((1, 4), (2, 3)) diff --git a/tests/exhaustive/basic/perms/05_equality/int/0006_in_comprehension/expected/model-solution000009.solution b/tests/exhaustive/basic/perms/05_equality/int/0006_in_comprehension/expected/model-solution000009.solution new file mode 100644 index 0000000000..af5b4b29f3 --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/int/0006_in_comprehension/expected/model-solution000009.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting p be permutation((1, 3, 4, 2)) +letting q be permutation((1, 2, 4, 3)) diff --git a/tests/exhaustive/basic/perms/05_equality/int/0006_in_comprehension/expected/model-solution000010.solution b/tests/exhaustive/basic/perms/05_equality/int/0006_in_comprehension/expected/model-solution000010.solution new file mode 100644 index 0000000000..970e0321ca --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/int/0006_in_comprehension/expected/model-solution000010.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting p be permutation((1, 3, 4, 2)) +letting q be permutation((1, 4), (2, 3)) diff --git a/tests/exhaustive/basic/perms/05_equality/int/0006_in_comprehension/expected/model-solution000011.solution b/tests/exhaustive/basic/perms/05_equality/int/0006_in_comprehension/expected/model-solution000011.solution new file mode 100644 index 0000000000..8315602e8d --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/int/0006_in_comprehension/expected/model-solution000011.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting p be permutation((1, 3), (2, 4)) +letting q be permutation((1, 2), (3, 4)) diff --git a/tests/exhaustive/basic/perms/05_equality/int/0006_in_comprehension/expected/model-solution000012.solution b/tests/exhaustive/basic/perms/05_equality/int/0006_in_comprehension/expected/model-solution000012.solution new file mode 100644 index 0000000000..2204f5074c --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/int/0006_in_comprehension/expected/model-solution000012.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting p be permutation((1, 3), (2, 4)) +letting q be permutation((1, 2, 3, 4)) diff --git a/tests/exhaustive/basic/perms/05_equality/int/0006_in_comprehension/expected/model-solution000013.solution b/tests/exhaustive/basic/perms/05_equality/int/0006_in_comprehension/expected/model-solution000013.solution new file mode 100644 index 0000000000..62e5676c64 --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/int/0006_in_comprehension/expected/model-solution000013.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting p be permutation((1, 3), (2, 4)) +letting q be permutation((1, 4, 3, 2)) diff --git a/tests/exhaustive/basic/perms/05_equality/int/0006_in_comprehension/expected/model-solution000014.solution b/tests/exhaustive/basic/perms/05_equality/int/0006_in_comprehension/expected/model-solution000014.solution new file mode 100644 index 0000000000..a27d73dc0f --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/int/0006_in_comprehension/expected/model-solution000014.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting p be permutation((1, 3), (2, 4)) +letting q be permutation((1, 4), (2, 3)) diff --git a/tests/exhaustive/basic/perms/05_equality/int/0006_in_comprehension/expected/model-solution000015.solution b/tests/exhaustive/basic/perms/05_equality/int/0006_in_comprehension/expected/model-solution000015.solution new file mode 100644 index 0000000000..cb6828e835 --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/int/0006_in_comprehension/expected/model-solution000015.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting p be permutation((1, 3, 2, 4)) +letting q be permutation((1, 2), (3, 4)) diff --git a/tests/exhaustive/basic/perms/05_equality/int/0006_in_comprehension/expected/model-solution000016.solution b/tests/exhaustive/basic/perms/05_equality/int/0006_in_comprehension/expected/model-solution000016.solution new file mode 100644 index 0000000000..3a66e67752 --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/int/0006_in_comprehension/expected/model-solution000016.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting p be permutation((1, 3, 2, 4)) +letting q be permutation((1, 4, 2, 3)) diff --git a/tests/exhaustive/basic/perms/05_equality/int/0006_in_comprehension/expected/model-solution000017.solution b/tests/exhaustive/basic/perms/05_equality/int/0006_in_comprehension/expected/model-solution000017.solution new file mode 100644 index 0000000000..83b0838785 --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/int/0006_in_comprehension/expected/model-solution000017.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting p be permutation((1, 4, 3, 2)) +letting q be permutation((1, 2, 3, 4)) diff --git a/tests/exhaustive/basic/perms/05_equality/int/0006_in_comprehension/expected/model-solution000018.solution b/tests/exhaustive/basic/perms/05_equality/int/0006_in_comprehension/expected/model-solution000018.solution new file mode 100644 index 0000000000..148ef18ea5 --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/int/0006_in_comprehension/expected/model-solution000018.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting p be permutation((1, 4, 3, 2)) +letting q be permutation((1, 3), (2, 4)) diff --git a/tests/exhaustive/basic/perms/05_equality/int/0006_in_comprehension/expected/model-solution000019.solution b/tests/exhaustive/basic/perms/05_equality/int/0006_in_comprehension/expected/model-solution000019.solution new file mode 100644 index 0000000000..a1dd0fc116 --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/int/0006_in_comprehension/expected/model-solution000019.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting p be permutation((1, 4, 2, 3)) +letting q be permutation((1, 2), (3, 4)) diff --git a/tests/exhaustive/basic/perms/05_equality/int/0006_in_comprehension/expected/model-solution000020.solution b/tests/exhaustive/basic/perms/05_equality/int/0006_in_comprehension/expected/model-solution000020.solution new file mode 100644 index 0000000000..e820c11b06 --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/int/0006_in_comprehension/expected/model-solution000020.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting p be permutation((1, 4, 2, 3)) +letting q be permutation((1, 3, 2, 4)) diff --git a/tests/exhaustive/basic/perms/05_equality/int/0006_in_comprehension/expected/model-solution000021.solution b/tests/exhaustive/basic/perms/05_equality/int/0006_in_comprehension/expected/model-solution000021.solution new file mode 100644 index 0000000000..7daee759cb --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/int/0006_in_comprehension/expected/model-solution000021.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting p be permutation((1, 4), (2, 3)) +letting q be permutation((1, 2), (3, 4)) diff --git a/tests/exhaustive/basic/perms/05_equality/int/0006_in_comprehension/expected/model-solution000022.solution b/tests/exhaustive/basic/perms/05_equality/int/0006_in_comprehension/expected/model-solution000022.solution new file mode 100644 index 0000000000..4f246093b8 --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/int/0006_in_comprehension/expected/model-solution000022.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting p be permutation((1, 4), (2, 3)) +letting q be permutation((1, 2, 4, 3)) diff --git a/tests/exhaustive/basic/perms/05_equality/int/0006_in_comprehension/expected/model-solution000023.solution b/tests/exhaustive/basic/perms/05_equality/int/0006_in_comprehension/expected/model-solution000023.solution new file mode 100644 index 0000000000..60f0efb84a --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/int/0006_in_comprehension/expected/model-solution000023.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting p be permutation((1, 4), (2, 3)) +letting q be permutation((1, 3, 4, 2)) diff --git a/tests/exhaustive/basic/perms/05_equality/int/0006_in_comprehension/expected/model-solution000024.solution b/tests/exhaustive/basic/perms/05_equality/int/0006_in_comprehension/expected/model-solution000024.solution new file mode 100644 index 0000000000..426df4ee11 --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/int/0006_in_comprehension/expected/model-solution000024.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting p be permutation((1, 4), (2, 3)) +letting q be permutation((1, 3), (2, 4)) diff --git a/tests/exhaustive/basic/perms/05_equality/int/0006_in_comprehension/expected/model.eprime b/tests/exhaustive/basic/perms/05_equality/int/0006_in_comprehension/expected/model.eprime new file mode 100644 index 0000000000..b06a4e1b4e --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/int/0006_in_comprehension/expected/model.eprime @@ -0,0 +1,21 @@ +language ESSENCE' 1.0 + +find p_PermutationAsFunction_PermutationFunction_Function1D: matrix indexed by [int(1..4)] of int(1..4) +find q_PermutationAsFunction_PermutationFunction_Function1D: matrix indexed by [int(1..4)] of int(1..4) +branching on + [p_PermutationAsFunction_PermutationFunction_Function1D, q_PermutationAsFunction_PermutationFunction_Function1D] +such that + and([q20 != q_PermutationAsFunction_PermutationFunction_Function1D[q20] /\ + q14 != p_PermutationAsFunction_PermutationFunction_Function1D[q14] + -> + !(q14 = q20 /\ + p_PermutationAsFunction_PermutationFunction_Function1D[q14] = + q_PermutationAsFunction_PermutationFunction_Function1D[q20]) + | q14 : int(1..4), q20 : int(1..4)]), + allDiff(p_PermutationAsFunction_PermutationFunction_Function1D), + and([or([p_PermutationAsFunction_PermutationFunction_Function1D[q3] = q2 | q3 : int(1..4)]) | q2 : int(1..4)]), + 4 = sum([toInt(q1 != p_PermutationAsFunction_PermutationFunction_Function1D[q1]) | q1 : int(1..4)]), + allDiff(q_PermutationAsFunction_PermutationFunction_Function1D), + and([or([q_PermutationAsFunction_PermutationFunction_Function1D[q7] = q6 | q7 : int(1..4)]) | q6 : int(1..4)]), + 4 = sum([toInt(q5 != q_PermutationAsFunction_PermutationFunction_Function1D[q5]) | q5 : int(1..4)]) + diff --git a/tests/exhaustive/basic/perms/05_equality/int/0006_in_comprehension/permutation.essence b/tests/exhaustive/basic/perms/05_equality/int/0006_in_comprehension/permutation.essence new file mode 100644 index 0000000000..eab596738f --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/int/0006_in_comprehension/permutation.essence @@ -0,0 +1,6 @@ +find p : permutation (size 4) of int(1..4) +find q : permutation (size 4) of int(1..4) + +such that + and([pt != qt | pt <- p, qt <- q]) + diff --git a/tests/exhaustive/basic/perms/05_equality/int/0007_letting_equal_letting/expected/model-solution000001.solution b/tests/exhaustive/basic/perms/05_equality/int/0007_letting_equal_letting/expected/model-solution000001.solution new file mode 100644 index 0000000000..97ec002915 --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/int/0007_letting_equal_letting/expected/model-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting b be false diff --git a/tests/exhaustive/basic/perms/05_equality/int/0007_letting_equal_letting/expected/model.eprime b/tests/exhaustive/basic/perms/05_equality/int/0007_letting_equal_letting/expected/model.eprime new file mode 100644 index 0000000000..873089f397 --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/int/0007_letting_equal_letting/expected/model.eprime @@ -0,0 +1,6 @@ +language ESSENCE' 1.0 + +find b: bool +branching on [b] +such that b = false + diff --git a/tests/exhaustive/basic/perms/05_equality/int/0007_letting_equal_letting/permutation.essence b/tests/exhaustive/basic/perms/05_equality/int/0007_letting_equal_letting/permutation.essence new file mode 100644 index 0000000000..77fdcef849 --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/int/0007_letting_equal_letting/permutation.essence @@ -0,0 +1,4 @@ +letting s be permutation((3, 4)) +letting sn be permutation((1, 4), (2, 3)) +find b : bool +such that b = (s = sn) diff --git a/tests/exhaustive/basic/perms/05_equality/int/expected/model-solution000001.solution b/tests/exhaustive/basic/perms/05_equality/int/expected/model-solution000001.solution new file mode 100644 index 0000000000..97ec002915 --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/int/expected/model-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting b be false diff --git a/tests/exhaustive/basic/perms/05_equality/int/expected/model.eprime b/tests/exhaustive/basic/perms/05_equality/int/expected/model.eprime new file mode 100644 index 0000000000..873089f397 --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/int/expected/model.eprime @@ -0,0 +1,6 @@ +language ESSENCE' 1.0 + +find b: bool +branching on [b] +such that b = false + diff --git a/tests/exhaustive/basic/perms/05_equality/int/new.essence b/tests/exhaustive/basic/perms/05_equality/int/new.essence new file mode 100644 index 0000000000..77fdcef849 --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/int/new.essence @@ -0,0 +1,4 @@ +letting s be permutation((3, 4)) +letting sn be permutation((1, 4), (2, 3)) +find b : bool +such that b = (s = sn) diff --git a/tests/exhaustive/basic/perms/05_equality/unnamed/0005_find_eq_find/expected/model-solution000001.solution b/tests/exhaustive/basic/perms/05_equality/unnamed/0005_find_eq_find/expected/model-solution000001.solution new file mode 100644 index 0000000000..62ed8f479d --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/unnamed/0005_find_eq_find/expected/model-solution000001.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation() +letting q be permutation() diff --git a/tests/exhaustive/basic/perms/05_equality/unnamed/0005_find_eq_find/expected/model-solution000002.solution b/tests/exhaustive/basic/perms/05_equality/unnamed/0005_find_eq_find/expected/model-solution000002.solution new file mode 100644 index 0000000000..0ddce59556 --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/unnamed/0005_find_eq_find/expected/model-solution000002.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_3, n_4)) +letting q be permutation((n_3, n_4)) diff --git a/tests/exhaustive/basic/perms/05_equality/unnamed/0005_find_eq_find/expected/model-solution000003.solution b/tests/exhaustive/basic/perms/05_equality/unnamed/0005_find_eq_find/expected/model-solution000003.solution new file mode 100644 index 0000000000..79869ab012 --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/unnamed/0005_find_eq_find/expected/model-solution000003.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_2, n_3)) +letting q be permutation((n_2, n_3)) diff --git a/tests/exhaustive/basic/perms/05_equality/unnamed/0005_find_eq_find/expected/model-solution000004.solution b/tests/exhaustive/basic/perms/05_equality/unnamed/0005_find_eq_find/expected/model-solution000004.solution new file mode 100644 index 0000000000..1461108679 --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/unnamed/0005_find_eq_find/expected/model-solution000004.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_2, n_3, n_4)) +letting q be permutation((n_2, n_3, n_4)) diff --git a/tests/exhaustive/basic/perms/05_equality/unnamed/0005_find_eq_find/expected/model-solution000005.solution b/tests/exhaustive/basic/perms/05_equality/unnamed/0005_find_eq_find/expected/model-solution000005.solution new file mode 100644 index 0000000000..42638edc81 --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/unnamed/0005_find_eq_find/expected/model-solution000005.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_2, n_4, n_3)) +letting q be permutation((n_2, n_4, n_3)) diff --git a/tests/exhaustive/basic/perms/05_equality/unnamed/0005_find_eq_find/expected/model-solution000006.solution b/tests/exhaustive/basic/perms/05_equality/unnamed/0005_find_eq_find/expected/model-solution000006.solution new file mode 100644 index 0000000000..d29c95896f --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/unnamed/0005_find_eq_find/expected/model-solution000006.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_2, n_4)) +letting q be permutation((n_2, n_4)) diff --git a/tests/exhaustive/basic/perms/05_equality/unnamed/0005_find_eq_find/expected/model-solution000007.solution b/tests/exhaustive/basic/perms/05_equality/unnamed/0005_find_eq_find/expected/model-solution000007.solution new file mode 100644 index 0000000000..416a44807f --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/unnamed/0005_find_eq_find/expected/model-solution000007.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_1, n_2)) +letting q be permutation((n_1, n_2)) diff --git a/tests/exhaustive/basic/perms/05_equality/unnamed/0005_find_eq_find/expected/model-solution000008.solution b/tests/exhaustive/basic/perms/05_equality/unnamed/0005_find_eq_find/expected/model-solution000008.solution new file mode 100644 index 0000000000..39e797413c --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/unnamed/0005_find_eq_find/expected/model-solution000008.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_1, n_2), (n_3, n_4)) +letting q be permutation((n_1, n_2), (n_3, n_4)) diff --git a/tests/exhaustive/basic/perms/05_equality/unnamed/0005_find_eq_find/expected/model-solution000009.solution b/tests/exhaustive/basic/perms/05_equality/unnamed/0005_find_eq_find/expected/model-solution000009.solution new file mode 100644 index 0000000000..ff54245ba4 --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/unnamed/0005_find_eq_find/expected/model-solution000009.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_1, n_2, n_3)) +letting q be permutation((n_1, n_2, n_3)) diff --git a/tests/exhaustive/basic/perms/05_equality/unnamed/0005_find_eq_find/expected/model-solution000010.solution b/tests/exhaustive/basic/perms/05_equality/unnamed/0005_find_eq_find/expected/model-solution000010.solution new file mode 100644 index 0000000000..c4a333f8a4 --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/unnamed/0005_find_eq_find/expected/model-solution000010.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_1, n_2, n_3, n_4)) +letting q be permutation((n_1, n_2, n_3, n_4)) diff --git a/tests/exhaustive/basic/perms/05_equality/unnamed/0005_find_eq_find/expected/model-solution000011.solution b/tests/exhaustive/basic/perms/05_equality/unnamed/0005_find_eq_find/expected/model-solution000011.solution new file mode 100644 index 0000000000..0efd2fde8e --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/unnamed/0005_find_eq_find/expected/model-solution000011.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_1, n_2, n_4, n_3)) +letting q be permutation((n_1, n_2, n_4, n_3)) diff --git a/tests/exhaustive/basic/perms/05_equality/unnamed/0005_find_eq_find/expected/model-solution000012.solution b/tests/exhaustive/basic/perms/05_equality/unnamed/0005_find_eq_find/expected/model-solution000012.solution new file mode 100644 index 0000000000..99452e0b3b --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/unnamed/0005_find_eq_find/expected/model-solution000012.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_1, n_2, n_4)) +letting q be permutation((n_1, n_2, n_4)) diff --git a/tests/exhaustive/basic/perms/05_equality/unnamed/0005_find_eq_find/expected/model-solution000013.solution b/tests/exhaustive/basic/perms/05_equality/unnamed/0005_find_eq_find/expected/model-solution000013.solution new file mode 100644 index 0000000000..081f94d03f --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/unnamed/0005_find_eq_find/expected/model-solution000013.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_1, n_3, n_2)) +letting q be permutation((n_1, n_3, n_2)) diff --git a/tests/exhaustive/basic/perms/05_equality/unnamed/0005_find_eq_find/expected/model-solution000014.solution b/tests/exhaustive/basic/perms/05_equality/unnamed/0005_find_eq_find/expected/model-solution000014.solution new file mode 100644 index 0000000000..1429c3c054 --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/unnamed/0005_find_eq_find/expected/model-solution000014.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_1, n_3, n_4, n_2)) +letting q be permutation((n_1, n_3, n_4, n_2)) diff --git a/tests/exhaustive/basic/perms/05_equality/unnamed/0005_find_eq_find/expected/model-solution000015.solution b/tests/exhaustive/basic/perms/05_equality/unnamed/0005_find_eq_find/expected/model-solution000015.solution new file mode 100644 index 0000000000..f33da1e2a1 --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/unnamed/0005_find_eq_find/expected/model-solution000015.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_1, n_3)) +letting q be permutation((n_1, n_3)) diff --git a/tests/exhaustive/basic/perms/05_equality/unnamed/0005_find_eq_find/expected/model-solution000016.solution b/tests/exhaustive/basic/perms/05_equality/unnamed/0005_find_eq_find/expected/model-solution000016.solution new file mode 100644 index 0000000000..949e7ba70d --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/unnamed/0005_find_eq_find/expected/model-solution000016.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_1, n_3, n_4)) +letting q be permutation((n_1, n_3, n_4)) diff --git a/tests/exhaustive/basic/perms/05_equality/unnamed/0005_find_eq_find/expected/model-solution000017.solution b/tests/exhaustive/basic/perms/05_equality/unnamed/0005_find_eq_find/expected/model-solution000017.solution new file mode 100644 index 0000000000..8647f75922 --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/unnamed/0005_find_eq_find/expected/model-solution000017.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_1, n_3), (n_2, n_4)) +letting q be permutation((n_1, n_3), (n_2, n_4)) diff --git a/tests/exhaustive/basic/perms/05_equality/unnamed/0005_find_eq_find/expected/model-solution000018.solution b/tests/exhaustive/basic/perms/05_equality/unnamed/0005_find_eq_find/expected/model-solution000018.solution new file mode 100644 index 0000000000..916f303ee2 --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/unnamed/0005_find_eq_find/expected/model-solution000018.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_1, n_3, n_2, n_4)) +letting q be permutation((n_1, n_3, n_2, n_4)) diff --git a/tests/exhaustive/basic/perms/05_equality/unnamed/0005_find_eq_find/expected/model-solution000019.solution b/tests/exhaustive/basic/perms/05_equality/unnamed/0005_find_eq_find/expected/model-solution000019.solution new file mode 100644 index 0000000000..7a531c09e9 --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/unnamed/0005_find_eq_find/expected/model-solution000019.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_1, n_4, n_3, n_2)) +letting q be permutation((n_1, n_4, n_3, n_2)) diff --git a/tests/exhaustive/basic/perms/05_equality/unnamed/0005_find_eq_find/expected/model-solution000020.solution b/tests/exhaustive/basic/perms/05_equality/unnamed/0005_find_eq_find/expected/model-solution000020.solution new file mode 100644 index 0000000000..296e4f9198 --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/unnamed/0005_find_eq_find/expected/model-solution000020.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_1, n_4, n_2)) +letting q be permutation((n_1, n_4, n_2)) diff --git a/tests/exhaustive/basic/perms/05_equality/unnamed/0005_find_eq_find/expected/model-solution000021.solution b/tests/exhaustive/basic/perms/05_equality/unnamed/0005_find_eq_find/expected/model-solution000021.solution new file mode 100644 index 0000000000..ae413056b8 --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/unnamed/0005_find_eq_find/expected/model-solution000021.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_1, n_4, n_3)) +letting q be permutation((n_1, n_4, n_3)) diff --git a/tests/exhaustive/basic/perms/05_equality/unnamed/0005_find_eq_find/expected/model-solution000022.solution b/tests/exhaustive/basic/perms/05_equality/unnamed/0005_find_eq_find/expected/model-solution000022.solution new file mode 100644 index 0000000000..9f584a929e --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/unnamed/0005_find_eq_find/expected/model-solution000022.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_1, n_4)) +letting q be permutation((n_1, n_4)) diff --git a/tests/exhaustive/basic/perms/05_equality/unnamed/0005_find_eq_find/expected/model-solution000023.solution b/tests/exhaustive/basic/perms/05_equality/unnamed/0005_find_eq_find/expected/model-solution000023.solution new file mode 100644 index 0000000000..b2e63b6b65 --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/unnamed/0005_find_eq_find/expected/model-solution000023.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_1, n_4, n_2, n_3)) +letting q be permutation((n_1, n_4, n_2, n_3)) diff --git a/tests/exhaustive/basic/perms/05_equality/unnamed/0005_find_eq_find/expected/model-solution000024.solution b/tests/exhaustive/basic/perms/05_equality/unnamed/0005_find_eq_find/expected/model-solution000024.solution new file mode 100644 index 0000000000..395d2dcf8e --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/unnamed/0005_find_eq_find/expected/model-solution000024.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_1, n_4), (n_2, n_3)) +letting q be permutation((n_1, n_4), (n_2, n_3)) diff --git a/tests/exhaustive/basic/perms/05_equality/unnamed/0005_find_eq_find/expected/model.eprime b/tests/exhaustive/basic/perms/05_equality/unnamed/0005_find_eq_find/expected/model.eprime new file mode 100644 index 0000000000..f1a2530c1a --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/unnamed/0005_find_eq_find/expected/model.eprime @@ -0,0 +1,15 @@ +language ESSENCE' 1.0 + +find p_PermutationAsFunction_PermutationFunction_Function1D: matrix indexed by [int(1..4)] of int(1..4) +find q_PermutationAsFunction_PermutationFunction_Function1D: matrix indexed by [int(1..4)] of int(1..4) +branching on + [p_PermutationAsFunction_PermutationFunction_Function1D, q_PermutationAsFunction_PermutationFunction_Function1D] +such that + and([q_PermutationAsFunction_PermutationFunction_Function1D[q9] = + p_PermutationAsFunction_PermutationFunction_Function1D[q9] + | q9 : int(1..4)]), + allDiff(q_PermutationAsFunction_PermutationFunction_Function1D), + and([or([q_PermutationAsFunction_PermutationFunction_Function1D[q3] = q2 | q3 : int(1..4)]) | q2 : int(1..4)]), + allDiff(p_PermutationAsFunction_PermutationFunction_Function1D), + and([or([p_PermutationAsFunction_PermutationFunction_Function1D[q7] = q6 | q7 : int(1..4)]) | q6 : int(1..4)]) + diff --git a/tests/exhaustive/basic/perms/05_equality/unnamed/0005_find_eq_find/permutation.essence b/tests/exhaustive/basic/perms/05_equality/unnamed/0005_find_eq_find/permutation.essence new file mode 100644 index 0000000000..00112283a9 --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/unnamed/0005_find_eq_find/permutation.essence @@ -0,0 +1,10 @@ +letting n be new type of size 4 + +find p : permutation of n +find q : permutation of n + +such that q = p + + + + diff --git a/tests/exhaustive/basic/perms/05_equality/unnamed/0006_in_comprehension/expected/model-solution000001.solution b/tests/exhaustive/basic/perms/05_equality/unnamed/0006_in_comprehension/expected/model-solution000001.solution new file mode 100644 index 0000000000..4f221ab058 --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/unnamed/0006_in_comprehension/expected/model-solution000001.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_1, n_2), (n_3, n_4)) +letting q be permutation((n_1, n_3), (n_2, n_4)) diff --git a/tests/exhaustive/basic/perms/05_equality/unnamed/0006_in_comprehension/expected/model-solution000002.solution b/tests/exhaustive/basic/perms/05_equality/unnamed/0006_in_comprehension/expected/model-solution000002.solution new file mode 100644 index 0000000000..17a965d7da --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/unnamed/0006_in_comprehension/expected/model-solution000002.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_1, n_2), (n_3, n_4)) +letting q be permutation((n_1, n_3, n_2, n_4)) diff --git a/tests/exhaustive/basic/perms/05_equality/unnamed/0006_in_comprehension/expected/model-solution000003.solution b/tests/exhaustive/basic/perms/05_equality/unnamed/0006_in_comprehension/expected/model-solution000003.solution new file mode 100644 index 0000000000..eb56a0f786 --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/unnamed/0006_in_comprehension/expected/model-solution000003.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_1, n_2), (n_3, n_4)) +letting q be permutation((n_1, n_4, n_2, n_3)) diff --git a/tests/exhaustive/basic/perms/05_equality/unnamed/0006_in_comprehension/expected/model-solution000004.solution b/tests/exhaustive/basic/perms/05_equality/unnamed/0006_in_comprehension/expected/model-solution000004.solution new file mode 100644 index 0000000000..9078481170 --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/unnamed/0006_in_comprehension/expected/model-solution000004.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_1, n_2), (n_3, n_4)) +letting q be permutation((n_1, n_4), (n_2, n_3)) diff --git a/tests/exhaustive/basic/perms/05_equality/unnamed/0006_in_comprehension/expected/model-solution000005.solution b/tests/exhaustive/basic/perms/05_equality/unnamed/0006_in_comprehension/expected/model-solution000005.solution new file mode 100644 index 0000000000..c2007d2732 --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/unnamed/0006_in_comprehension/expected/model-solution000005.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_1, n_2, n_3, n_4)) +letting q be permutation((n_1, n_3), (n_2, n_4)) diff --git a/tests/exhaustive/basic/perms/05_equality/unnamed/0006_in_comprehension/expected/model-solution000006.solution b/tests/exhaustive/basic/perms/05_equality/unnamed/0006_in_comprehension/expected/model-solution000006.solution new file mode 100644 index 0000000000..6fa827da68 --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/unnamed/0006_in_comprehension/expected/model-solution000006.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_1, n_2, n_3, n_4)) +letting q be permutation((n_1, n_4, n_3, n_2)) diff --git a/tests/exhaustive/basic/perms/05_equality/unnamed/0006_in_comprehension/expected/model-solution000007.solution b/tests/exhaustive/basic/perms/05_equality/unnamed/0006_in_comprehension/expected/model-solution000007.solution new file mode 100644 index 0000000000..1afc839f29 --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/unnamed/0006_in_comprehension/expected/model-solution000007.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_1, n_2, n_4, n_3)) +letting q be permutation((n_1, n_3, n_4, n_2)) diff --git a/tests/exhaustive/basic/perms/05_equality/unnamed/0006_in_comprehension/expected/model-solution000008.solution b/tests/exhaustive/basic/perms/05_equality/unnamed/0006_in_comprehension/expected/model-solution000008.solution new file mode 100644 index 0000000000..8c52e9f10e --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/unnamed/0006_in_comprehension/expected/model-solution000008.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_1, n_2, n_4, n_3)) +letting q be permutation((n_1, n_4), (n_2, n_3)) diff --git a/tests/exhaustive/basic/perms/05_equality/unnamed/0006_in_comprehension/expected/model-solution000009.solution b/tests/exhaustive/basic/perms/05_equality/unnamed/0006_in_comprehension/expected/model-solution000009.solution new file mode 100644 index 0000000000..131d19233a --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/unnamed/0006_in_comprehension/expected/model-solution000009.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_1, n_3, n_4, n_2)) +letting q be permutation((n_1, n_2, n_4, n_3)) diff --git a/tests/exhaustive/basic/perms/05_equality/unnamed/0006_in_comprehension/expected/model-solution000010.solution b/tests/exhaustive/basic/perms/05_equality/unnamed/0006_in_comprehension/expected/model-solution000010.solution new file mode 100644 index 0000000000..64181c450f --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/unnamed/0006_in_comprehension/expected/model-solution000010.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_1, n_3, n_4, n_2)) +letting q be permutation((n_1, n_4), (n_2, n_3)) diff --git a/tests/exhaustive/basic/perms/05_equality/unnamed/0006_in_comprehension/expected/model-solution000011.solution b/tests/exhaustive/basic/perms/05_equality/unnamed/0006_in_comprehension/expected/model-solution000011.solution new file mode 100644 index 0000000000..a47d34a5e0 --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/unnamed/0006_in_comprehension/expected/model-solution000011.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_1, n_3), (n_2, n_4)) +letting q be permutation((n_1, n_2), (n_3, n_4)) diff --git a/tests/exhaustive/basic/perms/05_equality/unnamed/0006_in_comprehension/expected/model-solution000012.solution b/tests/exhaustive/basic/perms/05_equality/unnamed/0006_in_comprehension/expected/model-solution000012.solution new file mode 100644 index 0000000000..cf8b9fdf83 --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/unnamed/0006_in_comprehension/expected/model-solution000012.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_1, n_3), (n_2, n_4)) +letting q be permutation((n_1, n_2, n_3, n_4)) diff --git a/tests/exhaustive/basic/perms/05_equality/unnamed/0006_in_comprehension/expected/model-solution000013.solution b/tests/exhaustive/basic/perms/05_equality/unnamed/0006_in_comprehension/expected/model-solution000013.solution new file mode 100644 index 0000000000..3a375b57f1 --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/unnamed/0006_in_comprehension/expected/model-solution000013.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_1, n_3), (n_2, n_4)) +letting q be permutation((n_1, n_4, n_3, n_2)) diff --git a/tests/exhaustive/basic/perms/05_equality/unnamed/0006_in_comprehension/expected/model-solution000014.solution b/tests/exhaustive/basic/perms/05_equality/unnamed/0006_in_comprehension/expected/model-solution000014.solution new file mode 100644 index 0000000000..9b7b5e71f2 --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/unnamed/0006_in_comprehension/expected/model-solution000014.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_1, n_3), (n_2, n_4)) +letting q be permutation((n_1, n_4), (n_2, n_3)) diff --git a/tests/exhaustive/basic/perms/05_equality/unnamed/0006_in_comprehension/expected/model-solution000015.solution b/tests/exhaustive/basic/perms/05_equality/unnamed/0006_in_comprehension/expected/model-solution000015.solution new file mode 100644 index 0000000000..45d81fc999 --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/unnamed/0006_in_comprehension/expected/model-solution000015.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_1, n_3, n_2, n_4)) +letting q be permutation((n_1, n_2), (n_3, n_4)) diff --git a/tests/exhaustive/basic/perms/05_equality/unnamed/0006_in_comprehension/expected/model-solution000016.solution b/tests/exhaustive/basic/perms/05_equality/unnamed/0006_in_comprehension/expected/model-solution000016.solution new file mode 100644 index 0000000000..24e8b3bd75 --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/unnamed/0006_in_comprehension/expected/model-solution000016.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_1, n_3, n_2, n_4)) +letting q be permutation((n_1, n_4, n_2, n_3)) diff --git a/tests/exhaustive/basic/perms/05_equality/unnamed/0006_in_comprehension/expected/model-solution000017.solution b/tests/exhaustive/basic/perms/05_equality/unnamed/0006_in_comprehension/expected/model-solution000017.solution new file mode 100644 index 0000000000..27ca51efdc --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/unnamed/0006_in_comprehension/expected/model-solution000017.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_1, n_4, n_3, n_2)) +letting q be permutation((n_1, n_2, n_3, n_4)) diff --git a/tests/exhaustive/basic/perms/05_equality/unnamed/0006_in_comprehension/expected/model-solution000018.solution b/tests/exhaustive/basic/perms/05_equality/unnamed/0006_in_comprehension/expected/model-solution000018.solution new file mode 100644 index 0000000000..27be03ea64 --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/unnamed/0006_in_comprehension/expected/model-solution000018.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_1, n_4, n_3, n_2)) +letting q be permutation((n_1, n_3), (n_2, n_4)) diff --git a/tests/exhaustive/basic/perms/05_equality/unnamed/0006_in_comprehension/expected/model-solution000019.solution b/tests/exhaustive/basic/perms/05_equality/unnamed/0006_in_comprehension/expected/model-solution000019.solution new file mode 100644 index 0000000000..c9b9015cc5 --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/unnamed/0006_in_comprehension/expected/model-solution000019.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_1, n_4, n_2, n_3)) +letting q be permutation((n_1, n_2), (n_3, n_4)) diff --git a/tests/exhaustive/basic/perms/05_equality/unnamed/0006_in_comprehension/expected/model-solution000020.solution b/tests/exhaustive/basic/perms/05_equality/unnamed/0006_in_comprehension/expected/model-solution000020.solution new file mode 100644 index 0000000000..9ef69e4cb6 --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/unnamed/0006_in_comprehension/expected/model-solution000020.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_1, n_4, n_2, n_3)) +letting q be permutation((n_1, n_3, n_2, n_4)) diff --git a/tests/exhaustive/basic/perms/05_equality/unnamed/0006_in_comprehension/expected/model-solution000021.solution b/tests/exhaustive/basic/perms/05_equality/unnamed/0006_in_comprehension/expected/model-solution000021.solution new file mode 100644 index 0000000000..e38e0489fb --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/unnamed/0006_in_comprehension/expected/model-solution000021.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_1, n_4), (n_2, n_3)) +letting q be permutation((n_1, n_2), (n_3, n_4)) diff --git a/tests/exhaustive/basic/perms/05_equality/unnamed/0006_in_comprehension/expected/model-solution000022.solution b/tests/exhaustive/basic/perms/05_equality/unnamed/0006_in_comprehension/expected/model-solution000022.solution new file mode 100644 index 0000000000..80609b3ec2 --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/unnamed/0006_in_comprehension/expected/model-solution000022.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_1, n_4), (n_2, n_3)) +letting q be permutation((n_1, n_2, n_4, n_3)) diff --git a/tests/exhaustive/basic/perms/05_equality/unnamed/0006_in_comprehension/expected/model-solution000023.solution b/tests/exhaustive/basic/perms/05_equality/unnamed/0006_in_comprehension/expected/model-solution000023.solution new file mode 100644 index 0000000000..8e11f52571 --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/unnamed/0006_in_comprehension/expected/model-solution000023.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_1, n_4), (n_2, n_3)) +letting q be permutation((n_1, n_3, n_4, n_2)) diff --git a/tests/exhaustive/basic/perms/05_equality/unnamed/0006_in_comprehension/expected/model-solution000024.solution b/tests/exhaustive/basic/perms/05_equality/unnamed/0006_in_comprehension/expected/model-solution000024.solution new file mode 100644 index 0000000000..f3299b2087 --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/unnamed/0006_in_comprehension/expected/model-solution000024.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting p be permutation((n_1, n_4), (n_2, n_3)) +letting q be permutation((n_1, n_3), (n_2, n_4)) diff --git a/tests/exhaustive/basic/perms/05_equality/unnamed/0006_in_comprehension/expected/model.eprime b/tests/exhaustive/basic/perms/05_equality/unnamed/0006_in_comprehension/expected/model.eprime new file mode 100644 index 0000000000..b06a4e1b4e --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/unnamed/0006_in_comprehension/expected/model.eprime @@ -0,0 +1,21 @@ +language ESSENCE' 1.0 + +find p_PermutationAsFunction_PermutationFunction_Function1D: matrix indexed by [int(1..4)] of int(1..4) +find q_PermutationAsFunction_PermutationFunction_Function1D: matrix indexed by [int(1..4)] of int(1..4) +branching on + [p_PermutationAsFunction_PermutationFunction_Function1D, q_PermutationAsFunction_PermutationFunction_Function1D] +such that + and([q20 != q_PermutationAsFunction_PermutationFunction_Function1D[q20] /\ + q14 != p_PermutationAsFunction_PermutationFunction_Function1D[q14] + -> + !(q14 = q20 /\ + p_PermutationAsFunction_PermutationFunction_Function1D[q14] = + q_PermutationAsFunction_PermutationFunction_Function1D[q20]) + | q14 : int(1..4), q20 : int(1..4)]), + allDiff(p_PermutationAsFunction_PermutationFunction_Function1D), + and([or([p_PermutationAsFunction_PermutationFunction_Function1D[q3] = q2 | q3 : int(1..4)]) | q2 : int(1..4)]), + 4 = sum([toInt(q1 != p_PermutationAsFunction_PermutationFunction_Function1D[q1]) | q1 : int(1..4)]), + allDiff(q_PermutationAsFunction_PermutationFunction_Function1D), + and([or([q_PermutationAsFunction_PermutationFunction_Function1D[q7] = q6 | q7 : int(1..4)]) | q6 : int(1..4)]), + 4 = sum([toInt(q5 != q_PermutationAsFunction_PermutationFunction_Function1D[q5]) | q5 : int(1..4)]) + diff --git a/tests/exhaustive/basic/perms/05_equality/unnamed/0006_in_comprehension/permutation.essence b/tests/exhaustive/basic/perms/05_equality/unnamed/0006_in_comprehension/permutation.essence new file mode 100644 index 0000000000..1788ddf5fc --- /dev/null +++ b/tests/exhaustive/basic/perms/05_equality/unnamed/0006_in_comprehension/permutation.essence @@ -0,0 +1,7 @@ +letting n be new type of size 4 +find p : permutation (size 4) of n +find q : permutation (size 4) of n + +such that + and([pt != qt | pt <- p, qt <- q]) + From 20d3c9e2ec6c080b52b83821f8240d3e65016ed6 Mon Sep 17 00:00:00 2001 From: Chris Jefferson Date: Tue, 11 Aug 2020 15:36:51 +0100 Subject: [PATCH 121/229] Add broken inverse test --- .../06_inverse/int/0005_find_eq_find/permutation.essence | 4 ++++ 1 file changed, 4 insertions(+) create mode 100644 tests/exhaustive/basic/perms/06_inverse/int/0005_find_eq_find/permutation.essence diff --git a/tests/exhaustive/basic/perms/06_inverse/int/0005_find_eq_find/permutation.essence b/tests/exhaustive/basic/perms/06_inverse/int/0005_find_eq_find/permutation.essence new file mode 100644 index 0000000000..31fede5d60 --- /dev/null +++ b/tests/exhaustive/basic/perms/06_inverse/int/0005_find_eq_find/permutation.essence @@ -0,0 +1,4 @@ +find p : permutation of int(1..4) +find q : permutation of int(1..4) + +such that inverse(p,q) From 2e998c4f205a0b722b47b007f858fe98b31a60c6 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?=C3=96zg=C3=BCr=20Akg=C3=BCn?= Date: Mon, 26 Feb 2024 12:20:18 +0000 Subject: [PATCH 122/229] ghc 9.0 deps --- etc/hs-deps/stack-9.0.yaml | 3 --- 1 file changed, 3 deletions(-) diff --git a/etc/hs-deps/stack-9.0.yaml b/etc/hs-deps/stack-9.0.yaml index 45c00e7989..9af60f939b 100644 --- a/etc/hs-deps/stack-9.0.yaml +++ b/etc/hs-deps/stack-9.0.yaml @@ -4,7 +4,4 @@ packages: system-ghc: true install-ghc: true extra-deps: -- megaparsec-4.4.0 -- tasty-1.1.0.1 -- tasty-ant-xml-1.1.4 - megaparsec-9.3.0 From 8472eea38bdb00b36fac2c08dd2a7156e177306c Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?=C3=96zg=C3=BCr=20Akg=C3=BCn?= Date: Mon, 26 Feb 2024 12:41:00 +0000 Subject: [PATCH 123/229] post-merge-test-update 1 (there is more to come) --- docs/conjure-help.html | 6 - docs/conjure-help.txt | 6 - src/Conjure/Compute/DomainOf.hs.orig | 668 ---- src/Conjure/Language/Constant.hs.orig | 535 --- src/Conjure/Language/Domain.hs.orig | 1079 ------ .../Language/Expression/Op/Defined.hs.orig | 55 - .../Language/Expression/Op/Image.hs.orig | 106 - .../Language/Expression/Op/Inverse.hs.orig | 67 - .../Language/Expression/Op/Product.hs.orig | 92 - .../Language/Expression/Op/ToSet.hs.orig | 72 - .../Language/Expression/Op/TwoBars.hs.orig | 73 - src/Conjure/Language/Instantiate.hs.orig | 436 --- src/Conjure/Language/Lexer.hs.orig | 623 ---- src/Conjure/Language/NameResolution.hs.orig | 340 -- src/Conjure/Representations.hs.orig | 234 -- .../Function/Function1D.hs.orig | 199 -- .../Function/Function1DPartial.hs.orig | 229 -- .../Function/FunctionND.hs.orig | 283 -- .../Representations/MSet/Occurrence.hs.orig | 122 - .../Partition/Occurrence.hs.orig | 329 -- src/Conjure/Representations/Record.hs.orig | 90 - .../Representations/Set/Explicit.hs.orig | 117 - .../Set/ExplicitVarSizeWithDummy.hs.orig | 178 - src/Conjure/Representations/Tuple.hs.orig | 90 - src/Conjure/Representations/Variant.hs.orig | 128 - src/Conjure/UI/Model.hs.orig | 2916 ----------------- .../function-literal-suggestion/run.sh.orig | 8 - .../stdout.expected.orig | 10 - .../custom/issues/119/1/stdout.expected.orig | 56 - .../custom/issues/119/2/stdout.expected.orig | 44 - .../custom/issues/370/01/stdout.expected.orig | 36 - .../custom/issues/370/03/stdout.expected.orig | 19 - .../custom/issues/388/2/stdout.expected.orig | 157 - .../model_1_1-solution000001.solution | 3 + .../model_1_1-solution000002.solution | 6 + .../model_1_1-solution000003.solution | 6 + .../model_1_1-solution000004.solution | 6 + .../model_1_1-solution000005.solution | 7 + .../model_1_1-solution000006.solution | 7 + .../model_1_1-solution000007.solution | 7 + .../model_1_1-solution000008.solution | 7 + .../model_1_1-solution000009.solution | 7 + .../model_1_1-solution000010.solution | 7 + .../model_1_1-solution000011.solution | 8 + .../model_1_1-solution000012.solution | 8 + .../model_1_1-solution000013.solution | 8 + .../model_1_1-solution000014.solution | 8 + .../model_1_1-solution000015.solution | 9 + .../gen02/expected/model_1_1.eprime.orig | 43 - .../model_1_2-solution000001.solution | 3 + .../model_1_2-solution000002.solution | 6 + .../model_1_2-solution000003.solution | 6 + .../model_1_2-solution000004.solution | 6 + .../model_1_2-solution000005.solution | 7 + .../model_1_2-solution000006.solution | 7 + .../model_1_2-solution000007.solution | 7 + .../model_1_2-solution000008.solution | 7 + .../model_1_2-solution000009.solution | 7 + .../model_1_2-solution000010.solution | 7 + .../model_1_2-solution000011.solution | 8 + .../model_1_2-solution000012.solution | 8 + .../model_1_2-solution000013.solution | 8 + .../model_1_2-solution000014.solution | 8 + .../model_1_2-solution000015.solution | 9 + .../gen02/expected/model_1_2.eprime.orig | 122 - .../model_1_3-solution000001.solution | 3 + .../model_1_3-solution000002.solution | 6 + .../model_1_3-solution000003.solution | 6 + .../model_1_3-solution000004.solution | 6 + .../model_1_3-solution000005.solution | 7 + .../model_1_3-solution000006.solution | 7 + .../model_1_3-solution000007.solution | 7 + .../model_1_3-solution000008.solution | 7 + .../model_1_3-solution000009.solution | 7 + .../model_1_3-solution000010.solution | 7 + .../model_1_3-solution000011.solution | 8 + .../model_1_3-solution000012.solution | 8 + .../model_1_3-solution000013.solution | 8 + .../model_1_3-solution000014.solution | 8 + .../model_1_3-solution000015.solution | 9 + .../gen02/expected/model_1_3.eprime.orig | 97 - .../model_1_4-solution000001.solution | 3 + .../model_1_4-solution000002.solution | 6 + .../model_1_4-solution000003.solution | 6 + .../model_1_4-solution000004.solution | 6 + .../model_1_4-solution000005.solution | 7 + .../model_1_4-solution000006.solution | 7 + .../model_1_4-solution000007.solution | 7 + .../model_1_4-solution000008.solution | 7 + .../model_1_4-solution000009.solution | 7 + .../model_1_4-solution000010.solution | 7 + .../model_1_4-solution000011.solution | 8 + .../model_1_4-solution000012.solution | 8 + .../model_1_4-solution000013.solution | 8 + .../model_1_4-solution000014.solution | 8 + .../model_1_4-solution000015.solution | 9 + .../gen02/expected/model_1_4.eprime.orig | 123 - .../model_2_1-solution000001.solution | 3 + .../model_2_1-solution000002.solution | 6 + .../model_2_1-solution000003.solution | 6 + .../model_2_1-solution000004.solution | 6 + .../model_2_1-solution000005.solution | 7 + .../model_2_1-solution000006.solution | 7 + .../model_2_1-solution000007.solution | 7 + .../model_2_1-solution000008.solution | 7 + .../model_2_1-solution000009.solution | 7 + .../model_2_1-solution000010.solution | 7 + .../model_2_1-solution000011.solution | 8 + .../model_2_1-solution000012.solution | 8 + .../model_2_1-solution000013.solution | 8 + .../model_2_1-solution000014.solution | 8 + .../model_2_1-solution000015.solution | 9 + .../gen02/expected/model_2_1.eprime.orig | 120 - .../model_2_2-solution000001.solution | 3 + .../model_2_2-solution000002.solution | 6 + .../model_2_2-solution000003.solution | 6 + .../model_2_2-solution000004.solution | 6 + .../model_2_2-solution000005.solution | 7 + .../model_2_2-solution000006.solution | 7 + .../model_2_2-solution000007.solution | 7 + .../model_2_2-solution000008.solution | 7 + .../model_2_2-solution000009.solution | 7 + .../model_2_2-solution000010.solution | 7 + .../model_2_2-solution000011.solution | 8 + .../model_2_2-solution000012.solution | 8 + .../model_2_2-solution000013.solution | 8 + .../model_2_2-solution000014.solution | 8 + .../model_2_2-solution000015.solution | 9 + .../autogen/gen02/expected/model_2_2.eprime | 53 + .../model_2_3-solution000001.solution | 3 + .../model_2_3-solution000002.solution | 6 + .../model_2_3-solution000003.solution | 6 + .../model_2_3-solution000004.solution | 6 + .../model_2_3-solution000005.solution | 7 + .../model_2_3-solution000006.solution | 7 + .../model_2_3-solution000007.solution | 7 + .../model_2_3-solution000008.solution | 7 + .../model_2_3-solution000009.solution | 7 + .../model_2_3-solution000010.solution | 7 + .../model_2_3-solution000011.solution | 8 + .../model_2_3-solution000012.solution | 8 + .../model_2_3-solution000013.solution | 8 + .../model_2_3-solution000014.solution | 8 + .../model_2_3-solution000015.solution | 9 + .../gen02/expected/model_2_3.eprime.orig | 121 - .../model_2_4-solution000001.solution | 3 + .../model_2_4-solution000002.solution | 6 + .../model_2_4-solution000003.solution | 6 + .../model_2_4-solution000004.solution | 6 + .../model_2_4-solution000005.solution | 7 + .../model_2_4-solution000006.solution | 7 + .../model_2_4-solution000007.solution | 7 + .../model_2_4-solution000008.solution | 7 + .../model_2_4-solution000009.solution | 7 + .../model_2_4-solution000010.solution | 7 + .../model_2_4-solution000011.solution | 8 + .../model_2_4-solution000012.solution | 8 + .../model_2_4-solution000013.solution | 8 + .../model_2_4-solution000014.solution | 8 + .../model_2_4-solution000015.solution | 9 + .../autogen/gen02/expected/model_2_4.eprime | 121 + .../model_3_1-solution000001.solution | 3 + .../model_3_1-solution000002.solution | 6 + .../model_3_1-solution000003.solution | 6 + .../model_3_1-solution000004.solution | 6 + .../model_3_1-solution000005.solution | 7 + .../model_3_1-solution000006.solution | 7 + .../model_3_1-solution000007.solution | 7 + .../model_3_1-solution000008.solution | 7 + .../model_3_1-solution000009.solution | 7 + .../model_3_1-solution000010.solution | 7 + .../model_3_1-solution000011.solution | 8 + .../model_3_1-solution000012.solution | 8 + .../model_3_1-solution000013.solution | 8 + .../model_3_1-solution000014.solution | 8 + .../model_3_1-solution000015.solution | 9 + .../gen02/expected/model_3_1.eprime.orig | 96 - .../model_3_2-solution000001.solution | 3 + .../model_3_2-solution000002.solution | 6 + .../model_3_2-solution000003.solution | 6 + .../model_3_2-solution000004.solution | 6 + .../model_3_2-solution000005.solution | 7 + .../model_3_2-solution000006.solution | 7 + .../model_3_2-solution000007.solution | 7 + .../model_3_2-solution000008.solution | 7 + .../model_3_2-solution000009.solution | 7 + .../model_3_2-solution000010.solution | 7 + .../model_3_2-solution000011.solution | 8 + .../model_3_2-solution000012.solution | 8 + .../model_3_2-solution000013.solution | 8 + .../model_3_2-solution000014.solution | 8 + .../model_3_2-solution000015.solution | 9 + .../gen02/expected/model_3_2.eprime.orig | 122 - .../model_3_3-solution000001.solution | 3 + .../model_3_3-solution000002.solution | 6 + .../model_3_3-solution000003.solution | 6 + .../model_3_3-solution000004.solution | 6 + .../model_3_3-solution000005.solution | 7 + .../model_3_3-solution000006.solution | 7 + .../model_3_3-solution000007.solution | 7 + .../model_3_3-solution000008.solution | 7 + .../model_3_3-solution000009.solution | 7 + .../model_3_3-solution000010.solution | 7 + .../model_3_3-solution000011.solution | 8 + .../model_3_3-solution000012.solution | 8 + .../model_3_3-solution000013.solution | 8 + .../model_3_3-solution000014.solution | 8 + .../model_3_3-solution000015.solution | 9 + .../gen02/expected/model_3_3.eprime.orig | 43 - .../model_3_4-solution000001.solution | 3 + .../model_3_4-solution000002.solution | 6 + .../model_3_4-solution000003.solution | 6 + .../model_3_4-solution000004.solution | 6 + .../model_3_4-solution000005.solution | 7 + .../model_3_4-solution000006.solution | 7 + .../model_3_4-solution000007.solution | 7 + .../model_3_4-solution000008.solution | 7 + .../model_3_4-solution000009.solution | 7 + .../model_3_4-solution000010.solution | 7 + .../model_3_4-solution000011.solution | 8 + .../model_3_4-solution000012.solution | 8 + .../model_3_4-solution000013.solution | 8 + .../model_3_4-solution000014.solution | 8 + .../model_3_4-solution000015.solution | 9 + .../gen02/expected/model_3_4.eprime.orig | 123 - .../model_4_1-solution000001.solution | 3 + .../model_4_1-solution000002.solution | 6 + .../model_4_1-solution000003.solution | 6 + .../model_4_1-solution000004.solution | 6 + .../model_4_1-solution000005.solution | 7 + .../model_4_1-solution000006.solution | 7 + .../model_4_1-solution000007.solution | 7 + .../model_4_1-solution000008.solution | 7 + .../model_4_1-solution000009.solution | 7 + .../model_4_1-solution000010.solution | 7 + .../model_4_1-solution000011.solution | 8 + .../model_4_1-solution000012.solution | 8 + .../model_4_1-solution000013.solution | 8 + .../model_4_1-solution000014.solution | 8 + .../model_4_1-solution000015.solution | 9 + .../gen02/expected/model_4_1.eprime.orig | 119 - .../model_4_2-solution000001.solution | 3 + .../model_4_2-solution000002.solution | 6 + .../model_4_2-solution000003.solution | 6 + .../model_4_2-solution000004.solution | 6 + .../model_4_2-solution000005.solution | 7 + .../model_4_2-solution000006.solution | 7 + .../model_4_2-solution000007.solution | 7 + .../model_4_2-solution000008.solution | 7 + .../model_4_2-solution000009.solution | 7 + .../model_4_2-solution000010.solution | 7 + .../model_4_2-solution000011.solution | 8 + .../model_4_2-solution000012.solution | 8 + .../model_4_2-solution000013.solution | 8 + .../model_4_2-solution000014.solution | 8 + .../model_4_2-solution000015.solution | 9 + .../autogen/gen02/expected/model_4_2.eprime | 119 + .../model_4_3-solution000001.solution | 3 + .../model_4_3-solution000002.solution | 6 + .../model_4_3-solution000003.solution | 6 + .../model_4_3-solution000004.solution | 6 + .../model_4_3-solution000005.solution | 7 + .../model_4_3-solution000006.solution | 7 + .../model_4_3-solution000007.solution | 7 + .../model_4_3-solution000008.solution | 7 + .../model_4_3-solution000009.solution | 7 + .../model_4_3-solution000010.solution | 7 + .../model_4_3-solution000011.solution | 8 + .../model_4_3-solution000012.solution | 8 + .../model_4_3-solution000013.solution | 8 + .../model_4_3-solution000014.solution | 8 + .../model_4_3-solution000015.solution | 9 + .../gen02/expected/model_4_3.eprime.orig | 120 - .../model_4_4-solution000001.solution | 3 + .../model_4_4-solution000002.solution | 6 + .../model_4_4-solution000003.solution | 6 + .../model_4_4-solution000004.solution | 6 + .../model_4_4-solution000005.solution | 7 + .../model_4_4-solution000006.solution | 7 + .../model_4_4-solution000007.solution | 7 + .../model_4_4-solution000008.solution | 7 + .../model_4_4-solution000009.solution | 7 + .../model_4_4-solution000010.solution | 7 + .../model_4_4-solution000011.solution | 8 + .../model_4_4-solution000012.solution | 8 + .../model_4_4-solution000013.solution | 8 + .../model_4_4-solution000014.solution | 8 + .../model_4_4-solution000015.solution | 9 + .../autogen/gen02/expected/model_4_4.eprime | 52 + .../expected/model_1-solution000001.solution | 6 + .../expected/model_1-solution000002.solution | 7 + .../gen14_1/expected/model_1.eprime.orig | 104 - .../expected/model_2-solution000001.solution | 6 + .../expected/model_2-solution000002.solution | 7 + .../gen14_1/expected/model_2.eprime.orig | 174 - .../expected/model_3-solution000001.solution | 6 + .../expected/model_3-solution000002.solution | 7 + .../gen14_1/expected/model_3.eprime.orig | 220 -- .../expected/model_4-solution000001.solution | 6 + .../expected/model_4-solution000002.solution | 7 + .../gen14_1/expected/model_4.eprime.orig | 97 - .../expected/model_1-solution000001.solution | 6 + .../expected/model_1-solution000002.solution | 7 + .../autogen/gen14_2/expected/model_1.eprime | 38 + .../expected/model_2-solution000001.solution | 6 + .../expected/model_2-solution000002.solution | 7 + .../autogen/gen14_2/expected/model_2.eprime | 58 + .../expected/model_3-solution000001.solution | 6 + .../expected/model_3-solution000002.solution | 7 + .../gen14_2/expected/model_3.eprime.orig | 67 - .../expected/model_4-solution000001.solution | 6 + .../expected/model_4-solution000002.solution | 7 + .../autogen/gen14_2/expected/model_4.eprime | 34 + .../autogen/gen17/expected/model_1.eprime | 3 +- .../autogen/gen17/expected/model_2.eprime | 3 +- .../autogen/gen25/expected/model_1.eprime | 3 +- .../autogen/gen25/expected/model_2.eprime | 3 +- .../autogen/gen32/expected/model_1_1_1.eprime | 9 + .../autogen/gen32/expected/model_1_1_2.eprime | 19 + .../autogen/gen32/expected/model_1_1_3.eprime | 22 + .../autogen/gen32/expected/model_1_1_4.eprime | 23 + .../autogen/gen32/expected/model_1_2_1.eprime | 23 + .../autogen/gen32/expected/model_1_2_3.eprime | 48 + .../autogen/gen32/expected/model_1_2_4.eprime | 49 + .../autogen/gen32/expected/model_1_3_1.eprime | 27 + .../autogen/gen32/expected/model_1_3_2.eprime | 49 + .../autogen/gen32/expected/model_1_3_4.eprime | 53 + .../autogen/gen32/expected/model_1_4_1.eprime | 28 + .../autogen/gen32/expected/model_1_4_2.eprime | 50 + .../autogen/gen32/expected/model_1_4_3.eprime | 53 + .../autogen/gen32/expected/model_2_1_1.eprime | 23 + .../autogen/gen32/expected/model_2_1_3.eprime | 48 + .../autogen/gen32/expected/model_2_1_4.eprime | 49 + .../autogen/gen32/expected/model_2_2_1.eprime | 28 + .../autogen/gen32/expected/model_2_2_2.eprime | 22 + .../autogen/gen32/expected/model_2_2_3.eprime | 40 + .../autogen/gen32/expected/model_2_2_4.eprime | 40 + .../autogen/gen32/expected/model_2_3_1.eprime | 53 + .../autogen/gen32/expected/model_2_3_2.eprime | 40 + .../autogen/gen32/expected/model_2_3_4.eprime | 69 + .../autogen/gen32/expected/model_2_4_1.eprime | 54 + .../autogen/gen32/expected/model_2_4_2.eprime | 40 + .../autogen/gen32/expected/model_2_4_3.eprime | 69 + .../autogen/gen32/expected/model_3_1_1.eprime | 27 + .../autogen/gen32/expected/model_3_1_2.eprime | 49 + .../autogen/gen32/expected/model_3_1_4.eprime | 53 + .../autogen/gen32/expected/model_3_2_1.eprime | 53 + .../autogen/gen32/expected/model_3_2_2.eprime | 40 + .../autogen/gen32/expected/model_3_2_4.eprime | 69 + .../autogen/gen32/expected/model_3_3_1.eprime | 31 + .../autogen/gen32/expected/model_3_3_2.eprime | 40 + .../autogen/gen32/expected/model_3_3_3.eprime | 24 + .../autogen/gen32/expected/model_3_3_4.eprime | 44 + .../autogen/gen32/expected/model_3_4_1.eprime | 57 + .../autogen/gen32/expected/model_3_4_2.eprime | 69 + .../autogen/gen32/expected/model_3_4_3.eprime | 44 + .../autogen/gen32/expected/model_4_1_1.eprime | 28 + .../autogen/gen32/expected/model_4_1_2.eprime | 50 + .../autogen/gen32/expected/model_4_1_3.eprime | 53 + .../autogen/gen32/expected/model_4_2_1.eprime | 54 + .../autogen/gen32/expected/model_4_2_2.eprime | 40 + .../autogen/gen32/expected/model_4_2_3.eprime | 69 + .../autogen/gen32/expected/model_4_3_1.eprime | 57 + .../autogen/gen32/expected/model_4_3_2.eprime | 69 + .../autogen/gen32/expected/model_4_3_3.eprime | 44 + .../autogen/gen32/expected/model_4_4_1.eprime | 32 + .../autogen/gen32/expected/model_4_4_2.eprime | 40 + .../autogen/gen32/expected/model_4_4_3.eprime | 44 + .../autogen/gen32/expected/model_4_4_4.eprime | 25 + .../autogen/gen35/expected/model_1.eprime | 24 - .../gen35/expected/model_1.eprime.orig | 57 - .../expected/model_1-solution000001.solution | 3 + .../expected/model_2-solution000001.solution | 3 + .../expected/model_3-solution000001.solution | 3 + .../gen36/expected/model_3.eprime.orig | 94 - .../expected/model_4-solution000001.solution | 3 + .../expected/model_5-solution000001.solution | 3 + .../expected/model_6-solution000001.solution | 3 + .../gen36/expected/model_6.eprime.orig | 95 - .../autogen/gen37/expected/model_1.eprime | 12 +- .../autogen/gen37/expected/model_2.eprime | 4 +- .../autogen/gen37/expected/model_3.eprime | 14 +- .../autogen/gen37/expected/model_4.eprime | 4 +- .../comprehension_01_2/expected/model.eprime | 3 +- .../comprehension_02_2/expected/model.eprime | 3 +- .../comprehension_03_2/expected/model.eprime | 3 +- .../expected/model-solution000001.solution | 5 + .../expected/model-solution000002.solution | 5 + .../expected/model-solution000003.solution | 5 + .../expected/model-solution000004.solution | 5 + .../comprehension_04_2/expected/model.eprime | 26 + .../model_1_1_1-solution000001.solution | 4 + .../model_1_1_1-solution000002.solution | 4 + .../model_1_1_1-solution000003.solution | 4 + .../model_1_1_1-solution000004.solution | 4 + .../model_1_1_1-solution000005.solution | 4 + .../model_1_1_1-solution000006.solution | 4 + .../model_1_1_1-solution000007.solution | 4 + .../expected/model_1_1_1.eprime | 25 + .../model_1_1_2-solution000001.solution | 4 + .../model_1_1_2-solution000002.solution | 4 + .../model_1_1_2-solution000003.solution | 4 + .../model_1_1_2-solution000004.solution | 4 + .../model_1_1_2-solution000005.solution | 4 + .../model_1_1_2-solution000006.solution | 4 + .../model_1_1_2-solution000007.solution | 4 + .../expected/model_1_1_2.eprime | 33 + .../model_1_1_3-solution000001.solution | 4 + .../model_1_1_3-solution000002.solution | 4 + .../model_1_1_3-solution000003.solution | 4 + .../model_1_1_3-solution000004.solution | 4 + .../model_1_1_3-solution000005.solution | 4 + .../model_1_1_3-solution000006.solution | 4 + .../model_1_1_3-solution000007.solution | 4 + .../expected/model_1_1_3.eprime | 36 + .../model_1_1_4-solution000001.solution | 4 + .../model_1_1_4-solution000002.solution | 4 + .../model_1_1_4-solution000003.solution | 4 + .../model_1_1_4-solution000004.solution | 4 + .../model_1_1_4-solution000005.solution | 4 + .../model_1_1_4-solution000006.solution | 4 + .../model_1_1_4-solution000007.solution | 4 + .../expected/model_1_1_4.eprime | 36 + .../model_1_2_1-solution000001.solution | 4 + .../model_1_2_1-solution000002.solution | 4 + .../model_1_2_1-solution000003.solution | 4 + .../model_1_2_1-solution000004.solution | 4 + .../model_1_2_1-solution000005.solution | 4 + .../model_1_2_1-solution000006.solution | 4 + .../model_1_2_1-solution000007.solution | 4 + .../expected/model_1_2_1.eprime | 68 + .../model_1_2_3-solution000001.solution | 4 + .../model_1_2_3-solution000002.solution | 4 + .../model_1_2_3-solution000003.solution | 4 + .../model_1_2_3-solution000004.solution | 4 + .../model_1_2_3-solution000005.solution | 4 + .../model_1_2_3-solution000006.solution | 4 + .../model_1_2_3-solution000007.solution | 4 + .../expected/model_1_2_3.eprime | 92 + .../model_1_2_4-solution000001.solution | 4 + .../model_1_2_4-solution000002.solution | 4 + .../model_1_2_4-solution000003.solution | 4 + .../model_1_2_4-solution000004.solution | 4 + .../model_1_2_4-solution000005.solution | 4 + .../model_1_2_4-solution000006.solution | 4 + .../model_1_2_4-solution000007.solution | 4 + .../expected/model_1_2_4.eprime | 92 + .../model_1_3_1-solution000001.solution | 4 + .../model_1_3_1-solution000002.solution | 4 + .../model_1_3_1-solution000003.solution | 4 + .../model_1_3_1-solution000004.solution | 4 + .../model_1_3_1-solution000005.solution | 4 + .../model_1_3_1-solution000006.solution | 4 + .../model_1_3_1-solution000007.solution | 4 + .../expected/model_1_3_1.eprime | 74 + .../model_1_3_2-solution000001.solution | 4 + .../model_1_3_2-solution000002.solution | 4 + .../model_1_3_2-solution000003.solution | 4 + .../model_1_3_2-solution000004.solution | 4 + .../model_1_3_2-solution000005.solution | 4 + .../model_1_3_2-solution000006.solution | 4 + .../model_1_3_2-solution000007.solution | 4 + .../expected/model_1_3_2.eprime | 94 + .../model_1_3_4-solution000001.solution | 4 + .../model_1_3_4-solution000002.solution | 4 + .../model_1_3_4-solution000003.solution | 4 + .../model_1_3_4-solution000004.solution | 4 + .../model_1_3_4-solution000005.solution | 4 + .../model_1_3_4-solution000006.solution | 4 + .../model_1_3_4-solution000007.solution | 4 + .../expected/model_1_3_4.eprime | 99 + .../model_1_4_1-solution000001.solution | 4 + .../model_1_4_1-solution000002.solution | 4 + .../model_1_4_1-solution000003.solution | 4 + .../model_1_4_1-solution000004.solution | 4 + .../model_1_4_1-solution000005.solution | 4 + .../model_1_4_1-solution000006.solution | 4 + .../model_1_4_1-solution000007.solution | 4 + .../expected/model_1_4_1.eprime | 71 + .../model_1_4_2-solution000001.solution | 4 + .../model_1_4_2-solution000002.solution | 4 + .../model_1_4_2-solution000003.solution | 4 + .../model_1_4_2-solution000004.solution | 4 + .../model_1_4_2-solution000005.solution | 4 + .../model_1_4_2-solution000006.solution | 4 + .../model_1_4_2-solution000007.solution | 4 + .../expected/model_1_4_2.eprime | 90 + .../model_1_4_3-solution000001.solution | 4 + .../model_1_4_3-solution000002.solution | 4 + .../model_1_4_3-solution000003.solution | 4 + .../model_1_4_3-solution000004.solution | 4 + .../model_1_4_3-solution000005.solution | 4 + .../model_1_4_3-solution000006.solution | 4 + .../model_1_4_3-solution000007.solution | 4 + .../expected/model_1_4_3.eprime | 95 + .../model_2_1_1-solution000001.solution | 4 + .../model_2_1_1-solution000002.solution | 4 + .../model_2_1_1-solution000003.solution | 4 + .../model_2_1_1-solution000004.solution | 4 + .../model_2_1_1-solution000005.solution | 4 + .../model_2_1_1-solution000006.solution | 4 + .../model_2_1_1-solution000007.solution | 4 + .../expected/model_2_1_1.eprime | 68 + .../model_2_1_3-solution000001.solution | 4 + .../model_2_1_3-solution000002.solution | 4 + .../model_2_1_3-solution000003.solution | 4 + .../model_2_1_3-solution000004.solution | 4 + .../model_2_1_3-solution000005.solution | 4 + .../model_2_1_3-solution000006.solution | 4 + .../model_2_1_3-solution000007.solution | 4 + .../expected/model_2_1_3.eprime | 92 + .../model_2_1_4-solution000001.solution | 4 + .../model_2_1_4-solution000002.solution | 4 + .../model_2_1_4-solution000003.solution | 4 + .../model_2_1_4-solution000004.solution | 4 + .../model_2_1_4-solution000005.solution | 4 + .../model_2_1_4-solution000006.solution | 4 + .../model_2_1_4-solution000007.solution | 4 + .../expected/model_2_1_4.eprime | 91 + .../model_2_2_1-solution000001.solution | 4 + .../model_2_2_1-solution000002.solution | 4 + .../model_2_2_1-solution000003.solution | 4 + .../model_2_2_1-solution000004.solution | 4 + .../model_2_2_1-solution000005.solution | 4 + .../model_2_2_1-solution000006.solution | 4 + .../model_2_2_1-solution000007.solution | 4 + .../expected/model_2_2_1.eprime | 82 + .../model_2_2_2-solution000001.solution | 4 + .../model_2_2_2-solution000002.solution | 4 + .../model_2_2_2-solution000003.solution | 4 + .../model_2_2_2-solution000004.solution | 4 + .../model_2_2_2-solution000005.solution | 4 + .../model_2_2_2-solution000006.solution | 4 + .../model_2_2_2-solution000007.solution | 4 + .../expected/model_2_2_2.eprime | 77 + .../model_2_2_3-solution000001.solution | 4 + .../model_2_2_3-solution000002.solution | 4 + .../model_2_2_3-solution000003.solution | 4 + .../model_2_2_3-solution000004.solution | 4 + .../model_2_2_3-solution000005.solution | 4 + .../model_2_2_3-solution000006.solution | 4 + .../model_2_2_3-solution000007.solution | 4 + .../expected/model_2_2_3.eprime | 93 + .../model_2_2_4-solution000001.solution | 4 + .../model_2_2_4-solution000002.solution | 4 + .../model_2_2_4-solution000003.solution | 4 + .../model_2_2_4-solution000004.solution | 4 + .../model_2_2_4-solution000005.solution | 4 + .../model_2_2_4-solution000006.solution | 4 + .../model_2_2_4-solution000007.solution | 4 + .../expected/model_2_2_4.eprime | 94 + .../model_2_3_1-solution000001.solution | 4 + .../model_2_3_1-solution000002.solution | 4 + .../model_2_3_1-solution000003.solution | 4 + .../model_2_3_1-solution000004.solution | 4 + .../model_2_3_1-solution000005.solution | 4 + .../model_2_3_1-solution000006.solution | 4 + .../model_2_3_1-solution000007.solution | 4 + .../expected/model_2_3_1.eprime | 106 + .../model_2_3_2-solution000001.solution | 4 + .../model_2_3_2-solution000002.solution | 4 + .../model_2_3_2-solution000003.solution | 4 + .../model_2_3_2-solution000004.solution | 4 + .../model_2_3_2-solution000005.solution | 4 + .../model_2_3_2-solution000006.solution | 4 + .../model_2_3_2-solution000007.solution | 4 + .../expected/model_2_3_2.eprime | 93 + .../model_2_3_4-solution000001.solution | 4 + .../model_2_3_4-solution000002.solution | 4 + .../model_2_3_4-solution000003.solution | 4 + .../model_2_3_4-solution000004.solution | 4 + .../model_2_3_4-solution000005.solution | 4 + .../model_2_3_4-solution000006.solution | 4 + .../model_2_3_4-solution000007.solution | 4 + .../expected/model_2_3_4.eprime | 123 + .../model_2_4_1-solution000001.solution | 4 + .../model_2_4_1-solution000002.solution | 4 + .../model_2_4_1-solution000003.solution | 4 + .../model_2_4_1-solution000004.solution | 4 + .../model_2_4_1-solution000005.solution | 4 + .../model_2_4_1-solution000006.solution | 4 + .../model_2_4_1-solution000007.solution | 4 + .../expected/model_2_4_1.eprime | 105 + .../model_2_4_2-solution000001.solution | 4 + .../model_2_4_2-solution000002.solution | 4 + .../model_2_4_2-solution000003.solution | 4 + .../model_2_4_2-solution000004.solution | 4 + .../model_2_4_2-solution000005.solution | 4 + .../model_2_4_2-solution000006.solution | 4 + .../model_2_4_2-solution000007.solution | 4 + .../expected/model_2_4_2.eprime | 94 + .../model_2_4_3-solution000001.solution | 4 + .../model_2_4_3-solution000002.solution | 4 + .../model_2_4_3-solution000003.solution | 4 + .../model_2_4_3-solution000004.solution | 4 + .../model_2_4_3-solution000005.solution | 4 + .../model_2_4_3-solution000006.solution | 4 + .../model_2_4_3-solution000007.solution | 4 + .../expected/model_2_4_3.eprime | 122 + .../model_3_1_1-solution000001.solution | 4 + .../model_3_1_1-solution000002.solution | 4 + .../model_3_1_1-solution000003.solution | 4 + .../model_3_1_1-solution000004.solution | 4 + .../model_3_1_1-solution000005.solution | 4 + .../model_3_1_1-solution000006.solution | 4 + .../model_3_1_1-solution000007.solution | 4 + .../expected/model_3_1_1.eprime | 75 + .../model_3_1_2-solution000001.solution | 4 + .../model_3_1_2-solution000002.solution | 4 + .../model_3_1_2-solution000003.solution | 4 + .../model_3_1_2-solution000004.solution | 4 + .../model_3_1_2-solution000005.solution | 4 + .../model_3_1_2-solution000006.solution | 4 + .../model_3_1_2-solution000007.solution | 4 + .../expected/model_3_1_2.eprime | 95 + .../model_3_1_4-solution000001.solution | 4 + .../model_3_1_4-solution000002.solution | 4 + .../model_3_1_4-solution000003.solution | 4 + .../model_3_1_4-solution000004.solution | 4 + .../model_3_1_4-solution000005.solution | 4 + .../model_3_1_4-solution000006.solution | 4 + .../model_3_1_4-solution000007.solution | 4 + .../expected/model_3_1_4.eprime | 99 + .../model_3_2_1-solution000001.solution | 4 + .../model_3_2_1-solution000002.solution | 4 + .../model_3_2_1-solution000003.solution | 4 + .../model_3_2_1-solution000004.solution | 4 + .../model_3_2_1-solution000005.solution | 4 + .../model_3_2_1-solution000006.solution | 4 + .../model_3_2_1-solution000007.solution | 4 + .../expected/model_3_2_1.eprime | 106 + .../model_3_2_2-solution000001.solution | 4 + .../model_3_2_2-solution000002.solution | 4 + .../model_3_2_2-solution000003.solution | 4 + .../model_3_2_2-solution000004.solution | 4 + .../model_3_2_2-solution000005.solution | 4 + .../model_3_2_2-solution000006.solution | 4 + .../model_3_2_2-solution000007.solution | 4 + .../expected/model_3_2_2.eprime | 93 + .../model_3_2_4-solution000001.solution | 4 + .../model_3_2_4-solution000002.solution | 4 + .../model_3_2_4-solution000003.solution | 4 + .../model_3_2_4-solution000004.solution | 4 + .../model_3_2_4-solution000005.solution | 4 + .../model_3_2_4-solution000006.solution | 4 + .../model_3_2_4-solution000007.solution | 4 + .../expected/model_3_2_4.eprime | 123 + .../model_3_3_1-solution000001.solution | 4 + .../model_3_3_1-solution000002.solution | 4 + .../model_3_3_1-solution000003.solution | 4 + .../model_3_3_1-solution000004.solution | 4 + .../model_3_3_1-solution000005.solution | 4 + .../model_3_3_1-solution000006.solution | 4 + .../model_3_3_1-solution000007.solution | 4 + .../expected/model_3_3_1.eprime | 86 + .../model_3_3_2-solution000001.solution | 4 + .../model_3_3_2-solution000002.solution | 4 + .../model_3_3_2-solution000003.solution | 4 + .../model_3_3_2-solution000004.solution | 4 + .../model_3_3_2-solution000005.solution | 4 + .../model_3_3_2-solution000006.solution | 4 + .../model_3_3_2-solution000007.solution | 4 + .../expected/model_3_3_2.eprime | 93 + .../model_3_3_3-solution000001.solution | 4 + .../model_3_3_3-solution000002.solution | 4 + .../model_3_3_3-solution000003.solution | 4 + .../model_3_3_3-solution000004.solution | 4 + .../model_3_3_3-solution000005.solution | 4 + .../model_3_3_3-solution000006.solution | 4 + .../model_3_3_3-solution000007.solution | 4 + .../expected/model_3_3_3.eprime | 79 + .../model_3_3_4-solution000001.solution | 4 + .../model_3_3_4-solution000002.solution | 4 + .../model_3_3_4-solution000003.solution | 4 + .../model_3_3_4-solution000004.solution | 4 + .../model_3_3_4-solution000005.solution | 4 + .../model_3_3_4-solution000006.solution | 4 + .../model_3_3_4-solution000007.solution | 4 + .../expected/model_3_3_4.eprime | 98 + .../model_3_4_1-solution000001.solution | 4 + .../model_3_4_1-solution000002.solution | 4 + .../model_3_4_1-solution000003.solution | 4 + .../model_3_4_1-solution000004.solution | 4 + .../model_3_4_1-solution000005.solution | 4 + .../model_3_4_1-solution000006.solution | 4 + .../model_3_4_1-solution000007.solution | 4 + .../expected/model_3_4_1.eprime | 110 + .../model_3_4_2-solution000001.solution | 4 + .../model_3_4_2-solution000002.solution | 4 + .../model_3_4_2-solution000003.solution | 4 + .../model_3_4_2-solution000004.solution | 4 + .../model_3_4_2-solution000005.solution | 4 + .../model_3_4_2-solution000006.solution | 4 + .../model_3_4_2-solution000007.solution | 4 + .../expected/model_3_4_2.eprime | 122 + .../model_3_4_3-solution000001.solution | 4 + .../model_3_4_3-solution000002.solution | 4 + .../model_3_4_3-solution000003.solution | 4 + .../model_3_4_3-solution000004.solution | 4 + .../model_3_4_3-solution000005.solution | 4 + .../model_3_4_3-solution000006.solution | 4 + .../model_3_4_3-solution000007.solution | 4 + .../expected/model_3_4_3.eprime | 98 + .../model_4_1_1-solution000001.solution | 4 + .../model_4_1_1-solution000002.solution | 4 + .../model_4_1_1-solution000003.solution | 4 + .../model_4_1_1-solution000004.solution | 4 + .../model_4_1_1-solution000005.solution | 4 + .../model_4_1_1-solution000006.solution | 4 + .../model_4_1_1-solution000007.solution | 4 + .../expected/model_4_1_1.eprime | 72 + .../model_4_1_2-solution000001.solution | 4 + .../model_4_1_2-solution000002.solution | 4 + .../model_4_1_2-solution000003.solution | 4 + .../model_4_1_2-solution000004.solution | 4 + .../model_4_1_2-solution000005.solution | 4 + .../model_4_1_2-solution000006.solution | 4 + .../model_4_1_2-solution000007.solution | 4 + .../expected/model_4_1_2.eprime | 91 + .../model_4_1_3-solution000001.solution | 4 + .../model_4_1_3-solution000002.solution | 4 + .../model_4_1_3-solution000003.solution | 4 + .../model_4_1_3-solution000004.solution | 4 + .../model_4_1_3-solution000005.solution | 4 + .../model_4_1_3-solution000006.solution | 4 + .../model_4_1_3-solution000007.solution | 4 + .../expected/model_4_1_3.eprime | 96 + .../model_4_2_1-solution000001.solution | 4 + .../model_4_2_1-solution000002.solution | 4 + .../model_4_2_1-solution000003.solution | 4 + .../model_4_2_1-solution000004.solution | 4 + .../model_4_2_1-solution000005.solution | 4 + .../model_4_2_1-solution000006.solution | 4 + .../model_4_2_1-solution000007.solution | 4 + .../expected/model_4_2_1.eprime | 105 + .../model_4_2_2-solution000001.solution | 4 + .../model_4_2_2-solution000002.solution | 4 + .../model_4_2_2-solution000003.solution | 4 + .../model_4_2_2-solution000004.solution | 4 + .../model_4_2_2-solution000005.solution | 4 + .../model_4_2_2-solution000006.solution | 4 + .../model_4_2_2-solution000007.solution | 4 + .../expected/model_4_2_2.eprime | 94 + .../model_4_2_3-solution000001.solution | 4 + .../model_4_2_3-solution000002.solution | 4 + .../model_4_2_3-solution000003.solution | 4 + .../model_4_2_3-solution000004.solution | 4 + .../model_4_2_3-solution000005.solution | 4 + .../model_4_2_3-solution000006.solution | 4 + .../model_4_2_3-solution000007.solution | 4 + .../expected/model_4_2_3.eprime | 122 + .../model_4_3_1-solution000001.solution | 4 + .../model_4_3_1-solution000002.solution | 4 + .../model_4_3_1-solution000003.solution | 4 + .../model_4_3_1-solution000004.solution | 4 + .../model_4_3_1-solution000005.solution | 4 + .../model_4_3_1-solution000006.solution | 4 + .../model_4_3_1-solution000007.solution | 4 + .../expected/model_4_3_1.eprime | 110 + .../model_4_3_2-solution000001.solution | 4 + .../model_4_3_2-solution000002.solution | 4 + .../model_4_3_2-solution000003.solution | 4 + .../model_4_3_2-solution000004.solution | 4 + .../model_4_3_2-solution000005.solution | 4 + .../model_4_3_2-solution000006.solution | 4 + .../model_4_3_2-solution000007.solution | 4 + .../expected/model_4_3_2.eprime | 122 + .../model_4_3_3-solution000001.solution | 4 + .../model_4_3_3-solution000002.solution | 4 + .../model_4_3_3-solution000003.solution | 4 + .../model_4_3_3-solution000004.solution | 4 + .../model_4_3_3-solution000005.solution | 4 + .../model_4_3_3-solution000006.solution | 4 + .../model_4_3_3-solution000007.solution | 4 + .../expected/model_4_3_3.eprime | 98 + .../model_4_4_1-solution000001.solution | 4 + .../model_4_4_1-solution000002.solution | 4 + .../model_4_4_1-solution000003.solution | 4 + .../model_4_4_1-solution000004.solution | 4 + .../model_4_4_1-solution000005.solution | 4 + .../model_4_4_1-solution000006.solution | 4 + .../model_4_4_1-solution000007.solution | 4 + .../expected/model_4_4_1.eprime | 86 + .../model_4_4_2-solution000001.solution | 4 + .../model_4_4_2-solution000002.solution | 4 + .../model_4_4_2-solution000003.solution | 4 + .../model_4_4_2-solution000004.solution | 4 + .../model_4_4_2-solution000005.solution | 4 + .../model_4_4_2-solution000006.solution | 4 + .../model_4_4_2-solution000007.solution | 4 + .../expected/model_4_4_2.eprime | 94 + .../model_4_4_3-solution000001.solution | 4 + .../model_4_4_3-solution000002.solution | 4 + .../model_4_4_3-solution000003.solution | 4 + .../model_4_4_3-solution000004.solution | 4 + .../model_4_4_3-solution000005.solution | 4 + .../model_4_4_3-solution000006.solution | 4 + .../model_4_4_3-solution000007.solution | 4 + .../expected/model_4_4_3.eprime | 98 + .../model_4_4_4-solution000001.solution | 4 + .../model_4_4_4-solution000002.solution | 4 + .../model_4_4_4-solution000003.solution | 4 + .../model_4_4_4-solution000004.solution | 4 + .../model_4_4_4-solution000005.solution | 4 + .../model_4_4_4-solution000006.solution | 4 + .../model_4_4_4-solution000007.solution | 4 + .../expected/model_4_4_4.eprime | 80 + .../basic/cut_01_off/expected/model_2.eprime | 3 +- .../basic/cut_01_off/expected/model_3.eprime | 2 +- .../basic/cut_01_off/expected/model_4.eprime | 2 +- .../model_1_1_1-solution000001.solution | 3 + .../model_1_1_1-solution000002.solution | 3 + .../model_1_1_1-solution000003.solution | 3 + .../model_1_1_1-solution000004.solution | 3 + .../model_1_1_1-solution000005.solution | 3 + .../model_1_1_1-solution000006.solution | 3 + .../model_1_1_1-solution000007.solution | 3 + .../model_1_1_1-solution000008.solution | 3 + .../cut_01_on/expected/model_1_1_1.eprime | 10 + .../model_1_1_2-solution000001.solution | 3 + .../model_1_1_2-solution000002.solution | 3 + .../model_1_1_2-solution000003.solution | 3 + .../model_1_1_2-solution000004.solution | 3 + .../model_1_1_2-solution000005.solution | 3 + .../model_1_1_2-solution000006.solution | 3 + .../model_1_1_2-solution000007.solution | 3 + .../model_1_1_2-solution000008.solution | 3 + ...l_1_2_1.eprime.orig => model_1_1_2.eprime} | 2 +- .../model_1_1_3-solution000001.solution | 3 + .../model_1_1_3-solution000002.solution | 3 + .../model_1_1_3-solution000003.solution | 3 + .../model_1_1_3-solution000004.solution | 3 + .../model_1_1_3-solution000005.solution | 3 + .../model_1_1_3-solution000006.solution | 3 + .../model_1_1_3-solution000007.solution | 3 + .../model_1_1_3-solution000008.solution | 3 + ...l_1_3_1.eprime.orig => model_1_1_3.eprime} | 3 +- .../model_1_1_4-solution000001.solution | 3 + .../model_1_1_4-solution000002.solution | 3 + .../model_1_1_4-solution000003.solution | 3 + .../model_1_1_4-solution000004.solution | 3 + .../model_1_1_4-solution000005.solution | 3 + .../model_1_1_4-solution000006.solution | 3 + .../model_1_1_4-solution000007.solution | 3 + .../model_1_1_4-solution000008.solution | 3 + ...l_1_4_1.eprime.orig => model_1_1_4.eprime} | 3 +- .../model_1_2_1-solution000001.solution | 3 + .../model_1_2_1-solution000002.solution | 3 + .../model_1_2_1-solution000003.solution | 3 + .../model_1_2_1-solution000004.solution | 3 + .../model_1_2_1-solution000005.solution | 3 + .../model_1_2_1-solution000006.solution | 3 + .../model_1_2_1-solution000007.solution | 3 + .../model_1_2_1-solution000008.solution | 3 + .../model_1_2_3-solution000001.solution | 3 + .../model_1_2_3-solution000002.solution | 3 + .../model_1_2_3-solution000003.solution | 3 + .../model_1_2_3-solution000004.solution | 3 + .../model_1_2_3-solution000005.solution | 3 + .../model_1_2_3-solution000006.solution | 3 + .../model_1_2_3-solution000007.solution | 3 + .../model_1_2_3-solution000008.solution | 3 + .../model_1_2_4-solution000001.solution | 3 + .../model_1_2_4-solution000002.solution | 3 + .../model_1_2_4-solution000003.solution | 3 + .../model_1_2_4-solution000004.solution | 3 + .../model_1_2_4-solution000005.solution | 3 + .../model_1_2_4-solution000006.solution | 3 + .../model_1_2_4-solution000007.solution | 3 + .../model_1_2_4-solution000008.solution | 3 + .../model_1_3_1-solution000001.solution | 3 + .../model_1_3_1-solution000002.solution | 3 + .../model_1_3_1-solution000003.solution | 3 + .../model_1_3_1-solution000004.solution | 3 + .../model_1_3_1-solution000005.solution | 3 + .../model_1_3_1-solution000006.solution | 3 + .../model_1_3_1-solution000007.solution | 3 + .../model_1_3_1-solution000008.solution | 3 + .../model_1_3_2-solution000001.solution | 3 + .../model_1_3_2-solution000002.solution | 3 + .../model_1_3_2-solution000003.solution | 3 + .../model_1_3_2-solution000004.solution | 3 + .../model_1_3_2-solution000005.solution | 3 + .../model_1_3_2-solution000006.solution | 3 + .../model_1_3_2-solution000007.solution | 3 + .../model_1_3_2-solution000008.solution | 3 + .../model_1_3_4-solution000001.solution | 3 + .../model_1_3_4-solution000002.solution | 3 + .../model_1_3_4-solution000003.solution | 3 + .../model_1_3_4-solution000004.solution | 3 + .../model_1_3_4-solution000005.solution | 3 + .../model_1_3_4-solution000006.solution | 3 + .../model_1_3_4-solution000007.solution | 3 + .../model_1_3_4-solution000008.solution | 3 + .../model_1_4_1-solution000001.solution | 3 + .../model_1_4_1-solution000002.solution | 3 + .../model_1_4_1-solution000003.solution | 3 + .../model_1_4_1-solution000004.solution | 3 + .../model_1_4_1-solution000005.solution | 3 + .../model_1_4_1-solution000006.solution | 3 + .../model_1_4_1-solution000007.solution | 3 + .../model_1_4_1-solution000008.solution | 3 + .../model_1_4_2-solution000001.solution | 3 + .../model_1_4_2-solution000002.solution | 3 + .../model_1_4_2-solution000003.solution | 3 + .../model_1_4_2-solution000004.solution | 3 + .../model_1_4_2-solution000005.solution | 3 + .../model_1_4_2-solution000006.solution | 3 + .../model_1_4_2-solution000007.solution | 3 + .../model_1_4_2-solution000008.solution | 3 + .../model_1_4_3-solution000001.solution | 3 + .../model_1_4_3-solution000002.solution | 3 + .../model_1_4_3-solution000003.solution | 3 + .../model_1_4_3-solution000004.solution | 3 + .../model_1_4_3-solution000005.solution | 3 + .../model_1_4_3-solution000006.solution | 3 + .../model_1_4_3-solution000007.solution | 3 + .../model_1_4_3-solution000008.solution | 3 + .../model_2_1_1-solution000001.solution | 3 + .../model_2_1_1-solution000002.solution | 3 + .../model_2_1_1-solution000003.solution | 3 + .../model_2_1_1-solution000004.solution | 3 + .../model_2_1_1-solution000005.solution | 3 + .../model_2_1_1-solution000006.solution | 3 + .../model_2_1_1-solution000007.solution | 3 + .../model_2_1_1-solution000008.solution | 3 + .../model_2_1_3-solution000001.solution | 3 + .../model_2_1_3-solution000002.solution | 3 + .../model_2_1_3-solution000003.solution | 3 + .../model_2_1_3-solution000004.solution | 3 + .../model_2_1_3-solution000005.solution | 3 + .../model_2_1_3-solution000006.solution | 3 + .../model_2_1_3-solution000007.solution | 3 + .../model_2_1_3-solution000008.solution | 3 + .../model_2_1_4-solution000001.solution | 3 + .../model_2_1_4-solution000002.solution | 3 + .../model_2_1_4-solution000003.solution | 3 + .../model_2_1_4-solution000004.solution | 3 + .../model_2_1_4-solution000005.solution | 3 + .../model_2_1_4-solution000006.solution | 3 + .../model_2_1_4-solution000007.solution | 3 + .../model_2_1_4-solution000008.solution | 3 + .../model_2_2_1-solution000001.solution | 3 + .../model_2_2_1-solution000002.solution | 3 + .../model_2_2_1-solution000003.solution | 3 + .../model_2_2_1-solution000004.solution | 3 + .../model_2_2_1-solution000005.solution | 3 + .../model_2_2_1-solution000006.solution | 3 + .../model_2_2_1-solution000007.solution | 3 + .../model_2_2_1-solution000008.solution | 3 + .../expected/model_2_2_1.eprime.orig | 20 - .../model_2_2_2-solution000001.solution | 3 + .../model_2_2_2-solution000002.solution | 3 + .../model_2_2_2-solution000003.solution | 3 + .../model_2_2_2-solution000004.solution | 3 + .../model_2_2_2-solution000005.solution | 3 + .../model_2_2_2-solution000006.solution | 3 + .../model_2_2_2-solution000007.solution | 3 + .../model_2_2_2-solution000008.solution | 3 + .../expected/model_2_2_2.eprime.orig | 15 - .../model_2_2_3-solution000001.solution | 3 + .../model_2_2_3-solution000002.solution | 3 + .../model_2_2_3-solution000003.solution | 3 + .../model_2_2_3-solution000004.solution | 3 + .../model_2_2_3-solution000005.solution | 3 + .../model_2_2_3-solution000006.solution | 3 + .../model_2_2_3-solution000007.solution | 3 + .../model_2_2_3-solution000008.solution | 3 + .../model_2_2_4-solution000001.solution | 3 + .../model_2_2_4-solution000002.solution | 3 + .../model_2_2_4-solution000003.solution | 3 + .../model_2_2_4-solution000004.solution | 3 + .../model_2_2_4-solution000005.solution | 3 + .../model_2_2_4-solution000006.solution | 3 + .../model_2_2_4-solution000007.solution | 3 + .../model_2_2_4-solution000008.solution | 3 + .../model_2_3_1-solution000001.solution | 3 + .../model_2_3_1-solution000002.solution | 3 + .../model_2_3_1-solution000003.solution | 3 + .../model_2_3_1-solution000004.solution | 3 + .../model_2_3_1-solution000005.solution | 3 + .../model_2_3_1-solution000006.solution | 3 + .../model_2_3_1-solution000007.solution | 3 + .../model_2_3_1-solution000008.solution | 3 + .../model_2_3_2-solution000001.solution | 3 + .../model_2_3_2-solution000002.solution | 3 + .../model_2_3_2-solution000003.solution | 3 + .../model_2_3_2-solution000004.solution | 3 + .../model_2_3_2-solution000005.solution | 3 + .../model_2_3_2-solution000006.solution | 3 + .../model_2_3_2-solution000007.solution | 3 + .../model_2_3_2-solution000008.solution | 3 + .../model_2_3_4-solution000001.solution | 3 + .../model_2_3_4-solution000002.solution | 3 + .../model_2_3_4-solution000003.solution | 3 + .../model_2_3_4-solution000004.solution | 3 + .../model_2_3_4-solution000005.solution | 3 + .../model_2_3_4-solution000006.solution | 3 + .../model_2_3_4-solution000007.solution | 3 + .../model_2_3_4-solution000008.solution | 3 + .../model_2_4_1-solution000001.solution | 3 + .../model_2_4_1-solution000002.solution | 3 + .../model_2_4_1-solution000003.solution | 3 + .../model_2_4_1-solution000004.solution | 3 + .../model_2_4_1-solution000005.solution | 3 + .../model_2_4_1-solution000006.solution | 3 + .../model_2_4_1-solution000007.solution | 3 + .../model_2_4_1-solution000008.solution | 3 + .../model_2_4_2-solution000001.solution | 3 + .../model_2_4_2-solution000002.solution | 3 + .../model_2_4_2-solution000003.solution | 3 + .../model_2_4_2-solution000004.solution | 3 + .../model_2_4_2-solution000005.solution | 3 + .../model_2_4_2-solution000006.solution | 3 + .../model_2_4_2-solution000007.solution | 3 + .../model_2_4_2-solution000008.solution | 3 + .../model_2_4_3-solution000001.solution | 3 + .../model_2_4_3-solution000002.solution | 3 + .../model_2_4_3-solution000003.solution | 3 + .../model_2_4_3-solution000004.solution | 3 + .../model_2_4_3-solution000005.solution | 3 + .../model_2_4_3-solution000006.solution | 3 + .../model_2_4_3-solution000007.solution | 3 + .../model_2_4_3-solution000008.solution | 3 + .../model_3_1_1-solution000001.solution | 3 + .../model_3_1_1-solution000002.solution | 3 + .../model_3_1_1-solution000003.solution | 3 + .../model_3_1_1-solution000004.solution | 3 + .../model_3_1_1-solution000005.solution | 3 + .../model_3_1_1-solution000006.solution | 3 + .../model_3_1_1-solution000007.solution | 3 + .../model_3_1_1-solution000008.solution | 3 + .../model_3_1_2-solution000001.solution | 3 + .../model_3_1_2-solution000002.solution | 3 + .../model_3_1_2-solution000003.solution | 3 + .../model_3_1_2-solution000004.solution | 3 + .../model_3_1_2-solution000005.solution | 3 + .../model_3_1_2-solution000006.solution | 3 + .../model_3_1_2-solution000007.solution | 3 + .../model_3_1_2-solution000008.solution | 3 + .../model_3_1_4-solution000001.solution | 3 + .../model_3_1_4-solution000002.solution | 3 + .../model_3_1_4-solution000003.solution | 3 + .../model_3_1_4-solution000004.solution | 3 + .../model_3_1_4-solution000005.solution | 3 + .../model_3_1_4-solution000006.solution | 3 + .../model_3_1_4-solution000007.solution | 3 + .../model_3_1_4-solution000008.solution | 3 + .../model_3_2_1-solution000001.solution | 3 + .../model_3_2_1-solution000002.solution | 3 + .../model_3_2_1-solution000003.solution | 3 + .../model_3_2_1-solution000004.solution | 3 + .../model_3_2_1-solution000005.solution | 3 + .../model_3_2_1-solution000006.solution | 3 + .../model_3_2_1-solution000007.solution | 3 + .../model_3_2_1-solution000008.solution | 3 + .../model_3_2_2-solution000001.solution | 3 + .../model_3_2_2-solution000002.solution | 3 + .../model_3_2_2-solution000003.solution | 3 + .../model_3_2_2-solution000004.solution | 3 + .../model_3_2_2-solution000005.solution | 3 + .../model_3_2_2-solution000006.solution | 3 + .../model_3_2_2-solution000007.solution | 3 + .../model_3_2_2-solution000008.solution | 3 + .../model_3_2_4-solution000001.solution | 3 + .../model_3_2_4-solution000002.solution | 3 + .../model_3_2_4-solution000003.solution | 3 + .../model_3_2_4-solution000004.solution | 3 + .../model_3_2_4-solution000005.solution | 3 + .../model_3_2_4-solution000006.solution | 3 + .../model_3_2_4-solution000007.solution | 3 + .../model_3_2_4-solution000008.solution | 3 + .../model_3_3_1-solution000001.solution | 3 + .../model_3_3_1-solution000002.solution | 3 + .../model_3_3_1-solution000003.solution | 3 + .../model_3_3_1-solution000004.solution | 3 + .../model_3_3_1-solution000005.solution | 3 + .../model_3_3_1-solution000006.solution | 3 + .../model_3_3_1-solution000007.solution | 3 + .../model_3_3_1-solution000008.solution | 3 + .../expected/model_3_3_1.eprime.orig | 25 - .../model_3_3_2-solution000001.solution | 3 + .../model_3_3_2-solution000002.solution | 3 + .../model_3_3_2-solution000003.solution | 3 + .../model_3_3_2-solution000004.solution | 3 + .../model_3_3_2-solution000005.solution | 3 + .../model_3_3_2-solution000006.solution | 3 + .../model_3_3_2-solution000007.solution | 3 + .../model_3_3_2-solution000008.solution | 3 + .../model_3_3_3-solution000001.solution | 3 + .../model_3_3_3-solution000002.solution | 3 + .../model_3_3_3-solution000003.solution | 3 + .../model_3_3_3-solution000004.solution | 3 + .../model_3_3_3-solution000005.solution | 3 + .../model_3_3_3-solution000006.solution | 3 + .../model_3_3_3-solution000007.solution | 3 + .../model_3_3_3-solution000008.solution | 3 + .../expected/model_3_3_3.eprime.orig | 18 - .../model_3_3_4-solution000001.solution | 3 + .../model_3_3_4-solution000002.solution | 3 + .../model_3_3_4-solution000003.solution | 3 + .../model_3_3_4-solution000004.solution | 3 + .../model_3_3_4-solution000005.solution | 3 + .../model_3_3_4-solution000006.solution | 3 + .../model_3_3_4-solution000007.solution | 3 + .../model_3_3_4-solution000008.solution | 3 + .../model_3_4_1-solution000001.solution | 3 + .../model_3_4_1-solution000002.solution | 3 + .../model_3_4_1-solution000003.solution | 3 + .../model_3_4_1-solution000004.solution | 3 + .../model_3_4_1-solution000005.solution | 3 + .../model_3_4_1-solution000006.solution | 3 + .../model_3_4_1-solution000007.solution | 3 + .../model_3_4_1-solution000008.solution | 3 + .../model_3_4_2-solution000001.solution | 3 + .../model_3_4_2-solution000002.solution | 3 + .../model_3_4_2-solution000003.solution | 3 + .../model_3_4_2-solution000004.solution | 3 + .../model_3_4_2-solution000005.solution | 3 + .../model_3_4_2-solution000006.solution | 3 + .../model_3_4_2-solution000007.solution | 3 + .../model_3_4_2-solution000008.solution | 3 + .../model_3_4_3-solution000001.solution | 3 + .../model_3_4_3-solution000002.solution | 3 + .../model_3_4_3-solution000003.solution | 3 + .../model_3_4_3-solution000004.solution | 3 + .../model_3_4_3-solution000005.solution | 3 + .../model_3_4_3-solution000006.solution | 3 + .../model_3_4_3-solution000007.solution | 3 + .../model_3_4_3-solution000008.solution | 3 + .../model_4_1_1-solution000001.solution | 3 + .../model_4_1_1-solution000002.solution | 3 + .../model_4_1_1-solution000003.solution | 3 + .../model_4_1_1-solution000004.solution | 3 + .../model_4_1_1-solution000005.solution | 3 + .../model_4_1_1-solution000006.solution | 3 + .../model_4_1_1-solution000007.solution | 3 + .../model_4_1_1-solution000008.solution | 3 + .../model_4_1_2-solution000001.solution | 3 + .../model_4_1_2-solution000002.solution | 3 + .../model_4_1_2-solution000003.solution | 3 + .../model_4_1_2-solution000004.solution | 3 + .../model_4_1_2-solution000005.solution | 3 + .../model_4_1_2-solution000006.solution | 3 + .../model_4_1_2-solution000007.solution | 3 + .../model_4_1_2-solution000008.solution | 3 + .../model_4_1_3-solution000001.solution | 3 + .../model_4_1_3-solution000002.solution | 3 + .../model_4_1_3-solution000003.solution | 3 + .../model_4_1_3-solution000004.solution | 3 + .../model_4_1_3-solution000005.solution | 3 + .../model_4_1_3-solution000006.solution | 3 + .../model_4_1_3-solution000007.solution | 3 + .../model_4_1_3-solution000008.solution | 3 + .../model_4_2_1-solution000001.solution | 3 + .../model_4_2_1-solution000002.solution | 3 + .../model_4_2_1-solution000003.solution | 3 + .../model_4_2_1-solution000004.solution | 3 + .../model_4_2_1-solution000005.solution | 3 + .../model_4_2_1-solution000006.solution | 3 + .../model_4_2_1-solution000007.solution | 3 + .../model_4_2_1-solution000008.solution | 3 + .../model_4_2_2-solution000001.solution | 3 + .../model_4_2_2-solution000002.solution | 3 + .../model_4_2_2-solution000003.solution | 3 + .../model_4_2_2-solution000004.solution | 3 + .../model_4_2_2-solution000005.solution | 3 + .../model_4_2_2-solution000006.solution | 3 + .../model_4_2_2-solution000007.solution | 3 + .../model_4_2_2-solution000008.solution | 3 + .../model_4_2_3-solution000001.solution | 3 + .../model_4_2_3-solution000002.solution | 3 + .../model_4_2_3-solution000003.solution | 3 + .../model_4_2_3-solution000004.solution | 3 + .../model_4_2_3-solution000005.solution | 3 + .../model_4_2_3-solution000006.solution | 3 + .../model_4_2_3-solution000007.solution | 3 + .../model_4_2_3-solution000008.solution | 3 + .../model_4_3_1-solution000001.solution | 3 + .../model_4_3_1-solution000002.solution | 3 + .../model_4_3_1-solution000003.solution | 3 + .../model_4_3_1-solution000004.solution | 3 + .../model_4_3_1-solution000005.solution | 3 + .../model_4_3_1-solution000006.solution | 3 + .../model_4_3_1-solution000007.solution | 3 + .../model_4_3_1-solution000008.solution | 3 + .../model_4_3_2-solution000001.solution | 3 + .../model_4_3_2-solution000002.solution | 3 + .../model_4_3_2-solution000003.solution | 3 + .../model_4_3_2-solution000004.solution | 3 + .../model_4_3_2-solution000005.solution | 3 + .../model_4_3_2-solution000006.solution | 3 + .../model_4_3_2-solution000007.solution | 3 + .../model_4_3_2-solution000008.solution | 3 + .../model_4_3_3-solution000001.solution | 3 + .../model_4_3_3-solution000002.solution | 3 + .../model_4_3_3-solution000003.solution | 3 + .../model_4_3_3-solution000004.solution | 3 + .../model_4_3_3-solution000005.solution | 3 + .../model_4_3_3-solution000006.solution | 3 + .../model_4_3_3-solution000007.solution | 3 + .../model_4_3_3-solution000008.solution | 3 + .../model_4_4_1-solution000001.solution | 3 + .../model_4_4_1-solution000002.solution | 3 + .../model_4_4_1-solution000003.solution | 3 + .../model_4_4_1-solution000004.solution | 3 + .../model_4_4_1-solution000005.solution | 3 + .../model_4_4_1-solution000006.solution | 3 + .../model_4_4_1-solution000007.solution | 3 + .../model_4_4_1-solution000008.solution | 3 + .../model_4_4_2-solution000001.solution | 3 + .../model_4_4_2-solution000002.solution | 3 + .../model_4_4_2-solution000003.solution | 3 + .../model_4_4_2-solution000004.solution | 3 + .../model_4_4_2-solution000005.solution | 3 + .../model_4_4_2-solution000006.solution | 3 + .../model_4_4_2-solution000007.solution | 3 + .../model_4_4_2-solution000008.solution | 3 + .../model_4_4_3-solution000001.solution | 3 + .../model_4_4_3-solution000002.solution | 3 + .../model_4_4_3-solution000003.solution | 3 + .../model_4_4_3-solution000004.solution | 3 + .../model_4_4_3-solution000005.solution | 3 + .../model_4_4_3-solution000006.solution | 3 + .../model_4_4_3-solution000007.solution | 3 + .../model_4_4_3-solution000008.solution | 3 + .../model_4_4_4-solution000001.solution | 3 + .../model_4_4_4-solution000002.solution | 3 + .../model_4_4_4-solution000003.solution | 3 + .../model_4_4_4-solution000004.solution | 3 + .../model_4_4_4-solution000005.solution | 3 + .../model_4_4_4-solution000006.solution | 3 + .../model_4_4_4-solution000007.solution | 3 + .../model_4_4_4-solution000008.solution | 3 + .../enum05/expected/model_1_2.eprime | 3 +- .../enum05/expected/model_1_3.eprime | 2 +- .../enum05/expected/model_1_4.eprime | 3 +- .../enum05/expected/model_2_1.eprime | 3 +- .../enum05/expected/model_2_2.eprime | 3 +- .../enum05/expected/model_2_3.eprime | 5 +- .../enum05/expected/model_2_4.eprime | 6 +- .../enum05/expected/model_3_1.eprime | 2 +- .../enum05/expected/model_3_2.eprime | 5 +- .../enum05/expected/model_3_3.eprime | 2 +- .../enum05/expected/model_3_4.eprime | 5 +- .../enum05/expected/model_4_1.eprime | 3 +- .../enum05/expected/model_4_2.eprime | 6 +- .../enum05/expected/model_4_3.eprime | 5 +- .../enum05/expected/model_4_4.eprime | 3 +- .../enum05-unnamed/expected/model_2.eprime | 3 +- .../enum05-unnamed/expected/model_3.eprime | 2 +- .../enum05-unnamed/expected/model_4.eprime | 3 +- .../basic/enum06/expected/model_1_1.eprime | 6 - .../basic/enum06/expected/model_1_2.eprime | 14 - .../basic/enum06/expected/model_1_3.eprime | 6 - .../basic/enum06/expected/model_2_1.eprime | 5 +- .../basic/enum06/expected/model_2_2.eprime | 2 +- .../basic/enum06/expected/model_2_3.eprime | 2 +- .../basic/enum06/expected/model_3_1.eprime | 3 +- .../basic/enum06/expected/model_3_2.eprime | 2 +- .../expected/model_1-solution000001.solution | 3 + .../expected/model_1-solution000002.solution | 3 + .../expected/model_1-solution000003.solution | 3 + .../expected/model_1-solution000004.solution | 3 + .../expected/model_1-solution000005.solution | 3 + .../expected/model_1-solution000006.solution | 3 + .../expected/model_2-solution000001.solution | 3 + .../expected/model_2-solution000002.solution | 3 + .../expected/model_2-solution000003.solution | 3 + .../expected/model_2-solution000004.solution | 3 + .../expected/model_2-solution000005.solution | 3 + .../expected/model_2-solution000006.solution | 3 + .../function_range/expected/model.eprime.orig | 12 - .../expected/model_1.eprime | 6 - .../expected/model_2.eprime | 8 - .../model_1_1-solution000001.solution | 3 + .../model_1_1-solution000002.solution | 7 + .../model_1_1-solution000003.solution | 7 + .../model_1_1-solution000004.solution | 7 + .../expected/model_1_1.eprime | 6 + .../model_1_2-solution000001.solution | 7 + .../model_1_2-solution000002.solution | 7 + .../model_1_2-solution000003.solution | 7 + .../model_1_2-solution000004.solution | 3 + .../expected/model_1_2.eprime | 22 + .../model_1_3-solution000001.solution | 3 + .../model_1_3-solution000002.solution | 7 + .../model_1_3-solution000003.solution | 7 + .../model_1_3-solution000004.solution | 7 + .../expected/model_1_3.eprime | 25 + .../model_1_4-solution000001.solution | 3 + .../model_1_4-solution000002.solution | 7 + .../model_1_4-solution000003.solution | 7 + .../model_1_4-solution000004.solution | 7 + .../expected/model_1_4.eprime | 27 + .../model_2_1-solution000001.solution | 3 + .../model_2_1-solution000002.solution | 7 + .../model_2_1-solution000003.solution | 7 + .../model_2_1-solution000004.solution | 7 + .../expected/model_2_1.eprime | 23 + .../model_2_2-solution000001.solution | 7 + .../model_2_2-solution000002.solution | 7 + .../model_2_2-solution000003.solution | 7 + .../model_2_2-solution000004.solution | 3 + .../expected/model_2_2.eprime | 14 + .../model_2_3-solution000001.solution | 3 + .../model_2_3-solution000002.solution | 7 + .../model_2_3-solution000003.solution | 7 + .../model_2_3-solution000004.solution | 7 + .../expected/model_2_3.eprime | 35 + .../model_2_4-solution000001.solution | 3 + .../model_2_4-solution000002.solution | 7 + .../model_2_4-solution000003.solution | 7 + .../model_2_4-solution000004.solution | 7 + .../expected/model_2_4.eprime | 38 + .../model_3_1-solution000001.solution | 3 + .../model_3_1-solution000002.solution | 7 + .../model_3_1-solution000003.solution | 7 + .../model_3_1-solution000004.solution | 7 + .../expected/model_3_1.eprime | 26 + .../model_3_2-solution000001.solution | 7 + .../model_3_2-solution000002.solution | 7 + .../model_3_2-solution000003.solution | 7 + .../model_3_2-solution000004.solution | 3 + .../expected/model_3_2.eprime | 35 + .../model_3_3-solution000001.solution | 3 + .../model_3_3-solution000002.solution | 7 + .../model_3_3-solution000003.solution | 7 + .../model_3_3-solution000004.solution | 7 + .../expected/model_3_3.eprime | 16 + .../model_3_4-solution000001.solution | 3 + .../model_3_4-solution000002.solution | 7 + .../model_3_4-solution000003.solution | 7 + .../model_3_4-solution000004.solution | 7 + .../expected/model_3_4.eprime | 42 + .../model_4_1-solution000001.solution | 3 + .../model_4_1-solution000002.solution | 7 + .../model_4_1-solution000003.solution | 7 + .../model_4_1-solution000004.solution | 7 + .../expected/model_4_1.eprime | 28 + .../model_4_2-solution000001.solution | 7 + .../model_4_2-solution000002.solution | 7 + .../model_4_2-solution000003.solution | 7 + .../model_4_2-solution000004.solution | 3 + .../expected/model_4_2.eprime | 38 + .../model_4_3-solution000001.solution | 3 + .../model_4_3-solution000002.solution | 7 + .../model_4_3-solution000003.solution | 7 + .../model_4_3-solution000004.solution | 7 + .../expected/model_4_3.eprime | 42 + .../model_4_4-solution000001.solution | 3 + .../model_4_4-solution000002.solution | 7 + .../model_4_4-solution000003.solution | 7 + .../model_4_4-solution000004.solution | 7 + .../expected/model_4_4.eprime | 19 + .../model_1_1-solution000001.solution | 13 + .../expected/model_1_1.eprime | 8 + .../model_1_2-solution000001.solution | 13 + .../expected/model_1_2.eprime | 30 + .../model_1_3-solution000001.solution | 13 + .../expected/model_1_3.eprime | 31 + .../model_1_4-solution000001.solution | 13 + .../expected/model_1_4.eprime | 37 + .../model_2_1-solution000001.solution | 13 + .../expected/model_2_1.eprime | 31 + .../model_2_2-solution000001.solution | 13 + .../expected/model_2_2.eprime | 19 + .../model_2_3-solution000001.solution | 13 + .../expected/model_2_3.eprime | 45 + .../model_2_4-solution000001.solution | 13 + .../expected/model_2_4.eprime | 50 + .../model_3_1-solution000001.solution | 13 + .../expected/model_3_1.eprime | 32 + .../model_3_2-solution000001.solution | 13 + .../expected/model_3_2.eprime | 44 + .../model_3_3-solution000001.solution | 13 + .../expected/model_3_3.eprime | 19 + .../model_3_4-solution000001.solution | 13 + .../expected/model_3_4.eprime | 54 + .../model_4_1-solution000001.solution | 13 + .../expected/model_4_1.eprime | 38 + .../model_4_2-solution000001.solution | 13 + .../expected/model_4_2.eprime | 50 + .../model_4_3-solution000001.solution | 13 + .../expected/model_4_3.eprime | 55 + .../model_4_4-solution000001.solution | 13 + .../expected/model_4_4.eprime | 25 + .../model_1_1_1_1-solution000001.solution | 4 + .../model_1_1_1_2-solution000001.solution | 4 + .../model_1_1_2_1-solution000001.solution | 4 + .../model_1_1_2_2-solution000001.solution | 4 + .../model_1_2_1_1-solution000001.solution | 4 + .../model_1_2_1_2-solution000001.solution | 4 + .../model_1_2_2_1-solution000001.solution | 4 + .../model_1_2_2_2-solution000001.solution | 4 + .../model_2_1_1_1-solution000001.solution | 4 + .../model_2_1_1_2-solution000001.solution | 4 + .../model_2_1_2_1-solution000001.solution | 4 + .../model_2_1_2_2-solution000001.solution | 4 + .../model_2_2_1_1-solution000001.solution | 4 + .../model_2_2_1_2-solution000001.solution | 4 + .../model_2_2_2_1-solution000001.solution | 4 + .../model_2_2_2_2-solution000001.solution | 4 + .../model_1_1_1_1-solution000001.solution | 4 + .../model_1_1_1_2-solution000001.solution | 4 + .../model_1_1_2_1-solution000001.solution | 4 + .../model_1_1_2_2-solution000001.solution | 4 + .../model_1_2_1_1-solution000001.solution | 4 + .../model_1_2_1_2-solution000001.solution | 4 + .../model_1_2_2_1-solution000001.solution | 4 + .../model_1_2_2_2-solution000001.solution | 4 + .../model_2_1_1_1-solution000001.solution | 4 + .../model_2_1_1_2-solution000001.solution | 4 + .../model_2_1_2_1-solution000001.solution | 4 + .../model_2_1_2_2-solution000001.solution | 4 + .../model_2_2_1_1-solution000001.solution | 4 + .../expected/model_2_2_1_1.eprime} | 11 - .../model_2_2_1_2-solution000001.solution | 4 + .../model_2_2_2_1-solution000001.solution | 4 + .../model_2_2_2_2-solution000001.solution | 4 + .../basic/mset01_find/expected/model_1.eprime | 3 +- .../basic/mset01_find/expected/model_2.eprime | 2 +- .../model_1_1-param1-solution000001.solution | 3 + .../expected/model_1_1-param1.eprime-param | 5 + .../model_1_1-param4-solution000001.solution | 3 + .../expected/model_1_1-param4.eprime-param | 5 + .../model_1_1-param7-solution000001.solution | 3 + .../expected/model_1_1-param7.eprime-param | 5 + .../model_1_2-param1-solution000001.solution | 3 + .../expected/model_1_2-param1.eprime-param | 5 + .../model_1_2-param4-solution000001.solution | 3 + .../expected/model_1_2-param4.eprime-param | 5 + .../model_1_2-param7-solution000001.solution | 3 + .../expected/model_1_2-param7.eprime-param | 5 + .../model_1_3-param1-solution000001.solution | 3 + .../expected/model_1_3-param1.eprime-param | 5 + .../model_1_3-param4-solution000001.solution | 3 + .../expected/model_1_3-param4.eprime-param | 5 + .../model_1_3-param7-solution000001.solution | 3 + .../expected/model_1_3-param7.eprime-param | 5 + .../model_2_1-param1-solution000001.solution | 3 + .../expected/model_2_1-param1.eprime-param | 5 + .../model_2_1-param4-solution000001.solution | 3 + .../expected/model_2_1-param4.eprime-param | 5 + .../model_2_1-param7-solution000001.solution | 3 + .../expected/model_2_1-param7.eprime-param | 5 + .../model_2_2-param1-solution000001.solution | 3 + .../expected/model_2_2-param1.eprime-param | 5 + .../model_2_2-param4-solution000001.solution | 3 + .../expected/model_2_2-param4.eprime-param | 5 + .../model_2_2-param7-solution000001.solution | 3 + .../expected/model_2_2-param7.eprime-param | 5 + .../mset01_param/expected/model_2_2.eprime | 37 + .../model_2_3-param1-solution000001.solution | 3 + .../expected/model_2_3-param1.eprime-param | 5 + .../model_2_3-param4-solution000001.solution | 3 + .../expected/model_2_3-param4.eprime-param | 5 + .../model_2_3-param7-solution000001.solution | 3 + .../expected/model_2_3-param7.eprime-param | 5 + .../mset01_param/expected/model_2_3.eprime | 51 + .../model_3_1-param1-solution000001.solution | 3 + .../expected/model_3_1-param1.eprime-param | 5 + .../model_3_1-param4-solution000001.solution | 3 + .../expected/model_3_1-param4.eprime-param | 5 + .../model_3_1-param7-solution000001.solution | 3 + .../expected/model_3_1-param7.eprime-param | 5 + .../model_3_2-param1-solution000001.solution | 3 + .../expected/model_3_2-param1.eprime-param | 5 + .../model_3_2-param4-solution000001.solution | 3 + .../expected/model_3_2-param4.eprime-param | 5 + .../model_3_2-param7-solution000001.solution | 3 + .../expected/model_3_2-param7.eprime-param | 5 + .../mset01_param/expected/model_3_2.eprime | 43 + .../model_3_3-param1-solution000001.solution | 3 + .../expected/model_3_3-param1.eprime-param | 5 + .../model_3_3-param4-solution000001.solution | 3 + .../expected/model_3_3-param4.eprime-param | 5 + .../model_3_3-param7-solution000001.solution | 3 + .../expected/model_3_3-param7.eprime-param | 5 + .../mset01_param/expected/model_3_3.eprime | 18 + .../basic/mset02/expected/model_1.eprime | 3 +- .../basic/mset02/expected/model_2.eprime | 2 +- .../basic/mset03_1/expected/model_1.eprime | 3 +- .../basic/mset03_1/expected/model_2.eprime | 2 +- .../basic/mset03_2/expected/model_1.eprime | 3 +- .../basic/mset03_2/expected/model_2.eprime | 2 +- .../basic/mset04/expected/model_1.eprime | 3 +- .../basic/mset04/expected/model_2.eprime | 3 +- .../basic/mset05/expected/model_1.eprime | 3 +- .../basic/mset05/expected/model_2.eprime | 2 +- .../basic/mset06_1/expected/model_1.eprime | 3 +- .../basic/mset06_1/expected/model_2.eprime | 2 +- .../basic/mset06_2/expected/model_1.eprime | 3 +- .../basic/mset06_2/expected/model_2.eprime | 2 +- .../basic/mset07/expected/model_1.eprime | 3 +- .../basic/mset07/expected/model_2.eprime | 2 +- .../model_1_1-solution000001.solution | 4 + .../model_1_1-solution000002.solution | 4 + .../name-reuse/expected/model_1_1.eprime | 13 + .../model_1_2-solution000001.solution | 4 + .../model_1_2-solution000002.solution | 4 + .../name-reuse/expected/model_1_2.eprime | 22 + .../model_1_3-solution000001.solution | 4 + .../model_1_3-solution000002.solution | 4 + .../name-reuse/expected/model_1_3.eprime | 25 + .../model_1_4-solution000001.solution | 4 + .../model_1_4-solution000002.solution | 4 + .../name-reuse/expected/model_1_4.eprime | 25 + .../model_2_1-solution000001.solution | 4 + .../model_2_1-solution000002.solution | 4 + .../name-reuse/expected/model_2_1.eprime | 22 + .../model_2_2-solution000001.solution | 4 + .../model_2_2-solution000002.solution | 4 + .../name-reuse/expected/model_2_2.eprime | 17 + .../model_2_3-solution000001.solution | 4 + .../model_2_3-solution000002.solution | 4 + .../name-reuse/expected/model_2_3.eprime | 34 + .../model_2_4-solution000001.solution | 4 + .../model_2_4-solution000002.solution | 4 + .../name-reuse/expected/model_2_4.eprime | 35 + .../model_3_1-solution000001.solution | 4 + .../model_3_1-solution000002.solution | 4 + .../name-reuse/expected/model_3_1.eprime | 27 + .../model_3_2-solution000001.solution | 4 + .../model_3_2-solution000002.solution | 4 + .../name-reuse/expected/model_3_2.eprime | 36 + .../model_3_3-solution000001.solution | 4 + .../model_3_3-solution000002.solution | 4 + .../name-reuse/expected/model_3_3.eprime | 21 + .../model_3_4-solution000001.solution | 4 + .../model_3_4-solution000002.solution | 4 + .../name-reuse/expected/model_3_4.eprime | 40 + .../model_4_1-solution000001.solution | 4 + .../model_4_1-solution000002.solution | 4 + .../name-reuse/expected/model_4_1.eprime | 28 + .../model_4_2-solution000001.solution | 4 + .../model_4_2-solution000002.solution | 4 + .../name-reuse/expected/model_4_2.eprime | 37 + .../model_4_3-solution000001.solution | 4 + .../model_4_3-solution000002.solution | 4 + .../name-reuse/expected/model_4_3.eprime | 40 + .../model_4_4-solution000001.solution | 4 + .../model_4_4-solution000002.solution | 4 + .../name-reuse/expected/model_4_4.eprime | 21 + .../partition_01/expected/model_2.eprime | 14 - .../partition_01/expected/model_2.eprime.orig | 17 - .../partition_02/expected/model_2.eprime | 4 +- .../partition_02/expected/model_3.eprime | 4 +- .../partition_03/expected/model_2.eprime | 8 - .../expected/model_1-solution000001.solution | 7 + .../expected/model_1.eprime.orig | 48 - .../expected/model_2-solution000001.solution | 7 + .../expected/model_2.eprime.orig | 83 - .../expected/model_3-solution000001.solution | 7 + .../expected/model_3.eprime.orig | 86 - .../expected/model_4-solution000001.solution | 7 + .../expected/model_4.eprime.orig | 40 - .../expected/model_1-solution000001.solution | 7 + .../expected/model_1.eprime.orig | 78 - .../expected/model_2-solution000001.solution | 7 + .../expected/model_2.eprime.orig | 116 - .../expected/model_3-solution000001.solution | 7 + .../expected/model_3.eprime.orig | 119 - .../expected/model_4-solution000001.solution | 7 + .../expected/model_4.eprime.orig | 61 - .../model_1_1-solution000001.solution | 7 + .../model_1_1-solution000002.solution | 7 + .../model_1_1-solution000003.solution | 7 + .../partition_06/expected/model_1_1.eprime | 37 + .../model_1_2-solution000001.solution | 7 + .../model_1_2-solution000002.solution | 7 + .../model_1_2-solution000003.solution | 7 + .../partition_06/expected/model_1_2.eprime | 116 + .../model_1_3-solution000001.solution | 7 + .../model_1_3-solution000002.solution | 7 + .../model_1_3-solution000003.solution | 7 + .../expected/model_1_3.eprime.orig | 126 - .../model_1_4-solution000001.solution | 7 + .../model_1_4-solution000002.solution | 7 + .../model_1_4-solution000003.solution | 7 + .../partition_06/expected/model_1_4.eprime | 85 + .../model_2_1-solution000001.solution | 7 + .../model_2_1-solution000002.solution | 7 + .../model_2_1-solution000003.solution | 7 + .../partition_06/expected/model_2_1.eprime | 117 + .../model_2_2-solution000001.solution | 7 + .../model_2_2-solution000002.solution | 7 + .../model_2_2-solution000003.solution | 7 + .../partition_06/expected/model_2_2.eprime | 60 + .../model_2_3-solution000001.solution | 7 + .../model_2_3-solution000002.solution | 7 + .../model_2_3-solution000003.solution | 7 + .../expected/model_2_3.eprime.orig | 153 - .../model_2_4-solution000001.solution | 7 + .../model_2_4-solution000002.solution | 7 + .../model_2_4-solution000003.solution | 7 + .../partition_06/expected/model_2_4.eprime | 116 + .../model_3_1-solution000001.solution | 7 + .../model_3_1-solution000002.solution | 7 + .../model_3_1-solution000003.solution | 7 + .../expected/model_3_1.eprime.orig | 126 - .../model_3_2-solution000001.solution | 7 + .../model_3_2-solution000002.solution | 7 + .../model_3_2-solution000003.solution | 7 + .../expected/model_3_2.eprime.orig | 152 - .../model_3_3-solution000001.solution | 7 + .../model_3_3-solution000002.solution | 7 + .../model_3_3-solution000003.solution | 7 + .../expected/model_3_3.eprime.orig | 65 - .../model_3_4-solution000001.solution | 7 + .../model_3_4-solution000002.solution | 7 + .../model_3_4-solution000003.solution | 7 + .../expected/model_3_4.eprime.orig | 125 - .../model_4_1-solution000001.solution | 7 + .../model_4_1-solution000002.solution | 7 + .../model_4_1-solution000003.solution | 7 + .../partition_06/expected/model_4_1.eprime | 82 + .../model_4_2-solution000001.solution | 7 + .../model_4_2-solution000002.solution | 7 + .../model_4_2-solution000003.solution | 7 + .../partition_06/expected/model_4_2.eprime | 112 + .../model_4_3-solution000001.solution | 7 + .../model_4_3-solution000002.solution | 7 + .../model_4_3-solution000003.solution | 7 + .../expected/model_4_3.eprime.orig | 123 - .../model_4_4-solution000001.solution | 7 + .../model_4_4-solution000002.solution | 7 + .../model_4_4-solution000003.solution | 7 + .../partition_06/expected/model_4_4.eprime | 32 + .../model_1_1-p-solution000001.solution | 3 + .../model_1_1-p-solution000002.solution | 3 + .../model_1_1-p-solution000003.solution | 3 + .../model_1_1-p-solution000004.solution | 3 + .../model_1_1-p-solution000005.solution | 3 + .../model_1_1-p-solution000006.solution | 3 + .../expected/model_1_1-p.eprime-param | 5 + .../expected/model_1_1.eprime | 20 + .../model_1_2-p-solution000001.solution | 3 + .../model_1_2-p-solution000002.solution | 3 + .../model_1_2-p-solution000003.solution | 3 + .../model_1_2-p-solution000004.solution | 3 + .../model_1_2-p-solution000005.solution | 3 + .../model_1_2-p-solution000006.solution | 3 + .../expected/model_1_2-p.eprime-param | 5 + .../expected/model_1_2.eprime | 32 + .../model_1_3-p-solution000001.solution | 3 + .../model_1_3-p-solution000002.solution | 3 + .../model_1_3-p-solution000003.solution | 3 + .../model_1_3-p-solution000004.solution | 3 + .../model_1_3-p-solution000005.solution | 3 + .../model_1_3-p-solution000006.solution | 3 + .../expected/model_1_3-p.eprime-param | 5 + .../expected/model_1_3.eprime | 34 + .../model_1_4-p-solution000001.solution | 3 + .../model_1_4-p-solution000002.solution | 3 + .../model_1_4-p-solution000003.solution | 3 + .../model_1_4-p-solution000004.solution | 3 + .../model_1_4-p-solution000005.solution | 3 + .../model_1_4-p-solution000006.solution | 3 + .../expected/model_1_4-p.eprime-param | 5 + .../expected/model_1_4.eprime | 36 + .../model_2_1-p-solution000001.solution | 3 + .../model_2_1-p-solution000002.solution | 3 + .../model_2_1-p-solution000003.solution | 3 + .../model_2_1-p-solution000004.solution | 3 + .../model_2_1-p-solution000005.solution | 3 + .../model_2_1-p-solution000006.solution | 3 + .../expected/model_2_1-p.eprime-param | 5 + .../expected/model_2_1.eprime | 33 + .../model_2_2-p-solution000001.solution | 3 + .../model_2_2-p-solution000002.solution | 3 + .../model_2_2-p-solution000003.solution | 3 + .../model_2_2-p-solution000004.solution | 3 + .../model_2_2-p-solution000005.solution | 3 + .../model_2_2-p-solution000006.solution | 3 + .../expected/model_2_2-p.eprime-param | 5 + .../expected/model_2_2.eprime | 26 + .../model_2_3-p-solution000001.solution | 3 + .../model_2_3-p-solution000002.solution | 3 + .../model_2_3-p-solution000003.solution | 3 + .../model_2_3-p-solution000004.solution | 3 + .../model_2_3-p-solution000005.solution | 3 + .../model_2_3-p-solution000006.solution | 3 + .../expected/model_2_3-p.eprime-param | 5 + .../expected/model_2_3.eprime | 44 + .../model_2_4-p-solution000001.solution | 3 + .../model_2_4-p-solution000002.solution | 3 + .../model_2_4-p-solution000003.solution | 3 + .../model_2_4-p-solution000004.solution | 3 + .../model_2_4-p-solution000005.solution | 3 + .../model_2_4-p-solution000006.solution | 3 + .../expected/model_2_4-p.eprime-param | 5 + .../expected/model_2_4.eprime | 46 + .../model_3_1-p-solution000001.solution | 3 + .../model_3_1-p-solution000002.solution | 3 + .../model_3_1-p-solution000003.solution | 3 + .../model_3_1-p-solution000004.solution | 3 + .../model_3_1-p-solution000005.solution | 3 + .../model_3_1-p-solution000006.solution | 3 + .../expected/model_3_1-p.eprime-param | 5 + .../expected/model_3_1.eprime | 36 + .../model_3_2-p-solution000001.solution | 3 + .../model_3_2-p-solution000002.solution | 3 + .../model_3_2-p-solution000003.solution | 3 + .../model_3_2-p-solution000004.solution | 3 + .../model_3_2-p-solution000005.solution | 3 + .../model_3_2-p-solution000006.solution | 3 + .../expected/model_3_2-p.eprime-param | 5 + .../expected/model_3_2.eprime | 44 + .../model_3_3-p-solution000001.solution | 3 + .../model_3_3-p-solution000002.solution | 3 + .../model_3_3-p-solution000003.solution | 3 + .../model_3_3-p-solution000004.solution | 3 + .../model_3_3-p-solution000005.solution | 3 + .../model_3_3-p-solution000006.solution | 3 + .../expected/model_3_3-p.eprime-param | 5 + .../expected/model_3_3.eprime | 28 + .../model_3_4-p-solution000001.solution | 3 + .../model_3_4-p-solution000002.solution | 3 + .../model_3_4-p-solution000003.solution | 3 + .../model_3_4-p-solution000004.solution | 3 + .../model_3_4-p-solution000005.solution | 3 + .../model_3_4-p-solution000006.solution | 3 + .../expected/model_3_4-p.eprime-param | 5 + .../expected/model_3_4.eprime | 50 + .../model_4_1-p-solution000001.solution | 3 + .../model_4_1-p-solution000002.solution | 3 + .../model_4_1-p-solution000003.solution | 3 + .../model_4_1-p-solution000004.solution | 3 + .../model_4_1-p-solution000005.solution | 3 + .../model_4_1-p-solution000006.solution | 3 + .../expected/model_4_1-p.eprime-param | 5 + .../expected/model_4_1.eprime | 38 + .../model_4_2-p-solution000001.solution | 3 + .../model_4_2-p-solution000002.solution | 3 + .../model_4_2-p-solution000003.solution | 3 + .../model_4_2-p-solution000004.solution | 3 + .../model_4_2-p-solution000005.solution | 3 + .../model_4_2-p-solution000006.solution | 3 + .../expected/model_4_2-p.eprime-param | 5 + .../expected/model_4_2.eprime | 46 + .../model_4_3-p-solution000001.solution | 3 + .../model_4_3-p-solution000002.solution | 3 + .../model_4_3-p-solution000003.solution | 3 + .../model_4_3-p-solution000004.solution | 3 + .../model_4_3-p-solution000005.solution | 3 + .../model_4_3-p-solution000006.solution | 3 + .../expected/model_4_3-p.eprime-param | 5 + .../expected/model_4_3.eprime | 50 + .../model_4_4-p-solution000001.solution | 3 + .../model_4_4-p-solution000002.solution | 3 + .../model_4_4-p-solution000003.solution | 3 + .../model_4_4-p-solution000004.solution | 3 + .../model_4_4-p-solution000005.solution | 3 + .../model_4_4-p-solution000006.solution | 3 + .../expected/model_4_4-p.eprime-param | 5 + .../expected/model_4_4.eprime | 30 + .../model_1_1-solution000001.solution | 3 + .../expected/model_1_1.eprime | 8 + .../model_1_2-solution000001.solution | 3 + .../expected/model_1_2.eprime | 17 + .../model_1_3-solution000001.solution | 3 + .../expected/model_1_3.eprime | 20 + .../model_1_4-solution000001.solution | 3 + .../expected/model_1_4.eprime | 20 + .../model_2_1-solution000001.solution | 3 + .../expected/model_2_1.eprime | 19 + .../model_2_2-solution000001.solution | 3 + .../expected/model_2_2.eprime | 13 + .../model_2_3-solution000001.solution | 3 + .../expected/model_2_3.eprime | 30 + .../model_2_4-solution000001.solution | 3 + .../expected/model_2_4.eprime | 31 + .../model_3_1-solution000001.solution | 3 + .../expected/model_3_1.eprime | 22 + .../model_3_2-solution000001.solution | 3 + .../expected/model_3_2.eprime | 30 + .../model_3_3-solution000001.solution | 3 + .../expected/model_3_3.eprime | 15 + .../model_3_4-solution000001.solution | 3 + .../expected/model_3_4.eprime | 35 + .../model_4_1-solution000001.solution | 3 + .../expected/model_4_1.eprime | 23 + .../model_4_2-solution000001.solution | 3 + .../expected/model_4_2.eprime | 31 + .../model_4_3-solution000001.solution | 3 + .../expected/model_4_3.eprime | 35 + .../model_4_4-solution000001.solution | 3 + .../expected/model_4_4.eprime | 16 + .../model_1_1-param4-solution000001.solution | 3 + .../expected/model_1_1-param4.eprime-param | 11 + .../expected/model_1_1.eprime | 70 + .../model_1_2-param4-solution000001.solution | 3 + .../expected/model_1_2-param4.eprime-param | 11 + .../expected/model_1_2.eprime | 152 + .../model_1_3-param4-solution000001.solution | 3 + .../expected/model_1_3-param4.eprime-param | 11 + .../expected/model_1_3.eprime.orig | 176 - .../model_1_4-param4-solution000001.solution | 3 + .../expected/model_1_4-param4.eprime-param | 11 + .../expected/model_1_4.eprime | 184 ++ .../model_2_1-param4-solution000001.solution | 3 + .../expected/model_2_1-param4.eprime-param | 11 + .../expected/model_2_1.eprime | 164 + .../model_2_2-param4-solution000001.solution | 3 + .../expected/model_2_2-param4.eprime-param | 11 + .../expected/model_2_2.eprime | 91 + .../model_2_3-param4-solution000001.solution | 3 + .../expected/model_2_3-param4.eprime-param | 11 + .../expected/model_2_3.eprime.orig | 204 -- .../model_2_4-param4-solution000001.solution | 3 + .../expected/model_2_4-param4.eprime-param | 11 + .../expected/model_2_4.eprime | 211 ++ .../model_3_1-param4-solution000001.solution | 3 + .../expected/model_3_1-param4.eprime-param | 11 + .../expected/model_3_1.eprime.orig | 196 -- .../model_3_2-param4-solution000001.solution | 3 + .../expected/model_3_2-param4.eprime-param | 11 + .../expected/model_3_2.eprime.orig | 211 -- .../model_3_3-param4-solution000001.solution | 3 + .../expected/model_3_3-param4.eprime-param | 11 + .../expected/model_3_3.eprime.orig | 113 - .../model_3_4-param4-solution000001.solution | 3 + .../expected/model_3_4-param4.eprime-param | 11 + .../expected/model_3_4.eprime.orig | 245 -- .../model_4_1-param4-solution000001.solution | 3 + .../expected/model_4_1-param4.eprime-param | 11 + .../expected/model_4_1.eprime | 202 ++ .../model_4_2-param4-solution000001.solution | 3 + .../expected/model_4_2-param4.eprime-param | 11 + ...model_4_3.eprime.orig => model_4_2.eprime} | 239 +- .../model_4_3-param4-solution000001.solution | 3 + .../expected/model_4_3-param4.eprime-param | 11 + .../model_4_4-param4-solution000001.solution | 3 + .../expected/model_4_4-param4.eprime-param | 11 + .../expected/model_4_4.eprime | 121 + .../expected/model_2.eprime | 6 - .../expected/model_2.eprime | 4 - .../expected/model_2.eprime | 8 - .../expected/model_2.eprime | 8 - .../expected/model_4.eprime | 9 - .../expected/model.eprime | 2 +- .../expected/model.eprime | 2 +- .../basic/set01_1/expected/model_2.eprime | 6 - .../basic/set01_2/expected/model_1_2.eprime | 8 - .../basic/set01_2/expected/model_2_1.eprime | 8 - .../basic/set01_2/expected/model_2_2.eprime | 5 - .../basic/set01_3/expected/model_1_2.eprime | 8 - .../basic/set01_3/expected/model_2_1.eprime | 8 - .../basic/set01_3/expected/model_2_2.eprime | 5 - .../basic/set02/expected/model_1_2.eprime | 8 - .../basic/set02/expected/model_2_1.eprime | 8 - .../basic/set02/expected/model_2_2.eprime | 5 - .../model_1_1-solution000001.solution | 3 + .../model_1_1-solution000002.solution | 3 + .../basic/set03/expected/model_1_1.eprime | 8 + .../model_1_2-solution000001.solution | 3 + .../model_1_2-solution000002.solution | 3 + .../basic/set03/expected/model_1_2.eprime | 16 + .../model_1_3-solution000001.solution | 3 + .../model_1_3-solution000002.solution | 3 + .../basic/set03/expected/model_1_3.eprime | 19 + .../model_1_4-solution000001.solution | 3 + .../model_1_4-solution000002.solution | 3 + .../basic/set03/expected/model_1_4.eprime | 18 + .../model_2_1-solution000001.solution | 3 + .../model_2_1-solution000002.solution | 3 + .../basic/set03/expected/model_2_1.eprime | 16 + .../model_2_2-solution000001.solution | 3 + .../model_2_2-solution000002.solution | 3 + .../basic/set03/expected/model_2_2.eprime | 10 + .../model_2_3-solution000001.solution | 3 + .../model_2_3-solution000002.solution | 3 + .../basic/set03/expected/model_2_3.eprime | 26 + .../model_2_4-solution000001.solution | 3 + .../model_2_4-solution000002.solution | 3 + .../basic/set03/expected/model_2_4.eprime | 26 + .../model_3_1-solution000001.solution | 3 + .../model_3_1-solution000002.solution | 3 + .../basic/set03/expected/model_3_1.eprime | 19 + .../model_3_2-solution000001.solution | 3 + .../model_3_2-solution000002.solution | 3 + .../basic/set03/expected/model_3_2.eprime | 26 + .../model_3_3-solution000001.solution | 3 + .../model_3_3-solution000002.solution | 3 + .../basic/set03/expected/model_3_3.eprime | 12 + .../model_3_4-solution000001.solution | 3 + .../model_3_4-solution000002.solution | 3 + .../basic/set03/expected/model_3_4.eprime | 30 + .../model_4_1-solution000001.solution | 3 + .../model_4_1-solution000002.solution | 3 + .../basic/set03/expected/model_4_1.eprime | 19 + .../model_4_2-solution000001.solution | 3 + .../model_4_2-solution000002.solution | 3 + .../basic/set03/expected/model_4_2.eprime | 26 + .../model_4_3-solution000001.solution | 3 + .../model_4_3-solution000002.solution | 3 + .../basic/set03/expected/model_4_3.eprime | 30 + .../model_4_4-solution000001.solution | 3 + .../model_4_4-solution000002.solution | 3 + .../basic/set03/expected/model_4_4.eprime | 12 + .../model_1_1_1-solution000001.solution | 3 + .../model_1_1_1-solution000002.solution | 3 + .../basic/set04/expected/model_1_1_1.eprime | 9 + .../model_1_1_2-solution000001.solution | 3 + .../model_1_1_2-solution000002.solution | 3 + .../expected/model_1_1_2.eprime} | 10 +- .../model_1_1_3-solution000001.solution | 3 + .../model_1_1_3-solution000002.solution | 3 + .../expected/model_1_1_3.eprime} | 11 +- .../model_1_1_4-solution000001.solution | 3 + .../model_1_1_4-solution000002.solution | 3 + .../expected/model_1_1_4.eprime} | 11 +- .../model_1_2_1-solution000001.solution | 3 + .../model_1_2_1-solution000002.solution | 3 + .../basic/set04/expected/model_1_2_1.eprime | 18 + .../model_1_2_3-solution000001.solution | 3 + .../model_1_2_3-solution000002.solution | 3 + .../expected/model_1_2_3.eprime} | 12 +- .../model_1_2_4-solution000001.solution | 3 + .../model_1_2_4-solution000002.solution | 3 + .../expected/model_1_2_4.eprime} | 12 +- .../model_1_3_1-solution000001.solution | 3 + .../model_1_3_1-solution000002.solution | 3 + .../basic/set04/expected/model_1_3_1.eprime | 21 + .../model_1_3_2-solution000001.solution | 3 + .../model_1_3_2-solution000002.solution | 3 + .../expected/model_1_3_2.eprime} | 13 +- .../model_1_3_4-solution000001.solution | 3 + .../model_1_3_4-solution000002.solution | 3 + .../expected/model_1_3_4.eprime} | 12 +- .../model_1_4_1-solution000001.solution | 3 + .../model_1_4_1-solution000002.solution | 3 + .../basic/set04/expected/model_1_4_1.eprime | 21 + .../model_1_4_2-solution000001.solution | 3 + .../model_1_4_2-solution000002.solution | 3 + .../expected/model_1_4_2.eprime} | 13 +- .../model_1_4_3-solution000001.solution | 3 + .../model_1_4_3-solution000002.solution | 3 + .../expected/model_1_4_3.eprime} | 12 +- .../model_2_1_1-solution000001.solution | 3 + .../model_2_1_1-solution000002.solution | 3 + .../expected/model_2_1_1.eprime} | 12 +- .../model_2_1_3-solution000001.solution | 3 + .../model_2_1_3-solution000002.solution | 3 + .../expected/model_2_1_3.eprime} | 14 +- .../model_2_1_4-solution000001.solution | 3 + .../model_2_1_4-solution000002.solution | 3 + .../expected/model_2_1_4.eprime} | 14 +- .../model_2_2_1-solution000001.solution | 3 + .../model_2_2_1-solution000002.solution | 3 + .../expected/model_2_2_1.eprime} | 12 +- .../model_2_2_2-solution000001.solution | 3 + .../model_2_2_2-solution000002.solution | 3 + .../basic/set04/expected/model_2_2_2.eprime | 12 + .../model_2_2_3-solution000001.solution | 3 + .../model_2_2_3-solution000002.solution | 3 + .../expected/model_2_2_3.eprime} | 13 +- .../model_2_2_4-solution000001.solution | 3 + .../model_2_2_4-solution000002.solution | 3 + .../expected/model_2_2_4.eprime} | 13 +- .../model_2_3_1-solution000001.solution | 3 + .../model_2_3_1-solution000002.solution | 3 + .../expected/model_2_3_1.eprime} | 35 +- .../model_2_3_2-solution000001.solution | 3 + .../model_2_3_2-solution000002.solution | 3 + .../expected/model_2_3_2.eprime} | 14 +- .../model_2_3_4-solution000001.solution | 3 + .../model_2_3_4-solution000002.solution | 3 + .../expected/model_2_3_4.eprime} | 14 +- .../model_2_4_1-solution000001.solution | 3 + .../model_2_4_1-solution000002.solution | 3 + .../expected/model_2_4_1.eprime} | 15 +- .../model_2_4_2-solution000001.solution | 3 + .../model_2_4_2-solution000002.solution | 3 + .../expected/model_2_4_2.eprime} | 14 +- .../model_2_4_3-solution000001.solution | 3 + .../model_2_4_3-solution000002.solution | 3 + .../expected/model_2_4_3.eprime} | 14 +- .../model_3_1_1-solution000001.solution | 3 + .../model_3_1_1-solution000002.solution | 3 + .../expected/model_3_1_1.eprime} | 12 +- .../model_3_1_2-solution000001.solution | 3 + .../model_3_1_2-solution000002.solution | 3 + .../expected/model_3_1_2.eprime} | 14 +- .../model_3_1_4-solution000001.solution | 3 + .../model_3_1_4-solution000002.solution | 3 + .../expected/model_3_1_4.eprime} | 15 +- .../model_3_2_1-solution000001.solution | 3 + .../model_3_2_1-solution000002.solution | 3 + .../expected/model_3_2_1.eprime} | 34 +- .../model_3_2_2-solution000001.solution | 3 + .../model_3_2_2-solution000002.solution | 3 + .../expected/model_3_2_2.eprime} | 13 +- .../model_3_2_4-solution000001.solution | 3 + .../model_3_2_4-solution000002.solution | 3 + .../expected/model_3_2_4.eprime} | 15 +- .../model_3_3_1-solution000001.solution | 3 + .../model_3_3_1-solution000002.solution | 3 + .../expected/model_3_3_1.eprime} | 12 +- .../model_3_3_2-solution000001.solution | 3 + .../model_3_3_2-solution000002.solution | 3 + .../expected/model_3_3_2.eprime} | 13 +- .../model_3_3_3-solution000001.solution | 3 + .../model_3_3_3-solution000002.solution | 3 + .../basic/set04/expected/model_3_3_3.eprime | 14 + .../model_3_3_4-solution000001.solution | 3 + .../model_3_3_4-solution000002.solution | 3 + .../expected/model_3_3_4.eprime} | 15 +- .../model_3_4_1-solution000001.solution | 3 + .../model_3_4_1-solution000002.solution | 3 + .../expected/model_3_4_1.eprime} | 14 +- .../model_3_4_2-solution000001.solution | 3 + .../model_3_4_2-solution000002.solution | 3 + .../expected/model_3_4_2.eprime} | 14 +- .../model_3_4_3-solution000001.solution | 3 + .../model_3_4_3-solution000002.solution | 3 + .../expected/model_3_4_3.eprime} | 15 +- .../model_4_1_1-solution000001.solution | 3 + .../model_4_1_1-solution000002.solution | 3 + .../expected/model_4_1_1.eprime} | 12 +- .../model_4_1_2-solution000001.solution | 3 + .../model_4_1_2-solution000002.solution | 3 + .../expected/model_4_1_2.eprime} | 14 +- .../model_4_1_3-solution000001.solution | 3 + .../model_4_1_3-solution000002.solution | 3 + .../expected/model_4_1_3.eprime} | 15 +- .../model_4_2_1-solution000001.solution | 3 + .../model_4_2_1-solution000002.solution | 3 + .../expected/model_4_2_1.eprime} | 14 +- .../model_4_2_2-solution000001.solution | 3 + .../model_4_2_2-solution000002.solution | 3 + .../expected/model_4_2_2.eprime} | 13 +- .../model_4_2_3-solution000001.solution | 3 + .../model_4_2_3-solution000002.solution | 3 + .../expected/model_4_2_3.eprime} | 15 +- .../model_4_3_1-solution000001.solution | 3 + .../model_4_3_1-solution000002.solution | 3 + .../expected/model_4_3_1.eprime} | 14 +- .../model_4_3_2-solution000001.solution | 3 + .../model_4_3_2-solution000002.solution | 3 + .../expected/model_4_3_2.eprime} | 14 +- .../model_4_3_3-solution000001.solution | 3 + .../model_4_3_3-solution000002.solution | 3 + .../expected/model_4_3_3.eprime} | 15 +- .../model_4_4_1-solution000001.solution | 3 + .../model_4_4_1-solution000002.solution | 3 + .../expected/model_4_4_1.eprime} | 12 +- .../model_4_4_2-solution000001.solution | 3 + .../model_4_4_2-solution000002.solution | 3 + .../expected/model_4_4_2.eprime} | 13 +- .../model_4_4_3-solution000001.solution | 3 + .../model_4_4_3-solution000002.solution | 3 + .../expected/model_4_4_3.eprime} | 15 +- .../model_4_4_4-solution000001.solution | 3 + .../model_4_4_4-solution000002.solution | 3 + .../expected/model_4_4_4.eprime} | 14 +- .../model_1_1_1-solution000001.solution | 3 + .../model_1_1_1-solution000002.solution | 3 + .../model_1_1_1-solution000003.solution | 3 + .../basic/set05/expected/model_1_1_1.eprime | 9 + .../model_1_1_2-solution000001.solution | 3 + .../model_1_1_2-solution000002.solution | 3 + .../model_1_1_2-solution000003.solution | 3 + .../basic/set05/expected/model_1_1_2.eprime | 18 + .../model_1_1_3-solution000001.solution | 3 + .../model_1_1_3-solution000002.solution | 3 + .../model_1_1_3-solution000003.solution | 3 + .../basic/set05/expected/model_1_1_3.eprime | 21 + .../model_1_1_4-solution000001.solution | 3 + .../model_1_1_4-solution000002.solution | 3 + .../model_1_1_4-solution000003.solution | 3 + .../basic/set05/expected/model_1_1_4.eprime | 21 + .../model_1_2_1-solution000001.solution | 3 + .../model_1_2_1-solution000002.solution | 3 + .../model_1_2_1-solution000003.solution | 3 + .../basic/set05/expected/model_1_2_1.eprime | 18 + .../model_1_2_3-solution000001.solution | 3 + .../model_1_2_3-solution000002.solution | 3 + .../model_1_2_3-solution000003.solution | 3 + .../basic/set05/expected/model_1_2_3.eprime | 42 + .../model_1_2_4-solution000001.solution | 3 + .../model_1_2_4-solution000002.solution | 3 + .../model_1_2_4-solution000003.solution | 3 + .../basic/set05/expected/model_1_2_4.eprime | 43 + .../model_1_3_1-solution000001.solution | 3 + .../model_1_3_1-solution000002.solution | 3 + .../model_1_3_1-solution000003.solution | 3 + .../basic/set05/expected/model_1_3_1.eprime | 21 + .../model_1_3_2-solution000001.solution | 3 + .../model_1_3_2-solution000002.solution | 3 + .../model_1_3_2-solution000003.solution | 3 + .../basic/set05/expected/model_1_3_2.eprime | 41 + .../model_1_3_4-solution000001.solution | 3 + .../model_1_3_4-solution000002.solution | 3 + .../model_1_3_4-solution000003.solution | 3 + .../basic/set05/expected/model_1_3_4.eprime | 47 + .../model_1_4_1-solution000001.solution | 3 + .../model_1_4_1-solution000002.solution | 3 + .../model_1_4_1-solution000003.solution | 3 + .../basic/set05/expected/model_1_4_1.eprime | 21 + .../model_1_4_2-solution000001.solution | 3 + .../model_1_4_2-solution000002.solution | 3 + .../model_1_4_2-solution000003.solution | 3 + .../basic/set05/expected/model_1_4_2.eprime | 41 + .../model_1_4_3-solution000001.solution | 3 + .../model_1_4_3-solution000002.solution | 3 + .../model_1_4_3-solution000003.solution | 3 + .../basic/set05/expected/model_1_4_3.eprime | 46 + .../model_2_1_1-solution000001.solution | 3 + .../model_2_1_1-solution000002.solution | 3 + .../model_2_1_1-solution000003.solution | 3 + .../basic/set05/expected/model_2_1_1.eprime | 18 + .../model_2_1_3-solution000001.solution | 3 + .../model_2_1_3-solution000002.solution | 3 + .../model_2_1_3-solution000003.solution | 3 + .../basic/set05/expected/model_2_1_3.eprime | 42 + .../model_2_1_4-solution000001.solution | 3 + .../model_2_1_4-solution000002.solution | 3 + .../model_2_1_4-solution000003.solution | 3 + .../basic/set05/expected/model_2_1_4.eprime | 42 + .../model_2_2_1-solution000001.solution | 3 + .../model_2_2_1-solution000002.solution | 3 + .../model_2_2_1-solution000003.solution | 3 + .../basic/set05/expected/model_2_2_1.eprime | 18 + .../model_2_2_2-solution000001.solution | 3 + .../model_2_2_2-solution000002.solution | 3 + .../model_2_2_2-solution000003.solution | 3 + .../basic/set05/expected/model_2_2_2.eprime | 12 + .../model_2_2_3-solution000001.solution | 3 + .../model_2_2_3-solution000002.solution | 3 + .../model_2_2_3-solution000003.solution | 3 + .../expected/model_2_2_3.eprime} | 26 +- .../model_2_2_4-solution000001.solution | 3 + .../model_2_2_4-solution000002.solution | 3 + .../model_2_2_4-solution000003.solution | 3 + .../expected/model_2_2_4.eprime} | 26 +- .../model_2_3_1-solution000001.solution | 3 + .../model_2_3_1-solution000002.solution | 3 + .../model_2_3_1-solution000003.solution | 3 + .../basic/set05/expected/model_2_3_1.eprime | 42 + .../model_2_3_2-solution000001.solution | 3 + .../model_2_3_2-solution000002.solution | 3 + .../model_2_3_2-solution000003.solution | 3 + .../basic/set05/expected/model_2_3_2.eprime | 29 + .../model_2_3_4-solution000001.solution | 3 + .../model_2_3_4-solution000002.solution | 3 + .../model_2_3_4-solution000003.solution | 3 + .../basic/set05/expected/model_2_3_4.eprime | 60 + .../model_2_4_1-solution000001.solution | 3 + .../model_2_4_1-solution000002.solution | 3 + .../model_2_4_1-solution000003.solution | 3 + .../basic/set05/expected/model_2_4_1.eprime | 42 + .../model_2_4_2-solution000001.solution | 3 + .../model_2_4_2-solution000002.solution | 3 + .../model_2_4_2-solution000003.solution | 3 + .../basic/set05/expected/model_2_4_2.eprime | 30 + .../model_2_4_3-solution000001.solution | 3 + .../model_2_4_3-solution000002.solution | 3 + .../model_2_4_3-solution000003.solution | 3 + .../basic/set05/expected/model_2_4_3.eprime | 59 + .../model_3_1_1-solution000001.solution | 3 + .../model_3_1_1-solution000002.solution | 3 + .../model_3_1_1-solution000003.solution | 3 + .../basic/set05/expected/model_3_1_1.eprime | 21 + .../model_3_1_2-solution000001.solution | 3 + .../model_3_1_2-solution000002.solution | 3 + .../model_3_1_2-solution000003.solution | 3 + .../basic/set05/expected/model_3_1_2.eprime | 42 + .../model_3_1_4-solution000001.solution | 3 + .../model_3_1_4-solution000002.solution | 3 + .../model_3_1_4-solution000003.solution | 3 + .../basic/set05/expected/model_3_1_4.eprime | 47 + .../model_3_2_1-solution000001.solution | 3 + .../model_3_2_1-solution000002.solution | 3 + .../model_3_2_1-solution000003.solution | 3 + .../basic/set05/expected/model_3_2_1.eprime | 42 + .../model_3_2_2-solution000001.solution | 3 + .../model_3_2_2-solution000002.solution | 3 + .../model_3_2_2-solution000003.solution | 3 + .../expected/model_3_2_2.eprime} | 26 +- .../model_3_2_4-solution000001.solution | 3 + .../model_3_2_4-solution000002.solution | 3 + .../model_3_2_4-solution000003.solution | 3 + .../basic/set05/expected/model_3_2_4.eprime | 60 + .../model_3_3_1-solution000001.solution | 3 + .../model_3_3_1-solution000002.solution | 3 + .../model_3_3_1-solution000003.solution | 3 + .../basic/set05/expected/model_3_3_1.eprime | 21 + .../model_3_3_2-solution000001.solution | 3 + .../model_3_3_2-solution000002.solution | 3 + .../model_3_3_2-solution000003.solution | 3 + .../basic/set05/expected/model_3_3_2.eprime | 29 + .../model_3_3_3-solution000001.solution | 3 + .../model_3_3_3-solution000002.solution | 3 + .../model_3_3_3-solution000003.solution | 3 + .../basic/set05/expected/model_3_3_3.eprime | 14 + .../model_3_3_4-solution000001.solution | 3 + .../model_3_3_4-solution000002.solution | 3 + .../model_3_3_4-solution000003.solution | 3 + .../expected/model_3_3_4.eprime} | 19 +- .../model_3_4_1-solution000001.solution | 3 + .../model_3_4_1-solution000002.solution | 3 + .../model_3_4_1-solution000003.solution | 3 + .../basic/set05/expected/model_3_4_1.eprime | 47 + .../model_3_4_2-solution000001.solution | 3 + .../model_3_4_2-solution000002.solution | 3 + .../model_3_4_2-solution000003.solution | 3 + .../basic/set05/expected/model_3_4_2.eprime | 59 + .../model_3_4_3-solution000001.solution | 3 + .../model_3_4_3-solution000002.solution | 3 + .../model_3_4_3-solution000003.solution | 3 + .../basic/set05/expected/model_3_4_3.eprime | 34 + .../model_4_1_1-solution000001.solution | 3 + .../model_4_1_1-solution000002.solution | 3 + .../model_4_1_1-solution000003.solution | 3 + .../expected/model_4_1_1.eprime} | 19 +- .../model_4_1_2-solution000001.solution | 3 + .../model_4_1_2-solution000002.solution | 3 + .../model_4_1_2-solution000003.solution | 3 + .../basic/set05/expected/model_4_1_2.eprime | 42 + .../model_4_1_3-solution000001.solution | 3 + .../model_4_1_3-solution000002.solution | 3 + .../model_4_1_3-solution000003.solution | 3 + .../basic/set05/expected/model_4_1_3.eprime | 47 + .../model_4_2_1-solution000001.solution | 3 + .../model_4_2_1-solution000002.solution | 3 + .../model_4_2_1-solution000003.solution | 3 + .../basic/set05/expected/model_4_2_1.eprime | 42 + .../model_4_2_2-solution000001.solution | 3 + .../model_4_2_2-solution000002.solution | 3 + .../model_4_2_2-solution000003.solution | 3 + .../expected/model_4_2_2.eprime} | 26 +- .../model_4_2_3-solution000001.solution | 3 + .../model_4_2_3-solution000002.solution | 3 + .../model_4_2_3-solution000003.solution | 3 + .../basic/set05/expected/model_4_2_3.eprime | 59 + .../model_4_3_1-solution000001.solution | 3 + .../model_4_3_1-solution000002.solution | 3 + .../model_4_3_1-solution000003.solution | 3 + .../basic/set05/expected/model_4_3_1.eprime | 47 + .../model_4_3_2-solution000001.solution | 3 + .../model_4_3_2-solution000002.solution | 3 + .../model_4_3_2-solution000003.solution | 3 + .../basic/set05/expected/model_4_3_2.eprime | 59 + .../model_4_3_3-solution000001.solution | 3 + .../model_4_3_3-solution000002.solution | 3 + .../model_4_3_3-solution000003.solution | 3 + .../expected/model_4_3_3.eprime} | 19 +- .../model_4_4_1-solution000001.solution | 3 + .../model_4_4_1-solution000002.solution | 3 + .../model_4_4_1-solution000003.solution | 3 + .../basic/set05/expected/model_4_4_1.eprime | 22 + .../model_4_4_2-solution000001.solution | 3 + .../model_4_4_2-solution000002.solution | 3 + .../model_4_4_2-solution000003.solution | 3 + .../basic/set05/expected/model_4_4_2.eprime | 30 + .../model_4_4_3-solution000001.solution | 3 + .../model_4_4_3-solution000002.solution | 3 + .../model_4_4_3-solution000003.solution | 3 + .../basic/set05/expected/model_4_4_3.eprime | 34 + .../model_4_4_4-solution000001.solution | 3 + .../model_4_4_4-solution000002.solution | 3 + .../model_4_4_4-solution000003.solution | 3 + .../basic/set05/expected/model_4_4_4.eprime | 15 + .../model_1_1_1_1-solution000001.solution | 3 + .../model_1_1_1_1-solution000002.solution | 3 + .../basic/set06/expected/model_1_1_1_1.eprime | 10 + .../model_1_1_1_2-solution000001.solution | 3 + .../model_1_1_1_2-solution000002.solution | 3 + .../basic/set06/expected/model_1_1_1_2.eprime | 19 + .../model_1_1_1_3-solution000001.solution | 3 + .../model_1_1_1_3-solution000002.solution | 3 + .../basic/set06/expected/model_1_1_1_3.eprime | 22 + .../model_1_1_1_4-solution000001.solution | 3 + .../model_1_1_1_4-solution000002.solution | 3 + .../basic/set06/expected/model_1_1_1_4.eprime | 22 + .../model_1_1_2_1-solution000001.solution | 3 + .../model_1_1_2_1-solution000002.solution | 3 + .../basic/set06/expected/model_1_1_2_1.eprime | 19 + .../model_1_1_2_3-solution000001.solution | 3 + .../model_1_1_2_3-solution000002.solution | 3 + .../basic/set06/expected/model_1_1_2_3.eprime | 43 + .../model_1_1_2_4-solution000001.solution | 3 + .../model_1_1_2_4-solution000002.solution | 3 + .../basic/set06/expected/model_1_1_2_4.eprime | 44 + .../model_1_1_3_1-solution000001.solution | 3 + .../model_1_1_3_1-solution000002.solution | 3 + .../basic/set06/expected/model_1_1_3_1.eprime | 22 + .../model_1_1_3_2-solution000001.solution | 3 + .../model_1_1_3_2-solution000002.solution | 3 + .../basic/set06/expected/model_1_1_3_2.eprime | 42 + .../model_1_1_3_4-solution000001.solution | 3 + .../model_1_1_3_4-solution000002.solution | 3 + .../basic/set06/expected/model_1_1_3_4.eprime | 48 + .../model_1_1_4_1-solution000001.solution | 3 + .../model_1_1_4_1-solution000002.solution | 3 + .../basic/set06/expected/model_1_1_4_1.eprime | 22 + .../model_1_1_4_2-solution000001.solution | 3 + .../model_1_1_4_2-solution000002.solution | 3 + .../basic/set06/expected/model_1_1_4_2.eprime | 42 + .../model_1_1_4_3-solution000001.solution | 3 + .../model_1_1_4_3-solution000002.solution | 3 + .../basic/set06/expected/model_1_1_4_3.eprime | 47 + .../model_1_2_1_1-solution000001.solution | 3 + .../model_1_2_1_1-solution000002.solution | 3 + .../basic/set06/expected/model_1_2_1_1.eprime | 19 + .../model_1_2_1_3-solution000001.solution | 3 + .../model_1_2_1_3-solution000002.solution | 3 + .../basic/set06/expected/model_1_2_1_3.eprime | 43 + .../model_1_2_1_4-solution000001.solution | 3 + .../model_1_2_1_4-solution000002.solution | 3 + .../basic/set06/expected/model_1_2_1_4.eprime | 44 + .../model_1_2_2_1-solution000001.solution | 3 + .../model_1_2_2_1-solution000002.solution | 3 + .../basic/set06/expected/model_1_2_2_1.eprime | 19 + .../model_1_2_2_3-solution000001.solution | 3 + .../model_1_2_2_3-solution000002.solution | 3 + .../basic/set06/expected/model_1_2_2_3.eprime | 43 + .../model_1_2_2_4-solution000001.solution | 3 + .../model_1_2_2_4-solution000002.solution | 3 + .../basic/set06/expected/model_1_2_2_4.eprime | 44 + .../model_1_2_3_1-solution000001.solution | 3 + .../model_1_2_3_1-solution000002.solution | 3 + .../basic/set06/expected/model_1_2_3_1.eprime | 43 + .../model_1_2_3_4-solution000001.solution | 3 + .../model_1_2_3_4-solution000002.solution | 3 + .../basic/set06/expected/model_1_2_3_4.eprime | 78 + .../model_1_2_4_1-solution000001.solution | 3 + .../model_1_2_4_1-solution000002.solution | 3 + .../basic/set06/expected/model_1_2_4_1.eprime | 44 + .../model_1_2_4_3-solution000001.solution | 3 + .../model_1_2_4_3-solution000002.solution | 3 + .../basic/set06/expected/model_1_2_4_3.eprime | 78 + .../model_1_3_1_1-solution000001.solution | 3 + .../model_1_3_1_1-solution000002.solution | 3 + .../basic/set06/expected/model_1_3_1_1.eprime | 22 + .../model_1_3_1_2-solution000001.solution | 3 + .../model_1_3_1_2-solution000002.solution | 3 + .../basic/set06/expected/model_1_3_1_2.eprime | 42 + .../model_1_3_1_4-solution000001.solution | 3 + .../model_1_3_1_4-solution000002.solution | 3 + .../basic/set06/expected/model_1_3_1_4.eprime | 48 + .../model_1_3_2_1-solution000001.solution | 3 + .../model_1_3_2_1-solution000002.solution | 3 + .../basic/set06/expected/model_1_3_2_1.eprime | 42 + .../model_1_3_2_4-solution000001.solution | 3 + .../model_1_3_2_4-solution000002.solution | 3 + .../basic/set06/expected/model_1_3_2_4.eprime | 77 + .../model_1_3_3_1-solution000001.solution | 3 + .../model_1_3_3_1-solution000002.solution | 3 + .../basic/set06/expected/model_1_3_3_1.eprime | 22 + .../model_1_3_3_2-solution000001.solution | 3 + .../model_1_3_3_2-solution000002.solution | 3 + .../basic/set06/expected/model_1_3_3_2.eprime | 42 + .../model_1_3_3_4-solution000001.solution | 3 + .../model_1_3_3_4-solution000002.solution | 3 + .../basic/set06/expected/model_1_3_3_4.eprime | 48 + .../model_1_3_4_1-solution000001.solution | 3 + .../model_1_3_4_1-solution000002.solution | 3 + .../basic/set06/expected/model_1_3_4_1.eprime | 48 + .../model_1_3_4_2-solution000001.solution | 3 + .../model_1_3_4_2-solution000002.solution | 3 + .../basic/set06/expected/model_1_3_4_2.eprime | 77 + .../model_1_4_1_1-solution000001.solution | 3 + .../model_1_4_1_1-solution000002.solution | 3 + .../basic/set06/expected/model_1_4_1_1.eprime | 22 + .../model_1_4_1_2-solution000001.solution | 3 + .../model_1_4_1_2-solution000002.solution | 3 + .../basic/set06/expected/model_1_4_1_2.eprime | 42 + .../model_1_4_1_3-solution000001.solution | 3 + .../model_1_4_1_3-solution000002.solution | 3 + .../basic/set06/expected/model_1_4_1_3.eprime | 47 + .../model_1_4_2_1-solution000001.solution | 3 + .../model_1_4_2_1-solution000002.solution | 3 + .../basic/set06/expected/model_1_4_2_1.eprime | 42 + .../model_1_4_2_3-solution000001.solution | 3 + .../model_1_4_2_3-solution000002.solution | 3 + .../basic/set06/expected/model_1_4_2_3.eprime | 76 + .../model_1_4_3_1-solution000001.solution | 3 + .../model_1_4_3_1-solution000002.solution | 3 + .../basic/set06/expected/model_1_4_3_1.eprime | 47 + .../model_1_4_3_2-solution000001.solution | 3 + .../model_1_4_3_2-solution000002.solution | 3 + .../basic/set06/expected/model_1_4_3_2.eprime | 76 + .../model_1_4_4_1-solution000001.solution | 3 + .../model_1_4_4_1-solution000002.solution | 3 + .../basic/set06/expected/model_1_4_4_1.eprime | 22 + .../model_1_4_4_2-solution000001.solution | 3 + .../model_1_4_4_2-solution000002.solution | 3 + .../basic/set06/expected/model_1_4_4_2.eprime | 42 + .../model_1_4_4_3-solution000001.solution | 3 + .../model_1_4_4_3-solution000002.solution | 3 + .../basic/set06/expected/model_1_4_4_3.eprime | 47 + .../model_2_1_1_1-solution000001.solution | 3 + .../model_2_1_1_1-solution000002.solution | 3 + .../basic/set06/expected/model_2_1_1_1.eprime | 19 + .../model_2_1_1_3-solution000001.solution | 3 + .../model_2_1_1_3-solution000002.solution | 3 + .../basic/set06/expected/model_2_1_1_3.eprime | 43 + .../model_2_1_1_4-solution000001.solution | 3 + .../model_2_1_1_4-solution000002.solution | 3 + .../basic/set06/expected/model_2_1_1_4.eprime | 43 + .../model_2_1_2_1-solution000001.solution | 3 + .../model_2_1_2_1-solution000002.solution | 3 + .../basic/set06/expected/model_2_1_2_1.eprime | 19 + .../model_2_1_2_3-solution000001.solution | 3 + .../model_2_1_2_3-solution000002.solution | 3 + .../basic/set06/expected/model_2_1_2_3.eprime | 43 + .../model_2_1_2_4-solution000001.solution | 3 + .../model_2_1_2_4-solution000002.solution | 3 + .../basic/set06/expected/model_2_1_2_4.eprime | 43 + .../model_2_1_3_1-solution000001.solution | 3 + .../model_2_1_3_1-solution000002.solution | 3 + .../basic/set06/expected/model_2_1_3_1.eprime | 43 + .../model_2_1_3_4-solution000001.solution | 3 + .../model_2_1_3_4-solution000002.solution | 3 + .../basic/set06/expected/model_2_1_3_4.eprime | 78 + .../model_2_1_4_1-solution000001.solution | 3 + .../model_2_1_4_1-solution000002.solution | 3 + .../basic/set06/expected/model_2_1_4_1.eprime | 43 + .../model_2_1_4_3-solution000001.solution | 3 + .../model_2_1_4_3-solution000002.solution | 3 + .../basic/set06/expected/model_2_1_4_3.eprime | 77 + .../model_2_2_1_1-solution000001.solution | 3 + .../model_2_2_1_1-solution000002.solution | 3 + .../basic/set06/expected/model_2_2_1_1.eprime | 19 + .../model_2_2_1_3-solution000001.solution | 3 + .../model_2_2_1_3-solution000002.solution | 3 + .../basic/set06/expected/model_2_2_1_3.eprime | 43 + .../model_2_2_1_4-solution000001.solution | 3 + .../model_2_2_1_4-solution000002.solution | 3 + .../basic/set06/expected/model_2_2_1_4.eprime | 43 + .../model_2_2_2_1-solution000001.solution | 3 + .../model_2_2_2_1-solution000002.solution | 3 + .../basic/set06/expected/model_2_2_2_1.eprime | 19 + .../model_2_2_2_2-solution000001.solution | 3 + .../model_2_2_2_2-solution000002.solution | 3 + .../basic/set06/expected/model_2_2_2_2.eprime | 13 + .../model_2_2_2_3-solution000001.solution | 3 + .../model_2_2_2_3-solution000002.solution | 3 + .../basic/set06/expected/model_2_2_2_3.eprime | 30 + .../model_2_2_2_4-solution000001.solution | 3 + .../model_2_2_2_4-solution000002.solution | 3 + .../basic/set06/expected/model_2_2_2_4.eprime | 31 + .../model_2_2_3_1-solution000001.solution | 3 + .../model_2_2_3_1-solution000002.solution | 3 + .../basic/set06/expected/model_2_2_3_1.eprime | 43 + .../model_2_2_3_2-solution000001.solution | 3 + .../model_2_2_3_2-solution000002.solution | 3 + .../basic/set06/expected/model_2_2_3_2.eprime | 30 + .../model_2_2_3_4-solution000001.solution | 3 + .../model_2_2_3_4-solution000002.solution | 3 + .../basic/set06/expected/model_2_2_3_4.eprime | 61 + .../model_2_2_4_1-solution000001.solution | 3 + .../model_2_2_4_1-solution000002.solution | 3 + .../basic/set06/expected/model_2_2_4_1.eprime | 43 + .../model_2_2_4_2-solution000001.solution | 3 + .../model_2_2_4_2-solution000002.solution | 3 + .../basic/set06/expected/model_2_2_4_2.eprime | 31 + .../model_2_2_4_3-solution000001.solution | 3 + .../model_2_2_4_3-solution000002.solution | 3 + .../basic/set06/expected/model_2_2_4_3.eprime | 60 + .../model_2_3_1_1-solution000001.solution | 3 + .../model_2_3_1_1-solution000002.solution | 3 + .../basic/set06/expected/model_2_3_1_1.eprime | 43 + .../model_2_3_1_4-solution000001.solution | 3 + .../model_2_3_1_4-solution000002.solution | 3 + .../basic/set06/expected/model_2_3_1_4.eprime | 78 + .../model_2_3_2_1-solution000001.solution | 3 + .../model_2_3_2_1-solution000002.solution | 3 + .../basic/set06/expected/model_2_3_2_1.eprime | 43 + .../model_2_3_2_2-solution000001.solution | 3 + .../model_2_3_2_2-solution000002.solution | 3 + .../basic/set06/expected/model_2_3_2_2.eprime | 30 + .../model_2_3_2_4-solution000001.solution | 3 + .../model_2_3_2_4-solution000002.solution | 3 + .../basic/set06/expected/model_2_3_2_4.eprime | 61 + .../model_2_3_3_1-solution000001.solution | 3 + .../model_2_3_3_1-solution000002.solution | 3 + .../basic/set06/expected/model_2_3_3_1.eprime | 43 + .../model_2_3_3_2-solution000001.solution | 3 + .../model_2_3_3_2-solution000002.solution | 3 + .../basic/set06/expected/model_2_3_3_2.eprime | 30 + .../model_2_3_3_4-solution000001.solution | 3 + .../model_2_3_3_4-solution000002.solution | 3 + .../basic/set06/expected/model_2_3_3_4.eprime | 61 + .../model_2_3_4_1-solution000001.solution | 3 + .../model_2_3_4_1-solution000002.solution | 3 + .../basic/set06/expected/model_2_3_4_1.eprime | 78 + .../model_2_3_4_2-solution000001.solution | 3 + .../model_2_3_4_2-solution000002.solution | 3 + .../basic/set06/expected/model_2_3_4_2.eprime | 61 + .../model_2_4_1_1-solution000001.solution | 3 + .../model_2_4_1_1-solution000002.solution | 3 + .../basic/set06/expected/model_2_4_1_1.eprime | 43 + .../model_2_4_1_3-solution000001.solution | 3 + .../model_2_4_1_3-solution000002.solution | 3 + .../basic/set06/expected/model_2_4_1_3.eprime | 77 + .../model_2_4_2_1-solution000001.solution | 3 + .../model_2_4_2_1-solution000002.solution | 3 + .../basic/set06/expected/model_2_4_2_1.eprime | 43 + .../model_2_4_2_2-solution000001.solution | 3 + .../model_2_4_2_2-solution000002.solution | 3 + .../basic/set06/expected/model_2_4_2_2.eprime | 31 + .../model_2_4_2_3-solution000001.solution | 3 + .../model_2_4_2_3-solution000002.solution | 3 + .../basic/set06/expected/model_2_4_2_3.eprime | 60 + .../model_2_4_3_1-solution000001.solution | 3 + .../model_2_4_3_1-solution000002.solution | 3 + .../basic/set06/expected/model_2_4_3_1.eprime | 77 + .../model_2_4_3_2-solution000001.solution | 3 + .../model_2_4_3_2-solution000002.solution | 3 + .../basic/set06/expected/model_2_4_3_2.eprime | 60 + .../model_2_4_4_1-solution000001.solution | 3 + .../model_2_4_4_1-solution000002.solution | 3 + .../basic/set06/expected/model_2_4_4_1.eprime | 43 + .../model_2_4_4_2-solution000001.solution | 3 + .../model_2_4_4_2-solution000002.solution | 3 + .../basic/set06/expected/model_2_4_4_2.eprime | 31 + .../model_2_4_4_3-solution000001.solution | 3 + .../model_2_4_4_3-solution000002.solution | 3 + .../basic/set06/expected/model_2_4_4_3.eprime | 60 + .../model_3_1_1_1-solution000001.solution | 3 + .../model_3_1_1_1-solution000002.solution | 3 + .../basic/set06/expected/model_3_1_1_1.eprime | 22 + .../model_3_1_1_2-solution000001.solution | 3 + .../model_3_1_1_2-solution000002.solution | 3 + .../basic/set06/expected/model_3_1_1_2.eprime | 43 + .../model_3_1_1_4-solution000001.solution | 3 + .../model_3_1_1_4-solution000002.solution | 3 + .../basic/set06/expected/model_3_1_1_4.eprime | 48 + .../model_3_1_2_1-solution000001.solution | 3 + .../model_3_1_2_1-solution000002.solution | 3 + .../basic/set06/expected/model_3_1_2_1.eprime | 43 + .../model_3_1_2_4-solution000001.solution | 3 + .../model_3_1_2_4-solution000002.solution | 3 + .../basic/set06/expected/model_3_1_2_4.eprime | 78 + .../model_3_1_3_1-solution000001.solution | 3 + .../model_3_1_3_1-solution000002.solution | 3 + .../basic/set06/expected/model_3_1_3_1.eprime | 22 + .../model_3_1_3_2-solution000001.solution | 3 + .../model_3_1_3_2-solution000002.solution | 3 + .../basic/set06/expected/model_3_1_3_2.eprime | 43 + .../model_3_1_3_4-solution000001.solution | 3 + .../model_3_1_3_4-solution000002.solution | 3 + .../basic/set06/expected/model_3_1_3_4.eprime | 48 + .../model_3_1_4_1-solution000001.solution | 3 + .../model_3_1_4_1-solution000002.solution | 3 + .../basic/set06/expected/model_3_1_4_1.eprime | 48 + .../model_3_1_4_2-solution000001.solution | 3 + .../model_3_1_4_2-solution000002.solution | 3 + .../basic/set06/expected/model_3_1_4_2.eprime | 77 + .../model_3_2_1_1-solution000001.solution | 3 + .../model_3_2_1_1-solution000002.solution | 3 + .../basic/set06/expected/model_3_2_1_1.eprime | 43 + .../model_3_2_1_4-solution000001.solution | 3 + .../model_3_2_1_4-solution000002.solution | 3 + .../basic/set06/expected/model_3_2_1_4.eprime | 78 + .../model_3_2_2_1-solution000001.solution | 3 + .../model_3_2_2_1-solution000002.solution | 3 + .../basic/set06/expected/model_3_2_2_1.eprime | 43 + .../model_3_2_2_2-solution000001.solution | 3 + .../model_3_2_2_2-solution000002.solution | 3 + .../basic/set06/expected/model_3_2_2_2.eprime | 30 + .../model_3_2_2_4-solution000001.solution | 3 + .../model_3_2_2_4-solution000002.solution | 3 + .../basic/set06/expected/model_3_2_2_4.eprime | 61 + .../model_3_2_3_1-solution000001.solution | 3 + .../model_3_2_3_1-solution000002.solution | 3 + .../basic/set06/expected/model_3_2_3_1.eprime | 43 + .../model_3_2_3_2-solution000001.solution | 3 + .../model_3_2_3_2-solution000002.solution | 3 + .../basic/set06/expected/model_3_2_3_2.eprime | 30 + .../model_3_2_3_4-solution000001.solution | 3 + .../model_3_2_3_4-solution000002.solution | 3 + .../basic/set06/expected/model_3_2_3_4.eprime | 61 + .../model_3_2_4_1-solution000001.solution | 3 + .../model_3_2_4_1-solution000002.solution | 3 + .../basic/set06/expected/model_3_2_4_1.eprime | 78 + .../model_3_2_4_2-solution000001.solution | 3 + .../model_3_2_4_2-solution000002.solution | 3 + .../basic/set06/expected/model_3_2_4_2.eprime | 61 + .../model_3_3_1_1-solution000001.solution | 3 + .../model_3_3_1_1-solution000002.solution | 3 + .../basic/set06/expected/model_3_3_1_1.eprime | 22 + .../model_3_3_1_2-solution000001.solution | 3 + .../model_3_3_1_2-solution000002.solution | 3 + .../basic/set06/expected/model_3_3_1_2.eprime | 43 + .../model_3_3_1_4-solution000001.solution | 3 + .../model_3_3_1_4-solution000002.solution | 3 + .../basic/set06/expected/model_3_3_1_4.eprime | 48 + .../model_3_3_2_1-solution000001.solution | 3 + .../model_3_3_2_1-solution000002.solution | 3 + .../basic/set06/expected/model_3_3_2_1.eprime | 43 + .../model_3_3_2_2-solution000001.solution | 3 + .../model_3_3_2_2-solution000002.solution | 3 + .../basic/set06/expected/model_3_3_2_2.eprime | 30 + .../model_3_3_2_4-solution000001.solution | 3 + .../model_3_3_2_4-solution000002.solution | 3 + .../basic/set06/expected/model_3_3_2_4.eprime | 61 + .../model_3_3_3_1-solution000001.solution | 3 + .../model_3_3_3_1-solution000002.solution | 3 + .../basic/set06/expected/model_3_3_3_1.eprime | 22 + .../model_3_3_3_2-solution000001.solution | 3 + .../model_3_3_3_2-solution000002.solution | 3 + .../basic/set06/expected/model_3_3_3_2.eprime | 30 + .../model_3_3_3_3-solution000001.solution | 3 + .../model_3_3_3_3-solution000002.solution | 3 + .../basic/set06/expected/model_3_3_3_3.eprime | 15 + .../model_3_3_3_4-solution000001.solution | 3 + .../model_3_3_3_4-solution000002.solution | 3 + .../basic/set06/expected/model_3_3_3_4.eprime | 35 + .../model_3_3_4_1-solution000001.solution | 3 + .../model_3_3_4_1-solution000002.solution | 3 + .../basic/set06/expected/model_3_3_4_1.eprime | 48 + .../model_3_3_4_2-solution000001.solution | 3 + .../model_3_3_4_2-solution000002.solution | 3 + .../basic/set06/expected/model_3_3_4_2.eprime | 60 + .../model_3_3_4_3-solution000001.solution | 3 + .../model_3_3_4_3-solution000002.solution | 3 + .../basic/set06/expected/model_3_3_4_3.eprime | 35 + .../model_3_4_1_1-solution000001.solution | 3 + .../model_3_4_1_1-solution000002.solution | 3 + .../basic/set06/expected/model_3_4_1_1.eprime | 48 + .../model_3_4_1_2-solution000001.solution | 3 + .../model_3_4_1_2-solution000002.solution | 3 + .../basic/set06/expected/model_3_4_1_2.eprime | 77 + .../model_3_4_2_1-solution000001.solution | 3 + .../model_3_4_2_1-solution000002.solution | 3 + .../basic/set06/expected/model_3_4_2_1.eprime | 77 + .../model_3_4_2_2-solution000001.solution | 3 + .../model_3_4_2_2-solution000002.solution | 3 + .../basic/set06/expected/model_3_4_2_2.eprime | 60 + .../model_3_4_3_1-solution000001.solution | 3 + .../model_3_4_3_1-solution000002.solution | 3 + .../basic/set06/expected/model_3_4_3_1.eprime | 48 + .../model_3_4_3_2-solution000001.solution | 3 + .../model_3_4_3_2-solution000002.solution | 3 + .../basic/set06/expected/model_3_4_3_2.eprime | 60 + .../model_3_4_3_3-solution000001.solution | 3 + .../model_3_4_3_3-solution000002.solution | 3 + .../basic/set06/expected/model_3_4_3_3.eprime | 35 + .../model_3_4_4_1-solution000001.solution | 3 + .../model_3_4_4_1-solution000002.solution | 3 + .../basic/set06/expected/model_3_4_4_1.eprime | 48 + .../model_3_4_4_2-solution000001.solution | 3 + .../model_3_4_4_2-solution000002.solution | 3 + .../basic/set06/expected/model_3_4_4_2.eprime | 60 + .../model_3_4_4_3-solution000001.solution | 3 + .../model_3_4_4_3-solution000002.solution | 3 + .../basic/set06/expected/model_3_4_4_3.eprime | 35 + .../model_4_1_1_1-solution000001.solution | 3 + .../model_4_1_1_1-solution000002.solution | 3 + .../basic/set06/expected/model_4_1_1_1.eprime | 23 + .../model_4_1_1_2-solution000001.solution | 3 + .../model_4_1_1_2-solution000002.solution | 3 + .../basic/set06/expected/model_4_1_1_2.eprime | 43 + .../model_4_1_1_3-solution000001.solution | 3 + .../model_4_1_1_3-solution000002.solution | 3 + .../basic/set06/expected/model_4_1_1_3.eprime | 48 + .../model_4_1_2_1-solution000001.solution | 3 + .../model_4_1_2_1-solution000002.solution | 3 + .../basic/set06/expected/model_4_1_2_1.eprime | 43 + .../model_4_1_2_3-solution000001.solution | 3 + .../model_4_1_2_3-solution000002.solution | 3 + .../basic/set06/expected/model_4_1_2_3.eprime | 77 + .../model_4_1_3_1-solution000001.solution | 3 + .../model_4_1_3_1-solution000002.solution | 3 + .../basic/set06/expected/model_4_1_3_1.eprime | 48 + .../model_4_1_3_2-solution000001.solution | 3 + .../model_4_1_3_2-solution000002.solution | 3 + .../basic/set06/expected/model_4_1_3_2.eprime | 77 + .../model_4_1_4_1-solution000001.solution | 3 + .../model_4_1_4_1-solution000002.solution | 3 + .../basic/set06/expected/model_4_1_4_1.eprime | 23 + .../model_4_1_4_2-solution000001.solution | 3 + .../model_4_1_4_2-solution000002.solution | 3 + .../basic/set06/expected/model_4_1_4_2.eprime | 43 + .../model_4_1_4_3-solution000001.solution | 3 + .../model_4_1_4_3-solution000002.solution | 3 + .../basic/set06/expected/model_4_1_4_3.eprime | 48 + .../model_4_2_1_1-solution000001.solution | 3 + .../model_4_2_1_1-solution000002.solution | 3 + .../basic/set06/expected/model_4_2_1_1.eprime | 43 + .../model_4_2_1_3-solution000001.solution | 3 + .../model_4_2_1_3-solution000002.solution | 3 + .../basic/set06/expected/model_4_2_1_3.eprime | 77 + .../model_4_2_2_1-solution000001.solution | 3 + .../model_4_2_2_1-solution000002.solution | 3 + .../basic/set06/expected/model_4_2_2_1.eprime | 43 + .../model_4_2_2_2-solution000001.solution | 3 + .../model_4_2_2_2-solution000002.solution | 3 + .../basic/set06/expected/model_4_2_2_2.eprime | 31 + .../model_4_2_2_3-solution000001.solution | 3 + .../model_4_2_2_3-solution000002.solution | 3 + .../basic/set06/expected/model_4_2_2_3.eprime | 60 + .../model_4_2_3_1-solution000001.solution | 3 + .../model_4_2_3_1-solution000002.solution | 3 + .../basic/set06/expected/model_4_2_3_1.eprime | 77 + .../model_4_2_3_2-solution000001.solution | 3 + .../model_4_2_3_2-solution000002.solution | 3 + .../basic/set06/expected/model_4_2_3_2.eprime | 60 + .../model_4_2_4_1-solution000001.solution | 3 + .../model_4_2_4_1-solution000002.solution | 3 + .../basic/set06/expected/model_4_2_4_1.eprime | 43 + .../model_4_2_4_2-solution000001.solution | 3 + .../model_4_2_4_2-solution000002.solution | 3 + .../basic/set06/expected/model_4_2_4_2.eprime | 31 + .../model_4_2_4_3-solution000001.solution | 3 + .../model_4_2_4_3-solution000002.solution | 3 + .../basic/set06/expected/model_4_2_4_3.eprime | 60 + .../model_4_3_1_1-solution000001.solution | 3 + .../model_4_3_1_1-solution000002.solution | 3 + .../basic/set06/expected/model_4_3_1_1.eprime | 48 + .../model_4_3_1_2-solution000001.solution | 3 + .../model_4_3_1_2-solution000002.solution | 3 + .../basic/set06/expected/model_4_3_1_2.eprime | 77 + .../model_4_3_2_1-solution000001.solution | 3 + .../model_4_3_2_1-solution000002.solution | 3 + .../basic/set06/expected/model_4_3_2_1.eprime | 77 + .../model_4_3_2_2-solution000001.solution | 3 + .../model_4_3_2_2-solution000002.solution | 3 + .../basic/set06/expected/model_4_3_2_2.eprime | 60 + .../model_4_3_3_1-solution000001.solution | 3 + .../model_4_3_3_1-solution000002.solution | 3 + .../basic/set06/expected/model_4_3_3_1.eprime | 48 + .../model_4_3_3_2-solution000001.solution | 3 + .../model_4_3_3_2-solution000002.solution | 3 + .../basic/set06/expected/model_4_3_3_2.eprime | 60 + .../model_4_3_3_3-solution000001.solution | 3 + .../model_4_3_3_3-solution000002.solution | 3 + .../basic/set06/expected/model_4_3_3_3.eprime | 35 + .../model_4_3_4_1-solution000001.solution | 3 + .../model_4_3_4_1-solution000002.solution | 3 + .../basic/set06/expected/model_4_3_4_1.eprime | 48 + .../model_4_3_4_2-solution000001.solution | 3 + .../model_4_3_4_2-solution000002.solution | 3 + .../basic/set06/expected/model_4_3_4_2.eprime | 60 + .../model_4_3_4_3-solution000001.solution | 3 + .../model_4_3_4_3-solution000002.solution | 3 + .../basic/set06/expected/model_4_3_4_3.eprime | 35 + .../model_4_4_1_1-solution000001.solution | 3 + .../model_4_4_1_1-solution000002.solution | 3 + .../basic/set06/expected/model_4_4_1_1.eprime | 23 + .../model_4_4_1_2-solution000001.solution | 3 + .../model_4_4_1_2-solution000002.solution | 3 + .../basic/set06/expected/model_4_4_1_2.eprime | 43 + .../model_4_4_1_3-solution000001.solution | 3 + .../model_4_4_1_3-solution000002.solution | 3 + .../basic/set06/expected/model_4_4_1_3.eprime | 48 + .../model_4_4_2_1-solution000001.solution | 3 + .../model_4_4_2_1-solution000002.solution | 3 + .../basic/set06/expected/model_4_4_2_1.eprime | 43 + .../model_4_4_2_2-solution000001.solution | 3 + .../model_4_4_2_2-solution000002.solution | 3 + .../basic/set06/expected/model_4_4_2_2.eprime | 31 + .../model_4_4_2_3-solution000001.solution | 3 + .../model_4_4_2_3-solution000002.solution | 3 + .../basic/set06/expected/model_4_4_2_3.eprime | 60 + .../model_4_4_3_1-solution000001.solution | 3 + .../model_4_4_3_1-solution000002.solution | 3 + .../basic/set06/expected/model_4_4_3_1.eprime | 48 + .../model_4_4_3_2-solution000001.solution | 3 + .../model_4_4_3_2-solution000002.solution | 3 + .../basic/set06/expected/model_4_4_3_2.eprime | 60 + .../model_4_4_3_3-solution000001.solution | 3 + .../model_4_4_3_3-solution000002.solution | 3 + .../basic/set06/expected/model_4_4_3_3.eprime | 35 + .../model_4_4_4_1-solution000001.solution | 3 + .../model_4_4_4_1-solution000002.solution | 3 + .../basic/set06/expected/model_4_4_4_1.eprime | 23 + .../model_4_4_4_2-solution000001.solution | 3 + .../model_4_4_4_2-solution000002.solution | 3 + .../basic/set06/expected/model_4_4_4_2.eprime | 31 + .../model_4_4_4_3-solution000001.solution | 3 + .../model_4_4_4_3-solution000002.solution | 3 + .../basic/set06/expected/model_4_4_4_3.eprime | 35 + .../model_4_4_4_4-solution000001.solution | 3 + .../model_4_4_4_4-solution000002.solution | 3 + .../basic/set06/expected/model_4_4_4_4.eprime | 16 + .../model_1_1_1-solution000001.solution | 3 + .../basic/set07/expected/model_1_1_1.eprime | 6 + .../model_1_1_2-solution000001.solution | 3 + .../basic/set07/expected/model_1_1_2.eprime | 15 + .../model_1_1_3-solution000001.solution | 3 + .../basic/set07/expected/model_1_1_3.eprime | 18 + .../model_1_1_4-solution000001.solution | 3 + .../basic/set07/expected/model_1_1_4.eprime | 18 + .../model_1_2_1-solution000001.solution | 3 + .../basic/set07/expected/model_1_2_1.eprime | 17 + .../model_1_2_3-solution000001.solution | 3 + .../basic/set07/expected/model_1_2_3.eprime | 40 + .../model_1_2_4-solution000001.solution | 3 + .../basic/set07/expected/model_1_2_4.eprime | 41 + .../model_1_3_1-solution000001.solution | 3 + .../basic/set07/expected/model_1_3_1.eprime | 21 + .../model_1_3_2-solution000001.solution | 3 + .../basic/set07/expected/model_1_3_2.eprime | 40 + .../model_1_3_4-solution000001.solution | 3 + .../basic/set07/expected/model_1_3_4.eprime | 46 + .../model_1_4_1-solution000001.solution | 3 + .../basic/set07/expected/model_1_4_1.eprime | 21 + .../model_1_4_2-solution000001.solution | 3 + .../basic/set07/expected/model_1_4_2.eprime | 40 + .../model_1_4_3-solution000001.solution | 3 + .../basic/set07/expected/model_1_4_3.eprime | 45 + .../model_2_1_1-solution000001.solution | 3 + .../basic/set07/expected/model_2_1_1.eprime | 17 + .../model_2_1_3-solution000001.solution | 3 + .../basic/set07/expected/model_2_1_3.eprime | 40 + .../model_2_1_4-solution000001.solution | 3 + .../basic/set07/expected/model_2_1_4.eprime | 40 + .../model_2_2_1-solution000001.solution | 3 + .../basic/set07/expected/model_2_2_1.eprime | 17 + .../model_2_2_2-solution000001.solution | 3 + .../basic/set07/expected/model_2_2_2.eprime | 12 + .../model_2_2_3-solution000001.solution | 3 + .../basic/set07/expected/model_2_2_3.eprime | 28 + .../model_2_2_4-solution000001.solution | 3 + .../basic/set07/expected/model_2_2_4.eprime | 29 + .../model_2_3_1-solution000001.solution | 3 + .../basic/set07/expected/model_2_3_1.eprime | 41 + .../model_2_3_2-solution000001.solution | 3 + .../basic/set07/expected/model_2_3_2.eprime | 29 + .../model_2_3_4-solution000001.solution | 3 + .../basic/set07/expected/model_2_3_4.eprime | 59 + .../model_2_4_1-solution000001.solution | 3 + .../basic/set07/expected/model_2_4_1.eprime | 41 + .../model_2_4_2-solution000001.solution | 3 + .../basic/set07/expected/model_2_4_2.eprime | 30 + .../model_2_4_3-solution000001.solution | 3 + .../basic/set07/expected/model_2_4_3.eprime | 58 + .../model_3_1_1-solution000001.solution | 3 + .../basic/set07/expected/model_3_1_1.eprime | 22 + .../model_3_1_2-solution000001.solution | 3 + .../basic/set07/expected/model_3_1_2.eprime | 41 + .../model_3_1_4-solution000001.solution | 3 + .../basic/set07/expected/model_3_1_4.eprime | 46 + .../model_3_2_1-solution000001.solution | 3 + .../basic/set07/expected/model_3_2_1.eprime | 41 + .../model_3_2_2-solution000001.solution | 3 + .../basic/set07/expected/model_3_2_2.eprime | 29 + .../model_3_2_4-solution000001.solution | 3 + .../basic/set07/expected/model_3_2_4.eprime | 59 + .../model_3_3_1-solution000001.solution | 3 + .../basic/set07/expected/model_3_3_1.eprime | 24 + .../model_3_3_2-solution000001.solution | 3 + .../basic/set07/expected/model_3_3_2.eprime | 31 + .../model_3_3_3-solution000001.solution | 3 + .../basic/set07/expected/model_3_3_3.eprime | 17 + .../model_3_3_4-solution000001.solution | 3 + .../basic/set07/expected/model_3_3_4.eprime | 36 + .../model_3_4_1-solution000001.solution | 3 + .../basic/set07/expected/model_3_4_1.eprime | 48 + .../model_3_4_2-solution000001.solution | 3 + .../basic/set07/expected/model_3_4_2.eprime | 60 + .../model_3_4_3-solution000001.solution | 3 + .../basic/set07/expected/model_3_4_3.eprime | 36 + .../model_4_1_1-solution000001.solution | 3 + .../basic/set07/expected/model_4_1_1.eprime | 21 + .../model_4_1_2-solution000001.solution | 3 + .../basic/set07/expected/model_4_1_2.eprime | 40 + .../model_4_1_3-solution000001.solution | 3 + .../basic/set07/expected/model_4_1_3.eprime | 45 + .../model_4_2_1-solution000001.solution | 3 + .../basic/set07/expected/model_4_2_1.eprime | 40 + .../model_4_2_2-solution000001.solution | 3 + .../basic/set07/expected/model_4_2_2.eprime | 29 + .../model_4_2_3-solution000001.solution | 3 + .../basic/set07/expected/model_4_2_3.eprime | 57 + .../model_4_3_1-solution000001.solution | 3 + .../basic/set07/expected/model_4_3_1.eprime | 47 + .../model_4_3_2-solution000001.solution | 3 + .../basic/set07/expected/model_4_3_2.eprime | 59 + .../model_4_3_3-solution000001.solution | 3 + .../basic/set07/expected/model_4_3_3.eprime | 35 + .../model_4_4_1-solution000001.solution | 3 + .../basic/set07/expected/model_4_4_1.eprime | 23 + .../model_4_4_2-solution000001.solution | 3 + .../basic/set07/expected/model_4_4_2.eprime | 31 + .../model_4_4_3-solution000001.solution | 3 + .../basic/set07/expected/model_4_4_3.eprime | 35 + .../model_4_4_4-solution000001.solution | 3 + .../basic/set07/expected/model_4_4_4.eprime | 15 + .../model_1_1-solution000001.solution | 7 + .../basic/set08/expected/model_1_1.eprime | 25 + .../model_1_2-solution000001.solution | 7 + .../basic/set08/expected/model_1_2.eprime | 54 + .../model_2_1-solution000001.solution | 7 + .../basic/set08/expected/model_2_1.eprime | 54 + .../model_2_2-solution000001.solution | 7 + .../basic/set08/expected/model_2_2.eprime | 25 + .../model_1_1_1_1-solution000001.solution | 4 + .../model_1_1_1_1-solution000002.solution | 4 + .../basic/set09/expected/model_1_1_1_1.eprime | 10 + .../model_1_1_1_2-solution000001.solution | 4 + .../model_1_1_1_2-solution000002.solution | 4 + .../basic/set09/expected/model_1_1_1_2.eprime | 19 + .../model_1_1_1_3-solution000001.solution | 4 + .../model_1_1_1_3-solution000002.solution | 4 + .../basic/set09/expected/model_1_1_1_3.eprime | 23 + .../model_1_1_1_4-solution000001.solution | 4 + .../model_1_1_1_4-solution000002.solution | 4 + .../basic/set09/expected/model_1_1_1_4.eprime | 22 + .../model_1_1_2_1-solution000001.solution | 4 + .../model_1_1_2_1-solution000002.solution | 4 + .../basic/set09/expected/model_1_1_2_1.eprime | 19 + .../model_1_1_2_2-solution000001.solution | 4 + .../model_1_1_2_2-solution000002.solution | 4 + .../basic/set09/expected/model_1_1_2_2.eprime | 28 + .../model_1_1_2_3-solution000001.solution | 4 + .../model_1_1_2_3-solution000002.solution | 4 + .../basic/set09/expected/model_1_1_2_3.eprime | 34 + .../model_1_1_2_4-solution000001.solution | 4 + .../model_1_1_2_4-solution000002.solution | 4 + .../basic/set09/expected/model_1_1_2_4.eprime | 35 + .../model_1_1_3_1-solution000001.solution | 4 + .../model_1_1_3_1-solution000002.solution | 4 + .../basic/set09/expected/model_1_1_3_1.eprime | 23 + .../model_1_1_3_2-solution000001.solution | 4 + .../model_1_1_3_2-solution000002.solution | 4 + .../basic/set09/expected/model_1_1_3_2.eprime | 34 + .../model_1_1_3_3-solution000001.solution | 4 + .../model_1_1_3_3-solution000002.solution | 4 + .../basic/set09/expected/model_1_1_3_3.eprime | 38 + .../model_1_1_3_4-solution000001.solution | 4 + .../model_1_1_3_4-solution000002.solution | 4 + .../basic/set09/expected/model_1_1_3_4.eprime | 39 + .../model_1_1_4_1-solution000001.solution | 4 + .../model_1_1_4_1-solution000002.solution | 4 + .../basic/set09/expected/model_1_1_4_1.eprime | 22 + .../model_1_1_4_2-solution000001.solution | 4 + .../model_1_1_4_2-solution000002.solution | 4 + .../basic/set09/expected/model_1_1_4_2.eprime | 33 + .../model_1_1_4_3-solution000001.solution | 4 + .../model_1_1_4_3-solution000002.solution | 4 + .../basic/set09/expected/model_1_1_4_3.eprime | 37 + .../model_1_1_4_4-solution000001.solution | 4 + .../model_1_1_4_4-solution000002.solution | 4 + .../basic/set09/expected/model_1_1_4_4.eprime | 38 + .../model_1_2_1_1-solution000001.solution | 4 + .../model_1_2_1_1-solution000002.solution | 4 + .../basic/set09/expected/model_1_2_1_1.eprime | 20 + .../model_1_2_1_2-solution000001.solution | 4 + .../model_1_2_1_2-solution000002.solution | 4 + .../basic/set09/expected/model_1_2_1_2.eprime | 14 + .../model_1_2_1_3-solution000001.solution | 4 + .../model_1_2_1_3-solution000002.solution | 4 + .../basic/set09/expected/model_1_2_1_3.eprime | 32 + .../model_1_2_1_4-solution000001.solution | 4 + .../model_1_2_1_4-solution000002.solution | 4 + .../basic/set09/expected/model_1_2_1_4.eprime | 33 + .../model_1_2_2_1-solution000001.solution | 4 + .../model_1_2_2_1-solution000002.solution | 4 + .../basic/set09/expected/model_1_2_2_1.eprime | 29 + .../model_1_2_2_2-solution000001.solution | 4 + .../model_1_2_2_2-solution000002.solution | 4 + .../basic/set09/expected/model_1_2_2_2.eprime | 23 + .../model_1_2_2_3-solution000001.solution | 4 + .../model_1_2_2_3-solution000002.solution | 4 + .../basic/set09/expected/model_1_2_2_3.eprime | 42 + .../model_1_2_2_4-solution000001.solution | 4 + .../model_1_2_2_4-solution000002.solution | 4 + .../basic/set09/expected/model_1_2_2_4.eprime | 44 + .../model_1_2_3_1-solution000001.solution | 4 + .../model_1_2_3_1-solution000002.solution | 4 + .../basic/set09/expected/model_1_2_3_1.eprime | 35 + .../model_1_2_3_2-solution000001.solution | 4 + .../model_1_2_3_2-solution000002.solution | 4 + .../basic/set09/expected/model_1_2_3_2.eprime | 28 + .../model_1_2_3_3-solution000001.solution | 4 + .../model_1_2_3_3-solution000002.solution | 4 + .../basic/set09/expected/model_1_2_3_3.eprime | 46 + .../model_1_2_3_4-solution000001.solution | 4 + .../model_1_2_3_4-solution000002.solution | 4 + .../basic/set09/expected/model_1_2_3_4.eprime | 48 + .../model_1_2_4_1-solution000001.solution | 4 + .../model_1_2_4_1-solution000002.solution | 4 + .../basic/set09/expected/model_1_2_4_1.eprime | 35 + .../model_1_2_4_2-solution000001.solution | 4 + .../model_1_2_4_2-solution000002.solution | 4 + .../basic/set09/expected/model_1_2_4_2.eprime | 28 + .../model_1_2_4_3-solution000001.solution | 4 + .../model_1_2_4_3-solution000002.solution | 4 + .../basic/set09/expected/model_1_2_4_3.eprime | 46 + .../model_1_2_4_4-solution000001.solution | 4 + .../model_1_2_4_4-solution000002.solution | 4 + .../basic/set09/expected/model_1_2_4_4.eprime | 48 + .../model_1_3_1_1-solution000001.solution | 4 + .../model_1_3_1_1-solution000002.solution | 4 + .../basic/set09/expected/model_1_3_1_1.eprime | 23 + .../model_1_3_1_2-solution000001.solution | 4 + .../model_1_3_1_2-solution000002.solution | 4 + .../basic/set09/expected/model_1_3_1_2.eprime | 32 + .../model_1_3_1_3-solution000001.solution | 4 + .../model_1_3_1_3-solution000002.solution | 4 + .../basic/set09/expected/model_1_3_1_3.eprime | 16 + .../model_1_3_1_4-solution000001.solution | 4 + .../model_1_3_1_4-solution000002.solution | 4 + .../basic/set09/expected/model_1_3_1_4.eprime | 36 + .../model_1_3_2_1-solution000001.solution | 4 + .../model_1_3_2_1-solution000002.solution | 4 + .../basic/set09/expected/model_1_3_2_1.eprime | 35 + .../model_1_3_2_2-solution000001.solution | 4 + .../model_1_3_2_2-solution000002.solution | 4 + .../basic/set09/expected/model_1_3_2_2.eprime | 42 + .../model_1_3_2_3-solution000001.solution | 4 + .../model_1_3_2_3-solution000002.solution | 4 + .../basic/set09/expected/model_1_3_2_3.eprime | 26 + .../model_1_3_2_4-solution000001.solution | 4 + .../model_1_3_2_4-solution000002.solution | 4 + .../basic/set09/expected/model_1_3_2_4.eprime | 46 + .../model_1_3_3_1-solution000001.solution | 4 + .../model_1_3_3_1-solution000002.solution | 4 + .../basic/set09/expected/model_1_3_3_1.eprime | 39 + .../model_1_3_3_2-solution000001.solution | 4 + .../model_1_3_3_2-solution000002.solution | 4 + .../basic/set09/expected/model_1_3_3_2.eprime | 46 + .../model_1_3_3_3-solution000001.solution | 4 + .../model_1_3_3_3-solution000002.solution | 4 + .../basic/set09/expected/model_1_3_3_3.eprime | 31 + .../model_1_3_3_4-solution000001.solution | 4 + .../model_1_3_3_4-solution000002.solution | 4 + .../basic/set09/expected/model_1_3_3_4.eprime | 51 + .../model_1_3_4_1-solution000001.solution | 4 + .../model_1_3_4_1-solution000002.solution | 4 + .../basic/set09/expected/model_1_3_4_1.eprime | 39 + .../model_1_3_4_2-solution000001.solution | 4 + .../model_1_3_4_2-solution000002.solution | 4 + .../basic/set09/expected/model_1_3_4_2.eprime | 46 + .../model_1_3_4_3-solution000001.solution | 4 + .../model_1_3_4_3-solution000002.solution | 4 + .../basic/set09/expected/model_1_3_4_3.eprime | 31 + .../model_1_3_4_4-solution000001.solution | 4 + .../model_1_3_4_4-solution000002.solution | 4 + .../basic/set09/expected/model_1_3_4_4.eprime | 51 + .../model_1_4_1_1-solution000001.solution | 4 + .../model_1_4_1_1-solution000002.solution | 4 + .../basic/set09/expected/model_1_4_1_1.eprime | 24 + .../model_1_4_1_2-solution000001.solution | 4 + .../model_1_4_1_2-solution000002.solution | 4 + .../basic/set09/expected/model_1_4_1_2.eprime | 33 + .../model_1_4_1_3-solution000001.solution | 4 + .../model_1_4_1_3-solution000002.solution | 4 + .../basic/set09/expected/model_1_4_1_3.eprime | 36 + .../model_1_4_1_4-solution000001.solution | 4 + .../model_1_4_1_4-solution000002.solution | 4 + .../basic/set09/expected/model_1_4_1_4.eprime | 17 + .../model_1_4_2_1-solution000001.solution | 4 + .../model_1_4_2_1-solution000002.solution | 4 + .../basic/set09/expected/model_1_4_2_1.eprime | 35 + .../model_1_4_2_2-solution000001.solution | 4 + .../model_1_4_2_2-solution000002.solution | 4 + .../basic/set09/expected/model_1_4_2_2.eprime | 43 + .../model_1_4_2_3-solution000001.solution | 4 + .../model_1_4_2_3-solution000002.solution | 4 + .../basic/set09/expected/model_1_4_2_3.eprime | 45 + .../model_1_4_2_4-solution000001.solution | 4 + .../model_1_4_2_4-solution000002.solution | 4 + .../basic/set09/expected/model_1_4_2_4.eprime | 27 + .../model_1_4_3_1-solution000001.solution | 4 + .../model_1_4_3_1-solution000002.solution | 4 + .../basic/set09/expected/model_1_4_3_1.eprime | 39 + .../model_1_4_3_2-solution000001.solution | 4 + .../model_1_4_3_2-solution000002.solution | 4 + .../basic/set09/expected/model_1_4_3_2.eprime | 47 + .../model_1_4_3_3-solution000001.solution | 4 + .../model_1_4_3_3-solution000002.solution | 4 + .../basic/set09/expected/model_1_4_3_3.eprime | 50 + .../model_1_4_3_4-solution000001.solution | 4 + .../model_1_4_3_4-solution000002.solution | 4 + .../basic/set09/expected/model_1_4_3_4.eprime | 32 + .../model_1_4_4_1-solution000001.solution | 4 + .../model_1_4_4_1-solution000002.solution | 4 + .../basic/set09/expected/model_1_4_4_1.eprime | 39 + .../model_1_4_4_2-solution000001.solution | 4 + .../model_1_4_4_2-solution000002.solution | 4 + .../basic/set09/expected/model_1_4_4_2.eprime | 47 + .../model_1_4_4_3-solution000001.solution | 4 + .../model_1_4_4_3-solution000002.solution | 4 + .../basic/set09/expected/model_1_4_4_3.eprime | 50 + .../model_1_4_4_4-solution000001.solution | 4 + .../model_1_4_4_4-solution000002.solution | 4 + .../basic/set09/expected/model_1_4_4_4.eprime | 32 + .../model_2_1_1_1-solution000001.solution | 4 + .../model_2_1_1_1-solution000002.solution | 4 + .../basic/set09/expected/model_2_1_1_1.eprime | 20 + .../model_2_1_1_2-solution000001.solution | 4 + .../model_2_1_1_2-solution000002.solution | 4 + .../basic/set09/expected/model_2_1_1_2.eprime | 29 + .../model_2_1_1_3-solution000001.solution | 4 + .../model_2_1_1_3-solution000002.solution | 4 + .../basic/set09/expected/model_2_1_1_3.eprime | 35 + .../model_2_1_1_4-solution000001.solution | 4 + .../model_2_1_1_4-solution000002.solution | 4 + .../basic/set09/expected/model_2_1_1_4.eprime | 35 + .../model_2_1_2_1-solution000001.solution | 4 + .../model_2_1_2_1-solution000002.solution | 4 + .../basic/set09/expected/model_2_1_2_1.eprime | 14 + .../model_2_1_2_2-solution000001.solution | 4 + .../model_2_1_2_2-solution000002.solution | 4 + .../basic/set09/expected/model_2_1_2_2.eprime | 23 + .../model_2_1_2_3-solution000001.solution | 4 + .../model_2_1_2_3-solution000002.solution | 4 + .../basic/set09/expected/model_2_1_2_3.eprime | 28 + .../model_2_1_2_4-solution000001.solution | 4 + .../model_2_1_2_4-solution000002.solution | 4 + .../basic/set09/expected/model_2_1_2_4.eprime | 28 + .../model_2_1_3_1-solution000001.solution | 4 + .../model_2_1_3_1-solution000002.solution | 4 + .../basic/set09/expected/model_2_1_3_1.eprime | 32 + .../model_2_1_3_2-solution000001.solution | 4 + .../model_2_1_3_2-solution000002.solution | 4 + .../basic/set09/expected/model_2_1_3_2.eprime | 42 + .../model_2_1_3_3-solution000001.solution | 4 + .../model_2_1_3_3-solution000002.solution | 4 + .../basic/set09/expected/model_2_1_3_3.eprime | 46 + .../model_2_1_3_4-solution000001.solution | 4 + .../model_2_1_3_4-solution000002.solution | 4 + .../basic/set09/expected/model_2_1_3_4.eprime | 47 + .../model_2_1_4_1-solution000001.solution | 4 + .../model_2_1_4_1-solution000002.solution | 4 + .../basic/set09/expected/model_2_1_4_1.eprime | 33 + .../model_2_1_4_2-solution000001.solution | 4 + .../model_2_1_4_2-solution000002.solution | 4 + .../basic/set09/expected/model_2_1_4_2.eprime | 43 + .../model_2_1_4_3-solution000001.solution | 4 + .../model_2_1_4_3-solution000002.solution | 4 + .../basic/set09/expected/model_2_1_4_3.eprime | 47 + .../model_2_1_4_4-solution000001.solution | 4 + .../model_2_1_4_4-solution000002.solution | 4 + .../basic/set09/expected/model_2_1_4_4.eprime | 48 + .../model_2_2_1_1-solution000001.solution | 4 + .../model_2_2_1_1-solution000002.solution | 4 + .../basic/set09/expected/model_2_2_1_1.eprime | 30 + .../model_2_2_1_2-solution000001.solution | 4 + .../model_2_2_1_2-solution000002.solution | 4 + .../basic/set09/expected/model_2_2_1_2.eprime | 24 + .../model_2_2_1_3-solution000001.solution | 4 + .../model_2_2_1_3-solution000002.solution | 4 + .../basic/set09/expected/model_2_2_1_3.eprime | 43 + .../model_2_2_1_4-solution000001.solution | 4 + .../model_2_2_1_4-solution000002.solution | 4 + .../basic/set09/expected/model_2_2_1_4.eprime | 45 + .../model_2_2_2_1-solution000001.solution | 4 + .../model_2_2_2_1-solution000002.solution | 4 + .../basic/set09/expected/model_2_2_2_1.eprime | 24 + .../model_2_2_2_2-solution000001.solution | 4 + .../model_2_2_2_2-solution000002.solution | 4 + .../basic/set09/expected/model_2_2_2_2.eprime | 18 + .../model_2_2_2_3-solution000001.solution | 4 + .../model_2_2_2_3-solution000002.solution | 4 + .../basic/set09/expected/model_2_2_2_3.eprime | 37 + .../model_2_2_2_4-solution000001.solution | 4 + .../model_2_2_2_4-solution000002.solution | 4 + .../basic/set09/expected/model_2_2_2_4.eprime | 39 + .../model_2_2_3_1-solution000001.solution | 4 + .../model_2_2_3_1-solution000002.solution | 4 + .../basic/set09/expected/model_2_2_3_1.eprime | 43 + .../model_2_2_3_2-solution000001.solution | 4 + .../model_2_2_3_2-solution000002.solution | 4 + .../basic/set09/expected/model_2_2_3_2.eprime | 37 + .../model_2_2_3_3-solution000001.solution | 4 + .../model_2_2_3_3-solution000002.solution | 4 + .../basic/set09/expected/model_2_2_3_3.eprime | 54 + .../model_2_2_3_4-solution000001.solution | 4 + .../model_2_2_3_4-solution000002.solution | 4 + .../basic/set09/expected/model_2_2_3_4.eprime | 56 + .../model_2_2_4_1-solution000001.solution | 4 + .../model_2_2_4_1-solution000002.solution | 4 + .../basic/set09/expected/model_2_2_4_1.eprime | 45 + .../model_2_2_4_2-solution000001.solution | 4 + .../model_2_2_4_2-solution000002.solution | 4 + .../basic/set09/expected/model_2_2_4_2.eprime | 39 + .../model_2_2_4_3-solution000001.solution | 4 + .../model_2_2_4_3-solution000002.solution | 4 + .../basic/set09/expected/model_2_2_4_3.eprime | 56 + .../model_2_2_4_4-solution000001.solution | 4 + .../model_2_2_4_4-solution000002.solution | 4 + .../basic/set09/expected/model_2_2_4_4.eprime | 58 + .../model_2_3_1_1-solution000001.solution | 4 + .../model_2_3_1_1-solution000002.solution | 4 + .../basic/set09/expected/model_2_3_1_1.eprime | 36 + .../model_2_3_1_2-solution000001.solution | 4 + .../model_2_3_1_2-solution000002.solution | 4 + .../basic/set09/expected/model_2_3_1_2.eprime | 43 + .../model_2_3_1_3-solution000001.solution | 4 + .../model_2_3_1_3-solution000002.solution | 4 + .../basic/set09/expected/model_2_3_1_3.eprime | 27 + .../model_2_3_1_4-solution000001.solution | 4 + .../model_2_3_1_4-solution000002.solution | 4 + .../basic/set09/expected/model_2_3_1_4.eprime | 47 + .../model_2_3_2_1-solution000001.solution | 4 + .../model_2_3_2_1-solution000002.solution | 4 + .../basic/set09/expected/model_2_3_2_1.eprime | 29 + .../model_2_3_2_2-solution000001.solution | 4 + .../model_2_3_2_2-solution000002.solution | 4 + .../basic/set09/expected/model_2_3_2_2.eprime | 37 + .../model_2_3_2_3-solution000001.solution | 4 + .../model_2_3_2_3-solution000002.solution | 4 + .../basic/set09/expected/model_2_3_2_3.eprime | 20 + .../model_2_3_2_4-solution000001.solution | 4 + .../model_2_3_2_4-solution000002.solution | 4 + .../basic/set09/expected/model_2_3_2_4.eprime | 40 + .../model_2_3_3_1-solution000001.solution | 4 + .../model_2_3_3_1-solution000002.solution | 4 + .../basic/set09/expected/model_2_3_3_1.eprime | 47 + .../model_2_3_3_2-solution000001.solution | 4 + .../model_2_3_3_2-solution000002.solution | 4 + .../basic/set09/expected/model_2_3_3_2.eprime | 54 + .../model_2_3_3_3-solution000001.solution | 4 + .../model_2_3_3_3-solution000002.solution | 4 + .../basic/set09/expected/model_2_3_3_3.eprime | 39 + .../model_2_3_3_4-solution000001.solution | 4 + .../model_2_3_3_4-solution000002.solution | 4 + .../basic/set09/expected/model_2_3_3_4.eprime | 59 + .../model_2_3_4_1-solution000001.solution | 4 + .../model_2_3_4_1-solution000002.solution | 4 + .../basic/set09/expected/model_2_3_4_1.eprime | 48 + .../model_2_3_4_2-solution000001.solution | 4 + .../model_2_3_4_2-solution000002.solution | 4 + .../basic/set09/expected/model_2_3_4_2.eprime | 55 + .../model_2_3_4_3-solution000001.solution | 4 + .../model_2_3_4_3-solution000002.solution | 4 + .../basic/set09/expected/model_2_3_4_3.eprime | 40 + .../model_2_3_4_4-solution000001.solution | 4 + .../model_2_3_4_4-solution000002.solution | 4 + .../basic/set09/expected/model_2_3_4_4.eprime | 60 + .../model_2_4_1_1-solution000001.solution | 4 + .../model_2_4_1_1-solution000002.solution | 4 + .../basic/set09/expected/model_2_4_1_1.eprime | 36 + .../model_2_4_1_2-solution000001.solution | 4 + .../model_2_4_1_2-solution000002.solution | 4 + .../basic/set09/expected/model_2_4_1_2.eprime | 44 + .../model_2_4_1_3-solution000001.solution | 4 + .../model_2_4_1_3-solution000002.solution | 4 + .../basic/set09/expected/model_2_4_1_3.eprime | 46 + .../model_2_4_1_4-solution000001.solution | 4 + .../model_2_4_1_4-solution000002.solution | 4 + .../basic/set09/expected/model_2_4_1_4.eprime | 28 + .../model_2_4_2_1-solution000001.solution | 4 + .../model_2_4_2_1-solution000002.solution | 4 + .../basic/set09/expected/model_2_4_2_1.eprime | 29 + .../model_2_4_2_2-solution000001.solution | 4 + .../model_2_4_2_2-solution000002.solution | 4 + .../basic/set09/expected/model_2_4_2_2.eprime | 38 + .../model_2_4_2_3-solution000001.solution | 4 + .../model_2_4_2_3-solution000002.solution | 4 + .../basic/set09/expected/model_2_4_2_3.eprime | 40 + .../model_2_4_2_4-solution000001.solution | 4 + .../model_2_4_2_4-solution000002.solution | 4 + .../basic/set09/expected/model_2_4_2_4.eprime | 21 + .../model_2_4_3_1-solution000001.solution | 4 + .../model_2_4_3_1-solution000002.solution | 4 + .../basic/set09/expected/model_2_4_3_1.eprime | 47 + .../model_2_4_3_2-solution000001.solution | 4 + .../model_2_4_3_2-solution000002.solution | 4 + .../basic/set09/expected/model_2_4_3_2.eprime | 55 + .../model_2_4_3_3-solution000001.solution | 4 + .../model_2_4_3_3-solution000002.solution | 4 + .../basic/set09/expected/model_2_4_3_3.eprime | 58 + .../model_2_4_3_4-solution000001.solution | 4 + .../model_2_4_3_4-solution000002.solution | 4 + .../basic/set09/expected/model_2_4_3_4.eprime | 40 + .../model_2_4_4_1-solution000001.solution | 4 + .../model_2_4_4_1-solution000002.solution | 4 + .../basic/set09/expected/model_2_4_4_1.eprime | 49 + .../model_2_4_4_2-solution000001.solution | 4 + .../model_2_4_4_2-solution000002.solution | 4 + .../basic/set09/expected/model_2_4_4_2.eprime | 57 + .../model_2_4_4_3-solution000001.solution | 4 + .../model_2_4_4_3-solution000002.solution | 4 + .../basic/set09/expected/model_2_4_4_3.eprime | 60 + .../model_2_4_4_4-solution000001.solution | 4 + .../model_2_4_4_4-solution000002.solution | 4 + .../basic/set09/expected/model_2_4_4_4.eprime | 42 + .../model_3_1_1_1-solution000001.solution | 4 + .../model_3_1_1_1-solution000002.solution | 4 + .../basic/set09/expected/model_3_1_1_1.eprime | 23 + .../model_3_1_1_2-solution000001.solution | 4 + .../model_3_1_1_2-solution000002.solution | 4 + .../basic/set09/expected/model_3_1_1_2.eprime | 35 + .../model_3_1_1_3-solution000001.solution | 4 + .../model_3_1_1_3-solution000002.solution | 4 + .../basic/set09/expected/model_3_1_1_3.eprime | 39 + .../model_3_1_1_4-solution000001.solution | 4 + .../model_3_1_1_4-solution000002.solution | 4 + .../basic/set09/expected/model_3_1_1_4.eprime | 39 + .../model_3_1_2_1-solution000001.solution | 4 + .../model_3_1_2_1-solution000002.solution | 4 + .../basic/set09/expected/model_3_1_2_1.eprime | 32 + .../model_3_1_2_2-solution000001.solution | 4 + .../model_3_1_2_2-solution000002.solution | 4 + .../basic/set09/expected/model_3_1_2_2.eprime | 42 + .../model_3_1_2_3-solution000001.solution | 4 + .../model_3_1_2_3-solution000002.solution | 4 + .../basic/set09/expected/model_3_1_2_3.eprime | 46 + .../model_3_1_2_4-solution000001.solution | 4 + .../model_3_1_2_4-solution000002.solution | 4 + .../basic/set09/expected/model_3_1_2_4.eprime | 47 + .../model_3_1_3_1-solution000001.solution | 4 + .../model_3_1_3_1-solution000002.solution | 4 + .../basic/set09/expected/model_3_1_3_1.eprime | 16 + .../model_3_1_3_2-solution000001.solution | 4 + .../model_3_1_3_2-solution000002.solution | 4 + .../basic/set09/expected/model_3_1_3_2.eprime | 26 + .../model_3_1_3_3-solution000001.solution | 4 + .../model_3_1_3_3-solution000002.solution | 4 + .../basic/set09/expected/model_3_1_3_3.eprime | 31 + .../model_3_1_3_4-solution000001.solution | 4 + .../model_3_1_3_4-solution000002.solution | 4 + .../basic/set09/expected/model_3_1_3_4.eprime | 31 + .../model_3_1_4_1-solution000001.solution | 4 + .../model_3_1_4_1-solution000002.solution | 4 + .../basic/set09/expected/model_3_1_4_1.eprime | 36 + .../model_3_1_4_2-solution000001.solution | 4 + .../model_3_1_4_2-solution000002.solution | 4 + .../basic/set09/expected/model_3_1_4_2.eprime | 45 + .../model_3_1_4_3-solution000001.solution | 4 + .../model_3_1_4_3-solution000002.solution | 4 + .../basic/set09/expected/model_3_1_4_3.eprime | 50 + .../model_3_1_4_4-solution000001.solution | 4 + .../model_3_1_4_4-solution000002.solution | 4 + .../basic/set09/expected/model_3_1_4_4.eprime | 51 + .../model_3_2_1_1-solution000001.solution | 4 + .../model_3_2_1_1-solution000002.solution | 4 + .../basic/set09/expected/model_3_2_1_1.eprime | 36 + .../model_3_2_1_2-solution000001.solution | 4 + .../model_3_2_1_2-solution000002.solution | 4 + .../basic/set09/expected/model_3_2_1_2.eprime | 29 + .../model_3_2_1_3-solution000001.solution | 4 + .../model_3_2_1_3-solution000002.solution | 4 + .../basic/set09/expected/model_3_2_1_3.eprime | 47 + .../model_3_2_1_4-solution000001.solution | 4 + .../model_3_2_1_4-solution000002.solution | 4 + .../basic/set09/expected/model_3_2_1_4.eprime | 49 + .../model_3_2_2_1-solution000001.solution | 4 + .../model_3_2_2_1-solution000002.solution | 4 + .../basic/set09/expected/model_3_2_2_1.eprime | 43 + .../model_3_2_2_2-solution000001.solution | 4 + .../model_3_2_2_2-solution000002.solution | 4 + .../basic/set09/expected/model_3_2_2_2.eprime | 37 + .../model_3_2_2_3-solution000001.solution | 4 + .../model_3_2_2_3-solution000002.solution | 4 + .../basic/set09/expected/model_3_2_2_3.eprime | 54 + .../model_3_2_2_4-solution000001.solution | 4 + .../model_3_2_2_4-solution000002.solution | 4 + .../basic/set09/expected/model_3_2_2_4.eprime | 56 + .../model_3_2_3_1-solution000001.solution | 4 + .../model_3_2_3_1-solution000002.solution | 4 + .../basic/set09/expected/model_3_2_3_1.eprime | 27 + .../model_3_2_3_2-solution000001.solution | 4 + .../model_3_2_3_2-solution000002.solution | 4 + .../basic/set09/expected/model_3_2_3_2.eprime | 20 + .../model_3_2_3_3-solution000001.solution | 4 + .../model_3_2_3_3-solution000002.solution | 4 + .../basic/set09/expected/model_3_2_3_3.eprime | 39 + .../model_3_2_3_4-solution000001.solution | 4 + .../model_3_2_3_4-solution000002.solution | 4 + .../basic/set09/expected/model_3_2_3_4.eprime | 40 + .../model_3_2_4_1-solution000001.solution | 4 + .../model_3_2_4_1-solution000002.solution | 4 + .../basic/set09/expected/model_3_2_4_1.eprime | 46 + .../model_3_2_4_2-solution000001.solution | 4 + .../model_3_2_4_2-solution000002.solution | 4 + .../basic/set09/expected/model_3_2_4_2.eprime | 40 + .../model_3_2_4_3-solution000001.solution | 4 + .../model_3_2_4_3-solution000002.solution | 4 + .../basic/set09/expected/model_3_2_4_3.eprime | 58 + .../model_3_2_4_4-solution000001.solution | 4 + .../model_3_2_4_4-solution000002.solution | 4 + .../basic/set09/expected/model_3_2_4_4.eprime | 60 + .../model_3_3_1_1-solution000001.solution | 4 + .../model_3_3_1_1-solution000002.solution | 4 + .../basic/set09/expected/model_3_3_1_1.eprime | 40 + .../model_3_3_1_2-solution000001.solution | 4 + .../model_3_3_1_2-solution000002.solution | 4 + .../basic/set09/expected/model_3_3_1_2.eprime | 47 + .../model_3_3_1_3-solution000001.solution | 4 + .../model_3_3_1_3-solution000002.solution | 4 + .../basic/set09/expected/model_3_3_1_3.eprime | 32 + .../model_3_3_1_4-solution000001.solution | 4 + .../model_3_3_1_4-solution000002.solution | 4 + .../basic/set09/expected/model_3_3_1_4.eprime | 51 + .../model_3_3_2_1-solution000001.solution | 4 + .../model_3_3_2_1-solution000002.solution | 4 + .../basic/set09/expected/model_3_3_2_1.eprime | 47 + .../model_3_3_2_2-solution000001.solution | 4 + .../model_3_3_2_2-solution000002.solution | 4 + .../basic/set09/expected/model_3_3_2_2.eprime | 54 + .../model_3_3_2_3-solution000001.solution | 4 + .../model_3_3_2_3-solution000002.solution | 4 + .../basic/set09/expected/model_3_3_2_3.eprime | 39 + .../model_3_3_2_4-solution000001.solution | 4 + .../model_3_3_2_4-solution000002.solution | 4 + .../basic/set09/expected/model_3_3_2_4.eprime | 59 + .../model_3_3_3_1-solution000001.solution | 4 + .../model_3_3_3_1-solution000002.solution | 4 + .../basic/set09/expected/model_3_3_3_1.eprime | 32 + .../model_3_3_3_2-solution000001.solution | 4 + .../model_3_3_3_2-solution000002.solution | 4 + .../basic/set09/expected/model_3_3_3_2.eprime | 39 + .../model_3_3_3_3-solution000001.solution | 4 + .../model_3_3_3_3-solution000002.solution | 4 + .../basic/set09/expected/model_3_3_3_3.eprime | 24 + .../model_3_3_3_4-solution000001.solution | 4 + .../model_3_3_3_4-solution000002.solution | 4 + .../basic/set09/expected/model_3_3_3_4.eprime | 42 + .../model_3_3_4_1-solution000001.solution | 4 + .../model_3_3_4_1-solution000002.solution | 4 + .../basic/set09/expected/model_3_3_4_1.eprime | 51 + .../model_3_3_4_2-solution000001.solution | 4 + .../model_3_3_4_2-solution000002.solution | 4 + .../basic/set09/expected/model_3_3_4_2.eprime | 58 + .../model_3_3_4_3-solution000001.solution | 4 + .../model_3_3_4_3-solution000002.solution | 4 + .../basic/set09/expected/model_3_3_4_3.eprime | 42 + .../model_3_3_4_4-solution000001.solution | 4 + .../model_3_3_4_4-solution000002.solution | 4 + .../basic/set09/expected/model_3_3_4_4.eprime | 62 + .../model_3_4_1_1-solution000001.solution | 4 + .../model_3_4_1_1-solution000002.solution | 4 + .../basic/set09/expected/model_3_4_1_1.eprime | 40 + .../model_3_4_1_2-solution000001.solution | 4 + .../model_3_4_1_2-solution000002.solution | 4 + .../basic/set09/expected/model_3_4_1_2.eprime | 48 + .../model_3_4_1_3-solution000001.solution | 4 + .../model_3_4_1_3-solution000002.solution | 4 + .../basic/set09/expected/model_3_4_1_3.eprime | 51 + .../model_3_4_1_4-solution000001.solution | 4 + .../model_3_4_1_4-solution000002.solution | 4 + .../basic/set09/expected/model_3_4_1_4.eprime | 33 + .../model_3_4_2_1-solution000001.solution | 4 + .../model_3_4_2_1-solution000002.solution | 4 + .../basic/set09/expected/model_3_4_2_1.eprime | 47 + .../model_3_4_2_2-solution000001.solution | 4 + .../model_3_4_2_2-solution000002.solution | 4 + .../basic/set09/expected/model_3_4_2_2.eprime | 55 + .../model_3_4_2_3-solution000001.solution | 4 + .../model_3_4_2_3-solution000002.solution | 4 + .../basic/set09/expected/model_3_4_2_3.eprime | 58 + .../model_3_4_2_4-solution000001.solution | 4 + .../model_3_4_2_4-solution000002.solution | 4 + .../basic/set09/expected/model_3_4_2_4.eprime | 40 + .../model_3_4_3_1-solution000001.solution | 4 + .../model_3_4_3_1-solution000002.solution | 4 + .../basic/set09/expected/model_3_4_3_1.eprime | 32 + .../model_3_4_3_2-solution000001.solution | 4 + .../model_3_4_3_2-solution000002.solution | 4 + .../basic/set09/expected/model_3_4_3_2.eprime | 40 + .../model_3_4_3_3-solution000001.solution | 4 + .../model_3_4_3_3-solution000002.solution | 4 + .../basic/set09/expected/model_3_4_3_3.eprime | 42 + .../model_3_4_3_4-solution000001.solution | 4 + .../model_3_4_3_4-solution000002.solution | 4 + .../basic/set09/expected/model_3_4_3_4.eprime | 25 + .../model_3_4_4_1-solution000001.solution | 4 + .../model_3_4_4_1-solution000002.solution | 4 + .../basic/set09/expected/model_3_4_4_1.eprime | 52 + .../model_3_4_4_2-solution000001.solution | 4 + .../model_3_4_4_2-solution000002.solution | 4 + .../basic/set09/expected/model_3_4_4_2.eprime | 60 + .../model_3_4_4_3-solution000001.solution | 4 + .../model_3_4_4_3-solution000002.solution | 4 + .../basic/set09/expected/model_3_4_4_3.eprime | 62 + .../model_3_4_4_4-solution000001.solution | 4 + .../model_3_4_4_4-solution000002.solution | 4 + .../basic/set09/expected/model_3_4_4_4.eprime | 44 + .../model_4_1_1_1-solution000001.solution | 4 + .../model_4_1_1_1-solution000002.solution | 4 + .../basic/set09/expected/model_4_1_1_1.eprime | 24 + .../model_4_1_1_2-solution000001.solution | 4 + .../model_4_1_1_2-solution000002.solution | 4 + .../basic/set09/expected/model_4_1_1_2.eprime | 35 + .../model_4_1_1_3-solution000001.solution | 4 + .../model_4_1_1_3-solution000002.solution | 4 + .../basic/set09/expected/model_4_1_1_3.eprime | 39 + .../model_4_1_1_4-solution000001.solution | 4 + .../model_4_1_1_4-solution000002.solution | 4 + .../basic/set09/expected/model_4_1_1_4.eprime | 39 + .../model_4_1_2_1-solution000001.solution | 4 + .../model_4_1_2_1-solution000002.solution | 4 + .../basic/set09/expected/model_4_1_2_1.eprime | 33 + .../model_4_1_2_2-solution000001.solution | 4 + .../model_4_1_2_2-solution000002.solution | 4 + .../basic/set09/expected/model_4_1_2_2.eprime | 43 + .../model_4_1_2_3-solution000001.solution | 4 + .../model_4_1_2_3-solution000002.solution | 4 + .../basic/set09/expected/model_4_1_2_3.eprime | 47 + .../model_4_1_2_4-solution000001.solution | 4 + .../model_4_1_2_4-solution000002.solution | 4 + .../basic/set09/expected/model_4_1_2_4.eprime | 48 + .../model_4_1_3_1-solution000001.solution | 4 + .../model_4_1_3_1-solution000002.solution | 4 + .../basic/set09/expected/model_4_1_3_1.eprime | 36 + .../model_4_1_3_2-solution000001.solution | 4 + .../model_4_1_3_2-solution000002.solution | 4 + .../basic/set09/expected/model_4_1_3_2.eprime | 45 + .../model_4_1_3_3-solution000001.solution | 4 + .../model_4_1_3_3-solution000002.solution | 4 + .../basic/set09/expected/model_4_1_3_3.eprime | 50 + .../model_4_1_3_4-solution000001.solution | 4 + .../model_4_1_3_4-solution000002.solution | 4 + .../basic/set09/expected/model_4_1_3_4.eprime | 51 + .../model_4_1_4_1-solution000001.solution | 4 + .../model_4_1_4_1-solution000002.solution | 4 + .../basic/set09/expected/model_4_1_4_1.eprime | 17 + .../model_4_1_4_2-solution000001.solution | 4 + .../model_4_1_4_2-solution000002.solution | 4 + .../basic/set09/expected/model_4_1_4_2.eprime | 27 + .../model_4_1_4_3-solution000001.solution | 4 + .../model_4_1_4_3-solution000002.solution | 4 + .../basic/set09/expected/model_4_1_4_3.eprime | 32 + .../model_4_1_4_4-solution000001.solution | 4 + .../model_4_1_4_4-solution000002.solution | 4 + .../basic/set09/expected/model_4_1_4_4.eprime | 32 + .../model_4_2_1_1-solution000001.solution | 4 + .../model_4_2_1_1-solution000002.solution | 4 + .../basic/set09/expected/model_4_2_1_1.eprime | 36 + .../model_4_2_1_2-solution000001.solution | 4 + .../model_4_2_1_2-solution000002.solution | 4 + .../basic/set09/expected/model_4_2_1_2.eprime | 29 + .../model_4_2_1_3-solution000001.solution | 4 + .../model_4_2_1_3-solution000002.solution | 4 + .../basic/set09/expected/model_4_2_1_3.eprime | 47 + .../model_4_2_1_4-solution000001.solution | 4 + .../model_4_2_1_4-solution000002.solution | 4 + .../basic/set09/expected/model_4_2_1_4.eprime | 49 + .../model_4_2_2_1-solution000001.solution | 4 + .../model_4_2_2_1-solution000002.solution | 4 + .../basic/set09/expected/model_4_2_2_1.eprime | 44 + .../model_4_2_2_2-solution000001.solution | 4 + .../model_4_2_2_2-solution000002.solution | 4 + .../basic/set09/expected/model_4_2_2_2.eprime | 38 + .../model_4_2_2_3-solution000001.solution | 4 + .../model_4_2_2_3-solution000002.solution | 4 + .../basic/set09/expected/model_4_2_2_3.eprime | 55 + .../model_4_2_2_4-solution000001.solution | 4 + .../model_4_2_2_4-solution000002.solution | 4 + .../basic/set09/expected/model_4_2_2_4.eprime | 57 + .../model_4_2_3_1-solution000001.solution | 4 + .../model_4_2_3_1-solution000002.solution | 4 + .../basic/set09/expected/model_4_2_3_1.eprime | 46 + .../model_4_2_3_2-solution000001.solution | 4 + .../model_4_2_3_2-solution000002.solution | 4 + .../basic/set09/expected/model_4_2_3_2.eprime | 40 + .../model_4_2_3_3-solution000001.solution | 4 + .../model_4_2_3_3-solution000002.solution | 4 + .../basic/set09/expected/model_4_2_3_3.eprime | 58 + .../model_4_2_3_4-solution000001.solution | 4 + .../model_4_2_3_4-solution000002.solution | 4 + .../basic/set09/expected/model_4_2_3_4.eprime | 60 + .../model_4_2_4_1-solution000001.solution | 4 + .../model_4_2_4_1-solution000002.solution | 4 + .../basic/set09/expected/model_4_2_4_1.eprime | 28 + .../model_4_2_4_2-solution000001.solution | 4 + .../model_4_2_4_2-solution000002.solution | 4 + .../basic/set09/expected/model_4_2_4_2.eprime | 21 + .../model_4_2_4_3-solution000001.solution | 4 + .../model_4_2_4_3-solution000002.solution | 4 + .../basic/set09/expected/model_4_2_4_3.eprime | 40 + .../model_4_2_4_4-solution000001.solution | 4 + .../model_4_2_4_4-solution000002.solution | 4 + .../basic/set09/expected/model_4_2_4_4.eprime | 42 + .../model_4_3_1_1-solution000001.solution | 4 + .../model_4_3_1_1-solution000002.solution | 4 + .../basic/set09/expected/model_4_3_1_1.eprime | 40 + .../model_4_3_1_2-solution000001.solution | 4 + .../model_4_3_1_2-solution000002.solution | 4 + .../basic/set09/expected/model_4_3_1_2.eprime | 47 + .../model_4_3_1_3-solution000001.solution | 4 + .../model_4_3_1_3-solution000002.solution | 4 + .../basic/set09/expected/model_4_3_1_3.eprime | 32 + .../model_4_3_1_4-solution000001.solution | 4 + .../model_4_3_1_4-solution000002.solution | 4 + .../basic/set09/expected/model_4_3_1_4.eprime | 52 + .../model_4_3_2_1-solution000001.solution | 4 + .../model_4_3_2_1-solution000002.solution | 4 + .../basic/set09/expected/model_4_3_2_1.eprime | 48 + .../model_4_3_2_2-solution000001.solution | 4 + .../model_4_3_2_2-solution000002.solution | 4 + .../basic/set09/expected/model_4_3_2_2.eprime | 55 + .../model_4_3_2_3-solution000001.solution | 4 + .../model_4_3_2_3-solution000002.solution | 4 + .../basic/set09/expected/model_4_3_2_3.eprime | 40 + .../model_4_3_2_4-solution000001.solution | 4 + .../model_4_3_2_4-solution000002.solution | 4 + .../basic/set09/expected/model_4_3_2_4.eprime | 60 + .../model_4_3_3_1-solution000001.solution | 4 + .../model_4_3_3_1-solution000002.solution | 4 + .../basic/set09/expected/model_4_3_3_1.eprime | 51 + .../model_4_3_3_2-solution000001.solution | 4 + .../model_4_3_3_2-solution000002.solution | 4 + .../basic/set09/expected/model_4_3_3_2.eprime | 58 + .../model_4_3_3_3-solution000001.solution | 4 + .../model_4_3_3_3-solution000002.solution | 4 + .../basic/set09/expected/model_4_3_3_3.eprime | 42 + .../model_4_3_3_4-solution000001.solution | 4 + .../model_4_3_3_4-solution000002.solution | 4 + .../basic/set09/expected/model_4_3_3_4.eprime | 62 + .../model_4_3_4_1-solution000001.solution | 4 + .../model_4_3_4_1-solution000002.solution | 4 + .../basic/set09/expected/model_4_3_4_1.eprime | 33 + .../model_4_3_4_2-solution000001.solution | 4 + .../model_4_3_4_2-solution000002.solution | 4 + .../basic/set09/expected/model_4_3_4_2.eprime | 40 + .../model_4_3_4_3-solution000001.solution | 4 + .../model_4_3_4_3-solution000002.solution | 4 + .../basic/set09/expected/model_4_3_4_3.eprime | 25 + .../model_4_3_4_4-solution000001.solution | 4 + .../model_4_3_4_4-solution000002.solution | 4 + .../basic/set09/expected/model_4_3_4_4.eprime | 44 + .../model_4_4_1_1-solution000001.solution | 4 + .../model_4_4_1_1-solution000002.solution | 4 + .../basic/set09/expected/model_4_4_1_1.eprime | 40 + .../model_4_4_1_2-solution000001.solution | 4 + .../model_4_4_1_2-solution000002.solution | 4 + .../basic/set09/expected/model_4_4_1_2.eprime | 48 + .../model_4_4_1_3-solution000001.solution | 4 + .../model_4_4_1_3-solution000002.solution | 4 + .../basic/set09/expected/model_4_4_1_3.eprime | 51 + .../model_4_4_1_4-solution000001.solution | 4 + .../model_4_4_1_4-solution000002.solution | 4 + .../basic/set09/expected/model_4_4_1_4.eprime | 33 + .../model_4_4_2_1-solution000001.solution | 4 + .../model_4_4_2_1-solution000002.solution | 4 + .../basic/set09/expected/model_4_4_2_1.eprime | 48 + .../model_4_4_2_2-solution000001.solution | 4 + .../model_4_4_2_2-solution000002.solution | 4 + .../basic/set09/expected/model_4_4_2_2.eprime | 56 + .../model_4_4_2_3-solution000001.solution | 4 + .../model_4_4_2_3-solution000002.solution | 4 + .../basic/set09/expected/model_4_4_2_3.eprime | 59 + .../model_4_4_2_4-solution000001.solution | 4 + .../model_4_4_2_4-solution000002.solution | 4 + .../basic/set09/expected/model_4_4_2_4.eprime | 41 + .../model_4_4_3_1-solution000001.solution | 4 + .../model_4_4_3_1-solution000002.solution | 4 + .../basic/set09/expected/model_4_4_3_1.eprime | 51 + .../model_4_4_3_2-solution000001.solution | 4 + .../model_4_4_3_2-solution000002.solution | 4 + .../basic/set09/expected/model_4_4_3_2.eprime | 59 + .../model_4_4_3_3-solution000001.solution | 4 + .../model_4_4_3_3-solution000002.solution | 4 + .../basic/set09/expected/model_4_4_3_3.eprime | 61 + .../model_4_4_3_4-solution000001.solution | 4 + .../model_4_4_3_4-solution000002.solution | 4 + .../basic/set09/expected/model_4_4_3_4.eprime | 43 + .../model_4_4_4_1-solution000001.solution | 4 + .../model_4_4_4_1-solution000002.solution | 4 + .../basic/set09/expected/model_4_4_4_1.eprime | 33 + .../model_4_4_4_2-solution000001.solution | 4 + .../model_4_4_4_2-solution000002.solution | 4 + .../basic/set09/expected/model_4_4_4_2.eprime | 41 + .../model_4_4_4_3-solution000001.solution | 4 + .../model_4_4_4_3-solution000002.solution | 4 + .../basic/set09/expected/model_4_4_4_3.eprime | 43 + .../model_4_4_4_4-solution000001.solution | 4 + .../model_4_4_4_4-solution000002.solution | 4 + .../basic/set09/expected/model_4_4_4_4.eprime | 26 + .../expected/model_1-solution000001.solution | 3 + .../expected/model_1-solution000002.solution | 3 + .../expected/model_1-solution000003.solution | 6 + .../expected/model_1-solution000004.solution | 6 + .../expected/model_1-solution000005.solution | 6 + .../expected/model_1-solution000006.solution | 7 + .../expected/model_1-solution000007.solution | 7 + .../expected/model_1-solution000008.solution | 7 + .../expected/model_1-solution000009.solution | 7 + .../expected/model_1-solution000010.solution | 7 + .../expected/model_1-solution000011.solution | 7 + .../expected/model_1-solution000012.solution | 8 + .../expected/model_1-solution000013.solution | 8 + .../expected/model_1-solution000014.solution | 8 + .../expected/model_1-solution000015.solution | 8 + .../expected/model_1-solution000016.solution | 9 + .../basic/setOfSet01/expected/model_1.eprime | 14 + .../expected/model_2-solution000001.solution | 3 + .../expected/model_2-solution000002.solution | 6 + .../expected/model_2-solution000003.solution | 6 + .../expected/model_2-solution000004.solution | 6 + .../expected/model_2-solution000005.solution | 3 + .../expected/model_2-solution000006.solution | 7 + .../expected/model_2-solution000007.solution | 7 + .../expected/model_2-solution000008.solution | 7 + .../expected/model_2-solution000009.solution | 7 + .../expected/model_2-solution000010.solution | 7 + .../expected/model_2-solution000011.solution | 7 + .../expected/model_2-solution000012.solution | 8 + .../expected/model_2-solution000013.solution | 8 + .../expected/model_2-solution000014.solution | 8 + .../expected/model_2-solution000015.solution | 8 + .../expected/model_2-solution000016.solution | 9 + .../basic/setOfSet01/expected/model_2.eprime | 24 + .../expected/model_3-solution000001.solution | 3 + .../expected/model_3-solution000002.solution | 3 + .../expected/model_3-solution000003.solution | 6 + .../expected/model_3-solution000004.solution | 6 + .../expected/model_3-solution000005.solution | 6 + .../expected/model_3-solution000006.solution | 7 + .../expected/model_3-solution000007.solution | 7 + .../expected/model_3-solution000008.solution | 7 + .../expected/model_3-solution000009.solution | 7 + .../expected/model_3-solution000010.solution | 7 + .../expected/model_3-solution000011.solution | 7 + .../expected/model_3-solution000012.solution | 8 + .../expected/model_3-solution000013.solution | 8 + .../expected/model_3-solution000014.solution | 8 + .../expected/model_3-solution000015.solution | 8 + .../expected/model_3-solution000016.solution | 9 + .../setOfSet01/expected/model_3.eprime.orig | 34 - .../expected/model_4-solution000001.solution | 3 + .../expected/model_4-solution000002.solution | 3 + .../expected/model_4-solution000003.solution | 6 + .../expected/model_4-solution000004.solution | 6 + .../expected/model_4-solution000005.solution | 6 + .../expected/model_4-solution000006.solution | 7 + .../expected/model_4-solution000007.solution | 7 + .../expected/model_4-solution000008.solution | 7 + .../expected/model_4-solution000009.solution | 7 + .../expected/model_4-solution000010.solution | 7 + .../expected/model_4-solution000011.solution | 7 + .../expected/model_4-solution000012.solution | 8 + .../expected/model_4-solution000013.solution | 8 + .../expected/model_4-solution000014.solution | 8 + .../expected/model_4-solution000015.solution | 8 + .../expected/model_4-solution000016.solution | 9 + .../basic/setOfSet01/expected/model_4.eprime | 43 + .../expected/model_5-solution000001.solution | 3 + .../expected/model_5-solution000002.solution | 3 + .../expected/model_5-solution000003.solution | 6 + .../expected/model_5-solution000004.solution | 6 + .../expected/model_5-solution000005.solution | 6 + .../expected/model_5-solution000006.solution | 7 + .../expected/model_5-solution000007.solution | 7 + .../expected/model_5-solution000008.solution | 7 + .../expected/model_5-solution000009.solution | 7 + .../expected/model_5-solution000010.solution | 7 + .../expected/model_5-solution000011.solution | 7 + .../expected/model_5-solution000012.solution | 8 + .../expected/model_5-solution000013.solution | 8 + .../expected/model_5-solution000014.solution | 8 + .../expected/model_5-solution000015.solution | 8 + .../expected/model_5-solution000016.solution | 9 + .../basic/setOfSet01/expected/model_5.eprime | 15 + .../expected/model_6-solution000001.solution | 3 + .../expected/model_6-solution000002.solution | 6 + .../expected/model_6-solution000003.solution | 6 + .../expected/model_6-solution000004.solution | 6 + .../expected/model_6-solution000005.solution | 3 + .../expected/model_6-solution000006.solution | 7 + .../expected/model_6-solution000007.solution | 7 + .../expected/model_6-solution000008.solution | 7 + .../expected/model_6-solution000009.solution | 7 + .../expected/model_6-solution000010.solution | 7 + .../expected/model_6-solution000011.solution | 7 + .../expected/model_6-solution000012.solution | 8 + .../expected/model_6-solution000013.solution | 8 + .../expected/model_6-solution000014.solution | 8 + .../expected/model_6-solution000015.solution | 8 + .../expected/model_6-solution000016.solution | 9 + .../basic/setOfSet01/expected/model_6.eprime | 24 + .../expected/model_7-solution000001.solution | 3 + .../expected/model_7-solution000002.solution | 3 + .../expected/model_7-solution000003.solution | 6 + .../expected/model_7-solution000004.solution | 6 + .../expected/model_7-solution000005.solution | 6 + .../expected/model_7-solution000006.solution | 7 + .../expected/model_7-solution000007.solution | 7 + .../expected/model_7-solution000008.solution | 7 + .../expected/model_7-solution000009.solution | 7 + .../expected/model_7-solution000010.solution | 7 + .../expected/model_7-solution000011.solution | 7 + .../expected/model_7-solution000012.solution | 8 + .../expected/model_7-solution000013.solution | 8 + .../expected/model_7-solution000014.solution | 8 + .../expected/model_7-solution000015.solution | 8 + .../expected/model_7-solution000016.solution | 9 + .../setOfSet01/expected/model_7.eprime.orig | 35 - .../expected/model_8-solution000001.solution | 3 + .../expected/model_8-solution000002.solution | 3 + .../expected/model_8-solution000003.solution | 6 + .../expected/model_8-solution000004.solution | 6 + .../expected/model_8-solution000005.solution | 6 + .../expected/model_8-solution000006.solution | 7 + .../expected/model_8-solution000007.solution | 7 + .../expected/model_8-solution000008.solution | 7 + .../expected/model_8-solution000009.solution | 7 + .../expected/model_8-solution000010.solution | 7 + .../expected/model_8-solution000011.solution | 7 + .../expected/model_8-solution000012.solution | 8 + .../expected/model_8-solution000013.solution | 8 + .../expected/model_8-solution000014.solution | 8 + .../expected/model_8-solution000015.solution | 8 + .../expected/model_8-solution000016.solution | 9 + .../basic/setOfSet01/expected/model_8.eprime | 44 + .../model_1_1-solution000002.solution | 7 + .../model_1_2-solution000002.solution | 7 + .../setOfSet02/expected/model_1_2.eprime.orig | 26 - .../model_2_1-solution000002.solution | 7 + .../setOfSet02/expected/model_2_1.eprime.orig | 32 - .../model_2_2-solution000002.solution | 7 + .../setOfSet02/expected/model_2_2.eprime.orig | 18 - .../basic/setOfSet03/expected/model_2.eprime | 11 - .../setOfSet03/expected/model_2.eprime.orig | 14 - .../model_1_1_1-solution000001.solution | 7 + .../model_1_1_1-solution000002.solution | 7 + .../model_1_1_1-solution000003.solution | 7 + .../model_1_1_1-solution000004.solution | 7 + .../model_1_1_1-solution000005.solution | 7 + .../model_1_1_1-solution000006.solution | 7 + .../setOfSet04/expected/model_1_1_1.eprime | 9 + .../model_1_1_2-solution000001.solution | 7 + .../model_1_1_2-solution000002.solution | 7 + .../model_1_1_2-solution000003.solution | 7 + .../model_1_1_2-solution000004.solution | 7 + .../model_1_1_2-solution000005.solution | 7 + .../model_1_1_2-solution000006.solution | 7 + .../setOfSet04/expected/model_1_1_2.eprime | 42 + .../model_1_1_3-solution000001.solution | 7 + .../model_1_1_3-solution000002.solution | 7 + .../model_1_1_3-solution000003.solution | 7 + .../model_1_1_3-solution000004.solution | 7 + .../model_1_1_3-solution000005.solution | 7 + .../model_1_1_3-solution000006.solution | 7 + .../expected/model_1_1_3.eprime.orig | 52 - .../model_1_1_4-solution000001.solution | 7 + .../model_1_1_4-solution000002.solution | 7 + .../model_1_1_4-solution000003.solution | 7 + .../model_1_1_4-solution000004.solution | 7 + .../model_1_1_4-solution000005.solution | 7 + .../model_1_1_4-solution000006.solution | 7 + .../setOfSet04/expected/model_1_1_4.eprime | 57 + .../model_1_2_3-solution000001.solution | 7 + .../model_1_2_3-solution000002.solution | 7 + .../model_1_2_3-solution000003.solution | 7 + .../model_1_2_3-solution000004.solution | 7 + .../model_1_2_3-solution000005.solution | 7 + .../model_1_2_3-solution000006.solution | 7 + .../expected/model_1_2_3.eprime.orig | 115 - .../model_1_2_4-solution000001.solution | 7 + .../model_1_2_4-solution000002.solution | 7 + .../model_1_2_4-solution000003.solution | 7 + .../model_1_2_4-solution000004.solution | 7 + .../model_1_2_4-solution000005.solution | 7 + .../model_1_2_4-solution000006.solution | 7 + .../setOfSet04/expected/model_1_2_4.eprime | 121 + .../expected/model_1_3_1.eprime.orig | 52 - .../model_1_3_2-solution000001.solution | 7 + .../model_1_3_2-solution000002.solution | 7 + .../model_1_3_2-solution000003.solution | 7 + .../model_1_3_2-solution000004.solution | 7 + .../model_1_3_2-solution000005.solution | 7 + .../model_1_3_2-solution000006.solution | 7 + .../expected/model_1_3_2.eprime.orig | 116 - .../expected/model_1_3_3.eprime.orig | 52 - .../model_1_3_4-solution000001.solution | 7 + .../model_1_3_4-solution000002.solution | 7 + .../model_1_3_4-solution000003.solution | 7 + .../model_1_3_4-solution000004.solution | 7 + .../model_1_3_4-solution000005.solution | 7 + .../model_1_3_4-solution000006.solution | 7 + .../expected/model_1_3_4.eprime.orig | 129 - .../model_1_4_2-solution000001.solution | 7 + .../model_1_4_2-solution000002.solution | 7 + .../model_1_4_2-solution000003.solution | 7 + .../model_1_4_2-solution000004.solution | 7 + .../model_1_4_2-solution000005.solution | 7 + .../model_1_4_2-solution000006.solution | 7 + ...l_1_4_3.eprime.orig => model_1_4_2.eprime} | 125 +- .../model_1_4_3-solution000001.solution | 7 + .../model_1_4_3-solution000002.solution | 7 + .../model_1_4_3-solution000003.solution | 7 + .../model_1_4_3-solution000004.solution | 7 + .../model_1_4_3-solution000005.solution | 7 + .../model_1_4_3-solution000006.solution | 7 + .../model_2_1_1-solution000001.solution | 7 + .../model_2_1_1-solution000002.solution | 7 + .../model_2_1_1-solution000003.solution | 7 + .../model_2_1_1-solution000004.solution | 7 + .../model_2_1_1-solution000005.solution | 7 + .../model_2_1_1-solution000006.solution | 7 + .../setOfSet04/expected/model_2_1_1.eprime | 42 + .../model_2_1_3-solution000001.solution | 7 + .../model_2_1_3-solution000002.solution | 7 + .../model_2_1_3-solution000003.solution | 7 + .../model_2_1_3-solution000004.solution | 7 + .../model_2_1_3-solution000005.solution | 7 + .../model_2_1_3-solution000006.solution | 7 + .../expected/model_2_1_3.eprime.orig | 115 - .../model_2_1_4-solution000001.solution | 7 + .../model_2_1_4-solution000002.solution | 7 + .../model_2_1_4-solution000003.solution | 7 + .../model_2_1_4-solution000004.solution | 7 + .../model_2_1_4-solution000005.solution | 7 + .../model_2_1_4-solution000006.solution | 7 + .../setOfSet04/expected/model_2_1_4.eprime | 121 + .../model_2_2_2-solution000001.solution | 7 + .../model_2_2_2-solution000002.solution | 7 + .../model_2_2_2-solution000003.solution | 7 + .../model_2_2_2-solution000004.solution | 7 + .../model_2_2_2-solution000005.solution | 7 + .../model_2_2_2-solution000006.solution | 7 + .../setOfSet04/expected/model_2_2_2.eprime | 16 + .../model_2_2_3-solution000001.solution | 7 + .../model_2_2_3-solution000002.solution | 7 + .../model_2_2_3-solution000003.solution | 7 + .../model_2_2_3-solution000004.solution | 7 + .../model_2_2_3-solution000005.solution | 7 + .../model_2_2_3-solution000006.solution | 7 + .../expected/model_2_2_3.eprime.orig | 67 - .../model_2_2_4-solution000001.solution | 7 + .../model_2_2_4-solution000002.solution | 7 + .../model_2_2_4-solution000003.solution | 7 + .../model_2_2_4-solution000004.solution | 7 + .../model_2_2_4-solution000005.solution | 7 + .../model_2_2_4-solution000006.solution | 7 + .../setOfSet04/expected/model_2_2_4.eprime | 73 + .../model_2_3_1-solution000001.solution | 7 + .../model_2_3_1-solution000002.solution | 7 + .../model_2_3_1-solution000003.solution | 7 + .../model_2_3_1-solution000004.solution | 7 + .../model_2_3_1-solution000005.solution | 7 + .../model_2_3_1-solution000006.solution | 7 + .../expected/model_2_3_1.eprime.orig | 115 - .../expected/model_2_3_2.eprime.orig | 67 - .../expected/model_2_3_3.eprime.orig | 67 - .../model_2_3_4-solution000001.solution | 7 + .../model_2_3_4-solution000002.solution | 7 + .../model_2_3_4-solution000003.solution | 7 + .../model_2_3_4-solution000004.solution | 7 + .../model_2_3_4-solution000005.solution | 7 + .../model_2_3_4-solution000006.solution | 7 + .../expected/model_2_3_4.eprime.orig | 153 - .../model_2_4_1-solution000001.solution | 7 + .../model_2_4_1-solution000002.solution | 7 + .../model_2_4_1-solution000003.solution | 7 + .../model_2_4_1-solution000004.solution | 7 + .../model_2_4_1-solution000005.solution | 7 + .../model_2_4_1-solution000006.solution | 7 + ...l_2_4_3.eprime.orig => model_2_4_1.eprime} | 118 +- .../model_2_4_3-solution000001.solution | 7 + .../model_2_4_3-solution000002.solution | 7 + .../model_2_4_3-solution000003.solution | 7 + .../model_2_4_3-solution000004.solution | 7 + .../model_2_4_3-solution000005.solution | 7 + .../model_2_4_3-solution000006.solution | 7 + .../model_3_1_1-solution000001.solution | 7 + .../model_3_1_1-solution000002.solution | 7 + .../model_3_1_1-solution000003.solution | 7 + .../model_3_1_1-solution000004.solution | 7 + .../model_3_1_1-solution000005.solution | 7 + .../model_3_1_1-solution000006.solution | 7 + .../expected/model_3_1_1.eprime.orig | 52 - .../model_3_1_2-solution000001.solution | 7 + .../model_3_1_2-solution000002.solution | 7 + .../model_3_1_2-solution000003.solution | 7 + .../model_3_1_2-solution000004.solution | 7 + .../model_3_1_2-solution000005.solution | 7 + .../model_3_1_2-solution000006.solution | 7 + .../expected/model_3_1_2.eprime.orig | 116 - .../expected/model_3_1_3.eprime.orig | 52 - .../model_3_1_4-solution000001.solution | 7 + .../model_3_1_4-solution000002.solution | 7 + .../model_3_1_4-solution000003.solution | 7 + .../model_3_1_4-solution000004.solution | 7 + .../model_3_1_4-solution000005.solution | 7 + .../model_3_1_4-solution000006.solution | 7 + .../expected/model_3_1_4.eprime.orig | 130 - .../model_3_2_1-solution000001.solution | 7 + .../model_3_2_1-solution000002.solution | 7 + .../model_3_2_1-solution000003.solution | 7 + .../model_3_2_1-solution000004.solution | 7 + .../model_3_2_1-solution000005.solution | 7 + .../model_3_2_1-solution000006.solution | 7 + .../expected/model_3_2_1.eprime.orig | 116 - .../model_3_2_2-solution000001.solution | 7 + .../model_3_2_2-solution000002.solution | 7 + .../model_3_2_2-solution000003.solution | 7 + .../model_3_2_2-solution000004.solution | 7 + .../model_3_2_2-solution000005.solution | 7 + .../model_3_2_2-solution000006.solution | 7 + .../expected/model_3_2_2.eprime.orig | 68 - .../expected/model_3_2_3.eprime.orig | 68 - .../model_3_2_4-solution000001.solution | 7 + .../model_3_2_4-solution000002.solution | 7 + .../model_3_2_4-solution000003.solution | 7 + .../model_3_2_4-solution000004.solution | 7 + .../model_3_2_4-solution000005.solution | 7 + .../model_3_2_4-solution000006.solution | 7 + .../expected/model_3_2_4.eprime.orig | 154 - .../expected/model_3_3_1.eprime.orig | 52 - .../expected/model_3_3_2.eprime.orig | 68 - .../model_3_3_3-solution000001.solution | 7 + .../model_3_3_3-solution000002.solution | 7 + .../model_3_3_3-solution000003.solution | 7 + .../model_3_3_3-solution000004.solution | 7 + .../model_3_3_3-solution000005.solution | 7 + .../model_3_3_3-solution000006.solution | 7 + .../expected/model_3_3_3.eprime.orig | 24 - .../model_3_3_4-solution000001.solution | 7 + .../model_3_3_4-solution000002.solution | 7 + .../model_3_3_4-solution000003.solution | 7 + .../model_3_3_4-solution000004.solution | 7 + .../model_3_3_4-solution000005.solution | 7 + .../model_3_3_4-solution000006.solution | 7 + .../expected/model_3_3_4.eprime.orig | 81 - .../model_3_4_1-solution000001.solution | 7 + .../model_3_4_1-solution000002.solution | 7 + .../model_3_4_1-solution000003.solution | 7 + .../model_3_4_1-solution000004.solution | 7 + .../model_3_4_1-solution000005.solution | 7 + .../model_3_4_1-solution000006.solution | 7 + .../expected/model_3_4_1.eprime.orig | 130 - .../model_3_4_2-solution000001.solution | 7 + .../model_3_4_2-solution000002.solution | 7 + .../model_3_4_2-solution000003.solution | 7 + .../model_3_4_2-solution000004.solution | 7 + .../model_3_4_2-solution000005.solution | 7 + .../model_3_4_2-solution000006.solution | 7 + .../expected/model_3_4_2.eprime.orig | 154 - .../expected/model_3_4_3.eprime.orig | 81 - .../expected/model_3_4_4.eprime.orig | 81 - .../model_4_1_1-solution000001.solution | 7 + .../model_4_1_1-solution000002.solution | 7 + .../model_4_1_1-solution000003.solution | 7 + .../model_4_1_1-solution000004.solution | 7 + .../model_4_1_1-solution000005.solution | 7 + .../model_4_1_1-solution000006.solution | 7 + .../setOfSet04/expected/model_4_1_1.eprime | 57 + .../model_4_1_2-solution000001.solution | 7 + .../model_4_1_2-solution000002.solution | 7 + .../model_4_1_2-solution000003.solution | 7 + .../model_4_1_2-solution000004.solution | 7 + .../model_4_1_2-solution000005.solution | 7 + .../model_4_1_2-solution000006.solution | 7 + ...l_4_1_3.eprime.orig => model_4_1_2.eprime} | 125 +- .../model_4_1_3-solution000001.solution | 7 + .../model_4_1_3-solution000002.solution | 7 + .../model_4_1_3-solution000003.solution | 7 + .../model_4_1_3-solution000004.solution | 7 + .../model_4_1_3-solution000005.solution | 7 + .../model_4_1_3-solution000006.solution | 7 + .../model_4_2_1-solution000001.solution | 7 + .../model_4_2_1-solution000002.solution | 7 + .../model_4_2_1-solution000003.solution | 7 + .../model_4_2_1-solution000004.solution | 7 + .../model_4_2_1-solution000005.solution | 7 + .../model_4_2_1-solution000006.solution | 7 + ...l_4_2_3.eprime.orig => model_4_2_1.eprime} | 118 +- .../model_4_2_2-solution000001.solution | 7 + .../model_4_2_2-solution000002.solution | 7 + .../model_4_2_2-solution000003.solution | 7 + .../model_4_2_2-solution000004.solution | 7 + .../model_4_2_2-solution000005.solution | 7 + .../model_4_2_2-solution000006.solution | 7 + .../setOfSet04/expected/model_4_2_2.eprime | 74 + .../model_4_2_3-solution000001.solution | 7 + .../model_4_2_3-solution000002.solution | 7 + .../model_4_2_3-solution000003.solution | 7 + .../model_4_2_3-solution000004.solution | 7 + .../model_4_2_3-solution000005.solution | 7 + .../model_4_2_3-solution000006.solution | 7 + .../model_4_3_1-solution000001.solution | 7 + .../model_4_3_1-solution000002.solution | 7 + .../model_4_3_1-solution000003.solution | 7 + .../model_4_3_1-solution000004.solution | 7 + .../model_4_3_1-solution000005.solution | 7 + .../model_4_3_1-solution000006.solution | 7 + .../expected/model_4_3_1.eprime.orig | 129 - .../model_4_3_2-solution000001.solution | 7 + .../model_4_3_2-solution000002.solution | 7 + .../model_4_3_2-solution000003.solution | 7 + .../model_4_3_2-solution000004.solution | 7 + .../model_4_3_2-solution000005.solution | 7 + .../model_4_3_2-solution000006.solution | 7 + .../expected/model_4_3_2.eprime.orig | 154 - .../model_4_3_3-solution000001.solution | 7 + .../model_4_3_3-solution000002.solution | 7 + .../model_4_3_3-solution000003.solution | 7 + .../model_4_3_3-solution000004.solution | 7 + .../model_4_3_3-solution000005.solution | 7 + .../model_4_3_3-solution000006.solution | 7 + .../expected/model_4_3_3.eprime.orig | 81 - .../expected/model_4_3_4.eprime.orig | 81 - .../expected/model_4_4_3.eprime.orig | 81 - .../model_4_4_4-solution000001.solution | 7 + .../model_4_4_4-solution000002.solution | 7 + .../model_4_4_4-solution000003.solution | 7 + .../model_4_4_4-solution000004.solution | 7 + .../model_4_4_4-solution000005.solution | 7 + .../model_4_4_4-solution000006.solution | 7 + .../setOfSet04/expected/model_4_4_4.eprime | 30 + .../model_1_1_1-solution000001.solution | 3 + .../model_1_1_1-solution000002.solution | 3 + .../set_card_00/expected/model_1_1_1.eprime | 6 + .../model_1_1_2-solution000001.solution | 3 + .../model_1_1_2-solution000002.solution | 3 + .../set_card_00/expected/model_1_1_2.eprime | 14 + .../model_1_1_3-solution000001.solution | 3 + .../model_1_1_3-solution000002.solution | 3 + .../set_card_00/expected/model_1_1_3.eprime | 17 + .../model_1_1_4-solution000001.solution | 3 + .../model_1_1_4-solution000002.solution | 3 + .../set_card_00/expected/model_1_1_4.eprime | 16 + .../model_1_2_1-solution000001.solution | 3 + .../model_1_2_1-solution000002.solution | 3 + .../set_card_00/expected/model_1_2_1.eprime | 16 + .../model_1_2_3-solution000001.solution | 3 + .../model_1_2_3-solution000002.solution | 3 + .../set_card_00/expected/model_1_2_3.eprime | 38 + .../model_1_2_4-solution000001.solution | 3 + .../model_1_2_4-solution000002.solution | 3 + .../set_card_00/expected/model_1_2_4.eprime | 38 + .../model_1_3_1-solution000001.solution | 3 + .../model_1_3_1-solution000002.solution | 3 + .../set_card_00/expected/model_1_3_1.eprime | 19 + .../model_1_3_2-solution000001.solution | 3 + .../model_1_3_2-solution000002.solution | 3 + .../set_card_00/expected/model_1_3_2.eprime | 37 + .../model_1_3_4-solution000001.solution | 3 + .../model_1_3_4-solution000002.solution | 3 + .../set_card_00/expected/model_1_3_4.eprime | 42 + .../model_1_4_1-solution000001.solution | 3 + .../model_1_4_1-solution000002.solution | 3 + .../set_card_00/expected/model_1_4_1.eprime | 18 + .../model_1_4_2-solution000001.solution | 3 + .../model_1_4_2-solution000002.solution | 3 + .../set_card_00/expected/model_1_4_2.eprime | 36 + .../model_1_4_3-solution000001.solution | 3 + .../model_1_4_3-solution000002.solution | 3 + .../set_card_00/expected/model_1_4_3.eprime | 41 + .../model_2_1_1-solution000001.solution | 3 + .../model_2_1_1-solution000002.solution | 3 + .../set_card_00/expected/model_2_1_1.eprime | 14 + .../model_2_1_3-solution000001.solution | 3 + .../model_2_1_3-solution000002.solution | 3 + .../set_card_00/expected/model_2_1_3.eprime | 36 + .../model_2_1_4-solution000001.solution | 3 + .../model_2_1_4-solution000002.solution | 3 + .../set_card_00/expected/model_2_1_4.eprime | 35 + .../model_2_2_1-solution000001.solution | 3 + .../model_2_2_1-solution000002.solution | 3 + .../set_card_00/expected/model_2_2_1.eprime | 16 + .../model_2_2_2-solution000001.solution | 3 + .../model_2_2_2-solution000002.solution | 3 + .../set_card_00/expected/model_2_2_2.eprime | 11 + .../model_2_2_3-solution000001.solution | 3 + .../model_2_2_3-solution000002.solution | 3 + .../set_card_00/expected/model_2_2_3.eprime | 26 + .../model_2_2_4-solution000001.solution | 3 + .../model_2_2_4-solution000002.solution | 3 + .../set_card_00/expected/model_2_2_4.eprime | 26 + .../model_2_3_1-solution000001.solution | 3 + .../model_2_3_1-solution000002.solution | 3 + .../set_card_00/expected/model_2_3_1.eprime | 38 + .../model_2_3_2-solution000001.solution | 3 + .../model_2_3_2-solution000002.solution | 3 + .../set_card_00/expected/model_2_3_2.eprime | 26 + .../model_2_3_4-solution000001.solution | 3 + .../model_2_3_4-solution000002.solution | 3 + .../set_card_00/expected/model_2_3_4.eprime | 54 + .../model_2_4_1-solution000001.solution | 3 + .../model_2_4_1-solution000002.solution | 3 + .../set_card_00/expected/model_2_4_1.eprime | 37 + .../model_2_4_2-solution000001.solution | 3 + .../model_2_4_2-solution000002.solution | 3 + .../set_card_00/expected/model_2_4_2.eprime | 26 + .../model_2_4_3-solution000001.solution | 3 + .../model_2_4_3-solution000002.solution | 3 + .../set_card_00/expected/model_2_4_3.eprime | 53 + .../model_3_1_1-solution000001.solution | 3 + .../model_3_1_1-solution000002.solution | 3 + .../set_card_00/expected/model_3_1_1.eprime | 17 + .../model_3_1_2-solution000001.solution | 3 + .../model_3_1_2-solution000002.solution | 3 + .../set_card_00/expected/model_3_1_2.eprime | 36 + .../model_3_1_4-solution000001.solution | 3 + .../model_3_1_4-solution000002.solution | 3 + .../set_card_00/expected/model_3_1_4.eprime | 40 + .../model_3_2_1-solution000001.solution | 3 + .../model_3_2_1-solution000002.solution | 3 + .../set_card_00/expected/model_3_2_1.eprime | 37 + .../model_3_2_2-solution000001.solution | 3 + .../model_3_2_2-solution000002.solution | 3 + .../set_card_00/expected/model_3_2_2.eprime | 25 + .../model_3_2_4-solution000001.solution | 3 + .../model_3_2_4-solution000002.solution | 3 + .../set_card_00/expected/model_3_2_4.eprime | 53 + .../model_3_3_1-solution000001.solution | 3 + .../model_3_3_1-solution000002.solution | 3 + .../set_card_00/expected/model_3_3_1.eprime | 19 + .../model_3_3_2-solution000001.solution | 3 + .../model_3_3_2-solution000002.solution | 3 + .../set_card_00/expected/model_3_3_2.eprime | 26 + .../model_3_3_3-solution000001.solution | 3 + .../model_3_3_3-solution000002.solution | 3 + .../set_card_00/expected/model_3_3_3.eprime | 13 + .../model_3_3_4-solution000001.solution | 3 + .../model_3_3_4-solution000002.solution | 3 + .../set_card_00/expected/model_3_3_4.eprime | 30 + .../model_3_4_1-solution000001.solution | 3 + .../model_3_4_1-solution000002.solution | 3 + .../set_card_00/expected/model_3_4_1.eprime | 42 + .../model_3_4_2-solution000001.solution | 3 + .../model_3_4_2-solution000002.solution | 3 + .../set_card_00/expected/model_3_4_2.eprime | 53 + .../model_3_4_3-solution000001.solution | 3 + .../model_3_4_3-solution000002.solution | 3 + .../set_card_00/expected/model_3_4_3.eprime | 30 + .../model_4_1_1-solution000001.solution | 3 + .../model_4_1_1-solution000002.solution | 3 + .../set_card_00/expected/model_4_1_1.eprime | 17 + .../model_4_1_2-solution000001.solution | 3 + .../model_4_1_2-solution000002.solution | 3 + .../set_card_00/expected/model_4_1_2.eprime | 35 + .../model_4_1_3-solution000001.solution | 3 + .../model_4_1_3-solution000002.solution | 3 + .../set_card_00/expected/model_4_1_3.eprime | 40 + .../model_4_2_1-solution000001.solution | 3 + .../model_4_2_1-solution000002.solution | 3 + .../set_card_00/expected/model_4_2_1.eprime | 37 + .../model_4_2_2-solution000001.solution | 3 + .../model_4_2_2-solution000002.solution | 3 + .../set_card_00/expected/model_4_2_2.eprime | 26 + .../model_4_2_3-solution000001.solution | 3 + .../model_4_2_3-solution000002.solution | 3 + .../set_card_00/expected/model_4_2_3.eprime | 53 + .../model_4_3_1-solution000001.solution | 3 + .../model_4_3_1-solution000002.solution | 3 + .../set_card_00/expected/model_4_3_1.eprime | 42 + .../model_4_3_2-solution000001.solution | 3 + .../model_4_3_2-solution000002.solution | 3 + .../set_card_00/expected/model_4_3_2.eprime | 53 + .../model_4_3_3-solution000001.solution | 3 + .../model_4_3_3-solution000002.solution | 3 + .../set_card_00/expected/model_4_3_3.eprime | 30 + .../model_4_4_1-solution000001.solution | 3 + .../model_4_4_1-solution000002.solution | 3 + .../set_card_00/expected/model_4_4_1.eprime | 19 + .../model_4_4_2-solution000001.solution | 3 + .../model_4_4_2-solution000002.solution | 3 + .../set_card_00/expected/model_4_4_2.eprime | 26 + .../model_4_4_3-solution000001.solution | 3 + .../model_4_4_3-solution000002.solution | 3 + .../set_card_00/expected/model_4_4_3.eprime | 30 + .../model_4_4_4-solution000001.solution | 3 + .../model_4_4_4-solution000002.solution | 3 + .../set_card_00/expected/model_4_4_4.eprime | 13 + .../set_card_02/expected/model_1_1_2.eprime | 8 - .../set_card_02/expected/model_1_2_1.eprime | 8 - .../set_card_02/expected/model_1_2_2.eprime | 12 - .../set_card_02/expected/model_2_1_1.eprime | 8 - .../set_card_02/expected/model_2_1_2.eprime | 12 - .../set_card_02/expected/model_2_2_1.eprime | 8 - .../set_card_02/expected/model_2_2_2.eprime | 5 - .../expected/model_2.eprime | 5 +- .../expected/model_3.eprime | 3 +- .../expected/model_4.eprime | 3 +- .../model_1_1_1_1-solution000001.solution | 4 + .../model_1_1_1_1-solution000002.solution | 4 + .../model_1_1_1_1-solution000003.solution | 4 + .../typed01/expected/model_1_1_1_1.eprime | 7 + .../model_1_1_1_2-solution000001.solution | 4 + .../model_1_1_1_2-solution000002.solution | 4 + .../model_1_1_1_2-solution000003.solution | 4 + .../typed01/expected/model_1_1_1_2.eprime | 11 + .../model_1_1_1_3-solution000001.solution | 4 + .../model_1_1_1_3-solution000002.solution | 4 + .../model_1_1_1_3-solution000003.solution | 4 + .../typed01/expected/model_1_1_1_3.eprime | 13 + .../model_1_1_1_4-solution000001.solution | 4 + .../model_1_1_1_4-solution000002.solution | 4 + .../model_1_1_1_4-solution000003.solution | 4 + .../typed01/expected/model_1_1_1_4.eprime | 13 + .../model_1_1_2_1-solution000001.solution | 4 + .../model_1_1_2_1-solution000002.solution | 4 + .../model_1_1_2_1-solution000003.solution | 4 + .../typed01/expected/model_1_1_2_1.eprime | 11 + .../model_1_1_2_2-solution000001.solution | 4 + .../model_1_1_2_2-solution000002.solution | 4 + .../model_1_1_2_2-solution000003.solution | 4 + .../typed01/expected/model_1_1_2_2.eprime | 14 + .../model_1_1_2_3-solution000001.solution | 4 + .../model_1_1_2_3-solution000002.solution | 4 + .../model_1_1_2_3-solution000003.solution | 4 + .../typed01/expected/model_1_1_2_3.eprime | 18 + .../model_1_1_2_4-solution000001.solution | 4 + .../model_1_1_2_4-solution000002.solution | 4 + .../model_1_1_2_4-solution000003.solution | 4 + .../typed01/expected/model_1_1_2_4.eprime | 18 + .../model_1_1_3_1-solution000001.solution | 4 + .../model_1_1_3_1-solution000002.solution | 4 + .../model_1_1_3_1-solution000003.solution | 4 + .../typed01/expected/model_1_1_3_1.eprime | 13 + .../model_1_1_3_2-solution000001.solution | 4 + .../model_1_1_3_2-solution000002.solution | 4 + .../model_1_1_3_2-solution000003.solution | 4 + .../typed01/expected/model_1_1_3_2.eprime | 18 + .../model_1_1_3_3-solution000001.solution | 4 + .../model_1_1_3_3-solution000002.solution | 4 + .../model_1_1_3_3-solution000003.solution | 4 + .../typed01/expected/model_1_1_3_3.eprime | 20 + .../model_1_1_3_4-solution000001.solution | 4 + .../model_1_1_3_4-solution000002.solution | 4 + .../model_1_1_3_4-solution000003.solution | 4 + .../typed01/expected/model_1_1_3_4.eprime | 20 + .../model_1_1_4_1-solution000001.solution | 4 + .../model_1_1_4_1-solution000002.solution | 4 + .../model_1_1_4_1-solution000003.solution | 4 + .../typed01/expected/model_1_1_4_1.eprime | 13 + .../model_1_1_4_2-solution000001.solution | 4 + .../model_1_1_4_2-solution000002.solution | 4 + .../model_1_1_4_2-solution000003.solution | 4 + .../typed01/expected/model_1_1_4_2.eprime | 18 + .../model_1_1_4_3-solution000001.solution | 4 + .../model_1_1_4_3-solution000002.solution | 4 + .../model_1_1_4_3-solution000003.solution | 4 + .../typed01/expected/model_1_1_4_3.eprime | 20 + .../model_1_1_4_4-solution000001.solution | 4 + .../model_1_1_4_4-solution000002.solution | 4 + .../model_1_1_4_4-solution000003.solution | 4 + .../typed01/expected/model_1_1_4_4.eprime | 20 + .../model_1_2_1_1-solution000001.solution | 4 + .../model_1_2_1_1-solution000002.solution | 4 + .../model_1_2_1_1-solution000003.solution | 4 + .../typed01/expected/model_1_2_1_1.eprime | 11 + .../model_1_2_1_2-solution000001.solution | 4 + .../model_1_2_1_2-solution000002.solution | 4 + .../model_1_2_1_2-solution000003.solution | 4 + .../typed01/expected/model_1_2_1_2.eprime | 7 + .../model_1_2_1_3-solution000001.solution | 4 + .../model_1_2_1_3-solution000002.solution | 4 + .../model_1_2_1_3-solution000003.solution | 4 + .../typed01/expected/model_1_2_1_3.eprime | 16 + .../model_1_2_1_4-solution000001.solution | 4 + .../model_1_2_1_4-solution000002.solution | 4 + .../model_1_2_1_4-solution000003.solution | 4 + .../typed01/expected/model_1_2_1_4.eprime | 16 + .../model_1_2_2_1-solution000001.solution | 4 + .../model_1_2_2_1-solution000002.solution | 4 + .../model_1_2_2_1-solution000003.solution | 4 + .../typed01/expected/model_1_2_2_1.eprime | 14 + .../model_1_2_2_2-solution000001.solution | 4 + .../model_1_2_2_2-solution000002.solution | 4 + .../model_1_2_2_2-solution000003.solution | 4 + .../typed01/expected/model_1_2_2_2.eprime | 11 + .../model_1_2_2_3-solution000001.solution | 4 + .../model_1_2_2_3-solution000002.solution | 4 + .../model_1_2_2_3-solution000003.solution | 4 + .../typed01/expected/model_1_2_2_3.eprime | 20 + .../model_1_2_2_4-solution000001.solution | 4 + .../model_1_2_2_4-solution000002.solution | 4 + .../model_1_2_2_4-solution000003.solution | 4 + .../typed01/expected/model_1_2_2_4.eprime | 20 + .../model_1_2_3_1-solution000001.solution | 4 + .../model_1_2_3_1-solution000002.solution | 4 + .../model_1_2_3_1-solution000003.solution | 4 + .../typed01/expected/model_1_2_3_1.eprime | 18 + .../model_1_2_3_2-solution000001.solution | 4 + .../model_1_2_3_2-solution000002.solution | 4 + .../model_1_2_3_2-solution000003.solution | 4 + .../typed01/expected/model_1_2_3_2.eprime | 14 + .../model_1_2_3_3-solution000001.solution | 4 + .../model_1_2_3_3-solution000002.solution | 4 + .../model_1_2_3_3-solution000003.solution | 4 + .../typed01/expected/model_1_2_3_3.eprime | 22 + .../model_1_2_3_4-solution000001.solution | 4 + .../model_1_2_3_4-solution000002.solution | 4 + .../model_1_2_3_4-solution000003.solution | 4 + .../typed01/expected/model_1_2_3_4.eprime | 22 + .../model_1_2_4_1-solution000001.solution | 4 + .../model_1_2_4_1-solution000002.solution | 4 + .../model_1_2_4_1-solution000003.solution | 4 + .../typed01/expected/model_1_2_4_1.eprime | 18 + .../model_1_2_4_2-solution000001.solution | 4 + .../model_1_2_4_2-solution000002.solution | 4 + .../model_1_2_4_2-solution000003.solution | 4 + .../typed01/expected/model_1_2_4_2.eprime | 14 + .../model_1_2_4_3-solution000001.solution | 4 + .../model_1_2_4_3-solution000002.solution | 4 + .../model_1_2_4_3-solution000003.solution | 4 + .../typed01/expected/model_1_2_4_3.eprime | 22 + .../model_1_2_4_4-solution000001.solution | 4 + .../model_1_2_4_4-solution000002.solution | 4 + .../model_1_2_4_4-solution000003.solution | 4 + .../typed01/expected/model_1_2_4_4.eprime | 22 + .../model_1_3_1_1-solution000001.solution | 4 + .../model_1_3_1_1-solution000002.solution | 4 + .../model_1_3_1_1-solution000003.solution | 4 + .../typed01/expected/model_1_3_1_1.eprime | 13 + .../model_1_3_1_2-solution000001.solution | 4 + .../model_1_3_1_2-solution000002.solution | 4 + .../model_1_3_1_2-solution000003.solution | 4 + .../typed01/expected/model_1_3_1_2.eprime | 16 + .../model_1_3_1_3-solution000001.solution | 4 + .../model_1_3_1_3-solution000002.solution | 4 + .../model_1_3_1_3-solution000003.solution | 4 + .../typed01/expected/model_1_3_1_3.eprime | 10 + .../model_1_3_1_4-solution000001.solution | 4 + .../model_1_3_1_4-solution000002.solution | 4 + .../model_1_3_1_4-solution000003.solution | 4 + .../typed01/expected/model_1_3_1_4.eprime | 20 + .../model_1_3_2_1-solution000001.solution | 4 + .../model_1_3_2_1-solution000002.solution | 4 + .../model_1_3_2_1-solution000003.solution | 4 + .../typed01/expected/model_1_3_2_1.eprime | 18 + .../model_1_3_2_2-solution000001.solution | 4 + .../model_1_3_2_2-solution000002.solution | 4 + .../model_1_3_2_2-solution000003.solution | 4 + .../typed01/expected/model_1_3_2_2.eprime | 20 + .../model_1_3_2_3-solution000001.solution | 4 + .../model_1_3_2_3-solution000002.solution | 4 + .../model_1_3_2_3-solution000003.solution | 4 + .../typed01/expected/model_1_3_2_3.eprime | 14 + .../model_1_3_2_4-solution000001.solution | 4 + .../model_1_3_2_4-solution000002.solution | 4 + .../model_1_3_2_4-solution000003.solution | 4 + .../typed01/expected/model_1_3_2_4.eprime | 23 + .../model_1_3_3_1-solution000001.solution | 4 + .../model_1_3_3_1-solution000002.solution | 4 + .../model_1_3_3_1-solution000003.solution | 4 + .../typed01/expected/model_1_3_3_1.eprime | 20 + .../model_1_3_3_2-solution000001.solution | 4 + .../model_1_3_3_2-solution000002.solution | 4 + .../model_1_3_3_2-solution000003.solution | 4 + .../typed01/expected/model_1_3_3_2.eprime | 22 + .../model_1_3_3_3-solution000001.solution | 4 + .../model_1_3_3_3-solution000002.solution | 4 + .../model_1_3_3_3-solution000003.solution | 4 + .../typed01/expected/model_1_3_3_3.eprime | 17 + .../model_1_3_3_4-solution000001.solution | 4 + .../model_1_3_3_4-solution000002.solution | 4 + .../model_1_3_3_4-solution000003.solution | 4 + .../typed01/expected/model_1_3_3_4.eprime | 26 + .../model_1_3_4_1-solution000001.solution | 4 + .../model_1_3_4_1-solution000002.solution | 4 + .../model_1_3_4_1-solution000003.solution | 4 + .../typed01/expected/model_1_3_4_1.eprime | 20 + .../model_1_3_4_2-solution000001.solution | 4 + .../model_1_3_4_2-solution000002.solution | 4 + .../model_1_3_4_2-solution000003.solution | 4 + .../typed01/expected/model_1_3_4_2.eprime | 22 + .../model_1_3_4_3-solution000001.solution | 4 + .../model_1_3_4_3-solution000002.solution | 4 + .../model_1_3_4_3-solution000003.solution | 4 + .../typed01/expected/model_1_3_4_3.eprime | 17 + .../model_1_3_4_4-solution000001.solution | 4 + .../model_1_3_4_4-solution000002.solution | 4 + .../model_1_3_4_4-solution000003.solution | 4 + .../typed01/expected/model_1_3_4_4.eprime | 26 + .../model_1_4_1_1-solution000001.solution | 4 + .../model_1_4_1_1-solution000002.solution | 4 + .../model_1_4_1_1-solution000003.solution | 4 + .../typed01/expected/model_1_4_1_1.eprime | 13 + .../model_1_4_1_2-solution000001.solution | 4 + .../model_1_4_1_2-solution000002.solution | 4 + .../model_1_4_1_2-solution000003.solution | 4 + .../typed01/expected/model_1_4_1_2.eprime | 16 + .../model_1_4_1_3-solution000001.solution | 4 + .../model_1_4_1_3-solution000002.solution | 4 + .../model_1_4_1_3-solution000003.solution | 4 + .../typed01/expected/model_1_4_1_3.eprime | 20 + .../model_1_4_1_4-solution000001.solution | 4 + .../model_1_4_1_4-solution000002.solution | 4 + .../model_1_4_1_4-solution000003.solution | 4 + .../typed01/expected/model_1_4_1_4.eprime | 10 + .../model_1_4_2_1-solution000001.solution | 4 + .../model_1_4_2_1-solution000002.solution | 4 + .../model_1_4_2_1-solution000003.solution | 4 + .../typed01/expected/model_1_4_2_1.eprime | 18 + .../model_1_4_2_2-solution000001.solution | 4 + .../model_1_4_2_2-solution000002.solution | 4 + .../model_1_4_2_2-solution000003.solution | 4 + .../typed01/expected/model_1_4_2_2.eprime | 20 + .../model_1_4_2_3-solution000001.solution | 4 + .../model_1_4_2_3-solution000002.solution | 4 + .../model_1_4_2_3-solution000003.solution | 4 + .../typed01/expected/model_1_4_2_3.eprime | 23 + .../model_1_4_2_4-solution000001.solution | 4 + .../model_1_4_2_4-solution000002.solution | 4 + .../model_1_4_2_4-solution000003.solution | 4 + .../typed01/expected/model_1_4_2_4.eprime | 14 + .../model_1_4_3_1-solution000001.solution | 4 + .../model_1_4_3_1-solution000002.solution | 4 + .../model_1_4_3_1-solution000003.solution | 4 + .../typed01/expected/model_1_4_3_1.eprime | 20 + .../model_1_4_3_2-solution000001.solution | 4 + .../model_1_4_3_2-solution000002.solution | 4 + .../model_1_4_3_2-solution000003.solution | 4 + .../typed01/expected/model_1_4_3_2.eprime | 22 + .../model_1_4_3_3-solution000001.solution | 4 + .../model_1_4_3_3-solution000002.solution | 4 + .../model_1_4_3_3-solution000003.solution | 4 + .../typed01/expected/model_1_4_3_3.eprime | 26 + .../model_1_4_3_4-solution000001.solution | 4 + .../model_1_4_3_4-solution000002.solution | 4 + .../model_1_4_3_4-solution000003.solution | 4 + .../typed01/expected/model_1_4_3_4.eprime | 17 + .../model_1_4_4_1-solution000001.solution | 4 + .../model_1_4_4_1-solution000002.solution | 4 + .../model_1_4_4_1-solution000003.solution | 4 + .../typed01/expected/model_1_4_4_1.eprime | 20 + .../model_1_4_4_2-solution000001.solution | 4 + .../model_1_4_4_2-solution000002.solution | 4 + .../model_1_4_4_2-solution000003.solution | 4 + .../typed01/expected/model_1_4_4_2.eprime | 22 + .../model_1_4_4_3-solution000001.solution | 4 + .../model_1_4_4_3-solution000002.solution | 4 + .../model_1_4_4_3-solution000003.solution | 4 + .../typed01/expected/model_1_4_4_3.eprime | 26 + .../model_1_4_4_4-solution000001.solution | 4 + .../model_1_4_4_4-solution000002.solution | 4 + .../model_1_4_4_4-solution000003.solution | 4 + .../typed01/expected/model_1_4_4_4.eprime | 17 + .../model_2_1_1_1-solution000001.solution | 4 + .../model_2_1_1_1-solution000002.solution | 4 + .../model_2_1_1_1-solution000003.solution | 4 + .../typed01/expected/model_2_1_1_1.eprime | 11 + .../model_2_1_1_2-solution000001.solution | 4 + .../model_2_1_1_2-solution000002.solution | 4 + .../model_2_1_1_2-solution000003.solution | 4 + .../typed01/expected/model_2_1_1_2.eprime | 14 + .../model_2_1_1_3-solution000001.solution | 4 + .../model_2_1_1_3-solution000002.solution | 4 + .../model_2_1_1_3-solution000003.solution | 4 + .../typed01/expected/model_2_1_1_3.eprime | 18 + .../model_2_1_1_4-solution000001.solution | 4 + .../model_2_1_1_4-solution000002.solution | 4 + .../model_2_1_1_4-solution000003.solution | 4 + .../typed01/expected/model_2_1_1_4.eprime | 18 + .../model_2_1_2_1-solution000001.solution | 4 + .../model_2_1_2_1-solution000002.solution | 4 + .../model_2_1_2_1-solution000003.solution | 4 + .../typed01/expected/model_2_1_2_1.eprime | 7 + .../model_2_1_2_2-solution000001.solution | 4 + .../model_2_1_2_2-solution000002.solution | 4 + .../model_2_1_2_2-solution000003.solution | 4 + .../typed01/expected/model_2_1_2_2.eprime | 11 + .../model_2_1_2_3-solution000001.solution | 4 + .../model_2_1_2_3-solution000002.solution | 4 + .../model_2_1_2_3-solution000003.solution | 4 + .../typed01/expected/model_2_1_2_3.eprime | 14 + .../model_2_1_2_4-solution000001.solution | 4 + .../model_2_1_2_4-solution000002.solution | 4 + .../model_2_1_2_4-solution000003.solution | 4 + .../typed01/expected/model_2_1_2_4.eprime | 14 + .../model_2_1_3_1-solution000001.solution | 4 + .../model_2_1_3_1-solution000002.solution | 4 + .../model_2_1_3_1-solution000003.solution | 4 + .../typed01/expected/model_2_1_3_1.eprime | 16 + .../model_2_1_3_2-solution000001.solution | 4 + .../model_2_1_3_2-solution000002.solution | 4 + .../model_2_1_3_2-solution000003.solution | 4 + .../typed01/expected/model_2_1_3_2.eprime | 20 + .../model_2_1_3_3-solution000001.solution | 4 + .../model_2_1_3_3-solution000002.solution | 4 + .../model_2_1_3_3-solution000003.solution | 4 + .../typed01/expected/model_2_1_3_3.eprime | 22 + .../model_2_1_3_4-solution000001.solution | 4 + .../model_2_1_3_4-solution000002.solution | 4 + .../model_2_1_3_4-solution000003.solution | 4 + .../typed01/expected/model_2_1_3_4.eprime | 22 + .../model_2_1_4_1-solution000001.solution | 4 + .../model_2_1_4_1-solution000002.solution | 4 + .../model_2_1_4_1-solution000003.solution | 4 + .../typed01/expected/model_2_1_4_1.eprime | 16 + .../model_2_1_4_2-solution000001.solution | 4 + .../model_2_1_4_2-solution000002.solution | 4 + .../model_2_1_4_2-solution000003.solution | 4 + .../typed01/expected/model_2_1_4_2.eprime | 20 + .../model_2_1_4_3-solution000001.solution | 4 + .../model_2_1_4_3-solution000002.solution | 4 + .../model_2_1_4_3-solution000003.solution | 4 + .../typed01/expected/model_2_1_4_3.eprime | 22 + .../model_2_1_4_4-solution000001.solution | 4 + .../model_2_1_4_4-solution000002.solution | 4 + .../model_2_1_4_4-solution000003.solution | 4 + .../typed01/expected/model_2_1_4_4.eprime | 22 + .../model_2_2_1_1-solution000001.solution | 4 + .../model_2_2_1_1-solution000002.solution | 4 + .../model_2_2_1_1-solution000003.solution | 4 + .../typed01/expected/model_2_2_1_1.eprime | 16 + .../model_2_2_1_2-solution000001.solution | 4 + .../model_2_2_1_2-solution000002.solution | 4 + .../model_2_2_1_2-solution000003.solution | 4 + .../typed01/expected/model_2_2_1_2.eprime | 13 + .../model_2_2_1_3-solution000001.solution | 4 + .../model_2_2_1_3-solution000002.solution | 4 + .../model_2_2_1_3-solution000003.solution | 4 + .../typed01/expected/model_2_2_1_3.eprime | 22 + .../model_2_2_1_4-solution000001.solution | 4 + .../model_2_2_1_4-solution000002.solution | 4 + .../model_2_2_1_4-solution000003.solution | 4 + .../typed01/expected/model_2_2_1_4.eprime | 22 + .../model_2_2_2_1-solution000001.solution | 4 + .../model_2_2_2_1-solution000002.solution | 4 + .../model_2_2_2_1-solution000003.solution | 4 + .../typed01/expected/model_2_2_2_1.eprime | 13 + .../model_2_2_2_2-solution000001.solution | 4 + .../model_2_2_2_2-solution000002.solution | 4 + .../model_2_2_2_2-solution000003.solution | 4 + .../typed01/expected/model_2_2_2_2.eprime | 10 + .../model_2_2_2_3-solution000001.solution | 4 + .../model_2_2_2_3-solution000002.solution | 4 + .../model_2_2_2_3-solution000003.solution | 4 + .../typed01/expected/model_2_2_2_3.eprime | 19 + .../model_2_2_2_4-solution000001.solution | 4 + .../model_2_2_2_4-solution000002.solution | 4 + .../model_2_2_2_4-solution000003.solution | 4 + .../typed01/expected/model_2_2_2_4.eprime | 19 + .../model_2_2_3_1-solution000001.solution | 4 + .../model_2_2_3_1-solution000002.solution | 4 + .../model_2_2_3_1-solution000003.solution | 4 + .../typed01/expected/model_2_2_3_1.eprime | 22 + .../model_2_2_3_2-solution000001.solution | 4 + .../model_2_2_3_2-solution000002.solution | 4 + .../model_2_2_3_2-solution000003.solution | 4 + .../typed01/expected/model_2_2_3_2.eprime | 19 + .../model_2_2_3_3-solution000001.solution | 4 + .../model_2_2_3_3-solution000002.solution | 4 + .../model_2_2_3_3-solution000003.solution | 4 + .../typed01/expected/model_2_2_3_3.eprime | 26 + .../model_2_2_3_4-solution000001.solution | 4 + .../model_2_2_3_4-solution000002.solution | 4 + .../model_2_2_3_4-solution000003.solution | 4 + .../typed01/expected/model_2_2_3_4.eprime | 26 + .../model_2_2_4_1-solution000001.solution | 4 + .../model_2_2_4_1-solution000002.solution | 4 + .../model_2_2_4_1-solution000003.solution | 4 + .../typed01/expected/model_2_2_4_1.eprime | 22 + .../model_2_2_4_2-solution000001.solution | 4 + .../model_2_2_4_2-solution000002.solution | 4 + .../model_2_2_4_2-solution000003.solution | 4 + .../typed01/expected/model_2_2_4_2.eprime | 19 + .../model_2_2_4_3-solution000001.solution | 4 + .../model_2_2_4_3-solution000002.solution | 4 + .../model_2_2_4_3-solution000003.solution | 4 + .../typed01/expected/model_2_2_4_3.eprime | 26 + .../model_2_2_4_4-solution000001.solution | 4 + .../model_2_2_4_4-solution000002.solution | 4 + .../model_2_2_4_4-solution000003.solution | 4 + .../typed01/expected/model_2_2_4_4.eprime | 26 + .../model_2_3_1_1-solution000001.solution | 4 + .../model_2_3_1_1-solution000002.solution | 4 + .../model_2_3_1_1-solution000003.solution | 4 + .../typed01/expected/model_2_3_1_1.eprime | 20 + .../model_2_3_1_2-solution000001.solution | 4 + .../model_2_3_1_2-solution000002.solution | 4 + .../model_2_3_1_2-solution000003.solution | 4 + .../typed01/expected/model_2_3_1_2.eprime | 22 + .../model_2_3_1_3-solution000001.solution | 4 + .../model_2_3_1_3-solution000002.solution | 4 + .../model_2_3_1_3-solution000003.solution | 4 + .../typed01/expected/model_2_3_1_3.eprime | 16 + .../model_2_3_1_4-solution000001.solution | 4 + .../model_2_3_1_4-solution000002.solution | 4 + .../model_2_3_1_4-solution000003.solution | 4 + .../typed01/expected/model_2_3_1_4.eprime | 25 + .../model_2_3_2_1-solution000001.solution | 4 + .../model_2_3_2_1-solution000002.solution | 4 + .../model_2_3_2_1-solution000003.solution | 4 + .../typed01/expected/model_2_3_2_1.eprime | 16 + .../model_2_3_2_2-solution000001.solution | 4 + .../model_2_3_2_2-solution000002.solution | 4 + .../model_2_3_2_2-solution000003.solution | 4 + .../typed01/expected/model_2_3_2_2.eprime | 19 + .../model_2_3_2_3-solution000001.solution | 4 + .../model_2_3_2_3-solution000002.solution | 4 + .../model_2_3_2_3-solution000003.solution | 4 + .../typed01/expected/model_2_3_2_3.eprime | 12 + .../model_2_3_2_4-solution000001.solution | 4 + .../model_2_3_2_4-solution000002.solution | 4 + .../model_2_3_2_4-solution000003.solution | 4 + .../typed01/expected/model_2_3_2_4.eprime | 22 + .../model_2_3_3_1-solution000001.solution | 4 + .../model_2_3_3_1-solution000002.solution | 4 + .../model_2_3_3_1-solution000003.solution | 4 + .../typed01/expected/model_2_3_3_1.eprime | 24 + .../model_2_3_3_2-solution000001.solution | 4 + .../model_2_3_3_2-solution000002.solution | 4 + .../model_2_3_3_2-solution000003.solution | 4 + .../typed01/expected/model_2_3_3_2.eprime | 26 + .../model_2_3_3_3-solution000001.solution | 4 + .../model_2_3_3_3-solution000002.solution | 4 + .../model_2_3_3_3-solution000003.solution | 4 + .../typed01/expected/model_2_3_3_3.eprime | 21 + .../model_2_3_3_4-solution000001.solution | 4 + .../model_2_3_3_4-solution000002.solution | 4 + .../model_2_3_3_4-solution000003.solution | 4 + .../typed01/expected/model_2_3_3_4.eprime | 30 + .../model_2_3_4_1-solution000001.solution | 4 + .../model_2_3_4_1-solution000002.solution | 4 + .../model_2_3_4_1-solution000003.solution | 4 + .../typed01/expected/model_2_3_4_1.eprime | 24 + .../model_2_3_4_2-solution000001.solution | 4 + .../model_2_3_4_2-solution000002.solution | 4 + .../model_2_3_4_2-solution000003.solution | 4 + .../typed01/expected/model_2_3_4_2.eprime | 26 + .../model_2_3_4_3-solution000001.solution | 4 + .../model_2_3_4_3-solution000002.solution | 4 + .../model_2_3_4_3-solution000003.solution | 4 + .../typed01/expected/model_2_3_4_3.eprime | 21 + .../model_2_3_4_4-solution000001.solution | 4 + .../model_2_3_4_4-solution000002.solution | 4 + .../model_2_3_4_4-solution000003.solution | 4 + .../typed01/expected/model_2_3_4_4.eprime | 30 + .../model_2_4_1_1-solution000001.solution | 4 + .../model_2_4_1_1-solution000002.solution | 4 + .../model_2_4_1_1-solution000003.solution | 4 + .../typed01/expected/model_2_4_1_1.eprime | 20 + .../model_2_4_1_2-solution000001.solution | 4 + .../model_2_4_1_2-solution000002.solution | 4 + .../model_2_4_1_2-solution000003.solution | 4 + .../typed01/expected/model_2_4_1_2.eprime | 22 + .../model_2_4_1_3-solution000001.solution | 4 + .../model_2_4_1_3-solution000002.solution | 4 + .../model_2_4_1_3-solution000003.solution | 4 + .../typed01/expected/model_2_4_1_3.eprime | 25 + .../model_2_4_1_4-solution000001.solution | 4 + .../model_2_4_1_4-solution000002.solution | 4 + .../model_2_4_1_4-solution000003.solution | 4 + .../typed01/expected/model_2_4_1_4.eprime | 16 + .../model_2_4_2_1-solution000001.solution | 4 + .../model_2_4_2_1-solution000002.solution | 4 + .../model_2_4_2_1-solution000003.solution | 4 + .../typed01/expected/model_2_4_2_1.eprime | 16 + .../model_2_4_2_2-solution000001.solution | 4 + .../model_2_4_2_2-solution000002.solution | 4 + .../model_2_4_2_2-solution000003.solution | 4 + .../typed01/expected/model_2_4_2_2.eprime | 19 + .../model_2_4_2_3-solution000001.solution | 4 + .../model_2_4_2_3-solution000002.solution | 4 + .../model_2_4_2_3-solution000003.solution | 4 + .../typed01/expected/model_2_4_2_3.eprime | 22 + .../model_2_4_2_4-solution000001.solution | 4 + .../model_2_4_2_4-solution000002.solution | 4 + .../model_2_4_2_4-solution000003.solution | 4 + .../typed01/expected/model_2_4_2_4.eprime | 12 + .../model_2_4_3_1-solution000001.solution | 4 + .../model_2_4_3_1-solution000002.solution | 4 + .../model_2_4_3_1-solution000003.solution | 4 + .../typed01/expected/model_2_4_3_1.eprime | 24 + .../model_2_4_3_2-solution000001.solution | 4 + .../model_2_4_3_2-solution000002.solution | 4 + .../model_2_4_3_2-solution000003.solution | 4 + .../typed01/expected/model_2_4_3_2.eprime | 26 + .../model_2_4_3_3-solution000001.solution | 4 + .../model_2_4_3_3-solution000002.solution | 4 + .../model_2_4_3_3-solution000003.solution | 4 + .../typed01/expected/model_2_4_3_3.eprime | 30 + .../model_2_4_3_4-solution000001.solution | 4 + .../model_2_4_3_4-solution000002.solution | 4 + .../model_2_4_3_4-solution000003.solution | 4 + .../typed01/expected/model_2_4_3_4.eprime | 21 + .../model_2_4_4_1-solution000001.solution | 4 + .../model_2_4_4_1-solution000002.solution | 4 + .../model_2_4_4_1-solution000003.solution | 4 + .../typed01/expected/model_2_4_4_1.eprime | 24 + .../model_2_4_4_2-solution000001.solution | 4 + .../model_2_4_4_2-solution000002.solution | 4 + .../model_2_4_4_2-solution000003.solution | 4 + .../typed01/expected/model_2_4_4_2.eprime | 26 + .../model_2_4_4_3-solution000001.solution | 4 + .../model_2_4_4_3-solution000002.solution | 4 + .../model_2_4_4_3-solution000003.solution | 4 + .../typed01/expected/model_2_4_4_3.eprime | 30 + .../model_2_4_4_4-solution000001.solution | 4 + .../model_2_4_4_4-solution000002.solution | 4 + .../model_2_4_4_4-solution000003.solution | 4 + .../typed01/expected/model_2_4_4_4.eprime | 21 + .../model_3_1_1_1-solution000001.solution | 4 + .../model_3_1_1_1-solution000002.solution | 4 + .../model_3_1_1_1-solution000003.solution | 4 + .../typed01/expected/model_3_1_1_1.eprime | 13 + .../model_3_1_1_2-solution000001.solution | 4 + .../model_3_1_1_2-solution000002.solution | 4 + .../model_3_1_1_2-solution000003.solution | 4 + .../typed01/expected/model_3_1_1_2.eprime | 18 + .../model_3_1_1_3-solution000001.solution | 4 + .../model_3_1_1_3-solution000002.solution | 4 + .../model_3_1_1_3-solution000003.solution | 4 + .../typed01/expected/model_3_1_1_3.eprime | 20 + .../model_3_1_1_4-solution000001.solution | 4 + .../model_3_1_1_4-solution000002.solution | 4 + .../model_3_1_1_4-solution000003.solution | 4 + .../typed01/expected/model_3_1_1_4.eprime | 20 + .../model_3_1_2_1-solution000001.solution | 4 + .../model_3_1_2_1-solution000002.solution | 4 + .../model_3_1_2_1-solution000003.solution | 4 + .../typed01/expected/model_3_1_2_1.eprime | 16 + .../model_3_1_2_2-solution000001.solution | 4 + .../model_3_1_2_2-solution000002.solution | 4 + .../model_3_1_2_2-solution000003.solution | 4 + .../typed01/expected/model_3_1_2_2.eprime | 20 + .../model_3_1_2_3-solution000001.solution | 4 + .../model_3_1_2_3-solution000002.solution | 4 + .../model_3_1_2_3-solution000003.solution | 4 + .../typed01/expected/model_3_1_2_3.eprime | 22 + .../model_3_1_2_4-solution000001.solution | 4 + .../model_3_1_2_4-solution000002.solution | 4 + .../model_3_1_2_4-solution000003.solution | 4 + .../typed01/expected/model_3_1_2_4.eprime | 22 + .../model_3_1_3_1-solution000001.solution | 4 + .../model_3_1_3_1-solution000002.solution | 4 + .../model_3_1_3_1-solution000003.solution | 4 + .../typed01/expected/model_3_1_3_1.eprime | 10 + .../model_3_1_3_2-solution000001.solution | 4 + .../model_3_1_3_2-solution000002.solution | 4 + .../model_3_1_3_2-solution000003.solution | 4 + .../typed01/expected/model_3_1_3_2.eprime | 14 + .../model_3_1_3_3-solution000001.solution | 4 + .../model_3_1_3_3-solution000002.solution | 4 + .../model_3_1_3_3-solution000003.solution | 4 + .../typed01/expected/model_3_1_3_3.eprime | 17 + .../model_3_1_3_4-solution000001.solution | 4 + .../model_3_1_3_4-solution000002.solution | 4 + .../model_3_1_3_4-solution000003.solution | 4 + .../typed01/expected/model_3_1_3_4.eprime | 17 + .../model_3_1_4_1-solution000001.solution | 4 + .../model_3_1_4_1-solution000002.solution | 4 + .../model_3_1_4_1-solution000003.solution | 4 + .../typed01/expected/model_3_1_4_1.eprime | 20 + .../model_3_1_4_2-solution000001.solution | 4 + .../model_3_1_4_2-solution000002.solution | 4 + .../model_3_1_4_2-solution000003.solution | 4 + .../typed01/expected/model_3_1_4_2.eprime | 23 + .../model_3_1_4_3-solution000001.solution | 4 + .../model_3_1_4_3-solution000002.solution | 4 + .../model_3_1_4_3-solution000003.solution | 4 + .../typed01/expected/model_3_1_4_3.eprime | 26 + .../model_3_1_4_4-solution000001.solution | 4 + .../model_3_1_4_4-solution000002.solution | 4 + .../model_3_1_4_4-solution000003.solution | 4 + .../typed01/expected/model_3_1_4_4.eprime | 26 + .../model_3_2_1_1-solution000001.solution | 4 + .../model_3_2_1_1-solution000002.solution | 4 + .../model_3_2_1_1-solution000003.solution | 4 + .../typed01/expected/model_3_2_1_1.eprime | 20 + .../model_3_2_1_2-solution000001.solution | 4 + .../model_3_2_1_2-solution000002.solution | 4 + .../model_3_2_1_2-solution000003.solution | 4 + .../typed01/expected/model_3_2_1_2.eprime | 16 + .../model_3_2_1_3-solution000001.solution | 4 + .../model_3_2_1_3-solution000002.solution | 4 + .../model_3_2_1_3-solution000003.solution | 4 + .../typed01/expected/model_3_2_1_3.eprime | 24 + .../model_3_2_1_4-solution000001.solution | 4 + .../model_3_2_1_4-solution000002.solution | 4 + .../model_3_2_1_4-solution000003.solution | 4 + .../typed01/expected/model_3_2_1_4.eprime | 24 + .../model_3_2_2_1-solution000001.solution | 4 + .../model_3_2_2_1-solution000002.solution | 4 + .../model_3_2_2_1-solution000003.solution | 4 + .../typed01/expected/model_3_2_2_1.eprime | 22 + .../model_3_2_2_2-solution000001.solution | 4 + .../model_3_2_2_2-solution000002.solution | 4 + .../model_3_2_2_2-solution000003.solution | 4 + .../typed01/expected/model_3_2_2_2.eprime | 19 + .../model_3_2_2_3-solution000001.solution | 4 + .../model_3_2_2_3-solution000002.solution | 4 + .../model_3_2_2_3-solution000003.solution | 4 + .../typed01/expected/model_3_2_2_3.eprime | 26 + .../model_3_2_2_4-solution000001.solution | 4 + .../model_3_2_2_4-solution000002.solution | 4 + .../model_3_2_2_4-solution000003.solution | 4 + .../typed01/expected/model_3_2_2_4.eprime | 26 + .../model_3_2_3_1-solution000001.solution | 4 + .../model_3_2_3_1-solution000002.solution | 4 + .../model_3_2_3_1-solution000003.solution | 4 + .../typed01/expected/model_3_2_3_1.eprime | 16 + .../model_3_2_3_2-solution000001.solution | 4 + .../model_3_2_3_2-solution000002.solution | 4 + .../model_3_2_3_2-solution000003.solution | 4 + .../typed01/expected/model_3_2_3_2.eprime | 12 + .../model_3_2_3_3-solution000001.solution | 4 + .../model_3_2_3_3-solution000002.solution | 4 + .../model_3_2_3_3-solution000003.solution | 4 + .../typed01/expected/model_3_2_3_3.eprime | 21 + .../model_3_2_3_4-solution000001.solution | 4 + .../model_3_2_3_4-solution000002.solution | 4 + .../model_3_2_3_4-solution000003.solution | 4 + .../typed01/expected/model_3_2_3_4.eprime | 21 + .../model_3_2_4_1-solution000001.solution | 4 + .../model_3_2_4_1-solution000002.solution | 4 + .../model_3_2_4_1-solution000003.solution | 4 + .../typed01/expected/model_3_2_4_1.eprime | 25 + .../model_3_2_4_2-solution000001.solution | 4 + .../model_3_2_4_2-solution000002.solution | 4 + .../model_3_2_4_2-solution000003.solution | 4 + .../typed01/expected/model_3_2_4_2.eprime | 22 + .../model_3_2_4_3-solution000001.solution | 4 + .../model_3_2_4_3-solution000002.solution | 4 + .../model_3_2_4_3-solution000003.solution | 4 + .../typed01/expected/model_3_2_4_3.eprime | 30 + .../model_3_2_4_4-solution000001.solution | 4 + .../model_3_2_4_4-solution000002.solution | 4 + .../model_3_2_4_4-solution000003.solution | 4 + .../typed01/expected/model_3_2_4_4.eprime | 30 + .../model_3_3_1_1-solution000001.solution | 4 + .../model_3_3_1_1-solution000002.solution | 4 + .../model_3_3_1_1-solution000003.solution | 4 + .../typed01/expected/model_3_3_1_1.eprime | 23 + .../model_3_3_1_2-solution000001.solution | 4 + .../model_3_3_1_2-solution000002.solution | 4 + .../model_3_3_1_2-solution000003.solution | 4 + .../typed01/expected/model_3_3_1_2.eprime | 25 + .../model_3_3_1_3-solution000001.solution | 4 + .../model_3_3_1_3-solution000002.solution | 4 + .../model_3_3_1_3-solution000003.solution | 4 + .../typed01/expected/model_3_3_1_3.eprime | 20 + .../model_3_3_1_4-solution000001.solution | 4 + .../model_3_3_1_4-solution000002.solution | 4 + .../model_3_3_1_4-solution000003.solution | 4 + .../typed01/expected/model_3_3_1_4.eprime | 29 + .../model_3_3_2_1-solution000001.solution | 4 + .../model_3_3_2_1-solution000002.solution | 4 + .../model_3_3_2_1-solution000003.solution | 4 + .../typed01/expected/model_3_3_2_1.eprime | 25 + .../model_3_3_2_2-solution000001.solution | 4 + .../model_3_3_2_2-solution000002.solution | 4 + .../model_3_3_2_2-solution000003.solution | 4 + .../typed01/expected/model_3_3_2_2.eprime | 27 + .../model_3_3_2_3-solution000001.solution | 4 + .../model_3_3_2_3-solution000002.solution | 4 + .../model_3_3_2_3-solution000003.solution | 4 + .../typed01/expected/model_3_3_2_3.eprime | 22 + .../model_3_3_2_4-solution000001.solution | 4 + .../model_3_3_2_4-solution000002.solution | 4 + .../model_3_3_2_4-solution000003.solution | 4 + .../typed01/expected/model_3_3_2_4.eprime | 31 + .../model_3_3_3_1-solution000001.solution | 4 + .../model_3_3_3_1-solution000002.solution | 4 + .../model_3_3_3_1-solution000003.solution | 4 + .../typed01/expected/model_3_3_3_1.eprime | 20 + .../model_3_3_3_2-solution000001.solution | 4 + .../model_3_3_3_2-solution000002.solution | 4 + .../model_3_3_3_2-solution000003.solution | 4 + .../typed01/expected/model_3_3_3_2.eprime | 22 + .../model_3_3_3_3-solution000001.solution | 4 + .../model_3_3_3_3-solution000002.solution | 4 + .../model_3_3_3_3-solution000003.solution | 4 + .../typed01/expected/model_3_3_3_3.eprime | 17 + .../model_3_3_3_4-solution000001.solution | 4 + .../model_3_3_3_4-solution000002.solution | 4 + .../model_3_3_3_4-solution000003.solution | 4 + .../typed01/expected/model_3_3_3_4.eprime | 25 + .../model_3_3_4_1-solution000001.solution | 4 + .../model_3_3_4_1-solution000002.solution | 4 + .../model_3_3_4_1-solution000003.solution | 4 + .../typed01/expected/model_3_3_4_1.eprime | 29 + .../model_3_3_4_2-solution000001.solution | 4 + .../model_3_3_4_2-solution000002.solution | 4 + .../model_3_3_4_2-solution000003.solution | 4 + .../typed01/expected/model_3_3_4_2.eprime | 31 + .../model_3_3_4_3-solution000001.solution | 4 + .../model_3_3_4_3-solution000002.solution | 4 + .../model_3_3_4_3-solution000003.solution | 4 + .../typed01/expected/model_3_3_4_3.eprime | 25 + .../model_3_3_4_4-solution000001.solution | 4 + .../model_3_3_4_4-solution000002.solution | 4 + .../model_3_3_4_4-solution000003.solution | 4 + .../typed01/expected/model_3_3_4_4.eprime | 34 + .../model_3_4_1_1-solution000001.solution | 4 + .../model_3_4_1_1-solution000002.solution | 4 + .../model_3_4_1_1-solution000003.solution | 4 + .../typed01/expected/model_3_4_1_1.eprime | 23 + .../model_3_4_1_2-solution000001.solution | 4 + .../model_3_4_1_2-solution000002.solution | 4 + .../model_3_4_1_2-solution000003.solution | 4 + .../typed01/expected/model_3_4_1_2.eprime | 25 + .../model_3_4_1_3-solution000001.solution | 4 + .../model_3_4_1_3-solution000002.solution | 4 + .../model_3_4_1_3-solution000003.solution | 4 + .../typed01/expected/model_3_4_1_3.eprime | 29 + .../model_3_4_1_4-solution000001.solution | 4 + .../model_3_4_1_4-solution000002.solution | 4 + .../model_3_4_1_4-solution000003.solution | 4 + .../typed01/expected/model_3_4_1_4.eprime | 20 + .../model_3_4_2_1-solution000001.solution | 4 + .../model_3_4_2_1-solution000002.solution | 4 + .../model_3_4_2_1-solution000003.solution | 4 + .../typed01/expected/model_3_4_2_1.eprime | 25 + .../model_3_4_2_2-solution000001.solution | 4 + .../model_3_4_2_2-solution000002.solution | 4 + .../model_3_4_2_2-solution000003.solution | 4 + .../typed01/expected/model_3_4_2_2.eprime | 27 + .../model_3_4_2_3-solution000001.solution | 4 + .../model_3_4_2_3-solution000002.solution | 4 + .../model_3_4_2_3-solution000003.solution | 4 + .../typed01/expected/model_3_4_2_3.eprime | 31 + .../model_3_4_2_4-solution000001.solution | 4 + .../model_3_4_2_4-solution000002.solution | 4 + .../model_3_4_2_4-solution000003.solution | 4 + .../typed01/expected/model_3_4_2_4.eprime | 22 + .../model_3_4_3_1-solution000001.solution | 4 + .../model_3_4_3_1-solution000002.solution | 4 + .../model_3_4_3_1-solution000003.solution | 4 + .../typed01/expected/model_3_4_3_1.eprime | 20 + .../model_3_4_3_2-solution000001.solution | 4 + .../model_3_4_3_2-solution000002.solution | 4 + .../model_3_4_3_2-solution000003.solution | 4 + .../typed01/expected/model_3_4_3_2.eprime | 22 + .../model_3_4_3_3-solution000001.solution | 4 + .../model_3_4_3_3-solution000002.solution | 4 + .../model_3_4_3_3-solution000003.solution | 4 + .../typed01/expected/model_3_4_3_3.eprime | 25 + .../model_3_4_3_4-solution000001.solution | 4 + .../model_3_4_3_4-solution000002.solution | 4 + .../model_3_4_3_4-solution000003.solution | 4 + .../typed01/expected/model_3_4_3_4.eprime | 17 + .../model_3_4_4_1-solution000001.solution | 4 + .../model_3_4_4_1-solution000002.solution | 4 + .../model_3_4_4_1-solution000003.solution | 4 + .../typed01/expected/model_3_4_4_1.eprime | 29 + .../model_3_4_4_2-solution000001.solution | 4 + .../model_3_4_4_2-solution000002.solution | 4 + .../model_3_4_4_2-solution000003.solution | 4 + .../typed01/expected/model_3_4_4_2.eprime | 31 + .../model_3_4_4_3-solution000001.solution | 4 + .../model_3_4_4_3-solution000002.solution | 4 + .../model_3_4_4_3-solution000003.solution | 4 + .../typed01/expected/model_3_4_4_3.eprime | 34 + .../model_3_4_4_4-solution000001.solution | 4 + .../model_3_4_4_4-solution000002.solution | 4 + .../model_3_4_4_4-solution000003.solution | 4 + .../typed01/expected/model_3_4_4_4.eprime | 25 + .../model_4_1_1_1-solution000001.solution | 4 + .../model_4_1_1_1-solution000002.solution | 4 + .../model_4_1_1_1-solution000003.solution | 4 + .../typed01/expected/model_4_1_1_1.eprime | 13 + .../model_4_1_1_2-solution000001.solution | 4 + .../model_4_1_1_2-solution000002.solution | 4 + .../model_4_1_1_2-solution000003.solution | 4 + .../typed01/expected/model_4_1_1_2.eprime | 18 + .../model_4_1_1_3-solution000001.solution | 4 + .../model_4_1_1_3-solution000002.solution | 4 + .../model_4_1_1_3-solution000003.solution | 4 + .../typed01/expected/model_4_1_1_3.eprime | 20 + .../model_4_1_1_4-solution000001.solution | 4 + .../model_4_1_1_4-solution000002.solution | 4 + .../model_4_1_1_4-solution000003.solution | 4 + .../typed01/expected/model_4_1_1_4.eprime | 20 + .../model_4_1_2_1-solution000001.solution | 4 + .../model_4_1_2_1-solution000002.solution | 4 + .../model_4_1_2_1-solution000003.solution | 4 + .../typed01/expected/model_4_1_2_1.eprime | 16 + .../model_4_1_2_2-solution000001.solution | 4 + .../model_4_1_2_2-solution000002.solution | 4 + .../model_4_1_2_2-solution000003.solution | 4 + .../typed01/expected/model_4_1_2_2.eprime | 20 + .../model_4_1_2_3-solution000001.solution | 4 + .../model_4_1_2_3-solution000002.solution | 4 + .../model_4_1_2_3-solution000003.solution | 4 + .../typed01/expected/model_4_1_2_3.eprime | 22 + .../model_4_1_2_4-solution000001.solution | 4 + .../model_4_1_2_4-solution000002.solution | 4 + .../model_4_1_2_4-solution000003.solution | 4 + .../typed01/expected/model_4_1_2_4.eprime | 22 + .../model_4_1_3_1-solution000001.solution | 4 + .../model_4_1_3_1-solution000002.solution | 4 + .../model_4_1_3_1-solution000003.solution | 4 + .../typed01/expected/model_4_1_3_1.eprime | 20 + .../model_4_1_3_2-solution000001.solution | 4 + .../model_4_1_3_2-solution000002.solution | 4 + .../model_4_1_3_2-solution000003.solution | 4 + .../typed01/expected/model_4_1_3_2.eprime | 23 + .../model_4_1_3_3-solution000001.solution | 4 + .../model_4_1_3_3-solution000002.solution | 4 + .../model_4_1_3_3-solution000003.solution | 4 + .../typed01/expected/model_4_1_3_3.eprime | 26 + .../model_4_1_3_4-solution000001.solution | 4 + .../model_4_1_3_4-solution000002.solution | 4 + .../model_4_1_3_4-solution000003.solution | 4 + .../typed01/expected/model_4_1_3_4.eprime | 26 + .../model_4_1_4_1-solution000001.solution | 4 + .../model_4_1_4_1-solution000002.solution | 4 + .../model_4_1_4_1-solution000003.solution | 4 + .../typed01/expected/model_4_1_4_1.eprime | 10 + .../model_4_1_4_2-solution000001.solution | 4 + .../model_4_1_4_2-solution000002.solution | 4 + .../model_4_1_4_2-solution000003.solution | 4 + .../typed01/expected/model_4_1_4_2.eprime | 14 + .../model_4_1_4_3-solution000001.solution | 4 + .../model_4_1_4_3-solution000002.solution | 4 + .../model_4_1_4_3-solution000003.solution | 4 + .../typed01/expected/model_4_1_4_3.eprime | 17 + .../model_4_1_4_4-solution000001.solution | 4 + .../model_4_1_4_4-solution000002.solution | 4 + .../model_4_1_4_4-solution000003.solution | 4 + .../typed01/expected/model_4_1_4_4.eprime | 17 + .../model_4_2_1_1-solution000001.solution | 4 + .../model_4_2_1_1-solution000002.solution | 4 + .../model_4_2_1_1-solution000003.solution | 4 + .../typed01/expected/model_4_2_1_1.eprime | 20 + .../model_4_2_1_2-solution000001.solution | 4 + .../model_4_2_1_2-solution000002.solution | 4 + .../model_4_2_1_2-solution000003.solution | 4 + .../typed01/expected/model_4_2_1_2.eprime | 16 + .../model_4_2_1_3-solution000001.solution | 4 + .../model_4_2_1_3-solution000002.solution | 4 + .../model_4_2_1_3-solution000003.solution | 4 + .../typed01/expected/model_4_2_1_3.eprime | 24 + .../model_4_2_1_4-solution000001.solution | 4 + .../model_4_2_1_4-solution000002.solution | 4 + .../model_4_2_1_4-solution000003.solution | 4 + .../typed01/expected/model_4_2_1_4.eprime | 24 + .../model_4_2_2_1-solution000001.solution | 4 + .../model_4_2_2_1-solution000002.solution | 4 + .../model_4_2_2_1-solution000003.solution | 4 + .../typed01/expected/model_4_2_2_1.eprime | 22 + .../model_4_2_2_2-solution000001.solution | 4 + .../model_4_2_2_2-solution000002.solution | 4 + .../model_4_2_2_2-solution000003.solution | 4 + .../typed01/expected/model_4_2_2_2.eprime | 19 + .../model_4_2_2_3-solution000001.solution | 4 + .../model_4_2_2_3-solution000002.solution | 4 + .../model_4_2_2_3-solution000003.solution | 4 + .../typed01/expected/model_4_2_2_3.eprime | 26 + .../model_4_2_2_4-solution000001.solution | 4 + .../model_4_2_2_4-solution000002.solution | 4 + .../model_4_2_2_4-solution000003.solution | 4 + .../typed01/expected/model_4_2_2_4.eprime | 26 + .../model_4_2_3_1-solution000001.solution | 4 + .../model_4_2_3_1-solution000002.solution | 4 + .../model_4_2_3_1-solution000003.solution | 4 + .../typed01/expected/model_4_2_3_1.eprime | 25 + .../model_4_2_3_2-solution000001.solution | 4 + .../model_4_2_3_2-solution000002.solution | 4 + .../model_4_2_3_2-solution000003.solution | 4 + .../typed01/expected/model_4_2_3_2.eprime | 22 + .../model_4_2_3_3-solution000001.solution | 4 + .../model_4_2_3_3-solution000002.solution | 4 + .../model_4_2_3_3-solution000003.solution | 4 + .../typed01/expected/model_4_2_3_3.eprime | 30 + .../model_4_2_3_4-solution000001.solution | 4 + .../model_4_2_3_4-solution000002.solution | 4 + .../model_4_2_3_4-solution000003.solution | 4 + .../typed01/expected/model_4_2_3_4.eprime | 30 + .../model_4_2_4_1-solution000001.solution | 4 + .../model_4_2_4_1-solution000002.solution | 4 + .../model_4_2_4_1-solution000003.solution | 4 + .../typed01/expected/model_4_2_4_1.eprime | 16 + .../model_4_2_4_2-solution000001.solution | 4 + .../model_4_2_4_2-solution000002.solution | 4 + .../model_4_2_4_2-solution000003.solution | 4 + .../typed01/expected/model_4_2_4_2.eprime | 12 + .../model_4_2_4_3-solution000001.solution | 4 + .../model_4_2_4_3-solution000002.solution | 4 + .../model_4_2_4_3-solution000003.solution | 4 + .../typed01/expected/model_4_2_4_3.eprime | 21 + .../model_4_2_4_4-solution000001.solution | 4 + .../model_4_2_4_4-solution000002.solution | 4 + .../model_4_2_4_4-solution000003.solution | 4 + .../typed01/expected/model_4_2_4_4.eprime | 21 + .../model_4_3_1_1-solution000001.solution | 4 + .../model_4_3_1_1-solution000002.solution | 4 + .../model_4_3_1_1-solution000003.solution | 4 + .../typed01/expected/model_4_3_1_1.eprime | 23 + .../model_4_3_1_2-solution000001.solution | 4 + .../model_4_3_1_2-solution000002.solution | 4 + .../model_4_3_1_2-solution000003.solution | 4 + .../typed01/expected/model_4_3_1_2.eprime | 25 + .../model_4_3_1_3-solution000001.solution | 4 + .../model_4_3_1_3-solution000002.solution | 4 + .../model_4_3_1_3-solution000003.solution | 4 + .../typed01/expected/model_4_3_1_3.eprime | 20 + .../model_4_3_1_4-solution000001.solution | 4 + .../model_4_3_1_4-solution000002.solution | 4 + .../model_4_3_1_4-solution000003.solution | 4 + .../typed01/expected/model_4_3_1_4.eprime | 29 + .../model_4_3_2_1-solution000001.solution | 4 + .../model_4_3_2_1-solution000002.solution | 4 + .../model_4_3_2_1-solution000003.solution | 4 + .../typed01/expected/model_4_3_2_1.eprime | 25 + .../model_4_3_2_2-solution000001.solution | 4 + .../model_4_3_2_2-solution000002.solution | 4 + .../model_4_3_2_2-solution000003.solution | 4 + .../typed01/expected/model_4_3_2_2.eprime | 27 + .../model_4_3_2_3-solution000001.solution | 4 + .../model_4_3_2_3-solution000002.solution | 4 + .../model_4_3_2_3-solution000003.solution | 4 + .../typed01/expected/model_4_3_2_3.eprime | 22 + .../model_4_3_2_4-solution000001.solution | 4 + .../model_4_3_2_4-solution000002.solution | 4 + .../model_4_3_2_4-solution000003.solution | 4 + .../typed01/expected/model_4_3_2_4.eprime | 31 + .../model_4_3_3_1-solution000001.solution | 4 + .../model_4_3_3_1-solution000002.solution | 4 + .../model_4_3_3_1-solution000003.solution | 4 + .../typed01/expected/model_4_3_3_1.eprime | 29 + .../model_4_3_3_2-solution000001.solution | 4 + .../model_4_3_3_2-solution000002.solution | 4 + .../model_4_3_3_2-solution000003.solution | 4 + .../typed01/expected/model_4_3_3_2.eprime | 31 + .../model_4_3_3_3-solution000001.solution | 4 + .../model_4_3_3_3-solution000002.solution | 4 + .../model_4_3_3_3-solution000003.solution | 4 + .../typed01/expected/model_4_3_3_3.eprime | 25 + .../model_4_3_3_4-solution000001.solution | 4 + .../model_4_3_3_4-solution000002.solution | 4 + .../model_4_3_3_4-solution000003.solution | 4 + .../typed01/expected/model_4_3_3_4.eprime | 34 + .../model_4_3_4_1-solution000001.solution | 4 + .../model_4_3_4_1-solution000002.solution | 4 + .../model_4_3_4_1-solution000003.solution | 4 + .../typed01/expected/model_4_3_4_1.eprime | 20 + .../model_4_3_4_2-solution000001.solution | 4 + .../model_4_3_4_2-solution000002.solution | 4 + .../model_4_3_4_2-solution000003.solution | 4 + .../typed01/expected/model_4_3_4_2.eprime | 22 + .../model_4_3_4_3-solution000001.solution | 4 + .../model_4_3_4_3-solution000002.solution | 4 + .../model_4_3_4_3-solution000003.solution | 4 + .../typed01/expected/model_4_3_4_3.eprime | 17 + .../model_4_3_4_4-solution000001.solution | 4 + .../model_4_3_4_4-solution000002.solution | 4 + .../model_4_3_4_4-solution000003.solution | 4 + .../typed01/expected/model_4_3_4_4.eprime | 25 + .../model_4_4_1_1-solution000001.solution | 4 + .../model_4_4_1_1-solution000002.solution | 4 + .../model_4_4_1_1-solution000003.solution | 4 + .../typed01/expected/model_4_4_1_1.eprime | 22 + .../model_4_4_1_2-solution000001.solution | 4 + .../model_4_4_1_2-solution000002.solution | 4 + .../model_4_4_1_2-solution000003.solution | 4 + .../typed01/expected/model_4_4_1_2.eprime | 24 + .../model_4_4_1_3-solution000001.solution | 4 + .../model_4_4_1_3-solution000002.solution | 4 + .../model_4_4_1_3-solution000003.solution | 4 + .../typed01/expected/model_4_4_1_3.eprime | 28 + .../model_4_4_1_4-solution000001.solution | 4 + .../model_4_4_1_4-solution000002.solution | 4 + .../model_4_4_1_4-solution000003.solution | 4 + .../typed01/expected/model_4_4_1_4.eprime | 19 + .../model_4_4_2_1-solution000001.solution | 4 + .../model_4_4_2_1-solution000002.solution | 4 + .../model_4_4_2_1-solution000003.solution | 4 + .../typed01/expected/model_4_4_2_1.eprime | 24 + .../model_4_4_2_2-solution000001.solution | 4 + .../model_4_4_2_2-solution000002.solution | 4 + .../model_4_4_2_2-solution000003.solution | 4 + .../typed01/expected/model_4_4_2_2.eprime | 26 + .../model_4_4_2_3-solution000001.solution | 4 + .../model_4_4_2_3-solution000002.solution | 4 + .../model_4_4_2_3-solution000003.solution | 4 + .../typed01/expected/model_4_4_2_3.eprime | 30 + .../model_4_4_2_4-solution000001.solution | 4 + .../model_4_4_2_4-solution000002.solution | 4 + .../model_4_4_2_4-solution000003.solution | 4 + .../typed01/expected/model_4_4_2_4.eprime | 21 + .../model_4_4_3_1-solution000001.solution | 4 + .../model_4_4_3_1-solution000002.solution | 4 + .../model_4_4_3_1-solution000003.solution | 4 + .../typed01/expected/model_4_4_3_1.eprime | 28 + .../model_4_4_3_2-solution000001.solution | 4 + .../model_4_4_3_2-solution000002.solution | 4 + .../model_4_4_3_2-solution000003.solution | 4 + .../typed01/expected/model_4_4_3_2.eprime | 30 + .../model_4_4_3_3-solution000001.solution | 4 + .../model_4_4_3_3-solution000002.solution | 4 + .../model_4_4_3_3-solution000003.solution | 4 + .../typed01/expected/model_4_4_3_3.eprime | 33 + .../model_4_4_3_4-solution000001.solution | 4 + .../model_4_4_3_4-solution000002.solution | 4 + .../model_4_4_3_4-solution000003.solution | 4 + .../typed01/expected/model_4_4_3_4.eprime | 24 + .../model_4_4_4_1-solution000001.solution | 4 + .../model_4_4_4_1-solution000002.solution | 4 + .../model_4_4_4_1-solution000003.solution | 4 + .../typed01/expected/model_4_4_4_1.eprime | 19 + .../model_4_4_4_2-solution000001.solution | 4 + .../model_4_4_4_2-solution000002.solution | 4 + .../model_4_4_4_2-solution000003.solution | 4 + .../typed01/expected/model_4_4_4_2.eprime | 21 + .../model_4_4_4_3-solution000001.solution | 4 + .../model_4_4_4_3-solution000002.solution | 4 + .../model_4_4_4_3-solution000003.solution | 4 + .../typed01/expected/model_4_4_4_3.eprime | 24 + .../model_4_4_4_4-solution000001.solution | 4 + .../model_4_4_4_4-solution000002.solution | 4 + .../model_4_4_4_4-solution000003.solution | 4 + .../typed01/expected/model_4_4_4_4.eprime | 16 + 5284 files changed, 59136 insertions(+), 18818 deletions(-) delete mode 100644 src/Conjure/Compute/DomainOf.hs.orig delete mode 100644 src/Conjure/Language/Constant.hs.orig delete mode 100644 src/Conjure/Language/Domain.hs.orig delete mode 100644 src/Conjure/Language/Expression/Op/Defined.hs.orig delete mode 100644 src/Conjure/Language/Expression/Op/Image.hs.orig delete mode 100644 src/Conjure/Language/Expression/Op/Inverse.hs.orig delete mode 100644 src/Conjure/Language/Expression/Op/Product.hs.orig delete mode 100644 src/Conjure/Language/Expression/Op/ToSet.hs.orig delete mode 100644 src/Conjure/Language/Expression/Op/TwoBars.hs.orig delete mode 100644 src/Conjure/Language/Instantiate.hs.orig delete mode 100644 src/Conjure/Language/Lexer.hs.orig delete mode 100644 src/Conjure/Language/NameResolution.hs.orig delete mode 100644 src/Conjure/Representations.hs.orig delete mode 100644 src/Conjure/Representations/Function/Function1D.hs.orig delete mode 100644 src/Conjure/Representations/Function/Function1DPartial.hs.orig delete mode 100644 src/Conjure/Representations/Function/FunctionND.hs.orig delete mode 100644 src/Conjure/Representations/MSet/Occurrence.hs.orig delete mode 100644 src/Conjure/Representations/Partition/Occurrence.hs.orig delete mode 100644 src/Conjure/Representations/Record.hs.orig delete mode 100644 src/Conjure/Representations/Set/Explicit.hs.orig delete mode 100644 src/Conjure/Representations/Set/ExplicitVarSizeWithDummy.hs.orig delete mode 100644 src/Conjure/Representations/Tuple.hs.orig delete mode 100644 src/Conjure/Representations/Variant.hs.orig delete mode 100644 src/Conjure/UI/Model.hs.orig delete mode 100755 tests/custom/basic/function-literal-suggestion/run.sh.orig delete mode 100644 tests/custom/basic/function-literal-suggestion/stdout.expected.orig delete mode 100644 tests/custom/issues/119/1/stdout.expected.orig delete mode 100644 tests/custom/issues/119/2/stdout.expected.orig delete mode 100644 tests/custom/issues/370/01/stdout.expected.orig delete mode 100644 tests/custom/issues/370/03/stdout.expected.orig delete mode 100644 tests/custom/issues/388/2/stdout.expected.orig create mode 100644 tests/exhaustive/autogen/gen02/expected/model_1_1-solution000001.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_1_1-solution000002.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_1_1-solution000003.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_1_1-solution000004.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_1_1-solution000005.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_1_1-solution000006.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_1_1-solution000007.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_1_1-solution000008.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_1_1-solution000009.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_1_1-solution000010.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_1_1-solution000011.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_1_1-solution000012.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_1_1-solution000013.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_1_1-solution000014.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_1_1-solution000015.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_1_1.eprime.orig create mode 100644 tests/exhaustive/autogen/gen02/expected/model_1_2-solution000001.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_1_2-solution000002.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_1_2-solution000003.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_1_2-solution000004.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_1_2-solution000005.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_1_2-solution000006.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_1_2-solution000007.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_1_2-solution000008.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_1_2-solution000009.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_1_2-solution000010.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_1_2-solution000011.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_1_2-solution000012.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_1_2-solution000013.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_1_2-solution000014.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_1_2-solution000015.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_1_2.eprime.orig create mode 100644 tests/exhaustive/autogen/gen02/expected/model_1_3-solution000001.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_1_3-solution000002.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_1_3-solution000003.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_1_3-solution000004.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_1_3-solution000005.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_1_3-solution000006.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_1_3-solution000007.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_1_3-solution000008.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_1_3-solution000009.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_1_3-solution000010.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_1_3-solution000011.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_1_3-solution000012.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_1_3-solution000013.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_1_3-solution000014.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_1_3-solution000015.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_1_3.eprime.orig create mode 100644 tests/exhaustive/autogen/gen02/expected/model_1_4-solution000001.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_1_4-solution000002.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_1_4-solution000003.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_1_4-solution000004.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_1_4-solution000005.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_1_4-solution000006.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_1_4-solution000007.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_1_4-solution000008.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_1_4-solution000009.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_1_4-solution000010.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_1_4-solution000011.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_1_4-solution000012.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_1_4-solution000013.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_1_4-solution000014.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_1_4-solution000015.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_1_4.eprime.orig create mode 100644 tests/exhaustive/autogen/gen02/expected/model_2_1-solution000001.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_2_1-solution000002.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_2_1-solution000003.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_2_1-solution000004.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_2_1-solution000005.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_2_1-solution000006.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_2_1-solution000007.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_2_1-solution000008.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_2_1-solution000009.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_2_1-solution000010.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_2_1-solution000011.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_2_1-solution000012.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_2_1-solution000013.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_2_1-solution000014.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_2_1-solution000015.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_2_1.eprime.orig create mode 100644 tests/exhaustive/autogen/gen02/expected/model_2_2-solution000001.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_2_2-solution000002.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_2_2-solution000003.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_2_2-solution000004.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_2_2-solution000005.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_2_2-solution000006.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_2_2-solution000007.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_2_2-solution000008.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_2_2-solution000009.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_2_2-solution000010.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_2_2-solution000011.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_2_2-solution000012.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_2_2-solution000013.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_2_2-solution000014.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_2_2-solution000015.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_2_2.eprime create mode 100644 tests/exhaustive/autogen/gen02/expected/model_2_3-solution000001.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_2_3-solution000002.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_2_3-solution000003.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_2_3-solution000004.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_2_3-solution000005.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_2_3-solution000006.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_2_3-solution000007.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_2_3-solution000008.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_2_3-solution000009.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_2_3-solution000010.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_2_3-solution000011.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_2_3-solution000012.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_2_3-solution000013.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_2_3-solution000014.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_2_3-solution000015.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_2_3.eprime.orig create mode 100644 tests/exhaustive/autogen/gen02/expected/model_2_4-solution000001.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_2_4-solution000002.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_2_4-solution000003.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_2_4-solution000004.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_2_4-solution000005.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_2_4-solution000006.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_2_4-solution000007.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_2_4-solution000008.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_2_4-solution000009.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_2_4-solution000010.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_2_4-solution000011.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_2_4-solution000012.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_2_4-solution000013.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_2_4-solution000014.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_2_4-solution000015.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_2_4.eprime create mode 100644 tests/exhaustive/autogen/gen02/expected/model_3_1-solution000001.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_3_1-solution000002.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_3_1-solution000003.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_3_1-solution000004.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_3_1-solution000005.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_3_1-solution000006.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_3_1-solution000007.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_3_1-solution000008.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_3_1-solution000009.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_3_1-solution000010.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_3_1-solution000011.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_3_1-solution000012.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_3_1-solution000013.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_3_1-solution000014.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_3_1-solution000015.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_3_1.eprime.orig create mode 100644 tests/exhaustive/autogen/gen02/expected/model_3_2-solution000001.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_3_2-solution000002.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_3_2-solution000003.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_3_2-solution000004.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_3_2-solution000005.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_3_2-solution000006.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_3_2-solution000007.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_3_2-solution000008.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_3_2-solution000009.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_3_2-solution000010.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_3_2-solution000011.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_3_2-solution000012.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_3_2-solution000013.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_3_2-solution000014.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_3_2-solution000015.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_3_2.eprime.orig create mode 100644 tests/exhaustive/autogen/gen02/expected/model_3_3-solution000001.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_3_3-solution000002.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_3_3-solution000003.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_3_3-solution000004.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_3_3-solution000005.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_3_3-solution000006.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_3_3-solution000007.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_3_3-solution000008.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_3_3-solution000009.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_3_3-solution000010.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_3_3-solution000011.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_3_3-solution000012.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_3_3-solution000013.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_3_3-solution000014.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_3_3-solution000015.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_3_3.eprime.orig create mode 100644 tests/exhaustive/autogen/gen02/expected/model_3_4-solution000001.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_3_4-solution000002.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_3_4-solution000003.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_3_4-solution000004.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_3_4-solution000005.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_3_4-solution000006.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_3_4-solution000007.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_3_4-solution000008.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_3_4-solution000009.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_3_4-solution000010.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_3_4-solution000011.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_3_4-solution000012.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_3_4-solution000013.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_3_4-solution000014.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_3_4-solution000015.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_3_4.eprime.orig create mode 100644 tests/exhaustive/autogen/gen02/expected/model_4_1-solution000001.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_4_1-solution000002.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_4_1-solution000003.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_4_1-solution000004.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_4_1-solution000005.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_4_1-solution000006.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_4_1-solution000007.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_4_1-solution000008.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_4_1-solution000009.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_4_1-solution000010.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_4_1-solution000011.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_4_1-solution000012.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_4_1-solution000013.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_4_1-solution000014.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_4_1-solution000015.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_4_1.eprime.orig create mode 100644 tests/exhaustive/autogen/gen02/expected/model_4_2-solution000001.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_4_2-solution000002.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_4_2-solution000003.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_4_2-solution000004.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_4_2-solution000005.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_4_2-solution000006.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_4_2-solution000007.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_4_2-solution000008.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_4_2-solution000009.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_4_2-solution000010.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_4_2-solution000011.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_4_2-solution000012.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_4_2-solution000013.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_4_2-solution000014.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_4_2-solution000015.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_4_2.eprime create mode 100644 tests/exhaustive/autogen/gen02/expected/model_4_3-solution000001.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_4_3-solution000002.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_4_3-solution000003.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_4_3-solution000004.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_4_3-solution000005.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_4_3-solution000006.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_4_3-solution000007.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_4_3-solution000008.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_4_3-solution000009.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_4_3-solution000010.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_4_3-solution000011.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_4_3-solution000012.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_4_3-solution000013.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_4_3-solution000014.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_4_3-solution000015.solution delete mode 100644 tests/exhaustive/autogen/gen02/expected/model_4_3.eprime.orig create mode 100644 tests/exhaustive/autogen/gen02/expected/model_4_4-solution000001.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_4_4-solution000002.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_4_4-solution000003.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_4_4-solution000004.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_4_4-solution000005.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_4_4-solution000006.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_4_4-solution000007.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_4_4-solution000008.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_4_4-solution000009.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_4_4-solution000010.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_4_4-solution000011.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_4_4-solution000012.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_4_4-solution000013.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_4_4-solution000014.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_4_4-solution000015.solution create mode 100644 tests/exhaustive/autogen/gen02/expected/model_4_4.eprime create mode 100644 tests/exhaustive/autogen/gen14_1/expected/model_1-solution000001.solution create mode 100644 tests/exhaustive/autogen/gen14_1/expected/model_1-solution000002.solution delete mode 100644 tests/exhaustive/autogen/gen14_1/expected/model_1.eprime.orig create mode 100644 tests/exhaustive/autogen/gen14_1/expected/model_2-solution000001.solution create mode 100644 tests/exhaustive/autogen/gen14_1/expected/model_2-solution000002.solution delete mode 100644 tests/exhaustive/autogen/gen14_1/expected/model_2.eprime.orig create mode 100644 tests/exhaustive/autogen/gen14_1/expected/model_3-solution000001.solution create mode 100644 tests/exhaustive/autogen/gen14_1/expected/model_3-solution000002.solution delete mode 100644 tests/exhaustive/autogen/gen14_1/expected/model_3.eprime.orig create mode 100644 tests/exhaustive/autogen/gen14_1/expected/model_4-solution000001.solution create mode 100644 tests/exhaustive/autogen/gen14_1/expected/model_4-solution000002.solution delete mode 100644 tests/exhaustive/autogen/gen14_1/expected/model_4.eprime.orig create mode 100644 tests/exhaustive/autogen/gen14_2/expected/model_1-solution000001.solution create mode 100644 tests/exhaustive/autogen/gen14_2/expected/model_1-solution000002.solution create mode 100644 tests/exhaustive/autogen/gen14_2/expected/model_1.eprime create mode 100644 tests/exhaustive/autogen/gen14_2/expected/model_2-solution000001.solution create mode 100644 tests/exhaustive/autogen/gen14_2/expected/model_2-solution000002.solution create mode 100644 tests/exhaustive/autogen/gen14_2/expected/model_2.eprime create mode 100644 tests/exhaustive/autogen/gen14_2/expected/model_3-solution000001.solution create mode 100644 tests/exhaustive/autogen/gen14_2/expected/model_3-solution000002.solution delete mode 100644 tests/exhaustive/autogen/gen14_2/expected/model_3.eprime.orig create mode 100644 tests/exhaustive/autogen/gen14_2/expected/model_4-solution000001.solution create mode 100644 tests/exhaustive/autogen/gen14_2/expected/model_4-solution000002.solution create mode 100644 tests/exhaustive/autogen/gen14_2/expected/model_4.eprime create mode 100644 tests/exhaustive/autogen/gen32/expected/model_1_1_1.eprime create mode 100644 tests/exhaustive/autogen/gen32/expected/model_1_1_2.eprime create mode 100644 tests/exhaustive/autogen/gen32/expected/model_1_1_3.eprime create mode 100644 tests/exhaustive/autogen/gen32/expected/model_1_1_4.eprime create mode 100644 tests/exhaustive/autogen/gen32/expected/model_1_2_1.eprime create mode 100644 tests/exhaustive/autogen/gen32/expected/model_1_2_3.eprime create mode 100644 tests/exhaustive/autogen/gen32/expected/model_1_2_4.eprime create mode 100644 tests/exhaustive/autogen/gen32/expected/model_1_3_1.eprime create mode 100644 tests/exhaustive/autogen/gen32/expected/model_1_3_2.eprime create mode 100644 tests/exhaustive/autogen/gen32/expected/model_1_3_4.eprime create mode 100644 tests/exhaustive/autogen/gen32/expected/model_1_4_1.eprime create mode 100644 tests/exhaustive/autogen/gen32/expected/model_1_4_2.eprime create mode 100644 tests/exhaustive/autogen/gen32/expected/model_1_4_3.eprime create mode 100644 tests/exhaustive/autogen/gen32/expected/model_2_1_1.eprime create mode 100644 tests/exhaustive/autogen/gen32/expected/model_2_1_3.eprime create mode 100644 tests/exhaustive/autogen/gen32/expected/model_2_1_4.eprime create mode 100644 tests/exhaustive/autogen/gen32/expected/model_2_2_1.eprime create mode 100644 tests/exhaustive/autogen/gen32/expected/model_2_2_2.eprime create mode 100644 tests/exhaustive/autogen/gen32/expected/model_2_2_3.eprime create mode 100644 tests/exhaustive/autogen/gen32/expected/model_2_2_4.eprime create mode 100644 tests/exhaustive/autogen/gen32/expected/model_2_3_1.eprime create mode 100644 tests/exhaustive/autogen/gen32/expected/model_2_3_2.eprime create mode 100644 tests/exhaustive/autogen/gen32/expected/model_2_3_4.eprime create mode 100644 tests/exhaustive/autogen/gen32/expected/model_2_4_1.eprime create mode 100644 tests/exhaustive/autogen/gen32/expected/model_2_4_2.eprime create mode 100644 tests/exhaustive/autogen/gen32/expected/model_2_4_3.eprime create mode 100644 tests/exhaustive/autogen/gen32/expected/model_3_1_1.eprime create mode 100644 tests/exhaustive/autogen/gen32/expected/model_3_1_2.eprime create mode 100644 tests/exhaustive/autogen/gen32/expected/model_3_1_4.eprime create mode 100644 tests/exhaustive/autogen/gen32/expected/model_3_2_1.eprime create mode 100644 tests/exhaustive/autogen/gen32/expected/model_3_2_2.eprime create mode 100644 tests/exhaustive/autogen/gen32/expected/model_3_2_4.eprime create mode 100644 tests/exhaustive/autogen/gen32/expected/model_3_3_1.eprime create mode 100644 tests/exhaustive/autogen/gen32/expected/model_3_3_2.eprime create mode 100644 tests/exhaustive/autogen/gen32/expected/model_3_3_3.eprime create mode 100644 tests/exhaustive/autogen/gen32/expected/model_3_3_4.eprime create mode 100644 tests/exhaustive/autogen/gen32/expected/model_3_4_1.eprime create mode 100644 tests/exhaustive/autogen/gen32/expected/model_3_4_2.eprime create mode 100644 tests/exhaustive/autogen/gen32/expected/model_3_4_3.eprime create mode 100644 tests/exhaustive/autogen/gen32/expected/model_4_1_1.eprime create mode 100644 tests/exhaustive/autogen/gen32/expected/model_4_1_2.eprime create mode 100644 tests/exhaustive/autogen/gen32/expected/model_4_1_3.eprime create mode 100644 tests/exhaustive/autogen/gen32/expected/model_4_2_1.eprime create mode 100644 tests/exhaustive/autogen/gen32/expected/model_4_2_2.eprime create mode 100644 tests/exhaustive/autogen/gen32/expected/model_4_2_3.eprime create mode 100644 tests/exhaustive/autogen/gen32/expected/model_4_3_1.eprime create mode 100644 tests/exhaustive/autogen/gen32/expected/model_4_3_2.eprime create mode 100644 tests/exhaustive/autogen/gen32/expected/model_4_3_3.eprime create mode 100644 tests/exhaustive/autogen/gen32/expected/model_4_4_1.eprime create mode 100644 tests/exhaustive/autogen/gen32/expected/model_4_4_2.eprime create mode 100644 tests/exhaustive/autogen/gen32/expected/model_4_4_3.eprime create mode 100644 tests/exhaustive/autogen/gen32/expected/model_4_4_4.eprime delete mode 100644 tests/exhaustive/autogen/gen35/expected/model_1.eprime.orig create mode 100644 tests/exhaustive/autogen/gen36/expected/model_1-solution000001.solution create mode 100644 tests/exhaustive/autogen/gen36/expected/model_2-solution000001.solution create mode 100644 tests/exhaustive/autogen/gen36/expected/model_3-solution000001.solution delete mode 100644 tests/exhaustive/autogen/gen36/expected/model_3.eprime.orig create mode 100644 tests/exhaustive/autogen/gen36/expected/model_4-solution000001.solution create mode 100644 tests/exhaustive/autogen/gen36/expected/model_5-solution000001.solution create mode 100644 tests/exhaustive/autogen/gen36/expected/model_6-solution000001.solution delete mode 100644 tests/exhaustive/autogen/gen36/expected/model_6.eprime.orig create mode 100644 tests/exhaustive/basic/comprehension_04_2/expected/model-solution000001.solution create mode 100644 tests/exhaustive/basic/comprehension_04_2/expected/model-solution000002.solution create mode 100644 tests/exhaustive/basic/comprehension_04_2/expected/model-solution000003.solution create mode 100644 tests/exhaustive/basic/comprehension_04_2/expected/model-solution000004.solution create mode 100644 tests/exhaustive/basic/comprehension_04_2/expected/model.eprime create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_1_1-solution000001.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_1_1-solution000002.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_1_1-solution000003.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_1_1-solution000004.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_1_1-solution000005.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_1_1-solution000006.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_1_1-solution000007.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_1_1.eprime create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_1_2-solution000001.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_1_2-solution000002.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_1_2-solution000003.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_1_2-solution000004.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_1_2-solution000005.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_1_2-solution000006.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_1_2-solution000007.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_1_2.eprime create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_1_3-solution000001.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_1_3-solution000002.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_1_3-solution000003.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_1_3-solution000004.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_1_3-solution000005.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_1_3-solution000006.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_1_3-solution000007.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_1_3.eprime create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_1_4-solution000001.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_1_4-solution000002.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_1_4-solution000003.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_1_4-solution000004.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_1_4-solution000005.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_1_4-solution000006.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_1_4-solution000007.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_1_4.eprime create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_2_1-solution000001.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_2_1-solution000002.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_2_1-solution000003.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_2_1-solution000004.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_2_1-solution000005.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_2_1-solution000006.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_2_1-solution000007.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_2_1.eprime create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_2_3-solution000001.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_2_3-solution000002.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_2_3-solution000003.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_2_3-solution000004.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_2_3-solution000005.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_2_3-solution000006.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_2_3-solution000007.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_2_3.eprime create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_2_4-solution000001.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_2_4-solution000002.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_2_4-solution000003.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_2_4-solution000004.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_2_4-solution000005.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_2_4-solution000006.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_2_4-solution000007.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_2_4.eprime create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_3_1-solution000001.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_3_1-solution000002.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_3_1-solution000003.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_3_1-solution000004.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_3_1-solution000005.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_3_1-solution000006.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_3_1-solution000007.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_3_1.eprime create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_3_2-solution000001.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_3_2-solution000002.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_3_2-solution000003.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_3_2-solution000004.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_3_2-solution000005.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_3_2-solution000006.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_3_2-solution000007.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_3_2.eprime create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_3_4-solution000001.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_3_4-solution000002.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_3_4-solution000003.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_3_4-solution000004.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_3_4-solution000005.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_3_4-solution000006.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_3_4-solution000007.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_3_4.eprime create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_4_1-solution000001.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_4_1-solution000002.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_4_1-solution000003.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_4_1-solution000004.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_4_1-solution000005.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_4_1-solution000006.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_4_1-solution000007.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_4_1.eprime create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_4_2-solution000001.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_4_2-solution000002.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_4_2-solution000003.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_4_2-solution000004.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_4_2-solution000005.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_4_2-solution000006.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_4_2-solution000007.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_4_2.eprime create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_4_3-solution000001.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_4_3-solution000002.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_4_3-solution000003.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_4_3-solution000004.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_4_3-solution000005.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_4_3-solution000006.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_4_3-solution000007.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_1_4_3.eprime create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_1_1-solution000001.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_1_1-solution000002.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_1_1-solution000003.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_1_1-solution000004.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_1_1-solution000005.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_1_1-solution000006.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_1_1-solution000007.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_1_1.eprime create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_1_3-solution000001.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_1_3-solution000002.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_1_3-solution000003.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_1_3-solution000004.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_1_3-solution000005.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_1_3-solution000006.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_1_3-solution000007.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_1_3.eprime create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_1_4-solution000001.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_1_4-solution000002.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_1_4-solution000003.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_1_4-solution000004.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_1_4-solution000005.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_1_4-solution000006.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_1_4-solution000007.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_1_4.eprime create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_2_1-solution000001.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_2_1-solution000002.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_2_1-solution000003.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_2_1-solution000004.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_2_1-solution000005.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_2_1-solution000006.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_2_1-solution000007.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_2_1.eprime create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_2_2-solution000001.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_2_2-solution000002.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_2_2-solution000003.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_2_2-solution000004.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_2_2-solution000005.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_2_2-solution000006.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_2_2-solution000007.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_2_2.eprime create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_2_3-solution000001.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_2_3-solution000002.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_2_3-solution000003.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_2_3-solution000004.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_2_3-solution000005.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_2_3-solution000006.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_2_3-solution000007.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_2_3.eprime create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_2_4-solution000001.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_2_4-solution000002.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_2_4-solution000003.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_2_4-solution000004.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_2_4-solution000005.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_2_4-solution000006.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_2_4-solution000007.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_2_4.eprime create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_3_1-solution000001.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_3_1-solution000002.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_3_1-solution000003.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_3_1-solution000004.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_3_1-solution000005.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_3_1-solution000006.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_3_1-solution000007.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_3_1.eprime create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_3_2-solution000001.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_3_2-solution000002.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_3_2-solution000003.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_3_2-solution000004.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_3_2-solution000005.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_3_2-solution000006.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_3_2-solution000007.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_3_2.eprime create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_3_4-solution000001.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_3_4-solution000002.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_3_4-solution000003.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_3_4-solution000004.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_3_4-solution000005.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_3_4-solution000006.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_3_4-solution000007.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_3_4.eprime create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_4_1-solution000001.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_4_1-solution000002.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_4_1-solution000003.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_4_1-solution000004.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_4_1-solution000005.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_4_1-solution000006.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_4_1-solution000007.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_4_1.eprime create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_4_2-solution000001.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_4_2-solution000002.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_4_2-solution000003.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_4_2-solution000004.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_4_2-solution000005.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_4_2-solution000006.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_4_2-solution000007.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_4_2.eprime create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_4_3-solution000001.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_4_3-solution000002.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_4_3-solution000003.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_4_3-solution000004.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_4_3-solution000005.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_4_3-solution000006.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_4_3-solution000007.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_2_4_3.eprime create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_1_1-solution000001.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_1_1-solution000002.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_1_1-solution000003.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_1_1-solution000004.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_1_1-solution000005.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_1_1-solution000006.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_1_1-solution000007.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_1_1.eprime create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_1_2-solution000001.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_1_2-solution000002.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_1_2-solution000003.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_1_2-solution000004.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_1_2-solution000005.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_1_2-solution000006.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_1_2-solution000007.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_1_2.eprime create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_1_4-solution000001.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_1_4-solution000002.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_1_4-solution000003.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_1_4-solution000004.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_1_4-solution000005.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_1_4-solution000006.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_1_4-solution000007.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_1_4.eprime create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_2_1-solution000001.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_2_1-solution000002.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_2_1-solution000003.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_2_1-solution000004.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_2_1-solution000005.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_2_1-solution000006.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_2_1-solution000007.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_2_1.eprime create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_2_2-solution000001.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_2_2-solution000002.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_2_2-solution000003.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_2_2-solution000004.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_2_2-solution000005.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_2_2-solution000006.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_2_2-solution000007.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_2_2.eprime create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_2_4-solution000001.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_2_4-solution000002.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_2_4-solution000003.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_2_4-solution000004.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_2_4-solution000005.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_2_4-solution000006.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_2_4-solution000007.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_2_4.eprime create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_3_1-solution000001.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_3_1-solution000002.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_3_1-solution000003.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_3_1-solution000004.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_3_1-solution000005.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_3_1-solution000006.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_3_1-solution000007.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_3_1.eprime create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_3_2-solution000001.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_3_2-solution000002.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_3_2-solution000003.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_3_2-solution000004.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_3_2-solution000005.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_3_2-solution000006.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_3_2-solution000007.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_3_2.eprime create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_3_3-solution000001.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_3_3-solution000002.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_3_3-solution000003.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_3_3-solution000004.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_3_3-solution000005.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_3_3-solution000006.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_3_3-solution000007.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_3_3.eprime create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_3_4-solution000001.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_3_4-solution000002.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_3_4-solution000003.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_3_4-solution000004.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_3_4-solution000005.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_3_4-solution000006.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_3_4-solution000007.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_3_4.eprime create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_4_1-solution000001.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_4_1-solution000002.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_4_1-solution000003.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_4_1-solution000004.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_4_1-solution000005.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_4_1-solution000006.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_4_1-solution000007.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_4_1.eprime create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_4_2-solution000001.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_4_2-solution000002.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_4_2-solution000003.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_4_2-solution000004.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_4_2-solution000005.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_4_2-solution000006.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_4_2-solution000007.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_4_2.eprime create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_4_3-solution000001.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_4_3-solution000002.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_4_3-solution000003.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_4_3-solution000004.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_4_3-solution000005.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_4_3-solution000006.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_4_3-solution000007.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_3_4_3.eprime create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_1_1-solution000001.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_1_1-solution000002.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_1_1-solution000003.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_1_1-solution000004.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_1_1-solution000005.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_1_1-solution000006.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_1_1-solution000007.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_1_1.eprime create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_1_2-solution000001.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_1_2-solution000002.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_1_2-solution000003.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_1_2-solution000004.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_1_2-solution000005.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_1_2-solution000006.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_1_2-solution000007.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_1_2.eprime create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_1_3-solution000001.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_1_3-solution000002.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_1_3-solution000003.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_1_3-solution000004.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_1_3-solution000005.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_1_3-solution000006.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_1_3-solution000007.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_1_3.eprime create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_2_1-solution000001.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_2_1-solution000002.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_2_1-solution000003.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_2_1-solution000004.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_2_1-solution000005.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_2_1-solution000006.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_2_1-solution000007.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_2_1.eprime create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_2_2-solution000001.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_2_2-solution000002.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_2_2-solution000003.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_2_2-solution000004.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_2_2-solution000005.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_2_2-solution000006.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_2_2-solution000007.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_2_2.eprime create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_2_3-solution000001.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_2_3-solution000002.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_2_3-solution000003.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_2_3-solution000004.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_2_3-solution000005.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_2_3-solution000006.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_2_3-solution000007.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_2_3.eprime create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_3_1-solution000001.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_3_1-solution000002.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_3_1-solution000003.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_3_1-solution000004.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_3_1-solution000005.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_3_1-solution000006.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_3_1-solution000007.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_3_1.eprime create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_3_2-solution000001.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_3_2-solution000002.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_3_2-solution000003.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_3_2-solution000004.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_3_2-solution000005.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_3_2-solution000006.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_3_2-solution000007.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_3_2.eprime create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_3_3-solution000001.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_3_3-solution000002.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_3_3-solution000003.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_3_3-solution000004.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_3_3-solution000005.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_3_3-solution000006.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_3_3-solution000007.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_3_3.eprime create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_4_1-solution000001.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_4_1-solution000002.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_4_1-solution000003.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_4_1-solution000004.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_4_1-solution000005.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_4_1-solution000006.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_4_1-solution000007.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_4_1.eprime create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_4_2-solution000001.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_4_2-solution000002.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_4_2-solution000003.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_4_2-solution000004.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_4_2-solution000005.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_4_2-solution000006.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_4_2-solution000007.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_4_2.eprime create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_4_3-solution000001.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_4_3-solution000002.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_4_3-solution000003.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_4_3-solution000004.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_4_3-solution000005.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_4_3-solution000006.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_4_3-solution000007.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_4_3.eprime create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_4_4-solution000001.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_4_4-solution000002.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_4_4-solution000003.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_4_4-solution000004.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_4_4-solution000005.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_4_4-solution000006.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_4_4-solution000007.solution create mode 100644 tests/exhaustive/basic/comprehension_letting/expected/model_4_4_4.eprime create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_1_1-solution000001.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_1_1-solution000002.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_1_1-solution000003.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_1_1-solution000004.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_1_1-solution000005.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_1_1-solution000006.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_1_1-solution000007.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_1_1-solution000008.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_1_1.eprime create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_1_2-solution000001.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_1_2-solution000002.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_1_2-solution000003.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_1_2-solution000004.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_1_2-solution000005.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_1_2-solution000006.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_1_2-solution000007.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_1_2-solution000008.solution rename tests/exhaustive/basic/cut_01_on/expected/{model_1_2_1.eprime.orig => model_1_1_2.eprime} (88%) create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_1_3-solution000001.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_1_3-solution000002.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_1_3-solution000003.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_1_3-solution000004.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_1_3-solution000005.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_1_3-solution000006.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_1_3-solution000007.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_1_3-solution000008.solution rename tests/exhaustive/basic/cut_01_on/expected/{model_1_3_1.eprime.orig => model_1_1_3.eprime} (88%) create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_1_4-solution000001.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_1_4-solution000002.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_1_4-solution000003.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_1_4-solution000004.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_1_4-solution000005.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_1_4-solution000006.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_1_4-solution000007.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_1_4-solution000008.solution rename tests/exhaustive/basic/cut_01_on/expected/{model_1_4_1.eprime.orig => model_1_1_4.eprime} (90%) create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_2_1-solution000001.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_2_1-solution000002.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_2_1-solution000003.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_2_1-solution000004.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_2_1-solution000005.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_2_1-solution000006.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_2_1-solution000007.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_2_1-solution000008.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_2_3-solution000001.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_2_3-solution000002.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_2_3-solution000003.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_2_3-solution000004.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_2_3-solution000005.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_2_3-solution000006.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_2_3-solution000007.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_2_3-solution000008.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_2_4-solution000001.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_2_4-solution000002.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_2_4-solution000003.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_2_4-solution000004.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_2_4-solution000005.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_2_4-solution000006.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_2_4-solution000007.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_2_4-solution000008.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_3_1-solution000001.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_3_1-solution000002.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_3_1-solution000003.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_3_1-solution000004.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_3_1-solution000005.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_3_1-solution000006.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_3_1-solution000007.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_3_1-solution000008.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_3_2-solution000001.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_3_2-solution000002.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_3_2-solution000003.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_3_2-solution000004.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_3_2-solution000005.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_3_2-solution000006.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_3_2-solution000007.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_3_2-solution000008.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_3_4-solution000001.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_3_4-solution000002.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_3_4-solution000003.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_3_4-solution000004.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_3_4-solution000005.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_3_4-solution000006.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_3_4-solution000007.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_3_4-solution000008.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_4_1-solution000001.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_4_1-solution000002.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_4_1-solution000003.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_4_1-solution000004.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_4_1-solution000005.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_4_1-solution000006.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_4_1-solution000007.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_4_1-solution000008.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_4_2-solution000001.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_4_2-solution000002.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_4_2-solution000003.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_4_2-solution000004.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_4_2-solution000005.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_4_2-solution000006.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_4_2-solution000007.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_4_2-solution000008.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_4_3-solution000001.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_4_3-solution000002.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_4_3-solution000003.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_4_3-solution000004.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_4_3-solution000005.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_4_3-solution000006.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_4_3-solution000007.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_1_4_3-solution000008.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_1_1-solution000001.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_1_1-solution000002.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_1_1-solution000003.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_1_1-solution000004.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_1_1-solution000005.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_1_1-solution000006.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_1_1-solution000007.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_1_1-solution000008.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_1_3-solution000001.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_1_3-solution000002.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_1_3-solution000003.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_1_3-solution000004.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_1_3-solution000005.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_1_3-solution000006.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_1_3-solution000007.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_1_3-solution000008.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_1_4-solution000001.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_1_4-solution000002.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_1_4-solution000003.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_1_4-solution000004.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_1_4-solution000005.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_1_4-solution000006.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_1_4-solution000007.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_1_4-solution000008.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_2_1-solution000001.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_2_1-solution000002.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_2_1-solution000003.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_2_1-solution000004.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_2_1-solution000005.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_2_1-solution000006.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_2_1-solution000007.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_2_1-solution000008.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_2_1.eprime.orig create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_2_2-solution000001.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_2_2-solution000002.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_2_2-solution000003.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_2_2-solution000004.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_2_2-solution000005.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_2_2-solution000006.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_2_2-solution000007.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_2_2-solution000008.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_2_2.eprime.orig create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_2_3-solution000001.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_2_3-solution000002.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_2_3-solution000003.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_2_3-solution000004.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_2_3-solution000005.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_2_3-solution000006.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_2_3-solution000007.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_2_3-solution000008.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_2_4-solution000001.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_2_4-solution000002.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_2_4-solution000003.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_2_4-solution000004.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_2_4-solution000005.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_2_4-solution000006.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_2_4-solution000007.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_2_4-solution000008.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_3_1-solution000001.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_3_1-solution000002.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_3_1-solution000003.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_3_1-solution000004.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_3_1-solution000005.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_3_1-solution000006.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_3_1-solution000007.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_3_1-solution000008.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_3_2-solution000001.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_3_2-solution000002.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_3_2-solution000003.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_3_2-solution000004.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_3_2-solution000005.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_3_2-solution000006.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_3_2-solution000007.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_3_2-solution000008.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_3_4-solution000001.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_3_4-solution000002.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_3_4-solution000003.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_3_4-solution000004.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_3_4-solution000005.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_3_4-solution000006.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_3_4-solution000007.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_3_4-solution000008.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_4_1-solution000001.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_4_1-solution000002.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_4_1-solution000003.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_4_1-solution000004.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_4_1-solution000005.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_4_1-solution000006.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_4_1-solution000007.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_4_1-solution000008.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_4_2-solution000001.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_4_2-solution000002.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_4_2-solution000003.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_4_2-solution000004.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_4_2-solution000005.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_4_2-solution000006.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_4_2-solution000007.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_4_2-solution000008.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_4_3-solution000001.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_4_3-solution000002.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_4_3-solution000003.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_4_3-solution000004.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_4_3-solution000005.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_4_3-solution000006.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_4_3-solution000007.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_2_4_3-solution000008.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_1_1-solution000001.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_1_1-solution000002.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_1_1-solution000003.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_1_1-solution000004.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_1_1-solution000005.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_1_1-solution000006.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_1_1-solution000007.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_1_1-solution000008.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_1_2-solution000001.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_1_2-solution000002.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_1_2-solution000003.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_1_2-solution000004.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_1_2-solution000005.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_1_2-solution000006.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_1_2-solution000007.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_1_2-solution000008.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_1_4-solution000001.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_1_4-solution000002.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_1_4-solution000003.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_1_4-solution000004.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_1_4-solution000005.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_1_4-solution000006.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_1_4-solution000007.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_1_4-solution000008.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_2_1-solution000001.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_2_1-solution000002.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_2_1-solution000003.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_2_1-solution000004.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_2_1-solution000005.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_2_1-solution000006.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_2_1-solution000007.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_2_1-solution000008.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_2_2-solution000001.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_2_2-solution000002.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_2_2-solution000003.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_2_2-solution000004.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_2_2-solution000005.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_2_2-solution000006.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_2_2-solution000007.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_2_2-solution000008.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_2_4-solution000001.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_2_4-solution000002.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_2_4-solution000003.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_2_4-solution000004.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_2_4-solution000005.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_2_4-solution000006.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_2_4-solution000007.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_2_4-solution000008.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_3_1-solution000001.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_3_1-solution000002.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_3_1-solution000003.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_3_1-solution000004.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_3_1-solution000005.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_3_1-solution000006.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_3_1-solution000007.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_3_1-solution000008.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_3_1.eprime.orig create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_3_2-solution000001.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_3_2-solution000002.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_3_2-solution000003.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_3_2-solution000004.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_3_2-solution000005.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_3_2-solution000006.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_3_2-solution000007.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_3_2-solution000008.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_3_3-solution000001.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_3_3-solution000002.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_3_3-solution000003.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_3_3-solution000004.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_3_3-solution000005.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_3_3-solution000006.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_3_3-solution000007.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_3_3-solution000008.solution delete mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_3_3.eprime.orig create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_3_4-solution000001.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_3_4-solution000002.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_3_4-solution000003.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_3_4-solution000004.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_3_4-solution000005.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_3_4-solution000006.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_3_4-solution000007.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_3_4-solution000008.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_4_1-solution000001.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_4_1-solution000002.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_4_1-solution000003.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_4_1-solution000004.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_4_1-solution000005.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_4_1-solution000006.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_4_1-solution000007.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_4_1-solution000008.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_4_2-solution000001.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_4_2-solution000002.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_4_2-solution000003.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_4_2-solution000004.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_4_2-solution000005.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_4_2-solution000006.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_4_2-solution000007.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_4_2-solution000008.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_4_3-solution000001.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_4_3-solution000002.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_4_3-solution000003.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_4_3-solution000004.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_4_3-solution000005.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_4_3-solution000006.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_4_3-solution000007.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_3_4_3-solution000008.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_1_1-solution000001.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_1_1-solution000002.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_1_1-solution000003.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_1_1-solution000004.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_1_1-solution000005.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_1_1-solution000006.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_1_1-solution000007.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_1_1-solution000008.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_1_2-solution000001.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_1_2-solution000002.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_1_2-solution000003.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_1_2-solution000004.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_1_2-solution000005.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_1_2-solution000006.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_1_2-solution000007.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_1_2-solution000008.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_1_3-solution000001.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_1_3-solution000002.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_1_3-solution000003.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_1_3-solution000004.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_1_3-solution000005.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_1_3-solution000006.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_1_3-solution000007.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_1_3-solution000008.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_2_1-solution000001.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_2_1-solution000002.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_2_1-solution000003.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_2_1-solution000004.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_2_1-solution000005.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_2_1-solution000006.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_2_1-solution000007.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_2_1-solution000008.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_2_2-solution000001.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_2_2-solution000002.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_2_2-solution000003.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_2_2-solution000004.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_2_2-solution000005.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_2_2-solution000006.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_2_2-solution000007.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_2_2-solution000008.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_2_3-solution000001.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_2_3-solution000002.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_2_3-solution000003.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_2_3-solution000004.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_2_3-solution000005.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_2_3-solution000006.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_2_3-solution000007.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_2_3-solution000008.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_3_1-solution000001.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_3_1-solution000002.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_3_1-solution000003.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_3_1-solution000004.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_3_1-solution000005.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_3_1-solution000006.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_3_1-solution000007.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_3_1-solution000008.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_3_2-solution000001.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_3_2-solution000002.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_3_2-solution000003.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_3_2-solution000004.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_3_2-solution000005.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_3_2-solution000006.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_3_2-solution000007.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_3_2-solution000008.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_3_3-solution000001.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_3_3-solution000002.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_3_3-solution000003.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_3_3-solution000004.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_3_3-solution000005.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_3_3-solution000006.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_3_3-solution000007.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_3_3-solution000008.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_4_1-solution000001.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_4_1-solution000002.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_4_1-solution000003.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_4_1-solution000004.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_4_1-solution000005.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_4_1-solution000006.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_4_1-solution000007.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_4_1-solution000008.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_4_2-solution000001.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_4_2-solution000002.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_4_2-solution000003.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_4_2-solution000004.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_4_2-solution000005.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_4_2-solution000006.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_4_2-solution000007.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_4_2-solution000008.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_4_3-solution000001.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_4_3-solution000002.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_4_3-solution000003.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_4_3-solution000004.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_4_3-solution000005.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_4_3-solution000006.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_4_3-solution000007.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_4_3-solution000008.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_4_4-solution000001.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_4_4-solution000002.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_4_4-solution000003.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_4_4-solution000004.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_4_4-solution000005.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_4_4-solution000006.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_4_4-solution000007.solution create mode 100644 tests/exhaustive/basic/cut_01_on/expected/model_4_4_4-solution000008.solution create mode 100644 tests/exhaustive/basic/function_complex_01/expected/model_1-solution000001.solution create mode 100644 tests/exhaustive/basic/function_complex_01/expected/model_1-solution000002.solution create mode 100644 tests/exhaustive/basic/function_complex_01/expected/model_1-solution000003.solution create mode 100644 tests/exhaustive/basic/function_complex_01/expected/model_1-solution000004.solution create mode 100644 tests/exhaustive/basic/function_complex_01/expected/model_1-solution000005.solution create mode 100644 tests/exhaustive/basic/function_complex_01/expected/model_1-solution000006.solution create mode 100644 tests/exhaustive/basic/function_complex_01/expected/model_2-solution000001.solution create mode 100644 tests/exhaustive/basic/function_complex_01/expected/model_2-solution000002.solution create mode 100644 tests/exhaustive/basic/function_complex_01/expected/model_2-solution000003.solution create mode 100644 tests/exhaustive/basic/function_complex_01/expected/model_2-solution000004.solution create mode 100644 tests/exhaustive/basic/function_complex_01/expected/model_2-solution000005.solution create mode 100644 tests/exhaustive/basic/function_complex_01/expected/model_2-solution000006.solution delete mode 100644 tests/exhaustive/basic/function_range/expected/model.eprime.orig create mode 100644 tests/exhaustive/basic/matrix_of_set_02/expected/model_1_1-solution000001.solution create mode 100644 tests/exhaustive/basic/matrix_of_set_02/expected/model_1_1-solution000002.solution create mode 100644 tests/exhaustive/basic/matrix_of_set_02/expected/model_1_1-solution000003.solution create mode 100644 tests/exhaustive/basic/matrix_of_set_02/expected/model_1_1-solution000004.solution create mode 100644 tests/exhaustive/basic/matrix_of_set_02/expected/model_1_1.eprime create mode 100644 tests/exhaustive/basic/matrix_of_set_02/expected/model_1_2-solution000001.solution create mode 100644 tests/exhaustive/basic/matrix_of_set_02/expected/model_1_2-solution000002.solution create mode 100644 tests/exhaustive/basic/matrix_of_set_02/expected/model_1_2-solution000003.solution create mode 100644 tests/exhaustive/basic/matrix_of_set_02/expected/model_1_2-solution000004.solution create mode 100644 tests/exhaustive/basic/matrix_of_set_02/expected/model_1_2.eprime create mode 100644 tests/exhaustive/basic/matrix_of_set_02/expected/model_1_3-solution000001.solution create mode 100644 tests/exhaustive/basic/matrix_of_set_02/expected/model_1_3-solution000002.solution create mode 100644 tests/exhaustive/basic/matrix_of_set_02/expected/model_1_3-solution000003.solution create mode 100644 tests/exhaustive/basic/matrix_of_set_02/expected/model_1_3-solution000004.solution create mode 100644 tests/exhaustive/basic/matrix_of_set_02/expected/model_1_3.eprime create mode 100644 tests/exhaustive/basic/matrix_of_set_02/expected/model_1_4-solution000001.solution create mode 100644 tests/exhaustive/basic/matrix_of_set_02/expected/model_1_4-solution000002.solution create mode 100644 tests/exhaustive/basic/matrix_of_set_02/expected/model_1_4-solution000003.solution create mode 100644 tests/exhaustive/basic/matrix_of_set_02/expected/model_1_4-solution000004.solution create mode 100644 tests/exhaustive/basic/matrix_of_set_02/expected/model_1_4.eprime create mode 100644 tests/exhaustive/basic/matrix_of_set_02/expected/model_2_1-solution000001.solution create mode 100644 tests/exhaustive/basic/matrix_of_set_02/expected/model_2_1-solution000002.solution create mode 100644 tests/exhaustive/basic/matrix_of_set_02/expected/model_2_1-solution000003.solution create mode 100644 tests/exhaustive/basic/matrix_of_set_02/expected/model_2_1-solution000004.solution create mode 100644 tests/exhaustive/basic/matrix_of_set_02/expected/model_2_1.eprime create mode 100644 tests/exhaustive/basic/matrix_of_set_02/expected/model_2_2-solution000001.solution create mode 100644 tests/exhaustive/basic/matrix_of_set_02/expected/model_2_2-solution000002.solution create mode 100644 tests/exhaustive/basic/matrix_of_set_02/expected/model_2_2-solution000003.solution create mode 100644 tests/exhaustive/basic/matrix_of_set_02/expected/model_2_2-solution000004.solution create mode 100644 tests/exhaustive/basic/matrix_of_set_02/expected/model_2_2.eprime create mode 100644 tests/exhaustive/basic/matrix_of_set_02/expected/model_2_3-solution000001.solution create mode 100644 tests/exhaustive/basic/matrix_of_set_02/expected/model_2_3-solution000002.solution create mode 100644 tests/exhaustive/basic/matrix_of_set_02/expected/model_2_3-solution000003.solution create mode 100644 tests/exhaustive/basic/matrix_of_set_02/expected/model_2_3-solution000004.solution create mode 100644 tests/exhaustive/basic/matrix_of_set_02/expected/model_2_3.eprime create mode 100644 tests/exhaustive/basic/matrix_of_set_02/expected/model_2_4-solution000001.solution create mode 100644 tests/exhaustive/basic/matrix_of_set_02/expected/model_2_4-solution000002.solution create mode 100644 tests/exhaustive/basic/matrix_of_set_02/expected/model_2_4-solution000003.solution create mode 100644 tests/exhaustive/basic/matrix_of_set_02/expected/model_2_4-solution000004.solution create mode 100644 tests/exhaustive/basic/matrix_of_set_02/expected/model_2_4.eprime create mode 100644 tests/exhaustive/basic/matrix_of_set_02/expected/model_3_1-solution000001.solution create mode 100644 tests/exhaustive/basic/matrix_of_set_02/expected/model_3_1-solution000002.solution create mode 100644 tests/exhaustive/basic/matrix_of_set_02/expected/model_3_1-solution000003.solution create mode 100644 tests/exhaustive/basic/matrix_of_set_02/expected/model_3_1-solution000004.solution create mode 100644 tests/exhaustive/basic/matrix_of_set_02/expected/model_3_1.eprime create mode 100644 tests/exhaustive/basic/matrix_of_set_02/expected/model_3_2-solution000001.solution create mode 100644 tests/exhaustive/basic/matrix_of_set_02/expected/model_3_2-solution000002.solution create mode 100644 tests/exhaustive/basic/matrix_of_set_02/expected/model_3_2-solution000003.solution create mode 100644 tests/exhaustive/basic/matrix_of_set_02/expected/model_3_2-solution000004.solution create mode 100644 tests/exhaustive/basic/matrix_of_set_02/expected/model_3_2.eprime create mode 100644 tests/exhaustive/basic/matrix_of_set_02/expected/model_3_3-solution000001.solution create mode 100644 tests/exhaustive/basic/matrix_of_set_02/expected/model_3_3-solution000002.solution create mode 100644 tests/exhaustive/basic/matrix_of_set_02/expected/model_3_3-solution000003.solution create mode 100644 tests/exhaustive/basic/matrix_of_set_02/expected/model_3_3-solution000004.solution create mode 100644 tests/exhaustive/basic/matrix_of_set_02/expected/model_3_3.eprime create mode 100644 tests/exhaustive/basic/matrix_of_set_02/expected/model_3_4-solution000001.solution create mode 100644 tests/exhaustive/basic/matrix_of_set_02/expected/model_3_4-solution000002.solution create mode 100644 tests/exhaustive/basic/matrix_of_set_02/expected/model_3_4-solution000003.solution create mode 100644 tests/exhaustive/basic/matrix_of_set_02/expected/model_3_4-solution000004.solution create mode 100644 tests/exhaustive/basic/matrix_of_set_02/expected/model_3_4.eprime create mode 100644 tests/exhaustive/basic/matrix_of_set_02/expected/model_4_1-solution000001.solution create mode 100644 tests/exhaustive/basic/matrix_of_set_02/expected/model_4_1-solution000002.solution create mode 100644 tests/exhaustive/basic/matrix_of_set_02/expected/model_4_1-solution000003.solution create mode 100644 tests/exhaustive/basic/matrix_of_set_02/expected/model_4_1-solution000004.solution create mode 100644 tests/exhaustive/basic/matrix_of_set_02/expected/model_4_1.eprime create mode 100644 tests/exhaustive/basic/matrix_of_set_02/expected/model_4_2-solution000001.solution create mode 100644 tests/exhaustive/basic/matrix_of_set_02/expected/model_4_2-solution000002.solution create mode 100644 tests/exhaustive/basic/matrix_of_set_02/expected/model_4_2-solution000003.solution create mode 100644 tests/exhaustive/basic/matrix_of_set_02/expected/model_4_2-solution000004.solution create mode 100644 tests/exhaustive/basic/matrix_of_set_02/expected/model_4_2.eprime create mode 100644 tests/exhaustive/basic/matrix_of_set_02/expected/model_4_3-solution000001.solution create mode 100644 tests/exhaustive/basic/matrix_of_set_02/expected/model_4_3-solution000002.solution create mode 100644 tests/exhaustive/basic/matrix_of_set_02/expected/model_4_3-solution000003.solution create mode 100644 tests/exhaustive/basic/matrix_of_set_02/expected/model_4_3-solution000004.solution create mode 100644 tests/exhaustive/basic/matrix_of_set_02/expected/model_4_3.eprime create mode 100644 tests/exhaustive/basic/matrix_of_set_02/expected/model_4_4-solution000001.solution create mode 100644 tests/exhaustive/basic/matrix_of_set_02/expected/model_4_4-solution000002.solution create mode 100644 tests/exhaustive/basic/matrix_of_set_02/expected/model_4_4-solution000003.solution create mode 100644 tests/exhaustive/basic/matrix_of_set_02/expected/model_4_4-solution000004.solution create mode 100644 tests/exhaustive/basic/matrix_of_set_02/expected/model_4_4.eprime create mode 100644 tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_1_1-solution000001.solution create mode 100644 tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_1_1.eprime create mode 100644 tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_1_2-solution000001.solution create mode 100644 tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_1_2.eprime create mode 100644 tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_1_3-solution000001.solution create mode 100644 tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_1_3.eprime create mode 100644 tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_1_4-solution000001.solution create mode 100644 tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_1_4.eprime create mode 100644 tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_2_1-solution000001.solution create mode 100644 tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_2_1.eprime create mode 100644 tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_2_2-solution000001.solution create mode 100644 tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_2_2.eprime create mode 100644 tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_2_3-solution000001.solution create mode 100644 tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_2_3.eprime create mode 100644 tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_2_4-solution000001.solution create mode 100644 tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_2_4.eprime create mode 100644 tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_3_1-solution000001.solution create mode 100644 tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_3_1.eprime create mode 100644 tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_3_2-solution000001.solution create mode 100644 tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_3_2.eprime create mode 100644 tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_3_3-solution000001.solution create mode 100644 tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_3_3.eprime create mode 100644 tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_3_4-solution000001.solution create mode 100644 tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_3_4.eprime create mode 100644 tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_4_1-solution000001.solution create mode 100644 tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_4_1.eprime create mode 100644 tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_4_2-solution000001.solution create mode 100644 tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_4_2.eprime create mode 100644 tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_4_3-solution000001.solution create mode 100644 tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_4_3.eprime create mode 100644 tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_4_4-solution000001.solution create mode 100644 tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_4_4.eprime create mode 100644 tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_1_1_1_1-solution000001.solution create mode 100644 tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_1_1_1_2-solution000001.solution create mode 100644 tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_1_1_2_1-solution000001.solution create mode 100644 tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_1_1_2_2-solution000001.solution create mode 100644 tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_1_2_1_1-solution000001.solution create mode 100644 tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_1_2_1_2-solution000001.solution create mode 100644 tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_1_2_2_1-solution000001.solution create mode 100644 tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_1_2_2_2-solution000001.solution create mode 100644 tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_2_1_1_1-solution000001.solution create mode 100644 tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_2_1_1_2-solution000001.solution create mode 100644 tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_2_1_2_1-solution000001.solution create mode 100644 tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_2_1_2_2-solution000001.solution create mode 100644 tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_2_2_1_1-solution000001.solution create mode 100644 tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_2_2_1_2-solution000001.solution create mode 100644 tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_2_2_2_1-solution000001.solution create mode 100644 tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_2_2_2_2-solution000001.solution create mode 100644 tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_1_1_1_1-solution000001.solution create mode 100644 tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_1_1_1_2-solution000001.solution create mode 100644 tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_1_1_2_1-solution000001.solution create mode 100644 tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_1_1_2_2-solution000001.solution create mode 100644 tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_1_2_1_1-solution000001.solution create mode 100644 tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_1_2_1_2-solution000001.solution create mode 100644 tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_1_2_2_1-solution000001.solution create mode 100644 tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_1_2_2_2-solution000001.solution create mode 100644 tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_2_1_1_1-solution000001.solution create mode 100644 tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_2_1_1_2-solution000001.solution create mode 100644 tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_2_1_2_1-solution000001.solution create mode 100644 tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_2_1_2_2-solution000001.solution create mode 100644 tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_2_2_1_1-solution000001.solution rename tests/exhaustive/basic/{matrix_of_set_04_2dLit/expected/model_2_2_1_1.eprime.orig => matrix_of_set_05_2dLit/expected/model_2_2_1_1.eprime} (60%) create mode 100644 tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_2_2_1_2-solution000001.solution create mode 100644 tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_2_2_2_1-solution000001.solution create mode 100644 tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_2_2_2_2-solution000001.solution create mode 100644 tests/exhaustive/basic/mset01_param/expected/model_1_1-param1-solution000001.solution create mode 100644 tests/exhaustive/basic/mset01_param/expected/model_1_1-param1.eprime-param create mode 100644 tests/exhaustive/basic/mset01_param/expected/model_1_1-param4-solution000001.solution create mode 100644 tests/exhaustive/basic/mset01_param/expected/model_1_1-param4.eprime-param create mode 100644 tests/exhaustive/basic/mset01_param/expected/model_1_1-param7-solution000001.solution create mode 100644 tests/exhaustive/basic/mset01_param/expected/model_1_1-param7.eprime-param create mode 100644 tests/exhaustive/basic/mset01_param/expected/model_1_2-param1-solution000001.solution create mode 100644 tests/exhaustive/basic/mset01_param/expected/model_1_2-param1.eprime-param create mode 100644 tests/exhaustive/basic/mset01_param/expected/model_1_2-param4-solution000001.solution create mode 100644 tests/exhaustive/basic/mset01_param/expected/model_1_2-param4.eprime-param create mode 100644 tests/exhaustive/basic/mset01_param/expected/model_1_2-param7-solution000001.solution create mode 100644 tests/exhaustive/basic/mset01_param/expected/model_1_2-param7.eprime-param create mode 100644 tests/exhaustive/basic/mset01_param/expected/model_1_3-param1-solution000001.solution create mode 100644 tests/exhaustive/basic/mset01_param/expected/model_1_3-param1.eprime-param create mode 100644 tests/exhaustive/basic/mset01_param/expected/model_1_3-param4-solution000001.solution create mode 100644 tests/exhaustive/basic/mset01_param/expected/model_1_3-param4.eprime-param create mode 100644 tests/exhaustive/basic/mset01_param/expected/model_1_3-param7-solution000001.solution create mode 100644 tests/exhaustive/basic/mset01_param/expected/model_1_3-param7.eprime-param create mode 100644 tests/exhaustive/basic/mset01_param/expected/model_2_1-param1-solution000001.solution create mode 100644 tests/exhaustive/basic/mset01_param/expected/model_2_1-param1.eprime-param create mode 100644 tests/exhaustive/basic/mset01_param/expected/model_2_1-param4-solution000001.solution create mode 100644 tests/exhaustive/basic/mset01_param/expected/model_2_1-param4.eprime-param create mode 100644 tests/exhaustive/basic/mset01_param/expected/model_2_1-param7-solution000001.solution create mode 100644 tests/exhaustive/basic/mset01_param/expected/model_2_1-param7.eprime-param create mode 100644 tests/exhaustive/basic/mset01_param/expected/model_2_2-param1-solution000001.solution create mode 100644 tests/exhaustive/basic/mset01_param/expected/model_2_2-param1.eprime-param create mode 100644 tests/exhaustive/basic/mset01_param/expected/model_2_2-param4-solution000001.solution create mode 100644 tests/exhaustive/basic/mset01_param/expected/model_2_2-param4.eprime-param create mode 100644 tests/exhaustive/basic/mset01_param/expected/model_2_2-param7-solution000001.solution create mode 100644 tests/exhaustive/basic/mset01_param/expected/model_2_2-param7.eprime-param create mode 100644 tests/exhaustive/basic/mset01_param/expected/model_2_2.eprime create mode 100644 tests/exhaustive/basic/mset01_param/expected/model_2_3-param1-solution000001.solution create mode 100644 tests/exhaustive/basic/mset01_param/expected/model_2_3-param1.eprime-param create mode 100644 tests/exhaustive/basic/mset01_param/expected/model_2_3-param4-solution000001.solution create mode 100644 tests/exhaustive/basic/mset01_param/expected/model_2_3-param4.eprime-param create mode 100644 tests/exhaustive/basic/mset01_param/expected/model_2_3-param7-solution000001.solution create mode 100644 tests/exhaustive/basic/mset01_param/expected/model_2_3-param7.eprime-param create mode 100644 tests/exhaustive/basic/mset01_param/expected/model_2_3.eprime create mode 100644 tests/exhaustive/basic/mset01_param/expected/model_3_1-param1-solution000001.solution create mode 100644 tests/exhaustive/basic/mset01_param/expected/model_3_1-param1.eprime-param create mode 100644 tests/exhaustive/basic/mset01_param/expected/model_3_1-param4-solution000001.solution create mode 100644 tests/exhaustive/basic/mset01_param/expected/model_3_1-param4.eprime-param create mode 100644 tests/exhaustive/basic/mset01_param/expected/model_3_1-param7-solution000001.solution create mode 100644 tests/exhaustive/basic/mset01_param/expected/model_3_1-param7.eprime-param create mode 100644 tests/exhaustive/basic/mset01_param/expected/model_3_2-param1-solution000001.solution create mode 100644 tests/exhaustive/basic/mset01_param/expected/model_3_2-param1.eprime-param create mode 100644 tests/exhaustive/basic/mset01_param/expected/model_3_2-param4-solution000001.solution create mode 100644 tests/exhaustive/basic/mset01_param/expected/model_3_2-param4.eprime-param create mode 100644 tests/exhaustive/basic/mset01_param/expected/model_3_2-param7-solution000001.solution create mode 100644 tests/exhaustive/basic/mset01_param/expected/model_3_2-param7.eprime-param create mode 100644 tests/exhaustive/basic/mset01_param/expected/model_3_2.eprime create mode 100644 tests/exhaustive/basic/mset01_param/expected/model_3_3-param1-solution000001.solution create mode 100644 tests/exhaustive/basic/mset01_param/expected/model_3_3-param1.eprime-param create mode 100644 tests/exhaustive/basic/mset01_param/expected/model_3_3-param4-solution000001.solution create mode 100644 tests/exhaustive/basic/mset01_param/expected/model_3_3-param4.eprime-param create mode 100644 tests/exhaustive/basic/mset01_param/expected/model_3_3-param7-solution000001.solution create mode 100644 tests/exhaustive/basic/mset01_param/expected/model_3_3-param7.eprime-param create mode 100644 tests/exhaustive/basic/mset01_param/expected/model_3_3.eprime create mode 100644 tests/exhaustive/basic/name-reuse/expected/model_1_1-solution000001.solution create mode 100644 tests/exhaustive/basic/name-reuse/expected/model_1_1-solution000002.solution create mode 100644 tests/exhaustive/basic/name-reuse/expected/model_1_1.eprime create mode 100644 tests/exhaustive/basic/name-reuse/expected/model_1_2-solution000001.solution create mode 100644 tests/exhaustive/basic/name-reuse/expected/model_1_2-solution000002.solution create mode 100644 tests/exhaustive/basic/name-reuse/expected/model_1_2.eprime create mode 100644 tests/exhaustive/basic/name-reuse/expected/model_1_3-solution000001.solution create mode 100644 tests/exhaustive/basic/name-reuse/expected/model_1_3-solution000002.solution create mode 100644 tests/exhaustive/basic/name-reuse/expected/model_1_3.eprime create mode 100644 tests/exhaustive/basic/name-reuse/expected/model_1_4-solution000001.solution create mode 100644 tests/exhaustive/basic/name-reuse/expected/model_1_4-solution000002.solution create mode 100644 tests/exhaustive/basic/name-reuse/expected/model_1_4.eprime create mode 100644 tests/exhaustive/basic/name-reuse/expected/model_2_1-solution000001.solution create mode 100644 tests/exhaustive/basic/name-reuse/expected/model_2_1-solution000002.solution create mode 100644 tests/exhaustive/basic/name-reuse/expected/model_2_1.eprime create mode 100644 tests/exhaustive/basic/name-reuse/expected/model_2_2-solution000001.solution create mode 100644 tests/exhaustive/basic/name-reuse/expected/model_2_2-solution000002.solution create mode 100644 tests/exhaustive/basic/name-reuse/expected/model_2_2.eprime create mode 100644 tests/exhaustive/basic/name-reuse/expected/model_2_3-solution000001.solution create mode 100644 tests/exhaustive/basic/name-reuse/expected/model_2_3-solution000002.solution create mode 100644 tests/exhaustive/basic/name-reuse/expected/model_2_3.eprime create mode 100644 tests/exhaustive/basic/name-reuse/expected/model_2_4-solution000001.solution create mode 100644 tests/exhaustive/basic/name-reuse/expected/model_2_4-solution000002.solution create mode 100644 tests/exhaustive/basic/name-reuse/expected/model_2_4.eprime create mode 100644 tests/exhaustive/basic/name-reuse/expected/model_3_1-solution000001.solution create mode 100644 tests/exhaustive/basic/name-reuse/expected/model_3_1-solution000002.solution create mode 100644 tests/exhaustive/basic/name-reuse/expected/model_3_1.eprime create mode 100644 tests/exhaustive/basic/name-reuse/expected/model_3_2-solution000001.solution create mode 100644 tests/exhaustive/basic/name-reuse/expected/model_3_2-solution000002.solution create mode 100644 tests/exhaustive/basic/name-reuse/expected/model_3_2.eprime create mode 100644 tests/exhaustive/basic/name-reuse/expected/model_3_3-solution000001.solution create mode 100644 tests/exhaustive/basic/name-reuse/expected/model_3_3-solution000002.solution create mode 100644 tests/exhaustive/basic/name-reuse/expected/model_3_3.eprime create mode 100644 tests/exhaustive/basic/name-reuse/expected/model_3_4-solution000001.solution create mode 100644 tests/exhaustive/basic/name-reuse/expected/model_3_4-solution000002.solution create mode 100644 tests/exhaustive/basic/name-reuse/expected/model_3_4.eprime create mode 100644 tests/exhaustive/basic/name-reuse/expected/model_4_1-solution000001.solution create mode 100644 tests/exhaustive/basic/name-reuse/expected/model_4_1-solution000002.solution create mode 100644 tests/exhaustive/basic/name-reuse/expected/model_4_1.eprime create mode 100644 tests/exhaustive/basic/name-reuse/expected/model_4_2-solution000001.solution create mode 100644 tests/exhaustive/basic/name-reuse/expected/model_4_2-solution000002.solution create mode 100644 tests/exhaustive/basic/name-reuse/expected/model_4_2.eprime create mode 100644 tests/exhaustive/basic/name-reuse/expected/model_4_3-solution000001.solution create mode 100644 tests/exhaustive/basic/name-reuse/expected/model_4_3-solution000002.solution create mode 100644 tests/exhaustive/basic/name-reuse/expected/model_4_3.eprime create mode 100644 tests/exhaustive/basic/name-reuse/expected/model_4_4-solution000001.solution create mode 100644 tests/exhaustive/basic/name-reuse/expected/model_4_4-solution000002.solution create mode 100644 tests/exhaustive/basic/name-reuse/expected/model_4_4.eprime delete mode 100644 tests/exhaustive/basic/partition_01/expected/model_2.eprime.orig create mode 100644 tests/exhaustive/basic/partition_05_1/expected/model_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/partition_05_1/expected/model_1.eprime.orig create mode 100644 tests/exhaustive/basic/partition_05_1/expected/model_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/partition_05_1/expected/model_2.eprime.orig create mode 100644 tests/exhaustive/basic/partition_05_1/expected/model_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/partition_05_1/expected/model_3.eprime.orig create mode 100644 tests/exhaustive/basic/partition_05_1/expected/model_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/partition_05_1/expected/model_4.eprime.orig create mode 100644 tests/exhaustive/basic/partition_05_2/expected/model_1-solution000001.solution delete mode 100644 tests/exhaustive/basic/partition_05_2/expected/model_1.eprime.orig create mode 100644 tests/exhaustive/basic/partition_05_2/expected/model_2-solution000001.solution delete mode 100644 tests/exhaustive/basic/partition_05_2/expected/model_2.eprime.orig create mode 100644 tests/exhaustive/basic/partition_05_2/expected/model_3-solution000001.solution delete mode 100644 tests/exhaustive/basic/partition_05_2/expected/model_3.eprime.orig create mode 100644 tests/exhaustive/basic/partition_05_2/expected/model_4-solution000001.solution delete mode 100644 tests/exhaustive/basic/partition_05_2/expected/model_4.eprime.orig create mode 100644 tests/exhaustive/basic/partition_06/expected/model_1_1-solution000001.solution create mode 100644 tests/exhaustive/basic/partition_06/expected/model_1_1-solution000002.solution create mode 100644 tests/exhaustive/basic/partition_06/expected/model_1_1-solution000003.solution create mode 100644 tests/exhaustive/basic/partition_06/expected/model_1_1.eprime create mode 100644 tests/exhaustive/basic/partition_06/expected/model_1_2-solution000001.solution create mode 100644 tests/exhaustive/basic/partition_06/expected/model_1_2-solution000002.solution create mode 100644 tests/exhaustive/basic/partition_06/expected/model_1_2-solution000003.solution create mode 100644 tests/exhaustive/basic/partition_06/expected/model_1_2.eprime create mode 100644 tests/exhaustive/basic/partition_06/expected/model_1_3-solution000001.solution create mode 100644 tests/exhaustive/basic/partition_06/expected/model_1_3-solution000002.solution create mode 100644 tests/exhaustive/basic/partition_06/expected/model_1_3-solution000003.solution delete mode 100644 tests/exhaustive/basic/partition_06/expected/model_1_3.eprime.orig create mode 100644 tests/exhaustive/basic/partition_06/expected/model_1_4-solution000001.solution create mode 100644 tests/exhaustive/basic/partition_06/expected/model_1_4-solution000002.solution create mode 100644 tests/exhaustive/basic/partition_06/expected/model_1_4-solution000003.solution create mode 100644 tests/exhaustive/basic/partition_06/expected/model_1_4.eprime create mode 100644 tests/exhaustive/basic/partition_06/expected/model_2_1-solution000001.solution create mode 100644 tests/exhaustive/basic/partition_06/expected/model_2_1-solution000002.solution create mode 100644 tests/exhaustive/basic/partition_06/expected/model_2_1-solution000003.solution create mode 100644 tests/exhaustive/basic/partition_06/expected/model_2_1.eprime create mode 100644 tests/exhaustive/basic/partition_06/expected/model_2_2-solution000001.solution create mode 100644 tests/exhaustive/basic/partition_06/expected/model_2_2-solution000002.solution create mode 100644 tests/exhaustive/basic/partition_06/expected/model_2_2-solution000003.solution create mode 100644 tests/exhaustive/basic/partition_06/expected/model_2_2.eprime create mode 100644 tests/exhaustive/basic/partition_06/expected/model_2_3-solution000001.solution create mode 100644 tests/exhaustive/basic/partition_06/expected/model_2_3-solution000002.solution create mode 100644 tests/exhaustive/basic/partition_06/expected/model_2_3-solution000003.solution delete mode 100644 tests/exhaustive/basic/partition_06/expected/model_2_3.eprime.orig create mode 100644 tests/exhaustive/basic/partition_06/expected/model_2_4-solution000001.solution create mode 100644 tests/exhaustive/basic/partition_06/expected/model_2_4-solution000002.solution create mode 100644 tests/exhaustive/basic/partition_06/expected/model_2_4-solution000003.solution create mode 100644 tests/exhaustive/basic/partition_06/expected/model_2_4.eprime create mode 100644 tests/exhaustive/basic/partition_06/expected/model_3_1-solution000001.solution create mode 100644 tests/exhaustive/basic/partition_06/expected/model_3_1-solution000002.solution create mode 100644 tests/exhaustive/basic/partition_06/expected/model_3_1-solution000003.solution delete mode 100644 tests/exhaustive/basic/partition_06/expected/model_3_1.eprime.orig create mode 100644 tests/exhaustive/basic/partition_06/expected/model_3_2-solution000001.solution create mode 100644 tests/exhaustive/basic/partition_06/expected/model_3_2-solution000002.solution create mode 100644 tests/exhaustive/basic/partition_06/expected/model_3_2-solution000003.solution delete mode 100644 tests/exhaustive/basic/partition_06/expected/model_3_2.eprime.orig create mode 100644 tests/exhaustive/basic/partition_06/expected/model_3_3-solution000001.solution create mode 100644 tests/exhaustive/basic/partition_06/expected/model_3_3-solution000002.solution create mode 100644 tests/exhaustive/basic/partition_06/expected/model_3_3-solution000003.solution delete mode 100644 tests/exhaustive/basic/partition_06/expected/model_3_3.eprime.orig create mode 100644 tests/exhaustive/basic/partition_06/expected/model_3_4-solution000001.solution create mode 100644 tests/exhaustive/basic/partition_06/expected/model_3_4-solution000002.solution create mode 100644 tests/exhaustive/basic/partition_06/expected/model_3_4-solution000003.solution delete mode 100644 tests/exhaustive/basic/partition_06/expected/model_3_4.eprime.orig create mode 100644 tests/exhaustive/basic/partition_06/expected/model_4_1-solution000001.solution create mode 100644 tests/exhaustive/basic/partition_06/expected/model_4_1-solution000002.solution create mode 100644 tests/exhaustive/basic/partition_06/expected/model_4_1-solution000003.solution create mode 100644 tests/exhaustive/basic/partition_06/expected/model_4_1.eprime create mode 100644 tests/exhaustive/basic/partition_06/expected/model_4_2-solution000001.solution create mode 100644 tests/exhaustive/basic/partition_06/expected/model_4_2-solution000002.solution create mode 100644 tests/exhaustive/basic/partition_06/expected/model_4_2-solution000003.solution create mode 100644 tests/exhaustive/basic/partition_06/expected/model_4_2.eprime create mode 100644 tests/exhaustive/basic/partition_06/expected/model_4_3-solution000001.solution create mode 100644 tests/exhaustive/basic/partition_06/expected/model_4_3-solution000002.solution create mode 100644 tests/exhaustive/basic/partition_06/expected/model_4_3-solution000003.solution delete mode 100644 tests/exhaustive/basic/partition_06/expected/model_4_3.eprime.orig create mode 100644 tests/exhaustive/basic/partition_06/expected/model_4_4-solution000001.solution create mode 100644 tests/exhaustive/basic/partition_06/expected/model_4_4-solution000002.solution create mode 100644 tests/exhaustive/basic/partition_06/expected/model_4_4-solution000003.solution create mode 100644 tests/exhaustive/basic/partition_06/expected/model_4_4.eprime create mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_1-p-solution000001.solution create mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_1-p-solution000002.solution create mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_1-p-solution000003.solution create mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_1-p-solution000004.solution create mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_1-p-solution000005.solution create mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_1-p-solution000006.solution create mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_1-p.eprime-param create mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_1.eprime create mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_2-p-solution000001.solution create mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_2-p-solution000002.solution create mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_2-p-solution000003.solution create mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_2-p-solution000004.solution create mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_2-p-solution000005.solution create mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_2-p-solution000006.solution create mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_2-p.eprime-param create mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_2.eprime create mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_3-p-solution000001.solution create mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_3-p-solution000002.solution create mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_3-p-solution000003.solution create mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_3-p-solution000004.solution create mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_3-p-solution000005.solution create mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_3-p-solution000006.solution create mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_3-p.eprime-param create mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_3.eprime create mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_4-p-solution000001.solution create mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_4-p-solution000002.solution create mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_4-p-solution000003.solution create mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_4-p-solution000004.solution create mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_4-p-solution000005.solution create mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_4-p-solution000006.solution create mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_4-p.eprime-param create mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_4.eprime create mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_1-p-solution000001.solution create mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_1-p-solution000002.solution create mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_1-p-solution000003.solution create mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_1-p-solution000004.solution create mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_1-p-solution000005.solution create mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_1-p-solution000006.solution create mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_1-p.eprime-param create mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_1.eprime create mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_2-p-solution000001.solution create mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_2-p-solution000002.solution create mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_2-p-solution000003.solution create mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_2-p-solution000004.solution create mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_2-p-solution000005.solution create mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_2-p-solution000006.solution create mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_2-p.eprime-param create mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_2.eprime create mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_3-p-solution000001.solution create mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_3-p-solution000002.solution create mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_3-p-solution000003.solution create mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_3-p-solution000004.solution create mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_3-p-solution000005.solution create mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_3-p-solution000006.solution create mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_3-p.eprime-param create mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_3.eprime create mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_4-p-solution000001.solution create mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_4-p-solution000002.solution create mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_4-p-solution000003.solution create mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_4-p-solution000004.solution create mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_4-p-solution000005.solution create mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_4-p-solution000006.solution create mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_4-p.eprime-param create mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_4.eprime create mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_1-p-solution000001.solution create mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_1-p-solution000002.solution create mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_1-p-solution000003.solution create mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_1-p-solution000004.solution create mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_1-p-solution000005.solution create mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_1-p-solution000006.solution create mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_1-p.eprime-param create mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_1.eprime create mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_2-p-solution000001.solution create mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_2-p-solution000002.solution create mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_2-p-solution000003.solution create mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_2-p-solution000004.solution create mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_2-p-solution000005.solution create mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_2-p-solution000006.solution create mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_2-p.eprime-param create mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_2.eprime create mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_3-p-solution000001.solution create mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_3-p-solution000002.solution create mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_3-p-solution000003.solution create mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_3-p-solution000004.solution create mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_3-p-solution000005.solution create mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_3-p-solution000006.solution create mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_3-p.eprime-param create mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_3.eprime create mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_4-p-solution000001.solution create mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_4-p-solution000002.solution create mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_4-p-solution000003.solution create mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_4-p-solution000004.solution create mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_4-p-solution000005.solution create mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_4-p-solution000006.solution create mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_4-p.eprime-param create mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_4.eprime create mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_1-p-solution000001.solution create mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_1-p-solution000002.solution create mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_1-p-solution000003.solution create mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_1-p-solution000004.solution create mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_1-p-solution000005.solution create mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_1-p-solution000006.solution create mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_1-p.eprime-param create mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_1.eprime create mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_2-p-solution000001.solution create mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_2-p-solution000002.solution create mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_2-p-solution000003.solution create mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_2-p-solution000004.solution create mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_2-p-solution000005.solution create mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_2-p-solution000006.solution create mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_2-p.eprime-param create mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_2.eprime create mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_3-p-solution000001.solution create mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_3-p-solution000002.solution create mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_3-p-solution000003.solution create mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_3-p-solution000004.solution create mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_3-p-solution000005.solution create mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_3-p-solution000006.solution create mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_3-p.eprime-param create mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_3.eprime create mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_4-p-solution000001.solution create mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_4-p-solution000002.solution create mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_4-p-solution000003.solution create mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_4-p-solution000004.solution create mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_4-p-solution000005.solution create mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_4-p-solution000006.solution create mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_4-p.eprime-param create mode 100644 tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_4.eprime create mode 100644 tests/exhaustive/basic/powerSetComprehensionPat/expected/model_1_1-solution000001.solution create mode 100644 tests/exhaustive/basic/powerSetComprehensionPat/expected/model_1_1.eprime create mode 100644 tests/exhaustive/basic/powerSetComprehensionPat/expected/model_1_2-solution000001.solution create mode 100644 tests/exhaustive/basic/powerSetComprehensionPat/expected/model_1_2.eprime create mode 100644 tests/exhaustive/basic/powerSetComprehensionPat/expected/model_1_3-solution000001.solution create mode 100644 tests/exhaustive/basic/powerSetComprehensionPat/expected/model_1_3.eprime create mode 100644 tests/exhaustive/basic/powerSetComprehensionPat/expected/model_1_4-solution000001.solution create mode 100644 tests/exhaustive/basic/powerSetComprehensionPat/expected/model_1_4.eprime create mode 100644 tests/exhaustive/basic/powerSetComprehensionPat/expected/model_2_1-solution000001.solution create mode 100644 tests/exhaustive/basic/powerSetComprehensionPat/expected/model_2_1.eprime create mode 100644 tests/exhaustive/basic/powerSetComprehensionPat/expected/model_2_2-solution000001.solution create mode 100644 tests/exhaustive/basic/powerSetComprehensionPat/expected/model_2_2.eprime create mode 100644 tests/exhaustive/basic/powerSetComprehensionPat/expected/model_2_3-solution000001.solution create mode 100644 tests/exhaustive/basic/powerSetComprehensionPat/expected/model_2_3.eprime create mode 100644 tests/exhaustive/basic/powerSetComprehensionPat/expected/model_2_4-solution000001.solution create mode 100644 tests/exhaustive/basic/powerSetComprehensionPat/expected/model_2_4.eprime create mode 100644 tests/exhaustive/basic/powerSetComprehensionPat/expected/model_3_1-solution000001.solution create mode 100644 tests/exhaustive/basic/powerSetComprehensionPat/expected/model_3_1.eprime create mode 100644 tests/exhaustive/basic/powerSetComprehensionPat/expected/model_3_2-solution000001.solution create mode 100644 tests/exhaustive/basic/powerSetComprehensionPat/expected/model_3_2.eprime create mode 100644 tests/exhaustive/basic/powerSetComprehensionPat/expected/model_3_3-solution000001.solution create mode 100644 tests/exhaustive/basic/powerSetComprehensionPat/expected/model_3_3.eprime create mode 100644 tests/exhaustive/basic/powerSetComprehensionPat/expected/model_3_4-solution000001.solution create mode 100644 tests/exhaustive/basic/powerSetComprehensionPat/expected/model_3_4.eprime create mode 100644 tests/exhaustive/basic/powerSetComprehensionPat/expected/model_4_1-solution000001.solution create mode 100644 tests/exhaustive/basic/powerSetComprehensionPat/expected/model_4_1.eprime create mode 100644 tests/exhaustive/basic/powerSetComprehensionPat/expected/model_4_2-solution000001.solution create mode 100644 tests/exhaustive/basic/powerSetComprehensionPat/expected/model_4_2.eprime create mode 100644 tests/exhaustive/basic/powerSetComprehensionPat/expected/model_4_3-solution000001.solution create mode 100644 tests/exhaustive/basic/powerSetComprehensionPat/expected/model_4_3.eprime create mode 100644 tests/exhaustive/basic/powerSetComprehensionPat/expected/model_4_4-solution000001.solution create mode 100644 tests/exhaustive/basic/powerSetComprehensionPat/expected/model_4_4.eprime create mode 100644 tests/exhaustive/basic/relation04_param/expected/model_1_1-param4-solution000001.solution create mode 100644 tests/exhaustive/basic/relation04_param/expected/model_1_1-param4.eprime-param create mode 100644 tests/exhaustive/basic/relation04_param/expected/model_1_1.eprime create mode 100644 tests/exhaustive/basic/relation04_param/expected/model_1_2-param4-solution000001.solution create mode 100644 tests/exhaustive/basic/relation04_param/expected/model_1_2-param4.eprime-param create mode 100644 tests/exhaustive/basic/relation04_param/expected/model_1_2.eprime create mode 100644 tests/exhaustive/basic/relation04_param/expected/model_1_3-param4-solution000001.solution create mode 100644 tests/exhaustive/basic/relation04_param/expected/model_1_3-param4.eprime-param delete mode 100644 tests/exhaustive/basic/relation04_param/expected/model_1_3.eprime.orig create mode 100644 tests/exhaustive/basic/relation04_param/expected/model_1_4-param4-solution000001.solution create mode 100644 tests/exhaustive/basic/relation04_param/expected/model_1_4-param4.eprime-param create mode 100644 tests/exhaustive/basic/relation04_param/expected/model_1_4.eprime create mode 100644 tests/exhaustive/basic/relation04_param/expected/model_2_1-param4-solution000001.solution create mode 100644 tests/exhaustive/basic/relation04_param/expected/model_2_1-param4.eprime-param create mode 100644 tests/exhaustive/basic/relation04_param/expected/model_2_1.eprime create mode 100644 tests/exhaustive/basic/relation04_param/expected/model_2_2-param4-solution000001.solution create mode 100644 tests/exhaustive/basic/relation04_param/expected/model_2_2-param4.eprime-param create mode 100644 tests/exhaustive/basic/relation04_param/expected/model_2_2.eprime create mode 100644 tests/exhaustive/basic/relation04_param/expected/model_2_3-param4-solution000001.solution create mode 100644 tests/exhaustive/basic/relation04_param/expected/model_2_3-param4.eprime-param delete mode 100644 tests/exhaustive/basic/relation04_param/expected/model_2_3.eprime.orig create mode 100644 tests/exhaustive/basic/relation04_param/expected/model_2_4-param4-solution000001.solution create mode 100644 tests/exhaustive/basic/relation04_param/expected/model_2_4-param4.eprime-param create mode 100644 tests/exhaustive/basic/relation04_param/expected/model_2_4.eprime create mode 100644 tests/exhaustive/basic/relation04_param/expected/model_3_1-param4-solution000001.solution create mode 100644 tests/exhaustive/basic/relation04_param/expected/model_3_1-param4.eprime-param delete mode 100644 tests/exhaustive/basic/relation04_param/expected/model_3_1.eprime.orig create mode 100644 tests/exhaustive/basic/relation04_param/expected/model_3_2-param4-solution000001.solution create mode 100644 tests/exhaustive/basic/relation04_param/expected/model_3_2-param4.eprime-param delete mode 100644 tests/exhaustive/basic/relation04_param/expected/model_3_2.eprime.orig create mode 100644 tests/exhaustive/basic/relation04_param/expected/model_3_3-param4-solution000001.solution create mode 100644 tests/exhaustive/basic/relation04_param/expected/model_3_3-param4.eprime-param delete mode 100644 tests/exhaustive/basic/relation04_param/expected/model_3_3.eprime.orig create mode 100644 tests/exhaustive/basic/relation04_param/expected/model_3_4-param4-solution000001.solution create mode 100644 tests/exhaustive/basic/relation04_param/expected/model_3_4-param4.eprime-param delete mode 100644 tests/exhaustive/basic/relation04_param/expected/model_3_4.eprime.orig create mode 100644 tests/exhaustive/basic/relation04_param/expected/model_4_1-param4-solution000001.solution create mode 100644 tests/exhaustive/basic/relation04_param/expected/model_4_1-param4.eprime-param create mode 100644 tests/exhaustive/basic/relation04_param/expected/model_4_1.eprime create mode 100644 tests/exhaustive/basic/relation04_param/expected/model_4_2-param4-solution000001.solution create mode 100644 tests/exhaustive/basic/relation04_param/expected/model_4_2-param4.eprime-param rename tests/exhaustive/basic/relation04_param/expected/{model_4_3.eprime.orig => model_4_2.eprime} (51%) create mode 100644 tests/exhaustive/basic/relation04_param/expected/model_4_3-param4-solution000001.solution create mode 100644 tests/exhaustive/basic/relation04_param/expected/model_4_3-param4.eprime-param create mode 100644 tests/exhaustive/basic/relation04_param/expected/model_4_4-param4-solution000001.solution create mode 100644 tests/exhaustive/basic/relation04_param/expected/model_4_4-param4.eprime-param create mode 100644 tests/exhaustive/basic/relation04_param/expected/model_4_4.eprime create mode 100644 tests/exhaustive/basic/set03/expected/model_1_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set03/expected/model_1_1-solution000002.solution create mode 100644 tests/exhaustive/basic/set03/expected/model_1_1.eprime create mode 100644 tests/exhaustive/basic/set03/expected/model_1_2-solution000001.solution create mode 100644 tests/exhaustive/basic/set03/expected/model_1_2-solution000002.solution create mode 100644 tests/exhaustive/basic/set03/expected/model_1_2.eprime create mode 100644 tests/exhaustive/basic/set03/expected/model_1_3-solution000001.solution create mode 100644 tests/exhaustive/basic/set03/expected/model_1_3-solution000002.solution create mode 100644 tests/exhaustive/basic/set03/expected/model_1_3.eprime create mode 100644 tests/exhaustive/basic/set03/expected/model_1_4-solution000001.solution create mode 100644 tests/exhaustive/basic/set03/expected/model_1_4-solution000002.solution create mode 100644 tests/exhaustive/basic/set03/expected/model_1_4.eprime create mode 100644 tests/exhaustive/basic/set03/expected/model_2_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set03/expected/model_2_1-solution000002.solution create mode 100644 tests/exhaustive/basic/set03/expected/model_2_1.eprime create mode 100644 tests/exhaustive/basic/set03/expected/model_2_2-solution000001.solution create mode 100644 tests/exhaustive/basic/set03/expected/model_2_2-solution000002.solution create mode 100644 tests/exhaustive/basic/set03/expected/model_2_2.eprime create mode 100644 tests/exhaustive/basic/set03/expected/model_2_3-solution000001.solution create mode 100644 tests/exhaustive/basic/set03/expected/model_2_3-solution000002.solution create mode 100644 tests/exhaustive/basic/set03/expected/model_2_3.eprime create mode 100644 tests/exhaustive/basic/set03/expected/model_2_4-solution000001.solution create mode 100644 tests/exhaustive/basic/set03/expected/model_2_4-solution000002.solution create mode 100644 tests/exhaustive/basic/set03/expected/model_2_4.eprime create mode 100644 tests/exhaustive/basic/set03/expected/model_3_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set03/expected/model_3_1-solution000002.solution create mode 100644 tests/exhaustive/basic/set03/expected/model_3_1.eprime create mode 100644 tests/exhaustive/basic/set03/expected/model_3_2-solution000001.solution create mode 100644 tests/exhaustive/basic/set03/expected/model_3_2-solution000002.solution create mode 100644 tests/exhaustive/basic/set03/expected/model_3_2.eprime create mode 100644 tests/exhaustive/basic/set03/expected/model_3_3-solution000001.solution create mode 100644 tests/exhaustive/basic/set03/expected/model_3_3-solution000002.solution create mode 100644 tests/exhaustive/basic/set03/expected/model_3_3.eprime create mode 100644 tests/exhaustive/basic/set03/expected/model_3_4-solution000001.solution create mode 100644 tests/exhaustive/basic/set03/expected/model_3_4-solution000002.solution create mode 100644 tests/exhaustive/basic/set03/expected/model_3_4.eprime create mode 100644 tests/exhaustive/basic/set03/expected/model_4_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set03/expected/model_4_1-solution000002.solution create mode 100644 tests/exhaustive/basic/set03/expected/model_4_1.eprime create mode 100644 tests/exhaustive/basic/set03/expected/model_4_2-solution000001.solution create mode 100644 tests/exhaustive/basic/set03/expected/model_4_2-solution000002.solution create mode 100644 tests/exhaustive/basic/set03/expected/model_4_2.eprime create mode 100644 tests/exhaustive/basic/set03/expected/model_4_3-solution000001.solution create mode 100644 tests/exhaustive/basic/set03/expected/model_4_3-solution000002.solution create mode 100644 tests/exhaustive/basic/set03/expected/model_4_3.eprime create mode 100644 tests/exhaustive/basic/set03/expected/model_4_4-solution000001.solution create mode 100644 tests/exhaustive/basic/set03/expected/model_4_4-solution000002.solution create mode 100644 tests/exhaustive/basic/set03/expected/model_4_4.eprime create mode 100644 tests/exhaustive/basic/set04/expected/model_1_1_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set04/expected/model_1_1_1-solution000002.solution create mode 100644 tests/exhaustive/basic/set04/expected/model_1_1_1.eprime create mode 100644 tests/exhaustive/basic/set04/expected/model_1_1_2-solution000001.solution create mode 100644 tests/exhaustive/basic/set04/expected/model_1_1_2-solution000002.solution rename tests/exhaustive/basic/{cut_01_on/expected/model_1_2_2.eprime.orig => set04/expected/model_1_1_2.eprime} (72%) create mode 100644 tests/exhaustive/basic/set04/expected/model_1_1_3-solution000001.solution create mode 100644 tests/exhaustive/basic/set04/expected/model_1_1_3-solution000002.solution rename tests/exhaustive/basic/{cut_01_on/expected/model_1_3_3.eprime.orig => set04/expected/model_1_1_3.eprime} (72%) create mode 100644 tests/exhaustive/basic/set04/expected/model_1_1_4-solution000001.solution create mode 100644 tests/exhaustive/basic/set04/expected/model_1_1_4-solution000002.solution rename tests/exhaustive/basic/{cut_01_on/expected/model_1_4_4.eprime.orig => set04/expected/model_1_1_4.eprime} (75%) create mode 100644 tests/exhaustive/basic/set04/expected/model_1_2_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set04/expected/model_1_2_1-solution000002.solution create mode 100644 tests/exhaustive/basic/set04/expected/model_1_2_1.eprime create mode 100644 tests/exhaustive/basic/set04/expected/model_1_2_3-solution000001.solution create mode 100644 tests/exhaustive/basic/set04/expected/model_1_2_3-solution000002.solution rename tests/exhaustive/basic/{cut_01_on/expected/model_1_2_3.eprime.orig => set04/expected/model_1_2_3.eprime} (82%) create mode 100644 tests/exhaustive/basic/set04/expected/model_1_2_4-solution000001.solution create mode 100644 tests/exhaustive/basic/set04/expected/model_1_2_4-solution000002.solution rename tests/exhaustive/basic/{cut_01_on/expected/model_1_2_4.eprime.orig => set04/expected/model_1_2_4.eprime} (82%) create mode 100644 tests/exhaustive/basic/set04/expected/model_1_3_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set04/expected/model_1_3_1-solution000002.solution create mode 100644 tests/exhaustive/basic/set04/expected/model_1_3_1.eprime create mode 100644 tests/exhaustive/basic/set04/expected/model_1_3_2-solution000001.solution create mode 100644 tests/exhaustive/basic/set04/expected/model_1_3_2-solution000002.solution rename tests/exhaustive/basic/{cut_01_on/expected/model_1_3_2.eprime.orig => set04/expected/model_1_3_2.eprime} (82%) create mode 100644 tests/exhaustive/basic/set04/expected/model_1_3_4-solution000001.solution create mode 100644 tests/exhaustive/basic/set04/expected/model_1_3_4-solution000002.solution rename tests/exhaustive/basic/{cut_01_on/expected/model_1_3_4.eprime.orig => set04/expected/model_1_3_4.eprime} (85%) create mode 100644 tests/exhaustive/basic/set04/expected/model_1_4_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set04/expected/model_1_4_1-solution000002.solution create mode 100644 tests/exhaustive/basic/set04/expected/model_1_4_1.eprime create mode 100644 tests/exhaustive/basic/set04/expected/model_1_4_2-solution000001.solution create mode 100644 tests/exhaustive/basic/set04/expected/model_1_4_2-solution000002.solution rename tests/exhaustive/basic/{cut_01_on/expected/model_1_4_2.eprime.orig => set04/expected/model_1_4_2.eprime} (81%) create mode 100644 tests/exhaustive/basic/set04/expected/model_1_4_3-solution000001.solution create mode 100644 tests/exhaustive/basic/set04/expected/model_1_4_3-solution000002.solution rename tests/exhaustive/basic/{cut_01_on/expected/model_1_4_3.eprime.orig => set04/expected/model_1_4_3.eprime} (85%) create mode 100644 tests/exhaustive/basic/set04/expected/model_2_1_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set04/expected/model_2_1_1-solution000002.solution rename tests/exhaustive/basic/{cut_01_on/expected/model_2_1_1.eprime.orig => set04/expected/model_2_1_1.eprime} (66%) create mode 100644 tests/exhaustive/basic/set04/expected/model_2_1_3-solution000001.solution create mode 100644 tests/exhaustive/basic/set04/expected/model_2_1_3-solution000002.solution rename tests/exhaustive/basic/{cut_01_on/expected/model_2_1_3.eprime.orig => set04/expected/model_2_1_3.eprime} (82%) create mode 100644 tests/exhaustive/basic/set04/expected/model_2_1_4-solution000001.solution create mode 100644 tests/exhaustive/basic/set04/expected/model_2_1_4-solution000002.solution rename tests/exhaustive/basic/{cut_01_on/expected/model_2_1_4.eprime.orig => set04/expected/model_2_1_4.eprime} (82%) create mode 100644 tests/exhaustive/basic/set04/expected/model_2_2_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set04/expected/model_2_2_1-solution000002.solution rename tests/exhaustive/basic/{cut_01_on/expected/model_2_1_2.eprime.orig => set04/expected/model_2_2_1.eprime} (63%) create mode 100644 tests/exhaustive/basic/set04/expected/model_2_2_2-solution000001.solution create mode 100644 tests/exhaustive/basic/set04/expected/model_2_2_2-solution000002.solution create mode 100644 tests/exhaustive/basic/set04/expected/model_2_2_2.eprime create mode 100644 tests/exhaustive/basic/set04/expected/model_2_2_3-solution000001.solution create mode 100644 tests/exhaustive/basic/set04/expected/model_2_2_3-solution000002.solution rename tests/exhaustive/basic/{cut_01_on/expected/model_2_2_3.eprime.orig => set04/expected/model_2_2_3.eprime} (72%) create mode 100644 tests/exhaustive/basic/set04/expected/model_2_2_4-solution000001.solution create mode 100644 tests/exhaustive/basic/set04/expected/model_2_2_4-solution000002.solution rename tests/exhaustive/basic/{cut_01_on/expected/model_2_2_4.eprime.orig => set04/expected/model_2_2_4.eprime} (74%) create mode 100644 tests/exhaustive/basic/set04/expected/model_2_3_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set04/expected/model_2_3_1-solution000002.solution rename tests/exhaustive/basic/{cut_01_on/expected/model_2_3_1.eprime.orig => set04/expected/model_2_3_1.eprime} (54%) create mode 100644 tests/exhaustive/basic/set04/expected/model_2_3_2-solution000001.solution create mode 100644 tests/exhaustive/basic/set04/expected/model_2_3_2-solution000002.solution rename tests/exhaustive/basic/{cut_01_on/expected/model_2_3_2.eprime.orig => set04/expected/model_2_3_2.eprime} (71%) create mode 100644 tests/exhaustive/basic/set04/expected/model_2_3_4-solution000001.solution create mode 100644 tests/exhaustive/basic/set04/expected/model_2_3_4-solution000002.solution rename tests/exhaustive/basic/{cut_01_on/expected/model_2_3_4.eprime.orig => set04/expected/model_2_3_4.eprime} (85%) create mode 100644 tests/exhaustive/basic/set04/expected/model_2_4_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set04/expected/model_2_4_1-solution000002.solution rename tests/exhaustive/basic/{cut_01_on/expected/model_2_4_1.eprime.orig => set04/expected/model_2_4_1.eprime} (79%) create mode 100644 tests/exhaustive/basic/set04/expected/model_2_4_2-solution000001.solution create mode 100644 tests/exhaustive/basic/set04/expected/model_2_4_2-solution000002.solution rename tests/exhaustive/basic/{cut_01_on/expected/model_2_4_2.eprime.orig => set04/expected/model_2_4_2.eprime} (73%) create mode 100644 tests/exhaustive/basic/set04/expected/model_2_4_3-solution000001.solution create mode 100644 tests/exhaustive/basic/set04/expected/model_2_4_3-solution000002.solution rename tests/exhaustive/basic/{cut_01_on/expected/model_2_4_3.eprime.orig => set04/expected/model_2_4_3.eprime} (85%) create mode 100644 tests/exhaustive/basic/set04/expected/model_3_1_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set04/expected/model_3_1_1-solution000002.solution rename tests/exhaustive/basic/{cut_01_on/expected/model_3_1_3.eprime.orig => set04/expected/model_3_1_1.eprime} (66%) create mode 100644 tests/exhaustive/basic/set04/expected/model_3_1_2-solution000001.solution create mode 100644 tests/exhaustive/basic/set04/expected/model_3_1_2-solution000002.solution rename tests/exhaustive/basic/{cut_01_on/expected/model_3_1_2.eprime.orig => set04/expected/model_3_1_2.eprime} (81%) create mode 100644 tests/exhaustive/basic/set04/expected/model_3_1_4-solution000001.solution create mode 100644 tests/exhaustive/basic/set04/expected/model_3_1_4-solution000002.solution rename tests/exhaustive/basic/{cut_01_on/expected/model_3_1_4.eprime.orig => set04/expected/model_3_1_4.eprime} (82%) create mode 100644 tests/exhaustive/basic/set04/expected/model_3_2_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set04/expected/model_3_2_1-solution000002.solution rename tests/exhaustive/basic/{cut_01_on/expected/model_3_2_1.eprime.orig => set04/expected/model_3_2_1.eprime} (54%) create mode 100644 tests/exhaustive/basic/set04/expected/model_3_2_2-solution000001.solution create mode 100644 tests/exhaustive/basic/set04/expected/model_3_2_2-solution000002.solution rename tests/exhaustive/basic/{cut_01_on/expected/model_3_2_3.eprime.orig => set04/expected/model_3_2_2.eprime} (71%) create mode 100644 tests/exhaustive/basic/set04/expected/model_3_2_4-solution000001.solution create mode 100644 tests/exhaustive/basic/set04/expected/model_3_2_4-solution000002.solution rename tests/exhaustive/basic/{cut_01_on/expected/model_3_2_4.eprime.orig => set04/expected/model_3_2_4.eprime} (83%) create mode 100644 tests/exhaustive/basic/set04/expected/model_3_3_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set04/expected/model_3_3_1-solution000002.solution rename tests/exhaustive/basic/{cut_01_on/expected/model_3_1_1.eprime.orig => set04/expected/model_3_3_1.eprime} (65%) create mode 100644 tests/exhaustive/basic/set04/expected/model_3_3_2-solution000001.solution create mode 100644 tests/exhaustive/basic/set04/expected/model_3_3_2-solution000002.solution rename tests/exhaustive/basic/{cut_01_on/expected/model_3_2_2.eprime.orig => set04/expected/model_3_3_2.eprime} (71%) create mode 100644 tests/exhaustive/basic/set04/expected/model_3_3_3-solution000001.solution create mode 100644 tests/exhaustive/basic/set04/expected/model_3_3_3-solution000002.solution create mode 100644 tests/exhaustive/basic/set04/expected/model_3_3_3.eprime create mode 100644 tests/exhaustive/basic/set04/expected/model_3_3_4-solution000001.solution create mode 100644 tests/exhaustive/basic/set04/expected/model_3_3_4-solution000002.solution rename tests/exhaustive/basic/{cut_01_on/expected/model_3_4_4.eprime.orig => set04/expected/model_3_3_4.eprime} (73%) create mode 100644 tests/exhaustive/basic/set04/expected/model_3_4_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set04/expected/model_3_4_1-solution000002.solution rename tests/exhaustive/basic/{cut_01_on/expected/model_3_4_1.eprime.orig => set04/expected/model_3_4_1.eprime} (82%) create mode 100644 tests/exhaustive/basic/set04/expected/model_3_4_2-solution000001.solution create mode 100644 tests/exhaustive/basic/set04/expected/model_3_4_2-solution000002.solution rename tests/exhaustive/basic/{cut_01_on/expected/model_3_4_2.eprime.orig => set04/expected/model_3_4_2.eprime} (85%) create mode 100644 tests/exhaustive/basic/set04/expected/model_3_4_3-solution000001.solution create mode 100644 tests/exhaustive/basic/set04/expected/model_3_4_3-solution000002.solution rename tests/exhaustive/basic/{cut_01_on/expected/model_3_4_3.eprime.orig => set04/expected/model_3_4_3.eprime} (73%) create mode 100644 tests/exhaustive/basic/set04/expected/model_4_1_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set04/expected/model_4_1_1-solution000002.solution rename tests/exhaustive/basic/{cut_01_on/expected/model_4_1_4.eprime.orig => set04/expected/model_4_1_1.eprime} (70%) create mode 100644 tests/exhaustive/basic/set04/expected/model_4_1_2-solution000001.solution create mode 100644 tests/exhaustive/basic/set04/expected/model_4_1_2-solution000002.solution rename tests/exhaustive/basic/{cut_01_on/expected/model_4_1_2.eprime.orig => set04/expected/model_4_1_2.eprime} (82%) create mode 100644 tests/exhaustive/basic/set04/expected/model_4_1_3-solution000001.solution create mode 100644 tests/exhaustive/basic/set04/expected/model_4_1_3-solution000002.solution rename tests/exhaustive/basic/{cut_01_on/expected/model_4_1_3.eprime.orig => set04/expected/model_4_1_3.eprime} (82%) create mode 100644 tests/exhaustive/basic/set04/expected/model_4_2_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set04/expected/model_4_2_1-solution000002.solution rename tests/exhaustive/basic/{cut_01_on/expected/model_4_2_1.eprime.orig => set04/expected/model_4_2_1.eprime} (79%) create mode 100644 tests/exhaustive/basic/set04/expected/model_4_2_2-solution000001.solution create mode 100644 tests/exhaustive/basic/set04/expected/model_4_2_2-solution000002.solution rename tests/exhaustive/basic/{cut_01_on/expected/model_4_2_2.eprime.orig => set04/expected/model_4_2_2.eprime} (73%) create mode 100644 tests/exhaustive/basic/set04/expected/model_4_2_3-solution000001.solution create mode 100644 tests/exhaustive/basic/set04/expected/model_4_2_3-solution000002.solution rename tests/exhaustive/basic/{cut_01_on/expected/model_4_2_3.eprime.orig => set04/expected/model_4_2_3.eprime} (83%) create mode 100644 tests/exhaustive/basic/set04/expected/model_4_3_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set04/expected/model_4_3_1-solution000002.solution rename tests/exhaustive/basic/{cut_01_on/expected/model_4_3_1.eprime.orig => set04/expected/model_4_3_1.eprime} (82%) create mode 100644 tests/exhaustive/basic/set04/expected/model_4_3_2-solution000001.solution create mode 100644 tests/exhaustive/basic/set04/expected/model_4_3_2-solution000002.solution rename tests/exhaustive/basic/{cut_01_on/expected/model_4_3_2.eprime.orig => set04/expected/model_4_3_2.eprime} (85%) create mode 100644 tests/exhaustive/basic/set04/expected/model_4_3_3-solution000001.solution create mode 100644 tests/exhaustive/basic/set04/expected/model_4_3_3-solution000002.solution rename tests/exhaustive/basic/{cut_01_on/expected/model_4_4_3.eprime.orig => set04/expected/model_4_3_3.eprime} (73%) create mode 100644 tests/exhaustive/basic/set04/expected/model_4_4_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set04/expected/model_4_4_1-solution000002.solution rename tests/exhaustive/basic/{cut_01_on/expected/model_4_1_1.eprime.orig => set04/expected/model_4_4_1.eprime} (67%) create mode 100644 tests/exhaustive/basic/set04/expected/model_4_4_2-solution000001.solution create mode 100644 tests/exhaustive/basic/set04/expected/model_4_4_2-solution000002.solution rename tests/exhaustive/basic/{cut_01_on/expected/model_4_2_4.eprime.orig => set04/expected/model_4_4_2.eprime} (73%) create mode 100644 tests/exhaustive/basic/set04/expected/model_4_4_3-solution000001.solution create mode 100644 tests/exhaustive/basic/set04/expected/model_4_4_3-solution000002.solution rename tests/exhaustive/basic/{cut_01_on/expected/model_4_3_3.eprime.orig => set04/expected/model_4_4_3.eprime} (73%) create mode 100644 tests/exhaustive/basic/set04/expected/model_4_4_4-solution000001.solution create mode 100644 tests/exhaustive/basic/set04/expected/model_4_4_4-solution000002.solution rename tests/exhaustive/basic/{cut_01_on/expected/model_4_4_4.eprime.orig => set04/expected/model_4_4_4.eprime} (50%) create mode 100644 tests/exhaustive/basic/set05/expected/model_1_1_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set05/expected/model_1_1_1-solution000002.solution create mode 100644 tests/exhaustive/basic/set05/expected/model_1_1_1-solution000003.solution create mode 100644 tests/exhaustive/basic/set05/expected/model_1_1_1.eprime create mode 100644 tests/exhaustive/basic/set05/expected/model_1_1_2-solution000001.solution create mode 100644 tests/exhaustive/basic/set05/expected/model_1_1_2-solution000002.solution create mode 100644 tests/exhaustive/basic/set05/expected/model_1_1_2-solution000003.solution create mode 100644 tests/exhaustive/basic/set05/expected/model_1_1_2.eprime create mode 100644 tests/exhaustive/basic/set05/expected/model_1_1_3-solution000001.solution create mode 100644 tests/exhaustive/basic/set05/expected/model_1_1_3-solution000002.solution create mode 100644 tests/exhaustive/basic/set05/expected/model_1_1_3-solution000003.solution create mode 100644 tests/exhaustive/basic/set05/expected/model_1_1_3.eprime create mode 100644 tests/exhaustive/basic/set05/expected/model_1_1_4-solution000001.solution create mode 100644 tests/exhaustive/basic/set05/expected/model_1_1_4-solution000002.solution create mode 100644 tests/exhaustive/basic/set05/expected/model_1_1_4-solution000003.solution create mode 100644 tests/exhaustive/basic/set05/expected/model_1_1_4.eprime create mode 100644 tests/exhaustive/basic/set05/expected/model_1_2_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set05/expected/model_1_2_1-solution000002.solution create mode 100644 tests/exhaustive/basic/set05/expected/model_1_2_1-solution000003.solution create mode 100644 tests/exhaustive/basic/set05/expected/model_1_2_1.eprime create mode 100644 tests/exhaustive/basic/set05/expected/model_1_2_3-solution000001.solution create mode 100644 tests/exhaustive/basic/set05/expected/model_1_2_3-solution000002.solution create mode 100644 tests/exhaustive/basic/set05/expected/model_1_2_3-solution000003.solution create mode 100644 tests/exhaustive/basic/set05/expected/model_1_2_3.eprime create mode 100644 tests/exhaustive/basic/set05/expected/model_1_2_4-solution000001.solution create mode 100644 tests/exhaustive/basic/set05/expected/model_1_2_4-solution000002.solution create mode 100644 tests/exhaustive/basic/set05/expected/model_1_2_4-solution000003.solution create mode 100644 tests/exhaustive/basic/set05/expected/model_1_2_4.eprime create mode 100644 tests/exhaustive/basic/set05/expected/model_1_3_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set05/expected/model_1_3_1-solution000002.solution create mode 100644 tests/exhaustive/basic/set05/expected/model_1_3_1-solution000003.solution create mode 100644 tests/exhaustive/basic/set05/expected/model_1_3_1.eprime create mode 100644 tests/exhaustive/basic/set05/expected/model_1_3_2-solution000001.solution create mode 100644 tests/exhaustive/basic/set05/expected/model_1_3_2-solution000002.solution create mode 100644 tests/exhaustive/basic/set05/expected/model_1_3_2-solution000003.solution create mode 100644 tests/exhaustive/basic/set05/expected/model_1_3_2.eprime create mode 100644 tests/exhaustive/basic/set05/expected/model_1_3_4-solution000001.solution create mode 100644 tests/exhaustive/basic/set05/expected/model_1_3_4-solution000002.solution create mode 100644 tests/exhaustive/basic/set05/expected/model_1_3_4-solution000003.solution create mode 100644 tests/exhaustive/basic/set05/expected/model_1_3_4.eprime create mode 100644 tests/exhaustive/basic/set05/expected/model_1_4_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set05/expected/model_1_4_1-solution000002.solution create mode 100644 tests/exhaustive/basic/set05/expected/model_1_4_1-solution000003.solution create mode 100644 tests/exhaustive/basic/set05/expected/model_1_4_1.eprime create mode 100644 tests/exhaustive/basic/set05/expected/model_1_4_2-solution000001.solution create mode 100644 tests/exhaustive/basic/set05/expected/model_1_4_2-solution000002.solution create mode 100644 tests/exhaustive/basic/set05/expected/model_1_4_2-solution000003.solution create mode 100644 tests/exhaustive/basic/set05/expected/model_1_4_2.eprime create mode 100644 tests/exhaustive/basic/set05/expected/model_1_4_3-solution000001.solution create mode 100644 tests/exhaustive/basic/set05/expected/model_1_4_3-solution000002.solution create mode 100644 tests/exhaustive/basic/set05/expected/model_1_4_3-solution000003.solution create mode 100644 tests/exhaustive/basic/set05/expected/model_1_4_3.eprime create mode 100644 tests/exhaustive/basic/set05/expected/model_2_1_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set05/expected/model_2_1_1-solution000002.solution create mode 100644 tests/exhaustive/basic/set05/expected/model_2_1_1-solution000003.solution create mode 100644 tests/exhaustive/basic/set05/expected/model_2_1_1.eprime create mode 100644 tests/exhaustive/basic/set05/expected/model_2_1_3-solution000001.solution create mode 100644 tests/exhaustive/basic/set05/expected/model_2_1_3-solution000002.solution create mode 100644 tests/exhaustive/basic/set05/expected/model_2_1_3-solution000003.solution create mode 100644 tests/exhaustive/basic/set05/expected/model_2_1_3.eprime create mode 100644 tests/exhaustive/basic/set05/expected/model_2_1_4-solution000001.solution create mode 100644 tests/exhaustive/basic/set05/expected/model_2_1_4-solution000002.solution create mode 100644 tests/exhaustive/basic/set05/expected/model_2_1_4-solution000003.solution create mode 100644 tests/exhaustive/basic/set05/expected/model_2_1_4.eprime create mode 100644 tests/exhaustive/basic/set05/expected/model_2_2_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set05/expected/model_2_2_1-solution000002.solution create mode 100644 tests/exhaustive/basic/set05/expected/model_2_2_1-solution000003.solution create mode 100644 tests/exhaustive/basic/set05/expected/model_2_2_1.eprime create mode 100644 tests/exhaustive/basic/set05/expected/model_2_2_2-solution000001.solution create mode 100644 tests/exhaustive/basic/set05/expected/model_2_2_2-solution000002.solution create mode 100644 tests/exhaustive/basic/set05/expected/model_2_2_2-solution000003.solution create mode 100644 tests/exhaustive/basic/set05/expected/model_2_2_2.eprime create mode 100644 tests/exhaustive/basic/set05/expected/model_2_2_3-solution000001.solution create mode 100644 tests/exhaustive/basic/set05/expected/model_2_2_3-solution000002.solution create mode 100644 tests/exhaustive/basic/set05/expected/model_2_2_3-solution000003.solution rename tests/exhaustive/basic/{cut_01_on/expected/model_2_3_3.eprime.orig => set05/expected/model_2_2_3.eprime} (55%) create mode 100644 tests/exhaustive/basic/set05/expected/model_2_2_4-solution000001.solution create mode 100644 tests/exhaustive/basic/set05/expected/model_2_2_4-solution000002.solution create mode 100644 tests/exhaustive/basic/set05/expected/model_2_2_4-solution000003.solution rename tests/exhaustive/basic/{cut_01_on/expected/model_2_4_4.eprime.orig => set05/expected/model_2_2_4.eprime} (59%) create mode 100644 tests/exhaustive/basic/set05/expected/model_2_3_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set05/expected/model_2_3_1-solution000002.solution create mode 100644 tests/exhaustive/basic/set05/expected/model_2_3_1-solution000003.solution create mode 100644 tests/exhaustive/basic/set05/expected/model_2_3_1.eprime create mode 100644 tests/exhaustive/basic/set05/expected/model_2_3_2-solution000001.solution create mode 100644 tests/exhaustive/basic/set05/expected/model_2_3_2-solution000002.solution create mode 100644 tests/exhaustive/basic/set05/expected/model_2_3_2-solution000003.solution create mode 100644 tests/exhaustive/basic/set05/expected/model_2_3_2.eprime create mode 100644 tests/exhaustive/basic/set05/expected/model_2_3_4-solution000001.solution create mode 100644 tests/exhaustive/basic/set05/expected/model_2_3_4-solution000002.solution create mode 100644 tests/exhaustive/basic/set05/expected/model_2_3_4-solution000003.solution create mode 100644 tests/exhaustive/basic/set05/expected/model_2_3_4.eprime create mode 100644 tests/exhaustive/basic/set05/expected/model_2_4_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set05/expected/model_2_4_1-solution000002.solution create mode 100644 tests/exhaustive/basic/set05/expected/model_2_4_1-solution000003.solution create mode 100644 tests/exhaustive/basic/set05/expected/model_2_4_1.eprime create mode 100644 tests/exhaustive/basic/set05/expected/model_2_4_2-solution000001.solution create mode 100644 tests/exhaustive/basic/set05/expected/model_2_4_2-solution000002.solution create mode 100644 tests/exhaustive/basic/set05/expected/model_2_4_2-solution000003.solution create mode 100644 tests/exhaustive/basic/set05/expected/model_2_4_2.eprime create mode 100644 tests/exhaustive/basic/set05/expected/model_2_4_3-solution000001.solution create mode 100644 tests/exhaustive/basic/set05/expected/model_2_4_3-solution000002.solution create mode 100644 tests/exhaustive/basic/set05/expected/model_2_4_3-solution000003.solution create mode 100644 tests/exhaustive/basic/set05/expected/model_2_4_3.eprime create mode 100644 tests/exhaustive/basic/set05/expected/model_3_1_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set05/expected/model_3_1_1-solution000002.solution create mode 100644 tests/exhaustive/basic/set05/expected/model_3_1_1-solution000003.solution create mode 100644 tests/exhaustive/basic/set05/expected/model_3_1_1.eprime create mode 100644 tests/exhaustive/basic/set05/expected/model_3_1_2-solution000001.solution create mode 100644 tests/exhaustive/basic/set05/expected/model_3_1_2-solution000002.solution create mode 100644 tests/exhaustive/basic/set05/expected/model_3_1_2-solution000003.solution create mode 100644 tests/exhaustive/basic/set05/expected/model_3_1_2.eprime create mode 100644 tests/exhaustive/basic/set05/expected/model_3_1_4-solution000001.solution create mode 100644 tests/exhaustive/basic/set05/expected/model_3_1_4-solution000002.solution create mode 100644 tests/exhaustive/basic/set05/expected/model_3_1_4-solution000003.solution create mode 100644 tests/exhaustive/basic/set05/expected/model_3_1_4.eprime create mode 100644 tests/exhaustive/basic/set05/expected/model_3_2_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set05/expected/model_3_2_1-solution000002.solution create mode 100644 tests/exhaustive/basic/set05/expected/model_3_2_1-solution000003.solution create mode 100644 tests/exhaustive/basic/set05/expected/model_3_2_1.eprime create mode 100644 tests/exhaustive/basic/set05/expected/model_3_2_2-solution000001.solution create mode 100644 tests/exhaustive/basic/set05/expected/model_3_2_2-solution000002.solution create mode 100644 tests/exhaustive/basic/set05/expected/model_3_2_2-solution000003.solution rename tests/exhaustive/basic/{cut_01_on/expected/model_3_3_2.eprime.orig => set05/expected/model_3_2_2.eprime} (55%) create mode 100644 tests/exhaustive/basic/set05/expected/model_3_2_4-solution000001.solution create mode 100644 tests/exhaustive/basic/set05/expected/model_3_2_4-solution000002.solution create mode 100644 tests/exhaustive/basic/set05/expected/model_3_2_4-solution000003.solution create mode 100644 tests/exhaustive/basic/set05/expected/model_3_2_4.eprime create mode 100644 tests/exhaustive/basic/set05/expected/model_3_3_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set05/expected/model_3_3_1-solution000002.solution create mode 100644 tests/exhaustive/basic/set05/expected/model_3_3_1-solution000003.solution create mode 100644 tests/exhaustive/basic/set05/expected/model_3_3_1.eprime create mode 100644 tests/exhaustive/basic/set05/expected/model_3_3_2-solution000001.solution create mode 100644 tests/exhaustive/basic/set05/expected/model_3_3_2-solution000002.solution create mode 100644 tests/exhaustive/basic/set05/expected/model_3_3_2-solution000003.solution create mode 100644 tests/exhaustive/basic/set05/expected/model_3_3_2.eprime create mode 100644 tests/exhaustive/basic/set05/expected/model_3_3_3-solution000001.solution create mode 100644 tests/exhaustive/basic/set05/expected/model_3_3_3-solution000002.solution create mode 100644 tests/exhaustive/basic/set05/expected/model_3_3_3-solution000003.solution create mode 100644 tests/exhaustive/basic/set05/expected/model_3_3_3.eprime create mode 100644 tests/exhaustive/basic/set05/expected/model_3_3_4-solution000001.solution create mode 100644 tests/exhaustive/basic/set05/expected/model_3_3_4-solution000002.solution create mode 100644 tests/exhaustive/basic/set05/expected/model_3_3_4-solution000003.solution rename tests/exhaustive/basic/{cut_01_on/expected/model_3_3_4.eprime.orig => set05/expected/model_3_3_4.eprime} (71%) create mode 100644 tests/exhaustive/basic/set05/expected/model_3_4_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set05/expected/model_3_4_1-solution000002.solution create mode 100644 tests/exhaustive/basic/set05/expected/model_3_4_1-solution000003.solution create mode 100644 tests/exhaustive/basic/set05/expected/model_3_4_1.eprime create mode 100644 tests/exhaustive/basic/set05/expected/model_3_4_2-solution000001.solution create mode 100644 tests/exhaustive/basic/set05/expected/model_3_4_2-solution000002.solution create mode 100644 tests/exhaustive/basic/set05/expected/model_3_4_2-solution000003.solution create mode 100644 tests/exhaustive/basic/set05/expected/model_3_4_2.eprime create mode 100644 tests/exhaustive/basic/set05/expected/model_3_4_3-solution000001.solution create mode 100644 tests/exhaustive/basic/set05/expected/model_3_4_3-solution000002.solution create mode 100644 tests/exhaustive/basic/set05/expected/model_3_4_3-solution000003.solution create mode 100644 tests/exhaustive/basic/set05/expected/model_3_4_3.eprime create mode 100644 tests/exhaustive/basic/set05/expected/model_4_1_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set05/expected/model_4_1_1-solution000002.solution create mode 100644 tests/exhaustive/basic/set05/expected/model_4_1_1-solution000003.solution rename tests/exhaustive/basic/{cut_01_on/expected/model_4_4_1.eprime.orig => set05/expected/model_4_1_1.eprime} (58%) create mode 100644 tests/exhaustive/basic/set05/expected/model_4_1_2-solution000001.solution create mode 100644 tests/exhaustive/basic/set05/expected/model_4_1_2-solution000002.solution create mode 100644 tests/exhaustive/basic/set05/expected/model_4_1_2-solution000003.solution create mode 100644 tests/exhaustive/basic/set05/expected/model_4_1_2.eprime create mode 100644 tests/exhaustive/basic/set05/expected/model_4_1_3-solution000001.solution create mode 100644 tests/exhaustive/basic/set05/expected/model_4_1_3-solution000002.solution create mode 100644 tests/exhaustive/basic/set05/expected/model_4_1_3-solution000003.solution create mode 100644 tests/exhaustive/basic/set05/expected/model_4_1_3.eprime create mode 100644 tests/exhaustive/basic/set05/expected/model_4_2_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set05/expected/model_4_2_1-solution000002.solution create mode 100644 tests/exhaustive/basic/set05/expected/model_4_2_1-solution000003.solution create mode 100644 tests/exhaustive/basic/set05/expected/model_4_2_1.eprime create mode 100644 tests/exhaustive/basic/set05/expected/model_4_2_2-solution000001.solution create mode 100644 tests/exhaustive/basic/set05/expected/model_4_2_2-solution000002.solution create mode 100644 tests/exhaustive/basic/set05/expected/model_4_2_2-solution000003.solution rename tests/exhaustive/basic/{cut_01_on/expected/model_4_4_2.eprime.orig => set05/expected/model_4_2_2.eprime} (58%) create mode 100644 tests/exhaustive/basic/set05/expected/model_4_2_3-solution000001.solution create mode 100644 tests/exhaustive/basic/set05/expected/model_4_2_3-solution000002.solution create mode 100644 tests/exhaustive/basic/set05/expected/model_4_2_3-solution000003.solution create mode 100644 tests/exhaustive/basic/set05/expected/model_4_2_3.eprime create mode 100644 tests/exhaustive/basic/set05/expected/model_4_3_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set05/expected/model_4_3_1-solution000002.solution create mode 100644 tests/exhaustive/basic/set05/expected/model_4_3_1-solution000003.solution create mode 100644 tests/exhaustive/basic/set05/expected/model_4_3_1.eprime create mode 100644 tests/exhaustive/basic/set05/expected/model_4_3_2-solution000001.solution create mode 100644 tests/exhaustive/basic/set05/expected/model_4_3_2-solution000002.solution create mode 100644 tests/exhaustive/basic/set05/expected/model_4_3_2-solution000003.solution create mode 100644 tests/exhaustive/basic/set05/expected/model_4_3_2.eprime create mode 100644 tests/exhaustive/basic/set05/expected/model_4_3_3-solution000001.solution create mode 100644 tests/exhaustive/basic/set05/expected/model_4_3_3-solution000002.solution create mode 100644 tests/exhaustive/basic/set05/expected/model_4_3_3-solution000003.solution rename tests/exhaustive/basic/{cut_01_on/expected/model_4_3_4.eprime.orig => set05/expected/model_4_3_3.eprime} (71%) create mode 100644 tests/exhaustive/basic/set05/expected/model_4_4_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set05/expected/model_4_4_1-solution000002.solution create mode 100644 tests/exhaustive/basic/set05/expected/model_4_4_1-solution000003.solution create mode 100644 tests/exhaustive/basic/set05/expected/model_4_4_1.eprime create mode 100644 tests/exhaustive/basic/set05/expected/model_4_4_2-solution000001.solution create mode 100644 tests/exhaustive/basic/set05/expected/model_4_4_2-solution000002.solution create mode 100644 tests/exhaustive/basic/set05/expected/model_4_4_2-solution000003.solution create mode 100644 tests/exhaustive/basic/set05/expected/model_4_4_2.eprime create mode 100644 tests/exhaustive/basic/set05/expected/model_4_4_3-solution000001.solution create mode 100644 tests/exhaustive/basic/set05/expected/model_4_4_3-solution000002.solution create mode 100644 tests/exhaustive/basic/set05/expected/model_4_4_3-solution000003.solution create mode 100644 tests/exhaustive/basic/set05/expected/model_4_4_3.eprime create mode 100644 tests/exhaustive/basic/set05/expected/model_4_4_4-solution000001.solution create mode 100644 tests/exhaustive/basic/set05/expected/model_4_4_4-solution000002.solution create mode 100644 tests/exhaustive/basic/set05/expected/model_4_4_4-solution000003.solution create mode 100644 tests/exhaustive/basic/set05/expected/model_4_4_4.eprime create mode 100644 tests/exhaustive/basic/set06/expected/model_1_1_1_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_1_1_1_1-solution000002.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_1_1_1_1.eprime create mode 100644 tests/exhaustive/basic/set06/expected/model_1_1_1_2-solution000001.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_1_1_1_2-solution000002.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_1_1_1_2.eprime create mode 100644 tests/exhaustive/basic/set06/expected/model_1_1_1_3-solution000001.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_1_1_1_3-solution000002.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_1_1_1_3.eprime create mode 100644 tests/exhaustive/basic/set06/expected/model_1_1_1_4-solution000001.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_1_1_1_4-solution000002.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_1_1_1_4.eprime create mode 100644 tests/exhaustive/basic/set06/expected/model_1_1_2_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_1_1_2_1-solution000002.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_1_1_2_1.eprime create mode 100644 tests/exhaustive/basic/set06/expected/model_1_1_2_3-solution000001.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_1_1_2_3-solution000002.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_1_1_2_3.eprime create mode 100644 tests/exhaustive/basic/set06/expected/model_1_1_2_4-solution000001.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_1_1_2_4-solution000002.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_1_1_2_4.eprime create mode 100644 tests/exhaustive/basic/set06/expected/model_1_1_3_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_1_1_3_1-solution000002.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_1_1_3_1.eprime create mode 100644 tests/exhaustive/basic/set06/expected/model_1_1_3_2-solution000001.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_1_1_3_2-solution000002.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_1_1_3_2.eprime create mode 100644 tests/exhaustive/basic/set06/expected/model_1_1_3_4-solution000001.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_1_1_3_4-solution000002.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_1_1_3_4.eprime create mode 100644 tests/exhaustive/basic/set06/expected/model_1_1_4_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_1_1_4_1-solution000002.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_1_1_4_1.eprime create mode 100644 tests/exhaustive/basic/set06/expected/model_1_1_4_2-solution000001.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_1_1_4_2-solution000002.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_1_1_4_2.eprime create mode 100644 tests/exhaustive/basic/set06/expected/model_1_1_4_3-solution000001.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_1_1_4_3-solution000002.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_1_1_4_3.eprime create mode 100644 tests/exhaustive/basic/set06/expected/model_1_2_1_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_1_2_1_1-solution000002.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_1_2_1_1.eprime create mode 100644 tests/exhaustive/basic/set06/expected/model_1_2_1_3-solution000001.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_1_2_1_3-solution000002.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_1_2_1_3.eprime create mode 100644 tests/exhaustive/basic/set06/expected/model_1_2_1_4-solution000001.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_1_2_1_4-solution000002.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_1_2_1_4.eprime create mode 100644 tests/exhaustive/basic/set06/expected/model_1_2_2_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_1_2_2_1-solution000002.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_1_2_2_1.eprime create mode 100644 tests/exhaustive/basic/set06/expected/model_1_2_2_3-solution000001.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_1_2_2_3-solution000002.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_1_2_2_3.eprime create mode 100644 tests/exhaustive/basic/set06/expected/model_1_2_2_4-solution000001.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_1_2_2_4-solution000002.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_1_2_2_4.eprime create mode 100644 tests/exhaustive/basic/set06/expected/model_1_2_3_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_1_2_3_1-solution000002.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_1_2_3_1.eprime create mode 100644 tests/exhaustive/basic/set06/expected/model_1_2_3_4-solution000001.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_1_2_3_4-solution000002.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_1_2_3_4.eprime create mode 100644 tests/exhaustive/basic/set06/expected/model_1_2_4_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_1_2_4_1-solution000002.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_1_2_4_1.eprime create mode 100644 tests/exhaustive/basic/set06/expected/model_1_2_4_3-solution000001.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_1_2_4_3-solution000002.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_1_2_4_3.eprime create mode 100644 tests/exhaustive/basic/set06/expected/model_1_3_1_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_1_3_1_1-solution000002.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_1_3_1_1.eprime create mode 100644 tests/exhaustive/basic/set06/expected/model_1_3_1_2-solution000001.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_1_3_1_2-solution000002.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_1_3_1_2.eprime create mode 100644 tests/exhaustive/basic/set06/expected/model_1_3_1_4-solution000001.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_1_3_1_4-solution000002.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_1_3_1_4.eprime create mode 100644 tests/exhaustive/basic/set06/expected/model_1_3_2_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_1_3_2_1-solution000002.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_1_3_2_1.eprime create mode 100644 tests/exhaustive/basic/set06/expected/model_1_3_2_4-solution000001.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_1_3_2_4-solution000002.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_1_3_2_4.eprime create mode 100644 tests/exhaustive/basic/set06/expected/model_1_3_3_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_1_3_3_1-solution000002.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_1_3_3_1.eprime create mode 100644 tests/exhaustive/basic/set06/expected/model_1_3_3_2-solution000001.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_1_3_3_2-solution000002.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_1_3_3_2.eprime create mode 100644 tests/exhaustive/basic/set06/expected/model_1_3_3_4-solution000001.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_1_3_3_4-solution000002.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_1_3_3_4.eprime create mode 100644 tests/exhaustive/basic/set06/expected/model_1_3_4_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_1_3_4_1-solution000002.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_1_3_4_1.eprime create mode 100644 tests/exhaustive/basic/set06/expected/model_1_3_4_2-solution000001.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_1_3_4_2-solution000002.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_1_3_4_2.eprime create mode 100644 tests/exhaustive/basic/set06/expected/model_1_4_1_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_1_4_1_1-solution000002.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_1_4_1_1.eprime create mode 100644 tests/exhaustive/basic/set06/expected/model_1_4_1_2-solution000001.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_1_4_1_2-solution000002.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_1_4_1_2.eprime create mode 100644 tests/exhaustive/basic/set06/expected/model_1_4_1_3-solution000001.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_1_4_1_3-solution000002.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_1_4_1_3.eprime create mode 100644 tests/exhaustive/basic/set06/expected/model_1_4_2_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_1_4_2_1-solution000002.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_1_4_2_1.eprime create mode 100644 tests/exhaustive/basic/set06/expected/model_1_4_2_3-solution000001.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_1_4_2_3-solution000002.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_1_4_2_3.eprime create mode 100644 tests/exhaustive/basic/set06/expected/model_1_4_3_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_1_4_3_1-solution000002.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_1_4_3_1.eprime create mode 100644 tests/exhaustive/basic/set06/expected/model_1_4_3_2-solution000001.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_1_4_3_2-solution000002.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_1_4_3_2.eprime create mode 100644 tests/exhaustive/basic/set06/expected/model_1_4_4_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_1_4_4_1-solution000002.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_1_4_4_1.eprime create mode 100644 tests/exhaustive/basic/set06/expected/model_1_4_4_2-solution000001.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_1_4_4_2-solution000002.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_1_4_4_2.eprime create mode 100644 tests/exhaustive/basic/set06/expected/model_1_4_4_3-solution000001.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_1_4_4_3-solution000002.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_1_4_4_3.eprime create mode 100644 tests/exhaustive/basic/set06/expected/model_2_1_1_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_2_1_1_1-solution000002.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_2_1_1_1.eprime create mode 100644 tests/exhaustive/basic/set06/expected/model_2_1_1_3-solution000001.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_2_1_1_3-solution000002.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_2_1_1_3.eprime create mode 100644 tests/exhaustive/basic/set06/expected/model_2_1_1_4-solution000001.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_2_1_1_4-solution000002.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_2_1_1_4.eprime create mode 100644 tests/exhaustive/basic/set06/expected/model_2_1_2_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_2_1_2_1-solution000002.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_2_1_2_1.eprime create mode 100644 tests/exhaustive/basic/set06/expected/model_2_1_2_3-solution000001.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_2_1_2_3-solution000002.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_2_1_2_3.eprime create mode 100644 tests/exhaustive/basic/set06/expected/model_2_1_2_4-solution000001.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_2_1_2_4-solution000002.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_2_1_2_4.eprime create mode 100644 tests/exhaustive/basic/set06/expected/model_2_1_3_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_2_1_3_1-solution000002.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_2_1_3_1.eprime create mode 100644 tests/exhaustive/basic/set06/expected/model_2_1_3_4-solution000001.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_2_1_3_4-solution000002.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_2_1_3_4.eprime create mode 100644 tests/exhaustive/basic/set06/expected/model_2_1_4_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_2_1_4_1-solution000002.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_2_1_4_1.eprime create mode 100644 tests/exhaustive/basic/set06/expected/model_2_1_4_3-solution000001.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_2_1_4_3-solution000002.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_2_1_4_3.eprime create mode 100644 tests/exhaustive/basic/set06/expected/model_2_2_1_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_2_2_1_1-solution000002.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_2_2_1_1.eprime create mode 100644 tests/exhaustive/basic/set06/expected/model_2_2_1_3-solution000001.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_2_2_1_3-solution000002.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_2_2_1_3.eprime create mode 100644 tests/exhaustive/basic/set06/expected/model_2_2_1_4-solution000001.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_2_2_1_4-solution000002.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_2_2_1_4.eprime create mode 100644 tests/exhaustive/basic/set06/expected/model_2_2_2_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_2_2_2_1-solution000002.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_2_2_2_1.eprime create mode 100644 tests/exhaustive/basic/set06/expected/model_2_2_2_2-solution000001.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_2_2_2_2-solution000002.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_2_2_2_2.eprime create mode 100644 tests/exhaustive/basic/set06/expected/model_2_2_2_3-solution000001.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_2_2_2_3-solution000002.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_2_2_2_3.eprime create mode 100644 tests/exhaustive/basic/set06/expected/model_2_2_2_4-solution000001.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_2_2_2_4-solution000002.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_2_2_2_4.eprime create mode 100644 tests/exhaustive/basic/set06/expected/model_2_2_3_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_2_2_3_1-solution000002.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_2_2_3_1.eprime create mode 100644 tests/exhaustive/basic/set06/expected/model_2_2_3_2-solution000001.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_2_2_3_2-solution000002.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_2_2_3_2.eprime create mode 100644 tests/exhaustive/basic/set06/expected/model_2_2_3_4-solution000001.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_2_2_3_4-solution000002.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_2_2_3_4.eprime create mode 100644 tests/exhaustive/basic/set06/expected/model_2_2_4_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_2_2_4_1-solution000002.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_2_2_4_1.eprime create mode 100644 tests/exhaustive/basic/set06/expected/model_2_2_4_2-solution000001.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_2_2_4_2-solution000002.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_2_2_4_2.eprime create mode 100644 tests/exhaustive/basic/set06/expected/model_2_2_4_3-solution000001.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_2_2_4_3-solution000002.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_2_2_4_3.eprime create mode 100644 tests/exhaustive/basic/set06/expected/model_2_3_1_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_2_3_1_1-solution000002.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_2_3_1_1.eprime create mode 100644 tests/exhaustive/basic/set06/expected/model_2_3_1_4-solution000001.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_2_3_1_4-solution000002.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_2_3_1_4.eprime create mode 100644 tests/exhaustive/basic/set06/expected/model_2_3_2_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_2_3_2_1-solution000002.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_2_3_2_1.eprime create mode 100644 tests/exhaustive/basic/set06/expected/model_2_3_2_2-solution000001.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_2_3_2_2-solution000002.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_2_3_2_2.eprime create mode 100644 tests/exhaustive/basic/set06/expected/model_2_3_2_4-solution000001.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_2_3_2_4-solution000002.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_2_3_2_4.eprime create mode 100644 tests/exhaustive/basic/set06/expected/model_2_3_3_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_2_3_3_1-solution000002.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_2_3_3_1.eprime create mode 100644 tests/exhaustive/basic/set06/expected/model_2_3_3_2-solution000001.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_2_3_3_2-solution000002.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_2_3_3_2.eprime create mode 100644 tests/exhaustive/basic/set06/expected/model_2_3_3_4-solution000001.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_2_3_3_4-solution000002.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_2_3_3_4.eprime create mode 100644 tests/exhaustive/basic/set06/expected/model_2_3_4_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_2_3_4_1-solution000002.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_2_3_4_1.eprime create mode 100644 tests/exhaustive/basic/set06/expected/model_2_3_4_2-solution000001.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_2_3_4_2-solution000002.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_2_3_4_2.eprime create mode 100644 tests/exhaustive/basic/set06/expected/model_2_4_1_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_2_4_1_1-solution000002.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_2_4_1_1.eprime create mode 100644 tests/exhaustive/basic/set06/expected/model_2_4_1_3-solution000001.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_2_4_1_3-solution000002.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_2_4_1_3.eprime create mode 100644 tests/exhaustive/basic/set06/expected/model_2_4_2_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_2_4_2_1-solution000002.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_2_4_2_1.eprime create mode 100644 tests/exhaustive/basic/set06/expected/model_2_4_2_2-solution000001.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_2_4_2_2-solution000002.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_2_4_2_2.eprime create mode 100644 tests/exhaustive/basic/set06/expected/model_2_4_2_3-solution000001.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_2_4_2_3-solution000002.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_2_4_2_3.eprime create mode 100644 tests/exhaustive/basic/set06/expected/model_2_4_3_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_2_4_3_1-solution000002.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_2_4_3_1.eprime create mode 100644 tests/exhaustive/basic/set06/expected/model_2_4_3_2-solution000001.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_2_4_3_2-solution000002.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_2_4_3_2.eprime create mode 100644 tests/exhaustive/basic/set06/expected/model_2_4_4_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_2_4_4_1-solution000002.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_2_4_4_1.eprime create mode 100644 tests/exhaustive/basic/set06/expected/model_2_4_4_2-solution000001.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_2_4_4_2-solution000002.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_2_4_4_2.eprime create mode 100644 tests/exhaustive/basic/set06/expected/model_2_4_4_3-solution000001.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_2_4_4_3-solution000002.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_2_4_4_3.eprime create mode 100644 tests/exhaustive/basic/set06/expected/model_3_1_1_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_3_1_1_1-solution000002.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_3_1_1_1.eprime create mode 100644 tests/exhaustive/basic/set06/expected/model_3_1_1_2-solution000001.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_3_1_1_2-solution000002.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_3_1_1_2.eprime create mode 100644 tests/exhaustive/basic/set06/expected/model_3_1_1_4-solution000001.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_3_1_1_4-solution000002.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_3_1_1_4.eprime create mode 100644 tests/exhaustive/basic/set06/expected/model_3_1_2_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_3_1_2_1-solution000002.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_3_1_2_1.eprime create mode 100644 tests/exhaustive/basic/set06/expected/model_3_1_2_4-solution000001.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_3_1_2_4-solution000002.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_3_1_2_4.eprime create mode 100644 tests/exhaustive/basic/set06/expected/model_3_1_3_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_3_1_3_1-solution000002.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_3_1_3_1.eprime create mode 100644 tests/exhaustive/basic/set06/expected/model_3_1_3_2-solution000001.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_3_1_3_2-solution000002.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_3_1_3_2.eprime create mode 100644 tests/exhaustive/basic/set06/expected/model_3_1_3_4-solution000001.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_3_1_3_4-solution000002.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_3_1_3_4.eprime create mode 100644 tests/exhaustive/basic/set06/expected/model_3_1_4_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_3_1_4_1-solution000002.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_3_1_4_1.eprime create mode 100644 tests/exhaustive/basic/set06/expected/model_3_1_4_2-solution000001.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_3_1_4_2-solution000002.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_3_1_4_2.eprime create mode 100644 tests/exhaustive/basic/set06/expected/model_3_2_1_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_3_2_1_1-solution000002.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_3_2_1_1.eprime create mode 100644 tests/exhaustive/basic/set06/expected/model_3_2_1_4-solution000001.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_3_2_1_4-solution000002.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_3_2_1_4.eprime create mode 100644 tests/exhaustive/basic/set06/expected/model_3_2_2_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_3_2_2_1-solution000002.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_3_2_2_1.eprime create mode 100644 tests/exhaustive/basic/set06/expected/model_3_2_2_2-solution000001.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_3_2_2_2-solution000002.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_3_2_2_2.eprime create mode 100644 tests/exhaustive/basic/set06/expected/model_3_2_2_4-solution000001.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_3_2_2_4-solution000002.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_3_2_2_4.eprime create mode 100644 tests/exhaustive/basic/set06/expected/model_3_2_3_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_3_2_3_1-solution000002.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_3_2_3_1.eprime create mode 100644 tests/exhaustive/basic/set06/expected/model_3_2_3_2-solution000001.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_3_2_3_2-solution000002.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_3_2_3_2.eprime create mode 100644 tests/exhaustive/basic/set06/expected/model_3_2_3_4-solution000001.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_3_2_3_4-solution000002.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_3_2_3_4.eprime create mode 100644 tests/exhaustive/basic/set06/expected/model_3_2_4_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_3_2_4_1-solution000002.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_3_2_4_1.eprime create mode 100644 tests/exhaustive/basic/set06/expected/model_3_2_4_2-solution000001.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_3_2_4_2-solution000002.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_3_2_4_2.eprime create mode 100644 tests/exhaustive/basic/set06/expected/model_3_3_1_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_3_3_1_1-solution000002.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_3_3_1_1.eprime create mode 100644 tests/exhaustive/basic/set06/expected/model_3_3_1_2-solution000001.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_3_3_1_2-solution000002.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_3_3_1_2.eprime create mode 100644 tests/exhaustive/basic/set06/expected/model_3_3_1_4-solution000001.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_3_3_1_4-solution000002.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_3_3_1_4.eprime create mode 100644 tests/exhaustive/basic/set06/expected/model_3_3_2_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_3_3_2_1-solution000002.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_3_3_2_1.eprime create mode 100644 tests/exhaustive/basic/set06/expected/model_3_3_2_2-solution000001.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_3_3_2_2-solution000002.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_3_3_2_2.eprime create mode 100644 tests/exhaustive/basic/set06/expected/model_3_3_2_4-solution000001.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_3_3_2_4-solution000002.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_3_3_2_4.eprime create mode 100644 tests/exhaustive/basic/set06/expected/model_3_3_3_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_3_3_3_1-solution000002.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_3_3_3_1.eprime create mode 100644 tests/exhaustive/basic/set06/expected/model_3_3_3_2-solution000001.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_3_3_3_2-solution000002.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_3_3_3_2.eprime create mode 100644 tests/exhaustive/basic/set06/expected/model_3_3_3_3-solution000001.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_3_3_3_3-solution000002.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_3_3_3_3.eprime create mode 100644 tests/exhaustive/basic/set06/expected/model_3_3_3_4-solution000001.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_3_3_3_4-solution000002.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_3_3_3_4.eprime create mode 100644 tests/exhaustive/basic/set06/expected/model_3_3_4_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_3_3_4_1-solution000002.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_3_3_4_1.eprime create mode 100644 tests/exhaustive/basic/set06/expected/model_3_3_4_2-solution000001.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_3_3_4_2-solution000002.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_3_3_4_2.eprime create mode 100644 tests/exhaustive/basic/set06/expected/model_3_3_4_3-solution000001.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_3_3_4_3-solution000002.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_3_3_4_3.eprime create mode 100644 tests/exhaustive/basic/set06/expected/model_3_4_1_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_3_4_1_1-solution000002.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_3_4_1_1.eprime create mode 100644 tests/exhaustive/basic/set06/expected/model_3_4_1_2-solution000001.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_3_4_1_2-solution000002.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_3_4_1_2.eprime create mode 100644 tests/exhaustive/basic/set06/expected/model_3_4_2_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_3_4_2_1-solution000002.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_3_4_2_1.eprime create mode 100644 tests/exhaustive/basic/set06/expected/model_3_4_2_2-solution000001.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_3_4_2_2-solution000002.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_3_4_2_2.eprime create mode 100644 tests/exhaustive/basic/set06/expected/model_3_4_3_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_3_4_3_1-solution000002.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_3_4_3_1.eprime create mode 100644 tests/exhaustive/basic/set06/expected/model_3_4_3_2-solution000001.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_3_4_3_2-solution000002.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_3_4_3_2.eprime create mode 100644 tests/exhaustive/basic/set06/expected/model_3_4_3_3-solution000001.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_3_4_3_3-solution000002.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_3_4_3_3.eprime create mode 100644 tests/exhaustive/basic/set06/expected/model_3_4_4_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_3_4_4_1-solution000002.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_3_4_4_1.eprime create mode 100644 tests/exhaustive/basic/set06/expected/model_3_4_4_2-solution000001.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_3_4_4_2-solution000002.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_3_4_4_2.eprime create mode 100644 tests/exhaustive/basic/set06/expected/model_3_4_4_3-solution000001.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_3_4_4_3-solution000002.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_3_4_4_3.eprime create mode 100644 tests/exhaustive/basic/set06/expected/model_4_1_1_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_4_1_1_1-solution000002.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_4_1_1_1.eprime create mode 100644 tests/exhaustive/basic/set06/expected/model_4_1_1_2-solution000001.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_4_1_1_2-solution000002.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_4_1_1_2.eprime create mode 100644 tests/exhaustive/basic/set06/expected/model_4_1_1_3-solution000001.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_4_1_1_3-solution000002.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_4_1_1_3.eprime create mode 100644 tests/exhaustive/basic/set06/expected/model_4_1_2_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_4_1_2_1-solution000002.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_4_1_2_1.eprime create mode 100644 tests/exhaustive/basic/set06/expected/model_4_1_2_3-solution000001.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_4_1_2_3-solution000002.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_4_1_2_3.eprime create mode 100644 tests/exhaustive/basic/set06/expected/model_4_1_3_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_4_1_3_1-solution000002.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_4_1_3_1.eprime create mode 100644 tests/exhaustive/basic/set06/expected/model_4_1_3_2-solution000001.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_4_1_3_2-solution000002.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_4_1_3_2.eprime create mode 100644 tests/exhaustive/basic/set06/expected/model_4_1_4_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_4_1_4_1-solution000002.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_4_1_4_1.eprime create mode 100644 tests/exhaustive/basic/set06/expected/model_4_1_4_2-solution000001.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_4_1_4_2-solution000002.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_4_1_4_2.eprime create mode 100644 tests/exhaustive/basic/set06/expected/model_4_1_4_3-solution000001.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_4_1_4_3-solution000002.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_4_1_4_3.eprime create mode 100644 tests/exhaustive/basic/set06/expected/model_4_2_1_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_4_2_1_1-solution000002.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_4_2_1_1.eprime create mode 100644 tests/exhaustive/basic/set06/expected/model_4_2_1_3-solution000001.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_4_2_1_3-solution000002.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_4_2_1_3.eprime create mode 100644 tests/exhaustive/basic/set06/expected/model_4_2_2_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_4_2_2_1-solution000002.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_4_2_2_1.eprime create mode 100644 tests/exhaustive/basic/set06/expected/model_4_2_2_2-solution000001.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_4_2_2_2-solution000002.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_4_2_2_2.eprime create mode 100644 tests/exhaustive/basic/set06/expected/model_4_2_2_3-solution000001.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_4_2_2_3-solution000002.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_4_2_2_3.eprime create mode 100644 tests/exhaustive/basic/set06/expected/model_4_2_3_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_4_2_3_1-solution000002.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_4_2_3_1.eprime create mode 100644 tests/exhaustive/basic/set06/expected/model_4_2_3_2-solution000001.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_4_2_3_2-solution000002.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_4_2_3_2.eprime create mode 100644 tests/exhaustive/basic/set06/expected/model_4_2_4_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_4_2_4_1-solution000002.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_4_2_4_1.eprime create mode 100644 tests/exhaustive/basic/set06/expected/model_4_2_4_2-solution000001.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_4_2_4_2-solution000002.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_4_2_4_2.eprime create mode 100644 tests/exhaustive/basic/set06/expected/model_4_2_4_3-solution000001.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_4_2_4_3-solution000002.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_4_2_4_3.eprime create mode 100644 tests/exhaustive/basic/set06/expected/model_4_3_1_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_4_3_1_1-solution000002.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_4_3_1_1.eprime create mode 100644 tests/exhaustive/basic/set06/expected/model_4_3_1_2-solution000001.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_4_3_1_2-solution000002.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_4_3_1_2.eprime create mode 100644 tests/exhaustive/basic/set06/expected/model_4_3_2_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_4_3_2_1-solution000002.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_4_3_2_1.eprime create mode 100644 tests/exhaustive/basic/set06/expected/model_4_3_2_2-solution000001.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_4_3_2_2-solution000002.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_4_3_2_2.eprime create mode 100644 tests/exhaustive/basic/set06/expected/model_4_3_3_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_4_3_3_1-solution000002.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_4_3_3_1.eprime create mode 100644 tests/exhaustive/basic/set06/expected/model_4_3_3_2-solution000001.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_4_3_3_2-solution000002.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_4_3_3_2.eprime create mode 100644 tests/exhaustive/basic/set06/expected/model_4_3_3_3-solution000001.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_4_3_3_3-solution000002.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_4_3_3_3.eprime create mode 100644 tests/exhaustive/basic/set06/expected/model_4_3_4_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_4_3_4_1-solution000002.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_4_3_4_1.eprime create mode 100644 tests/exhaustive/basic/set06/expected/model_4_3_4_2-solution000001.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_4_3_4_2-solution000002.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_4_3_4_2.eprime create mode 100644 tests/exhaustive/basic/set06/expected/model_4_3_4_3-solution000001.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_4_3_4_3-solution000002.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_4_3_4_3.eprime create mode 100644 tests/exhaustive/basic/set06/expected/model_4_4_1_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_4_4_1_1-solution000002.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_4_4_1_1.eprime create mode 100644 tests/exhaustive/basic/set06/expected/model_4_4_1_2-solution000001.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_4_4_1_2-solution000002.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_4_4_1_2.eprime create mode 100644 tests/exhaustive/basic/set06/expected/model_4_4_1_3-solution000001.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_4_4_1_3-solution000002.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_4_4_1_3.eprime create mode 100644 tests/exhaustive/basic/set06/expected/model_4_4_2_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_4_4_2_1-solution000002.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_4_4_2_1.eprime create mode 100644 tests/exhaustive/basic/set06/expected/model_4_4_2_2-solution000001.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_4_4_2_2-solution000002.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_4_4_2_2.eprime create mode 100644 tests/exhaustive/basic/set06/expected/model_4_4_2_3-solution000001.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_4_4_2_3-solution000002.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_4_4_2_3.eprime create mode 100644 tests/exhaustive/basic/set06/expected/model_4_4_3_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_4_4_3_1-solution000002.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_4_4_3_1.eprime create mode 100644 tests/exhaustive/basic/set06/expected/model_4_4_3_2-solution000001.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_4_4_3_2-solution000002.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_4_4_3_2.eprime create mode 100644 tests/exhaustive/basic/set06/expected/model_4_4_3_3-solution000001.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_4_4_3_3-solution000002.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_4_4_3_3.eprime create mode 100644 tests/exhaustive/basic/set06/expected/model_4_4_4_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_4_4_4_1-solution000002.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_4_4_4_1.eprime create mode 100644 tests/exhaustive/basic/set06/expected/model_4_4_4_2-solution000001.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_4_4_4_2-solution000002.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_4_4_4_2.eprime create mode 100644 tests/exhaustive/basic/set06/expected/model_4_4_4_3-solution000001.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_4_4_4_3-solution000002.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_4_4_4_3.eprime create mode 100644 tests/exhaustive/basic/set06/expected/model_4_4_4_4-solution000001.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_4_4_4_4-solution000002.solution create mode 100644 tests/exhaustive/basic/set06/expected/model_4_4_4_4.eprime create mode 100644 tests/exhaustive/basic/set07/expected/model_1_1_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set07/expected/model_1_1_1.eprime create mode 100644 tests/exhaustive/basic/set07/expected/model_1_1_2-solution000001.solution create mode 100644 tests/exhaustive/basic/set07/expected/model_1_1_2.eprime create mode 100644 tests/exhaustive/basic/set07/expected/model_1_1_3-solution000001.solution create mode 100644 tests/exhaustive/basic/set07/expected/model_1_1_3.eprime create mode 100644 tests/exhaustive/basic/set07/expected/model_1_1_4-solution000001.solution create mode 100644 tests/exhaustive/basic/set07/expected/model_1_1_4.eprime create mode 100644 tests/exhaustive/basic/set07/expected/model_1_2_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set07/expected/model_1_2_1.eprime create mode 100644 tests/exhaustive/basic/set07/expected/model_1_2_3-solution000001.solution create mode 100644 tests/exhaustive/basic/set07/expected/model_1_2_3.eprime create mode 100644 tests/exhaustive/basic/set07/expected/model_1_2_4-solution000001.solution create mode 100644 tests/exhaustive/basic/set07/expected/model_1_2_4.eprime create mode 100644 tests/exhaustive/basic/set07/expected/model_1_3_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set07/expected/model_1_3_1.eprime create mode 100644 tests/exhaustive/basic/set07/expected/model_1_3_2-solution000001.solution create mode 100644 tests/exhaustive/basic/set07/expected/model_1_3_2.eprime create mode 100644 tests/exhaustive/basic/set07/expected/model_1_3_4-solution000001.solution create mode 100644 tests/exhaustive/basic/set07/expected/model_1_3_4.eprime create mode 100644 tests/exhaustive/basic/set07/expected/model_1_4_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set07/expected/model_1_4_1.eprime create mode 100644 tests/exhaustive/basic/set07/expected/model_1_4_2-solution000001.solution create mode 100644 tests/exhaustive/basic/set07/expected/model_1_4_2.eprime create mode 100644 tests/exhaustive/basic/set07/expected/model_1_4_3-solution000001.solution create mode 100644 tests/exhaustive/basic/set07/expected/model_1_4_3.eprime create mode 100644 tests/exhaustive/basic/set07/expected/model_2_1_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set07/expected/model_2_1_1.eprime create mode 100644 tests/exhaustive/basic/set07/expected/model_2_1_3-solution000001.solution create mode 100644 tests/exhaustive/basic/set07/expected/model_2_1_3.eprime create mode 100644 tests/exhaustive/basic/set07/expected/model_2_1_4-solution000001.solution create mode 100644 tests/exhaustive/basic/set07/expected/model_2_1_4.eprime create mode 100644 tests/exhaustive/basic/set07/expected/model_2_2_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set07/expected/model_2_2_1.eprime create mode 100644 tests/exhaustive/basic/set07/expected/model_2_2_2-solution000001.solution create mode 100644 tests/exhaustive/basic/set07/expected/model_2_2_2.eprime create mode 100644 tests/exhaustive/basic/set07/expected/model_2_2_3-solution000001.solution create mode 100644 tests/exhaustive/basic/set07/expected/model_2_2_3.eprime create mode 100644 tests/exhaustive/basic/set07/expected/model_2_2_4-solution000001.solution create mode 100644 tests/exhaustive/basic/set07/expected/model_2_2_4.eprime create mode 100644 tests/exhaustive/basic/set07/expected/model_2_3_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set07/expected/model_2_3_1.eprime create mode 100644 tests/exhaustive/basic/set07/expected/model_2_3_2-solution000001.solution create mode 100644 tests/exhaustive/basic/set07/expected/model_2_3_2.eprime create mode 100644 tests/exhaustive/basic/set07/expected/model_2_3_4-solution000001.solution create mode 100644 tests/exhaustive/basic/set07/expected/model_2_3_4.eprime create mode 100644 tests/exhaustive/basic/set07/expected/model_2_4_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set07/expected/model_2_4_1.eprime create mode 100644 tests/exhaustive/basic/set07/expected/model_2_4_2-solution000001.solution create mode 100644 tests/exhaustive/basic/set07/expected/model_2_4_2.eprime create mode 100644 tests/exhaustive/basic/set07/expected/model_2_4_3-solution000001.solution create mode 100644 tests/exhaustive/basic/set07/expected/model_2_4_3.eprime create mode 100644 tests/exhaustive/basic/set07/expected/model_3_1_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set07/expected/model_3_1_1.eprime create mode 100644 tests/exhaustive/basic/set07/expected/model_3_1_2-solution000001.solution create mode 100644 tests/exhaustive/basic/set07/expected/model_3_1_2.eprime create mode 100644 tests/exhaustive/basic/set07/expected/model_3_1_4-solution000001.solution create mode 100644 tests/exhaustive/basic/set07/expected/model_3_1_4.eprime create mode 100644 tests/exhaustive/basic/set07/expected/model_3_2_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set07/expected/model_3_2_1.eprime create mode 100644 tests/exhaustive/basic/set07/expected/model_3_2_2-solution000001.solution create mode 100644 tests/exhaustive/basic/set07/expected/model_3_2_2.eprime create mode 100644 tests/exhaustive/basic/set07/expected/model_3_2_4-solution000001.solution create mode 100644 tests/exhaustive/basic/set07/expected/model_3_2_4.eprime create mode 100644 tests/exhaustive/basic/set07/expected/model_3_3_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set07/expected/model_3_3_1.eprime create mode 100644 tests/exhaustive/basic/set07/expected/model_3_3_2-solution000001.solution create mode 100644 tests/exhaustive/basic/set07/expected/model_3_3_2.eprime create mode 100644 tests/exhaustive/basic/set07/expected/model_3_3_3-solution000001.solution create mode 100644 tests/exhaustive/basic/set07/expected/model_3_3_3.eprime create mode 100644 tests/exhaustive/basic/set07/expected/model_3_3_4-solution000001.solution create mode 100644 tests/exhaustive/basic/set07/expected/model_3_3_4.eprime create mode 100644 tests/exhaustive/basic/set07/expected/model_3_4_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set07/expected/model_3_4_1.eprime create mode 100644 tests/exhaustive/basic/set07/expected/model_3_4_2-solution000001.solution create mode 100644 tests/exhaustive/basic/set07/expected/model_3_4_2.eprime create mode 100644 tests/exhaustive/basic/set07/expected/model_3_4_3-solution000001.solution create mode 100644 tests/exhaustive/basic/set07/expected/model_3_4_3.eprime create mode 100644 tests/exhaustive/basic/set07/expected/model_4_1_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set07/expected/model_4_1_1.eprime create mode 100644 tests/exhaustive/basic/set07/expected/model_4_1_2-solution000001.solution create mode 100644 tests/exhaustive/basic/set07/expected/model_4_1_2.eprime create mode 100644 tests/exhaustive/basic/set07/expected/model_4_1_3-solution000001.solution create mode 100644 tests/exhaustive/basic/set07/expected/model_4_1_3.eprime create mode 100644 tests/exhaustive/basic/set07/expected/model_4_2_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set07/expected/model_4_2_1.eprime create mode 100644 tests/exhaustive/basic/set07/expected/model_4_2_2-solution000001.solution create mode 100644 tests/exhaustive/basic/set07/expected/model_4_2_2.eprime create mode 100644 tests/exhaustive/basic/set07/expected/model_4_2_3-solution000001.solution create mode 100644 tests/exhaustive/basic/set07/expected/model_4_2_3.eprime create mode 100644 tests/exhaustive/basic/set07/expected/model_4_3_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set07/expected/model_4_3_1.eprime create mode 100644 tests/exhaustive/basic/set07/expected/model_4_3_2-solution000001.solution create mode 100644 tests/exhaustive/basic/set07/expected/model_4_3_2.eprime create mode 100644 tests/exhaustive/basic/set07/expected/model_4_3_3-solution000001.solution create mode 100644 tests/exhaustive/basic/set07/expected/model_4_3_3.eprime create mode 100644 tests/exhaustive/basic/set07/expected/model_4_4_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set07/expected/model_4_4_1.eprime create mode 100644 tests/exhaustive/basic/set07/expected/model_4_4_2-solution000001.solution create mode 100644 tests/exhaustive/basic/set07/expected/model_4_4_2.eprime create mode 100644 tests/exhaustive/basic/set07/expected/model_4_4_3-solution000001.solution create mode 100644 tests/exhaustive/basic/set07/expected/model_4_4_3.eprime create mode 100644 tests/exhaustive/basic/set07/expected/model_4_4_4-solution000001.solution create mode 100644 tests/exhaustive/basic/set07/expected/model_4_4_4.eprime create mode 100644 tests/exhaustive/basic/set08/expected/model_1_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set08/expected/model_1_1.eprime create mode 100644 tests/exhaustive/basic/set08/expected/model_1_2-solution000001.solution create mode 100644 tests/exhaustive/basic/set08/expected/model_1_2.eprime create mode 100644 tests/exhaustive/basic/set08/expected/model_2_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set08/expected/model_2_1.eprime create mode 100644 tests/exhaustive/basic/set08/expected/model_2_2-solution000001.solution create mode 100644 tests/exhaustive/basic/set08/expected/model_2_2.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_1_1_1_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_1_1_1_1-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_1_1_1_1.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_1_1_1_2-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_1_1_1_2-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_1_1_1_2.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_1_1_1_3-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_1_1_1_3-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_1_1_1_3.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_1_1_1_4-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_1_1_1_4-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_1_1_1_4.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_1_1_2_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_1_1_2_1-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_1_1_2_1.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_1_1_2_2-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_1_1_2_2-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_1_1_2_2.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_1_1_2_3-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_1_1_2_3-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_1_1_2_3.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_1_1_2_4-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_1_1_2_4-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_1_1_2_4.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_1_1_3_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_1_1_3_1-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_1_1_3_1.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_1_1_3_2-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_1_1_3_2-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_1_1_3_2.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_1_1_3_3-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_1_1_3_3-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_1_1_3_3.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_1_1_3_4-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_1_1_3_4-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_1_1_3_4.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_1_1_4_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_1_1_4_1-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_1_1_4_1.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_1_1_4_2-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_1_1_4_2-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_1_1_4_2.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_1_1_4_3-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_1_1_4_3-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_1_1_4_3.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_1_1_4_4-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_1_1_4_4-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_1_1_4_4.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_1_2_1_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_1_2_1_1-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_1_2_1_1.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_1_2_1_2-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_1_2_1_2-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_1_2_1_2.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_1_2_1_3-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_1_2_1_3-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_1_2_1_3.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_1_2_1_4-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_1_2_1_4-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_1_2_1_4.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_1_2_2_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_1_2_2_1-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_1_2_2_1.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_1_2_2_2-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_1_2_2_2-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_1_2_2_2.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_1_2_2_3-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_1_2_2_3-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_1_2_2_3.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_1_2_2_4-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_1_2_2_4-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_1_2_2_4.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_1_2_3_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_1_2_3_1-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_1_2_3_1.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_1_2_3_2-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_1_2_3_2-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_1_2_3_2.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_1_2_3_3-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_1_2_3_3-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_1_2_3_3.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_1_2_3_4-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_1_2_3_4-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_1_2_3_4.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_1_2_4_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_1_2_4_1-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_1_2_4_1.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_1_2_4_2-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_1_2_4_2-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_1_2_4_2.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_1_2_4_3-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_1_2_4_3-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_1_2_4_3.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_1_2_4_4-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_1_2_4_4-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_1_2_4_4.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_1_3_1_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_1_3_1_1-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_1_3_1_1.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_1_3_1_2-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_1_3_1_2-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_1_3_1_2.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_1_3_1_3-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_1_3_1_3-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_1_3_1_3.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_1_3_1_4-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_1_3_1_4-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_1_3_1_4.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_1_3_2_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_1_3_2_1-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_1_3_2_1.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_1_3_2_2-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_1_3_2_2-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_1_3_2_2.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_1_3_2_3-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_1_3_2_3-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_1_3_2_3.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_1_3_2_4-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_1_3_2_4-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_1_3_2_4.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_1_3_3_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_1_3_3_1-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_1_3_3_1.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_1_3_3_2-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_1_3_3_2-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_1_3_3_2.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_1_3_3_3-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_1_3_3_3-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_1_3_3_3.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_1_3_3_4-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_1_3_3_4-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_1_3_3_4.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_1_3_4_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_1_3_4_1-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_1_3_4_1.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_1_3_4_2-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_1_3_4_2-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_1_3_4_2.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_1_3_4_3-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_1_3_4_3-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_1_3_4_3.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_1_3_4_4-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_1_3_4_4-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_1_3_4_4.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_1_4_1_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_1_4_1_1-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_1_4_1_1.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_1_4_1_2-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_1_4_1_2-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_1_4_1_2.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_1_4_1_3-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_1_4_1_3-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_1_4_1_3.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_1_4_1_4-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_1_4_1_4-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_1_4_1_4.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_1_4_2_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_1_4_2_1-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_1_4_2_1.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_1_4_2_2-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_1_4_2_2-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_1_4_2_2.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_1_4_2_3-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_1_4_2_3-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_1_4_2_3.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_1_4_2_4-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_1_4_2_4-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_1_4_2_4.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_1_4_3_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_1_4_3_1-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_1_4_3_1.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_1_4_3_2-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_1_4_3_2-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_1_4_3_2.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_1_4_3_3-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_1_4_3_3-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_1_4_3_3.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_1_4_3_4-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_1_4_3_4-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_1_4_3_4.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_1_4_4_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_1_4_4_1-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_1_4_4_1.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_1_4_4_2-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_1_4_4_2-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_1_4_4_2.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_1_4_4_3-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_1_4_4_3-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_1_4_4_3.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_1_4_4_4-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_1_4_4_4-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_1_4_4_4.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_2_1_1_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_2_1_1_1-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_2_1_1_1.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_2_1_1_2-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_2_1_1_2-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_2_1_1_2.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_2_1_1_3-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_2_1_1_3-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_2_1_1_3.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_2_1_1_4-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_2_1_1_4-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_2_1_1_4.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_2_1_2_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_2_1_2_1-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_2_1_2_1.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_2_1_2_2-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_2_1_2_2-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_2_1_2_2.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_2_1_2_3-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_2_1_2_3-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_2_1_2_3.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_2_1_2_4-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_2_1_2_4-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_2_1_2_4.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_2_1_3_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_2_1_3_1-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_2_1_3_1.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_2_1_3_2-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_2_1_3_2-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_2_1_3_2.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_2_1_3_3-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_2_1_3_3-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_2_1_3_3.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_2_1_3_4-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_2_1_3_4-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_2_1_3_4.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_2_1_4_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_2_1_4_1-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_2_1_4_1.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_2_1_4_2-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_2_1_4_2-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_2_1_4_2.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_2_1_4_3-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_2_1_4_3-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_2_1_4_3.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_2_1_4_4-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_2_1_4_4-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_2_1_4_4.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_2_2_1_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_2_2_1_1-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_2_2_1_1.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_2_2_1_2-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_2_2_1_2-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_2_2_1_2.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_2_2_1_3-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_2_2_1_3-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_2_2_1_3.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_2_2_1_4-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_2_2_1_4-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_2_2_1_4.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_2_2_2_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_2_2_2_1-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_2_2_2_1.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_2_2_2_2-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_2_2_2_2-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_2_2_2_2.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_2_2_2_3-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_2_2_2_3-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_2_2_2_3.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_2_2_2_4-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_2_2_2_4-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_2_2_2_4.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_2_2_3_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_2_2_3_1-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_2_2_3_1.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_2_2_3_2-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_2_2_3_2-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_2_2_3_2.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_2_2_3_3-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_2_2_3_3-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_2_2_3_3.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_2_2_3_4-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_2_2_3_4-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_2_2_3_4.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_2_2_4_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_2_2_4_1-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_2_2_4_1.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_2_2_4_2-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_2_2_4_2-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_2_2_4_2.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_2_2_4_3-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_2_2_4_3-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_2_2_4_3.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_2_2_4_4-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_2_2_4_4-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_2_2_4_4.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_2_3_1_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_2_3_1_1-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_2_3_1_1.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_2_3_1_2-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_2_3_1_2-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_2_3_1_2.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_2_3_1_3-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_2_3_1_3-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_2_3_1_3.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_2_3_1_4-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_2_3_1_4-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_2_3_1_4.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_2_3_2_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_2_3_2_1-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_2_3_2_1.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_2_3_2_2-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_2_3_2_2-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_2_3_2_2.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_2_3_2_3-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_2_3_2_3-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_2_3_2_3.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_2_3_2_4-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_2_3_2_4-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_2_3_2_4.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_2_3_3_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_2_3_3_1-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_2_3_3_1.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_2_3_3_2-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_2_3_3_2-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_2_3_3_2.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_2_3_3_3-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_2_3_3_3-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_2_3_3_3.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_2_3_3_4-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_2_3_3_4-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_2_3_3_4.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_2_3_4_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_2_3_4_1-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_2_3_4_1.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_2_3_4_2-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_2_3_4_2-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_2_3_4_2.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_2_3_4_3-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_2_3_4_3-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_2_3_4_3.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_2_3_4_4-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_2_3_4_4-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_2_3_4_4.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_2_4_1_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_2_4_1_1-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_2_4_1_1.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_2_4_1_2-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_2_4_1_2-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_2_4_1_2.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_2_4_1_3-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_2_4_1_3-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_2_4_1_3.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_2_4_1_4-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_2_4_1_4-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_2_4_1_4.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_2_4_2_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_2_4_2_1-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_2_4_2_1.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_2_4_2_2-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_2_4_2_2-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_2_4_2_2.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_2_4_2_3-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_2_4_2_3-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_2_4_2_3.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_2_4_2_4-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_2_4_2_4-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_2_4_2_4.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_2_4_3_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_2_4_3_1-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_2_4_3_1.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_2_4_3_2-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_2_4_3_2-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_2_4_3_2.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_2_4_3_3-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_2_4_3_3-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_2_4_3_3.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_2_4_3_4-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_2_4_3_4-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_2_4_3_4.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_2_4_4_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_2_4_4_1-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_2_4_4_1.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_2_4_4_2-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_2_4_4_2-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_2_4_4_2.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_2_4_4_3-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_2_4_4_3-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_2_4_4_3.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_2_4_4_4-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_2_4_4_4-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_2_4_4_4.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_3_1_1_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_3_1_1_1-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_3_1_1_1.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_3_1_1_2-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_3_1_1_2-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_3_1_1_2.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_3_1_1_3-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_3_1_1_3-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_3_1_1_3.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_3_1_1_4-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_3_1_1_4-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_3_1_1_4.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_3_1_2_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_3_1_2_1-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_3_1_2_1.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_3_1_2_2-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_3_1_2_2-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_3_1_2_2.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_3_1_2_3-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_3_1_2_3-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_3_1_2_3.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_3_1_2_4-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_3_1_2_4-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_3_1_2_4.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_3_1_3_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_3_1_3_1-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_3_1_3_1.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_3_1_3_2-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_3_1_3_2-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_3_1_3_2.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_3_1_3_3-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_3_1_3_3-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_3_1_3_3.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_3_1_3_4-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_3_1_3_4-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_3_1_3_4.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_3_1_4_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_3_1_4_1-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_3_1_4_1.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_3_1_4_2-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_3_1_4_2-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_3_1_4_2.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_3_1_4_3-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_3_1_4_3-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_3_1_4_3.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_3_1_4_4-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_3_1_4_4-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_3_1_4_4.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_3_2_1_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_3_2_1_1-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_3_2_1_1.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_3_2_1_2-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_3_2_1_2-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_3_2_1_2.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_3_2_1_3-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_3_2_1_3-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_3_2_1_3.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_3_2_1_4-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_3_2_1_4-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_3_2_1_4.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_3_2_2_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_3_2_2_1-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_3_2_2_1.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_3_2_2_2-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_3_2_2_2-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_3_2_2_2.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_3_2_2_3-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_3_2_2_3-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_3_2_2_3.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_3_2_2_4-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_3_2_2_4-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_3_2_2_4.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_3_2_3_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_3_2_3_1-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_3_2_3_1.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_3_2_3_2-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_3_2_3_2-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_3_2_3_2.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_3_2_3_3-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_3_2_3_3-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_3_2_3_3.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_3_2_3_4-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_3_2_3_4-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_3_2_3_4.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_3_2_4_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_3_2_4_1-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_3_2_4_1.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_3_2_4_2-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_3_2_4_2-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_3_2_4_2.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_3_2_4_3-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_3_2_4_3-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_3_2_4_3.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_3_2_4_4-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_3_2_4_4-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_3_2_4_4.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_3_3_1_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_3_3_1_1-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_3_3_1_1.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_3_3_1_2-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_3_3_1_2-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_3_3_1_2.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_3_3_1_3-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_3_3_1_3-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_3_3_1_3.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_3_3_1_4-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_3_3_1_4-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_3_3_1_4.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_3_3_2_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_3_3_2_1-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_3_3_2_1.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_3_3_2_2-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_3_3_2_2-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_3_3_2_2.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_3_3_2_3-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_3_3_2_3-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_3_3_2_3.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_3_3_2_4-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_3_3_2_4-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_3_3_2_4.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_3_3_3_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_3_3_3_1-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_3_3_3_1.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_3_3_3_2-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_3_3_3_2-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_3_3_3_2.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_3_3_3_3-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_3_3_3_3-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_3_3_3_3.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_3_3_3_4-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_3_3_3_4-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_3_3_3_4.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_3_3_4_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_3_3_4_1-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_3_3_4_1.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_3_3_4_2-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_3_3_4_2-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_3_3_4_2.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_3_3_4_3-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_3_3_4_3-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_3_3_4_3.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_3_3_4_4-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_3_3_4_4-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_3_3_4_4.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_3_4_1_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_3_4_1_1-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_3_4_1_1.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_3_4_1_2-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_3_4_1_2-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_3_4_1_2.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_3_4_1_3-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_3_4_1_3-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_3_4_1_3.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_3_4_1_4-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_3_4_1_4-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_3_4_1_4.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_3_4_2_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_3_4_2_1-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_3_4_2_1.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_3_4_2_2-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_3_4_2_2-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_3_4_2_2.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_3_4_2_3-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_3_4_2_3-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_3_4_2_3.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_3_4_2_4-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_3_4_2_4-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_3_4_2_4.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_3_4_3_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_3_4_3_1-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_3_4_3_1.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_3_4_3_2-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_3_4_3_2-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_3_4_3_2.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_3_4_3_3-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_3_4_3_3-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_3_4_3_3.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_3_4_3_4-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_3_4_3_4-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_3_4_3_4.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_3_4_4_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_3_4_4_1-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_3_4_4_1.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_3_4_4_2-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_3_4_4_2-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_3_4_4_2.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_3_4_4_3-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_3_4_4_3-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_3_4_4_3.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_3_4_4_4-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_3_4_4_4-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_3_4_4_4.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_4_1_1_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_4_1_1_1-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_4_1_1_1.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_4_1_1_2-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_4_1_1_2-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_4_1_1_2.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_4_1_1_3-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_4_1_1_3-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_4_1_1_3.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_4_1_1_4-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_4_1_1_4-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_4_1_1_4.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_4_1_2_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_4_1_2_1-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_4_1_2_1.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_4_1_2_2-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_4_1_2_2-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_4_1_2_2.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_4_1_2_3-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_4_1_2_3-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_4_1_2_3.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_4_1_2_4-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_4_1_2_4-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_4_1_2_4.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_4_1_3_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_4_1_3_1-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_4_1_3_1.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_4_1_3_2-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_4_1_3_2-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_4_1_3_2.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_4_1_3_3-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_4_1_3_3-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_4_1_3_3.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_4_1_3_4-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_4_1_3_4-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_4_1_3_4.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_4_1_4_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_4_1_4_1-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_4_1_4_1.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_4_1_4_2-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_4_1_4_2-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_4_1_4_2.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_4_1_4_3-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_4_1_4_3-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_4_1_4_3.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_4_1_4_4-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_4_1_4_4-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_4_1_4_4.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_4_2_1_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_4_2_1_1-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_4_2_1_1.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_4_2_1_2-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_4_2_1_2-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_4_2_1_2.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_4_2_1_3-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_4_2_1_3-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_4_2_1_3.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_4_2_1_4-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_4_2_1_4-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_4_2_1_4.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_4_2_2_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_4_2_2_1-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_4_2_2_1.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_4_2_2_2-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_4_2_2_2-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_4_2_2_2.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_4_2_2_3-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_4_2_2_3-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_4_2_2_3.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_4_2_2_4-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_4_2_2_4-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_4_2_2_4.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_4_2_3_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_4_2_3_1-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_4_2_3_1.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_4_2_3_2-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_4_2_3_2-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_4_2_3_2.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_4_2_3_3-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_4_2_3_3-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_4_2_3_3.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_4_2_3_4-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_4_2_3_4-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_4_2_3_4.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_4_2_4_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_4_2_4_1-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_4_2_4_1.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_4_2_4_2-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_4_2_4_2-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_4_2_4_2.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_4_2_4_3-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_4_2_4_3-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_4_2_4_3.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_4_2_4_4-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_4_2_4_4-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_4_2_4_4.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_4_3_1_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_4_3_1_1-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_4_3_1_1.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_4_3_1_2-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_4_3_1_2-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_4_3_1_2.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_4_3_1_3-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_4_3_1_3-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_4_3_1_3.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_4_3_1_4-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_4_3_1_4-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_4_3_1_4.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_4_3_2_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_4_3_2_1-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_4_3_2_1.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_4_3_2_2-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_4_3_2_2-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_4_3_2_2.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_4_3_2_3-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_4_3_2_3-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_4_3_2_3.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_4_3_2_4-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_4_3_2_4-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_4_3_2_4.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_4_3_3_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_4_3_3_1-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_4_3_3_1.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_4_3_3_2-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_4_3_3_2-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_4_3_3_2.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_4_3_3_3-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_4_3_3_3-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_4_3_3_3.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_4_3_3_4-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_4_3_3_4-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_4_3_3_4.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_4_3_4_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_4_3_4_1-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_4_3_4_1.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_4_3_4_2-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_4_3_4_2-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_4_3_4_2.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_4_3_4_3-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_4_3_4_3-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_4_3_4_3.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_4_3_4_4-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_4_3_4_4-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_4_3_4_4.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_4_4_1_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_4_4_1_1-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_4_4_1_1.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_4_4_1_2-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_4_4_1_2-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_4_4_1_2.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_4_4_1_3-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_4_4_1_3-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_4_4_1_3.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_4_4_1_4-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_4_4_1_4-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_4_4_1_4.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_4_4_2_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_4_4_2_1-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_4_4_2_1.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_4_4_2_2-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_4_4_2_2-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_4_4_2_2.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_4_4_2_3-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_4_4_2_3-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_4_4_2_3.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_4_4_2_4-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_4_4_2_4-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_4_4_2_4.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_4_4_3_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_4_4_3_1-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_4_4_3_1.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_4_4_3_2-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_4_4_3_2-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_4_4_3_2.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_4_4_3_3-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_4_4_3_3-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_4_4_3_3.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_4_4_3_4-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_4_4_3_4-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_4_4_3_4.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_4_4_4_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_4_4_4_1-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_4_4_4_1.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_4_4_4_2-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_4_4_4_2-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_4_4_4_2.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_4_4_4_3-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_4_4_4_3-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_4_4_4_3.eprime create mode 100644 tests/exhaustive/basic/set09/expected/model_4_4_4_4-solution000001.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_4_4_4_4-solution000002.solution create mode 100644 tests/exhaustive/basic/set09/expected/model_4_4_4_4.eprime create mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_1-solution000001.solution create mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_1-solution000002.solution create mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_1-solution000003.solution create mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_1-solution000004.solution create mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_1-solution000005.solution create mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_1-solution000006.solution create mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_1-solution000007.solution create mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_1-solution000008.solution create mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_1-solution000009.solution create mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_1-solution000010.solution create mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_1-solution000011.solution create mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_1-solution000012.solution create mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_1-solution000013.solution create mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_1-solution000014.solution create mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_1-solution000015.solution create mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_1-solution000016.solution create mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_1.eprime create mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_2-solution000001.solution create mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_2-solution000002.solution create mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_2-solution000003.solution create mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_2-solution000004.solution create mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_2-solution000005.solution create mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_2-solution000006.solution create mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_2-solution000007.solution create mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_2-solution000008.solution create mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_2-solution000009.solution create mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_2-solution000010.solution create mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_2-solution000011.solution create mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_2-solution000012.solution create mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_2-solution000013.solution create mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_2-solution000014.solution create mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_2-solution000015.solution create mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_2-solution000016.solution create mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_2.eprime create mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_3-solution000001.solution create mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_3-solution000002.solution create mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_3-solution000003.solution create mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_3-solution000004.solution create mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_3-solution000005.solution create mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_3-solution000006.solution create mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_3-solution000007.solution create mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_3-solution000008.solution create mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_3-solution000009.solution create mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_3-solution000010.solution create mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_3-solution000011.solution create mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_3-solution000012.solution create mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_3-solution000013.solution create mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_3-solution000014.solution create mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_3-solution000015.solution create mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_3-solution000016.solution delete mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_3.eprime.orig create mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_4-solution000001.solution create mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_4-solution000002.solution create mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_4-solution000003.solution create mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_4-solution000004.solution create mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_4-solution000005.solution create mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_4-solution000006.solution create mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_4-solution000007.solution create mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_4-solution000008.solution create mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_4-solution000009.solution create mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_4-solution000010.solution create mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_4-solution000011.solution create mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_4-solution000012.solution create mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_4-solution000013.solution create mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_4-solution000014.solution create mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_4-solution000015.solution create mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_4-solution000016.solution create mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_4.eprime create mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_5-solution000001.solution create mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_5-solution000002.solution create mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_5-solution000003.solution create mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_5-solution000004.solution create mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_5-solution000005.solution create mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_5-solution000006.solution create mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_5-solution000007.solution create mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_5-solution000008.solution create mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_5-solution000009.solution create mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_5-solution000010.solution create mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_5-solution000011.solution create mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_5-solution000012.solution create mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_5-solution000013.solution create mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_5-solution000014.solution create mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_5-solution000015.solution create mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_5-solution000016.solution create mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_5.eprime create mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_6-solution000001.solution create mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_6-solution000002.solution create mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_6-solution000003.solution create mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_6-solution000004.solution create mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_6-solution000005.solution create mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_6-solution000006.solution create mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_6-solution000007.solution create mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_6-solution000008.solution create mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_6-solution000009.solution create mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_6-solution000010.solution create mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_6-solution000011.solution create mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_6-solution000012.solution create mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_6-solution000013.solution create mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_6-solution000014.solution create mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_6-solution000015.solution create mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_6-solution000016.solution create mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_6.eprime create mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_7-solution000001.solution create mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_7-solution000002.solution create mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_7-solution000003.solution create mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_7-solution000004.solution create mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_7-solution000005.solution create mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_7-solution000006.solution create mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_7-solution000007.solution create mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_7-solution000008.solution create mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_7-solution000009.solution create mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_7-solution000010.solution create mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_7-solution000011.solution create mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_7-solution000012.solution create mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_7-solution000013.solution create mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_7-solution000014.solution create mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_7-solution000015.solution create mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_7-solution000016.solution delete mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_7.eprime.orig create mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_8-solution000001.solution create mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_8-solution000002.solution create mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_8-solution000003.solution create mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_8-solution000004.solution create mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_8-solution000005.solution create mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_8-solution000006.solution create mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_8-solution000007.solution create mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_8-solution000008.solution create mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_8-solution000009.solution create mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_8-solution000010.solution create mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_8-solution000011.solution create mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_8-solution000012.solution create mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_8-solution000013.solution create mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_8-solution000014.solution create mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_8-solution000015.solution create mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_8-solution000016.solution create mode 100644 tests/exhaustive/basic/setOfSet01/expected/model_8.eprime create mode 100644 tests/exhaustive/basic/setOfSet02/expected/model_1_1-solution000002.solution create mode 100644 tests/exhaustive/basic/setOfSet02/expected/model_1_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/setOfSet02/expected/model_1_2.eprime.orig create mode 100644 tests/exhaustive/basic/setOfSet02/expected/model_2_1-solution000002.solution delete mode 100644 tests/exhaustive/basic/setOfSet02/expected/model_2_1.eprime.orig create mode 100644 tests/exhaustive/basic/setOfSet02/expected/model_2_2-solution000002.solution delete mode 100644 tests/exhaustive/basic/setOfSet02/expected/model_2_2.eprime.orig delete mode 100644 tests/exhaustive/basic/setOfSet03/expected/model_2.eprime.orig create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_1_1_1-solution000001.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_1_1_1-solution000002.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_1_1_1-solution000003.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_1_1_1-solution000004.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_1_1_1-solution000005.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_1_1_1-solution000006.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_1_1_1.eprime create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_1_1_2-solution000001.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_1_1_2-solution000002.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_1_1_2-solution000003.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_1_1_2-solution000004.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_1_1_2-solution000005.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_1_1_2-solution000006.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_1_1_2.eprime create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_1_1_3-solution000001.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_1_1_3-solution000002.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_1_1_3-solution000003.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_1_1_3-solution000004.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_1_1_3-solution000005.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_1_1_3-solution000006.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_1_1_3.eprime.orig create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_1_1_4-solution000001.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_1_1_4-solution000002.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_1_1_4-solution000003.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_1_1_4-solution000004.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_1_1_4-solution000005.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_1_1_4-solution000006.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_1_1_4.eprime create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_1_2_3-solution000001.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_1_2_3-solution000002.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_1_2_3-solution000003.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_1_2_3-solution000004.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_1_2_3-solution000005.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_1_2_3-solution000006.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_1_2_3.eprime.orig create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_1_2_4-solution000001.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_1_2_4-solution000002.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_1_2_4-solution000003.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_1_2_4-solution000004.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_1_2_4-solution000005.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_1_2_4-solution000006.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_1_2_4.eprime delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_1_3_1.eprime.orig create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_1_3_2-solution000001.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_1_3_2-solution000002.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_1_3_2-solution000003.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_1_3_2-solution000004.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_1_3_2-solution000005.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_1_3_2-solution000006.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_1_3_2.eprime.orig delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_1_3_3.eprime.orig create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_1_3_4-solution000001.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_1_3_4-solution000002.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_1_3_4-solution000003.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_1_3_4-solution000004.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_1_3_4-solution000005.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_1_3_4-solution000006.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_1_3_4.eprime.orig create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_1_4_2-solution000001.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_1_4_2-solution000002.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_1_4_2-solution000003.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_1_4_2-solution000004.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_1_4_2-solution000005.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_1_4_2-solution000006.solution rename tests/exhaustive/basic/setOfSet04/expected/{model_1_4_3.eprime.orig => model_1_4_2.eprime} (50%) create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_1_4_3-solution000001.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_1_4_3-solution000002.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_1_4_3-solution000003.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_1_4_3-solution000004.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_1_4_3-solution000005.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_1_4_3-solution000006.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_2_1_1-solution000001.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_2_1_1-solution000002.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_2_1_1-solution000003.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_2_1_1-solution000004.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_2_1_1-solution000005.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_2_1_1-solution000006.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_2_1_1.eprime create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_2_1_3-solution000001.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_2_1_3-solution000002.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_2_1_3-solution000003.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_2_1_3-solution000004.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_2_1_3-solution000005.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_2_1_3-solution000006.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_2_1_3.eprime.orig create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_2_1_4-solution000001.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_2_1_4-solution000002.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_2_1_4-solution000003.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_2_1_4-solution000004.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_2_1_4-solution000005.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_2_1_4-solution000006.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_2_1_4.eprime create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_2_2_2-solution000001.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_2_2_2-solution000002.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_2_2_2-solution000003.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_2_2_2-solution000004.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_2_2_2-solution000005.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_2_2_2-solution000006.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_2_2_2.eprime create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_2_2_3-solution000001.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_2_2_3-solution000002.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_2_2_3-solution000003.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_2_2_3-solution000004.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_2_2_3-solution000005.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_2_2_3-solution000006.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_2_2_3.eprime.orig create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_2_2_4-solution000001.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_2_2_4-solution000002.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_2_2_4-solution000003.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_2_2_4-solution000004.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_2_2_4-solution000005.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_2_2_4-solution000006.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_2_2_4.eprime create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_2_3_1-solution000001.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_2_3_1-solution000002.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_2_3_1-solution000003.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_2_3_1-solution000004.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_2_3_1-solution000005.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_2_3_1-solution000006.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_2_3_1.eprime.orig delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_2_3_2.eprime.orig delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_2_3_3.eprime.orig create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_2_3_4-solution000001.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_2_3_4-solution000002.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_2_3_4-solution000003.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_2_3_4-solution000004.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_2_3_4-solution000005.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_2_3_4-solution000006.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_2_3_4.eprime.orig create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_2_4_1-solution000001.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_2_4_1-solution000002.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_2_4_1-solution000003.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_2_4_1-solution000004.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_2_4_1-solution000005.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_2_4_1-solution000006.solution rename tests/exhaustive/basic/setOfSet04/expected/{model_2_4_3.eprime.orig => model_2_4_1.eprime} (51%) create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_2_4_3-solution000001.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_2_4_3-solution000002.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_2_4_3-solution000003.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_2_4_3-solution000004.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_2_4_3-solution000005.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_2_4_3-solution000006.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_3_1_1-solution000001.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_3_1_1-solution000002.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_3_1_1-solution000003.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_3_1_1-solution000004.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_3_1_1-solution000005.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_3_1_1-solution000006.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_3_1_1.eprime.orig create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_3_1_2-solution000001.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_3_1_2-solution000002.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_3_1_2-solution000003.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_3_1_2-solution000004.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_3_1_2-solution000005.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_3_1_2-solution000006.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_3_1_2.eprime.orig delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_3_1_3.eprime.orig create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_3_1_4-solution000001.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_3_1_4-solution000002.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_3_1_4-solution000003.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_3_1_4-solution000004.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_3_1_4-solution000005.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_3_1_4-solution000006.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_3_1_4.eprime.orig create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_3_2_1-solution000001.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_3_2_1-solution000002.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_3_2_1-solution000003.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_3_2_1-solution000004.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_3_2_1-solution000005.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_3_2_1-solution000006.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_3_2_1.eprime.orig create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_3_2_2-solution000001.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_3_2_2-solution000002.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_3_2_2-solution000003.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_3_2_2-solution000004.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_3_2_2-solution000005.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_3_2_2-solution000006.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_3_2_2.eprime.orig delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_3_2_3.eprime.orig create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_3_2_4-solution000001.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_3_2_4-solution000002.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_3_2_4-solution000003.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_3_2_4-solution000004.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_3_2_4-solution000005.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_3_2_4-solution000006.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_3_2_4.eprime.orig delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_3_3_1.eprime.orig delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_3_3_2.eprime.orig create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_3_3_3-solution000001.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_3_3_3-solution000002.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_3_3_3-solution000003.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_3_3_3-solution000004.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_3_3_3-solution000005.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_3_3_3-solution000006.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_3_3_3.eprime.orig create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_3_3_4-solution000001.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_3_3_4-solution000002.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_3_3_4-solution000003.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_3_3_4-solution000004.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_3_3_4-solution000005.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_3_3_4-solution000006.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_3_3_4.eprime.orig create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_3_4_1-solution000001.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_3_4_1-solution000002.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_3_4_1-solution000003.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_3_4_1-solution000004.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_3_4_1-solution000005.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_3_4_1-solution000006.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_3_4_1.eprime.orig create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_3_4_2-solution000001.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_3_4_2-solution000002.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_3_4_2-solution000003.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_3_4_2-solution000004.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_3_4_2-solution000005.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_3_4_2-solution000006.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_3_4_2.eprime.orig delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_3_4_3.eprime.orig delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_3_4_4.eprime.orig create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_4_1_1-solution000001.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_4_1_1-solution000002.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_4_1_1-solution000003.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_4_1_1-solution000004.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_4_1_1-solution000005.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_4_1_1-solution000006.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_4_1_1.eprime create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_4_1_2-solution000001.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_4_1_2-solution000002.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_4_1_2-solution000003.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_4_1_2-solution000004.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_4_1_2-solution000005.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_4_1_2-solution000006.solution rename tests/exhaustive/basic/setOfSet04/expected/{model_4_1_3.eprime.orig => model_4_1_2.eprime} (50%) create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_4_1_3-solution000001.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_4_1_3-solution000002.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_4_1_3-solution000003.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_4_1_3-solution000004.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_4_1_3-solution000005.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_4_1_3-solution000006.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_4_2_1-solution000001.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_4_2_1-solution000002.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_4_2_1-solution000003.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_4_2_1-solution000004.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_4_2_1-solution000005.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_4_2_1-solution000006.solution rename tests/exhaustive/basic/setOfSet04/expected/{model_4_2_3.eprime.orig => model_4_2_1.eprime} (51%) create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_4_2_2-solution000001.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_4_2_2-solution000002.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_4_2_2-solution000003.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_4_2_2-solution000004.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_4_2_2-solution000005.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_4_2_2-solution000006.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_4_2_2.eprime create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_4_2_3-solution000001.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_4_2_3-solution000002.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_4_2_3-solution000003.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_4_2_3-solution000004.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_4_2_3-solution000005.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_4_2_3-solution000006.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_4_3_1-solution000001.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_4_3_1-solution000002.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_4_3_1-solution000003.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_4_3_1-solution000004.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_4_3_1-solution000005.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_4_3_1-solution000006.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_4_3_1.eprime.orig create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_4_3_2-solution000001.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_4_3_2-solution000002.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_4_3_2-solution000003.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_4_3_2-solution000004.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_4_3_2-solution000005.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_4_3_2-solution000006.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_4_3_2.eprime.orig create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_4_3_3-solution000001.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_4_3_3-solution000002.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_4_3_3-solution000003.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_4_3_3-solution000004.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_4_3_3-solution000005.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_4_3_3-solution000006.solution delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_4_3_3.eprime.orig delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_4_3_4.eprime.orig delete mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_4_4_3.eprime.orig create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_4_4_4-solution000001.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_4_4_4-solution000002.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_4_4_4-solution000003.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_4_4_4-solution000004.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_4_4_4-solution000005.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_4_4_4-solution000006.solution create mode 100644 tests/exhaustive/basic/setOfSet04/expected/model_4_4_4.eprime create mode 100644 tests/exhaustive/basic/set_card_00/expected/model_1_1_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set_card_00/expected/model_1_1_1-solution000002.solution create mode 100644 tests/exhaustive/basic/set_card_00/expected/model_1_1_1.eprime create mode 100644 tests/exhaustive/basic/set_card_00/expected/model_1_1_2-solution000001.solution create mode 100644 tests/exhaustive/basic/set_card_00/expected/model_1_1_2-solution000002.solution create mode 100644 tests/exhaustive/basic/set_card_00/expected/model_1_1_2.eprime create mode 100644 tests/exhaustive/basic/set_card_00/expected/model_1_1_3-solution000001.solution create mode 100644 tests/exhaustive/basic/set_card_00/expected/model_1_1_3-solution000002.solution create mode 100644 tests/exhaustive/basic/set_card_00/expected/model_1_1_3.eprime create mode 100644 tests/exhaustive/basic/set_card_00/expected/model_1_1_4-solution000001.solution create mode 100644 tests/exhaustive/basic/set_card_00/expected/model_1_1_4-solution000002.solution create mode 100644 tests/exhaustive/basic/set_card_00/expected/model_1_1_4.eprime create mode 100644 tests/exhaustive/basic/set_card_00/expected/model_1_2_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set_card_00/expected/model_1_2_1-solution000002.solution create mode 100644 tests/exhaustive/basic/set_card_00/expected/model_1_2_1.eprime create mode 100644 tests/exhaustive/basic/set_card_00/expected/model_1_2_3-solution000001.solution create mode 100644 tests/exhaustive/basic/set_card_00/expected/model_1_2_3-solution000002.solution create mode 100644 tests/exhaustive/basic/set_card_00/expected/model_1_2_3.eprime create mode 100644 tests/exhaustive/basic/set_card_00/expected/model_1_2_4-solution000001.solution create mode 100644 tests/exhaustive/basic/set_card_00/expected/model_1_2_4-solution000002.solution create mode 100644 tests/exhaustive/basic/set_card_00/expected/model_1_2_4.eprime create mode 100644 tests/exhaustive/basic/set_card_00/expected/model_1_3_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set_card_00/expected/model_1_3_1-solution000002.solution create mode 100644 tests/exhaustive/basic/set_card_00/expected/model_1_3_1.eprime create mode 100644 tests/exhaustive/basic/set_card_00/expected/model_1_3_2-solution000001.solution create mode 100644 tests/exhaustive/basic/set_card_00/expected/model_1_3_2-solution000002.solution create mode 100644 tests/exhaustive/basic/set_card_00/expected/model_1_3_2.eprime create mode 100644 tests/exhaustive/basic/set_card_00/expected/model_1_3_4-solution000001.solution create mode 100644 tests/exhaustive/basic/set_card_00/expected/model_1_3_4-solution000002.solution create mode 100644 tests/exhaustive/basic/set_card_00/expected/model_1_3_4.eprime create mode 100644 tests/exhaustive/basic/set_card_00/expected/model_1_4_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set_card_00/expected/model_1_4_1-solution000002.solution create mode 100644 tests/exhaustive/basic/set_card_00/expected/model_1_4_1.eprime create mode 100644 tests/exhaustive/basic/set_card_00/expected/model_1_4_2-solution000001.solution create mode 100644 tests/exhaustive/basic/set_card_00/expected/model_1_4_2-solution000002.solution create mode 100644 tests/exhaustive/basic/set_card_00/expected/model_1_4_2.eprime create mode 100644 tests/exhaustive/basic/set_card_00/expected/model_1_4_3-solution000001.solution create mode 100644 tests/exhaustive/basic/set_card_00/expected/model_1_4_3-solution000002.solution create mode 100644 tests/exhaustive/basic/set_card_00/expected/model_1_4_3.eprime create mode 100644 tests/exhaustive/basic/set_card_00/expected/model_2_1_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set_card_00/expected/model_2_1_1-solution000002.solution create mode 100644 tests/exhaustive/basic/set_card_00/expected/model_2_1_1.eprime create mode 100644 tests/exhaustive/basic/set_card_00/expected/model_2_1_3-solution000001.solution create mode 100644 tests/exhaustive/basic/set_card_00/expected/model_2_1_3-solution000002.solution create mode 100644 tests/exhaustive/basic/set_card_00/expected/model_2_1_3.eprime create mode 100644 tests/exhaustive/basic/set_card_00/expected/model_2_1_4-solution000001.solution create mode 100644 tests/exhaustive/basic/set_card_00/expected/model_2_1_4-solution000002.solution create mode 100644 tests/exhaustive/basic/set_card_00/expected/model_2_1_4.eprime create mode 100644 tests/exhaustive/basic/set_card_00/expected/model_2_2_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set_card_00/expected/model_2_2_1-solution000002.solution create mode 100644 tests/exhaustive/basic/set_card_00/expected/model_2_2_1.eprime create mode 100644 tests/exhaustive/basic/set_card_00/expected/model_2_2_2-solution000001.solution create mode 100644 tests/exhaustive/basic/set_card_00/expected/model_2_2_2-solution000002.solution create mode 100644 tests/exhaustive/basic/set_card_00/expected/model_2_2_2.eprime create mode 100644 tests/exhaustive/basic/set_card_00/expected/model_2_2_3-solution000001.solution create mode 100644 tests/exhaustive/basic/set_card_00/expected/model_2_2_3-solution000002.solution create mode 100644 tests/exhaustive/basic/set_card_00/expected/model_2_2_3.eprime create mode 100644 tests/exhaustive/basic/set_card_00/expected/model_2_2_4-solution000001.solution create mode 100644 tests/exhaustive/basic/set_card_00/expected/model_2_2_4-solution000002.solution create mode 100644 tests/exhaustive/basic/set_card_00/expected/model_2_2_4.eprime create mode 100644 tests/exhaustive/basic/set_card_00/expected/model_2_3_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set_card_00/expected/model_2_3_1-solution000002.solution create mode 100644 tests/exhaustive/basic/set_card_00/expected/model_2_3_1.eprime create mode 100644 tests/exhaustive/basic/set_card_00/expected/model_2_3_2-solution000001.solution create mode 100644 tests/exhaustive/basic/set_card_00/expected/model_2_3_2-solution000002.solution create mode 100644 tests/exhaustive/basic/set_card_00/expected/model_2_3_2.eprime create mode 100644 tests/exhaustive/basic/set_card_00/expected/model_2_3_4-solution000001.solution create mode 100644 tests/exhaustive/basic/set_card_00/expected/model_2_3_4-solution000002.solution create mode 100644 tests/exhaustive/basic/set_card_00/expected/model_2_3_4.eprime create mode 100644 tests/exhaustive/basic/set_card_00/expected/model_2_4_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set_card_00/expected/model_2_4_1-solution000002.solution create mode 100644 tests/exhaustive/basic/set_card_00/expected/model_2_4_1.eprime create mode 100644 tests/exhaustive/basic/set_card_00/expected/model_2_4_2-solution000001.solution create mode 100644 tests/exhaustive/basic/set_card_00/expected/model_2_4_2-solution000002.solution create mode 100644 tests/exhaustive/basic/set_card_00/expected/model_2_4_2.eprime create mode 100644 tests/exhaustive/basic/set_card_00/expected/model_2_4_3-solution000001.solution create mode 100644 tests/exhaustive/basic/set_card_00/expected/model_2_4_3-solution000002.solution create mode 100644 tests/exhaustive/basic/set_card_00/expected/model_2_4_3.eprime create mode 100644 tests/exhaustive/basic/set_card_00/expected/model_3_1_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set_card_00/expected/model_3_1_1-solution000002.solution create mode 100644 tests/exhaustive/basic/set_card_00/expected/model_3_1_1.eprime create mode 100644 tests/exhaustive/basic/set_card_00/expected/model_3_1_2-solution000001.solution create mode 100644 tests/exhaustive/basic/set_card_00/expected/model_3_1_2-solution000002.solution create mode 100644 tests/exhaustive/basic/set_card_00/expected/model_3_1_2.eprime create mode 100644 tests/exhaustive/basic/set_card_00/expected/model_3_1_4-solution000001.solution create mode 100644 tests/exhaustive/basic/set_card_00/expected/model_3_1_4-solution000002.solution create mode 100644 tests/exhaustive/basic/set_card_00/expected/model_3_1_4.eprime create mode 100644 tests/exhaustive/basic/set_card_00/expected/model_3_2_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set_card_00/expected/model_3_2_1-solution000002.solution create mode 100644 tests/exhaustive/basic/set_card_00/expected/model_3_2_1.eprime create mode 100644 tests/exhaustive/basic/set_card_00/expected/model_3_2_2-solution000001.solution create mode 100644 tests/exhaustive/basic/set_card_00/expected/model_3_2_2-solution000002.solution create mode 100644 tests/exhaustive/basic/set_card_00/expected/model_3_2_2.eprime create mode 100644 tests/exhaustive/basic/set_card_00/expected/model_3_2_4-solution000001.solution create mode 100644 tests/exhaustive/basic/set_card_00/expected/model_3_2_4-solution000002.solution create mode 100644 tests/exhaustive/basic/set_card_00/expected/model_3_2_4.eprime create mode 100644 tests/exhaustive/basic/set_card_00/expected/model_3_3_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set_card_00/expected/model_3_3_1-solution000002.solution create mode 100644 tests/exhaustive/basic/set_card_00/expected/model_3_3_1.eprime create mode 100644 tests/exhaustive/basic/set_card_00/expected/model_3_3_2-solution000001.solution create mode 100644 tests/exhaustive/basic/set_card_00/expected/model_3_3_2-solution000002.solution create mode 100644 tests/exhaustive/basic/set_card_00/expected/model_3_3_2.eprime create mode 100644 tests/exhaustive/basic/set_card_00/expected/model_3_3_3-solution000001.solution create mode 100644 tests/exhaustive/basic/set_card_00/expected/model_3_3_3-solution000002.solution create mode 100644 tests/exhaustive/basic/set_card_00/expected/model_3_3_3.eprime create mode 100644 tests/exhaustive/basic/set_card_00/expected/model_3_3_4-solution000001.solution create mode 100644 tests/exhaustive/basic/set_card_00/expected/model_3_3_4-solution000002.solution create mode 100644 tests/exhaustive/basic/set_card_00/expected/model_3_3_4.eprime create mode 100644 tests/exhaustive/basic/set_card_00/expected/model_3_4_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set_card_00/expected/model_3_4_1-solution000002.solution create mode 100644 tests/exhaustive/basic/set_card_00/expected/model_3_4_1.eprime create mode 100644 tests/exhaustive/basic/set_card_00/expected/model_3_4_2-solution000001.solution create mode 100644 tests/exhaustive/basic/set_card_00/expected/model_3_4_2-solution000002.solution create mode 100644 tests/exhaustive/basic/set_card_00/expected/model_3_4_2.eprime create mode 100644 tests/exhaustive/basic/set_card_00/expected/model_3_4_3-solution000001.solution create mode 100644 tests/exhaustive/basic/set_card_00/expected/model_3_4_3-solution000002.solution create mode 100644 tests/exhaustive/basic/set_card_00/expected/model_3_4_3.eprime create mode 100644 tests/exhaustive/basic/set_card_00/expected/model_4_1_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set_card_00/expected/model_4_1_1-solution000002.solution create mode 100644 tests/exhaustive/basic/set_card_00/expected/model_4_1_1.eprime create mode 100644 tests/exhaustive/basic/set_card_00/expected/model_4_1_2-solution000001.solution create mode 100644 tests/exhaustive/basic/set_card_00/expected/model_4_1_2-solution000002.solution create mode 100644 tests/exhaustive/basic/set_card_00/expected/model_4_1_2.eprime create mode 100644 tests/exhaustive/basic/set_card_00/expected/model_4_1_3-solution000001.solution create mode 100644 tests/exhaustive/basic/set_card_00/expected/model_4_1_3-solution000002.solution create mode 100644 tests/exhaustive/basic/set_card_00/expected/model_4_1_3.eprime create mode 100644 tests/exhaustive/basic/set_card_00/expected/model_4_2_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set_card_00/expected/model_4_2_1-solution000002.solution create mode 100644 tests/exhaustive/basic/set_card_00/expected/model_4_2_1.eprime create mode 100644 tests/exhaustive/basic/set_card_00/expected/model_4_2_2-solution000001.solution create mode 100644 tests/exhaustive/basic/set_card_00/expected/model_4_2_2-solution000002.solution create mode 100644 tests/exhaustive/basic/set_card_00/expected/model_4_2_2.eprime create mode 100644 tests/exhaustive/basic/set_card_00/expected/model_4_2_3-solution000001.solution create mode 100644 tests/exhaustive/basic/set_card_00/expected/model_4_2_3-solution000002.solution create mode 100644 tests/exhaustive/basic/set_card_00/expected/model_4_2_3.eprime create mode 100644 tests/exhaustive/basic/set_card_00/expected/model_4_3_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set_card_00/expected/model_4_3_1-solution000002.solution create mode 100644 tests/exhaustive/basic/set_card_00/expected/model_4_3_1.eprime create mode 100644 tests/exhaustive/basic/set_card_00/expected/model_4_3_2-solution000001.solution create mode 100644 tests/exhaustive/basic/set_card_00/expected/model_4_3_2-solution000002.solution create mode 100644 tests/exhaustive/basic/set_card_00/expected/model_4_3_2.eprime create mode 100644 tests/exhaustive/basic/set_card_00/expected/model_4_3_3-solution000001.solution create mode 100644 tests/exhaustive/basic/set_card_00/expected/model_4_3_3-solution000002.solution create mode 100644 tests/exhaustive/basic/set_card_00/expected/model_4_3_3.eprime create mode 100644 tests/exhaustive/basic/set_card_00/expected/model_4_4_1-solution000001.solution create mode 100644 tests/exhaustive/basic/set_card_00/expected/model_4_4_1-solution000002.solution create mode 100644 tests/exhaustive/basic/set_card_00/expected/model_4_4_1.eprime create mode 100644 tests/exhaustive/basic/set_card_00/expected/model_4_4_2-solution000001.solution create mode 100644 tests/exhaustive/basic/set_card_00/expected/model_4_4_2-solution000002.solution create mode 100644 tests/exhaustive/basic/set_card_00/expected/model_4_4_2.eprime create mode 100644 tests/exhaustive/basic/set_card_00/expected/model_4_4_3-solution000001.solution create mode 100644 tests/exhaustive/basic/set_card_00/expected/model_4_4_3-solution000002.solution create mode 100644 tests/exhaustive/basic/set_card_00/expected/model_4_4_3.eprime create mode 100644 tests/exhaustive/basic/set_card_00/expected/model_4_4_4-solution000001.solution create mode 100644 tests/exhaustive/basic/set_card_00/expected/model_4_4_4-solution000002.solution create mode 100644 tests/exhaustive/basic/set_card_00/expected/model_4_4_4.eprime delete mode 100644 tests/exhaustive/basic/set_card_02/expected/model_1_2_2.eprime delete mode 100644 tests/exhaustive/basic/set_card_02/expected/model_2_1_2.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_1_1_1-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_1_1_1-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_1_1_1-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_1_1_1.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_1_1_2-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_1_1_2-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_1_1_2-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_1_1_2.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_1_1_3-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_1_1_3-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_1_1_3-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_1_1_3.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_1_1_4-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_1_1_4-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_1_1_4-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_1_1_4.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_1_2_1-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_1_2_1-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_1_2_1-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_1_2_1.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_1_2_2-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_1_2_2-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_1_2_2-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_1_2_2.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_1_2_3-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_1_2_3-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_1_2_3-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_1_2_3.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_1_2_4-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_1_2_4-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_1_2_4-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_1_2_4.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_1_3_1-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_1_3_1-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_1_3_1-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_1_3_1.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_1_3_2-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_1_3_2-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_1_3_2-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_1_3_2.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_1_3_3-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_1_3_3-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_1_3_3-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_1_3_3.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_1_3_4-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_1_3_4-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_1_3_4-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_1_3_4.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_1_4_1-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_1_4_1-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_1_4_1-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_1_4_1.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_1_4_2-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_1_4_2-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_1_4_2-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_1_4_2.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_1_4_3-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_1_4_3-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_1_4_3-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_1_4_3.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_1_4_4-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_1_4_4-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_1_4_4-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_1_4_4.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_2_1_1-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_2_1_1-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_2_1_1-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_2_1_1.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_2_1_2-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_2_1_2-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_2_1_2-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_2_1_2.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_2_1_3-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_2_1_3-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_2_1_3-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_2_1_3.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_2_1_4-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_2_1_4-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_2_1_4-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_2_1_4.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_2_2_1-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_2_2_1-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_2_2_1-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_2_2_1.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_2_2_2-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_2_2_2-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_2_2_2-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_2_2_2.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_2_2_3-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_2_2_3-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_2_2_3-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_2_2_3.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_2_2_4-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_2_2_4-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_2_2_4-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_2_2_4.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_2_3_1-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_2_3_1-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_2_3_1-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_2_3_1.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_2_3_2-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_2_3_2-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_2_3_2-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_2_3_2.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_2_3_3-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_2_3_3-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_2_3_3-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_2_3_3.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_2_3_4-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_2_3_4-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_2_3_4-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_2_3_4.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_2_4_1-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_2_4_1-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_2_4_1-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_2_4_1.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_2_4_2-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_2_4_2-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_2_4_2-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_2_4_2.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_2_4_3-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_2_4_3-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_2_4_3-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_2_4_3.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_2_4_4-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_2_4_4-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_2_4_4-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_2_4_4.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_3_1_1-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_3_1_1-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_3_1_1-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_3_1_1.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_3_1_2-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_3_1_2-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_3_1_2-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_3_1_2.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_3_1_3-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_3_1_3-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_3_1_3-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_3_1_3.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_3_1_4-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_3_1_4-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_3_1_4-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_3_1_4.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_3_2_1-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_3_2_1-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_3_2_1-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_3_2_1.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_3_2_2-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_3_2_2-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_3_2_2-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_3_2_2.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_3_2_3-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_3_2_3-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_3_2_3-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_3_2_3.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_3_2_4-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_3_2_4-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_3_2_4-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_3_2_4.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_3_3_1-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_3_3_1-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_3_3_1-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_3_3_1.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_3_3_2-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_3_3_2-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_3_3_2-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_3_3_2.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_3_3_3-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_3_3_3-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_3_3_3-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_3_3_3.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_3_3_4-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_3_3_4-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_3_3_4-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_3_3_4.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_3_4_1-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_3_4_1-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_3_4_1-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_3_4_1.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_3_4_2-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_3_4_2-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_3_4_2-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_3_4_2.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_3_4_3-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_3_4_3-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_3_4_3-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_3_4_3.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_3_4_4-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_3_4_4-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_3_4_4-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_3_4_4.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_4_1_1-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_4_1_1-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_4_1_1-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_4_1_1.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_4_1_2-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_4_1_2-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_4_1_2-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_4_1_2.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_4_1_3-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_4_1_3-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_4_1_3-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_4_1_3.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_4_1_4-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_4_1_4-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_4_1_4-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_4_1_4.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_4_2_1-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_4_2_1-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_4_2_1-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_4_2_1.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_4_2_2-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_4_2_2-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_4_2_2-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_4_2_2.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_4_2_3-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_4_2_3-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_4_2_3-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_4_2_3.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_4_2_4-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_4_2_4-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_4_2_4-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_4_2_4.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_4_3_1-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_4_3_1-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_4_3_1-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_4_3_1.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_4_3_2-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_4_3_2-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_4_3_2-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_4_3_2.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_4_3_3-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_4_3_3-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_4_3_3-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_4_3_3.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_4_3_4-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_4_3_4-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_4_3_4-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_4_3_4.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_4_4_1-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_4_4_1-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_4_4_1-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_4_4_1.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_4_4_2-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_4_4_2-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_4_4_2-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_4_4_2.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_4_4_3-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_4_4_3-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_4_4_3-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_4_4_3.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_4_4_4-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_4_4_4-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_4_4_4-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_1_4_4_4.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_1_1_1-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_1_1_1-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_1_1_1-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_1_1_1.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_1_1_2-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_1_1_2-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_1_1_2-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_1_1_2.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_1_1_3-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_1_1_3-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_1_1_3-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_1_1_3.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_1_1_4-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_1_1_4-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_1_1_4-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_1_1_4.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_1_2_1-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_1_2_1-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_1_2_1-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_1_2_1.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_1_2_2-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_1_2_2-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_1_2_2-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_1_2_2.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_1_2_3-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_1_2_3-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_1_2_3-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_1_2_3.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_1_2_4-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_1_2_4-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_1_2_4-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_1_2_4.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_1_3_1-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_1_3_1-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_1_3_1-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_1_3_1.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_1_3_2-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_1_3_2-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_1_3_2-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_1_3_2.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_1_3_3-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_1_3_3-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_1_3_3-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_1_3_3.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_1_3_4-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_1_3_4-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_1_3_4-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_1_3_4.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_1_4_1-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_1_4_1-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_1_4_1-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_1_4_1.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_1_4_2-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_1_4_2-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_1_4_2-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_1_4_2.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_1_4_3-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_1_4_3-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_1_4_3-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_1_4_3.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_1_4_4-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_1_4_4-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_1_4_4-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_1_4_4.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_2_1_1-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_2_1_1-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_2_1_1-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_2_1_1.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_2_1_2-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_2_1_2-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_2_1_2-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_2_1_2.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_2_1_3-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_2_1_3-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_2_1_3-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_2_1_3.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_2_1_4-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_2_1_4-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_2_1_4-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_2_1_4.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_2_2_1-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_2_2_1-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_2_2_1-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_2_2_1.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_2_2_2-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_2_2_2-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_2_2_2-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_2_2_2.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_2_2_3-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_2_2_3-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_2_2_3-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_2_2_3.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_2_2_4-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_2_2_4-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_2_2_4-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_2_2_4.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_2_3_1-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_2_3_1-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_2_3_1-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_2_3_1.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_2_3_2-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_2_3_2-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_2_3_2-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_2_3_2.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_2_3_3-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_2_3_3-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_2_3_3-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_2_3_3.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_2_3_4-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_2_3_4-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_2_3_4-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_2_3_4.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_2_4_1-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_2_4_1-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_2_4_1-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_2_4_1.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_2_4_2-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_2_4_2-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_2_4_2-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_2_4_2.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_2_4_3-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_2_4_3-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_2_4_3-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_2_4_3.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_2_4_4-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_2_4_4-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_2_4_4-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_2_4_4.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_3_1_1-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_3_1_1-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_3_1_1-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_3_1_1.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_3_1_2-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_3_1_2-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_3_1_2-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_3_1_2.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_3_1_3-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_3_1_3-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_3_1_3-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_3_1_3.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_3_1_4-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_3_1_4-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_3_1_4-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_3_1_4.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_3_2_1-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_3_2_1-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_3_2_1-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_3_2_1.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_3_2_2-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_3_2_2-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_3_2_2-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_3_2_2.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_3_2_3-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_3_2_3-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_3_2_3-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_3_2_3.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_3_2_4-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_3_2_4-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_3_2_4-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_3_2_4.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_3_3_1-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_3_3_1-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_3_3_1-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_3_3_1.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_3_3_2-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_3_3_2-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_3_3_2-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_3_3_2.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_3_3_3-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_3_3_3-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_3_3_3-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_3_3_3.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_3_3_4-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_3_3_4-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_3_3_4-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_3_3_4.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_3_4_1-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_3_4_1-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_3_4_1-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_3_4_1.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_3_4_2-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_3_4_2-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_3_4_2-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_3_4_2.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_3_4_3-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_3_4_3-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_3_4_3-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_3_4_3.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_3_4_4-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_3_4_4-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_3_4_4-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_3_4_4.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_4_1_1-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_4_1_1-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_4_1_1-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_4_1_1.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_4_1_2-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_4_1_2-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_4_1_2-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_4_1_2.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_4_1_3-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_4_1_3-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_4_1_3-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_4_1_3.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_4_1_4-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_4_1_4-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_4_1_4-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_4_1_4.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_4_2_1-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_4_2_1-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_4_2_1-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_4_2_1.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_4_2_2-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_4_2_2-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_4_2_2-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_4_2_2.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_4_2_3-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_4_2_3-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_4_2_3-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_4_2_3.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_4_2_4-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_4_2_4-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_4_2_4-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_4_2_4.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_4_3_1-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_4_3_1-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_4_3_1-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_4_3_1.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_4_3_2-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_4_3_2-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_4_3_2-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_4_3_2.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_4_3_3-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_4_3_3-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_4_3_3-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_4_3_3.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_4_3_4-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_4_3_4-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_4_3_4-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_4_3_4.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_4_4_1-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_4_4_1-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_4_4_1-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_4_4_1.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_4_4_2-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_4_4_2-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_4_4_2-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_4_4_2.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_4_4_3-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_4_4_3-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_4_4_3-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_4_4_3.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_4_4_4-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_4_4_4-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_4_4_4-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_2_4_4_4.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_1_1_1-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_1_1_1-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_1_1_1-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_1_1_1.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_1_1_2-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_1_1_2-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_1_1_2-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_1_1_2.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_1_1_3-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_1_1_3-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_1_1_3-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_1_1_3.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_1_1_4-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_1_1_4-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_1_1_4-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_1_1_4.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_1_2_1-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_1_2_1-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_1_2_1-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_1_2_1.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_1_2_2-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_1_2_2-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_1_2_2-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_1_2_2.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_1_2_3-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_1_2_3-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_1_2_3-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_1_2_3.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_1_2_4-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_1_2_4-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_1_2_4-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_1_2_4.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_1_3_1-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_1_3_1-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_1_3_1-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_1_3_1.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_1_3_2-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_1_3_2-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_1_3_2-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_1_3_2.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_1_3_3-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_1_3_3-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_1_3_3-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_1_3_3.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_1_3_4-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_1_3_4-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_1_3_4-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_1_3_4.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_1_4_1-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_1_4_1-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_1_4_1-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_1_4_1.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_1_4_2-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_1_4_2-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_1_4_2-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_1_4_2.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_1_4_3-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_1_4_3-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_1_4_3-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_1_4_3.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_1_4_4-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_1_4_4-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_1_4_4-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_1_4_4.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_2_1_1-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_2_1_1-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_2_1_1-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_2_1_1.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_2_1_2-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_2_1_2-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_2_1_2-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_2_1_2.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_2_1_3-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_2_1_3-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_2_1_3-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_2_1_3.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_2_1_4-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_2_1_4-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_2_1_4-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_2_1_4.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_2_2_1-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_2_2_1-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_2_2_1-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_2_2_1.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_2_2_2-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_2_2_2-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_2_2_2-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_2_2_2.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_2_2_3-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_2_2_3-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_2_2_3-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_2_2_3.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_2_2_4-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_2_2_4-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_2_2_4-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_2_2_4.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_2_3_1-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_2_3_1-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_2_3_1-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_2_3_1.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_2_3_2-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_2_3_2-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_2_3_2-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_2_3_2.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_2_3_3-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_2_3_3-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_2_3_3-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_2_3_3.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_2_3_4-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_2_3_4-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_2_3_4-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_2_3_4.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_2_4_1-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_2_4_1-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_2_4_1-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_2_4_1.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_2_4_2-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_2_4_2-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_2_4_2-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_2_4_2.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_2_4_3-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_2_4_3-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_2_4_3-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_2_4_3.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_2_4_4-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_2_4_4-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_2_4_4-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_2_4_4.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_3_1_1-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_3_1_1-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_3_1_1-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_3_1_1.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_3_1_2-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_3_1_2-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_3_1_2-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_3_1_2.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_3_1_3-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_3_1_3-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_3_1_3-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_3_1_3.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_3_1_4-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_3_1_4-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_3_1_4-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_3_1_4.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_3_2_1-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_3_2_1-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_3_2_1-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_3_2_1.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_3_2_2-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_3_2_2-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_3_2_2-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_3_2_2.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_3_2_3-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_3_2_3-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_3_2_3-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_3_2_3.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_3_2_4-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_3_2_4-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_3_2_4-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_3_2_4.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_3_3_1-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_3_3_1-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_3_3_1-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_3_3_1.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_3_3_2-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_3_3_2-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_3_3_2-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_3_3_2.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_3_3_3-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_3_3_3-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_3_3_3-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_3_3_3.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_3_3_4-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_3_3_4-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_3_3_4-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_3_3_4.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_3_4_1-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_3_4_1-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_3_4_1-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_3_4_1.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_3_4_2-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_3_4_2-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_3_4_2-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_3_4_2.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_3_4_3-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_3_4_3-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_3_4_3-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_3_4_3.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_3_4_4-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_3_4_4-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_3_4_4-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_3_4_4.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_4_1_1-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_4_1_1-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_4_1_1-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_4_1_1.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_4_1_2-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_4_1_2-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_4_1_2-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_4_1_2.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_4_1_3-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_4_1_3-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_4_1_3-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_4_1_3.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_4_1_4-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_4_1_4-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_4_1_4-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_4_1_4.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_4_2_1-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_4_2_1-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_4_2_1-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_4_2_1.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_4_2_2-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_4_2_2-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_4_2_2-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_4_2_2.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_4_2_3-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_4_2_3-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_4_2_3-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_4_2_3.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_4_2_4-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_4_2_4-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_4_2_4-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_4_2_4.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_4_3_1-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_4_3_1-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_4_3_1-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_4_3_1.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_4_3_2-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_4_3_2-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_4_3_2-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_4_3_2.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_4_3_3-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_4_3_3-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_4_3_3-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_4_3_3.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_4_3_4-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_4_3_4-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_4_3_4-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_4_3_4.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_4_4_1-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_4_4_1-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_4_4_1-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_4_4_1.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_4_4_2-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_4_4_2-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_4_4_2-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_4_4_2.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_4_4_3-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_4_4_3-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_4_4_3-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_4_4_3.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_4_4_4-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_4_4_4-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_4_4_4-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_3_4_4_4.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_1_1_1-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_1_1_1-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_1_1_1-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_1_1_1.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_1_1_2-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_1_1_2-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_1_1_2-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_1_1_2.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_1_1_3-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_1_1_3-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_1_1_3-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_1_1_3.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_1_1_4-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_1_1_4-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_1_1_4-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_1_1_4.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_1_2_1-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_1_2_1-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_1_2_1-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_1_2_1.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_1_2_2-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_1_2_2-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_1_2_2-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_1_2_2.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_1_2_3-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_1_2_3-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_1_2_3-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_1_2_3.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_1_2_4-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_1_2_4-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_1_2_4-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_1_2_4.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_1_3_1-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_1_3_1-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_1_3_1-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_1_3_1.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_1_3_2-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_1_3_2-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_1_3_2-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_1_3_2.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_1_3_3-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_1_3_3-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_1_3_3-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_1_3_3.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_1_3_4-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_1_3_4-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_1_3_4-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_1_3_4.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_1_4_1-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_1_4_1-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_1_4_1-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_1_4_1.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_1_4_2-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_1_4_2-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_1_4_2-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_1_4_2.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_1_4_3-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_1_4_3-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_1_4_3-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_1_4_3.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_1_4_4-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_1_4_4-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_1_4_4-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_1_4_4.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_2_1_1-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_2_1_1-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_2_1_1-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_2_1_1.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_2_1_2-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_2_1_2-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_2_1_2-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_2_1_2.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_2_1_3-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_2_1_3-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_2_1_3-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_2_1_3.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_2_1_4-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_2_1_4-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_2_1_4-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_2_1_4.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_2_2_1-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_2_2_1-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_2_2_1-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_2_2_1.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_2_2_2-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_2_2_2-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_2_2_2-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_2_2_2.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_2_2_3-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_2_2_3-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_2_2_3-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_2_2_3.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_2_2_4-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_2_2_4-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_2_2_4-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_2_2_4.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_2_3_1-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_2_3_1-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_2_3_1-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_2_3_1.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_2_3_2-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_2_3_2-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_2_3_2-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_2_3_2.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_2_3_3-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_2_3_3-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_2_3_3-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_2_3_3.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_2_3_4-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_2_3_4-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_2_3_4-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_2_3_4.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_2_4_1-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_2_4_1-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_2_4_1-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_2_4_1.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_2_4_2-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_2_4_2-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_2_4_2-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_2_4_2.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_2_4_3-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_2_4_3-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_2_4_3-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_2_4_3.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_2_4_4-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_2_4_4-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_2_4_4-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_2_4_4.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_3_1_1-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_3_1_1-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_3_1_1-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_3_1_1.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_3_1_2-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_3_1_2-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_3_1_2-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_3_1_2.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_3_1_3-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_3_1_3-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_3_1_3-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_3_1_3.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_3_1_4-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_3_1_4-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_3_1_4-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_3_1_4.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_3_2_1-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_3_2_1-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_3_2_1-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_3_2_1.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_3_2_2-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_3_2_2-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_3_2_2-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_3_2_2.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_3_2_3-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_3_2_3-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_3_2_3-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_3_2_3.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_3_2_4-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_3_2_4-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_3_2_4-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_3_2_4.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_3_3_1-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_3_3_1-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_3_3_1-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_3_3_1.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_3_3_2-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_3_3_2-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_3_3_2-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_3_3_2.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_3_3_3-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_3_3_3-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_3_3_3-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_3_3_3.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_3_3_4-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_3_3_4-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_3_3_4-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_3_3_4.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_3_4_1-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_3_4_1-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_3_4_1-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_3_4_1.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_3_4_2-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_3_4_2-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_3_4_2-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_3_4_2.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_3_4_3-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_3_4_3-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_3_4_3-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_3_4_3.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_3_4_4-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_3_4_4-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_3_4_4-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_3_4_4.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_4_1_1-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_4_1_1-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_4_1_1-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_4_1_1.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_4_1_2-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_4_1_2-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_4_1_2-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_4_1_2.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_4_1_3-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_4_1_3-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_4_1_3-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_4_1_3.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_4_1_4-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_4_1_4-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_4_1_4-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_4_1_4.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_4_2_1-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_4_2_1-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_4_2_1-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_4_2_1.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_4_2_2-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_4_2_2-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_4_2_2-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_4_2_2.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_4_2_3-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_4_2_3-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_4_2_3-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_4_2_3.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_4_2_4-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_4_2_4-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_4_2_4-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_4_2_4.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_4_3_1-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_4_3_1-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_4_3_1-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_4_3_1.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_4_3_2-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_4_3_2-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_4_3_2-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_4_3_2.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_4_3_3-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_4_3_3-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_4_3_3-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_4_3_3.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_4_3_4-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_4_3_4-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_4_3_4-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_4_3_4.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_4_4_1-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_4_4_1-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_4_4_1-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_4_4_1.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_4_4_2-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_4_4_2-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_4_4_2-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_4_4_2.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_4_4_3-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_4_4_3-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_4_4_3-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_4_4_3.eprime create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_4_4_4-solution000001.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_4_4_4-solution000002.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_4_4_4-solution000003.solution create mode 100644 tests/exhaustive/basic/typed01/expected/model_4_4_4_4.eprime diff --git a/docs/conjure-help.html b/docs/conjure-help.html index 4063fbd402..c5b17a7b79 100644 --- a/docs/conjure-help.html +++ b/docs/conjure-help.html @@ -40,11 +40,8 @@  --representations-cuts=STRATEGYStrategy for choosing a representation for cuts in 'branching on'.
Default value: same as --representations  --channellingWhether to produce channelled models (true by default).
 --representation-levelsWhether to use built-in precedence levels when choosing representations. Used to cut down the number of generated models.
Default: true -<<<<<<< HEAD  --unnamed-symmetry-breaking=ITEMLevel to use for breaking symmetries arising from unnamed types. Options: none / fast-consecutive / fast-allpairs / complete-independently / complete.
Default: none -=======  --follow-model=ITEMProvide a Conjure-generated Essence Prime model to be used as a guide during model generation. Conjure will try to imitate the modelling decisions from this file. ->>>>>>> main  --seed=INTRandom number generator seed.  --limit-models=INTMaximum number of models to generate.  --choices=FILEChoices to use for -al, either an eprime file (created by --log-choices), or a json file. @@ -134,11 +131,8 @@  --representations-cuts=STRATEGYStrategy for choosing a representation for cuts in 'branching on'.
Default value: same as --representations  --channellingWhether to produce channelled models (true by default).
 --representation-levelsWhether to use built-in precedence levels when choosing representations. Used to cut down the number of generated models.
Default: true -<<<<<<< HEAD  --unnamed-symmetry-breaking=ITEMLevel to use for breaking symmetries arising from unnamed types. Options: none / fast-consecutive / fast-allpairs / complete-independently / complete.
Default: none -=======  --follow-model=ITEMProvide a Conjure-generated Essence Prime model to be used as a guide during model generation. Conjure will try to imitate the modelling decisions from this file. ->>>>>>> main  --seed=INTRandom number generator seed.  --limit-models=INTMaximum number of models to generate.  --use-existing-models=FILEFile names of Essence' models generated beforehand.
If given, Conjure skips the modelling phase and uses the existing models for solving.
The models should be inside the output directory (See -o). diff --git a/docs/conjure-help.txt b/docs/conjure-help.txt index 60018ac460..bf34cb8af9 100644 --- a/docs/conjure-help.txt +++ b/docs/conjure-help.txt @@ -80,16 +80,13 @@ --representation-levels Whether to use built-in precedence levels when choosing representations. Used to cut down the number of generated models. Default: true -<<<<<<< HEAD --unnamed-symmetry-breaking=ITEM Level to use for breaking symmetries arising from unnamed types. Options: none / fast-consecutive / fast-allpairs / complete-independently / complete. Default: none -======= --follow-model=ITEM Provide a Conjure-generated Essence Prime model to be used as a guide during model generation. Conjure will try to imitate the modelling decisions from this file. ->>>>>>> main --seed=INT Random number generator seed. --limit-models=INT Maximum number of models to generate. --choices=FILE Choices to use for -al, either an eprime file (created by @@ -259,16 +256,13 @@ --representation-levels Whether to use built-in precedence levels when choosing representations. Used to cut down the number of generated models. Default: true -<<<<<<< HEAD --unnamed-symmetry-breaking=ITEM Level to use for breaking symmetries arising from unnamed types. Options: none / fast-consecutive / fast-allpairs / complete-independently / complete. Default: none -======= --follow-model=ITEM Provide a Conjure-generated Essence Prime model to be used as a guide during model generation. Conjure will try to imitate the modelling decisions from this file. ->>>>>>> main --seed=INT Random number generator seed. --limit-models=INT Maximum number of models to generate. --use-existing-models=FILE File names of Essence' models generated beforehand. diff --git a/src/Conjure/Compute/DomainOf.hs.orig b/src/Conjure/Compute/DomainOf.hs.orig deleted file mode 100644 index f8f435e242..0000000000 --- a/src/Conjure/Compute/DomainOf.hs.orig +++ /dev/null @@ -1,668 +0,0 @@ -{-# LANGUAGE QuasiQuotes #-} -{-# LANGUAGE UndecidableInstances #-} - -module Conjure.Compute.DomainOf ( DomainOf(..), domainOfR ) where - --- conjure -import Conjure.Prelude -import Conjure.Bug - -import Conjure.Language -import Conjure.Language.Domain ( HasRepresentation(..) ) -import Conjure.Language.RepresentationOf ( RepresentationOf(..) ) -import Conjure.Compute.DomainUnion - - -type Dom = Domain () Expression - -class DomainOf a where - - -- | calculate the domain of `a` - domainOf :: - MonadFail m => - NameGen m => - (?typeCheckerMode :: TypeCheckerMode) => - a -> m Dom - - -- | calculate the index domains of `a` - -- the index is the index of a matrix. - -- returns [] for non-matrix inputs. - -- has a default implementation in terms of domainOf, so doesn't need to be implemented specifically. - -- but sometimes it is better to implement this directly. - indexDomainsOf :: - MonadFail m => - NameGen m => - Pretty a => - (?typeCheckerMode :: TypeCheckerMode) => - a -> m [Dom] - indexDomainsOf = defIndexDomainsOf - - -domainOfR :: - DomainOf a => - RepresentationOf a => - MonadFail m => - NameGen m => - (?typeCheckerMode :: TypeCheckerMode) => - a -> m (Domain HasRepresentation Expression) -domainOfR inp = do - dom <- domainOf inp - rTree <- representationTreeOf inp - applyReprTree dom rTree - - -defIndexDomainsOf :: - MonadFail m => - NameGen m => - DomainOf a => - (?typeCheckerMode :: TypeCheckerMode) => - a -> m [Dom] -defIndexDomainsOf x = do - dom <- domainOf x - let - collect (DomainMatrix index inner) = index : collect inner - collect _ = [] - return (collect dom) - -instance DomainOf ReferenceTo where - domainOf (Alias x) = domainOf x - domainOf (InComprehension (GenDomainNoRepr Single{} dom)) = return dom - domainOf (InComprehension (GenDomainHasRepr _ dom)) = return (forgetRepr dom) - domainOf (InComprehension (GenInExpr Single{} x)) = domainOf x >>= innerDomainOf - domainOf x@InComprehension{} = fail $ vcat [ "domainOf-ReferenceTo-InComprehension", pretty x, pretty (show x) ] - domainOf (DeclNoRepr _ _ dom _) = return dom - domainOf (DeclHasRepr _ _ dom ) = return (forgetRepr dom) - domainOf RecordField{} = fail "domainOf-ReferenceTo-RecordField" - domainOf VariantField{} = fail "domainOf-ReferenceTo-VariantField" - - -instance DomainOf Expression where - domainOf (Reference _ (Just refTo)) = domainOf refTo - domainOf (Constant x) = domainOf x - domainOf (AbstractLiteral x) = domainOf x - domainOf (Op x) = domainOf x - domainOf (WithLocals h _) = domainOf h - domainOf x = fail ("domainOf{Expression}:" <+> pretty (show x)) - - -- if an empty matrix literal has a type annotation - indexDomainsOf (Typed lit ty) | emptyCollectionX lit = - let - tyToDom (TypeMatrix (TypeInt nm) t) = DomainInt nm [RangeBounded 1 0] : tyToDom t - tyToDom _ = [] - in - return (tyToDom ty) - - indexDomainsOf (Reference _ (Just refTo)) = indexDomainsOf refTo - indexDomainsOf (Constant x) = indexDomainsOf x - indexDomainsOf (AbstractLiteral x) = indexDomainsOf x - indexDomainsOf (Op x) = indexDomainsOf x - indexDomainsOf (WithLocals h _) = indexDomainsOf h - indexDomainsOf x = fail ("indexDomainsOf{Expression}:" <+> pretty (show x)) - --- this should be better implemented by some ghc-generics magic -instance (DomainOf x, TypeOf x, Pretty x, ExpressionLike x, Domain () x :< x, Dom :< x) => DomainOf (Op x) where - domainOf (MkOpActive x) = domainOf x - domainOf (MkOpAllDiff x) = domainOf x - domainOf (MkOpAllDiffExcept x) = domainOf x - domainOf (MkOpAnd x) = domainOf x - domainOf (MkOpApart x) = domainOf x - domainOf (MkOpCompose x) = domainOf x - domainOf (MkOpAttributeAsConstraint x) = domainOf x - domainOf (MkOpCatchUndef x) = domainOf x - domainOf (MkOpDefined x) = domainOf x - domainOf (MkOpDiv x) = domainOf x - domainOf (MkOpDontCare x) = domainOf x - domainOf (MkOpDotLeq x) = domainOf x - domainOf (MkOpDotLt x) = domainOf x - domainOf (MkOpEq x) = domainOf x - domainOf (MkOpFactorial x) = domainOf x - domainOf (MkOpFlatten x) = domainOf x - domainOf (MkOpFreq x) = domainOf x - domainOf (MkOpGeq x) = domainOf x - domainOf (MkOpGt x) = domainOf x - domainOf (MkOpHist x) = domainOf x - domainOf (MkOpIff x) = domainOf x - domainOf (MkOpImage x) = domainOf x - domainOf (MkOpImageSet x) = domainOf x - domainOf (MkOpImply x) = domainOf x - domainOf (MkOpIn x) = domainOf x - domainOf (MkOpIndexing x) = domainOf x - domainOf (MkOpIntersect x) = domainOf x - domainOf (MkOpInverse x) = domainOf x - domainOf (MkOpLeq x) = domainOf x - domainOf (MkOpLexLeq x) = domainOf x - domainOf (MkOpLexLt x) = domainOf x - domainOf (MkOpLt x) = domainOf x - domainOf (MkOpMax x) = domainOf x - domainOf (MkOpMin x) = domainOf x - domainOf (MkOpMinus x) = domainOf x - domainOf (MkOpMod x) = domainOf x - domainOf (MkOpNegate x) = domainOf x - domainOf (MkOpNeq x) = domainOf x - domainOf (MkOpNot x) = domainOf x - domainOf (MkOpOr x) = domainOf x - domainOf (MkOpParticipants x) = domainOf x - domainOf (MkOpParts x) = domainOf x - domainOf (MkOpParty x) = domainOf x - domainOf (MkOpPow x) = domainOf x - domainOf (MkOpPowerSet x) = domainOf x - domainOf (MkOpPred x) = domainOf x - domainOf (MkOpPreImage x) = domainOf x - domainOf (MkOpProduct x) = domainOf x - domainOf (MkOpRange x) = domainOf x - domainOf (MkOpRelationProj x) = domainOf x - domainOf (MkOpRestrict x) = domainOf x - domainOf (MkOpSlicing x) = domainOf x - domainOf (MkOpSubsequence x) = domainOf x - domainOf (MkOpSubset x) = domainOf x - domainOf (MkOpSubsetEq x) = domainOf x - domainOf (MkOpSubstring x) = domainOf x - domainOf (MkOpSucc x) = domainOf x - domainOf (MkOpSum x) = domainOf x - domainOf (MkOpSupset x) = domainOf x - domainOf (MkOpSupsetEq x) = domainOf x - domainOf (MkOpTildeLeq x) = domainOf x - domainOf (MkOpTildeLt x) = domainOf x - domainOf (MkOpTogether x) = domainOf x - domainOf (MkOpToInt x) = domainOf x - domainOf (MkOpToMSet x) = domainOf x - domainOf (MkOpToRelation x) = domainOf x - domainOf (MkOpToSet x) = domainOf x - domainOf (MkOpTransform x) = domainOf x - domainOf (MkOpTrue x) = domainOf x - domainOf (MkOpTwoBars x) = domainOf x - domainOf (MkOpUnion x) = domainOf x - domainOf (MkOpXor x) = domainOf x - - indexDomainsOf (MkOpActive x) = indexDomainsOf x - indexDomainsOf (MkOpAllDiff x) = indexDomainsOf x - indexDomainsOf (MkOpAllDiffExcept x) = indexDomainsOf x - indexDomainsOf (MkOpAnd x) = indexDomainsOf x - indexDomainsOf (MkOpApart x) = indexDomainsOf x - indexDomainsOf (MkOpCompose x) = indexDomainsOf x - indexDomainsOf (MkOpAttributeAsConstraint x) = indexDomainsOf x - indexDomainsOf (MkOpCatchUndef x) = indexDomainsOf x - indexDomainsOf (MkOpDefined x) = indexDomainsOf x - indexDomainsOf (MkOpDiv x) = indexDomainsOf x - indexDomainsOf (MkOpDontCare x) = indexDomainsOf x - indexDomainsOf (MkOpDotLeq x) = indexDomainsOf x - indexDomainsOf (MkOpDotLt x) = indexDomainsOf x - indexDomainsOf (MkOpEq x) = indexDomainsOf x - indexDomainsOf (MkOpFactorial x) = indexDomainsOf x - indexDomainsOf (MkOpFlatten x) = indexDomainsOf x - indexDomainsOf (MkOpFreq x) = indexDomainsOf x - indexDomainsOf (MkOpGeq x) = indexDomainsOf x - indexDomainsOf (MkOpGt x) = indexDomainsOf x - indexDomainsOf (MkOpHist x) = indexDomainsOf x - indexDomainsOf (MkOpIff x) = indexDomainsOf x - indexDomainsOf (MkOpImage x) = indexDomainsOf x - indexDomainsOf (MkOpImageSet x) = indexDomainsOf x - indexDomainsOf (MkOpImply x) = indexDomainsOf x - indexDomainsOf (MkOpIn x) = indexDomainsOf x - indexDomainsOf (MkOpIndexing x) = indexDomainsOf x - indexDomainsOf (MkOpIntersect x) = indexDomainsOf x - indexDomainsOf (MkOpInverse x) = indexDomainsOf x - indexDomainsOf (MkOpLeq x) = indexDomainsOf x - indexDomainsOf (MkOpLexLeq x) = indexDomainsOf x - indexDomainsOf (MkOpLexLt x) = indexDomainsOf x - indexDomainsOf (MkOpLt x) = indexDomainsOf x - indexDomainsOf (MkOpMax x) = indexDomainsOf x - indexDomainsOf (MkOpMin x) = indexDomainsOf x - indexDomainsOf (MkOpMinus x) = indexDomainsOf x - indexDomainsOf (MkOpMod x) = indexDomainsOf x - indexDomainsOf (MkOpNegate x) = indexDomainsOf x - indexDomainsOf (MkOpNeq x) = indexDomainsOf x - indexDomainsOf (MkOpNot x) = indexDomainsOf x - indexDomainsOf (MkOpOr x) = indexDomainsOf x - indexDomainsOf (MkOpParticipants x) = indexDomainsOf x - indexDomainsOf (MkOpParts x) = indexDomainsOf x - indexDomainsOf (MkOpParty x) = indexDomainsOf x - indexDomainsOf (MkOpPow x) = indexDomainsOf x - indexDomainsOf (MkOpPowerSet x) = indexDomainsOf x - indexDomainsOf (MkOpPred x) = indexDomainsOf x - indexDomainsOf (MkOpPreImage x) = indexDomainsOf x - indexDomainsOf (MkOpProduct x) = indexDomainsOf x - indexDomainsOf (MkOpRange x) = indexDomainsOf x - indexDomainsOf (MkOpRelationProj x) = indexDomainsOf x - indexDomainsOf (MkOpRestrict x) = indexDomainsOf x - indexDomainsOf (MkOpSlicing x) = indexDomainsOf x - indexDomainsOf (MkOpSubsequence x) = indexDomainsOf x - indexDomainsOf (MkOpSubset x) = indexDomainsOf x - indexDomainsOf (MkOpSubsetEq x) = indexDomainsOf x - indexDomainsOf (MkOpSubstring x) = indexDomainsOf x - indexDomainsOf (MkOpSucc x) = indexDomainsOf x - indexDomainsOf (MkOpSum x) = indexDomainsOf x - indexDomainsOf (MkOpSupset x) = indexDomainsOf x - indexDomainsOf (MkOpSupsetEq x) = indexDomainsOf x - indexDomainsOf (MkOpTildeLeq x) = indexDomainsOf x - indexDomainsOf (MkOpTildeLt x) = indexDomainsOf x - indexDomainsOf (MkOpTogether x) = indexDomainsOf x - indexDomainsOf (MkOpToInt x) = indexDomainsOf x - indexDomainsOf (MkOpToMSet x) = indexDomainsOf x - indexDomainsOf (MkOpToRelation x) = indexDomainsOf x - indexDomainsOf (MkOpToSet x) = indexDomainsOf x - indexDomainsOf (MkOpTransform (OpTransform _ x)) = indexDomainsOf x - indexDomainsOf (MkOpTrue x) = indexDomainsOf x - indexDomainsOf (MkOpTwoBars x) = indexDomainsOf x - indexDomainsOf (MkOpUnion x) = indexDomainsOf x - indexDomainsOf (MkOpXor x) = indexDomainsOf x - -instance DomainOf Constant where - domainOf ConstantBool{} = return DomainBool - domainOf i@(ConstantInt t _) = return $ DomainInt t [RangeSingle (Constant i)] - domainOf (ConstantEnum defn _ _ ) = return (DomainEnum defn Nothing Nothing) - domainOf ConstantField{} = fail "DomainOf-Constant-ConstantField" - domainOf (ConstantAbstract x) = domainOf (fmap Constant x) - domainOf (DomainInConstant dom) = return (fmap Constant dom) - domainOf (TypedConstant x ty) = domainOf (Typed (Constant x) ty) - domainOf ConstantUndefined{} = fail "DomainOf-Constant-ConstantUndefined" - - indexDomainsOf ConstantBool{} = return [] - indexDomainsOf ConstantInt{} = return [] - indexDomainsOf ConstantEnum{} = return [] - indexDomainsOf ConstantField{} = return [] - indexDomainsOf (ConstantAbstract x) = indexDomainsOf (fmap Constant x) - indexDomainsOf DomainInConstant{} = return [] - indexDomainsOf (TypedConstant x ty) = indexDomainsOf (Typed (Constant x) ty) - indexDomainsOf ConstantUndefined{} = return [] - -instance DomainOf (AbstractLiteral Expression) where - - domainOf (AbsLitTuple xs) = DomainTuple <$> mapM domainOf xs - - domainOf (AbsLitRecord xs) = DomainRecord <$> sequence [ do t <- domainOf x ; return (n,t) - | (n,x) <- xs ] - - domainOf (AbsLitVariant Nothing _ _) = fail "Cannot calculate the domain of variant literal." - domainOf (AbsLitVariant (Just t) _ _) = return (DomainVariant t) - - domainOf (AbsLitMatrix ind inn ) = DomainMatrix ind <$> (domainUnions =<< mapM domainOf inn) - - domainOf (AbsLitSet [] ) = return $ DomainSet def attr (DomainAny "domainOf-AbsLitSet-[]" TypeAny) - where attr = SetAttr (SizeAttr_Size 0) - domainOf (AbsLitSet xs ) = DomainSet def attr <$> (domainUnions =<< mapM domainOf xs) - where attr = SetAttr (SizeAttr_MaxSize $ fromInt $ genericLength xs) - - domainOf (AbsLitMSet [] ) = return $ DomainMSet def attr (DomainAny "domainOf-AbsLitMSet-[]" TypeAny) - where attr = MSetAttr (SizeAttr_Size 0) OccurAttr_None - domainOf (AbsLitMSet xs ) = DomainMSet def attr <$> (domainUnions =<< mapM domainOf xs) - where attr = MSetAttr (SizeAttr_MaxSize $ fromInt $ genericLength xs) OccurAttr_None - - domainOf (AbsLitFunction [] ) = return $ DomainFunction def attr - (DomainAny "domainOf-AbsLitFunction-[]-1" TypeAny) - (DomainAny "domainOf-AbsLitFunction-[]-2" TypeAny) - where attr = FunctionAttr (SizeAttr_Size 0) def def - domainOf (AbsLitFunction xs ) = DomainFunction def attr - <$> (domainUnions =<< mapM (domainOf . fst) xs) - <*> (domainUnions =<< mapM (domainOf . snd) xs) - where attr = FunctionAttr (SizeAttr_MaxSize $ fromInt $ genericLength xs) def def - - domainOf (AbsLitSequence [] ) = return $ DomainSequence def attr - (DomainAny "domainOf-AbsLitSequence-[]" TypeAny) - where attr = SequenceAttr (SizeAttr_Size 0) def - domainOf (AbsLitSequence xs ) = DomainSequence def attr - <$> (domainUnions =<< mapM domainOf xs) - where attr = SequenceAttr (SizeAttr_MaxSize (fromInt $ genericLength xs)) def - - domainOf (AbsLitRelation [] ) = return $ DomainRelation def attr [] - where attr = RelationAttr (SizeAttr_Size 0) def - domainOf (AbsLitRelation xss) = do - ty <- domainUnions =<< mapM (domainOf . AbsLitTuple) xss - case ty of - DomainTuple ts -> return (DomainRelation def attr ts) - _ -> bug "expecting DomainTuple in domainOf" - where attr = RelationAttr (SizeAttr_MaxSize (fromInt $ genericLength xss)) def - - domainOf (AbsLitPartition [] ) = return $ DomainPartition def attr - (DomainAny "domainOf-AbsLitPartition-[]" TypeAny) - where attr = PartitionAttr (SizeAttr_Size 0) (SizeAttr_Size 0) False - domainOf (AbsLitPartition xss) = DomainPartition def attr <$> (domainUnions =<< mapM domainOf (concat xss)) - where attr = PartitionAttr (SizeAttr_MaxSize (fromInt $ genericLength xss)) - (SizeAttr_MaxSize (fromInt $ maximum [genericLength xs | xs <- xss])) - False - domainOf (AbsLitPermutation [] ) = return $ DomainPermutation def attr (DomainAny "domainOf-AbsLitPermutation-[]" TypeAny) - where attr = PermutationAttr (SizeAttr_Size 0) - domainOf (AbsLitPermutation xss) = DomainPermutation def def <$> (domainUnions =<< mapM domainOf (concat xss)) - indexDomainsOf (AbsLitMatrix ind inn) = (ind :) <$> (mapM domainUnions =<< mapM indexDomainsOf inn) - indexDomainsOf _ = return [] - - - - --- all the `Op`s - -instance DomainOf (OpActive x) where - domainOf _ = return DomainBool - -instance DomainOf (OpAllDiff x) where - domainOf _ = return DomainBool - -instance DomainOf (OpAllDiffExcept x) where - domainOf _ = return DomainBool - -instance DomainOf x => DomainOf (OpCatchUndef x) where - domainOf (OpCatchUndef x _) = domainOf x - -instance DomainOf (OpAnd x) where - domainOf _ = return DomainBool - -instance DomainOf (OpApart x) where - domainOf _ = return DomainBool - -instance DomainOf (OpAttributeAsConstraint x) where - domainOf _ = return DomainBool - -instance DomainOf x => DomainOf (OpDefined x) where - domainOf (OpDefined f) = do - fDom <- domainOf f - case fDom of - DomainFunction _ _ fr _ -> return $ DomainSet def def fr - _ -> fail "domainOf, OpDefined, not a function" - -instance DomainOf x => DomainOf (OpDiv x) where - domainOf (OpDiv x y) = do - xDom :: Dom <- domainOf x - yDom :: Dom <- domainOf y - (iPat, i) <- quantifiedVar - (jPat, j) <- quantifiedVar - let vals = [essence| [ &i / &j - | &iPat : &xDom - , &jPat : &yDom - ] |] - let low = [essence| min(&vals) |] - let upp = [essence| max(&vals) |] - return (DomainInt TagInt [RangeBounded low upp] :: Dom) - -instance DomainOf (OpDontCare x) where - domainOf _ = return DomainBool - -instance DomainOf (OpDotLeq x) where - domainOf _ = return DomainBool - -instance DomainOf (OpDotLt x) where - domainOf _ = return DomainBool - -instance DomainOf (OpEq x) where - domainOf _ = return DomainBool - -instance (Pretty x, TypeOf x) => DomainOf (OpFactorial x) where - domainOf op = mkDomainAny ("OpFactorial:" <++> pretty op) <$> typeOf op - -instance (Pretty x, TypeOf x, DomainOf x) => DomainOf (OpFlatten x) where - domainOf (OpFlatten (Just 1) x) = domainOf x >>= innerDomainOf - domainOf op = mkDomainAny ("OpFlatten:" <++> pretty op) <$> typeOf op - -instance (Pretty x, TypeOf x) => DomainOf (OpFreq x) where - domainOf op = mkDomainAny ("OpFreq:" <++> pretty op) <$> typeOf op - -instance DomainOf (OpGeq x) where - domainOf _ = return DomainBool - -instance DomainOf (OpGt x) where - domainOf _ = return DomainBool - -instance (Pretty x, TypeOf x) => DomainOf (OpHist x) where - domainOf op = mkDomainAny ("OpHist:" <++> pretty op) <$> typeOf op - -instance DomainOf (OpIff x) where - domainOf _ = return DomainBool - -instance (Pretty x, TypeOf x, DomainOf x) => DomainOf (OpImage x) where -<<<<<<< HEAD - domainOf op = mkDomainAny ("OpImage:" <++> pretty op) <$> typeOf op - indexDomainsOf (OpImage _ x) = indexDomainsOf x -======= - domainOf (OpImage f _) = do - fDomain <- domainOf f - case fDomain of - DomainFunction _ _ _ to -> return to - DomainSequence _ _ to -> return to - _ -> fail "domainOf, OpImage, not a function or sequence" ->>>>>>> master - -instance (Pretty x, TypeOf x) => DomainOf (OpImageSet x) where - domainOf op = mkDomainAny ("OpImageSet:" <++> pretty op) <$> typeOf op - -instance DomainOf (OpImply x) where - domainOf _ = return DomainBool - -instance DomainOf (OpIn x) where - domainOf _ = return DomainBool - -instance (Pretty x, TypeOf x, ExpressionLike x, DomainOf x) => DomainOf (OpIndexing x) where - domainOf (OpIndexing m i) = do - iType <- typeOf i - case iType of - TypeBool{} -> return () - TypeInt{} -> return () - _ -> fail "domainOf, OpIndexing, not a bool or int index" - mDom <- domainOf m - case mDom of - DomainMatrix _ inner -> return inner - DomainTuple inners -> do - iInt <- intOut "domainOf OpIndexing" i - return $ atNote "domainOf" inners (fromInteger (iInt-1)) - _ -> fail "domainOf, OpIndexing, not a matrix or tuple" - - indexDomainsOf p@(OpIndexing m i) = do - iType <- typeOf i - case iType of - TypeBool{} -> return () - TypeInt{} -> return () - _ -> fail "domainOf, OpIndexing, not a bool or int index" - is <- indexDomainsOf m - case is of - [] -> fail ("indexDomainsOf{OpIndexing}, not a matrix domain:" <++> pretty p) - (_:is') -> return is' - -instance (Pretty x, TypeOf x) => DomainOf (OpIntersect x) where - domainOf op = mkDomainAny ("OpIntersect:" <++> pretty op) <$> typeOf op - -instance DomainOf (OpInverse x) where - domainOf _ = return DomainBool - -instance DomainOf (OpLeq x) where - domainOf _ = return DomainBool - -instance DomainOf (OpLexLeq x) where - domainOf _ = return DomainBool - -instance DomainOf (OpLexLt x) where - domainOf _ = return DomainBool - -instance DomainOf (OpLt x) where - domainOf _ = return DomainBool - -instance (Pretty x, TypeOf x, ExpressionLike x, DomainOf x, Domain () x :< x) => DomainOf (OpMax x) where - domainOf (OpMax x) - | Just xs <- listOut x - , not (null xs) = do - doms <- mapM domainOf xs - let lows = fromList [ [essence| min(`&d`) |] | d <- doms ] - let low = [essence| max(&lows) |] - let upps = fromList [ [essence| max(`&d`) |] | d <- doms ] - let upp = [essence| max(&upps) |] - TypeInt t <- typeOfDomain (head doms) - return (DomainInt t [RangeBounded low upp] :: Dom) - domainOf op = mkDomainAny ("OpMax:" <++> pretty op) <$> typeOf op - -instance (Pretty x, TypeOf x, ExpressionLike x, DomainOf x, Domain () x :< x) => DomainOf (OpMin x) where - domainOf (OpMin x) - | Just xs <- listOut x - , not (null xs) = do - doms <- mapM domainOf xs - let lows = fromList [ [essence| min(`&d`) |] | d <- doms ] - let low = [essence| min(&lows) |] - let upps = fromList [ [essence| max(`&d`) |] | d <- doms ] - let upp = [essence| min(&upps) |] - TypeInt t <- typeOfDomain (head doms) - return (DomainInt t [RangeBounded low upp] :: Dom) - domainOf op = mkDomainAny ("OpMin:" <++> pretty op) <$> typeOf op - -instance DomainOf x => DomainOf (OpMinus x) where - domainOf (OpMinus x y) = do - xDom :: Dom <- domainOf x - yDom :: Dom <- domainOf y - - xDom_Min <- minOfDomain xDom - xDom_Max <- maxOfDomain xDom - yDom_Min <- minOfDomain yDom - yDom_Max <- maxOfDomain yDom - - let low = [essence| &xDom_Min - &yDom_Max |] - let upp = [essence| &xDom_Max - &yDom_Min |] - - return (DomainInt TagInt [RangeBounded low upp] :: Dom) - -instance (Pretty x, TypeOf x) => DomainOf (OpMod x) where - domainOf op = mkDomainAny ("OpMod:" <++> pretty op) <$> typeOf op - -instance (Pretty x, TypeOf x) => DomainOf (OpNegate x) where - domainOf op = mkDomainAny ("OpNegate:" <++> pretty op) <$> typeOf op - -instance DomainOf (OpNeq x) where - domainOf _ = return DomainBool - -instance DomainOf (OpNot x) where - domainOf _ = return DomainBool - -instance DomainOf (OpOr x) where - domainOf _ = return DomainBool - -instance DomainOf (OpXor x) where - domainOf _ = return DomainBool - -instance (Pretty x, TypeOf x) => DomainOf (OpParticipants x) where - domainOf op = mkDomainAny ("OpParticipants:" <++> pretty op) <$> typeOf op - -instance DomainOf x => DomainOf (OpParts x) where - domainOf (OpParts p) = do - dom <- domainOf p - case dom of - DomainPartition _ _ inner -> return $ DomainSet def def $ DomainSet def def inner - _ -> fail "domainOf, OpParts, not a partition" - -instance (Pretty x, TypeOf x) => DomainOf (OpParty x) where - domainOf op = mkDomainAny ("OpParty:" <++> pretty op) <$> typeOf op - - -instance (Pretty x, TypeOf x) => DomainOf (OpCompose x) where - domainOf op = mkDomainAny ("OpCompose:" <++> pretty op) <$> typeOf op - -instance (Pretty x, TypeOf x) => DomainOf (OpPow x) where - domainOf op = mkDomainAny ("OpPow:" <++> pretty op) <$> typeOf op - -instance (Pretty x, TypeOf x) => DomainOf (OpPowerSet x) where - domainOf op = mkDomainAny ("OpPowerSet:" <++> pretty op) <$> typeOf op - -instance (Pretty x, TypeOf x) => DomainOf (OpPreImage x) where - domainOf op = mkDomainAny ("OpPreImage:" <++> pretty op) <$> typeOf op - -instance DomainOf x => DomainOf (OpPred x) where - domainOf (OpPred x) = domainOf x -- TODO: improve - -instance (ExpressionLike x, DomainOf x) => DomainOf (OpProduct x) where - domainOf (OpProduct x) - | Just xs <- listOut x - , not (null xs) = do - (iPat, i) <- quantifiedVar - doms <- mapM domainOf xs - -- maximum absolute value in each domain - let upps = fromList [ [essence| max([ |&i| | &iPat : &d ]) |] - | d <- doms ] - -- a (too lax) upper bound is multiplying all those together - let upp = [essence| product(&upps) |] - -- a (too lax) lower bound is -upp - let low = [essence| -1 * &upp |] - return $ DomainInt TagInt [RangeBounded low upp] - domainOf _ = return $ DomainInt TagInt [RangeBounded 1 1] - -instance DomainOf x => DomainOf (OpRange x) where - domainOf (OpRange f) = do - fDom <- domainOf f - case fDom of - DomainFunction _ _ _ to -> return $ DomainSet def def to - _ -> fail "domainOf, OpRange, not a function" - -instance (Pretty x, TypeOf x) => DomainOf (OpRelationProj x) where - domainOf op = mkDomainAny ("OpRelationProj:" <++> pretty op) <$> typeOf op - -instance (DomainOf x, Dom :< x) => DomainOf (OpRestrict x) where - domainOf (OpRestrict f x) = do - d <- project x - fDom <- domainOf f - case fDom of - DomainFunction fRepr a _ to -> return (DomainFunction fRepr a d to) - _ -> fail "domainOf, OpRestrict, not a function" - -instance (Pretty x, DomainOf x) => DomainOf (OpSlicing x) where - domainOf (OpSlicing x _ _) = domainOf x - indexDomainsOf (OpSlicing x _ _) = indexDomainsOf x - -instance DomainOf (OpSubsequence x) where - domainOf _ = fail "domainOf{OpSubsequence}" - -instance (Pretty x, TypeOf x) => DomainOf (OpSubset x) where - domainOf op = mkDomainAny ("OpSubset:" <++> pretty op) <$> typeOf op - -instance (Pretty x, TypeOf x) => DomainOf (OpSubsetEq x) where - domainOf op = mkDomainAny ("OpSubsetEq:" <++> pretty op) <$> typeOf op - -instance DomainOf (OpSubstring x) where - domainOf _ = fail "domainOf{OpSubstring}" - -instance DomainOf x => DomainOf (OpSucc x) where - domainOf (OpSucc x) = domainOf x -- TODO: improve - -instance (ExpressionLike x, DomainOf x) => DomainOf (OpSum x) where - domainOf (OpSum x) - | Just xs <- listOut x - , not (null xs) = do - doms <- mapM domainOf xs - let lows = fromList [ [essence| min(`&d`) |] | d <- doms ] - let low = [essence| sum(&lows) |] - let upps = fromList [ [essence| max(`&d`) |] | d <- doms ] - let upp = [essence| sum(&upps) |] - return (DomainInt TagInt [RangeBounded low upp] :: Dom) - domainOf _ = return $ DomainInt TagInt [RangeBounded 0 0] - - -instance DomainOf (OpSupset x) where - domainOf _ = return DomainBool - -instance DomainOf (OpSupsetEq x) where - domainOf _ = return DomainBool - -instance DomainOf (OpTildeLeq x) where - domainOf _ = return DomainBool - -instance DomainOf (OpTildeLt x) where - domainOf _ = return DomainBool - -instance DomainOf (OpToInt x) where - domainOf _ = return $ DomainInt TagInt [RangeBounded 0 1] - -instance (Pretty x, TypeOf x) => DomainOf (OpToMSet x) where - domainOf op = mkDomainAny ("OpToMSet:" <++> pretty op) <$> typeOf op - -instance (Pretty x, TypeOf x) => DomainOf (OpToRelation x) where - domainOf op = mkDomainAny ("OpToRelation:" <++> pretty op) <$> typeOf op - -instance (Pretty x, TypeOf x) => DomainOf (OpToSet x) where - domainOf op = mkDomainAny ("OpToSet:" <++> pretty op) <$> typeOf op - -instance DomainOf (OpTogether x) where - domainOf _ = return DomainBool - -instance (Pretty x, TypeOf x) => DomainOf (OpTransform x) where - domainOf op = mkDomainAny ("OpTransform:" <++> pretty op) <$> typeOf op - -instance DomainOf (OpTrue x) where - domainOf _ = return DomainBool - -instance (Pretty x, TypeOf x, Domain () x :< x) => DomainOf (OpTwoBars x) where - domainOf op = mkDomainAny ("OpTwoBars:" <++> pretty op) <$> typeOf op - -instance (Pretty x, TypeOf x) => DomainOf (OpUnion x) where - domainOf op = mkDomainAny ("OpUnion:" <++> pretty op) <$> typeOf op - diff --git a/src/Conjure/Language/Constant.hs.orig b/src/Conjure/Language/Constant.hs.orig deleted file mode 100644 index fcd2b6c26d..0000000000 --- a/src/Conjure/Language/Constant.hs.orig +++ /dev/null @@ -1,535 +0,0 @@ -{-# LANGUAGE DeriveGeneric, DeriveDataTypeable #-} - -module Conjure.Language.Constant - ( Constant(..) - , valuesInIntDomain - , normaliseConstant - , mkUndef, isUndef - , emptyCollection - , viewConstantBool - , viewConstantInt - , viewConstantTuple - , viewConstantRecord - , viewConstantVariant - , viewConstantMatrix - , viewConstantSet - , viewConstantMSet - , viewConstantFunction - , viewConstantSequence - , viewConstantRelation - , viewConstantPartition - , viewConstantPermutation - , reDomConst - ) where - --- conjure -import Conjure.Prelude -import Conjure.Bug -import Conjure.Language.Name -import Conjure.Language.Domain -import Conjure.Language.Type -import Conjure.Language.AbstractLiteral - -import Conjure.Language.DomainSizeOf -import Conjure.Language.TypeOf -import Conjure.Language.AdHoc -import Conjure.Language.Pretty - --- base -import Data.Data ( toConstr, constrIndex ) - --- QuickCheck -import Test.QuickCheck ( Arbitrary(..), oneof ) - - -data Constant - = ConstantBool Bool - | ConstantInt IntTag Integer - | ConstantEnum Name {- name for the enum domain -} - [Name] {- values in the enum domain -} - Name {- the literal -} - | ConstantField Name Type -- the name of a field of Record or Variant and its type - | ConstantAbstract (AbstractLiteral Constant) - | DomainInConstant (Domain () Constant) - | TypedConstant Constant Type - | ConstantUndefined Text Type -- never use this for a bool - -- use false instead for them - deriving (Show, Data, Typeable, Generic) - -instance Eq Constant where - a == b = compare a b == EQ - --- implementing the Eq&Ord instances by hand, because we want to special case the TypedConstant constructor -instance Ord Constant where - - -- do not use type info when comparing - compare (TypedConstant a _) (TypedConstant b _) = compare a b - compare (TypedConstant a _) b = compare a b - compare a (TypedConstant b _) = compare a b - - -- the "usual" comparisons - compare (ConstantBool a) (ConstantBool b) = compare a b - compare (ConstantInt _ a) (ConstantInt _ b) = compare a b - compare (ConstantEnum _ aVals aVal) (ConstantEnum _ bVals bVal) = - compare (elemIndex aVal aVals, aVal) (elemIndex bVal bVals, bVal) - compare (ConstantField a1 a2) (ConstantField b1 b2) = compare (a1,a2) (b1,b2) - compare (ConstantAbstract a) (ConstantAbstract b) = compare a b - compare (DomainInConstant a) (DomainInConstant b) = compare a b - compare (ConstantUndefined a1 a2) (ConstantUndefined b1 b2) = compare (a1,a2) (b1,b2) - - -- if the constructors do not match - compare a b = compare (constrIndex (toConstr a)) (constrIndex (toConstr b)) - -instance Serialize Constant -instance Hashable Constant -instance ToJSON Constant where toJSON = genericToJSON jsonOptions -instance FromJSON Constant where parseJSON = genericParseJSON jsonOptions - -instance Arbitrary Constant where - arbitrary = oneof - [ ConstantBool <$> arbitrary - , ConstantInt TagInt <$> arbitrary - ] - -instance TypeOf Constant where - typeOf ConstantBool{} = return TypeBool - typeOf (ConstantInt t _) = return (TypeInt t) - typeOf (ConstantEnum defn _ _ ) = return (TypeEnum defn) - typeOf (ConstantField _ ty) = return ty - typeOf (ConstantAbstract x ) = typeOf x - typeOf (DomainInConstant dom) = typeOfDomain dom - typeOf (TypedConstant _ ty) = return ty - typeOf (ConstantUndefined _ ty) = return ty - -instance DomainSizeOf Constant Integer where - domainSizeOf DomainBool{} = return 2 - domainSizeOf (DomainIntE x) = bug ("not implemented, domainSizeOf DomainIntE" <+> pretty (show x)) - domainSizeOf (DomainInt _ rs) = domainSizeOfRanges rs - domainSizeOf DomainEnum{} = fail "domainSizeOf: Unknown for given enum." - domainSizeOf (DomainTuple ds) = product <$> mapM domainSizeOf ds - domainSizeOf (DomainMatrix index inner) = intPow <$> domainSizeOf inner <*> domainSizeOf index - domainSizeOf d@(DomainSet _ (SetAttr attrs) inner) = - case attrs of - SizeAttr_None -> do - innerSize <- domainSizeOf inner - return (2 `intPow` innerSize) - SizeAttr_Size (ConstantInt _ size) -> do - innerSize <- domainSizeOf inner - return (nchoosek (product . enumFromTo 1) innerSize size) - SizeAttr_MinSize{} -> do - -- TODO: we can do better here - innerSize <- domainSizeOf inner - return (2 `intPow` innerSize) - SizeAttr_MaxSize (ConstantInt _ maxSize) -> do - innerSize <- domainSizeOf inner - return $ sum [ nchoosek (product . enumFromTo 1) innerSize k | k <- [0 .. maxSize] ] - SizeAttr_MinMaxSize (ConstantInt _ minSize) (ConstantInt _ maxSize) -> do - innerSize <- domainSizeOf inner - return $ sum [ nchoosek (product . enumFromTo 1) innerSize k | k <- [minSize .. maxSize] ] - _ -> fail ("domainSizeOf{Constant}" <+> pretty d) - domainSizeOf DomainMSet {} = bug "not implemented: domainSizeOf DomainMSet" - domainSizeOf DomainFunction {} = bug "not implemented: domainSizeOf DomainFunction" - domainSizeOf DomainRelation {} = bug "not implemented: domainSizeOf DomainRelation" - domainSizeOf DomainPartition {} = bug "not implemented: domainSizeOf DomainPartition" - domainSizeOf _ = bug "not implemented: domainSizeOf" - -emptyCollection :: Constant -> Bool -emptyCollection ConstantBool{} = False -emptyCollection ConstantInt{} = False -emptyCollection ConstantEnum{} = False -emptyCollection ConstantField{} = False -emptyCollection (ConstantAbstract x) = emptyCollectionAbsLit x -emptyCollection DomainInConstant{} = False -emptyCollection (TypedConstant x _) = emptyCollection x -emptyCollection ConstantUndefined{} = False - -intPow :: Integer -> Integer -> Integer -intPow = (^) - -domainSizeOfRanges :: MonadFail m => [Range Constant] -> m Integer -domainSizeOfRanges = fmap genericLength . valuesInIntDomain - -instance DomainSizeOf Constant Constant where - domainSizeOf = fmap (ConstantInt TagInt) . domainSizeOf - -instance Pretty Constant where - - -- hack, oh sweet hack! - -- print a domain instead of a type when printing an empty matrix literal. - -- this means we print "int()" instead of "int" inside the index of a matrix type - -- SR expects it this way... - pretty (TypedConstant (ConstantAbstract (AbsLitMatrix _ [])) ty) = - let - pretty' (TypeMatrix index innerNested) - = "matrix indexed by" <+> prettyList prBrackets "," (map pretty' indices) - <+> "of" <+> pretty inner - where - (indices,inner) = first (index:) $ collect innerNested - collect (TypeMatrix i j) = first (i:) $ collect j - collect x = ([],x) - pretty' TypeInt{} = "int()" - pretty' t = pretty t - in - prParens $ "[] : `" <> pretty' ty <> "`" - - pretty (ConstantBool False) = "false" - pretty (ConstantBool True ) = "true" - pretty (ConstantInt _ x ) = pretty x - pretty (ConstantEnum _ _ x) = pretty x - pretty (ConstantField n _) = pretty n - pretty (ConstantAbstract x) = pretty x - pretty (DomainInConstant d) = "`" <> pretty d <> "`" - pretty (TypedConstant x ty) = prParens $ pretty x <+> ":" <+> "`" <> pretty ty <> "`" - pretty (ConstantUndefined reason ty) = "undefined" <> prParens (pretty reason <+> ":" <+> "`" <> pretty ty <> "`") - -instance ExpressionLike Constant where - fromInt = ConstantInt TagInt - fromIntWithTag i t = ConstantInt t i - intOut _ (ConstantInt _ x) = return x - intOut doc c = fail $ vcat [ "Expecting an integer, but found:" <+> pretty c - , "Called from:" <+> doc - ] - - fromBool = ConstantBool - boolOut (ConstantBool x) = return x - boolOut ConstantUndefined{} = return False - boolOut c = fail ("Expecting a boolean, but found:" <+> pretty c) - - fromList xs = ConstantAbstract $ AbsLitMatrix (mkDomainIntB 1 (fromInt $ genericLength xs)) xs - listOut (ConstantAbstract (AbsLitMatrix _ xs)) = return xs - listOut c = fail ("Expecting a matrix literal, but found:" <+> pretty c) - -instance ReferenceContainer Constant where - fromName name = bug ("ReferenceContainer{Constant} fromName --" <+> pretty name) - nameOut (ConstantField nm _) = return nm - nameOut p = bug ("ReferenceContainer{Constant} nameOut --" <+> pretty p) - -instance DomainContainer Constant (Domain ()) where - fromDomain = DomainInConstant - domainOut (DomainInConstant dom) = return dom - domainOut _ = fail "domainOut{Constant}" - -mkUndef :: Type -> Doc -> Constant -mkUndef TypeBool _ = ConstantBool False -mkUndef ty reason = ConstantUndefined (stringToText $ show reason) ty - -isUndef :: Constant -> Bool -isUndef ConstantUndefined{} = True -isUndef _ = False - -normaliseConstant :: Constant -> Constant -normaliseConstant x@ConstantBool{} = x -normaliseConstant x@ConstantInt{} = x -normaliseConstant x@ConstantEnum{} = x -normaliseConstant x@ConstantField{} = x -normaliseConstant (ConstantAbstract x) = ConstantAbstract (normaliseAbsLit normaliseConstant x) -normaliseConstant (DomainInConstant d) = DomainInConstant (normaliseDomain normaliseConstant d) -normaliseConstant (TypedConstant c ty) = TypedConstant (normaliseConstant c) ty -normaliseConstant x@ConstantUndefined{} = x - -instance Num Constant where - ConstantInt _ x + ConstantInt _ y = ConstantInt TagInt (x+y) - x + y = bug $ vcat [ "Num Constant (+)", "x:" <+> pretty x, "y:" <+> pretty y ] - ConstantInt _ x - ConstantInt _ y = ConstantInt TagInt (x-y) - x - y = bug $ vcat [ "Num Constant (-)", "x:" <+> pretty x, "y:" <+> pretty y ] - ConstantInt _ x * ConstantInt _ y = ConstantInt TagInt (x*y) - x * y = bug $ vcat [ "Num Constant (*)", "x:" <+> pretty x, "y:" <+> pretty y ] - abs (ConstantInt t x) = ConstantInt t (abs x) - abs x = bug $ vcat [ "Num Constant abs", "x:" <+> pretty x ] - signum (ConstantInt t x) = ConstantInt t (signum x) - signum x = bug $ vcat [ "Num Constant signum", "x:" <+> pretty x ] - fromInteger = ConstantInt TagInt . fromInteger - - -valuesInIntDomain :: MonadFail m => [Range Constant] -> m [Integer] -valuesInIntDomain ranges = - if isFinite - then return allValues - else fail $ "Expected finite integer ranges, but got:" <++> prettyList id "," ranges - - where - - allRanges :: [Maybe [Integer]] - allRanges = - [ vals - | r <- ranges - , let vals = case r of - RangeSingle (ConstantInt _ x) -> return [x] - RangeBounded (ConstantInt _ l) (ConstantInt _ u) -> return [l..u] - _ -> Nothing - ] - - isFinite :: Bool - isFinite = Nothing `notElem` allRanges - - allValues :: [Integer] - allValues = sortNub $ concat $ catMaybes allRanges - - -<<<<<<< HEAD --- | Assuming both the value and the domain are normalised --- TODO: make this stricter, but write failing test cases first! -validateConstantForDomain :: forall m r . (MonadFail m, Pretty r) => Name -> Constant -> Domain r Constant -> m () - -validateConstantForDomain _ ConstantBool{} DomainBool{} = return () - -validateConstantForDomain _ _ (DomainInt _ []) = return () -- no restrictions - -validateConstantForDomain name c@(ConstantInt cTag i) d@(DomainInt dTag rs) | cTag == dTag = - let - intInRange RangeOpen = True - intInRange (RangeSingle (ConstantInt _ a)) = i == a - intInRange (RangeLowerBounded (ConstantInt _ a)) = i >= a - intInRange (RangeUpperBounded (ConstantInt _ a)) = i <= a - intInRange (RangeBounded (ConstantInt _ a) (ConstantInt _ b)) = i >= a && i <= b - intInRange _ = False - in unless (any intInRange rs) (constantNotInDomain name c d) - -validateConstantForDomain _ (ConstantInt _ i) (DomainUnnamed _ (ConstantInt _ a)) | i >= 1 && i <= a = return () - -validateConstantForDomain _ _ (DomainEnum _ Nothing _) = return () -- no restrictions -validateConstantForDomain name c d@(DomainEnum _ _ Nothing) = - fail $ vcat [ "validateConstantForDomain: enum not handled" - , pretty name - , pretty c - , pretty d - ] -validateConstantForDomain name - c@(ConstantInt cTag _) - d@(DomainEnum _ (Just ranges) (Just mp)) = nested c d $ do - let - -- lu :: MonadFail m => Name -> m Constant - lu (ConstantEnum _ _ nm) = - case lookup nm mp of - Nothing -> fail $ "No value for:" <+> pretty nm - Just v -> return (ConstantInt cTag v) - lu (ConstantInt t v) = return (ConstantInt t v) - lu x = fail $ "validateConstantForDomain.lu" <+> pretty x - - -- lu2 :: MonadFail m => Range Name -> m (Range Constant) - lu2 = mapM lu - - rs <- mapM lu2 ranges - validateConstantForDomain name c (DomainInt cTag rs :: Domain r Constant) - -validateConstantForDomain name - c@(ConstantAbstract (AbsLitTuple cs)) - d@(DomainTuple ds) = nested c d $ zipWithM_ (validateConstantForDomain name) cs ds - -validateConstantForDomain name - c@(ConstantAbstract (AbsLitRecord (sortOn fst -> cs))) - d@(DomainRecord (sortOn fst -> ds)) - | map fst cs == map fst ds - = nested c d $ zipWithM_ (validateConstantForDomain name) (map snd cs) (map snd ds) - | otherwise - = constantNotInDomain name c d - -validateConstantForDomain name - c@(ConstantAbstract (AbsLitVariant _ n c')) - d@(DomainVariant ds) - | Just d' <- lookup n ds - = nested c d $ validateConstantForDomain name c' d' - | otherwise - = constantNotInDomain name c d - -validateConstantForDomain name - c@(ConstantAbstract (AbsLitMatrix cIndex vals)) - d@(DomainMatrix dIndex dInner) = do - nested c d $ - mapM_ (\ val -> validateConstantForDomain name val dInner ) vals - let - isEmptyIntDomain (DomainInt _ []) = True - isEmptyIntDomain _ = False - unless (cIndex == dIndex || isEmptyIntDomain cIndex) $ fail $ vcat - [ "The indices do not match between the value and the domain." - , "Value :" <+> pretty c - , "Domain:" <+> pretty d - ] - -validateConstantForDomain name - c@(ConstantAbstract (AbsLitSet vals)) - d@(DomainSet _ (SetAttr sizeAttr) dInner) = do - let cardinalityOK = case sizeAttr of - SizeAttr_None -> True - SizeAttr_Size (ConstantInt _ s) -> s == genericLength vals - SizeAttr_MinSize (ConstantInt _ s) -> s <= genericLength vals - SizeAttr_MaxSize (ConstantInt _ s) -> genericLength vals <= s - SizeAttr_MinMaxSize (ConstantInt _ smin) (ConstantInt _ smax) -> - smin <= genericLength vals && genericLength vals <= smax - _ -> False - unless cardinalityOK $ fail $ vcat - [ "The value is not a member of the domain." - , "Value :" <+> pretty c - , "Domain:" <+> pretty d - , "Reason: Domain attributes are not satisfied." - , "Specifically:" <+> pretty sizeAttr - ] - nested c d $ mapM_ (\ val -> validateConstantForDomain name val dInner ) vals - -validateConstantForDomain name - c@(ConstantAbstract (AbsLitMSet vals)) - d@(DomainMSet _ (MSetAttr sizeAttr occurAttr) dInner) = do - let cardinalityOK = case sizeAttr of - SizeAttr_None -> True - SizeAttr_Size (ConstantInt _ s) -> s == genericLength vals - SizeAttr_MinSize (ConstantInt _ s) -> s <= genericLength vals - SizeAttr_MaxSize (ConstantInt _ s) -> genericLength vals <= s - SizeAttr_MinMaxSize (ConstantInt _ smin) (ConstantInt _ smax) -> - smin <= genericLength vals && genericLength vals <= smax - _ -> False - unless cardinalityOK $ fail $ vcat - [ "The value is not a member of the domain." - , "Value :" <+> pretty c - , "Domain:" <+> pretty d - , "Reason: Domain attributes are not satisfied." - , "Specifically:" <+> pretty sizeAttr - ] - let occurOK = case occurAttr of - OccurAttr_None -> True - OccurAttr_MinOccur (ConstantInt _ s) -> and [ s <= occ | (_, occ) <- histogram vals ] - OccurAttr_MaxOccur (ConstantInt _ s) -> and [ occ <= s | (_, occ) <- histogram vals ] - OccurAttr_MinMaxOccur (ConstantInt _ smin) (ConstantInt _ smax) -> - and [ smin <= occ && occ <= smax | (_, occ) <- histogram vals ] - _ -> False - unless occurOK $ fail $ vcat - [ "The value is not a member of the domain." - , "Value :" <+> pretty c - , "Domain:" <+> pretty d - , "Reason: Domain attributes are not satisfied." - , "Specifically:" <+> pretty occurAttr - ] - nested c d $ mapM_ (\ val -> validateConstantForDomain name val dInner ) vals - -validateConstantForDomain name - c@(ConstantAbstract (AbsLitFunction vals)) - d@(DomainFunction _ _ dFrom dTo) = nested c d $ do - mapM_ (\ val -> validateConstantForDomain name (fst val) dFrom) vals - mapM_ (\ val -> validateConstantForDomain name (snd val) dTo ) vals - -validateConstantForDomain name - c@(ConstantAbstract (AbsLitSequence vals)) - d@(DomainSequence _ _ dInner) = nested c d $ - mapM_ (\ val -> validateConstantForDomain name val dInner ) vals - -validateConstantForDomain name - c@(ConstantAbstract (AbsLitRelation valss)) - d@(DomainRelation _ _ dInners) = nested c d $ - forM_ valss $ \ vals -> - zipWithM_ (validateConstantForDomain name) vals dInners - -validateConstantForDomain name - c@(ConstantAbstract (AbsLitPartition valss)) - d@(DomainPartition _ _ dInner) = nested c d $ - mapM_ (\ val -> validateConstantForDomain name val dInner ) (concat valss) -validateConstantForDomain name - c@(ConstantAbstract (AbsLitPermutation valss)) - d@(DomainPermutation _ _ dInner) = nested c d $ - mapM_ (\ val -> validateConstantForDomain name val dInner ) (concat valss) -validateConstantForDomain name c@(TypedConstant c' _) d = nested c d $ validateConstantForDomain name c' d - -validateConstantForDomain name c d = constantNotInDomain name c d - - -nested :: (MonadFail m, Pretty r) => Constant -> Domain r Constant -> Either Doc () -> m () -nested _ _ Right{} = return () -nested c d (Left err) = fail $ vcat - [ "The value is not a member of the domain." - , "Value :" <+> pretty c - , "Domain:" <+> pretty d - , "Reason:" - , nest 4 err - ] - -constantNotInDomain :: (MonadFail m, Pretty r) => Name -> Constant -> Domain r Constant -> m () -constantNotInDomain n c d = fail $ vcat - [ "The value is not a member of the domain." - , "Name :" <+> pretty n - , "Value :" <+> pretty c - , "Domain:" <+> pretty d - ] - - -======= ->>>>>>> master -viewConstantBool :: MonadFail m => Constant -> m Bool -viewConstantBool (ConstantBool i) = return i -viewConstantBool (ConstantInt _ 0) = return False -viewConstantBool (ConstantInt _ 1) = return True -viewConstantBool constant = fail ("Expecting a boolean, but got:" <++> pretty constant) - -viewConstantInt :: MonadFail m => Constant -> m Integer -viewConstantInt (ConstantInt _ i) = return i -viewConstantInt constant = fail ("Expecting an integer, but got:" <++> pretty constant) - -viewConstantTuple :: MonadFail m => Constant -> m [Constant] -viewConstantTuple (ConstantAbstract (AbsLitTuple xs)) = return xs -viewConstantTuple (TypedConstant c _) = viewConstantTuple c -viewConstantTuple constant = fail ("Expecting a tuple, but got:" <++> pretty constant) - -viewConstantRecord :: MonadFail m => Constant -> m [(Name, Constant)] -viewConstantRecord (ConstantAbstract (AbsLitRecord xs)) = return xs -viewConstantRecord (TypedConstant c _) = viewConstantRecord c -viewConstantRecord constant = fail ("Expecting a record, but got:" <++> pretty constant) - -viewConstantVariant :: MonadFail m => Constant -> m (Maybe [(Name, Domain () Constant)], Name, Constant) -viewConstantVariant (ConstantAbstract (AbsLitVariant lu nm x)) = return (lu, nm, x) -viewConstantVariant (TypedConstant c _) = viewConstantVariant c -viewConstantVariant constant = fail ("Expecting a variant, but got:" <++> pretty constant) - -viewConstantMatrix :: MonadFail m => Constant -> m (Domain () Constant, [Constant]) -viewConstantMatrix (ConstantAbstract (AbsLitMatrix ind xs)) = return (ind, xs) -viewConstantMatrix (TypedConstant c _) = viewConstantMatrix c -viewConstantMatrix constant = fail ("Expecting a matrix, but got:" <++> pretty constant) - -viewConstantSet :: MonadFail m => Constant -> m [Constant] -viewConstantSet (ConstantAbstract (AbsLitSet xs)) = return xs -viewConstantSet (TypedConstant c _) = viewConstantSet c -viewConstantSet constant = fail ("Expecting a set, but got:" <++> pretty constant) - -viewConstantMSet :: MonadFail m => Constant -> m [Constant] -viewConstantMSet (ConstantAbstract (AbsLitMSet xs)) = return xs -viewConstantMSet (TypedConstant c _) = viewConstantMSet c -viewConstantMSet constant = fail ("Expecting an mset, but got:" <++> pretty constant) - -viewConstantFunction :: MonadFail m => Constant -> m [(Constant, Constant)] -viewConstantFunction (ConstantAbstract (AbsLitFunction xs)) = return xs -viewConstantFunction (TypedConstant c _) = viewConstantFunction c -viewConstantFunction constant = do - let - suggestion = case constant of - ConstantAbstract (AbsLitMatrix (DomainInt _ rs) vals) -> do - froms <- valuesInIntDomain rs - return $ Just $ pretty $ AbsLitFunction (zip (map (ConstantInt TagInt) froms) vals) - _ -> return Nothing - suggestion >>= \case - Nothing -> fail ("Expecting a function, but got:" <++> pretty constant) - Just sug -> fail (vcat [ "Expecting a function, but got:" <++> pretty constant - , "Maybe you meant:" <++> sug - ]) - -viewConstantSequence :: MonadFail m => Constant -> m [Constant] -viewConstantSequence (ConstantAbstract (AbsLitSequence xs)) = return xs -viewConstantSequence (TypedConstant c _) = viewConstantSequence c -viewConstantSequence constant = fail ("Expecting a sequence, but got:" <++> pretty constant) - -viewConstantRelation :: MonadFail m => Constant -> m [[Constant]] -viewConstantRelation (ConstantAbstract (AbsLitRelation xs)) = return xs -viewConstantRelation (TypedConstant c _) = viewConstantRelation c -viewConstantRelation constant = fail ("Expecting a relation, but got:" <++> pretty constant) - -viewConstantPartition :: MonadFail m => Constant -> m [[Constant]] -viewConstantPartition (ConstantAbstract (AbsLitPartition xs)) = return xs -viewConstantPartition (TypedConstant c _) = viewConstantPartition c -viewConstantPartition constant = fail ("Expecting a partition, but got:" <++> pretty constant) - -viewConstantPermutation :: MonadFail m => Constant -> m [[Constant]] -viewConstantPermutation (ConstantAbstract (AbsLitPermutation xs)) = return xs -viewConstantPermutation (TypedConstant c _) = viewConstantPermutation c -viewConstantPermutation constant = fail ("Expecting a permutation, but got:" <++> pretty constant) - - -reDomConst :: Domain () Constant -> Domain () Constant -reDomConst cns = case cns of - DomainInt t _ -> reTag t cns - _ -> cns - diff --git a/src/Conjure/Language/Domain.hs.orig b/src/Conjure/Language/Domain.hs.orig deleted file mode 100644 index 9164000946..0000000000 --- a/src/Conjure/Language/Domain.hs.orig +++ /dev/null @@ -1,1079 +0,0 @@ -{-# LANGUAGE DeriveGeneric, DeriveDataTypeable, DeriveFunctor, DeriveTraversable, DeriveFoldable #-} -{-# LANGUAGE TupleSections #-} -{-# LANGUAGE NoMonomorphismRestriction #-} -{-# LANGUAGE ViewPatterns #-} - -module Conjure.Language.Domain - ( Domain(..) - , HasRepresentation(..) - , Range(..), rangesInts - , SetAttr(..), SizeAttr(..), getMaxFrom_SizeAttr - , MSetAttr(..), OccurAttr(..), getMaxFrom_OccurAttr - , FunctionAttr(..), PartialityAttr(..), JectivityAttr(..) - , SequenceAttr(..) - , RelationAttr(..), BinaryRelationAttrs(..), BinaryRelationAttr(..) - , PartitionAttr(..) - , PermutationAttr(..) - , AttrName(..) - , DomainAttributes(..), DomainAttribute(..) -- only for parsing - , textToRepresentation, representationToShortText, representationToFullText - , isPrimitiveDomain, domainCanIndexMatrix, getIndices - , Tree(..), reprTree, reprAtTopLevel, applyReprTree - , reprTreeEncoded - , forgetRepr, changeRepr, defRepr - , mkDomainBool, mkDomainInt, mkDomainIntB, mkDomainIntBTagged, mkDomainAny - , typeOfDomain - , readBinRel, binRelToAttrName - , normaliseDomain, normaliseRange - , innerDomainOf - , singletonDomainInt - , matrixNumDimsD - ) where - --- conjure -import Conjure.Prelude -import Conjure.Bug -import Conjure.Language.Name -import Conjure.Language.Type -import Conjure.Language.TypeOf -import Conjure.Language.AdHoc -import Conjure.Language.Pretty - --- base -import qualified Data.Semigroup as Semigroup ( (<>) ) - --- QuickCheck -import Test.QuickCheck ( Arbitrary(..), choose, oneof, vectorOf, sized ) - --- containers -import Data.Set as S ( Set, empty, toList, union ) - --- syb -import Data.Data ( toConstr, constrIndex ) - - -data Domain r x - = DomainAny Text Type - | DomainBool - | DomainIntE x - | DomainInt IntTag [Range x] - | DomainEnum - Name - (Maybe [Range x]) -- subset of values for this domain - -- Nothing *only* when GivenDomainDefnEnum and not LettingDomainDefnEnum - (Maybe [(Name, Integer)]) -- the mapping to integers, if available - | DomainUnnamed Name x - | DomainTuple [Domain r x] - | DomainRecord [(Name, Domain r x)] - | DomainVariant [(Name, Domain r x)] - | DomainMatrix (Domain () x) (Domain r x) - | DomainSet r (SetAttr x) (Domain r x) - | DomainMSet r (MSetAttr x) (Domain r x) - | DomainFunction r (FunctionAttr x) (Domain r x) (Domain r x) - | DomainSequence r (SequenceAttr x) (Domain r x) - | DomainRelation r (RelationAttr x) [Domain r x] - | DomainPartition r (PartitionAttr x) (Domain r x) - | DomainPermutation r (PermutationAttr x) (Domain r x) - | DomainOp Name [Domain r x] - | DomainReference Name (Maybe (Domain r x)) - | DomainMetaVar String - deriving (Eq, Ord, Show, Data, Functor, Traversable, Foldable, Typeable, Generic) - -instance (VarSymBreakingDescription x, ToJSON r) => VarSymBreakingDescription (Domain r x) where - varSymBreakingDescription domain = toJSON $ fmap varSymBreakingDescription domain - -mkDomainBool :: Domain () x -mkDomainBool = DomainBool - -mkDomainInt :: [Range x] -> Domain () x -mkDomainInt = DomainInt TagInt - -mkDomainIntB :: x -> x -> Domain () x -mkDomainIntB l u = DomainInt TagInt [RangeBounded l u] - -mkDomainIntBTagged :: IntTag -> x -> x -> Domain () x -mkDomainIntBTagged t l u = DomainInt t [RangeBounded l u] - -mkDomainAny :: Doc -> Type -> Domain r x -mkDomainAny reason = DomainAny (stringToText $ show reason) - -instance (Serialize r, Serialize x) => Serialize (Domain r x) -instance (Hashable r, Hashable x) => Hashable (Domain r x) -instance (ToJSON r, ToJSON x) => ToJSON (Domain r x) where toJSON = genericToJSON jsonOptions -instance (FromJSON r, FromJSON x) => FromJSON (Domain r x) where parseJSON = genericParseJSON jsonOptions - -instance Arbitrary x => Arbitrary (Domain r x) where - arbitrary = sized f - where - f 0 = oneof [ return DomainBool - , DomainInt TagInt <$> arbitrary - -- , DomainEnum <$> arbitrary <*> arbitrary - ] - f s = do - arity <- choose (2 :: Int, 10) - DomainTuple <$> vectorOf arity (f (div s 10)) - shrink DomainBool = [] - shrink (DomainInt _ []) = [DomainBool] - shrink (DomainInt t [r]) = DomainBool : DomainInt t [] : [DomainInt t [r'] | r' <- shrink r] - shrink (DomainInt t rs) = [DomainInt t (init rs)] - shrink _ = [] - - -typeOfDomain :: - MonadFail m => - Pretty r => - TypeOf x => - Pretty x => - (?typeCheckerMode :: TypeCheckerMode) => - Domain r x -> m Type -typeOfDomain (DomainAny _ ty) = return ty -typeOfDomain DomainBool = return TypeBool -typeOfDomain d@(DomainIntE x) = do - ty <- typeOf x - case ty of - TypeInt{} -> return () -- pre recoverDomainInt - TypeList TypeInt{} -> return () - TypeMatrix _ TypeInt{} -> return () - TypeSet TypeInt{} -> return () - _ -> fail $ vcat [ "Expected an integer, but got:" <++> pretty ty - , "In domain:" <+> pretty d - ] - return (TypeInt TagInt) -typeOfDomain d@(DomainInt t rs) = do - forM_ rs $ \ r -> forM_ r $ \ x -> do - ty <- typeOf x - case ty of - TypeInt{} -> return () - _ -> fail $ vcat [ "Expected an integer, but got:" <++> pretty ty - , "For:" <+> pretty x - , "In domain:" <+> pretty d - ] - return (TypeInt t) -typeOfDomain (DomainEnum defn _ _ ) = return (TypeEnum defn) -typeOfDomain (DomainUnnamed defn _ ) = return (TypeUnnamed defn) -typeOfDomain (DomainTuple xs ) = TypeTuple <$> mapM typeOfDomain xs -typeOfDomain (DomainRecord xs ) = TypeRecord <$> sequence [ do t <- typeOfDomain d ; return (n, t) - | (n,d) <- xs ] -typeOfDomain (DomainVariant xs ) = TypeVariant <$> sequence [ do t <- typeOfDomain d ; return (n, t) - | (n,d) <- xs ] -<<<<<<< HEAD -typeOfDomain (DomainMatrix ind inn ) = TypeMatrix <$> typeOf ind <*> typeOf inn -typeOfDomain (DomainSet _ _ x ) = TypeSet <$> typeOf x -typeOfDomain (DomainMSet _ _ x ) = TypeMSet <$> typeOf x -typeOfDomain (DomainFunction _ _ x y) = TypeFunction <$> typeOf x <*> typeOf y -typeOfDomain (DomainSequence _ _ x ) = TypeSequence <$> typeOf x -typeOfDomain (DomainRelation _ _ xs ) = TypeRelation <$> mapM typeOf xs -typeOfDomain (DomainPartition _ _ x ) = TypePartition <$> typeOf x -typeOfDomain (DomainPermutation _ _ x ) = TypePermutation <$> typeOf x -======= -typeOfDomain (DomainMatrix ind inn ) = TypeMatrix <$> typeOfDomain ind <*> typeOfDomain inn -typeOfDomain (DomainSet _ _ x ) = TypeSet <$> typeOfDomain x -typeOfDomain (DomainMSet _ _ x ) = TypeMSet <$> typeOfDomain x -typeOfDomain (DomainFunction _ _ x y) = TypeFunction <$> typeOfDomain x <*> typeOfDomain y -typeOfDomain (DomainSequence _ _ x ) = TypeSequence <$> typeOfDomain x -typeOfDomain (DomainRelation _ _ xs ) = TypeRelation <$> mapM typeOfDomain xs -typeOfDomain (DomainPartition _ _ x ) = TypePartition <$> typeOfDomain x ->>>>>>> master -typeOfDomain p@(DomainOp _ ds) = do - ts <- mapM typeOfDomain ds - if typesUnify ts - then return (mostDefined ts) - else fail ("Type error in" <+> pretty p) -typeOfDomain (DomainReference _ (Just d)) = typeOfDomain d -typeOfDomain (DomainReference nm Nothing) = bug $ "typeOfDomain: DomainReference" <+> pretty nm -typeOfDomain (DomainMetaVar nm) = bug $ "typeOfDomain: DomainMetaVar &" <> pretty nm - -forgetRepr :: Domain r x -> Domain () x -forgetRepr = defRepr - -defRepr :: Default r2 => Domain r x -> Domain r2 x -defRepr = changeRepr def - -changeRepr :: r2 -> Domain r x -> Domain r2 x -changeRepr rep = go - where - go (DomainAny t ty) = DomainAny t ty - go DomainBool = DomainBool - go (DomainIntE x) = DomainIntE x - go (DomainInt t rs) = DomainInt t rs - go (DomainEnum defn rs mp) = DomainEnum defn rs mp - go (DomainUnnamed defn s) = DomainUnnamed defn s - go (DomainTuple ds) = DomainTuple (map go ds) - go (DomainRecord xs) = DomainRecord (map (second go) xs) - go (DomainVariant xs) = DomainVariant (map (second go) xs) - go (DomainMatrix index inner) = DomainMatrix index (go inner) - go (DomainSet _ attr d) = - DomainSet rep attr (go d) - go (DomainMSet _ attr d) = - DomainMSet rep attr (go d) - go (DomainFunction _ attr d1 d2) = - DomainFunction rep attr (go d1) (go d2) - go (DomainSequence _ attr d) = - DomainSequence rep attr (go d) - go (DomainRelation _ attr ds) = - DomainRelation rep attr (map go ds) - go (DomainPartition _ attr d) = DomainPartition rep attr (go d) - go (DomainPermutation _ attr d) = DomainPermutation rep attr (go d) - go (DomainOp op ds) = DomainOp op (map go ds) - go (DomainReference x r) = DomainReference x (fmap go r) - go (DomainMetaVar x) = DomainMetaVar x - - -data Tree a = Tree { rootLabel :: a, subForest :: [Tree a] } - deriving (Eq, Ord, Show, Data, Functor, Traversable, Foldable, Typeable, Generic) - -instance Serialize a => Serialize (Tree a) -instance Hashable a => Hashable (Tree a) -instance ToJSON a => ToJSON (Tree a) where toJSON = genericToJSON jsonOptions -instance FromJSON a => FromJSON (Tree a) where parseJSON = genericParseJSON jsonOptions - --- | This is to be used when defining `Conjure.Representations.Internal.mkOutName`. --- Reason is to avoid sharing variables for parts of the same decision variable with differing representations. --- Example case: --- (1) find x : set {A} of (int(a..b) , set {B} of int(c..d)) --- (2) find x : set {A} of (int(a..b) , set {C} of int(c..d)) --- Here x_1's should not be shared! --- If they are, the channelling and symmetry breaking constraints will clash and solutions will be lost. -reprTreeEncoded :: Domain HasRepresentation x -> Text -reprTreeEncoded = mconcat . enc1 . reprTree - where - enc1 (Tree lbl sub) = - maybe - (bug "reprTreeEncoded: top-most representation is Nothing") - representationToShortText - lbl - : concatMap enc sub - enc (Tree lbl sub) = - maybe [] representationConstrIndex lbl - ++ concatMap enc sub - -reprTree :: Domain r x -> Tree (Maybe r) -reprTree DomainAny{} = Tree Nothing [] -reprTree DomainBool{} = Tree Nothing [] -reprTree DomainIntE{} = Tree Nothing [] -reprTree DomainInt{} = Tree Nothing [] -reprTree DomainEnum{} = Tree Nothing [] -reprTree DomainUnnamed{} = Tree Nothing [] -reprTree (DomainTuple as ) = Tree Nothing (map reprTree as) -reprTree (DomainRecord as ) = Tree Nothing (map (reprTree . snd) as) -reprTree (DomainVariant as) = Tree Nothing (map (reprTree . snd) as) -reprTree (DomainMatrix _ a) = Tree Nothing [reprTree a] -reprTree (DomainSet r _ a ) = Tree (Just r) [reprTree a] -reprTree (DomainMSet r _ a ) = Tree (Just r) [reprTree a] -reprTree (DomainFunction r _ a b) = Tree (Just r) [reprTree a, reprTree b] -reprTree (DomainSequence r _ a ) = Tree (Just r) [reprTree a] -reprTree (DomainRelation r _ as ) = Tree (Just r) (map reprTree as) -reprTree (DomainPartition r _ a ) = Tree (Just r) [reprTree a] -reprTree (DomainPermutation r _ a) = Tree (Just r) [reprTree a] -reprTree DomainOp{} = Tree Nothing [] -reprTree DomainReference{} = Tree Nothing [] -reprTree DomainMetaVar{} = Tree Nothing [] - -reprAtTopLevel :: Domain r x -> Maybe r -reprAtTopLevel = rootLabel . reprTree - -applyReprTree :: (MonadFail m, Pretty x, Pretty r2, Default r) => Domain r2 x -> Tree (Maybe r) -> m (Domain r x) -applyReprTree dom@DomainBool{} (Tree Nothing []) = return (defRepr dom) -applyReprTree dom@DomainInt{} (Tree Nothing []) = return (defRepr dom) -applyReprTree dom@DomainIntE{} (Tree Nothing []) = return (defRepr dom) -applyReprTree dom@DomainEnum{} (Tree Nothing []) = return (defRepr dom) -applyReprTree dom@DomainUnnamed{} (Tree Nothing []) = return (defRepr dom) -applyReprTree (DomainTuple as ) (Tree Nothing asRepr) = - DomainTuple <$> zipWithM applyReprTree as asRepr -applyReprTree (DomainRecord as ) (Tree Nothing asRepr) = - (DomainRecord . zip (map fst as)) <$> zipWithM applyReprTree (map snd as) asRepr -applyReprTree (DomainVariant as) (Tree Nothing asRepr) = - (DomainVariant . zip (map fst as)) <$> zipWithM applyReprTree (map snd as) asRepr -applyReprTree (DomainMatrix b a) (Tree Nothing [aRepr]) = DomainMatrix b <$> applyReprTree a aRepr -applyReprTree (DomainSet _ attr a ) (Tree (Just r) [aRepr]) = DomainSet r attr <$> applyReprTree a aRepr -applyReprTree (DomainMSet _ attr a ) (Tree (Just r) [aRepr]) = DomainMSet r attr <$> applyReprTree a aRepr -applyReprTree (DomainFunction _ attr a b) (Tree (Just r) [aRepr, bRepr]) = DomainFunction r attr <$> applyReprTree a aRepr <*> applyReprTree b bRepr -applyReprTree (DomainSequence _ attr a ) (Tree (Just r) [aRepr]) = DomainSequence r attr <$> applyReprTree a aRepr -applyReprTree (DomainRelation _ attr as ) (Tree (Just r) asRepr) = DomainRelation r attr <$> zipWithM applyReprTree as asRepr -applyReprTree (DomainPartition _ attr a ) (Tree (Just r) [aRepr]) = DomainPartition r attr <$> applyReprTree a aRepr -applyReprTree (DomainPermutation _ attr a ) (Tree (Just r) [aRepr]) = DomainPermutation r attr <$> applyReprTree a aRepr -applyReprTree dom@DomainOp{} (Tree Nothing []) = return (defRepr dom) -applyReprTree dom@DomainReference{} (Tree Nothing []) = return (defRepr dom) -applyReprTree dom@DomainMetaVar{} (Tree Nothing []) = return (defRepr dom) -applyReprTree dom _ = fail $ "applyReprTree:" <++> pretty dom - -isPrimitiveDomain :: Domain r x -> Bool -isPrimitiveDomain DomainBool{} = True -isPrimitiveDomain DomainIntE{} = True -isPrimitiveDomain DomainInt{} = True -isPrimitiveDomain (DomainMatrix index inner) = and [isPrimitiveDomain index, isPrimitiveDomain inner] -isPrimitiveDomain _ = False - -getIndices :: Domain r x -> ([Domain () x], Domain r x) -getIndices (DomainMatrix index inner) = first (index:) (getIndices inner) -getIndices d = ([], d) - -domainCanIndexMatrix :: Domain r x -> Bool -domainCanIndexMatrix DomainBool{} = True -domainCanIndexMatrix DomainInt {} = True -domainCanIndexMatrix DomainIntE{} = True -domainCanIndexMatrix DomainEnum{} = True -domainCanIndexMatrix _ = False - - --------------------------------------------------------------------------------- --- attribute-as-constraint handling -------------------------------------------- --------------------------------------------------------------------------------- - -data AttrName - = AttrName_size - | AttrName_minSize - | AttrName_maxSize - | AttrName_minOccur - | AttrName_maxOccur - | AttrName_numParts - | AttrName_minNumParts - | AttrName_maxNumParts - | AttrName_partSize - | AttrName_minPartSize - | AttrName_maxPartSize - | AttrName_total - | AttrName_injective - | AttrName_surjective - | AttrName_bijective - | AttrName_regular - -- bin rel ones - | AttrName_reflexive - | AttrName_irreflexive - | AttrName_coreflexive - | AttrName_symmetric - | AttrName_antiSymmetric - | AttrName_aSymmetric - | AttrName_transitive - | AttrName_connex - | AttrName_Euclidean - | AttrName_serial - | AttrName_equivalence - | AttrName_partialOrder - deriving (Eq, Ord, Show, Data, Typeable, Generic) - -instance Serialize AttrName -instance Hashable AttrName -instance ToJSON AttrName where toJSON = genericToJSON jsonOptions -instance FromJSON AttrName where parseJSON = genericParseJSON jsonOptions - -instance Pretty AttrName where - pretty AttrName_size = "size" - pretty AttrName_minSize = "minSize" - pretty AttrName_maxSize = "maxSize" - pretty AttrName_minOccur = "minOccur" - pretty AttrName_maxOccur = "maxOccur" - pretty AttrName_numParts = "numParts" - pretty AttrName_minNumParts = "minNumParts" - pretty AttrName_maxNumParts = "maxNumParts" - pretty AttrName_partSize = "partSize" - pretty AttrName_minPartSize = "minPartSize" - pretty AttrName_maxPartSize = "maxPartSize" - pretty AttrName_total = "total" - pretty AttrName_injective = "injective" - pretty AttrName_surjective = "surjective" - pretty AttrName_bijective = "bijective" - pretty AttrName_regular = "regular" - pretty AttrName_reflexive = "reflexive" - pretty AttrName_irreflexive = "irreflexive" - pretty AttrName_coreflexive = "coreflexive" - pretty AttrName_symmetric = "symmetric" - pretty AttrName_antiSymmetric = "antiSymmetric" - pretty AttrName_aSymmetric = "aSymmetric" - pretty AttrName_transitive = "transitive" - pretty AttrName_connex = "connex" - pretty AttrName_Euclidean = "Euclidean" - pretty AttrName_serial = "serial" - pretty AttrName_equivalence = "equivalence" - pretty AttrName_partialOrder = "partialOrder" - -instance IsString AttrName where - fromString "size" = AttrName_size - fromString "minSize" = AttrName_minSize - fromString "maxSize" = AttrName_maxSize - fromString "minOccur" = AttrName_minOccur - fromString "maxOccur" = AttrName_maxOccur - fromString "numParts" = AttrName_numParts - fromString "minNumParts" = AttrName_minNumParts - fromString "maxNumParts" = AttrName_maxNumParts - fromString "partSize" = AttrName_partSize - fromString "minPartSize" = AttrName_minPartSize - fromString "maxPartSize" = AttrName_maxPartSize - fromString "total" = AttrName_total - fromString "injective" = AttrName_injective - fromString "surjective" = AttrName_surjective - fromString "bijective" = AttrName_bijective - fromString "regular" = AttrName_regular - fromString "reflexive" = AttrName_reflexive - fromString "irreflexive" = AttrName_irreflexive - fromString "coreflexive" = AttrName_coreflexive - fromString "symmetric" = AttrName_symmetric - fromString "antiSymmetric" = AttrName_antiSymmetric - fromString "aSymmetric" = AttrName_aSymmetric - fromString "transitive" = AttrName_transitive - fromString "connex" = AttrName_connex - fromString "Euclidean" = AttrName_Euclidean - fromString "serial" = AttrName_serial - fromString "equivalence" = AttrName_equivalence - fromString "partialOrder" = AttrName_partialOrder - fromString s = bug $ "fromString{AttrName}:" <+> pretty s - - --------------------------------------------------------------------------------- --- attribute definitions ------------------------------------------------------- --------------------------------------------------------------------------------- - -data SetAttr a = SetAttr (SizeAttr a) - deriving (Eq, Ord, Show, Data, Functor, Traversable, Foldable, Typeable, Generic) -instance Serialize a => Serialize (SetAttr a) -instance Hashable a => Hashable (SetAttr a) -instance ToJSON a => ToJSON (SetAttr a) where toJSON = genericToJSON jsonOptions -instance FromJSON a => FromJSON (SetAttr a) where parseJSON = genericParseJSON jsonOptions -instance Default (SetAttr a) where def = SetAttr def -instance Pretty a => Pretty (SetAttr a) where - pretty (SetAttr SizeAttr_None) = prEmpty - pretty (SetAttr a) = prParens (pretty a) - - -data SizeAttr a - = SizeAttr_None - | SizeAttr_Size a - | SizeAttr_MinSize a - | SizeAttr_MaxSize a - | SizeAttr_MinMaxSize a a - deriving (Eq, Ord, Show, Data, Functor, Traversable, Foldable, Typeable, Generic) -instance Serialize a => Serialize (SizeAttr a) -instance Hashable a => Hashable (SizeAttr a) -instance ToJSON a => ToJSON (SizeAttr a) where toJSON = genericToJSON jsonOptions -instance FromJSON a => FromJSON (SizeAttr a) where parseJSON = genericParseJSON jsonOptions -instance Default (SizeAttr a) where def = SizeAttr_None -instance Pretty a => Pretty (SizeAttr a) where - pretty SizeAttr_None = prEmpty - pretty (SizeAttr_Size x ) = "size" <+> pretty x - pretty (SizeAttr_MinSize x ) = "minSize" <+> pretty x - pretty (SizeAttr_MaxSize x ) = "maxSize" <+> pretty x - pretty (SizeAttr_MinMaxSize x y) = "minSize" <+> pretty x <> ", maxSize" <+> pretty y - - -getMaxFrom_SizeAttr :: MonadFail m => SizeAttr a -> m a -getMaxFrom_SizeAttr (SizeAttr_Size n) = return n -getMaxFrom_SizeAttr (SizeAttr_MaxSize n) = return n -getMaxFrom_SizeAttr (SizeAttr_MinMaxSize _ n) = return n -getMaxFrom_SizeAttr _ = fail "getMaxFrom_SizeAttr" - - -data MSetAttr a = MSetAttr (SizeAttr a) (OccurAttr a) - deriving (Eq, Ord, Show, Data, Functor, Traversable, Foldable, Typeable, Generic) -instance Serialize a => Serialize (MSetAttr a) -instance Hashable a => Hashable (MSetAttr a) -instance ToJSON a => ToJSON (MSetAttr a) where toJSON = genericToJSON jsonOptions -instance FromJSON a => FromJSON (MSetAttr a) where parseJSON = genericParseJSON jsonOptions -instance Default (MSetAttr a) where def = MSetAttr def def -instance Pretty a => Pretty (MSetAttr a) where - pretty (MSetAttr a b) = - let inside = filter (/=prEmpty) [ pretty a - , pretty b - ] - in if null inside - then prEmpty - else prettyList prParens "," inside - - -data OccurAttr a - = OccurAttr_None - | OccurAttr_MinOccur a - | OccurAttr_MaxOccur a - | OccurAttr_MinMaxOccur a a - deriving (Eq, Ord, Show, Data, Functor, Traversable, Foldable, Typeable, Generic) -instance Serialize a => Serialize (OccurAttr a) -instance Hashable a => Hashable (OccurAttr a) -instance ToJSON a => ToJSON (OccurAttr a) where toJSON = genericToJSON jsonOptions -instance FromJSON a => FromJSON (OccurAttr a) where parseJSON = genericParseJSON jsonOptions -instance Default (OccurAttr a) where def = OccurAttr_None -instance Pretty a => Pretty (OccurAttr a) where - pretty OccurAttr_None = prEmpty - pretty (OccurAttr_MinOccur x ) = "minOccur" <+> pretty x - pretty (OccurAttr_MaxOccur x ) = "maxOccur" <+> pretty x - pretty (OccurAttr_MinMaxOccur x y) = "minOccur" <+> pretty x <> ", maxOccur" <+> pretty y - - -getMaxFrom_OccurAttr :: MonadFail m => OccurAttr a -> m a -getMaxFrom_OccurAttr (OccurAttr_MaxOccur n) = return n -getMaxFrom_OccurAttr (OccurAttr_MinMaxOccur _ n) = return n -getMaxFrom_OccurAttr _ = fail "getMaxFrom_OccurAttr" - - -data FunctionAttr x - = FunctionAttr (SizeAttr x) PartialityAttr JectivityAttr - deriving (Eq, Ord, Show, Data, Functor, Traversable, Foldable, Typeable, Generic) -instance Serialize a => Serialize (FunctionAttr a) -instance Hashable a => Hashable (FunctionAttr a) -instance ToJSON a => ToJSON (FunctionAttr a) where toJSON = genericToJSON jsonOptions -instance FromJSON a => FromJSON (FunctionAttr a) where parseJSON = genericParseJSON jsonOptions -instance Default (FunctionAttr a) where def = FunctionAttr def def def -instance Pretty a => Pretty (FunctionAttr a) where - pretty (FunctionAttr a b c) = - let inside = filter (/=prEmpty) [pretty a, pretty b, pretty c] - in if null inside - then prEmpty - else prettyList prParens "," inside - - -data PartialityAttr - = PartialityAttr_Partial - | PartialityAttr_Total - deriving (Eq, Ord, Show, Data, Typeable, Generic) -instance Serialize PartialityAttr -instance Hashable PartialityAttr -instance ToJSON PartialityAttr where toJSON = genericToJSON jsonOptions -instance FromJSON PartialityAttr where parseJSON = genericParseJSON jsonOptions -instance Default PartialityAttr where def = PartialityAttr_Partial -instance Pretty PartialityAttr where - pretty PartialityAttr_Partial = prEmpty -- partial is the default - pretty PartialityAttr_Total = "total" - - -data JectivityAttr - = JectivityAttr_None - | JectivityAttr_Injective - | JectivityAttr_Surjective - | JectivityAttr_Bijective - deriving (Eq, Ord, Show, Data, Typeable, Generic) -instance Serialize JectivityAttr -instance Hashable JectivityAttr -instance ToJSON JectivityAttr where toJSON = genericToJSON jsonOptions -instance FromJSON JectivityAttr where parseJSON = genericParseJSON jsonOptions -instance Default JectivityAttr where def = JectivityAttr_None -instance Pretty JectivityAttr where - pretty JectivityAttr_None = prEmpty - pretty JectivityAttr_Injective = "injective" - pretty JectivityAttr_Surjective = "surjective" - pretty JectivityAttr_Bijective = "bijective" - - -data SequenceAttr x - = SequenceAttr (SizeAttr x) JectivityAttr - deriving (Eq, Ord, Show, Data, Functor, Traversable, Foldable, Typeable, Generic) -instance Serialize a => Serialize (SequenceAttr a) -instance Hashable a => Hashable (SequenceAttr a) -instance ToJSON a => ToJSON (SequenceAttr a) where toJSON = genericToJSON jsonOptions -instance FromJSON a => FromJSON (SequenceAttr a) where parseJSON = genericParseJSON jsonOptions -instance Default (SequenceAttr a) where def = SequenceAttr def def -instance Pretty a => Pretty (SequenceAttr a) where - pretty (SequenceAttr a b) = - let inside = filter (/=prEmpty) [pretty a, pretty b] - in if null inside - then prEmpty - else prettyList prParens "," inside - - -data RelationAttr a = RelationAttr (SizeAttr a) BinaryRelationAttrs - deriving (Eq, Ord, Show, Data, Functor, Traversable, Foldable, Typeable, Generic) -instance Serialize a => Serialize (RelationAttr a) -instance Hashable a => Hashable (RelationAttr a) -instance ToJSON a => ToJSON (RelationAttr a) where toJSON = genericToJSON jsonOptions -instance FromJSON a => FromJSON (RelationAttr a) where parseJSON = genericParseJSON jsonOptions -instance Default (RelationAttr a) where def = RelationAttr def def -instance Pretty a => Pretty (RelationAttr a) where - pretty (RelationAttr a b) = - let inside = filter (/=prEmpty) [pretty a, pretty b] - in if null inside - then prEmpty - else prettyList prParens "," inside - - -data BinaryRelationAttrs = BinaryRelationAttrs (S.Set BinaryRelationAttr) - deriving (Eq, Ord, Show, Data, Typeable, Generic) -instance Serialize BinaryRelationAttrs -instance Hashable BinaryRelationAttrs where hashWithSalt salt (BinaryRelationAttrs a) = hashWithSalt salt (S.toList a) -instance ToJSON BinaryRelationAttrs where toJSON = genericToJSON jsonOptions -instance FromJSON BinaryRelationAttrs where parseJSON = genericParseJSON jsonOptions -instance Default BinaryRelationAttrs where def = BinaryRelationAttrs S.empty -instance Pretty BinaryRelationAttrs where - pretty (BinaryRelationAttrs attrs) = prettyList id "," (S.toList attrs) -instance Semigroup BinaryRelationAttrs where - (<>) = mappend -instance Monoid BinaryRelationAttrs where - mempty = BinaryRelationAttrs def - mappend (BinaryRelationAttrs a) (BinaryRelationAttrs b) = BinaryRelationAttrs (S.union a b) - - -data BinaryRelationAttr - = BinRelAttr_Reflexive - | BinRelAttr_Irreflexive - | BinRelAttr_Coreflexive - | BinRelAttr_Symmetric - | BinRelAttr_AntiSymmetric - | BinRelAttr_ASymmetric - | BinRelAttr_Transitive - | BinRelAttr_Total - | BinRelAttr_Connex - | BinRelAttr_Euclidean - | BinRelAttr_Serial - | BinRelAttr_Equivalence - | BinRelAttr_PartialOrder - deriving (Eq, Ord, Show, Data, Typeable, Generic) -instance Serialize BinaryRelationAttr -instance Hashable BinaryRelationAttr -instance ToJSON BinaryRelationAttr where toJSON = genericToJSON jsonOptions -instance FromJSON BinaryRelationAttr where parseJSON = genericParseJSON jsonOptions -instance Pretty BinaryRelationAttr where - pretty BinRelAttr_Reflexive = "reflexive" - pretty BinRelAttr_Irreflexive = "irreflexive" - pretty BinRelAttr_Coreflexive = "coreflexive" - pretty BinRelAttr_Symmetric = "symmetric" - pretty BinRelAttr_AntiSymmetric = "antiSymmetric" - pretty BinRelAttr_ASymmetric = "aSymmetric" - pretty BinRelAttr_Transitive = "transitive" - pretty BinRelAttr_Total = "total" - pretty BinRelAttr_Connex = "connex" - pretty BinRelAttr_Euclidean = "Euclidean" - pretty BinRelAttr_Serial = "serial" - pretty BinRelAttr_Equivalence = "equivalence" - pretty BinRelAttr_PartialOrder = "partialOrder" - -readBinRel :: MonadFail m => AttrName -> m BinaryRelationAttr -readBinRel AttrName_reflexive = return BinRelAttr_Reflexive -readBinRel AttrName_irreflexive = return BinRelAttr_Irreflexive -readBinRel AttrName_coreflexive = return BinRelAttr_Coreflexive -readBinRel AttrName_symmetric = return BinRelAttr_Symmetric -readBinRel AttrName_antiSymmetric = return BinRelAttr_AntiSymmetric -readBinRel AttrName_aSymmetric = return BinRelAttr_ASymmetric -readBinRel AttrName_transitive = return BinRelAttr_Transitive -readBinRel AttrName_total = return BinRelAttr_Total -readBinRel AttrName_connex = return BinRelAttr_Connex -readBinRel AttrName_Euclidean = return BinRelAttr_Euclidean -readBinRel AttrName_serial = return BinRelAttr_Serial -readBinRel AttrName_equivalence = return BinRelAttr_Equivalence -readBinRel AttrName_partialOrder = return BinRelAttr_PartialOrder -readBinRel a = fail $ "Not a binary relation attribute:" <+> pretty a - -binRelToAttrName :: BinaryRelationAttr -> AttrName -binRelToAttrName BinRelAttr_Reflexive = AttrName_reflexive -binRelToAttrName BinRelAttr_Irreflexive = AttrName_irreflexive -binRelToAttrName BinRelAttr_Coreflexive = AttrName_coreflexive -binRelToAttrName BinRelAttr_Symmetric = AttrName_symmetric -binRelToAttrName BinRelAttr_AntiSymmetric = AttrName_antiSymmetric -binRelToAttrName BinRelAttr_ASymmetric = AttrName_aSymmetric -binRelToAttrName BinRelAttr_Transitive = AttrName_transitive -binRelToAttrName BinRelAttr_Total = AttrName_total -binRelToAttrName BinRelAttr_Connex = AttrName_connex -binRelToAttrName BinRelAttr_Euclidean = AttrName_Euclidean -binRelToAttrName BinRelAttr_Serial = AttrName_serial -binRelToAttrName BinRelAttr_Equivalence = AttrName_equivalence -binRelToAttrName BinRelAttr_PartialOrder = AttrName_partialOrder - --- reflexive forAll x : T . rel(x,x) --- irreflexive forAll x : T . !rel(x,x) --- coreflexive forAll x,y : T . rel(x,y) -> x = y --- --- symmetric forAll x,y : T . rel(x,y) -> rel(y,x) --- antisymmetric forAll x,y : T . rel(x,y) /\ rel(y,x) -> x = y --- asymmetric forAll x,y : T . rel(x,y) -> !rel(y,x) --- --- transitive forAll x,y,z : T . rel(x,y) /\ rel(y,z) -> rel(x,z) --- --- total forAll x,y : T . rel(x,y) \/ rel(y,x) --- connex forAll x,y : T . rel(x,y) \/ rel(y,x) \/ x = y --- Euclidean forAll x,y,z : T . rel(x,y) /\ rel(x,z) -> rel(y,z) --- serial forAll x : T . exists y : T . rel(x,y) --- equivalence reflexive + symmetric + transitive --- partialOrder reflexive + antisymmetric + transitive - - -data PartitionAttr a = PartitionAttr - { partsNum :: SizeAttr a - , partsSize :: SizeAttr a - , isRegular :: Bool - } - deriving (Eq, Ord, Show, Data, Functor, Traversable, Foldable, Typeable, Generic) -instance Serialize a => Serialize (PartitionAttr a) -instance Hashable a => Hashable (PartitionAttr a) -instance ToJSON a => ToJSON (PartitionAttr a) where toJSON = genericToJSON jsonOptions -instance FromJSON a => FromJSON (PartitionAttr a) where parseJSON = genericParseJSON jsonOptions -instance Default (PartitionAttr a) where def = PartitionAttr def def False -instance Pretty a => Pretty (PartitionAttr a) where - pretty (PartitionAttr a b c) = - let inside = filter (/=prEmpty) [ prettyNum a - , prettySize b - , prettyReg c - ] - - prettyNum SizeAttr_None = prEmpty - prettyNum (SizeAttr_Size x ) = "numParts" <+> pretty x - prettyNum (SizeAttr_MinSize x ) = "minNumParts" <+> pretty x - prettyNum (SizeAttr_MaxSize x ) = "maxNumParts" <+> pretty x - prettyNum (SizeAttr_MinMaxSize x y) = "minNumParts" <+> pretty x <> ", maxNumParts" <+> pretty y - - prettySize SizeAttr_None = prEmpty - prettySize (SizeAttr_Size x ) = "partSize" <+> pretty x - prettySize (SizeAttr_MinSize x ) = "minPartSize" <+> pretty x - prettySize (SizeAttr_MaxSize x ) = "maxPartSize" <+> pretty x - prettySize (SizeAttr_MinMaxSize x y) = "minPartSize" <+> pretty x <> ", maxPartSize" <+> pretty y - - prettyReg False = prEmpty - prettyReg True = "regular" - - in if null inside - then prEmpty - else prettyList prParens "," inside - - - -data PermutationAttr x - = PermutationAttr (SizeAttr x) - deriving (Eq, Ord, Show, Data, Functor, Traversable, Foldable, Typeable, Generic) -instance Serialize a => Serialize (PermutationAttr a) -instance Hashable a => Hashable (PermutationAttr a) -instance ToJSON a => ToJSON (PermutationAttr a) where toJSON = genericToJSON jsonOptions -instance FromJSON a => FromJSON (PermutationAttr a) where parseJSON = genericParseJSON jsonOptions -instance Default (PermutationAttr a) where def = PermutationAttr def -instance Pretty a => Pretty (PermutationAttr a) where - pretty (PermutationAttr a ) = - let inside = filter (/=prEmpty) [pretty a] - in if null inside - then prEmpty - else prettyList prParens "," inside - - - - -data DomainAttributes a = DomainAttributes [DomainAttribute a] - deriving (Eq, Ord, Show, Data, Functor, Traversable, Foldable, Typeable, Generic) - -instance Serialize a => Serialize (DomainAttributes a) -instance Hashable a => Hashable (DomainAttributes a) -instance ToJSON a => ToJSON (DomainAttributes a) where toJSON = genericToJSON jsonOptions -instance FromJSON a => FromJSON (DomainAttributes a) where parseJSON = genericParseJSON jsonOptions - -instance Default (DomainAttributes a) where - def = DomainAttributes [] - - -data DomainAttribute a - = DAName Name - | DANameValue Name a - | DADotDot - deriving (Eq, Ord, Show, Data, Functor, Traversable, Foldable, Typeable, Generic) - -instance Serialize a => Serialize (DomainAttribute a) -instance Hashable a => Hashable (DomainAttribute a) -instance ToJSON a => ToJSON (DomainAttribute a) where toJSON = genericToJSON jsonOptions -instance FromJSON a => FromJSON (DomainAttribute a) where parseJSON = genericParseJSON jsonOptions - - -data Range a - = RangeOpen - | RangeSingle a - | RangeLowerBounded a - | RangeUpperBounded a - | RangeBounded a a - deriving (Eq, Ord, Show, Data, Functor, Traversable, Foldable, Typeable, Generic) - -instance Serialize a => Serialize (Range a) -instance Hashable a => Hashable (Range a) -instance ToJSON a => ToJSON (Range a) where toJSON = genericToJSON jsonOptions -instance FromJSON a => FromJSON (Range a) where parseJSON = genericParseJSON jsonOptions - -instance Arbitrary a => Arbitrary (Range a) where - arbitrary = oneof - [ return RangeOpen - , RangeSingle <$> arbitrary - , RangeLowerBounded <$> arbitrary - , RangeUpperBounded <$> arbitrary - , RangeBounded <$> arbitrary <*> arbitrary - ] - -rangesInts :: (MonadFail m, ExpressionLike c) => [Range c] -> m [Integer] -rangesInts = fmap (sortNub . concat) . mapM rangeInts - where - rangeInts (RangeSingle x) = return <$> intOut "rangeInts 1" x - rangeInts (RangeBounded x y) = do x' <- intOut "rangeInts 2" x - y' <- intOut "rangeInts 3" y - return [x' .. y'] - rangeInts _ = fail "Infinite range (or not an integer range)" - -expandRanges :: ExpressionLike c => [Range c] -> [Range c] -expandRanges r = - case rangesInts r of - Nothing -> r - Just [] -> [] - Just is -> - if [ minimum is .. maximum is ] == is - then [RangeBounded (fromInt (minimum is)) (fromInt (maximum is))] - else map (RangeSingle . fromInt) is - - -data HasRepresentation - = NoRepresentation - - | Set_Occurrence - | Set_Explicit - | Set_ExplicitVarSizeWithFlags - | Set_ExplicitVarSizeWithMarker - | Set_ExplicitVarSizeWithDummy - - | MSet_Occurrence - | MSet_ExplicitWithFlags - | MSet_ExplicitWithRepetition - - | Function_1D - | Function_1DPartial - | Function_ND - | Function_NDPartial - | Function_AsRelation HasRepresentation -- carries: representation for the inner relation - - | Sequence_ExplicitBounded - - | Relation_AsMatrix - | Relation_AsSet HasRepresentation -- carries: representation for the inner set - - | Partition_AsSet HasRepresentation HasRepresentation -- carries: representations for the inner sets - | Partition_Occurrence - | Permutation_AsFunction - - deriving (Eq, Ord, Show, Data, Typeable, Generic) - -instance Serialize HasRepresentation -instance Hashable HasRepresentation -instance ToJSON HasRepresentation where toJSON = genericToJSON jsonOptions -instance FromJSON HasRepresentation where parseJSON = genericParseJSON jsonOptions - -instance Default HasRepresentation where - def = NoRepresentation - -representationConstrIndex :: HasRepresentation -> [Text] -representationConstrIndex r = oneLevel r : concatMap representationConstrIndex (children r) - where - oneLevel :: HasRepresentation -> Text - oneLevel = stringToText . ("R"++) . show . constrIndex . toConstr - -instance (Pretty r, Pretty a) => Pretty (Domain r a) where - - pretty DomainAny{} = "?" - - pretty DomainBool = "bool" - - pretty (DomainIntE x) = "int" <> prParens (pretty x) - - pretty (DomainInt (TagEnum nm) _) = pretty nm - pretty (DomainInt (TagUnnamed nm) _) = pretty nm - - pretty (DomainInt _ []) = "int" -<<<<<<< HEAD - - pretty (DomainInt _ ranges) = "int" <> prettyList prParens "," ranges - -======= - pretty (DomainInt _ ranges) = "int" <> prettyList prParens "," ranges - ->>>>>>> master - pretty (DomainEnum name (Just ranges) _) = pretty name <> prettyList prParens "," ranges - - pretty (DomainEnum name _ _) = pretty name - - pretty (DomainUnnamed name _) = pretty name - - pretty (DomainTuple inners) - = (if length inners < 2 then "tuple" else prEmpty) - <+> prettyList prParens "," inners - - pretty (DomainRecord xs) = "record" <+> prettyList prBraces "," - [ pretty nm <+> ":" <+> pretty d | (nm, d) <- xs ] - - pretty (DomainVariant xs) = "variant" <+> prettyList prBraces "," - [ pretty nm <+> ":" <+> pretty d | (nm, d) <- xs ] - - pretty (DomainMatrix index innerNested) - = "matrix indexed by" <+> prettyList prBrackets "," indices - <+> "of" <+> pretty inner - where - (indices,inner) = first (index:) $ collect innerNested - collect (DomainMatrix i j) = first (i:) $ collect j - collect x = ([],x) - - pretty (DomainSet r attrs inner) = - hang ("set" <+> prettyAttrs r attrs <+> "of") 4 (pretty inner) - - pretty (DomainMSet r attrs inner) = - hang ("mset" <+> prettyAttrs r attrs <+> "of") 4 (pretty inner) - - pretty (DomainFunction r attrs innerFrom innerTo) = - hang ("function" <+> prettyAttrs r attrs) 4 $ - hang (pretty innerFrom) 4 $ - "-->" <+> pretty innerTo - - pretty (DomainSequence r attrs inner) = - hang ("sequence" <+> prettyAttrs r attrs <+> "of") 4 (pretty inner) - - pretty (DomainRelation r attrs inners) - = hang ("relation" <+> prettyAttrs r attrs <+> "of") 4 (prettyList prParens " *" inners) - - pretty (DomainPartition r attrs inner) - = hang ("partition" <+> prettyAttrs r attrs <+> "from") 4 (pretty inner) - pretty (DomainPermutation r attrs inner) = hang ("permutation" <+> prettyAttrs r attrs <+> "of") 4 (pretty inner) - - pretty d@DomainOp{} = pretty (show d) - - pretty (DomainReference x _) = pretty x - - pretty (DomainMetaVar x) = "&" <> pretty x - - -prettyAttrs :: (Pretty a, Pretty b) => a -> b -> Doc -prettyAttrs a bs = - let prettya = pretty a - in if prettya == "()" - then pretty bs - else prBraces prettya <+> pretty bs - -instance Pretty a => Pretty (DomainAttributes a) where - pretty (DomainAttributes []) = prEmpty - pretty (DomainAttributes attrs) = prettyList prParens "," attrs - -instance Pretty a => Pretty (DomainAttribute a) where - pretty (DAName name) = pretty name - pretty (DANameValue name value) = pretty name <+> pretty value - pretty DADotDot = ".." - -instance Pretty a => Pretty (Range a) where - pretty RangeOpen = ".." - pretty (RangeSingle x) = pretty x - pretty (RangeLowerBounded x) = pretty x <> ".." - pretty (RangeUpperBounded x) = ".." <> pretty x - pretty (RangeBounded x y) | show (pretty x) == show (pretty y) = pretty x - pretty (RangeBounded x y) = pretty x <> ".." <> pretty y - -instance Pretty HasRepresentation where - pretty NoRepresentation = "∅" - pretty r = pretty (representationToFullText r) - -textToRepresentation :: Text -> [HasRepresentation] -> Maybe HasRepresentation -textToRepresentation t [] | t == "Occurrence" = return Set_Occurrence -textToRepresentation t [] | t == "Explicit" = return Set_Explicit -textToRepresentation t [] | t == "ExplicitVarSizeWithFlags" = return Set_ExplicitVarSizeWithFlags -textToRepresentation t [] | t == "ExplicitVarSizeWithMarker" = return Set_ExplicitVarSizeWithMarker -textToRepresentation t [] | t == "ExplicitVarSizeWithDummy" = return Set_ExplicitVarSizeWithDummy -textToRepresentation t [] | t == "MOccurrence" = return MSet_Occurrence -textToRepresentation t [] | t == "ExplicitWithFlags" = return MSet_ExplicitWithFlags -textToRepresentation t [] | t == "ExplicitWithRepetition" = return MSet_ExplicitWithRepetition -textToRepresentation t [] | t == "Function1D" = return Function_1D -textToRepresentation t [] | t == "Function1DPartial" = return Function_1DPartial -textToRepresentation t [] | t == "FunctionND" = return Function_ND -textToRepresentation t [] | t == "FunctionNDPartial" = return Function_NDPartial -textToRepresentation t [repr] | t == "FunctionAsRelation" = return (Function_AsRelation repr) -textToRepresentation t [] | t == "ExplicitBounded" = return Sequence_ExplicitBounded -textToRepresentation t [] | t == "RelationAsMatrix" = return Relation_AsMatrix -textToRepresentation t [repr] | t == "RelationAsSet" = return (Relation_AsSet repr) -textToRepresentation t [repr1, repr2] | t == "PartitionAsSet" = return (Partition_AsSet repr1 repr2) -textToRepresentation t [] | t == "PartitionOccurrence" = return Partition_Occurrence -<<<<<<< HEAD -textToRepresentation t [] | t == "PermutationAsFunction" = return Permutation_AsFunction -textToRepresentation t _ = bug ("textToRepresentation:" <+> pretty t) -======= -textToRepresentation _ _ = Nothing ->>>>>>> master - -representationToShortText :: HasRepresentation -> Text -representationToShortText Set_Occurrence = "Occurrence" -representationToShortText Set_Explicit = "Explicit" -representationToShortText Set_ExplicitVarSizeWithFlags = "ExplicitVarSizeWithFlags" -representationToShortText Set_ExplicitVarSizeWithMarker = "ExplicitVarSizeWithMarker" -representationToShortText Set_ExplicitVarSizeWithDummy = "ExplicitVarSizeWithDummy" -representationToShortText MSet_Occurrence = "MOccurrence" -representationToShortText MSet_ExplicitWithFlags = "ExplicitWithFlags" -representationToShortText MSet_ExplicitWithRepetition = "ExplicitWithRepetition" -representationToShortText Function_1D = "Function1D" -representationToShortText Function_1DPartial = "Function1DPartial" -representationToShortText Function_ND = "FunctionND" -representationToShortText Function_NDPartial = "FunctionNDPartial" -representationToShortText Function_AsRelation{} = "FunctionAsRelation" -representationToShortText Sequence_ExplicitBounded = "ExplicitBounded" -representationToShortText Relation_AsMatrix = "RelationAsMatrix" -representationToShortText Relation_AsSet{} = "RelationAsSet" -representationToShortText Partition_AsSet{} = "PartitionAsSet" -representationToShortText Partition_Occurrence = "PartitionOccurrence" -representationToShortText Permutation_AsFunction = "PermutationAsFunction" -representationToShortText r = bug ("representationToShortText:" <+> pretty (show r)) - -representationToFullText :: HasRepresentation -> Text -representationToFullText (Function_AsRelation repr) = mconcat [ "FunctionAsRelation" - , "[" - , representationToFullText repr - , "]" - ] -representationToFullText (Relation_AsSet repr) = mconcat [ "RelationAsSet" - , "[" - , representationToFullText repr - , "]" - ] -representationToFullText (Partition_AsSet repr1 repr2) = mconcat [ "PartitionAsSet" - , "[" - , representationToFullText repr1 - , "," - , representationToFullText repr2 - , "]" - ] -representationToFullText r = representationToShortText r - - -normaliseDomain :: (Ord c, ExpressionLike c) => (c -> c) -> Domain r c -> Domain r c -normaliseDomain _norm DomainBool = DomainBool -normaliseDomain norm (DomainInt t rs ) = DomainInt t $ sort $ map (normaliseRange norm) (expandRanges rs) -normaliseDomain _norm (DomainEnum n Nothing mp) = DomainEnum n Nothing mp -normaliseDomain _norm (DomainEnum n (Just rs) mp) = DomainEnum n (Just $ sort rs) mp -normaliseDomain norm (DomainUnnamed n x ) = DomainUnnamed n (norm x) -normaliseDomain norm (DomainRecord doms ) = DomainRecord [ (n, normaliseDomain norm d) - | (n, d) <- doms ] -normaliseDomain norm (DomainVariant doms ) = DomainVariant [ (n, normaliseDomain norm d) - | (n, d) <- doms ] -normaliseDomain norm (DomainTuple doms ) = DomainTuple $ map (normaliseDomain norm) doms -normaliseDomain norm (DomainMatrix dom1 dom2) = DomainMatrix (normaliseDomain norm dom1) - (normaliseDomain norm dom2) -normaliseDomain norm (DomainSet r attr dom ) = DomainSet r (fmap norm attr) - (normaliseDomain norm dom) -normaliseDomain norm (DomainMSet r attr dom ) = DomainMSet r (fmap norm attr) - (normaliseDomain norm dom) -normaliseDomain norm (DomainFunction r attr dom1 dom2) = DomainFunction r (fmap norm attr) - (normaliseDomain norm dom1) - (normaliseDomain norm dom2) -normaliseDomain norm (DomainSequence r attr dom ) = DomainSequence r (fmap norm attr) - (normaliseDomain norm dom) -normaliseDomain norm (DomainRelation r attr doms ) = DomainRelation r (fmap norm attr) - (map (normaliseDomain norm) doms) -normaliseDomain norm (DomainPartition r attr dom ) = DomainPartition r (fmap norm attr) - (normaliseDomain norm dom) -normaliseDomain _norm d = d - -normaliseRange :: (c -> c) -> Range c -> Range c -normaliseRange _norm RangeOpen = RangeOpen -normaliseRange norm (RangeSingle x) = RangeBounded (norm x) (norm x) -normaliseRange norm (RangeLowerBounded x) = RangeLowerBounded (norm x) -normaliseRange norm (RangeUpperBounded x) = RangeUpperBounded (norm x) -normaliseRange norm (RangeBounded x y) = RangeBounded (norm x) (norm y) - -innerDomainOf :: (MonadFail m, Show x) => Domain () x -> m (Domain () x) -innerDomainOf (DomainMatrix _ t) = return t -innerDomainOf (DomainSet _ _ t) = return t -innerDomainOf (DomainMSet _ _ t) = return t -innerDomainOf (DomainFunction _ _ a b) = return (DomainTuple [a,b]) -innerDomainOf (DomainRelation _ _ ts) = return (DomainTuple ts) -innerDomainOf (DomainPartition _ _ t) = return (DomainSet () def t) -innerDomainOf t = fail ("innerDomainOf:" <+> pretty (show t)) - -singletonDomainInt :: (Eq x, CanBeAnAlias x) => Domain r x -> Maybe x -singletonDomainInt (DomainInt _ [RangeSingle a]) = Just a -singletonDomainInt (DomainInt _ [RangeBounded a b]) = - let - followAlias (isAlias -> Just x) = followAlias x - followAlias x = x - in - if followAlias a == followAlias b - then Just a - else Nothing -singletonDomainInt _ = Nothing - -matrixNumDimsD :: Domain r x -> Int -matrixNumDimsD (DomainMatrix _ t) = 1 + matrixNumDimsD t -matrixNumDimsD _ = 0 - diff --git a/src/Conjure/Language/Expression/Op/Defined.hs.orig b/src/Conjure/Language/Expression/Op/Defined.hs.orig deleted file mode 100644 index ffd58e4b05..0000000000 --- a/src/Conjure/Language/Expression/Op/Defined.hs.orig +++ /dev/null @@ -1,55 +0,0 @@ -{-# LANGUAGE DeriveGeneric, DeriveDataTypeable, DeriveFunctor, DeriveTraversable, DeriveFoldable, ViewPatterns #-} - -module Conjure.Language.Expression.Op.Defined where - -import Conjure.Prelude -import Conjure.Language.Expression.Op.Internal.Common - -import qualified Data.Aeson as JSON -- aeson -import qualified Data.HashMap.Strict as M -- unordered-containers -import qualified Data.Vector as V -- vector - - -data OpDefined x = OpDefined x - deriving (Eq, Ord, Show, Data, Functor, Traversable, Foldable, Typeable, Generic) - -instance Serialize x => Serialize (OpDefined x) -instance Hashable x => Hashable (OpDefined x) -instance ToJSON x => ToJSON (OpDefined x) where toJSON = genericToJSON jsonOptions -instance FromJSON x => FromJSON (OpDefined x) where parseJSON = genericParseJSON jsonOptions - -instance (Pretty x, TypeOf x) => TypeOf (OpDefined x) where - typeOf p@(OpDefined x) = do - ty <- typeOf x - case ty of - TypeFunction a _ -> return (TypeSet a) - TypePermutation a -> return (TypeSet a) - TypeSequence _ -> return (TypeSet (TypeInt TagInt)) - _ -> raiseTypeError p - -<<<<<<< HEAD -instance EvaluateOp OpDefined where - evaluateOp p | any isUndef (childrenBi p) = do - ty <- typeOf p - return $ mkUndef ty $ "Has undefined children:" <+> pretty p - evaluateOp (OpDefined (viewConstantFunction -> Just xs)) = - return $ ConstantAbstract $ AbsLitSet $ sortNub $ map fst xs - evaluateOp (OpDefined (viewConstantPermutation -> Just xss)) = - return $ ConstantAbstract $ AbsLitSet $ join xss - evaluateOp op = na $ "evaluateOp{OpDefined}:" <++> pretty (show op) - -======= ->>>>>>> master -instance SimplifyOp OpDefined x where - simplifyOp _ = na "simplifyOp{OpDefined}" - -instance Pretty x => Pretty (OpDefined x) where - prettyPrec _ (OpDefined a) = "defined" <> prParens (pretty a) - -instance VarSymBreakingDescription x => VarSymBreakingDescription (OpDefined x) where - varSymBreakingDescription (OpDefined a) = JSON.Object $ M.fromList - [ ("type", JSON.String "OpDefined") - , ("children", JSON.Array $ V.fromList - [ varSymBreakingDescription a - ]) - ] diff --git a/src/Conjure/Language/Expression/Op/Image.hs.orig b/src/Conjure/Language/Expression/Op/Image.hs.orig deleted file mode 100644 index f70ac2cc3a..0000000000 --- a/src/Conjure/Language/Expression/Op/Image.hs.orig +++ /dev/null @@ -1,106 +0,0 @@ -{-# LANGUAGE DeriveGeneric, DeriveDataTypeable, DeriveFunctor, DeriveTraversable, DeriveFoldable, ViewPatterns #-} - -module Conjure.Language.Expression.Op.Image where - -import Conjure.Prelude -import Conjure.Language.Expression.Op.Internal.Common -import Conjure.Bug - -import qualified Data.Aeson as JSON -- aeson -import qualified Data.HashMap.Strict as M -- unordered-containers -import qualified Data.Vector as V -- vector - -import Data.List (cycle) - - -data OpImage x = OpImage x x - deriving (Eq, Ord, Show, Data, Functor, Traversable, Foldable, Typeable, Generic) - -instance Serialize x => Serialize (OpImage x) -instance Hashable x => Hashable (OpImage x) -instance ToJSON x => ToJSON (OpImage x) where toJSON = genericToJSON jsonOptions -instance FromJSON x => FromJSON (OpImage x) where parseJSON = genericParseJSON jsonOptions - -instance (TypeOf x, Pretty x) => TypeOf (OpImage x) where - typeOf p@(OpImage f x) = do - tyF <- typeOf f - tyX <- typeOf x - (from, to) <- case tyF of - TypeFunction from to -> return (from, to) - TypeSequence to -> return (TypeInt TagInt, to) - TypePermutation _ -> return (tyX, tyX) - _ -> raiseTypeError $ "(function application)" <+> pretty p - if typesUnify [tyX, from] - then return to - else raiseTypeError $ vcat - [ pretty p - , "function :" <+> pretty f - , "function type:" <+> pretty (TypeFunction from to) - , "argument :" <+> pretty x - , "argument type:" <+> pretty tyX - ] - -<<<<<<< HEAD -instance EvaluateOp OpImage where - evaluateOp (OpImage f@(viewConstantFunction -> Just xs) a) = - case [ y | (x,y) <- xs, a == x ] of - [y] -> return y - [] -> do - TypeFunction _ tyTo <- typeOf f - return $ mkUndef tyTo $ vcat - [ "Function is not defined at this point:" <+> pretty a - , "Function value:" <+> pretty f - ] - _ -> do - TypeFunction _ tyTo <- typeOf f - return $ mkUndef tyTo $ vcat - [ "Function is multiply defined at this point:" <+> pretty a - , "Function value:" <+> pretty f - ] - evaluateOp (OpImage f@(viewConstantSequence -> Just xs) a) = - case [ y | (x,y) <- zip allNats xs, a == fromInt x ] of - [y] -> return y - [] -> do - TypeSequence tyTo <- typeOf f - return $ mkUndef tyTo $ vcat - [ "Sequence is not defined at this point:" <+> pretty a - , "Sequence value:" <+> pretty f - ] - _ -> do - TypeSequence tyTo <- typeOf f - return $ mkUndef tyTo $ vcat - [ "Sequence is multiply defined at this point:" <+> pretty a - , "Sequence value:" <+> pretty f - ] - evaluateOp (OpImage p@(viewConstantPermutation -> Just xss) i) = do - (TypePermutation ip) <- typeOf p - ti <- typeOf i - if typesUnify [ti, ip] - then case filter (i `elem`) xss of - [] -> return i - [h] -> do - case length $ filter (== i) h of - 1 -> return $ head $ drop 1 $ dropWhile (/= i) $ cycle h - _ -> bug "evaluateOp{OpImage} element in cycle of permutationmore than once" - _ -> bug "evaluateOp{OpPermute} element in more than one cycle of permutation" - else if ti `containsType` ip - then na "refinement required to evaluate image of permutation" - else return i - evaluateOp op = na $ "evaluateOp{OpImage}:" <++> pretty (show op) - -======= ->>>>>>> master -instance SimplifyOp OpImage x where - simplifyOp _ = na "simplifyOp{OpImage}" - -instance Pretty x => Pretty (OpImage x) where - prettyPrec _ (OpImage a b) = "image" <> prettyList prParens "," [a,b] - -instance VarSymBreakingDescription x => VarSymBreakingDescription (OpImage x) where - varSymBreakingDescription (OpImage a b) = JSON.Object $ M.fromList - [ ("type", JSON.String "OpImage") - , ("children", JSON.Array $ V.fromList - [ varSymBreakingDescription a - , varSymBreakingDescription b - ]) - ] diff --git a/src/Conjure/Language/Expression/Op/Inverse.hs.orig b/src/Conjure/Language/Expression/Op/Inverse.hs.orig deleted file mode 100644 index 32ddf466b1..0000000000 --- a/src/Conjure/Language/Expression/Op/Inverse.hs.orig +++ /dev/null @@ -1,67 +0,0 @@ -{-# LANGUAGE DeriveGeneric, DeriveDataTypeable, DeriveFunctor, DeriveTraversable, DeriveFoldable, ViewPatterns #-} - -module Conjure.Language.Expression.Op.Inverse where - -import Conjure.Prelude -import Conjure.Language.Expression.Op.Internal.Common - -import qualified Data.Aeson as JSON -- aeson -import qualified Data.HashMap.Strict as M -- unordered-containers -import qualified Data.Vector as V -- vector - -import Data.Permutation - - -data OpInverse x = OpInverse x x - deriving (Eq, Ord, Show, Data, Functor, Traversable, Foldable, Typeable, Generic) - -instance Serialize x => Serialize (OpInverse x) -instance Hashable x => Hashable (OpInverse x) -instance ToJSON x => ToJSON (OpInverse x) where toJSON = genericToJSON jsonOptions -instance FromJSON x => FromJSON (OpInverse x) where parseJSON = genericParseJSON jsonOptions - -instance (TypeOf x, Pretty x) => TypeOf (OpInverse x) where - typeOf p@(OpInverse f g) = do - ft <- typeOf f - case ft of - TypeFunction fFrom fTo -> do - TypeFunction gFrom gTo <- typeOf g - if typesUnify [fFrom, gTo] && typesUnify [fTo, gFrom] - then return TypeBool - else raiseTypeError p - TypePermutation fi -> do - TypePermutation gi <- typeOf g - if typesUnify [fi,gi] - then return TypeBool - else raiseTypeError p - _ -> raiseTypeError p - -<<<<<<< HEAD -instance EvaluateOp OpInverse where - evaluateOp (OpInverse (viewConstantFunction -> Just xs) (viewConstantFunction -> Just ys)) = - return $ ConstantBool $ and $ concat [ [ (j,i) `elem` ys | (i,j) <- xs ] - , [ (j,i) `elem` xs | (i,j) <- ys ] - ] - evaluateOp (OpInverse (viewConstantPermutation -> Just xs) (viewConstantPermutation -> Just ys)) = - case (toFunction <$> fromCycles xs, toFunction <$> fromCycles ys) of - (Right xfn, Right lfn) -> return $ ConstantBool $ and $ (\x -> x == lfn (xfn x)) <$> join xs - (Left (PermutationError e),_) -> na $ "evaluateOp{OpInverse}:" <++> pretty e - (_,Left (PermutationError e)) -> na $ "evaluateOp{OpInverse}:" <++> pretty e - evaluateOp op = na $ "evaluateOp{OpInverse}:" <++> pretty (show op) - -======= ->>>>>>> master -instance SimplifyOp OpInverse x where - simplifyOp _ = na "simplifyOp{OpInverse}" - -instance Pretty x => Pretty (OpInverse x) where - prettyPrec _ (OpInverse a b) = "inverse" <> prettyList prParens "," [a,b] - -instance VarSymBreakingDescription x => VarSymBreakingDescription (OpInverse x) where - varSymBreakingDescription (OpInverse a b) = JSON.Object $ M.fromList - [ ("type", JSON.String "OpInverse") - , ("children", JSON.Array $ V.fromList - [ varSymBreakingDescription a - , varSymBreakingDescription b - ]) - ] diff --git a/src/Conjure/Language/Expression/Op/Product.hs.orig b/src/Conjure/Language/Expression/Op/Product.hs.orig deleted file mode 100644 index 426c3a45d5..0000000000 --- a/src/Conjure/Language/Expression/Op/Product.hs.orig +++ /dev/null @@ -1,92 +0,0 @@ -{-# LANGUAGE DeriveGeneric, DeriveDataTypeable, DeriveFunctor, DeriveTraversable, DeriveFoldable #-} -{-# LANGUAGE UndecidableInstances #-} - -module Conjure.Language.Expression.Op.Product where - -import Conjure.Prelude -import Conjure.Language.Expression.Op.Internal.Common - -import qualified Data.Aeson as JSON -- aeson -import qualified Data.HashMap.Strict as M -- unordered-containers -import qualified Data.Vector as V -- vector - - -data OpProduct x = OpProduct x - deriving (Eq, Ord, Show, Data, Functor, Traversable, Foldable, Typeable, Generic) - -instance Serialize x => Serialize (OpProduct x) -instance Hashable x => Hashable (OpProduct x) -instance ToJSON x => ToJSON (OpProduct x) where toJSON = genericToJSON jsonOptions -instance FromJSON x => FromJSON (OpProduct x) where parseJSON = genericParseJSON jsonOptions - -instance (TypeOf x, Pretty x, ExpressionLike x) => TypeOf (OpProduct x) where - typeOf p@(OpProduct x) = do - ty <- typeOf x - innerTy <- case ty of - TypeList t -> return t - TypeMatrix _ t -> return t - TypeSet t -> return t - TypeMSet t -> return t - _ -> raiseTypeError $ vcat [ pretty p - , "The argument has type:" <+> pretty ty - ] - case innerTy of - TypeInt t | ?typeCheckerMode == RelaxedIntegerTags -> return (TypeInt t) - TypeInt TagInt -> return (TypeInt TagInt) - _ -> raiseTypeError $ vcat [ pretty p - , "The argument has type:" <+> pretty ty - ] - -instance BinaryOperator (OpProduct x) where - opLexeme _ = L_Times - -instance EvaluateOp OpProduct where - evaluateOp p | any isUndef (childrenBi p) = - return $ mkUndef (TypeInt TagInt) $ "Has undefined children:" <+> pretty p - evaluateOp p@(OpProduct x) - | Just xs <- listOut x - , any isUndef xs = -<<<<<<< HEAD - return $ mkUndef (TypeInt AnyTag) $ "Has undefined children:" <+> pretty p - evaluateOp (OpProduct x) = ConstantInt AnyTag . product <$> intsOut "OpProduct" x - --- evaluateOp p@(OpProduct x) --- | Just xs <- listOut x --- , any isUndef xs = return $ mkUndef (TypeInt NoTag) $ "Has undefined children:" <+> pretty p --- evaluateOp (OpProduct x) = ConstantInt NoTag . product <$> intsOut "OpProduct" x --- -======= - return $ mkUndef (TypeInt TagInt) $ "Has undefined children:" <+> pretty p - evaluateOp (OpProduct x) = ConstantInt TagInt . product <$> intsOut "OpProduct" x ->>>>>>> master - -instance (OpProduct x :< x) => SimplifyOp OpProduct x where - simplifyOp (OpProduct x) - | Just xs <- listOut x - , let filtered = filter (/=0) xs - , length filtered /= length xs -- there were 0's - = return 0 - simplifyOp (OpProduct x) - | Just xs <- listOut x - , let filtered = filter (/=1) xs - , length filtered /= length xs -- there were 1's - = case filtered of - [] -> return 1 - [n] -> return n - _ -> return $ inject $ OpProduct $ fromList filtered - simplifyOp _ = na "simplifyOp{OpProduct}" - -instance (Pretty x, ExpressionLike x) => Pretty (OpProduct x) where - prettyPrec prec op@(OpProduct x) | Just [a,b] <- listOut x = prettyPrecBinOp prec [op] a b - prettyPrec _ (OpProduct x) = "product" <> prParens (pretty x) - -instance (VarSymBreakingDescription x, ExpressionLike x) => VarSymBreakingDescription (OpProduct x) where - varSymBreakingDescription (OpProduct x) | Just xs <- listOut x = JSON.Object $ M.fromList - [ ("type", JSON.String "OpProduct") - , ("children", JSON.Array $ V.fromList $ map varSymBreakingDescription xs) - , ("symmetricChildren", JSON.Bool True) - ] - varSymBreakingDescription (OpProduct x) = JSON.Object $ M.fromList - [ ("type", JSON.String "OpProduct") - , ("children", varSymBreakingDescription x) - ] diff --git a/src/Conjure/Language/Expression/Op/ToSet.hs.orig b/src/Conjure/Language/Expression/Op/ToSet.hs.orig deleted file mode 100644 index 54419cda1d..0000000000 --- a/src/Conjure/Language/Expression/Op/ToSet.hs.orig +++ /dev/null @@ -1,72 +0,0 @@ -{-# LANGUAGE DeriveGeneric, DeriveDataTypeable, DeriveFunctor, DeriveTraversable, DeriveFoldable, ViewPatterns #-} - -module Conjure.Language.Expression.Op.ToSet where - -import Conjure.Prelude -import Conjure.Language.Expression.Op.Internal.Common - -import qualified Data.Aeson as JSON -- aeson -import qualified Data.HashMap.Strict as M -- unordered-containers -import qualified Data.Vector as V -- vector - -import Data.Permutation - - -data OpToSet x = OpToSet - Bool -- True means we can assume there won't be any duplicates - x - deriving (Eq, Ord, Show, Data, Functor, Traversable, Foldable, Typeable, Generic) - -instance Serialize x => Serialize (OpToSet x) -instance Hashable x => Hashable (OpToSet x) -instance ToJSON x => ToJSON (OpToSet x) where toJSON = genericToJSON jsonOptions -instance FromJSON x => FromJSON (OpToSet x) where parseJSON = genericParseJSON jsonOptions - -instance (TypeOf x, Pretty x) => TypeOf (OpToSet x) where - typeOf p@(OpToSet _ x) = do - tx <- typeOf x - case tx of - TypeRelation is -> return (TypeSet (TypeTuple is)) - TypePermutation is -> return (TypeSet (TypeTuple [is, is])) - TypeMSet i -> return (TypeSet i) - TypeFunction i j -> return (TypeSet (TypeTuple [i,j])) - TypeMatrix _ i -> return (TypeSet i) - TypeList i -> return (TypeSet i) - _ -> raiseTypeError $ vcat [ pretty p - , "The argument has type:" <+> pretty tx - ] - -<<<<<<< HEAD -instance EvaluateOp OpToSet where - evaluateOp (OpToSet _ (viewConstantMatrix -> Just (_, xs))) = - return $ ConstantAbstract $ AbsLitSet $ sortNub xs - evaluateOp (OpToSet _ (viewConstantSet -> Just xs)) = - return $ ConstantAbstract $ AbsLitSet $ sortNub xs - evaluateOp (OpToSet _ (viewConstantMSet -> Just xs)) = - return $ ConstantAbstract $ AbsLitSet $ sortNub xs - evaluateOp (OpToSet _ (viewConstantFunction -> Just xs)) = - return $ ConstantAbstract $ AbsLitSet $ sortNub [ConstantAbstract $ AbsLitTuple [a,b] | (a,b) <- xs] - evaluateOp (OpToSet _ (viewConstantRelation -> Just xs)) = - return $ ConstantAbstract $ AbsLitSet $ sortNub $ map (ConstantAbstract . AbsLitTuple) xs - evaluateOp (OpToSet _ (viewConstantPermutation -> Just xs)) = - case toFunction <$> fromCycles xs of - Left (PermutationError e) -> na $ "evaluateOp{OpToSet}:" <++> pretty e - Right fn -> return $ ConstantAbstract $ AbsLitSet $ (ConstantAbstract . AbsLitTuple) <$> ((\x -> [x, fn x]) <$> join xs) - evaluateOp op = na $ "evaluateOp{OpToSet}:" <++> pretty (show op) - -======= ->>>>>>> master -instance SimplifyOp OpToSet x where - simplifyOp _ = na "simplifyOp{OpToSet}" - -instance Pretty x => Pretty (OpToSet x) where - prettyPrec _ (OpToSet _ a) = "toSet" <> prParens (pretty a) - -instance VarSymBreakingDescription x => VarSymBreakingDescription (OpToSet x) where - varSymBreakingDescription (OpToSet b x) = JSON.Object $ M.fromList - [ ("type", JSON.String "OpToSet") - , ("children", JSON.Array $ V.fromList - [ toJSON b - , varSymBreakingDescription x - ]) - ] diff --git a/src/Conjure/Language/Expression/Op/TwoBars.hs.orig b/src/Conjure/Language/Expression/Op/TwoBars.hs.orig deleted file mode 100644 index 12f5a57f32..0000000000 --- a/src/Conjure/Language/Expression/Op/TwoBars.hs.orig +++ /dev/null @@ -1,73 +0,0 @@ -{-# LANGUAGE DeriveGeneric, DeriveDataTypeable, DeriveFunctor, DeriveTraversable, DeriveFoldable, ViewPatterns #-} -{-# LANGUAGE UndecidableInstances #-} - -module Conjure.Language.Expression.Op.TwoBars where - -import Conjure.Prelude -import Conjure.Language.Expression.Op.Internal.Common - -import qualified Data.Aeson as JSON -- aeson -import qualified Data.HashMap.Strict as M -- unordered-containers -import qualified Data.Vector as V -- vector - - -data OpTwoBars x = OpTwoBars x - deriving (Eq, Ord, Show, Data, Functor, Traversable, Foldable, Typeable, Generic) - -instance Serialize x => Serialize (OpTwoBars x) -instance Hashable x => Hashable (OpTwoBars x) -instance ToJSON x => ToJSON (OpTwoBars x) where toJSON = genericToJSON jsonOptions -instance FromJSON x => FromJSON (OpTwoBars x) where parseJSON = genericParseJSON jsonOptions - -instance (TypeOf x, Pretty x, Domain () x :< x) => TypeOf (OpTwoBars x) where - typeOf p@(OpTwoBars a) = do -<<<<<<< HEAD - ty <- typeOf a - case ty of - TypeInt _ -> return () - TypeList{} -> return () - TypeSet{} -> return () - TypeMSet{} -> return () - TypeFunction{} -> return () - TypeSequence{} -> return () - TypeRelation{} -> return () - TypePartition{} -> return () - TypePermutation{} -> return () - _ -> raiseTypeError $ vcat [ pretty p - , "Expected an integer or a collection." - , "But got:" <+> pretty ty - ] -======= - case project a of - Just (_ :: Domain () x) -> return () - Nothing -> do - ty <- typeOf a - case ty of - TypeInt _ -> return () - TypeList{} -> return () - TypeSet{} -> return () - TypeMSet{} -> return () - TypeFunction{} -> return () - TypeSequence{} -> return () - TypeRelation{} -> return () - TypePartition{} -> return () - _ -> raiseTypeError $ vcat [ pretty p - , "Expected an integer or a collection." - , "But got:" <+> pretty ty - ] ->>>>>>> master - return $ TypeInt TagInt - -instance SimplifyOp OpTwoBars x where - simplifyOp _ = na "simplifyOp{OpTwoBars}" - -instance Pretty x => Pretty (OpTwoBars x) where - prettyPrec _ (OpTwoBars a) = "|" <> pretty a <> "|" - -instance VarSymBreakingDescription x => VarSymBreakingDescription (OpTwoBars x) where - varSymBreakingDescription (OpTwoBars a) = JSON.Object $ M.fromList - [ ("type", JSON.String "OpTwoBars") - , ("children", JSON.Array $ V.fromList - [ varSymBreakingDescription a - ]) - ] diff --git a/src/Conjure/Language/Instantiate.hs.orig b/src/Conjure/Language/Instantiate.hs.orig deleted file mode 100644 index d173e5a2f7..0000000000 --- a/src/Conjure/Language/Instantiate.hs.orig +++ /dev/null @@ -1,436 +0,0 @@ -{-# LANGUAGE GeneralizedNewtypeDeriving #-} - -module Conjure.Language.Instantiate - ( instantiateExpression - , instantiateDomain - , trySimplify - , entailed - ) where - --- conjure -import Conjure.Prelude -import Conjure.Bug -import Conjure.UserError -import Conjure.Language.Definition -import Conjure.Language.Expression.Op -import Conjure.Language.Domain -import Conjure.Language.Constant -import Conjure.Language.Type -import Conjure.Language.TypeOf -import Conjure.Language.Pretty -import Conjure.Process.Enumerate ( EnumerateDomain, enumerateDomain, enumerateInConstant ) - - --- | Try to simplify an expression recursively. -trySimplify :: - MonadUserError m => - EnumerateDomain m => - (?typeCheckerMode :: TypeCheckerMode) => - Expression -> m Expression -trySimplify x = do - res <- runMaybeT $ instantiateExpression [] x - case res of - Just c -- if the expression can be evaluated into a Constant - | null [() | ConstantUndefined{} <- universe c] -- and if it doesn't contain undefined's in it - -> return (Constant c) -- evaluate to the constant - _ -> descendM trySimplify x -- otherwise, try the same on its children - - -instantiateExpression :: - MonadFail m => - EnumerateDomain m => - (?typeCheckerMode :: TypeCheckerMode) => - [(Name, Expression)] -> Expression -> m Constant -instantiateExpression ctxt x = do - constant <- normaliseConstant <$> evalStateT (instantiateE x) ctxt - case (emptyCollection constant, constant) of - (_, TypedConstant{}) -> return constant - (True, _) -> do - ty <- typeOf x - return (TypedConstant constant ty) - (False, _) -> return constant - - -instantiateDomain :: - MonadFail m => - EnumerateDomain m => - Pretty r => - Default r => - (?typeCheckerMode :: TypeCheckerMode) => - [(Name, Expression)] -> Domain r Expression -> m (Domain r Constant) -instantiateDomain ctxt x = normaliseDomain normaliseConstant <$> evalStateT (instantiateD x) ctxt - - -newtype HasUndef = HasUndef Any - deriving (Semigroup, Monoid) - -instantiateE :: - MonadFail m => - MonadState [(Name, Expression)] m => - EnumerateDomain m => - (?typeCheckerMode :: TypeCheckerMode) => - Expression -> m Constant -instantiateE (Comprehension body gensOrConds) = do - let - loop :: ( MonadFail m - , MonadState [(Name, Expression)] m - , EnumerateDomain m - ) => [GeneratorOrCondition] -> WriterT HasUndef m [Constant] - loop [] = return <$> instantiateE body - loop (Generator (GenDomainNoRepr pat domain) : rest) = do - DomainInConstant domainConstant <- instantiateE (Domain domain) - let undefinedsInsideTheDomain = - [ und - | und@ConstantUndefined{} <- universeBi domainConstant - ] - if null undefinedsInsideTheDomain - then do - enumeration <- enumerateDomain domainConstant - concatMapM - (\ val -> scope $ do - valid <- bind pat val - if valid - then loop rest - else return [] ) - enumeration - else do - tell (HasUndef (Any True)) - return [] - loop (Generator (GenDomainHasRepr pat domain) : rest) = - loop (Generator (GenDomainNoRepr (Single pat) (forgetRepr domain)) : rest) - loop (Generator (GenInExpr pat expr) : rest) = do - exprConstant <- instantiateE expr - enumeration <- enumerateInConstant exprConstant - concatMapM - (\ val -> scope $ do - valid <- bind pat val - if valid - then loop rest - else return [] ) - enumeration - loop (Condition expr : rest) = do - constant <- instantiateE expr - if constant == ConstantBool True - then loop rest - else return [] - loop (ComprehensionLetting n expr : rest) = do - constant <- instantiateE expr - valid <- bind (Single n) constant - unless valid (bug "ComprehensionLetting.bind expected to be valid") - loop rest - - - (constants, HasUndef (Any undefinedsInsideGeneratorDomains)) <- runWriterT (loop gensOrConds) - if undefinedsInsideGeneratorDomains - then do - ty <- typeOf (Comprehension body gensOrConds) - return $ ConstantUndefined - "Comprehension contains undefined values inside generator domains." - ty - else - return $ ConstantAbstract $ AbsLitMatrix - (DomainInt TagInt [RangeBounded 1 (fromInt (genericLength constants))]) - constants - -instantiateE (Reference name (Just (RecordField _ ty))) = return $ ConstantField name ty -instantiateE (Reference name (Just (VariantField _ ty))) = return $ ConstantField name ty -instantiateE (Reference _ (Just (Alias x))) = instantiateE x -instantiateE (Reference name _) = do - ctxt <- gets id - case name `lookup` ctxt of - Nothing -> fail $ vcat - $ ("No value for:" <+> pretty name) - : "Bindings in context:" - : prettyContext ctxt - Just x -> instantiateE x - -instantiateE (Constant c) = return c -instantiateE (AbstractLiteral lit) = instantiateAbsLit lit -instantiateE (Typed x ty) = TypedConstant <$> instantiateE x <*> pure ty -instantiateE (Op op) = instantiateOp op - --- "Domain () Expression"s inside expressions are handled specially -instantiateE (Domain (DomainReference _ (Just d))) = instantiateE (Domain d) -instantiateE (Domain (DomainReference name Nothing)) = do - ctxt <- gets id - case name `lookup` ctxt of - Just (Domain d) -> instantiateE (Domain d) - _ -> fail $ vcat - $ ("No value for:" <+> pretty name) - : "Bindings in context:" - : prettyContext ctxt -instantiateE (Domain domain) = DomainInConstant <$> instantiateD domain - -instantiateE (WithLocals b (AuxiliaryVars locals)) = do - forM_ locals $ \ local -> case local of - SuchThat xs -> forM_ xs $ \ x -> do - constant <- instantiateE x - case constant of - ConstantBool True -> return () - _ -> fail $ "local:" <+> pretty constant - _ -> fail $ "local:" <+> pretty local - instantiateE b - -instantiateE (WithLocals b (DefinednessConstraints locals)) = do - forM_ locals $ \ x -> do - constant <- instantiateE x - case constant of - ConstantBool True -> return () - _ -> fail $ "local:" <+> pretty constant - instantiateE b - -instantiateE x = fail $ "instantiateE:" <+> pretty (show x) - - -instantiateOp :: - MonadFail m => - MonadState [(Name, Expression)] m => - EnumerateDomain m => - (?typeCheckerMode :: TypeCheckerMode) => - Op Expression -> m Constant -instantiateOp opx = mapM instantiateE opx >>= evaluateOp . fmap normaliseConstant - - -instantiateAbsLit :: - MonadFail m => - MonadState [(Name, Expression)] m => - EnumerateDomain m => - (?typeCheckerMode :: TypeCheckerMode) => - AbstractLiteral Expression -> m Constant -instantiateAbsLit x = do - c <- mapM instantiateE x - case c of - -- for functions, if the same thing is mapped to multiple values, the result is undefined - AbsLitFunction vals -> do - let nubVals = sortNub vals - if length (sortNub (map fst nubVals)) == length nubVals - then return $ ConstantAbstract $ AbsLitFunction nubVals - else do - ty <- typeOf c - return $ ConstantUndefined "Multiple mappings for the same value." ty - _ -> return $ ConstantAbstract c - - -instantiateD :: - MonadFail m => - MonadState [(Name, Expression)] m => - EnumerateDomain m => - Pretty r => - Default r => - (?typeCheckerMode :: TypeCheckerMode) => - Domain r Expression -> m (Domain r Constant) -instantiateD (DomainAny t ty) = return (DomainAny t ty) -instantiateD DomainBool = return DomainBool -instantiateD (DomainIntE x) = do - x' <- instantiateE x - let vals = case (x', viewConstantMatrix x', viewConstantSet x') of - (ConstantInt{}, _, _) -> [x'] - (_, Just (_, xs), _) -> xs - (_, _, Just xs) -> xs - _ -> [] - return (DomainInt TagInt (map RangeSingle vals)) -instantiateD (DomainInt t ranges) = DomainInt t <$> mapM instantiateR ranges -instantiateD (DomainEnum nm Nothing _) = do - st <- gets id - case lookup nm st of - Just (Domain dom) -> instantiateD (defRepr dom) - Just _ -> fail $ ("DomainEnum not found in state, Just:" <+> pretty nm) <++> vcat (map pretty st) - Nothing -> fail $ ("DomainEnum not found in state, Nothing:" <+> pretty nm) <++> vcat (map pretty st) -instantiateD (DomainEnum nm rs0 _) = do - let fmap4 = fmap . fmap . fmap . fmap - let e2c' x = either bug id (e2c x) - rs <- transformBiM (\ x -> Constant <$> instantiateE x ) (rs0 :: Maybe [Range Expression]) - |> fmap4 e2c' - st <- gets id - mp <- forM (universeBi rs :: [Name]) $ \ n -> case lookup n st of - Just (Constant (ConstantInt _ i)) -> return (n, i) - Nothing -> fail $ "No value for member of enum domain:" <+> pretty n - Just c -> fail $ vcat [ "Incompatible value for member of enum domain:" <+> pretty nm - , " Looking up for member:" <+> pretty n - , " Expected an integer, but got:" <+> pretty c - ] - return (DomainEnum nm (rs :: Maybe [Range Constant]) (Just mp)) -instantiateD (DomainUnnamed nm s) = DomainUnnamed nm <$> instantiateE s -instantiateD (DomainTuple inners) = DomainTuple <$> mapM instantiateD inners -instantiateD (DomainRecord inners) = DomainRecord <$> sequence [ do d' <- instantiateD d ; return (n,d') - | (n,d) <- inners ] -instantiateD (DomainVariant inners) = DomainVariant <$> sequence [ do d' <- instantiateD d ; return (n,d') - | (n,d) <- inners ] -instantiateD (DomainMatrix index inner) = DomainMatrix <$> instantiateD index <*> instantiateD inner -instantiateD (DomainSet r attrs inner) = DomainSet r <$> instantiateSetAttr attrs <*> instantiateD inner -instantiateD (DomainMSet r attrs inner) = DomainMSet r <$> instantiateMSetAttr attrs <*> instantiateD inner -instantiateD (DomainFunction r attrs innerFr innerTo) = DomainFunction r <$> instantiateFunctionAttr attrs <*> instantiateD innerFr <*> instantiateD innerTo -instantiateD (DomainSequence r attrs inner) = DomainSequence r <$> instantiateSequenceAttr attrs <*> instantiateD inner -instantiateD (DomainRelation r attrs inners) = DomainRelation r <$> instantiateRelationAttr attrs <*> mapM instantiateD inners -instantiateD (DomainPartition r attrs inner) = DomainPartition r <$> instantiatePartitionAttr attrs <*> instantiateD inner -instantiateD (DomainPermutation r attrs inner) = DomainPermutation r <$> instantiatePermutationAttr attrs <*> instantiateD inner -instantiateD (DomainOp nm ds) = DomainOp nm <$> mapM instantiateD ds -instantiateD (DomainReference _ (Just d)) = instantiateD d -instantiateD (DomainReference name Nothing) = do - ctxt <- gets id - case name `lookup` ctxt of - Just (Domain d) -> instantiateD (defRepr d) - _ -> fail $ vcat - $ ("No value for:" <+> pretty name) - : "Bindings in context:" - : prettyContext ctxt -instantiateD DomainMetaVar{} = bug "instantiateD DomainMetaVar" - - -instantiateSetAttr :: - MonadFail m => - MonadState [(Name, Expression)] m => - EnumerateDomain m => - (?typeCheckerMode :: TypeCheckerMode) => - SetAttr Expression -> m (SetAttr Constant) -instantiateSetAttr (SetAttr s) = SetAttr <$> instantiateSizeAttr s - - -instantiateSizeAttr :: - MonadFail m => - MonadState [(Name, Expression)] m => - EnumerateDomain m => - (?typeCheckerMode :: TypeCheckerMode) => - SizeAttr Expression -> m (SizeAttr Constant) -instantiateSizeAttr SizeAttr_None = return SizeAttr_None -instantiateSizeAttr (SizeAttr_Size x) = SizeAttr_Size <$> instantiateE x -instantiateSizeAttr (SizeAttr_MinSize x) = SizeAttr_MinSize <$> instantiateE x -instantiateSizeAttr (SizeAttr_MaxSize x) = SizeAttr_MaxSize <$> instantiateE x -instantiateSizeAttr (SizeAttr_MinMaxSize x y) = SizeAttr_MinMaxSize <$> instantiateE x <*> instantiateE y - - -instantiateMSetAttr :: - MonadFail m => - MonadState [(Name, Expression)] m => - EnumerateDomain m => - (?typeCheckerMode :: TypeCheckerMode) => - MSetAttr Expression -> m (MSetAttr Constant) -instantiateMSetAttr (MSetAttr s o) = MSetAttr <$> instantiateSizeAttr s <*> instantiateOccurAttr o - - -instantiateOccurAttr :: - MonadFail m => - MonadState [(Name, Expression)] m => - EnumerateDomain m => - (?typeCheckerMode :: TypeCheckerMode) => - OccurAttr Expression -> m (OccurAttr Constant) -instantiateOccurAttr OccurAttr_None = return OccurAttr_None -instantiateOccurAttr (OccurAttr_MinOccur x) = OccurAttr_MinOccur <$> instantiateE x -instantiateOccurAttr (OccurAttr_MaxOccur x) = OccurAttr_MaxOccur <$> instantiateE x -instantiateOccurAttr (OccurAttr_MinMaxOccur x y) = OccurAttr_MinMaxOccur <$> instantiateE x <*> instantiateE y - - -instantiateFunctionAttr :: - MonadFail m => - MonadState [(Name, Expression)] m => - EnumerateDomain m => - (?typeCheckerMode :: TypeCheckerMode) => - FunctionAttr Expression -> m (FunctionAttr Constant) -instantiateFunctionAttr (FunctionAttr s p j) = - FunctionAttr <$> instantiateSizeAttr s - <*> pure p - <*> pure j - - -instantiateSequenceAttr :: - MonadFail m => - MonadUserError m => - MonadState [(Name, Expression)] m => - EnumerateDomain m => - (?typeCheckerMode :: TypeCheckerMode) => - SequenceAttr Expression -> m (SequenceAttr Constant) -instantiateSequenceAttr (SequenceAttr s j) = - SequenceAttr <$> instantiateSizeAttr s - <*> pure j - - -instantiateRelationAttr :: - MonadFail m => - MonadUserError m => - MonadState [(Name, Expression)] m => - EnumerateDomain m => - (?typeCheckerMode :: TypeCheckerMode) => - RelationAttr Expression -> m (RelationAttr Constant) -instantiateRelationAttr (RelationAttr s b) = RelationAttr <$> instantiateSizeAttr s <*> pure b - - -instantiatePartitionAttr :: - MonadFail m => - MonadUserError m => - MonadState [(Name, Expression)] m => - EnumerateDomain m => - (?typeCheckerMode :: TypeCheckerMode) => - PartitionAttr Expression -> m (PartitionAttr Constant) -instantiatePartitionAttr (PartitionAttr a b r) = - PartitionAttr <$> instantiateSizeAttr a - <*> instantiateSizeAttr b - <*> pure r - - -<<<<<<< HEAD -instantiatePermutationAttr - :: ( MonadFail m - , MonadUserError m - , MonadState [(Name, Expression)] m - , EnumerateDomain m - ) - => PermutationAttr Expression - -> m (PermutationAttr Constant) -instantiatePermutationAttr (PermutationAttr s) = - PermutationAttr <$> instantiateSizeAttr s - - - -instantiateR - :: ( MonadFail m - , MonadUserError m - , MonadState [(Name, Expression)] m - , EnumerateDomain m - ) - => Range Expression - -> m (Range Constant) -======= -instantiateR :: - MonadFail m => - MonadState [(Name, Expression)] m => - EnumerateDomain m => - (?typeCheckerMode :: TypeCheckerMode) => - Range Expression -> m (Range Constant) ->>>>>>> master -instantiateR RangeOpen = return RangeOpen -instantiateR (RangeSingle x) = RangeSingle <$> instantiateE x -instantiateR (RangeLowerBounded x) = RangeLowerBounded <$> instantiateE x -instantiateR (RangeUpperBounded x) = RangeUpperBounded <$> instantiateE x -instantiateR (RangeBounded x y) = RangeBounded <$> instantiateE x <*> instantiateE y - - -bind :: (Functor m, MonadState [(Name, Expression)] m) - => AbstractPattern - -> Constant - -> m Bool -- False means skip -bind (Single nm) val = modify ((nm, Constant val) :) >> return True -bind (AbsPatTuple pats) (ConstantAbstract (AbsLitTuple vals)) - | length pats == length vals = and <$> zipWithM bind pats vals -bind (AbsPatMatrix pats) (ConstantAbstract (AbsLitMatrix _ vals)) - | length pats == length vals = and <$> zipWithM bind pats vals -bind (AbsPatSet pats) (ConstantAbstract (AbsLitSet vals)) - | length pats == length vals = and <$> zipWithM bind pats vals - | otherwise = return False -bind pat val = bug $ "Instantiate.bind:" <++> vcat ["pat:" <+> pretty pat, "val:" <+> pretty val] - - --- check if the given expression can be evaluated to True --- False means it is not entailed, as opposed to "it is known to be false" -entailed :: - MonadUserError m => - EnumerateDomain m => - (?typeCheckerMode :: TypeCheckerMode) => - Expression -> m Bool -entailed x = do - -- traceM $ show $ "entailed x:" <+> pretty x - c <- trySimplify x - -- traceM $ show $ "entailed c:" <+> pretty c - case c of - Constant (ConstantBool True) -> return True - _ -> return False - diff --git a/src/Conjure/Language/Lexer.hs.orig b/src/Conjure/Language/Lexer.hs.orig deleted file mode 100644 index 9092599169..0000000000 --- a/src/Conjure/Language/Lexer.hs.orig +++ /dev/null @@ -1,623 +0,0 @@ -{-# LANGUAGE DeriveGeneric #-} - -module Conjure.Language.Lexer - ( Lexeme(..) - , LexemePos(..) - , runLexer - , textToLexeme - , lexemeText - , lexemeFace - ) where - -import Conjure.Prelude - -import Data.Char ( isAlpha, isAlphaNum ) -import qualified Data.HashMap.Strict as M -import qualified Data.Text as T -import qualified Data.Text.Read as T -import qualified Text.PrettyPrint as Pr - -import Text.Megaparsec.Pos ( SourcePos, initialPos, incSourceLine, incSourceColumn, setSourceColumn ) -import Text.Megaparsec.ShowToken ( ShowToken(..) ) - - -data LexemePos = LexemePos - Lexeme -- the lexeme - SourcePos -- source position, the beginning of this lexeme - SourcePos -- source position, just after this lexeme, including whitespace after the lexeme - deriving Show - -data Lexeme - = LIntLiteral Integer - | LIdentifier T.Text - | LMetaVar T.Text - | LComment T.Text - - -- general - | L_be - | L_from - | L_of - | L_domain - - | L_language - | L_dim - | L_find - | L_given - | L_letting - | L_where - | L_such - | L_that - | L_minimising - | L_maximising - | L_branching - | L_on - | L_heuristic - - -- type: boolean - | L_bool - | L_false - | L_true - - -- type: integer - | L_int - - -- creating a new type - | L_new - | L_type - | L_enum - - -- type tuple - | L_tuple - - -- type record - | L_record - - -- type variant - | L_variant - | L_active - - -- type: matrix - | L_matrix - | L_indexed - | L_by - - -- type set - | L_set - | L_size - | L_minSize - | L_maxSize - - -- type: mset - | L_mset - | L_minOccur - | L_maxOccur - - -- type: function - | L_function - | L_total - | L_partial - | L_injective - | L_surjective - | L_bijective - - -- type: sequence - | L_sequence - - -- type: relation - | L_relation - - -- type: partition - | L_partition - | L_regular - | L_partSize - | L_minPartSize - | L_maxPartSize - | L_numParts - | L_minNumParts - | L_maxNumParts - - -- type: permutation - | L_permutation - | L_compose - - -- operators, page 21 of the holy paper - | L_union - | L_intersect - | L_subset - | L_subsetEq - | L_supset - | L_supsetEq - | L_in - | L_max - | L_min - | L_toSet - | L_toMSet - | L_toRelation - | L_defined - | L_range - | L_restrict - | L_image - | L_imageSet - | L_preImage - | L_inverse - | L_together - | L_apart - | L_party - | L_participants - | L_parts - | L_freq - | L_hist - - | L_toInt - - -- global constraints - | L_allDiff - | L_alldifferent_except - - | L_dontCare - - | L_catchUndef - - -- matrix only operators - | L_flatten - | L_concatenate - | L_normIndices - - -- in the rule language - -- | L_lambda - -- | L_quantifier - -- | L_representation - - -- arithmetic operators - - | L_Plus -- + -- sum, infix : (int,int) -> int - | L_Minus -- - -- (subtraction, infix : (int,int) -> int) OR (unary minus : int -> int) - | L_Times -- * -- multiplication, infix : (int,int) -> int - | L_Div -- / -- integer division, infix - | L_Mod -- % -- modulo, infix - | L_Pow -- ** -- exponentiation, infix : (int,int) -> int - | L_factorial - - -- equality - - | L_Eq -- = -- equals, infix. - | L_Neq -- != -- not-equals, infix - - -- comparison - - | L_Lt -- < -- less-than, infix. - | L_Leq -- <= -- less-than-or-eq, infix. - | L_Gt -- > -- greater-than, infix. - | L_Geq -- >= -- greater-than-or-eq, infix. - - -- logical operators - - | L_And -- /\ -- logical-and, infix - | L_Or -- \/ -- logical-or, infix. - | L_Imply -- -> -- implication, infix - | L_Iff -- <-> -- iff, infix. - -- | L_Not -- ! -- negation, prefix - | L_ExclamationMark -- for poth L_Factorial and L_ExclamationMark - - -- the function arrow - - | L_LongArrow -- --> -- function domains and constants - - -- in rule language - - | L_Colon -- : -- has-domain, infix, (expr,domain) -> bool. also does pattern matching. - | L_DoubleColon -- :: -- has-type, infix, (expr,type) -> bool. also does pattern matching. - | L_At -- @ -- bubble operator. - - -- lex operators - - | L_LexGeq -- >=lex - | L_LexGt -- >lex - | L_LexLt -- <=lex - | L_LexLeq -- >>>>>> master - deriving (Eq, Ord, Show, Generic) - -instance Hashable Lexeme - -lexemeText :: Lexeme -> T.Text -lexemeText l = T.pack $ show (lexemeFace l) - -textToLexeme :: T.Text -> Maybe Lexeme -textToLexeme t = M.lookup t mapTextToLexeme - -lexemeFace :: Lexeme -> Pr.Doc -lexemeFace L_Newline = "new line" -lexemeFace L_Carriage = "\\r" -lexemeFace L_Space = "space character" -lexemeFace L_Tab = "tab character" -lexemeFace (LIntLiteral i) = Pr.integer i -lexemeFace (LIdentifier i) = Pr.text (T.unpack i) -lexemeFace (LComment i) = Pr.text (T.unpack i) -lexemeFace l = - case M.lookup l mapLexemeToText of - Nothing -> Pr.text (show l) - Just t -> Pr.text (T.unpack t) - -lexemeWidth :: Lexeme -> Int -lexemeWidth L_Carriage = 0 -lexemeWidth L_Tab = 4 -lexemeWidth (LIntLiteral i) = length (show i) -lexemeWidth (LIdentifier i) = T.length i -lexemeWidth (LComment i) = T.length i -lexemeWidth l = - case lookup l (map swap lexemes) of - Nothing -> 0 - Just t -> T.length t - -mapTextToLexeme :: M.HashMap T.Text Lexeme -mapTextToLexeme = M.fromList lexemes - -mapLexemeToText :: M.HashMap Lexeme T.Text -mapLexemeToText = M.fromList $ map swap lexemes - -lexemes :: [(T.Text, Lexeme)] -lexemes = sortBy (flip (comparing (T.length . fst))) $ map swap - [ ( L_be , "be" ) - , ( L_from , "from" ) - , ( L_of , "of" ) - , ( L_domain , "domain" ) - , ( L_language , "language" ) - , ( L_dim , "dim" ) - , ( L_find , "find" ) - , ( L_given , "given" ) - , ( L_letting , "letting" ) - , ( L_where , "where" ) - , ( L_such , "such" ) - , ( L_that , "that" ) - , ( L_minimising , "minimising" ) - , ( L_maximising , "maximising" ) - , ( L_minimising , "minimizing" ) - , ( L_maximising , "maximizing" ) - , ( L_branching , "branching" ) - , ( L_on , "on" ) - , ( L_heuristic , "heuristic" ) - - , ( L_bool, "bool" ) - , ( L_false, "false" ) - , ( L_true, "true" ) - , ( L_int, "int" ) - , ( L_new, "new" ) - , ( L_type, "type" ) - , ( L_enum, "enum" ) - , ( L_tuple, "tuple" ) - , ( L_record, "record" ) - , ( L_variant, "variant" ) - , ( L_active, "active" ) - , ( L_matrix, "matrix" ) - , ( L_indexed, "indexed" ) - , ( L_by, "by" ) - , ( L_set, "set" ) - -- , ( L_size, "size" ) - -- , ( L_minSize, "minSize" ) - -- , ( L_maxSize, "maxSize" ) - , ( L_mset, "mset" ) - -- , ( L_minOccur, "minOccur" ) - -- , ( L_maxOccur, "maxOccur" ) - , ( L_function, "function" ) - -- , ( L_total, "total" ) - -- , ( L_partial, "partial" ) - -- , ( L_injective, "injective" ) - -- , ( L_surjective, "surjective" ) - -- , ( L_bijective, "bijective" ) - , ( L_sequence, "sequence" ) - , ( L_relation, "relation" ) - , ( L_partition, "partition" ) - - , ( L_permutation, "permutation" ) - , ( L_compose, "compose") - -- , ( L_regular, "regular" ) - -- , ( L_partSize, "partSize" ) - -- , ( L_minPartSize, "minPartSize" ) - -- , ( L_maxPartSize, "maxPartSize" ) - -- , ( L_numParts, "numParts" ) - -- , ( L_minNumParts, "minNumParts" ) - -- , ( L_maxNumParts, "maxNumParts" ) - , ( L_union, "union" ) - , ( L_intersect, "intersect" ) - , ( L_subset, "subset" ) - , ( L_subsetEq, "subsetEq" ) - , ( L_supset, "supset" ) - , ( L_supsetEq, "supsetEq" ) - , ( L_in, "in" ) - , ( L_max, "max" ) - , ( L_min, "min" ) - , ( L_toSet, "toSet" ) - , ( L_toMSet, "toMSet" ) - , ( L_toRelation, "toRelation" ) - , ( L_defined, "defined" ) - , ( L_range, "range" ) - , ( L_restrict, "restrict" ) - , ( L_image, "image" ) - , ( L_imageSet, "imageSet" ) - , ( L_preImage, "preImage" ) - , ( L_inverse, "inverse" ) - , ( L_together, "together" ) - , ( L_apart, "apart" ) - , ( L_party, "party" ) - , ( L_participants, "participants" ) - , ( L_parts, "parts" ) - , ( L_freq, "freq" ) - , ( L_hist, "hist" ) - , ( L_toInt, "toInt" ) - - , ( L_allDiff, "allDiff" ) - , ( L_alldifferent_except, "alldifferent_except" ) - - , ( L_dontCare, "dontCare" ) - , ( L_catchUndef, "catchUndef" ) - - , ( L_flatten, "flatten" ) - , ( L_concatenate, "concatenate" ) - , ( L_normIndices, "normIndices" ) - -- , ( L_lambda, "lambda" ) - -- , ( L_quantifier, "quantifier" ) - -- , ( L_representation, "representation" ) - , ( L_Plus , "+" ) - , ( L_Minus , "-" ) - , ( L_Times , "*" ) - , ( L_Div , "/" ) - , ( L_Mod , "%" ) - , ( L_Pow , "**" ) - , ( L_factorial , "factorial" ) - , ( L_Eq , "=" ) - , ( L_Neq , "!=" ) - , ( L_Lt , "<" ) - , ( L_Leq , "<=" ) - , ( L_Gt , ">" ) - , ( L_Geq , ">=" ) - , ( L_And , "/\\" ) - , ( L_Or , "\\/" ) - , ( L_Imply , "->" ) - , ( L_Iff , "<->" ) - , ( L_ExclamationMark , "!" ) - , ( L_LongArrow , "-->" ) - , ( L_Colon , ":" ) - , ( L_DoubleColon , "::" ) - , ( L_At , "@" ) - , ( L_LexGeq , ">=lex" ) - , ( L_LexGt , ">lex" ) - , ( L_LexLeq , "<=lex" ) - , ( L_LexLt , "" ) - , ( L_CaseSeparator , "***" ) - - , ( L_HasRepr , "hasRepr" ) - , ( L_HasType , "hasType" ) - , ( L_HasDomain , "hasDomain" ) - , ( L_indices , "indices" ) - - , ( L_DotLt , ".<" ) - , ( L_DotLeq , ".<=" ) - , ( L_DotGt , ".>" ) - , ( L_DotGeq , ".>=" ) - - , ( L_TildeLt , "~<" ) - , ( L_TildeLeq , "~<=" ) - , ( L_TildeGt , "~>" ) - , ( L_TildeGeq , "~>=" ) - - , ( L_LeftArrow , "<-" ) - - , ( L_subsequence , "subsequence" ) - , ( L_substring , "substring" ) - , ( L_powerSet , "powerSet" ) - - , ( L_pred, "pred" ) - , ( L_succ, "succ" ) - -<<<<<<< HEAD - , ( L_tagged, "tagged" ) -======= - - , ( L_transform, "transform") ->>>>>>> master - ] - -runLexer :: MonadFail m => T.Text -> m [LexemePos] -runLexer text = do - ls <- go text - let lsPaired = calcPos (initialPos "") ls - return lsPaired - where - go t = do - let results = catMaybes $ tryLexMetaVar t - : map (tryLex t) lexemes - ++ [ tryLexIntLiteral t - , tryLexIden t - , tryLexQuotedIden t - , tryLexComment t - ] - if T.null t - then return [] - else case results of - [] -> fail ("Lexing error:" Pr.<+> Pr.text (T.unpack t)) - ((rest,lexeme):_) -> (lexeme:) <$> go rest - - -- attach source positions to lexemes - -- discard whitespace, but calculate their contribution to source positions - calcPos :: SourcePos -> [Lexeme] -> [LexemePos] - calcPos _pos [] = [] - calcPos pos (this:rest) | isLexemeSpace this -- skip if this one is whitespace - = calcPos (nextPos pos this) rest -- can only happen at the beginning - calcPos pos (this:rest) = - let (restSpaces, restNonSpace) = span isLexemeSpace rest -- eat up all the whitespace after "this" - pos' = foldl nextPos pos (this:restSpaces) - in - if null restNonSpace - then [LexemePos this pos (nextPos pos this)] -- if this is the last non-whitespace lexeme - -- do not include the whitespace after it - else LexemePos this pos pos' : calcPos pos' restNonSpace - - nextPos :: SourcePos -> Lexeme -> SourcePos - nextPos pos L_Newline = incSourceLine (setSourceColumn pos 1) 1 - nextPos pos L_Carriage = pos -- just ignore '\r's - nextPos pos l = incSourceColumn pos (lexemeWidth l) - -isLexemeSpace :: Lexeme -> Bool -isLexemeSpace L_Newline {} = True -isLexemeSpace L_Carriage{} = True -isLexemeSpace L_Tab {} = True -isLexemeSpace L_Space {} = True -isLexemeSpace LComment {} = True -isLexemeSpace _ = False - -tryLex :: T.Text -> (T.Text, Lexeme) -> Maybe (T.Text, Lexeme) -tryLex running (face,lexeme) = do - rest <- T.stripPrefix face running - if T.all isIdentifierLetter face - then - case T.uncons rest of - Just (ch, _) | isIdentifierLetter ch -> Nothing - _ -> Just (rest, lexeme) - else Just (rest, lexeme) - -tryLexIntLiteral :: T.Text -> Maybe (T.Text, Lexeme) -tryLexIntLiteral t = - case T.decimal t of - Left _ -> Nothing - Right (x, rest) -> Just (rest, LIntLiteral x) - -isIdentifierFirstLetter :: Char -> Bool -isIdentifierFirstLetter ch = isAlpha ch || ch `elem` ("_" :: String) - -isIdentifierLetter :: Char -> Bool -isIdentifierLetter ch = isAlphaNum ch || ch `elem` ("_'" :: String) - -tryLexMetaVar :: T.Text -> Maybe (T.Text, Lexeme) -tryLexMetaVar running = do - ('&', rest) <- T.uncons running - (rest2, LIdentifier iden) <- tryLexIden rest - return (rest2, LMetaVar iden) - -tryLexIden :: T.Text -> Maybe (T.Text, Lexeme) -tryLexIden running = do - let (iden,rest) = T.span isIdentifierLetter running - (ch, _) <- T.uncons running - if isIdentifierFirstLetter ch - then - if T.null iden - then Nothing - else Just (rest, LIdentifier iden) - else Nothing - -tryLexQuotedIden :: T.Text -> Maybe (T.Text, Lexeme) -tryLexQuotedIden running = do - let - go inp = do - ('\"', rest) <- T.uncons inp - go2 "\"" rest - - -- after the first " - go2 sofar inp = do - (ch, rest) <- T.uncons inp - case ch of - -- end - '\"' - | sofar /= "\"" -- so we don't allow empty strings - -> Just (rest, LIdentifier (T.pack (reverse ('\"' : sofar)))) - -- escaped - '\\' -> do - (ch2, rest2) <- T.uncons rest - case ch2 of - '\"' -> go2 ('\"':sofar) rest2 - '\\' -> go2 ('\\':sofar) rest2 - _ -> Nothing - _ -> go2 (ch:sofar) rest - go running - -tryLexComment :: T.Text -> Maybe (T.Text, Lexeme) -tryLexComment running = let (dollar,rest1) = T.span (=='$') running - in if T.null dollar - then Nothing - else let (commentLine,rest2) = T.span (/='\n') rest1 - in Just (rest2, LComment commentLine) - - -instance ShowToken [LexemePos] where - showToken = intercalate ", " . map showToken - -instance ShowToken LexemePos where - showToken (LexemePos tok _ _) = showToken tok - -instance ShowToken Lexeme where - showToken = show . lexemeFace diff --git a/src/Conjure/Language/NameResolution.hs.orig b/src/Conjure/Language/NameResolution.hs.orig deleted file mode 100644 index dae17f1247..0000000000 --- a/src/Conjure/Language/NameResolution.hs.orig +++ /dev/null @@ -1,340 +0,0 @@ -{-# LANGUAGE TupleSections #-} -{-# LANGUAGE QuasiQuotes #-} - -module Conjure.Language.NameResolution - ( resolveNames - , resolveNamesMulti - , resolveNamesX - , resolveX, resolveD -- actually internal, use with care - ) where - -import Conjure.Prelude -import Conjure.Bug -import Conjure.UserError -import Conjure.Language.Definition -import Conjure.Language.Domain -import Conjure.Language.Type -import Conjure.Language.Pretty -<<<<<<< HEAD -import Conjure.Language.Expression ( reDomExp ) -import Conjure.Language.Constant ( reDomConst ) -======= -import Conjure.Language.TH ->>>>>>> master - - -resolveNamesMulti :: - MonadFail m => - MonadLog m => - MonadUserError m => - NameGen m => - (?typeCheckerMode :: TypeCheckerMode) => - [Model] -> m [Model] -resolveNamesMulti = flip evalStateT [] . go - where - go [] = return [] - go (m:ms) = (:) <$> resolveNames_ m <*> go ms - -resolveNames :: - MonadFail m => - MonadLog m => - MonadUserError m => - NameGen m => - (?typeCheckerMode :: TypeCheckerMode) => - Model -> m Model -resolveNames = flip evalStateT [] . resolveNames_ - -resolveNames_ :: - MonadFail m => - MonadLog m => - MonadState [(Name, ReferenceTo)] m => - MonadUserError m => - NameGen m => - (?typeCheckerMode :: TypeCheckerMode) => - Model -> m Model -resolveNames_ model = do - statements <- mapM resolveStatement (mStatements model) - mapM_ check (universeBi statements) - return model { mStatements = statements } - --- this is for when a name will shadow an already existing name that is outside of this expression --- we rename the new names to avoid name shadowing -shadowing :: - MonadFail m => - MonadState [(Name, ReferenceTo)] m => - NameGen m => - Expression -> m Expression -shadowing p@(Comprehension _ is) = do - -- list of names originating from this comprehension - let generators = concat - [ names - | Generator gen <- is - , let pat = generatorPat gen - , let names = [ n | n@Name{} <- universeBi pat ] - ] - ctxt <- gets id - -- a subset of names originating from this comprehension that will shadow already existing names - let shadows = [ g | g <- generators, g `elem` map fst ctxt ] - shadowsNew <- forM shadows $ \ s -> do n <- nextName "shadow" ; return (s,n) - let f n = fromMaybe n (lookup n shadowsNew) - return (transformBi f p) -shadowing p = return p - - -resolveNamesX :: - MonadFail m => - MonadUserError m => - NameGen m => - (?typeCheckerMode :: TypeCheckerMode) => - Expression -> m Expression -resolveNamesX x = do - x' <- evalStateT (resolveX x) [] - mapM_ check (universe x') - return x' - - -check :: MonadFail m => Expression -> m () -check (Reference nm Nothing) = fail ("Undefined:" <+> pretty nm) -check _ = return () - - -resolveStatement :: - MonadFail m => - MonadState [(Name, ReferenceTo)] m => - MonadUserError m => - NameGen m => - (?typeCheckerMode :: TypeCheckerMode) => - Statement -> m Statement -resolveStatement st = - case st of - Declaration decl -> - case decl of - FindOrGiven forg nm dom -> do - dom' <- resolveD dom - modify ((nm, DeclNoRepr forg nm dom' NoRegion) :) - return (Declaration (FindOrGiven forg nm dom')) - Letting nm x -> do - x' <- resolveX x - modify ((nm, Alias x') :) - return (Declaration (Letting nm x')) - LettingDomainDefnUnnamed nm x -> do - x' <- resolveX x - modify ((nm, Alias (Domain (DomainUnnamed nm x'))) :) - return (Declaration (LettingDomainDefnUnnamed nm x')) - LettingDomainDefnEnum (Name ename) nms -> do - modify ( [ (nm, Alias (Constant (ConstantInt (TagEnum ename) i))) - | (nm, i) <- zip nms [1..] - ] ++) - return st - LettingDomainDefnEnum{} -> bug "resolveStatement, Name" - GivenDomainDefnEnum{} -> return st -- ignoring - SearchOrder xs -> SearchOrder <$> mapM resolveSearchOrder xs - SearchHeuristic nm -> do - let allowed = ["static", "sdf", "conflict", "srf", "ldf", "wdeg", "domoverwdeg"] - if nm `elem` allowed - then return (SearchHeuristic nm) - else userErr1 $ vcat [ "Invalid heuristic:" <+> pretty nm - , "Allowed values are:" <+> prettyList id "," allowed - ] - Where xs -> Where <$> mapM resolveX xs - Objective obj x -> Objective obj <$> resolveX x - SuchThat xs -> SuchThat <$> mapM resolveX xs - - -<<<<<<< HEAD - -resolveSearchOrder - :: ( MonadFail m - , MonadUserError m - , MonadState [(Name, ReferenceTo)] m - , NameGen m - , ?typeCheckerMode :: TypeCheckerMode - ) - => SearchOrder - -> m SearchOrder -======= -resolveSearchOrder :: - MonadFail m => - MonadState [(Name, ReferenceTo)] m => - MonadUserError m => - NameGen m => - (?typeCheckerMode :: TypeCheckerMode) => - SearchOrder -> m SearchOrder ->>>>>>> master -resolveSearchOrder (BranchingOn nm) = do - ctxt <- gets id - mval <- gets (lookup nm) - case mval of - Nothing -> userErr1 $ vcat $ ("Undefined reference:" <+> pretty nm) - : ("Bindings in context:" : prettyContext ctxt) - Just{} -> return (BranchingOn nm) -resolveSearchOrder (Cut x) = - let f Find = CutFind - f forg = forg - in Cut . transformBi f <$> resolveX x - - -resolveX :: - MonadFail m => - MonadState [(Name, ReferenceTo)] m => - MonadUserError m => - NameGen m => - (?typeCheckerMode :: TypeCheckerMode) => - Expression -> m Expression -resolveX (Reference nm Nothing) = do - ctxt <- gets id - mval <- gets (lookup nm) - case mval of - Nothing -> userErr1 $ vcat $ ("Undefined reference:" <+> pretty nm) - : ("Bindings in context:" : prettyContext ctxt) - Just r -> return (Reference nm (Just r)) - -resolveX p@(Reference nm (Just refto)) = do -- this is for re-resolving - mval <- gets (lookup nm) - case mval of - Nothing -> return p -- hence, do not fail if not in the context - Just DeclNoRepr{} -- if the newly found guy doesn't have a repr - | DeclHasRepr{} <- refto -- but the old one did, do not update - -> return p - Just (DeclNoRepr forg_ nm_ dom_ _) -- if the newly found guy doesn't have a repr - | DeclNoRepr _ _ _ region <- refto -- and the old one didn't have one either - -- preserve the region information - -> return (Reference nm (Just (DeclNoRepr forg_ nm_ dom_ region))) - Just (Alias r) -> do - r' <- resolveX r - return (Reference nm (Just (Alias r'))) - Just r -> - return (Reference nm (Just r)) - -resolveX (AbstractLiteral lit) = AbstractLiteral <$> resolveAbsLit lit - -resolveX (Domain x) = Domain <$> resolveD x - -resolveX p@Comprehension{} = scope $ do - p' <- shadowing p - case p' of - Comprehension x is -> do - is' <- forM is $ \ i -> case i of - Generator gen -> do - (gen', refto) <- case gen of - GenDomainNoRepr pat dom -> do - dom' <- resolveD dom - let gen'' = GenDomainNoRepr pat dom' - return - ( gen'' - , case pat of - Single nm' -> DeclNoRepr Quantified nm' dom' NoRegion - _ -> InComprehension gen'' - ) - GenDomainHasRepr nm dom -> do - dom' <- resolveD dom - return - ( GenDomainHasRepr nm dom' - , DeclHasRepr Quantified nm dom' - ) - GenInExpr pat expr -> do - expr' <- resolveX expr - let gen'' = GenInExpr pat expr' - return ( gen'' , InComprehension gen'' ) - forM_ (universeBi (generatorPat gen)) $ \ nm -> - modify ((nm, refto) :) - return (Generator gen') - Condition y -> Condition <$> resolveX y - ComprehensionLetting pat expr -> do - expr' <- resolveX expr - resolveAbsPat p pat expr' - return (ComprehensionLetting pat expr') - x' <- resolveX x - return (Comprehension x' is') - _ -> bug "NameResolution.resolveX.shadowing" - -resolveX (WithLocals body (AuxiliaryVars locals)) = scope $ do - locals' <- mapM resolveStatement locals - body' <- resolveX body - return (WithLocals body' (AuxiliaryVars locals')) - -resolveX (WithLocals body (DefinednessConstraints locals)) = scope $ do - locals' <- mapM resolveX locals - body' <- resolveX body - return (WithLocals body' (DefinednessConstraints locals')) - -resolveX x = descendM resolveX x - - -resolveD :: - MonadFail m => - MonadState [(Name, ReferenceTo)] m => - MonadUserError m => - NameGen m => - Data r => - Default r => - Pretty r => - (?typeCheckerMode :: TypeCheckerMode) => - Domain r Expression -> m (Domain r Expression) -resolveD (DomainReference _ (Just d)) = resolveD d -resolveD (DomainReference nm Nothing) = do - mval <- gets (lookup nm) - case mval of - Nothing -> userErr1 ("Undefined reference to a domain:" <+> pretty nm) - Just (Alias (Domain r)) -> resolveD (changeRepr def r) - Just x -> userErr1 ("Expected a domain, but got an expression:" <+> pretty x) -resolveD (DomainRecord ds) = fmap DomainRecord $ forM ds $ \ (n, d) -> do - d' <- resolveD d - t <- typeOfDomain d' - modify ((n, RecordField n t) :) - return (n, d') -resolveD (DomainVariant ds) = fmap DomainVariant $ forM ds $ \ (n, d) -> do - d' <- resolveD d - t <- typeOfDomain d' - modify ((n, VariantField n t) :) - return (n, d') -resolveD d = do - d' <- descendM resolveD d - mapM resolveX d' - - -resolveAbsPat :: - MonadState [(Name, ReferenceTo)] m => - MonadUserError m => - Expression -> AbstractPattern -> Expression -> m () -resolveAbsPat _ AbstractPatternMetaVar{} _ = bug "resolveAbsPat AbstractPatternMetaVar" -resolveAbsPat _ (Single nm) x = modify ((nm, Alias x) :) -resolveAbsPat context (AbsPatTuple ps) x = - sequence_ [ resolveAbsPat context p [essence| &x[&i] |] - | (p, i_) <- zip ps allNats - , let i = fromInt i_ - ] -resolveAbsPat context (AbsPatMatrix ps) x = - sequence_ [ resolveAbsPat context p [essence| &x[&i] |] - | (p, i_) <- zip ps allNats - , let i = fromInt i_ - ] -resolveAbsPat context (AbsPatSet ps) x = do - ys <- case x of - Constant (ConstantAbstract (AbsLitSet xs)) -> return (map Constant xs) - AbstractLiteral (AbsLitSet xs) -> return xs - _ -> userErr1 $ "Abstract set pattern cannot be used in this context:" <++> pretty context - sequence_ [ resolveAbsPat context p y - | (p,y) <- zip ps ys - ] - - -resolveAbsLit :: - MonadFail m => - MonadState [(Name, ReferenceTo)] m => - MonadUserError m => - NameGen m => - (?typeCheckerMode :: TypeCheckerMode) => - AbstractLiteral Expression -> m (AbstractLiteral Expression) -resolveAbsLit (AbsLitVariant Nothing n x) = do - x' <- resolveX x - mval <- gets id - let - isTheVariant (Alias (Domain d@(DomainVariant nms))) | Just{} <- lookup n nms = Just d - isTheVariant _ = Nothing - case mapMaybe (isTheVariant . snd) mval of - (DomainVariant dom:_) -> return (AbsLitVariant (Just dom) n x') - _ -> return (AbsLitVariant Nothing n x') -resolveAbsLit lit = (descendBiM resolveX >=> descendBiM resolveD') lit - where - resolveD' d = resolveD (d :: Domain () Expression) diff --git a/src/Conjure/Representations.hs.orig b/src/Conjure/Representations.hs.orig deleted file mode 100644 index 8d82ac7364..0000000000 --- a/src/Conjure/Representations.hs.orig +++ /dev/null @@ -1,234 +0,0 @@ -{-# LANGUAGE QuasiQuotes #-} - -module Conjure.Representations - ( downD, downC, up - , downD1, downC1, up1 - , downToX1 - , reprOptions, getStructurals - , symmetryOrdering - , reprsStandardOrderNoLevels, reprsStandardOrder, reprsSparseOrder - , downX1 - , downX - ) where - --- conjure -import Conjure.Prelude -import Conjure.Bug -import Conjure.Language -import Conjure.Process.Enumerate -import Conjure.Compute.DomainOf -import Conjure.Representations.Combined - - --- | Refine (down) an expression (X), one level (1). -downX1 :: - MonadFail m => - NameGen m => - EnumerateDomain m => - (?typeCheckerMode :: TypeCheckerMode) => - Expression -> m [Expression] -downX1 (Constant x) = onConstant x -downX1 (AbstractLiteral x) = onAbstractLiteral x -downX1 (Reference x (Just refTo)) = onReference x refTo -downX1 (Op x) = onOp x -downX1 (Comprehension body stmts) = do - xs <- downX1 body - return [Comprehension x stmts | x <- xs] -downX1 x@WithLocals{} = fail ("downX1:" <++> pretty (show x)) -downX1 x = bug ("downX1:" <++> pretty (show x)) - - --- | Refine (down) an expression (X), all the way. -downX :: - NameGen m => - EnumerateDomain m => - (?typeCheckerMode :: TypeCheckerMode) => - Expression -> m [Expression] -downX x = do - res <- runMaybeT $ downX1 x - case res of - Nothing -> return [x] - Just [] -> return [x] - Just xs -> concatMapM downX xs - - -onConstant :: - MonadFail m => - NameGen m => - EnumerateDomain m => - (?typeCheckerMode :: TypeCheckerMode) => - Constant -> m [Expression] -onConstant (ConstantAbstract (AbsLitTuple xs)) = return (map Constant xs) -onConstant (ConstantAbstract (AbsLitRecord xs)) = return (map (Constant . snd) xs) -onConstant (ConstantAbstract (AbsLitVariant (Just t) n x)) - | Just i <- elemIndex n (map fst t) - , let iExpr = fromInt (fromIntegral (i+1)) - = return $ iExpr : [ if n == n' - then Constant x - else ExpressionMetaVar "zeroVal for variant" - | (n',_) <- t ] -onConstant (ConstantAbstract (AbsLitMatrix index xs)) = do - yss <- mapM (downX1 . Constant) xs - let indexX = fmap Constant index - return [ AbstractLiteral (AbsLitMatrix indexX ys) | ys <- transpose yss ] -onConstant (TypedConstant c _) = onConstant c -onConstant x = bug ("downX1.onConstant:" <++> pretty (show x)) - -onAbstractLiteral :: - MonadFail m => - NameGen m => - EnumerateDomain m => - (?typeCheckerMode :: TypeCheckerMode) => - AbstractLiteral Expression -> m [Expression] -onAbstractLiteral (AbsLitTuple xs) = return xs -onAbstractLiteral (AbsLitRecord xs) = return (map snd xs) -onAbstractLiteral (AbsLitVariant (Just t) n x) - | Just i <- elemIndex n (map fst t) - , let iExpr = fromInt (fromIntegral (i+1)) - = return $ iExpr : [ if n == n' - then x - else ExpressionMetaVar "zeroVal for variant" - | (n',_) <- t ] -onAbstractLiteral (AbsLitMatrix index xs) = do - yss <- mapM downX1 xs - return [ AbstractLiteral (AbsLitMatrix index ys) | ys <- transpose yss ] -onAbstractLiteral x = bug ("downX1.onAbstractLiteral:" <++> pretty (show x)) - -onReference :: - MonadFail m => - NameGen m => - EnumerateDomain m => - (?typeCheckerMode :: TypeCheckerMode) => - Name -> ReferenceTo -> m [Expression] -onReference nm refTo = - case refTo of - Alias x -> downX1 x - InComprehension{} -> fail ("downX1.onReference.InComprehension:" <++> pretty (show nm)) - DeclNoRepr{} -> fail ("downX1.onReference.DeclNoRepr:" <++> pretty (show nm)) - DeclHasRepr forg _ domain -> downToX1 forg nm domain - RecordField{} -> fail ("downX1.onReference.RecordField:" <++> pretty (show nm)) - VariantField{} -> fail ("downX1.onReference.VariantField:" <++> pretty (show nm)) - -onOp :: - MonadFail m => - NameGen m => - EnumerateDomain m => - (?typeCheckerMode :: TypeCheckerMode) => - Op Expression -> m [Expression] -onOp p@(MkOpIndexing (OpIndexing m i)) = do - ty <- typeOf m - case ty of - TypeMatrix{} -> return () - TypeList{} -> return () - _ -> fail $ "[onOp, not a TypeMatrix or TypeList]" <+> vcat [pretty ty, pretty p] - xs <- downX1 m - let iIndexed x = Op (MkOpIndexing (OpIndexing x i)) - return (map iIndexed xs) -onOp op = fail ("downX1.onOp:" <++> pretty op) - - - -symmetryOrdering :: - MonadFail m => - NameGen m => - EnumerateDomain m => - (?typeCheckerMode :: TypeCheckerMode) => - Expression -> m Expression -<<<<<<< HEAD -symmetryOrdering inp' = do - let constBool (ConstantBool True) = ConstantInt TagInt 1 - constBool (ConstantBool False) = ConstantInt TagInt 0 - constBool x = x - inp = transformBi constBool inp' - ta <- typeOf inp - case ta of - TypeBool -> return [essence| [-toInt(&inp)] |] - TypeInt{} -> return [essence| [&inp] |] - TypeList TypeInt{} -> return inp - TypeMatrix TypeInt{} TypeInt{} -> return inp - _ -> do - case inp of - -- Constant x -> so_onConstant x - -- AbstractLiteral _ -> return inp - Constant (ConstantAbstract x) -> do - case x of - AbsLitTuple xs -> do - soVals <- sequence (symmetryOrdering <$> (Constant <$> xs)) - return $ fromList soVals - AbsLitMatrix _ xs -> do - soVals <- sequence (symmetryOrdering <$> (Constant <$> xs)) - return $ fromList soVals - _ -> bug ("symmetryOrdering: AbstractLiteral:" <++> pretty (show inp) <++> pretty (inp)) - Constant (ConstantBool b) -> return [essence| -toInt(&inp) |] - AbstractLiteral x -> do - case x of - AbsLitTuple xs -> do - soVals <- sequence (symmetryOrdering <$> xs) - return $ AbstractLiteral $ AbsLitTuple soVals - AbsLitMatrix d xs -> do - soVals <- sequence (symmetryOrdering <$> xs) - return $ AbstractLiteral $ AbsLitMatrix d soVals - _ -> bug ("symmetryOrdering: AbstractLiteral:" <++> pretty (show inp) <++> pretty (inp)) - - - Reference _ (Just refTo) -> do - case refTo of - Alias x -> symmetryOrdering x - InComprehension{} -> bug ("symmetryOrdering.InComprehension:" <++> pretty (show inp)) - DeclNoRepr{} -> bug ("symmetryOrdering.DeclNoRepr:" <++> pretty (show inp)) - DeclHasRepr _forg _name domain -> symmetryOrderingDispatch downX1 inp domain - RecordField{} -> bug ("symmetryOrdering.RecordField:" <++> pretty (show inp)) - VariantField{} -> bug ("symmetryOrdering.VariantField:" <++> pretty (show inp)) - Op op -> case op of - MkOpIndexing (OpIndexing m _) -> do - - ty <- typeOf m - case ty of - TypeMatrix{} -> return () - TypeList{} -> return () - _ -> bug $ "[symmetryOrdering.onOp, not a TypeMatrix or TypeList]" <+> vcat [pretty ty, pretty op] - mDom <- domainOfR m - case mDom of - DomainMatrix _ domainInner -> symmetryOrderingDispatch downX1 inp domainInner - _ -> bug ("symmetryOrdering, not DomainMatrix:" <++> pretty (show op)) - MkOpImage (OpImage p x) -> do - so <- symmetryOrdering x - return [essence| image(&p, &so) |] - _ -> bug ("symmetryOrdering, no OpIndexing:" <++> pretty (show op)) - Comprehension body stmts -> do - xs <- symmetryOrdering body - return $ make opFlatten $ Comprehension xs stmts - -- x@WithLocals{} -> bug ("downX1:" <++> pretty (show x)) - _ -> bug ("symmetryOrdering:" <++> pretty (show inp) <++> pretty (inp)) -======= -symmetryOrdering inp = - case inp of - -- Constant x -> so_onConstant x - -- AbstractLiteral x - Reference _ (Just refTo) -> do - case refTo of - Alias x -> symmetryOrdering x - InComprehension{} -> bug ("symmetryOrdering.InComprehension:" <++> pretty (show inp)) - DeclNoRepr{} -> bug ("symmetryOrdering.DeclNoRepr:" <++> pretty (show inp)) - DeclHasRepr _forg _name domain -> symmetryOrderingDispatch downX1 inp domain - RecordField{} -> bug ("symmetryOrdering.RecordField:" <++> pretty (show inp)) - VariantField{} -> bug ("symmetryOrdering.VariantField:" <++> pretty (show inp)) - Op op -> case op of - MkOpIndexing (OpIndexing m _) -> do - ty <- typeOf m - case ty of - TypeMatrix{} -> return () - TypeList{} -> return () - _ -> bug $ "[symmetryOrdering.onOp, not a TypeMatrix or TypeList]" <+> vcat [pretty ty, pretty op] - mDom <- domainOfR m - case mDom of - DomainMatrix _ domainInner -> symmetryOrderingDispatch downX1 inp domainInner - _ -> bug ("symmetryOrdering, not DomainMatrix:" <++> pretty (show op)) - _ -> bug ("symmetryOrdering, unhandled Op:" <++> pretty (show op)) - -- Comprehension body stmts -> do - -- xs <- downX1 body - -- return [Comprehension x stmts | x <- xs] - -- x@WithLocals{} -> bug ("downX1:" <++> pretty (show x)) - _ -> bug ("symmetryOrdering:" <++> pretty (show inp)) ->>>>>>> master - diff --git a/src/Conjure/Representations/Function/Function1D.hs.orig b/src/Conjure/Representations/Function/Function1D.hs.orig deleted file mode 100644 index 57b2687cd6..0000000000 --- a/src/Conjure/Representations/Function/Function1D.hs.orig +++ /dev/null @@ -1,199 +0,0 @@ -{-# LANGUAGE QuasiQuotes #-} - -module Conjure.Representations.Function.Function1D - ( function1D - , domainValues - ) where - --- conjure -import Conjure.Prelude -import Conjure.Language.Definition -import Conjure.Language.Domain -import Conjure.Language.Type -import Conjure.Language.Constant -import Conjure.Language.DomainSizeOf -import Conjure.Language.Expression.DomainSizeOf () -import Conjure.Language.TH -import Conjure.Language.Pretty -import Conjure.Representations.Internal -import Conjure.Representations.Common - --- unordered-containers -import qualified Data.HashMap.Strict as M - - -function1D :: forall m . (MonadFail m, NameGen m, ?typeCheckerMode :: TypeCheckerMode) => Representation m -function1D = Representation chck downD structuralCons downC up symmetryOrdering - - where - - chck :: TypeOf_ReprCheck m - chck f (DomainFunction _ - attrs@(FunctionAttr _ PartialityAttr_Total _) - innerDomainFr - innerDomainTo) | domainCanIndexMatrix innerDomainFr = do - innerDomainFr' <- f innerDomainFr - innerDomainTo' <- f innerDomainTo - return [ DomainFunction Function_1D attrs fr to - | fr <- innerDomainFr' - , to <- innerDomainTo' - ] - chck _ _ = return [] - - outName :: Domain HasRepresentation x -> Name -> Name - outName = mkOutName Nothing - - downD :: TypeOf_DownD m - downD (name, domain@(DomainFunction Function_1D - (FunctionAttr _ PartialityAttr_Total _) - innerDomainFr - innerDomainTo)) | domainCanIndexMatrix innerDomainFr = return $ Just - [ ( outName domain name - , DomainMatrix - (forgetRepr innerDomainFr) - innerDomainTo - ) ] - downD _ = na "{downD} Function1D" - - structuralCons :: TypeOf_Structural m - structuralCons f downX1 - (DomainFunction Function_1D - (FunctionAttr sizeAttr PartialityAttr_Total jectivityAttr) - innerDomainFr - innerDomainTo) | domainCanIndexMatrix innerDomainFr = do - - let - injectiveCons :: Expression -> m [Expression] - injectiveCons m = do - tyTo <- typeOfDomain innerDomainTo - let canAllDiff = case tyTo of - TypeBool{} -> True - TypeInt{} -> True - TypeEnum{} -> True - _ -> False - if canAllDiff - then - return $ return $ -- list - [essence| allDiff(&m) |] - else do - (iPat, i) <- quantifiedVar - (jPat, j) <- quantifiedVar - return $ return $ -- list - [essence| - forAll &iPat, &jPat : &innerDomainFr . - &i .< &j -> &m[&i] != &m[&j] - |] - - surjectiveCons :: Expression -> m [Expression] - surjectiveCons m = do - (iPat, i) <- quantifiedVar - (jPat, j) <- quantifiedVar - return $ return $ -- list - [essence| - forAll &iPat : &innerDomainTo . - exists &jPat : &innerDomainFr . - &m[&j] = &i - |] - - jectivityCons :: Expression -> m [Expression] - jectivityCons m = case jectivityAttr of - JectivityAttr_None -> return [] - JectivityAttr_Injective -> injectiveCons m - JectivityAttr_Surjective -> surjectiveCons m - JectivityAttr_Bijective -> (++) <$> injectiveCons m <*> surjectiveCons m - - cardinality <- domainSizeOf innerDomainFr - - let innerStructuralCons m = do - (iPat, i) <- quantifiedVarOverDomain (forgetRepr innerDomainFr) - let activeZone b = [essence| forAll &iPat : &innerDomainFr . &b |] - - -- preparing structural constraints for the inner guys - innerStructuralConsGen <- f innerDomainTo - - let inLoop = [essence| &m[&i] |] - outs <- innerStructuralConsGen inLoop - return (map activeZone outs) - - return $ \ func -> do - refs <- downX1 func - case refs of - [m] -> - concat <$> sequence - [ jectivityCons m - , return (mkSizeCons sizeAttr cardinality) - , innerStructuralCons m - ] - _ -> na "{structuralCons} Function1D" - - structuralCons _ _ _ = na "{structuralCons} Function1D" - - downC :: TypeOf_DownC m - downC ( name - , domain@(DomainFunction Function_1D - (FunctionAttr _ PartialityAttr_Total _) - innerDomainFr - innerDomainTo) - , ConstantAbstract (AbsLitFunction vals_) - ) | domainCanIndexMatrix innerDomainFr = do - let vals = M.fromList vals_ - froms <- domainValues innerDomainFr - valsOut <- sequence - [ val - | fr <- froms - , let val = case M.lookup fr vals of - Nothing -> fail $ vcat [ "No value for" <+> pretty fr - , "In:" <+> pretty (AbsLitFunction vals_) - ] - Just v -> return v - ] - return $ Just - [ ( outName domain name - , DomainMatrix (forgetRepr innerDomainFr) innerDomainTo - , ConstantAbstract $ AbsLitMatrix (forgetRepr innerDomainFr) valsOut - ) ] - downC _ = na "{downC} Function1D" - - up :: TypeOf_Up m - up ctxt (name, domain@(DomainFunction Function_1D - (FunctionAttr _ PartialityAttr_Total _) - innerDomainFr _)) = - case lookup (outName domain name) ctxt of - Nothing -> fail $ vcat $ - [ "(in Function1D up)" - , "No value for:" <+> pretty (outName domain name) - , "When working on:" <+> pretty name - , "With domain:" <+> pretty domain - ] ++ - ("Bindings in context:" : prettyContext ctxt) - Just constant -> - case viewConstantMatrix constant of - Just (_, vals) -> do - froms <- domainValues innerDomainFr - return ( name - , ConstantAbstract $ AbsLitFunction $ zip froms vals - ) - _ -> fail $ vcat - [ "Expecting a matrix literal for:" <+> pretty (outName domain name) - , "But got:" <+> pretty constant - , "When working on:" <+> pretty name - , "With domain:" <+> pretty domain - ] - up _ _ = na "{up} Function1D" - - symmetryOrdering :: TypeOf_SymmetryOrdering m - symmetryOrdering innerSO downX1 inp domain = do - [inner] <- downX1 inp - Just [(_, innerDomain)] <- downD ("SO", domain) - innerSO downX1 inner innerDomain -<<<<<<< HEAD -======= - ->>>>>>> master - -domainValues :: (MonadFail m, Pretty r) => Domain r Constant -> m [Constant] -domainValues dom = - case dom of - DomainBool -> return [ConstantBool False, ConstantBool True] - DomainInt t rs -> map (ConstantInt t) <$> valuesInIntDomain rs - _ -> fail ("domainValues, not supported:" <+> pretty dom) diff --git a/src/Conjure/Representations/Function/Function1DPartial.hs.orig b/src/Conjure/Representations/Function/Function1DPartial.hs.orig deleted file mode 100644 index 96550c4858..0000000000 --- a/src/Conjure/Representations/Function/Function1DPartial.hs.orig +++ /dev/null @@ -1,229 +0,0 @@ -{-# LANGUAGE QuasiQuotes #-} - -module Conjure.Representations.Function.Function1DPartial ( function1DPartial ) where - --- conjure -import Conjure.Prelude -import Conjure.Language -import Conjure.Language.ZeroVal ( zeroVal, EnumerateDomain ) -import Conjure.Representations.Internal -import Conjure.Representations.Common -import Conjure.Representations.Function.Function1D ( domainValues ) - --- unordered-containers -import qualified Data.HashMap.Strict as M - - -function1DPartial :: forall m . (MonadFail m, NameGen m, EnumerateDomain m) => Representation m -function1DPartial = Representation chck downD structuralCons downC up symmetryOrdering - - where - - chck :: TypeOf_ReprCheck m - chck f (DomainFunction _ - attrs@(FunctionAttr _ PartialityAttr_Partial _) - innerDomainFr - innerDomainTo) | domainCanIndexMatrix innerDomainFr = do - innerDomainFr' <- f innerDomainFr - innerDomainTo' <- f innerDomainTo - return [ DomainFunction Function_1DPartial attrs fr to - | fr <- innerDomainFr' - , to <- innerDomainTo' - ] - chck _ _ = return [] - - nameFlags = mkOutName (Just "Flags") - nameValues = mkOutName (Just "Values") - - downD :: TypeOf_DownD m - downD (name, domain@(DomainFunction Function_1DPartial - (FunctionAttr _ PartialityAttr_Partial _) - innerDomainFr - innerDomainTo)) | domainCanIndexMatrix innerDomainFr = return $ Just - [ ( nameFlags domain name - , DomainMatrix - (forgetRepr innerDomainFr) - DomainBool - ) - , ( nameValues domain name - , DomainMatrix - (forgetRepr innerDomainFr) - innerDomainTo - ) - ] - downD _ = na "{downD} Function1DPartial" - - structuralCons :: TypeOf_Structural m - structuralCons f downX1 - (DomainFunction Function_1DPartial - (FunctionAttr sizeAttr PartialityAttr_Partial jectivityAttr) - innerDomainFr - innerDomainTo) | domainCanIndexMatrix innerDomainFr = do - - let injectiveCons flags values = do - (iPat, i) <- quantifiedVar - (jPat, j) <- quantifiedVar - return $ return $ -- list - [essence| - and([ &values[&i] != &values[&j] - | &iPat : &innerDomainFr - , &jPat : &innerDomainFr - , &i .< &j - , &flags[&i] - , &flags[&j] - ]) - |] - - let surjectiveCons flags values = do - (iPat, i) <- quantifiedVar - (jPat, j) <- quantifiedVar - return $ return $ -- list - [essence| - forAll &iPat : &innerDomainTo . - exists &jPat : &innerDomainFr . - &flags[&j] /\ &values[&j] = &i - |] - - let jectivityCons flags values = case jectivityAttr of - JectivityAttr_None -> return [] - JectivityAttr_Injective -> injectiveCons flags values - JectivityAttr_Surjective -> surjectiveCons flags values - JectivityAttr_Bijective -> (++) <$> injectiveCons flags values - <*> surjectiveCons flags values - - let cardinality flags = do - (iPat, i) <- quantifiedVar - return [essence| sum &iPat : &innerDomainFr . toInt(&flags[&i]) |] - - let dontCareInactives flags values = do - (iPat, i) <- quantifiedVar - return $ return $ -- list - [essence| - forAll &iPat : &innerDomainFr . &flags[&i] = false -> - dontCare(&values[&i]) - |] - - let innerStructuralCons flags values = do - (iPat, i) <- quantifiedVarOverDomain (forgetRepr innerDomainFr) - let activeZone b = [essence| forAll &iPat : &innerDomainFr . &flags[&i] -> &b |] - - -- preparing structural constraints for the inner guys - innerStructuralConsGen <- f innerDomainTo - - let inLoop = [essence| &values[&i] |] - outs <- innerStructuralConsGen inLoop - return (map activeZone outs) - - return $ \ func -> do - refs <- downX1 func - case refs of - [flags,values] -> - concat <$> sequence - [ jectivityCons flags values - , dontCareInactives flags values - , mkSizeCons sizeAttr <$> cardinality flags - , innerStructuralCons flags values - ] - _ -> na "{structuralCons} Function1DPartial" - - structuralCons _ _ _ = na "{structuralCons} Function1DPartial" - - downC :: TypeOf_DownC m - downC ( name - , domain@(DomainFunction Function_1DPartial - (FunctionAttr _ PartialityAttr_Partial _) - innerDomainFr - innerDomainTo) - , ConstantAbstract (AbsLitFunction vals_) - ) | domainCanIndexMatrix innerDomainFr = do - let vals = M.fromList vals_ - z <- zeroVal innerDomainTo - froms <- domainValues innerDomainFr - (flagsOut, valsOut) <- unzip <$> sequence - [ val - | fr <- froms - , let val = case M.lookup fr vals of - Nothing -> return (ConstantBool False, z) - Just v -> return (ConstantBool True , v) - ] - return $ Just - [ ( nameFlags domain name - , DomainMatrix - (forgetRepr innerDomainFr) - DomainBool - , ConstantAbstract $ AbsLitMatrix - (forgetRepr innerDomainFr) - flagsOut - ) - , ( nameValues domain name - , DomainMatrix - (forgetRepr innerDomainFr) - innerDomainTo - , ConstantAbstract $ AbsLitMatrix - (forgetRepr innerDomainFr) - valsOut - ) - ] - downC (name, domain, constant) = na $ vcat [ "{downC} Function1DPartial" - , "name:" <+> pretty name - , "domain:" <+> pretty domain - , "constant:" <+> pretty constant - ] - - up :: TypeOf_Up m - up ctxt (name, domain@(DomainFunction Function_1DPartial - (FunctionAttr _ PartialityAttr_Partial _) - innerDomainFr _)) = - case (lookup (nameFlags domain name) ctxt, lookup (nameValues domain name) ctxt) of - ( Just (ConstantAbstract (AbsLitMatrix _ flagMatrix)) , - Just (ConstantAbstract (AbsLitMatrix _ valuesMatrix)) ) -> do - froms <- domainValues innerDomainFr - functionValues <- forM (zip3 flagMatrix froms valuesMatrix) $ \ (flag, from, to) -> - case viewConstantBool flag of - Just b -> return $ if b then Just (from,to) else Nothing - Nothing -> fail $ vcat [ "Expected a boolean, but got:" <++> pretty flag - , "When working on:" <+> pretty name - , "With domain:" <+> pretty domain - ] - return ( name, ConstantAbstract $ AbsLitFunction $ catMaybes functionValues ) - (Nothing, _) -> fail $ vcat $ - [ "(in Function1DPartial up 1)" - , "No value for:" <+> pretty (nameFlags domain name) - , "When working on:" <+> pretty name - , "With domain:" <+> pretty domain - ] ++ - ("Bindings in context:" : prettyContext ctxt) - (_, Nothing) -> fail $ vcat $ - [ "(in Function1DPartial up 2)" - , "No value for:" <+> pretty (nameValues domain name) - , "When working on:" <+> pretty name - , "With domain:" <+> pretty domain - ] ++ - ("Bindings in context:" : prettyContext ctxt) - _ -> fail $ vcat $ - [ "Expected matrix literals for:" <+> pretty (nameFlags domain name) - <+> "and" <+> pretty (nameValues domain name) - , "When working on:" <+> pretty name - , "With domain:" <+> pretty domain - ] ++ - ("Bindings in context:" : prettyContext ctxt) - up _ _ = na "{up} Function1DPartial" - - symmetryOrdering :: TypeOf_SymmetryOrdering m - symmetryOrdering innerSO downX1 inp domain = do - [flags, values] <- downX1 inp - Just [_, (_, DomainMatrix innerDomainFr innerDomainTo)] <- downD ("SO", domain) - (iPat, i) <- quantifiedVar - soValues <- innerSO downX1 [essence| &values[&i] |] innerDomainTo - return - [essence| - [ ( -toInt(&flags[&i]) - , &soValues - ) - | &iPat : &innerDomainFr - ] - |] -<<<<<<< HEAD -======= - ->>>>>>> master diff --git a/src/Conjure/Representations/Function/FunctionND.hs.orig b/src/Conjure/Representations/Function/FunctionND.hs.orig deleted file mode 100644 index 948b9baaee..0000000000 --- a/src/Conjure/Representations/Function/FunctionND.hs.orig +++ /dev/null @@ -1,283 +0,0 @@ -{-# LANGUAGE QuasiQuotes #-} -{-# LANGUAGE ViewPatterns #-} - -module Conjure.Representations.Function.FunctionND ( functionND, viewAsDomainTuple, mkLensAsDomainTuple ) where - --- conjure -import Conjure.Prelude -import Conjure.Bug -import Conjure.Language -import Conjure.Representations.Internal -import Conjure.Representations.Common -import Conjure.Representations.Function.Function1D ( domainValues ) - - -functionND :: forall m . (MonadFail m, NameGen m, ?typeCheckerMode :: TypeCheckerMode) => Representation m -functionND = Representation chck downD structuralCons downC up symmetryOrdering - - where - - chck :: TypeOf_ReprCheck m - chck f (DomainFunction _ - attrs@(FunctionAttr _ PartialityAttr_Total _) - innerDomainFr@(viewAsDomainTuple -> Just innerDomainFrs) - innerDomainTo) | all domainCanIndexMatrix innerDomainFrs = do - innerDomainFr' <- f innerDomainFr - innerDomainTo' <- f innerDomainTo - return [ DomainFunction Function_ND attrs fr to - | fr <- innerDomainFr' - , to <- innerDomainTo' - ] - chck _ _ = return [] - - nameValues :: Domain HasRepresentation x -> Name -> Name - nameValues = mkOutName Nothing - - downD :: TypeOf_DownD m - downD (name, domain@(DomainFunction Function_ND - (FunctionAttr _ PartialityAttr_Total _) - (viewAsDomainTuple -> Just innerDomainFrs) - innerDomainTo)) | all domainCanIndexMatrix innerDomainFrs = do - let unroll is j = foldr DomainMatrix j is - return $ Just - [ ( nameValues domain name - , unroll (map forgetRepr innerDomainFrs) innerDomainTo - ) - ] - downD _ = na "{downD} FunctionND" - - structuralCons :: TypeOf_Structural m - structuralCons f downX1 - (DomainFunction Function_ND - (FunctionAttr sizeAttr PartialityAttr_Total jectivityAttr) - innerDomainFr@(viewAsDomainTuple -> Just innerDomainFrs) - innerDomainTo) | all domainCanIndexMatrix innerDomainFrs = do - - let - kRange = case innerDomainFr of - DomainTuple ts -> map fromInt [1 .. genericLength ts] - DomainRecord rs -> map (fromName . fst) rs - _ -> bug $ vcat [ "FunctionNDPartial.structuralCons" - , "innerDomainFr:" <+> pretty innerDomainFr - ] - toIndex x = [ [essence| &x[&k] |] | k <- kRange ] - index x m = make opMatrixIndexing m (toIndex x) - - let - injectiveCons :: Expression -> m [Expression] - injectiveCons values = do - tyTo <- typeOfDomain innerDomainTo - let canAllDiff = case tyTo of - TypeBool{} -> True - TypeInt{} -> True - TypeEnum{} -> True - _ -> False - if canAllDiff - then do - (iPat, i) <- quantifiedVar - let valuesIndexedI = index i values - return $ return $ -- list - [essence| - allDiff([ &valuesIndexedI - | &iPat : &innerDomainFr - ]) - |] - else do - (iPat, i) <- quantifiedVar - (jPat, j) <- quantifiedVar - let valuesIndexedI = index i values - let valuesIndexedJ = index j values - return $ return $ -- list - [essence| - forAll &iPat, &jPat : &innerDomainFr . - &i .< &j -> &valuesIndexedI != &valuesIndexedJ - |] - - surjectiveCons :: Expression -> m [Expression] - surjectiveCons values = do - (iPat, i) <- quantifiedVar - (jPat, j) <- quantifiedVar - let valuesIndexedJ = index j values - return $ return $ -- list - [essence| - forAll &iPat : &innerDomainTo . - exists &jPat : &innerDomainFr . - &valuesIndexedJ = &i - |] - - jectivityCons :: Expression -> m [Expression] - jectivityCons values = case jectivityAttr of - JectivityAttr_None -> return [] - JectivityAttr_Injective -> injectiveCons values - JectivityAttr_Surjective -> surjectiveCons values - JectivityAttr_Bijective -> (++) <$> injectiveCons values - <*> surjectiveCons values - - cardinality :: m Expression - cardinality = do - (iPat, _) <- quantifiedVar - return [essence| sum &iPat : &innerDomainFr . 1 |] - - let innerStructuralCons values = do - (iPat, i) <- quantifiedVarOverDomain (forgetRepr innerDomainFr) - let valuesIndexedI = index i values - let activeZone b = [essence| forAll &iPat : &innerDomainFr . &b |] - - -- preparing structural constraints for the inner guys - innerStructuralConsGen <- f innerDomainTo - - let inLoop = valuesIndexedI - outs <- innerStructuralConsGen inLoop - return (map activeZone outs) - - return $ \ func -> do - refs <- downX1 func - case refs of - [values] -> - concat <$> sequence - [ jectivityCons values - , mkSizeCons sizeAttr <$> cardinality - , innerStructuralCons values - ] - _ -> na "{structuralCons} FunctionND" - - structuralCons _ _ _ = na "{structuralCons} FunctionND" - - downC :: TypeOf_DownC m - downC ( name - , domain@(DomainFunction Function_ND - (FunctionAttr _ PartialityAttr_Total _) - innerDomainFr@(viewAsDomainTuple -> Just innerDomainFrs) - innerDomainTo) - , value@(ConstantAbstract (AbsLitFunction vals)) - ) | all domainCanIndexMatrix innerDomainFrs - , Just (_mk, inspect) <- mkLensAsDomainTuple innerDomainFr = do - let - check :: [Constant] -> Maybe Constant - check indices = listToMaybe [ v - | (inspect -> Just k, v) <- vals - , k == indices - ] - - let - unrollD :: [Domain () Constant] -> Domain r Constant -> Domain r Constant - unrollD is j = foldr DomainMatrix j is - - let - unrollC :: MonadFail m - => [Domain () Constant] - -> [Constant] -- indices - -> m Constant - unrollC [i] prevIndices = do - domVals <- domainValues i - let active val = check $ prevIndices ++ [val] - - missing <- concatForM domVals $ \ val -> - case active val of - Nothing -> return [ConstantAbstract $ AbsLitTuple $ prevIndices ++ [val]] - Just {} -> return [] - - unless (null missing) $ - fail $ vcat [ "Some points are undefined on a total function:" <++> prettyList id "," missing - , " Function:" <+> pretty name - , " Domain:" <++> pretty domain - , " Value :" <++> pretty value - ] - - return $ ConstantAbstract $ AbsLitMatrix i - [ fromMaybe (bug $ "FunctionND downC" <+> pretty val) (active val) - | val <- domVals ] - unrollC (i:is) prevIndices = do - domVals <- domainValues i - matrixVals <- forM domVals $ \ val -> - unrollC is (prevIndices ++ [val]) - return $ ConstantAbstract $ AbsLitMatrix i matrixVals - unrollC is prevIndices = fail $ vcat [ "FunctionND.up.unrollC" - , " is :" <+> vcat (map pretty is) - , " prevIndices:" <+> pretty (show prevIndices) - ] - - outValues <- unrollC (map forgetRepr innerDomainFrs) [] - return $ Just - [ ( nameValues domain name - , unrollD (map forgetRepr innerDomainFrs) innerDomainTo - , outValues - ) - ] - - downC _ = na "{downC} FunctionND" - - up :: TypeOf_Up m - up ctxt (name, domain@(DomainFunction Function_ND - (FunctionAttr _ PartialityAttr_Total _) - innerDomainFr@(viewAsDomainTuple -> Just innerDomainFrs) _)) - - | Just (mk, _inspect) <- mkLensAsDomainTuple innerDomainFr = - - case lookup (nameValues domain name) ctxt of - Just valuesMatrix -> do - let - allIndices :: (MonadFail m, Pretty r) => [Domain r Constant] -> m [[Constant]] - allIndices = fmap sequence . mapM domainValues - - index :: MonadFail m => Constant -> [Constant] -> m Constant - index m [] = return m - index (ConstantAbstract (AbsLitMatrix indexDomain vals)) (i:is) = do - froms <- domainValues indexDomain - case lookup i (zip froms vals) of - Nothing -> fail "Value not found. FunctionND.up.index" - Just v -> index v is - index m is = bug ("FunctionND.up.index" <+> pretty m <+> pretty (show is)) - - indices <- allIndices innerDomainFrs - vals <- forM indices $ \ these -> do - value <- index valuesMatrix these - return (mk these, value) - return ( name - , ConstantAbstract $ AbsLitFunction vals - ) - Nothing -> fail $ vcat $ - [ "(in FunctionND up)" - , "No value for:" <+> pretty (nameValues domain name) - , "When working on:" <+> pretty name - , "With domain:" <+> pretty domain - ] ++ - ("Bindings in context:" : prettyContext ctxt) - up _ _ = na "{up} FunctionND" - - symmetryOrdering :: TypeOf_SymmetryOrdering m - symmetryOrdering innerSO downX1 inp domain = do - [inner] <- downX1 inp - Just [(_, innerDomain)] <- downD ("SO", domain) - innerSO downX1 inner innerDomain -<<<<<<< HEAD - - -======= ->>>>>>> master - -viewAsDomainTuple :: Domain r x -> Maybe [Domain r x] -viewAsDomainTuple (DomainTuple doms) = Just doms -viewAsDomainTuple (DomainRecord doms) = Just (doms |> sortBy (comparing fst) |> map snd) -viewAsDomainTuple _ = Nothing - - -mkLensAsDomainTuple :: Domain r x -> Maybe ( [Constant] -> Constant -- how to make a literal - , Constant -> Maybe [Constant] -- how to inspect a literal - ) -mkLensAsDomainTuple (DomainTuple _) = - Just - ( \ vals -> ConstantAbstract (AbsLitTuple vals) - , \ val -> case val of - ConstantAbstract (AbsLitTuple vals) -> Just vals - _ -> Nothing - ) -mkLensAsDomainTuple (DomainRecord doms) = - let names = doms |> sortBy (comparing fst) |> map fst - in Just - ( \ vals -> ConstantAbstract (AbsLitRecord (zip names vals)) - , \ val -> case val of - ConstantAbstract (AbsLitRecord vals) -> Just (vals |> sortBy (comparing fst) |> map snd) - _ -> Nothing - ) -mkLensAsDomainTuple _ = Nothing diff --git a/src/Conjure/Representations/MSet/Occurrence.hs.orig b/src/Conjure/Representations/MSet/Occurrence.hs.orig deleted file mode 100644 index 4a870f7d39..0000000000 --- a/src/Conjure/Representations/MSet/Occurrence.hs.orig +++ /dev/null @@ -1,122 +0,0 @@ -{-# LANGUAGE QuasiQuotes #-} - -module Conjure.Representations.MSet.Occurrence ( msetOccurrence ) where - --- conjure -import Conjure.Prelude -import Conjure.Language -import Conjure.Representations.Internal -import Conjure.Representations.Common - - -msetOccurrence :: forall m . (MonadFail m, NameGen m) => Representation m -msetOccurrence = Representation chck downD structuralCons downC up symmetryOrdering - - where - - chck :: TypeOf_ReprCheck m - chck f (DomainMSet _ attrs innerDomain@DomainInt{}) = map (DomainMSet MSet_Occurrence attrs) <$> f innerDomain - chck _ _ = return [] - - outName :: Domain HasRepresentation x -> Name -> Name - outName = mkOutName Nothing - - getMinOccur attrs = case attrs of - MSetAttr _ (OccurAttr_MinOccur x) -> x - MSetAttr _ (OccurAttr_MinMaxOccur x _) -> x - MSetAttr _ _ -> 0 - - getMaxOccur attrs = case attrs of - MSetAttr _ (OccurAttr_MaxOccur x) -> return x - MSetAttr _ (OccurAttr_MinMaxOccur _ x) -> return x - MSetAttr (SizeAttr_Size x) _ -> return x - MSetAttr (SizeAttr_MaxSize x) _ -> return x - MSetAttr (SizeAttr_MinMaxSize _ x) _ -> return x - _ -> fail ("getMaxOccur, mset not supported. attributes:" <+> pretty attrs) - - downD :: TypeOf_DownD m - downD (name, domain@(DomainMSet MSet_Occurrence attrs innerDomain@DomainInt{})) = do - maxOccur <- getMaxOccur attrs - return $ Just - [ ( outName domain name - , DomainMatrix (forgetRepr innerDomain) (DomainInt TagInt [RangeBounded 0 maxOccur]) - ) - ] - downD _ = na "{downD} Occurrence" - - structuralCons :: TypeOf_Structural m - structuralCons _ downX1 (DomainMSet MSet_Occurrence - attrs@(MSetAttr sizeAttr _occurAttr) - innerDomain@DomainInt{}) = - return $ \ mset -> do - refs <- downX1 mset - case refs of - [m] -> do - (iPat, i) <- quantifiedVar - let - minOccur = getMinOccur attrs - minOccurCons = - [ [essence| forAll &iPat : &innerDomain . &m[&i] = 0 \/ &m[&i] >= &minOccur |] - | minOccur /= 0 ] - let - cardinality = [essence| sum &iPat : &innerDomain . &m[&i] |] - cardinalityCons = mkSizeCons sizeAttr cardinality - return (minOccurCons ++ cardinalityCons) - _ -> na "{structuralCons} Occurrence" - structuralCons _ _ _ = na "{structuralCons} Occurrence" - - downC :: TypeOf_DownC m - downC ( name - , domain@(DomainMSet MSet_Occurrence _attrs innerDomain@(DomainInt t intRanges)) - , ConstantAbstract (AbsLitMSet constants) - ) = do - innerDomainVals <- valuesInIntDomain intRanges - return $ Just - [ ( outName domain name - , DomainMatrix (forgetRepr innerDomain) DomainBool - , ConstantAbstract $ AbsLitMatrix (forgetRepr innerDomain) - [ ConstantBool isIn - | v <- innerDomainVals - , let isIn = ConstantInt t v `elem` constants - ] - ) - ] - downC _ = na "{downC} Occurrence" - - up :: TypeOf_Up m - up ctxt (name, domain@(DomainMSet _ _ (DomainInt t intRanges)))= - case lookup (outName domain name) ctxt of - Just constantMatrix -> - case viewConstantMatrix constantMatrix of - Just (_, vals) -> do - innerDomainVals <- valuesInIntDomain intRanges - return (name, ConstantAbstract $ AbsLitMSet $ concat - [ case viewConstantInt x of - Just n -> replicate (fromInteger n) (ConstantInt t v) - Nothing -> [] - | (v,x) <- zip innerDomainVals vals - ] ) - _ -> fail $ vcat - [ "Expecting a matrix literal for:" <+> pretty (outName domain name) - , "But got:" <+> pretty constantMatrix - , "When working on:" <+> pretty name - , "With domain:" <+> pretty domain - ] - Nothing -> fail $ vcat $ - [ "(in MSet Occurrence up)" - , "No value for:" <+> pretty (outName domain name) - , "When working on:" <+> pretty name - , "With domain:" <+> pretty domain - ] ++ - ("Bindings in context:" : prettyContext ctxt) - up _ _ = na "{up} Occurrence" - - symmetryOrdering :: TypeOf_SymmetryOrdering m - symmetryOrdering innerSO downX1 inp domain = do - [inner] <- downX1 inp - Just [(_, innerDomain)] <- downD ("SO", domain) - innerSO downX1 inner innerDomain -<<<<<<< HEAD -======= - ->>>>>>> master diff --git a/src/Conjure/Representations/Partition/Occurrence.hs.orig b/src/Conjure/Representations/Partition/Occurrence.hs.orig deleted file mode 100644 index f838692f5a..0000000000 --- a/src/Conjure/Representations/Partition/Occurrence.hs.orig +++ /dev/null @@ -1,329 +0,0 @@ --- {-# LANGUAGE Rank2Types #-} -{-# LANGUAGE RecordWildCards #-} -{-# LANGUAGE QuasiQuotes #-} -{-# LANGUAGE ViewPatterns #-} - -module Conjure.Representations.Partition.Occurrence ( partitionOccurrence ) where - --- conjure -import Conjure.Prelude -import Conjure.Bug -import Conjure.Language -import Conjure.Language.DomainSizeOf -import Conjure.Language.Expression.DomainSizeOf () -import Conjure.Language.ZeroVal ( zeroVal, EnumerateDomain ) -import Conjure.Representations.Internal -import Conjure.Representations.Common -import Conjure.Representations.Function.Function1D ( domainValues ) - - --- | works for "partition from A", where A can be used as an index of a matrix --- _WhichPart: matrix indexed by [A] of int(1..maxNumParts) --- (indicating which part an element belongs to) --- _NumParts : int(1..maxNumParts) --- (indicating the total number of parts) --- only use part numbers from 1.._NumParts, never use the others --- part(i) is used -> part(i-1) is used, forAll i:int(3..maxNumParts) -partitionOccurrence :: forall m . (MonadFail m, NameGen m, EnumerateDomain m) => Representation m -partitionOccurrence = Representation chck downD structuralCons downC up symmetryOrdering - - where - - chck :: TypeOf_ReprCheck m - chck f (DomainPartition _ attrs innerDomain) - | domainCanIndexMatrix innerDomain - = map (DomainPartition Partition_Occurrence attrs) <$> f innerDomain - chck _ _ = return [] - - nameNumParts = mkOutName (Just "NumParts") - nameWhichPart = mkOutName (Just "WhichPart") - namePartSizes = mkOutName (Just "PartSizes") - nameFirstIndex = mkOutName (Just "FirstIndex") - - getMaxNumParts attrs d = - case partsNum attrs of - SizeAttr_Size x -> return x - SizeAttr_MaxSize x -> return x - SizeAttr_MinMaxSize _ x -> return x - _ -> domainSizeOf d - - getMaxPartSizes attrs d = - case partsSize attrs of - SizeAttr_Size x -> return x - SizeAttr_MaxSize x -> return x - SizeAttr_MinMaxSize _ x -> return x - _ -> domainSizeOf d - - -- downD :: TypeOf_DownD m - downD (name, domain@(DomainPartition Partition_Occurrence attrs innerDomain)) - | domainCanIndexMatrix innerDomain = do - maxNumParts <- getMaxNumParts attrs innerDomain - maxPartSizes <- getMaxPartSizes attrs innerDomain - return $ Just - [ - -- number of active parts - ( nameNumParts domain name - , DomainInt TagInt [RangeBounded 1 maxNumParts] - ) - -- for each element, the part it belongs to - , ( nameWhichPart domain name - , DomainMatrix - (forgetRepr innerDomain) - (DomainInt TagInt [RangeBounded 1 maxNumParts]) - ) - -- for each part, number of elements in the part - , ( namePartSizes domain name - , DomainMatrix - (DomainInt TagInt [RangeBounded 1 maxNumParts]) - (DomainInt TagInt [RangeBounded 0 maxPartSizes]) - ) - -- wtf was this? - , ( nameFirstIndex domain name - , DomainMatrix - (DomainInt TagInt [RangeBounded 1 maxNumParts]) - innerDomain -- dontCare if not used - ) - ] - downD _ = na "{downD} Occurrence" - - structuralCons :: TypeOf_Structural m - structuralCons _ downX1 (DomainPartition _ attrs innerDomain) - | domainCanIndexMatrix innerDomain = do - maxNumParts <- getMaxNumParts attrs innerDomain - let - numPartsChannelling whichPart numPartsVar = do - (iPat, i) <- quantifiedVar - return $ return -- for list - [essence| - &numPartsVar = - max([ &whichPart[&i] | &iPat : &innerDomain ]) - |] - - partSizesChannelling whichPart partSizesVar = do - (iPat, i) <- quantifiedVar - (jPat, j) <- quantifiedVar - return $ return -- for list - [essence| - and([ &partSizesVar[&i] = sum([ 1 | &jPat : &innerDomain , &whichPart[&j] = &i ]) - | &iPat : int(1..&maxNumParts) - ]) - |] - - firstIndexChannelling whichPart numPartsVar firstIndexVar = do - (iPat, i) <- quantifiedVar - (jPat, j) <- quantifiedVar - return - [ -- firstIndexVar[i] is <= all indices belonging to part i - [essence| - forAll &iPat : int(1..&maxNumParts) , &i <= &numPartsVar . - forAll &jPat : &innerDomain . - &whichPart[&j] = &i -> &firstIndexVar[&i] <= &j - |] - , -- firstIndexVar[i] is equal to one of those - [essence| - forAll &iPat : int(1..&maxNumParts) , &i <= &numPartsVar . - exists &jPat : &innerDomain . - &whichPart[&j] = &i /\ &firstIndexVar[&i] = &j - |] - , -- firstIndexVar[i] is dontCare, if nothing is in part i - [essence| - forAll &iPat : int(1..&maxNumParts) , &i > &numPartsVar . - dontCare(&firstIndexVar[&i]) - |] - ] - - symmetryBreaking numPartsVar firstIndexVar = do - (iPat, i) <- quantifiedVar - (jPat, j) <- quantifiedVar - return $ return -- for list - [essence| - forAll &iPat, &jPat : int(1..&maxNumParts) , &i <= &numPartsVar /\ &j <= &numPartsVar . - &i < &j <-> &firstIndexVar[&i] < &firstIndexVar[&j] - |] - - numPartsCons numPartsVar = - return $ mkSizeCons (partsNum attrs) numPartsVar - - partSizeCons numPartsVar partSizesVar = do - (iPat, i) <- quantifiedVar - let theConsForI = make opAnd $ fromList $ - mkSizeCons (partsSize attrs) [essence| &partSizesVar[&i] |] - return - [ [essence| - and([ &theConsForI - | &iPat : int(1..&maxNumParts) $ forAll part numbers - , &i <= &numPartsVar $ that are active - ]) - |] - , [essence| - and([ &partSizesVar[&i] = 0 - | &iPat : int(1..&maxNumParts) $ forAll part numbers - , &i > &numPartsVar $ that are inactive - ]) - |] - ] - - noGaps whichPart numPartsVar = do - (iPat, i) <- quantifiedVar - (jPat, j) <- quantifiedVar - return $ return -- for list - [essence| - and([ or([ &whichPart[&j] = &i $ there must be a member in that part - | &jPat : &innerDomain - ]) - | &iPat : int(3..&maxNumParts) $ forAll part numbers (except 1 and 2) - , &i <= &numPartsVar $ that are active - ]) - |] - - fixedPartSize = - case attrs of - PartitionAttr _ SizeAttr_Size{} _ -> True - _ -> False - - regular numPartsVar partSizesVar | isRegular attrs && not fixedPartSize = do - (iPat, i) <- quantifiedVar - return $ return -- for list - [essence| - and([ &partSizesVar[&i-1] = &partSizesVar[&i] - | &iPat : int(2..&maxNumParts) - , &i <= &numPartsVar - ]) - |] - regular _ _ = return [] - - return $ \ inpPartition -> do - [numPartsVar, whichPart, partSizesVar, firstIndexVar] <- downX1 inpPartition - concat <$> sequence - [ partSizeCons numPartsVar partSizesVar - , numPartsCons numPartsVar - , noGaps whichPart numPartsVar - , regular numPartsVar partSizesVar - , numPartsChannelling whichPart numPartsVar - , partSizesChannelling whichPart partSizesVar - , firstIndexChannelling whichPart numPartsVar firstIndexVar - , symmetryBreaking numPartsVar firstIndexVar - ] - structuralCons _ _ domain = na $ vcat [ "{structuralCons} Occurrence" - , "domain:" <+> pretty domain - ] - - downC :: TypeOf_DownC m - downC ( name - , inDom@(DomainPartition Partition_Occurrence attrs innerDomain) - , inConstant@(ConstantAbstract (AbsLitPartition vals)) - ) = do - Just [ ( numPartsVar , numPartsDom ) - , ( whichPart , whichPartDom ) - , ( partSizesVar , partSizesDom ) - , ( firstIndexVar , firstIndexDom ) - ] <- downD (name, inDom) - members <- domainValues innerDomain - maxNumParts' <- getMaxNumParts attrs innerDomain - maxNumParts <- case viewConstantInt maxNumParts' of - Just i -> return i - Nothing -> bug ("expecting an integer literal, but got:" <++> pretty maxNumParts') - z <- zeroVal innerDomain - let - whichPartValInside :: [(Integer, Constant)] - whichPartValInside = - [ case whichPartIsIt of - [p] -> p - [] -> bug $ vcat [ "Not found:" <+> pretty mem - , "Inside:" <+> pretty inConstant - ] - _ -> bug $ vcat [ "Found multiple times:" <+> pretty mem - , "Inside:" <+> pretty inConstant - ] - | mem <- members - , let whichPartIsIt = [ (p, mem) - | (p, pVals) <- zip [1..] vals - , mem `elem` pVals - ] - ] - numPartsVal = ConstantInt TagInt (genericLength vals) - whichPartVal = ConstantAbstract (AbsLitMatrix - (forgetRepr innerDomain) - (map (ConstantInt TagInt . fst) whichPartValInside)) - partSizesVal = ConstantAbstract (AbsLitMatrix - (DomainInt TagInt [RangeBounded 1 maxNumParts']) - (map (ConstantInt TagInt . genericLength) vals - ++ replicate (fromInteger (maxNumParts - genericLength vals)) - (ConstantInt TagInt 0))) - firstIndexVal = ConstantAbstract (AbsLitMatrix - (DomainInt TagInt [RangeBounded 1 maxNumParts']) - ([ case lookup p whichPartValInside of - Nothing -> bug $ vcat [ "Not found:" <+> pretty p - , "Inside:" <+> prettyList id "," whichPartValInside - ] - Just i -> i - | p <- [1..genericLength vals] ] - ++ replicate (fromInteger (maxNumParts - genericLength vals)) - z)) - return $ Just - [ ( numPartsVar , numPartsDom , numPartsVal ) - , ( whichPart , whichPartDom , whichPartVal ) - , ( partSizesVar , partSizesDom , partSizesVal ) - , ( firstIndexVar , firstIndexDom , firstIndexVal ) - ] - downC (name, domain, constant) = na $ vcat [ "{downC} Occurrence" - , "name:" <+> pretty name - , "domain:" <+> pretty domain - , "constant:" <+> pretty constant - ] - - up :: TypeOf_Up m - up ctxt (name, domain@(DomainPartition Partition_Occurrence _ innerDomain)) = - case (lookup (nameNumParts domain name) ctxt, lookup (nameWhichPart domain name) ctxt) of - ( Just (viewConstantInt -> Just numPartsValue) , - Just (viewConstantMatrix -> Just (_, whichPartValues)) ) -> do - members <- domainValues innerDomain - return - ( name - , normaliseConstant $ ConstantAbstract $ AbsLitPartition - [ [ member | (member, b) <- zip members whichPartValues, b == ConstantInt TagInt bucket ] - | bucket <- [1..numPartsValue] - ] - ) - (Just val, _) -> fail $ vcat $ - [ "(in Partition Occurrence up)" - , "Expecting an integer literal for:" <+> pretty (nameNumParts domain name) - , "But got:" <+> pretty val - , "When working on:" <+> pretty name - , "With domain:" <+> pretty domain - ] ++ - ("Bindings in context:" : prettyContext ctxt) - (_, Just val) -> fail $ vcat $ - [ "(in Partition Occurrence up)" - , "Expecting a matrix literal for:" <+> pretty (nameWhichPart domain name) - , "But got:" <+> pretty val - , "When working on:" <+> pretty name - , "With domain:" <+> pretty domain - ] ++ - ("Bindings in context:" : prettyContext ctxt) - (Nothing, _) -> fail $ vcat $ - [ "(in Partition Occurrence up)" - , "No value for:" <+> pretty (nameNumParts domain name) - , "When working on:" <+> pretty name - , "With domain:" <+> pretty domain - ] ++ - ("Bindings in context:" : prettyContext ctxt) - up ctxt (name, domain) = - na $ vcat [ "{up} Occurrence" - , "name:" <+> pretty name - , "domain:" <+> pretty domain - , "ctxt:" <+> vcat (map pretty ctxt) - ] - - symmetryOrdering :: TypeOf_SymmetryOrdering m - symmetryOrdering innerSO downX1 inp domain = do - xs <- downX1 inp - Just xsDoms' <- downD ("SO", domain) - let xsDoms = map snd xsDoms' - soValues <- sequence [ innerSO downX1 x xDom | (x, xDom) <- zip xs xsDoms ] -<<<<<<< HEAD - return (fromList soValues) -======= - return $ AbstractLiteral $ AbsLitTuple soValues - ->>>>>>> master diff --git a/src/Conjure/Representations/Record.hs.orig b/src/Conjure/Representations/Record.hs.orig deleted file mode 100644 index 3a324772f4..0000000000 --- a/src/Conjure/Representations/Record.hs.orig +++ /dev/null @@ -1,90 +0,0 @@ -{-# LANGUAGE QuasiQuotes #-} - -module Conjure.Representations.Record - ( record - ) where - --- conjure -import Conjure.Prelude -import Conjure.Bug -import Conjure.Language -import Conjure.Representations.Internal - - -record :: forall m . (MonadFail m, NameGen m) => Representation m -record = Representation chck downD structuralCons downC up symmetryOrdering - - where - - chck :: TypeOf_ReprCheck m - chck f (DomainRecord ds) = do - let names = map fst ds - outDoms <- sequence <$> mapM (f . snd) ds - return [ DomainRecord (zip names ds') | ds' <- outDoms ] - chck _ _ = return [] - - mkName name n = mconcat [name, "_", n] - - downD :: TypeOf_DownD m - downD (name, DomainRecord ds) = return $ Just - [ (mkName name n, d) - | (n,d) <- ds - ] - downD _ = na "{downD}" - - structuralCons :: TypeOf_Structural m - structuralCons f downX1 (DomainRecord ds) = return $ \ tup -> do - refs <- downX1 tup - concat <$> sequence - [ do - innerStructuralConsGen <- f dom - outs <- innerStructuralConsGen ref - return outs - | (ref, (_n, dom)) <- zip refs ds - ] - structuralCons _ _ _ = na "{structuralCons} record" - - -- TODO: check if (length ds == length cs) - downC :: TypeOf_DownC m - downC (name, DomainRecord ds, ConstantAbstract (AbsLitRecord cs)) - | sort (map fst ds) == sort (map fst cs) = return $ Just - [ case lookup n cs of - Nothing -> bug "Record.downC" - Just c -> (mkName name n, d, c) - | (n,d) <- ds - ] - downC (n, d, c) = - na $ "{downC} record" <+> vcat - [ "name :" <+> pretty n - , "domain:" <+> pretty d - , "value :" <+> pretty c - ] - - up :: TypeOf_Up m - up ctxt (name, DomainRecord ds) = do - let names = map (mkName name . fst) ds - vals <- forM names $ \ n -> - case lookup n ctxt of - Nothing -> fail $ vcat $ - [ "(in Record up)" - , "No value for:" <+> pretty n - , "When working on:" <+> pretty name - , "With domain:" <+> pretty (DomainRecord ds) - ] ++ - ("Bindings in context:" : prettyContext ctxt) - Just val -> return (n, val) - -- TODO: check if (length ds == length vals) - return (name, ConstantAbstract (AbsLitRecord vals)) - up _ _ = na "{up}" - - symmetryOrdering :: TypeOf_SymmetryOrdering m - symmetryOrdering innerSO downX1 inp domain = do - xs <- downX1 inp - Just xsDoms' <- downD ("SO", domain) - let xsDoms = map snd xsDoms' - soValues <- sequence [ innerSO downX1 x xDom | (x, xDom) <- zip xs xsDoms ] - return $ AbstractLiteral $ AbsLitTuple soValues -<<<<<<< HEAD -======= - ->>>>>>> master diff --git a/src/Conjure/Representations/Set/Explicit.hs.orig b/src/Conjure/Representations/Set/Explicit.hs.orig deleted file mode 100644 index c0005d64c2..0000000000 --- a/src/Conjure/Representations/Set/Explicit.hs.orig +++ /dev/null @@ -1,117 +0,0 @@ -{-# LANGUAGE QuasiQuotes #-} - -module Conjure.Representations.Set.Explicit ( setExplicit ) where - --- conjure -import Conjure.Prelude -import Conjure.Language -import Conjure.Representations.Internal - - -setExplicit :: forall m . (MonadFail m, NameGen m) => Representation m -setExplicit = Representation chck downD structuralCons downC up symmetryOrdering - - where - - -- | We can represent any inner domain but set must be fixed size - chck :: TypeOf_ReprCheck m - chck f (DomainSet _ attrs@(SetAttr SizeAttr_Size{}) innerDomain) = - map (DomainSet Set_Explicit attrs) <$> f innerDomain - chck _ _ = return [] - - outName :: Domain HasRepresentation x -> Name -> Name - outName = mkOutName Nothing - - -- | A 1D matrix of size of set containing innerDomain objects - downD :: TypeOf_DownD m - downD (name, domain@(DomainSet Set_Explicit (SetAttr (SizeAttr_Size size)) innerDomain)) = return $ Just - [ ( outName domain name - , DomainMatrix - (DomainInt TagInt [RangeBounded 1 size]) - innerDomain - ) ] - downD _ = na "{downD} Explicit" - - -- | Enforce lex ordering of matrix (symmetry breaking) and inner structural constraints of - -- 'active' elements of inner domain - structuralCons :: TypeOf_Structural m - structuralCons f downX1 (DomainSet Set_Explicit (SetAttr (SizeAttr_Size size)) innerDomain) = do - let - -- | Makes sure i'th value is lex less than (i+1)'th value - -- a symmetry breaking structural constraint - ordering m = do - (iPat, i) <- quantifiedVar - return $ return -- for list - [essence| - forAll &iPat : int(1..&size-1) . - &m[&i] .< &m[&i+1] - |] - - -- | Enforces structural constraints for the elements of the inner domain - -- that are in the set. - innerStructuralCons m = do - (iPat, i) <- quantifiedVarOverDomain [essenceDomain| int(1..&size) |] - let activeZone b = [essence| forAll &iPat : int(1..&size) . &b |] - - -- preparing structural constraints for the inner guys - innerStructuralConsGen <- f innerDomain - - let inLoop = [essence| &m[&i] |] - outs <- innerStructuralConsGen inLoop - return (map activeZone outs) - - return $ \ ref -> do - refs <- downX1 ref - case refs of - [m] -> - concat <$> sequence - [ ordering m - , innerStructuralCons m - ] - _ -> na "{structuralCons} Explicit" - structuralCons _ _ _ = na "{structuralCons} Explicit" - - downC :: TypeOf_DownC m - downC ( name - , domain@(DomainSet Set_Explicit (SetAttr (SizeAttr_Size size)) innerDomain) - , ConstantAbstract (AbsLitSet constants) - ) = - let outIndexDomain = mkDomainIntB 1 size - in return $ Just - [ ( outName domain name - , DomainMatrix outIndexDomain innerDomain - , ConstantAbstract $ AbsLitMatrix outIndexDomain constants - ) ] - downC _ = na "{downC} Explicit" - - up :: TypeOf_Up m - up ctxt (name, domain@(DomainSet Set_Explicit (SetAttr (SizeAttr_Size _)) _)) = - case lookup (outName domain name) ctxt of - Nothing -> fail $ vcat $ - [ "(in Set Explicit up)" - , "No value for:" <+> pretty (outName domain name) - , "When working on:" <+> pretty name - , "With domain:" <+> pretty domain - ] ++ - ("Bindings in context:" : prettyContext ctxt) - Just constant -> - case viewConstantMatrix constant of - Just (_, vals) -> - return (name, ConstantAbstract (AbsLitSet vals)) - _ -> fail $ vcat - [ "Expecting a matrix literal for:" <+> pretty (outName domain name) - , "But got:" <+> pretty constant - , "When working on:" <+> pretty name - , "With domain:" <+> pretty domain - ] - up _ _ = na "{up} Explicit" - - symmetryOrdering :: TypeOf_SymmetryOrdering m - symmetryOrdering innerSO downX1 inp domain = do - [inner] <- downX1 inp - Just [(_, innerDomain)] <- downD ("SO", domain) - innerSO downX1 inner innerDomain -<<<<<<< HEAD - -======= ->>>>>>> master diff --git a/src/Conjure/Representations/Set/ExplicitVarSizeWithDummy.hs.orig b/src/Conjure/Representations/Set/ExplicitVarSizeWithDummy.hs.orig deleted file mode 100644 index b2687270ec..0000000000 --- a/src/Conjure/Representations/Set/ExplicitVarSizeWithDummy.hs.orig +++ /dev/null @@ -1,178 +0,0 @@ -{-# LANGUAGE QuasiQuotes #-} - -module Conjure.Representations.Set.ExplicitVarSizeWithDummy ( setExplicitVarSizeWithDummy ) where - --- conjure -import Conjure.Prelude -import Conjure.Bug -import Conjure.Language -import Conjure.Language.DomainSizeOf -import Conjure.Language.Expression.DomainSizeOf () -import Conjure.Representations.Internal -import Conjure.Representations.Common - - -setExplicitVarSizeWithDummy :: forall m . (MonadFail m, NameGen m) => Representation m -setExplicitVarSizeWithDummy = Representation chck downD structuralCons downC up symmetryOrdering - - where - - chck :: TypeOf_ReprCheck m - chck _ (DomainSet _ (SetAttr SizeAttr_Size{}) _) = return [] - chck f (DomainSet _ attrs innerDomain@DomainInt{}) = - map (DomainSet Set_ExplicitVarSizeWithDummy attrs) <$> f innerDomain - chck _ _ = return [] - - outName :: Domain HasRepresentation x -> Name -> Name - outName = mkOutName Nothing - - getMaxSize attrs innerDomain = case attrs of - SizeAttr_MaxSize x -> return x - SizeAttr_MinMaxSize _ x -> return x - _ -> reTag TagInt <$> domainSizeOf innerDomain - - calcDummyDomain :: Pretty r => Domain r Expression -> Domain r Expression - calcDummyDomain (DomainInt t [RangeBounded lb ub]) = - DomainInt t [RangeBounded lb [essence| &ub + 1 |]] - calcDummyDomain dom@(DomainInt t ranges) = - let dummyElem = calcDummyElem dom - in DomainInt t (ranges ++ [RangeSingle dummyElem]) - calcDummyDomain dom = bug ("ExplicitVarSizeWithDummy.calcDummyDomain" <+> pretty dom) - - calcDummyElem :: Pretty r => Domain r Expression -> Expression - calcDummyElem dom = - let theMax = bugFail "calcDummyElem: maxOfDomain" (maxOfDomain dom) - in [essence| &theMax + 1 |] - - calcDummyElemC :: Pretty r => Domain r Constant -> Constant - calcDummyElemC (DomainInt _ []) = bug "ExplicitVarSizeWithDummy.calcDummyElemC []" - calcDummyElemC (DomainInt t rs) = ConstantInt t $ - 1 + maximum [ i - | r <- rs - , i <- case r of - RangeSingle (ConstantInt _ x) -> [x] - RangeBounded (ConstantInt _ x) (ConstantInt _ y) -> [x..y] - _ -> bug ("ExplicitVarSizeWithDummy.calcDummyElemC" <+> pretty r) - ] - calcDummyElemC d = bug ("ExplicitVarSizeWithDummy.calcDummyElemC" <+> pretty d) - - downD :: TypeOf_DownD m - downD (name, domain@(DomainSet Set_ExplicitVarSizeWithDummy (SetAttr attrs) innerDomain@DomainInt{})) = do - let domainWithDummy = calcDummyDomain innerDomain - maxSize <- getMaxSize attrs innerDomain - return $ Just - [ ( outName domain name - , DomainMatrix - (DomainInt TagInt [RangeBounded 1 maxSize]) - domainWithDummy - ) ] - downD _ = na "{downD} ExplicitVarSizeWithDummy" - - structuralCons :: TypeOf_Structural m - structuralCons f downX1 (DomainSet Set_ExplicitVarSizeWithDummy (SetAttr attrs) innerDomain) = do - maxSize <- getMaxSize attrs innerDomain - let - dummyElem = calcDummyElem innerDomain - - ordering m = do - (iPat, i) <- quantifiedVar - return $ return -- for list - [essence| - forAll &iPat : int(1..&maxSize-1) . - (&m[&i] .< &m[&i+1]) \/ (&m[&i] = &dummyElem) - |] - - dummyToTheRight m = do - (iPat, i) <- quantifiedVar - return $ return -- for list - [essence| - forAll &iPat : int(1..&maxSize-1) . - (&m[&i] = &dummyElem) -> (&m[&i+1] = &dummyElem) - |] - - cardinality m = do - (iPat, i) <- quantifiedVar - return [essence| sum &iPat : int(1..&maxSize) . toInt(&m[&i] != &dummyElem) |] - - innerStructuralCons m = do - (iPat, i) <- quantifiedVarOverDomain [essenceDomain| int(1..&maxSize) |] - let activeZone b = [essence| forAll &iPat : int(1..&maxSize) . &m[&i] != &dummyElem -> &b |] - - -- preparing structural constraints for the inner guys - innerStructuralConsGen <- f innerDomain - - let inLoop = [essence| &m[&i] |] - outs <- innerStructuralConsGen inLoop - return (map activeZone outs) - - return $ \ ref -> do - refs <- downX1 ref - case refs of - [m] -> - concat <$> sequence - [ ordering m - , dummyToTheRight m - , mkSizeCons attrs <$> cardinality m - , innerStructuralCons m - ] - _ -> na "{structuralCons} ExplicitVarSizeWithDummy" - structuralCons _ _ _ = na "{structuralCons} ExplicitVarSizeWithDummy" - - downC :: TypeOf_DownC m - downC ( name - , domain@(DomainSet Set_ExplicitVarSizeWithDummy (SetAttr attrs) innerDomain) - , ConstantAbstract (AbsLitSet constants) - ) = do - maxSize <- getMaxSize attrs innerDomain - let indexDomain i = mkDomainIntB (fromInt i) maxSize - maxSizeInt <- - case maxSize of - ConstantInt _ x -> return x - _ -> fail $ vcat - [ "Expecting an integer for the maxSize attribute." - , "But got:" <+> pretty maxSize - , "When working on:" <+> pretty name - , "With domain:" <+> pretty domain - ] - let dummyElem = calcDummyElemC innerDomain - let dummies = replicate (fromInteger (maxSizeInt - genericLength constants)) dummyElem - return $ Just - [ ( outName domain name - , DomainMatrix (indexDomain 1) innerDomain - , ConstantAbstract $ AbsLitMatrix (indexDomain 1) (constants ++ dummies) - ) - ] - downC _ = na "{downC} ExplicitVarSizeWithDummy" - - up :: TypeOf_Up m - up ctxt (name, domain@(DomainSet Set_ExplicitVarSizeWithDummy _ innerDomain)) = do - let dummyElem = calcDummyElemC innerDomain - case lookup (outName domain name) ctxt of - Nothing -> fail $ vcat $ - [ "(in Set ExplicitVarSizeWithDummy up)" - , "No value for:" <+> pretty (outName domain name) - , "When working on:" <+> pretty name - , "With domain:" <+> pretty domain - ] ++ - ("Bindings in context:" : prettyContext ctxt) - Just constant -> - case viewConstantMatrix constant of - Just (_, vals) -> - return (name, ConstantAbstract (AbsLitSet [ v | v <- vals, v /= dummyElem ])) - _ -> fail $ vcat - [ "Expecting a matrix literal for:" <+> pretty (outName domain name) - , "But got:" <+> pretty constant - , "When working on:" <+> pretty name - , "With domain:" <+> pretty domain - ] - up _ _ = na "{up} ExplicitVarSizeWithDummy" - - symmetryOrdering :: TypeOf_SymmetryOrdering m - symmetryOrdering innerSO downX1 inp domain = do - [inner] <- downX1 inp - Just [(_, innerDomain)] <- downD ("SO", domain) - innerSO downX1 inner innerDomain -<<<<<<< HEAD -======= - ->>>>>>> master diff --git a/src/Conjure/Representations/Tuple.hs.orig b/src/Conjure/Representations/Tuple.hs.orig deleted file mode 100644 index 2673bde1ec..0000000000 --- a/src/Conjure/Representations/Tuple.hs.orig +++ /dev/null @@ -1,90 +0,0 @@ -{-# LANGUAGE QuasiQuotes #-} -{-# LANGUAGE ParallelListComp #-} - -module Conjure.Representations.Tuple - ( tuple - ) where - --- conjure -import Conjure.Prelude -import Conjure.Language -import Conjure.Representations.Internal - --- text -import Data.Text ( pack ) - - -tuple :: forall m . (MonadFail m, NameGen m) => Representation m -tuple = Representation chck downD structuralCons downC up symmetryOrdering - - where - - chck :: TypeOf_ReprCheck m - chck f (DomainTuple ds) = map DomainTuple . sequence <$> mapM f ds - chck _ _ = return [] - - mkName :: Name -> Int -> Name - mkName name i = mconcat [name, "_", Name (pack (show i))] - - downD :: TypeOf_DownD m - downD (name, DomainTuple ds) = return $ Just - [ (mkName name i, d) - | i <- [1..] - | d <- ds - ] - downD _ = na "{downD}" - - structuralCons :: TypeOf_Structural m - structuralCons f downX1 (DomainTuple ds) = return $ \ tup -> do - refs <- downX1 tup - concat <$> sequence - [ do - innerStructuralConsGen <- f dom - outs <- innerStructuralConsGen ref - return outs - | (ref, dom) <- zip refs ds - ] - structuralCons _ _ _ = na "{structuralCons} tuple" - - downC :: TypeOf_DownC m - downC (name, DomainTuple ds, ConstantAbstract (AbsLitTuple cs)) - | length ds == length cs = return $ Just - [ (mkName name i, d, c) - | i <- [1..] - | d <- ds - | c <- cs - ] - downC (n, d, c) = - na $ "{downC} tuple" <+> vcat - [ "name :" <+> pretty n - , "domain:" <+> pretty d - , "value :" <+> pretty c - ] - - up :: TypeOf_Up m - up ctxt (name, DomainTuple ds) = do - let names = map (mkName name) [1 .. length ds] - vals <- forM names $ \ n -> - case lookup n ctxt of - Nothing -> fail $ vcat $ - [ "(in Tuple up)" - , "No value for:" <+> pretty n - , "When working on:" <+> pretty name - , "With domain:" <+> pretty (DomainTuple ds) - ] ++ - ("Bindings in context:" : prettyContext ctxt) - Just val -> return val - return (name, ConstantAbstract (AbsLitTuple vals)) - up _ _ = na "{up}" - - symmetryOrdering :: TypeOf_SymmetryOrdering m - symmetryOrdering innerSO downX1 inp domain = do - xs <- downX1 inp - Just xsDoms' <- downD ("SO", domain) - let xsDoms = map snd xsDoms' - soValues <- sequence [ innerSO downX1 x xDom | (x, xDom) <- zip xs xsDoms ] - return $ AbstractLiteral $ AbsLitTuple soValues -<<<<<<< HEAD -======= - ->>>>>>> master diff --git a/src/Conjure/Representations/Variant.hs.orig b/src/Conjure/Representations/Variant.hs.orig deleted file mode 100644 index 80b443e699..0000000000 --- a/src/Conjure/Representations/Variant.hs.orig +++ /dev/null @@ -1,128 +0,0 @@ -{-# LANGUAGE QuasiQuotes #-} - -module Conjure.Representations.Variant - ( variant - ) where - --- conjure -import Conjure.Prelude -import Conjure.Bug -import Conjure.Language -import Conjure.Representations.Internal -import Conjure.Language.ZeroVal ( EnumerateDomain, zeroVal ) - - -variant :: forall m . (MonadFail m, NameGen m, EnumerateDomain m) => Representation m -variant = Representation chck downD structuralCons downC up symmetryOrdering - - where - - chck :: TypeOf_ReprCheck m - chck f (DomainVariant ds) = do - let names = map fst ds - outDoms <- sequence <$> mapM (f . snd) ds - return [ DomainVariant (zip names ds') | ds' <- outDoms ] - chck _ _ = return [] - - mkName name n = mconcat [name, "_", n] - - downD :: TypeOf_DownD m - downD (name, DomainVariant ds) = return $ Just - $ (mkName name "_tag", defRepr $ mkDomainIntB 1 (fromInt (genericLength ds))) - : [ (mkName name n, d) - | (n,d) <- ds - ] - downD _ = na "{downD}" - - structuralCons :: TypeOf_Structural m - structuralCons f downX1 (DomainVariant ds) = do - let - innerStructuralCons which thisIndex thisRef thisDom = do - let activeZone b = [essence| &which = &thisIndex -> &b |] - -- preparing structural constraints for the inner guys - innerStructuralConsGen <- f thisDom - outs <- innerStructuralConsGen thisRef - return (map activeZone outs) - - dontCares which thisIndex thisRef = - [essence| &which != &thisIndex -> dontCare(&thisRef) |] - - return $ \ rec -> do - (which:refs) <- downX1 rec - concat <$> sequence - [ do - isc <- innerStructuralCons which (fromInt i) ref dom - let dcs = dontCares which (fromInt i) ref - return (dcs:isc) - | (i, ref, (_, dom)) <- zip3 [1..] refs ds - ] - structuralCons _ _ _ = na "{structuralCons} variant" - - -- TODO: check if (length ds == length cs) - downC :: TypeOf_DownC m - downC (name, DomainVariant ds, ConstantAbstract (AbsLitVariant _ n c)) = do - let theTag = - ( mkName name "_tag" - , defRepr $ mkDomainIntB 1 (fromInt (genericLength ds)) - , case [ fromInt i - | (i, (n', _)) <- zip [1..] ds - , n == n' ] of - [v] -> v - _ -> bug "downC variant tag" - ) - outs <- forM ds $ \ (n', d) -> do - c' <- if n == n' - then return c - else zeroVal d - return (mkName name n', d, c') - return $ Just (theTag : outs) - downC (n, d, c) = - na $ "{downC} variant" <+> vcat - [ "name :" <+> pretty n - , "domain:" <+> pretty d - , "value :" <+> pretty c - ] - - up :: TypeOf_Up m - up ctxt (name, DomainVariant ds) = do - let dsForgotten = [ (n, defRepr d) | (n,d) <- ds ] - case lookup (mkName name "_tag") ctxt of - Just (ConstantInt _ i) -> - let iTag = at ds (fromInteger (i-1)) |> fst - iName = mkName name iTag - in case lookup iName ctxt of - Just val -> return (name, ConstantAbstract $ AbsLitVariant (Just dsForgotten) iTag val) - Nothing -> fail $ vcat $ - [ "(in Variant up 1)" - , "No value for:" <+> pretty iName - , "When working on:" <+> pretty name - , "With domain:" <+> pretty (DomainRecord ds) - ] ++ - ("Bindings in context:" : prettyContext ctxt) - Nothing -> fail $ vcat $ - [ "(in Variant up 2)" - , "No value for:" <+> pretty (mkName name "_tag") - , "When working on:" <+> pretty name - , "With domain:" <+> pretty (DomainRecord ds) - ] ++ - ("Bindings in context:" : prettyContext ctxt) - Just val -> fail $ vcat $ - [ "Expecting an integer value for:" <+> pretty (mkName name "_tag") - , "When working on:" <+> pretty name - , "With domain:" <+> pretty (DomainRecord ds) - , "But got:" <+> pretty val - ] ++ - ("Bindings in context:" : prettyContext ctxt) - up _ _ = na "{up}" - - symmetryOrdering :: TypeOf_SymmetryOrdering m - symmetryOrdering innerSO downX1 inp domain = do - xs <- downX1 inp - Just xsDoms' <- downD ("SO", domain) - let xsDoms = map snd xsDoms' - soValues <- sequence [ innerSO downX1 x xDom | (x, xDom) <- zip xs xsDoms ] - return (fromList soValues) -<<<<<<< HEAD -======= - ->>>>>>> master diff --git a/src/Conjure/UI/Model.hs.orig b/src/Conjure/UI/Model.hs.orig deleted file mode 100644 index da88b01869..0000000000 --- a/src/Conjure/UI/Model.hs.orig +++ /dev/null @@ -1,2916 +0,0 @@ -{-# LANGUAGE Rank2Types #-} -{-# LANGUAGE TupleSections #-} -{-# LANGUAGE QuasiQuotes #-} -{-# LANGUAGE ViewPatterns #-} -{-# LANGUAGE RecordWildCards #-} - -module Conjure.UI.Model - ( outputModels - , Strategy(..), Config(..), parseStrategy - , nbUses - , modelRepresentationsJSON - ) where - -import Conjure.Prelude -import Conjure.Bug -import Conjure.UserError -import Conjure.Language.Definition -import Conjure.Language.Expression.Internal.Generated () -import Conjure.Language.Domain -import Conjure.Language.Type -import Conjure.Language.Pretty -import Conjure.Language.CategoryOf -import Conjure.Language.TypeOf -import Conjure.Compute.DomainOf -import Conjure.Language.Lenses -import Conjure.Language.TH ( essence ) -import Conjure.Language.Expression ( reDomExp ) -import Conjure.Language.Constant ( reDomConst ) -import Conjure.Language.Expression.Op -import Conjure.Language.ModelStats ( modelInfo ) -import Conjure.Language.Instantiate ( instantiateExpression, trySimplify ) -import Conjure.Process.Sanity ( sanityChecks ) -import Conjure.Process.Enums ( removeEnumsFromModel ) -import Conjure.Process.Unnameds ( removeUnnamedsFromModel ) -import Conjure.Process.FiniteGivens ( finiteGivens ) -import Conjure.Process.LettingsForComplexInDoms ( lettingsForComplexInDoms - , inlineLettingDomainsForDecls - , removeDomainLettings - ) -import Conjure.Process.AttributeAsConstraints ( attributeAsConstraints, mkAttributeToConstraint ) -import Conjure.Process.InferAttributes ( inferAttributes ) -import Conjure.Process.DealWithCuts ( dealWithCuts ) -import Conjure.Process.Enumerate ( EnumerateDomain ) -import Conjure.Language.NameResolution ( resolveNames, resolveNamesX ) -import Conjure.UI.TypeCheck ( typeCheckModel, typeCheckModel_StandAlone ) -import Conjure.UI ( OutputFormat(..) ) -import Conjure.UI.IO ( writeModel ) -import Conjure.UI.NormaliseQuantified ( distinctQuantifiedVars, renameQuantifiedVarsToAvoidShadowing - , normaliseQuantifiedVariablesS, normaliseQuantifiedVariablesE - ) - -import Conjure.Representations - ( downX, downX1, downD, reprOptions, getStructurals - , symmetryOrdering - , reprsStandardOrderNoLevels, reprsStandardOrder, reprsSparseOrder - ) - -import Conjure.Rules.Definition - -import qualified Conjure.Rules.Vertical.Tuple as Vertical.Tuple -import qualified Conjure.Rules.Vertical.Record as Vertical.Record -import qualified Conjure.Rules.Vertical.Variant as Vertical.Variant -import qualified Conjure.Rules.Vertical.Matrix as Vertical.Matrix - -import qualified Conjure.Rules.Horizontal.Set as Horizontal.Set -import qualified Conjure.Rules.Vertical.Set.Explicit as Vertical.Set.Explicit -import qualified Conjure.Rules.Vertical.Set.ExplicitVarSizeWithDummy as Vertical.Set.ExplicitVarSizeWithDummy -import qualified Conjure.Rules.Vertical.Set.ExplicitVarSizeWithFlags as Vertical.Set.ExplicitVarSizeWithFlags -import qualified Conjure.Rules.Vertical.Set.ExplicitVarSizeWithMarker as Vertical.Set.ExplicitVarSizeWithMarker -import qualified Conjure.Rules.Vertical.Set.Occurrence as Vertical.Set.Occurrence - -import qualified Conjure.Rules.Horizontal.MSet as Horizontal.MSet -import qualified Conjure.Rules.Vertical.MSet.Occurrence as Vertical.MSet.Occurrence -import qualified Conjure.Rules.Vertical.MSet.ExplicitWithFlags as Vertical.MSet.ExplicitWithFlags -import qualified Conjure.Rules.Vertical.MSet.ExplicitWithRepetition as Vertical.MSet.ExplicitWithRepetition - -import qualified Conjure.Rules.Horizontal.Function as Horizontal.Function -import qualified Conjure.Rules.Vertical.Function.Function1D as Vertical.Function.Function1D -import qualified Conjure.Rules.Vertical.Function.Function1DPartial as Vertical.Function.Function1DPartial -import qualified Conjure.Rules.Vertical.Function.FunctionND as Vertical.Function.FunctionND -import qualified Conjure.Rules.Vertical.Function.FunctionNDPartial as Vertical.Function.FunctionNDPartial -import qualified Conjure.Rules.Vertical.Function.FunctionAsRelation as Vertical.Function.FunctionAsRelation - -import qualified Conjure.Rules.Horizontal.Sequence as Horizontal.Sequence -import qualified Conjure.Rules.Vertical.Sequence.ExplicitBounded as Vertical.Sequence.ExplicitBounded - -import qualified Conjure.Rules.Horizontal.Relation as Horizontal.Relation -import qualified Conjure.Rules.Vertical.Relation.RelationAsMatrix as Vertical.Relation.RelationAsMatrix -import qualified Conjure.Rules.Vertical.Relation.RelationAsSet as Vertical.Relation.RelationAsSet - -import qualified Conjure.Rules.Horizontal.Partition as Horizontal.Partition -import qualified Conjure.Rules.Vertical.Partition.PartitionAsSet as Vertical.Partition.PartitionAsSet -import qualified Conjure.Rules.Vertical.Partition.Occurrence as Vertical.Partition.Occurrence -import qualified Conjure.Rules.Transform as Transform - -import qualified Conjure.Rules.Vertical.Permutation as Vertical.Permutation -import qualified Conjure.Rules.Horizontal.Permutation as Horizontal.Permutation - -import qualified Conjure.Rules.BubbleUp as BubbleUp -import qualified Conjure.Rules.DontCare as DontCare -import qualified Conjure.Rules.TildeOrdering as TildeOrdering - --- base -import System.IO ( hFlush, stdout ) -import Data.IORef ( IORef, newIORef, readIORef, writeIORef ) -import System.IO.Unsafe ( unsafePerformIO ) - --- uniplate -import Data.Generics.Uniplate.Zipper ( hole, replaceHole ) -import Data.Generics.Uniplate.Zipper as Zipper ( right, up ) - --- pipes -import Pipes ( Pipe, Producer, await, yield, (>->), cat ) -import qualified Pipes.Prelude as Pipes ( foldM ) - -import qualified Data.Aeson.Types as JSON -- aeson -import qualified Data.HashMap.Strict as M -- containers -import qualified Data.Vector as V -- vector - - -outputModels :: - forall m . - MonadIO m => - MonadFail m => - MonadLog m => - NameGen m => - EnumerateDomain m => - MonadUserError m => - (?typeCheckerMode :: TypeCheckerMode) => - Config -> - Model -> - m () -outputModels config model = do - - liftIO $ writeIORef recordedResponses (responses config) - liftIO $ writeIORef recordedResponsesRepresentation (responsesRepresentation config) - - -- Savile Row does not support ' characters in identifiers - -- We could implement a workaround where we insert a marker (like __PRIME__) for each ' character - -- and recover these after a solution is found. - -- But this will be too hairy, instead we will reject such identifiers for now. - -- If somebody really needs to use a ' character as part of an identifier, we can revisit this decision. - let - primeyIdentifiers = catMaybes - [ if '\'' `elem` textToString identifier - then Just identifier - else Nothing - | Declaration decl <- mStatements model - , Name identifier <- universeBi decl - ] - unless (null primeyIdentifiers) $ userErr1 $ vcat - ["Identifiers cannot contain a quotation mark character in them:" <+> prettyList id "," primeyIdentifiers] - - let dir = outputDirectory config - - unless (estimateNumberOfModels config) $ - liftIO $ createDirectoryIfMissing True dir - - let - limitModelsIfEstimating :: Pipe LogOrModel LogOrModel m () - limitModelsIfEstimating = - if estimateNumberOfModels config - then limitModelsNeeded 1 - else Pipes.cat - - limitModelsIfNeeded :: Pipe LogOrModel LogOrModel m () - limitModelsIfNeeded = maybe Pipes.cat limitModelsNeeded (limitModels config) - - limitModelsNeeded :: Int -> Pipe LogOrModel LogOrModel m () - limitModelsNeeded 0 = return () - limitModelsNeeded n = do - x <- Pipes.await - Pipes.yield x - case x of - Left {} -> limitModelsNeeded n -- yielded a log, still n models to produce - Right{} -> limitModelsNeeded (n-1) -- yielded a model, produce n-1 more models - - each i logOrModel = - case logOrModel of - Left (l,msg) -> do - log l msg - return i - Right eprime -> do - let gen = - if smartFilenames config - then [ choice - | (_question, choice, numOptions) <- - eprime |> mInfo |> miTrailCompact - , numOptions > 1 - ] |> map (('_':) . show) - |> concat - else padLeft 6 '0' (show i) - let filename = dir "model" ++ gen ++ ".eprime" - if estimateNumberOfModels config - then do - let - estimate :: Integer - estimate = product $ 1 : [ toInteger numOptions - | (_question, _choice, numOptions) <- - eprime |> mInfo |> miTrailCompact - ] - liftIO $ print - $ "These options would generate at least" - <+> pretty estimate - <+> (if estimate == 1 then "model" else "models") <> "." - else writeModel (lineWidth config) Plain (Just filename) eprime - return (i+1) - - let ?typeCheckerMode = RelaxedIntegerTags - - Pipes.foldM each - (return (numberingStart config)) - (const $ return ()) - (toCompletion config model - >-> limitModelsIfNeeded - >-> limitModelsIfEstimating) - - -toCompletion :: forall m . - MonadIO m => - MonadFail m => - NameGen m => - EnumerateDomain m => - (?typeCheckerMode :: TypeCheckerMode) => - Config -> - Model -> - Producer LogOrModel m () -toCompletion config m = do - m2 <- let ?typeCheckerMode = StronglyTyped in prologue config m - namegenst <- exportNameGenState - let m2Info = mInfo m2 - let m3 = m2 { mInfo = m2Info { miStrategyQ = strategyQ config - , miStrategyA = strategyA config - , miNameGenState = namegenst - } } - logDebug $ modelInfo m3 - loopy (StartOver m3) - where - driver :: Driver - driver = strategyToDriver config - - loopy :: ModelWIP -> Producer LogOrModel m () - loopy modelWIP = do - logDebug $ "[loop]" <+> pretty ((modelWIPOut modelWIP) {mInfo = def}) - qs <- remainingWIP config modelWIP - if null qs - then do - let model = modelWIPOut modelWIP - model' <- epilogue model - yield (Right model') - else do - nextModels <- driver qs - mapM_ loopy nextModels - - -modelRepresentationsJSON :: - MonadFail m => - NameGen m => - EnumerateDomain m => - MonadLog m => - (?typeCheckerMode :: TypeCheckerMode) => - Model -> m JSONValue -modelRepresentationsJSON model = do - reprs <- modelRepresentations model - return $ JSON.Array $ V.fromList - [ JSON.Object $ M.fromList - [ "name" ~~ r name - , "representations" ~~ representationsJSON - ] - | (name, domains) <- reprs - , let representationsJSON = JSON.Array $ V.fromList - [ JSON.Object $ M.fromList - [ "description" ~~ r d - , "answer" ~~ toJSON i - ] - | (i, d) <- zip allNats domains - ] - ] - where - (~~) :: Text -> JSONValue -> (Text, JSONValue) - x ~~ y = (x, y) - r s = JSON.String $ stringToText $ render 100000 $ pretty s - - -modelRepresentations :: - MonadFail m => - NameGen m => - EnumerateDomain m => - MonadLog m => - (?typeCheckerMode :: TypeCheckerMode) => - Model -> m [(Name, [Domain HasRepresentation Expression])] -modelRepresentations model0 = do - model <- prologue model0 - concatForM (mStatements model) $ \case - Declaration (FindOrGiven _ name domain) -> do - domOpts <- reprOptions reprsStandardOrderNoLevels domain - return [(name, domOpts)] - _ -> return [] - - --- | If a rule is applied at a position P, the MonadZipper will be retained focused at that location --- and new rules will be tried using P as the top of the zipper-tree. --- The whole model (containing P too) will be tried later for completeness. -remainingWIP :: - MonadFail m => - MonadLog m => - NameGen m => - EnumerateDomain m => - (?typeCheckerMode :: TypeCheckerMode) => - Config -> - ModelWIP -> - m [Question] -remainingWIP config (StartOver model) - | Just modelZipper <- mkModelZipper model = do - qs <- remaining config modelZipper (mInfo model) - return qs - | otherwise = return [] -remainingWIP config wip@(TryThisFirst modelZipper info) = do - qs <- remaining config modelZipper info - case (null qs, Zipper.right modelZipper, Zipper.up modelZipper) of - (False, _, _) -> return qs -- not null, return - (_, Just r, _) -> remainingWIP config (TryThisFirst r info) -- there is a sibling to the right - (_, _, Just u) -> remainingWIP config (TryThisFirst u info) -- there is a parent - _ -> remainingWIP config (StartOver (modelWIPOut wip)) -- we are done here, - -- start-over the whole model in case - -- something on the left needs attention. - - -remaining :: - MonadFail m => - MonadLog m => - NameGen m => - EnumerateDomain m => - (?typeCheckerMode :: TypeCheckerMode) => - Config -> - ModelZipper -> - ModelInfo -> - m [Question] -remaining config modelZipper minfo = do - -- note: the call to getQuestions can update the NameGen state - importNameGenState (minfo |> miNameGenState) - questions <- getQuestions config modelZipper - namegenst0 <- exportNameGenState - forM questions $ \ (focus, answers0) -> do - answers1 <- forM answers0 $ \ (ruleName, RuleResult{..}) -> do - importNameGenState namegenst0 - ruleResultExpr <- ruleResult - -- ruleResultExpr <- fmap fixRelationProj ruleResult -- TODO: do we need the fixRelationProj? - let fullModelBeforeHook = replaceHole ruleResultExpr focus - let mtyBefore = typeOf (hole focus) - let mtyAfter = typeOf ruleResultExpr - case (mtyBefore, mtyAfter) of - (Right tyBefore, Right tyAfter) -> - unless (typesUnify [tyBefore, tyAfter]) $ - bug $ vcat - [ "Rule application changes type:" <+> pretty ruleName - , "Before:" <+> pretty (hole focus) - , "After :" <+> pretty ruleResultExpr - , "Type before:" <+> pretty (show tyBefore) - , "Type after :" <+> pretty (show tyAfter) - ] - (Left msg, _) -> bug $ vcat - [ "Type error before rule application:" <+> pretty ruleName - , "Before:" <+> pretty (hole focus) - , "After :" <+> pretty ruleResultExpr - , "Error :" <+> pretty msg - ] - (_, Left msg) -> bug $ vcat - [ "Type error after rule application:" <+> pretty ruleName - , "Before:" <+> pretty (hole focus) - , "After :" <+> pretty ruleResultExpr - , "Error :" <+> pretty msg - ] - - fullModelAfterHook <- case ruleResultHook of - Nothing -> do - namegenst <- exportNameGenState - return (TryThisFirst fullModelBeforeHook minfo { miNameGenState = namegenst }) - Just hook -> do - namegenst1 <- exportNameGenState - let m1 = fromModelZipper fullModelBeforeHook minfo { miNameGenState = namegenst1 } - m2 <- hook m1 - namegenst2 <- exportNameGenState - let m3 = m2 { mInfo = (mInfo m2) { miNameGenState = namegenst2 } } - return (StartOver m3) - - return - ( Answer - { aText = ruleName <> ":" <+> ruleResultDescr - , aRuleName = ruleName - , aBefore = hole focus - , aAnswer = ruleResultExpr - , aFullModel = fullModelAfterHook - } - , ruleResultType - ) - let qTypes = map snd answers1 - qType' <- if all (head qTypes ==) (tail qTypes) - then return (head qTypes) - else bug "Rules of different rule kinds applicable, this is a bug." - return Question - { qType = qType' - , qHole = hole focus - , qAscendants = tail (ascendants focus) - , qAnswers = map fst answers1 - } - - --- | Computes all applicable questions. --- strategyQ == PickFirst is special-cased for performance. -getQuestions :: - MonadLog m => - MonadFail m => - NameGen m => - EnumerateDomain m => - (?typeCheckerMode :: TypeCheckerMode) => - Config -> - ModelZipper -> - m [(ModelZipper, [(Doc, RuleResult m)])] -getQuestions config modelZipper | strategyQ config == PickFirst = maybeToList <$> - let - loopLevels :: Monad m => [m (Maybe a)] -> m (Maybe a) - loopLevels [] = return Nothing - loopLevels (a:as) = do bs <- a - case bs of - Nothing -> loopLevels as - Just {} -> return bs - - processLevel :: (MonadFail m, MonadLog m, NameGen m, EnumerateDomain m) - => [Rule] - -> m (Maybe (ModelZipper, [(Doc, RuleResult m)])) - processLevel rulesAtLevel = - let - go [] = return Nothing - go (x:xs) = do - ys <- applicableRules config rulesAtLevel x - if null ys - then go xs - else return (Just (x, ys)) - in - go (allContextsExceptReferences modelZipper) - in - loopLevels (map processLevel (allRules config)) -getQuestions config modelZipper = - let - loopLevels :: Monad m => [m [a]] -> m [a] - loopLevels [] = return [] - loopLevels (a:as) = do bs <- a - if null bs - then loopLevels as - else return bs - - processLevel :: (MonadFail m, MonadLog m, NameGen m, EnumerateDomain m) - => [Rule] - -> m [(ModelZipper, [(Doc, RuleResult m)])] - processLevel rulesAtLevel = - fmap catMaybes $ forM (allContextsExceptReferences modelZipper) $ \ x -> do - ys <- applicableRules config rulesAtLevel x - return $ if null ys - then Nothing - else Just (x, ys) - in - loopLevels (map processLevel (allRules config)) - - -strategyToDriver :: Config -> Driver -strategyToDriver config questions = do - let optionsQ = - [ (doc, q) - | (n, q) <- zip allNats questions - , let doc = - vcat $ ("Question" <+> pretty n <> ":" <+> pretty (qHole q)) - : [ nest 4 ("Context #" <> pretty i <> ":" <+> pretty c) -<<<<<<< HEAD - | (i,c) <- zip allNats (qAscendants q), i < 2 -======= - | (i,c) <- zip allNats (qAscendants q) - -- if logLevel < LogDebugVerbose, only show a select few levels - , logLevel config == LogDebugVerbose || i `elem` [1,3,5,10,25] ->>>>>>> master - ] - ] - pickedQs <- executeStrategy (bug "strategyToDriver no Question") optionsQ (strategyQ config) - fmap concat $ forM pickedQs $ \ (pickedQNumber, pickedQDescr, pickedQ) -> do - let optionsA = - [ (doc, a) - | (n, a) <- zip allNats (qAnswers pickedQ) - , let doc = nest 4 $ "Answer" <+> pretty n <> ":" <+> - if "choose-repr" `isPrefixOf` show (aRuleName a) - then pretty (aText a) - else vcat [ pretty (aText a) - , sep [pretty (qHole pickedQ), "~~>", pretty (aAnswer a)] - ] - ] - let strategyA' = case qType pickedQ of - ChooseRepr -> representations - ChooseRepr_Find{} -> representationsFinds - ChooseRepr_Given{} -> representationsGivens - ChooseRepr_Auxiliary -> representationsAuxiliaries - ChooseRepr_Quantified -> representationsQuantifieds - ChooseRepr_Cut{} -> representationsCuts - ExpressionRefinement -> strategyA - pickedAs <- executeAnswerStrategy config pickedQ optionsA (strategyA' config) - return - [ theModel - | (pickedANumber, pickedADescr, pickedA) <- pickedAs - , let upd = addToTrail - config - (strategyQ config) pickedQNumber pickedQDescr - (strategyA' config) pickedANumber (length optionsA) pickedADescr - (aText pickedA) - (aBefore pickedA) - (aAnswer pickedA) - , let theModel = updateModelWIPInfo upd (aFullModel pickedA) - ] - - -recordedResponses :: IORef (Maybe [Int]) -{-# NOINLINE recordedResponses #-} -recordedResponses = unsafePerformIO (newIORef Nothing) - -recordedResponsesRepresentation :: IORef (Maybe [(Name, Int)]) -{-# NOINLINE recordedResponsesRepresentation #-} -recordedResponsesRepresentation = unsafePerformIO (newIORef Nothing) - - -executeStrategy :: (MonadIO m, MonadLog m) => Question -> [(Doc, a)] -> Strategy -> m [(Int, Doc, a)] -executeStrategy _ [] _ = bug "executeStrategy: nothing to choose from" -executeStrategy _ [(doc, option)] (viewAuto -> (_, True)) = do - logDebug ("Picking the only option:" <+> doc) - return [(1, doc, option)] -executeStrategy question options@((doc, option):_) (viewAuto -> (strategy, _)) = - case strategy of - Auto _ -> bug "executeStrategy: Auto" - PickFirst -> do - logDebug ("Picking the first option:" <+> doc) - return [(1, doc, option)] - Sparse -> do - logDebug ("Picking the first option (in sparse order):" <+> doc) - return [(1, doc, option)] - PickAll -> return [ (i,d,o) | (i,(d,o)) <- zip [1..] options ] - Interactive -> liftIO $ do - putStrLn $ render 80 $ vcat (map fst options) - recordedResponsesRepresentation' <- readIORef recordedResponsesRepresentation - let - nextRecordedResponse :: IO (Maybe Int) - nextRecordedResponse = do - mres <- readIORef recordedResponses - case mres of - Just (next:rest) -> do - writeIORef recordedResponses (Just rest) - return (Just next) - _ -> return Nothing - - nextRecordedResponseRepresentation :: Name -> Maybe Int - nextRecordedResponseRepresentation nm = - case recordedResponsesRepresentation' of - Nothing -> Nothing - Just mres -> lookup nm mres - - pickIndex :: IO Int - pickIndex = do - let useStoredReprResponse = - case qType question of - ChooseRepr_Find nm -> Just nm - ChooseRepr_Given nm -> Just nm - ChooseRepr_Cut nm -> Just nm - _ -> Nothing - let storedReprResponse = - case useStoredReprResponse of - Just nm -> nextRecordedResponseRepresentation nm - Nothing -> Nothing - case storedReprResponse of - Just recorded -> do - putStrLn ("Response: " ++ show recorded) - unless (recorded >= 1 && recorded <= length options) $ - userErr1 $ vcat [ "Recorded response out of range." - , nest 4 $ "Expected a value between 1 and" <+> pretty (length options) - , nest 4 $ "But got: " <+> pretty recorded - ] - return recorded - Nothing -> do - mrecorded <- nextRecordedResponse - case mrecorded of - Just recorded -> do - putStrLn ("Response: " ++ show recorded) - unless (recorded >= 1 && recorded <= length options) $ - userErr1 $ vcat [ "Recorded response out of range." - , nest 4 $ "Expected a value between 1 and" <+> pretty (length options) - , nest 4 $ "But got: " <+> pretty recorded - ] - return recorded - Nothing -> do - putStr "Pick option: " - hFlush stdout - line <- getLine - case (line, readMay line) of - ("", _) -> return 1 - (_, Just lineInt) | lineInt >= 1 && lineInt <= length options -> return lineInt - (_, Nothing) -> do - putStrLn "Enter an integer value." - pickIndex - (_, Just _) -> do - print $ pretty $ "Enter a value between 1 and" <+> pretty (length options) - pickIndex - - pickedIndex <- pickIndex - let (pickedDescr, picked) = at options (pickedIndex - 1) - return [(pickedIndex, pickedDescr, picked)] - AtRandom -> do - let nbOptions = length options - pickedIndex <- liftIO $ randomRIO (1, nbOptions) - let (pickedDescr, picked) = at options (pickedIndex - 1) - logDebug ("Randomly picking option #" <> pretty pickedIndex <+> "out of" <+> pretty nbOptions) - return [(pickedIndex, pickedDescr, picked)] - Compact -> bug "executeStrategy: Compact" - - -executeAnswerStrategy :: (MonadIO m, MonadLog m) - => Config -> Question -> [(Doc, Answer)] -> Strategy -> m [(Int, Doc, Answer)] -executeAnswerStrategy _ _ [] _ = bug "executeStrategy: nothing to choose from" -executeAnswerStrategy _ _ [(doc, option)] (viewAuto -> (_, True)) = do - logDebug ("Picking the only option:" <+> doc) - return [(1, doc, option)] -executeAnswerStrategy _ question options st@(viewAuto -> (strategy, _)) = - case strategy of - Compact -> do - let (n,(doc,c)) = minimumBy (compactCompareAnswer `on` (snd . snd)) (zip [1..] options) - return [(n, doc, c)] - _ -> executeStrategy question options st - - -compactCompareAnswer :: Answer -> Answer -> Ordering -compactCompareAnswer = comparing (expressionDepth . aAnswer) - where - expressionDepth :: Data a => a -> Int - expressionDepth x = 1 + maximum (0 : map expressionDepth (children x)) - - -addToTrail - :: Config - -> Strategy -> Int -> Doc - -> Strategy -> Int -> Int -> Doc - -> Doc -> Expression -> Expression - -> ModelInfo -> ModelInfo -addToTrail Config{..} - questionStrategy questionNumber questionDescr - answerStrategy answerNumber answerNumbers answerDescr - ruleDescr oldExpr newExpr - oldInfo = newInfo - where - newInfo = oldInfo { miTrailCompact = (questionNumber, answerNumber, answerNumbers) - : miTrailCompact oldInfo - , miTrailVerbose = if verboseTrail - then theA : theQ : miTrailVerbose oldInfo - else [] - , miTrailRewrites = if rewritesTrail - then theRewrite : miTrailRewrites oldInfo - else [] - } - theQ = Decision - { dDescription = map (stringToText . renderWide) - $ ("Question #" <> pretty questionNumber) - : (" (Using strategy:" <+> pretty (show questionStrategy) <> ")") - : map pretty (lines (renderWide questionDescr)) - , dDecision = questionNumber - , dNumOptions = Nothing - } - theA = Decision - { dDescription = map (stringToText . renderWide) - $ ("Answer #" <> pretty answerNumber <+> "out of" <+> pretty (show answerNumbers)) - : (" (Using strategy:" <+> pretty (show answerStrategy) <> ")") - : map pretty (lines (renderWide answerDescr)) - , dDecision = answerNumber - , dNumOptions = Just answerNumbers - } - theRewrite = TrailRewrites - { trRule = stringToText $ renderWide ruleDescr - , trBefore = map stringToText $ lines $ renderWide $ pretty oldExpr - , trAfter = map stringToText $ lines $ renderWide $ pretty newExpr - } - - --- | Add a true-constraint, for every decision variable (whether it is used or not in the model) and --- for every parameter (that is not used in the model). --- A true-constraint has no effect, other than forcing Conjure to produce a representation. --- It can be used to make sure that a declaration doesn't get lost (if it isn't used anywhere in the model) --- It can also be used to produce "extra" representations (if it is used in the model) -addTrueConstraints :: Model -> Model -addTrueConstraints m = - let - mkTrueConstraint forg nm dom = Op $ MkOpTrue $ OpTrue (Reference nm (Just (DeclNoRepr forg nm dom NoRegion))) - trueConstraints = [ mkTrueConstraint forg nm d - | (Declaration (FindOrGiven forg nm d), after) <- withAfter (mStatements m) - , forg == Find || (forg == Given && nbUses nm after == 0) - ] - in - m { mStatements = mStatements m ++ [SuchThat trueConstraints] } - - -reverseTrails :: Model -> Model -reverseTrails m = - let - oldInfo = mInfo m - newInfo = oldInfo { miTrailCompact = reverse (miTrailCompact oldInfo) - , miTrailVerbose = reverse (miTrailVerbose oldInfo) - , miTrailRewrites = reverse (miTrailRewrites oldInfo) - } - in - m { mInfo = newInfo } - - -oneSuchThat :: Model -> Model -oneSuchThat m = m { mStatements = onStatements (mStatements m) - |> nubBy ((==) `on` normaliseQuantifiedVariablesS) } - - where - - onStatements :: [Statement] -> [Statement] - onStatements xs = - let - (suchThats0, objectives, others) = xs |> map collect |> mconcat - suchThats = suchThats0 - |> map breakConjunctions -- break top level /\'s - |> mconcat - |> filter (/= Constant (ConstantBool True)) -- remove top level true's - |> nubBy ((==) `on` normaliseQuantifiedVariablesE) -- uniq - in - others ++ objectives ++ [SuchThat (combine suchThats)] - - collect :: Statement -> ( [Expression] -- SuchThats - , [Statement] -- Objectives - , [Statement] -- other statements - ) - collect (SuchThat s) = (s, [], []) - collect s@Objective{} = ([], [s], []) - collect s = ([], [], [s]) - - combine :: [Expression] -> [Expression] - combine xs = if null xs - then [Constant (ConstantBool True)] - else xs - - breakConjunctions :: Expression -> [Expression] - breakConjunctions p@(Op (MkOpAnd (OpAnd x))) = - case listOut x of - Nothing -> [p] -- doesn't contain a list - Just xs -> concatMap breakConjunctions xs - breakConjunctions x = [x] - - -emptyMatrixLiterals :: Model -> Model -emptyMatrixLiterals model = - let - f (TypeList ty) = TypeMatrix (TypeInt TagInt) ty - f x = x - in - model { mStatements = mStatements model |> transformBi f } - - --- | Add a default search order (branching on [...]) --- to include all the primary variables and none of the aux variables that will potentailly be generated by Conjure. --- Do not change the model if it already contains a SearchOrder in it. -addSearchOrder :: Model -> Model -addSearchOrder model - | let hasSearchOrder = not $ null [ () | SearchOrder{} <- mStatements model ] - , hasSearchOrder = model - | otherwise = - let finds = [ nm | Declaration (FindOrGiven Find nm _domain) <- mStatements model ] - in model { mStatements = mStatements model ++ [SearchOrder (map BranchingOn finds)] } - - -inlineDecVarLettings :: Model -> Model -inlineDecVarLettings model = - let - inline p@(Reference nm _) = do - x <- gets (lookup nm) - return (fromMaybe p x) - inline p = return p - - statements = catMaybes - $ flip evalState [] - $ forM (mStatements model) - $ \ st -> - case st of - Declaration (Letting nm x) - | categoryOf x == CatDecision - -> modify ((nm,x) :) >> return Nothing - -- The following doesn't work when the identifier is used in a domain - -- Declaration (Letting nm x@Reference{}) - -- -> modify ((nm,x) :) >> return Nothing - _ -> Just <$> transformBiM inline st - in - model { mStatements = statements } - -flattenLex :: MonadFail m - => NameGen m - => (?typeCheckerMode :: TypeCheckerMode) - => Model -> m Model -flattenLex m = do - let - flatten a = do - ta <- typeOf a - case ta of - TypeBool -> return [essence| [-toInt(&a)] |] - TypeInt{} -> return [essence| [&a] |] - TypeList TypeInt{} -> return a - TypeMatrix TypeInt{} TypeInt{} -> return a - _ -> - case a of - AbstractLiteral x -> do - case x of - AbsLitTuple xs -> do - fxs <- sequence (flatten <$> xs) - let flatxs = fromList fxs - return [essence| flatten(&flatxs) |] - AbsLitMatrix _ xs -> do - fxs <- sequence (flatten <$> xs) - let flatxs = fromList fxs - return [essence| flatten(&flatxs) |] - _ -> bug $ "epilogue: flattenLex: isn't defined for this abslit fellow..." - <+> vcat [pretty a, pretty ta, stringToDoc $ show a] - Constant c -> - case c of - ConstantAbstract ca -> - case ca of - AbsLitTuple xs -> do - fxs <- sequence (flatten <$> (Constant <$> xs)) - let flatxs = fromList fxs - return [essence| flatten(&flatxs) |] - AbsLitMatrix _ xs -> do - fxs <- sequence (flatten <$> (Constant <$> xs)) - let flatxs = fromList fxs - return [essence| flatten(&flatxs) |] - _ -> bug $ "epilogue: flattenLex: isn't defined for this fellow..." - <+> vcat [pretty a, pretty ta, stringToDoc $ show a] - TypedConstant tc _ -> flatten (Constant tc) - _ -> bug $ "epilogue: flattenLex: isn't defined for this constant fellow." - <+> vcat [pretty a, pretty ta, stringToDoc $ show a] --- Op op -> do --- case op of --- MkOpIndexing (OpIndexing m i) -> --- bug $ "epilogue: flattenLex: flatten not defined for this indexed fellow." --- <+> vcat [stringToDoc (show a) --- ,"fellow:" <+> stringToDoc (show m) --- ,"index:" <+> stringToDoc (show i)] - Reference nm ex -> - bug $ "epilogue: flattenLex: flatten not defined for this referenced fellow." - <+> vcat [stringToDoc (show a) - ,"reference:" <+> stringToDoc (show nm) - ,"fellow:" <+> stringToDoc (show ex)] - Comprehension body gocs -> do - fbody <- flatten body - let comp = Comprehension fbody gocs --- return [essence| flatten(&comp) |] - return [essence| &comp |] - _ -> bug $ "epilogue: flattenLex: isn't defined for this expression fellow..." - <+> vcat [pretty a, pretty ta, stringToDoc $ show a] - - - flattener [essence| &a - (?typeCheckerMode :: TypeCheckerMode) => - Model -> m Model -dropTagForSR m = do - let - replacePredSucc [essence| pred(&x) |] = do - ty <- typeOf x - case ty of - TypeBool{} -> return [essence| false |] - -- since True becomes False - -- False becomes out-of-bounds, hence False - TypeInt{} -> do - let xTagInt = reTag TagInt x - return [essence| &xTagInt - 1 |] - _ -> bug "predSucc" - replacePredSucc [essence| succ(&x) |] = do - ty <- typeOf x - case ty of - TypeBool{} -> return [essence| !&x |] - -- since False becomes True - -- True becomes out-of-bounds, hence False - -- "succ" is exactly "negate" on bools - TypeInt{} -> do - let xTagInt = reTag TagInt x - return [essence| &xTagInt + 1 |] - _ -> bug "predSucc" - -- replacePredSucc [essence| &a .< &b |] = return [essence| &a < &b |] - -- replacePredSucc [essence| &a .<= &b |] = return [essence| &a <= &b |] - replacePredSucc x = return x - - st <- transformBiM replacePredSucc (mStatements m) - return m { mStatements = transformBi (\ _ -> TagInt) st } - - -updateDeclarations :: - MonadUserError m => - MonadFail m => - NameGen m => - EnumerateDomain m => - (?typeCheckerMode :: TypeCheckerMode) => - Model -> m Model -updateDeclarations model = do - let - representations = model |> mInfo |> miRepresentations - - onEachStatement (inStatement, afters) = - case inStatement of - Declaration (FindOrGiven forg nm _) -> do - let - -- the refined domains for the high level declaration - domains = [ d | (n, d) <- representations, n == nm ] - nub <$> concatMapM (onEachDomain forg nm) domains - Declaration (GivenDomainDefnEnum name) -> return - [ Declaration (FindOrGiven Given (name `mappend` "_EnumSize") (DomainInt TagInt [])) ] - Declaration (Letting nm x) -> do - let usedAfter = nbUses nm afters > 0 - let isRefined = (0 :: Int) == sum - [ case y of - Constant (ConstantAbstract AbsLitMatrix{}) -> 0 - Constant ConstantAbstract{} -> 1 - AbstractLiteral AbsLitMatrix{} -> 0 - AbstractLiteral{} -> 1 - _ -> 0 - | y <- universe x ] - return [inStatement | and [usedAfter, isRefined]] - Declaration LettingDomainDefnEnum{} -> return [] - Declaration LettingDomainDefnUnnamed{} -> return [] - SearchOrder orders -> do - orders' <- forM orders $ \case - BranchingOn nm -> do - let domains = [ d | (n, d) <- representations, n == nm ] - -- last one is the representation of what's in true(?) - -- put that first! - let reorder xs = - case reverse xs of - [] -> [] - (y:ys) -> y : reverse ys - outNames <- concatMapM (onEachDomainSearch nm) (reorder domains) - return $ map BranchingOn $ nub outNames - Cut{} -> bug "updateDeclarations, Cut shouldn't be here" - return [ SearchOrder (concat orders') ] - _ -> return [inStatement] - - onEachDomain forg nm domain = - runExceptT (downD (nm, domain)) >>= \case - Left err -> bug err - Right outs -> forM outs $ \ (n, d) -> do - d' <- transformBiM (trySimplify []) $ forgetRepr d - return $ Declaration (FindOrGiven forg n d') - - onEachDomainSearch nm domain = - runExceptT (downD (nm, domain)) >>= \case - Left err -> bug err - Right outs -> return [ n - | (n, _) <- outs - ] - - statements <- concatMapM onEachStatement (withAfter (mStatements model)) - return model { mStatements = statements } - - --- | checking whether any `Reference`s with `DeclHasRepr`s are left in the model -checkIfAllRefined :: MonadFail m => Model -> m Model -checkIfAllRefined m | Just modelZipper <- mkModelZipper m = do -- we exclude the mInfo here - let returnMsg x = return - $ "" - : ("Not refined:" <+> pretty (hole x)) - <+> stringToDoc(show (hole x)) - : [ nest 4 ("Context #" <> pretty i <> ":" <+> pretty c) - | (i, c) <- zip allNats (tail (ascendants x)) - ] - - fails <- fmap (nub . concat) $ forM (allContextsExceptReferences modelZipper) $ \ x -> - case hole x of - Reference _ (Just (DeclHasRepr _ _ dom)) - | not (isPrimitiveDomain dom) -> - return $ "" - : ("Not refined:" <+> pretty (hole x)) - <+> stringToDoc(show (hole x)) - : ("Domain :" <+> pretty dom) - : [ nest 4 ("Context #" <> pretty i <> ":" <+> pretty c) - | (i, c) <- zip allNats (tail (ascendants x)) - ] - Constant (ConstantAbstract AbsLitMatrix{}) -> return [] - Constant ConstantAbstract{} -> returnMsg x - AbstractLiteral AbsLitMatrix{} -> return [] - AbstractLiteral{} -> returnMsg x - WithLocals{} -> returnMsg x - Comprehension _ stmts -> do - decisionConditions <- - fmap catMaybes $ forM stmts $ \ stmt -> case stmt of - Condition c -> - if categoryOf c >= CatDecision - then return (Just c) - else return Nothing - _ -> return Nothing - comprehensionLettings <- - fmap catMaybes $ forM stmts $ \ stmt -> case stmt of - ComprehensionLetting{} -> return (Just stmt) - _ -> return Nothing - unsupportedGenerator <- - fmap catMaybes $ forM stmts $ \ stmt -> case stmt of - Generator GenInExpr{} -> return (Just stmt) - _ -> return Nothing - let msgs = [ "decision expressions as conditions" - | not (null decisionConditions) ] - ++ [ "local lettings" - | not (null comprehensionLettings) ] - ++ [ "unsupported generators" - | not (null unsupportedGenerator) ] - let msg = "Comprehension contains" <+> prettyListDoc id "," msgs <> "." - case msgs of - [] -> return [] - _ -> return $ [ msg ] - ++ [ nest 4 (pretty (hole x)) ] - ++ [ nest 4 ("Context #" <> pretty i <> ":" <+> pretty c) - | (i, c) <- zip allNats (tail (ascendants x)) - ] - [essence| &_ .< &_ |] -> - return ["", ("Not refined:" <+> pretty (hole x)) - <+> stringToDoc(show (hole x))] - [essence| &_ .<= &_ |] -> - return ["", ("Not refined:" <+> pretty (hole x)) - <+> stringToDoc(show (hole x))] - _ -> return [] - unless (null fails) (bug (vcat fails)) - return m -checkIfAllRefined m = return m - - --- | checking whether any undefined values creeped into the final model -checkIfHasUndefined :: MonadFail m => Model -> m Model -checkIfHasUndefined m | Just modelZipper <- mkModelZipper m = do - let returnMsg x = return - $ "" - : ("Undefined value in the final model:" <+> pretty (hole x)) - : [ nest 4 ("Context #" <> pretty i <> ":" <+> pretty c) - | (i, c) <- zip allNats (tail (ascendants x)) - ] - - fails <- fmap concat $ forM (allContextsExceptReferences modelZipper) $ \ x -> - case hole x of - Constant ConstantUndefined{} -> returnMsg x - _ -> return [] - unless (null fails) (bug (vcat fails)) - return m -checkIfHasUndefined m = return m - - -topLevelBubbles :: - MonadFail m => - MonadUserError m => - NameGen m => - (?typeCheckerMode :: TypeCheckerMode) => - Model -> m Model -topLevelBubbles m = do - let - onStmt (SuchThat xs) = onExprs xs - onStmt (Where xs) = concatMapM onWheres xs - onStmt (Objective obj (WithLocals h locals)) = - case locals of - AuxiliaryVars locs -> ( locs ++ [Objective obj h] ) |> onStmts - DefinednessConstraints locs -> ( [SuchThat locs] ++ [Objective obj h] ) |> onStmts - onStmt (Declaration decl) = - let - f (WithLocals h locs) = tell [locs] >> return h - f x = return x - - (decl', locals) = runWriter (transformBiM f decl) - - conv :: InBubble -> [Statement] - conv (AuxiliaryVars locs) = locs - conv (DefinednessConstraints locs) = [SuchThat locs] - - newStmts :: [Statement] - newStmts = concatMap conv locals - in - if null newStmts - then return [Declaration decl] - else onStmts (newStmts ++ [Declaration decl']) - onStmt s = return [s] - - -- a where that has a bubble at the top-most level will be replaced - -- with a Comprehension. this is to avoid creating a where with decision variables inside. - onWheres (WithLocals h (DefinednessConstraints locals)) = - return $ map (Where . return) (locals ++ [h]) - onWheres (WithLocals h (AuxiliaryVars locals)) = do - let (localfinds, gens) = mconcat - [ case local of - Declaration (FindOrGiven LocalFind nm dom) -> - ([nm], [Generator (GenDomainNoRepr (Single nm) dom)]) - SuchThat xs -> - ([], map Condition xs) - _ -> bug ("topLevelBubbles.onWheres:" <+> pretty local) - | local <- locals - ] - let forgetReprsOfLocalFinds (Reference nm _) | nm `elem` localfinds = Reference nm Nothing - forgetReprsOfLocalFinds x = descend forgetReprsOfLocalFinds x - let out = Comprehension h gens - out' <- resolveNamesX (forgetReprsOfLocalFinds out) - return [Where [out']] - onWheres x = return [Where [x]] - - onExpr (WithLocals h (AuxiliaryVars locals)) = ( locals ++ [SuchThat [h]]) |> onStmts - onExpr (WithLocals h (DefinednessConstraints locals)) = ([SuchThat locals] ++ [SuchThat [h]]) |> onStmts - onExpr x = return [SuchThat [x]] - - onStmts = concatMapM onStmt - onExprs = concatMapM onExpr - - statements' <- onStmts (mStatements m) - return m { mStatements = statements' } - - -sliceThemMatrices :: - Monad m => - (?typeCheckerMode :: TypeCheckerMode) => - Model -> m Model -sliceThemMatrices model = do - let - -- nothing stays with a matrix type - -- we are doing this top down - -- when we reach a matrix-typed expression, we know it needs to be sliced - -- we descend otherwise - -- we also descend into components of the matrix-typed expression during slicing - onExpr :: Monad m => Expression -> m Expression - onExpr p = do - let computeExistingSlices t = - case match opSlicing t of - Nothing -> return 0 - Just (t', _, _) -> (+1) <$> computeExistingSlices t' - let isIndexedMatrix = do - (m, is) <- match opMatrixIndexing p - tyM <- typeOf m - nSlices <- computeExistingSlices m - return (m, nSlices, is, tyM) - case isIndexedMatrix of - Nothing -> descendM onExpr p - Just (m, existingSlices, is, tyM) -> do - let nestingLevel (TypeMatrix _ a) = 1 + nestingLevel a - nestingLevel (TypeList a) = 1 + nestingLevel a - nestingLevel _ = 0 :: Int - -- "is" is the number of existing indices - -- "nestingLevel" is the nesting level of the original matrix - -- "existingSlices" is the number of existing slices - let howMany = nestingLevel tyM - existingSlices - length is - let unroll a 0 = a - unroll a i = make opSlicing (unroll a (i-1)) Nothing Nothing - m' <- descendM onExpr m - is' <- mapM onExpr is - let p' = make opMatrixIndexing m' is' - return $ unroll p' howMany - - statements <- descendBiM onExpr (mStatements model) - return model { mStatements = statements } - - -removeExtraSlices :: Monad m => Model -> m Model -removeExtraSlices model = do - let - -- a slice at the end of a chain of slices & indexings - -- does no good in Essence and should be removed - onExpr :: Monad m => Expression -> m Expression - onExpr (match opSlicing -> Just (m,_,_)) = onExpr m - onExpr p@(match opIndexing -> Just _) = return p - onExpr p = descendM onExpr p - - statements <- descendBiM onExpr (mStatements model) - return model { mStatements = statements } - - -lexSingletons :: (?typeCheckerMode :: TypeCheckerMode) - => Monad m - => Model -> m Model -lexSingletons model = do - let onExpr :: (?typeCheckerMode :: TypeCheckerMode) - => Monad m => Expression -> m Expression - onExpr [essence| &l return [essence| &l return [essence| &ls < &rs |] - _ -> bug $ "lexSingleton: match inconsistent" - onExpr [essence| &l <=lex &r |] = - case (matchSingleton l, matchSingleton r) of - (Nothing, Nothing) -> return [essence| &l <=lex &r |] - (Just ls, Just rs) -> return [essence| &ls <= &rs |] - _ -> bug $ "lexSingleton: match inconsistent" - onExpr x = return x - matchSingleton :: (?typeCheckerMode :: TypeCheckerMode) - => Expression -> Maybe Expression - matchSingleton (match matrixLiteral -> Just (TypeMatrix _ TypeInt{},_,[s])) = - Just s - matchSingleton _ = Nothing - statements <- transformBiM onExpr (mStatements model) - return model { mStatements = statements } - - -logDebugIdModel :: MonadLog m => Doc -> Model -> m Model -logDebugIdModel msg a = logDebug (msg <++> pretty (a {mInfo = def})) >> return a - -prologue :: - MonadFail m => - MonadLog m => - NameGen m => - EnumerateDomain m => - (?typeCheckerMode :: TypeCheckerMode) => - Config -> - Model -> - m Model -prologue config model = do - void $ typeCheckModel_StandAlone model - return model >>= logDebugIdModel "[input]" - >>= enforceTagConsistency >>= logDebugIdModel "[enforceTagConsistency]" - >>= return . addSearchOrder >>= logDebugIdModel "[addSearchOrder]" - >>= attributeAsConstraints >>= logDebugIdModel "[attributeAsConstraints]" - >>= inferAttributes >>= logDebugIdModel "[inferAttributes]" - >>= inlineLettingDomainsForDecls >>= logDebugIdModel "[inlineLettingDomainsForDecls]" - >>= lettingsForComplexInDoms >>= logDebugIdModel "[lettingsForComplexInDoms]" - >>= distinctQuantifiedVars >>= logDebugIdModel "[distinctQuantifiedVars]" - >>= return . initInfo >>= logDebugIdModel "[initInfo]" - >>= addUnnamedSymmetryBreaking (unnamedSymmetryBreaking config) - >>= logDebugIdModel "[addUnnamedSymmetryBreaking]" - >>= removeUnnamedsFromModel >>= logDebugIdModel "[removeUnnamedsFromModel]" - >>= removeEnumsFromModel >>= logDebugIdModel "[removeEnumsFromModel]" - >>= finiteGivens >>= logDebugIdModel "[finiteGivens]" - >>= renameQuantifiedVarsToAvoidShadowing - >>= logDebugIdModel "[renameQuantifiedVarsToAvoidShadowing]" - >>= resolveNames >>= logDebugIdModel "[resolveNames]" - >>= return . initInfo_Lettings >>= logDebugIdModel "[initInfo_Lettings]" - >>= removeDomainLettings >>= logDebugIdModel "[removeDomainLettings]" - >>= (let ?typeCheckerMode = RelaxedIntegerTags in typeCheckModel) - >>= logDebugIdModel "[typeCheckModel]" - >>= categoryChecking >>= logDebugIdModel "[categoryChecking]" - >>= sanityChecks >>= logDebugIdModel "[sanityChecks]" - >>= dealWithCuts >>= logDebugIdModel "[dealWithCuts]" - >>= removeExtraSlices >>= logDebugIdModel "[removeExtraSlices]" - >>= return . addTrueConstraints >>= logDebugIdModel "[addTrueConstraints]" - >>= enforceTagConsistency >>= logDebugIdModel "[enforceTagConsistency]" - - -epilogue :: - MonadFail m => - MonadLog m => - NameGen m => - EnumerateDomain m => - (?typeCheckerMode :: TypeCheckerMode) => - Model -> m Model -epilogue model = return model - >>= logDebugIdModel "[epilogue]" -<<<<<<< HEAD - >>= flattenLex >>= logDebugIdModel "[flattenLex]" - >>= dropTagForSR >>= logDebugIdModel "[dropTagForSR]" -======= - >>= lexSingletons >>= logDebugIdModel "[lexSingletons]" ->>>>>>> master - >>= updateDeclarations >>= logDebugIdModel "[updateDeclarations]" - >>= return . inlineDecVarLettings >>= logDebugIdModel "[inlineDecVarLettings]" - >>= topLevelBubbles >>= logDebugIdModel "[topLevelBubbles]" - >>= checkIfAllRefined >>= logDebugIdModel "[checkIfAllRefined]" - >>= checkIfHasUndefined >>= logDebugIdModel "[checkIfHasUndefined]" - >>= sliceThemMatrices >>= logDebugIdModel "[sliceThemMatrices]" - >>= dropTagForSR >>= logDebugIdModel "[dropTagForSR]" - >>= return . emptyMatrixLiterals >>= logDebugIdModel "[emptyMatrixLiterals]" - >>= return . reverseTrails >>= logDebugIdModel "[reverseTrails]" - >>= return . oneSuchThat >>= logDebugIdModel "[oneSuchThat]" - >>= return . languageEprime >>= logDebugIdModel "[languageEprime]" - - -applicableRules :: forall m n . - MonadUserError n => - MonadLog n => - NameGen n => - EnumerateDomain n => - MonadUserError m => - MonadLog m => - NameGen m => - EnumerateDomain m => - MonadFail m => - (?typeCheckerMode :: TypeCheckerMode) => - Config -> - [Rule] -> - ModelZipper -> - n [(Doc, RuleResult m)] -applicableRules Config{..} rulesAtLevel x = do - let logAttempt = if logRuleAttempts then logInfo else const (return ()) - let logFail = if logRuleFails then logInfo else const (return ()) - let logSuccess = if logRuleSuccesses then logInfo else const (return ()) - - mys <- sequence [ do logAttempt ("attempting rule" <+> rName r <+> "on" <+> pretty (hole x)) - applied <- runExceptT $ runReaderT (rApply r x (hole x)) x - return (rName r, applied) - | r <- rulesAtLevel ] - forM_ mys $ \ (rule, my) -> - case my of - Left failed -> unless ("N/A" `isPrefixOf` show failed) $ logFail $ vcat - [ " rule failed:" <+> rule - , " on:" <+> pretty (hole x) - , " message:" <+> failed - ] - Right ys -> logSuccess $ vcat - [ "rule applied:" <+> rule - , " on:" <+> pretty (hole x) - , " message:" <+> vcat (map ruleResultDescr ys) - ] - return [ (name, res {ruleResult = ruleResult'}) - | (name, Right ress) <- mys - , res <- ress - , let ruleResult' = do - rResult <- ruleResult res - case (hole x, rResult) of - (Reference nm1 _, Reference nm2 _) - | name /= "choose-repr" - , nm1 == nm2 -> bug $ vcat - [ "Rule applied inside a Reference." - , "Rule :" <+> pretty name - , "Rule input :" <+> pretty (hole x) - , "Rule output :" <+> pretty rResult - , "Rule input (show):" <+> pretty (show (hole x)) - , "Rule output (show):" <+> pretty (show rResult) - ] - _ -> return () - merr <- runExceptT (resolveNamesX rResult) - case merr of - Left err -> bug $ vcat - [ "Name resolution failed after rule application." - , "Rule :" <+> pretty name - , "Rule input :" <+> pretty (hole x) - , "Rule output :" <+> pretty rResult - , "Rule input (show):" <+> pretty (show (hole x)) - , "Rule output (show):" <+> pretty (show rResult) - , "The error :" <+> err - ] - Right r -> return r - ] - - -allRules :: (?typeCheckerMode :: TypeCheckerMode) => Config -> [[Rule]] -allRules config = - [ Transform.rules_Transform - , [ rule_FullEvaluate - ] - , [ rule_PartialEvaluate - ] - ] ++ paramRules ++ - [ [ rule_ChooseRepr config - , rule_ChooseReprForComprehension config - , rule_ChooseReprForLocals config - ] - , bubbleUpRules - , [ rule_Eq - , rule_Neq - , rule_Comprehension_Cardinality - , rule_Flatten_Cardinality - ] - , verticalRules - , horizontalRules - ] ++ otherRules - ++ delayedRules - - --- | For information that can be readily pulled out from parameters. --- Some things are easier when everything involved is a param. --- These rules aren't necessary for correctness, but they can help remove some verbose expressions from the output. --- Make Savile Row happier so it makes us happier. :) -paramRules :: [[Rule]] -paramRules = - [ [ Horizontal.Set.rule_Param_MinOfSet - , Horizontal.Set.rule_Param_MaxOfSet - , Horizontal.Set.rule_Param_Card - ] - , [ Horizontal.Function.rule_Param_DefinedRange - , Horizontal.Relation.rule_Param_Card - ] - ] - -verticalRules :: [Rule] -verticalRules = - [ Vertical.Permutation.rule_Image - , Vertical.Permutation.rule_Cardinality - , Vertical.Permutation.rule_Defined - , Vertical.Permutation.rule_Comprehension - - - , Vertical.Tuple.rule_Tuple_Eq - , Vertical.Tuple.rule_Tuple_Neq - , Vertical.Tuple.rule_Tuple_Leq - , Vertical.Tuple.rule_Tuple_Lt - , Vertical.Tuple.rule_Tuple_TildeLeq - , Vertical.Tuple.rule_Tuple_TildeLt - , Vertical.Tuple.rule_Tuple_Index - - - - , Vertical.Record.rule_Record_Eq - , Vertical.Record.rule_Record_Neq - , Vertical.Record.rule_Record_Leq - , Vertical.Record.rule_Record_Lt - , Vertical.Record.rule_Record_Index - - , Vertical.Variant.rule_Variant_Eq - , Vertical.Variant.rule_Variant_Neq - , Vertical.Variant.rule_Variant_Leq - , Vertical.Variant.rule_Variant_Lt - , Vertical.Variant.rule_Variant_Index - , Vertical.Variant.rule_Variant_Active - - , Vertical.Matrix.rule_Comprehension_Literal - , Vertical.Matrix.rule_Comprehension - , Vertical.Matrix.rule_Comprehension_Flatten - , Vertical.Matrix.rule_ModifierAroundIndexedMatrixLiteral - , Vertical.Matrix.rule_Comprehension_LiteralIndexed - , Vertical.Matrix.rule_Comprehension_Nested - , Vertical.Matrix.rule_Comprehension_Hist - , Vertical.Matrix.rule_Comprehension_ToSet_Matrix - , Vertical.Matrix.rule_Comprehension_ToSet_List - , Vertical.Matrix.rule_Comprehension_ToSet_List_DuplicateFree - , Vertical.Matrix.rule_Matrix_Eq - , Vertical.Matrix.rule_Matrix_Neq - , Vertical.Matrix.rule_Matrix_Leq_Primitive - , Vertical.Matrix.rule_Matrix_Leq_Decompose - , Vertical.Matrix.rule_Matrix_Lt_Primitive - , Vertical.Matrix.rule_Matrix_Lt_Decompose - , Vertical.Matrix.rule_IndexingIdentical - , Vertical.Matrix.rule_ExpandSlices - - , Vertical.Set.Explicit.rule_Min - , Vertical.Set.Explicit.rule_Max - , Vertical.Set.Explicit.rule_Card - , Vertical.Set.Explicit.rule_Comprehension - , Vertical.Set.Explicit.rule_PowerSet_Comprehension - , Vertical.Set.ExplicitVarSizeWithDummy.rule_Comprehension - , Vertical.Set.ExplicitVarSizeWithDummy.rule_PowerSet_Comprehension - , Vertical.Set.ExplicitVarSizeWithFlags.rule_Comprehension - , Vertical.Set.ExplicitVarSizeWithFlags.rule_PowerSet_Comprehension - , Vertical.Set.ExplicitVarSizeWithMarker.rule_Card - , Vertical.Set.ExplicitVarSizeWithMarker.rule_Comprehension - , Vertical.Set.ExplicitVarSizeWithMarker.rule_PowerSet_Comprehension - , Vertical.Set.Occurrence.rule_Comprehension - , Vertical.Set.Occurrence.rule_PowerSet_Comprehension - , Vertical.Set.Occurrence.rule_In - - , Vertical.MSet.Occurrence.rule_Comprehension - , Vertical.MSet.Occurrence.rule_Freq - - , Vertical.MSet.ExplicitWithFlags.rule_Comprehension - , Vertical.MSet.ExplicitWithFlags.rule_Freq - - , Vertical.MSet.ExplicitWithRepetition.rule_Comprehension - - , Vertical.Function.Function1D.rule_Comprehension - , Vertical.Function.Function1D.rule_Comprehension_Defined - , Vertical.Function.Function1D.rule_Image - - , Vertical.Function.Function1DPartial.rule_Comprehension - , Vertical.Function.Function1DPartial.rule_PowerSet_Comprehension - , Vertical.Function.Function1DPartial.rule_Image_NotABool - , Vertical.Function.Function1DPartial.rule_Image_Bool - , Vertical.Function.Function1DPartial.rule_InDefined - , Vertical.Function.Function1DPartial.rule_DefinedEqDefined - - , Vertical.Function.FunctionND.rule_Comprehension - , Vertical.Function.FunctionND.rule_Comprehension_Defined - , Vertical.Function.FunctionND.rule_Image - - , Vertical.Function.FunctionNDPartial.rule_Comprehension - , Vertical.Function.FunctionNDPartial.rule_Image_NotABool - , Vertical.Function.FunctionNDPartial.rule_Image_Bool - , Vertical.Function.FunctionNDPartial.rule_InDefined - - , Vertical.Function.FunctionAsRelation.rule_Comprehension - , Vertical.Function.FunctionAsRelation.rule_Image_Eq - - , Vertical.Sequence.ExplicitBounded.rule_Comprehension - , Vertical.Sequence.ExplicitBounded.rule_Card - , Vertical.Sequence.ExplicitBounded.rule_Image_Bool - , Vertical.Sequence.ExplicitBounded.rule_Image_NotABool - , Vertical.Sequence.ExplicitBounded.rule_Leq - , Vertical.Sequence.ExplicitBounded.rule_Lt - - , Vertical.Relation.RelationAsMatrix.rule_Comprehension - , Vertical.Relation.RelationAsMatrix.rule_Image - - , Vertical.Relation.RelationAsSet.rule_Comprehension - , Vertical.Relation.RelationAsSet.rule_Card - - , Vertical.Partition.PartitionAsSet.rule_Comprehension - , Vertical.Partition.Occurrence.rule_Comprehension - - ] - -horizontalRules :: [Rule] -horizontalRules = - [ Horizontal.Permutation.rule_Cardinality_Literal - , Horizontal.Permutation.rule_Equality - , Horizontal.Permutation.rule_Comprehension - , Horizontal.Permutation.rule_Compose_Image - , Horizontal.Permutation.rule_Image_Matrix_Indexing - , Horizontal.Permutation.rule_Image_Comprehension --- , Horizontal.Permutation.rule_Image_Matrix_Indexing_Comprehension --- , Horizontal.Permutation.rule_Compose - , Horizontal.Permutation.rule_Image_Partition - , Horizontal.Permutation.rule_Image_Sequence - , Horizontal.Permutation.rule_Image_Sequence_Defined - , Horizontal.Permutation.rule_In - , Horizontal.Permutation.rule_Permutation_Inverse - , Horizontal.Permutation.rule_Image_Comprehendable - , Horizontal.Permutation.rule_Image_Incomprehendable - , Horizontal.Permutation.rule_Image_Literal - - - , Horizontal.Set.rule_Comprehension_Literal - , Horizontal.Set.rule_Eq - , Horizontal.Set.rule_Neq - , Horizontal.Set.rule_Subset - , Horizontal.Set.rule_SubsetEq - , Horizontal.Set.rule_Supset - , Horizontal.Set.rule_SupsetEq - , Horizontal.Set.rule_In - , Horizontal.Set.rule_Card - , Horizontal.Set.rule_CardViaFreq - , Horizontal.Set.rule_Intersect - , Horizontal.Set.rule_Union - , Horizontal.Set.rule_Difference - , Horizontal.Set.rule_PowerSet_Comprehension - , Horizontal.Set.rule_PowerSet_Difference - , Horizontal.Set.rule_MaxMin - - , Horizontal.MSet.rule_Comprehension_Literal - , Horizontal.MSet.rule_Comprehension_ToSet_Literal - , Horizontal.MSet.rule_Eq - , Horizontal.MSet.rule_Neq - , Horizontal.MSet.rule_Subset - , Horizontal.MSet.rule_SubsetEq - , Horizontal.MSet.rule_Supset - , Horizontal.MSet.rule_SupsetEq - , Horizontal.MSet.rule_Freq - , Horizontal.MSet.rule_In - , Horizontal.MSet.rule_Card - , Horizontal.MSet.rule_MaxMin - - , Horizontal.Function.rule_Comprehension_Literal - , Horizontal.Function.rule_Image_Bool - , Horizontal.Function.rule_Image_BoolMatrixIndexed - , Horizontal.Function.rule_Image_BoolTupleIndexed - , Horizontal.Function.rule_Image_Int - , Horizontal.Function.rule_Image_IntMatrixIndexed - , Horizontal.Function.rule_Image_IntTupleIndexed - , Horizontal.Function.rule_Image_Matrix_LexLhs - , Horizontal.Function.rule_Image_Matrix_LexRhs - - , Horizontal.Function.rule_Comprehension_Image - , Horizontal.Function.rule_Comprehension_ImageSet - , Horizontal.Function.rule_Eq - , Horizontal.Function.rule_Neq - , Horizontal.Function.rule_Subset - , Horizontal.Function.rule_SubsetEq - , Horizontal.Function.rule_Supset - , Horizontal.Function.rule_SupsetEq - , Horizontal.Function.rule_Inverse - , Horizontal.Function.rule_Card - , Horizontal.Function.rule_Comprehension_PreImage - , Horizontal.Function.rule_Comprehension_Defined - , Horizontal.Function.rule_Comprehension_Range - , Horizontal.Function.rule_In - , Horizontal.Function.rule_Restrict_Image - , Horizontal.Function.rule_Restrict_Comprehension - , Horizontal.Function.rule_Comprehension_Defined_Size - , Horizontal.Function.rule_Comprehension_Range_Size - , Horizontal.Function.rule_Defined_Intersect - , Horizontal.Function.rule_DefinedOrRange_Union - , Horizontal.Function.rule_DefinedOrRange_Difference - - , Horizontal.Sequence.rule_Comprehension_Literal - , Horizontal.Sequence.rule_Image_Bool - , Horizontal.Sequence.rule_Image_Int - , Horizontal.Sequence.rule_Comprehension_Image - , Horizontal.Sequence.rule_Image_Literal_Bool - , Horizontal.Sequence.rule_Image_Literal_Int - , Horizontal.Sequence.rule_Eq_Literal - , Horizontal.Sequence.rule_Eq - , Horizontal.Sequence.rule_Eq_Comprehension - , Horizontal.Sequence.rule_Neq - , Horizontal.Sequence.rule_Subset - , Horizontal.Sequence.rule_SubsetEq - , Horizontal.Sequence.rule_Supset - , Horizontal.Sequence.rule_SupsetEq - , Horizontal.Sequence.rule_Card - , Horizontal.Sequence.rule_Comprehension_PreImage - , Horizontal.Sequence.rule_Comprehension_Defined - , Horizontal.Sequence.rule_Comprehension_Range - , Horizontal.Sequence.rule_In - , Horizontal.Sequence.rule_Restrict_Image - , Horizontal.Sequence.rule_Restrict_Comprehension - , Horizontal.Sequence.rule_Substring - , Horizontal.Sequence.rule_Subsequence - - , Horizontal.Relation.rule_Comprehension_Literal - , Horizontal.Relation.rule_Comprehension_Projection - , Horizontal.Relation.rule_PowerSet_Comprehension - , Horizontal.Relation.rule_Image - , Horizontal.Relation.rule_In - , Horizontal.Relation.rule_Eq - , Horizontal.Relation.rule_Neq - , Horizontal.Relation.rule_Subset - , Horizontal.Relation.rule_SubsetEq - , Horizontal.Relation.rule_Supset - , Horizontal.Relation.rule_SupsetEq - , Horizontal.Relation.rule_Card - - , Horizontal.Partition.rule_Comprehension_Literal - , Horizontal.Partition.rule_Eq - , Horizontal.Partition.rule_Neq - , Horizontal.Partition.rule_Together - , Horizontal.Partition.rule_Apart - , Horizontal.Partition.rule_Party - , Horizontal.Partition.rule_Participants - , Horizontal.Partition.rule_Card - , Horizontal.Partition.rule_In - - - ] - - -bubbleUpRules :: [Rule] -bubbleUpRules = - [ BubbleUp.rule_MergeNested - , BubbleUp.rule_ToAnd - , BubbleUp.rule_ToMultiply_HeadOfIntComprehension - , BubbleUp.rule_NotBoolYet - , BubbleUp.rule_ConditionInsideGeneratorDomain - , BubbleUp.rule_LiftVars - ] - - -otherRules :: [[Rule]] -otherRules = - [ - [ rule_Xor_To_Sum ] - , - [ TildeOrdering.rule_BoolInt - , TildeOrdering.rule_MSet - , TildeOrdering.rule_ViaMSet - , TildeOrdering.rule_TildeLeq - ] - , - [ DontCare.rule_Bool - , DontCare.rule_Int - , DontCare.rule_Tuple - , DontCare.rule_Record - , DontCare.rule_Variant - , DontCare.rule_Permutation - , DontCare.rule_Matrix - , DontCare.rule_Abstract - ] - , - [ rule_TrueIsNoOp - , rule_FlattenOf1D - , rule_Decompose_AllDiff - - , rule_GeneratorsFirst - ] - , - [ rule_DomainCardinality - , rule_DomainMinMax - - , rule_ComplexAbsPat - - , rule_AttributeToConstraint - - , rule_QuantifierShift - , rule_QuantifierShift2 - , rule_QuantifierShift3 - - ] - - , [ rule_Comprehension_Simplify - ] - - , [ rule_InlineConditions - , rule_InlineConditions_AllDiff - , rule_InlineConditions_MaxMin - ] - ] - --- | These rules depend on other rules firing first. -delayedRules :: [[Rule]] -delayedRules = - [ - [ Vertical.Matrix.rule_Comprehension_Singleton - , Vertical.Matrix.rule_Comprehension_SingletonDomain - , Vertical.Matrix.rule_Concatenate_Singleton - , Vertical.Matrix.rule_MatrixIndexing - - ] - , [ rule_ReducerToComprehension - ] - , [ rule_DotLtLeq - , rule_Flatten_Lex - ] - ] - - -rule_ChooseRepr :: (?typeCheckerMode :: TypeCheckerMode) => Config -> Rule -rule_ChooseRepr config = Rule "choose-repr" (const theRule) where - - theRule (Reference nm (Just (DeclNoRepr forg _ inpDom region))) | forg `elem` [Find, Given, CutFind] = do - let reprsWhichOrder - | (forg, representationsGivens config) == (Given, Sparse) = reprsSparseOrder - | representationLevels config == False = reprsStandardOrderNoLevels - | otherwise = reprsStandardOrder - domOpts <- reprOptions reprsWhichOrder inpDom - when (null domOpts) $ - bug $ "No representation matches this beast:" <++> pretty inpDom - let options = - [ RuleResult { ruleResultDescr = msg - , ruleResultType = case forg of - Find -> ChooseRepr_Find nm - Given -> ChooseRepr_Given nm - CutFind -> ChooseRepr_Cut nm - _ -> bug "rule_ChooseRepr ruleResultType" - , ruleResult = return out - , ruleResultHook = Just hook - } - | thisDom <- domOpts - , let msg = "Choosing representation for" <+> pretty nm <> ":" <++> pretty thisDom - , let out = Reference nm (Just (DeclHasRepr forg nm thisDom)) - , let hook = mkHook (channelling config) forg nm thisDom region - ] - return options - theRule _ = na "rule_ChooseRepr" - - mkHook - :: ( MonadLog m - , MonadFail m - , NameGen m - , EnumerateDomain m - ) - => Bool - -> FindOrGiven - -> Name - -> Domain HasRepresentation Expression - -> Region - -> Model - -> m Model - mkHook useChannelling -- whether to use channelling or not - forg -- find or given - name -- name of the original declaration - domain -- domain with representation selected - region -- the region of the Reference we are working on - model = do - let - - representations = model |> mInfo |> miRepresentations - representationsTree = model |> mInfo |> miRepresentationsTree - |> concatMap (\ (n, ds) -> map (n,) ds ) - - usedBefore = (name, reprTree domain) `elem` representationsTree - - mkStructurals :: (MonadLog m, MonadFail m, NameGen m, EnumerateDomain m) - => m [Expression] - mkStructurals = do - let ref = Reference name (Just (DeclHasRepr forg name domain)) - logDebugVerbose $ "Generating structural constraints for:" <+> vcat [pretty ref, pretty domain] - structurals <- getStructurals downX1 domain >>= \ gen -> gen ref - logDebugVerbose $ "Before name resolution:" <+> vcat (map pretty structurals) - resolved <- mapM resolveNamesX structurals -- re-resolving names - logDebugVerbose $ "After name resolution:" <+> vcat (map pretty resolved) - return resolved - - addStructurals :: (MonadLog m, MonadFail m, NameGen m, EnumerateDomain m) - => Model -> m Model - addStructurals - | forg == Given = return - | usedBefore = return - | otherwise = \ m -> do - structurals <- mkStructurals - return $ if null structurals - then m - else m { mStatements = mStatements m ++ [SuchThat structurals] } - - channels = - [ make opEq this that - | (n, d) <- representations - , n == name - , let this = Reference name (Just (DeclHasRepr forg name domain)) - , let that = Reference name (Just (DeclHasRepr forg name d)) - ] - - addChannels - | forg == Given = return - | usedBefore = return - | null channels = return - | otherwise = \ m -> return - m { mStatements = mStatements m ++ [SuchThat channels] } - - recordThis - | usedBefore = return - | otherwise = \ m -> - let - oldInfo = mInfo m - newInfo = oldInfo - { miRepresentations = representations ++ [(name, domain)] - , miRepresentationsTree = (representationsTree ++ [(name, reprTree domain)]) - |> sortBy (comparing fst) - |> groupBy ((==) `on` fst) - |> map (\ grp -> (fst (head grp), map snd grp) ) - } - in return m { mInfo = newInfo } - - fixReprForAllOthers - | useChannelling = return -- no-op, if channelling=yes - | otherwise = \ m -> - let - f (Reference nm _) - | nm == name - = Reference nm (Just (DeclHasRepr forg name domain)) - f x = x - in - return m { mStatements = transformBi f (mStatements m) } - - fixReprForSameRegion - | region == NoRegion = return -- no-op, if we aren't in a particular region - | otherwise = \ m -> - let - f (Reference nm (Just (DeclNoRepr _ _ _ region'))) - | nm == name - , region' == region - = Reference nm (Just (DeclHasRepr forg name domain)) - f x = x - in - return m { mStatements = transformBi f (mStatements m) } - - - logDebugVerbose $ vcat - [ "Name :" <+> pretty name - , "Previously :" <+> vcat [ pretty (show d) | (n,d) <- representations, n == name ] - , "This guy :" <+> pretty (show domain) - , "usedBefore? :" <+> pretty usedBefore - ] - - return model - >>= addStructurals -- unless usedBefore: add structurals - >>= addChannels -- for each in previously recorded representation - >>= recordThis -- unless usedBefore: record (name, domain) as being used in the model - >>= fixReprForAllOthers -- fix the representation of this guy in the whole model, if channelling=no - >>= fixReprForSameRegion -- fix the representation of this guy in the whole model, - -- for those references with the same "region" - >>= resolveNames -- we need to re-resolve names to avoid repeatedly selecting representations - -- for abstract stuff inside aliases. - - -rule_ChooseReprForComprehension :: Config -> Rule -rule_ChooseReprForComprehension config = Rule "choose-repr-for-comprehension" (const theRule) where - - theRule (Comprehension body gensOrConds) = do - (gocBefore, (nm, domain), gocAfter) <- matchFirst gensOrConds $ \ goc -> case goc of - Generator (GenDomainNoRepr (Single nm) domain) -> return (nm, domain) - _ -> na "rule_ChooseReprForComprehension" - - let reprsWhichOrder - | representationsGivens config == Sparse = reprsSparseOrder - | representationLevels config == False = reprsStandardOrderNoLevels - | otherwise = reprsStandardOrder - domOpts <- reprOptions reprsWhichOrder domain - when (null domOpts) $ - bug $ "No representation matches this beast:" <++> pretty domain - - return - [ RuleResult - { ruleResultDescr = "Choosing representation for quantified variable" <+> - pretty nm <> ":" <++> pretty thisDom - , ruleResultType = ChooseRepr_Quantified - , ruleResult = bugFailT "rule_ChooseReprForComprehension" $ do - outDomains <- downD (nm, thisDom) - structurals <- mkStructurals nm thisDom - let updateRepr (Reference nm' _) - | nm == nm' - = Reference nm (Just (DeclHasRepr Quantified nm thisDom)) - updateRepr p = p - let out' = Comprehension (transform updateRepr body) - $ gocBefore - ++ [ Generator (GenDomainHasRepr name dom) - | (name, dom) <- outDomains ] - ++ map Condition structurals - ++ transformBi updateRepr gocAfter - out <- resolveNamesX out' - return out - , ruleResultHook = Nothing - } - | thisDom <- domOpts - ] - theRule _ = na "rule_ChooseReprForComprehension" - - mkStructurals name domain = do - let ref = Reference name (Just (DeclHasRepr Quantified name domain)) - gen <- getStructurals downX1 domain - gen ref - - -rule_ChooseReprForLocals :: Config -> Rule -rule_ChooseReprForLocals config = Rule "choose-repr-for-locals" (const theRule) where - - theRule (WithLocals body (AuxiliaryVars locals)) = do - (stmtBefore, (nm, domain), stmtAfter) <- matchFirst locals $ \ local -> case local of - Declaration (FindOrGiven LocalFind nm domain) -> return (nm, domain) - _ -> na "rule_ChooseReprForLocals" - - let - isReferencedWithoutRepr (Reference nm' (Just DeclNoRepr{})) | nm == nm' = True - isReferencedWithoutRepr _ = False - - unless (any isReferencedWithoutRepr (universeBi (body, stmtBefore, stmtAfter))) $ - na $ "This local variable seems to be handled before:" <+> pretty nm - - let reprsWhichOrder - | representationsAuxiliaries config == Sparse = reprsSparseOrder - | representationLevels config == False = reprsStandardOrderNoLevels - | otherwise = reprsStandardOrder - domOpts <- reprOptions reprsWhichOrder domain - when (null domOpts) $ - bug $ "No representation matches this beast:" <++> pretty domain - - return - [ RuleResult - { ruleResultDescr = "Choosing representation for auxiliary variable" <+> - pretty nm <> ":" <++> pretty thisDom - , ruleResultType = ChooseRepr_Auxiliary - , ruleResult = bugFailT "rule_ChooseReprForLocals" $ do - outDomains <- downD (nm, thisDom) - structurals <- mkStructurals nm thisDom - let updateRepr (Reference nm' _) - | nm == nm' - = Reference nm (Just (DeclHasRepr LocalFind nm thisDom)) - updateRepr p = p - let out' = WithLocals (transform updateRepr body) $ AuxiliaryVars - ( stmtBefore - ++ [ Declaration (FindOrGiven - LocalFind - name - (forgetRepr dom)) - | (name, dom) <- outDomains ] - ++ [ SuchThat structurals | not (null structurals) ] - ++ transformBi updateRepr stmtAfter - ) - out <- resolveNamesX out' - return out - , ruleResultHook = Nothing - } - | thisDom <- domOpts - ] - theRule _ = na "rule_ChooseReprForLocals" - - mkStructurals name domain = do - let ref = Reference name (Just (DeclHasRepr LocalFind name domain)) - gen <- getStructurals downX1 domain - gen ref - - -rule_GeneratorsFirst :: Rule -rule_GeneratorsFirst = "generators-first" `namedRule` theRule where - theRule (Comprehension body []) - = return - ( "Empty generators." - , return $ AbstractLiteral $ AbsLitMatrix (mkDomainIntB 1 1) [body] - ) - theRule (Comprehension body gensOrConds) - | let (gens, rest) = mconcat - [ case x of - Generator{} -> ([x],[]) - _ -> ([],[x]) - | x <- gensOrConds - ] - , let gensOrConds' = gens ++ rest - , gensOrConds /= gensOrConds' - = return - ( "Generators come first." - , return $ Comprehension body gensOrConds' - ) - theRule (Comprehension body gensOrConds) - | let (lettings :: [Name], rest :: [GeneratorOrCondition]) = mconcat - [ case x of - ComprehensionLetting pat _ -> (universeBi pat,[] ) - _ -> ([] ,[x]) - | x <- gensOrConds - ] - , let f (Reference nm (Just (Alias x))) | nm `elem` lettings = f x - f x = x - , not (null lettings) - = return - ( "Inlining comprehension lettings." - , return $ transformBi f $ Comprehension body rest - ) - theRule _ = na "rule_GeneratorsFirst" - - -rule_Eq :: Rule -rule_Eq = "identical-domain-eq" `namedRule` theRule where - theRule p = do - (x,y) <- match opEq p - domX <- domainOf x - domY <- domainOf y - unless (domX == domY) $ na "rule_Eq domains not identical" - sameRepresentationTree x y - xs <- downX x - ys <- downX y - unless (length xs == length ys) $ na "rule_Eq" - when (xs == [x]) $ na "rule_Eq" - when (ys == [y]) $ na "rule_Eq" - return - ( "Generic vertical rule for identical-domain equality" - , return $ make opAnd $ fromList $ zipWith (\ i j -> [essence| &i = &j |] ) xs ys - ) - - -rule_Neq :: Rule -rule_Neq = "identical-domain-neq" `namedRule` theRule where - theRule p = do - (x,y) <- match opNeq p - domX <- domainOf x - domY <- domainOf y - unless (domX == domY) $ na "rule_Neq domains not identical" - sameRepresentationTree x y - xs <- downX x - ys <- downX y - unless (length xs == length ys) $ na "rule_Neq" - when (xs == [x]) $ na "rule_Neq" - when (ys == [y]) $ na "rule_Neq" - return - ( "Generic vertical rule for identical-domain equality" - , return $ make opOr $ fromList $ zipWith (\ i j -> [essence| &i != &j |] ) xs ys - ) - - -rule_DotLtLeq :: Rule -rule_DotLtLeq = "generic-DotLtLeq" `namedRule` theRule where - theRule p = do - (a,b,mk) <- case p of - [essence| &a .< &b |] -> return ( a, b, \ i j -> [essence| &i return ( a, b, \ i j -> [essence| &i <=lex &j |] ) - _ -> na "rule_DotLtLeq" -<<<<<<< HEAD - -- aType <- typeOf a - -- case aType of - -- TypeTuple{} -> return () - -- TypeMatrix{} -> return () - -- TypeSet{} -> return () - -- TypeMSet{} -> return () - -- TypeFunction{} -> return () - -- TypeSequence{} -> return () - -- TypeRelation{} -> return () - -- TypePartition{} -> return () - -- _ -> na "rule_DotLtLeq" - -- sameRepresentationTree a b - ma <- symmetryOrdering a -======= - ma <- symmetryOrdering a ->>>>>>> master - mb <- symmetryOrdering b - return - ( "Generic vertical rule for dotLt and dotLeq:" <+> pretty p - , return $ mk ma mb - ) - - -rule_Flatten_Lex :: Rule -rule_Flatten_Lex = "flatten-lex" `namedRule` theRule where - theRule [essence| &a - na "rule_Flatten_Lex" - (TypeMatrix TypeInt{} TypeInt{}, TypeMatrix TypeInt{} TypeInt{}) -> - na "rule_Flatten_Lex" - _ -> return () - fa <- flatten a - fb <- flatten b - tfa <- typeOf fa - tfb <- typeOf fb - case (tfa, tfb) of - (TypeList TypeInt{}, TypeList TypeInt{}) -> return () - (TypeMatrix TypeInt{} TypeInt{}, TypeMatrix TypeInt{} TypeInt{}) -> return () - _ -> bug $ "flattener: " <+> vcat [stringToDoc $ show tfa, stringToDoc $ show tfb] - return ( "Flatten Lex less" - , return [essence| &fa - na "rule_Flatten_Lex" - (TypeMatrix TypeInt{} TypeInt{}, TypeMatrix TypeInt{} TypeInt{}) -> - na "rule_Flatten_Lex" - _ -> return () - fa <- flatten a - fb <- flatten b - tfa <- typeOf fa - tfb <- typeOf fb - case (tfa, tfb) of - (TypeList TypeInt{}, TypeList TypeInt{}) -> return () - (TypeMatrix TypeInt{} TypeInt{}, TypeMatrix TypeInt{} TypeInt{}) -> return () - _ -> bug $ "flattener: " <+> vcat [stringToDoc $ show tfa, stringToDoc $ show tfb] - return ( "Flatten Lex Lt" - , return [essence| &fa <=lex &fb |] - ) - theRule _ = na "rule_Flatten_Lex" - flatten a = do - ta <- typeOf a - case ta of - TypeBool -> return [essence| [-toInt(&a)] |] - TypeInt{} -> return [essence| [&a] |] - TypeList TypeInt{} -> return a - TypeMatrix TypeInt{} TypeInt{} -> return a - TypeTuple ts -> do - case a of - AbstractLiteral x -> do - case x of - AbsLitTuple xs -> do - fxs <- sequence (flatten <$> xs) - let flatxs = fromList fxs - return [essence| flatten(&flatxs) |] - _ -> bug $ "rule_FlattenLex: flatten isn't defined for this abslit fellow..." - <+> vcat [pretty a, pretty ta, stringToDoc $ show a] - Constant c -> - case c of - ConstantAbstract ca -> - case ca of - AbsLitTuple xs -> do - fxs <- sequence (flatten <$> (Constant <$> xs)) - let flatxs = fromList fxs - return [essence| flatten(&flatxs) |] - _ -> bug $ "rule_FlattenLex: flatten isn't defined for this constant fellow..." - <+> vcat [pretty a, pretty ta, stringToDoc $ show a] - _ -> bug $ "rule_FlattenLex: flatten isn't defined for this constant fellow..." - <+> vcat [pretty a, pretty ta, stringToDoc $ show a] - Op _ -> do - (oName, o) <- quantifiedVar - flatten $ Comprehension o [ComprehensionLetting oName a] - _ -> do - ps <- sequence $ (\(i,_) -> do - (Single nm, tm) <- quantifiedVar - return (i,nm,tm)) <$> (zip [1..] ts) - let lts = (\(i,nm,_tm) -> ComprehensionLetting (Single nm) [essence| &a[&i] |]) <$> ps - tup = AbstractLiteral $ AbsLitTuple $ (\(_,_,tm) -> tm) <$> ps - flatten $ Comprehension tup lts - _ -> - case a of - AbstractLiteral x -> do - case x of - AbsLitMatrix _ xs -> do - fxs <- sequence (flatten <$> xs) - let flatxs = fromList fxs - return [essence| flatten(&flatxs) |] - _ -> bug $ "rule_FlattenLex: flatten isn't defined for this abslit fellow..." - <+> vcat [pretty a, pretty ta, stringToDoc $ show a] - Constant c -> - case c of - ConstantAbstract ca -> - case ca of - AbsLitMatrix _ [] -> - return [essence| ([] : `matrix indexed by [int()] of int`) |] - AbsLitMatrix _ xs -> do - fxs <- sequence (flatten <$> (Constant <$> xs)) - let flatxs = fromList fxs - return [essence| flatten(&flatxs) |] - _ -> bug $ "rule_FlattenLex: flatten isn't defined for this constant fellow..." - <+> vcat [pretty a, pretty ta, stringToDoc $ show a] - TypedConstant tc _ -> flatten (Constant tc) - _ -> bug $ "rule_FlattenLex: flatten isn't defined for this constant fellow..." - <+> vcat [pretty a, pretty ta, stringToDoc $ show a] - Op _ -> do - (oName, o) <- quantifiedVar - flatten $ Comprehension o [ComprehensionLetting oName a] - Reference nm ex -> - bug $ "rule_FlattenLex: flatten isn't defined for this reference fellow..." - <+> vcat [stringToDoc (show a) - ,"reference:" <+> stringToDoc (show nm) - ,"fellow:" <+> stringToDoc (show ex)] - Comprehension body gocs -> do - fbody <- flatten body - let comp = Comprehension fbody gocs - return [essence| flatten(&comp) |] - _ -> bug $ "rule_FlattenLex: flatten isn't defined for this expression fellow..." - - <+> vcat [pretty a, pretty ta, stringToDoc $ show a] - - -rule_ReducerToComprehension :: Rule -rule_ReducerToComprehension = "reducer-to-comprehension" `namedRule` theRule where - theRule p = do - (_, _, mk, coll) <- match opReducer p - -- leave comprehensions alone - let - isComprehension Comprehension{} = True - isComprehension _ = False - case followAliases isComprehension coll of - True -> na "rule_ReducerToComprehension" - False -> return () - -- leave matrix literals alone - case tryMatch matrixLiteral coll of - Nothing -> return () - Just {} -> na "rule_ReducerToComprehension" - tyColl <- typeOf coll - howToIndex <- case tyColl of - TypeSequence{} -> return $ Left () - TypeMatrix{} -> return $ Right () - TypeList{} -> return $ Right () - TypeSet{} -> return $ Right () - TypeMSet{} -> return $ Right () - _ -> na "rule_ReducerToComprehension" - return - ( "Creating a comprehension for the collection inside the reducer operator." - , do - (iPat, i) <- quantifiedVar - case howToIndex of - Left{} -> return $ mk [essence| [ &i[2] | &iPat <- &coll ] |] - Right{} -> return $ mk [essence| [ &i | &iPat <- &coll ] |] - ) - - -rule_TrueIsNoOp :: Rule -rule_TrueIsNoOp = "true-is-noop" `namedRule` theRule where - theRule (Op (MkOpTrue (OpTrue ref))) = - case ref of - Reference _ (Just DeclHasRepr{}) -> - return ( "Remove the argument from true." - , return $ Constant $ ConstantBool True - ) - _ -> na "The argument of true doesn't have a representation." - theRule _ = na "rule_TrueIsNoOp" - - -rule_FlattenOf1D :: Rule -rule_FlattenOf1D = "flatten-of-1D" `namedRule` theRule where - theRule p = do - x <- match opFlatten p - tyx <- typeOf x - out <- case tyx of - TypeList TypeBool{} -> return x - TypeList TypeInt{} -> return x - TypeMatrix _ TypeBool{} -> return x - TypeMatrix _ TypeInt{} -> return x - TypeMatrix{} -> -- more than 1D - case listOut x of - Just [y] -> return (make opFlatten y) - _ -> na "rule_FlattenOf1D" - _ -> na "rule_FlattenOf1D" - return ( "1D matrices do not need a flatten." - , return out - ) - - -rule_Decompose_AllDiff :: Rule -rule_Decompose_AllDiff = "decompose-allDiff" `namedRule` theRule where - theRule [essence| allDiff(&m) |] = do - ty <- typeOf m - case ty of - TypeMatrix _ TypeBool -> na "allDiff can stay" - TypeMatrix _ (TypeInt _) -> na "allDiff can stay" - TypeMatrix _ _ -> return () - _ -> na "allDiff on something other than a matrix." - index:_ <- indexDomainsOf m - return - ( "Decomposing allDiff. Type:" <+> pretty ty - , do - (iPat, i) <- quantifiedVar - (jPat, j) <- quantifiedVar - return - [essence| - and([ &m[&i] != &m[&j] - | &iPat : &index - , &jPat : &index - , &i < &j - ]) - |] - ) - theRule _ = na "rule_Decompose_AllDiff" - - -rule_DomainCardinality :: Rule -rule_DomainCardinality = "domain-cardinality" `namedRule` theRule where - theRule p = do - maybeDomain <- match opTwoBars p - d <- case maybeDomain of - Domain d -> return d - Reference _ (Just (Alias (Domain d))) -> return d - _ -> na "rule_DomainCardinality" - return - ( "Cardinality of a domain" - , case d of - DomainInt _ [RangeBounded 1 u] -> return u - _ -> do - (iPat, _) <- quantifiedVar - return [essence| sum([ 1 | &iPat : &d ]) |] - ) - - -rule_DomainMinMax :: Rule -rule_DomainMinMax = "domain-MinMax" `namedRule` theRule where - theRule [essence| max(&maybeDomain) |] = do - d <- getDomain maybeDomain - return - ( "max of a domain" - , maxOfDomain d - ) - theRule [essence| min(&maybeDomain) |] = do - d <- getDomain maybeDomain - return - ( "min of a domain" - , minOfDomain d - ) - theRule _ = na "rule_DomainMinMax" - - getDomain :: MonadFail m => Expression -> m (Domain () Expression) - getDomain (Domain d) = return d - getDomain (Reference _ (Just (Alias (Domain d)))) = getDomain (Domain d) - getDomain _ = na "rule_DomainMinMax.getDomain" - - -rule_ComplexAbsPat :: Rule -rule_ComplexAbsPat = "complex-pattern" `namedRule` theRule where - theRule (Comprehension body gensOrConds) = do - (gocBefore, (pat, domainOrExpr), gocAfter) <- matchFirst gensOrConds $ \ goc -> case goc of - Generator (GenDomainNoRepr pat@AbsPatTuple{} domain) -> return (pat, Left domain) - Generator (GenInExpr pat@AbsPatTuple{} expr) -> return (pat, Right expr) - _ -> na "rule_ComplexAbsPat" - return - ( "complex pattern on tuple patterns" - , do - (iPat, i) <- quantifiedVar - let replacements = [ (p, make opMatrixIndexing i (map (fromInt . fromIntegral) is)) - | (p, is) <- genMappings pat - ] - let f x@(Reference nm _) = fromMaybe x (lookup nm replacements) - f x = x - return $ Comprehension (transform f body) - $ gocBefore - ++ [ either (Generator . GenDomainNoRepr iPat) - (Generator . GenInExpr iPat) - domainOrExpr ] - ++ transformBi f gocAfter - ) - theRule _ = na "rule_ComplexAbsPat" - - -- i --> i -> [] - -- (i,j) --> i -> [1] - -- j -> [2] - -- (i,(j,k)) --> i -> [1] - -- j -> [2,1] - -- k -> [2,2] - genMappings :: AbstractPattern -> [(Name, [Int])] - genMappings (Single nm) = [(nm, [])] - genMappings (AbsPatTuple pats) - = concat - [ [ (patCore, i:is) | (patCore, is) <- genMappings pat ] - | (i, pat) <- zip [1..] pats - ] - genMappings (AbsPatMatrix pats) - = concat - [ [ (patCore, i:is) | (patCore, is) <- genMappings pat ] - | (i, pat) <- zip [1..] pats - ] - genMappings pat = bug ("rule_ComplexLambda.genMappings:" <+> pretty (show pat)) - - --- this rule doesn't use `namedRule` because it need access to ascendants through the zipper -rule_InlineConditions :: Rule -rule_InlineConditions = Rule "inline-conditions" theRule where - theRule z (Comprehension body gensOrConds) = do - let (toInline, toKeep) = mconcat - [ case goc of - Condition x | categoryOf x == CatDecision -> ([x],[]) - _ -> ([],[goc]) - | goc <- gensOrConds - ] - theGuard <- case toInline of - [] -> na "No condition to inline." - [x] -> return x - xs -> return $ make opAnd $ fromList xs - (nameQ, opSkip) <- queryQ z - let bodySkipped = opSkip theGuard body - return - [ RuleResult - { ruleResultDescr = "Inlining conditions, inside" <+> nameQ - , ruleResultType = ExpressionRefinement - , ruleResult = return $ Comprehension bodySkipped toKeep - , ruleResultHook = Nothing - } ] - theRule _ _ = na "rule_InlineConditions" - - -- keep going up, until finding a quantifier - -- when found, return the skipping operator for the quantifier - -- if none exists, do not apply the rule. - -- (or maybe we should call bug right ahead, it can't be anything else.) -<<<<<<< HEAD - queryQ z0 = case Zipper.up z0 of - Nothing -> na "rule_InlineConditions (top)" - Just z -> queryQ_handleLevel z (hole z) - - queryQ_handleLevel z h - | Just{} <- match opAnd h = return ("and", opAndSkip) - | Just{} <- match opOr h = return ("or" , opOrSkip ) - | Just{} <- match opSum h = return ("sum", opSumSkip) - | Just{} <- match opMin h = na "rule_InlineConditions (min)" - | Just{} <- match opMax h = na "rule_InlineConditions (max)" - | Just{} <- match opOrdering h = return ("ordering", opSumSkip) - | Comprehension{} <- h = queryQ z - | Just{} <- match opFlatten h = queryQ z - | otherwise = na "rule_InlineConditions (stop)" - - opAndSkip b x = [essence| &b -> &x |] - opOrSkip b x = [essence| &b /\ &x |] - - opSumSkip b [essence| flatten(&x)|] = make opFlatten (opSumSkip b x) - opSumSkip b (Comprehension body gocs) = Comprehension (opSumSkip b body) gocs - opSumSkip b x = [essence| toInt(&b) * catchUndef(&x, 0) |] -======= - queryQ z0 = - case Zipper.up z0 of - Nothing -> na "rule_InlineConditions (meh-1)" - Just z -> do - let h = hole z - case ( match opAnd h, match opOr h, match opSum h, match opProduct h - , match opMin h, match opMax h, match opOrdering h ) of - (Just{}, _, _, _, _, _, _) -> return ("and", opAndSkip) - (_, Just{}, _, _, _, _, _) -> return ("or" , opOrSkip ) - (_, _, Just{}, _, _, _, _) -> return ("sum", opSumSkip) - (_, _, _, Just{}, _, _, _) -> return ("product", opProductSkip) - (_, _, _, _, Just{}, _, _) -> na "rule_InlineConditions (min)" - (_, _, _, _, _, Just{}, _) -> na "rule_InlineConditions (max)" - (_, _, _, _, _, _, Just{}) -> return ("ordering", opSumSkip) - _ -> na "rule_InlineConditions (meh-2)" - -- case Zipper.up z of - -- Nothing -> na "queryQ" - -- Just u -> queryQ u - - opAndSkip b x = [essence| &b -> &x |] - opOrSkip b x = [essence| &b /\ &x |] - opSumSkip b x = [essence| toInt(&b) * catchUndef(&x, 0) |] - opProductSkip b x = [essence| [ 1 - , catchUndef(&x,1) - ; int(0..1) - ] [toInt(&b)] |] ->>>>>>> master - - -rule_InlineConditions_AllDiff :: Rule -rule_InlineConditions_AllDiff = "inline-conditions-allDiff" `namedRule` theRule where - theRule (Op (MkOpAllDiff (OpAllDiff (Comprehension body gensOrConds)))) = do - let (toInline, toKeep) = mconcat - [ case goc of - Condition x | categoryOf x == CatDecision -> ([x],[]) - _ -> ([],[goc]) - | goc <- gensOrConds - ] - theGuard <- case toInline of - [] -> na "No condition to inline." - [x] -> return x - xs -> return $ make opAnd $ fromList xs - - domBody <- domainOf body - let - collectLowerBounds (RangeSingle x) = return x - collectLowerBounds (RangeBounded x _) = return x - collectLowerBounds _ = userErr1 ("Unexpected infinite domain:" <+> pretty domBody) - - collectLowerBoundsD (DomainInt _ rs) = mapM collectLowerBounds rs - collectLowerBoundsD _ = userErr1 ("Expected an integer domain, but got:" <+> pretty domBody) - - bounds <- collectLowerBoundsD domBody - let lowerBound = make opMin (fromList bounds) - - -- for each element, we do element-lowerBound+1 - -- this makes sure the smallest element is 1 - -- hence we can use 0 as the except value! - let bodySkipped = [essence| toInt(&theGuard) * catchUndef(&body + (1 - &lowerBound), 0) |] - - return - ( "Inlining conditions, inside allDiff" - , return $ make opAllDiffExcept (Comprehension bodySkipped toKeep) 0 - ) - theRule _ = na "rule_InlineConditions_AllDiff" - - -rule_InlineConditions_MaxMin :: Rule -rule_InlineConditions_MaxMin = "aux-for-MaxMin" `namedRule` theRule where - theRule p = do - when (categoryOf p < CatDecision) $ na "rule_InlineConditions_MaxMin" - (nameQ, binOp, Comprehension body gensOrConds) <- - case (match opMax p, match opMin p) of - (Just res, _) -> return ("max", \ a b -> [essence| &a <= &b |], res ) - (_, Just res) -> return ("min", \ a b -> [essence| &a >= &b |], res ) - _ -> na "rule_InlineConditions_MaxMin" - let - (toInline, gocInExpr, _toKeep) = mconcat - [ case goc of - Condition x | categoryOf x == CatDecision -> ([x],[],[]) - Generator (GenInExpr {}) -> ([],[goc],[]) - _ -> ([],[],[goc]) - | goc <- gensOrConds - ] - when (null toInline && null gocInExpr) $ na "rule_InlineConditions_MaxMin" - auxDomain <- domainOf body - return - ( "Creating auxiliary variable for a" <+> nameQ - , do - (auxName, aux) <- auxiliaryVar - let auxDefinedLHS = make opSum (Comprehension 1 gensOrConds) - let auxDefined = [essence| &auxDefinedLHS > 0 |] - let auxUndefined = [essence| &auxDefinedLHS = 0 |] - let aux' = WithLocals aux (DefinednessConstraints [auxDefined]) - return $ WithLocals aux' - (AuxiliaryVars - [ Declaration (FindOrGiven LocalFind auxName auxDomain) - , SuchThat - [ make opAnd $ Comprehension - (binOp body aux) - gensOrConds - - -- either one of the members of this comprehension, or dontCare - -- if it is indeed dontCare, care should be taken to make sure it isn't used as a normal value - , make opAnd $ fromList - [ make opImply auxDefined - (make opOr $ Comprehension - [essence| &body = &aux |] - gensOrConds) - , make opImply auxUndefined (make opDontCare aux) - ] - ] - ]) - ) - - -rule_AttributeToConstraint :: Rule -rule_AttributeToConstraint = "attribute-to-constraint" `namedRule` theRule where - theRule (Op (MkOpAttributeAsConstraint (OpAttributeAsConstraint thing attr mval))) = do - dom <- domainOf thing - let conv = mkAttributeToConstraint dom attr mval thing - return - ( "Converting an attribute to a constraint" - , bugFailT "rule_AttributeToConstraint" conv - ) - theRule _ = na "rule_AttributeToConstraint" - - -rule_FullEvaluate :: Rule -rule_FullEvaluate = "full-evaluate" `namedRule` theRule where - theRule Constant{} = na "rule_FullEvaluate" - theRule Domain{} = na "rule_FullEvaluate" - theRule p = do - constant <- instantiateExpression [] p - unless (null [() | ConstantUndefined{} <- universe constant]) $ - na "rule_PartialEvaluate, undefined" - return - ( "Full evaluator" - , return $ Constant constant - ) - - -rule_PartialEvaluate :: Rule -rule_PartialEvaluate = "partial-evaluate" `namedRuleZ` theRule where - -- if a variable only has a single value in its domain, replace it with the value - theRule z (Reference _ (Just (DeclHasRepr _ _ (singletonDomainInt -> Just val)))) = - case hole <$> Zipper.up z of - Just (Op (MkOpTrue _)) -> na "rule_PartialEvaluate, inside a true(ref)" - _ -> return ( "Partial evaluator" - , return val - ) - theRule _ (Op op) - | Just (x, y) <- case op of - MkOpLeq (OpLeq x y) -> Just (x,y) - MkOpGeq (OpGeq x y) -> Just (x,y) - MkOpEq (OpEq x y) -> Just (x,y) - _ -> Nothing - , Reference nmX _ <- x - , Reference nmY _ <- y - , nmX == nmY - , categoryOf x <= CatQuantified - , categoryOf y <= CatQuantified - = return - ( "Parameter = parameter (or quantified)" - , return (fromBool True) - ) - theRule _ (Op x) = do - x' <- simplifyOp x - when (Op x == x') $ bug $ vcat - [ "rule_PartialEvaluate, simplifier returns the input unchanged." - , "input:" <+> vcat [ pretty (Op x) - , pretty (show (Op x)) - ] - ] - return - ( "Partial evaluator" - , return x' - ) - theRule _ _ = na "rule_PartialEvaluate" - - --- | shifting quantifiers inwards, if they operate on a row of a 2d matrix, --- make them operate on the rows directly then index -rule_QuantifierShift :: Rule -rule_QuantifierShift = "quantifier-shift" `namedRule` theRule where - theRule p = do - (_, _, mkQuan, inner) <- match opReducer p - (matrix, indexer) <- match opIndexing inner - (TypeMatrix _ ty, index, elems) <- match matrixLiteral matrix - case ty of - TypeMatrix{} -> return () - TypeList{} -> return () - _ -> na "rule_QuantifierShift" - return - ( "Shifting quantifier inwards" - , return $ make opIndexing - (make matrixLiteral - ty - index - (map mkQuan elems)) - indexer - ) - - --- | shifting quantifiers inwards, if they operate on a flattened multi-dim matrix. -rule_QuantifierShift2 :: Rule -rule_QuantifierShift2 = "quantifier-shift2" `namedRule` theRule where - theRule p = do - (_, _, mkQuan, inner) <- match opReducer p - matrix <- match opFlatten inner - (TypeMatrix _ ty, index, elems) <- match matrixLiteral matrix - case ty of - TypeMatrix{} -> return () -- the matrix literal should contain further matrix/list stuff. - TypeList{} -> return () - _ -> na "rule_QuantifierShift2" - return - ( "Shifting quantifier inwards" - , return $ mkQuan - (make matrixLiteral - ty - index - (map (mkQuan . flattenIfNeeded (matrixNumDims ty)) elems)) - ) - - --- | shifting quantifiers inwards, if they operate on a concatenated multi-dim matrix. -rule_QuantifierShift3 :: Rule -rule_QuantifierShift3 = "quantifier-shift3" `namedRule` theRule where - theRule p = do - (_, True, mkQuan, inner) <- match opReducer p - matrix <- match opConcatenate inner - (TypeMatrix _ ty, index, elems) <- match matrixLiteral matrix - return - ( "Shifting quantifier inwards" - , return $ mkQuan $ make matrixLiteral - ty - index - (map mkQuan elems) - ) - - -rule_Comprehension_Simplify :: Rule -rule_Comprehension_Simplify = "comprehension-simplify" `namedRule` theRule where - theRule (Comprehension x gocs) - | let isTrueCondition (Condition (Constant (ConstantBool True))) = True - isTrueCondition _ = False - , let gocs' = filter (not . isTrueCondition) gocs - , length gocs' < length gocs - = return - ( "Removing true conditions" - , return $ Comprehension x gocs' - ) - theRule _ = na "rule_Comprehension_Simplify" - - -rule_Xor_To_Sum :: Rule -rule_Xor_To_Sum = "xor-to-sum" `namedRule` theRule where - theRule [essence| xor(&arg) |] = - case arg of - Comprehension body goc -> do - let argOut = Comprehension [essence| toInt(&body) |] goc - return - ( "xor to sum" - , return [essence| 1 = sum(&argOut) |] - ) - AbstractLiteral (AbsLitMatrix dom elems) -> do - let argOut = AbstractLiteral $ AbsLitMatrix dom - [ [essence| toInt(&el) |] | el <- elems ] - return - ( "xor to sum" - , return [essence| 1 = sum(&argOut) |] - ) - _ -> do - (iPat, i) <- quantifiedVar - return - ( "xor to sum" - , return [essence| 1 = sum([ toInt(&i) | &iPat <- &arg ]) |] - ) - theRule _ = na "rule_Xor_To_Sum" - - -<<<<<<< HEAD -enforceTagConsistency :: MonadFail m => Model -> m Model -enforceTagConsistency model = do - let statements' = transformBi reDomExp $ transformBi reDomConst (mStatements model) - return model { mStatements = statements' } - - -addUnnamedSymmetryBreaking :: - NameGen m => - Maybe UnnamedSymmetryBreaking -> - Model -> - m Model -addUnnamedSymmetryBreaking mode model = do - - let - allUnnamedTypes :: [(Domain () Expression, Expression)] - allUnnamedTypes = - [ reTag (TagUnnamed nm') (DomainReference nm Nothing, x) --x is a TagInt at this point so we must reTag it - | Declaration (LettingDomainDefnUnnamed nm@(Name nm') x) <- mStatements model - ] - - allDecVars = - [ (Reference nm Nothing, domain) - | Declaration (FindOrGiven Find nm domain) <- mStatements model - ] - - allDecVarsAux auxSuffix = - [ (Reference (mconcat [nm, "_auxFor_", auxSuffix]) Nothing, domain) - | Declaration (FindOrGiven Find nm domain) <- mStatements model - ] - - varsTuple = AbstractLiteral $ AbsLitTuple $ map fst allDecVars - mkAuxTuple auxSuffix = AbstractLiteral $ AbsLitTuple $ map fst (allDecVarsAux auxSuffix) - --- traceM $ show $ "Unnamed types in this model:" <++> prettyList id "," allUnnamedTypes --- traceM $ show $ "Unnamed decision variables in this model:" <++> prettyList id "," allDecVars - - -- 3 axis of doom - -- 1. Quick/Complete. Quick is x .<= p(x) - -- Complete is x .<= y /\ y = p(x) - -- 2. Scope. Consecutive - -- AllPairs - -- AllPermutations - -- 3. Independently/Altogether - - case mode of - Nothing -> return model - Just (UnnamedSymmetryBreaking quickOrComplete usbScope independentlyOrAltogether) -> do - let newDecls = - case quickOrComplete of - USBQuick -> [] - USBComplete -> - case independentlyOrAltogether of - USBIndependently -> - [ Declaration (FindOrGiven LocalFind nm' domain) - | Declaration (FindOrGiven Find nm domain) <- mStatements model - , (DomainReference uName _, _) <- allUnnamedTypes - , let nm' = mconcat [nm, "_auxFor_", uName] - ] - USBAltogether -> - [ Declaration (FindOrGiven LocalFind nm' domain) - | Declaration (FindOrGiven Find nm domain) <- mStatements model - , let nm' = mconcat [nm, "_auxFor_all"] - ] - - let - - buildPermutationChain [] vars = vars - buildPermutationChain (p:ps) vars = - let applied = buildPermutationChain ps vars - in [essence| image(&p, &applied) |] - - nestInBubbles :: Expression -> Int -> [(Expression,Statement)] -> Expression -> Expression - nestInBubbles _ _ [] expr = expr - nestInBubbles modl i (fv:auxVars) expr = - let v = fst fv - ii = fromInt (fromIntegral i) - in WithLocals [essence| &modl[&ii] .<= &v |] (AuxiliaryVars ((snd fv):[SuchThat [nestInBubbles modl (i + 1) auxVars expr]])) - - combinedPermApply auxSuffix perms = - case quickOrComplete of - USBQuick -> - let applied = buildPermutationChain perms varsTuple - in [essence| &varsTuple .<= &applied |] - USBComplete -> - let applied = buildPermutationChain perms varsTuple - thisAuxTuple = mkAuxTuple auxSuffix - - dVars = map fst (allDecVarsAux auxSuffix) - in nestInBubbles varsTuple 1 (zip dVars newDecls) - [essence| &thisAuxTuple = &applied |] - - mkGenerator_Consecutive _ _ [] = bug "must have at least one unnamed type" - mkGenerator_Consecutive auxSuffix perms [(u, uSize)] = do - (iPat, i) <- quantifiedVar - let perm = [essence| permutation((&i, succ(&i))) |] - let applied = combinedPermApply auxSuffix (perm:perms) - return [essence| - and([ &applied - | &iPat : &u - , &i < &uSize - ]) - |] - mkGenerator_Consecutive auxSuffix perms ((u, uSize):us) = do - (iPat, i) <- quantifiedVar - let perm = [essence| permutation((&i, succ(&i))) |] - applied <- mkGenerator_Consecutive auxSuffix (perm:perms) us - return [essence| - and([ &applied - | &iPat : &u - , &i < &uSize - ]) - |] - - - mkGenerator_AllPairs _ _ [] = bug "must have at least one unnamed type" - mkGenerator_AllPairs auxSuffix perms [(u, _uSize)] = do - (iPat, i) <- quantifiedVar - (jPat, j) <- quantifiedVar - let perm = [essence| permutation((&i, &j)) |] - let applied = combinedPermApply auxSuffix (perm:perms) - return [essence| - and([ &applied - | &iPat : &u - , &jPat : &u - , &i < &j - ]) - |] - mkGenerator_AllPairs auxSuffix perms ((u, _uSize):us) = do - (iPat, i) <- quantifiedVar - (jPat, j) <- quantifiedVar - let perm = [essence| permutation((&i, &j)) |] - applied <- mkGenerator_AllPairs auxSuffix (perm:perms) us - return [essence| - and([ &applied - | &iPat : &u - , &jPat : &u - , &i < &j - ]) - |] - - mkGenerator_AllPermutations _ _ [] = bug "must have at least one unnamed type" - mkGenerator_AllPermutations auxSuffix perms [(u, _uSize)] = do - (iPat, i) <- quantifiedVar - let perm = i - let applied = combinedPermApply auxSuffix (perm:perms) - return [essence| - and([ &applied - | &iPat : permutation of &u - ]) - |] - mkGenerator_AllPermutations auxSuffix perms ((u, _uSize):us) = do - (iPat, i) <- quantifiedVar - let perm = i - applied <- mkGenerator_AllPermutations auxSuffix (perm:perms) us - return [essence| - and([ &applied - | &iPat : permutation of &u - ]) - |] - - mkGenerator auxSuffix perms us = - case usbScope of - USBConsecutive -> mkGenerator_Consecutive auxSuffix perms us - USBAllPairs -> mkGenerator_AllPairs auxSuffix perms us - USBAllPermutations -> mkGenerator_AllPermutations auxSuffix perms us - newCons <- - case independentlyOrAltogether of - USBIndependently -> do - xs <- (sequence - [ mkGenerator uName [] [(u, uSize)] - | (u@(DomainReference uName _), uSize) <- allUnnamedTypes - ]) - return [SuchThat xs] - USBAltogether -> do - cons <- mkGenerator "all" [] allUnnamedTypes - return [SuchThat [cons]] - - let stmts = newCons - traceM $ show $ vcat $ "Adding the following unnamed symmetry breaking constraints:" - : map (nest 4 . pretty) stmts - return model { mStatements = mStatements model ++ stmts} -======= -rule_Comprehension_Cardinality :: Rule -rule_Comprehension_Cardinality = "comprehension-cardinality" `namedRule` theRule where - theRule p = do - Comprehension _ gensOrConds <- match opTwoBars p - let ofones = Comprehension (fromInt 1) gensOrConds - return ( "Horizontal rule for comprehension cardinality" - , return [essence| sum(&ofones) |] - ) - -rule_Flatten_Cardinality :: Rule -rule_Flatten_Cardinality = "flatten-cardinality" `namedRule` theRule where - theRule p = do - list <- match opTwoBars p >>= match opConcatenate - return ( "Horizontal rule for comprehension cardinality" - , do - (iPat, i) <- quantifiedVar - return [essence| sum([ |&i| | &iPat <- &list ]) |] - ) ->>>>>>> master - diff --git a/tests/custom/basic/function-literal-suggestion/run.sh.orig b/tests/custom/basic/function-literal-suggestion/run.sh.orig deleted file mode 100755 index ddf5903d30..0000000000 --- a/tests/custom/basic/function-literal-suggestion/run.sh.orig +++ /dev/null @@ -1,8 +0,0 @@ -<<<<<<< HEAD -conjure solve *.essence *.param -||||||| merged common ancestors -======= -rm -rf conjure-output -conjure solve *.essence *.param -rm -rf conjure-output ->>>>>>> taggedints diff --git a/tests/custom/basic/function-literal-suggestion/stdout.expected.orig b/tests/custom/basic/function-literal-suggestion/stdout.expected.orig deleted file mode 100644 index 11c8d0c0e6..0000000000 --- a/tests/custom/basic/function-literal-suggestion/stdout.expected.orig +++ /dev/null @@ -1,10 +0,0 @@ -<<<<<<< HEAD -Using cached models. -Savile Row: model000001.eprime p.param -||||||| merged common ancestors -======= -Generating models for func.essence -Generated models: model000001.eprime -Saved under: conjure-output -Savile Row: model000001.eprime p.param ->>>>>>> taggedints diff --git a/tests/custom/issues/119/1/stdout.expected.orig b/tests/custom/issues/119/1/stdout.expected.orig deleted file mode 100644 index 8e4a745555..0000000000 --- a/tests/custom/issues/119/1/stdout.expected.orig +++ /dev/null @@ -1,56 +0,0 @@ -Generating models for _old_issues_118_smaller.essence -Generated models: model_1.eprime, model_2.eprime, model_3.eprime, model_4.eprime -Saved under: conjure-output -Savile Row: model_1.eprime -Running minion for domain filtering. -Running solver: minion -Savile Row: model_2.eprime -Running minion for domain filtering. -Running solver: minion -Savile Row: model_3.eprime -Running minion for domain filtering. -Running solver: minion -Savile Row: model_4.eprime -Running minion for domain filtering. -Running solver: minion -Validating solution: conjure-output/model_1-solution000001.solution -Validating solution: conjure-output/model_2-solution000001.solution -Validating solution: conjure-output/model_3-solution000001.solution -Validating solution: conjure-output/model_4-solution000001.solution ----- -language Essence 1.3 - -letting p be partition({1}, {2}, {3}) -$ Visualisation for p -$ 1 -$ 2 -$ 3 - -language Essence 1.3 - -letting p be partition({1}, {2}, {3}) -$ Visualisation for p -$ 1 -$ 2 -$ 3 - -language Essence 1.3 - -letting p be partition({1}, {2}, {3}) -$ Visualisation for p -$ 1 -$ 2 -$ 3 - -language Essence 1.3 - -letting p be partition({1}, {2}, {3}) -$ Visualisation for p -$ 1 -$ 2 -$ 3 - ----- - -language Essence 1.3 -letting p be partition({1}, {2}, {3}) diff --git a/tests/custom/issues/119/2/stdout.expected.orig b/tests/custom/issues/119/2/stdout.expected.orig deleted file mode 100644 index 0ca6e24ba7..0000000000 --- a/tests/custom/issues/119/2/stdout.expected.orig +++ /dev/null @@ -1,44 +0,0 @@ -Generating models for _old_issues_118_smaller2.essence -Generated models: model_1.eprime, model_2.eprime, model_3.eprime -Saved under: conjure-output -Savile Row: model_1.eprime -Running minion for domain filtering. -Running solver: minion -Savile Row: model_2.eprime -Running minion for domain filtering. -Running solver: minion -Savile Row: model_3.eprime -Running minion for domain filtering. -Running solver: minion -Validating solution: conjure-output/model_1-solution000001.solution -Validating solution: conjure-output/model_2-solution000001.solution -Validating solution: conjure-output/model_3-solution000001.solution ----- -language Essence 1.3 - -letting p be partition({1}, {2}, {3}) -$ Visualisation for p -$ 1 -$ 2 -$ 3 - -language Essence 1.3 - -letting p be partition({1}, {2}, {3}) -$ Visualisation for p -$ 1 -$ 2 -$ 3 - -language Essence 1.3 - -letting p be partition({1}, {2}, {3}) -$ Visualisation for p -$ 1 -$ 2 -$ 3 - ----- - -language Essence 1.3 -letting p be partition({1}, {2}, {3}) diff --git a/tests/custom/issues/370/01/stdout.expected.orig b/tests/custom/issues/370/01/stdout.expected.orig deleted file mode 100644 index ddc21686c5..0000000000 --- a/tests/custom/issues/370/01/stdout.expected.orig +++ /dev/null @@ -1,36 +0,0 @@ -Generating models for 370.essence -Generated models: model_1.eprime, model_2.eprime, model_3.eprime, model_4.eprime, model_5.eprime, model_6.eprime, - model_7.eprime, model_8.eprime -Saved under: conjure-output -Savile Row: model_1.eprime -Running minion for domain filtering. -Running solver: minion -Savile Row: model_2.eprime -Running minion for domain filtering. -Running solver: minion -Savile Row: model_3.eprime -Running minion for domain filtering. -Running solver: minion -Savile Row: model_4.eprime -Running minion for domain filtering. -Running solver: minion -Savile Row: model_5.eprime -Running minion for domain filtering. -Running solver: minion -Savile Row: model_6.eprime -Running minion for domain filtering. -Running solver: minion -Savile Row: model_7.eprime -Running minion for domain filtering. -Running solver: minion -Savile Row: model_8.eprime -Running minion for domain filtering. -Running solver: minion -Validating solution: conjure-output/model_1-solution000001.solution -Validating solution: conjure-output/model_2-solution000001.solution -Validating solution: conjure-output/model_3-solution000001.solution -Validating solution: conjure-output/model_4-solution000001.solution -Validating solution: conjure-output/model_5-solution000001.solution -Validating solution: conjure-output/model_6-solution000001.solution -Validating solution: conjure-output/model_7-solution000001.solution -Validating solution: conjure-output/model_8-solution000001.solution diff --git a/tests/custom/issues/370/03/stdout.expected.orig b/tests/custom/issues/370/03/stdout.expected.orig deleted file mode 100644 index 01531ebc89..0000000000 --- a/tests/custom/issues/370/03/stdout.expected.orig +++ /dev/null @@ -1,19 +0,0 @@ -Generating models for 370.essence -Generated models: model_1.eprime, model_2.eprime, model_3.eprime, model_4.eprime -Saved under: conjure-output -Savile Row: model_1.eprime -Running minion for domain filtering. -Running solver: minion -Savile Row: model_2.eprime -Running minion for domain filtering. -Running solver: minion -Savile Row: model_3.eprime -Running minion for domain filtering. -Running solver: minion -Savile Row: model_4.eprime -Running minion for domain filtering. -Running solver: minion -Validating solution: conjure-output/model_1-solution000001.solution -Validating solution: conjure-output/model_2-solution000001.solution -Validating solution: conjure-output/model_3-solution000001.solution -Validating solution: conjure-output/model_4-solution000001.solution diff --git a/tests/custom/issues/388/2/stdout.expected.orig b/tests/custom/issues/388/2/stdout.expected.orig deleted file mode 100644 index 8d07a74ca9..0000000000 --- a/tests/custom/issues/388/2/stdout.expected.orig +++ /dev/null @@ -1,157 +0,0 @@ -Generating models for 388-2.essence -Generated models: model_1_1.eprime, model_1_2.eprime, model_1_3.eprime, model_1_4.eprime, model_2_1.eprime, - model_2_2.eprime, model_2_3.eprime, model_2_4.eprime, model_3_1.eprime, model_3_2.eprime, - model_3_3.eprime, model_3_4.eprime, model_4_1.eprime, model_4_2.eprime, model_4_3.eprime, - model_4_4.eprime -Saved under: conjure-output -Savile Row: model_1_1.eprime -Running minion for domain filtering. -Running solver: minion -Savile Row: model_1_2.eprime -Running minion for domain filtering. -Running solver: minion -Savile Row: model_1_3.eprime -Running minion for domain filtering. -Running solver: minion -Savile Row: model_1_4.eprime -Running minion for domain filtering. -Running solver: minion -Savile Row: model_2_1.eprime -Running minion for domain filtering. -Running solver: minion -Savile Row: model_2_2.eprime -Running minion for domain filtering. -Running solver: minion -Savile Row: model_2_3.eprime -Running minion for domain filtering. -Running solver: minion -Savile Row: model_2_4.eprime -Running minion for domain filtering. -Running solver: minion -Savile Row: model_3_1.eprime -Running minion for domain filtering. -Running solver: minion -Savile Row: model_3_2.eprime -Running minion for domain filtering. -Running solver: minion -Savile Row: model_3_3.eprime -Running minion for domain filtering. -Running solver: minion -Savile Row: model_3_4.eprime -Running minion for domain filtering. -Running solver: minion -Savile Row: model_4_1.eprime -Running minion for domain filtering. -Running solver: minion -Savile Row: model_4_2.eprime -Running minion for domain filtering. -Running solver: minion -Savile Row: model_4_3.eprime -Running minion for domain filtering. -Running solver: minion -Savile Row: model_4_4.eprime -Running minion for domain filtering. -Running solver: minion -Validating solution: conjure-output/model_1_1-solution000001.solution -Validating solution: conjure-output/model_1_2-solution000001.solution -Validating solution: conjure-output/model_1_3-solution000001.solution -Validating solution: conjure-output/model_1_4-solution000001.solution -Validating solution: conjure-output/model_2_1-solution000001.solution -Validating solution: conjure-output/model_2_2-solution000001.solution -Validating solution: conjure-output/model_2_3-solution000001.solution -Validating solution: conjure-output/model_2_4-solution000001.solution -Validating solution: conjure-output/model_3_1-solution000001.solution -Validating solution: conjure-output/model_3_2-solution000001.solution -Validating solution: conjure-output/model_3_3-solution000001.solution -Validating solution: conjure-output/model_3_4-solution000001.solution -Validating solution: conjure-output/model_4_1-solution000001.solution -Validating solution: conjure-output/model_4_2-solution000001.solution -Validating solution: conjure-output/model_4_3-solution000001.solution -Validating solution: conjure-output/model_4_4-solution000001.solution ----- -language Essence 1.3 - -letting C be {1, 2, 3} -letting X be [2, 3, 1, 2, 3, 1, 2, 3, 1, 2; int(1..10)] -letting c be 3 -language Essence 1.3 - -letting C be {1, 2, 3} -letting X be [2, 3, 1, 2, 3, 1, 2, 3, 1, 2; int(1..10)] -letting c be 3 -language Essence 1.3 - -letting C be {1, 2, 3} -letting X be [2, 3, 1, 2, 3, 1, 2, 3, 1, 2; int(1..10)] -letting c be 3 -language Essence 1.3 - -letting C be {1, 2, 3} -letting X be [2, 3, 1, 2, 3, 1, 2, 3, 1, 2; int(1..10)] -letting c be 3 -language Essence 1.3 - -letting C be {1, 2, 3} -letting X be [2, 3, 1, 2, 3, 1, 2, 3, 1, 2; int(1..10)] -letting c be 3 -language Essence 1.3 - -letting C be {1, 2, 3} -letting X be [2, 3, 1, 2, 3, 1, 2, 3, 1, 2; int(1..10)] -letting c be 3 -language Essence 1.3 - -letting C be {1, 2, 3} -letting X be [2, 3, 1, 2, 3, 1, 2, 3, 1, 2; int(1..10)] -letting c be 3 -language Essence 1.3 - -letting C be {1, 2, 3} -letting X be [2, 3, 1, 2, 3, 1, 2, 3, 1, 2; int(1..10)] -letting c be 3 -language Essence 1.3 - -letting C be {1, 2, 3} -letting X be [2, 3, 1, 2, 3, 1, 2, 3, 1, 2; int(1..10)] -letting c be 3 -language Essence 1.3 - -letting C be {1, 2, 3} -letting X be [2, 3, 1, 2, 3, 1, 2, 3, 1, 2; int(1..10)] -letting c be 3 -language Essence 1.3 - -letting C be {1, 2, 3} -letting X be [2, 3, 1, 2, 3, 1, 2, 3, 1, 2; int(1..10)] -letting c be 3 -language Essence 1.3 - -letting C be {1, 2, 3} -letting X be [2, 3, 1, 2, 3, 1, 2, 3, 1, 2; int(1..10)] -letting c be 3 -language Essence 1.3 - -letting C be {1, 2, 3} -letting X be [2, 3, 1, 2, 3, 1, 2, 3, 1, 2; int(1..10)] -letting c be 3 -language Essence 1.3 - -letting C be {1, 2, 3} -letting X be [2, 3, 1, 2, 3, 1, 2, 3, 1, 2; int(1..10)] -letting c be 3 -language Essence 1.3 - -letting C be {1, 2, 3} -letting X be [2, 3, 1, 2, 3, 1, 2, 3, 1, 2; int(1..10)] -letting c be 3 -language Essence 1.3 - -letting C be {1, 2, 3} -letting X be [2, 3, 1, 2, 3, 1, 2, 3, 1, 2; int(1..10)] -letting c be 3 ----- - -language Essence 1.3 -letting C be {1, 2, 3} -letting X be [2, 3, 1, 2, 3, 1, 2, 3, 1, 2; int(1..10)] -letting c be 3 diff --git a/tests/exhaustive/autogen/gen02/expected/model_1_1-solution000001.solution b/tests/exhaustive/autogen/gen02/expected/model_1_1-solution000001.solution new file mode 100644 index 0000000000..19d999ca82 --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_1_1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting var2 be {{}} diff --git a/tests/exhaustive/autogen/gen02/expected/model_1_1-solution000002.solution b/tests/exhaustive/autogen/gen02/expected/model_1_1-solution000002.solution new file mode 100644 index 0000000000..937293310f --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_1_1-solution000002.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting var2 be {{false}} +$ Visualisation for var2 +$ _ + diff --git a/tests/exhaustive/autogen/gen02/expected/model_1_1-solution000003.solution b/tests/exhaustive/autogen/gen02/expected/model_1_1-solution000003.solution new file mode 100644 index 0000000000..5a187652fa --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_1_1-solution000003.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting var2 be {{true}} +$ Visualisation for var2 +$ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_1_1-solution000004.solution b/tests/exhaustive/autogen/gen02/expected/model_1_1-solution000004.solution new file mode 100644 index 0000000000..0678d41bf8 --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_1_1-solution000004.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting var2 be {{false, true}} +$ Visualisation for var2 +$ _ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_1_1-solution000005.solution b/tests/exhaustive/autogen/gen02/expected/model_1_1-solution000005.solution new file mode 100644 index 0000000000..73f1bfe1ac --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_1_1-solution000005.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting var2 be {{}, {false}} +$ Visualisation for var2 +$ +$ _ + diff --git a/tests/exhaustive/autogen/gen02/expected/model_1_1-solution000006.solution b/tests/exhaustive/autogen/gen02/expected/model_1_1-solution000006.solution new file mode 100644 index 0000000000..d4c4a238b9 --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_1_1-solution000006.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting var2 be {{}, {true}} +$ Visualisation for var2 +$ +$ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_1_1-solution000007.solution b/tests/exhaustive/autogen/gen02/expected/model_1_1-solution000007.solution new file mode 100644 index 0000000000..9c15a8e4e1 --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_1_1-solution000007.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting var2 be {{}, {false, true}} +$ Visualisation for var2 +$ +$ _ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_1_1-solution000008.solution b/tests/exhaustive/autogen/gen02/expected/model_1_1-solution000008.solution new file mode 100644 index 0000000000..2b6a8959da --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_1_1-solution000008.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting var2 be {{false}, {true}} +$ Visualisation for var2 +$ _ +$ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_1_1-solution000009.solution b/tests/exhaustive/autogen/gen02/expected/model_1_1-solution000009.solution new file mode 100644 index 0000000000..b2e98e56a6 --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_1_1-solution000009.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting var2 be {{false}, {false, true}} +$ Visualisation for var2 +$ _ +$ _ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_1_1-solution000010.solution b/tests/exhaustive/autogen/gen02/expected/model_1_1-solution000010.solution new file mode 100644 index 0000000000..4fc309134f --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_1_1-solution000010.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting var2 be {{false, true}, {true}} +$ Visualisation for var2 +$ _ T +$ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_1_1-solution000011.solution b/tests/exhaustive/autogen/gen02/expected/model_1_1-solution000011.solution new file mode 100644 index 0000000000..70d0f91f38 --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_1_1-solution000011.solution @@ -0,0 +1,8 @@ +language Essence 1.3 + +letting var2 be {{}, {false}, {true}} +$ Visualisation for var2 +$ +$ _ +$ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_1_1-solution000012.solution b/tests/exhaustive/autogen/gen02/expected/model_1_1-solution000012.solution new file mode 100644 index 0000000000..ebc3fe4182 --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_1_1-solution000012.solution @@ -0,0 +1,8 @@ +language Essence 1.3 + +letting var2 be {{}, {false}, {false, true}} +$ Visualisation for var2 +$ +$ _ +$ _ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_1_1-solution000013.solution b/tests/exhaustive/autogen/gen02/expected/model_1_1-solution000013.solution new file mode 100644 index 0000000000..fa4340a533 --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_1_1-solution000013.solution @@ -0,0 +1,8 @@ +language Essence 1.3 + +letting var2 be {{}, {false, true}, {true}} +$ Visualisation for var2 +$ +$ _ T +$ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_1_1-solution000014.solution b/tests/exhaustive/autogen/gen02/expected/model_1_1-solution000014.solution new file mode 100644 index 0000000000..371f28aab7 --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_1_1-solution000014.solution @@ -0,0 +1,8 @@ +language Essence 1.3 + +letting var2 be {{false}, {false, true}, {true}} +$ Visualisation for var2 +$ _ +$ _ T +$ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_1_1-solution000015.solution b/tests/exhaustive/autogen/gen02/expected/model_1_1-solution000015.solution new file mode 100644 index 0000000000..35cfa328e8 --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_1_1-solution000015.solution @@ -0,0 +1,9 @@ +language Essence 1.3 + +letting var2 be {{}, {false}, {false, true}, {true}} +$ Visualisation for var2 +$ +$ _ +$ _ T +$ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_1_1.eprime.orig b/tests/exhaustive/autogen/gen02/expected/model_1_1.eprime.orig deleted file mode 100644 index bd9607c328..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_1_1.eprime.orig +++ /dev/null @@ -1,43 +0,0 @@ -language ESSENCE' 1.0 - -find var2_ExplicitVarSizeWithMarkerR5_Marker: int(0..4) -find var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker: - matrix indexed by [int(1..4)] of int(0..2) -find var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values: - matrix indexed by [int(1..4), int(1..2)] of bool -branching on - [var2_ExplicitVarSizeWithMarkerR5_Marker, var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker, - var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values] -such that - or([q11 <= var2_ExplicitVarSizeWithMarkerR5_Marker /\ - sum([toInt(q12 <= var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q11]) - | q12 : int(1..2)]) - >= -7 - | q11 : int(1..4)]), - and([q2 + 1 <= var2_ExplicitVarSizeWithMarkerR5_Marker -> - flatten([[var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q2]; int(1)], - [-toInt(var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q2, q8]) - | q8 : int(1..2)]; - int(1..2)]) - var2_ExplicitVarSizeWithMarkerR5_Marker -> - var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q3] = 0 /\ - and([var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q3, q10] = false - | q10 : int(1..2)]) - | q3 : int(1..4)]), - and([q4 <= var2_ExplicitVarSizeWithMarkerR5_Marker -> - (2 <= var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q4] -> - -toInt(var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q4, 1]) < - -toInt(var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q4, 2])) - | q4 : int(1..4)]), - and([q4 <= var2_ExplicitVarSizeWithMarkerR5_Marker -> - and([q6 > var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q4] -> - var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q4, q6] = false - | q6 : int(1..2)]) - | q4 : int(1..4)]) - diff --git a/tests/exhaustive/autogen/gen02/expected/model_1_2-solution000001.solution b/tests/exhaustive/autogen/gen02/expected/model_1_2-solution000001.solution new file mode 100644 index 0000000000..19d999ca82 --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_1_2-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting var2 be {{}} diff --git a/tests/exhaustive/autogen/gen02/expected/model_1_2-solution000002.solution b/tests/exhaustive/autogen/gen02/expected/model_1_2-solution000002.solution new file mode 100644 index 0000000000..937293310f --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_1_2-solution000002.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting var2 be {{false}} +$ Visualisation for var2 +$ _ + diff --git a/tests/exhaustive/autogen/gen02/expected/model_1_2-solution000003.solution b/tests/exhaustive/autogen/gen02/expected/model_1_2-solution000003.solution new file mode 100644 index 0000000000..5a187652fa --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_1_2-solution000003.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting var2 be {{true}} +$ Visualisation for var2 +$ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_1_2-solution000004.solution b/tests/exhaustive/autogen/gen02/expected/model_1_2-solution000004.solution new file mode 100644 index 0000000000..0678d41bf8 --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_1_2-solution000004.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting var2 be {{false, true}} +$ Visualisation for var2 +$ _ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_1_2-solution000005.solution b/tests/exhaustive/autogen/gen02/expected/model_1_2-solution000005.solution new file mode 100644 index 0000000000..73f1bfe1ac --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_1_2-solution000005.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting var2 be {{}, {false}} +$ Visualisation for var2 +$ +$ _ + diff --git a/tests/exhaustive/autogen/gen02/expected/model_1_2-solution000006.solution b/tests/exhaustive/autogen/gen02/expected/model_1_2-solution000006.solution new file mode 100644 index 0000000000..d4c4a238b9 --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_1_2-solution000006.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting var2 be {{}, {true}} +$ Visualisation for var2 +$ +$ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_1_2-solution000007.solution b/tests/exhaustive/autogen/gen02/expected/model_1_2-solution000007.solution new file mode 100644 index 0000000000..2b6a8959da --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_1_2-solution000007.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting var2 be {{false}, {true}} +$ Visualisation for var2 +$ _ +$ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_1_2-solution000008.solution b/tests/exhaustive/autogen/gen02/expected/model_1_2-solution000008.solution new file mode 100644 index 0000000000..9c15a8e4e1 --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_1_2-solution000008.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting var2 be {{}, {false, true}} +$ Visualisation for var2 +$ +$ _ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_1_2-solution000009.solution b/tests/exhaustive/autogen/gen02/expected/model_1_2-solution000009.solution new file mode 100644 index 0000000000..b2e98e56a6 --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_1_2-solution000009.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting var2 be {{false}, {false, true}} +$ Visualisation for var2 +$ _ +$ _ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_1_2-solution000010.solution b/tests/exhaustive/autogen/gen02/expected/model_1_2-solution000010.solution new file mode 100644 index 0000000000..4fc309134f --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_1_2-solution000010.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting var2 be {{false, true}, {true}} +$ Visualisation for var2 +$ _ T +$ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_1_2-solution000011.solution b/tests/exhaustive/autogen/gen02/expected/model_1_2-solution000011.solution new file mode 100644 index 0000000000..70d0f91f38 --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_1_2-solution000011.solution @@ -0,0 +1,8 @@ +language Essence 1.3 + +letting var2 be {{}, {false}, {true}} +$ Visualisation for var2 +$ +$ _ +$ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_1_2-solution000012.solution b/tests/exhaustive/autogen/gen02/expected/model_1_2-solution000012.solution new file mode 100644 index 0000000000..ebc3fe4182 --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_1_2-solution000012.solution @@ -0,0 +1,8 @@ +language Essence 1.3 + +letting var2 be {{}, {false}, {false, true}} +$ Visualisation for var2 +$ +$ _ +$ _ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_1_2-solution000013.solution b/tests/exhaustive/autogen/gen02/expected/model_1_2-solution000013.solution new file mode 100644 index 0000000000..fa4340a533 --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_1_2-solution000013.solution @@ -0,0 +1,8 @@ +language Essence 1.3 + +letting var2 be {{}, {false, true}, {true}} +$ Visualisation for var2 +$ +$ _ T +$ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_1_2-solution000014.solution b/tests/exhaustive/autogen/gen02/expected/model_1_2-solution000014.solution new file mode 100644 index 0000000000..371f28aab7 --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_1_2-solution000014.solution @@ -0,0 +1,8 @@ +language Essence 1.3 + +letting var2 be {{false}, {false, true}, {true}} +$ Visualisation for var2 +$ _ +$ _ T +$ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_1_2-solution000015.solution b/tests/exhaustive/autogen/gen02/expected/model_1_2-solution000015.solution new file mode 100644 index 0000000000..35cfa328e8 --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_1_2-solution000015.solution @@ -0,0 +1,9 @@ +language Essence 1.3 + +letting var2 be {{}, {false}, {false, true}, {true}} +$ Visualisation for var2 +$ +$ _ +$ _ T +$ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_1_2.eprime.orig b/tests/exhaustive/autogen/gen02/expected/model_1_2.eprime.orig deleted file mode 100644 index e4f45c462c..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_1_2.eprime.orig +++ /dev/null @@ -1,122 +0,0 @@ -language ESSENCE' 1.0 - -find var2_ExplicitVarSizeWithMarkerR5_Marker: int(0..4) -find var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker: - matrix indexed by [int(1..4)] of int(0..2) -find var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values: - matrix indexed by [int(1..4), int(1..2)] of bool -find var2_ExplicitVarSizeWithMarkerR4_Marker: int(0..4) -find var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Flags: - matrix indexed by [int(1..4), int(1..2)] of bool -find var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Values: - matrix indexed by [int(1..4), int(1..2)] of bool -branching on - [var2_ExplicitVarSizeWithMarkerR4_Marker, var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Flags, - var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Values, var2_ExplicitVarSizeWithMarkerR5_Marker, - var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker, - var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values] -such that - or([q47 <= var2_ExplicitVarSizeWithMarkerR5_Marker /\ - sum([toInt(q48 <= var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q47]) - | q48 : int(1..2)]) - >= -7 - | q47 : int(1..4)]), - and([q2 + 1 <= var2_ExplicitVarSizeWithMarkerR5_Marker -> - flatten([[var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q2]; int(1)], - [-toInt(var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q2, q8]) - | q8 : int(1..2)]; - int(1..2)]) - var2_ExplicitVarSizeWithMarkerR5_Marker -> - var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q3] = 0 /\ - and([var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q3, q10] = false - | q10 : int(1..2)]) - | q3 : int(1..4)]), - and([q4 <= var2_ExplicitVarSizeWithMarkerR5_Marker -> - (2 <= var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q4] -> - -toInt(var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q4, 1]) < - -toInt(var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q4, 2])) - | q4 : int(1..4)]), - and([q4 <= var2_ExplicitVarSizeWithMarkerR5_Marker -> - and([q6 > var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q4] -> - var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q4, q6] = false - | q6 : int(1..2)]) - | q4 : int(1..4)]), - and([q11 + 1 <= var2_ExplicitVarSizeWithMarkerR4_Marker -> - flatten([flatten([[-toInt(var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Flags[q11, q19]); - int(1)], - [-toInt(var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Values[q11, q19]); - int(1)]; - int(1..2)]) - | q19 : int(1..2)]) - var2_ExplicitVarSizeWithMarkerR4_Marker -> - and([var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Flags[q12, q21] = false - | q21 : int(1..2)]) - /\ - and([var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Values[q12, q22] = false - | q22 : int(1..2)]) - | q12 : int(1..4)]), - and([q13 <= var2_ExplicitVarSizeWithMarkerR4_Marker -> - (var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Flags[q13, 2] -> - -toInt(var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Values[q13, 1]) < - -toInt(var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Values[q13, 2])) - | q13 : int(1..4)]), - and([q13 <= var2_ExplicitVarSizeWithMarkerR4_Marker -> - and([var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Flags[q13, q15] = false -> - var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Values[q13, q15] = false - | q15 : int(1..2)]) - | q13 : int(1..4)]), - and([q13 <= var2_ExplicitVarSizeWithMarkerR4_Marker -> - (var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Flags[q13, 2] -> - var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Flags[q13, 1]) - | q13 : int(1..4)]), - and([q24 <= var2_ExplicitVarSizeWithMarkerR4_Marker -> - or([q26 <= var2_ExplicitVarSizeWithMarkerR5_Marker /\ - (and([q28 <= var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q26] -> - or([var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Flags[q24, q30] /\ - var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Values[q24, q30] = - var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q26, q28] - | q30 : int(1..2)]) - | q28 : int(1..2)]) - /\ - and([var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Flags[q24, q32] -> - or([q34 <= var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q26] /\ - var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q26, q34] = - var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Values[q24, q32] - | q34 : int(1..2)]) - | q32 : int(1..2)])) - | q26 : int(1..4)]) - | q24 : int(1..4)]), - and([q36 <= var2_ExplicitVarSizeWithMarkerR5_Marker -> - or([q38 <= var2_ExplicitVarSizeWithMarkerR4_Marker /\ - (and([var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Flags[q38, q40] -> - or([q42 <= var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q36] /\ - var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q36, q42] = - var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Values[q38, q40] - | q42 : int(1..2)]) - | q40 : int(1..2)]) - /\ - and([q44 <= var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q36] -> - or([var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Flags[q38, q46] /\ - var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Values[q38, q46] = - var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q36, q44] - | q46 : int(1..2)]) - | q44 : int(1..2)])) - | q38 : int(1..4)]) - | q36 : int(1..4)]) - diff --git a/tests/exhaustive/autogen/gen02/expected/model_1_3-solution000001.solution b/tests/exhaustive/autogen/gen02/expected/model_1_3-solution000001.solution new file mode 100644 index 0000000000..19d999ca82 --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_1_3-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting var2 be {{}} diff --git a/tests/exhaustive/autogen/gen02/expected/model_1_3-solution000002.solution b/tests/exhaustive/autogen/gen02/expected/model_1_3-solution000002.solution new file mode 100644 index 0000000000..937293310f --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_1_3-solution000002.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting var2 be {{false}} +$ Visualisation for var2 +$ _ + diff --git a/tests/exhaustive/autogen/gen02/expected/model_1_3-solution000003.solution b/tests/exhaustive/autogen/gen02/expected/model_1_3-solution000003.solution new file mode 100644 index 0000000000..5a187652fa --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_1_3-solution000003.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting var2 be {{true}} +$ Visualisation for var2 +$ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_1_3-solution000004.solution b/tests/exhaustive/autogen/gen02/expected/model_1_3-solution000004.solution new file mode 100644 index 0000000000..0678d41bf8 --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_1_3-solution000004.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting var2 be {{false, true}} +$ Visualisation for var2 +$ _ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_1_3-solution000005.solution b/tests/exhaustive/autogen/gen02/expected/model_1_3-solution000005.solution new file mode 100644 index 0000000000..73f1bfe1ac --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_1_3-solution000005.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting var2 be {{}, {false}} +$ Visualisation for var2 +$ +$ _ + diff --git a/tests/exhaustive/autogen/gen02/expected/model_1_3-solution000006.solution b/tests/exhaustive/autogen/gen02/expected/model_1_3-solution000006.solution new file mode 100644 index 0000000000..d4c4a238b9 --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_1_3-solution000006.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting var2 be {{}, {true}} +$ Visualisation for var2 +$ +$ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_1_3-solution000007.solution b/tests/exhaustive/autogen/gen02/expected/model_1_3-solution000007.solution new file mode 100644 index 0000000000..9c15a8e4e1 --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_1_3-solution000007.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting var2 be {{}, {false, true}} +$ Visualisation for var2 +$ +$ _ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_1_3-solution000008.solution b/tests/exhaustive/autogen/gen02/expected/model_1_3-solution000008.solution new file mode 100644 index 0000000000..2b6a8959da --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_1_3-solution000008.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting var2 be {{false}, {true}} +$ Visualisation for var2 +$ _ +$ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_1_3-solution000009.solution b/tests/exhaustive/autogen/gen02/expected/model_1_3-solution000009.solution new file mode 100644 index 0000000000..b2e98e56a6 --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_1_3-solution000009.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting var2 be {{false}, {false, true}} +$ Visualisation for var2 +$ _ +$ _ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_1_3-solution000010.solution b/tests/exhaustive/autogen/gen02/expected/model_1_3-solution000010.solution new file mode 100644 index 0000000000..4fc309134f --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_1_3-solution000010.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting var2 be {{false, true}, {true}} +$ Visualisation for var2 +$ _ T +$ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_1_3-solution000011.solution b/tests/exhaustive/autogen/gen02/expected/model_1_3-solution000011.solution new file mode 100644 index 0000000000..70d0f91f38 --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_1_3-solution000011.solution @@ -0,0 +1,8 @@ +language Essence 1.3 + +letting var2 be {{}, {false}, {true}} +$ Visualisation for var2 +$ +$ _ +$ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_1_3-solution000012.solution b/tests/exhaustive/autogen/gen02/expected/model_1_3-solution000012.solution new file mode 100644 index 0000000000..ebc3fe4182 --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_1_3-solution000012.solution @@ -0,0 +1,8 @@ +language Essence 1.3 + +letting var2 be {{}, {false}, {false, true}} +$ Visualisation for var2 +$ +$ _ +$ _ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_1_3-solution000013.solution b/tests/exhaustive/autogen/gen02/expected/model_1_3-solution000013.solution new file mode 100644 index 0000000000..fa4340a533 --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_1_3-solution000013.solution @@ -0,0 +1,8 @@ +language Essence 1.3 + +letting var2 be {{}, {false, true}, {true}} +$ Visualisation for var2 +$ +$ _ T +$ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_1_3-solution000014.solution b/tests/exhaustive/autogen/gen02/expected/model_1_3-solution000014.solution new file mode 100644 index 0000000000..371f28aab7 --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_1_3-solution000014.solution @@ -0,0 +1,8 @@ +language Essence 1.3 + +letting var2 be {{false}, {false, true}, {true}} +$ Visualisation for var2 +$ _ +$ _ T +$ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_1_3-solution000015.solution b/tests/exhaustive/autogen/gen02/expected/model_1_3-solution000015.solution new file mode 100644 index 0000000000..35cfa328e8 --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_1_3-solution000015.solution @@ -0,0 +1,9 @@ +language Essence 1.3 + +letting var2 be {{}, {false}, {false, true}, {true}} +$ Visualisation for var2 +$ +$ _ +$ _ T +$ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_1_3.eprime.orig b/tests/exhaustive/autogen/gen02/expected/model_1_3.eprime.orig deleted file mode 100644 index 03b9841ffb..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_1_3.eprime.orig +++ /dev/null @@ -1,97 +0,0 @@ -language ESSENCE' 1.0 - -find var2_ExplicitVarSizeWithMarkerR5_Marker: int(0..4) -find var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker: - matrix indexed by [int(1..4)] of int(0..2) -find var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values: - matrix indexed by [int(1..4), int(1..2)] of bool -find var2_ExplicitVarSizeWithFlagsR5_Flags: matrix indexed by [int(1..4)] of bool -find var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Marker: matrix indexed by [int(1..4)] of int(0..2) -find var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Values: - matrix indexed by [int(1..4), int(1..2)] of bool -branching on - [var2_ExplicitVarSizeWithFlagsR5_Flags, var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Marker, - var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Values, var2_ExplicitVarSizeWithMarkerR5_Marker, - var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker, - var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values] -such that - or([q34 <= var2_ExplicitVarSizeWithMarkerR5_Marker /\ - sum([toInt(q35 <= var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q34]) - | q35 : int(1..2)]) - >= -7 - | q34 : int(1..4)]), - and([q2 + 1 <= var2_ExplicitVarSizeWithMarkerR5_Marker -> - flatten([[var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q2]; int(1)], - [-toInt(var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q2, q8]) - | q8 : int(1..2)]; - int(1..2)]) - var2_ExplicitVarSizeWithMarkerR5_Marker -> - var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q3] = 0 /\ - and([var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q3, q10] = false - | q10 : int(1..2)]) - | q3 : int(1..4)]), - and([q4 <= var2_ExplicitVarSizeWithMarkerR5_Marker -> - (2 <= var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q4] -> - -toInt(var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q4, 1]) < - -toInt(var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q4, 2])) - | q4 : int(1..4)]), - and([q4 <= var2_ExplicitVarSizeWithMarkerR5_Marker -> - and([q6 > var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q4] -> - var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q4, q6] = false - | q6 : int(1..2)]) - | q4 : int(1..4)]), - and([var2_ExplicitVarSizeWithFlagsR5_Flags[q11 + 1] -> - flatten([[var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Marker[q11]; int(1)], - [-toInt(var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Values[q11, q19]) - | q19 : int(1..2)]; - int(1..2)]) - - var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Marker[q12] = 0 /\ - and([var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Values[q12, q21] = false - | q21 : int(1..2)]) - | q12 : int(1..4)]), - and([var2_ExplicitVarSizeWithFlagsR5_Flags[q13 + 1] -> var2_ExplicitVarSizeWithFlagsR5_Flags[q13] - | q13 : int(1..3)]), - and([var2_ExplicitVarSizeWithFlagsR5_Flags[q15] -> - (2 <= var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Marker[q15] -> - -toInt(var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Values[q15, 1]) < - -toInt(var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Values[q15, 2])) - | q15 : int(1..4)]), - and([var2_ExplicitVarSizeWithFlagsR5_Flags[q15] -> - and([q17 > var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Marker[q15] -> - var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Values[q15, q17] = false - | q17 : int(1..2)]) - | q15 : int(1..4)]), - and([var2_ExplicitVarSizeWithFlagsR5_Flags[q23] -> - or([q25 <= var2_ExplicitVarSizeWithMarkerR5_Marker /\ - (var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q25] = - var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Marker[q23] - /\ - and([var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q25, q26] = - var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Values[q23, q26] - | q26 : int(1..2)])) - | q25 : int(1..4)]) - | q23 : int(1..4)]), - and([q29 <= var2_ExplicitVarSizeWithMarkerR5_Marker -> - or([var2_ExplicitVarSizeWithFlagsR5_Flags[q31] /\ - (var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Marker[q31] = - var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q29] - /\ - and([var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Values[q31, q32] = - var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q29, q32] - | q32 : int(1..2)])) - | q31 : int(1..4)]) - | q29 : int(1..4)]) - diff --git a/tests/exhaustive/autogen/gen02/expected/model_1_4-solution000001.solution b/tests/exhaustive/autogen/gen02/expected/model_1_4-solution000001.solution new file mode 100644 index 0000000000..19d999ca82 --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_1_4-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting var2 be {{}} diff --git a/tests/exhaustive/autogen/gen02/expected/model_1_4-solution000002.solution b/tests/exhaustive/autogen/gen02/expected/model_1_4-solution000002.solution new file mode 100644 index 0000000000..937293310f --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_1_4-solution000002.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting var2 be {{false}} +$ Visualisation for var2 +$ _ + diff --git a/tests/exhaustive/autogen/gen02/expected/model_1_4-solution000003.solution b/tests/exhaustive/autogen/gen02/expected/model_1_4-solution000003.solution new file mode 100644 index 0000000000..5a187652fa --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_1_4-solution000003.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting var2 be {{true}} +$ Visualisation for var2 +$ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_1_4-solution000004.solution b/tests/exhaustive/autogen/gen02/expected/model_1_4-solution000004.solution new file mode 100644 index 0000000000..0678d41bf8 --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_1_4-solution000004.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting var2 be {{false, true}} +$ Visualisation for var2 +$ _ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_1_4-solution000005.solution b/tests/exhaustive/autogen/gen02/expected/model_1_4-solution000005.solution new file mode 100644 index 0000000000..73f1bfe1ac --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_1_4-solution000005.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting var2 be {{}, {false}} +$ Visualisation for var2 +$ +$ _ + diff --git a/tests/exhaustive/autogen/gen02/expected/model_1_4-solution000006.solution b/tests/exhaustive/autogen/gen02/expected/model_1_4-solution000006.solution new file mode 100644 index 0000000000..d4c4a238b9 --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_1_4-solution000006.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting var2 be {{}, {true}} +$ Visualisation for var2 +$ +$ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_1_4-solution000007.solution b/tests/exhaustive/autogen/gen02/expected/model_1_4-solution000007.solution new file mode 100644 index 0000000000..2b6a8959da --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_1_4-solution000007.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting var2 be {{false}, {true}} +$ Visualisation for var2 +$ _ +$ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_1_4-solution000008.solution b/tests/exhaustive/autogen/gen02/expected/model_1_4-solution000008.solution new file mode 100644 index 0000000000..9c15a8e4e1 --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_1_4-solution000008.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting var2 be {{}, {false, true}} +$ Visualisation for var2 +$ +$ _ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_1_4-solution000009.solution b/tests/exhaustive/autogen/gen02/expected/model_1_4-solution000009.solution new file mode 100644 index 0000000000..b2e98e56a6 --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_1_4-solution000009.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting var2 be {{false}, {false, true}} +$ Visualisation for var2 +$ _ +$ _ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_1_4-solution000010.solution b/tests/exhaustive/autogen/gen02/expected/model_1_4-solution000010.solution new file mode 100644 index 0000000000..4fc309134f --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_1_4-solution000010.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting var2 be {{false, true}, {true}} +$ Visualisation for var2 +$ _ T +$ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_1_4-solution000011.solution b/tests/exhaustive/autogen/gen02/expected/model_1_4-solution000011.solution new file mode 100644 index 0000000000..70d0f91f38 --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_1_4-solution000011.solution @@ -0,0 +1,8 @@ +language Essence 1.3 + +letting var2 be {{}, {false}, {true}} +$ Visualisation for var2 +$ +$ _ +$ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_1_4-solution000012.solution b/tests/exhaustive/autogen/gen02/expected/model_1_4-solution000012.solution new file mode 100644 index 0000000000..ebc3fe4182 --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_1_4-solution000012.solution @@ -0,0 +1,8 @@ +language Essence 1.3 + +letting var2 be {{}, {false}, {false, true}} +$ Visualisation for var2 +$ +$ _ +$ _ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_1_4-solution000013.solution b/tests/exhaustive/autogen/gen02/expected/model_1_4-solution000013.solution new file mode 100644 index 0000000000..fa4340a533 --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_1_4-solution000013.solution @@ -0,0 +1,8 @@ +language Essence 1.3 + +letting var2 be {{}, {false, true}, {true}} +$ Visualisation for var2 +$ +$ _ T +$ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_1_4-solution000014.solution b/tests/exhaustive/autogen/gen02/expected/model_1_4-solution000014.solution new file mode 100644 index 0000000000..371f28aab7 --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_1_4-solution000014.solution @@ -0,0 +1,8 @@ +language Essence 1.3 + +letting var2 be {{false}, {false, true}, {true}} +$ Visualisation for var2 +$ _ +$ _ T +$ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_1_4-solution000015.solution b/tests/exhaustive/autogen/gen02/expected/model_1_4-solution000015.solution new file mode 100644 index 0000000000..35cfa328e8 --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_1_4-solution000015.solution @@ -0,0 +1,9 @@ +language Essence 1.3 + +letting var2 be {{}, {false}, {false, true}, {true}} +$ Visualisation for var2 +$ +$ _ +$ _ T +$ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_1_4.eprime.orig b/tests/exhaustive/autogen/gen02/expected/model_1_4.eprime.orig deleted file mode 100644 index d4d7fdf24c..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_1_4.eprime.orig +++ /dev/null @@ -1,123 +0,0 @@ -language ESSENCE' 1.0 - -find var2_ExplicitVarSizeWithMarkerR5_Marker: int(0..4) -find var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker: - matrix indexed by [int(1..4)] of int(0..2) -find var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values: - matrix indexed by [int(1..4), int(1..2)] of bool -find var2_ExplicitVarSizeWithFlagsR4_Flags: matrix indexed by [int(1..4)] of bool -find var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Flags: - matrix indexed by [int(1..4), int(1..2)] of bool -find var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Values: - matrix indexed by [int(1..4), int(1..2)] of bool -branching on - [var2_ExplicitVarSizeWithFlagsR4_Flags, var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Flags, - var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Values, var2_ExplicitVarSizeWithMarkerR5_Marker, - var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker, - var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values] -such that - or([q49 <= var2_ExplicitVarSizeWithMarkerR5_Marker /\ - sum([toInt(q50 <= var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q49]) - | q50 : int(1..2)]) - >= -7 - | q49 : int(1..4)]), - and([q2 + 1 <= var2_ExplicitVarSizeWithMarkerR5_Marker -> - flatten([[var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q2]; int(1)], - [-toInt(var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q2, q8]) - | q8 : int(1..2)]; - int(1..2)]) - var2_ExplicitVarSizeWithMarkerR5_Marker -> - var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q3] = 0 /\ - and([var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q3, q10] = false - | q10 : int(1..2)]) - | q3 : int(1..4)]), - and([q4 <= var2_ExplicitVarSizeWithMarkerR5_Marker -> - (2 <= var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q4] -> - -toInt(var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q4, 1]) < - -toInt(var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q4, 2])) - | q4 : int(1..4)]), - and([q4 <= var2_ExplicitVarSizeWithMarkerR5_Marker -> - and([q6 > var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q4] -> - var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q4, q6] = false - | q6 : int(1..2)]) - | q4 : int(1..4)]), - and([var2_ExplicitVarSizeWithFlagsR4_Flags[q11 + 1] -> - flatten([flatten([[-toInt(var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Flags[q11, q21]); - int(1)], - [-toInt(var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Values[q11, q21]); - int(1)]; - int(1..2)]) - | q21 : int(1..2)]) - - and([var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Flags[q12, q23] = false - | q23 : int(1..2)]) - /\ - and([var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Values[q12, q24] = false - | q24 : int(1..2)]) - | q12 : int(1..4)]), - and([var2_ExplicitVarSizeWithFlagsR4_Flags[q13 + 1] -> var2_ExplicitVarSizeWithFlagsR4_Flags[q13] - | q13 : int(1..3)]), - and([var2_ExplicitVarSizeWithFlagsR4_Flags[q15] -> - (var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Flags[q15, 2] -> - -toInt(var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Values[q15, 1]) < - -toInt(var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Values[q15, 2])) - | q15 : int(1..4)]), - and([var2_ExplicitVarSizeWithFlagsR4_Flags[q15] -> - and([var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Flags[q15, q17] = false -> - var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Values[q15, q17] = false - | q17 : int(1..2)]) - | q15 : int(1..4)]), - and([var2_ExplicitVarSizeWithFlagsR4_Flags[q15] -> - (var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Flags[q15, 2] -> - var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Flags[q15, 1]) - | q15 : int(1..4)]), - and([var2_ExplicitVarSizeWithFlagsR4_Flags[q26] -> - or([q28 <= var2_ExplicitVarSizeWithMarkerR5_Marker /\ - (and([q30 <= var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q28] -> - or([var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Flags[q26, q32] /\ - var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Values[q26, q32] = - var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q28, q30] - | q32 : int(1..2)]) - | q30 : int(1..2)]) - /\ - and([var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Flags[q26, q34] -> - or([q36 <= var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q28] /\ - var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q28, q36] = - var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Values[q26, q34] - | q36 : int(1..2)]) - | q34 : int(1..2)])) - | q28 : int(1..4)]) - | q26 : int(1..4)]), - and([q38 <= var2_ExplicitVarSizeWithMarkerR5_Marker -> - or([var2_ExplicitVarSizeWithFlagsR4_Flags[q40] /\ - (and([var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Flags[q40, q42] -> - or([q44 <= var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q38] /\ - var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q38, q44] = - var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Values[q40, q42] - | q44 : int(1..2)]) - | q42 : int(1..2)]) - /\ - and([q46 <= var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q38] -> - or([var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Flags[q40, q48] /\ - var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Values[q40, q48] = - var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q38, q46] - | q48 : int(1..2)]) - | q46 : int(1..2)])) - | q40 : int(1..4)]) - | q38 : int(1..4)]) - diff --git a/tests/exhaustive/autogen/gen02/expected/model_2_1-solution000001.solution b/tests/exhaustive/autogen/gen02/expected/model_2_1-solution000001.solution new file mode 100644 index 0000000000..19d999ca82 --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_2_1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting var2 be {{}} diff --git a/tests/exhaustive/autogen/gen02/expected/model_2_1-solution000002.solution b/tests/exhaustive/autogen/gen02/expected/model_2_1-solution000002.solution new file mode 100644 index 0000000000..937293310f --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_2_1-solution000002.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting var2 be {{false}} +$ Visualisation for var2 +$ _ + diff --git a/tests/exhaustive/autogen/gen02/expected/model_2_1-solution000003.solution b/tests/exhaustive/autogen/gen02/expected/model_2_1-solution000003.solution new file mode 100644 index 0000000000..5a187652fa --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_2_1-solution000003.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting var2 be {{true}} +$ Visualisation for var2 +$ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_2_1-solution000004.solution b/tests/exhaustive/autogen/gen02/expected/model_2_1-solution000004.solution new file mode 100644 index 0000000000..0678d41bf8 --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_2_1-solution000004.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting var2 be {{false, true}} +$ Visualisation for var2 +$ _ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_2_1-solution000005.solution b/tests/exhaustive/autogen/gen02/expected/model_2_1-solution000005.solution new file mode 100644 index 0000000000..73f1bfe1ac --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_2_1-solution000005.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting var2 be {{}, {false}} +$ Visualisation for var2 +$ +$ _ + diff --git a/tests/exhaustive/autogen/gen02/expected/model_2_1-solution000006.solution b/tests/exhaustive/autogen/gen02/expected/model_2_1-solution000006.solution new file mode 100644 index 0000000000..d4c4a238b9 --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_2_1-solution000006.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting var2 be {{}, {true}} +$ Visualisation for var2 +$ +$ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_2_1-solution000007.solution b/tests/exhaustive/autogen/gen02/expected/model_2_1-solution000007.solution new file mode 100644 index 0000000000..9c15a8e4e1 --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_2_1-solution000007.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting var2 be {{}, {false, true}} +$ Visualisation for var2 +$ +$ _ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_2_1-solution000008.solution b/tests/exhaustive/autogen/gen02/expected/model_2_1-solution000008.solution new file mode 100644 index 0000000000..2b6a8959da --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_2_1-solution000008.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting var2 be {{false}, {true}} +$ Visualisation for var2 +$ _ +$ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_2_1-solution000009.solution b/tests/exhaustive/autogen/gen02/expected/model_2_1-solution000009.solution new file mode 100644 index 0000000000..b2e98e56a6 --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_2_1-solution000009.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting var2 be {{false}, {false, true}} +$ Visualisation for var2 +$ _ +$ _ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_2_1-solution000010.solution b/tests/exhaustive/autogen/gen02/expected/model_2_1-solution000010.solution new file mode 100644 index 0000000000..4fc309134f --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_2_1-solution000010.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting var2 be {{false, true}, {true}} +$ Visualisation for var2 +$ _ T +$ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_2_1-solution000011.solution b/tests/exhaustive/autogen/gen02/expected/model_2_1-solution000011.solution new file mode 100644 index 0000000000..70d0f91f38 --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_2_1-solution000011.solution @@ -0,0 +1,8 @@ +language Essence 1.3 + +letting var2 be {{}, {false}, {true}} +$ Visualisation for var2 +$ +$ _ +$ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_2_1-solution000012.solution b/tests/exhaustive/autogen/gen02/expected/model_2_1-solution000012.solution new file mode 100644 index 0000000000..ebc3fe4182 --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_2_1-solution000012.solution @@ -0,0 +1,8 @@ +language Essence 1.3 + +letting var2 be {{}, {false}, {false, true}} +$ Visualisation for var2 +$ +$ _ +$ _ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_2_1-solution000013.solution b/tests/exhaustive/autogen/gen02/expected/model_2_1-solution000013.solution new file mode 100644 index 0000000000..fa4340a533 --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_2_1-solution000013.solution @@ -0,0 +1,8 @@ +language Essence 1.3 + +letting var2 be {{}, {false, true}, {true}} +$ Visualisation for var2 +$ +$ _ T +$ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_2_1-solution000014.solution b/tests/exhaustive/autogen/gen02/expected/model_2_1-solution000014.solution new file mode 100644 index 0000000000..371f28aab7 --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_2_1-solution000014.solution @@ -0,0 +1,8 @@ +language Essence 1.3 + +letting var2 be {{false}, {false, true}, {true}} +$ Visualisation for var2 +$ _ +$ _ T +$ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_2_1-solution000015.solution b/tests/exhaustive/autogen/gen02/expected/model_2_1-solution000015.solution new file mode 100644 index 0000000000..35cfa328e8 --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_2_1-solution000015.solution @@ -0,0 +1,9 @@ +language Essence 1.3 + +letting var2 be {{}, {false}, {false, true}, {true}} +$ Visualisation for var2 +$ +$ _ +$ _ T +$ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_2_1.eprime.orig b/tests/exhaustive/autogen/gen02/expected/model_2_1.eprime.orig deleted file mode 100644 index f5534e4857..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_2_1.eprime.orig +++ /dev/null @@ -1,120 +0,0 @@ -language ESSENCE' 1.0 - -find var2_ExplicitVarSizeWithMarkerR4_Marker: int(0..4) -find var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Flags: - matrix indexed by [int(1..4), int(1..2)] of bool -find var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Values: - matrix indexed by [int(1..4), int(1..2)] of bool -find var2_ExplicitVarSizeWithMarkerR5_Marker: int(0..4) -find var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker: - matrix indexed by [int(1..4)] of int(0..2) -find var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values: - matrix indexed by [int(1..4), int(1..2)] of bool -branching on - [var2_ExplicitVarSizeWithMarkerR5_Marker, var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker, - var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values, var2_ExplicitVarSizeWithMarkerR4_Marker, - var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Flags, - var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Values] -such that - or([q47 <= var2_ExplicitVarSizeWithMarkerR4_Marker /\ - sum([toInt(var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Flags[q47, q48]) | q48 : int(1..2)]) - >= -7 - | q47 : int(1..4)]), - and([q2 + 1 <= var2_ExplicitVarSizeWithMarkerR4_Marker -> - flatten([flatten([[-toInt(var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Flags[q2, q10]); - int(1)], - [-toInt(var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Values[q2, q10]); - int(1)]; - int(1..2)]) - | q10 : int(1..2)]) - var2_ExplicitVarSizeWithMarkerR4_Marker -> - and([var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Flags[q3, q12] = false - | q12 : int(1..2)]) - /\ - and([var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Values[q3, q13] = false - | q13 : int(1..2)]) - | q3 : int(1..4)]), - and([q4 <= var2_ExplicitVarSizeWithMarkerR4_Marker -> - (var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Flags[q4, 2] -> - -toInt(var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Values[q4, 1]) < - -toInt(var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Values[q4, 2])) - | q4 : int(1..4)]), - and([q4 <= var2_ExplicitVarSizeWithMarkerR4_Marker -> - and([var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Flags[q4, q6] = false -> - var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Values[q4, q6] = false - | q6 : int(1..2)]) - | q4 : int(1..4)]), - and([q4 <= var2_ExplicitVarSizeWithMarkerR4_Marker -> - (var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Flags[q4, 2] -> - var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Flags[q4, 1]) - | q4 : int(1..4)]), - and([q14 + 1 <= var2_ExplicitVarSizeWithMarkerR5_Marker -> - flatten([[var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q14]; int(1)], - [-toInt(var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q14, q20]) - | q20 : int(1..2)]; - int(1..2)]) - var2_ExplicitVarSizeWithMarkerR5_Marker -> - var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q15] = 0 /\ - and([var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q15, q22] = false - | q22 : int(1..2)]) - | q15 : int(1..4)]), - and([q16 <= var2_ExplicitVarSizeWithMarkerR5_Marker -> - (2 <= var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q16] -> - -toInt(var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q16, 1]) < - -toInt(var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q16, 2])) - | q16 : int(1..4)]), - and([q16 <= var2_ExplicitVarSizeWithMarkerR5_Marker -> - and([q18 > var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q16] -> - var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q16, q18] = false - | q18 : int(1..2)]) - | q16 : int(1..4)]), - and([q24 <= var2_ExplicitVarSizeWithMarkerR5_Marker -> - or([q26 <= var2_ExplicitVarSizeWithMarkerR4_Marker /\ - (and([var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Flags[q26, q28] -> - or([q30 <= var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q24] /\ - var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q24, q30] = - var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Values[q26, q28] - | q30 : int(1..2)]) - | q28 : int(1..2)]) - /\ - and([q32 <= var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q24] -> - or([var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Flags[q26, q34] /\ - var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Values[q26, q34] = - var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q24, q32] - | q34 : int(1..2)]) - | q32 : int(1..2)])) - | q26 : int(1..4)]) - | q24 : int(1..4)]), - and([q36 <= var2_ExplicitVarSizeWithMarkerR4_Marker -> - or([q38 <= var2_ExplicitVarSizeWithMarkerR5_Marker /\ - (and([q40 <= var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q38] -> - or([var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Flags[q36, q42] /\ - var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Values[q36, q42] = - var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q38, q40] - | q42 : int(1..2)]) - | q40 : int(1..2)]) - /\ - and([var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Flags[q36, q44] -> - or([q46 <= var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q38] /\ - var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q38, q46] = - var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Values[q36, q44] - | q46 : int(1..2)]) - | q44 : int(1..2)])) - | q38 : int(1..4)]) - | q36 : int(1..4)]) - diff --git a/tests/exhaustive/autogen/gen02/expected/model_2_2-solution000001.solution b/tests/exhaustive/autogen/gen02/expected/model_2_2-solution000001.solution new file mode 100644 index 0000000000..19d999ca82 --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_2_2-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting var2 be {{}} diff --git a/tests/exhaustive/autogen/gen02/expected/model_2_2-solution000002.solution b/tests/exhaustive/autogen/gen02/expected/model_2_2-solution000002.solution new file mode 100644 index 0000000000..937293310f --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_2_2-solution000002.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting var2 be {{false}} +$ Visualisation for var2 +$ _ + diff --git a/tests/exhaustive/autogen/gen02/expected/model_2_2-solution000003.solution b/tests/exhaustive/autogen/gen02/expected/model_2_2-solution000003.solution new file mode 100644 index 0000000000..5a187652fa --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_2_2-solution000003.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting var2 be {{true}} +$ Visualisation for var2 +$ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_2_2-solution000004.solution b/tests/exhaustive/autogen/gen02/expected/model_2_2-solution000004.solution new file mode 100644 index 0000000000..0678d41bf8 --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_2_2-solution000004.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting var2 be {{false, true}} +$ Visualisation for var2 +$ _ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_2_2-solution000005.solution b/tests/exhaustive/autogen/gen02/expected/model_2_2-solution000005.solution new file mode 100644 index 0000000000..73f1bfe1ac --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_2_2-solution000005.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting var2 be {{}, {false}} +$ Visualisation for var2 +$ +$ _ + diff --git a/tests/exhaustive/autogen/gen02/expected/model_2_2-solution000006.solution b/tests/exhaustive/autogen/gen02/expected/model_2_2-solution000006.solution new file mode 100644 index 0000000000..d4c4a238b9 --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_2_2-solution000006.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting var2 be {{}, {true}} +$ Visualisation for var2 +$ +$ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_2_2-solution000007.solution b/tests/exhaustive/autogen/gen02/expected/model_2_2-solution000007.solution new file mode 100644 index 0000000000..2b6a8959da --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_2_2-solution000007.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting var2 be {{false}, {true}} +$ Visualisation for var2 +$ _ +$ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_2_2-solution000008.solution b/tests/exhaustive/autogen/gen02/expected/model_2_2-solution000008.solution new file mode 100644 index 0000000000..9c15a8e4e1 --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_2_2-solution000008.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting var2 be {{}, {false, true}} +$ Visualisation for var2 +$ +$ _ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_2_2-solution000009.solution b/tests/exhaustive/autogen/gen02/expected/model_2_2-solution000009.solution new file mode 100644 index 0000000000..b2e98e56a6 --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_2_2-solution000009.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting var2 be {{false}, {false, true}} +$ Visualisation for var2 +$ _ +$ _ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_2_2-solution000010.solution b/tests/exhaustive/autogen/gen02/expected/model_2_2-solution000010.solution new file mode 100644 index 0000000000..4fc309134f --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_2_2-solution000010.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting var2 be {{false, true}, {true}} +$ Visualisation for var2 +$ _ T +$ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_2_2-solution000011.solution b/tests/exhaustive/autogen/gen02/expected/model_2_2-solution000011.solution new file mode 100644 index 0000000000..70d0f91f38 --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_2_2-solution000011.solution @@ -0,0 +1,8 @@ +language Essence 1.3 + +letting var2 be {{}, {false}, {true}} +$ Visualisation for var2 +$ +$ _ +$ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_2_2-solution000012.solution b/tests/exhaustive/autogen/gen02/expected/model_2_2-solution000012.solution new file mode 100644 index 0000000000..ebc3fe4182 --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_2_2-solution000012.solution @@ -0,0 +1,8 @@ +language Essence 1.3 + +letting var2 be {{}, {false}, {false, true}} +$ Visualisation for var2 +$ +$ _ +$ _ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_2_2-solution000013.solution b/tests/exhaustive/autogen/gen02/expected/model_2_2-solution000013.solution new file mode 100644 index 0000000000..fa4340a533 --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_2_2-solution000013.solution @@ -0,0 +1,8 @@ +language Essence 1.3 + +letting var2 be {{}, {false, true}, {true}} +$ Visualisation for var2 +$ +$ _ T +$ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_2_2-solution000014.solution b/tests/exhaustive/autogen/gen02/expected/model_2_2-solution000014.solution new file mode 100644 index 0000000000..371f28aab7 --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_2_2-solution000014.solution @@ -0,0 +1,8 @@ +language Essence 1.3 + +letting var2 be {{false}, {false, true}, {true}} +$ Visualisation for var2 +$ _ +$ _ T +$ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_2_2-solution000015.solution b/tests/exhaustive/autogen/gen02/expected/model_2_2-solution000015.solution new file mode 100644 index 0000000000..35cfa328e8 --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_2_2-solution000015.solution @@ -0,0 +1,9 @@ +language Essence 1.3 + +letting var2 be {{}, {false}, {false, true}, {true}} +$ Visualisation for var2 +$ +$ _ +$ _ T +$ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_2_2.eprime b/tests/exhaustive/autogen/gen02/expected/model_2_2.eprime new file mode 100644 index 0000000000..c1cfaf2da7 --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_2_2.eprime @@ -0,0 +1,53 @@ +language ESSENCE' 1.0 + +find var2_ExplicitVarSizeWithMarkerR4_Marker: int(0..4) +find var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Flags: + matrix indexed by [int(1..4), int(1..2)] of bool +find var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Values: + matrix indexed by [int(1..4), int(1..2)] of bool +branching on + [var2_ExplicitVarSizeWithMarkerR4_Marker, var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Flags, + var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Values] +such that + or([q14 <= var2_ExplicitVarSizeWithMarkerR4_Marker /\ + sum([toInt(var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Flags[q14, q15]) | q15 : int(1..2)]) + >= -7 + | q14 : int(1..4)]), + and([q2 + 1 <= var2_ExplicitVarSizeWithMarkerR4_Marker -> + flatten([flatten([[-toInt(var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Flags[q2, q10]); + int(1)], + [-toInt(var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Values[q2, q10]); + int(1)]; + int(1..2)]) + | q10 : int(1..2)]) + var2_ExplicitVarSizeWithMarkerR4_Marker -> + and([var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Flags[q3, q12] = false + | q12 : int(1..2)]) + /\ + and([var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Values[q3, q13] = false + | q13 : int(1..2)]) + | q3 : int(1..4)]), + and([q4 <= var2_ExplicitVarSizeWithMarkerR4_Marker -> + (var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Flags[q4, 2] -> + -toInt(var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Values[q4, 1]) < + -toInt(var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Values[q4, 2])) + | q4 : int(1..4)]), + and([q4 <= var2_ExplicitVarSizeWithMarkerR4_Marker -> + and([var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Flags[q4, q6] = false -> + var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Values[q4, q6] = false + | q6 : int(1..2)]) + | q4 : int(1..4)]), + and([q4 <= var2_ExplicitVarSizeWithMarkerR4_Marker -> + (var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Flags[q4, 2] -> + var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Flags[q4, 1]) + | q4 : int(1..4)]) + diff --git a/tests/exhaustive/autogen/gen02/expected/model_2_3-solution000001.solution b/tests/exhaustive/autogen/gen02/expected/model_2_3-solution000001.solution new file mode 100644 index 0000000000..19d999ca82 --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_2_3-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting var2 be {{}} diff --git a/tests/exhaustive/autogen/gen02/expected/model_2_3-solution000002.solution b/tests/exhaustive/autogen/gen02/expected/model_2_3-solution000002.solution new file mode 100644 index 0000000000..937293310f --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_2_3-solution000002.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting var2 be {{false}} +$ Visualisation for var2 +$ _ + diff --git a/tests/exhaustive/autogen/gen02/expected/model_2_3-solution000003.solution b/tests/exhaustive/autogen/gen02/expected/model_2_3-solution000003.solution new file mode 100644 index 0000000000..5a187652fa --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_2_3-solution000003.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting var2 be {{true}} +$ Visualisation for var2 +$ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_2_3-solution000004.solution b/tests/exhaustive/autogen/gen02/expected/model_2_3-solution000004.solution new file mode 100644 index 0000000000..0678d41bf8 --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_2_3-solution000004.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting var2 be {{false, true}} +$ Visualisation for var2 +$ _ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_2_3-solution000005.solution b/tests/exhaustive/autogen/gen02/expected/model_2_3-solution000005.solution new file mode 100644 index 0000000000..73f1bfe1ac --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_2_3-solution000005.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting var2 be {{}, {false}} +$ Visualisation for var2 +$ +$ _ + diff --git a/tests/exhaustive/autogen/gen02/expected/model_2_3-solution000006.solution b/tests/exhaustive/autogen/gen02/expected/model_2_3-solution000006.solution new file mode 100644 index 0000000000..d4c4a238b9 --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_2_3-solution000006.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting var2 be {{}, {true}} +$ Visualisation for var2 +$ +$ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_2_3-solution000007.solution b/tests/exhaustive/autogen/gen02/expected/model_2_3-solution000007.solution new file mode 100644 index 0000000000..9c15a8e4e1 --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_2_3-solution000007.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting var2 be {{}, {false, true}} +$ Visualisation for var2 +$ +$ _ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_2_3-solution000008.solution b/tests/exhaustive/autogen/gen02/expected/model_2_3-solution000008.solution new file mode 100644 index 0000000000..2b6a8959da --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_2_3-solution000008.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting var2 be {{false}, {true}} +$ Visualisation for var2 +$ _ +$ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_2_3-solution000009.solution b/tests/exhaustive/autogen/gen02/expected/model_2_3-solution000009.solution new file mode 100644 index 0000000000..b2e98e56a6 --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_2_3-solution000009.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting var2 be {{false}, {false, true}} +$ Visualisation for var2 +$ _ +$ _ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_2_3-solution000010.solution b/tests/exhaustive/autogen/gen02/expected/model_2_3-solution000010.solution new file mode 100644 index 0000000000..4fc309134f --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_2_3-solution000010.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting var2 be {{false, true}, {true}} +$ Visualisation for var2 +$ _ T +$ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_2_3-solution000011.solution b/tests/exhaustive/autogen/gen02/expected/model_2_3-solution000011.solution new file mode 100644 index 0000000000..70d0f91f38 --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_2_3-solution000011.solution @@ -0,0 +1,8 @@ +language Essence 1.3 + +letting var2 be {{}, {false}, {true}} +$ Visualisation for var2 +$ +$ _ +$ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_2_3-solution000012.solution b/tests/exhaustive/autogen/gen02/expected/model_2_3-solution000012.solution new file mode 100644 index 0000000000..ebc3fe4182 --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_2_3-solution000012.solution @@ -0,0 +1,8 @@ +language Essence 1.3 + +letting var2 be {{}, {false}, {false, true}} +$ Visualisation for var2 +$ +$ _ +$ _ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_2_3-solution000013.solution b/tests/exhaustive/autogen/gen02/expected/model_2_3-solution000013.solution new file mode 100644 index 0000000000..fa4340a533 --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_2_3-solution000013.solution @@ -0,0 +1,8 @@ +language Essence 1.3 + +letting var2 be {{}, {false, true}, {true}} +$ Visualisation for var2 +$ +$ _ T +$ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_2_3-solution000014.solution b/tests/exhaustive/autogen/gen02/expected/model_2_3-solution000014.solution new file mode 100644 index 0000000000..371f28aab7 --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_2_3-solution000014.solution @@ -0,0 +1,8 @@ +language Essence 1.3 + +letting var2 be {{false}, {false, true}, {true}} +$ Visualisation for var2 +$ _ +$ _ T +$ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_2_3-solution000015.solution b/tests/exhaustive/autogen/gen02/expected/model_2_3-solution000015.solution new file mode 100644 index 0000000000..35cfa328e8 --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_2_3-solution000015.solution @@ -0,0 +1,9 @@ +language Essence 1.3 + +letting var2 be {{}, {false}, {false, true}, {true}} +$ Visualisation for var2 +$ +$ _ +$ _ T +$ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_2_3.eprime.orig b/tests/exhaustive/autogen/gen02/expected/model_2_3.eprime.orig deleted file mode 100644 index 055cdc557c..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_2_3.eprime.orig +++ /dev/null @@ -1,121 +0,0 @@ -language ESSENCE' 1.0 - -find var2_ExplicitVarSizeWithMarkerR4_Marker: int(0..4) -find var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Flags: - matrix indexed by [int(1..4), int(1..2)] of bool -find var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Values: - matrix indexed by [int(1..4), int(1..2)] of bool -find var2_ExplicitVarSizeWithFlagsR5_Flags: matrix indexed by [int(1..4)] of bool -find var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Marker: matrix indexed by [int(1..4)] of int(0..2) -find var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Values: - matrix indexed by [int(1..4), int(1..2)] of bool -branching on - [var2_ExplicitVarSizeWithFlagsR5_Flags, var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Marker, - var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Values, var2_ExplicitVarSizeWithMarkerR4_Marker, - var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Flags, - var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Values] -such that - or([q49 <= var2_ExplicitVarSizeWithMarkerR4_Marker /\ - sum([toInt(var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Flags[q49, q50]) | q50 : int(1..2)]) - >= -7 - | q49 : int(1..4)]), - and([q2 + 1 <= var2_ExplicitVarSizeWithMarkerR4_Marker -> - flatten([flatten([[-toInt(var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Flags[q2, q10]); - int(1)], - [-toInt(var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Values[q2, q10]); - int(1)]; - int(1..2)]) - | q10 : int(1..2)]) - var2_ExplicitVarSizeWithMarkerR4_Marker -> - and([var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Flags[q3, q12] = false - | q12 : int(1..2)]) - /\ - and([var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Values[q3, q13] = false - | q13 : int(1..2)]) - | q3 : int(1..4)]), - and([q4 <= var2_ExplicitVarSizeWithMarkerR4_Marker -> - (var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Flags[q4, 2] -> - -toInt(var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Values[q4, 1]) < - -toInt(var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Values[q4, 2])) - | q4 : int(1..4)]), - and([q4 <= var2_ExplicitVarSizeWithMarkerR4_Marker -> - and([var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Flags[q4, q6] = false -> - var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Values[q4, q6] = false - | q6 : int(1..2)]) - | q4 : int(1..4)]), - and([q4 <= var2_ExplicitVarSizeWithMarkerR4_Marker -> - (var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Flags[q4, 2] -> - var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Flags[q4, 1]) - | q4 : int(1..4)]), - and([var2_ExplicitVarSizeWithFlagsR5_Flags[q14 + 1] -> - flatten([[var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Marker[q14]; int(1)], - [-toInt(var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Values[q14, q22]) - | q22 : int(1..2)]; - int(1..2)]) - - var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Marker[q15] = 0 /\ - and([var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Values[q15, q24] = false - | q24 : int(1..2)]) - | q15 : int(1..4)]), - and([var2_ExplicitVarSizeWithFlagsR5_Flags[q16 + 1] -> var2_ExplicitVarSizeWithFlagsR5_Flags[q16] - | q16 : int(1..3)]), - and([var2_ExplicitVarSizeWithFlagsR5_Flags[q18] -> - (2 <= var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Marker[q18] -> - -toInt(var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Values[q18, 1]) < - -toInt(var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Values[q18, 2])) - | q18 : int(1..4)]), - and([var2_ExplicitVarSizeWithFlagsR5_Flags[q18] -> - and([q20 > var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Marker[q18] -> - var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Values[q18, q20] = false - | q20 : int(1..2)]) - | q18 : int(1..4)]), - and([var2_ExplicitVarSizeWithFlagsR5_Flags[q26] -> - or([q28 <= var2_ExplicitVarSizeWithMarkerR4_Marker /\ - (and([var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Flags[q28, q30] -> - or([q32 <= var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Marker[q26] /\ - var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Values[q26, q32] = - var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Values[q28, q30] - | q32 : int(1..2)]) - | q30 : int(1..2)]) - /\ - and([q34 <= var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Marker[q26] -> - or([var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Flags[q28, q36] /\ - var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Values[q28, q36] = - var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Values[q26, q34] - | q36 : int(1..2)]) - | q34 : int(1..2)])) - | q28 : int(1..4)]) - | q26 : int(1..4)]), - and([q38 <= var2_ExplicitVarSizeWithMarkerR4_Marker -> - or([var2_ExplicitVarSizeWithFlagsR5_Flags[q40] /\ - (and([q42 <= var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Marker[q40] -> - or([var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Flags[q38, q44] /\ - var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Values[q38, q44] = - var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Values[q40, q42] - | q44 : int(1..2)]) - | q42 : int(1..2)]) - /\ - and([var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Flags[q38, q46] -> - or([q48 <= var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Marker[q40] /\ - var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Values[q40, q48] = - var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Values[q38, q46] - | q48 : int(1..2)]) - | q46 : int(1..2)])) - | q40 : int(1..4)]) - | q38 : int(1..4)]) - diff --git a/tests/exhaustive/autogen/gen02/expected/model_2_4-solution000001.solution b/tests/exhaustive/autogen/gen02/expected/model_2_4-solution000001.solution new file mode 100644 index 0000000000..19d999ca82 --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_2_4-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting var2 be {{}} diff --git a/tests/exhaustive/autogen/gen02/expected/model_2_4-solution000002.solution b/tests/exhaustive/autogen/gen02/expected/model_2_4-solution000002.solution new file mode 100644 index 0000000000..937293310f --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_2_4-solution000002.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting var2 be {{false}} +$ Visualisation for var2 +$ _ + diff --git a/tests/exhaustive/autogen/gen02/expected/model_2_4-solution000003.solution b/tests/exhaustive/autogen/gen02/expected/model_2_4-solution000003.solution new file mode 100644 index 0000000000..5a187652fa --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_2_4-solution000003.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting var2 be {{true}} +$ Visualisation for var2 +$ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_2_4-solution000004.solution b/tests/exhaustive/autogen/gen02/expected/model_2_4-solution000004.solution new file mode 100644 index 0000000000..0678d41bf8 --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_2_4-solution000004.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting var2 be {{false, true}} +$ Visualisation for var2 +$ _ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_2_4-solution000005.solution b/tests/exhaustive/autogen/gen02/expected/model_2_4-solution000005.solution new file mode 100644 index 0000000000..73f1bfe1ac --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_2_4-solution000005.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting var2 be {{}, {false}} +$ Visualisation for var2 +$ +$ _ + diff --git a/tests/exhaustive/autogen/gen02/expected/model_2_4-solution000006.solution b/tests/exhaustive/autogen/gen02/expected/model_2_4-solution000006.solution new file mode 100644 index 0000000000..d4c4a238b9 --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_2_4-solution000006.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting var2 be {{}, {true}} +$ Visualisation for var2 +$ +$ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_2_4-solution000007.solution b/tests/exhaustive/autogen/gen02/expected/model_2_4-solution000007.solution new file mode 100644 index 0000000000..2b6a8959da --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_2_4-solution000007.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting var2 be {{false}, {true}} +$ Visualisation for var2 +$ _ +$ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_2_4-solution000008.solution b/tests/exhaustive/autogen/gen02/expected/model_2_4-solution000008.solution new file mode 100644 index 0000000000..9c15a8e4e1 --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_2_4-solution000008.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting var2 be {{}, {false, true}} +$ Visualisation for var2 +$ +$ _ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_2_4-solution000009.solution b/tests/exhaustive/autogen/gen02/expected/model_2_4-solution000009.solution new file mode 100644 index 0000000000..b2e98e56a6 --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_2_4-solution000009.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting var2 be {{false}, {false, true}} +$ Visualisation for var2 +$ _ +$ _ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_2_4-solution000010.solution b/tests/exhaustive/autogen/gen02/expected/model_2_4-solution000010.solution new file mode 100644 index 0000000000..4fc309134f --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_2_4-solution000010.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting var2 be {{false, true}, {true}} +$ Visualisation for var2 +$ _ T +$ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_2_4-solution000011.solution b/tests/exhaustive/autogen/gen02/expected/model_2_4-solution000011.solution new file mode 100644 index 0000000000..70d0f91f38 --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_2_4-solution000011.solution @@ -0,0 +1,8 @@ +language Essence 1.3 + +letting var2 be {{}, {false}, {true}} +$ Visualisation for var2 +$ +$ _ +$ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_2_4-solution000012.solution b/tests/exhaustive/autogen/gen02/expected/model_2_4-solution000012.solution new file mode 100644 index 0000000000..ebc3fe4182 --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_2_4-solution000012.solution @@ -0,0 +1,8 @@ +language Essence 1.3 + +letting var2 be {{}, {false}, {false, true}} +$ Visualisation for var2 +$ +$ _ +$ _ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_2_4-solution000013.solution b/tests/exhaustive/autogen/gen02/expected/model_2_4-solution000013.solution new file mode 100644 index 0000000000..fa4340a533 --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_2_4-solution000013.solution @@ -0,0 +1,8 @@ +language Essence 1.3 + +letting var2 be {{}, {false, true}, {true}} +$ Visualisation for var2 +$ +$ _ T +$ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_2_4-solution000014.solution b/tests/exhaustive/autogen/gen02/expected/model_2_4-solution000014.solution new file mode 100644 index 0000000000..371f28aab7 --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_2_4-solution000014.solution @@ -0,0 +1,8 @@ +language Essence 1.3 + +letting var2 be {{false}, {false, true}, {true}} +$ Visualisation for var2 +$ _ +$ _ T +$ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_2_4-solution000015.solution b/tests/exhaustive/autogen/gen02/expected/model_2_4-solution000015.solution new file mode 100644 index 0000000000..35cfa328e8 --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_2_4-solution000015.solution @@ -0,0 +1,9 @@ +language Essence 1.3 + +letting var2 be {{}, {false}, {false, true}, {true}} +$ Visualisation for var2 +$ +$ _ +$ _ T +$ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_2_4.eprime b/tests/exhaustive/autogen/gen02/expected/model_2_4.eprime new file mode 100644 index 0000000000..1c6891d59e --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_2_4.eprime @@ -0,0 +1,121 @@ +language ESSENCE' 1.0 + +find var2_ExplicitVarSizeWithMarkerR4_Marker: int(0..4) +find var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Flags: + matrix indexed by [int(1..4), int(1..2)] of bool +find var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Values: + matrix indexed by [int(1..4), int(1..2)] of bool +find var2_ExplicitVarSizeWithFlagsR4_Flags: matrix indexed by [int(1..4)] of bool +find var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Flags: + matrix indexed by [int(1..4), int(1..2)] of bool +find var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Values: + matrix indexed by [int(1..4), int(1..2)] of bool +branching on + [var2_ExplicitVarSizeWithFlagsR4_Flags, var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Flags, + var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Values, var2_ExplicitVarSizeWithMarkerR4_Marker, + var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Flags, + var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Values] +such that + or([q44 <= var2_ExplicitVarSizeWithMarkerR4_Marker /\ + sum([toInt(var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Flags[q44, q45]) | q45 : int(1..2)]) + >= -7 + | q44 : int(1..4)]), + and([q2 + 1 <= var2_ExplicitVarSizeWithMarkerR4_Marker -> + flatten([flatten([[-toInt(var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Flags[q2, q10]); + int(1)], + [-toInt(var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Values[q2, q10]); + int(1)]; + int(1..2)]) + | q10 : int(1..2)]) + var2_ExplicitVarSizeWithMarkerR4_Marker -> + and([var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Flags[q3, q12] = false + | q12 : int(1..2)]) + /\ + and([var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Values[q3, q13] = false + | q13 : int(1..2)]) + | q3 : int(1..4)]), + and([q4 <= var2_ExplicitVarSizeWithMarkerR4_Marker -> + (var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Flags[q4, 2] -> + -toInt(var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Values[q4, 1]) < + -toInt(var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Values[q4, 2])) + | q4 : int(1..4)]), + and([q4 <= var2_ExplicitVarSizeWithMarkerR4_Marker -> + and([var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Flags[q4, q6] = false -> + var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Values[q4, q6] = false + | q6 : int(1..2)]) + | q4 : int(1..4)]), + and([q4 <= var2_ExplicitVarSizeWithMarkerR4_Marker -> + (var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Flags[q4, 2] -> + var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Flags[q4, 1]) + | q4 : int(1..4)]), + and([var2_ExplicitVarSizeWithFlagsR4_Flags[q14 + 1] -> + flatten([flatten([[-toInt(var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Flags[q14, q24]); + int(1)], + [-toInt(var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Values[q14, q24]); + int(1)]; + int(1..2)]) + | q24 : int(1..2)]) + + and([var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Flags[q15, q26] = false + | q26 : int(1..2)]) + /\ + and([var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Values[q15, q27] = false + | q27 : int(1..2)]) + | q15 : int(1..4)]), + and([var2_ExplicitVarSizeWithFlagsR4_Flags[q16 + 1] -> var2_ExplicitVarSizeWithFlagsR4_Flags[q16] + | q16 : int(1..3)]), + and([var2_ExplicitVarSizeWithFlagsR4_Flags[q18] -> + (var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Flags[q18, 2] -> + -toInt(var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Values[q18, 1]) < + -toInt(var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Values[q18, 2])) + | q18 : int(1..4)]), + and([var2_ExplicitVarSizeWithFlagsR4_Flags[q18] -> + and([var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Flags[q18, q20] = false -> + var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Values[q18, q20] = false + | q20 : int(1..2)]) + | q18 : int(1..4)]), + and([var2_ExplicitVarSizeWithFlagsR4_Flags[q18] -> + (var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Flags[q18, 2] -> + var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Flags[q18, 1]) + | q18 : int(1..4)]), + and([var2_ExplicitVarSizeWithFlagsR4_Flags[q29] -> + or([q31 <= var2_ExplicitVarSizeWithMarkerR4_Marker /\ + (and([var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Flags[q31, q32] = + var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Flags[q29, q32] + | q32 : int(1..2)]) + /\ + and([var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Values[q31, q34] = + var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Values[q29, q34] + | q34 : int(1..2)])) + | q31 : int(1..4)]) + | q29 : int(1..4)]), + and([q37 <= var2_ExplicitVarSizeWithMarkerR4_Marker -> + or([var2_ExplicitVarSizeWithFlagsR4_Flags[q39] /\ + (and([var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Flags[q39, q40] = + var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Flags[q37, q40] + | q40 : int(1..2)]) + /\ + and([var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Values[q39, q42] = + var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Values[q37, q42] + | q42 : int(1..2)])) + | q39 : int(1..4)]) + | q37 : int(1..4)]) + diff --git a/tests/exhaustive/autogen/gen02/expected/model_3_1-solution000001.solution b/tests/exhaustive/autogen/gen02/expected/model_3_1-solution000001.solution new file mode 100644 index 0000000000..19d999ca82 --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_3_1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting var2 be {{}} diff --git a/tests/exhaustive/autogen/gen02/expected/model_3_1-solution000002.solution b/tests/exhaustive/autogen/gen02/expected/model_3_1-solution000002.solution new file mode 100644 index 0000000000..937293310f --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_3_1-solution000002.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting var2 be {{false}} +$ Visualisation for var2 +$ _ + diff --git a/tests/exhaustive/autogen/gen02/expected/model_3_1-solution000003.solution b/tests/exhaustive/autogen/gen02/expected/model_3_1-solution000003.solution new file mode 100644 index 0000000000..5a187652fa --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_3_1-solution000003.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting var2 be {{true}} +$ Visualisation for var2 +$ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_3_1-solution000004.solution b/tests/exhaustive/autogen/gen02/expected/model_3_1-solution000004.solution new file mode 100644 index 0000000000..0678d41bf8 --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_3_1-solution000004.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting var2 be {{false, true}} +$ Visualisation for var2 +$ _ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_3_1-solution000005.solution b/tests/exhaustive/autogen/gen02/expected/model_3_1-solution000005.solution new file mode 100644 index 0000000000..73f1bfe1ac --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_3_1-solution000005.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting var2 be {{}, {false}} +$ Visualisation for var2 +$ +$ _ + diff --git a/tests/exhaustive/autogen/gen02/expected/model_3_1-solution000006.solution b/tests/exhaustive/autogen/gen02/expected/model_3_1-solution000006.solution new file mode 100644 index 0000000000..d4c4a238b9 --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_3_1-solution000006.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting var2 be {{}, {true}} +$ Visualisation for var2 +$ +$ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_3_1-solution000007.solution b/tests/exhaustive/autogen/gen02/expected/model_3_1-solution000007.solution new file mode 100644 index 0000000000..9c15a8e4e1 --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_3_1-solution000007.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting var2 be {{}, {false, true}} +$ Visualisation for var2 +$ +$ _ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_3_1-solution000008.solution b/tests/exhaustive/autogen/gen02/expected/model_3_1-solution000008.solution new file mode 100644 index 0000000000..2b6a8959da --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_3_1-solution000008.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting var2 be {{false}, {true}} +$ Visualisation for var2 +$ _ +$ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_3_1-solution000009.solution b/tests/exhaustive/autogen/gen02/expected/model_3_1-solution000009.solution new file mode 100644 index 0000000000..b2e98e56a6 --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_3_1-solution000009.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting var2 be {{false}, {false, true}} +$ Visualisation for var2 +$ _ +$ _ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_3_1-solution000010.solution b/tests/exhaustive/autogen/gen02/expected/model_3_1-solution000010.solution new file mode 100644 index 0000000000..4fc309134f --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_3_1-solution000010.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting var2 be {{false, true}, {true}} +$ Visualisation for var2 +$ _ T +$ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_3_1-solution000011.solution b/tests/exhaustive/autogen/gen02/expected/model_3_1-solution000011.solution new file mode 100644 index 0000000000..70d0f91f38 --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_3_1-solution000011.solution @@ -0,0 +1,8 @@ +language Essence 1.3 + +letting var2 be {{}, {false}, {true}} +$ Visualisation for var2 +$ +$ _ +$ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_3_1-solution000012.solution b/tests/exhaustive/autogen/gen02/expected/model_3_1-solution000012.solution new file mode 100644 index 0000000000..ebc3fe4182 --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_3_1-solution000012.solution @@ -0,0 +1,8 @@ +language Essence 1.3 + +letting var2 be {{}, {false}, {false, true}} +$ Visualisation for var2 +$ +$ _ +$ _ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_3_1-solution000013.solution b/tests/exhaustive/autogen/gen02/expected/model_3_1-solution000013.solution new file mode 100644 index 0000000000..fa4340a533 --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_3_1-solution000013.solution @@ -0,0 +1,8 @@ +language Essence 1.3 + +letting var2 be {{}, {false, true}, {true}} +$ Visualisation for var2 +$ +$ _ T +$ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_3_1-solution000014.solution b/tests/exhaustive/autogen/gen02/expected/model_3_1-solution000014.solution new file mode 100644 index 0000000000..371f28aab7 --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_3_1-solution000014.solution @@ -0,0 +1,8 @@ +language Essence 1.3 + +letting var2 be {{false}, {false, true}, {true}} +$ Visualisation for var2 +$ _ +$ _ T +$ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_3_1-solution000015.solution b/tests/exhaustive/autogen/gen02/expected/model_3_1-solution000015.solution new file mode 100644 index 0000000000..35cfa328e8 --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_3_1-solution000015.solution @@ -0,0 +1,9 @@ +language Essence 1.3 + +letting var2 be {{}, {false}, {false, true}, {true}} +$ Visualisation for var2 +$ +$ _ +$ _ T +$ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_3_1.eprime.orig b/tests/exhaustive/autogen/gen02/expected/model_3_1.eprime.orig deleted file mode 100644 index d6d73bb27b..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_3_1.eprime.orig +++ /dev/null @@ -1,96 +0,0 @@ -language ESSENCE' 1.0 - -find var2_ExplicitVarSizeWithFlagsR5_Flags: matrix indexed by [int(1..4)] of bool -find var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Marker: matrix indexed by [int(1..4)] of int(0..2) -find var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Values: - matrix indexed by [int(1..4), int(1..2)] of bool -find var2_ExplicitVarSizeWithMarkerR5_Marker: int(0..4) -find var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker: - matrix indexed by [int(1..4)] of int(0..2) -find var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values: - matrix indexed by [int(1..4), int(1..2)] of bool -branching on - [var2_ExplicitVarSizeWithMarkerR5_Marker, var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker, - var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values, var2_ExplicitVarSizeWithFlagsR5_Flags, - var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Marker, - var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Values] -such that - or([var2_ExplicitVarSizeWithFlagsR5_Flags[q34] /\ - sum([toInt(q35 <= var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Marker[q34]) - | q35 : int(1..2)]) - >= -7 - | q34 : int(1..4)]), - and([var2_ExplicitVarSizeWithFlagsR5_Flags[q2 + 1] -> - flatten([[var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Marker[q2]; int(1)], - [-toInt(var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Values[q2, q10]) - | q10 : int(1..2)]; - int(1..2)]) - - var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Marker[q3] = 0 /\ - and([var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Values[q3, q12] = false - | q12 : int(1..2)]) - | q3 : int(1..4)]), - and([var2_ExplicitVarSizeWithFlagsR5_Flags[q4 + 1] -> var2_ExplicitVarSizeWithFlagsR5_Flags[q4] | q4 : int(1..3)]), - and([var2_ExplicitVarSizeWithFlagsR5_Flags[q6] -> - (2 <= var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Marker[q6] -> - -toInt(var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Values[q6, 1]) < - -toInt(var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Values[q6, 2])) - | q6 : int(1..4)]), - and([var2_ExplicitVarSizeWithFlagsR5_Flags[q6] -> - and([q8 > var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Marker[q6] -> - var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Values[q6, q8] = false - | q8 : int(1..2)]) - | q6 : int(1..4)]), - and([q13 + 1 <= var2_ExplicitVarSizeWithMarkerR5_Marker -> - flatten([[var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q13]; int(1)], - [-toInt(var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q13, q19]) - | q19 : int(1..2)]; - int(1..2)]) - var2_ExplicitVarSizeWithMarkerR5_Marker -> - var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q14] = 0 /\ - and([var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q14, q21] = false - | q21 : int(1..2)]) - | q14 : int(1..4)]), - and([q15 <= var2_ExplicitVarSizeWithMarkerR5_Marker -> - (2 <= var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q15] -> - -toInt(var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q15, 1]) < - -toInt(var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q15, 2])) - | q15 : int(1..4)]), - and([q15 <= var2_ExplicitVarSizeWithMarkerR5_Marker -> - and([q17 > var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q15] -> - var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q15, q17] = false - | q17 : int(1..2)]) - | q15 : int(1..4)]), - and([q23 <= var2_ExplicitVarSizeWithMarkerR5_Marker -> - or([var2_ExplicitVarSizeWithFlagsR5_Flags[q25] /\ - (var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Marker[q25] = - var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q23] - /\ - and([var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Values[q25, q26] = - var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q23, q26] - | q26 : int(1..2)])) - | q25 : int(1..4)]) - | q23 : int(1..4)]), - and([var2_ExplicitVarSizeWithFlagsR5_Flags[q29] -> - or([q31 <= var2_ExplicitVarSizeWithMarkerR5_Marker /\ - (var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q31] = - var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Marker[q29] - /\ - and([var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q31, q32] = - var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Values[q29, q32] - | q32 : int(1..2)])) - | q31 : int(1..4)]) - | q29 : int(1..4)]) - diff --git a/tests/exhaustive/autogen/gen02/expected/model_3_2-solution000001.solution b/tests/exhaustive/autogen/gen02/expected/model_3_2-solution000001.solution new file mode 100644 index 0000000000..19d999ca82 --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_3_2-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting var2 be {{}} diff --git a/tests/exhaustive/autogen/gen02/expected/model_3_2-solution000002.solution b/tests/exhaustive/autogen/gen02/expected/model_3_2-solution000002.solution new file mode 100644 index 0000000000..937293310f --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_3_2-solution000002.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting var2 be {{false}} +$ Visualisation for var2 +$ _ + diff --git a/tests/exhaustive/autogen/gen02/expected/model_3_2-solution000003.solution b/tests/exhaustive/autogen/gen02/expected/model_3_2-solution000003.solution new file mode 100644 index 0000000000..5a187652fa --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_3_2-solution000003.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting var2 be {{true}} +$ Visualisation for var2 +$ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_3_2-solution000004.solution b/tests/exhaustive/autogen/gen02/expected/model_3_2-solution000004.solution new file mode 100644 index 0000000000..0678d41bf8 --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_3_2-solution000004.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting var2 be {{false, true}} +$ Visualisation for var2 +$ _ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_3_2-solution000005.solution b/tests/exhaustive/autogen/gen02/expected/model_3_2-solution000005.solution new file mode 100644 index 0000000000..73f1bfe1ac --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_3_2-solution000005.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting var2 be {{}, {false}} +$ Visualisation for var2 +$ +$ _ + diff --git a/tests/exhaustive/autogen/gen02/expected/model_3_2-solution000006.solution b/tests/exhaustive/autogen/gen02/expected/model_3_2-solution000006.solution new file mode 100644 index 0000000000..d4c4a238b9 --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_3_2-solution000006.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting var2 be {{}, {true}} +$ Visualisation for var2 +$ +$ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_3_2-solution000007.solution b/tests/exhaustive/autogen/gen02/expected/model_3_2-solution000007.solution new file mode 100644 index 0000000000..2b6a8959da --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_3_2-solution000007.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting var2 be {{false}, {true}} +$ Visualisation for var2 +$ _ +$ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_3_2-solution000008.solution b/tests/exhaustive/autogen/gen02/expected/model_3_2-solution000008.solution new file mode 100644 index 0000000000..9c15a8e4e1 --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_3_2-solution000008.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting var2 be {{}, {false, true}} +$ Visualisation for var2 +$ +$ _ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_3_2-solution000009.solution b/tests/exhaustive/autogen/gen02/expected/model_3_2-solution000009.solution new file mode 100644 index 0000000000..b2e98e56a6 --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_3_2-solution000009.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting var2 be {{false}, {false, true}} +$ Visualisation for var2 +$ _ +$ _ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_3_2-solution000010.solution b/tests/exhaustive/autogen/gen02/expected/model_3_2-solution000010.solution new file mode 100644 index 0000000000..4fc309134f --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_3_2-solution000010.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting var2 be {{false, true}, {true}} +$ Visualisation for var2 +$ _ T +$ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_3_2-solution000011.solution b/tests/exhaustive/autogen/gen02/expected/model_3_2-solution000011.solution new file mode 100644 index 0000000000..70d0f91f38 --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_3_2-solution000011.solution @@ -0,0 +1,8 @@ +language Essence 1.3 + +letting var2 be {{}, {false}, {true}} +$ Visualisation for var2 +$ +$ _ +$ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_3_2-solution000012.solution b/tests/exhaustive/autogen/gen02/expected/model_3_2-solution000012.solution new file mode 100644 index 0000000000..ebc3fe4182 --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_3_2-solution000012.solution @@ -0,0 +1,8 @@ +language Essence 1.3 + +letting var2 be {{}, {false}, {false, true}} +$ Visualisation for var2 +$ +$ _ +$ _ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_3_2-solution000013.solution b/tests/exhaustive/autogen/gen02/expected/model_3_2-solution000013.solution new file mode 100644 index 0000000000..fa4340a533 --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_3_2-solution000013.solution @@ -0,0 +1,8 @@ +language Essence 1.3 + +letting var2 be {{}, {false, true}, {true}} +$ Visualisation for var2 +$ +$ _ T +$ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_3_2-solution000014.solution b/tests/exhaustive/autogen/gen02/expected/model_3_2-solution000014.solution new file mode 100644 index 0000000000..371f28aab7 --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_3_2-solution000014.solution @@ -0,0 +1,8 @@ +language Essence 1.3 + +letting var2 be {{false}, {false, true}, {true}} +$ Visualisation for var2 +$ _ +$ _ T +$ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_3_2-solution000015.solution b/tests/exhaustive/autogen/gen02/expected/model_3_2-solution000015.solution new file mode 100644 index 0000000000..35cfa328e8 --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_3_2-solution000015.solution @@ -0,0 +1,9 @@ +language Essence 1.3 + +letting var2 be {{}, {false}, {false, true}, {true}} +$ Visualisation for var2 +$ +$ _ +$ _ T +$ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_3_2.eprime.orig b/tests/exhaustive/autogen/gen02/expected/model_3_2.eprime.orig deleted file mode 100644 index 8f85be80ea..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_3_2.eprime.orig +++ /dev/null @@ -1,122 +0,0 @@ -language ESSENCE' 1.0 - -find var2_ExplicitVarSizeWithFlagsR5_Flags: matrix indexed by [int(1..4)] of bool -find var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Marker: matrix indexed by [int(1..4)] of int(0..2) -find var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Values: - matrix indexed by [int(1..4), int(1..2)] of bool -find var2_ExplicitVarSizeWithMarkerR4_Marker: int(0..4) -find var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Flags: - matrix indexed by [int(1..4), int(1..2)] of bool -find var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Values: - matrix indexed by [int(1..4), int(1..2)] of bool -branching on - [var2_ExplicitVarSizeWithMarkerR4_Marker, var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Flags, - var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Values, var2_ExplicitVarSizeWithFlagsR5_Flags, - var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Marker, - var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Values] -such that - or([var2_ExplicitVarSizeWithFlagsR5_Flags[q49] /\ - sum([toInt(q50 <= var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Marker[q49]) - | q50 : int(1..2)]) - >= -7 - | q49 : int(1..4)]), - and([var2_ExplicitVarSizeWithFlagsR5_Flags[q2 + 1] -> - flatten([[var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Marker[q2]; int(1)], - [-toInt(var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Values[q2, q10]) - | q10 : int(1..2)]; - int(1..2)]) - - var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Marker[q3] = 0 /\ - and([var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Values[q3, q12] = false - | q12 : int(1..2)]) - | q3 : int(1..4)]), - and([var2_ExplicitVarSizeWithFlagsR5_Flags[q4 + 1] -> var2_ExplicitVarSizeWithFlagsR5_Flags[q4] | q4 : int(1..3)]), - and([var2_ExplicitVarSizeWithFlagsR5_Flags[q6] -> - (2 <= var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Marker[q6] -> - -toInt(var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Values[q6, 1]) < - -toInt(var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Values[q6, 2])) - | q6 : int(1..4)]), - and([var2_ExplicitVarSizeWithFlagsR5_Flags[q6] -> - and([q8 > var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Marker[q6] -> - var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Values[q6, q8] = false - | q8 : int(1..2)]) - | q6 : int(1..4)]), - and([q13 + 1 <= var2_ExplicitVarSizeWithMarkerR4_Marker -> - flatten([flatten([[-toInt(var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Flags[q13, q21]); - int(1)], - [-toInt(var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Values[q13, q21]); - int(1)]; - int(1..2)]) - | q21 : int(1..2)]) - var2_ExplicitVarSizeWithMarkerR4_Marker -> - and([var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Flags[q14, q23] = false - | q23 : int(1..2)]) - /\ - and([var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Values[q14, q24] = false - | q24 : int(1..2)]) - | q14 : int(1..4)]), - and([q15 <= var2_ExplicitVarSizeWithMarkerR4_Marker -> - (var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Flags[q15, 2] -> - -toInt(var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Values[q15, 1]) < - -toInt(var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Values[q15, 2])) - | q15 : int(1..4)]), - and([q15 <= var2_ExplicitVarSizeWithMarkerR4_Marker -> - and([var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Flags[q15, q17] = false -> - var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Values[q15, q17] = false - | q17 : int(1..2)]) - | q15 : int(1..4)]), - and([q15 <= var2_ExplicitVarSizeWithMarkerR4_Marker -> - (var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Flags[q15, 2] -> - var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Flags[q15, 1]) - | q15 : int(1..4)]), - and([q26 <= var2_ExplicitVarSizeWithMarkerR4_Marker -> - or([var2_ExplicitVarSizeWithFlagsR5_Flags[q28] /\ - (and([q30 <= var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Marker[q28] -> - or([var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Flags[q26, q32] /\ - var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Values[q26, q32] = - var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Values[q28, q30] - | q32 : int(1..2)]) - | q30 : int(1..2)]) - /\ - and([var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Flags[q26, q34] -> - or([q36 <= var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Marker[q28] /\ - var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Values[q28, q36] = - var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Values[q26, q34] - | q36 : int(1..2)]) - | q34 : int(1..2)])) - | q28 : int(1..4)]) - | q26 : int(1..4)]), - and([var2_ExplicitVarSizeWithFlagsR5_Flags[q38] -> - or([q40 <= var2_ExplicitVarSizeWithMarkerR4_Marker /\ - (and([var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Flags[q40, q42] -> - or([q44 <= var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Marker[q38] /\ - var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Values[q38, q44] = - var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Values[q40, q42] - | q44 : int(1..2)]) - | q42 : int(1..2)]) - /\ - and([q46 <= var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Marker[q38] -> - or([var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Flags[q40, q48] /\ - var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Values[q40, q48] = - var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Values[q38, q46] - | q48 : int(1..2)]) - | q46 : int(1..2)])) - | q40 : int(1..4)]) - | q38 : int(1..4)]) - diff --git a/tests/exhaustive/autogen/gen02/expected/model_3_3-solution000001.solution b/tests/exhaustive/autogen/gen02/expected/model_3_3-solution000001.solution new file mode 100644 index 0000000000..19d999ca82 --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_3_3-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting var2 be {{}} diff --git a/tests/exhaustive/autogen/gen02/expected/model_3_3-solution000002.solution b/tests/exhaustive/autogen/gen02/expected/model_3_3-solution000002.solution new file mode 100644 index 0000000000..937293310f --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_3_3-solution000002.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting var2 be {{false}} +$ Visualisation for var2 +$ _ + diff --git a/tests/exhaustive/autogen/gen02/expected/model_3_3-solution000003.solution b/tests/exhaustive/autogen/gen02/expected/model_3_3-solution000003.solution new file mode 100644 index 0000000000..5a187652fa --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_3_3-solution000003.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting var2 be {{true}} +$ Visualisation for var2 +$ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_3_3-solution000004.solution b/tests/exhaustive/autogen/gen02/expected/model_3_3-solution000004.solution new file mode 100644 index 0000000000..0678d41bf8 --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_3_3-solution000004.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting var2 be {{false, true}} +$ Visualisation for var2 +$ _ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_3_3-solution000005.solution b/tests/exhaustive/autogen/gen02/expected/model_3_3-solution000005.solution new file mode 100644 index 0000000000..73f1bfe1ac --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_3_3-solution000005.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting var2 be {{}, {false}} +$ Visualisation for var2 +$ +$ _ + diff --git a/tests/exhaustive/autogen/gen02/expected/model_3_3-solution000006.solution b/tests/exhaustive/autogen/gen02/expected/model_3_3-solution000006.solution new file mode 100644 index 0000000000..d4c4a238b9 --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_3_3-solution000006.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting var2 be {{}, {true}} +$ Visualisation for var2 +$ +$ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_3_3-solution000007.solution b/tests/exhaustive/autogen/gen02/expected/model_3_3-solution000007.solution new file mode 100644 index 0000000000..9c15a8e4e1 --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_3_3-solution000007.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting var2 be {{}, {false, true}} +$ Visualisation for var2 +$ +$ _ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_3_3-solution000008.solution b/tests/exhaustive/autogen/gen02/expected/model_3_3-solution000008.solution new file mode 100644 index 0000000000..2b6a8959da --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_3_3-solution000008.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting var2 be {{false}, {true}} +$ Visualisation for var2 +$ _ +$ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_3_3-solution000009.solution b/tests/exhaustive/autogen/gen02/expected/model_3_3-solution000009.solution new file mode 100644 index 0000000000..b2e98e56a6 --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_3_3-solution000009.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting var2 be {{false}, {false, true}} +$ Visualisation for var2 +$ _ +$ _ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_3_3-solution000010.solution b/tests/exhaustive/autogen/gen02/expected/model_3_3-solution000010.solution new file mode 100644 index 0000000000..4fc309134f --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_3_3-solution000010.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting var2 be {{false, true}, {true}} +$ Visualisation for var2 +$ _ T +$ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_3_3-solution000011.solution b/tests/exhaustive/autogen/gen02/expected/model_3_3-solution000011.solution new file mode 100644 index 0000000000..70d0f91f38 --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_3_3-solution000011.solution @@ -0,0 +1,8 @@ +language Essence 1.3 + +letting var2 be {{}, {false}, {true}} +$ Visualisation for var2 +$ +$ _ +$ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_3_3-solution000012.solution b/tests/exhaustive/autogen/gen02/expected/model_3_3-solution000012.solution new file mode 100644 index 0000000000..ebc3fe4182 --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_3_3-solution000012.solution @@ -0,0 +1,8 @@ +language Essence 1.3 + +letting var2 be {{}, {false}, {false, true}} +$ Visualisation for var2 +$ +$ _ +$ _ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_3_3-solution000013.solution b/tests/exhaustive/autogen/gen02/expected/model_3_3-solution000013.solution new file mode 100644 index 0000000000..fa4340a533 --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_3_3-solution000013.solution @@ -0,0 +1,8 @@ +language Essence 1.3 + +letting var2 be {{}, {false, true}, {true}} +$ Visualisation for var2 +$ +$ _ T +$ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_3_3-solution000014.solution b/tests/exhaustive/autogen/gen02/expected/model_3_3-solution000014.solution new file mode 100644 index 0000000000..371f28aab7 --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_3_3-solution000014.solution @@ -0,0 +1,8 @@ +language Essence 1.3 + +letting var2 be {{false}, {false, true}, {true}} +$ Visualisation for var2 +$ _ +$ _ T +$ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_3_3-solution000015.solution b/tests/exhaustive/autogen/gen02/expected/model_3_3-solution000015.solution new file mode 100644 index 0000000000..35cfa328e8 --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_3_3-solution000015.solution @@ -0,0 +1,9 @@ +language Essence 1.3 + +letting var2 be {{}, {false}, {false, true}, {true}} +$ Visualisation for var2 +$ +$ _ +$ _ T +$ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_3_3.eprime.orig b/tests/exhaustive/autogen/gen02/expected/model_3_3.eprime.orig deleted file mode 100644 index d983f1c128..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_3_3.eprime.orig +++ /dev/null @@ -1,43 +0,0 @@ -language ESSENCE' 1.0 - -find var2_ExplicitVarSizeWithFlagsR5_Flags: matrix indexed by [int(1..4)] of bool -find var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Marker: matrix indexed by [int(1..4)] of int(0..2) -find var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Values: - matrix indexed by [int(1..4), int(1..2)] of bool -branching on - [var2_ExplicitVarSizeWithFlagsR5_Flags, var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Marker, - var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Values] -such that - or([var2_ExplicitVarSizeWithFlagsR5_Flags[q13] /\ - sum([toInt(q14 <= var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Marker[q13]) - | q14 : int(1..2)]) - >= -7 - | q13 : int(1..4)]), - and([var2_ExplicitVarSizeWithFlagsR5_Flags[q2 + 1] -> - flatten([[var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Marker[q2]; int(1)], - [-toInt(var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Values[q2, q10]) - | q10 : int(1..2)]; - int(1..2)]) - - var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Marker[q3] = 0 /\ - and([var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Values[q3, q12] = false - | q12 : int(1..2)]) - | q3 : int(1..4)]), - and([var2_ExplicitVarSizeWithFlagsR5_Flags[q4 + 1] -> var2_ExplicitVarSizeWithFlagsR5_Flags[q4] | q4 : int(1..3)]), - and([var2_ExplicitVarSizeWithFlagsR5_Flags[q6] -> - (2 <= var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Marker[q6] -> - -toInt(var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Values[q6, 1]) < - -toInt(var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Values[q6, 2])) - | q6 : int(1..4)]), - and([var2_ExplicitVarSizeWithFlagsR5_Flags[q6] -> - and([q8 > var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Marker[q6] -> - var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Values[q6, q8] = false - | q8 : int(1..2)]) - | q6 : int(1..4)]) - diff --git a/tests/exhaustive/autogen/gen02/expected/model_3_4-solution000001.solution b/tests/exhaustive/autogen/gen02/expected/model_3_4-solution000001.solution new file mode 100644 index 0000000000..19d999ca82 --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_3_4-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting var2 be {{}} diff --git a/tests/exhaustive/autogen/gen02/expected/model_3_4-solution000002.solution b/tests/exhaustive/autogen/gen02/expected/model_3_4-solution000002.solution new file mode 100644 index 0000000000..937293310f --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_3_4-solution000002.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting var2 be {{false}} +$ Visualisation for var2 +$ _ + diff --git a/tests/exhaustive/autogen/gen02/expected/model_3_4-solution000003.solution b/tests/exhaustive/autogen/gen02/expected/model_3_4-solution000003.solution new file mode 100644 index 0000000000..5a187652fa --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_3_4-solution000003.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting var2 be {{true}} +$ Visualisation for var2 +$ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_3_4-solution000004.solution b/tests/exhaustive/autogen/gen02/expected/model_3_4-solution000004.solution new file mode 100644 index 0000000000..0678d41bf8 --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_3_4-solution000004.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting var2 be {{false, true}} +$ Visualisation for var2 +$ _ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_3_4-solution000005.solution b/tests/exhaustive/autogen/gen02/expected/model_3_4-solution000005.solution new file mode 100644 index 0000000000..73f1bfe1ac --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_3_4-solution000005.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting var2 be {{}, {false}} +$ Visualisation for var2 +$ +$ _ + diff --git a/tests/exhaustive/autogen/gen02/expected/model_3_4-solution000006.solution b/tests/exhaustive/autogen/gen02/expected/model_3_4-solution000006.solution new file mode 100644 index 0000000000..d4c4a238b9 --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_3_4-solution000006.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting var2 be {{}, {true}} +$ Visualisation for var2 +$ +$ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_3_4-solution000007.solution b/tests/exhaustive/autogen/gen02/expected/model_3_4-solution000007.solution new file mode 100644 index 0000000000..2b6a8959da --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_3_4-solution000007.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting var2 be {{false}, {true}} +$ Visualisation for var2 +$ _ +$ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_3_4-solution000008.solution b/tests/exhaustive/autogen/gen02/expected/model_3_4-solution000008.solution new file mode 100644 index 0000000000..9c15a8e4e1 --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_3_4-solution000008.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting var2 be {{}, {false, true}} +$ Visualisation for var2 +$ +$ _ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_3_4-solution000009.solution b/tests/exhaustive/autogen/gen02/expected/model_3_4-solution000009.solution new file mode 100644 index 0000000000..b2e98e56a6 --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_3_4-solution000009.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting var2 be {{false}, {false, true}} +$ Visualisation for var2 +$ _ +$ _ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_3_4-solution000010.solution b/tests/exhaustive/autogen/gen02/expected/model_3_4-solution000010.solution new file mode 100644 index 0000000000..4fc309134f --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_3_4-solution000010.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting var2 be {{false, true}, {true}} +$ Visualisation for var2 +$ _ T +$ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_3_4-solution000011.solution b/tests/exhaustive/autogen/gen02/expected/model_3_4-solution000011.solution new file mode 100644 index 0000000000..70d0f91f38 --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_3_4-solution000011.solution @@ -0,0 +1,8 @@ +language Essence 1.3 + +letting var2 be {{}, {false}, {true}} +$ Visualisation for var2 +$ +$ _ +$ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_3_4-solution000012.solution b/tests/exhaustive/autogen/gen02/expected/model_3_4-solution000012.solution new file mode 100644 index 0000000000..ebc3fe4182 --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_3_4-solution000012.solution @@ -0,0 +1,8 @@ +language Essence 1.3 + +letting var2 be {{}, {false}, {false, true}} +$ Visualisation for var2 +$ +$ _ +$ _ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_3_4-solution000013.solution b/tests/exhaustive/autogen/gen02/expected/model_3_4-solution000013.solution new file mode 100644 index 0000000000..fa4340a533 --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_3_4-solution000013.solution @@ -0,0 +1,8 @@ +language Essence 1.3 + +letting var2 be {{}, {false, true}, {true}} +$ Visualisation for var2 +$ +$ _ T +$ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_3_4-solution000014.solution b/tests/exhaustive/autogen/gen02/expected/model_3_4-solution000014.solution new file mode 100644 index 0000000000..371f28aab7 --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_3_4-solution000014.solution @@ -0,0 +1,8 @@ +language Essence 1.3 + +letting var2 be {{false}, {false, true}, {true}} +$ Visualisation for var2 +$ _ +$ _ T +$ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_3_4-solution000015.solution b/tests/exhaustive/autogen/gen02/expected/model_3_4-solution000015.solution new file mode 100644 index 0000000000..35cfa328e8 --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_3_4-solution000015.solution @@ -0,0 +1,9 @@ +language Essence 1.3 + +letting var2 be {{}, {false}, {false, true}, {true}} +$ Visualisation for var2 +$ +$ _ +$ _ T +$ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_3_4.eprime.orig b/tests/exhaustive/autogen/gen02/expected/model_3_4.eprime.orig deleted file mode 100644 index cb59ea7091..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_3_4.eprime.orig +++ /dev/null @@ -1,123 +0,0 @@ -language ESSENCE' 1.0 - -find var2_ExplicitVarSizeWithFlagsR5_Flags: matrix indexed by [int(1..4)] of bool -find var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Marker: matrix indexed by [int(1..4)] of int(0..2) -find var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Values: - matrix indexed by [int(1..4), int(1..2)] of bool -find var2_ExplicitVarSizeWithFlagsR4_Flags: matrix indexed by [int(1..4)] of bool -find var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Flags: - matrix indexed by [int(1..4), int(1..2)] of bool -find var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Values: - matrix indexed by [int(1..4), int(1..2)] of bool -branching on - [var2_ExplicitVarSizeWithFlagsR4_Flags, var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Flags, - var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Values, var2_ExplicitVarSizeWithFlagsR5_Flags, - var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Marker, - var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Values] -such that - or([var2_ExplicitVarSizeWithFlagsR5_Flags[q51] /\ - sum([toInt(q52 <= var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Marker[q51]) - | q52 : int(1..2)]) - >= -7 - | q51 : int(1..4)]), - and([var2_ExplicitVarSizeWithFlagsR5_Flags[q2 + 1] -> - flatten([[var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Marker[q2]; int(1)], - [-toInt(var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Values[q2, q10]) - | q10 : int(1..2)]; - int(1..2)]) - - var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Marker[q3] = 0 /\ - and([var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Values[q3, q12] = false - | q12 : int(1..2)]) - | q3 : int(1..4)]), - and([var2_ExplicitVarSizeWithFlagsR5_Flags[q4 + 1] -> var2_ExplicitVarSizeWithFlagsR5_Flags[q4] | q4 : int(1..3)]), - and([var2_ExplicitVarSizeWithFlagsR5_Flags[q6] -> - (2 <= var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Marker[q6] -> - -toInt(var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Values[q6, 1]) < - -toInt(var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Values[q6, 2])) - | q6 : int(1..4)]), - and([var2_ExplicitVarSizeWithFlagsR5_Flags[q6] -> - and([q8 > var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Marker[q6] -> - var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Values[q6, q8] = false - | q8 : int(1..2)]) - | q6 : int(1..4)]), - and([var2_ExplicitVarSizeWithFlagsR4_Flags[q13 + 1] -> - flatten([flatten([[-toInt(var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Flags[q13, q23]); - int(1)], - [-toInt(var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Values[q13, q23]); - int(1)]; - int(1..2)]) - | q23 : int(1..2)]) - - and([var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Flags[q14, q25] = false - | q25 : int(1..2)]) - /\ - and([var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Values[q14, q26] = false - | q26 : int(1..2)]) - | q14 : int(1..4)]), - and([var2_ExplicitVarSizeWithFlagsR4_Flags[q15 + 1] -> var2_ExplicitVarSizeWithFlagsR4_Flags[q15] - | q15 : int(1..3)]), - and([var2_ExplicitVarSizeWithFlagsR4_Flags[q17] -> - (var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Flags[q17, 2] -> - -toInt(var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Values[q17, 1]) < - -toInt(var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Values[q17, 2])) - | q17 : int(1..4)]), - and([var2_ExplicitVarSizeWithFlagsR4_Flags[q17] -> - and([var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Flags[q17, q19] = false -> - var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Values[q17, q19] = false - | q19 : int(1..2)]) - | q17 : int(1..4)]), - and([var2_ExplicitVarSizeWithFlagsR4_Flags[q17] -> - (var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Flags[q17, 2] -> - var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Flags[q17, 1]) - | q17 : int(1..4)]), - and([var2_ExplicitVarSizeWithFlagsR4_Flags[q28] -> - or([var2_ExplicitVarSizeWithFlagsR5_Flags[q30] /\ - (and([q32 <= var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Marker[q30] -> - or([var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Flags[q28, q34] /\ - var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Values[q28, q34] = - var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Values[q30, q32] - | q34 : int(1..2)]) - | q32 : int(1..2)]) - /\ - and([var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Flags[q28, q36] -> - or([q38 <= var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Marker[q30] /\ - var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Values[q30, q38] = - var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Values[q28, q36] - | q38 : int(1..2)]) - | q36 : int(1..2)])) - | q30 : int(1..4)]) - | q28 : int(1..4)]), - and([var2_ExplicitVarSizeWithFlagsR5_Flags[q40] -> - or([var2_ExplicitVarSizeWithFlagsR4_Flags[q42] /\ - (and([var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Flags[q42, q44] -> - or([q46 <= var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Marker[q40] /\ - var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Values[q40, q46] = - var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Values[q42, q44] - | q46 : int(1..2)]) - | q44 : int(1..2)]) - /\ - and([q48 <= var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Marker[q40] -> - or([var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Flags[q42, q50] /\ - var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Values[q42, q50] = - var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Values[q40, q48] - | q50 : int(1..2)]) - | q48 : int(1..2)])) - | q42 : int(1..4)]) - | q40 : int(1..4)]) - diff --git a/tests/exhaustive/autogen/gen02/expected/model_4_1-solution000001.solution b/tests/exhaustive/autogen/gen02/expected/model_4_1-solution000001.solution new file mode 100644 index 0000000000..19d999ca82 --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_4_1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting var2 be {{}} diff --git a/tests/exhaustive/autogen/gen02/expected/model_4_1-solution000002.solution b/tests/exhaustive/autogen/gen02/expected/model_4_1-solution000002.solution new file mode 100644 index 0000000000..937293310f --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_4_1-solution000002.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting var2 be {{false}} +$ Visualisation for var2 +$ _ + diff --git a/tests/exhaustive/autogen/gen02/expected/model_4_1-solution000003.solution b/tests/exhaustive/autogen/gen02/expected/model_4_1-solution000003.solution new file mode 100644 index 0000000000..5a187652fa --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_4_1-solution000003.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting var2 be {{true}} +$ Visualisation for var2 +$ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_4_1-solution000004.solution b/tests/exhaustive/autogen/gen02/expected/model_4_1-solution000004.solution new file mode 100644 index 0000000000..0678d41bf8 --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_4_1-solution000004.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting var2 be {{false, true}} +$ Visualisation for var2 +$ _ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_4_1-solution000005.solution b/tests/exhaustive/autogen/gen02/expected/model_4_1-solution000005.solution new file mode 100644 index 0000000000..73f1bfe1ac --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_4_1-solution000005.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting var2 be {{}, {false}} +$ Visualisation for var2 +$ +$ _ + diff --git a/tests/exhaustive/autogen/gen02/expected/model_4_1-solution000006.solution b/tests/exhaustive/autogen/gen02/expected/model_4_1-solution000006.solution new file mode 100644 index 0000000000..d4c4a238b9 --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_4_1-solution000006.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting var2 be {{}, {true}} +$ Visualisation for var2 +$ +$ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_4_1-solution000007.solution b/tests/exhaustive/autogen/gen02/expected/model_4_1-solution000007.solution new file mode 100644 index 0000000000..9c15a8e4e1 --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_4_1-solution000007.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting var2 be {{}, {false, true}} +$ Visualisation for var2 +$ +$ _ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_4_1-solution000008.solution b/tests/exhaustive/autogen/gen02/expected/model_4_1-solution000008.solution new file mode 100644 index 0000000000..2b6a8959da --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_4_1-solution000008.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting var2 be {{false}, {true}} +$ Visualisation for var2 +$ _ +$ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_4_1-solution000009.solution b/tests/exhaustive/autogen/gen02/expected/model_4_1-solution000009.solution new file mode 100644 index 0000000000..b2e98e56a6 --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_4_1-solution000009.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting var2 be {{false}, {false, true}} +$ Visualisation for var2 +$ _ +$ _ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_4_1-solution000010.solution b/tests/exhaustive/autogen/gen02/expected/model_4_1-solution000010.solution new file mode 100644 index 0000000000..4fc309134f --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_4_1-solution000010.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting var2 be {{false, true}, {true}} +$ Visualisation for var2 +$ _ T +$ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_4_1-solution000011.solution b/tests/exhaustive/autogen/gen02/expected/model_4_1-solution000011.solution new file mode 100644 index 0000000000..70d0f91f38 --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_4_1-solution000011.solution @@ -0,0 +1,8 @@ +language Essence 1.3 + +letting var2 be {{}, {false}, {true}} +$ Visualisation for var2 +$ +$ _ +$ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_4_1-solution000012.solution b/tests/exhaustive/autogen/gen02/expected/model_4_1-solution000012.solution new file mode 100644 index 0000000000..ebc3fe4182 --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_4_1-solution000012.solution @@ -0,0 +1,8 @@ +language Essence 1.3 + +letting var2 be {{}, {false}, {false, true}} +$ Visualisation for var2 +$ +$ _ +$ _ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_4_1-solution000013.solution b/tests/exhaustive/autogen/gen02/expected/model_4_1-solution000013.solution new file mode 100644 index 0000000000..fa4340a533 --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_4_1-solution000013.solution @@ -0,0 +1,8 @@ +language Essence 1.3 + +letting var2 be {{}, {false, true}, {true}} +$ Visualisation for var2 +$ +$ _ T +$ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_4_1-solution000014.solution b/tests/exhaustive/autogen/gen02/expected/model_4_1-solution000014.solution new file mode 100644 index 0000000000..371f28aab7 --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_4_1-solution000014.solution @@ -0,0 +1,8 @@ +language Essence 1.3 + +letting var2 be {{false}, {false, true}, {true}} +$ Visualisation for var2 +$ _ +$ _ T +$ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_4_1-solution000015.solution b/tests/exhaustive/autogen/gen02/expected/model_4_1-solution000015.solution new file mode 100644 index 0000000000..35cfa328e8 --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_4_1-solution000015.solution @@ -0,0 +1,9 @@ +language Essence 1.3 + +letting var2 be {{}, {false}, {false, true}, {true}} +$ Visualisation for var2 +$ +$ _ +$ _ T +$ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_4_1.eprime.orig b/tests/exhaustive/autogen/gen02/expected/model_4_1.eprime.orig deleted file mode 100644 index 5952bfe7b5..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_4_1.eprime.orig +++ /dev/null @@ -1,119 +0,0 @@ -language ESSENCE' 1.0 - -find var2_ExplicitVarSizeWithFlagsR4_Flags: matrix indexed by [int(1..4)] of bool -find var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Flags: - matrix indexed by [int(1..4), int(1..2)] of bool -find var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Values: - matrix indexed by [int(1..4), int(1..2)] of bool -find var2_ExplicitVarSizeWithMarkerR5_Marker: int(0..4) -find var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker: - matrix indexed by [int(1..4)] of int(0..2) -find var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values: - matrix indexed by [int(1..4), int(1..2)] of bool -branching on - [var2_ExplicitVarSizeWithMarkerR5_Marker, var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker, - var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values, var2_ExplicitVarSizeWithFlagsR4_Flags, - var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Flags, - var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Values] -such that - or([var2_ExplicitVarSizeWithFlagsR4_Flags[q49] /\ - sum([toInt(var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Flags[q49, q50]) | q50 : int(1..2)]) - >= -7 - | q49 : int(1..4)]), - and([var2_ExplicitVarSizeWithFlagsR4_Flags[q2 + 1] -> - flatten([flatten([[-toInt(var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Flags[q2, q12]); - int(1)], - [-toInt(var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Values[q2, q12]); - int(1)]; - int(1..2)]) - | q12 : int(1..2)]) - - and([var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Flags[q3, q14] = false | q14 : int(1..2)]) - /\ - and([var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Values[q3, q15] = false - | q15 : int(1..2)]) - | q3 : int(1..4)]), - and([var2_ExplicitVarSizeWithFlagsR4_Flags[q4 + 1] -> var2_ExplicitVarSizeWithFlagsR4_Flags[q4] | q4 : int(1..3)]), - and([var2_ExplicitVarSizeWithFlagsR4_Flags[q6] -> - (var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Flags[q6, 2] -> - -toInt(var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Values[q6, 1]) < - -toInt(var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Values[q6, 2])) - | q6 : int(1..4)]), - and([var2_ExplicitVarSizeWithFlagsR4_Flags[q6] -> - and([var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Flags[q6, q8] = false -> - var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Values[q6, q8] = false - | q8 : int(1..2)]) - | q6 : int(1..4)]), - and([var2_ExplicitVarSizeWithFlagsR4_Flags[q6] -> - (var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Flags[q6, 2] -> - var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Flags[q6, 1]) - | q6 : int(1..4)]), - and([q16 + 1 <= var2_ExplicitVarSizeWithMarkerR5_Marker -> - flatten([[var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q16]; int(1)], - [-toInt(var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q16, q22]) - | q22 : int(1..2)]; - int(1..2)]) - var2_ExplicitVarSizeWithMarkerR5_Marker -> - var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q17] = 0 /\ - and([var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q17, q24] = false - | q24 : int(1..2)]) - | q17 : int(1..4)]), - and([q18 <= var2_ExplicitVarSizeWithMarkerR5_Marker -> - (2 <= var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q18] -> - -toInt(var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q18, 1]) < - -toInt(var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q18, 2])) - | q18 : int(1..4)]), - and([q18 <= var2_ExplicitVarSizeWithMarkerR5_Marker -> - and([q20 > var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q18] -> - var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q18, q20] = false - | q20 : int(1..2)]) - | q18 : int(1..4)]), - and([q26 <= var2_ExplicitVarSizeWithMarkerR5_Marker -> - or([var2_ExplicitVarSizeWithFlagsR4_Flags[q28] /\ - (and([var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Flags[q28, q30] -> - or([q32 <= var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q26] /\ - var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q26, q32] = - var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Values[q28, q30] - | q32 : int(1..2)]) - | q30 : int(1..2)]) - /\ - and([q34 <= var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q26] -> - or([var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Flags[q28, q36] /\ - var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Values[q28, q36] = - var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q26, q34] - | q36 : int(1..2)]) - | q34 : int(1..2)])) - | q28 : int(1..4)]) - | q26 : int(1..4)]), - and([var2_ExplicitVarSizeWithFlagsR4_Flags[q38] -> - or([q40 <= var2_ExplicitVarSizeWithMarkerR5_Marker /\ - (and([q42 <= var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q40] -> - or([var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Flags[q38, q44] /\ - var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Values[q38, q44] = - var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q40, q42] - | q44 : int(1..2)]) - | q42 : int(1..2)]) - /\ - and([var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Flags[q38, q46] -> - or([q48 <= var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q40] /\ - var2_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q40, q48] = - var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Values[q38, q46] - | q48 : int(1..2)]) - | q46 : int(1..2)])) - | q40 : int(1..4)]) - | q38 : int(1..4)]) - diff --git a/tests/exhaustive/autogen/gen02/expected/model_4_2-solution000001.solution b/tests/exhaustive/autogen/gen02/expected/model_4_2-solution000001.solution new file mode 100644 index 0000000000..19d999ca82 --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_4_2-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting var2 be {{}} diff --git a/tests/exhaustive/autogen/gen02/expected/model_4_2-solution000002.solution b/tests/exhaustive/autogen/gen02/expected/model_4_2-solution000002.solution new file mode 100644 index 0000000000..937293310f --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_4_2-solution000002.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting var2 be {{false}} +$ Visualisation for var2 +$ _ + diff --git a/tests/exhaustive/autogen/gen02/expected/model_4_2-solution000003.solution b/tests/exhaustive/autogen/gen02/expected/model_4_2-solution000003.solution new file mode 100644 index 0000000000..5a187652fa --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_4_2-solution000003.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting var2 be {{true}} +$ Visualisation for var2 +$ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_4_2-solution000004.solution b/tests/exhaustive/autogen/gen02/expected/model_4_2-solution000004.solution new file mode 100644 index 0000000000..0678d41bf8 --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_4_2-solution000004.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting var2 be {{false, true}} +$ Visualisation for var2 +$ _ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_4_2-solution000005.solution b/tests/exhaustive/autogen/gen02/expected/model_4_2-solution000005.solution new file mode 100644 index 0000000000..73f1bfe1ac --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_4_2-solution000005.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting var2 be {{}, {false}} +$ Visualisation for var2 +$ +$ _ + diff --git a/tests/exhaustive/autogen/gen02/expected/model_4_2-solution000006.solution b/tests/exhaustive/autogen/gen02/expected/model_4_2-solution000006.solution new file mode 100644 index 0000000000..d4c4a238b9 --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_4_2-solution000006.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting var2 be {{}, {true}} +$ Visualisation for var2 +$ +$ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_4_2-solution000007.solution b/tests/exhaustive/autogen/gen02/expected/model_4_2-solution000007.solution new file mode 100644 index 0000000000..2b6a8959da --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_4_2-solution000007.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting var2 be {{false}, {true}} +$ Visualisation for var2 +$ _ +$ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_4_2-solution000008.solution b/tests/exhaustive/autogen/gen02/expected/model_4_2-solution000008.solution new file mode 100644 index 0000000000..9c15a8e4e1 --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_4_2-solution000008.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting var2 be {{}, {false, true}} +$ Visualisation for var2 +$ +$ _ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_4_2-solution000009.solution b/tests/exhaustive/autogen/gen02/expected/model_4_2-solution000009.solution new file mode 100644 index 0000000000..b2e98e56a6 --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_4_2-solution000009.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting var2 be {{false}, {false, true}} +$ Visualisation for var2 +$ _ +$ _ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_4_2-solution000010.solution b/tests/exhaustive/autogen/gen02/expected/model_4_2-solution000010.solution new file mode 100644 index 0000000000..4fc309134f --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_4_2-solution000010.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting var2 be {{false, true}, {true}} +$ Visualisation for var2 +$ _ T +$ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_4_2-solution000011.solution b/tests/exhaustive/autogen/gen02/expected/model_4_2-solution000011.solution new file mode 100644 index 0000000000..70d0f91f38 --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_4_2-solution000011.solution @@ -0,0 +1,8 @@ +language Essence 1.3 + +letting var2 be {{}, {false}, {true}} +$ Visualisation for var2 +$ +$ _ +$ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_4_2-solution000012.solution b/tests/exhaustive/autogen/gen02/expected/model_4_2-solution000012.solution new file mode 100644 index 0000000000..ebc3fe4182 --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_4_2-solution000012.solution @@ -0,0 +1,8 @@ +language Essence 1.3 + +letting var2 be {{}, {false}, {false, true}} +$ Visualisation for var2 +$ +$ _ +$ _ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_4_2-solution000013.solution b/tests/exhaustive/autogen/gen02/expected/model_4_2-solution000013.solution new file mode 100644 index 0000000000..fa4340a533 --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_4_2-solution000013.solution @@ -0,0 +1,8 @@ +language Essence 1.3 + +letting var2 be {{}, {false, true}, {true}} +$ Visualisation for var2 +$ +$ _ T +$ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_4_2-solution000014.solution b/tests/exhaustive/autogen/gen02/expected/model_4_2-solution000014.solution new file mode 100644 index 0000000000..371f28aab7 --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_4_2-solution000014.solution @@ -0,0 +1,8 @@ +language Essence 1.3 + +letting var2 be {{false}, {false, true}, {true}} +$ Visualisation for var2 +$ _ +$ _ T +$ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_4_2-solution000015.solution b/tests/exhaustive/autogen/gen02/expected/model_4_2-solution000015.solution new file mode 100644 index 0000000000..35cfa328e8 --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_4_2-solution000015.solution @@ -0,0 +1,9 @@ +language Essence 1.3 + +letting var2 be {{}, {false}, {false, true}, {true}} +$ Visualisation for var2 +$ +$ _ +$ _ T +$ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_4_2.eprime b/tests/exhaustive/autogen/gen02/expected/model_4_2.eprime new file mode 100644 index 0000000000..c50ffb2189 --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_4_2.eprime @@ -0,0 +1,119 @@ +language ESSENCE' 1.0 + +find var2_ExplicitVarSizeWithFlagsR4_Flags: matrix indexed by [int(1..4)] of bool +find var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Flags: + matrix indexed by [int(1..4), int(1..2)] of bool +find var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Values: + matrix indexed by [int(1..4), int(1..2)] of bool +find var2_ExplicitVarSizeWithMarkerR4_Marker: int(0..4) +find var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Flags: + matrix indexed by [int(1..4), int(1..2)] of bool +find var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Values: + matrix indexed by [int(1..4), int(1..2)] of bool +branching on + [var2_ExplicitVarSizeWithMarkerR4_Marker, var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Flags, + var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Values, var2_ExplicitVarSizeWithFlagsR4_Flags, + var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Flags, + var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Values] +such that + or([var2_ExplicitVarSizeWithFlagsR4_Flags[q44] /\ + sum([toInt(var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Flags[q44, q45]) | q45 : int(1..2)]) + >= -7 + | q44 : int(1..4)]), + and([var2_ExplicitVarSizeWithFlagsR4_Flags[q2 + 1] -> + flatten([flatten([[-toInt(var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Flags[q2, q12]); + int(1)], + [-toInt(var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Values[q2, q12]); + int(1)]; + int(1..2)]) + | q12 : int(1..2)]) + + and([var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Flags[q3, q14] = false | q14 : int(1..2)]) + /\ + and([var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Values[q3, q15] = false + | q15 : int(1..2)]) + | q3 : int(1..4)]), + and([var2_ExplicitVarSizeWithFlagsR4_Flags[q4 + 1] -> var2_ExplicitVarSizeWithFlagsR4_Flags[q4] | q4 : int(1..3)]), + and([var2_ExplicitVarSizeWithFlagsR4_Flags[q6] -> + (var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Flags[q6, 2] -> + -toInt(var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Values[q6, 1]) < + -toInt(var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Values[q6, 2])) + | q6 : int(1..4)]), + and([var2_ExplicitVarSizeWithFlagsR4_Flags[q6] -> + and([var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Flags[q6, q8] = false -> + var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Values[q6, q8] = false + | q8 : int(1..2)]) + | q6 : int(1..4)]), + and([var2_ExplicitVarSizeWithFlagsR4_Flags[q6] -> + (var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Flags[q6, 2] -> + var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Flags[q6, 1]) + | q6 : int(1..4)]), + and([q16 + 1 <= var2_ExplicitVarSizeWithMarkerR4_Marker -> + flatten([flatten([[-toInt(var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Flags[q16, q24]); + int(1)], + [-toInt(var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Values[q16, q24]); + int(1)]; + int(1..2)]) + | q24 : int(1..2)]) + var2_ExplicitVarSizeWithMarkerR4_Marker -> + and([var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Flags[q17, q26] = false + | q26 : int(1..2)]) + /\ + and([var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Values[q17, q27] = false + | q27 : int(1..2)]) + | q17 : int(1..4)]), + and([q18 <= var2_ExplicitVarSizeWithMarkerR4_Marker -> + (var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Flags[q18, 2] -> + -toInt(var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Values[q18, 1]) < + -toInt(var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Values[q18, 2])) + | q18 : int(1..4)]), + and([q18 <= var2_ExplicitVarSizeWithMarkerR4_Marker -> + and([var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Flags[q18, q20] = false -> + var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Values[q18, q20] = false + | q20 : int(1..2)]) + | q18 : int(1..4)]), + and([q18 <= var2_ExplicitVarSizeWithMarkerR4_Marker -> + (var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Flags[q18, 2] -> + var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Flags[q18, 1]) + | q18 : int(1..4)]), + and([q29 <= var2_ExplicitVarSizeWithMarkerR4_Marker -> + or([var2_ExplicitVarSizeWithFlagsR4_Flags[q31] /\ + (and([var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Flags[q31, q32] = + var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Flags[q29, q32] + | q32 : int(1..2)]) + /\ + and([var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Values[q31, q34] = + var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Values[q29, q34] + | q34 : int(1..2)])) + | q31 : int(1..4)]) + | q29 : int(1..4)]), + and([var2_ExplicitVarSizeWithFlagsR4_Flags[q37] -> + or([q39 <= var2_ExplicitVarSizeWithMarkerR4_Marker /\ + (and([var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Flags[q39, q40] = + var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Flags[q37, q40] + | q40 : int(1..2)]) + /\ + and([var2_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Values[q39, q42] = + var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Values[q37, q42] + | q42 : int(1..2)])) + | q39 : int(1..4)]) + | q37 : int(1..4)]) + diff --git a/tests/exhaustive/autogen/gen02/expected/model_4_3-solution000001.solution b/tests/exhaustive/autogen/gen02/expected/model_4_3-solution000001.solution new file mode 100644 index 0000000000..19d999ca82 --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_4_3-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting var2 be {{}} diff --git a/tests/exhaustive/autogen/gen02/expected/model_4_3-solution000002.solution b/tests/exhaustive/autogen/gen02/expected/model_4_3-solution000002.solution new file mode 100644 index 0000000000..937293310f --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_4_3-solution000002.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting var2 be {{false}} +$ Visualisation for var2 +$ _ + diff --git a/tests/exhaustive/autogen/gen02/expected/model_4_3-solution000003.solution b/tests/exhaustive/autogen/gen02/expected/model_4_3-solution000003.solution new file mode 100644 index 0000000000..5a187652fa --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_4_3-solution000003.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting var2 be {{true}} +$ Visualisation for var2 +$ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_4_3-solution000004.solution b/tests/exhaustive/autogen/gen02/expected/model_4_3-solution000004.solution new file mode 100644 index 0000000000..0678d41bf8 --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_4_3-solution000004.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting var2 be {{false, true}} +$ Visualisation for var2 +$ _ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_4_3-solution000005.solution b/tests/exhaustive/autogen/gen02/expected/model_4_3-solution000005.solution new file mode 100644 index 0000000000..73f1bfe1ac --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_4_3-solution000005.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting var2 be {{}, {false}} +$ Visualisation for var2 +$ +$ _ + diff --git a/tests/exhaustive/autogen/gen02/expected/model_4_3-solution000006.solution b/tests/exhaustive/autogen/gen02/expected/model_4_3-solution000006.solution new file mode 100644 index 0000000000..d4c4a238b9 --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_4_3-solution000006.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting var2 be {{}, {true}} +$ Visualisation for var2 +$ +$ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_4_3-solution000007.solution b/tests/exhaustive/autogen/gen02/expected/model_4_3-solution000007.solution new file mode 100644 index 0000000000..9c15a8e4e1 --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_4_3-solution000007.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting var2 be {{}, {false, true}} +$ Visualisation for var2 +$ +$ _ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_4_3-solution000008.solution b/tests/exhaustive/autogen/gen02/expected/model_4_3-solution000008.solution new file mode 100644 index 0000000000..2b6a8959da --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_4_3-solution000008.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting var2 be {{false}, {true}} +$ Visualisation for var2 +$ _ +$ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_4_3-solution000009.solution b/tests/exhaustive/autogen/gen02/expected/model_4_3-solution000009.solution new file mode 100644 index 0000000000..b2e98e56a6 --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_4_3-solution000009.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting var2 be {{false}, {false, true}} +$ Visualisation for var2 +$ _ +$ _ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_4_3-solution000010.solution b/tests/exhaustive/autogen/gen02/expected/model_4_3-solution000010.solution new file mode 100644 index 0000000000..4fc309134f --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_4_3-solution000010.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting var2 be {{false, true}, {true}} +$ Visualisation for var2 +$ _ T +$ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_4_3-solution000011.solution b/tests/exhaustive/autogen/gen02/expected/model_4_3-solution000011.solution new file mode 100644 index 0000000000..70d0f91f38 --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_4_3-solution000011.solution @@ -0,0 +1,8 @@ +language Essence 1.3 + +letting var2 be {{}, {false}, {true}} +$ Visualisation for var2 +$ +$ _ +$ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_4_3-solution000012.solution b/tests/exhaustive/autogen/gen02/expected/model_4_3-solution000012.solution new file mode 100644 index 0000000000..ebc3fe4182 --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_4_3-solution000012.solution @@ -0,0 +1,8 @@ +language Essence 1.3 + +letting var2 be {{}, {false}, {false, true}} +$ Visualisation for var2 +$ +$ _ +$ _ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_4_3-solution000013.solution b/tests/exhaustive/autogen/gen02/expected/model_4_3-solution000013.solution new file mode 100644 index 0000000000..fa4340a533 --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_4_3-solution000013.solution @@ -0,0 +1,8 @@ +language Essence 1.3 + +letting var2 be {{}, {false, true}, {true}} +$ Visualisation for var2 +$ +$ _ T +$ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_4_3-solution000014.solution b/tests/exhaustive/autogen/gen02/expected/model_4_3-solution000014.solution new file mode 100644 index 0000000000..371f28aab7 --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_4_3-solution000014.solution @@ -0,0 +1,8 @@ +language Essence 1.3 + +letting var2 be {{false}, {false, true}, {true}} +$ Visualisation for var2 +$ _ +$ _ T +$ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_4_3-solution000015.solution b/tests/exhaustive/autogen/gen02/expected/model_4_3-solution000015.solution new file mode 100644 index 0000000000..35cfa328e8 --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_4_3-solution000015.solution @@ -0,0 +1,9 @@ +language Essence 1.3 + +letting var2 be {{}, {false}, {false, true}, {true}} +$ Visualisation for var2 +$ +$ _ +$ _ T +$ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_4_3.eprime.orig b/tests/exhaustive/autogen/gen02/expected/model_4_3.eprime.orig deleted file mode 100644 index 8f90ca4866..0000000000 --- a/tests/exhaustive/autogen/gen02/expected/model_4_3.eprime.orig +++ /dev/null @@ -1,120 +0,0 @@ -language ESSENCE' 1.0 - -find var2_ExplicitVarSizeWithFlagsR4_Flags: matrix indexed by [int(1..4)] of bool -find var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Flags: - matrix indexed by [int(1..4), int(1..2)] of bool -find var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Values: - matrix indexed by [int(1..4), int(1..2)] of bool -find var2_ExplicitVarSizeWithFlagsR5_Flags: matrix indexed by [int(1..4)] of bool -find var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Marker: matrix indexed by [int(1..4)] of int(0..2) -find var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Values: - matrix indexed by [int(1..4), int(1..2)] of bool -branching on - [var2_ExplicitVarSizeWithFlagsR5_Flags, var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Marker, - var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Values, var2_ExplicitVarSizeWithFlagsR4_Flags, - var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Flags, - var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Values] -such that - or([var2_ExplicitVarSizeWithFlagsR4_Flags[q51] /\ - sum([toInt(var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Flags[q51, q52]) | q52 : int(1..2)]) - >= -7 - | q51 : int(1..4)]), - and([var2_ExplicitVarSizeWithFlagsR4_Flags[q2 + 1] -> - flatten([flatten([[-toInt(var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Flags[q2, q12]); - int(1)], - [-toInt(var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Values[q2, q12]); - int(1)]; - int(1..2)]) - | q12 : int(1..2)]) - - and([var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Flags[q3, q14] = false | q14 : int(1..2)]) - /\ - and([var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Values[q3, q15] = false - | q15 : int(1..2)]) - | q3 : int(1..4)]), - and([var2_ExplicitVarSizeWithFlagsR4_Flags[q4 + 1] -> var2_ExplicitVarSizeWithFlagsR4_Flags[q4] | q4 : int(1..3)]), - and([var2_ExplicitVarSizeWithFlagsR4_Flags[q6] -> - (var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Flags[q6, 2] -> - -toInt(var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Values[q6, 1]) < - -toInt(var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Values[q6, 2])) - | q6 : int(1..4)]), - and([var2_ExplicitVarSizeWithFlagsR4_Flags[q6] -> - and([var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Flags[q6, q8] = false -> - var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Values[q6, q8] = false - | q8 : int(1..2)]) - | q6 : int(1..4)]), - and([var2_ExplicitVarSizeWithFlagsR4_Flags[q6] -> - (var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Flags[q6, 2] -> - var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Flags[q6, 1]) - | q6 : int(1..4)]), - and([var2_ExplicitVarSizeWithFlagsR5_Flags[q16 + 1] -> - flatten([[var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Marker[q16]; int(1)], - [-toInt(var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Values[q16, q24]) - | q24 : int(1..2)]; - int(1..2)]) - - var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Marker[q17] = 0 /\ - and([var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Values[q17, q26] = false - | q26 : int(1..2)]) - | q17 : int(1..4)]), - and([var2_ExplicitVarSizeWithFlagsR5_Flags[q18 + 1] -> var2_ExplicitVarSizeWithFlagsR5_Flags[q18] - | q18 : int(1..3)]), - and([var2_ExplicitVarSizeWithFlagsR5_Flags[q20] -> - (2 <= var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Marker[q20] -> - -toInt(var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Values[q20, 1]) < - -toInt(var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Values[q20, 2])) - | q20 : int(1..4)]), - and([var2_ExplicitVarSizeWithFlagsR5_Flags[q20] -> - and([q22 > var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Marker[q20] -> - var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Values[q20, q22] = false - | q22 : int(1..2)]) - | q20 : int(1..4)]), - and([var2_ExplicitVarSizeWithFlagsR5_Flags[q28] -> - or([var2_ExplicitVarSizeWithFlagsR4_Flags[q30] /\ - (and([var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Flags[q30, q32] -> - or([q34 <= var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Marker[q28] /\ - var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Values[q28, q34] = - var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Values[q30, q32] - | q34 : int(1..2)]) - | q32 : int(1..2)]) - /\ - and([q36 <= var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Marker[q28] -> - or([var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Flags[q30, q38] /\ - var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Values[q30, q38] = - var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Values[q28, q36] - | q38 : int(1..2)]) - | q36 : int(1..2)])) - | q30 : int(1..4)]) - | q28 : int(1..4)]), - and([var2_ExplicitVarSizeWithFlagsR4_Flags[q40] -> - or([var2_ExplicitVarSizeWithFlagsR5_Flags[q42] /\ - (and([q44 <= var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Marker[q42] -> - or([var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Flags[q40, q46] /\ - var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Values[q40, q46] = - var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Values[q42, q44] - | q46 : int(1..2)]) - | q44 : int(1..2)]) - /\ - and([var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Flags[q40, q48] -> - or([q50 <= var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Marker[q42] /\ - var2_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Values[q42, q50] = - var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Values[q40, q48] - | q50 : int(1..2)]) - | q48 : int(1..2)])) - | q42 : int(1..4)]) - | q40 : int(1..4)]) - diff --git a/tests/exhaustive/autogen/gen02/expected/model_4_4-solution000001.solution b/tests/exhaustive/autogen/gen02/expected/model_4_4-solution000001.solution new file mode 100644 index 0000000000..19d999ca82 --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_4_4-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting var2 be {{}} diff --git a/tests/exhaustive/autogen/gen02/expected/model_4_4-solution000002.solution b/tests/exhaustive/autogen/gen02/expected/model_4_4-solution000002.solution new file mode 100644 index 0000000000..937293310f --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_4_4-solution000002.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting var2 be {{false}} +$ Visualisation for var2 +$ _ + diff --git a/tests/exhaustive/autogen/gen02/expected/model_4_4-solution000003.solution b/tests/exhaustive/autogen/gen02/expected/model_4_4-solution000003.solution new file mode 100644 index 0000000000..5a187652fa --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_4_4-solution000003.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting var2 be {{true}} +$ Visualisation for var2 +$ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_4_4-solution000004.solution b/tests/exhaustive/autogen/gen02/expected/model_4_4-solution000004.solution new file mode 100644 index 0000000000..0678d41bf8 --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_4_4-solution000004.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting var2 be {{false, true}} +$ Visualisation for var2 +$ _ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_4_4-solution000005.solution b/tests/exhaustive/autogen/gen02/expected/model_4_4-solution000005.solution new file mode 100644 index 0000000000..73f1bfe1ac --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_4_4-solution000005.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting var2 be {{}, {false}} +$ Visualisation for var2 +$ +$ _ + diff --git a/tests/exhaustive/autogen/gen02/expected/model_4_4-solution000006.solution b/tests/exhaustive/autogen/gen02/expected/model_4_4-solution000006.solution new file mode 100644 index 0000000000..d4c4a238b9 --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_4_4-solution000006.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting var2 be {{}, {true}} +$ Visualisation for var2 +$ +$ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_4_4-solution000007.solution b/tests/exhaustive/autogen/gen02/expected/model_4_4-solution000007.solution new file mode 100644 index 0000000000..2b6a8959da --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_4_4-solution000007.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting var2 be {{false}, {true}} +$ Visualisation for var2 +$ _ +$ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_4_4-solution000008.solution b/tests/exhaustive/autogen/gen02/expected/model_4_4-solution000008.solution new file mode 100644 index 0000000000..9c15a8e4e1 --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_4_4-solution000008.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting var2 be {{}, {false, true}} +$ Visualisation for var2 +$ +$ _ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_4_4-solution000009.solution b/tests/exhaustive/autogen/gen02/expected/model_4_4-solution000009.solution new file mode 100644 index 0000000000..b2e98e56a6 --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_4_4-solution000009.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting var2 be {{false}, {false, true}} +$ Visualisation for var2 +$ _ +$ _ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_4_4-solution000010.solution b/tests/exhaustive/autogen/gen02/expected/model_4_4-solution000010.solution new file mode 100644 index 0000000000..4fc309134f --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_4_4-solution000010.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting var2 be {{false, true}, {true}} +$ Visualisation for var2 +$ _ T +$ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_4_4-solution000011.solution b/tests/exhaustive/autogen/gen02/expected/model_4_4-solution000011.solution new file mode 100644 index 0000000000..70d0f91f38 --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_4_4-solution000011.solution @@ -0,0 +1,8 @@ +language Essence 1.3 + +letting var2 be {{}, {false}, {true}} +$ Visualisation for var2 +$ +$ _ +$ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_4_4-solution000012.solution b/tests/exhaustive/autogen/gen02/expected/model_4_4-solution000012.solution new file mode 100644 index 0000000000..ebc3fe4182 --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_4_4-solution000012.solution @@ -0,0 +1,8 @@ +language Essence 1.3 + +letting var2 be {{}, {false}, {false, true}} +$ Visualisation for var2 +$ +$ _ +$ _ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_4_4-solution000013.solution b/tests/exhaustive/autogen/gen02/expected/model_4_4-solution000013.solution new file mode 100644 index 0000000000..fa4340a533 --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_4_4-solution000013.solution @@ -0,0 +1,8 @@ +language Essence 1.3 + +letting var2 be {{}, {false, true}, {true}} +$ Visualisation for var2 +$ +$ _ T +$ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_4_4-solution000014.solution b/tests/exhaustive/autogen/gen02/expected/model_4_4-solution000014.solution new file mode 100644 index 0000000000..371f28aab7 --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_4_4-solution000014.solution @@ -0,0 +1,8 @@ +language Essence 1.3 + +letting var2 be {{false}, {false, true}, {true}} +$ Visualisation for var2 +$ _ +$ _ T +$ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_4_4-solution000015.solution b/tests/exhaustive/autogen/gen02/expected/model_4_4-solution000015.solution new file mode 100644 index 0000000000..35cfa328e8 --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_4_4-solution000015.solution @@ -0,0 +1,9 @@ +language Essence 1.3 + +letting var2 be {{}, {false}, {false, true}, {true}} +$ Visualisation for var2 +$ +$ _ +$ _ T +$ T + diff --git a/tests/exhaustive/autogen/gen02/expected/model_4_4.eprime b/tests/exhaustive/autogen/gen02/expected/model_4_4.eprime new file mode 100644 index 0000000000..e694258b7c --- /dev/null +++ b/tests/exhaustive/autogen/gen02/expected/model_4_4.eprime @@ -0,0 +1,52 @@ +language ESSENCE' 1.0 + +find var2_ExplicitVarSizeWithFlagsR4_Flags: matrix indexed by [int(1..4)] of bool +find var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Flags: + matrix indexed by [int(1..4), int(1..2)] of bool +find var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Values: + matrix indexed by [int(1..4), int(1..2)] of bool +branching on + [var2_ExplicitVarSizeWithFlagsR4_Flags, var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Flags, + var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Values] +such that + or([var2_ExplicitVarSizeWithFlagsR4_Flags[q16] /\ + sum([toInt(var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Flags[q16, q17]) | q17 : int(1..2)]) + >= -7 + | q16 : int(1..4)]), + and([var2_ExplicitVarSizeWithFlagsR4_Flags[q2 + 1] -> + flatten([flatten([[-toInt(var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Flags[q2, q12]); + int(1)], + [-toInt(var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Values[q2, q12]); + int(1)]; + int(1..2)]) + | q12 : int(1..2)]) + + and([var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Flags[q3, q14] = false | q14 : int(1..2)]) + /\ + and([var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Values[q3, q15] = false + | q15 : int(1..2)]) + | q3 : int(1..4)]), + and([var2_ExplicitVarSizeWithFlagsR4_Flags[q4 + 1] -> var2_ExplicitVarSizeWithFlagsR4_Flags[q4] | q4 : int(1..3)]), + and([var2_ExplicitVarSizeWithFlagsR4_Flags[q6] -> + (var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Flags[q6, 2] -> + -toInt(var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Values[q6, 1]) < + -toInt(var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Values[q6, 2])) + | q6 : int(1..4)]), + and([var2_ExplicitVarSizeWithFlagsR4_Flags[q6] -> + and([var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Flags[q6, q8] = false -> + var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Values[q6, q8] = false + | q8 : int(1..2)]) + | q6 : int(1..4)]), + and([var2_ExplicitVarSizeWithFlagsR4_Flags[q6] -> + (var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Flags[q6, 2] -> + var2_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Flags[q6, 1]) + | q6 : int(1..4)]) + diff --git a/tests/exhaustive/autogen/gen14_1/expected/model_1-solution000001.solution b/tests/exhaustive/autogen/gen14_1/expected/model_1-solution000001.solution new file mode 100644 index 0000000000..dc001498cc --- /dev/null +++ b/tests/exhaustive/autogen/gen14_1/expected/model_1-solution000001.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting var1 be partition({1, 2}) +$ Visualisation for var1 +$ 1 2 + diff --git a/tests/exhaustive/autogen/gen14_1/expected/model_1-solution000002.solution b/tests/exhaustive/autogen/gen14_1/expected/model_1-solution000002.solution new file mode 100644 index 0000000000..d53bf91bd1 --- /dev/null +++ b/tests/exhaustive/autogen/gen14_1/expected/model_1-solution000002.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting var1 be partition({1}, {2}) +$ Visualisation for var1 +$ 1 +$ 2 + diff --git a/tests/exhaustive/autogen/gen14_1/expected/model_1.eprime.orig b/tests/exhaustive/autogen/gen14_1/expected/model_1.eprime.orig deleted file mode 100644 index fcfc0075cb..0000000000 --- a/tests/exhaustive/autogen/gen14_1/expected/model_1.eprime.orig +++ /dev/null @@ -1,104 +0,0 @@ -language ESSENCE' 1.0 - -find var1_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker: int(0..2) -find var1_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence: matrix indexed by [int(1..2), int(1..2)] of bool -branching on - [var1_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker, - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence] -such that - !(and([q43 <= var1_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> - or([q47 <= var1_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ - (and([var1_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q47, q36] -> - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q43, q36] - | q36 : int(1..2)]) - /\ - and([var1_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q43, q37] -> - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q47, q37] - | q37 : int(1..2)])) - | q47 : int(1..2)]) - | q43 : int(1..2)]) - /\ - and([q49 <= var1_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> - or([q45 <= var1_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ - (and([var1_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q45, q40] -> - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q49, q40] - | q40 : int(1..2)]) - /\ - and([var1_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q49, q41] -> - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q45, q41] - | q41 : int(1..2)])) - | q45 : int(1..2)]) - | q49 : int(1..2)])) - \/ - !(and([q30 <= var1_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q30, 1] /\ - and([var1_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q30, q22] -> 1 = q22 - | q22 : int(1..2)]) - | q30 : int(1..2)]) - /\ - or([q32 <= var1_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ - (and([var1_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q32, q26] -> 1 = q26 - | q26 : int(1..2)]) - /\ var1_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q32, 1]) - | q32 : int(1..2)])) - \/ - !(and([q70 <= var1_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> - or([q74 <= var1_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ - (and([var1_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q74, q63] -> - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q70, q63] - | q63 : int(1..2)]) - /\ - and([var1_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q70, q64] -> - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q74, q64] - | q64 : int(1..2)])) - | q74 : int(1..2)]) - | q70 : int(1..2)]) - /\ - and([q76 <= var1_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> - or([q72 <= var1_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ - (and([var1_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q72, q67] -> - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q76, q67] - | q67 : int(1..2)]) - /\ - and([var1_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q76, q68] -> - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q72, q68] - | q68 : int(1..2)])) - | q72 : int(1..2)]) - | q76 : int(1..2)]) - \/ - or([q78 <= var1_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ - (and([var1_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q78, q53] -> 1 = q53 - | q53 : int(1..2)]) - /\ var1_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q78, 1]) - | q78 : int(1..2)]) - /\ - and([q80 <= var1_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q80, 1] /\ - and([var1_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q80, q59] -> 1 = q59 - | q59 : int(1..2)]) - | q80 : int(1..2)])), - and([1 = - sum([toInt(q14 <= var1_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q14, q1]) - | q14 : int(1..2)]) - | q1 : int(1..2)]), - and([q15 <= var1_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> - sum([toInt(var1_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q15, q16]) | q16 : int(1..2)]) >= - 1 | q15 : int(1..2)]), - 2 <= var1_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> - [-toInt(var1_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[1, q9]) | q9 : int(1..2)] var1_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> - and([var1_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q5, q11] = false | q11 : int(1..2)]) - | q5 : int(1..2)]), - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker <= 2, - and([q6 <= var1_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> - sum([toInt(var1_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q6, q7]) | q7 : int(1..2)]) <= 2 - | q6 : int(1..2)]), - 2 = - sum([toInt(q12 <= var1_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker) * - catchUndef(sum([toInt(var1_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q12, q13]) - | q13 : int(1..2)]), - 0) - | q12 : int(1..2)]) - diff --git a/tests/exhaustive/autogen/gen14_1/expected/model_2-solution000001.solution b/tests/exhaustive/autogen/gen14_1/expected/model_2-solution000001.solution new file mode 100644 index 0000000000..dc001498cc --- /dev/null +++ b/tests/exhaustive/autogen/gen14_1/expected/model_2-solution000001.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting var1 be partition({1, 2}) +$ Visualisation for var1 +$ 1 2 + diff --git a/tests/exhaustive/autogen/gen14_1/expected/model_2-solution000002.solution b/tests/exhaustive/autogen/gen14_1/expected/model_2-solution000002.solution new file mode 100644 index 0000000000..d53bf91bd1 --- /dev/null +++ b/tests/exhaustive/autogen/gen14_1/expected/model_2-solution000002.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting var1 be partition({1}, {2}) +$ Visualisation for var1 +$ 1 +$ 2 + diff --git a/tests/exhaustive/autogen/gen14_1/expected/model_2.eprime.orig b/tests/exhaustive/autogen/gen14_1/expected/model_2.eprime.orig deleted file mode 100644 index 357f1abe59..0000000000 --- a/tests/exhaustive/autogen/gen14_1/expected/model_2.eprime.orig +++ /dev/null @@ -1,174 +0,0 @@ -language ESSENCE' 1.0 - -find var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker: int(0..2) -find var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy: - matrix indexed by [int(1..2), int(1..2)] of int(1..3) -branching on - [var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker, - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy] -such that - !(and([q55 <= var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - or([q65 <= var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ - (and([var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q65, q66] != 3 -> - or([var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q55, q58] != 3 - /\ - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q55, q58] = - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q65, q66] - | q58 : int(1..2)]) - | q66 : int(1..2)]) - /\ - and([var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q55, q56] != 3 -> - or([var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q65, q68] != 3 - /\ - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q65, q68] = - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q55, q56] - | q68 : int(1..2)]) - | q56 : int(1..2)])) - | q65 : int(1..2)]) - | q55 : int(1..2)]) - /\ - and([q70 <= var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - or([q60 <= var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ - (and([var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q60, q61] != 3 -> - or([var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q70, q73] != 3 - /\ - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q70, q73] = - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q60, q61] - | q73 : int(1..2)]) - | q61 : int(1..2)]) - /\ - and([var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q70, q71] != 3 -> - or([var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q60, q63] != 3 - /\ - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q60, q63] = - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q70, q71] - | q63 : int(1..2)]) - | q71 : int(1..2)])) - | q60 : int(1..2)]) - | q70 : int(1..2)])) - \/ - !(and([q36 <= var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - or([var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q36, q39] != 3 /\ - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q36, q39] = 1 - | q39 : int(1..2)]) - /\ - and([var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q36, q37] != 3 -> - 1 = var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q36, q37] - | q37 : int(1..2)]) - | q36 : int(1..2)]) - /\ - or([q41 <= var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ - (and([var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q41, q42] != 3 -> - 1 = var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q41, q42] - | q42 : int(1..2)]) - /\ - or([var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q41, q44] != 3 /\ - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q41, q44] = 1 - | q44 : int(1..2)])) - | q41 : int(1..2)])) - \/ - !(and([q94 <= var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - or([q104 <= var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ - (and([var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q104, q105] != 3 -> - or([var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q94, q97] != 3 - /\ - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q94, q97] = - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q104, q105] - | q97 : int(1..2)]) - | q105 : int(1..2)]) - /\ - and([var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q94, q95] != 3 -> - or([var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q104, q107] != - 3 - /\ - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q104, q107] = - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q94, q95] - | q107 : int(1..2)]) - | q95 : int(1..2)])) - | q104 : int(1..2)]) - | q94 : int(1..2)]) - /\ - and([q109 <= var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - or([q99 <= var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ - (and([var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q99, q100] != 3 -> - or([var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q109, q112] != - 3 - /\ - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q109, q112] = - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q99, q100] - | q112 : int(1..2)]) - | q100 : int(1..2)]) - /\ - and([var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q109, q110] != 3 -> - or([var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q99, q102] != 3 - /\ - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q99, q102] = - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q109, q110] - | q102 : int(1..2)]) - | q110 : int(1..2)])) - | q99 : int(1..2)]) - | q109 : int(1..2)]) - \/ - or([q114 <= var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ - (and([var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q114, q115] != 3 -> - 1 = var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q114, q115] - | q115 : int(1..2)]) - /\ - or([var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q114, q117] != 3 /\ - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q114, q117] = 1 - | q117 : int(1..2)])) - | q114 : int(1..2)]) - /\ - and([q119 <= var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - or([var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q119, q122] != 3 /\ - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q119, q122] = 1 - | q122 : int(1..2)]) - /\ - and([var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q119, q120] != 3 -> - 1 = var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q119, q120] - | q120 : int(1..2)]) - | q119 : int(1..2)])), - alldifferent_except([toInt(q18 <= var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q18, q19] - != 3) - * - catchUndef(var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q18, q19], - 0) - | q18 : int(1..2), q19 : int(1..2)], - 0), - and([q20 <= var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - sum([toInt(var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q20, q22] != 3) - | q22 : int(1..2)]) - >= 1 - | q20 : int(1..2)]), - 2 <= var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - [var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[1, q12] | q12 : int(1..2)] var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - and([var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q5, q17] = 1 - | q17 : int(1..2)]) - | q5 : int(1..2)]), - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker <= 2, - and([q6 <= var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q6, 1] < - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q6, 2] - \/ var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q6, 1] = 3 - | q6 : int(1..2)]), - and([q6 <= var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - (var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q6, 1] = 3 -> - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q6, 2] = 3) - | q6 : int(1..2)]), - and([q6 <= var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - sum([toInt(var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q6, q9] != 3) - | q9 : int(1..2)]) - <= 2 - | q6 : int(1..2)]), - 2 = - sum([toInt(q14 <= var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker) * - catchUndef(sum([toInt(var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q14, q16] - != 3) - | q16 : int(1..2)]), - 0) - | q14 : int(1..2)]) - diff --git a/tests/exhaustive/autogen/gen14_1/expected/model_3-solution000001.solution b/tests/exhaustive/autogen/gen14_1/expected/model_3-solution000001.solution new file mode 100644 index 0000000000..dc001498cc --- /dev/null +++ b/tests/exhaustive/autogen/gen14_1/expected/model_3-solution000001.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting var1 be partition({1, 2}) +$ Visualisation for var1 +$ 1 2 + diff --git a/tests/exhaustive/autogen/gen14_1/expected/model_3-solution000002.solution b/tests/exhaustive/autogen/gen14_1/expected/model_3-solution000002.solution new file mode 100644 index 0000000000..d53bf91bd1 --- /dev/null +++ b/tests/exhaustive/autogen/gen14_1/expected/model_3-solution000002.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting var1 be partition({1}, {2}) +$ Visualisation for var1 +$ 1 +$ 2 + diff --git a/tests/exhaustive/autogen/gen14_1/expected/model_3.eprime.orig b/tests/exhaustive/autogen/gen14_1/expected/model_3.eprime.orig deleted file mode 100644 index 730eb14fca..0000000000 --- a/tests/exhaustive/autogen/gen14_1/expected/model_3.eprime.orig +++ /dev/null @@ -1,220 +0,0 @@ -language ESSENCE' 1.0 - -find var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker: int(0..2) -find var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker: - matrix indexed by [int(1..2)] of int(0..2) -find var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values: - matrix indexed by [int(1..2), int(1..2)] of int(1..2) -branching on - [var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker, - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker, - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values] -such that - !(and([q50 <= var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - or([q60 <= var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - (and([q61 <= var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q60] - -> - or([q53 <= - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q50] - /\ - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q50, q53] - = - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q60, q61] - | q53 : int(1..2)]) - | q61 : int(1..2)]) - /\ - and([q51 <= var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q50] - -> - or([q63 <= - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q60] - /\ - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q60, q63] - = - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q50, q51] - | q63 : int(1..2)]) - | q51 : int(1..2)])) - | q60 : int(1..2)]) - | q50 : int(1..2)]) - /\ - and([q65 <= var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - or([q55 <= var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - (and([q56 <= var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q55] - -> - or([q68 <= - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q65] - /\ - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q65, q68] - = - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q55, q56] - | q68 : int(1..2)]) - | q56 : int(1..2)]) - /\ - and([q66 <= var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q65] - -> - or([q58 <= - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q55] - /\ - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q55, q58] - = - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q65, q66] - | q58 : int(1..2)]) - | q66 : int(1..2)])) - | q55 : int(1..2)]) - | q65 : int(1..2)])) - \/ - !(and([q31 <= var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - or([q34 <= var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q31] /\ - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q31, q34] = 1 - | q34 : int(1..2)]) - /\ - and([q32 <= var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q31] -> - 1 = var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q31, q32] - | q32 : int(1..2)]) - | q31 : int(1..2)]) - /\ - or([q36 <= var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - (and([q37 <= var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q36] -> - 1 = var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q36, q37] - | q37 : int(1..2)]) - /\ - or([q39 <= var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q36] /\ - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q36, q39] = 1 - | q39 : int(1..2)])) - | q36 : int(1..2)])) - \/ - !(and([q89 <= var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - or([q99 <= var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - (and([q100 <= - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q99] - -> - or([q92 <= - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q89] - /\ - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q89, q92] - = - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q99, q100] - | q92 : int(1..2)]) - | q100 : int(1..2)]) - /\ - and([q90 <= var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q89] - -> - or([q102 <= - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q99] - /\ - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q99, q102] - = - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q89, q90] - | q102 : int(1..2)]) - | q90 : int(1..2)])) - | q99 : int(1..2)]) - | q89 : int(1..2)]) - /\ - and([q104 <= var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - or([q94 <= var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - (and([q95 <= var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q94] - -> - or([q107 <= - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q104] - /\ - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q104, q107] - = - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q94, q95] - | q107 : int(1..2)]) - | q95 : int(1..2)]) - /\ - and([q105 <= - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q104] - -> - or([q97 <= - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q94] - /\ - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q94, q97] - = - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q104, q105] - | q97 : int(1..2)]) - | q105 : int(1..2)])) - | q94 : int(1..2)]) - | q104 : int(1..2)]) - \/ - or([q109 <= var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - (and([q110 <= var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q109] -> - 1 = var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q109, q110] - | q110 : int(1..2)]) - /\ - or([q112 <= var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q109] /\ - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q109, q112] = 1 - | q112 : int(1..2)])) - | q109 : int(1..2)]) - /\ - and([q114 <= var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - or([q117 <= var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q114] /\ - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q114, q117] = 1 - | q117 : int(1..2)]) - /\ - and([q115 <= var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q114] -> - 1 = var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q114, q115] - | q115 : int(1..2)]) - | q114 : int(1..2)])), - alldifferent_except([toInt(q15 <= var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - q16 <= - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q15]) - * - catchUndef(var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q15, q16], - 0) - | q15 : int(1..2), q16 : int(1..2)], - 0), - and([q17 <= var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q17] >= 1 - | q17 : int(1..2)]), - 2 <= var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - flatten([[var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[1]; int(1)], - [var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[1, q11] - | q11 : int(1..2)]; - int(1..2)]) - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q5] = 0 /\ - and([var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q5, q14] = 1 - | q14 : int(1..2)]) - | q5 : int(1..2)]), - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker <= 2, - and([q6 <= var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - (2 <= var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q6] -> - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q6, 1] < - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q6, 2]) - | q6 : int(1..2)]), - and([q6 <= var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - and([q8 > var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q6] -> - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q6, q8] = 1 - | q8 : int(1..2)]) - | q6 : int(1..2)]), - and([q6 <= var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q6] <= 2 - | q6 : int(1..2)]), - 2 = - sum([toInt(q13 <= var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker) * - catchUndef(var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q13], 0) - | q13 : int(1..2)]) - diff --git a/tests/exhaustive/autogen/gen14_1/expected/model_4-solution000001.solution b/tests/exhaustive/autogen/gen14_1/expected/model_4-solution000001.solution new file mode 100644 index 0000000000..dc001498cc --- /dev/null +++ b/tests/exhaustive/autogen/gen14_1/expected/model_4-solution000001.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting var1 be partition({1, 2}) +$ Visualisation for var1 +$ 1 2 + diff --git a/tests/exhaustive/autogen/gen14_1/expected/model_4-solution000002.solution b/tests/exhaustive/autogen/gen14_1/expected/model_4-solution000002.solution new file mode 100644 index 0000000000..d53bf91bd1 --- /dev/null +++ b/tests/exhaustive/autogen/gen14_1/expected/model_4-solution000002.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting var1 be partition({1}, {2}) +$ Visualisation for var1 +$ 1 +$ 2 + diff --git a/tests/exhaustive/autogen/gen14_1/expected/model_4.eprime.orig b/tests/exhaustive/autogen/gen14_1/expected/model_4.eprime.orig deleted file mode 100644 index cf8cf69ad9..0000000000 --- a/tests/exhaustive/autogen/gen14_1/expected/model_4.eprime.orig +++ /dev/null @@ -1,97 +0,0 @@ -language ESSENCE' 1.0 - -find var1_PartitionOccurrence_NumParts: int(1..2) -find var1_PartitionOccurrence_WhichPart: matrix indexed by [int(1..2)] of int(1..2) -find var1_PartitionOccurrence_PartSizes: matrix indexed by [int(1..2)] of int(0..2) -find var1_PartitionOccurrence_FirstIndex: matrix indexed by [int(1..2)] of int(1..2) -branching on - [var1_PartitionOccurrence_NumParts, var1_PartitionOccurrence_WhichPart, var1_PartitionOccurrence_PartSizes, - var1_PartitionOccurrence_FirstIndex] -such that - !(and([q42 <= var1_PartitionOccurrence_NumParts -> - or([q52 <= var1_PartitionOccurrence_NumParts /\ - (and([var1_PartitionOccurrence_WhichPart[q54] = q52 -> - or([var1_PartitionOccurrence_WhichPart[q45] = q42 /\ q45 = q54 | q45 : int(1..2)]) - | q54 : int(1..2)]) - /\ - and([var1_PartitionOccurrence_WhichPart[q46] = q42 -> - or([var1_PartitionOccurrence_WhichPart[q56] = q52 /\ q56 = q46 | q56 : int(1..2)]) - | q46 : int(1..2)])) - | q52 : int(1..2)]) - | q42 : int(1..2)]) - /\ - and([q57 <= var1_PartitionOccurrence_NumParts -> - or([q47 <= var1_PartitionOccurrence_NumParts /\ - (and([var1_PartitionOccurrence_WhichPart[q49] = q47 -> - or([var1_PartitionOccurrence_WhichPart[q60] = q57 /\ q60 = q49 | q60 : int(1..2)]) - | q49 : int(1..2)]) - /\ - and([var1_PartitionOccurrence_WhichPart[q61] = q57 -> - or([var1_PartitionOccurrence_WhichPart[q51] = q47 /\ q51 = q61 | q51 : int(1..2)]) - | q61 : int(1..2)])) - | q47 : int(1..2)]) - | q57 : int(1..2)])) - \/ - !(and([q23 <= var1_PartitionOccurrence_NumParts -> - or([var1_PartitionOccurrence_WhichPart[q27] = q23 /\ q27 = 1 | q27 : int(1..2)]) /\ - and([var1_PartitionOccurrence_WhichPart[q25] = q23 -> 1 = q25 | q25 : int(1..2)]) - | q23 : int(1..2)]) - /\ - or([q28 <= var1_PartitionOccurrence_NumParts /\ - (and([var1_PartitionOccurrence_WhichPart[q30] = q28 -> 1 = q30 | q30 : int(1..2)]) /\ - or([var1_PartitionOccurrence_WhichPart[q32] = q28 /\ q32 = 1 | q32 : int(1..2)])) - | q28 : int(1..2)])) - \/ - !(and([q81 <= var1_PartitionOccurrence_NumParts -> - or([q91 <= var1_PartitionOccurrence_NumParts /\ - (and([var1_PartitionOccurrence_WhichPart[q93] = q91 -> - or([var1_PartitionOccurrence_WhichPart[q84] = q81 /\ q84 = q93 | q84 : int(1..2)]) - | q93 : int(1..2)]) - /\ - and([var1_PartitionOccurrence_WhichPart[q85] = q81 -> - or([var1_PartitionOccurrence_WhichPart[q95] = q91 /\ q95 = q85 | q95 : int(1..2)]) - | q85 : int(1..2)])) - | q91 : int(1..2)]) - | q81 : int(1..2)]) - /\ - and([q96 <= var1_PartitionOccurrence_NumParts -> - or([q86 <= var1_PartitionOccurrence_NumParts /\ - (and([var1_PartitionOccurrence_WhichPart[q88] = q86 -> - or([var1_PartitionOccurrence_WhichPart[q99] = q96 /\ q99 = q88 | q99 : int(1..2)]) - | q88 : int(1..2)]) - /\ - and([var1_PartitionOccurrence_WhichPart[q100] = q96 -> - or([var1_PartitionOccurrence_WhichPart[q90] = q86 /\ q90 = q100 | q90 : int(1..2)]) - | q100 : int(1..2)])) - | q86 : int(1..2)]) - | q96 : int(1..2)]) - \/ - or([q101 <= var1_PartitionOccurrence_NumParts /\ - (and([var1_PartitionOccurrence_WhichPart[q103] = q101 -> 1 = q103 | q103 : int(1..2)]) /\ - or([var1_PartitionOccurrence_WhichPart[q105] = q101 /\ q105 = 1 | q105 : int(1..2)])) - | q101 : int(1..2)]) - /\ - and([q106 <= var1_PartitionOccurrence_NumParts -> - or([var1_PartitionOccurrence_WhichPart[q110] = q106 /\ q110 = 1 | q110 : int(1..2)]) /\ - and([var1_PartitionOccurrence_WhichPart[q108] = q106 -> 1 = q108 | q108 : int(1..2)]) - | q106 : int(1..2)])), - and([q1 <= var1_PartitionOccurrence_NumParts -> var1_PartitionOccurrence_PartSizes[q1] <= 2 | q1 : int(1..2)]), - and([q1 > var1_PartitionOccurrence_NumParts -> var1_PartitionOccurrence_PartSizes[q1] = 0 | q1 : int(1..2)]), - var1_PartitionOccurrence_NumParts <= 2, - var1_PartitionOccurrence_NumParts = max([var1_PartitionOccurrence_WhichPart[q4] | q4 : int(1..2)]), - and([var1_PartitionOccurrence_PartSizes[q5] = - sum([toInt(var1_PartitionOccurrence_WhichPart[q6] = q5) | q6 : int(1..2)]) - | q5 : int(1..2)]), - and([q7 <= var1_PartitionOccurrence_NumParts -> - and([var1_PartitionOccurrence_WhichPart[q8] = q7 -> var1_PartitionOccurrence_FirstIndex[q7] <= q8 - | q8 : int(1..2)]) - | q7 : int(1..2)]), - and([q7 <= var1_PartitionOccurrence_NumParts -> - or([var1_PartitionOccurrence_WhichPart[q8] = q7 /\ var1_PartitionOccurrence_FirstIndex[q7] = q8 - | q8 : int(1..2)]) - | q7 : int(1..2)]), - and([q7 > var1_PartitionOccurrence_NumParts -> var1_PartitionOccurrence_FirstIndex[q7] = 1 | q7 : int(1..2)]), - and([q9 <= var1_PartitionOccurrence_NumParts /\ q10 <= var1_PartitionOccurrence_NumParts -> - (q9 < q10 <-> var1_PartitionOccurrence_FirstIndex[q9] < var1_PartitionOccurrence_FirstIndex[q10]) - | q9 : int(1..2), q10 : int(1..2)]) - diff --git a/tests/exhaustive/autogen/gen14_2/expected/model_1-solution000001.solution b/tests/exhaustive/autogen/gen14_2/expected/model_1-solution000001.solution new file mode 100644 index 0000000000..dc001498cc --- /dev/null +++ b/tests/exhaustive/autogen/gen14_2/expected/model_1-solution000001.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting var1 be partition({1, 2}) +$ Visualisation for var1 +$ 1 2 + diff --git a/tests/exhaustive/autogen/gen14_2/expected/model_1-solution000002.solution b/tests/exhaustive/autogen/gen14_2/expected/model_1-solution000002.solution new file mode 100644 index 0000000000..d53bf91bd1 --- /dev/null +++ b/tests/exhaustive/autogen/gen14_2/expected/model_1-solution000002.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting var1 be partition({1}, {2}) +$ Visualisation for var1 +$ 1 +$ 2 + diff --git a/tests/exhaustive/autogen/gen14_2/expected/model_1.eprime b/tests/exhaustive/autogen/gen14_2/expected/model_1.eprime new file mode 100644 index 0000000000..1f3c94bad0 --- /dev/null +++ b/tests/exhaustive/autogen/gen14_2/expected/model_1.eprime @@ -0,0 +1,38 @@ +language ESSENCE' 1.0 + +find var1_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker: int(0..2) +find var1_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence: matrix indexed by [int(1..2), int(1..2)] of bool +branching on + [var1_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker, + var1_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence] +such that + var1_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker = var1_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker, + and([and([var1_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q17, q19] = + var1_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q17, q19] + | q19 : int(1..2)]) + | q17 : int(1..2)]), + and([1 = + sum([toInt(q14 <= var1_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ + var1_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q14, q1]) + | q14 : int(1..2)]) + | q1 : int(1..2)]), + and([q15 <= var1_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> + sum([toInt(var1_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q15, q16]) | q16 : int(1..2)]) >= + 1 | q15 : int(1..2)]), + 2 <= var1_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> + [-toInt(var1_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[1, q9]) | q9 : int(1..2)] var1_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> + and([var1_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q5, q11] = false | q11 : int(1..2)]) + | q5 : int(1..2)]), + var1_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker <= 2, + and([q6 <= var1_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> + sum([toInt(var1_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q6, q7]) | q7 : int(1..2)]) <= 2 + | q6 : int(1..2)]), + 2 = + sum([toInt(q12 <= var1_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker) * + catchUndef(sum([toInt(var1_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q12, q13]) + | q13 : int(1..2)]), + 0) + | q12 : int(1..2)]) + diff --git a/tests/exhaustive/autogen/gen14_2/expected/model_2-solution000001.solution b/tests/exhaustive/autogen/gen14_2/expected/model_2-solution000001.solution new file mode 100644 index 0000000000..dc001498cc --- /dev/null +++ b/tests/exhaustive/autogen/gen14_2/expected/model_2-solution000001.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting var1 be partition({1, 2}) +$ Visualisation for var1 +$ 1 2 + diff --git a/tests/exhaustive/autogen/gen14_2/expected/model_2-solution000002.solution b/tests/exhaustive/autogen/gen14_2/expected/model_2-solution000002.solution new file mode 100644 index 0000000000..d53bf91bd1 --- /dev/null +++ b/tests/exhaustive/autogen/gen14_2/expected/model_2-solution000002.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting var1 be partition({1}, {2}) +$ Visualisation for var1 +$ 1 +$ 2 + diff --git a/tests/exhaustive/autogen/gen14_2/expected/model_2.eprime b/tests/exhaustive/autogen/gen14_2/expected/model_2.eprime new file mode 100644 index 0000000000..0da1c335c9 --- /dev/null +++ b/tests/exhaustive/autogen/gen14_2/expected/model_2.eprime @@ -0,0 +1,58 @@ +language ESSENCE' 1.0 + +find var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker: int(0..2) +find var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy: + matrix indexed by [int(1..2), int(1..2)] of int(1..3) +branching on + [var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker, + var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy] +such that + var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker = var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker, + and([and([var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q18, q20] = + var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q18, q20] + | q20 : int(1..2)]) + | q18 : int(1..2)]), + alldifferent_except([toInt(q22 <= var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ + var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q22, q23] + != 3) + * + catchUndef(var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q22, q23], + 0) + | q22 : int(1..2), q23 : int(1..2)], + 0), + and([q24 <= var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> + sum([toInt(var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q24, q26] != 3) + | q26 : int(1..2)]) + >= 1 + | q24 : int(1..2)]), + 2 <= var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> + [var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[1, q12] | q12 : int(1..2)] var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> + and([var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q5, q17] = 1 + | q17 : int(1..2)]) + | q5 : int(1..2)]), + var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker <= 2, + and([q6 <= var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> + var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q6, 1] < + var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q6, 2] + \/ var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q6, 1] = 3 + | q6 : int(1..2)]), + and([q6 <= var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> + (var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q6, 1] = 3 -> + var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q6, 2] = 3) + | q6 : int(1..2)]), + and([q6 <= var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> + sum([toInt(var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q6, q9] != 3) + | q9 : int(1..2)]) + <= 2 + | q6 : int(1..2)]), + 2 = + sum([toInt(q14 <= var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker) * + catchUndef(sum([toInt(var1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q14, q16] + != 3) + | q16 : int(1..2)]), + 0) + | q14 : int(1..2)]) + diff --git a/tests/exhaustive/autogen/gen14_2/expected/model_3-solution000001.solution b/tests/exhaustive/autogen/gen14_2/expected/model_3-solution000001.solution new file mode 100644 index 0000000000..dc001498cc --- /dev/null +++ b/tests/exhaustive/autogen/gen14_2/expected/model_3-solution000001.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting var1 be partition({1, 2}) +$ Visualisation for var1 +$ 1 2 + diff --git a/tests/exhaustive/autogen/gen14_2/expected/model_3-solution000002.solution b/tests/exhaustive/autogen/gen14_2/expected/model_3-solution000002.solution new file mode 100644 index 0000000000..d53bf91bd1 --- /dev/null +++ b/tests/exhaustive/autogen/gen14_2/expected/model_3-solution000002.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting var1 be partition({1}, {2}) +$ Visualisation for var1 +$ 1 +$ 2 + diff --git a/tests/exhaustive/autogen/gen14_2/expected/model_3.eprime.orig b/tests/exhaustive/autogen/gen14_2/expected/model_3.eprime.orig deleted file mode 100644 index 7cec03b856..0000000000 --- a/tests/exhaustive/autogen/gen14_2/expected/model_3.eprime.orig +++ /dev/null @@ -1,67 +0,0 @@ -language ESSENCE' 1.0 - -find var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker: int(0..2) -find var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker: - matrix indexed by [int(1..2)] of int(0..2) -find var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values: - matrix indexed by [int(1..2), int(1..2)] of int(1..2) -branching on - [var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker, - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker, - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values] -such that - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker = var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker, - and([var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q15] = - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q15] - | q15 : int(1..2)]), - and([and([var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q17, q19] = - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q17, q19] - | q19 : int(1..2)]) - | q17 : int(1..2)]), - alldifferent_except([toInt(q21 <= var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - q22 <= - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q21]) - * - catchUndef(var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q21, q22], - 0) - | q21 : int(1..2), q22 : int(1..2)], - 0), - and([q23 <= var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q23] >= 1 - | q23 : int(1..2)]), - 2 <= var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - flatten([[var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[1]; int(1)], - [var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[1, q11] - | q11 : int(1..2)]; - int(1..2)]) - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q5] = 0 /\ - and([var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q5, q14] = 1 - | q14 : int(1..2)]) - | q5 : int(1..2)]), - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker <= 2, - and([q6 <= var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - (2 <= var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q6] -> - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q6, 1] < - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q6, 2]) - | q6 : int(1..2)]), - and([q6 <= var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - and([q8 > var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q6] -> - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q6, q8] = 1 - | q8 : int(1..2)]) - | q6 : int(1..2)]), - and([q6 <= var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q6] <= 2 - | q6 : int(1..2)]), - 2 = - sum([toInt(q13 <= var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker) * - catchUndef(var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q13], 0) - | q13 : int(1..2)]) - diff --git a/tests/exhaustive/autogen/gen14_2/expected/model_4-solution000001.solution b/tests/exhaustive/autogen/gen14_2/expected/model_4-solution000001.solution new file mode 100644 index 0000000000..dc001498cc --- /dev/null +++ b/tests/exhaustive/autogen/gen14_2/expected/model_4-solution000001.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting var1 be partition({1, 2}) +$ Visualisation for var1 +$ 1 2 + diff --git a/tests/exhaustive/autogen/gen14_2/expected/model_4-solution000002.solution b/tests/exhaustive/autogen/gen14_2/expected/model_4-solution000002.solution new file mode 100644 index 0000000000..d53bf91bd1 --- /dev/null +++ b/tests/exhaustive/autogen/gen14_2/expected/model_4-solution000002.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting var1 be partition({1}, {2}) +$ Visualisation for var1 +$ 1 +$ 2 + diff --git a/tests/exhaustive/autogen/gen14_2/expected/model_4.eprime b/tests/exhaustive/autogen/gen14_2/expected/model_4.eprime new file mode 100644 index 0000000000..dadf615aea --- /dev/null +++ b/tests/exhaustive/autogen/gen14_2/expected/model_4.eprime @@ -0,0 +1,34 @@ +language ESSENCE' 1.0 + +find var1_PartitionOccurrence_NumParts: int(1..2) +find var1_PartitionOccurrence_WhichPart: matrix indexed by [int(1..2)] of int(1..2) +find var1_PartitionOccurrence_PartSizes: matrix indexed by [int(1..2)] of int(0..2) +find var1_PartitionOccurrence_FirstIndex: matrix indexed by [int(1..2)] of int(1..2) +branching on + [var1_PartitionOccurrence_NumParts, var1_PartitionOccurrence_WhichPart, var1_PartitionOccurrence_PartSizes, + var1_PartitionOccurrence_FirstIndex] +such that + var1_PartitionOccurrence_NumParts = var1_PartitionOccurrence_NumParts, + and([var1_PartitionOccurrence_WhichPart[q11] = var1_PartitionOccurrence_WhichPart[q11] | q11 : int(1..2)]), + and([var1_PartitionOccurrence_PartSizes[q13] = var1_PartitionOccurrence_PartSizes[q13] | q13 : int(1..2)]), + and([var1_PartitionOccurrence_FirstIndex[q15] = var1_PartitionOccurrence_FirstIndex[q15] | q15 : int(1..2)]), + and([q1 <= var1_PartitionOccurrence_NumParts -> var1_PartitionOccurrence_PartSizes[q1] <= 2 | q1 : int(1..2)]), + and([q1 > var1_PartitionOccurrence_NumParts -> var1_PartitionOccurrence_PartSizes[q1] = 0 | q1 : int(1..2)]), + var1_PartitionOccurrence_NumParts <= 2, + var1_PartitionOccurrence_NumParts = max([var1_PartitionOccurrence_WhichPart[q4] | q4 : int(1..2)]), + and([var1_PartitionOccurrence_PartSizes[q5] = + sum([toInt(var1_PartitionOccurrence_WhichPart[q6] = q5) | q6 : int(1..2)]) + | q5 : int(1..2)]), + and([q7 <= var1_PartitionOccurrence_NumParts -> + and([var1_PartitionOccurrence_WhichPart[q8] = q7 -> var1_PartitionOccurrence_FirstIndex[q7] <= q8 + | q8 : int(1..2)]) + | q7 : int(1..2)]), + and([q7 <= var1_PartitionOccurrence_NumParts -> + or([var1_PartitionOccurrence_WhichPart[q8] = q7 /\ var1_PartitionOccurrence_FirstIndex[q7] = q8 + | q8 : int(1..2)]) + | q7 : int(1..2)]), + and([q7 > var1_PartitionOccurrence_NumParts -> var1_PartitionOccurrence_FirstIndex[q7] = 1 | q7 : int(1..2)]), + and([q9 <= var1_PartitionOccurrence_NumParts /\ q10 <= var1_PartitionOccurrence_NumParts -> + (q9 < q10 <-> var1_PartitionOccurrence_FirstIndex[q9] < var1_PartitionOccurrence_FirstIndex[q10]) + | q9 : int(1..2), q10 : int(1..2)]) + diff --git a/tests/exhaustive/autogen/gen17/expected/model_1.eprime b/tests/exhaustive/autogen/gen17/expected/model_1.eprime index f2c7967cf9..b7c8b7620b 100644 --- a/tests/exhaustive/autogen/gen17/expected/model_1.eprime +++ b/tests/exhaustive/autogen/gen17/expected/model_1.eprime @@ -6,8 +6,7 @@ branching on [var1_ExplicitVarSizeWithMarker_Marker, var1_ExplicitVarSizeWithMar such that false, 2 <= var1_ExplicitVarSizeWithMarker_Marker -> - [-toInt(var1_ExplicitVarSizeWithMarker_Values[1]); int(1)] var1_ExplicitVarSizeWithMarker_Marker -> var1_ExplicitVarSizeWithMarker_Values[q2] = false | q2 : int(1..2)]) diff --git a/tests/exhaustive/autogen/gen17/expected/model_2.eprime b/tests/exhaustive/autogen/gen17/expected/model_2.eprime index be44a8c757..b7d0c50001 100644 --- a/tests/exhaustive/autogen/gen17/expected/model_2.eprime +++ b/tests/exhaustive/autogen/gen17/expected/model_2.eprime @@ -6,8 +6,7 @@ branching on [var1_ExplicitVarSizeWithFlags_Flags, var1_ExplicitVarSizeWithFlags such that false, var1_ExplicitVarSizeWithFlags_Flags[2] -> - [-toInt(var1_ExplicitVarSizeWithFlags_Values[1]); int(1)] var1_ExplicitVarSizeWithFlags_Values[q2] = false | q2 : int(1..2)]), var1_ExplicitVarSizeWithFlags_Flags[2] -> var1_ExplicitVarSizeWithFlags_Flags[1] diff --git a/tests/exhaustive/autogen/gen25/expected/model_1.eprime b/tests/exhaustive/autogen/gen25/expected/model_1.eprime index 7a7abed767..b1b11d3b44 100644 --- a/tests/exhaustive/autogen/gen25/expected/model_1.eprime +++ b/tests/exhaustive/autogen/gen25/expected/model_1.eprime @@ -6,8 +6,7 @@ find var3_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..5)] of boo branching on [var3_ExplicitVarSizeWithMarker_Marker, var3_ExplicitVarSizeWithMarker_Values] such that and([q1 + 1 <= var3_ExplicitVarSizeWithMarker_Marker -> - [-toInt(var3_ExplicitVarSizeWithMarker_Values[q1]); int(1)] var3_ExplicitVarSizeWithMarker_Marker -> var3_ExplicitVarSizeWithMarker_Values[q2] = false | q2 : int(1..5)]), diff --git a/tests/exhaustive/autogen/gen25/expected/model_2.eprime b/tests/exhaustive/autogen/gen25/expected/model_2.eprime index 2f3be37f18..daa108ae03 100644 --- a/tests/exhaustive/autogen/gen25/expected/model_2.eprime +++ b/tests/exhaustive/autogen/gen25/expected/model_2.eprime @@ -6,8 +6,7 @@ find var3_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..5)] of bool branching on [var3_ExplicitVarSizeWithFlags_Flags, var3_ExplicitVarSizeWithFlags_Values] such that and([var3_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - [-toInt(var3_ExplicitVarSizeWithFlags_Values[q1]); int(1)] var3_ExplicitVarSizeWithFlags_Values[q2] = false | q2 : int(1..5)]), diff --git a/tests/exhaustive/autogen/gen32/expected/model_1_1_1.eprime b/tests/exhaustive/autogen/gen32/expected/model_1_1_1.eprime new file mode 100644 index 0000000000..2e44586da2 --- /dev/null +++ b/tests/exhaustive/autogen/gen32/expected/model_1_1_1.eprime @@ -0,0 +1,9 @@ +language ESSENCE' 1.0 + +letting let1 be -4 +find var2_Occurrence: matrix indexed by [int(-4..5, 2)] of bool +branching on [var2_Occurrence] +such that + or([var2_Occurrence[q2] /\ !var2_Occurrence[q2] | q2 : int(-4..5, 2)]) \/ + or([var2_Occurrence[q2] /\ !var2_Occurrence[q2] | q2 : int(-4..5, 2)]) + diff --git a/tests/exhaustive/autogen/gen32/expected/model_1_1_2.eprime b/tests/exhaustive/autogen/gen32/expected/model_1_1_2.eprime new file mode 100644 index 0000000000..5d9dfb9509 --- /dev/null +++ b/tests/exhaustive/autogen/gen32/expected/model_1_1_2.eprime @@ -0,0 +1,19 @@ +language ESSENCE' 1.0 + +letting let1 be -4 +find var2_Occurrence: matrix indexed by [int(-4..5, 2)] of bool +find var2_ExplicitVarSizeWithDummy: matrix indexed by [int(1..11)] of int(-4..5, 2, 6) +branching on [var2_ExplicitVarSizeWithDummy, var2_Occurrence] +such that + or([var2_Occurrence[q11] /\ !var2_Occurrence[q11] | q11 : int(-4..5, 2)]) \/ + or([var2_Occurrence[q11] /\ !var2_Occurrence[q11] | q11 : int(-4..5, 2)]), + and([var2_ExplicitVarSizeWithDummy[q2] < var2_ExplicitVarSizeWithDummy[q2 + 1] \/ + var2_ExplicitVarSizeWithDummy[q2] = 6 + | q2 : int(1..10)]), + and([var2_ExplicitVarSizeWithDummy[q3] = 6 -> var2_ExplicitVarSizeWithDummy[q3 + 1] = 6 | q3 : int(1..10)]), + and([var2_ExplicitVarSizeWithDummy[q7] != 6 -> var2_Occurrence[var2_ExplicitVarSizeWithDummy[q7]] + | q7 : int(1..11)]), + and([var2_Occurrence[q8] -> + or([var2_ExplicitVarSizeWithDummy[q10] != 6 /\ var2_ExplicitVarSizeWithDummy[q10] = q8 | q10 : int(1..11)]) + | q8 : int(-4..5, 2)]) + diff --git a/tests/exhaustive/autogen/gen32/expected/model_1_1_3.eprime b/tests/exhaustive/autogen/gen32/expected/model_1_1_3.eprime new file mode 100644 index 0000000000..b7f0533fd6 --- /dev/null +++ b/tests/exhaustive/autogen/gen32/expected/model_1_1_3.eprime @@ -0,0 +1,22 @@ +language ESSENCE' 1.0 + +letting let1 be -4 +find var2_Occurrence: matrix indexed by [int(-4..5, 2)] of bool +find var2_ExplicitVarSizeWithMarker_Marker: int(0..11) +find var2_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..11)] of int(-4..5, 2) +branching on [var2_ExplicitVarSizeWithMarker_Marker, var2_ExplicitVarSizeWithMarker_Values, var2_Occurrence] +such that + or([var2_Occurrence[q10] /\ !var2_Occurrence[q10] | q10 : int(-4..5, 2)]) \/ + or([var2_Occurrence[q10] /\ !var2_Occurrence[q10] | q10 : int(-4..5, 2)]), + and([q2 + 1 <= var2_ExplicitVarSizeWithMarker_Marker -> + var2_ExplicitVarSizeWithMarker_Values[q2] < var2_ExplicitVarSizeWithMarker_Values[q2 + 1] + | q2 : int(1..10)]), + and([q3 > var2_ExplicitVarSizeWithMarker_Marker -> var2_ExplicitVarSizeWithMarker_Values[q3] = -4 + | q3 : int(1..11)]), + and([q6 <= var2_ExplicitVarSizeWithMarker_Marker -> var2_Occurrence[var2_ExplicitVarSizeWithMarker_Values[q6]] + | q6 : int(1..11)]), + and([var2_Occurrence[q7] -> + or([q9 <= var2_ExplicitVarSizeWithMarker_Marker /\ var2_ExplicitVarSizeWithMarker_Values[q9] = q7 + | q9 : int(1..11)]) + | q7 : int(-4..5, 2)]) + diff --git a/tests/exhaustive/autogen/gen32/expected/model_1_1_4.eprime b/tests/exhaustive/autogen/gen32/expected/model_1_1_4.eprime new file mode 100644 index 0000000000..bd003c9167 --- /dev/null +++ b/tests/exhaustive/autogen/gen32/expected/model_1_1_4.eprime @@ -0,0 +1,23 @@ +language ESSENCE' 1.0 + +letting let1 be -4 +find var2_Occurrence: matrix indexed by [int(-4..5, 2)] of bool +find var2_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..11)] of bool +find var2_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..11)] of int(-4..5, 2) +branching on [var2_ExplicitVarSizeWithFlags_Flags, var2_ExplicitVarSizeWithFlags_Values, var2_Occurrence] +such that + or([var2_Occurrence[q12] /\ !var2_Occurrence[q12] | q12 : int(-4..5, 2)]) \/ + or([var2_Occurrence[q12] /\ !var2_Occurrence[q12] | q12 : int(-4..5, 2)]), + and([var2_ExplicitVarSizeWithFlags_Flags[q2 + 1] -> + var2_ExplicitVarSizeWithFlags_Values[q2] < var2_ExplicitVarSizeWithFlags_Values[q2 + 1] + | q2 : int(1..10)]), + and([var2_ExplicitVarSizeWithFlags_Flags[q3] = false -> var2_ExplicitVarSizeWithFlags_Values[q3] = -4 + | q3 : int(1..11)]), + and([var2_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> var2_ExplicitVarSizeWithFlags_Flags[q4] | q4 : int(1..10)]), + and([var2_ExplicitVarSizeWithFlags_Flags[q8] -> var2_Occurrence[var2_ExplicitVarSizeWithFlags_Values[q8]] + | q8 : int(1..11)]), + and([var2_Occurrence[q9] -> + or([var2_ExplicitVarSizeWithFlags_Flags[q11] /\ var2_ExplicitVarSizeWithFlags_Values[q11] = q9 + | q11 : int(1..11)]) + | q9 : int(-4..5, 2)]) + diff --git a/tests/exhaustive/autogen/gen32/expected/model_1_2_1.eprime b/tests/exhaustive/autogen/gen32/expected/model_1_2_1.eprime new file mode 100644 index 0000000000..7ba618afa0 --- /dev/null +++ b/tests/exhaustive/autogen/gen32/expected/model_1_2_1.eprime @@ -0,0 +1,23 @@ +language ESSENCE' 1.0 + +letting let1 be -4 +find var2_Occurrence: matrix indexed by [int(-4..5, 2)] of bool +find var2_ExplicitVarSizeWithDummy: matrix indexed by [int(1..11)] of int(-4..5, 2, 6) +branching on [var2_ExplicitVarSizeWithDummy, var2_Occurrence] +such that + or([var2_Occurrence[q11] /\ + !or([var2_ExplicitVarSizeWithDummy[q13] != 6 /\ var2_ExplicitVarSizeWithDummy[q13] = q11 | q13 : int(1..11)]) + | q11 : int(-4..5, 2)]) + \/ + or([var2_ExplicitVarSizeWithDummy[q14] != 6 /\ !var2_Occurrence[var2_ExplicitVarSizeWithDummy[q14]] + | q14 : int(1..11)]), + and([var2_ExplicitVarSizeWithDummy[q2] < var2_ExplicitVarSizeWithDummy[q2 + 1] \/ + var2_ExplicitVarSizeWithDummy[q2] = 6 + | q2 : int(1..10)]), + and([var2_ExplicitVarSizeWithDummy[q3] = 6 -> var2_ExplicitVarSizeWithDummy[q3 + 1] = 6 | q3 : int(1..10)]), + and([var2_ExplicitVarSizeWithDummy[q7] != 6 -> var2_Occurrence[var2_ExplicitVarSizeWithDummy[q7]] + | q7 : int(1..11)]), + and([var2_Occurrence[q8] -> + or([var2_ExplicitVarSizeWithDummy[q10] != 6 /\ var2_ExplicitVarSizeWithDummy[q10] = q8 | q10 : int(1..11)]) + | q8 : int(-4..5, 2)]) + diff --git a/tests/exhaustive/autogen/gen32/expected/model_1_2_3.eprime b/tests/exhaustive/autogen/gen32/expected/model_1_2_3.eprime new file mode 100644 index 0000000000..9722a2c244 --- /dev/null +++ b/tests/exhaustive/autogen/gen32/expected/model_1_2_3.eprime @@ -0,0 +1,48 @@ +language ESSENCE' 1.0 + +letting let1 be -4 +find var2_Occurrence: matrix indexed by [int(-4..5, 2)] of bool +find var2_ExplicitVarSizeWithDummy: matrix indexed by [int(1..11)] of int(-4..5, 2, 6) +find var2_ExplicitVarSizeWithMarker_Marker: int(0..11) +find var2_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..11)] of int(-4..5, 2) +branching on + [var2_ExplicitVarSizeWithMarker_Marker, var2_ExplicitVarSizeWithMarker_Values, var2_Occurrence, + var2_ExplicitVarSizeWithDummy] +such that + or([var2_Occurrence[q27] /\ + !or([var2_ExplicitVarSizeWithDummy[q29] != 6 /\ var2_ExplicitVarSizeWithDummy[q29] = q27 | q29 : int(1..11)]) + | q27 : int(-4..5, 2)]) + \/ + or([var2_ExplicitVarSizeWithDummy[q30] != 6 /\ !var2_Occurrence[var2_ExplicitVarSizeWithDummy[q30]] + | q30 : int(1..11)]), + and([var2_ExplicitVarSizeWithDummy[q2] < var2_ExplicitVarSizeWithDummy[q2 + 1] \/ + var2_ExplicitVarSizeWithDummy[q2] = 6 + | q2 : int(1..10)]), + and([var2_ExplicitVarSizeWithDummy[q3] = 6 -> var2_ExplicitVarSizeWithDummy[q3 + 1] = 6 | q3 : int(1..10)]), + and([var2_ExplicitVarSizeWithDummy[q7] != 6 -> var2_Occurrence[var2_ExplicitVarSizeWithDummy[q7]] + | q7 : int(1..11)]), + and([var2_Occurrence[q8] -> + or([var2_ExplicitVarSizeWithDummy[q10] != 6 /\ var2_ExplicitVarSizeWithDummy[q10] = q8 | q10 : int(1..11)]) + | q8 : int(-4..5, 2)]), + and([q11 + 1 <= var2_ExplicitVarSizeWithMarker_Marker -> + var2_ExplicitVarSizeWithMarker_Values[q11] < var2_ExplicitVarSizeWithMarker_Values[q11 + 1] + | q11 : int(1..10)]), + and([q12 > var2_ExplicitVarSizeWithMarker_Marker -> var2_ExplicitVarSizeWithMarker_Values[q12] = -4 + | q12 : int(1..11)]), + and([q15 <= var2_ExplicitVarSizeWithMarker_Marker -> var2_Occurrence[var2_ExplicitVarSizeWithMarker_Values[q15]] + | q15 : int(1..11)]), + and([var2_Occurrence[q16] -> + or([q18 <= var2_ExplicitVarSizeWithMarker_Marker /\ var2_ExplicitVarSizeWithMarker_Values[q18] = q16 + | q18 : int(1..11)]) + | q16 : int(-4..5, 2)]), + and([q20 <= var2_ExplicitVarSizeWithMarker_Marker -> + or([var2_ExplicitVarSizeWithDummy[q22] != 6 /\ + var2_ExplicitVarSizeWithDummy[q22] = var2_ExplicitVarSizeWithMarker_Values[q20] + | q22 : int(1..11)]) + | q20 : int(1..11)]), + and([var2_ExplicitVarSizeWithDummy[q24] != 6 -> + or([q26 <= var2_ExplicitVarSizeWithMarker_Marker /\ + var2_ExplicitVarSizeWithMarker_Values[q26] = var2_ExplicitVarSizeWithDummy[q24] + | q26 : int(1..11)]) + | q24 : int(1..11)]) + diff --git a/tests/exhaustive/autogen/gen32/expected/model_1_2_4.eprime b/tests/exhaustive/autogen/gen32/expected/model_1_2_4.eprime new file mode 100644 index 0000000000..8ea95c72c3 --- /dev/null +++ b/tests/exhaustive/autogen/gen32/expected/model_1_2_4.eprime @@ -0,0 +1,49 @@ +language ESSENCE' 1.0 + +letting let1 be -4 +find var2_Occurrence: matrix indexed by [int(-4..5, 2)] of bool +find var2_ExplicitVarSizeWithDummy: matrix indexed by [int(1..11)] of int(-4..5, 2, 6) +find var2_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..11)] of bool +find var2_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..11)] of int(-4..5, 2) +branching on + [var2_ExplicitVarSizeWithFlags_Flags, var2_ExplicitVarSizeWithFlags_Values, var2_Occurrence, + var2_ExplicitVarSizeWithDummy] +such that + or([var2_Occurrence[q29] /\ + !or([var2_ExplicitVarSizeWithDummy[q31] != 6 /\ var2_ExplicitVarSizeWithDummy[q31] = q29 | q31 : int(1..11)]) + | q29 : int(-4..5, 2)]) + \/ + or([var2_ExplicitVarSizeWithDummy[q32] != 6 /\ !var2_Occurrence[var2_ExplicitVarSizeWithDummy[q32]] + | q32 : int(1..11)]), + and([var2_ExplicitVarSizeWithDummy[q2] < var2_ExplicitVarSizeWithDummy[q2 + 1] \/ + var2_ExplicitVarSizeWithDummy[q2] = 6 + | q2 : int(1..10)]), + and([var2_ExplicitVarSizeWithDummy[q3] = 6 -> var2_ExplicitVarSizeWithDummy[q3 + 1] = 6 | q3 : int(1..10)]), + and([var2_ExplicitVarSizeWithDummy[q7] != 6 -> var2_Occurrence[var2_ExplicitVarSizeWithDummy[q7]] + | q7 : int(1..11)]), + and([var2_Occurrence[q8] -> + or([var2_ExplicitVarSizeWithDummy[q10] != 6 /\ var2_ExplicitVarSizeWithDummy[q10] = q8 | q10 : int(1..11)]) + | q8 : int(-4..5, 2)]), + and([var2_ExplicitVarSizeWithFlags_Flags[q11 + 1] -> + var2_ExplicitVarSizeWithFlags_Values[q11] < var2_ExplicitVarSizeWithFlags_Values[q11 + 1] + | q11 : int(1..10)]), + and([var2_ExplicitVarSizeWithFlags_Flags[q12] = false -> var2_ExplicitVarSizeWithFlags_Values[q12] = -4 + | q12 : int(1..11)]), + and([var2_ExplicitVarSizeWithFlags_Flags[q13 + 1] -> var2_ExplicitVarSizeWithFlags_Flags[q13] | q13 : int(1..10)]), + and([var2_ExplicitVarSizeWithFlags_Flags[q17] -> var2_Occurrence[var2_ExplicitVarSizeWithFlags_Values[q17]] + | q17 : int(1..11)]), + and([var2_Occurrence[q18] -> + or([var2_ExplicitVarSizeWithFlags_Flags[q20] /\ var2_ExplicitVarSizeWithFlags_Values[q20] = q18 + | q20 : int(1..11)]) + | q18 : int(-4..5, 2)]), + and([var2_ExplicitVarSizeWithFlags_Flags[q22] -> + or([var2_ExplicitVarSizeWithDummy[q24] != 6 /\ + var2_ExplicitVarSizeWithDummy[q24] = var2_ExplicitVarSizeWithFlags_Values[q22] + | q24 : int(1..11)]) + | q22 : int(1..11)]), + and([var2_ExplicitVarSizeWithDummy[q26] != 6 -> + or([var2_ExplicitVarSizeWithFlags_Flags[q28] /\ + var2_ExplicitVarSizeWithFlags_Values[q28] = var2_ExplicitVarSizeWithDummy[q26] + | q28 : int(1..11)]) + | q26 : int(1..11)]) + diff --git a/tests/exhaustive/autogen/gen32/expected/model_1_3_1.eprime b/tests/exhaustive/autogen/gen32/expected/model_1_3_1.eprime new file mode 100644 index 0000000000..f4bcfbc82e --- /dev/null +++ b/tests/exhaustive/autogen/gen32/expected/model_1_3_1.eprime @@ -0,0 +1,27 @@ +language ESSENCE' 1.0 + +letting let1 be -4 +find var2_Occurrence: matrix indexed by [int(-4..5, 2)] of bool +find var2_ExplicitVarSizeWithMarker_Marker: int(0..11) +find var2_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..11)] of int(-4..5, 2) +branching on [var2_ExplicitVarSizeWithMarker_Marker, var2_ExplicitVarSizeWithMarker_Values, var2_Occurrence] +such that + or([var2_Occurrence[q10] /\ + !or([q12 <= var2_ExplicitVarSizeWithMarker_Marker /\ var2_ExplicitVarSizeWithMarker_Values[q12] = q10 + | q12 : int(1..11)]) + | q10 : int(-4..5, 2)]) + \/ + or([q13 <= var2_ExplicitVarSizeWithMarker_Marker /\ !var2_Occurrence[var2_ExplicitVarSizeWithMarker_Values[q13]] + | q13 : int(1..11)]), + and([q2 + 1 <= var2_ExplicitVarSizeWithMarker_Marker -> + var2_ExplicitVarSizeWithMarker_Values[q2] < var2_ExplicitVarSizeWithMarker_Values[q2 + 1] + | q2 : int(1..10)]), + and([q3 > var2_ExplicitVarSizeWithMarker_Marker -> var2_ExplicitVarSizeWithMarker_Values[q3] = -4 + | q3 : int(1..11)]), + and([q6 <= var2_ExplicitVarSizeWithMarker_Marker -> var2_Occurrence[var2_ExplicitVarSizeWithMarker_Values[q6]] + | q6 : int(1..11)]), + and([var2_Occurrence[q7] -> + or([q9 <= var2_ExplicitVarSizeWithMarker_Marker /\ var2_ExplicitVarSizeWithMarker_Values[q9] = q7 + | q9 : int(1..11)]) + | q7 : int(-4..5, 2)]) + diff --git a/tests/exhaustive/autogen/gen32/expected/model_1_3_2.eprime b/tests/exhaustive/autogen/gen32/expected/model_1_3_2.eprime new file mode 100644 index 0000000000..8612434ed5 --- /dev/null +++ b/tests/exhaustive/autogen/gen32/expected/model_1_3_2.eprime @@ -0,0 +1,49 @@ +language ESSENCE' 1.0 + +letting let1 be -4 +find var2_Occurrence: matrix indexed by [int(-4..5, 2)] of bool +find var2_ExplicitVarSizeWithMarker_Marker: int(0..11) +find var2_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..11)] of int(-4..5, 2) +find var2_ExplicitVarSizeWithDummy: matrix indexed by [int(1..11)] of int(-4..5, 2, 6) +branching on + [var2_ExplicitVarSizeWithDummy, var2_Occurrence, var2_ExplicitVarSizeWithMarker_Marker, + var2_ExplicitVarSizeWithMarker_Values] +such that + or([var2_Occurrence[q27] /\ + !or([q29 <= var2_ExplicitVarSizeWithMarker_Marker /\ var2_ExplicitVarSizeWithMarker_Values[q29] = q27 + | q29 : int(1..11)]) + | q27 : int(-4..5, 2)]) + \/ + or([q30 <= var2_ExplicitVarSizeWithMarker_Marker /\ !var2_Occurrence[var2_ExplicitVarSizeWithMarker_Values[q30]] + | q30 : int(1..11)]), + and([q2 + 1 <= var2_ExplicitVarSizeWithMarker_Marker -> + var2_ExplicitVarSizeWithMarker_Values[q2] < var2_ExplicitVarSizeWithMarker_Values[q2 + 1] + | q2 : int(1..10)]), + and([q3 > var2_ExplicitVarSizeWithMarker_Marker -> var2_ExplicitVarSizeWithMarker_Values[q3] = -4 + | q3 : int(1..11)]), + and([q6 <= var2_ExplicitVarSizeWithMarker_Marker -> var2_Occurrence[var2_ExplicitVarSizeWithMarker_Values[q6]] + | q6 : int(1..11)]), + and([var2_Occurrence[q7] -> + or([q9 <= var2_ExplicitVarSizeWithMarker_Marker /\ var2_ExplicitVarSizeWithMarker_Values[q9] = q7 + | q9 : int(1..11)]) + | q7 : int(-4..5, 2)]), + and([var2_ExplicitVarSizeWithDummy[q10] < var2_ExplicitVarSizeWithDummy[q10 + 1] \/ + var2_ExplicitVarSizeWithDummy[q10] = 6 + | q10 : int(1..10)]), + and([var2_ExplicitVarSizeWithDummy[q11] = 6 -> var2_ExplicitVarSizeWithDummy[q11 + 1] = 6 | q11 : int(1..10)]), + and([var2_ExplicitVarSizeWithDummy[q15] != 6 -> var2_Occurrence[var2_ExplicitVarSizeWithDummy[q15]] + | q15 : int(1..11)]), + and([var2_Occurrence[q16] -> + or([var2_ExplicitVarSizeWithDummy[q18] != 6 /\ var2_ExplicitVarSizeWithDummy[q18] = q16 | q18 : int(1..11)]) + | q16 : int(-4..5, 2)]), + and([var2_ExplicitVarSizeWithDummy[q20] != 6 -> + or([q22 <= var2_ExplicitVarSizeWithMarker_Marker /\ + var2_ExplicitVarSizeWithMarker_Values[q22] = var2_ExplicitVarSizeWithDummy[q20] + | q22 : int(1..11)]) + | q20 : int(1..11)]), + and([q24 <= var2_ExplicitVarSizeWithMarker_Marker -> + or([var2_ExplicitVarSizeWithDummy[q26] != 6 /\ + var2_ExplicitVarSizeWithDummy[q26] = var2_ExplicitVarSizeWithMarker_Values[q24] + | q26 : int(1..11)]) + | q24 : int(1..11)]) + diff --git a/tests/exhaustive/autogen/gen32/expected/model_1_3_4.eprime b/tests/exhaustive/autogen/gen32/expected/model_1_3_4.eprime new file mode 100644 index 0000000000..ef83393629 --- /dev/null +++ b/tests/exhaustive/autogen/gen32/expected/model_1_3_4.eprime @@ -0,0 +1,53 @@ +language ESSENCE' 1.0 + +letting let1 be -4 +find var2_Occurrence: matrix indexed by [int(-4..5, 2)] of bool +find var2_ExplicitVarSizeWithMarker_Marker: int(0..11) +find var2_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..11)] of int(-4..5, 2) +find var2_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..11)] of bool +find var2_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..11)] of int(-4..5, 2) +branching on + [var2_ExplicitVarSizeWithFlags_Flags, var2_ExplicitVarSizeWithFlags_Values, var2_Occurrence, + var2_ExplicitVarSizeWithMarker_Marker, var2_ExplicitVarSizeWithMarker_Values] +such that + or([var2_Occurrence[q28] /\ + !or([q30 <= var2_ExplicitVarSizeWithMarker_Marker /\ var2_ExplicitVarSizeWithMarker_Values[q30] = q28 + | q30 : int(1..11)]) + | q28 : int(-4..5, 2)]) + \/ + or([q31 <= var2_ExplicitVarSizeWithMarker_Marker /\ !var2_Occurrence[var2_ExplicitVarSizeWithMarker_Values[q31]] + | q31 : int(1..11)]), + and([q2 + 1 <= var2_ExplicitVarSizeWithMarker_Marker -> + var2_ExplicitVarSizeWithMarker_Values[q2] < var2_ExplicitVarSizeWithMarker_Values[q2 + 1] + | q2 : int(1..10)]), + and([q3 > var2_ExplicitVarSizeWithMarker_Marker -> var2_ExplicitVarSizeWithMarker_Values[q3] = -4 + | q3 : int(1..11)]), + and([q6 <= var2_ExplicitVarSizeWithMarker_Marker -> var2_Occurrence[var2_ExplicitVarSizeWithMarker_Values[q6]] + | q6 : int(1..11)]), + and([var2_Occurrence[q7] -> + or([q9 <= var2_ExplicitVarSizeWithMarker_Marker /\ var2_ExplicitVarSizeWithMarker_Values[q9] = q7 + | q9 : int(1..11)]) + | q7 : int(-4..5, 2)]), + and([var2_ExplicitVarSizeWithFlags_Flags[q10 + 1] -> + var2_ExplicitVarSizeWithFlags_Values[q10] < var2_ExplicitVarSizeWithFlags_Values[q10 + 1] + | q10 : int(1..10)]), + and([var2_ExplicitVarSizeWithFlags_Flags[q11] = false -> var2_ExplicitVarSizeWithFlags_Values[q11] = -4 + | q11 : int(1..11)]), + and([var2_ExplicitVarSizeWithFlags_Flags[q12 + 1] -> var2_ExplicitVarSizeWithFlags_Flags[q12] | q12 : int(1..10)]), + and([var2_ExplicitVarSizeWithFlags_Flags[q16] -> var2_Occurrence[var2_ExplicitVarSizeWithFlags_Values[q16]] + | q16 : int(1..11)]), + and([var2_Occurrence[q17] -> + or([var2_ExplicitVarSizeWithFlags_Flags[q19] /\ var2_ExplicitVarSizeWithFlags_Values[q19] = q17 + | q19 : int(1..11)]) + | q17 : int(-4..5, 2)]), + and([var2_ExplicitVarSizeWithFlags_Flags[q21] -> + or([q23 <= var2_ExplicitVarSizeWithMarker_Marker /\ + var2_ExplicitVarSizeWithMarker_Values[q23] = var2_ExplicitVarSizeWithFlags_Values[q21] + | q23 : int(1..11)]) + | q21 : int(1..11)]), + and([q25 <= var2_ExplicitVarSizeWithMarker_Marker -> + or([var2_ExplicitVarSizeWithFlags_Flags[q27] /\ + var2_ExplicitVarSizeWithFlags_Values[q27] = var2_ExplicitVarSizeWithMarker_Values[q25] + | q27 : int(1..11)]) + | q25 : int(1..11)]) + diff --git a/tests/exhaustive/autogen/gen32/expected/model_1_4_1.eprime b/tests/exhaustive/autogen/gen32/expected/model_1_4_1.eprime new file mode 100644 index 0000000000..ac3a2f9711 --- /dev/null +++ b/tests/exhaustive/autogen/gen32/expected/model_1_4_1.eprime @@ -0,0 +1,28 @@ +language ESSENCE' 1.0 + +letting let1 be -4 +find var2_Occurrence: matrix indexed by [int(-4..5, 2)] of bool +find var2_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..11)] of bool +find var2_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..11)] of int(-4..5, 2) +branching on [var2_ExplicitVarSizeWithFlags_Flags, var2_ExplicitVarSizeWithFlags_Values, var2_Occurrence] +such that + or([var2_Occurrence[q12] /\ + !or([var2_ExplicitVarSizeWithFlags_Flags[q14] /\ var2_ExplicitVarSizeWithFlags_Values[q14] = q12 + | q14 : int(1..11)]) + | q12 : int(-4..5, 2)]) + \/ + or([var2_ExplicitVarSizeWithFlags_Flags[q15] /\ !var2_Occurrence[var2_ExplicitVarSizeWithFlags_Values[q15]] + | q15 : int(1..11)]), + and([var2_ExplicitVarSizeWithFlags_Flags[q2 + 1] -> + var2_ExplicitVarSizeWithFlags_Values[q2] < var2_ExplicitVarSizeWithFlags_Values[q2 + 1] + | q2 : int(1..10)]), + and([var2_ExplicitVarSizeWithFlags_Flags[q3] = false -> var2_ExplicitVarSizeWithFlags_Values[q3] = -4 + | q3 : int(1..11)]), + and([var2_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> var2_ExplicitVarSizeWithFlags_Flags[q4] | q4 : int(1..10)]), + and([var2_ExplicitVarSizeWithFlags_Flags[q8] -> var2_Occurrence[var2_ExplicitVarSizeWithFlags_Values[q8]] + | q8 : int(1..11)]), + and([var2_Occurrence[q9] -> + or([var2_ExplicitVarSizeWithFlags_Flags[q11] /\ var2_ExplicitVarSizeWithFlags_Values[q11] = q9 + | q11 : int(1..11)]) + | q9 : int(-4..5, 2)]) + diff --git a/tests/exhaustive/autogen/gen32/expected/model_1_4_2.eprime b/tests/exhaustive/autogen/gen32/expected/model_1_4_2.eprime new file mode 100644 index 0000000000..ff6e8bf8e4 --- /dev/null +++ b/tests/exhaustive/autogen/gen32/expected/model_1_4_2.eprime @@ -0,0 +1,50 @@ +language ESSENCE' 1.0 + +letting let1 be -4 +find var2_Occurrence: matrix indexed by [int(-4..5, 2)] of bool +find var2_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..11)] of bool +find var2_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..11)] of int(-4..5, 2) +find var2_ExplicitVarSizeWithDummy: matrix indexed by [int(1..11)] of int(-4..5, 2, 6) +branching on + [var2_ExplicitVarSizeWithDummy, var2_Occurrence, var2_ExplicitVarSizeWithFlags_Flags, + var2_ExplicitVarSizeWithFlags_Values] +such that + or([var2_Occurrence[q29] /\ + !or([var2_ExplicitVarSizeWithFlags_Flags[q31] /\ var2_ExplicitVarSizeWithFlags_Values[q31] = q29 + | q31 : int(1..11)]) + | q29 : int(-4..5, 2)]) + \/ + or([var2_ExplicitVarSizeWithFlags_Flags[q32] /\ !var2_Occurrence[var2_ExplicitVarSizeWithFlags_Values[q32]] + | q32 : int(1..11)]), + and([var2_ExplicitVarSizeWithFlags_Flags[q2 + 1] -> + var2_ExplicitVarSizeWithFlags_Values[q2] < var2_ExplicitVarSizeWithFlags_Values[q2 + 1] + | q2 : int(1..10)]), + and([var2_ExplicitVarSizeWithFlags_Flags[q3] = false -> var2_ExplicitVarSizeWithFlags_Values[q3] = -4 + | q3 : int(1..11)]), + and([var2_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> var2_ExplicitVarSizeWithFlags_Flags[q4] | q4 : int(1..10)]), + and([var2_ExplicitVarSizeWithFlags_Flags[q8] -> var2_Occurrence[var2_ExplicitVarSizeWithFlags_Values[q8]] + | q8 : int(1..11)]), + and([var2_Occurrence[q9] -> + or([var2_ExplicitVarSizeWithFlags_Flags[q11] /\ var2_ExplicitVarSizeWithFlags_Values[q11] = q9 + | q11 : int(1..11)]) + | q9 : int(-4..5, 2)]), + and([var2_ExplicitVarSizeWithDummy[q12] < var2_ExplicitVarSizeWithDummy[q12 + 1] \/ + var2_ExplicitVarSizeWithDummy[q12] = 6 + | q12 : int(1..10)]), + and([var2_ExplicitVarSizeWithDummy[q13] = 6 -> var2_ExplicitVarSizeWithDummy[q13 + 1] = 6 | q13 : int(1..10)]), + and([var2_ExplicitVarSizeWithDummy[q17] != 6 -> var2_Occurrence[var2_ExplicitVarSizeWithDummy[q17]] + | q17 : int(1..11)]), + and([var2_Occurrence[q18] -> + or([var2_ExplicitVarSizeWithDummy[q20] != 6 /\ var2_ExplicitVarSizeWithDummy[q20] = q18 | q20 : int(1..11)]) + | q18 : int(-4..5, 2)]), + and([var2_ExplicitVarSizeWithDummy[q22] != 6 -> + or([var2_ExplicitVarSizeWithFlags_Flags[q24] /\ + var2_ExplicitVarSizeWithFlags_Values[q24] = var2_ExplicitVarSizeWithDummy[q22] + | q24 : int(1..11)]) + | q22 : int(1..11)]), + and([var2_ExplicitVarSizeWithFlags_Flags[q26] -> + or([var2_ExplicitVarSizeWithDummy[q28] != 6 /\ + var2_ExplicitVarSizeWithDummy[q28] = var2_ExplicitVarSizeWithFlags_Values[q26] + | q28 : int(1..11)]) + | q26 : int(1..11)]) + diff --git a/tests/exhaustive/autogen/gen32/expected/model_1_4_3.eprime b/tests/exhaustive/autogen/gen32/expected/model_1_4_3.eprime new file mode 100644 index 0000000000..74db93bcc4 --- /dev/null +++ b/tests/exhaustive/autogen/gen32/expected/model_1_4_3.eprime @@ -0,0 +1,53 @@ +language ESSENCE' 1.0 + +letting let1 be -4 +find var2_Occurrence: matrix indexed by [int(-4..5, 2)] of bool +find var2_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..11)] of bool +find var2_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..11)] of int(-4..5, 2) +find var2_ExplicitVarSizeWithMarker_Marker: int(0..11) +find var2_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..11)] of int(-4..5, 2) +branching on + [var2_ExplicitVarSizeWithMarker_Marker, var2_ExplicitVarSizeWithMarker_Values, var2_Occurrence, + var2_ExplicitVarSizeWithFlags_Flags, var2_ExplicitVarSizeWithFlags_Values] +such that + or([var2_Occurrence[q28] /\ + !or([var2_ExplicitVarSizeWithFlags_Flags[q30] /\ var2_ExplicitVarSizeWithFlags_Values[q30] = q28 + | q30 : int(1..11)]) + | q28 : int(-4..5, 2)]) + \/ + or([var2_ExplicitVarSizeWithFlags_Flags[q31] /\ !var2_Occurrence[var2_ExplicitVarSizeWithFlags_Values[q31]] + | q31 : int(1..11)]), + and([var2_ExplicitVarSizeWithFlags_Flags[q2 + 1] -> + var2_ExplicitVarSizeWithFlags_Values[q2] < var2_ExplicitVarSizeWithFlags_Values[q2 + 1] + | q2 : int(1..10)]), + and([var2_ExplicitVarSizeWithFlags_Flags[q3] = false -> var2_ExplicitVarSizeWithFlags_Values[q3] = -4 + | q3 : int(1..11)]), + and([var2_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> var2_ExplicitVarSizeWithFlags_Flags[q4] | q4 : int(1..10)]), + and([var2_ExplicitVarSizeWithFlags_Flags[q8] -> var2_Occurrence[var2_ExplicitVarSizeWithFlags_Values[q8]] + | q8 : int(1..11)]), + and([var2_Occurrence[q9] -> + or([var2_ExplicitVarSizeWithFlags_Flags[q11] /\ var2_ExplicitVarSizeWithFlags_Values[q11] = q9 + | q11 : int(1..11)]) + | q9 : int(-4..5, 2)]), + and([q12 + 1 <= var2_ExplicitVarSizeWithMarker_Marker -> + var2_ExplicitVarSizeWithMarker_Values[q12] < var2_ExplicitVarSizeWithMarker_Values[q12 + 1] + | q12 : int(1..10)]), + and([q13 > var2_ExplicitVarSizeWithMarker_Marker -> var2_ExplicitVarSizeWithMarker_Values[q13] = -4 + | q13 : int(1..11)]), + and([q16 <= var2_ExplicitVarSizeWithMarker_Marker -> var2_Occurrence[var2_ExplicitVarSizeWithMarker_Values[q16]] + | q16 : int(1..11)]), + and([var2_Occurrence[q17] -> + or([q19 <= var2_ExplicitVarSizeWithMarker_Marker /\ var2_ExplicitVarSizeWithMarker_Values[q19] = q17 + | q19 : int(1..11)]) + | q17 : int(-4..5, 2)]), + and([q21 <= var2_ExplicitVarSizeWithMarker_Marker -> + or([var2_ExplicitVarSizeWithFlags_Flags[q23] /\ + var2_ExplicitVarSizeWithFlags_Values[q23] = var2_ExplicitVarSizeWithMarker_Values[q21] + | q23 : int(1..11)]) + | q21 : int(1..11)]), + and([var2_ExplicitVarSizeWithFlags_Flags[q25] -> + or([q27 <= var2_ExplicitVarSizeWithMarker_Marker /\ + var2_ExplicitVarSizeWithMarker_Values[q27] = var2_ExplicitVarSizeWithFlags_Values[q25] + | q27 : int(1..11)]) + | q25 : int(1..11)]) + diff --git a/tests/exhaustive/autogen/gen32/expected/model_2_1_1.eprime b/tests/exhaustive/autogen/gen32/expected/model_2_1_1.eprime new file mode 100644 index 0000000000..cc87135b8c --- /dev/null +++ b/tests/exhaustive/autogen/gen32/expected/model_2_1_1.eprime @@ -0,0 +1,23 @@ +language ESSENCE' 1.0 + +letting let1 be -4 +find var2_ExplicitVarSizeWithDummy: matrix indexed by [int(1..11)] of int(-4..5, 2, 6) +find var2_Occurrence: matrix indexed by [int(-4..5, 2)] of bool +branching on [var2_Occurrence, var2_ExplicitVarSizeWithDummy] +such that + or([var2_ExplicitVarSizeWithDummy[q7] != 6 /\ !var2_Occurrence[var2_ExplicitVarSizeWithDummy[q7]] + | q7 : int(1..11)]) + \/ + or([var2_Occurrence[q6] /\ + !or([var2_ExplicitVarSizeWithDummy[q9] != 6 /\ var2_ExplicitVarSizeWithDummy[q9] = q6 | q9 : int(1..11)]) + | q6 : int(-4..5, 2)]), + and([var2_ExplicitVarSizeWithDummy[q1] < var2_ExplicitVarSizeWithDummy[q1 + 1] \/ + var2_ExplicitVarSizeWithDummy[q1] = 6 + | q1 : int(1..10)]), + and([var2_ExplicitVarSizeWithDummy[q2] = 6 -> var2_ExplicitVarSizeWithDummy[q2 + 1] = 6 | q2 : int(1..10)]), + and([var2_Occurrence[q10] -> + or([var2_ExplicitVarSizeWithDummy[q12] != 6 /\ var2_ExplicitVarSizeWithDummy[q12] = q10 | q12 : int(1..11)]) + | q10 : int(-4..5, 2)]), + and([var2_ExplicitVarSizeWithDummy[q14] != 6 -> var2_Occurrence[var2_ExplicitVarSizeWithDummy[q14]] + | q14 : int(1..11)]) + diff --git a/tests/exhaustive/autogen/gen32/expected/model_2_1_3.eprime b/tests/exhaustive/autogen/gen32/expected/model_2_1_3.eprime new file mode 100644 index 0000000000..ff7949c852 --- /dev/null +++ b/tests/exhaustive/autogen/gen32/expected/model_2_1_3.eprime @@ -0,0 +1,48 @@ +language ESSENCE' 1.0 + +letting let1 be -4 +find var2_ExplicitVarSizeWithDummy: matrix indexed by [int(1..11)] of int(-4..5, 2, 6) +find var2_Occurrence: matrix indexed by [int(-4..5, 2)] of bool +find var2_ExplicitVarSizeWithMarker_Marker: int(0..11) +find var2_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..11)] of int(-4..5, 2) +branching on + [var2_ExplicitVarSizeWithMarker_Marker, var2_ExplicitVarSizeWithMarker_Values, var2_ExplicitVarSizeWithDummy, + var2_Occurrence] +such that + or([var2_ExplicitVarSizeWithDummy[q23] != 6 /\ !var2_Occurrence[var2_ExplicitVarSizeWithDummy[q23]] + | q23 : int(1..11)]) + \/ + or([var2_Occurrence[q22] /\ + !or([var2_ExplicitVarSizeWithDummy[q25] != 6 /\ var2_ExplicitVarSizeWithDummy[q25] = q22 | q25 : int(1..11)]) + | q22 : int(-4..5, 2)]), + and([var2_ExplicitVarSizeWithDummy[q1] < var2_ExplicitVarSizeWithDummy[q1 + 1] \/ + var2_ExplicitVarSizeWithDummy[q1] = 6 + | q1 : int(1..10)]), + and([var2_ExplicitVarSizeWithDummy[q2] = 6 -> var2_ExplicitVarSizeWithDummy[q2 + 1] = 6 | q2 : int(1..10)]), + and([var2_Occurrence[q26] -> + or([var2_ExplicitVarSizeWithDummy[q28] != 6 /\ var2_ExplicitVarSizeWithDummy[q28] = q26 | q28 : int(1..11)]) + | q26 : int(-4..5, 2)]), + and([var2_ExplicitVarSizeWithDummy[q30] != 6 -> var2_Occurrence[var2_ExplicitVarSizeWithDummy[q30]] + | q30 : int(1..11)]), + and([q6 + 1 <= var2_ExplicitVarSizeWithMarker_Marker -> + var2_ExplicitVarSizeWithMarker_Values[q6] < var2_ExplicitVarSizeWithMarker_Values[q6 + 1] + | q6 : int(1..10)]), + and([q7 > var2_ExplicitVarSizeWithMarker_Marker -> var2_ExplicitVarSizeWithMarker_Values[q7] = -4 + | q7 : int(1..11)]), + and([q10 <= var2_ExplicitVarSizeWithMarker_Marker -> + or([var2_ExplicitVarSizeWithDummy[q12] != 6 /\ + var2_ExplicitVarSizeWithDummy[q12] = var2_ExplicitVarSizeWithMarker_Values[q10] + | q12 : int(1..11)]) + | q10 : int(1..11)]), + and([var2_ExplicitVarSizeWithDummy[q14] != 6 -> + or([q16 <= var2_ExplicitVarSizeWithMarker_Marker /\ + var2_ExplicitVarSizeWithMarker_Values[q16] = var2_ExplicitVarSizeWithDummy[q14] + | q16 : int(1..11)]) + | q14 : int(1..11)]), + and([q18 <= var2_ExplicitVarSizeWithMarker_Marker -> var2_Occurrence[var2_ExplicitVarSizeWithMarker_Values[q18]] + | q18 : int(1..11)]), + and([var2_Occurrence[q19] -> + or([q21 <= var2_ExplicitVarSizeWithMarker_Marker /\ var2_ExplicitVarSizeWithMarker_Values[q21] = q19 + | q21 : int(1..11)]) + | q19 : int(-4..5, 2)]) + diff --git a/tests/exhaustive/autogen/gen32/expected/model_2_1_4.eprime b/tests/exhaustive/autogen/gen32/expected/model_2_1_4.eprime new file mode 100644 index 0000000000..39bbf550cc --- /dev/null +++ b/tests/exhaustive/autogen/gen32/expected/model_2_1_4.eprime @@ -0,0 +1,49 @@ +language ESSENCE' 1.0 + +letting let1 be -4 +find var2_ExplicitVarSizeWithDummy: matrix indexed by [int(1..11)] of int(-4..5, 2, 6) +find var2_Occurrence: matrix indexed by [int(-4..5, 2)] of bool +find var2_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..11)] of bool +find var2_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..11)] of int(-4..5, 2) +branching on + [var2_ExplicitVarSizeWithFlags_Flags, var2_ExplicitVarSizeWithFlags_Values, var2_ExplicitVarSizeWithDummy, + var2_Occurrence] +such that + or([var2_ExplicitVarSizeWithDummy[q25] != 6 /\ !var2_Occurrence[var2_ExplicitVarSizeWithDummy[q25]] + | q25 : int(1..11)]) + \/ + or([var2_Occurrence[q24] /\ + !or([var2_ExplicitVarSizeWithDummy[q27] != 6 /\ var2_ExplicitVarSizeWithDummy[q27] = q24 | q27 : int(1..11)]) + | q24 : int(-4..5, 2)]), + and([var2_ExplicitVarSizeWithDummy[q1] < var2_ExplicitVarSizeWithDummy[q1 + 1] \/ + var2_ExplicitVarSizeWithDummy[q1] = 6 + | q1 : int(1..10)]), + and([var2_ExplicitVarSizeWithDummy[q2] = 6 -> var2_ExplicitVarSizeWithDummy[q2 + 1] = 6 | q2 : int(1..10)]), + and([var2_Occurrence[q28] -> + or([var2_ExplicitVarSizeWithDummy[q30] != 6 /\ var2_ExplicitVarSizeWithDummy[q30] = q28 | q30 : int(1..11)]) + | q28 : int(-4..5, 2)]), + and([var2_ExplicitVarSizeWithDummy[q32] != 6 -> var2_Occurrence[var2_ExplicitVarSizeWithDummy[q32]] + | q32 : int(1..11)]), + and([var2_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> + var2_ExplicitVarSizeWithFlags_Values[q6] < var2_ExplicitVarSizeWithFlags_Values[q6 + 1] + | q6 : int(1..10)]), + and([var2_ExplicitVarSizeWithFlags_Flags[q7] = false -> var2_ExplicitVarSizeWithFlags_Values[q7] = -4 + | q7 : int(1..11)]), + and([var2_ExplicitVarSizeWithFlags_Flags[q8 + 1] -> var2_ExplicitVarSizeWithFlags_Flags[q8] | q8 : int(1..10)]), + and([var2_ExplicitVarSizeWithFlags_Flags[q12] -> + or([var2_ExplicitVarSizeWithDummy[q14] != 6 /\ + var2_ExplicitVarSizeWithDummy[q14] = var2_ExplicitVarSizeWithFlags_Values[q12] + | q14 : int(1..11)]) + | q12 : int(1..11)]), + and([var2_ExplicitVarSizeWithDummy[q16] != 6 -> + or([var2_ExplicitVarSizeWithFlags_Flags[q18] /\ + var2_ExplicitVarSizeWithFlags_Values[q18] = var2_ExplicitVarSizeWithDummy[q16] + | q18 : int(1..11)]) + | q16 : int(1..11)]), + and([var2_ExplicitVarSizeWithFlags_Flags[q20] -> var2_Occurrence[var2_ExplicitVarSizeWithFlags_Values[q20]] + | q20 : int(1..11)]), + and([var2_Occurrence[q21] -> + or([var2_ExplicitVarSizeWithFlags_Flags[q23] /\ var2_ExplicitVarSizeWithFlags_Values[q23] = q21 + | q23 : int(1..11)]) + | q21 : int(-4..5, 2)]) + diff --git a/tests/exhaustive/autogen/gen32/expected/model_2_2_1.eprime b/tests/exhaustive/autogen/gen32/expected/model_2_2_1.eprime new file mode 100644 index 0000000000..c131688486 --- /dev/null +++ b/tests/exhaustive/autogen/gen32/expected/model_2_2_1.eprime @@ -0,0 +1,28 @@ +language ESSENCE' 1.0 + +letting let1 be -4 +find var2_ExplicitVarSizeWithDummy: matrix indexed by [int(1..11)] of int(-4..5, 2, 6) +find var2_Occurrence: matrix indexed by [int(-4..5, 2)] of bool +branching on [var2_Occurrence, var2_ExplicitVarSizeWithDummy] +such that + or([var2_ExplicitVarSizeWithDummy[q7] != 6 /\ + !or([var2_ExplicitVarSizeWithDummy[q9] != 6 /\ + var2_ExplicitVarSizeWithDummy[q9] = var2_ExplicitVarSizeWithDummy[q7] + | q9 : int(1..11)]) + | q7 : int(1..11)]) + \/ + or([var2_ExplicitVarSizeWithDummy[q10] != 6 /\ + !or([var2_ExplicitVarSizeWithDummy[q12] != 6 /\ + var2_ExplicitVarSizeWithDummy[q12] = var2_ExplicitVarSizeWithDummy[q10] + | q12 : int(1..11)]) + | q10 : int(1..11)]), + and([var2_ExplicitVarSizeWithDummy[q1] < var2_ExplicitVarSizeWithDummy[q1 + 1] \/ + var2_ExplicitVarSizeWithDummy[q1] = 6 + | q1 : int(1..10)]), + and([var2_ExplicitVarSizeWithDummy[q2] = 6 -> var2_ExplicitVarSizeWithDummy[q2 + 1] = 6 | q2 : int(1..10)]), + and([var2_Occurrence[q13] -> + or([var2_ExplicitVarSizeWithDummy[q15] != 6 /\ var2_ExplicitVarSizeWithDummy[q15] = q13 | q15 : int(1..11)]) + | q13 : int(-4..5, 2)]), + and([var2_ExplicitVarSizeWithDummy[q17] != 6 -> var2_Occurrence[var2_ExplicitVarSizeWithDummy[q17]] + | q17 : int(1..11)]) + diff --git a/tests/exhaustive/autogen/gen32/expected/model_2_2_2.eprime b/tests/exhaustive/autogen/gen32/expected/model_2_2_2.eprime new file mode 100644 index 0000000000..c724673a10 --- /dev/null +++ b/tests/exhaustive/autogen/gen32/expected/model_2_2_2.eprime @@ -0,0 +1,22 @@ +language ESSENCE' 1.0 + +letting let1 be -4 +find var2_ExplicitVarSizeWithDummy: matrix indexed by [int(1..11)] of int(-4..5, 2, 6) +branching on [var2_ExplicitVarSizeWithDummy] +such that + or([var2_ExplicitVarSizeWithDummy[q6] != 6 /\ + !or([var2_ExplicitVarSizeWithDummy[q8] != 6 /\ + var2_ExplicitVarSizeWithDummy[q8] = var2_ExplicitVarSizeWithDummy[q6] + | q8 : int(1..11)]) + | q6 : int(1..11)]) + \/ + or([var2_ExplicitVarSizeWithDummy[q9] != 6 /\ + !or([var2_ExplicitVarSizeWithDummy[q11] != 6 /\ + var2_ExplicitVarSizeWithDummy[q11] = var2_ExplicitVarSizeWithDummy[q9] + | q11 : int(1..11)]) + | q9 : int(1..11)]), + and([var2_ExplicitVarSizeWithDummy[q1] < var2_ExplicitVarSizeWithDummy[q1 + 1] \/ + var2_ExplicitVarSizeWithDummy[q1] = 6 + | q1 : int(1..10)]), + and([var2_ExplicitVarSizeWithDummy[q2] = 6 -> var2_ExplicitVarSizeWithDummy[q2 + 1] = 6 | q2 : int(1..10)]) + diff --git a/tests/exhaustive/autogen/gen32/expected/model_2_2_3.eprime b/tests/exhaustive/autogen/gen32/expected/model_2_2_3.eprime new file mode 100644 index 0000000000..a4c92861d6 --- /dev/null +++ b/tests/exhaustive/autogen/gen32/expected/model_2_2_3.eprime @@ -0,0 +1,40 @@ +language ESSENCE' 1.0 + +letting let1 be -4 +find var2_ExplicitVarSizeWithDummy: matrix indexed by [int(1..11)] of int(-4..5, 2, 6) +find var2_ExplicitVarSizeWithMarker_Marker: int(0..11) +find var2_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..11)] of int(-4..5, 2) +branching on + [var2_ExplicitVarSizeWithMarker_Marker, var2_ExplicitVarSizeWithMarker_Values, var2_ExplicitVarSizeWithDummy] +such that + or([var2_ExplicitVarSizeWithDummy[q17] != 6 /\ + !or([var2_ExplicitVarSizeWithDummy[q19] != 6 /\ + var2_ExplicitVarSizeWithDummy[q19] = var2_ExplicitVarSizeWithDummy[q17] + | q19 : int(1..11)]) + | q17 : int(1..11)]) + \/ + or([var2_ExplicitVarSizeWithDummy[q20] != 6 /\ + !or([var2_ExplicitVarSizeWithDummy[q22] != 6 /\ + var2_ExplicitVarSizeWithDummy[q22] = var2_ExplicitVarSizeWithDummy[q20] + | q22 : int(1..11)]) + | q20 : int(1..11)]), + and([var2_ExplicitVarSizeWithDummy[q1] < var2_ExplicitVarSizeWithDummy[q1 + 1] \/ + var2_ExplicitVarSizeWithDummy[q1] = 6 + | q1 : int(1..10)]), + and([var2_ExplicitVarSizeWithDummy[q2] = 6 -> var2_ExplicitVarSizeWithDummy[q2 + 1] = 6 | q2 : int(1..10)]), + and([q5 + 1 <= var2_ExplicitVarSizeWithMarker_Marker -> + var2_ExplicitVarSizeWithMarker_Values[q5] < var2_ExplicitVarSizeWithMarker_Values[q5 + 1] + | q5 : int(1..10)]), + and([q6 > var2_ExplicitVarSizeWithMarker_Marker -> var2_ExplicitVarSizeWithMarker_Values[q6] = -4 + | q6 : int(1..11)]), + and([q9 <= var2_ExplicitVarSizeWithMarker_Marker -> + or([var2_ExplicitVarSizeWithDummy[q11] != 6 /\ + var2_ExplicitVarSizeWithDummy[q11] = var2_ExplicitVarSizeWithMarker_Values[q9] + | q11 : int(1..11)]) + | q9 : int(1..11)]), + and([var2_ExplicitVarSizeWithDummy[q13] != 6 -> + or([q15 <= var2_ExplicitVarSizeWithMarker_Marker /\ + var2_ExplicitVarSizeWithMarker_Values[q15] = var2_ExplicitVarSizeWithDummy[q13] + | q15 : int(1..11)]) + | q13 : int(1..11)]) + diff --git a/tests/exhaustive/autogen/gen32/expected/model_2_2_4.eprime b/tests/exhaustive/autogen/gen32/expected/model_2_2_4.eprime new file mode 100644 index 0000000000..4b33c5a6af --- /dev/null +++ b/tests/exhaustive/autogen/gen32/expected/model_2_2_4.eprime @@ -0,0 +1,40 @@ +language ESSENCE' 1.0 + +letting let1 be -4 +find var2_ExplicitVarSizeWithDummy: matrix indexed by [int(1..11)] of int(-4..5, 2, 6) +find var2_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..11)] of bool +find var2_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..11)] of int(-4..5, 2) +branching on [var2_ExplicitVarSizeWithFlags_Flags, var2_ExplicitVarSizeWithFlags_Values, var2_ExplicitVarSizeWithDummy] +such that + or([var2_ExplicitVarSizeWithDummy[q19] != 6 /\ + !or([var2_ExplicitVarSizeWithDummy[q21] != 6 /\ + var2_ExplicitVarSizeWithDummy[q21] = var2_ExplicitVarSizeWithDummy[q19] + | q21 : int(1..11)]) + | q19 : int(1..11)]) + \/ + or([var2_ExplicitVarSizeWithDummy[q22] != 6 /\ + !or([var2_ExplicitVarSizeWithDummy[q24] != 6 /\ + var2_ExplicitVarSizeWithDummy[q24] = var2_ExplicitVarSizeWithDummy[q22] + | q24 : int(1..11)]) + | q22 : int(1..11)]), + and([var2_ExplicitVarSizeWithDummy[q1] < var2_ExplicitVarSizeWithDummy[q1 + 1] \/ + var2_ExplicitVarSizeWithDummy[q1] = 6 + | q1 : int(1..10)]), + and([var2_ExplicitVarSizeWithDummy[q2] = 6 -> var2_ExplicitVarSizeWithDummy[q2 + 1] = 6 | q2 : int(1..10)]), + and([var2_ExplicitVarSizeWithFlags_Flags[q5 + 1] -> + var2_ExplicitVarSizeWithFlags_Values[q5] < var2_ExplicitVarSizeWithFlags_Values[q5 + 1] + | q5 : int(1..10)]), + and([var2_ExplicitVarSizeWithFlags_Flags[q6] = false -> var2_ExplicitVarSizeWithFlags_Values[q6] = -4 + | q6 : int(1..11)]), + and([var2_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> var2_ExplicitVarSizeWithFlags_Flags[q7] | q7 : int(1..10)]), + and([var2_ExplicitVarSizeWithFlags_Flags[q11] -> + or([var2_ExplicitVarSizeWithDummy[q13] != 6 /\ + var2_ExplicitVarSizeWithDummy[q13] = var2_ExplicitVarSizeWithFlags_Values[q11] + | q13 : int(1..11)]) + | q11 : int(1..11)]), + and([var2_ExplicitVarSizeWithDummy[q15] != 6 -> + or([var2_ExplicitVarSizeWithFlags_Flags[q17] /\ + var2_ExplicitVarSizeWithFlags_Values[q17] = var2_ExplicitVarSizeWithDummy[q15] + | q17 : int(1..11)]) + | q15 : int(1..11)]) + diff --git a/tests/exhaustive/autogen/gen32/expected/model_2_3_1.eprime b/tests/exhaustive/autogen/gen32/expected/model_2_3_1.eprime new file mode 100644 index 0000000000..9e87cee675 --- /dev/null +++ b/tests/exhaustive/autogen/gen32/expected/model_2_3_1.eprime @@ -0,0 +1,53 @@ +language ESSENCE' 1.0 + +letting let1 be -4 +find var2_ExplicitVarSizeWithDummy: matrix indexed by [int(1..11)] of int(-4..5, 2, 6) +find var2_ExplicitVarSizeWithMarker_Marker: int(0..11) +find var2_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..11)] of int(-4..5, 2) +find var2_Occurrence: matrix indexed by [int(-4..5, 2)] of bool +branching on + [var2_Occurrence, var2_ExplicitVarSizeWithDummy, var2_ExplicitVarSizeWithMarker_Marker, + var2_ExplicitVarSizeWithMarker_Values] +such that + or([var2_ExplicitVarSizeWithDummy[q18] != 6 /\ + !or([q20 <= var2_ExplicitVarSizeWithMarker_Marker /\ + var2_ExplicitVarSizeWithMarker_Values[q20] = var2_ExplicitVarSizeWithDummy[q18] + | q20 : int(1..11)]) + | q18 : int(1..11)]) + \/ + or([q21 <= var2_ExplicitVarSizeWithMarker_Marker /\ + !or([var2_ExplicitVarSizeWithDummy[q23] != 6 /\ + var2_ExplicitVarSizeWithDummy[q23] = var2_ExplicitVarSizeWithMarker_Values[q21] + | q23 : int(1..11)]) + | q21 : int(1..11)]), + and([var2_ExplicitVarSizeWithDummy[q1] < var2_ExplicitVarSizeWithDummy[q1 + 1] \/ + var2_ExplicitVarSizeWithDummy[q1] = 6 + | q1 : int(1..10)]), + and([var2_ExplicitVarSizeWithDummy[q2] = 6 -> var2_ExplicitVarSizeWithDummy[q2 + 1] = 6 | q2 : int(1..10)]), + and([q5 + 1 <= var2_ExplicitVarSizeWithMarker_Marker -> + var2_ExplicitVarSizeWithMarker_Values[q5] < var2_ExplicitVarSizeWithMarker_Values[q5 + 1] + | q5 : int(1..10)]), + and([q6 > var2_ExplicitVarSizeWithMarker_Marker -> var2_ExplicitVarSizeWithMarker_Values[q6] = -4 + | q6 : int(1..11)]), + and([q9 <= var2_ExplicitVarSizeWithMarker_Marker -> + or([var2_ExplicitVarSizeWithDummy[q11] != 6 /\ + var2_ExplicitVarSizeWithDummy[q11] = var2_ExplicitVarSizeWithMarker_Values[q9] + | q11 : int(1..11)]) + | q9 : int(1..11)]), + and([var2_ExplicitVarSizeWithDummy[q13] != 6 -> + or([q15 <= var2_ExplicitVarSizeWithMarker_Marker /\ + var2_ExplicitVarSizeWithMarker_Values[q15] = var2_ExplicitVarSizeWithDummy[q13] + | q15 : int(1..11)]) + | q13 : int(1..11)]), + and([var2_Occurrence[q24] -> + or([var2_ExplicitVarSizeWithDummy[q26] != 6 /\ var2_ExplicitVarSizeWithDummy[q26] = q24 | q26 : int(1..11)]) + | q24 : int(-4..5, 2)]), + and([var2_ExplicitVarSizeWithDummy[q28] != 6 -> var2_Occurrence[var2_ExplicitVarSizeWithDummy[q28]] + | q28 : int(1..11)]), + and([var2_Occurrence[q29] -> + or([q31 <= var2_ExplicitVarSizeWithMarker_Marker /\ var2_ExplicitVarSizeWithMarker_Values[q31] = q29 + | q31 : int(1..11)]) + | q29 : int(-4..5, 2)]), + and([q33 <= var2_ExplicitVarSizeWithMarker_Marker -> var2_Occurrence[var2_ExplicitVarSizeWithMarker_Values[q33]] + | q33 : int(1..11)]) + diff --git a/tests/exhaustive/autogen/gen32/expected/model_2_3_2.eprime b/tests/exhaustive/autogen/gen32/expected/model_2_3_2.eprime new file mode 100644 index 0000000000..9aea3cfc02 --- /dev/null +++ b/tests/exhaustive/autogen/gen32/expected/model_2_3_2.eprime @@ -0,0 +1,40 @@ +language ESSENCE' 1.0 + +letting let1 be -4 +find var2_ExplicitVarSizeWithDummy: matrix indexed by [int(1..11)] of int(-4..5, 2, 6) +find var2_ExplicitVarSizeWithMarker_Marker: int(0..11) +find var2_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..11)] of int(-4..5, 2) +branching on + [var2_ExplicitVarSizeWithMarker_Marker, var2_ExplicitVarSizeWithMarker_Values, var2_ExplicitVarSizeWithDummy] +such that + or([var2_ExplicitVarSizeWithDummy[q17] != 6 /\ + !or([q19 <= var2_ExplicitVarSizeWithMarker_Marker /\ + var2_ExplicitVarSizeWithMarker_Values[q19] = var2_ExplicitVarSizeWithDummy[q17] + | q19 : int(1..11)]) + | q17 : int(1..11)]) + \/ + or([q20 <= var2_ExplicitVarSizeWithMarker_Marker /\ + !or([var2_ExplicitVarSizeWithDummy[q22] != 6 /\ + var2_ExplicitVarSizeWithDummy[q22] = var2_ExplicitVarSizeWithMarker_Values[q20] + | q22 : int(1..11)]) + | q20 : int(1..11)]), + and([var2_ExplicitVarSizeWithDummy[q1] < var2_ExplicitVarSizeWithDummy[q1 + 1] \/ + var2_ExplicitVarSizeWithDummy[q1] = 6 + | q1 : int(1..10)]), + and([var2_ExplicitVarSizeWithDummy[q2] = 6 -> var2_ExplicitVarSizeWithDummy[q2 + 1] = 6 | q2 : int(1..10)]), + and([q5 + 1 <= var2_ExplicitVarSizeWithMarker_Marker -> + var2_ExplicitVarSizeWithMarker_Values[q5] < var2_ExplicitVarSizeWithMarker_Values[q5 + 1] + | q5 : int(1..10)]), + and([q6 > var2_ExplicitVarSizeWithMarker_Marker -> var2_ExplicitVarSizeWithMarker_Values[q6] = -4 + | q6 : int(1..11)]), + and([q9 <= var2_ExplicitVarSizeWithMarker_Marker -> + or([var2_ExplicitVarSizeWithDummy[q11] != 6 /\ + var2_ExplicitVarSizeWithDummy[q11] = var2_ExplicitVarSizeWithMarker_Values[q9] + | q11 : int(1..11)]) + | q9 : int(1..11)]), + and([var2_ExplicitVarSizeWithDummy[q13] != 6 -> + or([q15 <= var2_ExplicitVarSizeWithMarker_Marker /\ + var2_ExplicitVarSizeWithMarker_Values[q15] = var2_ExplicitVarSizeWithDummy[q13] + | q15 : int(1..11)]) + | q13 : int(1..11)]) + diff --git a/tests/exhaustive/autogen/gen32/expected/model_2_3_4.eprime b/tests/exhaustive/autogen/gen32/expected/model_2_3_4.eprime new file mode 100644 index 0000000000..8caf045469 --- /dev/null +++ b/tests/exhaustive/autogen/gen32/expected/model_2_3_4.eprime @@ -0,0 +1,69 @@ +language ESSENCE' 1.0 + +letting let1 be -4 +find var2_ExplicitVarSizeWithDummy: matrix indexed by [int(1..11)] of int(-4..5, 2, 6) +find var2_ExplicitVarSizeWithMarker_Marker: int(0..11) +find var2_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..11)] of int(-4..5, 2) +find var2_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..11)] of bool +find var2_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..11)] of int(-4..5, 2) +branching on + [var2_ExplicitVarSizeWithFlags_Flags, var2_ExplicitVarSizeWithFlags_Values, var2_ExplicitVarSizeWithDummy, + var2_ExplicitVarSizeWithMarker_Marker, var2_ExplicitVarSizeWithMarker_Values] +such that + or([var2_ExplicitVarSizeWithDummy[q38] != 6 /\ + !or([q40 <= var2_ExplicitVarSizeWithMarker_Marker /\ + var2_ExplicitVarSizeWithMarker_Values[q40] = var2_ExplicitVarSizeWithDummy[q38] + | q40 : int(1..11)]) + | q38 : int(1..11)]) + \/ + or([q41 <= var2_ExplicitVarSizeWithMarker_Marker /\ + !or([var2_ExplicitVarSizeWithDummy[q43] != 6 /\ + var2_ExplicitVarSizeWithDummy[q43] = var2_ExplicitVarSizeWithMarker_Values[q41] + | q43 : int(1..11)]) + | q41 : int(1..11)]), + and([var2_ExplicitVarSizeWithDummy[q1] < var2_ExplicitVarSizeWithDummy[q1 + 1] \/ + var2_ExplicitVarSizeWithDummy[q1] = 6 + | q1 : int(1..10)]), + and([var2_ExplicitVarSizeWithDummy[q2] = 6 -> var2_ExplicitVarSizeWithDummy[q2 + 1] = 6 | q2 : int(1..10)]), + and([q5 + 1 <= var2_ExplicitVarSizeWithMarker_Marker -> + var2_ExplicitVarSizeWithMarker_Values[q5] < var2_ExplicitVarSizeWithMarker_Values[q5 + 1] + | q5 : int(1..10)]), + and([q6 > var2_ExplicitVarSizeWithMarker_Marker -> var2_ExplicitVarSizeWithMarker_Values[q6] = -4 + | q6 : int(1..11)]), + and([q9 <= var2_ExplicitVarSizeWithMarker_Marker -> + or([var2_ExplicitVarSizeWithDummy[q11] != 6 /\ + var2_ExplicitVarSizeWithDummy[q11] = var2_ExplicitVarSizeWithMarker_Values[q9] + | q11 : int(1..11)]) + | q9 : int(1..11)]), + and([var2_ExplicitVarSizeWithDummy[q13] != 6 -> + or([q15 <= var2_ExplicitVarSizeWithMarker_Marker /\ + var2_ExplicitVarSizeWithMarker_Values[q15] = var2_ExplicitVarSizeWithDummy[q13] + | q15 : int(1..11)]) + | q13 : int(1..11)]), + and([var2_ExplicitVarSizeWithFlags_Flags[q16 + 1] -> + var2_ExplicitVarSizeWithFlags_Values[q16] < var2_ExplicitVarSizeWithFlags_Values[q16 + 1] + | q16 : int(1..10)]), + and([var2_ExplicitVarSizeWithFlags_Flags[q17] = false -> var2_ExplicitVarSizeWithFlags_Values[q17] = -4 + | q17 : int(1..11)]), + and([var2_ExplicitVarSizeWithFlags_Flags[q18 + 1] -> var2_ExplicitVarSizeWithFlags_Flags[q18] | q18 : int(1..10)]), + and([var2_ExplicitVarSizeWithFlags_Flags[q22] -> + or([var2_ExplicitVarSizeWithDummy[q24] != 6 /\ + var2_ExplicitVarSizeWithDummy[q24] = var2_ExplicitVarSizeWithFlags_Values[q22] + | q24 : int(1..11)]) + | q22 : int(1..11)]), + and([var2_ExplicitVarSizeWithDummy[q26] != 6 -> + or([var2_ExplicitVarSizeWithFlags_Flags[q28] /\ + var2_ExplicitVarSizeWithFlags_Values[q28] = var2_ExplicitVarSizeWithDummy[q26] + | q28 : int(1..11)]) + | q26 : int(1..11)]), + and([var2_ExplicitVarSizeWithFlags_Flags[q30] -> + or([q32 <= var2_ExplicitVarSizeWithMarker_Marker /\ + var2_ExplicitVarSizeWithMarker_Values[q32] = var2_ExplicitVarSizeWithFlags_Values[q30] + | q32 : int(1..11)]) + | q30 : int(1..11)]), + and([q34 <= var2_ExplicitVarSizeWithMarker_Marker -> + or([var2_ExplicitVarSizeWithFlags_Flags[q36] /\ + var2_ExplicitVarSizeWithFlags_Values[q36] = var2_ExplicitVarSizeWithMarker_Values[q34] + | q36 : int(1..11)]) + | q34 : int(1..11)]) + diff --git a/tests/exhaustive/autogen/gen32/expected/model_2_4_1.eprime b/tests/exhaustive/autogen/gen32/expected/model_2_4_1.eprime new file mode 100644 index 0000000000..e1fcf174dd --- /dev/null +++ b/tests/exhaustive/autogen/gen32/expected/model_2_4_1.eprime @@ -0,0 +1,54 @@ +language ESSENCE' 1.0 + +letting let1 be -4 +find var2_ExplicitVarSizeWithDummy: matrix indexed by [int(1..11)] of int(-4..5, 2, 6) +find var2_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..11)] of bool +find var2_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..11)] of int(-4..5, 2) +find var2_Occurrence: matrix indexed by [int(-4..5, 2)] of bool +branching on + [var2_Occurrence, var2_ExplicitVarSizeWithDummy, var2_ExplicitVarSizeWithFlags_Flags, + var2_ExplicitVarSizeWithFlags_Values] +such that + or([var2_ExplicitVarSizeWithDummy[q20] != 6 /\ + !or([var2_ExplicitVarSizeWithFlags_Flags[q22] /\ + var2_ExplicitVarSizeWithFlags_Values[q22] = var2_ExplicitVarSizeWithDummy[q20] + | q22 : int(1..11)]) + | q20 : int(1..11)]) + \/ + or([var2_ExplicitVarSizeWithFlags_Flags[q23] /\ + !or([var2_ExplicitVarSizeWithDummy[q25] != 6 /\ + var2_ExplicitVarSizeWithDummy[q25] = var2_ExplicitVarSizeWithFlags_Values[q23] + | q25 : int(1..11)]) + | q23 : int(1..11)]), + and([var2_ExplicitVarSizeWithDummy[q1] < var2_ExplicitVarSizeWithDummy[q1 + 1] \/ + var2_ExplicitVarSizeWithDummy[q1] = 6 + | q1 : int(1..10)]), + and([var2_ExplicitVarSizeWithDummy[q2] = 6 -> var2_ExplicitVarSizeWithDummy[q2 + 1] = 6 | q2 : int(1..10)]), + and([var2_ExplicitVarSizeWithFlags_Flags[q5 + 1] -> + var2_ExplicitVarSizeWithFlags_Values[q5] < var2_ExplicitVarSizeWithFlags_Values[q5 + 1] + | q5 : int(1..10)]), + and([var2_ExplicitVarSizeWithFlags_Flags[q6] = false -> var2_ExplicitVarSizeWithFlags_Values[q6] = -4 + | q6 : int(1..11)]), + and([var2_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> var2_ExplicitVarSizeWithFlags_Flags[q7] | q7 : int(1..10)]), + and([var2_ExplicitVarSizeWithFlags_Flags[q11] -> + or([var2_ExplicitVarSizeWithDummy[q13] != 6 /\ + var2_ExplicitVarSizeWithDummy[q13] = var2_ExplicitVarSizeWithFlags_Values[q11] + | q13 : int(1..11)]) + | q11 : int(1..11)]), + and([var2_ExplicitVarSizeWithDummy[q15] != 6 -> + or([var2_ExplicitVarSizeWithFlags_Flags[q17] /\ + var2_ExplicitVarSizeWithFlags_Values[q17] = var2_ExplicitVarSizeWithDummy[q15] + | q17 : int(1..11)]) + | q15 : int(1..11)]), + and([var2_Occurrence[q26] -> + or([var2_ExplicitVarSizeWithDummy[q28] != 6 /\ var2_ExplicitVarSizeWithDummy[q28] = q26 | q28 : int(1..11)]) + | q26 : int(-4..5, 2)]), + and([var2_ExplicitVarSizeWithDummy[q30] != 6 -> var2_Occurrence[var2_ExplicitVarSizeWithDummy[q30]] + | q30 : int(1..11)]), + and([var2_Occurrence[q31] -> + or([var2_ExplicitVarSizeWithFlags_Flags[q33] /\ var2_ExplicitVarSizeWithFlags_Values[q33] = q31 + | q33 : int(1..11)]) + | q31 : int(-4..5, 2)]), + and([var2_ExplicitVarSizeWithFlags_Flags[q35] -> var2_Occurrence[var2_ExplicitVarSizeWithFlags_Values[q35]] + | q35 : int(1..11)]) + diff --git a/tests/exhaustive/autogen/gen32/expected/model_2_4_2.eprime b/tests/exhaustive/autogen/gen32/expected/model_2_4_2.eprime new file mode 100644 index 0000000000..d3c3ed6086 --- /dev/null +++ b/tests/exhaustive/autogen/gen32/expected/model_2_4_2.eprime @@ -0,0 +1,40 @@ +language ESSENCE' 1.0 + +letting let1 be -4 +find var2_ExplicitVarSizeWithDummy: matrix indexed by [int(1..11)] of int(-4..5, 2, 6) +find var2_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..11)] of bool +find var2_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..11)] of int(-4..5, 2) +branching on [var2_ExplicitVarSizeWithFlags_Flags, var2_ExplicitVarSizeWithFlags_Values, var2_ExplicitVarSizeWithDummy] +such that + or([var2_ExplicitVarSizeWithDummy[q19] != 6 /\ + !or([var2_ExplicitVarSizeWithFlags_Flags[q21] /\ + var2_ExplicitVarSizeWithFlags_Values[q21] = var2_ExplicitVarSizeWithDummy[q19] + | q21 : int(1..11)]) + | q19 : int(1..11)]) + \/ + or([var2_ExplicitVarSizeWithFlags_Flags[q22] /\ + !or([var2_ExplicitVarSizeWithDummy[q24] != 6 /\ + var2_ExplicitVarSizeWithDummy[q24] = var2_ExplicitVarSizeWithFlags_Values[q22] + | q24 : int(1..11)]) + | q22 : int(1..11)]), + and([var2_ExplicitVarSizeWithDummy[q1] < var2_ExplicitVarSizeWithDummy[q1 + 1] \/ + var2_ExplicitVarSizeWithDummy[q1] = 6 + | q1 : int(1..10)]), + and([var2_ExplicitVarSizeWithDummy[q2] = 6 -> var2_ExplicitVarSizeWithDummy[q2 + 1] = 6 | q2 : int(1..10)]), + and([var2_ExplicitVarSizeWithFlags_Flags[q5 + 1] -> + var2_ExplicitVarSizeWithFlags_Values[q5] < var2_ExplicitVarSizeWithFlags_Values[q5 + 1] + | q5 : int(1..10)]), + and([var2_ExplicitVarSizeWithFlags_Flags[q6] = false -> var2_ExplicitVarSizeWithFlags_Values[q6] = -4 + | q6 : int(1..11)]), + and([var2_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> var2_ExplicitVarSizeWithFlags_Flags[q7] | q7 : int(1..10)]), + and([var2_ExplicitVarSizeWithFlags_Flags[q11] -> + or([var2_ExplicitVarSizeWithDummy[q13] != 6 /\ + var2_ExplicitVarSizeWithDummy[q13] = var2_ExplicitVarSizeWithFlags_Values[q11] + | q13 : int(1..11)]) + | q11 : int(1..11)]), + and([var2_ExplicitVarSizeWithDummy[q15] != 6 -> + or([var2_ExplicitVarSizeWithFlags_Flags[q17] /\ + var2_ExplicitVarSizeWithFlags_Values[q17] = var2_ExplicitVarSizeWithDummy[q15] + | q17 : int(1..11)]) + | q15 : int(1..11)]) + diff --git a/tests/exhaustive/autogen/gen32/expected/model_2_4_3.eprime b/tests/exhaustive/autogen/gen32/expected/model_2_4_3.eprime new file mode 100644 index 0000000000..298bb93993 --- /dev/null +++ b/tests/exhaustive/autogen/gen32/expected/model_2_4_3.eprime @@ -0,0 +1,69 @@ +language ESSENCE' 1.0 + +letting let1 be -4 +find var2_ExplicitVarSizeWithDummy: matrix indexed by [int(1..11)] of int(-4..5, 2, 6) +find var2_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..11)] of bool +find var2_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..11)] of int(-4..5, 2) +find var2_ExplicitVarSizeWithMarker_Marker: int(0..11) +find var2_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..11)] of int(-4..5, 2) +branching on + [var2_ExplicitVarSizeWithMarker_Marker, var2_ExplicitVarSizeWithMarker_Values, var2_ExplicitVarSizeWithDummy, + var2_ExplicitVarSizeWithFlags_Flags, var2_ExplicitVarSizeWithFlags_Values] +such that + or([var2_ExplicitVarSizeWithDummy[q38] != 6 /\ + !or([var2_ExplicitVarSizeWithFlags_Flags[q40] /\ + var2_ExplicitVarSizeWithFlags_Values[q40] = var2_ExplicitVarSizeWithDummy[q38] + | q40 : int(1..11)]) + | q38 : int(1..11)]) + \/ + or([var2_ExplicitVarSizeWithFlags_Flags[q41] /\ + !or([var2_ExplicitVarSizeWithDummy[q43] != 6 /\ + var2_ExplicitVarSizeWithDummy[q43] = var2_ExplicitVarSizeWithFlags_Values[q41] + | q43 : int(1..11)]) + | q41 : int(1..11)]), + and([var2_ExplicitVarSizeWithDummy[q1] < var2_ExplicitVarSizeWithDummy[q1 + 1] \/ + var2_ExplicitVarSizeWithDummy[q1] = 6 + | q1 : int(1..10)]), + and([var2_ExplicitVarSizeWithDummy[q2] = 6 -> var2_ExplicitVarSizeWithDummy[q2 + 1] = 6 | q2 : int(1..10)]), + and([var2_ExplicitVarSizeWithFlags_Flags[q5 + 1] -> + var2_ExplicitVarSizeWithFlags_Values[q5] < var2_ExplicitVarSizeWithFlags_Values[q5 + 1] + | q5 : int(1..10)]), + and([var2_ExplicitVarSizeWithFlags_Flags[q6] = false -> var2_ExplicitVarSizeWithFlags_Values[q6] = -4 + | q6 : int(1..11)]), + and([var2_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> var2_ExplicitVarSizeWithFlags_Flags[q7] | q7 : int(1..10)]), + and([var2_ExplicitVarSizeWithFlags_Flags[q11] -> + or([var2_ExplicitVarSizeWithDummy[q13] != 6 /\ + var2_ExplicitVarSizeWithDummy[q13] = var2_ExplicitVarSizeWithFlags_Values[q11] + | q13 : int(1..11)]) + | q11 : int(1..11)]), + and([var2_ExplicitVarSizeWithDummy[q15] != 6 -> + or([var2_ExplicitVarSizeWithFlags_Flags[q17] /\ + var2_ExplicitVarSizeWithFlags_Values[q17] = var2_ExplicitVarSizeWithDummy[q15] + | q17 : int(1..11)]) + | q15 : int(1..11)]), + and([q18 + 1 <= var2_ExplicitVarSizeWithMarker_Marker -> + var2_ExplicitVarSizeWithMarker_Values[q18] < var2_ExplicitVarSizeWithMarker_Values[q18 + 1] + | q18 : int(1..10)]), + and([q19 > var2_ExplicitVarSizeWithMarker_Marker -> var2_ExplicitVarSizeWithMarker_Values[q19] = -4 + | q19 : int(1..11)]), + and([q22 <= var2_ExplicitVarSizeWithMarker_Marker -> + or([var2_ExplicitVarSizeWithDummy[q24] != 6 /\ + var2_ExplicitVarSizeWithDummy[q24] = var2_ExplicitVarSizeWithMarker_Values[q22] + | q24 : int(1..11)]) + | q22 : int(1..11)]), + and([var2_ExplicitVarSizeWithDummy[q26] != 6 -> + or([q28 <= var2_ExplicitVarSizeWithMarker_Marker /\ + var2_ExplicitVarSizeWithMarker_Values[q28] = var2_ExplicitVarSizeWithDummy[q26] + | q28 : int(1..11)]) + | q26 : int(1..11)]), + and([q30 <= var2_ExplicitVarSizeWithMarker_Marker -> + or([var2_ExplicitVarSizeWithFlags_Flags[q32] /\ + var2_ExplicitVarSizeWithFlags_Values[q32] = var2_ExplicitVarSizeWithMarker_Values[q30] + | q32 : int(1..11)]) + | q30 : int(1..11)]), + and([var2_ExplicitVarSizeWithFlags_Flags[q34] -> + or([q36 <= var2_ExplicitVarSizeWithMarker_Marker /\ + var2_ExplicitVarSizeWithMarker_Values[q36] = var2_ExplicitVarSizeWithFlags_Values[q34] + | q36 : int(1..11)]) + | q34 : int(1..11)]) + diff --git a/tests/exhaustive/autogen/gen32/expected/model_3_1_1.eprime b/tests/exhaustive/autogen/gen32/expected/model_3_1_1.eprime new file mode 100644 index 0000000000..c841bbbe9f --- /dev/null +++ b/tests/exhaustive/autogen/gen32/expected/model_3_1_1.eprime @@ -0,0 +1,27 @@ +language ESSENCE' 1.0 + +letting let1 be -4 +find var2_ExplicitVarSizeWithMarker_Marker: int(0..11) +find var2_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..11)] of int(-4..5, 2) +find var2_Occurrence: matrix indexed by [int(-4..5, 2)] of bool +branching on [var2_Occurrence, var2_ExplicitVarSizeWithMarker_Marker, var2_ExplicitVarSizeWithMarker_Values] +such that + or([q6 <= var2_ExplicitVarSizeWithMarker_Marker /\ !var2_Occurrence[var2_ExplicitVarSizeWithMarker_Values[q6]] + | q6 : int(1..11)]) + \/ + or([var2_Occurrence[q5] /\ + !or([q8 <= var2_ExplicitVarSizeWithMarker_Marker /\ var2_ExplicitVarSizeWithMarker_Values[q8] = q5 + | q8 : int(1..11)]) + | q5 : int(-4..5, 2)]), + and([q1 + 1 <= var2_ExplicitVarSizeWithMarker_Marker -> + var2_ExplicitVarSizeWithMarker_Values[q1] < var2_ExplicitVarSizeWithMarker_Values[q1 + 1] + | q1 : int(1..10)]), + and([q2 > var2_ExplicitVarSizeWithMarker_Marker -> var2_ExplicitVarSizeWithMarker_Values[q2] = -4 + | q2 : int(1..11)]), + and([var2_Occurrence[q9] -> + or([q11 <= var2_ExplicitVarSizeWithMarker_Marker /\ var2_ExplicitVarSizeWithMarker_Values[q11] = q9 + | q11 : int(1..11)]) + | q9 : int(-4..5, 2)]), + and([q13 <= var2_ExplicitVarSizeWithMarker_Marker -> var2_Occurrence[var2_ExplicitVarSizeWithMarker_Values[q13]] + | q13 : int(1..11)]) + diff --git a/tests/exhaustive/autogen/gen32/expected/model_3_1_2.eprime b/tests/exhaustive/autogen/gen32/expected/model_3_1_2.eprime new file mode 100644 index 0000000000..7e7b9ddfa6 --- /dev/null +++ b/tests/exhaustive/autogen/gen32/expected/model_3_1_2.eprime @@ -0,0 +1,49 @@ +language ESSENCE' 1.0 + +letting let1 be -4 +find var2_ExplicitVarSizeWithMarker_Marker: int(0..11) +find var2_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..11)] of int(-4..5, 2) +find var2_Occurrence: matrix indexed by [int(-4..5, 2)] of bool +find var2_ExplicitVarSizeWithDummy: matrix indexed by [int(1..11)] of int(-4..5, 2, 6) +branching on + [var2_ExplicitVarSizeWithDummy, var2_ExplicitVarSizeWithMarker_Marker, var2_ExplicitVarSizeWithMarker_Values, + var2_Occurrence] +such that + or([q23 <= var2_ExplicitVarSizeWithMarker_Marker /\ !var2_Occurrence[var2_ExplicitVarSizeWithMarker_Values[q23]] + | q23 : int(1..11)]) + \/ + or([var2_Occurrence[q22] /\ + !or([q25 <= var2_ExplicitVarSizeWithMarker_Marker /\ var2_ExplicitVarSizeWithMarker_Values[q25] = q22 + | q25 : int(1..11)]) + | q22 : int(-4..5, 2)]), + and([q1 + 1 <= var2_ExplicitVarSizeWithMarker_Marker -> + var2_ExplicitVarSizeWithMarker_Values[q1] < var2_ExplicitVarSizeWithMarker_Values[q1 + 1] + | q1 : int(1..10)]), + and([q2 > var2_ExplicitVarSizeWithMarker_Marker -> var2_ExplicitVarSizeWithMarker_Values[q2] = -4 + | q2 : int(1..11)]), + and([var2_Occurrence[q26] -> + or([q28 <= var2_ExplicitVarSizeWithMarker_Marker /\ var2_ExplicitVarSizeWithMarker_Values[q28] = q26 + | q28 : int(1..11)]) + | q26 : int(-4..5, 2)]), + and([q30 <= var2_ExplicitVarSizeWithMarker_Marker -> var2_Occurrence[var2_ExplicitVarSizeWithMarker_Values[q30]] + | q30 : int(1..11)]), + and([var2_ExplicitVarSizeWithDummy[q5] < var2_ExplicitVarSizeWithDummy[q5 + 1] \/ + var2_ExplicitVarSizeWithDummy[q5] = 6 + | q5 : int(1..10)]), + and([var2_ExplicitVarSizeWithDummy[q6] = 6 -> var2_ExplicitVarSizeWithDummy[q6 + 1] = 6 | q6 : int(1..10)]), + and([var2_ExplicitVarSizeWithDummy[q10] != 6 -> + or([q12 <= var2_ExplicitVarSizeWithMarker_Marker /\ + var2_ExplicitVarSizeWithMarker_Values[q12] = var2_ExplicitVarSizeWithDummy[q10] + | q12 : int(1..11)]) + | q10 : int(1..11)]), + and([q14 <= var2_ExplicitVarSizeWithMarker_Marker -> + or([var2_ExplicitVarSizeWithDummy[q16] != 6 /\ + var2_ExplicitVarSizeWithDummy[q16] = var2_ExplicitVarSizeWithMarker_Values[q14] + | q16 : int(1..11)]) + | q14 : int(1..11)]), + and([var2_ExplicitVarSizeWithDummy[q18] != 6 -> var2_Occurrence[var2_ExplicitVarSizeWithDummy[q18]] + | q18 : int(1..11)]), + and([var2_Occurrence[q19] -> + or([var2_ExplicitVarSizeWithDummy[q21] != 6 /\ var2_ExplicitVarSizeWithDummy[q21] = q19 | q21 : int(1..11)]) + | q19 : int(-4..5, 2)]) + diff --git a/tests/exhaustive/autogen/gen32/expected/model_3_1_4.eprime b/tests/exhaustive/autogen/gen32/expected/model_3_1_4.eprime new file mode 100644 index 0000000000..a2676c1f31 --- /dev/null +++ b/tests/exhaustive/autogen/gen32/expected/model_3_1_4.eprime @@ -0,0 +1,53 @@ +language ESSENCE' 1.0 + +letting let1 be -4 +find var2_ExplicitVarSizeWithMarker_Marker: int(0..11) +find var2_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..11)] of int(-4..5, 2) +find var2_Occurrence: matrix indexed by [int(-4..5, 2)] of bool +find var2_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..11)] of bool +find var2_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..11)] of int(-4..5, 2) +branching on + [var2_ExplicitVarSizeWithFlags_Flags, var2_ExplicitVarSizeWithFlags_Values, var2_ExplicitVarSizeWithMarker_Marker, + var2_ExplicitVarSizeWithMarker_Values, var2_Occurrence] +such that + or([q24 <= var2_ExplicitVarSizeWithMarker_Marker /\ !var2_Occurrence[var2_ExplicitVarSizeWithMarker_Values[q24]] + | q24 : int(1..11)]) + \/ + or([var2_Occurrence[q23] /\ + !or([q26 <= var2_ExplicitVarSizeWithMarker_Marker /\ var2_ExplicitVarSizeWithMarker_Values[q26] = q23 + | q26 : int(1..11)]) + | q23 : int(-4..5, 2)]), + and([q1 + 1 <= var2_ExplicitVarSizeWithMarker_Marker -> + var2_ExplicitVarSizeWithMarker_Values[q1] < var2_ExplicitVarSizeWithMarker_Values[q1 + 1] + | q1 : int(1..10)]), + and([q2 > var2_ExplicitVarSizeWithMarker_Marker -> var2_ExplicitVarSizeWithMarker_Values[q2] = -4 + | q2 : int(1..11)]), + and([var2_Occurrence[q27] -> + or([q29 <= var2_ExplicitVarSizeWithMarker_Marker /\ var2_ExplicitVarSizeWithMarker_Values[q29] = q27 + | q29 : int(1..11)]) + | q27 : int(-4..5, 2)]), + and([q31 <= var2_ExplicitVarSizeWithMarker_Marker -> var2_Occurrence[var2_ExplicitVarSizeWithMarker_Values[q31]] + | q31 : int(1..11)]), + and([var2_ExplicitVarSizeWithFlags_Flags[q5 + 1] -> + var2_ExplicitVarSizeWithFlags_Values[q5] < var2_ExplicitVarSizeWithFlags_Values[q5 + 1] + | q5 : int(1..10)]), + and([var2_ExplicitVarSizeWithFlags_Flags[q6] = false -> var2_ExplicitVarSizeWithFlags_Values[q6] = -4 + | q6 : int(1..11)]), + and([var2_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> var2_ExplicitVarSizeWithFlags_Flags[q7] | q7 : int(1..10)]), + and([var2_ExplicitVarSizeWithFlags_Flags[q11] -> + or([q13 <= var2_ExplicitVarSizeWithMarker_Marker /\ + var2_ExplicitVarSizeWithMarker_Values[q13] = var2_ExplicitVarSizeWithFlags_Values[q11] + | q13 : int(1..11)]) + | q11 : int(1..11)]), + and([q15 <= var2_ExplicitVarSizeWithMarker_Marker -> + or([var2_ExplicitVarSizeWithFlags_Flags[q17] /\ + var2_ExplicitVarSizeWithFlags_Values[q17] = var2_ExplicitVarSizeWithMarker_Values[q15] + | q17 : int(1..11)]) + | q15 : int(1..11)]), + and([var2_ExplicitVarSizeWithFlags_Flags[q19] -> var2_Occurrence[var2_ExplicitVarSizeWithFlags_Values[q19]] + | q19 : int(1..11)]), + and([var2_Occurrence[q20] -> + or([var2_ExplicitVarSizeWithFlags_Flags[q22] /\ var2_ExplicitVarSizeWithFlags_Values[q22] = q20 + | q22 : int(1..11)]) + | q20 : int(-4..5, 2)]) + diff --git a/tests/exhaustive/autogen/gen32/expected/model_3_2_1.eprime b/tests/exhaustive/autogen/gen32/expected/model_3_2_1.eprime new file mode 100644 index 0000000000..86dbab6810 --- /dev/null +++ b/tests/exhaustive/autogen/gen32/expected/model_3_2_1.eprime @@ -0,0 +1,53 @@ +language ESSENCE' 1.0 + +letting let1 be -4 +find var2_ExplicitVarSizeWithMarker_Marker: int(0..11) +find var2_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..11)] of int(-4..5, 2) +find var2_ExplicitVarSizeWithDummy: matrix indexed by [int(1..11)] of int(-4..5, 2, 6) +find var2_Occurrence: matrix indexed by [int(-4..5, 2)] of bool +branching on + [var2_Occurrence, var2_ExplicitVarSizeWithMarker_Marker, var2_ExplicitVarSizeWithMarker_Values, + var2_ExplicitVarSizeWithDummy] +such that + or([q18 <= var2_ExplicitVarSizeWithMarker_Marker /\ + !or([var2_ExplicitVarSizeWithDummy[q20] != 6 /\ + var2_ExplicitVarSizeWithDummy[q20] = var2_ExplicitVarSizeWithMarker_Values[q18] + | q20 : int(1..11)]) + | q18 : int(1..11)]) + \/ + or([var2_ExplicitVarSizeWithDummy[q21] != 6 /\ + !or([q23 <= var2_ExplicitVarSizeWithMarker_Marker /\ + var2_ExplicitVarSizeWithMarker_Values[q23] = var2_ExplicitVarSizeWithDummy[q21] + | q23 : int(1..11)]) + | q21 : int(1..11)]), + and([q1 + 1 <= var2_ExplicitVarSizeWithMarker_Marker -> + var2_ExplicitVarSizeWithMarker_Values[q1] < var2_ExplicitVarSizeWithMarker_Values[q1 + 1] + | q1 : int(1..10)]), + and([q2 > var2_ExplicitVarSizeWithMarker_Marker -> var2_ExplicitVarSizeWithMarker_Values[q2] = -4 + | q2 : int(1..11)]), + and([var2_ExplicitVarSizeWithDummy[q4] < var2_ExplicitVarSizeWithDummy[q4 + 1] \/ + var2_ExplicitVarSizeWithDummy[q4] = 6 + | q4 : int(1..10)]), + and([var2_ExplicitVarSizeWithDummy[q5] = 6 -> var2_ExplicitVarSizeWithDummy[q5 + 1] = 6 | q5 : int(1..10)]), + and([var2_ExplicitVarSizeWithDummy[q9] != 6 -> + or([q11 <= var2_ExplicitVarSizeWithMarker_Marker /\ + var2_ExplicitVarSizeWithMarker_Values[q11] = var2_ExplicitVarSizeWithDummy[q9] + | q11 : int(1..11)]) + | q9 : int(1..11)]), + and([q13 <= var2_ExplicitVarSizeWithMarker_Marker -> + or([var2_ExplicitVarSizeWithDummy[q15] != 6 /\ + var2_ExplicitVarSizeWithDummy[q15] = var2_ExplicitVarSizeWithMarker_Values[q13] + | q15 : int(1..11)]) + | q13 : int(1..11)]), + and([var2_Occurrence[q24] -> + or([q26 <= var2_ExplicitVarSizeWithMarker_Marker /\ var2_ExplicitVarSizeWithMarker_Values[q26] = q24 + | q26 : int(1..11)]) + | q24 : int(-4..5, 2)]), + and([q28 <= var2_ExplicitVarSizeWithMarker_Marker -> var2_Occurrence[var2_ExplicitVarSizeWithMarker_Values[q28]] + | q28 : int(1..11)]), + and([var2_Occurrence[q29] -> + or([var2_ExplicitVarSizeWithDummy[q31] != 6 /\ var2_ExplicitVarSizeWithDummy[q31] = q29 | q31 : int(1..11)]) + | q29 : int(-4..5, 2)]), + and([var2_ExplicitVarSizeWithDummy[q33] != 6 -> var2_Occurrence[var2_ExplicitVarSizeWithDummy[q33]] + | q33 : int(1..11)]) + diff --git a/tests/exhaustive/autogen/gen32/expected/model_3_2_2.eprime b/tests/exhaustive/autogen/gen32/expected/model_3_2_2.eprime new file mode 100644 index 0000000000..c9a6281665 --- /dev/null +++ b/tests/exhaustive/autogen/gen32/expected/model_3_2_2.eprime @@ -0,0 +1,40 @@ +language ESSENCE' 1.0 + +letting let1 be -4 +find var2_ExplicitVarSizeWithMarker_Marker: int(0..11) +find var2_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..11)] of int(-4..5, 2) +find var2_ExplicitVarSizeWithDummy: matrix indexed by [int(1..11)] of int(-4..5, 2, 6) +branching on + [var2_ExplicitVarSizeWithDummy, var2_ExplicitVarSizeWithMarker_Marker, var2_ExplicitVarSizeWithMarker_Values] +such that + or([q17 <= var2_ExplicitVarSizeWithMarker_Marker /\ + !or([var2_ExplicitVarSizeWithDummy[q19] != 6 /\ + var2_ExplicitVarSizeWithDummy[q19] = var2_ExplicitVarSizeWithMarker_Values[q17] + | q19 : int(1..11)]) + | q17 : int(1..11)]) + \/ + or([var2_ExplicitVarSizeWithDummy[q20] != 6 /\ + !or([q22 <= var2_ExplicitVarSizeWithMarker_Marker /\ + var2_ExplicitVarSizeWithMarker_Values[q22] = var2_ExplicitVarSizeWithDummy[q20] + | q22 : int(1..11)]) + | q20 : int(1..11)]), + and([q1 + 1 <= var2_ExplicitVarSizeWithMarker_Marker -> + var2_ExplicitVarSizeWithMarker_Values[q1] < var2_ExplicitVarSizeWithMarker_Values[q1 + 1] + | q1 : int(1..10)]), + and([q2 > var2_ExplicitVarSizeWithMarker_Marker -> var2_ExplicitVarSizeWithMarker_Values[q2] = -4 + | q2 : int(1..11)]), + and([var2_ExplicitVarSizeWithDummy[q4] < var2_ExplicitVarSizeWithDummy[q4 + 1] \/ + var2_ExplicitVarSizeWithDummy[q4] = 6 + | q4 : int(1..10)]), + and([var2_ExplicitVarSizeWithDummy[q5] = 6 -> var2_ExplicitVarSizeWithDummy[q5 + 1] = 6 | q5 : int(1..10)]), + and([var2_ExplicitVarSizeWithDummy[q9] != 6 -> + or([q11 <= var2_ExplicitVarSizeWithMarker_Marker /\ + var2_ExplicitVarSizeWithMarker_Values[q11] = var2_ExplicitVarSizeWithDummy[q9] + | q11 : int(1..11)]) + | q9 : int(1..11)]), + and([q13 <= var2_ExplicitVarSizeWithMarker_Marker -> + or([var2_ExplicitVarSizeWithDummy[q15] != 6 /\ + var2_ExplicitVarSizeWithDummy[q15] = var2_ExplicitVarSizeWithMarker_Values[q13] + | q15 : int(1..11)]) + | q13 : int(1..11)]) + diff --git a/tests/exhaustive/autogen/gen32/expected/model_3_2_4.eprime b/tests/exhaustive/autogen/gen32/expected/model_3_2_4.eprime new file mode 100644 index 0000000000..0a6285920a --- /dev/null +++ b/tests/exhaustive/autogen/gen32/expected/model_3_2_4.eprime @@ -0,0 +1,69 @@ +language ESSENCE' 1.0 + +letting let1 be -4 +find var2_ExplicitVarSizeWithMarker_Marker: int(0..11) +find var2_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..11)] of int(-4..5, 2) +find var2_ExplicitVarSizeWithDummy: matrix indexed by [int(1..11)] of int(-4..5, 2, 6) +find var2_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..11)] of bool +find var2_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..11)] of int(-4..5, 2) +branching on + [var2_ExplicitVarSizeWithFlags_Flags, var2_ExplicitVarSizeWithFlags_Values, var2_ExplicitVarSizeWithMarker_Marker, + var2_ExplicitVarSizeWithMarker_Values, var2_ExplicitVarSizeWithDummy] +such that + or([q38 <= var2_ExplicitVarSizeWithMarker_Marker /\ + !or([var2_ExplicitVarSizeWithDummy[q40] != 6 /\ + var2_ExplicitVarSizeWithDummy[q40] = var2_ExplicitVarSizeWithMarker_Values[q38] + | q40 : int(1..11)]) + | q38 : int(1..11)]) + \/ + or([var2_ExplicitVarSizeWithDummy[q41] != 6 /\ + !or([q43 <= var2_ExplicitVarSizeWithMarker_Marker /\ + var2_ExplicitVarSizeWithMarker_Values[q43] = var2_ExplicitVarSizeWithDummy[q41] + | q43 : int(1..11)]) + | q41 : int(1..11)]), + and([q1 + 1 <= var2_ExplicitVarSizeWithMarker_Marker -> + var2_ExplicitVarSizeWithMarker_Values[q1] < var2_ExplicitVarSizeWithMarker_Values[q1 + 1] + | q1 : int(1..10)]), + and([q2 > var2_ExplicitVarSizeWithMarker_Marker -> var2_ExplicitVarSizeWithMarker_Values[q2] = -4 + | q2 : int(1..11)]), + and([var2_ExplicitVarSizeWithDummy[q4] < var2_ExplicitVarSizeWithDummy[q4 + 1] \/ + var2_ExplicitVarSizeWithDummy[q4] = 6 + | q4 : int(1..10)]), + and([var2_ExplicitVarSizeWithDummy[q5] = 6 -> var2_ExplicitVarSizeWithDummy[q5 + 1] = 6 | q5 : int(1..10)]), + and([var2_ExplicitVarSizeWithDummy[q9] != 6 -> + or([q11 <= var2_ExplicitVarSizeWithMarker_Marker /\ + var2_ExplicitVarSizeWithMarker_Values[q11] = var2_ExplicitVarSizeWithDummy[q9] + | q11 : int(1..11)]) + | q9 : int(1..11)]), + and([q13 <= var2_ExplicitVarSizeWithMarker_Marker -> + or([var2_ExplicitVarSizeWithDummy[q15] != 6 /\ + var2_ExplicitVarSizeWithDummy[q15] = var2_ExplicitVarSizeWithMarker_Values[q13] + | q15 : int(1..11)]) + | q13 : int(1..11)]), + and([var2_ExplicitVarSizeWithFlags_Flags[q16 + 1] -> + var2_ExplicitVarSizeWithFlags_Values[q16] < var2_ExplicitVarSizeWithFlags_Values[q16 + 1] + | q16 : int(1..10)]), + and([var2_ExplicitVarSizeWithFlags_Flags[q17] = false -> var2_ExplicitVarSizeWithFlags_Values[q17] = -4 + | q17 : int(1..11)]), + and([var2_ExplicitVarSizeWithFlags_Flags[q18 + 1] -> var2_ExplicitVarSizeWithFlags_Flags[q18] | q18 : int(1..10)]), + and([var2_ExplicitVarSizeWithFlags_Flags[q22] -> + or([q24 <= var2_ExplicitVarSizeWithMarker_Marker /\ + var2_ExplicitVarSizeWithMarker_Values[q24] = var2_ExplicitVarSizeWithFlags_Values[q22] + | q24 : int(1..11)]) + | q22 : int(1..11)]), + and([q26 <= var2_ExplicitVarSizeWithMarker_Marker -> + or([var2_ExplicitVarSizeWithFlags_Flags[q28] /\ + var2_ExplicitVarSizeWithFlags_Values[q28] = var2_ExplicitVarSizeWithMarker_Values[q26] + | q28 : int(1..11)]) + | q26 : int(1..11)]), + and([var2_ExplicitVarSizeWithFlags_Flags[q30] -> + or([var2_ExplicitVarSizeWithDummy[q32] != 6 /\ + var2_ExplicitVarSizeWithDummy[q32] = var2_ExplicitVarSizeWithFlags_Values[q30] + | q32 : int(1..11)]) + | q30 : int(1..11)]), + and([var2_ExplicitVarSizeWithDummy[q34] != 6 -> + or([var2_ExplicitVarSizeWithFlags_Flags[q36] /\ + var2_ExplicitVarSizeWithFlags_Values[q36] = var2_ExplicitVarSizeWithDummy[q34] + | q36 : int(1..11)]) + | q34 : int(1..11)]) + diff --git a/tests/exhaustive/autogen/gen32/expected/model_3_3_1.eprime b/tests/exhaustive/autogen/gen32/expected/model_3_3_1.eprime new file mode 100644 index 0000000000..da12cb2407 --- /dev/null +++ b/tests/exhaustive/autogen/gen32/expected/model_3_3_1.eprime @@ -0,0 +1,31 @@ +language ESSENCE' 1.0 + +letting let1 be -4 +find var2_ExplicitVarSizeWithMarker_Marker: int(0..11) +find var2_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..11)] of int(-4..5, 2) +find var2_Occurrence: matrix indexed by [int(-4..5, 2)] of bool +branching on [var2_Occurrence, var2_ExplicitVarSizeWithMarker_Marker, var2_ExplicitVarSizeWithMarker_Values] +such that + or([q6 <= var2_ExplicitVarSizeWithMarker_Marker /\ + !or([q8 <= var2_ExplicitVarSizeWithMarker_Marker /\ + var2_ExplicitVarSizeWithMarker_Values[q8] = var2_ExplicitVarSizeWithMarker_Values[q6] + | q8 : int(1..11)]) + | q6 : int(1..11)]) + \/ + or([q9 <= var2_ExplicitVarSizeWithMarker_Marker /\ + !or([q11 <= var2_ExplicitVarSizeWithMarker_Marker /\ + var2_ExplicitVarSizeWithMarker_Values[q11] = var2_ExplicitVarSizeWithMarker_Values[q9] + | q11 : int(1..11)]) + | q9 : int(1..11)]), + and([q1 + 1 <= var2_ExplicitVarSizeWithMarker_Marker -> + var2_ExplicitVarSizeWithMarker_Values[q1] < var2_ExplicitVarSizeWithMarker_Values[q1 + 1] + | q1 : int(1..10)]), + and([q2 > var2_ExplicitVarSizeWithMarker_Marker -> var2_ExplicitVarSizeWithMarker_Values[q2] = -4 + | q2 : int(1..11)]), + and([var2_Occurrence[q12] -> + or([q14 <= var2_ExplicitVarSizeWithMarker_Marker /\ var2_ExplicitVarSizeWithMarker_Values[q14] = q12 + | q14 : int(1..11)]) + | q12 : int(-4..5, 2)]), + and([q16 <= var2_ExplicitVarSizeWithMarker_Marker -> var2_Occurrence[var2_ExplicitVarSizeWithMarker_Values[q16]] + | q16 : int(1..11)]) + diff --git a/tests/exhaustive/autogen/gen32/expected/model_3_3_2.eprime b/tests/exhaustive/autogen/gen32/expected/model_3_3_2.eprime new file mode 100644 index 0000000000..4b5f1c3017 --- /dev/null +++ b/tests/exhaustive/autogen/gen32/expected/model_3_3_2.eprime @@ -0,0 +1,40 @@ +language ESSENCE' 1.0 + +letting let1 be -4 +find var2_ExplicitVarSizeWithMarker_Marker: int(0..11) +find var2_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..11)] of int(-4..5, 2) +find var2_ExplicitVarSizeWithDummy: matrix indexed by [int(1..11)] of int(-4..5, 2, 6) +branching on + [var2_ExplicitVarSizeWithDummy, var2_ExplicitVarSizeWithMarker_Marker, var2_ExplicitVarSizeWithMarker_Values] +such that + or([q17 <= var2_ExplicitVarSizeWithMarker_Marker /\ + !or([q19 <= var2_ExplicitVarSizeWithMarker_Marker /\ + var2_ExplicitVarSizeWithMarker_Values[q19] = var2_ExplicitVarSizeWithMarker_Values[q17] + | q19 : int(1..11)]) + | q17 : int(1..11)]) + \/ + or([q20 <= var2_ExplicitVarSizeWithMarker_Marker /\ + !or([q22 <= var2_ExplicitVarSizeWithMarker_Marker /\ + var2_ExplicitVarSizeWithMarker_Values[q22] = var2_ExplicitVarSizeWithMarker_Values[q20] + | q22 : int(1..11)]) + | q20 : int(1..11)]), + and([q1 + 1 <= var2_ExplicitVarSizeWithMarker_Marker -> + var2_ExplicitVarSizeWithMarker_Values[q1] < var2_ExplicitVarSizeWithMarker_Values[q1 + 1] + | q1 : int(1..10)]), + and([q2 > var2_ExplicitVarSizeWithMarker_Marker -> var2_ExplicitVarSizeWithMarker_Values[q2] = -4 + | q2 : int(1..11)]), + and([var2_ExplicitVarSizeWithDummy[q4] < var2_ExplicitVarSizeWithDummy[q4 + 1] \/ + var2_ExplicitVarSizeWithDummy[q4] = 6 + | q4 : int(1..10)]), + and([var2_ExplicitVarSizeWithDummy[q5] = 6 -> var2_ExplicitVarSizeWithDummy[q5 + 1] = 6 | q5 : int(1..10)]), + and([var2_ExplicitVarSizeWithDummy[q9] != 6 -> + or([q11 <= var2_ExplicitVarSizeWithMarker_Marker /\ + var2_ExplicitVarSizeWithMarker_Values[q11] = var2_ExplicitVarSizeWithDummy[q9] + | q11 : int(1..11)]) + | q9 : int(1..11)]), + and([q13 <= var2_ExplicitVarSizeWithMarker_Marker -> + or([var2_ExplicitVarSizeWithDummy[q15] != 6 /\ + var2_ExplicitVarSizeWithDummy[q15] = var2_ExplicitVarSizeWithMarker_Values[q13] + | q15 : int(1..11)]) + | q13 : int(1..11)]) + diff --git a/tests/exhaustive/autogen/gen32/expected/model_3_3_3.eprime b/tests/exhaustive/autogen/gen32/expected/model_3_3_3.eprime new file mode 100644 index 0000000000..d30539480c --- /dev/null +++ b/tests/exhaustive/autogen/gen32/expected/model_3_3_3.eprime @@ -0,0 +1,24 @@ +language ESSENCE' 1.0 + +letting let1 be -4 +find var2_ExplicitVarSizeWithMarker_Marker: int(0..11) +find var2_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..11)] of int(-4..5, 2) +branching on [var2_ExplicitVarSizeWithMarker_Marker, var2_ExplicitVarSizeWithMarker_Values] +such that + or([q5 <= var2_ExplicitVarSizeWithMarker_Marker /\ + !or([q7 <= var2_ExplicitVarSizeWithMarker_Marker /\ + var2_ExplicitVarSizeWithMarker_Values[q7] = var2_ExplicitVarSizeWithMarker_Values[q5] + | q7 : int(1..11)]) + | q5 : int(1..11)]) + \/ + or([q8 <= var2_ExplicitVarSizeWithMarker_Marker /\ + !or([q10 <= var2_ExplicitVarSizeWithMarker_Marker /\ + var2_ExplicitVarSizeWithMarker_Values[q10] = var2_ExplicitVarSizeWithMarker_Values[q8] + | q10 : int(1..11)]) + | q8 : int(1..11)]), + and([q1 + 1 <= var2_ExplicitVarSizeWithMarker_Marker -> + var2_ExplicitVarSizeWithMarker_Values[q1] < var2_ExplicitVarSizeWithMarker_Values[q1 + 1] + | q1 : int(1..10)]), + and([q2 > var2_ExplicitVarSizeWithMarker_Marker -> var2_ExplicitVarSizeWithMarker_Values[q2] = -4 + | q2 : int(1..11)]) + diff --git a/tests/exhaustive/autogen/gen32/expected/model_3_3_4.eprime b/tests/exhaustive/autogen/gen32/expected/model_3_3_4.eprime new file mode 100644 index 0000000000..9cb3e7b96b --- /dev/null +++ b/tests/exhaustive/autogen/gen32/expected/model_3_3_4.eprime @@ -0,0 +1,44 @@ +language ESSENCE' 1.0 + +letting let1 be -4 +find var2_ExplicitVarSizeWithMarker_Marker: int(0..11) +find var2_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..11)] of int(-4..5, 2) +find var2_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..11)] of bool +find var2_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..11)] of int(-4..5, 2) +branching on + [var2_ExplicitVarSizeWithFlags_Flags, var2_ExplicitVarSizeWithFlags_Values, var2_ExplicitVarSizeWithMarker_Marker, + var2_ExplicitVarSizeWithMarker_Values] +such that + or([q18 <= var2_ExplicitVarSizeWithMarker_Marker /\ + !or([q20 <= var2_ExplicitVarSizeWithMarker_Marker /\ + var2_ExplicitVarSizeWithMarker_Values[q20] = var2_ExplicitVarSizeWithMarker_Values[q18] + | q20 : int(1..11)]) + | q18 : int(1..11)]) + \/ + or([q21 <= var2_ExplicitVarSizeWithMarker_Marker /\ + !or([q23 <= var2_ExplicitVarSizeWithMarker_Marker /\ + var2_ExplicitVarSizeWithMarker_Values[q23] = var2_ExplicitVarSizeWithMarker_Values[q21] + | q23 : int(1..11)]) + | q21 : int(1..11)]), + and([q1 + 1 <= var2_ExplicitVarSizeWithMarker_Marker -> + var2_ExplicitVarSizeWithMarker_Values[q1] < var2_ExplicitVarSizeWithMarker_Values[q1 + 1] + | q1 : int(1..10)]), + and([q2 > var2_ExplicitVarSizeWithMarker_Marker -> var2_ExplicitVarSizeWithMarker_Values[q2] = -4 + | q2 : int(1..11)]), + and([var2_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> + var2_ExplicitVarSizeWithFlags_Values[q4] < var2_ExplicitVarSizeWithFlags_Values[q4 + 1] + | q4 : int(1..10)]), + and([var2_ExplicitVarSizeWithFlags_Flags[q5] = false -> var2_ExplicitVarSizeWithFlags_Values[q5] = -4 + | q5 : int(1..11)]), + and([var2_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> var2_ExplicitVarSizeWithFlags_Flags[q6] | q6 : int(1..10)]), + and([var2_ExplicitVarSizeWithFlags_Flags[q10] -> + or([q12 <= var2_ExplicitVarSizeWithMarker_Marker /\ + var2_ExplicitVarSizeWithMarker_Values[q12] = var2_ExplicitVarSizeWithFlags_Values[q10] + | q12 : int(1..11)]) + | q10 : int(1..11)]), + and([q14 <= var2_ExplicitVarSizeWithMarker_Marker -> + or([var2_ExplicitVarSizeWithFlags_Flags[q16] /\ + var2_ExplicitVarSizeWithFlags_Values[q16] = var2_ExplicitVarSizeWithMarker_Values[q14] + | q16 : int(1..11)]) + | q14 : int(1..11)]) + diff --git a/tests/exhaustive/autogen/gen32/expected/model_3_4_1.eprime b/tests/exhaustive/autogen/gen32/expected/model_3_4_1.eprime new file mode 100644 index 0000000000..4ec1f855f0 --- /dev/null +++ b/tests/exhaustive/autogen/gen32/expected/model_3_4_1.eprime @@ -0,0 +1,57 @@ +language ESSENCE' 1.0 + +letting let1 be -4 +find var2_ExplicitVarSizeWithMarker_Marker: int(0..11) +find var2_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..11)] of int(-4..5, 2) +find var2_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..11)] of bool +find var2_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..11)] of int(-4..5, 2) +find var2_Occurrence: matrix indexed by [int(-4..5, 2)] of bool +branching on + [var2_Occurrence, var2_ExplicitVarSizeWithMarker_Marker, var2_ExplicitVarSizeWithMarker_Values, + var2_ExplicitVarSizeWithFlags_Flags, var2_ExplicitVarSizeWithFlags_Values] +such that + or([q19 <= var2_ExplicitVarSizeWithMarker_Marker /\ + !or([var2_ExplicitVarSizeWithFlags_Flags[q21] /\ + var2_ExplicitVarSizeWithFlags_Values[q21] = var2_ExplicitVarSizeWithMarker_Values[q19] + | q21 : int(1..11)]) + | q19 : int(1..11)]) + \/ + or([var2_ExplicitVarSizeWithFlags_Flags[q22] /\ + !or([q24 <= var2_ExplicitVarSizeWithMarker_Marker /\ + var2_ExplicitVarSizeWithMarker_Values[q24] = var2_ExplicitVarSizeWithFlags_Values[q22] + | q24 : int(1..11)]) + | q22 : int(1..11)]), + and([q1 + 1 <= var2_ExplicitVarSizeWithMarker_Marker -> + var2_ExplicitVarSizeWithMarker_Values[q1] < var2_ExplicitVarSizeWithMarker_Values[q1 + 1] + | q1 : int(1..10)]), + and([q2 > var2_ExplicitVarSizeWithMarker_Marker -> var2_ExplicitVarSizeWithMarker_Values[q2] = -4 + | q2 : int(1..11)]), + and([var2_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> + var2_ExplicitVarSizeWithFlags_Values[q4] < var2_ExplicitVarSizeWithFlags_Values[q4 + 1] + | q4 : int(1..10)]), + and([var2_ExplicitVarSizeWithFlags_Flags[q5] = false -> var2_ExplicitVarSizeWithFlags_Values[q5] = -4 + | q5 : int(1..11)]), + and([var2_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> var2_ExplicitVarSizeWithFlags_Flags[q6] | q6 : int(1..10)]), + and([var2_ExplicitVarSizeWithFlags_Flags[q10] -> + or([q12 <= var2_ExplicitVarSizeWithMarker_Marker /\ + var2_ExplicitVarSizeWithMarker_Values[q12] = var2_ExplicitVarSizeWithFlags_Values[q10] + | q12 : int(1..11)]) + | q10 : int(1..11)]), + and([q14 <= var2_ExplicitVarSizeWithMarker_Marker -> + or([var2_ExplicitVarSizeWithFlags_Flags[q16] /\ + var2_ExplicitVarSizeWithFlags_Values[q16] = var2_ExplicitVarSizeWithMarker_Values[q14] + | q16 : int(1..11)]) + | q14 : int(1..11)]), + and([var2_Occurrence[q25] -> + or([q27 <= var2_ExplicitVarSizeWithMarker_Marker /\ var2_ExplicitVarSizeWithMarker_Values[q27] = q25 + | q27 : int(1..11)]) + | q25 : int(-4..5, 2)]), + and([q29 <= var2_ExplicitVarSizeWithMarker_Marker -> var2_Occurrence[var2_ExplicitVarSizeWithMarker_Values[q29]] + | q29 : int(1..11)]), + and([var2_Occurrence[q30] -> + or([var2_ExplicitVarSizeWithFlags_Flags[q32] /\ var2_ExplicitVarSizeWithFlags_Values[q32] = q30 + | q32 : int(1..11)]) + | q30 : int(-4..5, 2)]), + and([var2_ExplicitVarSizeWithFlags_Flags[q34] -> var2_Occurrence[var2_ExplicitVarSizeWithFlags_Values[q34]] + | q34 : int(1..11)]) + diff --git a/tests/exhaustive/autogen/gen32/expected/model_3_4_2.eprime b/tests/exhaustive/autogen/gen32/expected/model_3_4_2.eprime new file mode 100644 index 0000000000..df59cf3084 --- /dev/null +++ b/tests/exhaustive/autogen/gen32/expected/model_3_4_2.eprime @@ -0,0 +1,69 @@ +language ESSENCE' 1.0 + +letting let1 be -4 +find var2_ExplicitVarSizeWithMarker_Marker: int(0..11) +find var2_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..11)] of int(-4..5, 2) +find var2_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..11)] of bool +find var2_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..11)] of int(-4..5, 2) +find var2_ExplicitVarSizeWithDummy: matrix indexed by [int(1..11)] of int(-4..5, 2, 6) +branching on + [var2_ExplicitVarSizeWithDummy, var2_ExplicitVarSizeWithMarker_Marker, var2_ExplicitVarSizeWithMarker_Values, + var2_ExplicitVarSizeWithFlags_Flags, var2_ExplicitVarSizeWithFlags_Values] +such that + or([q38 <= var2_ExplicitVarSizeWithMarker_Marker /\ + !or([var2_ExplicitVarSizeWithFlags_Flags[q40] /\ + var2_ExplicitVarSizeWithFlags_Values[q40] = var2_ExplicitVarSizeWithMarker_Values[q38] + | q40 : int(1..11)]) + | q38 : int(1..11)]) + \/ + or([var2_ExplicitVarSizeWithFlags_Flags[q41] /\ + !or([q43 <= var2_ExplicitVarSizeWithMarker_Marker /\ + var2_ExplicitVarSizeWithMarker_Values[q43] = var2_ExplicitVarSizeWithFlags_Values[q41] + | q43 : int(1..11)]) + | q41 : int(1..11)]), + and([q1 + 1 <= var2_ExplicitVarSizeWithMarker_Marker -> + var2_ExplicitVarSizeWithMarker_Values[q1] < var2_ExplicitVarSizeWithMarker_Values[q1 + 1] + | q1 : int(1..10)]), + and([q2 > var2_ExplicitVarSizeWithMarker_Marker -> var2_ExplicitVarSizeWithMarker_Values[q2] = -4 + | q2 : int(1..11)]), + and([var2_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> + var2_ExplicitVarSizeWithFlags_Values[q4] < var2_ExplicitVarSizeWithFlags_Values[q4 + 1] + | q4 : int(1..10)]), + and([var2_ExplicitVarSizeWithFlags_Flags[q5] = false -> var2_ExplicitVarSizeWithFlags_Values[q5] = -4 + | q5 : int(1..11)]), + and([var2_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> var2_ExplicitVarSizeWithFlags_Flags[q6] | q6 : int(1..10)]), + and([var2_ExplicitVarSizeWithFlags_Flags[q10] -> + or([q12 <= var2_ExplicitVarSizeWithMarker_Marker /\ + var2_ExplicitVarSizeWithMarker_Values[q12] = var2_ExplicitVarSizeWithFlags_Values[q10] + | q12 : int(1..11)]) + | q10 : int(1..11)]), + and([q14 <= var2_ExplicitVarSizeWithMarker_Marker -> + or([var2_ExplicitVarSizeWithFlags_Flags[q16] /\ + var2_ExplicitVarSizeWithFlags_Values[q16] = var2_ExplicitVarSizeWithMarker_Values[q14] + | q16 : int(1..11)]) + | q14 : int(1..11)]), + and([var2_ExplicitVarSizeWithDummy[q17] < var2_ExplicitVarSizeWithDummy[q17 + 1] \/ + var2_ExplicitVarSizeWithDummy[q17] = 6 + | q17 : int(1..10)]), + and([var2_ExplicitVarSizeWithDummy[q18] = 6 -> var2_ExplicitVarSizeWithDummy[q18 + 1] = 6 | q18 : int(1..10)]), + and([var2_ExplicitVarSizeWithDummy[q22] != 6 -> + or([q24 <= var2_ExplicitVarSizeWithMarker_Marker /\ + var2_ExplicitVarSizeWithMarker_Values[q24] = var2_ExplicitVarSizeWithDummy[q22] + | q24 : int(1..11)]) + | q22 : int(1..11)]), + and([q26 <= var2_ExplicitVarSizeWithMarker_Marker -> + or([var2_ExplicitVarSizeWithDummy[q28] != 6 /\ + var2_ExplicitVarSizeWithDummy[q28] = var2_ExplicitVarSizeWithMarker_Values[q26] + | q28 : int(1..11)]) + | q26 : int(1..11)]), + and([var2_ExplicitVarSizeWithDummy[q30] != 6 -> + or([var2_ExplicitVarSizeWithFlags_Flags[q32] /\ + var2_ExplicitVarSizeWithFlags_Values[q32] = var2_ExplicitVarSizeWithDummy[q30] + | q32 : int(1..11)]) + | q30 : int(1..11)]), + and([var2_ExplicitVarSizeWithFlags_Flags[q34] -> + or([var2_ExplicitVarSizeWithDummy[q36] != 6 /\ + var2_ExplicitVarSizeWithDummy[q36] = var2_ExplicitVarSizeWithFlags_Values[q34] + | q36 : int(1..11)]) + | q34 : int(1..11)]) + diff --git a/tests/exhaustive/autogen/gen32/expected/model_3_4_3.eprime b/tests/exhaustive/autogen/gen32/expected/model_3_4_3.eprime new file mode 100644 index 0000000000..4785a0c0ec --- /dev/null +++ b/tests/exhaustive/autogen/gen32/expected/model_3_4_3.eprime @@ -0,0 +1,44 @@ +language ESSENCE' 1.0 + +letting let1 be -4 +find var2_ExplicitVarSizeWithMarker_Marker: int(0..11) +find var2_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..11)] of int(-4..5, 2) +find var2_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..11)] of bool +find var2_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..11)] of int(-4..5, 2) +branching on + [var2_ExplicitVarSizeWithFlags_Flags, var2_ExplicitVarSizeWithFlags_Values, var2_ExplicitVarSizeWithMarker_Marker, + var2_ExplicitVarSizeWithMarker_Values] +such that + or([q18 <= var2_ExplicitVarSizeWithMarker_Marker /\ + !or([var2_ExplicitVarSizeWithFlags_Flags[q20] /\ + var2_ExplicitVarSizeWithFlags_Values[q20] = var2_ExplicitVarSizeWithMarker_Values[q18] + | q20 : int(1..11)]) + | q18 : int(1..11)]) + \/ + or([var2_ExplicitVarSizeWithFlags_Flags[q21] /\ + !or([q23 <= var2_ExplicitVarSizeWithMarker_Marker /\ + var2_ExplicitVarSizeWithMarker_Values[q23] = var2_ExplicitVarSizeWithFlags_Values[q21] + | q23 : int(1..11)]) + | q21 : int(1..11)]), + and([q1 + 1 <= var2_ExplicitVarSizeWithMarker_Marker -> + var2_ExplicitVarSizeWithMarker_Values[q1] < var2_ExplicitVarSizeWithMarker_Values[q1 + 1] + | q1 : int(1..10)]), + and([q2 > var2_ExplicitVarSizeWithMarker_Marker -> var2_ExplicitVarSizeWithMarker_Values[q2] = -4 + | q2 : int(1..11)]), + and([var2_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> + var2_ExplicitVarSizeWithFlags_Values[q4] < var2_ExplicitVarSizeWithFlags_Values[q4 + 1] + | q4 : int(1..10)]), + and([var2_ExplicitVarSizeWithFlags_Flags[q5] = false -> var2_ExplicitVarSizeWithFlags_Values[q5] = -4 + | q5 : int(1..11)]), + and([var2_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> var2_ExplicitVarSizeWithFlags_Flags[q6] | q6 : int(1..10)]), + and([var2_ExplicitVarSizeWithFlags_Flags[q10] -> + or([q12 <= var2_ExplicitVarSizeWithMarker_Marker /\ + var2_ExplicitVarSizeWithMarker_Values[q12] = var2_ExplicitVarSizeWithFlags_Values[q10] + | q12 : int(1..11)]) + | q10 : int(1..11)]), + and([q14 <= var2_ExplicitVarSizeWithMarker_Marker -> + or([var2_ExplicitVarSizeWithFlags_Flags[q16] /\ + var2_ExplicitVarSizeWithFlags_Values[q16] = var2_ExplicitVarSizeWithMarker_Values[q14] + | q16 : int(1..11)]) + | q14 : int(1..11)]) + diff --git a/tests/exhaustive/autogen/gen32/expected/model_4_1_1.eprime b/tests/exhaustive/autogen/gen32/expected/model_4_1_1.eprime new file mode 100644 index 0000000000..5c6854637e --- /dev/null +++ b/tests/exhaustive/autogen/gen32/expected/model_4_1_1.eprime @@ -0,0 +1,28 @@ +language ESSENCE' 1.0 + +letting let1 be -4 +find var2_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..11)] of bool +find var2_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..11)] of int(-4..5, 2) +find var2_Occurrence: matrix indexed by [int(-4..5, 2)] of bool +branching on [var2_Occurrence, var2_ExplicitVarSizeWithFlags_Flags, var2_ExplicitVarSizeWithFlags_Values] +such that + or([var2_ExplicitVarSizeWithFlags_Flags[q8] /\ !var2_Occurrence[var2_ExplicitVarSizeWithFlags_Values[q8]] + | q8 : int(1..11)]) + \/ + or([var2_Occurrence[q7] /\ + !or([var2_ExplicitVarSizeWithFlags_Flags[q10] /\ var2_ExplicitVarSizeWithFlags_Values[q10] = q7 + | q10 : int(1..11)]) + | q7 : int(-4..5, 2)]), + and([var2_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> + var2_ExplicitVarSizeWithFlags_Values[q1] < var2_ExplicitVarSizeWithFlags_Values[q1 + 1] + | q1 : int(1..10)]), + and([var2_ExplicitVarSizeWithFlags_Flags[q2] = false -> var2_ExplicitVarSizeWithFlags_Values[q2] = -4 + | q2 : int(1..11)]), + and([var2_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> var2_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..10)]), + and([var2_Occurrence[q11] -> + or([var2_ExplicitVarSizeWithFlags_Flags[q13] /\ var2_ExplicitVarSizeWithFlags_Values[q13] = q11 + | q13 : int(1..11)]) + | q11 : int(-4..5, 2)]), + and([var2_ExplicitVarSizeWithFlags_Flags[q15] -> var2_Occurrence[var2_ExplicitVarSizeWithFlags_Values[q15]] + | q15 : int(1..11)]) + diff --git a/tests/exhaustive/autogen/gen32/expected/model_4_1_2.eprime b/tests/exhaustive/autogen/gen32/expected/model_4_1_2.eprime new file mode 100644 index 0000000000..0f8965d6c5 --- /dev/null +++ b/tests/exhaustive/autogen/gen32/expected/model_4_1_2.eprime @@ -0,0 +1,50 @@ +language ESSENCE' 1.0 + +letting let1 be -4 +find var2_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..11)] of bool +find var2_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..11)] of int(-4..5, 2) +find var2_Occurrence: matrix indexed by [int(-4..5, 2)] of bool +find var2_ExplicitVarSizeWithDummy: matrix indexed by [int(1..11)] of int(-4..5, 2, 6) +branching on + [var2_ExplicitVarSizeWithDummy, var2_ExplicitVarSizeWithFlags_Flags, var2_ExplicitVarSizeWithFlags_Values, + var2_Occurrence] +such that + or([var2_ExplicitVarSizeWithFlags_Flags[q25] /\ !var2_Occurrence[var2_ExplicitVarSizeWithFlags_Values[q25]] + | q25 : int(1..11)]) + \/ + or([var2_Occurrence[q24] /\ + !or([var2_ExplicitVarSizeWithFlags_Flags[q27] /\ var2_ExplicitVarSizeWithFlags_Values[q27] = q24 + | q27 : int(1..11)]) + | q24 : int(-4..5, 2)]), + and([var2_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> + var2_ExplicitVarSizeWithFlags_Values[q1] < var2_ExplicitVarSizeWithFlags_Values[q1 + 1] + | q1 : int(1..10)]), + and([var2_ExplicitVarSizeWithFlags_Flags[q2] = false -> var2_ExplicitVarSizeWithFlags_Values[q2] = -4 + | q2 : int(1..11)]), + and([var2_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> var2_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..10)]), + and([var2_Occurrence[q28] -> + or([var2_ExplicitVarSizeWithFlags_Flags[q30] /\ var2_ExplicitVarSizeWithFlags_Values[q30] = q28 + | q30 : int(1..11)]) + | q28 : int(-4..5, 2)]), + and([var2_ExplicitVarSizeWithFlags_Flags[q32] -> var2_Occurrence[var2_ExplicitVarSizeWithFlags_Values[q32]] + | q32 : int(1..11)]), + and([var2_ExplicitVarSizeWithDummy[q7] < var2_ExplicitVarSizeWithDummy[q7 + 1] \/ + var2_ExplicitVarSizeWithDummy[q7] = 6 + | q7 : int(1..10)]), + and([var2_ExplicitVarSizeWithDummy[q8] = 6 -> var2_ExplicitVarSizeWithDummy[q8 + 1] = 6 | q8 : int(1..10)]), + and([var2_ExplicitVarSizeWithDummy[q12] != 6 -> + or([var2_ExplicitVarSizeWithFlags_Flags[q14] /\ + var2_ExplicitVarSizeWithFlags_Values[q14] = var2_ExplicitVarSizeWithDummy[q12] + | q14 : int(1..11)]) + | q12 : int(1..11)]), + and([var2_ExplicitVarSizeWithFlags_Flags[q16] -> + or([var2_ExplicitVarSizeWithDummy[q18] != 6 /\ + var2_ExplicitVarSizeWithDummy[q18] = var2_ExplicitVarSizeWithFlags_Values[q16] + | q18 : int(1..11)]) + | q16 : int(1..11)]), + and([var2_ExplicitVarSizeWithDummy[q20] != 6 -> var2_Occurrence[var2_ExplicitVarSizeWithDummy[q20]] + | q20 : int(1..11)]), + and([var2_Occurrence[q21] -> + or([var2_ExplicitVarSizeWithDummy[q23] != 6 /\ var2_ExplicitVarSizeWithDummy[q23] = q21 | q23 : int(1..11)]) + | q21 : int(-4..5, 2)]) + diff --git a/tests/exhaustive/autogen/gen32/expected/model_4_1_3.eprime b/tests/exhaustive/autogen/gen32/expected/model_4_1_3.eprime new file mode 100644 index 0000000000..6fff70a69f --- /dev/null +++ b/tests/exhaustive/autogen/gen32/expected/model_4_1_3.eprime @@ -0,0 +1,53 @@ +language ESSENCE' 1.0 + +letting let1 be -4 +find var2_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..11)] of bool +find var2_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..11)] of int(-4..5, 2) +find var2_Occurrence: matrix indexed by [int(-4..5, 2)] of bool +find var2_ExplicitVarSizeWithMarker_Marker: int(0..11) +find var2_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..11)] of int(-4..5, 2) +branching on + [var2_ExplicitVarSizeWithMarker_Marker, var2_ExplicitVarSizeWithMarker_Values, var2_ExplicitVarSizeWithFlags_Flags, + var2_ExplicitVarSizeWithFlags_Values, var2_Occurrence] +such that + or([var2_ExplicitVarSizeWithFlags_Flags[q24] /\ !var2_Occurrence[var2_ExplicitVarSizeWithFlags_Values[q24]] + | q24 : int(1..11)]) + \/ + or([var2_Occurrence[q23] /\ + !or([var2_ExplicitVarSizeWithFlags_Flags[q26] /\ var2_ExplicitVarSizeWithFlags_Values[q26] = q23 + | q26 : int(1..11)]) + | q23 : int(-4..5, 2)]), + and([var2_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> + var2_ExplicitVarSizeWithFlags_Values[q1] < var2_ExplicitVarSizeWithFlags_Values[q1 + 1] + | q1 : int(1..10)]), + and([var2_ExplicitVarSizeWithFlags_Flags[q2] = false -> var2_ExplicitVarSizeWithFlags_Values[q2] = -4 + | q2 : int(1..11)]), + and([var2_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> var2_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..10)]), + and([var2_Occurrence[q27] -> + or([var2_ExplicitVarSizeWithFlags_Flags[q29] /\ var2_ExplicitVarSizeWithFlags_Values[q29] = q27 + | q29 : int(1..11)]) + | q27 : int(-4..5, 2)]), + and([var2_ExplicitVarSizeWithFlags_Flags[q31] -> var2_Occurrence[var2_ExplicitVarSizeWithFlags_Values[q31]] + | q31 : int(1..11)]), + and([q7 + 1 <= var2_ExplicitVarSizeWithMarker_Marker -> + var2_ExplicitVarSizeWithMarker_Values[q7] < var2_ExplicitVarSizeWithMarker_Values[q7 + 1] + | q7 : int(1..10)]), + and([q8 > var2_ExplicitVarSizeWithMarker_Marker -> var2_ExplicitVarSizeWithMarker_Values[q8] = -4 + | q8 : int(1..11)]), + and([q11 <= var2_ExplicitVarSizeWithMarker_Marker -> + or([var2_ExplicitVarSizeWithFlags_Flags[q13] /\ + var2_ExplicitVarSizeWithFlags_Values[q13] = var2_ExplicitVarSizeWithMarker_Values[q11] + | q13 : int(1..11)]) + | q11 : int(1..11)]), + and([var2_ExplicitVarSizeWithFlags_Flags[q15] -> + or([q17 <= var2_ExplicitVarSizeWithMarker_Marker /\ + var2_ExplicitVarSizeWithMarker_Values[q17] = var2_ExplicitVarSizeWithFlags_Values[q15] + | q17 : int(1..11)]) + | q15 : int(1..11)]), + and([q19 <= var2_ExplicitVarSizeWithMarker_Marker -> var2_Occurrence[var2_ExplicitVarSizeWithMarker_Values[q19]] + | q19 : int(1..11)]), + and([var2_Occurrence[q20] -> + or([q22 <= var2_ExplicitVarSizeWithMarker_Marker /\ var2_ExplicitVarSizeWithMarker_Values[q22] = q20 + | q22 : int(1..11)]) + | q20 : int(-4..5, 2)]) + diff --git a/tests/exhaustive/autogen/gen32/expected/model_4_2_1.eprime b/tests/exhaustive/autogen/gen32/expected/model_4_2_1.eprime new file mode 100644 index 0000000000..b7b3b2ad4a --- /dev/null +++ b/tests/exhaustive/autogen/gen32/expected/model_4_2_1.eprime @@ -0,0 +1,54 @@ +language ESSENCE' 1.0 + +letting let1 be -4 +find var2_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..11)] of bool +find var2_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..11)] of int(-4..5, 2) +find var2_ExplicitVarSizeWithDummy: matrix indexed by [int(1..11)] of int(-4..5, 2, 6) +find var2_Occurrence: matrix indexed by [int(-4..5, 2)] of bool +branching on + [var2_Occurrence, var2_ExplicitVarSizeWithFlags_Flags, var2_ExplicitVarSizeWithFlags_Values, + var2_ExplicitVarSizeWithDummy] +such that + or([var2_ExplicitVarSizeWithFlags_Flags[q20] /\ + !or([var2_ExplicitVarSizeWithDummy[q22] != 6 /\ + var2_ExplicitVarSizeWithDummy[q22] = var2_ExplicitVarSizeWithFlags_Values[q20] + | q22 : int(1..11)]) + | q20 : int(1..11)]) + \/ + or([var2_ExplicitVarSizeWithDummy[q23] != 6 /\ + !or([var2_ExplicitVarSizeWithFlags_Flags[q25] /\ + var2_ExplicitVarSizeWithFlags_Values[q25] = var2_ExplicitVarSizeWithDummy[q23] + | q25 : int(1..11)]) + | q23 : int(1..11)]), + and([var2_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> + var2_ExplicitVarSizeWithFlags_Values[q1] < var2_ExplicitVarSizeWithFlags_Values[q1 + 1] + | q1 : int(1..10)]), + and([var2_ExplicitVarSizeWithFlags_Flags[q2] = false -> var2_ExplicitVarSizeWithFlags_Values[q2] = -4 + | q2 : int(1..11)]), + and([var2_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> var2_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..10)]), + and([var2_ExplicitVarSizeWithDummy[q6] < var2_ExplicitVarSizeWithDummy[q6 + 1] \/ + var2_ExplicitVarSizeWithDummy[q6] = 6 + | q6 : int(1..10)]), + and([var2_ExplicitVarSizeWithDummy[q7] = 6 -> var2_ExplicitVarSizeWithDummy[q7 + 1] = 6 | q7 : int(1..10)]), + and([var2_ExplicitVarSizeWithDummy[q11] != 6 -> + or([var2_ExplicitVarSizeWithFlags_Flags[q13] /\ + var2_ExplicitVarSizeWithFlags_Values[q13] = var2_ExplicitVarSizeWithDummy[q11] + | q13 : int(1..11)]) + | q11 : int(1..11)]), + and([var2_ExplicitVarSizeWithFlags_Flags[q15] -> + or([var2_ExplicitVarSizeWithDummy[q17] != 6 /\ + var2_ExplicitVarSizeWithDummy[q17] = var2_ExplicitVarSizeWithFlags_Values[q15] + | q17 : int(1..11)]) + | q15 : int(1..11)]), + and([var2_Occurrence[q26] -> + or([var2_ExplicitVarSizeWithFlags_Flags[q28] /\ var2_ExplicitVarSizeWithFlags_Values[q28] = q26 + | q28 : int(1..11)]) + | q26 : int(-4..5, 2)]), + and([var2_ExplicitVarSizeWithFlags_Flags[q30] -> var2_Occurrence[var2_ExplicitVarSizeWithFlags_Values[q30]] + | q30 : int(1..11)]), + and([var2_Occurrence[q31] -> + or([var2_ExplicitVarSizeWithDummy[q33] != 6 /\ var2_ExplicitVarSizeWithDummy[q33] = q31 | q33 : int(1..11)]) + | q31 : int(-4..5, 2)]), + and([var2_ExplicitVarSizeWithDummy[q35] != 6 -> var2_Occurrence[var2_ExplicitVarSizeWithDummy[q35]] + | q35 : int(1..11)]) + diff --git a/tests/exhaustive/autogen/gen32/expected/model_4_2_2.eprime b/tests/exhaustive/autogen/gen32/expected/model_4_2_2.eprime new file mode 100644 index 0000000000..9a094995de --- /dev/null +++ b/tests/exhaustive/autogen/gen32/expected/model_4_2_2.eprime @@ -0,0 +1,40 @@ +language ESSENCE' 1.0 + +letting let1 be -4 +find var2_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..11)] of bool +find var2_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..11)] of int(-4..5, 2) +find var2_ExplicitVarSizeWithDummy: matrix indexed by [int(1..11)] of int(-4..5, 2, 6) +branching on [var2_ExplicitVarSizeWithDummy, var2_ExplicitVarSizeWithFlags_Flags, var2_ExplicitVarSizeWithFlags_Values] +such that + or([var2_ExplicitVarSizeWithFlags_Flags[q19] /\ + !or([var2_ExplicitVarSizeWithDummy[q21] != 6 /\ + var2_ExplicitVarSizeWithDummy[q21] = var2_ExplicitVarSizeWithFlags_Values[q19] + | q21 : int(1..11)]) + | q19 : int(1..11)]) + \/ + or([var2_ExplicitVarSizeWithDummy[q22] != 6 /\ + !or([var2_ExplicitVarSizeWithFlags_Flags[q24] /\ + var2_ExplicitVarSizeWithFlags_Values[q24] = var2_ExplicitVarSizeWithDummy[q22] + | q24 : int(1..11)]) + | q22 : int(1..11)]), + and([var2_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> + var2_ExplicitVarSizeWithFlags_Values[q1] < var2_ExplicitVarSizeWithFlags_Values[q1 + 1] + | q1 : int(1..10)]), + and([var2_ExplicitVarSizeWithFlags_Flags[q2] = false -> var2_ExplicitVarSizeWithFlags_Values[q2] = -4 + | q2 : int(1..11)]), + and([var2_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> var2_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..10)]), + and([var2_ExplicitVarSizeWithDummy[q6] < var2_ExplicitVarSizeWithDummy[q6 + 1] \/ + var2_ExplicitVarSizeWithDummy[q6] = 6 + | q6 : int(1..10)]), + and([var2_ExplicitVarSizeWithDummy[q7] = 6 -> var2_ExplicitVarSizeWithDummy[q7 + 1] = 6 | q7 : int(1..10)]), + and([var2_ExplicitVarSizeWithDummy[q11] != 6 -> + or([var2_ExplicitVarSizeWithFlags_Flags[q13] /\ + var2_ExplicitVarSizeWithFlags_Values[q13] = var2_ExplicitVarSizeWithDummy[q11] + | q13 : int(1..11)]) + | q11 : int(1..11)]), + and([var2_ExplicitVarSizeWithFlags_Flags[q15] -> + or([var2_ExplicitVarSizeWithDummy[q17] != 6 /\ + var2_ExplicitVarSizeWithDummy[q17] = var2_ExplicitVarSizeWithFlags_Values[q15] + | q17 : int(1..11)]) + | q15 : int(1..11)]) + diff --git a/tests/exhaustive/autogen/gen32/expected/model_4_2_3.eprime b/tests/exhaustive/autogen/gen32/expected/model_4_2_3.eprime new file mode 100644 index 0000000000..ff001560cb --- /dev/null +++ b/tests/exhaustive/autogen/gen32/expected/model_4_2_3.eprime @@ -0,0 +1,69 @@ +language ESSENCE' 1.0 + +letting let1 be -4 +find var2_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..11)] of bool +find var2_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..11)] of int(-4..5, 2) +find var2_ExplicitVarSizeWithDummy: matrix indexed by [int(1..11)] of int(-4..5, 2, 6) +find var2_ExplicitVarSizeWithMarker_Marker: int(0..11) +find var2_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..11)] of int(-4..5, 2) +branching on + [var2_ExplicitVarSizeWithMarker_Marker, var2_ExplicitVarSizeWithMarker_Values, var2_ExplicitVarSizeWithFlags_Flags, + var2_ExplicitVarSizeWithFlags_Values, var2_ExplicitVarSizeWithDummy] +such that + or([var2_ExplicitVarSizeWithFlags_Flags[q38] /\ + !or([var2_ExplicitVarSizeWithDummy[q40] != 6 /\ + var2_ExplicitVarSizeWithDummy[q40] = var2_ExplicitVarSizeWithFlags_Values[q38] + | q40 : int(1..11)]) + | q38 : int(1..11)]) + \/ + or([var2_ExplicitVarSizeWithDummy[q41] != 6 /\ + !or([var2_ExplicitVarSizeWithFlags_Flags[q43] /\ + var2_ExplicitVarSizeWithFlags_Values[q43] = var2_ExplicitVarSizeWithDummy[q41] + | q43 : int(1..11)]) + | q41 : int(1..11)]), + and([var2_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> + var2_ExplicitVarSizeWithFlags_Values[q1] < var2_ExplicitVarSizeWithFlags_Values[q1 + 1] + | q1 : int(1..10)]), + and([var2_ExplicitVarSizeWithFlags_Flags[q2] = false -> var2_ExplicitVarSizeWithFlags_Values[q2] = -4 + | q2 : int(1..11)]), + and([var2_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> var2_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..10)]), + and([var2_ExplicitVarSizeWithDummy[q6] < var2_ExplicitVarSizeWithDummy[q6 + 1] \/ + var2_ExplicitVarSizeWithDummy[q6] = 6 + | q6 : int(1..10)]), + and([var2_ExplicitVarSizeWithDummy[q7] = 6 -> var2_ExplicitVarSizeWithDummy[q7 + 1] = 6 | q7 : int(1..10)]), + and([var2_ExplicitVarSizeWithDummy[q11] != 6 -> + or([var2_ExplicitVarSizeWithFlags_Flags[q13] /\ + var2_ExplicitVarSizeWithFlags_Values[q13] = var2_ExplicitVarSizeWithDummy[q11] + | q13 : int(1..11)]) + | q11 : int(1..11)]), + and([var2_ExplicitVarSizeWithFlags_Flags[q15] -> + or([var2_ExplicitVarSizeWithDummy[q17] != 6 /\ + var2_ExplicitVarSizeWithDummy[q17] = var2_ExplicitVarSizeWithFlags_Values[q15] + | q17 : int(1..11)]) + | q15 : int(1..11)]), + and([q18 + 1 <= var2_ExplicitVarSizeWithMarker_Marker -> + var2_ExplicitVarSizeWithMarker_Values[q18] < var2_ExplicitVarSizeWithMarker_Values[q18 + 1] + | q18 : int(1..10)]), + and([q19 > var2_ExplicitVarSizeWithMarker_Marker -> var2_ExplicitVarSizeWithMarker_Values[q19] = -4 + | q19 : int(1..11)]), + and([q22 <= var2_ExplicitVarSizeWithMarker_Marker -> + or([var2_ExplicitVarSizeWithFlags_Flags[q24] /\ + var2_ExplicitVarSizeWithFlags_Values[q24] = var2_ExplicitVarSizeWithMarker_Values[q22] + | q24 : int(1..11)]) + | q22 : int(1..11)]), + and([var2_ExplicitVarSizeWithFlags_Flags[q26] -> + or([q28 <= var2_ExplicitVarSizeWithMarker_Marker /\ + var2_ExplicitVarSizeWithMarker_Values[q28] = var2_ExplicitVarSizeWithFlags_Values[q26] + | q28 : int(1..11)]) + | q26 : int(1..11)]), + and([q30 <= var2_ExplicitVarSizeWithMarker_Marker -> + or([var2_ExplicitVarSizeWithDummy[q32] != 6 /\ + var2_ExplicitVarSizeWithDummy[q32] = var2_ExplicitVarSizeWithMarker_Values[q30] + | q32 : int(1..11)]) + | q30 : int(1..11)]), + and([var2_ExplicitVarSizeWithDummy[q34] != 6 -> + or([q36 <= var2_ExplicitVarSizeWithMarker_Marker /\ + var2_ExplicitVarSizeWithMarker_Values[q36] = var2_ExplicitVarSizeWithDummy[q34] + | q36 : int(1..11)]) + | q34 : int(1..11)]) + diff --git a/tests/exhaustive/autogen/gen32/expected/model_4_3_1.eprime b/tests/exhaustive/autogen/gen32/expected/model_4_3_1.eprime new file mode 100644 index 0000000000..eb41be6810 --- /dev/null +++ b/tests/exhaustive/autogen/gen32/expected/model_4_3_1.eprime @@ -0,0 +1,57 @@ +language ESSENCE' 1.0 + +letting let1 be -4 +find var2_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..11)] of bool +find var2_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..11)] of int(-4..5, 2) +find var2_ExplicitVarSizeWithMarker_Marker: int(0..11) +find var2_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..11)] of int(-4..5, 2) +find var2_Occurrence: matrix indexed by [int(-4..5, 2)] of bool +branching on + [var2_Occurrence, var2_ExplicitVarSizeWithFlags_Flags, var2_ExplicitVarSizeWithFlags_Values, + var2_ExplicitVarSizeWithMarker_Marker, var2_ExplicitVarSizeWithMarker_Values] +such that + or([var2_ExplicitVarSizeWithFlags_Flags[q19] /\ + !or([q21 <= var2_ExplicitVarSizeWithMarker_Marker /\ + var2_ExplicitVarSizeWithMarker_Values[q21] = var2_ExplicitVarSizeWithFlags_Values[q19] + | q21 : int(1..11)]) + | q19 : int(1..11)]) + \/ + or([q22 <= var2_ExplicitVarSizeWithMarker_Marker /\ + !or([var2_ExplicitVarSizeWithFlags_Flags[q24] /\ + var2_ExplicitVarSizeWithFlags_Values[q24] = var2_ExplicitVarSizeWithMarker_Values[q22] + | q24 : int(1..11)]) + | q22 : int(1..11)]), + and([var2_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> + var2_ExplicitVarSizeWithFlags_Values[q1] < var2_ExplicitVarSizeWithFlags_Values[q1 + 1] + | q1 : int(1..10)]), + and([var2_ExplicitVarSizeWithFlags_Flags[q2] = false -> var2_ExplicitVarSizeWithFlags_Values[q2] = -4 + | q2 : int(1..11)]), + and([var2_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> var2_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..10)]), + and([q6 + 1 <= var2_ExplicitVarSizeWithMarker_Marker -> + var2_ExplicitVarSizeWithMarker_Values[q6] < var2_ExplicitVarSizeWithMarker_Values[q6 + 1] + | q6 : int(1..10)]), + and([q7 > var2_ExplicitVarSizeWithMarker_Marker -> var2_ExplicitVarSizeWithMarker_Values[q7] = -4 + | q7 : int(1..11)]), + and([q10 <= var2_ExplicitVarSizeWithMarker_Marker -> + or([var2_ExplicitVarSizeWithFlags_Flags[q12] /\ + var2_ExplicitVarSizeWithFlags_Values[q12] = var2_ExplicitVarSizeWithMarker_Values[q10] + | q12 : int(1..11)]) + | q10 : int(1..11)]), + and([var2_ExplicitVarSizeWithFlags_Flags[q14] -> + or([q16 <= var2_ExplicitVarSizeWithMarker_Marker /\ + var2_ExplicitVarSizeWithMarker_Values[q16] = var2_ExplicitVarSizeWithFlags_Values[q14] + | q16 : int(1..11)]) + | q14 : int(1..11)]), + and([var2_Occurrence[q25] -> + or([var2_ExplicitVarSizeWithFlags_Flags[q27] /\ var2_ExplicitVarSizeWithFlags_Values[q27] = q25 + | q27 : int(1..11)]) + | q25 : int(-4..5, 2)]), + and([var2_ExplicitVarSizeWithFlags_Flags[q29] -> var2_Occurrence[var2_ExplicitVarSizeWithFlags_Values[q29]] + | q29 : int(1..11)]), + and([var2_Occurrence[q30] -> + or([q32 <= var2_ExplicitVarSizeWithMarker_Marker /\ var2_ExplicitVarSizeWithMarker_Values[q32] = q30 + | q32 : int(1..11)]) + | q30 : int(-4..5, 2)]), + and([q34 <= var2_ExplicitVarSizeWithMarker_Marker -> var2_Occurrence[var2_ExplicitVarSizeWithMarker_Values[q34]] + | q34 : int(1..11)]) + diff --git a/tests/exhaustive/autogen/gen32/expected/model_4_3_2.eprime b/tests/exhaustive/autogen/gen32/expected/model_4_3_2.eprime new file mode 100644 index 0000000000..8dcf88b159 --- /dev/null +++ b/tests/exhaustive/autogen/gen32/expected/model_4_3_2.eprime @@ -0,0 +1,69 @@ +language ESSENCE' 1.0 + +letting let1 be -4 +find var2_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..11)] of bool +find var2_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..11)] of int(-4..5, 2) +find var2_ExplicitVarSizeWithMarker_Marker: int(0..11) +find var2_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..11)] of int(-4..5, 2) +find var2_ExplicitVarSizeWithDummy: matrix indexed by [int(1..11)] of int(-4..5, 2, 6) +branching on + [var2_ExplicitVarSizeWithDummy, var2_ExplicitVarSizeWithFlags_Flags, var2_ExplicitVarSizeWithFlags_Values, + var2_ExplicitVarSizeWithMarker_Marker, var2_ExplicitVarSizeWithMarker_Values] +such that + or([var2_ExplicitVarSizeWithFlags_Flags[q38] /\ + !or([q40 <= var2_ExplicitVarSizeWithMarker_Marker /\ + var2_ExplicitVarSizeWithMarker_Values[q40] = var2_ExplicitVarSizeWithFlags_Values[q38] + | q40 : int(1..11)]) + | q38 : int(1..11)]) + \/ + or([q41 <= var2_ExplicitVarSizeWithMarker_Marker /\ + !or([var2_ExplicitVarSizeWithFlags_Flags[q43] /\ + var2_ExplicitVarSizeWithFlags_Values[q43] = var2_ExplicitVarSizeWithMarker_Values[q41] + | q43 : int(1..11)]) + | q41 : int(1..11)]), + and([var2_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> + var2_ExplicitVarSizeWithFlags_Values[q1] < var2_ExplicitVarSizeWithFlags_Values[q1 + 1] + | q1 : int(1..10)]), + and([var2_ExplicitVarSizeWithFlags_Flags[q2] = false -> var2_ExplicitVarSizeWithFlags_Values[q2] = -4 + | q2 : int(1..11)]), + and([var2_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> var2_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..10)]), + and([q6 + 1 <= var2_ExplicitVarSizeWithMarker_Marker -> + var2_ExplicitVarSizeWithMarker_Values[q6] < var2_ExplicitVarSizeWithMarker_Values[q6 + 1] + | q6 : int(1..10)]), + and([q7 > var2_ExplicitVarSizeWithMarker_Marker -> var2_ExplicitVarSizeWithMarker_Values[q7] = -4 + | q7 : int(1..11)]), + and([q10 <= var2_ExplicitVarSizeWithMarker_Marker -> + or([var2_ExplicitVarSizeWithFlags_Flags[q12] /\ + var2_ExplicitVarSizeWithFlags_Values[q12] = var2_ExplicitVarSizeWithMarker_Values[q10] + | q12 : int(1..11)]) + | q10 : int(1..11)]), + and([var2_ExplicitVarSizeWithFlags_Flags[q14] -> + or([q16 <= var2_ExplicitVarSizeWithMarker_Marker /\ + var2_ExplicitVarSizeWithMarker_Values[q16] = var2_ExplicitVarSizeWithFlags_Values[q14] + | q16 : int(1..11)]) + | q14 : int(1..11)]), + and([var2_ExplicitVarSizeWithDummy[q17] < var2_ExplicitVarSizeWithDummy[q17 + 1] \/ + var2_ExplicitVarSizeWithDummy[q17] = 6 + | q17 : int(1..10)]), + and([var2_ExplicitVarSizeWithDummy[q18] = 6 -> var2_ExplicitVarSizeWithDummy[q18 + 1] = 6 | q18 : int(1..10)]), + and([var2_ExplicitVarSizeWithDummy[q22] != 6 -> + or([var2_ExplicitVarSizeWithFlags_Flags[q24] /\ + var2_ExplicitVarSizeWithFlags_Values[q24] = var2_ExplicitVarSizeWithDummy[q22] + | q24 : int(1..11)]) + | q22 : int(1..11)]), + and([var2_ExplicitVarSizeWithFlags_Flags[q26] -> + or([var2_ExplicitVarSizeWithDummy[q28] != 6 /\ + var2_ExplicitVarSizeWithDummy[q28] = var2_ExplicitVarSizeWithFlags_Values[q26] + | q28 : int(1..11)]) + | q26 : int(1..11)]), + and([var2_ExplicitVarSizeWithDummy[q30] != 6 -> + or([q32 <= var2_ExplicitVarSizeWithMarker_Marker /\ + var2_ExplicitVarSizeWithMarker_Values[q32] = var2_ExplicitVarSizeWithDummy[q30] + | q32 : int(1..11)]) + | q30 : int(1..11)]), + and([q34 <= var2_ExplicitVarSizeWithMarker_Marker -> + or([var2_ExplicitVarSizeWithDummy[q36] != 6 /\ + var2_ExplicitVarSizeWithDummy[q36] = var2_ExplicitVarSizeWithMarker_Values[q34] + | q36 : int(1..11)]) + | q34 : int(1..11)]) + diff --git a/tests/exhaustive/autogen/gen32/expected/model_4_3_3.eprime b/tests/exhaustive/autogen/gen32/expected/model_4_3_3.eprime new file mode 100644 index 0000000000..d1c3ae501b --- /dev/null +++ b/tests/exhaustive/autogen/gen32/expected/model_4_3_3.eprime @@ -0,0 +1,44 @@ +language ESSENCE' 1.0 + +letting let1 be -4 +find var2_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..11)] of bool +find var2_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..11)] of int(-4..5, 2) +find var2_ExplicitVarSizeWithMarker_Marker: int(0..11) +find var2_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..11)] of int(-4..5, 2) +branching on + [var2_ExplicitVarSizeWithMarker_Marker, var2_ExplicitVarSizeWithMarker_Values, var2_ExplicitVarSizeWithFlags_Flags, + var2_ExplicitVarSizeWithFlags_Values] +such that + or([var2_ExplicitVarSizeWithFlags_Flags[q18] /\ + !or([q20 <= var2_ExplicitVarSizeWithMarker_Marker /\ + var2_ExplicitVarSizeWithMarker_Values[q20] = var2_ExplicitVarSizeWithFlags_Values[q18] + | q20 : int(1..11)]) + | q18 : int(1..11)]) + \/ + or([q21 <= var2_ExplicitVarSizeWithMarker_Marker /\ + !or([var2_ExplicitVarSizeWithFlags_Flags[q23] /\ + var2_ExplicitVarSizeWithFlags_Values[q23] = var2_ExplicitVarSizeWithMarker_Values[q21] + | q23 : int(1..11)]) + | q21 : int(1..11)]), + and([var2_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> + var2_ExplicitVarSizeWithFlags_Values[q1] < var2_ExplicitVarSizeWithFlags_Values[q1 + 1] + | q1 : int(1..10)]), + and([var2_ExplicitVarSizeWithFlags_Flags[q2] = false -> var2_ExplicitVarSizeWithFlags_Values[q2] = -4 + | q2 : int(1..11)]), + and([var2_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> var2_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..10)]), + and([q6 + 1 <= var2_ExplicitVarSizeWithMarker_Marker -> + var2_ExplicitVarSizeWithMarker_Values[q6] < var2_ExplicitVarSizeWithMarker_Values[q6 + 1] + | q6 : int(1..10)]), + and([q7 > var2_ExplicitVarSizeWithMarker_Marker -> var2_ExplicitVarSizeWithMarker_Values[q7] = -4 + | q7 : int(1..11)]), + and([q10 <= var2_ExplicitVarSizeWithMarker_Marker -> + or([var2_ExplicitVarSizeWithFlags_Flags[q12] /\ + var2_ExplicitVarSizeWithFlags_Values[q12] = var2_ExplicitVarSizeWithMarker_Values[q10] + | q12 : int(1..11)]) + | q10 : int(1..11)]), + and([var2_ExplicitVarSizeWithFlags_Flags[q14] -> + or([q16 <= var2_ExplicitVarSizeWithMarker_Marker /\ + var2_ExplicitVarSizeWithMarker_Values[q16] = var2_ExplicitVarSizeWithFlags_Values[q14] + | q16 : int(1..11)]) + | q14 : int(1..11)]) + diff --git a/tests/exhaustive/autogen/gen32/expected/model_4_4_1.eprime b/tests/exhaustive/autogen/gen32/expected/model_4_4_1.eprime new file mode 100644 index 0000000000..dc916012b6 --- /dev/null +++ b/tests/exhaustive/autogen/gen32/expected/model_4_4_1.eprime @@ -0,0 +1,32 @@ +language ESSENCE' 1.0 + +letting let1 be -4 +find var2_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..11)] of bool +find var2_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..11)] of int(-4..5, 2) +find var2_Occurrence: matrix indexed by [int(-4..5, 2)] of bool +branching on [var2_Occurrence, var2_ExplicitVarSizeWithFlags_Flags, var2_ExplicitVarSizeWithFlags_Values] +such that + or([var2_ExplicitVarSizeWithFlags_Flags[q8] /\ + !or([var2_ExplicitVarSizeWithFlags_Flags[q10] /\ + var2_ExplicitVarSizeWithFlags_Values[q10] = var2_ExplicitVarSizeWithFlags_Values[q8] + | q10 : int(1..11)]) + | q8 : int(1..11)]) + \/ + or([var2_ExplicitVarSizeWithFlags_Flags[q11] /\ + !or([var2_ExplicitVarSizeWithFlags_Flags[q13] /\ + var2_ExplicitVarSizeWithFlags_Values[q13] = var2_ExplicitVarSizeWithFlags_Values[q11] + | q13 : int(1..11)]) + | q11 : int(1..11)]), + and([var2_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> + var2_ExplicitVarSizeWithFlags_Values[q1] < var2_ExplicitVarSizeWithFlags_Values[q1 + 1] + | q1 : int(1..10)]), + and([var2_ExplicitVarSizeWithFlags_Flags[q2] = false -> var2_ExplicitVarSizeWithFlags_Values[q2] = -4 + | q2 : int(1..11)]), + and([var2_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> var2_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..10)]), + and([var2_Occurrence[q14] -> + or([var2_ExplicitVarSizeWithFlags_Flags[q16] /\ var2_ExplicitVarSizeWithFlags_Values[q16] = q14 + | q16 : int(1..11)]) + | q14 : int(-4..5, 2)]), + and([var2_ExplicitVarSizeWithFlags_Flags[q18] -> var2_Occurrence[var2_ExplicitVarSizeWithFlags_Values[q18]] + | q18 : int(1..11)]) + diff --git a/tests/exhaustive/autogen/gen32/expected/model_4_4_2.eprime b/tests/exhaustive/autogen/gen32/expected/model_4_4_2.eprime new file mode 100644 index 0000000000..26e15ff1e8 --- /dev/null +++ b/tests/exhaustive/autogen/gen32/expected/model_4_4_2.eprime @@ -0,0 +1,40 @@ +language ESSENCE' 1.0 + +letting let1 be -4 +find var2_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..11)] of bool +find var2_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..11)] of int(-4..5, 2) +find var2_ExplicitVarSizeWithDummy: matrix indexed by [int(1..11)] of int(-4..5, 2, 6) +branching on [var2_ExplicitVarSizeWithDummy, var2_ExplicitVarSizeWithFlags_Flags, var2_ExplicitVarSizeWithFlags_Values] +such that + or([var2_ExplicitVarSizeWithFlags_Flags[q19] /\ + !or([var2_ExplicitVarSizeWithFlags_Flags[q21] /\ + var2_ExplicitVarSizeWithFlags_Values[q21] = var2_ExplicitVarSizeWithFlags_Values[q19] + | q21 : int(1..11)]) + | q19 : int(1..11)]) + \/ + or([var2_ExplicitVarSizeWithFlags_Flags[q22] /\ + !or([var2_ExplicitVarSizeWithFlags_Flags[q24] /\ + var2_ExplicitVarSizeWithFlags_Values[q24] = var2_ExplicitVarSizeWithFlags_Values[q22] + | q24 : int(1..11)]) + | q22 : int(1..11)]), + and([var2_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> + var2_ExplicitVarSizeWithFlags_Values[q1] < var2_ExplicitVarSizeWithFlags_Values[q1 + 1] + | q1 : int(1..10)]), + and([var2_ExplicitVarSizeWithFlags_Flags[q2] = false -> var2_ExplicitVarSizeWithFlags_Values[q2] = -4 + | q2 : int(1..11)]), + and([var2_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> var2_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..10)]), + and([var2_ExplicitVarSizeWithDummy[q6] < var2_ExplicitVarSizeWithDummy[q6 + 1] \/ + var2_ExplicitVarSizeWithDummy[q6] = 6 + | q6 : int(1..10)]), + and([var2_ExplicitVarSizeWithDummy[q7] = 6 -> var2_ExplicitVarSizeWithDummy[q7 + 1] = 6 | q7 : int(1..10)]), + and([var2_ExplicitVarSizeWithDummy[q11] != 6 -> + or([var2_ExplicitVarSizeWithFlags_Flags[q13] /\ + var2_ExplicitVarSizeWithFlags_Values[q13] = var2_ExplicitVarSizeWithDummy[q11] + | q13 : int(1..11)]) + | q11 : int(1..11)]), + and([var2_ExplicitVarSizeWithFlags_Flags[q15] -> + or([var2_ExplicitVarSizeWithDummy[q17] != 6 /\ + var2_ExplicitVarSizeWithDummy[q17] = var2_ExplicitVarSizeWithFlags_Values[q15] + | q17 : int(1..11)]) + | q15 : int(1..11)]) + diff --git a/tests/exhaustive/autogen/gen32/expected/model_4_4_3.eprime b/tests/exhaustive/autogen/gen32/expected/model_4_4_3.eprime new file mode 100644 index 0000000000..a9522bafc7 --- /dev/null +++ b/tests/exhaustive/autogen/gen32/expected/model_4_4_3.eprime @@ -0,0 +1,44 @@ +language ESSENCE' 1.0 + +letting let1 be -4 +find var2_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..11)] of bool +find var2_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..11)] of int(-4..5, 2) +find var2_ExplicitVarSizeWithMarker_Marker: int(0..11) +find var2_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..11)] of int(-4..5, 2) +branching on + [var2_ExplicitVarSizeWithMarker_Marker, var2_ExplicitVarSizeWithMarker_Values, var2_ExplicitVarSizeWithFlags_Flags, + var2_ExplicitVarSizeWithFlags_Values] +such that + or([var2_ExplicitVarSizeWithFlags_Flags[q18] /\ + !or([var2_ExplicitVarSizeWithFlags_Flags[q20] /\ + var2_ExplicitVarSizeWithFlags_Values[q20] = var2_ExplicitVarSizeWithFlags_Values[q18] + | q20 : int(1..11)]) + | q18 : int(1..11)]) + \/ + or([var2_ExplicitVarSizeWithFlags_Flags[q21] /\ + !or([var2_ExplicitVarSizeWithFlags_Flags[q23] /\ + var2_ExplicitVarSizeWithFlags_Values[q23] = var2_ExplicitVarSizeWithFlags_Values[q21] + | q23 : int(1..11)]) + | q21 : int(1..11)]), + and([var2_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> + var2_ExplicitVarSizeWithFlags_Values[q1] < var2_ExplicitVarSizeWithFlags_Values[q1 + 1] + | q1 : int(1..10)]), + and([var2_ExplicitVarSizeWithFlags_Flags[q2] = false -> var2_ExplicitVarSizeWithFlags_Values[q2] = -4 + | q2 : int(1..11)]), + and([var2_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> var2_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..10)]), + and([q6 + 1 <= var2_ExplicitVarSizeWithMarker_Marker -> + var2_ExplicitVarSizeWithMarker_Values[q6] < var2_ExplicitVarSizeWithMarker_Values[q6 + 1] + | q6 : int(1..10)]), + and([q7 > var2_ExplicitVarSizeWithMarker_Marker -> var2_ExplicitVarSizeWithMarker_Values[q7] = -4 + | q7 : int(1..11)]), + and([q10 <= var2_ExplicitVarSizeWithMarker_Marker -> + or([var2_ExplicitVarSizeWithFlags_Flags[q12] /\ + var2_ExplicitVarSizeWithFlags_Values[q12] = var2_ExplicitVarSizeWithMarker_Values[q10] + | q12 : int(1..11)]) + | q10 : int(1..11)]), + and([var2_ExplicitVarSizeWithFlags_Flags[q14] -> + or([q16 <= var2_ExplicitVarSizeWithMarker_Marker /\ + var2_ExplicitVarSizeWithMarker_Values[q16] = var2_ExplicitVarSizeWithFlags_Values[q14] + | q16 : int(1..11)]) + | q14 : int(1..11)]) + diff --git a/tests/exhaustive/autogen/gen32/expected/model_4_4_4.eprime b/tests/exhaustive/autogen/gen32/expected/model_4_4_4.eprime new file mode 100644 index 0000000000..ec2da87b64 --- /dev/null +++ b/tests/exhaustive/autogen/gen32/expected/model_4_4_4.eprime @@ -0,0 +1,25 @@ +language ESSENCE' 1.0 + +letting let1 be -4 +find var2_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..11)] of bool +find var2_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..11)] of int(-4..5, 2) +branching on [var2_ExplicitVarSizeWithFlags_Flags, var2_ExplicitVarSizeWithFlags_Values] +such that + or([var2_ExplicitVarSizeWithFlags_Flags[q7] /\ + !or([var2_ExplicitVarSizeWithFlags_Flags[q9] /\ + var2_ExplicitVarSizeWithFlags_Values[q9] = var2_ExplicitVarSizeWithFlags_Values[q7] + | q9 : int(1..11)]) + | q7 : int(1..11)]) + \/ + or([var2_ExplicitVarSizeWithFlags_Flags[q10] /\ + !or([var2_ExplicitVarSizeWithFlags_Flags[q12] /\ + var2_ExplicitVarSizeWithFlags_Values[q12] = var2_ExplicitVarSizeWithFlags_Values[q10] + | q12 : int(1..11)]) + | q10 : int(1..11)]), + and([var2_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> + var2_ExplicitVarSizeWithFlags_Values[q1] < var2_ExplicitVarSizeWithFlags_Values[q1 + 1] + | q1 : int(1..10)]), + and([var2_ExplicitVarSizeWithFlags_Flags[q2] = false -> var2_ExplicitVarSizeWithFlags_Values[q2] = -4 + | q2 : int(1..11)]), + and([var2_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> var2_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..10)]) + diff --git a/tests/exhaustive/autogen/gen35/expected/model_1.eprime b/tests/exhaustive/autogen/gen35/expected/model_1.eprime index 49af6c5f46..0a734c1835 100644 --- a/tests/exhaustive/autogen/gen35/expected/model_1.eprime +++ b/tests/exhaustive/autogen/gen35/expected/model_1.eprime @@ -13,43 +13,19 @@ branching on var2_FunctionAsRelationR8R17_RelationAsSetR8R17_ExplicitVarSizeWithMarkerR8R17_Values_1_ExplicitWithFlags_Values, var2_FunctionAsRelationR8R17_RelationAsSetR8R17_ExplicitVarSizeWithMarkerR8R17_Values_2_RelationAsMatrix] such that -<<<<<<< HEAD - and([q1 + 1 <= var2_FunctionAsRelationR8R16_RelationAsSetR8R16_ExplicitVarSizeWithMarkerR8R16_Marker -> -<<<<<<< HEAD - flatten([flatten([]), -======= - flatten([([] : `matrix indexed by [int()] of int`), ->>>>>>> master - flatten([[-toInt(var2_FunctionAsRelationR8R16_RelationAsSetR8R16_ExplicitVarSizeWithMarkerR8R16_Values_2_RelationAsMatrix - [q1, q15, q16]) - | q16 : bool] - | q15 : bool]); -======= and([q1 + 1 <= var2_FunctionAsRelationR8R17_RelationAsSetR8R17_ExplicitVarSizeWithMarkerR8R17_Marker -> flatten([([] : `matrix indexed by [int()] of int`), flatten([[-toInt(var2_FunctionAsRelationR8R17_RelationAsSetR8R17_ExplicitVarSizeWithMarkerR8R17_Values_2_RelationAsMatrix [q1, q16, q17]) | q17 : bool] | q16 : bool]); ->>>>>>> main int(1..2)]) >>>>>> master - flatten([[-toInt(var2_FunctionAsRelationR8R16_RelationAsSetR8R16_ExplicitVarSizeWithMarkerR8R16_Values_2_RelationAsMatrix - [q1 + 1, q18, q19]) - | q19 : bool] - | q18 : bool]); -======= flatten([[-toInt(var2_FunctionAsRelationR8R17_RelationAsSetR8R17_ExplicitVarSizeWithMarkerR8R17_Values_2_RelationAsMatrix [q1 + 1, q19, q20]) | q20 : bool] | q19 : bool]); ->>>>>>> main int(1..2)]) | q1 : int(1..2)]), and([q2 > var2_FunctionAsRelationR8R17_RelationAsSetR8R17_ExplicitVarSizeWithMarkerR8R17_Marker -> diff --git a/tests/exhaustive/autogen/gen35/expected/model_1.eprime.orig b/tests/exhaustive/autogen/gen35/expected/model_1.eprime.orig deleted file mode 100644 index 6d09f93a09..0000000000 --- a/tests/exhaustive/autogen/gen35/expected/model_1.eprime.orig +++ /dev/null @@ -1,57 +0,0 @@ -language ESSENCE' 1.0 - -find var2_FunctionAsRelationR8R16_RelationAsSetR8R16_ExplicitVarSizeWithMarkerR8R16_Marker: int(0..3) -find var2_FunctionAsRelationR8R16_RelationAsSetR8R16_ExplicitVarSizeWithMarkerR8R16_Values_1_ExplicitWithFlags_Flags: - matrix indexed by [int(1..3), int(1..0)] of int(0) -find var2_FunctionAsRelationR8R16_RelationAsSetR8R16_ExplicitVarSizeWithMarkerR8R16_Values_1_ExplicitWithFlags_Values: - matrix indexed by [int(1..3), int(1..0)] of bool -find var2_FunctionAsRelationR8R16_RelationAsSetR8R16_ExplicitVarSizeWithMarkerR8R16_Values_2_RelationAsMatrix: - matrix indexed by [int(1..3), bool, bool] of bool -branching on - [var2_FunctionAsRelationR8R16_RelationAsSetR8R16_ExplicitVarSizeWithMarkerR8R16_Marker, - var2_FunctionAsRelationR8R16_RelationAsSetR8R16_ExplicitVarSizeWithMarkerR8R16_Values_1_ExplicitWithFlags_Flags, - var2_FunctionAsRelationR8R16_RelationAsSetR8R16_ExplicitVarSizeWithMarkerR8R16_Values_1_ExplicitWithFlags_Values, - var2_FunctionAsRelationR8R16_RelationAsSetR8R16_ExplicitVarSizeWithMarkerR8R16_Values_2_RelationAsMatrix] -such that - and([q1 + 1 <= var2_FunctionAsRelationR8R16_RelationAsSetR8R16_ExplicitVarSizeWithMarkerR8R16_Marker -> -<<<<<<< HEAD - flatten([flatten([]), -======= - flatten([([] : `matrix indexed by [int()] of int`), ->>>>>>> master - flatten([[-toInt(var2_FunctionAsRelationR8R16_RelationAsSetR8R16_ExplicitVarSizeWithMarkerR8R16_Values_2_RelationAsMatrix - [q1, q15, q16]) - | q16 : bool] - | q15 : bool]); - int(1..2)]) - >>>>>> master - flatten([[-toInt(var2_FunctionAsRelationR8R16_RelationAsSetR8R16_ExplicitVarSizeWithMarkerR8R16_Values_2_RelationAsMatrix - [q1 + 1, q18, q19]) - | q19 : bool] - | q18 : bool]); - int(1..2)]) - | q1 : int(1..2)]), - and([q2 > var2_FunctionAsRelationR8R16_RelationAsSetR8R16_ExplicitVarSizeWithMarkerR8R16_Marker -> - and([and([var2_FunctionAsRelationR8R16_RelationAsSetR8R16_ExplicitVarSizeWithMarkerR8R16_Values_2_RelationAsMatrix - [q2, q22, q23] - = false - | q23 : bool]) - | q22 : bool]) - | q2 : int(1..3)]), - 0 <= var2_FunctionAsRelationR8R16_RelationAsSetR8R16_ExplicitVarSizeWithMarkerR8R16_Marker, - var2_FunctionAsRelationR8R16_RelationAsSetR8R16_ExplicitVarSizeWithMarkerR8R16_Marker <= 3, - and([q3 <= var2_FunctionAsRelationR8R16_RelationAsSetR8R16_ExplicitVarSizeWithMarkerR8R16_Marker -> false - | q3 : int(1..3)]), - and([q3 <= var2_FunctionAsRelationR8R16_RelationAsSetR8R16_ExplicitVarSizeWithMarkerR8R16_Marker -> - 4 <= - sum([sum([toInt(var2_FunctionAsRelationR8R16_RelationAsSetR8R16_ExplicitVarSizeWithMarkerR8R16_Values_2_RelationAsMatrix - [q3, q10, q11]) - | q11 : bool]) - | q10 : bool]) - | q3 : int(1..3)]) - diff --git a/tests/exhaustive/autogen/gen36/expected/model_1-solution000001.solution b/tests/exhaustive/autogen/gen36/expected/model_1-solution000001.solution new file mode 100644 index 0000000000..78bab35d5f --- /dev/null +++ b/tests/exhaustive/autogen/gen36/expected/model_1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting var6 be {} diff --git a/tests/exhaustive/autogen/gen36/expected/model_2-solution000001.solution b/tests/exhaustive/autogen/gen36/expected/model_2-solution000001.solution new file mode 100644 index 0000000000..78bab35d5f --- /dev/null +++ b/tests/exhaustive/autogen/gen36/expected/model_2-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting var6 be {} diff --git a/tests/exhaustive/autogen/gen36/expected/model_3-solution000001.solution b/tests/exhaustive/autogen/gen36/expected/model_3-solution000001.solution new file mode 100644 index 0000000000..78bab35d5f --- /dev/null +++ b/tests/exhaustive/autogen/gen36/expected/model_3-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting var6 be {} diff --git a/tests/exhaustive/autogen/gen36/expected/model_3.eprime.orig b/tests/exhaustive/autogen/gen36/expected/model_3.eprime.orig deleted file mode 100644 index a5be2eacf9..0000000000 --- a/tests/exhaustive/autogen/gen36/expected/model_3.eprime.orig +++ /dev/null @@ -1,94 +0,0 @@ -language ESSENCE' 1.0 - -letting let1 be 2 -find var6_ExplicitVarSizeWithMarkerR19_Marker: int(0..2) -find var6_ExplicitVarSizeWithMarkerR19_Values_PartitionOccurrence_NumParts: matrix indexed by [int(1..2)] of int(1..2) -find var6_ExplicitVarSizeWithMarkerR19_Values_PartitionOccurrence_WhichPart: - matrix indexed by [int(1..2), int(2, 5)] of int(1..2) -find var6_ExplicitVarSizeWithMarkerR19_Values_PartitionOccurrence_PartSizes: - matrix indexed by [int(1..2), int(1..2)] of int(0) -find var6_ExplicitVarSizeWithMarkerR19_Values_PartitionOccurrence_FirstIndex: - matrix indexed by [int(1..2), int(1..2)] of int(2, 5) -branching on - [var6_ExplicitVarSizeWithMarkerR19_Marker, var6_ExplicitVarSizeWithMarkerR19_Values_PartitionOccurrence_NumParts, - var6_ExplicitVarSizeWithMarkerR19_Values_PartitionOccurrence_WhichPart, - var6_ExplicitVarSizeWithMarkerR19_Values_PartitionOccurrence_PartSizes, - var6_ExplicitVarSizeWithMarkerR19_Values_PartitionOccurrence_FirstIndex] -such that - 2 <= var6_ExplicitVarSizeWithMarkerR19_Marker -> - flatten([[var6_ExplicitVarSizeWithMarkerR19_Values_PartitionOccurrence_NumParts[1]; int(1)], - [var6_ExplicitVarSizeWithMarkerR19_Values_PartitionOccurrence_WhichPart[1, q14] | q14 : int(2, 5)], - [var6_ExplicitVarSizeWithMarkerR19_Values_PartitionOccurrence_PartSizes[1, q15] | q15 : int(1..2)], - [var6_ExplicitVarSizeWithMarkerR19_Values_PartitionOccurrence_FirstIndex[1, q16] | q16 : int(1..2)]; - int(1..4)]) - var6_ExplicitVarSizeWithMarkerR19_Marker -> - and([var6_ExplicitVarSizeWithMarkerR19_Values_PartitionOccurrence_NumParts[q2] = 1, - and([var6_ExplicitVarSizeWithMarkerR19_Values_PartitionOccurrence_WhichPart[q2, q20] = 1 - | q20 : int(2, 5)]), - and([var6_ExplicitVarSizeWithMarkerR19_Values_PartitionOccurrence_PartSizes[q2, q21] = 0 - | q21 : int(1..2)]), - and([var6_ExplicitVarSizeWithMarkerR19_Values_PartitionOccurrence_FirstIndex[q2, q22] = 2 - | q22 : int(1..2)]); - int(1..4)]) - | q2 : int(1..2)]), - and([q3 <= var6_ExplicitVarSizeWithMarkerR19_Marker -> - and([q4 <= var6_ExplicitVarSizeWithMarkerR19_Values_PartitionOccurrence_NumParts[q3] -> - 0 = var6_ExplicitVarSizeWithMarkerR19_Values_PartitionOccurrence_PartSizes[q3, q4] - | q4 : int(1..2)]) - | q3 : int(1..2)]), - and([q3 <= var6_ExplicitVarSizeWithMarkerR19_Marker -> - and([q4 > var6_ExplicitVarSizeWithMarkerR19_Values_PartitionOccurrence_NumParts[q3] -> - var6_ExplicitVarSizeWithMarkerR19_Values_PartitionOccurrence_PartSizes[q3, q4] = 0 - | q4 : int(1..2)]) - | q3 : int(1..2)]), - and([q3 <= var6_ExplicitVarSizeWithMarkerR19_Marker -> - 3 <= var6_ExplicitVarSizeWithMarkerR19_Values_PartitionOccurrence_NumParts[q3] - | q3 : int(1..2)]), - and([q3 <= var6_ExplicitVarSizeWithMarkerR19_Marker -> - var6_ExplicitVarSizeWithMarkerR19_Values_PartitionOccurrence_NumParts[q3] <= 2 - | q3 : int(1..2)]), - and([q3 <= var6_ExplicitVarSizeWithMarkerR19_Marker -> - var6_ExplicitVarSizeWithMarkerR19_Values_PartitionOccurrence_NumParts[q3] = - max([var6_ExplicitVarSizeWithMarkerR19_Values_PartitionOccurrence_WhichPart[q3, q7] | q7 : int(2, 5)]) - | q3 : int(1..2)]), - and([q3 <= var6_ExplicitVarSizeWithMarkerR19_Marker -> - and([var6_ExplicitVarSizeWithMarkerR19_Values_PartitionOccurrence_PartSizes[q3, q8] = - sum([toInt(var6_ExplicitVarSizeWithMarkerR19_Values_PartitionOccurrence_WhichPart[q3, q9] = q8) - | q9 : int(2, 5)]) - | q8 : int(1..2)]) - | q3 : int(1..2)]), - and([q3 <= var6_ExplicitVarSizeWithMarkerR19_Marker -> - and([q10 <= var6_ExplicitVarSizeWithMarkerR19_Values_PartitionOccurrence_NumParts[q3] -> - and([var6_ExplicitVarSizeWithMarkerR19_Values_PartitionOccurrence_WhichPart[q3, q11] = q10 -> - var6_ExplicitVarSizeWithMarkerR19_Values_PartitionOccurrence_FirstIndex[q3, q10] <= q11 - | q11 : int(2, 5)]) - | q10 : int(1..2)]) - | q3 : int(1..2)]), - and([q3 <= var6_ExplicitVarSizeWithMarkerR19_Marker -> - and([q10 <= var6_ExplicitVarSizeWithMarkerR19_Values_PartitionOccurrence_NumParts[q3] -> - or([var6_ExplicitVarSizeWithMarkerR19_Values_PartitionOccurrence_WhichPart[q3, q11] = q10 /\ - var6_ExplicitVarSizeWithMarkerR19_Values_PartitionOccurrence_FirstIndex[q3, q10] = q11 - | q11 : int(2, 5)]) - | q10 : int(1..2)]) - | q3 : int(1..2)]), - and([q3 <= var6_ExplicitVarSizeWithMarkerR19_Marker -> - and([q10 > var6_ExplicitVarSizeWithMarkerR19_Values_PartitionOccurrence_NumParts[q3] -> - var6_ExplicitVarSizeWithMarkerR19_Values_PartitionOccurrence_FirstIndex[q3, q10] = 2 - | q10 : int(1..2)]) - | q3 : int(1..2)]), - and([q3 <= var6_ExplicitVarSizeWithMarkerR19_Marker -> - and([q12 <= var6_ExplicitVarSizeWithMarkerR19_Values_PartitionOccurrence_NumParts[q3] /\ - q13 <= var6_ExplicitVarSizeWithMarkerR19_Values_PartitionOccurrence_NumParts[q3] - -> - (q12 < q13 <-> - var6_ExplicitVarSizeWithMarkerR19_Values_PartitionOccurrence_FirstIndex[q3, q12] < - var6_ExplicitVarSizeWithMarkerR19_Values_PartitionOccurrence_FirstIndex[q3, q13]) - | q12 : int(1..2), q13 : int(1..2)]) - | q3 : int(1..2)]) - diff --git a/tests/exhaustive/autogen/gen36/expected/model_4-solution000001.solution b/tests/exhaustive/autogen/gen36/expected/model_4-solution000001.solution new file mode 100644 index 0000000000..78bab35d5f --- /dev/null +++ b/tests/exhaustive/autogen/gen36/expected/model_4-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting var6 be {} diff --git a/tests/exhaustive/autogen/gen36/expected/model_5-solution000001.solution b/tests/exhaustive/autogen/gen36/expected/model_5-solution000001.solution new file mode 100644 index 0000000000..78bab35d5f --- /dev/null +++ b/tests/exhaustive/autogen/gen36/expected/model_5-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting var6 be {} diff --git a/tests/exhaustive/autogen/gen36/expected/model_6-solution000001.solution b/tests/exhaustive/autogen/gen36/expected/model_6-solution000001.solution new file mode 100644 index 0000000000..78bab35d5f --- /dev/null +++ b/tests/exhaustive/autogen/gen36/expected/model_6-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting var6 be {} diff --git a/tests/exhaustive/autogen/gen36/expected/model_6.eprime.orig b/tests/exhaustive/autogen/gen36/expected/model_6.eprime.orig deleted file mode 100644 index c2d0633786..0000000000 --- a/tests/exhaustive/autogen/gen36/expected/model_6.eprime.orig +++ /dev/null @@ -1,95 +0,0 @@ -language ESSENCE' 1.0 - -letting let1 be 2 -find var6_ExplicitVarSizeWithFlagsR19_Flags: matrix indexed by [int(1..2)] of bool -find var6_ExplicitVarSizeWithFlagsR19_Values_PartitionOccurrence_NumParts: matrix indexed by [int(1..2)] of int(1..2) -find var6_ExplicitVarSizeWithFlagsR19_Values_PartitionOccurrence_WhichPart: - matrix indexed by [int(1..2), int(2, 5)] of int(1..2) -find var6_ExplicitVarSizeWithFlagsR19_Values_PartitionOccurrence_PartSizes: - matrix indexed by [int(1..2), int(1..2)] of int(0) -find var6_ExplicitVarSizeWithFlagsR19_Values_PartitionOccurrence_FirstIndex: - matrix indexed by [int(1..2), int(1..2)] of int(2, 5) -branching on - [var6_ExplicitVarSizeWithFlagsR19_Flags, var6_ExplicitVarSizeWithFlagsR19_Values_PartitionOccurrence_NumParts, - var6_ExplicitVarSizeWithFlagsR19_Values_PartitionOccurrence_WhichPart, - var6_ExplicitVarSizeWithFlagsR19_Values_PartitionOccurrence_PartSizes, - var6_ExplicitVarSizeWithFlagsR19_Values_PartitionOccurrence_FirstIndex] -such that - var6_ExplicitVarSizeWithFlagsR19_Flags[2] -> - flatten([[var6_ExplicitVarSizeWithFlagsR19_Values_PartitionOccurrence_NumParts[1]; int(1)], - [var6_ExplicitVarSizeWithFlagsR19_Values_PartitionOccurrence_WhichPart[1, q16] | q16 : int(2, 5)], - [var6_ExplicitVarSizeWithFlagsR19_Values_PartitionOccurrence_PartSizes[1, q17] | q17 : int(1..2)], - [var6_ExplicitVarSizeWithFlagsR19_Values_PartitionOccurrence_FirstIndex[1, q18] | q18 : int(1..2)]; - int(1..4)]) - - and([var6_ExplicitVarSizeWithFlagsR19_Values_PartitionOccurrence_NumParts[q2] = 1, - and([var6_ExplicitVarSizeWithFlagsR19_Values_PartitionOccurrence_WhichPart[q2, q22] = 1 - | q22 : int(2, 5)]), - and([var6_ExplicitVarSizeWithFlagsR19_Values_PartitionOccurrence_PartSizes[q2, q23] = 0 - | q23 : int(1..2)]), - and([var6_ExplicitVarSizeWithFlagsR19_Values_PartitionOccurrence_FirstIndex[q2, q24] = 2 - | q24 : int(1..2)]); - int(1..4)]) - | q2 : int(1..2)]), - var6_ExplicitVarSizeWithFlagsR19_Flags[2] -> var6_ExplicitVarSizeWithFlagsR19_Flags[1], - and([var6_ExplicitVarSizeWithFlagsR19_Flags[q5] -> - and([q6 <= var6_ExplicitVarSizeWithFlagsR19_Values_PartitionOccurrence_NumParts[q5] -> - 0 = var6_ExplicitVarSizeWithFlagsR19_Values_PartitionOccurrence_PartSizes[q5, q6] - | q6 : int(1..2)]) - | q5 : int(1..2)]), - and([var6_ExplicitVarSizeWithFlagsR19_Flags[q5] -> - and([q6 > var6_ExplicitVarSizeWithFlagsR19_Values_PartitionOccurrence_NumParts[q5] -> - var6_ExplicitVarSizeWithFlagsR19_Values_PartitionOccurrence_PartSizes[q5, q6] = 0 - | q6 : int(1..2)]) - | q5 : int(1..2)]), - and([var6_ExplicitVarSizeWithFlagsR19_Flags[q5] -> - 3 <= var6_ExplicitVarSizeWithFlagsR19_Values_PartitionOccurrence_NumParts[q5] - | q5 : int(1..2)]), - and([var6_ExplicitVarSizeWithFlagsR19_Flags[q5] -> - var6_ExplicitVarSizeWithFlagsR19_Values_PartitionOccurrence_NumParts[q5] <= 2 - | q5 : int(1..2)]), - and([var6_ExplicitVarSizeWithFlagsR19_Flags[q5] -> - var6_ExplicitVarSizeWithFlagsR19_Values_PartitionOccurrence_NumParts[q5] = - max([var6_ExplicitVarSizeWithFlagsR19_Values_PartitionOccurrence_WhichPart[q5, q9] | q9 : int(2, 5)]) - | q5 : int(1..2)]), - and([var6_ExplicitVarSizeWithFlagsR19_Flags[q5] -> - and([var6_ExplicitVarSizeWithFlagsR19_Values_PartitionOccurrence_PartSizes[q5, q10] = - sum([toInt(var6_ExplicitVarSizeWithFlagsR19_Values_PartitionOccurrence_WhichPart[q5, q11] = q10) - | q11 : int(2, 5)]) - | q10 : int(1..2)]) - | q5 : int(1..2)]), - and([var6_ExplicitVarSizeWithFlagsR19_Flags[q5] -> - and([q12 <= var6_ExplicitVarSizeWithFlagsR19_Values_PartitionOccurrence_NumParts[q5] -> - and([var6_ExplicitVarSizeWithFlagsR19_Values_PartitionOccurrence_WhichPart[q5, q13] = q12 -> - var6_ExplicitVarSizeWithFlagsR19_Values_PartitionOccurrence_FirstIndex[q5, q12] <= q13 - | q13 : int(2, 5)]) - | q12 : int(1..2)]) - | q5 : int(1..2)]), - and([var6_ExplicitVarSizeWithFlagsR19_Flags[q5] -> - and([q12 <= var6_ExplicitVarSizeWithFlagsR19_Values_PartitionOccurrence_NumParts[q5] -> - or([var6_ExplicitVarSizeWithFlagsR19_Values_PartitionOccurrence_WhichPart[q5, q13] = q12 /\ - var6_ExplicitVarSizeWithFlagsR19_Values_PartitionOccurrence_FirstIndex[q5, q12] = q13 - | q13 : int(2, 5)]) - | q12 : int(1..2)]) - | q5 : int(1..2)]), - and([var6_ExplicitVarSizeWithFlagsR19_Flags[q5] -> - and([q12 > var6_ExplicitVarSizeWithFlagsR19_Values_PartitionOccurrence_NumParts[q5] -> - var6_ExplicitVarSizeWithFlagsR19_Values_PartitionOccurrence_FirstIndex[q5, q12] = 2 - | q12 : int(1..2)]) - | q5 : int(1..2)]), - and([var6_ExplicitVarSizeWithFlagsR19_Flags[q5] -> - and([q14 <= var6_ExplicitVarSizeWithFlagsR19_Values_PartitionOccurrence_NumParts[q5] /\ - q15 <= var6_ExplicitVarSizeWithFlagsR19_Values_PartitionOccurrence_NumParts[q5] - -> - (q14 < q15 <-> - var6_ExplicitVarSizeWithFlagsR19_Values_PartitionOccurrence_FirstIndex[q5, q14] < - var6_ExplicitVarSizeWithFlagsR19_Values_PartitionOccurrence_FirstIndex[q5, q15]) - | q14 : int(1..2), q15 : int(1..2)]) - | q5 : int(1..2)]) - diff --git a/tests/exhaustive/autogen/gen37/expected/model_1.eprime b/tests/exhaustive/autogen/gen37/expected/model_1.eprime index 335600f8a4..d9aff1a2af 100644 --- a/tests/exhaustive/autogen/gen37/expected/model_1.eprime +++ b/tests/exhaustive/autogen/gen37/expected/model_1.eprime @@ -16,32 +16,24 @@ such that [-toInt(var1_RelationAsSetR5R8_ExplicitR5R8_1_ExplicitVarSizeWithMarker_Values[1, q13]) | q13 : int(1..2)]; int(1..2)]), -<<<<<<< HEAD - flatten([]); -======= flatten([flatten([[-var1_RelationAsSetR5R8_ExplicitR5R8_2_ExplicitWithFlags_Flags[1, q14]; int(1)], [-toInt(var1_RelationAsSetR5R8_ExplicitR5R8_2_ExplicitWithFlags_Values[1, q14]); int(1)]; int(1..2)]) | q14 : int(1..2)]); ->>>>>>> main int(1..2)]) >>>>>> main int(1..2)]), and([2 <= var1_RelationAsSetR5R8_ExplicitR5R8_1_ExplicitVarSizeWithMarker_Marker[q2] -> - [-toInt(var1_RelationAsSetR5R8_ExplicitR5R8_1_ExplicitVarSizeWithMarker_Values[q2, 1]); int(1)] var1_RelationAsSetR5R8_ExplicitR5R8_1_ExplicitVarSizeWithMarker_Marker[q2] -> var1_RelationAsSetR5R8_ExplicitR5R8_1_ExplicitVarSizeWithMarker_Values[q2, q4] = false diff --git a/tests/exhaustive/autogen/gen37/expected/model_2.eprime b/tests/exhaustive/autogen/gen37/expected/model_2.eprime index 47b06b745d..e7a984ee90 100644 --- a/tests/exhaustive/autogen/gen37/expected/model_2.eprime +++ b/tests/exhaustive/autogen/gen37/expected/model_2.eprime @@ -32,8 +32,8 @@ such that int(1..2)]); int(1..2)]), and([2 <= var1_RelationAsSetR5R9_ExplicitR5R9_1_ExplicitVarSizeWithMarker_Marker[q2] -> - [-toInt(var1_RelationAsSetR5R9_ExplicitR5R9_1_ExplicitVarSizeWithMarker_Values[q2, 1]); int(1)] var1_RelationAsSetR5R9_ExplicitR5R9_1_ExplicitVarSizeWithMarker_Marker[q2] -> var1_RelationAsSetR5R9_ExplicitR5R9_1_ExplicitVarSizeWithMarker_Values[q2, q4] = false diff --git a/tests/exhaustive/autogen/gen37/expected/model_3.eprime b/tests/exhaustive/autogen/gen37/expected/model_3.eprime index 49469708bc..de9c2120e0 100644 --- a/tests/exhaustive/autogen/gen37/expected/model_3.eprime +++ b/tests/exhaustive/autogen/gen37/expected/model_3.eprime @@ -18,16 +18,11 @@ such that [-toInt(var1_RelationAsSetR4R8_ExplicitR4R8_1_ExplicitVarSizeWithFlags_Values[1, q15]); int(1)]; int(1..2)]) -<<<<<<< HEAD - | q14 : int(1..2)]), - flatten([]); -======= | q15 : int(1..2)]), flatten([flatten([[-var1_RelationAsSetR4R8_ExplicitR4R8_2_ExplicitWithFlags_Flags[1, q16]; int(1)], [-toInt(var1_RelationAsSetR4R8_ExplicitR4R8_2_ExplicitWithFlags_Values[1, q16]); int(1)]; int(1..2)]) | q16 : int(1..2)]); ->>>>>>> main int(1..2)]) >>>>>> main int(1..2)]), and([var1_RelationAsSetR4R8_ExplicitR4R8_1_ExplicitVarSizeWithFlags_Flags[q2, 2] -> - [-toInt(var1_RelationAsSetR4R8_ExplicitR4R8_1_ExplicitVarSizeWithFlags_Values[q2, 1]); int(1)] var1_RelationAsSetR4R8_ExplicitR4R8_1_ExplicitVarSizeWithFlags_Values[q2, q4] = false diff --git a/tests/exhaustive/autogen/gen37/expected/model_4.eprime b/tests/exhaustive/autogen/gen37/expected/model_4.eprime index bd2dd0aec4..8477dbbc36 100644 --- a/tests/exhaustive/autogen/gen37/expected/model_4.eprime +++ b/tests/exhaustive/autogen/gen37/expected/model_4.eprime @@ -37,8 +37,8 @@ such that int(1..2)]); int(1..2)]), and([var1_RelationAsSetR4R9_ExplicitR4R9_1_ExplicitVarSizeWithFlags_Flags[q2, 2] -> - [-toInt(var1_RelationAsSetR4R9_ExplicitR4R9_1_ExplicitVarSizeWithFlags_Values[q2, 1]); int(1)] var1_RelationAsSetR4R9_ExplicitR4R9_1_ExplicitVarSizeWithFlags_Values[q2, q4] = false diff --git a/tests/exhaustive/basic/comprehension_01_2/expected/model.eprime b/tests/exhaustive/basic/comprehension_01_2/expected/model.eprime index 8607f86a85..5928bc4873 100644 --- a/tests/exhaustive/basic/comprehension_01_2/expected/model.eprime +++ b/tests/exhaustive/basic/comprehension_01_2/expected/model.eprime @@ -6,6 +6,5 @@ branching on [x, y] such that x = sum([toInt(or([i_Explicit[q4] = y | q4 : int(1..2)])) - | i_Explicit : matrix indexed by [int(1..2)] of int(7..9), - [i_Explicit[1]; int(1)] i_ExplicitVarSizeWithDummy[2] = 9, 1 <= sum([toInt(i_ExplicitVarSizeWithDummy[q3] != 9) | q3 : int(1..2)]), sum([toInt(i_ExplicitVarSizeWithDummy[q3] != 9) | q3 : int(1..2)]) <= 2, diff --git a/tests/exhaustive/basic/comprehension_03_2/expected/model.eprime b/tests/exhaustive/basic/comprehension_03_2/expected/model.eprime index 71f6ae576f..52b5ee4f84 100644 --- a/tests/exhaustive/basic/comprehension_03_2/expected/model.eprime +++ b/tests/exhaustive/basic/comprehension_03_2/expected/model.eprime @@ -7,8 +7,7 @@ such that x = sum([toInt(or([i_ExplicitVarSizeWithDummy[q6] = y | q6 : int(1..2), i_ExplicitVarSizeWithDummy[q6] != 10])) | i_ExplicitVarSizeWithDummy : matrix indexed by [int(1..2)] of int(7..10), - [i_ExplicitVarSizeWithDummy[1]; int(1)] i_ExplicitVarSizeWithDummy[2] = 10, 1 <= sum([toInt(i_ExplicitVarSizeWithDummy[q3] != 10) | q3 : int(1..2)]), sum([toInt(i_ExplicitVarSizeWithDummy[q3] != 10) | q3 : int(1..2)]) <= 2]) diff --git a/tests/exhaustive/basic/comprehension_04_2/expected/model-solution000001.solution b/tests/exhaustive/basic/comprehension_04_2/expected/model-solution000001.solution new file mode 100644 index 0000000000..440e39fbc0 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_04_2/expected/model-solution000001.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting x be 6 +letting y be 7 +letting z be false diff --git a/tests/exhaustive/basic/comprehension_04_2/expected/model-solution000002.solution b/tests/exhaustive/basic/comprehension_04_2/expected/model-solution000002.solution new file mode 100644 index 0000000000..725a23fd95 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_04_2/expected/model-solution000002.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting x be 6 +letting y be 7 +letting z be true diff --git a/tests/exhaustive/basic/comprehension_04_2/expected/model-solution000003.solution b/tests/exhaustive/basic/comprehension_04_2/expected/model-solution000003.solution new file mode 100644 index 0000000000..d50b52fc2a --- /dev/null +++ b/tests/exhaustive/basic/comprehension_04_2/expected/model-solution000003.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting x be 6 +letting y be 8 +letting z be false diff --git a/tests/exhaustive/basic/comprehension_04_2/expected/model-solution000004.solution b/tests/exhaustive/basic/comprehension_04_2/expected/model-solution000004.solution new file mode 100644 index 0000000000..3b8775718d --- /dev/null +++ b/tests/exhaustive/basic/comprehension_04_2/expected/model-solution000004.solution @@ -0,0 +1,5 @@ +language Essence 1.3 + +letting x be 6 +letting y be 8 +letting z be true diff --git a/tests/exhaustive/basic/comprehension_04_2/expected/model.eprime b/tests/exhaustive/basic/comprehension_04_2/expected/model.eprime new file mode 100644 index 0000000000..0463a7c0be --- /dev/null +++ b/tests/exhaustive/basic/comprehension_04_2/expected/model.eprime @@ -0,0 +1,26 @@ +language ESSENCE' 1.0 + +find x: int(0..1000) +find y: int(7, 8) +find z: bool +branching on [x, y, z] +such that + x = + sum([toInt(or([i_ExplicitVarSizeWithMarker_Values_1[q5] = y /\ i_ExplicitVarSizeWithMarker_Values_2[q5] = z + | q5 : int(1..2), q5 <= i_ExplicitVarSizeWithMarker_Marker])) + | i_ExplicitVarSizeWithMarker_Marker : int(0..2), + i_ExplicitVarSizeWithMarker_Values_1 : matrix indexed by [int(1..2)] of int(7..9), + i_ExplicitVarSizeWithMarker_Values_2 : matrix indexed by [int(1..2)] of bool, + 2 <= i_ExplicitVarSizeWithMarker_Marker -> + flatten([[i_ExplicitVarSizeWithMarker_Values_1[1]; int(1)], + [-toInt(i_ExplicitVarSizeWithMarker_Values_2[1]); int(1)]; + int(1..2)]) + i_ExplicitVarSizeWithMarker_Marker -> + i_ExplicitVarSizeWithMarker_Values_1[q2] = 7 /\ i_ExplicitVarSizeWithMarker_Values_2[q2] = false + | q2 : int(1..2)]), + 1 <= i_ExplicitVarSizeWithMarker_Marker, i_ExplicitVarSizeWithMarker_Marker <= 2]) + diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_1-solution000001.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_1-solution000001.solution new file mode 100644 index 0000000000..159a613983 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {2, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_1-solution000002.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_1-solution000002.solution new file mode 100644 index 0000000000..40f3fd5c8f --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_1-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {2, 3, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_1-solution000003.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_1-solution000003.solution new file mode 100644 index 0000000000..8b4ecbb66d --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_1-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 3} +letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_1-solution000004.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_1-solution000004.solution new file mode 100644 index 0000000000..560dd0f2f7 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_1-solution000004.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 3, 4} +letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_1-solution000005.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_1-solution000005.solution new file mode 100644 index 0000000000..6eeacc9727 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_1-solution000005.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 2, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_1-solution000006.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_1-solution000006.solution new file mode 100644 index 0000000000..5963aac565 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_1-solution000006.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 2, 3} +letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_1-solution000007.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_1-solution000007.solution new file mode 100644 index 0000000000..bd956f44e3 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_1-solution000007.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 2, 3, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_1.eprime b/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_1.eprime new file mode 100644 index 0000000000..dd4a016cc8 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_1.eprime @@ -0,0 +1,25 @@ +language ESSENCE' 1.0 + +find s_Occurrence: matrix indexed by [int(1..4)] of bool +letting let1 be -100 +find x: int(-100..100) +find conjure_aux1: int(-16..3) +branching on [s_Occurrence, x] +such that + and([s_Occurrence[i] /\ s_Occurrence[j] -> min([i + j, i - j, i * j, i / j; int(1..4)]) <= conjure_aux1 + | i : int(1..4), j : int(1..4), i != j, allDiff([i + j, i * j, i / j; int(1..3)]), (i - j) % 2 = 0]), + sum([toInt(s_Occurrence[i] /\ s_Occurrence[j]) + | i : int(1..4), j : int(1..4), i != j, allDiff([i + j, i * j, i / j; int(1..3)]), (i - j) % 2 = 0]) + > 0 + -> + or([s_Occurrence[i] /\ s_Occurrence[j] /\ min([i + j, i - j, i * j, i / j; int(1..4)]) = conjure_aux1 + | i : int(1..4), j : int(1..4), i != j, allDiff([i + j, i * j, i / j; int(1..3)]), (i - j) % 2 = 0]), + sum([toInt(s_Occurrence[i] /\ s_Occurrence[j]) + | i : int(1..4), j : int(1..4), i != j, allDiff([i + j, i * j, i / j; int(1..3)]), (i - j) % 2 = 0]) + = 0 + -> conjure_aux1 = -16, + x = conjure_aux1, + sum([toInt(s_Occurrence[i] /\ s_Occurrence[j]) + | i : int(1..4), j : int(1..4), i != j, allDiff([i + j, i * j, i / j; int(1..3)]), (i - j) % 2 = 0]) + > 0 + diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_2-solution000001.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_2-solution000001.solution new file mode 100644 index 0000000000..bd956f44e3 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 2, 3, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_2-solution000002.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_2-solution000002.solution new file mode 100644 index 0000000000..5963aac565 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_2-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 2, 3} +letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_2-solution000003.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_2-solution000003.solution new file mode 100644 index 0000000000..6eeacc9727 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_2-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 2, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_2-solution000004.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_2-solution000004.solution new file mode 100644 index 0000000000..560dd0f2f7 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_2-solution000004.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 3, 4} +letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_2-solution000005.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_2-solution000005.solution new file mode 100644 index 0000000000..8b4ecbb66d --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_2-solution000005.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 3} +letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_2-solution000006.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_2-solution000006.solution new file mode 100644 index 0000000000..40f3fd5c8f --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_2-solution000006.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {2, 3, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_2-solution000007.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_2-solution000007.solution new file mode 100644 index 0000000000..159a613983 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_2-solution000007.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {2, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_2.eprime b/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_2.eprime new file mode 100644 index 0000000000..e5a61b11a8 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_2.eprime @@ -0,0 +1,33 @@ +language ESSENCE' 1.0 + +find s_Occurrence: matrix indexed by [int(1..4)] of bool +find s_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +letting let1 be -100 +find x: int(-100..100) +find conjure_aux1: int(-16..3) +branching on [s_ExplicitVarSizeWithDummy, s_Occurrence, x] +such that + and([s_Occurrence[i] /\ s_Occurrence[j] -> min([i + j, i - j, i * j, i / j; int(1..4)]) <= conjure_aux1 + | i : int(1..4), j : int(1..4), i != j, allDiff([i + j, i * j, i / j; int(1..3)]), (i - j) % 2 = 0]), + sum([toInt(s_Occurrence[i] /\ s_Occurrence[j]) + | i : int(1..4), j : int(1..4), i != j, allDiff([i + j, i * j, i / j; int(1..3)]), (i - j) % 2 = 0]) + > 0 + -> + or([s_Occurrence[i] /\ s_Occurrence[j] /\ min([i + j, i - j, i * j, i / j; int(1..4)]) = conjure_aux1 + | i : int(1..4), j : int(1..4), i != j, allDiff([i + j, i * j, i / j; int(1..3)]), (i - j) % 2 = 0]), + sum([toInt(s_Occurrence[i] /\ s_Occurrence[j]) + | i : int(1..4), j : int(1..4), i != j, allDiff([i + j, i * j, i / j; int(1..3)]), (i - j) % 2 = 0]) + = 0 + -> conjure_aux1 = -16, + x = conjure_aux1, + sum([toInt(s_Occurrence[i] /\ s_Occurrence[j]) + | i : int(1..4), j : int(1..4), i != j, allDiff([i + j, i * j, i / j; int(1..3)]), (i - j) % 2 = 0]) + > 0, + and([s_ExplicitVarSizeWithDummy[q2] < s_ExplicitVarSizeWithDummy[q2 + 1] \/ s_ExplicitVarSizeWithDummy[q2] = 5 + | q2 : int(1..3)]), + and([s_ExplicitVarSizeWithDummy[q3] = 5 -> s_ExplicitVarSizeWithDummy[q3 + 1] = 5 | q3 : int(1..3)]), + and([s_ExplicitVarSizeWithDummy[q7] != 5 -> s_Occurrence[s_ExplicitVarSizeWithDummy[q7]] | q7 : int(1..4)]), + and([s_Occurrence[q8] -> + or([s_ExplicitVarSizeWithDummy[q10] != 5 /\ s_ExplicitVarSizeWithDummy[q10] = q8 | q10 : int(1..4)]) + | q8 : int(1..4)]) + diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_3-solution000001.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_3-solution000001.solution new file mode 100644 index 0000000000..8b4ecbb66d --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_3-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 3} +letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_3-solution000002.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_3-solution000002.solution new file mode 100644 index 0000000000..159a613983 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_3-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {2, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_3-solution000003.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_3-solution000003.solution new file mode 100644 index 0000000000..5963aac565 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_3-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 2, 3} +letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_3-solution000004.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_3-solution000004.solution new file mode 100644 index 0000000000..6eeacc9727 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_3-solution000004.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 2, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_3-solution000005.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_3-solution000005.solution new file mode 100644 index 0000000000..560dd0f2f7 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_3-solution000005.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 3, 4} +letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_3-solution000006.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_3-solution000006.solution new file mode 100644 index 0000000000..40f3fd5c8f --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_3-solution000006.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {2, 3, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_3-solution000007.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_3-solution000007.solution new file mode 100644 index 0000000000..bd956f44e3 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_3-solution000007.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 2, 3, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_3.eprime b/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_3.eprime new file mode 100644 index 0000000000..dc118fd71c --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_3.eprime @@ -0,0 +1,36 @@ +language ESSENCE' 1.0 + +find s_Occurrence: matrix indexed by [int(1..4)] of bool +find s_ExplicitVarSizeWithMarker_Marker: int(0..4) +find s_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +letting let1 be -100 +find x: int(-100..100) +find conjure_aux1: int(-16..3) +branching on [s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithMarker_Values, s_Occurrence, x] +such that + and([s_Occurrence[i] /\ s_Occurrence[j] -> min([i + j, i - j, i * j, i / j; int(1..4)]) <= conjure_aux1 + | i : int(1..4), j : int(1..4), i != j, allDiff([i + j, i * j, i / j; int(1..3)]), (i - j) % 2 = 0]), + sum([toInt(s_Occurrence[i] /\ s_Occurrence[j]) + | i : int(1..4), j : int(1..4), i != j, allDiff([i + j, i * j, i / j; int(1..3)]), (i - j) % 2 = 0]) + > 0 + -> + or([s_Occurrence[i] /\ s_Occurrence[j] /\ min([i + j, i - j, i * j, i / j; int(1..4)]) = conjure_aux1 + | i : int(1..4), j : int(1..4), i != j, allDiff([i + j, i * j, i / j; int(1..3)]), (i - j) % 2 = 0]), + sum([toInt(s_Occurrence[i] /\ s_Occurrence[j]) + | i : int(1..4), j : int(1..4), i != j, allDiff([i + j, i * j, i / j; int(1..3)]), (i - j) % 2 = 0]) + = 0 + -> conjure_aux1 = -16, + x = conjure_aux1, + sum([toInt(s_Occurrence[i] /\ s_Occurrence[j]) + | i : int(1..4), j : int(1..4), i != j, allDiff([i + j, i * j, i / j; int(1..3)]), (i - j) % 2 = 0]) + > 0, + and([q2 + 1 <= s_ExplicitVarSizeWithMarker_Marker -> + s_ExplicitVarSizeWithMarker_Values[q2] < s_ExplicitVarSizeWithMarker_Values[q2 + 1] + | q2 : int(1..3)]), + and([q3 > s_ExplicitVarSizeWithMarker_Marker -> s_ExplicitVarSizeWithMarker_Values[q3] = 1 | q3 : int(1..4)]), + and([q6 <= s_ExplicitVarSizeWithMarker_Marker -> s_Occurrence[s_ExplicitVarSizeWithMarker_Values[q6]] + | q6 : int(1..4)]), + and([s_Occurrence[q7] -> + or([q9 <= s_ExplicitVarSizeWithMarker_Marker /\ s_ExplicitVarSizeWithMarker_Values[q9] = q7 | q9 : int(1..4)]) + | q7 : int(1..4)]) + diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_4-solution000001.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_4-solution000001.solution new file mode 100644 index 0000000000..8b4ecbb66d --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_4-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 3} +letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_4-solution000002.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_4-solution000002.solution new file mode 100644 index 0000000000..159a613983 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_4-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {2, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_4-solution000003.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_4-solution000003.solution new file mode 100644 index 0000000000..5963aac565 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_4-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 2, 3} +letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_4-solution000004.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_4-solution000004.solution new file mode 100644 index 0000000000..6eeacc9727 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_4-solution000004.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 2, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_4-solution000005.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_4-solution000005.solution new file mode 100644 index 0000000000..560dd0f2f7 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_4-solution000005.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 3, 4} +letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_4-solution000006.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_4-solution000006.solution new file mode 100644 index 0000000000..40f3fd5c8f --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_4-solution000006.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {2, 3, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_4-solution000007.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_4-solution000007.solution new file mode 100644 index 0000000000..bd956f44e3 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_4-solution000007.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 2, 3, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_4.eprime b/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_4.eprime new file mode 100644 index 0000000000..6c66694bc5 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_1_1_4.eprime @@ -0,0 +1,36 @@ +language ESSENCE' 1.0 + +find s_Occurrence: matrix indexed by [int(1..4)] of bool +find s_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find s_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +letting let1 be -100 +find x: int(-100..100) +find conjure_aux1: int(-16..3) +branching on [s_ExplicitVarSizeWithFlags_Flags, s_ExplicitVarSizeWithFlags_Values, s_Occurrence, x] +such that + and([s_Occurrence[i] /\ s_Occurrence[j] -> min([i + j, i - j, i * j, i / j; int(1..4)]) <= conjure_aux1 + | i : int(1..4), j : int(1..4), i != j, allDiff([i + j, i * j, i / j; int(1..3)]), (i - j) % 2 = 0]), + sum([toInt(s_Occurrence[i] /\ s_Occurrence[j]) + | i : int(1..4), j : int(1..4), i != j, allDiff([i + j, i * j, i / j; int(1..3)]), (i - j) % 2 = 0]) + > 0 + -> + or([s_Occurrence[i] /\ s_Occurrence[j] /\ min([i + j, i - j, i * j, i / j; int(1..4)]) = conjure_aux1 + | i : int(1..4), j : int(1..4), i != j, allDiff([i + j, i * j, i / j; int(1..3)]), (i - j) % 2 = 0]), + sum([toInt(s_Occurrence[i] /\ s_Occurrence[j]) + | i : int(1..4), j : int(1..4), i != j, allDiff([i + j, i * j, i / j; int(1..3)]), (i - j) % 2 = 0]) + = 0 + -> conjure_aux1 = -16, + x = conjure_aux1, + sum([toInt(s_Occurrence[i] /\ s_Occurrence[j]) + | i : int(1..4), j : int(1..4), i != j, allDiff([i + j, i * j, i / j; int(1..3)]), (i - j) % 2 = 0]) + > 0, + and([s_ExplicitVarSizeWithFlags_Flags[q2 + 1] -> + s_ExplicitVarSizeWithFlags_Values[q2] < s_ExplicitVarSizeWithFlags_Values[q2 + 1] + | q2 : int(1..3)]), + and([s_ExplicitVarSizeWithFlags_Flags[q3] = false -> s_ExplicitVarSizeWithFlags_Values[q3] = 1 | q3 : int(1..4)]), + and([s_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> s_ExplicitVarSizeWithFlags_Flags[q4] | q4 : int(1..3)]), + and([s_ExplicitVarSizeWithFlags_Flags[q8] -> s_Occurrence[s_ExplicitVarSizeWithFlags_Values[q8]] | q8 : int(1..4)]), + and([s_Occurrence[q9] -> + or([s_ExplicitVarSizeWithFlags_Flags[q11] /\ s_ExplicitVarSizeWithFlags_Values[q11] = q9 | q11 : int(1..4)]) + | q9 : int(1..4)]) + diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_2_1-solution000001.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_2_1-solution000001.solution new file mode 100644 index 0000000000..bd956f44e3 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_1_2_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 2, 3, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_2_1-solution000002.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_2_1-solution000002.solution new file mode 100644 index 0000000000..5963aac565 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_1_2_1-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 2, 3} +letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_2_1-solution000003.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_2_1-solution000003.solution new file mode 100644 index 0000000000..6eeacc9727 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_1_2_1-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 2, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_2_1-solution000004.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_2_1-solution000004.solution new file mode 100644 index 0000000000..560dd0f2f7 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_1_2_1-solution000004.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 3, 4} +letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_2_1-solution000005.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_2_1-solution000005.solution new file mode 100644 index 0000000000..8b4ecbb66d --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_1_2_1-solution000005.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 3} +letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_2_1-solution000006.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_2_1-solution000006.solution new file mode 100644 index 0000000000..40f3fd5c8f --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_1_2_1-solution000006.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {2, 3, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_2_1-solution000007.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_2_1-solution000007.solution new file mode 100644 index 0000000000..159a613983 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_1_2_1-solution000007.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {2, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_2_1.eprime b/tests/exhaustive/basic/comprehension_letting/expected/model_1_2_1.eprime new file mode 100644 index 0000000000..8697c1dbd6 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_1_2_1.eprime @@ -0,0 +1,68 @@ +language ESSENCE' 1.0 + +find s_Occurrence: matrix indexed by [int(1..4)] of bool +find s_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +letting let1 be -100 +find x: int(-100..100) +find conjure_aux1: int(-20..3) +branching on [s_ExplicitVarSizeWithDummy, s_Occurrence, x] +such that + and([and([s_Occurrence[i], s_ExplicitVarSizeWithDummy[q11] != 5, i != s_ExplicitVarSizeWithDummy[q11], + allDiff([i + s_ExplicitVarSizeWithDummy[q11], i * s_ExplicitVarSizeWithDummy[q11], + i / s_ExplicitVarSizeWithDummy[q11]; + int(1..3)]), + (i - s_ExplicitVarSizeWithDummy[q11]) % 2 = 0; + int(1..5)]) + -> + min([i + s_ExplicitVarSizeWithDummy[q11], i - s_ExplicitVarSizeWithDummy[q11], + i * s_ExplicitVarSizeWithDummy[q11], i / s_ExplicitVarSizeWithDummy[q11]; + int(1..4)]) + <= conjure_aux1 + | i : int(1..4), q11 : int(1..4)]), + sum([toInt(and([s_Occurrence[i], s_ExplicitVarSizeWithDummy[q11] != 5, i != s_ExplicitVarSizeWithDummy[q11], + allDiff([i + s_ExplicitVarSizeWithDummy[q11], i * s_ExplicitVarSizeWithDummy[q11], + i / s_ExplicitVarSizeWithDummy[q11]; + int(1..3)]), + (i - s_ExplicitVarSizeWithDummy[q11]) % 2 = 0; + int(1..5)])) + | i : int(1..4), q11 : int(1..4)]) + > 0 + -> + or([and([s_Occurrence[i], s_ExplicitVarSizeWithDummy[q11] != 5, i != s_ExplicitVarSizeWithDummy[q11], + allDiff([i + s_ExplicitVarSizeWithDummy[q11], i * s_ExplicitVarSizeWithDummy[q11], + i / s_ExplicitVarSizeWithDummy[q11]; + int(1..3)]), + (i - s_ExplicitVarSizeWithDummy[q11]) % 2 = 0; + int(1..5)]) + /\ + min([i + s_ExplicitVarSizeWithDummy[q11], i - s_ExplicitVarSizeWithDummy[q11], + i * s_ExplicitVarSizeWithDummy[q11], i / s_ExplicitVarSizeWithDummy[q11]; + int(1..4)]) + = conjure_aux1 + | i : int(1..4), q11 : int(1..4)]), + sum([toInt(and([s_Occurrence[i], s_ExplicitVarSizeWithDummy[q11] != 5, i != s_ExplicitVarSizeWithDummy[q11], + allDiff([i + s_ExplicitVarSizeWithDummy[q11], i * s_ExplicitVarSizeWithDummy[q11], + i / s_ExplicitVarSizeWithDummy[q11]; + int(1..3)]), + (i - s_ExplicitVarSizeWithDummy[q11]) % 2 = 0; + int(1..5)])) + | i : int(1..4), q11 : int(1..4)]) + = 0 + -> conjure_aux1 = -20, + x = conjure_aux1, + sum([toInt(and([s_Occurrence[i], s_ExplicitVarSizeWithDummy[q11] != 5, i != s_ExplicitVarSizeWithDummy[q11], + allDiff([i + s_ExplicitVarSizeWithDummy[q11], i * s_ExplicitVarSizeWithDummy[q11], + i / s_ExplicitVarSizeWithDummy[q11]; + int(1..3)]), + (i - s_ExplicitVarSizeWithDummy[q11]) % 2 = 0; + int(1..5)])) + | i : int(1..4), q11 : int(1..4)]) + > 0, + and([s_ExplicitVarSizeWithDummy[q2] < s_ExplicitVarSizeWithDummy[q2 + 1] \/ s_ExplicitVarSizeWithDummy[q2] = 5 + | q2 : int(1..3)]), + and([s_ExplicitVarSizeWithDummy[q3] = 5 -> s_ExplicitVarSizeWithDummy[q3 + 1] = 5 | q3 : int(1..3)]), + and([s_ExplicitVarSizeWithDummy[q7] != 5 -> s_Occurrence[s_ExplicitVarSizeWithDummy[q7]] | q7 : int(1..4)]), + and([s_Occurrence[q8] -> + or([s_ExplicitVarSizeWithDummy[q10] != 5 /\ s_ExplicitVarSizeWithDummy[q10] = q8 | q10 : int(1..4)]) + | q8 : int(1..4)]) + diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_2_3-solution000001.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_2_3-solution000001.solution new file mode 100644 index 0000000000..8b4ecbb66d --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_1_2_3-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 3} +letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_2_3-solution000002.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_2_3-solution000002.solution new file mode 100644 index 0000000000..159a613983 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_1_2_3-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {2, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_2_3-solution000003.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_2_3-solution000003.solution new file mode 100644 index 0000000000..5963aac565 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_1_2_3-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 2, 3} +letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_2_3-solution000004.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_2_3-solution000004.solution new file mode 100644 index 0000000000..6eeacc9727 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_1_2_3-solution000004.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 2, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_2_3-solution000005.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_2_3-solution000005.solution new file mode 100644 index 0000000000..560dd0f2f7 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_1_2_3-solution000005.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 3, 4} +letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_2_3-solution000006.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_2_3-solution000006.solution new file mode 100644 index 0000000000..40f3fd5c8f --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_1_2_3-solution000006.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {2, 3, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_2_3-solution000007.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_2_3-solution000007.solution new file mode 100644 index 0000000000..bd956f44e3 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_1_2_3-solution000007.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 2, 3, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_2_3.eprime b/tests/exhaustive/basic/comprehension_letting/expected/model_1_2_3.eprime new file mode 100644 index 0000000000..a5ab41cb34 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_1_2_3.eprime @@ -0,0 +1,92 @@ +language ESSENCE' 1.0 + +find s_Occurrence: matrix indexed by [int(1..4)] of bool +find s_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +find s_ExplicitVarSizeWithMarker_Marker: int(0..4) +find s_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +letting let1 be -100 +find x: int(-100..100) +find conjure_aux1: int(-20..3) +branching on + [s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithMarker_Values, s_Occurrence, s_ExplicitVarSizeWithDummy, + x] +such that + and([and([s_Occurrence[i], s_ExplicitVarSizeWithDummy[q27] != 5, i != s_ExplicitVarSizeWithDummy[q27], + allDiff([i + s_ExplicitVarSizeWithDummy[q27], i * s_ExplicitVarSizeWithDummy[q27], + i / s_ExplicitVarSizeWithDummy[q27]; + int(1..3)]), + (i - s_ExplicitVarSizeWithDummy[q27]) % 2 = 0; + int(1..5)]) + -> + min([i + s_ExplicitVarSizeWithDummy[q27], i - s_ExplicitVarSizeWithDummy[q27], + i * s_ExplicitVarSizeWithDummy[q27], i / s_ExplicitVarSizeWithDummy[q27]; + int(1..4)]) + <= conjure_aux1 + | i : int(1..4), q27 : int(1..4)]), + sum([toInt(and([s_Occurrence[i], s_ExplicitVarSizeWithDummy[q27] != 5, i != s_ExplicitVarSizeWithDummy[q27], + allDiff([i + s_ExplicitVarSizeWithDummy[q27], i * s_ExplicitVarSizeWithDummy[q27], + i / s_ExplicitVarSizeWithDummy[q27]; + int(1..3)]), + (i - s_ExplicitVarSizeWithDummy[q27]) % 2 = 0; + int(1..5)])) + | i : int(1..4), q27 : int(1..4)]) + > 0 + -> + or([and([s_Occurrence[i], s_ExplicitVarSizeWithDummy[q27] != 5, i != s_ExplicitVarSizeWithDummy[q27], + allDiff([i + s_ExplicitVarSizeWithDummy[q27], i * s_ExplicitVarSizeWithDummy[q27], + i / s_ExplicitVarSizeWithDummy[q27]; + int(1..3)]), + (i - s_ExplicitVarSizeWithDummy[q27]) % 2 = 0; + int(1..5)]) + /\ + min([i + s_ExplicitVarSizeWithDummy[q27], i - s_ExplicitVarSizeWithDummy[q27], + i * s_ExplicitVarSizeWithDummy[q27], i / s_ExplicitVarSizeWithDummy[q27]; + int(1..4)]) + = conjure_aux1 + | i : int(1..4), q27 : int(1..4)]), + sum([toInt(and([s_Occurrence[i], s_ExplicitVarSizeWithDummy[q27] != 5, i != s_ExplicitVarSizeWithDummy[q27], + allDiff([i + s_ExplicitVarSizeWithDummy[q27], i * s_ExplicitVarSizeWithDummy[q27], + i / s_ExplicitVarSizeWithDummy[q27]; + int(1..3)]), + (i - s_ExplicitVarSizeWithDummy[q27]) % 2 = 0; + int(1..5)])) + | i : int(1..4), q27 : int(1..4)]) + = 0 + -> conjure_aux1 = -20, + x = conjure_aux1, + sum([toInt(and([s_Occurrence[i], s_ExplicitVarSizeWithDummy[q27] != 5, i != s_ExplicitVarSizeWithDummy[q27], + allDiff([i + s_ExplicitVarSizeWithDummy[q27], i * s_ExplicitVarSizeWithDummy[q27], + i / s_ExplicitVarSizeWithDummy[q27]; + int(1..3)]), + (i - s_ExplicitVarSizeWithDummy[q27]) % 2 = 0; + int(1..5)])) + | i : int(1..4), q27 : int(1..4)]) + > 0, + and([s_ExplicitVarSizeWithDummy[q2] < s_ExplicitVarSizeWithDummy[q2 + 1] \/ s_ExplicitVarSizeWithDummy[q2] = 5 + | q2 : int(1..3)]), + and([s_ExplicitVarSizeWithDummy[q3] = 5 -> s_ExplicitVarSizeWithDummy[q3 + 1] = 5 | q3 : int(1..3)]), + and([s_ExplicitVarSizeWithDummy[q7] != 5 -> s_Occurrence[s_ExplicitVarSizeWithDummy[q7]] | q7 : int(1..4)]), + and([s_Occurrence[q8] -> + or([s_ExplicitVarSizeWithDummy[q10] != 5 /\ s_ExplicitVarSizeWithDummy[q10] = q8 | q10 : int(1..4)]) + | q8 : int(1..4)]), + and([q11 + 1 <= s_ExplicitVarSizeWithMarker_Marker -> + s_ExplicitVarSizeWithMarker_Values[q11] < s_ExplicitVarSizeWithMarker_Values[q11 + 1] + | q11 : int(1..3)]), + and([q12 > s_ExplicitVarSizeWithMarker_Marker -> s_ExplicitVarSizeWithMarker_Values[q12] = 1 | q12 : int(1..4)]), + and([q15 <= s_ExplicitVarSizeWithMarker_Marker -> s_Occurrence[s_ExplicitVarSizeWithMarker_Values[q15]] + | q15 : int(1..4)]), + and([s_Occurrence[q16] -> + or([q18 <= s_ExplicitVarSizeWithMarker_Marker /\ s_ExplicitVarSizeWithMarker_Values[q18] = q16 + | q18 : int(1..4)]) + | q16 : int(1..4)]), + and([q20 <= s_ExplicitVarSizeWithMarker_Marker -> + or([s_ExplicitVarSizeWithDummy[q22] != 5 /\ + s_ExplicitVarSizeWithDummy[q22] = s_ExplicitVarSizeWithMarker_Values[q20] + | q22 : int(1..4)]) + | q20 : int(1..4)]), + and([s_ExplicitVarSizeWithDummy[q24] != 5 -> + or([q26 <= s_ExplicitVarSizeWithMarker_Marker /\ + s_ExplicitVarSizeWithMarker_Values[q26] = s_ExplicitVarSizeWithDummy[q24] + | q26 : int(1..4)]) + | q24 : int(1..4)]) + diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_2_4-solution000001.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_2_4-solution000001.solution new file mode 100644 index 0000000000..8b4ecbb66d --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_1_2_4-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 3} +letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_2_4-solution000002.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_2_4-solution000002.solution new file mode 100644 index 0000000000..159a613983 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_1_2_4-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {2, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_2_4-solution000003.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_2_4-solution000003.solution new file mode 100644 index 0000000000..5963aac565 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_1_2_4-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 2, 3} +letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_2_4-solution000004.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_2_4-solution000004.solution new file mode 100644 index 0000000000..6eeacc9727 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_1_2_4-solution000004.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 2, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_2_4-solution000005.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_2_4-solution000005.solution new file mode 100644 index 0000000000..560dd0f2f7 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_1_2_4-solution000005.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 3, 4} +letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_2_4-solution000006.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_2_4-solution000006.solution new file mode 100644 index 0000000000..40f3fd5c8f --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_1_2_4-solution000006.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {2, 3, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_2_4-solution000007.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_2_4-solution000007.solution new file mode 100644 index 0000000000..bd956f44e3 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_1_2_4-solution000007.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 2, 3, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_2_4.eprime b/tests/exhaustive/basic/comprehension_letting/expected/model_1_2_4.eprime new file mode 100644 index 0000000000..264f061fe8 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_1_2_4.eprime @@ -0,0 +1,92 @@ +language ESSENCE' 1.0 + +find s_Occurrence: matrix indexed by [int(1..4)] of bool +find s_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +find s_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find s_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +letting let1 be -100 +find x: int(-100..100) +find conjure_aux1: int(-20..3) +branching on + [s_ExplicitVarSizeWithFlags_Flags, s_ExplicitVarSizeWithFlags_Values, s_Occurrence, s_ExplicitVarSizeWithDummy, x] +such that + and([and([s_Occurrence[i], s_ExplicitVarSizeWithDummy[q29] != 5, i != s_ExplicitVarSizeWithDummy[q29], + allDiff([i + s_ExplicitVarSizeWithDummy[q29], i * s_ExplicitVarSizeWithDummy[q29], + i / s_ExplicitVarSizeWithDummy[q29]; + int(1..3)]), + (i - s_ExplicitVarSizeWithDummy[q29]) % 2 = 0; + int(1..5)]) + -> + min([i + s_ExplicitVarSizeWithDummy[q29], i - s_ExplicitVarSizeWithDummy[q29], + i * s_ExplicitVarSizeWithDummy[q29], i / s_ExplicitVarSizeWithDummy[q29]; + int(1..4)]) + <= conjure_aux1 + | i : int(1..4), q29 : int(1..4)]), + sum([toInt(and([s_Occurrence[i], s_ExplicitVarSizeWithDummy[q29] != 5, i != s_ExplicitVarSizeWithDummy[q29], + allDiff([i + s_ExplicitVarSizeWithDummy[q29], i * s_ExplicitVarSizeWithDummy[q29], + i / s_ExplicitVarSizeWithDummy[q29]; + int(1..3)]), + (i - s_ExplicitVarSizeWithDummy[q29]) % 2 = 0; + int(1..5)])) + | i : int(1..4), q29 : int(1..4)]) + > 0 + -> + or([and([s_Occurrence[i], s_ExplicitVarSizeWithDummy[q29] != 5, i != s_ExplicitVarSizeWithDummy[q29], + allDiff([i + s_ExplicitVarSizeWithDummy[q29], i * s_ExplicitVarSizeWithDummy[q29], + i / s_ExplicitVarSizeWithDummy[q29]; + int(1..3)]), + (i - s_ExplicitVarSizeWithDummy[q29]) % 2 = 0; + int(1..5)]) + /\ + min([i + s_ExplicitVarSizeWithDummy[q29], i - s_ExplicitVarSizeWithDummy[q29], + i * s_ExplicitVarSizeWithDummy[q29], i / s_ExplicitVarSizeWithDummy[q29]; + int(1..4)]) + = conjure_aux1 + | i : int(1..4), q29 : int(1..4)]), + sum([toInt(and([s_Occurrence[i], s_ExplicitVarSizeWithDummy[q29] != 5, i != s_ExplicitVarSizeWithDummy[q29], + allDiff([i + s_ExplicitVarSizeWithDummy[q29], i * s_ExplicitVarSizeWithDummy[q29], + i / s_ExplicitVarSizeWithDummy[q29]; + int(1..3)]), + (i - s_ExplicitVarSizeWithDummy[q29]) % 2 = 0; + int(1..5)])) + | i : int(1..4), q29 : int(1..4)]) + = 0 + -> conjure_aux1 = -20, + x = conjure_aux1, + sum([toInt(and([s_Occurrence[i], s_ExplicitVarSizeWithDummy[q29] != 5, i != s_ExplicitVarSizeWithDummy[q29], + allDiff([i + s_ExplicitVarSizeWithDummy[q29], i * s_ExplicitVarSizeWithDummy[q29], + i / s_ExplicitVarSizeWithDummy[q29]; + int(1..3)]), + (i - s_ExplicitVarSizeWithDummy[q29]) % 2 = 0; + int(1..5)])) + | i : int(1..4), q29 : int(1..4)]) + > 0, + and([s_ExplicitVarSizeWithDummy[q2] < s_ExplicitVarSizeWithDummy[q2 + 1] \/ s_ExplicitVarSizeWithDummy[q2] = 5 + | q2 : int(1..3)]), + and([s_ExplicitVarSizeWithDummy[q3] = 5 -> s_ExplicitVarSizeWithDummy[q3 + 1] = 5 | q3 : int(1..3)]), + and([s_ExplicitVarSizeWithDummy[q7] != 5 -> s_Occurrence[s_ExplicitVarSizeWithDummy[q7]] | q7 : int(1..4)]), + and([s_Occurrence[q8] -> + or([s_ExplicitVarSizeWithDummy[q10] != 5 /\ s_ExplicitVarSizeWithDummy[q10] = q8 | q10 : int(1..4)]) + | q8 : int(1..4)]), + and([s_ExplicitVarSizeWithFlags_Flags[q11 + 1] -> + s_ExplicitVarSizeWithFlags_Values[q11] < s_ExplicitVarSizeWithFlags_Values[q11 + 1] + | q11 : int(1..3)]), + and([s_ExplicitVarSizeWithFlags_Flags[q12] = false -> s_ExplicitVarSizeWithFlags_Values[q12] = 1 + | q12 : int(1..4)]), + and([s_ExplicitVarSizeWithFlags_Flags[q13 + 1] -> s_ExplicitVarSizeWithFlags_Flags[q13] | q13 : int(1..3)]), + and([s_ExplicitVarSizeWithFlags_Flags[q17] -> s_Occurrence[s_ExplicitVarSizeWithFlags_Values[q17]] + | q17 : int(1..4)]), + and([s_Occurrence[q18] -> + or([s_ExplicitVarSizeWithFlags_Flags[q20] /\ s_ExplicitVarSizeWithFlags_Values[q20] = q18 | q20 : int(1..4)]) + | q18 : int(1..4)]), + and([s_ExplicitVarSizeWithFlags_Flags[q22] -> + or([s_ExplicitVarSizeWithDummy[q24] != 5 /\ + s_ExplicitVarSizeWithDummy[q24] = s_ExplicitVarSizeWithFlags_Values[q22] + | q24 : int(1..4)]) + | q22 : int(1..4)]), + and([s_ExplicitVarSizeWithDummy[q26] != 5 -> + or([s_ExplicitVarSizeWithFlags_Flags[q28] /\ + s_ExplicitVarSizeWithFlags_Values[q28] = s_ExplicitVarSizeWithDummy[q26] + | q28 : int(1..4)]) + | q26 : int(1..4)]) + diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_3_1-solution000001.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_3_1-solution000001.solution new file mode 100644 index 0000000000..8b4ecbb66d --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_1_3_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 3} +letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_3_1-solution000002.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_3_1-solution000002.solution new file mode 100644 index 0000000000..159a613983 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_1_3_1-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {2, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_3_1-solution000003.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_3_1-solution000003.solution new file mode 100644 index 0000000000..5963aac565 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_1_3_1-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 2, 3} +letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_3_1-solution000004.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_3_1-solution000004.solution new file mode 100644 index 0000000000..6eeacc9727 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_1_3_1-solution000004.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 2, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_3_1-solution000005.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_3_1-solution000005.solution new file mode 100644 index 0000000000..560dd0f2f7 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_1_3_1-solution000005.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 3, 4} +letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_3_1-solution000006.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_3_1-solution000006.solution new file mode 100644 index 0000000000..40f3fd5c8f --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_1_3_1-solution000006.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {2, 3, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_3_1-solution000007.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_3_1-solution000007.solution new file mode 100644 index 0000000000..bd956f44e3 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_1_3_1-solution000007.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 2, 3, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_3_1.eprime b/tests/exhaustive/basic/comprehension_letting/expected/model_1_3_1.eprime new file mode 100644 index 0000000000..52358293ff --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_1_3_1.eprime @@ -0,0 +1,74 @@ +language ESSENCE' 1.0 + +find s_Occurrence: matrix indexed by [int(1..4)] of bool +find s_ExplicitVarSizeWithMarker_Marker: int(0..4) +find s_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +letting let1 be -100 +find x: int(-100..100) +find conjure_aux1: int(-16..3) +branching on [s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithMarker_Values, s_Occurrence, x] +such that + and([and([s_Occurrence[i], q10 <= s_ExplicitVarSizeWithMarker_Marker, i != s_ExplicitVarSizeWithMarker_Values[q10], + allDiff([i + s_ExplicitVarSizeWithMarker_Values[q10], i * s_ExplicitVarSizeWithMarker_Values[q10], + i / s_ExplicitVarSizeWithMarker_Values[q10]; + int(1..3)]), + (i - s_ExplicitVarSizeWithMarker_Values[q10]) % 2 = 0; + int(1..5)]) + -> + min([i + s_ExplicitVarSizeWithMarker_Values[q10], i - s_ExplicitVarSizeWithMarker_Values[q10], + i * s_ExplicitVarSizeWithMarker_Values[q10], i / s_ExplicitVarSizeWithMarker_Values[q10]; + int(1..4)]) + <= conjure_aux1 + | i : int(1..4), q10 : int(1..4)]), + sum([toInt(and([s_Occurrence[i], q10 <= s_ExplicitVarSizeWithMarker_Marker, + i != s_ExplicitVarSizeWithMarker_Values[q10], + allDiff([i + s_ExplicitVarSizeWithMarker_Values[q10], i * s_ExplicitVarSizeWithMarker_Values[q10], + i / s_ExplicitVarSizeWithMarker_Values[q10]; + int(1..3)]), + (i - s_ExplicitVarSizeWithMarker_Values[q10]) % 2 = 0; + int(1..5)])) + | i : int(1..4), q10 : int(1..4)]) + > 0 + -> + or([and([s_Occurrence[i], q10 <= s_ExplicitVarSizeWithMarker_Marker, i != s_ExplicitVarSizeWithMarker_Values[q10], + allDiff([i + s_ExplicitVarSizeWithMarker_Values[q10], i * s_ExplicitVarSizeWithMarker_Values[q10], + i / s_ExplicitVarSizeWithMarker_Values[q10]; + int(1..3)]), + (i - s_ExplicitVarSizeWithMarker_Values[q10]) % 2 = 0; + int(1..5)]) + /\ + min([i + s_ExplicitVarSizeWithMarker_Values[q10], i - s_ExplicitVarSizeWithMarker_Values[q10], + i * s_ExplicitVarSizeWithMarker_Values[q10], i / s_ExplicitVarSizeWithMarker_Values[q10]; + int(1..4)]) + = conjure_aux1 + | i : int(1..4), q10 : int(1..4)]), + sum([toInt(and([s_Occurrence[i], q10 <= s_ExplicitVarSizeWithMarker_Marker, + i != s_ExplicitVarSizeWithMarker_Values[q10], + allDiff([i + s_ExplicitVarSizeWithMarker_Values[q10], i * s_ExplicitVarSizeWithMarker_Values[q10], + i / s_ExplicitVarSizeWithMarker_Values[q10]; + int(1..3)]), + (i - s_ExplicitVarSizeWithMarker_Values[q10]) % 2 = 0; + int(1..5)])) + | i : int(1..4), q10 : int(1..4)]) + = 0 + -> conjure_aux1 = -16, + x = conjure_aux1, + sum([toInt(and([s_Occurrence[i], q10 <= s_ExplicitVarSizeWithMarker_Marker, + i != s_ExplicitVarSizeWithMarker_Values[q10], + allDiff([i + s_ExplicitVarSizeWithMarker_Values[q10], i * s_ExplicitVarSizeWithMarker_Values[q10], + i / s_ExplicitVarSizeWithMarker_Values[q10]; + int(1..3)]), + (i - s_ExplicitVarSizeWithMarker_Values[q10]) % 2 = 0; + int(1..5)])) + | i : int(1..4), q10 : int(1..4)]) + > 0, + and([q2 + 1 <= s_ExplicitVarSizeWithMarker_Marker -> + s_ExplicitVarSizeWithMarker_Values[q2] < s_ExplicitVarSizeWithMarker_Values[q2 + 1] + | q2 : int(1..3)]), + and([q3 > s_ExplicitVarSizeWithMarker_Marker -> s_ExplicitVarSizeWithMarker_Values[q3] = 1 | q3 : int(1..4)]), + and([q6 <= s_ExplicitVarSizeWithMarker_Marker -> s_Occurrence[s_ExplicitVarSizeWithMarker_Values[q6]] + | q6 : int(1..4)]), + and([s_Occurrence[q7] -> + or([q9 <= s_ExplicitVarSizeWithMarker_Marker /\ s_ExplicitVarSizeWithMarker_Values[q9] = q7 | q9 : int(1..4)]) + | q7 : int(1..4)]) + diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_3_2-solution000001.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_3_2-solution000001.solution new file mode 100644 index 0000000000..bd956f44e3 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_1_3_2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 2, 3, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_3_2-solution000002.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_3_2-solution000002.solution new file mode 100644 index 0000000000..5963aac565 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_1_3_2-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 2, 3} +letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_3_2-solution000003.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_3_2-solution000003.solution new file mode 100644 index 0000000000..6eeacc9727 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_1_3_2-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 2, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_3_2-solution000004.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_3_2-solution000004.solution new file mode 100644 index 0000000000..560dd0f2f7 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_1_3_2-solution000004.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 3, 4} +letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_3_2-solution000005.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_3_2-solution000005.solution new file mode 100644 index 0000000000..8b4ecbb66d --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_1_3_2-solution000005.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 3} +letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_3_2-solution000006.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_3_2-solution000006.solution new file mode 100644 index 0000000000..40f3fd5c8f --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_1_3_2-solution000006.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {2, 3, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_3_2-solution000007.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_3_2-solution000007.solution new file mode 100644 index 0000000000..159a613983 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_1_3_2-solution000007.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {2, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_3_2.eprime b/tests/exhaustive/basic/comprehension_letting/expected/model_1_3_2.eprime new file mode 100644 index 0000000000..8aedcdcc81 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_1_3_2.eprime @@ -0,0 +1,94 @@ +language ESSENCE' 1.0 + +find s_Occurrence: matrix indexed by [int(1..4)] of bool +find s_ExplicitVarSizeWithMarker_Marker: int(0..4) +find s_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +find s_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +letting let1 be -100 +find x: int(-100..100) +find conjure_aux1: int(-16..3) +branching on + [s_ExplicitVarSizeWithDummy, s_Occurrence, s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithMarker_Values, + x] +such that + and([and([s_Occurrence[i], q27 <= s_ExplicitVarSizeWithMarker_Marker, i != s_ExplicitVarSizeWithMarker_Values[q27], + allDiff([i + s_ExplicitVarSizeWithMarker_Values[q27], i * s_ExplicitVarSizeWithMarker_Values[q27], + i / s_ExplicitVarSizeWithMarker_Values[q27]; + int(1..3)]), + (i - s_ExplicitVarSizeWithMarker_Values[q27]) % 2 = 0; + int(1..5)]) + -> + min([i + s_ExplicitVarSizeWithMarker_Values[q27], i - s_ExplicitVarSizeWithMarker_Values[q27], + i * s_ExplicitVarSizeWithMarker_Values[q27], i / s_ExplicitVarSizeWithMarker_Values[q27]; + int(1..4)]) + <= conjure_aux1 + | i : int(1..4), q27 : int(1..4)]), + sum([toInt(and([s_Occurrence[i], q27 <= s_ExplicitVarSizeWithMarker_Marker, + i != s_ExplicitVarSizeWithMarker_Values[q27], + allDiff([i + s_ExplicitVarSizeWithMarker_Values[q27], i * s_ExplicitVarSizeWithMarker_Values[q27], + i / s_ExplicitVarSizeWithMarker_Values[q27]; + int(1..3)]), + (i - s_ExplicitVarSizeWithMarker_Values[q27]) % 2 = 0; + int(1..5)])) + | i : int(1..4), q27 : int(1..4)]) + > 0 + -> + or([and([s_Occurrence[i], q27 <= s_ExplicitVarSizeWithMarker_Marker, i != s_ExplicitVarSizeWithMarker_Values[q27], + allDiff([i + s_ExplicitVarSizeWithMarker_Values[q27], i * s_ExplicitVarSizeWithMarker_Values[q27], + i / s_ExplicitVarSizeWithMarker_Values[q27]; + int(1..3)]), + (i - s_ExplicitVarSizeWithMarker_Values[q27]) % 2 = 0; + int(1..5)]) + /\ + min([i + s_ExplicitVarSizeWithMarker_Values[q27], i - s_ExplicitVarSizeWithMarker_Values[q27], + i * s_ExplicitVarSizeWithMarker_Values[q27], i / s_ExplicitVarSizeWithMarker_Values[q27]; + int(1..4)]) + = conjure_aux1 + | i : int(1..4), q27 : int(1..4)]), + sum([toInt(and([s_Occurrence[i], q27 <= s_ExplicitVarSizeWithMarker_Marker, + i != s_ExplicitVarSizeWithMarker_Values[q27], + allDiff([i + s_ExplicitVarSizeWithMarker_Values[q27], i * s_ExplicitVarSizeWithMarker_Values[q27], + i / s_ExplicitVarSizeWithMarker_Values[q27]; + int(1..3)]), + (i - s_ExplicitVarSizeWithMarker_Values[q27]) % 2 = 0; + int(1..5)])) + | i : int(1..4), q27 : int(1..4)]) + = 0 + -> conjure_aux1 = -16, + x = conjure_aux1, + sum([toInt(and([s_Occurrence[i], q27 <= s_ExplicitVarSizeWithMarker_Marker, + i != s_ExplicitVarSizeWithMarker_Values[q27], + allDiff([i + s_ExplicitVarSizeWithMarker_Values[q27], i * s_ExplicitVarSizeWithMarker_Values[q27], + i / s_ExplicitVarSizeWithMarker_Values[q27]; + int(1..3)]), + (i - s_ExplicitVarSizeWithMarker_Values[q27]) % 2 = 0; + int(1..5)])) + | i : int(1..4), q27 : int(1..4)]) + > 0, + and([q2 + 1 <= s_ExplicitVarSizeWithMarker_Marker -> + s_ExplicitVarSizeWithMarker_Values[q2] < s_ExplicitVarSizeWithMarker_Values[q2 + 1] + | q2 : int(1..3)]), + and([q3 > s_ExplicitVarSizeWithMarker_Marker -> s_ExplicitVarSizeWithMarker_Values[q3] = 1 | q3 : int(1..4)]), + and([q6 <= s_ExplicitVarSizeWithMarker_Marker -> s_Occurrence[s_ExplicitVarSizeWithMarker_Values[q6]] + | q6 : int(1..4)]), + and([s_Occurrence[q7] -> + or([q9 <= s_ExplicitVarSizeWithMarker_Marker /\ s_ExplicitVarSizeWithMarker_Values[q9] = q7 | q9 : int(1..4)]) + | q7 : int(1..4)]), + and([s_ExplicitVarSizeWithDummy[q10] < s_ExplicitVarSizeWithDummy[q10 + 1] \/ s_ExplicitVarSizeWithDummy[q10] = 5 + | q10 : int(1..3)]), + and([s_ExplicitVarSizeWithDummy[q11] = 5 -> s_ExplicitVarSizeWithDummy[q11 + 1] = 5 | q11 : int(1..3)]), + and([s_ExplicitVarSizeWithDummy[q15] != 5 -> s_Occurrence[s_ExplicitVarSizeWithDummy[q15]] | q15 : int(1..4)]), + and([s_Occurrence[q16] -> + or([s_ExplicitVarSizeWithDummy[q18] != 5 /\ s_ExplicitVarSizeWithDummy[q18] = q16 | q18 : int(1..4)]) + | q16 : int(1..4)]), + and([s_ExplicitVarSizeWithDummy[q20] != 5 -> + or([q22 <= s_ExplicitVarSizeWithMarker_Marker /\ + s_ExplicitVarSizeWithMarker_Values[q22] = s_ExplicitVarSizeWithDummy[q20] + | q22 : int(1..4)]) + | q20 : int(1..4)]), + and([q24 <= s_ExplicitVarSizeWithMarker_Marker -> + or([s_ExplicitVarSizeWithDummy[q26] != 5 /\ + s_ExplicitVarSizeWithDummy[q26] = s_ExplicitVarSizeWithMarker_Values[q24] + | q26 : int(1..4)]) + | q24 : int(1..4)]) + diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_3_4-solution000001.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_3_4-solution000001.solution new file mode 100644 index 0000000000..8b4ecbb66d --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_1_3_4-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 3} +letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_3_4-solution000002.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_3_4-solution000002.solution new file mode 100644 index 0000000000..159a613983 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_1_3_4-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {2, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_3_4-solution000003.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_3_4-solution000003.solution new file mode 100644 index 0000000000..5963aac565 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_1_3_4-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 2, 3} +letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_3_4-solution000004.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_3_4-solution000004.solution new file mode 100644 index 0000000000..6eeacc9727 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_1_3_4-solution000004.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 2, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_3_4-solution000005.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_3_4-solution000005.solution new file mode 100644 index 0000000000..560dd0f2f7 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_1_3_4-solution000005.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 3, 4} +letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_3_4-solution000006.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_3_4-solution000006.solution new file mode 100644 index 0000000000..40f3fd5c8f --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_1_3_4-solution000006.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {2, 3, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_3_4-solution000007.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_3_4-solution000007.solution new file mode 100644 index 0000000000..bd956f44e3 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_1_3_4-solution000007.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 2, 3, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_3_4.eprime b/tests/exhaustive/basic/comprehension_letting/expected/model_1_3_4.eprime new file mode 100644 index 0000000000..986b4a8cc2 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_1_3_4.eprime @@ -0,0 +1,99 @@ +language ESSENCE' 1.0 + +find s_Occurrence: matrix indexed by [int(1..4)] of bool +find s_ExplicitVarSizeWithMarker_Marker: int(0..4) +find s_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +find s_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find s_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +letting let1 be -100 +find x: int(-100..100) +find conjure_aux1: int(-16..3) +branching on + [s_ExplicitVarSizeWithFlags_Flags, s_ExplicitVarSizeWithFlags_Values, s_Occurrence, + s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithMarker_Values, x] +such that + and([and([s_Occurrence[i], q28 <= s_ExplicitVarSizeWithMarker_Marker, i != s_ExplicitVarSizeWithMarker_Values[q28], + allDiff([i + s_ExplicitVarSizeWithMarker_Values[q28], i * s_ExplicitVarSizeWithMarker_Values[q28], + i / s_ExplicitVarSizeWithMarker_Values[q28]; + int(1..3)]), + (i - s_ExplicitVarSizeWithMarker_Values[q28]) % 2 = 0; + int(1..5)]) + -> + min([i + s_ExplicitVarSizeWithMarker_Values[q28], i - s_ExplicitVarSizeWithMarker_Values[q28], + i * s_ExplicitVarSizeWithMarker_Values[q28], i / s_ExplicitVarSizeWithMarker_Values[q28]; + int(1..4)]) + <= conjure_aux1 + | i : int(1..4), q28 : int(1..4)]), + sum([toInt(and([s_Occurrence[i], q28 <= s_ExplicitVarSizeWithMarker_Marker, + i != s_ExplicitVarSizeWithMarker_Values[q28], + allDiff([i + s_ExplicitVarSizeWithMarker_Values[q28], i * s_ExplicitVarSizeWithMarker_Values[q28], + i / s_ExplicitVarSizeWithMarker_Values[q28]; + int(1..3)]), + (i - s_ExplicitVarSizeWithMarker_Values[q28]) % 2 = 0; + int(1..5)])) + | i : int(1..4), q28 : int(1..4)]) + > 0 + -> + or([and([s_Occurrence[i], q28 <= s_ExplicitVarSizeWithMarker_Marker, i != s_ExplicitVarSizeWithMarker_Values[q28], + allDiff([i + s_ExplicitVarSizeWithMarker_Values[q28], i * s_ExplicitVarSizeWithMarker_Values[q28], + i / s_ExplicitVarSizeWithMarker_Values[q28]; + int(1..3)]), + (i - s_ExplicitVarSizeWithMarker_Values[q28]) % 2 = 0; + int(1..5)]) + /\ + min([i + s_ExplicitVarSizeWithMarker_Values[q28], i - s_ExplicitVarSizeWithMarker_Values[q28], + i * s_ExplicitVarSizeWithMarker_Values[q28], i / s_ExplicitVarSizeWithMarker_Values[q28]; + int(1..4)]) + = conjure_aux1 + | i : int(1..4), q28 : int(1..4)]), + sum([toInt(and([s_Occurrence[i], q28 <= s_ExplicitVarSizeWithMarker_Marker, + i != s_ExplicitVarSizeWithMarker_Values[q28], + allDiff([i + s_ExplicitVarSizeWithMarker_Values[q28], i * s_ExplicitVarSizeWithMarker_Values[q28], + i / s_ExplicitVarSizeWithMarker_Values[q28]; + int(1..3)]), + (i - s_ExplicitVarSizeWithMarker_Values[q28]) % 2 = 0; + int(1..5)])) + | i : int(1..4), q28 : int(1..4)]) + = 0 + -> conjure_aux1 = -16, + x = conjure_aux1, + sum([toInt(and([s_Occurrence[i], q28 <= s_ExplicitVarSizeWithMarker_Marker, + i != s_ExplicitVarSizeWithMarker_Values[q28], + allDiff([i + s_ExplicitVarSizeWithMarker_Values[q28], i * s_ExplicitVarSizeWithMarker_Values[q28], + i / s_ExplicitVarSizeWithMarker_Values[q28]; + int(1..3)]), + (i - s_ExplicitVarSizeWithMarker_Values[q28]) % 2 = 0; + int(1..5)])) + | i : int(1..4), q28 : int(1..4)]) + > 0, + and([q2 + 1 <= s_ExplicitVarSizeWithMarker_Marker -> + s_ExplicitVarSizeWithMarker_Values[q2] < s_ExplicitVarSizeWithMarker_Values[q2 + 1] + | q2 : int(1..3)]), + and([q3 > s_ExplicitVarSizeWithMarker_Marker -> s_ExplicitVarSizeWithMarker_Values[q3] = 1 | q3 : int(1..4)]), + and([q6 <= s_ExplicitVarSizeWithMarker_Marker -> s_Occurrence[s_ExplicitVarSizeWithMarker_Values[q6]] + | q6 : int(1..4)]), + and([s_Occurrence[q7] -> + or([q9 <= s_ExplicitVarSizeWithMarker_Marker /\ s_ExplicitVarSizeWithMarker_Values[q9] = q7 | q9 : int(1..4)]) + | q7 : int(1..4)]), + and([s_ExplicitVarSizeWithFlags_Flags[q10 + 1] -> + s_ExplicitVarSizeWithFlags_Values[q10] < s_ExplicitVarSizeWithFlags_Values[q10 + 1] + | q10 : int(1..3)]), + and([s_ExplicitVarSizeWithFlags_Flags[q11] = false -> s_ExplicitVarSizeWithFlags_Values[q11] = 1 + | q11 : int(1..4)]), + and([s_ExplicitVarSizeWithFlags_Flags[q12 + 1] -> s_ExplicitVarSizeWithFlags_Flags[q12] | q12 : int(1..3)]), + and([s_ExplicitVarSizeWithFlags_Flags[q16] -> s_Occurrence[s_ExplicitVarSizeWithFlags_Values[q16]] + | q16 : int(1..4)]), + and([s_Occurrence[q17] -> + or([s_ExplicitVarSizeWithFlags_Flags[q19] /\ s_ExplicitVarSizeWithFlags_Values[q19] = q17 | q19 : int(1..4)]) + | q17 : int(1..4)]), + and([s_ExplicitVarSizeWithFlags_Flags[q21] -> + or([q23 <= s_ExplicitVarSizeWithMarker_Marker /\ + s_ExplicitVarSizeWithMarker_Values[q23] = s_ExplicitVarSizeWithFlags_Values[q21] + | q23 : int(1..4)]) + | q21 : int(1..4)]), + and([q25 <= s_ExplicitVarSizeWithMarker_Marker -> + or([s_ExplicitVarSizeWithFlags_Flags[q27] /\ + s_ExplicitVarSizeWithFlags_Values[q27] = s_ExplicitVarSizeWithMarker_Values[q25] + | q27 : int(1..4)]) + | q25 : int(1..4)]) + diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_4_1-solution000001.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_4_1-solution000001.solution new file mode 100644 index 0000000000..8b4ecbb66d --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_1_4_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 3} +letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_4_1-solution000002.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_4_1-solution000002.solution new file mode 100644 index 0000000000..159a613983 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_1_4_1-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {2, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_4_1-solution000003.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_4_1-solution000003.solution new file mode 100644 index 0000000000..5963aac565 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_1_4_1-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 2, 3} +letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_4_1-solution000004.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_4_1-solution000004.solution new file mode 100644 index 0000000000..6eeacc9727 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_1_4_1-solution000004.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 2, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_4_1-solution000005.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_4_1-solution000005.solution new file mode 100644 index 0000000000..560dd0f2f7 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_1_4_1-solution000005.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 3, 4} +letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_4_1-solution000006.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_4_1-solution000006.solution new file mode 100644 index 0000000000..40f3fd5c8f --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_1_4_1-solution000006.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {2, 3, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_4_1-solution000007.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_4_1-solution000007.solution new file mode 100644 index 0000000000..bd956f44e3 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_1_4_1-solution000007.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 2, 3, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_4_1.eprime b/tests/exhaustive/basic/comprehension_letting/expected/model_1_4_1.eprime new file mode 100644 index 0000000000..2c748ac8af --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_1_4_1.eprime @@ -0,0 +1,71 @@ +language ESSENCE' 1.0 + +find s_Occurrence: matrix indexed by [int(1..4)] of bool +find s_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find s_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +letting let1 be -100 +find x: int(-100..100) +find conjure_aux1: int(-16..3) +branching on [s_ExplicitVarSizeWithFlags_Flags, s_ExplicitVarSizeWithFlags_Values, s_Occurrence, x] +such that + and([and([s_Occurrence[i], s_ExplicitVarSizeWithFlags_Flags[q12], i != s_ExplicitVarSizeWithFlags_Values[q12], + allDiff([i + s_ExplicitVarSizeWithFlags_Values[q12], i * s_ExplicitVarSizeWithFlags_Values[q12], + i / s_ExplicitVarSizeWithFlags_Values[q12]; + int(1..3)]), + (i - s_ExplicitVarSizeWithFlags_Values[q12]) % 2 = 0; + int(1..5)]) + -> + min([i + s_ExplicitVarSizeWithFlags_Values[q12], i - s_ExplicitVarSizeWithFlags_Values[q12], + i * s_ExplicitVarSizeWithFlags_Values[q12], i / s_ExplicitVarSizeWithFlags_Values[q12]; + int(1..4)]) + <= conjure_aux1 + | i : int(1..4), q12 : int(1..4)]), + sum([toInt(and([s_Occurrence[i], s_ExplicitVarSizeWithFlags_Flags[q12], i != s_ExplicitVarSizeWithFlags_Values[q12], + allDiff([i + s_ExplicitVarSizeWithFlags_Values[q12], i * s_ExplicitVarSizeWithFlags_Values[q12], + i / s_ExplicitVarSizeWithFlags_Values[q12]; + int(1..3)]), + (i - s_ExplicitVarSizeWithFlags_Values[q12]) % 2 = 0; + int(1..5)])) + | i : int(1..4), q12 : int(1..4)]) + > 0 + -> + or([and([s_Occurrence[i], s_ExplicitVarSizeWithFlags_Flags[q12], i != s_ExplicitVarSizeWithFlags_Values[q12], + allDiff([i + s_ExplicitVarSizeWithFlags_Values[q12], i * s_ExplicitVarSizeWithFlags_Values[q12], + i / s_ExplicitVarSizeWithFlags_Values[q12]; + int(1..3)]), + (i - s_ExplicitVarSizeWithFlags_Values[q12]) % 2 = 0; + int(1..5)]) + /\ + min([i + s_ExplicitVarSizeWithFlags_Values[q12], i - s_ExplicitVarSizeWithFlags_Values[q12], + i * s_ExplicitVarSizeWithFlags_Values[q12], i / s_ExplicitVarSizeWithFlags_Values[q12]; + int(1..4)]) + = conjure_aux1 + | i : int(1..4), q12 : int(1..4)]), + sum([toInt(and([s_Occurrence[i], s_ExplicitVarSizeWithFlags_Flags[q12], i != s_ExplicitVarSizeWithFlags_Values[q12], + allDiff([i + s_ExplicitVarSizeWithFlags_Values[q12], i * s_ExplicitVarSizeWithFlags_Values[q12], + i / s_ExplicitVarSizeWithFlags_Values[q12]; + int(1..3)]), + (i - s_ExplicitVarSizeWithFlags_Values[q12]) % 2 = 0; + int(1..5)])) + | i : int(1..4), q12 : int(1..4)]) + = 0 + -> conjure_aux1 = -16, + x = conjure_aux1, + sum([toInt(and([s_Occurrence[i], s_ExplicitVarSizeWithFlags_Flags[q12], i != s_ExplicitVarSizeWithFlags_Values[q12], + allDiff([i + s_ExplicitVarSizeWithFlags_Values[q12], i * s_ExplicitVarSizeWithFlags_Values[q12], + i / s_ExplicitVarSizeWithFlags_Values[q12]; + int(1..3)]), + (i - s_ExplicitVarSizeWithFlags_Values[q12]) % 2 = 0; + int(1..5)])) + | i : int(1..4), q12 : int(1..4)]) + > 0, + and([s_ExplicitVarSizeWithFlags_Flags[q2 + 1] -> + s_ExplicitVarSizeWithFlags_Values[q2] < s_ExplicitVarSizeWithFlags_Values[q2 + 1] + | q2 : int(1..3)]), + and([s_ExplicitVarSizeWithFlags_Flags[q3] = false -> s_ExplicitVarSizeWithFlags_Values[q3] = 1 | q3 : int(1..4)]), + and([s_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> s_ExplicitVarSizeWithFlags_Flags[q4] | q4 : int(1..3)]), + and([s_ExplicitVarSizeWithFlags_Flags[q8] -> s_Occurrence[s_ExplicitVarSizeWithFlags_Values[q8]] | q8 : int(1..4)]), + and([s_Occurrence[q9] -> + or([s_ExplicitVarSizeWithFlags_Flags[q11] /\ s_ExplicitVarSizeWithFlags_Values[q11] = q9 | q11 : int(1..4)]) + | q9 : int(1..4)]) + diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_4_2-solution000001.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_4_2-solution000001.solution new file mode 100644 index 0000000000..bd956f44e3 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_1_4_2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 2, 3, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_4_2-solution000002.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_4_2-solution000002.solution new file mode 100644 index 0000000000..5963aac565 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_1_4_2-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 2, 3} +letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_4_2-solution000003.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_4_2-solution000003.solution new file mode 100644 index 0000000000..6eeacc9727 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_1_4_2-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 2, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_4_2-solution000004.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_4_2-solution000004.solution new file mode 100644 index 0000000000..560dd0f2f7 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_1_4_2-solution000004.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 3, 4} +letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_4_2-solution000005.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_4_2-solution000005.solution new file mode 100644 index 0000000000..8b4ecbb66d --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_1_4_2-solution000005.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 3} +letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_4_2-solution000006.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_4_2-solution000006.solution new file mode 100644 index 0000000000..40f3fd5c8f --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_1_4_2-solution000006.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {2, 3, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_4_2-solution000007.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_4_2-solution000007.solution new file mode 100644 index 0000000000..159a613983 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_1_4_2-solution000007.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {2, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_4_2.eprime b/tests/exhaustive/basic/comprehension_letting/expected/model_1_4_2.eprime new file mode 100644 index 0000000000..08c34a7a31 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_1_4_2.eprime @@ -0,0 +1,90 @@ +language ESSENCE' 1.0 + +find s_Occurrence: matrix indexed by [int(1..4)] of bool +find s_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find s_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +find s_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +letting let1 be -100 +find x: int(-100..100) +find conjure_aux1: int(-16..3) +branching on + [s_ExplicitVarSizeWithDummy, s_Occurrence, s_ExplicitVarSizeWithFlags_Flags, s_ExplicitVarSizeWithFlags_Values, x] +such that + and([and([s_Occurrence[i], s_ExplicitVarSizeWithFlags_Flags[q29], i != s_ExplicitVarSizeWithFlags_Values[q29], + allDiff([i + s_ExplicitVarSizeWithFlags_Values[q29], i * s_ExplicitVarSizeWithFlags_Values[q29], + i / s_ExplicitVarSizeWithFlags_Values[q29]; + int(1..3)]), + (i - s_ExplicitVarSizeWithFlags_Values[q29]) % 2 = 0; + int(1..5)]) + -> + min([i + s_ExplicitVarSizeWithFlags_Values[q29], i - s_ExplicitVarSizeWithFlags_Values[q29], + i * s_ExplicitVarSizeWithFlags_Values[q29], i / s_ExplicitVarSizeWithFlags_Values[q29]; + int(1..4)]) + <= conjure_aux1 + | i : int(1..4), q29 : int(1..4)]), + sum([toInt(and([s_Occurrence[i], s_ExplicitVarSizeWithFlags_Flags[q29], i != s_ExplicitVarSizeWithFlags_Values[q29], + allDiff([i + s_ExplicitVarSizeWithFlags_Values[q29], i * s_ExplicitVarSizeWithFlags_Values[q29], + i / s_ExplicitVarSizeWithFlags_Values[q29]; + int(1..3)]), + (i - s_ExplicitVarSizeWithFlags_Values[q29]) % 2 = 0; + int(1..5)])) + | i : int(1..4), q29 : int(1..4)]) + > 0 + -> + or([and([s_Occurrence[i], s_ExplicitVarSizeWithFlags_Flags[q29], i != s_ExplicitVarSizeWithFlags_Values[q29], + allDiff([i + s_ExplicitVarSizeWithFlags_Values[q29], i * s_ExplicitVarSizeWithFlags_Values[q29], + i / s_ExplicitVarSizeWithFlags_Values[q29]; + int(1..3)]), + (i - s_ExplicitVarSizeWithFlags_Values[q29]) % 2 = 0; + int(1..5)]) + /\ + min([i + s_ExplicitVarSizeWithFlags_Values[q29], i - s_ExplicitVarSizeWithFlags_Values[q29], + i * s_ExplicitVarSizeWithFlags_Values[q29], i / s_ExplicitVarSizeWithFlags_Values[q29]; + int(1..4)]) + = conjure_aux1 + | i : int(1..4), q29 : int(1..4)]), + sum([toInt(and([s_Occurrence[i], s_ExplicitVarSizeWithFlags_Flags[q29], i != s_ExplicitVarSizeWithFlags_Values[q29], + allDiff([i + s_ExplicitVarSizeWithFlags_Values[q29], i * s_ExplicitVarSizeWithFlags_Values[q29], + i / s_ExplicitVarSizeWithFlags_Values[q29]; + int(1..3)]), + (i - s_ExplicitVarSizeWithFlags_Values[q29]) % 2 = 0; + int(1..5)])) + | i : int(1..4), q29 : int(1..4)]) + = 0 + -> conjure_aux1 = -16, + x = conjure_aux1, + sum([toInt(and([s_Occurrence[i], s_ExplicitVarSizeWithFlags_Flags[q29], i != s_ExplicitVarSizeWithFlags_Values[q29], + allDiff([i + s_ExplicitVarSizeWithFlags_Values[q29], i * s_ExplicitVarSizeWithFlags_Values[q29], + i / s_ExplicitVarSizeWithFlags_Values[q29]; + int(1..3)]), + (i - s_ExplicitVarSizeWithFlags_Values[q29]) % 2 = 0; + int(1..5)])) + | i : int(1..4), q29 : int(1..4)]) + > 0, + and([s_ExplicitVarSizeWithFlags_Flags[q2 + 1] -> + s_ExplicitVarSizeWithFlags_Values[q2] < s_ExplicitVarSizeWithFlags_Values[q2 + 1] + | q2 : int(1..3)]), + and([s_ExplicitVarSizeWithFlags_Flags[q3] = false -> s_ExplicitVarSizeWithFlags_Values[q3] = 1 | q3 : int(1..4)]), + and([s_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> s_ExplicitVarSizeWithFlags_Flags[q4] | q4 : int(1..3)]), + and([s_ExplicitVarSizeWithFlags_Flags[q8] -> s_Occurrence[s_ExplicitVarSizeWithFlags_Values[q8]] | q8 : int(1..4)]), + and([s_Occurrence[q9] -> + or([s_ExplicitVarSizeWithFlags_Flags[q11] /\ s_ExplicitVarSizeWithFlags_Values[q11] = q9 | q11 : int(1..4)]) + | q9 : int(1..4)]), + and([s_ExplicitVarSizeWithDummy[q12] < s_ExplicitVarSizeWithDummy[q12 + 1] \/ s_ExplicitVarSizeWithDummy[q12] = 5 + | q12 : int(1..3)]), + and([s_ExplicitVarSizeWithDummy[q13] = 5 -> s_ExplicitVarSizeWithDummy[q13 + 1] = 5 | q13 : int(1..3)]), + and([s_ExplicitVarSizeWithDummy[q17] != 5 -> s_Occurrence[s_ExplicitVarSizeWithDummy[q17]] | q17 : int(1..4)]), + and([s_Occurrence[q18] -> + or([s_ExplicitVarSizeWithDummy[q20] != 5 /\ s_ExplicitVarSizeWithDummy[q20] = q18 | q20 : int(1..4)]) + | q18 : int(1..4)]), + and([s_ExplicitVarSizeWithDummy[q22] != 5 -> + or([s_ExplicitVarSizeWithFlags_Flags[q24] /\ + s_ExplicitVarSizeWithFlags_Values[q24] = s_ExplicitVarSizeWithDummy[q22] + | q24 : int(1..4)]) + | q22 : int(1..4)]), + and([s_ExplicitVarSizeWithFlags_Flags[q26] -> + or([s_ExplicitVarSizeWithDummy[q28] != 5 /\ + s_ExplicitVarSizeWithDummy[q28] = s_ExplicitVarSizeWithFlags_Values[q26] + | q28 : int(1..4)]) + | q26 : int(1..4)]) + diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_4_3-solution000001.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_4_3-solution000001.solution new file mode 100644 index 0000000000..8b4ecbb66d --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_1_4_3-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 3} +letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_4_3-solution000002.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_4_3-solution000002.solution new file mode 100644 index 0000000000..159a613983 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_1_4_3-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {2, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_4_3-solution000003.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_4_3-solution000003.solution new file mode 100644 index 0000000000..5963aac565 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_1_4_3-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 2, 3} +letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_4_3-solution000004.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_4_3-solution000004.solution new file mode 100644 index 0000000000..6eeacc9727 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_1_4_3-solution000004.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 2, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_4_3-solution000005.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_4_3-solution000005.solution new file mode 100644 index 0000000000..560dd0f2f7 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_1_4_3-solution000005.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 3, 4} +letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_4_3-solution000006.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_4_3-solution000006.solution new file mode 100644 index 0000000000..40f3fd5c8f --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_1_4_3-solution000006.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {2, 3, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_4_3-solution000007.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_1_4_3-solution000007.solution new file mode 100644 index 0000000000..bd956f44e3 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_1_4_3-solution000007.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 2, 3, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_1_4_3.eprime b/tests/exhaustive/basic/comprehension_letting/expected/model_1_4_3.eprime new file mode 100644 index 0000000000..c3e1894ef9 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_1_4_3.eprime @@ -0,0 +1,95 @@ +language ESSENCE' 1.0 + +find s_Occurrence: matrix indexed by [int(1..4)] of bool +find s_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find s_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +find s_ExplicitVarSizeWithMarker_Marker: int(0..4) +find s_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +letting let1 be -100 +find x: int(-100..100) +find conjure_aux1: int(-16..3) +branching on + [s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithMarker_Values, s_Occurrence, + s_ExplicitVarSizeWithFlags_Flags, s_ExplicitVarSizeWithFlags_Values, x] +such that + and([and([s_Occurrence[i], s_ExplicitVarSizeWithFlags_Flags[q28], i != s_ExplicitVarSizeWithFlags_Values[q28], + allDiff([i + s_ExplicitVarSizeWithFlags_Values[q28], i * s_ExplicitVarSizeWithFlags_Values[q28], + i / s_ExplicitVarSizeWithFlags_Values[q28]; + int(1..3)]), + (i - s_ExplicitVarSizeWithFlags_Values[q28]) % 2 = 0; + int(1..5)]) + -> + min([i + s_ExplicitVarSizeWithFlags_Values[q28], i - s_ExplicitVarSizeWithFlags_Values[q28], + i * s_ExplicitVarSizeWithFlags_Values[q28], i / s_ExplicitVarSizeWithFlags_Values[q28]; + int(1..4)]) + <= conjure_aux1 + | i : int(1..4), q28 : int(1..4)]), + sum([toInt(and([s_Occurrence[i], s_ExplicitVarSizeWithFlags_Flags[q28], i != s_ExplicitVarSizeWithFlags_Values[q28], + allDiff([i + s_ExplicitVarSizeWithFlags_Values[q28], i * s_ExplicitVarSizeWithFlags_Values[q28], + i / s_ExplicitVarSizeWithFlags_Values[q28]; + int(1..3)]), + (i - s_ExplicitVarSizeWithFlags_Values[q28]) % 2 = 0; + int(1..5)])) + | i : int(1..4), q28 : int(1..4)]) + > 0 + -> + or([and([s_Occurrence[i], s_ExplicitVarSizeWithFlags_Flags[q28], i != s_ExplicitVarSizeWithFlags_Values[q28], + allDiff([i + s_ExplicitVarSizeWithFlags_Values[q28], i * s_ExplicitVarSizeWithFlags_Values[q28], + i / s_ExplicitVarSizeWithFlags_Values[q28]; + int(1..3)]), + (i - s_ExplicitVarSizeWithFlags_Values[q28]) % 2 = 0; + int(1..5)]) + /\ + min([i + s_ExplicitVarSizeWithFlags_Values[q28], i - s_ExplicitVarSizeWithFlags_Values[q28], + i * s_ExplicitVarSizeWithFlags_Values[q28], i / s_ExplicitVarSizeWithFlags_Values[q28]; + int(1..4)]) + = conjure_aux1 + | i : int(1..4), q28 : int(1..4)]), + sum([toInt(and([s_Occurrence[i], s_ExplicitVarSizeWithFlags_Flags[q28], i != s_ExplicitVarSizeWithFlags_Values[q28], + allDiff([i + s_ExplicitVarSizeWithFlags_Values[q28], i * s_ExplicitVarSizeWithFlags_Values[q28], + i / s_ExplicitVarSizeWithFlags_Values[q28]; + int(1..3)]), + (i - s_ExplicitVarSizeWithFlags_Values[q28]) % 2 = 0; + int(1..5)])) + | i : int(1..4), q28 : int(1..4)]) + = 0 + -> conjure_aux1 = -16, + x = conjure_aux1, + sum([toInt(and([s_Occurrence[i], s_ExplicitVarSizeWithFlags_Flags[q28], i != s_ExplicitVarSizeWithFlags_Values[q28], + allDiff([i + s_ExplicitVarSizeWithFlags_Values[q28], i * s_ExplicitVarSizeWithFlags_Values[q28], + i / s_ExplicitVarSizeWithFlags_Values[q28]; + int(1..3)]), + (i - s_ExplicitVarSizeWithFlags_Values[q28]) % 2 = 0; + int(1..5)])) + | i : int(1..4), q28 : int(1..4)]) + > 0, + and([s_ExplicitVarSizeWithFlags_Flags[q2 + 1] -> + s_ExplicitVarSizeWithFlags_Values[q2] < s_ExplicitVarSizeWithFlags_Values[q2 + 1] + | q2 : int(1..3)]), + and([s_ExplicitVarSizeWithFlags_Flags[q3] = false -> s_ExplicitVarSizeWithFlags_Values[q3] = 1 | q3 : int(1..4)]), + and([s_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> s_ExplicitVarSizeWithFlags_Flags[q4] | q4 : int(1..3)]), + and([s_ExplicitVarSizeWithFlags_Flags[q8] -> s_Occurrence[s_ExplicitVarSizeWithFlags_Values[q8]] | q8 : int(1..4)]), + and([s_Occurrence[q9] -> + or([s_ExplicitVarSizeWithFlags_Flags[q11] /\ s_ExplicitVarSizeWithFlags_Values[q11] = q9 | q11 : int(1..4)]) + | q9 : int(1..4)]), + and([q12 + 1 <= s_ExplicitVarSizeWithMarker_Marker -> + s_ExplicitVarSizeWithMarker_Values[q12] < s_ExplicitVarSizeWithMarker_Values[q12 + 1] + | q12 : int(1..3)]), + and([q13 > s_ExplicitVarSizeWithMarker_Marker -> s_ExplicitVarSizeWithMarker_Values[q13] = 1 | q13 : int(1..4)]), + and([q16 <= s_ExplicitVarSizeWithMarker_Marker -> s_Occurrence[s_ExplicitVarSizeWithMarker_Values[q16]] + | q16 : int(1..4)]), + and([s_Occurrence[q17] -> + or([q19 <= s_ExplicitVarSizeWithMarker_Marker /\ s_ExplicitVarSizeWithMarker_Values[q19] = q17 + | q19 : int(1..4)]) + | q17 : int(1..4)]), + and([q21 <= s_ExplicitVarSizeWithMarker_Marker -> + or([s_ExplicitVarSizeWithFlags_Flags[q23] /\ + s_ExplicitVarSizeWithFlags_Values[q23] = s_ExplicitVarSizeWithMarker_Values[q21] + | q23 : int(1..4)]) + | q21 : int(1..4)]), + and([s_ExplicitVarSizeWithFlags_Flags[q25] -> + or([q27 <= s_ExplicitVarSizeWithMarker_Marker /\ + s_ExplicitVarSizeWithMarker_Values[q27] = s_ExplicitVarSizeWithFlags_Values[q25] + | q27 : int(1..4)]) + | q25 : int(1..4)]) + diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_1_1-solution000001.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_1_1-solution000001.solution new file mode 100644 index 0000000000..159a613983 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_2_1_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {2, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_1_1-solution000002.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_1_1-solution000002.solution new file mode 100644 index 0000000000..40f3fd5c8f --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_2_1_1-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {2, 3, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_1_1-solution000003.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_1_1-solution000003.solution new file mode 100644 index 0000000000..8b4ecbb66d --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_2_1_1-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 3} +letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_1_1-solution000004.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_1_1-solution000004.solution new file mode 100644 index 0000000000..560dd0f2f7 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_2_1_1-solution000004.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 3, 4} +letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_1_1-solution000005.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_1_1-solution000005.solution new file mode 100644 index 0000000000..6eeacc9727 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_2_1_1-solution000005.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 2, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_1_1-solution000006.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_1_1-solution000006.solution new file mode 100644 index 0000000000..5963aac565 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_2_1_1-solution000006.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 2, 3} +letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_1_1-solution000007.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_1_1-solution000007.solution new file mode 100644 index 0000000000..bd956f44e3 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_2_1_1-solution000007.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 2, 3, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_1_1.eprime b/tests/exhaustive/basic/comprehension_letting/expected/model_2_1_1.eprime new file mode 100644 index 0000000000..acf6c8641f --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_2_1_1.eprime @@ -0,0 +1,68 @@ +language ESSENCE' 1.0 + +find s_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +find s_Occurrence: matrix indexed by [int(1..4)] of bool +letting let1 be -100 +find x: int(-100..100) +find conjure_aux1: int(-20..4) +branching on [s_Occurrence, s_ExplicitVarSizeWithDummy, x] +such that + and([and([s_ExplicitVarSizeWithDummy[q6] != 5, s_Occurrence[j], s_ExplicitVarSizeWithDummy[q6] != j, + allDiff([s_ExplicitVarSizeWithDummy[q6] + j, s_ExplicitVarSizeWithDummy[q6] * j, + s_ExplicitVarSizeWithDummy[q6] / j; + int(1..3)]), + (s_ExplicitVarSizeWithDummy[q6] - j) % 2 = 0; + int(1..5)]) + -> + min([s_ExplicitVarSizeWithDummy[q6] + j, s_ExplicitVarSizeWithDummy[q6] - j, + s_ExplicitVarSizeWithDummy[q6] * j, s_ExplicitVarSizeWithDummy[q6] / j; + int(1..4)]) + <= conjure_aux1 + | q6 : int(1..4), j : int(1..4)]), + sum([toInt(and([s_ExplicitVarSizeWithDummy[q6] != 5, s_Occurrence[j], s_ExplicitVarSizeWithDummy[q6] != j, + allDiff([s_ExplicitVarSizeWithDummy[q6] + j, s_ExplicitVarSizeWithDummy[q6] * j, + s_ExplicitVarSizeWithDummy[q6] / j; + int(1..3)]), + (s_ExplicitVarSizeWithDummy[q6] - j) % 2 = 0; + int(1..5)])) + | q6 : int(1..4), j : int(1..4)]) + > 0 + -> + or([and([s_ExplicitVarSizeWithDummy[q6] != 5, s_Occurrence[j], s_ExplicitVarSizeWithDummy[q6] != j, + allDiff([s_ExplicitVarSizeWithDummy[q6] + j, s_ExplicitVarSizeWithDummy[q6] * j, + s_ExplicitVarSizeWithDummy[q6] / j; + int(1..3)]), + (s_ExplicitVarSizeWithDummy[q6] - j) % 2 = 0; + int(1..5)]) + /\ + min([s_ExplicitVarSizeWithDummy[q6] + j, s_ExplicitVarSizeWithDummy[q6] - j, s_ExplicitVarSizeWithDummy[q6] * j, + s_ExplicitVarSizeWithDummy[q6] / j; + int(1..4)]) + = conjure_aux1 + | q6 : int(1..4), j : int(1..4)]), + sum([toInt(and([s_ExplicitVarSizeWithDummy[q6] != 5, s_Occurrence[j], s_ExplicitVarSizeWithDummy[q6] != j, + allDiff([s_ExplicitVarSizeWithDummy[q6] + j, s_ExplicitVarSizeWithDummy[q6] * j, + s_ExplicitVarSizeWithDummy[q6] / j; + int(1..3)]), + (s_ExplicitVarSizeWithDummy[q6] - j) % 2 = 0; + int(1..5)])) + | q6 : int(1..4), j : int(1..4)]) + = 0 + -> conjure_aux1 = -20, + x = conjure_aux1, + sum([toInt(and([s_ExplicitVarSizeWithDummy[q6] != 5, s_Occurrence[j], s_ExplicitVarSizeWithDummy[q6] != j, + allDiff([s_ExplicitVarSizeWithDummy[q6] + j, s_ExplicitVarSizeWithDummy[q6] * j, + s_ExplicitVarSizeWithDummy[q6] / j; + int(1..3)]), + (s_ExplicitVarSizeWithDummy[q6] - j) % 2 = 0; + int(1..5)])) + | q6 : int(1..4), j : int(1..4)]) + > 0, + and([s_ExplicitVarSizeWithDummy[q1] < s_ExplicitVarSizeWithDummy[q1 + 1] \/ s_ExplicitVarSizeWithDummy[q1] = 5 + | q1 : int(1..3)]), + and([s_ExplicitVarSizeWithDummy[q2] = 5 -> s_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..3)]), + and([s_Occurrence[q28] -> + or([s_ExplicitVarSizeWithDummy[q30] != 5 /\ s_ExplicitVarSizeWithDummy[q30] = q28 | q30 : int(1..4)]) + | q28 : int(1..4)]), + and([s_ExplicitVarSizeWithDummy[q32] != 5 -> s_Occurrence[s_ExplicitVarSizeWithDummy[q32]] | q32 : int(1..4)]) + diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_1_3-solution000001.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_1_3-solution000001.solution new file mode 100644 index 0000000000..8b4ecbb66d --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_2_1_3-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 3} +letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_1_3-solution000002.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_1_3-solution000002.solution new file mode 100644 index 0000000000..159a613983 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_2_1_3-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {2, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_1_3-solution000003.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_1_3-solution000003.solution new file mode 100644 index 0000000000..5963aac565 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_2_1_3-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 2, 3} +letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_1_3-solution000004.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_1_3-solution000004.solution new file mode 100644 index 0000000000..6eeacc9727 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_2_1_3-solution000004.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 2, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_1_3-solution000005.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_1_3-solution000005.solution new file mode 100644 index 0000000000..560dd0f2f7 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_2_1_3-solution000005.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 3, 4} +letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_1_3-solution000006.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_1_3-solution000006.solution new file mode 100644 index 0000000000..40f3fd5c8f --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_2_1_3-solution000006.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {2, 3, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_1_3-solution000007.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_1_3-solution000007.solution new file mode 100644 index 0000000000..bd956f44e3 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_2_1_3-solution000007.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 2, 3, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_1_3.eprime b/tests/exhaustive/basic/comprehension_letting/expected/model_2_1_3.eprime new file mode 100644 index 0000000000..3f8f2d2249 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_2_1_3.eprime @@ -0,0 +1,92 @@ +language ESSENCE' 1.0 + +find s_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +find s_Occurrence: matrix indexed by [int(1..4)] of bool +find s_ExplicitVarSizeWithMarker_Marker: int(0..4) +find s_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +letting let1 be -100 +find x: int(-100..100) +find conjure_aux1: int(-20..4) +branching on + [s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithMarker_Values, s_ExplicitVarSizeWithDummy, s_Occurrence, + x] +such that + and([and([s_ExplicitVarSizeWithDummy[q22] != 5, s_Occurrence[j], s_ExplicitVarSizeWithDummy[q22] != j, + allDiff([s_ExplicitVarSizeWithDummy[q22] + j, s_ExplicitVarSizeWithDummy[q22] * j, + s_ExplicitVarSizeWithDummy[q22] / j; + int(1..3)]), + (s_ExplicitVarSizeWithDummy[q22] - j) % 2 = 0; + int(1..5)]) + -> + min([s_ExplicitVarSizeWithDummy[q22] + j, s_ExplicitVarSizeWithDummy[q22] - j, + s_ExplicitVarSizeWithDummy[q22] * j, s_ExplicitVarSizeWithDummy[q22] / j; + int(1..4)]) + <= conjure_aux1 + | q22 : int(1..4), j : int(1..4)]), + sum([toInt(and([s_ExplicitVarSizeWithDummy[q22] != 5, s_Occurrence[j], s_ExplicitVarSizeWithDummy[q22] != j, + allDiff([s_ExplicitVarSizeWithDummy[q22] + j, s_ExplicitVarSizeWithDummy[q22] * j, + s_ExplicitVarSizeWithDummy[q22] / j; + int(1..3)]), + (s_ExplicitVarSizeWithDummy[q22] - j) % 2 = 0; + int(1..5)])) + | q22 : int(1..4), j : int(1..4)]) + > 0 + -> + or([and([s_ExplicitVarSizeWithDummy[q22] != 5, s_Occurrence[j], s_ExplicitVarSizeWithDummy[q22] != j, + allDiff([s_ExplicitVarSizeWithDummy[q22] + j, s_ExplicitVarSizeWithDummy[q22] * j, + s_ExplicitVarSizeWithDummy[q22] / j; + int(1..3)]), + (s_ExplicitVarSizeWithDummy[q22] - j) % 2 = 0; + int(1..5)]) + /\ + min([s_ExplicitVarSizeWithDummy[q22] + j, s_ExplicitVarSizeWithDummy[q22] - j, + s_ExplicitVarSizeWithDummy[q22] * j, s_ExplicitVarSizeWithDummy[q22] / j; + int(1..4)]) + = conjure_aux1 + | q22 : int(1..4), j : int(1..4)]), + sum([toInt(and([s_ExplicitVarSizeWithDummy[q22] != 5, s_Occurrence[j], s_ExplicitVarSizeWithDummy[q22] != j, + allDiff([s_ExplicitVarSizeWithDummy[q22] + j, s_ExplicitVarSizeWithDummy[q22] * j, + s_ExplicitVarSizeWithDummy[q22] / j; + int(1..3)]), + (s_ExplicitVarSizeWithDummy[q22] - j) % 2 = 0; + int(1..5)])) + | q22 : int(1..4), j : int(1..4)]) + = 0 + -> conjure_aux1 = -20, + x = conjure_aux1, + sum([toInt(and([s_ExplicitVarSizeWithDummy[q22] != 5, s_Occurrence[j], s_ExplicitVarSizeWithDummy[q22] != j, + allDiff([s_ExplicitVarSizeWithDummy[q22] + j, s_ExplicitVarSizeWithDummy[q22] * j, + s_ExplicitVarSizeWithDummy[q22] / j; + int(1..3)]), + (s_ExplicitVarSizeWithDummy[q22] - j) % 2 = 0; + int(1..5)])) + | q22 : int(1..4), j : int(1..4)]) + > 0, + and([s_ExplicitVarSizeWithDummy[q1] < s_ExplicitVarSizeWithDummy[q1 + 1] \/ s_ExplicitVarSizeWithDummy[q1] = 5 + | q1 : int(1..3)]), + and([s_ExplicitVarSizeWithDummy[q2] = 5 -> s_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..3)]), + and([s_Occurrence[q44] -> + or([s_ExplicitVarSizeWithDummy[q46] != 5 /\ s_ExplicitVarSizeWithDummy[q46] = q44 | q46 : int(1..4)]) + | q44 : int(1..4)]), + and([s_ExplicitVarSizeWithDummy[q48] != 5 -> s_Occurrence[s_ExplicitVarSizeWithDummy[q48]] | q48 : int(1..4)]), + and([q6 + 1 <= s_ExplicitVarSizeWithMarker_Marker -> + s_ExplicitVarSizeWithMarker_Values[q6] < s_ExplicitVarSizeWithMarker_Values[q6 + 1] + | q6 : int(1..3)]), + and([q7 > s_ExplicitVarSizeWithMarker_Marker -> s_ExplicitVarSizeWithMarker_Values[q7] = 1 | q7 : int(1..4)]), + and([q10 <= s_ExplicitVarSizeWithMarker_Marker -> + or([s_ExplicitVarSizeWithDummy[q12] != 5 /\ + s_ExplicitVarSizeWithDummy[q12] = s_ExplicitVarSizeWithMarker_Values[q10] + | q12 : int(1..4)]) + | q10 : int(1..4)]), + and([s_ExplicitVarSizeWithDummy[q14] != 5 -> + or([q16 <= s_ExplicitVarSizeWithMarker_Marker /\ + s_ExplicitVarSizeWithMarker_Values[q16] = s_ExplicitVarSizeWithDummy[q14] + | q16 : int(1..4)]) + | q14 : int(1..4)]), + and([q18 <= s_ExplicitVarSizeWithMarker_Marker -> s_Occurrence[s_ExplicitVarSizeWithMarker_Values[q18]] + | q18 : int(1..4)]), + and([s_Occurrence[q19] -> + or([q21 <= s_ExplicitVarSizeWithMarker_Marker /\ s_ExplicitVarSizeWithMarker_Values[q21] = q19 + | q21 : int(1..4)]) + | q19 : int(1..4)]) + diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_1_4-solution000001.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_1_4-solution000001.solution new file mode 100644 index 0000000000..8b4ecbb66d --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_2_1_4-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 3} +letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_1_4-solution000002.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_1_4-solution000002.solution new file mode 100644 index 0000000000..159a613983 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_2_1_4-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {2, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_1_4-solution000003.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_1_4-solution000003.solution new file mode 100644 index 0000000000..5963aac565 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_2_1_4-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 2, 3} +letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_1_4-solution000004.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_1_4-solution000004.solution new file mode 100644 index 0000000000..6eeacc9727 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_2_1_4-solution000004.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 2, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_1_4-solution000005.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_1_4-solution000005.solution new file mode 100644 index 0000000000..560dd0f2f7 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_2_1_4-solution000005.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 3, 4} +letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_1_4-solution000006.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_1_4-solution000006.solution new file mode 100644 index 0000000000..40f3fd5c8f --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_2_1_4-solution000006.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {2, 3, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_1_4-solution000007.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_1_4-solution000007.solution new file mode 100644 index 0000000000..bd956f44e3 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_2_1_4-solution000007.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 2, 3, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_1_4.eprime b/tests/exhaustive/basic/comprehension_letting/expected/model_2_1_4.eprime new file mode 100644 index 0000000000..a9a3e9cd12 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_2_1_4.eprime @@ -0,0 +1,91 @@ +language ESSENCE' 1.0 + +find s_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +find s_Occurrence: matrix indexed by [int(1..4)] of bool +find s_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find s_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +letting let1 be -100 +find x: int(-100..100) +find conjure_aux1: int(-20..4) +branching on + [s_ExplicitVarSizeWithFlags_Flags, s_ExplicitVarSizeWithFlags_Values, s_ExplicitVarSizeWithDummy, s_Occurrence, x] +such that + and([and([s_ExplicitVarSizeWithDummy[q24] != 5, s_Occurrence[j], s_ExplicitVarSizeWithDummy[q24] != j, + allDiff([s_ExplicitVarSizeWithDummy[q24] + j, s_ExplicitVarSizeWithDummy[q24] * j, + s_ExplicitVarSizeWithDummy[q24] / j; + int(1..3)]), + (s_ExplicitVarSizeWithDummy[q24] - j) % 2 = 0; + int(1..5)]) + -> + min([s_ExplicitVarSizeWithDummy[q24] + j, s_ExplicitVarSizeWithDummy[q24] - j, + s_ExplicitVarSizeWithDummy[q24] * j, s_ExplicitVarSizeWithDummy[q24] / j; + int(1..4)]) + <= conjure_aux1 + | q24 : int(1..4), j : int(1..4)]), + sum([toInt(and([s_ExplicitVarSizeWithDummy[q24] != 5, s_Occurrence[j], s_ExplicitVarSizeWithDummy[q24] != j, + allDiff([s_ExplicitVarSizeWithDummy[q24] + j, s_ExplicitVarSizeWithDummy[q24] * j, + s_ExplicitVarSizeWithDummy[q24] / j; + int(1..3)]), + (s_ExplicitVarSizeWithDummy[q24] - j) % 2 = 0; + int(1..5)])) + | q24 : int(1..4), j : int(1..4)]) + > 0 + -> + or([and([s_ExplicitVarSizeWithDummy[q24] != 5, s_Occurrence[j], s_ExplicitVarSizeWithDummy[q24] != j, + allDiff([s_ExplicitVarSizeWithDummy[q24] + j, s_ExplicitVarSizeWithDummy[q24] * j, + s_ExplicitVarSizeWithDummy[q24] / j; + int(1..3)]), + (s_ExplicitVarSizeWithDummy[q24] - j) % 2 = 0; + int(1..5)]) + /\ + min([s_ExplicitVarSizeWithDummy[q24] + j, s_ExplicitVarSizeWithDummy[q24] - j, + s_ExplicitVarSizeWithDummy[q24] * j, s_ExplicitVarSizeWithDummy[q24] / j; + int(1..4)]) + = conjure_aux1 + | q24 : int(1..4), j : int(1..4)]), + sum([toInt(and([s_ExplicitVarSizeWithDummy[q24] != 5, s_Occurrence[j], s_ExplicitVarSizeWithDummy[q24] != j, + allDiff([s_ExplicitVarSizeWithDummy[q24] + j, s_ExplicitVarSizeWithDummy[q24] * j, + s_ExplicitVarSizeWithDummy[q24] / j; + int(1..3)]), + (s_ExplicitVarSizeWithDummy[q24] - j) % 2 = 0; + int(1..5)])) + | q24 : int(1..4), j : int(1..4)]) + = 0 + -> conjure_aux1 = -20, + x = conjure_aux1, + sum([toInt(and([s_ExplicitVarSizeWithDummy[q24] != 5, s_Occurrence[j], s_ExplicitVarSizeWithDummy[q24] != j, + allDiff([s_ExplicitVarSizeWithDummy[q24] + j, s_ExplicitVarSizeWithDummy[q24] * j, + s_ExplicitVarSizeWithDummy[q24] / j; + int(1..3)]), + (s_ExplicitVarSizeWithDummy[q24] - j) % 2 = 0; + int(1..5)])) + | q24 : int(1..4), j : int(1..4)]) + > 0, + and([s_ExplicitVarSizeWithDummy[q1] < s_ExplicitVarSizeWithDummy[q1 + 1] \/ s_ExplicitVarSizeWithDummy[q1] = 5 + | q1 : int(1..3)]), + and([s_ExplicitVarSizeWithDummy[q2] = 5 -> s_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..3)]), + and([s_Occurrence[q46] -> + or([s_ExplicitVarSizeWithDummy[q48] != 5 /\ s_ExplicitVarSizeWithDummy[q48] = q46 | q48 : int(1..4)]) + | q46 : int(1..4)]), + and([s_ExplicitVarSizeWithDummy[q50] != 5 -> s_Occurrence[s_ExplicitVarSizeWithDummy[q50]] | q50 : int(1..4)]), + and([s_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> + s_ExplicitVarSizeWithFlags_Values[q6] < s_ExplicitVarSizeWithFlags_Values[q6 + 1] + | q6 : int(1..3)]), + and([s_ExplicitVarSizeWithFlags_Flags[q7] = false -> s_ExplicitVarSizeWithFlags_Values[q7] = 1 | q7 : int(1..4)]), + and([s_ExplicitVarSizeWithFlags_Flags[q8 + 1] -> s_ExplicitVarSizeWithFlags_Flags[q8] | q8 : int(1..3)]), + and([s_ExplicitVarSizeWithFlags_Flags[q12] -> + or([s_ExplicitVarSizeWithDummy[q14] != 5 /\ + s_ExplicitVarSizeWithDummy[q14] = s_ExplicitVarSizeWithFlags_Values[q12] + | q14 : int(1..4)]) + | q12 : int(1..4)]), + and([s_ExplicitVarSizeWithDummy[q16] != 5 -> + or([s_ExplicitVarSizeWithFlags_Flags[q18] /\ + s_ExplicitVarSizeWithFlags_Values[q18] = s_ExplicitVarSizeWithDummy[q16] + | q18 : int(1..4)]) + | q16 : int(1..4)]), + and([s_ExplicitVarSizeWithFlags_Flags[q20] -> s_Occurrence[s_ExplicitVarSizeWithFlags_Values[q20]] + | q20 : int(1..4)]), + and([s_Occurrence[q21] -> + or([s_ExplicitVarSizeWithFlags_Flags[q23] /\ s_ExplicitVarSizeWithFlags_Values[q23] = q21 | q23 : int(1..4)]) + | q21 : int(1..4)]) + diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_1-solution000001.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_1-solution000001.solution new file mode 100644 index 0000000000..159a613983 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {2, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_1-solution000002.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_1-solution000002.solution new file mode 100644 index 0000000000..40f3fd5c8f --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_1-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {2, 3, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_1-solution000003.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_1-solution000003.solution new file mode 100644 index 0000000000..8b4ecbb66d --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_1-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 3} +letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_1-solution000004.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_1-solution000004.solution new file mode 100644 index 0000000000..560dd0f2f7 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_1-solution000004.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 3, 4} +letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_1-solution000005.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_1-solution000005.solution new file mode 100644 index 0000000000..6eeacc9727 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_1-solution000005.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 2, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_1-solution000006.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_1-solution000006.solution new file mode 100644 index 0000000000..5963aac565 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_1-solution000006.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 2, 3} +letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_1-solution000007.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_1-solution000007.solution new file mode 100644 index 0000000000..bd956f44e3 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_1-solution000007.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 2, 3, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_1.eprime b/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_1.eprime new file mode 100644 index 0000000000..5d253068bc --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_1.eprime @@ -0,0 +1,82 @@ +language ESSENCE' 1.0 + +find s_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +find s_Occurrence: matrix indexed by [int(1..4)] of bool +letting let1 be -100 +find x: int(-100..100) +find conjure_aux1: int(-25..4) +branching on [s_Occurrence, s_ExplicitVarSizeWithDummy, x] +such that + and([and([s_ExplicitVarSizeWithDummy[q6] != 5, s_ExplicitVarSizeWithDummy[q7] != 5, + s_ExplicitVarSizeWithDummy[q6] != s_ExplicitVarSizeWithDummy[q7], + allDiff([s_ExplicitVarSizeWithDummy[q6] + s_ExplicitVarSizeWithDummy[q7], + s_ExplicitVarSizeWithDummy[q6] * s_ExplicitVarSizeWithDummy[q7], + s_ExplicitVarSizeWithDummy[q6] / s_ExplicitVarSizeWithDummy[q7]; + int(1..3)]), + (s_ExplicitVarSizeWithDummy[q6] - s_ExplicitVarSizeWithDummy[q7]) % 2 = 0; + int(1..5)]) + -> + min([s_ExplicitVarSizeWithDummy[q6] + s_ExplicitVarSizeWithDummy[q7], + s_ExplicitVarSizeWithDummy[q6] - s_ExplicitVarSizeWithDummy[q7], + s_ExplicitVarSizeWithDummy[q6] * s_ExplicitVarSizeWithDummy[q7], + s_ExplicitVarSizeWithDummy[q6] / s_ExplicitVarSizeWithDummy[q7]; + int(1..4)]) + <= conjure_aux1 + | q6 : int(1..4), q7 : int(1..4)]), + sum([toInt(and([s_ExplicitVarSizeWithDummy[q6] != 5, s_ExplicitVarSizeWithDummy[q7] != 5, + s_ExplicitVarSizeWithDummy[q6] != s_ExplicitVarSizeWithDummy[q7], + allDiff([s_ExplicitVarSizeWithDummy[q6] + s_ExplicitVarSizeWithDummy[q7], + s_ExplicitVarSizeWithDummy[q6] * s_ExplicitVarSizeWithDummy[q7], + s_ExplicitVarSizeWithDummy[q6] / s_ExplicitVarSizeWithDummy[q7]; + int(1..3)]), + (s_ExplicitVarSizeWithDummy[q6] - s_ExplicitVarSizeWithDummy[q7]) % 2 = 0; + int(1..5)])) + | q6 : int(1..4), q7 : int(1..4)]) + > 0 + -> + or([and([s_ExplicitVarSizeWithDummy[q6] != 5, s_ExplicitVarSizeWithDummy[q7] != 5, + s_ExplicitVarSizeWithDummy[q6] != s_ExplicitVarSizeWithDummy[q7], + allDiff([s_ExplicitVarSizeWithDummy[q6] + s_ExplicitVarSizeWithDummy[q7], + s_ExplicitVarSizeWithDummy[q6] * s_ExplicitVarSizeWithDummy[q7], + s_ExplicitVarSizeWithDummy[q6] / s_ExplicitVarSizeWithDummy[q7]; + int(1..3)]), + (s_ExplicitVarSizeWithDummy[q6] - s_ExplicitVarSizeWithDummy[q7]) % 2 = 0; + int(1..5)]) + /\ + min([s_ExplicitVarSizeWithDummy[q6] + s_ExplicitVarSizeWithDummy[q7], + s_ExplicitVarSizeWithDummy[q6] - s_ExplicitVarSizeWithDummy[q7], + s_ExplicitVarSizeWithDummy[q6] * s_ExplicitVarSizeWithDummy[q7], + s_ExplicitVarSizeWithDummy[q6] / s_ExplicitVarSizeWithDummy[q7]; + int(1..4)]) + = conjure_aux1 + | q6 : int(1..4), q7 : int(1..4)]), + sum([toInt(and([s_ExplicitVarSizeWithDummy[q6] != 5, s_ExplicitVarSizeWithDummy[q7] != 5, + s_ExplicitVarSizeWithDummy[q6] != s_ExplicitVarSizeWithDummy[q7], + allDiff([s_ExplicitVarSizeWithDummy[q6] + s_ExplicitVarSizeWithDummy[q7], + s_ExplicitVarSizeWithDummy[q6] * s_ExplicitVarSizeWithDummy[q7], + s_ExplicitVarSizeWithDummy[q6] / s_ExplicitVarSizeWithDummy[q7]; + int(1..3)]), + (s_ExplicitVarSizeWithDummy[q6] - s_ExplicitVarSizeWithDummy[q7]) % 2 = 0; + int(1..5)])) + | q6 : int(1..4), q7 : int(1..4)]) + = 0 + -> conjure_aux1 = -25, + x = conjure_aux1, + sum([toInt(and([s_ExplicitVarSizeWithDummy[q6] != 5, s_ExplicitVarSizeWithDummy[q7] != 5, + s_ExplicitVarSizeWithDummy[q6] != s_ExplicitVarSizeWithDummy[q7], + allDiff([s_ExplicitVarSizeWithDummy[q6] + s_ExplicitVarSizeWithDummy[q7], + s_ExplicitVarSizeWithDummy[q6] * s_ExplicitVarSizeWithDummy[q7], + s_ExplicitVarSizeWithDummy[q6] / s_ExplicitVarSizeWithDummy[q7]; + int(1..3)]), + (s_ExplicitVarSizeWithDummy[q6] - s_ExplicitVarSizeWithDummy[q7]) % 2 = 0; + int(1..5)])) + | q6 : int(1..4), q7 : int(1..4)]) + > 0, + and([s_ExplicitVarSizeWithDummy[q1] < s_ExplicitVarSizeWithDummy[q1 + 1] \/ s_ExplicitVarSizeWithDummy[q1] = 5 + | q1 : int(1..3)]), + and([s_ExplicitVarSizeWithDummy[q2] = 5 -> s_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..3)]), + and([s_Occurrence[q29] -> + or([s_ExplicitVarSizeWithDummy[q31] != 5 /\ s_ExplicitVarSizeWithDummy[q31] = q29 | q31 : int(1..4)]) + | q29 : int(1..4)]), + and([s_ExplicitVarSizeWithDummy[q33] != 5 -> s_Occurrence[s_ExplicitVarSizeWithDummy[q33]] | q33 : int(1..4)]) + diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_2-solution000001.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_2-solution000001.solution new file mode 100644 index 0000000000..bd956f44e3 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 2, 3, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_2-solution000002.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_2-solution000002.solution new file mode 100644 index 0000000000..5963aac565 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_2-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 2, 3} +letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_2-solution000003.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_2-solution000003.solution new file mode 100644 index 0000000000..6eeacc9727 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_2-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 2, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_2-solution000004.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_2-solution000004.solution new file mode 100644 index 0000000000..560dd0f2f7 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_2-solution000004.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 3, 4} +letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_2-solution000005.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_2-solution000005.solution new file mode 100644 index 0000000000..8b4ecbb66d --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_2-solution000005.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 3} +letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_2-solution000006.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_2-solution000006.solution new file mode 100644 index 0000000000..40f3fd5c8f --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_2-solution000006.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {2, 3, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_2-solution000007.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_2-solution000007.solution new file mode 100644 index 0000000000..159a613983 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_2-solution000007.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {2, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_2.eprime b/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_2.eprime new file mode 100644 index 0000000000..4e8c4bc4e7 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_2.eprime @@ -0,0 +1,77 @@ +language ESSENCE' 1.0 + +find s_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +letting let1 be -100 +find x: int(-100..100) +find conjure_aux1: int(-25..4) +branching on [s_ExplicitVarSizeWithDummy, x] +such that + and([and([s_ExplicitVarSizeWithDummy[q5] != 5, s_ExplicitVarSizeWithDummy[q6] != 5, + s_ExplicitVarSizeWithDummy[q5] != s_ExplicitVarSizeWithDummy[q6], + allDiff([s_ExplicitVarSizeWithDummy[q5] + s_ExplicitVarSizeWithDummy[q6], + s_ExplicitVarSizeWithDummy[q5] * s_ExplicitVarSizeWithDummy[q6], + s_ExplicitVarSizeWithDummy[q5] / s_ExplicitVarSizeWithDummy[q6]; + int(1..3)]), + (s_ExplicitVarSizeWithDummy[q5] - s_ExplicitVarSizeWithDummy[q6]) % 2 = 0; + int(1..5)]) + -> + min([s_ExplicitVarSizeWithDummy[q5] + s_ExplicitVarSizeWithDummy[q6], + s_ExplicitVarSizeWithDummy[q5] - s_ExplicitVarSizeWithDummy[q6], + s_ExplicitVarSizeWithDummy[q5] * s_ExplicitVarSizeWithDummy[q6], + s_ExplicitVarSizeWithDummy[q5] / s_ExplicitVarSizeWithDummy[q6]; + int(1..4)]) + <= conjure_aux1 + | q5 : int(1..4), q6 : int(1..4)]), + sum([toInt(and([s_ExplicitVarSizeWithDummy[q5] != 5, s_ExplicitVarSizeWithDummy[q6] != 5, + s_ExplicitVarSizeWithDummy[q5] != s_ExplicitVarSizeWithDummy[q6], + allDiff([s_ExplicitVarSizeWithDummy[q5] + s_ExplicitVarSizeWithDummy[q6], + s_ExplicitVarSizeWithDummy[q5] * s_ExplicitVarSizeWithDummy[q6], + s_ExplicitVarSizeWithDummy[q5] / s_ExplicitVarSizeWithDummy[q6]; + int(1..3)]), + (s_ExplicitVarSizeWithDummy[q5] - s_ExplicitVarSizeWithDummy[q6]) % 2 = 0; + int(1..5)])) + | q5 : int(1..4), q6 : int(1..4)]) + > 0 + -> + or([and([s_ExplicitVarSizeWithDummy[q5] != 5, s_ExplicitVarSizeWithDummy[q6] != 5, + s_ExplicitVarSizeWithDummy[q5] != s_ExplicitVarSizeWithDummy[q6], + allDiff([s_ExplicitVarSizeWithDummy[q5] + s_ExplicitVarSizeWithDummy[q6], + s_ExplicitVarSizeWithDummy[q5] * s_ExplicitVarSizeWithDummy[q6], + s_ExplicitVarSizeWithDummy[q5] / s_ExplicitVarSizeWithDummy[q6]; + int(1..3)]), + (s_ExplicitVarSizeWithDummy[q5] - s_ExplicitVarSizeWithDummy[q6]) % 2 = 0; + int(1..5)]) + /\ + min([s_ExplicitVarSizeWithDummy[q5] + s_ExplicitVarSizeWithDummy[q6], + s_ExplicitVarSizeWithDummy[q5] - s_ExplicitVarSizeWithDummy[q6], + s_ExplicitVarSizeWithDummy[q5] * s_ExplicitVarSizeWithDummy[q6], + s_ExplicitVarSizeWithDummy[q5] / s_ExplicitVarSizeWithDummy[q6]; + int(1..4)]) + = conjure_aux1 + | q5 : int(1..4), q6 : int(1..4)]), + sum([toInt(and([s_ExplicitVarSizeWithDummy[q5] != 5, s_ExplicitVarSizeWithDummy[q6] != 5, + s_ExplicitVarSizeWithDummy[q5] != s_ExplicitVarSizeWithDummy[q6], + allDiff([s_ExplicitVarSizeWithDummy[q5] + s_ExplicitVarSizeWithDummy[q6], + s_ExplicitVarSizeWithDummy[q5] * s_ExplicitVarSizeWithDummy[q6], + s_ExplicitVarSizeWithDummy[q5] / s_ExplicitVarSizeWithDummy[q6]; + int(1..3)]), + (s_ExplicitVarSizeWithDummy[q5] - s_ExplicitVarSizeWithDummy[q6]) % 2 = 0; + int(1..5)])) + | q5 : int(1..4), q6 : int(1..4)]) + = 0 + -> conjure_aux1 = -25, + x = conjure_aux1, + sum([toInt(and([s_ExplicitVarSizeWithDummy[q5] != 5, s_ExplicitVarSizeWithDummy[q6] != 5, + s_ExplicitVarSizeWithDummy[q5] != s_ExplicitVarSizeWithDummy[q6], + allDiff([s_ExplicitVarSizeWithDummy[q5] + s_ExplicitVarSizeWithDummy[q6], + s_ExplicitVarSizeWithDummy[q5] * s_ExplicitVarSizeWithDummy[q6], + s_ExplicitVarSizeWithDummy[q5] / s_ExplicitVarSizeWithDummy[q6]; + int(1..3)]), + (s_ExplicitVarSizeWithDummy[q5] - s_ExplicitVarSizeWithDummy[q6]) % 2 = 0; + int(1..5)])) + | q5 : int(1..4), q6 : int(1..4)]) + > 0, + and([s_ExplicitVarSizeWithDummy[q1] < s_ExplicitVarSizeWithDummy[q1 + 1] \/ s_ExplicitVarSizeWithDummy[q1] = 5 + | q1 : int(1..3)]), + and([s_ExplicitVarSizeWithDummy[q2] = 5 -> s_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..3)]) + diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_3-solution000001.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_3-solution000001.solution new file mode 100644 index 0000000000..8b4ecbb66d --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_3-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 3} +letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_3-solution000002.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_3-solution000002.solution new file mode 100644 index 0000000000..159a613983 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_3-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {2, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_3-solution000003.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_3-solution000003.solution new file mode 100644 index 0000000000..5963aac565 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_3-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 2, 3} +letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_3-solution000004.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_3-solution000004.solution new file mode 100644 index 0000000000..6eeacc9727 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_3-solution000004.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 2, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_3-solution000005.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_3-solution000005.solution new file mode 100644 index 0000000000..560dd0f2f7 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_3-solution000005.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 3, 4} +letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_3-solution000006.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_3-solution000006.solution new file mode 100644 index 0000000000..40f3fd5c8f --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_3-solution000006.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {2, 3, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_3-solution000007.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_3-solution000007.solution new file mode 100644 index 0000000000..bd956f44e3 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_3-solution000007.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 2, 3, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_3.eprime b/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_3.eprime new file mode 100644 index 0000000000..6d91904813 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_3.eprime @@ -0,0 +1,93 @@ +language ESSENCE' 1.0 + +find s_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +find s_ExplicitVarSizeWithMarker_Marker: int(0..4) +find s_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +letting let1 be -100 +find x: int(-100..100) +find conjure_aux1: int(-25..4) +branching on [s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithMarker_Values, s_ExplicitVarSizeWithDummy, x] +such that + and([and([s_ExplicitVarSizeWithDummy[q16] != 5, s_ExplicitVarSizeWithDummy[q17] != 5, + s_ExplicitVarSizeWithDummy[q16] != s_ExplicitVarSizeWithDummy[q17], + allDiff([s_ExplicitVarSizeWithDummy[q16] + s_ExplicitVarSizeWithDummy[q17], + s_ExplicitVarSizeWithDummy[q16] * s_ExplicitVarSizeWithDummy[q17], + s_ExplicitVarSizeWithDummy[q16] / s_ExplicitVarSizeWithDummy[q17]; + int(1..3)]), + (s_ExplicitVarSizeWithDummy[q16] - s_ExplicitVarSizeWithDummy[q17]) % 2 = 0; + int(1..5)]) + -> + min([s_ExplicitVarSizeWithDummy[q16] + s_ExplicitVarSizeWithDummy[q17], + s_ExplicitVarSizeWithDummy[q16] - s_ExplicitVarSizeWithDummy[q17], + s_ExplicitVarSizeWithDummy[q16] * s_ExplicitVarSizeWithDummy[q17], + s_ExplicitVarSizeWithDummy[q16] / s_ExplicitVarSizeWithDummy[q17]; + int(1..4)]) + <= conjure_aux1 + | q16 : int(1..4), q17 : int(1..4)]), + sum([toInt(and([s_ExplicitVarSizeWithDummy[q16] != 5, s_ExplicitVarSizeWithDummy[q17] != 5, + s_ExplicitVarSizeWithDummy[q16] != s_ExplicitVarSizeWithDummy[q17], + allDiff([s_ExplicitVarSizeWithDummy[q16] + s_ExplicitVarSizeWithDummy[q17], + s_ExplicitVarSizeWithDummy[q16] * s_ExplicitVarSizeWithDummy[q17], + s_ExplicitVarSizeWithDummy[q16] / s_ExplicitVarSizeWithDummy[q17]; + int(1..3)]), + (s_ExplicitVarSizeWithDummy[q16] - s_ExplicitVarSizeWithDummy[q17]) % 2 = 0; + int(1..5)])) + | q16 : int(1..4), q17 : int(1..4)]) + > 0 + -> + or([and([s_ExplicitVarSizeWithDummy[q16] != 5, s_ExplicitVarSizeWithDummy[q17] != 5, + s_ExplicitVarSizeWithDummy[q16] != s_ExplicitVarSizeWithDummy[q17], + allDiff([s_ExplicitVarSizeWithDummy[q16] + s_ExplicitVarSizeWithDummy[q17], + s_ExplicitVarSizeWithDummy[q16] * s_ExplicitVarSizeWithDummy[q17], + s_ExplicitVarSizeWithDummy[q16] / s_ExplicitVarSizeWithDummy[q17]; + int(1..3)]), + (s_ExplicitVarSizeWithDummy[q16] - s_ExplicitVarSizeWithDummy[q17]) % 2 = 0; + int(1..5)]) + /\ + min([s_ExplicitVarSizeWithDummy[q16] + s_ExplicitVarSizeWithDummy[q17], + s_ExplicitVarSizeWithDummy[q16] - s_ExplicitVarSizeWithDummy[q17], + s_ExplicitVarSizeWithDummy[q16] * s_ExplicitVarSizeWithDummy[q17], + s_ExplicitVarSizeWithDummy[q16] / s_ExplicitVarSizeWithDummy[q17]; + int(1..4)]) + = conjure_aux1 + | q16 : int(1..4), q17 : int(1..4)]), + sum([toInt(and([s_ExplicitVarSizeWithDummy[q16] != 5, s_ExplicitVarSizeWithDummy[q17] != 5, + s_ExplicitVarSizeWithDummy[q16] != s_ExplicitVarSizeWithDummy[q17], + allDiff([s_ExplicitVarSizeWithDummy[q16] + s_ExplicitVarSizeWithDummy[q17], + s_ExplicitVarSizeWithDummy[q16] * s_ExplicitVarSizeWithDummy[q17], + s_ExplicitVarSizeWithDummy[q16] / s_ExplicitVarSizeWithDummy[q17]; + int(1..3)]), + (s_ExplicitVarSizeWithDummy[q16] - s_ExplicitVarSizeWithDummy[q17]) % 2 = 0; + int(1..5)])) + | q16 : int(1..4), q17 : int(1..4)]) + = 0 + -> conjure_aux1 = -25, + x = conjure_aux1, + sum([toInt(and([s_ExplicitVarSizeWithDummy[q16] != 5, s_ExplicitVarSizeWithDummy[q17] != 5, + s_ExplicitVarSizeWithDummy[q16] != s_ExplicitVarSizeWithDummy[q17], + allDiff([s_ExplicitVarSizeWithDummy[q16] + s_ExplicitVarSizeWithDummy[q17], + s_ExplicitVarSizeWithDummy[q16] * s_ExplicitVarSizeWithDummy[q17], + s_ExplicitVarSizeWithDummy[q16] / s_ExplicitVarSizeWithDummy[q17]; + int(1..3)]), + (s_ExplicitVarSizeWithDummy[q16] - s_ExplicitVarSizeWithDummy[q17]) % 2 = 0; + int(1..5)])) + | q16 : int(1..4), q17 : int(1..4)]) + > 0, + and([s_ExplicitVarSizeWithDummy[q1] < s_ExplicitVarSizeWithDummy[q1 + 1] \/ s_ExplicitVarSizeWithDummy[q1] = 5 + | q1 : int(1..3)]), + and([s_ExplicitVarSizeWithDummy[q2] = 5 -> s_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..3)]), + and([q5 + 1 <= s_ExplicitVarSizeWithMarker_Marker -> + s_ExplicitVarSizeWithMarker_Values[q5] < s_ExplicitVarSizeWithMarker_Values[q5 + 1] + | q5 : int(1..3)]), + and([q6 > s_ExplicitVarSizeWithMarker_Marker -> s_ExplicitVarSizeWithMarker_Values[q6] = 1 | q6 : int(1..4)]), + and([q9 <= s_ExplicitVarSizeWithMarker_Marker -> + or([s_ExplicitVarSizeWithDummy[q11] != 5 /\ + s_ExplicitVarSizeWithDummy[q11] = s_ExplicitVarSizeWithMarker_Values[q9] + | q11 : int(1..4)]) + | q9 : int(1..4)]), + and([s_ExplicitVarSizeWithDummy[q13] != 5 -> + or([q15 <= s_ExplicitVarSizeWithMarker_Marker /\ + s_ExplicitVarSizeWithMarker_Values[q15] = s_ExplicitVarSizeWithDummy[q13] + | q15 : int(1..4)]) + | q13 : int(1..4)]) + diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_4-solution000001.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_4-solution000001.solution new file mode 100644 index 0000000000..8b4ecbb66d --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_4-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 3} +letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_4-solution000002.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_4-solution000002.solution new file mode 100644 index 0000000000..159a613983 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_4-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {2, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_4-solution000003.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_4-solution000003.solution new file mode 100644 index 0000000000..5963aac565 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_4-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 2, 3} +letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_4-solution000004.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_4-solution000004.solution new file mode 100644 index 0000000000..6eeacc9727 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_4-solution000004.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 2, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_4-solution000005.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_4-solution000005.solution new file mode 100644 index 0000000000..560dd0f2f7 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_4-solution000005.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 3, 4} +letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_4-solution000006.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_4-solution000006.solution new file mode 100644 index 0000000000..40f3fd5c8f --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_4-solution000006.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {2, 3, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_4-solution000007.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_4-solution000007.solution new file mode 100644 index 0000000000..bd956f44e3 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_4-solution000007.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 2, 3, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_4.eprime b/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_4.eprime new file mode 100644 index 0000000000..3627386375 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_2_2_4.eprime @@ -0,0 +1,94 @@ +language ESSENCE' 1.0 + +find s_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +find s_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find s_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +letting let1 be -100 +find x: int(-100..100) +find conjure_aux1: int(-25..4) +branching on [s_ExplicitVarSizeWithFlags_Flags, s_ExplicitVarSizeWithFlags_Values, s_ExplicitVarSizeWithDummy, x] +such that + and([and([s_ExplicitVarSizeWithDummy[q18] != 5, s_ExplicitVarSizeWithDummy[q19] != 5, + s_ExplicitVarSizeWithDummy[q18] != s_ExplicitVarSizeWithDummy[q19], + allDiff([s_ExplicitVarSizeWithDummy[q18] + s_ExplicitVarSizeWithDummy[q19], + s_ExplicitVarSizeWithDummy[q18] * s_ExplicitVarSizeWithDummy[q19], + s_ExplicitVarSizeWithDummy[q18] / s_ExplicitVarSizeWithDummy[q19]; + int(1..3)]), + (s_ExplicitVarSizeWithDummy[q18] - s_ExplicitVarSizeWithDummy[q19]) % 2 = 0; + int(1..5)]) + -> + min([s_ExplicitVarSizeWithDummy[q18] + s_ExplicitVarSizeWithDummy[q19], + s_ExplicitVarSizeWithDummy[q18] - s_ExplicitVarSizeWithDummy[q19], + s_ExplicitVarSizeWithDummy[q18] * s_ExplicitVarSizeWithDummy[q19], + s_ExplicitVarSizeWithDummy[q18] / s_ExplicitVarSizeWithDummy[q19]; + int(1..4)]) + <= conjure_aux1 + | q18 : int(1..4), q19 : int(1..4)]), + sum([toInt(and([s_ExplicitVarSizeWithDummy[q18] != 5, s_ExplicitVarSizeWithDummy[q19] != 5, + s_ExplicitVarSizeWithDummy[q18] != s_ExplicitVarSizeWithDummy[q19], + allDiff([s_ExplicitVarSizeWithDummy[q18] + s_ExplicitVarSizeWithDummy[q19], + s_ExplicitVarSizeWithDummy[q18] * s_ExplicitVarSizeWithDummy[q19], + s_ExplicitVarSizeWithDummy[q18] / s_ExplicitVarSizeWithDummy[q19]; + int(1..3)]), + (s_ExplicitVarSizeWithDummy[q18] - s_ExplicitVarSizeWithDummy[q19]) % 2 = 0; + int(1..5)])) + | q18 : int(1..4), q19 : int(1..4)]) + > 0 + -> + or([and([s_ExplicitVarSizeWithDummy[q18] != 5, s_ExplicitVarSizeWithDummy[q19] != 5, + s_ExplicitVarSizeWithDummy[q18] != s_ExplicitVarSizeWithDummy[q19], + allDiff([s_ExplicitVarSizeWithDummy[q18] + s_ExplicitVarSizeWithDummy[q19], + s_ExplicitVarSizeWithDummy[q18] * s_ExplicitVarSizeWithDummy[q19], + s_ExplicitVarSizeWithDummy[q18] / s_ExplicitVarSizeWithDummy[q19]; + int(1..3)]), + (s_ExplicitVarSizeWithDummy[q18] - s_ExplicitVarSizeWithDummy[q19]) % 2 = 0; + int(1..5)]) + /\ + min([s_ExplicitVarSizeWithDummy[q18] + s_ExplicitVarSizeWithDummy[q19], + s_ExplicitVarSizeWithDummy[q18] - s_ExplicitVarSizeWithDummy[q19], + s_ExplicitVarSizeWithDummy[q18] * s_ExplicitVarSizeWithDummy[q19], + s_ExplicitVarSizeWithDummy[q18] / s_ExplicitVarSizeWithDummy[q19]; + int(1..4)]) + = conjure_aux1 + | q18 : int(1..4), q19 : int(1..4)]), + sum([toInt(and([s_ExplicitVarSizeWithDummy[q18] != 5, s_ExplicitVarSizeWithDummy[q19] != 5, + s_ExplicitVarSizeWithDummy[q18] != s_ExplicitVarSizeWithDummy[q19], + allDiff([s_ExplicitVarSizeWithDummy[q18] + s_ExplicitVarSizeWithDummy[q19], + s_ExplicitVarSizeWithDummy[q18] * s_ExplicitVarSizeWithDummy[q19], + s_ExplicitVarSizeWithDummy[q18] / s_ExplicitVarSizeWithDummy[q19]; + int(1..3)]), + (s_ExplicitVarSizeWithDummy[q18] - s_ExplicitVarSizeWithDummy[q19]) % 2 = 0; + int(1..5)])) + | q18 : int(1..4), q19 : int(1..4)]) + = 0 + -> conjure_aux1 = -25, + x = conjure_aux1, + sum([toInt(and([s_ExplicitVarSizeWithDummy[q18] != 5, s_ExplicitVarSizeWithDummy[q19] != 5, + s_ExplicitVarSizeWithDummy[q18] != s_ExplicitVarSizeWithDummy[q19], + allDiff([s_ExplicitVarSizeWithDummy[q18] + s_ExplicitVarSizeWithDummy[q19], + s_ExplicitVarSizeWithDummy[q18] * s_ExplicitVarSizeWithDummy[q19], + s_ExplicitVarSizeWithDummy[q18] / s_ExplicitVarSizeWithDummy[q19]; + int(1..3)]), + (s_ExplicitVarSizeWithDummy[q18] - s_ExplicitVarSizeWithDummy[q19]) % 2 = 0; + int(1..5)])) + | q18 : int(1..4), q19 : int(1..4)]) + > 0, + and([s_ExplicitVarSizeWithDummy[q1] < s_ExplicitVarSizeWithDummy[q1 + 1] \/ s_ExplicitVarSizeWithDummy[q1] = 5 + | q1 : int(1..3)]), + and([s_ExplicitVarSizeWithDummy[q2] = 5 -> s_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..3)]), + and([s_ExplicitVarSizeWithFlags_Flags[q5 + 1] -> + s_ExplicitVarSizeWithFlags_Values[q5] < s_ExplicitVarSizeWithFlags_Values[q5 + 1] + | q5 : int(1..3)]), + and([s_ExplicitVarSizeWithFlags_Flags[q6] = false -> s_ExplicitVarSizeWithFlags_Values[q6] = 1 | q6 : int(1..4)]), + and([s_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> s_ExplicitVarSizeWithFlags_Flags[q7] | q7 : int(1..3)]), + and([s_ExplicitVarSizeWithFlags_Flags[q11] -> + or([s_ExplicitVarSizeWithDummy[q13] != 5 /\ + s_ExplicitVarSizeWithDummy[q13] = s_ExplicitVarSizeWithFlags_Values[q11] + | q13 : int(1..4)]) + | q11 : int(1..4)]), + and([s_ExplicitVarSizeWithDummy[q15] != 5 -> + or([s_ExplicitVarSizeWithFlags_Flags[q17] /\ + s_ExplicitVarSizeWithFlags_Values[q17] = s_ExplicitVarSizeWithDummy[q15] + | q17 : int(1..4)]) + | q15 : int(1..4)]) + diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_3_1-solution000001.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_3_1-solution000001.solution new file mode 100644 index 0000000000..159a613983 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_2_3_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {2, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_3_1-solution000002.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_3_1-solution000002.solution new file mode 100644 index 0000000000..40f3fd5c8f --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_2_3_1-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {2, 3, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_3_1-solution000003.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_3_1-solution000003.solution new file mode 100644 index 0000000000..8b4ecbb66d --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_2_3_1-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 3} +letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_3_1-solution000004.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_3_1-solution000004.solution new file mode 100644 index 0000000000..560dd0f2f7 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_2_3_1-solution000004.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 3, 4} +letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_3_1-solution000005.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_3_1-solution000005.solution new file mode 100644 index 0000000000..6eeacc9727 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_2_3_1-solution000005.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 2, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_3_1-solution000006.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_3_1-solution000006.solution new file mode 100644 index 0000000000..5963aac565 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_2_3_1-solution000006.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 2, 3} +letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_3_1-solution000007.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_3_1-solution000007.solution new file mode 100644 index 0000000000..bd956f44e3 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_2_3_1-solution000007.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 2, 3, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_3_1.eprime b/tests/exhaustive/basic/comprehension_letting/expected/model_2_3_1.eprime new file mode 100644 index 0000000000..2b18a316f8 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_2_3_1.eprime @@ -0,0 +1,106 @@ +language ESSENCE' 1.0 + +find s_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +find s_ExplicitVarSizeWithMarker_Marker: int(0..4) +find s_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +find s_Occurrence: matrix indexed by [int(1..4)] of bool +letting let1 be -100 +find x: int(-100..100) +find conjure_aux1: int(-20..4) +branching on + [s_Occurrence, s_ExplicitVarSizeWithDummy, s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithMarker_Values, + x] +such that + and([and([s_ExplicitVarSizeWithDummy[q17] != 5, q18 <= s_ExplicitVarSizeWithMarker_Marker, + s_ExplicitVarSizeWithDummy[q17] != s_ExplicitVarSizeWithMarker_Values[q18], + allDiff([s_ExplicitVarSizeWithDummy[q17] + s_ExplicitVarSizeWithMarker_Values[q18], + s_ExplicitVarSizeWithDummy[q17] * s_ExplicitVarSizeWithMarker_Values[q18], + s_ExplicitVarSizeWithDummy[q17] / s_ExplicitVarSizeWithMarker_Values[q18]; + int(1..3)]), + (s_ExplicitVarSizeWithDummy[q17] - s_ExplicitVarSizeWithMarker_Values[q18]) % 2 = 0; + int(1..5)]) + -> + min([s_ExplicitVarSizeWithDummy[q17] + s_ExplicitVarSizeWithMarker_Values[q18], + s_ExplicitVarSizeWithDummy[q17] - s_ExplicitVarSizeWithMarker_Values[q18], + s_ExplicitVarSizeWithDummy[q17] * s_ExplicitVarSizeWithMarker_Values[q18], + s_ExplicitVarSizeWithDummy[q17] / s_ExplicitVarSizeWithMarker_Values[q18]; + int(1..4)]) + <= conjure_aux1 + | q17 : int(1..4), q18 : int(1..4)]), + sum([toInt(and([s_ExplicitVarSizeWithDummy[q17] != 5, q18 <= s_ExplicitVarSizeWithMarker_Marker, + s_ExplicitVarSizeWithDummy[q17] != s_ExplicitVarSizeWithMarker_Values[q18], + allDiff([s_ExplicitVarSizeWithDummy[q17] + s_ExplicitVarSizeWithMarker_Values[q18], + s_ExplicitVarSizeWithDummy[q17] * s_ExplicitVarSizeWithMarker_Values[q18], + s_ExplicitVarSizeWithDummy[q17] / s_ExplicitVarSizeWithMarker_Values[q18]; + int(1..3)]), + (s_ExplicitVarSizeWithDummy[q17] - s_ExplicitVarSizeWithMarker_Values[q18]) % 2 = 0; + int(1..5)])) + | q17 : int(1..4), q18 : int(1..4)]) + > 0 + -> + or([and([s_ExplicitVarSizeWithDummy[q17] != 5, q18 <= s_ExplicitVarSizeWithMarker_Marker, + s_ExplicitVarSizeWithDummy[q17] != s_ExplicitVarSizeWithMarker_Values[q18], + allDiff([s_ExplicitVarSizeWithDummy[q17] + s_ExplicitVarSizeWithMarker_Values[q18], + s_ExplicitVarSizeWithDummy[q17] * s_ExplicitVarSizeWithMarker_Values[q18], + s_ExplicitVarSizeWithDummy[q17] / s_ExplicitVarSizeWithMarker_Values[q18]; + int(1..3)]), + (s_ExplicitVarSizeWithDummy[q17] - s_ExplicitVarSizeWithMarker_Values[q18]) % 2 = 0; + int(1..5)]) + /\ + min([s_ExplicitVarSizeWithDummy[q17] + s_ExplicitVarSizeWithMarker_Values[q18], + s_ExplicitVarSizeWithDummy[q17] - s_ExplicitVarSizeWithMarker_Values[q18], + s_ExplicitVarSizeWithDummy[q17] * s_ExplicitVarSizeWithMarker_Values[q18], + s_ExplicitVarSizeWithDummy[q17] / s_ExplicitVarSizeWithMarker_Values[q18]; + int(1..4)]) + = conjure_aux1 + | q17 : int(1..4), q18 : int(1..4)]), + sum([toInt(and([s_ExplicitVarSizeWithDummy[q17] != 5, q18 <= s_ExplicitVarSizeWithMarker_Marker, + s_ExplicitVarSizeWithDummy[q17] != s_ExplicitVarSizeWithMarker_Values[q18], + allDiff([s_ExplicitVarSizeWithDummy[q17] + s_ExplicitVarSizeWithMarker_Values[q18], + s_ExplicitVarSizeWithDummy[q17] * s_ExplicitVarSizeWithMarker_Values[q18], + s_ExplicitVarSizeWithDummy[q17] / s_ExplicitVarSizeWithMarker_Values[q18]; + int(1..3)]), + (s_ExplicitVarSizeWithDummy[q17] - s_ExplicitVarSizeWithMarker_Values[q18]) % 2 = 0; + int(1..5)])) + | q17 : int(1..4), q18 : int(1..4)]) + = 0 + -> conjure_aux1 = -20, + x = conjure_aux1, + sum([toInt(and([s_ExplicitVarSizeWithDummy[q17] != 5, q18 <= s_ExplicitVarSizeWithMarker_Marker, + s_ExplicitVarSizeWithDummy[q17] != s_ExplicitVarSizeWithMarker_Values[q18], + allDiff([s_ExplicitVarSizeWithDummy[q17] + s_ExplicitVarSizeWithMarker_Values[q18], + s_ExplicitVarSizeWithDummy[q17] * s_ExplicitVarSizeWithMarker_Values[q18], + s_ExplicitVarSizeWithDummy[q17] / s_ExplicitVarSizeWithMarker_Values[q18]; + int(1..3)]), + (s_ExplicitVarSizeWithDummy[q17] - s_ExplicitVarSizeWithMarker_Values[q18]) % 2 = 0; + int(1..5)])) + | q17 : int(1..4), q18 : int(1..4)]) + > 0, + and([s_ExplicitVarSizeWithDummy[q1] < s_ExplicitVarSizeWithDummy[q1 + 1] \/ s_ExplicitVarSizeWithDummy[q1] = 5 + | q1 : int(1..3)]), + and([s_ExplicitVarSizeWithDummy[q2] = 5 -> s_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..3)]), + and([q5 + 1 <= s_ExplicitVarSizeWithMarker_Marker -> + s_ExplicitVarSizeWithMarker_Values[q5] < s_ExplicitVarSizeWithMarker_Values[q5 + 1] + | q5 : int(1..3)]), + and([q6 > s_ExplicitVarSizeWithMarker_Marker -> s_ExplicitVarSizeWithMarker_Values[q6] = 1 | q6 : int(1..4)]), + and([q9 <= s_ExplicitVarSizeWithMarker_Marker -> + or([s_ExplicitVarSizeWithDummy[q11] != 5 /\ + s_ExplicitVarSizeWithDummy[q11] = s_ExplicitVarSizeWithMarker_Values[q9] + | q11 : int(1..4)]) + | q9 : int(1..4)]), + and([s_ExplicitVarSizeWithDummy[q13] != 5 -> + or([q15 <= s_ExplicitVarSizeWithMarker_Marker /\ + s_ExplicitVarSizeWithMarker_Values[q15] = s_ExplicitVarSizeWithDummy[q13] + | q15 : int(1..4)]) + | q13 : int(1..4)]), + and([s_Occurrence[q40] -> + or([s_ExplicitVarSizeWithDummy[q42] != 5 /\ s_ExplicitVarSizeWithDummy[q42] = q40 | q42 : int(1..4)]) + | q40 : int(1..4)]), + and([s_ExplicitVarSizeWithDummy[q44] != 5 -> s_Occurrence[s_ExplicitVarSizeWithDummy[q44]] | q44 : int(1..4)]), + and([s_Occurrence[q45] -> + or([q47 <= s_ExplicitVarSizeWithMarker_Marker /\ s_ExplicitVarSizeWithMarker_Values[q47] = q45 + | q47 : int(1..4)]) + | q45 : int(1..4)]), + and([q49 <= s_ExplicitVarSizeWithMarker_Marker -> s_Occurrence[s_ExplicitVarSizeWithMarker_Values[q49]] + | q49 : int(1..4)]) + diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_3_2-solution000001.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_3_2-solution000001.solution new file mode 100644 index 0000000000..8b4ecbb66d --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_2_3_2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 3} +letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_3_2-solution000002.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_3_2-solution000002.solution new file mode 100644 index 0000000000..159a613983 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_2_3_2-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {2, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_3_2-solution000003.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_3_2-solution000003.solution new file mode 100644 index 0000000000..5963aac565 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_2_3_2-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 2, 3} +letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_3_2-solution000004.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_3_2-solution000004.solution new file mode 100644 index 0000000000..6eeacc9727 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_2_3_2-solution000004.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 2, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_3_2-solution000005.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_3_2-solution000005.solution new file mode 100644 index 0000000000..560dd0f2f7 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_2_3_2-solution000005.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 3, 4} +letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_3_2-solution000006.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_3_2-solution000006.solution new file mode 100644 index 0000000000..40f3fd5c8f --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_2_3_2-solution000006.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {2, 3, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_3_2-solution000007.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_3_2-solution000007.solution new file mode 100644 index 0000000000..bd956f44e3 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_2_3_2-solution000007.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 2, 3, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_3_2.eprime b/tests/exhaustive/basic/comprehension_letting/expected/model_2_3_2.eprime new file mode 100644 index 0000000000..6bede9f96d --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_2_3_2.eprime @@ -0,0 +1,93 @@ +language ESSENCE' 1.0 + +find s_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +find s_ExplicitVarSizeWithMarker_Marker: int(0..4) +find s_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +letting let1 be -100 +find x: int(-100..100) +find conjure_aux1: int(-20..4) +branching on [s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithMarker_Values, s_ExplicitVarSizeWithDummy, x] +such that + and([and([s_ExplicitVarSizeWithDummy[q16] != 5, q17 <= s_ExplicitVarSizeWithMarker_Marker, + s_ExplicitVarSizeWithDummy[q16] != s_ExplicitVarSizeWithMarker_Values[q17], + allDiff([s_ExplicitVarSizeWithDummy[q16] + s_ExplicitVarSizeWithMarker_Values[q17], + s_ExplicitVarSizeWithDummy[q16] * s_ExplicitVarSizeWithMarker_Values[q17], + s_ExplicitVarSizeWithDummy[q16] / s_ExplicitVarSizeWithMarker_Values[q17]; + int(1..3)]), + (s_ExplicitVarSizeWithDummy[q16] - s_ExplicitVarSizeWithMarker_Values[q17]) % 2 = 0; + int(1..5)]) + -> + min([s_ExplicitVarSizeWithDummy[q16] + s_ExplicitVarSizeWithMarker_Values[q17], + s_ExplicitVarSizeWithDummy[q16] - s_ExplicitVarSizeWithMarker_Values[q17], + s_ExplicitVarSizeWithDummy[q16] * s_ExplicitVarSizeWithMarker_Values[q17], + s_ExplicitVarSizeWithDummy[q16] / s_ExplicitVarSizeWithMarker_Values[q17]; + int(1..4)]) + <= conjure_aux1 + | q16 : int(1..4), q17 : int(1..4)]), + sum([toInt(and([s_ExplicitVarSizeWithDummy[q16] != 5, q17 <= s_ExplicitVarSizeWithMarker_Marker, + s_ExplicitVarSizeWithDummy[q16] != s_ExplicitVarSizeWithMarker_Values[q17], + allDiff([s_ExplicitVarSizeWithDummy[q16] + s_ExplicitVarSizeWithMarker_Values[q17], + s_ExplicitVarSizeWithDummy[q16] * s_ExplicitVarSizeWithMarker_Values[q17], + s_ExplicitVarSizeWithDummy[q16] / s_ExplicitVarSizeWithMarker_Values[q17]; + int(1..3)]), + (s_ExplicitVarSizeWithDummy[q16] - s_ExplicitVarSizeWithMarker_Values[q17]) % 2 = 0; + int(1..5)])) + | q16 : int(1..4), q17 : int(1..4)]) + > 0 + -> + or([and([s_ExplicitVarSizeWithDummy[q16] != 5, q17 <= s_ExplicitVarSizeWithMarker_Marker, + s_ExplicitVarSizeWithDummy[q16] != s_ExplicitVarSizeWithMarker_Values[q17], + allDiff([s_ExplicitVarSizeWithDummy[q16] + s_ExplicitVarSizeWithMarker_Values[q17], + s_ExplicitVarSizeWithDummy[q16] * s_ExplicitVarSizeWithMarker_Values[q17], + s_ExplicitVarSizeWithDummy[q16] / s_ExplicitVarSizeWithMarker_Values[q17]; + int(1..3)]), + (s_ExplicitVarSizeWithDummy[q16] - s_ExplicitVarSizeWithMarker_Values[q17]) % 2 = 0; + int(1..5)]) + /\ + min([s_ExplicitVarSizeWithDummy[q16] + s_ExplicitVarSizeWithMarker_Values[q17], + s_ExplicitVarSizeWithDummy[q16] - s_ExplicitVarSizeWithMarker_Values[q17], + s_ExplicitVarSizeWithDummy[q16] * s_ExplicitVarSizeWithMarker_Values[q17], + s_ExplicitVarSizeWithDummy[q16] / s_ExplicitVarSizeWithMarker_Values[q17]; + int(1..4)]) + = conjure_aux1 + | q16 : int(1..4), q17 : int(1..4)]), + sum([toInt(and([s_ExplicitVarSizeWithDummy[q16] != 5, q17 <= s_ExplicitVarSizeWithMarker_Marker, + s_ExplicitVarSizeWithDummy[q16] != s_ExplicitVarSizeWithMarker_Values[q17], + allDiff([s_ExplicitVarSizeWithDummy[q16] + s_ExplicitVarSizeWithMarker_Values[q17], + s_ExplicitVarSizeWithDummy[q16] * s_ExplicitVarSizeWithMarker_Values[q17], + s_ExplicitVarSizeWithDummy[q16] / s_ExplicitVarSizeWithMarker_Values[q17]; + int(1..3)]), + (s_ExplicitVarSizeWithDummy[q16] - s_ExplicitVarSizeWithMarker_Values[q17]) % 2 = 0; + int(1..5)])) + | q16 : int(1..4), q17 : int(1..4)]) + = 0 + -> conjure_aux1 = -20, + x = conjure_aux1, + sum([toInt(and([s_ExplicitVarSizeWithDummy[q16] != 5, q17 <= s_ExplicitVarSizeWithMarker_Marker, + s_ExplicitVarSizeWithDummy[q16] != s_ExplicitVarSizeWithMarker_Values[q17], + allDiff([s_ExplicitVarSizeWithDummy[q16] + s_ExplicitVarSizeWithMarker_Values[q17], + s_ExplicitVarSizeWithDummy[q16] * s_ExplicitVarSizeWithMarker_Values[q17], + s_ExplicitVarSizeWithDummy[q16] / s_ExplicitVarSizeWithMarker_Values[q17]; + int(1..3)]), + (s_ExplicitVarSizeWithDummy[q16] - s_ExplicitVarSizeWithMarker_Values[q17]) % 2 = 0; + int(1..5)])) + | q16 : int(1..4), q17 : int(1..4)]) + > 0, + and([s_ExplicitVarSizeWithDummy[q1] < s_ExplicitVarSizeWithDummy[q1 + 1] \/ s_ExplicitVarSizeWithDummy[q1] = 5 + | q1 : int(1..3)]), + and([s_ExplicitVarSizeWithDummy[q2] = 5 -> s_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..3)]), + and([q5 + 1 <= s_ExplicitVarSizeWithMarker_Marker -> + s_ExplicitVarSizeWithMarker_Values[q5] < s_ExplicitVarSizeWithMarker_Values[q5 + 1] + | q5 : int(1..3)]), + and([q6 > s_ExplicitVarSizeWithMarker_Marker -> s_ExplicitVarSizeWithMarker_Values[q6] = 1 | q6 : int(1..4)]), + and([q9 <= s_ExplicitVarSizeWithMarker_Marker -> + or([s_ExplicitVarSizeWithDummy[q11] != 5 /\ + s_ExplicitVarSizeWithDummy[q11] = s_ExplicitVarSizeWithMarker_Values[q9] + | q11 : int(1..4)]) + | q9 : int(1..4)]), + and([s_ExplicitVarSizeWithDummy[q13] != 5 -> + or([q15 <= s_ExplicitVarSizeWithMarker_Marker /\ + s_ExplicitVarSizeWithMarker_Values[q15] = s_ExplicitVarSizeWithDummy[q13] + | q15 : int(1..4)]) + | q13 : int(1..4)]) + diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_3_4-solution000001.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_3_4-solution000001.solution new file mode 100644 index 0000000000..8b4ecbb66d --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_2_3_4-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 3} +letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_3_4-solution000002.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_3_4-solution000002.solution new file mode 100644 index 0000000000..159a613983 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_2_3_4-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {2, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_3_4-solution000003.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_3_4-solution000003.solution new file mode 100644 index 0000000000..5963aac565 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_2_3_4-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 2, 3} +letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_3_4-solution000004.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_3_4-solution000004.solution new file mode 100644 index 0000000000..6eeacc9727 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_2_3_4-solution000004.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 2, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_3_4-solution000005.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_3_4-solution000005.solution new file mode 100644 index 0000000000..560dd0f2f7 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_2_3_4-solution000005.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 3, 4} +letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_3_4-solution000006.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_3_4-solution000006.solution new file mode 100644 index 0000000000..40f3fd5c8f --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_2_3_4-solution000006.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {2, 3, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_3_4-solution000007.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_3_4-solution000007.solution new file mode 100644 index 0000000000..bd956f44e3 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_2_3_4-solution000007.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 2, 3, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_3_4.eprime b/tests/exhaustive/basic/comprehension_letting/expected/model_2_3_4.eprime new file mode 100644 index 0000000000..bb0cb8b3e9 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_2_3_4.eprime @@ -0,0 +1,123 @@ +language ESSENCE' 1.0 + +find s_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +find s_ExplicitVarSizeWithMarker_Marker: int(0..4) +find s_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +find s_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find s_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +letting let1 be -100 +find x: int(-100..100) +find conjure_aux1: int(-20..4) +branching on + [s_ExplicitVarSizeWithFlags_Flags, s_ExplicitVarSizeWithFlags_Values, s_ExplicitVarSizeWithDummy, + s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithMarker_Values, x] +such that + and([and([s_ExplicitVarSizeWithDummy[q37] != 5, q38 <= s_ExplicitVarSizeWithMarker_Marker, + s_ExplicitVarSizeWithDummy[q37] != s_ExplicitVarSizeWithMarker_Values[q38], + allDiff([s_ExplicitVarSizeWithDummy[q37] + s_ExplicitVarSizeWithMarker_Values[q38], + s_ExplicitVarSizeWithDummy[q37] * s_ExplicitVarSizeWithMarker_Values[q38], + s_ExplicitVarSizeWithDummy[q37] / s_ExplicitVarSizeWithMarker_Values[q38]; + int(1..3)]), + (s_ExplicitVarSizeWithDummy[q37] - s_ExplicitVarSizeWithMarker_Values[q38]) % 2 = 0; + int(1..5)]) + -> + min([s_ExplicitVarSizeWithDummy[q37] + s_ExplicitVarSizeWithMarker_Values[q38], + s_ExplicitVarSizeWithDummy[q37] - s_ExplicitVarSizeWithMarker_Values[q38], + s_ExplicitVarSizeWithDummy[q37] * s_ExplicitVarSizeWithMarker_Values[q38], + s_ExplicitVarSizeWithDummy[q37] / s_ExplicitVarSizeWithMarker_Values[q38]; + int(1..4)]) + <= conjure_aux1 + | q37 : int(1..4), q38 : int(1..4)]), + sum([toInt(and([s_ExplicitVarSizeWithDummy[q37] != 5, q38 <= s_ExplicitVarSizeWithMarker_Marker, + s_ExplicitVarSizeWithDummy[q37] != s_ExplicitVarSizeWithMarker_Values[q38], + allDiff([s_ExplicitVarSizeWithDummy[q37] + s_ExplicitVarSizeWithMarker_Values[q38], + s_ExplicitVarSizeWithDummy[q37] * s_ExplicitVarSizeWithMarker_Values[q38], + s_ExplicitVarSizeWithDummy[q37] / s_ExplicitVarSizeWithMarker_Values[q38]; + int(1..3)]), + (s_ExplicitVarSizeWithDummy[q37] - s_ExplicitVarSizeWithMarker_Values[q38]) % 2 = 0; + int(1..5)])) + | q37 : int(1..4), q38 : int(1..4)]) + > 0 + -> + or([and([s_ExplicitVarSizeWithDummy[q37] != 5, q38 <= s_ExplicitVarSizeWithMarker_Marker, + s_ExplicitVarSizeWithDummy[q37] != s_ExplicitVarSizeWithMarker_Values[q38], + allDiff([s_ExplicitVarSizeWithDummy[q37] + s_ExplicitVarSizeWithMarker_Values[q38], + s_ExplicitVarSizeWithDummy[q37] * s_ExplicitVarSizeWithMarker_Values[q38], + s_ExplicitVarSizeWithDummy[q37] / s_ExplicitVarSizeWithMarker_Values[q38]; + int(1..3)]), + (s_ExplicitVarSizeWithDummy[q37] - s_ExplicitVarSizeWithMarker_Values[q38]) % 2 = 0; + int(1..5)]) + /\ + min([s_ExplicitVarSizeWithDummy[q37] + s_ExplicitVarSizeWithMarker_Values[q38], + s_ExplicitVarSizeWithDummy[q37] - s_ExplicitVarSizeWithMarker_Values[q38], + s_ExplicitVarSizeWithDummy[q37] * s_ExplicitVarSizeWithMarker_Values[q38], + s_ExplicitVarSizeWithDummy[q37] / s_ExplicitVarSizeWithMarker_Values[q38]; + int(1..4)]) + = conjure_aux1 + | q37 : int(1..4), q38 : int(1..4)]), + sum([toInt(and([s_ExplicitVarSizeWithDummy[q37] != 5, q38 <= s_ExplicitVarSizeWithMarker_Marker, + s_ExplicitVarSizeWithDummy[q37] != s_ExplicitVarSizeWithMarker_Values[q38], + allDiff([s_ExplicitVarSizeWithDummy[q37] + s_ExplicitVarSizeWithMarker_Values[q38], + s_ExplicitVarSizeWithDummy[q37] * s_ExplicitVarSizeWithMarker_Values[q38], + s_ExplicitVarSizeWithDummy[q37] / s_ExplicitVarSizeWithMarker_Values[q38]; + int(1..3)]), + (s_ExplicitVarSizeWithDummy[q37] - s_ExplicitVarSizeWithMarker_Values[q38]) % 2 = 0; + int(1..5)])) + | q37 : int(1..4), q38 : int(1..4)]) + = 0 + -> conjure_aux1 = -20, + x = conjure_aux1, + sum([toInt(and([s_ExplicitVarSizeWithDummy[q37] != 5, q38 <= s_ExplicitVarSizeWithMarker_Marker, + s_ExplicitVarSizeWithDummy[q37] != s_ExplicitVarSizeWithMarker_Values[q38], + allDiff([s_ExplicitVarSizeWithDummy[q37] + s_ExplicitVarSizeWithMarker_Values[q38], + s_ExplicitVarSizeWithDummy[q37] * s_ExplicitVarSizeWithMarker_Values[q38], + s_ExplicitVarSizeWithDummy[q37] / s_ExplicitVarSizeWithMarker_Values[q38]; + int(1..3)]), + (s_ExplicitVarSizeWithDummy[q37] - s_ExplicitVarSizeWithMarker_Values[q38]) % 2 = 0; + int(1..5)])) + | q37 : int(1..4), q38 : int(1..4)]) + > 0, + and([s_ExplicitVarSizeWithDummy[q1] < s_ExplicitVarSizeWithDummy[q1 + 1] \/ s_ExplicitVarSizeWithDummy[q1] = 5 + | q1 : int(1..3)]), + and([s_ExplicitVarSizeWithDummy[q2] = 5 -> s_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..3)]), + and([q5 + 1 <= s_ExplicitVarSizeWithMarker_Marker -> + s_ExplicitVarSizeWithMarker_Values[q5] < s_ExplicitVarSizeWithMarker_Values[q5 + 1] + | q5 : int(1..3)]), + and([q6 > s_ExplicitVarSizeWithMarker_Marker -> s_ExplicitVarSizeWithMarker_Values[q6] = 1 | q6 : int(1..4)]), + and([q9 <= s_ExplicitVarSizeWithMarker_Marker -> + or([s_ExplicitVarSizeWithDummy[q11] != 5 /\ + s_ExplicitVarSizeWithDummy[q11] = s_ExplicitVarSizeWithMarker_Values[q9] + | q11 : int(1..4)]) + | q9 : int(1..4)]), + and([s_ExplicitVarSizeWithDummy[q13] != 5 -> + or([q15 <= s_ExplicitVarSizeWithMarker_Marker /\ + s_ExplicitVarSizeWithMarker_Values[q15] = s_ExplicitVarSizeWithDummy[q13] + | q15 : int(1..4)]) + | q13 : int(1..4)]), + and([s_ExplicitVarSizeWithFlags_Flags[q16 + 1] -> + s_ExplicitVarSizeWithFlags_Values[q16] < s_ExplicitVarSizeWithFlags_Values[q16 + 1] + | q16 : int(1..3)]), + and([s_ExplicitVarSizeWithFlags_Flags[q17] = false -> s_ExplicitVarSizeWithFlags_Values[q17] = 1 + | q17 : int(1..4)]), + and([s_ExplicitVarSizeWithFlags_Flags[q18 + 1] -> s_ExplicitVarSizeWithFlags_Flags[q18] | q18 : int(1..3)]), + and([s_ExplicitVarSizeWithFlags_Flags[q22] -> + or([s_ExplicitVarSizeWithDummy[q24] != 5 /\ + s_ExplicitVarSizeWithDummy[q24] = s_ExplicitVarSizeWithFlags_Values[q22] + | q24 : int(1..4)]) + | q22 : int(1..4)]), + and([s_ExplicitVarSizeWithDummy[q26] != 5 -> + or([s_ExplicitVarSizeWithFlags_Flags[q28] /\ + s_ExplicitVarSizeWithFlags_Values[q28] = s_ExplicitVarSizeWithDummy[q26] + | q28 : int(1..4)]) + | q26 : int(1..4)]), + and([s_ExplicitVarSizeWithFlags_Flags[q30] -> + or([q32 <= s_ExplicitVarSizeWithMarker_Marker /\ + s_ExplicitVarSizeWithMarker_Values[q32] = s_ExplicitVarSizeWithFlags_Values[q30] + | q32 : int(1..4)]) + | q30 : int(1..4)]), + and([q34 <= s_ExplicitVarSizeWithMarker_Marker -> + or([s_ExplicitVarSizeWithFlags_Flags[q36] /\ + s_ExplicitVarSizeWithFlags_Values[q36] = s_ExplicitVarSizeWithMarker_Values[q34] + | q36 : int(1..4)]) + | q34 : int(1..4)]) + diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_4_1-solution000001.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_4_1-solution000001.solution new file mode 100644 index 0000000000..159a613983 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_2_4_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {2, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_4_1-solution000002.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_4_1-solution000002.solution new file mode 100644 index 0000000000..40f3fd5c8f --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_2_4_1-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {2, 3, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_4_1-solution000003.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_4_1-solution000003.solution new file mode 100644 index 0000000000..8b4ecbb66d --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_2_4_1-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 3} +letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_4_1-solution000004.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_4_1-solution000004.solution new file mode 100644 index 0000000000..560dd0f2f7 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_2_4_1-solution000004.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 3, 4} +letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_4_1-solution000005.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_4_1-solution000005.solution new file mode 100644 index 0000000000..6eeacc9727 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_2_4_1-solution000005.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 2, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_4_1-solution000006.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_4_1-solution000006.solution new file mode 100644 index 0000000000..5963aac565 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_2_4_1-solution000006.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 2, 3} +letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_4_1-solution000007.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_4_1-solution000007.solution new file mode 100644 index 0000000000..bd956f44e3 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_2_4_1-solution000007.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 2, 3, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_4_1.eprime b/tests/exhaustive/basic/comprehension_letting/expected/model_2_4_1.eprime new file mode 100644 index 0000000000..f8ee63e7f7 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_2_4_1.eprime @@ -0,0 +1,105 @@ +language ESSENCE' 1.0 + +find s_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +find s_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find s_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +find s_Occurrence: matrix indexed by [int(1..4)] of bool +letting let1 be -100 +find x: int(-100..100) +find conjure_aux1: int(-20..4) +branching on + [s_Occurrence, s_ExplicitVarSizeWithDummy, s_ExplicitVarSizeWithFlags_Flags, s_ExplicitVarSizeWithFlags_Values, x] +such that + and([and([s_ExplicitVarSizeWithDummy[q29] != 5, s_ExplicitVarSizeWithFlags_Flags[q30], + s_ExplicitVarSizeWithDummy[q29] != s_ExplicitVarSizeWithFlags_Values[q30], + allDiff([s_ExplicitVarSizeWithDummy[q29] + s_ExplicitVarSizeWithFlags_Values[q30], + s_ExplicitVarSizeWithDummy[q29] * s_ExplicitVarSizeWithFlags_Values[q30], + s_ExplicitVarSizeWithDummy[q29] / s_ExplicitVarSizeWithFlags_Values[q30]; + int(1..3)]), + (s_ExplicitVarSizeWithDummy[q29] - s_ExplicitVarSizeWithFlags_Values[q30]) % 2 = 0; + int(1..5)]) + -> + min([s_ExplicitVarSizeWithDummy[q29] + s_ExplicitVarSizeWithFlags_Values[q30], + s_ExplicitVarSizeWithDummy[q29] - s_ExplicitVarSizeWithFlags_Values[q30], + s_ExplicitVarSizeWithDummy[q29] * s_ExplicitVarSizeWithFlags_Values[q30], + s_ExplicitVarSizeWithDummy[q29] / s_ExplicitVarSizeWithFlags_Values[q30]; + int(1..4)]) + <= conjure_aux1 + | q29 : int(1..4), q30 : int(1..4)]), + sum([toInt(and([s_ExplicitVarSizeWithDummy[q29] != 5, s_ExplicitVarSizeWithFlags_Flags[q30], + s_ExplicitVarSizeWithDummy[q29] != s_ExplicitVarSizeWithFlags_Values[q30], + allDiff([s_ExplicitVarSizeWithDummy[q29] + s_ExplicitVarSizeWithFlags_Values[q30], + s_ExplicitVarSizeWithDummy[q29] * s_ExplicitVarSizeWithFlags_Values[q30], + s_ExplicitVarSizeWithDummy[q29] / s_ExplicitVarSizeWithFlags_Values[q30]; + int(1..3)]), + (s_ExplicitVarSizeWithDummy[q29] - s_ExplicitVarSizeWithFlags_Values[q30]) % 2 = 0; + int(1..5)])) + | q29 : int(1..4), q30 : int(1..4)]) + > 0 + -> + or([and([s_ExplicitVarSizeWithDummy[q29] != 5, s_ExplicitVarSizeWithFlags_Flags[q30], + s_ExplicitVarSizeWithDummy[q29] != s_ExplicitVarSizeWithFlags_Values[q30], + allDiff([s_ExplicitVarSizeWithDummy[q29] + s_ExplicitVarSizeWithFlags_Values[q30], + s_ExplicitVarSizeWithDummy[q29] * s_ExplicitVarSizeWithFlags_Values[q30], + s_ExplicitVarSizeWithDummy[q29] / s_ExplicitVarSizeWithFlags_Values[q30]; + int(1..3)]), + (s_ExplicitVarSizeWithDummy[q29] - s_ExplicitVarSizeWithFlags_Values[q30]) % 2 = 0; + int(1..5)]) + /\ + min([s_ExplicitVarSizeWithDummy[q29] + s_ExplicitVarSizeWithFlags_Values[q30], + s_ExplicitVarSizeWithDummy[q29] - s_ExplicitVarSizeWithFlags_Values[q30], + s_ExplicitVarSizeWithDummy[q29] * s_ExplicitVarSizeWithFlags_Values[q30], + s_ExplicitVarSizeWithDummy[q29] / s_ExplicitVarSizeWithFlags_Values[q30]; + int(1..4)]) + = conjure_aux1 + | q29 : int(1..4), q30 : int(1..4)]), + sum([toInt(and([s_ExplicitVarSizeWithDummy[q29] != 5, s_ExplicitVarSizeWithFlags_Flags[q30], + s_ExplicitVarSizeWithDummy[q29] != s_ExplicitVarSizeWithFlags_Values[q30], + allDiff([s_ExplicitVarSizeWithDummy[q29] + s_ExplicitVarSizeWithFlags_Values[q30], + s_ExplicitVarSizeWithDummy[q29] * s_ExplicitVarSizeWithFlags_Values[q30], + s_ExplicitVarSizeWithDummy[q29] / s_ExplicitVarSizeWithFlags_Values[q30]; + int(1..3)]), + (s_ExplicitVarSizeWithDummy[q29] - s_ExplicitVarSizeWithFlags_Values[q30]) % 2 = 0; + int(1..5)])) + | q29 : int(1..4), q30 : int(1..4)]) + = 0 + -> conjure_aux1 = -20, + x = conjure_aux1, + sum([toInt(and([s_ExplicitVarSizeWithDummy[q29] != 5, s_ExplicitVarSizeWithFlags_Flags[q30], + s_ExplicitVarSizeWithDummy[q29] != s_ExplicitVarSizeWithFlags_Values[q30], + allDiff([s_ExplicitVarSizeWithDummy[q29] + s_ExplicitVarSizeWithFlags_Values[q30], + s_ExplicitVarSizeWithDummy[q29] * s_ExplicitVarSizeWithFlags_Values[q30], + s_ExplicitVarSizeWithDummy[q29] / s_ExplicitVarSizeWithFlags_Values[q30]; + int(1..3)]), + (s_ExplicitVarSizeWithDummy[q29] - s_ExplicitVarSizeWithFlags_Values[q30]) % 2 = 0; + int(1..5)])) + | q29 : int(1..4), q30 : int(1..4)]) + > 0, + and([s_ExplicitVarSizeWithDummy[q1] < s_ExplicitVarSizeWithDummy[q1 + 1] \/ s_ExplicitVarSizeWithDummy[q1] = 5 + | q1 : int(1..3)]), + and([s_ExplicitVarSizeWithDummy[q2] = 5 -> s_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..3)]), + and([s_ExplicitVarSizeWithFlags_Flags[q5 + 1] -> + s_ExplicitVarSizeWithFlags_Values[q5] < s_ExplicitVarSizeWithFlags_Values[q5 + 1] + | q5 : int(1..3)]), + and([s_ExplicitVarSizeWithFlags_Flags[q6] = false -> s_ExplicitVarSizeWithFlags_Values[q6] = 1 | q6 : int(1..4)]), + and([s_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> s_ExplicitVarSizeWithFlags_Flags[q7] | q7 : int(1..3)]), + and([s_ExplicitVarSizeWithFlags_Flags[q11] -> + or([s_ExplicitVarSizeWithDummy[q13] != 5 /\ + s_ExplicitVarSizeWithDummy[q13] = s_ExplicitVarSizeWithFlags_Values[q11] + | q13 : int(1..4)]) + | q11 : int(1..4)]), + and([s_ExplicitVarSizeWithDummy[q15] != 5 -> + or([s_ExplicitVarSizeWithFlags_Flags[q17] /\ + s_ExplicitVarSizeWithFlags_Values[q17] = s_ExplicitVarSizeWithDummy[q15] + | q17 : int(1..4)]) + | q15 : int(1..4)]), + and([s_Occurrence[q19] -> + or([s_ExplicitVarSizeWithDummy[q21] != 5 /\ s_ExplicitVarSizeWithDummy[q21] = q19 | q21 : int(1..4)]) + | q19 : int(1..4)]), + and([s_ExplicitVarSizeWithDummy[q23] != 5 -> s_Occurrence[s_ExplicitVarSizeWithDummy[q23]] | q23 : int(1..4)]), + and([s_Occurrence[q24] -> + or([s_ExplicitVarSizeWithFlags_Flags[q26] /\ s_ExplicitVarSizeWithFlags_Values[q26] = q24 | q26 : int(1..4)]) + | q24 : int(1..4)]), + and([s_ExplicitVarSizeWithFlags_Flags[q28] -> s_Occurrence[s_ExplicitVarSizeWithFlags_Values[q28]] + | q28 : int(1..4)]) + diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_4_2-solution000001.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_4_2-solution000001.solution new file mode 100644 index 0000000000..8b4ecbb66d --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_2_4_2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 3} +letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_4_2-solution000002.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_4_2-solution000002.solution new file mode 100644 index 0000000000..159a613983 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_2_4_2-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {2, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_4_2-solution000003.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_4_2-solution000003.solution new file mode 100644 index 0000000000..5963aac565 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_2_4_2-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 2, 3} +letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_4_2-solution000004.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_4_2-solution000004.solution new file mode 100644 index 0000000000..6eeacc9727 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_2_4_2-solution000004.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 2, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_4_2-solution000005.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_4_2-solution000005.solution new file mode 100644 index 0000000000..560dd0f2f7 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_2_4_2-solution000005.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 3, 4} +letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_4_2-solution000006.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_4_2-solution000006.solution new file mode 100644 index 0000000000..40f3fd5c8f --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_2_4_2-solution000006.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {2, 3, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_4_2-solution000007.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_4_2-solution000007.solution new file mode 100644 index 0000000000..bd956f44e3 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_2_4_2-solution000007.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 2, 3, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_4_2.eprime b/tests/exhaustive/basic/comprehension_letting/expected/model_2_4_2.eprime new file mode 100644 index 0000000000..fcc240b9e7 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_2_4_2.eprime @@ -0,0 +1,94 @@ +language ESSENCE' 1.0 + +find s_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +find s_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find s_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +letting let1 be -100 +find x: int(-100..100) +find conjure_aux1: int(-20..4) +branching on [s_ExplicitVarSizeWithFlags_Flags, s_ExplicitVarSizeWithFlags_Values, s_ExplicitVarSizeWithDummy, x] +such that + and([and([s_ExplicitVarSizeWithDummy[q18] != 5, s_ExplicitVarSizeWithFlags_Flags[q19], + s_ExplicitVarSizeWithDummy[q18] != s_ExplicitVarSizeWithFlags_Values[q19], + allDiff([s_ExplicitVarSizeWithDummy[q18] + s_ExplicitVarSizeWithFlags_Values[q19], + s_ExplicitVarSizeWithDummy[q18] * s_ExplicitVarSizeWithFlags_Values[q19], + s_ExplicitVarSizeWithDummy[q18] / s_ExplicitVarSizeWithFlags_Values[q19]; + int(1..3)]), + (s_ExplicitVarSizeWithDummy[q18] - s_ExplicitVarSizeWithFlags_Values[q19]) % 2 = 0; + int(1..5)]) + -> + min([s_ExplicitVarSizeWithDummy[q18] + s_ExplicitVarSizeWithFlags_Values[q19], + s_ExplicitVarSizeWithDummy[q18] - s_ExplicitVarSizeWithFlags_Values[q19], + s_ExplicitVarSizeWithDummy[q18] * s_ExplicitVarSizeWithFlags_Values[q19], + s_ExplicitVarSizeWithDummy[q18] / s_ExplicitVarSizeWithFlags_Values[q19]; + int(1..4)]) + <= conjure_aux1 + | q18 : int(1..4), q19 : int(1..4)]), + sum([toInt(and([s_ExplicitVarSizeWithDummy[q18] != 5, s_ExplicitVarSizeWithFlags_Flags[q19], + s_ExplicitVarSizeWithDummy[q18] != s_ExplicitVarSizeWithFlags_Values[q19], + allDiff([s_ExplicitVarSizeWithDummy[q18] + s_ExplicitVarSizeWithFlags_Values[q19], + s_ExplicitVarSizeWithDummy[q18] * s_ExplicitVarSizeWithFlags_Values[q19], + s_ExplicitVarSizeWithDummy[q18] / s_ExplicitVarSizeWithFlags_Values[q19]; + int(1..3)]), + (s_ExplicitVarSizeWithDummy[q18] - s_ExplicitVarSizeWithFlags_Values[q19]) % 2 = 0; + int(1..5)])) + | q18 : int(1..4), q19 : int(1..4)]) + > 0 + -> + or([and([s_ExplicitVarSizeWithDummy[q18] != 5, s_ExplicitVarSizeWithFlags_Flags[q19], + s_ExplicitVarSizeWithDummy[q18] != s_ExplicitVarSizeWithFlags_Values[q19], + allDiff([s_ExplicitVarSizeWithDummy[q18] + s_ExplicitVarSizeWithFlags_Values[q19], + s_ExplicitVarSizeWithDummy[q18] * s_ExplicitVarSizeWithFlags_Values[q19], + s_ExplicitVarSizeWithDummy[q18] / s_ExplicitVarSizeWithFlags_Values[q19]; + int(1..3)]), + (s_ExplicitVarSizeWithDummy[q18] - s_ExplicitVarSizeWithFlags_Values[q19]) % 2 = 0; + int(1..5)]) + /\ + min([s_ExplicitVarSizeWithDummy[q18] + s_ExplicitVarSizeWithFlags_Values[q19], + s_ExplicitVarSizeWithDummy[q18] - s_ExplicitVarSizeWithFlags_Values[q19], + s_ExplicitVarSizeWithDummy[q18] * s_ExplicitVarSizeWithFlags_Values[q19], + s_ExplicitVarSizeWithDummy[q18] / s_ExplicitVarSizeWithFlags_Values[q19]; + int(1..4)]) + = conjure_aux1 + | q18 : int(1..4), q19 : int(1..4)]), + sum([toInt(and([s_ExplicitVarSizeWithDummy[q18] != 5, s_ExplicitVarSizeWithFlags_Flags[q19], + s_ExplicitVarSizeWithDummy[q18] != s_ExplicitVarSizeWithFlags_Values[q19], + allDiff([s_ExplicitVarSizeWithDummy[q18] + s_ExplicitVarSizeWithFlags_Values[q19], + s_ExplicitVarSizeWithDummy[q18] * s_ExplicitVarSizeWithFlags_Values[q19], + s_ExplicitVarSizeWithDummy[q18] / s_ExplicitVarSizeWithFlags_Values[q19]; + int(1..3)]), + (s_ExplicitVarSizeWithDummy[q18] - s_ExplicitVarSizeWithFlags_Values[q19]) % 2 = 0; + int(1..5)])) + | q18 : int(1..4), q19 : int(1..4)]) + = 0 + -> conjure_aux1 = -20, + x = conjure_aux1, + sum([toInt(and([s_ExplicitVarSizeWithDummy[q18] != 5, s_ExplicitVarSizeWithFlags_Flags[q19], + s_ExplicitVarSizeWithDummy[q18] != s_ExplicitVarSizeWithFlags_Values[q19], + allDiff([s_ExplicitVarSizeWithDummy[q18] + s_ExplicitVarSizeWithFlags_Values[q19], + s_ExplicitVarSizeWithDummy[q18] * s_ExplicitVarSizeWithFlags_Values[q19], + s_ExplicitVarSizeWithDummy[q18] / s_ExplicitVarSizeWithFlags_Values[q19]; + int(1..3)]), + (s_ExplicitVarSizeWithDummy[q18] - s_ExplicitVarSizeWithFlags_Values[q19]) % 2 = 0; + int(1..5)])) + | q18 : int(1..4), q19 : int(1..4)]) + > 0, + and([s_ExplicitVarSizeWithDummy[q1] < s_ExplicitVarSizeWithDummy[q1 + 1] \/ s_ExplicitVarSizeWithDummy[q1] = 5 + | q1 : int(1..3)]), + and([s_ExplicitVarSizeWithDummy[q2] = 5 -> s_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..3)]), + and([s_ExplicitVarSizeWithFlags_Flags[q5 + 1] -> + s_ExplicitVarSizeWithFlags_Values[q5] < s_ExplicitVarSizeWithFlags_Values[q5 + 1] + | q5 : int(1..3)]), + and([s_ExplicitVarSizeWithFlags_Flags[q6] = false -> s_ExplicitVarSizeWithFlags_Values[q6] = 1 | q6 : int(1..4)]), + and([s_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> s_ExplicitVarSizeWithFlags_Flags[q7] | q7 : int(1..3)]), + and([s_ExplicitVarSizeWithFlags_Flags[q11] -> + or([s_ExplicitVarSizeWithDummy[q13] != 5 /\ + s_ExplicitVarSizeWithDummy[q13] = s_ExplicitVarSizeWithFlags_Values[q11] + | q13 : int(1..4)]) + | q11 : int(1..4)]), + and([s_ExplicitVarSizeWithDummy[q15] != 5 -> + or([s_ExplicitVarSizeWithFlags_Flags[q17] /\ + s_ExplicitVarSizeWithFlags_Values[q17] = s_ExplicitVarSizeWithDummy[q15] + | q17 : int(1..4)]) + | q15 : int(1..4)]) + diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_4_3-solution000001.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_4_3-solution000001.solution new file mode 100644 index 0000000000..8b4ecbb66d --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_2_4_3-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 3} +letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_4_3-solution000002.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_4_3-solution000002.solution new file mode 100644 index 0000000000..159a613983 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_2_4_3-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {2, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_4_3-solution000003.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_4_3-solution000003.solution new file mode 100644 index 0000000000..5963aac565 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_2_4_3-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 2, 3} +letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_4_3-solution000004.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_4_3-solution000004.solution new file mode 100644 index 0000000000..6eeacc9727 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_2_4_3-solution000004.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 2, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_4_3-solution000005.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_4_3-solution000005.solution new file mode 100644 index 0000000000..560dd0f2f7 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_2_4_3-solution000005.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 3, 4} +letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_4_3-solution000006.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_4_3-solution000006.solution new file mode 100644 index 0000000000..40f3fd5c8f --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_2_4_3-solution000006.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {2, 3, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_4_3-solution000007.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_2_4_3-solution000007.solution new file mode 100644 index 0000000000..bd956f44e3 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_2_4_3-solution000007.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 2, 3, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_2_4_3.eprime b/tests/exhaustive/basic/comprehension_letting/expected/model_2_4_3.eprime new file mode 100644 index 0000000000..aa5a1b0079 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_2_4_3.eprime @@ -0,0 +1,122 @@ +language ESSENCE' 1.0 + +find s_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +find s_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find s_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +find s_ExplicitVarSizeWithMarker_Marker: int(0..4) +find s_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +letting let1 be -100 +find x: int(-100..100) +find conjure_aux1: int(-20..4) +branching on + [s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithMarker_Values, s_ExplicitVarSizeWithDummy, + s_ExplicitVarSizeWithFlags_Flags, s_ExplicitVarSizeWithFlags_Values, x] +such that + and([and([s_ExplicitVarSizeWithDummy[q37] != 5, s_ExplicitVarSizeWithFlags_Flags[q38], + s_ExplicitVarSizeWithDummy[q37] != s_ExplicitVarSizeWithFlags_Values[q38], + allDiff([s_ExplicitVarSizeWithDummy[q37] + s_ExplicitVarSizeWithFlags_Values[q38], + s_ExplicitVarSizeWithDummy[q37] * s_ExplicitVarSizeWithFlags_Values[q38], + s_ExplicitVarSizeWithDummy[q37] / s_ExplicitVarSizeWithFlags_Values[q38]; + int(1..3)]), + (s_ExplicitVarSizeWithDummy[q37] - s_ExplicitVarSizeWithFlags_Values[q38]) % 2 = 0; + int(1..5)]) + -> + min([s_ExplicitVarSizeWithDummy[q37] + s_ExplicitVarSizeWithFlags_Values[q38], + s_ExplicitVarSizeWithDummy[q37] - s_ExplicitVarSizeWithFlags_Values[q38], + s_ExplicitVarSizeWithDummy[q37] * s_ExplicitVarSizeWithFlags_Values[q38], + s_ExplicitVarSizeWithDummy[q37] / s_ExplicitVarSizeWithFlags_Values[q38]; + int(1..4)]) + <= conjure_aux1 + | q37 : int(1..4), q38 : int(1..4)]), + sum([toInt(and([s_ExplicitVarSizeWithDummy[q37] != 5, s_ExplicitVarSizeWithFlags_Flags[q38], + s_ExplicitVarSizeWithDummy[q37] != s_ExplicitVarSizeWithFlags_Values[q38], + allDiff([s_ExplicitVarSizeWithDummy[q37] + s_ExplicitVarSizeWithFlags_Values[q38], + s_ExplicitVarSizeWithDummy[q37] * s_ExplicitVarSizeWithFlags_Values[q38], + s_ExplicitVarSizeWithDummy[q37] / s_ExplicitVarSizeWithFlags_Values[q38]; + int(1..3)]), + (s_ExplicitVarSizeWithDummy[q37] - s_ExplicitVarSizeWithFlags_Values[q38]) % 2 = 0; + int(1..5)])) + | q37 : int(1..4), q38 : int(1..4)]) + > 0 + -> + or([and([s_ExplicitVarSizeWithDummy[q37] != 5, s_ExplicitVarSizeWithFlags_Flags[q38], + s_ExplicitVarSizeWithDummy[q37] != s_ExplicitVarSizeWithFlags_Values[q38], + allDiff([s_ExplicitVarSizeWithDummy[q37] + s_ExplicitVarSizeWithFlags_Values[q38], + s_ExplicitVarSizeWithDummy[q37] * s_ExplicitVarSizeWithFlags_Values[q38], + s_ExplicitVarSizeWithDummy[q37] / s_ExplicitVarSizeWithFlags_Values[q38]; + int(1..3)]), + (s_ExplicitVarSizeWithDummy[q37] - s_ExplicitVarSizeWithFlags_Values[q38]) % 2 = 0; + int(1..5)]) + /\ + min([s_ExplicitVarSizeWithDummy[q37] + s_ExplicitVarSizeWithFlags_Values[q38], + s_ExplicitVarSizeWithDummy[q37] - s_ExplicitVarSizeWithFlags_Values[q38], + s_ExplicitVarSizeWithDummy[q37] * s_ExplicitVarSizeWithFlags_Values[q38], + s_ExplicitVarSizeWithDummy[q37] / s_ExplicitVarSizeWithFlags_Values[q38]; + int(1..4)]) + = conjure_aux1 + | q37 : int(1..4), q38 : int(1..4)]), + sum([toInt(and([s_ExplicitVarSizeWithDummy[q37] != 5, s_ExplicitVarSizeWithFlags_Flags[q38], + s_ExplicitVarSizeWithDummy[q37] != s_ExplicitVarSizeWithFlags_Values[q38], + allDiff([s_ExplicitVarSizeWithDummy[q37] + s_ExplicitVarSizeWithFlags_Values[q38], + s_ExplicitVarSizeWithDummy[q37] * s_ExplicitVarSizeWithFlags_Values[q38], + s_ExplicitVarSizeWithDummy[q37] / s_ExplicitVarSizeWithFlags_Values[q38]; + int(1..3)]), + (s_ExplicitVarSizeWithDummy[q37] - s_ExplicitVarSizeWithFlags_Values[q38]) % 2 = 0; + int(1..5)])) + | q37 : int(1..4), q38 : int(1..4)]) + = 0 + -> conjure_aux1 = -20, + x = conjure_aux1, + sum([toInt(and([s_ExplicitVarSizeWithDummy[q37] != 5, s_ExplicitVarSizeWithFlags_Flags[q38], + s_ExplicitVarSizeWithDummy[q37] != s_ExplicitVarSizeWithFlags_Values[q38], + allDiff([s_ExplicitVarSizeWithDummy[q37] + s_ExplicitVarSizeWithFlags_Values[q38], + s_ExplicitVarSizeWithDummy[q37] * s_ExplicitVarSizeWithFlags_Values[q38], + s_ExplicitVarSizeWithDummy[q37] / s_ExplicitVarSizeWithFlags_Values[q38]; + int(1..3)]), + (s_ExplicitVarSizeWithDummy[q37] - s_ExplicitVarSizeWithFlags_Values[q38]) % 2 = 0; + int(1..5)])) + | q37 : int(1..4), q38 : int(1..4)]) + > 0, + and([s_ExplicitVarSizeWithDummy[q1] < s_ExplicitVarSizeWithDummy[q1 + 1] \/ s_ExplicitVarSizeWithDummy[q1] = 5 + | q1 : int(1..3)]), + and([s_ExplicitVarSizeWithDummy[q2] = 5 -> s_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..3)]), + and([s_ExplicitVarSizeWithFlags_Flags[q5 + 1] -> + s_ExplicitVarSizeWithFlags_Values[q5] < s_ExplicitVarSizeWithFlags_Values[q5 + 1] + | q5 : int(1..3)]), + and([s_ExplicitVarSizeWithFlags_Flags[q6] = false -> s_ExplicitVarSizeWithFlags_Values[q6] = 1 | q6 : int(1..4)]), + and([s_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> s_ExplicitVarSizeWithFlags_Flags[q7] | q7 : int(1..3)]), + and([s_ExplicitVarSizeWithFlags_Flags[q11] -> + or([s_ExplicitVarSizeWithDummy[q13] != 5 /\ + s_ExplicitVarSizeWithDummy[q13] = s_ExplicitVarSizeWithFlags_Values[q11] + | q13 : int(1..4)]) + | q11 : int(1..4)]), + and([s_ExplicitVarSizeWithDummy[q15] != 5 -> + or([s_ExplicitVarSizeWithFlags_Flags[q17] /\ + s_ExplicitVarSizeWithFlags_Values[q17] = s_ExplicitVarSizeWithDummy[q15] + | q17 : int(1..4)]) + | q15 : int(1..4)]), + and([q18 + 1 <= s_ExplicitVarSizeWithMarker_Marker -> + s_ExplicitVarSizeWithMarker_Values[q18] < s_ExplicitVarSizeWithMarker_Values[q18 + 1] + | q18 : int(1..3)]), + and([q19 > s_ExplicitVarSizeWithMarker_Marker -> s_ExplicitVarSizeWithMarker_Values[q19] = 1 | q19 : int(1..4)]), + and([q22 <= s_ExplicitVarSizeWithMarker_Marker -> + or([s_ExplicitVarSizeWithDummy[q24] != 5 /\ + s_ExplicitVarSizeWithDummy[q24] = s_ExplicitVarSizeWithMarker_Values[q22] + | q24 : int(1..4)]) + | q22 : int(1..4)]), + and([s_ExplicitVarSizeWithDummy[q26] != 5 -> + or([q28 <= s_ExplicitVarSizeWithMarker_Marker /\ + s_ExplicitVarSizeWithMarker_Values[q28] = s_ExplicitVarSizeWithDummy[q26] + | q28 : int(1..4)]) + | q26 : int(1..4)]), + and([q30 <= s_ExplicitVarSizeWithMarker_Marker -> + or([s_ExplicitVarSizeWithFlags_Flags[q32] /\ + s_ExplicitVarSizeWithFlags_Values[q32] = s_ExplicitVarSizeWithMarker_Values[q30] + | q32 : int(1..4)]) + | q30 : int(1..4)]), + and([s_ExplicitVarSizeWithFlags_Flags[q34] -> + or([q36 <= s_ExplicitVarSizeWithMarker_Marker /\ + s_ExplicitVarSizeWithMarker_Values[q36] = s_ExplicitVarSizeWithFlags_Values[q34] + | q36 : int(1..4)]) + | q34 : int(1..4)]) + diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_1_1-solution000001.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_1_1-solution000001.solution new file mode 100644 index 0000000000..159a613983 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_3_1_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {2, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_1_1-solution000002.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_1_1-solution000002.solution new file mode 100644 index 0000000000..40f3fd5c8f --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_3_1_1-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {2, 3, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_1_1-solution000003.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_1_1-solution000003.solution new file mode 100644 index 0000000000..8b4ecbb66d --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_3_1_1-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 3} +letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_1_1-solution000004.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_1_1-solution000004.solution new file mode 100644 index 0000000000..560dd0f2f7 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_3_1_1-solution000004.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 3, 4} +letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_1_1-solution000005.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_1_1-solution000005.solution new file mode 100644 index 0000000000..6eeacc9727 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_3_1_1-solution000005.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 2, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_1_1-solution000006.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_1_1-solution000006.solution new file mode 100644 index 0000000000..5963aac565 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_3_1_1-solution000006.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 2, 3} +letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_1_1-solution000007.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_1_1-solution000007.solution new file mode 100644 index 0000000000..bd956f44e3 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_3_1_1-solution000007.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 2, 3, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_1_1.eprime b/tests/exhaustive/basic/comprehension_letting/expected/model_3_1_1.eprime new file mode 100644 index 0000000000..73444ebdb1 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_3_1_1.eprime @@ -0,0 +1,75 @@ +language ESSENCE' 1.0 + +find s_ExplicitVarSizeWithMarker_Marker: int(0..4) +find s_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +find s_Occurrence: matrix indexed by [int(1..4)] of bool +letting let1 be -100 +find x: int(-100..100) +find conjure_aux1: int(-16..3) +branching on [s_Occurrence, s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithMarker_Values, x] +such that + and([and([q5 <= s_ExplicitVarSizeWithMarker_Marker, s_Occurrence[j], s_ExplicitVarSizeWithMarker_Values[q5] != j, + allDiff([s_ExplicitVarSizeWithMarker_Values[q5] + j, s_ExplicitVarSizeWithMarker_Values[q5] * j, + s_ExplicitVarSizeWithMarker_Values[q5] / j; + int(1..3)]), + (s_ExplicitVarSizeWithMarker_Values[q5] - j) % 2 = 0; + int(1..5)]) + -> + min([s_ExplicitVarSizeWithMarker_Values[q5] + j, s_ExplicitVarSizeWithMarker_Values[q5] - j, + s_ExplicitVarSizeWithMarker_Values[q5] * j, s_ExplicitVarSizeWithMarker_Values[q5] / j; + int(1..4)]) + <= conjure_aux1 + | q5 : int(1..4), j : int(1..4)]), + sum([toInt(and([q5 <= s_ExplicitVarSizeWithMarker_Marker, s_Occurrence[j], + s_ExplicitVarSizeWithMarker_Values[q5] != j, + allDiff([s_ExplicitVarSizeWithMarker_Values[q5] + j, s_ExplicitVarSizeWithMarker_Values[q5] * j, + s_ExplicitVarSizeWithMarker_Values[q5] / j; + int(1..3)]), + (s_ExplicitVarSizeWithMarker_Values[q5] - j) % 2 = 0; + int(1..5)])) + | q5 : int(1..4), j : int(1..4)]) + > 0 + -> + or([and([q5 <= s_ExplicitVarSizeWithMarker_Marker, s_Occurrence[j], s_ExplicitVarSizeWithMarker_Values[q5] != j, + allDiff([s_ExplicitVarSizeWithMarker_Values[q5] + j, s_ExplicitVarSizeWithMarker_Values[q5] * j, + s_ExplicitVarSizeWithMarker_Values[q5] / j; + int(1..3)]), + (s_ExplicitVarSizeWithMarker_Values[q5] - j) % 2 = 0; + int(1..5)]) + /\ + min([s_ExplicitVarSizeWithMarker_Values[q5] + j, s_ExplicitVarSizeWithMarker_Values[q5] - j, + s_ExplicitVarSizeWithMarker_Values[q5] * j, s_ExplicitVarSizeWithMarker_Values[q5] / j; + int(1..4)]) + = conjure_aux1 + | q5 : int(1..4), j : int(1..4)]), + sum([toInt(and([q5 <= s_ExplicitVarSizeWithMarker_Marker, s_Occurrence[j], + s_ExplicitVarSizeWithMarker_Values[q5] != j, + allDiff([s_ExplicitVarSizeWithMarker_Values[q5] + j, s_ExplicitVarSizeWithMarker_Values[q5] * j, + s_ExplicitVarSizeWithMarker_Values[q5] / j; + int(1..3)]), + (s_ExplicitVarSizeWithMarker_Values[q5] - j) % 2 = 0; + int(1..5)])) + | q5 : int(1..4), j : int(1..4)]) + = 0 + -> conjure_aux1 = -16, + x = conjure_aux1, + sum([toInt(and([q5 <= s_ExplicitVarSizeWithMarker_Marker, s_Occurrence[j], + s_ExplicitVarSizeWithMarker_Values[q5] != j, + allDiff([s_ExplicitVarSizeWithMarker_Values[q5] + j, s_ExplicitVarSizeWithMarker_Values[q5] * j, + s_ExplicitVarSizeWithMarker_Values[q5] / j; + int(1..3)]), + (s_ExplicitVarSizeWithMarker_Values[q5] - j) % 2 = 0; + int(1..5)])) + | q5 : int(1..4), j : int(1..4)]) + > 0, + and([q1 + 1 <= s_ExplicitVarSizeWithMarker_Marker -> + s_ExplicitVarSizeWithMarker_Values[q1] < s_ExplicitVarSizeWithMarker_Values[q1 + 1] + | q1 : int(1..3)]), + and([q2 > s_ExplicitVarSizeWithMarker_Marker -> s_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..4)]), + and([s_Occurrence[q27] -> + or([q29 <= s_ExplicitVarSizeWithMarker_Marker /\ s_ExplicitVarSizeWithMarker_Values[q29] = q27 + | q29 : int(1..4)]) + | q27 : int(1..4)]), + and([q31 <= s_ExplicitVarSizeWithMarker_Marker -> s_Occurrence[s_ExplicitVarSizeWithMarker_Values[q31]] + | q31 : int(1..4)]) + diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_1_2-solution000001.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_1_2-solution000001.solution new file mode 100644 index 0000000000..bd956f44e3 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_3_1_2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 2, 3, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_1_2-solution000002.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_1_2-solution000002.solution new file mode 100644 index 0000000000..5963aac565 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_3_1_2-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 2, 3} +letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_1_2-solution000003.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_1_2-solution000003.solution new file mode 100644 index 0000000000..6eeacc9727 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_3_1_2-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 2, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_1_2-solution000004.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_1_2-solution000004.solution new file mode 100644 index 0000000000..560dd0f2f7 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_3_1_2-solution000004.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 3, 4} +letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_1_2-solution000005.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_1_2-solution000005.solution new file mode 100644 index 0000000000..8b4ecbb66d --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_3_1_2-solution000005.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 3} +letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_1_2-solution000006.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_1_2-solution000006.solution new file mode 100644 index 0000000000..40f3fd5c8f --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_3_1_2-solution000006.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {2, 3, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_1_2-solution000007.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_1_2-solution000007.solution new file mode 100644 index 0000000000..159a613983 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_3_1_2-solution000007.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {2, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_1_2.eprime b/tests/exhaustive/basic/comprehension_letting/expected/model_3_1_2.eprime new file mode 100644 index 0000000000..45efc09186 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_3_1_2.eprime @@ -0,0 +1,95 @@ +language ESSENCE' 1.0 + +find s_ExplicitVarSizeWithMarker_Marker: int(0..4) +find s_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +find s_Occurrence: matrix indexed by [int(1..4)] of bool +find s_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +letting let1 be -100 +find x: int(-100..100) +find conjure_aux1: int(-16..3) +branching on + [s_ExplicitVarSizeWithDummy, s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithMarker_Values, s_Occurrence, + x] +such that + and([and([q22 <= s_ExplicitVarSizeWithMarker_Marker, s_Occurrence[j], s_ExplicitVarSizeWithMarker_Values[q22] != j, + allDiff([s_ExplicitVarSizeWithMarker_Values[q22] + j, s_ExplicitVarSizeWithMarker_Values[q22] * j, + s_ExplicitVarSizeWithMarker_Values[q22] / j; + int(1..3)]), + (s_ExplicitVarSizeWithMarker_Values[q22] - j) % 2 = 0; + int(1..5)]) + -> + min([s_ExplicitVarSizeWithMarker_Values[q22] + j, s_ExplicitVarSizeWithMarker_Values[q22] - j, + s_ExplicitVarSizeWithMarker_Values[q22] * j, s_ExplicitVarSizeWithMarker_Values[q22] / j; + int(1..4)]) + <= conjure_aux1 + | q22 : int(1..4), j : int(1..4)]), + sum([toInt(and([q22 <= s_ExplicitVarSizeWithMarker_Marker, s_Occurrence[j], + s_ExplicitVarSizeWithMarker_Values[q22] != j, + allDiff([s_ExplicitVarSizeWithMarker_Values[q22] + j, s_ExplicitVarSizeWithMarker_Values[q22] * j, + s_ExplicitVarSizeWithMarker_Values[q22] / j; + int(1..3)]), + (s_ExplicitVarSizeWithMarker_Values[q22] - j) % 2 = 0; + int(1..5)])) + | q22 : int(1..4), j : int(1..4)]) + > 0 + -> + or([and([q22 <= s_ExplicitVarSizeWithMarker_Marker, s_Occurrence[j], s_ExplicitVarSizeWithMarker_Values[q22] != j, + allDiff([s_ExplicitVarSizeWithMarker_Values[q22] + j, s_ExplicitVarSizeWithMarker_Values[q22] * j, + s_ExplicitVarSizeWithMarker_Values[q22] / j; + int(1..3)]), + (s_ExplicitVarSizeWithMarker_Values[q22] - j) % 2 = 0; + int(1..5)]) + /\ + min([s_ExplicitVarSizeWithMarker_Values[q22] + j, s_ExplicitVarSizeWithMarker_Values[q22] - j, + s_ExplicitVarSizeWithMarker_Values[q22] * j, s_ExplicitVarSizeWithMarker_Values[q22] / j; + int(1..4)]) + = conjure_aux1 + | q22 : int(1..4), j : int(1..4)]), + sum([toInt(and([q22 <= s_ExplicitVarSizeWithMarker_Marker, s_Occurrence[j], + s_ExplicitVarSizeWithMarker_Values[q22] != j, + allDiff([s_ExplicitVarSizeWithMarker_Values[q22] + j, s_ExplicitVarSizeWithMarker_Values[q22] * j, + s_ExplicitVarSizeWithMarker_Values[q22] / j; + int(1..3)]), + (s_ExplicitVarSizeWithMarker_Values[q22] - j) % 2 = 0; + int(1..5)])) + | q22 : int(1..4), j : int(1..4)]) + = 0 + -> conjure_aux1 = -16, + x = conjure_aux1, + sum([toInt(and([q22 <= s_ExplicitVarSizeWithMarker_Marker, s_Occurrence[j], + s_ExplicitVarSizeWithMarker_Values[q22] != j, + allDiff([s_ExplicitVarSizeWithMarker_Values[q22] + j, s_ExplicitVarSizeWithMarker_Values[q22] * j, + s_ExplicitVarSizeWithMarker_Values[q22] / j; + int(1..3)]), + (s_ExplicitVarSizeWithMarker_Values[q22] - j) % 2 = 0; + int(1..5)])) + | q22 : int(1..4), j : int(1..4)]) + > 0, + and([q1 + 1 <= s_ExplicitVarSizeWithMarker_Marker -> + s_ExplicitVarSizeWithMarker_Values[q1] < s_ExplicitVarSizeWithMarker_Values[q1 + 1] + | q1 : int(1..3)]), + and([q2 > s_ExplicitVarSizeWithMarker_Marker -> s_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..4)]), + and([s_Occurrence[q44] -> + or([q46 <= s_ExplicitVarSizeWithMarker_Marker /\ s_ExplicitVarSizeWithMarker_Values[q46] = q44 + | q46 : int(1..4)]) + | q44 : int(1..4)]), + and([q48 <= s_ExplicitVarSizeWithMarker_Marker -> s_Occurrence[s_ExplicitVarSizeWithMarker_Values[q48]] + | q48 : int(1..4)]), + and([s_ExplicitVarSizeWithDummy[q5] < s_ExplicitVarSizeWithDummy[q5 + 1] \/ s_ExplicitVarSizeWithDummy[q5] = 5 + | q5 : int(1..3)]), + and([s_ExplicitVarSizeWithDummy[q6] = 5 -> s_ExplicitVarSizeWithDummy[q6 + 1] = 5 | q6 : int(1..3)]), + and([s_ExplicitVarSizeWithDummy[q10] != 5 -> + or([q12 <= s_ExplicitVarSizeWithMarker_Marker /\ + s_ExplicitVarSizeWithMarker_Values[q12] = s_ExplicitVarSizeWithDummy[q10] + | q12 : int(1..4)]) + | q10 : int(1..4)]), + and([q14 <= s_ExplicitVarSizeWithMarker_Marker -> + or([s_ExplicitVarSizeWithDummy[q16] != 5 /\ + s_ExplicitVarSizeWithDummy[q16] = s_ExplicitVarSizeWithMarker_Values[q14] + | q16 : int(1..4)]) + | q14 : int(1..4)]), + and([s_ExplicitVarSizeWithDummy[q18] != 5 -> s_Occurrence[s_ExplicitVarSizeWithDummy[q18]] | q18 : int(1..4)]), + and([s_Occurrence[q19] -> + or([s_ExplicitVarSizeWithDummy[q21] != 5 /\ s_ExplicitVarSizeWithDummy[q21] = q19 | q21 : int(1..4)]) + | q19 : int(1..4)]) + diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_1_4-solution000001.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_1_4-solution000001.solution new file mode 100644 index 0000000000..8b4ecbb66d --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_3_1_4-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 3} +letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_1_4-solution000002.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_1_4-solution000002.solution new file mode 100644 index 0000000000..159a613983 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_3_1_4-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {2, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_1_4-solution000003.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_1_4-solution000003.solution new file mode 100644 index 0000000000..5963aac565 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_3_1_4-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 2, 3} +letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_1_4-solution000004.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_1_4-solution000004.solution new file mode 100644 index 0000000000..6eeacc9727 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_3_1_4-solution000004.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 2, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_1_4-solution000005.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_1_4-solution000005.solution new file mode 100644 index 0000000000..560dd0f2f7 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_3_1_4-solution000005.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 3, 4} +letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_1_4-solution000006.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_1_4-solution000006.solution new file mode 100644 index 0000000000..40f3fd5c8f --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_3_1_4-solution000006.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {2, 3, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_1_4-solution000007.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_1_4-solution000007.solution new file mode 100644 index 0000000000..bd956f44e3 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_3_1_4-solution000007.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 2, 3, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_1_4.eprime b/tests/exhaustive/basic/comprehension_letting/expected/model_3_1_4.eprime new file mode 100644 index 0000000000..d5db5a23e1 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_3_1_4.eprime @@ -0,0 +1,99 @@ +language ESSENCE' 1.0 + +find s_ExplicitVarSizeWithMarker_Marker: int(0..4) +find s_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +find s_Occurrence: matrix indexed by [int(1..4)] of bool +find s_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find s_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +letting let1 be -100 +find x: int(-100..100) +find conjure_aux1: int(-16..3) +branching on + [s_ExplicitVarSizeWithFlags_Flags, s_ExplicitVarSizeWithFlags_Values, s_ExplicitVarSizeWithMarker_Marker, + s_ExplicitVarSizeWithMarker_Values, s_Occurrence, x] +such that + and([and([q23 <= s_ExplicitVarSizeWithMarker_Marker, s_Occurrence[j], s_ExplicitVarSizeWithMarker_Values[q23] != j, + allDiff([s_ExplicitVarSizeWithMarker_Values[q23] + j, s_ExplicitVarSizeWithMarker_Values[q23] * j, + s_ExplicitVarSizeWithMarker_Values[q23] / j; + int(1..3)]), + (s_ExplicitVarSizeWithMarker_Values[q23] - j) % 2 = 0; + int(1..5)]) + -> + min([s_ExplicitVarSizeWithMarker_Values[q23] + j, s_ExplicitVarSizeWithMarker_Values[q23] - j, + s_ExplicitVarSizeWithMarker_Values[q23] * j, s_ExplicitVarSizeWithMarker_Values[q23] / j; + int(1..4)]) + <= conjure_aux1 + | q23 : int(1..4), j : int(1..4)]), + sum([toInt(and([q23 <= s_ExplicitVarSizeWithMarker_Marker, s_Occurrence[j], + s_ExplicitVarSizeWithMarker_Values[q23] != j, + allDiff([s_ExplicitVarSizeWithMarker_Values[q23] + j, s_ExplicitVarSizeWithMarker_Values[q23] * j, + s_ExplicitVarSizeWithMarker_Values[q23] / j; + int(1..3)]), + (s_ExplicitVarSizeWithMarker_Values[q23] - j) % 2 = 0; + int(1..5)])) + | q23 : int(1..4), j : int(1..4)]) + > 0 + -> + or([and([q23 <= s_ExplicitVarSizeWithMarker_Marker, s_Occurrence[j], s_ExplicitVarSizeWithMarker_Values[q23] != j, + allDiff([s_ExplicitVarSizeWithMarker_Values[q23] + j, s_ExplicitVarSizeWithMarker_Values[q23] * j, + s_ExplicitVarSizeWithMarker_Values[q23] / j; + int(1..3)]), + (s_ExplicitVarSizeWithMarker_Values[q23] - j) % 2 = 0; + int(1..5)]) + /\ + min([s_ExplicitVarSizeWithMarker_Values[q23] + j, s_ExplicitVarSizeWithMarker_Values[q23] - j, + s_ExplicitVarSizeWithMarker_Values[q23] * j, s_ExplicitVarSizeWithMarker_Values[q23] / j; + int(1..4)]) + = conjure_aux1 + | q23 : int(1..4), j : int(1..4)]), + sum([toInt(and([q23 <= s_ExplicitVarSizeWithMarker_Marker, s_Occurrence[j], + s_ExplicitVarSizeWithMarker_Values[q23] != j, + allDiff([s_ExplicitVarSizeWithMarker_Values[q23] + j, s_ExplicitVarSizeWithMarker_Values[q23] * j, + s_ExplicitVarSizeWithMarker_Values[q23] / j; + int(1..3)]), + (s_ExplicitVarSizeWithMarker_Values[q23] - j) % 2 = 0; + int(1..5)])) + | q23 : int(1..4), j : int(1..4)]) + = 0 + -> conjure_aux1 = -16, + x = conjure_aux1, + sum([toInt(and([q23 <= s_ExplicitVarSizeWithMarker_Marker, s_Occurrence[j], + s_ExplicitVarSizeWithMarker_Values[q23] != j, + allDiff([s_ExplicitVarSizeWithMarker_Values[q23] + j, s_ExplicitVarSizeWithMarker_Values[q23] * j, + s_ExplicitVarSizeWithMarker_Values[q23] / j; + int(1..3)]), + (s_ExplicitVarSizeWithMarker_Values[q23] - j) % 2 = 0; + int(1..5)])) + | q23 : int(1..4), j : int(1..4)]) + > 0, + and([q1 + 1 <= s_ExplicitVarSizeWithMarker_Marker -> + s_ExplicitVarSizeWithMarker_Values[q1] < s_ExplicitVarSizeWithMarker_Values[q1 + 1] + | q1 : int(1..3)]), + and([q2 > s_ExplicitVarSizeWithMarker_Marker -> s_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..4)]), + and([s_Occurrence[q45] -> + or([q47 <= s_ExplicitVarSizeWithMarker_Marker /\ s_ExplicitVarSizeWithMarker_Values[q47] = q45 + | q47 : int(1..4)]) + | q45 : int(1..4)]), + and([q49 <= s_ExplicitVarSizeWithMarker_Marker -> s_Occurrence[s_ExplicitVarSizeWithMarker_Values[q49]] + | q49 : int(1..4)]), + and([s_ExplicitVarSizeWithFlags_Flags[q5 + 1] -> + s_ExplicitVarSizeWithFlags_Values[q5] < s_ExplicitVarSizeWithFlags_Values[q5 + 1] + | q5 : int(1..3)]), + and([s_ExplicitVarSizeWithFlags_Flags[q6] = false -> s_ExplicitVarSizeWithFlags_Values[q6] = 1 | q6 : int(1..4)]), + and([s_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> s_ExplicitVarSizeWithFlags_Flags[q7] | q7 : int(1..3)]), + and([s_ExplicitVarSizeWithFlags_Flags[q11] -> + or([q13 <= s_ExplicitVarSizeWithMarker_Marker /\ + s_ExplicitVarSizeWithMarker_Values[q13] = s_ExplicitVarSizeWithFlags_Values[q11] + | q13 : int(1..4)]) + | q11 : int(1..4)]), + and([q15 <= s_ExplicitVarSizeWithMarker_Marker -> + or([s_ExplicitVarSizeWithFlags_Flags[q17] /\ + s_ExplicitVarSizeWithFlags_Values[q17] = s_ExplicitVarSizeWithMarker_Values[q15] + | q17 : int(1..4)]) + | q15 : int(1..4)]), + and([s_ExplicitVarSizeWithFlags_Flags[q19] -> s_Occurrence[s_ExplicitVarSizeWithFlags_Values[q19]] + | q19 : int(1..4)]), + and([s_Occurrence[q20] -> + or([s_ExplicitVarSizeWithFlags_Flags[q22] /\ s_ExplicitVarSizeWithFlags_Values[q22] = q20 | q22 : int(1..4)]) + | q20 : int(1..4)]) + diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_2_1-solution000001.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_2_1-solution000001.solution new file mode 100644 index 0000000000..159a613983 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_3_2_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {2, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_2_1-solution000002.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_2_1-solution000002.solution new file mode 100644 index 0000000000..40f3fd5c8f --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_3_2_1-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {2, 3, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_2_1-solution000003.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_2_1-solution000003.solution new file mode 100644 index 0000000000..8b4ecbb66d --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_3_2_1-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 3} +letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_2_1-solution000004.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_2_1-solution000004.solution new file mode 100644 index 0000000000..560dd0f2f7 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_3_2_1-solution000004.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 3, 4} +letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_2_1-solution000005.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_2_1-solution000005.solution new file mode 100644 index 0000000000..6eeacc9727 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_3_2_1-solution000005.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 2, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_2_1-solution000006.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_2_1-solution000006.solution new file mode 100644 index 0000000000..5963aac565 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_3_2_1-solution000006.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 2, 3} +letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_2_1-solution000007.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_2_1-solution000007.solution new file mode 100644 index 0000000000..bd956f44e3 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_3_2_1-solution000007.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 2, 3, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_2_1.eprime b/tests/exhaustive/basic/comprehension_letting/expected/model_3_2_1.eprime new file mode 100644 index 0000000000..b6f0c01a86 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_3_2_1.eprime @@ -0,0 +1,106 @@ +language ESSENCE' 1.0 + +find s_ExplicitVarSizeWithMarker_Marker: int(0..4) +find s_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +find s_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +find s_Occurrence: matrix indexed by [int(1..4)] of bool +letting let1 be -100 +find x: int(-100..100) +find conjure_aux1: int(-20..3) +branching on + [s_Occurrence, s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithMarker_Values, s_ExplicitVarSizeWithDummy, + x] +such that + and([and([q17 <= s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithDummy[q18] != 5, + s_ExplicitVarSizeWithMarker_Values[q17] != s_ExplicitVarSizeWithDummy[q18], + allDiff([s_ExplicitVarSizeWithMarker_Values[q17] + s_ExplicitVarSizeWithDummy[q18], + s_ExplicitVarSizeWithMarker_Values[q17] * s_ExplicitVarSizeWithDummy[q18], + s_ExplicitVarSizeWithMarker_Values[q17] / s_ExplicitVarSizeWithDummy[q18]; + int(1..3)]), + (s_ExplicitVarSizeWithMarker_Values[q17] - s_ExplicitVarSizeWithDummy[q18]) % 2 = 0; + int(1..5)]) + -> + min([s_ExplicitVarSizeWithMarker_Values[q17] + s_ExplicitVarSizeWithDummy[q18], + s_ExplicitVarSizeWithMarker_Values[q17] - s_ExplicitVarSizeWithDummy[q18], + s_ExplicitVarSizeWithMarker_Values[q17] * s_ExplicitVarSizeWithDummy[q18], + s_ExplicitVarSizeWithMarker_Values[q17] / s_ExplicitVarSizeWithDummy[q18]; + int(1..4)]) + <= conjure_aux1 + | q17 : int(1..4), q18 : int(1..4)]), + sum([toInt(and([q17 <= s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithDummy[q18] != 5, + s_ExplicitVarSizeWithMarker_Values[q17] != s_ExplicitVarSizeWithDummy[q18], + allDiff([s_ExplicitVarSizeWithMarker_Values[q17] + s_ExplicitVarSizeWithDummy[q18], + s_ExplicitVarSizeWithMarker_Values[q17] * s_ExplicitVarSizeWithDummy[q18], + s_ExplicitVarSizeWithMarker_Values[q17] / s_ExplicitVarSizeWithDummy[q18]; + int(1..3)]), + (s_ExplicitVarSizeWithMarker_Values[q17] - s_ExplicitVarSizeWithDummy[q18]) % 2 = 0; + int(1..5)])) + | q17 : int(1..4), q18 : int(1..4)]) + > 0 + -> + or([and([q17 <= s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithDummy[q18] != 5, + s_ExplicitVarSizeWithMarker_Values[q17] != s_ExplicitVarSizeWithDummy[q18], + allDiff([s_ExplicitVarSizeWithMarker_Values[q17] + s_ExplicitVarSizeWithDummy[q18], + s_ExplicitVarSizeWithMarker_Values[q17] * s_ExplicitVarSizeWithDummy[q18], + s_ExplicitVarSizeWithMarker_Values[q17] / s_ExplicitVarSizeWithDummy[q18]; + int(1..3)]), + (s_ExplicitVarSizeWithMarker_Values[q17] - s_ExplicitVarSizeWithDummy[q18]) % 2 = 0; + int(1..5)]) + /\ + min([s_ExplicitVarSizeWithMarker_Values[q17] + s_ExplicitVarSizeWithDummy[q18], + s_ExplicitVarSizeWithMarker_Values[q17] - s_ExplicitVarSizeWithDummy[q18], + s_ExplicitVarSizeWithMarker_Values[q17] * s_ExplicitVarSizeWithDummy[q18], + s_ExplicitVarSizeWithMarker_Values[q17] / s_ExplicitVarSizeWithDummy[q18]; + int(1..4)]) + = conjure_aux1 + | q17 : int(1..4), q18 : int(1..4)]), + sum([toInt(and([q17 <= s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithDummy[q18] != 5, + s_ExplicitVarSizeWithMarker_Values[q17] != s_ExplicitVarSizeWithDummy[q18], + allDiff([s_ExplicitVarSizeWithMarker_Values[q17] + s_ExplicitVarSizeWithDummy[q18], + s_ExplicitVarSizeWithMarker_Values[q17] * s_ExplicitVarSizeWithDummy[q18], + s_ExplicitVarSizeWithMarker_Values[q17] / s_ExplicitVarSizeWithDummy[q18]; + int(1..3)]), + (s_ExplicitVarSizeWithMarker_Values[q17] - s_ExplicitVarSizeWithDummy[q18]) % 2 = 0; + int(1..5)])) + | q17 : int(1..4), q18 : int(1..4)]) + = 0 + -> conjure_aux1 = -20, + x = conjure_aux1, + sum([toInt(and([q17 <= s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithDummy[q18] != 5, + s_ExplicitVarSizeWithMarker_Values[q17] != s_ExplicitVarSizeWithDummy[q18], + allDiff([s_ExplicitVarSizeWithMarker_Values[q17] + s_ExplicitVarSizeWithDummy[q18], + s_ExplicitVarSizeWithMarker_Values[q17] * s_ExplicitVarSizeWithDummy[q18], + s_ExplicitVarSizeWithMarker_Values[q17] / s_ExplicitVarSizeWithDummy[q18]; + int(1..3)]), + (s_ExplicitVarSizeWithMarker_Values[q17] - s_ExplicitVarSizeWithDummy[q18]) % 2 = 0; + int(1..5)])) + | q17 : int(1..4), q18 : int(1..4)]) + > 0, + and([q1 + 1 <= s_ExplicitVarSizeWithMarker_Marker -> + s_ExplicitVarSizeWithMarker_Values[q1] < s_ExplicitVarSizeWithMarker_Values[q1 + 1] + | q1 : int(1..3)]), + and([q2 > s_ExplicitVarSizeWithMarker_Marker -> s_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..4)]), + and([s_ExplicitVarSizeWithDummy[q4] < s_ExplicitVarSizeWithDummy[q4 + 1] \/ s_ExplicitVarSizeWithDummy[q4] = 5 + | q4 : int(1..3)]), + and([s_ExplicitVarSizeWithDummy[q5] = 5 -> s_ExplicitVarSizeWithDummy[q5 + 1] = 5 | q5 : int(1..3)]), + and([s_ExplicitVarSizeWithDummy[q9] != 5 -> + or([q11 <= s_ExplicitVarSizeWithMarker_Marker /\ + s_ExplicitVarSizeWithMarker_Values[q11] = s_ExplicitVarSizeWithDummy[q9] + | q11 : int(1..4)]) + | q9 : int(1..4)]), + and([q13 <= s_ExplicitVarSizeWithMarker_Marker -> + or([s_ExplicitVarSizeWithDummy[q15] != 5 /\ + s_ExplicitVarSizeWithDummy[q15] = s_ExplicitVarSizeWithMarker_Values[q13] + | q15 : int(1..4)]) + | q13 : int(1..4)]), + and([s_Occurrence[q40] -> + or([q42 <= s_ExplicitVarSizeWithMarker_Marker /\ s_ExplicitVarSizeWithMarker_Values[q42] = q40 + | q42 : int(1..4)]) + | q40 : int(1..4)]), + and([q44 <= s_ExplicitVarSizeWithMarker_Marker -> s_Occurrence[s_ExplicitVarSizeWithMarker_Values[q44]] + | q44 : int(1..4)]), + and([s_Occurrence[q45] -> + or([s_ExplicitVarSizeWithDummy[q47] != 5 /\ s_ExplicitVarSizeWithDummy[q47] = q45 | q47 : int(1..4)]) + | q45 : int(1..4)]), + and([s_ExplicitVarSizeWithDummy[q49] != 5 -> s_Occurrence[s_ExplicitVarSizeWithDummy[q49]] | q49 : int(1..4)]) + diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_2_2-solution000001.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_2_2-solution000001.solution new file mode 100644 index 0000000000..bd956f44e3 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_3_2_2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 2, 3, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_2_2-solution000002.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_2_2-solution000002.solution new file mode 100644 index 0000000000..5963aac565 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_3_2_2-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 2, 3} +letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_2_2-solution000003.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_2_2-solution000003.solution new file mode 100644 index 0000000000..6eeacc9727 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_3_2_2-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 2, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_2_2-solution000004.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_2_2-solution000004.solution new file mode 100644 index 0000000000..560dd0f2f7 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_3_2_2-solution000004.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 3, 4} +letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_2_2-solution000005.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_2_2-solution000005.solution new file mode 100644 index 0000000000..8b4ecbb66d --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_3_2_2-solution000005.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 3} +letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_2_2-solution000006.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_2_2-solution000006.solution new file mode 100644 index 0000000000..40f3fd5c8f --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_3_2_2-solution000006.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {2, 3, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_2_2-solution000007.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_2_2-solution000007.solution new file mode 100644 index 0000000000..159a613983 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_3_2_2-solution000007.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {2, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_2_2.eprime b/tests/exhaustive/basic/comprehension_letting/expected/model_3_2_2.eprime new file mode 100644 index 0000000000..4259b37168 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_3_2_2.eprime @@ -0,0 +1,93 @@ +language ESSENCE' 1.0 + +find s_ExplicitVarSizeWithMarker_Marker: int(0..4) +find s_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +find s_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +letting let1 be -100 +find x: int(-100..100) +find conjure_aux1: int(-20..3) +branching on [s_ExplicitVarSizeWithDummy, s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithMarker_Values, x] +such that + and([and([q16 <= s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithDummy[q17] != 5, + s_ExplicitVarSizeWithMarker_Values[q16] != s_ExplicitVarSizeWithDummy[q17], + allDiff([s_ExplicitVarSizeWithMarker_Values[q16] + s_ExplicitVarSizeWithDummy[q17], + s_ExplicitVarSizeWithMarker_Values[q16] * s_ExplicitVarSizeWithDummy[q17], + s_ExplicitVarSizeWithMarker_Values[q16] / s_ExplicitVarSizeWithDummy[q17]; + int(1..3)]), + (s_ExplicitVarSizeWithMarker_Values[q16] - s_ExplicitVarSizeWithDummy[q17]) % 2 = 0; + int(1..5)]) + -> + min([s_ExplicitVarSizeWithMarker_Values[q16] + s_ExplicitVarSizeWithDummy[q17], + s_ExplicitVarSizeWithMarker_Values[q16] - s_ExplicitVarSizeWithDummy[q17], + s_ExplicitVarSizeWithMarker_Values[q16] * s_ExplicitVarSizeWithDummy[q17], + s_ExplicitVarSizeWithMarker_Values[q16] / s_ExplicitVarSizeWithDummy[q17]; + int(1..4)]) + <= conjure_aux1 + | q16 : int(1..4), q17 : int(1..4)]), + sum([toInt(and([q16 <= s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithDummy[q17] != 5, + s_ExplicitVarSizeWithMarker_Values[q16] != s_ExplicitVarSizeWithDummy[q17], + allDiff([s_ExplicitVarSizeWithMarker_Values[q16] + s_ExplicitVarSizeWithDummy[q17], + s_ExplicitVarSizeWithMarker_Values[q16] * s_ExplicitVarSizeWithDummy[q17], + s_ExplicitVarSizeWithMarker_Values[q16] / s_ExplicitVarSizeWithDummy[q17]; + int(1..3)]), + (s_ExplicitVarSizeWithMarker_Values[q16] - s_ExplicitVarSizeWithDummy[q17]) % 2 = 0; + int(1..5)])) + | q16 : int(1..4), q17 : int(1..4)]) + > 0 + -> + or([and([q16 <= s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithDummy[q17] != 5, + s_ExplicitVarSizeWithMarker_Values[q16] != s_ExplicitVarSizeWithDummy[q17], + allDiff([s_ExplicitVarSizeWithMarker_Values[q16] + s_ExplicitVarSizeWithDummy[q17], + s_ExplicitVarSizeWithMarker_Values[q16] * s_ExplicitVarSizeWithDummy[q17], + s_ExplicitVarSizeWithMarker_Values[q16] / s_ExplicitVarSizeWithDummy[q17]; + int(1..3)]), + (s_ExplicitVarSizeWithMarker_Values[q16] - s_ExplicitVarSizeWithDummy[q17]) % 2 = 0; + int(1..5)]) + /\ + min([s_ExplicitVarSizeWithMarker_Values[q16] + s_ExplicitVarSizeWithDummy[q17], + s_ExplicitVarSizeWithMarker_Values[q16] - s_ExplicitVarSizeWithDummy[q17], + s_ExplicitVarSizeWithMarker_Values[q16] * s_ExplicitVarSizeWithDummy[q17], + s_ExplicitVarSizeWithMarker_Values[q16] / s_ExplicitVarSizeWithDummy[q17]; + int(1..4)]) + = conjure_aux1 + | q16 : int(1..4), q17 : int(1..4)]), + sum([toInt(and([q16 <= s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithDummy[q17] != 5, + s_ExplicitVarSizeWithMarker_Values[q16] != s_ExplicitVarSizeWithDummy[q17], + allDiff([s_ExplicitVarSizeWithMarker_Values[q16] + s_ExplicitVarSizeWithDummy[q17], + s_ExplicitVarSizeWithMarker_Values[q16] * s_ExplicitVarSizeWithDummy[q17], + s_ExplicitVarSizeWithMarker_Values[q16] / s_ExplicitVarSizeWithDummy[q17]; + int(1..3)]), + (s_ExplicitVarSizeWithMarker_Values[q16] - s_ExplicitVarSizeWithDummy[q17]) % 2 = 0; + int(1..5)])) + | q16 : int(1..4), q17 : int(1..4)]) + = 0 + -> conjure_aux1 = -20, + x = conjure_aux1, + sum([toInt(and([q16 <= s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithDummy[q17] != 5, + s_ExplicitVarSizeWithMarker_Values[q16] != s_ExplicitVarSizeWithDummy[q17], + allDiff([s_ExplicitVarSizeWithMarker_Values[q16] + s_ExplicitVarSizeWithDummy[q17], + s_ExplicitVarSizeWithMarker_Values[q16] * s_ExplicitVarSizeWithDummy[q17], + s_ExplicitVarSizeWithMarker_Values[q16] / s_ExplicitVarSizeWithDummy[q17]; + int(1..3)]), + (s_ExplicitVarSizeWithMarker_Values[q16] - s_ExplicitVarSizeWithDummy[q17]) % 2 = 0; + int(1..5)])) + | q16 : int(1..4), q17 : int(1..4)]) + > 0, + and([q1 + 1 <= s_ExplicitVarSizeWithMarker_Marker -> + s_ExplicitVarSizeWithMarker_Values[q1] < s_ExplicitVarSizeWithMarker_Values[q1 + 1] + | q1 : int(1..3)]), + and([q2 > s_ExplicitVarSizeWithMarker_Marker -> s_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..4)]), + and([s_ExplicitVarSizeWithDummy[q4] < s_ExplicitVarSizeWithDummy[q4 + 1] \/ s_ExplicitVarSizeWithDummy[q4] = 5 + | q4 : int(1..3)]), + and([s_ExplicitVarSizeWithDummy[q5] = 5 -> s_ExplicitVarSizeWithDummy[q5 + 1] = 5 | q5 : int(1..3)]), + and([s_ExplicitVarSizeWithDummy[q9] != 5 -> + or([q11 <= s_ExplicitVarSizeWithMarker_Marker /\ + s_ExplicitVarSizeWithMarker_Values[q11] = s_ExplicitVarSizeWithDummy[q9] + | q11 : int(1..4)]) + | q9 : int(1..4)]), + and([q13 <= s_ExplicitVarSizeWithMarker_Marker -> + or([s_ExplicitVarSizeWithDummy[q15] != 5 /\ + s_ExplicitVarSizeWithDummy[q15] = s_ExplicitVarSizeWithMarker_Values[q13] + | q15 : int(1..4)]) + | q13 : int(1..4)]) + diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_2_4-solution000001.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_2_4-solution000001.solution new file mode 100644 index 0000000000..8b4ecbb66d --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_3_2_4-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 3} +letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_2_4-solution000002.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_2_4-solution000002.solution new file mode 100644 index 0000000000..159a613983 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_3_2_4-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {2, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_2_4-solution000003.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_2_4-solution000003.solution new file mode 100644 index 0000000000..5963aac565 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_3_2_4-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 2, 3} +letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_2_4-solution000004.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_2_4-solution000004.solution new file mode 100644 index 0000000000..6eeacc9727 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_3_2_4-solution000004.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 2, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_2_4-solution000005.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_2_4-solution000005.solution new file mode 100644 index 0000000000..560dd0f2f7 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_3_2_4-solution000005.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 3, 4} +letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_2_4-solution000006.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_2_4-solution000006.solution new file mode 100644 index 0000000000..40f3fd5c8f --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_3_2_4-solution000006.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {2, 3, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_2_4-solution000007.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_2_4-solution000007.solution new file mode 100644 index 0000000000..bd956f44e3 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_3_2_4-solution000007.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 2, 3, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_2_4.eprime b/tests/exhaustive/basic/comprehension_letting/expected/model_3_2_4.eprime new file mode 100644 index 0000000000..0d153c4cd7 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_3_2_4.eprime @@ -0,0 +1,123 @@ +language ESSENCE' 1.0 + +find s_ExplicitVarSizeWithMarker_Marker: int(0..4) +find s_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +find s_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +find s_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find s_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +letting let1 be -100 +find x: int(-100..100) +find conjure_aux1: int(-20..3) +branching on + [s_ExplicitVarSizeWithFlags_Flags, s_ExplicitVarSizeWithFlags_Values, s_ExplicitVarSizeWithMarker_Marker, + s_ExplicitVarSizeWithMarker_Values, s_ExplicitVarSizeWithDummy, x] +such that + and([and([q37 <= s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithDummy[q38] != 5, + s_ExplicitVarSizeWithMarker_Values[q37] != s_ExplicitVarSizeWithDummy[q38], + allDiff([s_ExplicitVarSizeWithMarker_Values[q37] + s_ExplicitVarSizeWithDummy[q38], + s_ExplicitVarSizeWithMarker_Values[q37] * s_ExplicitVarSizeWithDummy[q38], + s_ExplicitVarSizeWithMarker_Values[q37] / s_ExplicitVarSizeWithDummy[q38]; + int(1..3)]), + (s_ExplicitVarSizeWithMarker_Values[q37] - s_ExplicitVarSizeWithDummy[q38]) % 2 = 0; + int(1..5)]) + -> + min([s_ExplicitVarSizeWithMarker_Values[q37] + s_ExplicitVarSizeWithDummy[q38], + s_ExplicitVarSizeWithMarker_Values[q37] - s_ExplicitVarSizeWithDummy[q38], + s_ExplicitVarSizeWithMarker_Values[q37] * s_ExplicitVarSizeWithDummy[q38], + s_ExplicitVarSizeWithMarker_Values[q37] / s_ExplicitVarSizeWithDummy[q38]; + int(1..4)]) + <= conjure_aux1 + | q37 : int(1..4), q38 : int(1..4)]), + sum([toInt(and([q37 <= s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithDummy[q38] != 5, + s_ExplicitVarSizeWithMarker_Values[q37] != s_ExplicitVarSizeWithDummy[q38], + allDiff([s_ExplicitVarSizeWithMarker_Values[q37] + s_ExplicitVarSizeWithDummy[q38], + s_ExplicitVarSizeWithMarker_Values[q37] * s_ExplicitVarSizeWithDummy[q38], + s_ExplicitVarSizeWithMarker_Values[q37] / s_ExplicitVarSizeWithDummy[q38]; + int(1..3)]), + (s_ExplicitVarSizeWithMarker_Values[q37] - s_ExplicitVarSizeWithDummy[q38]) % 2 = 0; + int(1..5)])) + | q37 : int(1..4), q38 : int(1..4)]) + > 0 + -> + or([and([q37 <= s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithDummy[q38] != 5, + s_ExplicitVarSizeWithMarker_Values[q37] != s_ExplicitVarSizeWithDummy[q38], + allDiff([s_ExplicitVarSizeWithMarker_Values[q37] + s_ExplicitVarSizeWithDummy[q38], + s_ExplicitVarSizeWithMarker_Values[q37] * s_ExplicitVarSizeWithDummy[q38], + s_ExplicitVarSizeWithMarker_Values[q37] / s_ExplicitVarSizeWithDummy[q38]; + int(1..3)]), + (s_ExplicitVarSizeWithMarker_Values[q37] - s_ExplicitVarSizeWithDummy[q38]) % 2 = 0; + int(1..5)]) + /\ + min([s_ExplicitVarSizeWithMarker_Values[q37] + s_ExplicitVarSizeWithDummy[q38], + s_ExplicitVarSizeWithMarker_Values[q37] - s_ExplicitVarSizeWithDummy[q38], + s_ExplicitVarSizeWithMarker_Values[q37] * s_ExplicitVarSizeWithDummy[q38], + s_ExplicitVarSizeWithMarker_Values[q37] / s_ExplicitVarSizeWithDummy[q38]; + int(1..4)]) + = conjure_aux1 + | q37 : int(1..4), q38 : int(1..4)]), + sum([toInt(and([q37 <= s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithDummy[q38] != 5, + s_ExplicitVarSizeWithMarker_Values[q37] != s_ExplicitVarSizeWithDummy[q38], + allDiff([s_ExplicitVarSizeWithMarker_Values[q37] + s_ExplicitVarSizeWithDummy[q38], + s_ExplicitVarSizeWithMarker_Values[q37] * s_ExplicitVarSizeWithDummy[q38], + s_ExplicitVarSizeWithMarker_Values[q37] / s_ExplicitVarSizeWithDummy[q38]; + int(1..3)]), + (s_ExplicitVarSizeWithMarker_Values[q37] - s_ExplicitVarSizeWithDummy[q38]) % 2 = 0; + int(1..5)])) + | q37 : int(1..4), q38 : int(1..4)]) + = 0 + -> conjure_aux1 = -20, + x = conjure_aux1, + sum([toInt(and([q37 <= s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithDummy[q38] != 5, + s_ExplicitVarSizeWithMarker_Values[q37] != s_ExplicitVarSizeWithDummy[q38], + allDiff([s_ExplicitVarSizeWithMarker_Values[q37] + s_ExplicitVarSizeWithDummy[q38], + s_ExplicitVarSizeWithMarker_Values[q37] * s_ExplicitVarSizeWithDummy[q38], + s_ExplicitVarSizeWithMarker_Values[q37] / s_ExplicitVarSizeWithDummy[q38]; + int(1..3)]), + (s_ExplicitVarSizeWithMarker_Values[q37] - s_ExplicitVarSizeWithDummy[q38]) % 2 = 0; + int(1..5)])) + | q37 : int(1..4), q38 : int(1..4)]) + > 0, + and([q1 + 1 <= s_ExplicitVarSizeWithMarker_Marker -> + s_ExplicitVarSizeWithMarker_Values[q1] < s_ExplicitVarSizeWithMarker_Values[q1 + 1] + | q1 : int(1..3)]), + and([q2 > s_ExplicitVarSizeWithMarker_Marker -> s_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..4)]), + and([s_ExplicitVarSizeWithDummy[q4] < s_ExplicitVarSizeWithDummy[q4 + 1] \/ s_ExplicitVarSizeWithDummy[q4] = 5 + | q4 : int(1..3)]), + and([s_ExplicitVarSizeWithDummy[q5] = 5 -> s_ExplicitVarSizeWithDummy[q5 + 1] = 5 | q5 : int(1..3)]), + and([s_ExplicitVarSizeWithDummy[q9] != 5 -> + or([q11 <= s_ExplicitVarSizeWithMarker_Marker /\ + s_ExplicitVarSizeWithMarker_Values[q11] = s_ExplicitVarSizeWithDummy[q9] + | q11 : int(1..4)]) + | q9 : int(1..4)]), + and([q13 <= s_ExplicitVarSizeWithMarker_Marker -> + or([s_ExplicitVarSizeWithDummy[q15] != 5 /\ + s_ExplicitVarSizeWithDummy[q15] = s_ExplicitVarSizeWithMarker_Values[q13] + | q15 : int(1..4)]) + | q13 : int(1..4)]), + and([s_ExplicitVarSizeWithFlags_Flags[q16 + 1] -> + s_ExplicitVarSizeWithFlags_Values[q16] < s_ExplicitVarSizeWithFlags_Values[q16 + 1] + | q16 : int(1..3)]), + and([s_ExplicitVarSizeWithFlags_Flags[q17] = false -> s_ExplicitVarSizeWithFlags_Values[q17] = 1 + | q17 : int(1..4)]), + and([s_ExplicitVarSizeWithFlags_Flags[q18 + 1] -> s_ExplicitVarSizeWithFlags_Flags[q18] | q18 : int(1..3)]), + and([s_ExplicitVarSizeWithFlags_Flags[q22] -> + or([q24 <= s_ExplicitVarSizeWithMarker_Marker /\ + s_ExplicitVarSizeWithMarker_Values[q24] = s_ExplicitVarSizeWithFlags_Values[q22] + | q24 : int(1..4)]) + | q22 : int(1..4)]), + and([q26 <= s_ExplicitVarSizeWithMarker_Marker -> + or([s_ExplicitVarSizeWithFlags_Flags[q28] /\ + s_ExplicitVarSizeWithFlags_Values[q28] = s_ExplicitVarSizeWithMarker_Values[q26] + | q28 : int(1..4)]) + | q26 : int(1..4)]), + and([s_ExplicitVarSizeWithFlags_Flags[q30] -> + or([s_ExplicitVarSizeWithDummy[q32] != 5 /\ + s_ExplicitVarSizeWithDummy[q32] = s_ExplicitVarSizeWithFlags_Values[q30] + | q32 : int(1..4)]) + | q30 : int(1..4)]), + and([s_ExplicitVarSizeWithDummy[q34] != 5 -> + or([s_ExplicitVarSizeWithFlags_Flags[q36] /\ + s_ExplicitVarSizeWithFlags_Values[q36] = s_ExplicitVarSizeWithDummy[q34] + | q36 : int(1..4)]) + | q34 : int(1..4)]) + diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_1-solution000001.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_1-solution000001.solution new file mode 100644 index 0000000000..159a613983 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {2, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_1-solution000002.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_1-solution000002.solution new file mode 100644 index 0000000000..40f3fd5c8f --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_1-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {2, 3, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_1-solution000003.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_1-solution000003.solution new file mode 100644 index 0000000000..8b4ecbb66d --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_1-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 3} +letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_1-solution000004.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_1-solution000004.solution new file mode 100644 index 0000000000..560dd0f2f7 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_1-solution000004.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 3, 4} +letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_1-solution000005.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_1-solution000005.solution new file mode 100644 index 0000000000..6eeacc9727 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_1-solution000005.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 2, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_1-solution000006.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_1-solution000006.solution new file mode 100644 index 0000000000..5963aac565 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_1-solution000006.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 2, 3} +letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_1-solution000007.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_1-solution000007.solution new file mode 100644 index 0000000000..bd956f44e3 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_1-solution000007.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 2, 3, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_1.eprime b/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_1.eprime new file mode 100644 index 0000000000..7c865a4def --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_1.eprime @@ -0,0 +1,86 @@ +language ESSENCE' 1.0 + +find s_ExplicitVarSizeWithMarker_Marker: int(0..4) +find s_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +find s_Occurrence: matrix indexed by [int(1..4)] of bool +letting let1 be -100 +find x: int(-100..100) +find conjure_aux1: int(-16..3) +branching on [s_Occurrence, s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithMarker_Values, x] +such that + and([and([q5 <= s_ExplicitVarSizeWithMarker_Marker, q6 <= s_ExplicitVarSizeWithMarker_Marker, + s_ExplicitVarSizeWithMarker_Values[q5] != s_ExplicitVarSizeWithMarker_Values[q6], + allDiff([s_ExplicitVarSizeWithMarker_Values[q5] + s_ExplicitVarSizeWithMarker_Values[q6], + s_ExplicitVarSizeWithMarker_Values[q5] * s_ExplicitVarSizeWithMarker_Values[q6], + s_ExplicitVarSizeWithMarker_Values[q5] / s_ExplicitVarSizeWithMarker_Values[q6]; + int(1..3)]), + (s_ExplicitVarSizeWithMarker_Values[q5] - s_ExplicitVarSizeWithMarker_Values[q6]) % 2 = 0; + int(1..5)]) + -> + min([s_ExplicitVarSizeWithMarker_Values[q5] + s_ExplicitVarSizeWithMarker_Values[q6], + s_ExplicitVarSizeWithMarker_Values[q5] - s_ExplicitVarSizeWithMarker_Values[q6], + s_ExplicitVarSizeWithMarker_Values[q5] * s_ExplicitVarSizeWithMarker_Values[q6], + s_ExplicitVarSizeWithMarker_Values[q5] / s_ExplicitVarSizeWithMarker_Values[q6]; + int(1..4)]) + <= conjure_aux1 + | q5 : int(1..4), q6 : int(1..4)]), + sum([toInt(and([q5 <= s_ExplicitVarSizeWithMarker_Marker, q6 <= s_ExplicitVarSizeWithMarker_Marker, + s_ExplicitVarSizeWithMarker_Values[q5] != s_ExplicitVarSizeWithMarker_Values[q6], + allDiff([s_ExplicitVarSizeWithMarker_Values[q5] + s_ExplicitVarSizeWithMarker_Values[q6], + s_ExplicitVarSizeWithMarker_Values[q5] * s_ExplicitVarSizeWithMarker_Values[q6], + s_ExplicitVarSizeWithMarker_Values[q5] / s_ExplicitVarSizeWithMarker_Values[q6]; + int(1..3)]), + (s_ExplicitVarSizeWithMarker_Values[q5] - s_ExplicitVarSizeWithMarker_Values[q6]) % 2 = 0; + int(1..5)])) + | q5 : int(1..4), q6 : int(1..4)]) + > 0 + -> + or([and([q5 <= s_ExplicitVarSizeWithMarker_Marker, q6 <= s_ExplicitVarSizeWithMarker_Marker, + s_ExplicitVarSizeWithMarker_Values[q5] != s_ExplicitVarSizeWithMarker_Values[q6], + allDiff([s_ExplicitVarSizeWithMarker_Values[q5] + s_ExplicitVarSizeWithMarker_Values[q6], + s_ExplicitVarSizeWithMarker_Values[q5] * s_ExplicitVarSizeWithMarker_Values[q6], + s_ExplicitVarSizeWithMarker_Values[q5] / s_ExplicitVarSizeWithMarker_Values[q6]; + int(1..3)]), + (s_ExplicitVarSizeWithMarker_Values[q5] - s_ExplicitVarSizeWithMarker_Values[q6]) % 2 = 0; + int(1..5)]) + /\ + min([s_ExplicitVarSizeWithMarker_Values[q5] + s_ExplicitVarSizeWithMarker_Values[q6], + s_ExplicitVarSizeWithMarker_Values[q5] - s_ExplicitVarSizeWithMarker_Values[q6], + s_ExplicitVarSizeWithMarker_Values[q5] * s_ExplicitVarSizeWithMarker_Values[q6], + s_ExplicitVarSizeWithMarker_Values[q5] / s_ExplicitVarSizeWithMarker_Values[q6]; + int(1..4)]) + = conjure_aux1 + | q5 : int(1..4), q6 : int(1..4)]), + sum([toInt(and([q5 <= s_ExplicitVarSizeWithMarker_Marker, q6 <= s_ExplicitVarSizeWithMarker_Marker, + s_ExplicitVarSizeWithMarker_Values[q5] != s_ExplicitVarSizeWithMarker_Values[q6], + allDiff([s_ExplicitVarSizeWithMarker_Values[q5] + s_ExplicitVarSizeWithMarker_Values[q6], + s_ExplicitVarSizeWithMarker_Values[q5] * s_ExplicitVarSizeWithMarker_Values[q6], + s_ExplicitVarSizeWithMarker_Values[q5] / s_ExplicitVarSizeWithMarker_Values[q6]; + int(1..3)]), + (s_ExplicitVarSizeWithMarker_Values[q5] - s_ExplicitVarSizeWithMarker_Values[q6]) % 2 = 0; + int(1..5)])) + | q5 : int(1..4), q6 : int(1..4)]) + = 0 + -> conjure_aux1 = -16, + x = conjure_aux1, + sum([toInt(and([q5 <= s_ExplicitVarSizeWithMarker_Marker, q6 <= s_ExplicitVarSizeWithMarker_Marker, + s_ExplicitVarSizeWithMarker_Values[q5] != s_ExplicitVarSizeWithMarker_Values[q6], + allDiff([s_ExplicitVarSizeWithMarker_Values[q5] + s_ExplicitVarSizeWithMarker_Values[q6], + s_ExplicitVarSizeWithMarker_Values[q5] * s_ExplicitVarSizeWithMarker_Values[q6], + s_ExplicitVarSizeWithMarker_Values[q5] / s_ExplicitVarSizeWithMarker_Values[q6]; + int(1..3)]), + (s_ExplicitVarSizeWithMarker_Values[q5] - s_ExplicitVarSizeWithMarker_Values[q6]) % 2 = 0; + int(1..5)])) + | q5 : int(1..4), q6 : int(1..4)]) + > 0, + and([q1 + 1 <= s_ExplicitVarSizeWithMarker_Marker -> + s_ExplicitVarSizeWithMarker_Values[q1] < s_ExplicitVarSizeWithMarker_Values[q1 + 1] + | q1 : int(1..3)]), + and([q2 > s_ExplicitVarSizeWithMarker_Marker -> s_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..4)]), + and([s_Occurrence[q28] -> + or([q30 <= s_ExplicitVarSizeWithMarker_Marker /\ s_ExplicitVarSizeWithMarker_Values[q30] = q28 + | q30 : int(1..4)]) + | q28 : int(1..4)]), + and([q32 <= s_ExplicitVarSizeWithMarker_Marker -> s_Occurrence[s_ExplicitVarSizeWithMarker_Values[q32]] + | q32 : int(1..4)]) + diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_2-solution000001.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_2-solution000001.solution new file mode 100644 index 0000000000..bd956f44e3 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 2, 3, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_2-solution000002.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_2-solution000002.solution new file mode 100644 index 0000000000..5963aac565 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_2-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 2, 3} +letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_2-solution000003.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_2-solution000003.solution new file mode 100644 index 0000000000..6eeacc9727 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_2-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 2, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_2-solution000004.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_2-solution000004.solution new file mode 100644 index 0000000000..560dd0f2f7 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_2-solution000004.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 3, 4} +letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_2-solution000005.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_2-solution000005.solution new file mode 100644 index 0000000000..8b4ecbb66d --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_2-solution000005.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 3} +letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_2-solution000006.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_2-solution000006.solution new file mode 100644 index 0000000000..40f3fd5c8f --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_2-solution000006.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {2, 3, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_2-solution000007.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_2-solution000007.solution new file mode 100644 index 0000000000..159a613983 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_2-solution000007.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {2, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_2.eprime b/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_2.eprime new file mode 100644 index 0000000000..28e3beabc3 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_2.eprime @@ -0,0 +1,93 @@ +language ESSENCE' 1.0 + +find s_ExplicitVarSizeWithMarker_Marker: int(0..4) +find s_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +find s_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +letting let1 be -100 +find x: int(-100..100) +find conjure_aux1: int(-16..3) +branching on [s_ExplicitVarSizeWithDummy, s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithMarker_Values, x] +such that + and([and([q16 <= s_ExplicitVarSizeWithMarker_Marker, q17 <= s_ExplicitVarSizeWithMarker_Marker, + s_ExplicitVarSizeWithMarker_Values[q16] != s_ExplicitVarSizeWithMarker_Values[q17], + allDiff([s_ExplicitVarSizeWithMarker_Values[q16] + s_ExplicitVarSizeWithMarker_Values[q17], + s_ExplicitVarSizeWithMarker_Values[q16] * s_ExplicitVarSizeWithMarker_Values[q17], + s_ExplicitVarSizeWithMarker_Values[q16] / s_ExplicitVarSizeWithMarker_Values[q17]; + int(1..3)]), + (s_ExplicitVarSizeWithMarker_Values[q16] - s_ExplicitVarSizeWithMarker_Values[q17]) % 2 = 0; + int(1..5)]) + -> + min([s_ExplicitVarSizeWithMarker_Values[q16] + s_ExplicitVarSizeWithMarker_Values[q17], + s_ExplicitVarSizeWithMarker_Values[q16] - s_ExplicitVarSizeWithMarker_Values[q17], + s_ExplicitVarSizeWithMarker_Values[q16] * s_ExplicitVarSizeWithMarker_Values[q17], + s_ExplicitVarSizeWithMarker_Values[q16] / s_ExplicitVarSizeWithMarker_Values[q17]; + int(1..4)]) + <= conjure_aux1 + | q16 : int(1..4), q17 : int(1..4)]), + sum([toInt(and([q16 <= s_ExplicitVarSizeWithMarker_Marker, q17 <= s_ExplicitVarSizeWithMarker_Marker, + s_ExplicitVarSizeWithMarker_Values[q16] != s_ExplicitVarSizeWithMarker_Values[q17], + allDiff([s_ExplicitVarSizeWithMarker_Values[q16] + s_ExplicitVarSizeWithMarker_Values[q17], + s_ExplicitVarSizeWithMarker_Values[q16] * s_ExplicitVarSizeWithMarker_Values[q17], + s_ExplicitVarSizeWithMarker_Values[q16] / s_ExplicitVarSizeWithMarker_Values[q17]; + int(1..3)]), + (s_ExplicitVarSizeWithMarker_Values[q16] - s_ExplicitVarSizeWithMarker_Values[q17]) % 2 = 0; + int(1..5)])) + | q16 : int(1..4), q17 : int(1..4)]) + > 0 + -> + or([and([q16 <= s_ExplicitVarSizeWithMarker_Marker, q17 <= s_ExplicitVarSizeWithMarker_Marker, + s_ExplicitVarSizeWithMarker_Values[q16] != s_ExplicitVarSizeWithMarker_Values[q17], + allDiff([s_ExplicitVarSizeWithMarker_Values[q16] + s_ExplicitVarSizeWithMarker_Values[q17], + s_ExplicitVarSizeWithMarker_Values[q16] * s_ExplicitVarSizeWithMarker_Values[q17], + s_ExplicitVarSizeWithMarker_Values[q16] / s_ExplicitVarSizeWithMarker_Values[q17]; + int(1..3)]), + (s_ExplicitVarSizeWithMarker_Values[q16] - s_ExplicitVarSizeWithMarker_Values[q17]) % 2 = 0; + int(1..5)]) + /\ + min([s_ExplicitVarSizeWithMarker_Values[q16] + s_ExplicitVarSizeWithMarker_Values[q17], + s_ExplicitVarSizeWithMarker_Values[q16] - s_ExplicitVarSizeWithMarker_Values[q17], + s_ExplicitVarSizeWithMarker_Values[q16] * s_ExplicitVarSizeWithMarker_Values[q17], + s_ExplicitVarSizeWithMarker_Values[q16] / s_ExplicitVarSizeWithMarker_Values[q17]; + int(1..4)]) + = conjure_aux1 + | q16 : int(1..4), q17 : int(1..4)]), + sum([toInt(and([q16 <= s_ExplicitVarSizeWithMarker_Marker, q17 <= s_ExplicitVarSizeWithMarker_Marker, + s_ExplicitVarSizeWithMarker_Values[q16] != s_ExplicitVarSizeWithMarker_Values[q17], + allDiff([s_ExplicitVarSizeWithMarker_Values[q16] + s_ExplicitVarSizeWithMarker_Values[q17], + s_ExplicitVarSizeWithMarker_Values[q16] * s_ExplicitVarSizeWithMarker_Values[q17], + s_ExplicitVarSizeWithMarker_Values[q16] / s_ExplicitVarSizeWithMarker_Values[q17]; + int(1..3)]), + (s_ExplicitVarSizeWithMarker_Values[q16] - s_ExplicitVarSizeWithMarker_Values[q17]) % 2 = 0; + int(1..5)])) + | q16 : int(1..4), q17 : int(1..4)]) + = 0 + -> conjure_aux1 = -16, + x = conjure_aux1, + sum([toInt(and([q16 <= s_ExplicitVarSizeWithMarker_Marker, q17 <= s_ExplicitVarSizeWithMarker_Marker, + s_ExplicitVarSizeWithMarker_Values[q16] != s_ExplicitVarSizeWithMarker_Values[q17], + allDiff([s_ExplicitVarSizeWithMarker_Values[q16] + s_ExplicitVarSizeWithMarker_Values[q17], + s_ExplicitVarSizeWithMarker_Values[q16] * s_ExplicitVarSizeWithMarker_Values[q17], + s_ExplicitVarSizeWithMarker_Values[q16] / s_ExplicitVarSizeWithMarker_Values[q17]; + int(1..3)]), + (s_ExplicitVarSizeWithMarker_Values[q16] - s_ExplicitVarSizeWithMarker_Values[q17]) % 2 = 0; + int(1..5)])) + | q16 : int(1..4), q17 : int(1..4)]) + > 0, + and([q1 + 1 <= s_ExplicitVarSizeWithMarker_Marker -> + s_ExplicitVarSizeWithMarker_Values[q1] < s_ExplicitVarSizeWithMarker_Values[q1 + 1] + | q1 : int(1..3)]), + and([q2 > s_ExplicitVarSizeWithMarker_Marker -> s_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..4)]), + and([s_ExplicitVarSizeWithDummy[q4] < s_ExplicitVarSizeWithDummy[q4 + 1] \/ s_ExplicitVarSizeWithDummy[q4] = 5 + | q4 : int(1..3)]), + and([s_ExplicitVarSizeWithDummy[q5] = 5 -> s_ExplicitVarSizeWithDummy[q5 + 1] = 5 | q5 : int(1..3)]), + and([s_ExplicitVarSizeWithDummy[q9] != 5 -> + or([q11 <= s_ExplicitVarSizeWithMarker_Marker /\ + s_ExplicitVarSizeWithMarker_Values[q11] = s_ExplicitVarSizeWithDummy[q9] + | q11 : int(1..4)]) + | q9 : int(1..4)]), + and([q13 <= s_ExplicitVarSizeWithMarker_Marker -> + or([s_ExplicitVarSizeWithDummy[q15] != 5 /\ + s_ExplicitVarSizeWithDummy[q15] = s_ExplicitVarSizeWithMarker_Values[q13] + | q15 : int(1..4)]) + | q13 : int(1..4)]) + diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_3-solution000001.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_3-solution000001.solution new file mode 100644 index 0000000000..8b4ecbb66d --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_3-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 3} +letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_3-solution000002.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_3-solution000002.solution new file mode 100644 index 0000000000..159a613983 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_3-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {2, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_3-solution000003.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_3-solution000003.solution new file mode 100644 index 0000000000..5963aac565 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_3-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 2, 3} +letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_3-solution000004.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_3-solution000004.solution new file mode 100644 index 0000000000..6eeacc9727 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_3-solution000004.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 2, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_3-solution000005.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_3-solution000005.solution new file mode 100644 index 0000000000..560dd0f2f7 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_3-solution000005.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 3, 4} +letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_3-solution000006.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_3-solution000006.solution new file mode 100644 index 0000000000..40f3fd5c8f --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_3-solution000006.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {2, 3, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_3-solution000007.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_3-solution000007.solution new file mode 100644 index 0000000000..bd956f44e3 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_3-solution000007.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 2, 3, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_3.eprime b/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_3.eprime new file mode 100644 index 0000000000..2395a6a64c --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_3.eprime @@ -0,0 +1,79 @@ +language ESSENCE' 1.0 + +find s_ExplicitVarSizeWithMarker_Marker: int(0..4) +find s_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +letting let1 be -100 +find x: int(-100..100) +find conjure_aux1: int(-16..3) +branching on [s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithMarker_Values, x] +such that + and([and([q4 <= s_ExplicitVarSizeWithMarker_Marker, q5 <= s_ExplicitVarSizeWithMarker_Marker, + s_ExplicitVarSizeWithMarker_Values[q4] != s_ExplicitVarSizeWithMarker_Values[q5], + allDiff([s_ExplicitVarSizeWithMarker_Values[q4] + s_ExplicitVarSizeWithMarker_Values[q5], + s_ExplicitVarSizeWithMarker_Values[q4] * s_ExplicitVarSizeWithMarker_Values[q5], + s_ExplicitVarSizeWithMarker_Values[q4] / s_ExplicitVarSizeWithMarker_Values[q5]; + int(1..3)]), + (s_ExplicitVarSizeWithMarker_Values[q4] - s_ExplicitVarSizeWithMarker_Values[q5]) % 2 = 0; + int(1..5)]) + -> + min([s_ExplicitVarSizeWithMarker_Values[q4] + s_ExplicitVarSizeWithMarker_Values[q5], + s_ExplicitVarSizeWithMarker_Values[q4] - s_ExplicitVarSizeWithMarker_Values[q5], + s_ExplicitVarSizeWithMarker_Values[q4] * s_ExplicitVarSizeWithMarker_Values[q5], + s_ExplicitVarSizeWithMarker_Values[q4] / s_ExplicitVarSizeWithMarker_Values[q5]; + int(1..4)]) + <= conjure_aux1 + | q4 : int(1..4), q5 : int(1..4)]), + sum([toInt(and([q4 <= s_ExplicitVarSizeWithMarker_Marker, q5 <= s_ExplicitVarSizeWithMarker_Marker, + s_ExplicitVarSizeWithMarker_Values[q4] != s_ExplicitVarSizeWithMarker_Values[q5], + allDiff([s_ExplicitVarSizeWithMarker_Values[q4] + s_ExplicitVarSizeWithMarker_Values[q5], + s_ExplicitVarSizeWithMarker_Values[q4] * s_ExplicitVarSizeWithMarker_Values[q5], + s_ExplicitVarSizeWithMarker_Values[q4] / s_ExplicitVarSizeWithMarker_Values[q5]; + int(1..3)]), + (s_ExplicitVarSizeWithMarker_Values[q4] - s_ExplicitVarSizeWithMarker_Values[q5]) % 2 = 0; + int(1..5)])) + | q4 : int(1..4), q5 : int(1..4)]) + > 0 + -> + or([and([q4 <= s_ExplicitVarSizeWithMarker_Marker, q5 <= s_ExplicitVarSizeWithMarker_Marker, + s_ExplicitVarSizeWithMarker_Values[q4] != s_ExplicitVarSizeWithMarker_Values[q5], + allDiff([s_ExplicitVarSizeWithMarker_Values[q4] + s_ExplicitVarSizeWithMarker_Values[q5], + s_ExplicitVarSizeWithMarker_Values[q4] * s_ExplicitVarSizeWithMarker_Values[q5], + s_ExplicitVarSizeWithMarker_Values[q4] / s_ExplicitVarSizeWithMarker_Values[q5]; + int(1..3)]), + (s_ExplicitVarSizeWithMarker_Values[q4] - s_ExplicitVarSizeWithMarker_Values[q5]) % 2 = 0; + int(1..5)]) + /\ + min([s_ExplicitVarSizeWithMarker_Values[q4] + s_ExplicitVarSizeWithMarker_Values[q5], + s_ExplicitVarSizeWithMarker_Values[q4] - s_ExplicitVarSizeWithMarker_Values[q5], + s_ExplicitVarSizeWithMarker_Values[q4] * s_ExplicitVarSizeWithMarker_Values[q5], + s_ExplicitVarSizeWithMarker_Values[q4] / s_ExplicitVarSizeWithMarker_Values[q5]; + int(1..4)]) + = conjure_aux1 + | q4 : int(1..4), q5 : int(1..4)]), + sum([toInt(and([q4 <= s_ExplicitVarSizeWithMarker_Marker, q5 <= s_ExplicitVarSizeWithMarker_Marker, + s_ExplicitVarSizeWithMarker_Values[q4] != s_ExplicitVarSizeWithMarker_Values[q5], + allDiff([s_ExplicitVarSizeWithMarker_Values[q4] + s_ExplicitVarSizeWithMarker_Values[q5], + s_ExplicitVarSizeWithMarker_Values[q4] * s_ExplicitVarSizeWithMarker_Values[q5], + s_ExplicitVarSizeWithMarker_Values[q4] / s_ExplicitVarSizeWithMarker_Values[q5]; + int(1..3)]), + (s_ExplicitVarSizeWithMarker_Values[q4] - s_ExplicitVarSizeWithMarker_Values[q5]) % 2 = 0; + int(1..5)])) + | q4 : int(1..4), q5 : int(1..4)]) + = 0 + -> conjure_aux1 = -16, + x = conjure_aux1, + sum([toInt(and([q4 <= s_ExplicitVarSizeWithMarker_Marker, q5 <= s_ExplicitVarSizeWithMarker_Marker, + s_ExplicitVarSizeWithMarker_Values[q4] != s_ExplicitVarSizeWithMarker_Values[q5], + allDiff([s_ExplicitVarSizeWithMarker_Values[q4] + s_ExplicitVarSizeWithMarker_Values[q5], + s_ExplicitVarSizeWithMarker_Values[q4] * s_ExplicitVarSizeWithMarker_Values[q5], + s_ExplicitVarSizeWithMarker_Values[q4] / s_ExplicitVarSizeWithMarker_Values[q5]; + int(1..3)]), + (s_ExplicitVarSizeWithMarker_Values[q4] - s_ExplicitVarSizeWithMarker_Values[q5]) % 2 = 0; + int(1..5)])) + | q4 : int(1..4), q5 : int(1..4)]) + > 0, + and([q1 + 1 <= s_ExplicitVarSizeWithMarker_Marker -> + s_ExplicitVarSizeWithMarker_Values[q1] < s_ExplicitVarSizeWithMarker_Values[q1 + 1] + | q1 : int(1..3)]), + and([q2 > s_ExplicitVarSizeWithMarker_Marker -> s_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..4)]) + diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_4-solution000001.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_4-solution000001.solution new file mode 100644 index 0000000000..8b4ecbb66d --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_4-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 3} +letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_4-solution000002.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_4-solution000002.solution new file mode 100644 index 0000000000..159a613983 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_4-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {2, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_4-solution000003.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_4-solution000003.solution new file mode 100644 index 0000000000..5963aac565 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_4-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 2, 3} +letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_4-solution000004.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_4-solution000004.solution new file mode 100644 index 0000000000..6eeacc9727 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_4-solution000004.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 2, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_4-solution000005.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_4-solution000005.solution new file mode 100644 index 0000000000..560dd0f2f7 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_4-solution000005.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 3, 4} +letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_4-solution000006.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_4-solution000006.solution new file mode 100644 index 0000000000..40f3fd5c8f --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_4-solution000006.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {2, 3, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_4-solution000007.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_4-solution000007.solution new file mode 100644 index 0000000000..bd956f44e3 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_4-solution000007.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 2, 3, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_4.eprime b/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_4.eprime new file mode 100644 index 0000000000..04c74bb0a1 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_3_3_4.eprime @@ -0,0 +1,98 @@ +language ESSENCE' 1.0 + +find s_ExplicitVarSizeWithMarker_Marker: int(0..4) +find s_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +find s_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find s_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +letting let1 be -100 +find x: int(-100..100) +find conjure_aux1: int(-16..3) +branching on + [s_ExplicitVarSizeWithFlags_Flags, s_ExplicitVarSizeWithFlags_Values, s_ExplicitVarSizeWithMarker_Marker, + s_ExplicitVarSizeWithMarker_Values, x] +such that + and([and([q17 <= s_ExplicitVarSizeWithMarker_Marker, q18 <= s_ExplicitVarSizeWithMarker_Marker, + s_ExplicitVarSizeWithMarker_Values[q17] != s_ExplicitVarSizeWithMarker_Values[q18], + allDiff([s_ExplicitVarSizeWithMarker_Values[q17] + s_ExplicitVarSizeWithMarker_Values[q18], + s_ExplicitVarSizeWithMarker_Values[q17] * s_ExplicitVarSizeWithMarker_Values[q18], + s_ExplicitVarSizeWithMarker_Values[q17] / s_ExplicitVarSizeWithMarker_Values[q18]; + int(1..3)]), + (s_ExplicitVarSizeWithMarker_Values[q17] - s_ExplicitVarSizeWithMarker_Values[q18]) % 2 = 0; + int(1..5)]) + -> + min([s_ExplicitVarSizeWithMarker_Values[q17] + s_ExplicitVarSizeWithMarker_Values[q18], + s_ExplicitVarSizeWithMarker_Values[q17] - s_ExplicitVarSizeWithMarker_Values[q18], + s_ExplicitVarSizeWithMarker_Values[q17] * s_ExplicitVarSizeWithMarker_Values[q18], + s_ExplicitVarSizeWithMarker_Values[q17] / s_ExplicitVarSizeWithMarker_Values[q18]; + int(1..4)]) + <= conjure_aux1 + | q17 : int(1..4), q18 : int(1..4)]), + sum([toInt(and([q17 <= s_ExplicitVarSizeWithMarker_Marker, q18 <= s_ExplicitVarSizeWithMarker_Marker, + s_ExplicitVarSizeWithMarker_Values[q17] != s_ExplicitVarSizeWithMarker_Values[q18], + allDiff([s_ExplicitVarSizeWithMarker_Values[q17] + s_ExplicitVarSizeWithMarker_Values[q18], + s_ExplicitVarSizeWithMarker_Values[q17] * s_ExplicitVarSizeWithMarker_Values[q18], + s_ExplicitVarSizeWithMarker_Values[q17] / s_ExplicitVarSizeWithMarker_Values[q18]; + int(1..3)]), + (s_ExplicitVarSizeWithMarker_Values[q17] - s_ExplicitVarSizeWithMarker_Values[q18]) % 2 = 0; + int(1..5)])) + | q17 : int(1..4), q18 : int(1..4)]) + > 0 + -> + or([and([q17 <= s_ExplicitVarSizeWithMarker_Marker, q18 <= s_ExplicitVarSizeWithMarker_Marker, + s_ExplicitVarSizeWithMarker_Values[q17] != s_ExplicitVarSizeWithMarker_Values[q18], + allDiff([s_ExplicitVarSizeWithMarker_Values[q17] + s_ExplicitVarSizeWithMarker_Values[q18], + s_ExplicitVarSizeWithMarker_Values[q17] * s_ExplicitVarSizeWithMarker_Values[q18], + s_ExplicitVarSizeWithMarker_Values[q17] / s_ExplicitVarSizeWithMarker_Values[q18]; + int(1..3)]), + (s_ExplicitVarSizeWithMarker_Values[q17] - s_ExplicitVarSizeWithMarker_Values[q18]) % 2 = 0; + int(1..5)]) + /\ + min([s_ExplicitVarSizeWithMarker_Values[q17] + s_ExplicitVarSizeWithMarker_Values[q18], + s_ExplicitVarSizeWithMarker_Values[q17] - s_ExplicitVarSizeWithMarker_Values[q18], + s_ExplicitVarSizeWithMarker_Values[q17] * s_ExplicitVarSizeWithMarker_Values[q18], + s_ExplicitVarSizeWithMarker_Values[q17] / s_ExplicitVarSizeWithMarker_Values[q18]; + int(1..4)]) + = conjure_aux1 + | q17 : int(1..4), q18 : int(1..4)]), + sum([toInt(and([q17 <= s_ExplicitVarSizeWithMarker_Marker, q18 <= s_ExplicitVarSizeWithMarker_Marker, + s_ExplicitVarSizeWithMarker_Values[q17] != s_ExplicitVarSizeWithMarker_Values[q18], + allDiff([s_ExplicitVarSizeWithMarker_Values[q17] + s_ExplicitVarSizeWithMarker_Values[q18], + s_ExplicitVarSizeWithMarker_Values[q17] * s_ExplicitVarSizeWithMarker_Values[q18], + s_ExplicitVarSizeWithMarker_Values[q17] / s_ExplicitVarSizeWithMarker_Values[q18]; + int(1..3)]), + (s_ExplicitVarSizeWithMarker_Values[q17] - s_ExplicitVarSizeWithMarker_Values[q18]) % 2 = 0; + int(1..5)])) + | q17 : int(1..4), q18 : int(1..4)]) + = 0 + -> conjure_aux1 = -16, + x = conjure_aux1, + sum([toInt(and([q17 <= s_ExplicitVarSizeWithMarker_Marker, q18 <= s_ExplicitVarSizeWithMarker_Marker, + s_ExplicitVarSizeWithMarker_Values[q17] != s_ExplicitVarSizeWithMarker_Values[q18], + allDiff([s_ExplicitVarSizeWithMarker_Values[q17] + s_ExplicitVarSizeWithMarker_Values[q18], + s_ExplicitVarSizeWithMarker_Values[q17] * s_ExplicitVarSizeWithMarker_Values[q18], + s_ExplicitVarSizeWithMarker_Values[q17] / s_ExplicitVarSizeWithMarker_Values[q18]; + int(1..3)]), + (s_ExplicitVarSizeWithMarker_Values[q17] - s_ExplicitVarSizeWithMarker_Values[q18]) % 2 = 0; + int(1..5)])) + | q17 : int(1..4), q18 : int(1..4)]) + > 0, + and([q1 + 1 <= s_ExplicitVarSizeWithMarker_Marker -> + s_ExplicitVarSizeWithMarker_Values[q1] < s_ExplicitVarSizeWithMarker_Values[q1 + 1] + | q1 : int(1..3)]), + and([q2 > s_ExplicitVarSizeWithMarker_Marker -> s_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..4)]), + and([s_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> + s_ExplicitVarSizeWithFlags_Values[q4] < s_ExplicitVarSizeWithFlags_Values[q4 + 1] + | q4 : int(1..3)]), + and([s_ExplicitVarSizeWithFlags_Flags[q5] = false -> s_ExplicitVarSizeWithFlags_Values[q5] = 1 | q5 : int(1..4)]), + and([s_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> s_ExplicitVarSizeWithFlags_Flags[q6] | q6 : int(1..3)]), + and([s_ExplicitVarSizeWithFlags_Flags[q10] -> + or([q12 <= s_ExplicitVarSizeWithMarker_Marker /\ + s_ExplicitVarSizeWithMarker_Values[q12] = s_ExplicitVarSizeWithFlags_Values[q10] + | q12 : int(1..4)]) + | q10 : int(1..4)]), + and([q14 <= s_ExplicitVarSizeWithMarker_Marker -> + or([s_ExplicitVarSizeWithFlags_Flags[q16] /\ + s_ExplicitVarSizeWithFlags_Values[q16] = s_ExplicitVarSizeWithMarker_Values[q14] + | q16 : int(1..4)]) + | q14 : int(1..4)]) + diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_4_1-solution000001.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_4_1-solution000001.solution new file mode 100644 index 0000000000..159a613983 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_3_4_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {2, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_4_1-solution000002.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_4_1-solution000002.solution new file mode 100644 index 0000000000..40f3fd5c8f --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_3_4_1-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {2, 3, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_4_1-solution000003.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_4_1-solution000003.solution new file mode 100644 index 0000000000..8b4ecbb66d --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_3_4_1-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 3} +letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_4_1-solution000004.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_4_1-solution000004.solution new file mode 100644 index 0000000000..560dd0f2f7 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_3_4_1-solution000004.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 3, 4} +letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_4_1-solution000005.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_4_1-solution000005.solution new file mode 100644 index 0000000000..6eeacc9727 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_3_4_1-solution000005.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 2, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_4_1-solution000006.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_4_1-solution000006.solution new file mode 100644 index 0000000000..5963aac565 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_3_4_1-solution000006.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 2, 3} +letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_4_1-solution000007.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_4_1-solution000007.solution new file mode 100644 index 0000000000..bd956f44e3 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_3_4_1-solution000007.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 2, 3, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_4_1.eprime b/tests/exhaustive/basic/comprehension_letting/expected/model_3_4_1.eprime new file mode 100644 index 0000000000..04d3b5c94a --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_3_4_1.eprime @@ -0,0 +1,110 @@ +language ESSENCE' 1.0 + +find s_ExplicitVarSizeWithMarker_Marker: int(0..4) +find s_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +find s_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find s_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +find s_Occurrence: matrix indexed by [int(1..4)] of bool +letting let1 be -100 +find x: int(-100..100) +find conjure_aux1: int(-16..3) +branching on + [s_Occurrence, s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithMarker_Values, + s_ExplicitVarSizeWithFlags_Flags, s_ExplicitVarSizeWithFlags_Values, x] +such that + and([and([q28 <= s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithFlags_Flags[q29], + s_ExplicitVarSizeWithMarker_Values[q28] != s_ExplicitVarSizeWithFlags_Values[q29], + allDiff([s_ExplicitVarSizeWithMarker_Values[q28] + s_ExplicitVarSizeWithFlags_Values[q29], + s_ExplicitVarSizeWithMarker_Values[q28] * s_ExplicitVarSizeWithFlags_Values[q29], + s_ExplicitVarSizeWithMarker_Values[q28] / s_ExplicitVarSizeWithFlags_Values[q29]; + int(1..3)]), + (s_ExplicitVarSizeWithMarker_Values[q28] - s_ExplicitVarSizeWithFlags_Values[q29]) % 2 = 0; + int(1..5)]) + -> + min([s_ExplicitVarSizeWithMarker_Values[q28] + s_ExplicitVarSizeWithFlags_Values[q29], + s_ExplicitVarSizeWithMarker_Values[q28] - s_ExplicitVarSizeWithFlags_Values[q29], + s_ExplicitVarSizeWithMarker_Values[q28] * s_ExplicitVarSizeWithFlags_Values[q29], + s_ExplicitVarSizeWithMarker_Values[q28] / s_ExplicitVarSizeWithFlags_Values[q29]; + int(1..4)]) + <= conjure_aux1 + | q28 : int(1..4), q29 : int(1..4)]), + sum([toInt(and([q28 <= s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithFlags_Flags[q29], + s_ExplicitVarSizeWithMarker_Values[q28] != s_ExplicitVarSizeWithFlags_Values[q29], + allDiff([s_ExplicitVarSizeWithMarker_Values[q28] + s_ExplicitVarSizeWithFlags_Values[q29], + s_ExplicitVarSizeWithMarker_Values[q28] * s_ExplicitVarSizeWithFlags_Values[q29], + s_ExplicitVarSizeWithMarker_Values[q28] / s_ExplicitVarSizeWithFlags_Values[q29]; + int(1..3)]), + (s_ExplicitVarSizeWithMarker_Values[q28] - s_ExplicitVarSizeWithFlags_Values[q29]) % 2 = 0; + int(1..5)])) + | q28 : int(1..4), q29 : int(1..4)]) + > 0 + -> + or([and([q28 <= s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithFlags_Flags[q29], + s_ExplicitVarSizeWithMarker_Values[q28] != s_ExplicitVarSizeWithFlags_Values[q29], + allDiff([s_ExplicitVarSizeWithMarker_Values[q28] + s_ExplicitVarSizeWithFlags_Values[q29], + s_ExplicitVarSizeWithMarker_Values[q28] * s_ExplicitVarSizeWithFlags_Values[q29], + s_ExplicitVarSizeWithMarker_Values[q28] / s_ExplicitVarSizeWithFlags_Values[q29]; + int(1..3)]), + (s_ExplicitVarSizeWithMarker_Values[q28] - s_ExplicitVarSizeWithFlags_Values[q29]) % 2 = 0; + int(1..5)]) + /\ + min([s_ExplicitVarSizeWithMarker_Values[q28] + s_ExplicitVarSizeWithFlags_Values[q29], + s_ExplicitVarSizeWithMarker_Values[q28] - s_ExplicitVarSizeWithFlags_Values[q29], + s_ExplicitVarSizeWithMarker_Values[q28] * s_ExplicitVarSizeWithFlags_Values[q29], + s_ExplicitVarSizeWithMarker_Values[q28] / s_ExplicitVarSizeWithFlags_Values[q29]; + int(1..4)]) + = conjure_aux1 + | q28 : int(1..4), q29 : int(1..4)]), + sum([toInt(and([q28 <= s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithFlags_Flags[q29], + s_ExplicitVarSizeWithMarker_Values[q28] != s_ExplicitVarSizeWithFlags_Values[q29], + allDiff([s_ExplicitVarSizeWithMarker_Values[q28] + s_ExplicitVarSizeWithFlags_Values[q29], + s_ExplicitVarSizeWithMarker_Values[q28] * s_ExplicitVarSizeWithFlags_Values[q29], + s_ExplicitVarSizeWithMarker_Values[q28] / s_ExplicitVarSizeWithFlags_Values[q29]; + int(1..3)]), + (s_ExplicitVarSizeWithMarker_Values[q28] - s_ExplicitVarSizeWithFlags_Values[q29]) % 2 = 0; + int(1..5)])) + | q28 : int(1..4), q29 : int(1..4)]) + = 0 + -> conjure_aux1 = -16, + x = conjure_aux1, + sum([toInt(and([q28 <= s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithFlags_Flags[q29], + s_ExplicitVarSizeWithMarker_Values[q28] != s_ExplicitVarSizeWithFlags_Values[q29], + allDiff([s_ExplicitVarSizeWithMarker_Values[q28] + s_ExplicitVarSizeWithFlags_Values[q29], + s_ExplicitVarSizeWithMarker_Values[q28] * s_ExplicitVarSizeWithFlags_Values[q29], + s_ExplicitVarSizeWithMarker_Values[q28] / s_ExplicitVarSizeWithFlags_Values[q29]; + int(1..3)]), + (s_ExplicitVarSizeWithMarker_Values[q28] - s_ExplicitVarSizeWithFlags_Values[q29]) % 2 = 0; + int(1..5)])) + | q28 : int(1..4), q29 : int(1..4)]) + > 0, + and([q1 + 1 <= s_ExplicitVarSizeWithMarker_Marker -> + s_ExplicitVarSizeWithMarker_Values[q1] < s_ExplicitVarSizeWithMarker_Values[q1 + 1] + | q1 : int(1..3)]), + and([q2 > s_ExplicitVarSizeWithMarker_Marker -> s_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..4)]), + and([s_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> + s_ExplicitVarSizeWithFlags_Values[q4] < s_ExplicitVarSizeWithFlags_Values[q4 + 1] + | q4 : int(1..3)]), + and([s_ExplicitVarSizeWithFlags_Flags[q5] = false -> s_ExplicitVarSizeWithFlags_Values[q5] = 1 | q5 : int(1..4)]), + and([s_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> s_ExplicitVarSizeWithFlags_Flags[q6] | q6 : int(1..3)]), + and([s_ExplicitVarSizeWithFlags_Flags[q10] -> + or([q12 <= s_ExplicitVarSizeWithMarker_Marker /\ + s_ExplicitVarSizeWithMarker_Values[q12] = s_ExplicitVarSizeWithFlags_Values[q10] + | q12 : int(1..4)]) + | q10 : int(1..4)]), + and([q14 <= s_ExplicitVarSizeWithMarker_Marker -> + or([s_ExplicitVarSizeWithFlags_Flags[q16] /\ + s_ExplicitVarSizeWithFlags_Values[q16] = s_ExplicitVarSizeWithMarker_Values[q14] + | q16 : int(1..4)]) + | q14 : int(1..4)]), + and([s_Occurrence[q18] -> + or([q20 <= s_ExplicitVarSizeWithMarker_Marker /\ s_ExplicitVarSizeWithMarker_Values[q20] = q18 + | q20 : int(1..4)]) + | q18 : int(1..4)]), + and([q22 <= s_ExplicitVarSizeWithMarker_Marker -> s_Occurrence[s_ExplicitVarSizeWithMarker_Values[q22]] + | q22 : int(1..4)]), + and([s_Occurrence[q23] -> + or([s_ExplicitVarSizeWithFlags_Flags[q25] /\ s_ExplicitVarSizeWithFlags_Values[q25] = q23 | q25 : int(1..4)]) + | q23 : int(1..4)]), + and([s_ExplicitVarSizeWithFlags_Flags[q27] -> s_Occurrence[s_ExplicitVarSizeWithFlags_Values[q27]] + | q27 : int(1..4)]) + diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_4_2-solution000001.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_4_2-solution000001.solution new file mode 100644 index 0000000000..bd956f44e3 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_3_4_2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 2, 3, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_4_2-solution000002.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_4_2-solution000002.solution new file mode 100644 index 0000000000..5963aac565 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_3_4_2-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 2, 3} +letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_4_2-solution000003.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_4_2-solution000003.solution new file mode 100644 index 0000000000..6eeacc9727 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_3_4_2-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 2, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_4_2-solution000004.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_4_2-solution000004.solution new file mode 100644 index 0000000000..560dd0f2f7 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_3_4_2-solution000004.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 3, 4} +letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_4_2-solution000005.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_4_2-solution000005.solution new file mode 100644 index 0000000000..8b4ecbb66d --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_3_4_2-solution000005.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 3} +letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_4_2-solution000006.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_4_2-solution000006.solution new file mode 100644 index 0000000000..40f3fd5c8f --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_3_4_2-solution000006.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {2, 3, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_4_2-solution000007.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_4_2-solution000007.solution new file mode 100644 index 0000000000..159a613983 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_3_4_2-solution000007.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {2, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_4_2.eprime b/tests/exhaustive/basic/comprehension_letting/expected/model_3_4_2.eprime new file mode 100644 index 0000000000..cc4980db20 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_3_4_2.eprime @@ -0,0 +1,122 @@ +language ESSENCE' 1.0 + +find s_ExplicitVarSizeWithMarker_Marker: int(0..4) +find s_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +find s_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find s_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +find s_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +letting let1 be -100 +find x: int(-100..100) +find conjure_aux1: int(-16..3) +branching on + [s_ExplicitVarSizeWithDummy, s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithMarker_Values, + s_ExplicitVarSizeWithFlags_Flags, s_ExplicitVarSizeWithFlags_Values, x] +such that + and([and([q37 <= s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithFlags_Flags[q38], + s_ExplicitVarSizeWithMarker_Values[q37] != s_ExplicitVarSizeWithFlags_Values[q38], + allDiff([s_ExplicitVarSizeWithMarker_Values[q37] + s_ExplicitVarSizeWithFlags_Values[q38], + s_ExplicitVarSizeWithMarker_Values[q37] * s_ExplicitVarSizeWithFlags_Values[q38], + s_ExplicitVarSizeWithMarker_Values[q37] / s_ExplicitVarSizeWithFlags_Values[q38]; + int(1..3)]), + (s_ExplicitVarSizeWithMarker_Values[q37] - s_ExplicitVarSizeWithFlags_Values[q38]) % 2 = 0; + int(1..5)]) + -> + min([s_ExplicitVarSizeWithMarker_Values[q37] + s_ExplicitVarSizeWithFlags_Values[q38], + s_ExplicitVarSizeWithMarker_Values[q37] - s_ExplicitVarSizeWithFlags_Values[q38], + s_ExplicitVarSizeWithMarker_Values[q37] * s_ExplicitVarSizeWithFlags_Values[q38], + s_ExplicitVarSizeWithMarker_Values[q37] / s_ExplicitVarSizeWithFlags_Values[q38]; + int(1..4)]) + <= conjure_aux1 + | q37 : int(1..4), q38 : int(1..4)]), + sum([toInt(and([q37 <= s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithFlags_Flags[q38], + s_ExplicitVarSizeWithMarker_Values[q37] != s_ExplicitVarSizeWithFlags_Values[q38], + allDiff([s_ExplicitVarSizeWithMarker_Values[q37] + s_ExplicitVarSizeWithFlags_Values[q38], + s_ExplicitVarSizeWithMarker_Values[q37] * s_ExplicitVarSizeWithFlags_Values[q38], + s_ExplicitVarSizeWithMarker_Values[q37] / s_ExplicitVarSizeWithFlags_Values[q38]; + int(1..3)]), + (s_ExplicitVarSizeWithMarker_Values[q37] - s_ExplicitVarSizeWithFlags_Values[q38]) % 2 = 0; + int(1..5)])) + | q37 : int(1..4), q38 : int(1..4)]) + > 0 + -> + or([and([q37 <= s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithFlags_Flags[q38], + s_ExplicitVarSizeWithMarker_Values[q37] != s_ExplicitVarSizeWithFlags_Values[q38], + allDiff([s_ExplicitVarSizeWithMarker_Values[q37] + s_ExplicitVarSizeWithFlags_Values[q38], + s_ExplicitVarSizeWithMarker_Values[q37] * s_ExplicitVarSizeWithFlags_Values[q38], + s_ExplicitVarSizeWithMarker_Values[q37] / s_ExplicitVarSizeWithFlags_Values[q38]; + int(1..3)]), + (s_ExplicitVarSizeWithMarker_Values[q37] - s_ExplicitVarSizeWithFlags_Values[q38]) % 2 = 0; + int(1..5)]) + /\ + min([s_ExplicitVarSizeWithMarker_Values[q37] + s_ExplicitVarSizeWithFlags_Values[q38], + s_ExplicitVarSizeWithMarker_Values[q37] - s_ExplicitVarSizeWithFlags_Values[q38], + s_ExplicitVarSizeWithMarker_Values[q37] * s_ExplicitVarSizeWithFlags_Values[q38], + s_ExplicitVarSizeWithMarker_Values[q37] / s_ExplicitVarSizeWithFlags_Values[q38]; + int(1..4)]) + = conjure_aux1 + | q37 : int(1..4), q38 : int(1..4)]), + sum([toInt(and([q37 <= s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithFlags_Flags[q38], + s_ExplicitVarSizeWithMarker_Values[q37] != s_ExplicitVarSizeWithFlags_Values[q38], + allDiff([s_ExplicitVarSizeWithMarker_Values[q37] + s_ExplicitVarSizeWithFlags_Values[q38], + s_ExplicitVarSizeWithMarker_Values[q37] * s_ExplicitVarSizeWithFlags_Values[q38], + s_ExplicitVarSizeWithMarker_Values[q37] / s_ExplicitVarSizeWithFlags_Values[q38]; + int(1..3)]), + (s_ExplicitVarSizeWithMarker_Values[q37] - s_ExplicitVarSizeWithFlags_Values[q38]) % 2 = 0; + int(1..5)])) + | q37 : int(1..4), q38 : int(1..4)]) + = 0 + -> conjure_aux1 = -16, + x = conjure_aux1, + sum([toInt(and([q37 <= s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithFlags_Flags[q38], + s_ExplicitVarSizeWithMarker_Values[q37] != s_ExplicitVarSizeWithFlags_Values[q38], + allDiff([s_ExplicitVarSizeWithMarker_Values[q37] + s_ExplicitVarSizeWithFlags_Values[q38], + s_ExplicitVarSizeWithMarker_Values[q37] * s_ExplicitVarSizeWithFlags_Values[q38], + s_ExplicitVarSizeWithMarker_Values[q37] / s_ExplicitVarSizeWithFlags_Values[q38]; + int(1..3)]), + (s_ExplicitVarSizeWithMarker_Values[q37] - s_ExplicitVarSizeWithFlags_Values[q38]) % 2 = 0; + int(1..5)])) + | q37 : int(1..4), q38 : int(1..4)]) + > 0, + and([q1 + 1 <= s_ExplicitVarSizeWithMarker_Marker -> + s_ExplicitVarSizeWithMarker_Values[q1] < s_ExplicitVarSizeWithMarker_Values[q1 + 1] + | q1 : int(1..3)]), + and([q2 > s_ExplicitVarSizeWithMarker_Marker -> s_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..4)]), + and([s_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> + s_ExplicitVarSizeWithFlags_Values[q4] < s_ExplicitVarSizeWithFlags_Values[q4 + 1] + | q4 : int(1..3)]), + and([s_ExplicitVarSizeWithFlags_Flags[q5] = false -> s_ExplicitVarSizeWithFlags_Values[q5] = 1 | q5 : int(1..4)]), + and([s_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> s_ExplicitVarSizeWithFlags_Flags[q6] | q6 : int(1..3)]), + and([s_ExplicitVarSizeWithFlags_Flags[q10] -> + or([q12 <= s_ExplicitVarSizeWithMarker_Marker /\ + s_ExplicitVarSizeWithMarker_Values[q12] = s_ExplicitVarSizeWithFlags_Values[q10] + | q12 : int(1..4)]) + | q10 : int(1..4)]), + and([q14 <= s_ExplicitVarSizeWithMarker_Marker -> + or([s_ExplicitVarSizeWithFlags_Flags[q16] /\ + s_ExplicitVarSizeWithFlags_Values[q16] = s_ExplicitVarSizeWithMarker_Values[q14] + | q16 : int(1..4)]) + | q14 : int(1..4)]), + and([s_ExplicitVarSizeWithDummy[q17] < s_ExplicitVarSizeWithDummy[q17 + 1] \/ s_ExplicitVarSizeWithDummy[q17] = 5 + | q17 : int(1..3)]), + and([s_ExplicitVarSizeWithDummy[q18] = 5 -> s_ExplicitVarSizeWithDummy[q18 + 1] = 5 | q18 : int(1..3)]), + and([s_ExplicitVarSizeWithDummy[q22] != 5 -> + or([q24 <= s_ExplicitVarSizeWithMarker_Marker /\ + s_ExplicitVarSizeWithMarker_Values[q24] = s_ExplicitVarSizeWithDummy[q22] + | q24 : int(1..4)]) + | q22 : int(1..4)]), + and([q26 <= s_ExplicitVarSizeWithMarker_Marker -> + or([s_ExplicitVarSizeWithDummy[q28] != 5 /\ + s_ExplicitVarSizeWithDummy[q28] = s_ExplicitVarSizeWithMarker_Values[q26] + | q28 : int(1..4)]) + | q26 : int(1..4)]), + and([s_ExplicitVarSizeWithDummy[q30] != 5 -> + or([s_ExplicitVarSizeWithFlags_Flags[q32] /\ + s_ExplicitVarSizeWithFlags_Values[q32] = s_ExplicitVarSizeWithDummy[q30] + | q32 : int(1..4)]) + | q30 : int(1..4)]), + and([s_ExplicitVarSizeWithFlags_Flags[q34] -> + or([s_ExplicitVarSizeWithDummy[q36] != 5 /\ + s_ExplicitVarSizeWithDummy[q36] = s_ExplicitVarSizeWithFlags_Values[q34] + | q36 : int(1..4)]) + | q34 : int(1..4)]) + diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_4_3-solution000001.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_4_3-solution000001.solution new file mode 100644 index 0000000000..8b4ecbb66d --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_3_4_3-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 3} +letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_4_3-solution000002.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_4_3-solution000002.solution new file mode 100644 index 0000000000..159a613983 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_3_4_3-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {2, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_4_3-solution000003.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_4_3-solution000003.solution new file mode 100644 index 0000000000..5963aac565 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_3_4_3-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 2, 3} +letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_4_3-solution000004.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_4_3-solution000004.solution new file mode 100644 index 0000000000..6eeacc9727 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_3_4_3-solution000004.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 2, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_4_3-solution000005.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_4_3-solution000005.solution new file mode 100644 index 0000000000..560dd0f2f7 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_3_4_3-solution000005.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 3, 4} +letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_4_3-solution000006.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_4_3-solution000006.solution new file mode 100644 index 0000000000..40f3fd5c8f --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_3_4_3-solution000006.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {2, 3, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_4_3-solution000007.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_3_4_3-solution000007.solution new file mode 100644 index 0000000000..bd956f44e3 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_3_4_3-solution000007.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 2, 3, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_3_4_3.eprime b/tests/exhaustive/basic/comprehension_letting/expected/model_3_4_3.eprime new file mode 100644 index 0000000000..0a797c0a81 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_3_4_3.eprime @@ -0,0 +1,98 @@ +language ESSENCE' 1.0 + +find s_ExplicitVarSizeWithMarker_Marker: int(0..4) +find s_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +find s_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find s_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +letting let1 be -100 +find x: int(-100..100) +find conjure_aux1: int(-16..3) +branching on + [s_ExplicitVarSizeWithFlags_Flags, s_ExplicitVarSizeWithFlags_Values, s_ExplicitVarSizeWithMarker_Marker, + s_ExplicitVarSizeWithMarker_Values, x] +such that + and([and([q17 <= s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithFlags_Flags[q18], + s_ExplicitVarSizeWithMarker_Values[q17] != s_ExplicitVarSizeWithFlags_Values[q18], + allDiff([s_ExplicitVarSizeWithMarker_Values[q17] + s_ExplicitVarSizeWithFlags_Values[q18], + s_ExplicitVarSizeWithMarker_Values[q17] * s_ExplicitVarSizeWithFlags_Values[q18], + s_ExplicitVarSizeWithMarker_Values[q17] / s_ExplicitVarSizeWithFlags_Values[q18]; + int(1..3)]), + (s_ExplicitVarSizeWithMarker_Values[q17] - s_ExplicitVarSizeWithFlags_Values[q18]) % 2 = 0; + int(1..5)]) + -> + min([s_ExplicitVarSizeWithMarker_Values[q17] + s_ExplicitVarSizeWithFlags_Values[q18], + s_ExplicitVarSizeWithMarker_Values[q17] - s_ExplicitVarSizeWithFlags_Values[q18], + s_ExplicitVarSizeWithMarker_Values[q17] * s_ExplicitVarSizeWithFlags_Values[q18], + s_ExplicitVarSizeWithMarker_Values[q17] / s_ExplicitVarSizeWithFlags_Values[q18]; + int(1..4)]) + <= conjure_aux1 + | q17 : int(1..4), q18 : int(1..4)]), + sum([toInt(and([q17 <= s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithFlags_Flags[q18], + s_ExplicitVarSizeWithMarker_Values[q17] != s_ExplicitVarSizeWithFlags_Values[q18], + allDiff([s_ExplicitVarSizeWithMarker_Values[q17] + s_ExplicitVarSizeWithFlags_Values[q18], + s_ExplicitVarSizeWithMarker_Values[q17] * s_ExplicitVarSizeWithFlags_Values[q18], + s_ExplicitVarSizeWithMarker_Values[q17] / s_ExplicitVarSizeWithFlags_Values[q18]; + int(1..3)]), + (s_ExplicitVarSizeWithMarker_Values[q17] - s_ExplicitVarSizeWithFlags_Values[q18]) % 2 = 0; + int(1..5)])) + | q17 : int(1..4), q18 : int(1..4)]) + > 0 + -> + or([and([q17 <= s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithFlags_Flags[q18], + s_ExplicitVarSizeWithMarker_Values[q17] != s_ExplicitVarSizeWithFlags_Values[q18], + allDiff([s_ExplicitVarSizeWithMarker_Values[q17] + s_ExplicitVarSizeWithFlags_Values[q18], + s_ExplicitVarSizeWithMarker_Values[q17] * s_ExplicitVarSizeWithFlags_Values[q18], + s_ExplicitVarSizeWithMarker_Values[q17] / s_ExplicitVarSizeWithFlags_Values[q18]; + int(1..3)]), + (s_ExplicitVarSizeWithMarker_Values[q17] - s_ExplicitVarSizeWithFlags_Values[q18]) % 2 = 0; + int(1..5)]) + /\ + min([s_ExplicitVarSizeWithMarker_Values[q17] + s_ExplicitVarSizeWithFlags_Values[q18], + s_ExplicitVarSizeWithMarker_Values[q17] - s_ExplicitVarSizeWithFlags_Values[q18], + s_ExplicitVarSizeWithMarker_Values[q17] * s_ExplicitVarSizeWithFlags_Values[q18], + s_ExplicitVarSizeWithMarker_Values[q17] / s_ExplicitVarSizeWithFlags_Values[q18]; + int(1..4)]) + = conjure_aux1 + | q17 : int(1..4), q18 : int(1..4)]), + sum([toInt(and([q17 <= s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithFlags_Flags[q18], + s_ExplicitVarSizeWithMarker_Values[q17] != s_ExplicitVarSizeWithFlags_Values[q18], + allDiff([s_ExplicitVarSizeWithMarker_Values[q17] + s_ExplicitVarSizeWithFlags_Values[q18], + s_ExplicitVarSizeWithMarker_Values[q17] * s_ExplicitVarSizeWithFlags_Values[q18], + s_ExplicitVarSizeWithMarker_Values[q17] / s_ExplicitVarSizeWithFlags_Values[q18]; + int(1..3)]), + (s_ExplicitVarSizeWithMarker_Values[q17] - s_ExplicitVarSizeWithFlags_Values[q18]) % 2 = 0; + int(1..5)])) + | q17 : int(1..4), q18 : int(1..4)]) + = 0 + -> conjure_aux1 = -16, + x = conjure_aux1, + sum([toInt(and([q17 <= s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithFlags_Flags[q18], + s_ExplicitVarSizeWithMarker_Values[q17] != s_ExplicitVarSizeWithFlags_Values[q18], + allDiff([s_ExplicitVarSizeWithMarker_Values[q17] + s_ExplicitVarSizeWithFlags_Values[q18], + s_ExplicitVarSizeWithMarker_Values[q17] * s_ExplicitVarSizeWithFlags_Values[q18], + s_ExplicitVarSizeWithMarker_Values[q17] / s_ExplicitVarSizeWithFlags_Values[q18]; + int(1..3)]), + (s_ExplicitVarSizeWithMarker_Values[q17] - s_ExplicitVarSizeWithFlags_Values[q18]) % 2 = 0; + int(1..5)])) + | q17 : int(1..4), q18 : int(1..4)]) + > 0, + and([q1 + 1 <= s_ExplicitVarSizeWithMarker_Marker -> + s_ExplicitVarSizeWithMarker_Values[q1] < s_ExplicitVarSizeWithMarker_Values[q1 + 1] + | q1 : int(1..3)]), + and([q2 > s_ExplicitVarSizeWithMarker_Marker -> s_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..4)]), + and([s_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> + s_ExplicitVarSizeWithFlags_Values[q4] < s_ExplicitVarSizeWithFlags_Values[q4 + 1] + | q4 : int(1..3)]), + and([s_ExplicitVarSizeWithFlags_Flags[q5] = false -> s_ExplicitVarSizeWithFlags_Values[q5] = 1 | q5 : int(1..4)]), + and([s_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> s_ExplicitVarSizeWithFlags_Flags[q6] | q6 : int(1..3)]), + and([s_ExplicitVarSizeWithFlags_Flags[q10] -> + or([q12 <= s_ExplicitVarSizeWithMarker_Marker /\ + s_ExplicitVarSizeWithMarker_Values[q12] = s_ExplicitVarSizeWithFlags_Values[q10] + | q12 : int(1..4)]) + | q10 : int(1..4)]), + and([q14 <= s_ExplicitVarSizeWithMarker_Marker -> + or([s_ExplicitVarSizeWithFlags_Flags[q16] /\ + s_ExplicitVarSizeWithFlags_Values[q16] = s_ExplicitVarSizeWithMarker_Values[q14] + | q16 : int(1..4)]) + | q14 : int(1..4)]) + diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_1_1-solution000001.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_1_1-solution000001.solution new file mode 100644 index 0000000000..159a613983 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_4_1_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {2, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_1_1-solution000002.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_1_1-solution000002.solution new file mode 100644 index 0000000000..40f3fd5c8f --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_4_1_1-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {2, 3, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_1_1-solution000003.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_1_1-solution000003.solution new file mode 100644 index 0000000000..8b4ecbb66d --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_4_1_1-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 3} +letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_1_1-solution000004.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_1_1-solution000004.solution new file mode 100644 index 0000000000..560dd0f2f7 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_4_1_1-solution000004.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 3, 4} +letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_1_1-solution000005.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_1_1-solution000005.solution new file mode 100644 index 0000000000..6eeacc9727 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_4_1_1-solution000005.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 2, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_1_1-solution000006.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_1_1-solution000006.solution new file mode 100644 index 0000000000..5963aac565 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_4_1_1-solution000006.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 2, 3} +letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_1_1-solution000007.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_1_1-solution000007.solution new file mode 100644 index 0000000000..bd956f44e3 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_4_1_1-solution000007.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 2, 3, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_1_1.eprime b/tests/exhaustive/basic/comprehension_letting/expected/model_4_1_1.eprime new file mode 100644 index 0000000000..adcf0207b3 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_4_1_1.eprime @@ -0,0 +1,72 @@ +language ESSENCE' 1.0 + +find s_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find s_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +find s_Occurrence: matrix indexed by [int(1..4)] of bool +letting let1 be -100 +find x: int(-100..100) +find conjure_aux1: int(-16..3) +branching on [s_Occurrence, s_ExplicitVarSizeWithFlags_Flags, s_ExplicitVarSizeWithFlags_Values, x] +such that + and([and([s_ExplicitVarSizeWithFlags_Flags[q12], s_Occurrence[j], s_ExplicitVarSizeWithFlags_Values[q12] != j, + allDiff([s_ExplicitVarSizeWithFlags_Values[q12] + j, s_ExplicitVarSizeWithFlags_Values[q12] * j, + s_ExplicitVarSizeWithFlags_Values[q12] / j; + int(1..3)]), + (s_ExplicitVarSizeWithFlags_Values[q12] - j) % 2 = 0; + int(1..5)]) + -> + min([s_ExplicitVarSizeWithFlags_Values[q12] + j, s_ExplicitVarSizeWithFlags_Values[q12] - j, + s_ExplicitVarSizeWithFlags_Values[q12] * j, s_ExplicitVarSizeWithFlags_Values[q12] / j; + int(1..4)]) + <= conjure_aux1 + | q12 : int(1..4), j : int(1..4)]), + sum([toInt(and([s_ExplicitVarSizeWithFlags_Flags[q12], s_Occurrence[j], s_ExplicitVarSizeWithFlags_Values[q12] != j, + allDiff([s_ExplicitVarSizeWithFlags_Values[q12] + j, s_ExplicitVarSizeWithFlags_Values[q12] * j, + s_ExplicitVarSizeWithFlags_Values[q12] / j; + int(1..3)]), + (s_ExplicitVarSizeWithFlags_Values[q12] - j) % 2 = 0; + int(1..5)])) + | q12 : int(1..4), j : int(1..4)]) + > 0 + -> + or([and([s_ExplicitVarSizeWithFlags_Flags[q12], s_Occurrence[j], s_ExplicitVarSizeWithFlags_Values[q12] != j, + allDiff([s_ExplicitVarSizeWithFlags_Values[q12] + j, s_ExplicitVarSizeWithFlags_Values[q12] * j, + s_ExplicitVarSizeWithFlags_Values[q12] / j; + int(1..3)]), + (s_ExplicitVarSizeWithFlags_Values[q12] - j) % 2 = 0; + int(1..5)]) + /\ + min([s_ExplicitVarSizeWithFlags_Values[q12] + j, s_ExplicitVarSizeWithFlags_Values[q12] - j, + s_ExplicitVarSizeWithFlags_Values[q12] * j, s_ExplicitVarSizeWithFlags_Values[q12] / j; + int(1..4)]) + = conjure_aux1 + | q12 : int(1..4), j : int(1..4)]), + sum([toInt(and([s_ExplicitVarSizeWithFlags_Flags[q12], s_Occurrence[j], s_ExplicitVarSizeWithFlags_Values[q12] != j, + allDiff([s_ExplicitVarSizeWithFlags_Values[q12] + j, s_ExplicitVarSizeWithFlags_Values[q12] * j, + s_ExplicitVarSizeWithFlags_Values[q12] / j; + int(1..3)]), + (s_ExplicitVarSizeWithFlags_Values[q12] - j) % 2 = 0; + int(1..5)])) + | q12 : int(1..4), j : int(1..4)]) + = 0 + -> conjure_aux1 = -16, + x = conjure_aux1, + sum([toInt(and([s_ExplicitVarSizeWithFlags_Flags[q12], s_Occurrence[j], s_ExplicitVarSizeWithFlags_Values[q12] != j, + allDiff([s_ExplicitVarSizeWithFlags_Values[q12] + j, s_ExplicitVarSizeWithFlags_Values[q12] * j, + s_ExplicitVarSizeWithFlags_Values[q12] / j; + int(1..3)]), + (s_ExplicitVarSizeWithFlags_Values[q12] - j) % 2 = 0; + int(1..5)])) + | q12 : int(1..4), j : int(1..4)]) + > 0, + and([s_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> + s_ExplicitVarSizeWithFlags_Values[q1] < s_ExplicitVarSizeWithFlags_Values[q1 + 1] + | q1 : int(1..3)]), + and([s_ExplicitVarSizeWithFlags_Flags[q2] = false -> s_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..4)]), + and([s_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> s_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), + and([s_Occurrence[q7] -> + or([s_ExplicitVarSizeWithFlags_Flags[q9] /\ s_ExplicitVarSizeWithFlags_Values[q9] = q7 | q9 : int(1..4)]) + | q7 : int(1..4)]), + and([s_ExplicitVarSizeWithFlags_Flags[q11] -> s_Occurrence[s_ExplicitVarSizeWithFlags_Values[q11]] + | q11 : int(1..4)]) + diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_1_2-solution000001.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_1_2-solution000001.solution new file mode 100644 index 0000000000..bd956f44e3 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_4_1_2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 2, 3, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_1_2-solution000002.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_1_2-solution000002.solution new file mode 100644 index 0000000000..5963aac565 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_4_1_2-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 2, 3} +letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_1_2-solution000003.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_1_2-solution000003.solution new file mode 100644 index 0000000000..6eeacc9727 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_4_1_2-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 2, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_1_2-solution000004.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_1_2-solution000004.solution new file mode 100644 index 0000000000..560dd0f2f7 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_4_1_2-solution000004.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 3, 4} +letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_1_2-solution000005.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_1_2-solution000005.solution new file mode 100644 index 0000000000..8b4ecbb66d --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_4_1_2-solution000005.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 3} +letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_1_2-solution000006.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_1_2-solution000006.solution new file mode 100644 index 0000000000..40f3fd5c8f --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_4_1_2-solution000006.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {2, 3, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_1_2-solution000007.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_1_2-solution000007.solution new file mode 100644 index 0000000000..159a613983 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_4_1_2-solution000007.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {2, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_1_2.eprime b/tests/exhaustive/basic/comprehension_letting/expected/model_4_1_2.eprime new file mode 100644 index 0000000000..9f5ba038eb --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_4_1_2.eprime @@ -0,0 +1,91 @@ +language ESSENCE' 1.0 + +find s_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find s_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +find s_Occurrence: matrix indexed by [int(1..4)] of bool +find s_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +letting let1 be -100 +find x: int(-100..100) +find conjure_aux1: int(-16..3) +branching on + [s_ExplicitVarSizeWithDummy, s_ExplicitVarSizeWithFlags_Flags, s_ExplicitVarSizeWithFlags_Values, s_Occurrence, x] +such that + and([and([s_ExplicitVarSizeWithFlags_Flags[q29], s_Occurrence[j], s_ExplicitVarSizeWithFlags_Values[q29] != j, + allDiff([s_ExplicitVarSizeWithFlags_Values[q29] + j, s_ExplicitVarSizeWithFlags_Values[q29] * j, + s_ExplicitVarSizeWithFlags_Values[q29] / j; + int(1..3)]), + (s_ExplicitVarSizeWithFlags_Values[q29] - j) % 2 = 0; + int(1..5)]) + -> + min([s_ExplicitVarSizeWithFlags_Values[q29] + j, s_ExplicitVarSizeWithFlags_Values[q29] - j, + s_ExplicitVarSizeWithFlags_Values[q29] * j, s_ExplicitVarSizeWithFlags_Values[q29] / j; + int(1..4)]) + <= conjure_aux1 + | q29 : int(1..4), j : int(1..4)]), + sum([toInt(and([s_ExplicitVarSizeWithFlags_Flags[q29], s_Occurrence[j], s_ExplicitVarSizeWithFlags_Values[q29] != j, + allDiff([s_ExplicitVarSizeWithFlags_Values[q29] + j, s_ExplicitVarSizeWithFlags_Values[q29] * j, + s_ExplicitVarSizeWithFlags_Values[q29] / j; + int(1..3)]), + (s_ExplicitVarSizeWithFlags_Values[q29] - j) % 2 = 0; + int(1..5)])) + | q29 : int(1..4), j : int(1..4)]) + > 0 + -> + or([and([s_ExplicitVarSizeWithFlags_Flags[q29], s_Occurrence[j], s_ExplicitVarSizeWithFlags_Values[q29] != j, + allDiff([s_ExplicitVarSizeWithFlags_Values[q29] + j, s_ExplicitVarSizeWithFlags_Values[q29] * j, + s_ExplicitVarSizeWithFlags_Values[q29] / j; + int(1..3)]), + (s_ExplicitVarSizeWithFlags_Values[q29] - j) % 2 = 0; + int(1..5)]) + /\ + min([s_ExplicitVarSizeWithFlags_Values[q29] + j, s_ExplicitVarSizeWithFlags_Values[q29] - j, + s_ExplicitVarSizeWithFlags_Values[q29] * j, s_ExplicitVarSizeWithFlags_Values[q29] / j; + int(1..4)]) + = conjure_aux1 + | q29 : int(1..4), j : int(1..4)]), + sum([toInt(and([s_ExplicitVarSizeWithFlags_Flags[q29], s_Occurrence[j], s_ExplicitVarSizeWithFlags_Values[q29] != j, + allDiff([s_ExplicitVarSizeWithFlags_Values[q29] + j, s_ExplicitVarSizeWithFlags_Values[q29] * j, + s_ExplicitVarSizeWithFlags_Values[q29] / j; + int(1..3)]), + (s_ExplicitVarSizeWithFlags_Values[q29] - j) % 2 = 0; + int(1..5)])) + | q29 : int(1..4), j : int(1..4)]) + = 0 + -> conjure_aux1 = -16, + x = conjure_aux1, + sum([toInt(and([s_ExplicitVarSizeWithFlags_Flags[q29], s_Occurrence[j], s_ExplicitVarSizeWithFlags_Values[q29] != j, + allDiff([s_ExplicitVarSizeWithFlags_Values[q29] + j, s_ExplicitVarSizeWithFlags_Values[q29] * j, + s_ExplicitVarSizeWithFlags_Values[q29] / j; + int(1..3)]), + (s_ExplicitVarSizeWithFlags_Values[q29] - j) % 2 = 0; + int(1..5)])) + | q29 : int(1..4), j : int(1..4)]) + > 0, + and([s_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> + s_ExplicitVarSizeWithFlags_Values[q1] < s_ExplicitVarSizeWithFlags_Values[q1 + 1] + | q1 : int(1..3)]), + and([s_ExplicitVarSizeWithFlags_Flags[q2] = false -> s_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..4)]), + and([s_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> s_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), + and([s_Occurrence[q24] -> + or([s_ExplicitVarSizeWithFlags_Flags[q26] /\ s_ExplicitVarSizeWithFlags_Values[q26] = q24 | q26 : int(1..4)]) + | q24 : int(1..4)]), + and([s_ExplicitVarSizeWithFlags_Flags[q28] -> s_Occurrence[s_ExplicitVarSizeWithFlags_Values[q28]] + | q28 : int(1..4)]), + and([s_ExplicitVarSizeWithDummy[q7] < s_ExplicitVarSizeWithDummy[q7 + 1] \/ s_ExplicitVarSizeWithDummy[q7] = 5 + | q7 : int(1..3)]), + and([s_ExplicitVarSizeWithDummy[q8] = 5 -> s_ExplicitVarSizeWithDummy[q8 + 1] = 5 | q8 : int(1..3)]), + and([s_ExplicitVarSizeWithDummy[q12] != 5 -> + or([s_ExplicitVarSizeWithFlags_Flags[q14] /\ + s_ExplicitVarSizeWithFlags_Values[q14] = s_ExplicitVarSizeWithDummy[q12] + | q14 : int(1..4)]) + | q12 : int(1..4)]), + and([s_ExplicitVarSizeWithFlags_Flags[q16] -> + or([s_ExplicitVarSizeWithDummy[q18] != 5 /\ + s_ExplicitVarSizeWithDummy[q18] = s_ExplicitVarSizeWithFlags_Values[q16] + | q18 : int(1..4)]) + | q16 : int(1..4)]), + and([s_ExplicitVarSizeWithDummy[q20] != 5 -> s_Occurrence[s_ExplicitVarSizeWithDummy[q20]] | q20 : int(1..4)]), + and([s_Occurrence[q21] -> + or([s_ExplicitVarSizeWithDummy[q23] != 5 /\ s_ExplicitVarSizeWithDummy[q23] = q21 | q23 : int(1..4)]) + | q21 : int(1..4)]) + diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_1_3-solution000001.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_1_3-solution000001.solution new file mode 100644 index 0000000000..8b4ecbb66d --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_4_1_3-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 3} +letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_1_3-solution000002.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_1_3-solution000002.solution new file mode 100644 index 0000000000..159a613983 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_4_1_3-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {2, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_1_3-solution000003.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_1_3-solution000003.solution new file mode 100644 index 0000000000..5963aac565 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_4_1_3-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 2, 3} +letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_1_3-solution000004.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_1_3-solution000004.solution new file mode 100644 index 0000000000..6eeacc9727 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_4_1_3-solution000004.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 2, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_1_3-solution000005.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_1_3-solution000005.solution new file mode 100644 index 0000000000..560dd0f2f7 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_4_1_3-solution000005.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 3, 4} +letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_1_3-solution000006.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_1_3-solution000006.solution new file mode 100644 index 0000000000..40f3fd5c8f --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_4_1_3-solution000006.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {2, 3, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_1_3-solution000007.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_1_3-solution000007.solution new file mode 100644 index 0000000000..bd956f44e3 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_4_1_3-solution000007.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 2, 3, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_1_3.eprime b/tests/exhaustive/basic/comprehension_letting/expected/model_4_1_3.eprime new file mode 100644 index 0000000000..d6762cf6f5 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_4_1_3.eprime @@ -0,0 +1,96 @@ +language ESSENCE' 1.0 + +find s_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find s_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +find s_Occurrence: matrix indexed by [int(1..4)] of bool +find s_ExplicitVarSizeWithMarker_Marker: int(0..4) +find s_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +letting let1 be -100 +find x: int(-100..100) +find conjure_aux1: int(-16..3) +branching on + [s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithMarker_Values, s_ExplicitVarSizeWithFlags_Flags, + s_ExplicitVarSizeWithFlags_Values, s_Occurrence, x] +such that + and([and([s_ExplicitVarSizeWithFlags_Flags[q28], s_Occurrence[j], s_ExplicitVarSizeWithFlags_Values[q28] != j, + allDiff([s_ExplicitVarSizeWithFlags_Values[q28] + j, s_ExplicitVarSizeWithFlags_Values[q28] * j, + s_ExplicitVarSizeWithFlags_Values[q28] / j; + int(1..3)]), + (s_ExplicitVarSizeWithFlags_Values[q28] - j) % 2 = 0; + int(1..5)]) + -> + min([s_ExplicitVarSizeWithFlags_Values[q28] + j, s_ExplicitVarSizeWithFlags_Values[q28] - j, + s_ExplicitVarSizeWithFlags_Values[q28] * j, s_ExplicitVarSizeWithFlags_Values[q28] / j; + int(1..4)]) + <= conjure_aux1 + | q28 : int(1..4), j : int(1..4)]), + sum([toInt(and([s_ExplicitVarSizeWithFlags_Flags[q28], s_Occurrence[j], s_ExplicitVarSizeWithFlags_Values[q28] != j, + allDiff([s_ExplicitVarSizeWithFlags_Values[q28] + j, s_ExplicitVarSizeWithFlags_Values[q28] * j, + s_ExplicitVarSizeWithFlags_Values[q28] / j; + int(1..3)]), + (s_ExplicitVarSizeWithFlags_Values[q28] - j) % 2 = 0; + int(1..5)])) + | q28 : int(1..4), j : int(1..4)]) + > 0 + -> + or([and([s_ExplicitVarSizeWithFlags_Flags[q28], s_Occurrence[j], s_ExplicitVarSizeWithFlags_Values[q28] != j, + allDiff([s_ExplicitVarSizeWithFlags_Values[q28] + j, s_ExplicitVarSizeWithFlags_Values[q28] * j, + s_ExplicitVarSizeWithFlags_Values[q28] / j; + int(1..3)]), + (s_ExplicitVarSizeWithFlags_Values[q28] - j) % 2 = 0; + int(1..5)]) + /\ + min([s_ExplicitVarSizeWithFlags_Values[q28] + j, s_ExplicitVarSizeWithFlags_Values[q28] - j, + s_ExplicitVarSizeWithFlags_Values[q28] * j, s_ExplicitVarSizeWithFlags_Values[q28] / j; + int(1..4)]) + = conjure_aux1 + | q28 : int(1..4), j : int(1..4)]), + sum([toInt(and([s_ExplicitVarSizeWithFlags_Flags[q28], s_Occurrence[j], s_ExplicitVarSizeWithFlags_Values[q28] != j, + allDiff([s_ExplicitVarSizeWithFlags_Values[q28] + j, s_ExplicitVarSizeWithFlags_Values[q28] * j, + s_ExplicitVarSizeWithFlags_Values[q28] / j; + int(1..3)]), + (s_ExplicitVarSizeWithFlags_Values[q28] - j) % 2 = 0; + int(1..5)])) + | q28 : int(1..4), j : int(1..4)]) + = 0 + -> conjure_aux1 = -16, + x = conjure_aux1, + sum([toInt(and([s_ExplicitVarSizeWithFlags_Flags[q28], s_Occurrence[j], s_ExplicitVarSizeWithFlags_Values[q28] != j, + allDiff([s_ExplicitVarSizeWithFlags_Values[q28] + j, s_ExplicitVarSizeWithFlags_Values[q28] * j, + s_ExplicitVarSizeWithFlags_Values[q28] / j; + int(1..3)]), + (s_ExplicitVarSizeWithFlags_Values[q28] - j) % 2 = 0; + int(1..5)])) + | q28 : int(1..4), j : int(1..4)]) + > 0, + and([s_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> + s_ExplicitVarSizeWithFlags_Values[q1] < s_ExplicitVarSizeWithFlags_Values[q1 + 1] + | q1 : int(1..3)]), + and([s_ExplicitVarSizeWithFlags_Flags[q2] = false -> s_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..4)]), + and([s_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> s_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), + and([s_Occurrence[q23] -> + or([s_ExplicitVarSizeWithFlags_Flags[q25] /\ s_ExplicitVarSizeWithFlags_Values[q25] = q23 | q25 : int(1..4)]) + | q23 : int(1..4)]), + and([s_ExplicitVarSizeWithFlags_Flags[q27] -> s_Occurrence[s_ExplicitVarSizeWithFlags_Values[q27]] + | q27 : int(1..4)]), + and([q7 + 1 <= s_ExplicitVarSizeWithMarker_Marker -> + s_ExplicitVarSizeWithMarker_Values[q7] < s_ExplicitVarSizeWithMarker_Values[q7 + 1] + | q7 : int(1..3)]), + and([q8 > s_ExplicitVarSizeWithMarker_Marker -> s_ExplicitVarSizeWithMarker_Values[q8] = 1 | q8 : int(1..4)]), + and([q11 <= s_ExplicitVarSizeWithMarker_Marker -> + or([s_ExplicitVarSizeWithFlags_Flags[q13] /\ + s_ExplicitVarSizeWithFlags_Values[q13] = s_ExplicitVarSizeWithMarker_Values[q11] + | q13 : int(1..4)]) + | q11 : int(1..4)]), + and([s_ExplicitVarSizeWithFlags_Flags[q15] -> + or([q17 <= s_ExplicitVarSizeWithMarker_Marker /\ + s_ExplicitVarSizeWithMarker_Values[q17] = s_ExplicitVarSizeWithFlags_Values[q15] + | q17 : int(1..4)]) + | q15 : int(1..4)]), + and([q19 <= s_ExplicitVarSizeWithMarker_Marker -> s_Occurrence[s_ExplicitVarSizeWithMarker_Values[q19]] + | q19 : int(1..4)]), + and([s_Occurrence[q20] -> + or([q22 <= s_ExplicitVarSizeWithMarker_Marker /\ s_ExplicitVarSizeWithMarker_Values[q22] = q20 + | q22 : int(1..4)]) + | q20 : int(1..4)]) + diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_2_1-solution000001.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_2_1-solution000001.solution new file mode 100644 index 0000000000..159a613983 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_4_2_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {2, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_2_1-solution000002.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_2_1-solution000002.solution new file mode 100644 index 0000000000..40f3fd5c8f --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_4_2_1-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {2, 3, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_2_1-solution000003.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_2_1-solution000003.solution new file mode 100644 index 0000000000..8b4ecbb66d --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_4_2_1-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 3} +letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_2_1-solution000004.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_2_1-solution000004.solution new file mode 100644 index 0000000000..560dd0f2f7 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_4_2_1-solution000004.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 3, 4} +letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_2_1-solution000005.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_2_1-solution000005.solution new file mode 100644 index 0000000000..6eeacc9727 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_4_2_1-solution000005.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 2, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_2_1-solution000006.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_2_1-solution000006.solution new file mode 100644 index 0000000000..5963aac565 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_4_2_1-solution000006.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 2, 3} +letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_2_1-solution000007.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_2_1-solution000007.solution new file mode 100644 index 0000000000..bd956f44e3 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_4_2_1-solution000007.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 2, 3, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_2_1.eprime b/tests/exhaustive/basic/comprehension_letting/expected/model_4_2_1.eprime new file mode 100644 index 0000000000..30ab2bb7fb --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_4_2_1.eprime @@ -0,0 +1,105 @@ +language ESSENCE' 1.0 + +find s_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find s_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +find s_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +find s_Occurrence: matrix indexed by [int(1..4)] of bool +letting let1 be -100 +find x: int(-100..100) +find conjure_aux1: int(-20..3) +branching on + [s_Occurrence, s_ExplicitVarSizeWithFlags_Flags, s_ExplicitVarSizeWithFlags_Values, s_ExplicitVarSizeWithDummy, x] +such that + and([and([s_ExplicitVarSizeWithFlags_Flags[q29], s_ExplicitVarSizeWithDummy[q30] != 5, + s_ExplicitVarSizeWithFlags_Values[q29] != s_ExplicitVarSizeWithDummy[q30], + allDiff([s_ExplicitVarSizeWithFlags_Values[q29] + s_ExplicitVarSizeWithDummy[q30], + s_ExplicitVarSizeWithFlags_Values[q29] * s_ExplicitVarSizeWithDummy[q30], + s_ExplicitVarSizeWithFlags_Values[q29] / s_ExplicitVarSizeWithDummy[q30]; + int(1..3)]), + (s_ExplicitVarSizeWithFlags_Values[q29] - s_ExplicitVarSizeWithDummy[q30]) % 2 = 0; + int(1..5)]) + -> + min([s_ExplicitVarSizeWithFlags_Values[q29] + s_ExplicitVarSizeWithDummy[q30], + s_ExplicitVarSizeWithFlags_Values[q29] - s_ExplicitVarSizeWithDummy[q30], + s_ExplicitVarSizeWithFlags_Values[q29] * s_ExplicitVarSizeWithDummy[q30], + s_ExplicitVarSizeWithFlags_Values[q29] / s_ExplicitVarSizeWithDummy[q30]; + int(1..4)]) + <= conjure_aux1 + | q29 : int(1..4), q30 : int(1..4)]), + sum([toInt(and([s_ExplicitVarSizeWithFlags_Flags[q29], s_ExplicitVarSizeWithDummy[q30] != 5, + s_ExplicitVarSizeWithFlags_Values[q29] != s_ExplicitVarSizeWithDummy[q30], + allDiff([s_ExplicitVarSizeWithFlags_Values[q29] + s_ExplicitVarSizeWithDummy[q30], + s_ExplicitVarSizeWithFlags_Values[q29] * s_ExplicitVarSizeWithDummy[q30], + s_ExplicitVarSizeWithFlags_Values[q29] / s_ExplicitVarSizeWithDummy[q30]; + int(1..3)]), + (s_ExplicitVarSizeWithFlags_Values[q29] - s_ExplicitVarSizeWithDummy[q30]) % 2 = 0; + int(1..5)])) + | q29 : int(1..4), q30 : int(1..4)]) + > 0 + -> + or([and([s_ExplicitVarSizeWithFlags_Flags[q29], s_ExplicitVarSizeWithDummy[q30] != 5, + s_ExplicitVarSizeWithFlags_Values[q29] != s_ExplicitVarSizeWithDummy[q30], + allDiff([s_ExplicitVarSizeWithFlags_Values[q29] + s_ExplicitVarSizeWithDummy[q30], + s_ExplicitVarSizeWithFlags_Values[q29] * s_ExplicitVarSizeWithDummy[q30], + s_ExplicitVarSizeWithFlags_Values[q29] / s_ExplicitVarSizeWithDummy[q30]; + int(1..3)]), + (s_ExplicitVarSizeWithFlags_Values[q29] - s_ExplicitVarSizeWithDummy[q30]) % 2 = 0; + int(1..5)]) + /\ + min([s_ExplicitVarSizeWithFlags_Values[q29] + s_ExplicitVarSizeWithDummy[q30], + s_ExplicitVarSizeWithFlags_Values[q29] - s_ExplicitVarSizeWithDummy[q30], + s_ExplicitVarSizeWithFlags_Values[q29] * s_ExplicitVarSizeWithDummy[q30], + s_ExplicitVarSizeWithFlags_Values[q29] / s_ExplicitVarSizeWithDummy[q30]; + int(1..4)]) + = conjure_aux1 + | q29 : int(1..4), q30 : int(1..4)]), + sum([toInt(and([s_ExplicitVarSizeWithFlags_Flags[q29], s_ExplicitVarSizeWithDummy[q30] != 5, + s_ExplicitVarSizeWithFlags_Values[q29] != s_ExplicitVarSizeWithDummy[q30], + allDiff([s_ExplicitVarSizeWithFlags_Values[q29] + s_ExplicitVarSizeWithDummy[q30], + s_ExplicitVarSizeWithFlags_Values[q29] * s_ExplicitVarSizeWithDummy[q30], + s_ExplicitVarSizeWithFlags_Values[q29] / s_ExplicitVarSizeWithDummy[q30]; + int(1..3)]), + (s_ExplicitVarSizeWithFlags_Values[q29] - s_ExplicitVarSizeWithDummy[q30]) % 2 = 0; + int(1..5)])) + | q29 : int(1..4), q30 : int(1..4)]) + = 0 + -> conjure_aux1 = -20, + x = conjure_aux1, + sum([toInt(and([s_ExplicitVarSizeWithFlags_Flags[q29], s_ExplicitVarSizeWithDummy[q30] != 5, + s_ExplicitVarSizeWithFlags_Values[q29] != s_ExplicitVarSizeWithDummy[q30], + allDiff([s_ExplicitVarSizeWithFlags_Values[q29] + s_ExplicitVarSizeWithDummy[q30], + s_ExplicitVarSizeWithFlags_Values[q29] * s_ExplicitVarSizeWithDummy[q30], + s_ExplicitVarSizeWithFlags_Values[q29] / s_ExplicitVarSizeWithDummy[q30]; + int(1..3)]), + (s_ExplicitVarSizeWithFlags_Values[q29] - s_ExplicitVarSizeWithDummy[q30]) % 2 = 0; + int(1..5)])) + | q29 : int(1..4), q30 : int(1..4)]) + > 0, + and([s_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> + s_ExplicitVarSizeWithFlags_Values[q1] < s_ExplicitVarSizeWithFlags_Values[q1 + 1] + | q1 : int(1..3)]), + and([s_ExplicitVarSizeWithFlags_Flags[q2] = false -> s_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..4)]), + and([s_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> s_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), + and([s_ExplicitVarSizeWithDummy[q6] < s_ExplicitVarSizeWithDummy[q6 + 1] \/ s_ExplicitVarSizeWithDummy[q6] = 5 + | q6 : int(1..3)]), + and([s_ExplicitVarSizeWithDummy[q7] = 5 -> s_ExplicitVarSizeWithDummy[q7 + 1] = 5 | q7 : int(1..3)]), + and([s_ExplicitVarSizeWithDummy[q11] != 5 -> + or([s_ExplicitVarSizeWithFlags_Flags[q13] /\ + s_ExplicitVarSizeWithFlags_Values[q13] = s_ExplicitVarSizeWithDummy[q11] + | q13 : int(1..4)]) + | q11 : int(1..4)]), + and([s_ExplicitVarSizeWithFlags_Flags[q15] -> + or([s_ExplicitVarSizeWithDummy[q17] != 5 /\ + s_ExplicitVarSizeWithDummy[q17] = s_ExplicitVarSizeWithFlags_Values[q15] + | q17 : int(1..4)]) + | q15 : int(1..4)]), + and([s_Occurrence[q19] -> + or([s_ExplicitVarSizeWithFlags_Flags[q21] /\ s_ExplicitVarSizeWithFlags_Values[q21] = q19 | q21 : int(1..4)]) + | q19 : int(1..4)]), + and([s_ExplicitVarSizeWithFlags_Flags[q23] -> s_Occurrence[s_ExplicitVarSizeWithFlags_Values[q23]] + | q23 : int(1..4)]), + and([s_Occurrence[q24] -> + or([s_ExplicitVarSizeWithDummy[q26] != 5 /\ s_ExplicitVarSizeWithDummy[q26] = q24 | q26 : int(1..4)]) + | q24 : int(1..4)]), + and([s_ExplicitVarSizeWithDummy[q28] != 5 -> s_Occurrence[s_ExplicitVarSizeWithDummy[q28]] | q28 : int(1..4)]) + diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_2_2-solution000001.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_2_2-solution000001.solution new file mode 100644 index 0000000000..bd956f44e3 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_4_2_2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 2, 3, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_2_2-solution000002.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_2_2-solution000002.solution new file mode 100644 index 0000000000..5963aac565 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_4_2_2-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 2, 3} +letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_2_2-solution000003.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_2_2-solution000003.solution new file mode 100644 index 0000000000..6eeacc9727 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_4_2_2-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 2, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_2_2-solution000004.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_2_2-solution000004.solution new file mode 100644 index 0000000000..560dd0f2f7 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_4_2_2-solution000004.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 3, 4} +letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_2_2-solution000005.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_2_2-solution000005.solution new file mode 100644 index 0000000000..8b4ecbb66d --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_4_2_2-solution000005.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 3} +letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_2_2-solution000006.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_2_2-solution000006.solution new file mode 100644 index 0000000000..40f3fd5c8f --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_4_2_2-solution000006.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {2, 3, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_2_2-solution000007.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_2_2-solution000007.solution new file mode 100644 index 0000000000..159a613983 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_4_2_2-solution000007.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {2, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_2_2.eprime b/tests/exhaustive/basic/comprehension_letting/expected/model_4_2_2.eprime new file mode 100644 index 0000000000..7d168cbf12 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_4_2_2.eprime @@ -0,0 +1,94 @@ +language ESSENCE' 1.0 + +find s_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find s_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +find s_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +letting let1 be -100 +find x: int(-100..100) +find conjure_aux1: int(-20..3) +branching on [s_ExplicitVarSizeWithDummy, s_ExplicitVarSizeWithFlags_Flags, s_ExplicitVarSizeWithFlags_Values, x] +such that + and([and([s_ExplicitVarSizeWithFlags_Flags[q18], s_ExplicitVarSizeWithDummy[q19] != 5, + s_ExplicitVarSizeWithFlags_Values[q18] != s_ExplicitVarSizeWithDummy[q19], + allDiff([s_ExplicitVarSizeWithFlags_Values[q18] + s_ExplicitVarSizeWithDummy[q19], + s_ExplicitVarSizeWithFlags_Values[q18] * s_ExplicitVarSizeWithDummy[q19], + s_ExplicitVarSizeWithFlags_Values[q18] / s_ExplicitVarSizeWithDummy[q19]; + int(1..3)]), + (s_ExplicitVarSizeWithFlags_Values[q18] - s_ExplicitVarSizeWithDummy[q19]) % 2 = 0; + int(1..5)]) + -> + min([s_ExplicitVarSizeWithFlags_Values[q18] + s_ExplicitVarSizeWithDummy[q19], + s_ExplicitVarSizeWithFlags_Values[q18] - s_ExplicitVarSizeWithDummy[q19], + s_ExplicitVarSizeWithFlags_Values[q18] * s_ExplicitVarSizeWithDummy[q19], + s_ExplicitVarSizeWithFlags_Values[q18] / s_ExplicitVarSizeWithDummy[q19]; + int(1..4)]) + <= conjure_aux1 + | q18 : int(1..4), q19 : int(1..4)]), + sum([toInt(and([s_ExplicitVarSizeWithFlags_Flags[q18], s_ExplicitVarSizeWithDummy[q19] != 5, + s_ExplicitVarSizeWithFlags_Values[q18] != s_ExplicitVarSizeWithDummy[q19], + allDiff([s_ExplicitVarSizeWithFlags_Values[q18] + s_ExplicitVarSizeWithDummy[q19], + s_ExplicitVarSizeWithFlags_Values[q18] * s_ExplicitVarSizeWithDummy[q19], + s_ExplicitVarSizeWithFlags_Values[q18] / s_ExplicitVarSizeWithDummy[q19]; + int(1..3)]), + (s_ExplicitVarSizeWithFlags_Values[q18] - s_ExplicitVarSizeWithDummy[q19]) % 2 = 0; + int(1..5)])) + | q18 : int(1..4), q19 : int(1..4)]) + > 0 + -> + or([and([s_ExplicitVarSizeWithFlags_Flags[q18], s_ExplicitVarSizeWithDummy[q19] != 5, + s_ExplicitVarSizeWithFlags_Values[q18] != s_ExplicitVarSizeWithDummy[q19], + allDiff([s_ExplicitVarSizeWithFlags_Values[q18] + s_ExplicitVarSizeWithDummy[q19], + s_ExplicitVarSizeWithFlags_Values[q18] * s_ExplicitVarSizeWithDummy[q19], + s_ExplicitVarSizeWithFlags_Values[q18] / s_ExplicitVarSizeWithDummy[q19]; + int(1..3)]), + (s_ExplicitVarSizeWithFlags_Values[q18] - s_ExplicitVarSizeWithDummy[q19]) % 2 = 0; + int(1..5)]) + /\ + min([s_ExplicitVarSizeWithFlags_Values[q18] + s_ExplicitVarSizeWithDummy[q19], + s_ExplicitVarSizeWithFlags_Values[q18] - s_ExplicitVarSizeWithDummy[q19], + s_ExplicitVarSizeWithFlags_Values[q18] * s_ExplicitVarSizeWithDummy[q19], + s_ExplicitVarSizeWithFlags_Values[q18] / s_ExplicitVarSizeWithDummy[q19]; + int(1..4)]) + = conjure_aux1 + | q18 : int(1..4), q19 : int(1..4)]), + sum([toInt(and([s_ExplicitVarSizeWithFlags_Flags[q18], s_ExplicitVarSizeWithDummy[q19] != 5, + s_ExplicitVarSizeWithFlags_Values[q18] != s_ExplicitVarSizeWithDummy[q19], + allDiff([s_ExplicitVarSizeWithFlags_Values[q18] + s_ExplicitVarSizeWithDummy[q19], + s_ExplicitVarSizeWithFlags_Values[q18] * s_ExplicitVarSizeWithDummy[q19], + s_ExplicitVarSizeWithFlags_Values[q18] / s_ExplicitVarSizeWithDummy[q19]; + int(1..3)]), + (s_ExplicitVarSizeWithFlags_Values[q18] - s_ExplicitVarSizeWithDummy[q19]) % 2 = 0; + int(1..5)])) + | q18 : int(1..4), q19 : int(1..4)]) + = 0 + -> conjure_aux1 = -20, + x = conjure_aux1, + sum([toInt(and([s_ExplicitVarSizeWithFlags_Flags[q18], s_ExplicitVarSizeWithDummy[q19] != 5, + s_ExplicitVarSizeWithFlags_Values[q18] != s_ExplicitVarSizeWithDummy[q19], + allDiff([s_ExplicitVarSizeWithFlags_Values[q18] + s_ExplicitVarSizeWithDummy[q19], + s_ExplicitVarSizeWithFlags_Values[q18] * s_ExplicitVarSizeWithDummy[q19], + s_ExplicitVarSizeWithFlags_Values[q18] / s_ExplicitVarSizeWithDummy[q19]; + int(1..3)]), + (s_ExplicitVarSizeWithFlags_Values[q18] - s_ExplicitVarSizeWithDummy[q19]) % 2 = 0; + int(1..5)])) + | q18 : int(1..4), q19 : int(1..4)]) + > 0, + and([s_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> + s_ExplicitVarSizeWithFlags_Values[q1] < s_ExplicitVarSizeWithFlags_Values[q1 + 1] + | q1 : int(1..3)]), + and([s_ExplicitVarSizeWithFlags_Flags[q2] = false -> s_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..4)]), + and([s_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> s_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), + and([s_ExplicitVarSizeWithDummy[q6] < s_ExplicitVarSizeWithDummy[q6 + 1] \/ s_ExplicitVarSizeWithDummy[q6] = 5 + | q6 : int(1..3)]), + and([s_ExplicitVarSizeWithDummy[q7] = 5 -> s_ExplicitVarSizeWithDummy[q7 + 1] = 5 | q7 : int(1..3)]), + and([s_ExplicitVarSizeWithDummy[q11] != 5 -> + or([s_ExplicitVarSizeWithFlags_Flags[q13] /\ + s_ExplicitVarSizeWithFlags_Values[q13] = s_ExplicitVarSizeWithDummy[q11] + | q13 : int(1..4)]) + | q11 : int(1..4)]), + and([s_ExplicitVarSizeWithFlags_Flags[q15] -> + or([s_ExplicitVarSizeWithDummy[q17] != 5 /\ + s_ExplicitVarSizeWithDummy[q17] = s_ExplicitVarSizeWithFlags_Values[q15] + | q17 : int(1..4)]) + | q15 : int(1..4)]) + diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_2_3-solution000001.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_2_3-solution000001.solution new file mode 100644 index 0000000000..8b4ecbb66d --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_4_2_3-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 3} +letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_2_3-solution000002.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_2_3-solution000002.solution new file mode 100644 index 0000000000..159a613983 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_4_2_3-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {2, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_2_3-solution000003.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_2_3-solution000003.solution new file mode 100644 index 0000000000..5963aac565 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_4_2_3-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 2, 3} +letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_2_3-solution000004.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_2_3-solution000004.solution new file mode 100644 index 0000000000..6eeacc9727 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_4_2_3-solution000004.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 2, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_2_3-solution000005.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_2_3-solution000005.solution new file mode 100644 index 0000000000..560dd0f2f7 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_4_2_3-solution000005.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 3, 4} +letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_2_3-solution000006.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_2_3-solution000006.solution new file mode 100644 index 0000000000..40f3fd5c8f --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_4_2_3-solution000006.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {2, 3, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_2_3-solution000007.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_2_3-solution000007.solution new file mode 100644 index 0000000000..bd956f44e3 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_4_2_3-solution000007.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 2, 3, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_2_3.eprime b/tests/exhaustive/basic/comprehension_letting/expected/model_4_2_3.eprime new file mode 100644 index 0000000000..ba3742175a --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_4_2_3.eprime @@ -0,0 +1,122 @@ +language ESSENCE' 1.0 + +find s_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find s_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +find s_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +find s_ExplicitVarSizeWithMarker_Marker: int(0..4) +find s_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +letting let1 be -100 +find x: int(-100..100) +find conjure_aux1: int(-20..3) +branching on + [s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithMarker_Values, s_ExplicitVarSizeWithFlags_Flags, + s_ExplicitVarSizeWithFlags_Values, s_ExplicitVarSizeWithDummy, x] +such that + and([and([s_ExplicitVarSizeWithFlags_Flags[q37], s_ExplicitVarSizeWithDummy[q38] != 5, + s_ExplicitVarSizeWithFlags_Values[q37] != s_ExplicitVarSizeWithDummy[q38], + allDiff([s_ExplicitVarSizeWithFlags_Values[q37] + s_ExplicitVarSizeWithDummy[q38], + s_ExplicitVarSizeWithFlags_Values[q37] * s_ExplicitVarSizeWithDummy[q38], + s_ExplicitVarSizeWithFlags_Values[q37] / s_ExplicitVarSizeWithDummy[q38]; + int(1..3)]), + (s_ExplicitVarSizeWithFlags_Values[q37] - s_ExplicitVarSizeWithDummy[q38]) % 2 = 0; + int(1..5)]) + -> + min([s_ExplicitVarSizeWithFlags_Values[q37] + s_ExplicitVarSizeWithDummy[q38], + s_ExplicitVarSizeWithFlags_Values[q37] - s_ExplicitVarSizeWithDummy[q38], + s_ExplicitVarSizeWithFlags_Values[q37] * s_ExplicitVarSizeWithDummy[q38], + s_ExplicitVarSizeWithFlags_Values[q37] / s_ExplicitVarSizeWithDummy[q38]; + int(1..4)]) + <= conjure_aux1 + | q37 : int(1..4), q38 : int(1..4)]), + sum([toInt(and([s_ExplicitVarSizeWithFlags_Flags[q37], s_ExplicitVarSizeWithDummy[q38] != 5, + s_ExplicitVarSizeWithFlags_Values[q37] != s_ExplicitVarSizeWithDummy[q38], + allDiff([s_ExplicitVarSizeWithFlags_Values[q37] + s_ExplicitVarSizeWithDummy[q38], + s_ExplicitVarSizeWithFlags_Values[q37] * s_ExplicitVarSizeWithDummy[q38], + s_ExplicitVarSizeWithFlags_Values[q37] / s_ExplicitVarSizeWithDummy[q38]; + int(1..3)]), + (s_ExplicitVarSizeWithFlags_Values[q37] - s_ExplicitVarSizeWithDummy[q38]) % 2 = 0; + int(1..5)])) + | q37 : int(1..4), q38 : int(1..4)]) + > 0 + -> + or([and([s_ExplicitVarSizeWithFlags_Flags[q37], s_ExplicitVarSizeWithDummy[q38] != 5, + s_ExplicitVarSizeWithFlags_Values[q37] != s_ExplicitVarSizeWithDummy[q38], + allDiff([s_ExplicitVarSizeWithFlags_Values[q37] + s_ExplicitVarSizeWithDummy[q38], + s_ExplicitVarSizeWithFlags_Values[q37] * s_ExplicitVarSizeWithDummy[q38], + s_ExplicitVarSizeWithFlags_Values[q37] / s_ExplicitVarSizeWithDummy[q38]; + int(1..3)]), + (s_ExplicitVarSizeWithFlags_Values[q37] - s_ExplicitVarSizeWithDummy[q38]) % 2 = 0; + int(1..5)]) + /\ + min([s_ExplicitVarSizeWithFlags_Values[q37] + s_ExplicitVarSizeWithDummy[q38], + s_ExplicitVarSizeWithFlags_Values[q37] - s_ExplicitVarSizeWithDummy[q38], + s_ExplicitVarSizeWithFlags_Values[q37] * s_ExplicitVarSizeWithDummy[q38], + s_ExplicitVarSizeWithFlags_Values[q37] / s_ExplicitVarSizeWithDummy[q38]; + int(1..4)]) + = conjure_aux1 + | q37 : int(1..4), q38 : int(1..4)]), + sum([toInt(and([s_ExplicitVarSizeWithFlags_Flags[q37], s_ExplicitVarSizeWithDummy[q38] != 5, + s_ExplicitVarSizeWithFlags_Values[q37] != s_ExplicitVarSizeWithDummy[q38], + allDiff([s_ExplicitVarSizeWithFlags_Values[q37] + s_ExplicitVarSizeWithDummy[q38], + s_ExplicitVarSizeWithFlags_Values[q37] * s_ExplicitVarSizeWithDummy[q38], + s_ExplicitVarSizeWithFlags_Values[q37] / s_ExplicitVarSizeWithDummy[q38]; + int(1..3)]), + (s_ExplicitVarSizeWithFlags_Values[q37] - s_ExplicitVarSizeWithDummy[q38]) % 2 = 0; + int(1..5)])) + | q37 : int(1..4), q38 : int(1..4)]) + = 0 + -> conjure_aux1 = -20, + x = conjure_aux1, + sum([toInt(and([s_ExplicitVarSizeWithFlags_Flags[q37], s_ExplicitVarSizeWithDummy[q38] != 5, + s_ExplicitVarSizeWithFlags_Values[q37] != s_ExplicitVarSizeWithDummy[q38], + allDiff([s_ExplicitVarSizeWithFlags_Values[q37] + s_ExplicitVarSizeWithDummy[q38], + s_ExplicitVarSizeWithFlags_Values[q37] * s_ExplicitVarSizeWithDummy[q38], + s_ExplicitVarSizeWithFlags_Values[q37] / s_ExplicitVarSizeWithDummy[q38]; + int(1..3)]), + (s_ExplicitVarSizeWithFlags_Values[q37] - s_ExplicitVarSizeWithDummy[q38]) % 2 = 0; + int(1..5)])) + | q37 : int(1..4), q38 : int(1..4)]) + > 0, + and([s_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> + s_ExplicitVarSizeWithFlags_Values[q1] < s_ExplicitVarSizeWithFlags_Values[q1 + 1] + | q1 : int(1..3)]), + and([s_ExplicitVarSizeWithFlags_Flags[q2] = false -> s_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..4)]), + and([s_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> s_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), + and([s_ExplicitVarSizeWithDummy[q6] < s_ExplicitVarSizeWithDummy[q6 + 1] \/ s_ExplicitVarSizeWithDummy[q6] = 5 + | q6 : int(1..3)]), + and([s_ExplicitVarSizeWithDummy[q7] = 5 -> s_ExplicitVarSizeWithDummy[q7 + 1] = 5 | q7 : int(1..3)]), + and([s_ExplicitVarSizeWithDummy[q11] != 5 -> + or([s_ExplicitVarSizeWithFlags_Flags[q13] /\ + s_ExplicitVarSizeWithFlags_Values[q13] = s_ExplicitVarSizeWithDummy[q11] + | q13 : int(1..4)]) + | q11 : int(1..4)]), + and([s_ExplicitVarSizeWithFlags_Flags[q15] -> + or([s_ExplicitVarSizeWithDummy[q17] != 5 /\ + s_ExplicitVarSizeWithDummy[q17] = s_ExplicitVarSizeWithFlags_Values[q15] + | q17 : int(1..4)]) + | q15 : int(1..4)]), + and([q18 + 1 <= s_ExplicitVarSizeWithMarker_Marker -> + s_ExplicitVarSizeWithMarker_Values[q18] < s_ExplicitVarSizeWithMarker_Values[q18 + 1] + | q18 : int(1..3)]), + and([q19 > s_ExplicitVarSizeWithMarker_Marker -> s_ExplicitVarSizeWithMarker_Values[q19] = 1 | q19 : int(1..4)]), + and([q22 <= s_ExplicitVarSizeWithMarker_Marker -> + or([s_ExplicitVarSizeWithFlags_Flags[q24] /\ + s_ExplicitVarSizeWithFlags_Values[q24] = s_ExplicitVarSizeWithMarker_Values[q22] + | q24 : int(1..4)]) + | q22 : int(1..4)]), + and([s_ExplicitVarSizeWithFlags_Flags[q26] -> + or([q28 <= s_ExplicitVarSizeWithMarker_Marker /\ + s_ExplicitVarSizeWithMarker_Values[q28] = s_ExplicitVarSizeWithFlags_Values[q26] + | q28 : int(1..4)]) + | q26 : int(1..4)]), + and([q30 <= s_ExplicitVarSizeWithMarker_Marker -> + or([s_ExplicitVarSizeWithDummy[q32] != 5 /\ + s_ExplicitVarSizeWithDummy[q32] = s_ExplicitVarSizeWithMarker_Values[q30] + | q32 : int(1..4)]) + | q30 : int(1..4)]), + and([s_ExplicitVarSizeWithDummy[q34] != 5 -> + or([q36 <= s_ExplicitVarSizeWithMarker_Marker /\ + s_ExplicitVarSizeWithMarker_Values[q36] = s_ExplicitVarSizeWithDummy[q34] + | q36 : int(1..4)]) + | q34 : int(1..4)]) + diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_3_1-solution000001.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_3_1-solution000001.solution new file mode 100644 index 0000000000..159a613983 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_4_3_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {2, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_3_1-solution000002.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_3_1-solution000002.solution new file mode 100644 index 0000000000..40f3fd5c8f --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_4_3_1-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {2, 3, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_3_1-solution000003.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_3_1-solution000003.solution new file mode 100644 index 0000000000..8b4ecbb66d --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_4_3_1-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 3} +letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_3_1-solution000004.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_3_1-solution000004.solution new file mode 100644 index 0000000000..560dd0f2f7 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_4_3_1-solution000004.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 3, 4} +letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_3_1-solution000005.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_3_1-solution000005.solution new file mode 100644 index 0000000000..6eeacc9727 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_4_3_1-solution000005.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 2, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_3_1-solution000006.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_3_1-solution000006.solution new file mode 100644 index 0000000000..5963aac565 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_4_3_1-solution000006.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 2, 3} +letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_3_1-solution000007.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_3_1-solution000007.solution new file mode 100644 index 0000000000..bd956f44e3 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_4_3_1-solution000007.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 2, 3, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_3_1.eprime b/tests/exhaustive/basic/comprehension_letting/expected/model_4_3_1.eprime new file mode 100644 index 0000000000..5e74dde769 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_4_3_1.eprime @@ -0,0 +1,110 @@ +language ESSENCE' 1.0 + +find s_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find s_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +find s_ExplicitVarSizeWithMarker_Marker: int(0..4) +find s_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +find s_Occurrence: matrix indexed by [int(1..4)] of bool +letting let1 be -100 +find x: int(-100..100) +find conjure_aux1: int(-16..3) +branching on + [s_Occurrence, s_ExplicitVarSizeWithFlags_Flags, s_ExplicitVarSizeWithFlags_Values, + s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithMarker_Values, x] +such that + and([and([s_ExplicitVarSizeWithFlags_Flags[q28], q29 <= s_ExplicitVarSizeWithMarker_Marker, + s_ExplicitVarSizeWithFlags_Values[q28] != s_ExplicitVarSizeWithMarker_Values[q29], + allDiff([s_ExplicitVarSizeWithFlags_Values[q28] + s_ExplicitVarSizeWithMarker_Values[q29], + s_ExplicitVarSizeWithFlags_Values[q28] * s_ExplicitVarSizeWithMarker_Values[q29], + s_ExplicitVarSizeWithFlags_Values[q28] / s_ExplicitVarSizeWithMarker_Values[q29]; + int(1..3)]), + (s_ExplicitVarSizeWithFlags_Values[q28] - s_ExplicitVarSizeWithMarker_Values[q29]) % 2 = 0; + int(1..5)]) + -> + min([s_ExplicitVarSizeWithFlags_Values[q28] + s_ExplicitVarSizeWithMarker_Values[q29], + s_ExplicitVarSizeWithFlags_Values[q28] - s_ExplicitVarSizeWithMarker_Values[q29], + s_ExplicitVarSizeWithFlags_Values[q28] * s_ExplicitVarSizeWithMarker_Values[q29], + s_ExplicitVarSizeWithFlags_Values[q28] / s_ExplicitVarSizeWithMarker_Values[q29]; + int(1..4)]) + <= conjure_aux1 + | q28 : int(1..4), q29 : int(1..4)]), + sum([toInt(and([s_ExplicitVarSizeWithFlags_Flags[q28], q29 <= s_ExplicitVarSizeWithMarker_Marker, + s_ExplicitVarSizeWithFlags_Values[q28] != s_ExplicitVarSizeWithMarker_Values[q29], + allDiff([s_ExplicitVarSizeWithFlags_Values[q28] + s_ExplicitVarSizeWithMarker_Values[q29], + s_ExplicitVarSizeWithFlags_Values[q28] * s_ExplicitVarSizeWithMarker_Values[q29], + s_ExplicitVarSizeWithFlags_Values[q28] / s_ExplicitVarSizeWithMarker_Values[q29]; + int(1..3)]), + (s_ExplicitVarSizeWithFlags_Values[q28] - s_ExplicitVarSizeWithMarker_Values[q29]) % 2 = 0; + int(1..5)])) + | q28 : int(1..4), q29 : int(1..4)]) + > 0 + -> + or([and([s_ExplicitVarSizeWithFlags_Flags[q28], q29 <= s_ExplicitVarSizeWithMarker_Marker, + s_ExplicitVarSizeWithFlags_Values[q28] != s_ExplicitVarSizeWithMarker_Values[q29], + allDiff([s_ExplicitVarSizeWithFlags_Values[q28] + s_ExplicitVarSizeWithMarker_Values[q29], + s_ExplicitVarSizeWithFlags_Values[q28] * s_ExplicitVarSizeWithMarker_Values[q29], + s_ExplicitVarSizeWithFlags_Values[q28] / s_ExplicitVarSizeWithMarker_Values[q29]; + int(1..3)]), + (s_ExplicitVarSizeWithFlags_Values[q28] - s_ExplicitVarSizeWithMarker_Values[q29]) % 2 = 0; + int(1..5)]) + /\ + min([s_ExplicitVarSizeWithFlags_Values[q28] + s_ExplicitVarSizeWithMarker_Values[q29], + s_ExplicitVarSizeWithFlags_Values[q28] - s_ExplicitVarSizeWithMarker_Values[q29], + s_ExplicitVarSizeWithFlags_Values[q28] * s_ExplicitVarSizeWithMarker_Values[q29], + s_ExplicitVarSizeWithFlags_Values[q28] / s_ExplicitVarSizeWithMarker_Values[q29]; + int(1..4)]) + = conjure_aux1 + | q28 : int(1..4), q29 : int(1..4)]), + sum([toInt(and([s_ExplicitVarSizeWithFlags_Flags[q28], q29 <= s_ExplicitVarSizeWithMarker_Marker, + s_ExplicitVarSizeWithFlags_Values[q28] != s_ExplicitVarSizeWithMarker_Values[q29], + allDiff([s_ExplicitVarSizeWithFlags_Values[q28] + s_ExplicitVarSizeWithMarker_Values[q29], + s_ExplicitVarSizeWithFlags_Values[q28] * s_ExplicitVarSizeWithMarker_Values[q29], + s_ExplicitVarSizeWithFlags_Values[q28] / s_ExplicitVarSizeWithMarker_Values[q29]; + int(1..3)]), + (s_ExplicitVarSizeWithFlags_Values[q28] - s_ExplicitVarSizeWithMarker_Values[q29]) % 2 = 0; + int(1..5)])) + | q28 : int(1..4), q29 : int(1..4)]) + = 0 + -> conjure_aux1 = -16, + x = conjure_aux1, + sum([toInt(and([s_ExplicitVarSizeWithFlags_Flags[q28], q29 <= s_ExplicitVarSizeWithMarker_Marker, + s_ExplicitVarSizeWithFlags_Values[q28] != s_ExplicitVarSizeWithMarker_Values[q29], + allDiff([s_ExplicitVarSizeWithFlags_Values[q28] + s_ExplicitVarSizeWithMarker_Values[q29], + s_ExplicitVarSizeWithFlags_Values[q28] * s_ExplicitVarSizeWithMarker_Values[q29], + s_ExplicitVarSizeWithFlags_Values[q28] / s_ExplicitVarSizeWithMarker_Values[q29]; + int(1..3)]), + (s_ExplicitVarSizeWithFlags_Values[q28] - s_ExplicitVarSizeWithMarker_Values[q29]) % 2 = 0; + int(1..5)])) + | q28 : int(1..4), q29 : int(1..4)]) + > 0, + and([s_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> + s_ExplicitVarSizeWithFlags_Values[q1] < s_ExplicitVarSizeWithFlags_Values[q1 + 1] + | q1 : int(1..3)]), + and([s_ExplicitVarSizeWithFlags_Flags[q2] = false -> s_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..4)]), + and([s_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> s_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), + and([q6 + 1 <= s_ExplicitVarSizeWithMarker_Marker -> + s_ExplicitVarSizeWithMarker_Values[q6] < s_ExplicitVarSizeWithMarker_Values[q6 + 1] + | q6 : int(1..3)]), + and([q7 > s_ExplicitVarSizeWithMarker_Marker -> s_ExplicitVarSizeWithMarker_Values[q7] = 1 | q7 : int(1..4)]), + and([q10 <= s_ExplicitVarSizeWithMarker_Marker -> + or([s_ExplicitVarSizeWithFlags_Flags[q12] /\ + s_ExplicitVarSizeWithFlags_Values[q12] = s_ExplicitVarSizeWithMarker_Values[q10] + | q12 : int(1..4)]) + | q10 : int(1..4)]), + and([s_ExplicitVarSizeWithFlags_Flags[q14] -> + or([q16 <= s_ExplicitVarSizeWithMarker_Marker /\ + s_ExplicitVarSizeWithMarker_Values[q16] = s_ExplicitVarSizeWithFlags_Values[q14] + | q16 : int(1..4)]) + | q14 : int(1..4)]), + and([s_Occurrence[q18] -> + or([s_ExplicitVarSizeWithFlags_Flags[q20] /\ s_ExplicitVarSizeWithFlags_Values[q20] = q18 | q20 : int(1..4)]) + | q18 : int(1..4)]), + and([s_ExplicitVarSizeWithFlags_Flags[q22] -> s_Occurrence[s_ExplicitVarSizeWithFlags_Values[q22]] + | q22 : int(1..4)]), + and([s_Occurrence[q23] -> + or([q25 <= s_ExplicitVarSizeWithMarker_Marker /\ s_ExplicitVarSizeWithMarker_Values[q25] = q23 + | q25 : int(1..4)]) + | q23 : int(1..4)]), + and([q27 <= s_ExplicitVarSizeWithMarker_Marker -> s_Occurrence[s_ExplicitVarSizeWithMarker_Values[q27]] + | q27 : int(1..4)]) + diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_3_2-solution000001.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_3_2-solution000001.solution new file mode 100644 index 0000000000..bd956f44e3 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_4_3_2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 2, 3, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_3_2-solution000002.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_3_2-solution000002.solution new file mode 100644 index 0000000000..5963aac565 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_4_3_2-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 2, 3} +letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_3_2-solution000003.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_3_2-solution000003.solution new file mode 100644 index 0000000000..6eeacc9727 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_4_3_2-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 2, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_3_2-solution000004.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_3_2-solution000004.solution new file mode 100644 index 0000000000..560dd0f2f7 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_4_3_2-solution000004.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 3, 4} +letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_3_2-solution000005.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_3_2-solution000005.solution new file mode 100644 index 0000000000..8b4ecbb66d --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_4_3_2-solution000005.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 3} +letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_3_2-solution000006.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_3_2-solution000006.solution new file mode 100644 index 0000000000..40f3fd5c8f --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_4_3_2-solution000006.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {2, 3, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_3_2-solution000007.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_3_2-solution000007.solution new file mode 100644 index 0000000000..159a613983 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_4_3_2-solution000007.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {2, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_3_2.eprime b/tests/exhaustive/basic/comprehension_letting/expected/model_4_3_2.eprime new file mode 100644 index 0000000000..80a6ca3fbf --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_4_3_2.eprime @@ -0,0 +1,122 @@ +language ESSENCE' 1.0 + +find s_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find s_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +find s_ExplicitVarSizeWithMarker_Marker: int(0..4) +find s_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +find s_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +letting let1 be -100 +find x: int(-100..100) +find conjure_aux1: int(-16..3) +branching on + [s_ExplicitVarSizeWithDummy, s_ExplicitVarSizeWithFlags_Flags, s_ExplicitVarSizeWithFlags_Values, + s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithMarker_Values, x] +such that + and([and([s_ExplicitVarSizeWithFlags_Flags[q37], q38 <= s_ExplicitVarSizeWithMarker_Marker, + s_ExplicitVarSizeWithFlags_Values[q37] != s_ExplicitVarSizeWithMarker_Values[q38], + allDiff([s_ExplicitVarSizeWithFlags_Values[q37] + s_ExplicitVarSizeWithMarker_Values[q38], + s_ExplicitVarSizeWithFlags_Values[q37] * s_ExplicitVarSizeWithMarker_Values[q38], + s_ExplicitVarSizeWithFlags_Values[q37] / s_ExplicitVarSizeWithMarker_Values[q38]; + int(1..3)]), + (s_ExplicitVarSizeWithFlags_Values[q37] - s_ExplicitVarSizeWithMarker_Values[q38]) % 2 = 0; + int(1..5)]) + -> + min([s_ExplicitVarSizeWithFlags_Values[q37] + s_ExplicitVarSizeWithMarker_Values[q38], + s_ExplicitVarSizeWithFlags_Values[q37] - s_ExplicitVarSizeWithMarker_Values[q38], + s_ExplicitVarSizeWithFlags_Values[q37] * s_ExplicitVarSizeWithMarker_Values[q38], + s_ExplicitVarSizeWithFlags_Values[q37] / s_ExplicitVarSizeWithMarker_Values[q38]; + int(1..4)]) + <= conjure_aux1 + | q37 : int(1..4), q38 : int(1..4)]), + sum([toInt(and([s_ExplicitVarSizeWithFlags_Flags[q37], q38 <= s_ExplicitVarSizeWithMarker_Marker, + s_ExplicitVarSizeWithFlags_Values[q37] != s_ExplicitVarSizeWithMarker_Values[q38], + allDiff([s_ExplicitVarSizeWithFlags_Values[q37] + s_ExplicitVarSizeWithMarker_Values[q38], + s_ExplicitVarSizeWithFlags_Values[q37] * s_ExplicitVarSizeWithMarker_Values[q38], + s_ExplicitVarSizeWithFlags_Values[q37] / s_ExplicitVarSizeWithMarker_Values[q38]; + int(1..3)]), + (s_ExplicitVarSizeWithFlags_Values[q37] - s_ExplicitVarSizeWithMarker_Values[q38]) % 2 = 0; + int(1..5)])) + | q37 : int(1..4), q38 : int(1..4)]) + > 0 + -> + or([and([s_ExplicitVarSizeWithFlags_Flags[q37], q38 <= s_ExplicitVarSizeWithMarker_Marker, + s_ExplicitVarSizeWithFlags_Values[q37] != s_ExplicitVarSizeWithMarker_Values[q38], + allDiff([s_ExplicitVarSizeWithFlags_Values[q37] + s_ExplicitVarSizeWithMarker_Values[q38], + s_ExplicitVarSizeWithFlags_Values[q37] * s_ExplicitVarSizeWithMarker_Values[q38], + s_ExplicitVarSizeWithFlags_Values[q37] / s_ExplicitVarSizeWithMarker_Values[q38]; + int(1..3)]), + (s_ExplicitVarSizeWithFlags_Values[q37] - s_ExplicitVarSizeWithMarker_Values[q38]) % 2 = 0; + int(1..5)]) + /\ + min([s_ExplicitVarSizeWithFlags_Values[q37] + s_ExplicitVarSizeWithMarker_Values[q38], + s_ExplicitVarSizeWithFlags_Values[q37] - s_ExplicitVarSizeWithMarker_Values[q38], + s_ExplicitVarSizeWithFlags_Values[q37] * s_ExplicitVarSizeWithMarker_Values[q38], + s_ExplicitVarSizeWithFlags_Values[q37] / s_ExplicitVarSizeWithMarker_Values[q38]; + int(1..4)]) + = conjure_aux1 + | q37 : int(1..4), q38 : int(1..4)]), + sum([toInt(and([s_ExplicitVarSizeWithFlags_Flags[q37], q38 <= s_ExplicitVarSizeWithMarker_Marker, + s_ExplicitVarSizeWithFlags_Values[q37] != s_ExplicitVarSizeWithMarker_Values[q38], + allDiff([s_ExplicitVarSizeWithFlags_Values[q37] + s_ExplicitVarSizeWithMarker_Values[q38], + s_ExplicitVarSizeWithFlags_Values[q37] * s_ExplicitVarSizeWithMarker_Values[q38], + s_ExplicitVarSizeWithFlags_Values[q37] / s_ExplicitVarSizeWithMarker_Values[q38]; + int(1..3)]), + (s_ExplicitVarSizeWithFlags_Values[q37] - s_ExplicitVarSizeWithMarker_Values[q38]) % 2 = 0; + int(1..5)])) + | q37 : int(1..4), q38 : int(1..4)]) + = 0 + -> conjure_aux1 = -16, + x = conjure_aux1, + sum([toInt(and([s_ExplicitVarSizeWithFlags_Flags[q37], q38 <= s_ExplicitVarSizeWithMarker_Marker, + s_ExplicitVarSizeWithFlags_Values[q37] != s_ExplicitVarSizeWithMarker_Values[q38], + allDiff([s_ExplicitVarSizeWithFlags_Values[q37] + s_ExplicitVarSizeWithMarker_Values[q38], + s_ExplicitVarSizeWithFlags_Values[q37] * s_ExplicitVarSizeWithMarker_Values[q38], + s_ExplicitVarSizeWithFlags_Values[q37] / s_ExplicitVarSizeWithMarker_Values[q38]; + int(1..3)]), + (s_ExplicitVarSizeWithFlags_Values[q37] - s_ExplicitVarSizeWithMarker_Values[q38]) % 2 = 0; + int(1..5)])) + | q37 : int(1..4), q38 : int(1..4)]) + > 0, + and([s_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> + s_ExplicitVarSizeWithFlags_Values[q1] < s_ExplicitVarSizeWithFlags_Values[q1 + 1] + | q1 : int(1..3)]), + and([s_ExplicitVarSizeWithFlags_Flags[q2] = false -> s_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..4)]), + and([s_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> s_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), + and([q6 + 1 <= s_ExplicitVarSizeWithMarker_Marker -> + s_ExplicitVarSizeWithMarker_Values[q6] < s_ExplicitVarSizeWithMarker_Values[q6 + 1] + | q6 : int(1..3)]), + and([q7 > s_ExplicitVarSizeWithMarker_Marker -> s_ExplicitVarSizeWithMarker_Values[q7] = 1 | q7 : int(1..4)]), + and([q10 <= s_ExplicitVarSizeWithMarker_Marker -> + or([s_ExplicitVarSizeWithFlags_Flags[q12] /\ + s_ExplicitVarSizeWithFlags_Values[q12] = s_ExplicitVarSizeWithMarker_Values[q10] + | q12 : int(1..4)]) + | q10 : int(1..4)]), + and([s_ExplicitVarSizeWithFlags_Flags[q14] -> + or([q16 <= s_ExplicitVarSizeWithMarker_Marker /\ + s_ExplicitVarSizeWithMarker_Values[q16] = s_ExplicitVarSizeWithFlags_Values[q14] + | q16 : int(1..4)]) + | q14 : int(1..4)]), + and([s_ExplicitVarSizeWithDummy[q17] < s_ExplicitVarSizeWithDummy[q17 + 1] \/ s_ExplicitVarSizeWithDummy[q17] = 5 + | q17 : int(1..3)]), + and([s_ExplicitVarSizeWithDummy[q18] = 5 -> s_ExplicitVarSizeWithDummy[q18 + 1] = 5 | q18 : int(1..3)]), + and([s_ExplicitVarSizeWithDummy[q22] != 5 -> + or([s_ExplicitVarSizeWithFlags_Flags[q24] /\ + s_ExplicitVarSizeWithFlags_Values[q24] = s_ExplicitVarSizeWithDummy[q22] + | q24 : int(1..4)]) + | q22 : int(1..4)]), + and([s_ExplicitVarSizeWithFlags_Flags[q26] -> + or([s_ExplicitVarSizeWithDummy[q28] != 5 /\ + s_ExplicitVarSizeWithDummy[q28] = s_ExplicitVarSizeWithFlags_Values[q26] + | q28 : int(1..4)]) + | q26 : int(1..4)]), + and([s_ExplicitVarSizeWithDummy[q30] != 5 -> + or([q32 <= s_ExplicitVarSizeWithMarker_Marker /\ + s_ExplicitVarSizeWithMarker_Values[q32] = s_ExplicitVarSizeWithDummy[q30] + | q32 : int(1..4)]) + | q30 : int(1..4)]), + and([q34 <= s_ExplicitVarSizeWithMarker_Marker -> + or([s_ExplicitVarSizeWithDummy[q36] != 5 /\ + s_ExplicitVarSizeWithDummy[q36] = s_ExplicitVarSizeWithMarker_Values[q34] + | q36 : int(1..4)]) + | q34 : int(1..4)]) + diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_3_3-solution000001.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_3_3-solution000001.solution new file mode 100644 index 0000000000..8b4ecbb66d --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_4_3_3-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 3} +letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_3_3-solution000002.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_3_3-solution000002.solution new file mode 100644 index 0000000000..159a613983 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_4_3_3-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {2, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_3_3-solution000003.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_3_3-solution000003.solution new file mode 100644 index 0000000000..5963aac565 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_4_3_3-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 2, 3} +letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_3_3-solution000004.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_3_3-solution000004.solution new file mode 100644 index 0000000000..6eeacc9727 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_4_3_3-solution000004.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 2, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_3_3-solution000005.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_3_3-solution000005.solution new file mode 100644 index 0000000000..560dd0f2f7 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_4_3_3-solution000005.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 3, 4} +letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_3_3-solution000006.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_3_3-solution000006.solution new file mode 100644 index 0000000000..40f3fd5c8f --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_4_3_3-solution000006.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {2, 3, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_3_3-solution000007.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_3_3-solution000007.solution new file mode 100644 index 0000000000..bd956f44e3 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_4_3_3-solution000007.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 2, 3, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_3_3.eprime b/tests/exhaustive/basic/comprehension_letting/expected/model_4_3_3.eprime new file mode 100644 index 0000000000..0a99214fbe --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_4_3_3.eprime @@ -0,0 +1,98 @@ +language ESSENCE' 1.0 + +find s_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find s_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +find s_ExplicitVarSizeWithMarker_Marker: int(0..4) +find s_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +letting let1 be -100 +find x: int(-100..100) +find conjure_aux1: int(-16..3) +branching on + [s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithMarker_Values, s_ExplicitVarSizeWithFlags_Flags, + s_ExplicitVarSizeWithFlags_Values, x] +such that + and([and([s_ExplicitVarSizeWithFlags_Flags[q17], q18 <= s_ExplicitVarSizeWithMarker_Marker, + s_ExplicitVarSizeWithFlags_Values[q17] != s_ExplicitVarSizeWithMarker_Values[q18], + allDiff([s_ExplicitVarSizeWithFlags_Values[q17] + s_ExplicitVarSizeWithMarker_Values[q18], + s_ExplicitVarSizeWithFlags_Values[q17] * s_ExplicitVarSizeWithMarker_Values[q18], + s_ExplicitVarSizeWithFlags_Values[q17] / s_ExplicitVarSizeWithMarker_Values[q18]; + int(1..3)]), + (s_ExplicitVarSizeWithFlags_Values[q17] - s_ExplicitVarSizeWithMarker_Values[q18]) % 2 = 0; + int(1..5)]) + -> + min([s_ExplicitVarSizeWithFlags_Values[q17] + s_ExplicitVarSizeWithMarker_Values[q18], + s_ExplicitVarSizeWithFlags_Values[q17] - s_ExplicitVarSizeWithMarker_Values[q18], + s_ExplicitVarSizeWithFlags_Values[q17] * s_ExplicitVarSizeWithMarker_Values[q18], + s_ExplicitVarSizeWithFlags_Values[q17] / s_ExplicitVarSizeWithMarker_Values[q18]; + int(1..4)]) + <= conjure_aux1 + | q17 : int(1..4), q18 : int(1..4)]), + sum([toInt(and([s_ExplicitVarSizeWithFlags_Flags[q17], q18 <= s_ExplicitVarSizeWithMarker_Marker, + s_ExplicitVarSizeWithFlags_Values[q17] != s_ExplicitVarSizeWithMarker_Values[q18], + allDiff([s_ExplicitVarSizeWithFlags_Values[q17] + s_ExplicitVarSizeWithMarker_Values[q18], + s_ExplicitVarSizeWithFlags_Values[q17] * s_ExplicitVarSizeWithMarker_Values[q18], + s_ExplicitVarSizeWithFlags_Values[q17] / s_ExplicitVarSizeWithMarker_Values[q18]; + int(1..3)]), + (s_ExplicitVarSizeWithFlags_Values[q17] - s_ExplicitVarSizeWithMarker_Values[q18]) % 2 = 0; + int(1..5)])) + | q17 : int(1..4), q18 : int(1..4)]) + > 0 + -> + or([and([s_ExplicitVarSizeWithFlags_Flags[q17], q18 <= s_ExplicitVarSizeWithMarker_Marker, + s_ExplicitVarSizeWithFlags_Values[q17] != s_ExplicitVarSizeWithMarker_Values[q18], + allDiff([s_ExplicitVarSizeWithFlags_Values[q17] + s_ExplicitVarSizeWithMarker_Values[q18], + s_ExplicitVarSizeWithFlags_Values[q17] * s_ExplicitVarSizeWithMarker_Values[q18], + s_ExplicitVarSizeWithFlags_Values[q17] / s_ExplicitVarSizeWithMarker_Values[q18]; + int(1..3)]), + (s_ExplicitVarSizeWithFlags_Values[q17] - s_ExplicitVarSizeWithMarker_Values[q18]) % 2 = 0; + int(1..5)]) + /\ + min([s_ExplicitVarSizeWithFlags_Values[q17] + s_ExplicitVarSizeWithMarker_Values[q18], + s_ExplicitVarSizeWithFlags_Values[q17] - s_ExplicitVarSizeWithMarker_Values[q18], + s_ExplicitVarSizeWithFlags_Values[q17] * s_ExplicitVarSizeWithMarker_Values[q18], + s_ExplicitVarSizeWithFlags_Values[q17] / s_ExplicitVarSizeWithMarker_Values[q18]; + int(1..4)]) + = conjure_aux1 + | q17 : int(1..4), q18 : int(1..4)]), + sum([toInt(and([s_ExplicitVarSizeWithFlags_Flags[q17], q18 <= s_ExplicitVarSizeWithMarker_Marker, + s_ExplicitVarSizeWithFlags_Values[q17] != s_ExplicitVarSizeWithMarker_Values[q18], + allDiff([s_ExplicitVarSizeWithFlags_Values[q17] + s_ExplicitVarSizeWithMarker_Values[q18], + s_ExplicitVarSizeWithFlags_Values[q17] * s_ExplicitVarSizeWithMarker_Values[q18], + s_ExplicitVarSizeWithFlags_Values[q17] / s_ExplicitVarSizeWithMarker_Values[q18]; + int(1..3)]), + (s_ExplicitVarSizeWithFlags_Values[q17] - s_ExplicitVarSizeWithMarker_Values[q18]) % 2 = 0; + int(1..5)])) + | q17 : int(1..4), q18 : int(1..4)]) + = 0 + -> conjure_aux1 = -16, + x = conjure_aux1, + sum([toInt(and([s_ExplicitVarSizeWithFlags_Flags[q17], q18 <= s_ExplicitVarSizeWithMarker_Marker, + s_ExplicitVarSizeWithFlags_Values[q17] != s_ExplicitVarSizeWithMarker_Values[q18], + allDiff([s_ExplicitVarSizeWithFlags_Values[q17] + s_ExplicitVarSizeWithMarker_Values[q18], + s_ExplicitVarSizeWithFlags_Values[q17] * s_ExplicitVarSizeWithMarker_Values[q18], + s_ExplicitVarSizeWithFlags_Values[q17] / s_ExplicitVarSizeWithMarker_Values[q18]; + int(1..3)]), + (s_ExplicitVarSizeWithFlags_Values[q17] - s_ExplicitVarSizeWithMarker_Values[q18]) % 2 = 0; + int(1..5)])) + | q17 : int(1..4), q18 : int(1..4)]) + > 0, + and([s_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> + s_ExplicitVarSizeWithFlags_Values[q1] < s_ExplicitVarSizeWithFlags_Values[q1 + 1] + | q1 : int(1..3)]), + and([s_ExplicitVarSizeWithFlags_Flags[q2] = false -> s_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..4)]), + and([s_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> s_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), + and([q6 + 1 <= s_ExplicitVarSizeWithMarker_Marker -> + s_ExplicitVarSizeWithMarker_Values[q6] < s_ExplicitVarSizeWithMarker_Values[q6 + 1] + | q6 : int(1..3)]), + and([q7 > s_ExplicitVarSizeWithMarker_Marker -> s_ExplicitVarSizeWithMarker_Values[q7] = 1 | q7 : int(1..4)]), + and([q10 <= s_ExplicitVarSizeWithMarker_Marker -> + or([s_ExplicitVarSizeWithFlags_Flags[q12] /\ + s_ExplicitVarSizeWithFlags_Values[q12] = s_ExplicitVarSizeWithMarker_Values[q10] + | q12 : int(1..4)]) + | q10 : int(1..4)]), + and([s_ExplicitVarSizeWithFlags_Flags[q14] -> + or([q16 <= s_ExplicitVarSizeWithMarker_Marker /\ + s_ExplicitVarSizeWithMarker_Values[q16] = s_ExplicitVarSizeWithFlags_Values[q14] + | q16 : int(1..4)]) + | q14 : int(1..4)]) + diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_1-solution000001.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_1-solution000001.solution new file mode 100644 index 0000000000..159a613983 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {2, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_1-solution000002.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_1-solution000002.solution new file mode 100644 index 0000000000..40f3fd5c8f --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_1-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {2, 3, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_1-solution000003.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_1-solution000003.solution new file mode 100644 index 0000000000..8b4ecbb66d --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_1-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 3} +letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_1-solution000004.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_1-solution000004.solution new file mode 100644 index 0000000000..560dd0f2f7 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_1-solution000004.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 3, 4} +letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_1-solution000005.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_1-solution000005.solution new file mode 100644 index 0000000000..6eeacc9727 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_1-solution000005.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 2, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_1-solution000006.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_1-solution000006.solution new file mode 100644 index 0000000000..5963aac565 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_1-solution000006.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 2, 3} +letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_1-solution000007.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_1-solution000007.solution new file mode 100644 index 0000000000..bd956f44e3 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_1-solution000007.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 2, 3, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_1.eprime b/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_1.eprime new file mode 100644 index 0000000000..f39e4e0ee6 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_1.eprime @@ -0,0 +1,86 @@ +language ESSENCE' 1.0 + +find s_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find s_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +find s_Occurrence: matrix indexed by [int(1..4)] of bool +letting let1 be -100 +find x: int(-100..100) +find conjure_aux1: int(-16..3) +branching on [s_Occurrence, s_ExplicitVarSizeWithFlags_Flags, s_ExplicitVarSizeWithFlags_Values, x] +such that + and([and([s_ExplicitVarSizeWithFlags_Flags[q12], s_ExplicitVarSizeWithFlags_Flags[q13], + s_ExplicitVarSizeWithFlags_Values[q12] != s_ExplicitVarSizeWithFlags_Values[q13], + allDiff([s_ExplicitVarSizeWithFlags_Values[q12] + s_ExplicitVarSizeWithFlags_Values[q13], + s_ExplicitVarSizeWithFlags_Values[q12] * s_ExplicitVarSizeWithFlags_Values[q13], + s_ExplicitVarSizeWithFlags_Values[q12] / s_ExplicitVarSizeWithFlags_Values[q13]; + int(1..3)]), + (s_ExplicitVarSizeWithFlags_Values[q12] - s_ExplicitVarSizeWithFlags_Values[q13]) % 2 = 0; + int(1..5)]) + -> + min([s_ExplicitVarSizeWithFlags_Values[q12] + s_ExplicitVarSizeWithFlags_Values[q13], + s_ExplicitVarSizeWithFlags_Values[q12] - s_ExplicitVarSizeWithFlags_Values[q13], + s_ExplicitVarSizeWithFlags_Values[q12] * s_ExplicitVarSizeWithFlags_Values[q13], + s_ExplicitVarSizeWithFlags_Values[q12] / s_ExplicitVarSizeWithFlags_Values[q13]; + int(1..4)]) + <= conjure_aux1 + | q12 : int(1..4), q13 : int(1..4)]), + sum([toInt(and([s_ExplicitVarSizeWithFlags_Flags[q12], s_ExplicitVarSizeWithFlags_Flags[q13], + s_ExplicitVarSizeWithFlags_Values[q12] != s_ExplicitVarSizeWithFlags_Values[q13], + allDiff([s_ExplicitVarSizeWithFlags_Values[q12] + s_ExplicitVarSizeWithFlags_Values[q13], + s_ExplicitVarSizeWithFlags_Values[q12] * s_ExplicitVarSizeWithFlags_Values[q13], + s_ExplicitVarSizeWithFlags_Values[q12] / s_ExplicitVarSizeWithFlags_Values[q13]; + int(1..3)]), + (s_ExplicitVarSizeWithFlags_Values[q12] - s_ExplicitVarSizeWithFlags_Values[q13]) % 2 = 0; + int(1..5)])) + | q12 : int(1..4), q13 : int(1..4)]) + > 0 + -> + or([and([s_ExplicitVarSizeWithFlags_Flags[q12], s_ExplicitVarSizeWithFlags_Flags[q13], + s_ExplicitVarSizeWithFlags_Values[q12] != s_ExplicitVarSizeWithFlags_Values[q13], + allDiff([s_ExplicitVarSizeWithFlags_Values[q12] + s_ExplicitVarSizeWithFlags_Values[q13], + s_ExplicitVarSizeWithFlags_Values[q12] * s_ExplicitVarSizeWithFlags_Values[q13], + s_ExplicitVarSizeWithFlags_Values[q12] / s_ExplicitVarSizeWithFlags_Values[q13]; + int(1..3)]), + (s_ExplicitVarSizeWithFlags_Values[q12] - s_ExplicitVarSizeWithFlags_Values[q13]) % 2 = 0; + int(1..5)]) + /\ + min([s_ExplicitVarSizeWithFlags_Values[q12] + s_ExplicitVarSizeWithFlags_Values[q13], + s_ExplicitVarSizeWithFlags_Values[q12] - s_ExplicitVarSizeWithFlags_Values[q13], + s_ExplicitVarSizeWithFlags_Values[q12] * s_ExplicitVarSizeWithFlags_Values[q13], + s_ExplicitVarSizeWithFlags_Values[q12] / s_ExplicitVarSizeWithFlags_Values[q13]; + int(1..4)]) + = conjure_aux1 + | q12 : int(1..4), q13 : int(1..4)]), + sum([toInt(and([s_ExplicitVarSizeWithFlags_Flags[q12], s_ExplicitVarSizeWithFlags_Flags[q13], + s_ExplicitVarSizeWithFlags_Values[q12] != s_ExplicitVarSizeWithFlags_Values[q13], + allDiff([s_ExplicitVarSizeWithFlags_Values[q12] + s_ExplicitVarSizeWithFlags_Values[q13], + s_ExplicitVarSizeWithFlags_Values[q12] * s_ExplicitVarSizeWithFlags_Values[q13], + s_ExplicitVarSizeWithFlags_Values[q12] / s_ExplicitVarSizeWithFlags_Values[q13]; + int(1..3)]), + (s_ExplicitVarSizeWithFlags_Values[q12] - s_ExplicitVarSizeWithFlags_Values[q13]) % 2 = 0; + int(1..5)])) + | q12 : int(1..4), q13 : int(1..4)]) + = 0 + -> conjure_aux1 = -16, + x = conjure_aux1, + sum([toInt(and([s_ExplicitVarSizeWithFlags_Flags[q12], s_ExplicitVarSizeWithFlags_Flags[q13], + s_ExplicitVarSizeWithFlags_Values[q12] != s_ExplicitVarSizeWithFlags_Values[q13], + allDiff([s_ExplicitVarSizeWithFlags_Values[q12] + s_ExplicitVarSizeWithFlags_Values[q13], + s_ExplicitVarSizeWithFlags_Values[q12] * s_ExplicitVarSizeWithFlags_Values[q13], + s_ExplicitVarSizeWithFlags_Values[q12] / s_ExplicitVarSizeWithFlags_Values[q13]; + int(1..3)]), + (s_ExplicitVarSizeWithFlags_Values[q12] - s_ExplicitVarSizeWithFlags_Values[q13]) % 2 = 0; + int(1..5)])) + | q12 : int(1..4), q13 : int(1..4)]) + > 0, + and([s_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> + s_ExplicitVarSizeWithFlags_Values[q1] < s_ExplicitVarSizeWithFlags_Values[q1 + 1] + | q1 : int(1..3)]), + and([s_ExplicitVarSizeWithFlags_Flags[q2] = false -> s_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..4)]), + and([s_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> s_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), + and([s_Occurrence[q7] -> + or([s_ExplicitVarSizeWithFlags_Flags[q9] /\ s_ExplicitVarSizeWithFlags_Values[q9] = q7 | q9 : int(1..4)]) + | q7 : int(1..4)]), + and([s_ExplicitVarSizeWithFlags_Flags[q11] -> s_Occurrence[s_ExplicitVarSizeWithFlags_Values[q11]] + | q11 : int(1..4)]) + diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_2-solution000001.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_2-solution000001.solution new file mode 100644 index 0000000000..bd956f44e3 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 2, 3, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_2-solution000002.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_2-solution000002.solution new file mode 100644 index 0000000000..5963aac565 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_2-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 2, 3} +letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_2-solution000003.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_2-solution000003.solution new file mode 100644 index 0000000000..6eeacc9727 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_2-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 2, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_2-solution000004.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_2-solution000004.solution new file mode 100644 index 0000000000..560dd0f2f7 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_2-solution000004.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 3, 4} +letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_2-solution000005.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_2-solution000005.solution new file mode 100644 index 0000000000..8b4ecbb66d --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_2-solution000005.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 3} +letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_2-solution000006.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_2-solution000006.solution new file mode 100644 index 0000000000..40f3fd5c8f --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_2-solution000006.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {2, 3, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_2-solution000007.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_2-solution000007.solution new file mode 100644 index 0000000000..159a613983 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_2-solution000007.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {2, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_2.eprime b/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_2.eprime new file mode 100644 index 0000000000..7af3076aa8 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_2.eprime @@ -0,0 +1,94 @@ +language ESSENCE' 1.0 + +find s_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find s_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +find s_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +letting let1 be -100 +find x: int(-100..100) +find conjure_aux1: int(-16..3) +branching on [s_ExplicitVarSizeWithDummy, s_ExplicitVarSizeWithFlags_Flags, s_ExplicitVarSizeWithFlags_Values, x] +such that + and([and([s_ExplicitVarSizeWithFlags_Flags[q18], s_ExplicitVarSizeWithFlags_Flags[q19], + s_ExplicitVarSizeWithFlags_Values[q18] != s_ExplicitVarSizeWithFlags_Values[q19], + allDiff([s_ExplicitVarSizeWithFlags_Values[q18] + s_ExplicitVarSizeWithFlags_Values[q19], + s_ExplicitVarSizeWithFlags_Values[q18] * s_ExplicitVarSizeWithFlags_Values[q19], + s_ExplicitVarSizeWithFlags_Values[q18] / s_ExplicitVarSizeWithFlags_Values[q19]; + int(1..3)]), + (s_ExplicitVarSizeWithFlags_Values[q18] - s_ExplicitVarSizeWithFlags_Values[q19]) % 2 = 0; + int(1..5)]) + -> + min([s_ExplicitVarSizeWithFlags_Values[q18] + s_ExplicitVarSizeWithFlags_Values[q19], + s_ExplicitVarSizeWithFlags_Values[q18] - s_ExplicitVarSizeWithFlags_Values[q19], + s_ExplicitVarSizeWithFlags_Values[q18] * s_ExplicitVarSizeWithFlags_Values[q19], + s_ExplicitVarSizeWithFlags_Values[q18] / s_ExplicitVarSizeWithFlags_Values[q19]; + int(1..4)]) + <= conjure_aux1 + | q18 : int(1..4), q19 : int(1..4)]), + sum([toInt(and([s_ExplicitVarSizeWithFlags_Flags[q18], s_ExplicitVarSizeWithFlags_Flags[q19], + s_ExplicitVarSizeWithFlags_Values[q18] != s_ExplicitVarSizeWithFlags_Values[q19], + allDiff([s_ExplicitVarSizeWithFlags_Values[q18] + s_ExplicitVarSizeWithFlags_Values[q19], + s_ExplicitVarSizeWithFlags_Values[q18] * s_ExplicitVarSizeWithFlags_Values[q19], + s_ExplicitVarSizeWithFlags_Values[q18] / s_ExplicitVarSizeWithFlags_Values[q19]; + int(1..3)]), + (s_ExplicitVarSizeWithFlags_Values[q18] - s_ExplicitVarSizeWithFlags_Values[q19]) % 2 = 0; + int(1..5)])) + | q18 : int(1..4), q19 : int(1..4)]) + > 0 + -> + or([and([s_ExplicitVarSizeWithFlags_Flags[q18], s_ExplicitVarSizeWithFlags_Flags[q19], + s_ExplicitVarSizeWithFlags_Values[q18] != s_ExplicitVarSizeWithFlags_Values[q19], + allDiff([s_ExplicitVarSizeWithFlags_Values[q18] + s_ExplicitVarSizeWithFlags_Values[q19], + s_ExplicitVarSizeWithFlags_Values[q18] * s_ExplicitVarSizeWithFlags_Values[q19], + s_ExplicitVarSizeWithFlags_Values[q18] / s_ExplicitVarSizeWithFlags_Values[q19]; + int(1..3)]), + (s_ExplicitVarSizeWithFlags_Values[q18] - s_ExplicitVarSizeWithFlags_Values[q19]) % 2 = 0; + int(1..5)]) + /\ + min([s_ExplicitVarSizeWithFlags_Values[q18] + s_ExplicitVarSizeWithFlags_Values[q19], + s_ExplicitVarSizeWithFlags_Values[q18] - s_ExplicitVarSizeWithFlags_Values[q19], + s_ExplicitVarSizeWithFlags_Values[q18] * s_ExplicitVarSizeWithFlags_Values[q19], + s_ExplicitVarSizeWithFlags_Values[q18] / s_ExplicitVarSizeWithFlags_Values[q19]; + int(1..4)]) + = conjure_aux1 + | q18 : int(1..4), q19 : int(1..4)]), + sum([toInt(and([s_ExplicitVarSizeWithFlags_Flags[q18], s_ExplicitVarSizeWithFlags_Flags[q19], + s_ExplicitVarSizeWithFlags_Values[q18] != s_ExplicitVarSizeWithFlags_Values[q19], + allDiff([s_ExplicitVarSizeWithFlags_Values[q18] + s_ExplicitVarSizeWithFlags_Values[q19], + s_ExplicitVarSizeWithFlags_Values[q18] * s_ExplicitVarSizeWithFlags_Values[q19], + s_ExplicitVarSizeWithFlags_Values[q18] / s_ExplicitVarSizeWithFlags_Values[q19]; + int(1..3)]), + (s_ExplicitVarSizeWithFlags_Values[q18] - s_ExplicitVarSizeWithFlags_Values[q19]) % 2 = 0; + int(1..5)])) + | q18 : int(1..4), q19 : int(1..4)]) + = 0 + -> conjure_aux1 = -16, + x = conjure_aux1, + sum([toInt(and([s_ExplicitVarSizeWithFlags_Flags[q18], s_ExplicitVarSizeWithFlags_Flags[q19], + s_ExplicitVarSizeWithFlags_Values[q18] != s_ExplicitVarSizeWithFlags_Values[q19], + allDiff([s_ExplicitVarSizeWithFlags_Values[q18] + s_ExplicitVarSizeWithFlags_Values[q19], + s_ExplicitVarSizeWithFlags_Values[q18] * s_ExplicitVarSizeWithFlags_Values[q19], + s_ExplicitVarSizeWithFlags_Values[q18] / s_ExplicitVarSizeWithFlags_Values[q19]; + int(1..3)]), + (s_ExplicitVarSizeWithFlags_Values[q18] - s_ExplicitVarSizeWithFlags_Values[q19]) % 2 = 0; + int(1..5)])) + | q18 : int(1..4), q19 : int(1..4)]) + > 0, + and([s_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> + s_ExplicitVarSizeWithFlags_Values[q1] < s_ExplicitVarSizeWithFlags_Values[q1 + 1] + | q1 : int(1..3)]), + and([s_ExplicitVarSizeWithFlags_Flags[q2] = false -> s_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..4)]), + and([s_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> s_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), + and([s_ExplicitVarSizeWithDummy[q6] < s_ExplicitVarSizeWithDummy[q6 + 1] \/ s_ExplicitVarSizeWithDummy[q6] = 5 + | q6 : int(1..3)]), + and([s_ExplicitVarSizeWithDummy[q7] = 5 -> s_ExplicitVarSizeWithDummy[q7 + 1] = 5 | q7 : int(1..3)]), + and([s_ExplicitVarSizeWithDummy[q11] != 5 -> + or([s_ExplicitVarSizeWithFlags_Flags[q13] /\ + s_ExplicitVarSizeWithFlags_Values[q13] = s_ExplicitVarSizeWithDummy[q11] + | q13 : int(1..4)]) + | q11 : int(1..4)]), + and([s_ExplicitVarSizeWithFlags_Flags[q15] -> + or([s_ExplicitVarSizeWithDummy[q17] != 5 /\ + s_ExplicitVarSizeWithDummy[q17] = s_ExplicitVarSizeWithFlags_Values[q15] + | q17 : int(1..4)]) + | q15 : int(1..4)]) + diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_3-solution000001.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_3-solution000001.solution new file mode 100644 index 0000000000..8b4ecbb66d --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_3-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 3} +letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_3-solution000002.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_3-solution000002.solution new file mode 100644 index 0000000000..159a613983 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_3-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {2, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_3-solution000003.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_3-solution000003.solution new file mode 100644 index 0000000000..5963aac565 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_3-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 2, 3} +letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_3-solution000004.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_3-solution000004.solution new file mode 100644 index 0000000000..6eeacc9727 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_3-solution000004.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 2, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_3-solution000005.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_3-solution000005.solution new file mode 100644 index 0000000000..560dd0f2f7 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_3-solution000005.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 3, 4} +letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_3-solution000006.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_3-solution000006.solution new file mode 100644 index 0000000000..40f3fd5c8f --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_3-solution000006.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {2, 3, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_3-solution000007.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_3-solution000007.solution new file mode 100644 index 0000000000..bd956f44e3 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_3-solution000007.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 2, 3, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_3.eprime b/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_3.eprime new file mode 100644 index 0000000000..5854a1dbb6 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_3.eprime @@ -0,0 +1,98 @@ +language ESSENCE' 1.0 + +find s_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find s_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +find s_ExplicitVarSizeWithMarker_Marker: int(0..4) +find s_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +letting let1 be -100 +find x: int(-100..100) +find conjure_aux1: int(-16..3) +branching on + [s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithMarker_Values, s_ExplicitVarSizeWithFlags_Flags, + s_ExplicitVarSizeWithFlags_Values, x] +such that + and([and([s_ExplicitVarSizeWithFlags_Flags[q17], s_ExplicitVarSizeWithFlags_Flags[q18], + s_ExplicitVarSizeWithFlags_Values[q17] != s_ExplicitVarSizeWithFlags_Values[q18], + allDiff([s_ExplicitVarSizeWithFlags_Values[q17] + s_ExplicitVarSizeWithFlags_Values[q18], + s_ExplicitVarSizeWithFlags_Values[q17] * s_ExplicitVarSizeWithFlags_Values[q18], + s_ExplicitVarSizeWithFlags_Values[q17] / s_ExplicitVarSizeWithFlags_Values[q18]; + int(1..3)]), + (s_ExplicitVarSizeWithFlags_Values[q17] - s_ExplicitVarSizeWithFlags_Values[q18]) % 2 = 0; + int(1..5)]) + -> + min([s_ExplicitVarSizeWithFlags_Values[q17] + s_ExplicitVarSizeWithFlags_Values[q18], + s_ExplicitVarSizeWithFlags_Values[q17] - s_ExplicitVarSizeWithFlags_Values[q18], + s_ExplicitVarSizeWithFlags_Values[q17] * s_ExplicitVarSizeWithFlags_Values[q18], + s_ExplicitVarSizeWithFlags_Values[q17] / s_ExplicitVarSizeWithFlags_Values[q18]; + int(1..4)]) + <= conjure_aux1 + | q17 : int(1..4), q18 : int(1..4)]), + sum([toInt(and([s_ExplicitVarSizeWithFlags_Flags[q17], s_ExplicitVarSizeWithFlags_Flags[q18], + s_ExplicitVarSizeWithFlags_Values[q17] != s_ExplicitVarSizeWithFlags_Values[q18], + allDiff([s_ExplicitVarSizeWithFlags_Values[q17] + s_ExplicitVarSizeWithFlags_Values[q18], + s_ExplicitVarSizeWithFlags_Values[q17] * s_ExplicitVarSizeWithFlags_Values[q18], + s_ExplicitVarSizeWithFlags_Values[q17] / s_ExplicitVarSizeWithFlags_Values[q18]; + int(1..3)]), + (s_ExplicitVarSizeWithFlags_Values[q17] - s_ExplicitVarSizeWithFlags_Values[q18]) % 2 = 0; + int(1..5)])) + | q17 : int(1..4), q18 : int(1..4)]) + > 0 + -> + or([and([s_ExplicitVarSizeWithFlags_Flags[q17], s_ExplicitVarSizeWithFlags_Flags[q18], + s_ExplicitVarSizeWithFlags_Values[q17] != s_ExplicitVarSizeWithFlags_Values[q18], + allDiff([s_ExplicitVarSizeWithFlags_Values[q17] + s_ExplicitVarSizeWithFlags_Values[q18], + s_ExplicitVarSizeWithFlags_Values[q17] * s_ExplicitVarSizeWithFlags_Values[q18], + s_ExplicitVarSizeWithFlags_Values[q17] / s_ExplicitVarSizeWithFlags_Values[q18]; + int(1..3)]), + (s_ExplicitVarSizeWithFlags_Values[q17] - s_ExplicitVarSizeWithFlags_Values[q18]) % 2 = 0; + int(1..5)]) + /\ + min([s_ExplicitVarSizeWithFlags_Values[q17] + s_ExplicitVarSizeWithFlags_Values[q18], + s_ExplicitVarSizeWithFlags_Values[q17] - s_ExplicitVarSizeWithFlags_Values[q18], + s_ExplicitVarSizeWithFlags_Values[q17] * s_ExplicitVarSizeWithFlags_Values[q18], + s_ExplicitVarSizeWithFlags_Values[q17] / s_ExplicitVarSizeWithFlags_Values[q18]; + int(1..4)]) + = conjure_aux1 + | q17 : int(1..4), q18 : int(1..4)]), + sum([toInt(and([s_ExplicitVarSizeWithFlags_Flags[q17], s_ExplicitVarSizeWithFlags_Flags[q18], + s_ExplicitVarSizeWithFlags_Values[q17] != s_ExplicitVarSizeWithFlags_Values[q18], + allDiff([s_ExplicitVarSizeWithFlags_Values[q17] + s_ExplicitVarSizeWithFlags_Values[q18], + s_ExplicitVarSizeWithFlags_Values[q17] * s_ExplicitVarSizeWithFlags_Values[q18], + s_ExplicitVarSizeWithFlags_Values[q17] / s_ExplicitVarSizeWithFlags_Values[q18]; + int(1..3)]), + (s_ExplicitVarSizeWithFlags_Values[q17] - s_ExplicitVarSizeWithFlags_Values[q18]) % 2 = 0; + int(1..5)])) + | q17 : int(1..4), q18 : int(1..4)]) + = 0 + -> conjure_aux1 = -16, + x = conjure_aux1, + sum([toInt(and([s_ExplicitVarSizeWithFlags_Flags[q17], s_ExplicitVarSizeWithFlags_Flags[q18], + s_ExplicitVarSizeWithFlags_Values[q17] != s_ExplicitVarSizeWithFlags_Values[q18], + allDiff([s_ExplicitVarSizeWithFlags_Values[q17] + s_ExplicitVarSizeWithFlags_Values[q18], + s_ExplicitVarSizeWithFlags_Values[q17] * s_ExplicitVarSizeWithFlags_Values[q18], + s_ExplicitVarSizeWithFlags_Values[q17] / s_ExplicitVarSizeWithFlags_Values[q18]; + int(1..3)]), + (s_ExplicitVarSizeWithFlags_Values[q17] - s_ExplicitVarSizeWithFlags_Values[q18]) % 2 = 0; + int(1..5)])) + | q17 : int(1..4), q18 : int(1..4)]) + > 0, + and([s_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> + s_ExplicitVarSizeWithFlags_Values[q1] < s_ExplicitVarSizeWithFlags_Values[q1 + 1] + | q1 : int(1..3)]), + and([s_ExplicitVarSizeWithFlags_Flags[q2] = false -> s_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..4)]), + and([s_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> s_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), + and([q6 + 1 <= s_ExplicitVarSizeWithMarker_Marker -> + s_ExplicitVarSizeWithMarker_Values[q6] < s_ExplicitVarSizeWithMarker_Values[q6 + 1] + | q6 : int(1..3)]), + and([q7 > s_ExplicitVarSizeWithMarker_Marker -> s_ExplicitVarSizeWithMarker_Values[q7] = 1 | q7 : int(1..4)]), + and([q10 <= s_ExplicitVarSizeWithMarker_Marker -> + or([s_ExplicitVarSizeWithFlags_Flags[q12] /\ + s_ExplicitVarSizeWithFlags_Values[q12] = s_ExplicitVarSizeWithMarker_Values[q10] + | q12 : int(1..4)]) + | q10 : int(1..4)]), + and([s_ExplicitVarSizeWithFlags_Flags[q14] -> + or([q16 <= s_ExplicitVarSizeWithMarker_Marker /\ + s_ExplicitVarSizeWithMarker_Values[q16] = s_ExplicitVarSizeWithFlags_Values[q14] + | q16 : int(1..4)]) + | q14 : int(1..4)]) + diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_4-solution000001.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_4-solution000001.solution new file mode 100644 index 0000000000..8b4ecbb66d --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_4-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 3} +letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_4-solution000002.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_4-solution000002.solution new file mode 100644 index 0000000000..159a613983 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_4-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {2, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_4-solution000003.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_4-solution000003.solution new file mode 100644 index 0000000000..5963aac565 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_4-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 2, 3} +letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_4-solution000004.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_4-solution000004.solution new file mode 100644 index 0000000000..6eeacc9727 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_4-solution000004.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 2, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_4-solution000005.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_4-solution000005.solution new file mode 100644 index 0000000000..560dd0f2f7 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_4-solution000005.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 3, 4} +letting x be -2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_4-solution000006.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_4-solution000006.solution new file mode 100644 index 0000000000..40f3fd5c8f --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_4-solution000006.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {2, 3, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_4-solution000007.solution b/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_4-solution000007.solution new file mode 100644 index 0000000000..bd956f44e3 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_4-solution000007.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting s be {1, 2, 3, 4} +letting x be 2 diff --git a/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_4.eprime b/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_4.eprime new file mode 100644 index 0000000000..bf58b8c524 --- /dev/null +++ b/tests/exhaustive/basic/comprehension_letting/expected/model_4_4_4.eprime @@ -0,0 +1,80 @@ +language ESSENCE' 1.0 + +find s_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find s_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +letting let1 be -100 +find x: int(-100..100) +find conjure_aux1: int(-16..3) +branching on [s_ExplicitVarSizeWithFlags_Flags, s_ExplicitVarSizeWithFlags_Values, x] +such that + and([and([s_ExplicitVarSizeWithFlags_Flags[q6], s_ExplicitVarSizeWithFlags_Flags[q7], + s_ExplicitVarSizeWithFlags_Values[q6] != s_ExplicitVarSizeWithFlags_Values[q7], + allDiff([s_ExplicitVarSizeWithFlags_Values[q6] + s_ExplicitVarSizeWithFlags_Values[q7], + s_ExplicitVarSizeWithFlags_Values[q6] * s_ExplicitVarSizeWithFlags_Values[q7], + s_ExplicitVarSizeWithFlags_Values[q6] / s_ExplicitVarSizeWithFlags_Values[q7]; + int(1..3)]), + (s_ExplicitVarSizeWithFlags_Values[q6] - s_ExplicitVarSizeWithFlags_Values[q7]) % 2 = 0; + int(1..5)]) + -> + min([s_ExplicitVarSizeWithFlags_Values[q6] + s_ExplicitVarSizeWithFlags_Values[q7], + s_ExplicitVarSizeWithFlags_Values[q6] - s_ExplicitVarSizeWithFlags_Values[q7], + s_ExplicitVarSizeWithFlags_Values[q6] * s_ExplicitVarSizeWithFlags_Values[q7], + s_ExplicitVarSizeWithFlags_Values[q6] / s_ExplicitVarSizeWithFlags_Values[q7]; + int(1..4)]) + <= conjure_aux1 + | q6 : int(1..4), q7 : int(1..4)]), + sum([toInt(and([s_ExplicitVarSizeWithFlags_Flags[q6], s_ExplicitVarSizeWithFlags_Flags[q7], + s_ExplicitVarSizeWithFlags_Values[q6] != s_ExplicitVarSizeWithFlags_Values[q7], + allDiff([s_ExplicitVarSizeWithFlags_Values[q6] + s_ExplicitVarSizeWithFlags_Values[q7], + s_ExplicitVarSizeWithFlags_Values[q6] * s_ExplicitVarSizeWithFlags_Values[q7], + s_ExplicitVarSizeWithFlags_Values[q6] / s_ExplicitVarSizeWithFlags_Values[q7]; + int(1..3)]), + (s_ExplicitVarSizeWithFlags_Values[q6] - s_ExplicitVarSizeWithFlags_Values[q7]) % 2 = 0; + int(1..5)])) + | q6 : int(1..4), q7 : int(1..4)]) + > 0 + -> + or([and([s_ExplicitVarSizeWithFlags_Flags[q6], s_ExplicitVarSizeWithFlags_Flags[q7], + s_ExplicitVarSizeWithFlags_Values[q6] != s_ExplicitVarSizeWithFlags_Values[q7], + allDiff([s_ExplicitVarSizeWithFlags_Values[q6] + s_ExplicitVarSizeWithFlags_Values[q7], + s_ExplicitVarSizeWithFlags_Values[q6] * s_ExplicitVarSizeWithFlags_Values[q7], + s_ExplicitVarSizeWithFlags_Values[q6] / s_ExplicitVarSizeWithFlags_Values[q7]; + int(1..3)]), + (s_ExplicitVarSizeWithFlags_Values[q6] - s_ExplicitVarSizeWithFlags_Values[q7]) % 2 = 0; + int(1..5)]) + /\ + min([s_ExplicitVarSizeWithFlags_Values[q6] + s_ExplicitVarSizeWithFlags_Values[q7], + s_ExplicitVarSizeWithFlags_Values[q6] - s_ExplicitVarSizeWithFlags_Values[q7], + s_ExplicitVarSizeWithFlags_Values[q6] * s_ExplicitVarSizeWithFlags_Values[q7], + s_ExplicitVarSizeWithFlags_Values[q6] / s_ExplicitVarSizeWithFlags_Values[q7]; + int(1..4)]) + = conjure_aux1 + | q6 : int(1..4), q7 : int(1..4)]), + sum([toInt(and([s_ExplicitVarSizeWithFlags_Flags[q6], s_ExplicitVarSizeWithFlags_Flags[q7], + s_ExplicitVarSizeWithFlags_Values[q6] != s_ExplicitVarSizeWithFlags_Values[q7], + allDiff([s_ExplicitVarSizeWithFlags_Values[q6] + s_ExplicitVarSizeWithFlags_Values[q7], + s_ExplicitVarSizeWithFlags_Values[q6] * s_ExplicitVarSizeWithFlags_Values[q7], + s_ExplicitVarSizeWithFlags_Values[q6] / s_ExplicitVarSizeWithFlags_Values[q7]; + int(1..3)]), + (s_ExplicitVarSizeWithFlags_Values[q6] - s_ExplicitVarSizeWithFlags_Values[q7]) % 2 = 0; + int(1..5)])) + | q6 : int(1..4), q7 : int(1..4)]) + = 0 + -> conjure_aux1 = -16, + x = conjure_aux1, + sum([toInt(and([s_ExplicitVarSizeWithFlags_Flags[q6], s_ExplicitVarSizeWithFlags_Flags[q7], + s_ExplicitVarSizeWithFlags_Values[q6] != s_ExplicitVarSizeWithFlags_Values[q7], + allDiff([s_ExplicitVarSizeWithFlags_Values[q6] + s_ExplicitVarSizeWithFlags_Values[q7], + s_ExplicitVarSizeWithFlags_Values[q6] * s_ExplicitVarSizeWithFlags_Values[q7], + s_ExplicitVarSizeWithFlags_Values[q6] / s_ExplicitVarSizeWithFlags_Values[q7]; + int(1..3)]), + (s_ExplicitVarSizeWithFlags_Values[q6] - s_ExplicitVarSizeWithFlags_Values[q7]) % 2 = 0; + int(1..5)])) + | q6 : int(1..4), q7 : int(1..4)]) + > 0, + and([s_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> + s_ExplicitVarSizeWithFlags_Values[q1] < s_ExplicitVarSizeWithFlags_Values[q1 + 1] + | q1 : int(1..3)]), + and([s_ExplicitVarSizeWithFlags_Flags[q2] = false -> s_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..4)]), + and([s_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> s_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]) + diff --git a/tests/exhaustive/basic/cut_01_off/expected/model_2.eprime b/tests/exhaustive/basic/cut_01_off/expected/model_2.eprime index 37164ea2c4..3d1fd14c52 100644 --- a/tests/exhaustive/basic/cut_01_off/expected/model_2.eprime +++ b/tests/exhaustive/basic/cut_01_off/expected/model_2.eprime @@ -3,8 +3,7 @@ language ESSENCE' 1.0 find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..3)] of int(1..4) branching on [x_ExplicitVarSizeWithDummy] such that - and([[x_ExplicitVarSizeWithDummy[q1]; int(1)] x_ExplicitVarSizeWithDummy[q2 + 1] = 4 | q2 : int(1..2)]) diff --git a/tests/exhaustive/basic/cut_01_off/expected/model_3.eprime b/tests/exhaustive/basic/cut_01_off/expected/model_3.eprime index 2450f96648..d729b76811 100644 --- a/tests/exhaustive/basic/cut_01_off/expected/model_3.eprime +++ b/tests/exhaustive/basic/cut_01_off/expected/model_3.eprime @@ -5,7 +5,7 @@ find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3)] of int(1. branching on [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] such that and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - [x_ExplicitVarSizeWithMarker_Values[q1]; int(1)] x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..3)]) diff --git a/tests/exhaustive/basic/cut_01_off/expected/model_4.eprime b/tests/exhaustive/basic/cut_01_off/expected/model_4.eprime index d0b0cedea3..1f10b1c798 100644 --- a/tests/exhaustive/basic/cut_01_off/expected/model_4.eprime +++ b/tests/exhaustive/basic/cut_01_off/expected/model_4.eprime @@ -5,7 +5,7 @@ find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3)] of int(1.. branching on [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] such that and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - [x_ExplicitVarSizeWithFlags_Values[q1]; int(1)] x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..3)]), and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..2)]) diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_1_1-solution000001.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_1_1-solution000001.solution new file mode 100644 index 0000000000..f90e0ba18c --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_1_1_1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_1_1-solution000002.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_1_1-solution000002.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_1_1_1-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_1_1-solution000003.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_1_1-solution000003.solution new file mode 100644 index 0000000000..de5cc861ad --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_1_1_1-solution000003.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_1_1-solution000004.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_1_1-solution000004.solution new file mode 100644 index 0000000000..a28b6d6203 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_1_1_1-solution000004.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_1_1-solution000005.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_1_1-solution000005.solution new file mode 100644 index 0000000000..1a734343d9 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_1_1_1-solution000005.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_1_1-solution000006.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_1_1-solution000006.solution new file mode 100644 index 0000000000..86a85825b3 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_1_1_1-solution000006.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_1_1-solution000007.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_1_1-solution000007.solution new file mode 100644 index 0000000000..76bc8cdc32 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_1_1_1-solution000007.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_1_1-solution000008.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_1_1-solution000008.solution new file mode 100644 index 0000000000..8dddb3b359 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_1_1_1-solution000008.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_1_1.eprime b/tests/exhaustive/basic/cut_01_on/expected/model_1_1_1.eprime new file mode 100644 index 0000000000..bc8f37139a --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_1_1_1.eprime @@ -0,0 +1,10 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(1..3)] of bool +find cut1: bool +find cut2: bool +branching on [cut1, cut2, x_Occurrence] +such that + !cut1 <-> x_Occurrence[1] /\ x_Occurrence[2], + !cut2 <-> x_Occurrence[1] + diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_1_2-solution000001.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_1_2-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_1_1_2-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_1_2-solution000002.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_1_2-solution000002.solution new file mode 100644 index 0000000000..f90e0ba18c --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_1_1_2-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_1_2-solution000003.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_1_2-solution000003.solution new file mode 100644 index 0000000000..a28b6d6203 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_1_1_2-solution000003.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_1_2-solution000004.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_1_2-solution000004.solution new file mode 100644 index 0000000000..de5cc861ad --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_1_1_2-solution000004.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_1_2-solution000005.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_1_2-solution000005.solution new file mode 100644 index 0000000000..8dddb3b359 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_1_1_2-solution000005.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_1_2-solution000006.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_1_2-solution000006.solution new file mode 100644 index 0000000000..76bc8cdc32 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_1_1_2-solution000006.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_1_2-solution000007.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_1_2-solution000007.solution new file mode 100644 index 0000000000..86a85825b3 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_1_1_2-solution000007.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_1_2-solution000008.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_1_2-solution000008.solution new file mode 100644 index 0000000000..1a734343d9 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_1_1_2-solution000008.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_2_1.eprime.orig b/tests/exhaustive/basic/cut_01_on/expected/model_1_1_2.eprime similarity index 88% rename from tests/exhaustive/basic/cut_01_on/expected/model_1_2_1.eprime.orig rename to tests/exhaustive/basic/cut_01_on/expected/model_1_1_2.eprime index bdba13c665..8a8719673a 100644 --- a/tests/exhaustive/basic/cut_01_on/expected/model_1_2_1.eprime.orig +++ b/tests/exhaustive/basic/cut_01_on/expected/model_1_1_2.eprime @@ -7,7 +7,7 @@ find cut2: bool branching on [cut1, cut2, x_ExplicitVarSizeWithDummy, x_Occurrence] such that !cut1 <-> x_Occurrence[1] /\ x_Occurrence[2], - !cut2 <-> or([x_ExplicitVarSizeWithDummy[q13] != 4 /\ x_ExplicitVarSizeWithDummy[q13] = 1 | q13 : int(1..3)]), + !cut2 <-> x_Occurrence[1], and([x_ExplicitVarSizeWithDummy[q2] < x_ExplicitVarSizeWithDummy[q2 + 1] \/ x_ExplicitVarSizeWithDummy[q2] = 4 | q2 : int(1..2)]), and([x_ExplicitVarSizeWithDummy[q3] = 4 -> x_ExplicitVarSizeWithDummy[q3 + 1] = 4 | q3 : int(1..2)]), diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_1_3-solution000001.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_1_3-solution000001.solution new file mode 100644 index 0000000000..f90e0ba18c --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_1_1_3-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_1_3-solution000002.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_1_3-solution000002.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_1_1_3-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_1_3-solution000003.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_1_3-solution000003.solution new file mode 100644 index 0000000000..de5cc861ad --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_1_1_3-solution000003.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_1_3-solution000004.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_1_3-solution000004.solution new file mode 100644 index 0000000000..a28b6d6203 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_1_1_3-solution000004.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_1_3-solution000005.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_1_3-solution000005.solution new file mode 100644 index 0000000000..1a734343d9 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_1_1_3-solution000005.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_1_3-solution000006.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_1_3-solution000006.solution new file mode 100644 index 0000000000..76bc8cdc32 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_1_1_3-solution000006.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_1_3-solution000007.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_1_3-solution000007.solution new file mode 100644 index 0000000000..86a85825b3 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_1_1_3-solution000007.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_1_3-solution000008.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_1_3-solution000008.solution new file mode 100644 index 0000000000..8dddb3b359 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_1_1_3-solution000008.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_3_1.eprime.orig b/tests/exhaustive/basic/cut_01_on/expected/model_1_1_3.eprime similarity index 88% rename from tests/exhaustive/basic/cut_01_on/expected/model_1_3_1.eprime.orig rename to tests/exhaustive/basic/cut_01_on/expected/model_1_1_3.eprime index e0ba9b28e5..5406286e79 100644 --- a/tests/exhaustive/basic/cut_01_on/expected/model_1_3_1.eprime.orig +++ b/tests/exhaustive/basic/cut_01_on/expected/model_1_1_3.eprime @@ -8,8 +8,7 @@ find cut2: bool branching on [cut1, cut2, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_Occurrence] such that !cut1 <-> x_Occurrence[1] /\ x_Occurrence[2], - !cut2 <-> - or([q12 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q12] = 1 | q12 : int(1..3)]), + !cut2 <-> x_Occurrence[1], and([q2 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] < x_ExplicitVarSizeWithMarker_Values[q2 + 1] | q2 : int(1..2)]), diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_1_4-solution000001.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_1_4-solution000001.solution new file mode 100644 index 0000000000..f90e0ba18c --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_1_1_4-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_1_4-solution000002.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_1_4-solution000002.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_1_1_4-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_1_4-solution000003.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_1_4-solution000003.solution new file mode 100644 index 0000000000..de5cc861ad --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_1_1_4-solution000003.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_1_4-solution000004.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_1_4-solution000004.solution new file mode 100644 index 0000000000..a28b6d6203 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_1_1_4-solution000004.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_1_4-solution000005.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_1_4-solution000005.solution new file mode 100644 index 0000000000..1a734343d9 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_1_1_4-solution000005.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_1_4-solution000006.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_1_4-solution000006.solution new file mode 100644 index 0000000000..76bc8cdc32 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_1_1_4-solution000006.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_1_4-solution000007.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_1_4-solution000007.solution new file mode 100644 index 0000000000..86a85825b3 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_1_1_4-solution000007.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_1_4-solution000008.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_1_4-solution000008.solution new file mode 100644 index 0000000000..8dddb3b359 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_1_1_4-solution000008.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_4_1.eprime.orig b/tests/exhaustive/basic/cut_01_on/expected/model_1_1_4.eprime similarity index 90% rename from tests/exhaustive/basic/cut_01_on/expected/model_1_4_1.eprime.orig rename to tests/exhaustive/basic/cut_01_on/expected/model_1_1_4.eprime index 59c07401b5..97272a9274 100644 --- a/tests/exhaustive/basic/cut_01_on/expected/model_1_4_1.eprime.orig +++ b/tests/exhaustive/basic/cut_01_on/expected/model_1_1_4.eprime @@ -8,8 +8,7 @@ find cut2: bool branching on [cut1, cut2, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_Occurrence] such that !cut1 <-> x_Occurrence[1] /\ x_Occurrence[2], - !cut2 <-> - or([x_ExplicitVarSizeWithFlags_Flags[q14] /\ x_ExplicitVarSizeWithFlags_Values[q14] = 1 | q14 : int(1..3)]), + !cut2 <-> x_Occurrence[1], and([x_ExplicitVarSizeWithFlags_Flags[q2 + 1] -> x_ExplicitVarSizeWithFlags_Values[q2] < x_ExplicitVarSizeWithFlags_Values[q2 + 1] | q2 : int(1..2)]), diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_2_1-solution000001.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_2_1-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_1_2_1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_2_1-solution000002.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_2_1-solution000002.solution new file mode 100644 index 0000000000..f90e0ba18c --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_1_2_1-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_2_1-solution000003.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_2_1-solution000003.solution new file mode 100644 index 0000000000..a28b6d6203 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_1_2_1-solution000003.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_2_1-solution000004.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_2_1-solution000004.solution new file mode 100644 index 0000000000..de5cc861ad --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_1_2_1-solution000004.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_2_1-solution000005.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_2_1-solution000005.solution new file mode 100644 index 0000000000..8dddb3b359 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_1_2_1-solution000005.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_2_1-solution000006.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_2_1-solution000006.solution new file mode 100644 index 0000000000..76bc8cdc32 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_1_2_1-solution000006.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_2_1-solution000007.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_2_1-solution000007.solution new file mode 100644 index 0000000000..86a85825b3 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_1_2_1-solution000007.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_2_1-solution000008.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_2_1-solution000008.solution new file mode 100644 index 0000000000..1a734343d9 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_1_2_1-solution000008.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_2_3-solution000001.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_2_3-solution000001.solution new file mode 100644 index 0000000000..f90e0ba18c --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_1_2_3-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_2_3-solution000002.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_2_3-solution000002.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_1_2_3-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_2_3-solution000003.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_2_3-solution000003.solution new file mode 100644 index 0000000000..de5cc861ad --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_1_2_3-solution000003.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_2_3-solution000004.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_2_3-solution000004.solution new file mode 100644 index 0000000000..a28b6d6203 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_1_2_3-solution000004.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_2_3-solution000005.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_2_3-solution000005.solution new file mode 100644 index 0000000000..1a734343d9 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_1_2_3-solution000005.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_2_3-solution000006.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_2_3-solution000006.solution new file mode 100644 index 0000000000..76bc8cdc32 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_1_2_3-solution000006.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_2_3-solution000007.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_2_3-solution000007.solution new file mode 100644 index 0000000000..86a85825b3 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_1_2_3-solution000007.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_2_3-solution000008.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_2_3-solution000008.solution new file mode 100644 index 0000000000..8dddb3b359 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_1_2_3-solution000008.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_2_4-solution000001.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_2_4-solution000001.solution new file mode 100644 index 0000000000..f90e0ba18c --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_1_2_4-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_2_4-solution000002.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_2_4-solution000002.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_1_2_4-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_2_4-solution000003.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_2_4-solution000003.solution new file mode 100644 index 0000000000..de5cc861ad --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_1_2_4-solution000003.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_2_4-solution000004.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_2_4-solution000004.solution new file mode 100644 index 0000000000..a28b6d6203 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_1_2_4-solution000004.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_2_4-solution000005.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_2_4-solution000005.solution new file mode 100644 index 0000000000..1a734343d9 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_1_2_4-solution000005.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_2_4-solution000006.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_2_4-solution000006.solution new file mode 100644 index 0000000000..76bc8cdc32 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_1_2_4-solution000006.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_2_4-solution000007.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_2_4-solution000007.solution new file mode 100644 index 0000000000..86a85825b3 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_1_2_4-solution000007.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_2_4-solution000008.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_2_4-solution000008.solution new file mode 100644 index 0000000000..8dddb3b359 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_1_2_4-solution000008.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_3_1-solution000001.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_3_1-solution000001.solution new file mode 100644 index 0000000000..f90e0ba18c --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_1_3_1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_3_1-solution000002.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_3_1-solution000002.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_1_3_1-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_3_1-solution000003.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_3_1-solution000003.solution new file mode 100644 index 0000000000..de5cc861ad --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_1_3_1-solution000003.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_3_1-solution000004.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_3_1-solution000004.solution new file mode 100644 index 0000000000..a28b6d6203 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_1_3_1-solution000004.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_3_1-solution000005.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_3_1-solution000005.solution new file mode 100644 index 0000000000..1a734343d9 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_1_3_1-solution000005.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_3_1-solution000006.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_3_1-solution000006.solution new file mode 100644 index 0000000000..76bc8cdc32 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_1_3_1-solution000006.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_3_1-solution000007.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_3_1-solution000007.solution new file mode 100644 index 0000000000..86a85825b3 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_1_3_1-solution000007.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_3_1-solution000008.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_3_1-solution000008.solution new file mode 100644 index 0000000000..8dddb3b359 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_1_3_1-solution000008.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_3_2-solution000001.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_3_2-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_1_3_2-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_3_2-solution000002.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_3_2-solution000002.solution new file mode 100644 index 0000000000..f90e0ba18c --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_1_3_2-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_3_2-solution000003.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_3_2-solution000003.solution new file mode 100644 index 0000000000..a28b6d6203 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_1_3_2-solution000003.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_3_2-solution000004.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_3_2-solution000004.solution new file mode 100644 index 0000000000..de5cc861ad --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_1_3_2-solution000004.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_3_2-solution000005.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_3_2-solution000005.solution new file mode 100644 index 0000000000..8dddb3b359 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_1_3_2-solution000005.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_3_2-solution000006.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_3_2-solution000006.solution new file mode 100644 index 0000000000..76bc8cdc32 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_1_3_2-solution000006.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_3_2-solution000007.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_3_2-solution000007.solution new file mode 100644 index 0000000000..86a85825b3 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_1_3_2-solution000007.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_3_2-solution000008.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_3_2-solution000008.solution new file mode 100644 index 0000000000..1a734343d9 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_1_3_2-solution000008.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_3_4-solution000001.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_3_4-solution000001.solution new file mode 100644 index 0000000000..f90e0ba18c --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_1_3_4-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_3_4-solution000002.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_3_4-solution000002.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_1_3_4-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_3_4-solution000003.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_3_4-solution000003.solution new file mode 100644 index 0000000000..de5cc861ad --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_1_3_4-solution000003.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_3_4-solution000004.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_3_4-solution000004.solution new file mode 100644 index 0000000000..a28b6d6203 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_1_3_4-solution000004.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_3_4-solution000005.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_3_4-solution000005.solution new file mode 100644 index 0000000000..1a734343d9 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_1_3_4-solution000005.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_3_4-solution000006.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_3_4-solution000006.solution new file mode 100644 index 0000000000..76bc8cdc32 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_1_3_4-solution000006.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_3_4-solution000007.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_3_4-solution000007.solution new file mode 100644 index 0000000000..86a85825b3 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_1_3_4-solution000007.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_3_4-solution000008.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_3_4-solution000008.solution new file mode 100644 index 0000000000..8dddb3b359 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_1_3_4-solution000008.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_4_1-solution000001.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_4_1-solution000001.solution new file mode 100644 index 0000000000..f90e0ba18c --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_1_4_1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_4_1-solution000002.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_4_1-solution000002.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_1_4_1-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_4_1-solution000003.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_4_1-solution000003.solution new file mode 100644 index 0000000000..de5cc861ad --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_1_4_1-solution000003.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_4_1-solution000004.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_4_1-solution000004.solution new file mode 100644 index 0000000000..a28b6d6203 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_1_4_1-solution000004.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_4_1-solution000005.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_4_1-solution000005.solution new file mode 100644 index 0000000000..1a734343d9 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_1_4_1-solution000005.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_4_1-solution000006.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_4_1-solution000006.solution new file mode 100644 index 0000000000..76bc8cdc32 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_1_4_1-solution000006.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_4_1-solution000007.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_4_1-solution000007.solution new file mode 100644 index 0000000000..86a85825b3 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_1_4_1-solution000007.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_4_1-solution000008.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_4_1-solution000008.solution new file mode 100644 index 0000000000..8dddb3b359 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_1_4_1-solution000008.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_4_2-solution000001.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_4_2-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_1_4_2-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_4_2-solution000002.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_4_2-solution000002.solution new file mode 100644 index 0000000000..f90e0ba18c --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_1_4_2-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_4_2-solution000003.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_4_2-solution000003.solution new file mode 100644 index 0000000000..a28b6d6203 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_1_4_2-solution000003.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_4_2-solution000004.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_4_2-solution000004.solution new file mode 100644 index 0000000000..de5cc861ad --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_1_4_2-solution000004.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_4_2-solution000005.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_4_2-solution000005.solution new file mode 100644 index 0000000000..8dddb3b359 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_1_4_2-solution000005.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_4_2-solution000006.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_4_2-solution000006.solution new file mode 100644 index 0000000000..76bc8cdc32 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_1_4_2-solution000006.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_4_2-solution000007.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_4_2-solution000007.solution new file mode 100644 index 0000000000..86a85825b3 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_1_4_2-solution000007.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_4_2-solution000008.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_4_2-solution000008.solution new file mode 100644 index 0000000000..1a734343d9 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_1_4_2-solution000008.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_4_3-solution000001.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_4_3-solution000001.solution new file mode 100644 index 0000000000..f90e0ba18c --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_1_4_3-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_4_3-solution000002.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_4_3-solution000002.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_1_4_3-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_4_3-solution000003.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_4_3-solution000003.solution new file mode 100644 index 0000000000..de5cc861ad --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_1_4_3-solution000003.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_4_3-solution000004.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_4_3-solution000004.solution new file mode 100644 index 0000000000..a28b6d6203 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_1_4_3-solution000004.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_4_3-solution000005.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_4_3-solution000005.solution new file mode 100644 index 0000000000..1a734343d9 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_1_4_3-solution000005.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_4_3-solution000006.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_4_3-solution000006.solution new file mode 100644 index 0000000000..76bc8cdc32 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_1_4_3-solution000006.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_4_3-solution000007.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_4_3-solution000007.solution new file mode 100644 index 0000000000..86a85825b3 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_1_4_3-solution000007.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_4_3-solution000008.solution b/tests/exhaustive/basic/cut_01_on/expected/model_1_4_3-solution000008.solution new file mode 100644 index 0000000000..8dddb3b359 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_1_4_3-solution000008.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_1_1-solution000001.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_1_1-solution000001.solution new file mode 100644 index 0000000000..f90e0ba18c --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_2_1_1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_1_1-solution000002.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_1_1-solution000002.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_2_1_1-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_1_1-solution000003.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_1_1-solution000003.solution new file mode 100644 index 0000000000..de5cc861ad --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_2_1_1-solution000003.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_1_1-solution000004.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_1_1-solution000004.solution new file mode 100644 index 0000000000..a28b6d6203 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_2_1_1-solution000004.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_1_1-solution000005.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_1_1-solution000005.solution new file mode 100644 index 0000000000..1a734343d9 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_2_1_1-solution000005.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_1_1-solution000006.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_1_1-solution000006.solution new file mode 100644 index 0000000000..86a85825b3 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_2_1_1-solution000006.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_1_1-solution000007.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_1_1-solution000007.solution new file mode 100644 index 0000000000..76bc8cdc32 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_2_1_1-solution000007.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_1_1-solution000008.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_1_1-solution000008.solution new file mode 100644 index 0000000000..8dddb3b359 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_2_1_1-solution000008.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_1_3-solution000001.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_1_3-solution000001.solution new file mode 100644 index 0000000000..f90e0ba18c --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_2_1_3-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_1_3-solution000002.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_1_3-solution000002.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_2_1_3-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_1_3-solution000003.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_1_3-solution000003.solution new file mode 100644 index 0000000000..de5cc861ad --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_2_1_3-solution000003.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_1_3-solution000004.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_1_3-solution000004.solution new file mode 100644 index 0000000000..a28b6d6203 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_2_1_3-solution000004.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_1_3-solution000005.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_1_3-solution000005.solution new file mode 100644 index 0000000000..1a734343d9 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_2_1_3-solution000005.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_1_3-solution000006.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_1_3-solution000006.solution new file mode 100644 index 0000000000..76bc8cdc32 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_2_1_3-solution000006.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_1_3-solution000007.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_1_3-solution000007.solution new file mode 100644 index 0000000000..86a85825b3 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_2_1_3-solution000007.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_1_3-solution000008.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_1_3-solution000008.solution new file mode 100644 index 0000000000..8dddb3b359 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_2_1_3-solution000008.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_1_4-solution000001.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_1_4-solution000001.solution new file mode 100644 index 0000000000..f90e0ba18c --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_2_1_4-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_1_4-solution000002.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_1_4-solution000002.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_2_1_4-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_1_4-solution000003.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_1_4-solution000003.solution new file mode 100644 index 0000000000..de5cc861ad --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_2_1_4-solution000003.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_1_4-solution000004.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_1_4-solution000004.solution new file mode 100644 index 0000000000..a28b6d6203 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_2_1_4-solution000004.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_1_4-solution000005.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_1_4-solution000005.solution new file mode 100644 index 0000000000..1a734343d9 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_2_1_4-solution000005.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_1_4-solution000006.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_1_4-solution000006.solution new file mode 100644 index 0000000000..76bc8cdc32 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_2_1_4-solution000006.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_1_4-solution000007.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_1_4-solution000007.solution new file mode 100644 index 0000000000..86a85825b3 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_2_1_4-solution000007.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_1_4-solution000008.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_1_4-solution000008.solution new file mode 100644 index 0000000000..8dddb3b359 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_2_1_4-solution000008.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_2_1-solution000001.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_2_1-solution000001.solution new file mode 100644 index 0000000000..f90e0ba18c --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_2_2_1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_2_1-solution000002.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_2_1-solution000002.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_2_2_1-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_2_1-solution000003.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_2_1-solution000003.solution new file mode 100644 index 0000000000..de5cc861ad --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_2_2_1-solution000003.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_2_1-solution000004.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_2_1-solution000004.solution new file mode 100644 index 0000000000..a28b6d6203 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_2_2_1-solution000004.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_2_1-solution000005.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_2_1-solution000005.solution new file mode 100644 index 0000000000..1a734343d9 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_2_2_1-solution000005.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_2_1-solution000006.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_2_1-solution000006.solution new file mode 100644 index 0000000000..86a85825b3 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_2_2_1-solution000006.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_2_1-solution000007.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_2_1-solution000007.solution new file mode 100644 index 0000000000..76bc8cdc32 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_2_2_1-solution000007.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_2_1-solution000008.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_2_1-solution000008.solution new file mode 100644 index 0000000000..8dddb3b359 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_2_2_1-solution000008.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_2_1.eprime.orig b/tests/exhaustive/basic/cut_01_on/expected/model_2_2_1.eprime.orig deleted file mode 100644 index 8c2f20a49b..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_2_2_1.eprime.orig +++ /dev/null @@ -1,20 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..3)] of int(1..4) -find x_Occurrence: matrix indexed by [int(1..3)] of bool -find cut1: bool -find cut2: bool -branching on [cut1, cut2, x_Occurrence, x_ExplicitVarSizeWithDummy] -such that - !cut1 <-> - or([x_ExplicitVarSizeWithDummy[q8] != 4 /\ x_ExplicitVarSizeWithDummy[q8] = 1 | q8 : int(1..3)]) /\ - or([x_ExplicitVarSizeWithDummy[q10] != 4 /\ x_ExplicitVarSizeWithDummy[q10] = 2 | q10 : int(1..3)]), - !cut2 <-> or([x_ExplicitVarSizeWithDummy[q12] != 4 /\ x_ExplicitVarSizeWithDummy[q12] = 1 | q12 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 4 - | q1 : int(1..2)]), - and([x_ExplicitVarSizeWithDummy[q2] = 4 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 4 | q2 : int(1..2)]), - and([x_Occurrence[q13] -> - or([x_ExplicitVarSizeWithDummy[q15] != 4 /\ x_ExplicitVarSizeWithDummy[q15] = q13 | q15 : int(1..3)]) - | q13 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q17] != 4 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q17]] | q17 : int(1..3)]) - diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_2_2-solution000001.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_2_2-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_2_2_2-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_2_2-solution000002.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_2_2-solution000002.solution new file mode 100644 index 0000000000..f90e0ba18c --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_2_2_2-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_2_2-solution000003.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_2_2-solution000003.solution new file mode 100644 index 0000000000..a28b6d6203 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_2_2_2-solution000003.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_2_2-solution000004.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_2_2-solution000004.solution new file mode 100644 index 0000000000..de5cc861ad --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_2_2_2-solution000004.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_2_2-solution000005.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_2_2-solution000005.solution new file mode 100644 index 0000000000..8dddb3b359 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_2_2_2-solution000005.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_2_2-solution000006.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_2_2-solution000006.solution new file mode 100644 index 0000000000..76bc8cdc32 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_2_2_2-solution000006.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_2_2-solution000007.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_2_2-solution000007.solution new file mode 100644 index 0000000000..86a85825b3 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_2_2_2-solution000007.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_2_2-solution000008.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_2_2-solution000008.solution new file mode 100644 index 0000000000..1a734343d9 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_2_2_2-solution000008.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_2_2.eprime.orig b/tests/exhaustive/basic/cut_01_on/expected/model_2_2_2.eprime.orig deleted file mode 100644 index 1ab97aa764..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_2_2_2.eprime.orig +++ /dev/null @@ -1,15 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..3)] of int(1..4) -find cut1: bool -find cut2: bool -branching on [cut1, cut2, x_ExplicitVarSizeWithDummy] -such that - !cut1 <-> - or([x_ExplicitVarSizeWithDummy[q7] != 4 /\ x_ExplicitVarSizeWithDummy[q7] = 1 | q7 : int(1..3)]) /\ - or([x_ExplicitVarSizeWithDummy[q9] != 4 /\ x_ExplicitVarSizeWithDummy[q9] = 2 | q9 : int(1..3)]), - !cut2 <-> or([x_ExplicitVarSizeWithDummy[q11] != 4 /\ x_ExplicitVarSizeWithDummy[q11] = 1 | q11 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 4 - | q1 : int(1..2)]), - and([x_ExplicitVarSizeWithDummy[q2] = 4 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 4 | q2 : int(1..2)]) - diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_2_3-solution000001.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_2_3-solution000001.solution new file mode 100644 index 0000000000..f90e0ba18c --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_2_2_3-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_2_3-solution000002.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_2_3-solution000002.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_2_2_3-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_2_3-solution000003.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_2_3-solution000003.solution new file mode 100644 index 0000000000..de5cc861ad --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_2_2_3-solution000003.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_2_3-solution000004.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_2_3-solution000004.solution new file mode 100644 index 0000000000..a28b6d6203 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_2_2_3-solution000004.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_2_3-solution000005.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_2_3-solution000005.solution new file mode 100644 index 0000000000..1a734343d9 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_2_2_3-solution000005.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_2_3-solution000006.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_2_3-solution000006.solution new file mode 100644 index 0000000000..76bc8cdc32 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_2_2_3-solution000006.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_2_3-solution000007.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_2_3-solution000007.solution new file mode 100644 index 0000000000..86a85825b3 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_2_2_3-solution000007.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_2_3-solution000008.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_2_3-solution000008.solution new file mode 100644 index 0000000000..8dddb3b359 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_2_2_3-solution000008.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_2_4-solution000001.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_2_4-solution000001.solution new file mode 100644 index 0000000000..f90e0ba18c --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_2_2_4-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_2_4-solution000002.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_2_4-solution000002.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_2_2_4-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_2_4-solution000003.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_2_4-solution000003.solution new file mode 100644 index 0000000000..de5cc861ad --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_2_2_4-solution000003.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_2_4-solution000004.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_2_4-solution000004.solution new file mode 100644 index 0000000000..a28b6d6203 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_2_2_4-solution000004.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_2_4-solution000005.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_2_4-solution000005.solution new file mode 100644 index 0000000000..1a734343d9 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_2_2_4-solution000005.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_2_4-solution000006.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_2_4-solution000006.solution new file mode 100644 index 0000000000..76bc8cdc32 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_2_2_4-solution000006.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_2_4-solution000007.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_2_4-solution000007.solution new file mode 100644 index 0000000000..86a85825b3 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_2_2_4-solution000007.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_2_4-solution000008.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_2_4-solution000008.solution new file mode 100644 index 0000000000..8dddb3b359 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_2_2_4-solution000008.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_3_1-solution000001.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_3_1-solution000001.solution new file mode 100644 index 0000000000..f90e0ba18c --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_2_3_1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_3_1-solution000002.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_3_1-solution000002.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_2_3_1-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_3_1-solution000003.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_3_1-solution000003.solution new file mode 100644 index 0000000000..de5cc861ad --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_2_3_1-solution000003.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_3_1-solution000004.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_3_1-solution000004.solution new file mode 100644 index 0000000000..a28b6d6203 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_2_3_1-solution000004.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_3_1-solution000005.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_3_1-solution000005.solution new file mode 100644 index 0000000000..1a734343d9 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_2_3_1-solution000005.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_3_1-solution000006.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_3_1-solution000006.solution new file mode 100644 index 0000000000..86a85825b3 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_2_3_1-solution000006.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_3_1-solution000007.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_3_1-solution000007.solution new file mode 100644 index 0000000000..76bc8cdc32 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_2_3_1-solution000007.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_3_1-solution000008.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_3_1-solution000008.solution new file mode 100644 index 0000000000..8dddb3b359 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_2_3_1-solution000008.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_3_2-solution000001.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_3_2-solution000001.solution new file mode 100644 index 0000000000..f90e0ba18c --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_2_3_2-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_3_2-solution000002.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_3_2-solution000002.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_2_3_2-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_3_2-solution000003.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_3_2-solution000003.solution new file mode 100644 index 0000000000..de5cc861ad --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_2_3_2-solution000003.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_3_2-solution000004.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_3_2-solution000004.solution new file mode 100644 index 0000000000..a28b6d6203 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_2_3_2-solution000004.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_3_2-solution000005.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_3_2-solution000005.solution new file mode 100644 index 0000000000..1a734343d9 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_2_3_2-solution000005.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_3_2-solution000006.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_3_2-solution000006.solution new file mode 100644 index 0000000000..76bc8cdc32 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_2_3_2-solution000006.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_3_2-solution000007.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_3_2-solution000007.solution new file mode 100644 index 0000000000..86a85825b3 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_2_3_2-solution000007.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_3_2-solution000008.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_3_2-solution000008.solution new file mode 100644 index 0000000000..8dddb3b359 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_2_3_2-solution000008.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_3_4-solution000001.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_3_4-solution000001.solution new file mode 100644 index 0000000000..f90e0ba18c --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_2_3_4-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_3_4-solution000002.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_3_4-solution000002.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_2_3_4-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_3_4-solution000003.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_3_4-solution000003.solution new file mode 100644 index 0000000000..de5cc861ad --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_2_3_4-solution000003.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_3_4-solution000004.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_3_4-solution000004.solution new file mode 100644 index 0000000000..a28b6d6203 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_2_3_4-solution000004.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_3_4-solution000005.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_3_4-solution000005.solution new file mode 100644 index 0000000000..1a734343d9 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_2_3_4-solution000005.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_3_4-solution000006.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_3_4-solution000006.solution new file mode 100644 index 0000000000..76bc8cdc32 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_2_3_4-solution000006.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_3_4-solution000007.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_3_4-solution000007.solution new file mode 100644 index 0000000000..86a85825b3 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_2_3_4-solution000007.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_3_4-solution000008.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_3_4-solution000008.solution new file mode 100644 index 0000000000..8dddb3b359 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_2_3_4-solution000008.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_4_1-solution000001.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_4_1-solution000001.solution new file mode 100644 index 0000000000..f90e0ba18c --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_2_4_1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_4_1-solution000002.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_4_1-solution000002.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_2_4_1-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_4_1-solution000003.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_4_1-solution000003.solution new file mode 100644 index 0000000000..de5cc861ad --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_2_4_1-solution000003.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_4_1-solution000004.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_4_1-solution000004.solution new file mode 100644 index 0000000000..a28b6d6203 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_2_4_1-solution000004.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_4_1-solution000005.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_4_1-solution000005.solution new file mode 100644 index 0000000000..1a734343d9 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_2_4_1-solution000005.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_4_1-solution000006.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_4_1-solution000006.solution new file mode 100644 index 0000000000..86a85825b3 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_2_4_1-solution000006.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_4_1-solution000007.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_4_1-solution000007.solution new file mode 100644 index 0000000000..76bc8cdc32 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_2_4_1-solution000007.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_4_1-solution000008.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_4_1-solution000008.solution new file mode 100644 index 0000000000..8dddb3b359 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_2_4_1-solution000008.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_4_2-solution000001.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_4_2-solution000001.solution new file mode 100644 index 0000000000..f90e0ba18c --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_2_4_2-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_4_2-solution000002.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_4_2-solution000002.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_2_4_2-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_4_2-solution000003.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_4_2-solution000003.solution new file mode 100644 index 0000000000..de5cc861ad --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_2_4_2-solution000003.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_4_2-solution000004.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_4_2-solution000004.solution new file mode 100644 index 0000000000..a28b6d6203 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_2_4_2-solution000004.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_4_2-solution000005.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_4_2-solution000005.solution new file mode 100644 index 0000000000..1a734343d9 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_2_4_2-solution000005.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_4_2-solution000006.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_4_2-solution000006.solution new file mode 100644 index 0000000000..76bc8cdc32 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_2_4_2-solution000006.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_4_2-solution000007.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_4_2-solution000007.solution new file mode 100644 index 0000000000..86a85825b3 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_2_4_2-solution000007.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_4_2-solution000008.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_4_2-solution000008.solution new file mode 100644 index 0000000000..8dddb3b359 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_2_4_2-solution000008.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_4_3-solution000001.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_4_3-solution000001.solution new file mode 100644 index 0000000000..f90e0ba18c --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_2_4_3-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_4_3-solution000002.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_4_3-solution000002.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_2_4_3-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_4_3-solution000003.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_4_3-solution000003.solution new file mode 100644 index 0000000000..de5cc861ad --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_2_4_3-solution000003.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_4_3-solution000004.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_4_3-solution000004.solution new file mode 100644 index 0000000000..a28b6d6203 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_2_4_3-solution000004.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_4_3-solution000005.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_4_3-solution000005.solution new file mode 100644 index 0000000000..1a734343d9 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_2_4_3-solution000005.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_4_3-solution000006.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_4_3-solution000006.solution new file mode 100644 index 0000000000..76bc8cdc32 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_2_4_3-solution000006.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_4_3-solution000007.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_4_3-solution000007.solution new file mode 100644 index 0000000000..86a85825b3 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_2_4_3-solution000007.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_4_3-solution000008.solution b/tests/exhaustive/basic/cut_01_on/expected/model_2_4_3-solution000008.solution new file mode 100644 index 0000000000..8dddb3b359 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_2_4_3-solution000008.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_1_1-solution000001.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_1_1-solution000001.solution new file mode 100644 index 0000000000..f90e0ba18c --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_3_1_1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_1_1-solution000002.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_1_1-solution000002.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_3_1_1-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_1_1-solution000003.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_1_1-solution000003.solution new file mode 100644 index 0000000000..de5cc861ad --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_3_1_1-solution000003.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_1_1-solution000004.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_1_1-solution000004.solution new file mode 100644 index 0000000000..a28b6d6203 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_3_1_1-solution000004.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_1_1-solution000005.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_1_1-solution000005.solution new file mode 100644 index 0000000000..1a734343d9 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_3_1_1-solution000005.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_1_1-solution000006.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_1_1-solution000006.solution new file mode 100644 index 0000000000..86a85825b3 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_3_1_1-solution000006.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_1_1-solution000007.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_1_1-solution000007.solution new file mode 100644 index 0000000000..76bc8cdc32 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_3_1_1-solution000007.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_1_1-solution000008.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_1_1-solution000008.solution new file mode 100644 index 0000000000..8dddb3b359 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_3_1_1-solution000008.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_1_2-solution000001.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_1_2-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_3_1_2-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_1_2-solution000002.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_1_2-solution000002.solution new file mode 100644 index 0000000000..f90e0ba18c --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_3_1_2-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_1_2-solution000003.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_1_2-solution000003.solution new file mode 100644 index 0000000000..a28b6d6203 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_3_1_2-solution000003.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_1_2-solution000004.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_1_2-solution000004.solution new file mode 100644 index 0000000000..de5cc861ad --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_3_1_2-solution000004.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_1_2-solution000005.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_1_2-solution000005.solution new file mode 100644 index 0000000000..8dddb3b359 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_3_1_2-solution000005.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_1_2-solution000006.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_1_2-solution000006.solution new file mode 100644 index 0000000000..76bc8cdc32 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_3_1_2-solution000006.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_1_2-solution000007.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_1_2-solution000007.solution new file mode 100644 index 0000000000..86a85825b3 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_3_1_2-solution000007.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_1_2-solution000008.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_1_2-solution000008.solution new file mode 100644 index 0000000000..1a734343d9 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_3_1_2-solution000008.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_1_4-solution000001.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_1_4-solution000001.solution new file mode 100644 index 0000000000..f90e0ba18c --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_3_1_4-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_1_4-solution000002.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_1_4-solution000002.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_3_1_4-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_1_4-solution000003.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_1_4-solution000003.solution new file mode 100644 index 0000000000..de5cc861ad --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_3_1_4-solution000003.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_1_4-solution000004.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_1_4-solution000004.solution new file mode 100644 index 0000000000..a28b6d6203 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_3_1_4-solution000004.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_1_4-solution000005.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_1_4-solution000005.solution new file mode 100644 index 0000000000..1a734343d9 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_3_1_4-solution000005.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_1_4-solution000006.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_1_4-solution000006.solution new file mode 100644 index 0000000000..76bc8cdc32 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_3_1_4-solution000006.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_1_4-solution000007.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_1_4-solution000007.solution new file mode 100644 index 0000000000..86a85825b3 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_3_1_4-solution000007.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_1_4-solution000008.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_1_4-solution000008.solution new file mode 100644 index 0000000000..8dddb3b359 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_3_1_4-solution000008.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_2_1-solution000001.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_2_1-solution000001.solution new file mode 100644 index 0000000000..f90e0ba18c --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_3_2_1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_2_1-solution000002.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_2_1-solution000002.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_3_2_1-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_2_1-solution000003.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_2_1-solution000003.solution new file mode 100644 index 0000000000..de5cc861ad --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_3_2_1-solution000003.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_2_1-solution000004.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_2_1-solution000004.solution new file mode 100644 index 0000000000..a28b6d6203 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_3_2_1-solution000004.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_2_1-solution000005.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_2_1-solution000005.solution new file mode 100644 index 0000000000..1a734343d9 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_3_2_1-solution000005.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_2_1-solution000006.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_2_1-solution000006.solution new file mode 100644 index 0000000000..86a85825b3 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_3_2_1-solution000006.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_2_1-solution000007.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_2_1-solution000007.solution new file mode 100644 index 0000000000..76bc8cdc32 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_3_2_1-solution000007.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_2_1-solution000008.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_2_1-solution000008.solution new file mode 100644 index 0000000000..8dddb3b359 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_3_2_1-solution000008.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_2_2-solution000001.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_2_2-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_3_2_2-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_2_2-solution000002.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_2_2-solution000002.solution new file mode 100644 index 0000000000..f90e0ba18c --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_3_2_2-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_2_2-solution000003.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_2_2-solution000003.solution new file mode 100644 index 0000000000..a28b6d6203 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_3_2_2-solution000003.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_2_2-solution000004.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_2_2-solution000004.solution new file mode 100644 index 0000000000..de5cc861ad --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_3_2_2-solution000004.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_2_2-solution000005.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_2_2-solution000005.solution new file mode 100644 index 0000000000..8dddb3b359 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_3_2_2-solution000005.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_2_2-solution000006.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_2_2-solution000006.solution new file mode 100644 index 0000000000..76bc8cdc32 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_3_2_2-solution000006.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_2_2-solution000007.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_2_2-solution000007.solution new file mode 100644 index 0000000000..86a85825b3 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_3_2_2-solution000007.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_2_2-solution000008.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_2_2-solution000008.solution new file mode 100644 index 0000000000..1a734343d9 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_3_2_2-solution000008.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_2_4-solution000001.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_2_4-solution000001.solution new file mode 100644 index 0000000000..f90e0ba18c --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_3_2_4-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_2_4-solution000002.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_2_4-solution000002.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_3_2_4-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_2_4-solution000003.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_2_4-solution000003.solution new file mode 100644 index 0000000000..de5cc861ad --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_3_2_4-solution000003.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_2_4-solution000004.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_2_4-solution000004.solution new file mode 100644 index 0000000000..a28b6d6203 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_3_2_4-solution000004.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_2_4-solution000005.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_2_4-solution000005.solution new file mode 100644 index 0000000000..1a734343d9 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_3_2_4-solution000005.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_2_4-solution000006.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_2_4-solution000006.solution new file mode 100644 index 0000000000..76bc8cdc32 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_3_2_4-solution000006.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_2_4-solution000007.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_2_4-solution000007.solution new file mode 100644 index 0000000000..86a85825b3 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_3_2_4-solution000007.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_2_4-solution000008.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_2_4-solution000008.solution new file mode 100644 index 0000000000..8dddb3b359 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_3_2_4-solution000008.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_3_1-solution000001.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_3_1-solution000001.solution new file mode 100644 index 0000000000..f90e0ba18c --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_3_3_1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_3_1-solution000002.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_3_1-solution000002.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_3_3_1-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_3_1-solution000003.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_3_1-solution000003.solution new file mode 100644 index 0000000000..de5cc861ad --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_3_3_1-solution000003.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_3_1-solution000004.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_3_1-solution000004.solution new file mode 100644 index 0000000000..a28b6d6203 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_3_3_1-solution000004.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_3_1-solution000005.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_3_1-solution000005.solution new file mode 100644 index 0000000000..1a734343d9 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_3_3_1-solution000005.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_3_1-solution000006.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_3_1-solution000006.solution new file mode 100644 index 0000000000..86a85825b3 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_3_3_1-solution000006.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_3_1-solution000007.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_3_1-solution000007.solution new file mode 100644 index 0000000000..76bc8cdc32 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_3_3_1-solution000007.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_3_1-solution000008.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_3_1-solution000008.solution new file mode 100644 index 0000000000..8dddb3b359 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_3_3_1-solution000008.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_3_1.eprime.orig b/tests/exhaustive/basic/cut_01_on/expected/model_3_3_1.eprime.orig deleted file mode 100644 index efb86f3a6f..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_3_3_1.eprime.orig +++ /dev/null @@ -1,25 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..3) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3)] of int(1..3) -find x_Occurrence: matrix indexed by [int(1..3)] of bool -find cut1: bool -find cut2: bool -branching on [cut1, cut2, x_Occurrence, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] -such that - !cut1 <-> - or([q7 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q7] = 1 | q7 : int(1..3)]) /\ - or([q9 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q9] = 2 | q9 : int(1..3)]), - !cut2 <-> - or([q11 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q11] = 1 | q11 : int(1..3)]), - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..2)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..3)]), - and([x_Occurrence[q12] -> - or([q14 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q14] = q12 - | q14 : int(1..3)]) - | q12 : int(1..3)]), - and([q16 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q16]] - | q16 : int(1..3)]) - diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_3_2-solution000001.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_3_2-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_3_3_2-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_3_2-solution000002.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_3_2-solution000002.solution new file mode 100644 index 0000000000..f90e0ba18c --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_3_3_2-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_3_2-solution000003.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_3_2-solution000003.solution new file mode 100644 index 0000000000..a28b6d6203 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_3_3_2-solution000003.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_3_2-solution000004.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_3_2-solution000004.solution new file mode 100644 index 0000000000..de5cc861ad --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_3_3_2-solution000004.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_3_2-solution000005.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_3_2-solution000005.solution new file mode 100644 index 0000000000..8dddb3b359 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_3_3_2-solution000005.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_3_2-solution000006.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_3_2-solution000006.solution new file mode 100644 index 0000000000..76bc8cdc32 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_3_3_2-solution000006.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_3_2-solution000007.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_3_2-solution000007.solution new file mode 100644 index 0000000000..86a85825b3 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_3_3_2-solution000007.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_3_2-solution000008.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_3_2-solution000008.solution new file mode 100644 index 0000000000..1a734343d9 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_3_3_2-solution000008.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_3_3-solution000001.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_3_3-solution000001.solution new file mode 100644 index 0000000000..f90e0ba18c --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_3_3_3-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_3_3-solution000002.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_3_3-solution000002.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_3_3_3-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_3_3-solution000003.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_3_3-solution000003.solution new file mode 100644 index 0000000000..de5cc861ad --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_3_3_3-solution000003.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_3_3-solution000004.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_3_3-solution000004.solution new file mode 100644 index 0000000000..a28b6d6203 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_3_3_3-solution000004.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_3_3-solution000005.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_3_3-solution000005.solution new file mode 100644 index 0000000000..1a734343d9 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_3_3_3-solution000005.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_3_3-solution000006.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_3_3-solution000006.solution new file mode 100644 index 0000000000..76bc8cdc32 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_3_3_3-solution000006.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_3_3-solution000007.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_3_3-solution000007.solution new file mode 100644 index 0000000000..86a85825b3 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_3_3_3-solution000007.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_3_3-solution000008.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_3_3-solution000008.solution new file mode 100644 index 0000000000..8dddb3b359 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_3_3_3-solution000008.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_3_3.eprime.orig b/tests/exhaustive/basic/cut_01_on/expected/model_3_3_3.eprime.orig deleted file mode 100644 index 989c9efdd0..0000000000 --- a/tests/exhaustive/basic/cut_01_on/expected/model_3_3_3.eprime.orig +++ /dev/null @@ -1,18 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarker_Marker: int(0..3) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3)] of int(1..3) -find cut1: bool -find cut2: bool -branching on [cut1, cut2, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] -such that - !cut1 <-> - or([q6 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q6] = 1 | q6 : int(1..3)]) /\ - or([q8 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q8] = 2 | q8 : int(1..3)]), - !cut2 <-> - or([q10 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q10] = 1 | q10 : int(1..3)]), - and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> - x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] - | q1 : int(1..2)]), - and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..3)]) - diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_3_4-solution000001.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_3_4-solution000001.solution new file mode 100644 index 0000000000..f90e0ba18c --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_3_3_4-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_3_4-solution000002.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_3_4-solution000002.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_3_3_4-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_3_4-solution000003.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_3_4-solution000003.solution new file mode 100644 index 0000000000..de5cc861ad --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_3_3_4-solution000003.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_3_4-solution000004.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_3_4-solution000004.solution new file mode 100644 index 0000000000..a28b6d6203 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_3_3_4-solution000004.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_3_4-solution000005.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_3_4-solution000005.solution new file mode 100644 index 0000000000..1a734343d9 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_3_3_4-solution000005.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_3_4-solution000006.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_3_4-solution000006.solution new file mode 100644 index 0000000000..76bc8cdc32 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_3_3_4-solution000006.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_3_4-solution000007.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_3_4-solution000007.solution new file mode 100644 index 0000000000..86a85825b3 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_3_3_4-solution000007.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_3_4-solution000008.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_3_4-solution000008.solution new file mode 100644 index 0000000000..8dddb3b359 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_3_3_4-solution000008.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_4_1-solution000001.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_4_1-solution000001.solution new file mode 100644 index 0000000000..f90e0ba18c --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_3_4_1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_4_1-solution000002.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_4_1-solution000002.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_3_4_1-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_4_1-solution000003.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_4_1-solution000003.solution new file mode 100644 index 0000000000..de5cc861ad --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_3_4_1-solution000003.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_4_1-solution000004.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_4_1-solution000004.solution new file mode 100644 index 0000000000..a28b6d6203 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_3_4_1-solution000004.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_4_1-solution000005.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_4_1-solution000005.solution new file mode 100644 index 0000000000..1a734343d9 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_3_4_1-solution000005.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_4_1-solution000006.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_4_1-solution000006.solution new file mode 100644 index 0000000000..86a85825b3 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_3_4_1-solution000006.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_4_1-solution000007.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_4_1-solution000007.solution new file mode 100644 index 0000000000..76bc8cdc32 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_3_4_1-solution000007.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_4_1-solution000008.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_4_1-solution000008.solution new file mode 100644 index 0000000000..8dddb3b359 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_3_4_1-solution000008.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_4_2-solution000001.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_4_2-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_3_4_2-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_4_2-solution000002.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_4_2-solution000002.solution new file mode 100644 index 0000000000..f90e0ba18c --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_3_4_2-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_4_2-solution000003.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_4_2-solution000003.solution new file mode 100644 index 0000000000..a28b6d6203 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_3_4_2-solution000003.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_4_2-solution000004.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_4_2-solution000004.solution new file mode 100644 index 0000000000..de5cc861ad --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_3_4_2-solution000004.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_4_2-solution000005.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_4_2-solution000005.solution new file mode 100644 index 0000000000..8dddb3b359 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_3_4_2-solution000005.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_4_2-solution000006.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_4_2-solution000006.solution new file mode 100644 index 0000000000..76bc8cdc32 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_3_4_2-solution000006.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_4_2-solution000007.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_4_2-solution000007.solution new file mode 100644 index 0000000000..86a85825b3 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_3_4_2-solution000007.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_4_2-solution000008.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_4_2-solution000008.solution new file mode 100644 index 0000000000..1a734343d9 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_3_4_2-solution000008.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_4_3-solution000001.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_4_3-solution000001.solution new file mode 100644 index 0000000000..f90e0ba18c --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_3_4_3-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_4_3-solution000002.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_4_3-solution000002.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_3_4_3-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_4_3-solution000003.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_4_3-solution000003.solution new file mode 100644 index 0000000000..de5cc861ad --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_3_4_3-solution000003.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_4_3-solution000004.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_4_3-solution000004.solution new file mode 100644 index 0000000000..a28b6d6203 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_3_4_3-solution000004.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_4_3-solution000005.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_4_3-solution000005.solution new file mode 100644 index 0000000000..1a734343d9 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_3_4_3-solution000005.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_4_3-solution000006.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_4_3-solution000006.solution new file mode 100644 index 0000000000..76bc8cdc32 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_3_4_3-solution000006.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_4_3-solution000007.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_4_3-solution000007.solution new file mode 100644 index 0000000000..86a85825b3 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_3_4_3-solution000007.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_4_3-solution000008.solution b/tests/exhaustive/basic/cut_01_on/expected/model_3_4_3-solution000008.solution new file mode 100644 index 0000000000..8dddb3b359 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_3_4_3-solution000008.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_1_1-solution000001.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_1_1-solution000001.solution new file mode 100644 index 0000000000..f90e0ba18c --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_4_1_1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_1_1-solution000002.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_1_1-solution000002.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_4_1_1-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_1_1-solution000003.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_1_1-solution000003.solution new file mode 100644 index 0000000000..de5cc861ad --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_4_1_1-solution000003.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_1_1-solution000004.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_1_1-solution000004.solution new file mode 100644 index 0000000000..a28b6d6203 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_4_1_1-solution000004.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_1_1-solution000005.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_1_1-solution000005.solution new file mode 100644 index 0000000000..1a734343d9 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_4_1_1-solution000005.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_1_1-solution000006.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_1_1-solution000006.solution new file mode 100644 index 0000000000..86a85825b3 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_4_1_1-solution000006.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_1_1-solution000007.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_1_1-solution000007.solution new file mode 100644 index 0000000000..76bc8cdc32 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_4_1_1-solution000007.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_1_1-solution000008.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_1_1-solution000008.solution new file mode 100644 index 0000000000..8dddb3b359 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_4_1_1-solution000008.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_1_2-solution000001.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_1_2-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_4_1_2-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_1_2-solution000002.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_1_2-solution000002.solution new file mode 100644 index 0000000000..f90e0ba18c --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_4_1_2-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_1_2-solution000003.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_1_2-solution000003.solution new file mode 100644 index 0000000000..a28b6d6203 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_4_1_2-solution000003.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_1_2-solution000004.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_1_2-solution000004.solution new file mode 100644 index 0000000000..de5cc861ad --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_4_1_2-solution000004.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_1_2-solution000005.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_1_2-solution000005.solution new file mode 100644 index 0000000000..8dddb3b359 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_4_1_2-solution000005.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_1_2-solution000006.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_1_2-solution000006.solution new file mode 100644 index 0000000000..76bc8cdc32 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_4_1_2-solution000006.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_1_2-solution000007.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_1_2-solution000007.solution new file mode 100644 index 0000000000..86a85825b3 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_4_1_2-solution000007.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_1_2-solution000008.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_1_2-solution000008.solution new file mode 100644 index 0000000000..1a734343d9 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_4_1_2-solution000008.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_1_3-solution000001.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_1_3-solution000001.solution new file mode 100644 index 0000000000..f90e0ba18c --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_4_1_3-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_1_3-solution000002.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_1_3-solution000002.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_4_1_3-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_1_3-solution000003.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_1_3-solution000003.solution new file mode 100644 index 0000000000..de5cc861ad --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_4_1_3-solution000003.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_1_3-solution000004.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_1_3-solution000004.solution new file mode 100644 index 0000000000..a28b6d6203 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_4_1_3-solution000004.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_1_3-solution000005.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_1_3-solution000005.solution new file mode 100644 index 0000000000..1a734343d9 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_4_1_3-solution000005.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_1_3-solution000006.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_1_3-solution000006.solution new file mode 100644 index 0000000000..76bc8cdc32 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_4_1_3-solution000006.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_1_3-solution000007.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_1_3-solution000007.solution new file mode 100644 index 0000000000..86a85825b3 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_4_1_3-solution000007.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_1_3-solution000008.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_1_3-solution000008.solution new file mode 100644 index 0000000000..8dddb3b359 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_4_1_3-solution000008.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_2_1-solution000001.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_2_1-solution000001.solution new file mode 100644 index 0000000000..f90e0ba18c --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_4_2_1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_2_1-solution000002.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_2_1-solution000002.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_4_2_1-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_2_1-solution000003.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_2_1-solution000003.solution new file mode 100644 index 0000000000..de5cc861ad --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_4_2_1-solution000003.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_2_1-solution000004.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_2_1-solution000004.solution new file mode 100644 index 0000000000..a28b6d6203 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_4_2_1-solution000004.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_2_1-solution000005.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_2_1-solution000005.solution new file mode 100644 index 0000000000..1a734343d9 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_4_2_1-solution000005.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_2_1-solution000006.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_2_1-solution000006.solution new file mode 100644 index 0000000000..86a85825b3 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_4_2_1-solution000006.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_2_1-solution000007.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_2_1-solution000007.solution new file mode 100644 index 0000000000..76bc8cdc32 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_4_2_1-solution000007.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_2_1-solution000008.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_2_1-solution000008.solution new file mode 100644 index 0000000000..8dddb3b359 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_4_2_1-solution000008.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_2_2-solution000001.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_2_2-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_4_2_2-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_2_2-solution000002.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_2_2-solution000002.solution new file mode 100644 index 0000000000..f90e0ba18c --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_4_2_2-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_2_2-solution000003.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_2_2-solution000003.solution new file mode 100644 index 0000000000..a28b6d6203 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_4_2_2-solution000003.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_2_2-solution000004.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_2_2-solution000004.solution new file mode 100644 index 0000000000..de5cc861ad --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_4_2_2-solution000004.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_2_2-solution000005.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_2_2-solution000005.solution new file mode 100644 index 0000000000..8dddb3b359 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_4_2_2-solution000005.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_2_2-solution000006.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_2_2-solution000006.solution new file mode 100644 index 0000000000..76bc8cdc32 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_4_2_2-solution000006.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_2_2-solution000007.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_2_2-solution000007.solution new file mode 100644 index 0000000000..86a85825b3 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_4_2_2-solution000007.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_2_2-solution000008.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_2_2-solution000008.solution new file mode 100644 index 0000000000..1a734343d9 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_4_2_2-solution000008.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_2_3-solution000001.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_2_3-solution000001.solution new file mode 100644 index 0000000000..f90e0ba18c --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_4_2_3-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_2_3-solution000002.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_2_3-solution000002.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_4_2_3-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_2_3-solution000003.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_2_3-solution000003.solution new file mode 100644 index 0000000000..de5cc861ad --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_4_2_3-solution000003.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_2_3-solution000004.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_2_3-solution000004.solution new file mode 100644 index 0000000000..a28b6d6203 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_4_2_3-solution000004.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_2_3-solution000005.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_2_3-solution000005.solution new file mode 100644 index 0000000000..1a734343d9 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_4_2_3-solution000005.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_2_3-solution000006.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_2_3-solution000006.solution new file mode 100644 index 0000000000..76bc8cdc32 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_4_2_3-solution000006.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_2_3-solution000007.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_2_3-solution000007.solution new file mode 100644 index 0000000000..86a85825b3 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_4_2_3-solution000007.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_2_3-solution000008.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_2_3-solution000008.solution new file mode 100644 index 0000000000..8dddb3b359 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_4_2_3-solution000008.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_3_1-solution000001.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_3_1-solution000001.solution new file mode 100644 index 0000000000..f90e0ba18c --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_4_3_1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_3_1-solution000002.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_3_1-solution000002.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_4_3_1-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_3_1-solution000003.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_3_1-solution000003.solution new file mode 100644 index 0000000000..de5cc861ad --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_4_3_1-solution000003.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_3_1-solution000004.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_3_1-solution000004.solution new file mode 100644 index 0000000000..a28b6d6203 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_4_3_1-solution000004.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_3_1-solution000005.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_3_1-solution000005.solution new file mode 100644 index 0000000000..1a734343d9 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_4_3_1-solution000005.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_3_1-solution000006.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_3_1-solution000006.solution new file mode 100644 index 0000000000..86a85825b3 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_4_3_1-solution000006.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_3_1-solution000007.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_3_1-solution000007.solution new file mode 100644 index 0000000000..76bc8cdc32 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_4_3_1-solution000007.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_3_1-solution000008.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_3_1-solution000008.solution new file mode 100644 index 0000000000..8dddb3b359 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_4_3_1-solution000008.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_3_2-solution000001.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_3_2-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_4_3_2-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_3_2-solution000002.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_3_2-solution000002.solution new file mode 100644 index 0000000000..f90e0ba18c --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_4_3_2-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_3_2-solution000003.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_3_2-solution000003.solution new file mode 100644 index 0000000000..a28b6d6203 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_4_3_2-solution000003.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_3_2-solution000004.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_3_2-solution000004.solution new file mode 100644 index 0000000000..de5cc861ad --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_4_3_2-solution000004.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_3_2-solution000005.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_3_2-solution000005.solution new file mode 100644 index 0000000000..8dddb3b359 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_4_3_2-solution000005.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_3_2-solution000006.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_3_2-solution000006.solution new file mode 100644 index 0000000000..76bc8cdc32 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_4_3_2-solution000006.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_3_2-solution000007.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_3_2-solution000007.solution new file mode 100644 index 0000000000..86a85825b3 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_4_3_2-solution000007.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_3_2-solution000008.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_3_2-solution000008.solution new file mode 100644 index 0000000000..1a734343d9 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_4_3_2-solution000008.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_3_3-solution000001.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_3_3-solution000001.solution new file mode 100644 index 0000000000..f90e0ba18c --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_4_3_3-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_3_3-solution000002.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_3_3-solution000002.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_4_3_3-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_3_3-solution000003.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_3_3-solution000003.solution new file mode 100644 index 0000000000..de5cc861ad --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_4_3_3-solution000003.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_3_3-solution000004.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_3_3-solution000004.solution new file mode 100644 index 0000000000..a28b6d6203 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_4_3_3-solution000004.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_3_3-solution000005.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_3_3-solution000005.solution new file mode 100644 index 0000000000..1a734343d9 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_4_3_3-solution000005.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_3_3-solution000006.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_3_3-solution000006.solution new file mode 100644 index 0000000000..76bc8cdc32 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_4_3_3-solution000006.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_3_3-solution000007.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_3_3-solution000007.solution new file mode 100644 index 0000000000..86a85825b3 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_4_3_3-solution000007.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_3_3-solution000008.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_3_3-solution000008.solution new file mode 100644 index 0000000000..8dddb3b359 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_4_3_3-solution000008.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_4_1-solution000001.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_4_1-solution000001.solution new file mode 100644 index 0000000000..f90e0ba18c --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_4_4_1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_4_1-solution000002.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_4_1-solution000002.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_4_4_1-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_4_1-solution000003.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_4_1-solution000003.solution new file mode 100644 index 0000000000..de5cc861ad --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_4_4_1-solution000003.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_4_1-solution000004.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_4_1-solution000004.solution new file mode 100644 index 0000000000..a28b6d6203 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_4_4_1-solution000004.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_4_1-solution000005.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_4_1-solution000005.solution new file mode 100644 index 0000000000..1a734343d9 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_4_4_1-solution000005.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_4_1-solution000006.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_4_1-solution000006.solution new file mode 100644 index 0000000000..86a85825b3 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_4_4_1-solution000006.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_4_1-solution000007.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_4_1-solution000007.solution new file mode 100644 index 0000000000..76bc8cdc32 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_4_4_1-solution000007.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_4_1-solution000008.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_4_1-solution000008.solution new file mode 100644 index 0000000000..8dddb3b359 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_4_4_1-solution000008.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_4_2-solution000001.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_4_2-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_4_4_2-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_4_2-solution000002.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_4_2-solution000002.solution new file mode 100644 index 0000000000..f90e0ba18c --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_4_4_2-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_4_2-solution000003.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_4_2-solution000003.solution new file mode 100644 index 0000000000..a28b6d6203 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_4_4_2-solution000003.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_4_2-solution000004.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_4_2-solution000004.solution new file mode 100644 index 0000000000..de5cc861ad --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_4_4_2-solution000004.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_4_2-solution000005.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_4_2-solution000005.solution new file mode 100644 index 0000000000..8dddb3b359 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_4_4_2-solution000005.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_4_2-solution000006.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_4_2-solution000006.solution new file mode 100644 index 0000000000..76bc8cdc32 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_4_4_2-solution000006.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_4_2-solution000007.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_4_2-solution000007.solution new file mode 100644 index 0000000000..86a85825b3 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_4_4_2-solution000007.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_4_2-solution000008.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_4_2-solution000008.solution new file mode 100644 index 0000000000..1a734343d9 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_4_4_2-solution000008.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_4_3-solution000001.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_4_3-solution000001.solution new file mode 100644 index 0000000000..f90e0ba18c --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_4_4_3-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_4_3-solution000002.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_4_3-solution000002.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_4_4_3-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_4_3-solution000003.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_4_3-solution000003.solution new file mode 100644 index 0000000000..de5cc861ad --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_4_4_3-solution000003.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_4_3-solution000004.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_4_3-solution000004.solution new file mode 100644 index 0000000000..a28b6d6203 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_4_4_3-solution000004.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_4_3-solution000005.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_4_3-solution000005.solution new file mode 100644 index 0000000000..1a734343d9 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_4_4_3-solution000005.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_4_3-solution000006.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_4_3-solution000006.solution new file mode 100644 index 0000000000..76bc8cdc32 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_4_4_3-solution000006.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_4_3-solution000007.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_4_3-solution000007.solution new file mode 100644 index 0000000000..86a85825b3 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_4_4_3-solution000007.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_4_3-solution000008.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_4_3-solution000008.solution new file mode 100644 index 0000000000..8dddb3b359 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_4_4_3-solution000008.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_4_4-solution000001.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_4_4-solution000001.solution new file mode 100644 index 0000000000..f90e0ba18c --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_4_4_4-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_4_4-solution000002.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_4_4-solution000002.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_4_4_4-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_4_4-solution000003.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_4_4-solution000003.solution new file mode 100644 index 0000000000..de5cc861ad --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_4_4_4-solution000003.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_4_4-solution000004.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_4_4-solution000004.solution new file mode 100644 index 0000000000..a28b6d6203 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_4_4_4-solution000004.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_4_4-solution000005.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_4_4-solution000005.solution new file mode 100644 index 0000000000..1a734343d9 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_4_4_4-solution000005.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_4_4-solution000006.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_4_4-solution000006.solution new file mode 100644 index 0000000000..76bc8cdc32 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_4_4_4-solution000006.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_4_4-solution000007.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_4_4-solution000007.solution new file mode 100644 index 0000000000..86a85825b3 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_4_4_4-solution000007.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_4_4-solution000008.solution b/tests/exhaustive/basic/cut_01_on/expected/model_4_4_4-solution000008.solution new file mode 100644 index 0000000000..8dddb3b359 --- /dev/null +++ b/tests/exhaustive/basic/cut_01_on/expected/model_4_4_4-solution000008.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {2, 3} diff --git a/tests/exhaustive/basic/enum05-enum/enum05/expected/model_1_2.eprime b/tests/exhaustive/basic/enum05-enum/enum05/expected/model_1_2.eprime index 5e1ac67e4f..3c466a4bfb 100644 --- a/tests/exhaustive/basic/enum05-enum/enum05/expected/model_1_2.eprime +++ b/tests/exhaustive/basic/enum05-enum/enum05/expected/model_1_2.eprime @@ -5,8 +5,7 @@ find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..2)] of int(1..3) branching on [x_ExplicitVarSizeWithDummy, x_Occurrence] such that x_Occurrence[1], - [x_ExplicitVarSizeWithDummy[1]; int(1)] x_ExplicitVarSizeWithDummy[2] = 3, and([x_ExplicitVarSizeWithDummy[q7] != 3 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q7]] | q7 : int(1..2)]), and([x_Occurrence[q8] -> diff --git a/tests/exhaustive/basic/enum05-enum/enum05/expected/model_1_3.eprime b/tests/exhaustive/basic/enum05-enum/enum05/expected/model_1_3.eprime index 1c517b2f64..caa450f69d 100644 --- a/tests/exhaustive/basic/enum05-enum/enum05/expected/model_1_3.eprime +++ b/tests/exhaustive/basic/enum05-enum/enum05/expected/model_1_3.eprime @@ -7,7 +7,7 @@ branching on [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Va such that x_Occurrence[1], 2 <= x_ExplicitVarSizeWithMarker_Marker -> - [x_ExplicitVarSizeWithMarker_Values[1]; int(1)] x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q3] = 1 | q3 : int(1..2)]), and([q6 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q6]] | q6 : int(1..2)]), diff --git a/tests/exhaustive/basic/enum05-enum/enum05/expected/model_1_4.eprime b/tests/exhaustive/basic/enum05-enum/enum05/expected/model_1_4.eprime index b0a108ce36..65b54149be 100644 --- a/tests/exhaustive/basic/enum05-enum/enum05/expected/model_1_4.eprime +++ b/tests/exhaustive/basic/enum05-enum/enum05/expected/model_1_4.eprime @@ -6,8 +6,7 @@ find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..2)] of int(1.. branching on [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_Occurrence] such that x_Occurrence[1], - x_ExplicitVarSizeWithFlags_Flags[2] -> - [x_ExplicitVarSizeWithFlags_Values[1]; int(1)] x_ExplicitVarSizeWithFlags_Values[1] < x_ExplicitVarSizeWithFlags_Values[2], and([x_ExplicitVarSizeWithFlags_Flags[q3] = false -> x_ExplicitVarSizeWithFlags_Values[q3] = 1 | q3 : int(1..2)]), x_ExplicitVarSizeWithFlags_Flags[2] -> x_ExplicitVarSizeWithFlags_Flags[1], and([x_ExplicitVarSizeWithFlags_Flags[q8] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q8]] | q8 : int(1..2)]), diff --git a/tests/exhaustive/basic/enum05-enum/enum05/expected/model_2_1.eprime b/tests/exhaustive/basic/enum05-enum/enum05/expected/model_2_1.eprime index 19b55ab58a..06dba1716a 100644 --- a/tests/exhaustive/basic/enum05-enum/enum05/expected/model_2_1.eprime +++ b/tests/exhaustive/basic/enum05-enum/enum05/expected/model_2_1.eprime @@ -5,8 +5,7 @@ find x_Occurrence: matrix indexed by [int(1..2)] of bool branching on [x_Occurrence, x_ExplicitVarSizeWithDummy] such that or([x_ExplicitVarSizeWithDummy[q7] != 3 /\ x_ExplicitVarSizeWithDummy[q7] = 1 | q7 : int(1..2)]), - [x_ExplicitVarSizeWithDummy[1]; int(1)] x_ExplicitVarSizeWithDummy[2] = 3, and([x_Occurrence[q8] -> or([x_ExplicitVarSizeWithDummy[q10] != 3 /\ x_ExplicitVarSizeWithDummy[q10] = q8 | q10 : int(1..2)]) diff --git a/tests/exhaustive/basic/enum05-enum/enum05/expected/model_2_2.eprime b/tests/exhaustive/basic/enum05-enum/enum05/expected/model_2_2.eprime index 3cd005c946..3cbe9f04b3 100644 --- a/tests/exhaustive/basic/enum05-enum/enum05/expected/model_2_2.eprime +++ b/tests/exhaustive/basic/enum05-enum/enum05/expected/model_2_2.eprime @@ -4,7 +4,6 @@ find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..2)] of int(1..3) branching on [x_ExplicitVarSizeWithDummy] such that or([x_ExplicitVarSizeWithDummy[q6] != 3 /\ x_ExplicitVarSizeWithDummy[q6] = 1 | q6 : int(1..2)]), - [x_ExplicitVarSizeWithDummy[1]; int(1)] x_ExplicitVarSizeWithDummy[2] = 3 diff --git a/tests/exhaustive/basic/enum05-enum/enum05/expected/model_2_3.eprime b/tests/exhaustive/basic/enum05-enum/enum05/expected/model_2_3.eprime index affa05405a..15b24ddce9 100644 --- a/tests/exhaustive/basic/enum05-enum/enum05/expected/model_2_3.eprime +++ b/tests/exhaustive/basic/enum05-enum/enum05/expected/model_2_3.eprime @@ -6,11 +6,10 @@ find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..2)] of int(1. branching on [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy] such that or([x_ExplicitVarSizeWithDummy[q17] != 3 /\ x_ExplicitVarSizeWithDummy[q17] = 1 | q17 : int(1..2)]), - [x_ExplicitVarSizeWithDummy[1]; int(1)] x_ExplicitVarSizeWithDummy[2] = 3, 2 <= x_ExplicitVarSizeWithMarker_Marker -> - [x_ExplicitVarSizeWithMarker_Values[1]; int(1)] x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q6] = 1 | q6 : int(1..2)]), and([q9 <= x_ExplicitVarSizeWithMarker_Marker -> or([x_ExplicitVarSizeWithDummy[q11] != 3 /\ diff --git a/tests/exhaustive/basic/enum05-enum/enum05/expected/model_2_4.eprime b/tests/exhaustive/basic/enum05-enum/enum05/expected/model_2_4.eprime index 20ee576a7b..e6286e36dc 100644 --- a/tests/exhaustive/basic/enum05-enum/enum05/expected/model_2_4.eprime +++ b/tests/exhaustive/basic/enum05-enum/enum05/expected/model_2_4.eprime @@ -6,11 +6,9 @@ find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..2)] of int(1.. branching on [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy] such that or([x_ExplicitVarSizeWithDummy[q19] != 3 /\ x_ExplicitVarSizeWithDummy[q19] = 1 | q19 : int(1..2)]), - [x_ExplicitVarSizeWithDummy[1]; int(1)] x_ExplicitVarSizeWithDummy[2] = 3, - x_ExplicitVarSizeWithFlags_Flags[2] -> - [x_ExplicitVarSizeWithFlags_Values[1]; int(1)] x_ExplicitVarSizeWithFlags_Values[1] < x_ExplicitVarSizeWithFlags_Values[2], and([x_ExplicitVarSizeWithFlags_Flags[q6] = false -> x_ExplicitVarSizeWithFlags_Values[q6] = 1 | q6 : int(1..2)]), x_ExplicitVarSizeWithFlags_Flags[2] -> x_ExplicitVarSizeWithFlags_Flags[1], and([x_ExplicitVarSizeWithFlags_Flags[q11] -> diff --git a/tests/exhaustive/basic/enum05-enum/enum05/expected/model_3_1.eprime b/tests/exhaustive/basic/enum05-enum/enum05/expected/model_3_1.eprime index 305e95e154..53b78284b9 100644 --- a/tests/exhaustive/basic/enum05-enum/enum05/expected/model_3_1.eprime +++ b/tests/exhaustive/basic/enum05-enum/enum05/expected/model_3_1.eprime @@ -7,7 +7,7 @@ branching on [x_Occurrence, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSiz such that or([q6 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q6] = 1 | q6 : int(1..2)]), 2 <= x_ExplicitVarSizeWithMarker_Marker -> - [x_ExplicitVarSizeWithMarker_Values[1]; int(1)] x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..2)]), and([x_Occurrence[q7] -> or([q9 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q9] = q7 | q9 : int(1..2)]) diff --git a/tests/exhaustive/basic/enum05-enum/enum05/expected/model_3_2.eprime b/tests/exhaustive/basic/enum05-enum/enum05/expected/model_3_2.eprime index 289392ed4b..9955c46684 100644 --- a/tests/exhaustive/basic/enum05-enum/enum05/expected/model_3_2.eprime +++ b/tests/exhaustive/basic/enum05-enum/enum05/expected/model_3_2.eprime @@ -7,10 +7,9 @@ branching on [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithMarker_Marker, x_ such that or([q17 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q17] = 1 | q17 : int(1..2)]), 2 <= x_ExplicitVarSizeWithMarker_Marker -> - [x_ExplicitVarSizeWithMarker_Values[1]; int(1)] x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..2)]), - [x_ExplicitVarSizeWithDummy[1]; int(1)] x_ExplicitVarSizeWithDummy[2] = 3, and([x_ExplicitVarSizeWithDummy[q9] != 3 -> or([q11 <= x_ExplicitVarSizeWithMarker_Marker /\ diff --git a/tests/exhaustive/basic/enum05-enum/enum05/expected/model_3_3.eprime b/tests/exhaustive/basic/enum05-enum/enum05/expected/model_3_3.eprime index cafd3e03b9..6bf0fbc245 100644 --- a/tests/exhaustive/basic/enum05-enum/enum05/expected/model_3_3.eprime +++ b/tests/exhaustive/basic/enum05-enum/enum05/expected/model_3_3.eprime @@ -6,6 +6,6 @@ branching on [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Va such that or([q5 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q5] = 1 | q5 : int(1..2)]), 2 <= x_ExplicitVarSizeWithMarker_Marker -> - [x_ExplicitVarSizeWithMarker_Values[1]; int(1)] x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..2)]) diff --git a/tests/exhaustive/basic/enum05-enum/enum05/expected/model_3_4.eprime b/tests/exhaustive/basic/enum05-enum/enum05/expected/model_3_4.eprime index e0e163e423..30b752c34b 100644 --- a/tests/exhaustive/basic/enum05-enum/enum05/expected/model_3_4.eprime +++ b/tests/exhaustive/basic/enum05-enum/enum05/expected/model_3_4.eprime @@ -10,10 +10,9 @@ branching on such that or([q18 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q18] = 1 | q18 : int(1..2)]), 2 <= x_ExplicitVarSizeWithMarker_Marker -> - [x_ExplicitVarSizeWithMarker_Values[1]; int(1)] x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..2)]), - x_ExplicitVarSizeWithFlags_Flags[2] -> - [x_ExplicitVarSizeWithFlags_Values[1]; int(1)] x_ExplicitVarSizeWithFlags_Values[1] < x_ExplicitVarSizeWithFlags_Values[2], and([x_ExplicitVarSizeWithFlags_Flags[q5] = false -> x_ExplicitVarSizeWithFlags_Values[q5] = 1 | q5 : int(1..2)]), x_ExplicitVarSizeWithFlags_Flags[2] -> x_ExplicitVarSizeWithFlags_Flags[1], and([x_ExplicitVarSizeWithFlags_Flags[q10] -> diff --git a/tests/exhaustive/basic/enum05-enum/enum05/expected/model_4_1.eprime b/tests/exhaustive/basic/enum05-enum/enum05/expected/model_4_1.eprime index 8d42b90c9e..d357287c6d 100644 --- a/tests/exhaustive/basic/enum05-enum/enum05/expected/model_4_1.eprime +++ b/tests/exhaustive/basic/enum05-enum/enum05/expected/model_4_1.eprime @@ -6,8 +6,7 @@ find x_Occurrence: matrix indexed by [int(1..2)] of bool branching on [x_Occurrence, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] such that or([x_ExplicitVarSizeWithFlags_Flags[q13] /\ x_ExplicitVarSizeWithFlags_Values[q13] = 1 | q13 : int(1..2)]), - x_ExplicitVarSizeWithFlags_Flags[2] -> - [x_ExplicitVarSizeWithFlags_Values[1]; int(1)] x_ExplicitVarSizeWithFlags_Values[1] < x_ExplicitVarSizeWithFlags_Values[2], and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..2)]), x_ExplicitVarSizeWithFlags_Flags[2] -> x_ExplicitVarSizeWithFlags_Flags[1], and([x_Occurrence[q7] -> diff --git a/tests/exhaustive/basic/enum05-enum/enum05/expected/model_4_2.eprime b/tests/exhaustive/basic/enum05-enum/enum05/expected/model_4_2.eprime index fa7a9b3cfb..7845f87b0a 100644 --- a/tests/exhaustive/basic/enum05-enum/enum05/expected/model_4_2.eprime +++ b/tests/exhaustive/basic/enum05-enum/enum05/expected/model_4_2.eprime @@ -6,12 +6,10 @@ find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..2)] of int(1..3) branching on [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] such that or([x_ExplicitVarSizeWithFlags_Flags[q19] /\ x_ExplicitVarSizeWithFlags_Values[q19] = 1 | q19 : int(1..2)]), - x_ExplicitVarSizeWithFlags_Flags[2] -> - [x_ExplicitVarSizeWithFlags_Values[1]; int(1)] x_ExplicitVarSizeWithFlags_Values[1] < x_ExplicitVarSizeWithFlags_Values[2], and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..2)]), x_ExplicitVarSizeWithFlags_Flags[2] -> x_ExplicitVarSizeWithFlags_Flags[1], - [x_ExplicitVarSizeWithDummy[1]; int(1)] x_ExplicitVarSizeWithDummy[2] = 3, and([x_ExplicitVarSizeWithDummy[q11] != 3 -> or([x_ExplicitVarSizeWithFlags_Flags[q13] /\ diff --git a/tests/exhaustive/basic/enum05-enum/enum05/expected/model_4_3.eprime b/tests/exhaustive/basic/enum05-enum/enum05/expected/model_4_3.eprime index 9339754f19..681490ebe2 100644 --- a/tests/exhaustive/basic/enum05-enum/enum05/expected/model_4_3.eprime +++ b/tests/exhaustive/basic/enum05-enum/enum05/expected/model_4_3.eprime @@ -9,12 +9,11 @@ branching on x_ExplicitVarSizeWithFlags_Values] such that or([x_ExplicitVarSizeWithFlags_Flags[q18] /\ x_ExplicitVarSizeWithFlags_Values[q18] = 1 | q18 : int(1..2)]), - x_ExplicitVarSizeWithFlags_Flags[2] -> - [x_ExplicitVarSizeWithFlags_Values[1]; int(1)] x_ExplicitVarSizeWithFlags_Values[1] < x_ExplicitVarSizeWithFlags_Values[2], and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..2)]), x_ExplicitVarSizeWithFlags_Flags[2] -> x_ExplicitVarSizeWithFlags_Flags[1], 2 <= x_ExplicitVarSizeWithMarker_Marker -> - [x_ExplicitVarSizeWithMarker_Values[1]; int(1)] x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q7] = 1 | q7 : int(1..2)]), and([q10 <= x_ExplicitVarSizeWithMarker_Marker -> or([x_ExplicitVarSizeWithFlags_Flags[q12] /\ diff --git a/tests/exhaustive/basic/enum05-enum/enum05/expected/model_4_4.eprime b/tests/exhaustive/basic/enum05-enum/enum05/expected/model_4_4.eprime index 4488d3c825..5045c01422 100644 --- a/tests/exhaustive/basic/enum05-enum/enum05/expected/model_4_4.eprime +++ b/tests/exhaustive/basic/enum05-enum/enum05/expected/model_4_4.eprime @@ -5,8 +5,7 @@ find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..2)] of int(1.. branching on [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] such that or([x_ExplicitVarSizeWithFlags_Flags[q7] /\ x_ExplicitVarSizeWithFlags_Values[q7] = 1 | q7 : int(1..2)]), - x_ExplicitVarSizeWithFlags_Flags[2] -> - [x_ExplicitVarSizeWithFlags_Values[1]; int(1)] x_ExplicitVarSizeWithFlags_Values[1] < x_ExplicitVarSizeWithFlags_Values[2], and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..2)]), x_ExplicitVarSizeWithFlags_Flags[2] -> x_ExplicitVarSizeWithFlags_Flags[1] diff --git a/tests/exhaustive/basic/enum05-unnamed/expected/model_2.eprime b/tests/exhaustive/basic/enum05-unnamed/expected/model_2.eprime index 32c39e4747..dd1644147e 100644 --- a/tests/exhaustive/basic/enum05-unnamed/expected/model_2.eprime +++ b/tests/exhaustive/basic/enum05-unnamed/expected/model_2.eprime @@ -3,7 +3,6 @@ language ESSENCE' 1.0 find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..2)] of int(1..3) branching on [x_ExplicitVarSizeWithDummy] such that - [x_ExplicitVarSizeWithDummy[1]; int(1)] x_ExplicitVarSizeWithDummy[2] = 3 diff --git a/tests/exhaustive/basic/enum05-unnamed/expected/model_3.eprime b/tests/exhaustive/basic/enum05-unnamed/expected/model_3.eprime index 4846bb6513..9baf5521b0 100644 --- a/tests/exhaustive/basic/enum05-unnamed/expected/model_3.eprime +++ b/tests/exhaustive/basic/enum05-unnamed/expected/model_3.eprime @@ -5,6 +5,6 @@ find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..2)] of int(1. branching on [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] such that 2 <= x_ExplicitVarSizeWithMarker_Marker -> - [x_ExplicitVarSizeWithMarker_Values[1]; int(1)] x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..2)]) diff --git a/tests/exhaustive/basic/enum05-unnamed/expected/model_4.eprime b/tests/exhaustive/basic/enum05-unnamed/expected/model_4.eprime index b922e0b97b..8c652122fc 100644 --- a/tests/exhaustive/basic/enum05-unnamed/expected/model_4.eprime +++ b/tests/exhaustive/basic/enum05-unnamed/expected/model_4.eprime @@ -4,8 +4,7 @@ find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..2)] of bool find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..2)] of int(1..2) branching on [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] such that - x_ExplicitVarSizeWithFlags_Flags[2] -> - [x_ExplicitVarSizeWithFlags_Values[1]; int(1)] x_ExplicitVarSizeWithFlags_Values[1] < x_ExplicitVarSizeWithFlags_Values[2], and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..2)]), x_ExplicitVarSizeWithFlags_Flags[2] -> x_ExplicitVarSizeWithFlags_Flags[1] diff --git a/tests/exhaustive/basic/enum06/expected/model_1_1.eprime b/tests/exhaustive/basic/enum06/expected/model_1_1.eprime index f03a6b45df..986fa491a6 100644 --- a/tests/exhaustive/basic/enum06/expected/model_1_1.eprime +++ b/tests/exhaustive/basic/enum06/expected/model_1_1.eprime @@ -4,14 +4,8 @@ find x_ExplicitWithFlags_Flags: matrix indexed by [int(1..4)] of int(0..4) find x_ExplicitWithFlags_Values: matrix indexed by [int(1..4)] of int(1..2) branching on [x_ExplicitWithFlags_Flags, x_ExplicitWithFlags_Values] such that -<<<<<<< HEAD - or([x_ExplicitWithFlags_Flags[q8] > 0 /\ x_ExplicitWithFlags_Values[q8] = 1 | q8 : int(1..4)]), - and([x_ExplicitWithFlags_Flags[q1 + 1] > 0 -> - [x_ExplicitWithFlags_Values[q1]; int(1)] 0 /\ x_ExplicitWithFlags_Values[q9] = 1 | q9 : int(1..4)]), and([x_ExplicitWithFlags_Flags[q1 + 1] > 0 -> x_ExplicitWithFlags_Values[q1] < x_ExplicitWithFlags_Values[q1 + 1] ->>>>>>> main | q1 : int(1..3)]), and([x_ExplicitWithFlags_Flags[q2] = 0 -> x_ExplicitWithFlags_Values[q2] = 1 | q2 : int(1..4)]), and([x_ExplicitWithFlags_Flags[q3 + 1] > 0 -> x_ExplicitWithFlags_Flags[q3] > 0 | q3 : int(1..3)]), diff --git a/tests/exhaustive/basic/enum06/expected/model_1_2.eprime b/tests/exhaustive/basic/enum06/expected/model_1_2.eprime index 8ca42b5521..5db82561f7 100644 --- a/tests/exhaustive/basic/enum06/expected/model_1_2.eprime +++ b/tests/exhaustive/basic/enum06/expected/model_1_2.eprime @@ -8,19 +8,6 @@ branching on [x_ExplicitWithRepetition_Flag, x_ExplicitWithRepetition_Values, x_ExplicitWithFlags_Flags, x_ExplicitWithFlags_Values] such that -<<<<<<< HEAD - or([x_ExplicitWithFlags_Flags[q22] > 0 /\ x_ExplicitWithFlags_Values[q22] = 1 | q22 : int(1..4)]), - and([x_ExplicitWithFlags_Flags[q1 + 1] > 0 -> - [x_ExplicitWithFlags_Values[q1]; int(1)] x_ExplicitWithFlags_Values[q2] = 1 | q2 : int(1..4)]), - and([x_ExplicitWithFlags_Flags[q3 + 1] > 0 -> x_ExplicitWithFlags_Flags[q3] > 0 | q3 : int(1..3)]), - sum([x_ExplicitWithFlags_Flags[q5] | q5 : int(1..4)]) <= 4, - and([q7 + 1 <= x_ExplicitWithRepetition_Flag -> - [x_ExplicitWithRepetition_Values[q7]; int(1)] <=lex [x_ExplicitWithRepetition_Values[q7 + 1]; int(1)] - | q7 : int(1..3)]), - and([q8 > x_ExplicitWithRepetition_Flag -> x_ExplicitWithRepetition_Values[q8] = 1 | q8 : int(1..4)]), -======= or([x_ExplicitWithFlags_Flags[q23] > 0 /\ x_ExplicitWithFlags_Values[q23] = 1 | q23 : int(1..4)]), and([x_ExplicitWithFlags_Flags[q1 + 1] > 0 -> x_ExplicitWithFlags_Values[q1] < x_ExplicitWithFlags_Values[q1 + 1] | q1 : int(1..3)]), @@ -31,7 +18,6 @@ such that x_ExplicitWithRepetition_Values[q8] <= x_ExplicitWithRepetition_Values[q8 + 1] | q8 : int(1..3)]), and([q9 > x_ExplicitWithRepetition_Flag -> x_ExplicitWithRepetition_Values[q9] = 1 | q9 : int(1..4)]), ->>>>>>> main x_ExplicitWithRepetition_Flag <= 4, and([q14 <= x_ExplicitWithRepetition_Flag -> sum([toInt(q17 <= x_ExplicitWithRepetition_Flag) * diff --git a/tests/exhaustive/basic/enum06/expected/model_1_3.eprime b/tests/exhaustive/basic/enum06/expected/model_1_3.eprime index 0dd7c6aa16..c2852c2ff8 100644 --- a/tests/exhaustive/basic/enum06/expected/model_1_3.eprime +++ b/tests/exhaustive/basic/enum06/expected/model_1_3.eprime @@ -5,14 +5,8 @@ find x_ExplicitWithFlags_Values: matrix indexed by [int(1..4)] of int(1..2) find x_MOccurrence: matrix indexed by [int(1..2)] of int(0..4) branching on [x_MOccurrence, x_ExplicitWithFlags_Flags, x_ExplicitWithFlags_Values] such that -<<<<<<< HEAD - or([x_ExplicitWithFlags_Flags[q14] > 0 /\ x_ExplicitWithFlags_Values[q14] = 1 | q14 : int(1..4)]), - and([x_ExplicitWithFlags_Flags[q1 + 1] > 0 -> - [x_ExplicitWithFlags_Values[q1]; int(1)] 0 /\ x_ExplicitWithFlags_Values[q15] = 1 | q15 : int(1..4)]), and([x_ExplicitWithFlags_Flags[q1 + 1] > 0 -> x_ExplicitWithFlags_Values[q1] < x_ExplicitWithFlags_Values[q1 + 1] ->>>>>>> main | q1 : int(1..3)]), and([x_ExplicitWithFlags_Flags[q2] = 0 -> x_ExplicitWithFlags_Values[q2] = 1 | q2 : int(1..4)]), and([x_ExplicitWithFlags_Flags[q3 + 1] > 0 -> x_ExplicitWithFlags_Flags[q3] > 0 | q3 : int(1..3)]), diff --git a/tests/exhaustive/basic/enum06/expected/model_2_1.eprime b/tests/exhaustive/basic/enum06/expected/model_2_1.eprime index ed7d0baf22..cee7612061 100644 --- a/tests/exhaustive/basic/enum06/expected/model_2_1.eprime +++ b/tests/exhaustive/basic/enum06/expected/model_2_1.eprime @@ -10,12 +10,11 @@ branching on such that or([q23 <= x_ExplicitWithRepetition_Flag /\ x_ExplicitWithRepetition_Values[q23] = 1 | q23 : int(1..4)]), and([q1 + 1 <= x_ExplicitWithRepetition_Flag -> - [x_ExplicitWithRepetition_Values[q1]; int(1)] <=lex [x_ExplicitWithRepetition_Values[q1 + 1]; int(1)] + x_ExplicitWithRepetition_Values[q1] <= x_ExplicitWithRepetition_Values[q1 + 1] | q1 : int(1..3)]), and([q2 > x_ExplicitWithRepetition_Flag -> x_ExplicitWithRepetition_Values[q2] = 1 | q2 : int(1..4)]), x_ExplicitWithRepetition_Flag <= 4, - and([x_ExplicitWithFlags_Flags[q6 + 1] > 0 -> - [x_ExplicitWithFlags_Values[q6]; int(1)] 0 -> x_ExplicitWithFlags_Values[q6] < x_ExplicitWithFlags_Values[q6 + 1] | q6 : int(1..3)]), and([x_ExplicitWithFlags_Flags[q7] = 0 -> x_ExplicitWithFlags_Values[q7] = 1 | q7 : int(1..4)]), and([x_ExplicitWithFlags_Flags[q8 + 1] > 0 -> x_ExplicitWithFlags_Flags[q8] > 0 | q8 : int(1..3)]), diff --git a/tests/exhaustive/basic/enum06/expected/model_2_2.eprime b/tests/exhaustive/basic/enum06/expected/model_2_2.eprime index ae8798327d..83a4f59f8c 100644 --- a/tests/exhaustive/basic/enum06/expected/model_2_2.eprime +++ b/tests/exhaustive/basic/enum06/expected/model_2_2.eprime @@ -6,7 +6,7 @@ branching on [x_ExplicitWithRepetition_Flag, x_ExplicitWithRepetition_Values] such that or([q7 <= x_ExplicitWithRepetition_Flag /\ x_ExplicitWithRepetition_Values[q7] = 1 | q7 : int(1..4)]), and([q1 + 1 <= x_ExplicitWithRepetition_Flag -> - [x_ExplicitWithRepetition_Values[q1]; int(1)] <=lex [x_ExplicitWithRepetition_Values[q1 + 1]; int(1)] + x_ExplicitWithRepetition_Values[q1] <= x_ExplicitWithRepetition_Values[q1 + 1] | q1 : int(1..3)]), and([q2 > x_ExplicitWithRepetition_Flag -> x_ExplicitWithRepetition_Values[q2] = 1 | q2 : int(1..4)]), x_ExplicitWithRepetition_Flag <= 4 diff --git a/tests/exhaustive/basic/enum06/expected/model_2_3.eprime b/tests/exhaustive/basic/enum06/expected/model_2_3.eprime index c53f6a7689..14637dd1da 100644 --- a/tests/exhaustive/basic/enum06/expected/model_2_3.eprime +++ b/tests/exhaustive/basic/enum06/expected/model_2_3.eprime @@ -7,7 +7,7 @@ branching on [x_MOccurrence, x_ExplicitWithRepetition_Flag, x_ExplicitWithRepeti such that or([q15 <= x_ExplicitWithRepetition_Flag /\ x_ExplicitWithRepetition_Values[q15] = 1 | q15 : int(1..4)]), and([q1 + 1 <= x_ExplicitWithRepetition_Flag -> - [x_ExplicitWithRepetition_Values[q1]; int(1)] <=lex [x_ExplicitWithRepetition_Values[q1 + 1]; int(1)] + x_ExplicitWithRepetition_Values[q1] <= x_ExplicitWithRepetition_Values[q1 + 1] | q1 : int(1..3)]), and([q2 > x_ExplicitWithRepetition_Flag -> x_ExplicitWithRepetition_Values[q2] = 1 | q2 : int(1..4)]), x_ExplicitWithRepetition_Flag <= 4, diff --git a/tests/exhaustive/basic/enum06/expected/model_3_1.eprime b/tests/exhaustive/basic/enum06/expected/model_3_1.eprime index 32770953a8..2ec0ae5b09 100644 --- a/tests/exhaustive/basic/enum06/expected/model_3_1.eprime +++ b/tests/exhaustive/basic/enum06/expected/model_3_1.eprime @@ -7,8 +7,7 @@ branching on [x_ExplicitWithFlags_Flags, x_ExplicitWithFlags_Values, x_MOccurren such that or([x_MOccurrence[q15] > 0 /\ q15 = 1 | q15 : int(1..2)]), sum([x_MOccurrence[q1] | q1 : int(1..2)]) <= 4, - and([x_ExplicitWithFlags_Flags[q2 + 1] > 0 -> - [x_ExplicitWithFlags_Values[q2]; int(1)] 0 -> x_ExplicitWithFlags_Values[q2] < x_ExplicitWithFlags_Values[q2 + 1] | q2 : int(1..3)]), and([x_ExplicitWithFlags_Flags[q3] = 0 -> x_ExplicitWithFlags_Values[q3] = 1 | q3 : int(1..4)]), and([x_ExplicitWithFlags_Flags[q4 + 1] > 0 -> x_ExplicitWithFlags_Flags[q4] > 0 | q4 : int(1..3)]), diff --git a/tests/exhaustive/basic/enum06/expected/model_3_2.eprime b/tests/exhaustive/basic/enum06/expected/model_3_2.eprime index ec9ac25a79..4309aabff6 100644 --- a/tests/exhaustive/basic/enum06/expected/model_3_2.eprime +++ b/tests/exhaustive/basic/enum06/expected/model_3_2.eprime @@ -8,7 +8,7 @@ such that or([x_MOccurrence[q15] > 0 /\ q15 = 1 | q15 : int(1..2)]), sum([x_MOccurrence[q1] | q1 : int(1..2)]) <= 4, and([q2 + 1 <= x_ExplicitWithRepetition_Flag -> - [x_ExplicitWithRepetition_Values[q2]; int(1)] <=lex [x_ExplicitWithRepetition_Values[q2 + 1]; int(1)] + x_ExplicitWithRepetition_Values[q2] <= x_ExplicitWithRepetition_Values[q2 + 1] | q2 : int(1..3)]), and([q3 > x_ExplicitWithRepetition_Flag -> x_ExplicitWithRepetition_Values[q3] = 1 | q3 : int(1..4)]), x_ExplicitWithRepetition_Flag <= 4, diff --git a/tests/exhaustive/basic/function_complex_01/expected/model_1-solution000001.solution b/tests/exhaustive/basic/function_complex_01/expected/model_1-solution000001.solution new file mode 100644 index 0000000000..2e109b6d40 --- /dev/null +++ b/tests/exhaustive/basic/function_complex_01/expected/model_1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be function({(7, false)} --> 17, {(7, true)} --> 13) diff --git a/tests/exhaustive/basic/function_complex_01/expected/model_1-solution000002.solution b/tests/exhaustive/basic/function_complex_01/expected/model_1-solution000002.solution new file mode 100644 index 0000000000..626dde8770 --- /dev/null +++ b/tests/exhaustive/basic/function_complex_01/expected/model_1-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be function({(7, false)} --> 13, {(7, true)} --> 17) diff --git a/tests/exhaustive/basic/function_complex_01/expected/model_1-solution000003.solution b/tests/exhaustive/basic/function_complex_01/expected/model_1-solution000003.solution new file mode 100644 index 0000000000..5ebd8e1209 --- /dev/null +++ b/tests/exhaustive/basic/function_complex_01/expected/model_1-solution000003.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be function({(7, false)} --> 13, {(7, false), (7, true)} --> 17) diff --git a/tests/exhaustive/basic/function_complex_01/expected/model_1-solution000004.solution b/tests/exhaustive/basic/function_complex_01/expected/model_1-solution000004.solution new file mode 100644 index 0000000000..ee811eb7ab --- /dev/null +++ b/tests/exhaustive/basic/function_complex_01/expected/model_1-solution000004.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be function({(7, false)} --> 17, {(7, false), (7, true)} --> 13) diff --git a/tests/exhaustive/basic/function_complex_01/expected/model_1-solution000005.solution b/tests/exhaustive/basic/function_complex_01/expected/model_1-solution000005.solution new file mode 100644 index 0000000000..30b06b719d --- /dev/null +++ b/tests/exhaustive/basic/function_complex_01/expected/model_1-solution000005.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be function({(7, false), (7, true)} --> 17, {(7, true)} --> 13) diff --git a/tests/exhaustive/basic/function_complex_01/expected/model_1-solution000006.solution b/tests/exhaustive/basic/function_complex_01/expected/model_1-solution000006.solution new file mode 100644 index 0000000000..65f731a60d --- /dev/null +++ b/tests/exhaustive/basic/function_complex_01/expected/model_1-solution000006.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be function({(7, false), (7, true)} --> 13, {(7, true)} --> 17) diff --git a/tests/exhaustive/basic/function_complex_01/expected/model_2-solution000001.solution b/tests/exhaustive/basic/function_complex_01/expected/model_2-solution000001.solution new file mode 100644 index 0000000000..2e109b6d40 --- /dev/null +++ b/tests/exhaustive/basic/function_complex_01/expected/model_2-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be function({(7, false)} --> 17, {(7, true)} --> 13) diff --git a/tests/exhaustive/basic/function_complex_01/expected/model_2-solution000002.solution b/tests/exhaustive/basic/function_complex_01/expected/model_2-solution000002.solution new file mode 100644 index 0000000000..626dde8770 --- /dev/null +++ b/tests/exhaustive/basic/function_complex_01/expected/model_2-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be function({(7, false)} --> 13, {(7, true)} --> 17) diff --git a/tests/exhaustive/basic/function_complex_01/expected/model_2-solution000003.solution b/tests/exhaustive/basic/function_complex_01/expected/model_2-solution000003.solution new file mode 100644 index 0000000000..ee811eb7ab --- /dev/null +++ b/tests/exhaustive/basic/function_complex_01/expected/model_2-solution000003.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be function({(7, false)} --> 17, {(7, false), (7, true)} --> 13) diff --git a/tests/exhaustive/basic/function_complex_01/expected/model_2-solution000004.solution b/tests/exhaustive/basic/function_complex_01/expected/model_2-solution000004.solution new file mode 100644 index 0000000000..5ebd8e1209 --- /dev/null +++ b/tests/exhaustive/basic/function_complex_01/expected/model_2-solution000004.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be function({(7, false)} --> 13, {(7, false), (7, true)} --> 17) diff --git a/tests/exhaustive/basic/function_complex_01/expected/model_2-solution000005.solution b/tests/exhaustive/basic/function_complex_01/expected/model_2-solution000005.solution new file mode 100644 index 0000000000..65f731a60d --- /dev/null +++ b/tests/exhaustive/basic/function_complex_01/expected/model_2-solution000005.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be function({(7, false), (7, true)} --> 13, {(7, true)} --> 17) diff --git a/tests/exhaustive/basic/function_complex_01/expected/model_2-solution000006.solution b/tests/exhaustive/basic/function_complex_01/expected/model_2-solution000006.solution new file mode 100644 index 0000000000..30b06b719d --- /dev/null +++ b/tests/exhaustive/basic/function_complex_01/expected/model_2-solution000006.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be function({(7, false), (7, true)} --> 17, {(7, true)} --> 13) diff --git a/tests/exhaustive/basic/function_range/expected/model.eprime.orig b/tests/exhaustive/basic/function_range/expected/model.eprime.orig deleted file mode 100644 index b47b2da335..0000000000 --- a/tests/exhaustive/basic/function_range/expected/model.eprime.orig +++ /dev/null @@ -1,12 +0,0 @@ -language ESSENCE' 1.0 - -find x_Function1DPartial_Flags: matrix indexed by [int(1..3)] of bool -find x_Function1DPartial_Values: matrix indexed by [int(1..3)] of int(1..3) -branching on [x_Function1DPartial_Flags, x_Function1DPartial_Values] -such that - or([x_Function1DPartial_Flags[q7] /\ x_Function1DPartial_Values[q7] = 1 | q7 : int(1..3)]), - or([x_Function1DPartial_Flags[q10] /\ x_Function1DPartial_Values[q10] = 2 | q10 : int(1..3)]), - and([x_Function1DPartial_Flags[q13] -> 1 = x_Function1DPartial_Values[q13] \/ 2 = x_Function1DPartial_Values[q13] - | q13 : int(1..3)]), - and([x_Function1DPartial_Flags[q1] = false -> x_Function1DPartial_Values[q1] = 1 | q1 : int(1..3)]) - diff --git a/tests/exhaustive/basic/function_total_int_set_01/expected/model_1.eprime b/tests/exhaustive/basic/function_total_int_set_01/expected/model_1.eprime index d338177dd2..4de8f61bbe 100644 --- a/tests/exhaustive/basic/function_total_int_set_01/expected/model_1.eprime +++ b/tests/exhaustive/basic/function_total_int_set_01/expected/model_1.eprime @@ -3,15 +3,9 @@ language ESSENCE' 1.0 find f_Function1DR3_Explicit: matrix indexed by [int(1..3), int(1..2)] of int(1..3) branching on [f_Function1DR3_Explicit] such that -<<<<<<< HEAD - and([[q1; int(1)] - or([f_Function1DR2_Occurrence[q1, q5] != f_Function1DR2_Occurrence[q2, q5] | q5 : int(1..3)]) \/ - or([f_Function1DR2_Occurrence[q1, q5] != f_Function1DR2_Occurrence[q2, q5] | q5 : int(1..3)]) -======= and([q1 < q2 -> or([f_Function1DR3_Explicit[q1, q6] != f_Function1DR3_Explicit[q2, q6] | q6 : int(1..2)]) \/ or([f_Function1DR3_Explicit[q1, q6] != f_Function1DR3_Explicit[q2, q6] | q6 : int(1..2)]) ->>>>>>> main | q1 : int(1..3), q2 : int(1..3)]), and([f_Function1DR3_Explicit[q3, 1] < f_Function1DR3_Explicit[q3, 2] | q3 : int(1..3)]) diff --git a/tests/exhaustive/basic/function_total_int_set_01/expected/model_2.eprime b/tests/exhaustive/basic/function_total_int_set_01/expected/model_2.eprime index 7c34c38b98..ee147a457c 100644 --- a/tests/exhaustive/basic/function_total_int_set_01/expected/model_2.eprime +++ b/tests/exhaustive/basic/function_total_int_set_01/expected/model_2.eprime @@ -3,17 +3,9 @@ language ESSENCE' 1.0 find f_Function1DR2_Occurrence: matrix indexed by [int(1..3), int(1..3)] of bool branching on [f_Function1DR2_Occurrence] such that -<<<<<<< HEAD - and([[q1; int(1)] - or([f_Function1DR3_Explicit[q1, q6] != f_Function1DR3_Explicit[q2, q6] | q6 : int(1..2)]) \/ - or([f_Function1DR3_Explicit[q1, q6] != f_Function1DR3_Explicit[q2, q6] | q6 : int(1..2)]) - | q1 : int(1..3), q2 : int(1..3)]), - and([[f_Function1DR3_Explicit[q3, 1]; int(1)] or([f_Function1DR2_Occurrence[q1, q5] != f_Function1DR2_Occurrence[q2, q5] | q5 : int(1..3)]) \/ or([f_Function1DR2_Occurrence[q1, q5] != f_Function1DR2_Occurrence[q2, q5] | q5 : int(1..3)]) | q1 : int(1..3), q2 : int(1..3)]), and([2 = sum([toInt(f_Function1DR2_Occurrence[q3, q4]) | q4 : int(1..3)]) | q3 : int(1..3)]) ->>>>>>> main diff --git a/tests/exhaustive/basic/matrix_of_set_02/expected/model_1_1-solution000001.solution b/tests/exhaustive/basic/matrix_of_set_02/expected/model_1_1-solution000001.solution new file mode 100644 index 0000000000..af7c1da5d8 --- /dev/null +++ b/tests/exhaustive/basic/matrix_of_set_02/expected/model_1_1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be [{}, {}; int(1..2)] diff --git a/tests/exhaustive/basic/matrix_of_set_02/expected/model_1_1-solution000002.solution b/tests/exhaustive/basic/matrix_of_set_02/expected/model_1_1-solution000002.solution new file mode 100644 index 0000000000..0b1f00f1a5 --- /dev/null +++ b/tests/exhaustive/basic/matrix_of_set_02/expected/model_1_1-solution000002.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be [{}, {2}; int(1..2)] +$ Visualisation for x +$ +$ 2 + diff --git a/tests/exhaustive/basic/matrix_of_set_02/expected/model_1_1-solution000003.solution b/tests/exhaustive/basic/matrix_of_set_02/expected/model_1_1-solution000003.solution new file mode 100644 index 0000000000..cbfa586d38 --- /dev/null +++ b/tests/exhaustive/basic/matrix_of_set_02/expected/model_1_1-solution000003.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be [{2}, {}; int(1..2)] +$ Visualisation for x +$ 2 +$ + diff --git a/tests/exhaustive/basic/matrix_of_set_02/expected/model_1_1-solution000004.solution b/tests/exhaustive/basic/matrix_of_set_02/expected/model_1_1-solution000004.solution new file mode 100644 index 0000000000..a392d5bbea --- /dev/null +++ b/tests/exhaustive/basic/matrix_of_set_02/expected/model_1_1-solution000004.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be [{2}, {2}; int(1..2)] +$ Visualisation for x +$ 2 +$ 2 + diff --git a/tests/exhaustive/basic/matrix_of_set_02/expected/model_1_1.eprime b/tests/exhaustive/basic/matrix_of_set_02/expected/model_1_1.eprime new file mode 100644 index 0000000000..7986231579 --- /dev/null +++ b/tests/exhaustive/basic/matrix_of_set_02/expected/model_1_1.eprime @@ -0,0 +1,6 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(1..2), int(1..3)] of bool +branching on [x_Occurrence] +such that and([x_Occurrence[j, i] -> i % 2 = 0 | j : int(1..2), i : int(1..3)]) + diff --git a/tests/exhaustive/basic/matrix_of_set_02/expected/model_1_2-solution000001.solution b/tests/exhaustive/basic/matrix_of_set_02/expected/model_1_2-solution000001.solution new file mode 100644 index 0000000000..a392d5bbea --- /dev/null +++ b/tests/exhaustive/basic/matrix_of_set_02/expected/model_1_2-solution000001.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be [{2}, {2}; int(1..2)] +$ Visualisation for x +$ 2 +$ 2 + diff --git a/tests/exhaustive/basic/matrix_of_set_02/expected/model_1_2-solution000002.solution b/tests/exhaustive/basic/matrix_of_set_02/expected/model_1_2-solution000002.solution new file mode 100644 index 0000000000..cbfa586d38 --- /dev/null +++ b/tests/exhaustive/basic/matrix_of_set_02/expected/model_1_2-solution000002.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be [{2}, {}; int(1..2)] +$ Visualisation for x +$ 2 +$ + diff --git a/tests/exhaustive/basic/matrix_of_set_02/expected/model_1_2-solution000003.solution b/tests/exhaustive/basic/matrix_of_set_02/expected/model_1_2-solution000003.solution new file mode 100644 index 0000000000..0b1f00f1a5 --- /dev/null +++ b/tests/exhaustive/basic/matrix_of_set_02/expected/model_1_2-solution000003.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be [{}, {2}; int(1..2)] +$ Visualisation for x +$ +$ 2 + diff --git a/tests/exhaustive/basic/matrix_of_set_02/expected/model_1_2-solution000004.solution b/tests/exhaustive/basic/matrix_of_set_02/expected/model_1_2-solution000004.solution new file mode 100644 index 0000000000..af7c1da5d8 --- /dev/null +++ b/tests/exhaustive/basic/matrix_of_set_02/expected/model_1_2-solution000004.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be [{}, {}; int(1..2)] diff --git a/tests/exhaustive/basic/matrix_of_set_02/expected/model_1_2.eprime b/tests/exhaustive/basic/matrix_of_set_02/expected/model_1_2.eprime new file mode 100644 index 0000000000..c5f1aed665 --- /dev/null +++ b/tests/exhaustive/basic/matrix_of_set_02/expected/model_1_2.eprime @@ -0,0 +1,22 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(1..2), int(1..3)] of bool +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..2), int(1..3)] of int(1..4) +branching on [x_ExplicitVarSizeWithDummy, x_Occurrence] +such that + and([x_Occurrence[j, i] -> i % 2 = 0 | j : int(1..2), i : int(1..3)]), + and([and([x_ExplicitVarSizeWithDummy[q3, q4] < x_ExplicitVarSizeWithDummy[q3, q4 + 1] \/ + x_ExplicitVarSizeWithDummy[q3, q4] = 4 + | q4 : int(1..2)]) + | q3 : int(1..2)]), + and([and([x_ExplicitVarSizeWithDummy[q3, q5] = 4 -> x_ExplicitVarSizeWithDummy[q3, q5 + 1] = 4 | q5 : int(1..2)]) + | q3 : int(1..2)]), + and([and([x_ExplicitVarSizeWithDummy[q8, q11] != 4 -> x_Occurrence[q8, x_ExplicitVarSizeWithDummy[q8, q11]] + | q11 : int(1..3)]) + /\ + and([x_Occurrence[q8, q12] -> + or([x_ExplicitVarSizeWithDummy[q8, q14] != 4 /\ x_ExplicitVarSizeWithDummy[q8, q14] = q12 + | q14 : int(1..3)]) + | q12 : int(1..3)]) + | q8 : int(1..2)]) + diff --git a/tests/exhaustive/basic/matrix_of_set_02/expected/model_1_3-solution000001.solution b/tests/exhaustive/basic/matrix_of_set_02/expected/model_1_3-solution000001.solution new file mode 100644 index 0000000000..af7c1da5d8 --- /dev/null +++ b/tests/exhaustive/basic/matrix_of_set_02/expected/model_1_3-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be [{}, {}; int(1..2)] diff --git a/tests/exhaustive/basic/matrix_of_set_02/expected/model_1_3-solution000002.solution b/tests/exhaustive/basic/matrix_of_set_02/expected/model_1_3-solution000002.solution new file mode 100644 index 0000000000..0b1f00f1a5 --- /dev/null +++ b/tests/exhaustive/basic/matrix_of_set_02/expected/model_1_3-solution000002.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be [{}, {2}; int(1..2)] +$ Visualisation for x +$ +$ 2 + diff --git a/tests/exhaustive/basic/matrix_of_set_02/expected/model_1_3-solution000003.solution b/tests/exhaustive/basic/matrix_of_set_02/expected/model_1_3-solution000003.solution new file mode 100644 index 0000000000..cbfa586d38 --- /dev/null +++ b/tests/exhaustive/basic/matrix_of_set_02/expected/model_1_3-solution000003.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be [{2}, {}; int(1..2)] +$ Visualisation for x +$ 2 +$ + diff --git a/tests/exhaustive/basic/matrix_of_set_02/expected/model_1_3-solution000004.solution b/tests/exhaustive/basic/matrix_of_set_02/expected/model_1_3-solution000004.solution new file mode 100644 index 0000000000..a392d5bbea --- /dev/null +++ b/tests/exhaustive/basic/matrix_of_set_02/expected/model_1_3-solution000004.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be [{2}, {2}; int(1..2)] +$ Visualisation for x +$ 2 +$ 2 + diff --git a/tests/exhaustive/basic/matrix_of_set_02/expected/model_1_3.eprime b/tests/exhaustive/basic/matrix_of_set_02/expected/model_1_3.eprime new file mode 100644 index 0000000000..d5a7d54f0f --- /dev/null +++ b/tests/exhaustive/basic/matrix_of_set_02/expected/model_1_3.eprime @@ -0,0 +1,25 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(1..2), int(1..3)] of bool +find x_ExplicitVarSizeWithMarker_Marker: matrix indexed by [int(1..2)] of int(0..3) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..2), int(1..3)] of int(1..3) +branching on [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_Occurrence] +such that + and([x_Occurrence[j, i] -> i % 2 = 0 | j : int(1..2), i : int(1..3)]), + and([and([q4 + 1 <= x_ExplicitVarSizeWithMarker_Marker[q3] -> + x_ExplicitVarSizeWithMarker_Values[q3, q4] < x_ExplicitVarSizeWithMarker_Values[q3, q4 + 1] + | q4 : int(1..2)]) + | q3 : int(1..2)]), + and([and([q5 > x_ExplicitVarSizeWithMarker_Marker[q3] -> x_ExplicitVarSizeWithMarker_Values[q3, q5] = 1 + | q5 : int(1..3)]) + | q3 : int(1..2)]), + and([and([q10 <= x_ExplicitVarSizeWithMarker_Marker[q7] -> + x_Occurrence[q7, x_ExplicitVarSizeWithMarker_Values[q7, q10]] + | q10 : int(1..3)]) + /\ + and([x_Occurrence[q7, q11] -> + or([q13 <= x_ExplicitVarSizeWithMarker_Marker[q7] /\ x_ExplicitVarSizeWithMarker_Values[q7, q13] = q11 + | q13 : int(1..3)]) + | q11 : int(1..3)]) + | q7 : int(1..2)]) + diff --git a/tests/exhaustive/basic/matrix_of_set_02/expected/model_1_4-solution000001.solution b/tests/exhaustive/basic/matrix_of_set_02/expected/model_1_4-solution000001.solution new file mode 100644 index 0000000000..af7c1da5d8 --- /dev/null +++ b/tests/exhaustive/basic/matrix_of_set_02/expected/model_1_4-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be [{}, {}; int(1..2)] diff --git a/tests/exhaustive/basic/matrix_of_set_02/expected/model_1_4-solution000002.solution b/tests/exhaustive/basic/matrix_of_set_02/expected/model_1_4-solution000002.solution new file mode 100644 index 0000000000..0b1f00f1a5 --- /dev/null +++ b/tests/exhaustive/basic/matrix_of_set_02/expected/model_1_4-solution000002.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be [{}, {2}; int(1..2)] +$ Visualisation for x +$ +$ 2 + diff --git a/tests/exhaustive/basic/matrix_of_set_02/expected/model_1_4-solution000003.solution b/tests/exhaustive/basic/matrix_of_set_02/expected/model_1_4-solution000003.solution new file mode 100644 index 0000000000..cbfa586d38 --- /dev/null +++ b/tests/exhaustive/basic/matrix_of_set_02/expected/model_1_4-solution000003.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be [{2}, {}; int(1..2)] +$ Visualisation for x +$ 2 +$ + diff --git a/tests/exhaustive/basic/matrix_of_set_02/expected/model_1_4-solution000004.solution b/tests/exhaustive/basic/matrix_of_set_02/expected/model_1_4-solution000004.solution new file mode 100644 index 0000000000..a392d5bbea --- /dev/null +++ b/tests/exhaustive/basic/matrix_of_set_02/expected/model_1_4-solution000004.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be [{2}, {2}; int(1..2)] +$ Visualisation for x +$ 2 +$ 2 + diff --git a/tests/exhaustive/basic/matrix_of_set_02/expected/model_1_4.eprime b/tests/exhaustive/basic/matrix_of_set_02/expected/model_1_4.eprime new file mode 100644 index 0000000000..b02ce75e70 --- /dev/null +++ b/tests/exhaustive/basic/matrix_of_set_02/expected/model_1_4.eprime @@ -0,0 +1,27 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(1..2), int(1..3)] of bool +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..2), int(1..3)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..2), int(1..3)] of int(1..3) +branching on [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_Occurrence] +such that + and([x_Occurrence[j, i] -> i % 2 = 0 | j : int(1..2), i : int(1..3)]), + and([and([x_ExplicitVarSizeWithFlags_Flags[q3, q4 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q3, q4] < x_ExplicitVarSizeWithFlags_Values[q3, q4 + 1] + | q4 : int(1..2)]) + | q3 : int(1..2)]), + and([and([x_ExplicitVarSizeWithFlags_Flags[q3, q5] = false -> x_ExplicitVarSizeWithFlags_Values[q3, q5] = 1 + | q5 : int(1..3)]) + | q3 : int(1..2)]), + and([and([x_ExplicitVarSizeWithFlags_Flags[q3, q6 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3, q6] + | q6 : int(1..2)]) + | q3 : int(1..2)]), + and([and([x_ExplicitVarSizeWithFlags_Flags[q9, q12] -> x_Occurrence[q9, x_ExplicitVarSizeWithFlags_Values[q9, q12]] + | q12 : int(1..3)]) + /\ + and([x_Occurrence[q9, q13] -> + or([x_ExplicitVarSizeWithFlags_Flags[q9, q15] /\ x_ExplicitVarSizeWithFlags_Values[q9, q15] = q13 + | q15 : int(1..3)]) + | q13 : int(1..3)]) + | q9 : int(1..2)]) + diff --git a/tests/exhaustive/basic/matrix_of_set_02/expected/model_2_1-solution000001.solution b/tests/exhaustive/basic/matrix_of_set_02/expected/model_2_1-solution000001.solution new file mode 100644 index 0000000000..af7c1da5d8 --- /dev/null +++ b/tests/exhaustive/basic/matrix_of_set_02/expected/model_2_1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be [{}, {}; int(1..2)] diff --git a/tests/exhaustive/basic/matrix_of_set_02/expected/model_2_1-solution000002.solution b/tests/exhaustive/basic/matrix_of_set_02/expected/model_2_1-solution000002.solution new file mode 100644 index 0000000000..0b1f00f1a5 --- /dev/null +++ b/tests/exhaustive/basic/matrix_of_set_02/expected/model_2_1-solution000002.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be [{}, {2}; int(1..2)] +$ Visualisation for x +$ +$ 2 + diff --git a/tests/exhaustive/basic/matrix_of_set_02/expected/model_2_1-solution000003.solution b/tests/exhaustive/basic/matrix_of_set_02/expected/model_2_1-solution000003.solution new file mode 100644 index 0000000000..cbfa586d38 --- /dev/null +++ b/tests/exhaustive/basic/matrix_of_set_02/expected/model_2_1-solution000003.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be [{2}, {}; int(1..2)] +$ Visualisation for x +$ 2 +$ + diff --git a/tests/exhaustive/basic/matrix_of_set_02/expected/model_2_1-solution000004.solution b/tests/exhaustive/basic/matrix_of_set_02/expected/model_2_1-solution000004.solution new file mode 100644 index 0000000000..a392d5bbea --- /dev/null +++ b/tests/exhaustive/basic/matrix_of_set_02/expected/model_2_1-solution000004.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be [{2}, {2}; int(1..2)] +$ Visualisation for x +$ 2 +$ 2 + diff --git a/tests/exhaustive/basic/matrix_of_set_02/expected/model_2_1.eprime b/tests/exhaustive/basic/matrix_of_set_02/expected/model_2_1.eprime new file mode 100644 index 0000000000..0bd5a5d8b6 --- /dev/null +++ b/tests/exhaustive/basic/matrix_of_set_02/expected/model_2_1.eprime @@ -0,0 +1,23 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..2), int(1..3)] of int(1..4) +find x_Occurrence: matrix indexed by [int(1..2), int(1..3)] of bool +branching on [x_Occurrence, x_ExplicitVarSizeWithDummy] +such that + and([x_ExplicitVarSizeWithDummy[j, q8] != 4 -> x_ExplicitVarSizeWithDummy[j, q8] % 2 = 0 + | j : int(1..2), q8 : int(1..3)]), + and([and([x_ExplicitVarSizeWithDummy[q1, q2] < x_ExplicitVarSizeWithDummy[q1, q2 + 1] \/ + x_ExplicitVarSizeWithDummy[q1, q2] = 4 + | q2 : int(1..2)]) + | q1 : int(1..2)]), + and([and([x_ExplicitVarSizeWithDummy[q1, q3] = 4 -> x_ExplicitVarSizeWithDummy[q1, q3 + 1] = 4 | q3 : int(1..2)]) + | q1 : int(1..2)]), + and([and([x_Occurrence[q9, q11] -> + or([x_ExplicitVarSizeWithDummy[q9, q13] != 4 /\ x_ExplicitVarSizeWithDummy[q9, q13] = q11 + | q13 : int(1..3)]) + | q11 : int(1..3)]) + /\ + and([x_ExplicitVarSizeWithDummy[q9, q15] != 4 -> x_Occurrence[q9, x_ExplicitVarSizeWithDummy[q9, q15]] + | q15 : int(1..3)]) + | q9 : int(1..2)]) + diff --git a/tests/exhaustive/basic/matrix_of_set_02/expected/model_2_2-solution000001.solution b/tests/exhaustive/basic/matrix_of_set_02/expected/model_2_2-solution000001.solution new file mode 100644 index 0000000000..a392d5bbea --- /dev/null +++ b/tests/exhaustive/basic/matrix_of_set_02/expected/model_2_2-solution000001.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be [{2}, {2}; int(1..2)] +$ Visualisation for x +$ 2 +$ 2 + diff --git a/tests/exhaustive/basic/matrix_of_set_02/expected/model_2_2-solution000002.solution b/tests/exhaustive/basic/matrix_of_set_02/expected/model_2_2-solution000002.solution new file mode 100644 index 0000000000..cbfa586d38 --- /dev/null +++ b/tests/exhaustive/basic/matrix_of_set_02/expected/model_2_2-solution000002.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be [{2}, {}; int(1..2)] +$ Visualisation for x +$ 2 +$ + diff --git a/tests/exhaustive/basic/matrix_of_set_02/expected/model_2_2-solution000003.solution b/tests/exhaustive/basic/matrix_of_set_02/expected/model_2_2-solution000003.solution new file mode 100644 index 0000000000..0b1f00f1a5 --- /dev/null +++ b/tests/exhaustive/basic/matrix_of_set_02/expected/model_2_2-solution000003.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be [{}, {2}; int(1..2)] +$ Visualisation for x +$ +$ 2 + diff --git a/tests/exhaustive/basic/matrix_of_set_02/expected/model_2_2-solution000004.solution b/tests/exhaustive/basic/matrix_of_set_02/expected/model_2_2-solution000004.solution new file mode 100644 index 0000000000..af7c1da5d8 --- /dev/null +++ b/tests/exhaustive/basic/matrix_of_set_02/expected/model_2_2-solution000004.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be [{}, {}; int(1..2)] diff --git a/tests/exhaustive/basic/matrix_of_set_02/expected/model_2_2.eprime b/tests/exhaustive/basic/matrix_of_set_02/expected/model_2_2.eprime new file mode 100644 index 0000000000..fea6c8a28f --- /dev/null +++ b/tests/exhaustive/basic/matrix_of_set_02/expected/model_2_2.eprime @@ -0,0 +1,14 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..2), int(1..3)] of int(1..4) +branching on [x_ExplicitVarSizeWithDummy] +such that + and([x_ExplicitVarSizeWithDummy[j, q6] != 4 -> x_ExplicitVarSizeWithDummy[j, q6] % 2 = 0 + | j : int(1..2), q6 : int(1..3)]), + and([and([x_ExplicitVarSizeWithDummy[q1, q2] < x_ExplicitVarSizeWithDummy[q1, q2 + 1] \/ + x_ExplicitVarSizeWithDummy[q1, q2] = 4 + | q2 : int(1..2)]) + | q1 : int(1..2)]), + and([and([x_ExplicitVarSizeWithDummy[q1, q3] = 4 -> x_ExplicitVarSizeWithDummy[q1, q3 + 1] = 4 | q3 : int(1..2)]) + | q1 : int(1..2)]) + diff --git a/tests/exhaustive/basic/matrix_of_set_02/expected/model_2_3-solution000001.solution b/tests/exhaustive/basic/matrix_of_set_02/expected/model_2_3-solution000001.solution new file mode 100644 index 0000000000..af7c1da5d8 --- /dev/null +++ b/tests/exhaustive/basic/matrix_of_set_02/expected/model_2_3-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be [{}, {}; int(1..2)] diff --git a/tests/exhaustive/basic/matrix_of_set_02/expected/model_2_3-solution000002.solution b/tests/exhaustive/basic/matrix_of_set_02/expected/model_2_3-solution000002.solution new file mode 100644 index 0000000000..0b1f00f1a5 --- /dev/null +++ b/tests/exhaustive/basic/matrix_of_set_02/expected/model_2_3-solution000002.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be [{}, {2}; int(1..2)] +$ Visualisation for x +$ +$ 2 + diff --git a/tests/exhaustive/basic/matrix_of_set_02/expected/model_2_3-solution000003.solution b/tests/exhaustive/basic/matrix_of_set_02/expected/model_2_3-solution000003.solution new file mode 100644 index 0000000000..cbfa586d38 --- /dev/null +++ b/tests/exhaustive/basic/matrix_of_set_02/expected/model_2_3-solution000003.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be [{2}, {}; int(1..2)] +$ Visualisation for x +$ 2 +$ + diff --git a/tests/exhaustive/basic/matrix_of_set_02/expected/model_2_3-solution000004.solution b/tests/exhaustive/basic/matrix_of_set_02/expected/model_2_3-solution000004.solution new file mode 100644 index 0000000000..a392d5bbea --- /dev/null +++ b/tests/exhaustive/basic/matrix_of_set_02/expected/model_2_3-solution000004.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be [{2}, {2}; int(1..2)] +$ Visualisation for x +$ 2 +$ 2 + diff --git a/tests/exhaustive/basic/matrix_of_set_02/expected/model_2_3.eprime b/tests/exhaustive/basic/matrix_of_set_02/expected/model_2_3.eprime new file mode 100644 index 0000000000..7612f7e6db --- /dev/null +++ b/tests/exhaustive/basic/matrix_of_set_02/expected/model_2_3.eprime @@ -0,0 +1,35 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..2), int(1..3)] of int(1..4) +find x_ExplicitVarSizeWithMarker_Marker: matrix indexed by [int(1..2)] of int(0..3) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..2), int(1..3)] of int(1..3) +branching on [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy] +such that + and([x_ExplicitVarSizeWithDummy[j, q20] != 4 -> x_ExplicitVarSizeWithDummy[j, q20] % 2 = 0 + | j : int(1..2), q20 : int(1..3)]), + and([and([x_ExplicitVarSizeWithDummy[q1, q2] < x_ExplicitVarSizeWithDummy[q1, q2 + 1] \/ + x_ExplicitVarSizeWithDummy[q1, q2] = 4 + | q2 : int(1..2)]) + | q1 : int(1..2)]), + and([and([x_ExplicitVarSizeWithDummy[q1, q3] = 4 -> x_ExplicitVarSizeWithDummy[q1, q3 + 1] = 4 | q3 : int(1..2)]) + | q1 : int(1..2)]), + and([and([q7 + 1 <= x_ExplicitVarSizeWithMarker_Marker[q6] -> + x_ExplicitVarSizeWithMarker_Values[q6, q7] < x_ExplicitVarSizeWithMarker_Values[q6, q7 + 1] + | q7 : int(1..2)]) + | q6 : int(1..2)]), + and([and([q8 > x_ExplicitVarSizeWithMarker_Marker[q6] -> x_ExplicitVarSizeWithMarker_Values[q6, q8] = 1 + | q8 : int(1..3)]) + | q6 : int(1..2)]), + and([and([q13 <= x_ExplicitVarSizeWithMarker_Marker[q10] -> + or([x_ExplicitVarSizeWithDummy[q10, q15] != 4 /\ + x_ExplicitVarSizeWithDummy[q10, q15] = x_ExplicitVarSizeWithMarker_Values[q10, q13] + | q15 : int(1..3)]) + | q13 : int(1..3)]) + /\ + and([x_ExplicitVarSizeWithDummy[q10, q17] != 4 -> + or([q19 <= x_ExplicitVarSizeWithMarker_Marker[q10] /\ + x_ExplicitVarSizeWithMarker_Values[q10, q19] = x_ExplicitVarSizeWithDummy[q10, q17] + | q19 : int(1..3)]) + | q17 : int(1..3)]) + | q10 : int(1..2)]) + diff --git a/tests/exhaustive/basic/matrix_of_set_02/expected/model_2_4-solution000001.solution b/tests/exhaustive/basic/matrix_of_set_02/expected/model_2_4-solution000001.solution new file mode 100644 index 0000000000..af7c1da5d8 --- /dev/null +++ b/tests/exhaustive/basic/matrix_of_set_02/expected/model_2_4-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be [{}, {}; int(1..2)] diff --git a/tests/exhaustive/basic/matrix_of_set_02/expected/model_2_4-solution000002.solution b/tests/exhaustive/basic/matrix_of_set_02/expected/model_2_4-solution000002.solution new file mode 100644 index 0000000000..0b1f00f1a5 --- /dev/null +++ b/tests/exhaustive/basic/matrix_of_set_02/expected/model_2_4-solution000002.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be [{}, {2}; int(1..2)] +$ Visualisation for x +$ +$ 2 + diff --git a/tests/exhaustive/basic/matrix_of_set_02/expected/model_2_4-solution000003.solution b/tests/exhaustive/basic/matrix_of_set_02/expected/model_2_4-solution000003.solution new file mode 100644 index 0000000000..cbfa586d38 --- /dev/null +++ b/tests/exhaustive/basic/matrix_of_set_02/expected/model_2_4-solution000003.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be [{2}, {}; int(1..2)] +$ Visualisation for x +$ 2 +$ + diff --git a/tests/exhaustive/basic/matrix_of_set_02/expected/model_2_4-solution000004.solution b/tests/exhaustive/basic/matrix_of_set_02/expected/model_2_4-solution000004.solution new file mode 100644 index 0000000000..a392d5bbea --- /dev/null +++ b/tests/exhaustive/basic/matrix_of_set_02/expected/model_2_4-solution000004.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be [{2}, {2}; int(1..2)] +$ Visualisation for x +$ 2 +$ 2 + diff --git a/tests/exhaustive/basic/matrix_of_set_02/expected/model_2_4.eprime b/tests/exhaustive/basic/matrix_of_set_02/expected/model_2_4.eprime new file mode 100644 index 0000000000..65e0448bbd --- /dev/null +++ b/tests/exhaustive/basic/matrix_of_set_02/expected/model_2_4.eprime @@ -0,0 +1,38 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..2), int(1..3)] of int(1..4) +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..2), int(1..3)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..2), int(1..3)] of int(1..3) +branching on [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy] +such that + and([x_ExplicitVarSizeWithDummy[j, q22] != 4 -> x_ExplicitVarSizeWithDummy[j, q22] % 2 = 0 + | j : int(1..2), q22 : int(1..3)]), + and([and([x_ExplicitVarSizeWithDummy[q1, q2] < x_ExplicitVarSizeWithDummy[q1, q2 + 1] \/ + x_ExplicitVarSizeWithDummy[q1, q2] = 4 + | q2 : int(1..2)]) + | q1 : int(1..2)]), + and([and([x_ExplicitVarSizeWithDummy[q1, q3] = 4 -> x_ExplicitVarSizeWithDummy[q1, q3 + 1] = 4 | q3 : int(1..2)]) + | q1 : int(1..2)]), + and([and([x_ExplicitVarSizeWithFlags_Flags[q6, q7 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q6, q7] < x_ExplicitVarSizeWithFlags_Values[q6, q7 + 1] + | q7 : int(1..2)]) + | q6 : int(1..2)]), + and([and([x_ExplicitVarSizeWithFlags_Flags[q6, q8] = false -> x_ExplicitVarSizeWithFlags_Values[q6, q8] = 1 + | q8 : int(1..3)]) + | q6 : int(1..2)]), + and([and([x_ExplicitVarSizeWithFlags_Flags[q6, q9 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q6, q9] + | q9 : int(1..2)]) + | q6 : int(1..2)]), + and([and([x_ExplicitVarSizeWithFlags_Flags[q12, q15] -> + or([x_ExplicitVarSizeWithDummy[q12, q17] != 4 /\ + x_ExplicitVarSizeWithDummy[q12, q17] = x_ExplicitVarSizeWithFlags_Values[q12, q15] + | q17 : int(1..3)]) + | q15 : int(1..3)]) + /\ + and([x_ExplicitVarSizeWithDummy[q12, q19] != 4 -> + or([x_ExplicitVarSizeWithFlags_Flags[q12, q21] /\ + x_ExplicitVarSizeWithFlags_Values[q12, q21] = x_ExplicitVarSizeWithDummy[q12, q19] + | q21 : int(1..3)]) + | q19 : int(1..3)]) + | q12 : int(1..2)]) + diff --git a/tests/exhaustive/basic/matrix_of_set_02/expected/model_3_1-solution000001.solution b/tests/exhaustive/basic/matrix_of_set_02/expected/model_3_1-solution000001.solution new file mode 100644 index 0000000000..af7c1da5d8 --- /dev/null +++ b/tests/exhaustive/basic/matrix_of_set_02/expected/model_3_1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be [{}, {}; int(1..2)] diff --git a/tests/exhaustive/basic/matrix_of_set_02/expected/model_3_1-solution000002.solution b/tests/exhaustive/basic/matrix_of_set_02/expected/model_3_1-solution000002.solution new file mode 100644 index 0000000000..0b1f00f1a5 --- /dev/null +++ b/tests/exhaustive/basic/matrix_of_set_02/expected/model_3_1-solution000002.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be [{}, {2}; int(1..2)] +$ Visualisation for x +$ +$ 2 + diff --git a/tests/exhaustive/basic/matrix_of_set_02/expected/model_3_1-solution000003.solution b/tests/exhaustive/basic/matrix_of_set_02/expected/model_3_1-solution000003.solution new file mode 100644 index 0000000000..cbfa586d38 --- /dev/null +++ b/tests/exhaustive/basic/matrix_of_set_02/expected/model_3_1-solution000003.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be [{2}, {}; int(1..2)] +$ Visualisation for x +$ 2 +$ + diff --git a/tests/exhaustive/basic/matrix_of_set_02/expected/model_3_1-solution000004.solution b/tests/exhaustive/basic/matrix_of_set_02/expected/model_3_1-solution000004.solution new file mode 100644 index 0000000000..a392d5bbea --- /dev/null +++ b/tests/exhaustive/basic/matrix_of_set_02/expected/model_3_1-solution000004.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be [{2}, {2}; int(1..2)] +$ Visualisation for x +$ 2 +$ 2 + diff --git a/tests/exhaustive/basic/matrix_of_set_02/expected/model_3_1.eprime b/tests/exhaustive/basic/matrix_of_set_02/expected/model_3_1.eprime new file mode 100644 index 0000000000..ea86dd3c32 --- /dev/null +++ b/tests/exhaustive/basic/matrix_of_set_02/expected/model_3_1.eprime @@ -0,0 +1,26 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: matrix indexed by [int(1..2)] of int(0..3) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..2), int(1..3)] of int(1..3) +find x_Occurrence: matrix indexed by [int(1..2), int(1..3)] of bool +branching on [x_Occurrence, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] +such that + and([q7 <= x_ExplicitVarSizeWithMarker_Marker[j] -> x_ExplicitVarSizeWithMarker_Values[j, q7] % 2 = 0 + | j : int(1..2), q7 : int(1..3)]), + and([and([q2 + 1 <= x_ExplicitVarSizeWithMarker_Marker[q1] -> + x_ExplicitVarSizeWithMarker_Values[q1, q2] < x_ExplicitVarSizeWithMarker_Values[q1, q2 + 1] + | q2 : int(1..2)]) + | q1 : int(1..2)]), + and([and([q3 > x_ExplicitVarSizeWithMarker_Marker[q1] -> x_ExplicitVarSizeWithMarker_Values[q1, q3] = 1 + | q3 : int(1..3)]) + | q1 : int(1..2)]), + and([and([x_Occurrence[q8, q10] -> + or([q12 <= x_ExplicitVarSizeWithMarker_Marker[q8] /\ x_ExplicitVarSizeWithMarker_Values[q8, q12] = q10 + | q12 : int(1..3)]) + | q10 : int(1..3)]) + /\ + and([q14 <= x_ExplicitVarSizeWithMarker_Marker[q8] -> + x_Occurrence[q8, x_ExplicitVarSizeWithMarker_Values[q8, q14]] + | q14 : int(1..3)]) + | q8 : int(1..2)]) + diff --git a/tests/exhaustive/basic/matrix_of_set_02/expected/model_3_2-solution000001.solution b/tests/exhaustive/basic/matrix_of_set_02/expected/model_3_2-solution000001.solution new file mode 100644 index 0000000000..a392d5bbea --- /dev/null +++ b/tests/exhaustive/basic/matrix_of_set_02/expected/model_3_2-solution000001.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be [{2}, {2}; int(1..2)] +$ Visualisation for x +$ 2 +$ 2 + diff --git a/tests/exhaustive/basic/matrix_of_set_02/expected/model_3_2-solution000002.solution b/tests/exhaustive/basic/matrix_of_set_02/expected/model_3_2-solution000002.solution new file mode 100644 index 0000000000..cbfa586d38 --- /dev/null +++ b/tests/exhaustive/basic/matrix_of_set_02/expected/model_3_2-solution000002.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be [{2}, {}; int(1..2)] +$ Visualisation for x +$ 2 +$ + diff --git a/tests/exhaustive/basic/matrix_of_set_02/expected/model_3_2-solution000003.solution b/tests/exhaustive/basic/matrix_of_set_02/expected/model_3_2-solution000003.solution new file mode 100644 index 0000000000..0b1f00f1a5 --- /dev/null +++ b/tests/exhaustive/basic/matrix_of_set_02/expected/model_3_2-solution000003.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be [{}, {2}; int(1..2)] +$ Visualisation for x +$ +$ 2 + diff --git a/tests/exhaustive/basic/matrix_of_set_02/expected/model_3_2-solution000004.solution b/tests/exhaustive/basic/matrix_of_set_02/expected/model_3_2-solution000004.solution new file mode 100644 index 0000000000..af7c1da5d8 --- /dev/null +++ b/tests/exhaustive/basic/matrix_of_set_02/expected/model_3_2-solution000004.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be [{}, {}; int(1..2)] diff --git a/tests/exhaustive/basic/matrix_of_set_02/expected/model_3_2.eprime b/tests/exhaustive/basic/matrix_of_set_02/expected/model_3_2.eprime new file mode 100644 index 0000000000..d2dad6cd2c --- /dev/null +++ b/tests/exhaustive/basic/matrix_of_set_02/expected/model_3_2.eprime @@ -0,0 +1,35 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: matrix indexed by [int(1..2)] of int(0..3) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..2), int(1..3)] of int(1..3) +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..2), int(1..3)] of int(1..4) +branching on [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] +such that + and([q20 <= x_ExplicitVarSizeWithMarker_Marker[j] -> x_ExplicitVarSizeWithMarker_Values[j, q20] % 2 = 0 + | j : int(1..2), q20 : int(1..3)]), + and([and([q2 + 1 <= x_ExplicitVarSizeWithMarker_Marker[q1] -> + x_ExplicitVarSizeWithMarker_Values[q1, q2] < x_ExplicitVarSizeWithMarker_Values[q1, q2 + 1] + | q2 : int(1..2)]) + | q1 : int(1..2)]), + and([and([q3 > x_ExplicitVarSizeWithMarker_Marker[q1] -> x_ExplicitVarSizeWithMarker_Values[q1, q3] = 1 + | q3 : int(1..3)]) + | q1 : int(1..2)]), + and([and([x_ExplicitVarSizeWithDummy[q5, q6] < x_ExplicitVarSizeWithDummy[q5, q6 + 1] \/ + x_ExplicitVarSizeWithDummy[q5, q6] = 4 + | q6 : int(1..2)]) + | q5 : int(1..2)]), + and([and([x_ExplicitVarSizeWithDummy[q5, q7] = 4 -> x_ExplicitVarSizeWithDummy[q5, q7 + 1] = 4 | q7 : int(1..2)]) + | q5 : int(1..2)]), + and([and([x_ExplicitVarSizeWithDummy[q10, q13] != 4 -> + or([q15 <= x_ExplicitVarSizeWithMarker_Marker[q10] /\ + x_ExplicitVarSizeWithMarker_Values[q10, q15] = x_ExplicitVarSizeWithDummy[q10, q13] + | q15 : int(1..3)]) + | q13 : int(1..3)]) + /\ + and([q17 <= x_ExplicitVarSizeWithMarker_Marker[q10] -> + or([x_ExplicitVarSizeWithDummy[q10, q19] != 4 /\ + x_ExplicitVarSizeWithDummy[q10, q19] = x_ExplicitVarSizeWithMarker_Values[q10, q17] + | q19 : int(1..3)]) + | q17 : int(1..3)]) + | q10 : int(1..2)]) + diff --git a/tests/exhaustive/basic/matrix_of_set_02/expected/model_3_3-solution000001.solution b/tests/exhaustive/basic/matrix_of_set_02/expected/model_3_3-solution000001.solution new file mode 100644 index 0000000000..af7c1da5d8 --- /dev/null +++ b/tests/exhaustive/basic/matrix_of_set_02/expected/model_3_3-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be [{}, {}; int(1..2)] diff --git a/tests/exhaustive/basic/matrix_of_set_02/expected/model_3_3-solution000002.solution b/tests/exhaustive/basic/matrix_of_set_02/expected/model_3_3-solution000002.solution new file mode 100644 index 0000000000..0b1f00f1a5 --- /dev/null +++ b/tests/exhaustive/basic/matrix_of_set_02/expected/model_3_3-solution000002.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be [{}, {2}; int(1..2)] +$ Visualisation for x +$ +$ 2 + diff --git a/tests/exhaustive/basic/matrix_of_set_02/expected/model_3_3-solution000003.solution b/tests/exhaustive/basic/matrix_of_set_02/expected/model_3_3-solution000003.solution new file mode 100644 index 0000000000..cbfa586d38 --- /dev/null +++ b/tests/exhaustive/basic/matrix_of_set_02/expected/model_3_3-solution000003.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be [{2}, {}; int(1..2)] +$ Visualisation for x +$ 2 +$ + diff --git a/tests/exhaustive/basic/matrix_of_set_02/expected/model_3_3-solution000004.solution b/tests/exhaustive/basic/matrix_of_set_02/expected/model_3_3-solution000004.solution new file mode 100644 index 0000000000..a392d5bbea --- /dev/null +++ b/tests/exhaustive/basic/matrix_of_set_02/expected/model_3_3-solution000004.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be [{2}, {2}; int(1..2)] +$ Visualisation for x +$ 2 +$ 2 + diff --git a/tests/exhaustive/basic/matrix_of_set_02/expected/model_3_3.eprime b/tests/exhaustive/basic/matrix_of_set_02/expected/model_3_3.eprime new file mode 100644 index 0000000000..8fc98162b2 --- /dev/null +++ b/tests/exhaustive/basic/matrix_of_set_02/expected/model_3_3.eprime @@ -0,0 +1,16 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: matrix indexed by [int(1..2)] of int(0..3) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..2), int(1..3)] of int(1..3) +branching on [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] +such that + and([q5 <= x_ExplicitVarSizeWithMarker_Marker[j] -> x_ExplicitVarSizeWithMarker_Values[j, q5] % 2 = 0 + | j : int(1..2), q5 : int(1..3)]), + and([and([q2 + 1 <= x_ExplicitVarSizeWithMarker_Marker[q1] -> + x_ExplicitVarSizeWithMarker_Values[q1, q2] < x_ExplicitVarSizeWithMarker_Values[q1, q2 + 1] + | q2 : int(1..2)]) + | q1 : int(1..2)]), + and([and([q3 > x_ExplicitVarSizeWithMarker_Marker[q1] -> x_ExplicitVarSizeWithMarker_Values[q1, q3] = 1 + | q3 : int(1..3)]) + | q1 : int(1..2)]) + diff --git a/tests/exhaustive/basic/matrix_of_set_02/expected/model_3_4-solution000001.solution b/tests/exhaustive/basic/matrix_of_set_02/expected/model_3_4-solution000001.solution new file mode 100644 index 0000000000..af7c1da5d8 --- /dev/null +++ b/tests/exhaustive/basic/matrix_of_set_02/expected/model_3_4-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be [{}, {}; int(1..2)] diff --git a/tests/exhaustive/basic/matrix_of_set_02/expected/model_3_4-solution000002.solution b/tests/exhaustive/basic/matrix_of_set_02/expected/model_3_4-solution000002.solution new file mode 100644 index 0000000000..0b1f00f1a5 --- /dev/null +++ b/tests/exhaustive/basic/matrix_of_set_02/expected/model_3_4-solution000002.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be [{}, {2}; int(1..2)] +$ Visualisation for x +$ +$ 2 + diff --git a/tests/exhaustive/basic/matrix_of_set_02/expected/model_3_4-solution000003.solution b/tests/exhaustive/basic/matrix_of_set_02/expected/model_3_4-solution000003.solution new file mode 100644 index 0000000000..cbfa586d38 --- /dev/null +++ b/tests/exhaustive/basic/matrix_of_set_02/expected/model_3_4-solution000003.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be [{2}, {}; int(1..2)] +$ Visualisation for x +$ 2 +$ + diff --git a/tests/exhaustive/basic/matrix_of_set_02/expected/model_3_4-solution000004.solution b/tests/exhaustive/basic/matrix_of_set_02/expected/model_3_4-solution000004.solution new file mode 100644 index 0000000000..a392d5bbea --- /dev/null +++ b/tests/exhaustive/basic/matrix_of_set_02/expected/model_3_4-solution000004.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be [{2}, {2}; int(1..2)] +$ Visualisation for x +$ 2 +$ 2 + diff --git a/tests/exhaustive/basic/matrix_of_set_02/expected/model_3_4.eprime b/tests/exhaustive/basic/matrix_of_set_02/expected/model_3_4.eprime new file mode 100644 index 0000000000..ad169aef90 --- /dev/null +++ b/tests/exhaustive/basic/matrix_of_set_02/expected/model_3_4.eprime @@ -0,0 +1,42 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: matrix indexed by [int(1..2)] of int(0..3) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..2), int(1..3)] of int(1..3) +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..2), int(1..3)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..2), int(1..3)] of int(1..3) +branching on + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithMarker_Marker, + x_ExplicitVarSizeWithMarker_Values] +such that + and([q21 <= x_ExplicitVarSizeWithMarker_Marker[j] -> x_ExplicitVarSizeWithMarker_Values[j, q21] % 2 = 0 + | j : int(1..2), q21 : int(1..3)]), + and([and([q2 + 1 <= x_ExplicitVarSizeWithMarker_Marker[q1] -> + x_ExplicitVarSizeWithMarker_Values[q1, q2] < x_ExplicitVarSizeWithMarker_Values[q1, q2 + 1] + | q2 : int(1..2)]) + | q1 : int(1..2)]), + and([and([q3 > x_ExplicitVarSizeWithMarker_Marker[q1] -> x_ExplicitVarSizeWithMarker_Values[q1, q3] = 1 + | q3 : int(1..3)]) + | q1 : int(1..2)]), + and([and([x_ExplicitVarSizeWithFlags_Flags[q5, q6 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q5, q6] < x_ExplicitVarSizeWithFlags_Values[q5, q6 + 1] + | q6 : int(1..2)]) + | q5 : int(1..2)]), + and([and([x_ExplicitVarSizeWithFlags_Flags[q5, q7] = false -> x_ExplicitVarSizeWithFlags_Values[q5, q7] = 1 + | q7 : int(1..3)]) + | q5 : int(1..2)]), + and([and([x_ExplicitVarSizeWithFlags_Flags[q5, q8 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q5, q8] + | q8 : int(1..2)]) + | q5 : int(1..2)]), + and([and([x_ExplicitVarSizeWithFlags_Flags[q11, q14] -> + or([q16 <= x_ExplicitVarSizeWithMarker_Marker[q11] /\ + x_ExplicitVarSizeWithMarker_Values[q11, q16] = x_ExplicitVarSizeWithFlags_Values[q11, q14] + | q16 : int(1..3)]) + | q14 : int(1..3)]) + /\ + and([q18 <= x_ExplicitVarSizeWithMarker_Marker[q11] -> + or([x_ExplicitVarSizeWithFlags_Flags[q11, q20] /\ + x_ExplicitVarSizeWithFlags_Values[q11, q20] = x_ExplicitVarSizeWithMarker_Values[q11, q18] + | q20 : int(1..3)]) + | q18 : int(1..3)]) + | q11 : int(1..2)]) + diff --git a/tests/exhaustive/basic/matrix_of_set_02/expected/model_4_1-solution000001.solution b/tests/exhaustive/basic/matrix_of_set_02/expected/model_4_1-solution000001.solution new file mode 100644 index 0000000000..af7c1da5d8 --- /dev/null +++ b/tests/exhaustive/basic/matrix_of_set_02/expected/model_4_1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be [{}, {}; int(1..2)] diff --git a/tests/exhaustive/basic/matrix_of_set_02/expected/model_4_1-solution000002.solution b/tests/exhaustive/basic/matrix_of_set_02/expected/model_4_1-solution000002.solution new file mode 100644 index 0000000000..0b1f00f1a5 --- /dev/null +++ b/tests/exhaustive/basic/matrix_of_set_02/expected/model_4_1-solution000002.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be [{}, {2}; int(1..2)] +$ Visualisation for x +$ +$ 2 + diff --git a/tests/exhaustive/basic/matrix_of_set_02/expected/model_4_1-solution000003.solution b/tests/exhaustive/basic/matrix_of_set_02/expected/model_4_1-solution000003.solution new file mode 100644 index 0000000000..cbfa586d38 --- /dev/null +++ b/tests/exhaustive/basic/matrix_of_set_02/expected/model_4_1-solution000003.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be [{2}, {}; int(1..2)] +$ Visualisation for x +$ 2 +$ + diff --git a/tests/exhaustive/basic/matrix_of_set_02/expected/model_4_1-solution000004.solution b/tests/exhaustive/basic/matrix_of_set_02/expected/model_4_1-solution000004.solution new file mode 100644 index 0000000000..a392d5bbea --- /dev/null +++ b/tests/exhaustive/basic/matrix_of_set_02/expected/model_4_1-solution000004.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be [{2}, {2}; int(1..2)] +$ Visualisation for x +$ 2 +$ 2 + diff --git a/tests/exhaustive/basic/matrix_of_set_02/expected/model_4_1.eprime b/tests/exhaustive/basic/matrix_of_set_02/expected/model_4_1.eprime new file mode 100644 index 0000000000..7b010d3180 --- /dev/null +++ b/tests/exhaustive/basic/matrix_of_set_02/expected/model_4_1.eprime @@ -0,0 +1,28 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..2), int(1..3)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..2), int(1..3)] of int(1..3) +find x_Occurrence: matrix indexed by [int(1..2), int(1..3)] of bool +branching on [x_Occurrence, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] +such that + and([x_ExplicitVarSizeWithFlags_Flags[j, q16] -> x_ExplicitVarSizeWithFlags_Values[j, q16] % 2 = 0 + | j : int(1..2), q16 : int(1..3)]), + and([and([x_ExplicitVarSizeWithFlags_Flags[q1, q2 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q1, q2] < x_ExplicitVarSizeWithFlags_Values[q1, q2 + 1] + | q2 : int(1..2)]) + | q1 : int(1..2)]), + and([and([x_ExplicitVarSizeWithFlags_Flags[q1, q3] = false -> x_ExplicitVarSizeWithFlags_Values[q1, q3] = 1 + | q3 : int(1..3)]) + | q1 : int(1..2)]), + and([and([x_ExplicitVarSizeWithFlags_Flags[q1, q4 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q1, q4] + | q4 : int(1..2)]) + | q1 : int(1..2)]), + and([and([x_Occurrence[q9, q11] -> + or([x_ExplicitVarSizeWithFlags_Flags[q9, q13] /\ x_ExplicitVarSizeWithFlags_Values[q9, q13] = q11 + | q13 : int(1..3)]) + | q11 : int(1..3)]) + /\ + and([x_ExplicitVarSizeWithFlags_Flags[q9, q15] -> x_Occurrence[q9, x_ExplicitVarSizeWithFlags_Values[q9, q15]] + | q15 : int(1..3)]) + | q9 : int(1..2)]) + diff --git a/tests/exhaustive/basic/matrix_of_set_02/expected/model_4_2-solution000001.solution b/tests/exhaustive/basic/matrix_of_set_02/expected/model_4_2-solution000001.solution new file mode 100644 index 0000000000..a392d5bbea --- /dev/null +++ b/tests/exhaustive/basic/matrix_of_set_02/expected/model_4_2-solution000001.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be [{2}, {2}; int(1..2)] +$ Visualisation for x +$ 2 +$ 2 + diff --git a/tests/exhaustive/basic/matrix_of_set_02/expected/model_4_2-solution000002.solution b/tests/exhaustive/basic/matrix_of_set_02/expected/model_4_2-solution000002.solution new file mode 100644 index 0000000000..cbfa586d38 --- /dev/null +++ b/tests/exhaustive/basic/matrix_of_set_02/expected/model_4_2-solution000002.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be [{2}, {}; int(1..2)] +$ Visualisation for x +$ 2 +$ + diff --git a/tests/exhaustive/basic/matrix_of_set_02/expected/model_4_2-solution000003.solution b/tests/exhaustive/basic/matrix_of_set_02/expected/model_4_2-solution000003.solution new file mode 100644 index 0000000000..0b1f00f1a5 --- /dev/null +++ b/tests/exhaustive/basic/matrix_of_set_02/expected/model_4_2-solution000003.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be [{}, {2}; int(1..2)] +$ Visualisation for x +$ +$ 2 + diff --git a/tests/exhaustive/basic/matrix_of_set_02/expected/model_4_2-solution000004.solution b/tests/exhaustive/basic/matrix_of_set_02/expected/model_4_2-solution000004.solution new file mode 100644 index 0000000000..af7c1da5d8 --- /dev/null +++ b/tests/exhaustive/basic/matrix_of_set_02/expected/model_4_2-solution000004.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be [{}, {}; int(1..2)] diff --git a/tests/exhaustive/basic/matrix_of_set_02/expected/model_4_2.eprime b/tests/exhaustive/basic/matrix_of_set_02/expected/model_4_2.eprime new file mode 100644 index 0000000000..39f8e990fe --- /dev/null +++ b/tests/exhaustive/basic/matrix_of_set_02/expected/model_4_2.eprime @@ -0,0 +1,38 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..2), int(1..3)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..2), int(1..3)] of int(1..3) +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..2), int(1..3)] of int(1..4) +branching on [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] +such that + and([x_ExplicitVarSizeWithFlags_Flags[j, q22] -> x_ExplicitVarSizeWithFlags_Values[j, q22] % 2 = 0 + | j : int(1..2), q22 : int(1..3)]), + and([and([x_ExplicitVarSizeWithFlags_Flags[q1, q2 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q1, q2] < x_ExplicitVarSizeWithFlags_Values[q1, q2 + 1] + | q2 : int(1..2)]) + | q1 : int(1..2)]), + and([and([x_ExplicitVarSizeWithFlags_Flags[q1, q3] = false -> x_ExplicitVarSizeWithFlags_Values[q1, q3] = 1 + | q3 : int(1..3)]) + | q1 : int(1..2)]), + and([and([x_ExplicitVarSizeWithFlags_Flags[q1, q4 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q1, q4] + | q4 : int(1..2)]) + | q1 : int(1..2)]), + and([and([x_ExplicitVarSizeWithDummy[q7, q8] < x_ExplicitVarSizeWithDummy[q7, q8 + 1] \/ + x_ExplicitVarSizeWithDummy[q7, q8] = 4 + | q8 : int(1..2)]) + | q7 : int(1..2)]), + and([and([x_ExplicitVarSizeWithDummy[q7, q9] = 4 -> x_ExplicitVarSizeWithDummy[q7, q9 + 1] = 4 | q9 : int(1..2)]) + | q7 : int(1..2)]), + and([and([x_ExplicitVarSizeWithDummy[q12, q15] != 4 -> + or([x_ExplicitVarSizeWithFlags_Flags[q12, q17] /\ + x_ExplicitVarSizeWithFlags_Values[q12, q17] = x_ExplicitVarSizeWithDummy[q12, q15] + | q17 : int(1..3)]) + | q15 : int(1..3)]) + /\ + and([x_ExplicitVarSizeWithFlags_Flags[q12, q19] -> + or([x_ExplicitVarSizeWithDummy[q12, q21] != 4 /\ + x_ExplicitVarSizeWithDummy[q12, q21] = x_ExplicitVarSizeWithFlags_Values[q12, q19] + | q21 : int(1..3)]) + | q19 : int(1..3)]) + | q12 : int(1..2)]) + diff --git a/tests/exhaustive/basic/matrix_of_set_02/expected/model_4_3-solution000001.solution b/tests/exhaustive/basic/matrix_of_set_02/expected/model_4_3-solution000001.solution new file mode 100644 index 0000000000..af7c1da5d8 --- /dev/null +++ b/tests/exhaustive/basic/matrix_of_set_02/expected/model_4_3-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be [{}, {}; int(1..2)] diff --git a/tests/exhaustive/basic/matrix_of_set_02/expected/model_4_3-solution000002.solution b/tests/exhaustive/basic/matrix_of_set_02/expected/model_4_3-solution000002.solution new file mode 100644 index 0000000000..0b1f00f1a5 --- /dev/null +++ b/tests/exhaustive/basic/matrix_of_set_02/expected/model_4_3-solution000002.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be [{}, {2}; int(1..2)] +$ Visualisation for x +$ +$ 2 + diff --git a/tests/exhaustive/basic/matrix_of_set_02/expected/model_4_3-solution000003.solution b/tests/exhaustive/basic/matrix_of_set_02/expected/model_4_3-solution000003.solution new file mode 100644 index 0000000000..cbfa586d38 --- /dev/null +++ b/tests/exhaustive/basic/matrix_of_set_02/expected/model_4_3-solution000003.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be [{2}, {}; int(1..2)] +$ Visualisation for x +$ 2 +$ + diff --git a/tests/exhaustive/basic/matrix_of_set_02/expected/model_4_3-solution000004.solution b/tests/exhaustive/basic/matrix_of_set_02/expected/model_4_3-solution000004.solution new file mode 100644 index 0000000000..a392d5bbea --- /dev/null +++ b/tests/exhaustive/basic/matrix_of_set_02/expected/model_4_3-solution000004.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be [{2}, {2}; int(1..2)] +$ Visualisation for x +$ 2 +$ 2 + diff --git a/tests/exhaustive/basic/matrix_of_set_02/expected/model_4_3.eprime b/tests/exhaustive/basic/matrix_of_set_02/expected/model_4_3.eprime new file mode 100644 index 0000000000..a67d88de35 --- /dev/null +++ b/tests/exhaustive/basic/matrix_of_set_02/expected/model_4_3.eprime @@ -0,0 +1,42 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..2), int(1..3)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..2), int(1..3)] of int(1..3) +find x_ExplicitVarSizeWithMarker_Marker: matrix indexed by [int(1..2)] of int(0..3) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..2), int(1..3)] of int(1..3) +branching on + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithFlags_Flags, + x_ExplicitVarSizeWithFlags_Values] +such that + and([x_ExplicitVarSizeWithFlags_Flags[j, q21] -> x_ExplicitVarSizeWithFlags_Values[j, q21] % 2 = 0 + | j : int(1..2), q21 : int(1..3)]), + and([and([x_ExplicitVarSizeWithFlags_Flags[q1, q2 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q1, q2] < x_ExplicitVarSizeWithFlags_Values[q1, q2 + 1] + | q2 : int(1..2)]) + | q1 : int(1..2)]), + and([and([x_ExplicitVarSizeWithFlags_Flags[q1, q3] = false -> x_ExplicitVarSizeWithFlags_Values[q1, q3] = 1 + | q3 : int(1..3)]) + | q1 : int(1..2)]), + and([and([x_ExplicitVarSizeWithFlags_Flags[q1, q4 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q1, q4] + | q4 : int(1..2)]) + | q1 : int(1..2)]), + and([and([q8 + 1 <= x_ExplicitVarSizeWithMarker_Marker[q7] -> + x_ExplicitVarSizeWithMarker_Values[q7, q8] < x_ExplicitVarSizeWithMarker_Values[q7, q8 + 1] + | q8 : int(1..2)]) + | q7 : int(1..2)]), + and([and([q9 > x_ExplicitVarSizeWithMarker_Marker[q7] -> x_ExplicitVarSizeWithMarker_Values[q7, q9] = 1 + | q9 : int(1..3)]) + | q7 : int(1..2)]), + and([and([q14 <= x_ExplicitVarSizeWithMarker_Marker[q11] -> + or([x_ExplicitVarSizeWithFlags_Flags[q11, q16] /\ + x_ExplicitVarSizeWithFlags_Values[q11, q16] = x_ExplicitVarSizeWithMarker_Values[q11, q14] + | q16 : int(1..3)]) + | q14 : int(1..3)]) + /\ + and([x_ExplicitVarSizeWithFlags_Flags[q11, q18] -> + or([q20 <= x_ExplicitVarSizeWithMarker_Marker[q11] /\ + x_ExplicitVarSizeWithMarker_Values[q11, q20] = x_ExplicitVarSizeWithFlags_Values[q11, q18] + | q20 : int(1..3)]) + | q18 : int(1..3)]) + | q11 : int(1..2)]) + diff --git a/tests/exhaustive/basic/matrix_of_set_02/expected/model_4_4-solution000001.solution b/tests/exhaustive/basic/matrix_of_set_02/expected/model_4_4-solution000001.solution new file mode 100644 index 0000000000..af7c1da5d8 --- /dev/null +++ b/tests/exhaustive/basic/matrix_of_set_02/expected/model_4_4-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be [{}, {}; int(1..2)] diff --git a/tests/exhaustive/basic/matrix_of_set_02/expected/model_4_4-solution000002.solution b/tests/exhaustive/basic/matrix_of_set_02/expected/model_4_4-solution000002.solution new file mode 100644 index 0000000000..0b1f00f1a5 --- /dev/null +++ b/tests/exhaustive/basic/matrix_of_set_02/expected/model_4_4-solution000002.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be [{}, {2}; int(1..2)] +$ Visualisation for x +$ +$ 2 + diff --git a/tests/exhaustive/basic/matrix_of_set_02/expected/model_4_4-solution000003.solution b/tests/exhaustive/basic/matrix_of_set_02/expected/model_4_4-solution000003.solution new file mode 100644 index 0000000000..cbfa586d38 --- /dev/null +++ b/tests/exhaustive/basic/matrix_of_set_02/expected/model_4_4-solution000003.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be [{2}, {}; int(1..2)] +$ Visualisation for x +$ 2 +$ + diff --git a/tests/exhaustive/basic/matrix_of_set_02/expected/model_4_4-solution000004.solution b/tests/exhaustive/basic/matrix_of_set_02/expected/model_4_4-solution000004.solution new file mode 100644 index 0000000000..a392d5bbea --- /dev/null +++ b/tests/exhaustive/basic/matrix_of_set_02/expected/model_4_4-solution000004.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be [{2}, {2}; int(1..2)] +$ Visualisation for x +$ 2 +$ 2 + diff --git a/tests/exhaustive/basic/matrix_of_set_02/expected/model_4_4.eprime b/tests/exhaustive/basic/matrix_of_set_02/expected/model_4_4.eprime new file mode 100644 index 0000000000..641fab2f7f --- /dev/null +++ b/tests/exhaustive/basic/matrix_of_set_02/expected/model_4_4.eprime @@ -0,0 +1,19 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..2), int(1..3)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..2), int(1..3)] of int(1..3) +branching on [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] +such that + and([x_ExplicitVarSizeWithFlags_Flags[j, q7] -> x_ExplicitVarSizeWithFlags_Values[j, q7] % 2 = 0 + | j : int(1..2), q7 : int(1..3)]), + and([and([x_ExplicitVarSizeWithFlags_Flags[q1, q2 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q1, q2] < x_ExplicitVarSizeWithFlags_Values[q1, q2 + 1] + | q2 : int(1..2)]) + | q1 : int(1..2)]), + and([and([x_ExplicitVarSizeWithFlags_Flags[q1, q3] = false -> x_ExplicitVarSizeWithFlags_Values[q1, q3] = 1 + | q3 : int(1..3)]) + | q1 : int(1..2)]), + and([and([x_ExplicitVarSizeWithFlags_Flags[q1, q4 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q1, q4] + | q4 : int(1..2)]) + | q1 : int(1..2)]) + diff --git a/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_1_1-solution000001.solution b/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_1_1-solution000001.solution new file mode 100644 index 0000000000..88e783b8b0 --- /dev/null +++ b/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_1_1-solution000001.solution @@ -0,0 +1,13 @@ +language Essence 1.3 + +letting x be [[{2}, {2}, {2}; int(1..3)], [{2}, {2}, {2}; int(1..3)]; int(1..2)] +$ Visualisation for x +$ 2 +$ 2 +$ 2 +$ +$ 2 +$ 2 +$ 2 +$ + diff --git a/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_1_1.eprime b/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_1_1.eprime new file mode 100644 index 0000000000..93e46c5fc0 --- /dev/null +++ b/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_1_1.eprime @@ -0,0 +1,8 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(1..2), int(1..3), int(1..3)] of bool +branching on [x_Occurrence] +such that + and([x_Occurrence[j1, j2, i] -> i % 2 = 0 | j1 : int(1..2), j2 : int(1..3), i : int(1..3)]), + and([and([1 <= sum([toInt(x_Occurrence[q1, q2, q3]) | q3 : int(1..3)]) | q2 : int(1..3)]) | q1 : int(1..2)]) + diff --git a/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_1_2-solution000001.solution b/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_1_2-solution000001.solution new file mode 100644 index 0000000000..88e783b8b0 --- /dev/null +++ b/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_1_2-solution000001.solution @@ -0,0 +1,13 @@ +language Essence 1.3 + +letting x be [[{2}, {2}, {2}; int(1..3)], [{2}, {2}, {2}; int(1..3)]; int(1..2)] +$ Visualisation for x +$ 2 +$ 2 +$ 2 +$ +$ 2 +$ 2 +$ 2 +$ + diff --git a/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_1_2.eprime b/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_1_2.eprime new file mode 100644 index 0000000000..d190146044 --- /dev/null +++ b/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_1_2.eprime @@ -0,0 +1,30 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(1..2), int(1..3), int(1..3)] of bool +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..2), int(1..3), int(1..3)] of int(1..4) +branching on [x_ExplicitVarSizeWithDummy, x_Occurrence] +such that + and([x_Occurrence[j1, j2, i] -> i % 2 = 0 | j1 : int(1..2), j2 : int(1..3), i : int(1..3)]), + and([and([1 <= sum([toInt(x_Occurrence[q1, q2, q3]) | q3 : int(1..3)]) | q2 : int(1..3)]) | q1 : int(1..2)]), + and([and([and([x_ExplicitVarSizeWithDummy[q4, q5, q6] < x_ExplicitVarSizeWithDummy[q4, q5, q6 + 1] \/ + x_ExplicitVarSizeWithDummy[q4, q5, q6] = 4 + | q6 : int(1..2)]) + | q5 : int(1..3)]) + | q4 : int(1..2)]), + and([and([and([x_ExplicitVarSizeWithDummy[q4, q5, q7] = 4 -> x_ExplicitVarSizeWithDummy[q4, q5, q7 + 1] = 4 + | q7 : int(1..2)]) + | q5 : int(1..3)]) + | q4 : int(1..2)]), + and([and([1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q4, q5, q8] != 4) | q8 : int(1..3)]) | q5 : int(1..3)]) + | q4 : int(1..2)]), + and([and([and([x_ExplicitVarSizeWithDummy[q10, q12, q15] != 4 -> + x_Occurrence[q10, q12, x_ExplicitVarSizeWithDummy[q10, q12, q15]] + | q15 : int(1..3)]) + /\ + and([x_Occurrence[q10, q12, q16] -> + or([x_ExplicitVarSizeWithDummy[q10, q12, q18] != 4 /\ x_ExplicitVarSizeWithDummy[q10, q12, q18] = q16 + | q18 : int(1..3)]) + | q16 : int(1..3)]) + | q12 : int(1..3)]) + | q10 : int(1..2)]) + diff --git a/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_1_3-solution000001.solution b/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_1_3-solution000001.solution new file mode 100644 index 0000000000..88e783b8b0 --- /dev/null +++ b/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_1_3-solution000001.solution @@ -0,0 +1,13 @@ +language Essence 1.3 + +letting x be [[{2}, {2}, {2}; int(1..3)], [{2}, {2}, {2}; int(1..3)]; int(1..2)] +$ Visualisation for x +$ 2 +$ 2 +$ 2 +$ +$ 2 +$ 2 +$ 2 +$ + diff --git a/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_1_3.eprime b/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_1_3.eprime new file mode 100644 index 0000000000..bf9afdb1e3 --- /dev/null +++ b/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_1_3.eprime @@ -0,0 +1,31 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(1..2), int(1..3), int(1..3)] of bool +find x_ExplicitVarSizeWithMarker_Marker: matrix indexed by [int(1..2), int(1..3)] of int(0..3) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..2), int(1..3), int(1..3)] of int(1..3) +branching on [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_Occurrence] +such that + and([x_Occurrence[j1, j2, i] -> i % 2 = 0 | j1 : int(1..2), j2 : int(1..3), i : int(1..3)]), + and([and([1 <= sum([toInt(x_Occurrence[q1, q2, q3]) | q3 : int(1..3)]) | q2 : int(1..3)]) | q1 : int(1..2)]), + and([and([and([q6 + 1 <= x_ExplicitVarSizeWithMarker_Marker[q4, q5] -> + x_ExplicitVarSizeWithMarker_Values[q4, q5, q6] < x_ExplicitVarSizeWithMarker_Values[q4, q5, q6 + 1] + | q6 : int(1..2)]) + | q5 : int(1..3)]) + | q4 : int(1..2)]), + and([and([and([q7 > x_ExplicitVarSizeWithMarker_Marker[q4, q5] -> x_ExplicitVarSizeWithMarker_Values[q4, q5, q7] = 1 + | q7 : int(1..3)]) + | q5 : int(1..3)]) + | q4 : int(1..2)]), + and([and([1 <= x_ExplicitVarSizeWithMarker_Marker[q4, q5] | q5 : int(1..3)]) | q4 : int(1..2)]), + and([and([and([q14 <= x_ExplicitVarSizeWithMarker_Marker[q9, q11] -> + x_Occurrence[q9, q11, x_ExplicitVarSizeWithMarker_Values[q9, q11, q14]] + | q14 : int(1..3)]) + /\ + and([x_Occurrence[q9, q11, q15] -> + or([q17 <= x_ExplicitVarSizeWithMarker_Marker[q9, q11] /\ + x_ExplicitVarSizeWithMarker_Values[q9, q11, q17] = q15 + | q17 : int(1..3)]) + | q15 : int(1..3)]) + | q11 : int(1..3)]) + | q9 : int(1..2)]) + diff --git a/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_1_4-solution000001.solution b/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_1_4-solution000001.solution new file mode 100644 index 0000000000..88e783b8b0 --- /dev/null +++ b/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_1_4-solution000001.solution @@ -0,0 +1,13 @@ +language Essence 1.3 + +letting x be [[{2}, {2}, {2}; int(1..3)], [{2}, {2}, {2}; int(1..3)]; int(1..2)] +$ Visualisation for x +$ 2 +$ 2 +$ 2 +$ +$ 2 +$ 2 +$ 2 +$ + diff --git a/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_1_4.eprime b/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_1_4.eprime new file mode 100644 index 0000000000..39b0762f3c --- /dev/null +++ b/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_1_4.eprime @@ -0,0 +1,37 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(1..2), int(1..3), int(1..3)] of bool +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..2), int(1..3), int(1..3)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..2), int(1..3), int(1..3)] of int(1..3) +branching on [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_Occurrence] +such that + and([x_Occurrence[j1, j2, i] -> i % 2 = 0 | j1 : int(1..2), j2 : int(1..3), i : int(1..3)]), + and([and([1 <= sum([toInt(x_Occurrence[q1, q2, q3]) | q3 : int(1..3)]) | q2 : int(1..3)]) | q1 : int(1..2)]), + and([and([and([x_ExplicitVarSizeWithFlags_Flags[q4, q5, q6 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q4, q5, q6] < x_ExplicitVarSizeWithFlags_Values[q4, q5, q6 + 1] + | q6 : int(1..2)]) + | q5 : int(1..3)]) + | q4 : int(1..2)]), + and([and([and([x_ExplicitVarSizeWithFlags_Flags[q4, q5, q7] = false -> + x_ExplicitVarSizeWithFlags_Values[q4, q5, q7] = 1 + | q7 : int(1..3)]) + | q5 : int(1..3)]) + | q4 : int(1..2)]), + and([and([and([x_ExplicitVarSizeWithFlags_Flags[q4, q5, q8 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q4, q5, q8] + | q8 : int(1..2)]) + | q5 : int(1..3)]) + | q4 : int(1..2)]), + and([and([1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4, q5, q9]) | q9 : int(1..3)]) | q5 : int(1..3)]) + | q4 : int(1..2)]), + and([and([and([x_ExplicitVarSizeWithFlags_Flags[q11, q13, q16] -> + x_Occurrence[q11, q13, x_ExplicitVarSizeWithFlags_Values[q11, q13, q16]] + | q16 : int(1..3)]) + /\ + and([x_Occurrence[q11, q13, q17] -> + or([x_ExplicitVarSizeWithFlags_Flags[q11, q13, q19] /\ + x_ExplicitVarSizeWithFlags_Values[q11, q13, q19] = q17 + | q19 : int(1..3)]) + | q17 : int(1..3)]) + | q13 : int(1..3)]) + | q11 : int(1..2)]) + diff --git a/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_2_1-solution000001.solution b/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_2_1-solution000001.solution new file mode 100644 index 0000000000..88e783b8b0 --- /dev/null +++ b/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_2_1-solution000001.solution @@ -0,0 +1,13 @@ +language Essence 1.3 + +letting x be [[{2}, {2}, {2}; int(1..3)], [{2}, {2}, {2}; int(1..3)]; int(1..2)] +$ Visualisation for x +$ 2 +$ 2 +$ 2 +$ +$ 2 +$ 2 +$ 2 +$ + diff --git a/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_2_1.eprime b/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_2_1.eprime new file mode 100644 index 0000000000..930a9b9b07 --- /dev/null +++ b/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_2_1.eprime @@ -0,0 +1,31 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..2), int(1..3), int(1..3)] of int(1..4) +find x_Occurrence: matrix indexed by [int(1..2), int(1..3), int(1..3)] of bool +branching on [x_Occurrence, x_ExplicitVarSizeWithDummy] +such that + and([x_ExplicitVarSizeWithDummy[j1, j2, q19] != 4 -> x_ExplicitVarSizeWithDummy[j1, j2, q19] % 2 = 0 + | j1 : int(1..2), j2 : int(1..3), q19 : int(1..3)]), + and([and([and([x_ExplicitVarSizeWithDummy[q1, q2, q3] < x_ExplicitVarSizeWithDummy[q1, q2, q3 + 1] \/ + x_ExplicitVarSizeWithDummy[q1, q2, q3] = 4 + | q3 : int(1..2)]) + | q2 : int(1..3)]) + | q1 : int(1..2)]), + and([and([and([x_ExplicitVarSizeWithDummy[q1, q2, q4] = 4 -> x_ExplicitVarSizeWithDummy[q1, q2, q4 + 1] = 4 + | q4 : int(1..2)]) + | q2 : int(1..3)]) + | q1 : int(1..2)]), + and([and([1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q1, q2, q5] != 4) | q5 : int(1..3)]) | q2 : int(1..3)]) + | q1 : int(1..2)]), + and([and([1 <= sum([toInt(x_Occurrence[q7, q8, q9]) | q9 : int(1..3)]) | q8 : int(1..3)]) | q7 : int(1..2)]), + and([and([and([x_Occurrence[q10, q12, q14] -> + or([x_ExplicitVarSizeWithDummy[q10, q12, q16] != 4 /\ x_ExplicitVarSizeWithDummy[q10, q12, q16] = q14 + | q16 : int(1..3)]) + | q14 : int(1..3)]) + /\ + and([x_ExplicitVarSizeWithDummy[q10, q12, q18] != 4 -> + x_Occurrence[q10, q12, x_ExplicitVarSizeWithDummy[q10, q12, q18]] + | q18 : int(1..3)]) + | q12 : int(1..3)]) + | q10 : int(1..2)]) + diff --git a/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_2_2-solution000001.solution b/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_2_2-solution000001.solution new file mode 100644 index 0000000000..88e783b8b0 --- /dev/null +++ b/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_2_2-solution000001.solution @@ -0,0 +1,13 @@ +language Essence 1.3 + +letting x be [[{2}, {2}, {2}; int(1..3)], [{2}, {2}, {2}; int(1..3)]; int(1..2)] +$ Visualisation for x +$ 2 +$ 2 +$ 2 +$ +$ 2 +$ 2 +$ 2 +$ + diff --git a/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_2_2.eprime b/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_2_2.eprime new file mode 100644 index 0000000000..e236ad9239 --- /dev/null +++ b/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_2_2.eprime @@ -0,0 +1,19 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..2), int(1..3), int(1..3)] of int(1..4) +branching on [x_ExplicitVarSizeWithDummy] +such that + and([x_ExplicitVarSizeWithDummy[j1, j2, q7] != 4 -> x_ExplicitVarSizeWithDummy[j1, j2, q7] % 2 = 0 + | j1 : int(1..2), j2 : int(1..3), q7 : int(1..3)]), + and([and([and([x_ExplicitVarSizeWithDummy[q1, q2, q3] < x_ExplicitVarSizeWithDummy[q1, q2, q3 + 1] \/ + x_ExplicitVarSizeWithDummy[q1, q2, q3] = 4 + | q3 : int(1..2)]) + | q2 : int(1..3)]) + | q1 : int(1..2)]), + and([and([and([x_ExplicitVarSizeWithDummy[q1, q2, q4] = 4 -> x_ExplicitVarSizeWithDummy[q1, q2, q4 + 1] = 4 + | q4 : int(1..2)]) + | q2 : int(1..3)]) + | q1 : int(1..2)]), + and([and([1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q1, q2, q5] != 4) | q5 : int(1..3)]) | q2 : int(1..3)]) + | q1 : int(1..2)]) + diff --git a/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_2_3-solution000001.solution b/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_2_3-solution000001.solution new file mode 100644 index 0000000000..88e783b8b0 --- /dev/null +++ b/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_2_3-solution000001.solution @@ -0,0 +1,13 @@ +language Essence 1.3 + +letting x be [[{2}, {2}, {2}; int(1..3)], [{2}, {2}, {2}; int(1..3)]; int(1..2)] +$ Visualisation for x +$ 2 +$ 2 +$ 2 +$ +$ 2 +$ 2 +$ 2 +$ + diff --git a/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_2_3.eprime b/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_2_3.eprime new file mode 100644 index 0000000000..7920954488 --- /dev/null +++ b/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_2_3.eprime @@ -0,0 +1,45 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..2), int(1..3), int(1..3)] of int(1..4) +find x_ExplicitVarSizeWithMarker_Marker: matrix indexed by [int(1..2), int(1..3)] of int(0..3) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..2), int(1..3), int(1..3)] of int(1..3) +branching on [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy] +such that + and([x_ExplicitVarSizeWithDummy[j1, j2, q24] != 4 -> x_ExplicitVarSizeWithDummy[j1, j2, q24] % 2 = 0 + | j1 : int(1..2), j2 : int(1..3), q24 : int(1..3)]), + and([and([and([x_ExplicitVarSizeWithDummy[q1, q2, q3] < x_ExplicitVarSizeWithDummy[q1, q2, q3 + 1] \/ + x_ExplicitVarSizeWithDummy[q1, q2, q3] = 4 + | q3 : int(1..2)]) + | q2 : int(1..3)]) + | q1 : int(1..2)]), + and([and([and([x_ExplicitVarSizeWithDummy[q1, q2, q4] = 4 -> x_ExplicitVarSizeWithDummy[q1, q2, q4 + 1] = 4 + | q4 : int(1..2)]) + | q2 : int(1..3)]) + | q1 : int(1..2)]), + and([and([1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q1, q2, q5] != 4) | q5 : int(1..3)]) | q2 : int(1..3)]) + | q1 : int(1..2)]), + and([and([and([q9 + 1 <= x_ExplicitVarSizeWithMarker_Marker[q7, q8] -> + x_ExplicitVarSizeWithMarker_Values[q7, q8, q9] < x_ExplicitVarSizeWithMarker_Values[q7, q8, q9 + 1] + | q9 : int(1..2)]) + | q8 : int(1..3)]) + | q7 : int(1..2)]), + and([and([and([q10 > x_ExplicitVarSizeWithMarker_Marker[q7, q8] -> + x_ExplicitVarSizeWithMarker_Values[q7, q8, q10] = 1 + | q10 : int(1..3)]) + | q8 : int(1..3)]) + | q7 : int(1..2)]), + and([and([1 <= x_ExplicitVarSizeWithMarker_Marker[q7, q8] | q8 : int(1..3)]) | q7 : int(1..2)]), + and([and([and([q17 <= x_ExplicitVarSizeWithMarker_Marker[q12, q14] -> + or([x_ExplicitVarSizeWithDummy[q12, q14, q19] != 4 /\ + x_ExplicitVarSizeWithDummy[q12, q14, q19] = x_ExplicitVarSizeWithMarker_Values[q12, q14, q17] + | q19 : int(1..3)]) + | q17 : int(1..3)]) + /\ + and([x_ExplicitVarSizeWithDummy[q12, q14, q21] != 4 -> + or([q23 <= x_ExplicitVarSizeWithMarker_Marker[q12, q14] /\ + x_ExplicitVarSizeWithMarker_Values[q12, q14, q23] = x_ExplicitVarSizeWithDummy[q12, q14, q21] + | q23 : int(1..3)]) + | q21 : int(1..3)]) + | q14 : int(1..3)]) + | q12 : int(1..2)]) + diff --git a/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_2_4-solution000001.solution b/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_2_4-solution000001.solution new file mode 100644 index 0000000000..88e783b8b0 --- /dev/null +++ b/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_2_4-solution000001.solution @@ -0,0 +1,13 @@ +language Essence 1.3 + +letting x be [[{2}, {2}, {2}; int(1..3)], [{2}, {2}, {2}; int(1..3)]; int(1..2)] +$ Visualisation for x +$ 2 +$ 2 +$ 2 +$ +$ 2 +$ 2 +$ 2 +$ + diff --git a/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_2_4.eprime b/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_2_4.eprime new file mode 100644 index 0000000000..7ea793896c --- /dev/null +++ b/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_2_4.eprime @@ -0,0 +1,50 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..2), int(1..3), int(1..3)] of int(1..4) +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..2), int(1..3), int(1..3)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..2), int(1..3), int(1..3)] of int(1..3) +branching on [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy] +such that + and([x_ExplicitVarSizeWithDummy[j1, j2, q26] != 4 -> x_ExplicitVarSizeWithDummy[j1, j2, q26] % 2 = 0 + | j1 : int(1..2), j2 : int(1..3), q26 : int(1..3)]), + and([and([and([x_ExplicitVarSizeWithDummy[q1, q2, q3] < x_ExplicitVarSizeWithDummy[q1, q2, q3 + 1] \/ + x_ExplicitVarSizeWithDummy[q1, q2, q3] = 4 + | q3 : int(1..2)]) + | q2 : int(1..3)]) + | q1 : int(1..2)]), + and([and([and([x_ExplicitVarSizeWithDummy[q1, q2, q4] = 4 -> x_ExplicitVarSizeWithDummy[q1, q2, q4 + 1] = 4 + | q4 : int(1..2)]) + | q2 : int(1..3)]) + | q1 : int(1..2)]), + and([and([1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q1, q2, q5] != 4) | q5 : int(1..3)]) | q2 : int(1..3)]) + | q1 : int(1..2)]), + and([and([and([x_ExplicitVarSizeWithFlags_Flags[q7, q8, q9 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q7, q8, q9] < x_ExplicitVarSizeWithFlags_Values[q7, q8, q9 + 1] + | q9 : int(1..2)]) + | q8 : int(1..3)]) + | q7 : int(1..2)]), + and([and([and([x_ExplicitVarSizeWithFlags_Flags[q7, q8, q10] = false -> + x_ExplicitVarSizeWithFlags_Values[q7, q8, q10] = 1 + | q10 : int(1..3)]) + | q8 : int(1..3)]) + | q7 : int(1..2)]), + and([and([and([x_ExplicitVarSizeWithFlags_Flags[q7, q8, q11 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q7, q8, q11] + | q11 : int(1..2)]) + | q8 : int(1..3)]) + | q7 : int(1..2)]), + and([and([1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q7, q8, q12]) | q12 : int(1..3)]) | q8 : int(1..3)]) + | q7 : int(1..2)]), + and([and([and([x_ExplicitVarSizeWithFlags_Flags[q14, q16, q19] -> + or([x_ExplicitVarSizeWithDummy[q14, q16, q21] != 4 /\ + x_ExplicitVarSizeWithDummy[q14, q16, q21] = x_ExplicitVarSizeWithFlags_Values[q14, q16, q19] + | q21 : int(1..3)]) + | q19 : int(1..3)]) + /\ + and([x_ExplicitVarSizeWithDummy[q14, q16, q23] != 4 -> + or([x_ExplicitVarSizeWithFlags_Flags[q14, q16, q25] /\ + x_ExplicitVarSizeWithFlags_Values[q14, q16, q25] = x_ExplicitVarSizeWithDummy[q14, q16, q23] + | q25 : int(1..3)]) + | q23 : int(1..3)]) + | q16 : int(1..3)]) + | q14 : int(1..2)]) + diff --git a/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_3_1-solution000001.solution b/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_3_1-solution000001.solution new file mode 100644 index 0000000000..88e783b8b0 --- /dev/null +++ b/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_3_1-solution000001.solution @@ -0,0 +1,13 @@ +language Essence 1.3 + +letting x be [[{2}, {2}, {2}; int(1..3)], [{2}, {2}, {2}; int(1..3)]; int(1..2)] +$ Visualisation for x +$ 2 +$ 2 +$ 2 +$ +$ 2 +$ 2 +$ 2 +$ + diff --git a/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_3_1.eprime b/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_3_1.eprime new file mode 100644 index 0000000000..8512304454 --- /dev/null +++ b/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_3_1.eprime @@ -0,0 +1,32 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: matrix indexed by [int(1..2), int(1..3)] of int(0..3) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..2), int(1..3), int(1..3)] of int(1..3) +find x_Occurrence: matrix indexed by [int(1..2), int(1..3), int(1..3)] of bool +branching on [x_Occurrence, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] +such that + and([q18 <= x_ExplicitVarSizeWithMarker_Marker[j1, j2] -> x_ExplicitVarSizeWithMarker_Values[j1, j2, q18] % 2 = 0 + | j1 : int(1..2), j2 : int(1..3), q18 : int(1..3)]), + and([and([and([q3 + 1 <= x_ExplicitVarSizeWithMarker_Marker[q1, q2] -> + x_ExplicitVarSizeWithMarker_Values[q1, q2, q3] < x_ExplicitVarSizeWithMarker_Values[q1, q2, q3 + 1] + | q3 : int(1..2)]) + | q2 : int(1..3)]) + | q1 : int(1..2)]), + and([and([and([q4 > x_ExplicitVarSizeWithMarker_Marker[q1, q2] -> x_ExplicitVarSizeWithMarker_Values[q1, q2, q4] = 1 + | q4 : int(1..3)]) + | q2 : int(1..3)]) + | q1 : int(1..2)]), + and([and([1 <= x_ExplicitVarSizeWithMarker_Marker[q1, q2] | q2 : int(1..3)]) | q1 : int(1..2)]), + and([and([1 <= sum([toInt(x_Occurrence[q6, q7, q8]) | q8 : int(1..3)]) | q7 : int(1..3)]) | q6 : int(1..2)]), + and([and([and([x_Occurrence[q9, q11, q13] -> + or([q15 <= x_ExplicitVarSizeWithMarker_Marker[q9, q11] /\ + x_ExplicitVarSizeWithMarker_Values[q9, q11, q15] = q13 + | q15 : int(1..3)]) + | q13 : int(1..3)]) + /\ + and([q17 <= x_ExplicitVarSizeWithMarker_Marker[q9, q11] -> + x_Occurrence[q9, q11, x_ExplicitVarSizeWithMarker_Values[q9, q11, q17]] + | q17 : int(1..3)]) + | q11 : int(1..3)]) + | q9 : int(1..2)]) + diff --git a/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_3_2-solution000001.solution b/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_3_2-solution000001.solution new file mode 100644 index 0000000000..88e783b8b0 --- /dev/null +++ b/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_3_2-solution000001.solution @@ -0,0 +1,13 @@ +language Essence 1.3 + +letting x be [[{2}, {2}, {2}; int(1..3)], [{2}, {2}, {2}; int(1..3)]; int(1..2)] +$ Visualisation for x +$ 2 +$ 2 +$ 2 +$ +$ 2 +$ 2 +$ 2 +$ + diff --git a/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_3_2.eprime b/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_3_2.eprime new file mode 100644 index 0000000000..1d07948b63 --- /dev/null +++ b/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_3_2.eprime @@ -0,0 +1,44 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: matrix indexed by [int(1..2), int(1..3)] of int(0..3) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..2), int(1..3), int(1..3)] of int(1..3) +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..2), int(1..3), int(1..3)] of int(1..4) +branching on [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] +such that + and([q24 <= x_ExplicitVarSizeWithMarker_Marker[j1, j2] -> x_ExplicitVarSizeWithMarker_Values[j1, j2, q24] % 2 = 0 + | j1 : int(1..2), j2 : int(1..3), q24 : int(1..3)]), + and([and([and([q3 + 1 <= x_ExplicitVarSizeWithMarker_Marker[q1, q2] -> + x_ExplicitVarSizeWithMarker_Values[q1, q2, q3] < x_ExplicitVarSizeWithMarker_Values[q1, q2, q3 + 1] + | q3 : int(1..2)]) + | q2 : int(1..3)]) + | q1 : int(1..2)]), + and([and([and([q4 > x_ExplicitVarSizeWithMarker_Marker[q1, q2] -> x_ExplicitVarSizeWithMarker_Values[q1, q2, q4] = 1 + | q4 : int(1..3)]) + | q2 : int(1..3)]) + | q1 : int(1..2)]), + and([and([1 <= x_ExplicitVarSizeWithMarker_Marker[q1, q2] | q2 : int(1..3)]) | q1 : int(1..2)]), + and([and([and([x_ExplicitVarSizeWithDummy[q6, q7, q8] < x_ExplicitVarSizeWithDummy[q6, q7, q8 + 1] \/ + x_ExplicitVarSizeWithDummy[q6, q7, q8] = 4 + | q8 : int(1..2)]) + | q7 : int(1..3)]) + | q6 : int(1..2)]), + and([and([and([x_ExplicitVarSizeWithDummy[q6, q7, q9] = 4 -> x_ExplicitVarSizeWithDummy[q6, q7, q9 + 1] = 4 + | q9 : int(1..2)]) + | q7 : int(1..3)]) + | q6 : int(1..2)]), + and([and([1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q6, q7, q10] != 4) | q10 : int(1..3)]) | q7 : int(1..3)]) + | q6 : int(1..2)]), + and([and([and([x_ExplicitVarSizeWithDummy[q12, q14, q17] != 4 -> + or([q19 <= x_ExplicitVarSizeWithMarker_Marker[q12, q14] /\ + x_ExplicitVarSizeWithMarker_Values[q12, q14, q19] = x_ExplicitVarSizeWithDummy[q12, q14, q17] + | q19 : int(1..3)]) + | q17 : int(1..3)]) + /\ + and([q21 <= x_ExplicitVarSizeWithMarker_Marker[q12, q14] -> + or([x_ExplicitVarSizeWithDummy[q12, q14, q23] != 4 /\ + x_ExplicitVarSizeWithDummy[q12, q14, q23] = x_ExplicitVarSizeWithMarker_Values[q12, q14, q21] + | q23 : int(1..3)]) + | q21 : int(1..3)]) + | q14 : int(1..3)]) + | q12 : int(1..2)]) + diff --git a/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_3_3-solution000001.solution b/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_3_3-solution000001.solution new file mode 100644 index 0000000000..88e783b8b0 --- /dev/null +++ b/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_3_3-solution000001.solution @@ -0,0 +1,13 @@ +language Essence 1.3 + +letting x be [[{2}, {2}, {2}; int(1..3)], [{2}, {2}, {2}; int(1..3)]; int(1..2)] +$ Visualisation for x +$ 2 +$ 2 +$ 2 +$ +$ 2 +$ 2 +$ 2 +$ + diff --git a/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_3_3.eprime b/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_3_3.eprime new file mode 100644 index 0000000000..470bd34100 --- /dev/null +++ b/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_3_3.eprime @@ -0,0 +1,19 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: matrix indexed by [int(1..2), int(1..3)] of int(0..3) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..2), int(1..3), int(1..3)] of int(1..3) +branching on [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] +such that + and([q6 <= x_ExplicitVarSizeWithMarker_Marker[j1, j2] -> x_ExplicitVarSizeWithMarker_Values[j1, j2, q6] % 2 = 0 + | j1 : int(1..2), j2 : int(1..3), q6 : int(1..3)]), + and([and([and([q3 + 1 <= x_ExplicitVarSizeWithMarker_Marker[q1, q2] -> + x_ExplicitVarSizeWithMarker_Values[q1, q2, q3] < x_ExplicitVarSizeWithMarker_Values[q1, q2, q3 + 1] + | q3 : int(1..2)]) + | q2 : int(1..3)]) + | q1 : int(1..2)]), + and([and([and([q4 > x_ExplicitVarSizeWithMarker_Marker[q1, q2] -> x_ExplicitVarSizeWithMarker_Values[q1, q2, q4] = 1 + | q4 : int(1..3)]) + | q2 : int(1..3)]) + | q1 : int(1..2)]), + and([and([1 <= x_ExplicitVarSizeWithMarker_Marker[q1, q2] | q2 : int(1..3)]) | q1 : int(1..2)]) + diff --git a/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_3_4-solution000001.solution b/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_3_4-solution000001.solution new file mode 100644 index 0000000000..88e783b8b0 --- /dev/null +++ b/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_3_4-solution000001.solution @@ -0,0 +1,13 @@ +language Essence 1.3 + +letting x be [[{2}, {2}, {2}; int(1..3)], [{2}, {2}, {2}; int(1..3)]; int(1..2)] +$ Visualisation for x +$ 2 +$ 2 +$ 2 +$ +$ 2 +$ 2 +$ 2 +$ + diff --git a/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_3_4.eprime b/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_3_4.eprime new file mode 100644 index 0000000000..3685e9f034 --- /dev/null +++ b/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_3_4.eprime @@ -0,0 +1,54 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: matrix indexed by [int(1..2), int(1..3)] of int(0..3) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..2), int(1..3), int(1..3)] of int(1..3) +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..2), int(1..3), int(1..3)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..2), int(1..3), int(1..3)] of int(1..3) +branching on + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithMarker_Marker, + x_ExplicitVarSizeWithMarker_Values] +such that + and([q25 <= x_ExplicitVarSizeWithMarker_Marker[j1, j2] -> x_ExplicitVarSizeWithMarker_Values[j1, j2, q25] % 2 = 0 + | j1 : int(1..2), j2 : int(1..3), q25 : int(1..3)]), + and([and([and([q3 + 1 <= x_ExplicitVarSizeWithMarker_Marker[q1, q2] -> + x_ExplicitVarSizeWithMarker_Values[q1, q2, q3] < x_ExplicitVarSizeWithMarker_Values[q1, q2, q3 + 1] + | q3 : int(1..2)]) + | q2 : int(1..3)]) + | q1 : int(1..2)]), + and([and([and([q4 > x_ExplicitVarSizeWithMarker_Marker[q1, q2] -> x_ExplicitVarSizeWithMarker_Values[q1, q2, q4] = 1 + | q4 : int(1..3)]) + | q2 : int(1..3)]) + | q1 : int(1..2)]), + and([and([1 <= x_ExplicitVarSizeWithMarker_Marker[q1, q2] | q2 : int(1..3)]) | q1 : int(1..2)]), + and([and([and([x_ExplicitVarSizeWithFlags_Flags[q6, q7, q8 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q6, q7, q8] < x_ExplicitVarSizeWithFlags_Values[q6, q7, q8 + 1] + | q8 : int(1..2)]) + | q7 : int(1..3)]) + | q6 : int(1..2)]), + and([and([and([x_ExplicitVarSizeWithFlags_Flags[q6, q7, q9] = false -> + x_ExplicitVarSizeWithFlags_Values[q6, q7, q9] = 1 + | q9 : int(1..3)]) + | q7 : int(1..3)]) + | q6 : int(1..2)]), + and([and([and([x_ExplicitVarSizeWithFlags_Flags[q6, q7, q10 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q6, q7, q10] + | q10 : int(1..2)]) + | q7 : int(1..3)]) + | q6 : int(1..2)]), + and([and([1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q6, q7, q11]) | q11 : int(1..3)]) | q7 : int(1..3)]) + | q6 : int(1..2)]), + and([and([and([x_ExplicitVarSizeWithFlags_Flags[q13, q15, q18] -> + or([q20 <= x_ExplicitVarSizeWithMarker_Marker[q13, q15] /\ + x_ExplicitVarSizeWithMarker_Values[q13, q15, q20] = + x_ExplicitVarSizeWithFlags_Values[q13, q15, q18] + | q20 : int(1..3)]) + | q18 : int(1..3)]) + /\ + and([q22 <= x_ExplicitVarSizeWithMarker_Marker[q13, q15] -> + or([x_ExplicitVarSizeWithFlags_Flags[q13, q15, q24] /\ + x_ExplicitVarSizeWithFlags_Values[q13, q15, q24] = + x_ExplicitVarSizeWithMarker_Values[q13, q15, q22] + | q24 : int(1..3)]) + | q22 : int(1..3)]) + | q15 : int(1..3)]) + | q13 : int(1..2)]) + diff --git a/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_4_1-solution000001.solution b/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_4_1-solution000001.solution new file mode 100644 index 0000000000..88e783b8b0 --- /dev/null +++ b/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_4_1-solution000001.solution @@ -0,0 +1,13 @@ +language Essence 1.3 + +letting x be [[{2}, {2}, {2}; int(1..3)], [{2}, {2}, {2}; int(1..3)]; int(1..2)] +$ Visualisation for x +$ 2 +$ 2 +$ 2 +$ +$ 2 +$ 2 +$ 2 +$ + diff --git a/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_4_1.eprime b/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_4_1.eprime new file mode 100644 index 0000000000..af1e5066df --- /dev/null +++ b/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_4_1.eprime @@ -0,0 +1,38 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..2), int(1..3), int(1..3)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..2), int(1..3), int(1..3)] of int(1..3) +find x_Occurrence: matrix indexed by [int(1..2), int(1..3), int(1..3)] of bool +branching on [x_Occurrence, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] +such that + and([x_ExplicitVarSizeWithFlags_Flags[j1, j2, q20] -> x_ExplicitVarSizeWithFlags_Values[j1, j2, q20] % 2 = 0 + | j1 : int(1..2), j2 : int(1..3), q20 : int(1..3)]), + and([and([and([x_ExplicitVarSizeWithFlags_Flags[q1, q2, q3 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q1, q2, q3] < x_ExplicitVarSizeWithFlags_Values[q1, q2, q3 + 1] + | q3 : int(1..2)]) + | q2 : int(1..3)]) + | q1 : int(1..2)]), + and([and([and([x_ExplicitVarSizeWithFlags_Flags[q1, q2, q4] = false -> + x_ExplicitVarSizeWithFlags_Values[q1, q2, q4] = 1 + | q4 : int(1..3)]) + | q2 : int(1..3)]) + | q1 : int(1..2)]), + and([and([and([x_ExplicitVarSizeWithFlags_Flags[q1, q2, q5 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q1, q2, q5] + | q5 : int(1..2)]) + | q2 : int(1..3)]) + | q1 : int(1..2)]), + and([and([1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q1, q2, q6]) | q6 : int(1..3)]) | q2 : int(1..3)]) + | q1 : int(1..2)]), + and([and([1 <= sum([toInt(x_Occurrence[q8, q9, q10]) | q10 : int(1..3)]) | q9 : int(1..3)]) | q8 : int(1..2)]), + and([and([and([x_Occurrence[q11, q13, q15] -> + or([x_ExplicitVarSizeWithFlags_Flags[q11, q13, q17] /\ + x_ExplicitVarSizeWithFlags_Values[q11, q13, q17] = q15 + | q17 : int(1..3)]) + | q15 : int(1..3)]) + /\ + and([x_ExplicitVarSizeWithFlags_Flags[q11, q13, q19] -> + x_Occurrence[q11, q13, x_ExplicitVarSizeWithFlags_Values[q11, q13, q19]] + | q19 : int(1..3)]) + | q13 : int(1..3)]) + | q11 : int(1..2)]) + diff --git a/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_4_2-solution000001.solution b/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_4_2-solution000001.solution new file mode 100644 index 0000000000..88e783b8b0 --- /dev/null +++ b/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_4_2-solution000001.solution @@ -0,0 +1,13 @@ +language Essence 1.3 + +letting x be [[{2}, {2}, {2}; int(1..3)], [{2}, {2}, {2}; int(1..3)]; int(1..2)] +$ Visualisation for x +$ 2 +$ 2 +$ 2 +$ +$ 2 +$ 2 +$ 2 +$ + diff --git a/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_4_2.eprime b/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_4_2.eprime new file mode 100644 index 0000000000..18fd6c5c2f --- /dev/null +++ b/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_4_2.eprime @@ -0,0 +1,50 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..2), int(1..3), int(1..3)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..2), int(1..3), int(1..3)] of int(1..3) +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..2), int(1..3), int(1..3)] of int(1..4) +branching on [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] +such that + and([x_ExplicitVarSizeWithFlags_Flags[j1, j2, q26] -> x_ExplicitVarSizeWithFlags_Values[j1, j2, q26] % 2 = 0 + | j1 : int(1..2), j2 : int(1..3), q26 : int(1..3)]), + and([and([and([x_ExplicitVarSizeWithFlags_Flags[q1, q2, q3 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q1, q2, q3] < x_ExplicitVarSizeWithFlags_Values[q1, q2, q3 + 1] + | q3 : int(1..2)]) + | q2 : int(1..3)]) + | q1 : int(1..2)]), + and([and([and([x_ExplicitVarSizeWithFlags_Flags[q1, q2, q4] = false -> + x_ExplicitVarSizeWithFlags_Values[q1, q2, q4] = 1 + | q4 : int(1..3)]) + | q2 : int(1..3)]) + | q1 : int(1..2)]), + and([and([and([x_ExplicitVarSizeWithFlags_Flags[q1, q2, q5 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q1, q2, q5] + | q5 : int(1..2)]) + | q2 : int(1..3)]) + | q1 : int(1..2)]), + and([and([1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q1, q2, q6]) | q6 : int(1..3)]) | q2 : int(1..3)]) + | q1 : int(1..2)]), + and([and([and([x_ExplicitVarSizeWithDummy[q8, q9, q10] < x_ExplicitVarSizeWithDummy[q8, q9, q10 + 1] \/ + x_ExplicitVarSizeWithDummy[q8, q9, q10] = 4 + | q10 : int(1..2)]) + | q9 : int(1..3)]) + | q8 : int(1..2)]), + and([and([and([x_ExplicitVarSizeWithDummy[q8, q9, q11] = 4 -> x_ExplicitVarSizeWithDummy[q8, q9, q11 + 1] = 4 + | q11 : int(1..2)]) + | q9 : int(1..3)]) + | q8 : int(1..2)]), + and([and([1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q8, q9, q12] != 4) | q12 : int(1..3)]) | q9 : int(1..3)]) + | q8 : int(1..2)]), + and([and([and([x_ExplicitVarSizeWithDummy[q14, q16, q19] != 4 -> + or([x_ExplicitVarSizeWithFlags_Flags[q14, q16, q21] /\ + x_ExplicitVarSizeWithFlags_Values[q14, q16, q21] = x_ExplicitVarSizeWithDummy[q14, q16, q19] + | q21 : int(1..3)]) + | q19 : int(1..3)]) + /\ + and([x_ExplicitVarSizeWithFlags_Flags[q14, q16, q23] -> + or([x_ExplicitVarSizeWithDummy[q14, q16, q25] != 4 /\ + x_ExplicitVarSizeWithDummy[q14, q16, q25] = x_ExplicitVarSizeWithFlags_Values[q14, q16, q23] + | q25 : int(1..3)]) + | q23 : int(1..3)]) + | q16 : int(1..3)]) + | q14 : int(1..2)]) + diff --git a/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_4_3-solution000001.solution b/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_4_3-solution000001.solution new file mode 100644 index 0000000000..88e783b8b0 --- /dev/null +++ b/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_4_3-solution000001.solution @@ -0,0 +1,13 @@ +language Essence 1.3 + +letting x be [[{2}, {2}, {2}; int(1..3)], [{2}, {2}, {2}; int(1..3)]; int(1..2)] +$ Visualisation for x +$ 2 +$ 2 +$ 2 +$ +$ 2 +$ 2 +$ 2 +$ + diff --git a/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_4_3.eprime b/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_4_3.eprime new file mode 100644 index 0000000000..0716f2019d --- /dev/null +++ b/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_4_3.eprime @@ -0,0 +1,55 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..2), int(1..3), int(1..3)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..2), int(1..3), int(1..3)] of int(1..3) +find x_ExplicitVarSizeWithMarker_Marker: matrix indexed by [int(1..2), int(1..3)] of int(0..3) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..2), int(1..3), int(1..3)] of int(1..3) +branching on + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithFlags_Flags, + x_ExplicitVarSizeWithFlags_Values] +such that + and([x_ExplicitVarSizeWithFlags_Flags[j1, j2, q25] -> x_ExplicitVarSizeWithFlags_Values[j1, j2, q25] % 2 = 0 + | j1 : int(1..2), j2 : int(1..3), q25 : int(1..3)]), + and([and([and([x_ExplicitVarSizeWithFlags_Flags[q1, q2, q3 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q1, q2, q3] < x_ExplicitVarSizeWithFlags_Values[q1, q2, q3 + 1] + | q3 : int(1..2)]) + | q2 : int(1..3)]) + | q1 : int(1..2)]), + and([and([and([x_ExplicitVarSizeWithFlags_Flags[q1, q2, q4] = false -> + x_ExplicitVarSizeWithFlags_Values[q1, q2, q4] = 1 + | q4 : int(1..3)]) + | q2 : int(1..3)]) + | q1 : int(1..2)]), + and([and([and([x_ExplicitVarSizeWithFlags_Flags[q1, q2, q5 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q1, q2, q5] + | q5 : int(1..2)]) + | q2 : int(1..3)]) + | q1 : int(1..2)]), + and([and([1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q1, q2, q6]) | q6 : int(1..3)]) | q2 : int(1..3)]) + | q1 : int(1..2)]), + and([and([and([q10 + 1 <= x_ExplicitVarSizeWithMarker_Marker[q8, q9] -> + x_ExplicitVarSizeWithMarker_Values[q8, q9, q10] < x_ExplicitVarSizeWithMarker_Values[q8, q9, q10 + 1] + | q10 : int(1..2)]) + | q9 : int(1..3)]) + | q8 : int(1..2)]), + and([and([and([q11 > x_ExplicitVarSizeWithMarker_Marker[q8, q9] -> + x_ExplicitVarSizeWithMarker_Values[q8, q9, q11] = 1 + | q11 : int(1..3)]) + | q9 : int(1..3)]) + | q8 : int(1..2)]), + and([and([1 <= x_ExplicitVarSizeWithMarker_Marker[q8, q9] | q9 : int(1..3)]) | q8 : int(1..2)]), + and([and([and([q18 <= x_ExplicitVarSizeWithMarker_Marker[q13, q15] -> + or([x_ExplicitVarSizeWithFlags_Flags[q13, q15, q20] /\ + x_ExplicitVarSizeWithFlags_Values[q13, q15, q20] = + x_ExplicitVarSizeWithMarker_Values[q13, q15, q18] + | q20 : int(1..3)]) + | q18 : int(1..3)]) + /\ + and([x_ExplicitVarSizeWithFlags_Flags[q13, q15, q22] -> + or([q24 <= x_ExplicitVarSizeWithMarker_Marker[q13, q15] /\ + x_ExplicitVarSizeWithMarker_Values[q13, q15, q24] = + x_ExplicitVarSizeWithFlags_Values[q13, q15, q22] + | q24 : int(1..3)]) + | q22 : int(1..3)]) + | q15 : int(1..3)]) + | q13 : int(1..2)]) + diff --git a/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_4_4-solution000001.solution b/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_4_4-solution000001.solution new file mode 100644 index 0000000000..88e783b8b0 --- /dev/null +++ b/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_4_4-solution000001.solution @@ -0,0 +1,13 @@ +language Essence 1.3 + +letting x be [[{2}, {2}, {2}; int(1..3)], [{2}, {2}, {2}; int(1..3)]; int(1..2)] +$ Visualisation for x +$ 2 +$ 2 +$ 2 +$ +$ 2 +$ 2 +$ 2 +$ + diff --git a/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_4_4.eprime b/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_4_4.eprime new file mode 100644 index 0000000000..a9f5c660d9 --- /dev/null +++ b/tests/exhaustive/basic/matrix_of_set_03_2d/expected/model_4_4.eprime @@ -0,0 +1,25 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..2), int(1..3), int(1..3)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..2), int(1..3), int(1..3)] of int(1..3) +branching on [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] +such that + and([x_ExplicitVarSizeWithFlags_Flags[j1, j2, q8] -> x_ExplicitVarSizeWithFlags_Values[j1, j2, q8] % 2 = 0 + | j1 : int(1..2), j2 : int(1..3), q8 : int(1..3)]), + and([and([and([x_ExplicitVarSizeWithFlags_Flags[q1, q2, q3 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q1, q2, q3] < x_ExplicitVarSizeWithFlags_Values[q1, q2, q3 + 1] + | q3 : int(1..2)]) + | q2 : int(1..3)]) + | q1 : int(1..2)]), + and([and([and([x_ExplicitVarSizeWithFlags_Flags[q1, q2, q4] = false -> + x_ExplicitVarSizeWithFlags_Values[q1, q2, q4] = 1 + | q4 : int(1..3)]) + | q2 : int(1..3)]) + | q1 : int(1..2)]), + and([and([and([x_ExplicitVarSizeWithFlags_Flags[q1, q2, q5 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q1, q2, q5] + | q5 : int(1..2)]) + | q2 : int(1..3)]) + | q1 : int(1..2)]), + and([and([1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q1, q2, q6]) | q6 : int(1..3)]) | q2 : int(1..3)]) + | q1 : int(1..2)]) + diff --git a/tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_1_1_1_1-solution000001.solution b/tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_1_1_1_1-solution000001.solution new file mode 100644 index 0000000000..908faf0601 --- /dev/null +++ b/tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_1_1_1_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be {2} +letting b be {2} diff --git a/tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_1_1_1_2-solution000001.solution b/tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_1_1_1_2-solution000001.solution new file mode 100644 index 0000000000..908faf0601 --- /dev/null +++ b/tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_1_1_1_2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be {2} +letting b be {2} diff --git a/tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_1_1_2_1-solution000001.solution b/tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_1_1_2_1-solution000001.solution new file mode 100644 index 0000000000..908faf0601 --- /dev/null +++ b/tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_1_1_2_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be {2} +letting b be {2} diff --git a/tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_1_1_2_2-solution000001.solution b/tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_1_1_2_2-solution000001.solution new file mode 100644 index 0000000000..908faf0601 --- /dev/null +++ b/tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_1_1_2_2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be {2} +letting b be {2} diff --git a/tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_1_2_1_1-solution000001.solution b/tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_1_2_1_1-solution000001.solution new file mode 100644 index 0000000000..908faf0601 --- /dev/null +++ b/tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_1_2_1_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be {2} +letting b be {2} diff --git a/tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_1_2_1_2-solution000001.solution b/tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_1_2_1_2-solution000001.solution new file mode 100644 index 0000000000..908faf0601 --- /dev/null +++ b/tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_1_2_1_2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be {2} +letting b be {2} diff --git a/tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_1_2_2_1-solution000001.solution b/tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_1_2_2_1-solution000001.solution new file mode 100644 index 0000000000..908faf0601 --- /dev/null +++ b/tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_1_2_2_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be {2} +letting b be {2} diff --git a/tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_1_2_2_2-solution000001.solution b/tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_1_2_2_2-solution000001.solution new file mode 100644 index 0000000000..908faf0601 --- /dev/null +++ b/tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_1_2_2_2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be {2} +letting b be {2} diff --git a/tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_2_1_1_1-solution000001.solution b/tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_2_1_1_1-solution000001.solution new file mode 100644 index 0000000000..908faf0601 --- /dev/null +++ b/tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_2_1_1_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be {2} +letting b be {2} diff --git a/tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_2_1_1_2-solution000001.solution b/tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_2_1_1_2-solution000001.solution new file mode 100644 index 0000000000..908faf0601 --- /dev/null +++ b/tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_2_1_1_2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be {2} +letting b be {2} diff --git a/tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_2_1_2_1-solution000001.solution b/tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_2_1_2_1-solution000001.solution new file mode 100644 index 0000000000..908faf0601 --- /dev/null +++ b/tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_2_1_2_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be {2} +letting b be {2} diff --git a/tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_2_1_2_2-solution000001.solution b/tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_2_1_2_2-solution000001.solution new file mode 100644 index 0000000000..908faf0601 --- /dev/null +++ b/tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_2_1_2_2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be {2} +letting b be {2} diff --git a/tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_2_2_1_1-solution000001.solution b/tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_2_2_1_1-solution000001.solution new file mode 100644 index 0000000000..908faf0601 --- /dev/null +++ b/tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_2_2_1_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be {2} +letting b be {2} diff --git a/tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_2_2_1_2-solution000001.solution b/tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_2_2_1_2-solution000001.solution new file mode 100644 index 0000000000..908faf0601 --- /dev/null +++ b/tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_2_2_1_2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be {2} +letting b be {2} diff --git a/tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_2_2_2_1-solution000001.solution b/tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_2_2_2_1-solution000001.solution new file mode 100644 index 0000000000..908faf0601 --- /dev/null +++ b/tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_2_2_2_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be {2} +letting b be {2} diff --git a/tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_2_2_2_2-solution000001.solution b/tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_2_2_2_2-solution000001.solution new file mode 100644 index 0000000000..908faf0601 --- /dev/null +++ b/tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_2_2_2_2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be {2} +letting b be {2} diff --git a/tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_1_1_1_1-solution000001.solution b/tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_1_1_1_1-solution000001.solution new file mode 100644 index 0000000000..908faf0601 --- /dev/null +++ b/tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_1_1_1_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be {2} +letting b be {2} diff --git a/tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_1_1_1_2-solution000001.solution b/tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_1_1_1_2-solution000001.solution new file mode 100644 index 0000000000..908faf0601 --- /dev/null +++ b/tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_1_1_1_2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be {2} +letting b be {2} diff --git a/tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_1_1_2_1-solution000001.solution b/tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_1_1_2_1-solution000001.solution new file mode 100644 index 0000000000..908faf0601 --- /dev/null +++ b/tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_1_1_2_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be {2} +letting b be {2} diff --git a/tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_1_1_2_2-solution000001.solution b/tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_1_1_2_2-solution000001.solution new file mode 100644 index 0000000000..908faf0601 --- /dev/null +++ b/tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_1_1_2_2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be {2} +letting b be {2} diff --git a/tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_1_2_1_1-solution000001.solution b/tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_1_2_1_1-solution000001.solution new file mode 100644 index 0000000000..908faf0601 --- /dev/null +++ b/tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_1_2_1_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be {2} +letting b be {2} diff --git a/tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_1_2_1_2-solution000001.solution b/tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_1_2_1_2-solution000001.solution new file mode 100644 index 0000000000..908faf0601 --- /dev/null +++ b/tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_1_2_1_2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be {2} +letting b be {2} diff --git a/tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_1_2_2_1-solution000001.solution b/tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_1_2_2_1-solution000001.solution new file mode 100644 index 0000000000..908faf0601 --- /dev/null +++ b/tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_1_2_2_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be {2} +letting b be {2} diff --git a/tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_1_2_2_2-solution000001.solution b/tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_1_2_2_2-solution000001.solution new file mode 100644 index 0000000000..908faf0601 --- /dev/null +++ b/tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_1_2_2_2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be {2} +letting b be {2} diff --git a/tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_2_1_1_1-solution000001.solution b/tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_2_1_1_1-solution000001.solution new file mode 100644 index 0000000000..908faf0601 --- /dev/null +++ b/tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_2_1_1_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be {2} +letting b be {2} diff --git a/tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_2_1_1_2-solution000001.solution b/tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_2_1_1_2-solution000001.solution new file mode 100644 index 0000000000..908faf0601 --- /dev/null +++ b/tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_2_1_1_2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be {2} +letting b be {2} diff --git a/tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_2_1_2_1-solution000001.solution b/tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_2_1_2_1-solution000001.solution new file mode 100644 index 0000000000..908faf0601 --- /dev/null +++ b/tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_2_1_2_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be {2} +letting b be {2} diff --git a/tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_2_1_2_2-solution000001.solution b/tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_2_1_2_2-solution000001.solution new file mode 100644 index 0000000000..908faf0601 --- /dev/null +++ b/tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_2_1_2_2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be {2} +letting b be {2} diff --git a/tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_2_2_1_1-solution000001.solution b/tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_2_2_1_1-solution000001.solution new file mode 100644 index 0000000000..908faf0601 --- /dev/null +++ b/tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_2_2_1_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be {2} +letting b be {2} diff --git a/tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_2_2_1_1.eprime.orig b/tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_2_2_1_1.eprime similarity index 60% rename from tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_2_2_1_1.eprime.orig rename to tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_2_2_1_1.eprime index 0779c860d2..ffecec8aba 100644 --- a/tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_2_2_1_1.eprime.orig +++ b/tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_2_2_1_1.eprime @@ -6,16 +6,6 @@ find b_Occurrence: matrix indexed by [int(1..3)] of bool find b_Explicit: matrix indexed by [int(1)] of int(1..3) branching on [a_Explicit, a_Occurrence, b_Explicit, b_Occurrence] such that -<<<<<<< HEAD:tests/exhaustive/basic/matrix_of_set_04_2dLit/expected/model_2_2_1_1.eprime.orig - a_Explicit[1] % 2 = 0, - b_Explicit[1] % 2 = 0, - 1 = sum([toInt(a_Occurrence[q5]) | q5 : int(1..3)]), - and([a_Occurrence[q14] -> a_Explicit[1] = q14 | q14 : int(1..3)]), - a_Occurrence[a_Explicit[1]], - 1 = sum([toInt(b_Occurrence[q6]) | q6 : int(1..3)]), - and([b_Occurrence[q7] -> b_Explicit[1] = q7 | q7 : int(1..3)]), - b_Occurrence[b_Explicit[1]] -======= and([a_Occurrence[i] -> i % 2 = 0 | j1 : int(1..2), j2 : int(1..3), i : int(1..3), 2 = j2, 1 = j1]), and([b_Occurrence[i] -> i % 2 = 0 | j1 : int(1..2), j2 : int(1..3), i : int(1..3), 3 = j2, 2 = j1]), 1 = sum([toInt(a_Occurrence[q1]) | q1 : int(1..3)]), @@ -24,5 +14,4 @@ such that and([a_Occurrence[q7] -> a_Explicit[1] = q7 | q7 : int(1..3)]), b_Occurrence[b_Explicit[1]], and([b_Occurrence[q14] -> b_Explicit[1] = q14 | q14 : int(1..3)]) ->>>>>>> main:tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_2_2_1_1.eprime diff --git a/tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_2_2_1_2-solution000001.solution b/tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_2_2_1_2-solution000001.solution new file mode 100644 index 0000000000..908faf0601 --- /dev/null +++ b/tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_2_2_1_2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be {2} +letting b be {2} diff --git a/tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_2_2_2_1-solution000001.solution b/tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_2_2_2_1-solution000001.solution new file mode 100644 index 0000000000..908faf0601 --- /dev/null +++ b/tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_2_2_2_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be {2} +letting b be {2} diff --git a/tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_2_2_2_2-solution000001.solution b/tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_2_2_2_2-solution000001.solution new file mode 100644 index 0000000000..908faf0601 --- /dev/null +++ b/tests/exhaustive/basic/matrix_of_set_05_2dLit/expected/model_2_2_2_2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be {2} +letting b be {2} diff --git a/tests/exhaustive/basic/mset01_find/expected/model_1.eprime b/tests/exhaustive/basic/mset01_find/expected/model_1.eprime index 9116445f09..3794f0e9f2 100644 --- a/tests/exhaustive/basic/mset01_find/expected/model_1.eprime +++ b/tests/exhaustive/basic/mset01_find/expected/model_1.eprime @@ -4,8 +4,7 @@ find x_ExplicitWithFlags_Flags: matrix indexed by [int(1..4)] of int(0..2) find x_ExplicitWithFlags_Values: matrix indexed by [int(1..4)] of int(1..2) branching on [x_ExplicitWithFlags_Flags, x_ExplicitWithFlags_Values] such that - and([x_ExplicitWithFlags_Flags[q1 + 1] > 0 -> - [x_ExplicitWithFlags_Values[q1]; int(1)] 0 -> x_ExplicitWithFlags_Values[q1] < x_ExplicitWithFlags_Values[q1 + 1] | q1 : int(1..3)]), and([x_ExplicitWithFlags_Flags[q2] = 0 -> x_ExplicitWithFlags_Values[q2] = 1 | q2 : int(1..4)]), and([x_ExplicitWithFlags_Flags[q3 + 1] > 0 -> x_ExplicitWithFlags_Flags[q3] > 0 | q3 : int(1..3)]), diff --git a/tests/exhaustive/basic/mset01_find/expected/model_2.eprime b/tests/exhaustive/basic/mset01_find/expected/model_2.eprime index 49768a43b8..622b9c2da2 100644 --- a/tests/exhaustive/basic/mset01_find/expected/model_2.eprime +++ b/tests/exhaustive/basic/mset01_find/expected/model_2.eprime @@ -5,7 +5,7 @@ find x_ExplicitWithRepetition_Values: matrix indexed by [int(1..4)] of int(1..2) branching on [x_ExplicitWithRepetition_Flag, x_ExplicitWithRepetition_Values] such that and([q1 + 1 <= x_ExplicitWithRepetition_Flag -> - [x_ExplicitWithRepetition_Values[q1]; int(1)] <=lex [x_ExplicitWithRepetition_Values[q1 + 1]; int(1)] + x_ExplicitWithRepetition_Values[q1] <= x_ExplicitWithRepetition_Values[q1 + 1] | q1 : int(1..3)]), and([q2 > x_ExplicitWithRepetition_Flag -> x_ExplicitWithRepetition_Values[q2] = 1 | q2 : int(1..4)]), and([q4 <= x_ExplicitWithRepetition_Flag -> diff --git a/tests/exhaustive/basic/mset01_param/expected/model_1_1-param1-solution000001.solution b/tests/exhaustive/basic/mset01_param/expected/model_1_1-param1-solution000001.solution new file mode 100644 index 0000000000..3fc3fafe52 --- /dev/null +++ b/tests/exhaustive/basic/mset01_param/expected/model_1_1-param1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be mset() diff --git a/tests/exhaustive/basic/mset01_param/expected/model_1_1-param1.eprime-param b/tests/exhaustive/basic/mset01_param/expected/model_1_1-param1.eprime-param new file mode 100644 index 0000000000..62e729a0fe --- /dev/null +++ b/tests/exhaustive/basic/mset01_param/expected/model_1_1-param1.eprime-param @@ -0,0 +1,5 @@ +language ESSENCE' 1.0 + +letting g_ExplicitWithFlags_Flags be ([] : `matrix indexed by [int()] of bool`) +letting g_ExplicitWithFlags_Values be ([] : `matrix indexed by [int()] of int`) +letting fin1 be 0 diff --git a/tests/exhaustive/basic/mset01_param/expected/model_1_1-param4-solution000001.solution b/tests/exhaustive/basic/mset01_param/expected/model_1_1-param4-solution000001.solution new file mode 100644 index 0000000000..43c40d1c6b --- /dev/null +++ b/tests/exhaustive/basic/mset01_param/expected/model_1_1-param4-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be mset(1, 2) diff --git a/tests/exhaustive/basic/mset01_param/expected/model_1_1-param4.eprime-param b/tests/exhaustive/basic/mset01_param/expected/model_1_1-param4.eprime-param new file mode 100644 index 0000000000..f1da505f58 --- /dev/null +++ b/tests/exhaustive/basic/mset01_param/expected/model_1_1-param4.eprime-param @@ -0,0 +1,5 @@ +language ESSENCE' 1.0 + +letting g_ExplicitWithFlags_Flags be [1, 1; int(1..2)] +letting g_ExplicitWithFlags_Values be [1, 2; int(1..2)] +letting fin1 be 2 diff --git a/tests/exhaustive/basic/mset01_param/expected/model_1_1-param7-solution000001.solution b/tests/exhaustive/basic/mset01_param/expected/model_1_1-param7-solution000001.solution new file mode 100644 index 0000000000..06be1e3b32 --- /dev/null +++ b/tests/exhaustive/basic/mset01_param/expected/model_1_1-param7-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be mset(2, 2) diff --git a/tests/exhaustive/basic/mset01_param/expected/model_1_1-param7.eprime-param b/tests/exhaustive/basic/mset01_param/expected/model_1_1-param7.eprime-param new file mode 100644 index 0000000000..468cfba281 --- /dev/null +++ b/tests/exhaustive/basic/mset01_param/expected/model_1_1-param7.eprime-param @@ -0,0 +1,5 @@ +language ESSENCE' 1.0 + +letting g_ExplicitWithFlags_Flags be [2, 0; int(1..2)] +letting g_ExplicitWithFlags_Values be [2, 1; int(1..2)] +letting fin1 be 2 diff --git a/tests/exhaustive/basic/mset01_param/expected/model_1_2-param1-solution000001.solution b/tests/exhaustive/basic/mset01_param/expected/model_1_2-param1-solution000001.solution new file mode 100644 index 0000000000..3fc3fafe52 --- /dev/null +++ b/tests/exhaustive/basic/mset01_param/expected/model_1_2-param1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be mset() diff --git a/tests/exhaustive/basic/mset01_param/expected/model_1_2-param1.eprime-param b/tests/exhaustive/basic/mset01_param/expected/model_1_2-param1.eprime-param new file mode 100644 index 0000000000..62e729a0fe --- /dev/null +++ b/tests/exhaustive/basic/mset01_param/expected/model_1_2-param1.eprime-param @@ -0,0 +1,5 @@ +language ESSENCE' 1.0 + +letting g_ExplicitWithFlags_Flags be ([] : `matrix indexed by [int()] of bool`) +letting g_ExplicitWithFlags_Values be ([] : `matrix indexed by [int()] of int`) +letting fin1 be 0 diff --git a/tests/exhaustive/basic/mset01_param/expected/model_1_2-param4-solution000001.solution b/tests/exhaustive/basic/mset01_param/expected/model_1_2-param4-solution000001.solution new file mode 100644 index 0000000000..43c40d1c6b --- /dev/null +++ b/tests/exhaustive/basic/mset01_param/expected/model_1_2-param4-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be mset(1, 2) diff --git a/tests/exhaustive/basic/mset01_param/expected/model_1_2-param4.eprime-param b/tests/exhaustive/basic/mset01_param/expected/model_1_2-param4.eprime-param new file mode 100644 index 0000000000..f1da505f58 --- /dev/null +++ b/tests/exhaustive/basic/mset01_param/expected/model_1_2-param4.eprime-param @@ -0,0 +1,5 @@ +language ESSENCE' 1.0 + +letting g_ExplicitWithFlags_Flags be [1, 1; int(1..2)] +letting g_ExplicitWithFlags_Values be [1, 2; int(1..2)] +letting fin1 be 2 diff --git a/tests/exhaustive/basic/mset01_param/expected/model_1_2-param7-solution000001.solution b/tests/exhaustive/basic/mset01_param/expected/model_1_2-param7-solution000001.solution new file mode 100644 index 0000000000..06be1e3b32 --- /dev/null +++ b/tests/exhaustive/basic/mset01_param/expected/model_1_2-param7-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be mset(2, 2) diff --git a/tests/exhaustive/basic/mset01_param/expected/model_1_2-param7.eprime-param b/tests/exhaustive/basic/mset01_param/expected/model_1_2-param7.eprime-param new file mode 100644 index 0000000000..468cfba281 --- /dev/null +++ b/tests/exhaustive/basic/mset01_param/expected/model_1_2-param7.eprime-param @@ -0,0 +1,5 @@ +language ESSENCE' 1.0 + +letting g_ExplicitWithFlags_Flags be [2, 0; int(1..2)] +letting g_ExplicitWithFlags_Values be [2, 1; int(1..2)] +letting fin1 be 2 diff --git a/tests/exhaustive/basic/mset01_param/expected/model_1_3-param1-solution000001.solution b/tests/exhaustive/basic/mset01_param/expected/model_1_3-param1-solution000001.solution new file mode 100644 index 0000000000..3fc3fafe52 --- /dev/null +++ b/tests/exhaustive/basic/mset01_param/expected/model_1_3-param1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be mset() diff --git a/tests/exhaustive/basic/mset01_param/expected/model_1_3-param1.eprime-param b/tests/exhaustive/basic/mset01_param/expected/model_1_3-param1.eprime-param new file mode 100644 index 0000000000..62e729a0fe --- /dev/null +++ b/tests/exhaustive/basic/mset01_param/expected/model_1_3-param1.eprime-param @@ -0,0 +1,5 @@ +language ESSENCE' 1.0 + +letting g_ExplicitWithFlags_Flags be ([] : `matrix indexed by [int()] of bool`) +letting g_ExplicitWithFlags_Values be ([] : `matrix indexed by [int()] of int`) +letting fin1 be 0 diff --git a/tests/exhaustive/basic/mset01_param/expected/model_1_3-param4-solution000001.solution b/tests/exhaustive/basic/mset01_param/expected/model_1_3-param4-solution000001.solution new file mode 100644 index 0000000000..43c40d1c6b --- /dev/null +++ b/tests/exhaustive/basic/mset01_param/expected/model_1_3-param4-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be mset(1, 2) diff --git a/tests/exhaustive/basic/mset01_param/expected/model_1_3-param4.eprime-param b/tests/exhaustive/basic/mset01_param/expected/model_1_3-param4.eprime-param new file mode 100644 index 0000000000..f1da505f58 --- /dev/null +++ b/tests/exhaustive/basic/mset01_param/expected/model_1_3-param4.eprime-param @@ -0,0 +1,5 @@ +language ESSENCE' 1.0 + +letting g_ExplicitWithFlags_Flags be [1, 1; int(1..2)] +letting g_ExplicitWithFlags_Values be [1, 2; int(1..2)] +letting fin1 be 2 diff --git a/tests/exhaustive/basic/mset01_param/expected/model_1_3-param7-solution000001.solution b/tests/exhaustive/basic/mset01_param/expected/model_1_3-param7-solution000001.solution new file mode 100644 index 0000000000..06be1e3b32 --- /dev/null +++ b/tests/exhaustive/basic/mset01_param/expected/model_1_3-param7-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be mset(2, 2) diff --git a/tests/exhaustive/basic/mset01_param/expected/model_1_3-param7.eprime-param b/tests/exhaustive/basic/mset01_param/expected/model_1_3-param7.eprime-param new file mode 100644 index 0000000000..468cfba281 --- /dev/null +++ b/tests/exhaustive/basic/mset01_param/expected/model_1_3-param7.eprime-param @@ -0,0 +1,5 @@ +language ESSENCE' 1.0 + +letting g_ExplicitWithFlags_Flags be [2, 0; int(1..2)] +letting g_ExplicitWithFlags_Values be [2, 1; int(1..2)] +letting fin1 be 2 diff --git a/tests/exhaustive/basic/mset01_param/expected/model_2_1-param1-solution000001.solution b/tests/exhaustive/basic/mset01_param/expected/model_2_1-param1-solution000001.solution new file mode 100644 index 0000000000..3fc3fafe52 --- /dev/null +++ b/tests/exhaustive/basic/mset01_param/expected/model_2_1-param1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be mset() diff --git a/tests/exhaustive/basic/mset01_param/expected/model_2_1-param1.eprime-param b/tests/exhaustive/basic/mset01_param/expected/model_2_1-param1.eprime-param new file mode 100644 index 0000000000..62e729a0fe --- /dev/null +++ b/tests/exhaustive/basic/mset01_param/expected/model_2_1-param1.eprime-param @@ -0,0 +1,5 @@ +language ESSENCE' 1.0 + +letting g_ExplicitWithFlags_Flags be ([] : `matrix indexed by [int()] of bool`) +letting g_ExplicitWithFlags_Values be ([] : `matrix indexed by [int()] of int`) +letting fin1 be 0 diff --git a/tests/exhaustive/basic/mset01_param/expected/model_2_1-param4-solution000001.solution b/tests/exhaustive/basic/mset01_param/expected/model_2_1-param4-solution000001.solution new file mode 100644 index 0000000000..43c40d1c6b --- /dev/null +++ b/tests/exhaustive/basic/mset01_param/expected/model_2_1-param4-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be mset(1, 2) diff --git a/tests/exhaustive/basic/mset01_param/expected/model_2_1-param4.eprime-param b/tests/exhaustive/basic/mset01_param/expected/model_2_1-param4.eprime-param new file mode 100644 index 0000000000..f1da505f58 --- /dev/null +++ b/tests/exhaustive/basic/mset01_param/expected/model_2_1-param4.eprime-param @@ -0,0 +1,5 @@ +language ESSENCE' 1.0 + +letting g_ExplicitWithFlags_Flags be [1, 1; int(1..2)] +letting g_ExplicitWithFlags_Values be [1, 2; int(1..2)] +letting fin1 be 2 diff --git a/tests/exhaustive/basic/mset01_param/expected/model_2_1-param7-solution000001.solution b/tests/exhaustive/basic/mset01_param/expected/model_2_1-param7-solution000001.solution new file mode 100644 index 0000000000..06be1e3b32 --- /dev/null +++ b/tests/exhaustive/basic/mset01_param/expected/model_2_1-param7-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be mset(2, 2) diff --git a/tests/exhaustive/basic/mset01_param/expected/model_2_1-param7.eprime-param b/tests/exhaustive/basic/mset01_param/expected/model_2_1-param7.eprime-param new file mode 100644 index 0000000000..468cfba281 --- /dev/null +++ b/tests/exhaustive/basic/mset01_param/expected/model_2_1-param7.eprime-param @@ -0,0 +1,5 @@ +language ESSENCE' 1.0 + +letting g_ExplicitWithFlags_Flags be [2, 0; int(1..2)] +letting g_ExplicitWithFlags_Values be [2, 1; int(1..2)] +letting fin1 be 2 diff --git a/tests/exhaustive/basic/mset01_param/expected/model_2_2-param1-solution000001.solution b/tests/exhaustive/basic/mset01_param/expected/model_2_2-param1-solution000001.solution new file mode 100644 index 0000000000..3fc3fafe52 --- /dev/null +++ b/tests/exhaustive/basic/mset01_param/expected/model_2_2-param1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be mset() diff --git a/tests/exhaustive/basic/mset01_param/expected/model_2_2-param1.eprime-param b/tests/exhaustive/basic/mset01_param/expected/model_2_2-param1.eprime-param new file mode 100644 index 0000000000..62e729a0fe --- /dev/null +++ b/tests/exhaustive/basic/mset01_param/expected/model_2_2-param1.eprime-param @@ -0,0 +1,5 @@ +language ESSENCE' 1.0 + +letting g_ExplicitWithFlags_Flags be ([] : `matrix indexed by [int()] of bool`) +letting g_ExplicitWithFlags_Values be ([] : `matrix indexed by [int()] of int`) +letting fin1 be 0 diff --git a/tests/exhaustive/basic/mset01_param/expected/model_2_2-param4-solution000001.solution b/tests/exhaustive/basic/mset01_param/expected/model_2_2-param4-solution000001.solution new file mode 100644 index 0000000000..43c40d1c6b --- /dev/null +++ b/tests/exhaustive/basic/mset01_param/expected/model_2_2-param4-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be mset(1, 2) diff --git a/tests/exhaustive/basic/mset01_param/expected/model_2_2-param4.eprime-param b/tests/exhaustive/basic/mset01_param/expected/model_2_2-param4.eprime-param new file mode 100644 index 0000000000..f1da505f58 --- /dev/null +++ b/tests/exhaustive/basic/mset01_param/expected/model_2_2-param4.eprime-param @@ -0,0 +1,5 @@ +language ESSENCE' 1.0 + +letting g_ExplicitWithFlags_Flags be [1, 1; int(1..2)] +letting g_ExplicitWithFlags_Values be [1, 2; int(1..2)] +letting fin1 be 2 diff --git a/tests/exhaustive/basic/mset01_param/expected/model_2_2-param7-solution000001.solution b/tests/exhaustive/basic/mset01_param/expected/model_2_2-param7-solution000001.solution new file mode 100644 index 0000000000..06be1e3b32 --- /dev/null +++ b/tests/exhaustive/basic/mset01_param/expected/model_2_2-param7-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be mset(2, 2) diff --git a/tests/exhaustive/basic/mset01_param/expected/model_2_2-param7.eprime-param b/tests/exhaustive/basic/mset01_param/expected/model_2_2-param7.eprime-param new file mode 100644 index 0000000000..468cfba281 --- /dev/null +++ b/tests/exhaustive/basic/mset01_param/expected/model_2_2-param7.eprime-param @@ -0,0 +1,5 @@ +language ESSENCE' 1.0 + +letting g_ExplicitWithFlags_Flags be [2, 0; int(1..2)] +letting g_ExplicitWithFlags_Values be [2, 1; int(1..2)] +letting fin1 be 2 diff --git a/tests/exhaustive/basic/mset01_param/expected/model_2_2.eprime b/tests/exhaustive/basic/mset01_param/expected/model_2_2.eprime new file mode 100644 index 0000000000..a7170a2566 --- /dev/null +++ b/tests/exhaustive/basic/mset01_param/expected/model_2_2.eprime @@ -0,0 +1,37 @@ +language ESSENCE' 1.0 + +given fin1: int +given g_ExplicitWithFlags_Flags: matrix indexed by [int(1..fin1)] of int(0..2) +given g_ExplicitWithFlags_Values: matrix indexed by [int(1..fin1)] of int(1..2) +find x_ExplicitWithRepetition_Flag: int(0..4) +find x_ExplicitWithRepetition_Values: matrix indexed by [int(1..4)] of int(1..2) +branching on [x_ExplicitWithRepetition_Flag, x_ExplicitWithRepetition_Values] +such that + and([sum([g_ExplicitWithFlags_Flags[q10] + | q10 : int(1..fin1), g_ExplicitWithFlags_Values[q10] = g_ExplicitWithFlags_Values[q9]]) + = + sum([toInt(q12 <= x_ExplicitWithRepetition_Flag) * + catchUndef(toInt(x_ExplicitWithRepetition_Values[q12] = g_ExplicitWithFlags_Values[q9]), 0) + | q12 : int(1..4)]) + | q9 : int(1..fin1), g_ExplicitWithFlags_Flags[q9] > 0]), + and([q13 <= x_ExplicitWithRepetition_Flag -> + sum([toInt(g_ExplicitWithFlags_Values[q14] = x_ExplicitWithRepetition_Values[q13]) * + catchUndef(g_ExplicitWithFlags_Flags[q14], 0) + | q14 : int(1..fin1)]) + = + sum([toInt(q16 <= x_ExplicitWithRepetition_Flag) * + catchUndef(toInt(x_ExplicitWithRepetition_Values[q16] = x_ExplicitWithRepetition_Values[q13]), 0) + | q16 : int(1..4)]) + | q13 : int(1..4)]), + and([q1 + 1 <= x_ExplicitWithRepetition_Flag -> + x_ExplicitWithRepetition_Values[q1] <= x_ExplicitWithRepetition_Values[q1 + 1] + | q1 : int(1..3)]), + and([q2 > x_ExplicitWithRepetition_Flag -> x_ExplicitWithRepetition_Values[q2] = 1 | q2 : int(1..4)]), + and([q4 <= x_ExplicitWithRepetition_Flag -> + sum([toInt(q7 <= x_ExplicitWithRepetition_Flag) * + catchUndef(toInt(x_ExplicitWithRepetition_Values[q7] = x_ExplicitWithRepetition_Values[q4]), 0) + | q7 : int(1..4)]) + <= 2 + | q4 : int(1..4)]), + x_ExplicitWithRepetition_Flag <= 4 + diff --git a/tests/exhaustive/basic/mset01_param/expected/model_2_3-param1-solution000001.solution b/tests/exhaustive/basic/mset01_param/expected/model_2_3-param1-solution000001.solution new file mode 100644 index 0000000000..3fc3fafe52 --- /dev/null +++ b/tests/exhaustive/basic/mset01_param/expected/model_2_3-param1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be mset() diff --git a/tests/exhaustive/basic/mset01_param/expected/model_2_3-param1.eprime-param b/tests/exhaustive/basic/mset01_param/expected/model_2_3-param1.eprime-param new file mode 100644 index 0000000000..62e729a0fe --- /dev/null +++ b/tests/exhaustive/basic/mset01_param/expected/model_2_3-param1.eprime-param @@ -0,0 +1,5 @@ +language ESSENCE' 1.0 + +letting g_ExplicitWithFlags_Flags be ([] : `matrix indexed by [int()] of bool`) +letting g_ExplicitWithFlags_Values be ([] : `matrix indexed by [int()] of int`) +letting fin1 be 0 diff --git a/tests/exhaustive/basic/mset01_param/expected/model_2_3-param4-solution000001.solution b/tests/exhaustive/basic/mset01_param/expected/model_2_3-param4-solution000001.solution new file mode 100644 index 0000000000..43c40d1c6b --- /dev/null +++ b/tests/exhaustive/basic/mset01_param/expected/model_2_3-param4-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be mset(1, 2) diff --git a/tests/exhaustive/basic/mset01_param/expected/model_2_3-param4.eprime-param b/tests/exhaustive/basic/mset01_param/expected/model_2_3-param4.eprime-param new file mode 100644 index 0000000000..f1da505f58 --- /dev/null +++ b/tests/exhaustive/basic/mset01_param/expected/model_2_3-param4.eprime-param @@ -0,0 +1,5 @@ +language ESSENCE' 1.0 + +letting g_ExplicitWithFlags_Flags be [1, 1; int(1..2)] +letting g_ExplicitWithFlags_Values be [1, 2; int(1..2)] +letting fin1 be 2 diff --git a/tests/exhaustive/basic/mset01_param/expected/model_2_3-param7-solution000001.solution b/tests/exhaustive/basic/mset01_param/expected/model_2_3-param7-solution000001.solution new file mode 100644 index 0000000000..06be1e3b32 --- /dev/null +++ b/tests/exhaustive/basic/mset01_param/expected/model_2_3-param7-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be mset(2, 2) diff --git a/tests/exhaustive/basic/mset01_param/expected/model_2_3-param7.eprime-param b/tests/exhaustive/basic/mset01_param/expected/model_2_3-param7.eprime-param new file mode 100644 index 0000000000..468cfba281 --- /dev/null +++ b/tests/exhaustive/basic/mset01_param/expected/model_2_3-param7.eprime-param @@ -0,0 +1,5 @@ +language ESSENCE' 1.0 + +letting g_ExplicitWithFlags_Flags be [2, 0; int(1..2)] +letting g_ExplicitWithFlags_Values be [2, 1; int(1..2)] +letting fin1 be 2 diff --git a/tests/exhaustive/basic/mset01_param/expected/model_2_3.eprime b/tests/exhaustive/basic/mset01_param/expected/model_2_3.eprime new file mode 100644 index 0000000000..333e369e13 --- /dev/null +++ b/tests/exhaustive/basic/mset01_param/expected/model_2_3.eprime @@ -0,0 +1,51 @@ +language ESSENCE' 1.0 + +given fin1: int +given g_ExplicitWithFlags_Flags: matrix indexed by [int(1..fin1)] of int(0..2) +given g_ExplicitWithFlags_Values: matrix indexed by [int(1..fin1)] of int(1..2) +find x_ExplicitWithRepetition_Flag: int(0..4) +find x_ExplicitWithRepetition_Values: matrix indexed by [int(1..4)] of int(1..2) +find x_MOccurrence: matrix indexed by [int(1..2)] of int(0..2) +branching on [x_MOccurrence, x_ExplicitWithRepetition_Flag, x_ExplicitWithRepetition_Values] +such that + and([sum([g_ExplicitWithFlags_Flags[q18] + | q18 : int(1..fin1), g_ExplicitWithFlags_Values[q18] = g_ExplicitWithFlags_Values[q17]]) + = + sum([toInt(q20 <= x_ExplicitWithRepetition_Flag) * + catchUndef(toInt(x_ExplicitWithRepetition_Values[q20] = g_ExplicitWithFlags_Values[q17]), 0) + | q20 : int(1..4)]) + | q17 : int(1..fin1), g_ExplicitWithFlags_Flags[q17] > 0]), + and([q21 <= x_ExplicitWithRepetition_Flag -> + sum([toInt(g_ExplicitWithFlags_Values[q22] = x_ExplicitWithRepetition_Values[q21]) * + catchUndef(g_ExplicitWithFlags_Flags[q22], 0) + | q22 : int(1..fin1)]) + = + sum([toInt(q24 <= x_ExplicitWithRepetition_Flag) * + catchUndef(toInt(x_ExplicitWithRepetition_Values[q24] = x_ExplicitWithRepetition_Values[q21]), 0) + | q24 : int(1..4)]) + | q21 : int(1..4)]), + and([q1 + 1 <= x_ExplicitWithRepetition_Flag -> + x_ExplicitWithRepetition_Values[q1] <= x_ExplicitWithRepetition_Values[q1 + 1] + | q1 : int(1..3)]), + and([q2 > x_ExplicitWithRepetition_Flag -> x_ExplicitWithRepetition_Values[q2] = 1 | q2 : int(1..4)]), + and([q4 <= x_ExplicitWithRepetition_Flag -> + sum([toInt(q7 <= x_ExplicitWithRepetition_Flag) * + catchUndef(toInt(x_ExplicitWithRepetition_Values[q7] = x_ExplicitWithRepetition_Values[q4]), 0) + | q7 : int(1..4)]) + <= 2 + | q4 : int(1..4)]), + x_ExplicitWithRepetition_Flag <= 4, + sum([x_MOccurrence[q8] | q8 : int(1..2)]) <= 4, + and([x_MOccurrence[q10] > 0 -> + x_MOccurrence[q10] = + sum([toInt(q12 <= x_ExplicitWithRepetition_Flag) * + catchUndef(toInt(x_ExplicitWithRepetition_Values[q12] = q10), 0) + | q12 : int(1..4)]) + | q10 : int(1..2)]), + and([q13 <= x_ExplicitWithRepetition_Flag -> + x_MOccurrence[x_ExplicitWithRepetition_Values[q13]] = + sum([toInt(q15 <= x_ExplicitWithRepetition_Flag) * + catchUndef(toInt(x_ExplicitWithRepetition_Values[q15] = x_ExplicitWithRepetition_Values[q13]), 0) + | q15 : int(1..4)]) + | q13 : int(1..4)]) + diff --git a/tests/exhaustive/basic/mset01_param/expected/model_3_1-param1-solution000001.solution b/tests/exhaustive/basic/mset01_param/expected/model_3_1-param1-solution000001.solution new file mode 100644 index 0000000000..3fc3fafe52 --- /dev/null +++ b/tests/exhaustive/basic/mset01_param/expected/model_3_1-param1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be mset() diff --git a/tests/exhaustive/basic/mset01_param/expected/model_3_1-param1.eprime-param b/tests/exhaustive/basic/mset01_param/expected/model_3_1-param1.eprime-param new file mode 100644 index 0000000000..62e729a0fe --- /dev/null +++ b/tests/exhaustive/basic/mset01_param/expected/model_3_1-param1.eprime-param @@ -0,0 +1,5 @@ +language ESSENCE' 1.0 + +letting g_ExplicitWithFlags_Flags be ([] : `matrix indexed by [int()] of bool`) +letting g_ExplicitWithFlags_Values be ([] : `matrix indexed by [int()] of int`) +letting fin1 be 0 diff --git a/tests/exhaustive/basic/mset01_param/expected/model_3_1-param4-solution000001.solution b/tests/exhaustive/basic/mset01_param/expected/model_3_1-param4-solution000001.solution new file mode 100644 index 0000000000..43c40d1c6b --- /dev/null +++ b/tests/exhaustive/basic/mset01_param/expected/model_3_1-param4-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be mset(1, 2) diff --git a/tests/exhaustive/basic/mset01_param/expected/model_3_1-param4.eprime-param b/tests/exhaustive/basic/mset01_param/expected/model_3_1-param4.eprime-param new file mode 100644 index 0000000000..f1da505f58 --- /dev/null +++ b/tests/exhaustive/basic/mset01_param/expected/model_3_1-param4.eprime-param @@ -0,0 +1,5 @@ +language ESSENCE' 1.0 + +letting g_ExplicitWithFlags_Flags be [1, 1; int(1..2)] +letting g_ExplicitWithFlags_Values be [1, 2; int(1..2)] +letting fin1 be 2 diff --git a/tests/exhaustive/basic/mset01_param/expected/model_3_1-param7-solution000001.solution b/tests/exhaustive/basic/mset01_param/expected/model_3_1-param7-solution000001.solution new file mode 100644 index 0000000000..06be1e3b32 --- /dev/null +++ b/tests/exhaustive/basic/mset01_param/expected/model_3_1-param7-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be mset(2, 2) diff --git a/tests/exhaustive/basic/mset01_param/expected/model_3_1-param7.eprime-param b/tests/exhaustive/basic/mset01_param/expected/model_3_1-param7.eprime-param new file mode 100644 index 0000000000..468cfba281 --- /dev/null +++ b/tests/exhaustive/basic/mset01_param/expected/model_3_1-param7.eprime-param @@ -0,0 +1,5 @@ +language ESSENCE' 1.0 + +letting g_ExplicitWithFlags_Flags be [2, 0; int(1..2)] +letting g_ExplicitWithFlags_Values be [2, 1; int(1..2)] +letting fin1 be 2 diff --git a/tests/exhaustive/basic/mset01_param/expected/model_3_2-param1-solution000001.solution b/tests/exhaustive/basic/mset01_param/expected/model_3_2-param1-solution000001.solution new file mode 100644 index 0000000000..3fc3fafe52 --- /dev/null +++ b/tests/exhaustive/basic/mset01_param/expected/model_3_2-param1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be mset() diff --git a/tests/exhaustive/basic/mset01_param/expected/model_3_2-param1.eprime-param b/tests/exhaustive/basic/mset01_param/expected/model_3_2-param1.eprime-param new file mode 100644 index 0000000000..62e729a0fe --- /dev/null +++ b/tests/exhaustive/basic/mset01_param/expected/model_3_2-param1.eprime-param @@ -0,0 +1,5 @@ +language ESSENCE' 1.0 + +letting g_ExplicitWithFlags_Flags be ([] : `matrix indexed by [int()] of bool`) +letting g_ExplicitWithFlags_Values be ([] : `matrix indexed by [int()] of int`) +letting fin1 be 0 diff --git a/tests/exhaustive/basic/mset01_param/expected/model_3_2-param4-solution000001.solution b/tests/exhaustive/basic/mset01_param/expected/model_3_2-param4-solution000001.solution new file mode 100644 index 0000000000..43c40d1c6b --- /dev/null +++ b/tests/exhaustive/basic/mset01_param/expected/model_3_2-param4-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be mset(1, 2) diff --git a/tests/exhaustive/basic/mset01_param/expected/model_3_2-param4.eprime-param b/tests/exhaustive/basic/mset01_param/expected/model_3_2-param4.eprime-param new file mode 100644 index 0000000000..f1da505f58 --- /dev/null +++ b/tests/exhaustive/basic/mset01_param/expected/model_3_2-param4.eprime-param @@ -0,0 +1,5 @@ +language ESSENCE' 1.0 + +letting g_ExplicitWithFlags_Flags be [1, 1; int(1..2)] +letting g_ExplicitWithFlags_Values be [1, 2; int(1..2)] +letting fin1 be 2 diff --git a/tests/exhaustive/basic/mset01_param/expected/model_3_2-param7-solution000001.solution b/tests/exhaustive/basic/mset01_param/expected/model_3_2-param7-solution000001.solution new file mode 100644 index 0000000000..06be1e3b32 --- /dev/null +++ b/tests/exhaustive/basic/mset01_param/expected/model_3_2-param7-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be mset(2, 2) diff --git a/tests/exhaustive/basic/mset01_param/expected/model_3_2-param7.eprime-param b/tests/exhaustive/basic/mset01_param/expected/model_3_2-param7.eprime-param new file mode 100644 index 0000000000..468cfba281 --- /dev/null +++ b/tests/exhaustive/basic/mset01_param/expected/model_3_2-param7.eprime-param @@ -0,0 +1,5 @@ +language ESSENCE' 1.0 + +letting g_ExplicitWithFlags_Flags be [2, 0; int(1..2)] +letting g_ExplicitWithFlags_Values be [2, 1; int(1..2)] +letting fin1 be 2 diff --git a/tests/exhaustive/basic/mset01_param/expected/model_3_2.eprime b/tests/exhaustive/basic/mset01_param/expected/model_3_2.eprime new file mode 100644 index 0000000000..40b69ccf3d --- /dev/null +++ b/tests/exhaustive/basic/mset01_param/expected/model_3_2.eprime @@ -0,0 +1,43 @@ +language ESSENCE' 1.0 + +given fin1: int +given g_ExplicitWithFlags_Flags: matrix indexed by [int(1..fin1)] of int(0..2) +given g_ExplicitWithFlags_Values: matrix indexed by [int(1..fin1)] of int(1..2) +find x_MOccurrence: matrix indexed by [int(1..2)] of int(0..2) +find x_ExplicitWithRepetition_Flag: int(0..4) +find x_ExplicitWithRepetition_Values: matrix indexed by [int(1..4)] of int(1..2) +branching on [x_ExplicitWithRepetition_Flag, x_ExplicitWithRepetition_Values, x_MOccurrence] +such that + and([sum([g_ExplicitWithFlags_Flags[q18] + | q18 : int(1..fin1), g_ExplicitWithFlags_Values[q18] = g_ExplicitWithFlags_Values[q17]]) + = x_MOccurrence[g_ExplicitWithFlags_Values[q17]] + | q17 : int(1..fin1), g_ExplicitWithFlags_Flags[q17] > 0]), + and([x_MOccurrence[q19] > 0 -> + sum([g_ExplicitWithFlags_Flags[q20] | q20 : int(1..fin1), g_ExplicitWithFlags_Values[q20] = q19]) = + x_MOccurrence[q19] + | q19 : int(1..2)]), + sum([x_MOccurrence[q1] | q1 : int(1..2)]) <= 4, + and([q2 + 1 <= x_ExplicitWithRepetition_Flag -> + x_ExplicitWithRepetition_Values[q2] <= x_ExplicitWithRepetition_Values[q2 + 1] + | q2 : int(1..3)]), + and([q3 > x_ExplicitWithRepetition_Flag -> x_ExplicitWithRepetition_Values[q3] = 1 | q3 : int(1..4)]), + and([q5 <= x_ExplicitWithRepetition_Flag -> + sum([toInt(q8 <= x_ExplicitWithRepetition_Flag) * + catchUndef(toInt(x_ExplicitWithRepetition_Values[q8] = x_ExplicitWithRepetition_Values[q5]), 0) + | q8 : int(1..4)]) + <= 2 + | q5 : int(1..4)]), + x_ExplicitWithRepetition_Flag <= 4, + and([q10 <= x_ExplicitWithRepetition_Flag -> + sum([toInt(q12 <= x_ExplicitWithRepetition_Flag) * + catchUndef(toInt(x_ExplicitWithRepetition_Values[q12] = x_ExplicitWithRepetition_Values[q10]), 0) + | q12 : int(1..4)]) + = x_MOccurrence[x_ExplicitWithRepetition_Values[q10]] + | q10 : int(1..4)]), + and([x_MOccurrence[q13] > 0 -> + sum([toInt(q15 <= x_ExplicitWithRepetition_Flag) * + catchUndef(toInt(x_ExplicitWithRepetition_Values[q15] = q13), 0) + | q15 : int(1..4)]) + = x_MOccurrence[q13] + | q13 : int(1..2)]) + diff --git a/tests/exhaustive/basic/mset01_param/expected/model_3_3-param1-solution000001.solution b/tests/exhaustive/basic/mset01_param/expected/model_3_3-param1-solution000001.solution new file mode 100644 index 0000000000..3fc3fafe52 --- /dev/null +++ b/tests/exhaustive/basic/mset01_param/expected/model_3_3-param1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be mset() diff --git a/tests/exhaustive/basic/mset01_param/expected/model_3_3-param1.eprime-param b/tests/exhaustive/basic/mset01_param/expected/model_3_3-param1.eprime-param new file mode 100644 index 0000000000..62e729a0fe --- /dev/null +++ b/tests/exhaustive/basic/mset01_param/expected/model_3_3-param1.eprime-param @@ -0,0 +1,5 @@ +language ESSENCE' 1.0 + +letting g_ExplicitWithFlags_Flags be ([] : `matrix indexed by [int()] of bool`) +letting g_ExplicitWithFlags_Values be ([] : `matrix indexed by [int()] of int`) +letting fin1 be 0 diff --git a/tests/exhaustive/basic/mset01_param/expected/model_3_3-param4-solution000001.solution b/tests/exhaustive/basic/mset01_param/expected/model_3_3-param4-solution000001.solution new file mode 100644 index 0000000000..43c40d1c6b --- /dev/null +++ b/tests/exhaustive/basic/mset01_param/expected/model_3_3-param4-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be mset(1, 2) diff --git a/tests/exhaustive/basic/mset01_param/expected/model_3_3-param4.eprime-param b/tests/exhaustive/basic/mset01_param/expected/model_3_3-param4.eprime-param new file mode 100644 index 0000000000..f1da505f58 --- /dev/null +++ b/tests/exhaustive/basic/mset01_param/expected/model_3_3-param4.eprime-param @@ -0,0 +1,5 @@ +language ESSENCE' 1.0 + +letting g_ExplicitWithFlags_Flags be [1, 1; int(1..2)] +letting g_ExplicitWithFlags_Values be [1, 2; int(1..2)] +letting fin1 be 2 diff --git a/tests/exhaustive/basic/mset01_param/expected/model_3_3-param7-solution000001.solution b/tests/exhaustive/basic/mset01_param/expected/model_3_3-param7-solution000001.solution new file mode 100644 index 0000000000..06be1e3b32 --- /dev/null +++ b/tests/exhaustive/basic/mset01_param/expected/model_3_3-param7-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be mset(2, 2) diff --git a/tests/exhaustive/basic/mset01_param/expected/model_3_3-param7.eprime-param b/tests/exhaustive/basic/mset01_param/expected/model_3_3-param7.eprime-param new file mode 100644 index 0000000000..468cfba281 --- /dev/null +++ b/tests/exhaustive/basic/mset01_param/expected/model_3_3-param7.eprime-param @@ -0,0 +1,5 @@ +language ESSENCE' 1.0 + +letting g_ExplicitWithFlags_Flags be [2, 0; int(1..2)] +letting g_ExplicitWithFlags_Values be [2, 1; int(1..2)] +letting fin1 be 2 diff --git a/tests/exhaustive/basic/mset01_param/expected/model_3_3.eprime b/tests/exhaustive/basic/mset01_param/expected/model_3_3.eprime new file mode 100644 index 0000000000..c7c31d20ea --- /dev/null +++ b/tests/exhaustive/basic/mset01_param/expected/model_3_3.eprime @@ -0,0 +1,18 @@ +language ESSENCE' 1.0 + +given fin1: int +given g_ExplicitWithFlags_Flags: matrix indexed by [int(1..fin1)] of int(0..2) +given g_ExplicitWithFlags_Values: matrix indexed by [int(1..fin1)] of int(1..2) +find x_MOccurrence: matrix indexed by [int(1..2)] of int(0..2) +branching on [x_MOccurrence] +such that + and([sum([g_ExplicitWithFlags_Flags[q4] + | q4 : int(1..fin1), g_ExplicitWithFlags_Values[q4] = g_ExplicitWithFlags_Values[q3]]) + = x_MOccurrence[g_ExplicitWithFlags_Values[q3]] + | q3 : int(1..fin1), g_ExplicitWithFlags_Flags[q3] > 0]), + and([x_MOccurrence[q5] > 0 -> + sum([g_ExplicitWithFlags_Flags[q6] | q6 : int(1..fin1), g_ExplicitWithFlags_Values[q6] = q5]) = + x_MOccurrence[q5] + | q5 : int(1..2)]), + sum([x_MOccurrence[q1] | q1 : int(1..2)]) <= 4 + diff --git a/tests/exhaustive/basic/mset02/expected/model_1.eprime b/tests/exhaustive/basic/mset02/expected/model_1.eprime index 39f9ff47d1..ff48e4e65b 100644 --- a/tests/exhaustive/basic/mset02/expected/model_1.eprime +++ b/tests/exhaustive/basic/mset02/expected/model_1.eprime @@ -4,8 +4,7 @@ find x_ExplicitWithFlags_Flags: matrix indexed by [int(1..4)] of int(0..4) find x_ExplicitWithFlags_Values: matrix indexed by [int(1..4)] of int(1..2) branching on [x_ExplicitWithFlags_Flags, x_ExplicitWithFlags_Values] such that - and([x_ExplicitWithFlags_Flags[q1 + 1] > 0 -> - [x_ExplicitWithFlags_Values[q1]; int(1)] 0 -> x_ExplicitWithFlags_Values[q1] < x_ExplicitWithFlags_Values[q1 + 1] | q1 : int(1..3)]), and([x_ExplicitWithFlags_Flags[q2] = 0 -> x_ExplicitWithFlags_Values[q2] = 1 | q2 : int(1..4)]), and([x_ExplicitWithFlags_Flags[q3 + 1] > 0 -> x_ExplicitWithFlags_Flags[q3] > 0 | q3 : int(1..3)]), diff --git a/tests/exhaustive/basic/mset02/expected/model_2.eprime b/tests/exhaustive/basic/mset02/expected/model_2.eprime index 239b853358..cc0afc5588 100644 --- a/tests/exhaustive/basic/mset02/expected/model_2.eprime +++ b/tests/exhaustive/basic/mset02/expected/model_2.eprime @@ -5,7 +5,7 @@ find x_ExplicitWithRepetition_Values: matrix indexed by [int(1..4)] of int(1..2) branching on [x_ExplicitWithRepetition_Flag, x_ExplicitWithRepetition_Values] such that and([q1 + 1 <= x_ExplicitWithRepetition_Flag -> - [x_ExplicitWithRepetition_Values[q1]; int(1)] <=lex [x_ExplicitWithRepetition_Values[q1 + 1]; int(1)] + x_ExplicitWithRepetition_Values[q1] <= x_ExplicitWithRepetition_Values[q1 + 1] | q1 : int(1..3)]), and([q2 > x_ExplicitWithRepetition_Flag -> x_ExplicitWithRepetition_Values[q2] = 1 | q2 : int(1..4)]), x_ExplicitWithRepetition_Flag <= 4 diff --git a/tests/exhaustive/basic/mset03_1/expected/model_1.eprime b/tests/exhaustive/basic/mset03_1/expected/model_1.eprime index 4c87dce0a5..c1f542f07a 100644 --- a/tests/exhaustive/basic/mset03_1/expected/model_1.eprime +++ b/tests/exhaustive/basic/mset03_1/expected/model_1.eprime @@ -4,8 +4,7 @@ find x_ExplicitWithFlags_Flags: matrix indexed by [int(1..4)] of int(0..2) find x_ExplicitWithFlags_Values: matrix indexed by [int(1..4)] of int(1..2) branching on [x_ExplicitWithFlags_Flags, x_ExplicitWithFlags_Values] such that - and([x_ExplicitWithFlags_Flags[q1 + 1] > 0 -> - [x_ExplicitWithFlags_Values[q1]; int(1)] 0 -> x_ExplicitWithFlags_Values[q1] < x_ExplicitWithFlags_Values[q1 + 1] | q1 : int(1..3)]), and([x_ExplicitWithFlags_Flags[q2] = 0 -> x_ExplicitWithFlags_Values[q2] = 1 | q2 : int(1..4)]), and([x_ExplicitWithFlags_Flags[q3 + 1] > 0 -> x_ExplicitWithFlags_Flags[q3] > 0 | q3 : int(1..3)]) diff --git a/tests/exhaustive/basic/mset03_1/expected/model_2.eprime b/tests/exhaustive/basic/mset03_1/expected/model_2.eprime index 31ae843509..44cf254dca 100644 --- a/tests/exhaustive/basic/mset03_1/expected/model_2.eprime +++ b/tests/exhaustive/basic/mset03_1/expected/model_2.eprime @@ -5,7 +5,7 @@ find x_ExplicitWithRepetition_Values: matrix indexed by [int(1..4)] of int(1..2) branching on [x_ExplicitWithRepetition_Flag, x_ExplicitWithRepetition_Values] such that and([q1 + 1 <= x_ExplicitWithRepetition_Flag -> - [x_ExplicitWithRepetition_Values[q1]; int(1)] <=lex [x_ExplicitWithRepetition_Values[q1 + 1]; int(1)] + x_ExplicitWithRepetition_Values[q1] <= x_ExplicitWithRepetition_Values[q1 + 1] | q1 : int(1..3)]), and([q2 > x_ExplicitWithRepetition_Flag -> x_ExplicitWithRepetition_Values[q2] = 1 | q2 : int(1..4)]), and([q4 <= x_ExplicitWithRepetition_Flag -> diff --git a/tests/exhaustive/basic/mset03_2/expected/model_1.eprime b/tests/exhaustive/basic/mset03_2/expected/model_1.eprime index 246464053e..53f85ab769 100644 --- a/tests/exhaustive/basic/mset03_2/expected/model_1.eprime +++ b/tests/exhaustive/basic/mset03_2/expected/model_1.eprime @@ -4,8 +4,7 @@ find x_ExplicitWithFlags_Flags: matrix indexed by [int(1..6)] of int(0..2) find x_ExplicitWithFlags_Values: matrix indexed by [int(1..6)] of int(1..3) branching on [x_ExplicitWithFlags_Flags, x_ExplicitWithFlags_Values] such that - and([x_ExplicitWithFlags_Flags[q1 + 1] > 0 -> - [x_ExplicitWithFlags_Values[q1]; int(1)] 0 -> x_ExplicitWithFlags_Values[q1] < x_ExplicitWithFlags_Values[q1 + 1] | q1 : int(1..5)]), and([x_ExplicitWithFlags_Flags[q2] = 0 -> x_ExplicitWithFlags_Values[q2] = 1 | q2 : int(1..6)]), and([x_ExplicitWithFlags_Flags[q3 + 1] > 0 -> x_ExplicitWithFlags_Flags[q3] > 0 | q3 : int(1..5)]) diff --git a/tests/exhaustive/basic/mset03_2/expected/model_2.eprime b/tests/exhaustive/basic/mset03_2/expected/model_2.eprime index bc7fd246d0..55d05e3479 100644 --- a/tests/exhaustive/basic/mset03_2/expected/model_2.eprime +++ b/tests/exhaustive/basic/mset03_2/expected/model_2.eprime @@ -5,7 +5,7 @@ find x_ExplicitWithRepetition_Values: matrix indexed by [int(1..6)] of int(1..3) branching on [x_ExplicitWithRepetition_Flag, x_ExplicitWithRepetition_Values] such that and([q1 + 1 <= x_ExplicitWithRepetition_Flag -> - [x_ExplicitWithRepetition_Values[q1]; int(1)] <=lex [x_ExplicitWithRepetition_Values[q1 + 1]; int(1)] + x_ExplicitWithRepetition_Values[q1] <= x_ExplicitWithRepetition_Values[q1 + 1] | q1 : int(1..5)]), and([q2 > x_ExplicitWithRepetition_Flag -> x_ExplicitWithRepetition_Values[q2] = 1 | q2 : int(1..6)]), and([q4 <= x_ExplicitWithRepetition_Flag -> diff --git a/tests/exhaustive/basic/mset04/expected/model_1.eprime b/tests/exhaustive/basic/mset04/expected/model_1.eprime index 20b79160e3..d76b344480 100644 --- a/tests/exhaustive/basic/mset04/expected/model_1.eprime +++ b/tests/exhaustive/basic/mset04/expected/model_1.eprime @@ -4,8 +4,7 @@ find x_ExplicitWithFlags_Flags: matrix indexed by [int(1..4)] of int(0..2) find x_ExplicitWithFlags_Values: matrix indexed by [int(1..4)] of int(1..2) branching on [x_ExplicitWithFlags_Flags, x_ExplicitWithFlags_Values] such that - and([x_ExplicitWithFlags_Flags[q1 + 1] > 0 -> - [x_ExplicitWithFlags_Values[q1]; int(1)] 0 -> x_ExplicitWithFlags_Values[q1] < x_ExplicitWithFlags_Values[q1 + 1] | q1 : int(1..3)]), and([x_ExplicitWithFlags_Flags[q2] = 0 -> x_ExplicitWithFlags_Values[q2] = 1 | q2 : int(1..4)]), and([x_ExplicitWithFlags_Flags[q3 + 1] > 0 -> x_ExplicitWithFlags_Flags[q3] > 0 | q3 : int(1..3)]), diff --git a/tests/exhaustive/basic/mset04/expected/model_2.eprime b/tests/exhaustive/basic/mset04/expected/model_2.eprime index bd0c3f362b..3c59a6b6a4 100644 --- a/tests/exhaustive/basic/mset04/expected/model_2.eprime +++ b/tests/exhaustive/basic/mset04/expected/model_2.eprime @@ -4,8 +4,7 @@ find x_ExplicitWithRepetition_Flag: int(4) find x_ExplicitWithRepetition_Values: matrix indexed by [int(1..4)] of int(1..2) branching on [x_ExplicitWithRepetition_Flag, x_ExplicitWithRepetition_Values] such that - and([[x_ExplicitWithRepetition_Values[q1]; int(1)] <=lex [x_ExplicitWithRepetition_Values[q1 + 1]; int(1)] - | q1 : int(1..3), q1 + 1 <= 4]), + and([x_ExplicitWithRepetition_Values[q1] <= x_ExplicitWithRepetition_Values[q1 + 1] | q1 : int(1..3), q1 + 1 <= 4]), and([sum([toInt(x_ExplicitWithRepetition_Values[q7] = x_ExplicitWithRepetition_Values[q4]) | q7 : int(1..4), q7 <= 4]) <= 2 diff --git a/tests/exhaustive/basic/mset05/expected/model_1.eprime b/tests/exhaustive/basic/mset05/expected/model_1.eprime index 2f37ebea0e..3b3d46b40e 100644 --- a/tests/exhaustive/basic/mset05/expected/model_1.eprime +++ b/tests/exhaustive/basic/mset05/expected/model_1.eprime @@ -4,8 +4,7 @@ find x_ExplicitWithFlags_Flags: matrix indexed by [int(1..4)] of int(0..2) find x_ExplicitWithFlags_Values: matrix indexed by [int(1..4)] of int(1..2) branching on [x_ExplicitWithFlags_Flags, x_ExplicitWithFlags_Values] such that - and([x_ExplicitWithFlags_Flags[q1 + 1] > 0 -> - [x_ExplicitWithFlags_Values[q1]; int(1)] 0 -> x_ExplicitWithFlags_Values[q1] < x_ExplicitWithFlags_Values[q1 + 1] | q1 : int(1..3)]), and([x_ExplicitWithFlags_Flags[q2] = 0 -> x_ExplicitWithFlags_Values[q2] = 1 | q2 : int(1..4)]), and([x_ExplicitWithFlags_Flags[q3 + 1] > 0 -> x_ExplicitWithFlags_Flags[q3] > 0 | q3 : int(1..3)]), diff --git a/tests/exhaustive/basic/mset05/expected/model_2.eprime b/tests/exhaustive/basic/mset05/expected/model_2.eprime index 1ecab17108..f1a0aec2a6 100644 --- a/tests/exhaustive/basic/mset05/expected/model_2.eprime +++ b/tests/exhaustive/basic/mset05/expected/model_2.eprime @@ -5,7 +5,7 @@ find x_ExplicitWithRepetition_Values: matrix indexed by [int(1..4)] of int(1..2) branching on [x_ExplicitWithRepetition_Flag, x_ExplicitWithRepetition_Values] such that and([q1 + 1 <= x_ExplicitWithRepetition_Flag -> - [x_ExplicitWithRepetition_Values[q1]; int(1)] <=lex [x_ExplicitWithRepetition_Values[q1 + 1]; int(1)] + x_ExplicitWithRepetition_Values[q1] <= x_ExplicitWithRepetition_Values[q1 + 1] | q1 : int(1..3)]), and([q2 > x_ExplicitWithRepetition_Flag -> x_ExplicitWithRepetition_Values[q2] = 1 | q2 : int(1..4)]), and([q4 <= x_ExplicitWithRepetition_Flag -> diff --git a/tests/exhaustive/basic/mset06_1/expected/model_1.eprime b/tests/exhaustive/basic/mset06_1/expected/model_1.eprime index 28efae43f7..a7ddaa7601 100644 --- a/tests/exhaustive/basic/mset06_1/expected/model_1.eprime +++ b/tests/exhaustive/basic/mset06_1/expected/model_1.eprime @@ -4,8 +4,7 @@ find x_ExplicitWithFlags_Flags: matrix indexed by [int(1..4)] of int(0..2) find x_ExplicitWithFlags_Values: matrix indexed by [int(1..4)] of int(1..2) branching on [x_ExplicitWithFlags_Flags, x_ExplicitWithFlags_Values] such that - and([x_ExplicitWithFlags_Flags[q1 + 1] > 0 -> - [x_ExplicitWithFlags_Values[q1]; int(1)] 0 -> x_ExplicitWithFlags_Values[q1] < x_ExplicitWithFlags_Values[q1 + 1] | q1 : int(1..3)]), and([x_ExplicitWithFlags_Flags[q2] = 0 -> x_ExplicitWithFlags_Values[q2] = 1 | q2 : int(1..4)]), and([x_ExplicitWithFlags_Flags[q3 + 1] > 0 -> x_ExplicitWithFlags_Flags[q3] > 0 | q3 : int(1..3)]), diff --git a/tests/exhaustive/basic/mset06_1/expected/model_2.eprime b/tests/exhaustive/basic/mset06_1/expected/model_2.eprime index ab84402fe5..9cb4a4bdb7 100644 --- a/tests/exhaustive/basic/mset06_1/expected/model_2.eprime +++ b/tests/exhaustive/basic/mset06_1/expected/model_2.eprime @@ -5,7 +5,7 @@ find x_ExplicitWithRepetition_Values: matrix indexed by [int(1..4)] of int(1..2) branching on [x_ExplicitWithRepetition_Flag, x_ExplicitWithRepetition_Values] such that and([q1 + 1 <= x_ExplicitWithRepetition_Flag -> - [x_ExplicitWithRepetition_Values[q1]; int(1)] <=lex [x_ExplicitWithRepetition_Values[q1 + 1]; int(1)] + x_ExplicitWithRepetition_Values[q1] <= x_ExplicitWithRepetition_Values[q1 + 1] | q1 : int(1..3)]), and([q2 > x_ExplicitWithRepetition_Flag -> x_ExplicitWithRepetition_Values[q2] = 1 | q2 : int(1..4)]), and([sum([toInt(q9 <= x_ExplicitWithRepetition_Flag) * diff --git a/tests/exhaustive/basic/mset06_2/expected/model_1.eprime b/tests/exhaustive/basic/mset06_2/expected/model_1.eprime index 6cfb201e7a..6490528eb8 100644 --- a/tests/exhaustive/basic/mset06_2/expected/model_1.eprime +++ b/tests/exhaustive/basic/mset06_2/expected/model_1.eprime @@ -4,8 +4,7 @@ find x_ExplicitWithFlags_Flags: matrix indexed by [int(1..12)] of int(0..3) find x_ExplicitWithFlags_Values: matrix indexed by [int(1..12)] of int(1..4) branching on [x_ExplicitWithFlags_Flags, x_ExplicitWithFlags_Values] such that - and([x_ExplicitWithFlags_Flags[q1 + 1] > 0 -> - [x_ExplicitWithFlags_Values[q1]; int(1)] 0 -> x_ExplicitWithFlags_Values[q1] < x_ExplicitWithFlags_Values[q1 + 1] | q1 : int(1..11)]), and([x_ExplicitWithFlags_Flags[q2] = 0 -> x_ExplicitWithFlags_Values[q2] = 1 | q2 : int(1..12)]), and([x_ExplicitWithFlags_Flags[q3 + 1] > 0 -> x_ExplicitWithFlags_Flags[q3] > 0 | q3 : int(1..11)]), diff --git a/tests/exhaustive/basic/mset06_2/expected/model_2.eprime b/tests/exhaustive/basic/mset06_2/expected/model_2.eprime index ecf21db30b..1f852a8511 100644 --- a/tests/exhaustive/basic/mset06_2/expected/model_2.eprime +++ b/tests/exhaustive/basic/mset06_2/expected/model_2.eprime @@ -5,7 +5,7 @@ find x_ExplicitWithRepetition_Values: matrix indexed by [int(1..12)] of int(1..4 branching on [x_ExplicitWithRepetition_Flag, x_ExplicitWithRepetition_Values] such that and([q1 + 1 <= x_ExplicitWithRepetition_Flag -> - [x_ExplicitWithRepetition_Values[q1]; int(1)] <=lex [x_ExplicitWithRepetition_Values[q1 + 1]; int(1)] + x_ExplicitWithRepetition_Values[q1] <= x_ExplicitWithRepetition_Values[q1 + 1] | q1 : int(1..11)]), and([q2 > x_ExplicitWithRepetition_Flag -> x_ExplicitWithRepetition_Values[q2] = 1 | q2 : int(1..12)]), and([sum([toInt(q9 <= x_ExplicitWithRepetition_Flag) * diff --git a/tests/exhaustive/basic/mset07/expected/model_1.eprime b/tests/exhaustive/basic/mset07/expected/model_1.eprime index e625813276..74dbb62a4a 100644 --- a/tests/exhaustive/basic/mset07/expected/model_1.eprime +++ b/tests/exhaustive/basic/mset07/expected/model_1.eprime @@ -5,8 +5,7 @@ find x_ExplicitWithFlags_Flags: matrix indexed by [int(1..2)] of int(0..2) find x_ExplicitWithFlags_Values: matrix indexed by [int(1..2)] of int(1..a) branching on [x_ExplicitWithFlags_Flags, x_ExplicitWithFlags_Values] such that - x_ExplicitWithFlags_Flags[2] > 0 -> - [x_ExplicitWithFlags_Values[1]; int(1)] 0 -> x_ExplicitWithFlags_Values[1] < x_ExplicitWithFlags_Values[2], and([x_ExplicitWithFlags_Flags[q2] = 0 -> x_ExplicitWithFlags_Values[q2] = 1 | q2 : int(1..2)]), x_ExplicitWithFlags_Flags[2] > 0 -> x_ExplicitWithFlags_Flags[1] > 0, 2 = sum([x_ExplicitWithFlags_Flags[q6] | q6 : int(1..2)]) diff --git a/tests/exhaustive/basic/mset07/expected/model_2.eprime b/tests/exhaustive/basic/mset07/expected/model_2.eprime index c2b0c8db50..0c20d756ee 100644 --- a/tests/exhaustive/basic/mset07/expected/model_2.eprime +++ b/tests/exhaustive/basic/mset07/expected/model_2.eprime @@ -4,5 +4,5 @@ given a: int find x_ExplicitWithRepetition_Flag: int(2) find x_ExplicitWithRepetition_Values: matrix indexed by [int(1..2)] of int(1..a) branching on [x_ExplicitWithRepetition_Flag, x_ExplicitWithRepetition_Values] -such that [x_ExplicitWithRepetition_Values[1]; int(1)] <=lex [x_ExplicitWithRepetition_Values[2]; int(1)] +such that x_ExplicitWithRepetition_Values[1] <= x_ExplicitWithRepetition_Values[2] diff --git a/tests/exhaustive/basic/name-reuse/expected/model_1_1-solution000001.solution b/tests/exhaustive/basic/name-reuse/expected/model_1_1-solution000001.solution new file mode 100644 index 0000000000..d4f1477569 --- /dev/null +++ b/tests/exhaustive/basic/name-reuse/expected/model_1_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting conjure_aux1 be 1 +letting s be {3} diff --git a/tests/exhaustive/basic/name-reuse/expected/model_1_1-solution000002.solution b/tests/exhaustive/basic/name-reuse/expected/model_1_1-solution000002.solution new file mode 100644 index 0000000000..ab91f42e83 --- /dev/null +++ b/tests/exhaustive/basic/name-reuse/expected/model_1_1-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting conjure_aux1 be 1 +letting s be {3, 4} diff --git a/tests/exhaustive/basic/name-reuse/expected/model_1_1.eprime b/tests/exhaustive/basic/name-reuse/expected/model_1_1.eprime new file mode 100644 index 0000000000..225fffebc9 --- /dev/null +++ b/tests/exhaustive/basic/name-reuse/expected/model_1_1.eprime @@ -0,0 +1,13 @@ +language ESSENCE' 1.0 + +find conjure_aux1: int(1) +find s_Occurrence: matrix indexed by [int(1..4)] of bool +find conjure_aux2: int(1..4) +branching on [conjure_aux1, s_Occurrence] +such that + and([s_Occurrence[q2] -> q2 >= conjure_aux2 | q2 : int(1..4)]), + sum([toInt(s_Occurrence[q2]) | q2 : int(1..4)]) > 0 -> or([s_Occurrence[q2] /\ q2 = conjure_aux2 | q2 : int(1..4)]), + sum([toInt(s_Occurrence[q2]) | q2 : int(1..4)]) = 0 -> conjure_aux2 = 1, + conjure_aux2 = 3, + sum([toInt(s_Occurrence[q2]) | q2 : int(1..4)]) > 0 + diff --git a/tests/exhaustive/basic/name-reuse/expected/model_1_2-solution000001.solution b/tests/exhaustive/basic/name-reuse/expected/model_1_2-solution000001.solution new file mode 100644 index 0000000000..ab91f42e83 --- /dev/null +++ b/tests/exhaustive/basic/name-reuse/expected/model_1_2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting conjure_aux1 be 1 +letting s be {3, 4} diff --git a/tests/exhaustive/basic/name-reuse/expected/model_1_2-solution000002.solution b/tests/exhaustive/basic/name-reuse/expected/model_1_2-solution000002.solution new file mode 100644 index 0000000000..d4f1477569 --- /dev/null +++ b/tests/exhaustive/basic/name-reuse/expected/model_1_2-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting conjure_aux1 be 1 +letting s be {3} diff --git a/tests/exhaustive/basic/name-reuse/expected/model_1_2.eprime b/tests/exhaustive/basic/name-reuse/expected/model_1_2.eprime new file mode 100644 index 0000000000..1aaa5e2e02 --- /dev/null +++ b/tests/exhaustive/basic/name-reuse/expected/model_1_2.eprime @@ -0,0 +1,22 @@ +language ESSENCE' 1.0 + +find conjure_aux1: int(1) +find s_Occurrence: matrix indexed by [int(1..4)] of bool +find s_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +find conjure_aux2: int(1..4) +branching on [conjure_aux1, s_ExplicitVarSizeWithDummy, s_Occurrence] +such that + and([s_Occurrence[q11] -> q11 >= conjure_aux2 | q11 : int(1..4)]), + sum([toInt(s_Occurrence[q11]) | q11 : int(1..4)]) > 0 -> + or([s_Occurrence[q11] /\ q11 = conjure_aux2 | q11 : int(1..4)]), + sum([toInt(s_Occurrence[q11]) | q11 : int(1..4)]) = 0 -> conjure_aux2 = 1, + conjure_aux2 = 3, + sum([toInt(s_Occurrence[q11]) | q11 : int(1..4)]) > 0, + and([s_ExplicitVarSizeWithDummy[q2] < s_ExplicitVarSizeWithDummy[q2 + 1] \/ s_ExplicitVarSizeWithDummy[q2] = 5 + | q2 : int(1..3)]), + and([s_ExplicitVarSizeWithDummy[q3] = 5 -> s_ExplicitVarSizeWithDummy[q3 + 1] = 5 | q3 : int(1..3)]), + and([s_ExplicitVarSizeWithDummy[q7] != 5 -> s_Occurrence[s_ExplicitVarSizeWithDummy[q7]] | q7 : int(1..4)]), + and([s_Occurrence[q8] -> + or([s_ExplicitVarSizeWithDummy[q10] != 5 /\ s_ExplicitVarSizeWithDummy[q10] = q8 | q10 : int(1..4)]) + | q8 : int(1..4)]) + diff --git a/tests/exhaustive/basic/name-reuse/expected/model_1_3-solution000001.solution b/tests/exhaustive/basic/name-reuse/expected/model_1_3-solution000001.solution new file mode 100644 index 0000000000..d4f1477569 --- /dev/null +++ b/tests/exhaustive/basic/name-reuse/expected/model_1_3-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting conjure_aux1 be 1 +letting s be {3} diff --git a/tests/exhaustive/basic/name-reuse/expected/model_1_3-solution000002.solution b/tests/exhaustive/basic/name-reuse/expected/model_1_3-solution000002.solution new file mode 100644 index 0000000000..ab91f42e83 --- /dev/null +++ b/tests/exhaustive/basic/name-reuse/expected/model_1_3-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting conjure_aux1 be 1 +letting s be {3, 4} diff --git a/tests/exhaustive/basic/name-reuse/expected/model_1_3.eprime b/tests/exhaustive/basic/name-reuse/expected/model_1_3.eprime new file mode 100644 index 0000000000..90ed8b70f3 --- /dev/null +++ b/tests/exhaustive/basic/name-reuse/expected/model_1_3.eprime @@ -0,0 +1,25 @@ +language ESSENCE' 1.0 + +find conjure_aux1: int(1) +find s_Occurrence: matrix indexed by [int(1..4)] of bool +find s_ExplicitVarSizeWithMarker_Marker: int(0..4) +find s_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +find conjure_aux2: int(1..4) +branching on [conjure_aux1, s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithMarker_Values, s_Occurrence] +such that + and([s_Occurrence[q10] -> q10 >= conjure_aux2 | q10 : int(1..4)]), + sum([toInt(s_Occurrence[q10]) | q10 : int(1..4)]) > 0 -> + or([s_Occurrence[q10] /\ q10 = conjure_aux2 | q10 : int(1..4)]), + sum([toInt(s_Occurrence[q10]) | q10 : int(1..4)]) = 0 -> conjure_aux2 = 1, + conjure_aux2 = 3, + sum([toInt(s_Occurrence[q10]) | q10 : int(1..4)]) > 0, + and([q2 + 1 <= s_ExplicitVarSizeWithMarker_Marker -> + s_ExplicitVarSizeWithMarker_Values[q2] < s_ExplicitVarSizeWithMarker_Values[q2 + 1] + | q2 : int(1..3)]), + and([q3 > s_ExplicitVarSizeWithMarker_Marker -> s_ExplicitVarSizeWithMarker_Values[q3] = 1 | q3 : int(1..4)]), + and([q6 <= s_ExplicitVarSizeWithMarker_Marker -> s_Occurrence[s_ExplicitVarSizeWithMarker_Values[q6]] + | q6 : int(1..4)]), + and([s_Occurrence[q7] -> + or([q9 <= s_ExplicitVarSizeWithMarker_Marker /\ s_ExplicitVarSizeWithMarker_Values[q9] = q7 | q9 : int(1..4)]) + | q7 : int(1..4)]) + diff --git a/tests/exhaustive/basic/name-reuse/expected/model_1_4-solution000001.solution b/tests/exhaustive/basic/name-reuse/expected/model_1_4-solution000001.solution new file mode 100644 index 0000000000..d4f1477569 --- /dev/null +++ b/tests/exhaustive/basic/name-reuse/expected/model_1_4-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting conjure_aux1 be 1 +letting s be {3} diff --git a/tests/exhaustive/basic/name-reuse/expected/model_1_4-solution000002.solution b/tests/exhaustive/basic/name-reuse/expected/model_1_4-solution000002.solution new file mode 100644 index 0000000000..ab91f42e83 --- /dev/null +++ b/tests/exhaustive/basic/name-reuse/expected/model_1_4-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting conjure_aux1 be 1 +letting s be {3, 4} diff --git a/tests/exhaustive/basic/name-reuse/expected/model_1_4.eprime b/tests/exhaustive/basic/name-reuse/expected/model_1_4.eprime new file mode 100644 index 0000000000..f0a2271016 --- /dev/null +++ b/tests/exhaustive/basic/name-reuse/expected/model_1_4.eprime @@ -0,0 +1,25 @@ +language ESSENCE' 1.0 + +find conjure_aux1: int(1) +find s_Occurrence: matrix indexed by [int(1..4)] of bool +find s_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find s_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +find conjure_aux2: int(1..4) +branching on [conjure_aux1, s_ExplicitVarSizeWithFlags_Flags, s_ExplicitVarSizeWithFlags_Values, s_Occurrence] +such that + and([s_Occurrence[q12] -> q12 >= conjure_aux2 | q12 : int(1..4)]), + sum([toInt(s_Occurrence[q12]) | q12 : int(1..4)]) > 0 -> + or([s_Occurrence[q12] /\ q12 = conjure_aux2 | q12 : int(1..4)]), + sum([toInt(s_Occurrence[q12]) | q12 : int(1..4)]) = 0 -> conjure_aux2 = 1, + conjure_aux2 = 3, + sum([toInt(s_Occurrence[q12]) | q12 : int(1..4)]) > 0, + and([s_ExplicitVarSizeWithFlags_Flags[q2 + 1] -> + s_ExplicitVarSizeWithFlags_Values[q2] < s_ExplicitVarSizeWithFlags_Values[q2 + 1] + | q2 : int(1..3)]), + and([s_ExplicitVarSizeWithFlags_Flags[q3] = false -> s_ExplicitVarSizeWithFlags_Values[q3] = 1 | q3 : int(1..4)]), + and([s_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> s_ExplicitVarSizeWithFlags_Flags[q4] | q4 : int(1..3)]), + and([s_ExplicitVarSizeWithFlags_Flags[q8] -> s_Occurrence[s_ExplicitVarSizeWithFlags_Values[q8]] | q8 : int(1..4)]), + and([s_Occurrence[q9] -> + or([s_ExplicitVarSizeWithFlags_Flags[q11] /\ s_ExplicitVarSizeWithFlags_Values[q11] = q9 | q11 : int(1..4)]) + | q9 : int(1..4)]) + diff --git a/tests/exhaustive/basic/name-reuse/expected/model_2_1-solution000001.solution b/tests/exhaustive/basic/name-reuse/expected/model_2_1-solution000001.solution new file mode 100644 index 0000000000..d4f1477569 --- /dev/null +++ b/tests/exhaustive/basic/name-reuse/expected/model_2_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting conjure_aux1 be 1 +letting s be {3} diff --git a/tests/exhaustive/basic/name-reuse/expected/model_2_1-solution000002.solution b/tests/exhaustive/basic/name-reuse/expected/model_2_1-solution000002.solution new file mode 100644 index 0000000000..ab91f42e83 --- /dev/null +++ b/tests/exhaustive/basic/name-reuse/expected/model_2_1-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting conjure_aux1 be 1 +letting s be {3, 4} diff --git a/tests/exhaustive/basic/name-reuse/expected/model_2_1.eprime b/tests/exhaustive/basic/name-reuse/expected/model_2_1.eprime new file mode 100644 index 0000000000..7abd51269f --- /dev/null +++ b/tests/exhaustive/basic/name-reuse/expected/model_2_1.eprime @@ -0,0 +1,22 @@ +language ESSENCE' 1.0 + +find conjure_aux1: int(1) +find s_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +find s_Occurrence: matrix indexed by [int(1..4)] of bool +find conjure_aux2: int(1..5) +branching on [conjure_aux1, s_Occurrence, s_ExplicitVarSizeWithDummy] +such that + and([s_ExplicitVarSizeWithDummy[q7] != 5 -> s_ExplicitVarSizeWithDummy[q7] >= conjure_aux2 | q7 : int(1..4)]), + sum([toInt(s_ExplicitVarSizeWithDummy[q7] != 5) | q7 : int(1..4)]) > 0 -> + or([s_ExplicitVarSizeWithDummy[q7] != 5 /\ s_ExplicitVarSizeWithDummy[q7] = conjure_aux2 | q7 : int(1..4)]), + sum([toInt(s_ExplicitVarSizeWithDummy[q7] != 5) | q7 : int(1..4)]) = 0 -> conjure_aux2 = 1, + conjure_aux2 = 3, + sum([toInt(s_ExplicitVarSizeWithDummy[q7] != 5) | q7 : int(1..4)]) > 0, + and([s_ExplicitVarSizeWithDummy[q1] < s_ExplicitVarSizeWithDummy[q1 + 1] \/ s_ExplicitVarSizeWithDummy[q1] = 5 + | q1 : int(1..3)]), + and([s_ExplicitVarSizeWithDummy[q2] = 5 -> s_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..3)]), + and([s_Occurrence[q8] -> + or([s_ExplicitVarSizeWithDummy[q10] != 5 /\ s_ExplicitVarSizeWithDummy[q10] = q8 | q10 : int(1..4)]) + | q8 : int(1..4)]), + and([s_ExplicitVarSizeWithDummy[q12] != 5 -> s_Occurrence[s_ExplicitVarSizeWithDummy[q12]] | q12 : int(1..4)]) + diff --git a/tests/exhaustive/basic/name-reuse/expected/model_2_2-solution000001.solution b/tests/exhaustive/basic/name-reuse/expected/model_2_2-solution000001.solution new file mode 100644 index 0000000000..ab91f42e83 --- /dev/null +++ b/tests/exhaustive/basic/name-reuse/expected/model_2_2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting conjure_aux1 be 1 +letting s be {3, 4} diff --git a/tests/exhaustive/basic/name-reuse/expected/model_2_2-solution000002.solution b/tests/exhaustive/basic/name-reuse/expected/model_2_2-solution000002.solution new file mode 100644 index 0000000000..d4f1477569 --- /dev/null +++ b/tests/exhaustive/basic/name-reuse/expected/model_2_2-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting conjure_aux1 be 1 +letting s be {3} diff --git a/tests/exhaustive/basic/name-reuse/expected/model_2_2.eprime b/tests/exhaustive/basic/name-reuse/expected/model_2_2.eprime new file mode 100644 index 0000000000..706b338fed --- /dev/null +++ b/tests/exhaustive/basic/name-reuse/expected/model_2_2.eprime @@ -0,0 +1,17 @@ +language ESSENCE' 1.0 + +find conjure_aux1: int(1) +find s_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +find conjure_aux2: int(1..5) +branching on [conjure_aux1, s_ExplicitVarSizeWithDummy] +such that + and([s_ExplicitVarSizeWithDummy[q6] != 5 -> s_ExplicitVarSizeWithDummy[q6] >= conjure_aux2 | q6 : int(1..4)]), + sum([toInt(s_ExplicitVarSizeWithDummy[q6] != 5) | q6 : int(1..4)]) > 0 -> + or([s_ExplicitVarSizeWithDummy[q6] != 5 /\ s_ExplicitVarSizeWithDummy[q6] = conjure_aux2 | q6 : int(1..4)]), + sum([toInt(s_ExplicitVarSizeWithDummy[q6] != 5) | q6 : int(1..4)]) = 0 -> conjure_aux2 = 1, + conjure_aux2 = 3, + sum([toInt(s_ExplicitVarSizeWithDummy[q6] != 5) | q6 : int(1..4)]) > 0, + and([s_ExplicitVarSizeWithDummy[q1] < s_ExplicitVarSizeWithDummy[q1 + 1] \/ s_ExplicitVarSizeWithDummy[q1] = 5 + | q1 : int(1..3)]), + and([s_ExplicitVarSizeWithDummy[q2] = 5 -> s_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..3)]) + diff --git a/tests/exhaustive/basic/name-reuse/expected/model_2_3-solution000001.solution b/tests/exhaustive/basic/name-reuse/expected/model_2_3-solution000001.solution new file mode 100644 index 0000000000..d4f1477569 --- /dev/null +++ b/tests/exhaustive/basic/name-reuse/expected/model_2_3-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting conjure_aux1 be 1 +letting s be {3} diff --git a/tests/exhaustive/basic/name-reuse/expected/model_2_3-solution000002.solution b/tests/exhaustive/basic/name-reuse/expected/model_2_3-solution000002.solution new file mode 100644 index 0000000000..ab91f42e83 --- /dev/null +++ b/tests/exhaustive/basic/name-reuse/expected/model_2_3-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting conjure_aux1 be 1 +letting s be {3, 4} diff --git a/tests/exhaustive/basic/name-reuse/expected/model_2_3.eprime b/tests/exhaustive/basic/name-reuse/expected/model_2_3.eprime new file mode 100644 index 0000000000..91c6277604 --- /dev/null +++ b/tests/exhaustive/basic/name-reuse/expected/model_2_3.eprime @@ -0,0 +1,34 @@ +language ESSENCE' 1.0 + +find conjure_aux1: int(1) +find s_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +find s_ExplicitVarSizeWithMarker_Marker: int(0..4) +find s_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +find conjure_aux2: int(1..5) +branching on + [conjure_aux1, s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithMarker_Values, s_ExplicitVarSizeWithDummy] +such that + and([s_ExplicitVarSizeWithDummy[q17] != 5 -> s_ExplicitVarSizeWithDummy[q17] >= conjure_aux2 | q17 : int(1..4)]), + sum([toInt(s_ExplicitVarSizeWithDummy[q17] != 5) | q17 : int(1..4)]) > 0 -> + or([s_ExplicitVarSizeWithDummy[q17] != 5 /\ s_ExplicitVarSizeWithDummy[q17] = conjure_aux2 | q17 : int(1..4)]), + sum([toInt(s_ExplicitVarSizeWithDummy[q17] != 5) | q17 : int(1..4)]) = 0 -> conjure_aux2 = 1, + conjure_aux2 = 3, + sum([toInt(s_ExplicitVarSizeWithDummy[q17] != 5) | q17 : int(1..4)]) > 0, + and([s_ExplicitVarSizeWithDummy[q1] < s_ExplicitVarSizeWithDummy[q1 + 1] \/ s_ExplicitVarSizeWithDummy[q1] = 5 + | q1 : int(1..3)]), + and([s_ExplicitVarSizeWithDummy[q2] = 5 -> s_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..3)]), + and([q5 + 1 <= s_ExplicitVarSizeWithMarker_Marker -> + s_ExplicitVarSizeWithMarker_Values[q5] < s_ExplicitVarSizeWithMarker_Values[q5 + 1] + | q5 : int(1..3)]), + and([q6 > s_ExplicitVarSizeWithMarker_Marker -> s_ExplicitVarSizeWithMarker_Values[q6] = 1 | q6 : int(1..4)]), + and([q9 <= s_ExplicitVarSizeWithMarker_Marker -> + or([s_ExplicitVarSizeWithDummy[q11] != 5 /\ + s_ExplicitVarSizeWithDummy[q11] = s_ExplicitVarSizeWithMarker_Values[q9] + | q11 : int(1..4)]) + | q9 : int(1..4)]), + and([s_ExplicitVarSizeWithDummy[q13] != 5 -> + or([q15 <= s_ExplicitVarSizeWithMarker_Marker /\ + s_ExplicitVarSizeWithMarker_Values[q15] = s_ExplicitVarSizeWithDummy[q13] + | q15 : int(1..4)]) + | q13 : int(1..4)]) + diff --git a/tests/exhaustive/basic/name-reuse/expected/model_2_4-solution000001.solution b/tests/exhaustive/basic/name-reuse/expected/model_2_4-solution000001.solution new file mode 100644 index 0000000000..d4f1477569 --- /dev/null +++ b/tests/exhaustive/basic/name-reuse/expected/model_2_4-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting conjure_aux1 be 1 +letting s be {3} diff --git a/tests/exhaustive/basic/name-reuse/expected/model_2_4-solution000002.solution b/tests/exhaustive/basic/name-reuse/expected/model_2_4-solution000002.solution new file mode 100644 index 0000000000..ab91f42e83 --- /dev/null +++ b/tests/exhaustive/basic/name-reuse/expected/model_2_4-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting conjure_aux1 be 1 +letting s be {3, 4} diff --git a/tests/exhaustive/basic/name-reuse/expected/model_2_4.eprime b/tests/exhaustive/basic/name-reuse/expected/model_2_4.eprime new file mode 100644 index 0000000000..a42a0dabce --- /dev/null +++ b/tests/exhaustive/basic/name-reuse/expected/model_2_4.eprime @@ -0,0 +1,35 @@ +language ESSENCE' 1.0 + +find conjure_aux1: int(1) +find s_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +find s_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find s_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +find conjure_aux2: int(1..5) +branching on + [conjure_aux1, s_ExplicitVarSizeWithFlags_Flags, s_ExplicitVarSizeWithFlags_Values, s_ExplicitVarSizeWithDummy] +such that + and([s_ExplicitVarSizeWithDummy[q19] != 5 -> s_ExplicitVarSizeWithDummy[q19] >= conjure_aux2 | q19 : int(1..4)]), + sum([toInt(s_ExplicitVarSizeWithDummy[q19] != 5) | q19 : int(1..4)]) > 0 -> + or([s_ExplicitVarSizeWithDummy[q19] != 5 /\ s_ExplicitVarSizeWithDummy[q19] = conjure_aux2 | q19 : int(1..4)]), + sum([toInt(s_ExplicitVarSizeWithDummy[q19] != 5) | q19 : int(1..4)]) = 0 -> conjure_aux2 = 1, + conjure_aux2 = 3, + sum([toInt(s_ExplicitVarSizeWithDummy[q19] != 5) | q19 : int(1..4)]) > 0, + and([s_ExplicitVarSizeWithDummy[q1] < s_ExplicitVarSizeWithDummy[q1 + 1] \/ s_ExplicitVarSizeWithDummy[q1] = 5 + | q1 : int(1..3)]), + and([s_ExplicitVarSizeWithDummy[q2] = 5 -> s_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..3)]), + and([s_ExplicitVarSizeWithFlags_Flags[q5 + 1] -> + s_ExplicitVarSizeWithFlags_Values[q5] < s_ExplicitVarSizeWithFlags_Values[q5 + 1] + | q5 : int(1..3)]), + and([s_ExplicitVarSizeWithFlags_Flags[q6] = false -> s_ExplicitVarSizeWithFlags_Values[q6] = 1 | q6 : int(1..4)]), + and([s_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> s_ExplicitVarSizeWithFlags_Flags[q7] | q7 : int(1..3)]), + and([s_ExplicitVarSizeWithFlags_Flags[q11] -> + or([s_ExplicitVarSizeWithDummy[q13] != 5 /\ + s_ExplicitVarSizeWithDummy[q13] = s_ExplicitVarSizeWithFlags_Values[q11] + | q13 : int(1..4)]) + | q11 : int(1..4)]), + and([s_ExplicitVarSizeWithDummy[q15] != 5 -> + or([s_ExplicitVarSizeWithFlags_Flags[q17] /\ + s_ExplicitVarSizeWithFlags_Values[q17] = s_ExplicitVarSizeWithDummy[q15] + | q17 : int(1..4)]) + | q15 : int(1..4)]) + diff --git a/tests/exhaustive/basic/name-reuse/expected/model_3_1-solution000001.solution b/tests/exhaustive/basic/name-reuse/expected/model_3_1-solution000001.solution new file mode 100644 index 0000000000..d4f1477569 --- /dev/null +++ b/tests/exhaustive/basic/name-reuse/expected/model_3_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting conjure_aux1 be 1 +letting s be {3} diff --git a/tests/exhaustive/basic/name-reuse/expected/model_3_1-solution000002.solution b/tests/exhaustive/basic/name-reuse/expected/model_3_1-solution000002.solution new file mode 100644 index 0000000000..ab91f42e83 --- /dev/null +++ b/tests/exhaustive/basic/name-reuse/expected/model_3_1-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting conjure_aux1 be 1 +letting s be {3, 4} diff --git a/tests/exhaustive/basic/name-reuse/expected/model_3_1.eprime b/tests/exhaustive/basic/name-reuse/expected/model_3_1.eprime new file mode 100644 index 0000000000..0f6a2844e2 --- /dev/null +++ b/tests/exhaustive/basic/name-reuse/expected/model_3_1.eprime @@ -0,0 +1,27 @@ +language ESSENCE' 1.0 + +find conjure_aux1: int(1) +find s_ExplicitVarSizeWithMarker_Marker: int(0..4) +find s_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +find s_Occurrence: matrix indexed by [int(1..4)] of bool +find conjure_aux2: int(1..4) +branching on [conjure_aux1, s_Occurrence, s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithMarker_Values] +such that + and([q6 <= s_ExplicitVarSizeWithMarker_Marker -> s_ExplicitVarSizeWithMarker_Values[q6] >= conjure_aux2 + | q6 : int(1..4)]), + sum([toInt(q6 <= s_ExplicitVarSizeWithMarker_Marker) | q6 : int(1..4)]) > 0 -> + or([q6 <= s_ExplicitVarSizeWithMarker_Marker /\ s_ExplicitVarSizeWithMarker_Values[q6] = conjure_aux2 + | q6 : int(1..4)]), + sum([toInt(q6 <= s_ExplicitVarSizeWithMarker_Marker) | q6 : int(1..4)]) = 0 -> conjure_aux2 = 1, + conjure_aux2 = 3, + sum([toInt(q6 <= s_ExplicitVarSizeWithMarker_Marker) | q6 : int(1..4)]) > 0, + and([q1 + 1 <= s_ExplicitVarSizeWithMarker_Marker -> + s_ExplicitVarSizeWithMarker_Values[q1] < s_ExplicitVarSizeWithMarker_Values[q1 + 1] + | q1 : int(1..3)]), + and([q2 > s_ExplicitVarSizeWithMarker_Marker -> s_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..4)]), + and([s_Occurrence[q7] -> + or([q9 <= s_ExplicitVarSizeWithMarker_Marker /\ s_ExplicitVarSizeWithMarker_Values[q9] = q7 | q9 : int(1..4)]) + | q7 : int(1..4)]), + and([q11 <= s_ExplicitVarSizeWithMarker_Marker -> s_Occurrence[s_ExplicitVarSizeWithMarker_Values[q11]] + | q11 : int(1..4)]) + diff --git a/tests/exhaustive/basic/name-reuse/expected/model_3_2-solution000001.solution b/tests/exhaustive/basic/name-reuse/expected/model_3_2-solution000001.solution new file mode 100644 index 0000000000..ab91f42e83 --- /dev/null +++ b/tests/exhaustive/basic/name-reuse/expected/model_3_2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting conjure_aux1 be 1 +letting s be {3, 4} diff --git a/tests/exhaustive/basic/name-reuse/expected/model_3_2-solution000002.solution b/tests/exhaustive/basic/name-reuse/expected/model_3_2-solution000002.solution new file mode 100644 index 0000000000..d4f1477569 --- /dev/null +++ b/tests/exhaustive/basic/name-reuse/expected/model_3_2-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting conjure_aux1 be 1 +letting s be {3} diff --git a/tests/exhaustive/basic/name-reuse/expected/model_3_2.eprime b/tests/exhaustive/basic/name-reuse/expected/model_3_2.eprime new file mode 100644 index 0000000000..ae3b9a8a9d --- /dev/null +++ b/tests/exhaustive/basic/name-reuse/expected/model_3_2.eprime @@ -0,0 +1,36 @@ +language ESSENCE' 1.0 + +find conjure_aux1: int(1) +find s_ExplicitVarSizeWithMarker_Marker: int(0..4) +find s_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +find s_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +find conjure_aux2: int(1..4) +branching on + [conjure_aux1, s_ExplicitVarSizeWithDummy, s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithMarker_Values] +such that + and([q17 <= s_ExplicitVarSizeWithMarker_Marker -> s_ExplicitVarSizeWithMarker_Values[q17] >= conjure_aux2 + | q17 : int(1..4)]), + sum([toInt(q17 <= s_ExplicitVarSizeWithMarker_Marker) | q17 : int(1..4)]) > 0 -> + or([q17 <= s_ExplicitVarSizeWithMarker_Marker /\ s_ExplicitVarSizeWithMarker_Values[q17] = conjure_aux2 + | q17 : int(1..4)]), + sum([toInt(q17 <= s_ExplicitVarSizeWithMarker_Marker) | q17 : int(1..4)]) = 0 -> conjure_aux2 = 1, + conjure_aux2 = 3, + sum([toInt(q17 <= s_ExplicitVarSizeWithMarker_Marker) | q17 : int(1..4)]) > 0, + and([q1 + 1 <= s_ExplicitVarSizeWithMarker_Marker -> + s_ExplicitVarSizeWithMarker_Values[q1] < s_ExplicitVarSizeWithMarker_Values[q1 + 1] + | q1 : int(1..3)]), + and([q2 > s_ExplicitVarSizeWithMarker_Marker -> s_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..4)]), + and([s_ExplicitVarSizeWithDummy[q4] < s_ExplicitVarSizeWithDummy[q4 + 1] \/ s_ExplicitVarSizeWithDummy[q4] = 5 + | q4 : int(1..3)]), + and([s_ExplicitVarSizeWithDummy[q5] = 5 -> s_ExplicitVarSizeWithDummy[q5 + 1] = 5 | q5 : int(1..3)]), + and([s_ExplicitVarSizeWithDummy[q9] != 5 -> + or([q11 <= s_ExplicitVarSizeWithMarker_Marker /\ + s_ExplicitVarSizeWithMarker_Values[q11] = s_ExplicitVarSizeWithDummy[q9] + | q11 : int(1..4)]) + | q9 : int(1..4)]), + and([q13 <= s_ExplicitVarSizeWithMarker_Marker -> + or([s_ExplicitVarSizeWithDummy[q15] != 5 /\ + s_ExplicitVarSizeWithDummy[q15] = s_ExplicitVarSizeWithMarker_Values[q13] + | q15 : int(1..4)]) + | q13 : int(1..4)]) + diff --git a/tests/exhaustive/basic/name-reuse/expected/model_3_3-solution000001.solution b/tests/exhaustive/basic/name-reuse/expected/model_3_3-solution000001.solution new file mode 100644 index 0000000000..d4f1477569 --- /dev/null +++ b/tests/exhaustive/basic/name-reuse/expected/model_3_3-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting conjure_aux1 be 1 +letting s be {3} diff --git a/tests/exhaustive/basic/name-reuse/expected/model_3_3-solution000002.solution b/tests/exhaustive/basic/name-reuse/expected/model_3_3-solution000002.solution new file mode 100644 index 0000000000..ab91f42e83 --- /dev/null +++ b/tests/exhaustive/basic/name-reuse/expected/model_3_3-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting conjure_aux1 be 1 +letting s be {3, 4} diff --git a/tests/exhaustive/basic/name-reuse/expected/model_3_3.eprime b/tests/exhaustive/basic/name-reuse/expected/model_3_3.eprime new file mode 100644 index 0000000000..ce6a4c6421 --- /dev/null +++ b/tests/exhaustive/basic/name-reuse/expected/model_3_3.eprime @@ -0,0 +1,21 @@ +language ESSENCE' 1.0 + +find conjure_aux1: int(1) +find s_ExplicitVarSizeWithMarker_Marker: int(0..4) +find s_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +find conjure_aux2: int(1..4) +branching on [conjure_aux1, s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithMarker_Values] +such that + and([q5 <= s_ExplicitVarSizeWithMarker_Marker -> s_ExplicitVarSizeWithMarker_Values[q5] >= conjure_aux2 + | q5 : int(1..4)]), + sum([toInt(q5 <= s_ExplicitVarSizeWithMarker_Marker) | q5 : int(1..4)]) > 0 -> + or([q5 <= s_ExplicitVarSizeWithMarker_Marker /\ s_ExplicitVarSizeWithMarker_Values[q5] = conjure_aux2 + | q5 : int(1..4)]), + sum([toInt(q5 <= s_ExplicitVarSizeWithMarker_Marker) | q5 : int(1..4)]) = 0 -> conjure_aux2 = 1, + conjure_aux2 = 3, + sum([toInt(q5 <= s_ExplicitVarSizeWithMarker_Marker) | q5 : int(1..4)]) > 0, + and([q1 + 1 <= s_ExplicitVarSizeWithMarker_Marker -> + s_ExplicitVarSizeWithMarker_Values[q1] < s_ExplicitVarSizeWithMarker_Values[q1 + 1] + | q1 : int(1..3)]), + and([q2 > s_ExplicitVarSizeWithMarker_Marker -> s_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..4)]) + diff --git a/tests/exhaustive/basic/name-reuse/expected/model_3_4-solution000001.solution b/tests/exhaustive/basic/name-reuse/expected/model_3_4-solution000001.solution new file mode 100644 index 0000000000..d4f1477569 --- /dev/null +++ b/tests/exhaustive/basic/name-reuse/expected/model_3_4-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting conjure_aux1 be 1 +letting s be {3} diff --git a/tests/exhaustive/basic/name-reuse/expected/model_3_4-solution000002.solution b/tests/exhaustive/basic/name-reuse/expected/model_3_4-solution000002.solution new file mode 100644 index 0000000000..ab91f42e83 --- /dev/null +++ b/tests/exhaustive/basic/name-reuse/expected/model_3_4-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting conjure_aux1 be 1 +letting s be {3, 4} diff --git a/tests/exhaustive/basic/name-reuse/expected/model_3_4.eprime b/tests/exhaustive/basic/name-reuse/expected/model_3_4.eprime new file mode 100644 index 0000000000..a98bd89235 --- /dev/null +++ b/tests/exhaustive/basic/name-reuse/expected/model_3_4.eprime @@ -0,0 +1,40 @@ +language ESSENCE' 1.0 + +find conjure_aux1: int(1) +find s_ExplicitVarSizeWithMarker_Marker: int(0..4) +find s_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +find s_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find s_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +find conjure_aux2: int(1..4) +branching on + [conjure_aux1, s_ExplicitVarSizeWithFlags_Flags, s_ExplicitVarSizeWithFlags_Values, + s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithMarker_Values] +such that + and([q18 <= s_ExplicitVarSizeWithMarker_Marker -> s_ExplicitVarSizeWithMarker_Values[q18] >= conjure_aux2 + | q18 : int(1..4)]), + sum([toInt(q18 <= s_ExplicitVarSizeWithMarker_Marker) | q18 : int(1..4)]) > 0 -> + or([q18 <= s_ExplicitVarSizeWithMarker_Marker /\ s_ExplicitVarSizeWithMarker_Values[q18] = conjure_aux2 + | q18 : int(1..4)]), + sum([toInt(q18 <= s_ExplicitVarSizeWithMarker_Marker) | q18 : int(1..4)]) = 0 -> conjure_aux2 = 1, + conjure_aux2 = 3, + sum([toInt(q18 <= s_ExplicitVarSizeWithMarker_Marker) | q18 : int(1..4)]) > 0, + and([q1 + 1 <= s_ExplicitVarSizeWithMarker_Marker -> + s_ExplicitVarSizeWithMarker_Values[q1] < s_ExplicitVarSizeWithMarker_Values[q1 + 1] + | q1 : int(1..3)]), + and([q2 > s_ExplicitVarSizeWithMarker_Marker -> s_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..4)]), + and([s_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> + s_ExplicitVarSizeWithFlags_Values[q4] < s_ExplicitVarSizeWithFlags_Values[q4 + 1] + | q4 : int(1..3)]), + and([s_ExplicitVarSizeWithFlags_Flags[q5] = false -> s_ExplicitVarSizeWithFlags_Values[q5] = 1 | q5 : int(1..4)]), + and([s_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> s_ExplicitVarSizeWithFlags_Flags[q6] | q6 : int(1..3)]), + and([s_ExplicitVarSizeWithFlags_Flags[q10] -> + or([q12 <= s_ExplicitVarSizeWithMarker_Marker /\ + s_ExplicitVarSizeWithMarker_Values[q12] = s_ExplicitVarSizeWithFlags_Values[q10] + | q12 : int(1..4)]) + | q10 : int(1..4)]), + and([q14 <= s_ExplicitVarSizeWithMarker_Marker -> + or([s_ExplicitVarSizeWithFlags_Flags[q16] /\ + s_ExplicitVarSizeWithFlags_Values[q16] = s_ExplicitVarSizeWithMarker_Values[q14] + | q16 : int(1..4)]) + | q14 : int(1..4)]) + diff --git a/tests/exhaustive/basic/name-reuse/expected/model_4_1-solution000001.solution b/tests/exhaustive/basic/name-reuse/expected/model_4_1-solution000001.solution new file mode 100644 index 0000000000..d4f1477569 --- /dev/null +++ b/tests/exhaustive/basic/name-reuse/expected/model_4_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting conjure_aux1 be 1 +letting s be {3} diff --git a/tests/exhaustive/basic/name-reuse/expected/model_4_1-solution000002.solution b/tests/exhaustive/basic/name-reuse/expected/model_4_1-solution000002.solution new file mode 100644 index 0000000000..ab91f42e83 --- /dev/null +++ b/tests/exhaustive/basic/name-reuse/expected/model_4_1-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting conjure_aux1 be 1 +letting s be {3, 4} diff --git a/tests/exhaustive/basic/name-reuse/expected/model_4_1.eprime b/tests/exhaustive/basic/name-reuse/expected/model_4_1.eprime new file mode 100644 index 0000000000..598929e0aa --- /dev/null +++ b/tests/exhaustive/basic/name-reuse/expected/model_4_1.eprime @@ -0,0 +1,28 @@ +language ESSENCE' 1.0 + +find conjure_aux1: int(1) +find s_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find s_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +find s_Occurrence: matrix indexed by [int(1..4)] of bool +find conjure_aux2: int(1..4) +branching on [conjure_aux1, s_Occurrence, s_ExplicitVarSizeWithFlags_Flags, s_ExplicitVarSizeWithFlags_Values] +such that + and([s_ExplicitVarSizeWithFlags_Flags[q13] -> s_ExplicitVarSizeWithFlags_Values[q13] >= conjure_aux2 + | q13 : int(1..4)]), + sum([toInt(s_ExplicitVarSizeWithFlags_Flags[q13]) | q13 : int(1..4)]) > 0 -> + or([s_ExplicitVarSizeWithFlags_Flags[q13] /\ s_ExplicitVarSizeWithFlags_Values[q13] = conjure_aux2 + | q13 : int(1..4)]), + sum([toInt(s_ExplicitVarSizeWithFlags_Flags[q13]) | q13 : int(1..4)]) = 0 -> conjure_aux2 = 1, + conjure_aux2 = 3, + sum([toInt(s_ExplicitVarSizeWithFlags_Flags[q13]) | q13 : int(1..4)]) > 0, + and([s_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> + s_ExplicitVarSizeWithFlags_Values[q1] < s_ExplicitVarSizeWithFlags_Values[q1 + 1] + | q1 : int(1..3)]), + and([s_ExplicitVarSizeWithFlags_Flags[q2] = false -> s_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..4)]), + and([s_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> s_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), + and([s_Occurrence[q7] -> + or([s_ExplicitVarSizeWithFlags_Flags[q9] /\ s_ExplicitVarSizeWithFlags_Values[q9] = q7 | q9 : int(1..4)]) + | q7 : int(1..4)]), + and([s_ExplicitVarSizeWithFlags_Flags[q11] -> s_Occurrence[s_ExplicitVarSizeWithFlags_Values[q11]] + | q11 : int(1..4)]) + diff --git a/tests/exhaustive/basic/name-reuse/expected/model_4_2-solution000001.solution b/tests/exhaustive/basic/name-reuse/expected/model_4_2-solution000001.solution new file mode 100644 index 0000000000..ab91f42e83 --- /dev/null +++ b/tests/exhaustive/basic/name-reuse/expected/model_4_2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting conjure_aux1 be 1 +letting s be {3, 4} diff --git a/tests/exhaustive/basic/name-reuse/expected/model_4_2-solution000002.solution b/tests/exhaustive/basic/name-reuse/expected/model_4_2-solution000002.solution new file mode 100644 index 0000000000..d4f1477569 --- /dev/null +++ b/tests/exhaustive/basic/name-reuse/expected/model_4_2-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting conjure_aux1 be 1 +letting s be {3} diff --git a/tests/exhaustive/basic/name-reuse/expected/model_4_2.eprime b/tests/exhaustive/basic/name-reuse/expected/model_4_2.eprime new file mode 100644 index 0000000000..41f3fb08cd --- /dev/null +++ b/tests/exhaustive/basic/name-reuse/expected/model_4_2.eprime @@ -0,0 +1,37 @@ +language ESSENCE' 1.0 + +find conjure_aux1: int(1) +find s_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find s_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +find s_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +find conjure_aux2: int(1..4) +branching on + [conjure_aux1, s_ExplicitVarSizeWithDummy, s_ExplicitVarSizeWithFlags_Flags, s_ExplicitVarSizeWithFlags_Values] +such that + and([s_ExplicitVarSizeWithFlags_Flags[q19] -> s_ExplicitVarSizeWithFlags_Values[q19] >= conjure_aux2 + | q19 : int(1..4)]), + sum([toInt(s_ExplicitVarSizeWithFlags_Flags[q19]) | q19 : int(1..4)]) > 0 -> + or([s_ExplicitVarSizeWithFlags_Flags[q19] /\ s_ExplicitVarSizeWithFlags_Values[q19] = conjure_aux2 + | q19 : int(1..4)]), + sum([toInt(s_ExplicitVarSizeWithFlags_Flags[q19]) | q19 : int(1..4)]) = 0 -> conjure_aux2 = 1, + conjure_aux2 = 3, + sum([toInt(s_ExplicitVarSizeWithFlags_Flags[q19]) | q19 : int(1..4)]) > 0, + and([s_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> + s_ExplicitVarSizeWithFlags_Values[q1] < s_ExplicitVarSizeWithFlags_Values[q1 + 1] + | q1 : int(1..3)]), + and([s_ExplicitVarSizeWithFlags_Flags[q2] = false -> s_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..4)]), + and([s_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> s_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), + and([s_ExplicitVarSizeWithDummy[q6] < s_ExplicitVarSizeWithDummy[q6 + 1] \/ s_ExplicitVarSizeWithDummy[q6] = 5 + | q6 : int(1..3)]), + and([s_ExplicitVarSizeWithDummy[q7] = 5 -> s_ExplicitVarSizeWithDummy[q7 + 1] = 5 | q7 : int(1..3)]), + and([s_ExplicitVarSizeWithDummy[q11] != 5 -> + or([s_ExplicitVarSizeWithFlags_Flags[q13] /\ + s_ExplicitVarSizeWithFlags_Values[q13] = s_ExplicitVarSizeWithDummy[q11] + | q13 : int(1..4)]) + | q11 : int(1..4)]), + and([s_ExplicitVarSizeWithFlags_Flags[q15] -> + or([s_ExplicitVarSizeWithDummy[q17] != 5 /\ + s_ExplicitVarSizeWithDummy[q17] = s_ExplicitVarSizeWithFlags_Values[q15] + | q17 : int(1..4)]) + | q15 : int(1..4)]) + diff --git a/tests/exhaustive/basic/name-reuse/expected/model_4_3-solution000001.solution b/tests/exhaustive/basic/name-reuse/expected/model_4_3-solution000001.solution new file mode 100644 index 0000000000..d4f1477569 --- /dev/null +++ b/tests/exhaustive/basic/name-reuse/expected/model_4_3-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting conjure_aux1 be 1 +letting s be {3} diff --git a/tests/exhaustive/basic/name-reuse/expected/model_4_3-solution000002.solution b/tests/exhaustive/basic/name-reuse/expected/model_4_3-solution000002.solution new file mode 100644 index 0000000000..ab91f42e83 --- /dev/null +++ b/tests/exhaustive/basic/name-reuse/expected/model_4_3-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting conjure_aux1 be 1 +letting s be {3, 4} diff --git a/tests/exhaustive/basic/name-reuse/expected/model_4_3.eprime b/tests/exhaustive/basic/name-reuse/expected/model_4_3.eprime new file mode 100644 index 0000000000..36aeadc30e --- /dev/null +++ b/tests/exhaustive/basic/name-reuse/expected/model_4_3.eprime @@ -0,0 +1,40 @@ +language ESSENCE' 1.0 + +find conjure_aux1: int(1) +find s_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find s_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +find s_ExplicitVarSizeWithMarker_Marker: int(0..4) +find s_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +find conjure_aux2: int(1..4) +branching on + [conjure_aux1, s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithMarker_Values, + s_ExplicitVarSizeWithFlags_Flags, s_ExplicitVarSizeWithFlags_Values] +such that + and([s_ExplicitVarSizeWithFlags_Flags[q18] -> s_ExplicitVarSizeWithFlags_Values[q18] >= conjure_aux2 + | q18 : int(1..4)]), + sum([toInt(s_ExplicitVarSizeWithFlags_Flags[q18]) | q18 : int(1..4)]) > 0 -> + or([s_ExplicitVarSizeWithFlags_Flags[q18] /\ s_ExplicitVarSizeWithFlags_Values[q18] = conjure_aux2 + | q18 : int(1..4)]), + sum([toInt(s_ExplicitVarSizeWithFlags_Flags[q18]) | q18 : int(1..4)]) = 0 -> conjure_aux2 = 1, + conjure_aux2 = 3, + sum([toInt(s_ExplicitVarSizeWithFlags_Flags[q18]) | q18 : int(1..4)]) > 0, + and([s_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> + s_ExplicitVarSizeWithFlags_Values[q1] < s_ExplicitVarSizeWithFlags_Values[q1 + 1] + | q1 : int(1..3)]), + and([s_ExplicitVarSizeWithFlags_Flags[q2] = false -> s_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..4)]), + and([s_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> s_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), + and([q6 + 1 <= s_ExplicitVarSizeWithMarker_Marker -> + s_ExplicitVarSizeWithMarker_Values[q6] < s_ExplicitVarSizeWithMarker_Values[q6 + 1] + | q6 : int(1..3)]), + and([q7 > s_ExplicitVarSizeWithMarker_Marker -> s_ExplicitVarSizeWithMarker_Values[q7] = 1 | q7 : int(1..4)]), + and([q10 <= s_ExplicitVarSizeWithMarker_Marker -> + or([s_ExplicitVarSizeWithFlags_Flags[q12] /\ + s_ExplicitVarSizeWithFlags_Values[q12] = s_ExplicitVarSizeWithMarker_Values[q10] + | q12 : int(1..4)]) + | q10 : int(1..4)]), + and([s_ExplicitVarSizeWithFlags_Flags[q14] -> + or([q16 <= s_ExplicitVarSizeWithMarker_Marker /\ + s_ExplicitVarSizeWithMarker_Values[q16] = s_ExplicitVarSizeWithFlags_Values[q14] + | q16 : int(1..4)]) + | q14 : int(1..4)]) + diff --git a/tests/exhaustive/basic/name-reuse/expected/model_4_4-solution000001.solution b/tests/exhaustive/basic/name-reuse/expected/model_4_4-solution000001.solution new file mode 100644 index 0000000000..d4f1477569 --- /dev/null +++ b/tests/exhaustive/basic/name-reuse/expected/model_4_4-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting conjure_aux1 be 1 +letting s be {3} diff --git a/tests/exhaustive/basic/name-reuse/expected/model_4_4-solution000002.solution b/tests/exhaustive/basic/name-reuse/expected/model_4_4-solution000002.solution new file mode 100644 index 0000000000..ab91f42e83 --- /dev/null +++ b/tests/exhaustive/basic/name-reuse/expected/model_4_4-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting conjure_aux1 be 1 +letting s be {3, 4} diff --git a/tests/exhaustive/basic/name-reuse/expected/model_4_4.eprime b/tests/exhaustive/basic/name-reuse/expected/model_4_4.eprime new file mode 100644 index 0000000000..1347ac40de --- /dev/null +++ b/tests/exhaustive/basic/name-reuse/expected/model_4_4.eprime @@ -0,0 +1,21 @@ +language ESSENCE' 1.0 + +find conjure_aux1: int(1) +find s_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find s_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +find conjure_aux2: int(1..4) +branching on [conjure_aux1, s_ExplicitVarSizeWithFlags_Flags, s_ExplicitVarSizeWithFlags_Values] +such that + and([s_ExplicitVarSizeWithFlags_Flags[q7] -> s_ExplicitVarSizeWithFlags_Values[q7] >= conjure_aux2 + | q7 : int(1..4)]), + sum([toInt(s_ExplicitVarSizeWithFlags_Flags[q7]) | q7 : int(1..4)]) > 0 -> + or([s_ExplicitVarSizeWithFlags_Flags[q7] /\ s_ExplicitVarSizeWithFlags_Values[q7] = conjure_aux2 | q7 : int(1..4)]), + sum([toInt(s_ExplicitVarSizeWithFlags_Flags[q7]) | q7 : int(1..4)]) = 0 -> conjure_aux2 = 1, + conjure_aux2 = 3, + sum([toInt(s_ExplicitVarSizeWithFlags_Flags[q7]) | q7 : int(1..4)]) > 0, + and([s_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> + s_ExplicitVarSizeWithFlags_Values[q1] < s_ExplicitVarSizeWithFlags_Values[q1 + 1] + | q1 : int(1..3)]), + and([s_ExplicitVarSizeWithFlags_Flags[q2] = false -> s_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..4)]), + and([s_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> s_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]) + diff --git a/tests/exhaustive/basic/partition_01/expected/model_2.eprime b/tests/exhaustive/basic/partition_01/expected/model_2.eprime index 950eec8576..b893233802 100644 --- a/tests/exhaustive/basic/partition_01/expected/model_2.eprime +++ b/tests/exhaustive/basic/partition_01/expected/model_2.eprime @@ -3,22 +3,8 @@ language ESSENCE' 1.0 find x_PartitionAsSet_ExplicitR2_Occurrence: matrix indexed by [int(1..2), int(3..8)] of bool branching on [x_PartitionAsSet_ExplicitR2_Occurrence] such that -<<<<<<< HEAD - allDiff([x_PartitionAsSet_ExplicitR3_Explicit[q12, q13] | q12 : int(1..2), q13 : int(1..3)]), - [x_PartitionAsSet_ExplicitR3_Explicit[1, q9] | q9 : int(1..3)] >>>>>> master - | q6 : int(1..2)]) - | q5 : int(1..2)]) -======= and([1 = sum([toInt(x_PartitionAsSet_ExplicitR2_Occurrence[q11, q1]) | q11 : int(1..2)]) | q1 : int(3..8)]), [-toInt(x_PartitionAsSet_ExplicitR2_Occurrence[1, q8]) | q8 : int(3..8)] >>>>>> main diff --git a/tests/exhaustive/basic/partition_01/expected/model_2.eprime.orig b/tests/exhaustive/basic/partition_01/expected/model_2.eprime.orig deleted file mode 100644 index 829c1f84a8..0000000000 --- a/tests/exhaustive/basic/partition_01/expected/model_2.eprime.orig +++ /dev/null @@ -1,17 +0,0 @@ -language ESSENCE' 1.0 - -find x_PartitionAsSet_ExplicitR3_Explicit: matrix indexed by [int(1..2), int(1..3)] of int(3..8) -branching on [x_PartitionAsSet_ExplicitR3_Explicit] -such that - allDiff([x_PartitionAsSet_ExplicitR3_Explicit[q12, q13] | q12 : int(1..2), q13 : int(1..3)]), - [x_PartitionAsSet_ExplicitR3_Explicit[1, q9] | q9 : int(1..3)] >>>>>> master - | q6 : int(1..2)]) - | q5 : int(1..2)]) - diff --git a/tests/exhaustive/basic/partition_02/expected/model_2.eprime b/tests/exhaustive/basic/partition_02/expected/model_2.eprime index 121146805d..61cba91532 100644 --- a/tests/exhaustive/basic/partition_02/expected/model_2.eprime +++ b/tests/exhaustive/basic/partition_02/expected/model_2.eprime @@ -14,8 +14,8 @@ such that | q26 : int(1..2)]), [x_PartitionAsSet_ExplicitR6_ExplicitVarSizeWithDummy[1, q13] | q13 : int(1..6)] - [x_PartitionAsSet_ExplicitR5_ExplicitVarSizeWithMarker_Values[q7, q8]; int(1)] x_PartitionAsSet_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q7] -> diff --git a/tests/exhaustive/basic/partition_03/expected/model_2.eprime b/tests/exhaustive/basic/partition_03/expected/model_2.eprime index 5bf41d80ca..44120a17bf 100644 --- a/tests/exhaustive/basic/partition_03/expected/model_2.eprime +++ b/tests/exhaustive/basic/partition_03/expected/model_2.eprime @@ -18,17 +18,9 @@ such that and([q5 > x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> and([x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q5, q11] = false | q11 : int(1..6)]) | q5 : int(1..6)]), -<<<<<<< HEAD - x_PartitionAsSet_ExplicitVarSizeWithMarkerR3_Marker <= 6, - and([q6 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR3_Marker -> - and([[x_PartitionAsSet_ExplicitVarSizeWithMarkerR3_Values_Explicit[q6, q7]; int(1)] 3 = sum([toInt(x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q6, q7]) | q7 : int(1..6)]) ->>>>>>> main | q6 : int(1..6)]), 6 = sum([toInt(q12 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker) * 3 | q12 : int(1..6)]) diff --git a/tests/exhaustive/basic/partition_05_1/expected/model_1-solution000001.solution b/tests/exhaustive/basic/partition_05_1/expected/model_1-solution000001.solution new file mode 100644 index 0000000000..b616543ee7 --- /dev/null +++ b/tests/exhaustive/basic/partition_05_1/expected/model_1-solution000001.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be partition({1, 3}, {2, 4}) +$ Visualisation for x +$ 1 3 +$ 2 4 + diff --git a/tests/exhaustive/basic/partition_05_1/expected/model_1.eprime.orig b/tests/exhaustive/basic/partition_05_1/expected/model_1.eprime.orig deleted file mode 100644 index ca7650b80c..0000000000 --- a/tests/exhaustive/basic/partition_05_1/expected/model_1.eprime.orig +++ /dev/null @@ -1,48 +0,0 @@ -language ESSENCE' 1.0 - -find x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker: int(0..4) -find x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence: matrix indexed by [int(1..4), int(1..4)] of bool -branching on - [x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker, - x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence] -such that - or([q27 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ - (x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q27, 1] /\ - x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q27, 3]) - | q27 : int(1..4)]), - and([q33 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> - !(x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q33, 1] /\ - x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q33, 2]) - | q33 : int(1..4)]), - and([1 = - sum([toInt(q16 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ - x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q16, q1]) - | q16 : int(1..4)]) - | q1 : int(1..4)]), - and([q17 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ - q18 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker - -> - sum([toInt(x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q17, q19]) | q19 : int(1..4)]) = - sum([toInt(x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q18, q20]) | q20 : int(1..4)]) - | q17 : int(1..4), q18 : int(1..4)]), - and([q21 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> - sum([toInt(x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q21, q22]) | q22 : int(1..4)]) >= 1 - | q21 : int(1..4)]), - and([q6 + 1 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> - [-toInt(x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q6, q11]) | q11 : int(1..4)] x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> - and([x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q7, q13] = false | q13 : int(1..4)]) - | q7 : int(1..4)]), - x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker <= 4, - and([q8 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> - sum([toInt(x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q8, q9]) | q9 : int(1..4)]) <= 4 - | q8 : int(1..4)]), - 4 = - sum([toInt(q14 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker) * - catchUndef(sum([toInt(x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q14, q15]) - | q15 : int(1..4)]), - 0) - | q14 : int(1..4)]) - diff --git a/tests/exhaustive/basic/partition_05_1/expected/model_2-solution000001.solution b/tests/exhaustive/basic/partition_05_1/expected/model_2-solution000001.solution new file mode 100644 index 0000000000..b616543ee7 --- /dev/null +++ b/tests/exhaustive/basic/partition_05_1/expected/model_2-solution000001.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be partition({1, 3}, {2, 4}) +$ Visualisation for x +$ 1 3 +$ 2 4 + diff --git a/tests/exhaustive/basic/partition_05_1/expected/model_2.eprime.orig b/tests/exhaustive/basic/partition_05_1/expected/model_2.eprime.orig deleted file mode 100644 index ede6ceb3a9..0000000000 --- a/tests/exhaustive/basic/partition_05_1/expected/model_2.eprime.orig +++ /dev/null @@ -1,83 +0,0 @@ -language ESSENCE' 1.0 - -find x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker: int(0..4) -find x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy: - matrix indexed by [int(1..4), int(1..4)] of int(1..5) -branching on - [x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker, - x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy] -such that - or([q35 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ - (or([x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q35, q38] != 5 /\ - x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q35, q38] = 1 - | q38 : int(1..4)]) - /\ - or([x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q35, q40] != 5 /\ - x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q35, q40] = 3 - | q40 : int(1..4)])) - | q35 : int(1..4)]), - and([q45 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - !(or([x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q45, q48] != 5 /\ - x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q45, q48] = 1 - | q48 : int(1..4)]) - /\ - or([x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q45, q50] != 5 /\ - x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q45, q50] = 2 - | q50 : int(1..4)])) - | q45 : int(1..4)]), - alldifferent_except([toInt(q20 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ - x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q20, q21] != - 5) - * - catchUndef(x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q20, q21], - 0) - | q20 : int(1..4), q21 : int(1..4)], - 0), - and([q22 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ - q23 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker - -> - sum([toInt(x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q22, q25] != 5) - | q25 : int(1..4)]) - = - sum([toInt(x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q23, q27] != 5) - | q27 : int(1..4)]) - | q22 : int(1..4), q23 : int(1..4)]), - and([q28 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - sum([toInt(x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q28, q30] != 5) - | q30 : int(1..4)]) - >= 1 - | q28 : int(1..4)]), - and([q6 + 1 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - [x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q6, q14] | q14 : int(1..4)] x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - and([x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q7, q19] = 1 - | q19 : int(1..4)]) - | q7 : int(1..4)]), - x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker <= 4, - and([q8 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - and([x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q8, q9] < - x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q8, q9 + 1] - \/ x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q8, q9] = 5 - | q9 : int(1..3)]) - | q8 : int(1..4)]), - and([q8 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - and([x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q8, q10] = 5 -> - x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q8, q10 + 1] = 5 - | q10 : int(1..3)]) - | q8 : int(1..4)]), - and([q8 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - sum([toInt(x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q8, q11] != 5) - | q11 : int(1..4)]) - <= 4 - | q8 : int(1..4)]), - 4 = - sum([toInt(q16 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker) * - catchUndef(sum([toInt(x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q16, q18] != - 5) - | q18 : int(1..4)]), - 0) - | q16 : int(1..4)]) - diff --git a/tests/exhaustive/basic/partition_05_1/expected/model_3-solution000001.solution b/tests/exhaustive/basic/partition_05_1/expected/model_3-solution000001.solution new file mode 100644 index 0000000000..b616543ee7 --- /dev/null +++ b/tests/exhaustive/basic/partition_05_1/expected/model_3-solution000001.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be partition({1, 3}, {2, 4}) +$ Visualisation for x +$ 1 3 +$ 2 4 + diff --git a/tests/exhaustive/basic/partition_05_1/expected/model_3.eprime.orig b/tests/exhaustive/basic/partition_05_1/expected/model_3.eprime.orig deleted file mode 100644 index c6e82e3987..0000000000 --- a/tests/exhaustive/basic/partition_05_1/expected/model_3.eprime.orig +++ /dev/null @@ -1,86 +0,0 @@ -language ESSENCE' 1.0 - -find x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker: int(0..4) -find x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker: - matrix indexed by [int(1..4)] of int(0..4) -find x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values: - matrix indexed by [int(1..4), int(1..4)] of int(1..4) -branching on - [x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker, - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker, - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values] -such that - or([q26 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - (or([q29 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q26] /\ - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q26, q29] = 1 - | q29 : int(1..4)]) - /\ - or([q31 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q26] /\ - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q26, q31] = 3 - | q31 : int(1..4)])) - | q26 : int(1..4)]), - and([q36 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - !(or([q39 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q36] /\ - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q36, q39] = 1 - | q39 : int(1..4)]) - /\ - or([q41 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q36] /\ - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q36, q41] = 2 - | q41 : int(1..4)])) - | q36 : int(1..4)]), - alldifferent_except([toInt(q17 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - q18 <= - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q17]) - * - catchUndef(x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q17, q18], - 0) - | q17 : int(1..4), q18 : int(1..4)], - 0), - and([q19 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - q20 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker - -> - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q19] = - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q20] - | q19 : int(1..4), q20 : int(1..4)]), - and([q21 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q21] >= 1 - | q21 : int(1..4)]), - and([q6 + 1 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - flatten([[x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q6]; int(1)], - [x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q6, q13] - | q13 : int(1..4)]; - int(1..2)]) - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q7] = 0 /\ - and([x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q7, q16] = 1 - | q16 : int(1..4)]) - | q7 : int(1..4)]), - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker <= 4, - and([q8 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - and([q9 + 1 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q8] -> - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q8, q9] < - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q8, q9 + 1] - | q9 : int(1..3)]) - | q8 : int(1..4)]), - and([q8 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - and([q10 > x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q8] -> - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q8, q10] = 1 - | q10 : int(1..4)]) - | q8 : int(1..4)]), - and([q8 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q8] <= 4 - | q8 : int(1..4)]), - 4 = - sum([toInt(q15 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker) * - catchUndef(x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q15], 0) - | q15 : int(1..4)]) - diff --git a/tests/exhaustive/basic/partition_05_1/expected/model_4-solution000001.solution b/tests/exhaustive/basic/partition_05_1/expected/model_4-solution000001.solution new file mode 100644 index 0000000000..b616543ee7 --- /dev/null +++ b/tests/exhaustive/basic/partition_05_1/expected/model_4-solution000001.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be partition({1, 3}, {2, 4}) +$ Visualisation for x +$ 1 3 +$ 2 4 + diff --git a/tests/exhaustive/basic/partition_05_1/expected/model_4.eprime.orig b/tests/exhaustive/basic/partition_05_1/expected/model_4.eprime.orig deleted file mode 100644 index 667deed4b3..0000000000 --- a/tests/exhaustive/basic/partition_05_1/expected/model_4.eprime.orig +++ /dev/null @@ -1,40 +0,0 @@ -language ESSENCE' 1.0 - -find x_PartitionOccurrence_NumParts: int(1..4) -find x_PartitionOccurrence_WhichPart: matrix indexed by [int(1..4)] of int(1..4) -find x_PartitionOccurrence_PartSizes: matrix indexed by [int(1..4)] of int(0..4) -find x_PartitionOccurrence_FirstIndex: matrix indexed by [int(1..4)] of int(1..4) -branching on - [x_PartitionOccurrence_NumParts, x_PartitionOccurrence_WhichPart, x_PartitionOccurrence_PartSizes, - x_PartitionOccurrence_FirstIndex] -such that - or([q15 <= x_PartitionOccurrence_NumParts /\ - (or([x_PartitionOccurrence_WhichPart[q19] = q15 /\ q19 = 1 | q19 : int(1..4)]) /\ - or([x_PartitionOccurrence_WhichPart[q21] = q15 /\ q21 = 3 | q21 : int(1..4)])) - | q15 : int(1..4)]), - and([q25 <= x_PartitionOccurrence_NumParts -> - !(or([x_PartitionOccurrence_WhichPart[q29] = q25 /\ q29 = 1 | q29 : int(1..4)]) /\ - or([x_PartitionOccurrence_WhichPart[q31] = q25 /\ q31 = 2 | q31 : int(1..4)])) - | q25 : int(1..4)]), - and([q1 <= x_PartitionOccurrence_NumParts -> x_PartitionOccurrence_PartSizes[q1] <= 4 | q1 : int(1..4)]), - and([q1 > x_PartitionOccurrence_NumParts -> x_PartitionOccurrence_PartSizes[q1] = 0 | q1 : int(1..4)]), - x_PartitionOccurrence_NumParts <= 4, - and([q2 <= x_PartitionOccurrence_NumParts -> or([x_PartitionOccurrence_WhichPart[q3] = q2 | q3 : int(1..4)]) - | q2 : int(3..4)]), - and([q4 <= x_PartitionOccurrence_NumParts -> - x_PartitionOccurrence_PartSizes[q4 - 1] = x_PartitionOccurrence_PartSizes[q4] - | q4 : int(2..4)]), - x_PartitionOccurrence_NumParts = max([x_PartitionOccurrence_WhichPart[q5] | q5 : int(1..4)]), - and([x_PartitionOccurrence_PartSizes[q6] = sum([toInt(x_PartitionOccurrence_WhichPart[q7] = q6) | q7 : int(1..4)]) - | q6 : int(1..4)]), - and([q8 <= x_PartitionOccurrence_NumParts -> - and([x_PartitionOccurrence_WhichPart[q9] = q8 -> x_PartitionOccurrence_FirstIndex[q8] <= q9 | q9 : int(1..4)]) - | q8 : int(1..4)]), - and([q8 <= x_PartitionOccurrence_NumParts -> - or([x_PartitionOccurrence_WhichPart[q9] = q8 /\ x_PartitionOccurrence_FirstIndex[q8] = q9 | q9 : int(1..4)]) - | q8 : int(1..4)]), - and([q8 > x_PartitionOccurrence_NumParts -> x_PartitionOccurrence_FirstIndex[q8] = 1 | q8 : int(1..4)]), - and([q10 <= x_PartitionOccurrence_NumParts /\ q11 <= x_PartitionOccurrence_NumParts -> - (q10 < q11 <-> x_PartitionOccurrence_FirstIndex[q10] < x_PartitionOccurrence_FirstIndex[q11]) - | q10 : int(1..4), q11 : int(1..4)]) - diff --git a/tests/exhaustive/basic/partition_05_2/expected/model_1-solution000001.solution b/tests/exhaustive/basic/partition_05_2/expected/model_1-solution000001.solution new file mode 100644 index 0000000000..b616543ee7 --- /dev/null +++ b/tests/exhaustive/basic/partition_05_2/expected/model_1-solution000001.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be partition({1, 3}, {2, 4}) +$ Visualisation for x +$ 1 3 +$ 2 4 + diff --git a/tests/exhaustive/basic/partition_05_2/expected/model_1.eprime.orig b/tests/exhaustive/basic/partition_05_2/expected/model_1.eprime.orig deleted file mode 100644 index 6265b3fc3d..0000000000 --- a/tests/exhaustive/basic/partition_05_2/expected/model_1.eprime.orig +++ /dev/null @@ -1,78 +0,0 @@ -language ESSENCE' 1.0 - -find x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker: int(0..4) -find x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence: matrix indexed by [int(1..4), int(1..4)] of bool -branching on - [x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker, - x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence] -such that - and([and([q27 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker, - x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q27, 2], - x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q27, q25]; - int(1..3)]) - -> 4 = q25 \/ 2 = q25 - | q27 : int(1..4), q25 : int(1..4)]), - or([and([q34 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker, - x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q34, 2], - x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q34, q32]; - int(1..3)]) - /\ q32 = 4 - | q34 : int(1..4), q32 : int(1..4)]), - or([and([q39 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker, - x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q39, 2], - x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q39, q37]; - int(1..3)]) - /\ q37 = 2 - | q39 : int(1..4), q37 : int(1..4)]), - and([q44 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ - x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q44, q42] - -> or([1 = q42, 2 = q42, 3 = q42, 4 = q42; int(1..4)]) - | q44 : int(1..4), q42 : int(1..4)]), - or([q51 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ - x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q51, q49] - /\ q49 = 1 - | q51 : int(1..4), q49 : int(1..4)]), - or([q56 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ - x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q56, q54] - /\ q54 = 2 - | q56 : int(1..4), q54 : int(1..4)]), - or([q61 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ - x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q61, q59] - /\ q59 = 3 - | q61 : int(1..4), q59 : int(1..4)]), - or([q66 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ - x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q66, q64] - /\ q64 = 4 - | q66 : int(1..4), q64 : int(1..4)]), - and([1 = - sum([toInt(q16 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ - x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q16, q1]) - | q16 : int(1..4)]) - | q1 : int(1..4)]), - and([q17 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ - q18 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker - -> - sum([toInt(x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q17, q19]) | q19 : int(1..4)]) = - sum([toInt(x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q18, q20]) | q20 : int(1..4)]) - | q17 : int(1..4), q18 : int(1..4)]), - and([q21 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> - sum([toInt(x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q21, q22]) | q22 : int(1..4)]) >= 1 - | q21 : int(1..4)]), - and([q6 + 1 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> - [-toInt(x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q6, q11]) | q11 : int(1..4)] x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> - and([x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q7, q13] = false | q13 : int(1..4)]) - | q7 : int(1..4)]), - x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker <= 4, - and([q8 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> - sum([toInt(x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q8, q9]) | q9 : int(1..4)]) <= 4 - | q8 : int(1..4)]), - 4 = - sum([toInt(q14 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker) * - catchUndef(sum([toInt(x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q14, q15]) - | q15 : int(1..4)]), - 0) - | q14 : int(1..4)]) - diff --git a/tests/exhaustive/basic/partition_05_2/expected/model_2-solution000001.solution b/tests/exhaustive/basic/partition_05_2/expected/model_2-solution000001.solution new file mode 100644 index 0000000000..b616543ee7 --- /dev/null +++ b/tests/exhaustive/basic/partition_05_2/expected/model_2-solution000001.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be partition({1, 3}, {2, 4}) +$ Visualisation for x +$ 1 3 +$ 2 4 + diff --git a/tests/exhaustive/basic/partition_05_2/expected/model_2.eprime.orig b/tests/exhaustive/basic/partition_05_2/expected/model_2.eprime.orig deleted file mode 100644 index 559aefda7e..0000000000 --- a/tests/exhaustive/basic/partition_05_2/expected/model_2.eprime.orig +++ /dev/null @@ -1,116 +0,0 @@ -language ESSENCE' 1.0 - -find x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker: int(0..4) -find x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy: - matrix indexed by [int(1..4), int(1..4)] of int(1..5) -branching on - [x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker, - x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy] -such that - and([and([q35 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker, - or([x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q35, q39] != 5 /\ - x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q35, q39] = 2 - | q39 : int(1..4)]), - x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q35, q36] != 5; - int(1..3)]) - -> - 4 = x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q35, q36] \/ - 2 = x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q35, q36] - | q35 : int(1..4), q36 : int(1..4)]), - or([and([q45 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker, - or([x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q45, q48] != 5 /\ - x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q45, q48] = 2 - | q48 : int(1..4)]), - x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q45, q46] != 5; - int(1..3)]) - /\ x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q45, q46] = 4 - | q45 : int(1..4), q46 : int(1..4)]), - or([and([q53 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker, - or([x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q53, q56] != 5 /\ - x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q53, q56] = 2 - | q56 : int(1..4)]), - x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q53, q54] != 5; - int(1..3)]) - /\ x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q53, q54] = 2 - | q53 : int(1..4), q54 : int(1..4)]), - and([q61 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ - x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q61, q62] != 5 - -> - or([1 = x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q61, q62], - 2 = x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q61, q62], - 3 = x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q61, q62], - 4 = x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q61, q62]; - int(1..4)]) - | q61 : int(1..4), q62 : int(1..4)]), - or([q69 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ - x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q69, q70] != 5 - /\ x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q69, q70] = 1 - | q69 : int(1..4), q70 : int(1..4)]), - or([q75 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ - x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q75, q76] != 5 - /\ x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q75, q76] = 2 - | q75 : int(1..4), q76 : int(1..4)]), - or([q81 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ - x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q81, q82] != 5 - /\ x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q81, q82] = 3 - | q81 : int(1..4), q82 : int(1..4)]), - or([q87 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ - x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q87, q88] != 5 - /\ x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q87, q88] = 4 - | q87 : int(1..4), q88 : int(1..4)]), - alldifferent_except([toInt(q20 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ - x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q20, q21] != - 5) - * - catchUndef(x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q20, q21], - 0) - | q20 : int(1..4), q21 : int(1..4)], - 0), - and([q22 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ - q23 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker - -> - sum([toInt(x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q22, q25] != 5) - | q25 : int(1..4)]) - = - sum([toInt(x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q23, q27] != 5) - | q27 : int(1..4)]) - | q22 : int(1..4), q23 : int(1..4)]), - and([q28 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - sum([toInt(x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q28, q30] != 5) - | q30 : int(1..4)]) - >= 1 - | q28 : int(1..4)]), - and([q6 + 1 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - [x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q6, q14] | q14 : int(1..4)] x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - and([x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q7, q19] = 1 - | q19 : int(1..4)]) - | q7 : int(1..4)]), - x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker <= 4, - and([q8 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - and([x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q8, q9] < - x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q8, q9 + 1] - \/ x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q8, q9] = 5 - | q9 : int(1..3)]) - | q8 : int(1..4)]), - and([q8 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - and([x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q8, q10] = 5 -> - x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q8, q10 + 1] = 5 - | q10 : int(1..3)]) - | q8 : int(1..4)]), - and([q8 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - sum([toInt(x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q8, q11] != 5) - | q11 : int(1..4)]) - <= 4 - | q8 : int(1..4)]), - 4 = - sum([toInt(q16 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker) * - catchUndef(sum([toInt(x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q16, q18] != - 5) - | q18 : int(1..4)]), - 0) - | q16 : int(1..4)]) - diff --git a/tests/exhaustive/basic/partition_05_2/expected/model_3-solution000001.solution b/tests/exhaustive/basic/partition_05_2/expected/model_3-solution000001.solution new file mode 100644 index 0000000000..b616543ee7 --- /dev/null +++ b/tests/exhaustive/basic/partition_05_2/expected/model_3-solution000001.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be partition({1, 3}, {2, 4}) +$ Visualisation for x +$ 1 3 +$ 2 4 + diff --git a/tests/exhaustive/basic/partition_05_2/expected/model_3.eprime.orig b/tests/exhaustive/basic/partition_05_2/expected/model_3.eprime.orig deleted file mode 100644 index 263daeb090..0000000000 --- a/tests/exhaustive/basic/partition_05_2/expected/model_3.eprime.orig +++ /dev/null @@ -1,119 +0,0 @@ -language ESSENCE' 1.0 - -find x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker: int(0..4) -find x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker: - matrix indexed by [int(1..4)] of int(0..4) -find x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values: - matrix indexed by [int(1..4), int(1..4)] of int(1..4) -branching on - [x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker, - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker, - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values] -such that - and([and([q26 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker, - or([q30 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q26] /\ - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q26, q30] = 2 - | q30 : int(1..4)]), - q27 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q26]; - int(1..3)]) - -> - 4 = x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q26, q27] \/ - 2 = x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q26, q27] - | q26 : int(1..4), q27 : int(1..4)]), - or([and([q36 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker, - or([q39 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q36] /\ - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q36, q39] = 2 - | q39 : int(1..4)]), - q37 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q36]; - int(1..3)]) - /\ x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q36, q37] = 4 - | q36 : int(1..4), q37 : int(1..4)]), - or([and([q44 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker, - or([q47 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q44] /\ - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q44, q47] = 2 - | q47 : int(1..4)]), - q45 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q44]; - int(1..3)]) - /\ x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q44, q45] = 2 - | q44 : int(1..4), q45 : int(1..4)]), - and([q52 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - q53 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q52] - -> - or([1 = x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q52, q53], - 2 = x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q52, q53], - 3 = x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q52, q53], - 4 = x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q52, q53]; - int(1..4)]) - | q52 : int(1..4), q53 : int(1..4)]), - or([q60 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - q61 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q60] - /\ x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q60, q61] = 1 - | q60 : int(1..4), q61 : int(1..4)]), - or([q66 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - q67 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q66] - /\ x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q66, q67] = 2 - | q66 : int(1..4), q67 : int(1..4)]), - or([q72 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - q73 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q72] - /\ x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q72, q73] = 3 - | q72 : int(1..4), q73 : int(1..4)]), - or([q78 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - q79 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q78] - /\ x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q78, q79] = 4 - | q78 : int(1..4), q79 : int(1..4)]), - alldifferent_except([toInt(q17 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - q18 <= - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q17]) - * - catchUndef(x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q17, q18], - 0) - | q17 : int(1..4), q18 : int(1..4)], - 0), - and([q19 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - q20 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker - -> - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q19] = - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q20] - | q19 : int(1..4), q20 : int(1..4)]), - and([q21 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q21] >= 1 - | q21 : int(1..4)]), - and([q6 + 1 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - flatten([[x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q6]; int(1)], - [x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q6, q13] - | q13 : int(1..4)]; - int(1..2)]) - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q7] = 0 /\ - and([x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q7, q16] = 1 - | q16 : int(1..4)]) - | q7 : int(1..4)]), - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker <= 4, - and([q8 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - and([q9 + 1 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q8] -> - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q8, q9] < - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q8, q9 + 1] - | q9 : int(1..3)]) - | q8 : int(1..4)]), - and([q8 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - and([q10 > x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q8] -> - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q8, q10] = 1 - | q10 : int(1..4)]) - | q8 : int(1..4)]), - and([q8 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q8] <= 4 - | q8 : int(1..4)]), - 4 = - sum([toInt(q15 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker) * - catchUndef(x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q15], 0) - | q15 : int(1..4)]) - diff --git a/tests/exhaustive/basic/partition_05_2/expected/model_4-solution000001.solution b/tests/exhaustive/basic/partition_05_2/expected/model_4-solution000001.solution new file mode 100644 index 0000000000..b616543ee7 --- /dev/null +++ b/tests/exhaustive/basic/partition_05_2/expected/model_4-solution000001.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be partition({1, 3}, {2, 4}) +$ Visualisation for x +$ 1 3 +$ 2 4 + diff --git a/tests/exhaustive/basic/partition_05_2/expected/model_4.eprime.orig b/tests/exhaustive/basic/partition_05_2/expected/model_4.eprime.orig deleted file mode 100644 index f37aa5dd69..0000000000 --- a/tests/exhaustive/basic/partition_05_2/expected/model_4.eprime.orig +++ /dev/null @@ -1,61 +0,0 @@ -language ESSENCE' 1.0 - -find x_PartitionOccurrence_NumParts: int(1..4) -find x_PartitionOccurrence_WhichPart: matrix indexed by [int(1..4)] of int(1..4) -find x_PartitionOccurrence_PartSizes: matrix indexed by [int(1..4)] of int(0..4) -find x_PartitionOccurrence_FirstIndex: matrix indexed by [int(1..4)] of int(1..4) -branching on - [x_PartitionOccurrence_NumParts, x_PartitionOccurrence_WhichPart, x_PartitionOccurrence_PartSizes, - x_PartitionOccurrence_FirstIndex] -such that - and([and([q15 <= x_PartitionOccurrence_NumParts, - or([x_PartitionOccurrence_WhichPart[q20] = q15 /\ q20 = 2 | q20 : int(1..4)]), - x_PartitionOccurrence_WhichPart[q17] = q15; - int(1..3)]) - -> 4 = q17 \/ 2 = q17 - | q15 : int(1..4), q17 : int(1..4)]), - or([and([q25 <= x_PartitionOccurrence_NumParts, - or([x_PartitionOccurrence_WhichPart[q29] = q25 /\ q29 = 2 | q29 : int(1..4)]), - x_PartitionOccurrence_WhichPart[q27] = q25; - int(1..3)]) - /\ q27 = 4 - | q25 : int(1..4), q27 : int(1..4)]), - or([and([q33 <= x_PartitionOccurrence_NumParts, - or([x_PartitionOccurrence_WhichPart[q37] = q33 /\ q37 = 2 | q37 : int(1..4)]), - x_PartitionOccurrence_WhichPart[q35] = q33; - int(1..3)]) - /\ q35 = 2 - | q33 : int(1..4), q35 : int(1..4)]), - and([q41 <= x_PartitionOccurrence_NumParts /\ x_PartitionOccurrence_WhichPart[q43] = q41 -> - or([1 = q43, 2 = q43, 3 = q43, 4 = q43; int(1..4)]) - | q41 : int(1..4), q43 : int(1..4)]), - or([q49 <= x_PartitionOccurrence_NumParts /\ x_PartitionOccurrence_WhichPart[q51] = q49 /\ q51 = 1 - | q49 : int(1..4), q51 : int(1..4)]), - or([q55 <= x_PartitionOccurrence_NumParts /\ x_PartitionOccurrence_WhichPart[q57] = q55 /\ q57 = 2 - | q55 : int(1..4), q57 : int(1..4)]), - or([q61 <= x_PartitionOccurrence_NumParts /\ x_PartitionOccurrence_WhichPart[q63] = q61 /\ q63 = 3 - | q61 : int(1..4), q63 : int(1..4)]), - or([q67 <= x_PartitionOccurrence_NumParts /\ x_PartitionOccurrence_WhichPart[q69] = q67 /\ q69 = 4 - | q67 : int(1..4), q69 : int(1..4)]), - and([q1 <= x_PartitionOccurrence_NumParts -> x_PartitionOccurrence_PartSizes[q1] <= 4 | q1 : int(1..4)]), - and([q1 > x_PartitionOccurrence_NumParts -> x_PartitionOccurrence_PartSizes[q1] = 0 | q1 : int(1..4)]), - x_PartitionOccurrence_NumParts <= 4, - and([q2 <= x_PartitionOccurrence_NumParts -> or([x_PartitionOccurrence_WhichPart[q3] = q2 | q3 : int(1..4)]) - | q2 : int(3..4)]), - and([q4 <= x_PartitionOccurrence_NumParts -> - x_PartitionOccurrence_PartSizes[q4 - 1] = x_PartitionOccurrence_PartSizes[q4] - | q4 : int(2..4)]), - x_PartitionOccurrence_NumParts = max([x_PartitionOccurrence_WhichPart[q5] | q5 : int(1..4)]), - and([x_PartitionOccurrence_PartSizes[q6] = sum([toInt(x_PartitionOccurrence_WhichPart[q7] = q6) | q7 : int(1..4)]) - | q6 : int(1..4)]), - and([q8 <= x_PartitionOccurrence_NumParts -> - and([x_PartitionOccurrence_WhichPart[q9] = q8 -> x_PartitionOccurrence_FirstIndex[q8] <= q9 | q9 : int(1..4)]) - | q8 : int(1..4)]), - and([q8 <= x_PartitionOccurrence_NumParts -> - or([x_PartitionOccurrence_WhichPart[q9] = q8 /\ x_PartitionOccurrence_FirstIndex[q8] = q9 | q9 : int(1..4)]) - | q8 : int(1..4)]), - and([q8 > x_PartitionOccurrence_NumParts -> x_PartitionOccurrence_FirstIndex[q8] = 1 | q8 : int(1..4)]), - and([q10 <= x_PartitionOccurrence_NumParts /\ q11 <= x_PartitionOccurrence_NumParts -> - (q10 < q11 <-> x_PartitionOccurrence_FirstIndex[q10] < x_PartitionOccurrence_FirstIndex[q11]) - | q10 : int(1..4), q11 : int(1..4)]) - diff --git a/tests/exhaustive/basic/partition_06/expected/model_1_1-solution000001.solution b/tests/exhaustive/basic/partition_06/expected/model_1_1-solution000001.solution new file mode 100644 index 0000000000..8d196199c8 --- /dev/null +++ b/tests/exhaustive/basic/partition_06/expected/model_1_1-solution000001.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be partition({1, 4}, {2, 3}) +$ Visualisation for x +$ 1 4 +$ 2 3 + diff --git a/tests/exhaustive/basic/partition_06/expected/model_1_1-solution000002.solution b/tests/exhaustive/basic/partition_06/expected/model_1_1-solution000002.solution new file mode 100644 index 0000000000..b616543ee7 --- /dev/null +++ b/tests/exhaustive/basic/partition_06/expected/model_1_1-solution000002.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be partition({1, 3}, {2, 4}) +$ Visualisation for x +$ 1 3 +$ 2 4 + diff --git a/tests/exhaustive/basic/partition_06/expected/model_1_1-solution000003.solution b/tests/exhaustive/basic/partition_06/expected/model_1_1-solution000003.solution new file mode 100644 index 0000000000..bdecd9ce5b --- /dev/null +++ b/tests/exhaustive/basic/partition_06/expected/model_1_1-solution000003.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be partition({1, 2}, {3, 4}) +$ Visualisation for x +$ 1 2 +$ 3 4 + diff --git a/tests/exhaustive/basic/partition_06/expected/model_1_1.eprime b/tests/exhaustive/basic/partition_06/expected/model_1_1.eprime new file mode 100644 index 0000000000..0185996261 --- /dev/null +++ b/tests/exhaustive/basic/partition_06/expected/model_1_1.eprime @@ -0,0 +1,37 @@ +language ESSENCE' 1.0 + +find x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker: int(0..4) +find x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence: matrix indexed by [int(1..4), int(1..4)] of bool +branching on + [x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker, + x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence] +such that + and([q18 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> + sum([toInt(x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q18, q19]) | q19 : int(1..4)]) = 2 + | q18 : int(1..4)]), + and([1 = + sum([toInt(q14 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ + x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q14, q1]) + | q14 : int(1..4)]) + | q1 : int(1..4)]), + and([q15 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> + sum([toInt(x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q15, q16]) | q16 : int(1..4)]) >= 1 + | q15 : int(1..4)]), + and([q4 + 1 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> + [-toInt(x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q4, q9]) | q9 : int(1..4)] x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> + and([x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q5, q11] = false | q11 : int(1..4)]) + | q5 : int(1..4)]), + x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker <= 4, + and([q6 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> + sum([toInt(x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q6, q7]) | q7 : int(1..4)]) <= 4 + | q6 : int(1..4)]), + 4 = + sum([toInt(q12 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker) * + catchUndef(sum([toInt(x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q12, q13]) + | q13 : int(1..4)]), + 0) + | q12 : int(1..4)]) + diff --git a/tests/exhaustive/basic/partition_06/expected/model_1_2-solution000001.solution b/tests/exhaustive/basic/partition_06/expected/model_1_2-solution000001.solution new file mode 100644 index 0000000000..bdecd9ce5b --- /dev/null +++ b/tests/exhaustive/basic/partition_06/expected/model_1_2-solution000001.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be partition({1, 2}, {3, 4}) +$ Visualisation for x +$ 1 2 +$ 3 4 + diff --git a/tests/exhaustive/basic/partition_06/expected/model_1_2-solution000002.solution b/tests/exhaustive/basic/partition_06/expected/model_1_2-solution000002.solution new file mode 100644 index 0000000000..b616543ee7 --- /dev/null +++ b/tests/exhaustive/basic/partition_06/expected/model_1_2-solution000002.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be partition({1, 3}, {2, 4}) +$ Visualisation for x +$ 1 3 +$ 2 4 + diff --git a/tests/exhaustive/basic/partition_06/expected/model_1_2-solution000003.solution b/tests/exhaustive/basic/partition_06/expected/model_1_2-solution000003.solution new file mode 100644 index 0000000000..8d196199c8 --- /dev/null +++ b/tests/exhaustive/basic/partition_06/expected/model_1_2-solution000003.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be partition({1, 4}, {2, 3}) +$ Visualisation for x +$ 1 4 +$ 2 3 + diff --git a/tests/exhaustive/basic/partition_06/expected/model_1_2.eprime b/tests/exhaustive/basic/partition_06/expected/model_1_2.eprime new file mode 100644 index 0000000000..337e8fc3c9 --- /dev/null +++ b/tests/exhaustive/basic/partition_06/expected/model_1_2.eprime @@ -0,0 +1,116 @@ +language ESSENCE' 1.0 + +find x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker: int(0..4) +find x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence: matrix indexed by [int(1..4), int(1..4)] of bool +find x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker: int(0..4) +find x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy: + matrix indexed by [int(1..4), int(1..4)] of int(1..5) +branching on + [x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker, + x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy, + x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker, + x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence] +such that + and([q55 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> + sum([toInt(x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q55, q56]) | q56 : int(1..4)]) = 2 + | q55 : int(1..4)]), + and([1 = + sum([toInt(q52 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ + x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q52, q1]) + | q52 : int(1..4)]) + | q1 : int(1..4)]), + and([q57 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> + sum([toInt(x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q57, q58]) | q58 : int(1..4)]) >= 1 + | q57 : int(1..4)]), + and([q4 + 1 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> + [-toInt(x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q4, q9]) | q9 : int(1..4)] x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> + and([x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q5, q11] = false | q11 : int(1..4)]) + | q5 : int(1..4)]), + x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker <= 4, + and([q6 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> + sum([toInt(x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q6, q7]) | q7 : int(1..4)]) <= 4 + | q6 : int(1..4)]), + 4 = + sum([toInt(q12 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker) * + catchUndef(sum([toInt(x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q12, q13]) + | q13 : int(1..4)]), + 0) + | q12 : int(1..4)]), + alldifferent_except([toInt(q59 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ + x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q59, q60] != + 5) + * + catchUndef(x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q59, q60], + 0) + | q59 : int(1..4), q60 : int(1..4)], + 0), + and([q61 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> + sum([toInt(x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q61, q63] != 5) + | q63 : int(1..4)]) + >= 1 + | q61 : int(1..4)]), + and([q17 + 1 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> + [x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q17, q25] | q25 : int(1..4)] x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> + and([x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q18, q53] = 1 + | q53 : int(1..4)]) + | q18 : int(1..4)]), + x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker <= 4, + and([q19 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> + and([x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q19, q20] < + x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q19, q20 + 1] + \/ x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q19, q20] = 5 + | q20 : int(1..3)]) + | q19 : int(1..4)]), + and([q19 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> + and([x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q19, q21] = 5 -> + x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q19, q21 + 1] = 5 + | q21 : int(1..3)]) + | q19 : int(1..4)]), + and([q19 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> + sum([toInt(x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q19, q22] != 5) + | q22 : int(1..4)]) + <= 4 + | q19 : int(1..4)]), + 4 = + sum([toInt(q27 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker) * + catchUndef(sum([toInt(x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q27, q29] != + 5) + | q29 : int(1..4)]), + 0) + | q27 : int(1..4)]), + and([q32 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> + or([q35 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ + (and([x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q35, q36] -> + or([x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q32, q38] != 5 /\ + x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q32, q38] = q36 + | q38 : int(1..4)]) + | q36 : int(1..4)]) + /\ + and([x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q32, q40] != 5 -> + x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence + [q35, x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q32, q40]] + | q40 : int(1..4)])) + | q35 : int(1..4)]) + | q32 : int(1..4)]), + and([q43 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> + or([q46 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ + (and([x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q46, q48] != 5 -> + x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence + [q43, x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q46, q48]] + | q48 : int(1..4)]) + /\ + and([x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q43, q49] -> + or([x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q46, q51] != 5 /\ + x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q46, q51] = q49 + | q51 : int(1..4)]) + | q49 : int(1..4)])) + | q46 : int(1..4)]) + | q43 : int(1..4)]) + diff --git a/tests/exhaustive/basic/partition_06/expected/model_1_3-solution000001.solution b/tests/exhaustive/basic/partition_06/expected/model_1_3-solution000001.solution new file mode 100644 index 0000000000..bdecd9ce5b --- /dev/null +++ b/tests/exhaustive/basic/partition_06/expected/model_1_3-solution000001.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be partition({1, 2}, {3, 4}) +$ Visualisation for x +$ 1 2 +$ 3 4 + diff --git a/tests/exhaustive/basic/partition_06/expected/model_1_3-solution000002.solution b/tests/exhaustive/basic/partition_06/expected/model_1_3-solution000002.solution new file mode 100644 index 0000000000..b616543ee7 --- /dev/null +++ b/tests/exhaustive/basic/partition_06/expected/model_1_3-solution000002.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be partition({1, 3}, {2, 4}) +$ Visualisation for x +$ 1 3 +$ 2 4 + diff --git a/tests/exhaustive/basic/partition_06/expected/model_1_3-solution000003.solution b/tests/exhaustive/basic/partition_06/expected/model_1_3-solution000003.solution new file mode 100644 index 0000000000..8d196199c8 --- /dev/null +++ b/tests/exhaustive/basic/partition_06/expected/model_1_3-solution000003.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be partition({1, 4}, {2, 3}) +$ Visualisation for x +$ 1 4 +$ 2 3 + diff --git a/tests/exhaustive/basic/partition_06/expected/model_1_3.eprime.orig b/tests/exhaustive/basic/partition_06/expected/model_1_3.eprime.orig deleted file mode 100644 index 777ff6324f..0000000000 --- a/tests/exhaustive/basic/partition_06/expected/model_1_3.eprime.orig +++ /dev/null @@ -1,126 +0,0 @@ -language ESSENCE' 1.0 - -find x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker: int(0..4) -find x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence: matrix indexed by [int(1..4), int(1..4)] of bool -find x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker: int(0..4) -find x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker: - matrix indexed by [int(1..4)] of int(0..4) -find x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values: - matrix indexed by [int(1..4), int(1..4)] of int(1..4) -branching on - [x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker, - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker, - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values, - x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker, - x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence] -such that - and([q52 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> - sum([toInt(x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q52, q53]) | q53 : int(1..4)]) = 2 - | q52 : int(1..4)]), - and([1 = - sum([toInt(q49 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ - x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q49, q1]) - | q49 : int(1..4)]) - | q1 : int(1..4)]), - and([q54 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> - sum([toInt(x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q54, q55]) | q55 : int(1..4)]) >= 1 - | q54 : int(1..4)]), - and([q4 + 1 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> - [-toInt(x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q4, q9]) | q9 : int(1..4)] x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> - and([x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q5, q11] = false | q11 : int(1..4)]) - | q5 : int(1..4)]), - x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker <= 4, - and([q6 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> - sum([toInt(x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q6, q7]) | q7 : int(1..4)]) <= 4 - | q6 : int(1..4)]), - 4 = - sum([toInt(q12 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker) * - catchUndef(sum([toInt(x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q12, q13]) - | q13 : int(1..4)]), - 0) - | q12 : int(1..4)]), - alldifferent_except([toInt(q56 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - q57 <= - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q56]) - * - catchUndef(x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q56, q57], - 0) - | q56 : int(1..4), q57 : int(1..4)], - 0), - and([q58 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q58] >= 1 - | q58 : int(1..4)]), - and([q17 + 1 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - flatten([[x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q17]; int(1)], - [x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q17, q24] - | q24 : int(1..4)]; - int(1..2)]) - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q18] = 0 /\ - and([x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q18, q50] = 1 - | q50 : int(1..4)]) - | q18 : int(1..4)]), - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker <= 4, - and([q19 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - and([q20 + 1 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q19] -> - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q19, q20] < - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q19, q20 + 1] - | q20 : int(1..3)]) - | q19 : int(1..4)]), - and([q19 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - and([q21 > x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q19] -> - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q19, q21] = 1 - | q21 : int(1..4)]) - | q19 : int(1..4)]), - and([q19 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q19] <= 4 - | q19 : int(1..4)]), - 4 = - sum([toInt(q26 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker) * - catchUndef(x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q26], 0) - | q26 : int(1..4)]), - and([q29 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - or([q32 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ - (and([x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q32, q33] -> - or([q35 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q29] - /\ - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q29, q35] = - q33 | q35 : int(1..4)]) - | q33 : int(1..4)]) - /\ - and([q37 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q29] -> - x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence - [q32, - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q29, q37]] - | q37 : int(1..4)])) - | q32 : int(1..4)]) - | q29 : int(1..4)]), - and([q40 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> - or([q43 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - (and([q45 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q43] -> - x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence - [q40, - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q43, q45]] - | q45 : int(1..4)]) - /\ - and([x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q40, q46] -> - or([q48 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q43] - /\ - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q43, q48] = - q46 | q48 : int(1..4)]) - | q46 : int(1..4)])) - | q43 : int(1..4)]) - | q40 : int(1..4)]) - diff --git a/tests/exhaustive/basic/partition_06/expected/model_1_4-solution000001.solution b/tests/exhaustive/basic/partition_06/expected/model_1_4-solution000001.solution new file mode 100644 index 0000000000..bdecd9ce5b --- /dev/null +++ b/tests/exhaustive/basic/partition_06/expected/model_1_4-solution000001.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be partition({1, 2}, {3, 4}) +$ Visualisation for x +$ 1 2 +$ 3 4 + diff --git a/tests/exhaustive/basic/partition_06/expected/model_1_4-solution000002.solution b/tests/exhaustive/basic/partition_06/expected/model_1_4-solution000002.solution new file mode 100644 index 0000000000..b616543ee7 --- /dev/null +++ b/tests/exhaustive/basic/partition_06/expected/model_1_4-solution000002.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be partition({1, 3}, {2, 4}) +$ Visualisation for x +$ 1 3 +$ 2 4 + diff --git a/tests/exhaustive/basic/partition_06/expected/model_1_4-solution000003.solution b/tests/exhaustive/basic/partition_06/expected/model_1_4-solution000003.solution new file mode 100644 index 0000000000..8d196199c8 --- /dev/null +++ b/tests/exhaustive/basic/partition_06/expected/model_1_4-solution000003.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be partition({1, 4}, {2, 3}) +$ Visualisation for x +$ 1 4 +$ 2 3 + diff --git a/tests/exhaustive/basic/partition_06/expected/model_1_4.eprime b/tests/exhaustive/basic/partition_06/expected/model_1_4.eprime new file mode 100644 index 0000000000..fe7ae25188 --- /dev/null +++ b/tests/exhaustive/basic/partition_06/expected/model_1_4.eprime @@ -0,0 +1,85 @@ +language ESSENCE' 1.0 + +find x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker: int(0..4) +find x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence: matrix indexed by [int(1..4), int(1..4)] of bool +find x_PartitionOccurrence_NumParts: int(1..4) +find x_PartitionOccurrence_WhichPart: matrix indexed by [int(1..4)] of int(1..4) +find x_PartitionOccurrence_PartSizes: matrix indexed by [int(1..4)] of int(0..4) +find x_PartitionOccurrence_FirstIndex: matrix indexed by [int(1..4)] of int(1..4) +branching on + [x_PartitionOccurrence_NumParts, x_PartitionOccurrence_WhichPart, x_PartitionOccurrence_PartSizes, + x_PartitionOccurrence_FirstIndex, x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker, + x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence] +such that + and([q48 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> + sum([toInt(x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q48, q49]) | q49 : int(1..4)]) = 2 + | q48 : int(1..4)]), + and([1 = + sum([toInt(q24 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ + x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q24, q1]) + | q24 : int(1..4)]) + | q1 : int(1..4)]), + and([q50 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> + sum([toInt(x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q50, q51]) | q51 : int(1..4)]) >= 1 + | q50 : int(1..4)]), + and([q4 + 1 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> + [-toInt(x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q4, q9]) | q9 : int(1..4)] x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> + and([x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q5, q11] = false | q11 : int(1..4)]) + | q5 : int(1..4)]), + x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker <= 4, + and([q6 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> + sum([toInt(x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q6, q7]) | q7 : int(1..4)]) <= 4 + | q6 : int(1..4)]), + 4 = + sum([toInt(q12 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker) * + catchUndef(sum([toInt(x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q12, q13]) + | q13 : int(1..4)]), + 0) + | q12 : int(1..4)]), + and([q14 <= x_PartitionOccurrence_NumParts -> x_PartitionOccurrence_PartSizes[q14] <= 4 | q14 : int(1..4)]), + and([q14 > x_PartitionOccurrence_NumParts -> x_PartitionOccurrence_PartSizes[q14] = 0 | q14 : int(1..4)]), + x_PartitionOccurrence_NumParts <= 4, + and([q15 <= x_PartitionOccurrence_NumParts -> or([x_PartitionOccurrence_WhichPart[q16] = q15 | q16 : int(1..4)]) + | q15 : int(3..4)]), + x_PartitionOccurrence_NumParts = max([x_PartitionOccurrence_WhichPart[q17] | q17 : int(1..4)]), + and([x_PartitionOccurrence_PartSizes[q18] = + sum([toInt(x_PartitionOccurrence_WhichPart[q19] = q18) | q19 : int(1..4)]) + | q18 : int(1..4)]), + and([q20 <= x_PartitionOccurrence_NumParts -> + and([x_PartitionOccurrence_WhichPart[q21] = q20 -> x_PartitionOccurrence_FirstIndex[q20] <= q21 + | q21 : int(1..4)]) + | q20 : int(1..4)]), + and([q20 <= x_PartitionOccurrence_NumParts -> + or([x_PartitionOccurrence_WhichPart[q21] = q20 /\ x_PartitionOccurrence_FirstIndex[q20] = q21 + | q21 : int(1..4)]) + | q20 : int(1..4)]), + and([q20 > x_PartitionOccurrence_NumParts -> x_PartitionOccurrence_FirstIndex[q20] = 1 | q20 : int(1..4)]), + and([q22 <= x_PartitionOccurrence_NumParts /\ q23 <= x_PartitionOccurrence_NumParts -> + (q22 < q23 <-> x_PartitionOccurrence_FirstIndex[q22] < x_PartitionOccurrence_FirstIndex[q23]) + | q22 : int(1..4), q23 : int(1..4)]), + and([q26 <= x_PartitionOccurrence_NumParts -> + or([q30 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ + (and([x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q30, q31] -> + or([x_PartitionOccurrence_WhichPart[q33] = q26 /\ q33 = q31 | q33 : int(1..4)]) + | q31 : int(1..4)]) + /\ + and([x_PartitionOccurrence_WhichPart[q35] = q26 -> + x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q30, q35] + | q35 : int(1..4)])) + | q30 : int(1..4)]) + | q26 : int(1..4)]), + and([q38 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> + or([q40 <= x_PartitionOccurrence_NumParts /\ + (and([x_PartitionOccurrence_WhichPart[q43] = q40 -> + x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q38, q43] + | q43 : int(1..4)]) + /\ + and([x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q38, q44] -> + or([x_PartitionOccurrence_WhichPart[q46] = q40 /\ q46 = q44 | q46 : int(1..4)]) + | q44 : int(1..4)])) + | q40 : int(1..4)]) + | q38 : int(1..4)]) + diff --git a/tests/exhaustive/basic/partition_06/expected/model_2_1-solution000001.solution b/tests/exhaustive/basic/partition_06/expected/model_2_1-solution000001.solution new file mode 100644 index 0000000000..8d196199c8 --- /dev/null +++ b/tests/exhaustive/basic/partition_06/expected/model_2_1-solution000001.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be partition({1, 4}, {2, 3}) +$ Visualisation for x +$ 1 4 +$ 2 3 + diff --git a/tests/exhaustive/basic/partition_06/expected/model_2_1-solution000002.solution b/tests/exhaustive/basic/partition_06/expected/model_2_1-solution000002.solution new file mode 100644 index 0000000000..b616543ee7 --- /dev/null +++ b/tests/exhaustive/basic/partition_06/expected/model_2_1-solution000002.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be partition({1, 3}, {2, 4}) +$ Visualisation for x +$ 1 3 +$ 2 4 + diff --git a/tests/exhaustive/basic/partition_06/expected/model_2_1-solution000003.solution b/tests/exhaustive/basic/partition_06/expected/model_2_1-solution000003.solution new file mode 100644 index 0000000000..bdecd9ce5b --- /dev/null +++ b/tests/exhaustive/basic/partition_06/expected/model_2_1-solution000003.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be partition({1, 2}, {3, 4}) +$ Visualisation for x +$ 1 2 +$ 3 4 + diff --git a/tests/exhaustive/basic/partition_06/expected/model_2_1.eprime b/tests/exhaustive/basic/partition_06/expected/model_2_1.eprime new file mode 100644 index 0000000000..8f0bcabfd6 --- /dev/null +++ b/tests/exhaustive/basic/partition_06/expected/model_2_1.eprime @@ -0,0 +1,117 @@ +language ESSENCE' 1.0 + +find x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker: int(0..4) +find x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy: + matrix indexed by [int(1..4), int(1..4)] of int(1..5) +find x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker: int(0..4) +find x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence: matrix indexed by [int(1..4), int(1..4)] of bool +branching on + [x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker, + x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence, + x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker, + x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy] +such that + and([q57 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> + sum([toInt(x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q57, q59] != 5) + | q59 : int(1..4)]) + = 2 | q57 : int(1..4)]), + alldifferent_except([toInt(q60 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ + x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q60, q61] != + 5) + * + catchUndef(x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q60, q61], + 0) + | q60 : int(1..4), q61 : int(1..4)], + 0), + and([q62 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> + sum([toInt(x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q62, q64] != 5) + | q64 : int(1..4)]) + >= 1 + | q62 : int(1..4)]), + and([q4 + 1 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> + [x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q4, q12] | q12 : int(1..4)] x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> + and([x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q5, q52] = 1 + | q52 : int(1..4)]) + | q5 : int(1..4)]), + x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker <= 4, + and([q6 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> + and([x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q6, q7] < + x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q6, q7 + 1] + \/ x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q6, q7] = 5 + | q7 : int(1..3)]) + | q6 : int(1..4)]), + and([q6 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> + and([x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q6, q8] = 5 -> + x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q6, q8 + 1] = 5 + | q8 : int(1..3)]) + | q6 : int(1..4)]), + and([q6 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> + sum([toInt(x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q6, q9] != 5) + | q9 : int(1..4)]) + <= 4 + | q6 : int(1..4)]), + 4 = + sum([toInt(q14 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker) * + catchUndef(sum([toInt(x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q14, q16] != + 5) + | q16 : int(1..4)]), + 0) + | q14 : int(1..4)]), + and([1 = + sum([toInt(q53 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ + x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q53, q17]) + | q53 : int(1..4)]) + | q17 : int(1..4)]), + and([q54 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> + sum([toInt(x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q54, q55]) | q55 : int(1..4)]) >= 1 + | q54 : int(1..4)]), + and([q20 + 1 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> + [-toInt(x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q20, q25]) | q25 : int(1..4)] x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> + and([x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q21, q27] = false | q27 : int(1..4)]) + | q21 : int(1..4)]), + x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker <= 4, + and([q22 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> + sum([toInt(x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q22, q23]) | q23 : int(1..4)]) <= 4 + | q22 : int(1..4)]), + 4 = + sum([toInt(q28 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker) * + catchUndef(sum([toInt(x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q28, q29]) + | q29 : int(1..4)]), + 0) + | q28 : int(1..4)]), + and([q32 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> + or([q35 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ + (and([x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q35, q37] != 5 -> + x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence + [q32, x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q35, q37]] + | q37 : int(1..4)]) + /\ + and([x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q32, q38] -> + or([x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q35, q40] != 5 /\ + x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q35, q40] = q38 + | q40 : int(1..4)]) + | q38 : int(1..4)])) + | q35 : int(1..4)]) + | q32 : int(1..4)]), + and([q43 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> + or([q46 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ + (and([x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q46, q47] -> + or([x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q43, q49] != 5 /\ + x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q43, q49] = q47 + | q49 : int(1..4)]) + | q47 : int(1..4)]) + /\ + and([x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q43, q51] != 5 -> + x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence + [q46, x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q43, q51]] + | q51 : int(1..4)])) + | q46 : int(1..4)]) + | q43 : int(1..4)]) + diff --git a/tests/exhaustive/basic/partition_06/expected/model_2_2-solution000001.solution b/tests/exhaustive/basic/partition_06/expected/model_2_2-solution000001.solution new file mode 100644 index 0000000000..bdecd9ce5b --- /dev/null +++ b/tests/exhaustive/basic/partition_06/expected/model_2_2-solution000001.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be partition({1, 2}, {3, 4}) +$ Visualisation for x +$ 1 2 +$ 3 4 + diff --git a/tests/exhaustive/basic/partition_06/expected/model_2_2-solution000002.solution b/tests/exhaustive/basic/partition_06/expected/model_2_2-solution000002.solution new file mode 100644 index 0000000000..b616543ee7 --- /dev/null +++ b/tests/exhaustive/basic/partition_06/expected/model_2_2-solution000002.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be partition({1, 3}, {2, 4}) +$ Visualisation for x +$ 1 3 +$ 2 4 + diff --git a/tests/exhaustive/basic/partition_06/expected/model_2_2-solution000003.solution b/tests/exhaustive/basic/partition_06/expected/model_2_2-solution000003.solution new file mode 100644 index 0000000000..8d196199c8 --- /dev/null +++ b/tests/exhaustive/basic/partition_06/expected/model_2_2-solution000003.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be partition({1, 4}, {2, 3}) +$ Visualisation for x +$ 1 4 +$ 2 3 + diff --git a/tests/exhaustive/basic/partition_06/expected/model_2_2.eprime b/tests/exhaustive/basic/partition_06/expected/model_2_2.eprime new file mode 100644 index 0000000000..4220a0f519 --- /dev/null +++ b/tests/exhaustive/basic/partition_06/expected/model_2_2.eprime @@ -0,0 +1,60 @@ +language ESSENCE' 1.0 + +find x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker: int(0..4) +find x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy: + matrix indexed by [int(1..4), int(1..4)] of int(1..5) +branching on + [x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker, + x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy] +such that + and([q19 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> + sum([toInt(x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q19, q21] != 5) + | q21 : int(1..4)]) + = 2 | q19 : int(1..4)]), + alldifferent_except([toInt(q22 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ + x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q22, q23] != + 5) + * + catchUndef(x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q22, q23], + 0) + | q22 : int(1..4), q23 : int(1..4)], + 0), + and([q24 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> + sum([toInt(x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q24, q26] != 5) + | q26 : int(1..4)]) + >= 1 + | q24 : int(1..4)]), + and([q4 + 1 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> + [x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q4, q12] | q12 : int(1..4)] x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> + and([x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q5, q17] = 1 + | q17 : int(1..4)]) + | q5 : int(1..4)]), + x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker <= 4, + and([q6 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> + and([x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q6, q7] < + x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q6, q7 + 1] + \/ x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q6, q7] = 5 + | q7 : int(1..3)]) + | q6 : int(1..4)]), + and([q6 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> + and([x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q6, q8] = 5 -> + x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q6, q8 + 1] = 5 + | q8 : int(1..3)]) + | q6 : int(1..4)]), + and([q6 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> + sum([toInt(x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q6, q9] != 5) + | q9 : int(1..4)]) + <= 4 + | q6 : int(1..4)]), + 4 = + sum([toInt(q14 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker) * + catchUndef(sum([toInt(x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q14, q16] != + 5) + | q16 : int(1..4)]), + 0) + | q14 : int(1..4)]) + diff --git a/tests/exhaustive/basic/partition_06/expected/model_2_3-solution000001.solution b/tests/exhaustive/basic/partition_06/expected/model_2_3-solution000001.solution new file mode 100644 index 0000000000..bdecd9ce5b --- /dev/null +++ b/tests/exhaustive/basic/partition_06/expected/model_2_3-solution000001.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be partition({1, 2}, {3, 4}) +$ Visualisation for x +$ 1 2 +$ 3 4 + diff --git a/tests/exhaustive/basic/partition_06/expected/model_2_3-solution000002.solution b/tests/exhaustive/basic/partition_06/expected/model_2_3-solution000002.solution new file mode 100644 index 0000000000..b616543ee7 --- /dev/null +++ b/tests/exhaustive/basic/partition_06/expected/model_2_3-solution000002.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be partition({1, 3}, {2, 4}) +$ Visualisation for x +$ 1 3 +$ 2 4 + diff --git a/tests/exhaustive/basic/partition_06/expected/model_2_3-solution000003.solution b/tests/exhaustive/basic/partition_06/expected/model_2_3-solution000003.solution new file mode 100644 index 0000000000..8d196199c8 --- /dev/null +++ b/tests/exhaustive/basic/partition_06/expected/model_2_3-solution000003.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be partition({1, 4}, {2, 3}) +$ Visualisation for x +$ 1 4 +$ 2 3 + diff --git a/tests/exhaustive/basic/partition_06/expected/model_2_3.eprime.orig b/tests/exhaustive/basic/partition_06/expected/model_2_3.eprime.orig deleted file mode 100644 index 5d89c386f7..0000000000 --- a/tests/exhaustive/basic/partition_06/expected/model_2_3.eprime.orig +++ /dev/null @@ -1,153 +0,0 @@ -language ESSENCE' 1.0 - -find x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker: int(0..4) -find x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy: - matrix indexed by [int(1..4), int(1..4)] of int(1..5) -find x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker: int(0..4) -find x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker: - matrix indexed by [int(1..4)] of int(0..4) -find x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values: - matrix indexed by [int(1..4), int(1..4)] of int(1..4) -branching on - [x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker, - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker, - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values, - x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker, - x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy] -such that - and([q61 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - sum([toInt(x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q61, q63] != 5) - | q63 : int(1..4)]) - = 2 | q61 : int(1..4)]), - alldifferent_except([toInt(q64 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ - x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q64, q65] != - 5) - * - catchUndef(x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q64, q65], - 0) - | q64 : int(1..4), q65 : int(1..4)], - 0), - and([q66 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - sum([toInt(x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q66, q68] != 5) - | q68 : int(1..4)]) - >= 1 - | q66 : int(1..4)]), - and([q4 + 1 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - [x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q4, q12] | q12 : int(1..4)] x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - and([x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q5, q58] = 1 - | q58 : int(1..4)]) - | q5 : int(1..4)]), - x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker <= 4, - and([q6 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - and([x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q6, q7] < - x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q6, q7 + 1] - \/ x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q6, q7] = 5 - | q7 : int(1..3)]) - | q6 : int(1..4)]), - and([q6 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - and([x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q6, q8] = 5 -> - x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q6, q8 + 1] = 5 - | q8 : int(1..3)]) - | q6 : int(1..4)]), - and([q6 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - sum([toInt(x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q6, q9] != 5) - | q9 : int(1..4)]) - <= 4 - | q6 : int(1..4)]), - 4 = - sum([toInt(q14 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker) * - catchUndef(sum([toInt(x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q14, q16] != - 5) - | q16 : int(1..4)]), - 0) - | q14 : int(1..4)]), - alldifferent_except([toInt(q69 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - q70 <= - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q69]) - * - catchUndef(x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q69, q70], - 0) - | q69 : int(1..4), q70 : int(1..4)], - 0), - and([q71 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q71] >= 1 - | q71 : int(1..4)]), - and([q20 + 1 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - flatten([[x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q20]; int(1)], - [x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q20, q27] - | q27 : int(1..4)]; - int(1..2)]) - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q21] = 0 /\ - and([x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q21, q59] = 1 - | q59 : int(1..4)]) - | q21 : int(1..4)]), - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker <= 4, - and([q22 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - and([q23 + 1 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q22] -> - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q22, q23] < - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q22, q23 + 1] - | q23 : int(1..3)]) - | q22 : int(1..4)]), - and([q22 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - and([q24 > x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q22] -> - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q22, q24] = 1 - | q24 : int(1..4)]) - | q22 : int(1..4)]), - and([q22 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q22] <= 4 - | q22 : int(1..4)]), - 4 = - sum([toInt(q29 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker) * - catchUndef(x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q29], 0) - | q29 : int(1..4)]), - and([q32 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - or([q35 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ - (and([x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q35, q37] != 5 -> - or([q39 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q32] - /\ - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q32, q39] = - x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q35, q37] - | q39 : int(1..4)]) - | q37 : int(1..4)]) - /\ - and([q41 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q32] -> - or([x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q35, q43] != 5 /\ - x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q35, q43] = - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q32, q41] - | q43 : int(1..4)]) - | q41 : int(1..4)])) - | q35 : int(1..4)]) - | q32 : int(1..4)]), - and([q46 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - or([q49 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - (and([q51 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q49] -> - or([x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q46, q53] != 5 /\ - x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q46, q53] = - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q49, q51] - | q53 : int(1..4)]) - | q51 : int(1..4)]) - /\ - and([x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q46, q55] != 5 -> - or([q57 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q49] - /\ - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q49, q57] = - x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q46, q55] - | q57 : int(1..4)]) - | q55 : int(1..4)])) - | q49 : int(1..4)]) - | q46 : int(1..4)]) - diff --git a/tests/exhaustive/basic/partition_06/expected/model_2_4-solution000001.solution b/tests/exhaustive/basic/partition_06/expected/model_2_4-solution000001.solution new file mode 100644 index 0000000000..bdecd9ce5b --- /dev/null +++ b/tests/exhaustive/basic/partition_06/expected/model_2_4-solution000001.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be partition({1, 2}, {3, 4}) +$ Visualisation for x +$ 1 2 +$ 3 4 + diff --git a/tests/exhaustive/basic/partition_06/expected/model_2_4-solution000002.solution b/tests/exhaustive/basic/partition_06/expected/model_2_4-solution000002.solution new file mode 100644 index 0000000000..b616543ee7 --- /dev/null +++ b/tests/exhaustive/basic/partition_06/expected/model_2_4-solution000002.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be partition({1, 3}, {2, 4}) +$ Visualisation for x +$ 1 3 +$ 2 4 + diff --git a/tests/exhaustive/basic/partition_06/expected/model_2_4-solution000003.solution b/tests/exhaustive/basic/partition_06/expected/model_2_4-solution000003.solution new file mode 100644 index 0000000000..8d196199c8 --- /dev/null +++ b/tests/exhaustive/basic/partition_06/expected/model_2_4-solution000003.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be partition({1, 4}, {2, 3}) +$ Visualisation for x +$ 1 4 +$ 2 3 + diff --git a/tests/exhaustive/basic/partition_06/expected/model_2_4.eprime b/tests/exhaustive/basic/partition_06/expected/model_2_4.eprime new file mode 100644 index 0000000000..bbbd3ba3be --- /dev/null +++ b/tests/exhaustive/basic/partition_06/expected/model_2_4.eprime @@ -0,0 +1,116 @@ +language ESSENCE' 1.0 + +find x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker: int(0..4) +find x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy: + matrix indexed by [int(1..4), int(1..4)] of int(1..5) +find x_PartitionOccurrence_NumParts: int(1..4) +find x_PartitionOccurrence_WhichPart: matrix indexed by [int(1..4)] of int(1..4) +find x_PartitionOccurrence_PartSizes: matrix indexed by [int(1..4)] of int(0..4) +find x_PartitionOccurrence_FirstIndex: matrix indexed by [int(1..4)] of int(1..4) +branching on + [x_PartitionOccurrence_NumParts, x_PartitionOccurrence_WhichPart, x_PartitionOccurrence_PartSizes, + x_PartitionOccurrence_FirstIndex, x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker, + x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy] +such that + and([q57 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> + sum([toInt(x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q57, q59] != 5) + | q59 : int(1..4)]) + = 2 | q57 : int(1..4)]), + alldifferent_except([toInt(q60 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ + x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q60, q61] != + 5) + * + catchUndef(x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q60, q61], + 0) + | q60 : int(1..4), q61 : int(1..4)], + 0), + and([q62 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> + sum([toInt(x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q62, q64] != 5) + | q64 : int(1..4)]) + >= 1 + | q62 : int(1..4)]), + and([q4 + 1 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> + [x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q4, q12] | q12 : int(1..4)] x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> + and([x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q5, q27] = 1 + | q27 : int(1..4)]) + | q5 : int(1..4)]), + x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker <= 4, + and([q6 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> + and([x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q6, q7] < + x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q6, q7 + 1] + \/ x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q6, q7] = 5 + | q7 : int(1..3)]) + | q6 : int(1..4)]), + and([q6 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> + and([x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q6, q8] = 5 -> + x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q6, q8 + 1] = 5 + | q8 : int(1..3)]) + | q6 : int(1..4)]), + and([q6 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> + sum([toInt(x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q6, q9] != 5) + | q9 : int(1..4)]) + <= 4 + | q6 : int(1..4)]), + 4 = + sum([toInt(q14 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker) * + catchUndef(sum([toInt(x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q14, q16] != + 5) + | q16 : int(1..4)]), + 0) + | q14 : int(1..4)]), + and([q17 <= x_PartitionOccurrence_NumParts -> x_PartitionOccurrence_PartSizes[q17] <= 4 | q17 : int(1..4)]), + and([q17 > x_PartitionOccurrence_NumParts -> x_PartitionOccurrence_PartSizes[q17] = 0 | q17 : int(1..4)]), + x_PartitionOccurrence_NumParts <= 4, + and([q18 <= x_PartitionOccurrence_NumParts -> or([x_PartitionOccurrence_WhichPart[q19] = q18 | q19 : int(1..4)]) + | q18 : int(3..4)]), + x_PartitionOccurrence_NumParts = max([x_PartitionOccurrence_WhichPart[q20] | q20 : int(1..4)]), + and([x_PartitionOccurrence_PartSizes[q21] = + sum([toInt(x_PartitionOccurrence_WhichPart[q22] = q21) | q22 : int(1..4)]) + | q21 : int(1..4)]), + and([q23 <= x_PartitionOccurrence_NumParts -> + and([x_PartitionOccurrence_WhichPart[q24] = q23 -> x_PartitionOccurrence_FirstIndex[q23] <= q24 + | q24 : int(1..4)]) + | q23 : int(1..4)]), + and([q23 <= x_PartitionOccurrence_NumParts -> + or([x_PartitionOccurrence_WhichPart[q24] = q23 /\ x_PartitionOccurrence_FirstIndex[q23] = q24 + | q24 : int(1..4)]) + | q23 : int(1..4)]), + and([q23 > x_PartitionOccurrence_NumParts -> x_PartitionOccurrence_FirstIndex[q23] = 1 | q23 : int(1..4)]), + and([q25 <= x_PartitionOccurrence_NumParts /\ q26 <= x_PartitionOccurrence_NumParts -> + (q25 < q26 <-> x_PartitionOccurrence_FirstIndex[q25] < x_PartitionOccurrence_FirstIndex[q26]) + | q25 : int(1..4), q26 : int(1..4)]), + and([q29 <= x_PartitionOccurrence_NumParts -> + or([q33 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ + (and([x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q33, q35] != 5 -> + or([x_PartitionOccurrence_WhichPart[q37] = q29 /\ + q37 = x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q33, q35] + | q37 : int(1..4)]) + | q35 : int(1..4)]) + /\ + and([x_PartitionOccurrence_WhichPart[q39] = q29 -> + or([x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q33, q41] != 5 /\ + x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q33, q41] = q39 + | q41 : int(1..4)]) + | q39 : int(1..4)])) + | q33 : int(1..4)]) + | q29 : int(1..4)]), + and([q44 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> + or([q46 <= x_PartitionOccurrence_NumParts /\ + (and([x_PartitionOccurrence_WhichPart[q49] = q46 -> + or([x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q44, q51] != 5 /\ + x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q44, q51] = q49 + | q51 : int(1..4)]) + | q49 : int(1..4)]) + /\ + and([x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q44, q53] != 5 -> + or([x_PartitionOccurrence_WhichPart[q55] = q46 /\ + q55 = x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q44, q53] + | q55 : int(1..4)]) + | q53 : int(1..4)])) + | q46 : int(1..4)]) + | q44 : int(1..4)]) + diff --git a/tests/exhaustive/basic/partition_06/expected/model_3_1-solution000001.solution b/tests/exhaustive/basic/partition_06/expected/model_3_1-solution000001.solution new file mode 100644 index 0000000000..8d196199c8 --- /dev/null +++ b/tests/exhaustive/basic/partition_06/expected/model_3_1-solution000001.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be partition({1, 4}, {2, 3}) +$ Visualisation for x +$ 1 4 +$ 2 3 + diff --git a/tests/exhaustive/basic/partition_06/expected/model_3_1-solution000002.solution b/tests/exhaustive/basic/partition_06/expected/model_3_1-solution000002.solution new file mode 100644 index 0000000000..b616543ee7 --- /dev/null +++ b/tests/exhaustive/basic/partition_06/expected/model_3_1-solution000002.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be partition({1, 3}, {2, 4}) +$ Visualisation for x +$ 1 3 +$ 2 4 + diff --git a/tests/exhaustive/basic/partition_06/expected/model_3_1-solution000003.solution b/tests/exhaustive/basic/partition_06/expected/model_3_1-solution000003.solution new file mode 100644 index 0000000000..bdecd9ce5b --- /dev/null +++ b/tests/exhaustive/basic/partition_06/expected/model_3_1-solution000003.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be partition({1, 2}, {3, 4}) +$ Visualisation for x +$ 1 2 +$ 3 4 + diff --git a/tests/exhaustive/basic/partition_06/expected/model_3_1.eprime.orig b/tests/exhaustive/basic/partition_06/expected/model_3_1.eprime.orig deleted file mode 100644 index 22b58118fa..0000000000 --- a/tests/exhaustive/basic/partition_06/expected/model_3_1.eprime.orig +++ /dev/null @@ -1,126 +0,0 @@ -language ESSENCE' 1.0 - -find x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker: int(0..4) -find x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker: - matrix indexed by [int(1..4)] of int(0..4) -find x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values: - matrix indexed by [int(1..4), int(1..4)] of int(1..4) -find x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker: int(0..4) -find x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence: matrix indexed by [int(1..4), int(1..4)] of bool -branching on - [x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker, - x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence, - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker, - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker, - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values] -such that - and([q54 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q54] = 2 - | q54 : int(1..4)]), - alldifferent_except([toInt(q55 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - q56 <= - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q55]) - * - catchUndef(x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q55, q56], - 0) - | q55 : int(1..4), q56 : int(1..4)], - 0), - and([q57 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q57] >= 1 - | q57 : int(1..4)]), - and([q4 + 1 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - flatten([[x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q4]; int(1)], - [x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q4, q11] - | q11 : int(1..4)]; - int(1..2)]) - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q5] = 0 /\ - and([x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q5, q49] = 1 - | q49 : int(1..4)]) - | q5 : int(1..4)]), - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker <= 4, - and([q6 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - and([q7 + 1 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q6] -> - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q6, q7] < - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q6, q7 + 1] - | q7 : int(1..3)]) - | q6 : int(1..4)]), - and([q6 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - and([q8 > x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q6] -> - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q6, q8] = 1 - | q8 : int(1..4)]) - | q6 : int(1..4)]), - and([q6 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q6] <= 4 - | q6 : int(1..4)]), - 4 = - sum([toInt(q13 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker) * - catchUndef(x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q13], 0) - | q13 : int(1..4)]), - and([1 = - sum([toInt(q50 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ - x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q50, q14]) - | q50 : int(1..4)]) - | q14 : int(1..4)]), - and([q51 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> - sum([toInt(x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q51, q52]) | q52 : int(1..4)]) >= 1 - | q51 : int(1..4)]), - and([q17 + 1 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> - [-toInt(x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q17, q22]) | q22 : int(1..4)] x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> - and([x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q18, q24] = false | q24 : int(1..4)]) - | q18 : int(1..4)]), - x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker <= 4, - and([q19 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> - sum([toInt(x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q19, q20]) | q20 : int(1..4)]) <= 4 - | q19 : int(1..4)]), - 4 = - sum([toInt(q25 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker) * - catchUndef(sum([toInt(x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q25, q26]) - | q26 : int(1..4)]), - 0) - | q25 : int(1..4)]), - and([q29 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> - or([q32 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - (and([q34 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q32] -> - x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence - [q29, - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q32, q34]] - | q34 : int(1..4)]) - /\ - and([x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q29, q35] -> - or([q37 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q32] - /\ - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q32, q37] = - q35 | q37 : int(1..4)]) - | q35 : int(1..4)])) - | q32 : int(1..4)]) - | q29 : int(1..4)]), - and([q40 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - or([q43 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ - (and([x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q43, q44] -> - or([q46 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q40] - /\ - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q40, q46] = - q44 | q46 : int(1..4)]) - | q44 : int(1..4)]) - /\ - and([q48 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q40] -> - x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence - [q43, - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q40, q48]] - | q48 : int(1..4)])) - | q43 : int(1..4)]) - | q40 : int(1..4)]) - diff --git a/tests/exhaustive/basic/partition_06/expected/model_3_2-solution000001.solution b/tests/exhaustive/basic/partition_06/expected/model_3_2-solution000001.solution new file mode 100644 index 0000000000..bdecd9ce5b --- /dev/null +++ b/tests/exhaustive/basic/partition_06/expected/model_3_2-solution000001.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be partition({1, 2}, {3, 4}) +$ Visualisation for x +$ 1 2 +$ 3 4 + diff --git a/tests/exhaustive/basic/partition_06/expected/model_3_2-solution000002.solution b/tests/exhaustive/basic/partition_06/expected/model_3_2-solution000002.solution new file mode 100644 index 0000000000..b616543ee7 --- /dev/null +++ b/tests/exhaustive/basic/partition_06/expected/model_3_2-solution000002.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be partition({1, 3}, {2, 4}) +$ Visualisation for x +$ 1 3 +$ 2 4 + diff --git a/tests/exhaustive/basic/partition_06/expected/model_3_2-solution000003.solution b/tests/exhaustive/basic/partition_06/expected/model_3_2-solution000003.solution new file mode 100644 index 0000000000..8d196199c8 --- /dev/null +++ b/tests/exhaustive/basic/partition_06/expected/model_3_2-solution000003.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be partition({1, 4}, {2, 3}) +$ Visualisation for x +$ 1 4 +$ 2 3 + diff --git a/tests/exhaustive/basic/partition_06/expected/model_3_2.eprime.orig b/tests/exhaustive/basic/partition_06/expected/model_3_2.eprime.orig deleted file mode 100644 index 933cc936fc..0000000000 --- a/tests/exhaustive/basic/partition_06/expected/model_3_2.eprime.orig +++ /dev/null @@ -1,152 +0,0 @@ -language ESSENCE' 1.0 - -find x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker: int(0..4) -find x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker: - matrix indexed by [int(1..4)] of int(0..4) -find x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values: - matrix indexed by [int(1..4), int(1..4)] of int(1..4) -find x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker: int(0..4) -find x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy: - matrix indexed by [int(1..4), int(1..4)] of int(1..5) -branching on - [x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker, - x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy, - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker, - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker, - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values] -such that - and([q61 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q61] = 2 - | q61 : int(1..4)]), - alldifferent_except([toInt(q62 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - q63 <= - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q62]) - * - catchUndef(x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q62, q63], - 0) - | q62 : int(1..4), q63 : int(1..4)], - 0), - and([q64 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q64] >= 1 - | q64 : int(1..4)]), - and([q4 + 1 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - flatten([[x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q4]; int(1)], - [x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q4, q11] - | q11 : int(1..4)]; - int(1..2)]) - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q5] = 0 /\ - and([x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q5, q58] = 1 - | q58 : int(1..4)]) - | q5 : int(1..4)]), - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker <= 4, - and([q6 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - and([q7 + 1 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q6] -> - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q6, q7] < - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q6, q7 + 1] - | q7 : int(1..3)]) - | q6 : int(1..4)]), - and([q6 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - and([q8 > x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q6] -> - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q6, q8] = 1 - | q8 : int(1..4)]) - | q6 : int(1..4)]), - and([q6 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q6] <= 4 - | q6 : int(1..4)]), - 4 = - sum([toInt(q13 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker) * - catchUndef(x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q13], 0) - | q13 : int(1..4)]), - alldifferent_except([toInt(q65 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ - x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q65, q66] != - 5) - * - catchUndef(x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q65, q66], - 0) - | q65 : int(1..4), q66 : int(1..4)], - 0), - and([q67 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - sum([toInt(x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q67, q69] != 5) - | q69 : int(1..4)]) - >= 1 - | q67 : int(1..4)]), - and([q17 + 1 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - [x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q17, q25] | q25 : int(1..4)] x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - and([x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q18, q59] = 1 - | q59 : int(1..4)]) - | q18 : int(1..4)]), - x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker <= 4, - and([q19 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - and([x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q19, q20] < - x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q19, q20 + 1] - \/ x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q19, q20] = 5 - | q20 : int(1..3)]) - | q19 : int(1..4)]), - and([q19 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - and([x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q19, q21] = 5 -> - x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q19, q21 + 1] = 5 - | q21 : int(1..3)]) - | q19 : int(1..4)]), - and([q19 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - sum([toInt(x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q19, q22] != 5) - | q22 : int(1..4)]) - <= 4 - | q19 : int(1..4)]), - 4 = - sum([toInt(q27 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker) * - catchUndef(sum([toInt(x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q27, q29] != - 5) - | q29 : int(1..4)]), - 0) - | q27 : int(1..4)]), - and([q32 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - or([q35 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - (and([q37 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q35] -> - or([x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q32, q39] != 5 /\ - x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q32, q39] = - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q35, q37] - | q39 : int(1..4)]) - | q37 : int(1..4)]) - /\ - and([x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q32, q41] != 5 -> - or([q43 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q35] - /\ - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q35, q43] = - x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q32, q41] - | q43 : int(1..4)]) - | q41 : int(1..4)])) - | q35 : int(1..4)]) - | q32 : int(1..4)]), - and([q46 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - or([q49 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ - (and([x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q49, q51] != 5 -> - or([q53 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q46] - /\ - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q46, q53] = - x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q49, q51] - | q53 : int(1..4)]) - | q51 : int(1..4)]) - /\ - and([q55 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q46] -> - or([x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q49, q57] != 5 /\ - x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q49, q57] = - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q46, q55] - | q57 : int(1..4)]) - | q55 : int(1..4)])) - | q49 : int(1..4)]) - | q46 : int(1..4)]) - diff --git a/tests/exhaustive/basic/partition_06/expected/model_3_3-solution000001.solution b/tests/exhaustive/basic/partition_06/expected/model_3_3-solution000001.solution new file mode 100644 index 0000000000..bdecd9ce5b --- /dev/null +++ b/tests/exhaustive/basic/partition_06/expected/model_3_3-solution000001.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be partition({1, 2}, {3, 4}) +$ Visualisation for x +$ 1 2 +$ 3 4 + diff --git a/tests/exhaustive/basic/partition_06/expected/model_3_3-solution000002.solution b/tests/exhaustive/basic/partition_06/expected/model_3_3-solution000002.solution new file mode 100644 index 0000000000..b616543ee7 --- /dev/null +++ b/tests/exhaustive/basic/partition_06/expected/model_3_3-solution000002.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be partition({1, 3}, {2, 4}) +$ Visualisation for x +$ 1 3 +$ 2 4 + diff --git a/tests/exhaustive/basic/partition_06/expected/model_3_3-solution000003.solution b/tests/exhaustive/basic/partition_06/expected/model_3_3-solution000003.solution new file mode 100644 index 0000000000..8d196199c8 --- /dev/null +++ b/tests/exhaustive/basic/partition_06/expected/model_3_3-solution000003.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be partition({1, 4}, {2, 3}) +$ Visualisation for x +$ 1 4 +$ 2 3 + diff --git a/tests/exhaustive/basic/partition_06/expected/model_3_3.eprime.orig b/tests/exhaustive/basic/partition_06/expected/model_3_3.eprime.orig deleted file mode 100644 index 91a23d8bc7..0000000000 --- a/tests/exhaustive/basic/partition_06/expected/model_3_3.eprime.orig +++ /dev/null @@ -1,65 +0,0 @@ -language ESSENCE' 1.0 - -find x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker: int(0..4) -find x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker: - matrix indexed by [int(1..4)] of int(0..4) -find x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values: - matrix indexed by [int(1..4), int(1..4)] of int(1..4) -branching on - [x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker, - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker, - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values] -such that - and([q16 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q16] = 2 - | q16 : int(1..4)]), - alldifferent_except([toInt(q17 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - q18 <= - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q17]) - * - catchUndef(x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q17, q18], - 0) - | q17 : int(1..4), q18 : int(1..4)], - 0), - and([q19 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q19] >= 1 - | q19 : int(1..4)]), - and([q4 + 1 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - flatten([[x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q4]; int(1)], - [x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q4, q11] - | q11 : int(1..4)]; - int(1..2)]) - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q5] = 0 /\ - and([x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q5, q14] = 1 - | q14 : int(1..4)]) - | q5 : int(1..4)]), - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker <= 4, - and([q6 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - and([q7 + 1 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q6] -> - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q6, q7] < - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q6, q7 + 1] - | q7 : int(1..3)]) - | q6 : int(1..4)]), - and([q6 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - and([q8 > x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q6] -> - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q6, q8] = 1 - | q8 : int(1..4)]) - | q6 : int(1..4)]), - and([q6 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q6] <= 4 - | q6 : int(1..4)]), - 4 = - sum([toInt(q13 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker) * - catchUndef(x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q13], 0) - | q13 : int(1..4)]) - diff --git a/tests/exhaustive/basic/partition_06/expected/model_3_4-solution000001.solution b/tests/exhaustive/basic/partition_06/expected/model_3_4-solution000001.solution new file mode 100644 index 0000000000..bdecd9ce5b --- /dev/null +++ b/tests/exhaustive/basic/partition_06/expected/model_3_4-solution000001.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be partition({1, 2}, {3, 4}) +$ Visualisation for x +$ 1 2 +$ 3 4 + diff --git a/tests/exhaustive/basic/partition_06/expected/model_3_4-solution000002.solution b/tests/exhaustive/basic/partition_06/expected/model_3_4-solution000002.solution new file mode 100644 index 0000000000..b616543ee7 --- /dev/null +++ b/tests/exhaustive/basic/partition_06/expected/model_3_4-solution000002.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be partition({1, 3}, {2, 4}) +$ Visualisation for x +$ 1 3 +$ 2 4 + diff --git a/tests/exhaustive/basic/partition_06/expected/model_3_4-solution000003.solution b/tests/exhaustive/basic/partition_06/expected/model_3_4-solution000003.solution new file mode 100644 index 0000000000..8d196199c8 --- /dev/null +++ b/tests/exhaustive/basic/partition_06/expected/model_3_4-solution000003.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be partition({1, 4}, {2, 3}) +$ Visualisation for x +$ 1 4 +$ 2 3 + diff --git a/tests/exhaustive/basic/partition_06/expected/model_3_4.eprime.orig b/tests/exhaustive/basic/partition_06/expected/model_3_4.eprime.orig deleted file mode 100644 index 8a20b60fc0..0000000000 --- a/tests/exhaustive/basic/partition_06/expected/model_3_4.eprime.orig +++ /dev/null @@ -1,125 +0,0 @@ -language ESSENCE' 1.0 - -find x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker: int(0..4) -find x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker: - matrix indexed by [int(1..4)] of int(0..4) -find x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values: - matrix indexed by [int(1..4), int(1..4)] of int(1..4) -find x_PartitionOccurrence_NumParts: int(1..4) -find x_PartitionOccurrence_WhichPart: matrix indexed by [int(1..4)] of int(1..4) -find x_PartitionOccurrence_PartSizes: matrix indexed by [int(1..4)] of int(0..4) -find x_PartitionOccurrence_FirstIndex: matrix indexed by [int(1..4)] of int(1..4) -branching on - [x_PartitionOccurrence_NumParts, x_PartitionOccurrence_WhichPart, x_PartitionOccurrence_PartSizes, - x_PartitionOccurrence_FirstIndex, x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker, - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker, - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values] -such that - and([q54 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q54] = 2 - | q54 : int(1..4)]), - alldifferent_except([toInt(q55 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - q56 <= - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q55]) - * - catchUndef(x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q55, q56], - 0) - | q55 : int(1..4), q56 : int(1..4)], - 0), - and([q57 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q57] >= 1 - | q57 : int(1..4)]), - and([q4 + 1 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - flatten([[x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q4]; int(1)], - [x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q4, q11] - | q11 : int(1..4)]; - int(1..2)]) - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q5] = 0 /\ - and([x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q5, q24] = 1 - | q24 : int(1..4)]) - | q5 : int(1..4)]), - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker <= 4, - and([q6 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - and([q7 + 1 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q6] -> - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q6, q7] < - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q6, q7 + 1] - | q7 : int(1..3)]) - | q6 : int(1..4)]), - and([q6 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - and([q8 > x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q6] -> - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q6, q8] = 1 - | q8 : int(1..4)]) - | q6 : int(1..4)]), - and([q6 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q6] <= 4 - | q6 : int(1..4)]), - 4 = - sum([toInt(q13 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker) * - catchUndef(x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q13], 0) - | q13 : int(1..4)]), - and([q14 <= x_PartitionOccurrence_NumParts -> x_PartitionOccurrence_PartSizes[q14] <= 4 | q14 : int(1..4)]), - and([q14 > x_PartitionOccurrence_NumParts -> x_PartitionOccurrence_PartSizes[q14] = 0 | q14 : int(1..4)]), - x_PartitionOccurrence_NumParts <= 4, - and([q15 <= x_PartitionOccurrence_NumParts -> or([x_PartitionOccurrence_WhichPart[q16] = q15 | q16 : int(1..4)]) - | q15 : int(3..4)]), - x_PartitionOccurrence_NumParts = max([x_PartitionOccurrence_WhichPart[q17] | q17 : int(1..4)]), - and([x_PartitionOccurrence_PartSizes[q18] = - sum([toInt(x_PartitionOccurrence_WhichPart[q19] = q18) | q19 : int(1..4)]) - | q18 : int(1..4)]), - and([q20 <= x_PartitionOccurrence_NumParts -> - and([x_PartitionOccurrence_WhichPart[q21] = q20 -> x_PartitionOccurrence_FirstIndex[q20] <= q21 - | q21 : int(1..4)]) - | q20 : int(1..4)]), - and([q20 <= x_PartitionOccurrence_NumParts -> - or([x_PartitionOccurrence_WhichPart[q21] = q20 /\ x_PartitionOccurrence_FirstIndex[q20] = q21 - | q21 : int(1..4)]) - | q20 : int(1..4)]), - and([q20 > x_PartitionOccurrence_NumParts -> x_PartitionOccurrence_FirstIndex[q20] = 1 | q20 : int(1..4)]), - and([q22 <= x_PartitionOccurrence_NumParts /\ q23 <= x_PartitionOccurrence_NumParts -> - (q22 < q23 <-> x_PartitionOccurrence_FirstIndex[q22] < x_PartitionOccurrence_FirstIndex[q23]) - | q22 : int(1..4), q23 : int(1..4)]), - and([q26 <= x_PartitionOccurrence_NumParts -> - or([q30 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - (and([q32 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q30] -> - or([x_PartitionOccurrence_WhichPart[q34] = q26 /\ - q34 = - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q30, q32] - | q34 : int(1..4)]) - | q32 : int(1..4)]) - /\ - and([x_PartitionOccurrence_WhichPart[q36] = q26 -> - or([q38 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q30] - /\ - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q30, q38] = - q36 | q38 : int(1..4)]) - | q36 : int(1..4)])) - | q30 : int(1..4)]) - | q26 : int(1..4)]), - and([q41 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - or([q43 <= x_PartitionOccurrence_NumParts /\ - (and([x_PartitionOccurrence_WhichPart[q46] = q43 -> - or([q48 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q41] - /\ - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q41, q48] = - q46 | q48 : int(1..4)]) - | q46 : int(1..4)]) - /\ - and([q50 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q41] -> - or([x_PartitionOccurrence_WhichPart[q52] = q43 /\ - q52 = - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q41, q50] - | q52 : int(1..4)]) - | q50 : int(1..4)])) - | q43 : int(1..4)]) - | q41 : int(1..4)]) - diff --git a/tests/exhaustive/basic/partition_06/expected/model_4_1-solution000001.solution b/tests/exhaustive/basic/partition_06/expected/model_4_1-solution000001.solution new file mode 100644 index 0000000000..8d196199c8 --- /dev/null +++ b/tests/exhaustive/basic/partition_06/expected/model_4_1-solution000001.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be partition({1, 4}, {2, 3}) +$ Visualisation for x +$ 1 4 +$ 2 3 + diff --git a/tests/exhaustive/basic/partition_06/expected/model_4_1-solution000002.solution b/tests/exhaustive/basic/partition_06/expected/model_4_1-solution000002.solution new file mode 100644 index 0000000000..b616543ee7 --- /dev/null +++ b/tests/exhaustive/basic/partition_06/expected/model_4_1-solution000002.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be partition({1, 3}, {2, 4}) +$ Visualisation for x +$ 1 3 +$ 2 4 + diff --git a/tests/exhaustive/basic/partition_06/expected/model_4_1-solution000003.solution b/tests/exhaustive/basic/partition_06/expected/model_4_1-solution000003.solution new file mode 100644 index 0000000000..bdecd9ce5b --- /dev/null +++ b/tests/exhaustive/basic/partition_06/expected/model_4_1-solution000003.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be partition({1, 2}, {3, 4}) +$ Visualisation for x +$ 1 2 +$ 3 4 + diff --git a/tests/exhaustive/basic/partition_06/expected/model_4_1.eprime b/tests/exhaustive/basic/partition_06/expected/model_4_1.eprime new file mode 100644 index 0000000000..7b16b63344 --- /dev/null +++ b/tests/exhaustive/basic/partition_06/expected/model_4_1.eprime @@ -0,0 +1,82 @@ +language ESSENCE' 1.0 + +find x_PartitionOccurrence_NumParts: int(1..4) +find x_PartitionOccurrence_WhichPart: matrix indexed by [int(1..4)] of int(1..4) +find x_PartitionOccurrence_PartSizes: matrix indexed by [int(1..4)] of int(0..4) +find x_PartitionOccurrence_FirstIndex: matrix indexed by [int(1..4)] of int(1..4) +find x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker: int(0..4) +find x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence: matrix indexed by [int(1..4), int(1..4)] of bool +branching on + [x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker, + x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence, x_PartitionOccurrence_NumParts, + x_PartitionOccurrence_WhichPart, x_PartitionOccurrence_PartSizes, x_PartitionOccurrence_FirstIndex] +such that + and([q49 <= x_PartitionOccurrence_NumParts -> + sum([toInt(x_PartitionOccurrence_WhichPart[q52] = q49) | q52 : int(1..4)]) = 2 + | q49 : int(1..4)]), + and([q1 <= x_PartitionOccurrence_NumParts -> x_PartitionOccurrence_PartSizes[q1] <= 4 | q1 : int(1..4)]), + and([q1 > x_PartitionOccurrence_NumParts -> x_PartitionOccurrence_PartSizes[q1] = 0 | q1 : int(1..4)]), + x_PartitionOccurrence_NumParts <= 4, + and([q2 <= x_PartitionOccurrence_NumParts -> or([x_PartitionOccurrence_WhichPart[q3] = q2 | q3 : int(1..4)]) + | q2 : int(3..4)]), + x_PartitionOccurrence_NumParts = max([x_PartitionOccurrence_WhichPart[q4] | q4 : int(1..4)]), + and([x_PartitionOccurrence_PartSizes[q5] = sum([toInt(x_PartitionOccurrence_WhichPart[q6] = q5) | q6 : int(1..4)]) + | q5 : int(1..4)]), + and([q7 <= x_PartitionOccurrence_NumParts -> + and([x_PartitionOccurrence_WhichPart[q8] = q7 -> x_PartitionOccurrence_FirstIndex[q7] <= q8 | q8 : int(1..4)]) + | q7 : int(1..4)]), + and([q7 <= x_PartitionOccurrence_NumParts -> + or([x_PartitionOccurrence_WhichPart[q8] = q7 /\ x_PartitionOccurrence_FirstIndex[q7] = q8 | q8 : int(1..4)]) + | q7 : int(1..4)]), + and([q7 > x_PartitionOccurrence_NumParts -> x_PartitionOccurrence_FirstIndex[q7] = 1 | q7 : int(1..4)]), + and([q9 <= x_PartitionOccurrence_NumParts /\ q10 <= x_PartitionOccurrence_NumParts -> + (q9 < q10 <-> x_PartitionOccurrence_FirstIndex[q9] < x_PartitionOccurrence_FirstIndex[q10]) + | q9 : int(1..4), q10 : int(1..4)]), + and([1 = + sum([toInt(q46 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ + x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q46, q11]) + | q46 : int(1..4)]) + | q11 : int(1..4)]), + and([q47 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> + sum([toInt(x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q47, q48]) | q48 : int(1..4)]) >= 1 + | q47 : int(1..4)]), + and([q14 + 1 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> + [-toInt(x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q14, q19]) | q19 : int(1..4)] x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> + and([x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q15, q21] = false | q21 : int(1..4)]) + | q15 : int(1..4)]), + x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker <= 4, + and([q16 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> + sum([toInt(x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q16, q17]) | q17 : int(1..4)]) <= 4 + | q16 : int(1..4)]), + 4 = + sum([toInt(q22 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker) * + catchUndef(sum([toInt(x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q22, q23]) + | q23 : int(1..4)]), + 0) + | q22 : int(1..4)]), + and([q26 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> + or([q28 <= x_PartitionOccurrence_NumParts /\ + (and([x_PartitionOccurrence_WhichPart[q31] = q28 -> + x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q26, q31] + | q31 : int(1..4)]) + /\ + and([x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q26, q32] -> + or([x_PartitionOccurrence_WhichPart[q34] = q28 /\ q34 = q32 | q34 : int(1..4)]) + | q32 : int(1..4)])) + | q28 : int(1..4)]) + | q26 : int(1..4)]), + and([q36 <= x_PartitionOccurrence_NumParts -> + or([q40 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ + (and([x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q40, q41] -> + or([x_PartitionOccurrence_WhichPart[q43] = q36 /\ q43 = q41 | q43 : int(1..4)]) + | q41 : int(1..4)]) + /\ + and([x_PartitionOccurrence_WhichPart[q45] = q36 -> + x_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q40, q45] + | q45 : int(1..4)])) + | q40 : int(1..4)]) + | q36 : int(1..4)]) + diff --git a/tests/exhaustive/basic/partition_06/expected/model_4_2-solution000001.solution b/tests/exhaustive/basic/partition_06/expected/model_4_2-solution000001.solution new file mode 100644 index 0000000000..bdecd9ce5b --- /dev/null +++ b/tests/exhaustive/basic/partition_06/expected/model_4_2-solution000001.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be partition({1, 2}, {3, 4}) +$ Visualisation for x +$ 1 2 +$ 3 4 + diff --git a/tests/exhaustive/basic/partition_06/expected/model_4_2-solution000002.solution b/tests/exhaustive/basic/partition_06/expected/model_4_2-solution000002.solution new file mode 100644 index 0000000000..b616543ee7 --- /dev/null +++ b/tests/exhaustive/basic/partition_06/expected/model_4_2-solution000002.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be partition({1, 3}, {2, 4}) +$ Visualisation for x +$ 1 3 +$ 2 4 + diff --git a/tests/exhaustive/basic/partition_06/expected/model_4_2-solution000003.solution b/tests/exhaustive/basic/partition_06/expected/model_4_2-solution000003.solution new file mode 100644 index 0000000000..8d196199c8 --- /dev/null +++ b/tests/exhaustive/basic/partition_06/expected/model_4_2-solution000003.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be partition({1, 4}, {2, 3}) +$ Visualisation for x +$ 1 4 +$ 2 3 + diff --git a/tests/exhaustive/basic/partition_06/expected/model_4_2.eprime b/tests/exhaustive/basic/partition_06/expected/model_4_2.eprime new file mode 100644 index 0000000000..7413ed3262 --- /dev/null +++ b/tests/exhaustive/basic/partition_06/expected/model_4_2.eprime @@ -0,0 +1,112 @@ +language ESSENCE' 1.0 + +find x_PartitionOccurrence_NumParts: int(1..4) +find x_PartitionOccurrence_WhichPart: matrix indexed by [int(1..4)] of int(1..4) +find x_PartitionOccurrence_PartSizes: matrix indexed by [int(1..4)] of int(0..4) +find x_PartitionOccurrence_FirstIndex: matrix indexed by [int(1..4)] of int(1..4) +find x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker: int(0..4) +find x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy: + matrix indexed by [int(1..4), int(1..4)] of int(1..5) +branching on + [x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker, + x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy, x_PartitionOccurrence_NumParts, + x_PartitionOccurrence_WhichPart, x_PartitionOccurrence_PartSizes, x_PartitionOccurrence_FirstIndex] +such that + and([q56 <= x_PartitionOccurrence_NumParts -> + sum([toInt(x_PartitionOccurrence_WhichPart[q59] = q56) | q59 : int(1..4)]) = 2 + | q56 : int(1..4)]), + and([q1 <= x_PartitionOccurrence_NumParts -> x_PartitionOccurrence_PartSizes[q1] <= 4 | q1 : int(1..4)]), + and([q1 > x_PartitionOccurrence_NumParts -> x_PartitionOccurrence_PartSizes[q1] = 0 | q1 : int(1..4)]), + x_PartitionOccurrence_NumParts <= 4, + and([q2 <= x_PartitionOccurrence_NumParts -> or([x_PartitionOccurrence_WhichPart[q3] = q2 | q3 : int(1..4)]) + | q2 : int(3..4)]), + x_PartitionOccurrence_NumParts = max([x_PartitionOccurrence_WhichPart[q4] | q4 : int(1..4)]), + and([x_PartitionOccurrence_PartSizes[q5] = sum([toInt(x_PartitionOccurrence_WhichPart[q6] = q5) | q6 : int(1..4)]) + | q5 : int(1..4)]), + and([q7 <= x_PartitionOccurrence_NumParts -> + and([x_PartitionOccurrence_WhichPart[q8] = q7 -> x_PartitionOccurrence_FirstIndex[q7] <= q8 | q8 : int(1..4)]) + | q7 : int(1..4)]), + and([q7 <= x_PartitionOccurrence_NumParts -> + or([x_PartitionOccurrence_WhichPart[q8] = q7 /\ x_PartitionOccurrence_FirstIndex[q7] = q8 | q8 : int(1..4)]) + | q7 : int(1..4)]), + and([q7 > x_PartitionOccurrence_NumParts -> x_PartitionOccurrence_FirstIndex[q7] = 1 | q7 : int(1..4)]), + and([q9 <= x_PartitionOccurrence_NumParts /\ q10 <= x_PartitionOccurrence_NumParts -> + (q9 < q10 <-> x_PartitionOccurrence_FirstIndex[q9] < x_PartitionOccurrence_FirstIndex[q10]) + | q9 : int(1..4), q10 : int(1..4)]), + alldifferent_except([toInt(q60 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ + x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q60, q61] != + 5) + * + catchUndef(x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q60, q61], + 0) + | q60 : int(1..4), q61 : int(1..4)], + 0), + and([q62 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> + sum([toInt(x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q62, q64] != 5) + | q64 : int(1..4)]) + >= 1 + | q62 : int(1..4)]), + and([q14 + 1 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> + [x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q14, q22] | q22 : int(1..4)] x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> + and([x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q15, q55] = 1 + | q55 : int(1..4)]) + | q15 : int(1..4)]), + x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker <= 4, + and([q16 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> + and([x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q16, q17] < + x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q16, q17 + 1] + \/ x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q16, q17] = 5 + | q17 : int(1..3)]) + | q16 : int(1..4)]), + and([q16 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> + and([x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q16, q18] = 5 -> + x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q16, q18 + 1] = 5 + | q18 : int(1..3)]) + | q16 : int(1..4)]), + and([q16 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> + sum([toInt(x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q16, q19] != 5) + | q19 : int(1..4)]) + <= 4 + | q16 : int(1..4)]), + 4 = + sum([toInt(q24 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker) * + catchUndef(sum([toInt(x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q24, q26] != + 5) + | q26 : int(1..4)]), + 0) + | q24 : int(1..4)]), + and([q29 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> + or([q31 <= x_PartitionOccurrence_NumParts /\ + (and([x_PartitionOccurrence_WhichPart[q34] = q31 -> + or([x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q29, q36] != 5 /\ + x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q29, q36] = q34 + | q36 : int(1..4)]) + | q34 : int(1..4)]) + /\ + and([x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q29, q38] != 5 -> + or([x_PartitionOccurrence_WhichPart[q40] = q31 /\ + q40 = x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q29, q38] + | q40 : int(1..4)]) + | q38 : int(1..4)])) + | q31 : int(1..4)]) + | q29 : int(1..4)]), + and([q42 <= x_PartitionOccurrence_NumParts -> + or([q46 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ + (and([x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q46, q48] != 5 -> + or([x_PartitionOccurrence_WhichPart[q50] = q42 /\ + q50 = x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q46, q48] + | q50 : int(1..4)]) + | q48 : int(1..4)]) + /\ + and([x_PartitionOccurrence_WhichPart[q52] = q42 -> + or([x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q46, q54] != 5 /\ + x_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q46, q54] = q52 + | q54 : int(1..4)]) + | q52 : int(1..4)])) + | q46 : int(1..4)]) + | q42 : int(1..4)]) + diff --git a/tests/exhaustive/basic/partition_06/expected/model_4_3-solution000001.solution b/tests/exhaustive/basic/partition_06/expected/model_4_3-solution000001.solution new file mode 100644 index 0000000000..bdecd9ce5b --- /dev/null +++ b/tests/exhaustive/basic/partition_06/expected/model_4_3-solution000001.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be partition({1, 2}, {3, 4}) +$ Visualisation for x +$ 1 2 +$ 3 4 + diff --git a/tests/exhaustive/basic/partition_06/expected/model_4_3-solution000002.solution b/tests/exhaustive/basic/partition_06/expected/model_4_3-solution000002.solution new file mode 100644 index 0000000000..b616543ee7 --- /dev/null +++ b/tests/exhaustive/basic/partition_06/expected/model_4_3-solution000002.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be partition({1, 3}, {2, 4}) +$ Visualisation for x +$ 1 3 +$ 2 4 + diff --git a/tests/exhaustive/basic/partition_06/expected/model_4_3-solution000003.solution b/tests/exhaustive/basic/partition_06/expected/model_4_3-solution000003.solution new file mode 100644 index 0000000000..8d196199c8 --- /dev/null +++ b/tests/exhaustive/basic/partition_06/expected/model_4_3-solution000003.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be partition({1, 4}, {2, 3}) +$ Visualisation for x +$ 1 4 +$ 2 3 + diff --git a/tests/exhaustive/basic/partition_06/expected/model_4_3.eprime.orig b/tests/exhaustive/basic/partition_06/expected/model_4_3.eprime.orig deleted file mode 100644 index a855ea9d5c..0000000000 --- a/tests/exhaustive/basic/partition_06/expected/model_4_3.eprime.orig +++ /dev/null @@ -1,123 +0,0 @@ -language ESSENCE' 1.0 - -find x_PartitionOccurrence_NumParts: int(1..4) -find x_PartitionOccurrence_WhichPart: matrix indexed by [int(1..4)] of int(1..4) -find x_PartitionOccurrence_PartSizes: matrix indexed by [int(1..4)] of int(0..4) -find x_PartitionOccurrence_FirstIndex: matrix indexed by [int(1..4)] of int(1..4) -find x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker: int(0..4) -find x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker: - matrix indexed by [int(1..4)] of int(0..4) -find x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values: - matrix indexed by [int(1..4), int(1..4)] of int(1..4) -branching on - [x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker, - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker, - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values, - x_PartitionOccurrence_NumParts, x_PartitionOccurrence_WhichPart, x_PartitionOccurrence_PartSizes, - x_PartitionOccurrence_FirstIndex] -such that - and([q53 <= x_PartitionOccurrence_NumParts -> - sum([toInt(x_PartitionOccurrence_WhichPart[q56] = q53) | q56 : int(1..4)]) = 2 - | q53 : int(1..4)]), - and([q1 <= x_PartitionOccurrence_NumParts -> x_PartitionOccurrence_PartSizes[q1] <= 4 | q1 : int(1..4)]), - and([q1 > x_PartitionOccurrence_NumParts -> x_PartitionOccurrence_PartSizes[q1] = 0 | q1 : int(1..4)]), - x_PartitionOccurrence_NumParts <= 4, - and([q2 <= x_PartitionOccurrence_NumParts -> or([x_PartitionOccurrence_WhichPart[q3] = q2 | q3 : int(1..4)]) - | q2 : int(3..4)]), - x_PartitionOccurrence_NumParts = max([x_PartitionOccurrence_WhichPart[q4] | q4 : int(1..4)]), - and([x_PartitionOccurrence_PartSizes[q5] = sum([toInt(x_PartitionOccurrence_WhichPart[q6] = q5) | q6 : int(1..4)]) - | q5 : int(1..4)]), - and([q7 <= x_PartitionOccurrence_NumParts -> - and([x_PartitionOccurrence_WhichPart[q8] = q7 -> x_PartitionOccurrence_FirstIndex[q7] <= q8 | q8 : int(1..4)]) - | q7 : int(1..4)]), - and([q7 <= x_PartitionOccurrence_NumParts -> - or([x_PartitionOccurrence_WhichPart[q8] = q7 /\ x_PartitionOccurrence_FirstIndex[q7] = q8 | q8 : int(1..4)]) - | q7 : int(1..4)]), - and([q7 > x_PartitionOccurrence_NumParts -> x_PartitionOccurrence_FirstIndex[q7] = 1 | q7 : int(1..4)]), - and([q9 <= x_PartitionOccurrence_NumParts /\ q10 <= x_PartitionOccurrence_NumParts -> - (q9 < q10 <-> x_PartitionOccurrence_FirstIndex[q9] < x_PartitionOccurrence_FirstIndex[q10]) - | q9 : int(1..4), q10 : int(1..4)]), - alldifferent_except([toInt(q57 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - q58 <= - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q57]) - * - catchUndef(x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q57, q58], - 0) - | q57 : int(1..4), q58 : int(1..4)], - 0), - and([q59 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q59] >= 1 - | q59 : int(1..4)]), - and([q14 + 1 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - flatten([[x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q14]; int(1)], - [x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q14, q21] - | q21 : int(1..4)]; - int(1..2)]) - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q15] = 0 /\ - and([x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q15, q52] = 1 - | q52 : int(1..4)]) - | q15 : int(1..4)]), - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker <= 4, - and([q16 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - and([q17 + 1 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q16] -> - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q16, q17] < - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q16, q17 + 1] - | q17 : int(1..3)]) - | q16 : int(1..4)]), - and([q16 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - and([q18 > x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q16] -> - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q16, q18] = 1 - | q18 : int(1..4)]) - | q16 : int(1..4)]), - and([q16 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q16] <= 4 - | q16 : int(1..4)]), - 4 = - sum([toInt(q23 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker) * - catchUndef(x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q23], 0) - | q23 : int(1..4)]), - and([q26 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - or([q28 <= x_PartitionOccurrence_NumParts /\ - (and([x_PartitionOccurrence_WhichPart[q31] = q28 -> - or([q33 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q26] - /\ - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q26, q33] = - q31 | q33 : int(1..4)]) - | q31 : int(1..4)]) - /\ - and([q35 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q26] -> - or([x_PartitionOccurrence_WhichPart[q37] = q28 /\ - q37 = - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q26, q35] - | q37 : int(1..4)]) - | q35 : int(1..4)])) - | q28 : int(1..4)]) - | q26 : int(1..4)]), - and([q39 <= x_PartitionOccurrence_NumParts -> - or([q43 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - (and([q45 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q43] -> - or([x_PartitionOccurrence_WhichPart[q47] = q39 /\ - q47 = - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q43, q45] - | q47 : int(1..4)]) - | q45 : int(1..4)]) - /\ - and([x_PartitionOccurrence_WhichPart[q49] = q39 -> - or([q51 <= x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q43] - /\ - x_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q43, q51] = - q49 | q51 : int(1..4)]) - | q49 : int(1..4)])) - | q43 : int(1..4)]) - | q39 : int(1..4)]) - diff --git a/tests/exhaustive/basic/partition_06/expected/model_4_4-solution000001.solution b/tests/exhaustive/basic/partition_06/expected/model_4_4-solution000001.solution new file mode 100644 index 0000000000..bdecd9ce5b --- /dev/null +++ b/tests/exhaustive/basic/partition_06/expected/model_4_4-solution000001.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be partition({1, 2}, {3, 4}) +$ Visualisation for x +$ 1 2 +$ 3 4 + diff --git a/tests/exhaustive/basic/partition_06/expected/model_4_4-solution000002.solution b/tests/exhaustive/basic/partition_06/expected/model_4_4-solution000002.solution new file mode 100644 index 0000000000..b616543ee7 --- /dev/null +++ b/tests/exhaustive/basic/partition_06/expected/model_4_4-solution000002.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be partition({1, 3}, {2, 4}) +$ Visualisation for x +$ 1 3 +$ 2 4 + diff --git a/tests/exhaustive/basic/partition_06/expected/model_4_4-solution000003.solution b/tests/exhaustive/basic/partition_06/expected/model_4_4-solution000003.solution new file mode 100644 index 0000000000..8d196199c8 --- /dev/null +++ b/tests/exhaustive/basic/partition_06/expected/model_4_4-solution000003.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be partition({1, 4}, {2, 3}) +$ Visualisation for x +$ 1 4 +$ 2 3 + diff --git a/tests/exhaustive/basic/partition_06/expected/model_4_4.eprime b/tests/exhaustive/basic/partition_06/expected/model_4_4.eprime new file mode 100644 index 0000000000..6be4048cce --- /dev/null +++ b/tests/exhaustive/basic/partition_06/expected/model_4_4.eprime @@ -0,0 +1,32 @@ +language ESSENCE' 1.0 + +find x_PartitionOccurrence_NumParts: int(1..4) +find x_PartitionOccurrence_WhichPart: matrix indexed by [int(1..4)] of int(1..4) +find x_PartitionOccurrence_PartSizes: matrix indexed by [int(1..4)] of int(0..4) +find x_PartitionOccurrence_FirstIndex: matrix indexed by [int(1..4)] of int(1..4) +branching on + [x_PartitionOccurrence_NumParts, x_PartitionOccurrence_WhichPart, x_PartitionOccurrence_PartSizes, + x_PartitionOccurrence_FirstIndex] +such that + and([q11 <= x_PartitionOccurrence_NumParts -> + sum([toInt(x_PartitionOccurrence_WhichPart[q14] = q11) | q14 : int(1..4)]) = 2 + | q11 : int(1..4)]), + and([q1 <= x_PartitionOccurrence_NumParts -> x_PartitionOccurrence_PartSizes[q1] <= 4 | q1 : int(1..4)]), + and([q1 > x_PartitionOccurrence_NumParts -> x_PartitionOccurrence_PartSizes[q1] = 0 | q1 : int(1..4)]), + x_PartitionOccurrence_NumParts <= 4, + and([q2 <= x_PartitionOccurrence_NumParts -> or([x_PartitionOccurrence_WhichPart[q3] = q2 | q3 : int(1..4)]) + | q2 : int(3..4)]), + x_PartitionOccurrence_NumParts = max([x_PartitionOccurrence_WhichPart[q4] | q4 : int(1..4)]), + and([x_PartitionOccurrence_PartSizes[q5] = sum([toInt(x_PartitionOccurrence_WhichPart[q6] = q5) | q6 : int(1..4)]) + | q5 : int(1..4)]), + and([q7 <= x_PartitionOccurrence_NumParts -> + and([x_PartitionOccurrence_WhichPart[q8] = q7 -> x_PartitionOccurrence_FirstIndex[q7] <= q8 | q8 : int(1..4)]) + | q7 : int(1..4)]), + and([q7 <= x_PartitionOccurrence_NumParts -> + or([x_PartitionOccurrence_WhichPart[q8] = q7 /\ x_PartitionOccurrence_FirstIndex[q7] = q8 | q8 : int(1..4)]) + | q7 : int(1..4)]), + and([q7 > x_PartitionOccurrence_NumParts -> x_PartitionOccurrence_FirstIndex[q7] = 1 | q7 : int(1..4)]), + and([q9 <= x_PartitionOccurrence_NumParts /\ q10 <= x_PartitionOccurrence_NumParts -> + (q9 < q10 <-> x_PartitionOccurrence_FirstIndex[q9] < x_PartitionOccurrence_FirstIndex[q10]) + | q9 : int(1..4), q10 : int(1..4)]) + diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_1-p-solution000001.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_1-p-solution000001.solution new file mode 100644 index 0000000000..991fac89aa --- /dev/null +++ b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_1-p-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {2, 4} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_1-p-solution000002.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_1-p-solution000002.solution new file mode 100644 index 0000000000..8dddb3b359 --- /dev/null +++ b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_1-p-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {2, 3} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_1-p-solution000003.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_1-p-solution000003.solution new file mode 100644 index 0000000000..be06a54735 --- /dev/null +++ b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_1-p-solution000003.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 4} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_1-p-solution000004.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_1-p-solution000004.solution new file mode 100644 index 0000000000..a28b6d6203 --- /dev/null +++ b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_1-p-solution000004.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 3} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_1-p-solution000005.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_1-p-solution000005.solution new file mode 100644 index 0000000000..f90e0ba18c --- /dev/null +++ b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_1-p-solution000005.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_1-p-solution000006.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_1-p-solution000006.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_1-p-solution000006.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_1-p.eprime-param b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_1-p.eprime-param new file mode 100644 index 0000000000..7d6b9721c5 --- /dev/null +++ b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_1-p.eprime-param @@ -0,0 +1,5 @@ +language ESSENCE' 1.0 + +letting n be 2 +letting a be 1 +letting b be 4 diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_1.eprime b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_1.eprime new file mode 100644 index 0000000000..029d9f718f --- /dev/null +++ b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_1.eprime @@ -0,0 +1,20 @@ +language ESSENCE' 1.0 + +given n: int +given a: int +given b: int +find x_Occurrence: matrix indexed by [int(a..b)] of bool +branching on [x_Occurrence] +such that + and([and([x_Occurrence[t_ExplicitVarSizeWithDummy[q7]] + | q7 : int(1..1 + (b - a)), t_ExplicitVarSizeWithDummy[q7] != b + 1]) + -> + sum([t_ExplicitVarSizeWithDummy[q8] | q8 : int(1..1 + (b - a)), t_ExplicitVarSizeWithDummy[q8] != b + 1]) <= 6 + | t_ExplicitVarSizeWithDummy : matrix indexed by [int(1..1 + (b - a))] of int(a..b + 1), + and([t_ExplicitVarSizeWithDummy[q2] < t_ExplicitVarSizeWithDummy[q2 + 1] \/ + t_ExplicitVarSizeWithDummy[q2] = b + 1 + | q2 : int(1..1 + (b - a) - 1)]), + and([t_ExplicitVarSizeWithDummy[q3] = b + 1 -> t_ExplicitVarSizeWithDummy[q3 + 1] = b + 1 + | q3 : int(1..1 + (b - a) - 1)])]), + n <= sum([toInt(x_Occurrence[q1]) | q1 : int(a..b)]) + diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_2-p-solution000001.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_2-p-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_2-p-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_2-p-solution000002.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_2-p-solution000002.solution new file mode 100644 index 0000000000..f90e0ba18c --- /dev/null +++ b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_2-p-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_2-p-solution000003.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_2-p-solution000003.solution new file mode 100644 index 0000000000..a28b6d6203 --- /dev/null +++ b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_2-p-solution000003.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 3} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_2-p-solution000004.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_2-p-solution000004.solution new file mode 100644 index 0000000000..be06a54735 --- /dev/null +++ b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_2-p-solution000004.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 4} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_2-p-solution000005.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_2-p-solution000005.solution new file mode 100644 index 0000000000..8dddb3b359 --- /dev/null +++ b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_2-p-solution000005.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {2, 3} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_2-p-solution000006.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_2-p-solution000006.solution new file mode 100644 index 0000000000..991fac89aa --- /dev/null +++ b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_2-p-solution000006.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {2, 4} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_2-p.eprime-param b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_2-p.eprime-param new file mode 100644 index 0000000000..7d6b9721c5 --- /dev/null +++ b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_2-p.eprime-param @@ -0,0 +1,5 @@ +language ESSENCE' 1.0 + +letting n be 2 +letting a be 1 +letting b be 4 diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_2.eprime b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_2.eprime new file mode 100644 index 0000000000..2334196ec8 --- /dev/null +++ b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_2.eprime @@ -0,0 +1,32 @@ +language ESSENCE' 1.0 + +given n: int +given a: int +given b: int +find x_Occurrence: matrix indexed by [int(a..b)] of bool +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..1 + (b - a))] of int(a..b + 1) +branching on [x_ExplicitVarSizeWithDummy, x_Occurrence] +such that + and([and([x_Occurrence[t_ExplicitVarSizeWithDummy[q16]] + | q16 : int(1..1 + (b - a)), t_ExplicitVarSizeWithDummy[q16] != b + 1]) + -> + sum([t_ExplicitVarSizeWithDummy[q17] | q17 : int(1..1 + (b - a)), t_ExplicitVarSizeWithDummy[q17] != b + 1]) <= + 6 | t_ExplicitVarSizeWithDummy : matrix indexed by [int(1..1 + (b - a))] of int(a..b + 1), + and([t_ExplicitVarSizeWithDummy[q11] < t_ExplicitVarSizeWithDummy[q11 + 1] \/ + t_ExplicitVarSizeWithDummy[q11] = b + 1 + | q11 : int(1..1 + (b - a) - 1)]), + and([t_ExplicitVarSizeWithDummy[q12] = b + 1 -> t_ExplicitVarSizeWithDummy[q12 + 1] = b + 1 + | q12 : int(1..1 + (b - a) - 1)])]), + n <= sum([toInt(x_Occurrence[q1]) | q1 : int(a..b)]), + and([x_ExplicitVarSizeWithDummy[q2] < x_ExplicitVarSizeWithDummy[q2 + 1] \/ x_ExplicitVarSizeWithDummy[q2] = b + 1 + | q2 : int(1..1 + (b - a) - 1)]), + and([x_ExplicitVarSizeWithDummy[q3] = b + 1 -> x_ExplicitVarSizeWithDummy[q3 + 1] = b + 1 + | q3 : int(1..1 + (b - a) - 1)]), + n <= sum([toInt(x_ExplicitVarSizeWithDummy[q4] != b + 1) | q4 : int(1..1 + (b - a))]), + and([x_ExplicitVarSizeWithDummy[q7] != b + 1 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q7]] + | q7 : int(1..1 + (b - a))]), + and([x_Occurrence[q8] -> + or([x_ExplicitVarSizeWithDummy[q10] != b + 1 /\ x_ExplicitVarSizeWithDummy[q10] = q8 + | q10 : int(1..1 + (b - a))]) + | q8 : int(a..b)]) + diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_3-p-solution000001.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_3-p-solution000001.solution new file mode 100644 index 0000000000..f90e0ba18c --- /dev/null +++ b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_3-p-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_3-p-solution000002.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_3-p-solution000002.solution new file mode 100644 index 0000000000..a28b6d6203 --- /dev/null +++ b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_3-p-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 3} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_3-p-solution000003.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_3-p-solution000003.solution new file mode 100644 index 0000000000..be06a54735 --- /dev/null +++ b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_3-p-solution000003.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 4} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_3-p-solution000004.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_3-p-solution000004.solution new file mode 100644 index 0000000000..8dddb3b359 --- /dev/null +++ b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_3-p-solution000004.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {2, 3} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_3-p-solution000005.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_3-p-solution000005.solution new file mode 100644 index 0000000000..991fac89aa --- /dev/null +++ b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_3-p-solution000005.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {2, 4} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_3-p-solution000006.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_3-p-solution000006.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_3-p-solution000006.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_3-p.eprime-param b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_3-p.eprime-param new file mode 100644 index 0000000000..7d6b9721c5 --- /dev/null +++ b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_3-p.eprime-param @@ -0,0 +1,5 @@ +language ESSENCE' 1.0 + +letting n be 2 +letting a be 1 +letting b be 4 diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_3.eprime b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_3.eprime new file mode 100644 index 0000000000..d44b8ab518 --- /dev/null +++ b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_3.eprime @@ -0,0 +1,34 @@ +language ESSENCE' 1.0 + +given n: int +given a: int +given b: int +find x_Occurrence: matrix indexed by [int(a..b)] of bool +find x_ExplicitVarSizeWithMarker_Marker: int(0..1 + (b - a)) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..1 + (b - a))] of int(a..b) +branching on [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_Occurrence] +such that + and([and([x_Occurrence[t_ExplicitVarSizeWithDummy[q15]] + | q15 : int(1..1 + (b - a)), t_ExplicitVarSizeWithDummy[q15] != b + 1]) + -> + sum([t_ExplicitVarSizeWithDummy[q16] | q16 : int(1..1 + (b - a)), t_ExplicitVarSizeWithDummy[q16] != b + 1]) <= + 6 | t_ExplicitVarSizeWithDummy : matrix indexed by [int(1..1 + (b - a))] of int(a..b + 1), + and([t_ExplicitVarSizeWithDummy[q10] < t_ExplicitVarSizeWithDummy[q10 + 1] \/ + t_ExplicitVarSizeWithDummy[q10] = b + 1 + | q10 : int(1..1 + (b - a) - 1)]), + and([t_ExplicitVarSizeWithDummy[q11] = b + 1 -> t_ExplicitVarSizeWithDummy[q11 + 1] = b + 1 + | q11 : int(1..1 + (b - a) - 1)])]), + n <= sum([toInt(x_Occurrence[q1]) | q1 : int(a..b)]), + and([q2 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q2] < x_ExplicitVarSizeWithMarker_Values[q2 + 1] + | q2 : int(1..1 + (b - a) - 1)]), + and([q3 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q3] = a + | q3 : int(1..1 + (b - a))]), + n <= x_ExplicitVarSizeWithMarker_Marker, + and([q6 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q6]] + | q6 : int(1..1 + (b - a))]), + and([x_Occurrence[q7] -> + or([q9 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q9] = q7 + | q9 : int(1..1 + (b - a))]) + | q7 : int(a..b)]) + diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_4-p-solution000001.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_4-p-solution000001.solution new file mode 100644 index 0000000000..f90e0ba18c --- /dev/null +++ b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_4-p-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_4-p-solution000002.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_4-p-solution000002.solution new file mode 100644 index 0000000000..a28b6d6203 --- /dev/null +++ b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_4-p-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 3} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_4-p-solution000003.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_4-p-solution000003.solution new file mode 100644 index 0000000000..be06a54735 --- /dev/null +++ b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_4-p-solution000003.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 4} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_4-p-solution000004.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_4-p-solution000004.solution new file mode 100644 index 0000000000..8dddb3b359 --- /dev/null +++ b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_4-p-solution000004.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {2, 3} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_4-p-solution000005.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_4-p-solution000005.solution new file mode 100644 index 0000000000..991fac89aa --- /dev/null +++ b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_4-p-solution000005.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {2, 4} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_4-p-solution000006.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_4-p-solution000006.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_4-p-solution000006.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_4-p.eprime-param b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_4-p.eprime-param new file mode 100644 index 0000000000..7d6b9721c5 --- /dev/null +++ b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_4-p.eprime-param @@ -0,0 +1,5 @@ +language ESSENCE' 1.0 + +letting n be 2 +letting a be 1 +letting b be 4 diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_4.eprime b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_4.eprime new file mode 100644 index 0000000000..c5a3851fe1 --- /dev/null +++ b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_1_4.eprime @@ -0,0 +1,36 @@ +language ESSENCE' 1.0 + +given n: int +given a: int +given b: int +find x_Occurrence: matrix indexed by [int(a..b)] of bool +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..1 + (b - a))] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..1 + (b - a))] of int(a..b) +branching on [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_Occurrence] +such that + and([and([x_Occurrence[t_ExplicitVarSizeWithDummy[q17]] + | q17 : int(1..1 + (b - a)), t_ExplicitVarSizeWithDummy[q17] != b + 1]) + -> + sum([t_ExplicitVarSizeWithDummy[q18] | q18 : int(1..1 + (b - a)), t_ExplicitVarSizeWithDummy[q18] != b + 1]) <= + 6 | t_ExplicitVarSizeWithDummy : matrix indexed by [int(1..1 + (b - a))] of int(a..b + 1), + and([t_ExplicitVarSizeWithDummy[q12] < t_ExplicitVarSizeWithDummy[q12 + 1] \/ + t_ExplicitVarSizeWithDummy[q12] = b + 1 + | q12 : int(1..1 + (b - a) - 1)]), + and([t_ExplicitVarSizeWithDummy[q13] = b + 1 -> t_ExplicitVarSizeWithDummy[q13 + 1] = b + 1 + | q13 : int(1..1 + (b - a) - 1)])]), + n <= sum([toInt(x_Occurrence[q1]) | q1 : int(a..b)]), + and([x_ExplicitVarSizeWithFlags_Flags[q2 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q2] < x_ExplicitVarSizeWithFlags_Values[q2 + 1] + | q2 : int(1..1 + (b - a) - 1)]), + and([x_ExplicitVarSizeWithFlags_Flags[q3] = false -> x_ExplicitVarSizeWithFlags_Values[q3] = a + | q3 : int(1..1 + (b - a))]), + and([x_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q4] + | q4 : int(1..1 + (b - a) - 1)]), + n <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q5]) | q5 : int(1..1 + (b - a))]), + and([x_ExplicitVarSizeWithFlags_Flags[q8] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q8]] + | q8 : int(1..1 + (b - a))]), + and([x_Occurrence[q9] -> + or([x_ExplicitVarSizeWithFlags_Flags[q11] /\ x_ExplicitVarSizeWithFlags_Values[q11] = q9 + | q11 : int(1..1 + (b - a))]) + | q9 : int(a..b)]) + diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_1-p-solution000001.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_1-p-solution000001.solution new file mode 100644 index 0000000000..991fac89aa --- /dev/null +++ b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_1-p-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {2, 4} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_1-p-solution000002.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_1-p-solution000002.solution new file mode 100644 index 0000000000..8dddb3b359 --- /dev/null +++ b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_1-p-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {2, 3} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_1-p-solution000003.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_1-p-solution000003.solution new file mode 100644 index 0000000000..be06a54735 --- /dev/null +++ b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_1-p-solution000003.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 4} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_1-p-solution000004.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_1-p-solution000004.solution new file mode 100644 index 0000000000..a28b6d6203 --- /dev/null +++ b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_1-p-solution000004.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 3} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_1-p-solution000005.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_1-p-solution000005.solution new file mode 100644 index 0000000000..f90e0ba18c --- /dev/null +++ b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_1-p-solution000005.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_1-p-solution000006.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_1-p-solution000006.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_1-p-solution000006.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_1-p.eprime-param b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_1-p.eprime-param new file mode 100644 index 0000000000..7d6b9721c5 --- /dev/null +++ b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_1-p.eprime-param @@ -0,0 +1,5 @@ +language ESSENCE' 1.0 + +letting n be 2 +letting a be 1 +letting b be 4 diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_1.eprime b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_1.eprime new file mode 100644 index 0000000000..6a88075ca6 --- /dev/null +++ b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_1.eprime @@ -0,0 +1,33 @@ +language ESSENCE' 1.0 + +given n: int +given a: int +given b: int +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..1 + (b - a))] of int(a..b + 1) +find x_Occurrence: matrix indexed by [int(a..b)] of bool +branching on [x_Occurrence, x_ExplicitVarSizeWithDummy] +such that + and([and([or([x_ExplicitVarSizeWithDummy[q18] != b + 1 /\ + x_ExplicitVarSizeWithDummy[q18] = t_ExplicitVarSizeWithDummy[q16] + | q18 : int(1..1 + (b - a))]) + | q16 : int(1..1 + (b - a)), t_ExplicitVarSizeWithDummy[q16] != b + 1]) + -> + sum([t_ExplicitVarSizeWithDummy[q19] | q19 : int(1..1 + (b - a)), t_ExplicitVarSizeWithDummy[q19] != b + 1]) <= + 6 | t_ExplicitVarSizeWithDummy : matrix indexed by [int(1..1 + (b - a))] of int(a..b + 1), + and([t_ExplicitVarSizeWithDummy[q11] < t_ExplicitVarSizeWithDummy[q11 + 1] \/ + t_ExplicitVarSizeWithDummy[q11] = b + 1 + | q11 : int(1..1 + (b - a) - 1)]), + and([t_ExplicitVarSizeWithDummy[q12] = b + 1 -> t_ExplicitVarSizeWithDummy[q12 + 1] = b + 1 + | q12 : int(1..1 + (b - a) - 1)])]), + and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = b + 1 + | q1 : int(1..1 + (b - a) - 1)]), + and([x_ExplicitVarSizeWithDummy[q2] = b + 1 -> x_ExplicitVarSizeWithDummy[q2 + 1] = b + 1 + | q2 : int(1..1 + (b - a) - 1)]), + n <= sum([toInt(x_ExplicitVarSizeWithDummy[q3] != b + 1) | q3 : int(1..1 + (b - a))]), + n <= sum([toInt(x_Occurrence[q5]) | q5 : int(a..b)]), + and([x_Occurrence[q6] -> + or([x_ExplicitVarSizeWithDummy[q8] != b + 1 /\ x_ExplicitVarSizeWithDummy[q8] = q6 | q8 : int(1..1 + (b - a))]) + | q6 : int(a..b)]), + and([x_ExplicitVarSizeWithDummy[q10] != b + 1 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q10]] + | q10 : int(1..1 + (b - a))]) + diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_2-p-solution000001.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_2-p-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_2-p-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_2-p-solution000002.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_2-p-solution000002.solution new file mode 100644 index 0000000000..f90e0ba18c --- /dev/null +++ b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_2-p-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_2-p-solution000003.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_2-p-solution000003.solution new file mode 100644 index 0000000000..a28b6d6203 --- /dev/null +++ b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_2-p-solution000003.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 3} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_2-p-solution000004.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_2-p-solution000004.solution new file mode 100644 index 0000000000..be06a54735 --- /dev/null +++ b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_2-p-solution000004.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 4} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_2-p-solution000005.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_2-p-solution000005.solution new file mode 100644 index 0000000000..8dddb3b359 --- /dev/null +++ b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_2-p-solution000005.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {2, 3} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_2-p-solution000006.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_2-p-solution000006.solution new file mode 100644 index 0000000000..991fac89aa --- /dev/null +++ b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_2-p-solution000006.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {2, 4} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_2-p.eprime-param b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_2-p.eprime-param new file mode 100644 index 0000000000..7d6b9721c5 --- /dev/null +++ b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_2-p.eprime-param @@ -0,0 +1,5 @@ +language ESSENCE' 1.0 + +letting n be 2 +letting a be 1 +letting b be 4 diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_2.eprime b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_2.eprime new file mode 100644 index 0000000000..f4dd241cca --- /dev/null +++ b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_2.eprime @@ -0,0 +1,26 @@ +language ESSENCE' 1.0 + +given n: int +given a: int +given b: int +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..1 + (b - a))] of int(a..b + 1) +branching on [x_ExplicitVarSizeWithDummy] +such that + and([and([or([x_ExplicitVarSizeWithDummy[q12] != b + 1 /\ + x_ExplicitVarSizeWithDummy[q12] = t_ExplicitVarSizeWithDummy[q10] + | q12 : int(1..1 + (b - a))]) + | q10 : int(1..1 + (b - a)), t_ExplicitVarSizeWithDummy[q10] != b + 1]) + -> + sum([t_ExplicitVarSizeWithDummy[q13] | q13 : int(1..1 + (b - a)), t_ExplicitVarSizeWithDummy[q13] != b + 1]) <= + 6 | t_ExplicitVarSizeWithDummy : matrix indexed by [int(1..1 + (b - a))] of int(a..b + 1), + and([t_ExplicitVarSizeWithDummy[q5] < t_ExplicitVarSizeWithDummy[q5 + 1] \/ + t_ExplicitVarSizeWithDummy[q5] = b + 1 + | q5 : int(1..1 + (b - a) - 1)]), + and([t_ExplicitVarSizeWithDummy[q6] = b + 1 -> t_ExplicitVarSizeWithDummy[q6 + 1] = b + 1 + | q6 : int(1..1 + (b - a) - 1)])]), + and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = b + 1 + | q1 : int(1..1 + (b - a) - 1)]), + and([x_ExplicitVarSizeWithDummy[q2] = b + 1 -> x_ExplicitVarSizeWithDummy[q2 + 1] = b + 1 + | q2 : int(1..1 + (b - a) - 1)]), + n <= sum([toInt(x_ExplicitVarSizeWithDummy[q3] != b + 1) | q3 : int(1..1 + (b - a))]) + diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_3-p-solution000001.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_3-p-solution000001.solution new file mode 100644 index 0000000000..f90e0ba18c --- /dev/null +++ b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_3-p-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_3-p-solution000002.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_3-p-solution000002.solution new file mode 100644 index 0000000000..a28b6d6203 --- /dev/null +++ b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_3-p-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 3} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_3-p-solution000003.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_3-p-solution000003.solution new file mode 100644 index 0000000000..be06a54735 --- /dev/null +++ b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_3-p-solution000003.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 4} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_3-p-solution000004.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_3-p-solution000004.solution new file mode 100644 index 0000000000..8dddb3b359 --- /dev/null +++ b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_3-p-solution000004.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {2, 3} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_3-p-solution000005.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_3-p-solution000005.solution new file mode 100644 index 0000000000..991fac89aa --- /dev/null +++ b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_3-p-solution000005.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {2, 4} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_3-p-solution000006.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_3-p-solution000006.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_3-p-solution000006.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_3-p.eprime-param b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_3-p.eprime-param new file mode 100644 index 0000000000..7d6b9721c5 --- /dev/null +++ b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_3-p.eprime-param @@ -0,0 +1,5 @@ +language ESSENCE' 1.0 + +letting n be 2 +letting a be 1 +letting b be 4 diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_3.eprime b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_3.eprime new file mode 100644 index 0000000000..92c80b9133 --- /dev/null +++ b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_3.eprime @@ -0,0 +1,44 @@ +language ESSENCE' 1.0 + +given n: int +given a: int +given b: int +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..1 + (b - a))] of int(a..b + 1) +find x_ExplicitVarSizeWithMarker_Marker: int(0..1 + (b - a)) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..1 + (b - a))] of int(a..b) +branching on [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy] +such that + and([and([or([x_ExplicitVarSizeWithDummy[q23] != b + 1 /\ + x_ExplicitVarSizeWithDummy[q23] = t_ExplicitVarSizeWithDummy[q21] + | q23 : int(1..1 + (b - a))]) + | q21 : int(1..1 + (b - a)), t_ExplicitVarSizeWithDummy[q21] != b + 1]) + -> + sum([t_ExplicitVarSizeWithDummy[q24] | q24 : int(1..1 + (b - a)), t_ExplicitVarSizeWithDummy[q24] != b + 1]) <= + 6 | t_ExplicitVarSizeWithDummy : matrix indexed by [int(1..1 + (b - a))] of int(a..b + 1), + and([t_ExplicitVarSizeWithDummy[q16] < t_ExplicitVarSizeWithDummy[q16 + 1] \/ + t_ExplicitVarSizeWithDummy[q16] = b + 1 + | q16 : int(1..1 + (b - a) - 1)]), + and([t_ExplicitVarSizeWithDummy[q17] = b + 1 -> t_ExplicitVarSizeWithDummy[q17 + 1] = b + 1 + | q17 : int(1..1 + (b - a) - 1)])]), + and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = b + 1 + | q1 : int(1..1 + (b - a) - 1)]), + and([x_ExplicitVarSizeWithDummy[q2] = b + 1 -> x_ExplicitVarSizeWithDummy[q2 + 1] = b + 1 + | q2 : int(1..1 + (b - a) - 1)]), + n <= sum([toInt(x_ExplicitVarSizeWithDummy[q3] != b + 1) | q3 : int(1..1 + (b - a))]), + and([q5 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q5] < x_ExplicitVarSizeWithMarker_Values[q5 + 1] + | q5 : int(1..1 + (b - a) - 1)]), + and([q6 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q6] = a + | q6 : int(1..1 + (b - a))]), + n <= x_ExplicitVarSizeWithMarker_Marker, + and([q9 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithDummy[q11] != b + 1 /\ + x_ExplicitVarSizeWithDummy[q11] = x_ExplicitVarSizeWithMarker_Values[q9] + | q11 : int(1..1 + (b - a))]) + | q9 : int(1..1 + (b - a))]), + and([x_ExplicitVarSizeWithDummy[q13] != b + 1 -> + or([q15 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q15] = x_ExplicitVarSizeWithDummy[q13] + | q15 : int(1..1 + (b - a))]) + | q13 : int(1..1 + (b - a))]) + diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_4-p-solution000001.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_4-p-solution000001.solution new file mode 100644 index 0000000000..f90e0ba18c --- /dev/null +++ b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_4-p-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_4-p-solution000002.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_4-p-solution000002.solution new file mode 100644 index 0000000000..a28b6d6203 --- /dev/null +++ b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_4-p-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 3} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_4-p-solution000003.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_4-p-solution000003.solution new file mode 100644 index 0000000000..be06a54735 --- /dev/null +++ b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_4-p-solution000003.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 4} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_4-p-solution000004.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_4-p-solution000004.solution new file mode 100644 index 0000000000..8dddb3b359 --- /dev/null +++ b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_4-p-solution000004.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {2, 3} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_4-p-solution000005.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_4-p-solution000005.solution new file mode 100644 index 0000000000..991fac89aa --- /dev/null +++ b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_4-p-solution000005.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {2, 4} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_4-p-solution000006.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_4-p-solution000006.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_4-p-solution000006.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_4-p.eprime-param b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_4-p.eprime-param new file mode 100644 index 0000000000..7d6b9721c5 --- /dev/null +++ b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_4-p.eprime-param @@ -0,0 +1,5 @@ +language ESSENCE' 1.0 + +letting n be 2 +letting a be 1 +letting b be 4 diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_4.eprime b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_4.eprime new file mode 100644 index 0000000000..4b598c63b3 --- /dev/null +++ b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_2_4.eprime @@ -0,0 +1,46 @@ +language ESSENCE' 1.0 + +given n: int +given a: int +given b: int +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..1 + (b - a))] of int(a..b + 1) +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..1 + (b - a))] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..1 + (b - a))] of int(a..b) +branching on [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy] +such that + and([and([or([x_ExplicitVarSizeWithDummy[q25] != b + 1 /\ + x_ExplicitVarSizeWithDummy[q25] = t_ExplicitVarSizeWithDummy[q23] + | q25 : int(1..1 + (b - a))]) + | q23 : int(1..1 + (b - a)), t_ExplicitVarSizeWithDummy[q23] != b + 1]) + -> + sum([t_ExplicitVarSizeWithDummy[q26] | q26 : int(1..1 + (b - a)), t_ExplicitVarSizeWithDummy[q26] != b + 1]) <= + 6 | t_ExplicitVarSizeWithDummy : matrix indexed by [int(1..1 + (b - a))] of int(a..b + 1), + and([t_ExplicitVarSizeWithDummy[q18] < t_ExplicitVarSizeWithDummy[q18 + 1] \/ + t_ExplicitVarSizeWithDummy[q18] = b + 1 + | q18 : int(1..1 + (b - a) - 1)]), + and([t_ExplicitVarSizeWithDummy[q19] = b + 1 -> t_ExplicitVarSizeWithDummy[q19 + 1] = b + 1 + | q19 : int(1..1 + (b - a) - 1)])]), + and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = b + 1 + | q1 : int(1..1 + (b - a) - 1)]), + and([x_ExplicitVarSizeWithDummy[q2] = b + 1 -> x_ExplicitVarSizeWithDummy[q2 + 1] = b + 1 + | q2 : int(1..1 + (b - a) - 1)]), + n <= sum([toInt(x_ExplicitVarSizeWithDummy[q3] != b + 1) | q3 : int(1..1 + (b - a))]), + and([x_ExplicitVarSizeWithFlags_Flags[q5 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q5] < x_ExplicitVarSizeWithFlags_Values[q5 + 1] + | q5 : int(1..1 + (b - a) - 1)]), + and([x_ExplicitVarSizeWithFlags_Flags[q6] = false -> x_ExplicitVarSizeWithFlags_Values[q6] = a + | q6 : int(1..1 + (b - a))]), + and([x_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q7] + | q7 : int(1..1 + (b - a) - 1)]), + n <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q8]) | q8 : int(1..1 + (b - a))]), + and([x_ExplicitVarSizeWithFlags_Flags[q11] -> + or([x_ExplicitVarSizeWithDummy[q13] != b + 1 /\ + x_ExplicitVarSizeWithDummy[q13] = x_ExplicitVarSizeWithFlags_Values[q11] + | q13 : int(1..1 + (b - a))]) + | q11 : int(1..1 + (b - a))]), + and([x_ExplicitVarSizeWithDummy[q15] != b + 1 -> + or([x_ExplicitVarSizeWithFlags_Flags[q17] /\ + x_ExplicitVarSizeWithFlags_Values[q17] = x_ExplicitVarSizeWithDummy[q15] + | q17 : int(1..1 + (b - a))]) + | q15 : int(1..1 + (b - a))]) + diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_1-p-solution000001.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_1-p-solution000001.solution new file mode 100644 index 0000000000..991fac89aa --- /dev/null +++ b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_1-p-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {2, 4} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_1-p-solution000002.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_1-p-solution000002.solution new file mode 100644 index 0000000000..8dddb3b359 --- /dev/null +++ b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_1-p-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {2, 3} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_1-p-solution000003.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_1-p-solution000003.solution new file mode 100644 index 0000000000..be06a54735 --- /dev/null +++ b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_1-p-solution000003.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 4} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_1-p-solution000004.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_1-p-solution000004.solution new file mode 100644 index 0000000000..a28b6d6203 --- /dev/null +++ b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_1-p-solution000004.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 3} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_1-p-solution000005.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_1-p-solution000005.solution new file mode 100644 index 0000000000..f90e0ba18c --- /dev/null +++ b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_1-p-solution000005.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_1-p-solution000006.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_1-p-solution000006.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_1-p-solution000006.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_1-p.eprime-param b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_1-p.eprime-param new file mode 100644 index 0000000000..7d6b9721c5 --- /dev/null +++ b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_1-p.eprime-param @@ -0,0 +1,5 @@ +language ESSENCE' 1.0 + +letting n be 2 +letting a be 1 +letting b be 4 diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_1.eprime b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_1.eprime new file mode 100644 index 0000000000..00361f80a7 --- /dev/null +++ b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_1.eprime @@ -0,0 +1,36 @@ +language ESSENCE' 1.0 + +given n: int +given a: int +given b: int +find x_ExplicitVarSizeWithMarker_Marker: int(0..1 + (b - a)) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..1 + (b - a))] of int(a..b) +find x_Occurrence: matrix indexed by [int(a..b)] of bool +branching on [x_Occurrence, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] +such that + and([and([or([q17 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q17] = t_ExplicitVarSizeWithDummy[q15] + | q17 : int(1..1 + (b - a))]) + | q15 : int(1..1 + (b - a)), t_ExplicitVarSizeWithDummy[q15] != b + 1]) + -> + sum([t_ExplicitVarSizeWithDummy[q18] | q18 : int(1..1 + (b - a)), t_ExplicitVarSizeWithDummy[q18] != b + 1]) <= + 6 | t_ExplicitVarSizeWithDummy : matrix indexed by [int(1..1 + (b - a))] of int(a..b + 1), + and([t_ExplicitVarSizeWithDummy[q10] < t_ExplicitVarSizeWithDummy[q10 + 1] \/ + t_ExplicitVarSizeWithDummy[q10] = b + 1 + | q10 : int(1..1 + (b - a) - 1)]), + and([t_ExplicitVarSizeWithDummy[q11] = b + 1 -> t_ExplicitVarSizeWithDummy[q11 + 1] = b + 1 + | q11 : int(1..1 + (b - a) - 1)])]), + and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] + | q1 : int(1..1 + (b - a) - 1)]), + and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = a + | q2 : int(1..1 + (b - a))]), + n <= x_ExplicitVarSizeWithMarker_Marker, + n <= sum([toInt(x_Occurrence[q4]) | q4 : int(a..b)]), + and([x_Occurrence[q5] -> + or([q7 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q7] = q5 + | q7 : int(1..1 + (b - a))]) + | q5 : int(a..b)]), + and([q9 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q9]] + | q9 : int(1..1 + (b - a))]) + diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_2-p-solution000001.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_2-p-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_2-p-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_2-p-solution000002.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_2-p-solution000002.solution new file mode 100644 index 0000000000..f90e0ba18c --- /dev/null +++ b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_2-p-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_2-p-solution000003.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_2-p-solution000003.solution new file mode 100644 index 0000000000..a28b6d6203 --- /dev/null +++ b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_2-p-solution000003.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 3} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_2-p-solution000004.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_2-p-solution000004.solution new file mode 100644 index 0000000000..be06a54735 --- /dev/null +++ b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_2-p-solution000004.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 4} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_2-p-solution000005.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_2-p-solution000005.solution new file mode 100644 index 0000000000..8dddb3b359 --- /dev/null +++ b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_2-p-solution000005.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {2, 3} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_2-p-solution000006.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_2-p-solution000006.solution new file mode 100644 index 0000000000..991fac89aa --- /dev/null +++ b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_2-p-solution000006.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {2, 4} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_2-p.eprime-param b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_2-p.eprime-param new file mode 100644 index 0000000000..7d6b9721c5 --- /dev/null +++ b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_2-p.eprime-param @@ -0,0 +1,5 @@ +language ESSENCE' 1.0 + +letting n be 2 +letting a be 1 +letting b be 4 diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_2.eprime b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_2.eprime new file mode 100644 index 0000000000..f071e0ff08 --- /dev/null +++ b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_2.eprime @@ -0,0 +1,44 @@ +language ESSENCE' 1.0 + +given n: int +given a: int +given b: int +find x_ExplicitVarSizeWithMarker_Marker: int(0..1 + (b - a)) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..1 + (b - a))] of int(a..b) +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..1 + (b - a))] of int(a..b + 1) +branching on [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] +such that + and([and([or([q23 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q23] = t_ExplicitVarSizeWithDummy[q21] + | q23 : int(1..1 + (b - a))]) + | q21 : int(1..1 + (b - a)), t_ExplicitVarSizeWithDummy[q21] != b + 1]) + -> + sum([t_ExplicitVarSizeWithDummy[q24] | q24 : int(1..1 + (b - a)), t_ExplicitVarSizeWithDummy[q24] != b + 1]) <= + 6 | t_ExplicitVarSizeWithDummy : matrix indexed by [int(1..1 + (b - a))] of int(a..b + 1), + and([t_ExplicitVarSizeWithDummy[q16] < t_ExplicitVarSizeWithDummy[q16 + 1] \/ + t_ExplicitVarSizeWithDummy[q16] = b + 1 + | q16 : int(1..1 + (b - a) - 1)]), + and([t_ExplicitVarSizeWithDummy[q17] = b + 1 -> t_ExplicitVarSizeWithDummy[q17 + 1] = b + 1 + | q17 : int(1..1 + (b - a) - 1)])]), + and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] + | q1 : int(1..1 + (b - a) - 1)]), + and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = a + | q2 : int(1..1 + (b - a))]), + n <= x_ExplicitVarSizeWithMarker_Marker, + and([x_ExplicitVarSizeWithDummy[q4] < x_ExplicitVarSizeWithDummy[q4 + 1] \/ x_ExplicitVarSizeWithDummy[q4] = b + 1 + | q4 : int(1..1 + (b - a) - 1)]), + and([x_ExplicitVarSizeWithDummy[q5] = b + 1 -> x_ExplicitVarSizeWithDummy[q5 + 1] = b + 1 + | q5 : int(1..1 + (b - a) - 1)]), + n <= sum([toInt(x_ExplicitVarSizeWithDummy[q6] != b + 1) | q6 : int(1..1 + (b - a))]), + and([x_ExplicitVarSizeWithDummy[q9] != b + 1 -> + or([q11 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q11] = x_ExplicitVarSizeWithDummy[q9] + | q11 : int(1..1 + (b - a))]) + | q9 : int(1..1 + (b - a))]), + and([q13 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithDummy[q15] != b + 1 /\ + x_ExplicitVarSizeWithDummy[q15] = x_ExplicitVarSizeWithMarker_Values[q13] + | q15 : int(1..1 + (b - a))]) + | q13 : int(1..1 + (b - a))]) + diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_3-p-solution000001.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_3-p-solution000001.solution new file mode 100644 index 0000000000..f90e0ba18c --- /dev/null +++ b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_3-p-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_3-p-solution000002.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_3-p-solution000002.solution new file mode 100644 index 0000000000..a28b6d6203 --- /dev/null +++ b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_3-p-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 3} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_3-p-solution000003.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_3-p-solution000003.solution new file mode 100644 index 0000000000..be06a54735 --- /dev/null +++ b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_3-p-solution000003.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 4} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_3-p-solution000004.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_3-p-solution000004.solution new file mode 100644 index 0000000000..8dddb3b359 --- /dev/null +++ b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_3-p-solution000004.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {2, 3} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_3-p-solution000005.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_3-p-solution000005.solution new file mode 100644 index 0000000000..991fac89aa --- /dev/null +++ b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_3-p-solution000005.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {2, 4} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_3-p-solution000006.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_3-p-solution000006.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_3-p-solution000006.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_3-p.eprime-param b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_3-p.eprime-param new file mode 100644 index 0000000000..7d6b9721c5 --- /dev/null +++ b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_3-p.eprime-param @@ -0,0 +1,5 @@ +language ESSENCE' 1.0 + +letting n be 2 +letting a be 1 +letting b be 4 diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_3.eprime b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_3.eprime new file mode 100644 index 0000000000..8fa49fbf6d --- /dev/null +++ b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_3.eprime @@ -0,0 +1,28 @@ +language ESSENCE' 1.0 + +given n: int +given a: int +given b: int +find x_ExplicitVarSizeWithMarker_Marker: int(0..1 + (b - a)) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..1 + (b - a))] of int(a..b) +branching on [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] +such that + and([and([or([q11 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q11] = t_ExplicitVarSizeWithDummy[q9] + | q11 : int(1..1 + (b - a))]) + | q9 : int(1..1 + (b - a)), t_ExplicitVarSizeWithDummy[q9] != b + 1]) + -> + sum([t_ExplicitVarSizeWithDummy[q12] | q12 : int(1..1 + (b - a)), t_ExplicitVarSizeWithDummy[q12] != b + 1]) <= + 6 | t_ExplicitVarSizeWithDummy : matrix indexed by [int(1..1 + (b - a))] of int(a..b + 1), + and([t_ExplicitVarSizeWithDummy[q4] < t_ExplicitVarSizeWithDummy[q4 + 1] \/ + t_ExplicitVarSizeWithDummy[q4] = b + 1 + | q4 : int(1..1 + (b - a) - 1)]), + and([t_ExplicitVarSizeWithDummy[q5] = b + 1 -> t_ExplicitVarSizeWithDummy[q5 + 1] = b + 1 + | q5 : int(1..1 + (b - a) - 1)])]), + and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] + | q1 : int(1..1 + (b - a) - 1)]), + and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = a + | q2 : int(1..1 + (b - a))]), + n <= x_ExplicitVarSizeWithMarker_Marker + diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_4-p-solution000001.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_4-p-solution000001.solution new file mode 100644 index 0000000000..f90e0ba18c --- /dev/null +++ b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_4-p-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_4-p-solution000002.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_4-p-solution000002.solution new file mode 100644 index 0000000000..a28b6d6203 --- /dev/null +++ b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_4-p-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 3} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_4-p-solution000003.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_4-p-solution000003.solution new file mode 100644 index 0000000000..be06a54735 --- /dev/null +++ b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_4-p-solution000003.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 4} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_4-p-solution000004.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_4-p-solution000004.solution new file mode 100644 index 0000000000..8dddb3b359 --- /dev/null +++ b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_4-p-solution000004.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {2, 3} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_4-p-solution000005.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_4-p-solution000005.solution new file mode 100644 index 0000000000..991fac89aa --- /dev/null +++ b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_4-p-solution000005.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {2, 4} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_4-p-solution000006.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_4-p-solution000006.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_4-p-solution000006.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_4-p.eprime-param b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_4-p.eprime-param new file mode 100644 index 0000000000..7d6b9721c5 --- /dev/null +++ b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_4-p.eprime-param @@ -0,0 +1,5 @@ +language ESSENCE' 1.0 + +letting n be 2 +letting a be 1 +letting b be 4 diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_4.eprime b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_4.eprime new file mode 100644 index 0000000000..bacc7d46b3 --- /dev/null +++ b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_3_4.eprime @@ -0,0 +1,50 @@ +language ESSENCE' 1.0 + +given n: int +given a: int +given b: int +find x_ExplicitVarSizeWithMarker_Marker: int(0..1 + (b - a)) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..1 + (b - a))] of int(a..b) +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..1 + (b - a))] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..1 + (b - a))] of int(a..b) +branching on + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithMarker_Marker, + x_ExplicitVarSizeWithMarker_Values] +such that + and([and([or([q24 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q24] = t_ExplicitVarSizeWithDummy[q22] + | q24 : int(1..1 + (b - a))]) + | q22 : int(1..1 + (b - a)), t_ExplicitVarSizeWithDummy[q22] != b + 1]) + -> + sum([t_ExplicitVarSizeWithDummy[q25] | q25 : int(1..1 + (b - a)), t_ExplicitVarSizeWithDummy[q25] != b + 1]) <= + 6 | t_ExplicitVarSizeWithDummy : matrix indexed by [int(1..1 + (b - a))] of int(a..b + 1), + and([t_ExplicitVarSizeWithDummy[q17] < t_ExplicitVarSizeWithDummy[q17 + 1] \/ + t_ExplicitVarSizeWithDummy[q17] = b + 1 + | q17 : int(1..1 + (b - a) - 1)]), + and([t_ExplicitVarSizeWithDummy[q18] = b + 1 -> t_ExplicitVarSizeWithDummy[q18 + 1] = b + 1 + | q18 : int(1..1 + (b - a) - 1)])]), + and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] + | q1 : int(1..1 + (b - a) - 1)]), + and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = a + | q2 : int(1..1 + (b - a))]), + n <= x_ExplicitVarSizeWithMarker_Marker, + and([x_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q4] < x_ExplicitVarSizeWithFlags_Values[q4 + 1] + | q4 : int(1..1 + (b - a) - 1)]), + and([x_ExplicitVarSizeWithFlags_Flags[q5] = false -> x_ExplicitVarSizeWithFlags_Values[q5] = a + | q5 : int(1..1 + (b - a))]), + and([x_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q6] + | q6 : int(1..1 + (b - a) - 1)]), + n <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q7]) | q7 : int(1..1 + (b - a))]), + and([x_ExplicitVarSizeWithFlags_Flags[q10] -> + or([q12 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q12] = x_ExplicitVarSizeWithFlags_Values[q10] + | q12 : int(1..1 + (b - a))]) + | q10 : int(1..1 + (b - a))]), + and([q14 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithFlags_Flags[q16] /\ + x_ExplicitVarSizeWithFlags_Values[q16] = x_ExplicitVarSizeWithMarker_Values[q14] + | q16 : int(1..1 + (b - a))]) + | q14 : int(1..1 + (b - a))]) + diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_1-p-solution000001.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_1-p-solution000001.solution new file mode 100644 index 0000000000..991fac89aa --- /dev/null +++ b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_1-p-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {2, 4} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_1-p-solution000002.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_1-p-solution000002.solution new file mode 100644 index 0000000000..8dddb3b359 --- /dev/null +++ b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_1-p-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {2, 3} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_1-p-solution000003.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_1-p-solution000003.solution new file mode 100644 index 0000000000..be06a54735 --- /dev/null +++ b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_1-p-solution000003.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 4} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_1-p-solution000004.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_1-p-solution000004.solution new file mode 100644 index 0000000000..a28b6d6203 --- /dev/null +++ b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_1-p-solution000004.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 3} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_1-p-solution000005.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_1-p-solution000005.solution new file mode 100644 index 0000000000..f90e0ba18c --- /dev/null +++ b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_1-p-solution000005.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_1-p-solution000006.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_1-p-solution000006.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_1-p-solution000006.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_1-p.eprime-param b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_1-p.eprime-param new file mode 100644 index 0000000000..7d6b9721c5 --- /dev/null +++ b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_1-p.eprime-param @@ -0,0 +1,5 @@ +language ESSENCE' 1.0 + +letting n be 2 +letting a be 1 +letting b be 4 diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_1.eprime b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_1.eprime new file mode 100644 index 0000000000..5b6f7598a4 --- /dev/null +++ b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_1.eprime @@ -0,0 +1,38 @@ +language ESSENCE' 1.0 + +given n: int +given a: int +given b: int +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..1 + (b - a))] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..1 + (b - a))] of int(a..b) +find x_Occurrence: matrix indexed by [int(a..b)] of bool +branching on [x_Occurrence, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] +such that + and([and([or([x_ExplicitVarSizeWithFlags_Flags[q19] /\ + x_ExplicitVarSizeWithFlags_Values[q19] = t_ExplicitVarSizeWithDummy[q17] + | q19 : int(1..1 + (b - a))]) + | q17 : int(1..1 + (b - a)), t_ExplicitVarSizeWithDummy[q17] != b + 1]) + -> + sum([t_ExplicitVarSizeWithDummy[q20] | q20 : int(1..1 + (b - a)), t_ExplicitVarSizeWithDummy[q20] != b + 1]) <= + 6 | t_ExplicitVarSizeWithDummy : matrix indexed by [int(1..1 + (b - a))] of int(a..b + 1), + and([t_ExplicitVarSizeWithDummy[q12] < t_ExplicitVarSizeWithDummy[q12 + 1] \/ + t_ExplicitVarSizeWithDummy[q12] = b + 1 + | q12 : int(1..1 + (b - a) - 1)]), + and([t_ExplicitVarSizeWithDummy[q13] = b + 1 -> t_ExplicitVarSizeWithDummy[q13 + 1] = b + 1 + | q13 : int(1..1 + (b - a) - 1)])]), + and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] + | q1 : int(1..1 + (b - a) - 1)]), + and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = a + | q2 : int(1..1 + (b - a))]), + and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] + | q3 : int(1..1 + (b - a) - 1)]), + n <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..1 + (b - a))]), + n <= sum([toInt(x_Occurrence[q6]) | q6 : int(a..b)]), + and([x_Occurrence[q7] -> + or([x_ExplicitVarSizeWithFlags_Flags[q9] /\ x_ExplicitVarSizeWithFlags_Values[q9] = q7 + | q9 : int(1..1 + (b - a))]) + | q7 : int(a..b)]), + and([x_ExplicitVarSizeWithFlags_Flags[q11] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q11]] + | q11 : int(1..1 + (b - a))]) + diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_2-p-solution000001.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_2-p-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_2-p-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_2-p-solution000002.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_2-p-solution000002.solution new file mode 100644 index 0000000000..f90e0ba18c --- /dev/null +++ b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_2-p-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_2-p-solution000003.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_2-p-solution000003.solution new file mode 100644 index 0000000000..a28b6d6203 --- /dev/null +++ b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_2-p-solution000003.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 3} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_2-p-solution000004.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_2-p-solution000004.solution new file mode 100644 index 0000000000..be06a54735 --- /dev/null +++ b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_2-p-solution000004.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 4} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_2-p-solution000005.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_2-p-solution000005.solution new file mode 100644 index 0000000000..8dddb3b359 --- /dev/null +++ b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_2-p-solution000005.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {2, 3} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_2-p-solution000006.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_2-p-solution000006.solution new file mode 100644 index 0000000000..991fac89aa --- /dev/null +++ b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_2-p-solution000006.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {2, 4} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_2-p.eprime-param b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_2-p.eprime-param new file mode 100644 index 0000000000..7d6b9721c5 --- /dev/null +++ b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_2-p.eprime-param @@ -0,0 +1,5 @@ +language ESSENCE' 1.0 + +letting n be 2 +letting a be 1 +letting b be 4 diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_2.eprime b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_2.eprime new file mode 100644 index 0000000000..97885f92e5 --- /dev/null +++ b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_2.eprime @@ -0,0 +1,46 @@ +language ESSENCE' 1.0 + +given n: int +given a: int +given b: int +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..1 + (b - a))] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..1 + (b - a))] of int(a..b) +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..1 + (b - a))] of int(a..b + 1) +branching on [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] +such that + and([and([or([x_ExplicitVarSizeWithFlags_Flags[q25] /\ + x_ExplicitVarSizeWithFlags_Values[q25] = t_ExplicitVarSizeWithDummy[q23] + | q25 : int(1..1 + (b - a))]) + | q23 : int(1..1 + (b - a)), t_ExplicitVarSizeWithDummy[q23] != b + 1]) + -> + sum([t_ExplicitVarSizeWithDummy[q26] | q26 : int(1..1 + (b - a)), t_ExplicitVarSizeWithDummy[q26] != b + 1]) <= + 6 | t_ExplicitVarSizeWithDummy : matrix indexed by [int(1..1 + (b - a))] of int(a..b + 1), + and([t_ExplicitVarSizeWithDummy[q18] < t_ExplicitVarSizeWithDummy[q18 + 1] \/ + t_ExplicitVarSizeWithDummy[q18] = b + 1 + | q18 : int(1..1 + (b - a) - 1)]), + and([t_ExplicitVarSizeWithDummy[q19] = b + 1 -> t_ExplicitVarSizeWithDummy[q19 + 1] = b + 1 + | q19 : int(1..1 + (b - a) - 1)])]), + and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] + | q1 : int(1..1 + (b - a) - 1)]), + and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = a + | q2 : int(1..1 + (b - a))]), + and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] + | q3 : int(1..1 + (b - a) - 1)]), + n <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..1 + (b - a))]), + and([x_ExplicitVarSizeWithDummy[q6] < x_ExplicitVarSizeWithDummy[q6 + 1] \/ x_ExplicitVarSizeWithDummy[q6] = b + 1 + | q6 : int(1..1 + (b - a) - 1)]), + and([x_ExplicitVarSizeWithDummy[q7] = b + 1 -> x_ExplicitVarSizeWithDummy[q7 + 1] = b + 1 + | q7 : int(1..1 + (b - a) - 1)]), + n <= sum([toInt(x_ExplicitVarSizeWithDummy[q8] != b + 1) | q8 : int(1..1 + (b - a))]), + and([x_ExplicitVarSizeWithDummy[q11] != b + 1 -> + or([x_ExplicitVarSizeWithFlags_Flags[q13] /\ + x_ExplicitVarSizeWithFlags_Values[q13] = x_ExplicitVarSizeWithDummy[q11] + | q13 : int(1..1 + (b - a))]) + | q11 : int(1..1 + (b - a))]), + and([x_ExplicitVarSizeWithFlags_Flags[q15] -> + or([x_ExplicitVarSizeWithDummy[q17] != b + 1 /\ + x_ExplicitVarSizeWithDummy[q17] = x_ExplicitVarSizeWithFlags_Values[q15] + | q17 : int(1..1 + (b - a))]) + | q15 : int(1..1 + (b - a))]) + diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_3-p-solution000001.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_3-p-solution000001.solution new file mode 100644 index 0000000000..f90e0ba18c --- /dev/null +++ b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_3-p-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_3-p-solution000002.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_3-p-solution000002.solution new file mode 100644 index 0000000000..a28b6d6203 --- /dev/null +++ b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_3-p-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 3} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_3-p-solution000003.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_3-p-solution000003.solution new file mode 100644 index 0000000000..be06a54735 --- /dev/null +++ b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_3-p-solution000003.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 4} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_3-p-solution000004.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_3-p-solution000004.solution new file mode 100644 index 0000000000..8dddb3b359 --- /dev/null +++ b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_3-p-solution000004.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {2, 3} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_3-p-solution000005.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_3-p-solution000005.solution new file mode 100644 index 0000000000..991fac89aa --- /dev/null +++ b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_3-p-solution000005.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {2, 4} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_3-p-solution000006.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_3-p-solution000006.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_3-p-solution000006.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_3-p.eprime-param b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_3-p.eprime-param new file mode 100644 index 0000000000..7d6b9721c5 --- /dev/null +++ b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_3-p.eprime-param @@ -0,0 +1,5 @@ +language ESSENCE' 1.0 + +letting n be 2 +letting a be 1 +letting b be 4 diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_3.eprime b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_3.eprime new file mode 100644 index 0000000000..60687fba2b --- /dev/null +++ b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_3.eprime @@ -0,0 +1,50 @@ +language ESSENCE' 1.0 + +given n: int +given a: int +given b: int +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..1 + (b - a))] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..1 + (b - a))] of int(a..b) +find x_ExplicitVarSizeWithMarker_Marker: int(0..1 + (b - a)) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..1 + (b - a))] of int(a..b) +branching on + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithFlags_Flags, + x_ExplicitVarSizeWithFlags_Values] +such that + and([and([or([x_ExplicitVarSizeWithFlags_Flags[q24] /\ + x_ExplicitVarSizeWithFlags_Values[q24] = t_ExplicitVarSizeWithDummy[q22] + | q24 : int(1..1 + (b - a))]) + | q22 : int(1..1 + (b - a)), t_ExplicitVarSizeWithDummy[q22] != b + 1]) + -> + sum([t_ExplicitVarSizeWithDummy[q25] | q25 : int(1..1 + (b - a)), t_ExplicitVarSizeWithDummy[q25] != b + 1]) <= + 6 | t_ExplicitVarSizeWithDummy : matrix indexed by [int(1..1 + (b - a))] of int(a..b + 1), + and([t_ExplicitVarSizeWithDummy[q17] < t_ExplicitVarSizeWithDummy[q17 + 1] \/ + t_ExplicitVarSizeWithDummy[q17] = b + 1 + | q17 : int(1..1 + (b - a) - 1)]), + and([t_ExplicitVarSizeWithDummy[q18] = b + 1 -> t_ExplicitVarSizeWithDummy[q18 + 1] = b + 1 + | q18 : int(1..1 + (b - a) - 1)])]), + and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] + | q1 : int(1..1 + (b - a) - 1)]), + and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = a + | q2 : int(1..1 + (b - a))]), + and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] + | q3 : int(1..1 + (b - a) - 1)]), + n <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..1 + (b - a))]), + and([q6 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q6] < x_ExplicitVarSizeWithMarker_Values[q6 + 1] + | q6 : int(1..1 + (b - a) - 1)]), + and([q7 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q7] = a + | q7 : int(1..1 + (b - a))]), + n <= x_ExplicitVarSizeWithMarker_Marker, + and([q10 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithFlags_Flags[q12] /\ + x_ExplicitVarSizeWithFlags_Values[q12] = x_ExplicitVarSizeWithMarker_Values[q10] + | q12 : int(1..1 + (b - a))]) + | q10 : int(1..1 + (b - a))]), + and([x_ExplicitVarSizeWithFlags_Flags[q14] -> + or([q16 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q16] = x_ExplicitVarSizeWithFlags_Values[q14] + | q16 : int(1..1 + (b - a))]) + | q14 : int(1..1 + (b - a))]) + diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_4-p-solution000001.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_4-p-solution000001.solution new file mode 100644 index 0000000000..f90e0ba18c --- /dev/null +++ b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_4-p-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_4-p-solution000002.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_4-p-solution000002.solution new file mode 100644 index 0000000000..a28b6d6203 --- /dev/null +++ b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_4-p-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 3} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_4-p-solution000003.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_4-p-solution000003.solution new file mode 100644 index 0000000000..be06a54735 --- /dev/null +++ b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_4-p-solution000003.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 4} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_4-p-solution000004.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_4-p-solution000004.solution new file mode 100644 index 0000000000..8dddb3b359 --- /dev/null +++ b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_4-p-solution000004.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {2, 3} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_4-p-solution000005.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_4-p-solution000005.solution new file mode 100644 index 0000000000..991fac89aa --- /dev/null +++ b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_4-p-solution000005.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {2, 4} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_4-p-solution000006.solution b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_4-p-solution000006.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_4-p-solution000006.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_4-p.eprime-param b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_4-p.eprime-param new file mode 100644 index 0000000000..7d6b9721c5 --- /dev/null +++ b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_4-p.eprime-param @@ -0,0 +1,5 @@ +language ESSENCE' 1.0 + +letting n be 2 +letting a be 1 +letting b be 4 diff --git a/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_4.eprime b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_4.eprime new file mode 100644 index 0000000000..ba348b8892 --- /dev/null +++ b/tests/exhaustive/basic/powerSetComprehensionDirect/expected/model_4_4.eprime @@ -0,0 +1,30 @@ +language ESSENCE' 1.0 + +given n: int +given a: int +given b: int +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..1 + (b - a))] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..1 + (b - a))] of int(a..b) +branching on [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] +such that + and([and([or([x_ExplicitVarSizeWithFlags_Flags[q13] /\ + x_ExplicitVarSizeWithFlags_Values[q13] = t_ExplicitVarSizeWithDummy[q11] + | q13 : int(1..1 + (b - a))]) + | q11 : int(1..1 + (b - a)), t_ExplicitVarSizeWithDummy[q11] != b + 1]) + -> + sum([t_ExplicitVarSizeWithDummy[q14] | q14 : int(1..1 + (b - a)), t_ExplicitVarSizeWithDummy[q14] != b + 1]) <= + 6 | t_ExplicitVarSizeWithDummy : matrix indexed by [int(1..1 + (b - a))] of int(a..b + 1), + and([t_ExplicitVarSizeWithDummy[q6] < t_ExplicitVarSizeWithDummy[q6 + 1] \/ + t_ExplicitVarSizeWithDummy[q6] = b + 1 + | q6 : int(1..1 + (b - a) - 1)]), + and([t_ExplicitVarSizeWithDummy[q7] = b + 1 -> t_ExplicitVarSizeWithDummy[q7 + 1] = b + 1 + | q7 : int(1..1 + (b - a) - 1)])]), + and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] + | q1 : int(1..1 + (b - a) - 1)]), + and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = a + | q2 : int(1..1 + (b - a))]), + and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] + | q3 : int(1..1 + (b - a) - 1)]), + n <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..1 + (b - a))]) + diff --git a/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_1_1-solution000001.solution b/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_1_1-solution000001.solution new file mode 100644 index 0000000000..f1495354fe --- /dev/null +++ b/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_1_1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 4, 7} diff --git a/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_1_1.eprime b/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_1_1.eprime new file mode 100644 index 0000000000..b9c9ef2a41 --- /dev/null +++ b/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_1_1.eprime @@ -0,0 +1,8 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(1..7)] of bool +branching on [x_Occurrence] +such that + and([x_Occurrence[i] /\ x_Occurrence[j] -> |i - j| >= 3 | i : int(1..7), j : int(1..7), j > i]), + 3 <= sum([toInt(x_Occurrence[q1]) | q1 : int(1..7)]) + diff --git a/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_1_2-solution000001.solution b/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_1_2-solution000001.solution new file mode 100644 index 0000000000..f1495354fe --- /dev/null +++ b/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_1_2-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 4, 7} diff --git a/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_1_2.eprime b/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_1_2.eprime new file mode 100644 index 0000000000..f4555045bf --- /dev/null +++ b/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_1_2.eprime @@ -0,0 +1,17 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(1..7)] of bool +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..7)] of int(1..8) +branching on [x_ExplicitVarSizeWithDummy, x_Occurrence] +such that + and([x_Occurrence[i] /\ x_Occurrence[j] -> |i - j| >= 3 | i : int(1..7), j : int(1..7), j > i]), + 3 <= sum([toInt(x_Occurrence[q1]) | q1 : int(1..7)]), + and([x_ExplicitVarSizeWithDummy[q2] < x_ExplicitVarSizeWithDummy[q2 + 1] \/ x_ExplicitVarSizeWithDummy[q2] = 8 + | q2 : int(1..6)]), + and([x_ExplicitVarSizeWithDummy[q3] = 8 -> x_ExplicitVarSizeWithDummy[q3 + 1] = 8 | q3 : int(1..6)]), + 3 <= sum([toInt(x_ExplicitVarSizeWithDummy[q4] != 8) | q4 : int(1..7)]), + and([x_ExplicitVarSizeWithDummy[q7] != 8 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q7]] | q7 : int(1..7)]), + and([x_Occurrence[q8] -> + or([x_ExplicitVarSizeWithDummy[q10] != 8 /\ x_ExplicitVarSizeWithDummy[q10] = q8 | q10 : int(1..7)]) + | q8 : int(1..7)]) + diff --git a/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_1_3-solution000001.solution b/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_1_3-solution000001.solution new file mode 100644 index 0000000000..f1495354fe --- /dev/null +++ b/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_1_3-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 4, 7} diff --git a/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_1_3.eprime b/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_1_3.eprime new file mode 100644 index 0000000000..a9df3b1a89 --- /dev/null +++ b/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_1_3.eprime @@ -0,0 +1,20 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(1..7)] of bool +find x_ExplicitVarSizeWithMarker_Marker: int(0..7) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..7)] of int(1..7) +branching on [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_Occurrence] +such that + and([x_Occurrence[i] /\ x_Occurrence[j] -> |i - j| >= 3 | i : int(1..7), j : int(1..7), j > i]), + 3 <= sum([toInt(x_Occurrence[q1]) | q1 : int(1..7)]), + and([q2 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q2] < x_ExplicitVarSizeWithMarker_Values[q2 + 1] + | q2 : int(1..6)]), + and([q3 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q3] = 1 | q3 : int(1..7)]), + 3 <= x_ExplicitVarSizeWithMarker_Marker, + and([q6 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q6]] + | q6 : int(1..7)]), + and([x_Occurrence[q7] -> + or([q9 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q9] = q7 | q9 : int(1..7)]) + | q7 : int(1..7)]) + diff --git a/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_1_4-solution000001.solution b/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_1_4-solution000001.solution new file mode 100644 index 0000000000..f1495354fe --- /dev/null +++ b/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_1_4-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 4, 7} diff --git a/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_1_4.eprime b/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_1_4.eprime new file mode 100644 index 0000000000..f343493acc --- /dev/null +++ b/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_1_4.eprime @@ -0,0 +1,20 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(1..7)] of bool +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..7)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..7)] of int(1..7) +branching on [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_Occurrence] +such that + and([x_Occurrence[i] /\ x_Occurrence[j] -> |i - j| >= 3 | i : int(1..7), j : int(1..7), j > i]), + 3 <= sum([toInt(x_Occurrence[q1]) | q1 : int(1..7)]), + and([x_ExplicitVarSizeWithFlags_Flags[q2 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q2] < x_ExplicitVarSizeWithFlags_Values[q2 + 1] + | q2 : int(1..6)]), + and([x_ExplicitVarSizeWithFlags_Flags[q3] = false -> x_ExplicitVarSizeWithFlags_Values[q3] = 1 | q3 : int(1..7)]), + and([x_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q4] | q4 : int(1..6)]), + 3 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q5]) | q5 : int(1..7)]), + and([x_ExplicitVarSizeWithFlags_Flags[q8] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q8]] | q8 : int(1..7)]), + and([x_Occurrence[q9] -> + or([x_ExplicitVarSizeWithFlags_Flags[q11] /\ x_ExplicitVarSizeWithFlags_Values[q11] = q9 | q11 : int(1..7)]) + | q9 : int(1..7)]) + diff --git a/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_2_1-solution000001.solution b/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_2_1-solution000001.solution new file mode 100644 index 0000000000..f1495354fe --- /dev/null +++ b/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_2_1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 4, 7} diff --git a/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_2_1.eprime b/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_2_1.eprime new file mode 100644 index 0000000000..0f44241558 --- /dev/null +++ b/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_2_1.eprime @@ -0,0 +1,19 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..7)] of int(1..8) +find x_Occurrence: matrix indexed by [int(1..7)] of bool +branching on [x_Occurrence, x_ExplicitVarSizeWithDummy] +such that + and([x_ExplicitVarSizeWithDummy[q11] != 8 /\ x_ExplicitVarSizeWithDummy[q12] != 8 -> + |x_ExplicitVarSizeWithDummy[q11] - x_ExplicitVarSizeWithDummy[q12]| >= 3 + | q11 : int(1..7), q12 : int(1..7), q12 > q11]), + and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 8 + | q1 : int(1..6)]), + and([x_ExplicitVarSizeWithDummy[q2] = 8 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 8 | q2 : int(1..6)]), + 3 <= sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 8) | q3 : int(1..7)]), + 3 <= sum([toInt(x_Occurrence[q5]) | q5 : int(1..7)]), + and([x_Occurrence[q6] -> + or([x_ExplicitVarSizeWithDummy[q8] != 8 /\ x_ExplicitVarSizeWithDummy[q8] = q6 | q8 : int(1..7)]) + | q6 : int(1..7)]), + and([x_ExplicitVarSizeWithDummy[q10] != 8 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q10]] | q10 : int(1..7)]) + diff --git a/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_2_2-solution000001.solution b/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_2_2-solution000001.solution new file mode 100644 index 0000000000..f1495354fe --- /dev/null +++ b/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_2_2-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 4, 7} diff --git a/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_2_2.eprime b/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_2_2.eprime new file mode 100644 index 0000000000..4fb1321636 --- /dev/null +++ b/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_2_2.eprime @@ -0,0 +1,13 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..7)] of int(1..8) +branching on [x_ExplicitVarSizeWithDummy] +such that + and([x_ExplicitVarSizeWithDummy[q5] != 8 /\ x_ExplicitVarSizeWithDummy[q6] != 8 -> + |x_ExplicitVarSizeWithDummy[q5] - x_ExplicitVarSizeWithDummy[q6]| >= 3 + | q5 : int(1..7), q6 : int(1..7), q6 > q5]), + and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 8 + | q1 : int(1..6)]), + and([x_ExplicitVarSizeWithDummy[q2] = 8 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 8 | q2 : int(1..6)]), + 3 <= sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 8) | q3 : int(1..7)]) + diff --git a/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_2_3-solution000001.solution b/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_2_3-solution000001.solution new file mode 100644 index 0000000000..f1495354fe --- /dev/null +++ b/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_2_3-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 4, 7} diff --git a/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_2_3.eprime b/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_2_3.eprime new file mode 100644 index 0000000000..0c4c4b73d9 --- /dev/null +++ b/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_2_3.eprime @@ -0,0 +1,30 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..7)] of int(1..8) +find x_ExplicitVarSizeWithMarker_Marker: int(0..7) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..7)] of int(1..7) +branching on [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy] +such that + and([x_ExplicitVarSizeWithDummy[q16] != 8 /\ x_ExplicitVarSizeWithDummy[q17] != 8 -> + |x_ExplicitVarSizeWithDummy[q16] - x_ExplicitVarSizeWithDummy[q17]| >= 3 + | q16 : int(1..7), q17 : int(1..7), q17 > q16]), + and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 8 + | q1 : int(1..6)]), + and([x_ExplicitVarSizeWithDummy[q2] = 8 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 8 | q2 : int(1..6)]), + 3 <= sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 8) | q3 : int(1..7)]), + and([q5 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q5] < x_ExplicitVarSizeWithMarker_Values[q5 + 1] + | q5 : int(1..6)]), + and([q6 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q6] = 1 | q6 : int(1..7)]), + 3 <= x_ExplicitVarSizeWithMarker_Marker, + and([q9 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithDummy[q11] != 8 /\ + x_ExplicitVarSizeWithDummy[q11] = x_ExplicitVarSizeWithMarker_Values[q9] + | q11 : int(1..7)]) + | q9 : int(1..7)]), + and([x_ExplicitVarSizeWithDummy[q13] != 8 -> + or([q15 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q15] = x_ExplicitVarSizeWithDummy[q13] + | q15 : int(1..7)]) + | q13 : int(1..7)]) + diff --git a/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_2_4-solution000001.solution b/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_2_4-solution000001.solution new file mode 100644 index 0000000000..f1495354fe --- /dev/null +++ b/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_2_4-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 4, 7} diff --git a/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_2_4.eprime b/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_2_4.eprime new file mode 100644 index 0000000000..dde41e36d9 --- /dev/null +++ b/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_2_4.eprime @@ -0,0 +1,31 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..7)] of int(1..8) +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..7)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..7)] of int(1..7) +branching on [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy] +such that + and([x_ExplicitVarSizeWithDummy[q18] != 8 /\ x_ExplicitVarSizeWithDummy[q19] != 8 -> + |x_ExplicitVarSizeWithDummy[q18] - x_ExplicitVarSizeWithDummy[q19]| >= 3 + | q18 : int(1..7), q19 : int(1..7), q19 > q18]), + and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 8 + | q1 : int(1..6)]), + and([x_ExplicitVarSizeWithDummy[q2] = 8 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 8 | q2 : int(1..6)]), + 3 <= sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 8) | q3 : int(1..7)]), + and([x_ExplicitVarSizeWithFlags_Flags[q5 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q5] < x_ExplicitVarSizeWithFlags_Values[q5 + 1] + | q5 : int(1..6)]), + and([x_ExplicitVarSizeWithFlags_Flags[q6] = false -> x_ExplicitVarSizeWithFlags_Values[q6] = 1 | q6 : int(1..7)]), + and([x_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q7] | q7 : int(1..6)]), + 3 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q8]) | q8 : int(1..7)]), + and([x_ExplicitVarSizeWithFlags_Flags[q11] -> + or([x_ExplicitVarSizeWithDummy[q13] != 8 /\ + x_ExplicitVarSizeWithDummy[q13] = x_ExplicitVarSizeWithFlags_Values[q11] + | q13 : int(1..7)]) + | q11 : int(1..7)]), + and([x_ExplicitVarSizeWithDummy[q15] != 8 -> + or([x_ExplicitVarSizeWithFlags_Flags[q17] /\ + x_ExplicitVarSizeWithFlags_Values[q17] = x_ExplicitVarSizeWithDummy[q15] + | q17 : int(1..7)]) + | q15 : int(1..7)]) + diff --git a/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_3_1-solution000001.solution b/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_3_1-solution000001.solution new file mode 100644 index 0000000000..f1495354fe --- /dev/null +++ b/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_3_1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 4, 7} diff --git a/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_3_1.eprime b/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_3_1.eprime new file mode 100644 index 0000000000..8a8eb99ad1 --- /dev/null +++ b/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_3_1.eprime @@ -0,0 +1,22 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..7) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..7)] of int(1..7) +find x_Occurrence: matrix indexed by [int(1..7)] of bool +branching on [x_Occurrence, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] +such that + and([q10 <= x_ExplicitVarSizeWithMarker_Marker /\ q11 <= x_ExplicitVarSizeWithMarker_Marker -> + |x_ExplicitVarSizeWithMarker_Values[q10] - x_ExplicitVarSizeWithMarker_Values[q11]| >= 3 + | q10 : int(1..7), q11 : int(1..7), q11 > q10]), + and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] + | q1 : int(1..6)]), + and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..7)]), + 3 <= x_ExplicitVarSizeWithMarker_Marker, + 3 <= sum([toInt(x_Occurrence[q4]) | q4 : int(1..7)]), + and([x_Occurrence[q5] -> + or([q7 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q7] = q5 | q7 : int(1..7)]) + | q5 : int(1..7)]), + and([q9 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q9]] + | q9 : int(1..7)]) + diff --git a/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_3_2-solution000001.solution b/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_3_2-solution000001.solution new file mode 100644 index 0000000000..f1495354fe --- /dev/null +++ b/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_3_2-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 4, 7} diff --git a/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_3_2.eprime b/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_3_2.eprime new file mode 100644 index 0000000000..dfacb2f87a --- /dev/null +++ b/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_3_2.eprime @@ -0,0 +1,30 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..7) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..7)] of int(1..7) +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..7)] of int(1..8) +branching on [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] +such that + and([q16 <= x_ExplicitVarSizeWithMarker_Marker /\ q17 <= x_ExplicitVarSizeWithMarker_Marker -> + |x_ExplicitVarSizeWithMarker_Values[q16] - x_ExplicitVarSizeWithMarker_Values[q17]| >= 3 + | q16 : int(1..7), q17 : int(1..7), q17 > q16]), + and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] + | q1 : int(1..6)]), + and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..7)]), + 3 <= x_ExplicitVarSizeWithMarker_Marker, + and([x_ExplicitVarSizeWithDummy[q4] < x_ExplicitVarSizeWithDummy[q4 + 1] \/ x_ExplicitVarSizeWithDummy[q4] = 8 + | q4 : int(1..6)]), + and([x_ExplicitVarSizeWithDummy[q5] = 8 -> x_ExplicitVarSizeWithDummy[q5 + 1] = 8 | q5 : int(1..6)]), + 3 <= sum([toInt(x_ExplicitVarSizeWithDummy[q6] != 8) | q6 : int(1..7)]), + and([x_ExplicitVarSizeWithDummy[q9] != 8 -> + or([q11 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q11] = x_ExplicitVarSizeWithDummy[q9] + | q11 : int(1..7)]) + | q9 : int(1..7)]), + and([q13 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithDummy[q15] != 8 /\ + x_ExplicitVarSizeWithDummy[q15] = x_ExplicitVarSizeWithMarker_Values[q13] + | q15 : int(1..7)]) + | q13 : int(1..7)]) + diff --git a/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_3_3-solution000001.solution b/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_3_3-solution000001.solution new file mode 100644 index 0000000000..f1495354fe --- /dev/null +++ b/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_3_3-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 4, 7} diff --git a/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_3_3.eprime b/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_3_3.eprime new file mode 100644 index 0000000000..a58004f8c5 --- /dev/null +++ b/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_3_3.eprime @@ -0,0 +1,15 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..7) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..7)] of int(1..7) +branching on [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] +such that + and([q4 <= x_ExplicitVarSizeWithMarker_Marker /\ q5 <= x_ExplicitVarSizeWithMarker_Marker -> + |x_ExplicitVarSizeWithMarker_Values[q4] - x_ExplicitVarSizeWithMarker_Values[q5]| >= 3 + | q4 : int(1..7), q5 : int(1..7), q5 > q4]), + and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] + | q1 : int(1..6)]), + and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..7)]), + 3 <= x_ExplicitVarSizeWithMarker_Marker + diff --git a/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_3_4-solution000001.solution b/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_3_4-solution000001.solution new file mode 100644 index 0000000000..f1495354fe --- /dev/null +++ b/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_3_4-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 4, 7} diff --git a/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_3_4.eprime b/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_3_4.eprime new file mode 100644 index 0000000000..0e6666e578 --- /dev/null +++ b/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_3_4.eprime @@ -0,0 +1,35 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..7) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..7)] of int(1..7) +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..7)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..7)] of int(1..7) +branching on + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithMarker_Marker, + x_ExplicitVarSizeWithMarker_Values] +such that + and([q17 <= x_ExplicitVarSizeWithMarker_Marker /\ q18 <= x_ExplicitVarSizeWithMarker_Marker -> + |x_ExplicitVarSizeWithMarker_Values[q17] - x_ExplicitVarSizeWithMarker_Values[q18]| >= 3 + | q17 : int(1..7), q18 : int(1..7), q18 > q17]), + and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] + | q1 : int(1..6)]), + and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..7)]), + 3 <= x_ExplicitVarSizeWithMarker_Marker, + and([x_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q4] < x_ExplicitVarSizeWithFlags_Values[q4 + 1] + | q4 : int(1..6)]), + and([x_ExplicitVarSizeWithFlags_Flags[q5] = false -> x_ExplicitVarSizeWithFlags_Values[q5] = 1 | q5 : int(1..7)]), + and([x_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q6] | q6 : int(1..6)]), + 3 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q7]) | q7 : int(1..7)]), + and([x_ExplicitVarSizeWithFlags_Flags[q10] -> + or([q12 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q12] = x_ExplicitVarSizeWithFlags_Values[q10] + | q12 : int(1..7)]) + | q10 : int(1..7)]), + and([q14 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithFlags_Flags[q16] /\ + x_ExplicitVarSizeWithFlags_Values[q16] = x_ExplicitVarSizeWithMarker_Values[q14] + | q16 : int(1..7)]) + | q14 : int(1..7)]) + diff --git a/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_4_1-solution000001.solution b/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_4_1-solution000001.solution new file mode 100644 index 0000000000..f1495354fe --- /dev/null +++ b/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_4_1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 4, 7} diff --git a/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_4_1.eprime b/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_4_1.eprime new file mode 100644 index 0000000000..65f611992a --- /dev/null +++ b/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_4_1.eprime @@ -0,0 +1,23 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..7)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..7)] of int(1..7) +find x_Occurrence: matrix indexed by [int(1..7)] of bool +branching on [x_Occurrence, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] +such that + and([x_ExplicitVarSizeWithFlags_Flags[q12] /\ x_ExplicitVarSizeWithFlags_Flags[q13] -> + |x_ExplicitVarSizeWithFlags_Values[q12] - x_ExplicitVarSizeWithFlags_Values[q13]| >= 3 + | q12 : int(1..7), q13 : int(1..7), q13 > q12]), + and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] + | q1 : int(1..6)]), + and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..7)]), + and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..6)]), + 3 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..7)]), + 3 <= sum([toInt(x_Occurrence[q6]) | q6 : int(1..7)]), + and([x_Occurrence[q7] -> + or([x_ExplicitVarSizeWithFlags_Flags[q9] /\ x_ExplicitVarSizeWithFlags_Values[q9] = q7 | q9 : int(1..7)]) + | q7 : int(1..7)]), + and([x_ExplicitVarSizeWithFlags_Flags[q11] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q11]] + | q11 : int(1..7)]) + diff --git a/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_4_2-solution000001.solution b/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_4_2-solution000001.solution new file mode 100644 index 0000000000..f1495354fe --- /dev/null +++ b/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_4_2-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 4, 7} diff --git a/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_4_2.eprime b/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_4_2.eprime new file mode 100644 index 0000000000..ff6745f307 --- /dev/null +++ b/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_4_2.eprime @@ -0,0 +1,31 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..7)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..7)] of int(1..7) +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..7)] of int(1..8) +branching on [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] +such that + and([x_ExplicitVarSizeWithFlags_Flags[q18] /\ x_ExplicitVarSizeWithFlags_Flags[q19] -> + |x_ExplicitVarSizeWithFlags_Values[q18] - x_ExplicitVarSizeWithFlags_Values[q19]| >= 3 + | q18 : int(1..7), q19 : int(1..7), q19 > q18]), + and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] + | q1 : int(1..6)]), + and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..7)]), + and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..6)]), + 3 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..7)]), + and([x_ExplicitVarSizeWithDummy[q6] < x_ExplicitVarSizeWithDummy[q6 + 1] \/ x_ExplicitVarSizeWithDummy[q6] = 8 + | q6 : int(1..6)]), + and([x_ExplicitVarSizeWithDummy[q7] = 8 -> x_ExplicitVarSizeWithDummy[q7 + 1] = 8 | q7 : int(1..6)]), + 3 <= sum([toInt(x_ExplicitVarSizeWithDummy[q8] != 8) | q8 : int(1..7)]), + and([x_ExplicitVarSizeWithDummy[q11] != 8 -> + or([x_ExplicitVarSizeWithFlags_Flags[q13] /\ + x_ExplicitVarSizeWithFlags_Values[q13] = x_ExplicitVarSizeWithDummy[q11] + | q13 : int(1..7)]) + | q11 : int(1..7)]), + and([x_ExplicitVarSizeWithFlags_Flags[q15] -> + or([x_ExplicitVarSizeWithDummy[q17] != 8 /\ + x_ExplicitVarSizeWithDummy[q17] = x_ExplicitVarSizeWithFlags_Values[q15] + | q17 : int(1..7)]) + | q15 : int(1..7)]) + diff --git a/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_4_3-solution000001.solution b/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_4_3-solution000001.solution new file mode 100644 index 0000000000..f1495354fe --- /dev/null +++ b/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_4_3-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 4, 7} diff --git a/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_4_3.eprime b/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_4_3.eprime new file mode 100644 index 0000000000..1d7cf573bd --- /dev/null +++ b/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_4_3.eprime @@ -0,0 +1,35 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..7)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..7)] of int(1..7) +find x_ExplicitVarSizeWithMarker_Marker: int(0..7) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..7)] of int(1..7) +branching on + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithFlags_Flags, + x_ExplicitVarSizeWithFlags_Values] +such that + and([x_ExplicitVarSizeWithFlags_Flags[q17] /\ x_ExplicitVarSizeWithFlags_Flags[q18] -> + |x_ExplicitVarSizeWithFlags_Values[q17] - x_ExplicitVarSizeWithFlags_Values[q18]| >= 3 + | q17 : int(1..7), q18 : int(1..7), q18 > q17]), + and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] + | q1 : int(1..6)]), + and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..7)]), + and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..6)]), + 3 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..7)]), + and([q6 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q6] < x_ExplicitVarSizeWithMarker_Values[q6 + 1] + | q6 : int(1..6)]), + and([q7 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q7] = 1 | q7 : int(1..7)]), + 3 <= x_ExplicitVarSizeWithMarker_Marker, + and([q10 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithFlags_Flags[q12] /\ + x_ExplicitVarSizeWithFlags_Values[q12] = x_ExplicitVarSizeWithMarker_Values[q10] + | q12 : int(1..7)]) + | q10 : int(1..7)]), + and([x_ExplicitVarSizeWithFlags_Flags[q14] -> + or([q16 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q16] = x_ExplicitVarSizeWithFlags_Values[q14] + | q16 : int(1..7)]) + | q14 : int(1..7)]) + diff --git a/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_4_4-solution000001.solution b/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_4_4-solution000001.solution new file mode 100644 index 0000000000..f1495354fe --- /dev/null +++ b/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_4_4-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 4, 7} diff --git a/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_4_4.eprime b/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_4_4.eprime new file mode 100644 index 0000000000..4d96a6fb8a --- /dev/null +++ b/tests/exhaustive/basic/powerSetComprehensionPat/expected/model_4_4.eprime @@ -0,0 +1,16 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..7)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..7)] of int(1..7) +branching on [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] +such that + and([x_ExplicitVarSizeWithFlags_Flags[q6] /\ x_ExplicitVarSizeWithFlags_Flags[q7] -> + |x_ExplicitVarSizeWithFlags_Values[q6] - x_ExplicitVarSizeWithFlags_Values[q7]| >= 3 + | q6 : int(1..7), q7 : int(1..7), q7 > q6]), + and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] + | q1 : int(1..6)]), + and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..7)]), + and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..6)]), + 3 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..7)]) + diff --git a/tests/exhaustive/basic/relation04_param/expected/model_1_1-param4-solution000001.solution b/tests/exhaustive/basic/relation04_param/expected/model_1_1-param4-solution000001.solution new file mode 100644 index 0000000000..547e6d2e7e --- /dev/null +++ b/tests/exhaustive/basic/relation04_param/expected/model_1_1-param4-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting r be relation((3, {2}, 6), (3, {3}, 9)) diff --git a/tests/exhaustive/basic/relation04_param/expected/model_1_1-param4.eprime-param b/tests/exhaustive/basic/relation04_param/expected/model_1_1-param4.eprime-param new file mode 100644 index 0000000000..87708d95a4 --- /dev/null +++ b/tests/exhaustive/basic/relation04_param/expected/model_1_1-param4.eprime-param @@ -0,0 +1,11 @@ +language ESSENCE' 1.0 + +letting a_RelationAsSetR6_ExplicitR6_1 be [3, 3; int(1..2)] +letting a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy be [[2; int(1)], [3; int(1)]; int(1..2)] +$ Visualisation for a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy +$ 2 +$ 3 + +letting a_RelationAsSetR6_ExplicitR6_3 be [6, 9; int(1..2)] +letting fin1 be 2 +letting fin2 be 1 diff --git a/tests/exhaustive/basic/relation04_param/expected/model_1_1.eprime b/tests/exhaustive/basic/relation04_param/expected/model_1_1.eprime new file mode 100644 index 0000000000..2ec04d204d --- /dev/null +++ b/tests/exhaustive/basic/relation04_param/expected/model_1_1.eprime @@ -0,0 +1,70 @@ +language ESSENCE' 1.0 + +given fin1: int +given fin2: int +given a_RelationAsSetR6_ExplicitR6_1: matrix indexed by [int(1..fin1)] of int(1..3) +given a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy: + matrix indexed by [int(1..fin1), int(1..fin2)] of int(2..4) +given a_RelationAsSetR6_ExplicitR6_3: matrix indexed by [int(1..fin1)] of int(4..10) +find r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Marker: int(0..84) +find r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_1: matrix indexed by [int(1..84)] of int(1..3) +find r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_2_Occurrence: + matrix indexed by [int(1..84), int(2..3)] of bool +find r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_3: matrix indexed by [int(1..84)] of int(4..10) +branching on + [r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Marker, r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_1, + r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_2_Occurrence, + r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_3] +such that + and([q9 <= r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Marker -> + or([and([a_RelationAsSetR6_ExplicitR6_1[q11] = r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_1[q9], + and([r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_2_Occurrence + [q9, a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q11, q13]] + | q13 : int(1..fin2), + a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q11, q13] != 4]) + /\ + and([r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_2_Occurrence[q9, q14] -> + or([a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q11, q16] = q14 + | q16 : int(1..fin2), + a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q11, q16] != 4]) + | q14 : int(2..3)]), + a_RelationAsSetR6_ExplicitR6_3[q11] = r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_3[q9]; + int(1..3)]) + | q11 : int(1..fin1)]) + | q9 : int(1..84)]), + and([or([q19 <= r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Marker /\ + and([r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_1[q19] = a_RelationAsSetR6_ExplicitR6_1[q17], + and([r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_2_Occurrence[q19, q20] -> + or([a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q17, q22] = q20 + | q22 : int(1..fin2), + a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q17, q22] != 4]) + | q20 : int(2..3)]) + /\ + and([r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_2_Occurrence + [q19, a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q17, q24]] + | q24 : int(1..fin2), + a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q17, q24] != 4]), + r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_3[q19] = a_RelationAsSetR6_ExplicitR6_3[q17]; + int(1..3)]) + | q19 : int(1..84)]) + | q17 : int(1..fin1)]), + r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Marker = fin1, + and([q1 + 1 <= r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Marker -> + flatten([[r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_1[q1]; int(1)], + [-toInt(r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_2_Occurrence[q1, q5]) | q5 : int(2..3)], + [r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_3[q1]; int(1)]; + int(1..3)]) + r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Marker -> + and([r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_1[q2] = 1, + and([r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_2_Occurrence[q2, q7] = false | q7 : int(2..3)]), + r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_3[q2] = 4; + int(1..3)]) + | q2 : int(1..84)]) + diff --git a/tests/exhaustive/basic/relation04_param/expected/model_1_2-param4-solution000001.solution b/tests/exhaustive/basic/relation04_param/expected/model_1_2-param4-solution000001.solution new file mode 100644 index 0000000000..547e6d2e7e --- /dev/null +++ b/tests/exhaustive/basic/relation04_param/expected/model_1_2-param4-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting r be relation((3, {2}, 6), (3, {3}, 9)) diff --git a/tests/exhaustive/basic/relation04_param/expected/model_1_2-param4.eprime-param b/tests/exhaustive/basic/relation04_param/expected/model_1_2-param4.eprime-param new file mode 100644 index 0000000000..87708d95a4 --- /dev/null +++ b/tests/exhaustive/basic/relation04_param/expected/model_1_2-param4.eprime-param @@ -0,0 +1,11 @@ +language ESSENCE' 1.0 + +letting a_RelationAsSetR6_ExplicitR6_1 be [3, 3; int(1..2)] +letting a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy be [[2; int(1)], [3; int(1)]; int(1..2)] +$ Visualisation for a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy +$ 2 +$ 3 + +letting a_RelationAsSetR6_ExplicitR6_3 be [6, 9; int(1..2)] +letting fin1 be 2 +letting fin2 be 1 diff --git a/tests/exhaustive/basic/relation04_param/expected/model_1_2.eprime b/tests/exhaustive/basic/relation04_param/expected/model_1_2.eprime new file mode 100644 index 0000000000..2a255134f0 --- /dev/null +++ b/tests/exhaustive/basic/relation04_param/expected/model_1_2.eprime @@ -0,0 +1,152 @@ +language ESSENCE' 1.0 + +given fin1: int +given fin2: int +given a_RelationAsSetR6_ExplicitR6_1: matrix indexed by [int(1..fin1)] of int(1..3) +given a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy: + matrix indexed by [int(1..fin1), int(1..fin2)] of int(2..4) +given a_RelationAsSetR6_ExplicitR6_3: matrix indexed by [int(1..fin1)] of int(4..10) +find r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Marker: int(0..84) +find r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_1: matrix indexed by [int(1..84)] of int(1..3) +find r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_2_Occurrence: + matrix indexed by [int(1..84), int(2..3)] of bool +find r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_3: matrix indexed by [int(1..84)] of int(4..10) +find r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Marker: int(0..84) +find r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_1: matrix indexed by [int(1..84)] of int(1..3) +find r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy: + matrix indexed by [int(1..84), int(1..2)] of int(2..4) +find r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_3: matrix indexed by [int(1..84)] of int(4..10) +branching on + [r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Marker, r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_1, + r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy, + r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_3, r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Marker, + r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_1, + r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_2_Occurrence, + r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_3] +such that + and([q36 <= r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Marker -> + or([and([a_RelationAsSetR6_ExplicitR6_1[q38] = r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_1[q36], + and([r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_2_Occurrence + [q36, a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q38, q40]] + | q40 : int(1..fin2), + a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q38, q40] != 4]) + /\ + and([r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_2_Occurrence[q36, q41] -> + or([a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q38, q43] = q41 + | q43 : int(1..fin2), + a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q38, q43] != 4]) + | q41 : int(2..3)]), + a_RelationAsSetR6_ExplicitR6_3[q38] = r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_3[q36]; + int(1..3)]) + | q38 : int(1..fin1)]) + | q36 : int(1..84)]), + and([or([q46 <= r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Marker /\ + and([r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_1[q46] = a_RelationAsSetR6_ExplicitR6_1[q44], + and([r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_2_Occurrence[q46, q47] -> + or([a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q44, q49] = q47 + | q49 : int(1..fin2), + a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q44, q49] != 4]) + | q47 : int(2..3)]) + /\ + and([r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_2_Occurrence + [q46, a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q44, q51]] + | q51 : int(1..fin2), + a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q44, q51] != 4]), + r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_3[q46] = a_RelationAsSetR6_ExplicitR6_3[q44]; + int(1..3)]) + | q46 : int(1..84)]) + | q44 : int(1..fin1)]), + r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Marker = fin1, + and([q1 + 1 <= r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Marker -> + flatten([[r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_1[q1]; int(1)], + [-toInt(r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_2_Occurrence[q1, q5]) | q5 : int(2..3)], + [r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_3[q1]; int(1)]; + int(1..3)]) + r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Marker -> + and([r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_1[q2] = 1, + and([r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_2_Occurrence[q2, q7] = false | q7 : int(2..3)]), + r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_3[q2] = 4; + int(1..3)]) + | q2 : int(1..84)]), + and([q8 + 1 <= r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Marker -> + flatten([[r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_1[q8]; int(1)], + [r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q8, q15] + | q15 : int(1..2)], + [r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_3[q8]; int(1)]; + int(1..3)]) + r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Marker -> + and([r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_1[q9] = 1, + and([r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q9, q17] = 2 + | q17 : int(1..2)]), + r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_3[q9] = 4; + int(1..3)]) + | q9 : int(1..84)]), + and([q10 <= r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Marker -> + r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q10, 1] < + r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q10, 2] + \/ r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q10, 1] = 4 + | q10 : int(1..84)]), + and([q10 <= r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Marker -> + (r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q10, 1] = 4 -> + r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q10, 2] = 4) + | q10 : int(1..84)]), + and([q19 <= r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Marker -> + or([q21 <= r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Marker /\ + and([r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_1[q21] = + r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_1[q19], + and([r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_2_Occurrence[q21, q22] -> + or([r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q19, q24] != + 4 + /\ + r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q19, q24] = + q22 | q24 : int(1..2)]) + | q22 : int(2..3)]) + /\ + and([r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q19, q26] != 4 -> + r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_2_Occurrence + [q21, + r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q19, q26]] + | q26 : int(1..2)]), + r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_3[q21] = + r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_3[q19]; + int(1..3)]) + | q21 : int(1..84)]) + | q19 : int(1..84)]), + and([q27 <= r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Marker -> + or([q29 <= r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Marker /\ + and([r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_1[q29] = + r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_1[q27], + and([r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q29, q31] != 4 -> + r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_2_Occurrence + [q27, + r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q29, q31]] + | q31 : int(1..2)]) + /\ + and([r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_2_Occurrence[q27, q32] -> + or([r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q29, q34] != + 4 + /\ + r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q29, q34] = + q32 | q34 : int(1..2)]) + | q32 : int(2..3)]), + r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_3[q29] = + r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_3[q27]; + int(1..3)]) + | q29 : int(1..84)]) + | q27 : int(1..84)]), + r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Marker = r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Marker + diff --git a/tests/exhaustive/basic/relation04_param/expected/model_1_3-param4-solution000001.solution b/tests/exhaustive/basic/relation04_param/expected/model_1_3-param4-solution000001.solution new file mode 100644 index 0000000000..547e6d2e7e --- /dev/null +++ b/tests/exhaustive/basic/relation04_param/expected/model_1_3-param4-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting r be relation((3, {2}, 6), (3, {3}, 9)) diff --git a/tests/exhaustive/basic/relation04_param/expected/model_1_3-param4.eprime-param b/tests/exhaustive/basic/relation04_param/expected/model_1_3-param4.eprime-param new file mode 100644 index 0000000000..87708d95a4 --- /dev/null +++ b/tests/exhaustive/basic/relation04_param/expected/model_1_3-param4.eprime-param @@ -0,0 +1,11 @@ +language ESSENCE' 1.0 + +letting a_RelationAsSetR6_ExplicitR6_1 be [3, 3; int(1..2)] +letting a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy be [[2; int(1)], [3; int(1)]; int(1..2)] +$ Visualisation for a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy +$ 2 +$ 3 + +letting a_RelationAsSetR6_ExplicitR6_3 be [6, 9; int(1..2)] +letting fin1 be 2 +letting fin2 be 1 diff --git a/tests/exhaustive/basic/relation04_param/expected/model_1_3.eprime.orig b/tests/exhaustive/basic/relation04_param/expected/model_1_3.eprime.orig deleted file mode 100644 index d0d64b442c..0000000000 --- a/tests/exhaustive/basic/relation04_param/expected/model_1_3.eprime.orig +++ /dev/null @@ -1,176 +0,0 @@ -language ESSENCE' 1.0 - -given fin1: int -given fin2: int -given a_RelationAsSetR6_ExplicitR6_1: matrix indexed by [int(1..fin1)] of int(1..3) -given a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy: - matrix indexed by [int(1..fin1), int(1..fin2)] of int(2..4) -given a_RelationAsSetR6_ExplicitR6_3: matrix indexed by [int(1..fin1)] of int(4..10) -find r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Marker: int(0..84) -find r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_1: matrix indexed by [int(1..84)] of int(1..3) -find r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_2_Occurrence: - matrix indexed by [int(1..84), int(2..3)] of bool -find r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_3: matrix indexed by [int(1..84)] of int(4..10) -find r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Marker: int(0..84) -find r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_1: matrix indexed by [int(1..84)] of int(1..3) -find r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Marker: - matrix indexed by [int(1..84)] of int(0..2) -find r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Values: - matrix indexed by [int(1..84), int(1..2)] of int(2..3) -find r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_3: matrix indexed by [int(1..84)] of int(4..10) -branching on - [r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Marker, r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_1, - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Marker, - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Values, - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_3, r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Marker, - r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_1, - r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_2_Occurrence, - r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_3] -such that - and([q35 <= r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Marker -> - or([and([a_RelationAsSetR6_ExplicitR6_1[q37] = r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_1[q35], - and([r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_2_Occurrence - [q35, a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q37, q39]] - | q39 : int(1..fin2), - a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q37, q39] != 4]) - /\ - and([r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_2_Occurrence[q35, q40] -> - or([a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q37, q42] = q40 - | q42 : int(1..fin2), - a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q37, q42] != 4]) - | q40 : int(2..3)]), - a_RelationAsSetR6_ExplicitR6_3[q37] = r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_3[q35]; - int(1..3)]) - | q37 : int(1..fin1)]) - | q35 : int(1..84)]), - and([or([q45 <= r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Marker /\ - and([r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_1[q45] = a_RelationAsSetR6_ExplicitR6_1[q43], - and([r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_2_Occurrence[q45, q46] -> - or([a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q43, q48] = q46 - | q48 : int(1..fin2), - a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q43, q48] != 4]) - | q46 : int(2..3)]) - /\ - and([r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_2_Occurrence - [q45, a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q43, q50]] - | q50 : int(1..fin2), - a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q43, q50] != 4]), - r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_3[q45] = a_RelationAsSetR6_ExplicitR6_3[q43]; - int(1..3)]) - | q45 : int(1..84)]) - | q43 : int(1..fin1)]), - r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Marker = fin1, - and([q1 + 1 <= r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Marker -> - flatten([[r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_1[q1]; int(1)], - [-toInt(r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_2_Occurrence[q1, q5]) | q5 : int(2..3)], - [r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_3[q1]; int(1)]; - int(1..3)]) - r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Marker -> - and([r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_1[q2] = 1, - and([r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_2_Occurrence[q2, q7] = false | q7 : int(2..3)]), - r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_3[q2] = 4; - int(1..3)]) - | q2 : int(1..84)]), - and([q8 + 1 <= r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Marker -> - flatten([[r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_1[q8]; int(1)], - flatten([[r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Marker[q8]; - int(1)], - [r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Values - [q8, q14] - | q14 : int(1..2)]; - int(1..2)]), - [r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_3[q8]; int(1)]; - int(1..3)]) - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Marker -> - and([r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_1[q9] = 1, - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Marker[q9] = 0 /\ - and([r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Values[q9, q16] = 2 - | q16 : int(1..2)]), - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_3[q9] = 4; - int(1..3)]) - | q9 : int(1..84)]), - and([q10 <= r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Marker -> - (2 <= r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Marker[q10] -> - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Values[q10, 1] < - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Values[q10, 2]) - | q10 : int(1..84)]), - and([q10 <= r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Marker -> - and([q12 > r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Marker[q10] -> - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Values[q10, q12] = 2 - | q12 : int(1..2)]) - | q10 : int(1..84)]), - and([q18 <= r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Marker -> - or([q20 <= r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Marker /\ - and([r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_1[q20] = - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_1[q18], - and([r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_2_Occurrence[q20, q21] -> - or([q23 <= - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Marker[q18] - /\ - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Values - [q18, q23] - = q21 - | q23 : int(1..2)]) - | q21 : int(2..3)]) - /\ - and([q25 <= - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Marker[q18] - -> - r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_2_Occurrence - [q20, - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Values - [q18, q25]] - | q25 : int(1..2)]), - r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_3[q20] = - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_3[q18]; - int(1..3)]) - | q20 : int(1..84)]) - | q18 : int(1..84)]), - and([q26 <= r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Marker -> - or([q28 <= r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Marker /\ - and([r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_1[q28] = - r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_1[q26], - and([q30 <= - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Marker[q28] - -> - r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_2_Occurrence - [q26, - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Values - [q28, q30]] - | q30 : int(1..2)]) - /\ - and([r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_2_Occurrence[q26, q31] -> - or([q33 <= - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Marker[q28] - /\ - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Values - [q28, q33] - = q31 - | q33 : int(1..2)]) - | q31 : int(2..3)]), - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_3[q28] = - r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_3[q26]; - int(1..3)]) - | q28 : int(1..84)]) - | q26 : int(1..84)]), - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Marker = r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Marker - diff --git a/tests/exhaustive/basic/relation04_param/expected/model_1_4-param4-solution000001.solution b/tests/exhaustive/basic/relation04_param/expected/model_1_4-param4-solution000001.solution new file mode 100644 index 0000000000..547e6d2e7e --- /dev/null +++ b/tests/exhaustive/basic/relation04_param/expected/model_1_4-param4-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting r be relation((3, {2}, 6), (3, {3}, 9)) diff --git a/tests/exhaustive/basic/relation04_param/expected/model_1_4-param4.eprime-param b/tests/exhaustive/basic/relation04_param/expected/model_1_4-param4.eprime-param new file mode 100644 index 0000000000..87708d95a4 --- /dev/null +++ b/tests/exhaustive/basic/relation04_param/expected/model_1_4-param4.eprime-param @@ -0,0 +1,11 @@ +language ESSENCE' 1.0 + +letting a_RelationAsSetR6_ExplicitR6_1 be [3, 3; int(1..2)] +letting a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy be [[2; int(1)], [3; int(1)]; int(1..2)] +$ Visualisation for a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy +$ 2 +$ 3 + +letting a_RelationAsSetR6_ExplicitR6_3 be [6, 9; int(1..2)] +letting fin1 be 2 +letting fin2 be 1 diff --git a/tests/exhaustive/basic/relation04_param/expected/model_1_4.eprime b/tests/exhaustive/basic/relation04_param/expected/model_1_4.eprime new file mode 100644 index 0000000000..b140b9955b --- /dev/null +++ b/tests/exhaustive/basic/relation04_param/expected/model_1_4.eprime @@ -0,0 +1,184 @@ +language ESSENCE' 1.0 + +given fin1: int +given fin2: int +given a_RelationAsSetR6_ExplicitR6_1: matrix indexed by [int(1..fin1)] of int(1..3) +given a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy: + matrix indexed by [int(1..fin1), int(1..fin2)] of int(2..4) +given a_RelationAsSetR6_ExplicitR6_3: matrix indexed by [int(1..fin1)] of int(4..10) +find r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Marker: int(0..84) +find r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_1: matrix indexed by [int(1..84)] of int(1..3) +find r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_2_Occurrence: + matrix indexed by [int(1..84), int(2..3)] of bool +find r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_3: matrix indexed by [int(1..84)] of int(4..10) +find r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Marker: int(0..84) +find r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_1: matrix indexed by [int(1..84)] of int(1..3) +find r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Flags: + matrix indexed by [int(1..84), int(1..2)] of bool +find r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Values: + matrix indexed by [int(1..84), int(1..2)] of int(2..3) +find r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_3: matrix indexed by [int(1..84)] of int(4..10) +branching on + [r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Marker, r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_1, + r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Flags, + r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Values, + r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_3, r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Marker, + r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_1, + r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_2_Occurrence, + r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_3] +such that + and([q38 <= r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Marker -> + or([and([a_RelationAsSetR6_ExplicitR6_1[q40] = r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_1[q38], + and([r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_2_Occurrence + [q38, a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q40, q42]] + | q42 : int(1..fin2), + a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q40, q42] != 4]) + /\ + and([r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_2_Occurrence[q38, q43] -> + or([a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q40, q45] = q43 + | q45 : int(1..fin2), + a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q40, q45] != 4]) + | q43 : int(2..3)]), + a_RelationAsSetR6_ExplicitR6_3[q40] = r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_3[q38]; + int(1..3)]) + | q40 : int(1..fin1)]) + | q38 : int(1..84)]), + and([or([q48 <= r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Marker /\ + and([r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_1[q48] = a_RelationAsSetR6_ExplicitR6_1[q46], + and([r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_2_Occurrence[q48, q49] -> + or([a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q46, q51] = q49 + | q51 : int(1..fin2), + a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q46, q51] != 4]) + | q49 : int(2..3)]) + /\ + and([r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_2_Occurrence + [q48, a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q46, q53]] + | q53 : int(1..fin2), + a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q46, q53] != 4]), + r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_3[q48] = a_RelationAsSetR6_ExplicitR6_3[q46]; + int(1..3)]) + | q48 : int(1..84)]) + | q46 : int(1..fin1)]), + r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Marker = fin1, + and([q1 + 1 <= r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Marker -> + flatten([[r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_1[q1]; int(1)], + [-toInt(r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_2_Occurrence[q1, q5]) | q5 : int(2..3)], + [r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_3[q1]; int(1)]; + int(1..3)]) + r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Marker -> + and([r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_1[q2] = 1, + and([r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_2_Occurrence[q2, q7] = false | q7 : int(2..3)]), + r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_3[q2] = 4; + int(1..3)]) + | q2 : int(1..84)]), + and([q8 + 1 <= r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Marker -> + flatten([[r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_1[q8]; int(1)], + flatten([flatten([[-toInt(r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Flags + [q8, q16]); + int(1)], + [r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Values + [q8, q16]; + int(1)]; + int(1..2)]) + | q16 : int(1..2)]), + [r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_3[q8]; int(1)]; + int(1..3)]) + r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Marker -> + and([r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_1[q9] = 1, + and([r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Flags[q9, q18] = + false + | q18 : int(1..2)]) + /\ + and([r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Values[q9, q19] = 2 + | q19 : int(1..2)]), + r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_3[q9] = 4; + int(1..3)]) + | q9 : int(1..84)]), + and([q10 <= r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Marker -> + (r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Flags[q10, 2] -> + r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Values[q10, 1] < + r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Values[q10, 2]) + | q10 : int(1..84)]), + and([q10 <= r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Marker -> + and([r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Flags[q10, q12] = false -> + r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Values[q10, q12] = 2 + | q12 : int(1..2)]) + | q10 : int(1..84)]), + and([q10 <= r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Marker -> + (r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Flags[q10, 2] -> + r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Flags[q10, 1]) + | q10 : int(1..84)]), + and([q21 <= r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Marker -> + or([q23 <= r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Marker /\ + and([r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_1[q23] = + r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_1[q21], + and([r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_2_Occurrence[q23, q24] -> + or([r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Flags + [q21, q26] + /\ + r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Values + [q21, q26] + = q24 + | q26 : int(1..2)]) + | q24 : int(2..3)]) + /\ + and([r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Flags[q21, q28] + -> + r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_2_Occurrence + [q23, + r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Values + [q21, q28]] + | q28 : int(1..2)]), + r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_3[q23] = + r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_3[q21]; + int(1..3)]) + | q23 : int(1..84)]) + | q21 : int(1..84)]), + and([q29 <= r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Marker -> + or([q31 <= r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Marker /\ + and([r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_1[q31] = + r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_1[q29], + and([r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Flags[q31, q33] + -> + r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_2_Occurrence + [q29, + r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Values + [q31, q33]] + | q33 : int(1..2)]) + /\ + and([r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_2_Occurrence[q29, q34] -> + or([r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Flags + [q31, q36] + /\ + r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Values + [q31, q36] + = q34 + | q36 : int(1..2)]) + | q34 : int(2..3)]), + r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_3[q31] = + r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_3[q29]; + int(1..3)]) + | q31 : int(1..84)]) + | q29 : int(1..84)]), + r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Marker = r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Marker + diff --git a/tests/exhaustive/basic/relation04_param/expected/model_2_1-param4-solution000001.solution b/tests/exhaustive/basic/relation04_param/expected/model_2_1-param4-solution000001.solution new file mode 100644 index 0000000000..547e6d2e7e --- /dev/null +++ b/tests/exhaustive/basic/relation04_param/expected/model_2_1-param4-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting r be relation((3, {2}, 6), (3, {3}, 9)) diff --git a/tests/exhaustive/basic/relation04_param/expected/model_2_1-param4.eprime-param b/tests/exhaustive/basic/relation04_param/expected/model_2_1-param4.eprime-param new file mode 100644 index 0000000000..87708d95a4 --- /dev/null +++ b/tests/exhaustive/basic/relation04_param/expected/model_2_1-param4.eprime-param @@ -0,0 +1,11 @@ +language ESSENCE' 1.0 + +letting a_RelationAsSetR6_ExplicitR6_1 be [3, 3; int(1..2)] +letting a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy be [[2; int(1)], [3; int(1)]; int(1..2)] +$ Visualisation for a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy +$ 2 +$ 3 + +letting a_RelationAsSetR6_ExplicitR6_3 be [6, 9; int(1..2)] +letting fin1 be 2 +letting fin2 be 1 diff --git a/tests/exhaustive/basic/relation04_param/expected/model_2_1.eprime b/tests/exhaustive/basic/relation04_param/expected/model_2_1.eprime new file mode 100644 index 0000000000..ca4ced56b2 --- /dev/null +++ b/tests/exhaustive/basic/relation04_param/expected/model_2_1.eprime @@ -0,0 +1,164 @@ +language ESSENCE' 1.0 + +given fin1: int +given fin2: int +given a_RelationAsSetR6_ExplicitR6_1: matrix indexed by [int(1..fin1)] of int(1..3) +given a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy: + matrix indexed by [int(1..fin1), int(1..fin2)] of int(2..4) +given a_RelationAsSetR6_ExplicitR6_3: matrix indexed by [int(1..fin1)] of int(4..10) +find r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Marker: int(0..84) +find r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_1: matrix indexed by [int(1..84)] of int(1..3) +find r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy: + matrix indexed by [int(1..84), int(1..2)] of int(2..4) +find r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_3: matrix indexed by [int(1..84)] of int(4..10) +find r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Marker: int(0..84) +find r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_1: matrix indexed by [int(1..84)] of int(1..3) +find r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_2_Occurrence: + matrix indexed by [int(1..84), int(2..3)] of bool +find r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_3: matrix indexed by [int(1..84)] of int(4..10) +branching on + [r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Marker, r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_1, + r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_2_Occurrence, + r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_3, r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Marker, + r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_1, + r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy, + r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_3] +such that + and([q36 <= r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Marker -> + or([and([a_RelationAsSetR6_ExplicitR6_1[q38] = r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_1[q36], + and([or([r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q36, q42] != + 4 + /\ + r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q36, q42] = + a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q38, q40] + | q42 : int(1..2)]) + | q40 : int(1..fin2), + a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q38, q40] != 4]) + /\ + and([r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q36, q44] != 4 -> + or([a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q38, q46] = + r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q36, q44] + | q46 : int(1..fin2), + a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q38, q46] != 4]) + | q44 : int(1..2)]), + a_RelationAsSetR6_ExplicitR6_3[q38] = r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_3[q36]; + int(1..3)]) + | q38 : int(1..fin1)]) + | q36 : int(1..84)]), + and([or([q49 <= r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Marker /\ + and([r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_1[q49] = a_RelationAsSetR6_ExplicitR6_1[q47], + and([r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q49, q51] != 4 -> + or([a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q47, q53] = + r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q49, q51] + | q53 : int(1..fin2), + a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q47, q53] != 4]) + | q51 : int(1..2)]) + /\ + and([or([r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q49, q57] != + 4 + /\ + r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q49, q57] = + a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q47, q55] + | q57 : int(1..2)]) + | q55 : int(1..fin2), + a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q47, q55] != 4]), + r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_3[q49] = a_RelationAsSetR6_ExplicitR6_3[q47]; + int(1..3)]) + | q49 : int(1..84)]) + | q47 : int(1..fin1)]), + r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Marker = fin1, + and([q1 + 1 <= r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Marker -> + flatten([[r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_1[q1]; int(1)], + [r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q1, q8] + | q8 : int(1..2)], + [r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_3[q1]; int(1)]; + int(1..3)]) + r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Marker -> + and([r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_1[q2] = 1, + and([r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q2, q10] = 2 + | q10 : int(1..2)]), + r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_3[q2] = 4; + int(1..3)]) + | q2 : int(1..84)]), + and([q3 <= r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Marker -> + r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q3, 1] < + r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q3, 2] + \/ r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q3, 1] = 4 + | q3 : int(1..84)]), + and([q3 <= r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Marker -> + (r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q3, 1] = 4 -> + r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q3, 2] = 4) + | q3 : int(1..84)]), + and([q11 + 1 <= r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Marker -> + flatten([[r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_1[q11]; int(1)], + [-toInt(r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_2_Occurrence[q11, q15]) + | q15 : int(2..3)], + [r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_3[q11]; int(1)]; + int(1..3)]) + r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Marker -> + and([r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_1[q12] = 1, + and([r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_2_Occurrence[q12, q17] = false + | q17 : int(2..3)]), + r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_3[q12] = 4; + int(1..3)]) + | q12 : int(1..84)]), + and([q19 <= r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Marker -> + or([q21 <= r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Marker /\ + and([r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_1[q21] = + r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_1[q19], + and([r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q21, q23] != 4 -> + r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_2_Occurrence + [q19, + r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q21, q23]] + | q23 : int(1..2)]) + /\ + and([r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_2_Occurrence[q19, q24] -> + or([r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q21, q26] != + 4 + /\ + r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q21, q26] = + q24 | q26 : int(1..2)]) + | q24 : int(2..3)]), + r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_3[q21] = + r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_3[q19]; + int(1..3)]) + | q21 : int(1..84)]) + | q19 : int(1..84)]), + and([q27 <= r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Marker -> + or([q29 <= r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Marker /\ + and([r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_1[q29] = + r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_1[q27], + and([r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_2_Occurrence[q29, q30] -> + or([r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q27, q32] != + 4 + /\ + r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q27, q32] = + q30 | q32 : int(1..2)]) + | q30 : int(2..3)]) + /\ + and([r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q27, q34] != 4 -> + r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_2_Occurrence + [q29, + r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q27, q34]] + | q34 : int(1..2)]), + r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_3[q29] = + r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_3[q27]; + int(1..3)]) + | q29 : int(1..84)]) + | q27 : int(1..84)]), + r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Marker = r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Marker + diff --git a/tests/exhaustive/basic/relation04_param/expected/model_2_2-param4-solution000001.solution b/tests/exhaustive/basic/relation04_param/expected/model_2_2-param4-solution000001.solution new file mode 100644 index 0000000000..547e6d2e7e --- /dev/null +++ b/tests/exhaustive/basic/relation04_param/expected/model_2_2-param4-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting r be relation((3, {2}, 6), (3, {3}, 9)) diff --git a/tests/exhaustive/basic/relation04_param/expected/model_2_2-param4.eprime-param b/tests/exhaustive/basic/relation04_param/expected/model_2_2-param4.eprime-param new file mode 100644 index 0000000000..87708d95a4 --- /dev/null +++ b/tests/exhaustive/basic/relation04_param/expected/model_2_2-param4.eprime-param @@ -0,0 +1,11 @@ +language ESSENCE' 1.0 + +letting a_RelationAsSetR6_ExplicitR6_1 be [3, 3; int(1..2)] +letting a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy be [[2; int(1)], [3; int(1)]; int(1..2)] +$ Visualisation for a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy +$ 2 +$ 3 + +letting a_RelationAsSetR6_ExplicitR6_3 be [6, 9; int(1..2)] +letting fin1 be 2 +letting fin2 be 1 diff --git a/tests/exhaustive/basic/relation04_param/expected/model_2_2.eprime b/tests/exhaustive/basic/relation04_param/expected/model_2_2.eprime new file mode 100644 index 0000000000..bda11c6f36 --- /dev/null +++ b/tests/exhaustive/basic/relation04_param/expected/model_2_2.eprime @@ -0,0 +1,91 @@ +language ESSENCE' 1.0 + +given fin1: int +given fin2: int +given a_RelationAsSetR6_ExplicitR6_1: matrix indexed by [int(1..fin1)] of int(1..3) +given a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy: + matrix indexed by [int(1..fin1), int(1..fin2)] of int(2..4) +given a_RelationAsSetR6_ExplicitR6_3: matrix indexed by [int(1..fin1)] of int(4..10) +find r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Marker: int(0..84) +find r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_1: matrix indexed by [int(1..84)] of int(1..3) +find r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy: + matrix indexed by [int(1..84), int(1..2)] of int(2..4) +find r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_3: matrix indexed by [int(1..84)] of int(4..10) +branching on + [r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Marker, r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_1, + r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy, + r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_3] +such that + and([q12 <= r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Marker -> + or([and([a_RelationAsSetR6_ExplicitR6_1[q14] = r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_1[q12], + and([or([r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q12, q18] != + 4 + /\ + r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q12, q18] = + a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q14, q16] + | q18 : int(1..2)]) + | q16 : int(1..fin2), + a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q14, q16] != 4]) + /\ + and([r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q12, q20] != 4 -> + or([a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q14, q22] = + r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q12, q20] + | q22 : int(1..fin2), + a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q14, q22] != 4]) + | q20 : int(1..2)]), + a_RelationAsSetR6_ExplicitR6_3[q14] = r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_3[q12]; + int(1..3)]) + | q14 : int(1..fin1)]) + | q12 : int(1..84)]), + and([or([q25 <= r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Marker /\ + and([r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_1[q25] = a_RelationAsSetR6_ExplicitR6_1[q23], + and([r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q25, q27] != 4 -> + or([a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q23, q29] = + r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q25, q27] + | q29 : int(1..fin2), + a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q23, q29] != 4]) + | q27 : int(1..2)]) + /\ + and([or([r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q25, q33] != + 4 + /\ + r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q25, q33] = + a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q23, q31] + | q33 : int(1..2)]) + | q31 : int(1..fin2), + a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q23, q31] != 4]), + r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_3[q25] = a_RelationAsSetR6_ExplicitR6_3[q23]; + int(1..3)]) + | q25 : int(1..84)]) + | q23 : int(1..fin1)]), + r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Marker = fin1, + and([q1 + 1 <= r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Marker -> + flatten([[r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_1[q1]; int(1)], + [r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q1, q8] + | q8 : int(1..2)], + [r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_3[q1]; int(1)]; + int(1..3)]) + r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Marker -> + and([r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_1[q2] = 1, + and([r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q2, q10] = 2 + | q10 : int(1..2)]), + r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_3[q2] = 4; + int(1..3)]) + | q2 : int(1..84)]), + and([q3 <= r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Marker -> + r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q3, 1] < + r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q3, 2] + \/ r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q3, 1] = 4 + | q3 : int(1..84)]), + and([q3 <= r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Marker -> + (r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q3, 1] = 4 -> + r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q3, 2] = 4) + | q3 : int(1..84)]) + diff --git a/tests/exhaustive/basic/relation04_param/expected/model_2_3-param4-solution000001.solution b/tests/exhaustive/basic/relation04_param/expected/model_2_3-param4-solution000001.solution new file mode 100644 index 0000000000..547e6d2e7e --- /dev/null +++ b/tests/exhaustive/basic/relation04_param/expected/model_2_3-param4-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting r be relation((3, {2}, 6), (3, {3}, 9)) diff --git a/tests/exhaustive/basic/relation04_param/expected/model_2_3-param4.eprime-param b/tests/exhaustive/basic/relation04_param/expected/model_2_3-param4.eprime-param new file mode 100644 index 0000000000..87708d95a4 --- /dev/null +++ b/tests/exhaustive/basic/relation04_param/expected/model_2_3-param4.eprime-param @@ -0,0 +1,11 @@ +language ESSENCE' 1.0 + +letting a_RelationAsSetR6_ExplicitR6_1 be [3, 3; int(1..2)] +letting a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy be [[2; int(1)], [3; int(1)]; int(1..2)] +$ Visualisation for a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy +$ 2 +$ 3 + +letting a_RelationAsSetR6_ExplicitR6_3 be [6, 9; int(1..2)] +letting fin1 be 2 +letting fin2 be 1 diff --git a/tests/exhaustive/basic/relation04_param/expected/model_2_3.eprime.orig b/tests/exhaustive/basic/relation04_param/expected/model_2_3.eprime.orig deleted file mode 100644 index a73716ba56..0000000000 --- a/tests/exhaustive/basic/relation04_param/expected/model_2_3.eprime.orig +++ /dev/null @@ -1,204 +0,0 @@ -language ESSENCE' 1.0 - -given fin1: int -given fin2: int -given a_RelationAsSetR6_ExplicitR6_1: matrix indexed by [int(1..fin1)] of int(1..3) -given a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy: - matrix indexed by [int(1..fin1), int(1..fin2)] of int(2..4) -given a_RelationAsSetR6_ExplicitR6_3: matrix indexed by [int(1..fin1)] of int(4..10) -find r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Marker: int(0..84) -find r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_1: matrix indexed by [int(1..84)] of int(1..3) -find r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy: - matrix indexed by [int(1..84), int(1..2)] of int(2..4) -find r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_3: matrix indexed by [int(1..84)] of int(4..10) -find r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Marker: int(0..84) -find r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_1: matrix indexed by [int(1..84)] of int(1..3) -find r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Marker: - matrix indexed by [int(1..84)] of int(0..2) -find r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Values: - matrix indexed by [int(1..84), int(1..2)] of int(2..3) -find r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_3: matrix indexed by [int(1..84)] of int(4..10) -branching on - [r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Marker, r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_1, - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Marker, - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Values, - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_3, r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Marker, - r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_1, - r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy, - r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_3] -such that - and([q44 <= r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Marker -> - or([and([a_RelationAsSetR6_ExplicitR6_1[q46] = r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_1[q44], - and([or([r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q44, q50] != - 4 - /\ - r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q44, q50] = - a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q46, q48] - | q50 : int(1..2)]) - | q48 : int(1..fin2), - a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q46, q48] != 4]) - /\ - and([r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q44, q52] != 4 -> - or([a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q46, q54] = - r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q44, q52] - | q54 : int(1..fin2), - a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q46, q54] != 4]) - | q52 : int(1..2)]), - a_RelationAsSetR6_ExplicitR6_3[q46] = r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_3[q44]; - int(1..3)]) - | q46 : int(1..fin1)]) - | q44 : int(1..84)]), - and([or([q57 <= r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Marker /\ - and([r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_1[q57] = a_RelationAsSetR6_ExplicitR6_1[q55], - and([r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q57, q59] != 4 -> - or([a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q55, q61] = - r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q57, q59] - | q61 : int(1..fin2), - a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q55, q61] != 4]) - | q59 : int(1..2)]) - /\ - and([or([r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q57, q65] != - 4 - /\ - r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q57, q65] = - a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q55, q63] - | q65 : int(1..2)]) - | q63 : int(1..fin2), - a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q55, q63] != 4]), - r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_3[q57] = a_RelationAsSetR6_ExplicitR6_3[q55]; - int(1..3)]) - | q57 : int(1..84)]) - | q55 : int(1..fin1)]), - r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Marker = fin1, - and([q1 + 1 <= r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Marker -> - flatten([[r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_1[q1]; int(1)], - [r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q1, q8] - | q8 : int(1..2)], - [r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_3[q1]; int(1)]; - int(1..3)]) - r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Marker -> - and([r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_1[q2] = 1, - and([r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q2, q10] = 2 - | q10 : int(1..2)]), - r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_3[q2] = 4; - int(1..3)]) - | q2 : int(1..84)]), - and([q3 <= r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Marker -> - r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q3, 1] < - r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q3, 2] - \/ r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q3, 1] = 4 - | q3 : int(1..84)]), - and([q3 <= r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Marker -> - (r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q3, 1] = 4 -> - r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q3, 2] = 4) - | q3 : int(1..84)]), - and([q11 + 1 <= r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Marker -> - flatten([[r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_1[q11]; int(1)], - flatten([[r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Marker - [q11]; - int(1)], - [r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Values - [q11, q17] - | q17 : int(1..2)]; - int(1..2)]), - [r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_3[q11]; int(1)]; - int(1..3)]) - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Marker -> - and([r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_1[q12] = 1, - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Marker[q12] = 0 /\ - and([r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Values[q12, q19] = 2 - | q19 : int(1..2)]), - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_3[q12] = 4; - int(1..3)]) - | q12 : int(1..84)]), - and([q13 <= r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Marker -> - (2 <= r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Marker[q13] -> - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Values[q13, 1] < - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Values[q13, 2]) - | q13 : int(1..84)]), - and([q13 <= r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Marker -> - and([q15 > r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Marker[q13] -> - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Values[q13, q15] = 2 - | q15 : int(1..2)]) - | q13 : int(1..84)]), - and([q21 <= r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Marker -> - or([q23 <= r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Marker /\ - and([r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_1[q23] = - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_1[q21], - and([r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q23, q25] != 4 -> - or([q27 <= - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Marker[q21] - /\ - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Values - [q21, q27] - = r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q23, q25] - | q27 : int(1..2)]) - | q25 : int(1..2)]) - /\ - and([q29 <= - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Marker[q21] - -> - or([r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q23, q31] != - 4 - /\ - r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q23, q31] = - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Values - [q21, q29] - | q31 : int(1..2)]) - | q29 : int(1..2)]), - r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_3[q23] = - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_3[q21]; - int(1..3)]) - | q23 : int(1..84)]) - | q21 : int(1..84)]), - and([q32 <= r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Marker -> - or([q34 <= r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Marker /\ - and([r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_1[q34] = - r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_1[q32], - and([q36 <= - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Marker[q34] - -> - or([r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q32, q38] != - 4 - /\ - r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q32, q38] = - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Values - [q34, q36] - | q38 : int(1..2)]) - | q36 : int(1..2)]) - /\ - and([r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q32, q40] != 4 -> - or([q42 <= - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Marker[q34] - /\ - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Values - [q34, q42] - = r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q32, q40] - | q42 : int(1..2)]) - | q40 : int(1..2)]), - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_3[q34] = - r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_3[q32]; - int(1..3)]) - | q34 : int(1..84)]) - | q32 : int(1..84)]), - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Marker = r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Marker - diff --git a/tests/exhaustive/basic/relation04_param/expected/model_2_4-param4-solution000001.solution b/tests/exhaustive/basic/relation04_param/expected/model_2_4-param4-solution000001.solution new file mode 100644 index 0000000000..547e6d2e7e --- /dev/null +++ b/tests/exhaustive/basic/relation04_param/expected/model_2_4-param4-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting r be relation((3, {2}, 6), (3, {3}, 9)) diff --git a/tests/exhaustive/basic/relation04_param/expected/model_2_4-param4.eprime-param b/tests/exhaustive/basic/relation04_param/expected/model_2_4-param4.eprime-param new file mode 100644 index 0000000000..87708d95a4 --- /dev/null +++ b/tests/exhaustive/basic/relation04_param/expected/model_2_4-param4.eprime-param @@ -0,0 +1,11 @@ +language ESSENCE' 1.0 + +letting a_RelationAsSetR6_ExplicitR6_1 be [3, 3; int(1..2)] +letting a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy be [[2; int(1)], [3; int(1)]; int(1..2)] +$ Visualisation for a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy +$ 2 +$ 3 + +letting a_RelationAsSetR6_ExplicitR6_3 be [6, 9; int(1..2)] +letting fin1 be 2 +letting fin2 be 1 diff --git a/tests/exhaustive/basic/relation04_param/expected/model_2_4.eprime b/tests/exhaustive/basic/relation04_param/expected/model_2_4.eprime new file mode 100644 index 0000000000..9f13f2adc7 --- /dev/null +++ b/tests/exhaustive/basic/relation04_param/expected/model_2_4.eprime @@ -0,0 +1,211 @@ +language ESSENCE' 1.0 + +given fin1: int +given fin2: int +given a_RelationAsSetR6_ExplicitR6_1: matrix indexed by [int(1..fin1)] of int(1..3) +given a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy: + matrix indexed by [int(1..fin1), int(1..fin2)] of int(2..4) +given a_RelationAsSetR6_ExplicitR6_3: matrix indexed by [int(1..fin1)] of int(4..10) +find r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Marker: int(0..84) +find r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_1: matrix indexed by [int(1..84)] of int(1..3) +find r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy: + matrix indexed by [int(1..84), int(1..2)] of int(2..4) +find r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_3: matrix indexed by [int(1..84)] of int(4..10) +find r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Marker: int(0..84) +find r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_1: matrix indexed by [int(1..84)] of int(1..3) +find r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Flags: + matrix indexed by [int(1..84), int(1..2)] of bool +find r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Values: + matrix indexed by [int(1..84), int(1..2)] of int(2..3) +find r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_3: matrix indexed by [int(1..84)] of int(4..10) +branching on + [r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Marker, r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_1, + r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Flags, + r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Values, + r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_3, r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Marker, + r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_1, + r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy, + r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_3] +such that + and([q47 <= r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Marker -> + or([and([a_RelationAsSetR6_ExplicitR6_1[q49] = r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_1[q47], + and([or([r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q47, q53] != + 4 + /\ + r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q47, q53] = + a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q49, q51] + | q53 : int(1..2)]) + | q51 : int(1..fin2), + a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q49, q51] != 4]) + /\ + and([r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q47, q55] != 4 -> + or([a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q49, q57] = + r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q47, q55] + | q57 : int(1..fin2), + a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q49, q57] != 4]) + | q55 : int(1..2)]), + a_RelationAsSetR6_ExplicitR6_3[q49] = r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_3[q47]; + int(1..3)]) + | q49 : int(1..fin1)]) + | q47 : int(1..84)]), + and([or([q60 <= r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Marker /\ + and([r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_1[q60] = a_RelationAsSetR6_ExplicitR6_1[q58], + and([r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q60, q62] != 4 -> + or([a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q58, q64] = + r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q60, q62] + | q64 : int(1..fin2), + a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q58, q64] != 4]) + | q62 : int(1..2)]) + /\ + and([or([r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q60, q68] != + 4 + /\ + r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q60, q68] = + a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q58, q66] + | q68 : int(1..2)]) + | q66 : int(1..fin2), + a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q58, q66] != 4]), + r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_3[q60] = a_RelationAsSetR6_ExplicitR6_3[q58]; + int(1..3)]) + | q60 : int(1..84)]) + | q58 : int(1..fin1)]), + r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Marker = fin1, + and([q1 + 1 <= r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Marker -> + flatten([[r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_1[q1]; int(1)], + [r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q1, q8] + | q8 : int(1..2)], + [r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_3[q1]; int(1)]; + int(1..3)]) + r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Marker -> + and([r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_1[q2] = 1, + and([r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q2, q10] = 2 + | q10 : int(1..2)]), + r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_3[q2] = 4; + int(1..3)]) + | q2 : int(1..84)]), + and([q3 <= r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Marker -> + r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q3, 1] < + r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q3, 2] + \/ r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q3, 1] = 4 + | q3 : int(1..84)]), + and([q3 <= r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Marker -> + (r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q3, 1] = 4 -> + r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q3, 2] = 4) + | q3 : int(1..84)]), + and([q11 + 1 <= r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Marker -> + flatten([[r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_1[q11]; int(1)], + flatten([flatten([[-toInt(r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Flags + [q11, q19]); + int(1)], + [r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Values + [q11, q19]; + int(1)]; + int(1..2)]) + | q19 : int(1..2)]), + [r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_3[q11]; int(1)]; + int(1..3)]) + r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Marker -> + and([r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_1[q12] = 1, + and([r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Flags[q12, q21] = + false + | q21 : int(1..2)]) + /\ + and([r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Values[q12, q22] = 2 + | q22 : int(1..2)]), + r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_3[q12] = 4; + int(1..3)]) + | q12 : int(1..84)]), + and([q13 <= r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Marker -> + (r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Flags[q13, 2] -> + r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Values[q13, 1] < + r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Values[q13, 2]) + | q13 : int(1..84)]), + and([q13 <= r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Marker -> + and([r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Flags[q13, q15] = false -> + r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Values[q13, q15] = 2 + | q15 : int(1..2)]) + | q13 : int(1..84)]), + and([q13 <= r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Marker -> + (r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Flags[q13, 2] -> + r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Flags[q13, 1]) + | q13 : int(1..84)]), + and([q24 <= r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Marker -> + or([q26 <= r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Marker /\ + and([r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_1[q26] = + r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_1[q24], + and([r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q26, q28] != 4 -> + or([r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Flags + [q24, q30] + /\ + r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Values + [q24, q30] + = r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q26, q28] + | q30 : int(1..2)]) + | q28 : int(1..2)]) + /\ + and([r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Flags[q24, q32] + -> + or([r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q26, q34] != + 4 + /\ + r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q26, q34] = + r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Values + [q24, q32] + | q34 : int(1..2)]) + | q32 : int(1..2)]), + r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_3[q26] = + r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_3[q24]; + int(1..3)]) + | q26 : int(1..84)]) + | q24 : int(1..84)]), + and([q35 <= r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Marker -> + or([q37 <= r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Marker /\ + and([r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_1[q37] = + r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_1[q35], + and([r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Flags[q37, q39] + -> + or([r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q35, q41] != + 4 + /\ + r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q35, q41] = + r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Values + [q37, q39] + | q41 : int(1..2)]) + | q39 : int(1..2)]) + /\ + and([r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q35, q43] != 4 -> + or([r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Flags + [q37, q45] + /\ + r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Values + [q37, q45] + = r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q35, q43] + | q45 : int(1..2)]) + | q43 : int(1..2)]), + r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_3[q37] = + r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_3[q35]; + int(1..3)]) + | q37 : int(1..84)]) + | q35 : int(1..84)]), + r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Marker = r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Marker + diff --git a/tests/exhaustive/basic/relation04_param/expected/model_3_1-param4-solution000001.solution b/tests/exhaustive/basic/relation04_param/expected/model_3_1-param4-solution000001.solution new file mode 100644 index 0000000000..547e6d2e7e --- /dev/null +++ b/tests/exhaustive/basic/relation04_param/expected/model_3_1-param4-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting r be relation((3, {2}, 6), (3, {3}, 9)) diff --git a/tests/exhaustive/basic/relation04_param/expected/model_3_1-param4.eprime-param b/tests/exhaustive/basic/relation04_param/expected/model_3_1-param4.eprime-param new file mode 100644 index 0000000000..87708d95a4 --- /dev/null +++ b/tests/exhaustive/basic/relation04_param/expected/model_3_1-param4.eprime-param @@ -0,0 +1,11 @@ +language ESSENCE' 1.0 + +letting a_RelationAsSetR6_ExplicitR6_1 be [3, 3; int(1..2)] +letting a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy be [[2; int(1)], [3; int(1)]; int(1..2)] +$ Visualisation for a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy +$ 2 +$ 3 + +letting a_RelationAsSetR6_ExplicitR6_3 be [6, 9; int(1..2)] +letting fin1 be 2 +letting fin2 be 1 diff --git a/tests/exhaustive/basic/relation04_param/expected/model_3_1.eprime.orig b/tests/exhaustive/basic/relation04_param/expected/model_3_1.eprime.orig deleted file mode 100644 index e8bce5f5e1..0000000000 --- a/tests/exhaustive/basic/relation04_param/expected/model_3_1.eprime.orig +++ /dev/null @@ -1,196 +0,0 @@ -language ESSENCE' 1.0 - -given fin1: int -given fin2: int -given a_RelationAsSetR6_ExplicitR6_1: matrix indexed by [int(1..fin1)] of int(1..3) -given a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy: - matrix indexed by [int(1..fin1), int(1..fin2)] of int(2..4) -given a_RelationAsSetR6_ExplicitR6_3: matrix indexed by [int(1..fin1)] of int(4..10) -find r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Marker: int(0..84) -find r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_1: matrix indexed by [int(1..84)] of int(1..3) -find r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Marker: - matrix indexed by [int(1..84)] of int(0..2) -find r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Values: - matrix indexed by [int(1..84), int(1..2)] of int(2..3) -find r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_3: matrix indexed by [int(1..84)] of int(4..10) -find r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Marker: int(0..84) -find r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_1: matrix indexed by [int(1..84)] of int(1..3) -find r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_2_Occurrence: - matrix indexed by [int(1..84), int(2..3)] of bool -find r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_3: matrix indexed by [int(1..84)] of int(4..10) -branching on - [r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Marker, r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_1, - r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_2_Occurrence, - r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_3, r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Marker, - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_1, - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Marker, - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Values, - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_3] -such that - and([q35 <= r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Marker -> - or([and([a_RelationAsSetR6_ExplicitR6_1[q37] = r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_1[q35], - and([or([q41 <= - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Marker[q35] - /\ - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Values - [q35, q41] - = a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q37, q39] - | q41 : int(1..2)]) - | q39 : int(1..fin2), - a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q37, q39] != 4]) - /\ - and([q43 <= - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Marker[q35] - -> - or([a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q37, q45] = - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Values - [q35, q43] - | q45 : int(1..fin2), - a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q37, q45] != 4]) - | q43 : int(1..2)]), - a_RelationAsSetR6_ExplicitR6_3[q37] = r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_3[q35]; - int(1..3)]) - | q37 : int(1..fin1)]) - | q35 : int(1..84)]), - and([or([q48 <= r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Marker /\ - and([r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_1[q48] = a_RelationAsSetR6_ExplicitR6_1[q46], - and([q50 <= - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Marker[q48] - -> - or([a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q46, q52] = - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Values - [q48, q50] - | q52 : int(1..fin2), - a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q46, q52] != 4]) - | q50 : int(1..2)]) - /\ - and([or([q56 <= - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Marker[q48] - /\ - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Values - [q48, q56] - = a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q46, q54] - | q56 : int(1..2)]) - | q54 : int(1..fin2), - a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q46, q54] != 4]), - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_3[q48] = a_RelationAsSetR6_ExplicitR6_3[q46]; - int(1..3)]) - | q48 : int(1..84)]) - | q46 : int(1..fin1)]), - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Marker = fin1, - and([q1 + 1 <= r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Marker -> - flatten([[r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_1[q1]; int(1)], - flatten([[r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Marker[q1]; - int(1)], - [r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Values - [q1, q7] - | q7 : int(1..2)]; - int(1..2)]), - [r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_3[q1]; int(1)]; - int(1..3)]) - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Marker -> - and([r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_1[q2] = 1, - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Marker[q2] = 0 /\ - and([r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Values[q2, q9] = 2 - | q9 : int(1..2)]), - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_3[q2] = 4; - int(1..3)]) - | q2 : int(1..84)]), - and([q3 <= r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Marker -> - (2 <= r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Marker[q3] -> - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Values[q3, 1] < - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Values[q3, 2]) - | q3 : int(1..84)]), - and([q3 <= r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Marker -> - and([q5 > r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Marker[q3] -> - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Values[q3, q5] = 2 - | q5 : int(1..2)]) - | q3 : int(1..84)]), - and([q10 + 1 <= r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Marker -> - flatten([[r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_1[q10]; int(1)], - [-toInt(r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_2_Occurrence[q10, q14]) - | q14 : int(2..3)], - [r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_3[q10]; int(1)]; - int(1..3)]) - r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Marker -> - and([r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_1[q11] = 1, - and([r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_2_Occurrence[q11, q16] = false - | q16 : int(2..3)]), - r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_3[q11] = 4; - int(1..3)]) - | q11 : int(1..84)]), - and([q18 <= r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Marker -> - or([q20 <= r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Marker /\ - and([r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_1[q20] = - r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_1[q18], - and([q22 <= - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Marker[q20] - -> - r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_2_Occurrence - [q18, - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Values - [q20, q22]] - | q22 : int(1..2)]) - /\ - and([r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_2_Occurrence[q18, q23] -> - or([q25 <= - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Marker[q20] - /\ - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Values - [q20, q25] - = q23 - | q25 : int(1..2)]) - | q23 : int(2..3)]), - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_3[q20] = - r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_3[q18]; - int(1..3)]) - | q20 : int(1..84)]) - | q18 : int(1..84)]), - and([q26 <= r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Marker -> - or([q28 <= r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Marker /\ - and([r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_1[q28] = - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_1[q26], - and([r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_2_Occurrence[q28, q29] -> - or([q31 <= - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Marker[q26] - /\ - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Values - [q26, q31] - = q29 - | q31 : int(1..2)]) - | q29 : int(2..3)]) - /\ - and([q33 <= - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Marker[q26] - -> - r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_2_Occurrence - [q28, - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Values - [q26, q33]] - | q33 : int(1..2)]), - r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_3[q28] = - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_3[q26]; - int(1..3)]) - | q28 : int(1..84)]) - | q26 : int(1..84)]), - r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Marker = r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Marker - diff --git a/tests/exhaustive/basic/relation04_param/expected/model_3_2-param4-solution000001.solution b/tests/exhaustive/basic/relation04_param/expected/model_3_2-param4-solution000001.solution new file mode 100644 index 0000000000..547e6d2e7e --- /dev/null +++ b/tests/exhaustive/basic/relation04_param/expected/model_3_2-param4-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting r be relation((3, {2}, 6), (3, {3}, 9)) diff --git a/tests/exhaustive/basic/relation04_param/expected/model_3_2-param4.eprime-param b/tests/exhaustive/basic/relation04_param/expected/model_3_2-param4.eprime-param new file mode 100644 index 0000000000..87708d95a4 --- /dev/null +++ b/tests/exhaustive/basic/relation04_param/expected/model_3_2-param4.eprime-param @@ -0,0 +1,11 @@ +language ESSENCE' 1.0 + +letting a_RelationAsSetR6_ExplicitR6_1 be [3, 3; int(1..2)] +letting a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy be [[2; int(1)], [3; int(1)]; int(1..2)] +$ Visualisation for a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy +$ 2 +$ 3 + +letting a_RelationAsSetR6_ExplicitR6_3 be [6, 9; int(1..2)] +letting fin1 be 2 +letting fin2 be 1 diff --git a/tests/exhaustive/basic/relation04_param/expected/model_3_2.eprime.orig b/tests/exhaustive/basic/relation04_param/expected/model_3_2.eprime.orig deleted file mode 100644 index a248f3fbe6..0000000000 --- a/tests/exhaustive/basic/relation04_param/expected/model_3_2.eprime.orig +++ /dev/null @@ -1,211 +0,0 @@ -language ESSENCE' 1.0 - -given fin1: int -given fin2: int -given a_RelationAsSetR6_ExplicitR6_1: matrix indexed by [int(1..fin1)] of int(1..3) -given a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy: - matrix indexed by [int(1..fin1), int(1..fin2)] of int(2..4) -given a_RelationAsSetR6_ExplicitR6_3: matrix indexed by [int(1..fin1)] of int(4..10) -find r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Marker: int(0..84) -find r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_1: matrix indexed by [int(1..84)] of int(1..3) -find r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Marker: - matrix indexed by [int(1..84)] of int(0..2) -find r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Values: - matrix indexed by [int(1..84), int(1..2)] of int(2..3) -find r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_3: matrix indexed by [int(1..84)] of int(4..10) -find r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Marker: int(0..84) -find r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_1: matrix indexed by [int(1..84)] of int(1..3) -find r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy: - matrix indexed by [int(1..84), int(1..2)] of int(2..4) -find r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_3: matrix indexed by [int(1..84)] of int(4..10) -branching on - [r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Marker, r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_1, - r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy, - r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_3, r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Marker, - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_1, - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Marker, - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Values, - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_3] -such that - and([q44 <= r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Marker -> - or([and([a_RelationAsSetR6_ExplicitR6_1[q46] = r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_1[q44], - and([or([q50 <= - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Marker[q44] - /\ - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Values - [q44, q50] - = a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q46, q48] - | q50 : int(1..2)]) - | q48 : int(1..fin2), - a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q46, q48] != 4]) - /\ - and([q52 <= - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Marker[q44] - -> - or([a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q46, q54] = - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Values - [q44, q52] - | q54 : int(1..fin2), - a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q46, q54] != 4]) - | q52 : int(1..2)]), - a_RelationAsSetR6_ExplicitR6_3[q46] = r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_3[q44]; - int(1..3)]) - | q46 : int(1..fin1)]) - | q44 : int(1..84)]), - and([or([q57 <= r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Marker /\ - and([r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_1[q57] = a_RelationAsSetR6_ExplicitR6_1[q55], - and([q59 <= - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Marker[q57] - -> - or([a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q55, q61] = - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Values - [q57, q59] - | q61 : int(1..fin2), - a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q55, q61] != 4]) - | q59 : int(1..2)]) - /\ - and([or([q65 <= - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Marker[q57] - /\ - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Values - [q57, q65] - = a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q55, q63] - | q65 : int(1..2)]) - | q63 : int(1..fin2), - a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q55, q63] != 4]), - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_3[q57] = a_RelationAsSetR6_ExplicitR6_3[q55]; - int(1..3)]) - | q57 : int(1..84)]) - | q55 : int(1..fin1)]), - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Marker = fin1, - and([q1 + 1 <= r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Marker -> - flatten([[r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_1[q1]; int(1)], - flatten([[r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Marker[q1]; - int(1)], - [r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Values - [q1, q7] - | q7 : int(1..2)]; - int(1..2)]), - [r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_3[q1]; int(1)]; - int(1..3)]) - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Marker -> - and([r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_1[q2] = 1, - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Marker[q2] = 0 /\ - and([r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Values[q2, q9] = 2 - | q9 : int(1..2)]), - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_3[q2] = 4; - int(1..3)]) - | q2 : int(1..84)]), - and([q3 <= r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Marker -> - (2 <= r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Marker[q3] -> - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Values[q3, 1] < - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Values[q3, 2]) - | q3 : int(1..84)]), - and([q3 <= r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Marker -> - and([q5 > r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Marker[q3] -> - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Values[q3, q5] = 2 - | q5 : int(1..2)]) - | q3 : int(1..84)]), - and([q10 + 1 <= r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Marker -> - flatten([[r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_1[q10]; int(1)], - [r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q10, q17] - | q17 : int(1..2)], - [r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_3[q10]; int(1)]; - int(1..3)]) - r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Marker -> - and([r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_1[q11] = 1, - and([r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q11, q19] = 2 - | q19 : int(1..2)]), - r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_3[q11] = 4; - int(1..3)]) - | q11 : int(1..84)]), - and([q12 <= r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Marker -> - r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q12, 1] < - r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q12, 2] - \/ r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q12, 1] = 4 - | q12 : int(1..84)]), - and([q12 <= r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Marker -> - (r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q12, 1] = 4 -> - r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q12, 2] = 4) - | q12 : int(1..84)]), - and([q21 <= r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Marker -> - or([q23 <= r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Marker /\ - and([r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_1[q23] = - r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_1[q21], - and([q25 <= - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Marker[q23] - -> - or([r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q21, q27] != - 4 - /\ - r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q21, q27] = - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Values - [q23, q25] - | q27 : int(1..2)]) - | q25 : int(1..2)]) - /\ - and([r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q21, q29] != 4 -> - or([q31 <= - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Marker[q23] - /\ - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Values - [q23, q31] - = r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q21, q29] - | q31 : int(1..2)]) - | q29 : int(1..2)]), - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_3[q23] = - r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_3[q21]; - int(1..3)]) - | q23 : int(1..84)]) - | q21 : int(1..84)]), - and([q32 <= r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Marker -> - or([q34 <= r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Marker /\ - and([r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_1[q34] = - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_1[q32], - and([r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q34, q36] != 4 -> - or([q38 <= - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Marker[q32] - /\ - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Values - [q32, q38] - = r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q34, q36] - | q38 : int(1..2)]) - | q36 : int(1..2)]) - /\ - and([q40 <= - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Marker[q32] - -> - or([r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q34, q42] != - 4 - /\ - r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q34, q42] = - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Values - [q32, q40] - | q42 : int(1..2)]) - | q40 : int(1..2)]), - r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_3[q34] = - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_3[q32]; - int(1..3)]) - | q34 : int(1..84)]) - | q32 : int(1..84)]), - r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Marker = r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Marker - diff --git a/tests/exhaustive/basic/relation04_param/expected/model_3_3-param4-solution000001.solution b/tests/exhaustive/basic/relation04_param/expected/model_3_3-param4-solution000001.solution new file mode 100644 index 0000000000..547e6d2e7e --- /dev/null +++ b/tests/exhaustive/basic/relation04_param/expected/model_3_3-param4-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting r be relation((3, {2}, 6), (3, {3}, 9)) diff --git a/tests/exhaustive/basic/relation04_param/expected/model_3_3-param4.eprime-param b/tests/exhaustive/basic/relation04_param/expected/model_3_3-param4.eprime-param new file mode 100644 index 0000000000..87708d95a4 --- /dev/null +++ b/tests/exhaustive/basic/relation04_param/expected/model_3_3-param4.eprime-param @@ -0,0 +1,11 @@ +language ESSENCE' 1.0 + +letting a_RelationAsSetR6_ExplicitR6_1 be [3, 3; int(1..2)] +letting a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy be [[2; int(1)], [3; int(1)]; int(1..2)] +$ Visualisation for a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy +$ 2 +$ 3 + +letting a_RelationAsSetR6_ExplicitR6_3 be [6, 9; int(1..2)] +letting fin1 be 2 +letting fin2 be 1 diff --git a/tests/exhaustive/basic/relation04_param/expected/model_3_3.eprime.orig b/tests/exhaustive/basic/relation04_param/expected/model_3_3.eprime.orig deleted file mode 100644 index 54108a9243..0000000000 --- a/tests/exhaustive/basic/relation04_param/expected/model_3_3.eprime.orig +++ /dev/null @@ -1,113 +0,0 @@ -language ESSENCE' 1.0 - -given fin1: int -given fin2: int -given a_RelationAsSetR6_ExplicitR6_1: matrix indexed by [int(1..fin1)] of int(1..3) -given a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy: - matrix indexed by [int(1..fin1), int(1..fin2)] of int(2..4) -given a_RelationAsSetR6_ExplicitR6_3: matrix indexed by [int(1..fin1)] of int(4..10) -find r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Marker: int(0..84) -find r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_1: matrix indexed by [int(1..84)] of int(1..3) -find r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Marker: - matrix indexed by [int(1..84)] of int(0..2) -find r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Values: - matrix indexed by [int(1..84), int(1..2)] of int(2..3) -find r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_3: matrix indexed by [int(1..84)] of int(4..10) -branching on - [r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Marker, r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_1, - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Marker, - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Values, - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_3] -such that - and([q11 <= r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Marker -> - or([and([a_RelationAsSetR6_ExplicitR6_1[q13] = r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_1[q11], - and([or([q17 <= - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Marker[q11] - /\ - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Values - [q11, q17] - = a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q13, q15] - | q17 : int(1..2)]) - | q15 : int(1..fin2), - a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q13, q15] != 4]) - /\ - and([q19 <= - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Marker[q11] - -> - or([a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q13, q21] = - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Values - [q11, q19] - | q21 : int(1..fin2), - a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q13, q21] != 4]) - | q19 : int(1..2)]), - a_RelationAsSetR6_ExplicitR6_3[q13] = r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_3[q11]; - int(1..3)]) - | q13 : int(1..fin1)]) - | q11 : int(1..84)]), - and([or([q24 <= r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Marker /\ - and([r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_1[q24] = a_RelationAsSetR6_ExplicitR6_1[q22], - and([q26 <= - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Marker[q24] - -> - or([a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q22, q28] = - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Values - [q24, q26] - | q28 : int(1..fin2), - a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q22, q28] != 4]) - | q26 : int(1..2)]) - /\ - and([or([q32 <= - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Marker[q24] - /\ - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Values - [q24, q32] - = a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q22, q30] - | q32 : int(1..2)]) - | q30 : int(1..fin2), - a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q22, q30] != 4]), - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_3[q24] = a_RelationAsSetR6_ExplicitR6_3[q22]; - int(1..3)]) - | q24 : int(1..84)]) - | q22 : int(1..fin1)]), - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Marker = fin1, - and([q1 + 1 <= r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Marker -> - flatten([[r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_1[q1]; int(1)], - flatten([[r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Marker[q1]; - int(1)], - [r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Values - [q1, q7] - | q7 : int(1..2)]; - int(1..2)]), - [r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_3[q1]; int(1)]; - int(1..3)]) - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Marker -> - and([r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_1[q2] = 1, - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Marker[q2] = 0 /\ - and([r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Values[q2, q9] = 2 - | q9 : int(1..2)]), - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_3[q2] = 4; - int(1..3)]) - | q2 : int(1..84)]), - and([q3 <= r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Marker -> - (2 <= r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Marker[q3] -> - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Values[q3, 1] < - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Values[q3, 2]) - | q3 : int(1..84)]), - and([q3 <= r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Marker -> - and([q5 > r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Marker[q3] -> - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Values[q3, q5] = 2 - | q5 : int(1..2)]) - | q3 : int(1..84)]) - diff --git a/tests/exhaustive/basic/relation04_param/expected/model_3_4-param4-solution000001.solution b/tests/exhaustive/basic/relation04_param/expected/model_3_4-param4-solution000001.solution new file mode 100644 index 0000000000..547e6d2e7e --- /dev/null +++ b/tests/exhaustive/basic/relation04_param/expected/model_3_4-param4-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting r be relation((3, {2}, 6), (3, {3}, 9)) diff --git a/tests/exhaustive/basic/relation04_param/expected/model_3_4-param4.eprime-param b/tests/exhaustive/basic/relation04_param/expected/model_3_4-param4.eprime-param new file mode 100644 index 0000000000..87708d95a4 --- /dev/null +++ b/tests/exhaustive/basic/relation04_param/expected/model_3_4-param4.eprime-param @@ -0,0 +1,11 @@ +language ESSENCE' 1.0 + +letting a_RelationAsSetR6_ExplicitR6_1 be [3, 3; int(1..2)] +letting a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy be [[2; int(1)], [3; int(1)]; int(1..2)] +$ Visualisation for a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy +$ 2 +$ 3 + +letting a_RelationAsSetR6_ExplicitR6_3 be [6, 9; int(1..2)] +letting fin1 be 2 +letting fin2 be 1 diff --git a/tests/exhaustive/basic/relation04_param/expected/model_3_4.eprime.orig b/tests/exhaustive/basic/relation04_param/expected/model_3_4.eprime.orig deleted file mode 100644 index fecc76d420..0000000000 --- a/tests/exhaustive/basic/relation04_param/expected/model_3_4.eprime.orig +++ /dev/null @@ -1,245 +0,0 @@ -language ESSENCE' 1.0 - -given fin1: int -given fin2: int -given a_RelationAsSetR6_ExplicitR6_1: matrix indexed by [int(1..fin1)] of int(1..3) -given a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy: - matrix indexed by [int(1..fin1), int(1..fin2)] of int(2..4) -given a_RelationAsSetR6_ExplicitR6_3: matrix indexed by [int(1..fin1)] of int(4..10) -find r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Marker: int(0..84) -find r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_1: matrix indexed by [int(1..84)] of int(1..3) -find r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Marker: - matrix indexed by [int(1..84)] of int(0..2) -find r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Values: - matrix indexed by [int(1..84), int(1..2)] of int(2..3) -find r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_3: matrix indexed by [int(1..84)] of int(4..10) -find r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Marker: int(0..84) -find r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_1: matrix indexed by [int(1..84)] of int(1..3) -find r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Flags: - matrix indexed by [int(1..84), int(1..2)] of bool -find r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Values: - matrix indexed by [int(1..84), int(1..2)] of int(2..3) -find r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_3: matrix indexed by [int(1..84)] of int(4..10) -branching on - [r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Marker, r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_1, - r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Flags, - r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Values, - r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_3, r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Marker, - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_1, - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Marker, - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Values, - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_3] -such that - and([q46 <= r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Marker -> - or([and([a_RelationAsSetR6_ExplicitR6_1[q48] = r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_1[q46], - and([or([q52 <= - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Marker[q46] - /\ - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Values - [q46, q52] - = a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q48, q50] - | q52 : int(1..2)]) - | q50 : int(1..fin2), - a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q48, q50] != 4]) - /\ - and([q54 <= - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Marker[q46] - -> - or([a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q48, q56] = - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Values - [q46, q54] - | q56 : int(1..fin2), - a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q48, q56] != 4]) - | q54 : int(1..2)]), - a_RelationAsSetR6_ExplicitR6_3[q48] = r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_3[q46]; - int(1..3)]) - | q48 : int(1..fin1)]) - | q46 : int(1..84)]), - and([or([q59 <= r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Marker /\ - and([r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_1[q59] = a_RelationAsSetR6_ExplicitR6_1[q57], - and([q61 <= - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Marker[q59] - -> - or([a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q57, q63] = - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Values - [q59, q61] - | q63 : int(1..fin2), - a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q57, q63] != 4]) - | q61 : int(1..2)]) - /\ - and([or([q67 <= - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Marker[q59] - /\ - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Values - [q59, q67] - = a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q57, q65] - | q67 : int(1..2)]) - | q65 : int(1..fin2), - a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q57, q65] != 4]), - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_3[q59] = a_RelationAsSetR6_ExplicitR6_3[q57]; - int(1..3)]) - | q59 : int(1..84)]) - | q57 : int(1..fin1)]), - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Marker = fin1, - and([q1 + 1 <= r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Marker -> - flatten([[r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_1[q1]; int(1)], - flatten([[r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Marker[q1]; - int(1)], - [r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Values - [q1, q7] - | q7 : int(1..2)]; - int(1..2)]), - [r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_3[q1]; int(1)]; - int(1..3)]) - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Marker -> - and([r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_1[q2] = 1, - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Marker[q2] = 0 /\ - and([r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Values[q2, q9] = 2 - | q9 : int(1..2)]), - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_3[q2] = 4; - int(1..3)]) - | q2 : int(1..84)]), - and([q3 <= r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Marker -> - (2 <= r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Marker[q3] -> - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Values[q3, 1] < - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Values[q3, 2]) - | q3 : int(1..84)]), - and([q3 <= r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Marker -> - and([q5 > r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Marker[q3] -> - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Values[q3, q5] = 2 - | q5 : int(1..2)]) - | q3 : int(1..84)]), - and([q10 + 1 <= r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Marker -> - flatten([[r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_1[q10]; int(1)], - flatten([flatten([[-toInt(r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Flags - [q10, q18]); - int(1)], - [r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Values - [q10, q18]; - int(1)]; - int(1..2)]) - | q18 : int(1..2)]), - [r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_3[q10]; int(1)]; - int(1..3)]) - r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Marker -> - and([r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_1[q11] = 1, - and([r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Flags[q11, q20] = - false - | q20 : int(1..2)]) - /\ - and([r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Values[q11, q21] = 2 - | q21 : int(1..2)]), - r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_3[q11] = 4; - int(1..3)]) - | q11 : int(1..84)]), - and([q12 <= r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Marker -> - (r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Flags[q12, 2] -> - r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Values[q12, 1] < - r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Values[q12, 2]) - | q12 : int(1..84)]), - and([q12 <= r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Marker -> - and([r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Flags[q12, q14] = false -> - r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Values[q12, q14] = 2 - | q14 : int(1..2)]) - | q12 : int(1..84)]), - and([q12 <= r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Marker -> - (r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Flags[q12, 2] -> - r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Flags[q12, 1]) - | q12 : int(1..84)]), - and([q23 <= r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Marker -> - or([q25 <= r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Marker /\ - and([r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_1[q25] = - r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_1[q23], - and([q27 <= - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Marker[q25] - -> - or([r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Flags - [q23, q29] - /\ - r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Values - [q23, q29] - = - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Values - [q25, q27] - | q29 : int(1..2)]) - | q27 : int(1..2)]) - /\ - and([r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Flags[q23, q31] - -> - or([q33 <= - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Marker[q25] - /\ - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Values - [q25, q33] - = - r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Values - [q23, q31] - | q33 : int(1..2)]) - | q31 : int(1..2)]), - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_3[q25] = - r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_3[q23]; - int(1..3)]) - | q25 : int(1..84)]) - | q23 : int(1..84)]), - and([q34 <= r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Marker -> - or([q36 <= r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Marker /\ - and([r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_1[q36] = - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_1[q34], - and([r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Flags[q36, q38] - -> - or([q40 <= - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Marker[q34] - /\ - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Values - [q34, q40] - = - r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Values - [q36, q38] - | q40 : int(1..2)]) - | q38 : int(1..2)]) - /\ - and([q42 <= - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Marker[q34] - -> - or([r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Flags - [q36, q44] - /\ - r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Values - [q36, q44] - = - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Values - [q34, q42] - | q44 : int(1..2)]) - | q42 : int(1..2)]), - r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_3[q36] = - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_3[q34]; - int(1..3)]) - | q36 : int(1..84)]) - | q34 : int(1..84)]), - r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Marker = r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Marker - diff --git a/tests/exhaustive/basic/relation04_param/expected/model_4_1-param4-solution000001.solution b/tests/exhaustive/basic/relation04_param/expected/model_4_1-param4-solution000001.solution new file mode 100644 index 0000000000..547e6d2e7e --- /dev/null +++ b/tests/exhaustive/basic/relation04_param/expected/model_4_1-param4-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting r be relation((3, {2}, 6), (3, {3}, 9)) diff --git a/tests/exhaustive/basic/relation04_param/expected/model_4_1-param4.eprime-param b/tests/exhaustive/basic/relation04_param/expected/model_4_1-param4.eprime-param new file mode 100644 index 0000000000..87708d95a4 --- /dev/null +++ b/tests/exhaustive/basic/relation04_param/expected/model_4_1-param4.eprime-param @@ -0,0 +1,11 @@ +language ESSENCE' 1.0 + +letting a_RelationAsSetR6_ExplicitR6_1 be [3, 3; int(1..2)] +letting a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy be [[2; int(1)], [3; int(1)]; int(1..2)] +$ Visualisation for a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy +$ 2 +$ 3 + +letting a_RelationAsSetR6_ExplicitR6_3 be [6, 9; int(1..2)] +letting fin1 be 2 +letting fin2 be 1 diff --git a/tests/exhaustive/basic/relation04_param/expected/model_4_1.eprime b/tests/exhaustive/basic/relation04_param/expected/model_4_1.eprime new file mode 100644 index 0000000000..6539c4f97f --- /dev/null +++ b/tests/exhaustive/basic/relation04_param/expected/model_4_1.eprime @@ -0,0 +1,202 @@ +language ESSENCE' 1.0 + +given fin1: int +given fin2: int +given a_RelationAsSetR6_ExplicitR6_1: matrix indexed by [int(1..fin1)] of int(1..3) +given a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy: + matrix indexed by [int(1..fin1), int(1..fin2)] of int(2..4) +given a_RelationAsSetR6_ExplicitR6_3: matrix indexed by [int(1..fin1)] of int(4..10) +find r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Marker: int(0..84) +find r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_1: matrix indexed by [int(1..84)] of int(1..3) +find r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Flags: + matrix indexed by [int(1..84), int(1..2)] of bool +find r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Values: + matrix indexed by [int(1..84), int(1..2)] of int(2..3) +find r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_3: matrix indexed by [int(1..84)] of int(4..10) +find r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Marker: int(0..84) +find r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_1: matrix indexed by [int(1..84)] of int(1..3) +find r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_2_Occurrence: + matrix indexed by [int(1..84), int(2..3)] of bool +find r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_3: matrix indexed by [int(1..84)] of int(4..10) +branching on + [r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Marker, r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_1, + r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_2_Occurrence, + r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_3, r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Marker, + r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_1, + r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Flags, + r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Values, + r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_3] +such that + and([q38 <= r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Marker -> + or([and([a_RelationAsSetR6_ExplicitR6_1[q40] = r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_1[q38], + and([or([r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Flags + [q38, q44] + /\ + r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Values + [q38, q44] + = a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q40, q42] + | q44 : int(1..2)]) + | q42 : int(1..fin2), + a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q40, q42] != 4]) + /\ + and([r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Flags[q38, q46] + -> + or([a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q40, q48] = + r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Values + [q38, q46] + | q48 : int(1..fin2), + a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q40, q48] != 4]) + | q46 : int(1..2)]), + a_RelationAsSetR6_ExplicitR6_3[q40] = r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_3[q38]; + int(1..3)]) + | q40 : int(1..fin1)]) + | q38 : int(1..84)]), + and([or([q51 <= r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Marker /\ + and([r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_1[q51] = a_RelationAsSetR6_ExplicitR6_1[q49], + and([r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Flags[q51, q53] + -> + or([a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q49, q55] = + r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Values + [q51, q53] + | q55 : int(1..fin2), + a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q49, q55] != 4]) + | q53 : int(1..2)]) + /\ + and([or([r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Flags + [q51, q59] + /\ + r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Values + [q51, q59] + = a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q49, q57] + | q59 : int(1..2)]) + | q57 : int(1..fin2), + a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q49, q57] != 4]), + r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_3[q51] = a_RelationAsSetR6_ExplicitR6_3[q49]; + int(1..3)]) + | q51 : int(1..84)]) + | q49 : int(1..fin1)]), + r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Marker = fin1, + and([q1 + 1 <= r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Marker -> + flatten([[r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_1[q1]; int(1)], + flatten([flatten([[-toInt(r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Flags + [q1, q9]); + int(1)], + [r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Values + [q1, q9]; + int(1)]; + int(1..2)]) + | q9 : int(1..2)]), + [r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_3[q1]; int(1)]; + int(1..3)]) + r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Marker -> + and([r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_1[q2] = 1, + and([r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Flags[q2, q11] = + false + | q11 : int(1..2)]) + /\ + and([r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Values[q2, q12] = 2 + | q12 : int(1..2)]), + r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_3[q2] = 4; + int(1..3)]) + | q2 : int(1..84)]), + and([q3 <= r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Marker -> + (r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Flags[q3, 2] -> + r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Values[q3, 1] < + r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Values[q3, 2]) + | q3 : int(1..84)]), + and([q3 <= r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Marker -> + and([r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Flags[q3, q5] = false -> + r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Values[q3, q5] = 2 + | q5 : int(1..2)]) + | q3 : int(1..84)]), + and([q3 <= r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Marker -> + (r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Flags[q3, 2] -> + r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Flags[q3, 1]) + | q3 : int(1..84)]), + and([q13 + 1 <= r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Marker -> + flatten([[r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_1[q13]; int(1)], + [-toInt(r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_2_Occurrence[q13, q17]) + | q17 : int(2..3)], + [r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_3[q13]; int(1)]; + int(1..3)]) + r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Marker -> + and([r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_1[q14] = 1, + and([r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_2_Occurrence[q14, q19] = false + | q19 : int(2..3)]), + r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_3[q14] = 4; + int(1..3)]) + | q14 : int(1..84)]), + and([q21 <= r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Marker -> + or([q23 <= r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Marker /\ + and([r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_1[q23] = + r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_1[q21], + and([r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Flags[q23, q25] + -> + r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_2_Occurrence + [q21, + r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Values + [q23, q25]] + | q25 : int(1..2)]) + /\ + and([r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_2_Occurrence[q21, q26] -> + or([r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Flags + [q23, q28] + /\ + r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Values + [q23, q28] + = q26 + | q28 : int(1..2)]) + | q26 : int(2..3)]), + r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_3[q23] = + r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_3[q21]; + int(1..3)]) + | q23 : int(1..84)]) + | q21 : int(1..84)]), + and([q29 <= r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Marker -> + or([q31 <= r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Marker /\ + and([r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_1[q31] = + r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_1[q29], + and([r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_2_Occurrence[q31, q32] -> + or([r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Flags + [q29, q34] + /\ + r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Values + [q29, q34] + = q32 + | q34 : int(1..2)]) + | q32 : int(2..3)]) + /\ + and([r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Flags[q29, q36] + -> + r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_2_Occurrence + [q31, + r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Values + [q29, q36]] + | q36 : int(1..2)]), + r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_3[q31] = + r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_3[q29]; + int(1..3)]) + | q31 : int(1..84)]) + | q29 : int(1..84)]), + r_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Marker = r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Marker + diff --git a/tests/exhaustive/basic/relation04_param/expected/model_4_2-param4-solution000001.solution b/tests/exhaustive/basic/relation04_param/expected/model_4_2-param4-solution000001.solution new file mode 100644 index 0000000000..547e6d2e7e --- /dev/null +++ b/tests/exhaustive/basic/relation04_param/expected/model_4_2-param4-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting r be relation((3, {2}, 6), (3, {3}, 9)) diff --git a/tests/exhaustive/basic/relation04_param/expected/model_4_2-param4.eprime-param b/tests/exhaustive/basic/relation04_param/expected/model_4_2-param4.eprime-param new file mode 100644 index 0000000000..87708d95a4 --- /dev/null +++ b/tests/exhaustive/basic/relation04_param/expected/model_4_2-param4.eprime-param @@ -0,0 +1,11 @@ +language ESSENCE' 1.0 + +letting a_RelationAsSetR6_ExplicitR6_1 be [3, 3; int(1..2)] +letting a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy be [[2; int(1)], [3; int(1)]; int(1..2)] +$ Visualisation for a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy +$ 2 +$ 3 + +letting a_RelationAsSetR6_ExplicitR6_3 be [6, 9; int(1..2)] +letting fin1 be 2 +letting fin2 be 1 diff --git a/tests/exhaustive/basic/relation04_param/expected/model_4_3.eprime.orig b/tests/exhaustive/basic/relation04_param/expected/model_4_2.eprime similarity index 51% rename from tests/exhaustive/basic/relation04_param/expected/model_4_3.eprime.orig rename to tests/exhaustive/basic/relation04_param/expected/model_4_2.eprime index f535969c32..d76b74b4f4 100644 --- a/tests/exhaustive/basic/relation04_param/expected/model_4_3.eprime.orig +++ b/tests/exhaustive/basic/relation04_param/expected/model_4_2.eprime @@ -13,71 +13,68 @@ find r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithF find r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..84), int(1..2)] of int(2..3) find r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_3: matrix indexed by [int(1..84)] of int(4..10) -find r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Marker: int(0..84) -find r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_1: matrix indexed by [int(1..84)] of int(1..3) -find r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Marker: - matrix indexed by [int(1..84)] of int(0..2) -find r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Values: - matrix indexed by [int(1..84), int(1..2)] of int(2..3) -find r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_3: matrix indexed by [int(1..84)] of int(4..10) +find r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Marker: int(0..84) +find r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_1: matrix indexed by [int(1..84)] of int(1..3) +find r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy: + matrix indexed by [int(1..84), int(1..2)] of int(2..4) +find r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_3: matrix indexed by [int(1..84)] of int(4..10) branching on - [r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Marker, r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_1, - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Marker, - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Values, - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_3, r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Marker, + [r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Marker, r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_1, + r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy, + r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_3, r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Marker, r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_1, r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Flags, r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Values, r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_3] such that - and([q46 <= r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Marker -> - or([and([a_RelationAsSetR6_ExplicitR6_1[q48] = r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_1[q46], + and([q47 <= r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Marker -> + or([and([a_RelationAsSetR6_ExplicitR6_1[q49] = r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_1[q47], and([or([r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Flags - [q46, q52] + [q47, q53] /\ r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Values - [q46, q52] - = a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q48, q50] - | q52 : int(1..2)]) - | q50 : int(1..fin2), - a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q48, q50] != 4]) + [q47, q53] + = a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q49, q51] + | q53 : int(1..2)]) + | q51 : int(1..fin2), + a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q49, q51] != 4]) /\ - and([r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Flags[q46, q54] + and([r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Flags[q47, q55] -> - or([a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q48, q56] = + or([a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q49, q57] = r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Values - [q46, q54] - | q56 : int(1..fin2), - a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q48, q56] != 4]) - | q54 : int(1..2)]), - a_RelationAsSetR6_ExplicitR6_3[q48] = r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_3[q46]; + [q47, q55] + | q57 : int(1..fin2), + a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q49, q57] != 4]) + | q55 : int(1..2)]), + a_RelationAsSetR6_ExplicitR6_3[q49] = r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_3[q47]; int(1..3)]) - | q48 : int(1..fin1)]) - | q46 : int(1..84)]), - and([or([q59 <= r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Marker /\ - and([r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_1[q59] = a_RelationAsSetR6_ExplicitR6_1[q57], - and([r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Flags[q59, q61] + | q49 : int(1..fin1)]) + | q47 : int(1..84)]), + and([or([q60 <= r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Marker /\ + and([r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_1[q60] = a_RelationAsSetR6_ExplicitR6_1[q58], + and([r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Flags[q60, q62] -> - or([a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q57, q63] = + or([a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q58, q64] = r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Values - [q59, q61] - | q63 : int(1..fin2), - a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q57, q63] != 4]) - | q61 : int(1..2)]) + [q60, q62] + | q64 : int(1..fin2), + a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q58, q64] != 4]) + | q62 : int(1..2)]) /\ and([or([r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Flags - [q59, q67] + [q60, q68] /\ r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Values - [q59, q67] - = a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q57, q65] - | q67 : int(1..2)]) - | q65 : int(1..fin2), - a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q57, q65] != 4]), - r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_3[q59] = a_RelationAsSetR6_ExplicitR6_3[q57]; + [q60, q68] + = a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q58, q66] + | q68 : int(1..2)]) + | q66 : int(1..fin2), + a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q58, q66] != 4]), + r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_3[q60] = a_RelationAsSetR6_ExplicitR6_3[q58]; int(1..3)]) - | q59 : int(1..84)]) - | q57 : int(1..fin1)]), + | q60 : int(1..84)]) + | q58 : int(1..fin1)]), r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Marker = fin1, and([q1 + 1 <= r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Marker -> flatten([[r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_1[q1]; int(1)], @@ -129,116 +126,92 @@ such that (r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Flags[q3, 2] -> r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Flags[q3, 1]) | q3 : int(1..84)]), - and([q13 + 1 <= r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Marker -> - flatten([[r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_1[q13]; int(1)], - flatten([[r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Marker - [q13]; - int(1)], - [r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Values - [q13, q19] - | q19 : int(1..2)]; - int(1..2)]), - [r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_3[q13]; int(1)]; + and([q13 + 1 <= r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Marker -> + flatten([[r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_1[q13]; int(1)], + [r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q13, q20] + | q20 : int(1..2)], + [r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_3[q13]; int(1)]; int(1..3)]) r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Marker -> - and([r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_1[q14] = 1, - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Marker[q14] = 0 /\ - and([r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Values[q14, q21] = 2 - | q21 : int(1..2)]), - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_3[q14] = 4; + and([q14 > r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Marker -> + and([r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_1[q14] = 1, + and([r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q14, q22] = 2 + | q22 : int(1..2)]), + r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_3[q14] = 4; int(1..3)]) | q14 : int(1..84)]), - and([q15 <= r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Marker -> - (2 <= r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Marker[q15] -> - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Values[q15, 1] < - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Values[q15, 2]) + and([q15 <= r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Marker -> + r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q15, 1] < + r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q15, 2] + \/ r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q15, 1] = 4 | q15 : int(1..84)]), - and([q15 <= r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Marker -> - and([q17 > r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Marker[q15] -> - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Values[q15, q17] = 2 - | q17 : int(1..2)]) + and([q15 <= r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Marker -> + (r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q15, 1] = 4 -> + r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q15, 2] = 4) | q15 : int(1..84)]), - and([q23 <= r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Marker -> - or([q25 <= r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Marker /\ - and([r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_1[q25] = - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_1[q23], - and([r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Flags[q25, q27] + and([q24 <= r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Marker -> + or([q26 <= r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Marker /\ + and([r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_1[q26] = + r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_1[q24], + and([r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Flags[q26, q28] -> - or([q29 <= - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Marker[q23] + or([r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q24, q30] != + 4 /\ - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Values - [q23, q29] - = + r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q24, q30] = r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Values - [q25, q27] - | q29 : int(1..2)]) - | q27 : int(1..2)]) + [q26, q28] + | q30 : int(1..2)]) + | q28 : int(1..2)]) /\ - and([q31 <= - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Marker[q23] - -> + and([r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q24, q32] != 4 -> or([r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Flags - [q25, q33] + [q26, q34] /\ r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Values - [q25, q33] - = - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Values - [q23, q31] - | q33 : int(1..2)]) - | q31 : int(1..2)]), - r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_3[q25] = - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_3[q23]; + [q26, q34] + = r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q24, q32] + | q34 : int(1..2)]) + | q32 : int(1..2)]), + r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_3[q26] = + r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_3[q24]; int(1..3)]) - | q25 : int(1..84)]) - | q23 : int(1..84)]), - and([q34 <= r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Marker -> - or([q36 <= r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Marker /\ - and([r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_1[q36] = - r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_1[q34], - and([q38 <= - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Marker[q36] - -> + | q26 : int(1..84)]) + | q24 : int(1..84)]), + and([q35 <= r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Marker -> + or([q37 <= r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Marker /\ + and([r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_1[q37] = + r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_1[q35], + and([r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q37, q39] != 4 -> or([r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Flags - [q34, q40] + [q35, q41] /\ r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Values - [q34, q40] - = - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Values - [q36, q38] - | q40 : int(1..2)]) - | q38 : int(1..2)]) + [q35, q41] + = r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q37, q39] + | q41 : int(1..2)]) + | q39 : int(1..2)]) /\ - and([r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Flags[q34, q42] + and([r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Flags[q35, q43] -> - or([q44 <= - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Marker[q36] + or([r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q37, q45] != + 4 /\ - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_2_ExplicitVarSizeWithMarker_Values - [q36, q44] - = + r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_2_ExplicitVarSizeWithDummy[q37, q45] = r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Values - [q34, q42] - | q44 : int(1..2)]) - | q42 : int(1..2)]), - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Values_3[q36] = - r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_3[q34]; + [q35, q43] + | q45 : int(1..2)]) + | q43 : int(1..2)]), + r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Values_3[q37] = + r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_3[q35]; int(1..3)]) - | q36 : int(1..84)]) - | q34 : int(1..84)]), - r_RelationAsSetR5_ExplicitVarSizeWithMarkerR5_Marker = r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Marker + | q37 : int(1..84)]) + | q35 : int(1..84)]), + r_RelationAsSetR6_ExplicitVarSizeWithMarkerR6_Marker = r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Marker diff --git a/tests/exhaustive/basic/relation04_param/expected/model_4_3-param4-solution000001.solution b/tests/exhaustive/basic/relation04_param/expected/model_4_3-param4-solution000001.solution new file mode 100644 index 0000000000..547e6d2e7e --- /dev/null +++ b/tests/exhaustive/basic/relation04_param/expected/model_4_3-param4-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting r be relation((3, {2}, 6), (3, {3}, 9)) diff --git a/tests/exhaustive/basic/relation04_param/expected/model_4_3-param4.eprime-param b/tests/exhaustive/basic/relation04_param/expected/model_4_3-param4.eprime-param new file mode 100644 index 0000000000..87708d95a4 --- /dev/null +++ b/tests/exhaustive/basic/relation04_param/expected/model_4_3-param4.eprime-param @@ -0,0 +1,11 @@ +language ESSENCE' 1.0 + +letting a_RelationAsSetR6_ExplicitR6_1 be [3, 3; int(1..2)] +letting a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy be [[2; int(1)], [3; int(1)]; int(1..2)] +$ Visualisation for a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy +$ 2 +$ 3 + +letting a_RelationAsSetR6_ExplicitR6_3 be [6, 9; int(1..2)] +letting fin1 be 2 +letting fin2 be 1 diff --git a/tests/exhaustive/basic/relation04_param/expected/model_4_4-param4-solution000001.solution b/tests/exhaustive/basic/relation04_param/expected/model_4_4-param4-solution000001.solution new file mode 100644 index 0000000000..547e6d2e7e --- /dev/null +++ b/tests/exhaustive/basic/relation04_param/expected/model_4_4-param4-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting r be relation((3, {2}, 6), (3, {3}, 9)) diff --git a/tests/exhaustive/basic/relation04_param/expected/model_4_4-param4.eprime-param b/tests/exhaustive/basic/relation04_param/expected/model_4_4-param4.eprime-param new file mode 100644 index 0000000000..87708d95a4 --- /dev/null +++ b/tests/exhaustive/basic/relation04_param/expected/model_4_4-param4.eprime-param @@ -0,0 +1,11 @@ +language ESSENCE' 1.0 + +letting a_RelationAsSetR6_ExplicitR6_1 be [3, 3; int(1..2)] +letting a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy be [[2; int(1)], [3; int(1)]; int(1..2)] +$ Visualisation for a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy +$ 2 +$ 3 + +letting a_RelationAsSetR6_ExplicitR6_3 be [6, 9; int(1..2)] +letting fin1 be 2 +letting fin2 be 1 diff --git a/tests/exhaustive/basic/relation04_param/expected/model_4_4.eprime b/tests/exhaustive/basic/relation04_param/expected/model_4_4.eprime new file mode 100644 index 0000000000..e4cbdf3e64 --- /dev/null +++ b/tests/exhaustive/basic/relation04_param/expected/model_4_4.eprime @@ -0,0 +1,121 @@ +language ESSENCE' 1.0 + +given fin1: int +given fin2: int +given a_RelationAsSetR6_ExplicitR6_1: matrix indexed by [int(1..fin1)] of int(1..3) +given a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy: + matrix indexed by [int(1..fin1), int(1..fin2)] of int(2..4) +given a_RelationAsSetR6_ExplicitR6_3: matrix indexed by [int(1..fin1)] of int(4..10) +find r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Marker: int(0..84) +find r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_1: matrix indexed by [int(1..84)] of int(1..3) +find r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Flags: + matrix indexed by [int(1..84), int(1..2)] of bool +find r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Values: + matrix indexed by [int(1..84), int(1..2)] of int(2..3) +find r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_3: matrix indexed by [int(1..84)] of int(4..10) +branching on + [r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Marker, r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_1, + r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Flags, + r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Values, + r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_3] +such that + and([q14 <= r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Marker -> + or([and([a_RelationAsSetR6_ExplicitR6_1[q16] = r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_1[q14], + and([or([r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Flags + [q14, q20] + /\ + r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Values + [q14, q20] + = a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q16, q18] + | q20 : int(1..2)]) + | q18 : int(1..fin2), + a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q16, q18] != 4]) + /\ + and([r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Flags[q14, q22] + -> + or([a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q16, q24] = + r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Values + [q14, q22] + | q24 : int(1..fin2), + a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q16, q24] != 4]) + | q22 : int(1..2)]), + a_RelationAsSetR6_ExplicitR6_3[q16] = r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_3[q14]; + int(1..3)]) + | q16 : int(1..fin1)]) + | q14 : int(1..84)]), + and([or([q27 <= r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Marker /\ + and([r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_1[q27] = a_RelationAsSetR6_ExplicitR6_1[q25], + and([r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Flags[q27, q29] + -> + or([a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q25, q31] = + r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Values + [q27, q29] + | q31 : int(1..fin2), + a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q25, q31] != 4]) + | q29 : int(1..2)]) + /\ + and([or([r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Flags + [q27, q35] + /\ + r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Values + [q27, q35] + = a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q25, q33] + | q35 : int(1..2)]) + | q33 : int(1..fin2), + a_RelationAsSetR6_ExplicitR6_2_ExplicitVarSizeWithDummy[q25, q33] != 4]), + r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_3[q27] = a_RelationAsSetR6_ExplicitR6_3[q25]; + int(1..3)]) + | q27 : int(1..84)]) + | q25 : int(1..fin1)]), + r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Marker = fin1, + and([q1 + 1 <= r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Marker -> + flatten([[r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_1[q1]; int(1)], + flatten([flatten([[-toInt(r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Flags + [q1, q9]); + int(1)], + [r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Values + [q1, q9]; + int(1)]; + int(1..2)]) + | q9 : int(1..2)]), + [r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_3[q1]; int(1)]; + int(1..3)]) + r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Marker -> + and([r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_1[q2] = 1, + and([r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Flags[q2, q11] = + false + | q11 : int(1..2)]) + /\ + and([r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Values[q2, q12] = 2 + | q12 : int(1..2)]), + r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_3[q2] = 4; + int(1..3)]) + | q2 : int(1..84)]), + and([q3 <= r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Marker -> + (r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Flags[q3, 2] -> + r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Values[q3, 1] < + r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Values[q3, 2]) + | q3 : int(1..84)]), + and([q3 <= r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Marker -> + and([r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Flags[q3, q5] = false -> + r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Values[q3, q5] = 2 + | q5 : int(1..2)]) + | q3 : int(1..84)]), + and([q3 <= r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Marker -> + (r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Flags[q3, 2] -> + r_RelationAsSetR4_ExplicitVarSizeWithMarkerR4_Values_2_ExplicitVarSizeWithFlags_Flags[q3, 1]) + | q3 : int(1..84)]) + diff --git a/tests/exhaustive/basic/relation05_set_fixed_direct/expected/model_2.eprime b/tests/exhaustive/basic/relation05_set_fixed_direct/expected/model_2.eprime index 35f582c602..cdd331bb1d 100644 --- a/tests/exhaustive/basic/relation05_set_fixed_direct/expected/model_2.eprime +++ b/tests/exhaustive/basic/relation05_set_fixed_direct/expected/model_2.eprime @@ -12,11 +12,5 @@ such that [-toInt(x_RelationAsSetR2_ExplicitR2_2_Occurrence[q1 + 1, q5]) | q5 : int(1..3)]; int(1..2)]) | q1 : int(1..3)]), -<<<<<<< HEAD - and([[x_RelationAsSetR3_ExplicitR3_2_Explicit[q2, 1]; int(1)] >>>>>> main diff --git a/tests/exhaustive/basic/relation05_set_fixed_setty/expected/model_2.eprime b/tests/exhaustive/basic/relation05_set_fixed_setty/expected/model_2.eprime index 1f7af37e2a..f35ec39261 100644 --- a/tests/exhaustive/basic/relation05_set_fixed_setty/expected/model_2.eprime +++ b/tests/exhaustive/basic/relation05_set_fixed_setty/expected/model_2.eprime @@ -10,9 +10,5 @@ such that flatten([[x_ExplicitR2_1[q1 + 1]; int(1)], [-toInt(x_ExplicitR2_2_Occurrence[q1 + 1, q5]) | q5 : int(1..3)]; int(1..2)]) | q1 : int(1..3)]), -<<<<<<< HEAD - and([[x_ExplicitR3_2_Explicit[q2, 1]; int(1)] >>>>>> main diff --git a/tests/exhaustive/basic/relation06_set_bounded_direct/expected/model_2.eprime b/tests/exhaustive/basic/relation06_set_bounded_direct/expected/model_2.eprime index bb7be86392..5c9f630e85 100644 --- a/tests/exhaustive/basic/relation06_set_bounded_direct/expected/model_2.eprime +++ b/tests/exhaustive/basic/relation06_set_bounded_direct/expected/model_2.eprime @@ -21,17 +21,9 @@ such that x_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_1[q2] = 1 /\ and([x_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_2_Occurrence[q2, q7] = false | q7 : int(1..3)]) | q2 : int(1..3)]), -<<<<<<< HEAD - 2 <= x_RelationAsSetR3_ExplicitVarSizeWithMarkerR3_Marker, - x_RelationAsSetR3_ExplicitVarSizeWithMarkerR3_Marker <= 3, - and([q3 <= x_RelationAsSetR3_ExplicitVarSizeWithMarkerR3_Marker -> - [x_RelationAsSetR3_ExplicitVarSizeWithMarkerR3_Values_2_Explicit[q3, 1]; int(1)] 2 = sum([toInt(x_RelationAsSetR2_ExplicitVarSizeWithMarkerR2_Values_2_Occurrence[q3, q4]) | q4 : int(1..3)]) ->>>>>>> main | q3 : int(1..3)]) diff --git a/tests/exhaustive/basic/relation06_set_bounded_setty/expected/model_2.eprime b/tests/exhaustive/basic/relation06_set_bounded_setty/expected/model_2.eprime index d1349cf0d0..2a175b772c 100644 --- a/tests/exhaustive/basic/relation06_set_bounded_setty/expected/model_2.eprime +++ b/tests/exhaustive/basic/relation06_set_bounded_setty/expected/model_2.eprime @@ -20,17 +20,9 @@ such that x_ExplicitVarSizeWithMarkerR2_Values_1[q2] = 1 /\ and([x_ExplicitVarSizeWithMarkerR2_Values_2_Occurrence[q2, q7] = false | q7 : int(1..3)]) | q2 : int(1..3)]), -<<<<<<< HEAD - 2 <= x_ExplicitVarSizeWithMarkerR3_Marker, - x_ExplicitVarSizeWithMarkerR3_Marker <= 3, - and([q3 <= x_ExplicitVarSizeWithMarkerR3_Marker -> - [x_ExplicitVarSizeWithMarkerR3_Values_2_Explicit[q3, 1]; int(1)] 2 = sum([toInt(x_ExplicitVarSizeWithMarkerR2_Values_2_Occurrence[q3, q4]) | q4 : int(1..3)]) ->>>>>>> main | q3 : int(1..3)]) diff --git a/tests/exhaustive/basic/relation06_set_bounded_setty/expected/model_4.eprime b/tests/exhaustive/basic/relation06_set_bounded_setty/expected/model_4.eprime index 4f317c83dc..ef02aab680 100644 --- a/tests/exhaustive/basic/relation06_set_bounded_setty/expected/model_4.eprime +++ b/tests/exhaustive/basic/relation06_set_bounded_setty/expected/model_4.eprime @@ -20,19 +20,10 @@ such that x_ExplicitVarSizeWithFlagsR2_Values_1[q2] = 1 /\ and([x_ExplicitVarSizeWithFlagsR2_Values_2_Occurrence[q2, q9] = false | q9 : int(1..3)]) | q2 : int(1..3)]), -<<<<<<< HEAD - and([x_ExplicitVarSizeWithFlagsR3_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlagsR3_Flags[q3] | q3 : int(1..2)]), - 2 <= sum([toInt(x_ExplicitVarSizeWithFlagsR3_Flags[q4]) | q4 : int(1..3)]), - sum([toInt(x_ExplicitVarSizeWithFlagsR3_Flags[q4]) | q4 : int(1..3)]) <= 3, - and([x_ExplicitVarSizeWithFlagsR3_Flags[q5] -> - [x_ExplicitVarSizeWithFlagsR3_Values_2_Explicit[q5, 1]; int(1)] x_ExplicitVarSizeWithFlagsR2_Flags[q3] | q3 : int(1..2)]), 2 <= sum([toInt(x_ExplicitVarSizeWithFlagsR2_Flags[q4]) | q4 : int(1..3)]), sum([toInt(x_ExplicitVarSizeWithFlagsR2_Flags[q4]) | q4 : int(1..3)]) <= 3, and([x_ExplicitVarSizeWithFlagsR2_Flags[q5] -> 2 = sum([toInt(x_ExplicitVarSizeWithFlagsR2_Values_2_Occurrence[q5, q6]) | q6 : int(1..3)]) ->>>>>>> main | q5 : int(1..3)]) diff --git a/tests/exhaustive/basic/sequence_injective_01/expected/model.eprime b/tests/exhaustive/basic/sequence_injective_01/expected/model.eprime index c8d80819ad..6b789c1341 100644 --- a/tests/exhaustive/basic/sequence_injective_01/expected/model.eprime +++ b/tests/exhaustive/basic/sequence_injective_01/expected/model.eprime @@ -7,5 +7,5 @@ branching on [f_ExplicitBounded_Length, f_ExplicitBounded_Values_1, f_ExplicitBo such that and([f_ExplicitBounded_Values_1[q1] != f_ExplicitBounded_Values_1[q2] \/ f_ExplicitBounded_Values_2[q1] != f_ExplicitBounded_Values_2[q2] - | q1 : int(1..2), q2 : int(1..2), [q1; int(1)] f_ExplicitBounded_Values_1[q2] != f_ExplicitBounded_Values_1[q3] \/ f_ExplicitBounded_Values_2[q2] != f_ExplicitBounded_Values_2[q3] - | q2 : int(1..2), q3 : int(1..2), [q2; int(1)] >>>>>> main diff --git a/tests/exhaustive/basic/set01_2/expected/model_1_2.eprime b/tests/exhaustive/basic/set01_2/expected/model_1_2.eprime index e944088997..560304aacd 100644 --- a/tests/exhaustive/basic/set01_2/expected/model_1_2.eprime +++ b/tests/exhaustive/basic/set01_2/expected/model_1_2.eprime @@ -4,17 +4,9 @@ find x_Explicit: matrix indexed by [int(1..2)] of int(1..3) find x_Occurrence: matrix indexed by [int(1..3)] of bool branching on [x_Occurrence, x_Explicit] such that -<<<<<<< HEAD - and([x_Occurrence[i] | i : int(1..2)]), - 2 = sum([toInt(x_Occurrence[q1]) | q1 : int(1..3)]), - [x_Explicit[1]; int(1)] or([x_Explicit[q8] = q6 | q8 : int(1..2)]) | q6 : int(1..3)]) -======= and([or([x_Explicit[q10] = i | q10 : int(1..2)]) | i : int(1..2)]), x_Explicit[1] < x_Explicit[2], 2 = sum([toInt(x_Occurrence[q3]) | q3 : int(1..3)]), and([x_Occurrence[q4] -> or([x_Explicit[q6] = q4 | q6 : int(1..2)]) | q4 : int(1..3)]), and([x_Occurrence[x_Explicit[q8]] | q8 : int(1..2)]) ->>>>>>> main diff --git a/tests/exhaustive/basic/set01_2/expected/model_2_1.eprime b/tests/exhaustive/basic/set01_2/expected/model_2_1.eprime index 7b0834eddc..d0220e3ef9 100644 --- a/tests/exhaustive/basic/set01_2/expected/model_2_1.eprime +++ b/tests/exhaustive/basic/set01_2/expected/model_2_1.eprime @@ -4,17 +4,9 @@ find x_Occurrence: matrix indexed by [int(1..3)] of bool find x_Explicit: matrix indexed by [int(1..2)] of int(1..3) branching on [x_Explicit, x_Occurrence] such that -<<<<<<< HEAD - and([or([x_Explicit[q10] = i | q10 : int(1..2)]) | i : int(1..2)]), - [x_Explicit[1]; int(1)] or([x_Explicit[q6] = q4 | q6 : int(1..2)]) | q4 : int(1..3)]), - and([x_Occurrence[x_Explicit[q8]] | q8 : int(1..2)]) -======= and([x_Occurrence[i] | i : int(1..2)]), 2 = sum([toInt(x_Occurrence[q1]) | q1 : int(1..3)]), x_Explicit[1] < x_Explicit[2], and([x_Occurrence[x_Explicit[q5]] | q5 : int(1..2)]), and([x_Occurrence[q6] -> or([x_Explicit[q8] = q6 | q8 : int(1..2)]) | q6 : int(1..3)]) ->>>>>>> main diff --git a/tests/exhaustive/basic/set01_2/expected/model_2_2.eprime b/tests/exhaustive/basic/set01_2/expected/model_2_2.eprime index ba601dd7d5..e83e48b7e4 100644 --- a/tests/exhaustive/basic/set01_2/expected/model_2_2.eprime +++ b/tests/exhaustive/basic/set01_2/expected/model_2_2.eprime @@ -3,11 +3,6 @@ language ESSENCE' 1.0 find x_Occurrence: matrix indexed by [int(1..3)] of bool branching on [x_Occurrence] such that -<<<<<<< HEAD - and([or([x_Explicit[q4] = i | q4 : int(1..2)]) | i : int(1..2)]), - [x_Explicit[1]; int(1)] >>>>>> main diff --git a/tests/exhaustive/basic/set01_3/expected/model_1_2.eprime b/tests/exhaustive/basic/set01_3/expected/model_1_2.eprime index e944088997..560304aacd 100644 --- a/tests/exhaustive/basic/set01_3/expected/model_1_2.eprime +++ b/tests/exhaustive/basic/set01_3/expected/model_1_2.eprime @@ -4,17 +4,9 @@ find x_Explicit: matrix indexed by [int(1..2)] of int(1..3) find x_Occurrence: matrix indexed by [int(1..3)] of bool branching on [x_Occurrence, x_Explicit] such that -<<<<<<< HEAD - and([x_Occurrence[i] | i : int(1..2)]), - 2 = sum([toInt(x_Occurrence[q1]) | q1 : int(1..3)]), - [x_Explicit[1]; int(1)] or([x_Explicit[q8] = q6 | q8 : int(1..2)]) | q6 : int(1..3)]) -======= and([or([x_Explicit[q10] = i | q10 : int(1..2)]) | i : int(1..2)]), x_Explicit[1] < x_Explicit[2], 2 = sum([toInt(x_Occurrence[q3]) | q3 : int(1..3)]), and([x_Occurrence[q4] -> or([x_Explicit[q6] = q4 | q6 : int(1..2)]) | q4 : int(1..3)]), and([x_Occurrence[x_Explicit[q8]] | q8 : int(1..2)]) ->>>>>>> main diff --git a/tests/exhaustive/basic/set01_3/expected/model_2_1.eprime b/tests/exhaustive/basic/set01_3/expected/model_2_1.eprime index 7b0834eddc..d0220e3ef9 100644 --- a/tests/exhaustive/basic/set01_3/expected/model_2_1.eprime +++ b/tests/exhaustive/basic/set01_3/expected/model_2_1.eprime @@ -4,17 +4,9 @@ find x_Occurrence: matrix indexed by [int(1..3)] of bool find x_Explicit: matrix indexed by [int(1..2)] of int(1..3) branching on [x_Explicit, x_Occurrence] such that -<<<<<<< HEAD - and([or([x_Explicit[q10] = i | q10 : int(1..2)]) | i : int(1..2)]), - [x_Explicit[1]; int(1)] or([x_Explicit[q6] = q4 | q6 : int(1..2)]) | q4 : int(1..3)]), - and([x_Occurrence[x_Explicit[q8]] | q8 : int(1..2)]) -======= and([x_Occurrence[i] | i : int(1..2)]), 2 = sum([toInt(x_Occurrence[q1]) | q1 : int(1..3)]), x_Explicit[1] < x_Explicit[2], and([x_Occurrence[x_Explicit[q5]] | q5 : int(1..2)]), and([x_Occurrence[q6] -> or([x_Explicit[q8] = q6 | q8 : int(1..2)]) | q6 : int(1..3)]) ->>>>>>> main diff --git a/tests/exhaustive/basic/set01_3/expected/model_2_2.eprime b/tests/exhaustive/basic/set01_3/expected/model_2_2.eprime index ba601dd7d5..e83e48b7e4 100644 --- a/tests/exhaustive/basic/set01_3/expected/model_2_2.eprime +++ b/tests/exhaustive/basic/set01_3/expected/model_2_2.eprime @@ -3,11 +3,6 @@ language ESSENCE' 1.0 find x_Occurrence: matrix indexed by [int(1..3)] of bool branching on [x_Occurrence] such that -<<<<<<< HEAD - and([or([x_Explicit[q4] = i | q4 : int(1..2)]) | i : int(1..2)]), - [x_Explicit[1]; int(1)] >>>>>> main diff --git a/tests/exhaustive/basic/set02/expected/model_1_2.eprime b/tests/exhaustive/basic/set02/expected/model_1_2.eprime index f551eb02e0..0434a4ad13 100644 --- a/tests/exhaustive/basic/set02/expected/model_1_2.eprime +++ b/tests/exhaustive/basic/set02/expected/model_1_2.eprime @@ -4,17 +4,9 @@ find x_Explicit: matrix indexed by [int(1..2)] of int(1..3) find x_Occurrence: matrix indexed by [int(1..3)] of bool branching on [x_Occurrence, x_Explicit] such that -<<<<<<< HEAD - x_Occurrence[1], - 2 = sum([toInt(x_Occurrence[q1]) | q1 : int(1..3)]), - [x_Explicit[1]; int(1)] or([x_Explicit[q8] = q6 | q8 : int(1..2)]) | q6 : int(1..3)]) -======= or([x_Explicit[q10] = 1 | q10 : int(1..2)]), x_Explicit[1] < x_Explicit[2], 2 = sum([toInt(x_Occurrence[q3]) | q3 : int(1..3)]), and([x_Occurrence[q4] -> or([x_Explicit[q6] = q4 | q6 : int(1..2)]) | q4 : int(1..3)]), and([x_Occurrence[x_Explicit[q8]] | q8 : int(1..2)]) ->>>>>>> main diff --git a/tests/exhaustive/basic/set02/expected/model_2_1.eprime b/tests/exhaustive/basic/set02/expected/model_2_1.eprime index db500dda0f..4fe89c0a58 100644 --- a/tests/exhaustive/basic/set02/expected/model_2_1.eprime +++ b/tests/exhaustive/basic/set02/expected/model_2_1.eprime @@ -4,17 +4,9 @@ find x_Occurrence: matrix indexed by [int(1..3)] of bool find x_Explicit: matrix indexed by [int(1..2)] of int(1..3) branching on [x_Explicit, x_Occurrence] such that -<<<<<<< HEAD - or([x_Explicit[q10] = 1 | q10 : int(1..2)]), - [x_Explicit[1]; int(1)] or([x_Explicit[q6] = q4 | q6 : int(1..2)]) | q4 : int(1..3)]), - and([x_Occurrence[x_Explicit[q8]] | q8 : int(1..2)]) -======= x_Occurrence[1], 2 = sum([toInt(x_Occurrence[q1]) | q1 : int(1..3)]), x_Explicit[1] < x_Explicit[2], and([x_Occurrence[x_Explicit[q5]] | q5 : int(1..2)]), and([x_Occurrence[q6] -> or([x_Explicit[q8] = q6 | q8 : int(1..2)]) | q6 : int(1..3)]) ->>>>>>> main diff --git a/tests/exhaustive/basic/set02/expected/model_2_2.eprime b/tests/exhaustive/basic/set02/expected/model_2_2.eprime index 7294fc8d3b..7fddcb8930 100644 --- a/tests/exhaustive/basic/set02/expected/model_2_2.eprime +++ b/tests/exhaustive/basic/set02/expected/model_2_2.eprime @@ -3,11 +3,6 @@ language ESSENCE' 1.0 find x_Occurrence: matrix indexed by [int(1..3)] of bool branching on [x_Occurrence] such that -<<<<<<< HEAD - or([x_Explicit[q4] = 1 | q4 : int(1..2)]), - [x_Explicit[1]; int(1)] >>>>>> main diff --git a/tests/exhaustive/basic/set03/expected/model_1_1-solution000001.solution b/tests/exhaustive/basic/set03/expected/model_1_1-solution000001.solution new file mode 100644 index 0000000000..de5cc861ad --- /dev/null +++ b/tests/exhaustive/basic/set03/expected/model_1_1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1} diff --git a/tests/exhaustive/basic/set03/expected/model_1_1-solution000002.solution b/tests/exhaustive/basic/set03/expected/model_1_1-solution000002.solution new file mode 100644 index 0000000000..f90e0ba18c --- /dev/null +++ b/tests/exhaustive/basic/set03/expected/model_1_1-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2} diff --git a/tests/exhaustive/basic/set03/expected/model_1_1.eprime b/tests/exhaustive/basic/set03/expected/model_1_1.eprime new file mode 100644 index 0000000000..16b384a5f6 --- /dev/null +++ b/tests/exhaustive/basic/set03/expected/model_1_1.eprime @@ -0,0 +1,8 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(1..2)] of bool +branching on [x_Occurrence] +such that + x_Occurrence[1], + sum([toInt(x_Occurrence[q1]) | q1 : int(1..2)]) <= 2 + diff --git a/tests/exhaustive/basic/set03/expected/model_1_2-solution000001.solution b/tests/exhaustive/basic/set03/expected/model_1_2-solution000001.solution new file mode 100644 index 0000000000..f90e0ba18c --- /dev/null +++ b/tests/exhaustive/basic/set03/expected/model_1_2-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2} diff --git a/tests/exhaustive/basic/set03/expected/model_1_2-solution000002.solution b/tests/exhaustive/basic/set03/expected/model_1_2-solution000002.solution new file mode 100644 index 0000000000..de5cc861ad --- /dev/null +++ b/tests/exhaustive/basic/set03/expected/model_1_2-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1} diff --git a/tests/exhaustive/basic/set03/expected/model_1_2.eprime b/tests/exhaustive/basic/set03/expected/model_1_2.eprime new file mode 100644 index 0000000000..8e12c0f3a2 --- /dev/null +++ b/tests/exhaustive/basic/set03/expected/model_1_2.eprime @@ -0,0 +1,16 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(1..2)] of bool +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..2)] of int(1..3) +branching on [x_ExplicitVarSizeWithDummy, x_Occurrence] +such that + x_Occurrence[1], + sum([toInt(x_Occurrence[q1]) | q1 : int(1..2)]) <= 2, + x_ExplicitVarSizeWithDummy[1] < x_ExplicitVarSizeWithDummy[2] \/ x_ExplicitVarSizeWithDummy[1] = 3, + x_ExplicitVarSizeWithDummy[1] = 3 -> x_ExplicitVarSizeWithDummy[2] = 3, + sum([toInt(x_ExplicitVarSizeWithDummy[q4] != 3) | q4 : int(1..2)]) <= 2, + and([x_ExplicitVarSizeWithDummy[q7] != 3 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q7]] | q7 : int(1..2)]), + and([x_Occurrence[q8] -> + or([x_ExplicitVarSizeWithDummy[q10] != 3 /\ x_ExplicitVarSizeWithDummy[q10] = q8 | q10 : int(1..2)]) + | q8 : int(1..2)]) + diff --git a/tests/exhaustive/basic/set03/expected/model_1_3-solution000001.solution b/tests/exhaustive/basic/set03/expected/model_1_3-solution000001.solution new file mode 100644 index 0000000000..de5cc861ad --- /dev/null +++ b/tests/exhaustive/basic/set03/expected/model_1_3-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1} diff --git a/tests/exhaustive/basic/set03/expected/model_1_3-solution000002.solution b/tests/exhaustive/basic/set03/expected/model_1_3-solution000002.solution new file mode 100644 index 0000000000..f90e0ba18c --- /dev/null +++ b/tests/exhaustive/basic/set03/expected/model_1_3-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2} diff --git a/tests/exhaustive/basic/set03/expected/model_1_3.eprime b/tests/exhaustive/basic/set03/expected/model_1_3.eprime new file mode 100644 index 0000000000..6fb9afa1ba --- /dev/null +++ b/tests/exhaustive/basic/set03/expected/model_1_3.eprime @@ -0,0 +1,19 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(1..2)] of bool +find x_ExplicitVarSizeWithMarker_Marker: int(0..2) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..2)] of int(1..2) +branching on [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_Occurrence] +such that + x_Occurrence[1], + sum([toInt(x_Occurrence[q1]) | q1 : int(1..2)]) <= 2, + 2 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[1] < x_ExplicitVarSizeWithMarker_Values[2], + and([q3 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q3] = 1 | q3 : int(1..2)]), + x_ExplicitVarSizeWithMarker_Marker <= 2, + and([q6 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q6]] + | q6 : int(1..2)]), + and([x_Occurrence[q7] -> + or([q9 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q9] = q7 | q9 : int(1..2)]) + | q7 : int(1..2)]) + diff --git a/tests/exhaustive/basic/set03/expected/model_1_4-solution000001.solution b/tests/exhaustive/basic/set03/expected/model_1_4-solution000001.solution new file mode 100644 index 0000000000..de5cc861ad --- /dev/null +++ b/tests/exhaustive/basic/set03/expected/model_1_4-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1} diff --git a/tests/exhaustive/basic/set03/expected/model_1_4-solution000002.solution b/tests/exhaustive/basic/set03/expected/model_1_4-solution000002.solution new file mode 100644 index 0000000000..f90e0ba18c --- /dev/null +++ b/tests/exhaustive/basic/set03/expected/model_1_4-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2} diff --git a/tests/exhaustive/basic/set03/expected/model_1_4.eprime b/tests/exhaustive/basic/set03/expected/model_1_4.eprime new file mode 100644 index 0000000000..6301346892 --- /dev/null +++ b/tests/exhaustive/basic/set03/expected/model_1_4.eprime @@ -0,0 +1,18 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(1..2)] of bool +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..2)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..2)] of int(1..2) +branching on [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_Occurrence] +such that + x_Occurrence[1], + sum([toInt(x_Occurrence[q1]) | q1 : int(1..2)]) <= 2, + x_ExplicitVarSizeWithFlags_Flags[2] -> x_ExplicitVarSizeWithFlags_Values[1] < x_ExplicitVarSizeWithFlags_Values[2], + and([x_ExplicitVarSizeWithFlags_Flags[q3] = false -> x_ExplicitVarSizeWithFlags_Values[q3] = 1 | q3 : int(1..2)]), + x_ExplicitVarSizeWithFlags_Flags[2] -> x_ExplicitVarSizeWithFlags_Flags[1], + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q5]) | q5 : int(1..2)]) <= 2, + and([x_ExplicitVarSizeWithFlags_Flags[q8] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q8]] | q8 : int(1..2)]), + and([x_Occurrence[q9] -> + or([x_ExplicitVarSizeWithFlags_Flags[q11] /\ x_ExplicitVarSizeWithFlags_Values[q11] = q9 | q11 : int(1..2)]) + | q9 : int(1..2)]) + diff --git a/tests/exhaustive/basic/set03/expected/model_2_1-solution000001.solution b/tests/exhaustive/basic/set03/expected/model_2_1-solution000001.solution new file mode 100644 index 0000000000..de5cc861ad --- /dev/null +++ b/tests/exhaustive/basic/set03/expected/model_2_1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1} diff --git a/tests/exhaustive/basic/set03/expected/model_2_1-solution000002.solution b/tests/exhaustive/basic/set03/expected/model_2_1-solution000002.solution new file mode 100644 index 0000000000..f90e0ba18c --- /dev/null +++ b/tests/exhaustive/basic/set03/expected/model_2_1-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2} diff --git a/tests/exhaustive/basic/set03/expected/model_2_1.eprime b/tests/exhaustive/basic/set03/expected/model_2_1.eprime new file mode 100644 index 0000000000..b209f517b3 --- /dev/null +++ b/tests/exhaustive/basic/set03/expected/model_2_1.eprime @@ -0,0 +1,16 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..2)] of int(1..3) +find x_Occurrence: matrix indexed by [int(1..2)] of bool +branching on [x_Occurrence, x_ExplicitVarSizeWithDummy] +such that + or([x_ExplicitVarSizeWithDummy[q12] != 3 /\ x_ExplicitVarSizeWithDummy[q12] = 1 | q12 : int(1..2)]), + x_ExplicitVarSizeWithDummy[1] < x_ExplicitVarSizeWithDummy[2] \/ x_ExplicitVarSizeWithDummy[1] = 3, + x_ExplicitVarSizeWithDummy[1] = 3 -> x_ExplicitVarSizeWithDummy[2] = 3, + sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 3) | q3 : int(1..2)]) <= 2, + sum([toInt(x_Occurrence[q5]) | q5 : int(1..2)]) <= 2, + and([x_Occurrence[q6] -> + or([x_ExplicitVarSizeWithDummy[q8] != 3 /\ x_ExplicitVarSizeWithDummy[q8] = q6 | q8 : int(1..2)]) + | q6 : int(1..2)]), + and([x_ExplicitVarSizeWithDummy[q10] != 3 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q10]] | q10 : int(1..2)]) + diff --git a/tests/exhaustive/basic/set03/expected/model_2_2-solution000001.solution b/tests/exhaustive/basic/set03/expected/model_2_2-solution000001.solution new file mode 100644 index 0000000000..f90e0ba18c --- /dev/null +++ b/tests/exhaustive/basic/set03/expected/model_2_2-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2} diff --git a/tests/exhaustive/basic/set03/expected/model_2_2-solution000002.solution b/tests/exhaustive/basic/set03/expected/model_2_2-solution000002.solution new file mode 100644 index 0000000000..de5cc861ad --- /dev/null +++ b/tests/exhaustive/basic/set03/expected/model_2_2-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1} diff --git a/tests/exhaustive/basic/set03/expected/model_2_2.eprime b/tests/exhaustive/basic/set03/expected/model_2_2.eprime new file mode 100644 index 0000000000..99d5e5a575 --- /dev/null +++ b/tests/exhaustive/basic/set03/expected/model_2_2.eprime @@ -0,0 +1,10 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..2)] of int(1..3) +branching on [x_ExplicitVarSizeWithDummy] +such that + or([x_ExplicitVarSizeWithDummy[q6] != 3 /\ x_ExplicitVarSizeWithDummy[q6] = 1 | q6 : int(1..2)]), + x_ExplicitVarSizeWithDummy[1] < x_ExplicitVarSizeWithDummy[2] \/ x_ExplicitVarSizeWithDummy[1] = 3, + x_ExplicitVarSizeWithDummy[1] = 3 -> x_ExplicitVarSizeWithDummy[2] = 3, + sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 3) | q3 : int(1..2)]) <= 2 + diff --git a/tests/exhaustive/basic/set03/expected/model_2_3-solution000001.solution b/tests/exhaustive/basic/set03/expected/model_2_3-solution000001.solution new file mode 100644 index 0000000000..de5cc861ad --- /dev/null +++ b/tests/exhaustive/basic/set03/expected/model_2_3-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1} diff --git a/tests/exhaustive/basic/set03/expected/model_2_3-solution000002.solution b/tests/exhaustive/basic/set03/expected/model_2_3-solution000002.solution new file mode 100644 index 0000000000..f90e0ba18c --- /dev/null +++ b/tests/exhaustive/basic/set03/expected/model_2_3-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2} diff --git a/tests/exhaustive/basic/set03/expected/model_2_3.eprime b/tests/exhaustive/basic/set03/expected/model_2_3.eprime new file mode 100644 index 0000000000..94cefde44a --- /dev/null +++ b/tests/exhaustive/basic/set03/expected/model_2_3.eprime @@ -0,0 +1,26 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..2)] of int(1..3) +find x_ExplicitVarSizeWithMarker_Marker: int(0..2) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..2)] of int(1..2) +branching on [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy] +such that + or([x_ExplicitVarSizeWithDummy[q17] != 3 /\ x_ExplicitVarSizeWithDummy[q17] = 1 | q17 : int(1..2)]), + x_ExplicitVarSizeWithDummy[1] < x_ExplicitVarSizeWithDummy[2] \/ x_ExplicitVarSizeWithDummy[1] = 3, + x_ExplicitVarSizeWithDummy[1] = 3 -> x_ExplicitVarSizeWithDummy[2] = 3, + sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 3) | q3 : int(1..2)]) <= 2, + 2 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[1] < x_ExplicitVarSizeWithMarker_Values[2], + and([q6 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q6] = 1 | q6 : int(1..2)]), + x_ExplicitVarSizeWithMarker_Marker <= 2, + and([q9 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithDummy[q11] != 3 /\ + x_ExplicitVarSizeWithDummy[q11] = x_ExplicitVarSizeWithMarker_Values[q9] + | q11 : int(1..2)]) + | q9 : int(1..2)]), + and([x_ExplicitVarSizeWithDummy[q13] != 3 -> + or([q15 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q15] = x_ExplicitVarSizeWithDummy[q13] + | q15 : int(1..2)]) + | q13 : int(1..2)]) + diff --git a/tests/exhaustive/basic/set03/expected/model_2_4-solution000001.solution b/tests/exhaustive/basic/set03/expected/model_2_4-solution000001.solution new file mode 100644 index 0000000000..de5cc861ad --- /dev/null +++ b/tests/exhaustive/basic/set03/expected/model_2_4-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1} diff --git a/tests/exhaustive/basic/set03/expected/model_2_4-solution000002.solution b/tests/exhaustive/basic/set03/expected/model_2_4-solution000002.solution new file mode 100644 index 0000000000..f90e0ba18c --- /dev/null +++ b/tests/exhaustive/basic/set03/expected/model_2_4-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2} diff --git a/tests/exhaustive/basic/set03/expected/model_2_4.eprime b/tests/exhaustive/basic/set03/expected/model_2_4.eprime new file mode 100644 index 0000000000..3b3251ce37 --- /dev/null +++ b/tests/exhaustive/basic/set03/expected/model_2_4.eprime @@ -0,0 +1,26 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..2)] of int(1..3) +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..2)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..2)] of int(1..2) +branching on [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy] +such that + or([x_ExplicitVarSizeWithDummy[q19] != 3 /\ x_ExplicitVarSizeWithDummy[q19] = 1 | q19 : int(1..2)]), + x_ExplicitVarSizeWithDummy[1] < x_ExplicitVarSizeWithDummy[2] \/ x_ExplicitVarSizeWithDummy[1] = 3, + x_ExplicitVarSizeWithDummy[1] = 3 -> x_ExplicitVarSizeWithDummy[2] = 3, + sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 3) | q3 : int(1..2)]) <= 2, + x_ExplicitVarSizeWithFlags_Flags[2] -> x_ExplicitVarSizeWithFlags_Values[1] < x_ExplicitVarSizeWithFlags_Values[2], + and([x_ExplicitVarSizeWithFlags_Flags[q6] = false -> x_ExplicitVarSizeWithFlags_Values[q6] = 1 | q6 : int(1..2)]), + x_ExplicitVarSizeWithFlags_Flags[2] -> x_ExplicitVarSizeWithFlags_Flags[1], + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q8]) | q8 : int(1..2)]) <= 2, + and([x_ExplicitVarSizeWithFlags_Flags[q11] -> + or([x_ExplicitVarSizeWithDummy[q13] != 3 /\ + x_ExplicitVarSizeWithDummy[q13] = x_ExplicitVarSizeWithFlags_Values[q11] + | q13 : int(1..2)]) + | q11 : int(1..2)]), + and([x_ExplicitVarSizeWithDummy[q15] != 3 -> + or([x_ExplicitVarSizeWithFlags_Flags[q17] /\ + x_ExplicitVarSizeWithFlags_Values[q17] = x_ExplicitVarSizeWithDummy[q15] + | q17 : int(1..2)]) + | q15 : int(1..2)]) + diff --git a/tests/exhaustive/basic/set03/expected/model_3_1-solution000001.solution b/tests/exhaustive/basic/set03/expected/model_3_1-solution000001.solution new file mode 100644 index 0000000000..de5cc861ad --- /dev/null +++ b/tests/exhaustive/basic/set03/expected/model_3_1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1} diff --git a/tests/exhaustive/basic/set03/expected/model_3_1-solution000002.solution b/tests/exhaustive/basic/set03/expected/model_3_1-solution000002.solution new file mode 100644 index 0000000000..f90e0ba18c --- /dev/null +++ b/tests/exhaustive/basic/set03/expected/model_3_1-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2} diff --git a/tests/exhaustive/basic/set03/expected/model_3_1.eprime b/tests/exhaustive/basic/set03/expected/model_3_1.eprime new file mode 100644 index 0000000000..fe211d2c59 --- /dev/null +++ b/tests/exhaustive/basic/set03/expected/model_3_1.eprime @@ -0,0 +1,19 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..2) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..2)] of int(1..2) +find x_Occurrence: matrix indexed by [int(1..2)] of bool +branching on [x_Occurrence, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] +such that + or([q11 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q11] = 1 | q11 : int(1..2)]), + 2 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[1] < x_ExplicitVarSizeWithMarker_Values[2], + and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..2)]), + x_ExplicitVarSizeWithMarker_Marker <= 2, + sum([toInt(x_Occurrence[q4]) | q4 : int(1..2)]) <= 2, + and([x_Occurrence[q5] -> + or([q7 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q7] = q5 | q7 : int(1..2)]) + | q5 : int(1..2)]), + and([q9 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q9]] + | q9 : int(1..2)]) + diff --git a/tests/exhaustive/basic/set03/expected/model_3_2-solution000001.solution b/tests/exhaustive/basic/set03/expected/model_3_2-solution000001.solution new file mode 100644 index 0000000000..f90e0ba18c --- /dev/null +++ b/tests/exhaustive/basic/set03/expected/model_3_2-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2} diff --git a/tests/exhaustive/basic/set03/expected/model_3_2-solution000002.solution b/tests/exhaustive/basic/set03/expected/model_3_2-solution000002.solution new file mode 100644 index 0000000000..de5cc861ad --- /dev/null +++ b/tests/exhaustive/basic/set03/expected/model_3_2-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1} diff --git a/tests/exhaustive/basic/set03/expected/model_3_2.eprime b/tests/exhaustive/basic/set03/expected/model_3_2.eprime new file mode 100644 index 0000000000..f1ac7634ba --- /dev/null +++ b/tests/exhaustive/basic/set03/expected/model_3_2.eprime @@ -0,0 +1,26 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..2) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..2)] of int(1..2) +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..2)] of int(1..3) +branching on [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] +such that + or([q17 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q17] = 1 | q17 : int(1..2)]), + 2 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[1] < x_ExplicitVarSizeWithMarker_Values[2], + and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..2)]), + x_ExplicitVarSizeWithMarker_Marker <= 2, + x_ExplicitVarSizeWithDummy[1] < x_ExplicitVarSizeWithDummy[2] \/ x_ExplicitVarSizeWithDummy[1] = 3, + x_ExplicitVarSizeWithDummy[1] = 3 -> x_ExplicitVarSizeWithDummy[2] = 3, + sum([toInt(x_ExplicitVarSizeWithDummy[q6] != 3) | q6 : int(1..2)]) <= 2, + and([x_ExplicitVarSizeWithDummy[q9] != 3 -> + or([q11 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q11] = x_ExplicitVarSizeWithDummy[q9] + | q11 : int(1..2)]) + | q9 : int(1..2)]), + and([q13 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithDummy[q15] != 3 /\ + x_ExplicitVarSizeWithDummy[q15] = x_ExplicitVarSizeWithMarker_Values[q13] + | q15 : int(1..2)]) + | q13 : int(1..2)]) + diff --git a/tests/exhaustive/basic/set03/expected/model_3_3-solution000001.solution b/tests/exhaustive/basic/set03/expected/model_3_3-solution000001.solution new file mode 100644 index 0000000000..de5cc861ad --- /dev/null +++ b/tests/exhaustive/basic/set03/expected/model_3_3-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1} diff --git a/tests/exhaustive/basic/set03/expected/model_3_3-solution000002.solution b/tests/exhaustive/basic/set03/expected/model_3_3-solution000002.solution new file mode 100644 index 0000000000..f90e0ba18c --- /dev/null +++ b/tests/exhaustive/basic/set03/expected/model_3_3-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2} diff --git a/tests/exhaustive/basic/set03/expected/model_3_3.eprime b/tests/exhaustive/basic/set03/expected/model_3_3.eprime new file mode 100644 index 0000000000..aebac4895f --- /dev/null +++ b/tests/exhaustive/basic/set03/expected/model_3_3.eprime @@ -0,0 +1,12 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..2) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..2)] of int(1..2) +branching on [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] +such that + or([q5 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q5] = 1 | q5 : int(1..2)]), + 2 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[1] < x_ExplicitVarSizeWithMarker_Values[2], + and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..2)]), + x_ExplicitVarSizeWithMarker_Marker <= 2 + diff --git a/tests/exhaustive/basic/set03/expected/model_3_4-solution000001.solution b/tests/exhaustive/basic/set03/expected/model_3_4-solution000001.solution new file mode 100644 index 0000000000..de5cc861ad --- /dev/null +++ b/tests/exhaustive/basic/set03/expected/model_3_4-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1} diff --git a/tests/exhaustive/basic/set03/expected/model_3_4-solution000002.solution b/tests/exhaustive/basic/set03/expected/model_3_4-solution000002.solution new file mode 100644 index 0000000000..f90e0ba18c --- /dev/null +++ b/tests/exhaustive/basic/set03/expected/model_3_4-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2} diff --git a/tests/exhaustive/basic/set03/expected/model_3_4.eprime b/tests/exhaustive/basic/set03/expected/model_3_4.eprime new file mode 100644 index 0000000000..c839c9c5b8 --- /dev/null +++ b/tests/exhaustive/basic/set03/expected/model_3_4.eprime @@ -0,0 +1,30 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..2) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..2)] of int(1..2) +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..2)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..2)] of int(1..2) +branching on + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithMarker_Marker, + x_ExplicitVarSizeWithMarker_Values] +such that + or([q18 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q18] = 1 | q18 : int(1..2)]), + 2 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[1] < x_ExplicitVarSizeWithMarker_Values[2], + and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..2)]), + x_ExplicitVarSizeWithMarker_Marker <= 2, + x_ExplicitVarSizeWithFlags_Flags[2] -> x_ExplicitVarSizeWithFlags_Values[1] < x_ExplicitVarSizeWithFlags_Values[2], + and([x_ExplicitVarSizeWithFlags_Flags[q5] = false -> x_ExplicitVarSizeWithFlags_Values[q5] = 1 | q5 : int(1..2)]), + x_ExplicitVarSizeWithFlags_Flags[2] -> x_ExplicitVarSizeWithFlags_Flags[1], + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q7]) | q7 : int(1..2)]) <= 2, + and([x_ExplicitVarSizeWithFlags_Flags[q10] -> + or([q12 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q12] = x_ExplicitVarSizeWithFlags_Values[q10] + | q12 : int(1..2)]) + | q10 : int(1..2)]), + and([q14 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithFlags_Flags[q16] /\ + x_ExplicitVarSizeWithFlags_Values[q16] = x_ExplicitVarSizeWithMarker_Values[q14] + | q16 : int(1..2)]) + | q14 : int(1..2)]) + diff --git a/tests/exhaustive/basic/set03/expected/model_4_1-solution000001.solution b/tests/exhaustive/basic/set03/expected/model_4_1-solution000001.solution new file mode 100644 index 0000000000..de5cc861ad --- /dev/null +++ b/tests/exhaustive/basic/set03/expected/model_4_1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1} diff --git a/tests/exhaustive/basic/set03/expected/model_4_1-solution000002.solution b/tests/exhaustive/basic/set03/expected/model_4_1-solution000002.solution new file mode 100644 index 0000000000..f90e0ba18c --- /dev/null +++ b/tests/exhaustive/basic/set03/expected/model_4_1-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2} diff --git a/tests/exhaustive/basic/set03/expected/model_4_1.eprime b/tests/exhaustive/basic/set03/expected/model_4_1.eprime new file mode 100644 index 0000000000..248c3e3b42 --- /dev/null +++ b/tests/exhaustive/basic/set03/expected/model_4_1.eprime @@ -0,0 +1,19 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..2)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..2)] of int(1..2) +find x_Occurrence: matrix indexed by [int(1..2)] of bool +branching on [x_Occurrence, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] +such that + or([x_ExplicitVarSizeWithFlags_Flags[q13] /\ x_ExplicitVarSizeWithFlags_Values[q13] = 1 | q13 : int(1..2)]), + x_ExplicitVarSizeWithFlags_Flags[2] -> x_ExplicitVarSizeWithFlags_Values[1] < x_ExplicitVarSizeWithFlags_Values[2], + and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..2)]), + x_ExplicitVarSizeWithFlags_Flags[2] -> x_ExplicitVarSizeWithFlags_Flags[1], + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..2)]) <= 2, + sum([toInt(x_Occurrence[q6]) | q6 : int(1..2)]) <= 2, + and([x_Occurrence[q7] -> + or([x_ExplicitVarSizeWithFlags_Flags[q9] /\ x_ExplicitVarSizeWithFlags_Values[q9] = q7 | q9 : int(1..2)]) + | q7 : int(1..2)]), + and([x_ExplicitVarSizeWithFlags_Flags[q11] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q11]] + | q11 : int(1..2)]) + diff --git a/tests/exhaustive/basic/set03/expected/model_4_2-solution000001.solution b/tests/exhaustive/basic/set03/expected/model_4_2-solution000001.solution new file mode 100644 index 0000000000..f90e0ba18c --- /dev/null +++ b/tests/exhaustive/basic/set03/expected/model_4_2-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2} diff --git a/tests/exhaustive/basic/set03/expected/model_4_2-solution000002.solution b/tests/exhaustive/basic/set03/expected/model_4_2-solution000002.solution new file mode 100644 index 0000000000..de5cc861ad --- /dev/null +++ b/tests/exhaustive/basic/set03/expected/model_4_2-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1} diff --git a/tests/exhaustive/basic/set03/expected/model_4_2.eprime b/tests/exhaustive/basic/set03/expected/model_4_2.eprime new file mode 100644 index 0000000000..ab8292a451 --- /dev/null +++ b/tests/exhaustive/basic/set03/expected/model_4_2.eprime @@ -0,0 +1,26 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..2)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..2)] of int(1..2) +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..2)] of int(1..3) +branching on [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] +such that + or([x_ExplicitVarSizeWithFlags_Flags[q19] /\ x_ExplicitVarSizeWithFlags_Values[q19] = 1 | q19 : int(1..2)]), + x_ExplicitVarSizeWithFlags_Flags[2] -> x_ExplicitVarSizeWithFlags_Values[1] < x_ExplicitVarSizeWithFlags_Values[2], + and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..2)]), + x_ExplicitVarSizeWithFlags_Flags[2] -> x_ExplicitVarSizeWithFlags_Flags[1], + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..2)]) <= 2, + x_ExplicitVarSizeWithDummy[1] < x_ExplicitVarSizeWithDummy[2] \/ x_ExplicitVarSizeWithDummy[1] = 3, + x_ExplicitVarSizeWithDummy[1] = 3 -> x_ExplicitVarSizeWithDummy[2] = 3, + sum([toInt(x_ExplicitVarSizeWithDummy[q8] != 3) | q8 : int(1..2)]) <= 2, + and([x_ExplicitVarSizeWithDummy[q11] != 3 -> + or([x_ExplicitVarSizeWithFlags_Flags[q13] /\ + x_ExplicitVarSizeWithFlags_Values[q13] = x_ExplicitVarSizeWithDummy[q11] + | q13 : int(1..2)]) + | q11 : int(1..2)]), + and([x_ExplicitVarSizeWithFlags_Flags[q15] -> + or([x_ExplicitVarSizeWithDummy[q17] != 3 /\ + x_ExplicitVarSizeWithDummy[q17] = x_ExplicitVarSizeWithFlags_Values[q15] + | q17 : int(1..2)]) + | q15 : int(1..2)]) + diff --git a/tests/exhaustive/basic/set03/expected/model_4_3-solution000001.solution b/tests/exhaustive/basic/set03/expected/model_4_3-solution000001.solution new file mode 100644 index 0000000000..de5cc861ad --- /dev/null +++ b/tests/exhaustive/basic/set03/expected/model_4_3-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1} diff --git a/tests/exhaustive/basic/set03/expected/model_4_3-solution000002.solution b/tests/exhaustive/basic/set03/expected/model_4_3-solution000002.solution new file mode 100644 index 0000000000..f90e0ba18c --- /dev/null +++ b/tests/exhaustive/basic/set03/expected/model_4_3-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2} diff --git a/tests/exhaustive/basic/set03/expected/model_4_3.eprime b/tests/exhaustive/basic/set03/expected/model_4_3.eprime new file mode 100644 index 0000000000..3a1cb29286 --- /dev/null +++ b/tests/exhaustive/basic/set03/expected/model_4_3.eprime @@ -0,0 +1,30 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..2)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..2)] of int(1..2) +find x_ExplicitVarSizeWithMarker_Marker: int(0..2) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..2)] of int(1..2) +branching on + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithFlags_Flags, + x_ExplicitVarSizeWithFlags_Values] +such that + or([x_ExplicitVarSizeWithFlags_Flags[q18] /\ x_ExplicitVarSizeWithFlags_Values[q18] = 1 | q18 : int(1..2)]), + x_ExplicitVarSizeWithFlags_Flags[2] -> x_ExplicitVarSizeWithFlags_Values[1] < x_ExplicitVarSizeWithFlags_Values[2], + and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..2)]), + x_ExplicitVarSizeWithFlags_Flags[2] -> x_ExplicitVarSizeWithFlags_Flags[1], + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..2)]) <= 2, + 2 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[1] < x_ExplicitVarSizeWithMarker_Values[2], + and([q7 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q7] = 1 | q7 : int(1..2)]), + x_ExplicitVarSizeWithMarker_Marker <= 2, + and([q10 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithFlags_Flags[q12] /\ + x_ExplicitVarSizeWithFlags_Values[q12] = x_ExplicitVarSizeWithMarker_Values[q10] + | q12 : int(1..2)]) + | q10 : int(1..2)]), + and([x_ExplicitVarSizeWithFlags_Flags[q14] -> + or([q16 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q16] = x_ExplicitVarSizeWithFlags_Values[q14] + | q16 : int(1..2)]) + | q14 : int(1..2)]) + diff --git a/tests/exhaustive/basic/set03/expected/model_4_4-solution000001.solution b/tests/exhaustive/basic/set03/expected/model_4_4-solution000001.solution new file mode 100644 index 0000000000..de5cc861ad --- /dev/null +++ b/tests/exhaustive/basic/set03/expected/model_4_4-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1} diff --git a/tests/exhaustive/basic/set03/expected/model_4_4-solution000002.solution b/tests/exhaustive/basic/set03/expected/model_4_4-solution000002.solution new file mode 100644 index 0000000000..f90e0ba18c --- /dev/null +++ b/tests/exhaustive/basic/set03/expected/model_4_4-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2} diff --git a/tests/exhaustive/basic/set03/expected/model_4_4.eprime b/tests/exhaustive/basic/set03/expected/model_4_4.eprime new file mode 100644 index 0000000000..ec9b61f711 --- /dev/null +++ b/tests/exhaustive/basic/set03/expected/model_4_4.eprime @@ -0,0 +1,12 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..2)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..2)] of int(1..2) +branching on [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] +such that + or([x_ExplicitVarSizeWithFlags_Flags[q7] /\ x_ExplicitVarSizeWithFlags_Values[q7] = 1 | q7 : int(1..2)]), + x_ExplicitVarSizeWithFlags_Flags[2] -> x_ExplicitVarSizeWithFlags_Values[1] < x_ExplicitVarSizeWithFlags_Values[2], + and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..2)]), + x_ExplicitVarSizeWithFlags_Flags[2] -> x_ExplicitVarSizeWithFlags_Flags[1], + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..2)]) <= 2 + diff --git a/tests/exhaustive/basic/set04/expected/model_1_1_1-solution000001.solution b/tests/exhaustive/basic/set04/expected/model_1_1_1-solution000001.solution new file mode 100644 index 0000000000..f90e0ba18c --- /dev/null +++ b/tests/exhaustive/basic/set04/expected/model_1_1_1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2} diff --git a/tests/exhaustive/basic/set04/expected/model_1_1_1-solution000002.solution b/tests/exhaustive/basic/set04/expected/model_1_1_1-solution000002.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set04/expected/model_1_1_1-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set04/expected/model_1_1_1.eprime b/tests/exhaustive/basic/set04/expected/model_1_1_1.eprime new file mode 100644 index 0000000000..758eeb2d3a --- /dev/null +++ b/tests/exhaustive/basic/set04/expected/model_1_1_1.eprime @@ -0,0 +1,9 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(1..3)] of bool +branching on [x_Occurrence] +such that + x_Occurrence[1], + x_Occurrence[2], + sum([toInt(x_Occurrence[q1]) | q1 : int(1..3)]) <= 3 + diff --git a/tests/exhaustive/basic/set04/expected/model_1_1_2-solution000001.solution b/tests/exhaustive/basic/set04/expected/model_1_1_2-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set04/expected/model_1_1_2-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set04/expected/model_1_1_2-solution000002.solution b/tests/exhaustive/basic/set04/expected/model_1_1_2-solution000002.solution new file mode 100644 index 0000000000..f90e0ba18c --- /dev/null +++ b/tests/exhaustive/basic/set04/expected/model_1_1_2-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_2_2.eprime.orig b/tests/exhaustive/basic/set04/expected/model_1_1_2.eprime similarity index 72% rename from tests/exhaustive/basic/cut_01_on/expected/model_1_2_2.eprime.orig rename to tests/exhaustive/basic/set04/expected/model_1_1_2.eprime index bdba13c665..f368f0ac5a 100644 --- a/tests/exhaustive/basic/cut_01_on/expected/model_1_2_2.eprime.orig +++ b/tests/exhaustive/basic/set04/expected/model_1_1_2.eprime @@ -2,15 +2,15 @@ language ESSENCE' 1.0 find x_Occurrence: matrix indexed by [int(1..3)] of bool find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..3)] of int(1..4) -find cut1: bool -find cut2: bool -branching on [cut1, cut2, x_ExplicitVarSizeWithDummy, x_Occurrence] +branching on [x_ExplicitVarSizeWithDummy, x_Occurrence] such that - !cut1 <-> x_Occurrence[1] /\ x_Occurrence[2], - !cut2 <-> or([x_ExplicitVarSizeWithDummy[q13] != 4 /\ x_ExplicitVarSizeWithDummy[q13] = 1 | q13 : int(1..3)]), + x_Occurrence[1], + x_Occurrence[2], + sum([toInt(x_Occurrence[q1]) | q1 : int(1..3)]) <= 3, and([x_ExplicitVarSizeWithDummy[q2] < x_ExplicitVarSizeWithDummy[q2 + 1] \/ x_ExplicitVarSizeWithDummy[q2] = 4 | q2 : int(1..2)]), and([x_ExplicitVarSizeWithDummy[q3] = 4 -> x_ExplicitVarSizeWithDummy[q3 + 1] = 4 | q3 : int(1..2)]), + sum([toInt(x_ExplicitVarSizeWithDummy[q4] != 4) | q4 : int(1..3)]) <= 3, and([x_ExplicitVarSizeWithDummy[q7] != 4 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q7]] | q7 : int(1..3)]), and([x_Occurrence[q8] -> or([x_ExplicitVarSizeWithDummy[q10] != 4 /\ x_ExplicitVarSizeWithDummy[q10] = q8 | q10 : int(1..3)]) diff --git a/tests/exhaustive/basic/set04/expected/model_1_1_3-solution000001.solution b/tests/exhaustive/basic/set04/expected/model_1_1_3-solution000001.solution new file mode 100644 index 0000000000..f90e0ba18c --- /dev/null +++ b/tests/exhaustive/basic/set04/expected/model_1_1_3-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2} diff --git a/tests/exhaustive/basic/set04/expected/model_1_1_3-solution000002.solution b/tests/exhaustive/basic/set04/expected/model_1_1_3-solution000002.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set04/expected/model_1_1_3-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_3_3.eprime.orig b/tests/exhaustive/basic/set04/expected/model_1_1_3.eprime similarity index 72% rename from tests/exhaustive/basic/cut_01_on/expected/model_1_3_3.eprime.orig rename to tests/exhaustive/basic/set04/expected/model_1_1_3.eprime index e0ba9b28e5..2eabb913cf 100644 --- a/tests/exhaustive/basic/cut_01_on/expected/model_1_3_3.eprime.orig +++ b/tests/exhaustive/basic/set04/expected/model_1_1_3.eprime @@ -3,17 +3,16 @@ language ESSENCE' 1.0 find x_Occurrence: matrix indexed by [int(1..3)] of bool find x_ExplicitVarSizeWithMarker_Marker: int(0..3) find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3)] of int(1..3) -find cut1: bool -find cut2: bool -branching on [cut1, cut2, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_Occurrence] +branching on [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_Occurrence] such that - !cut1 <-> x_Occurrence[1] /\ x_Occurrence[2], - !cut2 <-> - or([q12 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q12] = 1 | q12 : int(1..3)]), + x_Occurrence[1], + x_Occurrence[2], + sum([toInt(x_Occurrence[q1]) | q1 : int(1..3)]) <= 3, and([q2 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] < x_ExplicitVarSizeWithMarker_Values[q2 + 1] | q2 : int(1..2)]), and([q3 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q3] = 1 | q3 : int(1..3)]), + x_ExplicitVarSizeWithMarker_Marker <= 3, and([q6 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q6]] | q6 : int(1..3)]), and([x_Occurrence[q7] -> diff --git a/tests/exhaustive/basic/set04/expected/model_1_1_4-solution000001.solution b/tests/exhaustive/basic/set04/expected/model_1_1_4-solution000001.solution new file mode 100644 index 0000000000..f90e0ba18c --- /dev/null +++ b/tests/exhaustive/basic/set04/expected/model_1_1_4-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2} diff --git a/tests/exhaustive/basic/set04/expected/model_1_1_4-solution000002.solution b/tests/exhaustive/basic/set04/expected/model_1_1_4-solution000002.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set04/expected/model_1_1_4-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_4_4.eprime.orig b/tests/exhaustive/basic/set04/expected/model_1_1_4.eprime similarity index 75% rename from tests/exhaustive/basic/cut_01_on/expected/model_1_4_4.eprime.orig rename to tests/exhaustive/basic/set04/expected/model_1_1_4.eprime index 59c07401b5..ab61dc16a9 100644 --- a/tests/exhaustive/basic/cut_01_on/expected/model_1_4_4.eprime.orig +++ b/tests/exhaustive/basic/set04/expected/model_1_1_4.eprime @@ -3,18 +3,17 @@ language ESSENCE' 1.0 find x_Occurrence: matrix indexed by [int(1..3)] of bool find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..3)] of bool find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3)] of int(1..3) -find cut1: bool -find cut2: bool -branching on [cut1, cut2, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_Occurrence] +branching on [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_Occurrence] such that - !cut1 <-> x_Occurrence[1] /\ x_Occurrence[2], - !cut2 <-> - or([x_ExplicitVarSizeWithFlags_Flags[q14] /\ x_ExplicitVarSizeWithFlags_Values[q14] = 1 | q14 : int(1..3)]), + x_Occurrence[1], + x_Occurrence[2], + sum([toInt(x_Occurrence[q1]) | q1 : int(1..3)]) <= 3, and([x_ExplicitVarSizeWithFlags_Flags[q2 + 1] -> x_ExplicitVarSizeWithFlags_Values[q2] < x_ExplicitVarSizeWithFlags_Values[q2 + 1] | q2 : int(1..2)]), and([x_ExplicitVarSizeWithFlags_Flags[q3] = false -> x_ExplicitVarSizeWithFlags_Values[q3] = 1 | q3 : int(1..3)]), and([x_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q4] | q4 : int(1..2)]), + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q5]) | q5 : int(1..3)]) <= 3, and([x_ExplicitVarSizeWithFlags_Flags[q8] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q8]] | q8 : int(1..3)]), and([x_Occurrence[q9] -> or([x_ExplicitVarSizeWithFlags_Flags[q11] /\ x_ExplicitVarSizeWithFlags_Values[q11] = q9 | q11 : int(1..3)]) diff --git a/tests/exhaustive/basic/set04/expected/model_1_2_1-solution000001.solution b/tests/exhaustive/basic/set04/expected/model_1_2_1-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set04/expected/model_1_2_1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set04/expected/model_1_2_1-solution000002.solution b/tests/exhaustive/basic/set04/expected/model_1_2_1-solution000002.solution new file mode 100644 index 0000000000..f90e0ba18c --- /dev/null +++ b/tests/exhaustive/basic/set04/expected/model_1_2_1-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2} diff --git a/tests/exhaustive/basic/set04/expected/model_1_2_1.eprime b/tests/exhaustive/basic/set04/expected/model_1_2_1.eprime new file mode 100644 index 0000000000..f3b700efaf --- /dev/null +++ b/tests/exhaustive/basic/set04/expected/model_1_2_1.eprime @@ -0,0 +1,18 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(1..3)] of bool +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..3)] of int(1..4) +branching on [x_ExplicitVarSizeWithDummy, x_Occurrence] +such that + x_Occurrence[1], + or([x_ExplicitVarSizeWithDummy[q12] != 4 /\ x_ExplicitVarSizeWithDummy[q12] = 2 | q12 : int(1..3)]), + sum([toInt(x_Occurrence[q1]) | q1 : int(1..3)]) <= 3, + and([x_ExplicitVarSizeWithDummy[q2] < x_ExplicitVarSizeWithDummy[q2 + 1] \/ x_ExplicitVarSizeWithDummy[q2] = 4 + | q2 : int(1..2)]), + and([x_ExplicitVarSizeWithDummy[q3] = 4 -> x_ExplicitVarSizeWithDummy[q3 + 1] = 4 | q3 : int(1..2)]), + sum([toInt(x_ExplicitVarSizeWithDummy[q4] != 4) | q4 : int(1..3)]) <= 3, + and([x_ExplicitVarSizeWithDummy[q7] != 4 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q7]] | q7 : int(1..3)]), + and([x_Occurrence[q8] -> + or([x_ExplicitVarSizeWithDummy[q10] != 4 /\ x_ExplicitVarSizeWithDummy[q10] = q8 | q10 : int(1..3)]) + | q8 : int(1..3)]) + diff --git a/tests/exhaustive/basic/set04/expected/model_1_2_3-solution000001.solution b/tests/exhaustive/basic/set04/expected/model_1_2_3-solution000001.solution new file mode 100644 index 0000000000..f90e0ba18c --- /dev/null +++ b/tests/exhaustive/basic/set04/expected/model_1_2_3-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2} diff --git a/tests/exhaustive/basic/set04/expected/model_1_2_3-solution000002.solution b/tests/exhaustive/basic/set04/expected/model_1_2_3-solution000002.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set04/expected/model_1_2_3-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_2_3.eprime.orig b/tests/exhaustive/basic/set04/expected/model_1_2_3.eprime similarity index 82% rename from tests/exhaustive/basic/cut_01_on/expected/model_1_2_3.eprime.orig rename to tests/exhaustive/basic/set04/expected/model_1_2_3.eprime index ae3d5b6397..72080d2343 100644 --- a/tests/exhaustive/basic/cut_01_on/expected/model_1_2_3.eprime.orig +++ b/tests/exhaustive/basic/set04/expected/model_1_2_3.eprime @@ -4,17 +4,16 @@ find x_Occurrence: matrix indexed by [int(1..3)] of bool find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..3)] of int(1..4) find x_ExplicitVarSizeWithMarker_Marker: int(0..3) find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3)] of int(1..3) -find cut1: bool -find cut2: bool branching on - [cut1, cut2, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_Occurrence, - x_ExplicitVarSizeWithDummy] + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_Occurrence, x_ExplicitVarSizeWithDummy] such that - !cut1 <-> x_Occurrence[1] /\ x_Occurrence[2], - !cut2 <-> or([x_ExplicitVarSizeWithDummy[q29] != 4 /\ x_ExplicitVarSizeWithDummy[q29] = 1 | q29 : int(1..3)]), + x_Occurrence[1], + or([x_ExplicitVarSizeWithDummy[q28] != 4 /\ x_ExplicitVarSizeWithDummy[q28] = 2 | q28 : int(1..3)]), + sum([toInt(x_Occurrence[q1]) | q1 : int(1..3)]) <= 3, and([x_ExplicitVarSizeWithDummy[q2] < x_ExplicitVarSizeWithDummy[q2 + 1] \/ x_ExplicitVarSizeWithDummy[q2] = 4 | q2 : int(1..2)]), and([x_ExplicitVarSizeWithDummy[q3] = 4 -> x_ExplicitVarSizeWithDummy[q3 + 1] = 4 | q3 : int(1..2)]), + sum([toInt(x_ExplicitVarSizeWithDummy[q4] != 4) | q4 : int(1..3)]) <= 3, and([x_ExplicitVarSizeWithDummy[q7] != 4 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q7]] | q7 : int(1..3)]), and([x_Occurrence[q8] -> or([x_ExplicitVarSizeWithDummy[q10] != 4 /\ x_ExplicitVarSizeWithDummy[q10] = q8 | q10 : int(1..3)]) @@ -23,6 +22,7 @@ such that x_ExplicitVarSizeWithMarker_Values[q11] < x_ExplicitVarSizeWithMarker_Values[q11 + 1] | q11 : int(1..2)]), and([q12 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q12] = 1 | q12 : int(1..3)]), + x_ExplicitVarSizeWithMarker_Marker <= 3, and([q15 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q15]] | q15 : int(1..3)]), and([x_Occurrence[q16] -> diff --git a/tests/exhaustive/basic/set04/expected/model_1_2_4-solution000001.solution b/tests/exhaustive/basic/set04/expected/model_1_2_4-solution000001.solution new file mode 100644 index 0000000000..f90e0ba18c --- /dev/null +++ b/tests/exhaustive/basic/set04/expected/model_1_2_4-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2} diff --git a/tests/exhaustive/basic/set04/expected/model_1_2_4-solution000002.solution b/tests/exhaustive/basic/set04/expected/model_1_2_4-solution000002.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set04/expected/model_1_2_4-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_2_4.eprime.orig b/tests/exhaustive/basic/set04/expected/model_1_2_4.eprime similarity index 82% rename from tests/exhaustive/basic/cut_01_on/expected/model_1_2_4.eprime.orig rename to tests/exhaustive/basic/set04/expected/model_1_2_4.eprime index 51db4a59f6..245f216d5c 100644 --- a/tests/exhaustive/basic/cut_01_on/expected/model_1_2_4.eprime.orig +++ b/tests/exhaustive/basic/set04/expected/model_1_2_4.eprime @@ -4,17 +4,16 @@ find x_Occurrence: matrix indexed by [int(1..3)] of bool find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..3)] of int(1..4) find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..3)] of bool find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3)] of int(1..3) -find cut1: bool -find cut2: bool branching on - [cut1, cut2, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_Occurrence, - x_ExplicitVarSizeWithDummy] + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_Occurrence, x_ExplicitVarSizeWithDummy] such that - !cut1 <-> x_Occurrence[1] /\ x_Occurrence[2], - !cut2 <-> or([x_ExplicitVarSizeWithDummy[q31] != 4 /\ x_ExplicitVarSizeWithDummy[q31] = 1 | q31 : int(1..3)]), + x_Occurrence[1], + or([x_ExplicitVarSizeWithDummy[q30] != 4 /\ x_ExplicitVarSizeWithDummy[q30] = 2 | q30 : int(1..3)]), + sum([toInt(x_Occurrence[q1]) | q1 : int(1..3)]) <= 3, and([x_ExplicitVarSizeWithDummy[q2] < x_ExplicitVarSizeWithDummy[q2 + 1] \/ x_ExplicitVarSizeWithDummy[q2] = 4 | q2 : int(1..2)]), and([x_ExplicitVarSizeWithDummy[q3] = 4 -> x_ExplicitVarSizeWithDummy[q3 + 1] = 4 | q3 : int(1..2)]), + sum([toInt(x_ExplicitVarSizeWithDummy[q4] != 4) | q4 : int(1..3)]) <= 3, and([x_ExplicitVarSizeWithDummy[q7] != 4 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q7]] | q7 : int(1..3)]), and([x_Occurrence[q8] -> or([x_ExplicitVarSizeWithDummy[q10] != 4 /\ x_ExplicitVarSizeWithDummy[q10] = q8 | q10 : int(1..3)]) @@ -25,6 +24,7 @@ such that and([x_ExplicitVarSizeWithFlags_Flags[q12] = false -> x_ExplicitVarSizeWithFlags_Values[q12] = 1 | q12 : int(1..3)]), and([x_ExplicitVarSizeWithFlags_Flags[q13 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q13] | q13 : int(1..2)]), + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q14]) | q14 : int(1..3)]) <= 3, and([x_ExplicitVarSizeWithFlags_Flags[q17] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q17]] | q17 : int(1..3)]), and([x_Occurrence[q18] -> diff --git a/tests/exhaustive/basic/set04/expected/model_1_3_1-solution000001.solution b/tests/exhaustive/basic/set04/expected/model_1_3_1-solution000001.solution new file mode 100644 index 0000000000..f90e0ba18c --- /dev/null +++ b/tests/exhaustive/basic/set04/expected/model_1_3_1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2} diff --git a/tests/exhaustive/basic/set04/expected/model_1_3_1-solution000002.solution b/tests/exhaustive/basic/set04/expected/model_1_3_1-solution000002.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set04/expected/model_1_3_1-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set04/expected/model_1_3_1.eprime b/tests/exhaustive/basic/set04/expected/model_1_3_1.eprime new file mode 100644 index 0000000000..567ac8830a --- /dev/null +++ b/tests/exhaustive/basic/set04/expected/model_1_3_1.eprime @@ -0,0 +1,21 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(1..3)] of bool +find x_ExplicitVarSizeWithMarker_Marker: int(0..3) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3)] of int(1..3) +branching on [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_Occurrence] +such that + x_Occurrence[1], + or([q11 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q11] = 2 | q11 : int(1..3)]), + sum([toInt(x_Occurrence[q1]) | q1 : int(1..3)]) <= 3, + and([q2 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q2] < x_ExplicitVarSizeWithMarker_Values[q2 + 1] + | q2 : int(1..2)]), + and([q3 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q3] = 1 | q3 : int(1..3)]), + x_ExplicitVarSizeWithMarker_Marker <= 3, + and([q6 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q6]] + | q6 : int(1..3)]), + and([x_Occurrence[q7] -> + or([q9 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q9] = q7 | q9 : int(1..3)]) + | q7 : int(1..3)]) + diff --git a/tests/exhaustive/basic/set04/expected/model_1_3_2-solution000001.solution b/tests/exhaustive/basic/set04/expected/model_1_3_2-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set04/expected/model_1_3_2-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set04/expected/model_1_3_2-solution000002.solution b/tests/exhaustive/basic/set04/expected/model_1_3_2-solution000002.solution new file mode 100644 index 0000000000..f90e0ba18c --- /dev/null +++ b/tests/exhaustive/basic/set04/expected/model_1_3_2-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_3_2.eprime.orig b/tests/exhaustive/basic/set04/expected/model_1_3_2.eprime similarity index 82% rename from tests/exhaustive/basic/cut_01_on/expected/model_1_3_2.eprime.orig rename to tests/exhaustive/basic/set04/expected/model_1_3_2.eprime index 73bccb6f90..8afee978bf 100644 --- a/tests/exhaustive/basic/cut_01_on/expected/model_1_3_2.eprime.orig +++ b/tests/exhaustive/basic/set04/expected/model_1_3_2.eprime @@ -4,19 +4,17 @@ find x_Occurrence: matrix indexed by [int(1..3)] of bool find x_ExplicitVarSizeWithMarker_Marker: int(0..3) find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3)] of int(1..3) find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..3)] of int(1..4) -find cut1: bool -find cut2: bool branching on - [cut1, cut2, x_ExplicitVarSizeWithDummy, x_Occurrence, x_ExplicitVarSizeWithMarker_Marker, - x_ExplicitVarSizeWithMarker_Values] + [x_ExplicitVarSizeWithDummy, x_Occurrence, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] such that - !cut1 <-> x_Occurrence[1] /\ x_Occurrence[2], - !cut2 <-> - or([q29 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q29] = 1 | q29 : int(1..3)]), + x_Occurrence[1], + or([q28 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q28] = 2 | q28 : int(1..3)]), + sum([toInt(x_Occurrence[q1]) | q1 : int(1..3)]) <= 3, and([q2 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] < x_ExplicitVarSizeWithMarker_Values[q2 + 1] | q2 : int(1..2)]), and([q3 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q3] = 1 | q3 : int(1..3)]), + x_ExplicitVarSizeWithMarker_Marker <= 3, and([q6 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q6]] | q6 : int(1..3)]), and([x_Occurrence[q7] -> @@ -25,6 +23,7 @@ such that and([x_ExplicitVarSizeWithDummy[q10] < x_ExplicitVarSizeWithDummy[q10 + 1] \/ x_ExplicitVarSizeWithDummy[q10] = 4 | q10 : int(1..2)]), and([x_ExplicitVarSizeWithDummy[q11] = 4 -> x_ExplicitVarSizeWithDummy[q11 + 1] = 4 | q11 : int(1..2)]), + sum([toInt(x_ExplicitVarSizeWithDummy[q12] != 4) | q12 : int(1..3)]) <= 3, and([x_ExplicitVarSizeWithDummy[q15] != 4 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q15]] | q15 : int(1..3)]), and([x_Occurrence[q16] -> or([x_ExplicitVarSizeWithDummy[q18] != 4 /\ x_ExplicitVarSizeWithDummy[q18] = q16 | q18 : int(1..3)]) diff --git a/tests/exhaustive/basic/set04/expected/model_1_3_4-solution000001.solution b/tests/exhaustive/basic/set04/expected/model_1_3_4-solution000001.solution new file mode 100644 index 0000000000..f90e0ba18c --- /dev/null +++ b/tests/exhaustive/basic/set04/expected/model_1_3_4-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2} diff --git a/tests/exhaustive/basic/set04/expected/model_1_3_4-solution000002.solution b/tests/exhaustive/basic/set04/expected/model_1_3_4-solution000002.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set04/expected/model_1_3_4-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_3_4.eprime.orig b/tests/exhaustive/basic/set04/expected/model_1_3_4.eprime similarity index 85% rename from tests/exhaustive/basic/cut_01_on/expected/model_1_3_4.eprime.orig rename to tests/exhaustive/basic/set04/expected/model_1_3_4.eprime index 3b9d9c1c5b..6d2bd5ff5b 100644 --- a/tests/exhaustive/basic/cut_01_on/expected/model_1_3_4.eprime.orig +++ b/tests/exhaustive/basic/set04/expected/model_1_3_4.eprime @@ -5,19 +5,18 @@ find x_ExplicitVarSizeWithMarker_Marker: int(0..3) find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3)] of int(1..3) find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..3)] of bool find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3)] of int(1..3) -find cut1: bool -find cut2: bool branching on - [cut1, cut2, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_Occurrence, + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_Occurrence, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] such that - !cut1 <-> x_Occurrence[1] /\ x_Occurrence[2], - !cut2 <-> - or([q30 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q30] = 1 | q30 : int(1..3)]), + x_Occurrence[1], + or([q29 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q29] = 2 | q29 : int(1..3)]), + sum([toInt(x_Occurrence[q1]) | q1 : int(1..3)]) <= 3, and([q2 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] < x_ExplicitVarSizeWithMarker_Values[q2 + 1] | q2 : int(1..2)]), and([q3 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q3] = 1 | q3 : int(1..3)]), + x_ExplicitVarSizeWithMarker_Marker <= 3, and([q6 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q6]] | q6 : int(1..3)]), and([x_Occurrence[q7] -> @@ -29,6 +28,7 @@ such that and([x_ExplicitVarSizeWithFlags_Flags[q11] = false -> x_ExplicitVarSizeWithFlags_Values[q11] = 1 | q11 : int(1..3)]), and([x_ExplicitVarSizeWithFlags_Flags[q12 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q12] | q12 : int(1..2)]), + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q13]) | q13 : int(1..3)]) <= 3, and([x_ExplicitVarSizeWithFlags_Flags[q16] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q16]] | q16 : int(1..3)]), and([x_Occurrence[q17] -> diff --git a/tests/exhaustive/basic/set04/expected/model_1_4_1-solution000001.solution b/tests/exhaustive/basic/set04/expected/model_1_4_1-solution000001.solution new file mode 100644 index 0000000000..f90e0ba18c --- /dev/null +++ b/tests/exhaustive/basic/set04/expected/model_1_4_1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2} diff --git a/tests/exhaustive/basic/set04/expected/model_1_4_1-solution000002.solution b/tests/exhaustive/basic/set04/expected/model_1_4_1-solution000002.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set04/expected/model_1_4_1-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set04/expected/model_1_4_1.eprime b/tests/exhaustive/basic/set04/expected/model_1_4_1.eprime new file mode 100644 index 0000000000..5915d91c83 --- /dev/null +++ b/tests/exhaustive/basic/set04/expected/model_1_4_1.eprime @@ -0,0 +1,21 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(1..3)] of bool +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..3)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3)] of int(1..3) +branching on [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_Occurrence] +such that + x_Occurrence[1], + or([x_ExplicitVarSizeWithFlags_Flags[q13] /\ x_ExplicitVarSizeWithFlags_Values[q13] = 2 | q13 : int(1..3)]), + sum([toInt(x_Occurrence[q1]) | q1 : int(1..3)]) <= 3, + and([x_ExplicitVarSizeWithFlags_Flags[q2 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q2] < x_ExplicitVarSizeWithFlags_Values[q2 + 1] + | q2 : int(1..2)]), + and([x_ExplicitVarSizeWithFlags_Flags[q3] = false -> x_ExplicitVarSizeWithFlags_Values[q3] = 1 | q3 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q4] | q4 : int(1..2)]), + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q5]) | q5 : int(1..3)]) <= 3, + and([x_ExplicitVarSizeWithFlags_Flags[q8] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q8]] | q8 : int(1..3)]), + and([x_Occurrence[q9] -> + or([x_ExplicitVarSizeWithFlags_Flags[q11] /\ x_ExplicitVarSizeWithFlags_Values[q11] = q9 | q11 : int(1..3)]) + | q9 : int(1..3)]) + diff --git a/tests/exhaustive/basic/set04/expected/model_1_4_2-solution000001.solution b/tests/exhaustive/basic/set04/expected/model_1_4_2-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set04/expected/model_1_4_2-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set04/expected/model_1_4_2-solution000002.solution b/tests/exhaustive/basic/set04/expected/model_1_4_2-solution000002.solution new file mode 100644 index 0000000000..f90e0ba18c --- /dev/null +++ b/tests/exhaustive/basic/set04/expected/model_1_4_2-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_4_2.eprime.orig b/tests/exhaustive/basic/set04/expected/model_1_4_2.eprime similarity index 81% rename from tests/exhaustive/basic/cut_01_on/expected/model_1_4_2.eprime.orig rename to tests/exhaustive/basic/set04/expected/model_1_4_2.eprime index cc5451afda..2b37e1dd5a 100644 --- a/tests/exhaustive/basic/cut_01_on/expected/model_1_4_2.eprime.orig +++ b/tests/exhaustive/basic/set04/expected/model_1_4_2.eprime @@ -4,20 +4,18 @@ find x_Occurrence: matrix indexed by [int(1..3)] of bool find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..3)] of bool find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3)] of int(1..3) find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..3)] of int(1..4) -find cut1: bool -find cut2: bool branching on - [cut1, cut2, x_ExplicitVarSizeWithDummy, x_Occurrence, x_ExplicitVarSizeWithFlags_Flags, - x_ExplicitVarSizeWithFlags_Values] + [x_ExplicitVarSizeWithDummy, x_Occurrence, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] such that - !cut1 <-> x_Occurrence[1] /\ x_Occurrence[2], - !cut2 <-> - or([x_ExplicitVarSizeWithFlags_Flags[q31] /\ x_ExplicitVarSizeWithFlags_Values[q31] = 1 | q31 : int(1..3)]), + x_Occurrence[1], + or([x_ExplicitVarSizeWithFlags_Flags[q30] /\ x_ExplicitVarSizeWithFlags_Values[q30] = 2 | q30 : int(1..3)]), + sum([toInt(x_Occurrence[q1]) | q1 : int(1..3)]) <= 3, and([x_ExplicitVarSizeWithFlags_Flags[q2 + 1] -> x_ExplicitVarSizeWithFlags_Values[q2] < x_ExplicitVarSizeWithFlags_Values[q2 + 1] | q2 : int(1..2)]), and([x_ExplicitVarSizeWithFlags_Flags[q3] = false -> x_ExplicitVarSizeWithFlags_Values[q3] = 1 | q3 : int(1..3)]), and([x_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q4] | q4 : int(1..2)]), + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q5]) | q5 : int(1..3)]) <= 3, and([x_ExplicitVarSizeWithFlags_Flags[q8] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q8]] | q8 : int(1..3)]), and([x_Occurrence[q9] -> or([x_ExplicitVarSizeWithFlags_Flags[q11] /\ x_ExplicitVarSizeWithFlags_Values[q11] = q9 | q11 : int(1..3)]) @@ -25,6 +23,7 @@ such that and([x_ExplicitVarSizeWithDummy[q12] < x_ExplicitVarSizeWithDummy[q12 + 1] \/ x_ExplicitVarSizeWithDummy[q12] = 4 | q12 : int(1..2)]), and([x_ExplicitVarSizeWithDummy[q13] = 4 -> x_ExplicitVarSizeWithDummy[q13 + 1] = 4 | q13 : int(1..2)]), + sum([toInt(x_ExplicitVarSizeWithDummy[q14] != 4) | q14 : int(1..3)]) <= 3, and([x_ExplicitVarSizeWithDummy[q17] != 4 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q17]] | q17 : int(1..3)]), and([x_Occurrence[q18] -> or([x_ExplicitVarSizeWithDummy[q20] != 4 /\ x_ExplicitVarSizeWithDummy[q20] = q18 | q20 : int(1..3)]) diff --git a/tests/exhaustive/basic/set04/expected/model_1_4_3-solution000001.solution b/tests/exhaustive/basic/set04/expected/model_1_4_3-solution000001.solution new file mode 100644 index 0000000000..f90e0ba18c --- /dev/null +++ b/tests/exhaustive/basic/set04/expected/model_1_4_3-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2} diff --git a/tests/exhaustive/basic/set04/expected/model_1_4_3-solution000002.solution b/tests/exhaustive/basic/set04/expected/model_1_4_3-solution000002.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set04/expected/model_1_4_3-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_1_4_3.eprime.orig b/tests/exhaustive/basic/set04/expected/model_1_4_3.eprime similarity index 85% rename from tests/exhaustive/basic/cut_01_on/expected/model_1_4_3.eprime.orig rename to tests/exhaustive/basic/set04/expected/model_1_4_3.eprime index ff3bcc9dc1..df30a96b17 100644 --- a/tests/exhaustive/basic/cut_01_on/expected/model_1_4_3.eprime.orig +++ b/tests/exhaustive/basic/set04/expected/model_1_4_3.eprime @@ -5,20 +5,19 @@ find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..3)] of bool find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3)] of int(1..3) find x_ExplicitVarSizeWithMarker_Marker: int(0..3) find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3)] of int(1..3) -find cut1: bool -find cut2: bool branching on - [cut1, cut2, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_Occurrence, + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_Occurrence, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] such that - !cut1 <-> x_Occurrence[1] /\ x_Occurrence[2], - !cut2 <-> - or([x_ExplicitVarSizeWithFlags_Flags[q30] /\ x_ExplicitVarSizeWithFlags_Values[q30] = 1 | q30 : int(1..3)]), + x_Occurrence[1], + or([x_ExplicitVarSizeWithFlags_Flags[q29] /\ x_ExplicitVarSizeWithFlags_Values[q29] = 2 | q29 : int(1..3)]), + sum([toInt(x_Occurrence[q1]) | q1 : int(1..3)]) <= 3, and([x_ExplicitVarSizeWithFlags_Flags[q2 + 1] -> x_ExplicitVarSizeWithFlags_Values[q2] < x_ExplicitVarSizeWithFlags_Values[q2 + 1] | q2 : int(1..2)]), and([x_ExplicitVarSizeWithFlags_Flags[q3] = false -> x_ExplicitVarSizeWithFlags_Values[q3] = 1 | q3 : int(1..3)]), and([x_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q4] | q4 : int(1..2)]), + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q5]) | q5 : int(1..3)]) <= 3, and([x_ExplicitVarSizeWithFlags_Flags[q8] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q8]] | q8 : int(1..3)]), and([x_Occurrence[q9] -> or([x_ExplicitVarSizeWithFlags_Flags[q11] /\ x_ExplicitVarSizeWithFlags_Values[q11] = q9 | q11 : int(1..3)]) @@ -27,6 +26,7 @@ such that x_ExplicitVarSizeWithMarker_Values[q12] < x_ExplicitVarSizeWithMarker_Values[q12 + 1] | q12 : int(1..2)]), and([q13 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q13] = 1 | q13 : int(1..3)]), + x_ExplicitVarSizeWithMarker_Marker <= 3, and([q16 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q16]] | q16 : int(1..3)]), and([x_Occurrence[q17] -> diff --git a/tests/exhaustive/basic/set04/expected/model_2_1_1-solution000001.solution b/tests/exhaustive/basic/set04/expected/model_2_1_1-solution000001.solution new file mode 100644 index 0000000000..f90e0ba18c --- /dev/null +++ b/tests/exhaustive/basic/set04/expected/model_2_1_1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2} diff --git a/tests/exhaustive/basic/set04/expected/model_2_1_1-solution000002.solution b/tests/exhaustive/basic/set04/expected/model_2_1_1-solution000002.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set04/expected/model_2_1_1-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_1_1.eprime.orig b/tests/exhaustive/basic/set04/expected/model_2_1_1.eprime similarity index 66% rename from tests/exhaustive/basic/cut_01_on/expected/model_2_1_1.eprime.orig rename to tests/exhaustive/basic/set04/expected/model_2_1_1.eprime index f6a1975870..3f095c1e18 100644 --- a/tests/exhaustive/basic/cut_01_on/expected/model_2_1_1.eprime.orig +++ b/tests/exhaustive/basic/set04/expected/model_2_1_1.eprime @@ -2,17 +2,15 @@ language ESSENCE' 1.0 find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..3)] of int(1..4) find x_Occurrence: matrix indexed by [int(1..3)] of bool -find cut1: bool -find cut2: bool -branching on [cut1, cut2, x_Occurrence, x_ExplicitVarSizeWithDummy] +branching on [x_Occurrence, x_ExplicitVarSizeWithDummy] such that - !cut1 <-> - or([x_ExplicitVarSizeWithDummy[q13] != 4 /\ x_ExplicitVarSizeWithDummy[q13] = 1 | q13 : int(1..3)]) /\ - or([x_ExplicitVarSizeWithDummy[q15] != 4 /\ x_ExplicitVarSizeWithDummy[q15] = 2 | q15 : int(1..3)]), - !cut2 <-> x_Occurrence[1], + or([x_ExplicitVarSizeWithDummy[q12] != 4 /\ x_ExplicitVarSizeWithDummy[q12] = 1 | q12 : int(1..3)]), + x_Occurrence[2], and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 4 | q1 : int(1..2)]), and([x_ExplicitVarSizeWithDummy[q2] = 4 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 4 | q2 : int(1..2)]), + sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 4) | q3 : int(1..3)]) <= 3, + sum([toInt(x_Occurrence[q5]) | q5 : int(1..3)]) <= 3, and([x_Occurrence[q6] -> or([x_ExplicitVarSizeWithDummy[q8] != 4 /\ x_ExplicitVarSizeWithDummy[q8] = q6 | q8 : int(1..3)]) | q6 : int(1..3)]), diff --git a/tests/exhaustive/basic/set04/expected/model_2_1_3-solution000001.solution b/tests/exhaustive/basic/set04/expected/model_2_1_3-solution000001.solution new file mode 100644 index 0000000000..f90e0ba18c --- /dev/null +++ b/tests/exhaustive/basic/set04/expected/model_2_1_3-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2} diff --git a/tests/exhaustive/basic/set04/expected/model_2_1_3-solution000002.solution b/tests/exhaustive/basic/set04/expected/model_2_1_3-solution000002.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set04/expected/model_2_1_3-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_1_3.eprime.orig b/tests/exhaustive/basic/set04/expected/model_2_1_3.eprime similarity index 82% rename from tests/exhaustive/basic/cut_01_on/expected/model_2_1_3.eprime.orig rename to tests/exhaustive/basic/set04/expected/model_2_1_3.eprime index 97d66e8808..c0e6fb3f20 100644 --- a/tests/exhaustive/basic/cut_01_on/expected/model_2_1_3.eprime.orig +++ b/tests/exhaustive/basic/set04/expected/model_2_1_3.eprime @@ -4,19 +4,16 @@ find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..3)] of int(1..4) find x_Occurrence: matrix indexed by [int(1..3)] of bool find x_ExplicitVarSizeWithMarker_Marker: int(0..3) find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3)] of int(1..3) -find cut1: bool -find cut2: bool branching on - [cut1, cut2, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy, - x_Occurrence] + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy, x_Occurrence] such that - !cut1 <-> - or([x_ExplicitVarSizeWithDummy[q29] != 4 /\ x_ExplicitVarSizeWithDummy[q29] = 1 | q29 : int(1..3)]) /\ - or([x_ExplicitVarSizeWithDummy[q31] != 4 /\ x_ExplicitVarSizeWithDummy[q31] = 2 | q31 : int(1..3)]), - !cut2 <-> x_Occurrence[1], + or([x_ExplicitVarSizeWithDummy[q28] != 4 /\ x_ExplicitVarSizeWithDummy[q28] = 1 | q28 : int(1..3)]), + x_Occurrence[2], and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 4 | q1 : int(1..2)]), and([x_ExplicitVarSizeWithDummy[q2] = 4 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 4 | q2 : int(1..2)]), + sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 4) | q3 : int(1..3)]) <= 3, + sum([toInt(x_Occurrence[q5]) | q5 : int(1..3)]) <= 3, and([x_Occurrence[q22] -> or([x_ExplicitVarSizeWithDummy[q24] != 4 /\ x_ExplicitVarSizeWithDummy[q24] = q22 | q24 : int(1..3)]) | q22 : int(1..3)]), @@ -25,6 +22,7 @@ such that x_ExplicitVarSizeWithMarker_Values[q6] < x_ExplicitVarSizeWithMarker_Values[q6 + 1] | q6 : int(1..2)]), and([q7 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q7] = 1 | q7 : int(1..3)]), + x_ExplicitVarSizeWithMarker_Marker <= 3, and([q10 <= x_ExplicitVarSizeWithMarker_Marker -> or([x_ExplicitVarSizeWithDummy[q12] != 4 /\ x_ExplicitVarSizeWithDummy[q12] = x_ExplicitVarSizeWithMarker_Values[q10] diff --git a/tests/exhaustive/basic/set04/expected/model_2_1_4-solution000001.solution b/tests/exhaustive/basic/set04/expected/model_2_1_4-solution000001.solution new file mode 100644 index 0000000000..f90e0ba18c --- /dev/null +++ b/tests/exhaustive/basic/set04/expected/model_2_1_4-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2} diff --git a/tests/exhaustive/basic/set04/expected/model_2_1_4-solution000002.solution b/tests/exhaustive/basic/set04/expected/model_2_1_4-solution000002.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set04/expected/model_2_1_4-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_1_4.eprime.orig b/tests/exhaustive/basic/set04/expected/model_2_1_4.eprime similarity index 82% rename from tests/exhaustive/basic/cut_01_on/expected/model_2_1_4.eprime.orig rename to tests/exhaustive/basic/set04/expected/model_2_1_4.eprime index 3a9b95e862..5636e1d31f 100644 --- a/tests/exhaustive/basic/cut_01_on/expected/model_2_1_4.eprime.orig +++ b/tests/exhaustive/basic/set04/expected/model_2_1_4.eprime @@ -4,19 +4,16 @@ find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..3)] of int(1..4) find x_Occurrence: matrix indexed by [int(1..3)] of bool find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..3)] of bool find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3)] of int(1..3) -find cut1: bool -find cut2: bool branching on - [cut1, cut2, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy, - x_Occurrence] + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy, x_Occurrence] such that - !cut1 <-> - or([x_ExplicitVarSizeWithDummy[q31] != 4 /\ x_ExplicitVarSizeWithDummy[q31] = 1 | q31 : int(1..3)]) /\ - or([x_ExplicitVarSizeWithDummy[q33] != 4 /\ x_ExplicitVarSizeWithDummy[q33] = 2 | q33 : int(1..3)]), - !cut2 <-> x_Occurrence[1], + or([x_ExplicitVarSizeWithDummy[q30] != 4 /\ x_ExplicitVarSizeWithDummy[q30] = 1 | q30 : int(1..3)]), + x_Occurrence[2], and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 4 | q1 : int(1..2)]), and([x_ExplicitVarSizeWithDummy[q2] = 4 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 4 | q2 : int(1..2)]), + sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 4) | q3 : int(1..3)]) <= 3, + sum([toInt(x_Occurrence[q5]) | q5 : int(1..3)]) <= 3, and([x_Occurrence[q24] -> or([x_ExplicitVarSizeWithDummy[q26] != 4 /\ x_ExplicitVarSizeWithDummy[q26] = q24 | q26 : int(1..3)]) | q24 : int(1..3)]), @@ -26,6 +23,7 @@ such that | q6 : int(1..2)]), and([x_ExplicitVarSizeWithFlags_Flags[q7] = false -> x_ExplicitVarSizeWithFlags_Values[q7] = 1 | q7 : int(1..3)]), and([x_ExplicitVarSizeWithFlags_Flags[q8 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q8] | q8 : int(1..2)]), + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q9]) | q9 : int(1..3)]) <= 3, and([x_ExplicitVarSizeWithFlags_Flags[q12] -> or([x_ExplicitVarSizeWithDummy[q14] != 4 /\ x_ExplicitVarSizeWithDummy[q14] = x_ExplicitVarSizeWithFlags_Values[q12] diff --git a/tests/exhaustive/basic/set04/expected/model_2_2_1-solution000001.solution b/tests/exhaustive/basic/set04/expected/model_2_2_1-solution000001.solution new file mode 100644 index 0000000000..f90e0ba18c --- /dev/null +++ b/tests/exhaustive/basic/set04/expected/model_2_2_1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2} diff --git a/tests/exhaustive/basic/set04/expected/model_2_2_1-solution000002.solution b/tests/exhaustive/basic/set04/expected/model_2_2_1-solution000002.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set04/expected/model_2_2_1-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_1_2.eprime.orig b/tests/exhaustive/basic/set04/expected/model_2_2_1.eprime similarity index 63% rename from tests/exhaustive/basic/cut_01_on/expected/model_2_1_2.eprime.orig rename to tests/exhaustive/basic/set04/expected/model_2_2_1.eprime index f6a1975870..ab9e099117 100644 --- a/tests/exhaustive/basic/cut_01_on/expected/model_2_1_2.eprime.orig +++ b/tests/exhaustive/basic/set04/expected/model_2_2_1.eprime @@ -2,17 +2,15 @@ language ESSENCE' 1.0 find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..3)] of int(1..4) find x_Occurrence: matrix indexed by [int(1..3)] of bool -find cut1: bool -find cut2: bool -branching on [cut1, cut2, x_Occurrence, x_ExplicitVarSizeWithDummy] +branching on [x_Occurrence, x_ExplicitVarSizeWithDummy] such that - !cut1 <-> - or([x_ExplicitVarSizeWithDummy[q13] != 4 /\ x_ExplicitVarSizeWithDummy[q13] = 1 | q13 : int(1..3)]) /\ - or([x_ExplicitVarSizeWithDummy[q15] != 4 /\ x_ExplicitVarSizeWithDummy[q15] = 2 | q15 : int(1..3)]), - !cut2 <-> x_Occurrence[1], + or([x_ExplicitVarSizeWithDummy[q12] != 4 /\ x_ExplicitVarSizeWithDummy[q12] = 1 | q12 : int(1..3)]), + or([x_ExplicitVarSizeWithDummy[q14] != 4 /\ x_ExplicitVarSizeWithDummy[q14] = 2 | q14 : int(1..3)]), and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 4 | q1 : int(1..2)]), and([x_ExplicitVarSizeWithDummy[q2] = 4 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 4 | q2 : int(1..2)]), + sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 4) | q3 : int(1..3)]) <= 3, + sum([toInt(x_Occurrence[q5]) | q5 : int(1..3)]) <= 3, and([x_Occurrence[q6] -> or([x_ExplicitVarSizeWithDummy[q8] != 4 /\ x_ExplicitVarSizeWithDummy[q8] = q6 | q8 : int(1..3)]) | q6 : int(1..3)]), diff --git a/tests/exhaustive/basic/set04/expected/model_2_2_2-solution000001.solution b/tests/exhaustive/basic/set04/expected/model_2_2_2-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set04/expected/model_2_2_2-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set04/expected/model_2_2_2-solution000002.solution b/tests/exhaustive/basic/set04/expected/model_2_2_2-solution000002.solution new file mode 100644 index 0000000000..f90e0ba18c --- /dev/null +++ b/tests/exhaustive/basic/set04/expected/model_2_2_2-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2} diff --git a/tests/exhaustive/basic/set04/expected/model_2_2_2.eprime b/tests/exhaustive/basic/set04/expected/model_2_2_2.eprime new file mode 100644 index 0000000000..6f4df0cbd5 --- /dev/null +++ b/tests/exhaustive/basic/set04/expected/model_2_2_2.eprime @@ -0,0 +1,12 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..3)] of int(1..4) +branching on [x_ExplicitVarSizeWithDummy] +such that + or([x_ExplicitVarSizeWithDummy[q6] != 4 /\ x_ExplicitVarSizeWithDummy[q6] = 1 | q6 : int(1..3)]), + or([x_ExplicitVarSizeWithDummy[q8] != 4 /\ x_ExplicitVarSizeWithDummy[q8] = 2 | q8 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 4 + | q1 : int(1..2)]), + and([x_ExplicitVarSizeWithDummy[q2] = 4 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 4 | q2 : int(1..2)]), + sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 4) | q3 : int(1..3)]) <= 3 + diff --git a/tests/exhaustive/basic/set04/expected/model_2_2_3-solution000001.solution b/tests/exhaustive/basic/set04/expected/model_2_2_3-solution000001.solution new file mode 100644 index 0000000000..f90e0ba18c --- /dev/null +++ b/tests/exhaustive/basic/set04/expected/model_2_2_3-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2} diff --git a/tests/exhaustive/basic/set04/expected/model_2_2_3-solution000002.solution b/tests/exhaustive/basic/set04/expected/model_2_2_3-solution000002.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set04/expected/model_2_2_3-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_2_3.eprime.orig b/tests/exhaustive/basic/set04/expected/model_2_2_3.eprime similarity index 72% rename from tests/exhaustive/basic/cut_01_on/expected/model_2_2_3.eprime.orig rename to tests/exhaustive/basic/set04/expected/model_2_2_3.eprime index ef5020a88a..047d06d041 100644 --- a/tests/exhaustive/basic/cut_01_on/expected/model_2_2_3.eprime.orig +++ b/tests/exhaustive/basic/set04/expected/model_2_2_3.eprime @@ -3,22 +3,19 @@ language ESSENCE' 1.0 find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..3)] of int(1..4) find x_ExplicitVarSizeWithMarker_Marker: int(0..3) find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3)] of int(1..3) -find cut1: bool -find cut2: bool -branching on - [cut1, cut2, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy] +branching on [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy] such that - !cut1 <-> - or([x_ExplicitVarSizeWithDummy[q18] != 4 /\ x_ExplicitVarSizeWithDummy[q18] = 1 | q18 : int(1..3)]) /\ - or([x_ExplicitVarSizeWithDummy[q20] != 4 /\ x_ExplicitVarSizeWithDummy[q20] = 2 | q20 : int(1..3)]), - !cut2 <-> or([x_ExplicitVarSizeWithDummy[q22] != 4 /\ x_ExplicitVarSizeWithDummy[q22] = 1 | q22 : int(1..3)]), + or([x_ExplicitVarSizeWithDummy[q17] != 4 /\ x_ExplicitVarSizeWithDummy[q17] = 1 | q17 : int(1..3)]), + or([x_ExplicitVarSizeWithDummy[q19] != 4 /\ x_ExplicitVarSizeWithDummy[q19] = 2 | q19 : int(1..3)]), and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 4 | q1 : int(1..2)]), and([x_ExplicitVarSizeWithDummy[q2] = 4 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 4 | q2 : int(1..2)]), + sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 4) | q3 : int(1..3)]) <= 3, and([q5 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q5] < x_ExplicitVarSizeWithMarker_Values[q5 + 1] | q5 : int(1..2)]), and([q6 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q6] = 1 | q6 : int(1..3)]), + x_ExplicitVarSizeWithMarker_Marker <= 3, and([q9 <= x_ExplicitVarSizeWithMarker_Marker -> or([x_ExplicitVarSizeWithDummy[q11] != 4 /\ x_ExplicitVarSizeWithDummy[q11] = x_ExplicitVarSizeWithMarker_Values[q9] diff --git a/tests/exhaustive/basic/set04/expected/model_2_2_4-solution000001.solution b/tests/exhaustive/basic/set04/expected/model_2_2_4-solution000001.solution new file mode 100644 index 0000000000..f90e0ba18c --- /dev/null +++ b/tests/exhaustive/basic/set04/expected/model_2_2_4-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2} diff --git a/tests/exhaustive/basic/set04/expected/model_2_2_4-solution000002.solution b/tests/exhaustive/basic/set04/expected/model_2_2_4-solution000002.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set04/expected/model_2_2_4-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_2_4.eprime.orig b/tests/exhaustive/basic/set04/expected/model_2_2_4.eprime similarity index 74% rename from tests/exhaustive/basic/cut_01_on/expected/model_2_2_4.eprime.orig rename to tests/exhaustive/basic/set04/expected/model_2_2_4.eprime index 02cfe37098..05a8f136b6 100644 --- a/tests/exhaustive/basic/cut_01_on/expected/model_2_2_4.eprime.orig +++ b/tests/exhaustive/basic/set04/expected/model_2_2_4.eprime @@ -3,23 +3,20 @@ language ESSENCE' 1.0 find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..3)] of int(1..4) find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..3)] of bool find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3)] of int(1..3) -find cut1: bool -find cut2: bool -branching on - [cut1, cut2, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy] +branching on [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy] such that - !cut1 <-> - or([x_ExplicitVarSizeWithDummy[q20] != 4 /\ x_ExplicitVarSizeWithDummy[q20] = 1 | q20 : int(1..3)]) /\ - or([x_ExplicitVarSizeWithDummy[q22] != 4 /\ x_ExplicitVarSizeWithDummy[q22] = 2 | q22 : int(1..3)]), - !cut2 <-> or([x_ExplicitVarSizeWithDummy[q24] != 4 /\ x_ExplicitVarSizeWithDummy[q24] = 1 | q24 : int(1..3)]), + or([x_ExplicitVarSizeWithDummy[q19] != 4 /\ x_ExplicitVarSizeWithDummy[q19] = 1 | q19 : int(1..3)]), + or([x_ExplicitVarSizeWithDummy[q21] != 4 /\ x_ExplicitVarSizeWithDummy[q21] = 2 | q21 : int(1..3)]), and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 4 | q1 : int(1..2)]), and([x_ExplicitVarSizeWithDummy[q2] = 4 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 4 | q2 : int(1..2)]), + sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 4) | q3 : int(1..3)]) <= 3, and([x_ExplicitVarSizeWithFlags_Flags[q5 + 1] -> x_ExplicitVarSizeWithFlags_Values[q5] < x_ExplicitVarSizeWithFlags_Values[q5 + 1] | q5 : int(1..2)]), and([x_ExplicitVarSizeWithFlags_Flags[q6] = false -> x_ExplicitVarSizeWithFlags_Values[q6] = 1 | q6 : int(1..3)]), and([x_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q7] | q7 : int(1..2)]), + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q8]) | q8 : int(1..3)]) <= 3, and([x_ExplicitVarSizeWithFlags_Flags[q11] -> or([x_ExplicitVarSizeWithDummy[q13] != 4 /\ x_ExplicitVarSizeWithDummy[q13] = x_ExplicitVarSizeWithFlags_Values[q11] diff --git a/tests/exhaustive/basic/set04/expected/model_2_3_1-solution000001.solution b/tests/exhaustive/basic/set04/expected/model_2_3_1-solution000001.solution new file mode 100644 index 0000000000..f90e0ba18c --- /dev/null +++ b/tests/exhaustive/basic/set04/expected/model_2_3_1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2} diff --git a/tests/exhaustive/basic/set04/expected/model_2_3_1-solution000002.solution b/tests/exhaustive/basic/set04/expected/model_2_3_1-solution000002.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set04/expected/model_2_3_1-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_3_1.eprime.orig b/tests/exhaustive/basic/set04/expected/model_2_3_1.eprime similarity index 54% rename from tests/exhaustive/basic/cut_01_on/expected/model_2_3_1.eprime.orig rename to tests/exhaustive/basic/set04/expected/model_2_3_1.eprime index b19839d2f0..9c7150af48 100644 --- a/tests/exhaustive/basic/cut_01_on/expected/model_2_3_1.eprime.orig +++ b/tests/exhaustive/basic/set04/expected/model_2_3_1.eprime @@ -4,24 +4,20 @@ find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..3)] of int(1..4) find x_ExplicitVarSizeWithMarker_Marker: int(0..3) find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3)] of int(1..3) find x_Occurrence: matrix indexed by [int(1..3)] of bool -find cut1: bool -find cut2: bool branching on - [cut1, cut2, x_Occurrence, x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithMarker_Marker, - x_ExplicitVarSizeWithMarker_Values] + [x_Occurrence, x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] such that - !cut1 <-> - or([x_ExplicitVarSizeWithDummy[q19] != 4 /\ x_ExplicitVarSizeWithDummy[q19] = 1 | q19 : int(1..3)]) /\ - or([x_ExplicitVarSizeWithDummy[q21] != 4 /\ x_ExplicitVarSizeWithDummy[q21] = 2 | q21 : int(1..3)]), - !cut2 <-> - or([q23 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q23] = 1 | q23 : int(1..3)]), + or([x_ExplicitVarSizeWithDummy[q28] != 4 /\ x_ExplicitVarSizeWithDummy[q28] = 1 | q28 : int(1..3)]), + or([q30 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q30] = 2 | q30 : int(1..3)]), and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 4 | q1 : int(1..2)]), and([x_ExplicitVarSizeWithDummy[q2] = 4 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 4 | q2 : int(1..2)]), + sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 4) | q3 : int(1..3)]) <= 3, and([q5 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q5] < x_ExplicitVarSizeWithMarker_Values[q5 + 1] | q5 : int(1..2)]), and([q6 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q6] = 1 | q6 : int(1..3)]), + x_ExplicitVarSizeWithMarker_Marker <= 3, and([q9 <= x_ExplicitVarSizeWithMarker_Marker -> or([x_ExplicitVarSizeWithDummy[q11] != 4 /\ x_ExplicitVarSizeWithDummy[q11] = x_ExplicitVarSizeWithMarker_Values[q9] @@ -32,14 +28,15 @@ such that x_ExplicitVarSizeWithMarker_Values[q15] = x_ExplicitVarSizeWithDummy[q13] | q15 : int(1..3)]) | q13 : int(1..3)]), - and([x_Occurrence[q24] -> - or([x_ExplicitVarSizeWithDummy[q26] != 4 /\ x_ExplicitVarSizeWithDummy[q26] = q24 | q26 : int(1..3)]) - | q24 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q28] != 4 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q28]] | q28 : int(1..3)]), - and([x_Occurrence[q29] -> - or([q31 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q31] = q29 - | q31 : int(1..3)]) - | q29 : int(1..3)]), - and([q33 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q33]] - | q33 : int(1..3)]) + sum([toInt(x_Occurrence[q16]) | q16 : int(1..3)]) <= 3, + and([x_Occurrence[q17] -> + or([x_ExplicitVarSizeWithDummy[q19] != 4 /\ x_ExplicitVarSizeWithDummy[q19] = q17 | q19 : int(1..3)]) + | q17 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q21] != 4 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q21]] | q21 : int(1..3)]), + and([x_Occurrence[q22] -> + or([q24 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q24] = q22 + | q24 : int(1..3)]) + | q22 : int(1..3)]), + and([q26 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q26]] + | q26 : int(1..3)]) diff --git a/tests/exhaustive/basic/set04/expected/model_2_3_2-solution000001.solution b/tests/exhaustive/basic/set04/expected/model_2_3_2-solution000001.solution new file mode 100644 index 0000000000..f90e0ba18c --- /dev/null +++ b/tests/exhaustive/basic/set04/expected/model_2_3_2-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2} diff --git a/tests/exhaustive/basic/set04/expected/model_2_3_2-solution000002.solution b/tests/exhaustive/basic/set04/expected/model_2_3_2-solution000002.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set04/expected/model_2_3_2-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_3_2.eprime.orig b/tests/exhaustive/basic/set04/expected/model_2_3_2.eprime similarity index 71% rename from tests/exhaustive/basic/cut_01_on/expected/model_2_3_2.eprime.orig rename to tests/exhaustive/basic/set04/expected/model_2_3_2.eprime index 841093014c..3aa6f1b412 100644 --- a/tests/exhaustive/basic/cut_01_on/expected/model_2_3_2.eprime.orig +++ b/tests/exhaustive/basic/set04/expected/model_2_3_2.eprime @@ -3,23 +3,19 @@ language ESSENCE' 1.0 find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..3)] of int(1..4) find x_ExplicitVarSizeWithMarker_Marker: int(0..3) find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3)] of int(1..3) -find cut1: bool -find cut2: bool -branching on - [cut1, cut2, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy] +branching on [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy] such that - !cut1 <-> - or([x_ExplicitVarSizeWithDummy[q18] != 4 /\ x_ExplicitVarSizeWithDummy[q18] = 1 | q18 : int(1..3)]) /\ - or([x_ExplicitVarSizeWithDummy[q20] != 4 /\ x_ExplicitVarSizeWithDummy[q20] = 2 | q20 : int(1..3)]), - !cut2 <-> - or([q22 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q22] = 1 | q22 : int(1..3)]), + or([x_ExplicitVarSizeWithDummy[q17] != 4 /\ x_ExplicitVarSizeWithDummy[q17] = 1 | q17 : int(1..3)]), + or([q19 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q19] = 2 | q19 : int(1..3)]), and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 4 | q1 : int(1..2)]), and([x_ExplicitVarSizeWithDummy[q2] = 4 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 4 | q2 : int(1..2)]), + sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 4) | q3 : int(1..3)]) <= 3, and([q5 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q5] < x_ExplicitVarSizeWithMarker_Values[q5 + 1] | q5 : int(1..2)]), and([q6 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q6] = 1 | q6 : int(1..3)]), + x_ExplicitVarSizeWithMarker_Marker <= 3, and([q9 <= x_ExplicitVarSizeWithMarker_Marker -> or([x_ExplicitVarSizeWithDummy[q11] != 4 /\ x_ExplicitVarSizeWithDummy[q11] = x_ExplicitVarSizeWithMarker_Values[q9] diff --git a/tests/exhaustive/basic/set04/expected/model_2_3_4-solution000001.solution b/tests/exhaustive/basic/set04/expected/model_2_3_4-solution000001.solution new file mode 100644 index 0000000000..f90e0ba18c --- /dev/null +++ b/tests/exhaustive/basic/set04/expected/model_2_3_4-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2} diff --git a/tests/exhaustive/basic/set04/expected/model_2_3_4-solution000002.solution b/tests/exhaustive/basic/set04/expected/model_2_3_4-solution000002.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set04/expected/model_2_3_4-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_3_4.eprime.orig b/tests/exhaustive/basic/set04/expected/model_2_3_4.eprime similarity index 85% rename from tests/exhaustive/basic/cut_01_on/expected/model_2_3_4.eprime.orig rename to tests/exhaustive/basic/set04/expected/model_2_3_4.eprime index 85ebb942bb..cc9085b2c5 100644 --- a/tests/exhaustive/basic/cut_01_on/expected/model_2_3_4.eprime.orig +++ b/tests/exhaustive/basic/set04/expected/model_2_3_4.eprime @@ -5,24 +5,21 @@ find x_ExplicitVarSizeWithMarker_Marker: int(0..3) find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3)] of int(1..3) find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..3)] of bool find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3)] of int(1..3) -find cut1: bool -find cut2: bool branching on - [cut1, cut2, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy, + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] such that - !cut1 <-> - or([x_ExplicitVarSizeWithDummy[q39] != 4 /\ x_ExplicitVarSizeWithDummy[q39] = 1 | q39 : int(1..3)]) /\ - or([x_ExplicitVarSizeWithDummy[q41] != 4 /\ x_ExplicitVarSizeWithDummy[q41] = 2 | q41 : int(1..3)]), - !cut2 <-> - or([q43 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q43] = 1 | q43 : int(1..3)]), + or([x_ExplicitVarSizeWithDummy[q38] != 4 /\ x_ExplicitVarSizeWithDummy[q38] = 1 | q38 : int(1..3)]), + or([q40 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q40] = 2 | q40 : int(1..3)]), and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 4 | q1 : int(1..2)]), and([x_ExplicitVarSizeWithDummy[q2] = 4 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 4 | q2 : int(1..2)]), + sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 4) | q3 : int(1..3)]) <= 3, and([q5 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q5] < x_ExplicitVarSizeWithMarker_Values[q5 + 1] | q5 : int(1..2)]), and([q6 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q6] = 1 | q6 : int(1..3)]), + x_ExplicitVarSizeWithMarker_Marker <= 3, and([q9 <= x_ExplicitVarSizeWithMarker_Marker -> or([x_ExplicitVarSizeWithDummy[q11] != 4 /\ x_ExplicitVarSizeWithDummy[q11] = x_ExplicitVarSizeWithMarker_Values[q9] @@ -39,6 +36,7 @@ such that and([x_ExplicitVarSizeWithFlags_Flags[q17] = false -> x_ExplicitVarSizeWithFlags_Values[q17] = 1 | q17 : int(1..3)]), and([x_ExplicitVarSizeWithFlags_Flags[q18 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q18] | q18 : int(1..2)]), + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q19]) | q19 : int(1..3)]) <= 3, and([x_ExplicitVarSizeWithFlags_Flags[q22] -> or([x_ExplicitVarSizeWithDummy[q24] != 4 /\ x_ExplicitVarSizeWithDummy[q24] = x_ExplicitVarSizeWithFlags_Values[q22] diff --git a/tests/exhaustive/basic/set04/expected/model_2_4_1-solution000001.solution b/tests/exhaustive/basic/set04/expected/model_2_4_1-solution000001.solution new file mode 100644 index 0000000000..f90e0ba18c --- /dev/null +++ b/tests/exhaustive/basic/set04/expected/model_2_4_1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2} diff --git a/tests/exhaustive/basic/set04/expected/model_2_4_1-solution000002.solution b/tests/exhaustive/basic/set04/expected/model_2_4_1-solution000002.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set04/expected/model_2_4_1-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_4_1.eprime.orig b/tests/exhaustive/basic/set04/expected/model_2_4_1.eprime similarity index 79% rename from tests/exhaustive/basic/cut_01_on/expected/model_2_4_1.eprime.orig rename to tests/exhaustive/basic/set04/expected/model_2_4_1.eprime index f6983c9c0e..f56d2aa970 100644 --- a/tests/exhaustive/basic/cut_01_on/expected/model_2_4_1.eprime.orig +++ b/tests/exhaustive/basic/set04/expected/model_2_4_1.eprime @@ -4,25 +4,21 @@ find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..3)] of int(1..4) find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..3)] of bool find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3)] of int(1..3) find x_Occurrence: matrix indexed by [int(1..3)] of bool -find cut1: bool -find cut2: bool branching on - [cut1, cut2, x_Occurrence, x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithFlags_Flags, - x_ExplicitVarSizeWithFlags_Values] + [x_Occurrence, x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] such that - !cut1 <-> - or([x_ExplicitVarSizeWithDummy[q31] != 4 /\ x_ExplicitVarSizeWithDummy[q31] = 1 | q31 : int(1..3)]) /\ - or([x_ExplicitVarSizeWithDummy[q33] != 4 /\ x_ExplicitVarSizeWithDummy[q33] = 2 | q33 : int(1..3)]), - !cut2 <-> - or([x_ExplicitVarSizeWithFlags_Flags[q35] /\ x_ExplicitVarSizeWithFlags_Values[q35] = 1 | q35 : int(1..3)]), + or([x_ExplicitVarSizeWithDummy[q30] != 4 /\ x_ExplicitVarSizeWithDummy[q30] = 1 | q30 : int(1..3)]), + or([x_ExplicitVarSizeWithFlags_Flags[q32] /\ x_ExplicitVarSizeWithFlags_Values[q32] = 2 | q32 : int(1..3)]), and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 4 | q1 : int(1..2)]), and([x_ExplicitVarSizeWithDummy[q2] = 4 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 4 | q2 : int(1..2)]), + sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 4) | q3 : int(1..3)]) <= 3, and([x_ExplicitVarSizeWithFlags_Flags[q5 + 1] -> x_ExplicitVarSizeWithFlags_Values[q5] < x_ExplicitVarSizeWithFlags_Values[q5 + 1] | q5 : int(1..2)]), and([x_ExplicitVarSizeWithFlags_Flags[q6] = false -> x_ExplicitVarSizeWithFlags_Values[q6] = 1 | q6 : int(1..3)]), and([x_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q7] | q7 : int(1..2)]), + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q8]) | q8 : int(1..3)]) <= 3, and([x_ExplicitVarSizeWithFlags_Flags[q11] -> or([x_ExplicitVarSizeWithDummy[q13] != 4 /\ x_ExplicitVarSizeWithDummy[q13] = x_ExplicitVarSizeWithFlags_Values[q11] @@ -33,6 +29,7 @@ such that x_ExplicitVarSizeWithFlags_Values[q17] = x_ExplicitVarSizeWithDummy[q15] | q17 : int(1..3)]) | q15 : int(1..3)]), + sum([toInt(x_Occurrence[q18]) | q18 : int(1..3)]) <= 3, and([x_Occurrence[q19] -> or([x_ExplicitVarSizeWithDummy[q21] != 4 /\ x_ExplicitVarSizeWithDummy[q21] = q19 | q21 : int(1..3)]) | q19 : int(1..3)]), diff --git a/tests/exhaustive/basic/set04/expected/model_2_4_2-solution000001.solution b/tests/exhaustive/basic/set04/expected/model_2_4_2-solution000001.solution new file mode 100644 index 0000000000..f90e0ba18c --- /dev/null +++ b/tests/exhaustive/basic/set04/expected/model_2_4_2-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2} diff --git a/tests/exhaustive/basic/set04/expected/model_2_4_2-solution000002.solution b/tests/exhaustive/basic/set04/expected/model_2_4_2-solution000002.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set04/expected/model_2_4_2-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_4_2.eprime.orig b/tests/exhaustive/basic/set04/expected/model_2_4_2.eprime similarity index 73% rename from tests/exhaustive/basic/cut_01_on/expected/model_2_4_2.eprime.orig rename to tests/exhaustive/basic/set04/expected/model_2_4_2.eprime index 31db1d1a15..3e7f4a0be3 100644 --- a/tests/exhaustive/basic/cut_01_on/expected/model_2_4_2.eprime.orig +++ b/tests/exhaustive/basic/set04/expected/model_2_4_2.eprime @@ -3,24 +3,20 @@ language ESSENCE' 1.0 find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..3)] of int(1..4) find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..3)] of bool find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3)] of int(1..3) -find cut1: bool -find cut2: bool -branching on - [cut1, cut2, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy] +branching on [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy] such that - !cut1 <-> - or([x_ExplicitVarSizeWithDummy[q20] != 4 /\ x_ExplicitVarSizeWithDummy[q20] = 1 | q20 : int(1..3)]) /\ - or([x_ExplicitVarSizeWithDummy[q22] != 4 /\ x_ExplicitVarSizeWithDummy[q22] = 2 | q22 : int(1..3)]), - !cut2 <-> - or([x_ExplicitVarSizeWithFlags_Flags[q24] /\ x_ExplicitVarSizeWithFlags_Values[q24] = 1 | q24 : int(1..3)]), + or([x_ExplicitVarSizeWithDummy[q19] != 4 /\ x_ExplicitVarSizeWithDummy[q19] = 1 | q19 : int(1..3)]), + or([x_ExplicitVarSizeWithFlags_Flags[q21] /\ x_ExplicitVarSizeWithFlags_Values[q21] = 2 | q21 : int(1..3)]), and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 4 | q1 : int(1..2)]), and([x_ExplicitVarSizeWithDummy[q2] = 4 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 4 | q2 : int(1..2)]), + sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 4) | q3 : int(1..3)]) <= 3, and([x_ExplicitVarSizeWithFlags_Flags[q5 + 1] -> x_ExplicitVarSizeWithFlags_Values[q5] < x_ExplicitVarSizeWithFlags_Values[q5 + 1] | q5 : int(1..2)]), and([x_ExplicitVarSizeWithFlags_Flags[q6] = false -> x_ExplicitVarSizeWithFlags_Values[q6] = 1 | q6 : int(1..3)]), and([x_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q7] | q7 : int(1..2)]), + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q8]) | q8 : int(1..3)]) <= 3, and([x_ExplicitVarSizeWithFlags_Flags[q11] -> or([x_ExplicitVarSizeWithDummy[q13] != 4 /\ x_ExplicitVarSizeWithDummy[q13] = x_ExplicitVarSizeWithFlags_Values[q11] diff --git a/tests/exhaustive/basic/set04/expected/model_2_4_3-solution000001.solution b/tests/exhaustive/basic/set04/expected/model_2_4_3-solution000001.solution new file mode 100644 index 0000000000..f90e0ba18c --- /dev/null +++ b/tests/exhaustive/basic/set04/expected/model_2_4_3-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2} diff --git a/tests/exhaustive/basic/set04/expected/model_2_4_3-solution000002.solution b/tests/exhaustive/basic/set04/expected/model_2_4_3-solution000002.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set04/expected/model_2_4_3-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_4_3.eprime.orig b/tests/exhaustive/basic/set04/expected/model_2_4_3.eprime similarity index 85% rename from tests/exhaustive/basic/cut_01_on/expected/model_2_4_3.eprime.orig rename to tests/exhaustive/basic/set04/expected/model_2_4_3.eprime index afe6f3dbbb..71047bdbd3 100644 --- a/tests/exhaustive/basic/cut_01_on/expected/model_2_4_3.eprime.orig +++ b/tests/exhaustive/basic/set04/expected/model_2_4_3.eprime @@ -5,25 +5,22 @@ find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..3)] of bool find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3)] of int(1..3) find x_ExplicitVarSizeWithMarker_Marker: int(0..3) find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3)] of int(1..3) -find cut1: bool -find cut2: bool branching on - [cut1, cut2, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy, + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] such that - !cut1 <-> - or([x_ExplicitVarSizeWithDummy[q39] != 4 /\ x_ExplicitVarSizeWithDummy[q39] = 1 | q39 : int(1..3)]) /\ - or([x_ExplicitVarSizeWithDummy[q41] != 4 /\ x_ExplicitVarSizeWithDummy[q41] = 2 | q41 : int(1..3)]), - !cut2 <-> - or([x_ExplicitVarSizeWithFlags_Flags[q43] /\ x_ExplicitVarSizeWithFlags_Values[q43] = 1 | q43 : int(1..3)]), + or([x_ExplicitVarSizeWithDummy[q38] != 4 /\ x_ExplicitVarSizeWithDummy[q38] = 1 | q38 : int(1..3)]), + or([x_ExplicitVarSizeWithFlags_Flags[q40] /\ x_ExplicitVarSizeWithFlags_Values[q40] = 2 | q40 : int(1..3)]), and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 4 | q1 : int(1..2)]), and([x_ExplicitVarSizeWithDummy[q2] = 4 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 4 | q2 : int(1..2)]), + sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 4) | q3 : int(1..3)]) <= 3, and([x_ExplicitVarSizeWithFlags_Flags[q5 + 1] -> x_ExplicitVarSizeWithFlags_Values[q5] < x_ExplicitVarSizeWithFlags_Values[q5 + 1] | q5 : int(1..2)]), and([x_ExplicitVarSizeWithFlags_Flags[q6] = false -> x_ExplicitVarSizeWithFlags_Values[q6] = 1 | q6 : int(1..3)]), and([x_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q7] | q7 : int(1..2)]), + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q8]) | q8 : int(1..3)]) <= 3, and([x_ExplicitVarSizeWithFlags_Flags[q11] -> or([x_ExplicitVarSizeWithDummy[q13] != 4 /\ x_ExplicitVarSizeWithDummy[q13] = x_ExplicitVarSizeWithFlags_Values[q11] @@ -38,6 +35,7 @@ such that x_ExplicitVarSizeWithMarker_Values[q18] < x_ExplicitVarSizeWithMarker_Values[q18 + 1] | q18 : int(1..2)]), and([q19 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q19] = 1 | q19 : int(1..3)]), + x_ExplicitVarSizeWithMarker_Marker <= 3, and([q22 <= x_ExplicitVarSizeWithMarker_Marker -> or([x_ExplicitVarSizeWithDummy[q24] != 4 /\ x_ExplicitVarSizeWithDummy[q24] = x_ExplicitVarSizeWithMarker_Values[q22] diff --git a/tests/exhaustive/basic/set04/expected/model_3_1_1-solution000001.solution b/tests/exhaustive/basic/set04/expected/model_3_1_1-solution000001.solution new file mode 100644 index 0000000000..f90e0ba18c --- /dev/null +++ b/tests/exhaustive/basic/set04/expected/model_3_1_1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2} diff --git a/tests/exhaustive/basic/set04/expected/model_3_1_1-solution000002.solution b/tests/exhaustive/basic/set04/expected/model_3_1_1-solution000002.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set04/expected/model_3_1_1-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_1_3.eprime.orig b/tests/exhaustive/basic/set04/expected/model_3_1_1.eprime similarity index 66% rename from tests/exhaustive/basic/cut_01_on/expected/model_3_1_3.eprime.orig rename to tests/exhaustive/basic/set04/expected/model_3_1_1.eprime index a48a84aee7..11b75e4c19 100644 --- a/tests/exhaustive/basic/cut_01_on/expected/model_3_1_3.eprime.orig +++ b/tests/exhaustive/basic/set04/expected/model_3_1_1.eprime @@ -3,18 +3,16 @@ language ESSENCE' 1.0 find x_ExplicitVarSizeWithMarker_Marker: int(0..3) find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3)] of int(1..3) find x_Occurrence: matrix indexed by [int(1..3)] of bool -find cut1: bool -find cut2: bool -branching on [cut1, cut2, x_Occurrence, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] +branching on [x_Occurrence, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] such that - !cut1 <-> - or([q12 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q12] = 1 | q12 : int(1..3)]) /\ - or([q14 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q14] = 2 | q14 : int(1..3)]), - !cut2 <-> x_Occurrence[1], + or([q11 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q11] = 1 | q11 : int(1..3)]), + x_Occurrence[2], and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] | q1 : int(1..2)]), and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..3)]), + x_ExplicitVarSizeWithMarker_Marker <= 3, + sum([toInt(x_Occurrence[q4]) | q4 : int(1..3)]) <= 3, and([x_Occurrence[q5] -> or([q7 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q7] = q5 | q7 : int(1..3)]) | q5 : int(1..3)]), diff --git a/tests/exhaustive/basic/set04/expected/model_3_1_2-solution000001.solution b/tests/exhaustive/basic/set04/expected/model_3_1_2-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set04/expected/model_3_1_2-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set04/expected/model_3_1_2-solution000002.solution b/tests/exhaustive/basic/set04/expected/model_3_1_2-solution000002.solution new file mode 100644 index 0000000000..f90e0ba18c --- /dev/null +++ b/tests/exhaustive/basic/set04/expected/model_3_1_2-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_1_2.eprime.orig b/tests/exhaustive/basic/set04/expected/model_3_1_2.eprime similarity index 81% rename from tests/exhaustive/basic/cut_01_on/expected/model_3_1_2.eprime.orig rename to tests/exhaustive/basic/set04/expected/model_3_1_2.eprime index 02751a648d..5a6b86cc08 100644 --- a/tests/exhaustive/basic/cut_01_on/expected/model_3_1_2.eprime.orig +++ b/tests/exhaustive/basic/set04/expected/model_3_1_2.eprime @@ -4,20 +4,17 @@ find x_ExplicitVarSizeWithMarker_Marker: int(0..3) find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3)] of int(1..3) find x_Occurrence: matrix indexed by [int(1..3)] of bool find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..3)] of int(1..4) -find cut1: bool -find cut2: bool branching on - [cut1, cut2, x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, - x_Occurrence] + [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_Occurrence] such that - !cut1 <-> - or([q29 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q29] = 1 | q29 : int(1..3)]) /\ - or([q31 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q31] = 2 | q31 : int(1..3)]), - !cut2 <-> x_Occurrence[1], + or([q28 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q28] = 1 | q28 : int(1..3)]), + x_Occurrence[2], and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] | q1 : int(1..2)]), and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..3)]), + x_ExplicitVarSizeWithMarker_Marker <= 3, + sum([toInt(x_Occurrence[q4]) | q4 : int(1..3)]) <= 3, and([x_Occurrence[q22] -> or([q24 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q24] = q22 | q24 : int(1..3)]) @@ -27,6 +24,7 @@ such that and([x_ExplicitVarSizeWithDummy[q5] < x_ExplicitVarSizeWithDummy[q5 + 1] \/ x_ExplicitVarSizeWithDummy[q5] = 4 | q5 : int(1..2)]), and([x_ExplicitVarSizeWithDummy[q6] = 4 -> x_ExplicitVarSizeWithDummy[q6 + 1] = 4 | q6 : int(1..2)]), + sum([toInt(x_ExplicitVarSizeWithDummy[q7] != 4) | q7 : int(1..3)]) <= 3, and([x_ExplicitVarSizeWithDummy[q10] != 4 -> or([q12 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q12] = x_ExplicitVarSizeWithDummy[q10] diff --git a/tests/exhaustive/basic/set04/expected/model_3_1_4-solution000001.solution b/tests/exhaustive/basic/set04/expected/model_3_1_4-solution000001.solution new file mode 100644 index 0000000000..f90e0ba18c --- /dev/null +++ b/tests/exhaustive/basic/set04/expected/model_3_1_4-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2} diff --git a/tests/exhaustive/basic/set04/expected/model_3_1_4-solution000002.solution b/tests/exhaustive/basic/set04/expected/model_3_1_4-solution000002.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set04/expected/model_3_1_4-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_1_4.eprime.orig b/tests/exhaustive/basic/set04/expected/model_3_1_4.eprime similarity index 82% rename from tests/exhaustive/basic/cut_01_on/expected/model_3_1_4.eprime.orig rename to tests/exhaustive/basic/set04/expected/model_3_1_4.eprime index b63ab0aee3..d07b3c46b8 100644 --- a/tests/exhaustive/basic/cut_01_on/expected/model_3_1_4.eprime.orig +++ b/tests/exhaustive/basic/set04/expected/model_3_1_4.eprime @@ -5,20 +5,18 @@ find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3)] of int(1. find x_Occurrence: matrix indexed by [int(1..3)] of bool find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..3)] of bool find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3)] of int(1..3) -find cut1: bool -find cut2: bool branching on - [cut1, cut2, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, - x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_Occurrence] + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithMarker_Marker, + x_ExplicitVarSizeWithMarker_Values, x_Occurrence] such that - !cut1 <-> - or([q30 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q30] = 1 | q30 : int(1..3)]) /\ - or([q32 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q32] = 2 | q32 : int(1..3)]), - !cut2 <-> x_Occurrence[1], + or([q29 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q29] = 1 | q29 : int(1..3)]), + x_Occurrence[2], and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] | q1 : int(1..2)]), and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..3)]), + x_ExplicitVarSizeWithMarker_Marker <= 3, + sum([toInt(x_Occurrence[q4]) | q4 : int(1..3)]) <= 3, and([x_Occurrence[q23] -> or([q25 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q25] = q23 | q25 : int(1..3)]) @@ -30,6 +28,7 @@ such that | q5 : int(1..2)]), and([x_ExplicitVarSizeWithFlags_Flags[q6] = false -> x_ExplicitVarSizeWithFlags_Values[q6] = 1 | q6 : int(1..3)]), and([x_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q7] | q7 : int(1..2)]), + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q8]) | q8 : int(1..3)]) <= 3, and([x_ExplicitVarSizeWithFlags_Flags[q11] -> or([q13 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q13] = x_ExplicitVarSizeWithFlags_Values[q11] diff --git a/tests/exhaustive/basic/set04/expected/model_3_2_1-solution000001.solution b/tests/exhaustive/basic/set04/expected/model_3_2_1-solution000001.solution new file mode 100644 index 0000000000..f90e0ba18c --- /dev/null +++ b/tests/exhaustive/basic/set04/expected/model_3_2_1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2} diff --git a/tests/exhaustive/basic/set04/expected/model_3_2_1-solution000002.solution b/tests/exhaustive/basic/set04/expected/model_3_2_1-solution000002.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set04/expected/model_3_2_1-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_2_1.eprime.orig b/tests/exhaustive/basic/set04/expected/model_3_2_1.eprime similarity index 54% rename from tests/exhaustive/basic/cut_01_on/expected/model_3_2_1.eprime.orig rename to tests/exhaustive/basic/set04/expected/model_3_2_1.eprime index d412332f03..e22f63bd77 100644 --- a/tests/exhaustive/basic/cut_01_on/expected/model_3_2_1.eprime.orig +++ b/tests/exhaustive/basic/set04/expected/model_3_2_1.eprime @@ -4,23 +4,20 @@ find x_ExplicitVarSizeWithMarker_Marker: int(0..3) find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3)] of int(1..3) find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..3)] of int(1..4) find x_Occurrence: matrix indexed by [int(1..3)] of bool -find cut1: bool -find cut2: bool branching on - [cut1, cut2, x_Occurrence, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, - x_ExplicitVarSizeWithDummy] + [x_Occurrence, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy] such that - !cut1 <-> - or([q19 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q19] = 1 | q19 : int(1..3)]) /\ - or([q21 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q21] = 2 | q21 : int(1..3)]), - !cut2 <-> or([x_ExplicitVarSizeWithDummy[q23] != 4 /\ x_ExplicitVarSizeWithDummy[q23] = 1 | q23 : int(1..3)]), + or([q28 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q28] = 1 | q28 : int(1..3)]), + or([x_ExplicitVarSizeWithDummy[q30] != 4 /\ x_ExplicitVarSizeWithDummy[q30] = 2 | q30 : int(1..3)]), and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] | q1 : int(1..2)]), and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..3)]), + x_ExplicitVarSizeWithMarker_Marker <= 3, and([x_ExplicitVarSizeWithDummy[q4] < x_ExplicitVarSizeWithDummy[q4 + 1] \/ x_ExplicitVarSizeWithDummy[q4] = 4 | q4 : int(1..2)]), and([x_ExplicitVarSizeWithDummy[q5] = 4 -> x_ExplicitVarSizeWithDummy[q5 + 1] = 4 | q5 : int(1..2)]), + sum([toInt(x_ExplicitVarSizeWithDummy[q6] != 4) | q6 : int(1..3)]) <= 3, and([x_ExplicitVarSizeWithDummy[q9] != 4 -> or([q11 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q11] = x_ExplicitVarSizeWithDummy[q9] @@ -31,14 +28,15 @@ such that x_ExplicitVarSizeWithDummy[q15] = x_ExplicitVarSizeWithMarker_Values[q13] | q15 : int(1..3)]) | q13 : int(1..3)]), - and([x_Occurrence[q24] -> - or([q26 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q26] = q24 - | q26 : int(1..3)]) - | q24 : int(1..3)]), - and([q28 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q28]] - | q28 : int(1..3)]), - and([x_Occurrence[q29] -> - or([x_ExplicitVarSizeWithDummy[q31] != 4 /\ x_ExplicitVarSizeWithDummy[q31] = q29 | q31 : int(1..3)]) - | q29 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q33] != 4 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q33]] | q33 : int(1..3)]) + sum([toInt(x_Occurrence[q16]) | q16 : int(1..3)]) <= 3, + and([x_Occurrence[q17] -> + or([q19 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q19] = q17 + | q19 : int(1..3)]) + | q17 : int(1..3)]), + and([q21 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q21]] + | q21 : int(1..3)]), + and([x_Occurrence[q22] -> + or([x_ExplicitVarSizeWithDummy[q24] != 4 /\ x_ExplicitVarSizeWithDummy[q24] = q22 | q24 : int(1..3)]) + | q22 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q26] != 4 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q26]] | q26 : int(1..3)]) diff --git a/tests/exhaustive/basic/set04/expected/model_3_2_2-solution000001.solution b/tests/exhaustive/basic/set04/expected/model_3_2_2-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set04/expected/model_3_2_2-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set04/expected/model_3_2_2-solution000002.solution b/tests/exhaustive/basic/set04/expected/model_3_2_2-solution000002.solution new file mode 100644 index 0000000000..f90e0ba18c --- /dev/null +++ b/tests/exhaustive/basic/set04/expected/model_3_2_2-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_2_3.eprime.orig b/tests/exhaustive/basic/set04/expected/model_3_2_2.eprime similarity index 71% rename from tests/exhaustive/basic/cut_01_on/expected/model_3_2_3.eprime.orig rename to tests/exhaustive/basic/set04/expected/model_3_2_2.eprime index afa2877b97..29d9a0d39b 100644 --- a/tests/exhaustive/basic/cut_01_on/expected/model_3_2_3.eprime.orig +++ b/tests/exhaustive/basic/set04/expected/model_3_2_2.eprime @@ -3,22 +3,19 @@ language ESSENCE' 1.0 find x_ExplicitVarSizeWithMarker_Marker: int(0..3) find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3)] of int(1..3) find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..3)] of int(1..4) -find cut1: bool -find cut2: bool -branching on - [cut1, cut2, x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] +branching on [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] such that - !cut1 <-> - or([q18 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q18] = 1 | q18 : int(1..3)]) /\ - or([q20 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q20] = 2 | q20 : int(1..3)]), - !cut2 <-> or([x_ExplicitVarSizeWithDummy[q22] != 4 /\ x_ExplicitVarSizeWithDummy[q22] = 1 | q22 : int(1..3)]), + or([q17 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q17] = 1 | q17 : int(1..3)]), + or([x_ExplicitVarSizeWithDummy[q19] != 4 /\ x_ExplicitVarSizeWithDummy[q19] = 2 | q19 : int(1..3)]), and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] | q1 : int(1..2)]), and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..3)]), + x_ExplicitVarSizeWithMarker_Marker <= 3, and([x_ExplicitVarSizeWithDummy[q4] < x_ExplicitVarSizeWithDummy[q4 + 1] \/ x_ExplicitVarSizeWithDummy[q4] = 4 | q4 : int(1..2)]), and([x_ExplicitVarSizeWithDummy[q5] = 4 -> x_ExplicitVarSizeWithDummy[q5 + 1] = 4 | q5 : int(1..2)]), + sum([toInt(x_ExplicitVarSizeWithDummy[q6] != 4) | q6 : int(1..3)]) <= 3, and([x_ExplicitVarSizeWithDummy[q9] != 4 -> or([q11 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q11] = x_ExplicitVarSizeWithDummy[q9] diff --git a/tests/exhaustive/basic/set04/expected/model_3_2_4-solution000001.solution b/tests/exhaustive/basic/set04/expected/model_3_2_4-solution000001.solution new file mode 100644 index 0000000000..f90e0ba18c --- /dev/null +++ b/tests/exhaustive/basic/set04/expected/model_3_2_4-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2} diff --git a/tests/exhaustive/basic/set04/expected/model_3_2_4-solution000002.solution b/tests/exhaustive/basic/set04/expected/model_3_2_4-solution000002.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set04/expected/model_3_2_4-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_2_4.eprime.orig b/tests/exhaustive/basic/set04/expected/model_3_2_4.eprime similarity index 83% rename from tests/exhaustive/basic/cut_01_on/expected/model_3_2_4.eprime.orig rename to tests/exhaustive/basic/set04/expected/model_3_2_4.eprime index c1b1de927b..73a3773a1d 100644 --- a/tests/exhaustive/basic/cut_01_on/expected/model_3_2_4.eprime.orig +++ b/tests/exhaustive/basic/set04/expected/model_3_2_4.eprime @@ -5,23 +5,21 @@ find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3)] of int(1. find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..3)] of int(1..4) find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..3)] of bool find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3)] of int(1..3) -find cut1: bool -find cut2: bool branching on - [cut1, cut2, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, - x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy] + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithMarker_Marker, + x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy] such that - !cut1 <-> - or([q39 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q39] = 1 | q39 : int(1..3)]) /\ - or([q41 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q41] = 2 | q41 : int(1..3)]), - !cut2 <-> or([x_ExplicitVarSizeWithDummy[q43] != 4 /\ x_ExplicitVarSizeWithDummy[q43] = 1 | q43 : int(1..3)]), + or([q38 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q38] = 1 | q38 : int(1..3)]), + or([x_ExplicitVarSizeWithDummy[q40] != 4 /\ x_ExplicitVarSizeWithDummy[q40] = 2 | q40 : int(1..3)]), and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] | q1 : int(1..2)]), and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..3)]), + x_ExplicitVarSizeWithMarker_Marker <= 3, and([x_ExplicitVarSizeWithDummy[q4] < x_ExplicitVarSizeWithDummy[q4 + 1] \/ x_ExplicitVarSizeWithDummy[q4] = 4 | q4 : int(1..2)]), and([x_ExplicitVarSizeWithDummy[q5] = 4 -> x_ExplicitVarSizeWithDummy[q5 + 1] = 4 | q5 : int(1..2)]), + sum([toInt(x_ExplicitVarSizeWithDummy[q6] != 4) | q6 : int(1..3)]) <= 3, and([x_ExplicitVarSizeWithDummy[q9] != 4 -> or([q11 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q11] = x_ExplicitVarSizeWithDummy[q9] @@ -38,6 +36,7 @@ such that and([x_ExplicitVarSizeWithFlags_Flags[q17] = false -> x_ExplicitVarSizeWithFlags_Values[q17] = 1 | q17 : int(1..3)]), and([x_ExplicitVarSizeWithFlags_Flags[q18 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q18] | q18 : int(1..2)]), + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q19]) | q19 : int(1..3)]) <= 3, and([x_ExplicitVarSizeWithFlags_Flags[q22] -> or([q24 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q24] = x_ExplicitVarSizeWithFlags_Values[q22] diff --git a/tests/exhaustive/basic/set04/expected/model_3_3_1-solution000001.solution b/tests/exhaustive/basic/set04/expected/model_3_3_1-solution000001.solution new file mode 100644 index 0000000000..f90e0ba18c --- /dev/null +++ b/tests/exhaustive/basic/set04/expected/model_3_3_1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2} diff --git a/tests/exhaustive/basic/set04/expected/model_3_3_1-solution000002.solution b/tests/exhaustive/basic/set04/expected/model_3_3_1-solution000002.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set04/expected/model_3_3_1-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_1_1.eprime.orig b/tests/exhaustive/basic/set04/expected/model_3_3_1.eprime similarity index 65% rename from tests/exhaustive/basic/cut_01_on/expected/model_3_1_1.eprime.orig rename to tests/exhaustive/basic/set04/expected/model_3_3_1.eprime index a48a84aee7..2c7c27bef8 100644 --- a/tests/exhaustive/basic/cut_01_on/expected/model_3_1_1.eprime.orig +++ b/tests/exhaustive/basic/set04/expected/model_3_3_1.eprime @@ -3,18 +3,16 @@ language ESSENCE' 1.0 find x_ExplicitVarSizeWithMarker_Marker: int(0..3) find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3)] of int(1..3) find x_Occurrence: matrix indexed by [int(1..3)] of bool -find cut1: bool -find cut2: bool -branching on [cut1, cut2, x_Occurrence, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] +branching on [x_Occurrence, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] such that - !cut1 <-> - or([q12 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q12] = 1 | q12 : int(1..3)]) /\ - or([q14 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q14] = 2 | q14 : int(1..3)]), - !cut2 <-> x_Occurrence[1], + or([q11 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q11] = 1 | q11 : int(1..3)]), + or([q13 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q13] = 2 | q13 : int(1..3)]), and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] | q1 : int(1..2)]), and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..3)]), + x_ExplicitVarSizeWithMarker_Marker <= 3, + sum([toInt(x_Occurrence[q4]) | q4 : int(1..3)]) <= 3, and([x_Occurrence[q5] -> or([q7 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q7] = q5 | q7 : int(1..3)]) | q5 : int(1..3)]), diff --git a/tests/exhaustive/basic/set04/expected/model_3_3_2-solution000001.solution b/tests/exhaustive/basic/set04/expected/model_3_3_2-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set04/expected/model_3_3_2-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set04/expected/model_3_3_2-solution000002.solution b/tests/exhaustive/basic/set04/expected/model_3_3_2-solution000002.solution new file mode 100644 index 0000000000..f90e0ba18c --- /dev/null +++ b/tests/exhaustive/basic/set04/expected/model_3_3_2-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_2_2.eprime.orig b/tests/exhaustive/basic/set04/expected/model_3_3_2.eprime similarity index 71% rename from tests/exhaustive/basic/cut_01_on/expected/model_3_2_2.eprime.orig rename to tests/exhaustive/basic/set04/expected/model_3_3_2.eprime index afa2877b97..3b583676e9 100644 --- a/tests/exhaustive/basic/cut_01_on/expected/model_3_2_2.eprime.orig +++ b/tests/exhaustive/basic/set04/expected/model_3_3_2.eprime @@ -3,22 +3,19 @@ language ESSENCE' 1.0 find x_ExplicitVarSizeWithMarker_Marker: int(0..3) find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3)] of int(1..3) find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..3)] of int(1..4) -find cut1: bool -find cut2: bool -branching on - [cut1, cut2, x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] +branching on [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] such that - !cut1 <-> - or([q18 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q18] = 1 | q18 : int(1..3)]) /\ - or([q20 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q20] = 2 | q20 : int(1..3)]), - !cut2 <-> or([x_ExplicitVarSizeWithDummy[q22] != 4 /\ x_ExplicitVarSizeWithDummy[q22] = 1 | q22 : int(1..3)]), + or([q17 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q17] = 1 | q17 : int(1..3)]), + or([q19 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q19] = 2 | q19 : int(1..3)]), and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] | q1 : int(1..2)]), and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..3)]), + x_ExplicitVarSizeWithMarker_Marker <= 3, and([x_ExplicitVarSizeWithDummy[q4] < x_ExplicitVarSizeWithDummy[q4 + 1] \/ x_ExplicitVarSizeWithDummy[q4] = 4 | q4 : int(1..2)]), and([x_ExplicitVarSizeWithDummy[q5] = 4 -> x_ExplicitVarSizeWithDummy[q5 + 1] = 4 | q5 : int(1..2)]), + sum([toInt(x_ExplicitVarSizeWithDummy[q6] != 4) | q6 : int(1..3)]) <= 3, and([x_ExplicitVarSizeWithDummy[q9] != 4 -> or([q11 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q11] = x_ExplicitVarSizeWithDummy[q9] diff --git a/tests/exhaustive/basic/set04/expected/model_3_3_3-solution000001.solution b/tests/exhaustive/basic/set04/expected/model_3_3_3-solution000001.solution new file mode 100644 index 0000000000..f90e0ba18c --- /dev/null +++ b/tests/exhaustive/basic/set04/expected/model_3_3_3-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2} diff --git a/tests/exhaustive/basic/set04/expected/model_3_3_3-solution000002.solution b/tests/exhaustive/basic/set04/expected/model_3_3_3-solution000002.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set04/expected/model_3_3_3-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set04/expected/model_3_3_3.eprime b/tests/exhaustive/basic/set04/expected/model_3_3_3.eprime new file mode 100644 index 0000000000..ac50cfaa35 --- /dev/null +++ b/tests/exhaustive/basic/set04/expected/model_3_3_3.eprime @@ -0,0 +1,14 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..3) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3)] of int(1..3) +branching on [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] +such that + or([q5 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q5] = 1 | q5 : int(1..3)]), + or([q7 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q7] = 2 | q7 : int(1..3)]), + and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] + | q1 : int(1..2)]), + and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..3)]), + x_ExplicitVarSizeWithMarker_Marker <= 3 + diff --git a/tests/exhaustive/basic/set04/expected/model_3_3_4-solution000001.solution b/tests/exhaustive/basic/set04/expected/model_3_3_4-solution000001.solution new file mode 100644 index 0000000000..f90e0ba18c --- /dev/null +++ b/tests/exhaustive/basic/set04/expected/model_3_3_4-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2} diff --git a/tests/exhaustive/basic/set04/expected/model_3_3_4-solution000002.solution b/tests/exhaustive/basic/set04/expected/model_3_3_4-solution000002.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set04/expected/model_3_3_4-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_4_4.eprime.orig b/tests/exhaustive/basic/set04/expected/model_3_3_4.eprime similarity index 73% rename from tests/exhaustive/basic/cut_01_on/expected/model_3_4_4.eprime.orig rename to tests/exhaustive/basic/set04/expected/model_3_3_4.eprime index 04a3b8e694..d4336a8b4e 100644 --- a/tests/exhaustive/basic/cut_01_on/expected/model_3_4_4.eprime.orig +++ b/tests/exhaustive/basic/set04/expected/model_3_3_4.eprime @@ -4,26 +4,23 @@ find x_ExplicitVarSizeWithMarker_Marker: int(0..3) find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3)] of int(1..3) find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..3)] of bool find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3)] of int(1..3) -find cut1: bool -find cut2: bool branching on - [cut1, cut2, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, - x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithMarker_Marker, + x_ExplicitVarSizeWithMarker_Values] such that - !cut1 <-> - or([q19 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q19] = 1 | q19 : int(1..3)]) /\ - or([q21 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q21] = 2 | q21 : int(1..3)]), - !cut2 <-> - or([x_ExplicitVarSizeWithFlags_Flags[q23] /\ x_ExplicitVarSizeWithFlags_Values[q23] = 1 | q23 : int(1..3)]), + or([q18 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q18] = 1 | q18 : int(1..3)]), + or([q20 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q20] = 2 | q20 : int(1..3)]), and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] | q1 : int(1..2)]), and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..3)]), + x_ExplicitVarSizeWithMarker_Marker <= 3, and([x_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> x_ExplicitVarSizeWithFlags_Values[q4] < x_ExplicitVarSizeWithFlags_Values[q4 + 1] | q4 : int(1..2)]), and([x_ExplicitVarSizeWithFlags_Flags[q5] = false -> x_ExplicitVarSizeWithFlags_Values[q5] = 1 | q5 : int(1..3)]), and([x_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q6] | q6 : int(1..2)]), + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q7]) | q7 : int(1..3)]) <= 3, and([x_ExplicitVarSizeWithFlags_Flags[q10] -> or([q12 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q12] = x_ExplicitVarSizeWithFlags_Values[q10] diff --git a/tests/exhaustive/basic/set04/expected/model_3_4_1-solution000001.solution b/tests/exhaustive/basic/set04/expected/model_3_4_1-solution000001.solution new file mode 100644 index 0000000000..f90e0ba18c --- /dev/null +++ b/tests/exhaustive/basic/set04/expected/model_3_4_1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2} diff --git a/tests/exhaustive/basic/set04/expected/model_3_4_1-solution000002.solution b/tests/exhaustive/basic/set04/expected/model_3_4_1-solution000002.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set04/expected/model_3_4_1-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_4_1.eprime.orig b/tests/exhaustive/basic/set04/expected/model_3_4_1.eprime similarity index 82% rename from tests/exhaustive/basic/cut_01_on/expected/model_3_4_1.eprime.orig rename to tests/exhaustive/basic/set04/expected/model_3_4_1.eprime index 5941707e6f..72055038e8 100644 --- a/tests/exhaustive/basic/cut_01_on/expected/model_3_4_1.eprime.orig +++ b/tests/exhaustive/basic/set04/expected/model_3_4_1.eprime @@ -5,26 +5,23 @@ find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3)] of int(1. find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..3)] of bool find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3)] of int(1..3) find x_Occurrence: matrix indexed by [int(1..3)] of bool -find cut1: bool -find cut2: bool branching on - [cut1, cut2, x_Occurrence, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, + [x_Occurrence, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] such that - !cut1 <-> - or([q30 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q30] = 1 | q30 : int(1..3)]) /\ - or([q32 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q32] = 2 | q32 : int(1..3)]), - !cut2 <-> - or([x_ExplicitVarSizeWithFlags_Flags[q34] /\ x_ExplicitVarSizeWithFlags_Values[q34] = 1 | q34 : int(1..3)]), + or([q29 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q29] = 1 | q29 : int(1..3)]), + or([x_ExplicitVarSizeWithFlags_Flags[q31] /\ x_ExplicitVarSizeWithFlags_Values[q31] = 2 | q31 : int(1..3)]), and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] | q1 : int(1..2)]), and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..3)]), + x_ExplicitVarSizeWithMarker_Marker <= 3, and([x_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> x_ExplicitVarSizeWithFlags_Values[q4] < x_ExplicitVarSizeWithFlags_Values[q4 + 1] | q4 : int(1..2)]), and([x_ExplicitVarSizeWithFlags_Flags[q5] = false -> x_ExplicitVarSizeWithFlags_Values[q5] = 1 | q5 : int(1..3)]), and([x_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q6] | q6 : int(1..2)]), + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q7]) | q7 : int(1..3)]) <= 3, and([x_ExplicitVarSizeWithFlags_Flags[q10] -> or([q12 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q12] = x_ExplicitVarSizeWithFlags_Values[q10] @@ -35,6 +32,7 @@ such that x_ExplicitVarSizeWithFlags_Values[q16] = x_ExplicitVarSizeWithMarker_Values[q14] | q16 : int(1..3)]) | q14 : int(1..3)]), + sum([toInt(x_Occurrence[q17]) | q17 : int(1..3)]) <= 3, and([x_Occurrence[q18] -> or([q20 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q20] = q18 | q20 : int(1..3)]) diff --git a/tests/exhaustive/basic/set04/expected/model_3_4_2-solution000001.solution b/tests/exhaustive/basic/set04/expected/model_3_4_2-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set04/expected/model_3_4_2-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set04/expected/model_3_4_2-solution000002.solution b/tests/exhaustive/basic/set04/expected/model_3_4_2-solution000002.solution new file mode 100644 index 0000000000..f90e0ba18c --- /dev/null +++ b/tests/exhaustive/basic/set04/expected/model_3_4_2-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_4_2.eprime.orig b/tests/exhaustive/basic/set04/expected/model_3_4_2.eprime similarity index 85% rename from tests/exhaustive/basic/cut_01_on/expected/model_3_4_2.eprime.orig rename to tests/exhaustive/basic/set04/expected/model_3_4_2.eprime index acf89d418d..3d0a63ab93 100644 --- a/tests/exhaustive/basic/cut_01_on/expected/model_3_4_2.eprime.orig +++ b/tests/exhaustive/basic/set04/expected/model_3_4_2.eprime @@ -5,26 +5,23 @@ find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3)] of int(1. find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..3)] of bool find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3)] of int(1..3) find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..3)] of int(1..4) -find cut1: bool -find cut2: bool branching on - [cut1, cut2, x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, + [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] such that - !cut1 <-> - or([q39 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q39] = 1 | q39 : int(1..3)]) /\ - or([q41 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q41] = 2 | q41 : int(1..3)]), - !cut2 <-> - or([x_ExplicitVarSizeWithFlags_Flags[q43] /\ x_ExplicitVarSizeWithFlags_Values[q43] = 1 | q43 : int(1..3)]), + or([q38 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q38] = 1 | q38 : int(1..3)]), + or([x_ExplicitVarSizeWithFlags_Flags[q40] /\ x_ExplicitVarSizeWithFlags_Values[q40] = 2 | q40 : int(1..3)]), and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] | q1 : int(1..2)]), and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..3)]), + x_ExplicitVarSizeWithMarker_Marker <= 3, and([x_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> x_ExplicitVarSizeWithFlags_Values[q4] < x_ExplicitVarSizeWithFlags_Values[q4 + 1] | q4 : int(1..2)]), and([x_ExplicitVarSizeWithFlags_Flags[q5] = false -> x_ExplicitVarSizeWithFlags_Values[q5] = 1 | q5 : int(1..3)]), and([x_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q6] | q6 : int(1..2)]), + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q7]) | q7 : int(1..3)]) <= 3, and([x_ExplicitVarSizeWithFlags_Flags[q10] -> or([q12 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q12] = x_ExplicitVarSizeWithFlags_Values[q10] @@ -38,6 +35,7 @@ such that and([x_ExplicitVarSizeWithDummy[q17] < x_ExplicitVarSizeWithDummy[q17 + 1] \/ x_ExplicitVarSizeWithDummy[q17] = 4 | q17 : int(1..2)]), and([x_ExplicitVarSizeWithDummy[q18] = 4 -> x_ExplicitVarSizeWithDummy[q18 + 1] = 4 | q18 : int(1..2)]), + sum([toInt(x_ExplicitVarSizeWithDummy[q19] != 4) | q19 : int(1..3)]) <= 3, and([x_ExplicitVarSizeWithDummy[q22] != 4 -> or([q24 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q24] = x_ExplicitVarSizeWithDummy[q22] diff --git a/tests/exhaustive/basic/set04/expected/model_3_4_3-solution000001.solution b/tests/exhaustive/basic/set04/expected/model_3_4_3-solution000001.solution new file mode 100644 index 0000000000..f90e0ba18c --- /dev/null +++ b/tests/exhaustive/basic/set04/expected/model_3_4_3-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2} diff --git a/tests/exhaustive/basic/set04/expected/model_3_4_3-solution000002.solution b/tests/exhaustive/basic/set04/expected/model_3_4_3-solution000002.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set04/expected/model_3_4_3-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_4_3.eprime.orig b/tests/exhaustive/basic/set04/expected/model_3_4_3.eprime similarity index 73% rename from tests/exhaustive/basic/cut_01_on/expected/model_3_4_3.eprime.orig rename to tests/exhaustive/basic/set04/expected/model_3_4_3.eprime index 04a3b8e694..0c780bf7c5 100644 --- a/tests/exhaustive/basic/cut_01_on/expected/model_3_4_3.eprime.orig +++ b/tests/exhaustive/basic/set04/expected/model_3_4_3.eprime @@ -4,26 +4,23 @@ find x_ExplicitVarSizeWithMarker_Marker: int(0..3) find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3)] of int(1..3) find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..3)] of bool find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3)] of int(1..3) -find cut1: bool -find cut2: bool branching on - [cut1, cut2, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, - x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithMarker_Marker, + x_ExplicitVarSizeWithMarker_Values] such that - !cut1 <-> - or([q19 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q19] = 1 | q19 : int(1..3)]) /\ - or([q21 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q21] = 2 | q21 : int(1..3)]), - !cut2 <-> - or([x_ExplicitVarSizeWithFlags_Flags[q23] /\ x_ExplicitVarSizeWithFlags_Values[q23] = 1 | q23 : int(1..3)]), + or([q18 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q18] = 1 | q18 : int(1..3)]), + or([x_ExplicitVarSizeWithFlags_Flags[q20] /\ x_ExplicitVarSizeWithFlags_Values[q20] = 2 | q20 : int(1..3)]), and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] | q1 : int(1..2)]), and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..3)]), + x_ExplicitVarSizeWithMarker_Marker <= 3, and([x_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> x_ExplicitVarSizeWithFlags_Values[q4] < x_ExplicitVarSizeWithFlags_Values[q4 + 1] | q4 : int(1..2)]), and([x_ExplicitVarSizeWithFlags_Flags[q5] = false -> x_ExplicitVarSizeWithFlags_Values[q5] = 1 | q5 : int(1..3)]), and([x_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q6] | q6 : int(1..2)]), + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q7]) | q7 : int(1..3)]) <= 3, and([x_ExplicitVarSizeWithFlags_Flags[q10] -> or([q12 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q12] = x_ExplicitVarSizeWithFlags_Values[q10] diff --git a/tests/exhaustive/basic/set04/expected/model_4_1_1-solution000001.solution b/tests/exhaustive/basic/set04/expected/model_4_1_1-solution000001.solution new file mode 100644 index 0000000000..f90e0ba18c --- /dev/null +++ b/tests/exhaustive/basic/set04/expected/model_4_1_1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2} diff --git a/tests/exhaustive/basic/set04/expected/model_4_1_1-solution000002.solution b/tests/exhaustive/basic/set04/expected/model_4_1_1-solution000002.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set04/expected/model_4_1_1-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_1_4.eprime.orig b/tests/exhaustive/basic/set04/expected/model_4_1_1.eprime similarity index 70% rename from tests/exhaustive/basic/cut_01_on/expected/model_4_1_4.eprime.orig rename to tests/exhaustive/basic/set04/expected/model_4_1_1.eprime index 5d7a188800..5e98c11020 100644 --- a/tests/exhaustive/basic/cut_01_on/expected/model_4_1_4.eprime.orig +++ b/tests/exhaustive/basic/set04/expected/model_4_1_1.eprime @@ -3,19 +3,17 @@ language ESSENCE' 1.0 find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..3)] of bool find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3)] of int(1..3) find x_Occurrence: matrix indexed by [int(1..3)] of bool -find cut1: bool -find cut2: bool -branching on [cut1, cut2, x_Occurrence, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] +branching on [x_Occurrence, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] such that - !cut1 <-> - or([x_ExplicitVarSizeWithFlags_Flags[q14] /\ x_ExplicitVarSizeWithFlags_Values[q14] = 1 | q14 : int(1..3)]) /\ - or([x_ExplicitVarSizeWithFlags_Flags[q16] /\ x_ExplicitVarSizeWithFlags_Values[q16] = 2 | q16 : int(1..3)]), - !cut2 <-> x_Occurrence[1], + or([x_ExplicitVarSizeWithFlags_Flags[q13] /\ x_ExplicitVarSizeWithFlags_Values[q13] = 1 | q13 : int(1..3)]), + x_Occurrence[2], and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] | q1 : int(1..2)]), and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..3)]), and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..2)]), + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..3)]) <= 3, + sum([toInt(x_Occurrence[q6]) | q6 : int(1..3)]) <= 3, and([x_Occurrence[q7] -> or([x_ExplicitVarSizeWithFlags_Flags[q9] /\ x_ExplicitVarSizeWithFlags_Values[q9] = q7 | q9 : int(1..3)]) | q7 : int(1..3)]), diff --git a/tests/exhaustive/basic/set04/expected/model_4_1_2-solution000001.solution b/tests/exhaustive/basic/set04/expected/model_4_1_2-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set04/expected/model_4_1_2-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set04/expected/model_4_1_2-solution000002.solution b/tests/exhaustive/basic/set04/expected/model_4_1_2-solution000002.solution new file mode 100644 index 0000000000..f90e0ba18c --- /dev/null +++ b/tests/exhaustive/basic/set04/expected/model_4_1_2-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_1_2.eprime.orig b/tests/exhaustive/basic/set04/expected/model_4_1_2.eprime similarity index 82% rename from tests/exhaustive/basic/cut_01_on/expected/model_4_1_2.eprime.orig rename to tests/exhaustive/basic/set04/expected/model_4_1_2.eprime index 07bbb3554a..22076b537b 100644 --- a/tests/exhaustive/basic/cut_01_on/expected/model_4_1_2.eprime.orig +++ b/tests/exhaustive/basic/set04/expected/model_4_1_2.eprime @@ -4,21 +4,18 @@ find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..3)] of bool find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3)] of int(1..3) find x_Occurrence: matrix indexed by [int(1..3)] of bool find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..3)] of int(1..4) -find cut1: bool -find cut2: bool branching on - [cut1, cut2, x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, - x_Occurrence] + [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_Occurrence] such that - !cut1 <-> - or([x_ExplicitVarSizeWithFlags_Flags[q31] /\ x_ExplicitVarSizeWithFlags_Values[q31] = 1 | q31 : int(1..3)]) /\ - or([x_ExplicitVarSizeWithFlags_Flags[q33] /\ x_ExplicitVarSizeWithFlags_Values[q33] = 2 | q33 : int(1..3)]), - !cut2 <-> x_Occurrence[1], + or([x_ExplicitVarSizeWithFlags_Flags[q30] /\ x_ExplicitVarSizeWithFlags_Values[q30] = 1 | q30 : int(1..3)]), + x_Occurrence[2], and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] | q1 : int(1..2)]), and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..3)]), and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..2)]), + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..3)]) <= 3, + sum([toInt(x_Occurrence[q6]) | q6 : int(1..3)]) <= 3, and([x_Occurrence[q24] -> or([x_ExplicitVarSizeWithFlags_Flags[q26] /\ x_ExplicitVarSizeWithFlags_Values[q26] = q24 | q26 : int(1..3)]) | q24 : int(1..3)]), @@ -27,6 +24,7 @@ such that and([x_ExplicitVarSizeWithDummy[q7] < x_ExplicitVarSizeWithDummy[q7 + 1] \/ x_ExplicitVarSizeWithDummy[q7] = 4 | q7 : int(1..2)]), and([x_ExplicitVarSizeWithDummy[q8] = 4 -> x_ExplicitVarSizeWithDummy[q8 + 1] = 4 | q8 : int(1..2)]), + sum([toInt(x_ExplicitVarSizeWithDummy[q9] != 4) | q9 : int(1..3)]) <= 3, and([x_ExplicitVarSizeWithDummy[q12] != 4 -> or([x_ExplicitVarSizeWithFlags_Flags[q14] /\ x_ExplicitVarSizeWithFlags_Values[q14] = x_ExplicitVarSizeWithDummy[q12] diff --git a/tests/exhaustive/basic/set04/expected/model_4_1_3-solution000001.solution b/tests/exhaustive/basic/set04/expected/model_4_1_3-solution000001.solution new file mode 100644 index 0000000000..f90e0ba18c --- /dev/null +++ b/tests/exhaustive/basic/set04/expected/model_4_1_3-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2} diff --git a/tests/exhaustive/basic/set04/expected/model_4_1_3-solution000002.solution b/tests/exhaustive/basic/set04/expected/model_4_1_3-solution000002.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set04/expected/model_4_1_3-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_1_3.eprime.orig b/tests/exhaustive/basic/set04/expected/model_4_1_3.eprime similarity index 82% rename from tests/exhaustive/basic/cut_01_on/expected/model_4_1_3.eprime.orig rename to tests/exhaustive/basic/set04/expected/model_4_1_3.eprime index 0fe7e57c62..c4e74c86f3 100644 --- a/tests/exhaustive/basic/cut_01_on/expected/model_4_1_3.eprime.orig +++ b/tests/exhaustive/basic/set04/expected/model_4_1_3.eprime @@ -5,21 +5,19 @@ find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3)] of int(1.. find x_Occurrence: matrix indexed by [int(1..3)] of bool find x_ExplicitVarSizeWithMarker_Marker: int(0..3) find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3)] of int(1..3) -find cut1: bool -find cut2: bool branching on - [cut1, cut2, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, - x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_Occurrence] + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithFlags_Flags, + x_ExplicitVarSizeWithFlags_Values, x_Occurrence] such that - !cut1 <-> - or([x_ExplicitVarSizeWithFlags_Flags[q30] /\ x_ExplicitVarSizeWithFlags_Values[q30] = 1 | q30 : int(1..3)]) /\ - or([x_ExplicitVarSizeWithFlags_Flags[q32] /\ x_ExplicitVarSizeWithFlags_Values[q32] = 2 | q32 : int(1..3)]), - !cut2 <-> x_Occurrence[1], + or([x_ExplicitVarSizeWithFlags_Flags[q29] /\ x_ExplicitVarSizeWithFlags_Values[q29] = 1 | q29 : int(1..3)]), + x_Occurrence[2], and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] | q1 : int(1..2)]), and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..3)]), and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..2)]), + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..3)]) <= 3, + sum([toInt(x_Occurrence[q6]) | q6 : int(1..3)]) <= 3, and([x_Occurrence[q23] -> or([x_ExplicitVarSizeWithFlags_Flags[q25] /\ x_ExplicitVarSizeWithFlags_Values[q25] = q23 | q25 : int(1..3)]) | q23 : int(1..3)]), @@ -29,6 +27,7 @@ such that x_ExplicitVarSizeWithMarker_Values[q7] < x_ExplicitVarSizeWithMarker_Values[q7 + 1] | q7 : int(1..2)]), and([q8 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q8] = 1 | q8 : int(1..3)]), + x_ExplicitVarSizeWithMarker_Marker <= 3, and([q11 <= x_ExplicitVarSizeWithMarker_Marker -> or([x_ExplicitVarSizeWithFlags_Flags[q13] /\ x_ExplicitVarSizeWithFlags_Values[q13] = x_ExplicitVarSizeWithMarker_Values[q11] diff --git a/tests/exhaustive/basic/set04/expected/model_4_2_1-solution000001.solution b/tests/exhaustive/basic/set04/expected/model_4_2_1-solution000001.solution new file mode 100644 index 0000000000..f90e0ba18c --- /dev/null +++ b/tests/exhaustive/basic/set04/expected/model_4_2_1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2} diff --git a/tests/exhaustive/basic/set04/expected/model_4_2_1-solution000002.solution b/tests/exhaustive/basic/set04/expected/model_4_2_1-solution000002.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set04/expected/model_4_2_1-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_2_1.eprime.orig b/tests/exhaustive/basic/set04/expected/model_4_2_1.eprime similarity index 79% rename from tests/exhaustive/basic/cut_01_on/expected/model_4_2_1.eprime.orig rename to tests/exhaustive/basic/set04/expected/model_4_2_1.eprime index 34ffb66fa4..3e4cb54b04 100644 --- a/tests/exhaustive/basic/cut_01_on/expected/model_4_2_1.eprime.orig +++ b/tests/exhaustive/basic/set04/expected/model_4_2_1.eprime @@ -4,24 +4,21 @@ find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..3)] of bool find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3)] of int(1..3) find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..3)] of int(1..4) find x_Occurrence: matrix indexed by [int(1..3)] of bool -find cut1: bool -find cut2: bool branching on - [cut1, cut2, x_Occurrence, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, - x_ExplicitVarSizeWithDummy] + [x_Occurrence, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy] such that - !cut1 <-> - or([x_ExplicitVarSizeWithFlags_Flags[q31] /\ x_ExplicitVarSizeWithFlags_Values[q31] = 1 | q31 : int(1..3)]) /\ - or([x_ExplicitVarSizeWithFlags_Flags[q33] /\ x_ExplicitVarSizeWithFlags_Values[q33] = 2 | q33 : int(1..3)]), - !cut2 <-> or([x_ExplicitVarSizeWithDummy[q35] != 4 /\ x_ExplicitVarSizeWithDummy[q35] = 1 | q35 : int(1..3)]), + or([x_ExplicitVarSizeWithFlags_Flags[q30] /\ x_ExplicitVarSizeWithFlags_Values[q30] = 1 | q30 : int(1..3)]), + or([x_ExplicitVarSizeWithDummy[q32] != 4 /\ x_ExplicitVarSizeWithDummy[q32] = 2 | q32 : int(1..3)]), and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] | q1 : int(1..2)]), and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..3)]), and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..2)]), + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..3)]) <= 3, and([x_ExplicitVarSizeWithDummy[q6] < x_ExplicitVarSizeWithDummy[q6 + 1] \/ x_ExplicitVarSizeWithDummy[q6] = 4 | q6 : int(1..2)]), and([x_ExplicitVarSizeWithDummy[q7] = 4 -> x_ExplicitVarSizeWithDummy[q7 + 1] = 4 | q7 : int(1..2)]), + sum([toInt(x_ExplicitVarSizeWithDummy[q8] != 4) | q8 : int(1..3)]) <= 3, and([x_ExplicitVarSizeWithDummy[q11] != 4 -> or([x_ExplicitVarSizeWithFlags_Flags[q13] /\ x_ExplicitVarSizeWithFlags_Values[q13] = x_ExplicitVarSizeWithDummy[q11] @@ -32,6 +29,7 @@ such that x_ExplicitVarSizeWithDummy[q17] = x_ExplicitVarSizeWithFlags_Values[q15] | q17 : int(1..3)]) | q15 : int(1..3)]), + sum([toInt(x_Occurrence[q18]) | q18 : int(1..3)]) <= 3, and([x_Occurrence[q19] -> or([x_ExplicitVarSizeWithFlags_Flags[q21] /\ x_ExplicitVarSizeWithFlags_Values[q21] = q19 | q21 : int(1..3)]) | q19 : int(1..3)]), diff --git a/tests/exhaustive/basic/set04/expected/model_4_2_2-solution000001.solution b/tests/exhaustive/basic/set04/expected/model_4_2_2-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set04/expected/model_4_2_2-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set04/expected/model_4_2_2-solution000002.solution b/tests/exhaustive/basic/set04/expected/model_4_2_2-solution000002.solution new file mode 100644 index 0000000000..f90e0ba18c --- /dev/null +++ b/tests/exhaustive/basic/set04/expected/model_4_2_2-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_2_2.eprime.orig b/tests/exhaustive/basic/set04/expected/model_4_2_2.eprime similarity index 73% rename from tests/exhaustive/basic/cut_01_on/expected/model_4_2_2.eprime.orig rename to tests/exhaustive/basic/set04/expected/model_4_2_2.eprime index 8c3544f807..42d1680aae 100644 --- a/tests/exhaustive/basic/cut_01_on/expected/model_4_2_2.eprime.orig +++ b/tests/exhaustive/basic/set04/expected/model_4_2_2.eprime @@ -3,23 +3,20 @@ language ESSENCE' 1.0 find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..3)] of bool find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3)] of int(1..3) find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..3)] of int(1..4) -find cut1: bool -find cut2: bool -branching on - [cut1, cut2, x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] +branching on [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] such that - !cut1 <-> - or([x_ExplicitVarSizeWithFlags_Flags[q20] /\ x_ExplicitVarSizeWithFlags_Values[q20] = 1 | q20 : int(1..3)]) /\ - or([x_ExplicitVarSizeWithFlags_Flags[q22] /\ x_ExplicitVarSizeWithFlags_Values[q22] = 2 | q22 : int(1..3)]), - !cut2 <-> or([x_ExplicitVarSizeWithDummy[q24] != 4 /\ x_ExplicitVarSizeWithDummy[q24] = 1 | q24 : int(1..3)]), + or([x_ExplicitVarSizeWithFlags_Flags[q19] /\ x_ExplicitVarSizeWithFlags_Values[q19] = 1 | q19 : int(1..3)]), + or([x_ExplicitVarSizeWithDummy[q21] != 4 /\ x_ExplicitVarSizeWithDummy[q21] = 2 | q21 : int(1..3)]), and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] | q1 : int(1..2)]), and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..3)]), and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..2)]), + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..3)]) <= 3, and([x_ExplicitVarSizeWithDummy[q6] < x_ExplicitVarSizeWithDummy[q6 + 1] \/ x_ExplicitVarSizeWithDummy[q6] = 4 | q6 : int(1..2)]), and([x_ExplicitVarSizeWithDummy[q7] = 4 -> x_ExplicitVarSizeWithDummy[q7 + 1] = 4 | q7 : int(1..2)]), + sum([toInt(x_ExplicitVarSizeWithDummy[q8] != 4) | q8 : int(1..3)]) <= 3, and([x_ExplicitVarSizeWithDummy[q11] != 4 -> or([x_ExplicitVarSizeWithFlags_Flags[q13] /\ x_ExplicitVarSizeWithFlags_Values[q13] = x_ExplicitVarSizeWithDummy[q11] diff --git a/tests/exhaustive/basic/set04/expected/model_4_2_3-solution000001.solution b/tests/exhaustive/basic/set04/expected/model_4_2_3-solution000001.solution new file mode 100644 index 0000000000..f90e0ba18c --- /dev/null +++ b/tests/exhaustive/basic/set04/expected/model_4_2_3-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2} diff --git a/tests/exhaustive/basic/set04/expected/model_4_2_3-solution000002.solution b/tests/exhaustive/basic/set04/expected/model_4_2_3-solution000002.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set04/expected/model_4_2_3-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_2_3.eprime.orig b/tests/exhaustive/basic/set04/expected/model_4_2_3.eprime similarity index 83% rename from tests/exhaustive/basic/cut_01_on/expected/model_4_2_3.eprime.orig rename to tests/exhaustive/basic/set04/expected/model_4_2_3.eprime index eb547110ba..01219074fb 100644 --- a/tests/exhaustive/basic/cut_01_on/expected/model_4_2_3.eprime.orig +++ b/tests/exhaustive/basic/set04/expected/model_4_2_3.eprime @@ -5,24 +5,22 @@ find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3)] of int(1.. find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..3)] of int(1..4) find x_ExplicitVarSizeWithMarker_Marker: int(0..3) find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3)] of int(1..3) -find cut1: bool -find cut2: bool branching on - [cut1, cut2, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, - x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy] + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithFlags_Flags, + x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy] such that - !cut1 <-> - or([x_ExplicitVarSizeWithFlags_Flags[q39] /\ x_ExplicitVarSizeWithFlags_Values[q39] = 1 | q39 : int(1..3)]) /\ - or([x_ExplicitVarSizeWithFlags_Flags[q41] /\ x_ExplicitVarSizeWithFlags_Values[q41] = 2 | q41 : int(1..3)]), - !cut2 <-> or([x_ExplicitVarSizeWithDummy[q43] != 4 /\ x_ExplicitVarSizeWithDummy[q43] = 1 | q43 : int(1..3)]), + or([x_ExplicitVarSizeWithFlags_Flags[q38] /\ x_ExplicitVarSizeWithFlags_Values[q38] = 1 | q38 : int(1..3)]), + or([x_ExplicitVarSizeWithDummy[q40] != 4 /\ x_ExplicitVarSizeWithDummy[q40] = 2 | q40 : int(1..3)]), and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] | q1 : int(1..2)]), and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..3)]), and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..2)]), + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..3)]) <= 3, and([x_ExplicitVarSizeWithDummy[q6] < x_ExplicitVarSizeWithDummy[q6 + 1] \/ x_ExplicitVarSizeWithDummy[q6] = 4 | q6 : int(1..2)]), and([x_ExplicitVarSizeWithDummy[q7] = 4 -> x_ExplicitVarSizeWithDummy[q7 + 1] = 4 | q7 : int(1..2)]), + sum([toInt(x_ExplicitVarSizeWithDummy[q8] != 4) | q8 : int(1..3)]) <= 3, and([x_ExplicitVarSizeWithDummy[q11] != 4 -> or([x_ExplicitVarSizeWithFlags_Flags[q13] /\ x_ExplicitVarSizeWithFlags_Values[q13] = x_ExplicitVarSizeWithDummy[q11] @@ -37,6 +35,7 @@ such that x_ExplicitVarSizeWithMarker_Values[q18] < x_ExplicitVarSizeWithMarker_Values[q18 + 1] | q18 : int(1..2)]), and([q19 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q19] = 1 | q19 : int(1..3)]), + x_ExplicitVarSizeWithMarker_Marker <= 3, and([q22 <= x_ExplicitVarSizeWithMarker_Marker -> or([x_ExplicitVarSizeWithFlags_Flags[q24] /\ x_ExplicitVarSizeWithFlags_Values[q24] = x_ExplicitVarSizeWithMarker_Values[q22] diff --git a/tests/exhaustive/basic/set04/expected/model_4_3_1-solution000001.solution b/tests/exhaustive/basic/set04/expected/model_4_3_1-solution000001.solution new file mode 100644 index 0000000000..f90e0ba18c --- /dev/null +++ b/tests/exhaustive/basic/set04/expected/model_4_3_1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2} diff --git a/tests/exhaustive/basic/set04/expected/model_4_3_1-solution000002.solution b/tests/exhaustive/basic/set04/expected/model_4_3_1-solution000002.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set04/expected/model_4_3_1-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_3_1.eprime.orig b/tests/exhaustive/basic/set04/expected/model_4_3_1.eprime similarity index 82% rename from tests/exhaustive/basic/cut_01_on/expected/model_4_3_1.eprime.orig rename to tests/exhaustive/basic/set04/expected/model_4_3_1.eprime index b8aa2bdc4b..87587667fc 100644 --- a/tests/exhaustive/basic/cut_01_on/expected/model_4_3_1.eprime.orig +++ b/tests/exhaustive/basic/set04/expected/model_4_3_1.eprime @@ -5,26 +5,23 @@ find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3)] of int(1.. find x_ExplicitVarSizeWithMarker_Marker: int(0..3) find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3)] of int(1..3) find x_Occurrence: matrix indexed by [int(1..3)] of bool -find cut1: bool -find cut2: bool branching on - [cut1, cut2, x_Occurrence, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, + [x_Occurrence, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] such that - !cut1 <-> - or([x_ExplicitVarSizeWithFlags_Flags[q30] /\ x_ExplicitVarSizeWithFlags_Values[q30] = 1 | q30 : int(1..3)]) /\ - or([x_ExplicitVarSizeWithFlags_Flags[q32] /\ x_ExplicitVarSizeWithFlags_Values[q32] = 2 | q32 : int(1..3)]), - !cut2 <-> - or([q34 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q34] = 1 | q34 : int(1..3)]), + or([x_ExplicitVarSizeWithFlags_Flags[q29] /\ x_ExplicitVarSizeWithFlags_Values[q29] = 1 | q29 : int(1..3)]), + or([q31 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q31] = 2 | q31 : int(1..3)]), and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] | q1 : int(1..2)]), and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..3)]), and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..2)]), + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..3)]) <= 3, and([q6 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q6] < x_ExplicitVarSizeWithMarker_Values[q6 + 1] | q6 : int(1..2)]), and([q7 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q7] = 1 | q7 : int(1..3)]), + x_ExplicitVarSizeWithMarker_Marker <= 3, and([q10 <= x_ExplicitVarSizeWithMarker_Marker -> or([x_ExplicitVarSizeWithFlags_Flags[q12] /\ x_ExplicitVarSizeWithFlags_Values[q12] = x_ExplicitVarSizeWithMarker_Values[q10] @@ -35,6 +32,7 @@ such that x_ExplicitVarSizeWithMarker_Values[q16] = x_ExplicitVarSizeWithFlags_Values[q14] | q16 : int(1..3)]) | q14 : int(1..3)]), + sum([toInt(x_Occurrence[q17]) | q17 : int(1..3)]) <= 3, and([x_Occurrence[q18] -> or([x_ExplicitVarSizeWithFlags_Flags[q20] /\ x_ExplicitVarSizeWithFlags_Values[q20] = q18 | q20 : int(1..3)]) | q18 : int(1..3)]), diff --git a/tests/exhaustive/basic/set04/expected/model_4_3_2-solution000001.solution b/tests/exhaustive/basic/set04/expected/model_4_3_2-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set04/expected/model_4_3_2-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set04/expected/model_4_3_2-solution000002.solution b/tests/exhaustive/basic/set04/expected/model_4_3_2-solution000002.solution new file mode 100644 index 0000000000..f90e0ba18c --- /dev/null +++ b/tests/exhaustive/basic/set04/expected/model_4_3_2-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_3_2.eprime.orig b/tests/exhaustive/basic/set04/expected/model_4_3_2.eprime similarity index 85% rename from tests/exhaustive/basic/cut_01_on/expected/model_4_3_2.eprime.orig rename to tests/exhaustive/basic/set04/expected/model_4_3_2.eprime index 511d1b6814..8a1052d0da 100644 --- a/tests/exhaustive/basic/cut_01_on/expected/model_4_3_2.eprime.orig +++ b/tests/exhaustive/basic/set04/expected/model_4_3_2.eprime @@ -5,26 +5,23 @@ find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3)] of int(1.. find x_ExplicitVarSizeWithMarker_Marker: int(0..3) find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3)] of int(1..3) find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..3)] of int(1..4) -find cut1: bool -find cut2: bool branching on - [cut1, cut2, x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, + [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] such that - !cut1 <-> - or([x_ExplicitVarSizeWithFlags_Flags[q39] /\ x_ExplicitVarSizeWithFlags_Values[q39] = 1 | q39 : int(1..3)]) /\ - or([x_ExplicitVarSizeWithFlags_Flags[q41] /\ x_ExplicitVarSizeWithFlags_Values[q41] = 2 | q41 : int(1..3)]), - !cut2 <-> - or([q43 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q43] = 1 | q43 : int(1..3)]), + or([x_ExplicitVarSizeWithFlags_Flags[q38] /\ x_ExplicitVarSizeWithFlags_Values[q38] = 1 | q38 : int(1..3)]), + or([q40 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q40] = 2 | q40 : int(1..3)]), and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] | q1 : int(1..2)]), and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..3)]), and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..2)]), + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..3)]) <= 3, and([q6 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q6] < x_ExplicitVarSizeWithMarker_Values[q6 + 1] | q6 : int(1..2)]), and([q7 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q7] = 1 | q7 : int(1..3)]), + x_ExplicitVarSizeWithMarker_Marker <= 3, and([q10 <= x_ExplicitVarSizeWithMarker_Marker -> or([x_ExplicitVarSizeWithFlags_Flags[q12] /\ x_ExplicitVarSizeWithFlags_Values[q12] = x_ExplicitVarSizeWithMarker_Values[q10] @@ -38,6 +35,7 @@ such that and([x_ExplicitVarSizeWithDummy[q17] < x_ExplicitVarSizeWithDummy[q17 + 1] \/ x_ExplicitVarSizeWithDummy[q17] = 4 | q17 : int(1..2)]), and([x_ExplicitVarSizeWithDummy[q18] = 4 -> x_ExplicitVarSizeWithDummy[q18 + 1] = 4 | q18 : int(1..2)]), + sum([toInt(x_ExplicitVarSizeWithDummy[q19] != 4) | q19 : int(1..3)]) <= 3, and([x_ExplicitVarSizeWithDummy[q22] != 4 -> or([x_ExplicitVarSizeWithFlags_Flags[q24] /\ x_ExplicitVarSizeWithFlags_Values[q24] = x_ExplicitVarSizeWithDummy[q22] diff --git a/tests/exhaustive/basic/set04/expected/model_4_3_3-solution000001.solution b/tests/exhaustive/basic/set04/expected/model_4_3_3-solution000001.solution new file mode 100644 index 0000000000..f90e0ba18c --- /dev/null +++ b/tests/exhaustive/basic/set04/expected/model_4_3_3-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2} diff --git a/tests/exhaustive/basic/set04/expected/model_4_3_3-solution000002.solution b/tests/exhaustive/basic/set04/expected/model_4_3_3-solution000002.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set04/expected/model_4_3_3-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_4_3.eprime.orig b/tests/exhaustive/basic/set04/expected/model_4_3_3.eprime similarity index 73% rename from tests/exhaustive/basic/cut_01_on/expected/model_4_4_3.eprime.orig rename to tests/exhaustive/basic/set04/expected/model_4_3_3.eprime index 9f0674828c..50c9eadc30 100644 --- a/tests/exhaustive/basic/cut_01_on/expected/model_4_4_3.eprime.orig +++ b/tests/exhaustive/basic/set04/expected/model_4_3_3.eprime @@ -4,26 +4,23 @@ find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..3)] of bool find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3)] of int(1..3) find x_ExplicitVarSizeWithMarker_Marker: int(0..3) find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3)] of int(1..3) -find cut1: bool -find cut2: bool branching on - [cut1, cut2, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, - x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithFlags_Flags, + x_ExplicitVarSizeWithFlags_Values] such that - !cut1 <-> - or([x_ExplicitVarSizeWithFlags_Flags[q19] /\ x_ExplicitVarSizeWithFlags_Values[q19] = 1 | q19 : int(1..3)]) /\ - or([x_ExplicitVarSizeWithFlags_Flags[q21] /\ x_ExplicitVarSizeWithFlags_Values[q21] = 2 | q21 : int(1..3)]), - !cut2 <-> - or([x_ExplicitVarSizeWithFlags_Flags[q23] /\ x_ExplicitVarSizeWithFlags_Values[q23] = 1 | q23 : int(1..3)]), + or([x_ExplicitVarSizeWithFlags_Flags[q18] /\ x_ExplicitVarSizeWithFlags_Values[q18] = 1 | q18 : int(1..3)]), + or([q20 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q20] = 2 | q20 : int(1..3)]), and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] | q1 : int(1..2)]), and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..3)]), and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..2)]), + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..3)]) <= 3, and([q6 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q6] < x_ExplicitVarSizeWithMarker_Values[q6 + 1] | q6 : int(1..2)]), and([q7 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q7] = 1 | q7 : int(1..3)]), + x_ExplicitVarSizeWithMarker_Marker <= 3, and([q10 <= x_ExplicitVarSizeWithMarker_Marker -> or([x_ExplicitVarSizeWithFlags_Flags[q12] /\ x_ExplicitVarSizeWithFlags_Values[q12] = x_ExplicitVarSizeWithMarker_Values[q10] diff --git a/tests/exhaustive/basic/set04/expected/model_4_4_1-solution000001.solution b/tests/exhaustive/basic/set04/expected/model_4_4_1-solution000001.solution new file mode 100644 index 0000000000..f90e0ba18c --- /dev/null +++ b/tests/exhaustive/basic/set04/expected/model_4_4_1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2} diff --git a/tests/exhaustive/basic/set04/expected/model_4_4_1-solution000002.solution b/tests/exhaustive/basic/set04/expected/model_4_4_1-solution000002.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set04/expected/model_4_4_1-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_1_1.eprime.orig b/tests/exhaustive/basic/set04/expected/model_4_4_1.eprime similarity index 67% rename from tests/exhaustive/basic/cut_01_on/expected/model_4_1_1.eprime.orig rename to tests/exhaustive/basic/set04/expected/model_4_4_1.eprime index 5d7a188800..1679fe4372 100644 --- a/tests/exhaustive/basic/cut_01_on/expected/model_4_1_1.eprime.orig +++ b/tests/exhaustive/basic/set04/expected/model_4_4_1.eprime @@ -3,19 +3,17 @@ language ESSENCE' 1.0 find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..3)] of bool find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3)] of int(1..3) find x_Occurrence: matrix indexed by [int(1..3)] of bool -find cut1: bool -find cut2: bool -branching on [cut1, cut2, x_Occurrence, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] +branching on [x_Occurrence, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] such that - !cut1 <-> - or([x_ExplicitVarSizeWithFlags_Flags[q14] /\ x_ExplicitVarSizeWithFlags_Values[q14] = 1 | q14 : int(1..3)]) /\ - or([x_ExplicitVarSizeWithFlags_Flags[q16] /\ x_ExplicitVarSizeWithFlags_Values[q16] = 2 | q16 : int(1..3)]), - !cut2 <-> x_Occurrence[1], + or([x_ExplicitVarSizeWithFlags_Flags[q13] /\ x_ExplicitVarSizeWithFlags_Values[q13] = 1 | q13 : int(1..3)]), + or([x_ExplicitVarSizeWithFlags_Flags[q15] /\ x_ExplicitVarSizeWithFlags_Values[q15] = 2 | q15 : int(1..3)]), and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] | q1 : int(1..2)]), and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..3)]), and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..2)]), + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..3)]) <= 3, + sum([toInt(x_Occurrence[q6]) | q6 : int(1..3)]) <= 3, and([x_Occurrence[q7] -> or([x_ExplicitVarSizeWithFlags_Flags[q9] /\ x_ExplicitVarSizeWithFlags_Values[q9] = q7 | q9 : int(1..3)]) | q7 : int(1..3)]), diff --git a/tests/exhaustive/basic/set04/expected/model_4_4_2-solution000001.solution b/tests/exhaustive/basic/set04/expected/model_4_4_2-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set04/expected/model_4_4_2-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set04/expected/model_4_4_2-solution000002.solution b/tests/exhaustive/basic/set04/expected/model_4_4_2-solution000002.solution new file mode 100644 index 0000000000..f90e0ba18c --- /dev/null +++ b/tests/exhaustive/basic/set04/expected/model_4_4_2-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_2_4.eprime.orig b/tests/exhaustive/basic/set04/expected/model_4_4_2.eprime similarity index 73% rename from tests/exhaustive/basic/cut_01_on/expected/model_4_2_4.eprime.orig rename to tests/exhaustive/basic/set04/expected/model_4_4_2.eprime index 8c3544f807..41d16504a6 100644 --- a/tests/exhaustive/basic/cut_01_on/expected/model_4_2_4.eprime.orig +++ b/tests/exhaustive/basic/set04/expected/model_4_4_2.eprime @@ -3,23 +3,20 @@ language ESSENCE' 1.0 find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..3)] of bool find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3)] of int(1..3) find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..3)] of int(1..4) -find cut1: bool -find cut2: bool -branching on - [cut1, cut2, x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] +branching on [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] such that - !cut1 <-> - or([x_ExplicitVarSizeWithFlags_Flags[q20] /\ x_ExplicitVarSizeWithFlags_Values[q20] = 1 | q20 : int(1..3)]) /\ - or([x_ExplicitVarSizeWithFlags_Flags[q22] /\ x_ExplicitVarSizeWithFlags_Values[q22] = 2 | q22 : int(1..3)]), - !cut2 <-> or([x_ExplicitVarSizeWithDummy[q24] != 4 /\ x_ExplicitVarSizeWithDummy[q24] = 1 | q24 : int(1..3)]), + or([x_ExplicitVarSizeWithFlags_Flags[q19] /\ x_ExplicitVarSizeWithFlags_Values[q19] = 1 | q19 : int(1..3)]), + or([x_ExplicitVarSizeWithFlags_Flags[q21] /\ x_ExplicitVarSizeWithFlags_Values[q21] = 2 | q21 : int(1..3)]), and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] | q1 : int(1..2)]), and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..3)]), and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..2)]), + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..3)]) <= 3, and([x_ExplicitVarSizeWithDummy[q6] < x_ExplicitVarSizeWithDummy[q6 + 1] \/ x_ExplicitVarSizeWithDummy[q6] = 4 | q6 : int(1..2)]), and([x_ExplicitVarSizeWithDummy[q7] = 4 -> x_ExplicitVarSizeWithDummy[q7 + 1] = 4 | q7 : int(1..2)]), + sum([toInt(x_ExplicitVarSizeWithDummy[q8] != 4) | q8 : int(1..3)]) <= 3, and([x_ExplicitVarSizeWithDummy[q11] != 4 -> or([x_ExplicitVarSizeWithFlags_Flags[q13] /\ x_ExplicitVarSizeWithFlags_Values[q13] = x_ExplicitVarSizeWithDummy[q11] diff --git a/tests/exhaustive/basic/set04/expected/model_4_4_3-solution000001.solution b/tests/exhaustive/basic/set04/expected/model_4_4_3-solution000001.solution new file mode 100644 index 0000000000..f90e0ba18c --- /dev/null +++ b/tests/exhaustive/basic/set04/expected/model_4_4_3-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2} diff --git a/tests/exhaustive/basic/set04/expected/model_4_4_3-solution000002.solution b/tests/exhaustive/basic/set04/expected/model_4_4_3-solution000002.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set04/expected/model_4_4_3-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_3_3.eprime.orig b/tests/exhaustive/basic/set04/expected/model_4_4_3.eprime similarity index 73% rename from tests/exhaustive/basic/cut_01_on/expected/model_4_3_3.eprime.orig rename to tests/exhaustive/basic/set04/expected/model_4_4_3.eprime index 3f66e92dd5..6c0162b987 100644 --- a/tests/exhaustive/basic/cut_01_on/expected/model_4_3_3.eprime.orig +++ b/tests/exhaustive/basic/set04/expected/model_4_4_3.eprime @@ -4,26 +4,23 @@ find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..3)] of bool find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3)] of int(1..3) find x_ExplicitVarSizeWithMarker_Marker: int(0..3) find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3)] of int(1..3) -find cut1: bool -find cut2: bool branching on - [cut1, cut2, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, - x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithFlags_Flags, + x_ExplicitVarSizeWithFlags_Values] such that - !cut1 <-> - or([x_ExplicitVarSizeWithFlags_Flags[q19] /\ x_ExplicitVarSizeWithFlags_Values[q19] = 1 | q19 : int(1..3)]) /\ - or([x_ExplicitVarSizeWithFlags_Flags[q21] /\ x_ExplicitVarSizeWithFlags_Values[q21] = 2 | q21 : int(1..3)]), - !cut2 <-> - or([q23 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q23] = 1 | q23 : int(1..3)]), + or([x_ExplicitVarSizeWithFlags_Flags[q18] /\ x_ExplicitVarSizeWithFlags_Values[q18] = 1 | q18 : int(1..3)]), + or([x_ExplicitVarSizeWithFlags_Flags[q20] /\ x_ExplicitVarSizeWithFlags_Values[q20] = 2 | q20 : int(1..3)]), and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] | q1 : int(1..2)]), and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..3)]), and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..2)]), + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..3)]) <= 3, and([q6 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q6] < x_ExplicitVarSizeWithMarker_Values[q6 + 1] | q6 : int(1..2)]), and([q7 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q7] = 1 | q7 : int(1..3)]), + x_ExplicitVarSizeWithMarker_Marker <= 3, and([q10 <= x_ExplicitVarSizeWithMarker_Marker -> or([x_ExplicitVarSizeWithFlags_Flags[q12] /\ x_ExplicitVarSizeWithFlags_Values[q12] = x_ExplicitVarSizeWithMarker_Values[q10] diff --git a/tests/exhaustive/basic/set04/expected/model_4_4_4-solution000001.solution b/tests/exhaustive/basic/set04/expected/model_4_4_4-solution000001.solution new file mode 100644 index 0000000000..f90e0ba18c --- /dev/null +++ b/tests/exhaustive/basic/set04/expected/model_4_4_4-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2} diff --git a/tests/exhaustive/basic/set04/expected/model_4_4_4-solution000002.solution b/tests/exhaustive/basic/set04/expected/model_4_4_4-solution000002.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set04/expected/model_4_4_4-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_4_4.eprime.orig b/tests/exhaustive/basic/set04/expected/model_4_4_4.eprime similarity index 50% rename from tests/exhaustive/basic/cut_01_on/expected/model_4_4_4.eprime.orig rename to tests/exhaustive/basic/set04/expected/model_4_4_4.eprime index 17be20c392..a91619f489 100644 --- a/tests/exhaustive/basic/cut_01_on/expected/model_4_4_4.eprime.orig +++ b/tests/exhaustive/basic/set04/expected/model_4_4_4.eprime @@ -2,18 +2,14 @@ language ESSENCE' 1.0 find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..3)] of bool find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3)] of int(1..3) -find cut1: bool -find cut2: bool -branching on [cut1, cut2, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] +branching on [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] such that - !cut1 <-> - or([x_ExplicitVarSizeWithFlags_Flags[q8] /\ x_ExplicitVarSizeWithFlags_Values[q8] = 1 | q8 : int(1..3)]) /\ - or([x_ExplicitVarSizeWithFlags_Flags[q10] /\ x_ExplicitVarSizeWithFlags_Values[q10] = 2 | q10 : int(1..3)]), - !cut2 <-> - or([x_ExplicitVarSizeWithFlags_Flags[q12] /\ x_ExplicitVarSizeWithFlags_Values[q12] = 1 | q12 : int(1..3)]), + or([x_ExplicitVarSizeWithFlags_Flags[q7] /\ x_ExplicitVarSizeWithFlags_Values[q7] = 1 | q7 : int(1..3)]), + or([x_ExplicitVarSizeWithFlags_Flags[q9] /\ x_ExplicitVarSizeWithFlags_Values[q9] = 2 | q9 : int(1..3)]), and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] | q1 : int(1..2)]), and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..3)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..2)]) + and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..2)]), + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..3)]) <= 3 diff --git a/tests/exhaustive/basic/set05/expected/model_1_1_1-solution000001.solution b/tests/exhaustive/basic/set05/expected/model_1_1_1-solution000001.solution new file mode 100644 index 0000000000..f90e0ba18c --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_1_1_1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2} diff --git a/tests/exhaustive/basic/set05/expected/model_1_1_1-solution000002.solution b/tests/exhaustive/basic/set05/expected/model_1_1_1-solution000002.solution new file mode 100644 index 0000000000..fdc0f02f96 --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_1_1_1-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 4} diff --git a/tests/exhaustive/basic/set05/expected/model_1_1_1-solution000003.solution b/tests/exhaustive/basic/set05/expected/model_1_1_1-solution000003.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_1_1_1-solution000003.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set05/expected/model_1_1_1.eprime b/tests/exhaustive/basic/set05/expected/model_1_1_1.eprime new file mode 100644 index 0000000000..3c56114ac2 --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_1_1_1.eprime @@ -0,0 +1,9 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(1..4)] of bool +branching on [x_Occurrence] +such that + x_Occurrence[1], + x_Occurrence[2], + sum([toInt(x_Occurrence[q1]) | q1 : int(1..4)]) <= 3 + diff --git a/tests/exhaustive/basic/set05/expected/model_1_1_2-solution000001.solution b/tests/exhaustive/basic/set05/expected/model_1_1_2-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_1_1_2-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set05/expected/model_1_1_2-solution000002.solution b/tests/exhaustive/basic/set05/expected/model_1_1_2-solution000002.solution new file mode 100644 index 0000000000..fdc0f02f96 --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_1_1_2-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 4} diff --git a/tests/exhaustive/basic/set05/expected/model_1_1_2-solution000003.solution b/tests/exhaustive/basic/set05/expected/model_1_1_2-solution000003.solution new file mode 100644 index 0000000000..f90e0ba18c --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_1_1_2-solution000003.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2} diff --git a/tests/exhaustive/basic/set05/expected/model_1_1_2.eprime b/tests/exhaustive/basic/set05/expected/model_1_1_2.eprime new file mode 100644 index 0000000000..17c15fcd6b --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_1_1_2.eprime @@ -0,0 +1,18 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..3)] of int(1..5) +branching on [x_ExplicitVarSizeWithDummy, x_Occurrence] +such that + x_Occurrence[1], + x_Occurrence[2], + sum([toInt(x_Occurrence[q1]) | q1 : int(1..4)]) <= 3, + and([x_ExplicitVarSizeWithDummy[q2] < x_ExplicitVarSizeWithDummy[q2 + 1] \/ x_ExplicitVarSizeWithDummy[q2] = 5 + | q2 : int(1..2)]), + and([x_ExplicitVarSizeWithDummy[q3] = 5 -> x_ExplicitVarSizeWithDummy[q3 + 1] = 5 | q3 : int(1..2)]), + sum([toInt(x_ExplicitVarSizeWithDummy[q4] != 5) | q4 : int(1..3)]) <= 3, + and([x_ExplicitVarSizeWithDummy[q7] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q7]] | q7 : int(1..3)]), + and([x_Occurrence[q8] -> + or([x_ExplicitVarSizeWithDummy[q10] != 5 /\ x_ExplicitVarSizeWithDummy[q10] = q8 | q10 : int(1..3)]) + | q8 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set05/expected/model_1_1_3-solution000001.solution b/tests/exhaustive/basic/set05/expected/model_1_1_3-solution000001.solution new file mode 100644 index 0000000000..f90e0ba18c --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_1_1_3-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2} diff --git a/tests/exhaustive/basic/set05/expected/model_1_1_3-solution000002.solution b/tests/exhaustive/basic/set05/expected/model_1_1_3-solution000002.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_1_1_3-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set05/expected/model_1_1_3-solution000003.solution b/tests/exhaustive/basic/set05/expected/model_1_1_3-solution000003.solution new file mode 100644 index 0000000000..fdc0f02f96 --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_1_1_3-solution000003.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 4} diff --git a/tests/exhaustive/basic/set05/expected/model_1_1_3.eprime b/tests/exhaustive/basic/set05/expected/model_1_1_3.eprime new file mode 100644 index 0000000000..70361154b0 --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_1_1_3.eprime @@ -0,0 +1,21 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithMarker_Marker: int(0..3) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3)] of int(1..4) +branching on [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_Occurrence] +such that + x_Occurrence[1], + x_Occurrence[2], + sum([toInt(x_Occurrence[q1]) | q1 : int(1..4)]) <= 3, + and([q2 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q2] < x_ExplicitVarSizeWithMarker_Values[q2 + 1] + | q2 : int(1..2)]), + and([q3 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q3] = 1 | q3 : int(1..3)]), + x_ExplicitVarSizeWithMarker_Marker <= 3, + and([q6 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q6]] + | q6 : int(1..3)]), + and([x_Occurrence[q7] -> + or([q9 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q9] = q7 | q9 : int(1..3)]) + | q7 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set05/expected/model_1_1_4-solution000001.solution b/tests/exhaustive/basic/set05/expected/model_1_1_4-solution000001.solution new file mode 100644 index 0000000000..f90e0ba18c --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_1_1_4-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2} diff --git a/tests/exhaustive/basic/set05/expected/model_1_1_4-solution000002.solution b/tests/exhaustive/basic/set05/expected/model_1_1_4-solution000002.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_1_1_4-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set05/expected/model_1_1_4-solution000003.solution b/tests/exhaustive/basic/set05/expected/model_1_1_4-solution000003.solution new file mode 100644 index 0000000000..fdc0f02f96 --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_1_1_4-solution000003.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 4} diff --git a/tests/exhaustive/basic/set05/expected/model_1_1_4.eprime b/tests/exhaustive/basic/set05/expected/model_1_1_4.eprime new file mode 100644 index 0000000000..42983848f0 --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_1_1_4.eprime @@ -0,0 +1,21 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..3)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3)] of int(1..4) +branching on [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_Occurrence] +such that + x_Occurrence[1], + x_Occurrence[2], + sum([toInt(x_Occurrence[q1]) | q1 : int(1..4)]) <= 3, + and([x_ExplicitVarSizeWithFlags_Flags[q2 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q2] < x_ExplicitVarSizeWithFlags_Values[q2 + 1] + | q2 : int(1..2)]), + and([x_ExplicitVarSizeWithFlags_Flags[q3] = false -> x_ExplicitVarSizeWithFlags_Values[q3] = 1 | q3 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q4] | q4 : int(1..2)]), + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q5]) | q5 : int(1..3)]) <= 3, + and([x_ExplicitVarSizeWithFlags_Flags[q8] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q8]] | q8 : int(1..3)]), + and([x_Occurrence[q9] -> + or([x_ExplicitVarSizeWithFlags_Flags[q11] /\ x_ExplicitVarSizeWithFlags_Values[q11] = q9 | q11 : int(1..3)]) + | q9 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set05/expected/model_1_2_1-solution000001.solution b/tests/exhaustive/basic/set05/expected/model_1_2_1-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_1_2_1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set05/expected/model_1_2_1-solution000002.solution b/tests/exhaustive/basic/set05/expected/model_1_2_1-solution000002.solution new file mode 100644 index 0000000000..fdc0f02f96 --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_1_2_1-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 4} diff --git a/tests/exhaustive/basic/set05/expected/model_1_2_1-solution000003.solution b/tests/exhaustive/basic/set05/expected/model_1_2_1-solution000003.solution new file mode 100644 index 0000000000..f90e0ba18c --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_1_2_1-solution000003.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2} diff --git a/tests/exhaustive/basic/set05/expected/model_1_2_1.eprime b/tests/exhaustive/basic/set05/expected/model_1_2_1.eprime new file mode 100644 index 0000000000..c5886a217c --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_1_2_1.eprime @@ -0,0 +1,18 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..3)] of int(1..5) +branching on [x_ExplicitVarSizeWithDummy, x_Occurrence] +such that + x_Occurrence[1], + or([x_ExplicitVarSizeWithDummy[q12] != 5 /\ x_ExplicitVarSizeWithDummy[q12] = 2 | q12 : int(1..3)]), + sum([toInt(x_Occurrence[q1]) | q1 : int(1..4)]) <= 3, + and([x_ExplicitVarSizeWithDummy[q2] < x_ExplicitVarSizeWithDummy[q2 + 1] \/ x_ExplicitVarSizeWithDummy[q2] = 5 + | q2 : int(1..2)]), + and([x_ExplicitVarSizeWithDummy[q3] = 5 -> x_ExplicitVarSizeWithDummy[q3 + 1] = 5 | q3 : int(1..2)]), + sum([toInt(x_ExplicitVarSizeWithDummy[q4] != 5) | q4 : int(1..3)]) <= 3, + and([x_ExplicitVarSizeWithDummy[q7] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q7]] | q7 : int(1..3)]), + and([x_Occurrence[q8] -> + or([x_ExplicitVarSizeWithDummy[q10] != 5 /\ x_ExplicitVarSizeWithDummy[q10] = q8 | q10 : int(1..3)]) + | q8 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set05/expected/model_1_2_3-solution000001.solution b/tests/exhaustive/basic/set05/expected/model_1_2_3-solution000001.solution new file mode 100644 index 0000000000..f90e0ba18c --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_1_2_3-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2} diff --git a/tests/exhaustive/basic/set05/expected/model_1_2_3-solution000002.solution b/tests/exhaustive/basic/set05/expected/model_1_2_3-solution000002.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_1_2_3-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set05/expected/model_1_2_3-solution000003.solution b/tests/exhaustive/basic/set05/expected/model_1_2_3-solution000003.solution new file mode 100644 index 0000000000..fdc0f02f96 --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_1_2_3-solution000003.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 4} diff --git a/tests/exhaustive/basic/set05/expected/model_1_2_3.eprime b/tests/exhaustive/basic/set05/expected/model_1_2_3.eprime new file mode 100644 index 0000000000..2ef8fa28a9 --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_1_2_3.eprime @@ -0,0 +1,42 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..3)] of int(1..5) +find x_ExplicitVarSizeWithMarker_Marker: int(0..3) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3)] of int(1..4) +branching on + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_Occurrence, x_ExplicitVarSizeWithDummy] +such that + x_Occurrence[1], + or([x_ExplicitVarSizeWithDummy[q28] != 5 /\ x_ExplicitVarSizeWithDummy[q28] = 2 | q28 : int(1..3)]), + sum([toInt(x_Occurrence[q1]) | q1 : int(1..4)]) <= 3, + and([x_ExplicitVarSizeWithDummy[q2] < x_ExplicitVarSizeWithDummy[q2 + 1] \/ x_ExplicitVarSizeWithDummy[q2] = 5 + | q2 : int(1..2)]), + and([x_ExplicitVarSizeWithDummy[q3] = 5 -> x_ExplicitVarSizeWithDummy[q3 + 1] = 5 | q3 : int(1..2)]), + sum([toInt(x_ExplicitVarSizeWithDummy[q4] != 5) | q4 : int(1..3)]) <= 3, + and([x_ExplicitVarSizeWithDummy[q7] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q7]] | q7 : int(1..3)]), + and([x_Occurrence[q8] -> + or([x_ExplicitVarSizeWithDummy[q10] != 5 /\ x_ExplicitVarSizeWithDummy[q10] = q8 | q10 : int(1..3)]) + | q8 : int(1..4)]), + and([q11 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q11] < x_ExplicitVarSizeWithMarker_Values[q11 + 1] + | q11 : int(1..2)]), + and([q12 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q12] = 1 | q12 : int(1..3)]), + x_ExplicitVarSizeWithMarker_Marker <= 3, + and([q15 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q15]] + | q15 : int(1..3)]), + and([x_Occurrence[q16] -> + or([q18 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q18] = q16 + | q18 : int(1..3)]) + | q16 : int(1..4)]), + and([q20 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithDummy[q22] != 5 /\ + x_ExplicitVarSizeWithDummy[q22] = x_ExplicitVarSizeWithMarker_Values[q20] + | q22 : int(1..3)]) + | q20 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q24] != 5 -> + or([q26 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q26] = x_ExplicitVarSizeWithDummy[q24] + | q26 : int(1..3)]) + | q24 : int(1..3)]) + diff --git a/tests/exhaustive/basic/set05/expected/model_1_2_4-solution000001.solution b/tests/exhaustive/basic/set05/expected/model_1_2_4-solution000001.solution new file mode 100644 index 0000000000..f90e0ba18c --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_1_2_4-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2} diff --git a/tests/exhaustive/basic/set05/expected/model_1_2_4-solution000002.solution b/tests/exhaustive/basic/set05/expected/model_1_2_4-solution000002.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_1_2_4-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set05/expected/model_1_2_4-solution000003.solution b/tests/exhaustive/basic/set05/expected/model_1_2_4-solution000003.solution new file mode 100644 index 0000000000..fdc0f02f96 --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_1_2_4-solution000003.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 4} diff --git a/tests/exhaustive/basic/set05/expected/model_1_2_4.eprime b/tests/exhaustive/basic/set05/expected/model_1_2_4.eprime new file mode 100644 index 0000000000..6970c8923c --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_1_2_4.eprime @@ -0,0 +1,43 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..3)] of int(1..5) +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..3)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3)] of int(1..4) +branching on + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_Occurrence, x_ExplicitVarSizeWithDummy] +such that + x_Occurrence[1], + or([x_ExplicitVarSizeWithDummy[q30] != 5 /\ x_ExplicitVarSizeWithDummy[q30] = 2 | q30 : int(1..3)]), + sum([toInt(x_Occurrence[q1]) | q1 : int(1..4)]) <= 3, + and([x_ExplicitVarSizeWithDummy[q2] < x_ExplicitVarSizeWithDummy[q2 + 1] \/ x_ExplicitVarSizeWithDummy[q2] = 5 + | q2 : int(1..2)]), + and([x_ExplicitVarSizeWithDummy[q3] = 5 -> x_ExplicitVarSizeWithDummy[q3 + 1] = 5 | q3 : int(1..2)]), + sum([toInt(x_ExplicitVarSizeWithDummy[q4] != 5) | q4 : int(1..3)]) <= 3, + and([x_ExplicitVarSizeWithDummy[q7] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q7]] | q7 : int(1..3)]), + and([x_Occurrence[q8] -> + or([x_ExplicitVarSizeWithDummy[q10] != 5 /\ x_ExplicitVarSizeWithDummy[q10] = q8 | q10 : int(1..3)]) + | q8 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q11 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q11] < x_ExplicitVarSizeWithFlags_Values[q11 + 1] + | q11 : int(1..2)]), + and([x_ExplicitVarSizeWithFlags_Flags[q12] = false -> x_ExplicitVarSizeWithFlags_Values[q12] = 1 + | q12 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q13 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q13] | q13 : int(1..2)]), + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q14]) | q14 : int(1..3)]) <= 3, + and([x_ExplicitVarSizeWithFlags_Flags[q17] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q17]] + | q17 : int(1..3)]), + and([x_Occurrence[q18] -> + or([x_ExplicitVarSizeWithFlags_Flags[q20] /\ x_ExplicitVarSizeWithFlags_Values[q20] = q18 | q20 : int(1..3)]) + | q18 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q22] -> + or([x_ExplicitVarSizeWithDummy[q24] != 5 /\ + x_ExplicitVarSizeWithDummy[q24] = x_ExplicitVarSizeWithFlags_Values[q22] + | q24 : int(1..3)]) + | q22 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q26] != 5 -> + or([x_ExplicitVarSizeWithFlags_Flags[q28] /\ + x_ExplicitVarSizeWithFlags_Values[q28] = x_ExplicitVarSizeWithDummy[q26] + | q28 : int(1..3)]) + | q26 : int(1..3)]) + diff --git a/tests/exhaustive/basic/set05/expected/model_1_3_1-solution000001.solution b/tests/exhaustive/basic/set05/expected/model_1_3_1-solution000001.solution new file mode 100644 index 0000000000..f90e0ba18c --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_1_3_1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2} diff --git a/tests/exhaustive/basic/set05/expected/model_1_3_1-solution000002.solution b/tests/exhaustive/basic/set05/expected/model_1_3_1-solution000002.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_1_3_1-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set05/expected/model_1_3_1-solution000003.solution b/tests/exhaustive/basic/set05/expected/model_1_3_1-solution000003.solution new file mode 100644 index 0000000000..fdc0f02f96 --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_1_3_1-solution000003.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 4} diff --git a/tests/exhaustive/basic/set05/expected/model_1_3_1.eprime b/tests/exhaustive/basic/set05/expected/model_1_3_1.eprime new file mode 100644 index 0000000000..79fbdc8209 --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_1_3_1.eprime @@ -0,0 +1,21 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithMarker_Marker: int(0..3) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3)] of int(1..4) +branching on [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_Occurrence] +such that + x_Occurrence[1], + or([q11 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q11] = 2 | q11 : int(1..3)]), + sum([toInt(x_Occurrence[q1]) | q1 : int(1..4)]) <= 3, + and([q2 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q2] < x_ExplicitVarSizeWithMarker_Values[q2 + 1] + | q2 : int(1..2)]), + and([q3 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q3] = 1 | q3 : int(1..3)]), + x_ExplicitVarSizeWithMarker_Marker <= 3, + and([q6 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q6]] + | q6 : int(1..3)]), + and([x_Occurrence[q7] -> + or([q9 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q9] = q7 | q9 : int(1..3)]) + | q7 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set05/expected/model_1_3_2-solution000001.solution b/tests/exhaustive/basic/set05/expected/model_1_3_2-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_1_3_2-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set05/expected/model_1_3_2-solution000002.solution b/tests/exhaustive/basic/set05/expected/model_1_3_2-solution000002.solution new file mode 100644 index 0000000000..fdc0f02f96 --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_1_3_2-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 4} diff --git a/tests/exhaustive/basic/set05/expected/model_1_3_2-solution000003.solution b/tests/exhaustive/basic/set05/expected/model_1_3_2-solution000003.solution new file mode 100644 index 0000000000..f90e0ba18c --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_1_3_2-solution000003.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2} diff --git a/tests/exhaustive/basic/set05/expected/model_1_3_2.eprime b/tests/exhaustive/basic/set05/expected/model_1_3_2.eprime new file mode 100644 index 0000000000..85dcbc6f16 --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_1_3_2.eprime @@ -0,0 +1,41 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithMarker_Marker: int(0..3) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3)] of int(1..4) +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..3)] of int(1..5) +branching on + [x_ExplicitVarSizeWithDummy, x_Occurrence, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] +such that + x_Occurrence[1], + or([q28 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q28] = 2 | q28 : int(1..3)]), + sum([toInt(x_Occurrence[q1]) | q1 : int(1..4)]) <= 3, + and([q2 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q2] < x_ExplicitVarSizeWithMarker_Values[q2 + 1] + | q2 : int(1..2)]), + and([q3 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q3] = 1 | q3 : int(1..3)]), + x_ExplicitVarSizeWithMarker_Marker <= 3, + and([q6 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q6]] + | q6 : int(1..3)]), + and([x_Occurrence[q7] -> + or([q9 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q9] = q7 | q9 : int(1..3)]) + | q7 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q10] < x_ExplicitVarSizeWithDummy[q10 + 1] \/ x_ExplicitVarSizeWithDummy[q10] = 5 + | q10 : int(1..2)]), + and([x_ExplicitVarSizeWithDummy[q11] = 5 -> x_ExplicitVarSizeWithDummy[q11 + 1] = 5 | q11 : int(1..2)]), + sum([toInt(x_ExplicitVarSizeWithDummy[q12] != 5) | q12 : int(1..3)]) <= 3, + and([x_ExplicitVarSizeWithDummy[q15] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q15]] | q15 : int(1..3)]), + and([x_Occurrence[q16] -> + or([x_ExplicitVarSizeWithDummy[q18] != 5 /\ x_ExplicitVarSizeWithDummy[q18] = q16 | q18 : int(1..3)]) + | q16 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q20] != 5 -> + or([q22 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q22] = x_ExplicitVarSizeWithDummy[q20] + | q22 : int(1..3)]) + | q20 : int(1..3)]), + and([q24 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithDummy[q26] != 5 /\ + x_ExplicitVarSizeWithDummy[q26] = x_ExplicitVarSizeWithMarker_Values[q24] + | q26 : int(1..3)]) + | q24 : int(1..3)]) + diff --git a/tests/exhaustive/basic/set05/expected/model_1_3_4-solution000001.solution b/tests/exhaustive/basic/set05/expected/model_1_3_4-solution000001.solution new file mode 100644 index 0000000000..f90e0ba18c --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_1_3_4-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2} diff --git a/tests/exhaustive/basic/set05/expected/model_1_3_4-solution000002.solution b/tests/exhaustive/basic/set05/expected/model_1_3_4-solution000002.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_1_3_4-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set05/expected/model_1_3_4-solution000003.solution b/tests/exhaustive/basic/set05/expected/model_1_3_4-solution000003.solution new file mode 100644 index 0000000000..fdc0f02f96 --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_1_3_4-solution000003.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 4} diff --git a/tests/exhaustive/basic/set05/expected/model_1_3_4.eprime b/tests/exhaustive/basic/set05/expected/model_1_3_4.eprime new file mode 100644 index 0000000000..5d9c9d1d13 --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_1_3_4.eprime @@ -0,0 +1,47 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithMarker_Marker: int(0..3) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3)] of int(1..4) +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..3)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3)] of int(1..4) +branching on + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_Occurrence, + x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] +such that + x_Occurrence[1], + or([q29 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q29] = 2 | q29 : int(1..3)]), + sum([toInt(x_Occurrence[q1]) | q1 : int(1..4)]) <= 3, + and([q2 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q2] < x_ExplicitVarSizeWithMarker_Values[q2 + 1] + | q2 : int(1..2)]), + and([q3 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q3] = 1 | q3 : int(1..3)]), + x_ExplicitVarSizeWithMarker_Marker <= 3, + and([q6 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q6]] + | q6 : int(1..3)]), + and([x_Occurrence[q7] -> + or([q9 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q9] = q7 | q9 : int(1..3)]) + | q7 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q10 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q10] < x_ExplicitVarSizeWithFlags_Values[q10 + 1] + | q10 : int(1..2)]), + and([x_ExplicitVarSizeWithFlags_Flags[q11] = false -> x_ExplicitVarSizeWithFlags_Values[q11] = 1 + | q11 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q12 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q12] | q12 : int(1..2)]), + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q13]) | q13 : int(1..3)]) <= 3, + and([x_ExplicitVarSizeWithFlags_Flags[q16] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q16]] + | q16 : int(1..3)]), + and([x_Occurrence[q17] -> + or([x_ExplicitVarSizeWithFlags_Flags[q19] /\ x_ExplicitVarSizeWithFlags_Values[q19] = q17 | q19 : int(1..3)]) + | q17 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q21] -> + or([q23 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q23] = x_ExplicitVarSizeWithFlags_Values[q21] + | q23 : int(1..3)]) + | q21 : int(1..3)]), + and([q25 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithFlags_Flags[q27] /\ + x_ExplicitVarSizeWithFlags_Values[q27] = x_ExplicitVarSizeWithMarker_Values[q25] + | q27 : int(1..3)]) + | q25 : int(1..3)]) + diff --git a/tests/exhaustive/basic/set05/expected/model_1_4_1-solution000001.solution b/tests/exhaustive/basic/set05/expected/model_1_4_1-solution000001.solution new file mode 100644 index 0000000000..f90e0ba18c --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_1_4_1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2} diff --git a/tests/exhaustive/basic/set05/expected/model_1_4_1-solution000002.solution b/tests/exhaustive/basic/set05/expected/model_1_4_1-solution000002.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_1_4_1-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set05/expected/model_1_4_1-solution000003.solution b/tests/exhaustive/basic/set05/expected/model_1_4_1-solution000003.solution new file mode 100644 index 0000000000..fdc0f02f96 --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_1_4_1-solution000003.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 4} diff --git a/tests/exhaustive/basic/set05/expected/model_1_4_1.eprime b/tests/exhaustive/basic/set05/expected/model_1_4_1.eprime new file mode 100644 index 0000000000..9ede8575b3 --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_1_4_1.eprime @@ -0,0 +1,21 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..3)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3)] of int(1..4) +branching on [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_Occurrence] +such that + x_Occurrence[1], + or([x_ExplicitVarSizeWithFlags_Flags[q13] /\ x_ExplicitVarSizeWithFlags_Values[q13] = 2 | q13 : int(1..3)]), + sum([toInt(x_Occurrence[q1]) | q1 : int(1..4)]) <= 3, + and([x_ExplicitVarSizeWithFlags_Flags[q2 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q2] < x_ExplicitVarSizeWithFlags_Values[q2 + 1] + | q2 : int(1..2)]), + and([x_ExplicitVarSizeWithFlags_Flags[q3] = false -> x_ExplicitVarSizeWithFlags_Values[q3] = 1 | q3 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q4] | q4 : int(1..2)]), + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q5]) | q5 : int(1..3)]) <= 3, + and([x_ExplicitVarSizeWithFlags_Flags[q8] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q8]] | q8 : int(1..3)]), + and([x_Occurrence[q9] -> + or([x_ExplicitVarSizeWithFlags_Flags[q11] /\ x_ExplicitVarSizeWithFlags_Values[q11] = q9 | q11 : int(1..3)]) + | q9 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set05/expected/model_1_4_2-solution000001.solution b/tests/exhaustive/basic/set05/expected/model_1_4_2-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_1_4_2-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set05/expected/model_1_4_2-solution000002.solution b/tests/exhaustive/basic/set05/expected/model_1_4_2-solution000002.solution new file mode 100644 index 0000000000..fdc0f02f96 --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_1_4_2-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 4} diff --git a/tests/exhaustive/basic/set05/expected/model_1_4_2-solution000003.solution b/tests/exhaustive/basic/set05/expected/model_1_4_2-solution000003.solution new file mode 100644 index 0000000000..f90e0ba18c --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_1_4_2-solution000003.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2} diff --git a/tests/exhaustive/basic/set05/expected/model_1_4_2.eprime b/tests/exhaustive/basic/set05/expected/model_1_4_2.eprime new file mode 100644 index 0000000000..ee08cbe011 --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_1_4_2.eprime @@ -0,0 +1,41 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..3)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3)] of int(1..4) +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..3)] of int(1..5) +branching on + [x_ExplicitVarSizeWithDummy, x_Occurrence, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] +such that + x_Occurrence[1], + or([x_ExplicitVarSizeWithFlags_Flags[q30] /\ x_ExplicitVarSizeWithFlags_Values[q30] = 2 | q30 : int(1..3)]), + sum([toInt(x_Occurrence[q1]) | q1 : int(1..4)]) <= 3, + and([x_ExplicitVarSizeWithFlags_Flags[q2 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q2] < x_ExplicitVarSizeWithFlags_Values[q2 + 1] + | q2 : int(1..2)]), + and([x_ExplicitVarSizeWithFlags_Flags[q3] = false -> x_ExplicitVarSizeWithFlags_Values[q3] = 1 | q3 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q4] | q4 : int(1..2)]), + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q5]) | q5 : int(1..3)]) <= 3, + and([x_ExplicitVarSizeWithFlags_Flags[q8] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q8]] | q8 : int(1..3)]), + and([x_Occurrence[q9] -> + or([x_ExplicitVarSizeWithFlags_Flags[q11] /\ x_ExplicitVarSizeWithFlags_Values[q11] = q9 | q11 : int(1..3)]) + | q9 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q12] < x_ExplicitVarSizeWithDummy[q12 + 1] \/ x_ExplicitVarSizeWithDummy[q12] = 5 + | q12 : int(1..2)]), + and([x_ExplicitVarSizeWithDummy[q13] = 5 -> x_ExplicitVarSizeWithDummy[q13 + 1] = 5 | q13 : int(1..2)]), + sum([toInt(x_ExplicitVarSizeWithDummy[q14] != 5) | q14 : int(1..3)]) <= 3, + and([x_ExplicitVarSizeWithDummy[q17] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q17]] | q17 : int(1..3)]), + and([x_Occurrence[q18] -> + or([x_ExplicitVarSizeWithDummy[q20] != 5 /\ x_ExplicitVarSizeWithDummy[q20] = q18 | q20 : int(1..3)]) + | q18 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q22] != 5 -> + or([x_ExplicitVarSizeWithFlags_Flags[q24] /\ + x_ExplicitVarSizeWithFlags_Values[q24] = x_ExplicitVarSizeWithDummy[q22] + | q24 : int(1..3)]) + | q22 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q26] -> + or([x_ExplicitVarSizeWithDummy[q28] != 5 /\ + x_ExplicitVarSizeWithDummy[q28] = x_ExplicitVarSizeWithFlags_Values[q26] + | q28 : int(1..3)]) + | q26 : int(1..3)]) + diff --git a/tests/exhaustive/basic/set05/expected/model_1_4_3-solution000001.solution b/tests/exhaustive/basic/set05/expected/model_1_4_3-solution000001.solution new file mode 100644 index 0000000000..f90e0ba18c --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_1_4_3-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2} diff --git a/tests/exhaustive/basic/set05/expected/model_1_4_3-solution000002.solution b/tests/exhaustive/basic/set05/expected/model_1_4_3-solution000002.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_1_4_3-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set05/expected/model_1_4_3-solution000003.solution b/tests/exhaustive/basic/set05/expected/model_1_4_3-solution000003.solution new file mode 100644 index 0000000000..fdc0f02f96 --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_1_4_3-solution000003.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 4} diff --git a/tests/exhaustive/basic/set05/expected/model_1_4_3.eprime b/tests/exhaustive/basic/set05/expected/model_1_4_3.eprime new file mode 100644 index 0000000000..387a3320f5 --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_1_4_3.eprime @@ -0,0 +1,46 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..3)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3)] of int(1..4) +find x_ExplicitVarSizeWithMarker_Marker: int(0..3) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3)] of int(1..4) +branching on + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_Occurrence, + x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] +such that + x_Occurrence[1], + or([x_ExplicitVarSizeWithFlags_Flags[q29] /\ x_ExplicitVarSizeWithFlags_Values[q29] = 2 | q29 : int(1..3)]), + sum([toInt(x_Occurrence[q1]) | q1 : int(1..4)]) <= 3, + and([x_ExplicitVarSizeWithFlags_Flags[q2 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q2] < x_ExplicitVarSizeWithFlags_Values[q2 + 1] + | q2 : int(1..2)]), + and([x_ExplicitVarSizeWithFlags_Flags[q3] = false -> x_ExplicitVarSizeWithFlags_Values[q3] = 1 | q3 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q4] | q4 : int(1..2)]), + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q5]) | q5 : int(1..3)]) <= 3, + and([x_ExplicitVarSizeWithFlags_Flags[q8] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q8]] | q8 : int(1..3)]), + and([x_Occurrence[q9] -> + or([x_ExplicitVarSizeWithFlags_Flags[q11] /\ x_ExplicitVarSizeWithFlags_Values[q11] = q9 | q11 : int(1..3)]) + | q9 : int(1..4)]), + and([q12 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q12] < x_ExplicitVarSizeWithMarker_Values[q12 + 1] + | q12 : int(1..2)]), + and([q13 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q13] = 1 | q13 : int(1..3)]), + x_ExplicitVarSizeWithMarker_Marker <= 3, + and([q16 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q16]] + | q16 : int(1..3)]), + and([x_Occurrence[q17] -> + or([q19 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q19] = q17 + | q19 : int(1..3)]) + | q17 : int(1..4)]), + and([q21 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithFlags_Flags[q23] /\ + x_ExplicitVarSizeWithFlags_Values[q23] = x_ExplicitVarSizeWithMarker_Values[q21] + | q23 : int(1..3)]) + | q21 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q25] -> + or([q27 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q27] = x_ExplicitVarSizeWithFlags_Values[q25] + | q27 : int(1..3)]) + | q25 : int(1..3)]) + diff --git a/tests/exhaustive/basic/set05/expected/model_2_1_1-solution000001.solution b/tests/exhaustive/basic/set05/expected/model_2_1_1-solution000001.solution new file mode 100644 index 0000000000..f90e0ba18c --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_2_1_1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2} diff --git a/tests/exhaustive/basic/set05/expected/model_2_1_1-solution000002.solution b/tests/exhaustive/basic/set05/expected/model_2_1_1-solution000002.solution new file mode 100644 index 0000000000..fdc0f02f96 --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_2_1_1-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 4} diff --git a/tests/exhaustive/basic/set05/expected/model_2_1_1-solution000003.solution b/tests/exhaustive/basic/set05/expected/model_2_1_1-solution000003.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_2_1_1-solution000003.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set05/expected/model_2_1_1.eprime b/tests/exhaustive/basic/set05/expected/model_2_1_1.eprime new file mode 100644 index 0000000000..6b99e48d14 --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_2_1_1.eprime @@ -0,0 +1,18 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..3)] of int(1..5) +find x_Occurrence: matrix indexed by [int(1..4)] of bool +branching on [x_Occurrence, x_ExplicitVarSizeWithDummy] +such that + or([x_ExplicitVarSizeWithDummy[q12] != 5 /\ x_ExplicitVarSizeWithDummy[q12] = 1 | q12 : int(1..3)]), + x_Occurrence[2], + and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 5 + | q1 : int(1..2)]), + and([x_ExplicitVarSizeWithDummy[q2] = 5 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..2)]), + sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 5) | q3 : int(1..3)]) <= 3, + sum([toInt(x_Occurrence[q5]) | q5 : int(1..4)]) <= 3, + and([x_Occurrence[q6] -> + or([x_ExplicitVarSizeWithDummy[q8] != 5 /\ x_ExplicitVarSizeWithDummy[q8] = q6 | q8 : int(1..3)]) + | q6 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q10] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q10]] | q10 : int(1..3)]) + diff --git a/tests/exhaustive/basic/set05/expected/model_2_1_3-solution000001.solution b/tests/exhaustive/basic/set05/expected/model_2_1_3-solution000001.solution new file mode 100644 index 0000000000..f90e0ba18c --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_2_1_3-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2} diff --git a/tests/exhaustive/basic/set05/expected/model_2_1_3-solution000002.solution b/tests/exhaustive/basic/set05/expected/model_2_1_3-solution000002.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_2_1_3-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set05/expected/model_2_1_3-solution000003.solution b/tests/exhaustive/basic/set05/expected/model_2_1_3-solution000003.solution new file mode 100644 index 0000000000..fdc0f02f96 --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_2_1_3-solution000003.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 4} diff --git a/tests/exhaustive/basic/set05/expected/model_2_1_3.eprime b/tests/exhaustive/basic/set05/expected/model_2_1_3.eprime new file mode 100644 index 0000000000..3afbad58c6 --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_2_1_3.eprime @@ -0,0 +1,42 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..3)] of int(1..5) +find x_Occurrence: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithMarker_Marker: int(0..3) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3)] of int(1..4) +branching on + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy, x_Occurrence] +such that + or([x_ExplicitVarSizeWithDummy[q28] != 5 /\ x_ExplicitVarSizeWithDummy[q28] = 1 | q28 : int(1..3)]), + x_Occurrence[2], + and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 5 + | q1 : int(1..2)]), + and([x_ExplicitVarSizeWithDummy[q2] = 5 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..2)]), + sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 5) | q3 : int(1..3)]) <= 3, + sum([toInt(x_Occurrence[q5]) | q5 : int(1..4)]) <= 3, + and([x_Occurrence[q22] -> + or([x_ExplicitVarSizeWithDummy[q24] != 5 /\ x_ExplicitVarSizeWithDummy[q24] = q22 | q24 : int(1..3)]) + | q22 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q26] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q26]] | q26 : int(1..3)]), + and([q6 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q6] < x_ExplicitVarSizeWithMarker_Values[q6 + 1] + | q6 : int(1..2)]), + and([q7 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q7] = 1 | q7 : int(1..3)]), + x_ExplicitVarSizeWithMarker_Marker <= 3, + and([q10 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithDummy[q12] != 5 /\ + x_ExplicitVarSizeWithDummy[q12] = x_ExplicitVarSizeWithMarker_Values[q10] + | q12 : int(1..3)]) + | q10 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q14] != 5 -> + or([q16 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q16] = x_ExplicitVarSizeWithDummy[q14] + | q16 : int(1..3)]) + | q14 : int(1..3)]), + and([q18 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q18]] + | q18 : int(1..3)]), + and([x_Occurrence[q19] -> + or([q21 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q21] = q19 + | q21 : int(1..3)]) + | q19 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set05/expected/model_2_1_4-solution000001.solution b/tests/exhaustive/basic/set05/expected/model_2_1_4-solution000001.solution new file mode 100644 index 0000000000..f90e0ba18c --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_2_1_4-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2} diff --git a/tests/exhaustive/basic/set05/expected/model_2_1_4-solution000002.solution b/tests/exhaustive/basic/set05/expected/model_2_1_4-solution000002.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_2_1_4-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set05/expected/model_2_1_4-solution000003.solution b/tests/exhaustive/basic/set05/expected/model_2_1_4-solution000003.solution new file mode 100644 index 0000000000..fdc0f02f96 --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_2_1_4-solution000003.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 4} diff --git a/tests/exhaustive/basic/set05/expected/model_2_1_4.eprime b/tests/exhaustive/basic/set05/expected/model_2_1_4.eprime new file mode 100644 index 0000000000..3cf7e10a32 --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_2_1_4.eprime @@ -0,0 +1,42 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..3)] of int(1..5) +find x_Occurrence: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..3)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3)] of int(1..4) +branching on + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy, x_Occurrence] +such that + or([x_ExplicitVarSizeWithDummy[q30] != 5 /\ x_ExplicitVarSizeWithDummy[q30] = 1 | q30 : int(1..3)]), + x_Occurrence[2], + and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 5 + | q1 : int(1..2)]), + and([x_ExplicitVarSizeWithDummy[q2] = 5 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..2)]), + sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 5) | q3 : int(1..3)]) <= 3, + sum([toInt(x_Occurrence[q5]) | q5 : int(1..4)]) <= 3, + and([x_Occurrence[q24] -> + or([x_ExplicitVarSizeWithDummy[q26] != 5 /\ x_ExplicitVarSizeWithDummy[q26] = q24 | q26 : int(1..3)]) + | q24 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q28] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q28]] | q28 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q6] < x_ExplicitVarSizeWithFlags_Values[q6 + 1] + | q6 : int(1..2)]), + and([x_ExplicitVarSizeWithFlags_Flags[q7] = false -> x_ExplicitVarSizeWithFlags_Values[q7] = 1 | q7 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q8 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q8] | q8 : int(1..2)]), + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q9]) | q9 : int(1..3)]) <= 3, + and([x_ExplicitVarSizeWithFlags_Flags[q12] -> + or([x_ExplicitVarSizeWithDummy[q14] != 5 /\ + x_ExplicitVarSizeWithDummy[q14] = x_ExplicitVarSizeWithFlags_Values[q12] + | q14 : int(1..3)]) + | q12 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q16] != 5 -> + or([x_ExplicitVarSizeWithFlags_Flags[q18] /\ + x_ExplicitVarSizeWithFlags_Values[q18] = x_ExplicitVarSizeWithDummy[q16] + | q18 : int(1..3)]) + | q16 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q20] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q20]] + | q20 : int(1..3)]), + and([x_Occurrence[q21] -> + or([x_ExplicitVarSizeWithFlags_Flags[q23] /\ x_ExplicitVarSizeWithFlags_Values[q23] = q21 | q23 : int(1..3)]) + | q21 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set05/expected/model_2_2_1-solution000001.solution b/tests/exhaustive/basic/set05/expected/model_2_2_1-solution000001.solution new file mode 100644 index 0000000000..f90e0ba18c --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_2_2_1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2} diff --git a/tests/exhaustive/basic/set05/expected/model_2_2_1-solution000002.solution b/tests/exhaustive/basic/set05/expected/model_2_2_1-solution000002.solution new file mode 100644 index 0000000000..fdc0f02f96 --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_2_2_1-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 4} diff --git a/tests/exhaustive/basic/set05/expected/model_2_2_1-solution000003.solution b/tests/exhaustive/basic/set05/expected/model_2_2_1-solution000003.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_2_2_1-solution000003.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set05/expected/model_2_2_1.eprime b/tests/exhaustive/basic/set05/expected/model_2_2_1.eprime new file mode 100644 index 0000000000..cb17af9c96 --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_2_2_1.eprime @@ -0,0 +1,18 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..3)] of int(1..5) +find x_Occurrence: matrix indexed by [int(1..4)] of bool +branching on [x_Occurrence, x_ExplicitVarSizeWithDummy] +such that + or([x_ExplicitVarSizeWithDummy[q12] != 5 /\ x_ExplicitVarSizeWithDummy[q12] = 1 | q12 : int(1..3)]), + or([x_ExplicitVarSizeWithDummy[q14] != 5 /\ x_ExplicitVarSizeWithDummy[q14] = 2 | q14 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 5 + | q1 : int(1..2)]), + and([x_ExplicitVarSizeWithDummy[q2] = 5 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..2)]), + sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 5) | q3 : int(1..3)]) <= 3, + sum([toInt(x_Occurrence[q5]) | q5 : int(1..4)]) <= 3, + and([x_Occurrence[q6] -> + or([x_ExplicitVarSizeWithDummy[q8] != 5 /\ x_ExplicitVarSizeWithDummy[q8] = q6 | q8 : int(1..3)]) + | q6 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q10] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q10]] | q10 : int(1..3)]) + diff --git a/tests/exhaustive/basic/set05/expected/model_2_2_2-solution000001.solution b/tests/exhaustive/basic/set05/expected/model_2_2_2-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_2_2_2-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set05/expected/model_2_2_2-solution000002.solution b/tests/exhaustive/basic/set05/expected/model_2_2_2-solution000002.solution new file mode 100644 index 0000000000..fdc0f02f96 --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_2_2_2-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 4} diff --git a/tests/exhaustive/basic/set05/expected/model_2_2_2-solution000003.solution b/tests/exhaustive/basic/set05/expected/model_2_2_2-solution000003.solution new file mode 100644 index 0000000000..f90e0ba18c --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_2_2_2-solution000003.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2} diff --git a/tests/exhaustive/basic/set05/expected/model_2_2_2.eprime b/tests/exhaustive/basic/set05/expected/model_2_2_2.eprime new file mode 100644 index 0000000000..4cb7d7d439 --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_2_2_2.eprime @@ -0,0 +1,12 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..3)] of int(1..5) +branching on [x_ExplicitVarSizeWithDummy] +such that + or([x_ExplicitVarSizeWithDummy[q6] != 5 /\ x_ExplicitVarSizeWithDummy[q6] = 1 | q6 : int(1..3)]), + or([x_ExplicitVarSizeWithDummy[q8] != 5 /\ x_ExplicitVarSizeWithDummy[q8] = 2 | q8 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 5 + | q1 : int(1..2)]), + and([x_ExplicitVarSizeWithDummy[q2] = 5 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..2)]), + sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 5) | q3 : int(1..3)]) <= 3 + diff --git a/tests/exhaustive/basic/set05/expected/model_2_2_3-solution000001.solution b/tests/exhaustive/basic/set05/expected/model_2_2_3-solution000001.solution new file mode 100644 index 0000000000..f90e0ba18c --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_2_2_3-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2} diff --git a/tests/exhaustive/basic/set05/expected/model_2_2_3-solution000002.solution b/tests/exhaustive/basic/set05/expected/model_2_2_3-solution000002.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_2_2_3-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set05/expected/model_2_2_3-solution000003.solution b/tests/exhaustive/basic/set05/expected/model_2_2_3-solution000003.solution new file mode 100644 index 0000000000..fdc0f02f96 --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_2_2_3-solution000003.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 4} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_3_3.eprime.orig b/tests/exhaustive/basic/set05/expected/model_2_2_3.eprime similarity index 55% rename from tests/exhaustive/basic/cut_01_on/expected/model_2_3_3.eprime.orig rename to tests/exhaustive/basic/set05/expected/model_2_2_3.eprime index 841093014c..e60bea847e 100644 --- a/tests/exhaustive/basic/cut_01_on/expected/model_2_3_3.eprime.orig +++ b/tests/exhaustive/basic/set05/expected/model_2_2_3.eprime @@ -1,31 +1,27 @@ language ESSENCE' 1.0 -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..3)] of int(1..4) +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..3)] of int(1..5) find x_ExplicitVarSizeWithMarker_Marker: int(0..3) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3)] of int(1..3) -find cut1: bool -find cut2: bool -branching on - [cut1, cut2, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy] +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3)] of int(1..4) +branching on [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy] such that - !cut1 <-> - or([x_ExplicitVarSizeWithDummy[q18] != 4 /\ x_ExplicitVarSizeWithDummy[q18] = 1 | q18 : int(1..3)]) /\ - or([x_ExplicitVarSizeWithDummy[q20] != 4 /\ x_ExplicitVarSizeWithDummy[q20] = 2 | q20 : int(1..3)]), - !cut2 <-> - or([q22 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q22] = 1 | q22 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 4 + or([x_ExplicitVarSizeWithDummy[q17] != 5 /\ x_ExplicitVarSizeWithDummy[q17] = 1 | q17 : int(1..3)]), + or([x_ExplicitVarSizeWithDummy[q19] != 5 /\ x_ExplicitVarSizeWithDummy[q19] = 2 | q19 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 5 | q1 : int(1..2)]), - and([x_ExplicitVarSizeWithDummy[q2] = 4 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 4 | q2 : int(1..2)]), + and([x_ExplicitVarSizeWithDummy[q2] = 5 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..2)]), + sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 5) | q3 : int(1..3)]) <= 3, and([q5 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q5] < x_ExplicitVarSizeWithMarker_Values[q5 + 1] | q5 : int(1..2)]), and([q6 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q6] = 1 | q6 : int(1..3)]), + x_ExplicitVarSizeWithMarker_Marker <= 3, and([q9 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q11] != 4 /\ + or([x_ExplicitVarSizeWithDummy[q11] != 5 /\ x_ExplicitVarSizeWithDummy[q11] = x_ExplicitVarSizeWithMarker_Values[q9] | q11 : int(1..3)]) | q9 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q13] != 4 -> + and([x_ExplicitVarSizeWithDummy[q13] != 5 -> or([q15 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q15] = x_ExplicitVarSizeWithDummy[q13] | q15 : int(1..3)]) diff --git a/tests/exhaustive/basic/set05/expected/model_2_2_4-solution000001.solution b/tests/exhaustive/basic/set05/expected/model_2_2_4-solution000001.solution new file mode 100644 index 0000000000..f90e0ba18c --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_2_2_4-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2} diff --git a/tests/exhaustive/basic/set05/expected/model_2_2_4-solution000002.solution b/tests/exhaustive/basic/set05/expected/model_2_2_4-solution000002.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_2_2_4-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set05/expected/model_2_2_4-solution000003.solution b/tests/exhaustive/basic/set05/expected/model_2_2_4-solution000003.solution new file mode 100644 index 0000000000..fdc0f02f96 --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_2_2_4-solution000003.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 4} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_2_4_4.eprime.orig b/tests/exhaustive/basic/set05/expected/model_2_2_4.eprime similarity index 59% rename from tests/exhaustive/basic/cut_01_on/expected/model_2_4_4.eprime.orig rename to tests/exhaustive/basic/set05/expected/model_2_2_4.eprime index 31db1d1a15..06f804e4d5 100644 --- a/tests/exhaustive/basic/cut_01_on/expected/model_2_4_4.eprime.orig +++ b/tests/exhaustive/basic/set05/expected/model_2_2_4.eprime @@ -1,32 +1,28 @@ language ESSENCE' 1.0 -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..3)] of int(1..4) +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..3)] of int(1..5) find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..3)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3)] of int(1..3) -find cut1: bool -find cut2: bool -branching on - [cut1, cut2, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy] +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3)] of int(1..4) +branching on [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy] such that - !cut1 <-> - or([x_ExplicitVarSizeWithDummy[q20] != 4 /\ x_ExplicitVarSizeWithDummy[q20] = 1 | q20 : int(1..3)]) /\ - or([x_ExplicitVarSizeWithDummy[q22] != 4 /\ x_ExplicitVarSizeWithDummy[q22] = 2 | q22 : int(1..3)]), - !cut2 <-> - or([x_ExplicitVarSizeWithFlags_Flags[q24] /\ x_ExplicitVarSizeWithFlags_Values[q24] = 1 | q24 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 4 + or([x_ExplicitVarSizeWithDummy[q19] != 5 /\ x_ExplicitVarSizeWithDummy[q19] = 1 | q19 : int(1..3)]), + or([x_ExplicitVarSizeWithDummy[q21] != 5 /\ x_ExplicitVarSizeWithDummy[q21] = 2 | q21 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 5 | q1 : int(1..2)]), - and([x_ExplicitVarSizeWithDummy[q2] = 4 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 4 | q2 : int(1..2)]), + and([x_ExplicitVarSizeWithDummy[q2] = 5 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..2)]), + sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 5) | q3 : int(1..3)]) <= 3, and([x_ExplicitVarSizeWithFlags_Flags[q5 + 1] -> x_ExplicitVarSizeWithFlags_Values[q5] < x_ExplicitVarSizeWithFlags_Values[q5 + 1] | q5 : int(1..2)]), and([x_ExplicitVarSizeWithFlags_Flags[q6] = false -> x_ExplicitVarSizeWithFlags_Values[q6] = 1 | q6 : int(1..3)]), and([x_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q7] | q7 : int(1..2)]), + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q8]) | q8 : int(1..3)]) <= 3, and([x_ExplicitVarSizeWithFlags_Flags[q11] -> - or([x_ExplicitVarSizeWithDummy[q13] != 4 /\ + or([x_ExplicitVarSizeWithDummy[q13] != 5 /\ x_ExplicitVarSizeWithDummy[q13] = x_ExplicitVarSizeWithFlags_Values[q11] | q13 : int(1..3)]) | q11 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q15] != 4 -> + and([x_ExplicitVarSizeWithDummy[q15] != 5 -> or([x_ExplicitVarSizeWithFlags_Flags[q17] /\ x_ExplicitVarSizeWithFlags_Values[q17] = x_ExplicitVarSizeWithDummy[q15] | q17 : int(1..3)]) diff --git a/tests/exhaustive/basic/set05/expected/model_2_3_1-solution000001.solution b/tests/exhaustive/basic/set05/expected/model_2_3_1-solution000001.solution new file mode 100644 index 0000000000..f90e0ba18c --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_2_3_1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2} diff --git a/tests/exhaustive/basic/set05/expected/model_2_3_1-solution000002.solution b/tests/exhaustive/basic/set05/expected/model_2_3_1-solution000002.solution new file mode 100644 index 0000000000..fdc0f02f96 --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_2_3_1-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 4} diff --git a/tests/exhaustive/basic/set05/expected/model_2_3_1-solution000003.solution b/tests/exhaustive/basic/set05/expected/model_2_3_1-solution000003.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_2_3_1-solution000003.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set05/expected/model_2_3_1.eprime b/tests/exhaustive/basic/set05/expected/model_2_3_1.eprime new file mode 100644 index 0000000000..40eab4116d --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_2_3_1.eprime @@ -0,0 +1,42 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..3)] of int(1..5) +find x_ExplicitVarSizeWithMarker_Marker: int(0..3) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3)] of int(1..4) +find x_Occurrence: matrix indexed by [int(1..4)] of bool +branching on + [x_Occurrence, x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] +such that + or([x_ExplicitVarSizeWithDummy[q28] != 5 /\ x_ExplicitVarSizeWithDummy[q28] = 1 | q28 : int(1..3)]), + or([q30 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q30] = 2 | q30 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 5 + | q1 : int(1..2)]), + and([x_ExplicitVarSizeWithDummy[q2] = 5 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..2)]), + sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 5) | q3 : int(1..3)]) <= 3, + and([q5 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q5] < x_ExplicitVarSizeWithMarker_Values[q5 + 1] + | q5 : int(1..2)]), + and([q6 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q6] = 1 | q6 : int(1..3)]), + x_ExplicitVarSizeWithMarker_Marker <= 3, + and([q9 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithDummy[q11] != 5 /\ + x_ExplicitVarSizeWithDummy[q11] = x_ExplicitVarSizeWithMarker_Values[q9] + | q11 : int(1..3)]) + | q9 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q13] != 5 -> + or([q15 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q15] = x_ExplicitVarSizeWithDummy[q13] + | q15 : int(1..3)]) + | q13 : int(1..3)]), + sum([toInt(x_Occurrence[q16]) | q16 : int(1..4)]) <= 3, + and([x_Occurrence[q17] -> + or([x_ExplicitVarSizeWithDummy[q19] != 5 /\ x_ExplicitVarSizeWithDummy[q19] = q17 | q19 : int(1..3)]) + | q17 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q21] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q21]] | q21 : int(1..3)]), + and([x_Occurrence[q22] -> + or([q24 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q24] = q22 + | q24 : int(1..3)]) + | q22 : int(1..4)]), + and([q26 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q26]] + | q26 : int(1..3)]) + diff --git a/tests/exhaustive/basic/set05/expected/model_2_3_2-solution000001.solution b/tests/exhaustive/basic/set05/expected/model_2_3_2-solution000001.solution new file mode 100644 index 0000000000..f90e0ba18c --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_2_3_2-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2} diff --git a/tests/exhaustive/basic/set05/expected/model_2_3_2-solution000002.solution b/tests/exhaustive/basic/set05/expected/model_2_3_2-solution000002.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_2_3_2-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set05/expected/model_2_3_2-solution000003.solution b/tests/exhaustive/basic/set05/expected/model_2_3_2-solution000003.solution new file mode 100644 index 0000000000..fdc0f02f96 --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_2_3_2-solution000003.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 4} diff --git a/tests/exhaustive/basic/set05/expected/model_2_3_2.eprime b/tests/exhaustive/basic/set05/expected/model_2_3_2.eprime new file mode 100644 index 0000000000..9ddf8ddf04 --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_2_3_2.eprime @@ -0,0 +1,29 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..3)] of int(1..5) +find x_ExplicitVarSizeWithMarker_Marker: int(0..3) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3)] of int(1..4) +branching on [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy] +such that + or([x_ExplicitVarSizeWithDummy[q17] != 5 /\ x_ExplicitVarSizeWithDummy[q17] = 1 | q17 : int(1..3)]), + or([q19 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q19] = 2 | q19 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 5 + | q1 : int(1..2)]), + and([x_ExplicitVarSizeWithDummy[q2] = 5 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..2)]), + sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 5) | q3 : int(1..3)]) <= 3, + and([q5 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q5] < x_ExplicitVarSizeWithMarker_Values[q5 + 1] + | q5 : int(1..2)]), + and([q6 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q6] = 1 | q6 : int(1..3)]), + x_ExplicitVarSizeWithMarker_Marker <= 3, + and([q9 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithDummy[q11] != 5 /\ + x_ExplicitVarSizeWithDummy[q11] = x_ExplicitVarSizeWithMarker_Values[q9] + | q11 : int(1..3)]) + | q9 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q13] != 5 -> + or([q15 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q15] = x_ExplicitVarSizeWithDummy[q13] + | q15 : int(1..3)]) + | q13 : int(1..3)]) + diff --git a/tests/exhaustive/basic/set05/expected/model_2_3_4-solution000001.solution b/tests/exhaustive/basic/set05/expected/model_2_3_4-solution000001.solution new file mode 100644 index 0000000000..f90e0ba18c --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_2_3_4-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2} diff --git a/tests/exhaustive/basic/set05/expected/model_2_3_4-solution000002.solution b/tests/exhaustive/basic/set05/expected/model_2_3_4-solution000002.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_2_3_4-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set05/expected/model_2_3_4-solution000003.solution b/tests/exhaustive/basic/set05/expected/model_2_3_4-solution000003.solution new file mode 100644 index 0000000000..fdc0f02f96 --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_2_3_4-solution000003.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 4} diff --git a/tests/exhaustive/basic/set05/expected/model_2_3_4.eprime b/tests/exhaustive/basic/set05/expected/model_2_3_4.eprime new file mode 100644 index 0000000000..933ef63b6a --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_2_3_4.eprime @@ -0,0 +1,60 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..3)] of int(1..5) +find x_ExplicitVarSizeWithMarker_Marker: int(0..3) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3)] of int(1..4) +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..3)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3)] of int(1..4) +branching on + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy, + x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] +such that + or([x_ExplicitVarSizeWithDummy[q38] != 5 /\ x_ExplicitVarSizeWithDummy[q38] = 1 | q38 : int(1..3)]), + or([q40 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q40] = 2 | q40 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 5 + | q1 : int(1..2)]), + and([x_ExplicitVarSizeWithDummy[q2] = 5 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..2)]), + sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 5) | q3 : int(1..3)]) <= 3, + and([q5 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q5] < x_ExplicitVarSizeWithMarker_Values[q5 + 1] + | q5 : int(1..2)]), + and([q6 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q6] = 1 | q6 : int(1..3)]), + x_ExplicitVarSizeWithMarker_Marker <= 3, + and([q9 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithDummy[q11] != 5 /\ + x_ExplicitVarSizeWithDummy[q11] = x_ExplicitVarSizeWithMarker_Values[q9] + | q11 : int(1..3)]) + | q9 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q13] != 5 -> + or([q15 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q15] = x_ExplicitVarSizeWithDummy[q13] + | q15 : int(1..3)]) + | q13 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q16 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q16] < x_ExplicitVarSizeWithFlags_Values[q16 + 1] + | q16 : int(1..2)]), + and([x_ExplicitVarSizeWithFlags_Flags[q17] = false -> x_ExplicitVarSizeWithFlags_Values[q17] = 1 + | q17 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q18 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q18] | q18 : int(1..2)]), + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q19]) | q19 : int(1..3)]) <= 3, + and([x_ExplicitVarSizeWithFlags_Flags[q22] -> + or([x_ExplicitVarSizeWithDummy[q24] != 5 /\ + x_ExplicitVarSizeWithDummy[q24] = x_ExplicitVarSizeWithFlags_Values[q22] + | q24 : int(1..3)]) + | q22 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q26] != 5 -> + or([x_ExplicitVarSizeWithFlags_Flags[q28] /\ + x_ExplicitVarSizeWithFlags_Values[q28] = x_ExplicitVarSizeWithDummy[q26] + | q28 : int(1..3)]) + | q26 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q30] -> + or([q32 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q32] = x_ExplicitVarSizeWithFlags_Values[q30] + | q32 : int(1..3)]) + | q30 : int(1..3)]), + and([q34 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithFlags_Flags[q36] /\ + x_ExplicitVarSizeWithFlags_Values[q36] = x_ExplicitVarSizeWithMarker_Values[q34] + | q36 : int(1..3)]) + | q34 : int(1..3)]) + diff --git a/tests/exhaustive/basic/set05/expected/model_2_4_1-solution000001.solution b/tests/exhaustive/basic/set05/expected/model_2_4_1-solution000001.solution new file mode 100644 index 0000000000..f90e0ba18c --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_2_4_1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2} diff --git a/tests/exhaustive/basic/set05/expected/model_2_4_1-solution000002.solution b/tests/exhaustive/basic/set05/expected/model_2_4_1-solution000002.solution new file mode 100644 index 0000000000..fdc0f02f96 --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_2_4_1-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 4} diff --git a/tests/exhaustive/basic/set05/expected/model_2_4_1-solution000003.solution b/tests/exhaustive/basic/set05/expected/model_2_4_1-solution000003.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_2_4_1-solution000003.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set05/expected/model_2_4_1.eprime b/tests/exhaustive/basic/set05/expected/model_2_4_1.eprime new file mode 100644 index 0000000000..81a9200abd --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_2_4_1.eprime @@ -0,0 +1,42 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..3)] of int(1..5) +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..3)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3)] of int(1..4) +find x_Occurrence: matrix indexed by [int(1..4)] of bool +branching on + [x_Occurrence, x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] +such that + or([x_ExplicitVarSizeWithDummy[q30] != 5 /\ x_ExplicitVarSizeWithDummy[q30] = 1 | q30 : int(1..3)]), + or([x_ExplicitVarSizeWithFlags_Flags[q32] /\ x_ExplicitVarSizeWithFlags_Values[q32] = 2 | q32 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 5 + | q1 : int(1..2)]), + and([x_ExplicitVarSizeWithDummy[q2] = 5 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..2)]), + sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 5) | q3 : int(1..3)]) <= 3, + and([x_ExplicitVarSizeWithFlags_Flags[q5 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q5] < x_ExplicitVarSizeWithFlags_Values[q5 + 1] + | q5 : int(1..2)]), + and([x_ExplicitVarSizeWithFlags_Flags[q6] = false -> x_ExplicitVarSizeWithFlags_Values[q6] = 1 | q6 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q7] | q7 : int(1..2)]), + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q8]) | q8 : int(1..3)]) <= 3, + and([x_ExplicitVarSizeWithFlags_Flags[q11] -> + or([x_ExplicitVarSizeWithDummy[q13] != 5 /\ + x_ExplicitVarSizeWithDummy[q13] = x_ExplicitVarSizeWithFlags_Values[q11] + | q13 : int(1..3)]) + | q11 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q15] != 5 -> + or([x_ExplicitVarSizeWithFlags_Flags[q17] /\ + x_ExplicitVarSizeWithFlags_Values[q17] = x_ExplicitVarSizeWithDummy[q15] + | q17 : int(1..3)]) + | q15 : int(1..3)]), + sum([toInt(x_Occurrence[q18]) | q18 : int(1..4)]) <= 3, + and([x_Occurrence[q19] -> + or([x_ExplicitVarSizeWithDummy[q21] != 5 /\ x_ExplicitVarSizeWithDummy[q21] = q19 | q21 : int(1..3)]) + | q19 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q23] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q23]] | q23 : int(1..3)]), + and([x_Occurrence[q24] -> + or([x_ExplicitVarSizeWithFlags_Flags[q26] /\ x_ExplicitVarSizeWithFlags_Values[q26] = q24 | q26 : int(1..3)]) + | q24 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q28] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q28]] + | q28 : int(1..3)]) + diff --git a/tests/exhaustive/basic/set05/expected/model_2_4_2-solution000001.solution b/tests/exhaustive/basic/set05/expected/model_2_4_2-solution000001.solution new file mode 100644 index 0000000000..f90e0ba18c --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_2_4_2-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2} diff --git a/tests/exhaustive/basic/set05/expected/model_2_4_2-solution000002.solution b/tests/exhaustive/basic/set05/expected/model_2_4_2-solution000002.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_2_4_2-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set05/expected/model_2_4_2-solution000003.solution b/tests/exhaustive/basic/set05/expected/model_2_4_2-solution000003.solution new file mode 100644 index 0000000000..fdc0f02f96 --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_2_4_2-solution000003.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 4} diff --git a/tests/exhaustive/basic/set05/expected/model_2_4_2.eprime b/tests/exhaustive/basic/set05/expected/model_2_4_2.eprime new file mode 100644 index 0000000000..c9dd09c7ea --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_2_4_2.eprime @@ -0,0 +1,30 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..3)] of int(1..5) +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..3)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3)] of int(1..4) +branching on [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy] +such that + or([x_ExplicitVarSizeWithDummy[q19] != 5 /\ x_ExplicitVarSizeWithDummy[q19] = 1 | q19 : int(1..3)]), + or([x_ExplicitVarSizeWithFlags_Flags[q21] /\ x_ExplicitVarSizeWithFlags_Values[q21] = 2 | q21 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 5 + | q1 : int(1..2)]), + and([x_ExplicitVarSizeWithDummy[q2] = 5 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..2)]), + sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 5) | q3 : int(1..3)]) <= 3, + and([x_ExplicitVarSizeWithFlags_Flags[q5 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q5] < x_ExplicitVarSizeWithFlags_Values[q5 + 1] + | q5 : int(1..2)]), + and([x_ExplicitVarSizeWithFlags_Flags[q6] = false -> x_ExplicitVarSizeWithFlags_Values[q6] = 1 | q6 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q7] | q7 : int(1..2)]), + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q8]) | q8 : int(1..3)]) <= 3, + and([x_ExplicitVarSizeWithFlags_Flags[q11] -> + or([x_ExplicitVarSizeWithDummy[q13] != 5 /\ + x_ExplicitVarSizeWithDummy[q13] = x_ExplicitVarSizeWithFlags_Values[q11] + | q13 : int(1..3)]) + | q11 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q15] != 5 -> + or([x_ExplicitVarSizeWithFlags_Flags[q17] /\ + x_ExplicitVarSizeWithFlags_Values[q17] = x_ExplicitVarSizeWithDummy[q15] + | q17 : int(1..3)]) + | q15 : int(1..3)]) + diff --git a/tests/exhaustive/basic/set05/expected/model_2_4_3-solution000001.solution b/tests/exhaustive/basic/set05/expected/model_2_4_3-solution000001.solution new file mode 100644 index 0000000000..f90e0ba18c --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_2_4_3-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2} diff --git a/tests/exhaustive/basic/set05/expected/model_2_4_3-solution000002.solution b/tests/exhaustive/basic/set05/expected/model_2_4_3-solution000002.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_2_4_3-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set05/expected/model_2_4_3-solution000003.solution b/tests/exhaustive/basic/set05/expected/model_2_4_3-solution000003.solution new file mode 100644 index 0000000000..fdc0f02f96 --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_2_4_3-solution000003.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 4} diff --git a/tests/exhaustive/basic/set05/expected/model_2_4_3.eprime b/tests/exhaustive/basic/set05/expected/model_2_4_3.eprime new file mode 100644 index 0000000000..b649797fe9 --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_2_4_3.eprime @@ -0,0 +1,59 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..3)] of int(1..5) +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..3)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3)] of int(1..4) +find x_ExplicitVarSizeWithMarker_Marker: int(0..3) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3)] of int(1..4) +branching on + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy, + x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] +such that + or([x_ExplicitVarSizeWithDummy[q38] != 5 /\ x_ExplicitVarSizeWithDummy[q38] = 1 | q38 : int(1..3)]), + or([x_ExplicitVarSizeWithFlags_Flags[q40] /\ x_ExplicitVarSizeWithFlags_Values[q40] = 2 | q40 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 5 + | q1 : int(1..2)]), + and([x_ExplicitVarSizeWithDummy[q2] = 5 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..2)]), + sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 5) | q3 : int(1..3)]) <= 3, + and([x_ExplicitVarSizeWithFlags_Flags[q5 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q5] < x_ExplicitVarSizeWithFlags_Values[q5 + 1] + | q5 : int(1..2)]), + and([x_ExplicitVarSizeWithFlags_Flags[q6] = false -> x_ExplicitVarSizeWithFlags_Values[q6] = 1 | q6 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q7] | q7 : int(1..2)]), + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q8]) | q8 : int(1..3)]) <= 3, + and([x_ExplicitVarSizeWithFlags_Flags[q11] -> + or([x_ExplicitVarSizeWithDummy[q13] != 5 /\ + x_ExplicitVarSizeWithDummy[q13] = x_ExplicitVarSizeWithFlags_Values[q11] + | q13 : int(1..3)]) + | q11 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q15] != 5 -> + or([x_ExplicitVarSizeWithFlags_Flags[q17] /\ + x_ExplicitVarSizeWithFlags_Values[q17] = x_ExplicitVarSizeWithDummy[q15] + | q17 : int(1..3)]) + | q15 : int(1..3)]), + and([q18 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q18] < x_ExplicitVarSizeWithMarker_Values[q18 + 1] + | q18 : int(1..2)]), + and([q19 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q19] = 1 | q19 : int(1..3)]), + x_ExplicitVarSizeWithMarker_Marker <= 3, + and([q22 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithDummy[q24] != 5 /\ + x_ExplicitVarSizeWithDummy[q24] = x_ExplicitVarSizeWithMarker_Values[q22] + | q24 : int(1..3)]) + | q22 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q26] != 5 -> + or([q28 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q28] = x_ExplicitVarSizeWithDummy[q26] + | q28 : int(1..3)]) + | q26 : int(1..3)]), + and([q30 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithFlags_Flags[q32] /\ + x_ExplicitVarSizeWithFlags_Values[q32] = x_ExplicitVarSizeWithMarker_Values[q30] + | q32 : int(1..3)]) + | q30 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q34] -> + or([q36 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q36] = x_ExplicitVarSizeWithFlags_Values[q34] + | q36 : int(1..3)]) + | q34 : int(1..3)]) + diff --git a/tests/exhaustive/basic/set05/expected/model_3_1_1-solution000001.solution b/tests/exhaustive/basic/set05/expected/model_3_1_1-solution000001.solution new file mode 100644 index 0000000000..f90e0ba18c --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_3_1_1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2} diff --git a/tests/exhaustive/basic/set05/expected/model_3_1_1-solution000002.solution b/tests/exhaustive/basic/set05/expected/model_3_1_1-solution000002.solution new file mode 100644 index 0000000000..fdc0f02f96 --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_3_1_1-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 4} diff --git a/tests/exhaustive/basic/set05/expected/model_3_1_1-solution000003.solution b/tests/exhaustive/basic/set05/expected/model_3_1_1-solution000003.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_3_1_1-solution000003.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set05/expected/model_3_1_1.eprime b/tests/exhaustive/basic/set05/expected/model_3_1_1.eprime new file mode 100644 index 0000000000..18b6d63112 --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_3_1_1.eprime @@ -0,0 +1,21 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..3) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3)] of int(1..4) +find x_Occurrence: matrix indexed by [int(1..4)] of bool +branching on [x_Occurrence, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] +such that + or([q11 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q11] = 1 | q11 : int(1..3)]), + x_Occurrence[2], + and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] + | q1 : int(1..2)]), + and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..3)]), + x_ExplicitVarSizeWithMarker_Marker <= 3, + sum([toInt(x_Occurrence[q4]) | q4 : int(1..4)]) <= 3, + and([x_Occurrence[q5] -> + or([q7 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q7] = q5 | q7 : int(1..3)]) + | q5 : int(1..4)]), + and([q9 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q9]] + | q9 : int(1..3)]) + diff --git a/tests/exhaustive/basic/set05/expected/model_3_1_2-solution000001.solution b/tests/exhaustive/basic/set05/expected/model_3_1_2-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_3_1_2-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set05/expected/model_3_1_2-solution000002.solution b/tests/exhaustive/basic/set05/expected/model_3_1_2-solution000002.solution new file mode 100644 index 0000000000..fdc0f02f96 --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_3_1_2-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 4} diff --git a/tests/exhaustive/basic/set05/expected/model_3_1_2-solution000003.solution b/tests/exhaustive/basic/set05/expected/model_3_1_2-solution000003.solution new file mode 100644 index 0000000000..f90e0ba18c --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_3_1_2-solution000003.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2} diff --git a/tests/exhaustive/basic/set05/expected/model_3_1_2.eprime b/tests/exhaustive/basic/set05/expected/model_3_1_2.eprime new file mode 100644 index 0000000000..56c03f8d80 --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_3_1_2.eprime @@ -0,0 +1,42 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..3) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3)] of int(1..4) +find x_Occurrence: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..3)] of int(1..5) +branching on + [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_Occurrence] +such that + or([q28 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q28] = 1 | q28 : int(1..3)]), + x_Occurrence[2], + and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] + | q1 : int(1..2)]), + and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..3)]), + x_ExplicitVarSizeWithMarker_Marker <= 3, + sum([toInt(x_Occurrence[q4]) | q4 : int(1..4)]) <= 3, + and([x_Occurrence[q22] -> + or([q24 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q24] = q22 + | q24 : int(1..3)]) + | q22 : int(1..4)]), + and([q26 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q26]] + | q26 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q5] < x_ExplicitVarSizeWithDummy[q5 + 1] \/ x_ExplicitVarSizeWithDummy[q5] = 5 + | q5 : int(1..2)]), + and([x_ExplicitVarSizeWithDummy[q6] = 5 -> x_ExplicitVarSizeWithDummy[q6 + 1] = 5 | q6 : int(1..2)]), + sum([toInt(x_ExplicitVarSizeWithDummy[q7] != 5) | q7 : int(1..3)]) <= 3, + and([x_ExplicitVarSizeWithDummy[q10] != 5 -> + or([q12 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q12] = x_ExplicitVarSizeWithDummy[q10] + | q12 : int(1..3)]) + | q10 : int(1..3)]), + and([q14 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithDummy[q16] != 5 /\ + x_ExplicitVarSizeWithDummy[q16] = x_ExplicitVarSizeWithMarker_Values[q14] + | q16 : int(1..3)]) + | q14 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q18] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q18]] | q18 : int(1..3)]), + and([x_Occurrence[q19] -> + or([x_ExplicitVarSizeWithDummy[q21] != 5 /\ x_ExplicitVarSizeWithDummy[q21] = q19 | q21 : int(1..3)]) + | q19 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set05/expected/model_3_1_4-solution000001.solution b/tests/exhaustive/basic/set05/expected/model_3_1_4-solution000001.solution new file mode 100644 index 0000000000..f90e0ba18c --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_3_1_4-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2} diff --git a/tests/exhaustive/basic/set05/expected/model_3_1_4-solution000002.solution b/tests/exhaustive/basic/set05/expected/model_3_1_4-solution000002.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_3_1_4-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set05/expected/model_3_1_4-solution000003.solution b/tests/exhaustive/basic/set05/expected/model_3_1_4-solution000003.solution new file mode 100644 index 0000000000..fdc0f02f96 --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_3_1_4-solution000003.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 4} diff --git a/tests/exhaustive/basic/set05/expected/model_3_1_4.eprime b/tests/exhaustive/basic/set05/expected/model_3_1_4.eprime new file mode 100644 index 0000000000..742dd902aa --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_3_1_4.eprime @@ -0,0 +1,47 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..3) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3)] of int(1..4) +find x_Occurrence: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..3)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3)] of int(1..4) +branching on + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithMarker_Marker, + x_ExplicitVarSizeWithMarker_Values, x_Occurrence] +such that + or([q29 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q29] = 1 | q29 : int(1..3)]), + x_Occurrence[2], + and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] + | q1 : int(1..2)]), + and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..3)]), + x_ExplicitVarSizeWithMarker_Marker <= 3, + sum([toInt(x_Occurrence[q4]) | q4 : int(1..4)]) <= 3, + and([x_Occurrence[q23] -> + or([q25 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q25] = q23 + | q25 : int(1..3)]) + | q23 : int(1..4)]), + and([q27 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q27]] + | q27 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q5 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q5] < x_ExplicitVarSizeWithFlags_Values[q5 + 1] + | q5 : int(1..2)]), + and([x_ExplicitVarSizeWithFlags_Flags[q6] = false -> x_ExplicitVarSizeWithFlags_Values[q6] = 1 | q6 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q7] | q7 : int(1..2)]), + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q8]) | q8 : int(1..3)]) <= 3, + and([x_ExplicitVarSizeWithFlags_Flags[q11] -> + or([q13 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q13] = x_ExplicitVarSizeWithFlags_Values[q11] + | q13 : int(1..3)]) + | q11 : int(1..3)]), + and([q15 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithFlags_Flags[q17] /\ + x_ExplicitVarSizeWithFlags_Values[q17] = x_ExplicitVarSizeWithMarker_Values[q15] + | q17 : int(1..3)]) + | q15 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q19] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q19]] + | q19 : int(1..3)]), + and([x_Occurrence[q20] -> + or([x_ExplicitVarSizeWithFlags_Flags[q22] /\ x_ExplicitVarSizeWithFlags_Values[q22] = q20 | q22 : int(1..3)]) + | q20 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set05/expected/model_3_2_1-solution000001.solution b/tests/exhaustive/basic/set05/expected/model_3_2_1-solution000001.solution new file mode 100644 index 0000000000..f90e0ba18c --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_3_2_1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2} diff --git a/tests/exhaustive/basic/set05/expected/model_3_2_1-solution000002.solution b/tests/exhaustive/basic/set05/expected/model_3_2_1-solution000002.solution new file mode 100644 index 0000000000..fdc0f02f96 --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_3_2_1-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 4} diff --git a/tests/exhaustive/basic/set05/expected/model_3_2_1-solution000003.solution b/tests/exhaustive/basic/set05/expected/model_3_2_1-solution000003.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_3_2_1-solution000003.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set05/expected/model_3_2_1.eprime b/tests/exhaustive/basic/set05/expected/model_3_2_1.eprime new file mode 100644 index 0000000000..4d541e34ee --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_3_2_1.eprime @@ -0,0 +1,42 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..3) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3)] of int(1..4) +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..3)] of int(1..5) +find x_Occurrence: matrix indexed by [int(1..4)] of bool +branching on + [x_Occurrence, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy] +such that + or([q28 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q28] = 1 | q28 : int(1..3)]), + or([x_ExplicitVarSizeWithDummy[q30] != 5 /\ x_ExplicitVarSizeWithDummy[q30] = 2 | q30 : int(1..3)]), + and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] + | q1 : int(1..2)]), + and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..3)]), + x_ExplicitVarSizeWithMarker_Marker <= 3, + and([x_ExplicitVarSizeWithDummy[q4] < x_ExplicitVarSizeWithDummy[q4 + 1] \/ x_ExplicitVarSizeWithDummy[q4] = 5 + | q4 : int(1..2)]), + and([x_ExplicitVarSizeWithDummy[q5] = 5 -> x_ExplicitVarSizeWithDummy[q5 + 1] = 5 | q5 : int(1..2)]), + sum([toInt(x_ExplicitVarSizeWithDummy[q6] != 5) | q6 : int(1..3)]) <= 3, + and([x_ExplicitVarSizeWithDummy[q9] != 5 -> + or([q11 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q11] = x_ExplicitVarSizeWithDummy[q9] + | q11 : int(1..3)]) + | q9 : int(1..3)]), + and([q13 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithDummy[q15] != 5 /\ + x_ExplicitVarSizeWithDummy[q15] = x_ExplicitVarSizeWithMarker_Values[q13] + | q15 : int(1..3)]) + | q13 : int(1..3)]), + sum([toInt(x_Occurrence[q16]) | q16 : int(1..4)]) <= 3, + and([x_Occurrence[q17] -> + or([q19 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q19] = q17 + | q19 : int(1..3)]) + | q17 : int(1..4)]), + and([q21 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q21]] + | q21 : int(1..3)]), + and([x_Occurrence[q22] -> + or([x_ExplicitVarSizeWithDummy[q24] != 5 /\ x_ExplicitVarSizeWithDummy[q24] = q22 | q24 : int(1..3)]) + | q22 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q26] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q26]] | q26 : int(1..3)]) + diff --git a/tests/exhaustive/basic/set05/expected/model_3_2_2-solution000001.solution b/tests/exhaustive/basic/set05/expected/model_3_2_2-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_3_2_2-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set05/expected/model_3_2_2-solution000002.solution b/tests/exhaustive/basic/set05/expected/model_3_2_2-solution000002.solution new file mode 100644 index 0000000000..fdc0f02f96 --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_3_2_2-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 4} diff --git a/tests/exhaustive/basic/set05/expected/model_3_2_2-solution000003.solution b/tests/exhaustive/basic/set05/expected/model_3_2_2-solution000003.solution new file mode 100644 index 0000000000..f90e0ba18c --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_3_2_2-solution000003.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_3_2.eprime.orig b/tests/exhaustive/basic/set05/expected/model_3_2_2.eprime similarity index 55% rename from tests/exhaustive/basic/cut_01_on/expected/model_3_3_2.eprime.orig rename to tests/exhaustive/basic/set05/expected/model_3_2_2.eprime index 342b5ec1dc..aff63a4eef 100644 --- a/tests/exhaustive/basic/cut_01_on/expected/model_3_3_2.eprime.orig +++ b/tests/exhaustive/basic/set05/expected/model_3_2_2.eprime @@ -1,32 +1,28 @@ language ESSENCE' 1.0 find x_ExplicitVarSizeWithMarker_Marker: int(0..3) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3)] of int(1..3) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..3)] of int(1..4) -find cut1: bool -find cut2: bool -branching on - [cut1, cut2, x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3)] of int(1..4) +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..3)] of int(1..5) +branching on [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] such that - !cut1 <-> - or([q18 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q18] = 1 | q18 : int(1..3)]) /\ - or([q20 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q20] = 2 | q20 : int(1..3)]), - !cut2 <-> - or([q22 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q22] = 1 | q22 : int(1..3)]), + or([q17 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q17] = 1 | q17 : int(1..3)]), + or([x_ExplicitVarSizeWithDummy[q19] != 5 /\ x_ExplicitVarSizeWithDummy[q19] = 2 | q19 : int(1..3)]), and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] | q1 : int(1..2)]), and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..3)]), - and([x_ExplicitVarSizeWithDummy[q4] < x_ExplicitVarSizeWithDummy[q4 + 1] \/ x_ExplicitVarSizeWithDummy[q4] = 4 + x_ExplicitVarSizeWithMarker_Marker <= 3, + and([x_ExplicitVarSizeWithDummy[q4] < x_ExplicitVarSizeWithDummy[q4 + 1] \/ x_ExplicitVarSizeWithDummy[q4] = 5 | q4 : int(1..2)]), - and([x_ExplicitVarSizeWithDummy[q5] = 4 -> x_ExplicitVarSizeWithDummy[q5 + 1] = 4 | q5 : int(1..2)]), - and([x_ExplicitVarSizeWithDummy[q9] != 4 -> + and([x_ExplicitVarSizeWithDummy[q5] = 5 -> x_ExplicitVarSizeWithDummy[q5 + 1] = 5 | q5 : int(1..2)]), + sum([toInt(x_ExplicitVarSizeWithDummy[q6] != 5) | q6 : int(1..3)]) <= 3, + and([x_ExplicitVarSizeWithDummy[q9] != 5 -> or([q11 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q11] = x_ExplicitVarSizeWithDummy[q9] | q11 : int(1..3)]) | q9 : int(1..3)]), and([q13 <= x_ExplicitVarSizeWithMarker_Marker -> - or([x_ExplicitVarSizeWithDummy[q15] != 4 /\ + or([x_ExplicitVarSizeWithDummy[q15] != 5 /\ x_ExplicitVarSizeWithDummy[q15] = x_ExplicitVarSizeWithMarker_Values[q13] | q15 : int(1..3)]) | q13 : int(1..3)]) diff --git a/tests/exhaustive/basic/set05/expected/model_3_2_4-solution000001.solution b/tests/exhaustive/basic/set05/expected/model_3_2_4-solution000001.solution new file mode 100644 index 0000000000..f90e0ba18c --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_3_2_4-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2} diff --git a/tests/exhaustive/basic/set05/expected/model_3_2_4-solution000002.solution b/tests/exhaustive/basic/set05/expected/model_3_2_4-solution000002.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_3_2_4-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set05/expected/model_3_2_4-solution000003.solution b/tests/exhaustive/basic/set05/expected/model_3_2_4-solution000003.solution new file mode 100644 index 0000000000..fdc0f02f96 --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_3_2_4-solution000003.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 4} diff --git a/tests/exhaustive/basic/set05/expected/model_3_2_4.eprime b/tests/exhaustive/basic/set05/expected/model_3_2_4.eprime new file mode 100644 index 0000000000..ca17b6551d --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_3_2_4.eprime @@ -0,0 +1,60 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..3) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3)] of int(1..4) +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..3)] of int(1..5) +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..3)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3)] of int(1..4) +branching on + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithMarker_Marker, + x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy] +such that + or([q38 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q38] = 1 | q38 : int(1..3)]), + or([x_ExplicitVarSizeWithDummy[q40] != 5 /\ x_ExplicitVarSizeWithDummy[q40] = 2 | q40 : int(1..3)]), + and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] + | q1 : int(1..2)]), + and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..3)]), + x_ExplicitVarSizeWithMarker_Marker <= 3, + and([x_ExplicitVarSizeWithDummy[q4] < x_ExplicitVarSizeWithDummy[q4 + 1] \/ x_ExplicitVarSizeWithDummy[q4] = 5 + | q4 : int(1..2)]), + and([x_ExplicitVarSizeWithDummy[q5] = 5 -> x_ExplicitVarSizeWithDummy[q5 + 1] = 5 | q5 : int(1..2)]), + sum([toInt(x_ExplicitVarSizeWithDummy[q6] != 5) | q6 : int(1..3)]) <= 3, + and([x_ExplicitVarSizeWithDummy[q9] != 5 -> + or([q11 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q11] = x_ExplicitVarSizeWithDummy[q9] + | q11 : int(1..3)]) + | q9 : int(1..3)]), + and([q13 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithDummy[q15] != 5 /\ + x_ExplicitVarSizeWithDummy[q15] = x_ExplicitVarSizeWithMarker_Values[q13] + | q15 : int(1..3)]) + | q13 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q16 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q16] < x_ExplicitVarSizeWithFlags_Values[q16 + 1] + | q16 : int(1..2)]), + and([x_ExplicitVarSizeWithFlags_Flags[q17] = false -> x_ExplicitVarSizeWithFlags_Values[q17] = 1 + | q17 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q18 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q18] | q18 : int(1..2)]), + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q19]) | q19 : int(1..3)]) <= 3, + and([x_ExplicitVarSizeWithFlags_Flags[q22] -> + or([q24 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q24] = x_ExplicitVarSizeWithFlags_Values[q22] + | q24 : int(1..3)]) + | q22 : int(1..3)]), + and([q26 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithFlags_Flags[q28] /\ + x_ExplicitVarSizeWithFlags_Values[q28] = x_ExplicitVarSizeWithMarker_Values[q26] + | q28 : int(1..3)]) + | q26 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q30] -> + or([x_ExplicitVarSizeWithDummy[q32] != 5 /\ + x_ExplicitVarSizeWithDummy[q32] = x_ExplicitVarSizeWithFlags_Values[q30] + | q32 : int(1..3)]) + | q30 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q34] != 5 -> + or([x_ExplicitVarSizeWithFlags_Flags[q36] /\ + x_ExplicitVarSizeWithFlags_Values[q36] = x_ExplicitVarSizeWithDummy[q34] + | q36 : int(1..3)]) + | q34 : int(1..3)]) + diff --git a/tests/exhaustive/basic/set05/expected/model_3_3_1-solution000001.solution b/tests/exhaustive/basic/set05/expected/model_3_3_1-solution000001.solution new file mode 100644 index 0000000000..f90e0ba18c --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_3_3_1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2} diff --git a/tests/exhaustive/basic/set05/expected/model_3_3_1-solution000002.solution b/tests/exhaustive/basic/set05/expected/model_3_3_1-solution000002.solution new file mode 100644 index 0000000000..fdc0f02f96 --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_3_3_1-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 4} diff --git a/tests/exhaustive/basic/set05/expected/model_3_3_1-solution000003.solution b/tests/exhaustive/basic/set05/expected/model_3_3_1-solution000003.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_3_3_1-solution000003.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set05/expected/model_3_3_1.eprime b/tests/exhaustive/basic/set05/expected/model_3_3_1.eprime new file mode 100644 index 0000000000..5def062aca --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_3_3_1.eprime @@ -0,0 +1,21 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..3) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3)] of int(1..4) +find x_Occurrence: matrix indexed by [int(1..4)] of bool +branching on [x_Occurrence, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] +such that + or([q11 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q11] = 1 | q11 : int(1..3)]), + or([q13 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q13] = 2 | q13 : int(1..3)]), + and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] + | q1 : int(1..2)]), + and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..3)]), + x_ExplicitVarSizeWithMarker_Marker <= 3, + sum([toInt(x_Occurrence[q4]) | q4 : int(1..4)]) <= 3, + and([x_Occurrence[q5] -> + or([q7 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q7] = q5 | q7 : int(1..3)]) + | q5 : int(1..4)]), + and([q9 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q9]] + | q9 : int(1..3)]) + diff --git a/tests/exhaustive/basic/set05/expected/model_3_3_2-solution000001.solution b/tests/exhaustive/basic/set05/expected/model_3_3_2-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_3_3_2-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set05/expected/model_3_3_2-solution000002.solution b/tests/exhaustive/basic/set05/expected/model_3_3_2-solution000002.solution new file mode 100644 index 0000000000..fdc0f02f96 --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_3_3_2-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 4} diff --git a/tests/exhaustive/basic/set05/expected/model_3_3_2-solution000003.solution b/tests/exhaustive/basic/set05/expected/model_3_3_2-solution000003.solution new file mode 100644 index 0000000000..f90e0ba18c --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_3_3_2-solution000003.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2} diff --git a/tests/exhaustive/basic/set05/expected/model_3_3_2.eprime b/tests/exhaustive/basic/set05/expected/model_3_3_2.eprime new file mode 100644 index 0000000000..c7e4092e7b --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_3_3_2.eprime @@ -0,0 +1,29 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..3) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3)] of int(1..4) +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..3)] of int(1..5) +branching on [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] +such that + or([q17 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q17] = 1 | q17 : int(1..3)]), + or([q19 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q19] = 2 | q19 : int(1..3)]), + and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] + | q1 : int(1..2)]), + and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..3)]), + x_ExplicitVarSizeWithMarker_Marker <= 3, + and([x_ExplicitVarSizeWithDummy[q4] < x_ExplicitVarSizeWithDummy[q4 + 1] \/ x_ExplicitVarSizeWithDummy[q4] = 5 + | q4 : int(1..2)]), + and([x_ExplicitVarSizeWithDummy[q5] = 5 -> x_ExplicitVarSizeWithDummy[q5 + 1] = 5 | q5 : int(1..2)]), + sum([toInt(x_ExplicitVarSizeWithDummy[q6] != 5) | q6 : int(1..3)]) <= 3, + and([x_ExplicitVarSizeWithDummy[q9] != 5 -> + or([q11 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q11] = x_ExplicitVarSizeWithDummy[q9] + | q11 : int(1..3)]) + | q9 : int(1..3)]), + and([q13 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithDummy[q15] != 5 /\ + x_ExplicitVarSizeWithDummy[q15] = x_ExplicitVarSizeWithMarker_Values[q13] + | q15 : int(1..3)]) + | q13 : int(1..3)]) + diff --git a/tests/exhaustive/basic/set05/expected/model_3_3_3-solution000001.solution b/tests/exhaustive/basic/set05/expected/model_3_3_3-solution000001.solution new file mode 100644 index 0000000000..f90e0ba18c --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_3_3_3-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2} diff --git a/tests/exhaustive/basic/set05/expected/model_3_3_3-solution000002.solution b/tests/exhaustive/basic/set05/expected/model_3_3_3-solution000002.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_3_3_3-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set05/expected/model_3_3_3-solution000003.solution b/tests/exhaustive/basic/set05/expected/model_3_3_3-solution000003.solution new file mode 100644 index 0000000000..fdc0f02f96 --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_3_3_3-solution000003.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 4} diff --git a/tests/exhaustive/basic/set05/expected/model_3_3_3.eprime b/tests/exhaustive/basic/set05/expected/model_3_3_3.eprime new file mode 100644 index 0000000000..30415d39e4 --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_3_3_3.eprime @@ -0,0 +1,14 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..3) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3)] of int(1..4) +branching on [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] +such that + or([q5 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q5] = 1 | q5 : int(1..3)]), + or([q7 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q7] = 2 | q7 : int(1..3)]), + and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] + | q1 : int(1..2)]), + and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..3)]), + x_ExplicitVarSizeWithMarker_Marker <= 3 + diff --git a/tests/exhaustive/basic/set05/expected/model_3_3_4-solution000001.solution b/tests/exhaustive/basic/set05/expected/model_3_3_4-solution000001.solution new file mode 100644 index 0000000000..f90e0ba18c --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_3_3_4-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2} diff --git a/tests/exhaustive/basic/set05/expected/model_3_3_4-solution000002.solution b/tests/exhaustive/basic/set05/expected/model_3_3_4-solution000002.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_3_3_4-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set05/expected/model_3_3_4-solution000003.solution b/tests/exhaustive/basic/set05/expected/model_3_3_4-solution000003.solution new file mode 100644 index 0000000000..fdc0f02f96 --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_3_3_4-solution000003.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 4} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_3_3_4.eprime.orig b/tests/exhaustive/basic/set05/expected/model_3_3_4.eprime similarity index 71% rename from tests/exhaustive/basic/cut_01_on/expected/model_3_3_4.eprime.orig rename to tests/exhaustive/basic/set05/expected/model_3_3_4.eprime index adccf8a668..5a6f8f4a1f 100644 --- a/tests/exhaustive/basic/cut_01_on/expected/model_3_3_4.eprime.orig +++ b/tests/exhaustive/basic/set05/expected/model_3_3_4.eprime @@ -1,29 +1,26 @@ language ESSENCE' 1.0 find x_ExplicitVarSizeWithMarker_Marker: int(0..3) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3)] of int(1..3) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3)] of int(1..4) find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..3)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3)] of int(1..3) -find cut1: bool -find cut2: bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3)] of int(1..4) branching on - [cut1, cut2, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, - x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithMarker_Marker, + x_ExplicitVarSizeWithMarker_Values] such that - !cut1 <-> - or([q19 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q19] = 1 | q19 : int(1..3)]) /\ - or([q21 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q21] = 2 | q21 : int(1..3)]), - !cut2 <-> - or([q23 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q23] = 1 | q23 : int(1..3)]), + or([q18 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q18] = 1 | q18 : int(1..3)]), + or([q20 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q20] = 2 | q20 : int(1..3)]), and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] | q1 : int(1..2)]), and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..3)]), + x_ExplicitVarSizeWithMarker_Marker <= 3, and([x_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> x_ExplicitVarSizeWithFlags_Values[q4] < x_ExplicitVarSizeWithFlags_Values[q4 + 1] | q4 : int(1..2)]), and([x_ExplicitVarSizeWithFlags_Flags[q5] = false -> x_ExplicitVarSizeWithFlags_Values[q5] = 1 | q5 : int(1..3)]), and([x_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q6] | q6 : int(1..2)]), + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q7]) | q7 : int(1..3)]) <= 3, and([x_ExplicitVarSizeWithFlags_Flags[q10] -> or([q12 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q12] = x_ExplicitVarSizeWithFlags_Values[q10] diff --git a/tests/exhaustive/basic/set05/expected/model_3_4_1-solution000001.solution b/tests/exhaustive/basic/set05/expected/model_3_4_1-solution000001.solution new file mode 100644 index 0000000000..f90e0ba18c --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_3_4_1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2} diff --git a/tests/exhaustive/basic/set05/expected/model_3_4_1-solution000002.solution b/tests/exhaustive/basic/set05/expected/model_3_4_1-solution000002.solution new file mode 100644 index 0000000000..fdc0f02f96 --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_3_4_1-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 4} diff --git a/tests/exhaustive/basic/set05/expected/model_3_4_1-solution000003.solution b/tests/exhaustive/basic/set05/expected/model_3_4_1-solution000003.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_3_4_1-solution000003.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set05/expected/model_3_4_1.eprime b/tests/exhaustive/basic/set05/expected/model_3_4_1.eprime new file mode 100644 index 0000000000..8aebac7513 --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_3_4_1.eprime @@ -0,0 +1,47 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..3) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3)] of int(1..4) +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..3)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3)] of int(1..4) +find x_Occurrence: matrix indexed by [int(1..4)] of bool +branching on + [x_Occurrence, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, + x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] +such that + or([q29 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q29] = 1 | q29 : int(1..3)]), + or([x_ExplicitVarSizeWithFlags_Flags[q31] /\ x_ExplicitVarSizeWithFlags_Values[q31] = 2 | q31 : int(1..3)]), + and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] + | q1 : int(1..2)]), + and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..3)]), + x_ExplicitVarSizeWithMarker_Marker <= 3, + and([x_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q4] < x_ExplicitVarSizeWithFlags_Values[q4 + 1] + | q4 : int(1..2)]), + and([x_ExplicitVarSizeWithFlags_Flags[q5] = false -> x_ExplicitVarSizeWithFlags_Values[q5] = 1 | q5 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q6] | q6 : int(1..2)]), + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q7]) | q7 : int(1..3)]) <= 3, + and([x_ExplicitVarSizeWithFlags_Flags[q10] -> + or([q12 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q12] = x_ExplicitVarSizeWithFlags_Values[q10] + | q12 : int(1..3)]) + | q10 : int(1..3)]), + and([q14 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithFlags_Flags[q16] /\ + x_ExplicitVarSizeWithFlags_Values[q16] = x_ExplicitVarSizeWithMarker_Values[q14] + | q16 : int(1..3)]) + | q14 : int(1..3)]), + sum([toInt(x_Occurrence[q17]) | q17 : int(1..4)]) <= 3, + and([x_Occurrence[q18] -> + or([q20 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q20] = q18 + | q20 : int(1..3)]) + | q18 : int(1..4)]), + and([q22 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q22]] + | q22 : int(1..3)]), + and([x_Occurrence[q23] -> + or([x_ExplicitVarSizeWithFlags_Flags[q25] /\ x_ExplicitVarSizeWithFlags_Values[q25] = q23 | q25 : int(1..3)]) + | q23 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q27] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q27]] + | q27 : int(1..3)]) + diff --git a/tests/exhaustive/basic/set05/expected/model_3_4_2-solution000001.solution b/tests/exhaustive/basic/set05/expected/model_3_4_2-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_3_4_2-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set05/expected/model_3_4_2-solution000002.solution b/tests/exhaustive/basic/set05/expected/model_3_4_2-solution000002.solution new file mode 100644 index 0000000000..fdc0f02f96 --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_3_4_2-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 4} diff --git a/tests/exhaustive/basic/set05/expected/model_3_4_2-solution000003.solution b/tests/exhaustive/basic/set05/expected/model_3_4_2-solution000003.solution new file mode 100644 index 0000000000..f90e0ba18c --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_3_4_2-solution000003.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2} diff --git a/tests/exhaustive/basic/set05/expected/model_3_4_2.eprime b/tests/exhaustive/basic/set05/expected/model_3_4_2.eprime new file mode 100644 index 0000000000..5f5f7c970d --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_3_4_2.eprime @@ -0,0 +1,59 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..3) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3)] of int(1..4) +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..3)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3)] of int(1..4) +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..3)] of int(1..5) +branching on + [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, + x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] +such that + or([q38 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q38] = 1 | q38 : int(1..3)]), + or([x_ExplicitVarSizeWithFlags_Flags[q40] /\ x_ExplicitVarSizeWithFlags_Values[q40] = 2 | q40 : int(1..3)]), + and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] + | q1 : int(1..2)]), + and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..3)]), + x_ExplicitVarSizeWithMarker_Marker <= 3, + and([x_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q4] < x_ExplicitVarSizeWithFlags_Values[q4 + 1] + | q4 : int(1..2)]), + and([x_ExplicitVarSizeWithFlags_Flags[q5] = false -> x_ExplicitVarSizeWithFlags_Values[q5] = 1 | q5 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q6] | q6 : int(1..2)]), + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q7]) | q7 : int(1..3)]) <= 3, + and([x_ExplicitVarSizeWithFlags_Flags[q10] -> + or([q12 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q12] = x_ExplicitVarSizeWithFlags_Values[q10] + | q12 : int(1..3)]) + | q10 : int(1..3)]), + and([q14 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithFlags_Flags[q16] /\ + x_ExplicitVarSizeWithFlags_Values[q16] = x_ExplicitVarSizeWithMarker_Values[q14] + | q16 : int(1..3)]) + | q14 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q17] < x_ExplicitVarSizeWithDummy[q17 + 1] \/ x_ExplicitVarSizeWithDummy[q17] = 5 + | q17 : int(1..2)]), + and([x_ExplicitVarSizeWithDummy[q18] = 5 -> x_ExplicitVarSizeWithDummy[q18 + 1] = 5 | q18 : int(1..2)]), + sum([toInt(x_ExplicitVarSizeWithDummy[q19] != 5) | q19 : int(1..3)]) <= 3, + and([x_ExplicitVarSizeWithDummy[q22] != 5 -> + or([q24 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q24] = x_ExplicitVarSizeWithDummy[q22] + | q24 : int(1..3)]) + | q22 : int(1..3)]), + and([q26 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithDummy[q28] != 5 /\ + x_ExplicitVarSizeWithDummy[q28] = x_ExplicitVarSizeWithMarker_Values[q26] + | q28 : int(1..3)]) + | q26 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q30] != 5 -> + or([x_ExplicitVarSizeWithFlags_Flags[q32] /\ + x_ExplicitVarSizeWithFlags_Values[q32] = x_ExplicitVarSizeWithDummy[q30] + | q32 : int(1..3)]) + | q30 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q34] -> + or([x_ExplicitVarSizeWithDummy[q36] != 5 /\ + x_ExplicitVarSizeWithDummy[q36] = x_ExplicitVarSizeWithFlags_Values[q34] + | q36 : int(1..3)]) + | q34 : int(1..3)]) + diff --git a/tests/exhaustive/basic/set05/expected/model_3_4_3-solution000001.solution b/tests/exhaustive/basic/set05/expected/model_3_4_3-solution000001.solution new file mode 100644 index 0000000000..f90e0ba18c --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_3_4_3-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2} diff --git a/tests/exhaustive/basic/set05/expected/model_3_4_3-solution000002.solution b/tests/exhaustive/basic/set05/expected/model_3_4_3-solution000002.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_3_4_3-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set05/expected/model_3_4_3-solution000003.solution b/tests/exhaustive/basic/set05/expected/model_3_4_3-solution000003.solution new file mode 100644 index 0000000000..fdc0f02f96 --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_3_4_3-solution000003.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 4} diff --git a/tests/exhaustive/basic/set05/expected/model_3_4_3.eprime b/tests/exhaustive/basic/set05/expected/model_3_4_3.eprime new file mode 100644 index 0000000000..b29a9e6cdd --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_3_4_3.eprime @@ -0,0 +1,34 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..3) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3)] of int(1..4) +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..3)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3)] of int(1..4) +branching on + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithMarker_Marker, + x_ExplicitVarSizeWithMarker_Values] +such that + or([q18 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q18] = 1 | q18 : int(1..3)]), + or([x_ExplicitVarSizeWithFlags_Flags[q20] /\ x_ExplicitVarSizeWithFlags_Values[q20] = 2 | q20 : int(1..3)]), + and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] + | q1 : int(1..2)]), + and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..3)]), + x_ExplicitVarSizeWithMarker_Marker <= 3, + and([x_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q4] < x_ExplicitVarSizeWithFlags_Values[q4 + 1] + | q4 : int(1..2)]), + and([x_ExplicitVarSizeWithFlags_Flags[q5] = false -> x_ExplicitVarSizeWithFlags_Values[q5] = 1 | q5 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q6] | q6 : int(1..2)]), + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q7]) | q7 : int(1..3)]) <= 3, + and([x_ExplicitVarSizeWithFlags_Flags[q10] -> + or([q12 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q12] = x_ExplicitVarSizeWithFlags_Values[q10] + | q12 : int(1..3)]) + | q10 : int(1..3)]), + and([q14 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithFlags_Flags[q16] /\ + x_ExplicitVarSizeWithFlags_Values[q16] = x_ExplicitVarSizeWithMarker_Values[q14] + | q16 : int(1..3)]) + | q14 : int(1..3)]) + diff --git a/tests/exhaustive/basic/set05/expected/model_4_1_1-solution000001.solution b/tests/exhaustive/basic/set05/expected/model_4_1_1-solution000001.solution new file mode 100644 index 0000000000..f90e0ba18c --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_4_1_1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2} diff --git a/tests/exhaustive/basic/set05/expected/model_4_1_1-solution000002.solution b/tests/exhaustive/basic/set05/expected/model_4_1_1-solution000002.solution new file mode 100644 index 0000000000..fdc0f02f96 --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_4_1_1-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 4} diff --git a/tests/exhaustive/basic/set05/expected/model_4_1_1-solution000003.solution b/tests/exhaustive/basic/set05/expected/model_4_1_1-solution000003.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_4_1_1-solution000003.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_4_1.eprime.orig b/tests/exhaustive/basic/set05/expected/model_4_1_1.eprime similarity index 58% rename from tests/exhaustive/basic/cut_01_on/expected/model_4_4_1.eprime.orig rename to tests/exhaustive/basic/set05/expected/model_4_1_1.eprime index a5e320a159..9358d40bd8 100644 --- a/tests/exhaustive/basic/cut_01_on/expected/model_4_4_1.eprime.orig +++ b/tests/exhaustive/basic/set05/expected/model_4_1_1.eprime @@ -1,25 +1,22 @@ language ESSENCE' 1.0 find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..3)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3)] of int(1..3) -find x_Occurrence: matrix indexed by [int(1..3)] of bool -find cut1: bool -find cut2: bool -branching on [cut1, cut2, x_Occurrence, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3)] of int(1..4) +find x_Occurrence: matrix indexed by [int(1..4)] of bool +branching on [x_Occurrence, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] such that - !cut1 <-> - or([x_ExplicitVarSizeWithFlags_Flags[q14] /\ x_ExplicitVarSizeWithFlags_Values[q14] = 1 | q14 : int(1..3)]) /\ - or([x_ExplicitVarSizeWithFlags_Flags[q16] /\ x_ExplicitVarSizeWithFlags_Values[q16] = 2 | q16 : int(1..3)]), - !cut2 <-> - or([x_ExplicitVarSizeWithFlags_Flags[q18] /\ x_ExplicitVarSizeWithFlags_Values[q18] = 1 | q18 : int(1..3)]), + or([x_ExplicitVarSizeWithFlags_Flags[q13] /\ x_ExplicitVarSizeWithFlags_Values[q13] = 1 | q13 : int(1..3)]), + x_Occurrence[2], and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] | q1 : int(1..2)]), and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..3)]), and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..2)]), + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..3)]) <= 3, + sum([toInt(x_Occurrence[q6]) | q6 : int(1..4)]) <= 3, and([x_Occurrence[q7] -> or([x_ExplicitVarSizeWithFlags_Flags[q9] /\ x_ExplicitVarSizeWithFlags_Values[q9] = q7 | q9 : int(1..3)]) - | q7 : int(1..3)]), + | q7 : int(1..4)]), and([x_ExplicitVarSizeWithFlags_Flags[q11] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q11]] | q11 : int(1..3)]) diff --git a/tests/exhaustive/basic/set05/expected/model_4_1_2-solution000001.solution b/tests/exhaustive/basic/set05/expected/model_4_1_2-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_4_1_2-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set05/expected/model_4_1_2-solution000002.solution b/tests/exhaustive/basic/set05/expected/model_4_1_2-solution000002.solution new file mode 100644 index 0000000000..fdc0f02f96 --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_4_1_2-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 4} diff --git a/tests/exhaustive/basic/set05/expected/model_4_1_2-solution000003.solution b/tests/exhaustive/basic/set05/expected/model_4_1_2-solution000003.solution new file mode 100644 index 0000000000..f90e0ba18c --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_4_1_2-solution000003.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2} diff --git a/tests/exhaustive/basic/set05/expected/model_4_1_2.eprime b/tests/exhaustive/basic/set05/expected/model_4_1_2.eprime new file mode 100644 index 0000000000..d279aa617d --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_4_1_2.eprime @@ -0,0 +1,42 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..3)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3)] of int(1..4) +find x_Occurrence: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..3)] of int(1..5) +branching on + [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_Occurrence] +such that + or([x_ExplicitVarSizeWithFlags_Flags[q30] /\ x_ExplicitVarSizeWithFlags_Values[q30] = 1 | q30 : int(1..3)]), + x_Occurrence[2], + and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] + | q1 : int(1..2)]), + and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..2)]), + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..3)]) <= 3, + sum([toInt(x_Occurrence[q6]) | q6 : int(1..4)]) <= 3, + and([x_Occurrence[q24] -> + or([x_ExplicitVarSizeWithFlags_Flags[q26] /\ x_ExplicitVarSizeWithFlags_Values[q26] = q24 | q26 : int(1..3)]) + | q24 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q28] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q28]] + | q28 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q7] < x_ExplicitVarSizeWithDummy[q7 + 1] \/ x_ExplicitVarSizeWithDummy[q7] = 5 + | q7 : int(1..2)]), + and([x_ExplicitVarSizeWithDummy[q8] = 5 -> x_ExplicitVarSizeWithDummy[q8 + 1] = 5 | q8 : int(1..2)]), + sum([toInt(x_ExplicitVarSizeWithDummy[q9] != 5) | q9 : int(1..3)]) <= 3, + and([x_ExplicitVarSizeWithDummy[q12] != 5 -> + or([x_ExplicitVarSizeWithFlags_Flags[q14] /\ + x_ExplicitVarSizeWithFlags_Values[q14] = x_ExplicitVarSizeWithDummy[q12] + | q14 : int(1..3)]) + | q12 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q16] -> + or([x_ExplicitVarSizeWithDummy[q18] != 5 /\ + x_ExplicitVarSizeWithDummy[q18] = x_ExplicitVarSizeWithFlags_Values[q16] + | q18 : int(1..3)]) + | q16 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q20] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q20]] | q20 : int(1..3)]), + and([x_Occurrence[q21] -> + or([x_ExplicitVarSizeWithDummy[q23] != 5 /\ x_ExplicitVarSizeWithDummy[q23] = q21 | q23 : int(1..3)]) + | q21 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set05/expected/model_4_1_3-solution000001.solution b/tests/exhaustive/basic/set05/expected/model_4_1_3-solution000001.solution new file mode 100644 index 0000000000..f90e0ba18c --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_4_1_3-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2} diff --git a/tests/exhaustive/basic/set05/expected/model_4_1_3-solution000002.solution b/tests/exhaustive/basic/set05/expected/model_4_1_3-solution000002.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_4_1_3-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set05/expected/model_4_1_3-solution000003.solution b/tests/exhaustive/basic/set05/expected/model_4_1_3-solution000003.solution new file mode 100644 index 0000000000..fdc0f02f96 --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_4_1_3-solution000003.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 4} diff --git a/tests/exhaustive/basic/set05/expected/model_4_1_3.eprime b/tests/exhaustive/basic/set05/expected/model_4_1_3.eprime new file mode 100644 index 0000000000..f773f1d64b --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_4_1_3.eprime @@ -0,0 +1,47 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..3)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3)] of int(1..4) +find x_Occurrence: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithMarker_Marker: int(0..3) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3)] of int(1..4) +branching on + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithFlags_Flags, + x_ExplicitVarSizeWithFlags_Values, x_Occurrence] +such that + or([x_ExplicitVarSizeWithFlags_Flags[q29] /\ x_ExplicitVarSizeWithFlags_Values[q29] = 1 | q29 : int(1..3)]), + x_Occurrence[2], + and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] + | q1 : int(1..2)]), + and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..2)]), + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..3)]) <= 3, + sum([toInt(x_Occurrence[q6]) | q6 : int(1..4)]) <= 3, + and([x_Occurrence[q23] -> + or([x_ExplicitVarSizeWithFlags_Flags[q25] /\ x_ExplicitVarSizeWithFlags_Values[q25] = q23 | q25 : int(1..3)]) + | q23 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q27] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q27]] + | q27 : int(1..3)]), + and([q7 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q7] < x_ExplicitVarSizeWithMarker_Values[q7 + 1] + | q7 : int(1..2)]), + and([q8 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q8] = 1 | q8 : int(1..3)]), + x_ExplicitVarSizeWithMarker_Marker <= 3, + and([q11 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithFlags_Flags[q13] /\ + x_ExplicitVarSizeWithFlags_Values[q13] = x_ExplicitVarSizeWithMarker_Values[q11] + | q13 : int(1..3)]) + | q11 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q15] -> + or([q17 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q17] = x_ExplicitVarSizeWithFlags_Values[q15] + | q17 : int(1..3)]) + | q15 : int(1..3)]), + and([q19 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q19]] + | q19 : int(1..3)]), + and([x_Occurrence[q20] -> + or([q22 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q22] = q20 + | q22 : int(1..3)]) + | q20 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set05/expected/model_4_2_1-solution000001.solution b/tests/exhaustive/basic/set05/expected/model_4_2_1-solution000001.solution new file mode 100644 index 0000000000..f90e0ba18c --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_4_2_1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2} diff --git a/tests/exhaustive/basic/set05/expected/model_4_2_1-solution000002.solution b/tests/exhaustive/basic/set05/expected/model_4_2_1-solution000002.solution new file mode 100644 index 0000000000..fdc0f02f96 --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_4_2_1-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 4} diff --git a/tests/exhaustive/basic/set05/expected/model_4_2_1-solution000003.solution b/tests/exhaustive/basic/set05/expected/model_4_2_1-solution000003.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_4_2_1-solution000003.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set05/expected/model_4_2_1.eprime b/tests/exhaustive/basic/set05/expected/model_4_2_1.eprime new file mode 100644 index 0000000000..4459490acf --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_4_2_1.eprime @@ -0,0 +1,42 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..3)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3)] of int(1..4) +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..3)] of int(1..5) +find x_Occurrence: matrix indexed by [int(1..4)] of bool +branching on + [x_Occurrence, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy] +such that + or([x_ExplicitVarSizeWithFlags_Flags[q30] /\ x_ExplicitVarSizeWithFlags_Values[q30] = 1 | q30 : int(1..3)]), + or([x_ExplicitVarSizeWithDummy[q32] != 5 /\ x_ExplicitVarSizeWithDummy[q32] = 2 | q32 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] + | q1 : int(1..2)]), + and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..2)]), + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..3)]) <= 3, + and([x_ExplicitVarSizeWithDummy[q6] < x_ExplicitVarSizeWithDummy[q6 + 1] \/ x_ExplicitVarSizeWithDummy[q6] = 5 + | q6 : int(1..2)]), + and([x_ExplicitVarSizeWithDummy[q7] = 5 -> x_ExplicitVarSizeWithDummy[q7 + 1] = 5 | q7 : int(1..2)]), + sum([toInt(x_ExplicitVarSizeWithDummy[q8] != 5) | q8 : int(1..3)]) <= 3, + and([x_ExplicitVarSizeWithDummy[q11] != 5 -> + or([x_ExplicitVarSizeWithFlags_Flags[q13] /\ + x_ExplicitVarSizeWithFlags_Values[q13] = x_ExplicitVarSizeWithDummy[q11] + | q13 : int(1..3)]) + | q11 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q15] -> + or([x_ExplicitVarSizeWithDummy[q17] != 5 /\ + x_ExplicitVarSizeWithDummy[q17] = x_ExplicitVarSizeWithFlags_Values[q15] + | q17 : int(1..3)]) + | q15 : int(1..3)]), + sum([toInt(x_Occurrence[q18]) | q18 : int(1..4)]) <= 3, + and([x_Occurrence[q19] -> + or([x_ExplicitVarSizeWithFlags_Flags[q21] /\ x_ExplicitVarSizeWithFlags_Values[q21] = q19 | q21 : int(1..3)]) + | q19 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q23] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q23]] + | q23 : int(1..3)]), + and([x_Occurrence[q24] -> + or([x_ExplicitVarSizeWithDummy[q26] != 5 /\ x_ExplicitVarSizeWithDummy[q26] = q24 | q26 : int(1..3)]) + | q24 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q28] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q28]] | q28 : int(1..3)]) + diff --git a/tests/exhaustive/basic/set05/expected/model_4_2_2-solution000001.solution b/tests/exhaustive/basic/set05/expected/model_4_2_2-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_4_2_2-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set05/expected/model_4_2_2-solution000002.solution b/tests/exhaustive/basic/set05/expected/model_4_2_2-solution000002.solution new file mode 100644 index 0000000000..fdc0f02f96 --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_4_2_2-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 4} diff --git a/tests/exhaustive/basic/set05/expected/model_4_2_2-solution000003.solution b/tests/exhaustive/basic/set05/expected/model_4_2_2-solution000003.solution new file mode 100644 index 0000000000..f90e0ba18c --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_4_2_2-solution000003.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_4_2.eprime.orig b/tests/exhaustive/basic/set05/expected/model_4_2_2.eprime similarity index 58% rename from tests/exhaustive/basic/cut_01_on/expected/model_4_4_2.eprime.orig rename to tests/exhaustive/basic/set05/expected/model_4_2_2.eprime index 51f2077d26..1fc3837d42 100644 --- a/tests/exhaustive/basic/cut_01_on/expected/model_4_4_2.eprime.orig +++ b/tests/exhaustive/basic/set05/expected/model_4_2_2.eprime @@ -1,33 +1,29 @@ language ESSENCE' 1.0 find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..3)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3)] of int(1..3) -find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..3)] of int(1..4) -find cut1: bool -find cut2: bool -branching on - [cut1, cut2, x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3)] of int(1..4) +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..3)] of int(1..5) +branching on [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] such that - !cut1 <-> - or([x_ExplicitVarSizeWithFlags_Flags[q20] /\ x_ExplicitVarSizeWithFlags_Values[q20] = 1 | q20 : int(1..3)]) /\ - or([x_ExplicitVarSizeWithFlags_Flags[q22] /\ x_ExplicitVarSizeWithFlags_Values[q22] = 2 | q22 : int(1..3)]), - !cut2 <-> - or([x_ExplicitVarSizeWithFlags_Flags[q24] /\ x_ExplicitVarSizeWithFlags_Values[q24] = 1 | q24 : int(1..3)]), + or([x_ExplicitVarSizeWithFlags_Flags[q19] /\ x_ExplicitVarSizeWithFlags_Values[q19] = 1 | q19 : int(1..3)]), + or([x_ExplicitVarSizeWithDummy[q21] != 5 /\ x_ExplicitVarSizeWithDummy[q21] = 2 | q21 : int(1..3)]), and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] | q1 : int(1..2)]), and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..3)]), and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..2)]), - and([x_ExplicitVarSizeWithDummy[q6] < x_ExplicitVarSizeWithDummy[q6 + 1] \/ x_ExplicitVarSizeWithDummy[q6] = 4 + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..3)]) <= 3, + and([x_ExplicitVarSizeWithDummy[q6] < x_ExplicitVarSizeWithDummy[q6 + 1] \/ x_ExplicitVarSizeWithDummy[q6] = 5 | q6 : int(1..2)]), - and([x_ExplicitVarSizeWithDummy[q7] = 4 -> x_ExplicitVarSizeWithDummy[q7 + 1] = 4 | q7 : int(1..2)]), - and([x_ExplicitVarSizeWithDummy[q11] != 4 -> + and([x_ExplicitVarSizeWithDummy[q7] = 5 -> x_ExplicitVarSizeWithDummy[q7 + 1] = 5 | q7 : int(1..2)]), + sum([toInt(x_ExplicitVarSizeWithDummy[q8] != 5) | q8 : int(1..3)]) <= 3, + and([x_ExplicitVarSizeWithDummy[q11] != 5 -> or([x_ExplicitVarSizeWithFlags_Flags[q13] /\ x_ExplicitVarSizeWithFlags_Values[q13] = x_ExplicitVarSizeWithDummy[q11] | q13 : int(1..3)]) | q11 : int(1..3)]), and([x_ExplicitVarSizeWithFlags_Flags[q15] -> - or([x_ExplicitVarSizeWithDummy[q17] != 4 /\ + or([x_ExplicitVarSizeWithDummy[q17] != 5 /\ x_ExplicitVarSizeWithDummy[q17] = x_ExplicitVarSizeWithFlags_Values[q15] | q17 : int(1..3)]) | q15 : int(1..3)]) diff --git a/tests/exhaustive/basic/set05/expected/model_4_2_3-solution000001.solution b/tests/exhaustive/basic/set05/expected/model_4_2_3-solution000001.solution new file mode 100644 index 0000000000..f90e0ba18c --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_4_2_3-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2} diff --git a/tests/exhaustive/basic/set05/expected/model_4_2_3-solution000002.solution b/tests/exhaustive/basic/set05/expected/model_4_2_3-solution000002.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_4_2_3-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set05/expected/model_4_2_3-solution000003.solution b/tests/exhaustive/basic/set05/expected/model_4_2_3-solution000003.solution new file mode 100644 index 0000000000..fdc0f02f96 --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_4_2_3-solution000003.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 4} diff --git a/tests/exhaustive/basic/set05/expected/model_4_2_3.eprime b/tests/exhaustive/basic/set05/expected/model_4_2_3.eprime new file mode 100644 index 0000000000..e3382d275b --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_4_2_3.eprime @@ -0,0 +1,59 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..3)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3)] of int(1..4) +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..3)] of int(1..5) +find x_ExplicitVarSizeWithMarker_Marker: int(0..3) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3)] of int(1..4) +branching on + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithFlags_Flags, + x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy] +such that + or([x_ExplicitVarSizeWithFlags_Flags[q38] /\ x_ExplicitVarSizeWithFlags_Values[q38] = 1 | q38 : int(1..3)]), + or([x_ExplicitVarSizeWithDummy[q40] != 5 /\ x_ExplicitVarSizeWithDummy[q40] = 2 | q40 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] + | q1 : int(1..2)]), + and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..2)]), + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..3)]) <= 3, + and([x_ExplicitVarSizeWithDummy[q6] < x_ExplicitVarSizeWithDummy[q6 + 1] \/ x_ExplicitVarSizeWithDummy[q6] = 5 + | q6 : int(1..2)]), + and([x_ExplicitVarSizeWithDummy[q7] = 5 -> x_ExplicitVarSizeWithDummy[q7 + 1] = 5 | q7 : int(1..2)]), + sum([toInt(x_ExplicitVarSizeWithDummy[q8] != 5) | q8 : int(1..3)]) <= 3, + and([x_ExplicitVarSizeWithDummy[q11] != 5 -> + or([x_ExplicitVarSizeWithFlags_Flags[q13] /\ + x_ExplicitVarSizeWithFlags_Values[q13] = x_ExplicitVarSizeWithDummy[q11] + | q13 : int(1..3)]) + | q11 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q15] -> + or([x_ExplicitVarSizeWithDummy[q17] != 5 /\ + x_ExplicitVarSizeWithDummy[q17] = x_ExplicitVarSizeWithFlags_Values[q15] + | q17 : int(1..3)]) + | q15 : int(1..3)]), + and([q18 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q18] < x_ExplicitVarSizeWithMarker_Values[q18 + 1] + | q18 : int(1..2)]), + and([q19 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q19] = 1 | q19 : int(1..3)]), + x_ExplicitVarSizeWithMarker_Marker <= 3, + and([q22 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithFlags_Flags[q24] /\ + x_ExplicitVarSizeWithFlags_Values[q24] = x_ExplicitVarSizeWithMarker_Values[q22] + | q24 : int(1..3)]) + | q22 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q26] -> + or([q28 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q28] = x_ExplicitVarSizeWithFlags_Values[q26] + | q28 : int(1..3)]) + | q26 : int(1..3)]), + and([q30 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithDummy[q32] != 5 /\ + x_ExplicitVarSizeWithDummy[q32] = x_ExplicitVarSizeWithMarker_Values[q30] + | q32 : int(1..3)]) + | q30 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q34] != 5 -> + or([q36 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q36] = x_ExplicitVarSizeWithDummy[q34] + | q36 : int(1..3)]) + | q34 : int(1..3)]) + diff --git a/tests/exhaustive/basic/set05/expected/model_4_3_1-solution000001.solution b/tests/exhaustive/basic/set05/expected/model_4_3_1-solution000001.solution new file mode 100644 index 0000000000..f90e0ba18c --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_4_3_1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2} diff --git a/tests/exhaustive/basic/set05/expected/model_4_3_1-solution000002.solution b/tests/exhaustive/basic/set05/expected/model_4_3_1-solution000002.solution new file mode 100644 index 0000000000..fdc0f02f96 --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_4_3_1-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 4} diff --git a/tests/exhaustive/basic/set05/expected/model_4_3_1-solution000003.solution b/tests/exhaustive/basic/set05/expected/model_4_3_1-solution000003.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_4_3_1-solution000003.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set05/expected/model_4_3_1.eprime b/tests/exhaustive/basic/set05/expected/model_4_3_1.eprime new file mode 100644 index 0000000000..1a72db7f80 --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_4_3_1.eprime @@ -0,0 +1,47 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..3)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3)] of int(1..4) +find x_ExplicitVarSizeWithMarker_Marker: int(0..3) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3)] of int(1..4) +find x_Occurrence: matrix indexed by [int(1..4)] of bool +branching on + [x_Occurrence, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, + x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] +such that + or([x_ExplicitVarSizeWithFlags_Flags[q29] /\ x_ExplicitVarSizeWithFlags_Values[q29] = 1 | q29 : int(1..3)]), + or([q31 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q31] = 2 | q31 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] + | q1 : int(1..2)]), + and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..2)]), + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..3)]) <= 3, + and([q6 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q6] < x_ExplicitVarSizeWithMarker_Values[q6 + 1] + | q6 : int(1..2)]), + and([q7 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q7] = 1 | q7 : int(1..3)]), + x_ExplicitVarSizeWithMarker_Marker <= 3, + and([q10 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithFlags_Flags[q12] /\ + x_ExplicitVarSizeWithFlags_Values[q12] = x_ExplicitVarSizeWithMarker_Values[q10] + | q12 : int(1..3)]) + | q10 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q14] -> + or([q16 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q16] = x_ExplicitVarSizeWithFlags_Values[q14] + | q16 : int(1..3)]) + | q14 : int(1..3)]), + sum([toInt(x_Occurrence[q17]) | q17 : int(1..4)]) <= 3, + and([x_Occurrence[q18] -> + or([x_ExplicitVarSizeWithFlags_Flags[q20] /\ x_ExplicitVarSizeWithFlags_Values[q20] = q18 | q20 : int(1..3)]) + | q18 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q22] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q22]] + | q22 : int(1..3)]), + and([x_Occurrence[q23] -> + or([q25 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q25] = q23 + | q25 : int(1..3)]) + | q23 : int(1..4)]), + and([q27 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q27]] + | q27 : int(1..3)]) + diff --git a/tests/exhaustive/basic/set05/expected/model_4_3_2-solution000001.solution b/tests/exhaustive/basic/set05/expected/model_4_3_2-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_4_3_2-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set05/expected/model_4_3_2-solution000002.solution b/tests/exhaustive/basic/set05/expected/model_4_3_2-solution000002.solution new file mode 100644 index 0000000000..fdc0f02f96 --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_4_3_2-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 4} diff --git a/tests/exhaustive/basic/set05/expected/model_4_3_2-solution000003.solution b/tests/exhaustive/basic/set05/expected/model_4_3_2-solution000003.solution new file mode 100644 index 0000000000..f90e0ba18c --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_4_3_2-solution000003.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2} diff --git a/tests/exhaustive/basic/set05/expected/model_4_3_2.eprime b/tests/exhaustive/basic/set05/expected/model_4_3_2.eprime new file mode 100644 index 0000000000..411a506bdc --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_4_3_2.eprime @@ -0,0 +1,59 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..3)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3)] of int(1..4) +find x_ExplicitVarSizeWithMarker_Marker: int(0..3) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3)] of int(1..4) +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..3)] of int(1..5) +branching on + [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, + x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] +such that + or([x_ExplicitVarSizeWithFlags_Flags[q38] /\ x_ExplicitVarSizeWithFlags_Values[q38] = 1 | q38 : int(1..3)]), + or([q40 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q40] = 2 | q40 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] + | q1 : int(1..2)]), + and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..2)]), + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..3)]) <= 3, + and([q6 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q6] < x_ExplicitVarSizeWithMarker_Values[q6 + 1] + | q6 : int(1..2)]), + and([q7 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q7] = 1 | q7 : int(1..3)]), + x_ExplicitVarSizeWithMarker_Marker <= 3, + and([q10 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithFlags_Flags[q12] /\ + x_ExplicitVarSizeWithFlags_Values[q12] = x_ExplicitVarSizeWithMarker_Values[q10] + | q12 : int(1..3)]) + | q10 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q14] -> + or([q16 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q16] = x_ExplicitVarSizeWithFlags_Values[q14] + | q16 : int(1..3)]) + | q14 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q17] < x_ExplicitVarSizeWithDummy[q17 + 1] \/ x_ExplicitVarSizeWithDummy[q17] = 5 + | q17 : int(1..2)]), + and([x_ExplicitVarSizeWithDummy[q18] = 5 -> x_ExplicitVarSizeWithDummy[q18 + 1] = 5 | q18 : int(1..2)]), + sum([toInt(x_ExplicitVarSizeWithDummy[q19] != 5) | q19 : int(1..3)]) <= 3, + and([x_ExplicitVarSizeWithDummy[q22] != 5 -> + or([x_ExplicitVarSizeWithFlags_Flags[q24] /\ + x_ExplicitVarSizeWithFlags_Values[q24] = x_ExplicitVarSizeWithDummy[q22] + | q24 : int(1..3)]) + | q22 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q26] -> + or([x_ExplicitVarSizeWithDummy[q28] != 5 /\ + x_ExplicitVarSizeWithDummy[q28] = x_ExplicitVarSizeWithFlags_Values[q26] + | q28 : int(1..3)]) + | q26 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q30] != 5 -> + or([q32 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q32] = x_ExplicitVarSizeWithDummy[q30] + | q32 : int(1..3)]) + | q30 : int(1..3)]), + and([q34 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithDummy[q36] != 5 /\ + x_ExplicitVarSizeWithDummy[q36] = x_ExplicitVarSizeWithMarker_Values[q34] + | q36 : int(1..3)]) + | q34 : int(1..3)]) + diff --git a/tests/exhaustive/basic/set05/expected/model_4_3_3-solution000001.solution b/tests/exhaustive/basic/set05/expected/model_4_3_3-solution000001.solution new file mode 100644 index 0000000000..f90e0ba18c --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_4_3_3-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2} diff --git a/tests/exhaustive/basic/set05/expected/model_4_3_3-solution000002.solution b/tests/exhaustive/basic/set05/expected/model_4_3_3-solution000002.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_4_3_3-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set05/expected/model_4_3_3-solution000003.solution b/tests/exhaustive/basic/set05/expected/model_4_3_3-solution000003.solution new file mode 100644 index 0000000000..fdc0f02f96 --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_4_3_3-solution000003.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 4} diff --git a/tests/exhaustive/basic/cut_01_on/expected/model_4_3_4.eprime.orig b/tests/exhaustive/basic/set05/expected/model_4_3_3.eprime similarity index 71% rename from tests/exhaustive/basic/cut_01_on/expected/model_4_3_4.eprime.orig rename to tests/exhaustive/basic/set05/expected/model_4_3_3.eprime index 3f66e92dd5..e1aec900de 100644 --- a/tests/exhaustive/basic/cut_01_on/expected/model_4_3_4.eprime.orig +++ b/tests/exhaustive/basic/set05/expected/model_4_3_3.eprime @@ -1,29 +1,26 @@ language ESSENCE' 1.0 find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..3)] of bool -find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3)] of int(1..3) +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3)] of int(1..4) find x_ExplicitVarSizeWithMarker_Marker: int(0..3) -find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3)] of int(1..3) -find cut1: bool -find cut2: bool +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3)] of int(1..4) branching on - [cut1, cut2, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, - x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithFlags_Flags, + x_ExplicitVarSizeWithFlags_Values] such that - !cut1 <-> - or([x_ExplicitVarSizeWithFlags_Flags[q19] /\ x_ExplicitVarSizeWithFlags_Values[q19] = 1 | q19 : int(1..3)]) /\ - or([x_ExplicitVarSizeWithFlags_Flags[q21] /\ x_ExplicitVarSizeWithFlags_Values[q21] = 2 | q21 : int(1..3)]), - !cut2 <-> - or([q23 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q23] = 1 | q23 : int(1..3)]), + or([x_ExplicitVarSizeWithFlags_Flags[q18] /\ x_ExplicitVarSizeWithFlags_Values[q18] = 1 | q18 : int(1..3)]), + or([q20 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q20] = 2 | q20 : int(1..3)]), and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] | q1 : int(1..2)]), and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..3)]), and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..2)]), + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..3)]) <= 3, and([q6 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q6] < x_ExplicitVarSizeWithMarker_Values[q6 + 1] | q6 : int(1..2)]), and([q7 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q7] = 1 | q7 : int(1..3)]), + x_ExplicitVarSizeWithMarker_Marker <= 3, and([q10 <= x_ExplicitVarSizeWithMarker_Marker -> or([x_ExplicitVarSizeWithFlags_Flags[q12] /\ x_ExplicitVarSizeWithFlags_Values[q12] = x_ExplicitVarSizeWithMarker_Values[q10] diff --git a/tests/exhaustive/basic/set05/expected/model_4_4_1-solution000001.solution b/tests/exhaustive/basic/set05/expected/model_4_4_1-solution000001.solution new file mode 100644 index 0000000000..f90e0ba18c --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_4_4_1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2} diff --git a/tests/exhaustive/basic/set05/expected/model_4_4_1-solution000002.solution b/tests/exhaustive/basic/set05/expected/model_4_4_1-solution000002.solution new file mode 100644 index 0000000000..fdc0f02f96 --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_4_4_1-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 4} diff --git a/tests/exhaustive/basic/set05/expected/model_4_4_1-solution000003.solution b/tests/exhaustive/basic/set05/expected/model_4_4_1-solution000003.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_4_4_1-solution000003.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set05/expected/model_4_4_1.eprime b/tests/exhaustive/basic/set05/expected/model_4_4_1.eprime new file mode 100644 index 0000000000..728004701a --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_4_4_1.eprime @@ -0,0 +1,22 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..3)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3)] of int(1..4) +find x_Occurrence: matrix indexed by [int(1..4)] of bool +branching on [x_Occurrence, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] +such that + or([x_ExplicitVarSizeWithFlags_Flags[q13] /\ x_ExplicitVarSizeWithFlags_Values[q13] = 1 | q13 : int(1..3)]), + or([x_ExplicitVarSizeWithFlags_Flags[q15] /\ x_ExplicitVarSizeWithFlags_Values[q15] = 2 | q15 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] + | q1 : int(1..2)]), + and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..2)]), + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..3)]) <= 3, + sum([toInt(x_Occurrence[q6]) | q6 : int(1..4)]) <= 3, + and([x_Occurrence[q7] -> + or([x_ExplicitVarSizeWithFlags_Flags[q9] /\ x_ExplicitVarSizeWithFlags_Values[q9] = q7 | q9 : int(1..3)]) + | q7 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q11] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q11]] + | q11 : int(1..3)]) + diff --git a/tests/exhaustive/basic/set05/expected/model_4_4_2-solution000001.solution b/tests/exhaustive/basic/set05/expected/model_4_4_2-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_4_4_2-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set05/expected/model_4_4_2-solution000002.solution b/tests/exhaustive/basic/set05/expected/model_4_4_2-solution000002.solution new file mode 100644 index 0000000000..fdc0f02f96 --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_4_4_2-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 4} diff --git a/tests/exhaustive/basic/set05/expected/model_4_4_2-solution000003.solution b/tests/exhaustive/basic/set05/expected/model_4_4_2-solution000003.solution new file mode 100644 index 0000000000..f90e0ba18c --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_4_4_2-solution000003.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2} diff --git a/tests/exhaustive/basic/set05/expected/model_4_4_2.eprime b/tests/exhaustive/basic/set05/expected/model_4_4_2.eprime new file mode 100644 index 0000000000..0a5bd5c53a --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_4_4_2.eprime @@ -0,0 +1,30 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..3)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3)] of int(1..4) +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..3)] of int(1..5) +branching on [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] +such that + or([x_ExplicitVarSizeWithFlags_Flags[q19] /\ x_ExplicitVarSizeWithFlags_Values[q19] = 1 | q19 : int(1..3)]), + or([x_ExplicitVarSizeWithFlags_Flags[q21] /\ x_ExplicitVarSizeWithFlags_Values[q21] = 2 | q21 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] + | q1 : int(1..2)]), + and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..2)]), + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..3)]) <= 3, + and([x_ExplicitVarSizeWithDummy[q6] < x_ExplicitVarSizeWithDummy[q6 + 1] \/ x_ExplicitVarSizeWithDummy[q6] = 5 + | q6 : int(1..2)]), + and([x_ExplicitVarSizeWithDummy[q7] = 5 -> x_ExplicitVarSizeWithDummy[q7 + 1] = 5 | q7 : int(1..2)]), + sum([toInt(x_ExplicitVarSizeWithDummy[q8] != 5) | q8 : int(1..3)]) <= 3, + and([x_ExplicitVarSizeWithDummy[q11] != 5 -> + or([x_ExplicitVarSizeWithFlags_Flags[q13] /\ + x_ExplicitVarSizeWithFlags_Values[q13] = x_ExplicitVarSizeWithDummy[q11] + | q13 : int(1..3)]) + | q11 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q15] -> + or([x_ExplicitVarSizeWithDummy[q17] != 5 /\ + x_ExplicitVarSizeWithDummy[q17] = x_ExplicitVarSizeWithFlags_Values[q15] + | q17 : int(1..3)]) + | q15 : int(1..3)]) + diff --git a/tests/exhaustive/basic/set05/expected/model_4_4_3-solution000001.solution b/tests/exhaustive/basic/set05/expected/model_4_4_3-solution000001.solution new file mode 100644 index 0000000000..f90e0ba18c --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_4_4_3-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2} diff --git a/tests/exhaustive/basic/set05/expected/model_4_4_3-solution000002.solution b/tests/exhaustive/basic/set05/expected/model_4_4_3-solution000002.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_4_4_3-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set05/expected/model_4_4_3-solution000003.solution b/tests/exhaustive/basic/set05/expected/model_4_4_3-solution000003.solution new file mode 100644 index 0000000000..fdc0f02f96 --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_4_4_3-solution000003.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 4} diff --git a/tests/exhaustive/basic/set05/expected/model_4_4_3.eprime b/tests/exhaustive/basic/set05/expected/model_4_4_3.eprime new file mode 100644 index 0000000000..ac17616362 --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_4_4_3.eprime @@ -0,0 +1,34 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..3)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3)] of int(1..4) +find x_ExplicitVarSizeWithMarker_Marker: int(0..3) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3)] of int(1..4) +branching on + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithFlags_Flags, + x_ExplicitVarSizeWithFlags_Values] +such that + or([x_ExplicitVarSizeWithFlags_Flags[q18] /\ x_ExplicitVarSizeWithFlags_Values[q18] = 1 | q18 : int(1..3)]), + or([x_ExplicitVarSizeWithFlags_Flags[q20] /\ x_ExplicitVarSizeWithFlags_Values[q20] = 2 | q20 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] + | q1 : int(1..2)]), + and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..2)]), + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..3)]) <= 3, + and([q6 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q6] < x_ExplicitVarSizeWithMarker_Values[q6 + 1] + | q6 : int(1..2)]), + and([q7 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q7] = 1 | q7 : int(1..3)]), + x_ExplicitVarSizeWithMarker_Marker <= 3, + and([q10 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithFlags_Flags[q12] /\ + x_ExplicitVarSizeWithFlags_Values[q12] = x_ExplicitVarSizeWithMarker_Values[q10] + | q12 : int(1..3)]) + | q10 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q14] -> + or([q16 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q16] = x_ExplicitVarSizeWithFlags_Values[q14] + | q16 : int(1..3)]) + | q14 : int(1..3)]) + diff --git a/tests/exhaustive/basic/set05/expected/model_4_4_4-solution000001.solution b/tests/exhaustive/basic/set05/expected/model_4_4_4-solution000001.solution new file mode 100644 index 0000000000..f90e0ba18c --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_4_4_4-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2} diff --git a/tests/exhaustive/basic/set05/expected/model_4_4_4-solution000002.solution b/tests/exhaustive/basic/set05/expected/model_4_4_4-solution000002.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_4_4_4-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set05/expected/model_4_4_4-solution000003.solution b/tests/exhaustive/basic/set05/expected/model_4_4_4-solution000003.solution new file mode 100644 index 0000000000..fdc0f02f96 --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_4_4_4-solution000003.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 4} diff --git a/tests/exhaustive/basic/set05/expected/model_4_4_4.eprime b/tests/exhaustive/basic/set05/expected/model_4_4_4.eprime new file mode 100644 index 0000000000..e4489eba01 --- /dev/null +++ b/tests/exhaustive/basic/set05/expected/model_4_4_4.eprime @@ -0,0 +1,15 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..3)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3)] of int(1..4) +branching on [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] +such that + or([x_ExplicitVarSizeWithFlags_Flags[q7] /\ x_ExplicitVarSizeWithFlags_Values[q7] = 1 | q7 : int(1..3)]), + or([x_ExplicitVarSizeWithFlags_Flags[q9] /\ x_ExplicitVarSizeWithFlags_Values[q9] = 2 | q9 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] + | q1 : int(1..2)]), + and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..2)]), + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..3)]) <= 3 + diff --git a/tests/exhaustive/basic/set06/expected/model_1_1_1_1-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_1_1_1_1-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_1_1_1_1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_1_1_1_1-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_1_1_1_1-solution000002.solution new file mode 100644 index 0000000000..85149821f6 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_1_1_1_1-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_1_1_1_1.eprime b/tests/exhaustive/basic/set06/expected/model_1_1_1_1.eprime new file mode 100644 index 0000000000..f1447509f6 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_1_1_1_1.eprime @@ -0,0 +1,10 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(1..4)] of bool +branching on [x_Occurrence] +such that + x_Occurrence[1], + x_Occurrence[2], + x_Occurrence[3], + sum([toInt(x_Occurrence[q1]) | q1 : int(1..4)]) <= 4 + diff --git a/tests/exhaustive/basic/set06/expected/model_1_1_1_2-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_1_1_1_2-solution000001.solution new file mode 100644 index 0000000000..85149821f6 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_1_1_1_2-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_1_1_1_2-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_1_1_1_2-solution000002.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_1_1_1_2-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_1_1_1_2.eprime b/tests/exhaustive/basic/set06/expected/model_1_1_1_2.eprime new file mode 100644 index 0000000000..da7b2486bc --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_1_1_1_2.eprime @@ -0,0 +1,19 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +branching on [x_ExplicitVarSizeWithDummy, x_Occurrence] +such that + x_Occurrence[1], + x_Occurrence[2], + x_Occurrence[3], + sum([toInt(x_Occurrence[q1]) | q1 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithDummy[q2] < x_ExplicitVarSizeWithDummy[q2 + 1] \/ x_ExplicitVarSizeWithDummy[q2] = 5 + | q2 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q3] = 5 -> x_ExplicitVarSizeWithDummy[q3 + 1] = 5 | q3 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithDummy[q4] != 5) | q4 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithDummy[q7] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q7]] | q7 : int(1..4)]), + and([x_Occurrence[q8] -> + or([x_ExplicitVarSizeWithDummy[q10] != 5 /\ x_ExplicitVarSizeWithDummy[q10] = q8 | q10 : int(1..4)]) + | q8 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set06/expected/model_1_1_1_3-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_1_1_1_3-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_1_1_1_3-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_1_1_1_3-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_1_1_1_3-solution000002.solution new file mode 100644 index 0000000000..85149821f6 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_1_1_1_3-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_1_1_1_3.eprime b/tests/exhaustive/basic/set06/expected/model_1_1_1_3.eprime new file mode 100644 index 0000000000..d1ee49268b --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_1_1_1_3.eprime @@ -0,0 +1,22 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +branching on [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_Occurrence] +such that + x_Occurrence[1], + x_Occurrence[2], + x_Occurrence[3], + sum([toInt(x_Occurrence[q1]) | q1 : int(1..4)]) <= 4, + and([q2 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q2] < x_ExplicitVarSizeWithMarker_Values[q2 + 1] + | q2 : int(1..3)]), + and([q3 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q3] = 1 | q3 : int(1..4)]), + x_ExplicitVarSizeWithMarker_Marker <= 4, + and([q6 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q6]] + | q6 : int(1..4)]), + and([x_Occurrence[q7] -> + or([q9 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q9] = q7 | q9 : int(1..4)]) + | q7 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set06/expected/model_1_1_1_4-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_1_1_1_4-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_1_1_1_4-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_1_1_1_4-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_1_1_1_4-solution000002.solution new file mode 100644 index 0000000000..85149821f6 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_1_1_1_4-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_1_1_1_4.eprime b/tests/exhaustive/basic/set06/expected/model_1_1_1_4.eprime new file mode 100644 index 0000000000..52a9a6c855 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_1_1_1_4.eprime @@ -0,0 +1,22 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +branching on [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_Occurrence] +such that + x_Occurrence[1], + x_Occurrence[2], + x_Occurrence[3], + sum([toInt(x_Occurrence[q1]) | q1 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithFlags_Flags[q2 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q2] < x_ExplicitVarSizeWithFlags_Values[q2 + 1] + | q2 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q3] = false -> x_ExplicitVarSizeWithFlags_Values[q3] = 1 | q3 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q4] | q4 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q5]) | q5 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithFlags_Flags[q8] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q8]] | q8 : int(1..4)]), + and([x_Occurrence[q9] -> + or([x_ExplicitVarSizeWithFlags_Flags[q11] /\ x_ExplicitVarSizeWithFlags_Values[q11] = q9 | q11 : int(1..4)]) + | q9 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set06/expected/model_1_1_2_1-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_1_1_2_1-solution000001.solution new file mode 100644 index 0000000000..85149821f6 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_1_1_2_1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_1_1_2_1-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_1_1_2_1-solution000002.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_1_1_2_1-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_1_1_2_1.eprime b/tests/exhaustive/basic/set06/expected/model_1_1_2_1.eprime new file mode 100644 index 0000000000..f6358320c2 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_1_1_2_1.eprime @@ -0,0 +1,19 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +branching on [x_ExplicitVarSizeWithDummy, x_Occurrence] +such that + x_Occurrence[1], + x_Occurrence[2], + or([x_ExplicitVarSizeWithDummy[q12] != 5 /\ x_ExplicitVarSizeWithDummy[q12] = 3 | q12 : int(1..4)]), + sum([toInt(x_Occurrence[q1]) | q1 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithDummy[q2] < x_ExplicitVarSizeWithDummy[q2 + 1] \/ x_ExplicitVarSizeWithDummy[q2] = 5 + | q2 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q3] = 5 -> x_ExplicitVarSizeWithDummy[q3 + 1] = 5 | q3 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithDummy[q4] != 5) | q4 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithDummy[q7] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q7]] | q7 : int(1..4)]), + and([x_Occurrence[q8] -> + or([x_ExplicitVarSizeWithDummy[q10] != 5 /\ x_ExplicitVarSizeWithDummy[q10] = q8 | q10 : int(1..4)]) + | q8 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set06/expected/model_1_1_2_3-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_1_1_2_3-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_1_1_2_3-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_1_1_2_3-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_1_1_2_3-solution000002.solution new file mode 100644 index 0000000000..85149821f6 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_1_1_2_3-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_1_1_2_3.eprime b/tests/exhaustive/basic/set06/expected/model_1_1_2_3.eprime new file mode 100644 index 0000000000..38d4e045e4 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_1_1_2_3.eprime @@ -0,0 +1,43 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +branching on + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_Occurrence, x_ExplicitVarSizeWithDummy] +such that + x_Occurrence[1], + x_Occurrence[2], + or([x_ExplicitVarSizeWithDummy[q28] != 5 /\ x_ExplicitVarSizeWithDummy[q28] = 3 | q28 : int(1..4)]), + sum([toInt(x_Occurrence[q1]) | q1 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithDummy[q2] < x_ExplicitVarSizeWithDummy[q2 + 1] \/ x_ExplicitVarSizeWithDummy[q2] = 5 + | q2 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q3] = 5 -> x_ExplicitVarSizeWithDummy[q3 + 1] = 5 | q3 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithDummy[q4] != 5) | q4 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithDummy[q7] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q7]] | q7 : int(1..4)]), + and([x_Occurrence[q8] -> + or([x_ExplicitVarSizeWithDummy[q10] != 5 /\ x_ExplicitVarSizeWithDummy[q10] = q8 | q10 : int(1..4)]) + | q8 : int(1..4)]), + and([q11 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q11] < x_ExplicitVarSizeWithMarker_Values[q11 + 1] + | q11 : int(1..3)]), + and([q12 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q12] = 1 | q12 : int(1..4)]), + x_ExplicitVarSizeWithMarker_Marker <= 4, + and([q15 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q15]] + | q15 : int(1..4)]), + and([x_Occurrence[q16] -> + or([q18 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q18] = q16 + | q18 : int(1..4)]) + | q16 : int(1..4)]), + and([q20 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithDummy[q22] != 5 /\ + x_ExplicitVarSizeWithDummy[q22] = x_ExplicitVarSizeWithMarker_Values[q20] + | q22 : int(1..4)]) + | q20 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q24] != 5 -> + or([q26 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q26] = x_ExplicitVarSizeWithDummy[q24] + | q26 : int(1..4)]) + | q24 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set06/expected/model_1_1_2_4-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_1_1_2_4-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_1_1_2_4-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_1_1_2_4-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_1_1_2_4-solution000002.solution new file mode 100644 index 0000000000..85149821f6 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_1_1_2_4-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_1_1_2_4.eprime b/tests/exhaustive/basic/set06/expected/model_1_1_2_4.eprime new file mode 100644 index 0000000000..ef4fbb7269 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_1_1_2_4.eprime @@ -0,0 +1,44 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +branching on + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_Occurrence, x_ExplicitVarSizeWithDummy] +such that + x_Occurrence[1], + x_Occurrence[2], + or([x_ExplicitVarSizeWithDummy[q30] != 5 /\ x_ExplicitVarSizeWithDummy[q30] = 3 | q30 : int(1..4)]), + sum([toInt(x_Occurrence[q1]) | q1 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithDummy[q2] < x_ExplicitVarSizeWithDummy[q2 + 1] \/ x_ExplicitVarSizeWithDummy[q2] = 5 + | q2 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q3] = 5 -> x_ExplicitVarSizeWithDummy[q3 + 1] = 5 | q3 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithDummy[q4] != 5) | q4 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithDummy[q7] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q7]] | q7 : int(1..4)]), + and([x_Occurrence[q8] -> + or([x_ExplicitVarSizeWithDummy[q10] != 5 /\ x_ExplicitVarSizeWithDummy[q10] = q8 | q10 : int(1..4)]) + | q8 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q11 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q11] < x_ExplicitVarSizeWithFlags_Values[q11 + 1] + | q11 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q12] = false -> x_ExplicitVarSizeWithFlags_Values[q12] = 1 + | q12 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q13 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q13] | q13 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q14]) | q14 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithFlags_Flags[q17] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q17]] + | q17 : int(1..4)]), + and([x_Occurrence[q18] -> + or([x_ExplicitVarSizeWithFlags_Flags[q20] /\ x_ExplicitVarSizeWithFlags_Values[q20] = q18 | q20 : int(1..4)]) + | q18 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q22] -> + or([x_ExplicitVarSizeWithDummy[q24] != 5 /\ + x_ExplicitVarSizeWithDummy[q24] = x_ExplicitVarSizeWithFlags_Values[q22] + | q24 : int(1..4)]) + | q22 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q26] != 5 -> + or([x_ExplicitVarSizeWithFlags_Flags[q28] /\ + x_ExplicitVarSizeWithFlags_Values[q28] = x_ExplicitVarSizeWithDummy[q26] + | q28 : int(1..4)]) + | q26 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set06/expected/model_1_1_3_1-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_1_1_3_1-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_1_1_3_1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_1_1_3_1-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_1_1_3_1-solution000002.solution new file mode 100644 index 0000000000..85149821f6 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_1_1_3_1-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_1_1_3_1.eprime b/tests/exhaustive/basic/set06/expected/model_1_1_3_1.eprime new file mode 100644 index 0000000000..70953f52c2 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_1_1_3_1.eprime @@ -0,0 +1,22 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +branching on [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_Occurrence] +such that + x_Occurrence[1], + x_Occurrence[2], + or([q11 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q11] = 3 | q11 : int(1..4)]), + sum([toInt(x_Occurrence[q1]) | q1 : int(1..4)]) <= 4, + and([q2 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q2] < x_ExplicitVarSizeWithMarker_Values[q2 + 1] + | q2 : int(1..3)]), + and([q3 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q3] = 1 | q3 : int(1..4)]), + x_ExplicitVarSizeWithMarker_Marker <= 4, + and([q6 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q6]] + | q6 : int(1..4)]), + and([x_Occurrence[q7] -> + or([q9 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q9] = q7 | q9 : int(1..4)]) + | q7 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set06/expected/model_1_1_3_2-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_1_1_3_2-solution000001.solution new file mode 100644 index 0000000000..85149821f6 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_1_1_3_2-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_1_1_3_2-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_1_1_3_2-solution000002.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_1_1_3_2-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_1_1_3_2.eprime b/tests/exhaustive/basic/set06/expected/model_1_1_3_2.eprime new file mode 100644 index 0000000000..07088141cf --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_1_1_3_2.eprime @@ -0,0 +1,42 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +branching on + [x_ExplicitVarSizeWithDummy, x_Occurrence, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] +such that + x_Occurrence[1], + x_Occurrence[2], + or([q28 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q28] = 3 | q28 : int(1..4)]), + sum([toInt(x_Occurrence[q1]) | q1 : int(1..4)]) <= 4, + and([q2 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q2] < x_ExplicitVarSizeWithMarker_Values[q2 + 1] + | q2 : int(1..3)]), + and([q3 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q3] = 1 | q3 : int(1..4)]), + x_ExplicitVarSizeWithMarker_Marker <= 4, + and([q6 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q6]] + | q6 : int(1..4)]), + and([x_Occurrence[q7] -> + or([q9 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q9] = q7 | q9 : int(1..4)]) + | q7 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q10] < x_ExplicitVarSizeWithDummy[q10 + 1] \/ x_ExplicitVarSizeWithDummy[q10] = 5 + | q10 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q11] = 5 -> x_ExplicitVarSizeWithDummy[q11 + 1] = 5 | q11 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithDummy[q12] != 5) | q12 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithDummy[q15] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q15]] | q15 : int(1..4)]), + and([x_Occurrence[q16] -> + or([x_ExplicitVarSizeWithDummy[q18] != 5 /\ x_ExplicitVarSizeWithDummy[q18] = q16 | q18 : int(1..4)]) + | q16 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q20] != 5 -> + or([q22 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q22] = x_ExplicitVarSizeWithDummy[q20] + | q22 : int(1..4)]) + | q20 : int(1..4)]), + and([q24 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithDummy[q26] != 5 /\ + x_ExplicitVarSizeWithDummy[q26] = x_ExplicitVarSizeWithMarker_Values[q24] + | q26 : int(1..4)]) + | q24 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set06/expected/model_1_1_3_4-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_1_1_3_4-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_1_1_3_4-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_1_1_3_4-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_1_1_3_4-solution000002.solution new file mode 100644 index 0000000000..85149821f6 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_1_1_3_4-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_1_1_3_4.eprime b/tests/exhaustive/basic/set06/expected/model_1_1_3_4.eprime new file mode 100644 index 0000000000..9e996001f2 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_1_1_3_4.eprime @@ -0,0 +1,48 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +branching on + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_Occurrence, + x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] +such that + x_Occurrence[1], + x_Occurrence[2], + or([q29 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q29] = 3 | q29 : int(1..4)]), + sum([toInt(x_Occurrence[q1]) | q1 : int(1..4)]) <= 4, + and([q2 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q2] < x_ExplicitVarSizeWithMarker_Values[q2 + 1] + | q2 : int(1..3)]), + and([q3 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q3] = 1 | q3 : int(1..4)]), + x_ExplicitVarSizeWithMarker_Marker <= 4, + and([q6 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q6]] + | q6 : int(1..4)]), + and([x_Occurrence[q7] -> + or([q9 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q9] = q7 | q9 : int(1..4)]) + | q7 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q10 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q10] < x_ExplicitVarSizeWithFlags_Values[q10 + 1] + | q10 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q11] = false -> x_ExplicitVarSizeWithFlags_Values[q11] = 1 + | q11 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q12 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q12] | q12 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q13]) | q13 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithFlags_Flags[q16] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q16]] + | q16 : int(1..4)]), + and([x_Occurrence[q17] -> + or([x_ExplicitVarSizeWithFlags_Flags[q19] /\ x_ExplicitVarSizeWithFlags_Values[q19] = q17 | q19 : int(1..4)]) + | q17 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q21] -> + or([q23 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q23] = x_ExplicitVarSizeWithFlags_Values[q21] + | q23 : int(1..4)]) + | q21 : int(1..4)]), + and([q25 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithFlags_Flags[q27] /\ + x_ExplicitVarSizeWithFlags_Values[q27] = x_ExplicitVarSizeWithMarker_Values[q25] + | q27 : int(1..4)]) + | q25 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set06/expected/model_1_1_4_1-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_1_1_4_1-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_1_1_4_1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_1_1_4_1-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_1_1_4_1-solution000002.solution new file mode 100644 index 0000000000..85149821f6 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_1_1_4_1-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_1_1_4_1.eprime b/tests/exhaustive/basic/set06/expected/model_1_1_4_1.eprime new file mode 100644 index 0000000000..2ced4fdbb0 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_1_1_4_1.eprime @@ -0,0 +1,22 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +branching on [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_Occurrence] +such that + x_Occurrence[1], + x_Occurrence[2], + or([x_ExplicitVarSizeWithFlags_Flags[q13] /\ x_ExplicitVarSizeWithFlags_Values[q13] = 3 | q13 : int(1..4)]), + sum([toInt(x_Occurrence[q1]) | q1 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithFlags_Flags[q2 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q2] < x_ExplicitVarSizeWithFlags_Values[q2 + 1] + | q2 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q3] = false -> x_ExplicitVarSizeWithFlags_Values[q3] = 1 | q3 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q4] | q4 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q5]) | q5 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithFlags_Flags[q8] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q8]] | q8 : int(1..4)]), + and([x_Occurrence[q9] -> + or([x_ExplicitVarSizeWithFlags_Flags[q11] /\ x_ExplicitVarSizeWithFlags_Values[q11] = q9 | q11 : int(1..4)]) + | q9 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set06/expected/model_1_1_4_2-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_1_1_4_2-solution000001.solution new file mode 100644 index 0000000000..85149821f6 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_1_1_4_2-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_1_1_4_2-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_1_1_4_2-solution000002.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_1_1_4_2-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_1_1_4_2.eprime b/tests/exhaustive/basic/set06/expected/model_1_1_4_2.eprime new file mode 100644 index 0000000000..faf6fcb130 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_1_1_4_2.eprime @@ -0,0 +1,42 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +branching on + [x_ExplicitVarSizeWithDummy, x_Occurrence, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] +such that + x_Occurrence[1], + x_Occurrence[2], + or([x_ExplicitVarSizeWithFlags_Flags[q30] /\ x_ExplicitVarSizeWithFlags_Values[q30] = 3 | q30 : int(1..4)]), + sum([toInt(x_Occurrence[q1]) | q1 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithFlags_Flags[q2 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q2] < x_ExplicitVarSizeWithFlags_Values[q2 + 1] + | q2 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q3] = false -> x_ExplicitVarSizeWithFlags_Values[q3] = 1 | q3 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q4] | q4 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q5]) | q5 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithFlags_Flags[q8] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q8]] | q8 : int(1..4)]), + and([x_Occurrence[q9] -> + or([x_ExplicitVarSizeWithFlags_Flags[q11] /\ x_ExplicitVarSizeWithFlags_Values[q11] = q9 | q11 : int(1..4)]) + | q9 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q12] < x_ExplicitVarSizeWithDummy[q12 + 1] \/ x_ExplicitVarSizeWithDummy[q12] = 5 + | q12 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q13] = 5 -> x_ExplicitVarSizeWithDummy[q13 + 1] = 5 | q13 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithDummy[q14] != 5) | q14 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithDummy[q17] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q17]] | q17 : int(1..4)]), + and([x_Occurrence[q18] -> + or([x_ExplicitVarSizeWithDummy[q20] != 5 /\ x_ExplicitVarSizeWithDummy[q20] = q18 | q20 : int(1..4)]) + | q18 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q22] != 5 -> + or([x_ExplicitVarSizeWithFlags_Flags[q24] /\ + x_ExplicitVarSizeWithFlags_Values[q24] = x_ExplicitVarSizeWithDummy[q22] + | q24 : int(1..4)]) + | q22 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q26] -> + or([x_ExplicitVarSizeWithDummy[q28] != 5 /\ + x_ExplicitVarSizeWithDummy[q28] = x_ExplicitVarSizeWithFlags_Values[q26] + | q28 : int(1..4)]) + | q26 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set06/expected/model_1_1_4_3-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_1_1_4_3-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_1_1_4_3-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_1_1_4_3-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_1_1_4_3-solution000002.solution new file mode 100644 index 0000000000..85149821f6 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_1_1_4_3-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_1_1_4_3.eprime b/tests/exhaustive/basic/set06/expected/model_1_1_4_3.eprime new file mode 100644 index 0000000000..21bbdced45 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_1_1_4_3.eprime @@ -0,0 +1,47 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +branching on + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_Occurrence, + x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] +such that + x_Occurrence[1], + x_Occurrence[2], + or([x_ExplicitVarSizeWithFlags_Flags[q29] /\ x_ExplicitVarSizeWithFlags_Values[q29] = 3 | q29 : int(1..4)]), + sum([toInt(x_Occurrence[q1]) | q1 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithFlags_Flags[q2 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q2] < x_ExplicitVarSizeWithFlags_Values[q2 + 1] + | q2 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q3] = false -> x_ExplicitVarSizeWithFlags_Values[q3] = 1 | q3 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q4] | q4 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q5]) | q5 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithFlags_Flags[q8] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q8]] | q8 : int(1..4)]), + and([x_Occurrence[q9] -> + or([x_ExplicitVarSizeWithFlags_Flags[q11] /\ x_ExplicitVarSizeWithFlags_Values[q11] = q9 | q11 : int(1..4)]) + | q9 : int(1..4)]), + and([q12 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q12] < x_ExplicitVarSizeWithMarker_Values[q12 + 1] + | q12 : int(1..3)]), + and([q13 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q13] = 1 | q13 : int(1..4)]), + x_ExplicitVarSizeWithMarker_Marker <= 4, + and([q16 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q16]] + | q16 : int(1..4)]), + and([x_Occurrence[q17] -> + or([q19 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q19] = q17 + | q19 : int(1..4)]) + | q17 : int(1..4)]), + and([q21 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithFlags_Flags[q23] /\ + x_ExplicitVarSizeWithFlags_Values[q23] = x_ExplicitVarSizeWithMarker_Values[q21] + | q23 : int(1..4)]) + | q21 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q25] -> + or([q27 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q27] = x_ExplicitVarSizeWithFlags_Values[q25] + | q27 : int(1..4)]) + | q25 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set06/expected/model_1_2_1_1-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_1_2_1_1-solution000001.solution new file mode 100644 index 0000000000..85149821f6 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_1_2_1_1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_1_2_1_1-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_1_2_1_1-solution000002.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_1_2_1_1-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_1_2_1_1.eprime b/tests/exhaustive/basic/set06/expected/model_1_2_1_1.eprime new file mode 100644 index 0000000000..fd00042c48 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_1_2_1_1.eprime @@ -0,0 +1,19 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +branching on [x_ExplicitVarSizeWithDummy, x_Occurrence] +such that + x_Occurrence[1], + or([x_ExplicitVarSizeWithDummy[q12] != 5 /\ x_ExplicitVarSizeWithDummy[q12] = 2 | q12 : int(1..4)]), + x_Occurrence[3], + sum([toInt(x_Occurrence[q1]) | q1 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithDummy[q2] < x_ExplicitVarSizeWithDummy[q2 + 1] \/ x_ExplicitVarSizeWithDummy[q2] = 5 + | q2 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q3] = 5 -> x_ExplicitVarSizeWithDummy[q3 + 1] = 5 | q3 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithDummy[q4] != 5) | q4 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithDummy[q7] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q7]] | q7 : int(1..4)]), + and([x_Occurrence[q8] -> + or([x_ExplicitVarSizeWithDummy[q10] != 5 /\ x_ExplicitVarSizeWithDummy[q10] = q8 | q10 : int(1..4)]) + | q8 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set06/expected/model_1_2_1_3-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_1_2_1_3-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_1_2_1_3-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_1_2_1_3-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_1_2_1_3-solution000002.solution new file mode 100644 index 0000000000..85149821f6 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_1_2_1_3-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_1_2_1_3.eprime b/tests/exhaustive/basic/set06/expected/model_1_2_1_3.eprime new file mode 100644 index 0000000000..9cd2a1ceb8 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_1_2_1_3.eprime @@ -0,0 +1,43 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +branching on + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_Occurrence, x_ExplicitVarSizeWithDummy] +such that + x_Occurrence[1], + or([x_ExplicitVarSizeWithDummy[q28] != 5 /\ x_ExplicitVarSizeWithDummy[q28] = 2 | q28 : int(1..4)]), + x_Occurrence[3], + sum([toInt(x_Occurrence[q1]) | q1 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithDummy[q2] < x_ExplicitVarSizeWithDummy[q2 + 1] \/ x_ExplicitVarSizeWithDummy[q2] = 5 + | q2 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q3] = 5 -> x_ExplicitVarSizeWithDummy[q3 + 1] = 5 | q3 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithDummy[q4] != 5) | q4 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithDummy[q7] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q7]] | q7 : int(1..4)]), + and([x_Occurrence[q8] -> + or([x_ExplicitVarSizeWithDummy[q10] != 5 /\ x_ExplicitVarSizeWithDummy[q10] = q8 | q10 : int(1..4)]) + | q8 : int(1..4)]), + and([q11 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q11] < x_ExplicitVarSizeWithMarker_Values[q11 + 1] + | q11 : int(1..3)]), + and([q12 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q12] = 1 | q12 : int(1..4)]), + x_ExplicitVarSizeWithMarker_Marker <= 4, + and([q15 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q15]] + | q15 : int(1..4)]), + and([x_Occurrence[q16] -> + or([q18 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q18] = q16 + | q18 : int(1..4)]) + | q16 : int(1..4)]), + and([q20 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithDummy[q22] != 5 /\ + x_ExplicitVarSizeWithDummy[q22] = x_ExplicitVarSizeWithMarker_Values[q20] + | q22 : int(1..4)]) + | q20 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q24] != 5 -> + or([q26 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q26] = x_ExplicitVarSizeWithDummy[q24] + | q26 : int(1..4)]) + | q24 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set06/expected/model_1_2_1_4-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_1_2_1_4-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_1_2_1_4-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_1_2_1_4-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_1_2_1_4-solution000002.solution new file mode 100644 index 0000000000..85149821f6 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_1_2_1_4-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_1_2_1_4.eprime b/tests/exhaustive/basic/set06/expected/model_1_2_1_4.eprime new file mode 100644 index 0000000000..16ffeaa1a3 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_1_2_1_4.eprime @@ -0,0 +1,44 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +branching on + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_Occurrence, x_ExplicitVarSizeWithDummy] +such that + x_Occurrence[1], + or([x_ExplicitVarSizeWithDummy[q30] != 5 /\ x_ExplicitVarSizeWithDummy[q30] = 2 | q30 : int(1..4)]), + x_Occurrence[3], + sum([toInt(x_Occurrence[q1]) | q1 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithDummy[q2] < x_ExplicitVarSizeWithDummy[q2 + 1] \/ x_ExplicitVarSizeWithDummy[q2] = 5 + | q2 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q3] = 5 -> x_ExplicitVarSizeWithDummy[q3 + 1] = 5 | q3 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithDummy[q4] != 5) | q4 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithDummy[q7] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q7]] | q7 : int(1..4)]), + and([x_Occurrence[q8] -> + or([x_ExplicitVarSizeWithDummy[q10] != 5 /\ x_ExplicitVarSizeWithDummy[q10] = q8 | q10 : int(1..4)]) + | q8 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q11 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q11] < x_ExplicitVarSizeWithFlags_Values[q11 + 1] + | q11 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q12] = false -> x_ExplicitVarSizeWithFlags_Values[q12] = 1 + | q12 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q13 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q13] | q13 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q14]) | q14 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithFlags_Flags[q17] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q17]] + | q17 : int(1..4)]), + and([x_Occurrence[q18] -> + or([x_ExplicitVarSizeWithFlags_Flags[q20] /\ x_ExplicitVarSizeWithFlags_Values[q20] = q18 | q20 : int(1..4)]) + | q18 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q22] -> + or([x_ExplicitVarSizeWithDummy[q24] != 5 /\ + x_ExplicitVarSizeWithDummy[q24] = x_ExplicitVarSizeWithFlags_Values[q22] + | q24 : int(1..4)]) + | q22 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q26] != 5 -> + or([x_ExplicitVarSizeWithFlags_Flags[q28] /\ + x_ExplicitVarSizeWithFlags_Values[q28] = x_ExplicitVarSizeWithDummy[q26] + | q28 : int(1..4)]) + | q26 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set06/expected/model_1_2_2_1-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_1_2_2_1-solution000001.solution new file mode 100644 index 0000000000..85149821f6 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_1_2_2_1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_1_2_2_1-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_1_2_2_1-solution000002.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_1_2_2_1-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_1_2_2_1.eprime b/tests/exhaustive/basic/set06/expected/model_1_2_2_1.eprime new file mode 100644 index 0000000000..31cd01bf55 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_1_2_2_1.eprime @@ -0,0 +1,19 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +branching on [x_ExplicitVarSizeWithDummy, x_Occurrence] +such that + x_Occurrence[1], + or([x_ExplicitVarSizeWithDummy[q12] != 5 /\ x_ExplicitVarSizeWithDummy[q12] = 2 | q12 : int(1..4)]), + or([x_ExplicitVarSizeWithDummy[q14] != 5 /\ x_ExplicitVarSizeWithDummy[q14] = 3 | q14 : int(1..4)]), + sum([toInt(x_Occurrence[q1]) | q1 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithDummy[q2] < x_ExplicitVarSizeWithDummy[q2 + 1] \/ x_ExplicitVarSizeWithDummy[q2] = 5 + | q2 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q3] = 5 -> x_ExplicitVarSizeWithDummy[q3 + 1] = 5 | q3 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithDummy[q4] != 5) | q4 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithDummy[q7] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q7]] | q7 : int(1..4)]), + and([x_Occurrence[q8] -> + or([x_ExplicitVarSizeWithDummy[q10] != 5 /\ x_ExplicitVarSizeWithDummy[q10] = q8 | q10 : int(1..4)]) + | q8 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set06/expected/model_1_2_2_3-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_1_2_2_3-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_1_2_2_3-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_1_2_2_3-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_1_2_2_3-solution000002.solution new file mode 100644 index 0000000000..85149821f6 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_1_2_2_3-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_1_2_2_3.eprime b/tests/exhaustive/basic/set06/expected/model_1_2_2_3.eprime new file mode 100644 index 0000000000..2a7394dd4b --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_1_2_2_3.eprime @@ -0,0 +1,43 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +branching on + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_Occurrence, x_ExplicitVarSizeWithDummy] +such that + x_Occurrence[1], + or([x_ExplicitVarSizeWithDummy[q28] != 5 /\ x_ExplicitVarSizeWithDummy[q28] = 2 | q28 : int(1..4)]), + or([x_ExplicitVarSizeWithDummy[q30] != 5 /\ x_ExplicitVarSizeWithDummy[q30] = 3 | q30 : int(1..4)]), + sum([toInt(x_Occurrence[q1]) | q1 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithDummy[q2] < x_ExplicitVarSizeWithDummy[q2 + 1] \/ x_ExplicitVarSizeWithDummy[q2] = 5 + | q2 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q3] = 5 -> x_ExplicitVarSizeWithDummy[q3 + 1] = 5 | q3 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithDummy[q4] != 5) | q4 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithDummy[q7] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q7]] | q7 : int(1..4)]), + and([x_Occurrence[q8] -> + or([x_ExplicitVarSizeWithDummy[q10] != 5 /\ x_ExplicitVarSizeWithDummy[q10] = q8 | q10 : int(1..4)]) + | q8 : int(1..4)]), + and([q11 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q11] < x_ExplicitVarSizeWithMarker_Values[q11 + 1] + | q11 : int(1..3)]), + and([q12 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q12] = 1 | q12 : int(1..4)]), + x_ExplicitVarSizeWithMarker_Marker <= 4, + and([q15 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q15]] + | q15 : int(1..4)]), + and([x_Occurrence[q16] -> + or([q18 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q18] = q16 + | q18 : int(1..4)]) + | q16 : int(1..4)]), + and([q20 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithDummy[q22] != 5 /\ + x_ExplicitVarSizeWithDummy[q22] = x_ExplicitVarSizeWithMarker_Values[q20] + | q22 : int(1..4)]) + | q20 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q24] != 5 -> + or([q26 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q26] = x_ExplicitVarSizeWithDummy[q24] + | q26 : int(1..4)]) + | q24 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set06/expected/model_1_2_2_4-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_1_2_2_4-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_1_2_2_4-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_1_2_2_4-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_1_2_2_4-solution000002.solution new file mode 100644 index 0000000000..85149821f6 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_1_2_2_4-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_1_2_2_4.eprime b/tests/exhaustive/basic/set06/expected/model_1_2_2_4.eprime new file mode 100644 index 0000000000..cd3be25f64 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_1_2_2_4.eprime @@ -0,0 +1,44 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +branching on + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_Occurrence, x_ExplicitVarSizeWithDummy] +such that + x_Occurrence[1], + or([x_ExplicitVarSizeWithDummy[q30] != 5 /\ x_ExplicitVarSizeWithDummy[q30] = 2 | q30 : int(1..4)]), + or([x_ExplicitVarSizeWithDummy[q32] != 5 /\ x_ExplicitVarSizeWithDummy[q32] = 3 | q32 : int(1..4)]), + sum([toInt(x_Occurrence[q1]) | q1 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithDummy[q2] < x_ExplicitVarSizeWithDummy[q2 + 1] \/ x_ExplicitVarSizeWithDummy[q2] = 5 + | q2 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q3] = 5 -> x_ExplicitVarSizeWithDummy[q3 + 1] = 5 | q3 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithDummy[q4] != 5) | q4 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithDummy[q7] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q7]] | q7 : int(1..4)]), + and([x_Occurrence[q8] -> + or([x_ExplicitVarSizeWithDummy[q10] != 5 /\ x_ExplicitVarSizeWithDummy[q10] = q8 | q10 : int(1..4)]) + | q8 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q11 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q11] < x_ExplicitVarSizeWithFlags_Values[q11 + 1] + | q11 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q12] = false -> x_ExplicitVarSizeWithFlags_Values[q12] = 1 + | q12 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q13 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q13] | q13 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q14]) | q14 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithFlags_Flags[q17] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q17]] + | q17 : int(1..4)]), + and([x_Occurrence[q18] -> + or([x_ExplicitVarSizeWithFlags_Flags[q20] /\ x_ExplicitVarSizeWithFlags_Values[q20] = q18 | q20 : int(1..4)]) + | q18 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q22] -> + or([x_ExplicitVarSizeWithDummy[q24] != 5 /\ + x_ExplicitVarSizeWithDummy[q24] = x_ExplicitVarSizeWithFlags_Values[q22] + | q24 : int(1..4)]) + | q22 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q26] != 5 -> + or([x_ExplicitVarSizeWithFlags_Flags[q28] /\ + x_ExplicitVarSizeWithFlags_Values[q28] = x_ExplicitVarSizeWithDummy[q26] + | q28 : int(1..4)]) + | q26 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set06/expected/model_1_2_3_1-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_1_2_3_1-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_1_2_3_1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_1_2_3_1-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_1_2_3_1-solution000002.solution new file mode 100644 index 0000000000..85149821f6 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_1_2_3_1-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_1_2_3_1.eprime b/tests/exhaustive/basic/set06/expected/model_1_2_3_1.eprime new file mode 100644 index 0000000000..c6b9ef4264 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_1_2_3_1.eprime @@ -0,0 +1,43 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +branching on + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_Occurrence, x_ExplicitVarSizeWithDummy] +such that + x_Occurrence[1], + or([x_ExplicitVarSizeWithDummy[q28] != 5 /\ x_ExplicitVarSizeWithDummy[q28] = 2 | q28 : int(1..4)]), + or([q30 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q30] = 3 | q30 : int(1..4)]), + sum([toInt(x_Occurrence[q1]) | q1 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithDummy[q2] < x_ExplicitVarSizeWithDummy[q2 + 1] \/ x_ExplicitVarSizeWithDummy[q2] = 5 + | q2 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q3] = 5 -> x_ExplicitVarSizeWithDummy[q3 + 1] = 5 | q3 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithDummy[q4] != 5) | q4 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithDummy[q7] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q7]] | q7 : int(1..4)]), + and([x_Occurrence[q8] -> + or([x_ExplicitVarSizeWithDummy[q10] != 5 /\ x_ExplicitVarSizeWithDummy[q10] = q8 | q10 : int(1..4)]) + | q8 : int(1..4)]), + and([q11 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q11] < x_ExplicitVarSizeWithMarker_Values[q11 + 1] + | q11 : int(1..3)]), + and([q12 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q12] = 1 | q12 : int(1..4)]), + x_ExplicitVarSizeWithMarker_Marker <= 4, + and([q15 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q15]] + | q15 : int(1..4)]), + and([x_Occurrence[q16] -> + or([q18 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q18] = q16 + | q18 : int(1..4)]) + | q16 : int(1..4)]), + and([q20 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithDummy[q22] != 5 /\ + x_ExplicitVarSizeWithDummy[q22] = x_ExplicitVarSizeWithMarker_Values[q20] + | q22 : int(1..4)]) + | q20 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q24] != 5 -> + or([q26 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q26] = x_ExplicitVarSizeWithDummy[q24] + | q26 : int(1..4)]) + | q24 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set06/expected/model_1_2_3_4-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_1_2_3_4-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_1_2_3_4-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_1_2_3_4-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_1_2_3_4-solution000002.solution new file mode 100644 index 0000000000..85149821f6 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_1_2_3_4-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_1_2_3_4.eprime b/tests/exhaustive/basic/set06/expected/model_1_2_3_4.eprime new file mode 100644 index 0000000000..6015b45fb3 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_1_2_3_4.eprime @@ -0,0 +1,78 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +branching on + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_Occurrence, x_ExplicitVarSizeWithDummy, + x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] +such that + x_Occurrence[1], + or([x_ExplicitVarSizeWithDummy[q54] != 5 /\ x_ExplicitVarSizeWithDummy[q54] = 2 | q54 : int(1..4)]), + or([q56 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q56] = 3 | q56 : int(1..4)]), + sum([toInt(x_Occurrence[q1]) | q1 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithDummy[q2] < x_ExplicitVarSizeWithDummy[q2 + 1] \/ x_ExplicitVarSizeWithDummy[q2] = 5 + | q2 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q3] = 5 -> x_ExplicitVarSizeWithDummy[q3 + 1] = 5 | q3 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithDummy[q4] != 5) | q4 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithDummy[q7] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q7]] | q7 : int(1..4)]), + and([x_Occurrence[q8] -> + or([x_ExplicitVarSizeWithDummy[q10] != 5 /\ x_ExplicitVarSizeWithDummy[q10] = q8 | q10 : int(1..4)]) + | q8 : int(1..4)]), + and([q11 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q11] < x_ExplicitVarSizeWithMarker_Values[q11 + 1] + | q11 : int(1..3)]), + and([q12 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q12] = 1 | q12 : int(1..4)]), + x_ExplicitVarSizeWithMarker_Marker <= 4, + and([q15 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q15]] + | q15 : int(1..4)]), + and([x_Occurrence[q16] -> + or([q18 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q18] = q16 + | q18 : int(1..4)]) + | q16 : int(1..4)]), + and([q20 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithDummy[q22] != 5 /\ + x_ExplicitVarSizeWithDummy[q22] = x_ExplicitVarSizeWithMarker_Values[q20] + | q22 : int(1..4)]) + | q20 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q24] != 5 -> + or([q26 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q26] = x_ExplicitVarSizeWithDummy[q24] + | q26 : int(1..4)]) + | q24 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q27 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q27] < x_ExplicitVarSizeWithFlags_Values[q27 + 1] + | q27 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q28] = false -> x_ExplicitVarSizeWithFlags_Values[q28] = 1 + | q28 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q29 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q29] | q29 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q30]) | q30 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithFlags_Flags[q33] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q33]] + | q33 : int(1..4)]), + and([x_Occurrence[q34] -> + or([x_ExplicitVarSizeWithFlags_Flags[q36] /\ x_ExplicitVarSizeWithFlags_Values[q36] = q34 | q36 : int(1..4)]) + | q34 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q38] -> + or([x_ExplicitVarSizeWithDummy[q40] != 5 /\ + x_ExplicitVarSizeWithDummy[q40] = x_ExplicitVarSizeWithFlags_Values[q38] + | q40 : int(1..4)]) + | q38 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q42] != 5 -> + or([x_ExplicitVarSizeWithFlags_Flags[q44] /\ + x_ExplicitVarSizeWithFlags_Values[q44] = x_ExplicitVarSizeWithDummy[q42] + | q44 : int(1..4)]) + | q42 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q46] -> + or([q48 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q48] = x_ExplicitVarSizeWithFlags_Values[q46] + | q48 : int(1..4)]) + | q46 : int(1..4)]), + and([q50 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithFlags_Flags[q52] /\ + x_ExplicitVarSizeWithFlags_Values[q52] = x_ExplicitVarSizeWithMarker_Values[q50] + | q52 : int(1..4)]) + | q50 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set06/expected/model_1_2_4_1-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_1_2_4_1-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_1_2_4_1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_1_2_4_1-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_1_2_4_1-solution000002.solution new file mode 100644 index 0000000000..85149821f6 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_1_2_4_1-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_1_2_4_1.eprime b/tests/exhaustive/basic/set06/expected/model_1_2_4_1.eprime new file mode 100644 index 0000000000..aed016ee53 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_1_2_4_1.eprime @@ -0,0 +1,44 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +branching on + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_Occurrence, x_ExplicitVarSizeWithDummy] +such that + x_Occurrence[1], + or([x_ExplicitVarSizeWithDummy[q30] != 5 /\ x_ExplicitVarSizeWithDummy[q30] = 2 | q30 : int(1..4)]), + or([x_ExplicitVarSizeWithFlags_Flags[q32] /\ x_ExplicitVarSizeWithFlags_Values[q32] = 3 | q32 : int(1..4)]), + sum([toInt(x_Occurrence[q1]) | q1 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithDummy[q2] < x_ExplicitVarSizeWithDummy[q2 + 1] \/ x_ExplicitVarSizeWithDummy[q2] = 5 + | q2 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q3] = 5 -> x_ExplicitVarSizeWithDummy[q3 + 1] = 5 | q3 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithDummy[q4] != 5) | q4 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithDummy[q7] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q7]] | q7 : int(1..4)]), + and([x_Occurrence[q8] -> + or([x_ExplicitVarSizeWithDummy[q10] != 5 /\ x_ExplicitVarSizeWithDummy[q10] = q8 | q10 : int(1..4)]) + | q8 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q11 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q11] < x_ExplicitVarSizeWithFlags_Values[q11 + 1] + | q11 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q12] = false -> x_ExplicitVarSizeWithFlags_Values[q12] = 1 + | q12 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q13 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q13] | q13 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q14]) | q14 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithFlags_Flags[q17] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q17]] + | q17 : int(1..4)]), + and([x_Occurrence[q18] -> + or([x_ExplicitVarSizeWithFlags_Flags[q20] /\ x_ExplicitVarSizeWithFlags_Values[q20] = q18 | q20 : int(1..4)]) + | q18 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q22] -> + or([x_ExplicitVarSizeWithDummy[q24] != 5 /\ + x_ExplicitVarSizeWithDummy[q24] = x_ExplicitVarSizeWithFlags_Values[q22] + | q24 : int(1..4)]) + | q22 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q26] != 5 -> + or([x_ExplicitVarSizeWithFlags_Flags[q28] /\ + x_ExplicitVarSizeWithFlags_Values[q28] = x_ExplicitVarSizeWithDummy[q26] + | q28 : int(1..4)]) + | q26 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set06/expected/model_1_2_4_3-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_1_2_4_3-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_1_2_4_3-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_1_2_4_3-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_1_2_4_3-solution000002.solution new file mode 100644 index 0000000000..85149821f6 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_1_2_4_3-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_1_2_4_3.eprime b/tests/exhaustive/basic/set06/expected/model_1_2_4_3.eprime new file mode 100644 index 0000000000..bb79bbed91 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_1_2_4_3.eprime @@ -0,0 +1,78 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +branching on + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_Occurrence, x_ExplicitVarSizeWithDummy, + x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] +such that + x_Occurrence[1], + or([x_ExplicitVarSizeWithDummy[q54] != 5 /\ x_ExplicitVarSizeWithDummy[q54] = 2 | q54 : int(1..4)]), + or([x_ExplicitVarSizeWithFlags_Flags[q56] /\ x_ExplicitVarSizeWithFlags_Values[q56] = 3 | q56 : int(1..4)]), + sum([toInt(x_Occurrence[q1]) | q1 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithDummy[q2] < x_ExplicitVarSizeWithDummy[q2 + 1] \/ x_ExplicitVarSizeWithDummy[q2] = 5 + | q2 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q3] = 5 -> x_ExplicitVarSizeWithDummy[q3 + 1] = 5 | q3 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithDummy[q4] != 5) | q4 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithDummy[q7] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q7]] | q7 : int(1..4)]), + and([x_Occurrence[q8] -> + or([x_ExplicitVarSizeWithDummy[q10] != 5 /\ x_ExplicitVarSizeWithDummy[q10] = q8 | q10 : int(1..4)]) + | q8 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q11 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q11] < x_ExplicitVarSizeWithFlags_Values[q11 + 1] + | q11 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q12] = false -> x_ExplicitVarSizeWithFlags_Values[q12] = 1 + | q12 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q13 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q13] | q13 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q14]) | q14 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithFlags_Flags[q17] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q17]] + | q17 : int(1..4)]), + and([x_Occurrence[q18] -> + or([x_ExplicitVarSizeWithFlags_Flags[q20] /\ x_ExplicitVarSizeWithFlags_Values[q20] = q18 | q20 : int(1..4)]) + | q18 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q22] -> + or([x_ExplicitVarSizeWithDummy[q24] != 5 /\ + x_ExplicitVarSizeWithDummy[q24] = x_ExplicitVarSizeWithFlags_Values[q22] + | q24 : int(1..4)]) + | q22 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q26] != 5 -> + or([x_ExplicitVarSizeWithFlags_Flags[q28] /\ + x_ExplicitVarSizeWithFlags_Values[q28] = x_ExplicitVarSizeWithDummy[q26] + | q28 : int(1..4)]) + | q26 : int(1..4)]), + and([q29 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q29] < x_ExplicitVarSizeWithMarker_Values[q29 + 1] + | q29 : int(1..3)]), + and([q30 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q30] = 1 | q30 : int(1..4)]), + x_ExplicitVarSizeWithMarker_Marker <= 4, + and([q33 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q33]] + | q33 : int(1..4)]), + and([x_Occurrence[q34] -> + or([q36 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q36] = q34 + | q36 : int(1..4)]) + | q34 : int(1..4)]), + and([q38 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithDummy[q40] != 5 /\ + x_ExplicitVarSizeWithDummy[q40] = x_ExplicitVarSizeWithMarker_Values[q38] + | q40 : int(1..4)]) + | q38 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q42] != 5 -> + or([q44 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q44] = x_ExplicitVarSizeWithDummy[q42] + | q44 : int(1..4)]) + | q42 : int(1..4)]), + and([q46 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithFlags_Flags[q48] /\ + x_ExplicitVarSizeWithFlags_Values[q48] = x_ExplicitVarSizeWithMarker_Values[q46] + | q48 : int(1..4)]) + | q46 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q50] -> + or([q52 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q52] = x_ExplicitVarSizeWithFlags_Values[q50] + | q52 : int(1..4)]) + | q50 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set06/expected/model_1_3_1_1-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_1_3_1_1-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_1_3_1_1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_1_3_1_1-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_1_3_1_1-solution000002.solution new file mode 100644 index 0000000000..85149821f6 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_1_3_1_1-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_1_3_1_1.eprime b/tests/exhaustive/basic/set06/expected/model_1_3_1_1.eprime new file mode 100644 index 0000000000..534888a487 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_1_3_1_1.eprime @@ -0,0 +1,22 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +branching on [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_Occurrence] +such that + x_Occurrence[1], + or([q11 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q11] = 2 | q11 : int(1..4)]), + x_Occurrence[3], + sum([toInt(x_Occurrence[q1]) | q1 : int(1..4)]) <= 4, + and([q2 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q2] < x_ExplicitVarSizeWithMarker_Values[q2 + 1] + | q2 : int(1..3)]), + and([q3 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q3] = 1 | q3 : int(1..4)]), + x_ExplicitVarSizeWithMarker_Marker <= 4, + and([q6 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q6]] + | q6 : int(1..4)]), + and([x_Occurrence[q7] -> + or([q9 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q9] = q7 | q9 : int(1..4)]) + | q7 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set06/expected/model_1_3_1_2-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_1_3_1_2-solution000001.solution new file mode 100644 index 0000000000..85149821f6 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_1_3_1_2-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_1_3_1_2-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_1_3_1_2-solution000002.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_1_3_1_2-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_1_3_1_2.eprime b/tests/exhaustive/basic/set06/expected/model_1_3_1_2.eprime new file mode 100644 index 0000000000..3a488b51f2 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_1_3_1_2.eprime @@ -0,0 +1,42 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +branching on + [x_ExplicitVarSizeWithDummy, x_Occurrence, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] +such that + x_Occurrence[1], + or([q28 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q28] = 2 | q28 : int(1..4)]), + x_Occurrence[3], + sum([toInt(x_Occurrence[q1]) | q1 : int(1..4)]) <= 4, + and([q2 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q2] < x_ExplicitVarSizeWithMarker_Values[q2 + 1] + | q2 : int(1..3)]), + and([q3 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q3] = 1 | q3 : int(1..4)]), + x_ExplicitVarSizeWithMarker_Marker <= 4, + and([q6 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q6]] + | q6 : int(1..4)]), + and([x_Occurrence[q7] -> + or([q9 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q9] = q7 | q9 : int(1..4)]) + | q7 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q10] < x_ExplicitVarSizeWithDummy[q10 + 1] \/ x_ExplicitVarSizeWithDummy[q10] = 5 + | q10 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q11] = 5 -> x_ExplicitVarSizeWithDummy[q11 + 1] = 5 | q11 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithDummy[q12] != 5) | q12 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithDummy[q15] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q15]] | q15 : int(1..4)]), + and([x_Occurrence[q16] -> + or([x_ExplicitVarSizeWithDummy[q18] != 5 /\ x_ExplicitVarSizeWithDummy[q18] = q16 | q18 : int(1..4)]) + | q16 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q20] != 5 -> + or([q22 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q22] = x_ExplicitVarSizeWithDummy[q20] + | q22 : int(1..4)]) + | q20 : int(1..4)]), + and([q24 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithDummy[q26] != 5 /\ + x_ExplicitVarSizeWithDummy[q26] = x_ExplicitVarSizeWithMarker_Values[q24] + | q26 : int(1..4)]) + | q24 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set06/expected/model_1_3_1_4-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_1_3_1_4-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_1_3_1_4-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_1_3_1_4-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_1_3_1_4-solution000002.solution new file mode 100644 index 0000000000..85149821f6 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_1_3_1_4-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_1_3_1_4.eprime b/tests/exhaustive/basic/set06/expected/model_1_3_1_4.eprime new file mode 100644 index 0000000000..c11065ed05 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_1_3_1_4.eprime @@ -0,0 +1,48 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +branching on + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_Occurrence, + x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] +such that + x_Occurrence[1], + or([q29 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q29] = 2 | q29 : int(1..4)]), + x_Occurrence[3], + sum([toInt(x_Occurrence[q1]) | q1 : int(1..4)]) <= 4, + and([q2 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q2] < x_ExplicitVarSizeWithMarker_Values[q2 + 1] + | q2 : int(1..3)]), + and([q3 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q3] = 1 | q3 : int(1..4)]), + x_ExplicitVarSizeWithMarker_Marker <= 4, + and([q6 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q6]] + | q6 : int(1..4)]), + and([x_Occurrence[q7] -> + or([q9 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q9] = q7 | q9 : int(1..4)]) + | q7 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q10 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q10] < x_ExplicitVarSizeWithFlags_Values[q10 + 1] + | q10 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q11] = false -> x_ExplicitVarSizeWithFlags_Values[q11] = 1 + | q11 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q12 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q12] | q12 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q13]) | q13 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithFlags_Flags[q16] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q16]] + | q16 : int(1..4)]), + and([x_Occurrence[q17] -> + or([x_ExplicitVarSizeWithFlags_Flags[q19] /\ x_ExplicitVarSizeWithFlags_Values[q19] = q17 | q19 : int(1..4)]) + | q17 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q21] -> + or([q23 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q23] = x_ExplicitVarSizeWithFlags_Values[q21] + | q23 : int(1..4)]) + | q21 : int(1..4)]), + and([q25 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithFlags_Flags[q27] /\ + x_ExplicitVarSizeWithFlags_Values[q27] = x_ExplicitVarSizeWithMarker_Values[q25] + | q27 : int(1..4)]) + | q25 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set06/expected/model_1_3_2_1-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_1_3_2_1-solution000001.solution new file mode 100644 index 0000000000..85149821f6 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_1_3_2_1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_1_3_2_1-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_1_3_2_1-solution000002.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_1_3_2_1-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_1_3_2_1.eprime b/tests/exhaustive/basic/set06/expected/model_1_3_2_1.eprime new file mode 100644 index 0000000000..1df703b36a --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_1_3_2_1.eprime @@ -0,0 +1,42 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +branching on + [x_ExplicitVarSizeWithDummy, x_Occurrence, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] +such that + x_Occurrence[1], + or([q28 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q28] = 2 | q28 : int(1..4)]), + or([x_ExplicitVarSizeWithDummy[q30] != 5 /\ x_ExplicitVarSizeWithDummy[q30] = 3 | q30 : int(1..4)]), + sum([toInt(x_Occurrence[q1]) | q1 : int(1..4)]) <= 4, + and([q2 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q2] < x_ExplicitVarSizeWithMarker_Values[q2 + 1] + | q2 : int(1..3)]), + and([q3 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q3] = 1 | q3 : int(1..4)]), + x_ExplicitVarSizeWithMarker_Marker <= 4, + and([q6 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q6]] + | q6 : int(1..4)]), + and([x_Occurrence[q7] -> + or([q9 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q9] = q7 | q9 : int(1..4)]) + | q7 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q10] < x_ExplicitVarSizeWithDummy[q10 + 1] \/ x_ExplicitVarSizeWithDummy[q10] = 5 + | q10 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q11] = 5 -> x_ExplicitVarSizeWithDummy[q11 + 1] = 5 | q11 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithDummy[q12] != 5) | q12 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithDummy[q15] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q15]] | q15 : int(1..4)]), + and([x_Occurrence[q16] -> + or([x_ExplicitVarSizeWithDummy[q18] != 5 /\ x_ExplicitVarSizeWithDummy[q18] = q16 | q18 : int(1..4)]) + | q16 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q20] != 5 -> + or([q22 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q22] = x_ExplicitVarSizeWithDummy[q20] + | q22 : int(1..4)]) + | q20 : int(1..4)]), + and([q24 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithDummy[q26] != 5 /\ + x_ExplicitVarSizeWithDummy[q26] = x_ExplicitVarSizeWithMarker_Values[q24] + | q26 : int(1..4)]) + | q24 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set06/expected/model_1_3_2_4-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_1_3_2_4-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_1_3_2_4-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_1_3_2_4-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_1_3_2_4-solution000002.solution new file mode 100644 index 0000000000..85149821f6 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_1_3_2_4-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_1_3_2_4.eprime b/tests/exhaustive/basic/set06/expected/model_1_3_2_4.eprime new file mode 100644 index 0000000000..d71d427457 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_1_3_2_4.eprime @@ -0,0 +1,77 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +branching on + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_Occurrence, + x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy] +such that + x_Occurrence[1], + or([q54 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q54] = 2 | q54 : int(1..4)]), + or([x_ExplicitVarSizeWithDummy[q56] != 5 /\ x_ExplicitVarSizeWithDummy[q56] = 3 | q56 : int(1..4)]), + sum([toInt(x_Occurrence[q1]) | q1 : int(1..4)]) <= 4, + and([q2 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q2] < x_ExplicitVarSizeWithMarker_Values[q2 + 1] + | q2 : int(1..3)]), + and([q3 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q3] = 1 | q3 : int(1..4)]), + x_ExplicitVarSizeWithMarker_Marker <= 4, + and([q6 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q6]] + | q6 : int(1..4)]), + and([x_Occurrence[q7] -> + or([q9 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q9] = q7 | q9 : int(1..4)]) + | q7 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q10] < x_ExplicitVarSizeWithDummy[q10 + 1] \/ x_ExplicitVarSizeWithDummy[q10] = 5 + | q10 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q11] = 5 -> x_ExplicitVarSizeWithDummy[q11 + 1] = 5 | q11 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithDummy[q12] != 5) | q12 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithDummy[q15] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q15]] | q15 : int(1..4)]), + and([x_Occurrence[q16] -> + or([x_ExplicitVarSizeWithDummy[q18] != 5 /\ x_ExplicitVarSizeWithDummy[q18] = q16 | q18 : int(1..4)]) + | q16 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q20] != 5 -> + or([q22 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q22] = x_ExplicitVarSizeWithDummy[q20] + | q22 : int(1..4)]) + | q20 : int(1..4)]), + and([q24 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithDummy[q26] != 5 /\ + x_ExplicitVarSizeWithDummy[q26] = x_ExplicitVarSizeWithMarker_Values[q24] + | q26 : int(1..4)]) + | q24 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q27 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q27] < x_ExplicitVarSizeWithFlags_Values[q27 + 1] + | q27 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q28] = false -> x_ExplicitVarSizeWithFlags_Values[q28] = 1 + | q28 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q29 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q29] | q29 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q30]) | q30 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithFlags_Flags[q33] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q33]] + | q33 : int(1..4)]), + and([x_Occurrence[q34] -> + or([x_ExplicitVarSizeWithFlags_Flags[q36] /\ x_ExplicitVarSizeWithFlags_Values[q36] = q34 | q36 : int(1..4)]) + | q34 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q38] -> + or([q40 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q40] = x_ExplicitVarSizeWithFlags_Values[q38] + | q40 : int(1..4)]) + | q38 : int(1..4)]), + and([q42 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithFlags_Flags[q44] /\ + x_ExplicitVarSizeWithFlags_Values[q44] = x_ExplicitVarSizeWithMarker_Values[q42] + | q44 : int(1..4)]) + | q42 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q46] -> + or([x_ExplicitVarSizeWithDummy[q48] != 5 /\ + x_ExplicitVarSizeWithDummy[q48] = x_ExplicitVarSizeWithFlags_Values[q46] + | q48 : int(1..4)]) + | q46 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q50] != 5 -> + or([x_ExplicitVarSizeWithFlags_Flags[q52] /\ + x_ExplicitVarSizeWithFlags_Values[q52] = x_ExplicitVarSizeWithDummy[q50] + | q52 : int(1..4)]) + | q50 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set06/expected/model_1_3_3_1-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_1_3_3_1-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_1_3_3_1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_1_3_3_1-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_1_3_3_1-solution000002.solution new file mode 100644 index 0000000000..85149821f6 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_1_3_3_1-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_1_3_3_1.eprime b/tests/exhaustive/basic/set06/expected/model_1_3_3_1.eprime new file mode 100644 index 0000000000..10616f2d34 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_1_3_3_1.eprime @@ -0,0 +1,22 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +branching on [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_Occurrence] +such that + x_Occurrence[1], + or([q11 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q11] = 2 | q11 : int(1..4)]), + or([q13 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q13] = 3 | q13 : int(1..4)]), + sum([toInt(x_Occurrence[q1]) | q1 : int(1..4)]) <= 4, + and([q2 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q2] < x_ExplicitVarSizeWithMarker_Values[q2 + 1] + | q2 : int(1..3)]), + and([q3 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q3] = 1 | q3 : int(1..4)]), + x_ExplicitVarSizeWithMarker_Marker <= 4, + and([q6 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q6]] + | q6 : int(1..4)]), + and([x_Occurrence[q7] -> + or([q9 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q9] = q7 | q9 : int(1..4)]) + | q7 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set06/expected/model_1_3_3_2-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_1_3_3_2-solution000001.solution new file mode 100644 index 0000000000..85149821f6 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_1_3_3_2-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_1_3_3_2-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_1_3_3_2-solution000002.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_1_3_3_2-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_1_3_3_2.eprime b/tests/exhaustive/basic/set06/expected/model_1_3_3_2.eprime new file mode 100644 index 0000000000..0a6a65be24 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_1_3_3_2.eprime @@ -0,0 +1,42 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +branching on + [x_ExplicitVarSizeWithDummy, x_Occurrence, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] +such that + x_Occurrence[1], + or([q28 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q28] = 2 | q28 : int(1..4)]), + or([q30 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q30] = 3 | q30 : int(1..4)]), + sum([toInt(x_Occurrence[q1]) | q1 : int(1..4)]) <= 4, + and([q2 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q2] < x_ExplicitVarSizeWithMarker_Values[q2 + 1] + | q2 : int(1..3)]), + and([q3 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q3] = 1 | q3 : int(1..4)]), + x_ExplicitVarSizeWithMarker_Marker <= 4, + and([q6 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q6]] + | q6 : int(1..4)]), + and([x_Occurrence[q7] -> + or([q9 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q9] = q7 | q9 : int(1..4)]) + | q7 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q10] < x_ExplicitVarSizeWithDummy[q10 + 1] \/ x_ExplicitVarSizeWithDummy[q10] = 5 + | q10 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q11] = 5 -> x_ExplicitVarSizeWithDummy[q11 + 1] = 5 | q11 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithDummy[q12] != 5) | q12 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithDummy[q15] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q15]] | q15 : int(1..4)]), + and([x_Occurrence[q16] -> + or([x_ExplicitVarSizeWithDummy[q18] != 5 /\ x_ExplicitVarSizeWithDummy[q18] = q16 | q18 : int(1..4)]) + | q16 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q20] != 5 -> + or([q22 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q22] = x_ExplicitVarSizeWithDummy[q20] + | q22 : int(1..4)]) + | q20 : int(1..4)]), + and([q24 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithDummy[q26] != 5 /\ + x_ExplicitVarSizeWithDummy[q26] = x_ExplicitVarSizeWithMarker_Values[q24] + | q26 : int(1..4)]) + | q24 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set06/expected/model_1_3_3_4-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_1_3_3_4-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_1_3_3_4-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_1_3_3_4-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_1_3_3_4-solution000002.solution new file mode 100644 index 0000000000..85149821f6 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_1_3_3_4-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_1_3_3_4.eprime b/tests/exhaustive/basic/set06/expected/model_1_3_3_4.eprime new file mode 100644 index 0000000000..0d2728b93c --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_1_3_3_4.eprime @@ -0,0 +1,48 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +branching on + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_Occurrence, + x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] +such that + x_Occurrence[1], + or([q29 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q29] = 2 | q29 : int(1..4)]), + or([q31 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q31] = 3 | q31 : int(1..4)]), + sum([toInt(x_Occurrence[q1]) | q1 : int(1..4)]) <= 4, + and([q2 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q2] < x_ExplicitVarSizeWithMarker_Values[q2 + 1] + | q2 : int(1..3)]), + and([q3 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q3] = 1 | q3 : int(1..4)]), + x_ExplicitVarSizeWithMarker_Marker <= 4, + and([q6 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q6]] + | q6 : int(1..4)]), + and([x_Occurrence[q7] -> + or([q9 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q9] = q7 | q9 : int(1..4)]) + | q7 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q10 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q10] < x_ExplicitVarSizeWithFlags_Values[q10 + 1] + | q10 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q11] = false -> x_ExplicitVarSizeWithFlags_Values[q11] = 1 + | q11 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q12 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q12] | q12 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q13]) | q13 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithFlags_Flags[q16] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q16]] + | q16 : int(1..4)]), + and([x_Occurrence[q17] -> + or([x_ExplicitVarSizeWithFlags_Flags[q19] /\ x_ExplicitVarSizeWithFlags_Values[q19] = q17 | q19 : int(1..4)]) + | q17 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q21] -> + or([q23 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q23] = x_ExplicitVarSizeWithFlags_Values[q21] + | q23 : int(1..4)]) + | q21 : int(1..4)]), + and([q25 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithFlags_Flags[q27] /\ + x_ExplicitVarSizeWithFlags_Values[q27] = x_ExplicitVarSizeWithMarker_Values[q25] + | q27 : int(1..4)]) + | q25 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set06/expected/model_1_3_4_1-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_1_3_4_1-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_1_3_4_1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_1_3_4_1-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_1_3_4_1-solution000002.solution new file mode 100644 index 0000000000..85149821f6 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_1_3_4_1-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_1_3_4_1.eprime b/tests/exhaustive/basic/set06/expected/model_1_3_4_1.eprime new file mode 100644 index 0000000000..73b9732e42 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_1_3_4_1.eprime @@ -0,0 +1,48 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +branching on + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_Occurrence, + x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] +such that + x_Occurrence[1], + or([q29 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q29] = 2 | q29 : int(1..4)]), + or([x_ExplicitVarSizeWithFlags_Flags[q31] /\ x_ExplicitVarSizeWithFlags_Values[q31] = 3 | q31 : int(1..4)]), + sum([toInt(x_Occurrence[q1]) | q1 : int(1..4)]) <= 4, + and([q2 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q2] < x_ExplicitVarSizeWithMarker_Values[q2 + 1] + | q2 : int(1..3)]), + and([q3 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q3] = 1 | q3 : int(1..4)]), + x_ExplicitVarSizeWithMarker_Marker <= 4, + and([q6 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q6]] + | q6 : int(1..4)]), + and([x_Occurrence[q7] -> + or([q9 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q9] = q7 | q9 : int(1..4)]) + | q7 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q10 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q10] < x_ExplicitVarSizeWithFlags_Values[q10 + 1] + | q10 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q11] = false -> x_ExplicitVarSizeWithFlags_Values[q11] = 1 + | q11 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q12 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q12] | q12 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q13]) | q13 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithFlags_Flags[q16] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q16]] + | q16 : int(1..4)]), + and([x_Occurrence[q17] -> + or([x_ExplicitVarSizeWithFlags_Flags[q19] /\ x_ExplicitVarSizeWithFlags_Values[q19] = q17 | q19 : int(1..4)]) + | q17 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q21] -> + or([q23 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q23] = x_ExplicitVarSizeWithFlags_Values[q21] + | q23 : int(1..4)]) + | q21 : int(1..4)]), + and([q25 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithFlags_Flags[q27] /\ + x_ExplicitVarSizeWithFlags_Values[q27] = x_ExplicitVarSizeWithMarker_Values[q25] + | q27 : int(1..4)]) + | q25 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set06/expected/model_1_3_4_2-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_1_3_4_2-solution000001.solution new file mode 100644 index 0000000000..85149821f6 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_1_3_4_2-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_1_3_4_2-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_1_3_4_2-solution000002.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_1_3_4_2-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_1_3_4_2.eprime b/tests/exhaustive/basic/set06/expected/model_1_3_4_2.eprime new file mode 100644 index 0000000000..1c2efaa35b --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_1_3_4_2.eprime @@ -0,0 +1,77 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +branching on + [x_ExplicitVarSizeWithDummy, x_Occurrence, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, + x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] +such that + x_Occurrence[1], + or([q54 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q54] = 2 | q54 : int(1..4)]), + or([x_ExplicitVarSizeWithFlags_Flags[q56] /\ x_ExplicitVarSizeWithFlags_Values[q56] = 3 | q56 : int(1..4)]), + sum([toInt(x_Occurrence[q1]) | q1 : int(1..4)]) <= 4, + and([q2 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q2] < x_ExplicitVarSizeWithMarker_Values[q2 + 1] + | q2 : int(1..3)]), + and([q3 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q3] = 1 | q3 : int(1..4)]), + x_ExplicitVarSizeWithMarker_Marker <= 4, + and([q6 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q6]] + | q6 : int(1..4)]), + and([x_Occurrence[q7] -> + or([q9 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q9] = q7 | q9 : int(1..4)]) + | q7 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q10 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q10] < x_ExplicitVarSizeWithFlags_Values[q10 + 1] + | q10 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q11] = false -> x_ExplicitVarSizeWithFlags_Values[q11] = 1 + | q11 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q12 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q12] | q12 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q13]) | q13 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithFlags_Flags[q16] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q16]] + | q16 : int(1..4)]), + and([x_Occurrence[q17] -> + or([x_ExplicitVarSizeWithFlags_Flags[q19] /\ x_ExplicitVarSizeWithFlags_Values[q19] = q17 | q19 : int(1..4)]) + | q17 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q21] -> + or([q23 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q23] = x_ExplicitVarSizeWithFlags_Values[q21] + | q23 : int(1..4)]) + | q21 : int(1..4)]), + and([q25 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithFlags_Flags[q27] /\ + x_ExplicitVarSizeWithFlags_Values[q27] = x_ExplicitVarSizeWithMarker_Values[q25] + | q27 : int(1..4)]) + | q25 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q28] < x_ExplicitVarSizeWithDummy[q28 + 1] \/ x_ExplicitVarSizeWithDummy[q28] = 5 + | q28 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q29] = 5 -> x_ExplicitVarSizeWithDummy[q29 + 1] = 5 | q29 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithDummy[q30] != 5) | q30 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithDummy[q33] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q33]] | q33 : int(1..4)]), + and([x_Occurrence[q34] -> + or([x_ExplicitVarSizeWithDummy[q36] != 5 /\ x_ExplicitVarSizeWithDummy[q36] = q34 | q36 : int(1..4)]) + | q34 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q38] != 5 -> + or([q40 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q40] = x_ExplicitVarSizeWithDummy[q38] + | q40 : int(1..4)]) + | q38 : int(1..4)]), + and([q42 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithDummy[q44] != 5 /\ + x_ExplicitVarSizeWithDummy[q44] = x_ExplicitVarSizeWithMarker_Values[q42] + | q44 : int(1..4)]) + | q42 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q46] != 5 -> + or([x_ExplicitVarSizeWithFlags_Flags[q48] /\ + x_ExplicitVarSizeWithFlags_Values[q48] = x_ExplicitVarSizeWithDummy[q46] + | q48 : int(1..4)]) + | q46 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q50] -> + or([x_ExplicitVarSizeWithDummy[q52] != 5 /\ + x_ExplicitVarSizeWithDummy[q52] = x_ExplicitVarSizeWithFlags_Values[q50] + | q52 : int(1..4)]) + | q50 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set06/expected/model_1_4_1_1-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_1_4_1_1-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_1_4_1_1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_1_4_1_1-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_1_4_1_1-solution000002.solution new file mode 100644 index 0000000000..85149821f6 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_1_4_1_1-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_1_4_1_1.eprime b/tests/exhaustive/basic/set06/expected/model_1_4_1_1.eprime new file mode 100644 index 0000000000..d01150a180 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_1_4_1_1.eprime @@ -0,0 +1,22 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +branching on [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_Occurrence] +such that + x_Occurrence[1], + or([x_ExplicitVarSizeWithFlags_Flags[q13] /\ x_ExplicitVarSizeWithFlags_Values[q13] = 2 | q13 : int(1..4)]), + x_Occurrence[3], + sum([toInt(x_Occurrence[q1]) | q1 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithFlags_Flags[q2 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q2] < x_ExplicitVarSizeWithFlags_Values[q2 + 1] + | q2 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q3] = false -> x_ExplicitVarSizeWithFlags_Values[q3] = 1 | q3 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q4] | q4 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q5]) | q5 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithFlags_Flags[q8] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q8]] | q8 : int(1..4)]), + and([x_Occurrence[q9] -> + or([x_ExplicitVarSizeWithFlags_Flags[q11] /\ x_ExplicitVarSizeWithFlags_Values[q11] = q9 | q11 : int(1..4)]) + | q9 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set06/expected/model_1_4_1_2-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_1_4_1_2-solution000001.solution new file mode 100644 index 0000000000..85149821f6 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_1_4_1_2-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_1_4_1_2-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_1_4_1_2-solution000002.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_1_4_1_2-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_1_4_1_2.eprime b/tests/exhaustive/basic/set06/expected/model_1_4_1_2.eprime new file mode 100644 index 0000000000..dd23a21391 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_1_4_1_2.eprime @@ -0,0 +1,42 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +branching on + [x_ExplicitVarSizeWithDummy, x_Occurrence, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] +such that + x_Occurrence[1], + or([x_ExplicitVarSizeWithFlags_Flags[q30] /\ x_ExplicitVarSizeWithFlags_Values[q30] = 2 | q30 : int(1..4)]), + x_Occurrence[3], + sum([toInt(x_Occurrence[q1]) | q1 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithFlags_Flags[q2 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q2] < x_ExplicitVarSizeWithFlags_Values[q2 + 1] + | q2 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q3] = false -> x_ExplicitVarSizeWithFlags_Values[q3] = 1 | q3 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q4] | q4 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q5]) | q5 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithFlags_Flags[q8] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q8]] | q8 : int(1..4)]), + and([x_Occurrence[q9] -> + or([x_ExplicitVarSizeWithFlags_Flags[q11] /\ x_ExplicitVarSizeWithFlags_Values[q11] = q9 | q11 : int(1..4)]) + | q9 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q12] < x_ExplicitVarSizeWithDummy[q12 + 1] \/ x_ExplicitVarSizeWithDummy[q12] = 5 + | q12 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q13] = 5 -> x_ExplicitVarSizeWithDummy[q13 + 1] = 5 | q13 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithDummy[q14] != 5) | q14 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithDummy[q17] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q17]] | q17 : int(1..4)]), + and([x_Occurrence[q18] -> + or([x_ExplicitVarSizeWithDummy[q20] != 5 /\ x_ExplicitVarSizeWithDummy[q20] = q18 | q20 : int(1..4)]) + | q18 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q22] != 5 -> + or([x_ExplicitVarSizeWithFlags_Flags[q24] /\ + x_ExplicitVarSizeWithFlags_Values[q24] = x_ExplicitVarSizeWithDummy[q22] + | q24 : int(1..4)]) + | q22 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q26] -> + or([x_ExplicitVarSizeWithDummy[q28] != 5 /\ + x_ExplicitVarSizeWithDummy[q28] = x_ExplicitVarSizeWithFlags_Values[q26] + | q28 : int(1..4)]) + | q26 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set06/expected/model_1_4_1_3-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_1_4_1_3-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_1_4_1_3-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_1_4_1_3-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_1_4_1_3-solution000002.solution new file mode 100644 index 0000000000..85149821f6 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_1_4_1_3-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_1_4_1_3.eprime b/tests/exhaustive/basic/set06/expected/model_1_4_1_3.eprime new file mode 100644 index 0000000000..a6b5c001d1 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_1_4_1_3.eprime @@ -0,0 +1,47 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +branching on + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_Occurrence, + x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] +such that + x_Occurrence[1], + or([x_ExplicitVarSizeWithFlags_Flags[q29] /\ x_ExplicitVarSizeWithFlags_Values[q29] = 2 | q29 : int(1..4)]), + x_Occurrence[3], + sum([toInt(x_Occurrence[q1]) | q1 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithFlags_Flags[q2 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q2] < x_ExplicitVarSizeWithFlags_Values[q2 + 1] + | q2 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q3] = false -> x_ExplicitVarSizeWithFlags_Values[q3] = 1 | q3 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q4] | q4 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q5]) | q5 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithFlags_Flags[q8] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q8]] | q8 : int(1..4)]), + and([x_Occurrence[q9] -> + or([x_ExplicitVarSizeWithFlags_Flags[q11] /\ x_ExplicitVarSizeWithFlags_Values[q11] = q9 | q11 : int(1..4)]) + | q9 : int(1..4)]), + and([q12 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q12] < x_ExplicitVarSizeWithMarker_Values[q12 + 1] + | q12 : int(1..3)]), + and([q13 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q13] = 1 | q13 : int(1..4)]), + x_ExplicitVarSizeWithMarker_Marker <= 4, + and([q16 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q16]] + | q16 : int(1..4)]), + and([x_Occurrence[q17] -> + or([q19 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q19] = q17 + | q19 : int(1..4)]) + | q17 : int(1..4)]), + and([q21 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithFlags_Flags[q23] /\ + x_ExplicitVarSizeWithFlags_Values[q23] = x_ExplicitVarSizeWithMarker_Values[q21] + | q23 : int(1..4)]) + | q21 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q25] -> + or([q27 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q27] = x_ExplicitVarSizeWithFlags_Values[q25] + | q27 : int(1..4)]) + | q25 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set06/expected/model_1_4_2_1-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_1_4_2_1-solution000001.solution new file mode 100644 index 0000000000..85149821f6 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_1_4_2_1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_1_4_2_1-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_1_4_2_1-solution000002.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_1_4_2_1-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_1_4_2_1.eprime b/tests/exhaustive/basic/set06/expected/model_1_4_2_1.eprime new file mode 100644 index 0000000000..551631d48b --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_1_4_2_1.eprime @@ -0,0 +1,42 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +branching on + [x_ExplicitVarSizeWithDummy, x_Occurrence, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] +such that + x_Occurrence[1], + or([x_ExplicitVarSizeWithFlags_Flags[q30] /\ x_ExplicitVarSizeWithFlags_Values[q30] = 2 | q30 : int(1..4)]), + or([x_ExplicitVarSizeWithDummy[q32] != 5 /\ x_ExplicitVarSizeWithDummy[q32] = 3 | q32 : int(1..4)]), + sum([toInt(x_Occurrence[q1]) | q1 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithFlags_Flags[q2 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q2] < x_ExplicitVarSizeWithFlags_Values[q2 + 1] + | q2 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q3] = false -> x_ExplicitVarSizeWithFlags_Values[q3] = 1 | q3 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q4] | q4 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q5]) | q5 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithFlags_Flags[q8] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q8]] | q8 : int(1..4)]), + and([x_Occurrence[q9] -> + or([x_ExplicitVarSizeWithFlags_Flags[q11] /\ x_ExplicitVarSizeWithFlags_Values[q11] = q9 | q11 : int(1..4)]) + | q9 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q12] < x_ExplicitVarSizeWithDummy[q12 + 1] \/ x_ExplicitVarSizeWithDummy[q12] = 5 + | q12 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q13] = 5 -> x_ExplicitVarSizeWithDummy[q13 + 1] = 5 | q13 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithDummy[q14] != 5) | q14 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithDummy[q17] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q17]] | q17 : int(1..4)]), + and([x_Occurrence[q18] -> + or([x_ExplicitVarSizeWithDummy[q20] != 5 /\ x_ExplicitVarSizeWithDummy[q20] = q18 | q20 : int(1..4)]) + | q18 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q22] != 5 -> + or([x_ExplicitVarSizeWithFlags_Flags[q24] /\ + x_ExplicitVarSizeWithFlags_Values[q24] = x_ExplicitVarSizeWithDummy[q22] + | q24 : int(1..4)]) + | q22 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q26] -> + or([x_ExplicitVarSizeWithDummy[q28] != 5 /\ + x_ExplicitVarSizeWithDummy[q28] = x_ExplicitVarSizeWithFlags_Values[q26] + | q28 : int(1..4)]) + | q26 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set06/expected/model_1_4_2_3-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_1_4_2_3-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_1_4_2_3-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_1_4_2_3-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_1_4_2_3-solution000002.solution new file mode 100644 index 0000000000..85149821f6 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_1_4_2_3-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_1_4_2_3.eprime b/tests/exhaustive/basic/set06/expected/model_1_4_2_3.eprime new file mode 100644 index 0000000000..380d82c5c6 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_1_4_2_3.eprime @@ -0,0 +1,76 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +branching on + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_Occurrence, + x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy] +such that + x_Occurrence[1], + or([x_ExplicitVarSizeWithFlags_Flags[q54] /\ x_ExplicitVarSizeWithFlags_Values[q54] = 2 | q54 : int(1..4)]), + or([x_ExplicitVarSizeWithDummy[q56] != 5 /\ x_ExplicitVarSizeWithDummy[q56] = 3 | q56 : int(1..4)]), + sum([toInt(x_Occurrence[q1]) | q1 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithFlags_Flags[q2 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q2] < x_ExplicitVarSizeWithFlags_Values[q2 + 1] + | q2 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q3] = false -> x_ExplicitVarSizeWithFlags_Values[q3] = 1 | q3 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q4] | q4 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q5]) | q5 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithFlags_Flags[q8] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q8]] | q8 : int(1..4)]), + and([x_Occurrence[q9] -> + or([x_ExplicitVarSizeWithFlags_Flags[q11] /\ x_ExplicitVarSizeWithFlags_Values[q11] = q9 | q11 : int(1..4)]) + | q9 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q12] < x_ExplicitVarSizeWithDummy[q12 + 1] \/ x_ExplicitVarSizeWithDummy[q12] = 5 + | q12 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q13] = 5 -> x_ExplicitVarSizeWithDummy[q13 + 1] = 5 | q13 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithDummy[q14] != 5) | q14 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithDummy[q17] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q17]] | q17 : int(1..4)]), + and([x_Occurrence[q18] -> + or([x_ExplicitVarSizeWithDummy[q20] != 5 /\ x_ExplicitVarSizeWithDummy[q20] = q18 | q20 : int(1..4)]) + | q18 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q22] != 5 -> + or([x_ExplicitVarSizeWithFlags_Flags[q24] /\ + x_ExplicitVarSizeWithFlags_Values[q24] = x_ExplicitVarSizeWithDummy[q22] + | q24 : int(1..4)]) + | q22 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q26] -> + or([x_ExplicitVarSizeWithDummy[q28] != 5 /\ + x_ExplicitVarSizeWithDummy[q28] = x_ExplicitVarSizeWithFlags_Values[q26] + | q28 : int(1..4)]) + | q26 : int(1..4)]), + and([q29 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q29] < x_ExplicitVarSizeWithMarker_Values[q29 + 1] + | q29 : int(1..3)]), + and([q30 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q30] = 1 | q30 : int(1..4)]), + x_ExplicitVarSizeWithMarker_Marker <= 4, + and([q33 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q33]] + | q33 : int(1..4)]), + and([x_Occurrence[q34] -> + or([q36 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q36] = q34 + | q36 : int(1..4)]) + | q34 : int(1..4)]), + and([q38 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithFlags_Flags[q40] /\ + x_ExplicitVarSizeWithFlags_Values[q40] = x_ExplicitVarSizeWithMarker_Values[q38] + | q40 : int(1..4)]) + | q38 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q42] -> + or([q44 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q44] = x_ExplicitVarSizeWithFlags_Values[q42] + | q44 : int(1..4)]) + | q42 : int(1..4)]), + and([q46 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithDummy[q48] != 5 /\ + x_ExplicitVarSizeWithDummy[q48] = x_ExplicitVarSizeWithMarker_Values[q46] + | q48 : int(1..4)]) + | q46 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q50] != 5 -> + or([q52 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q52] = x_ExplicitVarSizeWithDummy[q50] + | q52 : int(1..4)]) + | q50 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set06/expected/model_1_4_3_1-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_1_4_3_1-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_1_4_3_1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_1_4_3_1-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_1_4_3_1-solution000002.solution new file mode 100644 index 0000000000..85149821f6 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_1_4_3_1-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_1_4_3_1.eprime b/tests/exhaustive/basic/set06/expected/model_1_4_3_1.eprime new file mode 100644 index 0000000000..f88dbdf42f --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_1_4_3_1.eprime @@ -0,0 +1,47 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +branching on + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_Occurrence, + x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] +such that + x_Occurrence[1], + or([x_ExplicitVarSizeWithFlags_Flags[q29] /\ x_ExplicitVarSizeWithFlags_Values[q29] = 2 | q29 : int(1..4)]), + or([q31 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q31] = 3 | q31 : int(1..4)]), + sum([toInt(x_Occurrence[q1]) | q1 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithFlags_Flags[q2 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q2] < x_ExplicitVarSizeWithFlags_Values[q2 + 1] + | q2 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q3] = false -> x_ExplicitVarSizeWithFlags_Values[q3] = 1 | q3 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q4] | q4 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q5]) | q5 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithFlags_Flags[q8] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q8]] | q8 : int(1..4)]), + and([x_Occurrence[q9] -> + or([x_ExplicitVarSizeWithFlags_Flags[q11] /\ x_ExplicitVarSizeWithFlags_Values[q11] = q9 | q11 : int(1..4)]) + | q9 : int(1..4)]), + and([q12 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q12] < x_ExplicitVarSizeWithMarker_Values[q12 + 1] + | q12 : int(1..3)]), + and([q13 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q13] = 1 | q13 : int(1..4)]), + x_ExplicitVarSizeWithMarker_Marker <= 4, + and([q16 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q16]] + | q16 : int(1..4)]), + and([x_Occurrence[q17] -> + or([q19 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q19] = q17 + | q19 : int(1..4)]) + | q17 : int(1..4)]), + and([q21 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithFlags_Flags[q23] /\ + x_ExplicitVarSizeWithFlags_Values[q23] = x_ExplicitVarSizeWithMarker_Values[q21] + | q23 : int(1..4)]) + | q21 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q25] -> + or([q27 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q27] = x_ExplicitVarSizeWithFlags_Values[q25] + | q27 : int(1..4)]) + | q25 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set06/expected/model_1_4_3_2-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_1_4_3_2-solution000001.solution new file mode 100644 index 0000000000..85149821f6 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_1_4_3_2-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_1_4_3_2-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_1_4_3_2-solution000002.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_1_4_3_2-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_1_4_3_2.eprime b/tests/exhaustive/basic/set06/expected/model_1_4_3_2.eprime new file mode 100644 index 0000000000..708901a3dd --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_1_4_3_2.eprime @@ -0,0 +1,76 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +branching on + [x_ExplicitVarSizeWithDummy, x_Occurrence, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, + x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] +such that + x_Occurrence[1], + or([x_ExplicitVarSizeWithFlags_Flags[q54] /\ x_ExplicitVarSizeWithFlags_Values[q54] = 2 | q54 : int(1..4)]), + or([q56 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q56] = 3 | q56 : int(1..4)]), + sum([toInt(x_Occurrence[q1]) | q1 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithFlags_Flags[q2 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q2] < x_ExplicitVarSizeWithFlags_Values[q2 + 1] + | q2 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q3] = false -> x_ExplicitVarSizeWithFlags_Values[q3] = 1 | q3 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q4] | q4 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q5]) | q5 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithFlags_Flags[q8] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q8]] | q8 : int(1..4)]), + and([x_Occurrence[q9] -> + or([x_ExplicitVarSizeWithFlags_Flags[q11] /\ x_ExplicitVarSizeWithFlags_Values[q11] = q9 | q11 : int(1..4)]) + | q9 : int(1..4)]), + and([q12 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q12] < x_ExplicitVarSizeWithMarker_Values[q12 + 1] + | q12 : int(1..3)]), + and([q13 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q13] = 1 | q13 : int(1..4)]), + x_ExplicitVarSizeWithMarker_Marker <= 4, + and([q16 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q16]] + | q16 : int(1..4)]), + and([x_Occurrence[q17] -> + or([q19 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q19] = q17 + | q19 : int(1..4)]) + | q17 : int(1..4)]), + and([q21 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithFlags_Flags[q23] /\ + x_ExplicitVarSizeWithFlags_Values[q23] = x_ExplicitVarSizeWithMarker_Values[q21] + | q23 : int(1..4)]) + | q21 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q25] -> + or([q27 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q27] = x_ExplicitVarSizeWithFlags_Values[q25] + | q27 : int(1..4)]) + | q25 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q28] < x_ExplicitVarSizeWithDummy[q28 + 1] \/ x_ExplicitVarSizeWithDummy[q28] = 5 + | q28 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q29] = 5 -> x_ExplicitVarSizeWithDummy[q29 + 1] = 5 | q29 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithDummy[q30] != 5) | q30 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithDummy[q33] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q33]] | q33 : int(1..4)]), + and([x_Occurrence[q34] -> + or([x_ExplicitVarSizeWithDummy[q36] != 5 /\ x_ExplicitVarSizeWithDummy[q36] = q34 | q36 : int(1..4)]) + | q34 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q38] != 5 -> + or([x_ExplicitVarSizeWithFlags_Flags[q40] /\ + x_ExplicitVarSizeWithFlags_Values[q40] = x_ExplicitVarSizeWithDummy[q38] + | q40 : int(1..4)]) + | q38 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q42] -> + or([x_ExplicitVarSizeWithDummy[q44] != 5 /\ + x_ExplicitVarSizeWithDummy[q44] = x_ExplicitVarSizeWithFlags_Values[q42] + | q44 : int(1..4)]) + | q42 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q46] != 5 -> + or([q48 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q48] = x_ExplicitVarSizeWithDummy[q46] + | q48 : int(1..4)]) + | q46 : int(1..4)]), + and([q50 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithDummy[q52] != 5 /\ + x_ExplicitVarSizeWithDummy[q52] = x_ExplicitVarSizeWithMarker_Values[q50] + | q52 : int(1..4)]) + | q50 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set06/expected/model_1_4_4_1-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_1_4_4_1-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_1_4_4_1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_1_4_4_1-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_1_4_4_1-solution000002.solution new file mode 100644 index 0000000000..85149821f6 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_1_4_4_1-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_1_4_4_1.eprime b/tests/exhaustive/basic/set06/expected/model_1_4_4_1.eprime new file mode 100644 index 0000000000..3ed6afb03d --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_1_4_4_1.eprime @@ -0,0 +1,22 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +branching on [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_Occurrence] +such that + x_Occurrence[1], + or([x_ExplicitVarSizeWithFlags_Flags[q13] /\ x_ExplicitVarSizeWithFlags_Values[q13] = 2 | q13 : int(1..4)]), + or([x_ExplicitVarSizeWithFlags_Flags[q15] /\ x_ExplicitVarSizeWithFlags_Values[q15] = 3 | q15 : int(1..4)]), + sum([toInt(x_Occurrence[q1]) | q1 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithFlags_Flags[q2 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q2] < x_ExplicitVarSizeWithFlags_Values[q2 + 1] + | q2 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q3] = false -> x_ExplicitVarSizeWithFlags_Values[q3] = 1 | q3 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q4] | q4 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q5]) | q5 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithFlags_Flags[q8] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q8]] | q8 : int(1..4)]), + and([x_Occurrence[q9] -> + or([x_ExplicitVarSizeWithFlags_Flags[q11] /\ x_ExplicitVarSizeWithFlags_Values[q11] = q9 | q11 : int(1..4)]) + | q9 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set06/expected/model_1_4_4_2-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_1_4_4_2-solution000001.solution new file mode 100644 index 0000000000..85149821f6 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_1_4_4_2-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_1_4_4_2-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_1_4_4_2-solution000002.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_1_4_4_2-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_1_4_4_2.eprime b/tests/exhaustive/basic/set06/expected/model_1_4_4_2.eprime new file mode 100644 index 0000000000..a5be74d4e9 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_1_4_4_2.eprime @@ -0,0 +1,42 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +branching on + [x_ExplicitVarSizeWithDummy, x_Occurrence, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] +such that + x_Occurrence[1], + or([x_ExplicitVarSizeWithFlags_Flags[q30] /\ x_ExplicitVarSizeWithFlags_Values[q30] = 2 | q30 : int(1..4)]), + or([x_ExplicitVarSizeWithFlags_Flags[q32] /\ x_ExplicitVarSizeWithFlags_Values[q32] = 3 | q32 : int(1..4)]), + sum([toInt(x_Occurrence[q1]) | q1 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithFlags_Flags[q2 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q2] < x_ExplicitVarSizeWithFlags_Values[q2 + 1] + | q2 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q3] = false -> x_ExplicitVarSizeWithFlags_Values[q3] = 1 | q3 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q4] | q4 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q5]) | q5 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithFlags_Flags[q8] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q8]] | q8 : int(1..4)]), + and([x_Occurrence[q9] -> + or([x_ExplicitVarSizeWithFlags_Flags[q11] /\ x_ExplicitVarSizeWithFlags_Values[q11] = q9 | q11 : int(1..4)]) + | q9 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q12] < x_ExplicitVarSizeWithDummy[q12 + 1] \/ x_ExplicitVarSizeWithDummy[q12] = 5 + | q12 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q13] = 5 -> x_ExplicitVarSizeWithDummy[q13 + 1] = 5 | q13 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithDummy[q14] != 5) | q14 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithDummy[q17] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q17]] | q17 : int(1..4)]), + and([x_Occurrence[q18] -> + or([x_ExplicitVarSizeWithDummy[q20] != 5 /\ x_ExplicitVarSizeWithDummy[q20] = q18 | q20 : int(1..4)]) + | q18 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q22] != 5 -> + or([x_ExplicitVarSizeWithFlags_Flags[q24] /\ + x_ExplicitVarSizeWithFlags_Values[q24] = x_ExplicitVarSizeWithDummy[q22] + | q24 : int(1..4)]) + | q22 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q26] -> + or([x_ExplicitVarSizeWithDummy[q28] != 5 /\ + x_ExplicitVarSizeWithDummy[q28] = x_ExplicitVarSizeWithFlags_Values[q26] + | q28 : int(1..4)]) + | q26 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set06/expected/model_1_4_4_3-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_1_4_4_3-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_1_4_4_3-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_1_4_4_3-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_1_4_4_3-solution000002.solution new file mode 100644 index 0000000000..85149821f6 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_1_4_4_3-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_1_4_4_3.eprime b/tests/exhaustive/basic/set06/expected/model_1_4_4_3.eprime new file mode 100644 index 0000000000..8cdcc8bdaa --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_1_4_4_3.eprime @@ -0,0 +1,47 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +branching on + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_Occurrence, + x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] +such that + x_Occurrence[1], + or([x_ExplicitVarSizeWithFlags_Flags[q29] /\ x_ExplicitVarSizeWithFlags_Values[q29] = 2 | q29 : int(1..4)]), + or([x_ExplicitVarSizeWithFlags_Flags[q31] /\ x_ExplicitVarSizeWithFlags_Values[q31] = 3 | q31 : int(1..4)]), + sum([toInt(x_Occurrence[q1]) | q1 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithFlags_Flags[q2 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q2] < x_ExplicitVarSizeWithFlags_Values[q2 + 1] + | q2 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q3] = false -> x_ExplicitVarSizeWithFlags_Values[q3] = 1 | q3 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q4] | q4 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q5]) | q5 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithFlags_Flags[q8] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q8]] | q8 : int(1..4)]), + and([x_Occurrence[q9] -> + or([x_ExplicitVarSizeWithFlags_Flags[q11] /\ x_ExplicitVarSizeWithFlags_Values[q11] = q9 | q11 : int(1..4)]) + | q9 : int(1..4)]), + and([q12 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q12] < x_ExplicitVarSizeWithMarker_Values[q12 + 1] + | q12 : int(1..3)]), + and([q13 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q13] = 1 | q13 : int(1..4)]), + x_ExplicitVarSizeWithMarker_Marker <= 4, + and([q16 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q16]] + | q16 : int(1..4)]), + and([x_Occurrence[q17] -> + or([q19 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q19] = q17 + | q19 : int(1..4)]) + | q17 : int(1..4)]), + and([q21 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithFlags_Flags[q23] /\ + x_ExplicitVarSizeWithFlags_Values[q23] = x_ExplicitVarSizeWithMarker_Values[q21] + | q23 : int(1..4)]) + | q21 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q25] -> + or([q27 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q27] = x_ExplicitVarSizeWithFlags_Values[q25] + | q27 : int(1..4)]) + | q25 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set06/expected/model_2_1_1_1-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_2_1_1_1-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_2_1_1_1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_2_1_1_1-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_2_1_1_1-solution000002.solution new file mode 100644 index 0000000000..85149821f6 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_2_1_1_1-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_2_1_1_1.eprime b/tests/exhaustive/basic/set06/expected/model_2_1_1_1.eprime new file mode 100644 index 0000000000..1f68a56e57 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_2_1_1_1.eprime @@ -0,0 +1,19 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +find x_Occurrence: matrix indexed by [int(1..4)] of bool +branching on [x_Occurrence, x_ExplicitVarSizeWithDummy] +such that + or([x_ExplicitVarSizeWithDummy[q12] != 5 /\ x_ExplicitVarSizeWithDummy[q12] = 1 | q12 : int(1..4)]), + x_Occurrence[2], + x_Occurrence[3], + and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 5 + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q2] = 5 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 5) | q3 : int(1..4)]) <= 4, + sum([toInt(x_Occurrence[q5]) | q5 : int(1..4)]) <= 4, + and([x_Occurrence[q6] -> + or([x_ExplicitVarSizeWithDummy[q8] != 5 /\ x_ExplicitVarSizeWithDummy[q8] = q6 | q8 : int(1..4)]) + | q6 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q10] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q10]] | q10 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set06/expected/model_2_1_1_3-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_2_1_1_3-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_2_1_1_3-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_2_1_1_3-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_2_1_1_3-solution000002.solution new file mode 100644 index 0000000000..85149821f6 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_2_1_1_3-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_2_1_1_3.eprime b/tests/exhaustive/basic/set06/expected/model_2_1_1_3.eprime new file mode 100644 index 0000000000..7a02ca5f86 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_2_1_1_3.eprime @@ -0,0 +1,43 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +find x_Occurrence: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +branching on + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy, x_Occurrence] +such that + or([x_ExplicitVarSizeWithDummy[q28] != 5 /\ x_ExplicitVarSizeWithDummy[q28] = 1 | q28 : int(1..4)]), + x_Occurrence[2], + x_Occurrence[3], + and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 5 + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q2] = 5 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 5) | q3 : int(1..4)]) <= 4, + sum([toInt(x_Occurrence[q5]) | q5 : int(1..4)]) <= 4, + and([x_Occurrence[q22] -> + or([x_ExplicitVarSizeWithDummy[q24] != 5 /\ x_ExplicitVarSizeWithDummy[q24] = q22 | q24 : int(1..4)]) + | q22 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q26] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q26]] | q26 : int(1..4)]), + and([q6 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q6] < x_ExplicitVarSizeWithMarker_Values[q6 + 1] + | q6 : int(1..3)]), + and([q7 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q7] = 1 | q7 : int(1..4)]), + x_ExplicitVarSizeWithMarker_Marker <= 4, + and([q10 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithDummy[q12] != 5 /\ + x_ExplicitVarSizeWithDummy[q12] = x_ExplicitVarSizeWithMarker_Values[q10] + | q12 : int(1..4)]) + | q10 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q14] != 5 -> + or([q16 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q16] = x_ExplicitVarSizeWithDummy[q14] + | q16 : int(1..4)]) + | q14 : int(1..4)]), + and([q18 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q18]] + | q18 : int(1..4)]), + and([x_Occurrence[q19] -> + or([q21 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q21] = q19 + | q21 : int(1..4)]) + | q19 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set06/expected/model_2_1_1_4-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_2_1_1_4-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_2_1_1_4-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_2_1_1_4-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_2_1_1_4-solution000002.solution new file mode 100644 index 0000000000..85149821f6 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_2_1_1_4-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_2_1_1_4.eprime b/tests/exhaustive/basic/set06/expected/model_2_1_1_4.eprime new file mode 100644 index 0000000000..e966231466 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_2_1_1_4.eprime @@ -0,0 +1,43 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +find x_Occurrence: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +branching on + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy, x_Occurrence] +such that + or([x_ExplicitVarSizeWithDummy[q30] != 5 /\ x_ExplicitVarSizeWithDummy[q30] = 1 | q30 : int(1..4)]), + x_Occurrence[2], + x_Occurrence[3], + and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 5 + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q2] = 5 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 5) | q3 : int(1..4)]) <= 4, + sum([toInt(x_Occurrence[q5]) | q5 : int(1..4)]) <= 4, + and([x_Occurrence[q24] -> + or([x_ExplicitVarSizeWithDummy[q26] != 5 /\ x_ExplicitVarSizeWithDummy[q26] = q24 | q26 : int(1..4)]) + | q24 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q28] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q28]] | q28 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q6] < x_ExplicitVarSizeWithFlags_Values[q6 + 1] + | q6 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q7] = false -> x_ExplicitVarSizeWithFlags_Values[q7] = 1 | q7 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q8 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q8] | q8 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q9]) | q9 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithFlags_Flags[q12] -> + or([x_ExplicitVarSizeWithDummy[q14] != 5 /\ + x_ExplicitVarSizeWithDummy[q14] = x_ExplicitVarSizeWithFlags_Values[q12] + | q14 : int(1..4)]) + | q12 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q16] != 5 -> + or([x_ExplicitVarSizeWithFlags_Flags[q18] /\ + x_ExplicitVarSizeWithFlags_Values[q18] = x_ExplicitVarSizeWithDummy[q16] + | q18 : int(1..4)]) + | q16 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q20] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q20]] + | q20 : int(1..4)]), + and([x_Occurrence[q21] -> + or([x_ExplicitVarSizeWithFlags_Flags[q23] /\ x_ExplicitVarSizeWithFlags_Values[q23] = q21 | q23 : int(1..4)]) + | q21 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set06/expected/model_2_1_2_1-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_2_1_2_1-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_2_1_2_1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_2_1_2_1-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_2_1_2_1-solution000002.solution new file mode 100644 index 0000000000..85149821f6 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_2_1_2_1-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_2_1_2_1.eprime b/tests/exhaustive/basic/set06/expected/model_2_1_2_1.eprime new file mode 100644 index 0000000000..9cfdfdc9c0 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_2_1_2_1.eprime @@ -0,0 +1,19 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +find x_Occurrence: matrix indexed by [int(1..4)] of bool +branching on [x_Occurrence, x_ExplicitVarSizeWithDummy] +such that + or([x_ExplicitVarSizeWithDummy[q14] != 5 /\ x_ExplicitVarSizeWithDummy[q14] = 1 | q14 : int(1..4)]), + x_Occurrence[2], + or([x_ExplicitVarSizeWithDummy[q12] != 5 /\ x_ExplicitVarSizeWithDummy[q12] = 3 | q12 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 5 + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q2] = 5 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 5) | q3 : int(1..4)]) <= 4, + sum([toInt(x_Occurrence[q5]) | q5 : int(1..4)]) <= 4, + and([x_Occurrence[q6] -> + or([x_ExplicitVarSizeWithDummy[q8] != 5 /\ x_ExplicitVarSizeWithDummy[q8] = q6 | q8 : int(1..4)]) + | q6 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q10] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q10]] | q10 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set06/expected/model_2_1_2_3-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_2_1_2_3-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_2_1_2_3-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_2_1_2_3-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_2_1_2_3-solution000002.solution new file mode 100644 index 0000000000..85149821f6 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_2_1_2_3-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_2_1_2_3.eprime b/tests/exhaustive/basic/set06/expected/model_2_1_2_3.eprime new file mode 100644 index 0000000000..2fe1df7714 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_2_1_2_3.eprime @@ -0,0 +1,43 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +find x_Occurrence: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +branching on + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy, x_Occurrence] +such that + or([x_ExplicitVarSizeWithDummy[q30] != 5 /\ x_ExplicitVarSizeWithDummy[q30] = 1 | q30 : int(1..4)]), + x_Occurrence[2], + or([x_ExplicitVarSizeWithDummy[q28] != 5 /\ x_ExplicitVarSizeWithDummy[q28] = 3 | q28 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 5 + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q2] = 5 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 5) | q3 : int(1..4)]) <= 4, + sum([toInt(x_Occurrence[q5]) | q5 : int(1..4)]) <= 4, + and([x_Occurrence[q22] -> + or([x_ExplicitVarSizeWithDummy[q24] != 5 /\ x_ExplicitVarSizeWithDummy[q24] = q22 | q24 : int(1..4)]) + | q22 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q26] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q26]] | q26 : int(1..4)]), + and([q6 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q6] < x_ExplicitVarSizeWithMarker_Values[q6 + 1] + | q6 : int(1..3)]), + and([q7 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q7] = 1 | q7 : int(1..4)]), + x_ExplicitVarSizeWithMarker_Marker <= 4, + and([q10 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithDummy[q12] != 5 /\ + x_ExplicitVarSizeWithDummy[q12] = x_ExplicitVarSizeWithMarker_Values[q10] + | q12 : int(1..4)]) + | q10 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q14] != 5 -> + or([q16 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q16] = x_ExplicitVarSizeWithDummy[q14] + | q16 : int(1..4)]) + | q14 : int(1..4)]), + and([q18 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q18]] + | q18 : int(1..4)]), + and([x_Occurrence[q19] -> + or([q21 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q21] = q19 + | q21 : int(1..4)]) + | q19 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set06/expected/model_2_1_2_4-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_2_1_2_4-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_2_1_2_4-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_2_1_2_4-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_2_1_2_4-solution000002.solution new file mode 100644 index 0000000000..85149821f6 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_2_1_2_4-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_2_1_2_4.eprime b/tests/exhaustive/basic/set06/expected/model_2_1_2_4.eprime new file mode 100644 index 0000000000..36aec49af7 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_2_1_2_4.eprime @@ -0,0 +1,43 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +find x_Occurrence: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +branching on + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy, x_Occurrence] +such that + or([x_ExplicitVarSizeWithDummy[q32] != 5 /\ x_ExplicitVarSizeWithDummy[q32] = 1 | q32 : int(1..4)]), + x_Occurrence[2], + or([x_ExplicitVarSizeWithDummy[q25] != 5 /\ x_ExplicitVarSizeWithDummy[q25] = 3 | q25 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 5 + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q2] = 5 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 5) | q3 : int(1..4)]) <= 4, + sum([toInt(x_Occurrence[q5]) | q5 : int(1..4)]) <= 4, + and([x_Occurrence[q26] -> + or([x_ExplicitVarSizeWithDummy[q28] != 5 /\ x_ExplicitVarSizeWithDummy[q28] = q26 | q28 : int(1..4)]) + | q26 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q30] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q30]] | q30 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q6] < x_ExplicitVarSizeWithFlags_Values[q6 + 1] + | q6 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q7] = false -> x_ExplicitVarSizeWithFlags_Values[q7] = 1 | q7 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q8 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q8] | q8 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q9]) | q9 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithFlags_Flags[q12] -> + or([x_ExplicitVarSizeWithDummy[q14] != 5 /\ + x_ExplicitVarSizeWithDummy[q14] = x_ExplicitVarSizeWithFlags_Values[q12] + | q14 : int(1..4)]) + | q12 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q16] != 5 -> + or([x_ExplicitVarSizeWithFlags_Flags[q18] /\ + x_ExplicitVarSizeWithFlags_Values[q18] = x_ExplicitVarSizeWithDummy[q16] + | q18 : int(1..4)]) + | q16 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q20] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q20]] + | q20 : int(1..4)]), + and([x_Occurrence[q21] -> + or([x_ExplicitVarSizeWithFlags_Flags[q23] /\ x_ExplicitVarSizeWithFlags_Values[q23] = q21 | q23 : int(1..4)]) + | q21 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set06/expected/model_2_1_3_1-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_2_1_3_1-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_2_1_3_1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_2_1_3_1-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_2_1_3_1-solution000002.solution new file mode 100644 index 0000000000..85149821f6 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_2_1_3_1-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_2_1_3_1.eprime b/tests/exhaustive/basic/set06/expected/model_2_1_3_1.eprime new file mode 100644 index 0000000000..1efc26667b --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_2_1_3_1.eprime @@ -0,0 +1,43 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +find x_Occurrence: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +branching on + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy, x_Occurrence] +such that + or([x_ExplicitVarSizeWithDummy[q30] != 5 /\ x_ExplicitVarSizeWithDummy[q30] = 1 | q30 : int(1..4)]), + x_Occurrence[2], + or([q28 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q28] = 3 | q28 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 5 + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q2] = 5 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 5) | q3 : int(1..4)]) <= 4, + sum([toInt(x_Occurrence[q5]) | q5 : int(1..4)]) <= 4, + and([x_Occurrence[q22] -> + or([x_ExplicitVarSizeWithDummy[q24] != 5 /\ x_ExplicitVarSizeWithDummy[q24] = q22 | q24 : int(1..4)]) + | q22 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q26] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q26]] | q26 : int(1..4)]), + and([q6 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q6] < x_ExplicitVarSizeWithMarker_Values[q6 + 1] + | q6 : int(1..3)]), + and([q7 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q7] = 1 | q7 : int(1..4)]), + x_ExplicitVarSizeWithMarker_Marker <= 4, + and([q10 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithDummy[q12] != 5 /\ + x_ExplicitVarSizeWithDummy[q12] = x_ExplicitVarSizeWithMarker_Values[q10] + | q12 : int(1..4)]) + | q10 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q14] != 5 -> + or([q16 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q16] = x_ExplicitVarSizeWithDummy[q14] + | q16 : int(1..4)]) + | q14 : int(1..4)]), + and([q18 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q18]] + | q18 : int(1..4)]), + and([x_Occurrence[q19] -> + or([q21 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q21] = q19 + | q21 : int(1..4)]) + | q19 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set06/expected/model_2_1_3_4-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_2_1_3_4-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_2_1_3_4-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_2_1_3_4-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_2_1_3_4-solution000002.solution new file mode 100644 index 0000000000..85149821f6 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_2_1_3_4-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_2_1_3_4.eprime b/tests/exhaustive/basic/set06/expected/model_2_1_3_4.eprime new file mode 100644 index 0000000000..ced251790b --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_2_1_3_4.eprime @@ -0,0 +1,78 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +find x_Occurrence: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +branching on + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy, x_Occurrence, + x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] +such that + or([x_ExplicitVarSizeWithDummy[q56] != 5 /\ x_ExplicitVarSizeWithDummy[q56] = 1 | q56 : int(1..4)]), + x_Occurrence[2], + or([q49 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q49] = 3 | q49 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 5 + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q2] = 5 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 5) | q3 : int(1..4)]) <= 4, + sum([toInt(x_Occurrence[q5]) | q5 : int(1..4)]) <= 4, + and([x_Occurrence[q50] -> + or([x_ExplicitVarSizeWithDummy[q52] != 5 /\ x_ExplicitVarSizeWithDummy[q52] = q50 | q52 : int(1..4)]) + | q50 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q54] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q54]] | q54 : int(1..4)]), + and([q6 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q6] < x_ExplicitVarSizeWithMarker_Values[q6 + 1] + | q6 : int(1..3)]), + and([q7 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q7] = 1 | q7 : int(1..4)]), + x_ExplicitVarSizeWithMarker_Marker <= 4, + and([q10 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithDummy[q12] != 5 /\ + x_ExplicitVarSizeWithDummy[q12] = x_ExplicitVarSizeWithMarker_Values[q10] + | q12 : int(1..4)]) + | q10 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q14] != 5 -> + or([q16 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q16] = x_ExplicitVarSizeWithDummy[q14] + | q16 : int(1..4)]) + | q14 : int(1..4)]), + and([q18 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q18]] + | q18 : int(1..4)]), + and([x_Occurrence[q19] -> + or([q21 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q21] = q19 + | q21 : int(1..4)]) + | q19 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q22 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q22] < x_ExplicitVarSizeWithFlags_Values[q22 + 1] + | q22 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q23] = false -> x_ExplicitVarSizeWithFlags_Values[q23] = 1 + | q23 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q24 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q24] | q24 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q25]) | q25 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithFlags_Flags[q28] -> + or([x_ExplicitVarSizeWithDummy[q30] != 5 /\ + x_ExplicitVarSizeWithDummy[q30] = x_ExplicitVarSizeWithFlags_Values[q28] + | q30 : int(1..4)]) + | q28 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q32] != 5 -> + or([x_ExplicitVarSizeWithFlags_Flags[q34] /\ + x_ExplicitVarSizeWithFlags_Values[q34] = x_ExplicitVarSizeWithDummy[q32] + | q34 : int(1..4)]) + | q32 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q36] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q36]] + | q36 : int(1..4)]), + and([x_Occurrence[q37] -> + or([x_ExplicitVarSizeWithFlags_Flags[q39] /\ x_ExplicitVarSizeWithFlags_Values[q39] = q37 | q39 : int(1..4)]) + | q37 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q41] -> + or([q43 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q43] = x_ExplicitVarSizeWithFlags_Values[q41] + | q43 : int(1..4)]) + | q41 : int(1..4)]), + and([q45 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithFlags_Flags[q47] /\ + x_ExplicitVarSizeWithFlags_Values[q47] = x_ExplicitVarSizeWithMarker_Values[q45] + | q47 : int(1..4)]) + | q45 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set06/expected/model_2_1_4_1-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_2_1_4_1-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_2_1_4_1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_2_1_4_1-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_2_1_4_1-solution000002.solution new file mode 100644 index 0000000000..85149821f6 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_2_1_4_1-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_2_1_4_1.eprime b/tests/exhaustive/basic/set06/expected/model_2_1_4_1.eprime new file mode 100644 index 0000000000..4763aec36a --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_2_1_4_1.eprime @@ -0,0 +1,43 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +find x_Occurrence: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +branching on + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy, x_Occurrence] +such that + or([x_ExplicitVarSizeWithDummy[q32] != 5 /\ x_ExplicitVarSizeWithDummy[q32] = 1 | q32 : int(1..4)]), + x_Occurrence[2], + or([x_ExplicitVarSizeWithFlags_Flags[q25] /\ x_ExplicitVarSizeWithFlags_Values[q25] = 3 | q25 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 5 + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q2] = 5 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 5) | q3 : int(1..4)]) <= 4, + sum([toInt(x_Occurrence[q5]) | q5 : int(1..4)]) <= 4, + and([x_Occurrence[q26] -> + or([x_ExplicitVarSizeWithDummy[q28] != 5 /\ x_ExplicitVarSizeWithDummy[q28] = q26 | q28 : int(1..4)]) + | q26 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q30] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q30]] | q30 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q6] < x_ExplicitVarSizeWithFlags_Values[q6 + 1] + | q6 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q7] = false -> x_ExplicitVarSizeWithFlags_Values[q7] = 1 | q7 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q8 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q8] | q8 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q9]) | q9 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithFlags_Flags[q12] -> + or([x_ExplicitVarSizeWithDummy[q14] != 5 /\ + x_ExplicitVarSizeWithDummy[q14] = x_ExplicitVarSizeWithFlags_Values[q12] + | q14 : int(1..4)]) + | q12 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q16] != 5 -> + or([x_ExplicitVarSizeWithFlags_Flags[q18] /\ + x_ExplicitVarSizeWithFlags_Values[q18] = x_ExplicitVarSizeWithDummy[q16] + | q18 : int(1..4)]) + | q16 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q20] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q20]] + | q20 : int(1..4)]), + and([x_Occurrence[q21] -> + or([x_ExplicitVarSizeWithFlags_Flags[q23] /\ x_ExplicitVarSizeWithFlags_Values[q23] = q21 | q23 : int(1..4)]) + | q21 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set06/expected/model_2_1_4_3-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_2_1_4_3-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_2_1_4_3-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_2_1_4_3-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_2_1_4_3-solution000002.solution new file mode 100644 index 0000000000..85149821f6 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_2_1_4_3-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_2_1_4_3.eprime b/tests/exhaustive/basic/set06/expected/model_2_1_4_3.eprime new file mode 100644 index 0000000000..f9660743b6 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_2_1_4_3.eprime @@ -0,0 +1,77 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +find x_Occurrence: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +branching on + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy, x_Occurrence, + x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] +such that + or([x_ExplicitVarSizeWithDummy[q56] != 5 /\ x_ExplicitVarSizeWithDummy[q56] = 1 | q56 : int(1..4)]), + x_Occurrence[2], + or([x_ExplicitVarSizeWithFlags_Flags[q49] /\ x_ExplicitVarSizeWithFlags_Values[q49] = 3 | q49 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 5 + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q2] = 5 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 5) | q3 : int(1..4)]) <= 4, + sum([toInt(x_Occurrence[q5]) | q5 : int(1..4)]) <= 4, + and([x_Occurrence[q50] -> + or([x_ExplicitVarSizeWithDummy[q52] != 5 /\ x_ExplicitVarSizeWithDummy[q52] = q50 | q52 : int(1..4)]) + | q50 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q54] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q54]] | q54 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q6] < x_ExplicitVarSizeWithFlags_Values[q6 + 1] + | q6 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q7] = false -> x_ExplicitVarSizeWithFlags_Values[q7] = 1 | q7 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q8 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q8] | q8 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q9]) | q9 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithFlags_Flags[q12] -> + or([x_ExplicitVarSizeWithDummy[q14] != 5 /\ + x_ExplicitVarSizeWithDummy[q14] = x_ExplicitVarSizeWithFlags_Values[q12] + | q14 : int(1..4)]) + | q12 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q16] != 5 -> + or([x_ExplicitVarSizeWithFlags_Flags[q18] /\ + x_ExplicitVarSizeWithFlags_Values[q18] = x_ExplicitVarSizeWithDummy[q16] + | q18 : int(1..4)]) + | q16 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q20] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q20]] + | q20 : int(1..4)]), + and([x_Occurrence[q21] -> + or([x_ExplicitVarSizeWithFlags_Flags[q23] /\ x_ExplicitVarSizeWithFlags_Values[q23] = q21 | q23 : int(1..4)]) + | q21 : int(1..4)]), + and([q24 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q24] < x_ExplicitVarSizeWithMarker_Values[q24 + 1] + | q24 : int(1..3)]), + and([q25 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q25] = 1 | q25 : int(1..4)]), + x_ExplicitVarSizeWithMarker_Marker <= 4, + and([q28 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithDummy[q30] != 5 /\ + x_ExplicitVarSizeWithDummy[q30] = x_ExplicitVarSizeWithMarker_Values[q28] + | q30 : int(1..4)]) + | q28 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q32] != 5 -> + or([q34 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q34] = x_ExplicitVarSizeWithDummy[q32] + | q34 : int(1..4)]) + | q32 : int(1..4)]), + and([q36 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q36]] + | q36 : int(1..4)]), + and([x_Occurrence[q37] -> + or([q39 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q39] = q37 + | q39 : int(1..4)]) + | q37 : int(1..4)]), + and([q41 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithFlags_Flags[q43] /\ + x_ExplicitVarSizeWithFlags_Values[q43] = x_ExplicitVarSizeWithMarker_Values[q41] + | q43 : int(1..4)]) + | q41 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q45] -> + or([q47 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q47] = x_ExplicitVarSizeWithFlags_Values[q45] + | q47 : int(1..4)]) + | q45 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set06/expected/model_2_2_1_1-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_2_2_1_1-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_2_2_1_1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_2_2_1_1-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_2_2_1_1-solution000002.solution new file mode 100644 index 0000000000..85149821f6 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_2_2_1_1-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_2_2_1_1.eprime b/tests/exhaustive/basic/set06/expected/model_2_2_1_1.eprime new file mode 100644 index 0000000000..c05e9cc08f --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_2_2_1_1.eprime @@ -0,0 +1,19 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +find x_Occurrence: matrix indexed by [int(1..4)] of bool +branching on [x_Occurrence, x_ExplicitVarSizeWithDummy] +such that + or([x_ExplicitVarSizeWithDummy[q12] != 5 /\ x_ExplicitVarSizeWithDummy[q12] = 1 | q12 : int(1..4)]), + or([x_ExplicitVarSizeWithDummy[q14] != 5 /\ x_ExplicitVarSizeWithDummy[q14] = 2 | q14 : int(1..4)]), + x_Occurrence[3], + and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 5 + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q2] = 5 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 5) | q3 : int(1..4)]) <= 4, + sum([toInt(x_Occurrence[q5]) | q5 : int(1..4)]) <= 4, + and([x_Occurrence[q6] -> + or([x_ExplicitVarSizeWithDummy[q8] != 5 /\ x_ExplicitVarSizeWithDummy[q8] = q6 | q8 : int(1..4)]) + | q6 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q10] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q10]] | q10 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set06/expected/model_2_2_1_3-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_2_2_1_3-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_2_2_1_3-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_2_2_1_3-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_2_2_1_3-solution000002.solution new file mode 100644 index 0000000000..85149821f6 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_2_2_1_3-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_2_2_1_3.eprime b/tests/exhaustive/basic/set06/expected/model_2_2_1_3.eprime new file mode 100644 index 0000000000..ca46d4ab65 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_2_2_1_3.eprime @@ -0,0 +1,43 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +find x_Occurrence: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +branching on + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy, x_Occurrence] +such that + or([x_ExplicitVarSizeWithDummy[q28] != 5 /\ x_ExplicitVarSizeWithDummy[q28] = 1 | q28 : int(1..4)]), + or([x_ExplicitVarSizeWithDummy[q30] != 5 /\ x_ExplicitVarSizeWithDummy[q30] = 2 | q30 : int(1..4)]), + x_Occurrence[3], + and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 5 + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q2] = 5 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 5) | q3 : int(1..4)]) <= 4, + sum([toInt(x_Occurrence[q5]) | q5 : int(1..4)]) <= 4, + and([x_Occurrence[q22] -> + or([x_ExplicitVarSizeWithDummy[q24] != 5 /\ x_ExplicitVarSizeWithDummy[q24] = q22 | q24 : int(1..4)]) + | q22 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q26] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q26]] | q26 : int(1..4)]), + and([q6 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q6] < x_ExplicitVarSizeWithMarker_Values[q6 + 1] + | q6 : int(1..3)]), + and([q7 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q7] = 1 | q7 : int(1..4)]), + x_ExplicitVarSizeWithMarker_Marker <= 4, + and([q10 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithDummy[q12] != 5 /\ + x_ExplicitVarSizeWithDummy[q12] = x_ExplicitVarSizeWithMarker_Values[q10] + | q12 : int(1..4)]) + | q10 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q14] != 5 -> + or([q16 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q16] = x_ExplicitVarSizeWithDummy[q14] + | q16 : int(1..4)]) + | q14 : int(1..4)]), + and([q18 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q18]] + | q18 : int(1..4)]), + and([x_Occurrence[q19] -> + or([q21 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q21] = q19 + | q21 : int(1..4)]) + | q19 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set06/expected/model_2_2_1_4-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_2_2_1_4-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_2_2_1_4-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_2_2_1_4-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_2_2_1_4-solution000002.solution new file mode 100644 index 0000000000..85149821f6 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_2_2_1_4-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_2_2_1_4.eprime b/tests/exhaustive/basic/set06/expected/model_2_2_1_4.eprime new file mode 100644 index 0000000000..354ad47498 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_2_2_1_4.eprime @@ -0,0 +1,43 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +find x_Occurrence: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +branching on + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy, x_Occurrence] +such that + or([x_ExplicitVarSizeWithDummy[q30] != 5 /\ x_ExplicitVarSizeWithDummy[q30] = 1 | q30 : int(1..4)]), + or([x_ExplicitVarSizeWithDummy[q32] != 5 /\ x_ExplicitVarSizeWithDummy[q32] = 2 | q32 : int(1..4)]), + x_Occurrence[3], + and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 5 + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q2] = 5 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 5) | q3 : int(1..4)]) <= 4, + sum([toInt(x_Occurrence[q5]) | q5 : int(1..4)]) <= 4, + and([x_Occurrence[q24] -> + or([x_ExplicitVarSizeWithDummy[q26] != 5 /\ x_ExplicitVarSizeWithDummy[q26] = q24 | q26 : int(1..4)]) + | q24 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q28] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q28]] | q28 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q6] < x_ExplicitVarSizeWithFlags_Values[q6 + 1] + | q6 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q7] = false -> x_ExplicitVarSizeWithFlags_Values[q7] = 1 | q7 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q8 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q8] | q8 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q9]) | q9 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithFlags_Flags[q12] -> + or([x_ExplicitVarSizeWithDummy[q14] != 5 /\ + x_ExplicitVarSizeWithDummy[q14] = x_ExplicitVarSizeWithFlags_Values[q12] + | q14 : int(1..4)]) + | q12 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q16] != 5 -> + or([x_ExplicitVarSizeWithFlags_Flags[q18] /\ + x_ExplicitVarSizeWithFlags_Values[q18] = x_ExplicitVarSizeWithDummy[q16] + | q18 : int(1..4)]) + | q16 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q20] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q20]] + | q20 : int(1..4)]), + and([x_Occurrence[q21] -> + or([x_ExplicitVarSizeWithFlags_Flags[q23] /\ x_ExplicitVarSizeWithFlags_Values[q23] = q21 | q23 : int(1..4)]) + | q21 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set06/expected/model_2_2_2_1-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_2_2_2_1-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_2_2_2_1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_2_2_2_1-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_2_2_2_1-solution000002.solution new file mode 100644 index 0000000000..85149821f6 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_2_2_2_1-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_2_2_2_1.eprime b/tests/exhaustive/basic/set06/expected/model_2_2_2_1.eprime new file mode 100644 index 0000000000..4a891ab86b --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_2_2_2_1.eprime @@ -0,0 +1,19 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +find x_Occurrence: matrix indexed by [int(1..4)] of bool +branching on [x_Occurrence, x_ExplicitVarSizeWithDummy] +such that + or([x_ExplicitVarSizeWithDummy[q12] != 5 /\ x_ExplicitVarSizeWithDummy[q12] = 1 | q12 : int(1..4)]), + or([x_ExplicitVarSizeWithDummy[q14] != 5 /\ x_ExplicitVarSizeWithDummy[q14] = 2 | q14 : int(1..4)]), + or([x_ExplicitVarSizeWithDummy[q16] != 5 /\ x_ExplicitVarSizeWithDummy[q16] = 3 | q16 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 5 + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q2] = 5 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 5) | q3 : int(1..4)]) <= 4, + sum([toInt(x_Occurrence[q5]) | q5 : int(1..4)]) <= 4, + and([x_Occurrence[q6] -> + or([x_ExplicitVarSizeWithDummy[q8] != 5 /\ x_ExplicitVarSizeWithDummy[q8] = q6 | q8 : int(1..4)]) + | q6 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q10] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q10]] | q10 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set06/expected/model_2_2_2_2-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_2_2_2_2-solution000001.solution new file mode 100644 index 0000000000..85149821f6 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_2_2_2_2-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_2_2_2_2-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_2_2_2_2-solution000002.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_2_2_2_2-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_2_2_2_2.eprime b/tests/exhaustive/basic/set06/expected/model_2_2_2_2.eprime new file mode 100644 index 0000000000..c69010fadb --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_2_2_2_2.eprime @@ -0,0 +1,13 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +branching on [x_ExplicitVarSizeWithDummy] +such that + or([x_ExplicitVarSizeWithDummy[q6] != 5 /\ x_ExplicitVarSizeWithDummy[q6] = 1 | q6 : int(1..4)]), + or([x_ExplicitVarSizeWithDummy[q8] != 5 /\ x_ExplicitVarSizeWithDummy[q8] = 2 | q8 : int(1..4)]), + or([x_ExplicitVarSizeWithDummy[q10] != 5 /\ x_ExplicitVarSizeWithDummy[q10] = 3 | q10 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 5 + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q2] = 5 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 5) | q3 : int(1..4)]) <= 4 + diff --git a/tests/exhaustive/basic/set06/expected/model_2_2_2_3-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_2_2_2_3-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_2_2_2_3-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_2_2_2_3-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_2_2_2_3-solution000002.solution new file mode 100644 index 0000000000..85149821f6 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_2_2_2_3-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_2_2_2_3.eprime b/tests/exhaustive/basic/set06/expected/model_2_2_2_3.eprime new file mode 100644 index 0000000000..18a5bb99e1 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_2_2_2_3.eprime @@ -0,0 +1,30 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +branching on [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy] +such that + or([x_ExplicitVarSizeWithDummy[q17] != 5 /\ x_ExplicitVarSizeWithDummy[q17] = 1 | q17 : int(1..4)]), + or([x_ExplicitVarSizeWithDummy[q19] != 5 /\ x_ExplicitVarSizeWithDummy[q19] = 2 | q19 : int(1..4)]), + or([x_ExplicitVarSizeWithDummy[q21] != 5 /\ x_ExplicitVarSizeWithDummy[q21] = 3 | q21 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 5 + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q2] = 5 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 5) | q3 : int(1..4)]) <= 4, + and([q5 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q5] < x_ExplicitVarSizeWithMarker_Values[q5 + 1] + | q5 : int(1..3)]), + and([q6 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q6] = 1 | q6 : int(1..4)]), + x_ExplicitVarSizeWithMarker_Marker <= 4, + and([q9 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithDummy[q11] != 5 /\ + x_ExplicitVarSizeWithDummy[q11] = x_ExplicitVarSizeWithMarker_Values[q9] + | q11 : int(1..4)]) + | q9 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q13] != 5 -> + or([q15 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q15] = x_ExplicitVarSizeWithDummy[q13] + | q15 : int(1..4)]) + | q13 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set06/expected/model_2_2_2_4-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_2_2_2_4-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_2_2_2_4-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_2_2_2_4-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_2_2_2_4-solution000002.solution new file mode 100644 index 0000000000..85149821f6 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_2_2_2_4-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_2_2_2_4.eprime b/tests/exhaustive/basic/set06/expected/model_2_2_2_4.eprime new file mode 100644 index 0000000000..dcecde5147 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_2_2_2_4.eprime @@ -0,0 +1,31 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +branching on [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy] +such that + or([x_ExplicitVarSizeWithDummy[q19] != 5 /\ x_ExplicitVarSizeWithDummy[q19] = 1 | q19 : int(1..4)]), + or([x_ExplicitVarSizeWithDummy[q21] != 5 /\ x_ExplicitVarSizeWithDummy[q21] = 2 | q21 : int(1..4)]), + or([x_ExplicitVarSizeWithDummy[q23] != 5 /\ x_ExplicitVarSizeWithDummy[q23] = 3 | q23 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 5 + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q2] = 5 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 5) | q3 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithFlags_Flags[q5 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q5] < x_ExplicitVarSizeWithFlags_Values[q5 + 1] + | q5 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q6] = false -> x_ExplicitVarSizeWithFlags_Values[q6] = 1 | q6 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q7] | q7 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q8]) | q8 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithFlags_Flags[q11] -> + or([x_ExplicitVarSizeWithDummy[q13] != 5 /\ + x_ExplicitVarSizeWithDummy[q13] = x_ExplicitVarSizeWithFlags_Values[q11] + | q13 : int(1..4)]) + | q11 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q15] != 5 -> + or([x_ExplicitVarSizeWithFlags_Flags[q17] /\ + x_ExplicitVarSizeWithFlags_Values[q17] = x_ExplicitVarSizeWithDummy[q15] + | q17 : int(1..4)]) + | q15 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set06/expected/model_2_2_3_1-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_2_2_3_1-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_2_2_3_1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_2_2_3_1-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_2_2_3_1-solution000002.solution new file mode 100644 index 0000000000..85149821f6 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_2_2_3_1-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_2_2_3_1.eprime b/tests/exhaustive/basic/set06/expected/model_2_2_3_1.eprime new file mode 100644 index 0000000000..0ba2c449b2 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_2_2_3_1.eprime @@ -0,0 +1,43 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_Occurrence: matrix indexed by [int(1..4)] of bool +branching on + [x_Occurrence, x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] +such that + or([x_ExplicitVarSizeWithDummy[q28] != 5 /\ x_ExplicitVarSizeWithDummy[q28] = 1 | q28 : int(1..4)]), + or([x_ExplicitVarSizeWithDummy[q30] != 5 /\ x_ExplicitVarSizeWithDummy[q30] = 2 | q30 : int(1..4)]), + or([q32 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q32] = 3 | q32 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 5 + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q2] = 5 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 5) | q3 : int(1..4)]) <= 4, + and([q5 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q5] < x_ExplicitVarSizeWithMarker_Values[q5 + 1] + | q5 : int(1..3)]), + and([q6 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q6] = 1 | q6 : int(1..4)]), + x_ExplicitVarSizeWithMarker_Marker <= 4, + and([q9 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithDummy[q11] != 5 /\ + x_ExplicitVarSizeWithDummy[q11] = x_ExplicitVarSizeWithMarker_Values[q9] + | q11 : int(1..4)]) + | q9 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q13] != 5 -> + or([q15 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q15] = x_ExplicitVarSizeWithDummy[q13] + | q15 : int(1..4)]) + | q13 : int(1..4)]), + sum([toInt(x_Occurrence[q16]) | q16 : int(1..4)]) <= 4, + and([x_Occurrence[q17] -> + or([x_ExplicitVarSizeWithDummy[q19] != 5 /\ x_ExplicitVarSizeWithDummy[q19] = q17 | q19 : int(1..4)]) + | q17 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q21] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q21]] | q21 : int(1..4)]), + and([x_Occurrence[q22] -> + or([q24 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q24] = q22 + | q24 : int(1..4)]) + | q22 : int(1..4)]), + and([q26 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q26]] + | q26 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set06/expected/model_2_2_3_2-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_2_2_3_2-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_2_2_3_2-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_2_2_3_2-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_2_2_3_2-solution000002.solution new file mode 100644 index 0000000000..85149821f6 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_2_2_3_2-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_2_2_3_2.eprime b/tests/exhaustive/basic/set06/expected/model_2_2_3_2.eprime new file mode 100644 index 0000000000..875689727a --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_2_2_3_2.eprime @@ -0,0 +1,30 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +branching on [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy] +such that + or([x_ExplicitVarSizeWithDummy[q17] != 5 /\ x_ExplicitVarSizeWithDummy[q17] = 1 | q17 : int(1..4)]), + or([x_ExplicitVarSizeWithDummy[q19] != 5 /\ x_ExplicitVarSizeWithDummy[q19] = 2 | q19 : int(1..4)]), + or([q21 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q21] = 3 | q21 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 5 + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q2] = 5 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 5) | q3 : int(1..4)]) <= 4, + and([q5 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q5] < x_ExplicitVarSizeWithMarker_Values[q5 + 1] + | q5 : int(1..3)]), + and([q6 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q6] = 1 | q6 : int(1..4)]), + x_ExplicitVarSizeWithMarker_Marker <= 4, + and([q9 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithDummy[q11] != 5 /\ + x_ExplicitVarSizeWithDummy[q11] = x_ExplicitVarSizeWithMarker_Values[q9] + | q11 : int(1..4)]) + | q9 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q13] != 5 -> + or([q15 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q15] = x_ExplicitVarSizeWithDummy[q13] + | q15 : int(1..4)]) + | q13 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set06/expected/model_2_2_3_4-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_2_2_3_4-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_2_2_3_4-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_2_2_3_4-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_2_2_3_4-solution000002.solution new file mode 100644 index 0000000000..85149821f6 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_2_2_3_4-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_2_2_3_4.eprime b/tests/exhaustive/basic/set06/expected/model_2_2_3_4.eprime new file mode 100644 index 0000000000..ca3fdd46a7 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_2_2_3_4.eprime @@ -0,0 +1,61 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +branching on + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy, + x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] +such that + or([x_ExplicitVarSizeWithDummy[q38] != 5 /\ x_ExplicitVarSizeWithDummy[q38] = 1 | q38 : int(1..4)]), + or([x_ExplicitVarSizeWithDummy[q40] != 5 /\ x_ExplicitVarSizeWithDummy[q40] = 2 | q40 : int(1..4)]), + or([q42 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q42] = 3 | q42 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 5 + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q2] = 5 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 5) | q3 : int(1..4)]) <= 4, + and([q5 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q5] < x_ExplicitVarSizeWithMarker_Values[q5 + 1] + | q5 : int(1..3)]), + and([q6 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q6] = 1 | q6 : int(1..4)]), + x_ExplicitVarSizeWithMarker_Marker <= 4, + and([q9 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithDummy[q11] != 5 /\ + x_ExplicitVarSizeWithDummy[q11] = x_ExplicitVarSizeWithMarker_Values[q9] + | q11 : int(1..4)]) + | q9 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q13] != 5 -> + or([q15 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q15] = x_ExplicitVarSizeWithDummy[q13] + | q15 : int(1..4)]) + | q13 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q16 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q16] < x_ExplicitVarSizeWithFlags_Values[q16 + 1] + | q16 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q17] = false -> x_ExplicitVarSizeWithFlags_Values[q17] = 1 + | q17 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q18 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q18] | q18 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q19]) | q19 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithFlags_Flags[q22] -> + or([x_ExplicitVarSizeWithDummy[q24] != 5 /\ + x_ExplicitVarSizeWithDummy[q24] = x_ExplicitVarSizeWithFlags_Values[q22] + | q24 : int(1..4)]) + | q22 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q26] != 5 -> + or([x_ExplicitVarSizeWithFlags_Flags[q28] /\ + x_ExplicitVarSizeWithFlags_Values[q28] = x_ExplicitVarSizeWithDummy[q26] + | q28 : int(1..4)]) + | q26 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q30] -> + or([q32 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q32] = x_ExplicitVarSizeWithFlags_Values[q30] + | q32 : int(1..4)]) + | q30 : int(1..4)]), + and([q34 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithFlags_Flags[q36] /\ + x_ExplicitVarSizeWithFlags_Values[q36] = x_ExplicitVarSizeWithMarker_Values[q34] + | q36 : int(1..4)]) + | q34 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set06/expected/model_2_2_4_1-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_2_2_4_1-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_2_2_4_1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_2_2_4_1-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_2_2_4_1-solution000002.solution new file mode 100644 index 0000000000..85149821f6 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_2_2_4_1-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_2_2_4_1.eprime b/tests/exhaustive/basic/set06/expected/model_2_2_4_1.eprime new file mode 100644 index 0000000000..9dbf7c903e --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_2_2_4_1.eprime @@ -0,0 +1,43 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_Occurrence: matrix indexed by [int(1..4)] of bool +branching on + [x_Occurrence, x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] +such that + or([x_ExplicitVarSizeWithDummy[q30] != 5 /\ x_ExplicitVarSizeWithDummy[q30] = 1 | q30 : int(1..4)]), + or([x_ExplicitVarSizeWithDummy[q32] != 5 /\ x_ExplicitVarSizeWithDummy[q32] = 2 | q32 : int(1..4)]), + or([x_ExplicitVarSizeWithFlags_Flags[q34] /\ x_ExplicitVarSizeWithFlags_Values[q34] = 3 | q34 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 5 + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q2] = 5 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 5) | q3 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithFlags_Flags[q5 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q5] < x_ExplicitVarSizeWithFlags_Values[q5 + 1] + | q5 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q6] = false -> x_ExplicitVarSizeWithFlags_Values[q6] = 1 | q6 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q7] | q7 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q8]) | q8 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithFlags_Flags[q11] -> + or([x_ExplicitVarSizeWithDummy[q13] != 5 /\ + x_ExplicitVarSizeWithDummy[q13] = x_ExplicitVarSizeWithFlags_Values[q11] + | q13 : int(1..4)]) + | q11 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q15] != 5 -> + or([x_ExplicitVarSizeWithFlags_Flags[q17] /\ + x_ExplicitVarSizeWithFlags_Values[q17] = x_ExplicitVarSizeWithDummy[q15] + | q17 : int(1..4)]) + | q15 : int(1..4)]), + sum([toInt(x_Occurrence[q18]) | q18 : int(1..4)]) <= 4, + and([x_Occurrence[q19] -> + or([x_ExplicitVarSizeWithDummy[q21] != 5 /\ x_ExplicitVarSizeWithDummy[q21] = q19 | q21 : int(1..4)]) + | q19 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q23] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q23]] | q23 : int(1..4)]), + and([x_Occurrence[q24] -> + or([x_ExplicitVarSizeWithFlags_Flags[q26] /\ x_ExplicitVarSizeWithFlags_Values[q26] = q24 | q26 : int(1..4)]) + | q24 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q28] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q28]] + | q28 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set06/expected/model_2_2_4_2-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_2_2_4_2-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_2_2_4_2-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_2_2_4_2-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_2_2_4_2-solution000002.solution new file mode 100644 index 0000000000..85149821f6 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_2_2_4_2-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_2_2_4_2.eprime b/tests/exhaustive/basic/set06/expected/model_2_2_4_2.eprime new file mode 100644 index 0000000000..8a79eef455 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_2_2_4_2.eprime @@ -0,0 +1,31 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +branching on [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy] +such that + or([x_ExplicitVarSizeWithDummy[q19] != 5 /\ x_ExplicitVarSizeWithDummy[q19] = 1 | q19 : int(1..4)]), + or([x_ExplicitVarSizeWithDummy[q21] != 5 /\ x_ExplicitVarSizeWithDummy[q21] = 2 | q21 : int(1..4)]), + or([x_ExplicitVarSizeWithFlags_Flags[q23] /\ x_ExplicitVarSizeWithFlags_Values[q23] = 3 | q23 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 5 + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q2] = 5 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 5) | q3 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithFlags_Flags[q5 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q5] < x_ExplicitVarSizeWithFlags_Values[q5 + 1] + | q5 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q6] = false -> x_ExplicitVarSizeWithFlags_Values[q6] = 1 | q6 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q7] | q7 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q8]) | q8 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithFlags_Flags[q11] -> + or([x_ExplicitVarSizeWithDummy[q13] != 5 /\ + x_ExplicitVarSizeWithDummy[q13] = x_ExplicitVarSizeWithFlags_Values[q11] + | q13 : int(1..4)]) + | q11 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q15] != 5 -> + or([x_ExplicitVarSizeWithFlags_Flags[q17] /\ + x_ExplicitVarSizeWithFlags_Values[q17] = x_ExplicitVarSizeWithDummy[q15] + | q17 : int(1..4)]) + | q15 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set06/expected/model_2_2_4_3-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_2_2_4_3-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_2_2_4_3-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_2_2_4_3-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_2_2_4_3-solution000002.solution new file mode 100644 index 0000000000..85149821f6 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_2_2_4_3-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_2_2_4_3.eprime b/tests/exhaustive/basic/set06/expected/model_2_2_4_3.eprime new file mode 100644 index 0000000000..7d292ec23b --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_2_2_4_3.eprime @@ -0,0 +1,60 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +branching on + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy, + x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] +such that + or([x_ExplicitVarSizeWithDummy[q38] != 5 /\ x_ExplicitVarSizeWithDummy[q38] = 1 | q38 : int(1..4)]), + or([x_ExplicitVarSizeWithDummy[q40] != 5 /\ x_ExplicitVarSizeWithDummy[q40] = 2 | q40 : int(1..4)]), + or([x_ExplicitVarSizeWithFlags_Flags[q42] /\ x_ExplicitVarSizeWithFlags_Values[q42] = 3 | q42 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 5 + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q2] = 5 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 5) | q3 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithFlags_Flags[q5 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q5] < x_ExplicitVarSizeWithFlags_Values[q5 + 1] + | q5 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q6] = false -> x_ExplicitVarSizeWithFlags_Values[q6] = 1 | q6 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q7] | q7 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q8]) | q8 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithFlags_Flags[q11] -> + or([x_ExplicitVarSizeWithDummy[q13] != 5 /\ + x_ExplicitVarSizeWithDummy[q13] = x_ExplicitVarSizeWithFlags_Values[q11] + | q13 : int(1..4)]) + | q11 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q15] != 5 -> + or([x_ExplicitVarSizeWithFlags_Flags[q17] /\ + x_ExplicitVarSizeWithFlags_Values[q17] = x_ExplicitVarSizeWithDummy[q15] + | q17 : int(1..4)]) + | q15 : int(1..4)]), + and([q18 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q18] < x_ExplicitVarSizeWithMarker_Values[q18 + 1] + | q18 : int(1..3)]), + and([q19 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q19] = 1 | q19 : int(1..4)]), + x_ExplicitVarSizeWithMarker_Marker <= 4, + and([q22 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithDummy[q24] != 5 /\ + x_ExplicitVarSizeWithDummy[q24] = x_ExplicitVarSizeWithMarker_Values[q22] + | q24 : int(1..4)]) + | q22 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q26] != 5 -> + or([q28 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q28] = x_ExplicitVarSizeWithDummy[q26] + | q28 : int(1..4)]) + | q26 : int(1..4)]), + and([q30 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithFlags_Flags[q32] /\ + x_ExplicitVarSizeWithFlags_Values[q32] = x_ExplicitVarSizeWithMarker_Values[q30] + | q32 : int(1..4)]) + | q30 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q34] -> + or([q36 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q36] = x_ExplicitVarSizeWithFlags_Values[q34] + | q36 : int(1..4)]) + | q34 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set06/expected/model_2_3_1_1-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_2_3_1_1-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_2_3_1_1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_2_3_1_1-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_2_3_1_1-solution000002.solution new file mode 100644 index 0000000000..85149821f6 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_2_3_1_1-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_2_3_1_1.eprime b/tests/exhaustive/basic/set06/expected/model_2_3_1_1.eprime new file mode 100644 index 0000000000..38b040fe91 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_2_3_1_1.eprime @@ -0,0 +1,43 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_Occurrence: matrix indexed by [int(1..4)] of bool +branching on + [x_Occurrence, x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] +such that + or([x_ExplicitVarSizeWithDummy[q28] != 5 /\ x_ExplicitVarSizeWithDummy[q28] = 1 | q28 : int(1..4)]), + or([q30 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q30] = 2 | q30 : int(1..4)]), + x_Occurrence[3], + and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 5 + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q2] = 5 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 5) | q3 : int(1..4)]) <= 4, + and([q5 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q5] < x_ExplicitVarSizeWithMarker_Values[q5 + 1] + | q5 : int(1..3)]), + and([q6 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q6] = 1 | q6 : int(1..4)]), + x_ExplicitVarSizeWithMarker_Marker <= 4, + and([q9 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithDummy[q11] != 5 /\ + x_ExplicitVarSizeWithDummy[q11] = x_ExplicitVarSizeWithMarker_Values[q9] + | q11 : int(1..4)]) + | q9 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q13] != 5 -> + or([q15 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q15] = x_ExplicitVarSizeWithDummy[q13] + | q15 : int(1..4)]) + | q13 : int(1..4)]), + sum([toInt(x_Occurrence[q16]) | q16 : int(1..4)]) <= 4, + and([x_Occurrence[q17] -> + or([x_ExplicitVarSizeWithDummy[q19] != 5 /\ x_ExplicitVarSizeWithDummy[q19] = q17 | q19 : int(1..4)]) + | q17 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q21] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q21]] | q21 : int(1..4)]), + and([x_Occurrence[q22] -> + or([q24 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q24] = q22 + | q24 : int(1..4)]) + | q22 : int(1..4)]), + and([q26 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q26]] + | q26 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set06/expected/model_2_3_1_4-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_2_3_1_4-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_2_3_1_4-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_2_3_1_4-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_2_3_1_4-solution000002.solution new file mode 100644 index 0000000000..85149821f6 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_2_3_1_4-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_2_3_1_4.eprime b/tests/exhaustive/basic/set06/expected/model_2_3_1_4.eprime new file mode 100644 index 0000000000..02a7c6a35f --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_2_3_1_4.eprime @@ -0,0 +1,78 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_Occurrence: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +branching on + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy, + x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_Occurrence] +such that + or([x_ExplicitVarSizeWithDummy[q54] != 5 /\ x_ExplicitVarSizeWithDummy[q54] = 1 | q54 : int(1..4)]), + or([q56 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q56] = 2 | q56 : int(1..4)]), + x_Occurrence[3], + and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 5 + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q2] = 5 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 5) | q3 : int(1..4)]) <= 4, + and([q5 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q5] < x_ExplicitVarSizeWithMarker_Values[q5 + 1] + | q5 : int(1..3)]), + and([q6 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q6] = 1 | q6 : int(1..4)]), + x_ExplicitVarSizeWithMarker_Marker <= 4, + and([q9 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithDummy[q11] != 5 /\ + x_ExplicitVarSizeWithDummy[q11] = x_ExplicitVarSizeWithMarker_Values[q9] + | q11 : int(1..4)]) + | q9 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q13] != 5 -> + or([q15 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q15] = x_ExplicitVarSizeWithDummy[q13] + | q15 : int(1..4)]) + | q13 : int(1..4)]), + sum([toInt(x_Occurrence[q16]) | q16 : int(1..4)]) <= 4, + and([x_Occurrence[q43] -> + or([x_ExplicitVarSizeWithDummy[q45] != 5 /\ x_ExplicitVarSizeWithDummy[q45] = q43 | q45 : int(1..4)]) + | q43 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q47] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q47]] | q47 : int(1..4)]), + and([x_Occurrence[q48] -> + or([q50 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q50] = q48 + | q50 : int(1..4)]) + | q48 : int(1..4)]), + and([q52 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q52]] + | q52 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q17 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q17] < x_ExplicitVarSizeWithFlags_Values[q17 + 1] + | q17 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q18] = false -> x_ExplicitVarSizeWithFlags_Values[q18] = 1 + | q18 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q19 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q19] | q19 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q20]) | q20 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithFlags_Flags[q23] -> + or([x_ExplicitVarSizeWithDummy[q25] != 5 /\ + x_ExplicitVarSizeWithDummy[q25] = x_ExplicitVarSizeWithFlags_Values[q23] + | q25 : int(1..4)]) + | q23 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q27] != 5 -> + or([x_ExplicitVarSizeWithFlags_Flags[q29] /\ + x_ExplicitVarSizeWithFlags_Values[q29] = x_ExplicitVarSizeWithDummy[q27] + | q29 : int(1..4)]) + | q27 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q31] -> + or([q33 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q33] = x_ExplicitVarSizeWithFlags_Values[q31] + | q33 : int(1..4)]) + | q31 : int(1..4)]), + and([q35 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithFlags_Flags[q37] /\ + x_ExplicitVarSizeWithFlags_Values[q37] = x_ExplicitVarSizeWithMarker_Values[q35] + | q37 : int(1..4)]) + | q35 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q39] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q39]] + | q39 : int(1..4)]), + and([x_Occurrence[q40] -> + or([x_ExplicitVarSizeWithFlags_Flags[q42] /\ x_ExplicitVarSizeWithFlags_Values[q42] = q40 | q42 : int(1..4)]) + | q40 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set06/expected/model_2_3_2_1-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_2_3_2_1-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_2_3_2_1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_2_3_2_1-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_2_3_2_1-solution000002.solution new file mode 100644 index 0000000000..85149821f6 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_2_3_2_1-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_2_3_2_1.eprime b/tests/exhaustive/basic/set06/expected/model_2_3_2_1.eprime new file mode 100644 index 0000000000..69afb8a756 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_2_3_2_1.eprime @@ -0,0 +1,43 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_Occurrence: matrix indexed by [int(1..4)] of bool +branching on + [x_Occurrence, x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] +such that + or([x_ExplicitVarSizeWithDummy[q28] != 5 /\ x_ExplicitVarSizeWithDummy[q28] = 1 | q28 : int(1..4)]), + or([q30 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q30] = 2 | q30 : int(1..4)]), + or([x_ExplicitVarSizeWithDummy[q32] != 5 /\ x_ExplicitVarSizeWithDummy[q32] = 3 | q32 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 5 + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q2] = 5 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 5) | q3 : int(1..4)]) <= 4, + and([q5 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q5] < x_ExplicitVarSizeWithMarker_Values[q5 + 1] + | q5 : int(1..3)]), + and([q6 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q6] = 1 | q6 : int(1..4)]), + x_ExplicitVarSizeWithMarker_Marker <= 4, + and([q9 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithDummy[q11] != 5 /\ + x_ExplicitVarSizeWithDummy[q11] = x_ExplicitVarSizeWithMarker_Values[q9] + | q11 : int(1..4)]) + | q9 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q13] != 5 -> + or([q15 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q15] = x_ExplicitVarSizeWithDummy[q13] + | q15 : int(1..4)]) + | q13 : int(1..4)]), + sum([toInt(x_Occurrence[q16]) | q16 : int(1..4)]) <= 4, + and([x_Occurrence[q17] -> + or([x_ExplicitVarSizeWithDummy[q19] != 5 /\ x_ExplicitVarSizeWithDummy[q19] = q17 | q19 : int(1..4)]) + | q17 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q21] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q21]] | q21 : int(1..4)]), + and([x_Occurrence[q22] -> + or([q24 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q24] = q22 + | q24 : int(1..4)]) + | q22 : int(1..4)]), + and([q26 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q26]] + | q26 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set06/expected/model_2_3_2_2-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_2_3_2_2-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_2_3_2_2-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_2_3_2_2-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_2_3_2_2-solution000002.solution new file mode 100644 index 0000000000..85149821f6 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_2_3_2_2-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_2_3_2_2.eprime b/tests/exhaustive/basic/set06/expected/model_2_3_2_2.eprime new file mode 100644 index 0000000000..9902fda506 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_2_3_2_2.eprime @@ -0,0 +1,30 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +branching on [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy] +such that + or([x_ExplicitVarSizeWithDummy[q17] != 5 /\ x_ExplicitVarSizeWithDummy[q17] = 1 | q17 : int(1..4)]), + or([q19 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q19] = 2 | q19 : int(1..4)]), + or([x_ExplicitVarSizeWithDummy[q21] != 5 /\ x_ExplicitVarSizeWithDummy[q21] = 3 | q21 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 5 + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q2] = 5 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 5) | q3 : int(1..4)]) <= 4, + and([q5 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q5] < x_ExplicitVarSizeWithMarker_Values[q5 + 1] + | q5 : int(1..3)]), + and([q6 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q6] = 1 | q6 : int(1..4)]), + x_ExplicitVarSizeWithMarker_Marker <= 4, + and([q9 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithDummy[q11] != 5 /\ + x_ExplicitVarSizeWithDummy[q11] = x_ExplicitVarSizeWithMarker_Values[q9] + | q11 : int(1..4)]) + | q9 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q13] != 5 -> + or([q15 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q15] = x_ExplicitVarSizeWithDummy[q13] + | q15 : int(1..4)]) + | q13 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set06/expected/model_2_3_2_4-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_2_3_2_4-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_2_3_2_4-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_2_3_2_4-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_2_3_2_4-solution000002.solution new file mode 100644 index 0000000000..85149821f6 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_2_3_2_4-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_2_3_2_4.eprime b/tests/exhaustive/basic/set06/expected/model_2_3_2_4.eprime new file mode 100644 index 0000000000..5697b5087d --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_2_3_2_4.eprime @@ -0,0 +1,61 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +branching on + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy, + x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] +such that + or([x_ExplicitVarSizeWithDummy[q38] != 5 /\ x_ExplicitVarSizeWithDummy[q38] = 1 | q38 : int(1..4)]), + or([q40 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q40] = 2 | q40 : int(1..4)]), + or([x_ExplicitVarSizeWithDummy[q42] != 5 /\ x_ExplicitVarSizeWithDummy[q42] = 3 | q42 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 5 + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q2] = 5 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 5) | q3 : int(1..4)]) <= 4, + and([q5 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q5] < x_ExplicitVarSizeWithMarker_Values[q5 + 1] + | q5 : int(1..3)]), + and([q6 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q6] = 1 | q6 : int(1..4)]), + x_ExplicitVarSizeWithMarker_Marker <= 4, + and([q9 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithDummy[q11] != 5 /\ + x_ExplicitVarSizeWithDummy[q11] = x_ExplicitVarSizeWithMarker_Values[q9] + | q11 : int(1..4)]) + | q9 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q13] != 5 -> + or([q15 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q15] = x_ExplicitVarSizeWithDummy[q13] + | q15 : int(1..4)]) + | q13 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q16 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q16] < x_ExplicitVarSizeWithFlags_Values[q16 + 1] + | q16 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q17] = false -> x_ExplicitVarSizeWithFlags_Values[q17] = 1 + | q17 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q18 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q18] | q18 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q19]) | q19 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithFlags_Flags[q22] -> + or([x_ExplicitVarSizeWithDummy[q24] != 5 /\ + x_ExplicitVarSizeWithDummy[q24] = x_ExplicitVarSizeWithFlags_Values[q22] + | q24 : int(1..4)]) + | q22 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q26] != 5 -> + or([x_ExplicitVarSizeWithFlags_Flags[q28] /\ + x_ExplicitVarSizeWithFlags_Values[q28] = x_ExplicitVarSizeWithDummy[q26] + | q28 : int(1..4)]) + | q26 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q30] -> + or([q32 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q32] = x_ExplicitVarSizeWithFlags_Values[q30] + | q32 : int(1..4)]) + | q30 : int(1..4)]), + and([q34 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithFlags_Flags[q36] /\ + x_ExplicitVarSizeWithFlags_Values[q36] = x_ExplicitVarSizeWithMarker_Values[q34] + | q36 : int(1..4)]) + | q34 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set06/expected/model_2_3_3_1-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_2_3_3_1-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_2_3_3_1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_2_3_3_1-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_2_3_3_1-solution000002.solution new file mode 100644 index 0000000000..85149821f6 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_2_3_3_1-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_2_3_3_1.eprime b/tests/exhaustive/basic/set06/expected/model_2_3_3_1.eprime new file mode 100644 index 0000000000..37607392b7 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_2_3_3_1.eprime @@ -0,0 +1,43 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_Occurrence: matrix indexed by [int(1..4)] of bool +branching on + [x_Occurrence, x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] +such that + or([x_ExplicitVarSizeWithDummy[q28] != 5 /\ x_ExplicitVarSizeWithDummy[q28] = 1 | q28 : int(1..4)]), + or([q30 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q30] = 2 | q30 : int(1..4)]), + or([q32 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q32] = 3 | q32 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 5 + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q2] = 5 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 5) | q3 : int(1..4)]) <= 4, + and([q5 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q5] < x_ExplicitVarSizeWithMarker_Values[q5 + 1] + | q5 : int(1..3)]), + and([q6 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q6] = 1 | q6 : int(1..4)]), + x_ExplicitVarSizeWithMarker_Marker <= 4, + and([q9 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithDummy[q11] != 5 /\ + x_ExplicitVarSizeWithDummy[q11] = x_ExplicitVarSizeWithMarker_Values[q9] + | q11 : int(1..4)]) + | q9 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q13] != 5 -> + or([q15 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q15] = x_ExplicitVarSizeWithDummy[q13] + | q15 : int(1..4)]) + | q13 : int(1..4)]), + sum([toInt(x_Occurrence[q16]) | q16 : int(1..4)]) <= 4, + and([x_Occurrence[q17] -> + or([x_ExplicitVarSizeWithDummy[q19] != 5 /\ x_ExplicitVarSizeWithDummy[q19] = q17 | q19 : int(1..4)]) + | q17 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q21] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q21]] | q21 : int(1..4)]), + and([x_Occurrence[q22] -> + or([q24 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q24] = q22 + | q24 : int(1..4)]) + | q22 : int(1..4)]), + and([q26 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q26]] + | q26 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set06/expected/model_2_3_3_2-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_2_3_3_2-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_2_3_3_2-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_2_3_3_2-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_2_3_3_2-solution000002.solution new file mode 100644 index 0000000000..85149821f6 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_2_3_3_2-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_2_3_3_2.eprime b/tests/exhaustive/basic/set06/expected/model_2_3_3_2.eprime new file mode 100644 index 0000000000..1f36b524f8 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_2_3_3_2.eprime @@ -0,0 +1,30 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +branching on [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy] +such that + or([x_ExplicitVarSizeWithDummy[q17] != 5 /\ x_ExplicitVarSizeWithDummy[q17] = 1 | q17 : int(1..4)]), + or([q19 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q19] = 2 | q19 : int(1..4)]), + or([q21 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q21] = 3 | q21 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 5 + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q2] = 5 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 5) | q3 : int(1..4)]) <= 4, + and([q5 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q5] < x_ExplicitVarSizeWithMarker_Values[q5 + 1] + | q5 : int(1..3)]), + and([q6 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q6] = 1 | q6 : int(1..4)]), + x_ExplicitVarSizeWithMarker_Marker <= 4, + and([q9 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithDummy[q11] != 5 /\ + x_ExplicitVarSizeWithDummy[q11] = x_ExplicitVarSizeWithMarker_Values[q9] + | q11 : int(1..4)]) + | q9 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q13] != 5 -> + or([q15 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q15] = x_ExplicitVarSizeWithDummy[q13] + | q15 : int(1..4)]) + | q13 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set06/expected/model_2_3_3_4-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_2_3_3_4-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_2_3_3_4-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_2_3_3_4-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_2_3_3_4-solution000002.solution new file mode 100644 index 0000000000..85149821f6 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_2_3_3_4-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_2_3_3_4.eprime b/tests/exhaustive/basic/set06/expected/model_2_3_3_4.eprime new file mode 100644 index 0000000000..b9010e4669 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_2_3_3_4.eprime @@ -0,0 +1,61 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +branching on + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy, + x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] +such that + or([x_ExplicitVarSizeWithDummy[q38] != 5 /\ x_ExplicitVarSizeWithDummy[q38] = 1 | q38 : int(1..4)]), + or([q40 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q40] = 2 | q40 : int(1..4)]), + or([q42 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q42] = 3 | q42 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 5 + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q2] = 5 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 5) | q3 : int(1..4)]) <= 4, + and([q5 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q5] < x_ExplicitVarSizeWithMarker_Values[q5 + 1] + | q5 : int(1..3)]), + and([q6 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q6] = 1 | q6 : int(1..4)]), + x_ExplicitVarSizeWithMarker_Marker <= 4, + and([q9 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithDummy[q11] != 5 /\ + x_ExplicitVarSizeWithDummy[q11] = x_ExplicitVarSizeWithMarker_Values[q9] + | q11 : int(1..4)]) + | q9 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q13] != 5 -> + or([q15 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q15] = x_ExplicitVarSizeWithDummy[q13] + | q15 : int(1..4)]) + | q13 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q16 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q16] < x_ExplicitVarSizeWithFlags_Values[q16 + 1] + | q16 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q17] = false -> x_ExplicitVarSizeWithFlags_Values[q17] = 1 + | q17 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q18 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q18] | q18 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q19]) | q19 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithFlags_Flags[q22] -> + or([x_ExplicitVarSizeWithDummy[q24] != 5 /\ + x_ExplicitVarSizeWithDummy[q24] = x_ExplicitVarSizeWithFlags_Values[q22] + | q24 : int(1..4)]) + | q22 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q26] != 5 -> + or([x_ExplicitVarSizeWithFlags_Flags[q28] /\ + x_ExplicitVarSizeWithFlags_Values[q28] = x_ExplicitVarSizeWithDummy[q26] + | q28 : int(1..4)]) + | q26 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q30] -> + or([q32 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q32] = x_ExplicitVarSizeWithFlags_Values[q30] + | q32 : int(1..4)]) + | q30 : int(1..4)]), + and([q34 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithFlags_Flags[q36] /\ + x_ExplicitVarSizeWithFlags_Values[q36] = x_ExplicitVarSizeWithMarker_Values[q34] + | q36 : int(1..4)]) + | q34 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set06/expected/model_2_3_4_1-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_2_3_4_1-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_2_3_4_1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_2_3_4_1-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_2_3_4_1-solution000002.solution new file mode 100644 index 0000000000..85149821f6 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_2_3_4_1-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_2_3_4_1.eprime b/tests/exhaustive/basic/set06/expected/model_2_3_4_1.eprime new file mode 100644 index 0000000000..3132c81925 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_2_3_4_1.eprime @@ -0,0 +1,78 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_Occurrence: matrix indexed by [int(1..4)] of bool +branching on + [x_Occurrence, x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, + x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] +such that + or([x_ExplicitVarSizeWithDummy[q54] != 5 /\ x_ExplicitVarSizeWithDummy[q54] = 1 | q54 : int(1..4)]), + or([q56 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q56] = 2 | q56 : int(1..4)]), + or([x_ExplicitVarSizeWithFlags_Flags[q58] /\ x_ExplicitVarSizeWithFlags_Values[q58] = 3 | q58 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 5 + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q2] = 5 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 5) | q3 : int(1..4)]) <= 4, + and([q5 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q5] < x_ExplicitVarSizeWithMarker_Values[q5 + 1] + | q5 : int(1..3)]), + and([q6 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q6] = 1 | q6 : int(1..4)]), + x_ExplicitVarSizeWithMarker_Marker <= 4, + and([q9 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithDummy[q11] != 5 /\ + x_ExplicitVarSizeWithDummy[q11] = x_ExplicitVarSizeWithMarker_Values[q9] + | q11 : int(1..4)]) + | q9 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q13] != 5 -> + or([q15 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q15] = x_ExplicitVarSizeWithDummy[q13] + | q15 : int(1..4)]) + | q13 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q16 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q16] < x_ExplicitVarSizeWithFlags_Values[q16 + 1] + | q16 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q17] = false -> x_ExplicitVarSizeWithFlags_Values[q17] = 1 + | q17 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q18 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q18] | q18 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q19]) | q19 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithFlags_Flags[q22] -> + or([x_ExplicitVarSizeWithDummy[q24] != 5 /\ + x_ExplicitVarSizeWithDummy[q24] = x_ExplicitVarSizeWithFlags_Values[q22] + | q24 : int(1..4)]) + | q22 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q26] != 5 -> + or([x_ExplicitVarSizeWithFlags_Flags[q28] /\ + x_ExplicitVarSizeWithFlags_Values[q28] = x_ExplicitVarSizeWithDummy[q26] + | q28 : int(1..4)]) + | q26 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q30] -> + or([q32 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q32] = x_ExplicitVarSizeWithFlags_Values[q30] + | q32 : int(1..4)]) + | q30 : int(1..4)]), + and([q34 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithFlags_Flags[q36] /\ + x_ExplicitVarSizeWithFlags_Values[q36] = x_ExplicitVarSizeWithMarker_Values[q34] + | q36 : int(1..4)]) + | q34 : int(1..4)]), + sum([toInt(x_Occurrence[q37]) | q37 : int(1..4)]) <= 4, + and([x_Occurrence[q38] -> + or([x_ExplicitVarSizeWithDummy[q40] != 5 /\ x_ExplicitVarSizeWithDummy[q40] = q38 | q40 : int(1..4)]) + | q38 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q42] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q42]] | q42 : int(1..4)]), + and([x_Occurrence[q43] -> + or([q45 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q45] = q43 + | q45 : int(1..4)]) + | q43 : int(1..4)]), + and([q47 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q47]] + | q47 : int(1..4)]), + and([x_Occurrence[q48] -> + or([x_ExplicitVarSizeWithFlags_Flags[q50] /\ x_ExplicitVarSizeWithFlags_Values[q50] = q48 | q50 : int(1..4)]) + | q48 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q52] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q52]] + | q52 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set06/expected/model_2_3_4_2-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_2_3_4_2-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_2_3_4_2-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_2_3_4_2-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_2_3_4_2-solution000002.solution new file mode 100644 index 0000000000..85149821f6 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_2_3_4_2-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_2_3_4_2.eprime b/tests/exhaustive/basic/set06/expected/model_2_3_4_2.eprime new file mode 100644 index 0000000000..1359af27c8 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_2_3_4_2.eprime @@ -0,0 +1,61 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +branching on + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy, + x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] +such that + or([x_ExplicitVarSizeWithDummy[q38] != 5 /\ x_ExplicitVarSizeWithDummy[q38] = 1 | q38 : int(1..4)]), + or([q40 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q40] = 2 | q40 : int(1..4)]), + or([x_ExplicitVarSizeWithFlags_Flags[q42] /\ x_ExplicitVarSizeWithFlags_Values[q42] = 3 | q42 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 5 + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q2] = 5 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 5) | q3 : int(1..4)]) <= 4, + and([q5 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q5] < x_ExplicitVarSizeWithMarker_Values[q5 + 1] + | q5 : int(1..3)]), + and([q6 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q6] = 1 | q6 : int(1..4)]), + x_ExplicitVarSizeWithMarker_Marker <= 4, + and([q9 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithDummy[q11] != 5 /\ + x_ExplicitVarSizeWithDummy[q11] = x_ExplicitVarSizeWithMarker_Values[q9] + | q11 : int(1..4)]) + | q9 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q13] != 5 -> + or([q15 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q15] = x_ExplicitVarSizeWithDummy[q13] + | q15 : int(1..4)]) + | q13 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q16 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q16] < x_ExplicitVarSizeWithFlags_Values[q16 + 1] + | q16 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q17] = false -> x_ExplicitVarSizeWithFlags_Values[q17] = 1 + | q17 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q18 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q18] | q18 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q19]) | q19 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithFlags_Flags[q22] -> + or([x_ExplicitVarSizeWithDummy[q24] != 5 /\ + x_ExplicitVarSizeWithDummy[q24] = x_ExplicitVarSizeWithFlags_Values[q22] + | q24 : int(1..4)]) + | q22 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q26] != 5 -> + or([x_ExplicitVarSizeWithFlags_Flags[q28] /\ + x_ExplicitVarSizeWithFlags_Values[q28] = x_ExplicitVarSizeWithDummy[q26] + | q28 : int(1..4)]) + | q26 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q30] -> + or([q32 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q32] = x_ExplicitVarSizeWithFlags_Values[q30] + | q32 : int(1..4)]) + | q30 : int(1..4)]), + and([q34 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithFlags_Flags[q36] /\ + x_ExplicitVarSizeWithFlags_Values[q36] = x_ExplicitVarSizeWithMarker_Values[q34] + | q36 : int(1..4)]) + | q34 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set06/expected/model_2_4_1_1-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_2_4_1_1-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_2_4_1_1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_2_4_1_1-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_2_4_1_1-solution000002.solution new file mode 100644 index 0000000000..85149821f6 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_2_4_1_1-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_2_4_1_1.eprime b/tests/exhaustive/basic/set06/expected/model_2_4_1_1.eprime new file mode 100644 index 0000000000..632496e075 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_2_4_1_1.eprime @@ -0,0 +1,43 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_Occurrence: matrix indexed by [int(1..4)] of bool +branching on + [x_Occurrence, x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] +such that + or([x_ExplicitVarSizeWithDummy[q30] != 5 /\ x_ExplicitVarSizeWithDummy[q30] = 1 | q30 : int(1..4)]), + or([x_ExplicitVarSizeWithFlags_Flags[q32] /\ x_ExplicitVarSizeWithFlags_Values[q32] = 2 | q32 : int(1..4)]), + x_Occurrence[3], + and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 5 + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q2] = 5 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 5) | q3 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithFlags_Flags[q5 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q5] < x_ExplicitVarSizeWithFlags_Values[q5 + 1] + | q5 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q6] = false -> x_ExplicitVarSizeWithFlags_Values[q6] = 1 | q6 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q7] | q7 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q8]) | q8 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithFlags_Flags[q11] -> + or([x_ExplicitVarSizeWithDummy[q13] != 5 /\ + x_ExplicitVarSizeWithDummy[q13] = x_ExplicitVarSizeWithFlags_Values[q11] + | q13 : int(1..4)]) + | q11 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q15] != 5 -> + or([x_ExplicitVarSizeWithFlags_Flags[q17] /\ + x_ExplicitVarSizeWithFlags_Values[q17] = x_ExplicitVarSizeWithDummy[q15] + | q17 : int(1..4)]) + | q15 : int(1..4)]), + sum([toInt(x_Occurrence[q18]) | q18 : int(1..4)]) <= 4, + and([x_Occurrence[q19] -> + or([x_ExplicitVarSizeWithDummy[q21] != 5 /\ x_ExplicitVarSizeWithDummy[q21] = q19 | q21 : int(1..4)]) + | q19 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q23] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q23]] | q23 : int(1..4)]), + and([x_Occurrence[q24] -> + or([x_ExplicitVarSizeWithFlags_Flags[q26] /\ x_ExplicitVarSizeWithFlags_Values[q26] = q24 | q26 : int(1..4)]) + | q24 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q28] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q28]] + | q28 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set06/expected/model_2_4_1_3-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_2_4_1_3-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_2_4_1_3-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_2_4_1_3-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_2_4_1_3-solution000002.solution new file mode 100644 index 0000000000..85149821f6 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_2_4_1_3-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_2_4_1_3.eprime b/tests/exhaustive/basic/set06/expected/model_2_4_1_3.eprime new file mode 100644 index 0000000000..1e494d1026 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_2_4_1_3.eprime @@ -0,0 +1,77 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_Occurrence: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +branching on + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy, + x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_Occurrence] +such that + or([x_ExplicitVarSizeWithDummy[q54] != 5 /\ x_ExplicitVarSizeWithDummy[q54] = 1 | q54 : int(1..4)]), + or([x_ExplicitVarSizeWithFlags_Flags[q56] /\ x_ExplicitVarSizeWithFlags_Values[q56] = 2 | q56 : int(1..4)]), + x_Occurrence[3], + and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 5 + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q2] = 5 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 5) | q3 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithFlags_Flags[q5 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q5] < x_ExplicitVarSizeWithFlags_Values[q5 + 1] + | q5 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q6] = false -> x_ExplicitVarSizeWithFlags_Values[q6] = 1 | q6 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q7] | q7 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q8]) | q8 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithFlags_Flags[q11] -> + or([x_ExplicitVarSizeWithDummy[q13] != 5 /\ + x_ExplicitVarSizeWithDummy[q13] = x_ExplicitVarSizeWithFlags_Values[q11] + | q13 : int(1..4)]) + | q11 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q15] != 5 -> + or([x_ExplicitVarSizeWithFlags_Flags[q17] /\ + x_ExplicitVarSizeWithFlags_Values[q17] = x_ExplicitVarSizeWithDummy[q15] + | q17 : int(1..4)]) + | q15 : int(1..4)]), + sum([toInt(x_Occurrence[q18]) | q18 : int(1..4)]) <= 4, + and([x_Occurrence[q43] -> + or([x_ExplicitVarSizeWithDummy[q45] != 5 /\ x_ExplicitVarSizeWithDummy[q45] = q43 | q45 : int(1..4)]) + | q43 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q47] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q47]] | q47 : int(1..4)]), + and([x_Occurrence[q48] -> + or([x_ExplicitVarSizeWithFlags_Flags[q50] /\ x_ExplicitVarSizeWithFlags_Values[q50] = q48 | q50 : int(1..4)]) + | q48 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q52] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q52]] + | q52 : int(1..4)]), + and([q19 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q19] < x_ExplicitVarSizeWithMarker_Values[q19 + 1] + | q19 : int(1..3)]), + and([q20 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q20] = 1 | q20 : int(1..4)]), + x_ExplicitVarSizeWithMarker_Marker <= 4, + and([q23 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithDummy[q25] != 5 /\ + x_ExplicitVarSizeWithDummy[q25] = x_ExplicitVarSizeWithMarker_Values[q23] + | q25 : int(1..4)]) + | q23 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q27] != 5 -> + or([q29 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q29] = x_ExplicitVarSizeWithDummy[q27] + | q29 : int(1..4)]) + | q27 : int(1..4)]), + and([q31 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithFlags_Flags[q33] /\ + x_ExplicitVarSizeWithFlags_Values[q33] = x_ExplicitVarSizeWithMarker_Values[q31] + | q33 : int(1..4)]) + | q31 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q35] -> + or([q37 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q37] = x_ExplicitVarSizeWithFlags_Values[q35] + | q37 : int(1..4)]) + | q35 : int(1..4)]), + and([q39 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q39]] + | q39 : int(1..4)]), + and([x_Occurrence[q40] -> + or([q42 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q42] = q40 + | q42 : int(1..4)]) + | q40 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set06/expected/model_2_4_2_1-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_2_4_2_1-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_2_4_2_1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_2_4_2_1-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_2_4_2_1-solution000002.solution new file mode 100644 index 0000000000..85149821f6 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_2_4_2_1-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_2_4_2_1.eprime b/tests/exhaustive/basic/set06/expected/model_2_4_2_1.eprime new file mode 100644 index 0000000000..fc14f2c0db --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_2_4_2_1.eprime @@ -0,0 +1,43 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_Occurrence: matrix indexed by [int(1..4)] of bool +branching on + [x_Occurrence, x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] +such that + or([x_ExplicitVarSizeWithDummy[q30] != 5 /\ x_ExplicitVarSizeWithDummy[q30] = 1 | q30 : int(1..4)]), + or([x_ExplicitVarSizeWithFlags_Flags[q32] /\ x_ExplicitVarSizeWithFlags_Values[q32] = 2 | q32 : int(1..4)]), + or([x_ExplicitVarSizeWithDummy[q34] != 5 /\ x_ExplicitVarSizeWithDummy[q34] = 3 | q34 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 5 + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q2] = 5 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 5) | q3 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithFlags_Flags[q5 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q5] < x_ExplicitVarSizeWithFlags_Values[q5 + 1] + | q5 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q6] = false -> x_ExplicitVarSizeWithFlags_Values[q6] = 1 | q6 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q7] | q7 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q8]) | q8 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithFlags_Flags[q11] -> + or([x_ExplicitVarSizeWithDummy[q13] != 5 /\ + x_ExplicitVarSizeWithDummy[q13] = x_ExplicitVarSizeWithFlags_Values[q11] + | q13 : int(1..4)]) + | q11 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q15] != 5 -> + or([x_ExplicitVarSizeWithFlags_Flags[q17] /\ + x_ExplicitVarSizeWithFlags_Values[q17] = x_ExplicitVarSizeWithDummy[q15] + | q17 : int(1..4)]) + | q15 : int(1..4)]), + sum([toInt(x_Occurrence[q18]) | q18 : int(1..4)]) <= 4, + and([x_Occurrence[q19] -> + or([x_ExplicitVarSizeWithDummy[q21] != 5 /\ x_ExplicitVarSizeWithDummy[q21] = q19 | q21 : int(1..4)]) + | q19 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q23] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q23]] | q23 : int(1..4)]), + and([x_Occurrence[q24] -> + or([x_ExplicitVarSizeWithFlags_Flags[q26] /\ x_ExplicitVarSizeWithFlags_Values[q26] = q24 | q26 : int(1..4)]) + | q24 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q28] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q28]] + | q28 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set06/expected/model_2_4_2_2-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_2_4_2_2-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_2_4_2_2-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_2_4_2_2-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_2_4_2_2-solution000002.solution new file mode 100644 index 0000000000..85149821f6 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_2_4_2_2-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_2_4_2_2.eprime b/tests/exhaustive/basic/set06/expected/model_2_4_2_2.eprime new file mode 100644 index 0000000000..c887a723c4 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_2_4_2_2.eprime @@ -0,0 +1,31 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +branching on [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy] +such that + or([x_ExplicitVarSizeWithDummy[q19] != 5 /\ x_ExplicitVarSizeWithDummy[q19] = 1 | q19 : int(1..4)]), + or([x_ExplicitVarSizeWithFlags_Flags[q21] /\ x_ExplicitVarSizeWithFlags_Values[q21] = 2 | q21 : int(1..4)]), + or([x_ExplicitVarSizeWithDummy[q23] != 5 /\ x_ExplicitVarSizeWithDummy[q23] = 3 | q23 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 5 + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q2] = 5 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 5) | q3 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithFlags_Flags[q5 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q5] < x_ExplicitVarSizeWithFlags_Values[q5 + 1] + | q5 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q6] = false -> x_ExplicitVarSizeWithFlags_Values[q6] = 1 | q6 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q7] | q7 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q8]) | q8 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithFlags_Flags[q11] -> + or([x_ExplicitVarSizeWithDummy[q13] != 5 /\ + x_ExplicitVarSizeWithDummy[q13] = x_ExplicitVarSizeWithFlags_Values[q11] + | q13 : int(1..4)]) + | q11 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q15] != 5 -> + or([x_ExplicitVarSizeWithFlags_Flags[q17] /\ + x_ExplicitVarSizeWithFlags_Values[q17] = x_ExplicitVarSizeWithDummy[q15] + | q17 : int(1..4)]) + | q15 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set06/expected/model_2_4_2_3-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_2_4_2_3-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_2_4_2_3-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_2_4_2_3-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_2_4_2_3-solution000002.solution new file mode 100644 index 0000000000..85149821f6 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_2_4_2_3-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_2_4_2_3.eprime b/tests/exhaustive/basic/set06/expected/model_2_4_2_3.eprime new file mode 100644 index 0000000000..9f009dc6b0 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_2_4_2_3.eprime @@ -0,0 +1,60 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +branching on + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy, + x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] +such that + or([x_ExplicitVarSizeWithDummy[q38] != 5 /\ x_ExplicitVarSizeWithDummy[q38] = 1 | q38 : int(1..4)]), + or([x_ExplicitVarSizeWithFlags_Flags[q40] /\ x_ExplicitVarSizeWithFlags_Values[q40] = 2 | q40 : int(1..4)]), + or([x_ExplicitVarSizeWithDummy[q42] != 5 /\ x_ExplicitVarSizeWithDummy[q42] = 3 | q42 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 5 + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q2] = 5 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 5) | q3 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithFlags_Flags[q5 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q5] < x_ExplicitVarSizeWithFlags_Values[q5 + 1] + | q5 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q6] = false -> x_ExplicitVarSizeWithFlags_Values[q6] = 1 | q6 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q7] | q7 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q8]) | q8 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithFlags_Flags[q11] -> + or([x_ExplicitVarSizeWithDummy[q13] != 5 /\ + x_ExplicitVarSizeWithDummy[q13] = x_ExplicitVarSizeWithFlags_Values[q11] + | q13 : int(1..4)]) + | q11 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q15] != 5 -> + or([x_ExplicitVarSizeWithFlags_Flags[q17] /\ + x_ExplicitVarSizeWithFlags_Values[q17] = x_ExplicitVarSizeWithDummy[q15] + | q17 : int(1..4)]) + | q15 : int(1..4)]), + and([q18 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q18] < x_ExplicitVarSizeWithMarker_Values[q18 + 1] + | q18 : int(1..3)]), + and([q19 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q19] = 1 | q19 : int(1..4)]), + x_ExplicitVarSizeWithMarker_Marker <= 4, + and([q22 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithDummy[q24] != 5 /\ + x_ExplicitVarSizeWithDummy[q24] = x_ExplicitVarSizeWithMarker_Values[q22] + | q24 : int(1..4)]) + | q22 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q26] != 5 -> + or([q28 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q28] = x_ExplicitVarSizeWithDummy[q26] + | q28 : int(1..4)]) + | q26 : int(1..4)]), + and([q30 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithFlags_Flags[q32] /\ + x_ExplicitVarSizeWithFlags_Values[q32] = x_ExplicitVarSizeWithMarker_Values[q30] + | q32 : int(1..4)]) + | q30 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q34] -> + or([q36 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q36] = x_ExplicitVarSizeWithFlags_Values[q34] + | q36 : int(1..4)]) + | q34 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set06/expected/model_2_4_3_1-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_2_4_3_1-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_2_4_3_1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_2_4_3_1-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_2_4_3_1-solution000002.solution new file mode 100644 index 0000000000..85149821f6 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_2_4_3_1-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_2_4_3_1.eprime b/tests/exhaustive/basic/set06/expected/model_2_4_3_1.eprime new file mode 100644 index 0000000000..c5d220fcc3 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_2_4_3_1.eprime @@ -0,0 +1,77 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_Occurrence: matrix indexed by [int(1..4)] of bool +branching on + [x_Occurrence, x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, + x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] +such that + or([x_ExplicitVarSizeWithDummy[q54] != 5 /\ x_ExplicitVarSizeWithDummy[q54] = 1 | q54 : int(1..4)]), + or([x_ExplicitVarSizeWithFlags_Flags[q56] /\ x_ExplicitVarSizeWithFlags_Values[q56] = 2 | q56 : int(1..4)]), + or([q58 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q58] = 3 | q58 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 5 + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q2] = 5 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 5) | q3 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithFlags_Flags[q5 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q5] < x_ExplicitVarSizeWithFlags_Values[q5 + 1] + | q5 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q6] = false -> x_ExplicitVarSizeWithFlags_Values[q6] = 1 | q6 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q7] | q7 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q8]) | q8 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithFlags_Flags[q11] -> + or([x_ExplicitVarSizeWithDummy[q13] != 5 /\ + x_ExplicitVarSizeWithDummy[q13] = x_ExplicitVarSizeWithFlags_Values[q11] + | q13 : int(1..4)]) + | q11 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q15] != 5 -> + or([x_ExplicitVarSizeWithFlags_Flags[q17] /\ + x_ExplicitVarSizeWithFlags_Values[q17] = x_ExplicitVarSizeWithDummy[q15] + | q17 : int(1..4)]) + | q15 : int(1..4)]), + and([q18 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q18] < x_ExplicitVarSizeWithMarker_Values[q18 + 1] + | q18 : int(1..3)]), + and([q19 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q19] = 1 | q19 : int(1..4)]), + x_ExplicitVarSizeWithMarker_Marker <= 4, + and([q22 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithDummy[q24] != 5 /\ + x_ExplicitVarSizeWithDummy[q24] = x_ExplicitVarSizeWithMarker_Values[q22] + | q24 : int(1..4)]) + | q22 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q26] != 5 -> + or([q28 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q28] = x_ExplicitVarSizeWithDummy[q26] + | q28 : int(1..4)]) + | q26 : int(1..4)]), + and([q30 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithFlags_Flags[q32] /\ + x_ExplicitVarSizeWithFlags_Values[q32] = x_ExplicitVarSizeWithMarker_Values[q30] + | q32 : int(1..4)]) + | q30 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q34] -> + or([q36 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q36] = x_ExplicitVarSizeWithFlags_Values[q34] + | q36 : int(1..4)]) + | q34 : int(1..4)]), + sum([toInt(x_Occurrence[q37]) | q37 : int(1..4)]) <= 4, + and([x_Occurrence[q38] -> + or([x_ExplicitVarSizeWithDummy[q40] != 5 /\ x_ExplicitVarSizeWithDummy[q40] = q38 | q40 : int(1..4)]) + | q38 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q42] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q42]] | q42 : int(1..4)]), + and([x_Occurrence[q43] -> + or([x_ExplicitVarSizeWithFlags_Flags[q45] /\ x_ExplicitVarSizeWithFlags_Values[q45] = q43 | q45 : int(1..4)]) + | q43 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q47] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q47]] + | q47 : int(1..4)]), + and([x_Occurrence[q48] -> + or([q50 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q50] = q48 + | q50 : int(1..4)]) + | q48 : int(1..4)]), + and([q52 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q52]] + | q52 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set06/expected/model_2_4_3_2-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_2_4_3_2-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_2_4_3_2-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_2_4_3_2-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_2_4_3_2-solution000002.solution new file mode 100644 index 0000000000..85149821f6 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_2_4_3_2-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_2_4_3_2.eprime b/tests/exhaustive/basic/set06/expected/model_2_4_3_2.eprime new file mode 100644 index 0000000000..58bc43d769 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_2_4_3_2.eprime @@ -0,0 +1,60 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +branching on + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy, + x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] +such that + or([x_ExplicitVarSizeWithDummy[q38] != 5 /\ x_ExplicitVarSizeWithDummy[q38] = 1 | q38 : int(1..4)]), + or([x_ExplicitVarSizeWithFlags_Flags[q40] /\ x_ExplicitVarSizeWithFlags_Values[q40] = 2 | q40 : int(1..4)]), + or([q42 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q42] = 3 | q42 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 5 + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q2] = 5 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 5) | q3 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithFlags_Flags[q5 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q5] < x_ExplicitVarSizeWithFlags_Values[q5 + 1] + | q5 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q6] = false -> x_ExplicitVarSizeWithFlags_Values[q6] = 1 | q6 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q7] | q7 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q8]) | q8 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithFlags_Flags[q11] -> + or([x_ExplicitVarSizeWithDummy[q13] != 5 /\ + x_ExplicitVarSizeWithDummy[q13] = x_ExplicitVarSizeWithFlags_Values[q11] + | q13 : int(1..4)]) + | q11 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q15] != 5 -> + or([x_ExplicitVarSizeWithFlags_Flags[q17] /\ + x_ExplicitVarSizeWithFlags_Values[q17] = x_ExplicitVarSizeWithDummy[q15] + | q17 : int(1..4)]) + | q15 : int(1..4)]), + and([q18 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q18] < x_ExplicitVarSizeWithMarker_Values[q18 + 1] + | q18 : int(1..3)]), + and([q19 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q19] = 1 | q19 : int(1..4)]), + x_ExplicitVarSizeWithMarker_Marker <= 4, + and([q22 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithDummy[q24] != 5 /\ + x_ExplicitVarSizeWithDummy[q24] = x_ExplicitVarSizeWithMarker_Values[q22] + | q24 : int(1..4)]) + | q22 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q26] != 5 -> + or([q28 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q28] = x_ExplicitVarSizeWithDummy[q26] + | q28 : int(1..4)]) + | q26 : int(1..4)]), + and([q30 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithFlags_Flags[q32] /\ + x_ExplicitVarSizeWithFlags_Values[q32] = x_ExplicitVarSizeWithMarker_Values[q30] + | q32 : int(1..4)]) + | q30 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q34] -> + or([q36 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q36] = x_ExplicitVarSizeWithFlags_Values[q34] + | q36 : int(1..4)]) + | q34 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set06/expected/model_2_4_4_1-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_2_4_4_1-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_2_4_4_1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_2_4_4_1-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_2_4_4_1-solution000002.solution new file mode 100644 index 0000000000..85149821f6 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_2_4_4_1-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_2_4_4_1.eprime b/tests/exhaustive/basic/set06/expected/model_2_4_4_1.eprime new file mode 100644 index 0000000000..5312aea309 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_2_4_4_1.eprime @@ -0,0 +1,43 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_Occurrence: matrix indexed by [int(1..4)] of bool +branching on + [x_Occurrence, x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] +such that + or([x_ExplicitVarSizeWithDummy[q30] != 5 /\ x_ExplicitVarSizeWithDummy[q30] = 1 | q30 : int(1..4)]), + or([x_ExplicitVarSizeWithFlags_Flags[q32] /\ x_ExplicitVarSizeWithFlags_Values[q32] = 2 | q32 : int(1..4)]), + or([x_ExplicitVarSizeWithFlags_Flags[q34] /\ x_ExplicitVarSizeWithFlags_Values[q34] = 3 | q34 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 5 + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q2] = 5 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 5) | q3 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithFlags_Flags[q5 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q5] < x_ExplicitVarSizeWithFlags_Values[q5 + 1] + | q5 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q6] = false -> x_ExplicitVarSizeWithFlags_Values[q6] = 1 | q6 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q7] | q7 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q8]) | q8 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithFlags_Flags[q11] -> + or([x_ExplicitVarSizeWithDummy[q13] != 5 /\ + x_ExplicitVarSizeWithDummy[q13] = x_ExplicitVarSizeWithFlags_Values[q11] + | q13 : int(1..4)]) + | q11 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q15] != 5 -> + or([x_ExplicitVarSizeWithFlags_Flags[q17] /\ + x_ExplicitVarSizeWithFlags_Values[q17] = x_ExplicitVarSizeWithDummy[q15] + | q17 : int(1..4)]) + | q15 : int(1..4)]), + sum([toInt(x_Occurrence[q18]) | q18 : int(1..4)]) <= 4, + and([x_Occurrence[q19] -> + or([x_ExplicitVarSizeWithDummy[q21] != 5 /\ x_ExplicitVarSizeWithDummy[q21] = q19 | q21 : int(1..4)]) + | q19 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q23] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q23]] | q23 : int(1..4)]), + and([x_Occurrence[q24] -> + or([x_ExplicitVarSizeWithFlags_Flags[q26] /\ x_ExplicitVarSizeWithFlags_Values[q26] = q24 | q26 : int(1..4)]) + | q24 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q28] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q28]] + | q28 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set06/expected/model_2_4_4_2-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_2_4_4_2-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_2_4_4_2-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_2_4_4_2-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_2_4_4_2-solution000002.solution new file mode 100644 index 0000000000..85149821f6 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_2_4_4_2-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_2_4_4_2.eprime b/tests/exhaustive/basic/set06/expected/model_2_4_4_2.eprime new file mode 100644 index 0000000000..819431e7aa --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_2_4_4_2.eprime @@ -0,0 +1,31 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +branching on [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy] +such that + or([x_ExplicitVarSizeWithDummy[q19] != 5 /\ x_ExplicitVarSizeWithDummy[q19] = 1 | q19 : int(1..4)]), + or([x_ExplicitVarSizeWithFlags_Flags[q21] /\ x_ExplicitVarSizeWithFlags_Values[q21] = 2 | q21 : int(1..4)]), + or([x_ExplicitVarSizeWithFlags_Flags[q23] /\ x_ExplicitVarSizeWithFlags_Values[q23] = 3 | q23 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 5 + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q2] = 5 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 5) | q3 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithFlags_Flags[q5 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q5] < x_ExplicitVarSizeWithFlags_Values[q5 + 1] + | q5 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q6] = false -> x_ExplicitVarSizeWithFlags_Values[q6] = 1 | q6 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q7] | q7 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q8]) | q8 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithFlags_Flags[q11] -> + or([x_ExplicitVarSizeWithDummy[q13] != 5 /\ + x_ExplicitVarSizeWithDummy[q13] = x_ExplicitVarSizeWithFlags_Values[q11] + | q13 : int(1..4)]) + | q11 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q15] != 5 -> + or([x_ExplicitVarSizeWithFlags_Flags[q17] /\ + x_ExplicitVarSizeWithFlags_Values[q17] = x_ExplicitVarSizeWithDummy[q15] + | q17 : int(1..4)]) + | q15 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set06/expected/model_2_4_4_3-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_2_4_4_3-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_2_4_4_3-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_2_4_4_3-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_2_4_4_3-solution000002.solution new file mode 100644 index 0000000000..85149821f6 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_2_4_4_3-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_2_4_4_3.eprime b/tests/exhaustive/basic/set06/expected/model_2_4_4_3.eprime new file mode 100644 index 0000000000..7c6e3d9d88 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_2_4_4_3.eprime @@ -0,0 +1,60 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +branching on + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy, + x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] +such that + or([x_ExplicitVarSizeWithDummy[q38] != 5 /\ x_ExplicitVarSizeWithDummy[q38] = 1 | q38 : int(1..4)]), + or([x_ExplicitVarSizeWithFlags_Flags[q40] /\ x_ExplicitVarSizeWithFlags_Values[q40] = 2 | q40 : int(1..4)]), + or([x_ExplicitVarSizeWithFlags_Flags[q42] /\ x_ExplicitVarSizeWithFlags_Values[q42] = 3 | q42 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 5 + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q2] = 5 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 5) | q3 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithFlags_Flags[q5 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q5] < x_ExplicitVarSizeWithFlags_Values[q5 + 1] + | q5 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q6] = false -> x_ExplicitVarSizeWithFlags_Values[q6] = 1 | q6 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q7] | q7 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q8]) | q8 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithFlags_Flags[q11] -> + or([x_ExplicitVarSizeWithDummy[q13] != 5 /\ + x_ExplicitVarSizeWithDummy[q13] = x_ExplicitVarSizeWithFlags_Values[q11] + | q13 : int(1..4)]) + | q11 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q15] != 5 -> + or([x_ExplicitVarSizeWithFlags_Flags[q17] /\ + x_ExplicitVarSizeWithFlags_Values[q17] = x_ExplicitVarSizeWithDummy[q15] + | q17 : int(1..4)]) + | q15 : int(1..4)]), + and([q18 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q18] < x_ExplicitVarSizeWithMarker_Values[q18 + 1] + | q18 : int(1..3)]), + and([q19 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q19] = 1 | q19 : int(1..4)]), + x_ExplicitVarSizeWithMarker_Marker <= 4, + and([q22 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithDummy[q24] != 5 /\ + x_ExplicitVarSizeWithDummy[q24] = x_ExplicitVarSizeWithMarker_Values[q22] + | q24 : int(1..4)]) + | q22 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q26] != 5 -> + or([q28 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q28] = x_ExplicitVarSizeWithDummy[q26] + | q28 : int(1..4)]) + | q26 : int(1..4)]), + and([q30 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithFlags_Flags[q32] /\ + x_ExplicitVarSizeWithFlags_Values[q32] = x_ExplicitVarSizeWithMarker_Values[q30] + | q32 : int(1..4)]) + | q30 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q34] -> + or([q36 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q36] = x_ExplicitVarSizeWithFlags_Values[q34] + | q36 : int(1..4)]) + | q34 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set06/expected/model_3_1_1_1-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_3_1_1_1-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_3_1_1_1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_3_1_1_1-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_3_1_1_1-solution000002.solution new file mode 100644 index 0000000000..85149821f6 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_3_1_1_1-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_3_1_1_1.eprime b/tests/exhaustive/basic/set06/expected/model_3_1_1_1.eprime new file mode 100644 index 0000000000..b786f3d150 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_3_1_1_1.eprime @@ -0,0 +1,22 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_Occurrence: matrix indexed by [int(1..4)] of bool +branching on [x_Occurrence, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] +such that + or([q11 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q11] = 1 | q11 : int(1..4)]), + x_Occurrence[2], + x_Occurrence[3], + and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] + | q1 : int(1..3)]), + and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..4)]), + x_ExplicitVarSizeWithMarker_Marker <= 4, + sum([toInt(x_Occurrence[q4]) | q4 : int(1..4)]) <= 4, + and([x_Occurrence[q5] -> + or([q7 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q7] = q5 | q7 : int(1..4)]) + | q5 : int(1..4)]), + and([q9 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q9]] + | q9 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set06/expected/model_3_1_1_2-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_3_1_1_2-solution000001.solution new file mode 100644 index 0000000000..85149821f6 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_3_1_1_2-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_3_1_1_2-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_3_1_1_2-solution000002.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_3_1_1_2-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_3_1_1_2.eprime b/tests/exhaustive/basic/set06/expected/model_3_1_1_2.eprime new file mode 100644 index 0000000000..8f65d99356 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_3_1_1_2.eprime @@ -0,0 +1,43 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_Occurrence: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +branching on + [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_Occurrence] +such that + or([q28 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q28] = 1 | q28 : int(1..4)]), + x_Occurrence[2], + x_Occurrence[3], + and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] + | q1 : int(1..3)]), + and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..4)]), + x_ExplicitVarSizeWithMarker_Marker <= 4, + sum([toInt(x_Occurrence[q4]) | q4 : int(1..4)]) <= 4, + and([x_Occurrence[q22] -> + or([q24 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q24] = q22 + | q24 : int(1..4)]) + | q22 : int(1..4)]), + and([q26 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q26]] + | q26 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q5] < x_ExplicitVarSizeWithDummy[q5 + 1] \/ x_ExplicitVarSizeWithDummy[q5] = 5 + | q5 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q6] = 5 -> x_ExplicitVarSizeWithDummy[q6 + 1] = 5 | q6 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithDummy[q7] != 5) | q7 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithDummy[q10] != 5 -> + or([q12 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q12] = x_ExplicitVarSizeWithDummy[q10] + | q12 : int(1..4)]) + | q10 : int(1..4)]), + and([q14 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithDummy[q16] != 5 /\ + x_ExplicitVarSizeWithDummy[q16] = x_ExplicitVarSizeWithMarker_Values[q14] + | q16 : int(1..4)]) + | q14 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q18] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q18]] | q18 : int(1..4)]), + and([x_Occurrence[q19] -> + or([x_ExplicitVarSizeWithDummy[q21] != 5 /\ x_ExplicitVarSizeWithDummy[q21] = q19 | q21 : int(1..4)]) + | q19 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set06/expected/model_3_1_1_4-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_3_1_1_4-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_3_1_1_4-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_3_1_1_4-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_3_1_1_4-solution000002.solution new file mode 100644 index 0000000000..85149821f6 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_3_1_1_4-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_3_1_1_4.eprime b/tests/exhaustive/basic/set06/expected/model_3_1_1_4.eprime new file mode 100644 index 0000000000..a8dbd5fdde --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_3_1_1_4.eprime @@ -0,0 +1,48 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_Occurrence: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +branching on + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithMarker_Marker, + x_ExplicitVarSizeWithMarker_Values, x_Occurrence] +such that + or([q29 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q29] = 1 | q29 : int(1..4)]), + x_Occurrence[2], + x_Occurrence[3], + and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] + | q1 : int(1..3)]), + and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..4)]), + x_ExplicitVarSizeWithMarker_Marker <= 4, + sum([toInt(x_Occurrence[q4]) | q4 : int(1..4)]) <= 4, + and([x_Occurrence[q23] -> + or([q25 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q25] = q23 + | q25 : int(1..4)]) + | q23 : int(1..4)]), + and([q27 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q27]] + | q27 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q5 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q5] < x_ExplicitVarSizeWithFlags_Values[q5 + 1] + | q5 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q6] = false -> x_ExplicitVarSizeWithFlags_Values[q6] = 1 | q6 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q7] | q7 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q8]) | q8 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithFlags_Flags[q11] -> + or([q13 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q13] = x_ExplicitVarSizeWithFlags_Values[q11] + | q13 : int(1..4)]) + | q11 : int(1..4)]), + and([q15 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithFlags_Flags[q17] /\ + x_ExplicitVarSizeWithFlags_Values[q17] = x_ExplicitVarSizeWithMarker_Values[q15] + | q17 : int(1..4)]) + | q15 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q19] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q19]] + | q19 : int(1..4)]), + and([x_Occurrence[q20] -> + or([x_ExplicitVarSizeWithFlags_Flags[q22] /\ x_ExplicitVarSizeWithFlags_Values[q22] = q20 | q22 : int(1..4)]) + | q20 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set06/expected/model_3_1_2_1-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_3_1_2_1-solution000001.solution new file mode 100644 index 0000000000..85149821f6 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_3_1_2_1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_3_1_2_1-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_3_1_2_1-solution000002.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_3_1_2_1-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_3_1_2_1.eprime b/tests/exhaustive/basic/set06/expected/model_3_1_2_1.eprime new file mode 100644 index 0000000000..f2fd3908db --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_3_1_2_1.eprime @@ -0,0 +1,43 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_Occurrence: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +branching on + [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_Occurrence] +such that + or([q30 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q30] = 1 | q30 : int(1..4)]), + x_Occurrence[2], + or([x_ExplicitVarSizeWithDummy[q28] != 5 /\ x_ExplicitVarSizeWithDummy[q28] = 3 | q28 : int(1..4)]), + and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] + | q1 : int(1..3)]), + and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..4)]), + x_ExplicitVarSizeWithMarker_Marker <= 4, + sum([toInt(x_Occurrence[q4]) | q4 : int(1..4)]) <= 4, + and([x_Occurrence[q22] -> + or([q24 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q24] = q22 + | q24 : int(1..4)]) + | q22 : int(1..4)]), + and([q26 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q26]] + | q26 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q5] < x_ExplicitVarSizeWithDummy[q5 + 1] \/ x_ExplicitVarSizeWithDummy[q5] = 5 + | q5 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q6] = 5 -> x_ExplicitVarSizeWithDummy[q6 + 1] = 5 | q6 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithDummy[q7] != 5) | q7 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithDummy[q10] != 5 -> + or([q12 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q12] = x_ExplicitVarSizeWithDummy[q10] + | q12 : int(1..4)]) + | q10 : int(1..4)]), + and([q14 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithDummy[q16] != 5 /\ + x_ExplicitVarSizeWithDummy[q16] = x_ExplicitVarSizeWithMarker_Values[q14] + | q16 : int(1..4)]) + | q14 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q18] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q18]] | q18 : int(1..4)]), + and([x_Occurrence[q19] -> + or([x_ExplicitVarSizeWithDummy[q21] != 5 /\ x_ExplicitVarSizeWithDummy[q21] = q19 | q21 : int(1..4)]) + | q19 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set06/expected/model_3_1_2_4-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_3_1_2_4-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_3_1_2_4-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_3_1_2_4-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_3_1_2_4-solution000002.solution new file mode 100644 index 0000000000..85149821f6 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_3_1_2_4-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_3_1_2_4.eprime b/tests/exhaustive/basic/set06/expected/model_3_1_2_4.eprime new file mode 100644 index 0000000000..525362fb4b --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_3_1_2_4.eprime @@ -0,0 +1,78 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_Occurrence: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +branching on + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithMarker_Marker, + x_ExplicitVarSizeWithMarker_Values, x_Occurrence, x_ExplicitVarSizeWithDummy] +such that + or([q56 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q56] = 1 | q56 : int(1..4)]), + x_Occurrence[2], + or([x_ExplicitVarSizeWithDummy[q49] != 5 /\ x_ExplicitVarSizeWithDummy[q49] = 3 | q49 : int(1..4)]), + and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] + | q1 : int(1..3)]), + and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..4)]), + x_ExplicitVarSizeWithMarker_Marker <= 4, + sum([toInt(x_Occurrence[q4]) | q4 : int(1..4)]) <= 4, + and([x_Occurrence[q50] -> + or([q52 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q52] = q50 + | q52 : int(1..4)]) + | q50 : int(1..4)]), + and([q54 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q54]] + | q54 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q5] < x_ExplicitVarSizeWithDummy[q5 + 1] \/ x_ExplicitVarSizeWithDummy[q5] = 5 + | q5 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q6] = 5 -> x_ExplicitVarSizeWithDummy[q6 + 1] = 5 | q6 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithDummy[q7] != 5) | q7 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithDummy[q10] != 5 -> + or([q12 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q12] = x_ExplicitVarSizeWithDummy[q10] + | q12 : int(1..4)]) + | q10 : int(1..4)]), + and([q14 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithDummy[q16] != 5 /\ + x_ExplicitVarSizeWithDummy[q16] = x_ExplicitVarSizeWithMarker_Values[q14] + | q16 : int(1..4)]) + | q14 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q18] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q18]] | q18 : int(1..4)]), + and([x_Occurrence[q19] -> + or([x_ExplicitVarSizeWithDummy[q21] != 5 /\ x_ExplicitVarSizeWithDummy[q21] = q19 | q21 : int(1..4)]) + | q19 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q22 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q22] < x_ExplicitVarSizeWithFlags_Values[q22 + 1] + | q22 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q23] = false -> x_ExplicitVarSizeWithFlags_Values[q23] = 1 + | q23 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q24 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q24] | q24 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q25]) | q25 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithFlags_Flags[q28] -> + or([q30 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q30] = x_ExplicitVarSizeWithFlags_Values[q28] + | q30 : int(1..4)]) + | q28 : int(1..4)]), + and([q32 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithFlags_Flags[q34] /\ + x_ExplicitVarSizeWithFlags_Values[q34] = x_ExplicitVarSizeWithMarker_Values[q32] + | q34 : int(1..4)]) + | q32 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q36] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q36]] + | q36 : int(1..4)]), + and([x_Occurrence[q37] -> + or([x_ExplicitVarSizeWithFlags_Flags[q39] /\ x_ExplicitVarSizeWithFlags_Values[q39] = q37 | q39 : int(1..4)]) + | q37 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q41] -> + or([x_ExplicitVarSizeWithDummy[q43] != 5 /\ + x_ExplicitVarSizeWithDummy[q43] = x_ExplicitVarSizeWithFlags_Values[q41] + | q43 : int(1..4)]) + | q41 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q45] != 5 -> + or([x_ExplicitVarSizeWithFlags_Flags[q47] /\ + x_ExplicitVarSizeWithFlags_Values[q47] = x_ExplicitVarSizeWithDummy[q45] + | q47 : int(1..4)]) + | q45 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set06/expected/model_3_1_3_1-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_3_1_3_1-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_3_1_3_1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_3_1_3_1-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_3_1_3_1-solution000002.solution new file mode 100644 index 0000000000..85149821f6 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_3_1_3_1-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_3_1_3_1.eprime b/tests/exhaustive/basic/set06/expected/model_3_1_3_1.eprime new file mode 100644 index 0000000000..5e6282546a --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_3_1_3_1.eprime @@ -0,0 +1,22 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_Occurrence: matrix indexed by [int(1..4)] of bool +branching on [x_Occurrence, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] +such that + or([q13 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q13] = 1 | q13 : int(1..4)]), + x_Occurrence[2], + or([q11 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q11] = 3 | q11 : int(1..4)]), + and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] + | q1 : int(1..3)]), + and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..4)]), + x_ExplicitVarSizeWithMarker_Marker <= 4, + sum([toInt(x_Occurrence[q4]) | q4 : int(1..4)]) <= 4, + and([x_Occurrence[q5] -> + or([q7 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q7] = q5 | q7 : int(1..4)]) + | q5 : int(1..4)]), + and([q9 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q9]] + | q9 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set06/expected/model_3_1_3_2-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_3_1_3_2-solution000001.solution new file mode 100644 index 0000000000..85149821f6 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_3_1_3_2-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_3_1_3_2-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_3_1_3_2-solution000002.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_3_1_3_2-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_3_1_3_2.eprime b/tests/exhaustive/basic/set06/expected/model_3_1_3_2.eprime new file mode 100644 index 0000000000..b537bac469 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_3_1_3_2.eprime @@ -0,0 +1,43 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_Occurrence: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +branching on + [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_Occurrence] +such that + or([q30 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q30] = 1 | q30 : int(1..4)]), + x_Occurrence[2], + or([q28 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q28] = 3 | q28 : int(1..4)]), + and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] + | q1 : int(1..3)]), + and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..4)]), + x_ExplicitVarSizeWithMarker_Marker <= 4, + sum([toInt(x_Occurrence[q4]) | q4 : int(1..4)]) <= 4, + and([x_Occurrence[q22] -> + or([q24 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q24] = q22 + | q24 : int(1..4)]) + | q22 : int(1..4)]), + and([q26 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q26]] + | q26 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q5] < x_ExplicitVarSizeWithDummy[q5 + 1] \/ x_ExplicitVarSizeWithDummy[q5] = 5 + | q5 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q6] = 5 -> x_ExplicitVarSizeWithDummy[q6 + 1] = 5 | q6 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithDummy[q7] != 5) | q7 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithDummy[q10] != 5 -> + or([q12 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q12] = x_ExplicitVarSizeWithDummy[q10] + | q12 : int(1..4)]) + | q10 : int(1..4)]), + and([q14 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithDummy[q16] != 5 /\ + x_ExplicitVarSizeWithDummy[q16] = x_ExplicitVarSizeWithMarker_Values[q14] + | q16 : int(1..4)]) + | q14 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q18] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q18]] | q18 : int(1..4)]), + and([x_Occurrence[q19] -> + or([x_ExplicitVarSizeWithDummy[q21] != 5 /\ x_ExplicitVarSizeWithDummy[q21] = q19 | q21 : int(1..4)]) + | q19 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set06/expected/model_3_1_3_4-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_3_1_3_4-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_3_1_3_4-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_3_1_3_4-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_3_1_3_4-solution000002.solution new file mode 100644 index 0000000000..85149821f6 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_3_1_3_4-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_3_1_3_4.eprime b/tests/exhaustive/basic/set06/expected/model_3_1_3_4.eprime new file mode 100644 index 0000000000..3befc5cd42 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_3_1_3_4.eprime @@ -0,0 +1,48 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_Occurrence: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +branching on + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithMarker_Marker, + x_ExplicitVarSizeWithMarker_Values, x_Occurrence] +such that + or([q31 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q31] = 1 | q31 : int(1..4)]), + x_Occurrence[2], + or([q24 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q24] = 3 | q24 : int(1..4)]), + and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] + | q1 : int(1..3)]), + and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..4)]), + x_ExplicitVarSizeWithMarker_Marker <= 4, + sum([toInt(x_Occurrence[q4]) | q4 : int(1..4)]) <= 4, + and([x_Occurrence[q25] -> + or([q27 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q27] = q25 + | q27 : int(1..4)]) + | q25 : int(1..4)]), + and([q29 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q29]] + | q29 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q5 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q5] < x_ExplicitVarSizeWithFlags_Values[q5 + 1] + | q5 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q6] = false -> x_ExplicitVarSizeWithFlags_Values[q6] = 1 | q6 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q7] | q7 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q8]) | q8 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithFlags_Flags[q11] -> + or([q13 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q13] = x_ExplicitVarSizeWithFlags_Values[q11] + | q13 : int(1..4)]) + | q11 : int(1..4)]), + and([q15 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithFlags_Flags[q17] /\ + x_ExplicitVarSizeWithFlags_Values[q17] = x_ExplicitVarSizeWithMarker_Values[q15] + | q17 : int(1..4)]) + | q15 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q19] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q19]] + | q19 : int(1..4)]), + and([x_Occurrence[q20] -> + or([x_ExplicitVarSizeWithFlags_Flags[q22] /\ x_ExplicitVarSizeWithFlags_Values[q22] = q20 | q22 : int(1..4)]) + | q20 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set06/expected/model_3_1_4_1-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_3_1_4_1-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_3_1_4_1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_3_1_4_1-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_3_1_4_1-solution000002.solution new file mode 100644 index 0000000000..85149821f6 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_3_1_4_1-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_3_1_4_1.eprime b/tests/exhaustive/basic/set06/expected/model_3_1_4_1.eprime new file mode 100644 index 0000000000..8671f81ae6 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_3_1_4_1.eprime @@ -0,0 +1,48 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_Occurrence: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +branching on + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithMarker_Marker, + x_ExplicitVarSizeWithMarker_Values, x_Occurrence] +such that + or([q31 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q31] = 1 | q31 : int(1..4)]), + x_Occurrence[2], + or([x_ExplicitVarSizeWithFlags_Flags[q24] /\ x_ExplicitVarSizeWithFlags_Values[q24] = 3 | q24 : int(1..4)]), + and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] + | q1 : int(1..3)]), + and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..4)]), + x_ExplicitVarSizeWithMarker_Marker <= 4, + sum([toInt(x_Occurrence[q4]) | q4 : int(1..4)]) <= 4, + and([x_Occurrence[q25] -> + or([q27 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q27] = q25 + | q27 : int(1..4)]) + | q25 : int(1..4)]), + and([q29 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q29]] + | q29 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q5 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q5] < x_ExplicitVarSizeWithFlags_Values[q5 + 1] + | q5 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q6] = false -> x_ExplicitVarSizeWithFlags_Values[q6] = 1 | q6 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q7] | q7 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q8]) | q8 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithFlags_Flags[q11] -> + or([q13 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q13] = x_ExplicitVarSizeWithFlags_Values[q11] + | q13 : int(1..4)]) + | q11 : int(1..4)]), + and([q15 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithFlags_Flags[q17] /\ + x_ExplicitVarSizeWithFlags_Values[q17] = x_ExplicitVarSizeWithMarker_Values[q15] + | q17 : int(1..4)]) + | q15 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q19] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q19]] + | q19 : int(1..4)]), + and([x_Occurrence[q20] -> + or([x_ExplicitVarSizeWithFlags_Flags[q22] /\ x_ExplicitVarSizeWithFlags_Values[q22] = q20 | q22 : int(1..4)]) + | q20 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set06/expected/model_3_1_4_2-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_3_1_4_2-solution000001.solution new file mode 100644 index 0000000000..85149821f6 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_3_1_4_2-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_3_1_4_2-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_3_1_4_2-solution000002.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_3_1_4_2-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_3_1_4_2.eprime b/tests/exhaustive/basic/set06/expected/model_3_1_4_2.eprime new file mode 100644 index 0000000000..66ffd146e3 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_3_1_4_2.eprime @@ -0,0 +1,77 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_Occurrence: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +branching on + [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_Occurrence, + x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] +such that + or([q56 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q56] = 1 | q56 : int(1..4)]), + x_Occurrence[2], + or([x_ExplicitVarSizeWithFlags_Flags[q49] /\ x_ExplicitVarSizeWithFlags_Values[q49] = 3 | q49 : int(1..4)]), + and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] + | q1 : int(1..3)]), + and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..4)]), + x_ExplicitVarSizeWithMarker_Marker <= 4, + sum([toInt(x_Occurrence[q4]) | q4 : int(1..4)]) <= 4, + and([x_Occurrence[q50] -> + or([q52 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q52] = q50 + | q52 : int(1..4)]) + | q50 : int(1..4)]), + and([q54 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q54]] + | q54 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q5 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q5] < x_ExplicitVarSizeWithFlags_Values[q5 + 1] + | q5 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q6] = false -> x_ExplicitVarSizeWithFlags_Values[q6] = 1 | q6 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q7] | q7 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q8]) | q8 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithFlags_Flags[q11] -> + or([q13 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q13] = x_ExplicitVarSizeWithFlags_Values[q11] + | q13 : int(1..4)]) + | q11 : int(1..4)]), + and([q15 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithFlags_Flags[q17] /\ + x_ExplicitVarSizeWithFlags_Values[q17] = x_ExplicitVarSizeWithMarker_Values[q15] + | q17 : int(1..4)]) + | q15 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q19] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q19]] + | q19 : int(1..4)]), + and([x_Occurrence[q20] -> + or([x_ExplicitVarSizeWithFlags_Flags[q22] /\ x_ExplicitVarSizeWithFlags_Values[q22] = q20 | q22 : int(1..4)]) + | q20 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q23] < x_ExplicitVarSizeWithDummy[q23 + 1] \/ x_ExplicitVarSizeWithDummy[q23] = 5 + | q23 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q24] = 5 -> x_ExplicitVarSizeWithDummy[q24 + 1] = 5 | q24 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithDummy[q25] != 5) | q25 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithDummy[q28] != 5 -> + or([q30 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q30] = x_ExplicitVarSizeWithDummy[q28] + | q30 : int(1..4)]) + | q28 : int(1..4)]), + and([q32 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithDummy[q34] != 5 /\ + x_ExplicitVarSizeWithDummy[q34] = x_ExplicitVarSizeWithMarker_Values[q32] + | q34 : int(1..4)]) + | q32 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q36] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q36]] | q36 : int(1..4)]), + and([x_Occurrence[q37] -> + or([x_ExplicitVarSizeWithDummy[q39] != 5 /\ x_ExplicitVarSizeWithDummy[q39] = q37 | q39 : int(1..4)]) + | q37 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q41] != 5 -> + or([x_ExplicitVarSizeWithFlags_Flags[q43] /\ + x_ExplicitVarSizeWithFlags_Values[q43] = x_ExplicitVarSizeWithDummy[q41] + | q43 : int(1..4)]) + | q41 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q45] -> + or([x_ExplicitVarSizeWithDummy[q47] != 5 /\ + x_ExplicitVarSizeWithDummy[q47] = x_ExplicitVarSizeWithFlags_Values[q45] + | q47 : int(1..4)]) + | q45 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set06/expected/model_3_2_1_1-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_3_2_1_1-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_3_2_1_1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_3_2_1_1-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_3_2_1_1-solution000002.solution new file mode 100644 index 0000000000..85149821f6 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_3_2_1_1-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_3_2_1_1.eprime b/tests/exhaustive/basic/set06/expected/model_3_2_1_1.eprime new file mode 100644 index 0000000000..9ce4f6b713 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_3_2_1_1.eprime @@ -0,0 +1,43 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +find x_Occurrence: matrix indexed by [int(1..4)] of bool +branching on + [x_Occurrence, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy] +such that + or([q28 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q28] = 1 | q28 : int(1..4)]), + or([x_ExplicitVarSizeWithDummy[q30] != 5 /\ x_ExplicitVarSizeWithDummy[q30] = 2 | q30 : int(1..4)]), + x_Occurrence[3], + and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] + | q1 : int(1..3)]), + and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..4)]), + x_ExplicitVarSizeWithMarker_Marker <= 4, + and([x_ExplicitVarSizeWithDummy[q4] < x_ExplicitVarSizeWithDummy[q4 + 1] \/ x_ExplicitVarSizeWithDummy[q4] = 5 + | q4 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q5] = 5 -> x_ExplicitVarSizeWithDummy[q5 + 1] = 5 | q5 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithDummy[q6] != 5) | q6 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithDummy[q9] != 5 -> + or([q11 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q11] = x_ExplicitVarSizeWithDummy[q9] + | q11 : int(1..4)]) + | q9 : int(1..4)]), + and([q13 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithDummy[q15] != 5 /\ + x_ExplicitVarSizeWithDummy[q15] = x_ExplicitVarSizeWithMarker_Values[q13] + | q15 : int(1..4)]) + | q13 : int(1..4)]), + sum([toInt(x_Occurrence[q16]) | q16 : int(1..4)]) <= 4, + and([x_Occurrence[q17] -> + or([q19 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q19] = q17 + | q19 : int(1..4)]) + | q17 : int(1..4)]), + and([q21 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q21]] + | q21 : int(1..4)]), + and([x_Occurrence[q22] -> + or([x_ExplicitVarSizeWithDummy[q24] != 5 /\ x_ExplicitVarSizeWithDummy[q24] = q22 | q24 : int(1..4)]) + | q22 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q26] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q26]] | q26 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set06/expected/model_3_2_1_4-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_3_2_1_4-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_3_2_1_4-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_3_2_1_4-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_3_2_1_4-solution000002.solution new file mode 100644 index 0000000000..85149821f6 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_3_2_1_4-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_3_2_1_4.eprime b/tests/exhaustive/basic/set06/expected/model_3_2_1_4.eprime new file mode 100644 index 0000000000..89bd1983d1 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_3_2_1_4.eprime @@ -0,0 +1,78 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +find x_Occurrence: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +branching on + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithMarker_Marker, + x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy, x_Occurrence] +such that + or([q54 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q54] = 1 | q54 : int(1..4)]), + or([x_ExplicitVarSizeWithDummy[q56] != 5 /\ x_ExplicitVarSizeWithDummy[q56] = 2 | q56 : int(1..4)]), + x_Occurrence[3], + and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] + | q1 : int(1..3)]), + and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..4)]), + x_ExplicitVarSizeWithMarker_Marker <= 4, + and([x_ExplicitVarSizeWithDummy[q4] < x_ExplicitVarSizeWithDummy[q4 + 1] \/ x_ExplicitVarSizeWithDummy[q4] = 5 + | q4 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q5] = 5 -> x_ExplicitVarSizeWithDummy[q5 + 1] = 5 | q5 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithDummy[q6] != 5) | q6 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithDummy[q9] != 5 -> + or([q11 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q11] = x_ExplicitVarSizeWithDummy[q9] + | q11 : int(1..4)]) + | q9 : int(1..4)]), + and([q13 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithDummy[q15] != 5 /\ + x_ExplicitVarSizeWithDummy[q15] = x_ExplicitVarSizeWithMarker_Values[q13] + | q15 : int(1..4)]) + | q13 : int(1..4)]), + sum([toInt(x_Occurrence[q16]) | q16 : int(1..4)]) <= 4, + and([x_Occurrence[q43] -> + or([q45 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q45] = q43 + | q45 : int(1..4)]) + | q43 : int(1..4)]), + and([q47 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q47]] + | q47 : int(1..4)]), + and([x_Occurrence[q48] -> + or([x_ExplicitVarSizeWithDummy[q50] != 5 /\ x_ExplicitVarSizeWithDummy[q50] = q48 | q50 : int(1..4)]) + | q48 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q52] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q52]] | q52 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q17 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q17] < x_ExplicitVarSizeWithFlags_Values[q17 + 1] + | q17 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q18] = false -> x_ExplicitVarSizeWithFlags_Values[q18] = 1 + | q18 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q19 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q19] | q19 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q20]) | q20 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithFlags_Flags[q23] -> + or([q25 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q25] = x_ExplicitVarSizeWithFlags_Values[q23] + | q25 : int(1..4)]) + | q23 : int(1..4)]), + and([q27 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithFlags_Flags[q29] /\ + x_ExplicitVarSizeWithFlags_Values[q29] = x_ExplicitVarSizeWithMarker_Values[q27] + | q29 : int(1..4)]) + | q27 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q31] -> + or([x_ExplicitVarSizeWithDummy[q33] != 5 /\ + x_ExplicitVarSizeWithDummy[q33] = x_ExplicitVarSizeWithFlags_Values[q31] + | q33 : int(1..4)]) + | q31 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q35] != 5 -> + or([x_ExplicitVarSizeWithFlags_Flags[q37] /\ + x_ExplicitVarSizeWithFlags_Values[q37] = x_ExplicitVarSizeWithDummy[q35] + | q37 : int(1..4)]) + | q35 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q39] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q39]] + | q39 : int(1..4)]), + and([x_Occurrence[q40] -> + or([x_ExplicitVarSizeWithFlags_Flags[q42] /\ x_ExplicitVarSizeWithFlags_Values[q42] = q40 | q42 : int(1..4)]) + | q40 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set06/expected/model_3_2_2_1-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_3_2_2_1-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_3_2_2_1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_3_2_2_1-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_3_2_2_1-solution000002.solution new file mode 100644 index 0000000000..85149821f6 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_3_2_2_1-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_3_2_2_1.eprime b/tests/exhaustive/basic/set06/expected/model_3_2_2_1.eprime new file mode 100644 index 0000000000..0bc238b946 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_3_2_2_1.eprime @@ -0,0 +1,43 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +find x_Occurrence: matrix indexed by [int(1..4)] of bool +branching on + [x_Occurrence, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy] +such that + or([q28 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q28] = 1 | q28 : int(1..4)]), + or([x_ExplicitVarSizeWithDummy[q30] != 5 /\ x_ExplicitVarSizeWithDummy[q30] = 2 | q30 : int(1..4)]), + or([x_ExplicitVarSizeWithDummy[q32] != 5 /\ x_ExplicitVarSizeWithDummy[q32] = 3 | q32 : int(1..4)]), + and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] + | q1 : int(1..3)]), + and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..4)]), + x_ExplicitVarSizeWithMarker_Marker <= 4, + and([x_ExplicitVarSizeWithDummy[q4] < x_ExplicitVarSizeWithDummy[q4 + 1] \/ x_ExplicitVarSizeWithDummy[q4] = 5 + | q4 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q5] = 5 -> x_ExplicitVarSizeWithDummy[q5 + 1] = 5 | q5 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithDummy[q6] != 5) | q6 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithDummy[q9] != 5 -> + or([q11 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q11] = x_ExplicitVarSizeWithDummy[q9] + | q11 : int(1..4)]) + | q9 : int(1..4)]), + and([q13 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithDummy[q15] != 5 /\ + x_ExplicitVarSizeWithDummy[q15] = x_ExplicitVarSizeWithMarker_Values[q13] + | q15 : int(1..4)]) + | q13 : int(1..4)]), + sum([toInt(x_Occurrence[q16]) | q16 : int(1..4)]) <= 4, + and([x_Occurrence[q17] -> + or([q19 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q19] = q17 + | q19 : int(1..4)]) + | q17 : int(1..4)]), + and([q21 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q21]] + | q21 : int(1..4)]), + and([x_Occurrence[q22] -> + or([x_ExplicitVarSizeWithDummy[q24] != 5 /\ x_ExplicitVarSizeWithDummy[q24] = q22 | q24 : int(1..4)]) + | q22 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q26] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q26]] | q26 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set06/expected/model_3_2_2_2-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_3_2_2_2-solution000001.solution new file mode 100644 index 0000000000..85149821f6 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_3_2_2_2-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_3_2_2_2-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_3_2_2_2-solution000002.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_3_2_2_2-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_3_2_2_2.eprime b/tests/exhaustive/basic/set06/expected/model_3_2_2_2.eprime new file mode 100644 index 0000000000..dbfe72b7f6 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_3_2_2_2.eprime @@ -0,0 +1,30 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +branching on [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] +such that + or([q17 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q17] = 1 | q17 : int(1..4)]), + or([x_ExplicitVarSizeWithDummy[q19] != 5 /\ x_ExplicitVarSizeWithDummy[q19] = 2 | q19 : int(1..4)]), + or([x_ExplicitVarSizeWithDummy[q21] != 5 /\ x_ExplicitVarSizeWithDummy[q21] = 3 | q21 : int(1..4)]), + and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] + | q1 : int(1..3)]), + and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..4)]), + x_ExplicitVarSizeWithMarker_Marker <= 4, + and([x_ExplicitVarSizeWithDummy[q4] < x_ExplicitVarSizeWithDummy[q4 + 1] \/ x_ExplicitVarSizeWithDummy[q4] = 5 + | q4 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q5] = 5 -> x_ExplicitVarSizeWithDummy[q5 + 1] = 5 | q5 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithDummy[q6] != 5) | q6 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithDummy[q9] != 5 -> + or([q11 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q11] = x_ExplicitVarSizeWithDummy[q9] + | q11 : int(1..4)]) + | q9 : int(1..4)]), + and([q13 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithDummy[q15] != 5 /\ + x_ExplicitVarSizeWithDummy[q15] = x_ExplicitVarSizeWithMarker_Values[q13] + | q15 : int(1..4)]) + | q13 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set06/expected/model_3_2_2_4-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_3_2_2_4-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_3_2_2_4-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_3_2_2_4-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_3_2_2_4-solution000002.solution new file mode 100644 index 0000000000..85149821f6 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_3_2_2_4-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_3_2_2_4.eprime b/tests/exhaustive/basic/set06/expected/model_3_2_2_4.eprime new file mode 100644 index 0000000000..7a1a6ff738 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_3_2_2_4.eprime @@ -0,0 +1,61 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +branching on + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithMarker_Marker, + x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy] +such that + or([q38 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q38] = 1 | q38 : int(1..4)]), + or([x_ExplicitVarSizeWithDummy[q40] != 5 /\ x_ExplicitVarSizeWithDummy[q40] = 2 | q40 : int(1..4)]), + or([x_ExplicitVarSizeWithDummy[q42] != 5 /\ x_ExplicitVarSizeWithDummy[q42] = 3 | q42 : int(1..4)]), + and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] + | q1 : int(1..3)]), + and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..4)]), + x_ExplicitVarSizeWithMarker_Marker <= 4, + and([x_ExplicitVarSizeWithDummy[q4] < x_ExplicitVarSizeWithDummy[q4 + 1] \/ x_ExplicitVarSizeWithDummy[q4] = 5 + | q4 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q5] = 5 -> x_ExplicitVarSizeWithDummy[q5 + 1] = 5 | q5 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithDummy[q6] != 5) | q6 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithDummy[q9] != 5 -> + or([q11 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q11] = x_ExplicitVarSizeWithDummy[q9] + | q11 : int(1..4)]) + | q9 : int(1..4)]), + and([q13 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithDummy[q15] != 5 /\ + x_ExplicitVarSizeWithDummy[q15] = x_ExplicitVarSizeWithMarker_Values[q13] + | q15 : int(1..4)]) + | q13 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q16 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q16] < x_ExplicitVarSizeWithFlags_Values[q16 + 1] + | q16 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q17] = false -> x_ExplicitVarSizeWithFlags_Values[q17] = 1 + | q17 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q18 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q18] | q18 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q19]) | q19 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithFlags_Flags[q22] -> + or([q24 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q24] = x_ExplicitVarSizeWithFlags_Values[q22] + | q24 : int(1..4)]) + | q22 : int(1..4)]), + and([q26 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithFlags_Flags[q28] /\ + x_ExplicitVarSizeWithFlags_Values[q28] = x_ExplicitVarSizeWithMarker_Values[q26] + | q28 : int(1..4)]) + | q26 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q30] -> + or([x_ExplicitVarSizeWithDummy[q32] != 5 /\ + x_ExplicitVarSizeWithDummy[q32] = x_ExplicitVarSizeWithFlags_Values[q30] + | q32 : int(1..4)]) + | q30 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q34] != 5 -> + or([x_ExplicitVarSizeWithFlags_Flags[q36] /\ + x_ExplicitVarSizeWithFlags_Values[q36] = x_ExplicitVarSizeWithDummy[q34] + | q36 : int(1..4)]) + | q34 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set06/expected/model_3_2_3_1-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_3_2_3_1-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_3_2_3_1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_3_2_3_1-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_3_2_3_1-solution000002.solution new file mode 100644 index 0000000000..85149821f6 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_3_2_3_1-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_3_2_3_1.eprime b/tests/exhaustive/basic/set06/expected/model_3_2_3_1.eprime new file mode 100644 index 0000000000..ff7bb579b2 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_3_2_3_1.eprime @@ -0,0 +1,43 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +find x_Occurrence: matrix indexed by [int(1..4)] of bool +branching on + [x_Occurrence, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy] +such that + or([q28 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q28] = 1 | q28 : int(1..4)]), + or([x_ExplicitVarSizeWithDummy[q30] != 5 /\ x_ExplicitVarSizeWithDummy[q30] = 2 | q30 : int(1..4)]), + or([q32 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q32] = 3 | q32 : int(1..4)]), + and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] + | q1 : int(1..3)]), + and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..4)]), + x_ExplicitVarSizeWithMarker_Marker <= 4, + and([x_ExplicitVarSizeWithDummy[q4] < x_ExplicitVarSizeWithDummy[q4 + 1] \/ x_ExplicitVarSizeWithDummy[q4] = 5 + | q4 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q5] = 5 -> x_ExplicitVarSizeWithDummy[q5 + 1] = 5 | q5 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithDummy[q6] != 5) | q6 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithDummy[q9] != 5 -> + or([q11 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q11] = x_ExplicitVarSizeWithDummy[q9] + | q11 : int(1..4)]) + | q9 : int(1..4)]), + and([q13 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithDummy[q15] != 5 /\ + x_ExplicitVarSizeWithDummy[q15] = x_ExplicitVarSizeWithMarker_Values[q13] + | q15 : int(1..4)]) + | q13 : int(1..4)]), + sum([toInt(x_Occurrence[q16]) | q16 : int(1..4)]) <= 4, + and([x_Occurrence[q17] -> + or([q19 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q19] = q17 + | q19 : int(1..4)]) + | q17 : int(1..4)]), + and([q21 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q21]] + | q21 : int(1..4)]), + and([x_Occurrence[q22] -> + or([x_ExplicitVarSizeWithDummy[q24] != 5 /\ x_ExplicitVarSizeWithDummy[q24] = q22 | q24 : int(1..4)]) + | q22 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q26] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q26]] | q26 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set06/expected/model_3_2_3_2-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_3_2_3_2-solution000001.solution new file mode 100644 index 0000000000..85149821f6 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_3_2_3_2-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_3_2_3_2-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_3_2_3_2-solution000002.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_3_2_3_2-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_3_2_3_2.eprime b/tests/exhaustive/basic/set06/expected/model_3_2_3_2.eprime new file mode 100644 index 0000000000..e1d4abb5fe --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_3_2_3_2.eprime @@ -0,0 +1,30 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +branching on [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] +such that + or([q17 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q17] = 1 | q17 : int(1..4)]), + or([x_ExplicitVarSizeWithDummy[q19] != 5 /\ x_ExplicitVarSizeWithDummy[q19] = 2 | q19 : int(1..4)]), + or([q21 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q21] = 3 | q21 : int(1..4)]), + and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] + | q1 : int(1..3)]), + and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..4)]), + x_ExplicitVarSizeWithMarker_Marker <= 4, + and([x_ExplicitVarSizeWithDummy[q4] < x_ExplicitVarSizeWithDummy[q4 + 1] \/ x_ExplicitVarSizeWithDummy[q4] = 5 + | q4 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q5] = 5 -> x_ExplicitVarSizeWithDummy[q5 + 1] = 5 | q5 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithDummy[q6] != 5) | q6 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithDummy[q9] != 5 -> + or([q11 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q11] = x_ExplicitVarSizeWithDummy[q9] + | q11 : int(1..4)]) + | q9 : int(1..4)]), + and([q13 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithDummy[q15] != 5 /\ + x_ExplicitVarSizeWithDummy[q15] = x_ExplicitVarSizeWithMarker_Values[q13] + | q15 : int(1..4)]) + | q13 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set06/expected/model_3_2_3_4-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_3_2_3_4-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_3_2_3_4-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_3_2_3_4-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_3_2_3_4-solution000002.solution new file mode 100644 index 0000000000..85149821f6 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_3_2_3_4-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_3_2_3_4.eprime b/tests/exhaustive/basic/set06/expected/model_3_2_3_4.eprime new file mode 100644 index 0000000000..b28bec21c6 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_3_2_3_4.eprime @@ -0,0 +1,61 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +branching on + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithMarker_Marker, + x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy] +such that + or([q38 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q38] = 1 | q38 : int(1..4)]), + or([x_ExplicitVarSizeWithDummy[q40] != 5 /\ x_ExplicitVarSizeWithDummy[q40] = 2 | q40 : int(1..4)]), + or([q42 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q42] = 3 | q42 : int(1..4)]), + and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] + | q1 : int(1..3)]), + and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..4)]), + x_ExplicitVarSizeWithMarker_Marker <= 4, + and([x_ExplicitVarSizeWithDummy[q4] < x_ExplicitVarSizeWithDummy[q4 + 1] \/ x_ExplicitVarSizeWithDummy[q4] = 5 + | q4 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q5] = 5 -> x_ExplicitVarSizeWithDummy[q5 + 1] = 5 | q5 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithDummy[q6] != 5) | q6 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithDummy[q9] != 5 -> + or([q11 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q11] = x_ExplicitVarSizeWithDummy[q9] + | q11 : int(1..4)]) + | q9 : int(1..4)]), + and([q13 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithDummy[q15] != 5 /\ + x_ExplicitVarSizeWithDummy[q15] = x_ExplicitVarSizeWithMarker_Values[q13] + | q15 : int(1..4)]) + | q13 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q16 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q16] < x_ExplicitVarSizeWithFlags_Values[q16 + 1] + | q16 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q17] = false -> x_ExplicitVarSizeWithFlags_Values[q17] = 1 + | q17 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q18 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q18] | q18 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q19]) | q19 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithFlags_Flags[q22] -> + or([q24 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q24] = x_ExplicitVarSizeWithFlags_Values[q22] + | q24 : int(1..4)]) + | q22 : int(1..4)]), + and([q26 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithFlags_Flags[q28] /\ + x_ExplicitVarSizeWithFlags_Values[q28] = x_ExplicitVarSizeWithMarker_Values[q26] + | q28 : int(1..4)]) + | q26 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q30] -> + or([x_ExplicitVarSizeWithDummy[q32] != 5 /\ + x_ExplicitVarSizeWithDummy[q32] = x_ExplicitVarSizeWithFlags_Values[q30] + | q32 : int(1..4)]) + | q30 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q34] != 5 -> + or([x_ExplicitVarSizeWithFlags_Flags[q36] /\ + x_ExplicitVarSizeWithFlags_Values[q36] = x_ExplicitVarSizeWithDummy[q34] + | q36 : int(1..4)]) + | q34 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set06/expected/model_3_2_4_1-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_3_2_4_1-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_3_2_4_1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_3_2_4_1-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_3_2_4_1-solution000002.solution new file mode 100644 index 0000000000..85149821f6 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_3_2_4_1-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_3_2_4_1.eprime b/tests/exhaustive/basic/set06/expected/model_3_2_4_1.eprime new file mode 100644 index 0000000000..5966d0ab74 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_3_2_4_1.eprime @@ -0,0 +1,78 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_Occurrence: matrix indexed by [int(1..4)] of bool +branching on + [x_Occurrence, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy, + x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] +such that + or([q54 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q54] = 1 | q54 : int(1..4)]), + or([x_ExplicitVarSizeWithDummy[q56] != 5 /\ x_ExplicitVarSizeWithDummy[q56] = 2 | q56 : int(1..4)]), + or([x_ExplicitVarSizeWithFlags_Flags[q58] /\ x_ExplicitVarSizeWithFlags_Values[q58] = 3 | q58 : int(1..4)]), + and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] + | q1 : int(1..3)]), + and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..4)]), + x_ExplicitVarSizeWithMarker_Marker <= 4, + and([x_ExplicitVarSizeWithDummy[q4] < x_ExplicitVarSizeWithDummy[q4 + 1] \/ x_ExplicitVarSizeWithDummy[q4] = 5 + | q4 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q5] = 5 -> x_ExplicitVarSizeWithDummy[q5 + 1] = 5 | q5 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithDummy[q6] != 5) | q6 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithDummy[q9] != 5 -> + or([q11 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q11] = x_ExplicitVarSizeWithDummy[q9] + | q11 : int(1..4)]) + | q9 : int(1..4)]), + and([q13 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithDummy[q15] != 5 /\ + x_ExplicitVarSizeWithDummy[q15] = x_ExplicitVarSizeWithMarker_Values[q13] + | q15 : int(1..4)]) + | q13 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q16 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q16] < x_ExplicitVarSizeWithFlags_Values[q16 + 1] + | q16 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q17] = false -> x_ExplicitVarSizeWithFlags_Values[q17] = 1 + | q17 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q18 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q18] | q18 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q19]) | q19 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithFlags_Flags[q22] -> + or([q24 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q24] = x_ExplicitVarSizeWithFlags_Values[q22] + | q24 : int(1..4)]) + | q22 : int(1..4)]), + and([q26 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithFlags_Flags[q28] /\ + x_ExplicitVarSizeWithFlags_Values[q28] = x_ExplicitVarSizeWithMarker_Values[q26] + | q28 : int(1..4)]) + | q26 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q30] -> + or([x_ExplicitVarSizeWithDummy[q32] != 5 /\ + x_ExplicitVarSizeWithDummy[q32] = x_ExplicitVarSizeWithFlags_Values[q30] + | q32 : int(1..4)]) + | q30 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q34] != 5 -> + or([x_ExplicitVarSizeWithFlags_Flags[q36] /\ + x_ExplicitVarSizeWithFlags_Values[q36] = x_ExplicitVarSizeWithDummy[q34] + | q36 : int(1..4)]) + | q34 : int(1..4)]), + sum([toInt(x_Occurrence[q37]) | q37 : int(1..4)]) <= 4, + and([x_Occurrence[q38] -> + or([q40 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q40] = q38 + | q40 : int(1..4)]) + | q38 : int(1..4)]), + and([q42 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q42]] + | q42 : int(1..4)]), + and([x_Occurrence[q43] -> + or([x_ExplicitVarSizeWithDummy[q45] != 5 /\ x_ExplicitVarSizeWithDummy[q45] = q43 | q45 : int(1..4)]) + | q43 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q47] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q47]] | q47 : int(1..4)]), + and([x_Occurrence[q48] -> + or([x_ExplicitVarSizeWithFlags_Flags[q50] /\ x_ExplicitVarSizeWithFlags_Values[q50] = q48 | q50 : int(1..4)]) + | q48 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q52] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q52]] + | q52 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set06/expected/model_3_2_4_2-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_3_2_4_2-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_3_2_4_2-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_3_2_4_2-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_3_2_4_2-solution000002.solution new file mode 100644 index 0000000000..85149821f6 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_3_2_4_2-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_3_2_4_2.eprime b/tests/exhaustive/basic/set06/expected/model_3_2_4_2.eprime new file mode 100644 index 0000000000..d35a7e7b68 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_3_2_4_2.eprime @@ -0,0 +1,61 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +branching on + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithMarker_Marker, + x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy] +such that + or([q38 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q38] = 1 | q38 : int(1..4)]), + or([x_ExplicitVarSizeWithDummy[q40] != 5 /\ x_ExplicitVarSizeWithDummy[q40] = 2 | q40 : int(1..4)]), + or([x_ExplicitVarSizeWithFlags_Flags[q42] /\ x_ExplicitVarSizeWithFlags_Values[q42] = 3 | q42 : int(1..4)]), + and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] + | q1 : int(1..3)]), + and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..4)]), + x_ExplicitVarSizeWithMarker_Marker <= 4, + and([x_ExplicitVarSizeWithDummy[q4] < x_ExplicitVarSizeWithDummy[q4 + 1] \/ x_ExplicitVarSizeWithDummy[q4] = 5 + | q4 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q5] = 5 -> x_ExplicitVarSizeWithDummy[q5 + 1] = 5 | q5 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithDummy[q6] != 5) | q6 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithDummy[q9] != 5 -> + or([q11 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q11] = x_ExplicitVarSizeWithDummy[q9] + | q11 : int(1..4)]) + | q9 : int(1..4)]), + and([q13 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithDummy[q15] != 5 /\ + x_ExplicitVarSizeWithDummy[q15] = x_ExplicitVarSizeWithMarker_Values[q13] + | q15 : int(1..4)]) + | q13 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q16 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q16] < x_ExplicitVarSizeWithFlags_Values[q16 + 1] + | q16 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q17] = false -> x_ExplicitVarSizeWithFlags_Values[q17] = 1 + | q17 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q18 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q18] | q18 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q19]) | q19 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithFlags_Flags[q22] -> + or([q24 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q24] = x_ExplicitVarSizeWithFlags_Values[q22] + | q24 : int(1..4)]) + | q22 : int(1..4)]), + and([q26 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithFlags_Flags[q28] /\ + x_ExplicitVarSizeWithFlags_Values[q28] = x_ExplicitVarSizeWithMarker_Values[q26] + | q28 : int(1..4)]) + | q26 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q30] -> + or([x_ExplicitVarSizeWithDummy[q32] != 5 /\ + x_ExplicitVarSizeWithDummy[q32] = x_ExplicitVarSizeWithFlags_Values[q30] + | q32 : int(1..4)]) + | q30 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q34] != 5 -> + or([x_ExplicitVarSizeWithFlags_Flags[q36] /\ + x_ExplicitVarSizeWithFlags_Values[q36] = x_ExplicitVarSizeWithDummy[q34] + | q36 : int(1..4)]) + | q34 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set06/expected/model_3_3_1_1-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_3_3_1_1-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_3_3_1_1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_3_3_1_1-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_3_3_1_1-solution000002.solution new file mode 100644 index 0000000000..85149821f6 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_3_3_1_1-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_3_3_1_1.eprime b/tests/exhaustive/basic/set06/expected/model_3_3_1_1.eprime new file mode 100644 index 0000000000..80713ad04e --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_3_3_1_1.eprime @@ -0,0 +1,22 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_Occurrence: matrix indexed by [int(1..4)] of bool +branching on [x_Occurrence, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] +such that + or([q11 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q11] = 1 | q11 : int(1..4)]), + or([q13 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q13] = 2 | q13 : int(1..4)]), + x_Occurrence[3], + and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] + | q1 : int(1..3)]), + and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..4)]), + x_ExplicitVarSizeWithMarker_Marker <= 4, + sum([toInt(x_Occurrence[q4]) | q4 : int(1..4)]) <= 4, + and([x_Occurrence[q5] -> + or([q7 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q7] = q5 | q7 : int(1..4)]) + | q5 : int(1..4)]), + and([q9 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q9]] + | q9 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set06/expected/model_3_3_1_2-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_3_3_1_2-solution000001.solution new file mode 100644 index 0000000000..85149821f6 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_3_3_1_2-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_3_3_1_2-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_3_3_1_2-solution000002.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_3_3_1_2-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_3_3_1_2.eprime b/tests/exhaustive/basic/set06/expected/model_3_3_1_2.eprime new file mode 100644 index 0000000000..53cfc835b6 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_3_3_1_2.eprime @@ -0,0 +1,43 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_Occurrence: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +branching on + [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_Occurrence] +such that + or([q28 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q28] = 1 | q28 : int(1..4)]), + or([q30 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q30] = 2 | q30 : int(1..4)]), + x_Occurrence[3], + and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] + | q1 : int(1..3)]), + and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..4)]), + x_ExplicitVarSizeWithMarker_Marker <= 4, + sum([toInt(x_Occurrence[q4]) | q4 : int(1..4)]) <= 4, + and([x_Occurrence[q22] -> + or([q24 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q24] = q22 + | q24 : int(1..4)]) + | q22 : int(1..4)]), + and([q26 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q26]] + | q26 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q5] < x_ExplicitVarSizeWithDummy[q5 + 1] \/ x_ExplicitVarSizeWithDummy[q5] = 5 + | q5 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q6] = 5 -> x_ExplicitVarSizeWithDummy[q6 + 1] = 5 | q6 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithDummy[q7] != 5) | q7 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithDummy[q10] != 5 -> + or([q12 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q12] = x_ExplicitVarSizeWithDummy[q10] + | q12 : int(1..4)]) + | q10 : int(1..4)]), + and([q14 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithDummy[q16] != 5 /\ + x_ExplicitVarSizeWithDummy[q16] = x_ExplicitVarSizeWithMarker_Values[q14] + | q16 : int(1..4)]) + | q14 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q18] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q18]] | q18 : int(1..4)]), + and([x_Occurrence[q19] -> + or([x_ExplicitVarSizeWithDummy[q21] != 5 /\ x_ExplicitVarSizeWithDummy[q21] = q19 | q21 : int(1..4)]) + | q19 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set06/expected/model_3_3_1_4-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_3_3_1_4-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_3_3_1_4-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_3_3_1_4-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_3_3_1_4-solution000002.solution new file mode 100644 index 0000000000..85149821f6 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_3_3_1_4-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_3_3_1_4.eprime b/tests/exhaustive/basic/set06/expected/model_3_3_1_4.eprime new file mode 100644 index 0000000000..0f704594c0 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_3_3_1_4.eprime @@ -0,0 +1,48 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_Occurrence: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +branching on + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithMarker_Marker, + x_ExplicitVarSizeWithMarker_Values, x_Occurrence] +such that + or([q29 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q29] = 1 | q29 : int(1..4)]), + or([q31 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q31] = 2 | q31 : int(1..4)]), + x_Occurrence[3], + and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] + | q1 : int(1..3)]), + and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..4)]), + x_ExplicitVarSizeWithMarker_Marker <= 4, + sum([toInt(x_Occurrence[q4]) | q4 : int(1..4)]) <= 4, + and([x_Occurrence[q23] -> + or([q25 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q25] = q23 + | q25 : int(1..4)]) + | q23 : int(1..4)]), + and([q27 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q27]] + | q27 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q5 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q5] < x_ExplicitVarSizeWithFlags_Values[q5 + 1] + | q5 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q6] = false -> x_ExplicitVarSizeWithFlags_Values[q6] = 1 | q6 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q7] | q7 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q8]) | q8 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithFlags_Flags[q11] -> + or([q13 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q13] = x_ExplicitVarSizeWithFlags_Values[q11] + | q13 : int(1..4)]) + | q11 : int(1..4)]), + and([q15 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithFlags_Flags[q17] /\ + x_ExplicitVarSizeWithFlags_Values[q17] = x_ExplicitVarSizeWithMarker_Values[q15] + | q17 : int(1..4)]) + | q15 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q19] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q19]] + | q19 : int(1..4)]), + and([x_Occurrence[q20] -> + or([x_ExplicitVarSizeWithFlags_Flags[q22] /\ x_ExplicitVarSizeWithFlags_Values[q22] = q20 | q22 : int(1..4)]) + | q20 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set06/expected/model_3_3_2_1-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_3_3_2_1-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_3_3_2_1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_3_3_2_1-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_3_3_2_1-solution000002.solution new file mode 100644 index 0000000000..85149821f6 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_3_3_2_1-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_3_3_2_1.eprime b/tests/exhaustive/basic/set06/expected/model_3_3_2_1.eprime new file mode 100644 index 0000000000..918bc71bcb --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_3_3_2_1.eprime @@ -0,0 +1,43 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +find x_Occurrence: matrix indexed by [int(1..4)] of bool +branching on + [x_Occurrence, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy] +such that + or([q28 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q28] = 1 | q28 : int(1..4)]), + or([q30 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q30] = 2 | q30 : int(1..4)]), + or([x_ExplicitVarSizeWithDummy[q32] != 5 /\ x_ExplicitVarSizeWithDummy[q32] = 3 | q32 : int(1..4)]), + and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] + | q1 : int(1..3)]), + and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..4)]), + x_ExplicitVarSizeWithMarker_Marker <= 4, + and([x_ExplicitVarSizeWithDummy[q4] < x_ExplicitVarSizeWithDummy[q4 + 1] \/ x_ExplicitVarSizeWithDummy[q4] = 5 + | q4 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q5] = 5 -> x_ExplicitVarSizeWithDummy[q5 + 1] = 5 | q5 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithDummy[q6] != 5) | q6 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithDummy[q9] != 5 -> + or([q11 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q11] = x_ExplicitVarSizeWithDummy[q9] + | q11 : int(1..4)]) + | q9 : int(1..4)]), + and([q13 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithDummy[q15] != 5 /\ + x_ExplicitVarSizeWithDummy[q15] = x_ExplicitVarSizeWithMarker_Values[q13] + | q15 : int(1..4)]) + | q13 : int(1..4)]), + sum([toInt(x_Occurrence[q16]) | q16 : int(1..4)]) <= 4, + and([x_Occurrence[q17] -> + or([q19 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q19] = q17 + | q19 : int(1..4)]) + | q17 : int(1..4)]), + and([q21 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q21]] + | q21 : int(1..4)]), + and([x_Occurrence[q22] -> + or([x_ExplicitVarSizeWithDummy[q24] != 5 /\ x_ExplicitVarSizeWithDummy[q24] = q22 | q24 : int(1..4)]) + | q22 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q26] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q26]] | q26 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set06/expected/model_3_3_2_2-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_3_3_2_2-solution000001.solution new file mode 100644 index 0000000000..85149821f6 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_3_3_2_2-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_3_3_2_2-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_3_3_2_2-solution000002.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_3_3_2_2-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_3_3_2_2.eprime b/tests/exhaustive/basic/set06/expected/model_3_3_2_2.eprime new file mode 100644 index 0000000000..ddb40c5b40 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_3_3_2_2.eprime @@ -0,0 +1,30 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +branching on [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] +such that + or([q17 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q17] = 1 | q17 : int(1..4)]), + or([q19 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q19] = 2 | q19 : int(1..4)]), + or([x_ExplicitVarSizeWithDummy[q21] != 5 /\ x_ExplicitVarSizeWithDummy[q21] = 3 | q21 : int(1..4)]), + and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] + | q1 : int(1..3)]), + and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..4)]), + x_ExplicitVarSizeWithMarker_Marker <= 4, + and([x_ExplicitVarSizeWithDummy[q4] < x_ExplicitVarSizeWithDummy[q4 + 1] \/ x_ExplicitVarSizeWithDummy[q4] = 5 + | q4 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q5] = 5 -> x_ExplicitVarSizeWithDummy[q5 + 1] = 5 | q5 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithDummy[q6] != 5) | q6 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithDummy[q9] != 5 -> + or([q11 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q11] = x_ExplicitVarSizeWithDummy[q9] + | q11 : int(1..4)]) + | q9 : int(1..4)]), + and([q13 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithDummy[q15] != 5 /\ + x_ExplicitVarSizeWithDummy[q15] = x_ExplicitVarSizeWithMarker_Values[q13] + | q15 : int(1..4)]) + | q13 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set06/expected/model_3_3_2_4-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_3_3_2_4-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_3_3_2_4-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_3_3_2_4-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_3_3_2_4-solution000002.solution new file mode 100644 index 0000000000..85149821f6 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_3_3_2_4-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_3_3_2_4.eprime b/tests/exhaustive/basic/set06/expected/model_3_3_2_4.eprime new file mode 100644 index 0000000000..f03b23d86a --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_3_3_2_4.eprime @@ -0,0 +1,61 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +branching on + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithMarker_Marker, + x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy] +such that + or([q38 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q38] = 1 | q38 : int(1..4)]), + or([q40 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q40] = 2 | q40 : int(1..4)]), + or([x_ExplicitVarSizeWithDummy[q42] != 5 /\ x_ExplicitVarSizeWithDummy[q42] = 3 | q42 : int(1..4)]), + and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] + | q1 : int(1..3)]), + and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..4)]), + x_ExplicitVarSizeWithMarker_Marker <= 4, + and([x_ExplicitVarSizeWithDummy[q4] < x_ExplicitVarSizeWithDummy[q4 + 1] \/ x_ExplicitVarSizeWithDummy[q4] = 5 + | q4 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q5] = 5 -> x_ExplicitVarSizeWithDummy[q5 + 1] = 5 | q5 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithDummy[q6] != 5) | q6 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithDummy[q9] != 5 -> + or([q11 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q11] = x_ExplicitVarSizeWithDummy[q9] + | q11 : int(1..4)]) + | q9 : int(1..4)]), + and([q13 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithDummy[q15] != 5 /\ + x_ExplicitVarSizeWithDummy[q15] = x_ExplicitVarSizeWithMarker_Values[q13] + | q15 : int(1..4)]) + | q13 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q16 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q16] < x_ExplicitVarSizeWithFlags_Values[q16 + 1] + | q16 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q17] = false -> x_ExplicitVarSizeWithFlags_Values[q17] = 1 + | q17 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q18 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q18] | q18 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q19]) | q19 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithFlags_Flags[q22] -> + or([q24 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q24] = x_ExplicitVarSizeWithFlags_Values[q22] + | q24 : int(1..4)]) + | q22 : int(1..4)]), + and([q26 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithFlags_Flags[q28] /\ + x_ExplicitVarSizeWithFlags_Values[q28] = x_ExplicitVarSizeWithMarker_Values[q26] + | q28 : int(1..4)]) + | q26 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q30] -> + or([x_ExplicitVarSizeWithDummy[q32] != 5 /\ + x_ExplicitVarSizeWithDummy[q32] = x_ExplicitVarSizeWithFlags_Values[q30] + | q32 : int(1..4)]) + | q30 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q34] != 5 -> + or([x_ExplicitVarSizeWithFlags_Flags[q36] /\ + x_ExplicitVarSizeWithFlags_Values[q36] = x_ExplicitVarSizeWithDummy[q34] + | q36 : int(1..4)]) + | q34 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set06/expected/model_3_3_3_1-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_3_3_3_1-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_3_3_3_1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_3_3_3_1-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_3_3_3_1-solution000002.solution new file mode 100644 index 0000000000..85149821f6 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_3_3_3_1-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_3_3_3_1.eprime b/tests/exhaustive/basic/set06/expected/model_3_3_3_1.eprime new file mode 100644 index 0000000000..c15dc11975 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_3_3_3_1.eprime @@ -0,0 +1,22 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_Occurrence: matrix indexed by [int(1..4)] of bool +branching on [x_Occurrence, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] +such that + or([q11 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q11] = 1 | q11 : int(1..4)]), + or([q13 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q13] = 2 | q13 : int(1..4)]), + or([q15 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q15] = 3 | q15 : int(1..4)]), + and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] + | q1 : int(1..3)]), + and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..4)]), + x_ExplicitVarSizeWithMarker_Marker <= 4, + sum([toInt(x_Occurrence[q4]) | q4 : int(1..4)]) <= 4, + and([x_Occurrence[q5] -> + or([q7 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q7] = q5 | q7 : int(1..4)]) + | q5 : int(1..4)]), + and([q9 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q9]] + | q9 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set06/expected/model_3_3_3_2-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_3_3_3_2-solution000001.solution new file mode 100644 index 0000000000..85149821f6 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_3_3_3_2-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_3_3_3_2-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_3_3_3_2-solution000002.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_3_3_3_2-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_3_3_3_2.eprime b/tests/exhaustive/basic/set06/expected/model_3_3_3_2.eprime new file mode 100644 index 0000000000..85731e5fd2 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_3_3_3_2.eprime @@ -0,0 +1,30 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +branching on [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] +such that + or([q17 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q17] = 1 | q17 : int(1..4)]), + or([q19 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q19] = 2 | q19 : int(1..4)]), + or([q21 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q21] = 3 | q21 : int(1..4)]), + and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] + | q1 : int(1..3)]), + and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..4)]), + x_ExplicitVarSizeWithMarker_Marker <= 4, + and([x_ExplicitVarSizeWithDummy[q4] < x_ExplicitVarSizeWithDummy[q4 + 1] \/ x_ExplicitVarSizeWithDummy[q4] = 5 + | q4 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q5] = 5 -> x_ExplicitVarSizeWithDummy[q5 + 1] = 5 | q5 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithDummy[q6] != 5) | q6 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithDummy[q9] != 5 -> + or([q11 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q11] = x_ExplicitVarSizeWithDummy[q9] + | q11 : int(1..4)]) + | q9 : int(1..4)]), + and([q13 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithDummy[q15] != 5 /\ + x_ExplicitVarSizeWithDummy[q15] = x_ExplicitVarSizeWithMarker_Values[q13] + | q15 : int(1..4)]) + | q13 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set06/expected/model_3_3_3_3-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_3_3_3_3-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_3_3_3_3-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_3_3_3_3-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_3_3_3_3-solution000002.solution new file mode 100644 index 0000000000..85149821f6 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_3_3_3_3-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_3_3_3_3.eprime b/tests/exhaustive/basic/set06/expected/model_3_3_3_3.eprime new file mode 100644 index 0000000000..68ea664f7c --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_3_3_3_3.eprime @@ -0,0 +1,15 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +branching on [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] +such that + or([q5 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q5] = 1 | q5 : int(1..4)]), + or([q7 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q7] = 2 | q7 : int(1..4)]), + or([q9 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q9] = 3 | q9 : int(1..4)]), + and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] + | q1 : int(1..3)]), + and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..4)]), + x_ExplicitVarSizeWithMarker_Marker <= 4 + diff --git a/tests/exhaustive/basic/set06/expected/model_3_3_3_4-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_3_3_3_4-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_3_3_3_4-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_3_3_3_4-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_3_3_3_4-solution000002.solution new file mode 100644 index 0000000000..85149821f6 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_3_3_3_4-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_3_3_3_4.eprime b/tests/exhaustive/basic/set06/expected/model_3_3_3_4.eprime new file mode 100644 index 0000000000..5ea57c61e2 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_3_3_3_4.eprime @@ -0,0 +1,35 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +branching on + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithMarker_Marker, + x_ExplicitVarSizeWithMarker_Values] +such that + or([q18 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q18] = 1 | q18 : int(1..4)]), + or([q20 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q20] = 2 | q20 : int(1..4)]), + or([q22 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q22] = 3 | q22 : int(1..4)]), + and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] + | q1 : int(1..3)]), + and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..4)]), + x_ExplicitVarSizeWithMarker_Marker <= 4, + and([x_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q4] < x_ExplicitVarSizeWithFlags_Values[q4 + 1] + | q4 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q5] = false -> x_ExplicitVarSizeWithFlags_Values[q5] = 1 | q5 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q6] | q6 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q7]) | q7 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithFlags_Flags[q10] -> + or([q12 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q12] = x_ExplicitVarSizeWithFlags_Values[q10] + | q12 : int(1..4)]) + | q10 : int(1..4)]), + and([q14 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithFlags_Flags[q16] /\ + x_ExplicitVarSizeWithFlags_Values[q16] = x_ExplicitVarSizeWithMarker_Values[q14] + | q16 : int(1..4)]) + | q14 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set06/expected/model_3_3_4_1-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_3_3_4_1-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_3_3_4_1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_3_3_4_1-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_3_3_4_1-solution000002.solution new file mode 100644 index 0000000000..85149821f6 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_3_3_4_1-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_3_3_4_1.eprime b/tests/exhaustive/basic/set06/expected/model_3_3_4_1.eprime new file mode 100644 index 0000000000..73c28def99 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_3_3_4_1.eprime @@ -0,0 +1,48 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_Occurrence: matrix indexed by [int(1..4)] of bool +branching on + [x_Occurrence, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, + x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] +such that + or([q29 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q29] = 1 | q29 : int(1..4)]), + or([q31 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q31] = 2 | q31 : int(1..4)]), + or([x_ExplicitVarSizeWithFlags_Flags[q33] /\ x_ExplicitVarSizeWithFlags_Values[q33] = 3 | q33 : int(1..4)]), + and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] + | q1 : int(1..3)]), + and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..4)]), + x_ExplicitVarSizeWithMarker_Marker <= 4, + and([x_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q4] < x_ExplicitVarSizeWithFlags_Values[q4 + 1] + | q4 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q5] = false -> x_ExplicitVarSizeWithFlags_Values[q5] = 1 | q5 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q6] | q6 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q7]) | q7 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithFlags_Flags[q10] -> + or([q12 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q12] = x_ExplicitVarSizeWithFlags_Values[q10] + | q12 : int(1..4)]) + | q10 : int(1..4)]), + and([q14 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithFlags_Flags[q16] /\ + x_ExplicitVarSizeWithFlags_Values[q16] = x_ExplicitVarSizeWithMarker_Values[q14] + | q16 : int(1..4)]) + | q14 : int(1..4)]), + sum([toInt(x_Occurrence[q17]) | q17 : int(1..4)]) <= 4, + and([x_Occurrence[q18] -> + or([q20 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q20] = q18 + | q20 : int(1..4)]) + | q18 : int(1..4)]), + and([q22 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q22]] + | q22 : int(1..4)]), + and([x_Occurrence[q23] -> + or([x_ExplicitVarSizeWithFlags_Flags[q25] /\ x_ExplicitVarSizeWithFlags_Values[q25] = q23 | q25 : int(1..4)]) + | q23 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q27] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q27]] + | q27 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set06/expected/model_3_3_4_2-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_3_3_4_2-solution000001.solution new file mode 100644 index 0000000000..85149821f6 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_3_3_4_2-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_3_3_4_2-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_3_3_4_2-solution000002.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_3_3_4_2-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_3_3_4_2.eprime b/tests/exhaustive/basic/set06/expected/model_3_3_4_2.eprime new file mode 100644 index 0000000000..d37fd441e0 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_3_3_4_2.eprime @@ -0,0 +1,60 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +branching on + [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, + x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] +such that + or([q38 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q38] = 1 | q38 : int(1..4)]), + or([q40 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q40] = 2 | q40 : int(1..4)]), + or([x_ExplicitVarSizeWithFlags_Flags[q42] /\ x_ExplicitVarSizeWithFlags_Values[q42] = 3 | q42 : int(1..4)]), + and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] + | q1 : int(1..3)]), + and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..4)]), + x_ExplicitVarSizeWithMarker_Marker <= 4, + and([x_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q4] < x_ExplicitVarSizeWithFlags_Values[q4 + 1] + | q4 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q5] = false -> x_ExplicitVarSizeWithFlags_Values[q5] = 1 | q5 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q6] | q6 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q7]) | q7 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithFlags_Flags[q10] -> + or([q12 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q12] = x_ExplicitVarSizeWithFlags_Values[q10] + | q12 : int(1..4)]) + | q10 : int(1..4)]), + and([q14 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithFlags_Flags[q16] /\ + x_ExplicitVarSizeWithFlags_Values[q16] = x_ExplicitVarSizeWithMarker_Values[q14] + | q16 : int(1..4)]) + | q14 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q17] < x_ExplicitVarSizeWithDummy[q17 + 1] \/ x_ExplicitVarSizeWithDummy[q17] = 5 + | q17 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q18] = 5 -> x_ExplicitVarSizeWithDummy[q18 + 1] = 5 | q18 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithDummy[q19] != 5) | q19 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithDummy[q22] != 5 -> + or([q24 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q24] = x_ExplicitVarSizeWithDummy[q22] + | q24 : int(1..4)]) + | q22 : int(1..4)]), + and([q26 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithDummy[q28] != 5 /\ + x_ExplicitVarSizeWithDummy[q28] = x_ExplicitVarSizeWithMarker_Values[q26] + | q28 : int(1..4)]) + | q26 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q30] != 5 -> + or([x_ExplicitVarSizeWithFlags_Flags[q32] /\ + x_ExplicitVarSizeWithFlags_Values[q32] = x_ExplicitVarSizeWithDummy[q30] + | q32 : int(1..4)]) + | q30 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q34] -> + or([x_ExplicitVarSizeWithDummy[q36] != 5 /\ + x_ExplicitVarSizeWithDummy[q36] = x_ExplicitVarSizeWithFlags_Values[q34] + | q36 : int(1..4)]) + | q34 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set06/expected/model_3_3_4_3-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_3_3_4_3-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_3_3_4_3-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_3_3_4_3-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_3_3_4_3-solution000002.solution new file mode 100644 index 0000000000..85149821f6 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_3_3_4_3-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_3_3_4_3.eprime b/tests/exhaustive/basic/set06/expected/model_3_3_4_3.eprime new file mode 100644 index 0000000000..8356b4d465 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_3_3_4_3.eprime @@ -0,0 +1,35 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +branching on + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithMarker_Marker, + x_ExplicitVarSizeWithMarker_Values] +such that + or([q18 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q18] = 1 | q18 : int(1..4)]), + or([q20 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q20] = 2 | q20 : int(1..4)]), + or([x_ExplicitVarSizeWithFlags_Flags[q22] /\ x_ExplicitVarSizeWithFlags_Values[q22] = 3 | q22 : int(1..4)]), + and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] + | q1 : int(1..3)]), + and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..4)]), + x_ExplicitVarSizeWithMarker_Marker <= 4, + and([x_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q4] < x_ExplicitVarSizeWithFlags_Values[q4 + 1] + | q4 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q5] = false -> x_ExplicitVarSizeWithFlags_Values[q5] = 1 | q5 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q6] | q6 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q7]) | q7 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithFlags_Flags[q10] -> + or([q12 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q12] = x_ExplicitVarSizeWithFlags_Values[q10] + | q12 : int(1..4)]) + | q10 : int(1..4)]), + and([q14 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithFlags_Flags[q16] /\ + x_ExplicitVarSizeWithFlags_Values[q16] = x_ExplicitVarSizeWithMarker_Values[q14] + | q16 : int(1..4)]) + | q14 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set06/expected/model_3_4_1_1-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_3_4_1_1-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_3_4_1_1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_3_4_1_1-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_3_4_1_1-solution000002.solution new file mode 100644 index 0000000000..85149821f6 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_3_4_1_1-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_3_4_1_1.eprime b/tests/exhaustive/basic/set06/expected/model_3_4_1_1.eprime new file mode 100644 index 0000000000..4e52803143 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_3_4_1_1.eprime @@ -0,0 +1,48 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_Occurrence: matrix indexed by [int(1..4)] of bool +branching on + [x_Occurrence, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, + x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] +such that + or([q29 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q29] = 1 | q29 : int(1..4)]), + or([x_ExplicitVarSizeWithFlags_Flags[q31] /\ x_ExplicitVarSizeWithFlags_Values[q31] = 2 | q31 : int(1..4)]), + x_Occurrence[3], + and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] + | q1 : int(1..3)]), + and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..4)]), + x_ExplicitVarSizeWithMarker_Marker <= 4, + and([x_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q4] < x_ExplicitVarSizeWithFlags_Values[q4 + 1] + | q4 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q5] = false -> x_ExplicitVarSizeWithFlags_Values[q5] = 1 | q5 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q6] | q6 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q7]) | q7 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithFlags_Flags[q10] -> + or([q12 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q12] = x_ExplicitVarSizeWithFlags_Values[q10] + | q12 : int(1..4)]) + | q10 : int(1..4)]), + and([q14 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithFlags_Flags[q16] /\ + x_ExplicitVarSizeWithFlags_Values[q16] = x_ExplicitVarSizeWithMarker_Values[q14] + | q16 : int(1..4)]) + | q14 : int(1..4)]), + sum([toInt(x_Occurrence[q17]) | q17 : int(1..4)]) <= 4, + and([x_Occurrence[q18] -> + or([q20 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q20] = q18 + | q20 : int(1..4)]) + | q18 : int(1..4)]), + and([q22 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q22]] + | q22 : int(1..4)]), + and([x_Occurrence[q23] -> + or([x_ExplicitVarSizeWithFlags_Flags[q25] /\ x_ExplicitVarSizeWithFlags_Values[q25] = q23 | q25 : int(1..4)]) + | q23 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q27] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q27]] + | q27 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set06/expected/model_3_4_1_2-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_3_4_1_2-solution000001.solution new file mode 100644 index 0000000000..85149821f6 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_3_4_1_2-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_3_4_1_2-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_3_4_1_2-solution000002.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_3_4_1_2-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_3_4_1_2.eprime b/tests/exhaustive/basic/set06/expected/model_3_4_1_2.eprime new file mode 100644 index 0000000000..74a01c0599 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_3_4_1_2.eprime @@ -0,0 +1,77 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_Occurrence: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +branching on + [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, + x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_Occurrence] +such that + or([q54 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q54] = 1 | q54 : int(1..4)]), + or([x_ExplicitVarSizeWithFlags_Flags[q56] /\ x_ExplicitVarSizeWithFlags_Values[q56] = 2 | q56 : int(1..4)]), + x_Occurrence[3], + and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] + | q1 : int(1..3)]), + and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..4)]), + x_ExplicitVarSizeWithMarker_Marker <= 4, + and([x_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q4] < x_ExplicitVarSizeWithFlags_Values[q4 + 1] + | q4 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q5] = false -> x_ExplicitVarSizeWithFlags_Values[q5] = 1 | q5 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q6] | q6 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q7]) | q7 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithFlags_Flags[q10] -> + or([q12 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q12] = x_ExplicitVarSizeWithFlags_Values[q10] + | q12 : int(1..4)]) + | q10 : int(1..4)]), + and([q14 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithFlags_Flags[q16] /\ + x_ExplicitVarSizeWithFlags_Values[q16] = x_ExplicitVarSizeWithMarker_Values[q14] + | q16 : int(1..4)]) + | q14 : int(1..4)]), + sum([toInt(x_Occurrence[q17]) | q17 : int(1..4)]) <= 4, + and([x_Occurrence[q43] -> + or([q45 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q45] = q43 + | q45 : int(1..4)]) + | q43 : int(1..4)]), + and([q47 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q47]] + | q47 : int(1..4)]), + and([x_Occurrence[q48] -> + or([x_ExplicitVarSizeWithFlags_Flags[q50] /\ x_ExplicitVarSizeWithFlags_Values[q50] = q48 | q50 : int(1..4)]) + | q48 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q52] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q52]] + | q52 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q18] < x_ExplicitVarSizeWithDummy[q18 + 1] \/ x_ExplicitVarSizeWithDummy[q18] = 5 + | q18 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q19] = 5 -> x_ExplicitVarSizeWithDummy[q19 + 1] = 5 | q19 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithDummy[q20] != 5) | q20 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithDummy[q23] != 5 -> + or([q25 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q25] = x_ExplicitVarSizeWithDummy[q23] + | q25 : int(1..4)]) + | q23 : int(1..4)]), + and([q27 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithDummy[q29] != 5 /\ + x_ExplicitVarSizeWithDummy[q29] = x_ExplicitVarSizeWithMarker_Values[q27] + | q29 : int(1..4)]) + | q27 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q31] != 5 -> + or([x_ExplicitVarSizeWithFlags_Flags[q33] /\ + x_ExplicitVarSizeWithFlags_Values[q33] = x_ExplicitVarSizeWithDummy[q31] + | q33 : int(1..4)]) + | q31 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q35] -> + or([x_ExplicitVarSizeWithDummy[q37] != 5 /\ + x_ExplicitVarSizeWithDummy[q37] = x_ExplicitVarSizeWithFlags_Values[q35] + | q37 : int(1..4)]) + | q35 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q39] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q39]] | q39 : int(1..4)]), + and([x_Occurrence[q40] -> + or([x_ExplicitVarSizeWithDummy[q42] != 5 /\ x_ExplicitVarSizeWithDummy[q42] = q40 | q42 : int(1..4)]) + | q40 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set06/expected/model_3_4_2_1-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_3_4_2_1-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_3_4_2_1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_3_4_2_1-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_3_4_2_1-solution000002.solution new file mode 100644 index 0000000000..85149821f6 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_3_4_2_1-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_3_4_2_1.eprime b/tests/exhaustive/basic/set06/expected/model_3_4_2_1.eprime new file mode 100644 index 0000000000..f93afbb056 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_3_4_2_1.eprime @@ -0,0 +1,77 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +find x_Occurrence: matrix indexed by [int(1..4)] of bool +branching on + [x_Occurrence, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, + x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy] +such that + or([q54 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q54] = 1 | q54 : int(1..4)]), + or([x_ExplicitVarSizeWithFlags_Flags[q56] /\ x_ExplicitVarSizeWithFlags_Values[q56] = 2 | q56 : int(1..4)]), + or([x_ExplicitVarSizeWithDummy[q58] != 5 /\ x_ExplicitVarSizeWithDummy[q58] = 3 | q58 : int(1..4)]), + and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] + | q1 : int(1..3)]), + and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..4)]), + x_ExplicitVarSizeWithMarker_Marker <= 4, + and([x_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q4] < x_ExplicitVarSizeWithFlags_Values[q4 + 1] + | q4 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q5] = false -> x_ExplicitVarSizeWithFlags_Values[q5] = 1 | q5 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q6] | q6 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q7]) | q7 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithFlags_Flags[q10] -> + or([q12 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q12] = x_ExplicitVarSizeWithFlags_Values[q10] + | q12 : int(1..4)]) + | q10 : int(1..4)]), + and([q14 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithFlags_Flags[q16] /\ + x_ExplicitVarSizeWithFlags_Values[q16] = x_ExplicitVarSizeWithMarker_Values[q14] + | q16 : int(1..4)]) + | q14 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q17] < x_ExplicitVarSizeWithDummy[q17 + 1] \/ x_ExplicitVarSizeWithDummy[q17] = 5 + | q17 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q18] = 5 -> x_ExplicitVarSizeWithDummy[q18 + 1] = 5 | q18 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithDummy[q19] != 5) | q19 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithDummy[q22] != 5 -> + or([q24 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q24] = x_ExplicitVarSizeWithDummy[q22] + | q24 : int(1..4)]) + | q22 : int(1..4)]), + and([q26 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithDummy[q28] != 5 /\ + x_ExplicitVarSizeWithDummy[q28] = x_ExplicitVarSizeWithMarker_Values[q26] + | q28 : int(1..4)]) + | q26 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q30] != 5 -> + or([x_ExplicitVarSizeWithFlags_Flags[q32] /\ + x_ExplicitVarSizeWithFlags_Values[q32] = x_ExplicitVarSizeWithDummy[q30] + | q32 : int(1..4)]) + | q30 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q34] -> + or([x_ExplicitVarSizeWithDummy[q36] != 5 /\ + x_ExplicitVarSizeWithDummy[q36] = x_ExplicitVarSizeWithFlags_Values[q34] + | q36 : int(1..4)]) + | q34 : int(1..4)]), + sum([toInt(x_Occurrence[q37]) | q37 : int(1..4)]) <= 4, + and([x_Occurrence[q38] -> + or([q40 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q40] = q38 + | q40 : int(1..4)]) + | q38 : int(1..4)]), + and([q42 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q42]] + | q42 : int(1..4)]), + and([x_Occurrence[q43] -> + or([x_ExplicitVarSizeWithFlags_Flags[q45] /\ x_ExplicitVarSizeWithFlags_Values[q45] = q43 | q45 : int(1..4)]) + | q43 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q47] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q47]] + | q47 : int(1..4)]), + and([x_Occurrence[q48] -> + or([x_ExplicitVarSizeWithDummy[q50] != 5 /\ x_ExplicitVarSizeWithDummy[q50] = q48 | q50 : int(1..4)]) + | q48 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q52] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q52]] | q52 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set06/expected/model_3_4_2_2-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_3_4_2_2-solution000001.solution new file mode 100644 index 0000000000..85149821f6 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_3_4_2_2-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_3_4_2_2-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_3_4_2_2-solution000002.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_3_4_2_2-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_3_4_2_2.eprime b/tests/exhaustive/basic/set06/expected/model_3_4_2_2.eprime new file mode 100644 index 0000000000..f2d9d0a651 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_3_4_2_2.eprime @@ -0,0 +1,60 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +branching on + [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, + x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] +such that + or([q38 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q38] = 1 | q38 : int(1..4)]), + or([x_ExplicitVarSizeWithFlags_Flags[q40] /\ x_ExplicitVarSizeWithFlags_Values[q40] = 2 | q40 : int(1..4)]), + or([x_ExplicitVarSizeWithDummy[q42] != 5 /\ x_ExplicitVarSizeWithDummy[q42] = 3 | q42 : int(1..4)]), + and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] + | q1 : int(1..3)]), + and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..4)]), + x_ExplicitVarSizeWithMarker_Marker <= 4, + and([x_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q4] < x_ExplicitVarSizeWithFlags_Values[q4 + 1] + | q4 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q5] = false -> x_ExplicitVarSizeWithFlags_Values[q5] = 1 | q5 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q6] | q6 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q7]) | q7 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithFlags_Flags[q10] -> + or([q12 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q12] = x_ExplicitVarSizeWithFlags_Values[q10] + | q12 : int(1..4)]) + | q10 : int(1..4)]), + and([q14 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithFlags_Flags[q16] /\ + x_ExplicitVarSizeWithFlags_Values[q16] = x_ExplicitVarSizeWithMarker_Values[q14] + | q16 : int(1..4)]) + | q14 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q17] < x_ExplicitVarSizeWithDummy[q17 + 1] \/ x_ExplicitVarSizeWithDummy[q17] = 5 + | q17 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q18] = 5 -> x_ExplicitVarSizeWithDummy[q18 + 1] = 5 | q18 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithDummy[q19] != 5) | q19 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithDummy[q22] != 5 -> + or([q24 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q24] = x_ExplicitVarSizeWithDummy[q22] + | q24 : int(1..4)]) + | q22 : int(1..4)]), + and([q26 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithDummy[q28] != 5 /\ + x_ExplicitVarSizeWithDummy[q28] = x_ExplicitVarSizeWithMarker_Values[q26] + | q28 : int(1..4)]) + | q26 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q30] != 5 -> + or([x_ExplicitVarSizeWithFlags_Flags[q32] /\ + x_ExplicitVarSizeWithFlags_Values[q32] = x_ExplicitVarSizeWithDummy[q30] + | q32 : int(1..4)]) + | q30 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q34] -> + or([x_ExplicitVarSizeWithDummy[q36] != 5 /\ + x_ExplicitVarSizeWithDummy[q36] = x_ExplicitVarSizeWithFlags_Values[q34] + | q36 : int(1..4)]) + | q34 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set06/expected/model_3_4_3_1-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_3_4_3_1-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_3_4_3_1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_3_4_3_1-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_3_4_3_1-solution000002.solution new file mode 100644 index 0000000000..85149821f6 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_3_4_3_1-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_3_4_3_1.eprime b/tests/exhaustive/basic/set06/expected/model_3_4_3_1.eprime new file mode 100644 index 0000000000..eb620a3fab --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_3_4_3_1.eprime @@ -0,0 +1,48 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_Occurrence: matrix indexed by [int(1..4)] of bool +branching on + [x_Occurrence, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, + x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] +such that + or([q29 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q29] = 1 | q29 : int(1..4)]), + or([x_ExplicitVarSizeWithFlags_Flags[q31] /\ x_ExplicitVarSizeWithFlags_Values[q31] = 2 | q31 : int(1..4)]), + or([q33 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q33] = 3 | q33 : int(1..4)]), + and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] + | q1 : int(1..3)]), + and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..4)]), + x_ExplicitVarSizeWithMarker_Marker <= 4, + and([x_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q4] < x_ExplicitVarSizeWithFlags_Values[q4 + 1] + | q4 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q5] = false -> x_ExplicitVarSizeWithFlags_Values[q5] = 1 | q5 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q6] | q6 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q7]) | q7 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithFlags_Flags[q10] -> + or([q12 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q12] = x_ExplicitVarSizeWithFlags_Values[q10] + | q12 : int(1..4)]) + | q10 : int(1..4)]), + and([q14 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithFlags_Flags[q16] /\ + x_ExplicitVarSizeWithFlags_Values[q16] = x_ExplicitVarSizeWithMarker_Values[q14] + | q16 : int(1..4)]) + | q14 : int(1..4)]), + sum([toInt(x_Occurrence[q17]) | q17 : int(1..4)]) <= 4, + and([x_Occurrence[q18] -> + or([q20 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q20] = q18 + | q20 : int(1..4)]) + | q18 : int(1..4)]), + and([q22 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q22]] + | q22 : int(1..4)]), + and([x_Occurrence[q23] -> + or([x_ExplicitVarSizeWithFlags_Flags[q25] /\ x_ExplicitVarSizeWithFlags_Values[q25] = q23 | q25 : int(1..4)]) + | q23 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q27] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q27]] + | q27 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set06/expected/model_3_4_3_2-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_3_4_3_2-solution000001.solution new file mode 100644 index 0000000000..85149821f6 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_3_4_3_2-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_3_4_3_2-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_3_4_3_2-solution000002.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_3_4_3_2-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_3_4_3_2.eprime b/tests/exhaustive/basic/set06/expected/model_3_4_3_2.eprime new file mode 100644 index 0000000000..99ec382079 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_3_4_3_2.eprime @@ -0,0 +1,60 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +branching on + [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, + x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] +such that + or([q38 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q38] = 1 | q38 : int(1..4)]), + or([x_ExplicitVarSizeWithFlags_Flags[q40] /\ x_ExplicitVarSizeWithFlags_Values[q40] = 2 | q40 : int(1..4)]), + or([q42 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q42] = 3 | q42 : int(1..4)]), + and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] + | q1 : int(1..3)]), + and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..4)]), + x_ExplicitVarSizeWithMarker_Marker <= 4, + and([x_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q4] < x_ExplicitVarSizeWithFlags_Values[q4 + 1] + | q4 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q5] = false -> x_ExplicitVarSizeWithFlags_Values[q5] = 1 | q5 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q6] | q6 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q7]) | q7 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithFlags_Flags[q10] -> + or([q12 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q12] = x_ExplicitVarSizeWithFlags_Values[q10] + | q12 : int(1..4)]) + | q10 : int(1..4)]), + and([q14 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithFlags_Flags[q16] /\ + x_ExplicitVarSizeWithFlags_Values[q16] = x_ExplicitVarSizeWithMarker_Values[q14] + | q16 : int(1..4)]) + | q14 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q17] < x_ExplicitVarSizeWithDummy[q17 + 1] \/ x_ExplicitVarSizeWithDummy[q17] = 5 + | q17 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q18] = 5 -> x_ExplicitVarSizeWithDummy[q18 + 1] = 5 | q18 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithDummy[q19] != 5) | q19 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithDummy[q22] != 5 -> + or([q24 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q24] = x_ExplicitVarSizeWithDummy[q22] + | q24 : int(1..4)]) + | q22 : int(1..4)]), + and([q26 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithDummy[q28] != 5 /\ + x_ExplicitVarSizeWithDummy[q28] = x_ExplicitVarSizeWithMarker_Values[q26] + | q28 : int(1..4)]) + | q26 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q30] != 5 -> + or([x_ExplicitVarSizeWithFlags_Flags[q32] /\ + x_ExplicitVarSizeWithFlags_Values[q32] = x_ExplicitVarSizeWithDummy[q30] + | q32 : int(1..4)]) + | q30 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q34] -> + or([x_ExplicitVarSizeWithDummy[q36] != 5 /\ + x_ExplicitVarSizeWithDummy[q36] = x_ExplicitVarSizeWithFlags_Values[q34] + | q36 : int(1..4)]) + | q34 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set06/expected/model_3_4_3_3-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_3_4_3_3-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_3_4_3_3-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_3_4_3_3-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_3_4_3_3-solution000002.solution new file mode 100644 index 0000000000..85149821f6 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_3_4_3_3-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_3_4_3_3.eprime b/tests/exhaustive/basic/set06/expected/model_3_4_3_3.eprime new file mode 100644 index 0000000000..5a5960dab7 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_3_4_3_3.eprime @@ -0,0 +1,35 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +branching on + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithMarker_Marker, + x_ExplicitVarSizeWithMarker_Values] +such that + or([q18 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q18] = 1 | q18 : int(1..4)]), + or([x_ExplicitVarSizeWithFlags_Flags[q20] /\ x_ExplicitVarSizeWithFlags_Values[q20] = 2 | q20 : int(1..4)]), + or([q22 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q22] = 3 | q22 : int(1..4)]), + and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] + | q1 : int(1..3)]), + and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..4)]), + x_ExplicitVarSizeWithMarker_Marker <= 4, + and([x_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q4] < x_ExplicitVarSizeWithFlags_Values[q4 + 1] + | q4 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q5] = false -> x_ExplicitVarSizeWithFlags_Values[q5] = 1 | q5 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q6] | q6 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q7]) | q7 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithFlags_Flags[q10] -> + or([q12 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q12] = x_ExplicitVarSizeWithFlags_Values[q10] + | q12 : int(1..4)]) + | q10 : int(1..4)]), + and([q14 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithFlags_Flags[q16] /\ + x_ExplicitVarSizeWithFlags_Values[q16] = x_ExplicitVarSizeWithMarker_Values[q14] + | q16 : int(1..4)]) + | q14 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set06/expected/model_3_4_4_1-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_3_4_4_1-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_3_4_4_1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_3_4_4_1-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_3_4_4_1-solution000002.solution new file mode 100644 index 0000000000..85149821f6 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_3_4_4_1-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_3_4_4_1.eprime b/tests/exhaustive/basic/set06/expected/model_3_4_4_1.eprime new file mode 100644 index 0000000000..5887490b4d --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_3_4_4_1.eprime @@ -0,0 +1,48 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_Occurrence: matrix indexed by [int(1..4)] of bool +branching on + [x_Occurrence, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, + x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] +such that + or([q29 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q29] = 1 | q29 : int(1..4)]), + or([x_ExplicitVarSizeWithFlags_Flags[q31] /\ x_ExplicitVarSizeWithFlags_Values[q31] = 2 | q31 : int(1..4)]), + or([x_ExplicitVarSizeWithFlags_Flags[q33] /\ x_ExplicitVarSizeWithFlags_Values[q33] = 3 | q33 : int(1..4)]), + and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] + | q1 : int(1..3)]), + and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..4)]), + x_ExplicitVarSizeWithMarker_Marker <= 4, + and([x_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q4] < x_ExplicitVarSizeWithFlags_Values[q4 + 1] + | q4 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q5] = false -> x_ExplicitVarSizeWithFlags_Values[q5] = 1 | q5 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q6] | q6 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q7]) | q7 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithFlags_Flags[q10] -> + or([q12 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q12] = x_ExplicitVarSizeWithFlags_Values[q10] + | q12 : int(1..4)]) + | q10 : int(1..4)]), + and([q14 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithFlags_Flags[q16] /\ + x_ExplicitVarSizeWithFlags_Values[q16] = x_ExplicitVarSizeWithMarker_Values[q14] + | q16 : int(1..4)]) + | q14 : int(1..4)]), + sum([toInt(x_Occurrence[q17]) | q17 : int(1..4)]) <= 4, + and([x_Occurrence[q18] -> + or([q20 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q20] = q18 + | q20 : int(1..4)]) + | q18 : int(1..4)]), + and([q22 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q22]] + | q22 : int(1..4)]), + and([x_Occurrence[q23] -> + or([x_ExplicitVarSizeWithFlags_Flags[q25] /\ x_ExplicitVarSizeWithFlags_Values[q25] = q23 | q25 : int(1..4)]) + | q23 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q27] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q27]] + | q27 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set06/expected/model_3_4_4_2-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_3_4_4_2-solution000001.solution new file mode 100644 index 0000000000..85149821f6 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_3_4_4_2-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_3_4_4_2-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_3_4_4_2-solution000002.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_3_4_4_2-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_3_4_4_2.eprime b/tests/exhaustive/basic/set06/expected/model_3_4_4_2.eprime new file mode 100644 index 0000000000..5acf1611b5 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_3_4_4_2.eprime @@ -0,0 +1,60 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +branching on + [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, + x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] +such that + or([q38 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q38] = 1 | q38 : int(1..4)]), + or([x_ExplicitVarSizeWithFlags_Flags[q40] /\ x_ExplicitVarSizeWithFlags_Values[q40] = 2 | q40 : int(1..4)]), + or([x_ExplicitVarSizeWithFlags_Flags[q42] /\ x_ExplicitVarSizeWithFlags_Values[q42] = 3 | q42 : int(1..4)]), + and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] + | q1 : int(1..3)]), + and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..4)]), + x_ExplicitVarSizeWithMarker_Marker <= 4, + and([x_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q4] < x_ExplicitVarSizeWithFlags_Values[q4 + 1] + | q4 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q5] = false -> x_ExplicitVarSizeWithFlags_Values[q5] = 1 | q5 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q6] | q6 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q7]) | q7 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithFlags_Flags[q10] -> + or([q12 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q12] = x_ExplicitVarSizeWithFlags_Values[q10] + | q12 : int(1..4)]) + | q10 : int(1..4)]), + and([q14 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithFlags_Flags[q16] /\ + x_ExplicitVarSizeWithFlags_Values[q16] = x_ExplicitVarSizeWithMarker_Values[q14] + | q16 : int(1..4)]) + | q14 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q17] < x_ExplicitVarSizeWithDummy[q17 + 1] \/ x_ExplicitVarSizeWithDummy[q17] = 5 + | q17 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q18] = 5 -> x_ExplicitVarSizeWithDummy[q18 + 1] = 5 | q18 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithDummy[q19] != 5) | q19 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithDummy[q22] != 5 -> + or([q24 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q24] = x_ExplicitVarSizeWithDummy[q22] + | q24 : int(1..4)]) + | q22 : int(1..4)]), + and([q26 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithDummy[q28] != 5 /\ + x_ExplicitVarSizeWithDummy[q28] = x_ExplicitVarSizeWithMarker_Values[q26] + | q28 : int(1..4)]) + | q26 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q30] != 5 -> + or([x_ExplicitVarSizeWithFlags_Flags[q32] /\ + x_ExplicitVarSizeWithFlags_Values[q32] = x_ExplicitVarSizeWithDummy[q30] + | q32 : int(1..4)]) + | q30 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q34] -> + or([x_ExplicitVarSizeWithDummy[q36] != 5 /\ + x_ExplicitVarSizeWithDummy[q36] = x_ExplicitVarSizeWithFlags_Values[q34] + | q36 : int(1..4)]) + | q34 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set06/expected/model_3_4_4_3-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_3_4_4_3-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_3_4_4_3-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_3_4_4_3-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_3_4_4_3-solution000002.solution new file mode 100644 index 0000000000..85149821f6 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_3_4_4_3-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_3_4_4_3.eprime b/tests/exhaustive/basic/set06/expected/model_3_4_4_3.eprime new file mode 100644 index 0000000000..fadbf77294 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_3_4_4_3.eprime @@ -0,0 +1,35 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +branching on + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithMarker_Marker, + x_ExplicitVarSizeWithMarker_Values] +such that + or([q18 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q18] = 1 | q18 : int(1..4)]), + or([x_ExplicitVarSizeWithFlags_Flags[q20] /\ x_ExplicitVarSizeWithFlags_Values[q20] = 2 | q20 : int(1..4)]), + or([x_ExplicitVarSizeWithFlags_Flags[q22] /\ x_ExplicitVarSizeWithFlags_Values[q22] = 3 | q22 : int(1..4)]), + and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] + | q1 : int(1..3)]), + and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..4)]), + x_ExplicitVarSizeWithMarker_Marker <= 4, + and([x_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q4] < x_ExplicitVarSizeWithFlags_Values[q4 + 1] + | q4 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q5] = false -> x_ExplicitVarSizeWithFlags_Values[q5] = 1 | q5 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q6] | q6 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q7]) | q7 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithFlags_Flags[q10] -> + or([q12 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q12] = x_ExplicitVarSizeWithFlags_Values[q10] + | q12 : int(1..4)]) + | q10 : int(1..4)]), + and([q14 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithFlags_Flags[q16] /\ + x_ExplicitVarSizeWithFlags_Values[q16] = x_ExplicitVarSizeWithMarker_Values[q14] + | q16 : int(1..4)]) + | q14 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set06/expected/model_4_1_1_1-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_4_1_1_1-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_4_1_1_1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_4_1_1_1-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_4_1_1_1-solution000002.solution new file mode 100644 index 0000000000..85149821f6 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_4_1_1_1-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_4_1_1_1.eprime b/tests/exhaustive/basic/set06/expected/model_4_1_1_1.eprime new file mode 100644 index 0000000000..840476d8f2 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_4_1_1_1.eprime @@ -0,0 +1,23 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_Occurrence: matrix indexed by [int(1..4)] of bool +branching on [x_Occurrence, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] +such that + or([x_ExplicitVarSizeWithFlags_Flags[q13] /\ x_ExplicitVarSizeWithFlags_Values[q13] = 1 | q13 : int(1..4)]), + x_Occurrence[2], + x_Occurrence[3], + and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]) <= 4, + sum([toInt(x_Occurrence[q6]) | q6 : int(1..4)]) <= 4, + and([x_Occurrence[q7] -> + or([x_ExplicitVarSizeWithFlags_Flags[q9] /\ x_ExplicitVarSizeWithFlags_Values[q9] = q7 | q9 : int(1..4)]) + | q7 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q11] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q11]] + | q11 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set06/expected/model_4_1_1_2-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_4_1_1_2-solution000001.solution new file mode 100644 index 0000000000..85149821f6 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_4_1_1_2-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_4_1_1_2-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_4_1_1_2-solution000002.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_4_1_1_2-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_4_1_1_2.eprime b/tests/exhaustive/basic/set06/expected/model_4_1_1_2.eprime new file mode 100644 index 0000000000..c40a34fba9 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_4_1_1_2.eprime @@ -0,0 +1,43 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_Occurrence: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +branching on + [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_Occurrence] +such that + or([x_ExplicitVarSizeWithFlags_Flags[q30] /\ x_ExplicitVarSizeWithFlags_Values[q30] = 1 | q30 : int(1..4)]), + x_Occurrence[2], + x_Occurrence[3], + and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]) <= 4, + sum([toInt(x_Occurrence[q6]) | q6 : int(1..4)]) <= 4, + and([x_Occurrence[q24] -> + or([x_ExplicitVarSizeWithFlags_Flags[q26] /\ x_ExplicitVarSizeWithFlags_Values[q26] = q24 | q26 : int(1..4)]) + | q24 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q28] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q28]] + | q28 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q7] < x_ExplicitVarSizeWithDummy[q7 + 1] \/ x_ExplicitVarSizeWithDummy[q7] = 5 + | q7 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q8] = 5 -> x_ExplicitVarSizeWithDummy[q8 + 1] = 5 | q8 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithDummy[q9] != 5) | q9 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithDummy[q12] != 5 -> + or([x_ExplicitVarSizeWithFlags_Flags[q14] /\ + x_ExplicitVarSizeWithFlags_Values[q14] = x_ExplicitVarSizeWithDummy[q12] + | q14 : int(1..4)]) + | q12 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q16] -> + or([x_ExplicitVarSizeWithDummy[q18] != 5 /\ + x_ExplicitVarSizeWithDummy[q18] = x_ExplicitVarSizeWithFlags_Values[q16] + | q18 : int(1..4)]) + | q16 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q20] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q20]] | q20 : int(1..4)]), + and([x_Occurrence[q21] -> + or([x_ExplicitVarSizeWithDummy[q23] != 5 /\ x_ExplicitVarSizeWithDummy[q23] = q21 | q23 : int(1..4)]) + | q21 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set06/expected/model_4_1_1_3-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_4_1_1_3-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_4_1_1_3-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_4_1_1_3-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_4_1_1_3-solution000002.solution new file mode 100644 index 0000000000..85149821f6 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_4_1_1_3-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_4_1_1_3.eprime b/tests/exhaustive/basic/set06/expected/model_4_1_1_3.eprime new file mode 100644 index 0000000000..cf6fdd09fe --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_4_1_1_3.eprime @@ -0,0 +1,48 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_Occurrence: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +branching on + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithFlags_Flags, + x_ExplicitVarSizeWithFlags_Values, x_Occurrence] +such that + or([x_ExplicitVarSizeWithFlags_Flags[q29] /\ x_ExplicitVarSizeWithFlags_Values[q29] = 1 | q29 : int(1..4)]), + x_Occurrence[2], + x_Occurrence[3], + and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]) <= 4, + sum([toInt(x_Occurrence[q6]) | q6 : int(1..4)]) <= 4, + and([x_Occurrence[q23] -> + or([x_ExplicitVarSizeWithFlags_Flags[q25] /\ x_ExplicitVarSizeWithFlags_Values[q25] = q23 | q25 : int(1..4)]) + | q23 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q27] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q27]] + | q27 : int(1..4)]), + and([q7 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q7] < x_ExplicitVarSizeWithMarker_Values[q7 + 1] + | q7 : int(1..3)]), + and([q8 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q8] = 1 | q8 : int(1..4)]), + x_ExplicitVarSizeWithMarker_Marker <= 4, + and([q11 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithFlags_Flags[q13] /\ + x_ExplicitVarSizeWithFlags_Values[q13] = x_ExplicitVarSizeWithMarker_Values[q11] + | q13 : int(1..4)]) + | q11 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q15] -> + or([q17 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q17] = x_ExplicitVarSizeWithFlags_Values[q15] + | q17 : int(1..4)]) + | q15 : int(1..4)]), + and([q19 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q19]] + | q19 : int(1..4)]), + and([x_Occurrence[q20] -> + or([q22 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q22] = q20 + | q22 : int(1..4)]) + | q20 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set06/expected/model_4_1_2_1-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_4_1_2_1-solution000001.solution new file mode 100644 index 0000000000..85149821f6 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_4_1_2_1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_4_1_2_1-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_4_1_2_1-solution000002.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_4_1_2_1-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_4_1_2_1.eprime b/tests/exhaustive/basic/set06/expected/model_4_1_2_1.eprime new file mode 100644 index 0000000000..4e673b02e4 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_4_1_2_1.eprime @@ -0,0 +1,43 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_Occurrence: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +branching on + [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_Occurrence] +such that + or([x_ExplicitVarSizeWithFlags_Flags[q32] /\ x_ExplicitVarSizeWithFlags_Values[q32] = 1 | q32 : int(1..4)]), + x_Occurrence[2], + or([x_ExplicitVarSizeWithDummy[q30] != 5 /\ x_ExplicitVarSizeWithDummy[q30] = 3 | q30 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]) <= 4, + sum([toInt(x_Occurrence[q6]) | q6 : int(1..4)]) <= 4, + and([x_Occurrence[q24] -> + or([x_ExplicitVarSizeWithFlags_Flags[q26] /\ x_ExplicitVarSizeWithFlags_Values[q26] = q24 | q26 : int(1..4)]) + | q24 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q28] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q28]] + | q28 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q7] < x_ExplicitVarSizeWithDummy[q7 + 1] \/ x_ExplicitVarSizeWithDummy[q7] = 5 + | q7 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q8] = 5 -> x_ExplicitVarSizeWithDummy[q8 + 1] = 5 | q8 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithDummy[q9] != 5) | q9 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithDummy[q12] != 5 -> + or([x_ExplicitVarSizeWithFlags_Flags[q14] /\ + x_ExplicitVarSizeWithFlags_Values[q14] = x_ExplicitVarSizeWithDummy[q12] + | q14 : int(1..4)]) + | q12 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q16] -> + or([x_ExplicitVarSizeWithDummy[q18] != 5 /\ + x_ExplicitVarSizeWithDummy[q18] = x_ExplicitVarSizeWithFlags_Values[q16] + | q18 : int(1..4)]) + | q16 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q20] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q20]] | q20 : int(1..4)]), + and([x_Occurrence[q21] -> + or([x_ExplicitVarSizeWithDummy[q23] != 5 /\ x_ExplicitVarSizeWithDummy[q23] = q21 | q23 : int(1..4)]) + | q21 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set06/expected/model_4_1_2_3-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_4_1_2_3-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_4_1_2_3-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_4_1_2_3-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_4_1_2_3-solution000002.solution new file mode 100644 index 0000000000..85149821f6 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_4_1_2_3-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_4_1_2_3.eprime b/tests/exhaustive/basic/set06/expected/model_4_1_2_3.eprime new file mode 100644 index 0000000000..f80a5a1df4 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_4_1_2_3.eprime @@ -0,0 +1,77 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_Occurrence: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +branching on + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithFlags_Flags, + x_ExplicitVarSizeWithFlags_Values, x_Occurrence, x_ExplicitVarSizeWithDummy] +such that + or([x_ExplicitVarSizeWithFlags_Flags[q56] /\ x_ExplicitVarSizeWithFlags_Values[q56] = 1 | q56 : int(1..4)]), + x_Occurrence[2], + or([x_ExplicitVarSizeWithDummy[q54] != 5 /\ x_ExplicitVarSizeWithDummy[q54] = 3 | q54 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]) <= 4, + sum([toInt(x_Occurrence[q6]) | q6 : int(1..4)]) <= 4, + and([x_Occurrence[q48] -> + or([x_ExplicitVarSizeWithFlags_Flags[q50] /\ x_ExplicitVarSizeWithFlags_Values[q50] = q48 | q50 : int(1..4)]) + | q48 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q52] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q52]] + | q52 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q7] < x_ExplicitVarSizeWithDummy[q7 + 1] \/ x_ExplicitVarSizeWithDummy[q7] = 5 + | q7 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q8] = 5 -> x_ExplicitVarSizeWithDummy[q8 + 1] = 5 | q8 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithDummy[q9] != 5) | q9 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithDummy[q12] != 5 -> + or([x_ExplicitVarSizeWithFlags_Flags[q14] /\ + x_ExplicitVarSizeWithFlags_Values[q14] = x_ExplicitVarSizeWithDummy[q12] + | q14 : int(1..4)]) + | q12 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q16] -> + or([x_ExplicitVarSizeWithDummy[q18] != 5 /\ + x_ExplicitVarSizeWithDummy[q18] = x_ExplicitVarSizeWithFlags_Values[q16] + | q18 : int(1..4)]) + | q16 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q20] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q20]] | q20 : int(1..4)]), + and([x_Occurrence[q21] -> + or([x_ExplicitVarSizeWithDummy[q23] != 5 /\ x_ExplicitVarSizeWithDummy[q23] = q21 | q23 : int(1..4)]) + | q21 : int(1..4)]), + and([q24 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q24] < x_ExplicitVarSizeWithMarker_Values[q24 + 1] + | q24 : int(1..3)]), + and([q25 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q25] = 1 | q25 : int(1..4)]), + x_ExplicitVarSizeWithMarker_Marker <= 4, + and([q28 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithFlags_Flags[q30] /\ + x_ExplicitVarSizeWithFlags_Values[q30] = x_ExplicitVarSizeWithMarker_Values[q28] + | q30 : int(1..4)]) + | q28 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q32] -> + or([q34 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q34] = x_ExplicitVarSizeWithFlags_Values[q32] + | q34 : int(1..4)]) + | q32 : int(1..4)]), + and([q36 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q36]] + | q36 : int(1..4)]), + and([x_Occurrence[q37] -> + or([q39 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q39] = q37 + | q39 : int(1..4)]) + | q37 : int(1..4)]), + and([q41 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithDummy[q43] != 5 /\ + x_ExplicitVarSizeWithDummy[q43] = x_ExplicitVarSizeWithMarker_Values[q41] + | q43 : int(1..4)]) + | q41 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q45] != 5 -> + or([q47 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q47] = x_ExplicitVarSizeWithDummy[q45] + | q47 : int(1..4)]) + | q45 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set06/expected/model_4_1_3_1-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_4_1_3_1-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_4_1_3_1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_4_1_3_1-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_4_1_3_1-solution000002.solution new file mode 100644 index 0000000000..85149821f6 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_4_1_3_1-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_4_1_3_1.eprime b/tests/exhaustive/basic/set06/expected/model_4_1_3_1.eprime new file mode 100644 index 0000000000..408fd414ac --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_4_1_3_1.eprime @@ -0,0 +1,48 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_Occurrence: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +branching on + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithFlags_Flags, + x_ExplicitVarSizeWithFlags_Values, x_Occurrence] +such that + or([x_ExplicitVarSizeWithFlags_Flags[q31] /\ x_ExplicitVarSizeWithFlags_Values[q31] = 1 | q31 : int(1..4)]), + x_Occurrence[2], + or([q29 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q29] = 3 | q29 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]) <= 4, + sum([toInt(x_Occurrence[q6]) | q6 : int(1..4)]) <= 4, + and([x_Occurrence[q23] -> + or([x_ExplicitVarSizeWithFlags_Flags[q25] /\ x_ExplicitVarSizeWithFlags_Values[q25] = q23 | q25 : int(1..4)]) + | q23 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q27] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q27]] + | q27 : int(1..4)]), + and([q7 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q7] < x_ExplicitVarSizeWithMarker_Values[q7 + 1] + | q7 : int(1..3)]), + and([q8 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q8] = 1 | q8 : int(1..4)]), + x_ExplicitVarSizeWithMarker_Marker <= 4, + and([q11 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithFlags_Flags[q13] /\ + x_ExplicitVarSizeWithFlags_Values[q13] = x_ExplicitVarSizeWithMarker_Values[q11] + | q13 : int(1..4)]) + | q11 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q15] -> + or([q17 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q17] = x_ExplicitVarSizeWithFlags_Values[q15] + | q17 : int(1..4)]) + | q15 : int(1..4)]), + and([q19 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q19]] + | q19 : int(1..4)]), + and([x_Occurrence[q20] -> + or([q22 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q22] = q20 + | q22 : int(1..4)]) + | q20 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set06/expected/model_4_1_3_2-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_4_1_3_2-solution000001.solution new file mode 100644 index 0000000000..85149821f6 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_4_1_3_2-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_4_1_3_2-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_4_1_3_2-solution000002.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_4_1_3_2-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_4_1_3_2.eprime b/tests/exhaustive/basic/set06/expected/model_4_1_3_2.eprime new file mode 100644 index 0000000000..d20e6ad442 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_4_1_3_2.eprime @@ -0,0 +1,77 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_Occurrence: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +branching on + [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_Occurrence, + x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] +such that + or([x_ExplicitVarSizeWithFlags_Flags[q56] /\ x_ExplicitVarSizeWithFlags_Values[q56] = 1 | q56 : int(1..4)]), + x_Occurrence[2], + or([q54 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q54] = 3 | q54 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]) <= 4, + sum([toInt(x_Occurrence[q6]) | q6 : int(1..4)]) <= 4, + and([x_Occurrence[q48] -> + or([x_ExplicitVarSizeWithFlags_Flags[q50] /\ x_ExplicitVarSizeWithFlags_Values[q50] = q48 | q50 : int(1..4)]) + | q48 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q52] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q52]] + | q52 : int(1..4)]), + and([q7 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q7] < x_ExplicitVarSizeWithMarker_Values[q7 + 1] + | q7 : int(1..3)]), + and([q8 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q8] = 1 | q8 : int(1..4)]), + x_ExplicitVarSizeWithMarker_Marker <= 4, + and([q11 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithFlags_Flags[q13] /\ + x_ExplicitVarSizeWithFlags_Values[q13] = x_ExplicitVarSizeWithMarker_Values[q11] + | q13 : int(1..4)]) + | q11 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q15] -> + or([q17 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q17] = x_ExplicitVarSizeWithFlags_Values[q15] + | q17 : int(1..4)]) + | q15 : int(1..4)]), + and([q19 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q19]] + | q19 : int(1..4)]), + and([x_Occurrence[q20] -> + or([q22 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q22] = q20 + | q22 : int(1..4)]) + | q20 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q23] < x_ExplicitVarSizeWithDummy[q23 + 1] \/ x_ExplicitVarSizeWithDummy[q23] = 5 + | q23 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q24] = 5 -> x_ExplicitVarSizeWithDummy[q24 + 1] = 5 | q24 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithDummy[q25] != 5) | q25 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithDummy[q28] != 5 -> + or([x_ExplicitVarSizeWithFlags_Flags[q30] /\ + x_ExplicitVarSizeWithFlags_Values[q30] = x_ExplicitVarSizeWithDummy[q28] + | q30 : int(1..4)]) + | q28 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q32] -> + or([x_ExplicitVarSizeWithDummy[q34] != 5 /\ + x_ExplicitVarSizeWithDummy[q34] = x_ExplicitVarSizeWithFlags_Values[q32] + | q34 : int(1..4)]) + | q32 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q36] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q36]] | q36 : int(1..4)]), + and([x_Occurrence[q37] -> + or([x_ExplicitVarSizeWithDummy[q39] != 5 /\ x_ExplicitVarSizeWithDummy[q39] = q37 | q39 : int(1..4)]) + | q37 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q41] != 5 -> + or([q43 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q43] = x_ExplicitVarSizeWithDummy[q41] + | q43 : int(1..4)]) + | q41 : int(1..4)]), + and([q45 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithDummy[q47] != 5 /\ + x_ExplicitVarSizeWithDummy[q47] = x_ExplicitVarSizeWithMarker_Values[q45] + | q47 : int(1..4)]) + | q45 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set06/expected/model_4_1_4_1-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_4_1_4_1-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_4_1_4_1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_4_1_4_1-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_4_1_4_1-solution000002.solution new file mode 100644 index 0000000000..85149821f6 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_4_1_4_1-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_4_1_4_1.eprime b/tests/exhaustive/basic/set06/expected/model_4_1_4_1.eprime new file mode 100644 index 0000000000..ab45974aa0 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_4_1_4_1.eprime @@ -0,0 +1,23 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_Occurrence: matrix indexed by [int(1..4)] of bool +branching on [x_Occurrence, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] +such that + or([x_ExplicitVarSizeWithFlags_Flags[q15] /\ x_ExplicitVarSizeWithFlags_Values[q15] = 1 | q15 : int(1..4)]), + x_Occurrence[2], + or([x_ExplicitVarSizeWithFlags_Flags[q13] /\ x_ExplicitVarSizeWithFlags_Values[q13] = 3 | q13 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]) <= 4, + sum([toInt(x_Occurrence[q6]) | q6 : int(1..4)]) <= 4, + and([x_Occurrence[q7] -> + or([x_ExplicitVarSizeWithFlags_Flags[q9] /\ x_ExplicitVarSizeWithFlags_Values[q9] = q7 | q9 : int(1..4)]) + | q7 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q11] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q11]] + | q11 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set06/expected/model_4_1_4_2-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_4_1_4_2-solution000001.solution new file mode 100644 index 0000000000..85149821f6 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_4_1_4_2-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_4_1_4_2-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_4_1_4_2-solution000002.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_4_1_4_2-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_4_1_4_2.eprime b/tests/exhaustive/basic/set06/expected/model_4_1_4_2.eprime new file mode 100644 index 0000000000..db7ef3b013 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_4_1_4_2.eprime @@ -0,0 +1,43 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_Occurrence: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +branching on + [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_Occurrence] +such that + or([x_ExplicitVarSizeWithFlags_Flags[q32] /\ x_ExplicitVarSizeWithFlags_Values[q32] = 1 | q32 : int(1..4)]), + x_Occurrence[2], + or([x_ExplicitVarSizeWithFlags_Flags[q30] /\ x_ExplicitVarSizeWithFlags_Values[q30] = 3 | q30 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]) <= 4, + sum([toInt(x_Occurrence[q6]) | q6 : int(1..4)]) <= 4, + and([x_Occurrence[q24] -> + or([x_ExplicitVarSizeWithFlags_Flags[q26] /\ x_ExplicitVarSizeWithFlags_Values[q26] = q24 | q26 : int(1..4)]) + | q24 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q28] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q28]] + | q28 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q7] < x_ExplicitVarSizeWithDummy[q7 + 1] \/ x_ExplicitVarSizeWithDummy[q7] = 5 + | q7 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q8] = 5 -> x_ExplicitVarSizeWithDummy[q8 + 1] = 5 | q8 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithDummy[q9] != 5) | q9 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithDummy[q12] != 5 -> + or([x_ExplicitVarSizeWithFlags_Flags[q14] /\ + x_ExplicitVarSizeWithFlags_Values[q14] = x_ExplicitVarSizeWithDummy[q12] + | q14 : int(1..4)]) + | q12 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q16] -> + or([x_ExplicitVarSizeWithDummy[q18] != 5 /\ + x_ExplicitVarSizeWithDummy[q18] = x_ExplicitVarSizeWithFlags_Values[q16] + | q18 : int(1..4)]) + | q16 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q20] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q20]] | q20 : int(1..4)]), + and([x_Occurrence[q21] -> + or([x_ExplicitVarSizeWithDummy[q23] != 5 /\ x_ExplicitVarSizeWithDummy[q23] = q21 | q23 : int(1..4)]) + | q21 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set06/expected/model_4_1_4_3-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_4_1_4_3-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_4_1_4_3-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_4_1_4_3-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_4_1_4_3-solution000002.solution new file mode 100644 index 0000000000..85149821f6 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_4_1_4_3-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_4_1_4_3.eprime b/tests/exhaustive/basic/set06/expected/model_4_1_4_3.eprime new file mode 100644 index 0000000000..4cec8ec549 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_4_1_4_3.eprime @@ -0,0 +1,48 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_Occurrence: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +branching on + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithFlags_Flags, + x_ExplicitVarSizeWithFlags_Values, x_Occurrence] +such that + or([x_ExplicitVarSizeWithFlags_Flags[q31] /\ x_ExplicitVarSizeWithFlags_Values[q31] = 1 | q31 : int(1..4)]), + x_Occurrence[2], + or([x_ExplicitVarSizeWithFlags_Flags[q29] /\ x_ExplicitVarSizeWithFlags_Values[q29] = 3 | q29 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]) <= 4, + sum([toInt(x_Occurrence[q6]) | q6 : int(1..4)]) <= 4, + and([x_Occurrence[q23] -> + or([x_ExplicitVarSizeWithFlags_Flags[q25] /\ x_ExplicitVarSizeWithFlags_Values[q25] = q23 | q25 : int(1..4)]) + | q23 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q27] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q27]] + | q27 : int(1..4)]), + and([q7 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q7] < x_ExplicitVarSizeWithMarker_Values[q7 + 1] + | q7 : int(1..3)]), + and([q8 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q8] = 1 | q8 : int(1..4)]), + x_ExplicitVarSizeWithMarker_Marker <= 4, + and([q11 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithFlags_Flags[q13] /\ + x_ExplicitVarSizeWithFlags_Values[q13] = x_ExplicitVarSizeWithMarker_Values[q11] + | q13 : int(1..4)]) + | q11 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q15] -> + or([q17 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q17] = x_ExplicitVarSizeWithFlags_Values[q15] + | q17 : int(1..4)]) + | q15 : int(1..4)]), + and([q19 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q19]] + | q19 : int(1..4)]), + and([x_Occurrence[q20] -> + or([q22 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q22] = q20 + | q22 : int(1..4)]) + | q20 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set06/expected/model_4_2_1_1-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_4_2_1_1-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_4_2_1_1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_4_2_1_1-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_4_2_1_1-solution000002.solution new file mode 100644 index 0000000000..85149821f6 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_4_2_1_1-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_4_2_1_1.eprime b/tests/exhaustive/basic/set06/expected/model_4_2_1_1.eprime new file mode 100644 index 0000000000..ab9510be14 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_4_2_1_1.eprime @@ -0,0 +1,43 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +find x_Occurrence: matrix indexed by [int(1..4)] of bool +branching on + [x_Occurrence, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy] +such that + or([x_ExplicitVarSizeWithFlags_Flags[q30] /\ x_ExplicitVarSizeWithFlags_Values[q30] = 1 | q30 : int(1..4)]), + or([x_ExplicitVarSizeWithDummy[q32] != 5 /\ x_ExplicitVarSizeWithDummy[q32] = 2 | q32 : int(1..4)]), + x_Occurrence[3], + and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithDummy[q6] < x_ExplicitVarSizeWithDummy[q6 + 1] \/ x_ExplicitVarSizeWithDummy[q6] = 5 + | q6 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q7] = 5 -> x_ExplicitVarSizeWithDummy[q7 + 1] = 5 | q7 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithDummy[q8] != 5) | q8 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithDummy[q11] != 5 -> + or([x_ExplicitVarSizeWithFlags_Flags[q13] /\ + x_ExplicitVarSizeWithFlags_Values[q13] = x_ExplicitVarSizeWithDummy[q11] + | q13 : int(1..4)]) + | q11 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q15] -> + or([x_ExplicitVarSizeWithDummy[q17] != 5 /\ + x_ExplicitVarSizeWithDummy[q17] = x_ExplicitVarSizeWithFlags_Values[q15] + | q17 : int(1..4)]) + | q15 : int(1..4)]), + sum([toInt(x_Occurrence[q18]) | q18 : int(1..4)]) <= 4, + and([x_Occurrence[q19] -> + or([x_ExplicitVarSizeWithFlags_Flags[q21] /\ x_ExplicitVarSizeWithFlags_Values[q21] = q19 | q21 : int(1..4)]) + | q19 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q23] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q23]] + | q23 : int(1..4)]), + and([x_Occurrence[q24] -> + or([x_ExplicitVarSizeWithDummy[q26] != 5 /\ x_ExplicitVarSizeWithDummy[q26] = q24 | q26 : int(1..4)]) + | q24 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q28] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q28]] | q28 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set06/expected/model_4_2_1_3-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_4_2_1_3-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_4_2_1_3-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_4_2_1_3-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_4_2_1_3-solution000002.solution new file mode 100644 index 0000000000..85149821f6 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_4_2_1_3-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_4_2_1_3.eprime b/tests/exhaustive/basic/set06/expected/model_4_2_1_3.eprime new file mode 100644 index 0000000000..85e53801b8 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_4_2_1_3.eprime @@ -0,0 +1,77 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +find x_Occurrence: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +branching on + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithFlags_Flags, + x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy, x_Occurrence] +such that + or([x_ExplicitVarSizeWithFlags_Flags[q54] /\ x_ExplicitVarSizeWithFlags_Values[q54] = 1 | q54 : int(1..4)]), + or([x_ExplicitVarSizeWithDummy[q56] != 5 /\ x_ExplicitVarSizeWithDummy[q56] = 2 | q56 : int(1..4)]), + x_Occurrence[3], + and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithDummy[q6] < x_ExplicitVarSizeWithDummy[q6 + 1] \/ x_ExplicitVarSizeWithDummy[q6] = 5 + | q6 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q7] = 5 -> x_ExplicitVarSizeWithDummy[q7 + 1] = 5 | q7 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithDummy[q8] != 5) | q8 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithDummy[q11] != 5 -> + or([x_ExplicitVarSizeWithFlags_Flags[q13] /\ + x_ExplicitVarSizeWithFlags_Values[q13] = x_ExplicitVarSizeWithDummy[q11] + | q13 : int(1..4)]) + | q11 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q15] -> + or([x_ExplicitVarSizeWithDummy[q17] != 5 /\ + x_ExplicitVarSizeWithDummy[q17] = x_ExplicitVarSizeWithFlags_Values[q15] + | q17 : int(1..4)]) + | q15 : int(1..4)]), + sum([toInt(x_Occurrence[q18]) | q18 : int(1..4)]) <= 4, + and([x_Occurrence[q43] -> + or([x_ExplicitVarSizeWithFlags_Flags[q45] /\ x_ExplicitVarSizeWithFlags_Values[q45] = q43 | q45 : int(1..4)]) + | q43 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q47] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q47]] + | q47 : int(1..4)]), + and([x_Occurrence[q48] -> + or([x_ExplicitVarSizeWithDummy[q50] != 5 /\ x_ExplicitVarSizeWithDummy[q50] = q48 | q50 : int(1..4)]) + | q48 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q52] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q52]] | q52 : int(1..4)]), + and([q19 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q19] < x_ExplicitVarSizeWithMarker_Values[q19 + 1] + | q19 : int(1..3)]), + and([q20 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q20] = 1 | q20 : int(1..4)]), + x_ExplicitVarSizeWithMarker_Marker <= 4, + and([q23 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithFlags_Flags[q25] /\ + x_ExplicitVarSizeWithFlags_Values[q25] = x_ExplicitVarSizeWithMarker_Values[q23] + | q25 : int(1..4)]) + | q23 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q27] -> + or([q29 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q29] = x_ExplicitVarSizeWithFlags_Values[q27] + | q29 : int(1..4)]) + | q27 : int(1..4)]), + and([q31 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithDummy[q33] != 5 /\ + x_ExplicitVarSizeWithDummy[q33] = x_ExplicitVarSizeWithMarker_Values[q31] + | q33 : int(1..4)]) + | q31 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q35] != 5 -> + or([q37 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q37] = x_ExplicitVarSizeWithDummy[q35] + | q37 : int(1..4)]) + | q35 : int(1..4)]), + and([q39 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q39]] + | q39 : int(1..4)]), + and([x_Occurrence[q40] -> + or([q42 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q42] = q40 + | q42 : int(1..4)]) + | q40 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set06/expected/model_4_2_2_1-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_4_2_2_1-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_4_2_2_1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_4_2_2_1-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_4_2_2_1-solution000002.solution new file mode 100644 index 0000000000..85149821f6 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_4_2_2_1-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_4_2_2_1.eprime b/tests/exhaustive/basic/set06/expected/model_4_2_2_1.eprime new file mode 100644 index 0000000000..dad34d0ed0 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_4_2_2_1.eprime @@ -0,0 +1,43 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +find x_Occurrence: matrix indexed by [int(1..4)] of bool +branching on + [x_Occurrence, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy] +such that + or([x_ExplicitVarSizeWithFlags_Flags[q30] /\ x_ExplicitVarSizeWithFlags_Values[q30] = 1 | q30 : int(1..4)]), + or([x_ExplicitVarSizeWithDummy[q32] != 5 /\ x_ExplicitVarSizeWithDummy[q32] = 2 | q32 : int(1..4)]), + or([x_ExplicitVarSizeWithDummy[q34] != 5 /\ x_ExplicitVarSizeWithDummy[q34] = 3 | q34 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithDummy[q6] < x_ExplicitVarSizeWithDummy[q6 + 1] \/ x_ExplicitVarSizeWithDummy[q6] = 5 + | q6 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q7] = 5 -> x_ExplicitVarSizeWithDummy[q7 + 1] = 5 | q7 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithDummy[q8] != 5) | q8 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithDummy[q11] != 5 -> + or([x_ExplicitVarSizeWithFlags_Flags[q13] /\ + x_ExplicitVarSizeWithFlags_Values[q13] = x_ExplicitVarSizeWithDummy[q11] + | q13 : int(1..4)]) + | q11 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q15] -> + or([x_ExplicitVarSizeWithDummy[q17] != 5 /\ + x_ExplicitVarSizeWithDummy[q17] = x_ExplicitVarSizeWithFlags_Values[q15] + | q17 : int(1..4)]) + | q15 : int(1..4)]), + sum([toInt(x_Occurrence[q18]) | q18 : int(1..4)]) <= 4, + and([x_Occurrence[q19] -> + or([x_ExplicitVarSizeWithFlags_Flags[q21] /\ x_ExplicitVarSizeWithFlags_Values[q21] = q19 | q21 : int(1..4)]) + | q19 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q23] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q23]] + | q23 : int(1..4)]), + and([x_Occurrence[q24] -> + or([x_ExplicitVarSizeWithDummy[q26] != 5 /\ x_ExplicitVarSizeWithDummy[q26] = q24 | q26 : int(1..4)]) + | q24 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q28] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q28]] | q28 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set06/expected/model_4_2_2_2-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_4_2_2_2-solution000001.solution new file mode 100644 index 0000000000..85149821f6 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_4_2_2_2-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_4_2_2_2-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_4_2_2_2-solution000002.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_4_2_2_2-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_4_2_2_2.eprime b/tests/exhaustive/basic/set06/expected/model_4_2_2_2.eprime new file mode 100644 index 0000000000..669eaa19ca --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_4_2_2_2.eprime @@ -0,0 +1,31 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +branching on [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] +such that + or([x_ExplicitVarSizeWithFlags_Flags[q19] /\ x_ExplicitVarSizeWithFlags_Values[q19] = 1 | q19 : int(1..4)]), + or([x_ExplicitVarSizeWithDummy[q21] != 5 /\ x_ExplicitVarSizeWithDummy[q21] = 2 | q21 : int(1..4)]), + or([x_ExplicitVarSizeWithDummy[q23] != 5 /\ x_ExplicitVarSizeWithDummy[q23] = 3 | q23 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithDummy[q6] < x_ExplicitVarSizeWithDummy[q6 + 1] \/ x_ExplicitVarSizeWithDummy[q6] = 5 + | q6 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q7] = 5 -> x_ExplicitVarSizeWithDummy[q7 + 1] = 5 | q7 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithDummy[q8] != 5) | q8 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithDummy[q11] != 5 -> + or([x_ExplicitVarSizeWithFlags_Flags[q13] /\ + x_ExplicitVarSizeWithFlags_Values[q13] = x_ExplicitVarSizeWithDummy[q11] + | q13 : int(1..4)]) + | q11 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q15] -> + or([x_ExplicitVarSizeWithDummy[q17] != 5 /\ + x_ExplicitVarSizeWithDummy[q17] = x_ExplicitVarSizeWithFlags_Values[q15] + | q17 : int(1..4)]) + | q15 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set06/expected/model_4_2_2_3-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_4_2_2_3-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_4_2_2_3-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_4_2_2_3-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_4_2_2_3-solution000002.solution new file mode 100644 index 0000000000..85149821f6 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_4_2_2_3-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_4_2_2_3.eprime b/tests/exhaustive/basic/set06/expected/model_4_2_2_3.eprime new file mode 100644 index 0000000000..61e6544c34 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_4_2_2_3.eprime @@ -0,0 +1,60 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +branching on + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithFlags_Flags, + x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy] +such that + or([x_ExplicitVarSizeWithFlags_Flags[q38] /\ x_ExplicitVarSizeWithFlags_Values[q38] = 1 | q38 : int(1..4)]), + or([x_ExplicitVarSizeWithDummy[q40] != 5 /\ x_ExplicitVarSizeWithDummy[q40] = 2 | q40 : int(1..4)]), + or([x_ExplicitVarSizeWithDummy[q42] != 5 /\ x_ExplicitVarSizeWithDummy[q42] = 3 | q42 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithDummy[q6] < x_ExplicitVarSizeWithDummy[q6 + 1] \/ x_ExplicitVarSizeWithDummy[q6] = 5 + | q6 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q7] = 5 -> x_ExplicitVarSizeWithDummy[q7 + 1] = 5 | q7 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithDummy[q8] != 5) | q8 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithDummy[q11] != 5 -> + or([x_ExplicitVarSizeWithFlags_Flags[q13] /\ + x_ExplicitVarSizeWithFlags_Values[q13] = x_ExplicitVarSizeWithDummy[q11] + | q13 : int(1..4)]) + | q11 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q15] -> + or([x_ExplicitVarSizeWithDummy[q17] != 5 /\ + x_ExplicitVarSizeWithDummy[q17] = x_ExplicitVarSizeWithFlags_Values[q15] + | q17 : int(1..4)]) + | q15 : int(1..4)]), + and([q18 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q18] < x_ExplicitVarSizeWithMarker_Values[q18 + 1] + | q18 : int(1..3)]), + and([q19 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q19] = 1 | q19 : int(1..4)]), + x_ExplicitVarSizeWithMarker_Marker <= 4, + and([q22 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithFlags_Flags[q24] /\ + x_ExplicitVarSizeWithFlags_Values[q24] = x_ExplicitVarSizeWithMarker_Values[q22] + | q24 : int(1..4)]) + | q22 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q26] -> + or([q28 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q28] = x_ExplicitVarSizeWithFlags_Values[q26] + | q28 : int(1..4)]) + | q26 : int(1..4)]), + and([q30 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithDummy[q32] != 5 /\ + x_ExplicitVarSizeWithDummy[q32] = x_ExplicitVarSizeWithMarker_Values[q30] + | q32 : int(1..4)]) + | q30 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q34] != 5 -> + or([q36 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q36] = x_ExplicitVarSizeWithDummy[q34] + | q36 : int(1..4)]) + | q34 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set06/expected/model_4_2_3_1-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_4_2_3_1-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_4_2_3_1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_4_2_3_1-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_4_2_3_1-solution000002.solution new file mode 100644 index 0000000000..85149821f6 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_4_2_3_1-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_4_2_3_1.eprime b/tests/exhaustive/basic/set06/expected/model_4_2_3_1.eprime new file mode 100644 index 0000000000..1199423e9f --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_4_2_3_1.eprime @@ -0,0 +1,77 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_Occurrence: matrix indexed by [int(1..4)] of bool +branching on + [x_Occurrence, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy, + x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] +such that + or([x_ExplicitVarSizeWithFlags_Flags[q54] /\ x_ExplicitVarSizeWithFlags_Values[q54] = 1 | q54 : int(1..4)]), + or([x_ExplicitVarSizeWithDummy[q56] != 5 /\ x_ExplicitVarSizeWithDummy[q56] = 2 | q56 : int(1..4)]), + or([q58 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q58] = 3 | q58 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithDummy[q6] < x_ExplicitVarSizeWithDummy[q6 + 1] \/ x_ExplicitVarSizeWithDummy[q6] = 5 + | q6 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q7] = 5 -> x_ExplicitVarSizeWithDummy[q7 + 1] = 5 | q7 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithDummy[q8] != 5) | q8 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithDummy[q11] != 5 -> + or([x_ExplicitVarSizeWithFlags_Flags[q13] /\ + x_ExplicitVarSizeWithFlags_Values[q13] = x_ExplicitVarSizeWithDummy[q11] + | q13 : int(1..4)]) + | q11 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q15] -> + or([x_ExplicitVarSizeWithDummy[q17] != 5 /\ + x_ExplicitVarSizeWithDummy[q17] = x_ExplicitVarSizeWithFlags_Values[q15] + | q17 : int(1..4)]) + | q15 : int(1..4)]), + and([q18 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q18] < x_ExplicitVarSizeWithMarker_Values[q18 + 1] + | q18 : int(1..3)]), + and([q19 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q19] = 1 | q19 : int(1..4)]), + x_ExplicitVarSizeWithMarker_Marker <= 4, + and([q22 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithFlags_Flags[q24] /\ + x_ExplicitVarSizeWithFlags_Values[q24] = x_ExplicitVarSizeWithMarker_Values[q22] + | q24 : int(1..4)]) + | q22 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q26] -> + or([q28 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q28] = x_ExplicitVarSizeWithFlags_Values[q26] + | q28 : int(1..4)]) + | q26 : int(1..4)]), + and([q30 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithDummy[q32] != 5 /\ + x_ExplicitVarSizeWithDummy[q32] = x_ExplicitVarSizeWithMarker_Values[q30] + | q32 : int(1..4)]) + | q30 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q34] != 5 -> + or([q36 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q36] = x_ExplicitVarSizeWithDummy[q34] + | q36 : int(1..4)]) + | q34 : int(1..4)]), + sum([toInt(x_Occurrence[q37]) | q37 : int(1..4)]) <= 4, + and([x_Occurrence[q38] -> + or([x_ExplicitVarSizeWithFlags_Flags[q40] /\ x_ExplicitVarSizeWithFlags_Values[q40] = q38 | q40 : int(1..4)]) + | q38 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q42] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q42]] + | q42 : int(1..4)]), + and([x_Occurrence[q43] -> + or([x_ExplicitVarSizeWithDummy[q45] != 5 /\ x_ExplicitVarSizeWithDummy[q45] = q43 | q45 : int(1..4)]) + | q43 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q47] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q47]] | q47 : int(1..4)]), + and([x_Occurrence[q48] -> + or([q50 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q50] = q48 + | q50 : int(1..4)]) + | q48 : int(1..4)]), + and([q52 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q52]] + | q52 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set06/expected/model_4_2_3_2-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_4_2_3_2-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_4_2_3_2-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_4_2_3_2-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_4_2_3_2-solution000002.solution new file mode 100644 index 0000000000..85149821f6 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_4_2_3_2-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_4_2_3_2.eprime b/tests/exhaustive/basic/set06/expected/model_4_2_3_2.eprime new file mode 100644 index 0000000000..81418c3d6c --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_4_2_3_2.eprime @@ -0,0 +1,60 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +branching on + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithFlags_Flags, + x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy] +such that + or([x_ExplicitVarSizeWithFlags_Flags[q38] /\ x_ExplicitVarSizeWithFlags_Values[q38] = 1 | q38 : int(1..4)]), + or([x_ExplicitVarSizeWithDummy[q40] != 5 /\ x_ExplicitVarSizeWithDummy[q40] = 2 | q40 : int(1..4)]), + or([q42 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q42] = 3 | q42 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithDummy[q6] < x_ExplicitVarSizeWithDummy[q6 + 1] \/ x_ExplicitVarSizeWithDummy[q6] = 5 + | q6 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q7] = 5 -> x_ExplicitVarSizeWithDummy[q7 + 1] = 5 | q7 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithDummy[q8] != 5) | q8 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithDummy[q11] != 5 -> + or([x_ExplicitVarSizeWithFlags_Flags[q13] /\ + x_ExplicitVarSizeWithFlags_Values[q13] = x_ExplicitVarSizeWithDummy[q11] + | q13 : int(1..4)]) + | q11 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q15] -> + or([x_ExplicitVarSizeWithDummy[q17] != 5 /\ + x_ExplicitVarSizeWithDummy[q17] = x_ExplicitVarSizeWithFlags_Values[q15] + | q17 : int(1..4)]) + | q15 : int(1..4)]), + and([q18 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q18] < x_ExplicitVarSizeWithMarker_Values[q18 + 1] + | q18 : int(1..3)]), + and([q19 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q19] = 1 | q19 : int(1..4)]), + x_ExplicitVarSizeWithMarker_Marker <= 4, + and([q22 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithFlags_Flags[q24] /\ + x_ExplicitVarSizeWithFlags_Values[q24] = x_ExplicitVarSizeWithMarker_Values[q22] + | q24 : int(1..4)]) + | q22 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q26] -> + or([q28 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q28] = x_ExplicitVarSizeWithFlags_Values[q26] + | q28 : int(1..4)]) + | q26 : int(1..4)]), + and([q30 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithDummy[q32] != 5 /\ + x_ExplicitVarSizeWithDummy[q32] = x_ExplicitVarSizeWithMarker_Values[q30] + | q32 : int(1..4)]) + | q30 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q34] != 5 -> + or([q36 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q36] = x_ExplicitVarSizeWithDummy[q34] + | q36 : int(1..4)]) + | q34 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set06/expected/model_4_2_4_1-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_4_2_4_1-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_4_2_4_1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_4_2_4_1-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_4_2_4_1-solution000002.solution new file mode 100644 index 0000000000..85149821f6 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_4_2_4_1-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_4_2_4_1.eprime b/tests/exhaustive/basic/set06/expected/model_4_2_4_1.eprime new file mode 100644 index 0000000000..a14326708e --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_4_2_4_1.eprime @@ -0,0 +1,43 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +find x_Occurrence: matrix indexed by [int(1..4)] of bool +branching on + [x_Occurrence, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy] +such that + or([x_ExplicitVarSizeWithFlags_Flags[q30] /\ x_ExplicitVarSizeWithFlags_Values[q30] = 1 | q30 : int(1..4)]), + or([x_ExplicitVarSizeWithDummy[q32] != 5 /\ x_ExplicitVarSizeWithDummy[q32] = 2 | q32 : int(1..4)]), + or([x_ExplicitVarSizeWithFlags_Flags[q34] /\ x_ExplicitVarSizeWithFlags_Values[q34] = 3 | q34 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithDummy[q6] < x_ExplicitVarSizeWithDummy[q6 + 1] \/ x_ExplicitVarSizeWithDummy[q6] = 5 + | q6 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q7] = 5 -> x_ExplicitVarSizeWithDummy[q7 + 1] = 5 | q7 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithDummy[q8] != 5) | q8 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithDummy[q11] != 5 -> + or([x_ExplicitVarSizeWithFlags_Flags[q13] /\ + x_ExplicitVarSizeWithFlags_Values[q13] = x_ExplicitVarSizeWithDummy[q11] + | q13 : int(1..4)]) + | q11 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q15] -> + or([x_ExplicitVarSizeWithDummy[q17] != 5 /\ + x_ExplicitVarSizeWithDummy[q17] = x_ExplicitVarSizeWithFlags_Values[q15] + | q17 : int(1..4)]) + | q15 : int(1..4)]), + sum([toInt(x_Occurrence[q18]) | q18 : int(1..4)]) <= 4, + and([x_Occurrence[q19] -> + or([x_ExplicitVarSizeWithFlags_Flags[q21] /\ x_ExplicitVarSizeWithFlags_Values[q21] = q19 | q21 : int(1..4)]) + | q19 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q23] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q23]] + | q23 : int(1..4)]), + and([x_Occurrence[q24] -> + or([x_ExplicitVarSizeWithDummy[q26] != 5 /\ x_ExplicitVarSizeWithDummy[q26] = q24 | q26 : int(1..4)]) + | q24 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q28] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q28]] | q28 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set06/expected/model_4_2_4_2-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_4_2_4_2-solution000001.solution new file mode 100644 index 0000000000..85149821f6 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_4_2_4_2-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_4_2_4_2-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_4_2_4_2-solution000002.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_4_2_4_2-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_4_2_4_2.eprime b/tests/exhaustive/basic/set06/expected/model_4_2_4_2.eprime new file mode 100644 index 0000000000..e7dbd3a21e --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_4_2_4_2.eprime @@ -0,0 +1,31 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +branching on [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] +such that + or([x_ExplicitVarSizeWithFlags_Flags[q19] /\ x_ExplicitVarSizeWithFlags_Values[q19] = 1 | q19 : int(1..4)]), + or([x_ExplicitVarSizeWithDummy[q21] != 5 /\ x_ExplicitVarSizeWithDummy[q21] = 2 | q21 : int(1..4)]), + or([x_ExplicitVarSizeWithFlags_Flags[q23] /\ x_ExplicitVarSizeWithFlags_Values[q23] = 3 | q23 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithDummy[q6] < x_ExplicitVarSizeWithDummy[q6 + 1] \/ x_ExplicitVarSizeWithDummy[q6] = 5 + | q6 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q7] = 5 -> x_ExplicitVarSizeWithDummy[q7 + 1] = 5 | q7 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithDummy[q8] != 5) | q8 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithDummy[q11] != 5 -> + or([x_ExplicitVarSizeWithFlags_Flags[q13] /\ + x_ExplicitVarSizeWithFlags_Values[q13] = x_ExplicitVarSizeWithDummy[q11] + | q13 : int(1..4)]) + | q11 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q15] -> + or([x_ExplicitVarSizeWithDummy[q17] != 5 /\ + x_ExplicitVarSizeWithDummy[q17] = x_ExplicitVarSizeWithFlags_Values[q15] + | q17 : int(1..4)]) + | q15 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set06/expected/model_4_2_4_3-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_4_2_4_3-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_4_2_4_3-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_4_2_4_3-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_4_2_4_3-solution000002.solution new file mode 100644 index 0000000000..85149821f6 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_4_2_4_3-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_4_2_4_3.eprime b/tests/exhaustive/basic/set06/expected/model_4_2_4_3.eprime new file mode 100644 index 0000000000..148d795f19 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_4_2_4_3.eprime @@ -0,0 +1,60 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +branching on + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithFlags_Flags, + x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy] +such that + or([x_ExplicitVarSizeWithFlags_Flags[q38] /\ x_ExplicitVarSizeWithFlags_Values[q38] = 1 | q38 : int(1..4)]), + or([x_ExplicitVarSizeWithDummy[q40] != 5 /\ x_ExplicitVarSizeWithDummy[q40] = 2 | q40 : int(1..4)]), + or([x_ExplicitVarSizeWithFlags_Flags[q42] /\ x_ExplicitVarSizeWithFlags_Values[q42] = 3 | q42 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithDummy[q6] < x_ExplicitVarSizeWithDummy[q6 + 1] \/ x_ExplicitVarSizeWithDummy[q6] = 5 + | q6 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q7] = 5 -> x_ExplicitVarSizeWithDummy[q7 + 1] = 5 | q7 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithDummy[q8] != 5) | q8 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithDummy[q11] != 5 -> + or([x_ExplicitVarSizeWithFlags_Flags[q13] /\ + x_ExplicitVarSizeWithFlags_Values[q13] = x_ExplicitVarSizeWithDummy[q11] + | q13 : int(1..4)]) + | q11 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q15] -> + or([x_ExplicitVarSizeWithDummy[q17] != 5 /\ + x_ExplicitVarSizeWithDummy[q17] = x_ExplicitVarSizeWithFlags_Values[q15] + | q17 : int(1..4)]) + | q15 : int(1..4)]), + and([q18 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q18] < x_ExplicitVarSizeWithMarker_Values[q18 + 1] + | q18 : int(1..3)]), + and([q19 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q19] = 1 | q19 : int(1..4)]), + x_ExplicitVarSizeWithMarker_Marker <= 4, + and([q22 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithFlags_Flags[q24] /\ + x_ExplicitVarSizeWithFlags_Values[q24] = x_ExplicitVarSizeWithMarker_Values[q22] + | q24 : int(1..4)]) + | q22 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q26] -> + or([q28 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q28] = x_ExplicitVarSizeWithFlags_Values[q26] + | q28 : int(1..4)]) + | q26 : int(1..4)]), + and([q30 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithDummy[q32] != 5 /\ + x_ExplicitVarSizeWithDummy[q32] = x_ExplicitVarSizeWithMarker_Values[q30] + | q32 : int(1..4)]) + | q30 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q34] != 5 -> + or([q36 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q36] = x_ExplicitVarSizeWithDummy[q34] + | q36 : int(1..4)]) + | q34 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set06/expected/model_4_3_1_1-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_4_3_1_1-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_4_3_1_1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_4_3_1_1-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_4_3_1_1-solution000002.solution new file mode 100644 index 0000000000..85149821f6 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_4_3_1_1-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_4_3_1_1.eprime b/tests/exhaustive/basic/set06/expected/model_4_3_1_1.eprime new file mode 100644 index 0000000000..ac596bf128 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_4_3_1_1.eprime @@ -0,0 +1,48 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_Occurrence: matrix indexed by [int(1..4)] of bool +branching on + [x_Occurrence, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, + x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] +such that + or([x_ExplicitVarSizeWithFlags_Flags[q29] /\ x_ExplicitVarSizeWithFlags_Values[q29] = 1 | q29 : int(1..4)]), + or([q31 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q31] = 2 | q31 : int(1..4)]), + x_Occurrence[3], + and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]) <= 4, + and([q6 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q6] < x_ExplicitVarSizeWithMarker_Values[q6 + 1] + | q6 : int(1..3)]), + and([q7 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q7] = 1 | q7 : int(1..4)]), + x_ExplicitVarSizeWithMarker_Marker <= 4, + and([q10 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithFlags_Flags[q12] /\ + x_ExplicitVarSizeWithFlags_Values[q12] = x_ExplicitVarSizeWithMarker_Values[q10] + | q12 : int(1..4)]) + | q10 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q14] -> + or([q16 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q16] = x_ExplicitVarSizeWithFlags_Values[q14] + | q16 : int(1..4)]) + | q14 : int(1..4)]), + sum([toInt(x_Occurrence[q17]) | q17 : int(1..4)]) <= 4, + and([x_Occurrence[q18] -> + or([x_ExplicitVarSizeWithFlags_Flags[q20] /\ x_ExplicitVarSizeWithFlags_Values[q20] = q18 | q20 : int(1..4)]) + | q18 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q22] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q22]] + | q22 : int(1..4)]), + and([x_Occurrence[q23] -> + or([q25 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q25] = q23 + | q25 : int(1..4)]) + | q23 : int(1..4)]), + and([q27 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q27]] + | q27 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set06/expected/model_4_3_1_2-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_4_3_1_2-solution000001.solution new file mode 100644 index 0000000000..85149821f6 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_4_3_1_2-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_4_3_1_2-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_4_3_1_2-solution000002.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_4_3_1_2-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_4_3_1_2.eprime b/tests/exhaustive/basic/set06/expected/model_4_3_1_2.eprime new file mode 100644 index 0000000000..17571cdb85 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_4_3_1_2.eprime @@ -0,0 +1,77 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_Occurrence: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +branching on + [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, + x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_Occurrence] +such that + or([x_ExplicitVarSizeWithFlags_Flags[q54] /\ x_ExplicitVarSizeWithFlags_Values[q54] = 1 | q54 : int(1..4)]), + or([q56 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q56] = 2 | q56 : int(1..4)]), + x_Occurrence[3], + and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]) <= 4, + and([q6 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q6] < x_ExplicitVarSizeWithMarker_Values[q6 + 1] + | q6 : int(1..3)]), + and([q7 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q7] = 1 | q7 : int(1..4)]), + x_ExplicitVarSizeWithMarker_Marker <= 4, + and([q10 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithFlags_Flags[q12] /\ + x_ExplicitVarSizeWithFlags_Values[q12] = x_ExplicitVarSizeWithMarker_Values[q10] + | q12 : int(1..4)]) + | q10 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q14] -> + or([q16 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q16] = x_ExplicitVarSizeWithFlags_Values[q14] + | q16 : int(1..4)]) + | q14 : int(1..4)]), + sum([toInt(x_Occurrence[q17]) | q17 : int(1..4)]) <= 4, + and([x_Occurrence[q43] -> + or([x_ExplicitVarSizeWithFlags_Flags[q45] /\ x_ExplicitVarSizeWithFlags_Values[q45] = q43 | q45 : int(1..4)]) + | q43 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q47] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q47]] + | q47 : int(1..4)]), + and([x_Occurrence[q48] -> + or([q50 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q50] = q48 + | q50 : int(1..4)]) + | q48 : int(1..4)]), + and([q52 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q52]] + | q52 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q18] < x_ExplicitVarSizeWithDummy[q18 + 1] \/ x_ExplicitVarSizeWithDummy[q18] = 5 + | q18 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q19] = 5 -> x_ExplicitVarSizeWithDummy[q19 + 1] = 5 | q19 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithDummy[q20] != 5) | q20 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithDummy[q23] != 5 -> + or([x_ExplicitVarSizeWithFlags_Flags[q25] /\ + x_ExplicitVarSizeWithFlags_Values[q25] = x_ExplicitVarSizeWithDummy[q23] + | q25 : int(1..4)]) + | q23 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q27] -> + or([x_ExplicitVarSizeWithDummy[q29] != 5 /\ + x_ExplicitVarSizeWithDummy[q29] = x_ExplicitVarSizeWithFlags_Values[q27] + | q29 : int(1..4)]) + | q27 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q31] != 5 -> + or([q33 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q33] = x_ExplicitVarSizeWithDummy[q31] + | q33 : int(1..4)]) + | q31 : int(1..4)]), + and([q35 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithDummy[q37] != 5 /\ + x_ExplicitVarSizeWithDummy[q37] = x_ExplicitVarSizeWithMarker_Values[q35] + | q37 : int(1..4)]) + | q35 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q39] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q39]] | q39 : int(1..4)]), + and([x_Occurrence[q40] -> + or([x_ExplicitVarSizeWithDummy[q42] != 5 /\ x_ExplicitVarSizeWithDummy[q42] = q40 | q42 : int(1..4)]) + | q40 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set06/expected/model_4_3_2_1-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_4_3_2_1-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_4_3_2_1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_4_3_2_1-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_4_3_2_1-solution000002.solution new file mode 100644 index 0000000000..85149821f6 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_4_3_2_1-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_4_3_2_1.eprime b/tests/exhaustive/basic/set06/expected/model_4_3_2_1.eprime new file mode 100644 index 0000000000..5b1aff728e --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_4_3_2_1.eprime @@ -0,0 +1,77 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +find x_Occurrence: matrix indexed by [int(1..4)] of bool +branching on + [x_Occurrence, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, + x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy] +such that + or([x_ExplicitVarSizeWithFlags_Flags[q54] /\ x_ExplicitVarSizeWithFlags_Values[q54] = 1 | q54 : int(1..4)]), + or([q56 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q56] = 2 | q56 : int(1..4)]), + or([x_ExplicitVarSizeWithDummy[q58] != 5 /\ x_ExplicitVarSizeWithDummy[q58] = 3 | q58 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]) <= 4, + and([q6 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q6] < x_ExplicitVarSizeWithMarker_Values[q6 + 1] + | q6 : int(1..3)]), + and([q7 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q7] = 1 | q7 : int(1..4)]), + x_ExplicitVarSizeWithMarker_Marker <= 4, + and([q10 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithFlags_Flags[q12] /\ + x_ExplicitVarSizeWithFlags_Values[q12] = x_ExplicitVarSizeWithMarker_Values[q10] + | q12 : int(1..4)]) + | q10 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q14] -> + or([q16 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q16] = x_ExplicitVarSizeWithFlags_Values[q14] + | q16 : int(1..4)]) + | q14 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q17] < x_ExplicitVarSizeWithDummy[q17 + 1] \/ x_ExplicitVarSizeWithDummy[q17] = 5 + | q17 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q18] = 5 -> x_ExplicitVarSizeWithDummy[q18 + 1] = 5 | q18 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithDummy[q19] != 5) | q19 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithDummy[q22] != 5 -> + or([x_ExplicitVarSizeWithFlags_Flags[q24] /\ + x_ExplicitVarSizeWithFlags_Values[q24] = x_ExplicitVarSizeWithDummy[q22] + | q24 : int(1..4)]) + | q22 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q26] -> + or([x_ExplicitVarSizeWithDummy[q28] != 5 /\ + x_ExplicitVarSizeWithDummy[q28] = x_ExplicitVarSizeWithFlags_Values[q26] + | q28 : int(1..4)]) + | q26 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q30] != 5 -> + or([q32 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q32] = x_ExplicitVarSizeWithDummy[q30] + | q32 : int(1..4)]) + | q30 : int(1..4)]), + and([q34 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithDummy[q36] != 5 /\ + x_ExplicitVarSizeWithDummy[q36] = x_ExplicitVarSizeWithMarker_Values[q34] + | q36 : int(1..4)]) + | q34 : int(1..4)]), + sum([toInt(x_Occurrence[q37]) | q37 : int(1..4)]) <= 4, + and([x_Occurrence[q38] -> + or([x_ExplicitVarSizeWithFlags_Flags[q40] /\ x_ExplicitVarSizeWithFlags_Values[q40] = q38 | q40 : int(1..4)]) + | q38 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q42] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q42]] + | q42 : int(1..4)]), + and([x_Occurrence[q43] -> + or([q45 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q45] = q43 + | q45 : int(1..4)]) + | q43 : int(1..4)]), + and([q47 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q47]] + | q47 : int(1..4)]), + and([x_Occurrence[q48] -> + or([x_ExplicitVarSizeWithDummy[q50] != 5 /\ x_ExplicitVarSizeWithDummy[q50] = q48 | q50 : int(1..4)]) + | q48 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q52] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q52]] | q52 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set06/expected/model_4_3_2_2-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_4_3_2_2-solution000001.solution new file mode 100644 index 0000000000..85149821f6 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_4_3_2_2-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_4_3_2_2-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_4_3_2_2-solution000002.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_4_3_2_2-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_4_3_2_2.eprime b/tests/exhaustive/basic/set06/expected/model_4_3_2_2.eprime new file mode 100644 index 0000000000..76550b1cd1 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_4_3_2_2.eprime @@ -0,0 +1,60 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +branching on + [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, + x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] +such that + or([x_ExplicitVarSizeWithFlags_Flags[q38] /\ x_ExplicitVarSizeWithFlags_Values[q38] = 1 | q38 : int(1..4)]), + or([q40 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q40] = 2 | q40 : int(1..4)]), + or([x_ExplicitVarSizeWithDummy[q42] != 5 /\ x_ExplicitVarSizeWithDummy[q42] = 3 | q42 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]) <= 4, + and([q6 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q6] < x_ExplicitVarSizeWithMarker_Values[q6 + 1] + | q6 : int(1..3)]), + and([q7 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q7] = 1 | q7 : int(1..4)]), + x_ExplicitVarSizeWithMarker_Marker <= 4, + and([q10 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithFlags_Flags[q12] /\ + x_ExplicitVarSizeWithFlags_Values[q12] = x_ExplicitVarSizeWithMarker_Values[q10] + | q12 : int(1..4)]) + | q10 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q14] -> + or([q16 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q16] = x_ExplicitVarSizeWithFlags_Values[q14] + | q16 : int(1..4)]) + | q14 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q17] < x_ExplicitVarSizeWithDummy[q17 + 1] \/ x_ExplicitVarSizeWithDummy[q17] = 5 + | q17 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q18] = 5 -> x_ExplicitVarSizeWithDummy[q18 + 1] = 5 | q18 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithDummy[q19] != 5) | q19 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithDummy[q22] != 5 -> + or([x_ExplicitVarSizeWithFlags_Flags[q24] /\ + x_ExplicitVarSizeWithFlags_Values[q24] = x_ExplicitVarSizeWithDummy[q22] + | q24 : int(1..4)]) + | q22 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q26] -> + or([x_ExplicitVarSizeWithDummy[q28] != 5 /\ + x_ExplicitVarSizeWithDummy[q28] = x_ExplicitVarSizeWithFlags_Values[q26] + | q28 : int(1..4)]) + | q26 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q30] != 5 -> + or([q32 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q32] = x_ExplicitVarSizeWithDummy[q30] + | q32 : int(1..4)]) + | q30 : int(1..4)]), + and([q34 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithDummy[q36] != 5 /\ + x_ExplicitVarSizeWithDummy[q36] = x_ExplicitVarSizeWithMarker_Values[q34] + | q36 : int(1..4)]) + | q34 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set06/expected/model_4_3_3_1-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_4_3_3_1-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_4_3_3_1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_4_3_3_1-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_4_3_3_1-solution000002.solution new file mode 100644 index 0000000000..85149821f6 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_4_3_3_1-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_4_3_3_1.eprime b/tests/exhaustive/basic/set06/expected/model_4_3_3_1.eprime new file mode 100644 index 0000000000..9a58f97a9b --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_4_3_3_1.eprime @@ -0,0 +1,48 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_Occurrence: matrix indexed by [int(1..4)] of bool +branching on + [x_Occurrence, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, + x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] +such that + or([x_ExplicitVarSizeWithFlags_Flags[q29] /\ x_ExplicitVarSizeWithFlags_Values[q29] = 1 | q29 : int(1..4)]), + or([q31 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q31] = 2 | q31 : int(1..4)]), + or([q33 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q33] = 3 | q33 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]) <= 4, + and([q6 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q6] < x_ExplicitVarSizeWithMarker_Values[q6 + 1] + | q6 : int(1..3)]), + and([q7 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q7] = 1 | q7 : int(1..4)]), + x_ExplicitVarSizeWithMarker_Marker <= 4, + and([q10 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithFlags_Flags[q12] /\ + x_ExplicitVarSizeWithFlags_Values[q12] = x_ExplicitVarSizeWithMarker_Values[q10] + | q12 : int(1..4)]) + | q10 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q14] -> + or([q16 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q16] = x_ExplicitVarSizeWithFlags_Values[q14] + | q16 : int(1..4)]) + | q14 : int(1..4)]), + sum([toInt(x_Occurrence[q17]) | q17 : int(1..4)]) <= 4, + and([x_Occurrence[q18] -> + or([x_ExplicitVarSizeWithFlags_Flags[q20] /\ x_ExplicitVarSizeWithFlags_Values[q20] = q18 | q20 : int(1..4)]) + | q18 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q22] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q22]] + | q22 : int(1..4)]), + and([x_Occurrence[q23] -> + or([q25 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q25] = q23 + | q25 : int(1..4)]) + | q23 : int(1..4)]), + and([q27 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q27]] + | q27 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set06/expected/model_4_3_3_2-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_4_3_3_2-solution000001.solution new file mode 100644 index 0000000000..85149821f6 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_4_3_3_2-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_4_3_3_2-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_4_3_3_2-solution000002.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_4_3_3_2-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_4_3_3_2.eprime b/tests/exhaustive/basic/set06/expected/model_4_3_3_2.eprime new file mode 100644 index 0000000000..f359e7ac0b --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_4_3_3_2.eprime @@ -0,0 +1,60 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +branching on + [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, + x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] +such that + or([x_ExplicitVarSizeWithFlags_Flags[q38] /\ x_ExplicitVarSizeWithFlags_Values[q38] = 1 | q38 : int(1..4)]), + or([q40 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q40] = 2 | q40 : int(1..4)]), + or([q42 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q42] = 3 | q42 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]) <= 4, + and([q6 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q6] < x_ExplicitVarSizeWithMarker_Values[q6 + 1] + | q6 : int(1..3)]), + and([q7 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q7] = 1 | q7 : int(1..4)]), + x_ExplicitVarSizeWithMarker_Marker <= 4, + and([q10 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithFlags_Flags[q12] /\ + x_ExplicitVarSizeWithFlags_Values[q12] = x_ExplicitVarSizeWithMarker_Values[q10] + | q12 : int(1..4)]) + | q10 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q14] -> + or([q16 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q16] = x_ExplicitVarSizeWithFlags_Values[q14] + | q16 : int(1..4)]) + | q14 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q17] < x_ExplicitVarSizeWithDummy[q17 + 1] \/ x_ExplicitVarSizeWithDummy[q17] = 5 + | q17 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q18] = 5 -> x_ExplicitVarSizeWithDummy[q18 + 1] = 5 | q18 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithDummy[q19] != 5) | q19 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithDummy[q22] != 5 -> + or([x_ExplicitVarSizeWithFlags_Flags[q24] /\ + x_ExplicitVarSizeWithFlags_Values[q24] = x_ExplicitVarSizeWithDummy[q22] + | q24 : int(1..4)]) + | q22 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q26] -> + or([x_ExplicitVarSizeWithDummy[q28] != 5 /\ + x_ExplicitVarSizeWithDummy[q28] = x_ExplicitVarSizeWithFlags_Values[q26] + | q28 : int(1..4)]) + | q26 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q30] != 5 -> + or([q32 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q32] = x_ExplicitVarSizeWithDummy[q30] + | q32 : int(1..4)]) + | q30 : int(1..4)]), + and([q34 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithDummy[q36] != 5 /\ + x_ExplicitVarSizeWithDummy[q36] = x_ExplicitVarSizeWithMarker_Values[q34] + | q36 : int(1..4)]) + | q34 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set06/expected/model_4_3_3_3-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_4_3_3_3-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_4_3_3_3-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_4_3_3_3-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_4_3_3_3-solution000002.solution new file mode 100644 index 0000000000..85149821f6 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_4_3_3_3-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_4_3_3_3.eprime b/tests/exhaustive/basic/set06/expected/model_4_3_3_3.eprime new file mode 100644 index 0000000000..aac2bf1a2e --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_4_3_3_3.eprime @@ -0,0 +1,35 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +branching on + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithFlags_Flags, + x_ExplicitVarSizeWithFlags_Values] +such that + or([x_ExplicitVarSizeWithFlags_Flags[q18] /\ x_ExplicitVarSizeWithFlags_Values[q18] = 1 | q18 : int(1..4)]), + or([q20 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q20] = 2 | q20 : int(1..4)]), + or([q22 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q22] = 3 | q22 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]) <= 4, + and([q6 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q6] < x_ExplicitVarSizeWithMarker_Values[q6 + 1] + | q6 : int(1..3)]), + and([q7 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q7] = 1 | q7 : int(1..4)]), + x_ExplicitVarSizeWithMarker_Marker <= 4, + and([q10 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithFlags_Flags[q12] /\ + x_ExplicitVarSizeWithFlags_Values[q12] = x_ExplicitVarSizeWithMarker_Values[q10] + | q12 : int(1..4)]) + | q10 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q14] -> + or([q16 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q16] = x_ExplicitVarSizeWithFlags_Values[q14] + | q16 : int(1..4)]) + | q14 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set06/expected/model_4_3_4_1-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_4_3_4_1-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_4_3_4_1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_4_3_4_1-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_4_3_4_1-solution000002.solution new file mode 100644 index 0000000000..85149821f6 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_4_3_4_1-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_4_3_4_1.eprime b/tests/exhaustive/basic/set06/expected/model_4_3_4_1.eprime new file mode 100644 index 0000000000..42f3b460a6 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_4_3_4_1.eprime @@ -0,0 +1,48 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_Occurrence: matrix indexed by [int(1..4)] of bool +branching on + [x_Occurrence, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, + x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] +such that + or([x_ExplicitVarSizeWithFlags_Flags[q29] /\ x_ExplicitVarSizeWithFlags_Values[q29] = 1 | q29 : int(1..4)]), + or([q31 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q31] = 2 | q31 : int(1..4)]), + or([x_ExplicitVarSizeWithFlags_Flags[q33] /\ x_ExplicitVarSizeWithFlags_Values[q33] = 3 | q33 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]) <= 4, + and([q6 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q6] < x_ExplicitVarSizeWithMarker_Values[q6 + 1] + | q6 : int(1..3)]), + and([q7 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q7] = 1 | q7 : int(1..4)]), + x_ExplicitVarSizeWithMarker_Marker <= 4, + and([q10 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithFlags_Flags[q12] /\ + x_ExplicitVarSizeWithFlags_Values[q12] = x_ExplicitVarSizeWithMarker_Values[q10] + | q12 : int(1..4)]) + | q10 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q14] -> + or([q16 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q16] = x_ExplicitVarSizeWithFlags_Values[q14] + | q16 : int(1..4)]) + | q14 : int(1..4)]), + sum([toInt(x_Occurrence[q17]) | q17 : int(1..4)]) <= 4, + and([x_Occurrence[q18] -> + or([x_ExplicitVarSizeWithFlags_Flags[q20] /\ x_ExplicitVarSizeWithFlags_Values[q20] = q18 | q20 : int(1..4)]) + | q18 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q22] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q22]] + | q22 : int(1..4)]), + and([x_Occurrence[q23] -> + or([q25 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q25] = q23 + | q25 : int(1..4)]) + | q23 : int(1..4)]), + and([q27 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q27]] + | q27 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set06/expected/model_4_3_4_2-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_4_3_4_2-solution000001.solution new file mode 100644 index 0000000000..85149821f6 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_4_3_4_2-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_4_3_4_2-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_4_3_4_2-solution000002.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_4_3_4_2-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_4_3_4_2.eprime b/tests/exhaustive/basic/set06/expected/model_4_3_4_2.eprime new file mode 100644 index 0000000000..215f736030 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_4_3_4_2.eprime @@ -0,0 +1,60 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +branching on + [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, + x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] +such that + or([x_ExplicitVarSizeWithFlags_Flags[q38] /\ x_ExplicitVarSizeWithFlags_Values[q38] = 1 | q38 : int(1..4)]), + or([q40 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q40] = 2 | q40 : int(1..4)]), + or([x_ExplicitVarSizeWithFlags_Flags[q42] /\ x_ExplicitVarSizeWithFlags_Values[q42] = 3 | q42 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]) <= 4, + and([q6 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q6] < x_ExplicitVarSizeWithMarker_Values[q6 + 1] + | q6 : int(1..3)]), + and([q7 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q7] = 1 | q7 : int(1..4)]), + x_ExplicitVarSizeWithMarker_Marker <= 4, + and([q10 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithFlags_Flags[q12] /\ + x_ExplicitVarSizeWithFlags_Values[q12] = x_ExplicitVarSizeWithMarker_Values[q10] + | q12 : int(1..4)]) + | q10 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q14] -> + or([q16 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q16] = x_ExplicitVarSizeWithFlags_Values[q14] + | q16 : int(1..4)]) + | q14 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q17] < x_ExplicitVarSizeWithDummy[q17 + 1] \/ x_ExplicitVarSizeWithDummy[q17] = 5 + | q17 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q18] = 5 -> x_ExplicitVarSizeWithDummy[q18 + 1] = 5 | q18 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithDummy[q19] != 5) | q19 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithDummy[q22] != 5 -> + or([x_ExplicitVarSizeWithFlags_Flags[q24] /\ + x_ExplicitVarSizeWithFlags_Values[q24] = x_ExplicitVarSizeWithDummy[q22] + | q24 : int(1..4)]) + | q22 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q26] -> + or([x_ExplicitVarSizeWithDummy[q28] != 5 /\ + x_ExplicitVarSizeWithDummy[q28] = x_ExplicitVarSizeWithFlags_Values[q26] + | q28 : int(1..4)]) + | q26 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q30] != 5 -> + or([q32 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q32] = x_ExplicitVarSizeWithDummy[q30] + | q32 : int(1..4)]) + | q30 : int(1..4)]), + and([q34 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithDummy[q36] != 5 /\ + x_ExplicitVarSizeWithDummy[q36] = x_ExplicitVarSizeWithMarker_Values[q34] + | q36 : int(1..4)]) + | q34 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set06/expected/model_4_3_4_3-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_4_3_4_3-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_4_3_4_3-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_4_3_4_3-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_4_3_4_3-solution000002.solution new file mode 100644 index 0000000000..85149821f6 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_4_3_4_3-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_4_3_4_3.eprime b/tests/exhaustive/basic/set06/expected/model_4_3_4_3.eprime new file mode 100644 index 0000000000..f84e5ef823 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_4_3_4_3.eprime @@ -0,0 +1,35 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +branching on + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithFlags_Flags, + x_ExplicitVarSizeWithFlags_Values] +such that + or([x_ExplicitVarSizeWithFlags_Flags[q18] /\ x_ExplicitVarSizeWithFlags_Values[q18] = 1 | q18 : int(1..4)]), + or([q20 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q20] = 2 | q20 : int(1..4)]), + or([x_ExplicitVarSizeWithFlags_Flags[q22] /\ x_ExplicitVarSizeWithFlags_Values[q22] = 3 | q22 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]) <= 4, + and([q6 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q6] < x_ExplicitVarSizeWithMarker_Values[q6 + 1] + | q6 : int(1..3)]), + and([q7 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q7] = 1 | q7 : int(1..4)]), + x_ExplicitVarSizeWithMarker_Marker <= 4, + and([q10 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithFlags_Flags[q12] /\ + x_ExplicitVarSizeWithFlags_Values[q12] = x_ExplicitVarSizeWithMarker_Values[q10] + | q12 : int(1..4)]) + | q10 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q14] -> + or([q16 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q16] = x_ExplicitVarSizeWithFlags_Values[q14] + | q16 : int(1..4)]) + | q14 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set06/expected/model_4_4_1_1-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_4_4_1_1-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_4_4_1_1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_4_4_1_1-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_4_4_1_1-solution000002.solution new file mode 100644 index 0000000000..85149821f6 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_4_4_1_1-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_4_4_1_1.eprime b/tests/exhaustive/basic/set06/expected/model_4_4_1_1.eprime new file mode 100644 index 0000000000..89df5f9b59 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_4_4_1_1.eprime @@ -0,0 +1,23 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_Occurrence: matrix indexed by [int(1..4)] of bool +branching on [x_Occurrence, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] +such that + or([x_ExplicitVarSizeWithFlags_Flags[q13] /\ x_ExplicitVarSizeWithFlags_Values[q13] = 1 | q13 : int(1..4)]), + or([x_ExplicitVarSizeWithFlags_Flags[q15] /\ x_ExplicitVarSizeWithFlags_Values[q15] = 2 | q15 : int(1..4)]), + x_Occurrence[3], + and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]) <= 4, + sum([toInt(x_Occurrence[q6]) | q6 : int(1..4)]) <= 4, + and([x_Occurrence[q7] -> + or([x_ExplicitVarSizeWithFlags_Flags[q9] /\ x_ExplicitVarSizeWithFlags_Values[q9] = q7 | q9 : int(1..4)]) + | q7 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q11] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q11]] + | q11 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set06/expected/model_4_4_1_2-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_4_4_1_2-solution000001.solution new file mode 100644 index 0000000000..85149821f6 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_4_4_1_2-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_4_4_1_2-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_4_4_1_2-solution000002.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_4_4_1_2-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_4_4_1_2.eprime b/tests/exhaustive/basic/set06/expected/model_4_4_1_2.eprime new file mode 100644 index 0000000000..fb935649b7 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_4_4_1_2.eprime @@ -0,0 +1,43 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_Occurrence: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +branching on + [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_Occurrence] +such that + or([x_ExplicitVarSizeWithFlags_Flags[q30] /\ x_ExplicitVarSizeWithFlags_Values[q30] = 1 | q30 : int(1..4)]), + or([x_ExplicitVarSizeWithFlags_Flags[q32] /\ x_ExplicitVarSizeWithFlags_Values[q32] = 2 | q32 : int(1..4)]), + x_Occurrence[3], + and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]) <= 4, + sum([toInt(x_Occurrence[q6]) | q6 : int(1..4)]) <= 4, + and([x_Occurrence[q24] -> + or([x_ExplicitVarSizeWithFlags_Flags[q26] /\ x_ExplicitVarSizeWithFlags_Values[q26] = q24 | q26 : int(1..4)]) + | q24 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q28] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q28]] + | q28 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q7] < x_ExplicitVarSizeWithDummy[q7 + 1] \/ x_ExplicitVarSizeWithDummy[q7] = 5 + | q7 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q8] = 5 -> x_ExplicitVarSizeWithDummy[q8 + 1] = 5 | q8 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithDummy[q9] != 5) | q9 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithDummy[q12] != 5 -> + or([x_ExplicitVarSizeWithFlags_Flags[q14] /\ + x_ExplicitVarSizeWithFlags_Values[q14] = x_ExplicitVarSizeWithDummy[q12] + | q14 : int(1..4)]) + | q12 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q16] -> + or([x_ExplicitVarSizeWithDummy[q18] != 5 /\ + x_ExplicitVarSizeWithDummy[q18] = x_ExplicitVarSizeWithFlags_Values[q16] + | q18 : int(1..4)]) + | q16 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q20] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q20]] | q20 : int(1..4)]), + and([x_Occurrence[q21] -> + or([x_ExplicitVarSizeWithDummy[q23] != 5 /\ x_ExplicitVarSizeWithDummy[q23] = q21 | q23 : int(1..4)]) + | q21 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set06/expected/model_4_4_1_3-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_4_4_1_3-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_4_4_1_3-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_4_4_1_3-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_4_4_1_3-solution000002.solution new file mode 100644 index 0000000000..85149821f6 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_4_4_1_3-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_4_4_1_3.eprime b/tests/exhaustive/basic/set06/expected/model_4_4_1_3.eprime new file mode 100644 index 0000000000..188765c81e --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_4_4_1_3.eprime @@ -0,0 +1,48 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_Occurrence: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +branching on + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithFlags_Flags, + x_ExplicitVarSizeWithFlags_Values, x_Occurrence] +such that + or([x_ExplicitVarSizeWithFlags_Flags[q29] /\ x_ExplicitVarSizeWithFlags_Values[q29] = 1 | q29 : int(1..4)]), + or([x_ExplicitVarSizeWithFlags_Flags[q31] /\ x_ExplicitVarSizeWithFlags_Values[q31] = 2 | q31 : int(1..4)]), + x_Occurrence[3], + and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]) <= 4, + sum([toInt(x_Occurrence[q6]) | q6 : int(1..4)]) <= 4, + and([x_Occurrence[q23] -> + or([x_ExplicitVarSizeWithFlags_Flags[q25] /\ x_ExplicitVarSizeWithFlags_Values[q25] = q23 | q25 : int(1..4)]) + | q23 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q27] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q27]] + | q27 : int(1..4)]), + and([q7 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q7] < x_ExplicitVarSizeWithMarker_Values[q7 + 1] + | q7 : int(1..3)]), + and([q8 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q8] = 1 | q8 : int(1..4)]), + x_ExplicitVarSizeWithMarker_Marker <= 4, + and([q11 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithFlags_Flags[q13] /\ + x_ExplicitVarSizeWithFlags_Values[q13] = x_ExplicitVarSizeWithMarker_Values[q11] + | q13 : int(1..4)]) + | q11 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q15] -> + or([q17 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q17] = x_ExplicitVarSizeWithFlags_Values[q15] + | q17 : int(1..4)]) + | q15 : int(1..4)]), + and([q19 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q19]] + | q19 : int(1..4)]), + and([x_Occurrence[q20] -> + or([q22 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q22] = q20 + | q22 : int(1..4)]) + | q20 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set06/expected/model_4_4_2_1-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_4_4_2_1-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_4_4_2_1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_4_4_2_1-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_4_4_2_1-solution000002.solution new file mode 100644 index 0000000000..85149821f6 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_4_4_2_1-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_4_4_2_1.eprime b/tests/exhaustive/basic/set06/expected/model_4_4_2_1.eprime new file mode 100644 index 0000000000..5efd46fc5d --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_4_4_2_1.eprime @@ -0,0 +1,43 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +find x_Occurrence: matrix indexed by [int(1..4)] of bool +branching on + [x_Occurrence, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy] +such that + or([x_ExplicitVarSizeWithFlags_Flags[q30] /\ x_ExplicitVarSizeWithFlags_Values[q30] = 1 | q30 : int(1..4)]), + or([x_ExplicitVarSizeWithFlags_Flags[q32] /\ x_ExplicitVarSizeWithFlags_Values[q32] = 2 | q32 : int(1..4)]), + or([x_ExplicitVarSizeWithDummy[q34] != 5 /\ x_ExplicitVarSizeWithDummy[q34] = 3 | q34 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithDummy[q6] < x_ExplicitVarSizeWithDummy[q6 + 1] \/ x_ExplicitVarSizeWithDummy[q6] = 5 + | q6 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q7] = 5 -> x_ExplicitVarSizeWithDummy[q7 + 1] = 5 | q7 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithDummy[q8] != 5) | q8 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithDummy[q11] != 5 -> + or([x_ExplicitVarSizeWithFlags_Flags[q13] /\ + x_ExplicitVarSizeWithFlags_Values[q13] = x_ExplicitVarSizeWithDummy[q11] + | q13 : int(1..4)]) + | q11 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q15] -> + or([x_ExplicitVarSizeWithDummy[q17] != 5 /\ + x_ExplicitVarSizeWithDummy[q17] = x_ExplicitVarSizeWithFlags_Values[q15] + | q17 : int(1..4)]) + | q15 : int(1..4)]), + sum([toInt(x_Occurrence[q18]) | q18 : int(1..4)]) <= 4, + and([x_Occurrence[q19] -> + or([x_ExplicitVarSizeWithFlags_Flags[q21] /\ x_ExplicitVarSizeWithFlags_Values[q21] = q19 | q21 : int(1..4)]) + | q19 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q23] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q23]] + | q23 : int(1..4)]), + and([x_Occurrence[q24] -> + or([x_ExplicitVarSizeWithDummy[q26] != 5 /\ x_ExplicitVarSizeWithDummy[q26] = q24 | q26 : int(1..4)]) + | q24 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q28] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q28]] | q28 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set06/expected/model_4_4_2_2-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_4_4_2_2-solution000001.solution new file mode 100644 index 0000000000..85149821f6 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_4_4_2_2-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_4_4_2_2-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_4_4_2_2-solution000002.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_4_4_2_2-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_4_4_2_2.eprime b/tests/exhaustive/basic/set06/expected/model_4_4_2_2.eprime new file mode 100644 index 0000000000..0fa0747d3f --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_4_4_2_2.eprime @@ -0,0 +1,31 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +branching on [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] +such that + or([x_ExplicitVarSizeWithFlags_Flags[q19] /\ x_ExplicitVarSizeWithFlags_Values[q19] = 1 | q19 : int(1..4)]), + or([x_ExplicitVarSizeWithFlags_Flags[q21] /\ x_ExplicitVarSizeWithFlags_Values[q21] = 2 | q21 : int(1..4)]), + or([x_ExplicitVarSizeWithDummy[q23] != 5 /\ x_ExplicitVarSizeWithDummy[q23] = 3 | q23 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithDummy[q6] < x_ExplicitVarSizeWithDummy[q6 + 1] \/ x_ExplicitVarSizeWithDummy[q6] = 5 + | q6 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q7] = 5 -> x_ExplicitVarSizeWithDummy[q7 + 1] = 5 | q7 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithDummy[q8] != 5) | q8 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithDummy[q11] != 5 -> + or([x_ExplicitVarSizeWithFlags_Flags[q13] /\ + x_ExplicitVarSizeWithFlags_Values[q13] = x_ExplicitVarSizeWithDummy[q11] + | q13 : int(1..4)]) + | q11 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q15] -> + or([x_ExplicitVarSizeWithDummy[q17] != 5 /\ + x_ExplicitVarSizeWithDummy[q17] = x_ExplicitVarSizeWithFlags_Values[q15] + | q17 : int(1..4)]) + | q15 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set06/expected/model_4_4_2_3-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_4_4_2_3-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_4_4_2_3-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_4_4_2_3-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_4_4_2_3-solution000002.solution new file mode 100644 index 0000000000..85149821f6 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_4_4_2_3-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_4_4_2_3.eprime b/tests/exhaustive/basic/set06/expected/model_4_4_2_3.eprime new file mode 100644 index 0000000000..4fe9b7fb6a --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_4_4_2_3.eprime @@ -0,0 +1,60 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +branching on + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithFlags_Flags, + x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy] +such that + or([x_ExplicitVarSizeWithFlags_Flags[q38] /\ x_ExplicitVarSizeWithFlags_Values[q38] = 1 | q38 : int(1..4)]), + or([x_ExplicitVarSizeWithFlags_Flags[q40] /\ x_ExplicitVarSizeWithFlags_Values[q40] = 2 | q40 : int(1..4)]), + or([x_ExplicitVarSizeWithDummy[q42] != 5 /\ x_ExplicitVarSizeWithDummy[q42] = 3 | q42 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithDummy[q6] < x_ExplicitVarSizeWithDummy[q6 + 1] \/ x_ExplicitVarSizeWithDummy[q6] = 5 + | q6 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q7] = 5 -> x_ExplicitVarSizeWithDummy[q7 + 1] = 5 | q7 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithDummy[q8] != 5) | q8 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithDummy[q11] != 5 -> + or([x_ExplicitVarSizeWithFlags_Flags[q13] /\ + x_ExplicitVarSizeWithFlags_Values[q13] = x_ExplicitVarSizeWithDummy[q11] + | q13 : int(1..4)]) + | q11 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q15] -> + or([x_ExplicitVarSizeWithDummy[q17] != 5 /\ + x_ExplicitVarSizeWithDummy[q17] = x_ExplicitVarSizeWithFlags_Values[q15] + | q17 : int(1..4)]) + | q15 : int(1..4)]), + and([q18 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q18] < x_ExplicitVarSizeWithMarker_Values[q18 + 1] + | q18 : int(1..3)]), + and([q19 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q19] = 1 | q19 : int(1..4)]), + x_ExplicitVarSizeWithMarker_Marker <= 4, + and([q22 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithFlags_Flags[q24] /\ + x_ExplicitVarSizeWithFlags_Values[q24] = x_ExplicitVarSizeWithMarker_Values[q22] + | q24 : int(1..4)]) + | q22 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q26] -> + or([q28 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q28] = x_ExplicitVarSizeWithFlags_Values[q26] + | q28 : int(1..4)]) + | q26 : int(1..4)]), + and([q30 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithDummy[q32] != 5 /\ + x_ExplicitVarSizeWithDummy[q32] = x_ExplicitVarSizeWithMarker_Values[q30] + | q32 : int(1..4)]) + | q30 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q34] != 5 -> + or([q36 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q36] = x_ExplicitVarSizeWithDummy[q34] + | q36 : int(1..4)]) + | q34 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set06/expected/model_4_4_3_1-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_4_4_3_1-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_4_4_3_1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_4_4_3_1-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_4_4_3_1-solution000002.solution new file mode 100644 index 0000000000..85149821f6 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_4_4_3_1-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_4_4_3_1.eprime b/tests/exhaustive/basic/set06/expected/model_4_4_3_1.eprime new file mode 100644 index 0000000000..9eb1652af5 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_4_4_3_1.eprime @@ -0,0 +1,48 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_Occurrence: matrix indexed by [int(1..4)] of bool +branching on + [x_Occurrence, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, + x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] +such that + or([x_ExplicitVarSizeWithFlags_Flags[q29] /\ x_ExplicitVarSizeWithFlags_Values[q29] = 1 | q29 : int(1..4)]), + or([x_ExplicitVarSizeWithFlags_Flags[q31] /\ x_ExplicitVarSizeWithFlags_Values[q31] = 2 | q31 : int(1..4)]), + or([q33 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q33] = 3 | q33 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]) <= 4, + and([q6 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q6] < x_ExplicitVarSizeWithMarker_Values[q6 + 1] + | q6 : int(1..3)]), + and([q7 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q7] = 1 | q7 : int(1..4)]), + x_ExplicitVarSizeWithMarker_Marker <= 4, + and([q10 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithFlags_Flags[q12] /\ + x_ExplicitVarSizeWithFlags_Values[q12] = x_ExplicitVarSizeWithMarker_Values[q10] + | q12 : int(1..4)]) + | q10 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q14] -> + or([q16 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q16] = x_ExplicitVarSizeWithFlags_Values[q14] + | q16 : int(1..4)]) + | q14 : int(1..4)]), + sum([toInt(x_Occurrence[q17]) | q17 : int(1..4)]) <= 4, + and([x_Occurrence[q18] -> + or([x_ExplicitVarSizeWithFlags_Flags[q20] /\ x_ExplicitVarSizeWithFlags_Values[q20] = q18 | q20 : int(1..4)]) + | q18 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q22] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q22]] + | q22 : int(1..4)]), + and([x_Occurrence[q23] -> + or([q25 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q25] = q23 + | q25 : int(1..4)]) + | q23 : int(1..4)]), + and([q27 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q27]] + | q27 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set06/expected/model_4_4_3_2-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_4_4_3_2-solution000001.solution new file mode 100644 index 0000000000..85149821f6 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_4_4_3_2-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_4_4_3_2-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_4_4_3_2-solution000002.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_4_4_3_2-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_4_4_3_2.eprime b/tests/exhaustive/basic/set06/expected/model_4_4_3_2.eprime new file mode 100644 index 0000000000..bf7ce16ba1 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_4_4_3_2.eprime @@ -0,0 +1,60 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +branching on + [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, + x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] +such that + or([x_ExplicitVarSizeWithFlags_Flags[q38] /\ x_ExplicitVarSizeWithFlags_Values[q38] = 1 | q38 : int(1..4)]), + or([x_ExplicitVarSizeWithFlags_Flags[q40] /\ x_ExplicitVarSizeWithFlags_Values[q40] = 2 | q40 : int(1..4)]), + or([q42 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q42] = 3 | q42 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]) <= 4, + and([q6 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q6] < x_ExplicitVarSizeWithMarker_Values[q6 + 1] + | q6 : int(1..3)]), + and([q7 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q7] = 1 | q7 : int(1..4)]), + x_ExplicitVarSizeWithMarker_Marker <= 4, + and([q10 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithFlags_Flags[q12] /\ + x_ExplicitVarSizeWithFlags_Values[q12] = x_ExplicitVarSizeWithMarker_Values[q10] + | q12 : int(1..4)]) + | q10 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q14] -> + or([q16 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q16] = x_ExplicitVarSizeWithFlags_Values[q14] + | q16 : int(1..4)]) + | q14 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q17] < x_ExplicitVarSizeWithDummy[q17 + 1] \/ x_ExplicitVarSizeWithDummy[q17] = 5 + | q17 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q18] = 5 -> x_ExplicitVarSizeWithDummy[q18 + 1] = 5 | q18 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithDummy[q19] != 5) | q19 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithDummy[q22] != 5 -> + or([x_ExplicitVarSizeWithFlags_Flags[q24] /\ + x_ExplicitVarSizeWithFlags_Values[q24] = x_ExplicitVarSizeWithDummy[q22] + | q24 : int(1..4)]) + | q22 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q26] -> + or([x_ExplicitVarSizeWithDummy[q28] != 5 /\ + x_ExplicitVarSizeWithDummy[q28] = x_ExplicitVarSizeWithFlags_Values[q26] + | q28 : int(1..4)]) + | q26 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q30] != 5 -> + or([q32 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q32] = x_ExplicitVarSizeWithDummy[q30] + | q32 : int(1..4)]) + | q30 : int(1..4)]), + and([q34 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithDummy[q36] != 5 /\ + x_ExplicitVarSizeWithDummy[q36] = x_ExplicitVarSizeWithMarker_Values[q34] + | q36 : int(1..4)]) + | q34 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set06/expected/model_4_4_3_3-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_4_4_3_3-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_4_4_3_3-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_4_4_3_3-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_4_4_3_3-solution000002.solution new file mode 100644 index 0000000000..85149821f6 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_4_4_3_3-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_4_4_3_3.eprime b/tests/exhaustive/basic/set06/expected/model_4_4_3_3.eprime new file mode 100644 index 0000000000..7c1be4c4b9 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_4_4_3_3.eprime @@ -0,0 +1,35 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +branching on + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithFlags_Flags, + x_ExplicitVarSizeWithFlags_Values] +such that + or([x_ExplicitVarSizeWithFlags_Flags[q18] /\ x_ExplicitVarSizeWithFlags_Values[q18] = 1 | q18 : int(1..4)]), + or([x_ExplicitVarSizeWithFlags_Flags[q20] /\ x_ExplicitVarSizeWithFlags_Values[q20] = 2 | q20 : int(1..4)]), + or([q22 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q22] = 3 | q22 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]) <= 4, + and([q6 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q6] < x_ExplicitVarSizeWithMarker_Values[q6 + 1] + | q6 : int(1..3)]), + and([q7 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q7] = 1 | q7 : int(1..4)]), + x_ExplicitVarSizeWithMarker_Marker <= 4, + and([q10 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithFlags_Flags[q12] /\ + x_ExplicitVarSizeWithFlags_Values[q12] = x_ExplicitVarSizeWithMarker_Values[q10] + | q12 : int(1..4)]) + | q10 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q14] -> + or([q16 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q16] = x_ExplicitVarSizeWithFlags_Values[q14] + | q16 : int(1..4)]) + | q14 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set06/expected/model_4_4_4_1-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_4_4_4_1-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_4_4_4_1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_4_4_4_1-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_4_4_4_1-solution000002.solution new file mode 100644 index 0000000000..85149821f6 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_4_4_4_1-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_4_4_4_1.eprime b/tests/exhaustive/basic/set06/expected/model_4_4_4_1.eprime new file mode 100644 index 0000000000..5ce826b766 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_4_4_4_1.eprime @@ -0,0 +1,23 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_Occurrence: matrix indexed by [int(1..4)] of bool +branching on [x_Occurrence, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] +such that + or([x_ExplicitVarSizeWithFlags_Flags[q13] /\ x_ExplicitVarSizeWithFlags_Values[q13] = 1 | q13 : int(1..4)]), + or([x_ExplicitVarSizeWithFlags_Flags[q15] /\ x_ExplicitVarSizeWithFlags_Values[q15] = 2 | q15 : int(1..4)]), + or([x_ExplicitVarSizeWithFlags_Flags[q17] /\ x_ExplicitVarSizeWithFlags_Values[q17] = 3 | q17 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]) <= 4, + sum([toInt(x_Occurrence[q6]) | q6 : int(1..4)]) <= 4, + and([x_Occurrence[q7] -> + or([x_ExplicitVarSizeWithFlags_Flags[q9] /\ x_ExplicitVarSizeWithFlags_Values[q9] = q7 | q9 : int(1..4)]) + | q7 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q11] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q11]] + | q11 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set06/expected/model_4_4_4_2-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_4_4_4_2-solution000001.solution new file mode 100644 index 0000000000..85149821f6 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_4_4_4_2-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_4_4_4_2-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_4_4_4_2-solution000002.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_4_4_4_2-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_4_4_4_2.eprime b/tests/exhaustive/basic/set06/expected/model_4_4_4_2.eprime new file mode 100644 index 0000000000..c25dce1965 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_4_4_4_2.eprime @@ -0,0 +1,31 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +branching on [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] +such that + or([x_ExplicitVarSizeWithFlags_Flags[q19] /\ x_ExplicitVarSizeWithFlags_Values[q19] = 1 | q19 : int(1..4)]), + or([x_ExplicitVarSizeWithFlags_Flags[q21] /\ x_ExplicitVarSizeWithFlags_Values[q21] = 2 | q21 : int(1..4)]), + or([x_ExplicitVarSizeWithFlags_Flags[q23] /\ x_ExplicitVarSizeWithFlags_Values[q23] = 3 | q23 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithDummy[q6] < x_ExplicitVarSizeWithDummy[q6 + 1] \/ x_ExplicitVarSizeWithDummy[q6] = 5 + | q6 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q7] = 5 -> x_ExplicitVarSizeWithDummy[q7 + 1] = 5 | q7 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithDummy[q8] != 5) | q8 : int(1..4)]) <= 4, + and([x_ExplicitVarSizeWithDummy[q11] != 5 -> + or([x_ExplicitVarSizeWithFlags_Flags[q13] /\ + x_ExplicitVarSizeWithFlags_Values[q13] = x_ExplicitVarSizeWithDummy[q11] + | q13 : int(1..4)]) + | q11 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q15] -> + or([x_ExplicitVarSizeWithDummy[q17] != 5 /\ + x_ExplicitVarSizeWithDummy[q17] = x_ExplicitVarSizeWithFlags_Values[q15] + | q17 : int(1..4)]) + | q15 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set06/expected/model_4_4_4_3-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_4_4_4_3-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_4_4_4_3-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_4_4_4_3-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_4_4_4_3-solution000002.solution new file mode 100644 index 0000000000..85149821f6 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_4_4_4_3-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_4_4_4_3.eprime b/tests/exhaustive/basic/set06/expected/model_4_4_4_3.eprime new file mode 100644 index 0000000000..b5daed7250 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_4_4_4_3.eprime @@ -0,0 +1,35 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +branching on + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithFlags_Flags, + x_ExplicitVarSizeWithFlags_Values] +such that + or([x_ExplicitVarSizeWithFlags_Flags[q18] /\ x_ExplicitVarSizeWithFlags_Values[q18] = 1 | q18 : int(1..4)]), + or([x_ExplicitVarSizeWithFlags_Flags[q20] /\ x_ExplicitVarSizeWithFlags_Values[q20] = 2 | q20 : int(1..4)]), + or([x_ExplicitVarSizeWithFlags_Flags[q22] /\ x_ExplicitVarSizeWithFlags_Values[q22] = 3 | q22 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]) <= 4, + and([q6 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q6] < x_ExplicitVarSizeWithMarker_Values[q6 + 1] + | q6 : int(1..3)]), + and([q7 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q7] = 1 | q7 : int(1..4)]), + x_ExplicitVarSizeWithMarker_Marker <= 4, + and([q10 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithFlags_Flags[q12] /\ + x_ExplicitVarSizeWithFlags_Values[q12] = x_ExplicitVarSizeWithMarker_Values[q10] + | q12 : int(1..4)]) + | q10 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q14] -> + or([q16 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q16] = x_ExplicitVarSizeWithFlags_Values[q14] + | q16 : int(1..4)]) + | q14 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set06/expected/model_4_4_4_4-solution000001.solution b/tests/exhaustive/basic/set06/expected/model_4_4_4_4-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_4_4_4_4-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set06/expected/model_4_4_4_4-solution000002.solution b/tests/exhaustive/basic/set06/expected/model_4_4_4_4-solution000002.solution new file mode 100644 index 0000000000..85149821f6 --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_4_4_4_4-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3, 4} diff --git a/tests/exhaustive/basic/set06/expected/model_4_4_4_4.eprime b/tests/exhaustive/basic/set06/expected/model_4_4_4_4.eprime new file mode 100644 index 0000000000..9cb0f0f85d --- /dev/null +++ b/tests/exhaustive/basic/set06/expected/model_4_4_4_4.eprime @@ -0,0 +1,16 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +branching on [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] +such that + or([x_ExplicitVarSizeWithFlags_Flags[q7] /\ x_ExplicitVarSizeWithFlags_Values[q7] = 1 | q7 : int(1..4)]), + or([x_ExplicitVarSizeWithFlags_Flags[q9] /\ x_ExplicitVarSizeWithFlags_Values[q9] = 2 | q9 : int(1..4)]), + or([x_ExplicitVarSizeWithFlags_Flags[q11] /\ x_ExplicitVarSizeWithFlags_Values[q11] = 3 | q11 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]) <= 4 + diff --git a/tests/exhaustive/basic/set07/expected/model_1_1_1-solution000001.solution b/tests/exhaustive/basic/set07/expected/model_1_1_1-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set07/expected/model_1_1_1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set07/expected/model_1_1_1.eprime b/tests/exhaustive/basic/set07/expected/model_1_1_1.eprime new file mode 100644 index 0000000000..1c2a0f3332 --- /dev/null +++ b/tests/exhaustive/basic/set07/expected/model_1_1_1.eprime @@ -0,0 +1,6 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(1..4)] of bool +branching on [x_Occurrence] +such that and([x_Occurrence[q2_1] /\ !x_Occurrence[q2_2] | q2_1 : int(1..3), q2_2 : int(4..9)]) + diff --git a/tests/exhaustive/basic/set07/expected/model_1_1_2-solution000001.solution b/tests/exhaustive/basic/set07/expected/model_1_1_2-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set07/expected/model_1_1_2-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set07/expected/model_1_1_2.eprime b/tests/exhaustive/basic/set07/expected/model_1_1_2.eprime new file mode 100644 index 0000000000..db14667a95 --- /dev/null +++ b/tests/exhaustive/basic/set07/expected/model_1_1_2.eprime @@ -0,0 +1,15 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +branching on [x_ExplicitVarSizeWithDummy, x_Occurrence] +such that + and([x_Occurrence[q11_1] /\ !x_Occurrence[q11_2] | q11_1 : int(1..3), q11_2 : int(4..9)]), + and([x_ExplicitVarSizeWithDummy[q2] < x_ExplicitVarSizeWithDummy[q2 + 1] \/ x_ExplicitVarSizeWithDummy[q2] = 5 + | q2 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q3] = 5 -> x_ExplicitVarSizeWithDummy[q3 + 1] = 5 | q3 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q7] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q7]] | q7 : int(1..4)]), + and([x_Occurrence[q8] -> + or([x_ExplicitVarSizeWithDummy[q10] != 5 /\ x_ExplicitVarSizeWithDummy[q10] = q8 | q10 : int(1..4)]) + | q8 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set07/expected/model_1_1_3-solution000001.solution b/tests/exhaustive/basic/set07/expected/model_1_1_3-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set07/expected/model_1_1_3-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set07/expected/model_1_1_3.eprime b/tests/exhaustive/basic/set07/expected/model_1_1_3.eprime new file mode 100644 index 0000000000..c710eaa6a1 --- /dev/null +++ b/tests/exhaustive/basic/set07/expected/model_1_1_3.eprime @@ -0,0 +1,18 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +branching on [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_Occurrence] +such that + and([x_Occurrence[q10_1] /\ !x_Occurrence[q10_2] | q10_1 : int(1..3), q10_2 : int(4..9)]), + and([q2 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q2] < x_ExplicitVarSizeWithMarker_Values[q2 + 1] + | q2 : int(1..3)]), + and([q3 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q3] = 1 | q3 : int(1..4)]), + and([q6 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q6]] + | q6 : int(1..4)]), + and([x_Occurrence[q7] -> + or([q9 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q9] = q7 | q9 : int(1..4)]) + | q7 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set07/expected/model_1_1_4-solution000001.solution b/tests/exhaustive/basic/set07/expected/model_1_1_4-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set07/expected/model_1_1_4-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set07/expected/model_1_1_4.eprime b/tests/exhaustive/basic/set07/expected/model_1_1_4.eprime new file mode 100644 index 0000000000..71e8baf956 --- /dev/null +++ b/tests/exhaustive/basic/set07/expected/model_1_1_4.eprime @@ -0,0 +1,18 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +branching on [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_Occurrence] +such that + and([x_Occurrence[q12_1] /\ !x_Occurrence[q12_2] | q12_1 : int(1..3), q12_2 : int(4..9)]), + and([x_ExplicitVarSizeWithFlags_Flags[q2 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q2] < x_ExplicitVarSizeWithFlags_Values[q2 + 1] + | q2 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q3] = false -> x_ExplicitVarSizeWithFlags_Values[q3] = 1 | q3 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q4] | q4 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q8] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q8]] | q8 : int(1..4)]), + and([x_Occurrence[q9] -> + or([x_ExplicitVarSizeWithFlags_Flags[q11] /\ x_ExplicitVarSizeWithFlags_Values[q11] = q9 | q11 : int(1..4)]) + | q9 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set07/expected/model_1_2_1-solution000001.solution b/tests/exhaustive/basic/set07/expected/model_1_2_1-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set07/expected/model_1_2_1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set07/expected/model_1_2_1.eprime b/tests/exhaustive/basic/set07/expected/model_1_2_1.eprime new file mode 100644 index 0000000000..43b3a76c2e --- /dev/null +++ b/tests/exhaustive/basic/set07/expected/model_1_2_1.eprime @@ -0,0 +1,17 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +branching on [x_ExplicitVarSizeWithDummy, x_Occurrence] +such that + and([x_Occurrence[q13_1] /\ + !or([x_ExplicitVarSizeWithDummy[q12] != 5 /\ x_ExplicitVarSizeWithDummy[q12] = q13_2 | q12 : int(1..4)]) + | q13_1 : int(1..3), q13_2 : int(4..9)]), + and([x_ExplicitVarSizeWithDummy[q2] < x_ExplicitVarSizeWithDummy[q2 + 1] \/ x_ExplicitVarSizeWithDummy[q2] = 5 + | q2 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q3] = 5 -> x_ExplicitVarSizeWithDummy[q3 + 1] = 5 | q3 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q7] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q7]] | q7 : int(1..4)]), + and([x_Occurrence[q8] -> + or([x_ExplicitVarSizeWithDummy[q10] != 5 /\ x_ExplicitVarSizeWithDummy[q10] = q8 | q10 : int(1..4)]) + | q8 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set07/expected/model_1_2_3-solution000001.solution b/tests/exhaustive/basic/set07/expected/model_1_2_3-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set07/expected/model_1_2_3-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set07/expected/model_1_2_3.eprime b/tests/exhaustive/basic/set07/expected/model_1_2_3.eprime new file mode 100644 index 0000000000..2a83287908 --- /dev/null +++ b/tests/exhaustive/basic/set07/expected/model_1_2_3.eprime @@ -0,0 +1,40 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +branching on + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_Occurrence, x_ExplicitVarSizeWithDummy] +such that + and([x_Occurrence[q29_1] /\ + !or([x_ExplicitVarSizeWithDummy[q28] != 5 /\ x_ExplicitVarSizeWithDummy[q28] = q29_2 | q28 : int(1..4)]) + | q29_1 : int(1..3), q29_2 : int(4..9)]), + and([x_ExplicitVarSizeWithDummy[q2] < x_ExplicitVarSizeWithDummy[q2 + 1] \/ x_ExplicitVarSizeWithDummy[q2] = 5 + | q2 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q3] = 5 -> x_ExplicitVarSizeWithDummy[q3 + 1] = 5 | q3 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q7] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q7]] | q7 : int(1..4)]), + and([x_Occurrence[q8] -> + or([x_ExplicitVarSizeWithDummy[q10] != 5 /\ x_ExplicitVarSizeWithDummy[q10] = q8 | q10 : int(1..4)]) + | q8 : int(1..4)]), + and([q11 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q11] < x_ExplicitVarSizeWithMarker_Values[q11 + 1] + | q11 : int(1..3)]), + and([q12 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q12] = 1 | q12 : int(1..4)]), + and([q15 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q15]] + | q15 : int(1..4)]), + and([x_Occurrence[q16] -> + or([q18 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q18] = q16 + | q18 : int(1..4)]) + | q16 : int(1..4)]), + and([q20 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithDummy[q22] != 5 /\ + x_ExplicitVarSizeWithDummy[q22] = x_ExplicitVarSizeWithMarker_Values[q20] + | q22 : int(1..4)]) + | q20 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q24] != 5 -> + or([q26 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q26] = x_ExplicitVarSizeWithDummy[q24] + | q26 : int(1..4)]) + | q24 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set07/expected/model_1_2_4-solution000001.solution b/tests/exhaustive/basic/set07/expected/model_1_2_4-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set07/expected/model_1_2_4-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set07/expected/model_1_2_4.eprime b/tests/exhaustive/basic/set07/expected/model_1_2_4.eprime new file mode 100644 index 0000000000..4700b607d4 --- /dev/null +++ b/tests/exhaustive/basic/set07/expected/model_1_2_4.eprime @@ -0,0 +1,41 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +branching on + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_Occurrence, x_ExplicitVarSizeWithDummy] +such that + and([x_Occurrence[q31_1] /\ + !or([x_ExplicitVarSizeWithDummy[q30] != 5 /\ x_ExplicitVarSizeWithDummy[q30] = q31_2 | q30 : int(1..4)]) + | q31_1 : int(1..3), q31_2 : int(4..9)]), + and([x_ExplicitVarSizeWithDummy[q2] < x_ExplicitVarSizeWithDummy[q2 + 1] \/ x_ExplicitVarSizeWithDummy[q2] = 5 + | q2 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q3] = 5 -> x_ExplicitVarSizeWithDummy[q3 + 1] = 5 | q3 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q7] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q7]] | q7 : int(1..4)]), + and([x_Occurrence[q8] -> + or([x_ExplicitVarSizeWithDummy[q10] != 5 /\ x_ExplicitVarSizeWithDummy[q10] = q8 | q10 : int(1..4)]) + | q8 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q11 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q11] < x_ExplicitVarSizeWithFlags_Values[q11 + 1] + | q11 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q12] = false -> x_ExplicitVarSizeWithFlags_Values[q12] = 1 + | q12 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q13 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q13] | q13 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q17] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q17]] + | q17 : int(1..4)]), + and([x_Occurrence[q18] -> + or([x_ExplicitVarSizeWithFlags_Flags[q20] /\ x_ExplicitVarSizeWithFlags_Values[q20] = q18 | q20 : int(1..4)]) + | q18 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q22] -> + or([x_ExplicitVarSizeWithDummy[q24] != 5 /\ + x_ExplicitVarSizeWithDummy[q24] = x_ExplicitVarSizeWithFlags_Values[q22] + | q24 : int(1..4)]) + | q22 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q26] != 5 -> + or([x_ExplicitVarSizeWithFlags_Flags[q28] /\ + x_ExplicitVarSizeWithFlags_Values[q28] = x_ExplicitVarSizeWithDummy[q26] + | q28 : int(1..4)]) + | q26 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set07/expected/model_1_3_1-solution000001.solution b/tests/exhaustive/basic/set07/expected/model_1_3_1-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set07/expected/model_1_3_1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set07/expected/model_1_3_1.eprime b/tests/exhaustive/basic/set07/expected/model_1_3_1.eprime new file mode 100644 index 0000000000..6da06e040b --- /dev/null +++ b/tests/exhaustive/basic/set07/expected/model_1_3_1.eprime @@ -0,0 +1,21 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +branching on [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_Occurrence] +such that + and([x_Occurrence[q12_1] /\ + !or([q11 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q11] = q12_2 + | q11 : int(1..4)]) + | q12_1 : int(1..3), q12_2 : int(4..9)]), + and([q2 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q2] < x_ExplicitVarSizeWithMarker_Values[q2 + 1] + | q2 : int(1..3)]), + and([q3 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q3] = 1 | q3 : int(1..4)]), + and([q6 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q6]] + | q6 : int(1..4)]), + and([x_Occurrence[q7] -> + or([q9 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q9] = q7 | q9 : int(1..4)]) + | q7 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set07/expected/model_1_3_2-solution000001.solution b/tests/exhaustive/basic/set07/expected/model_1_3_2-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set07/expected/model_1_3_2-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set07/expected/model_1_3_2.eprime b/tests/exhaustive/basic/set07/expected/model_1_3_2.eprime new file mode 100644 index 0000000000..f8fefa8170 --- /dev/null +++ b/tests/exhaustive/basic/set07/expected/model_1_3_2.eprime @@ -0,0 +1,40 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +branching on + [x_ExplicitVarSizeWithDummy, x_Occurrence, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] +such that + and([x_Occurrence[q29_1] /\ + !or([q28 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q28] = q29_2 + | q28 : int(1..4)]) + | q29_1 : int(1..3), q29_2 : int(4..9)]), + and([q2 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q2] < x_ExplicitVarSizeWithMarker_Values[q2 + 1] + | q2 : int(1..3)]), + and([q3 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q3] = 1 | q3 : int(1..4)]), + and([q6 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q6]] + | q6 : int(1..4)]), + and([x_Occurrence[q7] -> + or([q9 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q9] = q7 | q9 : int(1..4)]) + | q7 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q10] < x_ExplicitVarSizeWithDummy[q10 + 1] \/ x_ExplicitVarSizeWithDummy[q10] = 5 + | q10 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q11] = 5 -> x_ExplicitVarSizeWithDummy[q11 + 1] = 5 | q11 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q15] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q15]] | q15 : int(1..4)]), + and([x_Occurrence[q16] -> + or([x_ExplicitVarSizeWithDummy[q18] != 5 /\ x_ExplicitVarSizeWithDummy[q18] = q16 | q18 : int(1..4)]) + | q16 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q20] != 5 -> + or([q22 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q22] = x_ExplicitVarSizeWithDummy[q20] + | q22 : int(1..4)]) + | q20 : int(1..4)]), + and([q24 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithDummy[q26] != 5 /\ + x_ExplicitVarSizeWithDummy[q26] = x_ExplicitVarSizeWithMarker_Values[q24] + | q26 : int(1..4)]) + | q24 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set07/expected/model_1_3_4-solution000001.solution b/tests/exhaustive/basic/set07/expected/model_1_3_4-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set07/expected/model_1_3_4-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set07/expected/model_1_3_4.eprime b/tests/exhaustive/basic/set07/expected/model_1_3_4.eprime new file mode 100644 index 0000000000..744a29abf7 --- /dev/null +++ b/tests/exhaustive/basic/set07/expected/model_1_3_4.eprime @@ -0,0 +1,46 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +branching on + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_Occurrence, + x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] +such that + and([x_Occurrence[q30_1] /\ + !or([q29 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q29] = q30_2 + | q29 : int(1..4)]) + | q30_1 : int(1..3), q30_2 : int(4..9)]), + and([q2 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q2] < x_ExplicitVarSizeWithMarker_Values[q2 + 1] + | q2 : int(1..3)]), + and([q3 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q3] = 1 | q3 : int(1..4)]), + and([q6 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q6]] + | q6 : int(1..4)]), + and([x_Occurrence[q7] -> + or([q9 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q9] = q7 | q9 : int(1..4)]) + | q7 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q10 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q10] < x_ExplicitVarSizeWithFlags_Values[q10 + 1] + | q10 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q11] = false -> x_ExplicitVarSizeWithFlags_Values[q11] = 1 + | q11 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q12 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q12] | q12 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q16] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q16]] + | q16 : int(1..4)]), + and([x_Occurrence[q17] -> + or([x_ExplicitVarSizeWithFlags_Flags[q19] /\ x_ExplicitVarSizeWithFlags_Values[q19] = q17 | q19 : int(1..4)]) + | q17 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q21] -> + or([q23 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q23] = x_ExplicitVarSizeWithFlags_Values[q21] + | q23 : int(1..4)]) + | q21 : int(1..4)]), + and([q25 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithFlags_Flags[q27] /\ + x_ExplicitVarSizeWithFlags_Values[q27] = x_ExplicitVarSizeWithMarker_Values[q25] + | q27 : int(1..4)]) + | q25 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set07/expected/model_1_4_1-solution000001.solution b/tests/exhaustive/basic/set07/expected/model_1_4_1-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set07/expected/model_1_4_1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set07/expected/model_1_4_1.eprime b/tests/exhaustive/basic/set07/expected/model_1_4_1.eprime new file mode 100644 index 0000000000..38303ddfee --- /dev/null +++ b/tests/exhaustive/basic/set07/expected/model_1_4_1.eprime @@ -0,0 +1,21 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +branching on [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_Occurrence] +such that + and([x_Occurrence[q14_1] /\ + !or([x_ExplicitVarSizeWithFlags_Flags[q13] /\ x_ExplicitVarSizeWithFlags_Values[q13] = q14_2 + | q13 : int(1..4)]) + | q14_1 : int(1..3), q14_2 : int(4..9)]), + and([x_ExplicitVarSizeWithFlags_Flags[q2 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q2] < x_ExplicitVarSizeWithFlags_Values[q2 + 1] + | q2 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q3] = false -> x_ExplicitVarSizeWithFlags_Values[q3] = 1 | q3 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q4] | q4 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q8] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q8]] | q8 : int(1..4)]), + and([x_Occurrence[q9] -> + or([x_ExplicitVarSizeWithFlags_Flags[q11] /\ x_ExplicitVarSizeWithFlags_Values[q11] = q9 | q11 : int(1..4)]) + | q9 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set07/expected/model_1_4_2-solution000001.solution b/tests/exhaustive/basic/set07/expected/model_1_4_2-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set07/expected/model_1_4_2-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set07/expected/model_1_4_2.eprime b/tests/exhaustive/basic/set07/expected/model_1_4_2.eprime new file mode 100644 index 0000000000..e9a9b228b7 --- /dev/null +++ b/tests/exhaustive/basic/set07/expected/model_1_4_2.eprime @@ -0,0 +1,40 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +branching on + [x_ExplicitVarSizeWithDummy, x_Occurrence, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] +such that + and([x_Occurrence[q31_1] /\ + !or([x_ExplicitVarSizeWithFlags_Flags[q30] /\ x_ExplicitVarSizeWithFlags_Values[q30] = q31_2 + | q30 : int(1..4)]) + | q31_1 : int(1..3), q31_2 : int(4..9)]), + and([x_ExplicitVarSizeWithFlags_Flags[q2 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q2] < x_ExplicitVarSizeWithFlags_Values[q2 + 1] + | q2 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q3] = false -> x_ExplicitVarSizeWithFlags_Values[q3] = 1 | q3 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q4] | q4 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q8] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q8]] | q8 : int(1..4)]), + and([x_Occurrence[q9] -> + or([x_ExplicitVarSizeWithFlags_Flags[q11] /\ x_ExplicitVarSizeWithFlags_Values[q11] = q9 | q11 : int(1..4)]) + | q9 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q12] < x_ExplicitVarSizeWithDummy[q12 + 1] \/ x_ExplicitVarSizeWithDummy[q12] = 5 + | q12 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q13] = 5 -> x_ExplicitVarSizeWithDummy[q13 + 1] = 5 | q13 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q17] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q17]] | q17 : int(1..4)]), + and([x_Occurrence[q18] -> + or([x_ExplicitVarSizeWithDummy[q20] != 5 /\ x_ExplicitVarSizeWithDummy[q20] = q18 | q20 : int(1..4)]) + | q18 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q22] != 5 -> + or([x_ExplicitVarSizeWithFlags_Flags[q24] /\ + x_ExplicitVarSizeWithFlags_Values[q24] = x_ExplicitVarSizeWithDummy[q22] + | q24 : int(1..4)]) + | q22 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q26] -> + or([x_ExplicitVarSizeWithDummy[q28] != 5 /\ + x_ExplicitVarSizeWithDummy[q28] = x_ExplicitVarSizeWithFlags_Values[q26] + | q28 : int(1..4)]) + | q26 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set07/expected/model_1_4_3-solution000001.solution b/tests/exhaustive/basic/set07/expected/model_1_4_3-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set07/expected/model_1_4_3-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set07/expected/model_1_4_3.eprime b/tests/exhaustive/basic/set07/expected/model_1_4_3.eprime new file mode 100644 index 0000000000..7b8fce9b8d --- /dev/null +++ b/tests/exhaustive/basic/set07/expected/model_1_4_3.eprime @@ -0,0 +1,45 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +branching on + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_Occurrence, + x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] +such that + and([x_Occurrence[q30_1] /\ + !or([x_ExplicitVarSizeWithFlags_Flags[q29] /\ x_ExplicitVarSizeWithFlags_Values[q29] = q30_2 + | q29 : int(1..4)]) + | q30_1 : int(1..3), q30_2 : int(4..9)]), + and([x_ExplicitVarSizeWithFlags_Flags[q2 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q2] < x_ExplicitVarSizeWithFlags_Values[q2 + 1] + | q2 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q3] = false -> x_ExplicitVarSizeWithFlags_Values[q3] = 1 | q3 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q4] | q4 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q8] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q8]] | q8 : int(1..4)]), + and([x_Occurrence[q9] -> + or([x_ExplicitVarSizeWithFlags_Flags[q11] /\ x_ExplicitVarSizeWithFlags_Values[q11] = q9 | q11 : int(1..4)]) + | q9 : int(1..4)]), + and([q12 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q12] < x_ExplicitVarSizeWithMarker_Values[q12 + 1] + | q12 : int(1..3)]), + and([q13 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q13] = 1 | q13 : int(1..4)]), + and([q16 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q16]] + | q16 : int(1..4)]), + and([x_Occurrence[q17] -> + or([q19 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q19] = q17 + | q19 : int(1..4)]) + | q17 : int(1..4)]), + and([q21 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithFlags_Flags[q23] /\ + x_ExplicitVarSizeWithFlags_Values[q23] = x_ExplicitVarSizeWithMarker_Values[q21] + | q23 : int(1..4)]) + | q21 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q25] -> + or([q27 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q27] = x_ExplicitVarSizeWithFlags_Values[q25] + | q27 : int(1..4)]) + | q25 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set07/expected/model_2_1_1-solution000001.solution b/tests/exhaustive/basic/set07/expected/model_2_1_1-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set07/expected/model_2_1_1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set07/expected/model_2_1_1.eprime b/tests/exhaustive/basic/set07/expected/model_2_1_1.eprime new file mode 100644 index 0000000000..9157723de1 --- /dev/null +++ b/tests/exhaustive/basic/set07/expected/model_2_1_1.eprime @@ -0,0 +1,17 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +find x_Occurrence: matrix indexed by [int(1..4)] of bool +branching on [x_Occurrence, x_ExplicitVarSizeWithDummy] +such that + and([or([x_ExplicitVarSizeWithDummy[q7] != 5 /\ x_ExplicitVarSizeWithDummy[q7] = q8_1 | q7 : int(1..4)]) /\ + !x_Occurrence[q8_2] + | q8_1 : int(1..3), q8_2 : int(4..9)]), + and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 5 + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q2] = 5 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..3)]), + and([x_Occurrence[q9] -> + or([x_ExplicitVarSizeWithDummy[q11] != 5 /\ x_ExplicitVarSizeWithDummy[q11] = q9 | q11 : int(1..4)]) + | q9 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q13] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q13]] | q13 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set07/expected/model_2_1_3-solution000001.solution b/tests/exhaustive/basic/set07/expected/model_2_1_3-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set07/expected/model_2_1_3-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set07/expected/model_2_1_3.eprime b/tests/exhaustive/basic/set07/expected/model_2_1_3.eprime new file mode 100644 index 0000000000..71931d01a0 --- /dev/null +++ b/tests/exhaustive/basic/set07/expected/model_2_1_3.eprime @@ -0,0 +1,40 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +find x_Occurrence: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +branching on + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy, x_Occurrence] +such that + and([or([x_ExplicitVarSizeWithDummy[q23] != 5 /\ x_ExplicitVarSizeWithDummy[q23] = q24_1 | q23 : int(1..4)]) /\ + !x_Occurrence[q24_2] + | q24_1 : int(1..3), q24_2 : int(4..9)]), + and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 5 + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q2] = 5 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..3)]), + and([x_Occurrence[q25] -> + or([x_ExplicitVarSizeWithDummy[q27] != 5 /\ x_ExplicitVarSizeWithDummy[q27] = q25 | q27 : int(1..4)]) + | q25 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q29] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q29]] | q29 : int(1..4)]), + and([q6 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q6] < x_ExplicitVarSizeWithMarker_Values[q6 + 1] + | q6 : int(1..3)]), + and([q7 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q7] = 1 | q7 : int(1..4)]), + and([q10 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithDummy[q12] != 5 /\ + x_ExplicitVarSizeWithDummy[q12] = x_ExplicitVarSizeWithMarker_Values[q10] + | q12 : int(1..4)]) + | q10 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q14] != 5 -> + or([q16 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q16] = x_ExplicitVarSizeWithDummy[q14] + | q16 : int(1..4)]) + | q14 : int(1..4)]), + and([q18 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q18]] + | q18 : int(1..4)]), + and([x_Occurrence[q19] -> + or([q21 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q21] = q19 + | q21 : int(1..4)]) + | q19 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set07/expected/model_2_1_4-solution000001.solution b/tests/exhaustive/basic/set07/expected/model_2_1_4-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set07/expected/model_2_1_4-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set07/expected/model_2_1_4.eprime b/tests/exhaustive/basic/set07/expected/model_2_1_4.eprime new file mode 100644 index 0000000000..1b82376576 --- /dev/null +++ b/tests/exhaustive/basic/set07/expected/model_2_1_4.eprime @@ -0,0 +1,40 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +find x_Occurrence: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +branching on + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy, x_Occurrence] +such that + and([or([x_ExplicitVarSizeWithDummy[q25] != 5 /\ x_ExplicitVarSizeWithDummy[q25] = q26_1 | q25 : int(1..4)]) /\ + !x_Occurrence[q26_2] + | q26_1 : int(1..3), q26_2 : int(4..9)]), + and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 5 + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q2] = 5 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..3)]), + and([x_Occurrence[q27] -> + or([x_ExplicitVarSizeWithDummy[q29] != 5 /\ x_ExplicitVarSizeWithDummy[q29] = q27 | q29 : int(1..4)]) + | q27 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q31] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q31]] | q31 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q6] < x_ExplicitVarSizeWithFlags_Values[q6 + 1] + | q6 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q7] = false -> x_ExplicitVarSizeWithFlags_Values[q7] = 1 | q7 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q8 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q8] | q8 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q12] -> + or([x_ExplicitVarSizeWithDummy[q14] != 5 /\ + x_ExplicitVarSizeWithDummy[q14] = x_ExplicitVarSizeWithFlags_Values[q12] + | q14 : int(1..4)]) + | q12 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q16] != 5 -> + or([x_ExplicitVarSizeWithFlags_Flags[q18] /\ + x_ExplicitVarSizeWithFlags_Values[q18] = x_ExplicitVarSizeWithDummy[q16] + | q18 : int(1..4)]) + | q16 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q20] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q20]] + | q20 : int(1..4)]), + and([x_Occurrence[q21] -> + or([x_ExplicitVarSizeWithFlags_Flags[q23] /\ x_ExplicitVarSizeWithFlags_Values[q23] = q21 | q23 : int(1..4)]) + | q21 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set07/expected/model_2_2_1-solution000001.solution b/tests/exhaustive/basic/set07/expected/model_2_2_1-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set07/expected/model_2_2_1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set07/expected/model_2_2_1.eprime b/tests/exhaustive/basic/set07/expected/model_2_2_1.eprime new file mode 100644 index 0000000000..f490f980a2 --- /dev/null +++ b/tests/exhaustive/basic/set07/expected/model_2_2_1.eprime @@ -0,0 +1,17 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +find x_Occurrence: matrix indexed by [int(1..4)] of bool +branching on [x_Occurrence, x_ExplicitVarSizeWithDummy] +such that + and([or([x_ExplicitVarSizeWithDummy[q7] != 5 /\ x_ExplicitVarSizeWithDummy[q7] = q10_1 | q7 : int(1..4)]) /\ + !or([x_ExplicitVarSizeWithDummy[q9] != 5 /\ x_ExplicitVarSizeWithDummy[q9] = q10_2 | q9 : int(1..4)]) + | q10_1 : int(1..3), q10_2 : int(4..9)]), + and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 5 + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q2] = 5 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..3)]), + and([x_Occurrence[q11] -> + or([x_ExplicitVarSizeWithDummy[q13] != 5 /\ x_ExplicitVarSizeWithDummy[q13] = q11 | q13 : int(1..4)]) + | q11 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q15] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q15]] | q15 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set07/expected/model_2_2_2-solution000001.solution b/tests/exhaustive/basic/set07/expected/model_2_2_2-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set07/expected/model_2_2_2-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set07/expected/model_2_2_2.eprime b/tests/exhaustive/basic/set07/expected/model_2_2_2.eprime new file mode 100644 index 0000000000..ccc364f0fe --- /dev/null +++ b/tests/exhaustive/basic/set07/expected/model_2_2_2.eprime @@ -0,0 +1,12 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +branching on [x_ExplicitVarSizeWithDummy] +such that + and([or([x_ExplicitVarSizeWithDummy[q6] != 5 /\ x_ExplicitVarSizeWithDummy[q6] = q9_1 | q6 : int(1..4)]) /\ + !or([x_ExplicitVarSizeWithDummy[q8] != 5 /\ x_ExplicitVarSizeWithDummy[q8] = q9_2 | q8 : int(1..4)]) + | q9_1 : int(1..3), q9_2 : int(4..9)]), + and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 5 + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q2] = 5 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..3)]) + diff --git a/tests/exhaustive/basic/set07/expected/model_2_2_3-solution000001.solution b/tests/exhaustive/basic/set07/expected/model_2_2_3-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set07/expected/model_2_2_3-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set07/expected/model_2_2_3.eprime b/tests/exhaustive/basic/set07/expected/model_2_2_3.eprime new file mode 100644 index 0000000000..c1bc8f0602 --- /dev/null +++ b/tests/exhaustive/basic/set07/expected/model_2_2_3.eprime @@ -0,0 +1,28 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +branching on [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy] +such that + and([or([x_ExplicitVarSizeWithDummy[q17] != 5 /\ x_ExplicitVarSizeWithDummy[q17] = q20_1 | q17 : int(1..4)]) /\ + !or([x_ExplicitVarSizeWithDummy[q19] != 5 /\ x_ExplicitVarSizeWithDummy[q19] = q20_2 | q19 : int(1..4)]) + | q20_1 : int(1..3), q20_2 : int(4..9)]), + and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 5 + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q2] = 5 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..3)]), + and([q5 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q5] < x_ExplicitVarSizeWithMarker_Values[q5 + 1] + | q5 : int(1..3)]), + and([q6 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q6] = 1 | q6 : int(1..4)]), + and([q9 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithDummy[q11] != 5 /\ + x_ExplicitVarSizeWithDummy[q11] = x_ExplicitVarSizeWithMarker_Values[q9] + | q11 : int(1..4)]) + | q9 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q13] != 5 -> + or([q15 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q15] = x_ExplicitVarSizeWithDummy[q13] + | q15 : int(1..4)]) + | q13 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set07/expected/model_2_2_4-solution000001.solution b/tests/exhaustive/basic/set07/expected/model_2_2_4-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set07/expected/model_2_2_4-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set07/expected/model_2_2_4.eprime b/tests/exhaustive/basic/set07/expected/model_2_2_4.eprime new file mode 100644 index 0000000000..128577ea84 --- /dev/null +++ b/tests/exhaustive/basic/set07/expected/model_2_2_4.eprime @@ -0,0 +1,29 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +branching on [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy] +such that + and([or([x_ExplicitVarSizeWithDummy[q19] != 5 /\ x_ExplicitVarSizeWithDummy[q19] = q22_1 | q19 : int(1..4)]) /\ + !or([x_ExplicitVarSizeWithDummy[q21] != 5 /\ x_ExplicitVarSizeWithDummy[q21] = q22_2 | q21 : int(1..4)]) + | q22_1 : int(1..3), q22_2 : int(4..9)]), + and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 5 + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q2] = 5 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q5 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q5] < x_ExplicitVarSizeWithFlags_Values[q5 + 1] + | q5 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q6] = false -> x_ExplicitVarSizeWithFlags_Values[q6] = 1 | q6 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q7] | q7 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q11] -> + or([x_ExplicitVarSizeWithDummy[q13] != 5 /\ + x_ExplicitVarSizeWithDummy[q13] = x_ExplicitVarSizeWithFlags_Values[q11] + | q13 : int(1..4)]) + | q11 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q15] != 5 -> + or([x_ExplicitVarSizeWithFlags_Flags[q17] /\ + x_ExplicitVarSizeWithFlags_Values[q17] = x_ExplicitVarSizeWithDummy[q15] + | q17 : int(1..4)]) + | q15 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set07/expected/model_2_3_1-solution000001.solution b/tests/exhaustive/basic/set07/expected/model_2_3_1-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set07/expected/model_2_3_1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set07/expected/model_2_3_1.eprime b/tests/exhaustive/basic/set07/expected/model_2_3_1.eprime new file mode 100644 index 0000000000..bb5d893672 --- /dev/null +++ b/tests/exhaustive/basic/set07/expected/model_2_3_1.eprime @@ -0,0 +1,41 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_Occurrence: matrix indexed by [int(1..4)] of bool +branching on + [x_Occurrence, x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] +such that + and([or([x_ExplicitVarSizeWithDummy[q18] != 5 /\ x_ExplicitVarSizeWithDummy[q18] = q21_1 | q18 : int(1..4)]) /\ + !or([q20 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q20] = q21_2 + | q20 : int(1..4)]) + | q21_1 : int(1..3), q21_2 : int(4..9)]), + and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 5 + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q2] = 5 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..3)]), + and([q5 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q5] < x_ExplicitVarSizeWithMarker_Values[q5 + 1] + | q5 : int(1..3)]), + and([q6 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q6] = 1 | q6 : int(1..4)]), + and([q9 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithDummy[q11] != 5 /\ + x_ExplicitVarSizeWithDummy[q11] = x_ExplicitVarSizeWithMarker_Values[q9] + | q11 : int(1..4)]) + | q9 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q13] != 5 -> + or([q15 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q15] = x_ExplicitVarSizeWithDummy[q13] + | q15 : int(1..4)]) + | q13 : int(1..4)]), + and([x_Occurrence[q22] -> + or([x_ExplicitVarSizeWithDummy[q24] != 5 /\ x_ExplicitVarSizeWithDummy[q24] = q22 | q24 : int(1..4)]) + | q22 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q26] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q26]] | q26 : int(1..4)]), + and([x_Occurrence[q27] -> + or([q29 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q29] = q27 + | q29 : int(1..4)]) + | q27 : int(1..4)]), + and([q31 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q31]] + | q31 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set07/expected/model_2_3_2-solution000001.solution b/tests/exhaustive/basic/set07/expected/model_2_3_2-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set07/expected/model_2_3_2-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set07/expected/model_2_3_2.eprime b/tests/exhaustive/basic/set07/expected/model_2_3_2.eprime new file mode 100644 index 0000000000..9623bc7a26 --- /dev/null +++ b/tests/exhaustive/basic/set07/expected/model_2_3_2.eprime @@ -0,0 +1,29 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +branching on [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy] +such that + and([or([x_ExplicitVarSizeWithDummy[q17] != 5 /\ x_ExplicitVarSizeWithDummy[q17] = q20_1 | q17 : int(1..4)]) /\ + !or([q19 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q19] = q20_2 + | q19 : int(1..4)]) + | q20_1 : int(1..3), q20_2 : int(4..9)]), + and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 5 + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q2] = 5 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..3)]), + and([q5 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q5] < x_ExplicitVarSizeWithMarker_Values[q5 + 1] + | q5 : int(1..3)]), + and([q6 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q6] = 1 | q6 : int(1..4)]), + and([q9 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithDummy[q11] != 5 /\ + x_ExplicitVarSizeWithDummy[q11] = x_ExplicitVarSizeWithMarker_Values[q9] + | q11 : int(1..4)]) + | q9 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q13] != 5 -> + or([q15 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q15] = x_ExplicitVarSizeWithDummy[q13] + | q15 : int(1..4)]) + | q13 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set07/expected/model_2_3_4-solution000001.solution b/tests/exhaustive/basic/set07/expected/model_2_3_4-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set07/expected/model_2_3_4-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set07/expected/model_2_3_4.eprime b/tests/exhaustive/basic/set07/expected/model_2_3_4.eprime new file mode 100644 index 0000000000..5172fad9a2 --- /dev/null +++ b/tests/exhaustive/basic/set07/expected/model_2_3_4.eprime @@ -0,0 +1,59 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +branching on + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy, + x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] +such that + and([or([x_ExplicitVarSizeWithDummy[q38] != 5 /\ x_ExplicitVarSizeWithDummy[q38] = q41_1 | q38 : int(1..4)]) /\ + !or([q40 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q40] = q41_2 + | q40 : int(1..4)]) + | q41_1 : int(1..3), q41_2 : int(4..9)]), + and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 5 + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q2] = 5 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..3)]), + and([q5 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q5] < x_ExplicitVarSizeWithMarker_Values[q5 + 1] + | q5 : int(1..3)]), + and([q6 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q6] = 1 | q6 : int(1..4)]), + and([q9 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithDummy[q11] != 5 /\ + x_ExplicitVarSizeWithDummy[q11] = x_ExplicitVarSizeWithMarker_Values[q9] + | q11 : int(1..4)]) + | q9 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q13] != 5 -> + or([q15 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q15] = x_ExplicitVarSizeWithDummy[q13] + | q15 : int(1..4)]) + | q13 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q16 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q16] < x_ExplicitVarSizeWithFlags_Values[q16 + 1] + | q16 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q17] = false -> x_ExplicitVarSizeWithFlags_Values[q17] = 1 + | q17 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q18 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q18] | q18 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q22] -> + or([x_ExplicitVarSizeWithDummy[q24] != 5 /\ + x_ExplicitVarSizeWithDummy[q24] = x_ExplicitVarSizeWithFlags_Values[q22] + | q24 : int(1..4)]) + | q22 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q26] != 5 -> + or([x_ExplicitVarSizeWithFlags_Flags[q28] /\ + x_ExplicitVarSizeWithFlags_Values[q28] = x_ExplicitVarSizeWithDummy[q26] + | q28 : int(1..4)]) + | q26 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q30] -> + or([q32 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q32] = x_ExplicitVarSizeWithFlags_Values[q30] + | q32 : int(1..4)]) + | q30 : int(1..4)]), + and([q34 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithFlags_Flags[q36] /\ + x_ExplicitVarSizeWithFlags_Values[q36] = x_ExplicitVarSizeWithMarker_Values[q34] + | q36 : int(1..4)]) + | q34 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set07/expected/model_2_4_1-solution000001.solution b/tests/exhaustive/basic/set07/expected/model_2_4_1-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set07/expected/model_2_4_1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set07/expected/model_2_4_1.eprime b/tests/exhaustive/basic/set07/expected/model_2_4_1.eprime new file mode 100644 index 0000000000..d96379070f --- /dev/null +++ b/tests/exhaustive/basic/set07/expected/model_2_4_1.eprime @@ -0,0 +1,41 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_Occurrence: matrix indexed by [int(1..4)] of bool +branching on + [x_Occurrence, x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] +such that + and([or([x_ExplicitVarSizeWithDummy[q30] != 5 /\ x_ExplicitVarSizeWithDummy[q30] = q33_1 | q30 : int(1..4)]) /\ + !or([x_ExplicitVarSizeWithFlags_Flags[q32] /\ x_ExplicitVarSizeWithFlags_Values[q32] = q33_2 + | q32 : int(1..4)]) + | q33_1 : int(1..3), q33_2 : int(4..9)]), + and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 5 + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q2] = 5 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q5 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q5] < x_ExplicitVarSizeWithFlags_Values[q5 + 1] + | q5 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q6] = false -> x_ExplicitVarSizeWithFlags_Values[q6] = 1 | q6 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q7] | q7 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q11] -> + or([x_ExplicitVarSizeWithDummy[q13] != 5 /\ + x_ExplicitVarSizeWithDummy[q13] = x_ExplicitVarSizeWithFlags_Values[q11] + | q13 : int(1..4)]) + | q11 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q15] != 5 -> + or([x_ExplicitVarSizeWithFlags_Flags[q17] /\ + x_ExplicitVarSizeWithFlags_Values[q17] = x_ExplicitVarSizeWithDummy[q15] + | q17 : int(1..4)]) + | q15 : int(1..4)]), + and([x_Occurrence[q19] -> + or([x_ExplicitVarSizeWithDummy[q21] != 5 /\ x_ExplicitVarSizeWithDummy[q21] = q19 | q21 : int(1..4)]) + | q19 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q23] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q23]] | q23 : int(1..4)]), + and([x_Occurrence[q24] -> + or([x_ExplicitVarSizeWithFlags_Flags[q26] /\ x_ExplicitVarSizeWithFlags_Values[q26] = q24 | q26 : int(1..4)]) + | q24 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q28] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q28]] + | q28 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set07/expected/model_2_4_2-solution000001.solution b/tests/exhaustive/basic/set07/expected/model_2_4_2-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set07/expected/model_2_4_2-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set07/expected/model_2_4_2.eprime b/tests/exhaustive/basic/set07/expected/model_2_4_2.eprime new file mode 100644 index 0000000000..82fca6cda7 --- /dev/null +++ b/tests/exhaustive/basic/set07/expected/model_2_4_2.eprime @@ -0,0 +1,30 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +branching on [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy] +such that + and([or([x_ExplicitVarSizeWithDummy[q19] != 5 /\ x_ExplicitVarSizeWithDummy[q19] = q22_1 | q19 : int(1..4)]) /\ + !or([x_ExplicitVarSizeWithFlags_Flags[q21] /\ x_ExplicitVarSizeWithFlags_Values[q21] = q22_2 + | q21 : int(1..4)]) + | q22_1 : int(1..3), q22_2 : int(4..9)]), + and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 5 + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q2] = 5 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q5 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q5] < x_ExplicitVarSizeWithFlags_Values[q5 + 1] + | q5 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q6] = false -> x_ExplicitVarSizeWithFlags_Values[q6] = 1 | q6 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q7] | q7 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q11] -> + or([x_ExplicitVarSizeWithDummy[q13] != 5 /\ + x_ExplicitVarSizeWithDummy[q13] = x_ExplicitVarSizeWithFlags_Values[q11] + | q13 : int(1..4)]) + | q11 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q15] != 5 -> + or([x_ExplicitVarSizeWithFlags_Flags[q17] /\ + x_ExplicitVarSizeWithFlags_Values[q17] = x_ExplicitVarSizeWithDummy[q15] + | q17 : int(1..4)]) + | q15 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set07/expected/model_2_4_3-solution000001.solution b/tests/exhaustive/basic/set07/expected/model_2_4_3-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set07/expected/model_2_4_3-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set07/expected/model_2_4_3.eprime b/tests/exhaustive/basic/set07/expected/model_2_4_3.eprime new file mode 100644 index 0000000000..d9bc3fdee6 --- /dev/null +++ b/tests/exhaustive/basic/set07/expected/model_2_4_3.eprime @@ -0,0 +1,58 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +branching on + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy, + x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] +such that + and([or([x_ExplicitVarSizeWithDummy[q38] != 5 /\ x_ExplicitVarSizeWithDummy[q38] = q41_1 | q38 : int(1..4)]) /\ + !or([x_ExplicitVarSizeWithFlags_Flags[q40] /\ x_ExplicitVarSizeWithFlags_Values[q40] = q41_2 + | q40 : int(1..4)]) + | q41_1 : int(1..3), q41_2 : int(4..9)]), + and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 5 + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q2] = 5 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 5 | q2 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q5 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q5] < x_ExplicitVarSizeWithFlags_Values[q5 + 1] + | q5 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q6] = false -> x_ExplicitVarSizeWithFlags_Values[q6] = 1 | q6 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q7] | q7 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q11] -> + or([x_ExplicitVarSizeWithDummy[q13] != 5 /\ + x_ExplicitVarSizeWithDummy[q13] = x_ExplicitVarSizeWithFlags_Values[q11] + | q13 : int(1..4)]) + | q11 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q15] != 5 -> + or([x_ExplicitVarSizeWithFlags_Flags[q17] /\ + x_ExplicitVarSizeWithFlags_Values[q17] = x_ExplicitVarSizeWithDummy[q15] + | q17 : int(1..4)]) + | q15 : int(1..4)]), + and([q18 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q18] < x_ExplicitVarSizeWithMarker_Values[q18 + 1] + | q18 : int(1..3)]), + and([q19 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q19] = 1 | q19 : int(1..4)]), + and([q22 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithDummy[q24] != 5 /\ + x_ExplicitVarSizeWithDummy[q24] = x_ExplicitVarSizeWithMarker_Values[q22] + | q24 : int(1..4)]) + | q22 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q26] != 5 -> + or([q28 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q28] = x_ExplicitVarSizeWithDummy[q26] + | q28 : int(1..4)]) + | q26 : int(1..4)]), + and([q30 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithFlags_Flags[q32] /\ + x_ExplicitVarSizeWithFlags_Values[q32] = x_ExplicitVarSizeWithMarker_Values[q30] + | q32 : int(1..4)]) + | q30 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q34] -> + or([q36 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q36] = x_ExplicitVarSizeWithFlags_Values[q34] + | q36 : int(1..4)]) + | q34 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set07/expected/model_3_1_1-solution000001.solution b/tests/exhaustive/basic/set07/expected/model_3_1_1-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set07/expected/model_3_1_1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set07/expected/model_3_1_1.eprime b/tests/exhaustive/basic/set07/expected/model_3_1_1.eprime new file mode 100644 index 0000000000..a9299de8e5 --- /dev/null +++ b/tests/exhaustive/basic/set07/expected/model_3_1_1.eprime @@ -0,0 +1,22 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_Occurrence: matrix indexed by [int(1..4)] of bool +branching on [x_Occurrence, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] +such that + and([or([q6 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q6] = q7_1 + | q6 : int(1..4)]) + /\ !x_Occurrence[q7_2] + | q7_1 : int(1..3), q7_2 : int(4..9)]), + and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] + | q1 : int(1..3)]), + and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..4)]), + and([x_Occurrence[q8] -> + or([q10 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q10] = q8 + | q10 : int(1..4)]) + | q8 : int(1..4)]), + and([q12 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q12]] + | q12 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set07/expected/model_3_1_2-solution000001.solution b/tests/exhaustive/basic/set07/expected/model_3_1_2-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set07/expected/model_3_1_2-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set07/expected/model_3_1_2.eprime b/tests/exhaustive/basic/set07/expected/model_3_1_2.eprime new file mode 100644 index 0000000000..8897452e59 --- /dev/null +++ b/tests/exhaustive/basic/set07/expected/model_3_1_2.eprime @@ -0,0 +1,41 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_Occurrence: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +branching on + [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_Occurrence] +such that + and([or([q23 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q23] = q24_1 + | q23 : int(1..4)]) + /\ !x_Occurrence[q24_2] + | q24_1 : int(1..3), q24_2 : int(4..9)]), + and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] + | q1 : int(1..3)]), + and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..4)]), + and([x_Occurrence[q25] -> + or([q27 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q27] = q25 + | q27 : int(1..4)]) + | q25 : int(1..4)]), + and([q29 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q29]] + | q29 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q5] < x_ExplicitVarSizeWithDummy[q5 + 1] \/ x_ExplicitVarSizeWithDummy[q5] = 5 + | q5 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q6] = 5 -> x_ExplicitVarSizeWithDummy[q6 + 1] = 5 | q6 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q10] != 5 -> + or([q12 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q12] = x_ExplicitVarSizeWithDummy[q10] + | q12 : int(1..4)]) + | q10 : int(1..4)]), + and([q14 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithDummy[q16] != 5 /\ + x_ExplicitVarSizeWithDummy[q16] = x_ExplicitVarSizeWithMarker_Values[q14] + | q16 : int(1..4)]) + | q14 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q18] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q18]] | q18 : int(1..4)]), + and([x_Occurrence[q19] -> + or([x_ExplicitVarSizeWithDummy[q21] != 5 /\ x_ExplicitVarSizeWithDummy[q21] = q19 | q21 : int(1..4)]) + | q19 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set07/expected/model_3_1_4-solution000001.solution b/tests/exhaustive/basic/set07/expected/model_3_1_4-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set07/expected/model_3_1_4-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set07/expected/model_3_1_4.eprime b/tests/exhaustive/basic/set07/expected/model_3_1_4.eprime new file mode 100644 index 0000000000..e3716d35cd --- /dev/null +++ b/tests/exhaustive/basic/set07/expected/model_3_1_4.eprime @@ -0,0 +1,46 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_Occurrence: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +branching on + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithMarker_Marker, + x_ExplicitVarSizeWithMarker_Values, x_Occurrence] +such that + and([or([q24 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q24] = q25_1 + | q24 : int(1..4)]) + /\ !x_Occurrence[q25_2] + | q25_1 : int(1..3), q25_2 : int(4..9)]), + and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] + | q1 : int(1..3)]), + and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..4)]), + and([x_Occurrence[q26] -> + or([q28 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q28] = q26 + | q28 : int(1..4)]) + | q26 : int(1..4)]), + and([q30 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q30]] + | q30 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q5 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q5] < x_ExplicitVarSizeWithFlags_Values[q5 + 1] + | q5 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q6] = false -> x_ExplicitVarSizeWithFlags_Values[q6] = 1 | q6 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q7] | q7 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q11] -> + or([q13 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q13] = x_ExplicitVarSizeWithFlags_Values[q11] + | q13 : int(1..4)]) + | q11 : int(1..4)]), + and([q15 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithFlags_Flags[q17] /\ + x_ExplicitVarSizeWithFlags_Values[q17] = x_ExplicitVarSizeWithMarker_Values[q15] + | q17 : int(1..4)]) + | q15 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q19] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q19]] + | q19 : int(1..4)]), + and([x_Occurrence[q20] -> + or([x_ExplicitVarSizeWithFlags_Flags[q22] /\ x_ExplicitVarSizeWithFlags_Values[q22] = q20 | q22 : int(1..4)]) + | q20 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set07/expected/model_3_2_1-solution000001.solution b/tests/exhaustive/basic/set07/expected/model_3_2_1-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set07/expected/model_3_2_1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set07/expected/model_3_2_1.eprime b/tests/exhaustive/basic/set07/expected/model_3_2_1.eprime new file mode 100644 index 0000000000..a4f4f9d9e3 --- /dev/null +++ b/tests/exhaustive/basic/set07/expected/model_3_2_1.eprime @@ -0,0 +1,41 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +find x_Occurrence: matrix indexed by [int(1..4)] of bool +branching on + [x_Occurrence, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy] +such that + and([or([q18 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q18] = q21_1 + | q18 : int(1..4)]) + /\ !or([x_ExplicitVarSizeWithDummy[q20] != 5 /\ x_ExplicitVarSizeWithDummy[q20] = q21_2 | q20 : int(1..4)]) + | q21_1 : int(1..3), q21_2 : int(4..9)]), + and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] + | q1 : int(1..3)]), + and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q4] < x_ExplicitVarSizeWithDummy[q4 + 1] \/ x_ExplicitVarSizeWithDummy[q4] = 5 + | q4 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q5] = 5 -> x_ExplicitVarSizeWithDummy[q5 + 1] = 5 | q5 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q9] != 5 -> + or([q11 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q11] = x_ExplicitVarSizeWithDummy[q9] + | q11 : int(1..4)]) + | q9 : int(1..4)]), + and([q13 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithDummy[q15] != 5 /\ + x_ExplicitVarSizeWithDummy[q15] = x_ExplicitVarSizeWithMarker_Values[q13] + | q15 : int(1..4)]) + | q13 : int(1..4)]), + and([x_Occurrence[q22] -> + or([q24 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q24] = q22 + | q24 : int(1..4)]) + | q22 : int(1..4)]), + and([q26 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q26]] + | q26 : int(1..4)]), + and([x_Occurrence[q27] -> + or([x_ExplicitVarSizeWithDummy[q29] != 5 /\ x_ExplicitVarSizeWithDummy[q29] = q27 | q29 : int(1..4)]) + | q27 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q31] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q31]] | q31 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set07/expected/model_3_2_2-solution000001.solution b/tests/exhaustive/basic/set07/expected/model_3_2_2-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set07/expected/model_3_2_2-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set07/expected/model_3_2_2.eprime b/tests/exhaustive/basic/set07/expected/model_3_2_2.eprime new file mode 100644 index 0000000000..a7e9b28aa7 --- /dev/null +++ b/tests/exhaustive/basic/set07/expected/model_3_2_2.eprime @@ -0,0 +1,29 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +branching on [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] +such that + and([or([q17 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q17] = q20_1 + | q17 : int(1..4)]) + /\ !or([x_ExplicitVarSizeWithDummy[q19] != 5 /\ x_ExplicitVarSizeWithDummy[q19] = q20_2 | q19 : int(1..4)]) + | q20_1 : int(1..3), q20_2 : int(4..9)]), + and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] + | q1 : int(1..3)]), + and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q4] < x_ExplicitVarSizeWithDummy[q4 + 1] \/ x_ExplicitVarSizeWithDummy[q4] = 5 + | q4 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q5] = 5 -> x_ExplicitVarSizeWithDummy[q5 + 1] = 5 | q5 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q9] != 5 -> + or([q11 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q11] = x_ExplicitVarSizeWithDummy[q9] + | q11 : int(1..4)]) + | q9 : int(1..4)]), + and([q13 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithDummy[q15] != 5 /\ + x_ExplicitVarSizeWithDummy[q15] = x_ExplicitVarSizeWithMarker_Values[q13] + | q15 : int(1..4)]) + | q13 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set07/expected/model_3_2_4-solution000001.solution b/tests/exhaustive/basic/set07/expected/model_3_2_4-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set07/expected/model_3_2_4-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set07/expected/model_3_2_4.eprime b/tests/exhaustive/basic/set07/expected/model_3_2_4.eprime new file mode 100644 index 0000000000..9ba2c2499e --- /dev/null +++ b/tests/exhaustive/basic/set07/expected/model_3_2_4.eprime @@ -0,0 +1,59 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +branching on + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithMarker_Marker, + x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy] +such that + and([or([q38 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q38] = q41_1 + | q38 : int(1..4)]) + /\ !or([x_ExplicitVarSizeWithDummy[q40] != 5 /\ x_ExplicitVarSizeWithDummy[q40] = q41_2 | q40 : int(1..4)]) + | q41_1 : int(1..3), q41_2 : int(4..9)]), + and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] + | q1 : int(1..3)]), + and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q4] < x_ExplicitVarSizeWithDummy[q4 + 1] \/ x_ExplicitVarSizeWithDummy[q4] = 5 + | q4 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q5] = 5 -> x_ExplicitVarSizeWithDummy[q5 + 1] = 5 | q5 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q9] != 5 -> + or([q11 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q11] = x_ExplicitVarSizeWithDummy[q9] + | q11 : int(1..4)]) + | q9 : int(1..4)]), + and([q13 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithDummy[q15] != 5 /\ + x_ExplicitVarSizeWithDummy[q15] = x_ExplicitVarSizeWithMarker_Values[q13] + | q15 : int(1..4)]) + | q13 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q16 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q16] < x_ExplicitVarSizeWithFlags_Values[q16 + 1] + | q16 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q17] = false -> x_ExplicitVarSizeWithFlags_Values[q17] = 1 + | q17 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q18 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q18] | q18 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q22] -> + or([q24 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q24] = x_ExplicitVarSizeWithFlags_Values[q22] + | q24 : int(1..4)]) + | q22 : int(1..4)]), + and([q26 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithFlags_Flags[q28] /\ + x_ExplicitVarSizeWithFlags_Values[q28] = x_ExplicitVarSizeWithMarker_Values[q26] + | q28 : int(1..4)]) + | q26 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q30] -> + or([x_ExplicitVarSizeWithDummy[q32] != 5 /\ + x_ExplicitVarSizeWithDummy[q32] = x_ExplicitVarSizeWithFlags_Values[q30] + | q32 : int(1..4)]) + | q30 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q34] != 5 -> + or([x_ExplicitVarSizeWithFlags_Flags[q36] /\ + x_ExplicitVarSizeWithFlags_Values[q36] = x_ExplicitVarSizeWithDummy[q34] + | q36 : int(1..4)]) + | q34 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set07/expected/model_3_3_1-solution000001.solution b/tests/exhaustive/basic/set07/expected/model_3_3_1-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set07/expected/model_3_3_1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set07/expected/model_3_3_1.eprime b/tests/exhaustive/basic/set07/expected/model_3_3_1.eprime new file mode 100644 index 0000000000..f69ec68546 --- /dev/null +++ b/tests/exhaustive/basic/set07/expected/model_3_3_1.eprime @@ -0,0 +1,24 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_Occurrence: matrix indexed by [int(1..4)] of bool +branching on [x_Occurrence, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] +such that + and([or([q6 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q6] = q9_1 + | q6 : int(1..4)]) + /\ + !or([q8 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q8] = q9_2 + | q8 : int(1..4)]) + | q9_1 : int(1..3), q9_2 : int(4..9)]), + and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] + | q1 : int(1..3)]), + and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..4)]), + and([x_Occurrence[q10] -> + or([q12 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q12] = q10 + | q12 : int(1..4)]) + | q10 : int(1..4)]), + and([q14 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q14]] + | q14 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set07/expected/model_3_3_2-solution000001.solution b/tests/exhaustive/basic/set07/expected/model_3_3_2-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set07/expected/model_3_3_2-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set07/expected/model_3_3_2.eprime b/tests/exhaustive/basic/set07/expected/model_3_3_2.eprime new file mode 100644 index 0000000000..adc45bc4e1 --- /dev/null +++ b/tests/exhaustive/basic/set07/expected/model_3_3_2.eprime @@ -0,0 +1,31 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +branching on [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] +such that + and([or([q17 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q17] = q20_1 + | q17 : int(1..4)]) + /\ + !or([q19 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q19] = q20_2 + | q19 : int(1..4)]) + | q20_1 : int(1..3), q20_2 : int(4..9)]), + and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] + | q1 : int(1..3)]), + and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q4] < x_ExplicitVarSizeWithDummy[q4 + 1] \/ x_ExplicitVarSizeWithDummy[q4] = 5 + | q4 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q5] = 5 -> x_ExplicitVarSizeWithDummy[q5 + 1] = 5 | q5 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q9] != 5 -> + or([q11 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q11] = x_ExplicitVarSizeWithDummy[q9] + | q11 : int(1..4)]) + | q9 : int(1..4)]), + and([q13 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithDummy[q15] != 5 /\ + x_ExplicitVarSizeWithDummy[q15] = x_ExplicitVarSizeWithMarker_Values[q13] + | q15 : int(1..4)]) + | q13 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set07/expected/model_3_3_3-solution000001.solution b/tests/exhaustive/basic/set07/expected/model_3_3_3-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set07/expected/model_3_3_3-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set07/expected/model_3_3_3.eprime b/tests/exhaustive/basic/set07/expected/model_3_3_3.eprime new file mode 100644 index 0000000000..fbcbcb55a2 --- /dev/null +++ b/tests/exhaustive/basic/set07/expected/model_3_3_3.eprime @@ -0,0 +1,17 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +branching on [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] +such that + and([or([q5 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q5] = q8_1 + | q5 : int(1..4)]) + /\ + !or([q7 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q7] = q8_2 + | q7 : int(1..4)]) + | q8_1 : int(1..3), q8_2 : int(4..9)]), + and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] + | q1 : int(1..3)]), + and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set07/expected/model_3_3_4-solution000001.solution b/tests/exhaustive/basic/set07/expected/model_3_3_4-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set07/expected/model_3_3_4-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set07/expected/model_3_3_4.eprime b/tests/exhaustive/basic/set07/expected/model_3_3_4.eprime new file mode 100644 index 0000000000..50a1db36c3 --- /dev/null +++ b/tests/exhaustive/basic/set07/expected/model_3_3_4.eprime @@ -0,0 +1,36 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +branching on + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithMarker_Marker, + x_ExplicitVarSizeWithMarker_Values] +such that + and([or([q18 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q18] = q21_1 + | q18 : int(1..4)]) + /\ + !or([q20 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q20] = q21_2 + | q20 : int(1..4)]) + | q21_1 : int(1..3), q21_2 : int(4..9)]), + and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] + | q1 : int(1..3)]), + and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q4] < x_ExplicitVarSizeWithFlags_Values[q4 + 1] + | q4 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q5] = false -> x_ExplicitVarSizeWithFlags_Values[q5] = 1 | q5 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q6] | q6 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q10] -> + or([q12 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q12] = x_ExplicitVarSizeWithFlags_Values[q10] + | q12 : int(1..4)]) + | q10 : int(1..4)]), + and([q14 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithFlags_Flags[q16] /\ + x_ExplicitVarSizeWithFlags_Values[q16] = x_ExplicitVarSizeWithMarker_Values[q14] + | q16 : int(1..4)]) + | q14 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set07/expected/model_3_4_1-solution000001.solution b/tests/exhaustive/basic/set07/expected/model_3_4_1-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set07/expected/model_3_4_1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set07/expected/model_3_4_1.eprime b/tests/exhaustive/basic/set07/expected/model_3_4_1.eprime new file mode 100644 index 0000000000..61e664ad10 --- /dev/null +++ b/tests/exhaustive/basic/set07/expected/model_3_4_1.eprime @@ -0,0 +1,48 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_Occurrence: matrix indexed by [int(1..4)] of bool +branching on + [x_Occurrence, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, + x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] +such that + and([or([q29 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q29] = q32_1 + | q29 : int(1..4)]) + /\ + !or([x_ExplicitVarSizeWithFlags_Flags[q31] /\ x_ExplicitVarSizeWithFlags_Values[q31] = q32_2 + | q31 : int(1..4)]) + | q32_1 : int(1..3), q32_2 : int(4..9)]), + and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] + | q1 : int(1..3)]), + and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q4] < x_ExplicitVarSizeWithFlags_Values[q4 + 1] + | q4 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q5] = false -> x_ExplicitVarSizeWithFlags_Values[q5] = 1 | q5 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q6] | q6 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q10] -> + or([q12 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q12] = x_ExplicitVarSizeWithFlags_Values[q10] + | q12 : int(1..4)]) + | q10 : int(1..4)]), + and([q14 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithFlags_Flags[q16] /\ + x_ExplicitVarSizeWithFlags_Values[q16] = x_ExplicitVarSizeWithMarker_Values[q14] + | q16 : int(1..4)]) + | q14 : int(1..4)]), + and([x_Occurrence[q18] -> + or([q20 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q20] = q18 + | q20 : int(1..4)]) + | q18 : int(1..4)]), + and([q22 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q22]] + | q22 : int(1..4)]), + and([x_Occurrence[q23] -> + or([x_ExplicitVarSizeWithFlags_Flags[q25] /\ x_ExplicitVarSizeWithFlags_Values[q25] = q23 | q25 : int(1..4)]) + | q23 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q27] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q27]] + | q27 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set07/expected/model_3_4_2-solution000001.solution b/tests/exhaustive/basic/set07/expected/model_3_4_2-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set07/expected/model_3_4_2-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set07/expected/model_3_4_2.eprime b/tests/exhaustive/basic/set07/expected/model_3_4_2.eprime new file mode 100644 index 0000000000..b565f5f402 --- /dev/null +++ b/tests/exhaustive/basic/set07/expected/model_3_4_2.eprime @@ -0,0 +1,60 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +branching on + [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, + x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] +such that + and([or([q38 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q38] = q41_1 + | q38 : int(1..4)]) + /\ + !or([x_ExplicitVarSizeWithFlags_Flags[q40] /\ x_ExplicitVarSizeWithFlags_Values[q40] = q41_2 + | q40 : int(1..4)]) + | q41_1 : int(1..3), q41_2 : int(4..9)]), + and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] + | q1 : int(1..3)]), + and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q4] < x_ExplicitVarSizeWithFlags_Values[q4 + 1] + | q4 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q5] = false -> x_ExplicitVarSizeWithFlags_Values[q5] = 1 | q5 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q6] | q6 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q10] -> + or([q12 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q12] = x_ExplicitVarSizeWithFlags_Values[q10] + | q12 : int(1..4)]) + | q10 : int(1..4)]), + and([q14 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithFlags_Flags[q16] /\ + x_ExplicitVarSizeWithFlags_Values[q16] = x_ExplicitVarSizeWithMarker_Values[q14] + | q16 : int(1..4)]) + | q14 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q17] < x_ExplicitVarSizeWithDummy[q17 + 1] \/ x_ExplicitVarSizeWithDummy[q17] = 5 + | q17 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q18] = 5 -> x_ExplicitVarSizeWithDummy[q18 + 1] = 5 | q18 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q22] != 5 -> + or([q24 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q24] = x_ExplicitVarSizeWithDummy[q22] + | q24 : int(1..4)]) + | q22 : int(1..4)]), + and([q26 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithDummy[q28] != 5 /\ + x_ExplicitVarSizeWithDummy[q28] = x_ExplicitVarSizeWithMarker_Values[q26] + | q28 : int(1..4)]) + | q26 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q30] != 5 -> + or([x_ExplicitVarSizeWithFlags_Flags[q32] /\ + x_ExplicitVarSizeWithFlags_Values[q32] = x_ExplicitVarSizeWithDummy[q30] + | q32 : int(1..4)]) + | q30 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q34] -> + or([x_ExplicitVarSizeWithDummy[q36] != 5 /\ + x_ExplicitVarSizeWithDummy[q36] = x_ExplicitVarSizeWithFlags_Values[q34] + | q36 : int(1..4)]) + | q34 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set07/expected/model_3_4_3-solution000001.solution b/tests/exhaustive/basic/set07/expected/model_3_4_3-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set07/expected/model_3_4_3-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set07/expected/model_3_4_3.eprime b/tests/exhaustive/basic/set07/expected/model_3_4_3.eprime new file mode 100644 index 0000000000..d801442667 --- /dev/null +++ b/tests/exhaustive/basic/set07/expected/model_3_4_3.eprime @@ -0,0 +1,36 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +branching on + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithMarker_Marker, + x_ExplicitVarSizeWithMarker_Values] +such that + and([or([q18 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q18] = q21_1 + | q18 : int(1..4)]) + /\ + !or([x_ExplicitVarSizeWithFlags_Flags[q20] /\ x_ExplicitVarSizeWithFlags_Values[q20] = q21_2 + | q20 : int(1..4)]) + | q21_1 : int(1..3), q21_2 : int(4..9)]), + and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] + | q1 : int(1..3)]), + and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q4] < x_ExplicitVarSizeWithFlags_Values[q4 + 1] + | q4 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q5] = false -> x_ExplicitVarSizeWithFlags_Values[q5] = 1 | q5 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q6] | q6 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q10] -> + or([q12 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q12] = x_ExplicitVarSizeWithFlags_Values[q10] + | q12 : int(1..4)]) + | q10 : int(1..4)]), + and([q14 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithFlags_Flags[q16] /\ + x_ExplicitVarSizeWithFlags_Values[q16] = x_ExplicitVarSizeWithMarker_Values[q14] + | q16 : int(1..4)]) + | q14 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set07/expected/model_4_1_1-solution000001.solution b/tests/exhaustive/basic/set07/expected/model_4_1_1-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set07/expected/model_4_1_1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set07/expected/model_4_1_1.eprime b/tests/exhaustive/basic/set07/expected/model_4_1_1.eprime new file mode 100644 index 0000000000..981837a4f9 --- /dev/null +++ b/tests/exhaustive/basic/set07/expected/model_4_1_1.eprime @@ -0,0 +1,21 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_Occurrence: matrix indexed by [int(1..4)] of bool +branching on [x_Occurrence, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] +such that + and([or([x_ExplicitVarSizeWithFlags_Flags[q13] /\ x_ExplicitVarSizeWithFlags_Values[q13] = q14_1 | q13 : int(1..4)]) + /\ !x_Occurrence[q14_2] + | q14_1 : int(1..3), q14_2 : int(4..9)]), + and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), + and([x_Occurrence[q7] -> + or([x_ExplicitVarSizeWithFlags_Flags[q9] /\ x_ExplicitVarSizeWithFlags_Values[q9] = q7 | q9 : int(1..4)]) + | q7 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q11] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q11]] + | q11 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set07/expected/model_4_1_2-solution000001.solution b/tests/exhaustive/basic/set07/expected/model_4_1_2-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set07/expected/model_4_1_2-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set07/expected/model_4_1_2.eprime b/tests/exhaustive/basic/set07/expected/model_4_1_2.eprime new file mode 100644 index 0000000000..3c2a07f559 --- /dev/null +++ b/tests/exhaustive/basic/set07/expected/model_4_1_2.eprime @@ -0,0 +1,40 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_Occurrence: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +branching on + [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_Occurrence] +such that + and([or([x_ExplicitVarSizeWithFlags_Flags[q30] /\ x_ExplicitVarSizeWithFlags_Values[q30] = q31_1 | q30 : int(1..4)]) + /\ !x_Occurrence[q31_2] + | q31_1 : int(1..3), q31_2 : int(4..9)]), + and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), + and([x_Occurrence[q24] -> + or([x_ExplicitVarSizeWithFlags_Flags[q26] /\ x_ExplicitVarSizeWithFlags_Values[q26] = q24 | q26 : int(1..4)]) + | q24 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q28] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q28]] + | q28 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q7] < x_ExplicitVarSizeWithDummy[q7 + 1] \/ x_ExplicitVarSizeWithDummy[q7] = 5 + | q7 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q8] = 5 -> x_ExplicitVarSizeWithDummy[q8 + 1] = 5 | q8 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q12] != 5 -> + or([x_ExplicitVarSizeWithFlags_Flags[q14] /\ + x_ExplicitVarSizeWithFlags_Values[q14] = x_ExplicitVarSizeWithDummy[q12] + | q14 : int(1..4)]) + | q12 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q16] -> + or([x_ExplicitVarSizeWithDummy[q18] != 5 /\ + x_ExplicitVarSizeWithDummy[q18] = x_ExplicitVarSizeWithFlags_Values[q16] + | q18 : int(1..4)]) + | q16 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q20] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q20]] | q20 : int(1..4)]), + and([x_Occurrence[q21] -> + or([x_ExplicitVarSizeWithDummy[q23] != 5 /\ x_ExplicitVarSizeWithDummy[q23] = q21 | q23 : int(1..4)]) + | q21 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set07/expected/model_4_1_3-solution000001.solution b/tests/exhaustive/basic/set07/expected/model_4_1_3-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set07/expected/model_4_1_3-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set07/expected/model_4_1_3.eprime b/tests/exhaustive/basic/set07/expected/model_4_1_3.eprime new file mode 100644 index 0000000000..00c2bc51f1 --- /dev/null +++ b/tests/exhaustive/basic/set07/expected/model_4_1_3.eprime @@ -0,0 +1,45 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_Occurrence: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +branching on + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithFlags_Flags, + x_ExplicitVarSizeWithFlags_Values, x_Occurrence] +such that + and([or([x_ExplicitVarSizeWithFlags_Flags[q29] /\ x_ExplicitVarSizeWithFlags_Values[q29] = q30_1 | q29 : int(1..4)]) + /\ !x_Occurrence[q30_2] + | q30_1 : int(1..3), q30_2 : int(4..9)]), + and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), + and([x_Occurrence[q23] -> + or([x_ExplicitVarSizeWithFlags_Flags[q25] /\ x_ExplicitVarSizeWithFlags_Values[q25] = q23 | q25 : int(1..4)]) + | q23 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q27] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q27]] + | q27 : int(1..4)]), + and([q7 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q7] < x_ExplicitVarSizeWithMarker_Values[q7 + 1] + | q7 : int(1..3)]), + and([q8 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q8] = 1 | q8 : int(1..4)]), + and([q11 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithFlags_Flags[q13] /\ + x_ExplicitVarSizeWithFlags_Values[q13] = x_ExplicitVarSizeWithMarker_Values[q11] + | q13 : int(1..4)]) + | q11 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q15] -> + or([q17 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q17] = x_ExplicitVarSizeWithFlags_Values[q15] + | q17 : int(1..4)]) + | q15 : int(1..4)]), + and([q19 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q19]] + | q19 : int(1..4)]), + and([x_Occurrence[q20] -> + or([q22 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q22] = q20 + | q22 : int(1..4)]) + | q20 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set07/expected/model_4_2_1-solution000001.solution b/tests/exhaustive/basic/set07/expected/model_4_2_1-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set07/expected/model_4_2_1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set07/expected/model_4_2_1.eprime b/tests/exhaustive/basic/set07/expected/model_4_2_1.eprime new file mode 100644 index 0000000000..c197a46407 --- /dev/null +++ b/tests/exhaustive/basic/set07/expected/model_4_2_1.eprime @@ -0,0 +1,40 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +find x_Occurrence: matrix indexed by [int(1..4)] of bool +branching on + [x_Occurrence, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy] +such that + and([or([x_ExplicitVarSizeWithFlags_Flags[q30] /\ x_ExplicitVarSizeWithFlags_Values[q30] = q33_1 | q30 : int(1..4)]) + /\ !or([x_ExplicitVarSizeWithDummy[q32] != 5 /\ x_ExplicitVarSizeWithDummy[q32] = q33_2 | q32 : int(1..4)]) + | q33_1 : int(1..3), q33_2 : int(4..9)]), + and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q6] < x_ExplicitVarSizeWithDummy[q6 + 1] \/ x_ExplicitVarSizeWithDummy[q6] = 5 + | q6 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q7] = 5 -> x_ExplicitVarSizeWithDummy[q7 + 1] = 5 | q7 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q11] != 5 -> + or([x_ExplicitVarSizeWithFlags_Flags[q13] /\ + x_ExplicitVarSizeWithFlags_Values[q13] = x_ExplicitVarSizeWithDummy[q11] + | q13 : int(1..4)]) + | q11 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q15] -> + or([x_ExplicitVarSizeWithDummy[q17] != 5 /\ + x_ExplicitVarSizeWithDummy[q17] = x_ExplicitVarSizeWithFlags_Values[q15] + | q17 : int(1..4)]) + | q15 : int(1..4)]), + and([x_Occurrence[q19] -> + or([x_ExplicitVarSizeWithFlags_Flags[q21] /\ x_ExplicitVarSizeWithFlags_Values[q21] = q19 | q21 : int(1..4)]) + | q19 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q23] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q23]] + | q23 : int(1..4)]), + and([x_Occurrence[q24] -> + or([x_ExplicitVarSizeWithDummy[q26] != 5 /\ x_ExplicitVarSizeWithDummy[q26] = q24 | q26 : int(1..4)]) + | q24 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q28] != 5 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q28]] | q28 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set07/expected/model_4_2_2-solution000001.solution b/tests/exhaustive/basic/set07/expected/model_4_2_2-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set07/expected/model_4_2_2-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set07/expected/model_4_2_2.eprime b/tests/exhaustive/basic/set07/expected/model_4_2_2.eprime new file mode 100644 index 0000000000..8c36b6b158 --- /dev/null +++ b/tests/exhaustive/basic/set07/expected/model_4_2_2.eprime @@ -0,0 +1,29 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +branching on [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] +such that + and([or([x_ExplicitVarSizeWithFlags_Flags[q19] /\ x_ExplicitVarSizeWithFlags_Values[q19] = q22_1 | q19 : int(1..4)]) + /\ !or([x_ExplicitVarSizeWithDummy[q21] != 5 /\ x_ExplicitVarSizeWithDummy[q21] = q22_2 | q21 : int(1..4)]) + | q22_1 : int(1..3), q22_2 : int(4..9)]), + and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q6] < x_ExplicitVarSizeWithDummy[q6 + 1] \/ x_ExplicitVarSizeWithDummy[q6] = 5 + | q6 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q7] = 5 -> x_ExplicitVarSizeWithDummy[q7 + 1] = 5 | q7 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q11] != 5 -> + or([x_ExplicitVarSizeWithFlags_Flags[q13] /\ + x_ExplicitVarSizeWithFlags_Values[q13] = x_ExplicitVarSizeWithDummy[q11] + | q13 : int(1..4)]) + | q11 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q15] -> + or([x_ExplicitVarSizeWithDummy[q17] != 5 /\ + x_ExplicitVarSizeWithDummy[q17] = x_ExplicitVarSizeWithFlags_Values[q15] + | q17 : int(1..4)]) + | q15 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set07/expected/model_4_2_3-solution000001.solution b/tests/exhaustive/basic/set07/expected/model_4_2_3-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set07/expected/model_4_2_3-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set07/expected/model_4_2_3.eprime b/tests/exhaustive/basic/set07/expected/model_4_2_3.eprime new file mode 100644 index 0000000000..99e67ea897 --- /dev/null +++ b/tests/exhaustive/basic/set07/expected/model_4_2_3.eprime @@ -0,0 +1,57 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +branching on + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithFlags_Flags, + x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy] +such that + and([or([x_ExplicitVarSizeWithFlags_Flags[q38] /\ x_ExplicitVarSizeWithFlags_Values[q38] = q41_1 | q38 : int(1..4)]) + /\ !or([x_ExplicitVarSizeWithDummy[q40] != 5 /\ x_ExplicitVarSizeWithDummy[q40] = q41_2 | q40 : int(1..4)]) + | q41_1 : int(1..3), q41_2 : int(4..9)]), + and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q6] < x_ExplicitVarSizeWithDummy[q6 + 1] \/ x_ExplicitVarSizeWithDummy[q6] = 5 + | q6 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q7] = 5 -> x_ExplicitVarSizeWithDummy[q7 + 1] = 5 | q7 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q11] != 5 -> + or([x_ExplicitVarSizeWithFlags_Flags[q13] /\ + x_ExplicitVarSizeWithFlags_Values[q13] = x_ExplicitVarSizeWithDummy[q11] + | q13 : int(1..4)]) + | q11 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q15] -> + or([x_ExplicitVarSizeWithDummy[q17] != 5 /\ + x_ExplicitVarSizeWithDummy[q17] = x_ExplicitVarSizeWithFlags_Values[q15] + | q17 : int(1..4)]) + | q15 : int(1..4)]), + and([q18 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q18] < x_ExplicitVarSizeWithMarker_Values[q18 + 1] + | q18 : int(1..3)]), + and([q19 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q19] = 1 | q19 : int(1..4)]), + and([q22 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithFlags_Flags[q24] /\ + x_ExplicitVarSizeWithFlags_Values[q24] = x_ExplicitVarSizeWithMarker_Values[q22] + | q24 : int(1..4)]) + | q22 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q26] -> + or([q28 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q28] = x_ExplicitVarSizeWithFlags_Values[q26] + | q28 : int(1..4)]) + | q26 : int(1..4)]), + and([q30 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithDummy[q32] != 5 /\ + x_ExplicitVarSizeWithDummy[q32] = x_ExplicitVarSizeWithMarker_Values[q30] + | q32 : int(1..4)]) + | q30 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q34] != 5 -> + or([q36 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q36] = x_ExplicitVarSizeWithDummy[q34] + | q36 : int(1..4)]) + | q34 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set07/expected/model_4_3_1-solution000001.solution b/tests/exhaustive/basic/set07/expected/model_4_3_1-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set07/expected/model_4_3_1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set07/expected/model_4_3_1.eprime b/tests/exhaustive/basic/set07/expected/model_4_3_1.eprime new file mode 100644 index 0000000000..f8b5b0c4f9 --- /dev/null +++ b/tests/exhaustive/basic/set07/expected/model_4_3_1.eprime @@ -0,0 +1,47 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_Occurrence: matrix indexed by [int(1..4)] of bool +branching on + [x_Occurrence, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, + x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] +such that + and([or([x_ExplicitVarSizeWithFlags_Flags[q29] /\ x_ExplicitVarSizeWithFlags_Values[q29] = q32_1 | q29 : int(1..4)]) + /\ + !or([q31 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q31] = q32_2 + | q31 : int(1..4)]) + | q32_1 : int(1..3), q32_2 : int(4..9)]), + and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), + and([q6 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q6] < x_ExplicitVarSizeWithMarker_Values[q6 + 1] + | q6 : int(1..3)]), + and([q7 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q7] = 1 | q7 : int(1..4)]), + and([q10 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithFlags_Flags[q12] /\ + x_ExplicitVarSizeWithFlags_Values[q12] = x_ExplicitVarSizeWithMarker_Values[q10] + | q12 : int(1..4)]) + | q10 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q14] -> + or([q16 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q16] = x_ExplicitVarSizeWithFlags_Values[q14] + | q16 : int(1..4)]) + | q14 : int(1..4)]), + and([x_Occurrence[q18] -> + or([x_ExplicitVarSizeWithFlags_Flags[q20] /\ x_ExplicitVarSizeWithFlags_Values[q20] = q18 | q20 : int(1..4)]) + | q18 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q22] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q22]] + | q22 : int(1..4)]), + and([x_Occurrence[q23] -> + or([q25 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q25] = q23 + | q25 : int(1..4)]) + | q23 : int(1..4)]), + and([q27 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q27]] + | q27 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set07/expected/model_4_3_2-solution000001.solution b/tests/exhaustive/basic/set07/expected/model_4_3_2-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set07/expected/model_4_3_2-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set07/expected/model_4_3_2.eprime b/tests/exhaustive/basic/set07/expected/model_4_3_2.eprime new file mode 100644 index 0000000000..7b940b4c6d --- /dev/null +++ b/tests/exhaustive/basic/set07/expected/model_4_3_2.eprime @@ -0,0 +1,59 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +branching on + [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, + x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] +such that + and([or([x_ExplicitVarSizeWithFlags_Flags[q38] /\ x_ExplicitVarSizeWithFlags_Values[q38] = q41_1 | q38 : int(1..4)]) + /\ + !or([q40 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q40] = q41_2 + | q40 : int(1..4)]) + | q41_1 : int(1..3), q41_2 : int(4..9)]), + and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), + and([q6 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q6] < x_ExplicitVarSizeWithMarker_Values[q6 + 1] + | q6 : int(1..3)]), + and([q7 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q7] = 1 | q7 : int(1..4)]), + and([q10 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithFlags_Flags[q12] /\ + x_ExplicitVarSizeWithFlags_Values[q12] = x_ExplicitVarSizeWithMarker_Values[q10] + | q12 : int(1..4)]) + | q10 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q14] -> + or([q16 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q16] = x_ExplicitVarSizeWithFlags_Values[q14] + | q16 : int(1..4)]) + | q14 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q17] < x_ExplicitVarSizeWithDummy[q17 + 1] \/ x_ExplicitVarSizeWithDummy[q17] = 5 + | q17 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q18] = 5 -> x_ExplicitVarSizeWithDummy[q18 + 1] = 5 | q18 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q22] != 5 -> + or([x_ExplicitVarSizeWithFlags_Flags[q24] /\ + x_ExplicitVarSizeWithFlags_Values[q24] = x_ExplicitVarSizeWithDummy[q22] + | q24 : int(1..4)]) + | q22 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q26] -> + or([x_ExplicitVarSizeWithDummy[q28] != 5 /\ + x_ExplicitVarSizeWithDummy[q28] = x_ExplicitVarSizeWithFlags_Values[q26] + | q28 : int(1..4)]) + | q26 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q30] != 5 -> + or([q32 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q32] = x_ExplicitVarSizeWithDummy[q30] + | q32 : int(1..4)]) + | q30 : int(1..4)]), + and([q34 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithDummy[q36] != 5 /\ + x_ExplicitVarSizeWithDummy[q36] = x_ExplicitVarSizeWithMarker_Values[q34] + | q36 : int(1..4)]) + | q34 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set07/expected/model_4_3_3-solution000001.solution b/tests/exhaustive/basic/set07/expected/model_4_3_3-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set07/expected/model_4_3_3-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set07/expected/model_4_3_3.eprime b/tests/exhaustive/basic/set07/expected/model_4_3_3.eprime new file mode 100644 index 0000000000..430b2929c9 --- /dev/null +++ b/tests/exhaustive/basic/set07/expected/model_4_3_3.eprime @@ -0,0 +1,35 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +branching on + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithFlags_Flags, + x_ExplicitVarSizeWithFlags_Values] +such that + and([or([x_ExplicitVarSizeWithFlags_Flags[q18] /\ x_ExplicitVarSizeWithFlags_Values[q18] = q21_1 | q18 : int(1..4)]) + /\ + !or([q20 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q20] = q21_2 + | q20 : int(1..4)]) + | q21_1 : int(1..3), q21_2 : int(4..9)]), + and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), + and([q6 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q6] < x_ExplicitVarSizeWithMarker_Values[q6 + 1] + | q6 : int(1..3)]), + and([q7 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q7] = 1 | q7 : int(1..4)]), + and([q10 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithFlags_Flags[q12] /\ + x_ExplicitVarSizeWithFlags_Values[q12] = x_ExplicitVarSizeWithMarker_Values[q10] + | q12 : int(1..4)]) + | q10 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q14] -> + or([q16 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q16] = x_ExplicitVarSizeWithFlags_Values[q14] + | q16 : int(1..4)]) + | q14 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set07/expected/model_4_4_1-solution000001.solution b/tests/exhaustive/basic/set07/expected/model_4_4_1-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set07/expected/model_4_4_1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set07/expected/model_4_4_1.eprime b/tests/exhaustive/basic/set07/expected/model_4_4_1.eprime new file mode 100644 index 0000000000..c330baaa50 --- /dev/null +++ b/tests/exhaustive/basic/set07/expected/model_4_4_1.eprime @@ -0,0 +1,23 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_Occurrence: matrix indexed by [int(1..4)] of bool +branching on [x_Occurrence, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] +such that + and([or([x_ExplicitVarSizeWithFlags_Flags[q13] /\ x_ExplicitVarSizeWithFlags_Values[q13] = q16_1 | q13 : int(1..4)]) + /\ + !or([x_ExplicitVarSizeWithFlags_Flags[q15] /\ x_ExplicitVarSizeWithFlags_Values[q15] = q16_2 + | q15 : int(1..4)]) + | q16_1 : int(1..3), q16_2 : int(4..9)]), + and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), + and([x_Occurrence[q7] -> + or([x_ExplicitVarSizeWithFlags_Flags[q9] /\ x_ExplicitVarSizeWithFlags_Values[q9] = q7 | q9 : int(1..4)]) + | q7 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q11] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q11]] + | q11 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set07/expected/model_4_4_2-solution000001.solution b/tests/exhaustive/basic/set07/expected/model_4_4_2-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set07/expected/model_4_4_2-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set07/expected/model_4_4_2.eprime b/tests/exhaustive/basic/set07/expected/model_4_4_2.eprime new file mode 100644 index 0000000000..73b079af26 --- /dev/null +++ b/tests/exhaustive/basic/set07/expected/model_4_4_2.eprime @@ -0,0 +1,31 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(1..5) +branching on [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] +such that + and([or([x_ExplicitVarSizeWithFlags_Flags[q19] /\ x_ExplicitVarSizeWithFlags_Values[q19] = q22_1 | q19 : int(1..4)]) + /\ + !or([x_ExplicitVarSizeWithFlags_Flags[q21] /\ x_ExplicitVarSizeWithFlags_Values[q21] = q22_2 + | q21 : int(1..4)]) + | q22_1 : int(1..3), q22_2 : int(4..9)]), + and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q6] < x_ExplicitVarSizeWithDummy[q6 + 1] \/ x_ExplicitVarSizeWithDummy[q6] = 5 + | q6 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q7] = 5 -> x_ExplicitVarSizeWithDummy[q7 + 1] = 5 | q7 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q11] != 5 -> + or([x_ExplicitVarSizeWithFlags_Flags[q13] /\ + x_ExplicitVarSizeWithFlags_Values[q13] = x_ExplicitVarSizeWithDummy[q11] + | q13 : int(1..4)]) + | q11 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q15] -> + or([x_ExplicitVarSizeWithDummy[q17] != 5 /\ + x_ExplicitVarSizeWithDummy[q17] = x_ExplicitVarSizeWithFlags_Values[q15] + | q17 : int(1..4)]) + | q15 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set07/expected/model_4_4_3-solution000001.solution b/tests/exhaustive/basic/set07/expected/model_4_4_3-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set07/expected/model_4_4_3-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set07/expected/model_4_4_3.eprime b/tests/exhaustive/basic/set07/expected/model_4_4_3.eprime new file mode 100644 index 0000000000..e83bd430d2 --- /dev/null +++ b/tests/exhaustive/basic/set07/expected/model_4_4_3.eprime @@ -0,0 +1,35 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(1..4) +branching on + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithFlags_Flags, + x_ExplicitVarSizeWithFlags_Values] +such that + and([or([x_ExplicitVarSizeWithFlags_Flags[q18] /\ x_ExplicitVarSizeWithFlags_Values[q18] = q21_1 | q18 : int(1..4)]) + /\ + !or([x_ExplicitVarSizeWithFlags_Flags[q20] /\ x_ExplicitVarSizeWithFlags_Values[q20] = q21_2 + | q20 : int(1..4)]) + | q21_1 : int(1..3), q21_2 : int(4..9)]), + and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), + and([q6 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q6] < x_ExplicitVarSizeWithMarker_Values[q6 + 1] + | q6 : int(1..3)]), + and([q7 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q7] = 1 | q7 : int(1..4)]), + and([q10 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithFlags_Flags[q12] /\ + x_ExplicitVarSizeWithFlags_Values[q12] = x_ExplicitVarSizeWithMarker_Values[q10] + | q12 : int(1..4)]) + | q10 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q14] -> + or([q16 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q16] = x_ExplicitVarSizeWithFlags_Values[q14] + | q16 : int(1..4)]) + | q14 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set07/expected/model_4_4_4-solution000001.solution b/tests/exhaustive/basic/set07/expected/model_4_4_4-solution000001.solution new file mode 100644 index 0000000000..f909cc486d --- /dev/null +++ b/tests/exhaustive/basic/set07/expected/model_4_4_4-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1, 2, 3} diff --git a/tests/exhaustive/basic/set07/expected/model_4_4_4.eprime b/tests/exhaustive/basic/set07/expected/model_4_4_4.eprime new file mode 100644 index 0000000000..c0bc6dbb9a --- /dev/null +++ b/tests/exhaustive/basic/set07/expected/model_4_4_4.eprime @@ -0,0 +1,15 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(1..4) +branching on [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] +such that + and([or([x_ExplicitVarSizeWithFlags_Flags[q7] /\ x_ExplicitVarSizeWithFlags_Values[q7] = q10_1 | q7 : int(1..4)]) /\ + !or([x_ExplicitVarSizeWithFlags_Flags[q9] /\ x_ExplicitVarSizeWithFlags_Values[q9] = q10_2 | q9 : int(1..4)]) + | q10_1 : int(1..3), q10_2 : int(4..9)]), + and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]) + diff --git a/tests/exhaustive/basic/set08/expected/model_1_1-solution000001.solution b/tests/exhaustive/basic/set08/expected/model_1_1-solution000001.solution new file mode 100644 index 0000000000..cb83c94151 --- /dev/null +++ b/tests/exhaustive/basic/set08/expected/model_1_1-solution000001.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {(3, 3), (4, 4)} +$ Visualisation for x +$ 3 3 +$ 4 4 + diff --git a/tests/exhaustive/basic/set08/expected/model_1_1.eprime b/tests/exhaustive/basic/set08/expected/model_1_1.eprime new file mode 100644 index 0000000000..95a52bf5c1 --- /dev/null +++ b/tests/exhaustive/basic/set08/expected/model_1_1.eprime @@ -0,0 +1,25 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..16) +find x_ExplicitVarSizeWithMarker_Values_1: matrix indexed by [int(1..16)] of int(1..4) +find x_ExplicitVarSizeWithMarker_Values_2: matrix indexed by [int(1..16)] of int(3..6) +branching on + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values_1, x_ExplicitVarSizeWithMarker_Values_2] +such that + and([q5 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values_1[q5] = x_ExplicitVarSizeWithMarker_Values_2[q5] + | q5 : int(1..16)]), + and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + flatten([[x_ExplicitVarSizeWithMarker_Values_1[q1]; int(1)], + [x_ExplicitVarSizeWithMarker_Values_2[q1]; int(1)]; + int(1..2)]) + x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values_1[q2] = 1 /\ x_ExplicitVarSizeWithMarker_Values_2[q2] = 3 + | q2 : int(1..16)]), + 2 <= x_ExplicitVarSizeWithMarker_Marker + diff --git a/tests/exhaustive/basic/set08/expected/model_1_2-solution000001.solution b/tests/exhaustive/basic/set08/expected/model_1_2-solution000001.solution new file mode 100644 index 0000000000..cb83c94151 --- /dev/null +++ b/tests/exhaustive/basic/set08/expected/model_1_2-solution000001.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {(3, 3), (4, 4)} +$ Visualisation for x +$ 3 3 +$ 4 4 + diff --git a/tests/exhaustive/basic/set08/expected/model_1_2.eprime b/tests/exhaustive/basic/set08/expected/model_1_2.eprime new file mode 100644 index 0000000000..659a99c583 --- /dev/null +++ b/tests/exhaustive/basic/set08/expected/model_1_2.eprime @@ -0,0 +1,54 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..16) +find x_ExplicitVarSizeWithMarker_Values_1: matrix indexed by [int(1..16)] of int(1..4) +find x_ExplicitVarSizeWithMarker_Values_2: matrix indexed by [int(1..16)] of int(3..6) +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..16)] of bool +find x_ExplicitVarSizeWithFlags_Values_1: matrix indexed by [int(1..16)] of int(1..4) +find x_ExplicitVarSizeWithFlags_Values_2: matrix indexed by [int(1..16)] of int(3..6) +branching on + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values_1, x_ExplicitVarSizeWithFlags_Values_2, + x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values_1, x_ExplicitVarSizeWithMarker_Values_2] +such that + and([q18 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values_1[q18] = x_ExplicitVarSizeWithMarker_Values_2[q18] + | q18 : int(1..16)]), + and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + flatten([[x_ExplicitVarSizeWithMarker_Values_1[q1]; int(1)], + [x_ExplicitVarSizeWithMarker_Values_2[q1]; int(1)]; + int(1..2)]) + x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values_1[q2] = 1 /\ x_ExplicitVarSizeWithMarker_Values_2[q2] = 3 + | q2 : int(1..16)]), + 2 <= x_ExplicitVarSizeWithMarker_Marker, + and([x_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> + flatten([[x_ExplicitVarSizeWithFlags_Values_1[q4]; int(1)], [x_ExplicitVarSizeWithFlags_Values_2[q4]; int(1)]; + int(1..2)]) + + x_ExplicitVarSizeWithFlags_Values_1[q5] = 1 /\ x_ExplicitVarSizeWithFlags_Values_2[q5] = 3 + | q5 : int(1..16)]), + and([x_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q6] | q6 : int(1..15)]), + 2 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q7]) | q7 : int(1..16)]), + and([x_ExplicitVarSizeWithFlags_Flags[q10] -> + or([q12 <= x_ExplicitVarSizeWithMarker_Marker /\ + (x_ExplicitVarSizeWithMarker_Values_1[q12] = x_ExplicitVarSizeWithFlags_Values_1[q10] /\ + x_ExplicitVarSizeWithMarker_Values_2[q12] = x_ExplicitVarSizeWithFlags_Values_2[q10]) + | q12 : int(1..16)]) + | q10 : int(1..16)]), + and([q14 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithFlags_Flags[q16] /\ + (x_ExplicitVarSizeWithFlags_Values_1[q16] = x_ExplicitVarSizeWithMarker_Values_1[q14] /\ + x_ExplicitVarSizeWithFlags_Values_2[q16] = x_ExplicitVarSizeWithMarker_Values_2[q14]) + | q16 : int(1..16)]) + | q14 : int(1..16)]) + diff --git a/tests/exhaustive/basic/set08/expected/model_2_1-solution000001.solution b/tests/exhaustive/basic/set08/expected/model_2_1-solution000001.solution new file mode 100644 index 0000000000..cb83c94151 --- /dev/null +++ b/tests/exhaustive/basic/set08/expected/model_2_1-solution000001.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {(3, 3), (4, 4)} +$ Visualisation for x +$ 3 3 +$ 4 4 + diff --git a/tests/exhaustive/basic/set08/expected/model_2_1.eprime b/tests/exhaustive/basic/set08/expected/model_2_1.eprime new file mode 100644 index 0000000000..cb39a7bb11 --- /dev/null +++ b/tests/exhaustive/basic/set08/expected/model_2_1.eprime @@ -0,0 +1,54 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..16)] of bool +find x_ExplicitVarSizeWithFlags_Values_1: matrix indexed by [int(1..16)] of int(1..4) +find x_ExplicitVarSizeWithFlags_Values_2: matrix indexed by [int(1..16)] of int(3..6) +find x_ExplicitVarSizeWithMarker_Marker: int(0..16) +find x_ExplicitVarSizeWithMarker_Values_1: matrix indexed by [int(1..16)] of int(1..4) +find x_ExplicitVarSizeWithMarker_Values_2: matrix indexed by [int(1..16)] of int(3..6) +branching on + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values_1, x_ExplicitVarSizeWithMarker_Values_2, + x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values_1, x_ExplicitVarSizeWithFlags_Values_2] +such that + and([x_ExplicitVarSizeWithFlags_Flags[q18] -> + x_ExplicitVarSizeWithFlags_Values_1[q18] = x_ExplicitVarSizeWithFlags_Values_2[q18] + | q18 : int(1..16)]), + and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> + flatten([[x_ExplicitVarSizeWithFlags_Values_1[q1]; int(1)], [x_ExplicitVarSizeWithFlags_Values_2[q1]; int(1)]; + int(1..2)]) + + x_ExplicitVarSizeWithFlags_Values_1[q2] = 1 /\ x_ExplicitVarSizeWithFlags_Values_2[q2] = 3 + | q2 : int(1..16)]), + and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..15)]), + 2 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..16)]), + and([q6 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + flatten([[x_ExplicitVarSizeWithMarker_Values_1[q6]; int(1)], + [x_ExplicitVarSizeWithMarker_Values_2[q6]; int(1)]; + int(1..2)]) + x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values_1[q7] = 1 /\ x_ExplicitVarSizeWithMarker_Values_2[q7] = 3 + | q7 : int(1..16)]), + 2 <= x_ExplicitVarSizeWithMarker_Marker, + and([q10 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithFlags_Flags[q12] /\ + (x_ExplicitVarSizeWithFlags_Values_1[q12] = x_ExplicitVarSizeWithMarker_Values_1[q10] /\ + x_ExplicitVarSizeWithFlags_Values_2[q12] = x_ExplicitVarSizeWithMarker_Values_2[q10]) + | q12 : int(1..16)]) + | q10 : int(1..16)]), + and([x_ExplicitVarSizeWithFlags_Flags[q14] -> + or([q16 <= x_ExplicitVarSizeWithMarker_Marker /\ + (x_ExplicitVarSizeWithMarker_Values_1[q16] = x_ExplicitVarSizeWithFlags_Values_1[q14] /\ + x_ExplicitVarSizeWithMarker_Values_2[q16] = x_ExplicitVarSizeWithFlags_Values_2[q14]) + | q16 : int(1..16)]) + | q14 : int(1..16)]) + diff --git a/tests/exhaustive/basic/set08/expected/model_2_2-solution000001.solution b/tests/exhaustive/basic/set08/expected/model_2_2-solution000001.solution new file mode 100644 index 0000000000..cb83c94151 --- /dev/null +++ b/tests/exhaustive/basic/set08/expected/model_2_2-solution000001.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {(3, 3), (4, 4)} +$ Visualisation for x +$ 3 3 +$ 4 4 + diff --git a/tests/exhaustive/basic/set08/expected/model_2_2.eprime b/tests/exhaustive/basic/set08/expected/model_2_2.eprime new file mode 100644 index 0000000000..7cd4078178 --- /dev/null +++ b/tests/exhaustive/basic/set08/expected/model_2_2.eprime @@ -0,0 +1,25 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..16)] of bool +find x_ExplicitVarSizeWithFlags_Values_1: matrix indexed by [int(1..16)] of int(1..4) +find x_ExplicitVarSizeWithFlags_Values_2: matrix indexed by [int(1..16)] of int(3..6) +branching on + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values_1, x_ExplicitVarSizeWithFlags_Values_2] +such that + and([x_ExplicitVarSizeWithFlags_Flags[q7] -> + x_ExplicitVarSizeWithFlags_Values_1[q7] = x_ExplicitVarSizeWithFlags_Values_2[q7] + | q7 : int(1..16)]), + and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> + flatten([[x_ExplicitVarSizeWithFlags_Values_1[q1]; int(1)], [x_ExplicitVarSizeWithFlags_Values_2[q1]; int(1)]; + int(1..2)]) + + x_ExplicitVarSizeWithFlags_Values_1[q2] = 1 /\ x_ExplicitVarSizeWithFlags_Values_2[q2] = 3 + | q2 : int(1..16)]), + and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..15)]), + 2 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..16)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_1_1_1_1-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_1_1_1_1-solution000001.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_1_1_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_1_1_1_1-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_1_1_1_1-solution000002.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_1_1_1-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_1_1_1_1.eprime b/tests/exhaustive/basic/set09/expected/model_1_1_1_1.eprime new file mode 100644 index 0000000000..0a40809bac --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_1_1_1.eprime @@ -0,0 +1,10 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(2..5)] of bool +find y_Occurrence: matrix indexed by [int(2..5)] of bool +branching on [x_Occurrence, y_Occurrence] +such that + and([x_Occurrence[i] /\ y_Occurrence[j] -> i + 2 = j | i : int(2..5), j : int(2..5)]), + 1 <= sum([toInt(x_Occurrence[q1]) | q1 : int(2..5)]), + 1 <= sum([toInt(y_Occurrence[q2]) | q2 : int(2..5)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_1_1_1_2-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_1_1_1_2-solution000001.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_1_1_2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_1_1_1_2-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_1_1_1_2-solution000002.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_1_1_2-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_1_1_1_2.eprime b/tests/exhaustive/basic/set09/expected/model_1_1_1_2.eprime new file mode 100644 index 0000000000..3ef4eacc1f --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_1_1_2.eprime @@ -0,0 +1,19 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(2..5)] of bool +find y_Occurrence: matrix indexed by [int(2..5)] of bool +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +branching on [x_Occurrence, y_ExplicitVarSizeWithDummy, y_Occurrence] +such that + and([x_Occurrence[i] /\ y_Occurrence[j] -> i + 2 = j | i : int(2..5), j : int(2..5)]), + 1 <= sum([toInt(x_Occurrence[q1]) | q1 : int(2..5)]), + 1 <= sum([toInt(y_Occurrence[q2]) | q2 : int(2..5)]), + and([y_ExplicitVarSizeWithDummy[q3] < y_ExplicitVarSizeWithDummy[q3 + 1] \/ y_ExplicitVarSizeWithDummy[q3] = 6 + | q3 : int(1..3)]), + and([y_ExplicitVarSizeWithDummy[q4] = 6 -> y_ExplicitVarSizeWithDummy[q4 + 1] = 6 | q4 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q5] != 6) | q5 : int(1..4)]), + and([y_ExplicitVarSizeWithDummy[q8] != 6 -> y_Occurrence[y_ExplicitVarSizeWithDummy[q8]] | q8 : int(1..4)]), + and([y_Occurrence[q9] -> + or([y_ExplicitVarSizeWithDummy[q11] != 6 /\ y_ExplicitVarSizeWithDummy[q11] = q9 | q11 : int(1..4)]) + | q9 : int(2..5)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_1_1_1_3-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_1_1_1_3-solution000001.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_1_1_3-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_1_1_1_3-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_1_1_1_3-solution000002.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_1_1_3-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_1_1_1_3.eprime b/tests/exhaustive/basic/set09/expected/model_1_1_1_3.eprime new file mode 100644 index 0000000000..0079456c1a --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_1_1_3.eprime @@ -0,0 +1,23 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(2..5)] of bool +find y_Occurrence: matrix indexed by [int(2..5)] of bool +find y_ExplicitVarSizeWithMarker_Marker: int(0..4) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +branching on [x_Occurrence, y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values, y_Occurrence] +such that + and([x_Occurrence[i] /\ y_Occurrence[j] -> i + 2 = j | i : int(2..5), j : int(2..5)]), + 1 <= sum([toInt(x_Occurrence[q1]) | q1 : int(2..5)]), + 1 <= sum([toInt(y_Occurrence[q2]) | q2 : int(2..5)]), + and([q3 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> + y_ExplicitVarSizeWithMarker_Values[q3] < y_ExplicitVarSizeWithMarker_Values[q3 + 1] + | q3 : int(1..3)]), + and([q4 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q4] = 2 | q4 : int(1..4)]), + 1 <= y_ExplicitVarSizeWithMarker_Marker, + and([q7 <= y_ExplicitVarSizeWithMarker_Marker -> y_Occurrence[y_ExplicitVarSizeWithMarker_Values[q7]] + | q7 : int(1..4)]), + and([y_Occurrence[q8] -> + or([q10 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[q10] = q8 + | q10 : int(1..4)]) + | q8 : int(2..5)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_1_1_1_4-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_1_1_1_4-solution000001.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_1_1_4-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_1_1_1_4-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_1_1_1_4-solution000002.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_1_1_4-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_1_1_1_4.eprime b/tests/exhaustive/basic/set09/expected/model_1_1_1_4.eprime new file mode 100644 index 0000000000..ec2d788f13 --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_1_1_4.eprime @@ -0,0 +1,22 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(2..5)] of bool +find y_Occurrence: matrix indexed by [int(2..5)] of bool +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +branching on [x_Occurrence, y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values, y_Occurrence] +such that + and([x_Occurrence[i] /\ y_Occurrence[j] -> i + 2 = j | i : int(2..5), j : int(2..5)]), + 1 <= sum([toInt(x_Occurrence[q1]) | q1 : int(2..5)]), + 1 <= sum([toInt(y_Occurrence[q2]) | q2 : int(2..5)]), + and([y_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> + y_ExplicitVarSizeWithFlags_Values[q3] < y_ExplicitVarSizeWithFlags_Values[q3 + 1] + | q3 : int(1..3)]), + and([y_ExplicitVarSizeWithFlags_Flags[q4] = false -> y_ExplicitVarSizeWithFlags_Values[q4] = 2 | q4 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q5 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q5] | q5 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q6]) | q6 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q9] -> y_Occurrence[y_ExplicitVarSizeWithFlags_Values[q9]] | q9 : int(1..4)]), + and([y_Occurrence[q10] -> + or([y_ExplicitVarSizeWithFlags_Flags[q12] /\ y_ExplicitVarSizeWithFlags_Values[q12] = q10 | q12 : int(1..4)]) + | q10 : int(2..5)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_1_1_2_1-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_1_1_2_1-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_1_2_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_1_1_2_1-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_1_1_2_1-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_1_2_1-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_1_1_2_1.eprime b/tests/exhaustive/basic/set09/expected/model_1_1_2_1.eprime new file mode 100644 index 0000000000..9f2dbd49dd --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_1_2_1.eprime @@ -0,0 +1,19 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(2..5)] of bool +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +find y_Occurrence: matrix indexed by [int(2..5)] of bool +branching on [x_ExplicitVarSizeWithDummy, x_Occurrence, y_Occurrence] +such that + and([x_Occurrence[i] /\ y_Occurrence[j] -> i + 2 = j | i : int(2..5), j : int(2..5)]), + 1 <= sum([toInt(x_Occurrence[q1]) | q1 : int(2..5)]), + 1 <= sum([toInt(y_Occurrence[q2]) | q2 : int(2..5)]), + and([x_ExplicitVarSizeWithDummy[q3] < x_ExplicitVarSizeWithDummy[q3 + 1] \/ x_ExplicitVarSizeWithDummy[q3] = 6 + | q3 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q4] = 6 -> x_ExplicitVarSizeWithDummy[q4 + 1] = 6 | q4 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q5] != 6) | q5 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q8] != 6 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q8]] | q8 : int(1..4)]), + and([x_Occurrence[q9] -> + or([x_ExplicitVarSizeWithDummy[q11] != 6 /\ x_ExplicitVarSizeWithDummy[q11] = q9 | q11 : int(1..4)]) + | q9 : int(2..5)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_1_1_2_2-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_1_1_2_2-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_1_2_2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_1_1_2_2-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_1_1_2_2-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_1_2_2-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_1_1_2_2.eprime b/tests/exhaustive/basic/set09/expected/model_1_1_2_2.eprime new file mode 100644 index 0000000000..40de4c9235 --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_1_2_2.eprime @@ -0,0 +1,28 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(2..5)] of bool +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +find y_Occurrence: matrix indexed by [int(2..5)] of bool +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +branching on [x_ExplicitVarSizeWithDummy, x_Occurrence, y_ExplicitVarSizeWithDummy, y_Occurrence] +such that + and([x_Occurrence[i] /\ y_Occurrence[j] -> i + 2 = j | i : int(2..5), j : int(2..5)]), + 1 <= sum([toInt(x_Occurrence[q1]) | q1 : int(2..5)]), + 1 <= sum([toInt(y_Occurrence[q2]) | q2 : int(2..5)]), + and([x_ExplicitVarSizeWithDummy[q3] < x_ExplicitVarSizeWithDummy[q3 + 1] \/ x_ExplicitVarSizeWithDummy[q3] = 6 + | q3 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q4] = 6 -> x_ExplicitVarSizeWithDummy[q4 + 1] = 6 | q4 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q5] != 6) | q5 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q8] != 6 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q8]] | q8 : int(1..4)]), + and([x_Occurrence[q9] -> + or([x_ExplicitVarSizeWithDummy[q11] != 6 /\ x_ExplicitVarSizeWithDummy[q11] = q9 | q11 : int(1..4)]) + | q9 : int(2..5)]), + and([y_ExplicitVarSizeWithDummy[q12] < y_ExplicitVarSizeWithDummy[q12 + 1] \/ y_ExplicitVarSizeWithDummy[q12] = 6 + | q12 : int(1..3)]), + and([y_ExplicitVarSizeWithDummy[q13] = 6 -> y_ExplicitVarSizeWithDummy[q13 + 1] = 6 | q13 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q14] != 6) | q14 : int(1..4)]), + and([y_ExplicitVarSizeWithDummy[q17] != 6 -> y_Occurrence[y_ExplicitVarSizeWithDummy[q17]] | q17 : int(1..4)]), + and([y_Occurrence[q18] -> + or([y_ExplicitVarSizeWithDummy[q20] != 6 /\ y_ExplicitVarSizeWithDummy[q20] = q18 | q20 : int(1..4)]) + | q18 : int(2..5)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_1_1_2_3-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_1_1_2_3-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_1_2_3-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_1_1_2_3-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_1_1_2_3-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_1_2_3-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_1_1_2_3.eprime b/tests/exhaustive/basic/set09/expected/model_1_1_2_3.eprime new file mode 100644 index 0000000000..c2ab749e23 --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_1_2_3.eprime @@ -0,0 +1,34 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(2..5)] of bool +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +find y_Occurrence: matrix indexed by [int(2..5)] of bool +find y_ExplicitVarSizeWithMarker_Marker: int(0..4) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +branching on + [x_ExplicitVarSizeWithDummy, x_Occurrence, y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values, + y_Occurrence] +such that + and([x_Occurrence[i] /\ y_Occurrence[j] -> i + 2 = j | i : int(2..5), j : int(2..5)]), + 1 <= sum([toInt(x_Occurrence[q1]) | q1 : int(2..5)]), + 1 <= sum([toInt(y_Occurrence[q2]) | q2 : int(2..5)]), + and([x_ExplicitVarSizeWithDummy[q3] < x_ExplicitVarSizeWithDummy[q3 + 1] \/ x_ExplicitVarSizeWithDummy[q3] = 6 + | q3 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q4] = 6 -> x_ExplicitVarSizeWithDummy[q4 + 1] = 6 | q4 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q5] != 6) | q5 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q8] != 6 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q8]] | q8 : int(1..4)]), + and([x_Occurrence[q9] -> + or([x_ExplicitVarSizeWithDummy[q11] != 6 /\ x_ExplicitVarSizeWithDummy[q11] = q9 | q11 : int(1..4)]) + | q9 : int(2..5)]), + and([q12 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> + y_ExplicitVarSizeWithMarker_Values[q12] < y_ExplicitVarSizeWithMarker_Values[q12 + 1] + | q12 : int(1..3)]), + and([q13 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q13] = 2 | q13 : int(1..4)]), + 1 <= y_ExplicitVarSizeWithMarker_Marker, + and([q16 <= y_ExplicitVarSizeWithMarker_Marker -> y_Occurrence[y_ExplicitVarSizeWithMarker_Values[q16]] + | q16 : int(1..4)]), + and([y_Occurrence[q17] -> + or([q19 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[q19] = q17 + | q19 : int(1..4)]) + | q17 : int(2..5)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_1_1_2_4-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_1_1_2_4-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_1_2_4-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_1_1_2_4-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_1_1_2_4-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_1_2_4-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_1_1_2_4.eprime b/tests/exhaustive/basic/set09/expected/model_1_1_2_4.eprime new file mode 100644 index 0000000000..3439f1ddf8 --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_1_2_4.eprime @@ -0,0 +1,35 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(2..5)] of bool +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +find y_Occurrence: matrix indexed by [int(2..5)] of bool +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +branching on + [x_ExplicitVarSizeWithDummy, x_Occurrence, y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values, + y_Occurrence] +such that + and([x_Occurrence[i] /\ y_Occurrence[j] -> i + 2 = j | i : int(2..5), j : int(2..5)]), + 1 <= sum([toInt(x_Occurrence[q1]) | q1 : int(2..5)]), + 1 <= sum([toInt(y_Occurrence[q2]) | q2 : int(2..5)]), + and([x_ExplicitVarSizeWithDummy[q3] < x_ExplicitVarSizeWithDummy[q3 + 1] \/ x_ExplicitVarSizeWithDummy[q3] = 6 + | q3 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q4] = 6 -> x_ExplicitVarSizeWithDummy[q4 + 1] = 6 | q4 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q5] != 6) | q5 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q8] != 6 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q8]] | q8 : int(1..4)]), + and([x_Occurrence[q9] -> + or([x_ExplicitVarSizeWithDummy[q11] != 6 /\ x_ExplicitVarSizeWithDummy[q11] = q9 | q11 : int(1..4)]) + | q9 : int(2..5)]), + and([y_ExplicitVarSizeWithFlags_Flags[q12 + 1] -> + y_ExplicitVarSizeWithFlags_Values[q12] < y_ExplicitVarSizeWithFlags_Values[q12 + 1] + | q12 : int(1..3)]), + and([y_ExplicitVarSizeWithFlags_Flags[q13] = false -> y_ExplicitVarSizeWithFlags_Values[q13] = 2 + | q13 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q14 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q14] | q14 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q15]) | q15 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q18] -> y_Occurrence[y_ExplicitVarSizeWithFlags_Values[q18]] + | q18 : int(1..4)]), + and([y_Occurrence[q19] -> + or([y_ExplicitVarSizeWithFlags_Flags[q21] /\ y_ExplicitVarSizeWithFlags_Values[q21] = q19 | q21 : int(1..4)]) + | q19 : int(2..5)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_1_1_3_1-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_1_1_3_1-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_1_3_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_1_1_3_1-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_1_1_3_1-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_1_3_1-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_1_1_3_1.eprime b/tests/exhaustive/basic/set09/expected/model_1_1_3_1.eprime new file mode 100644 index 0000000000..745ddbf47d --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_1_3_1.eprime @@ -0,0 +1,23 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(2..5)] of bool +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_Occurrence: matrix indexed by [int(2..5)] of bool +branching on [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_Occurrence, y_Occurrence] +such that + and([x_Occurrence[i] /\ y_Occurrence[j] -> i + 2 = j | i : int(2..5), j : int(2..5)]), + 1 <= sum([toInt(x_Occurrence[q1]) | q1 : int(2..5)]), + 1 <= sum([toInt(y_Occurrence[q2]) | q2 : int(2..5)]), + and([q3 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q3] < x_ExplicitVarSizeWithMarker_Values[q3 + 1] + | q3 : int(1..3)]), + and([q4 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q4] = 2 | q4 : int(1..4)]), + 1 <= x_ExplicitVarSizeWithMarker_Marker, + and([q7 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q7]] + | q7 : int(1..4)]), + and([x_Occurrence[q8] -> + or([q10 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q10] = q8 + | q10 : int(1..4)]) + | q8 : int(2..5)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_1_1_3_2-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_1_1_3_2-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_1_3_2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_1_1_3_2-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_1_1_3_2-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_1_3_2-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_1_1_3_2.eprime b/tests/exhaustive/basic/set09/expected/model_1_1_3_2.eprime new file mode 100644 index 0000000000..6ac452cb87 --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_1_3_2.eprime @@ -0,0 +1,34 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(2..5)] of bool +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_Occurrence: matrix indexed by [int(2..5)] of bool +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +branching on + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_Occurrence, y_ExplicitVarSizeWithDummy, + y_Occurrence] +such that + and([x_Occurrence[i] /\ y_Occurrence[j] -> i + 2 = j | i : int(2..5), j : int(2..5)]), + 1 <= sum([toInt(x_Occurrence[q1]) | q1 : int(2..5)]), + 1 <= sum([toInt(y_Occurrence[q2]) | q2 : int(2..5)]), + and([q3 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q3] < x_ExplicitVarSizeWithMarker_Values[q3 + 1] + | q3 : int(1..3)]), + and([q4 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q4] = 2 | q4 : int(1..4)]), + 1 <= x_ExplicitVarSizeWithMarker_Marker, + and([q7 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q7]] + | q7 : int(1..4)]), + and([x_Occurrence[q8] -> + or([q10 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q10] = q8 + | q10 : int(1..4)]) + | q8 : int(2..5)]), + and([y_ExplicitVarSizeWithDummy[q11] < y_ExplicitVarSizeWithDummy[q11 + 1] \/ y_ExplicitVarSizeWithDummy[q11] = 6 + | q11 : int(1..3)]), + and([y_ExplicitVarSizeWithDummy[q12] = 6 -> y_ExplicitVarSizeWithDummy[q12 + 1] = 6 | q12 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q13] != 6) | q13 : int(1..4)]), + and([y_ExplicitVarSizeWithDummy[q16] != 6 -> y_Occurrence[y_ExplicitVarSizeWithDummy[q16]] | q16 : int(1..4)]), + and([y_Occurrence[q17] -> + or([y_ExplicitVarSizeWithDummy[q19] != 6 /\ y_ExplicitVarSizeWithDummy[q19] = q17 | q19 : int(1..4)]) + | q17 : int(2..5)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_1_1_3_3-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_1_1_3_3-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_1_3_3-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_1_1_3_3-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_1_1_3_3-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_1_3_3-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_1_1_3_3.eprime b/tests/exhaustive/basic/set09/expected/model_1_1_3_3.eprime new file mode 100644 index 0000000000..9477b707c7 --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_1_3_3.eprime @@ -0,0 +1,38 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(2..5)] of bool +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_Occurrence: matrix indexed by [int(2..5)] of bool +find y_ExplicitVarSizeWithMarker_Marker: int(0..4) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +branching on + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_Occurrence, + y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values, y_Occurrence] +such that + and([x_Occurrence[i] /\ y_Occurrence[j] -> i + 2 = j | i : int(2..5), j : int(2..5)]), + 1 <= sum([toInt(x_Occurrence[q1]) | q1 : int(2..5)]), + 1 <= sum([toInt(y_Occurrence[q2]) | q2 : int(2..5)]), + and([q3 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q3] < x_ExplicitVarSizeWithMarker_Values[q3 + 1] + | q3 : int(1..3)]), + and([q4 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q4] = 2 | q4 : int(1..4)]), + 1 <= x_ExplicitVarSizeWithMarker_Marker, + and([q7 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q7]] + | q7 : int(1..4)]), + and([x_Occurrence[q8] -> + or([q10 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q10] = q8 + | q10 : int(1..4)]) + | q8 : int(2..5)]), + and([q11 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> + y_ExplicitVarSizeWithMarker_Values[q11] < y_ExplicitVarSizeWithMarker_Values[q11 + 1] + | q11 : int(1..3)]), + and([q12 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q12] = 2 | q12 : int(1..4)]), + 1 <= y_ExplicitVarSizeWithMarker_Marker, + and([q15 <= y_ExplicitVarSizeWithMarker_Marker -> y_Occurrence[y_ExplicitVarSizeWithMarker_Values[q15]] + | q15 : int(1..4)]), + and([y_Occurrence[q16] -> + or([q18 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[q18] = q16 + | q18 : int(1..4)]) + | q16 : int(2..5)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_1_1_3_4-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_1_1_3_4-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_1_3_4-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_1_1_3_4-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_1_1_3_4-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_1_3_4-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_1_1_3_4.eprime b/tests/exhaustive/basic/set09/expected/model_1_1_3_4.eprime new file mode 100644 index 0000000000..a002cc2f24 --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_1_3_4.eprime @@ -0,0 +1,39 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(2..5)] of bool +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_Occurrence: matrix indexed by [int(2..5)] of bool +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +branching on + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_Occurrence, + y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values, y_Occurrence] +such that + and([x_Occurrence[i] /\ y_Occurrence[j] -> i + 2 = j | i : int(2..5), j : int(2..5)]), + 1 <= sum([toInt(x_Occurrence[q1]) | q1 : int(2..5)]), + 1 <= sum([toInt(y_Occurrence[q2]) | q2 : int(2..5)]), + and([q3 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q3] < x_ExplicitVarSizeWithMarker_Values[q3 + 1] + | q3 : int(1..3)]), + and([q4 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q4] = 2 | q4 : int(1..4)]), + 1 <= x_ExplicitVarSizeWithMarker_Marker, + and([q7 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q7]] + | q7 : int(1..4)]), + and([x_Occurrence[q8] -> + or([q10 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q10] = q8 + | q10 : int(1..4)]) + | q8 : int(2..5)]), + and([y_ExplicitVarSizeWithFlags_Flags[q11 + 1] -> + y_ExplicitVarSizeWithFlags_Values[q11] < y_ExplicitVarSizeWithFlags_Values[q11 + 1] + | q11 : int(1..3)]), + and([y_ExplicitVarSizeWithFlags_Flags[q12] = false -> y_ExplicitVarSizeWithFlags_Values[q12] = 2 + | q12 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q13 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q13] | q13 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q14]) | q14 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q17] -> y_Occurrence[y_ExplicitVarSizeWithFlags_Values[q17]] + | q17 : int(1..4)]), + and([y_Occurrence[q18] -> + or([y_ExplicitVarSizeWithFlags_Flags[q20] /\ y_ExplicitVarSizeWithFlags_Values[q20] = q18 | q20 : int(1..4)]) + | q18 : int(2..5)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_1_1_4_1-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_1_1_4_1-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_1_4_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_1_1_4_1-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_1_1_4_1-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_1_4_1-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_1_1_4_1.eprime b/tests/exhaustive/basic/set09/expected/model_1_1_4_1.eprime new file mode 100644 index 0000000000..ef5ab46d55 --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_1_4_1.eprime @@ -0,0 +1,22 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(2..5)] of bool +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_Occurrence: matrix indexed by [int(2..5)] of bool +branching on [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_Occurrence, y_Occurrence] +such that + and([x_Occurrence[i] /\ y_Occurrence[j] -> i + 2 = j | i : int(2..5), j : int(2..5)]), + 1 <= sum([toInt(x_Occurrence[q1]) | q1 : int(2..5)]), + 1 <= sum([toInt(y_Occurrence[q2]) | q2 : int(2..5)]), + and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q3] < x_ExplicitVarSizeWithFlags_Values[q3 + 1] + | q3 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q4] = false -> x_ExplicitVarSizeWithFlags_Values[q4] = 2 | q4 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q5 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q5] | q5 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q6]) | q6 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q9] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q9]] | q9 : int(1..4)]), + and([x_Occurrence[q10] -> + or([x_ExplicitVarSizeWithFlags_Flags[q12] /\ x_ExplicitVarSizeWithFlags_Values[q12] = q10 | q12 : int(1..4)]) + | q10 : int(2..5)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_1_1_4_2-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_1_1_4_2-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_1_4_2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_1_1_4_2-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_1_1_4_2-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_1_4_2-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_1_1_4_2.eprime b/tests/exhaustive/basic/set09/expected/model_1_1_4_2.eprime new file mode 100644 index 0000000000..5f1fccfa5a --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_1_4_2.eprime @@ -0,0 +1,33 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(2..5)] of bool +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_Occurrence: matrix indexed by [int(2..5)] of bool +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +branching on + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_Occurrence, y_ExplicitVarSizeWithDummy, + y_Occurrence] +such that + and([x_Occurrence[i] /\ y_Occurrence[j] -> i + 2 = j | i : int(2..5), j : int(2..5)]), + 1 <= sum([toInt(x_Occurrence[q1]) | q1 : int(2..5)]), + 1 <= sum([toInt(y_Occurrence[q2]) | q2 : int(2..5)]), + and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q3] < x_ExplicitVarSizeWithFlags_Values[q3 + 1] + | q3 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q4] = false -> x_ExplicitVarSizeWithFlags_Values[q4] = 2 | q4 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q5 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q5] | q5 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q6]) | q6 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q9] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q9]] | q9 : int(1..4)]), + and([x_Occurrence[q10] -> + or([x_ExplicitVarSizeWithFlags_Flags[q12] /\ x_ExplicitVarSizeWithFlags_Values[q12] = q10 | q12 : int(1..4)]) + | q10 : int(2..5)]), + and([y_ExplicitVarSizeWithDummy[q13] < y_ExplicitVarSizeWithDummy[q13 + 1] \/ y_ExplicitVarSizeWithDummy[q13] = 6 + | q13 : int(1..3)]), + and([y_ExplicitVarSizeWithDummy[q14] = 6 -> y_ExplicitVarSizeWithDummy[q14 + 1] = 6 | q14 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q15] != 6) | q15 : int(1..4)]), + and([y_ExplicitVarSizeWithDummy[q18] != 6 -> y_Occurrence[y_ExplicitVarSizeWithDummy[q18]] | q18 : int(1..4)]), + and([y_Occurrence[q19] -> + or([y_ExplicitVarSizeWithDummy[q21] != 6 /\ y_ExplicitVarSizeWithDummy[q21] = q19 | q21 : int(1..4)]) + | q19 : int(2..5)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_1_1_4_3-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_1_1_4_3-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_1_4_3-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_1_1_4_3-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_1_1_4_3-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_1_4_3-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_1_1_4_3.eprime b/tests/exhaustive/basic/set09/expected/model_1_1_4_3.eprime new file mode 100644 index 0000000000..e9925fe769 --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_1_4_3.eprime @@ -0,0 +1,37 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(2..5)] of bool +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_Occurrence: matrix indexed by [int(2..5)] of bool +find y_ExplicitVarSizeWithMarker_Marker: int(0..4) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +branching on + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_Occurrence, + y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values, y_Occurrence] +such that + and([x_Occurrence[i] /\ y_Occurrence[j] -> i + 2 = j | i : int(2..5), j : int(2..5)]), + 1 <= sum([toInt(x_Occurrence[q1]) | q1 : int(2..5)]), + 1 <= sum([toInt(y_Occurrence[q2]) | q2 : int(2..5)]), + and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q3] < x_ExplicitVarSizeWithFlags_Values[q3 + 1] + | q3 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q4] = false -> x_ExplicitVarSizeWithFlags_Values[q4] = 2 | q4 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q5 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q5] | q5 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q6]) | q6 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q9] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q9]] | q9 : int(1..4)]), + and([x_Occurrence[q10] -> + or([x_ExplicitVarSizeWithFlags_Flags[q12] /\ x_ExplicitVarSizeWithFlags_Values[q12] = q10 | q12 : int(1..4)]) + | q10 : int(2..5)]), + and([q13 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> + y_ExplicitVarSizeWithMarker_Values[q13] < y_ExplicitVarSizeWithMarker_Values[q13 + 1] + | q13 : int(1..3)]), + and([q14 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q14] = 2 | q14 : int(1..4)]), + 1 <= y_ExplicitVarSizeWithMarker_Marker, + and([q17 <= y_ExplicitVarSizeWithMarker_Marker -> y_Occurrence[y_ExplicitVarSizeWithMarker_Values[q17]] + | q17 : int(1..4)]), + and([y_Occurrence[q18] -> + or([q20 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[q20] = q18 + | q20 : int(1..4)]) + | q18 : int(2..5)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_1_1_4_4-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_1_1_4_4-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_1_4_4-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_1_1_4_4-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_1_1_4_4-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_1_4_4-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_1_1_4_4.eprime b/tests/exhaustive/basic/set09/expected/model_1_1_4_4.eprime new file mode 100644 index 0000000000..83b55b09e8 --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_1_4_4.eprime @@ -0,0 +1,38 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(2..5)] of bool +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_Occurrence: matrix indexed by [int(2..5)] of bool +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +branching on + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_Occurrence, + y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values, y_Occurrence] +such that + and([x_Occurrence[i] /\ y_Occurrence[j] -> i + 2 = j | i : int(2..5), j : int(2..5)]), + 1 <= sum([toInt(x_Occurrence[q1]) | q1 : int(2..5)]), + 1 <= sum([toInt(y_Occurrence[q2]) | q2 : int(2..5)]), + and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q3] < x_ExplicitVarSizeWithFlags_Values[q3 + 1] + | q3 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q4] = false -> x_ExplicitVarSizeWithFlags_Values[q4] = 2 | q4 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q5 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q5] | q5 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q6]) | q6 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q9] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q9]] | q9 : int(1..4)]), + and([x_Occurrence[q10] -> + or([x_ExplicitVarSizeWithFlags_Flags[q12] /\ x_ExplicitVarSizeWithFlags_Values[q12] = q10 | q12 : int(1..4)]) + | q10 : int(2..5)]), + and([y_ExplicitVarSizeWithFlags_Flags[q13 + 1] -> + y_ExplicitVarSizeWithFlags_Values[q13] < y_ExplicitVarSizeWithFlags_Values[q13 + 1] + | q13 : int(1..3)]), + and([y_ExplicitVarSizeWithFlags_Flags[q14] = false -> y_ExplicitVarSizeWithFlags_Values[q14] = 2 + | q14 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q15 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q15] | q15 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q16]) | q16 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q19] -> y_Occurrence[y_ExplicitVarSizeWithFlags_Values[q19]] + | q19 : int(1..4)]), + and([y_Occurrence[q20] -> + or([y_ExplicitVarSizeWithFlags_Flags[q22] /\ y_ExplicitVarSizeWithFlags_Values[q22] = q20 | q22 : int(1..4)]) + | q20 : int(2..5)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_1_2_1_1-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_1_2_1_1-solution000001.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_2_1_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_1_2_1_1-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_1_2_1_1-solution000002.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_2_1_1-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_1_2_1_1.eprime b/tests/exhaustive/basic/set09/expected/model_1_2_1_1.eprime new file mode 100644 index 0000000000..a263bf4a81 --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_2_1_1.eprime @@ -0,0 +1,20 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(2..5)] of bool +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +find y_Occurrence: matrix indexed by [int(2..5)] of bool +branching on [x_Occurrence, y_Occurrence, y_ExplicitVarSizeWithDummy] +such that + and([x_Occurrence[i] /\ y_ExplicitVarSizeWithDummy[q12] != 6 -> i + 2 = y_ExplicitVarSizeWithDummy[q12] + | i : int(2..5), q12 : int(1..4)]), + 1 <= sum([toInt(x_Occurrence[q1]) | q1 : int(2..5)]), + and([y_ExplicitVarSizeWithDummy[q2] < y_ExplicitVarSizeWithDummy[q2 + 1] \/ y_ExplicitVarSizeWithDummy[q2] = 6 + | q2 : int(1..3)]), + and([y_ExplicitVarSizeWithDummy[q3] = 6 -> y_ExplicitVarSizeWithDummy[q3 + 1] = 6 | q3 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q4] != 6) | q4 : int(1..4)]), + 1 <= sum([toInt(y_Occurrence[q6]) | q6 : int(2..5)]), + and([y_Occurrence[q7] -> + or([y_ExplicitVarSizeWithDummy[q9] != 6 /\ y_ExplicitVarSizeWithDummy[q9] = q7 | q9 : int(1..4)]) + | q7 : int(2..5)]), + and([y_ExplicitVarSizeWithDummy[q11] != 6 -> y_Occurrence[y_ExplicitVarSizeWithDummy[q11]] | q11 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_1_2_1_2-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_1_2_1_2-solution000001.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_2_1_2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_1_2_1_2-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_1_2_1_2-solution000002.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_2_1_2-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_1_2_1_2.eprime b/tests/exhaustive/basic/set09/expected/model_1_2_1_2.eprime new file mode 100644 index 0000000000..970b65361f --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_2_1_2.eprime @@ -0,0 +1,14 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(2..5)] of bool +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +branching on [x_Occurrence, y_ExplicitVarSizeWithDummy] +such that + and([x_Occurrence[i] /\ y_ExplicitVarSizeWithDummy[q6] != 6 -> i + 2 = y_ExplicitVarSizeWithDummy[q6] + | i : int(2..5), q6 : int(1..4)]), + 1 <= sum([toInt(x_Occurrence[q1]) | q1 : int(2..5)]), + and([y_ExplicitVarSizeWithDummy[q2] < y_ExplicitVarSizeWithDummy[q2 + 1] \/ y_ExplicitVarSizeWithDummy[q2] = 6 + | q2 : int(1..3)]), + and([y_ExplicitVarSizeWithDummy[q3] = 6 -> y_ExplicitVarSizeWithDummy[q3 + 1] = 6 | q3 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q4] != 6) | q4 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_1_2_1_3-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_1_2_1_3-solution000001.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_2_1_3-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_1_2_1_3-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_1_2_1_3-solution000002.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_2_1_3-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_1_2_1_3.eprime b/tests/exhaustive/basic/set09/expected/model_1_2_1_3.eprime new file mode 100644 index 0000000000..34f57c451d --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_2_1_3.eprime @@ -0,0 +1,32 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(2..5)] of bool +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +find y_ExplicitVarSizeWithMarker_Marker: int(0..4) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +branching on + [x_Occurrence, y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithDummy] +such that + and([x_Occurrence[i] /\ y_ExplicitVarSizeWithDummy[q17] != 6 -> i + 2 = y_ExplicitVarSizeWithDummy[q17] + | i : int(2..5), q17 : int(1..4)]), + 1 <= sum([toInt(x_Occurrence[q1]) | q1 : int(2..5)]), + and([y_ExplicitVarSizeWithDummy[q2] < y_ExplicitVarSizeWithDummy[q2 + 1] \/ y_ExplicitVarSizeWithDummy[q2] = 6 + | q2 : int(1..3)]), + and([y_ExplicitVarSizeWithDummy[q3] = 6 -> y_ExplicitVarSizeWithDummy[q3 + 1] = 6 | q3 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q4] != 6) | q4 : int(1..4)]), + and([q6 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> + y_ExplicitVarSizeWithMarker_Values[q6] < y_ExplicitVarSizeWithMarker_Values[q6 + 1] + | q6 : int(1..3)]), + and([q7 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q7] = 2 | q7 : int(1..4)]), + 1 <= y_ExplicitVarSizeWithMarker_Marker, + and([q10 <= y_ExplicitVarSizeWithMarker_Marker -> + or([y_ExplicitVarSizeWithDummy[q12] != 6 /\ + y_ExplicitVarSizeWithDummy[q12] = y_ExplicitVarSizeWithMarker_Values[q10] + | q12 : int(1..4)]) + | q10 : int(1..4)]), + and([y_ExplicitVarSizeWithDummy[q14] != 6 -> + or([q16 <= y_ExplicitVarSizeWithMarker_Marker /\ + y_ExplicitVarSizeWithMarker_Values[q16] = y_ExplicitVarSizeWithDummy[q14] + | q16 : int(1..4)]) + | q14 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_1_2_1_4-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_1_2_1_4-solution000001.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_2_1_4-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_1_2_1_4-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_1_2_1_4-solution000002.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_2_1_4-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_1_2_1_4.eprime b/tests/exhaustive/basic/set09/expected/model_1_2_1_4.eprime new file mode 100644 index 0000000000..e89acaaa36 --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_2_1_4.eprime @@ -0,0 +1,33 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(2..5)] of bool +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +branching on + [x_Occurrence, y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithDummy] +such that + and([x_Occurrence[i] /\ y_ExplicitVarSizeWithDummy[q19] != 6 -> i + 2 = y_ExplicitVarSizeWithDummy[q19] + | i : int(2..5), q19 : int(1..4)]), + 1 <= sum([toInt(x_Occurrence[q1]) | q1 : int(2..5)]), + and([y_ExplicitVarSizeWithDummy[q2] < y_ExplicitVarSizeWithDummy[q2 + 1] \/ y_ExplicitVarSizeWithDummy[q2] = 6 + | q2 : int(1..3)]), + and([y_ExplicitVarSizeWithDummy[q3] = 6 -> y_ExplicitVarSizeWithDummy[q3 + 1] = 6 | q3 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q4] != 6) | q4 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> + y_ExplicitVarSizeWithFlags_Values[q6] < y_ExplicitVarSizeWithFlags_Values[q6 + 1] + | q6 : int(1..3)]), + and([y_ExplicitVarSizeWithFlags_Flags[q7] = false -> y_ExplicitVarSizeWithFlags_Values[q7] = 2 | q7 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q8 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q8] | q8 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q9]) | q9 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q12] -> + or([y_ExplicitVarSizeWithDummy[q14] != 6 /\ + y_ExplicitVarSizeWithDummy[q14] = y_ExplicitVarSizeWithFlags_Values[q12] + | q14 : int(1..4)]) + | q12 : int(1..4)]), + and([y_ExplicitVarSizeWithDummy[q16] != 6 -> + or([y_ExplicitVarSizeWithFlags_Flags[q18] /\ + y_ExplicitVarSizeWithFlags_Values[q18] = y_ExplicitVarSizeWithDummy[q16] + | q18 : int(1..4)]) + | q16 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_1_2_2_1-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_1_2_2_1-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_2_2_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_1_2_2_1-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_1_2_2_1-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_2_2_1-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_1_2_2_1.eprime b/tests/exhaustive/basic/set09/expected/model_1_2_2_1.eprime new file mode 100644 index 0000000000..b50b8217a7 --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_2_2_1.eprime @@ -0,0 +1,29 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(2..5)] of bool +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +find y_Occurrence: matrix indexed by [int(2..5)] of bool +branching on [x_ExplicitVarSizeWithDummy, x_Occurrence, y_Occurrence, y_ExplicitVarSizeWithDummy] +such that + and([x_Occurrence[i] /\ y_ExplicitVarSizeWithDummy[q21] != 6 -> i + 2 = y_ExplicitVarSizeWithDummy[q21] + | i : int(2..5), q21 : int(1..4)]), + 1 <= sum([toInt(x_Occurrence[q1]) | q1 : int(2..5)]), + and([y_ExplicitVarSizeWithDummy[q2] < y_ExplicitVarSizeWithDummy[q2 + 1] \/ y_ExplicitVarSizeWithDummy[q2] = 6 + | q2 : int(1..3)]), + and([y_ExplicitVarSizeWithDummy[q3] = 6 -> y_ExplicitVarSizeWithDummy[q3 + 1] = 6 | q3 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q4] != 6) | q4 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q6] < x_ExplicitVarSizeWithDummy[q6 + 1] \/ x_ExplicitVarSizeWithDummy[q6] = 6 + | q6 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q7] = 6 -> x_ExplicitVarSizeWithDummy[q7 + 1] = 6 | q7 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q8] != 6) | q8 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q11] != 6 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q11]] | q11 : int(1..4)]), + and([x_Occurrence[q12] -> + or([x_ExplicitVarSizeWithDummy[q14] != 6 /\ x_ExplicitVarSizeWithDummy[q14] = q12 | q14 : int(1..4)]) + | q12 : int(2..5)]), + 1 <= sum([toInt(y_Occurrence[q15]) | q15 : int(2..5)]), + and([y_Occurrence[q16] -> + or([y_ExplicitVarSizeWithDummy[q18] != 6 /\ y_ExplicitVarSizeWithDummy[q18] = q16 | q18 : int(1..4)]) + | q16 : int(2..5)]), + and([y_ExplicitVarSizeWithDummy[q20] != 6 -> y_Occurrence[y_ExplicitVarSizeWithDummy[q20]] | q20 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_1_2_2_2-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_1_2_2_2-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_2_2_2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_1_2_2_2-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_1_2_2_2-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_2_2_2-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_1_2_2_2.eprime b/tests/exhaustive/basic/set09/expected/model_1_2_2_2.eprime new file mode 100644 index 0000000000..97ccb1e791 --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_2_2_2.eprime @@ -0,0 +1,23 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(2..5)] of bool +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +branching on [x_ExplicitVarSizeWithDummy, x_Occurrence, y_ExplicitVarSizeWithDummy] +such that + and([x_Occurrence[i] /\ y_ExplicitVarSizeWithDummy[q15] != 6 -> i + 2 = y_ExplicitVarSizeWithDummy[q15] + | i : int(2..5), q15 : int(1..4)]), + 1 <= sum([toInt(x_Occurrence[q1]) | q1 : int(2..5)]), + and([y_ExplicitVarSizeWithDummy[q2] < y_ExplicitVarSizeWithDummy[q2 + 1] \/ y_ExplicitVarSizeWithDummy[q2] = 6 + | q2 : int(1..3)]), + and([y_ExplicitVarSizeWithDummy[q3] = 6 -> y_ExplicitVarSizeWithDummy[q3 + 1] = 6 | q3 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q4] != 6) | q4 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q6] < x_ExplicitVarSizeWithDummy[q6 + 1] \/ x_ExplicitVarSizeWithDummy[q6] = 6 + | q6 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q7] = 6 -> x_ExplicitVarSizeWithDummy[q7 + 1] = 6 | q7 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q8] != 6) | q8 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q11] != 6 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q11]] | q11 : int(1..4)]), + and([x_Occurrence[q12] -> + or([x_ExplicitVarSizeWithDummy[q14] != 6 /\ x_ExplicitVarSizeWithDummy[q14] = q12 | q14 : int(1..4)]) + | q12 : int(2..5)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_1_2_2_3-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_1_2_2_3-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_2_2_3-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_1_2_2_3-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_1_2_2_3-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_2_2_3-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_1_2_2_3.eprime b/tests/exhaustive/basic/set09/expected/model_1_2_2_3.eprime new file mode 100644 index 0000000000..834e686023 --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_2_2_3.eprime @@ -0,0 +1,42 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(2..5)] of bool +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +find y_ExplicitVarSizeWithMarker_Marker: int(0..4) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +branching on + [x_ExplicitVarSizeWithDummy, x_Occurrence, y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values, + y_ExplicitVarSizeWithDummy] +such that + and([x_Occurrence[i] /\ y_ExplicitVarSizeWithDummy[q26] != 6 -> i + 2 = y_ExplicitVarSizeWithDummy[q26] + | i : int(2..5), q26 : int(1..4)]), + 1 <= sum([toInt(x_Occurrence[q1]) | q1 : int(2..5)]), + and([y_ExplicitVarSizeWithDummy[q2] < y_ExplicitVarSizeWithDummy[q2 + 1] \/ y_ExplicitVarSizeWithDummy[q2] = 6 + | q2 : int(1..3)]), + and([y_ExplicitVarSizeWithDummy[q3] = 6 -> y_ExplicitVarSizeWithDummy[q3 + 1] = 6 | q3 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q4] != 6) | q4 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q6] < x_ExplicitVarSizeWithDummy[q6 + 1] \/ x_ExplicitVarSizeWithDummy[q6] = 6 + | q6 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q7] = 6 -> x_ExplicitVarSizeWithDummy[q7 + 1] = 6 | q7 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q8] != 6) | q8 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q11] != 6 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q11]] | q11 : int(1..4)]), + and([x_Occurrence[q12] -> + or([x_ExplicitVarSizeWithDummy[q14] != 6 /\ x_ExplicitVarSizeWithDummy[q14] = q12 | q14 : int(1..4)]) + | q12 : int(2..5)]), + and([q15 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> + y_ExplicitVarSizeWithMarker_Values[q15] < y_ExplicitVarSizeWithMarker_Values[q15 + 1] + | q15 : int(1..3)]), + and([q16 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q16] = 2 | q16 : int(1..4)]), + 1 <= y_ExplicitVarSizeWithMarker_Marker, + and([q19 <= y_ExplicitVarSizeWithMarker_Marker -> + or([y_ExplicitVarSizeWithDummy[q21] != 6 /\ + y_ExplicitVarSizeWithDummy[q21] = y_ExplicitVarSizeWithMarker_Values[q19] + | q21 : int(1..4)]) + | q19 : int(1..4)]), + and([y_ExplicitVarSizeWithDummy[q23] != 6 -> + or([q25 <= y_ExplicitVarSizeWithMarker_Marker /\ + y_ExplicitVarSizeWithMarker_Values[q25] = y_ExplicitVarSizeWithDummy[q23] + | q25 : int(1..4)]) + | q23 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_1_2_2_4-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_1_2_2_4-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_2_2_4-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_1_2_2_4-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_1_2_2_4-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_2_2_4-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_1_2_2_4.eprime b/tests/exhaustive/basic/set09/expected/model_1_2_2_4.eprime new file mode 100644 index 0000000000..7f9c9565ff --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_2_2_4.eprime @@ -0,0 +1,44 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(2..5)] of bool +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +branching on + [x_ExplicitVarSizeWithDummy, x_Occurrence, y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values, + y_ExplicitVarSizeWithDummy] +such that + and([x_Occurrence[i] /\ y_ExplicitVarSizeWithDummy[q28] != 6 -> i + 2 = y_ExplicitVarSizeWithDummy[q28] + | i : int(2..5), q28 : int(1..4)]), + 1 <= sum([toInt(x_Occurrence[q1]) | q1 : int(2..5)]), + and([y_ExplicitVarSizeWithDummy[q2] < y_ExplicitVarSizeWithDummy[q2 + 1] \/ y_ExplicitVarSizeWithDummy[q2] = 6 + | q2 : int(1..3)]), + and([y_ExplicitVarSizeWithDummy[q3] = 6 -> y_ExplicitVarSizeWithDummy[q3 + 1] = 6 | q3 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q4] != 6) | q4 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q6] < x_ExplicitVarSizeWithDummy[q6 + 1] \/ x_ExplicitVarSizeWithDummy[q6] = 6 + | q6 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q7] = 6 -> x_ExplicitVarSizeWithDummy[q7 + 1] = 6 | q7 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q8] != 6) | q8 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q11] != 6 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q11]] | q11 : int(1..4)]), + and([x_Occurrence[q12] -> + or([x_ExplicitVarSizeWithDummy[q14] != 6 /\ x_ExplicitVarSizeWithDummy[q14] = q12 | q14 : int(1..4)]) + | q12 : int(2..5)]), + and([y_ExplicitVarSizeWithFlags_Flags[q15 + 1] -> + y_ExplicitVarSizeWithFlags_Values[q15] < y_ExplicitVarSizeWithFlags_Values[q15 + 1] + | q15 : int(1..3)]), + and([y_ExplicitVarSizeWithFlags_Flags[q16] = false -> y_ExplicitVarSizeWithFlags_Values[q16] = 2 + | q16 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q17 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q17] | q17 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q18]) | q18 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q21] -> + or([y_ExplicitVarSizeWithDummy[q23] != 6 /\ + y_ExplicitVarSizeWithDummy[q23] = y_ExplicitVarSizeWithFlags_Values[q21] + | q23 : int(1..4)]) + | q21 : int(1..4)]), + and([y_ExplicitVarSizeWithDummy[q25] != 6 -> + or([y_ExplicitVarSizeWithFlags_Flags[q27] /\ + y_ExplicitVarSizeWithFlags_Values[q27] = y_ExplicitVarSizeWithDummy[q25] + | q27 : int(1..4)]) + | q25 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_1_2_3_1-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_1_2_3_1-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_2_3_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_1_2_3_1-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_1_2_3_1-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_2_3_1-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_1_2_3_1.eprime b/tests/exhaustive/basic/set09/expected/model_1_2_3_1.eprime new file mode 100644 index 0000000000..a173ae9198 --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_2_3_1.eprime @@ -0,0 +1,35 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(2..5)] of bool +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +find y_Occurrence: matrix indexed by [int(2..5)] of bool +branching on + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_Occurrence, y_Occurrence, + y_ExplicitVarSizeWithDummy] +such that + and([x_Occurrence[i] /\ y_ExplicitVarSizeWithDummy[q20] != 6 -> i + 2 = y_ExplicitVarSizeWithDummy[q20] + | i : int(2..5), q20 : int(1..4)]), + 1 <= sum([toInt(x_Occurrence[q1]) | q1 : int(2..5)]), + and([y_ExplicitVarSizeWithDummy[q2] < y_ExplicitVarSizeWithDummy[q2 + 1] \/ y_ExplicitVarSizeWithDummy[q2] = 6 + | q2 : int(1..3)]), + and([y_ExplicitVarSizeWithDummy[q3] = 6 -> y_ExplicitVarSizeWithDummy[q3 + 1] = 6 | q3 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q4] != 6) | q4 : int(1..4)]), + and([q6 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q6] < x_ExplicitVarSizeWithMarker_Values[q6 + 1] + | q6 : int(1..3)]), + and([q7 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q7] = 2 | q7 : int(1..4)]), + 1 <= x_ExplicitVarSizeWithMarker_Marker, + and([q10 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q10]] + | q10 : int(1..4)]), + and([x_Occurrence[q11] -> + or([q13 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q13] = q11 + | q13 : int(1..4)]) + | q11 : int(2..5)]), + 1 <= sum([toInt(y_Occurrence[q14]) | q14 : int(2..5)]), + and([y_Occurrence[q15] -> + or([y_ExplicitVarSizeWithDummy[q17] != 6 /\ y_ExplicitVarSizeWithDummy[q17] = q15 | q17 : int(1..4)]) + | q15 : int(2..5)]), + and([y_ExplicitVarSizeWithDummy[q19] != 6 -> y_Occurrence[y_ExplicitVarSizeWithDummy[q19]] | q19 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_1_2_3_2-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_1_2_3_2-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_2_3_2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_1_2_3_2-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_1_2_3_2-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_2_3_2-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_1_2_3_2.eprime b/tests/exhaustive/basic/set09/expected/model_1_2_3_2.eprime new file mode 100644 index 0000000000..85a3d62f8d --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_2_3_2.eprime @@ -0,0 +1,28 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(2..5)] of bool +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +branching on + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_Occurrence, y_ExplicitVarSizeWithDummy] +such that + and([x_Occurrence[i] /\ y_ExplicitVarSizeWithDummy[q14] != 6 -> i + 2 = y_ExplicitVarSizeWithDummy[q14] + | i : int(2..5), q14 : int(1..4)]), + 1 <= sum([toInt(x_Occurrence[q1]) | q1 : int(2..5)]), + and([y_ExplicitVarSizeWithDummy[q2] < y_ExplicitVarSizeWithDummy[q2 + 1] \/ y_ExplicitVarSizeWithDummy[q2] = 6 + | q2 : int(1..3)]), + and([y_ExplicitVarSizeWithDummy[q3] = 6 -> y_ExplicitVarSizeWithDummy[q3 + 1] = 6 | q3 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q4] != 6) | q4 : int(1..4)]), + and([q6 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q6] < x_ExplicitVarSizeWithMarker_Values[q6 + 1] + | q6 : int(1..3)]), + and([q7 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q7] = 2 | q7 : int(1..4)]), + 1 <= x_ExplicitVarSizeWithMarker_Marker, + and([q10 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q10]] + | q10 : int(1..4)]), + and([x_Occurrence[q11] -> + or([q13 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q13] = q11 + | q13 : int(1..4)]) + | q11 : int(2..5)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_1_2_3_3-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_1_2_3_3-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_2_3_3-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_1_2_3_3-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_1_2_3_3-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_2_3_3-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_1_2_3_3.eprime b/tests/exhaustive/basic/set09/expected/model_1_2_3_3.eprime new file mode 100644 index 0000000000..7e2bed2d00 --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_2_3_3.eprime @@ -0,0 +1,46 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(2..5)] of bool +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +find y_ExplicitVarSizeWithMarker_Marker: int(0..4) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +branching on + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_Occurrence, + y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithDummy] +such that + and([x_Occurrence[i] /\ y_ExplicitVarSizeWithDummy[q25] != 6 -> i + 2 = y_ExplicitVarSizeWithDummy[q25] + | i : int(2..5), q25 : int(1..4)]), + 1 <= sum([toInt(x_Occurrence[q1]) | q1 : int(2..5)]), + and([y_ExplicitVarSizeWithDummy[q2] < y_ExplicitVarSizeWithDummy[q2 + 1] \/ y_ExplicitVarSizeWithDummy[q2] = 6 + | q2 : int(1..3)]), + and([y_ExplicitVarSizeWithDummy[q3] = 6 -> y_ExplicitVarSizeWithDummy[q3 + 1] = 6 | q3 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q4] != 6) | q4 : int(1..4)]), + and([q6 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q6] < x_ExplicitVarSizeWithMarker_Values[q6 + 1] + | q6 : int(1..3)]), + and([q7 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q7] = 2 | q7 : int(1..4)]), + 1 <= x_ExplicitVarSizeWithMarker_Marker, + and([q10 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q10]] + | q10 : int(1..4)]), + and([x_Occurrence[q11] -> + or([q13 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q13] = q11 + | q13 : int(1..4)]) + | q11 : int(2..5)]), + and([q14 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> + y_ExplicitVarSizeWithMarker_Values[q14] < y_ExplicitVarSizeWithMarker_Values[q14 + 1] + | q14 : int(1..3)]), + and([q15 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q15] = 2 | q15 : int(1..4)]), + 1 <= y_ExplicitVarSizeWithMarker_Marker, + and([q18 <= y_ExplicitVarSizeWithMarker_Marker -> + or([y_ExplicitVarSizeWithDummy[q20] != 6 /\ + y_ExplicitVarSizeWithDummy[q20] = y_ExplicitVarSizeWithMarker_Values[q18] + | q20 : int(1..4)]) + | q18 : int(1..4)]), + and([y_ExplicitVarSizeWithDummy[q22] != 6 -> + or([q24 <= y_ExplicitVarSizeWithMarker_Marker /\ + y_ExplicitVarSizeWithMarker_Values[q24] = y_ExplicitVarSizeWithDummy[q22] + | q24 : int(1..4)]) + | q22 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_1_2_3_4-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_1_2_3_4-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_2_3_4-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_1_2_3_4-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_1_2_3_4-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_2_3_4-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_1_2_3_4.eprime b/tests/exhaustive/basic/set09/expected/model_1_2_3_4.eprime new file mode 100644 index 0000000000..fac749f4d5 --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_2_3_4.eprime @@ -0,0 +1,48 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(2..5)] of bool +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +branching on + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_Occurrence, + y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithDummy] +such that + and([x_Occurrence[i] /\ y_ExplicitVarSizeWithDummy[q27] != 6 -> i + 2 = y_ExplicitVarSizeWithDummy[q27] + | i : int(2..5), q27 : int(1..4)]), + 1 <= sum([toInt(x_Occurrence[q1]) | q1 : int(2..5)]), + and([y_ExplicitVarSizeWithDummy[q2] < y_ExplicitVarSizeWithDummy[q2 + 1] \/ y_ExplicitVarSizeWithDummy[q2] = 6 + | q2 : int(1..3)]), + and([y_ExplicitVarSizeWithDummy[q3] = 6 -> y_ExplicitVarSizeWithDummy[q3 + 1] = 6 | q3 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q4] != 6) | q4 : int(1..4)]), + and([q6 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q6] < x_ExplicitVarSizeWithMarker_Values[q6 + 1] + | q6 : int(1..3)]), + and([q7 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q7] = 2 | q7 : int(1..4)]), + 1 <= x_ExplicitVarSizeWithMarker_Marker, + and([q10 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q10]] + | q10 : int(1..4)]), + and([x_Occurrence[q11] -> + or([q13 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q13] = q11 + | q13 : int(1..4)]) + | q11 : int(2..5)]), + and([y_ExplicitVarSizeWithFlags_Flags[q14 + 1] -> + y_ExplicitVarSizeWithFlags_Values[q14] < y_ExplicitVarSizeWithFlags_Values[q14 + 1] + | q14 : int(1..3)]), + and([y_ExplicitVarSizeWithFlags_Flags[q15] = false -> y_ExplicitVarSizeWithFlags_Values[q15] = 2 + | q15 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q16 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q16] | q16 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q17]) | q17 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q20] -> + or([y_ExplicitVarSizeWithDummy[q22] != 6 /\ + y_ExplicitVarSizeWithDummy[q22] = y_ExplicitVarSizeWithFlags_Values[q20] + | q22 : int(1..4)]) + | q20 : int(1..4)]), + and([y_ExplicitVarSizeWithDummy[q24] != 6 -> + or([y_ExplicitVarSizeWithFlags_Flags[q26] /\ + y_ExplicitVarSizeWithFlags_Values[q26] = y_ExplicitVarSizeWithDummy[q24] + | q26 : int(1..4)]) + | q24 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_1_2_4_1-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_1_2_4_1-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_2_4_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_1_2_4_1-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_1_2_4_1-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_2_4_1-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_1_2_4_1.eprime b/tests/exhaustive/basic/set09/expected/model_1_2_4_1.eprime new file mode 100644 index 0000000000..eec7a2f559 --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_2_4_1.eprime @@ -0,0 +1,35 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(2..5)] of bool +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +find y_Occurrence: matrix indexed by [int(2..5)] of bool +branching on + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_Occurrence, y_Occurrence, + y_ExplicitVarSizeWithDummy] +such that + and([x_Occurrence[i] /\ y_ExplicitVarSizeWithDummy[q22] != 6 -> i + 2 = y_ExplicitVarSizeWithDummy[q22] + | i : int(2..5), q22 : int(1..4)]), + 1 <= sum([toInt(x_Occurrence[q1]) | q1 : int(2..5)]), + and([y_ExplicitVarSizeWithDummy[q2] < y_ExplicitVarSizeWithDummy[q2 + 1] \/ y_ExplicitVarSizeWithDummy[q2] = 6 + | q2 : int(1..3)]), + and([y_ExplicitVarSizeWithDummy[q3] = 6 -> y_ExplicitVarSizeWithDummy[q3 + 1] = 6 | q3 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q4] != 6) | q4 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q6] < x_ExplicitVarSizeWithFlags_Values[q6 + 1] + | q6 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q7] = false -> x_ExplicitVarSizeWithFlags_Values[q7] = 2 | q7 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q8 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q8] | q8 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q9]) | q9 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q12] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q12]] + | q12 : int(1..4)]), + and([x_Occurrence[q13] -> + or([x_ExplicitVarSizeWithFlags_Flags[q15] /\ x_ExplicitVarSizeWithFlags_Values[q15] = q13 | q15 : int(1..4)]) + | q13 : int(2..5)]), + 1 <= sum([toInt(y_Occurrence[q16]) | q16 : int(2..5)]), + and([y_Occurrence[q17] -> + or([y_ExplicitVarSizeWithDummy[q19] != 6 /\ y_ExplicitVarSizeWithDummy[q19] = q17 | q19 : int(1..4)]) + | q17 : int(2..5)]), + and([y_ExplicitVarSizeWithDummy[q21] != 6 -> y_Occurrence[y_ExplicitVarSizeWithDummy[q21]] | q21 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_1_2_4_2-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_1_2_4_2-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_2_4_2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_1_2_4_2-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_1_2_4_2-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_2_4_2-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_1_2_4_2.eprime b/tests/exhaustive/basic/set09/expected/model_1_2_4_2.eprime new file mode 100644 index 0000000000..fbd69fb422 --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_2_4_2.eprime @@ -0,0 +1,28 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(2..5)] of bool +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +branching on + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_Occurrence, y_ExplicitVarSizeWithDummy] +such that + and([x_Occurrence[i] /\ y_ExplicitVarSizeWithDummy[q16] != 6 -> i + 2 = y_ExplicitVarSizeWithDummy[q16] + | i : int(2..5), q16 : int(1..4)]), + 1 <= sum([toInt(x_Occurrence[q1]) | q1 : int(2..5)]), + and([y_ExplicitVarSizeWithDummy[q2] < y_ExplicitVarSizeWithDummy[q2 + 1] \/ y_ExplicitVarSizeWithDummy[q2] = 6 + | q2 : int(1..3)]), + and([y_ExplicitVarSizeWithDummy[q3] = 6 -> y_ExplicitVarSizeWithDummy[q3 + 1] = 6 | q3 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q4] != 6) | q4 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q6] < x_ExplicitVarSizeWithFlags_Values[q6 + 1] + | q6 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q7] = false -> x_ExplicitVarSizeWithFlags_Values[q7] = 2 | q7 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q8 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q8] | q8 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q9]) | q9 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q12] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q12]] + | q12 : int(1..4)]), + and([x_Occurrence[q13] -> + or([x_ExplicitVarSizeWithFlags_Flags[q15] /\ x_ExplicitVarSizeWithFlags_Values[q15] = q13 | q15 : int(1..4)]) + | q13 : int(2..5)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_1_2_4_3-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_1_2_4_3-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_2_4_3-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_1_2_4_3-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_1_2_4_3-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_2_4_3-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_1_2_4_3.eprime b/tests/exhaustive/basic/set09/expected/model_1_2_4_3.eprime new file mode 100644 index 0000000000..db9fd6336e --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_2_4_3.eprime @@ -0,0 +1,46 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(2..5)] of bool +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +find y_ExplicitVarSizeWithMarker_Marker: int(0..4) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +branching on + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_Occurrence, + y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithDummy] +such that + and([x_Occurrence[i] /\ y_ExplicitVarSizeWithDummy[q27] != 6 -> i + 2 = y_ExplicitVarSizeWithDummy[q27] + | i : int(2..5), q27 : int(1..4)]), + 1 <= sum([toInt(x_Occurrence[q1]) | q1 : int(2..5)]), + and([y_ExplicitVarSizeWithDummy[q2] < y_ExplicitVarSizeWithDummy[q2 + 1] \/ y_ExplicitVarSizeWithDummy[q2] = 6 + | q2 : int(1..3)]), + and([y_ExplicitVarSizeWithDummy[q3] = 6 -> y_ExplicitVarSizeWithDummy[q3 + 1] = 6 | q3 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q4] != 6) | q4 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q6] < x_ExplicitVarSizeWithFlags_Values[q6 + 1] + | q6 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q7] = false -> x_ExplicitVarSizeWithFlags_Values[q7] = 2 | q7 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q8 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q8] | q8 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q9]) | q9 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q12] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q12]] + | q12 : int(1..4)]), + and([x_Occurrence[q13] -> + or([x_ExplicitVarSizeWithFlags_Flags[q15] /\ x_ExplicitVarSizeWithFlags_Values[q15] = q13 | q15 : int(1..4)]) + | q13 : int(2..5)]), + and([q16 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> + y_ExplicitVarSizeWithMarker_Values[q16] < y_ExplicitVarSizeWithMarker_Values[q16 + 1] + | q16 : int(1..3)]), + and([q17 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q17] = 2 | q17 : int(1..4)]), + 1 <= y_ExplicitVarSizeWithMarker_Marker, + and([q20 <= y_ExplicitVarSizeWithMarker_Marker -> + or([y_ExplicitVarSizeWithDummy[q22] != 6 /\ + y_ExplicitVarSizeWithDummy[q22] = y_ExplicitVarSizeWithMarker_Values[q20] + | q22 : int(1..4)]) + | q20 : int(1..4)]), + and([y_ExplicitVarSizeWithDummy[q24] != 6 -> + or([q26 <= y_ExplicitVarSizeWithMarker_Marker /\ + y_ExplicitVarSizeWithMarker_Values[q26] = y_ExplicitVarSizeWithDummy[q24] + | q26 : int(1..4)]) + | q24 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_1_2_4_4-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_1_2_4_4-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_2_4_4-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_1_2_4_4-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_1_2_4_4-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_2_4_4-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_1_2_4_4.eprime b/tests/exhaustive/basic/set09/expected/model_1_2_4_4.eprime new file mode 100644 index 0000000000..f82060de74 --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_2_4_4.eprime @@ -0,0 +1,48 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(2..5)] of bool +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +branching on + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_Occurrence, + y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithDummy] +such that + and([x_Occurrence[i] /\ y_ExplicitVarSizeWithDummy[q29] != 6 -> i + 2 = y_ExplicitVarSizeWithDummy[q29] + | i : int(2..5), q29 : int(1..4)]), + 1 <= sum([toInt(x_Occurrence[q1]) | q1 : int(2..5)]), + and([y_ExplicitVarSizeWithDummy[q2] < y_ExplicitVarSizeWithDummy[q2 + 1] \/ y_ExplicitVarSizeWithDummy[q2] = 6 + | q2 : int(1..3)]), + and([y_ExplicitVarSizeWithDummy[q3] = 6 -> y_ExplicitVarSizeWithDummy[q3 + 1] = 6 | q3 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q4] != 6) | q4 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q6] < x_ExplicitVarSizeWithFlags_Values[q6 + 1] + | q6 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q7] = false -> x_ExplicitVarSizeWithFlags_Values[q7] = 2 | q7 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q8 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q8] | q8 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q9]) | q9 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q12] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q12]] + | q12 : int(1..4)]), + and([x_Occurrence[q13] -> + or([x_ExplicitVarSizeWithFlags_Flags[q15] /\ x_ExplicitVarSizeWithFlags_Values[q15] = q13 | q15 : int(1..4)]) + | q13 : int(2..5)]), + and([y_ExplicitVarSizeWithFlags_Flags[q16 + 1] -> + y_ExplicitVarSizeWithFlags_Values[q16] < y_ExplicitVarSizeWithFlags_Values[q16 + 1] + | q16 : int(1..3)]), + and([y_ExplicitVarSizeWithFlags_Flags[q17] = false -> y_ExplicitVarSizeWithFlags_Values[q17] = 2 + | q17 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q18 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q18] | q18 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q19]) | q19 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q22] -> + or([y_ExplicitVarSizeWithDummy[q24] != 6 /\ + y_ExplicitVarSizeWithDummy[q24] = y_ExplicitVarSizeWithFlags_Values[q22] + | q24 : int(1..4)]) + | q22 : int(1..4)]), + and([y_ExplicitVarSizeWithDummy[q26] != 6 -> + or([y_ExplicitVarSizeWithFlags_Flags[q28] /\ + y_ExplicitVarSizeWithFlags_Values[q28] = y_ExplicitVarSizeWithDummy[q26] + | q28 : int(1..4)]) + | q26 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_1_3_1_1-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_1_3_1_1-solution000001.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_3_1_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_1_3_1_1-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_1_3_1_1-solution000002.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_3_1_1-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_1_3_1_1.eprime b/tests/exhaustive/basic/set09/expected/model_1_3_1_1.eprime new file mode 100644 index 0000000000..5aa5be2149 --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_3_1_1.eprime @@ -0,0 +1,23 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(2..5)] of bool +find y_ExplicitVarSizeWithMarker_Marker: int(0..4) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_Occurrence: matrix indexed by [int(2..5)] of bool +branching on [x_Occurrence, y_Occurrence, y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values] +such that + and([x_Occurrence[i] /\ q11 <= y_ExplicitVarSizeWithMarker_Marker -> i + 2 = y_ExplicitVarSizeWithMarker_Values[q11] + | i : int(2..5), q11 : int(1..4)]), + 1 <= sum([toInt(x_Occurrence[q1]) | q1 : int(2..5)]), + and([q2 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> + y_ExplicitVarSizeWithMarker_Values[q2] < y_ExplicitVarSizeWithMarker_Values[q2 + 1] + | q2 : int(1..3)]), + and([q3 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q3] = 2 | q3 : int(1..4)]), + 1 <= y_ExplicitVarSizeWithMarker_Marker, + 1 <= sum([toInt(y_Occurrence[q5]) | q5 : int(2..5)]), + and([y_Occurrence[q6] -> + or([q8 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[q8] = q6 | q8 : int(1..4)]) + | q6 : int(2..5)]), + and([q10 <= y_ExplicitVarSizeWithMarker_Marker -> y_Occurrence[y_ExplicitVarSizeWithMarker_Values[q10]] + | q10 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_1_3_1_2-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_1_3_1_2-solution000001.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_3_1_2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_1_3_1_2-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_1_3_1_2-solution000002.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_3_1_2-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_1_3_1_2.eprime b/tests/exhaustive/basic/set09/expected/model_1_3_1_2.eprime new file mode 100644 index 0000000000..fd2bbeeb87 --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_3_1_2.eprime @@ -0,0 +1,32 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(2..5)] of bool +find y_ExplicitVarSizeWithMarker_Marker: int(0..4) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +branching on + [x_Occurrence, y_ExplicitVarSizeWithDummy, y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values] +such that + and([x_Occurrence[i] /\ q17 <= y_ExplicitVarSizeWithMarker_Marker -> i + 2 = y_ExplicitVarSizeWithMarker_Values[q17] + | i : int(2..5), q17 : int(1..4)]), + 1 <= sum([toInt(x_Occurrence[q1]) | q1 : int(2..5)]), + and([q2 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> + y_ExplicitVarSizeWithMarker_Values[q2] < y_ExplicitVarSizeWithMarker_Values[q2 + 1] + | q2 : int(1..3)]), + and([q3 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q3] = 2 | q3 : int(1..4)]), + 1 <= y_ExplicitVarSizeWithMarker_Marker, + and([y_ExplicitVarSizeWithDummy[q5] < y_ExplicitVarSizeWithDummy[q5 + 1] \/ y_ExplicitVarSizeWithDummy[q5] = 6 + | q5 : int(1..3)]), + and([y_ExplicitVarSizeWithDummy[q6] = 6 -> y_ExplicitVarSizeWithDummy[q6 + 1] = 6 | q6 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q7] != 6) | q7 : int(1..4)]), + and([y_ExplicitVarSizeWithDummy[q10] != 6 -> + or([q12 <= y_ExplicitVarSizeWithMarker_Marker /\ + y_ExplicitVarSizeWithMarker_Values[q12] = y_ExplicitVarSizeWithDummy[q10] + | q12 : int(1..4)]) + | q10 : int(1..4)]), + and([q14 <= y_ExplicitVarSizeWithMarker_Marker -> + or([y_ExplicitVarSizeWithDummy[q16] != 6 /\ + y_ExplicitVarSizeWithDummy[q16] = y_ExplicitVarSizeWithMarker_Values[q14] + | q16 : int(1..4)]) + | q14 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_1_3_1_3-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_1_3_1_3-solution000001.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_3_1_3-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_1_3_1_3-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_1_3_1_3-solution000002.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_3_1_3-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_1_3_1_3.eprime b/tests/exhaustive/basic/set09/expected/model_1_3_1_3.eprime new file mode 100644 index 0000000000..a2de25f50a --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_3_1_3.eprime @@ -0,0 +1,16 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(2..5)] of bool +find y_ExplicitVarSizeWithMarker_Marker: int(0..4) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +branching on [x_Occurrence, y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values] +such that + and([x_Occurrence[i] /\ q5 <= y_ExplicitVarSizeWithMarker_Marker -> i + 2 = y_ExplicitVarSizeWithMarker_Values[q5] + | i : int(2..5), q5 : int(1..4)]), + 1 <= sum([toInt(x_Occurrence[q1]) | q1 : int(2..5)]), + and([q2 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> + y_ExplicitVarSizeWithMarker_Values[q2] < y_ExplicitVarSizeWithMarker_Values[q2 + 1] + | q2 : int(1..3)]), + and([q3 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q3] = 2 | q3 : int(1..4)]), + 1 <= y_ExplicitVarSizeWithMarker_Marker + diff --git a/tests/exhaustive/basic/set09/expected/model_1_3_1_4-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_1_3_1_4-solution000001.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_3_1_4-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_1_3_1_4-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_1_3_1_4-solution000002.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_3_1_4-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_1_3_1_4.eprime b/tests/exhaustive/basic/set09/expected/model_1_3_1_4.eprime new file mode 100644 index 0000000000..7d10ae0289 --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_3_1_4.eprime @@ -0,0 +1,36 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(2..5)] of bool +find y_ExplicitVarSizeWithMarker_Marker: int(0..4) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +branching on + [x_Occurrence, y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values, + y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values] +such that + and([x_Occurrence[i] /\ q18 <= y_ExplicitVarSizeWithMarker_Marker -> i + 2 = y_ExplicitVarSizeWithMarker_Values[q18] + | i : int(2..5), q18 : int(1..4)]), + 1 <= sum([toInt(x_Occurrence[q1]) | q1 : int(2..5)]), + and([q2 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> + y_ExplicitVarSizeWithMarker_Values[q2] < y_ExplicitVarSizeWithMarker_Values[q2 + 1] + | q2 : int(1..3)]), + and([q3 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q3] = 2 | q3 : int(1..4)]), + 1 <= y_ExplicitVarSizeWithMarker_Marker, + and([y_ExplicitVarSizeWithFlags_Flags[q5 + 1] -> + y_ExplicitVarSizeWithFlags_Values[q5] < y_ExplicitVarSizeWithFlags_Values[q5 + 1] + | q5 : int(1..3)]), + and([y_ExplicitVarSizeWithFlags_Flags[q6] = false -> y_ExplicitVarSizeWithFlags_Values[q6] = 2 | q6 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q7] | q7 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q8]) | q8 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q11] -> + or([q13 <= y_ExplicitVarSizeWithMarker_Marker /\ + y_ExplicitVarSizeWithMarker_Values[q13] = y_ExplicitVarSizeWithFlags_Values[q11] + | q13 : int(1..4)]) + | q11 : int(1..4)]), + and([q15 <= y_ExplicitVarSizeWithMarker_Marker -> + or([y_ExplicitVarSizeWithFlags_Flags[q17] /\ + y_ExplicitVarSizeWithFlags_Values[q17] = y_ExplicitVarSizeWithMarker_Values[q15] + | q17 : int(1..4)]) + | q15 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_1_3_2_1-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_1_3_2_1-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_3_2_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_1_3_2_1-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_1_3_2_1-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_3_2_1-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_1_3_2_1.eprime b/tests/exhaustive/basic/set09/expected/model_1_3_2_1.eprime new file mode 100644 index 0000000000..aa45ad18ec --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_3_2_1.eprime @@ -0,0 +1,35 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(2..5)] of bool +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +find y_ExplicitVarSizeWithMarker_Marker: int(0..4) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_Occurrence: matrix indexed by [int(2..5)] of bool +branching on + [x_ExplicitVarSizeWithDummy, x_Occurrence, y_Occurrence, y_ExplicitVarSizeWithMarker_Marker, + y_ExplicitVarSizeWithMarker_Values] +such that + and([x_Occurrence[i] /\ q20 <= y_ExplicitVarSizeWithMarker_Marker -> i + 2 = y_ExplicitVarSizeWithMarker_Values[q20] + | i : int(2..5), q20 : int(1..4)]), + 1 <= sum([toInt(x_Occurrence[q1]) | q1 : int(2..5)]), + and([q2 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> + y_ExplicitVarSizeWithMarker_Values[q2] < y_ExplicitVarSizeWithMarker_Values[q2 + 1] + | q2 : int(1..3)]), + and([q3 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q3] = 2 | q3 : int(1..4)]), + 1 <= y_ExplicitVarSizeWithMarker_Marker, + and([x_ExplicitVarSizeWithDummy[q5] < x_ExplicitVarSizeWithDummy[q5 + 1] \/ x_ExplicitVarSizeWithDummy[q5] = 6 + | q5 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q6] = 6 -> x_ExplicitVarSizeWithDummy[q6 + 1] = 6 | q6 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q7] != 6) | q7 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q10] != 6 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q10]] | q10 : int(1..4)]), + and([x_Occurrence[q11] -> + or([x_ExplicitVarSizeWithDummy[q13] != 6 /\ x_ExplicitVarSizeWithDummy[q13] = q11 | q13 : int(1..4)]) + | q11 : int(2..5)]), + 1 <= sum([toInt(y_Occurrence[q14]) | q14 : int(2..5)]), + and([y_Occurrence[q15] -> + or([q17 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[q17] = q15 + | q17 : int(1..4)]) + | q15 : int(2..5)]), + and([q19 <= y_ExplicitVarSizeWithMarker_Marker -> y_Occurrence[y_ExplicitVarSizeWithMarker_Values[q19]] + | q19 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_1_3_2_2-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_1_3_2_2-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_3_2_2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_1_3_2_2-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_1_3_2_2-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_3_2_2-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_1_3_2_2.eprime b/tests/exhaustive/basic/set09/expected/model_1_3_2_2.eprime new file mode 100644 index 0000000000..12abc5a79c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_3_2_2.eprime @@ -0,0 +1,42 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(2..5)] of bool +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +find y_ExplicitVarSizeWithMarker_Marker: int(0..4) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +branching on + [x_ExplicitVarSizeWithDummy, x_Occurrence, y_ExplicitVarSizeWithDummy, y_ExplicitVarSizeWithMarker_Marker, + y_ExplicitVarSizeWithMarker_Values] +such that + and([x_Occurrence[i] /\ q26 <= y_ExplicitVarSizeWithMarker_Marker -> i + 2 = y_ExplicitVarSizeWithMarker_Values[q26] + | i : int(2..5), q26 : int(1..4)]), + 1 <= sum([toInt(x_Occurrence[q1]) | q1 : int(2..5)]), + and([q2 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> + y_ExplicitVarSizeWithMarker_Values[q2] < y_ExplicitVarSizeWithMarker_Values[q2 + 1] + | q2 : int(1..3)]), + and([q3 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q3] = 2 | q3 : int(1..4)]), + 1 <= y_ExplicitVarSizeWithMarker_Marker, + and([x_ExplicitVarSizeWithDummy[q5] < x_ExplicitVarSizeWithDummy[q5 + 1] \/ x_ExplicitVarSizeWithDummy[q5] = 6 + | q5 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q6] = 6 -> x_ExplicitVarSizeWithDummy[q6 + 1] = 6 | q6 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q7] != 6) | q7 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q10] != 6 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q10]] | q10 : int(1..4)]), + and([x_Occurrence[q11] -> + or([x_ExplicitVarSizeWithDummy[q13] != 6 /\ x_ExplicitVarSizeWithDummy[q13] = q11 | q13 : int(1..4)]) + | q11 : int(2..5)]), + and([y_ExplicitVarSizeWithDummy[q14] < y_ExplicitVarSizeWithDummy[q14 + 1] \/ y_ExplicitVarSizeWithDummy[q14] = 6 + | q14 : int(1..3)]), + and([y_ExplicitVarSizeWithDummy[q15] = 6 -> y_ExplicitVarSizeWithDummy[q15 + 1] = 6 | q15 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q16] != 6) | q16 : int(1..4)]), + and([y_ExplicitVarSizeWithDummy[q19] != 6 -> + or([q21 <= y_ExplicitVarSizeWithMarker_Marker /\ + y_ExplicitVarSizeWithMarker_Values[q21] = y_ExplicitVarSizeWithDummy[q19] + | q21 : int(1..4)]) + | q19 : int(1..4)]), + and([q23 <= y_ExplicitVarSizeWithMarker_Marker -> + or([y_ExplicitVarSizeWithDummy[q25] != 6 /\ + y_ExplicitVarSizeWithDummy[q25] = y_ExplicitVarSizeWithMarker_Values[q23] + | q25 : int(1..4)]) + | q23 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_1_3_2_3-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_1_3_2_3-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_3_2_3-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_1_3_2_3-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_1_3_2_3-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_3_2_3-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_1_3_2_3.eprime b/tests/exhaustive/basic/set09/expected/model_1_3_2_3.eprime new file mode 100644 index 0000000000..beae6fe911 --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_3_2_3.eprime @@ -0,0 +1,26 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(2..5)] of bool +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +find y_ExplicitVarSizeWithMarker_Marker: int(0..4) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +branching on + [x_ExplicitVarSizeWithDummy, x_Occurrence, y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values] +such that + and([x_Occurrence[i] /\ q14 <= y_ExplicitVarSizeWithMarker_Marker -> i + 2 = y_ExplicitVarSizeWithMarker_Values[q14] + | i : int(2..5), q14 : int(1..4)]), + 1 <= sum([toInt(x_Occurrence[q1]) | q1 : int(2..5)]), + and([q2 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> + y_ExplicitVarSizeWithMarker_Values[q2] < y_ExplicitVarSizeWithMarker_Values[q2 + 1] + | q2 : int(1..3)]), + and([q3 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q3] = 2 | q3 : int(1..4)]), + 1 <= y_ExplicitVarSizeWithMarker_Marker, + and([x_ExplicitVarSizeWithDummy[q5] < x_ExplicitVarSizeWithDummy[q5 + 1] \/ x_ExplicitVarSizeWithDummy[q5] = 6 + | q5 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q6] = 6 -> x_ExplicitVarSizeWithDummy[q6 + 1] = 6 | q6 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q7] != 6) | q7 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q10] != 6 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q10]] | q10 : int(1..4)]), + and([x_Occurrence[q11] -> + or([x_ExplicitVarSizeWithDummy[q13] != 6 /\ x_ExplicitVarSizeWithDummy[q13] = q11 | q13 : int(1..4)]) + | q11 : int(2..5)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_1_3_2_4-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_1_3_2_4-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_3_2_4-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_1_3_2_4-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_1_3_2_4-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_3_2_4-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_1_3_2_4.eprime b/tests/exhaustive/basic/set09/expected/model_1_3_2_4.eprime new file mode 100644 index 0000000000..0129c25cc0 --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_3_2_4.eprime @@ -0,0 +1,46 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(2..5)] of bool +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +find y_ExplicitVarSizeWithMarker_Marker: int(0..4) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +branching on + [x_ExplicitVarSizeWithDummy, x_Occurrence, y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values, + y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values] +such that + and([x_Occurrence[i] /\ q27 <= y_ExplicitVarSizeWithMarker_Marker -> i + 2 = y_ExplicitVarSizeWithMarker_Values[q27] + | i : int(2..5), q27 : int(1..4)]), + 1 <= sum([toInt(x_Occurrence[q1]) | q1 : int(2..5)]), + and([q2 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> + y_ExplicitVarSizeWithMarker_Values[q2] < y_ExplicitVarSizeWithMarker_Values[q2 + 1] + | q2 : int(1..3)]), + and([q3 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q3] = 2 | q3 : int(1..4)]), + 1 <= y_ExplicitVarSizeWithMarker_Marker, + and([x_ExplicitVarSizeWithDummy[q5] < x_ExplicitVarSizeWithDummy[q5 + 1] \/ x_ExplicitVarSizeWithDummy[q5] = 6 + | q5 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q6] = 6 -> x_ExplicitVarSizeWithDummy[q6 + 1] = 6 | q6 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q7] != 6) | q7 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q10] != 6 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q10]] | q10 : int(1..4)]), + and([x_Occurrence[q11] -> + or([x_ExplicitVarSizeWithDummy[q13] != 6 /\ x_ExplicitVarSizeWithDummy[q13] = q11 | q13 : int(1..4)]) + | q11 : int(2..5)]), + and([y_ExplicitVarSizeWithFlags_Flags[q14 + 1] -> + y_ExplicitVarSizeWithFlags_Values[q14] < y_ExplicitVarSizeWithFlags_Values[q14 + 1] + | q14 : int(1..3)]), + and([y_ExplicitVarSizeWithFlags_Flags[q15] = false -> y_ExplicitVarSizeWithFlags_Values[q15] = 2 + | q15 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q16 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q16] | q16 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q17]) | q17 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q20] -> + or([q22 <= y_ExplicitVarSizeWithMarker_Marker /\ + y_ExplicitVarSizeWithMarker_Values[q22] = y_ExplicitVarSizeWithFlags_Values[q20] + | q22 : int(1..4)]) + | q20 : int(1..4)]), + and([q24 <= y_ExplicitVarSizeWithMarker_Marker -> + or([y_ExplicitVarSizeWithFlags_Flags[q26] /\ + y_ExplicitVarSizeWithFlags_Values[q26] = y_ExplicitVarSizeWithMarker_Values[q24] + | q26 : int(1..4)]) + | q24 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_1_3_3_1-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_1_3_3_1-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_3_3_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_1_3_3_1-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_1_3_3_1-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_3_3_1-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_1_3_3_1.eprime b/tests/exhaustive/basic/set09/expected/model_1_3_3_1.eprime new file mode 100644 index 0000000000..e299f22797 --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_3_3_1.eprime @@ -0,0 +1,39 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(2..5)] of bool +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_ExplicitVarSizeWithMarker_Marker: int(0..4) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_Occurrence: matrix indexed by [int(2..5)] of bool +branching on + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_Occurrence, y_Occurrence, + y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values] +such that + and([x_Occurrence[i] /\ q19 <= y_ExplicitVarSizeWithMarker_Marker -> i + 2 = y_ExplicitVarSizeWithMarker_Values[q19] + | i : int(2..5), q19 : int(1..4)]), + 1 <= sum([toInt(x_Occurrence[q1]) | q1 : int(2..5)]), + and([q2 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> + y_ExplicitVarSizeWithMarker_Values[q2] < y_ExplicitVarSizeWithMarker_Values[q2 + 1] + | q2 : int(1..3)]), + and([q3 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q3] = 2 | q3 : int(1..4)]), + 1 <= y_ExplicitVarSizeWithMarker_Marker, + and([q5 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q5] < x_ExplicitVarSizeWithMarker_Values[q5 + 1] + | q5 : int(1..3)]), + and([q6 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q6] = 2 | q6 : int(1..4)]), + 1 <= x_ExplicitVarSizeWithMarker_Marker, + and([q9 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q9]] + | q9 : int(1..4)]), + and([x_Occurrence[q10] -> + or([q12 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q12] = q10 + | q12 : int(1..4)]) + | q10 : int(2..5)]), + 1 <= sum([toInt(y_Occurrence[q13]) | q13 : int(2..5)]), + and([y_Occurrence[q14] -> + or([q16 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[q16] = q14 + | q16 : int(1..4)]) + | q14 : int(2..5)]), + and([q18 <= y_ExplicitVarSizeWithMarker_Marker -> y_Occurrence[y_ExplicitVarSizeWithMarker_Values[q18]] + | q18 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_1_3_3_2-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_1_3_3_2-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_3_3_2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_1_3_3_2-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_1_3_3_2-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_3_3_2-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_1_3_3_2.eprime b/tests/exhaustive/basic/set09/expected/model_1_3_3_2.eprime new file mode 100644 index 0000000000..75e285106e --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_3_3_2.eprime @@ -0,0 +1,46 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(2..5)] of bool +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_ExplicitVarSizeWithMarker_Marker: int(0..4) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +branching on + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_Occurrence, y_ExplicitVarSizeWithDummy, + y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values] +such that + and([x_Occurrence[i] /\ q25 <= y_ExplicitVarSizeWithMarker_Marker -> i + 2 = y_ExplicitVarSizeWithMarker_Values[q25] + | i : int(2..5), q25 : int(1..4)]), + 1 <= sum([toInt(x_Occurrence[q1]) | q1 : int(2..5)]), + and([q2 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> + y_ExplicitVarSizeWithMarker_Values[q2] < y_ExplicitVarSizeWithMarker_Values[q2 + 1] + | q2 : int(1..3)]), + and([q3 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q3] = 2 | q3 : int(1..4)]), + 1 <= y_ExplicitVarSizeWithMarker_Marker, + and([q5 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q5] < x_ExplicitVarSizeWithMarker_Values[q5 + 1] + | q5 : int(1..3)]), + and([q6 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q6] = 2 | q6 : int(1..4)]), + 1 <= x_ExplicitVarSizeWithMarker_Marker, + and([q9 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q9]] + | q9 : int(1..4)]), + and([x_Occurrence[q10] -> + or([q12 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q12] = q10 + | q12 : int(1..4)]) + | q10 : int(2..5)]), + and([y_ExplicitVarSizeWithDummy[q13] < y_ExplicitVarSizeWithDummy[q13 + 1] \/ y_ExplicitVarSizeWithDummy[q13] = 6 + | q13 : int(1..3)]), + and([y_ExplicitVarSizeWithDummy[q14] = 6 -> y_ExplicitVarSizeWithDummy[q14 + 1] = 6 | q14 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q15] != 6) | q15 : int(1..4)]), + and([y_ExplicitVarSizeWithDummy[q18] != 6 -> + or([q20 <= y_ExplicitVarSizeWithMarker_Marker /\ + y_ExplicitVarSizeWithMarker_Values[q20] = y_ExplicitVarSizeWithDummy[q18] + | q20 : int(1..4)]) + | q18 : int(1..4)]), + and([q22 <= y_ExplicitVarSizeWithMarker_Marker -> + or([y_ExplicitVarSizeWithDummy[q24] != 6 /\ + y_ExplicitVarSizeWithDummy[q24] = y_ExplicitVarSizeWithMarker_Values[q22] + | q24 : int(1..4)]) + | q22 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_1_3_3_3-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_1_3_3_3-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_3_3_3-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_1_3_3_3-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_1_3_3_3-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_3_3_3-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_1_3_3_3.eprime b/tests/exhaustive/basic/set09/expected/model_1_3_3_3.eprime new file mode 100644 index 0000000000..c8c2dc92cf --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_3_3_3.eprime @@ -0,0 +1,31 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(2..5)] of bool +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_ExplicitVarSizeWithMarker_Marker: int(0..4) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +branching on + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_Occurrence, + y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values] +such that + and([x_Occurrence[i] /\ q13 <= y_ExplicitVarSizeWithMarker_Marker -> i + 2 = y_ExplicitVarSizeWithMarker_Values[q13] + | i : int(2..5), q13 : int(1..4)]), + 1 <= sum([toInt(x_Occurrence[q1]) | q1 : int(2..5)]), + and([q2 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> + y_ExplicitVarSizeWithMarker_Values[q2] < y_ExplicitVarSizeWithMarker_Values[q2 + 1] + | q2 : int(1..3)]), + and([q3 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q3] = 2 | q3 : int(1..4)]), + 1 <= y_ExplicitVarSizeWithMarker_Marker, + and([q5 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q5] < x_ExplicitVarSizeWithMarker_Values[q5 + 1] + | q5 : int(1..3)]), + and([q6 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q6] = 2 | q6 : int(1..4)]), + 1 <= x_ExplicitVarSizeWithMarker_Marker, + and([q9 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q9]] + | q9 : int(1..4)]), + and([x_Occurrence[q10] -> + or([q12 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q12] = q10 + | q12 : int(1..4)]) + | q10 : int(2..5)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_1_3_3_4-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_1_3_3_4-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_3_3_4-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_1_3_3_4-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_1_3_3_4-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_3_3_4-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_1_3_3_4.eprime b/tests/exhaustive/basic/set09/expected/model_1_3_3_4.eprime new file mode 100644 index 0000000000..04d78aaca9 --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_3_3_4.eprime @@ -0,0 +1,51 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(2..5)] of bool +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_ExplicitVarSizeWithMarker_Marker: int(0..4) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +branching on + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_Occurrence, + y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithMarker_Marker, + y_ExplicitVarSizeWithMarker_Values] +such that + and([x_Occurrence[i] /\ q26 <= y_ExplicitVarSizeWithMarker_Marker -> i + 2 = y_ExplicitVarSizeWithMarker_Values[q26] + | i : int(2..5), q26 : int(1..4)]), + 1 <= sum([toInt(x_Occurrence[q1]) | q1 : int(2..5)]), + and([q2 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> + y_ExplicitVarSizeWithMarker_Values[q2] < y_ExplicitVarSizeWithMarker_Values[q2 + 1] + | q2 : int(1..3)]), + and([q3 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q3] = 2 | q3 : int(1..4)]), + 1 <= y_ExplicitVarSizeWithMarker_Marker, + and([q5 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q5] < x_ExplicitVarSizeWithMarker_Values[q5 + 1] + | q5 : int(1..3)]), + and([q6 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q6] = 2 | q6 : int(1..4)]), + 1 <= x_ExplicitVarSizeWithMarker_Marker, + and([q9 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q9]] + | q9 : int(1..4)]), + and([x_Occurrence[q10] -> + or([q12 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q12] = q10 + | q12 : int(1..4)]) + | q10 : int(2..5)]), + and([y_ExplicitVarSizeWithFlags_Flags[q13 + 1] -> + y_ExplicitVarSizeWithFlags_Values[q13] < y_ExplicitVarSizeWithFlags_Values[q13 + 1] + | q13 : int(1..3)]), + and([y_ExplicitVarSizeWithFlags_Flags[q14] = false -> y_ExplicitVarSizeWithFlags_Values[q14] = 2 + | q14 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q15 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q15] | q15 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q16]) | q16 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q19] -> + or([q21 <= y_ExplicitVarSizeWithMarker_Marker /\ + y_ExplicitVarSizeWithMarker_Values[q21] = y_ExplicitVarSizeWithFlags_Values[q19] + | q21 : int(1..4)]) + | q19 : int(1..4)]), + and([q23 <= y_ExplicitVarSizeWithMarker_Marker -> + or([y_ExplicitVarSizeWithFlags_Flags[q25] /\ + y_ExplicitVarSizeWithFlags_Values[q25] = y_ExplicitVarSizeWithMarker_Values[q23] + | q25 : int(1..4)]) + | q23 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_1_3_4_1-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_1_3_4_1-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_3_4_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_1_3_4_1-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_1_3_4_1-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_3_4_1-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_1_3_4_1.eprime b/tests/exhaustive/basic/set09/expected/model_1_3_4_1.eprime new file mode 100644 index 0000000000..4beb160d92 --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_3_4_1.eprime @@ -0,0 +1,39 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(2..5)] of bool +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_ExplicitVarSizeWithMarker_Marker: int(0..4) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_Occurrence: matrix indexed by [int(2..5)] of bool +branching on + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_Occurrence, y_Occurrence, + y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values] +such that + and([x_Occurrence[i] /\ q21 <= y_ExplicitVarSizeWithMarker_Marker -> i + 2 = y_ExplicitVarSizeWithMarker_Values[q21] + | i : int(2..5), q21 : int(1..4)]), + 1 <= sum([toInt(x_Occurrence[q1]) | q1 : int(2..5)]), + and([q2 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> + y_ExplicitVarSizeWithMarker_Values[q2] < y_ExplicitVarSizeWithMarker_Values[q2 + 1] + | q2 : int(1..3)]), + and([q3 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q3] = 2 | q3 : int(1..4)]), + 1 <= y_ExplicitVarSizeWithMarker_Marker, + and([x_ExplicitVarSizeWithFlags_Flags[q5 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q5] < x_ExplicitVarSizeWithFlags_Values[q5 + 1] + | q5 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q6] = false -> x_ExplicitVarSizeWithFlags_Values[q6] = 2 | q6 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q7] | q7 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q8]) | q8 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q11] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q11]] + | q11 : int(1..4)]), + and([x_Occurrence[q12] -> + or([x_ExplicitVarSizeWithFlags_Flags[q14] /\ x_ExplicitVarSizeWithFlags_Values[q14] = q12 | q14 : int(1..4)]) + | q12 : int(2..5)]), + 1 <= sum([toInt(y_Occurrence[q15]) | q15 : int(2..5)]), + and([y_Occurrence[q16] -> + or([q18 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[q18] = q16 + | q18 : int(1..4)]) + | q16 : int(2..5)]), + and([q20 <= y_ExplicitVarSizeWithMarker_Marker -> y_Occurrence[y_ExplicitVarSizeWithMarker_Values[q20]] + | q20 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_1_3_4_2-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_1_3_4_2-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_3_4_2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_1_3_4_2-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_1_3_4_2-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_3_4_2-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_1_3_4_2.eprime b/tests/exhaustive/basic/set09/expected/model_1_3_4_2.eprime new file mode 100644 index 0000000000..9db3707298 --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_3_4_2.eprime @@ -0,0 +1,46 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(2..5)] of bool +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_ExplicitVarSizeWithMarker_Marker: int(0..4) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +branching on + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_Occurrence, y_ExplicitVarSizeWithDummy, + y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values] +such that + and([x_Occurrence[i] /\ q27 <= y_ExplicitVarSizeWithMarker_Marker -> i + 2 = y_ExplicitVarSizeWithMarker_Values[q27] + | i : int(2..5), q27 : int(1..4)]), + 1 <= sum([toInt(x_Occurrence[q1]) | q1 : int(2..5)]), + and([q2 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> + y_ExplicitVarSizeWithMarker_Values[q2] < y_ExplicitVarSizeWithMarker_Values[q2 + 1] + | q2 : int(1..3)]), + and([q3 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q3] = 2 | q3 : int(1..4)]), + 1 <= y_ExplicitVarSizeWithMarker_Marker, + and([x_ExplicitVarSizeWithFlags_Flags[q5 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q5] < x_ExplicitVarSizeWithFlags_Values[q5 + 1] + | q5 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q6] = false -> x_ExplicitVarSizeWithFlags_Values[q6] = 2 | q6 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q7] | q7 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q8]) | q8 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q11] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q11]] + | q11 : int(1..4)]), + and([x_Occurrence[q12] -> + or([x_ExplicitVarSizeWithFlags_Flags[q14] /\ x_ExplicitVarSizeWithFlags_Values[q14] = q12 | q14 : int(1..4)]) + | q12 : int(2..5)]), + and([y_ExplicitVarSizeWithDummy[q15] < y_ExplicitVarSizeWithDummy[q15 + 1] \/ y_ExplicitVarSizeWithDummy[q15] = 6 + | q15 : int(1..3)]), + and([y_ExplicitVarSizeWithDummy[q16] = 6 -> y_ExplicitVarSizeWithDummy[q16 + 1] = 6 | q16 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q17] != 6) | q17 : int(1..4)]), + and([y_ExplicitVarSizeWithDummy[q20] != 6 -> + or([q22 <= y_ExplicitVarSizeWithMarker_Marker /\ + y_ExplicitVarSizeWithMarker_Values[q22] = y_ExplicitVarSizeWithDummy[q20] + | q22 : int(1..4)]) + | q20 : int(1..4)]), + and([q24 <= y_ExplicitVarSizeWithMarker_Marker -> + or([y_ExplicitVarSizeWithDummy[q26] != 6 /\ + y_ExplicitVarSizeWithDummy[q26] = y_ExplicitVarSizeWithMarker_Values[q24] + | q26 : int(1..4)]) + | q24 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_1_3_4_3-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_1_3_4_3-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_3_4_3-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_1_3_4_3-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_1_3_4_3-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_3_4_3-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_1_3_4_3.eprime b/tests/exhaustive/basic/set09/expected/model_1_3_4_3.eprime new file mode 100644 index 0000000000..f452bb39ff --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_3_4_3.eprime @@ -0,0 +1,31 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(2..5)] of bool +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_ExplicitVarSizeWithMarker_Marker: int(0..4) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +branching on + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_Occurrence, + y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values] +such that + and([x_Occurrence[i] /\ q15 <= y_ExplicitVarSizeWithMarker_Marker -> i + 2 = y_ExplicitVarSizeWithMarker_Values[q15] + | i : int(2..5), q15 : int(1..4)]), + 1 <= sum([toInt(x_Occurrence[q1]) | q1 : int(2..5)]), + and([q2 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> + y_ExplicitVarSizeWithMarker_Values[q2] < y_ExplicitVarSizeWithMarker_Values[q2 + 1] + | q2 : int(1..3)]), + and([q3 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q3] = 2 | q3 : int(1..4)]), + 1 <= y_ExplicitVarSizeWithMarker_Marker, + and([x_ExplicitVarSizeWithFlags_Flags[q5 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q5] < x_ExplicitVarSizeWithFlags_Values[q5 + 1] + | q5 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q6] = false -> x_ExplicitVarSizeWithFlags_Values[q6] = 2 | q6 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q7] | q7 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q8]) | q8 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q11] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q11]] + | q11 : int(1..4)]), + and([x_Occurrence[q12] -> + or([x_ExplicitVarSizeWithFlags_Flags[q14] /\ x_ExplicitVarSizeWithFlags_Values[q14] = q12 | q14 : int(1..4)]) + | q12 : int(2..5)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_1_3_4_4-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_1_3_4_4-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_3_4_4-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_1_3_4_4-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_1_3_4_4-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_3_4_4-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_1_3_4_4.eprime b/tests/exhaustive/basic/set09/expected/model_1_3_4_4.eprime new file mode 100644 index 0000000000..dec6657450 --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_3_4_4.eprime @@ -0,0 +1,51 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(2..5)] of bool +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_ExplicitVarSizeWithMarker_Marker: int(0..4) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +branching on + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_Occurrence, + y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithMarker_Marker, + y_ExplicitVarSizeWithMarker_Values] +such that + and([x_Occurrence[i] /\ q28 <= y_ExplicitVarSizeWithMarker_Marker -> i + 2 = y_ExplicitVarSizeWithMarker_Values[q28] + | i : int(2..5), q28 : int(1..4)]), + 1 <= sum([toInt(x_Occurrence[q1]) | q1 : int(2..5)]), + and([q2 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> + y_ExplicitVarSizeWithMarker_Values[q2] < y_ExplicitVarSizeWithMarker_Values[q2 + 1] + | q2 : int(1..3)]), + and([q3 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q3] = 2 | q3 : int(1..4)]), + 1 <= y_ExplicitVarSizeWithMarker_Marker, + and([x_ExplicitVarSizeWithFlags_Flags[q5 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q5] < x_ExplicitVarSizeWithFlags_Values[q5 + 1] + | q5 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q6] = false -> x_ExplicitVarSizeWithFlags_Values[q6] = 2 | q6 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q7] | q7 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q8]) | q8 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q11] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q11]] + | q11 : int(1..4)]), + and([x_Occurrence[q12] -> + or([x_ExplicitVarSizeWithFlags_Flags[q14] /\ x_ExplicitVarSizeWithFlags_Values[q14] = q12 | q14 : int(1..4)]) + | q12 : int(2..5)]), + and([y_ExplicitVarSizeWithFlags_Flags[q15 + 1] -> + y_ExplicitVarSizeWithFlags_Values[q15] < y_ExplicitVarSizeWithFlags_Values[q15 + 1] + | q15 : int(1..3)]), + and([y_ExplicitVarSizeWithFlags_Flags[q16] = false -> y_ExplicitVarSizeWithFlags_Values[q16] = 2 + | q16 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q17 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q17] | q17 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q18]) | q18 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q21] -> + or([q23 <= y_ExplicitVarSizeWithMarker_Marker /\ + y_ExplicitVarSizeWithMarker_Values[q23] = y_ExplicitVarSizeWithFlags_Values[q21] + | q23 : int(1..4)]) + | q21 : int(1..4)]), + and([q25 <= y_ExplicitVarSizeWithMarker_Marker -> + or([y_ExplicitVarSizeWithFlags_Flags[q27] /\ + y_ExplicitVarSizeWithFlags_Values[q27] = y_ExplicitVarSizeWithMarker_Values[q25] + | q27 : int(1..4)]) + | q25 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_1_4_1_1-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_1_4_1_1-solution000001.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_4_1_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_1_4_1_1-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_1_4_1_1-solution000002.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_4_1_1-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_1_4_1_1.eprime b/tests/exhaustive/basic/set09/expected/model_1_4_1_1.eprime new file mode 100644 index 0000000000..6809b5e1fc --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_4_1_1.eprime @@ -0,0 +1,24 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(2..5)] of bool +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_Occurrence: matrix indexed by [int(2..5)] of bool +branching on [x_Occurrence, y_Occurrence, y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values] +such that + and([x_Occurrence[i] /\ y_ExplicitVarSizeWithFlags_Flags[q13] -> i + 2 = y_ExplicitVarSizeWithFlags_Values[q13] + | i : int(2..5), q13 : int(1..4)]), + 1 <= sum([toInt(x_Occurrence[q1]) | q1 : int(2..5)]), + and([y_ExplicitVarSizeWithFlags_Flags[q2 + 1] -> + y_ExplicitVarSizeWithFlags_Values[q2] < y_ExplicitVarSizeWithFlags_Values[q2 + 1] + | q2 : int(1..3)]), + and([y_ExplicitVarSizeWithFlags_Flags[q3] = false -> y_ExplicitVarSizeWithFlags_Values[q3] = 2 | q3 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q4] | q4 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q5]) | q5 : int(1..4)]), + 1 <= sum([toInt(y_Occurrence[q7]) | q7 : int(2..5)]), + and([y_Occurrence[q8] -> + or([y_ExplicitVarSizeWithFlags_Flags[q10] /\ y_ExplicitVarSizeWithFlags_Values[q10] = q8 | q10 : int(1..4)]) + | q8 : int(2..5)]), + and([y_ExplicitVarSizeWithFlags_Flags[q12] -> y_Occurrence[y_ExplicitVarSizeWithFlags_Values[q12]] + | q12 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_1_4_1_2-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_1_4_1_2-solution000001.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_4_1_2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_1_4_1_2-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_1_4_1_2-solution000002.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_4_1_2-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_1_4_1_2.eprime b/tests/exhaustive/basic/set09/expected/model_1_4_1_2.eprime new file mode 100644 index 0000000000..771b008b83 --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_4_1_2.eprime @@ -0,0 +1,33 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(2..5)] of bool +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +branching on + [x_Occurrence, y_ExplicitVarSizeWithDummy, y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values] +such that + and([x_Occurrence[i] /\ y_ExplicitVarSizeWithFlags_Flags[q19] -> i + 2 = y_ExplicitVarSizeWithFlags_Values[q19] + | i : int(2..5), q19 : int(1..4)]), + 1 <= sum([toInt(x_Occurrence[q1]) | q1 : int(2..5)]), + and([y_ExplicitVarSizeWithFlags_Flags[q2 + 1] -> + y_ExplicitVarSizeWithFlags_Values[q2] < y_ExplicitVarSizeWithFlags_Values[q2 + 1] + | q2 : int(1..3)]), + and([y_ExplicitVarSizeWithFlags_Flags[q3] = false -> y_ExplicitVarSizeWithFlags_Values[q3] = 2 | q3 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q4] | q4 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q5]) | q5 : int(1..4)]), + and([y_ExplicitVarSizeWithDummy[q7] < y_ExplicitVarSizeWithDummy[q7 + 1] \/ y_ExplicitVarSizeWithDummy[q7] = 6 + | q7 : int(1..3)]), + and([y_ExplicitVarSizeWithDummy[q8] = 6 -> y_ExplicitVarSizeWithDummy[q8 + 1] = 6 | q8 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q9] != 6) | q9 : int(1..4)]), + and([y_ExplicitVarSizeWithDummy[q12] != 6 -> + or([y_ExplicitVarSizeWithFlags_Flags[q14] /\ + y_ExplicitVarSizeWithFlags_Values[q14] = y_ExplicitVarSizeWithDummy[q12] + | q14 : int(1..4)]) + | q12 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q16] -> + or([y_ExplicitVarSizeWithDummy[q18] != 6 /\ + y_ExplicitVarSizeWithDummy[q18] = y_ExplicitVarSizeWithFlags_Values[q16] + | q18 : int(1..4)]) + | q16 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_1_4_1_3-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_1_4_1_3-solution000001.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_4_1_3-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_1_4_1_3-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_1_4_1_3-solution000002.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_4_1_3-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_1_4_1_3.eprime b/tests/exhaustive/basic/set09/expected/model_1_4_1_3.eprime new file mode 100644 index 0000000000..366e35ebb5 --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_4_1_3.eprime @@ -0,0 +1,36 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(2..5)] of bool +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_ExplicitVarSizeWithMarker_Marker: int(0..4) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +branching on + [x_Occurrence, y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values, + y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values] +such that + and([x_Occurrence[i] /\ y_ExplicitVarSizeWithFlags_Flags[q18] -> i + 2 = y_ExplicitVarSizeWithFlags_Values[q18] + | i : int(2..5), q18 : int(1..4)]), + 1 <= sum([toInt(x_Occurrence[q1]) | q1 : int(2..5)]), + and([y_ExplicitVarSizeWithFlags_Flags[q2 + 1] -> + y_ExplicitVarSizeWithFlags_Values[q2] < y_ExplicitVarSizeWithFlags_Values[q2 + 1] + | q2 : int(1..3)]), + and([y_ExplicitVarSizeWithFlags_Flags[q3] = false -> y_ExplicitVarSizeWithFlags_Values[q3] = 2 | q3 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q4] | q4 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q5]) | q5 : int(1..4)]), + and([q7 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> + y_ExplicitVarSizeWithMarker_Values[q7] < y_ExplicitVarSizeWithMarker_Values[q7 + 1] + | q7 : int(1..3)]), + and([q8 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q8] = 2 | q8 : int(1..4)]), + 1 <= y_ExplicitVarSizeWithMarker_Marker, + and([q11 <= y_ExplicitVarSizeWithMarker_Marker -> + or([y_ExplicitVarSizeWithFlags_Flags[q13] /\ + y_ExplicitVarSizeWithFlags_Values[q13] = y_ExplicitVarSizeWithMarker_Values[q11] + | q13 : int(1..4)]) + | q11 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q15] -> + or([q17 <= y_ExplicitVarSizeWithMarker_Marker /\ + y_ExplicitVarSizeWithMarker_Values[q17] = y_ExplicitVarSizeWithFlags_Values[q15] + | q17 : int(1..4)]) + | q15 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_1_4_1_4-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_1_4_1_4-solution000001.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_4_1_4-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_1_4_1_4-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_1_4_1_4-solution000002.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_4_1_4-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_1_4_1_4.eprime b/tests/exhaustive/basic/set09/expected/model_1_4_1_4.eprime new file mode 100644 index 0000000000..bfdab410df --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_4_1_4.eprime @@ -0,0 +1,17 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(2..5)] of bool +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +branching on [x_Occurrence, y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values] +such that + and([x_Occurrence[i] /\ y_ExplicitVarSizeWithFlags_Flags[q7] -> i + 2 = y_ExplicitVarSizeWithFlags_Values[q7] + | i : int(2..5), q7 : int(1..4)]), + 1 <= sum([toInt(x_Occurrence[q1]) | q1 : int(2..5)]), + and([y_ExplicitVarSizeWithFlags_Flags[q2 + 1] -> + y_ExplicitVarSizeWithFlags_Values[q2] < y_ExplicitVarSizeWithFlags_Values[q2 + 1] + | q2 : int(1..3)]), + and([y_ExplicitVarSizeWithFlags_Flags[q3] = false -> y_ExplicitVarSizeWithFlags_Values[q3] = 2 | q3 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q4] | q4 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q5]) | q5 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_1_4_2_1-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_1_4_2_1-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_4_2_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_1_4_2_1-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_1_4_2_1-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_4_2_1-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_1_4_2_1.eprime b/tests/exhaustive/basic/set09/expected/model_1_4_2_1.eprime new file mode 100644 index 0000000000..e41a4cfc54 --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_4_2_1.eprime @@ -0,0 +1,35 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(2..5)] of bool +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_Occurrence: matrix indexed by [int(2..5)] of bool +branching on + [x_ExplicitVarSizeWithDummy, x_Occurrence, y_Occurrence, y_ExplicitVarSizeWithFlags_Flags, + y_ExplicitVarSizeWithFlags_Values] +such that + and([x_Occurrence[i] /\ y_ExplicitVarSizeWithFlags_Flags[q22] -> i + 2 = y_ExplicitVarSizeWithFlags_Values[q22] + | i : int(2..5), q22 : int(1..4)]), + 1 <= sum([toInt(x_Occurrence[q1]) | q1 : int(2..5)]), + and([y_ExplicitVarSizeWithFlags_Flags[q2 + 1] -> + y_ExplicitVarSizeWithFlags_Values[q2] < y_ExplicitVarSizeWithFlags_Values[q2 + 1] + | q2 : int(1..3)]), + and([y_ExplicitVarSizeWithFlags_Flags[q3] = false -> y_ExplicitVarSizeWithFlags_Values[q3] = 2 | q3 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q4] | q4 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q5]) | q5 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q7] < x_ExplicitVarSizeWithDummy[q7 + 1] \/ x_ExplicitVarSizeWithDummy[q7] = 6 + | q7 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q8] = 6 -> x_ExplicitVarSizeWithDummy[q8 + 1] = 6 | q8 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q9] != 6) | q9 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q12] != 6 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q12]] | q12 : int(1..4)]), + and([x_Occurrence[q13] -> + or([x_ExplicitVarSizeWithDummy[q15] != 6 /\ x_ExplicitVarSizeWithDummy[q15] = q13 | q15 : int(1..4)]) + | q13 : int(2..5)]), + 1 <= sum([toInt(y_Occurrence[q16]) | q16 : int(2..5)]), + and([y_Occurrence[q17] -> + or([y_ExplicitVarSizeWithFlags_Flags[q19] /\ y_ExplicitVarSizeWithFlags_Values[q19] = q17 | q19 : int(1..4)]) + | q17 : int(2..5)]), + and([y_ExplicitVarSizeWithFlags_Flags[q21] -> y_Occurrence[y_ExplicitVarSizeWithFlags_Values[q21]] + | q21 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_1_4_2_2-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_1_4_2_2-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_4_2_2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_1_4_2_2-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_1_4_2_2-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_4_2_2-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_1_4_2_2.eprime b/tests/exhaustive/basic/set09/expected/model_1_4_2_2.eprime new file mode 100644 index 0000000000..64521d1cd6 --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_4_2_2.eprime @@ -0,0 +1,43 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(2..5)] of bool +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +branching on + [x_ExplicitVarSizeWithDummy, x_Occurrence, y_ExplicitVarSizeWithDummy, y_ExplicitVarSizeWithFlags_Flags, + y_ExplicitVarSizeWithFlags_Values] +such that + and([x_Occurrence[i] /\ y_ExplicitVarSizeWithFlags_Flags[q28] -> i + 2 = y_ExplicitVarSizeWithFlags_Values[q28] + | i : int(2..5), q28 : int(1..4)]), + 1 <= sum([toInt(x_Occurrence[q1]) | q1 : int(2..5)]), + and([y_ExplicitVarSizeWithFlags_Flags[q2 + 1] -> + y_ExplicitVarSizeWithFlags_Values[q2] < y_ExplicitVarSizeWithFlags_Values[q2 + 1] + | q2 : int(1..3)]), + and([y_ExplicitVarSizeWithFlags_Flags[q3] = false -> y_ExplicitVarSizeWithFlags_Values[q3] = 2 | q3 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q4] | q4 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q5]) | q5 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q7] < x_ExplicitVarSizeWithDummy[q7 + 1] \/ x_ExplicitVarSizeWithDummy[q7] = 6 + | q7 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q8] = 6 -> x_ExplicitVarSizeWithDummy[q8 + 1] = 6 | q8 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q9] != 6) | q9 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q12] != 6 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q12]] | q12 : int(1..4)]), + and([x_Occurrence[q13] -> + or([x_ExplicitVarSizeWithDummy[q15] != 6 /\ x_ExplicitVarSizeWithDummy[q15] = q13 | q15 : int(1..4)]) + | q13 : int(2..5)]), + and([y_ExplicitVarSizeWithDummy[q16] < y_ExplicitVarSizeWithDummy[q16 + 1] \/ y_ExplicitVarSizeWithDummy[q16] = 6 + | q16 : int(1..3)]), + and([y_ExplicitVarSizeWithDummy[q17] = 6 -> y_ExplicitVarSizeWithDummy[q17 + 1] = 6 | q17 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q18] != 6) | q18 : int(1..4)]), + and([y_ExplicitVarSizeWithDummy[q21] != 6 -> + or([y_ExplicitVarSizeWithFlags_Flags[q23] /\ + y_ExplicitVarSizeWithFlags_Values[q23] = y_ExplicitVarSizeWithDummy[q21] + | q23 : int(1..4)]) + | q21 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q25] -> + or([y_ExplicitVarSizeWithDummy[q27] != 6 /\ + y_ExplicitVarSizeWithDummy[q27] = y_ExplicitVarSizeWithFlags_Values[q25] + | q27 : int(1..4)]) + | q25 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_1_4_2_3-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_1_4_2_3-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_4_2_3-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_1_4_2_3-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_1_4_2_3-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_4_2_3-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_1_4_2_3.eprime b/tests/exhaustive/basic/set09/expected/model_1_4_2_3.eprime new file mode 100644 index 0000000000..68e8249552 --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_4_2_3.eprime @@ -0,0 +1,45 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(2..5)] of bool +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_ExplicitVarSizeWithMarker_Marker: int(0..4) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +branching on + [x_ExplicitVarSizeWithDummy, x_Occurrence, y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values, + y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values] +such that + and([x_Occurrence[i] /\ y_ExplicitVarSizeWithFlags_Flags[q27] -> i + 2 = y_ExplicitVarSizeWithFlags_Values[q27] + | i : int(2..5), q27 : int(1..4)]), + 1 <= sum([toInt(x_Occurrence[q1]) | q1 : int(2..5)]), + and([y_ExplicitVarSizeWithFlags_Flags[q2 + 1] -> + y_ExplicitVarSizeWithFlags_Values[q2] < y_ExplicitVarSizeWithFlags_Values[q2 + 1] + | q2 : int(1..3)]), + and([y_ExplicitVarSizeWithFlags_Flags[q3] = false -> y_ExplicitVarSizeWithFlags_Values[q3] = 2 | q3 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q4] | q4 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q5]) | q5 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q7] < x_ExplicitVarSizeWithDummy[q7 + 1] \/ x_ExplicitVarSizeWithDummy[q7] = 6 + | q7 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q8] = 6 -> x_ExplicitVarSizeWithDummy[q8 + 1] = 6 | q8 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q9] != 6) | q9 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q12] != 6 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q12]] | q12 : int(1..4)]), + and([x_Occurrence[q13] -> + or([x_ExplicitVarSizeWithDummy[q15] != 6 /\ x_ExplicitVarSizeWithDummy[q15] = q13 | q15 : int(1..4)]) + | q13 : int(2..5)]), + and([q16 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> + y_ExplicitVarSizeWithMarker_Values[q16] < y_ExplicitVarSizeWithMarker_Values[q16 + 1] + | q16 : int(1..3)]), + and([q17 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q17] = 2 | q17 : int(1..4)]), + 1 <= y_ExplicitVarSizeWithMarker_Marker, + and([q20 <= y_ExplicitVarSizeWithMarker_Marker -> + or([y_ExplicitVarSizeWithFlags_Flags[q22] /\ + y_ExplicitVarSizeWithFlags_Values[q22] = y_ExplicitVarSizeWithMarker_Values[q20] + | q22 : int(1..4)]) + | q20 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q24] -> + or([q26 <= y_ExplicitVarSizeWithMarker_Marker /\ + y_ExplicitVarSizeWithMarker_Values[q26] = y_ExplicitVarSizeWithFlags_Values[q24] + | q26 : int(1..4)]) + | q24 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_1_4_2_4-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_1_4_2_4-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_4_2_4-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_1_4_2_4-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_1_4_2_4-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_4_2_4-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_1_4_2_4.eprime b/tests/exhaustive/basic/set09/expected/model_1_4_2_4.eprime new file mode 100644 index 0000000000..2c847ef491 --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_4_2_4.eprime @@ -0,0 +1,27 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(2..5)] of bool +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +branching on + [x_ExplicitVarSizeWithDummy, x_Occurrence, y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values] +such that + and([x_Occurrence[i] /\ y_ExplicitVarSizeWithFlags_Flags[q16] -> i + 2 = y_ExplicitVarSizeWithFlags_Values[q16] + | i : int(2..5), q16 : int(1..4)]), + 1 <= sum([toInt(x_Occurrence[q1]) | q1 : int(2..5)]), + and([y_ExplicitVarSizeWithFlags_Flags[q2 + 1] -> + y_ExplicitVarSizeWithFlags_Values[q2] < y_ExplicitVarSizeWithFlags_Values[q2 + 1] + | q2 : int(1..3)]), + and([y_ExplicitVarSizeWithFlags_Flags[q3] = false -> y_ExplicitVarSizeWithFlags_Values[q3] = 2 | q3 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q4] | q4 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q5]) | q5 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q7] < x_ExplicitVarSizeWithDummy[q7 + 1] \/ x_ExplicitVarSizeWithDummy[q7] = 6 + | q7 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q8] = 6 -> x_ExplicitVarSizeWithDummy[q8 + 1] = 6 | q8 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q9] != 6) | q9 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q12] != 6 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q12]] | q12 : int(1..4)]), + and([x_Occurrence[q13] -> + or([x_ExplicitVarSizeWithDummy[q15] != 6 /\ x_ExplicitVarSizeWithDummy[q15] = q13 | q15 : int(1..4)]) + | q13 : int(2..5)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_1_4_3_1-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_1_4_3_1-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_4_3_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_1_4_3_1-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_1_4_3_1-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_4_3_1-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_1_4_3_1.eprime b/tests/exhaustive/basic/set09/expected/model_1_4_3_1.eprime new file mode 100644 index 0000000000..2c2cd8735b --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_4_3_1.eprime @@ -0,0 +1,39 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(2..5)] of bool +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_Occurrence: matrix indexed by [int(2..5)] of bool +branching on + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_Occurrence, y_Occurrence, + y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values] +such that + and([x_Occurrence[i] /\ y_ExplicitVarSizeWithFlags_Flags[q21] -> i + 2 = y_ExplicitVarSizeWithFlags_Values[q21] + | i : int(2..5), q21 : int(1..4)]), + 1 <= sum([toInt(x_Occurrence[q1]) | q1 : int(2..5)]), + and([y_ExplicitVarSizeWithFlags_Flags[q2 + 1] -> + y_ExplicitVarSizeWithFlags_Values[q2] < y_ExplicitVarSizeWithFlags_Values[q2 + 1] + | q2 : int(1..3)]), + and([y_ExplicitVarSizeWithFlags_Flags[q3] = false -> y_ExplicitVarSizeWithFlags_Values[q3] = 2 | q3 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q4] | q4 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q5]) | q5 : int(1..4)]), + and([q7 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q7] < x_ExplicitVarSizeWithMarker_Values[q7 + 1] + | q7 : int(1..3)]), + and([q8 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q8] = 2 | q8 : int(1..4)]), + 1 <= x_ExplicitVarSizeWithMarker_Marker, + and([q11 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q11]] + | q11 : int(1..4)]), + and([x_Occurrence[q12] -> + or([q14 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q14] = q12 + | q14 : int(1..4)]) + | q12 : int(2..5)]), + 1 <= sum([toInt(y_Occurrence[q15]) | q15 : int(2..5)]), + and([y_Occurrence[q16] -> + or([y_ExplicitVarSizeWithFlags_Flags[q18] /\ y_ExplicitVarSizeWithFlags_Values[q18] = q16 | q18 : int(1..4)]) + | q16 : int(2..5)]), + and([y_ExplicitVarSizeWithFlags_Flags[q20] -> y_Occurrence[y_ExplicitVarSizeWithFlags_Values[q20]] + | q20 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_1_4_3_2-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_1_4_3_2-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_4_3_2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_1_4_3_2-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_1_4_3_2-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_4_3_2-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_1_4_3_2.eprime b/tests/exhaustive/basic/set09/expected/model_1_4_3_2.eprime new file mode 100644 index 0000000000..dca70c6bd1 --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_4_3_2.eprime @@ -0,0 +1,47 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(2..5)] of bool +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +branching on + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_Occurrence, y_ExplicitVarSizeWithDummy, + y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values] +such that + and([x_Occurrence[i] /\ y_ExplicitVarSizeWithFlags_Flags[q27] -> i + 2 = y_ExplicitVarSizeWithFlags_Values[q27] + | i : int(2..5), q27 : int(1..4)]), + 1 <= sum([toInt(x_Occurrence[q1]) | q1 : int(2..5)]), + and([y_ExplicitVarSizeWithFlags_Flags[q2 + 1] -> + y_ExplicitVarSizeWithFlags_Values[q2] < y_ExplicitVarSizeWithFlags_Values[q2 + 1] + | q2 : int(1..3)]), + and([y_ExplicitVarSizeWithFlags_Flags[q3] = false -> y_ExplicitVarSizeWithFlags_Values[q3] = 2 | q3 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q4] | q4 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q5]) | q5 : int(1..4)]), + and([q7 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q7] < x_ExplicitVarSizeWithMarker_Values[q7 + 1] + | q7 : int(1..3)]), + and([q8 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q8] = 2 | q8 : int(1..4)]), + 1 <= x_ExplicitVarSizeWithMarker_Marker, + and([q11 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q11]] + | q11 : int(1..4)]), + and([x_Occurrence[q12] -> + or([q14 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q14] = q12 + | q14 : int(1..4)]) + | q12 : int(2..5)]), + and([y_ExplicitVarSizeWithDummy[q15] < y_ExplicitVarSizeWithDummy[q15 + 1] \/ y_ExplicitVarSizeWithDummy[q15] = 6 + | q15 : int(1..3)]), + and([y_ExplicitVarSizeWithDummy[q16] = 6 -> y_ExplicitVarSizeWithDummy[q16 + 1] = 6 | q16 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q17] != 6) | q17 : int(1..4)]), + and([y_ExplicitVarSizeWithDummy[q20] != 6 -> + or([y_ExplicitVarSizeWithFlags_Flags[q22] /\ + y_ExplicitVarSizeWithFlags_Values[q22] = y_ExplicitVarSizeWithDummy[q20] + | q22 : int(1..4)]) + | q20 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q24] -> + or([y_ExplicitVarSizeWithDummy[q26] != 6 /\ + y_ExplicitVarSizeWithDummy[q26] = y_ExplicitVarSizeWithFlags_Values[q24] + | q26 : int(1..4)]) + | q24 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_1_4_3_3-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_1_4_3_3-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_4_3_3-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_1_4_3_3-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_1_4_3_3-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_4_3_3-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_1_4_3_3.eprime b/tests/exhaustive/basic/set09/expected/model_1_4_3_3.eprime new file mode 100644 index 0000000000..bd28a832b9 --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_4_3_3.eprime @@ -0,0 +1,50 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(2..5)] of bool +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_ExplicitVarSizeWithMarker_Marker: int(0..4) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +branching on + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_Occurrence, + y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithFlags_Flags, + y_ExplicitVarSizeWithFlags_Values] +such that + and([x_Occurrence[i] /\ y_ExplicitVarSizeWithFlags_Flags[q26] -> i + 2 = y_ExplicitVarSizeWithFlags_Values[q26] + | i : int(2..5), q26 : int(1..4)]), + 1 <= sum([toInt(x_Occurrence[q1]) | q1 : int(2..5)]), + and([y_ExplicitVarSizeWithFlags_Flags[q2 + 1] -> + y_ExplicitVarSizeWithFlags_Values[q2] < y_ExplicitVarSizeWithFlags_Values[q2 + 1] + | q2 : int(1..3)]), + and([y_ExplicitVarSizeWithFlags_Flags[q3] = false -> y_ExplicitVarSizeWithFlags_Values[q3] = 2 | q3 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q4] | q4 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q5]) | q5 : int(1..4)]), + and([q7 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q7] < x_ExplicitVarSizeWithMarker_Values[q7 + 1] + | q7 : int(1..3)]), + and([q8 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q8] = 2 | q8 : int(1..4)]), + 1 <= x_ExplicitVarSizeWithMarker_Marker, + and([q11 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q11]] + | q11 : int(1..4)]), + and([x_Occurrence[q12] -> + or([q14 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q14] = q12 + | q14 : int(1..4)]) + | q12 : int(2..5)]), + and([q15 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> + y_ExplicitVarSizeWithMarker_Values[q15] < y_ExplicitVarSizeWithMarker_Values[q15 + 1] + | q15 : int(1..3)]), + and([q16 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q16] = 2 | q16 : int(1..4)]), + 1 <= y_ExplicitVarSizeWithMarker_Marker, + and([q19 <= y_ExplicitVarSizeWithMarker_Marker -> + or([y_ExplicitVarSizeWithFlags_Flags[q21] /\ + y_ExplicitVarSizeWithFlags_Values[q21] = y_ExplicitVarSizeWithMarker_Values[q19] + | q21 : int(1..4)]) + | q19 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q23] -> + or([q25 <= y_ExplicitVarSizeWithMarker_Marker /\ + y_ExplicitVarSizeWithMarker_Values[q25] = y_ExplicitVarSizeWithFlags_Values[q23] + | q25 : int(1..4)]) + | q23 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_1_4_3_4-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_1_4_3_4-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_4_3_4-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_1_4_3_4-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_1_4_3_4-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_4_3_4-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_1_4_3_4.eprime b/tests/exhaustive/basic/set09/expected/model_1_4_3_4.eprime new file mode 100644 index 0000000000..276806a903 --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_4_3_4.eprime @@ -0,0 +1,32 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(2..5)] of bool +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +branching on + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_Occurrence, + y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values] +such that + and([x_Occurrence[i] /\ y_ExplicitVarSizeWithFlags_Flags[q15] -> i + 2 = y_ExplicitVarSizeWithFlags_Values[q15] + | i : int(2..5), q15 : int(1..4)]), + 1 <= sum([toInt(x_Occurrence[q1]) | q1 : int(2..5)]), + and([y_ExplicitVarSizeWithFlags_Flags[q2 + 1] -> + y_ExplicitVarSizeWithFlags_Values[q2] < y_ExplicitVarSizeWithFlags_Values[q2 + 1] + | q2 : int(1..3)]), + and([y_ExplicitVarSizeWithFlags_Flags[q3] = false -> y_ExplicitVarSizeWithFlags_Values[q3] = 2 | q3 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q4] | q4 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q5]) | q5 : int(1..4)]), + and([q7 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q7] < x_ExplicitVarSizeWithMarker_Values[q7 + 1] + | q7 : int(1..3)]), + and([q8 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q8] = 2 | q8 : int(1..4)]), + 1 <= x_ExplicitVarSizeWithMarker_Marker, + and([q11 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q11]] + | q11 : int(1..4)]), + and([x_Occurrence[q12] -> + or([q14 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q14] = q12 + | q14 : int(1..4)]) + | q12 : int(2..5)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_1_4_4_1-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_1_4_4_1-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_4_4_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_1_4_4_1-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_1_4_4_1-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_4_4_1-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_1_4_4_1.eprime b/tests/exhaustive/basic/set09/expected/model_1_4_4_1.eprime new file mode 100644 index 0000000000..f3dfc3a80b --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_4_4_1.eprime @@ -0,0 +1,39 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(2..5)] of bool +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_Occurrence: matrix indexed by [int(2..5)] of bool +branching on + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_Occurrence, y_Occurrence, + y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values] +such that + and([x_Occurrence[i] /\ y_ExplicitVarSizeWithFlags_Flags[q23] -> i + 2 = y_ExplicitVarSizeWithFlags_Values[q23] + | i : int(2..5), q23 : int(1..4)]), + 1 <= sum([toInt(x_Occurrence[q1]) | q1 : int(2..5)]), + and([y_ExplicitVarSizeWithFlags_Flags[q2 + 1] -> + y_ExplicitVarSizeWithFlags_Values[q2] < y_ExplicitVarSizeWithFlags_Values[q2 + 1] + | q2 : int(1..3)]), + and([y_ExplicitVarSizeWithFlags_Flags[q3] = false -> y_ExplicitVarSizeWithFlags_Values[q3] = 2 | q3 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q4] | q4 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q5]) | q5 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q7] < x_ExplicitVarSizeWithFlags_Values[q7 + 1] + | q7 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q8] = false -> x_ExplicitVarSizeWithFlags_Values[q8] = 2 | q8 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q9 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q9] | q9 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q10]) | q10 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q13] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q13]] + | q13 : int(1..4)]), + and([x_Occurrence[q14] -> + or([x_ExplicitVarSizeWithFlags_Flags[q16] /\ x_ExplicitVarSizeWithFlags_Values[q16] = q14 | q16 : int(1..4)]) + | q14 : int(2..5)]), + 1 <= sum([toInt(y_Occurrence[q17]) | q17 : int(2..5)]), + and([y_Occurrence[q18] -> + or([y_ExplicitVarSizeWithFlags_Flags[q20] /\ y_ExplicitVarSizeWithFlags_Values[q20] = q18 | q20 : int(1..4)]) + | q18 : int(2..5)]), + and([y_ExplicitVarSizeWithFlags_Flags[q22] -> y_Occurrence[y_ExplicitVarSizeWithFlags_Values[q22]] + | q22 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_1_4_4_2-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_1_4_4_2-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_4_4_2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_1_4_4_2-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_1_4_4_2-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_4_4_2-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_1_4_4_2.eprime b/tests/exhaustive/basic/set09/expected/model_1_4_4_2.eprime new file mode 100644 index 0000000000..7d3a34561a --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_4_4_2.eprime @@ -0,0 +1,47 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(2..5)] of bool +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +branching on + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_Occurrence, y_ExplicitVarSizeWithDummy, + y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values] +such that + and([x_Occurrence[i] /\ y_ExplicitVarSizeWithFlags_Flags[q29] -> i + 2 = y_ExplicitVarSizeWithFlags_Values[q29] + | i : int(2..5), q29 : int(1..4)]), + 1 <= sum([toInt(x_Occurrence[q1]) | q1 : int(2..5)]), + and([y_ExplicitVarSizeWithFlags_Flags[q2 + 1] -> + y_ExplicitVarSizeWithFlags_Values[q2] < y_ExplicitVarSizeWithFlags_Values[q2 + 1] + | q2 : int(1..3)]), + and([y_ExplicitVarSizeWithFlags_Flags[q3] = false -> y_ExplicitVarSizeWithFlags_Values[q3] = 2 | q3 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q4] | q4 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q5]) | q5 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q7] < x_ExplicitVarSizeWithFlags_Values[q7 + 1] + | q7 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q8] = false -> x_ExplicitVarSizeWithFlags_Values[q8] = 2 | q8 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q9 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q9] | q9 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q10]) | q10 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q13] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q13]] + | q13 : int(1..4)]), + and([x_Occurrence[q14] -> + or([x_ExplicitVarSizeWithFlags_Flags[q16] /\ x_ExplicitVarSizeWithFlags_Values[q16] = q14 | q16 : int(1..4)]) + | q14 : int(2..5)]), + and([y_ExplicitVarSizeWithDummy[q17] < y_ExplicitVarSizeWithDummy[q17 + 1] \/ y_ExplicitVarSizeWithDummy[q17] = 6 + | q17 : int(1..3)]), + and([y_ExplicitVarSizeWithDummy[q18] = 6 -> y_ExplicitVarSizeWithDummy[q18 + 1] = 6 | q18 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q19] != 6) | q19 : int(1..4)]), + and([y_ExplicitVarSizeWithDummy[q22] != 6 -> + or([y_ExplicitVarSizeWithFlags_Flags[q24] /\ + y_ExplicitVarSizeWithFlags_Values[q24] = y_ExplicitVarSizeWithDummy[q22] + | q24 : int(1..4)]) + | q22 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q26] -> + or([y_ExplicitVarSizeWithDummy[q28] != 6 /\ + y_ExplicitVarSizeWithDummy[q28] = y_ExplicitVarSizeWithFlags_Values[q26] + | q28 : int(1..4)]) + | q26 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_1_4_4_3-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_1_4_4_3-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_4_4_3-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_1_4_4_3-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_1_4_4_3-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_4_4_3-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_1_4_4_3.eprime b/tests/exhaustive/basic/set09/expected/model_1_4_4_3.eprime new file mode 100644 index 0000000000..eeb7266e57 --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_4_4_3.eprime @@ -0,0 +1,50 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(2..5)] of bool +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_ExplicitVarSizeWithMarker_Marker: int(0..4) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +branching on + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_Occurrence, + y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithFlags_Flags, + y_ExplicitVarSizeWithFlags_Values] +such that + and([x_Occurrence[i] /\ y_ExplicitVarSizeWithFlags_Flags[q28] -> i + 2 = y_ExplicitVarSizeWithFlags_Values[q28] + | i : int(2..5), q28 : int(1..4)]), + 1 <= sum([toInt(x_Occurrence[q1]) | q1 : int(2..5)]), + and([y_ExplicitVarSizeWithFlags_Flags[q2 + 1] -> + y_ExplicitVarSizeWithFlags_Values[q2] < y_ExplicitVarSizeWithFlags_Values[q2 + 1] + | q2 : int(1..3)]), + and([y_ExplicitVarSizeWithFlags_Flags[q3] = false -> y_ExplicitVarSizeWithFlags_Values[q3] = 2 | q3 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q4] | q4 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q5]) | q5 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q7] < x_ExplicitVarSizeWithFlags_Values[q7 + 1] + | q7 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q8] = false -> x_ExplicitVarSizeWithFlags_Values[q8] = 2 | q8 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q9 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q9] | q9 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q10]) | q10 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q13] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q13]] + | q13 : int(1..4)]), + and([x_Occurrence[q14] -> + or([x_ExplicitVarSizeWithFlags_Flags[q16] /\ x_ExplicitVarSizeWithFlags_Values[q16] = q14 | q16 : int(1..4)]) + | q14 : int(2..5)]), + and([q17 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> + y_ExplicitVarSizeWithMarker_Values[q17] < y_ExplicitVarSizeWithMarker_Values[q17 + 1] + | q17 : int(1..3)]), + and([q18 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q18] = 2 | q18 : int(1..4)]), + 1 <= y_ExplicitVarSizeWithMarker_Marker, + and([q21 <= y_ExplicitVarSizeWithMarker_Marker -> + or([y_ExplicitVarSizeWithFlags_Flags[q23] /\ + y_ExplicitVarSizeWithFlags_Values[q23] = y_ExplicitVarSizeWithMarker_Values[q21] + | q23 : int(1..4)]) + | q21 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q25] -> + or([q27 <= y_ExplicitVarSizeWithMarker_Marker /\ + y_ExplicitVarSizeWithMarker_Values[q27] = y_ExplicitVarSizeWithFlags_Values[q25] + | q27 : int(1..4)]) + | q25 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_1_4_4_4-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_1_4_4_4-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_4_4_4-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_1_4_4_4-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_1_4_4_4-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_4_4_4-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_1_4_4_4.eprime b/tests/exhaustive/basic/set09/expected/model_1_4_4_4.eprime new file mode 100644 index 0000000000..f0669c2cb4 --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_1_4_4_4.eprime @@ -0,0 +1,32 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(2..5)] of bool +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +branching on + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_Occurrence, + y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values] +such that + and([x_Occurrence[i] /\ y_ExplicitVarSizeWithFlags_Flags[q17] -> i + 2 = y_ExplicitVarSizeWithFlags_Values[q17] + | i : int(2..5), q17 : int(1..4)]), + 1 <= sum([toInt(x_Occurrence[q1]) | q1 : int(2..5)]), + and([y_ExplicitVarSizeWithFlags_Flags[q2 + 1] -> + y_ExplicitVarSizeWithFlags_Values[q2] < y_ExplicitVarSizeWithFlags_Values[q2 + 1] + | q2 : int(1..3)]), + and([y_ExplicitVarSizeWithFlags_Flags[q3] = false -> y_ExplicitVarSizeWithFlags_Values[q3] = 2 | q3 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q4] | q4 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q5]) | q5 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q7] < x_ExplicitVarSizeWithFlags_Values[q7 + 1] + | q7 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q8] = false -> x_ExplicitVarSizeWithFlags_Values[q8] = 2 | q8 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q9 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q9] | q9 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q10]) | q10 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q13] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q13]] + | q13 : int(1..4)]), + and([x_Occurrence[q14] -> + or([x_ExplicitVarSizeWithFlags_Flags[q16] /\ x_ExplicitVarSizeWithFlags_Values[q16] = q14 | q16 : int(1..4)]) + | q14 : int(2..5)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_2_1_1_1-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_2_1_1_1-solution000001.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_1_1_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_2_1_1_1-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_2_1_1_1-solution000002.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_1_1_1-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_2_1_1_1.eprime b/tests/exhaustive/basic/set09/expected/model_2_1_1_1.eprime new file mode 100644 index 0000000000..761535fe98 --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_1_1_1.eprime @@ -0,0 +1,20 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +find x_Occurrence: matrix indexed by [int(2..5)] of bool +find y_Occurrence: matrix indexed by [int(2..5)] of bool +branching on [x_Occurrence, x_ExplicitVarSizeWithDummy, y_Occurrence] +such that + and([x_ExplicitVarSizeWithDummy[q12] != 6 /\ y_Occurrence[j] -> x_ExplicitVarSizeWithDummy[q12] + 2 = j + | q12 : int(1..4), j : int(2..5)]), + and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 6 + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q2] = 6 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 6 | q2 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 6) | q3 : int(1..4)]), + 1 <= sum([toInt(y_Occurrence[q5]) | q5 : int(2..5)]), + 1 <= sum([toInt(x_Occurrence[q6]) | q6 : int(2..5)]), + and([x_Occurrence[q7] -> + or([x_ExplicitVarSizeWithDummy[q9] != 6 /\ x_ExplicitVarSizeWithDummy[q9] = q7 | q9 : int(1..4)]) + | q7 : int(2..5)]), + and([x_ExplicitVarSizeWithDummy[q11] != 6 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q11]] | q11 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_2_1_1_2-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_2_1_1_2-solution000001.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_1_1_2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_2_1_1_2-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_2_1_1_2-solution000002.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_1_1_2-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_2_1_1_2.eprime b/tests/exhaustive/basic/set09/expected/model_2_1_1_2.eprime new file mode 100644 index 0000000000..b519538402 --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_1_1_2.eprime @@ -0,0 +1,29 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +find x_Occurrence: matrix indexed by [int(2..5)] of bool +find y_Occurrence: matrix indexed by [int(2..5)] of bool +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +branching on [x_Occurrence, x_ExplicitVarSizeWithDummy, y_ExplicitVarSizeWithDummy, y_Occurrence] +such that + and([x_ExplicitVarSizeWithDummy[q21] != 6 /\ y_Occurrence[j] -> x_ExplicitVarSizeWithDummy[q21] + 2 = j + | q21 : int(1..4), j : int(2..5)]), + and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 6 + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q2] = 6 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 6 | q2 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 6) | q3 : int(1..4)]), + 1 <= sum([toInt(y_Occurrence[q5]) | q5 : int(2..5)]), + 1 <= sum([toInt(x_Occurrence[q6]) | q6 : int(2..5)]), + and([x_Occurrence[q16] -> + or([x_ExplicitVarSizeWithDummy[q18] != 6 /\ x_ExplicitVarSizeWithDummy[q18] = q16 | q18 : int(1..4)]) + | q16 : int(2..5)]), + and([x_ExplicitVarSizeWithDummy[q20] != 6 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q20]] | q20 : int(1..4)]), + and([y_ExplicitVarSizeWithDummy[q7] < y_ExplicitVarSizeWithDummy[q7 + 1] \/ y_ExplicitVarSizeWithDummy[q7] = 6 + | q7 : int(1..3)]), + and([y_ExplicitVarSizeWithDummy[q8] = 6 -> y_ExplicitVarSizeWithDummy[q8 + 1] = 6 | q8 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q9] != 6) | q9 : int(1..4)]), + and([y_ExplicitVarSizeWithDummy[q12] != 6 -> y_Occurrence[y_ExplicitVarSizeWithDummy[q12]] | q12 : int(1..4)]), + and([y_Occurrence[q13] -> + or([y_ExplicitVarSizeWithDummy[q15] != 6 /\ y_ExplicitVarSizeWithDummy[q15] = q13 | q15 : int(1..4)]) + | q13 : int(2..5)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_2_1_1_3-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_2_1_1_3-solution000001.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_1_1_3-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_2_1_1_3-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_2_1_1_3-solution000002.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_1_1_3-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_2_1_1_3.eprime b/tests/exhaustive/basic/set09/expected/model_2_1_1_3.eprime new file mode 100644 index 0000000000..0726845331 --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_1_1_3.eprime @@ -0,0 +1,35 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +find x_Occurrence: matrix indexed by [int(2..5)] of bool +find y_Occurrence: matrix indexed by [int(2..5)] of bool +find y_ExplicitVarSizeWithMarker_Marker: int(0..4) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +branching on + [x_Occurrence, x_ExplicitVarSizeWithDummy, y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values, + y_Occurrence] +such that + and([x_ExplicitVarSizeWithDummy[q20] != 6 /\ y_Occurrence[j] -> x_ExplicitVarSizeWithDummy[q20] + 2 = j + | q20 : int(1..4), j : int(2..5)]), + and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 6 + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q2] = 6 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 6 | q2 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 6) | q3 : int(1..4)]), + 1 <= sum([toInt(y_Occurrence[q5]) | q5 : int(2..5)]), + 1 <= sum([toInt(x_Occurrence[q6]) | q6 : int(2..5)]), + and([x_Occurrence[q15] -> + or([x_ExplicitVarSizeWithDummy[q17] != 6 /\ x_ExplicitVarSizeWithDummy[q17] = q15 | q17 : int(1..4)]) + | q15 : int(2..5)]), + and([x_ExplicitVarSizeWithDummy[q19] != 6 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q19]] | q19 : int(1..4)]), + and([q7 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> + y_ExplicitVarSizeWithMarker_Values[q7] < y_ExplicitVarSizeWithMarker_Values[q7 + 1] + | q7 : int(1..3)]), + and([q8 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q8] = 2 | q8 : int(1..4)]), + 1 <= y_ExplicitVarSizeWithMarker_Marker, + and([q11 <= y_ExplicitVarSizeWithMarker_Marker -> y_Occurrence[y_ExplicitVarSizeWithMarker_Values[q11]] + | q11 : int(1..4)]), + and([y_Occurrence[q12] -> + or([q14 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[q14] = q12 + | q14 : int(1..4)]) + | q12 : int(2..5)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_2_1_1_4-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_2_1_1_4-solution000001.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_1_1_4-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_2_1_1_4-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_2_1_1_4-solution000002.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_1_1_4-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_2_1_1_4.eprime b/tests/exhaustive/basic/set09/expected/model_2_1_1_4.eprime new file mode 100644 index 0000000000..9d5ebd556d --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_1_1_4.eprime @@ -0,0 +1,35 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +find x_Occurrence: matrix indexed by [int(2..5)] of bool +find y_Occurrence: matrix indexed by [int(2..5)] of bool +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +branching on + [x_Occurrence, x_ExplicitVarSizeWithDummy, y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values, + y_Occurrence] +such that + and([x_ExplicitVarSizeWithDummy[q22] != 6 /\ y_Occurrence[j] -> x_ExplicitVarSizeWithDummy[q22] + 2 = j + | q22 : int(1..4), j : int(2..5)]), + and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 6 + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q2] = 6 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 6 | q2 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 6) | q3 : int(1..4)]), + 1 <= sum([toInt(y_Occurrence[q5]) | q5 : int(2..5)]), + 1 <= sum([toInt(x_Occurrence[q6]) | q6 : int(2..5)]), + and([x_Occurrence[q17] -> + or([x_ExplicitVarSizeWithDummy[q19] != 6 /\ x_ExplicitVarSizeWithDummy[q19] = q17 | q19 : int(1..4)]) + | q17 : int(2..5)]), + and([x_ExplicitVarSizeWithDummy[q21] != 6 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q21]] | q21 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> + y_ExplicitVarSizeWithFlags_Values[q7] < y_ExplicitVarSizeWithFlags_Values[q7 + 1] + | q7 : int(1..3)]), + and([y_ExplicitVarSizeWithFlags_Flags[q8] = false -> y_ExplicitVarSizeWithFlags_Values[q8] = 2 | q8 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q9 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q9] | q9 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q10]) | q10 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q13] -> y_Occurrence[y_ExplicitVarSizeWithFlags_Values[q13]] + | q13 : int(1..4)]), + and([y_Occurrence[q14] -> + or([y_ExplicitVarSizeWithFlags_Flags[q16] /\ y_ExplicitVarSizeWithFlags_Values[q16] = q14 | q16 : int(1..4)]) + | q14 : int(2..5)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_2_1_2_1-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_2_1_2_1-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_1_2_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_2_1_2_1-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_2_1_2_1-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_1_2_1-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_2_1_2_1.eprime b/tests/exhaustive/basic/set09/expected/model_2_1_2_1.eprime new file mode 100644 index 0000000000..5a90ec4c66 --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_1_2_1.eprime @@ -0,0 +1,14 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +find y_Occurrence: matrix indexed by [int(2..5)] of bool +branching on [x_ExplicitVarSizeWithDummy, y_Occurrence] +such that + and([x_ExplicitVarSizeWithDummy[q6] != 6 /\ y_Occurrence[j] -> x_ExplicitVarSizeWithDummy[q6] + 2 = j + | q6 : int(1..4), j : int(2..5)]), + and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 6 + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q2] = 6 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 6 | q2 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 6) | q3 : int(1..4)]), + 1 <= sum([toInt(y_Occurrence[q5]) | q5 : int(2..5)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_2_1_2_2-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_2_1_2_2-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_1_2_2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_2_1_2_2-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_2_1_2_2-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_1_2_2-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_2_1_2_2.eprime b/tests/exhaustive/basic/set09/expected/model_2_1_2_2.eprime new file mode 100644 index 0000000000..8811fd557f --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_1_2_2.eprime @@ -0,0 +1,23 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +find y_Occurrence: matrix indexed by [int(2..5)] of bool +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +branching on [x_ExplicitVarSizeWithDummy, y_ExplicitVarSizeWithDummy, y_Occurrence] +such that + and([x_ExplicitVarSizeWithDummy[q15] != 6 /\ y_Occurrence[j] -> x_ExplicitVarSizeWithDummy[q15] + 2 = j + | q15 : int(1..4), j : int(2..5)]), + and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 6 + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q2] = 6 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 6 | q2 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 6) | q3 : int(1..4)]), + 1 <= sum([toInt(y_Occurrence[q5]) | q5 : int(2..5)]), + and([y_ExplicitVarSizeWithDummy[q6] < y_ExplicitVarSizeWithDummy[q6 + 1] \/ y_ExplicitVarSizeWithDummy[q6] = 6 + | q6 : int(1..3)]), + and([y_ExplicitVarSizeWithDummy[q7] = 6 -> y_ExplicitVarSizeWithDummy[q7 + 1] = 6 | q7 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q8] != 6) | q8 : int(1..4)]), + and([y_ExplicitVarSizeWithDummy[q11] != 6 -> y_Occurrence[y_ExplicitVarSizeWithDummy[q11]] | q11 : int(1..4)]), + and([y_Occurrence[q12] -> + or([y_ExplicitVarSizeWithDummy[q14] != 6 /\ y_ExplicitVarSizeWithDummy[q14] = q12 | q14 : int(1..4)]) + | q12 : int(2..5)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_2_1_2_3-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_2_1_2_3-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_1_2_3-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_2_1_2_3-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_2_1_2_3-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_1_2_3-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_2_1_2_3.eprime b/tests/exhaustive/basic/set09/expected/model_2_1_2_3.eprime new file mode 100644 index 0000000000..5f0bbfbbee --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_1_2_3.eprime @@ -0,0 +1,28 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +find y_Occurrence: matrix indexed by [int(2..5)] of bool +find y_ExplicitVarSizeWithMarker_Marker: int(0..4) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +branching on + [x_ExplicitVarSizeWithDummy, y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values, y_Occurrence] +such that + and([x_ExplicitVarSizeWithDummy[q14] != 6 /\ y_Occurrence[j] -> x_ExplicitVarSizeWithDummy[q14] + 2 = j + | q14 : int(1..4), j : int(2..5)]), + and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 6 + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q2] = 6 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 6 | q2 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 6) | q3 : int(1..4)]), + 1 <= sum([toInt(y_Occurrence[q5]) | q5 : int(2..5)]), + and([q6 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> + y_ExplicitVarSizeWithMarker_Values[q6] < y_ExplicitVarSizeWithMarker_Values[q6 + 1] + | q6 : int(1..3)]), + and([q7 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q7] = 2 | q7 : int(1..4)]), + 1 <= y_ExplicitVarSizeWithMarker_Marker, + and([q10 <= y_ExplicitVarSizeWithMarker_Marker -> y_Occurrence[y_ExplicitVarSizeWithMarker_Values[q10]] + | q10 : int(1..4)]), + and([y_Occurrence[q11] -> + or([q13 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[q13] = q11 + | q13 : int(1..4)]) + | q11 : int(2..5)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_2_1_2_4-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_2_1_2_4-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_1_2_4-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_2_1_2_4-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_2_1_2_4-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_1_2_4-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_2_1_2_4.eprime b/tests/exhaustive/basic/set09/expected/model_2_1_2_4.eprime new file mode 100644 index 0000000000..d9eedcd6c7 --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_1_2_4.eprime @@ -0,0 +1,28 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +find y_Occurrence: matrix indexed by [int(2..5)] of bool +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +branching on + [x_ExplicitVarSizeWithDummy, y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values, y_Occurrence] +such that + and([x_ExplicitVarSizeWithDummy[q16] != 6 /\ y_Occurrence[j] -> x_ExplicitVarSizeWithDummy[q16] + 2 = j + | q16 : int(1..4), j : int(2..5)]), + and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 6 + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q2] = 6 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 6 | q2 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 6) | q3 : int(1..4)]), + 1 <= sum([toInt(y_Occurrence[q5]) | q5 : int(2..5)]), + and([y_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> + y_ExplicitVarSizeWithFlags_Values[q6] < y_ExplicitVarSizeWithFlags_Values[q6 + 1] + | q6 : int(1..3)]), + and([y_ExplicitVarSizeWithFlags_Flags[q7] = false -> y_ExplicitVarSizeWithFlags_Values[q7] = 2 | q7 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q8 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q8] | q8 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q9]) | q9 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q12] -> y_Occurrence[y_ExplicitVarSizeWithFlags_Values[q12]] + | q12 : int(1..4)]), + and([y_Occurrence[q13] -> + or([y_ExplicitVarSizeWithFlags_Flags[q15] /\ y_ExplicitVarSizeWithFlags_Values[q15] = q13 | q15 : int(1..4)]) + | q13 : int(2..5)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_2_1_3_1-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_2_1_3_1-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_1_3_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_2_1_3_1-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_2_1_3_1-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_1_3_1-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_2_1_3_1.eprime b/tests/exhaustive/basic/set09/expected/model_2_1_3_1.eprime new file mode 100644 index 0000000000..65dba9f00f --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_1_3_1.eprime @@ -0,0 +1,32 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_Occurrence: matrix indexed by [int(2..5)] of bool +branching on + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy, y_Occurrence] +such that + and([x_ExplicitVarSizeWithDummy[q17] != 6 /\ y_Occurrence[j] -> x_ExplicitVarSizeWithDummy[q17] + 2 = j + | q17 : int(1..4), j : int(2..5)]), + and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 6 + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q2] = 6 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 6 | q2 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 6) | q3 : int(1..4)]), + 1 <= sum([toInt(y_Occurrence[q5]) | q5 : int(2..5)]), + and([q6 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q6] < x_ExplicitVarSizeWithMarker_Values[q6 + 1] + | q6 : int(1..3)]), + and([q7 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q7] = 2 | q7 : int(1..4)]), + 1 <= x_ExplicitVarSizeWithMarker_Marker, + and([q10 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithDummy[q12] != 6 /\ + x_ExplicitVarSizeWithDummy[q12] = x_ExplicitVarSizeWithMarker_Values[q10] + | q12 : int(1..4)]) + | q10 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q14] != 6 -> + or([q16 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q16] = x_ExplicitVarSizeWithDummy[q14] + | q16 : int(1..4)]) + | q14 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_2_1_3_2-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_2_1_3_2-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_1_3_2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_2_1_3_2-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_2_1_3_2-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_1_3_2-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_2_1_3_2.eprime b/tests/exhaustive/basic/set09/expected/model_2_1_3_2.eprime new file mode 100644 index 0000000000..d2382f30b2 --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_1_3_2.eprime @@ -0,0 +1,42 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_Occurrence: matrix indexed by [int(2..5)] of bool +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +branching on + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy, + y_ExplicitVarSizeWithDummy, y_Occurrence] +such that + and([x_ExplicitVarSizeWithDummy[q26] != 6 /\ y_Occurrence[j] -> x_ExplicitVarSizeWithDummy[q26] + 2 = j + | q26 : int(1..4), j : int(2..5)]), + and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 6 + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q2] = 6 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 6 | q2 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 6) | q3 : int(1..4)]), + 1 <= sum([toInt(y_Occurrence[q5]) | q5 : int(2..5)]), + and([q6 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q6] < x_ExplicitVarSizeWithMarker_Values[q6 + 1] + | q6 : int(1..3)]), + and([q7 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q7] = 2 | q7 : int(1..4)]), + 1 <= x_ExplicitVarSizeWithMarker_Marker, + and([q10 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithDummy[q12] != 6 /\ + x_ExplicitVarSizeWithDummy[q12] = x_ExplicitVarSizeWithMarker_Values[q10] + | q12 : int(1..4)]) + | q10 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q14] != 6 -> + or([q16 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q16] = x_ExplicitVarSizeWithDummy[q14] + | q16 : int(1..4)]) + | q14 : int(1..4)]), + and([y_ExplicitVarSizeWithDummy[q17] < y_ExplicitVarSizeWithDummy[q17 + 1] \/ y_ExplicitVarSizeWithDummy[q17] = 6 + | q17 : int(1..3)]), + and([y_ExplicitVarSizeWithDummy[q18] = 6 -> y_ExplicitVarSizeWithDummy[q18 + 1] = 6 | q18 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q19] != 6) | q19 : int(1..4)]), + and([y_ExplicitVarSizeWithDummy[q22] != 6 -> y_Occurrence[y_ExplicitVarSizeWithDummy[q22]] | q22 : int(1..4)]), + and([y_Occurrence[q23] -> + or([y_ExplicitVarSizeWithDummy[q25] != 6 /\ y_ExplicitVarSizeWithDummy[q25] = q23 | q25 : int(1..4)]) + | q23 : int(2..5)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_2_1_3_3-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_2_1_3_3-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_1_3_3-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_2_1_3_3-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_2_1_3_3-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_1_3_3-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_2_1_3_3.eprime b/tests/exhaustive/basic/set09/expected/model_2_1_3_3.eprime new file mode 100644 index 0000000000..1ab91b53e0 --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_1_3_3.eprime @@ -0,0 +1,46 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_Occurrence: matrix indexed by [int(2..5)] of bool +find y_ExplicitVarSizeWithMarker_Marker: int(0..4) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +branching on + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy, + y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values, y_Occurrence] +such that + and([x_ExplicitVarSizeWithDummy[q25] != 6 /\ y_Occurrence[j] -> x_ExplicitVarSizeWithDummy[q25] + 2 = j + | q25 : int(1..4), j : int(2..5)]), + and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 6 + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q2] = 6 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 6 | q2 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 6) | q3 : int(1..4)]), + 1 <= sum([toInt(y_Occurrence[q5]) | q5 : int(2..5)]), + and([q6 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q6] < x_ExplicitVarSizeWithMarker_Values[q6 + 1] + | q6 : int(1..3)]), + and([q7 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q7] = 2 | q7 : int(1..4)]), + 1 <= x_ExplicitVarSizeWithMarker_Marker, + and([q10 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithDummy[q12] != 6 /\ + x_ExplicitVarSizeWithDummy[q12] = x_ExplicitVarSizeWithMarker_Values[q10] + | q12 : int(1..4)]) + | q10 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q14] != 6 -> + or([q16 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q16] = x_ExplicitVarSizeWithDummy[q14] + | q16 : int(1..4)]) + | q14 : int(1..4)]), + and([q17 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> + y_ExplicitVarSizeWithMarker_Values[q17] < y_ExplicitVarSizeWithMarker_Values[q17 + 1] + | q17 : int(1..3)]), + and([q18 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q18] = 2 | q18 : int(1..4)]), + 1 <= y_ExplicitVarSizeWithMarker_Marker, + and([q21 <= y_ExplicitVarSizeWithMarker_Marker -> y_Occurrence[y_ExplicitVarSizeWithMarker_Values[q21]] + | q21 : int(1..4)]), + and([y_Occurrence[q22] -> + or([q24 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[q24] = q22 + | q24 : int(1..4)]) + | q22 : int(2..5)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_2_1_3_4-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_2_1_3_4-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_1_3_4-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_2_1_3_4-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_2_1_3_4-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_1_3_4-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_2_1_3_4.eprime b/tests/exhaustive/basic/set09/expected/model_2_1_3_4.eprime new file mode 100644 index 0000000000..43ccdc1260 --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_1_3_4.eprime @@ -0,0 +1,47 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_Occurrence: matrix indexed by [int(2..5)] of bool +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +branching on + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy, + y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values, y_Occurrence] +such that + and([x_ExplicitVarSizeWithDummy[q27] != 6 /\ y_Occurrence[j] -> x_ExplicitVarSizeWithDummy[q27] + 2 = j + | q27 : int(1..4), j : int(2..5)]), + and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 6 + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q2] = 6 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 6 | q2 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 6) | q3 : int(1..4)]), + 1 <= sum([toInt(y_Occurrence[q5]) | q5 : int(2..5)]), + and([q6 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q6] < x_ExplicitVarSizeWithMarker_Values[q6 + 1] + | q6 : int(1..3)]), + and([q7 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q7] = 2 | q7 : int(1..4)]), + 1 <= x_ExplicitVarSizeWithMarker_Marker, + and([q10 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithDummy[q12] != 6 /\ + x_ExplicitVarSizeWithDummy[q12] = x_ExplicitVarSizeWithMarker_Values[q10] + | q12 : int(1..4)]) + | q10 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q14] != 6 -> + or([q16 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q16] = x_ExplicitVarSizeWithDummy[q14] + | q16 : int(1..4)]) + | q14 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q17 + 1] -> + y_ExplicitVarSizeWithFlags_Values[q17] < y_ExplicitVarSizeWithFlags_Values[q17 + 1] + | q17 : int(1..3)]), + and([y_ExplicitVarSizeWithFlags_Flags[q18] = false -> y_ExplicitVarSizeWithFlags_Values[q18] = 2 + | q18 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q19 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q19] | q19 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q20]) | q20 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q23] -> y_Occurrence[y_ExplicitVarSizeWithFlags_Values[q23]] + | q23 : int(1..4)]), + and([y_Occurrence[q24] -> + or([y_ExplicitVarSizeWithFlags_Flags[q26] /\ y_ExplicitVarSizeWithFlags_Values[q26] = q24 | q26 : int(1..4)]) + | q24 : int(2..5)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_2_1_4_1-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_2_1_4_1-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_1_4_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_2_1_4_1-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_2_1_4_1-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_1_4_1-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_2_1_4_1.eprime b/tests/exhaustive/basic/set09/expected/model_2_1_4_1.eprime new file mode 100644 index 0000000000..b726d03c45 --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_1_4_1.eprime @@ -0,0 +1,33 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_Occurrence: matrix indexed by [int(2..5)] of bool +branching on + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy, y_Occurrence] +such that + and([x_ExplicitVarSizeWithDummy[q19] != 6 /\ y_Occurrence[j] -> x_ExplicitVarSizeWithDummy[q19] + 2 = j + | q19 : int(1..4), j : int(2..5)]), + and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 6 + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q2] = 6 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 6 | q2 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 6) | q3 : int(1..4)]), + 1 <= sum([toInt(y_Occurrence[q5]) | q5 : int(2..5)]), + and([x_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q6] < x_ExplicitVarSizeWithFlags_Values[q6 + 1] + | q6 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q7] = false -> x_ExplicitVarSizeWithFlags_Values[q7] = 2 | q7 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q8 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q8] | q8 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q9]) | q9 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q12] -> + or([x_ExplicitVarSizeWithDummy[q14] != 6 /\ + x_ExplicitVarSizeWithDummy[q14] = x_ExplicitVarSizeWithFlags_Values[q12] + | q14 : int(1..4)]) + | q12 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q16] != 6 -> + or([x_ExplicitVarSizeWithFlags_Flags[q18] /\ + x_ExplicitVarSizeWithFlags_Values[q18] = x_ExplicitVarSizeWithDummy[q16] + | q18 : int(1..4)]) + | q16 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_2_1_4_2-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_2_1_4_2-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_1_4_2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_2_1_4_2-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_2_1_4_2-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_1_4_2-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_2_1_4_2.eprime b/tests/exhaustive/basic/set09/expected/model_2_1_4_2.eprime new file mode 100644 index 0000000000..6e2528d6b3 --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_1_4_2.eprime @@ -0,0 +1,43 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_Occurrence: matrix indexed by [int(2..5)] of bool +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +branching on + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy, + y_ExplicitVarSizeWithDummy, y_Occurrence] +such that + and([x_ExplicitVarSizeWithDummy[q28] != 6 /\ y_Occurrence[j] -> x_ExplicitVarSizeWithDummy[q28] + 2 = j + | q28 : int(1..4), j : int(2..5)]), + and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 6 + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q2] = 6 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 6 | q2 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 6) | q3 : int(1..4)]), + 1 <= sum([toInt(y_Occurrence[q5]) | q5 : int(2..5)]), + and([x_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q6] < x_ExplicitVarSizeWithFlags_Values[q6 + 1] + | q6 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q7] = false -> x_ExplicitVarSizeWithFlags_Values[q7] = 2 | q7 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q8 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q8] | q8 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q9]) | q9 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q12] -> + or([x_ExplicitVarSizeWithDummy[q14] != 6 /\ + x_ExplicitVarSizeWithDummy[q14] = x_ExplicitVarSizeWithFlags_Values[q12] + | q14 : int(1..4)]) + | q12 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q16] != 6 -> + or([x_ExplicitVarSizeWithFlags_Flags[q18] /\ + x_ExplicitVarSizeWithFlags_Values[q18] = x_ExplicitVarSizeWithDummy[q16] + | q18 : int(1..4)]) + | q16 : int(1..4)]), + and([y_ExplicitVarSizeWithDummy[q19] < y_ExplicitVarSizeWithDummy[q19 + 1] \/ y_ExplicitVarSizeWithDummy[q19] = 6 + | q19 : int(1..3)]), + and([y_ExplicitVarSizeWithDummy[q20] = 6 -> y_ExplicitVarSizeWithDummy[q20 + 1] = 6 | q20 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q21] != 6) | q21 : int(1..4)]), + and([y_ExplicitVarSizeWithDummy[q24] != 6 -> y_Occurrence[y_ExplicitVarSizeWithDummy[q24]] | q24 : int(1..4)]), + and([y_Occurrence[q25] -> + or([y_ExplicitVarSizeWithDummy[q27] != 6 /\ y_ExplicitVarSizeWithDummy[q27] = q25 | q27 : int(1..4)]) + | q25 : int(2..5)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_2_1_4_3-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_2_1_4_3-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_1_4_3-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_2_1_4_3-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_2_1_4_3-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_1_4_3-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_2_1_4_3.eprime b/tests/exhaustive/basic/set09/expected/model_2_1_4_3.eprime new file mode 100644 index 0000000000..6517abff37 --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_1_4_3.eprime @@ -0,0 +1,47 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_Occurrence: matrix indexed by [int(2..5)] of bool +find y_ExplicitVarSizeWithMarker_Marker: int(0..4) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +branching on + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy, + y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values, y_Occurrence] +such that + and([x_ExplicitVarSizeWithDummy[q27] != 6 /\ y_Occurrence[j] -> x_ExplicitVarSizeWithDummy[q27] + 2 = j + | q27 : int(1..4), j : int(2..5)]), + and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 6 + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q2] = 6 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 6 | q2 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 6) | q3 : int(1..4)]), + 1 <= sum([toInt(y_Occurrence[q5]) | q5 : int(2..5)]), + and([x_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q6] < x_ExplicitVarSizeWithFlags_Values[q6 + 1] + | q6 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q7] = false -> x_ExplicitVarSizeWithFlags_Values[q7] = 2 | q7 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q8 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q8] | q8 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q9]) | q9 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q12] -> + or([x_ExplicitVarSizeWithDummy[q14] != 6 /\ + x_ExplicitVarSizeWithDummy[q14] = x_ExplicitVarSizeWithFlags_Values[q12] + | q14 : int(1..4)]) + | q12 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q16] != 6 -> + or([x_ExplicitVarSizeWithFlags_Flags[q18] /\ + x_ExplicitVarSizeWithFlags_Values[q18] = x_ExplicitVarSizeWithDummy[q16] + | q18 : int(1..4)]) + | q16 : int(1..4)]), + and([q19 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> + y_ExplicitVarSizeWithMarker_Values[q19] < y_ExplicitVarSizeWithMarker_Values[q19 + 1] + | q19 : int(1..3)]), + and([q20 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q20] = 2 | q20 : int(1..4)]), + 1 <= y_ExplicitVarSizeWithMarker_Marker, + and([q23 <= y_ExplicitVarSizeWithMarker_Marker -> y_Occurrence[y_ExplicitVarSizeWithMarker_Values[q23]] + | q23 : int(1..4)]), + and([y_Occurrence[q24] -> + or([q26 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[q26] = q24 + | q26 : int(1..4)]) + | q24 : int(2..5)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_2_1_4_4-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_2_1_4_4-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_1_4_4-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_2_1_4_4-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_2_1_4_4-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_1_4_4-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_2_1_4_4.eprime b/tests/exhaustive/basic/set09/expected/model_2_1_4_4.eprime new file mode 100644 index 0000000000..a99b49c2ba --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_1_4_4.eprime @@ -0,0 +1,48 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_Occurrence: matrix indexed by [int(2..5)] of bool +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +branching on + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy, + y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values, y_Occurrence] +such that + and([x_ExplicitVarSizeWithDummy[q29] != 6 /\ y_Occurrence[j] -> x_ExplicitVarSizeWithDummy[q29] + 2 = j + | q29 : int(1..4), j : int(2..5)]), + and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 6 + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q2] = 6 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 6 | q2 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 6) | q3 : int(1..4)]), + 1 <= sum([toInt(y_Occurrence[q5]) | q5 : int(2..5)]), + and([x_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q6] < x_ExplicitVarSizeWithFlags_Values[q6 + 1] + | q6 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q7] = false -> x_ExplicitVarSizeWithFlags_Values[q7] = 2 | q7 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q8 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q8] | q8 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q9]) | q9 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q12] -> + or([x_ExplicitVarSizeWithDummy[q14] != 6 /\ + x_ExplicitVarSizeWithDummy[q14] = x_ExplicitVarSizeWithFlags_Values[q12] + | q14 : int(1..4)]) + | q12 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q16] != 6 -> + or([x_ExplicitVarSizeWithFlags_Flags[q18] /\ + x_ExplicitVarSizeWithFlags_Values[q18] = x_ExplicitVarSizeWithDummy[q16] + | q18 : int(1..4)]) + | q16 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q19 + 1] -> + y_ExplicitVarSizeWithFlags_Values[q19] < y_ExplicitVarSizeWithFlags_Values[q19 + 1] + | q19 : int(1..3)]), + and([y_ExplicitVarSizeWithFlags_Flags[q20] = false -> y_ExplicitVarSizeWithFlags_Values[q20] = 2 + | q20 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q21 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q21] | q21 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q22]) | q22 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q25] -> y_Occurrence[y_ExplicitVarSizeWithFlags_Values[q25]] + | q25 : int(1..4)]), + and([y_Occurrence[q26] -> + or([y_ExplicitVarSizeWithFlags_Flags[q28] /\ y_ExplicitVarSizeWithFlags_Values[q28] = q26 | q28 : int(1..4)]) + | q26 : int(2..5)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_2_2_1_1-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_2_2_1_1-solution000001.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_2_1_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_2_2_1_1-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_2_2_1_1-solution000002.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_2_1_1-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_2_2_1_1.eprime b/tests/exhaustive/basic/set09/expected/model_2_2_1_1.eprime new file mode 100644 index 0000000000..6abf3ea8b6 --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_2_1_1.eprime @@ -0,0 +1,30 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +find x_Occurrence: matrix indexed by [int(2..5)] of bool +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +find y_Occurrence: matrix indexed by [int(2..5)] of bool +branching on [x_Occurrence, x_ExplicitVarSizeWithDummy, y_Occurrence, y_ExplicitVarSizeWithDummy] +such that + and([x_ExplicitVarSizeWithDummy[q16] != 6 /\ y_ExplicitVarSizeWithDummy[q17] != 6 -> + x_ExplicitVarSizeWithDummy[q16] + 2 = y_ExplicitVarSizeWithDummy[q17] + | q16 : int(1..4), q17 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 6 + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q2] = 6 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 6 | q2 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 6) | q3 : int(1..4)]), + and([y_ExplicitVarSizeWithDummy[q5] < y_ExplicitVarSizeWithDummy[q5 + 1] \/ y_ExplicitVarSizeWithDummy[q5] = 6 + | q5 : int(1..3)]), + and([y_ExplicitVarSizeWithDummy[q6] = 6 -> y_ExplicitVarSizeWithDummy[q6 + 1] = 6 | q6 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q7] != 6) | q7 : int(1..4)]), + 1 <= sum([toInt(x_Occurrence[q9]) | q9 : int(2..5)]), + and([x_Occurrence[q18] -> + or([x_ExplicitVarSizeWithDummy[q20] != 6 /\ x_ExplicitVarSizeWithDummy[q20] = q18 | q20 : int(1..4)]) + | q18 : int(2..5)]), + and([x_ExplicitVarSizeWithDummy[q22] != 6 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q22]] | q22 : int(1..4)]), + 1 <= sum([toInt(y_Occurrence[q10]) | q10 : int(2..5)]), + and([y_Occurrence[q11] -> + or([y_ExplicitVarSizeWithDummy[q13] != 6 /\ y_ExplicitVarSizeWithDummy[q13] = q11 | q13 : int(1..4)]) + | q11 : int(2..5)]), + and([y_ExplicitVarSizeWithDummy[q15] != 6 -> y_Occurrence[y_ExplicitVarSizeWithDummy[q15]] | q15 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_2_2_1_2-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_2_2_1_2-solution000001.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_2_1_2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_2_2_1_2-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_2_2_1_2-solution000002.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_2_1_2-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_2_2_1_2.eprime b/tests/exhaustive/basic/set09/expected/model_2_2_1_2.eprime new file mode 100644 index 0000000000..0b17a9f152 --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_2_1_2.eprime @@ -0,0 +1,24 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +find x_Occurrence: matrix indexed by [int(2..5)] of bool +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +branching on [x_Occurrence, x_ExplicitVarSizeWithDummy, y_ExplicitVarSizeWithDummy] +such that + and([x_ExplicitVarSizeWithDummy[q15] != 6 /\ y_ExplicitVarSizeWithDummy[q16] != 6 -> + x_ExplicitVarSizeWithDummy[q15] + 2 = y_ExplicitVarSizeWithDummy[q16] + | q15 : int(1..4), q16 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 6 + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q2] = 6 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 6 | q2 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 6) | q3 : int(1..4)]), + and([y_ExplicitVarSizeWithDummy[q5] < y_ExplicitVarSizeWithDummy[q5 + 1] \/ y_ExplicitVarSizeWithDummy[q5] = 6 + | q5 : int(1..3)]), + and([y_ExplicitVarSizeWithDummy[q6] = 6 -> y_ExplicitVarSizeWithDummy[q6 + 1] = 6 | q6 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q7] != 6) | q7 : int(1..4)]), + 1 <= sum([toInt(x_Occurrence[q9]) | q9 : int(2..5)]), + and([x_Occurrence[q10] -> + or([x_ExplicitVarSizeWithDummy[q12] != 6 /\ x_ExplicitVarSizeWithDummy[q12] = q10 | q12 : int(1..4)]) + | q10 : int(2..5)]), + and([x_ExplicitVarSizeWithDummy[q14] != 6 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q14]] | q14 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_2_2_1_3-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_2_2_1_3-solution000001.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_2_1_3-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_2_2_1_3-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_2_2_1_3-solution000002.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_2_1_3-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_2_2_1_3.eprime b/tests/exhaustive/basic/set09/expected/model_2_2_1_3.eprime new file mode 100644 index 0000000000..c40c45e8b1 --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_2_1_3.eprime @@ -0,0 +1,43 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +find x_Occurrence: matrix indexed by [int(2..5)] of bool +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +find y_ExplicitVarSizeWithMarker_Marker: int(0..4) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +branching on + [x_Occurrence, x_ExplicitVarSizeWithDummy, y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values, + y_ExplicitVarSizeWithDummy] +such that + and([x_ExplicitVarSizeWithDummy[q26] != 6 /\ y_ExplicitVarSizeWithDummy[q27] != 6 -> + x_ExplicitVarSizeWithDummy[q26] + 2 = y_ExplicitVarSizeWithDummy[q27] + | q26 : int(1..4), q27 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 6 + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q2] = 6 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 6 | q2 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 6) | q3 : int(1..4)]), + and([y_ExplicitVarSizeWithDummy[q5] < y_ExplicitVarSizeWithDummy[q5 + 1] \/ y_ExplicitVarSizeWithDummy[q5] = 6 + | q5 : int(1..3)]), + and([y_ExplicitVarSizeWithDummy[q6] = 6 -> y_ExplicitVarSizeWithDummy[q6 + 1] = 6 | q6 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q7] != 6) | q7 : int(1..4)]), + 1 <= sum([toInt(x_Occurrence[q9]) | q9 : int(2..5)]), + and([x_Occurrence[q21] -> + or([x_ExplicitVarSizeWithDummy[q23] != 6 /\ x_ExplicitVarSizeWithDummy[q23] = q21 | q23 : int(1..4)]) + | q21 : int(2..5)]), + and([x_ExplicitVarSizeWithDummy[q25] != 6 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q25]] | q25 : int(1..4)]), + and([q10 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> + y_ExplicitVarSizeWithMarker_Values[q10] < y_ExplicitVarSizeWithMarker_Values[q10 + 1] + | q10 : int(1..3)]), + and([q11 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q11] = 2 | q11 : int(1..4)]), + 1 <= y_ExplicitVarSizeWithMarker_Marker, + and([q14 <= y_ExplicitVarSizeWithMarker_Marker -> + or([y_ExplicitVarSizeWithDummy[q16] != 6 /\ + y_ExplicitVarSizeWithDummy[q16] = y_ExplicitVarSizeWithMarker_Values[q14] + | q16 : int(1..4)]) + | q14 : int(1..4)]), + and([y_ExplicitVarSizeWithDummy[q18] != 6 -> + or([q20 <= y_ExplicitVarSizeWithMarker_Marker /\ + y_ExplicitVarSizeWithMarker_Values[q20] = y_ExplicitVarSizeWithDummy[q18] + | q20 : int(1..4)]) + | q18 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_2_2_1_4-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_2_2_1_4-solution000001.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_2_1_4-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_2_2_1_4-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_2_2_1_4-solution000002.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_2_1_4-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_2_2_1_4.eprime b/tests/exhaustive/basic/set09/expected/model_2_2_1_4.eprime new file mode 100644 index 0000000000..0cdf8a54bd --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_2_1_4.eprime @@ -0,0 +1,45 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +find x_Occurrence: matrix indexed by [int(2..5)] of bool +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +branching on + [x_Occurrence, x_ExplicitVarSizeWithDummy, y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values, + y_ExplicitVarSizeWithDummy] +such that + and([x_ExplicitVarSizeWithDummy[q28] != 6 /\ y_ExplicitVarSizeWithDummy[q29] != 6 -> + x_ExplicitVarSizeWithDummy[q28] + 2 = y_ExplicitVarSizeWithDummy[q29] + | q28 : int(1..4), q29 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 6 + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q2] = 6 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 6 | q2 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 6) | q3 : int(1..4)]), + and([y_ExplicitVarSizeWithDummy[q5] < y_ExplicitVarSizeWithDummy[q5 + 1] \/ y_ExplicitVarSizeWithDummy[q5] = 6 + | q5 : int(1..3)]), + and([y_ExplicitVarSizeWithDummy[q6] = 6 -> y_ExplicitVarSizeWithDummy[q6 + 1] = 6 | q6 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q7] != 6) | q7 : int(1..4)]), + 1 <= sum([toInt(x_Occurrence[q9]) | q9 : int(2..5)]), + and([x_Occurrence[q23] -> + or([x_ExplicitVarSizeWithDummy[q25] != 6 /\ x_ExplicitVarSizeWithDummy[q25] = q23 | q25 : int(1..4)]) + | q23 : int(2..5)]), + and([x_ExplicitVarSizeWithDummy[q27] != 6 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q27]] | q27 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q10 + 1] -> + y_ExplicitVarSizeWithFlags_Values[q10] < y_ExplicitVarSizeWithFlags_Values[q10 + 1] + | q10 : int(1..3)]), + and([y_ExplicitVarSizeWithFlags_Flags[q11] = false -> y_ExplicitVarSizeWithFlags_Values[q11] = 2 + | q11 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q12 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q12] | q12 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q13]) | q13 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q16] -> + or([y_ExplicitVarSizeWithDummy[q18] != 6 /\ + y_ExplicitVarSizeWithDummy[q18] = y_ExplicitVarSizeWithFlags_Values[q16] + | q18 : int(1..4)]) + | q16 : int(1..4)]), + and([y_ExplicitVarSizeWithDummy[q20] != 6 -> + or([y_ExplicitVarSizeWithFlags_Flags[q22] /\ + y_ExplicitVarSizeWithFlags_Values[q22] = y_ExplicitVarSizeWithDummy[q20] + | q22 : int(1..4)]) + | q20 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_2_2_2_1-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_2_2_2_1-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_2_2_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_2_2_2_1-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_2_2_2_1-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_2_2_1-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_2_2_2_1.eprime b/tests/exhaustive/basic/set09/expected/model_2_2_2_1.eprime new file mode 100644 index 0000000000..ccc426d080 --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_2_2_1.eprime @@ -0,0 +1,24 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +find y_Occurrence: matrix indexed by [int(2..5)] of bool +branching on [x_ExplicitVarSizeWithDummy, y_Occurrence, y_ExplicitVarSizeWithDummy] +such that + and([x_ExplicitVarSizeWithDummy[q15] != 6 /\ y_ExplicitVarSizeWithDummy[q16] != 6 -> + x_ExplicitVarSizeWithDummy[q15] + 2 = y_ExplicitVarSizeWithDummy[q16] + | q15 : int(1..4), q16 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 6 + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q2] = 6 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 6 | q2 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 6) | q3 : int(1..4)]), + and([y_ExplicitVarSizeWithDummy[q5] < y_ExplicitVarSizeWithDummy[q5 + 1] \/ y_ExplicitVarSizeWithDummy[q5] = 6 + | q5 : int(1..3)]), + and([y_ExplicitVarSizeWithDummy[q6] = 6 -> y_ExplicitVarSizeWithDummy[q6 + 1] = 6 | q6 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q7] != 6) | q7 : int(1..4)]), + 1 <= sum([toInt(y_Occurrence[q9]) | q9 : int(2..5)]), + and([y_Occurrence[q10] -> + or([y_ExplicitVarSizeWithDummy[q12] != 6 /\ y_ExplicitVarSizeWithDummy[q12] = q10 | q12 : int(1..4)]) + | q10 : int(2..5)]), + and([y_ExplicitVarSizeWithDummy[q14] != 6 -> y_Occurrence[y_ExplicitVarSizeWithDummy[q14]] | q14 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_2_2_2_2-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_2_2_2_2-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_2_2_2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_2_2_2_2-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_2_2_2_2-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_2_2_2-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_2_2_2_2.eprime b/tests/exhaustive/basic/set09/expected/model_2_2_2_2.eprime new file mode 100644 index 0000000000..bce1fcad7f --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_2_2_2.eprime @@ -0,0 +1,18 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +branching on [x_ExplicitVarSizeWithDummy, y_ExplicitVarSizeWithDummy] +such that + and([x_ExplicitVarSizeWithDummy[q9] != 6 /\ y_ExplicitVarSizeWithDummy[q10] != 6 -> + x_ExplicitVarSizeWithDummy[q9] + 2 = y_ExplicitVarSizeWithDummy[q10] + | q9 : int(1..4), q10 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 6 + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q2] = 6 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 6 | q2 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 6) | q3 : int(1..4)]), + and([y_ExplicitVarSizeWithDummy[q5] < y_ExplicitVarSizeWithDummy[q5 + 1] \/ y_ExplicitVarSizeWithDummy[q5] = 6 + | q5 : int(1..3)]), + and([y_ExplicitVarSizeWithDummy[q6] = 6 -> y_ExplicitVarSizeWithDummy[q6 + 1] = 6 | q6 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q7] != 6) | q7 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_2_2_2_3-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_2_2_2_3-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_2_2_3-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_2_2_2_3-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_2_2_2_3-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_2_2_3-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_2_2_2_3.eprime b/tests/exhaustive/basic/set09/expected/model_2_2_2_3.eprime new file mode 100644 index 0000000000..f3540e7f47 --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_2_2_3.eprime @@ -0,0 +1,37 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +find y_ExplicitVarSizeWithMarker_Marker: int(0..4) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +branching on + [x_ExplicitVarSizeWithDummy, y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values, + y_ExplicitVarSizeWithDummy] +such that + and([x_ExplicitVarSizeWithDummy[q20] != 6 /\ y_ExplicitVarSizeWithDummy[q21] != 6 -> + x_ExplicitVarSizeWithDummy[q20] + 2 = y_ExplicitVarSizeWithDummy[q21] + | q20 : int(1..4), q21 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 6 + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q2] = 6 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 6 | q2 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 6) | q3 : int(1..4)]), + and([y_ExplicitVarSizeWithDummy[q5] < y_ExplicitVarSizeWithDummy[q5 + 1] \/ y_ExplicitVarSizeWithDummy[q5] = 6 + | q5 : int(1..3)]), + and([y_ExplicitVarSizeWithDummy[q6] = 6 -> y_ExplicitVarSizeWithDummy[q6 + 1] = 6 | q6 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q7] != 6) | q7 : int(1..4)]), + and([q9 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> + y_ExplicitVarSizeWithMarker_Values[q9] < y_ExplicitVarSizeWithMarker_Values[q9 + 1] + | q9 : int(1..3)]), + and([q10 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q10] = 2 | q10 : int(1..4)]), + 1 <= y_ExplicitVarSizeWithMarker_Marker, + and([q13 <= y_ExplicitVarSizeWithMarker_Marker -> + or([y_ExplicitVarSizeWithDummy[q15] != 6 /\ + y_ExplicitVarSizeWithDummy[q15] = y_ExplicitVarSizeWithMarker_Values[q13] + | q15 : int(1..4)]) + | q13 : int(1..4)]), + and([y_ExplicitVarSizeWithDummy[q17] != 6 -> + or([q19 <= y_ExplicitVarSizeWithMarker_Marker /\ + y_ExplicitVarSizeWithMarker_Values[q19] = y_ExplicitVarSizeWithDummy[q17] + | q19 : int(1..4)]) + | q17 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_2_2_2_4-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_2_2_2_4-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_2_2_4-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_2_2_2_4-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_2_2_2_4-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_2_2_4-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_2_2_2_4.eprime b/tests/exhaustive/basic/set09/expected/model_2_2_2_4.eprime new file mode 100644 index 0000000000..88248fc78d --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_2_2_4.eprime @@ -0,0 +1,39 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +branching on + [x_ExplicitVarSizeWithDummy, y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values, + y_ExplicitVarSizeWithDummy] +such that + and([x_ExplicitVarSizeWithDummy[q22] != 6 /\ y_ExplicitVarSizeWithDummy[q23] != 6 -> + x_ExplicitVarSizeWithDummy[q22] + 2 = y_ExplicitVarSizeWithDummy[q23] + | q22 : int(1..4), q23 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 6 + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q2] = 6 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 6 | q2 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 6) | q3 : int(1..4)]), + and([y_ExplicitVarSizeWithDummy[q5] < y_ExplicitVarSizeWithDummy[q5 + 1] \/ y_ExplicitVarSizeWithDummy[q5] = 6 + | q5 : int(1..3)]), + and([y_ExplicitVarSizeWithDummy[q6] = 6 -> y_ExplicitVarSizeWithDummy[q6 + 1] = 6 | q6 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q7] != 6) | q7 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q9 + 1] -> + y_ExplicitVarSizeWithFlags_Values[q9] < y_ExplicitVarSizeWithFlags_Values[q9 + 1] + | q9 : int(1..3)]), + and([y_ExplicitVarSizeWithFlags_Flags[q10] = false -> y_ExplicitVarSizeWithFlags_Values[q10] = 2 + | q10 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q11 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q11] | q11 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q12]) | q12 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q15] -> + or([y_ExplicitVarSizeWithDummy[q17] != 6 /\ + y_ExplicitVarSizeWithDummy[q17] = y_ExplicitVarSizeWithFlags_Values[q15] + | q17 : int(1..4)]) + | q15 : int(1..4)]), + and([y_ExplicitVarSizeWithDummy[q19] != 6 -> + or([y_ExplicitVarSizeWithFlags_Flags[q21] /\ + y_ExplicitVarSizeWithFlags_Values[q21] = y_ExplicitVarSizeWithDummy[q19] + | q21 : int(1..4)]) + | q19 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_2_2_3_1-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_2_2_3_1-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_2_3_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_2_2_3_1-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_2_2_3_1-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_2_3_1-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_2_2_3_1.eprime b/tests/exhaustive/basic/set09/expected/model_2_2_3_1.eprime new file mode 100644 index 0000000000..bf64c42988 --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_2_3_1.eprime @@ -0,0 +1,43 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +find y_Occurrence: matrix indexed by [int(2..5)] of bool +branching on + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy, y_Occurrence, + y_ExplicitVarSizeWithDummy] +such that + and([x_ExplicitVarSizeWithDummy[q26] != 6 /\ y_ExplicitVarSizeWithDummy[q27] != 6 -> + x_ExplicitVarSizeWithDummy[q26] + 2 = y_ExplicitVarSizeWithDummy[q27] + | q26 : int(1..4), q27 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 6 + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q2] = 6 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 6 | q2 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 6) | q3 : int(1..4)]), + and([y_ExplicitVarSizeWithDummy[q5] < y_ExplicitVarSizeWithDummy[q5 + 1] \/ y_ExplicitVarSizeWithDummy[q5] = 6 + | q5 : int(1..3)]), + and([y_ExplicitVarSizeWithDummy[q6] = 6 -> y_ExplicitVarSizeWithDummy[q6 + 1] = 6 | q6 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q7] != 6) | q7 : int(1..4)]), + and([q9 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q9] < x_ExplicitVarSizeWithMarker_Values[q9 + 1] + | q9 : int(1..3)]), + and([q10 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q10] = 2 | q10 : int(1..4)]), + 1 <= x_ExplicitVarSizeWithMarker_Marker, + and([q13 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithDummy[q15] != 6 /\ + x_ExplicitVarSizeWithDummy[q15] = x_ExplicitVarSizeWithMarker_Values[q13] + | q15 : int(1..4)]) + | q13 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q17] != 6 -> + or([q19 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q19] = x_ExplicitVarSizeWithDummy[q17] + | q19 : int(1..4)]) + | q17 : int(1..4)]), + 1 <= sum([toInt(y_Occurrence[q20]) | q20 : int(2..5)]), + and([y_Occurrence[q21] -> + or([y_ExplicitVarSizeWithDummy[q23] != 6 /\ y_ExplicitVarSizeWithDummy[q23] = q21 | q23 : int(1..4)]) + | q21 : int(2..5)]), + and([y_ExplicitVarSizeWithDummy[q25] != 6 -> y_Occurrence[y_ExplicitVarSizeWithDummy[q25]] | q25 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_2_2_3_2-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_2_2_3_2-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_2_3_2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_2_2_3_2-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_2_2_3_2-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_2_3_2-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_2_2_3_2.eprime b/tests/exhaustive/basic/set09/expected/model_2_2_3_2.eprime new file mode 100644 index 0000000000..e948b9d5dd --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_2_3_2.eprime @@ -0,0 +1,37 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +branching on + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy, + y_ExplicitVarSizeWithDummy] +such that + and([x_ExplicitVarSizeWithDummy[q20] != 6 /\ y_ExplicitVarSizeWithDummy[q21] != 6 -> + x_ExplicitVarSizeWithDummy[q20] + 2 = y_ExplicitVarSizeWithDummy[q21] + | q20 : int(1..4), q21 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 6 + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q2] = 6 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 6 | q2 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 6) | q3 : int(1..4)]), + and([y_ExplicitVarSizeWithDummy[q5] < y_ExplicitVarSizeWithDummy[q5 + 1] \/ y_ExplicitVarSizeWithDummy[q5] = 6 + | q5 : int(1..3)]), + and([y_ExplicitVarSizeWithDummy[q6] = 6 -> y_ExplicitVarSizeWithDummy[q6 + 1] = 6 | q6 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q7] != 6) | q7 : int(1..4)]), + and([q9 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q9] < x_ExplicitVarSizeWithMarker_Values[q9 + 1] + | q9 : int(1..3)]), + and([q10 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q10] = 2 | q10 : int(1..4)]), + 1 <= x_ExplicitVarSizeWithMarker_Marker, + and([q13 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithDummy[q15] != 6 /\ + x_ExplicitVarSizeWithDummy[q15] = x_ExplicitVarSizeWithMarker_Values[q13] + | q15 : int(1..4)]) + | q13 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q17] != 6 -> + or([q19 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q19] = x_ExplicitVarSizeWithDummy[q17] + | q19 : int(1..4)]) + | q17 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_2_2_3_3-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_2_2_3_3-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_2_3_3-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_2_2_3_3-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_2_2_3_3-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_2_3_3-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_2_2_3_3.eprime b/tests/exhaustive/basic/set09/expected/model_2_2_3_3.eprime new file mode 100644 index 0000000000..96a79f1b62 --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_2_3_3.eprime @@ -0,0 +1,54 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +find y_ExplicitVarSizeWithMarker_Marker: int(0..4) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +branching on + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy, + y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithDummy] +such that + and([x_ExplicitVarSizeWithDummy[q31] != 6 /\ y_ExplicitVarSizeWithDummy[q32] != 6 -> + x_ExplicitVarSizeWithDummy[q31] + 2 = y_ExplicitVarSizeWithDummy[q32] + | q31 : int(1..4), q32 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 6 + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q2] = 6 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 6 | q2 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 6) | q3 : int(1..4)]), + and([y_ExplicitVarSizeWithDummy[q5] < y_ExplicitVarSizeWithDummy[q5 + 1] \/ y_ExplicitVarSizeWithDummy[q5] = 6 + | q5 : int(1..3)]), + and([y_ExplicitVarSizeWithDummy[q6] = 6 -> y_ExplicitVarSizeWithDummy[q6 + 1] = 6 | q6 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q7] != 6) | q7 : int(1..4)]), + and([q9 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q9] < x_ExplicitVarSizeWithMarker_Values[q9 + 1] + | q9 : int(1..3)]), + and([q10 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q10] = 2 | q10 : int(1..4)]), + 1 <= x_ExplicitVarSizeWithMarker_Marker, + and([q13 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithDummy[q15] != 6 /\ + x_ExplicitVarSizeWithDummy[q15] = x_ExplicitVarSizeWithMarker_Values[q13] + | q15 : int(1..4)]) + | q13 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q17] != 6 -> + or([q19 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q19] = x_ExplicitVarSizeWithDummy[q17] + | q19 : int(1..4)]) + | q17 : int(1..4)]), + and([q20 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> + y_ExplicitVarSizeWithMarker_Values[q20] < y_ExplicitVarSizeWithMarker_Values[q20 + 1] + | q20 : int(1..3)]), + and([q21 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q21] = 2 | q21 : int(1..4)]), + 1 <= y_ExplicitVarSizeWithMarker_Marker, + and([q24 <= y_ExplicitVarSizeWithMarker_Marker -> + or([y_ExplicitVarSizeWithDummy[q26] != 6 /\ + y_ExplicitVarSizeWithDummy[q26] = y_ExplicitVarSizeWithMarker_Values[q24] + | q26 : int(1..4)]) + | q24 : int(1..4)]), + and([y_ExplicitVarSizeWithDummy[q28] != 6 -> + or([q30 <= y_ExplicitVarSizeWithMarker_Marker /\ + y_ExplicitVarSizeWithMarker_Values[q30] = y_ExplicitVarSizeWithDummy[q28] + | q30 : int(1..4)]) + | q28 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_2_2_3_4-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_2_2_3_4-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_2_3_4-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_2_2_3_4-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_2_2_3_4-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_2_3_4-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_2_2_3_4.eprime b/tests/exhaustive/basic/set09/expected/model_2_2_3_4.eprime new file mode 100644 index 0000000000..466ab4e3bf --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_2_3_4.eprime @@ -0,0 +1,56 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +branching on + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy, + y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithDummy] +such that + and([x_ExplicitVarSizeWithDummy[q33] != 6 /\ y_ExplicitVarSizeWithDummy[q34] != 6 -> + x_ExplicitVarSizeWithDummy[q33] + 2 = y_ExplicitVarSizeWithDummy[q34] + | q33 : int(1..4), q34 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 6 + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q2] = 6 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 6 | q2 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 6) | q3 : int(1..4)]), + and([y_ExplicitVarSizeWithDummy[q5] < y_ExplicitVarSizeWithDummy[q5 + 1] \/ y_ExplicitVarSizeWithDummy[q5] = 6 + | q5 : int(1..3)]), + and([y_ExplicitVarSizeWithDummy[q6] = 6 -> y_ExplicitVarSizeWithDummy[q6 + 1] = 6 | q6 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q7] != 6) | q7 : int(1..4)]), + and([q9 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q9] < x_ExplicitVarSizeWithMarker_Values[q9 + 1] + | q9 : int(1..3)]), + and([q10 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q10] = 2 | q10 : int(1..4)]), + 1 <= x_ExplicitVarSizeWithMarker_Marker, + and([q13 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithDummy[q15] != 6 /\ + x_ExplicitVarSizeWithDummy[q15] = x_ExplicitVarSizeWithMarker_Values[q13] + | q15 : int(1..4)]) + | q13 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q17] != 6 -> + or([q19 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q19] = x_ExplicitVarSizeWithDummy[q17] + | q19 : int(1..4)]) + | q17 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q20 + 1] -> + y_ExplicitVarSizeWithFlags_Values[q20] < y_ExplicitVarSizeWithFlags_Values[q20 + 1] + | q20 : int(1..3)]), + and([y_ExplicitVarSizeWithFlags_Flags[q21] = false -> y_ExplicitVarSizeWithFlags_Values[q21] = 2 + | q21 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q22 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q22] | q22 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q23]) | q23 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q26] -> + or([y_ExplicitVarSizeWithDummy[q28] != 6 /\ + y_ExplicitVarSizeWithDummy[q28] = y_ExplicitVarSizeWithFlags_Values[q26] + | q28 : int(1..4)]) + | q26 : int(1..4)]), + and([y_ExplicitVarSizeWithDummy[q30] != 6 -> + or([y_ExplicitVarSizeWithFlags_Flags[q32] /\ + y_ExplicitVarSizeWithFlags_Values[q32] = y_ExplicitVarSizeWithDummy[q30] + | q32 : int(1..4)]) + | q30 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_2_2_4_1-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_2_2_4_1-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_2_4_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_2_2_4_1-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_2_2_4_1-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_2_4_1-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_2_2_4_1.eprime b/tests/exhaustive/basic/set09/expected/model_2_2_4_1.eprime new file mode 100644 index 0000000000..a1084e9824 --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_2_4_1.eprime @@ -0,0 +1,45 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +find y_Occurrence: matrix indexed by [int(2..5)] of bool +branching on + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy, y_Occurrence, + y_ExplicitVarSizeWithDummy] +such that + and([x_ExplicitVarSizeWithDummy[q28] != 6 /\ y_ExplicitVarSizeWithDummy[q29] != 6 -> + x_ExplicitVarSizeWithDummy[q28] + 2 = y_ExplicitVarSizeWithDummy[q29] + | q28 : int(1..4), q29 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 6 + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q2] = 6 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 6 | q2 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 6) | q3 : int(1..4)]), + and([y_ExplicitVarSizeWithDummy[q5] < y_ExplicitVarSizeWithDummy[q5 + 1] \/ y_ExplicitVarSizeWithDummy[q5] = 6 + | q5 : int(1..3)]), + and([y_ExplicitVarSizeWithDummy[q6] = 6 -> y_ExplicitVarSizeWithDummy[q6 + 1] = 6 | q6 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q7] != 6) | q7 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q9 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q9] < x_ExplicitVarSizeWithFlags_Values[q9 + 1] + | q9 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q10] = false -> x_ExplicitVarSizeWithFlags_Values[q10] = 2 + | q10 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q11 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q11] | q11 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q12]) | q12 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q15] -> + or([x_ExplicitVarSizeWithDummy[q17] != 6 /\ + x_ExplicitVarSizeWithDummy[q17] = x_ExplicitVarSizeWithFlags_Values[q15] + | q17 : int(1..4)]) + | q15 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q19] != 6 -> + or([x_ExplicitVarSizeWithFlags_Flags[q21] /\ + x_ExplicitVarSizeWithFlags_Values[q21] = x_ExplicitVarSizeWithDummy[q19] + | q21 : int(1..4)]) + | q19 : int(1..4)]), + 1 <= sum([toInt(y_Occurrence[q22]) | q22 : int(2..5)]), + and([y_Occurrence[q23] -> + or([y_ExplicitVarSizeWithDummy[q25] != 6 /\ y_ExplicitVarSizeWithDummy[q25] = q23 | q25 : int(1..4)]) + | q23 : int(2..5)]), + and([y_ExplicitVarSizeWithDummy[q27] != 6 -> y_Occurrence[y_ExplicitVarSizeWithDummy[q27]] | q27 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_2_2_4_2-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_2_2_4_2-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_2_4_2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_2_2_4_2-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_2_2_4_2-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_2_4_2-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_2_2_4_2.eprime b/tests/exhaustive/basic/set09/expected/model_2_2_4_2.eprime new file mode 100644 index 0000000000..43b2f0a07f --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_2_4_2.eprime @@ -0,0 +1,39 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +branching on + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy, + y_ExplicitVarSizeWithDummy] +such that + and([x_ExplicitVarSizeWithDummy[q22] != 6 /\ y_ExplicitVarSizeWithDummy[q23] != 6 -> + x_ExplicitVarSizeWithDummy[q22] + 2 = y_ExplicitVarSizeWithDummy[q23] + | q22 : int(1..4), q23 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 6 + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q2] = 6 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 6 | q2 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 6) | q3 : int(1..4)]), + and([y_ExplicitVarSizeWithDummy[q5] < y_ExplicitVarSizeWithDummy[q5 + 1] \/ y_ExplicitVarSizeWithDummy[q5] = 6 + | q5 : int(1..3)]), + and([y_ExplicitVarSizeWithDummy[q6] = 6 -> y_ExplicitVarSizeWithDummy[q6 + 1] = 6 | q6 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q7] != 6) | q7 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q9 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q9] < x_ExplicitVarSizeWithFlags_Values[q9 + 1] + | q9 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q10] = false -> x_ExplicitVarSizeWithFlags_Values[q10] = 2 + | q10 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q11 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q11] | q11 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q12]) | q12 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q15] -> + or([x_ExplicitVarSizeWithDummy[q17] != 6 /\ + x_ExplicitVarSizeWithDummy[q17] = x_ExplicitVarSizeWithFlags_Values[q15] + | q17 : int(1..4)]) + | q15 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q19] != 6 -> + or([x_ExplicitVarSizeWithFlags_Flags[q21] /\ + x_ExplicitVarSizeWithFlags_Values[q21] = x_ExplicitVarSizeWithDummy[q19] + | q21 : int(1..4)]) + | q19 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_2_2_4_3-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_2_2_4_3-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_2_4_3-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_2_2_4_3-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_2_2_4_3-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_2_4_3-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_2_2_4_3.eprime b/tests/exhaustive/basic/set09/expected/model_2_2_4_3.eprime new file mode 100644 index 0000000000..d589c54438 --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_2_4_3.eprime @@ -0,0 +1,56 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +find y_ExplicitVarSizeWithMarker_Marker: int(0..4) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +branching on + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy, + y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithDummy] +such that + and([x_ExplicitVarSizeWithDummy[q33] != 6 /\ y_ExplicitVarSizeWithDummy[q34] != 6 -> + x_ExplicitVarSizeWithDummy[q33] + 2 = y_ExplicitVarSizeWithDummy[q34] + | q33 : int(1..4), q34 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 6 + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q2] = 6 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 6 | q2 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 6) | q3 : int(1..4)]), + and([y_ExplicitVarSizeWithDummy[q5] < y_ExplicitVarSizeWithDummy[q5 + 1] \/ y_ExplicitVarSizeWithDummy[q5] = 6 + | q5 : int(1..3)]), + and([y_ExplicitVarSizeWithDummy[q6] = 6 -> y_ExplicitVarSizeWithDummy[q6 + 1] = 6 | q6 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q7] != 6) | q7 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q9 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q9] < x_ExplicitVarSizeWithFlags_Values[q9 + 1] + | q9 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q10] = false -> x_ExplicitVarSizeWithFlags_Values[q10] = 2 + | q10 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q11 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q11] | q11 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q12]) | q12 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q15] -> + or([x_ExplicitVarSizeWithDummy[q17] != 6 /\ + x_ExplicitVarSizeWithDummy[q17] = x_ExplicitVarSizeWithFlags_Values[q15] + | q17 : int(1..4)]) + | q15 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q19] != 6 -> + or([x_ExplicitVarSizeWithFlags_Flags[q21] /\ + x_ExplicitVarSizeWithFlags_Values[q21] = x_ExplicitVarSizeWithDummy[q19] + | q21 : int(1..4)]) + | q19 : int(1..4)]), + and([q22 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> + y_ExplicitVarSizeWithMarker_Values[q22] < y_ExplicitVarSizeWithMarker_Values[q22 + 1] + | q22 : int(1..3)]), + and([q23 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q23] = 2 | q23 : int(1..4)]), + 1 <= y_ExplicitVarSizeWithMarker_Marker, + and([q26 <= y_ExplicitVarSizeWithMarker_Marker -> + or([y_ExplicitVarSizeWithDummy[q28] != 6 /\ + y_ExplicitVarSizeWithDummy[q28] = y_ExplicitVarSizeWithMarker_Values[q26] + | q28 : int(1..4)]) + | q26 : int(1..4)]), + and([y_ExplicitVarSizeWithDummy[q30] != 6 -> + or([q32 <= y_ExplicitVarSizeWithMarker_Marker /\ + y_ExplicitVarSizeWithMarker_Values[q32] = y_ExplicitVarSizeWithDummy[q30] + | q32 : int(1..4)]) + | q30 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_2_2_4_4-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_2_2_4_4-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_2_4_4-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_2_2_4_4-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_2_2_4_4-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_2_4_4-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_2_2_4_4.eprime b/tests/exhaustive/basic/set09/expected/model_2_2_4_4.eprime new file mode 100644 index 0000000000..eccd37c27c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_2_4_4.eprime @@ -0,0 +1,58 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +branching on + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy, + y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithDummy] +such that + and([x_ExplicitVarSizeWithDummy[q35] != 6 /\ y_ExplicitVarSizeWithDummy[q36] != 6 -> + x_ExplicitVarSizeWithDummy[q35] + 2 = y_ExplicitVarSizeWithDummy[q36] + | q35 : int(1..4), q36 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 6 + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q2] = 6 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 6 | q2 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 6) | q3 : int(1..4)]), + and([y_ExplicitVarSizeWithDummy[q5] < y_ExplicitVarSizeWithDummy[q5 + 1] \/ y_ExplicitVarSizeWithDummy[q5] = 6 + | q5 : int(1..3)]), + and([y_ExplicitVarSizeWithDummy[q6] = 6 -> y_ExplicitVarSizeWithDummy[q6 + 1] = 6 | q6 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q7] != 6) | q7 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q9 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q9] < x_ExplicitVarSizeWithFlags_Values[q9 + 1] + | q9 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q10] = false -> x_ExplicitVarSizeWithFlags_Values[q10] = 2 + | q10 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q11 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q11] | q11 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q12]) | q12 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q15] -> + or([x_ExplicitVarSizeWithDummy[q17] != 6 /\ + x_ExplicitVarSizeWithDummy[q17] = x_ExplicitVarSizeWithFlags_Values[q15] + | q17 : int(1..4)]) + | q15 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q19] != 6 -> + or([x_ExplicitVarSizeWithFlags_Flags[q21] /\ + x_ExplicitVarSizeWithFlags_Values[q21] = x_ExplicitVarSizeWithDummy[q19] + | q21 : int(1..4)]) + | q19 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q22 + 1] -> + y_ExplicitVarSizeWithFlags_Values[q22] < y_ExplicitVarSizeWithFlags_Values[q22 + 1] + | q22 : int(1..3)]), + and([y_ExplicitVarSizeWithFlags_Flags[q23] = false -> y_ExplicitVarSizeWithFlags_Values[q23] = 2 + | q23 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q24 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q24] | q24 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q25]) | q25 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q28] -> + or([y_ExplicitVarSizeWithDummy[q30] != 6 /\ + y_ExplicitVarSizeWithDummy[q30] = y_ExplicitVarSizeWithFlags_Values[q28] + | q30 : int(1..4)]) + | q28 : int(1..4)]), + and([y_ExplicitVarSizeWithDummy[q32] != 6 -> + or([y_ExplicitVarSizeWithFlags_Flags[q34] /\ + y_ExplicitVarSizeWithFlags_Values[q34] = y_ExplicitVarSizeWithDummy[q32] + | q34 : int(1..4)]) + | q32 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_2_3_1_1-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_2_3_1_1-solution000001.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_3_1_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_2_3_1_1-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_2_3_1_1-solution000002.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_3_1_1-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_2_3_1_1.eprime b/tests/exhaustive/basic/set09/expected/model_2_3_1_1.eprime new file mode 100644 index 0000000000..37bb76ce7c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_3_1_1.eprime @@ -0,0 +1,36 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +find x_Occurrence: matrix indexed by [int(2..5)] of bool +find y_ExplicitVarSizeWithMarker_Marker: int(0..4) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_Occurrence: matrix indexed by [int(2..5)] of bool +branching on + [x_Occurrence, x_ExplicitVarSizeWithDummy, y_Occurrence, y_ExplicitVarSizeWithMarker_Marker, + y_ExplicitVarSizeWithMarker_Values] +such that + and([x_ExplicitVarSizeWithDummy[q15] != 6 /\ q16 <= y_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithDummy[q15] + 2 = y_ExplicitVarSizeWithMarker_Values[q16] + | q15 : int(1..4), q16 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 6 + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q2] = 6 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 6 | q2 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 6) | q3 : int(1..4)]), + and([q5 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> + y_ExplicitVarSizeWithMarker_Values[q5] < y_ExplicitVarSizeWithMarker_Values[q5 + 1] + | q5 : int(1..3)]), + and([q6 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q6] = 2 | q6 : int(1..4)]), + 1 <= y_ExplicitVarSizeWithMarker_Marker, + 1 <= sum([toInt(x_Occurrence[q8]) | q8 : int(2..5)]), + and([x_Occurrence[q17] -> + or([x_ExplicitVarSizeWithDummy[q19] != 6 /\ x_ExplicitVarSizeWithDummy[q19] = q17 | q19 : int(1..4)]) + | q17 : int(2..5)]), + and([x_ExplicitVarSizeWithDummy[q21] != 6 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q21]] | q21 : int(1..4)]), + 1 <= sum([toInt(y_Occurrence[q9]) | q9 : int(2..5)]), + and([y_Occurrence[q10] -> + or([q12 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[q12] = q10 + | q12 : int(1..4)]) + | q10 : int(2..5)]), + and([q14 <= y_ExplicitVarSizeWithMarker_Marker -> y_Occurrence[y_ExplicitVarSizeWithMarker_Values[q14]] + | q14 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_2_3_1_2-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_2_3_1_2-solution000001.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_3_1_2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_2_3_1_2-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_2_3_1_2-solution000002.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_3_1_2-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_2_3_1_2.eprime b/tests/exhaustive/basic/set09/expected/model_2_3_1_2.eprime new file mode 100644 index 0000000000..ef24047245 --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_3_1_2.eprime @@ -0,0 +1,43 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +find x_Occurrence: matrix indexed by [int(2..5)] of bool +find y_ExplicitVarSizeWithMarker_Marker: int(0..4) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +branching on + [x_Occurrence, x_ExplicitVarSizeWithDummy, y_ExplicitVarSizeWithDummy, y_ExplicitVarSizeWithMarker_Marker, + y_ExplicitVarSizeWithMarker_Values] +such that + and([x_ExplicitVarSizeWithDummy[q26] != 6 /\ q27 <= y_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithDummy[q26] + 2 = y_ExplicitVarSizeWithMarker_Values[q27] + | q26 : int(1..4), q27 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 6 + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q2] = 6 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 6 | q2 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 6) | q3 : int(1..4)]), + and([q5 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> + y_ExplicitVarSizeWithMarker_Values[q5] < y_ExplicitVarSizeWithMarker_Values[q5 + 1] + | q5 : int(1..3)]), + and([q6 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q6] = 2 | q6 : int(1..4)]), + 1 <= y_ExplicitVarSizeWithMarker_Marker, + 1 <= sum([toInt(x_Occurrence[q8]) | q8 : int(2..5)]), + and([x_Occurrence[q21] -> + or([x_ExplicitVarSizeWithDummy[q23] != 6 /\ x_ExplicitVarSizeWithDummy[q23] = q21 | q23 : int(1..4)]) + | q21 : int(2..5)]), + and([x_ExplicitVarSizeWithDummy[q25] != 6 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q25]] | q25 : int(1..4)]), + and([y_ExplicitVarSizeWithDummy[q9] < y_ExplicitVarSizeWithDummy[q9 + 1] \/ y_ExplicitVarSizeWithDummy[q9] = 6 + | q9 : int(1..3)]), + and([y_ExplicitVarSizeWithDummy[q10] = 6 -> y_ExplicitVarSizeWithDummy[q10 + 1] = 6 | q10 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q11] != 6) | q11 : int(1..4)]), + and([y_ExplicitVarSizeWithDummy[q14] != 6 -> + or([q16 <= y_ExplicitVarSizeWithMarker_Marker /\ + y_ExplicitVarSizeWithMarker_Values[q16] = y_ExplicitVarSizeWithDummy[q14] + | q16 : int(1..4)]) + | q14 : int(1..4)]), + and([q18 <= y_ExplicitVarSizeWithMarker_Marker -> + or([y_ExplicitVarSizeWithDummy[q20] != 6 /\ + y_ExplicitVarSizeWithDummy[q20] = y_ExplicitVarSizeWithMarker_Values[q18] + | q20 : int(1..4)]) + | q18 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_2_3_1_3-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_2_3_1_3-solution000001.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_3_1_3-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_2_3_1_3-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_2_3_1_3-solution000002.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_3_1_3-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_2_3_1_3.eprime b/tests/exhaustive/basic/set09/expected/model_2_3_1_3.eprime new file mode 100644 index 0000000000..e78df8b806 --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_3_1_3.eprime @@ -0,0 +1,27 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +find x_Occurrence: matrix indexed by [int(2..5)] of bool +find y_ExplicitVarSizeWithMarker_Marker: int(0..4) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +branching on + [x_Occurrence, x_ExplicitVarSizeWithDummy, y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values] +such that + and([x_ExplicitVarSizeWithDummy[q14] != 6 /\ q15 <= y_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithDummy[q14] + 2 = y_ExplicitVarSizeWithMarker_Values[q15] + | q14 : int(1..4), q15 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 6 + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q2] = 6 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 6 | q2 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 6) | q3 : int(1..4)]), + and([q5 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> + y_ExplicitVarSizeWithMarker_Values[q5] < y_ExplicitVarSizeWithMarker_Values[q5 + 1] + | q5 : int(1..3)]), + and([q6 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q6] = 2 | q6 : int(1..4)]), + 1 <= y_ExplicitVarSizeWithMarker_Marker, + 1 <= sum([toInt(x_Occurrence[q8]) | q8 : int(2..5)]), + and([x_Occurrence[q9] -> + or([x_ExplicitVarSizeWithDummy[q11] != 6 /\ x_ExplicitVarSizeWithDummy[q11] = q9 | q11 : int(1..4)]) + | q9 : int(2..5)]), + and([x_ExplicitVarSizeWithDummy[q13] != 6 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q13]] | q13 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_2_3_1_4-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_2_3_1_4-solution000001.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_3_1_4-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_2_3_1_4-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_2_3_1_4-solution000002.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_3_1_4-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_2_3_1_4.eprime b/tests/exhaustive/basic/set09/expected/model_2_3_1_4.eprime new file mode 100644 index 0000000000..1760ad207f --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_3_1_4.eprime @@ -0,0 +1,47 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +find x_Occurrence: matrix indexed by [int(2..5)] of bool +find y_ExplicitVarSizeWithMarker_Marker: int(0..4) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +branching on + [x_Occurrence, x_ExplicitVarSizeWithDummy, y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values, + y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values] +such that + and([x_ExplicitVarSizeWithDummy[q27] != 6 /\ q28 <= y_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithDummy[q27] + 2 = y_ExplicitVarSizeWithMarker_Values[q28] + | q27 : int(1..4), q28 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 6 + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q2] = 6 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 6 | q2 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 6) | q3 : int(1..4)]), + and([q5 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> + y_ExplicitVarSizeWithMarker_Values[q5] < y_ExplicitVarSizeWithMarker_Values[q5 + 1] + | q5 : int(1..3)]), + and([q6 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q6] = 2 | q6 : int(1..4)]), + 1 <= y_ExplicitVarSizeWithMarker_Marker, + 1 <= sum([toInt(x_Occurrence[q8]) | q8 : int(2..5)]), + and([x_Occurrence[q22] -> + or([x_ExplicitVarSizeWithDummy[q24] != 6 /\ x_ExplicitVarSizeWithDummy[q24] = q22 | q24 : int(1..4)]) + | q22 : int(2..5)]), + and([x_ExplicitVarSizeWithDummy[q26] != 6 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q26]] | q26 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q9 + 1] -> + y_ExplicitVarSizeWithFlags_Values[q9] < y_ExplicitVarSizeWithFlags_Values[q9 + 1] + | q9 : int(1..3)]), + and([y_ExplicitVarSizeWithFlags_Flags[q10] = false -> y_ExplicitVarSizeWithFlags_Values[q10] = 2 + | q10 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q11 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q11] | q11 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q12]) | q12 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q15] -> + or([q17 <= y_ExplicitVarSizeWithMarker_Marker /\ + y_ExplicitVarSizeWithMarker_Values[q17] = y_ExplicitVarSizeWithFlags_Values[q15] + | q17 : int(1..4)]) + | q15 : int(1..4)]), + and([q19 <= y_ExplicitVarSizeWithMarker_Marker -> + or([y_ExplicitVarSizeWithFlags_Flags[q21] /\ + y_ExplicitVarSizeWithFlags_Values[q21] = y_ExplicitVarSizeWithMarker_Values[q19] + | q21 : int(1..4)]) + | q19 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_2_3_2_1-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_2_3_2_1-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_3_2_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_2_3_2_1-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_2_3_2_1-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_3_2_1-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_2_3_2_1.eprime b/tests/exhaustive/basic/set09/expected/model_2_3_2_1.eprime new file mode 100644 index 0000000000..230e345c18 --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_3_2_1.eprime @@ -0,0 +1,29 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +find y_ExplicitVarSizeWithMarker_Marker: int(0..4) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_Occurrence: matrix indexed by [int(2..5)] of bool +branching on + [x_ExplicitVarSizeWithDummy, y_Occurrence, y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values] +such that + and([x_ExplicitVarSizeWithDummy[q14] != 6 /\ q15 <= y_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithDummy[q14] + 2 = y_ExplicitVarSizeWithMarker_Values[q15] + | q14 : int(1..4), q15 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 6 + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q2] = 6 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 6 | q2 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 6) | q3 : int(1..4)]), + and([q5 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> + y_ExplicitVarSizeWithMarker_Values[q5] < y_ExplicitVarSizeWithMarker_Values[q5 + 1] + | q5 : int(1..3)]), + and([q6 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q6] = 2 | q6 : int(1..4)]), + 1 <= y_ExplicitVarSizeWithMarker_Marker, + 1 <= sum([toInt(y_Occurrence[q8]) | q8 : int(2..5)]), + and([y_Occurrence[q9] -> + or([q11 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[q11] = q9 + | q11 : int(1..4)]) + | q9 : int(2..5)]), + and([q13 <= y_ExplicitVarSizeWithMarker_Marker -> y_Occurrence[y_ExplicitVarSizeWithMarker_Values[q13]] + | q13 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_2_3_2_2-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_2_3_2_2-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_3_2_2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_2_3_2_2-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_2_3_2_2-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_3_2_2-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_2_3_2_2.eprime b/tests/exhaustive/basic/set09/expected/model_2_3_2_2.eprime new file mode 100644 index 0000000000..f2e207b1c7 --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_3_2_2.eprime @@ -0,0 +1,37 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +find y_ExplicitVarSizeWithMarker_Marker: int(0..4) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +branching on + [x_ExplicitVarSizeWithDummy, y_ExplicitVarSizeWithDummy, y_ExplicitVarSizeWithMarker_Marker, + y_ExplicitVarSizeWithMarker_Values] +such that + and([x_ExplicitVarSizeWithDummy[q20] != 6 /\ q21 <= y_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithDummy[q20] + 2 = y_ExplicitVarSizeWithMarker_Values[q21] + | q20 : int(1..4), q21 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 6 + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q2] = 6 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 6 | q2 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 6) | q3 : int(1..4)]), + and([q5 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> + y_ExplicitVarSizeWithMarker_Values[q5] < y_ExplicitVarSizeWithMarker_Values[q5 + 1] + | q5 : int(1..3)]), + and([q6 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q6] = 2 | q6 : int(1..4)]), + 1 <= y_ExplicitVarSizeWithMarker_Marker, + and([y_ExplicitVarSizeWithDummy[q8] < y_ExplicitVarSizeWithDummy[q8 + 1] \/ y_ExplicitVarSizeWithDummy[q8] = 6 + | q8 : int(1..3)]), + and([y_ExplicitVarSizeWithDummy[q9] = 6 -> y_ExplicitVarSizeWithDummy[q9 + 1] = 6 | q9 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q10] != 6) | q10 : int(1..4)]), + and([y_ExplicitVarSizeWithDummy[q13] != 6 -> + or([q15 <= y_ExplicitVarSizeWithMarker_Marker /\ + y_ExplicitVarSizeWithMarker_Values[q15] = y_ExplicitVarSizeWithDummy[q13] + | q15 : int(1..4)]) + | q13 : int(1..4)]), + and([q17 <= y_ExplicitVarSizeWithMarker_Marker -> + or([y_ExplicitVarSizeWithDummy[q19] != 6 /\ + y_ExplicitVarSizeWithDummy[q19] = y_ExplicitVarSizeWithMarker_Values[q17] + | q19 : int(1..4)]) + | q17 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_2_3_2_3-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_2_3_2_3-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_3_2_3-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_2_3_2_3-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_2_3_2_3-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_3_2_3-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_2_3_2_3.eprime b/tests/exhaustive/basic/set09/expected/model_2_3_2_3.eprime new file mode 100644 index 0000000000..55128bbafc --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_3_2_3.eprime @@ -0,0 +1,20 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +find y_ExplicitVarSizeWithMarker_Marker: int(0..4) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +branching on [x_ExplicitVarSizeWithDummy, y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values] +such that + and([x_ExplicitVarSizeWithDummy[q8] != 6 /\ q9 <= y_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithDummy[q8] + 2 = y_ExplicitVarSizeWithMarker_Values[q9] + | q8 : int(1..4), q9 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 6 + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q2] = 6 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 6 | q2 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 6) | q3 : int(1..4)]), + and([q5 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> + y_ExplicitVarSizeWithMarker_Values[q5] < y_ExplicitVarSizeWithMarker_Values[q5 + 1] + | q5 : int(1..3)]), + and([q6 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q6] = 2 | q6 : int(1..4)]), + 1 <= y_ExplicitVarSizeWithMarker_Marker + diff --git a/tests/exhaustive/basic/set09/expected/model_2_3_2_4-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_2_3_2_4-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_3_2_4-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_2_3_2_4-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_2_3_2_4-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_3_2_4-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_2_3_2_4.eprime b/tests/exhaustive/basic/set09/expected/model_2_3_2_4.eprime new file mode 100644 index 0000000000..f69d957f61 --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_3_2_4.eprime @@ -0,0 +1,40 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +find y_ExplicitVarSizeWithMarker_Marker: int(0..4) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +branching on + [x_ExplicitVarSizeWithDummy, y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values, + y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values] +such that + and([x_ExplicitVarSizeWithDummy[q21] != 6 /\ q22 <= y_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithDummy[q21] + 2 = y_ExplicitVarSizeWithMarker_Values[q22] + | q21 : int(1..4), q22 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 6 + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q2] = 6 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 6 | q2 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 6) | q3 : int(1..4)]), + and([q5 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> + y_ExplicitVarSizeWithMarker_Values[q5] < y_ExplicitVarSizeWithMarker_Values[q5 + 1] + | q5 : int(1..3)]), + and([q6 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q6] = 2 | q6 : int(1..4)]), + 1 <= y_ExplicitVarSizeWithMarker_Marker, + and([y_ExplicitVarSizeWithFlags_Flags[q8 + 1] -> + y_ExplicitVarSizeWithFlags_Values[q8] < y_ExplicitVarSizeWithFlags_Values[q8 + 1] + | q8 : int(1..3)]), + and([y_ExplicitVarSizeWithFlags_Flags[q9] = false -> y_ExplicitVarSizeWithFlags_Values[q9] = 2 | q9 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q10 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q10] | q10 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q11]) | q11 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q14] -> + or([q16 <= y_ExplicitVarSizeWithMarker_Marker /\ + y_ExplicitVarSizeWithMarker_Values[q16] = y_ExplicitVarSizeWithFlags_Values[q14] + | q16 : int(1..4)]) + | q14 : int(1..4)]), + and([q18 <= y_ExplicitVarSizeWithMarker_Marker -> + or([y_ExplicitVarSizeWithFlags_Flags[q20] /\ + y_ExplicitVarSizeWithFlags_Values[q20] = y_ExplicitVarSizeWithMarker_Values[q18] + | q20 : int(1..4)]) + | q18 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_2_3_3_1-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_2_3_3_1-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_3_3_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_2_3_3_1-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_2_3_3_1-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_3_3_1-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_2_3_3_1.eprime b/tests/exhaustive/basic/set09/expected/model_2_3_3_1.eprime new file mode 100644 index 0000000000..a25e81deb3 --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_3_3_1.eprime @@ -0,0 +1,47 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_ExplicitVarSizeWithMarker_Marker: int(0..4) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_Occurrence: matrix indexed by [int(2..5)] of bool +branching on + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy, y_Occurrence, + y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values] +such that + and([x_ExplicitVarSizeWithDummy[q25] != 6 /\ q26 <= y_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithDummy[q25] + 2 = y_ExplicitVarSizeWithMarker_Values[q26] + | q25 : int(1..4), q26 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 6 + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q2] = 6 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 6 | q2 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 6) | q3 : int(1..4)]), + and([q5 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> + y_ExplicitVarSizeWithMarker_Values[q5] < y_ExplicitVarSizeWithMarker_Values[q5 + 1] + | q5 : int(1..3)]), + and([q6 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q6] = 2 | q6 : int(1..4)]), + 1 <= y_ExplicitVarSizeWithMarker_Marker, + and([q8 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q8] < x_ExplicitVarSizeWithMarker_Values[q8 + 1] + | q8 : int(1..3)]), + and([q9 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q9] = 2 | q9 : int(1..4)]), + 1 <= x_ExplicitVarSizeWithMarker_Marker, + and([q12 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithDummy[q14] != 6 /\ + x_ExplicitVarSizeWithDummy[q14] = x_ExplicitVarSizeWithMarker_Values[q12] + | q14 : int(1..4)]) + | q12 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q16] != 6 -> + or([q18 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q18] = x_ExplicitVarSizeWithDummy[q16] + | q18 : int(1..4)]) + | q16 : int(1..4)]), + 1 <= sum([toInt(y_Occurrence[q19]) | q19 : int(2..5)]), + and([y_Occurrence[q20] -> + or([q22 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[q22] = q20 + | q22 : int(1..4)]) + | q20 : int(2..5)]), + and([q24 <= y_ExplicitVarSizeWithMarker_Marker -> y_Occurrence[y_ExplicitVarSizeWithMarker_Values[q24]] + | q24 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_2_3_3_2-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_2_3_3_2-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_3_3_2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_2_3_3_2-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_2_3_3_2-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_3_3_2-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_2_3_3_2.eprime b/tests/exhaustive/basic/set09/expected/model_2_3_3_2.eprime new file mode 100644 index 0000000000..f4cb2aafb3 --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_3_3_2.eprime @@ -0,0 +1,54 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_ExplicitVarSizeWithMarker_Marker: int(0..4) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +branching on + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy, + y_ExplicitVarSizeWithDummy, y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values] +such that + and([x_ExplicitVarSizeWithDummy[q31] != 6 /\ q32 <= y_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithDummy[q31] + 2 = y_ExplicitVarSizeWithMarker_Values[q32] + | q31 : int(1..4), q32 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 6 + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q2] = 6 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 6 | q2 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 6) | q3 : int(1..4)]), + and([q5 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> + y_ExplicitVarSizeWithMarker_Values[q5] < y_ExplicitVarSizeWithMarker_Values[q5 + 1] + | q5 : int(1..3)]), + and([q6 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q6] = 2 | q6 : int(1..4)]), + 1 <= y_ExplicitVarSizeWithMarker_Marker, + and([q8 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q8] < x_ExplicitVarSizeWithMarker_Values[q8 + 1] + | q8 : int(1..3)]), + and([q9 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q9] = 2 | q9 : int(1..4)]), + 1 <= x_ExplicitVarSizeWithMarker_Marker, + and([q12 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithDummy[q14] != 6 /\ + x_ExplicitVarSizeWithDummy[q14] = x_ExplicitVarSizeWithMarker_Values[q12] + | q14 : int(1..4)]) + | q12 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q16] != 6 -> + or([q18 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q18] = x_ExplicitVarSizeWithDummy[q16] + | q18 : int(1..4)]) + | q16 : int(1..4)]), + and([y_ExplicitVarSizeWithDummy[q19] < y_ExplicitVarSizeWithDummy[q19 + 1] \/ y_ExplicitVarSizeWithDummy[q19] = 6 + | q19 : int(1..3)]), + and([y_ExplicitVarSizeWithDummy[q20] = 6 -> y_ExplicitVarSizeWithDummy[q20 + 1] = 6 | q20 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q21] != 6) | q21 : int(1..4)]), + and([y_ExplicitVarSizeWithDummy[q24] != 6 -> + or([q26 <= y_ExplicitVarSizeWithMarker_Marker /\ + y_ExplicitVarSizeWithMarker_Values[q26] = y_ExplicitVarSizeWithDummy[q24] + | q26 : int(1..4)]) + | q24 : int(1..4)]), + and([q28 <= y_ExplicitVarSizeWithMarker_Marker -> + or([y_ExplicitVarSizeWithDummy[q30] != 6 /\ + y_ExplicitVarSizeWithDummy[q30] = y_ExplicitVarSizeWithMarker_Values[q28] + | q30 : int(1..4)]) + | q28 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_2_3_3_3-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_2_3_3_3-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_3_3_3-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_2_3_3_3-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_2_3_3_3-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_3_3_3-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_2_3_3_3.eprime b/tests/exhaustive/basic/set09/expected/model_2_3_3_3.eprime new file mode 100644 index 0000000000..8cb929ecd5 --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_3_3_3.eprime @@ -0,0 +1,39 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_ExplicitVarSizeWithMarker_Marker: int(0..4) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +branching on + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy, + y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values] +such that + and([x_ExplicitVarSizeWithDummy[q19] != 6 /\ q20 <= y_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithDummy[q19] + 2 = y_ExplicitVarSizeWithMarker_Values[q20] + | q19 : int(1..4), q20 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 6 + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q2] = 6 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 6 | q2 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 6) | q3 : int(1..4)]), + and([q5 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> + y_ExplicitVarSizeWithMarker_Values[q5] < y_ExplicitVarSizeWithMarker_Values[q5 + 1] + | q5 : int(1..3)]), + and([q6 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q6] = 2 | q6 : int(1..4)]), + 1 <= y_ExplicitVarSizeWithMarker_Marker, + and([q8 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q8] < x_ExplicitVarSizeWithMarker_Values[q8 + 1] + | q8 : int(1..3)]), + and([q9 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q9] = 2 | q9 : int(1..4)]), + 1 <= x_ExplicitVarSizeWithMarker_Marker, + and([q12 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithDummy[q14] != 6 /\ + x_ExplicitVarSizeWithDummy[q14] = x_ExplicitVarSizeWithMarker_Values[q12] + | q14 : int(1..4)]) + | q12 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q16] != 6 -> + or([q18 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q18] = x_ExplicitVarSizeWithDummy[q16] + | q18 : int(1..4)]) + | q16 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_2_3_3_4-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_2_3_3_4-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_3_3_4-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_2_3_3_4-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_2_3_3_4-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_3_3_4-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_2_3_3_4.eprime b/tests/exhaustive/basic/set09/expected/model_2_3_3_4.eprime new file mode 100644 index 0000000000..28b7796968 --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_3_3_4.eprime @@ -0,0 +1,59 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_ExplicitVarSizeWithMarker_Marker: int(0..4) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +branching on + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy, + y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithMarker_Marker, + y_ExplicitVarSizeWithMarker_Values] +such that + and([x_ExplicitVarSizeWithDummy[q32] != 6 /\ q33 <= y_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithDummy[q32] + 2 = y_ExplicitVarSizeWithMarker_Values[q33] + | q32 : int(1..4), q33 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 6 + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q2] = 6 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 6 | q2 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 6) | q3 : int(1..4)]), + and([q5 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> + y_ExplicitVarSizeWithMarker_Values[q5] < y_ExplicitVarSizeWithMarker_Values[q5 + 1] + | q5 : int(1..3)]), + and([q6 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q6] = 2 | q6 : int(1..4)]), + 1 <= y_ExplicitVarSizeWithMarker_Marker, + and([q8 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q8] < x_ExplicitVarSizeWithMarker_Values[q8 + 1] + | q8 : int(1..3)]), + and([q9 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q9] = 2 | q9 : int(1..4)]), + 1 <= x_ExplicitVarSizeWithMarker_Marker, + and([q12 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithDummy[q14] != 6 /\ + x_ExplicitVarSizeWithDummy[q14] = x_ExplicitVarSizeWithMarker_Values[q12] + | q14 : int(1..4)]) + | q12 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q16] != 6 -> + or([q18 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q18] = x_ExplicitVarSizeWithDummy[q16] + | q18 : int(1..4)]) + | q16 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q19 + 1] -> + y_ExplicitVarSizeWithFlags_Values[q19] < y_ExplicitVarSizeWithFlags_Values[q19 + 1] + | q19 : int(1..3)]), + and([y_ExplicitVarSizeWithFlags_Flags[q20] = false -> y_ExplicitVarSizeWithFlags_Values[q20] = 2 + | q20 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q21 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q21] | q21 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q22]) | q22 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q25] -> + or([q27 <= y_ExplicitVarSizeWithMarker_Marker /\ + y_ExplicitVarSizeWithMarker_Values[q27] = y_ExplicitVarSizeWithFlags_Values[q25] + | q27 : int(1..4)]) + | q25 : int(1..4)]), + and([q29 <= y_ExplicitVarSizeWithMarker_Marker -> + or([y_ExplicitVarSizeWithFlags_Flags[q31] /\ + y_ExplicitVarSizeWithFlags_Values[q31] = y_ExplicitVarSizeWithMarker_Values[q29] + | q31 : int(1..4)]) + | q29 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_2_3_4_1-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_2_3_4_1-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_3_4_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_2_3_4_1-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_2_3_4_1-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_3_4_1-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_2_3_4_1.eprime b/tests/exhaustive/basic/set09/expected/model_2_3_4_1.eprime new file mode 100644 index 0000000000..65a1069752 --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_3_4_1.eprime @@ -0,0 +1,48 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_ExplicitVarSizeWithMarker_Marker: int(0..4) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_Occurrence: matrix indexed by [int(2..5)] of bool +branching on + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy, y_Occurrence, + y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values] +such that + and([x_ExplicitVarSizeWithDummy[q27] != 6 /\ q28 <= y_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithDummy[q27] + 2 = y_ExplicitVarSizeWithMarker_Values[q28] + | q27 : int(1..4), q28 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 6 + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q2] = 6 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 6 | q2 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 6) | q3 : int(1..4)]), + and([q5 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> + y_ExplicitVarSizeWithMarker_Values[q5] < y_ExplicitVarSizeWithMarker_Values[q5 + 1] + | q5 : int(1..3)]), + and([q6 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q6] = 2 | q6 : int(1..4)]), + 1 <= y_ExplicitVarSizeWithMarker_Marker, + and([x_ExplicitVarSizeWithFlags_Flags[q8 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q8] < x_ExplicitVarSizeWithFlags_Values[q8 + 1] + | q8 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q9] = false -> x_ExplicitVarSizeWithFlags_Values[q9] = 2 | q9 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q10 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q10] | q10 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q11]) | q11 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q14] -> + or([x_ExplicitVarSizeWithDummy[q16] != 6 /\ + x_ExplicitVarSizeWithDummy[q16] = x_ExplicitVarSizeWithFlags_Values[q14] + | q16 : int(1..4)]) + | q14 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q18] != 6 -> + or([x_ExplicitVarSizeWithFlags_Flags[q20] /\ + x_ExplicitVarSizeWithFlags_Values[q20] = x_ExplicitVarSizeWithDummy[q18] + | q20 : int(1..4)]) + | q18 : int(1..4)]), + 1 <= sum([toInt(y_Occurrence[q21]) | q21 : int(2..5)]), + and([y_Occurrence[q22] -> + or([q24 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[q24] = q22 + | q24 : int(1..4)]) + | q22 : int(2..5)]), + and([q26 <= y_ExplicitVarSizeWithMarker_Marker -> y_Occurrence[y_ExplicitVarSizeWithMarker_Values[q26]] + | q26 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_2_3_4_2-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_2_3_4_2-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_3_4_2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_2_3_4_2-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_2_3_4_2-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_3_4_2-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_2_3_4_2.eprime b/tests/exhaustive/basic/set09/expected/model_2_3_4_2.eprime new file mode 100644 index 0000000000..6026ed497b --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_3_4_2.eprime @@ -0,0 +1,55 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_ExplicitVarSizeWithMarker_Marker: int(0..4) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +branching on + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy, + y_ExplicitVarSizeWithDummy, y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values] +such that + and([x_ExplicitVarSizeWithDummy[q33] != 6 /\ q34 <= y_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithDummy[q33] + 2 = y_ExplicitVarSizeWithMarker_Values[q34] + | q33 : int(1..4), q34 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 6 + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q2] = 6 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 6 | q2 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 6) | q3 : int(1..4)]), + and([q5 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> + y_ExplicitVarSizeWithMarker_Values[q5] < y_ExplicitVarSizeWithMarker_Values[q5 + 1] + | q5 : int(1..3)]), + and([q6 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q6] = 2 | q6 : int(1..4)]), + 1 <= y_ExplicitVarSizeWithMarker_Marker, + and([x_ExplicitVarSizeWithFlags_Flags[q8 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q8] < x_ExplicitVarSizeWithFlags_Values[q8 + 1] + | q8 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q9] = false -> x_ExplicitVarSizeWithFlags_Values[q9] = 2 | q9 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q10 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q10] | q10 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q11]) | q11 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q14] -> + or([x_ExplicitVarSizeWithDummy[q16] != 6 /\ + x_ExplicitVarSizeWithDummy[q16] = x_ExplicitVarSizeWithFlags_Values[q14] + | q16 : int(1..4)]) + | q14 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q18] != 6 -> + or([x_ExplicitVarSizeWithFlags_Flags[q20] /\ + x_ExplicitVarSizeWithFlags_Values[q20] = x_ExplicitVarSizeWithDummy[q18] + | q20 : int(1..4)]) + | q18 : int(1..4)]), + and([y_ExplicitVarSizeWithDummy[q21] < y_ExplicitVarSizeWithDummy[q21 + 1] \/ y_ExplicitVarSizeWithDummy[q21] = 6 + | q21 : int(1..3)]), + and([y_ExplicitVarSizeWithDummy[q22] = 6 -> y_ExplicitVarSizeWithDummy[q22 + 1] = 6 | q22 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q23] != 6) | q23 : int(1..4)]), + and([y_ExplicitVarSizeWithDummy[q26] != 6 -> + or([q28 <= y_ExplicitVarSizeWithMarker_Marker /\ + y_ExplicitVarSizeWithMarker_Values[q28] = y_ExplicitVarSizeWithDummy[q26] + | q28 : int(1..4)]) + | q26 : int(1..4)]), + and([q30 <= y_ExplicitVarSizeWithMarker_Marker -> + or([y_ExplicitVarSizeWithDummy[q32] != 6 /\ + y_ExplicitVarSizeWithDummy[q32] = y_ExplicitVarSizeWithMarker_Values[q30] + | q32 : int(1..4)]) + | q30 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_2_3_4_3-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_2_3_4_3-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_3_4_3-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_2_3_4_3-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_2_3_4_3-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_3_4_3-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_2_3_4_3.eprime b/tests/exhaustive/basic/set09/expected/model_2_3_4_3.eprime new file mode 100644 index 0000000000..f8dcddf3df --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_3_4_3.eprime @@ -0,0 +1,40 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_ExplicitVarSizeWithMarker_Marker: int(0..4) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +branching on + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy, + y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values] +such that + and([x_ExplicitVarSizeWithDummy[q21] != 6 /\ q22 <= y_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithDummy[q21] + 2 = y_ExplicitVarSizeWithMarker_Values[q22] + | q21 : int(1..4), q22 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 6 + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q2] = 6 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 6 | q2 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 6) | q3 : int(1..4)]), + and([q5 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> + y_ExplicitVarSizeWithMarker_Values[q5] < y_ExplicitVarSizeWithMarker_Values[q5 + 1] + | q5 : int(1..3)]), + and([q6 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q6] = 2 | q6 : int(1..4)]), + 1 <= y_ExplicitVarSizeWithMarker_Marker, + and([x_ExplicitVarSizeWithFlags_Flags[q8 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q8] < x_ExplicitVarSizeWithFlags_Values[q8 + 1] + | q8 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q9] = false -> x_ExplicitVarSizeWithFlags_Values[q9] = 2 | q9 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q10 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q10] | q10 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q11]) | q11 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q14] -> + or([x_ExplicitVarSizeWithDummy[q16] != 6 /\ + x_ExplicitVarSizeWithDummy[q16] = x_ExplicitVarSizeWithFlags_Values[q14] + | q16 : int(1..4)]) + | q14 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q18] != 6 -> + or([x_ExplicitVarSizeWithFlags_Flags[q20] /\ + x_ExplicitVarSizeWithFlags_Values[q20] = x_ExplicitVarSizeWithDummy[q18] + | q20 : int(1..4)]) + | q18 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_2_3_4_4-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_2_3_4_4-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_3_4_4-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_2_3_4_4-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_2_3_4_4-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_3_4_4-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_2_3_4_4.eprime b/tests/exhaustive/basic/set09/expected/model_2_3_4_4.eprime new file mode 100644 index 0000000000..1cc5077042 --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_3_4_4.eprime @@ -0,0 +1,60 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_ExplicitVarSizeWithMarker_Marker: int(0..4) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +branching on + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy, + y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithMarker_Marker, + y_ExplicitVarSizeWithMarker_Values] +such that + and([x_ExplicitVarSizeWithDummy[q34] != 6 /\ q35 <= y_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithDummy[q34] + 2 = y_ExplicitVarSizeWithMarker_Values[q35] + | q34 : int(1..4), q35 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 6 + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q2] = 6 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 6 | q2 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 6) | q3 : int(1..4)]), + and([q5 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> + y_ExplicitVarSizeWithMarker_Values[q5] < y_ExplicitVarSizeWithMarker_Values[q5 + 1] + | q5 : int(1..3)]), + and([q6 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q6] = 2 | q6 : int(1..4)]), + 1 <= y_ExplicitVarSizeWithMarker_Marker, + and([x_ExplicitVarSizeWithFlags_Flags[q8 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q8] < x_ExplicitVarSizeWithFlags_Values[q8 + 1] + | q8 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q9] = false -> x_ExplicitVarSizeWithFlags_Values[q9] = 2 | q9 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q10 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q10] | q10 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q11]) | q11 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q14] -> + or([x_ExplicitVarSizeWithDummy[q16] != 6 /\ + x_ExplicitVarSizeWithDummy[q16] = x_ExplicitVarSizeWithFlags_Values[q14] + | q16 : int(1..4)]) + | q14 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q18] != 6 -> + or([x_ExplicitVarSizeWithFlags_Flags[q20] /\ + x_ExplicitVarSizeWithFlags_Values[q20] = x_ExplicitVarSizeWithDummy[q18] + | q20 : int(1..4)]) + | q18 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q21 + 1] -> + y_ExplicitVarSizeWithFlags_Values[q21] < y_ExplicitVarSizeWithFlags_Values[q21 + 1] + | q21 : int(1..3)]), + and([y_ExplicitVarSizeWithFlags_Flags[q22] = false -> y_ExplicitVarSizeWithFlags_Values[q22] = 2 + | q22 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q23 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q23] | q23 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q24]) | q24 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q27] -> + or([q29 <= y_ExplicitVarSizeWithMarker_Marker /\ + y_ExplicitVarSizeWithMarker_Values[q29] = y_ExplicitVarSizeWithFlags_Values[q27] + | q29 : int(1..4)]) + | q27 : int(1..4)]), + and([q31 <= y_ExplicitVarSizeWithMarker_Marker -> + or([y_ExplicitVarSizeWithFlags_Flags[q33] /\ + y_ExplicitVarSizeWithFlags_Values[q33] = y_ExplicitVarSizeWithMarker_Values[q31] + | q33 : int(1..4)]) + | q31 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_2_4_1_1-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_2_4_1_1-solution000001.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_4_1_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_2_4_1_1-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_2_4_1_1-solution000002.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_4_1_1-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_2_4_1_1.eprime b/tests/exhaustive/basic/set09/expected/model_2_4_1_1.eprime new file mode 100644 index 0000000000..51a23a711f --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_4_1_1.eprime @@ -0,0 +1,36 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +find x_Occurrence: matrix indexed by [int(2..5)] of bool +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_Occurrence: matrix indexed by [int(2..5)] of bool +branching on + [x_Occurrence, x_ExplicitVarSizeWithDummy, y_Occurrence, y_ExplicitVarSizeWithFlags_Flags, + y_ExplicitVarSizeWithFlags_Values] +such that + and([x_ExplicitVarSizeWithDummy[q17] != 6 /\ y_ExplicitVarSizeWithFlags_Flags[q18] -> + x_ExplicitVarSizeWithDummy[q17] + 2 = y_ExplicitVarSizeWithFlags_Values[q18] + | q17 : int(1..4), q18 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 6 + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q2] = 6 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 6 | q2 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 6) | q3 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q5 + 1] -> + y_ExplicitVarSizeWithFlags_Values[q5] < y_ExplicitVarSizeWithFlags_Values[q5 + 1] + | q5 : int(1..3)]), + and([y_ExplicitVarSizeWithFlags_Flags[q6] = false -> y_ExplicitVarSizeWithFlags_Values[q6] = 2 | q6 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q7] | q7 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q8]) | q8 : int(1..4)]), + 1 <= sum([toInt(x_Occurrence[q10]) | q10 : int(2..5)]), + and([x_Occurrence[q19] -> + or([x_ExplicitVarSizeWithDummy[q21] != 6 /\ x_ExplicitVarSizeWithDummy[q21] = q19 | q21 : int(1..4)]) + | q19 : int(2..5)]), + and([x_ExplicitVarSizeWithDummy[q23] != 6 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q23]] | q23 : int(1..4)]), + 1 <= sum([toInt(y_Occurrence[q11]) | q11 : int(2..5)]), + and([y_Occurrence[q12] -> + or([y_ExplicitVarSizeWithFlags_Flags[q14] /\ y_ExplicitVarSizeWithFlags_Values[q14] = q12 | q14 : int(1..4)]) + | q12 : int(2..5)]), + and([y_ExplicitVarSizeWithFlags_Flags[q16] -> y_Occurrence[y_ExplicitVarSizeWithFlags_Values[q16]] + | q16 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_2_4_1_2-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_2_4_1_2-solution000001.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_4_1_2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_2_4_1_2-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_2_4_1_2-solution000002.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_4_1_2-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_2_4_1_2.eprime b/tests/exhaustive/basic/set09/expected/model_2_4_1_2.eprime new file mode 100644 index 0000000000..083bfa5f86 --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_4_1_2.eprime @@ -0,0 +1,44 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +find x_Occurrence: matrix indexed by [int(2..5)] of bool +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +branching on + [x_Occurrence, x_ExplicitVarSizeWithDummy, y_ExplicitVarSizeWithDummy, y_ExplicitVarSizeWithFlags_Flags, + y_ExplicitVarSizeWithFlags_Values] +such that + and([x_ExplicitVarSizeWithDummy[q28] != 6 /\ y_ExplicitVarSizeWithFlags_Flags[q29] -> + x_ExplicitVarSizeWithDummy[q28] + 2 = y_ExplicitVarSizeWithFlags_Values[q29] + | q28 : int(1..4), q29 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 6 + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q2] = 6 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 6 | q2 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 6) | q3 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q5 + 1] -> + y_ExplicitVarSizeWithFlags_Values[q5] < y_ExplicitVarSizeWithFlags_Values[q5 + 1] + | q5 : int(1..3)]), + and([y_ExplicitVarSizeWithFlags_Flags[q6] = false -> y_ExplicitVarSizeWithFlags_Values[q6] = 2 | q6 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q7] | q7 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q8]) | q8 : int(1..4)]), + 1 <= sum([toInt(x_Occurrence[q10]) | q10 : int(2..5)]), + and([x_Occurrence[q23] -> + or([x_ExplicitVarSizeWithDummy[q25] != 6 /\ x_ExplicitVarSizeWithDummy[q25] = q23 | q25 : int(1..4)]) + | q23 : int(2..5)]), + and([x_ExplicitVarSizeWithDummy[q27] != 6 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q27]] | q27 : int(1..4)]), + and([y_ExplicitVarSizeWithDummy[q11] < y_ExplicitVarSizeWithDummy[q11 + 1] \/ y_ExplicitVarSizeWithDummy[q11] = 6 + | q11 : int(1..3)]), + and([y_ExplicitVarSizeWithDummy[q12] = 6 -> y_ExplicitVarSizeWithDummy[q12 + 1] = 6 | q12 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q13] != 6) | q13 : int(1..4)]), + and([y_ExplicitVarSizeWithDummy[q16] != 6 -> + or([y_ExplicitVarSizeWithFlags_Flags[q18] /\ + y_ExplicitVarSizeWithFlags_Values[q18] = y_ExplicitVarSizeWithDummy[q16] + | q18 : int(1..4)]) + | q16 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q20] -> + or([y_ExplicitVarSizeWithDummy[q22] != 6 /\ + y_ExplicitVarSizeWithDummy[q22] = y_ExplicitVarSizeWithFlags_Values[q20] + | q22 : int(1..4)]) + | q20 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_2_4_1_3-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_2_4_1_3-solution000001.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_4_1_3-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_2_4_1_3-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_2_4_1_3-solution000002.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_4_1_3-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_2_4_1_3.eprime b/tests/exhaustive/basic/set09/expected/model_2_4_1_3.eprime new file mode 100644 index 0000000000..c74d6fc321 --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_4_1_3.eprime @@ -0,0 +1,46 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +find x_Occurrence: matrix indexed by [int(2..5)] of bool +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_ExplicitVarSizeWithMarker_Marker: int(0..4) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +branching on + [x_Occurrence, x_ExplicitVarSizeWithDummy, y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values, + y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values] +such that + and([x_ExplicitVarSizeWithDummy[q27] != 6 /\ y_ExplicitVarSizeWithFlags_Flags[q28] -> + x_ExplicitVarSizeWithDummy[q27] + 2 = y_ExplicitVarSizeWithFlags_Values[q28] + | q27 : int(1..4), q28 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 6 + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q2] = 6 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 6 | q2 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 6) | q3 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q5 + 1] -> + y_ExplicitVarSizeWithFlags_Values[q5] < y_ExplicitVarSizeWithFlags_Values[q5 + 1] + | q5 : int(1..3)]), + and([y_ExplicitVarSizeWithFlags_Flags[q6] = false -> y_ExplicitVarSizeWithFlags_Values[q6] = 2 | q6 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q7] | q7 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q8]) | q8 : int(1..4)]), + 1 <= sum([toInt(x_Occurrence[q10]) | q10 : int(2..5)]), + and([x_Occurrence[q22] -> + or([x_ExplicitVarSizeWithDummy[q24] != 6 /\ x_ExplicitVarSizeWithDummy[q24] = q22 | q24 : int(1..4)]) + | q22 : int(2..5)]), + and([x_ExplicitVarSizeWithDummy[q26] != 6 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q26]] | q26 : int(1..4)]), + and([q11 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> + y_ExplicitVarSizeWithMarker_Values[q11] < y_ExplicitVarSizeWithMarker_Values[q11 + 1] + | q11 : int(1..3)]), + and([q12 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q12] = 2 | q12 : int(1..4)]), + 1 <= y_ExplicitVarSizeWithMarker_Marker, + and([q15 <= y_ExplicitVarSizeWithMarker_Marker -> + or([y_ExplicitVarSizeWithFlags_Flags[q17] /\ + y_ExplicitVarSizeWithFlags_Values[q17] = y_ExplicitVarSizeWithMarker_Values[q15] + | q17 : int(1..4)]) + | q15 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q19] -> + or([q21 <= y_ExplicitVarSizeWithMarker_Marker /\ + y_ExplicitVarSizeWithMarker_Values[q21] = y_ExplicitVarSizeWithFlags_Values[q19] + | q21 : int(1..4)]) + | q19 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_2_4_1_4-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_2_4_1_4-solution000001.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_4_1_4-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_2_4_1_4-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_2_4_1_4-solution000002.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_4_1_4-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_2_4_1_4.eprime b/tests/exhaustive/basic/set09/expected/model_2_4_1_4.eprime new file mode 100644 index 0000000000..97d878a880 --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_4_1_4.eprime @@ -0,0 +1,28 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +find x_Occurrence: matrix indexed by [int(2..5)] of bool +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +branching on + [x_Occurrence, x_ExplicitVarSizeWithDummy, y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values] +such that + and([x_ExplicitVarSizeWithDummy[q16] != 6 /\ y_ExplicitVarSizeWithFlags_Flags[q17] -> + x_ExplicitVarSizeWithDummy[q16] + 2 = y_ExplicitVarSizeWithFlags_Values[q17] + | q16 : int(1..4), q17 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 6 + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q2] = 6 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 6 | q2 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 6) | q3 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q5 + 1] -> + y_ExplicitVarSizeWithFlags_Values[q5] < y_ExplicitVarSizeWithFlags_Values[q5 + 1] + | q5 : int(1..3)]), + and([y_ExplicitVarSizeWithFlags_Flags[q6] = false -> y_ExplicitVarSizeWithFlags_Values[q6] = 2 | q6 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q7] | q7 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q8]) | q8 : int(1..4)]), + 1 <= sum([toInt(x_Occurrence[q10]) | q10 : int(2..5)]), + and([x_Occurrence[q11] -> + or([x_ExplicitVarSizeWithDummy[q13] != 6 /\ x_ExplicitVarSizeWithDummy[q13] = q11 | q13 : int(1..4)]) + | q11 : int(2..5)]), + and([x_ExplicitVarSizeWithDummy[q15] != 6 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q15]] | q15 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_2_4_2_1-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_2_4_2_1-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_4_2_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_2_4_2_1-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_2_4_2_1-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_4_2_1-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_2_4_2_1.eprime b/tests/exhaustive/basic/set09/expected/model_2_4_2_1.eprime new file mode 100644 index 0000000000..d2d26b37e7 --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_4_2_1.eprime @@ -0,0 +1,29 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_Occurrence: matrix indexed by [int(2..5)] of bool +branching on + [x_ExplicitVarSizeWithDummy, y_Occurrence, y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values] +such that + and([x_ExplicitVarSizeWithDummy[q16] != 6 /\ y_ExplicitVarSizeWithFlags_Flags[q17] -> + x_ExplicitVarSizeWithDummy[q16] + 2 = y_ExplicitVarSizeWithFlags_Values[q17] + | q16 : int(1..4), q17 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 6 + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q2] = 6 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 6 | q2 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 6) | q3 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q5 + 1] -> + y_ExplicitVarSizeWithFlags_Values[q5] < y_ExplicitVarSizeWithFlags_Values[q5 + 1] + | q5 : int(1..3)]), + and([y_ExplicitVarSizeWithFlags_Flags[q6] = false -> y_ExplicitVarSizeWithFlags_Values[q6] = 2 | q6 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q7] | q7 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q8]) | q8 : int(1..4)]), + 1 <= sum([toInt(y_Occurrence[q10]) | q10 : int(2..5)]), + and([y_Occurrence[q11] -> + or([y_ExplicitVarSizeWithFlags_Flags[q13] /\ y_ExplicitVarSizeWithFlags_Values[q13] = q11 | q13 : int(1..4)]) + | q11 : int(2..5)]), + and([y_ExplicitVarSizeWithFlags_Flags[q15] -> y_Occurrence[y_ExplicitVarSizeWithFlags_Values[q15]] + | q15 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_2_4_2_2-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_2_4_2_2-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_4_2_2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_2_4_2_2-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_2_4_2_2-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_4_2_2-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_2_4_2_2.eprime b/tests/exhaustive/basic/set09/expected/model_2_4_2_2.eprime new file mode 100644 index 0000000000..327bbcc12e --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_4_2_2.eprime @@ -0,0 +1,38 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +branching on + [x_ExplicitVarSizeWithDummy, y_ExplicitVarSizeWithDummy, y_ExplicitVarSizeWithFlags_Flags, + y_ExplicitVarSizeWithFlags_Values] +such that + and([x_ExplicitVarSizeWithDummy[q22] != 6 /\ y_ExplicitVarSizeWithFlags_Flags[q23] -> + x_ExplicitVarSizeWithDummy[q22] + 2 = y_ExplicitVarSizeWithFlags_Values[q23] + | q22 : int(1..4), q23 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 6 + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q2] = 6 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 6 | q2 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 6) | q3 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q5 + 1] -> + y_ExplicitVarSizeWithFlags_Values[q5] < y_ExplicitVarSizeWithFlags_Values[q5 + 1] + | q5 : int(1..3)]), + and([y_ExplicitVarSizeWithFlags_Flags[q6] = false -> y_ExplicitVarSizeWithFlags_Values[q6] = 2 | q6 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q7] | q7 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q8]) | q8 : int(1..4)]), + and([y_ExplicitVarSizeWithDummy[q10] < y_ExplicitVarSizeWithDummy[q10 + 1] \/ y_ExplicitVarSizeWithDummy[q10] = 6 + | q10 : int(1..3)]), + and([y_ExplicitVarSizeWithDummy[q11] = 6 -> y_ExplicitVarSizeWithDummy[q11 + 1] = 6 | q11 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q12] != 6) | q12 : int(1..4)]), + and([y_ExplicitVarSizeWithDummy[q15] != 6 -> + or([y_ExplicitVarSizeWithFlags_Flags[q17] /\ + y_ExplicitVarSizeWithFlags_Values[q17] = y_ExplicitVarSizeWithDummy[q15] + | q17 : int(1..4)]) + | q15 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q19] -> + or([y_ExplicitVarSizeWithDummy[q21] != 6 /\ + y_ExplicitVarSizeWithDummy[q21] = y_ExplicitVarSizeWithFlags_Values[q19] + | q21 : int(1..4)]) + | q19 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_2_4_2_3-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_2_4_2_3-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_4_2_3-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_2_4_2_3-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_2_4_2_3-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_4_2_3-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_2_4_2_3.eprime b/tests/exhaustive/basic/set09/expected/model_2_4_2_3.eprime new file mode 100644 index 0000000000..7b22da50fd --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_4_2_3.eprime @@ -0,0 +1,40 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_ExplicitVarSizeWithMarker_Marker: int(0..4) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +branching on + [x_ExplicitVarSizeWithDummy, y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values, + y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values] +such that + and([x_ExplicitVarSizeWithDummy[q21] != 6 /\ y_ExplicitVarSizeWithFlags_Flags[q22] -> + x_ExplicitVarSizeWithDummy[q21] + 2 = y_ExplicitVarSizeWithFlags_Values[q22] + | q21 : int(1..4), q22 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 6 + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q2] = 6 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 6 | q2 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 6) | q3 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q5 + 1] -> + y_ExplicitVarSizeWithFlags_Values[q5] < y_ExplicitVarSizeWithFlags_Values[q5 + 1] + | q5 : int(1..3)]), + and([y_ExplicitVarSizeWithFlags_Flags[q6] = false -> y_ExplicitVarSizeWithFlags_Values[q6] = 2 | q6 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q7] | q7 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q8]) | q8 : int(1..4)]), + and([q10 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> + y_ExplicitVarSizeWithMarker_Values[q10] < y_ExplicitVarSizeWithMarker_Values[q10 + 1] + | q10 : int(1..3)]), + and([q11 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q11] = 2 | q11 : int(1..4)]), + 1 <= y_ExplicitVarSizeWithMarker_Marker, + and([q14 <= y_ExplicitVarSizeWithMarker_Marker -> + or([y_ExplicitVarSizeWithFlags_Flags[q16] /\ + y_ExplicitVarSizeWithFlags_Values[q16] = y_ExplicitVarSizeWithMarker_Values[q14] + | q16 : int(1..4)]) + | q14 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q18] -> + or([q20 <= y_ExplicitVarSizeWithMarker_Marker /\ + y_ExplicitVarSizeWithMarker_Values[q20] = y_ExplicitVarSizeWithFlags_Values[q18] + | q20 : int(1..4)]) + | q18 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_2_4_2_4-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_2_4_2_4-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_4_2_4-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_2_4_2_4-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_2_4_2_4-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_4_2_4-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_2_4_2_4.eprime b/tests/exhaustive/basic/set09/expected/model_2_4_2_4.eprime new file mode 100644 index 0000000000..1fa334760d --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_4_2_4.eprime @@ -0,0 +1,21 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +branching on [x_ExplicitVarSizeWithDummy, y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values] +such that + and([x_ExplicitVarSizeWithDummy[q10] != 6 /\ y_ExplicitVarSizeWithFlags_Flags[q11] -> + x_ExplicitVarSizeWithDummy[q10] + 2 = y_ExplicitVarSizeWithFlags_Values[q11] + | q10 : int(1..4), q11 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 6 + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q2] = 6 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 6 | q2 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 6) | q3 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q5 + 1] -> + y_ExplicitVarSizeWithFlags_Values[q5] < y_ExplicitVarSizeWithFlags_Values[q5 + 1] + | q5 : int(1..3)]), + and([y_ExplicitVarSizeWithFlags_Flags[q6] = false -> y_ExplicitVarSizeWithFlags_Values[q6] = 2 | q6 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q7] | q7 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q8]) | q8 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_2_4_3_1-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_2_4_3_1-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_4_3_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_2_4_3_1-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_2_4_3_1-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_4_3_1-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_2_4_3_1.eprime b/tests/exhaustive/basic/set09/expected/model_2_4_3_1.eprime new file mode 100644 index 0000000000..25a9e61546 --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_4_3_1.eprime @@ -0,0 +1,47 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_Occurrence: matrix indexed by [int(2..5)] of bool +branching on + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy, y_Occurrence, + y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values] +such that + and([x_ExplicitVarSizeWithDummy[q27] != 6 /\ y_ExplicitVarSizeWithFlags_Flags[q28] -> + x_ExplicitVarSizeWithDummy[q27] + 2 = y_ExplicitVarSizeWithFlags_Values[q28] + | q27 : int(1..4), q28 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 6 + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q2] = 6 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 6 | q2 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 6) | q3 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q5 + 1] -> + y_ExplicitVarSizeWithFlags_Values[q5] < y_ExplicitVarSizeWithFlags_Values[q5 + 1] + | q5 : int(1..3)]), + and([y_ExplicitVarSizeWithFlags_Flags[q6] = false -> y_ExplicitVarSizeWithFlags_Values[q6] = 2 | q6 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q7] | q7 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q8]) | q8 : int(1..4)]), + and([q10 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q10] < x_ExplicitVarSizeWithMarker_Values[q10 + 1] + | q10 : int(1..3)]), + and([q11 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q11] = 2 | q11 : int(1..4)]), + 1 <= x_ExplicitVarSizeWithMarker_Marker, + and([q14 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithDummy[q16] != 6 /\ + x_ExplicitVarSizeWithDummy[q16] = x_ExplicitVarSizeWithMarker_Values[q14] + | q16 : int(1..4)]) + | q14 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q18] != 6 -> + or([q20 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q20] = x_ExplicitVarSizeWithDummy[q18] + | q20 : int(1..4)]) + | q18 : int(1..4)]), + 1 <= sum([toInt(y_Occurrence[q21]) | q21 : int(2..5)]), + and([y_Occurrence[q22] -> + or([y_ExplicitVarSizeWithFlags_Flags[q24] /\ y_ExplicitVarSizeWithFlags_Values[q24] = q22 | q24 : int(1..4)]) + | q22 : int(2..5)]), + and([y_ExplicitVarSizeWithFlags_Flags[q26] -> y_Occurrence[y_ExplicitVarSizeWithFlags_Values[q26]] + | q26 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_2_4_3_2-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_2_4_3_2-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_4_3_2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_2_4_3_2-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_2_4_3_2-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_4_3_2-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_2_4_3_2.eprime b/tests/exhaustive/basic/set09/expected/model_2_4_3_2.eprime new file mode 100644 index 0000000000..64200ff954 --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_4_3_2.eprime @@ -0,0 +1,55 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +branching on + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy, + y_ExplicitVarSizeWithDummy, y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values] +such that + and([x_ExplicitVarSizeWithDummy[q33] != 6 /\ y_ExplicitVarSizeWithFlags_Flags[q34] -> + x_ExplicitVarSizeWithDummy[q33] + 2 = y_ExplicitVarSizeWithFlags_Values[q34] + | q33 : int(1..4), q34 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 6 + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q2] = 6 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 6 | q2 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 6) | q3 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q5 + 1] -> + y_ExplicitVarSizeWithFlags_Values[q5] < y_ExplicitVarSizeWithFlags_Values[q5 + 1] + | q5 : int(1..3)]), + and([y_ExplicitVarSizeWithFlags_Flags[q6] = false -> y_ExplicitVarSizeWithFlags_Values[q6] = 2 | q6 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q7] | q7 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q8]) | q8 : int(1..4)]), + and([q10 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q10] < x_ExplicitVarSizeWithMarker_Values[q10 + 1] + | q10 : int(1..3)]), + and([q11 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q11] = 2 | q11 : int(1..4)]), + 1 <= x_ExplicitVarSizeWithMarker_Marker, + and([q14 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithDummy[q16] != 6 /\ + x_ExplicitVarSizeWithDummy[q16] = x_ExplicitVarSizeWithMarker_Values[q14] + | q16 : int(1..4)]) + | q14 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q18] != 6 -> + or([q20 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q20] = x_ExplicitVarSizeWithDummy[q18] + | q20 : int(1..4)]) + | q18 : int(1..4)]), + and([y_ExplicitVarSizeWithDummy[q21] < y_ExplicitVarSizeWithDummy[q21 + 1] \/ y_ExplicitVarSizeWithDummy[q21] = 6 + | q21 : int(1..3)]), + and([y_ExplicitVarSizeWithDummy[q22] = 6 -> y_ExplicitVarSizeWithDummy[q22 + 1] = 6 | q22 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q23] != 6) | q23 : int(1..4)]), + and([y_ExplicitVarSizeWithDummy[q26] != 6 -> + or([y_ExplicitVarSizeWithFlags_Flags[q28] /\ + y_ExplicitVarSizeWithFlags_Values[q28] = y_ExplicitVarSizeWithDummy[q26] + | q28 : int(1..4)]) + | q26 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q30] -> + or([y_ExplicitVarSizeWithDummy[q32] != 6 /\ + y_ExplicitVarSizeWithDummy[q32] = y_ExplicitVarSizeWithFlags_Values[q30] + | q32 : int(1..4)]) + | q30 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_2_4_3_3-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_2_4_3_3-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_4_3_3-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_2_4_3_3-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_2_4_3_3-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_4_3_3-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_2_4_3_3.eprime b/tests/exhaustive/basic/set09/expected/model_2_4_3_3.eprime new file mode 100644 index 0000000000..ccb1314b95 --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_4_3_3.eprime @@ -0,0 +1,58 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_ExplicitVarSizeWithMarker_Marker: int(0..4) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +branching on + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy, + y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithFlags_Flags, + y_ExplicitVarSizeWithFlags_Values] +such that + and([x_ExplicitVarSizeWithDummy[q32] != 6 /\ y_ExplicitVarSizeWithFlags_Flags[q33] -> + x_ExplicitVarSizeWithDummy[q32] + 2 = y_ExplicitVarSizeWithFlags_Values[q33] + | q32 : int(1..4), q33 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 6 + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q2] = 6 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 6 | q2 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 6) | q3 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q5 + 1] -> + y_ExplicitVarSizeWithFlags_Values[q5] < y_ExplicitVarSizeWithFlags_Values[q5 + 1] + | q5 : int(1..3)]), + and([y_ExplicitVarSizeWithFlags_Flags[q6] = false -> y_ExplicitVarSizeWithFlags_Values[q6] = 2 | q6 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q7] | q7 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q8]) | q8 : int(1..4)]), + and([q10 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q10] < x_ExplicitVarSizeWithMarker_Values[q10 + 1] + | q10 : int(1..3)]), + and([q11 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q11] = 2 | q11 : int(1..4)]), + 1 <= x_ExplicitVarSizeWithMarker_Marker, + and([q14 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithDummy[q16] != 6 /\ + x_ExplicitVarSizeWithDummy[q16] = x_ExplicitVarSizeWithMarker_Values[q14] + | q16 : int(1..4)]) + | q14 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q18] != 6 -> + or([q20 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q20] = x_ExplicitVarSizeWithDummy[q18] + | q20 : int(1..4)]) + | q18 : int(1..4)]), + and([q21 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> + y_ExplicitVarSizeWithMarker_Values[q21] < y_ExplicitVarSizeWithMarker_Values[q21 + 1] + | q21 : int(1..3)]), + and([q22 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q22] = 2 | q22 : int(1..4)]), + 1 <= y_ExplicitVarSizeWithMarker_Marker, + and([q25 <= y_ExplicitVarSizeWithMarker_Marker -> + or([y_ExplicitVarSizeWithFlags_Flags[q27] /\ + y_ExplicitVarSizeWithFlags_Values[q27] = y_ExplicitVarSizeWithMarker_Values[q25] + | q27 : int(1..4)]) + | q25 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q29] -> + or([q31 <= y_ExplicitVarSizeWithMarker_Marker /\ + y_ExplicitVarSizeWithMarker_Values[q31] = y_ExplicitVarSizeWithFlags_Values[q29] + | q31 : int(1..4)]) + | q29 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_2_4_3_4-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_2_4_3_4-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_4_3_4-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_2_4_3_4-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_2_4_3_4-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_4_3_4-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_2_4_3_4.eprime b/tests/exhaustive/basic/set09/expected/model_2_4_3_4.eprime new file mode 100644 index 0000000000..f3cf03d434 --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_4_3_4.eprime @@ -0,0 +1,40 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +branching on + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy, + y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values] +such that + and([x_ExplicitVarSizeWithDummy[q21] != 6 /\ y_ExplicitVarSizeWithFlags_Flags[q22] -> + x_ExplicitVarSizeWithDummy[q21] + 2 = y_ExplicitVarSizeWithFlags_Values[q22] + | q21 : int(1..4), q22 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 6 + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q2] = 6 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 6 | q2 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 6) | q3 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q5 + 1] -> + y_ExplicitVarSizeWithFlags_Values[q5] < y_ExplicitVarSizeWithFlags_Values[q5 + 1] + | q5 : int(1..3)]), + and([y_ExplicitVarSizeWithFlags_Flags[q6] = false -> y_ExplicitVarSizeWithFlags_Values[q6] = 2 | q6 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q7] | q7 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q8]) | q8 : int(1..4)]), + and([q10 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q10] < x_ExplicitVarSizeWithMarker_Values[q10 + 1] + | q10 : int(1..3)]), + and([q11 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q11] = 2 | q11 : int(1..4)]), + 1 <= x_ExplicitVarSizeWithMarker_Marker, + and([q14 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithDummy[q16] != 6 /\ + x_ExplicitVarSizeWithDummy[q16] = x_ExplicitVarSizeWithMarker_Values[q14] + | q16 : int(1..4)]) + | q14 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q18] != 6 -> + or([q20 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q20] = x_ExplicitVarSizeWithDummy[q18] + | q20 : int(1..4)]) + | q18 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_2_4_4_1-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_2_4_4_1-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_4_4_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_2_4_4_1-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_2_4_4_1-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_4_4_1-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_2_4_4_1.eprime b/tests/exhaustive/basic/set09/expected/model_2_4_4_1.eprime new file mode 100644 index 0000000000..2e1cf8717a --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_4_4_1.eprime @@ -0,0 +1,49 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_Occurrence: matrix indexed by [int(2..5)] of bool +branching on + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy, y_Occurrence, + y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values] +such that + and([x_ExplicitVarSizeWithDummy[q29] != 6 /\ y_ExplicitVarSizeWithFlags_Flags[q30] -> + x_ExplicitVarSizeWithDummy[q29] + 2 = y_ExplicitVarSizeWithFlags_Values[q30] + | q29 : int(1..4), q30 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 6 + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q2] = 6 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 6 | q2 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 6) | q3 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q5 + 1] -> + y_ExplicitVarSizeWithFlags_Values[q5] < y_ExplicitVarSizeWithFlags_Values[q5 + 1] + | q5 : int(1..3)]), + and([y_ExplicitVarSizeWithFlags_Flags[q6] = false -> y_ExplicitVarSizeWithFlags_Values[q6] = 2 | q6 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q7] | q7 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q8]) | q8 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q10 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q10] < x_ExplicitVarSizeWithFlags_Values[q10 + 1] + | q10 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q11] = false -> x_ExplicitVarSizeWithFlags_Values[q11] = 2 + | q11 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q12 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q12] | q12 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q13]) | q13 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q16] -> + or([x_ExplicitVarSizeWithDummy[q18] != 6 /\ + x_ExplicitVarSizeWithDummy[q18] = x_ExplicitVarSizeWithFlags_Values[q16] + | q18 : int(1..4)]) + | q16 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q20] != 6 -> + or([x_ExplicitVarSizeWithFlags_Flags[q22] /\ + x_ExplicitVarSizeWithFlags_Values[q22] = x_ExplicitVarSizeWithDummy[q20] + | q22 : int(1..4)]) + | q20 : int(1..4)]), + 1 <= sum([toInt(y_Occurrence[q23]) | q23 : int(2..5)]), + and([y_Occurrence[q24] -> + or([y_ExplicitVarSizeWithFlags_Flags[q26] /\ y_ExplicitVarSizeWithFlags_Values[q26] = q24 | q26 : int(1..4)]) + | q24 : int(2..5)]), + and([y_ExplicitVarSizeWithFlags_Flags[q28] -> y_Occurrence[y_ExplicitVarSizeWithFlags_Values[q28]] + | q28 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_2_4_4_2-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_2_4_4_2-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_4_4_2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_2_4_4_2-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_2_4_4_2-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_4_4_2-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_2_4_4_2.eprime b/tests/exhaustive/basic/set09/expected/model_2_4_4_2.eprime new file mode 100644 index 0000000000..ad0d98f173 --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_4_4_2.eprime @@ -0,0 +1,57 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +branching on + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy, + y_ExplicitVarSizeWithDummy, y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values] +such that + and([x_ExplicitVarSizeWithDummy[q35] != 6 /\ y_ExplicitVarSizeWithFlags_Flags[q36] -> + x_ExplicitVarSizeWithDummy[q35] + 2 = y_ExplicitVarSizeWithFlags_Values[q36] + | q35 : int(1..4), q36 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 6 + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q2] = 6 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 6 | q2 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 6) | q3 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q5 + 1] -> + y_ExplicitVarSizeWithFlags_Values[q5] < y_ExplicitVarSizeWithFlags_Values[q5 + 1] + | q5 : int(1..3)]), + and([y_ExplicitVarSizeWithFlags_Flags[q6] = false -> y_ExplicitVarSizeWithFlags_Values[q6] = 2 | q6 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q7] | q7 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q8]) | q8 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q10 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q10] < x_ExplicitVarSizeWithFlags_Values[q10 + 1] + | q10 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q11] = false -> x_ExplicitVarSizeWithFlags_Values[q11] = 2 + | q11 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q12 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q12] | q12 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q13]) | q13 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q16] -> + or([x_ExplicitVarSizeWithDummy[q18] != 6 /\ + x_ExplicitVarSizeWithDummy[q18] = x_ExplicitVarSizeWithFlags_Values[q16] + | q18 : int(1..4)]) + | q16 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q20] != 6 -> + or([x_ExplicitVarSizeWithFlags_Flags[q22] /\ + x_ExplicitVarSizeWithFlags_Values[q22] = x_ExplicitVarSizeWithDummy[q20] + | q22 : int(1..4)]) + | q20 : int(1..4)]), + and([y_ExplicitVarSizeWithDummy[q23] < y_ExplicitVarSizeWithDummy[q23 + 1] \/ y_ExplicitVarSizeWithDummy[q23] = 6 + | q23 : int(1..3)]), + and([y_ExplicitVarSizeWithDummy[q24] = 6 -> y_ExplicitVarSizeWithDummy[q24 + 1] = 6 | q24 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q25] != 6) | q25 : int(1..4)]), + and([y_ExplicitVarSizeWithDummy[q28] != 6 -> + or([y_ExplicitVarSizeWithFlags_Flags[q30] /\ + y_ExplicitVarSizeWithFlags_Values[q30] = y_ExplicitVarSizeWithDummy[q28] + | q30 : int(1..4)]) + | q28 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q32] -> + or([y_ExplicitVarSizeWithDummy[q34] != 6 /\ + y_ExplicitVarSizeWithDummy[q34] = y_ExplicitVarSizeWithFlags_Values[q32] + | q34 : int(1..4)]) + | q32 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_2_4_4_3-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_2_4_4_3-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_4_4_3-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_2_4_4_3-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_2_4_4_3-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_4_4_3-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_2_4_4_3.eprime b/tests/exhaustive/basic/set09/expected/model_2_4_4_3.eprime new file mode 100644 index 0000000000..c1250928a1 --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_4_4_3.eprime @@ -0,0 +1,60 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_ExplicitVarSizeWithMarker_Marker: int(0..4) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +branching on + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy, + y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithFlags_Flags, + y_ExplicitVarSizeWithFlags_Values] +such that + and([x_ExplicitVarSizeWithDummy[q34] != 6 /\ y_ExplicitVarSizeWithFlags_Flags[q35] -> + x_ExplicitVarSizeWithDummy[q34] + 2 = y_ExplicitVarSizeWithFlags_Values[q35] + | q34 : int(1..4), q35 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 6 + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q2] = 6 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 6 | q2 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 6) | q3 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q5 + 1] -> + y_ExplicitVarSizeWithFlags_Values[q5] < y_ExplicitVarSizeWithFlags_Values[q5 + 1] + | q5 : int(1..3)]), + and([y_ExplicitVarSizeWithFlags_Flags[q6] = false -> y_ExplicitVarSizeWithFlags_Values[q6] = 2 | q6 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q7] | q7 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q8]) | q8 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q10 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q10] < x_ExplicitVarSizeWithFlags_Values[q10 + 1] + | q10 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q11] = false -> x_ExplicitVarSizeWithFlags_Values[q11] = 2 + | q11 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q12 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q12] | q12 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q13]) | q13 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q16] -> + or([x_ExplicitVarSizeWithDummy[q18] != 6 /\ + x_ExplicitVarSizeWithDummy[q18] = x_ExplicitVarSizeWithFlags_Values[q16] + | q18 : int(1..4)]) + | q16 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q20] != 6 -> + or([x_ExplicitVarSizeWithFlags_Flags[q22] /\ + x_ExplicitVarSizeWithFlags_Values[q22] = x_ExplicitVarSizeWithDummy[q20] + | q22 : int(1..4)]) + | q20 : int(1..4)]), + and([q23 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> + y_ExplicitVarSizeWithMarker_Values[q23] < y_ExplicitVarSizeWithMarker_Values[q23 + 1] + | q23 : int(1..3)]), + and([q24 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q24] = 2 | q24 : int(1..4)]), + 1 <= y_ExplicitVarSizeWithMarker_Marker, + and([q27 <= y_ExplicitVarSizeWithMarker_Marker -> + or([y_ExplicitVarSizeWithFlags_Flags[q29] /\ + y_ExplicitVarSizeWithFlags_Values[q29] = y_ExplicitVarSizeWithMarker_Values[q27] + | q29 : int(1..4)]) + | q27 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q31] -> + or([q33 <= y_ExplicitVarSizeWithMarker_Marker /\ + y_ExplicitVarSizeWithMarker_Values[q33] = y_ExplicitVarSizeWithFlags_Values[q31] + | q33 : int(1..4)]) + | q31 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_2_4_4_4-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_2_4_4_4-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_4_4_4-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_2_4_4_4-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_2_4_4_4-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_4_4_4-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_2_4_4_4.eprime b/tests/exhaustive/basic/set09/expected/model_2_4_4_4.eprime new file mode 100644 index 0000000000..b577e5f27d --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_2_4_4_4.eprime @@ -0,0 +1,42 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +branching on + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy, + y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values] +such that + and([x_ExplicitVarSizeWithDummy[q23] != 6 /\ y_ExplicitVarSizeWithFlags_Flags[q24] -> + x_ExplicitVarSizeWithDummy[q23] + 2 = y_ExplicitVarSizeWithFlags_Values[q24] + | q23 : int(1..4), q24 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 6 + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q2] = 6 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 6 | q2 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q3] != 6) | q3 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q5 + 1] -> + y_ExplicitVarSizeWithFlags_Values[q5] < y_ExplicitVarSizeWithFlags_Values[q5 + 1] + | q5 : int(1..3)]), + and([y_ExplicitVarSizeWithFlags_Flags[q6] = false -> y_ExplicitVarSizeWithFlags_Values[q6] = 2 | q6 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q7] | q7 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q8]) | q8 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q10 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q10] < x_ExplicitVarSizeWithFlags_Values[q10 + 1] + | q10 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q11] = false -> x_ExplicitVarSizeWithFlags_Values[q11] = 2 + | q11 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q12 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q12] | q12 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q13]) | q13 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q16] -> + or([x_ExplicitVarSizeWithDummy[q18] != 6 /\ + x_ExplicitVarSizeWithDummy[q18] = x_ExplicitVarSizeWithFlags_Values[q16] + | q18 : int(1..4)]) + | q16 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q20] != 6 -> + or([x_ExplicitVarSizeWithFlags_Flags[q22] /\ + x_ExplicitVarSizeWithFlags_Values[q22] = x_ExplicitVarSizeWithDummy[q20] + | q22 : int(1..4)]) + | q20 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_3_1_1_1-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_3_1_1_1-solution000001.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_1_1_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_3_1_1_1-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_3_1_1_1-solution000002.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_1_1_1-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_3_1_1_1.eprime b/tests/exhaustive/basic/set09/expected/model_3_1_1_1.eprime new file mode 100644 index 0000000000..0898d273ff --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_1_1_1.eprime @@ -0,0 +1,23 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +find x_Occurrence: matrix indexed by [int(2..5)] of bool +find y_Occurrence: matrix indexed by [int(2..5)] of bool +branching on [x_Occurrence, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, y_Occurrence] +such that + and([q11 <= x_ExplicitVarSizeWithMarker_Marker /\ y_Occurrence[j] -> x_ExplicitVarSizeWithMarker_Values[q11] + 2 = j + | q11 : int(1..4), j : int(2..5)]), + and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] + | q1 : int(1..3)]), + and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 2 | q2 : int(1..4)]), + 1 <= x_ExplicitVarSizeWithMarker_Marker, + 1 <= sum([toInt(y_Occurrence[q4]) | q4 : int(2..5)]), + 1 <= sum([toInt(x_Occurrence[q5]) | q5 : int(2..5)]), + and([x_Occurrence[q6] -> + or([q8 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q8] = q6 | q8 : int(1..4)]) + | q6 : int(2..5)]), + and([q10 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q10]] + | q10 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_3_1_1_2-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_3_1_1_2-solution000001.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_1_1_2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_3_1_1_2-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_3_1_1_2-solution000002.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_1_1_2-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_3_1_1_2.eprime b/tests/exhaustive/basic/set09/expected/model_3_1_1_2.eprime new file mode 100644 index 0000000000..0d82bb728f --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_1_1_2.eprime @@ -0,0 +1,35 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +find x_Occurrence: matrix indexed by [int(2..5)] of bool +find y_Occurrence: matrix indexed by [int(2..5)] of bool +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +branching on + [x_Occurrence, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithDummy, + y_Occurrence] +such that + and([q20 <= x_ExplicitVarSizeWithMarker_Marker /\ y_Occurrence[j] -> x_ExplicitVarSizeWithMarker_Values[q20] + 2 = j + | q20 : int(1..4), j : int(2..5)]), + and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] + | q1 : int(1..3)]), + and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 2 | q2 : int(1..4)]), + 1 <= x_ExplicitVarSizeWithMarker_Marker, + 1 <= sum([toInt(y_Occurrence[q4]) | q4 : int(2..5)]), + 1 <= sum([toInt(x_Occurrence[q5]) | q5 : int(2..5)]), + and([x_Occurrence[q15] -> + or([q17 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q17] = q15 + | q17 : int(1..4)]) + | q15 : int(2..5)]), + and([q19 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q19]] + | q19 : int(1..4)]), + and([y_ExplicitVarSizeWithDummy[q6] < y_ExplicitVarSizeWithDummy[q6 + 1] \/ y_ExplicitVarSizeWithDummy[q6] = 6 + | q6 : int(1..3)]), + and([y_ExplicitVarSizeWithDummy[q7] = 6 -> y_ExplicitVarSizeWithDummy[q7 + 1] = 6 | q7 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q8] != 6) | q8 : int(1..4)]), + and([y_ExplicitVarSizeWithDummy[q11] != 6 -> y_Occurrence[y_ExplicitVarSizeWithDummy[q11]] | q11 : int(1..4)]), + and([y_Occurrence[q12] -> + or([y_ExplicitVarSizeWithDummy[q14] != 6 /\ y_ExplicitVarSizeWithDummy[q14] = q12 | q14 : int(1..4)]) + | q12 : int(2..5)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_3_1_1_3-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_3_1_1_3-solution000001.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_1_1_3-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_3_1_1_3-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_3_1_1_3-solution000002.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_1_1_3-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_3_1_1_3.eprime b/tests/exhaustive/basic/set09/expected/model_3_1_1_3.eprime new file mode 100644 index 0000000000..19d7d14337 --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_1_1_3.eprime @@ -0,0 +1,39 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +find x_Occurrence: matrix indexed by [int(2..5)] of bool +find y_Occurrence: matrix indexed by [int(2..5)] of bool +find y_ExplicitVarSizeWithMarker_Marker: int(0..4) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +branching on + [x_Occurrence, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, + y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values, y_Occurrence] +such that + and([q19 <= x_ExplicitVarSizeWithMarker_Marker /\ y_Occurrence[j] -> x_ExplicitVarSizeWithMarker_Values[q19] + 2 = j + | q19 : int(1..4), j : int(2..5)]), + and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] + | q1 : int(1..3)]), + and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 2 | q2 : int(1..4)]), + 1 <= x_ExplicitVarSizeWithMarker_Marker, + 1 <= sum([toInt(y_Occurrence[q4]) | q4 : int(2..5)]), + 1 <= sum([toInt(x_Occurrence[q5]) | q5 : int(2..5)]), + and([x_Occurrence[q14] -> + or([q16 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q16] = q14 + | q16 : int(1..4)]) + | q14 : int(2..5)]), + and([q18 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q18]] + | q18 : int(1..4)]), + and([q6 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> + y_ExplicitVarSizeWithMarker_Values[q6] < y_ExplicitVarSizeWithMarker_Values[q6 + 1] + | q6 : int(1..3)]), + and([q7 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q7] = 2 | q7 : int(1..4)]), + 1 <= y_ExplicitVarSizeWithMarker_Marker, + and([q10 <= y_ExplicitVarSizeWithMarker_Marker -> y_Occurrence[y_ExplicitVarSizeWithMarker_Values[q10]] + | q10 : int(1..4)]), + and([y_Occurrence[q11] -> + or([q13 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[q13] = q11 + | q13 : int(1..4)]) + | q11 : int(2..5)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_3_1_1_4-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_3_1_1_4-solution000001.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_1_1_4-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_3_1_1_4-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_3_1_1_4-solution000002.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_1_1_4-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_3_1_1_4.eprime b/tests/exhaustive/basic/set09/expected/model_3_1_1_4.eprime new file mode 100644 index 0000000000..367803c85b --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_1_1_4.eprime @@ -0,0 +1,39 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +find x_Occurrence: matrix indexed by [int(2..5)] of bool +find y_Occurrence: matrix indexed by [int(2..5)] of bool +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +branching on + [x_Occurrence, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, + y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values, y_Occurrence] +such that + and([q21 <= x_ExplicitVarSizeWithMarker_Marker /\ y_Occurrence[j] -> x_ExplicitVarSizeWithMarker_Values[q21] + 2 = j + | q21 : int(1..4), j : int(2..5)]), + and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] + | q1 : int(1..3)]), + and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 2 | q2 : int(1..4)]), + 1 <= x_ExplicitVarSizeWithMarker_Marker, + 1 <= sum([toInt(y_Occurrence[q4]) | q4 : int(2..5)]), + 1 <= sum([toInt(x_Occurrence[q5]) | q5 : int(2..5)]), + and([x_Occurrence[q16] -> + or([q18 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q18] = q16 + | q18 : int(1..4)]) + | q16 : int(2..5)]), + and([q20 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q20]] + | q20 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> + y_ExplicitVarSizeWithFlags_Values[q6] < y_ExplicitVarSizeWithFlags_Values[q6 + 1] + | q6 : int(1..3)]), + and([y_ExplicitVarSizeWithFlags_Flags[q7] = false -> y_ExplicitVarSizeWithFlags_Values[q7] = 2 | q7 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q8 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q8] | q8 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q9]) | q9 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q12] -> y_Occurrence[y_ExplicitVarSizeWithFlags_Values[q12]] + | q12 : int(1..4)]), + and([y_Occurrence[q13] -> + or([y_ExplicitVarSizeWithFlags_Flags[q15] /\ y_ExplicitVarSizeWithFlags_Values[q15] = q13 | q15 : int(1..4)]) + | q13 : int(2..5)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_3_1_2_1-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_3_1_2_1-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_1_2_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_3_1_2_1-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_3_1_2_1-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_1_2_1-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_3_1_2_1.eprime b/tests/exhaustive/basic/set09/expected/model_3_1_2_1.eprime new file mode 100644 index 0000000000..5fb49b3743 --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_1_2_1.eprime @@ -0,0 +1,32 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +find y_Occurrence: matrix indexed by [int(2..5)] of bool +branching on + [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, y_Occurrence] +such that + and([q17 <= x_ExplicitVarSizeWithMarker_Marker /\ y_Occurrence[j] -> x_ExplicitVarSizeWithMarker_Values[q17] + 2 = j + | q17 : int(1..4), j : int(2..5)]), + and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] + | q1 : int(1..3)]), + and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 2 | q2 : int(1..4)]), + 1 <= x_ExplicitVarSizeWithMarker_Marker, + 1 <= sum([toInt(y_Occurrence[q4]) | q4 : int(2..5)]), + and([x_ExplicitVarSizeWithDummy[q5] < x_ExplicitVarSizeWithDummy[q5 + 1] \/ x_ExplicitVarSizeWithDummy[q5] = 6 + | q5 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q6] = 6 -> x_ExplicitVarSizeWithDummy[q6 + 1] = 6 | q6 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q7] != 6) | q7 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q10] != 6 -> + or([q12 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q12] = x_ExplicitVarSizeWithDummy[q10] + | q12 : int(1..4)]) + | q10 : int(1..4)]), + and([q14 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithDummy[q16] != 6 /\ + x_ExplicitVarSizeWithDummy[q16] = x_ExplicitVarSizeWithMarker_Values[q14] + | q16 : int(1..4)]) + | q14 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_3_1_2_2-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_3_1_2_2-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_1_2_2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_3_1_2_2-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_3_1_2_2-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_1_2_2-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_3_1_2_2.eprime b/tests/exhaustive/basic/set09/expected/model_3_1_2_2.eprime new file mode 100644 index 0000000000..76e803c650 --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_1_2_2.eprime @@ -0,0 +1,42 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +find y_Occurrence: matrix indexed by [int(2..5)] of bool +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +branching on + [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, + y_ExplicitVarSizeWithDummy, y_Occurrence] +such that + and([q26 <= x_ExplicitVarSizeWithMarker_Marker /\ y_Occurrence[j] -> x_ExplicitVarSizeWithMarker_Values[q26] + 2 = j + | q26 : int(1..4), j : int(2..5)]), + and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] + | q1 : int(1..3)]), + and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 2 | q2 : int(1..4)]), + 1 <= x_ExplicitVarSizeWithMarker_Marker, + 1 <= sum([toInt(y_Occurrence[q4]) | q4 : int(2..5)]), + and([x_ExplicitVarSizeWithDummy[q5] < x_ExplicitVarSizeWithDummy[q5 + 1] \/ x_ExplicitVarSizeWithDummy[q5] = 6 + | q5 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q6] = 6 -> x_ExplicitVarSizeWithDummy[q6 + 1] = 6 | q6 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q7] != 6) | q7 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q10] != 6 -> + or([q12 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q12] = x_ExplicitVarSizeWithDummy[q10] + | q12 : int(1..4)]) + | q10 : int(1..4)]), + and([q14 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithDummy[q16] != 6 /\ + x_ExplicitVarSizeWithDummy[q16] = x_ExplicitVarSizeWithMarker_Values[q14] + | q16 : int(1..4)]) + | q14 : int(1..4)]), + and([y_ExplicitVarSizeWithDummy[q17] < y_ExplicitVarSizeWithDummy[q17 + 1] \/ y_ExplicitVarSizeWithDummy[q17] = 6 + | q17 : int(1..3)]), + and([y_ExplicitVarSizeWithDummy[q18] = 6 -> y_ExplicitVarSizeWithDummy[q18 + 1] = 6 | q18 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q19] != 6) | q19 : int(1..4)]), + and([y_ExplicitVarSizeWithDummy[q22] != 6 -> y_Occurrence[y_ExplicitVarSizeWithDummy[q22]] | q22 : int(1..4)]), + and([y_Occurrence[q23] -> + or([y_ExplicitVarSizeWithDummy[q25] != 6 /\ y_ExplicitVarSizeWithDummy[q25] = q23 | q25 : int(1..4)]) + | q23 : int(2..5)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_3_1_2_3-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_3_1_2_3-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_1_2_3-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_3_1_2_3-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_3_1_2_3-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_1_2_3-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_3_1_2_3.eprime b/tests/exhaustive/basic/set09/expected/model_3_1_2_3.eprime new file mode 100644 index 0000000000..8f44fada43 --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_1_2_3.eprime @@ -0,0 +1,46 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +find y_Occurrence: matrix indexed by [int(2..5)] of bool +find y_ExplicitVarSizeWithMarker_Marker: int(0..4) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +branching on + [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, + y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values, y_Occurrence] +such that + and([q25 <= x_ExplicitVarSizeWithMarker_Marker /\ y_Occurrence[j] -> x_ExplicitVarSizeWithMarker_Values[q25] + 2 = j + | q25 : int(1..4), j : int(2..5)]), + and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] + | q1 : int(1..3)]), + and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 2 | q2 : int(1..4)]), + 1 <= x_ExplicitVarSizeWithMarker_Marker, + 1 <= sum([toInt(y_Occurrence[q4]) | q4 : int(2..5)]), + and([x_ExplicitVarSizeWithDummy[q5] < x_ExplicitVarSizeWithDummy[q5 + 1] \/ x_ExplicitVarSizeWithDummy[q5] = 6 + | q5 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q6] = 6 -> x_ExplicitVarSizeWithDummy[q6 + 1] = 6 | q6 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q7] != 6) | q7 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q10] != 6 -> + or([q12 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q12] = x_ExplicitVarSizeWithDummy[q10] + | q12 : int(1..4)]) + | q10 : int(1..4)]), + and([q14 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithDummy[q16] != 6 /\ + x_ExplicitVarSizeWithDummy[q16] = x_ExplicitVarSizeWithMarker_Values[q14] + | q16 : int(1..4)]) + | q14 : int(1..4)]), + and([q17 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> + y_ExplicitVarSizeWithMarker_Values[q17] < y_ExplicitVarSizeWithMarker_Values[q17 + 1] + | q17 : int(1..3)]), + and([q18 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q18] = 2 | q18 : int(1..4)]), + 1 <= y_ExplicitVarSizeWithMarker_Marker, + and([q21 <= y_ExplicitVarSizeWithMarker_Marker -> y_Occurrence[y_ExplicitVarSizeWithMarker_Values[q21]] + | q21 : int(1..4)]), + and([y_Occurrence[q22] -> + or([q24 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[q24] = q22 + | q24 : int(1..4)]) + | q22 : int(2..5)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_3_1_2_4-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_3_1_2_4-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_1_2_4-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_3_1_2_4-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_3_1_2_4-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_1_2_4-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_3_1_2_4.eprime b/tests/exhaustive/basic/set09/expected/model_3_1_2_4.eprime new file mode 100644 index 0000000000..228e19fb6b --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_1_2_4.eprime @@ -0,0 +1,47 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +find y_Occurrence: matrix indexed by [int(2..5)] of bool +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +branching on + [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, + y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values, y_Occurrence] +such that + and([q27 <= x_ExplicitVarSizeWithMarker_Marker /\ y_Occurrence[j] -> x_ExplicitVarSizeWithMarker_Values[q27] + 2 = j + | q27 : int(1..4), j : int(2..5)]), + and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] + | q1 : int(1..3)]), + and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 2 | q2 : int(1..4)]), + 1 <= x_ExplicitVarSizeWithMarker_Marker, + 1 <= sum([toInt(y_Occurrence[q4]) | q4 : int(2..5)]), + and([x_ExplicitVarSizeWithDummy[q5] < x_ExplicitVarSizeWithDummy[q5 + 1] \/ x_ExplicitVarSizeWithDummy[q5] = 6 + | q5 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q6] = 6 -> x_ExplicitVarSizeWithDummy[q6 + 1] = 6 | q6 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q7] != 6) | q7 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q10] != 6 -> + or([q12 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q12] = x_ExplicitVarSizeWithDummy[q10] + | q12 : int(1..4)]) + | q10 : int(1..4)]), + and([q14 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithDummy[q16] != 6 /\ + x_ExplicitVarSizeWithDummy[q16] = x_ExplicitVarSizeWithMarker_Values[q14] + | q16 : int(1..4)]) + | q14 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q17 + 1] -> + y_ExplicitVarSizeWithFlags_Values[q17] < y_ExplicitVarSizeWithFlags_Values[q17 + 1] + | q17 : int(1..3)]), + and([y_ExplicitVarSizeWithFlags_Flags[q18] = false -> y_ExplicitVarSizeWithFlags_Values[q18] = 2 + | q18 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q19 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q19] | q19 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q20]) | q20 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q23] -> y_Occurrence[y_ExplicitVarSizeWithFlags_Values[q23]] + | q23 : int(1..4)]), + and([y_Occurrence[q24] -> + or([y_ExplicitVarSizeWithFlags_Flags[q26] /\ y_ExplicitVarSizeWithFlags_Values[q26] = q24 | q26 : int(1..4)]) + | q24 : int(2..5)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_3_1_3_1-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_3_1_3_1-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_1_3_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_3_1_3_1-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_3_1_3_1-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_1_3_1-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_3_1_3_1.eprime b/tests/exhaustive/basic/set09/expected/model_3_1_3_1.eprime new file mode 100644 index 0000000000..1b5ab3050f --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_1_3_1.eprime @@ -0,0 +1,16 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_Occurrence: matrix indexed by [int(2..5)] of bool +branching on [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, y_Occurrence] +such that + and([q5 <= x_ExplicitVarSizeWithMarker_Marker /\ y_Occurrence[j] -> x_ExplicitVarSizeWithMarker_Values[q5] + 2 = j + | q5 : int(1..4), j : int(2..5)]), + and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] + | q1 : int(1..3)]), + and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 2 | q2 : int(1..4)]), + 1 <= x_ExplicitVarSizeWithMarker_Marker, + 1 <= sum([toInt(y_Occurrence[q4]) | q4 : int(2..5)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_3_1_3_2-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_3_1_3_2-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_1_3_2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_3_1_3_2-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_3_1_3_2-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_1_3_2-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_3_1_3_2.eprime b/tests/exhaustive/basic/set09/expected/model_3_1_3_2.eprime new file mode 100644 index 0000000000..67c1711a50 --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_1_3_2.eprime @@ -0,0 +1,26 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_Occurrence: matrix indexed by [int(2..5)] of bool +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +branching on + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithDummy, y_Occurrence] +such that + and([q14 <= x_ExplicitVarSizeWithMarker_Marker /\ y_Occurrence[j] -> x_ExplicitVarSizeWithMarker_Values[q14] + 2 = j + | q14 : int(1..4), j : int(2..5)]), + and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] + | q1 : int(1..3)]), + and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 2 | q2 : int(1..4)]), + 1 <= x_ExplicitVarSizeWithMarker_Marker, + 1 <= sum([toInt(y_Occurrence[q4]) | q4 : int(2..5)]), + and([y_ExplicitVarSizeWithDummy[q5] < y_ExplicitVarSizeWithDummy[q5 + 1] \/ y_ExplicitVarSizeWithDummy[q5] = 6 + | q5 : int(1..3)]), + and([y_ExplicitVarSizeWithDummy[q6] = 6 -> y_ExplicitVarSizeWithDummy[q6 + 1] = 6 | q6 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q7] != 6) | q7 : int(1..4)]), + and([y_ExplicitVarSizeWithDummy[q10] != 6 -> y_Occurrence[y_ExplicitVarSizeWithDummy[q10]] | q10 : int(1..4)]), + and([y_Occurrence[q11] -> + or([y_ExplicitVarSizeWithDummy[q13] != 6 /\ y_ExplicitVarSizeWithDummy[q13] = q11 | q13 : int(1..4)]) + | q11 : int(2..5)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_3_1_3_3-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_3_1_3_3-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_1_3_3-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_3_1_3_3-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_3_1_3_3-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_1_3_3-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_3_1_3_3.eprime b/tests/exhaustive/basic/set09/expected/model_3_1_3_3.eprime new file mode 100644 index 0000000000..ae76323065 --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_1_3_3.eprime @@ -0,0 +1,31 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_Occurrence: matrix indexed by [int(2..5)] of bool +find y_ExplicitVarSizeWithMarker_Marker: int(0..4) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +branching on + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithMarker_Marker, + y_ExplicitVarSizeWithMarker_Values, y_Occurrence] +such that + and([q13 <= x_ExplicitVarSizeWithMarker_Marker /\ y_Occurrence[j] -> x_ExplicitVarSizeWithMarker_Values[q13] + 2 = j + | q13 : int(1..4), j : int(2..5)]), + and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] + | q1 : int(1..3)]), + and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 2 | q2 : int(1..4)]), + 1 <= x_ExplicitVarSizeWithMarker_Marker, + 1 <= sum([toInt(y_Occurrence[q4]) | q4 : int(2..5)]), + and([q5 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> + y_ExplicitVarSizeWithMarker_Values[q5] < y_ExplicitVarSizeWithMarker_Values[q5 + 1] + | q5 : int(1..3)]), + and([q6 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q6] = 2 | q6 : int(1..4)]), + 1 <= y_ExplicitVarSizeWithMarker_Marker, + and([q9 <= y_ExplicitVarSizeWithMarker_Marker -> y_Occurrence[y_ExplicitVarSizeWithMarker_Values[q9]] + | q9 : int(1..4)]), + and([y_Occurrence[q10] -> + or([q12 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[q12] = q10 + | q12 : int(1..4)]) + | q10 : int(2..5)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_3_1_3_4-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_3_1_3_4-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_1_3_4-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_3_1_3_4-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_3_1_3_4-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_1_3_4-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_3_1_3_4.eprime b/tests/exhaustive/basic/set09/expected/model_3_1_3_4.eprime new file mode 100644 index 0000000000..c222d89b6a --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_1_3_4.eprime @@ -0,0 +1,31 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_Occurrence: matrix indexed by [int(2..5)] of bool +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +branching on + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithFlags_Flags, + y_ExplicitVarSizeWithFlags_Values, y_Occurrence] +such that + and([q15 <= x_ExplicitVarSizeWithMarker_Marker /\ y_Occurrence[j] -> x_ExplicitVarSizeWithMarker_Values[q15] + 2 = j + | q15 : int(1..4), j : int(2..5)]), + and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] + | q1 : int(1..3)]), + and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 2 | q2 : int(1..4)]), + 1 <= x_ExplicitVarSizeWithMarker_Marker, + 1 <= sum([toInt(y_Occurrence[q4]) | q4 : int(2..5)]), + and([y_ExplicitVarSizeWithFlags_Flags[q5 + 1] -> + y_ExplicitVarSizeWithFlags_Values[q5] < y_ExplicitVarSizeWithFlags_Values[q5 + 1] + | q5 : int(1..3)]), + and([y_ExplicitVarSizeWithFlags_Flags[q6] = false -> y_ExplicitVarSizeWithFlags_Values[q6] = 2 | q6 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q7] | q7 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q8]) | q8 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q11] -> y_Occurrence[y_ExplicitVarSizeWithFlags_Values[q11]] + | q11 : int(1..4)]), + and([y_Occurrence[q12] -> + or([y_ExplicitVarSizeWithFlags_Flags[q14] /\ y_ExplicitVarSizeWithFlags_Values[q14] = q12 | q14 : int(1..4)]) + | q12 : int(2..5)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_3_1_4_1-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_3_1_4_1-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_1_4_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_3_1_4_1-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_3_1_4_1-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_1_4_1-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_3_1_4_1.eprime b/tests/exhaustive/basic/set09/expected/model_3_1_4_1.eprime new file mode 100644 index 0000000000..d55d8473f1 --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_1_4_1.eprime @@ -0,0 +1,36 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_Occurrence: matrix indexed by [int(2..5)] of bool +branching on + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithMarker_Marker, + x_ExplicitVarSizeWithMarker_Values, y_Occurrence] +such that + and([q18 <= x_ExplicitVarSizeWithMarker_Marker /\ y_Occurrence[j] -> x_ExplicitVarSizeWithMarker_Values[q18] + 2 = j + | q18 : int(1..4), j : int(2..5)]), + and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] + | q1 : int(1..3)]), + and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 2 | q2 : int(1..4)]), + 1 <= x_ExplicitVarSizeWithMarker_Marker, + 1 <= sum([toInt(y_Occurrence[q4]) | q4 : int(2..5)]), + and([x_ExplicitVarSizeWithFlags_Flags[q5 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q5] < x_ExplicitVarSizeWithFlags_Values[q5 + 1] + | q5 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q6] = false -> x_ExplicitVarSizeWithFlags_Values[q6] = 2 | q6 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q7] | q7 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q8]) | q8 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q11] -> + or([q13 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q13] = x_ExplicitVarSizeWithFlags_Values[q11] + | q13 : int(1..4)]) + | q11 : int(1..4)]), + and([q15 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithFlags_Flags[q17] /\ + x_ExplicitVarSizeWithFlags_Values[q17] = x_ExplicitVarSizeWithMarker_Values[q15] + | q17 : int(1..4)]) + | q15 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_3_1_4_2-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_3_1_4_2-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_1_4_2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_3_1_4_2-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_3_1_4_2-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_1_4_2-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_3_1_4_2.eprime b/tests/exhaustive/basic/set09/expected/model_3_1_4_2.eprime new file mode 100644 index 0000000000..4db7080ac5 --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_1_4_2.eprime @@ -0,0 +1,45 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_Occurrence: matrix indexed by [int(2..5)] of bool +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +branching on + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithMarker_Marker, + x_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithDummy, y_Occurrence] +such that + and([q27 <= x_ExplicitVarSizeWithMarker_Marker /\ y_Occurrence[j] -> x_ExplicitVarSizeWithMarker_Values[q27] + 2 = j + | q27 : int(1..4), j : int(2..5)]), + and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] + | q1 : int(1..3)]), + and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 2 | q2 : int(1..4)]), + 1 <= x_ExplicitVarSizeWithMarker_Marker, + 1 <= sum([toInt(y_Occurrence[q4]) | q4 : int(2..5)]), + and([x_ExplicitVarSizeWithFlags_Flags[q5 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q5] < x_ExplicitVarSizeWithFlags_Values[q5 + 1] + | q5 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q6] = false -> x_ExplicitVarSizeWithFlags_Values[q6] = 2 | q6 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q7] | q7 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q8]) | q8 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q11] -> + or([q13 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q13] = x_ExplicitVarSizeWithFlags_Values[q11] + | q13 : int(1..4)]) + | q11 : int(1..4)]), + and([q15 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithFlags_Flags[q17] /\ + x_ExplicitVarSizeWithFlags_Values[q17] = x_ExplicitVarSizeWithMarker_Values[q15] + | q17 : int(1..4)]) + | q15 : int(1..4)]), + and([y_ExplicitVarSizeWithDummy[q18] < y_ExplicitVarSizeWithDummy[q18 + 1] \/ y_ExplicitVarSizeWithDummy[q18] = 6 + | q18 : int(1..3)]), + and([y_ExplicitVarSizeWithDummy[q19] = 6 -> y_ExplicitVarSizeWithDummy[q19 + 1] = 6 | q19 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q20] != 6) | q20 : int(1..4)]), + and([y_ExplicitVarSizeWithDummy[q23] != 6 -> y_Occurrence[y_ExplicitVarSizeWithDummy[q23]] | q23 : int(1..4)]), + and([y_Occurrence[q24] -> + or([y_ExplicitVarSizeWithDummy[q26] != 6 /\ y_ExplicitVarSizeWithDummy[q26] = q24 | q26 : int(1..4)]) + | q24 : int(2..5)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_3_1_4_3-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_3_1_4_3-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_1_4_3-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_3_1_4_3-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_3_1_4_3-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_1_4_3-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_3_1_4_3.eprime b/tests/exhaustive/basic/set09/expected/model_3_1_4_3.eprime new file mode 100644 index 0000000000..cc9cb3a8fe --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_1_4_3.eprime @@ -0,0 +1,50 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_Occurrence: matrix indexed by [int(2..5)] of bool +find y_ExplicitVarSizeWithMarker_Marker: int(0..4) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +branching on + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithMarker_Marker, + x_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values, + y_Occurrence] +such that + and([q26 <= x_ExplicitVarSizeWithMarker_Marker /\ y_Occurrence[j] -> x_ExplicitVarSizeWithMarker_Values[q26] + 2 = j + | q26 : int(1..4), j : int(2..5)]), + and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] + | q1 : int(1..3)]), + and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 2 | q2 : int(1..4)]), + 1 <= x_ExplicitVarSizeWithMarker_Marker, + 1 <= sum([toInt(y_Occurrence[q4]) | q4 : int(2..5)]), + and([x_ExplicitVarSizeWithFlags_Flags[q5 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q5] < x_ExplicitVarSizeWithFlags_Values[q5 + 1] + | q5 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q6] = false -> x_ExplicitVarSizeWithFlags_Values[q6] = 2 | q6 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q7] | q7 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q8]) | q8 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q11] -> + or([q13 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q13] = x_ExplicitVarSizeWithFlags_Values[q11] + | q13 : int(1..4)]) + | q11 : int(1..4)]), + and([q15 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithFlags_Flags[q17] /\ + x_ExplicitVarSizeWithFlags_Values[q17] = x_ExplicitVarSizeWithMarker_Values[q15] + | q17 : int(1..4)]) + | q15 : int(1..4)]), + and([q18 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> + y_ExplicitVarSizeWithMarker_Values[q18] < y_ExplicitVarSizeWithMarker_Values[q18 + 1] + | q18 : int(1..3)]), + and([q19 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q19] = 2 | q19 : int(1..4)]), + 1 <= y_ExplicitVarSizeWithMarker_Marker, + and([q22 <= y_ExplicitVarSizeWithMarker_Marker -> y_Occurrence[y_ExplicitVarSizeWithMarker_Values[q22]] + | q22 : int(1..4)]), + and([y_Occurrence[q23] -> + or([q25 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[q25] = q23 + | q25 : int(1..4)]) + | q23 : int(2..5)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_3_1_4_4-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_3_1_4_4-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_1_4_4-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_3_1_4_4-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_3_1_4_4-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_1_4_4-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_3_1_4_4.eprime b/tests/exhaustive/basic/set09/expected/model_3_1_4_4.eprime new file mode 100644 index 0000000000..286649e6b5 --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_1_4_4.eprime @@ -0,0 +1,51 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_Occurrence: matrix indexed by [int(2..5)] of bool +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +branching on + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithMarker_Marker, + x_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values, + y_Occurrence] +such that + and([q28 <= x_ExplicitVarSizeWithMarker_Marker /\ y_Occurrence[j] -> x_ExplicitVarSizeWithMarker_Values[q28] + 2 = j + | q28 : int(1..4), j : int(2..5)]), + and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] + | q1 : int(1..3)]), + and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 2 | q2 : int(1..4)]), + 1 <= x_ExplicitVarSizeWithMarker_Marker, + 1 <= sum([toInt(y_Occurrence[q4]) | q4 : int(2..5)]), + and([x_ExplicitVarSizeWithFlags_Flags[q5 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q5] < x_ExplicitVarSizeWithFlags_Values[q5 + 1] + | q5 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q6] = false -> x_ExplicitVarSizeWithFlags_Values[q6] = 2 | q6 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q7] | q7 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q8]) | q8 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q11] -> + or([q13 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q13] = x_ExplicitVarSizeWithFlags_Values[q11] + | q13 : int(1..4)]) + | q11 : int(1..4)]), + and([q15 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithFlags_Flags[q17] /\ + x_ExplicitVarSizeWithFlags_Values[q17] = x_ExplicitVarSizeWithMarker_Values[q15] + | q17 : int(1..4)]) + | q15 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q18 + 1] -> + y_ExplicitVarSizeWithFlags_Values[q18] < y_ExplicitVarSizeWithFlags_Values[q18 + 1] + | q18 : int(1..3)]), + and([y_ExplicitVarSizeWithFlags_Flags[q19] = false -> y_ExplicitVarSizeWithFlags_Values[q19] = 2 + | q19 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q20 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q20] | q20 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q21]) | q21 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q24] -> y_Occurrence[y_ExplicitVarSizeWithFlags_Values[q24]] + | q24 : int(1..4)]), + and([y_Occurrence[q25] -> + or([y_ExplicitVarSizeWithFlags_Flags[q27] /\ y_ExplicitVarSizeWithFlags_Values[q27] = q25 | q27 : int(1..4)]) + | q25 : int(2..5)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_3_2_1_1-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_3_2_1_1-solution000001.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_2_1_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_3_2_1_1-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_3_2_1_1-solution000002.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_2_1_1-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_3_2_1_1.eprime b/tests/exhaustive/basic/set09/expected/model_3_2_1_1.eprime new file mode 100644 index 0000000000..3478aef4b6 --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_2_1_1.eprime @@ -0,0 +1,36 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +find x_Occurrence: matrix indexed by [int(2..5)] of bool +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +find y_Occurrence: matrix indexed by [int(2..5)] of bool +branching on + [x_Occurrence, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, y_Occurrence, + y_ExplicitVarSizeWithDummy] +such that + and([q15 <= x_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithDummy[q16] != 6 -> + x_ExplicitVarSizeWithMarker_Values[q15] + 2 = y_ExplicitVarSizeWithDummy[q16] + | q15 : int(1..4), q16 : int(1..4)]), + and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] + | q1 : int(1..3)]), + and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 2 | q2 : int(1..4)]), + 1 <= x_ExplicitVarSizeWithMarker_Marker, + and([y_ExplicitVarSizeWithDummy[q4] < y_ExplicitVarSizeWithDummy[q4 + 1] \/ y_ExplicitVarSizeWithDummy[q4] = 6 + | q4 : int(1..3)]), + and([y_ExplicitVarSizeWithDummy[q5] = 6 -> y_ExplicitVarSizeWithDummy[q5 + 1] = 6 | q5 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q6] != 6) | q6 : int(1..4)]), + 1 <= sum([toInt(x_Occurrence[q8]) | q8 : int(2..5)]), + and([x_Occurrence[q17] -> + or([q19 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q19] = q17 + | q19 : int(1..4)]) + | q17 : int(2..5)]), + and([q21 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q21]] + | q21 : int(1..4)]), + 1 <= sum([toInt(y_Occurrence[q9]) | q9 : int(2..5)]), + and([y_Occurrence[q10] -> + or([y_ExplicitVarSizeWithDummy[q12] != 6 /\ y_ExplicitVarSizeWithDummy[q12] = q10 | q12 : int(1..4)]) + | q10 : int(2..5)]), + and([y_ExplicitVarSizeWithDummy[q14] != 6 -> y_Occurrence[y_ExplicitVarSizeWithDummy[q14]] | q14 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_3_2_1_2-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_3_2_1_2-solution000001.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_2_1_2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_3_2_1_2-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_3_2_1_2-solution000002.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_2_1_2-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_3_2_1_2.eprime b/tests/exhaustive/basic/set09/expected/model_3_2_1_2.eprime new file mode 100644 index 0000000000..fd0da5899f --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_2_1_2.eprime @@ -0,0 +1,29 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +find x_Occurrence: matrix indexed by [int(2..5)] of bool +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +branching on + [x_Occurrence, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithDummy] +such that + and([q14 <= x_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithDummy[q15] != 6 -> + x_ExplicitVarSizeWithMarker_Values[q14] + 2 = y_ExplicitVarSizeWithDummy[q15] + | q14 : int(1..4), q15 : int(1..4)]), + and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] + | q1 : int(1..3)]), + and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 2 | q2 : int(1..4)]), + 1 <= x_ExplicitVarSizeWithMarker_Marker, + and([y_ExplicitVarSizeWithDummy[q4] < y_ExplicitVarSizeWithDummy[q4 + 1] \/ y_ExplicitVarSizeWithDummy[q4] = 6 + | q4 : int(1..3)]), + and([y_ExplicitVarSizeWithDummy[q5] = 6 -> y_ExplicitVarSizeWithDummy[q5 + 1] = 6 | q5 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q6] != 6) | q6 : int(1..4)]), + 1 <= sum([toInt(x_Occurrence[q8]) | q8 : int(2..5)]), + and([x_Occurrence[q9] -> + or([q11 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q11] = q9 + | q11 : int(1..4)]) + | q9 : int(2..5)]), + and([q13 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q13]] + | q13 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_3_2_1_3-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_3_2_1_3-solution000001.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_2_1_3-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_3_2_1_3-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_3_2_1_3-solution000002.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_2_1_3-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_3_2_1_3.eprime b/tests/exhaustive/basic/set09/expected/model_3_2_1_3.eprime new file mode 100644 index 0000000000..bbd02c7005 --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_2_1_3.eprime @@ -0,0 +1,47 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +find x_Occurrence: matrix indexed by [int(2..5)] of bool +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +find y_ExplicitVarSizeWithMarker_Marker: int(0..4) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +branching on + [x_Occurrence, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, + y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithDummy] +such that + and([q25 <= x_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithDummy[q26] != 6 -> + x_ExplicitVarSizeWithMarker_Values[q25] + 2 = y_ExplicitVarSizeWithDummy[q26] + | q25 : int(1..4), q26 : int(1..4)]), + and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] + | q1 : int(1..3)]), + and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 2 | q2 : int(1..4)]), + 1 <= x_ExplicitVarSizeWithMarker_Marker, + and([y_ExplicitVarSizeWithDummy[q4] < y_ExplicitVarSizeWithDummy[q4 + 1] \/ y_ExplicitVarSizeWithDummy[q4] = 6 + | q4 : int(1..3)]), + and([y_ExplicitVarSizeWithDummy[q5] = 6 -> y_ExplicitVarSizeWithDummy[q5 + 1] = 6 | q5 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q6] != 6) | q6 : int(1..4)]), + 1 <= sum([toInt(x_Occurrence[q8]) | q8 : int(2..5)]), + and([x_Occurrence[q20] -> + or([q22 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q22] = q20 + | q22 : int(1..4)]) + | q20 : int(2..5)]), + and([q24 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q24]] + | q24 : int(1..4)]), + and([q9 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> + y_ExplicitVarSizeWithMarker_Values[q9] < y_ExplicitVarSizeWithMarker_Values[q9 + 1] + | q9 : int(1..3)]), + and([q10 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q10] = 2 | q10 : int(1..4)]), + 1 <= y_ExplicitVarSizeWithMarker_Marker, + and([q13 <= y_ExplicitVarSizeWithMarker_Marker -> + or([y_ExplicitVarSizeWithDummy[q15] != 6 /\ + y_ExplicitVarSizeWithDummy[q15] = y_ExplicitVarSizeWithMarker_Values[q13] + | q15 : int(1..4)]) + | q13 : int(1..4)]), + and([y_ExplicitVarSizeWithDummy[q17] != 6 -> + or([q19 <= y_ExplicitVarSizeWithMarker_Marker /\ + y_ExplicitVarSizeWithMarker_Values[q19] = y_ExplicitVarSizeWithDummy[q17] + | q19 : int(1..4)]) + | q17 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_3_2_1_4-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_3_2_1_4-solution000001.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_2_1_4-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_3_2_1_4-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_3_2_1_4-solution000002.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_2_1_4-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_3_2_1_4.eprime b/tests/exhaustive/basic/set09/expected/model_3_2_1_4.eprime new file mode 100644 index 0000000000..f53ee8d570 --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_2_1_4.eprime @@ -0,0 +1,49 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +find x_Occurrence: matrix indexed by [int(2..5)] of bool +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +branching on + [x_Occurrence, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, + y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithDummy] +such that + and([q27 <= x_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithDummy[q28] != 6 -> + x_ExplicitVarSizeWithMarker_Values[q27] + 2 = y_ExplicitVarSizeWithDummy[q28] + | q27 : int(1..4), q28 : int(1..4)]), + and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] + | q1 : int(1..3)]), + and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 2 | q2 : int(1..4)]), + 1 <= x_ExplicitVarSizeWithMarker_Marker, + and([y_ExplicitVarSizeWithDummy[q4] < y_ExplicitVarSizeWithDummy[q4 + 1] \/ y_ExplicitVarSizeWithDummy[q4] = 6 + | q4 : int(1..3)]), + and([y_ExplicitVarSizeWithDummy[q5] = 6 -> y_ExplicitVarSizeWithDummy[q5 + 1] = 6 | q5 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q6] != 6) | q6 : int(1..4)]), + 1 <= sum([toInt(x_Occurrence[q8]) | q8 : int(2..5)]), + and([x_Occurrence[q22] -> + or([q24 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q24] = q22 + | q24 : int(1..4)]) + | q22 : int(2..5)]), + and([q26 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q26]] + | q26 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q9 + 1] -> + y_ExplicitVarSizeWithFlags_Values[q9] < y_ExplicitVarSizeWithFlags_Values[q9 + 1] + | q9 : int(1..3)]), + and([y_ExplicitVarSizeWithFlags_Flags[q10] = false -> y_ExplicitVarSizeWithFlags_Values[q10] = 2 + | q10 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q11 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q11] | q11 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q12]) | q12 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q15] -> + or([y_ExplicitVarSizeWithDummy[q17] != 6 /\ + y_ExplicitVarSizeWithDummy[q17] = y_ExplicitVarSizeWithFlags_Values[q15] + | q17 : int(1..4)]) + | q15 : int(1..4)]), + and([y_ExplicitVarSizeWithDummy[q19] != 6 -> + or([y_ExplicitVarSizeWithFlags_Flags[q21] /\ + y_ExplicitVarSizeWithFlags_Values[q21] = y_ExplicitVarSizeWithDummy[q19] + | q21 : int(1..4)]) + | q19 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_3_2_2_1-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_3_2_2_1-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_2_2_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_3_2_2_1-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_3_2_2_1-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_2_2_1-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_3_2_2_1.eprime b/tests/exhaustive/basic/set09/expected/model_3_2_2_1.eprime new file mode 100644 index 0000000000..6a169fe5a6 --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_2_2_1.eprime @@ -0,0 +1,43 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +find y_Occurrence: matrix indexed by [int(2..5)] of bool +branching on + [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, y_Occurrence, + y_ExplicitVarSizeWithDummy] +such that + and([q26 <= x_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithDummy[q27] != 6 -> + x_ExplicitVarSizeWithMarker_Values[q26] + 2 = y_ExplicitVarSizeWithDummy[q27] + | q26 : int(1..4), q27 : int(1..4)]), + and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] + | q1 : int(1..3)]), + and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 2 | q2 : int(1..4)]), + 1 <= x_ExplicitVarSizeWithMarker_Marker, + and([y_ExplicitVarSizeWithDummy[q4] < y_ExplicitVarSizeWithDummy[q4 + 1] \/ y_ExplicitVarSizeWithDummy[q4] = 6 + | q4 : int(1..3)]), + and([y_ExplicitVarSizeWithDummy[q5] = 6 -> y_ExplicitVarSizeWithDummy[q5 + 1] = 6 | q5 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q6] != 6) | q6 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q8] < x_ExplicitVarSizeWithDummy[q8 + 1] \/ x_ExplicitVarSizeWithDummy[q8] = 6 + | q8 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q9] = 6 -> x_ExplicitVarSizeWithDummy[q9 + 1] = 6 | q9 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q10] != 6) | q10 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q13] != 6 -> + or([q15 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q15] = x_ExplicitVarSizeWithDummy[q13] + | q15 : int(1..4)]) + | q13 : int(1..4)]), + and([q17 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithDummy[q19] != 6 /\ + x_ExplicitVarSizeWithDummy[q19] = x_ExplicitVarSizeWithMarker_Values[q17] + | q19 : int(1..4)]) + | q17 : int(1..4)]), + 1 <= sum([toInt(y_Occurrence[q20]) | q20 : int(2..5)]), + and([y_Occurrence[q21] -> + or([y_ExplicitVarSizeWithDummy[q23] != 6 /\ y_ExplicitVarSizeWithDummy[q23] = q21 | q23 : int(1..4)]) + | q21 : int(2..5)]), + and([y_ExplicitVarSizeWithDummy[q25] != 6 -> y_Occurrence[y_ExplicitVarSizeWithDummy[q25]] | q25 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_3_2_2_2-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_3_2_2_2-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_2_2_2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_3_2_2_2-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_3_2_2_2-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_2_2_2-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_3_2_2_2.eprime b/tests/exhaustive/basic/set09/expected/model_3_2_2_2.eprime new file mode 100644 index 0000000000..7f3fb2bd48 --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_2_2_2.eprime @@ -0,0 +1,37 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +branching on + [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, + y_ExplicitVarSizeWithDummy] +such that + and([q20 <= x_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithDummy[q21] != 6 -> + x_ExplicitVarSizeWithMarker_Values[q20] + 2 = y_ExplicitVarSizeWithDummy[q21] + | q20 : int(1..4), q21 : int(1..4)]), + and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] + | q1 : int(1..3)]), + and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 2 | q2 : int(1..4)]), + 1 <= x_ExplicitVarSizeWithMarker_Marker, + and([y_ExplicitVarSizeWithDummy[q4] < y_ExplicitVarSizeWithDummy[q4 + 1] \/ y_ExplicitVarSizeWithDummy[q4] = 6 + | q4 : int(1..3)]), + and([y_ExplicitVarSizeWithDummy[q5] = 6 -> y_ExplicitVarSizeWithDummy[q5 + 1] = 6 | q5 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q6] != 6) | q6 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q8] < x_ExplicitVarSizeWithDummy[q8 + 1] \/ x_ExplicitVarSizeWithDummy[q8] = 6 + | q8 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q9] = 6 -> x_ExplicitVarSizeWithDummy[q9 + 1] = 6 | q9 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q10] != 6) | q10 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q13] != 6 -> + or([q15 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q15] = x_ExplicitVarSizeWithDummy[q13] + | q15 : int(1..4)]) + | q13 : int(1..4)]), + and([q17 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithDummy[q19] != 6 /\ + x_ExplicitVarSizeWithDummy[q19] = x_ExplicitVarSizeWithMarker_Values[q17] + | q19 : int(1..4)]) + | q17 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_3_2_2_3-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_3_2_2_3-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_2_2_3-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_3_2_2_3-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_3_2_2_3-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_2_2_3-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_3_2_2_3.eprime b/tests/exhaustive/basic/set09/expected/model_3_2_2_3.eprime new file mode 100644 index 0000000000..cc44894190 --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_2_2_3.eprime @@ -0,0 +1,54 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +find y_ExplicitVarSizeWithMarker_Marker: int(0..4) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +branching on + [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, + y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithDummy] +such that + and([q31 <= x_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithDummy[q32] != 6 -> + x_ExplicitVarSizeWithMarker_Values[q31] + 2 = y_ExplicitVarSizeWithDummy[q32] + | q31 : int(1..4), q32 : int(1..4)]), + and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] + | q1 : int(1..3)]), + and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 2 | q2 : int(1..4)]), + 1 <= x_ExplicitVarSizeWithMarker_Marker, + and([y_ExplicitVarSizeWithDummy[q4] < y_ExplicitVarSizeWithDummy[q4 + 1] \/ y_ExplicitVarSizeWithDummy[q4] = 6 + | q4 : int(1..3)]), + and([y_ExplicitVarSizeWithDummy[q5] = 6 -> y_ExplicitVarSizeWithDummy[q5 + 1] = 6 | q5 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q6] != 6) | q6 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q8] < x_ExplicitVarSizeWithDummy[q8 + 1] \/ x_ExplicitVarSizeWithDummy[q8] = 6 + | q8 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q9] = 6 -> x_ExplicitVarSizeWithDummy[q9 + 1] = 6 | q9 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q10] != 6) | q10 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q13] != 6 -> + or([q15 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q15] = x_ExplicitVarSizeWithDummy[q13] + | q15 : int(1..4)]) + | q13 : int(1..4)]), + and([q17 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithDummy[q19] != 6 /\ + x_ExplicitVarSizeWithDummy[q19] = x_ExplicitVarSizeWithMarker_Values[q17] + | q19 : int(1..4)]) + | q17 : int(1..4)]), + and([q20 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> + y_ExplicitVarSizeWithMarker_Values[q20] < y_ExplicitVarSizeWithMarker_Values[q20 + 1] + | q20 : int(1..3)]), + and([q21 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q21] = 2 | q21 : int(1..4)]), + 1 <= y_ExplicitVarSizeWithMarker_Marker, + and([q24 <= y_ExplicitVarSizeWithMarker_Marker -> + or([y_ExplicitVarSizeWithDummy[q26] != 6 /\ + y_ExplicitVarSizeWithDummy[q26] = y_ExplicitVarSizeWithMarker_Values[q24] + | q26 : int(1..4)]) + | q24 : int(1..4)]), + and([y_ExplicitVarSizeWithDummy[q28] != 6 -> + or([q30 <= y_ExplicitVarSizeWithMarker_Marker /\ + y_ExplicitVarSizeWithMarker_Values[q30] = y_ExplicitVarSizeWithDummy[q28] + | q30 : int(1..4)]) + | q28 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_3_2_2_4-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_3_2_2_4-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_2_2_4-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_3_2_2_4-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_3_2_2_4-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_2_2_4-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_3_2_2_4.eprime b/tests/exhaustive/basic/set09/expected/model_3_2_2_4.eprime new file mode 100644 index 0000000000..c22f517453 --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_2_2_4.eprime @@ -0,0 +1,56 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +branching on + [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, + y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithDummy] +such that + and([q33 <= x_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithDummy[q34] != 6 -> + x_ExplicitVarSizeWithMarker_Values[q33] + 2 = y_ExplicitVarSizeWithDummy[q34] + | q33 : int(1..4), q34 : int(1..4)]), + and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] + | q1 : int(1..3)]), + and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 2 | q2 : int(1..4)]), + 1 <= x_ExplicitVarSizeWithMarker_Marker, + and([y_ExplicitVarSizeWithDummy[q4] < y_ExplicitVarSizeWithDummy[q4 + 1] \/ y_ExplicitVarSizeWithDummy[q4] = 6 + | q4 : int(1..3)]), + and([y_ExplicitVarSizeWithDummy[q5] = 6 -> y_ExplicitVarSizeWithDummy[q5 + 1] = 6 | q5 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q6] != 6) | q6 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q8] < x_ExplicitVarSizeWithDummy[q8 + 1] \/ x_ExplicitVarSizeWithDummy[q8] = 6 + | q8 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q9] = 6 -> x_ExplicitVarSizeWithDummy[q9 + 1] = 6 | q9 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q10] != 6) | q10 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q13] != 6 -> + or([q15 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q15] = x_ExplicitVarSizeWithDummy[q13] + | q15 : int(1..4)]) + | q13 : int(1..4)]), + and([q17 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithDummy[q19] != 6 /\ + x_ExplicitVarSizeWithDummy[q19] = x_ExplicitVarSizeWithMarker_Values[q17] + | q19 : int(1..4)]) + | q17 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q20 + 1] -> + y_ExplicitVarSizeWithFlags_Values[q20] < y_ExplicitVarSizeWithFlags_Values[q20 + 1] + | q20 : int(1..3)]), + and([y_ExplicitVarSizeWithFlags_Flags[q21] = false -> y_ExplicitVarSizeWithFlags_Values[q21] = 2 + | q21 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q22 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q22] | q22 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q23]) | q23 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q26] -> + or([y_ExplicitVarSizeWithDummy[q28] != 6 /\ + y_ExplicitVarSizeWithDummy[q28] = y_ExplicitVarSizeWithFlags_Values[q26] + | q28 : int(1..4)]) + | q26 : int(1..4)]), + and([y_ExplicitVarSizeWithDummy[q30] != 6 -> + or([y_ExplicitVarSizeWithFlags_Flags[q32] /\ + y_ExplicitVarSizeWithFlags_Values[q32] = y_ExplicitVarSizeWithDummy[q30] + | q32 : int(1..4)]) + | q30 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_3_2_3_1-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_3_2_3_1-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_2_3_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_3_2_3_1-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_3_2_3_1-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_2_3_1-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_3_2_3_1.eprime b/tests/exhaustive/basic/set09/expected/model_3_2_3_1.eprime new file mode 100644 index 0000000000..0059fed8b2 --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_2_3_1.eprime @@ -0,0 +1,27 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +find y_Occurrence: matrix indexed by [int(2..5)] of bool +branching on + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, y_Occurrence, y_ExplicitVarSizeWithDummy] +such that + and([q14 <= x_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithDummy[q15] != 6 -> + x_ExplicitVarSizeWithMarker_Values[q14] + 2 = y_ExplicitVarSizeWithDummy[q15] + | q14 : int(1..4), q15 : int(1..4)]), + and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] + | q1 : int(1..3)]), + and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 2 | q2 : int(1..4)]), + 1 <= x_ExplicitVarSizeWithMarker_Marker, + and([y_ExplicitVarSizeWithDummy[q4] < y_ExplicitVarSizeWithDummy[q4 + 1] \/ y_ExplicitVarSizeWithDummy[q4] = 6 + | q4 : int(1..3)]), + and([y_ExplicitVarSizeWithDummy[q5] = 6 -> y_ExplicitVarSizeWithDummy[q5 + 1] = 6 | q5 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q6] != 6) | q6 : int(1..4)]), + 1 <= sum([toInt(y_Occurrence[q8]) | q8 : int(2..5)]), + and([y_Occurrence[q9] -> + or([y_ExplicitVarSizeWithDummy[q11] != 6 /\ y_ExplicitVarSizeWithDummy[q11] = q9 | q11 : int(1..4)]) + | q9 : int(2..5)]), + and([y_ExplicitVarSizeWithDummy[q13] != 6 -> y_Occurrence[y_ExplicitVarSizeWithDummy[q13]] | q13 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_3_2_3_2-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_3_2_3_2-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_2_3_2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_3_2_3_2-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_3_2_3_2-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_2_3_2-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_3_2_3_2.eprime b/tests/exhaustive/basic/set09/expected/model_3_2_3_2.eprime new file mode 100644 index 0000000000..99499bc7b1 --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_2_3_2.eprime @@ -0,0 +1,20 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +branching on [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithDummy] +such that + and([q8 <= x_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithDummy[q9] != 6 -> + x_ExplicitVarSizeWithMarker_Values[q8] + 2 = y_ExplicitVarSizeWithDummy[q9] + | q8 : int(1..4), q9 : int(1..4)]), + and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] + | q1 : int(1..3)]), + and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 2 | q2 : int(1..4)]), + 1 <= x_ExplicitVarSizeWithMarker_Marker, + and([y_ExplicitVarSizeWithDummy[q4] < y_ExplicitVarSizeWithDummy[q4 + 1] \/ y_ExplicitVarSizeWithDummy[q4] = 6 + | q4 : int(1..3)]), + and([y_ExplicitVarSizeWithDummy[q5] = 6 -> y_ExplicitVarSizeWithDummy[q5 + 1] = 6 | q5 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q6] != 6) | q6 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_3_2_3_3-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_3_2_3_3-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_2_3_3-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_3_2_3_3-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_3_2_3_3-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_2_3_3-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_3_2_3_3.eprime b/tests/exhaustive/basic/set09/expected/model_3_2_3_3.eprime new file mode 100644 index 0000000000..45e304f746 --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_2_3_3.eprime @@ -0,0 +1,39 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +find y_ExplicitVarSizeWithMarker_Marker: int(0..4) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +branching on + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithMarker_Marker, + y_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithDummy] +such that + and([q19 <= x_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithDummy[q20] != 6 -> + x_ExplicitVarSizeWithMarker_Values[q19] + 2 = y_ExplicitVarSizeWithDummy[q20] + | q19 : int(1..4), q20 : int(1..4)]), + and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] + | q1 : int(1..3)]), + and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 2 | q2 : int(1..4)]), + 1 <= x_ExplicitVarSizeWithMarker_Marker, + and([y_ExplicitVarSizeWithDummy[q4] < y_ExplicitVarSizeWithDummy[q4 + 1] \/ y_ExplicitVarSizeWithDummy[q4] = 6 + | q4 : int(1..3)]), + and([y_ExplicitVarSizeWithDummy[q5] = 6 -> y_ExplicitVarSizeWithDummy[q5 + 1] = 6 | q5 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q6] != 6) | q6 : int(1..4)]), + and([q8 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> + y_ExplicitVarSizeWithMarker_Values[q8] < y_ExplicitVarSizeWithMarker_Values[q8 + 1] + | q8 : int(1..3)]), + and([q9 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q9] = 2 | q9 : int(1..4)]), + 1 <= y_ExplicitVarSizeWithMarker_Marker, + and([q12 <= y_ExplicitVarSizeWithMarker_Marker -> + or([y_ExplicitVarSizeWithDummy[q14] != 6 /\ + y_ExplicitVarSizeWithDummy[q14] = y_ExplicitVarSizeWithMarker_Values[q12] + | q14 : int(1..4)]) + | q12 : int(1..4)]), + and([y_ExplicitVarSizeWithDummy[q16] != 6 -> + or([q18 <= y_ExplicitVarSizeWithMarker_Marker /\ + y_ExplicitVarSizeWithMarker_Values[q18] = y_ExplicitVarSizeWithDummy[q16] + | q18 : int(1..4)]) + | q16 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_3_2_3_4-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_3_2_3_4-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_2_3_4-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_3_2_3_4-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_3_2_3_4-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_2_3_4-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_3_2_3_4.eprime b/tests/exhaustive/basic/set09/expected/model_3_2_3_4.eprime new file mode 100644 index 0000000000..f098a13d32 --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_2_3_4.eprime @@ -0,0 +1,40 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +branching on + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithFlags_Flags, + y_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithDummy] +such that + and([q21 <= x_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithDummy[q22] != 6 -> + x_ExplicitVarSizeWithMarker_Values[q21] + 2 = y_ExplicitVarSizeWithDummy[q22] + | q21 : int(1..4), q22 : int(1..4)]), + and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] + | q1 : int(1..3)]), + and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 2 | q2 : int(1..4)]), + 1 <= x_ExplicitVarSizeWithMarker_Marker, + and([y_ExplicitVarSizeWithDummy[q4] < y_ExplicitVarSizeWithDummy[q4 + 1] \/ y_ExplicitVarSizeWithDummy[q4] = 6 + | q4 : int(1..3)]), + and([y_ExplicitVarSizeWithDummy[q5] = 6 -> y_ExplicitVarSizeWithDummy[q5 + 1] = 6 | q5 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q6] != 6) | q6 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q8 + 1] -> + y_ExplicitVarSizeWithFlags_Values[q8] < y_ExplicitVarSizeWithFlags_Values[q8 + 1] + | q8 : int(1..3)]), + and([y_ExplicitVarSizeWithFlags_Flags[q9] = false -> y_ExplicitVarSizeWithFlags_Values[q9] = 2 | q9 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q10 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q10] | q10 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q11]) | q11 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q14] -> + or([y_ExplicitVarSizeWithDummy[q16] != 6 /\ + y_ExplicitVarSizeWithDummy[q16] = y_ExplicitVarSizeWithFlags_Values[q14] + | q16 : int(1..4)]) + | q14 : int(1..4)]), + and([y_ExplicitVarSizeWithDummy[q18] != 6 -> + or([y_ExplicitVarSizeWithFlags_Flags[q20] /\ + y_ExplicitVarSizeWithFlags_Values[q20] = y_ExplicitVarSizeWithDummy[q18] + | q20 : int(1..4)]) + | q18 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_3_2_4_1-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_3_2_4_1-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_2_4_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_3_2_4_1-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_3_2_4_1-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_2_4_1-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_3_2_4_1.eprime b/tests/exhaustive/basic/set09/expected/model_3_2_4_1.eprime new file mode 100644 index 0000000000..6fc2962eea --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_2_4_1.eprime @@ -0,0 +1,46 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +find y_Occurrence: matrix indexed by [int(2..5)] of bool +branching on + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithMarker_Marker, + x_ExplicitVarSizeWithMarker_Values, y_Occurrence, y_ExplicitVarSizeWithDummy] +such that + and([q27 <= x_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithDummy[q28] != 6 -> + x_ExplicitVarSizeWithMarker_Values[q27] + 2 = y_ExplicitVarSizeWithDummy[q28] + | q27 : int(1..4), q28 : int(1..4)]), + and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] + | q1 : int(1..3)]), + and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 2 | q2 : int(1..4)]), + 1 <= x_ExplicitVarSizeWithMarker_Marker, + and([y_ExplicitVarSizeWithDummy[q4] < y_ExplicitVarSizeWithDummy[q4 + 1] \/ y_ExplicitVarSizeWithDummy[q4] = 6 + | q4 : int(1..3)]), + and([y_ExplicitVarSizeWithDummy[q5] = 6 -> y_ExplicitVarSizeWithDummy[q5 + 1] = 6 | q5 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q6] != 6) | q6 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q8 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q8] < x_ExplicitVarSizeWithFlags_Values[q8 + 1] + | q8 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q9] = false -> x_ExplicitVarSizeWithFlags_Values[q9] = 2 | q9 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q10 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q10] | q10 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q11]) | q11 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q14] -> + or([q16 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q16] = x_ExplicitVarSizeWithFlags_Values[q14] + | q16 : int(1..4)]) + | q14 : int(1..4)]), + and([q18 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithFlags_Flags[q20] /\ + x_ExplicitVarSizeWithFlags_Values[q20] = x_ExplicitVarSizeWithMarker_Values[q18] + | q20 : int(1..4)]) + | q18 : int(1..4)]), + 1 <= sum([toInt(y_Occurrence[q21]) | q21 : int(2..5)]), + and([y_Occurrence[q22] -> + or([y_ExplicitVarSizeWithDummy[q24] != 6 /\ y_ExplicitVarSizeWithDummy[q24] = q22 | q24 : int(1..4)]) + | q22 : int(2..5)]), + and([y_ExplicitVarSizeWithDummy[q26] != 6 -> y_Occurrence[y_ExplicitVarSizeWithDummy[q26]] | q26 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_3_2_4_2-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_3_2_4_2-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_2_4_2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_3_2_4_2-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_3_2_4_2-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_2_4_2-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_3_2_4_2.eprime b/tests/exhaustive/basic/set09/expected/model_3_2_4_2.eprime new file mode 100644 index 0000000000..dbe9bc7729 --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_2_4_2.eprime @@ -0,0 +1,40 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +branching on + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithMarker_Marker, + x_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithDummy] +such that + and([q21 <= x_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithDummy[q22] != 6 -> + x_ExplicitVarSizeWithMarker_Values[q21] + 2 = y_ExplicitVarSizeWithDummy[q22] + | q21 : int(1..4), q22 : int(1..4)]), + and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] + | q1 : int(1..3)]), + and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 2 | q2 : int(1..4)]), + 1 <= x_ExplicitVarSizeWithMarker_Marker, + and([y_ExplicitVarSizeWithDummy[q4] < y_ExplicitVarSizeWithDummy[q4 + 1] \/ y_ExplicitVarSizeWithDummy[q4] = 6 + | q4 : int(1..3)]), + and([y_ExplicitVarSizeWithDummy[q5] = 6 -> y_ExplicitVarSizeWithDummy[q5 + 1] = 6 | q5 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q6] != 6) | q6 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q8 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q8] < x_ExplicitVarSizeWithFlags_Values[q8 + 1] + | q8 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q9] = false -> x_ExplicitVarSizeWithFlags_Values[q9] = 2 | q9 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q10 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q10] | q10 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q11]) | q11 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q14] -> + or([q16 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q16] = x_ExplicitVarSizeWithFlags_Values[q14] + | q16 : int(1..4)]) + | q14 : int(1..4)]), + and([q18 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithFlags_Flags[q20] /\ + x_ExplicitVarSizeWithFlags_Values[q20] = x_ExplicitVarSizeWithMarker_Values[q18] + | q20 : int(1..4)]) + | q18 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_3_2_4_3-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_3_2_4_3-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_2_4_3-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_3_2_4_3-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_3_2_4_3-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_2_4_3-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_3_2_4_3.eprime b/tests/exhaustive/basic/set09/expected/model_3_2_4_3.eprime new file mode 100644 index 0000000000..39e771368e --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_2_4_3.eprime @@ -0,0 +1,58 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +find y_ExplicitVarSizeWithMarker_Marker: int(0..4) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +branching on + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithMarker_Marker, + x_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values, + y_ExplicitVarSizeWithDummy] +such that + and([q32 <= x_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithDummy[q33] != 6 -> + x_ExplicitVarSizeWithMarker_Values[q32] + 2 = y_ExplicitVarSizeWithDummy[q33] + | q32 : int(1..4), q33 : int(1..4)]), + and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] + | q1 : int(1..3)]), + and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 2 | q2 : int(1..4)]), + 1 <= x_ExplicitVarSizeWithMarker_Marker, + and([y_ExplicitVarSizeWithDummy[q4] < y_ExplicitVarSizeWithDummy[q4 + 1] \/ y_ExplicitVarSizeWithDummy[q4] = 6 + | q4 : int(1..3)]), + and([y_ExplicitVarSizeWithDummy[q5] = 6 -> y_ExplicitVarSizeWithDummy[q5 + 1] = 6 | q5 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q6] != 6) | q6 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q8 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q8] < x_ExplicitVarSizeWithFlags_Values[q8 + 1] + | q8 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q9] = false -> x_ExplicitVarSizeWithFlags_Values[q9] = 2 | q9 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q10 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q10] | q10 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q11]) | q11 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q14] -> + or([q16 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q16] = x_ExplicitVarSizeWithFlags_Values[q14] + | q16 : int(1..4)]) + | q14 : int(1..4)]), + and([q18 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithFlags_Flags[q20] /\ + x_ExplicitVarSizeWithFlags_Values[q20] = x_ExplicitVarSizeWithMarker_Values[q18] + | q20 : int(1..4)]) + | q18 : int(1..4)]), + and([q21 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> + y_ExplicitVarSizeWithMarker_Values[q21] < y_ExplicitVarSizeWithMarker_Values[q21 + 1] + | q21 : int(1..3)]), + and([q22 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q22] = 2 | q22 : int(1..4)]), + 1 <= y_ExplicitVarSizeWithMarker_Marker, + and([q25 <= y_ExplicitVarSizeWithMarker_Marker -> + or([y_ExplicitVarSizeWithDummy[q27] != 6 /\ + y_ExplicitVarSizeWithDummy[q27] = y_ExplicitVarSizeWithMarker_Values[q25] + | q27 : int(1..4)]) + | q25 : int(1..4)]), + and([y_ExplicitVarSizeWithDummy[q29] != 6 -> + or([q31 <= y_ExplicitVarSizeWithMarker_Marker /\ + y_ExplicitVarSizeWithMarker_Values[q31] = y_ExplicitVarSizeWithDummy[q29] + | q31 : int(1..4)]) + | q29 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_3_2_4_4-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_3_2_4_4-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_2_4_4-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_3_2_4_4-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_3_2_4_4-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_2_4_4-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_3_2_4_4.eprime b/tests/exhaustive/basic/set09/expected/model_3_2_4_4.eprime new file mode 100644 index 0000000000..6425ad0a2b --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_2_4_4.eprime @@ -0,0 +1,60 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +branching on + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithMarker_Marker, + x_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values, + y_ExplicitVarSizeWithDummy] +such that + and([q34 <= x_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithDummy[q35] != 6 -> + x_ExplicitVarSizeWithMarker_Values[q34] + 2 = y_ExplicitVarSizeWithDummy[q35] + | q34 : int(1..4), q35 : int(1..4)]), + and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] + | q1 : int(1..3)]), + and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 2 | q2 : int(1..4)]), + 1 <= x_ExplicitVarSizeWithMarker_Marker, + and([y_ExplicitVarSizeWithDummy[q4] < y_ExplicitVarSizeWithDummy[q4 + 1] \/ y_ExplicitVarSizeWithDummy[q4] = 6 + | q4 : int(1..3)]), + and([y_ExplicitVarSizeWithDummy[q5] = 6 -> y_ExplicitVarSizeWithDummy[q5 + 1] = 6 | q5 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q6] != 6) | q6 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q8 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q8] < x_ExplicitVarSizeWithFlags_Values[q8 + 1] + | q8 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q9] = false -> x_ExplicitVarSizeWithFlags_Values[q9] = 2 | q9 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q10 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q10] | q10 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q11]) | q11 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q14] -> + or([q16 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q16] = x_ExplicitVarSizeWithFlags_Values[q14] + | q16 : int(1..4)]) + | q14 : int(1..4)]), + and([q18 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithFlags_Flags[q20] /\ + x_ExplicitVarSizeWithFlags_Values[q20] = x_ExplicitVarSizeWithMarker_Values[q18] + | q20 : int(1..4)]) + | q18 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q21 + 1] -> + y_ExplicitVarSizeWithFlags_Values[q21] < y_ExplicitVarSizeWithFlags_Values[q21 + 1] + | q21 : int(1..3)]), + and([y_ExplicitVarSizeWithFlags_Flags[q22] = false -> y_ExplicitVarSizeWithFlags_Values[q22] = 2 + | q22 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q23 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q23] | q23 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q24]) | q24 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q27] -> + or([y_ExplicitVarSizeWithDummy[q29] != 6 /\ + y_ExplicitVarSizeWithDummy[q29] = y_ExplicitVarSizeWithFlags_Values[q27] + | q29 : int(1..4)]) + | q27 : int(1..4)]), + and([y_ExplicitVarSizeWithDummy[q31] != 6 -> + or([y_ExplicitVarSizeWithFlags_Flags[q33] /\ + y_ExplicitVarSizeWithFlags_Values[q33] = y_ExplicitVarSizeWithDummy[q31] + | q33 : int(1..4)]) + | q31 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_3_3_1_1-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_3_3_1_1-solution000001.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_3_1_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_3_3_1_1-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_3_3_1_1-solution000002.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_3_1_1-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_3_3_1_1.eprime b/tests/exhaustive/basic/set09/expected/model_3_3_1_1.eprime new file mode 100644 index 0000000000..3ec2bcc362 --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_3_1_1.eprime @@ -0,0 +1,40 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +find x_Occurrence: matrix indexed by [int(2..5)] of bool +find y_ExplicitVarSizeWithMarker_Marker: int(0..4) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_Occurrence: matrix indexed by [int(2..5)] of bool +branching on + [x_Occurrence, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, y_Occurrence, + y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values] +such that + and([q14 <= x_ExplicitVarSizeWithMarker_Marker /\ q15 <= y_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q14] + 2 = y_ExplicitVarSizeWithMarker_Values[q15] + | q14 : int(1..4), q15 : int(1..4)]), + and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] + | q1 : int(1..3)]), + and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 2 | q2 : int(1..4)]), + 1 <= x_ExplicitVarSizeWithMarker_Marker, + and([q4 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> + y_ExplicitVarSizeWithMarker_Values[q4] < y_ExplicitVarSizeWithMarker_Values[q4 + 1] + | q4 : int(1..3)]), + and([q5 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q5] = 2 | q5 : int(1..4)]), + 1 <= y_ExplicitVarSizeWithMarker_Marker, + 1 <= sum([toInt(x_Occurrence[q7]) | q7 : int(2..5)]), + and([x_Occurrence[q16] -> + or([q18 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q18] = q16 + | q18 : int(1..4)]) + | q16 : int(2..5)]), + and([q20 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q20]] + | q20 : int(1..4)]), + 1 <= sum([toInt(y_Occurrence[q8]) | q8 : int(2..5)]), + and([y_Occurrence[q9] -> + or([q11 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[q11] = q9 + | q11 : int(1..4)]) + | q9 : int(2..5)]), + and([q13 <= y_ExplicitVarSizeWithMarker_Marker -> y_Occurrence[y_ExplicitVarSizeWithMarker_Values[q13]] + | q13 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_3_3_1_2-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_3_3_1_2-solution000001.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_3_1_2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_3_3_1_2-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_3_3_1_2-solution000002.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_3_1_2-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_3_3_1_2.eprime b/tests/exhaustive/basic/set09/expected/model_3_3_1_2.eprime new file mode 100644 index 0000000000..8eaef50691 --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_3_1_2.eprime @@ -0,0 +1,47 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +find x_Occurrence: matrix indexed by [int(2..5)] of bool +find y_ExplicitVarSizeWithMarker_Marker: int(0..4) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +branching on + [x_Occurrence, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithDummy, + y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values] +such that + and([q25 <= x_ExplicitVarSizeWithMarker_Marker /\ q26 <= y_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q25] + 2 = y_ExplicitVarSizeWithMarker_Values[q26] + | q25 : int(1..4), q26 : int(1..4)]), + and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] + | q1 : int(1..3)]), + and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 2 | q2 : int(1..4)]), + 1 <= x_ExplicitVarSizeWithMarker_Marker, + and([q4 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> + y_ExplicitVarSizeWithMarker_Values[q4] < y_ExplicitVarSizeWithMarker_Values[q4 + 1] + | q4 : int(1..3)]), + and([q5 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q5] = 2 | q5 : int(1..4)]), + 1 <= y_ExplicitVarSizeWithMarker_Marker, + 1 <= sum([toInt(x_Occurrence[q7]) | q7 : int(2..5)]), + and([x_Occurrence[q20] -> + or([q22 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q22] = q20 + | q22 : int(1..4)]) + | q20 : int(2..5)]), + and([q24 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q24]] + | q24 : int(1..4)]), + and([y_ExplicitVarSizeWithDummy[q8] < y_ExplicitVarSizeWithDummy[q8 + 1] \/ y_ExplicitVarSizeWithDummy[q8] = 6 + | q8 : int(1..3)]), + and([y_ExplicitVarSizeWithDummy[q9] = 6 -> y_ExplicitVarSizeWithDummy[q9 + 1] = 6 | q9 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q10] != 6) | q10 : int(1..4)]), + and([y_ExplicitVarSizeWithDummy[q13] != 6 -> + or([q15 <= y_ExplicitVarSizeWithMarker_Marker /\ + y_ExplicitVarSizeWithMarker_Values[q15] = y_ExplicitVarSizeWithDummy[q13] + | q15 : int(1..4)]) + | q13 : int(1..4)]), + and([q17 <= y_ExplicitVarSizeWithMarker_Marker -> + or([y_ExplicitVarSizeWithDummy[q19] != 6 /\ + y_ExplicitVarSizeWithDummy[q19] = y_ExplicitVarSizeWithMarker_Values[q17] + | q19 : int(1..4)]) + | q17 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_3_3_1_3-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_3_3_1_3-solution000001.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_3_1_3-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_3_3_1_3-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_3_3_1_3-solution000002.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_3_1_3-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_3_3_1_3.eprime b/tests/exhaustive/basic/set09/expected/model_3_3_1_3.eprime new file mode 100644 index 0000000000..16bba88020 --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_3_1_3.eprime @@ -0,0 +1,32 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +find x_Occurrence: matrix indexed by [int(2..5)] of bool +find y_ExplicitVarSizeWithMarker_Marker: int(0..4) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +branching on + [x_Occurrence, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, + y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values] +such that + and([q13 <= x_ExplicitVarSizeWithMarker_Marker /\ q14 <= y_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q13] + 2 = y_ExplicitVarSizeWithMarker_Values[q14] + | q13 : int(1..4), q14 : int(1..4)]), + and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] + | q1 : int(1..3)]), + and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 2 | q2 : int(1..4)]), + 1 <= x_ExplicitVarSizeWithMarker_Marker, + and([q4 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> + y_ExplicitVarSizeWithMarker_Values[q4] < y_ExplicitVarSizeWithMarker_Values[q4 + 1] + | q4 : int(1..3)]), + and([q5 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q5] = 2 | q5 : int(1..4)]), + 1 <= y_ExplicitVarSizeWithMarker_Marker, + 1 <= sum([toInt(x_Occurrence[q7]) | q7 : int(2..5)]), + and([x_Occurrence[q8] -> + or([q10 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q10] = q8 + | q10 : int(1..4)]) + | q8 : int(2..5)]), + and([q12 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q12]] + | q12 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_3_3_1_4-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_3_3_1_4-solution000001.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_3_1_4-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_3_3_1_4-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_3_3_1_4-solution000002.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_3_1_4-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_3_3_1_4.eprime b/tests/exhaustive/basic/set09/expected/model_3_3_1_4.eprime new file mode 100644 index 0000000000..487253019b --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_3_1_4.eprime @@ -0,0 +1,51 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +find x_Occurrence: matrix indexed by [int(2..5)] of bool +find y_ExplicitVarSizeWithMarker_Marker: int(0..4) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +branching on + [x_Occurrence, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, + y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithMarker_Marker, + y_ExplicitVarSizeWithMarker_Values] +such that + and([q26 <= x_ExplicitVarSizeWithMarker_Marker /\ q27 <= y_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q26] + 2 = y_ExplicitVarSizeWithMarker_Values[q27] + | q26 : int(1..4), q27 : int(1..4)]), + and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] + | q1 : int(1..3)]), + and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 2 | q2 : int(1..4)]), + 1 <= x_ExplicitVarSizeWithMarker_Marker, + and([q4 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> + y_ExplicitVarSizeWithMarker_Values[q4] < y_ExplicitVarSizeWithMarker_Values[q4 + 1] + | q4 : int(1..3)]), + and([q5 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q5] = 2 | q5 : int(1..4)]), + 1 <= y_ExplicitVarSizeWithMarker_Marker, + 1 <= sum([toInt(x_Occurrence[q7]) | q7 : int(2..5)]), + and([x_Occurrence[q21] -> + or([q23 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q23] = q21 + | q23 : int(1..4)]) + | q21 : int(2..5)]), + and([q25 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q25]] + | q25 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q8 + 1] -> + y_ExplicitVarSizeWithFlags_Values[q8] < y_ExplicitVarSizeWithFlags_Values[q8 + 1] + | q8 : int(1..3)]), + and([y_ExplicitVarSizeWithFlags_Flags[q9] = false -> y_ExplicitVarSizeWithFlags_Values[q9] = 2 | q9 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q10 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q10] | q10 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q11]) | q11 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q14] -> + or([q16 <= y_ExplicitVarSizeWithMarker_Marker /\ + y_ExplicitVarSizeWithMarker_Values[q16] = y_ExplicitVarSizeWithFlags_Values[q14] + | q16 : int(1..4)]) + | q14 : int(1..4)]), + and([q18 <= y_ExplicitVarSizeWithMarker_Marker -> + or([y_ExplicitVarSizeWithFlags_Flags[q20] /\ + y_ExplicitVarSizeWithFlags_Values[q20] = y_ExplicitVarSizeWithMarker_Values[q18] + | q20 : int(1..4)]) + | q18 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_3_3_2_1-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_3_3_2_1-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_3_2_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_3_3_2_1-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_3_3_2_1-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_3_2_1-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_3_3_2_1.eprime b/tests/exhaustive/basic/set09/expected/model_3_3_2_1.eprime new file mode 100644 index 0000000000..124edd1223 --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_3_2_1.eprime @@ -0,0 +1,47 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +find y_ExplicitVarSizeWithMarker_Marker: int(0..4) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_Occurrence: matrix indexed by [int(2..5)] of bool +branching on + [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, y_Occurrence, + y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values] +such that + and([q25 <= x_ExplicitVarSizeWithMarker_Marker /\ q26 <= y_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q25] + 2 = y_ExplicitVarSizeWithMarker_Values[q26] + | q25 : int(1..4), q26 : int(1..4)]), + and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] + | q1 : int(1..3)]), + and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 2 | q2 : int(1..4)]), + 1 <= x_ExplicitVarSizeWithMarker_Marker, + and([q4 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> + y_ExplicitVarSizeWithMarker_Values[q4] < y_ExplicitVarSizeWithMarker_Values[q4 + 1] + | q4 : int(1..3)]), + and([q5 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q5] = 2 | q5 : int(1..4)]), + 1 <= y_ExplicitVarSizeWithMarker_Marker, + and([x_ExplicitVarSizeWithDummy[q7] < x_ExplicitVarSizeWithDummy[q7 + 1] \/ x_ExplicitVarSizeWithDummy[q7] = 6 + | q7 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q8] = 6 -> x_ExplicitVarSizeWithDummy[q8 + 1] = 6 | q8 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q9] != 6) | q9 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q12] != 6 -> + or([q14 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q14] = x_ExplicitVarSizeWithDummy[q12] + | q14 : int(1..4)]) + | q12 : int(1..4)]), + and([q16 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithDummy[q18] != 6 /\ + x_ExplicitVarSizeWithDummy[q18] = x_ExplicitVarSizeWithMarker_Values[q16] + | q18 : int(1..4)]) + | q16 : int(1..4)]), + 1 <= sum([toInt(y_Occurrence[q19]) | q19 : int(2..5)]), + and([y_Occurrence[q20] -> + or([q22 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[q22] = q20 + | q22 : int(1..4)]) + | q20 : int(2..5)]), + and([q24 <= y_ExplicitVarSizeWithMarker_Marker -> y_Occurrence[y_ExplicitVarSizeWithMarker_Values[q24]] + | q24 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_3_3_2_2-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_3_3_2_2-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_3_2_2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_3_3_2_2-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_3_3_2_2-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_3_2_2-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_3_3_2_2.eprime b/tests/exhaustive/basic/set09/expected/model_3_3_2_2.eprime new file mode 100644 index 0000000000..7806a133c2 --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_3_2_2.eprime @@ -0,0 +1,54 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +find y_ExplicitVarSizeWithMarker_Marker: int(0..4) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +branching on + [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, + y_ExplicitVarSizeWithDummy, y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values] +such that + and([q31 <= x_ExplicitVarSizeWithMarker_Marker /\ q32 <= y_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q31] + 2 = y_ExplicitVarSizeWithMarker_Values[q32] + | q31 : int(1..4), q32 : int(1..4)]), + and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] + | q1 : int(1..3)]), + and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 2 | q2 : int(1..4)]), + 1 <= x_ExplicitVarSizeWithMarker_Marker, + and([q4 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> + y_ExplicitVarSizeWithMarker_Values[q4] < y_ExplicitVarSizeWithMarker_Values[q4 + 1] + | q4 : int(1..3)]), + and([q5 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q5] = 2 | q5 : int(1..4)]), + 1 <= y_ExplicitVarSizeWithMarker_Marker, + and([x_ExplicitVarSizeWithDummy[q7] < x_ExplicitVarSizeWithDummy[q7 + 1] \/ x_ExplicitVarSizeWithDummy[q7] = 6 + | q7 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q8] = 6 -> x_ExplicitVarSizeWithDummy[q8 + 1] = 6 | q8 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q9] != 6) | q9 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q12] != 6 -> + or([q14 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q14] = x_ExplicitVarSizeWithDummy[q12] + | q14 : int(1..4)]) + | q12 : int(1..4)]), + and([q16 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithDummy[q18] != 6 /\ + x_ExplicitVarSizeWithDummy[q18] = x_ExplicitVarSizeWithMarker_Values[q16] + | q18 : int(1..4)]) + | q16 : int(1..4)]), + and([y_ExplicitVarSizeWithDummy[q19] < y_ExplicitVarSizeWithDummy[q19 + 1] \/ y_ExplicitVarSizeWithDummy[q19] = 6 + | q19 : int(1..3)]), + and([y_ExplicitVarSizeWithDummy[q20] = 6 -> y_ExplicitVarSizeWithDummy[q20 + 1] = 6 | q20 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q21] != 6) | q21 : int(1..4)]), + and([y_ExplicitVarSizeWithDummy[q24] != 6 -> + or([q26 <= y_ExplicitVarSizeWithMarker_Marker /\ + y_ExplicitVarSizeWithMarker_Values[q26] = y_ExplicitVarSizeWithDummy[q24] + | q26 : int(1..4)]) + | q24 : int(1..4)]), + and([q28 <= y_ExplicitVarSizeWithMarker_Marker -> + or([y_ExplicitVarSizeWithDummy[q30] != 6 /\ + y_ExplicitVarSizeWithDummy[q30] = y_ExplicitVarSizeWithMarker_Values[q28] + | q30 : int(1..4)]) + | q28 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_3_3_2_3-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_3_3_2_3-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_3_2_3-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_3_3_2_3-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_3_3_2_3-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_3_2_3-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_3_3_2_3.eprime b/tests/exhaustive/basic/set09/expected/model_3_3_2_3.eprime new file mode 100644 index 0000000000..8c27f375ef --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_3_2_3.eprime @@ -0,0 +1,39 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +find y_ExplicitVarSizeWithMarker_Marker: int(0..4) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +branching on + [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, + y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values] +such that + and([q19 <= x_ExplicitVarSizeWithMarker_Marker /\ q20 <= y_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q19] + 2 = y_ExplicitVarSizeWithMarker_Values[q20] + | q19 : int(1..4), q20 : int(1..4)]), + and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] + | q1 : int(1..3)]), + and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 2 | q2 : int(1..4)]), + 1 <= x_ExplicitVarSizeWithMarker_Marker, + and([q4 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> + y_ExplicitVarSizeWithMarker_Values[q4] < y_ExplicitVarSizeWithMarker_Values[q4 + 1] + | q4 : int(1..3)]), + and([q5 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q5] = 2 | q5 : int(1..4)]), + 1 <= y_ExplicitVarSizeWithMarker_Marker, + and([x_ExplicitVarSizeWithDummy[q7] < x_ExplicitVarSizeWithDummy[q7 + 1] \/ x_ExplicitVarSizeWithDummy[q7] = 6 + | q7 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q8] = 6 -> x_ExplicitVarSizeWithDummy[q8 + 1] = 6 | q8 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q9] != 6) | q9 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q12] != 6 -> + or([q14 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q14] = x_ExplicitVarSizeWithDummy[q12] + | q14 : int(1..4)]) + | q12 : int(1..4)]), + and([q16 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithDummy[q18] != 6 /\ + x_ExplicitVarSizeWithDummy[q18] = x_ExplicitVarSizeWithMarker_Values[q16] + | q18 : int(1..4)]) + | q16 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_3_3_2_4-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_3_3_2_4-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_3_2_4-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_3_3_2_4-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_3_3_2_4-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_3_2_4-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_3_3_2_4.eprime b/tests/exhaustive/basic/set09/expected/model_3_3_2_4.eprime new file mode 100644 index 0000000000..85a12b9508 --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_3_2_4.eprime @@ -0,0 +1,59 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +find y_ExplicitVarSizeWithMarker_Marker: int(0..4) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +branching on + [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, + y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithMarker_Marker, + y_ExplicitVarSizeWithMarker_Values] +such that + and([q32 <= x_ExplicitVarSizeWithMarker_Marker /\ q33 <= y_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q32] + 2 = y_ExplicitVarSizeWithMarker_Values[q33] + | q32 : int(1..4), q33 : int(1..4)]), + and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] + | q1 : int(1..3)]), + and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 2 | q2 : int(1..4)]), + 1 <= x_ExplicitVarSizeWithMarker_Marker, + and([q4 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> + y_ExplicitVarSizeWithMarker_Values[q4] < y_ExplicitVarSizeWithMarker_Values[q4 + 1] + | q4 : int(1..3)]), + and([q5 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q5] = 2 | q5 : int(1..4)]), + 1 <= y_ExplicitVarSizeWithMarker_Marker, + and([x_ExplicitVarSizeWithDummy[q7] < x_ExplicitVarSizeWithDummy[q7 + 1] \/ x_ExplicitVarSizeWithDummy[q7] = 6 + | q7 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q8] = 6 -> x_ExplicitVarSizeWithDummy[q8 + 1] = 6 | q8 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q9] != 6) | q9 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q12] != 6 -> + or([q14 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q14] = x_ExplicitVarSizeWithDummy[q12] + | q14 : int(1..4)]) + | q12 : int(1..4)]), + and([q16 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithDummy[q18] != 6 /\ + x_ExplicitVarSizeWithDummy[q18] = x_ExplicitVarSizeWithMarker_Values[q16] + | q18 : int(1..4)]) + | q16 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q19 + 1] -> + y_ExplicitVarSizeWithFlags_Values[q19] < y_ExplicitVarSizeWithFlags_Values[q19 + 1] + | q19 : int(1..3)]), + and([y_ExplicitVarSizeWithFlags_Flags[q20] = false -> y_ExplicitVarSizeWithFlags_Values[q20] = 2 + | q20 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q21 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q21] | q21 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q22]) | q22 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q25] -> + or([q27 <= y_ExplicitVarSizeWithMarker_Marker /\ + y_ExplicitVarSizeWithMarker_Values[q27] = y_ExplicitVarSizeWithFlags_Values[q25] + | q27 : int(1..4)]) + | q25 : int(1..4)]), + and([q29 <= y_ExplicitVarSizeWithMarker_Marker -> + or([y_ExplicitVarSizeWithFlags_Flags[q31] /\ + y_ExplicitVarSizeWithFlags_Values[q31] = y_ExplicitVarSizeWithMarker_Values[q29] + | q31 : int(1..4)]) + | q29 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_3_3_3_1-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_3_3_3_1-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_3_3_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_3_3_3_1-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_3_3_3_1-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_3_3_1-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_3_3_3_1.eprime b/tests/exhaustive/basic/set09/expected/model_3_3_3_1.eprime new file mode 100644 index 0000000000..66dc7e15ca --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_3_3_1.eprime @@ -0,0 +1,32 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_ExplicitVarSizeWithMarker_Marker: int(0..4) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_Occurrence: matrix indexed by [int(2..5)] of bool +branching on + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, y_Occurrence, + y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values] +such that + and([q13 <= x_ExplicitVarSizeWithMarker_Marker /\ q14 <= y_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q13] + 2 = y_ExplicitVarSizeWithMarker_Values[q14] + | q13 : int(1..4), q14 : int(1..4)]), + and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] + | q1 : int(1..3)]), + and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 2 | q2 : int(1..4)]), + 1 <= x_ExplicitVarSizeWithMarker_Marker, + and([q4 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> + y_ExplicitVarSizeWithMarker_Values[q4] < y_ExplicitVarSizeWithMarker_Values[q4 + 1] + | q4 : int(1..3)]), + and([q5 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q5] = 2 | q5 : int(1..4)]), + 1 <= y_ExplicitVarSizeWithMarker_Marker, + 1 <= sum([toInt(y_Occurrence[q7]) | q7 : int(2..5)]), + and([y_Occurrence[q8] -> + or([q10 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[q10] = q8 + | q10 : int(1..4)]) + | q8 : int(2..5)]), + and([q12 <= y_ExplicitVarSizeWithMarker_Marker -> y_Occurrence[y_ExplicitVarSizeWithMarker_Values[q12]] + | q12 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_3_3_3_2-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_3_3_3_2-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_3_3_2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_3_3_3_2-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_3_3_3_2-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_3_3_2-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_3_3_3_2.eprime b/tests/exhaustive/basic/set09/expected/model_3_3_3_2.eprime new file mode 100644 index 0000000000..9618629cd8 --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_3_3_2.eprime @@ -0,0 +1,39 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_ExplicitVarSizeWithMarker_Marker: int(0..4) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +branching on + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithDummy, + y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values] +such that + and([q19 <= x_ExplicitVarSizeWithMarker_Marker /\ q20 <= y_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q19] + 2 = y_ExplicitVarSizeWithMarker_Values[q20] + | q19 : int(1..4), q20 : int(1..4)]), + and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] + | q1 : int(1..3)]), + and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 2 | q2 : int(1..4)]), + 1 <= x_ExplicitVarSizeWithMarker_Marker, + and([q4 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> + y_ExplicitVarSizeWithMarker_Values[q4] < y_ExplicitVarSizeWithMarker_Values[q4 + 1] + | q4 : int(1..3)]), + and([q5 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q5] = 2 | q5 : int(1..4)]), + 1 <= y_ExplicitVarSizeWithMarker_Marker, + and([y_ExplicitVarSizeWithDummy[q7] < y_ExplicitVarSizeWithDummy[q7 + 1] \/ y_ExplicitVarSizeWithDummy[q7] = 6 + | q7 : int(1..3)]), + and([y_ExplicitVarSizeWithDummy[q8] = 6 -> y_ExplicitVarSizeWithDummy[q8 + 1] = 6 | q8 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q9] != 6) | q9 : int(1..4)]), + and([y_ExplicitVarSizeWithDummy[q12] != 6 -> + or([q14 <= y_ExplicitVarSizeWithMarker_Marker /\ + y_ExplicitVarSizeWithMarker_Values[q14] = y_ExplicitVarSizeWithDummy[q12] + | q14 : int(1..4)]) + | q12 : int(1..4)]), + and([q16 <= y_ExplicitVarSizeWithMarker_Marker -> + or([y_ExplicitVarSizeWithDummy[q18] != 6 /\ + y_ExplicitVarSizeWithDummy[q18] = y_ExplicitVarSizeWithMarker_Values[q16] + | q18 : int(1..4)]) + | q16 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_3_3_3_3-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_3_3_3_3-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_3_3_3-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_3_3_3_3-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_3_3_3_3-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_3_3_3-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_3_3_3_3.eprime b/tests/exhaustive/basic/set09/expected/model_3_3_3_3.eprime new file mode 100644 index 0000000000..ad1e9ea981 --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_3_3_3.eprime @@ -0,0 +1,24 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_ExplicitVarSizeWithMarker_Marker: int(0..4) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +branching on + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithMarker_Marker, + y_ExplicitVarSizeWithMarker_Values] +such that + and([q7 <= x_ExplicitVarSizeWithMarker_Marker /\ q8 <= y_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q7] + 2 = y_ExplicitVarSizeWithMarker_Values[q8] + | q7 : int(1..4), q8 : int(1..4)]), + and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] + | q1 : int(1..3)]), + and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 2 | q2 : int(1..4)]), + 1 <= x_ExplicitVarSizeWithMarker_Marker, + and([q4 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> + y_ExplicitVarSizeWithMarker_Values[q4] < y_ExplicitVarSizeWithMarker_Values[q4 + 1] + | q4 : int(1..3)]), + and([q5 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q5] = 2 | q5 : int(1..4)]), + 1 <= y_ExplicitVarSizeWithMarker_Marker + diff --git a/tests/exhaustive/basic/set09/expected/model_3_3_3_4-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_3_3_3_4-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_3_3_4-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_3_3_3_4-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_3_3_3_4-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_3_3_4-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_3_3_3_4.eprime b/tests/exhaustive/basic/set09/expected/model_3_3_3_4.eprime new file mode 100644 index 0000000000..4fbee84c05 --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_3_3_4.eprime @@ -0,0 +1,42 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_ExplicitVarSizeWithMarker_Marker: int(0..4) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +branching on + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithFlags_Flags, + y_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values] +such that + and([q20 <= x_ExplicitVarSizeWithMarker_Marker /\ q21 <= y_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q20] + 2 = y_ExplicitVarSizeWithMarker_Values[q21] + | q20 : int(1..4), q21 : int(1..4)]), + and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] + | q1 : int(1..3)]), + and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 2 | q2 : int(1..4)]), + 1 <= x_ExplicitVarSizeWithMarker_Marker, + and([q4 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> + y_ExplicitVarSizeWithMarker_Values[q4] < y_ExplicitVarSizeWithMarker_Values[q4 + 1] + | q4 : int(1..3)]), + and([q5 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q5] = 2 | q5 : int(1..4)]), + 1 <= y_ExplicitVarSizeWithMarker_Marker, + and([y_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> + y_ExplicitVarSizeWithFlags_Values[q7] < y_ExplicitVarSizeWithFlags_Values[q7 + 1] + | q7 : int(1..3)]), + and([y_ExplicitVarSizeWithFlags_Flags[q8] = false -> y_ExplicitVarSizeWithFlags_Values[q8] = 2 | q8 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q9 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q9] | q9 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q10]) | q10 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q13] -> + or([q15 <= y_ExplicitVarSizeWithMarker_Marker /\ + y_ExplicitVarSizeWithMarker_Values[q15] = y_ExplicitVarSizeWithFlags_Values[q13] + | q15 : int(1..4)]) + | q13 : int(1..4)]), + and([q17 <= y_ExplicitVarSizeWithMarker_Marker -> + or([y_ExplicitVarSizeWithFlags_Flags[q19] /\ + y_ExplicitVarSizeWithFlags_Values[q19] = y_ExplicitVarSizeWithMarker_Values[q17] + | q19 : int(1..4)]) + | q17 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_3_3_4_1-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_3_3_4_1-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_3_4_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_3_3_4_1-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_3_3_4_1-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_3_4_1-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_3_3_4_1.eprime b/tests/exhaustive/basic/set09/expected/model_3_3_4_1.eprime new file mode 100644 index 0000000000..54b4d0bf42 --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_3_4_1.eprime @@ -0,0 +1,51 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_ExplicitVarSizeWithMarker_Marker: int(0..4) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_Occurrence: matrix indexed by [int(2..5)] of bool +branching on + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithMarker_Marker, + x_ExplicitVarSizeWithMarker_Values, y_Occurrence, y_ExplicitVarSizeWithMarker_Marker, + y_ExplicitVarSizeWithMarker_Values] +such that + and([q26 <= x_ExplicitVarSizeWithMarker_Marker /\ q27 <= y_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q26] + 2 = y_ExplicitVarSizeWithMarker_Values[q27] + | q26 : int(1..4), q27 : int(1..4)]), + and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] + | q1 : int(1..3)]), + and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 2 | q2 : int(1..4)]), + 1 <= x_ExplicitVarSizeWithMarker_Marker, + and([q4 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> + y_ExplicitVarSizeWithMarker_Values[q4] < y_ExplicitVarSizeWithMarker_Values[q4 + 1] + | q4 : int(1..3)]), + and([q5 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q5] = 2 | q5 : int(1..4)]), + 1 <= y_ExplicitVarSizeWithMarker_Marker, + and([x_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q7] < x_ExplicitVarSizeWithFlags_Values[q7 + 1] + | q7 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q8] = false -> x_ExplicitVarSizeWithFlags_Values[q8] = 2 | q8 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q9 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q9] | q9 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q10]) | q10 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q13] -> + or([q15 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q15] = x_ExplicitVarSizeWithFlags_Values[q13] + | q15 : int(1..4)]) + | q13 : int(1..4)]), + and([q17 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithFlags_Flags[q19] /\ + x_ExplicitVarSizeWithFlags_Values[q19] = x_ExplicitVarSizeWithMarker_Values[q17] + | q19 : int(1..4)]) + | q17 : int(1..4)]), + 1 <= sum([toInt(y_Occurrence[q20]) | q20 : int(2..5)]), + and([y_Occurrence[q21] -> + or([q23 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[q23] = q21 + | q23 : int(1..4)]) + | q21 : int(2..5)]), + and([q25 <= y_ExplicitVarSizeWithMarker_Marker -> y_Occurrence[y_ExplicitVarSizeWithMarker_Values[q25]] + | q25 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_3_3_4_2-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_3_3_4_2-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_3_4_2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_3_3_4_2-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_3_3_4_2-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_3_4_2-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_3_3_4_2.eprime b/tests/exhaustive/basic/set09/expected/model_3_3_4_2.eprime new file mode 100644 index 0000000000..157e866343 --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_3_4_2.eprime @@ -0,0 +1,58 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_ExplicitVarSizeWithMarker_Marker: int(0..4) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +branching on + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithMarker_Marker, + x_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithDummy, y_ExplicitVarSizeWithMarker_Marker, + y_ExplicitVarSizeWithMarker_Values] +such that + and([q32 <= x_ExplicitVarSizeWithMarker_Marker /\ q33 <= y_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q32] + 2 = y_ExplicitVarSizeWithMarker_Values[q33] + | q32 : int(1..4), q33 : int(1..4)]), + and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] + | q1 : int(1..3)]), + and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 2 | q2 : int(1..4)]), + 1 <= x_ExplicitVarSizeWithMarker_Marker, + and([q4 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> + y_ExplicitVarSizeWithMarker_Values[q4] < y_ExplicitVarSizeWithMarker_Values[q4 + 1] + | q4 : int(1..3)]), + and([q5 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q5] = 2 | q5 : int(1..4)]), + 1 <= y_ExplicitVarSizeWithMarker_Marker, + and([x_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q7] < x_ExplicitVarSizeWithFlags_Values[q7 + 1] + | q7 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q8] = false -> x_ExplicitVarSizeWithFlags_Values[q8] = 2 | q8 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q9 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q9] | q9 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q10]) | q10 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q13] -> + or([q15 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q15] = x_ExplicitVarSizeWithFlags_Values[q13] + | q15 : int(1..4)]) + | q13 : int(1..4)]), + and([q17 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithFlags_Flags[q19] /\ + x_ExplicitVarSizeWithFlags_Values[q19] = x_ExplicitVarSizeWithMarker_Values[q17] + | q19 : int(1..4)]) + | q17 : int(1..4)]), + and([y_ExplicitVarSizeWithDummy[q20] < y_ExplicitVarSizeWithDummy[q20 + 1] \/ y_ExplicitVarSizeWithDummy[q20] = 6 + | q20 : int(1..3)]), + and([y_ExplicitVarSizeWithDummy[q21] = 6 -> y_ExplicitVarSizeWithDummy[q21 + 1] = 6 | q21 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q22] != 6) | q22 : int(1..4)]), + and([y_ExplicitVarSizeWithDummy[q25] != 6 -> + or([q27 <= y_ExplicitVarSizeWithMarker_Marker /\ + y_ExplicitVarSizeWithMarker_Values[q27] = y_ExplicitVarSizeWithDummy[q25] + | q27 : int(1..4)]) + | q25 : int(1..4)]), + and([q29 <= y_ExplicitVarSizeWithMarker_Marker -> + or([y_ExplicitVarSizeWithDummy[q31] != 6 /\ + y_ExplicitVarSizeWithDummy[q31] = y_ExplicitVarSizeWithMarker_Values[q29] + | q31 : int(1..4)]) + | q29 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_3_3_4_3-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_3_3_4_3-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_3_4_3-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_3_3_4_3-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_3_3_4_3-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_3_4_3-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_3_3_4_3.eprime b/tests/exhaustive/basic/set09/expected/model_3_3_4_3.eprime new file mode 100644 index 0000000000..58d27cf48a --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_3_4_3.eprime @@ -0,0 +1,42 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_ExplicitVarSizeWithMarker_Marker: int(0..4) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +branching on + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithMarker_Marker, + x_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values] +such that + and([q20 <= x_ExplicitVarSizeWithMarker_Marker /\ q21 <= y_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q20] + 2 = y_ExplicitVarSizeWithMarker_Values[q21] + | q20 : int(1..4), q21 : int(1..4)]), + and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] + | q1 : int(1..3)]), + and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 2 | q2 : int(1..4)]), + 1 <= x_ExplicitVarSizeWithMarker_Marker, + and([q4 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> + y_ExplicitVarSizeWithMarker_Values[q4] < y_ExplicitVarSizeWithMarker_Values[q4 + 1] + | q4 : int(1..3)]), + and([q5 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q5] = 2 | q5 : int(1..4)]), + 1 <= y_ExplicitVarSizeWithMarker_Marker, + and([x_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q7] < x_ExplicitVarSizeWithFlags_Values[q7 + 1] + | q7 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q8] = false -> x_ExplicitVarSizeWithFlags_Values[q8] = 2 | q8 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q9 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q9] | q9 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q10]) | q10 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q13] -> + or([q15 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q15] = x_ExplicitVarSizeWithFlags_Values[q13] + | q15 : int(1..4)]) + | q13 : int(1..4)]), + and([q17 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithFlags_Flags[q19] /\ + x_ExplicitVarSizeWithFlags_Values[q19] = x_ExplicitVarSizeWithMarker_Values[q17] + | q19 : int(1..4)]) + | q17 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_3_3_4_4-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_3_3_4_4-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_3_4_4-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_3_3_4_4-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_3_3_4_4-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_3_4_4-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_3_3_4_4.eprime b/tests/exhaustive/basic/set09/expected/model_3_3_4_4.eprime new file mode 100644 index 0000000000..8eeab52a56 --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_3_4_4.eprime @@ -0,0 +1,62 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_ExplicitVarSizeWithMarker_Marker: int(0..4) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +branching on + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithMarker_Marker, + x_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values, + y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values] +such that + and([q33 <= x_ExplicitVarSizeWithMarker_Marker /\ q34 <= y_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q33] + 2 = y_ExplicitVarSizeWithMarker_Values[q34] + | q33 : int(1..4), q34 : int(1..4)]), + and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] + | q1 : int(1..3)]), + and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 2 | q2 : int(1..4)]), + 1 <= x_ExplicitVarSizeWithMarker_Marker, + and([q4 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> + y_ExplicitVarSizeWithMarker_Values[q4] < y_ExplicitVarSizeWithMarker_Values[q4 + 1] + | q4 : int(1..3)]), + and([q5 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q5] = 2 | q5 : int(1..4)]), + 1 <= y_ExplicitVarSizeWithMarker_Marker, + and([x_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q7] < x_ExplicitVarSizeWithFlags_Values[q7 + 1] + | q7 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q8] = false -> x_ExplicitVarSizeWithFlags_Values[q8] = 2 | q8 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q9 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q9] | q9 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q10]) | q10 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q13] -> + or([q15 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q15] = x_ExplicitVarSizeWithFlags_Values[q13] + | q15 : int(1..4)]) + | q13 : int(1..4)]), + and([q17 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithFlags_Flags[q19] /\ + x_ExplicitVarSizeWithFlags_Values[q19] = x_ExplicitVarSizeWithMarker_Values[q17] + | q19 : int(1..4)]) + | q17 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q20 + 1] -> + y_ExplicitVarSizeWithFlags_Values[q20] < y_ExplicitVarSizeWithFlags_Values[q20 + 1] + | q20 : int(1..3)]), + and([y_ExplicitVarSizeWithFlags_Flags[q21] = false -> y_ExplicitVarSizeWithFlags_Values[q21] = 2 + | q21 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q22 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q22] | q22 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q23]) | q23 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q26] -> + or([q28 <= y_ExplicitVarSizeWithMarker_Marker /\ + y_ExplicitVarSizeWithMarker_Values[q28] = y_ExplicitVarSizeWithFlags_Values[q26] + | q28 : int(1..4)]) + | q26 : int(1..4)]), + and([q30 <= y_ExplicitVarSizeWithMarker_Marker -> + or([y_ExplicitVarSizeWithFlags_Flags[q32] /\ + y_ExplicitVarSizeWithFlags_Values[q32] = y_ExplicitVarSizeWithMarker_Values[q30] + | q32 : int(1..4)]) + | q30 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_3_4_1_1-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_3_4_1_1-solution000001.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_4_1_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_3_4_1_1-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_3_4_1_1-solution000002.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_4_1_1-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_3_4_1_1.eprime b/tests/exhaustive/basic/set09/expected/model_3_4_1_1.eprime new file mode 100644 index 0000000000..842f840473 --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_4_1_1.eprime @@ -0,0 +1,40 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +find x_Occurrence: matrix indexed by [int(2..5)] of bool +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_Occurrence: matrix indexed by [int(2..5)] of bool +branching on + [x_Occurrence, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, y_Occurrence, + y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values] +such that + and([q16 <= x_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithFlags_Flags[q17] -> + x_ExplicitVarSizeWithMarker_Values[q16] + 2 = y_ExplicitVarSizeWithFlags_Values[q17] + | q16 : int(1..4), q17 : int(1..4)]), + and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] + | q1 : int(1..3)]), + and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 2 | q2 : int(1..4)]), + 1 <= x_ExplicitVarSizeWithMarker_Marker, + and([y_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> + y_ExplicitVarSizeWithFlags_Values[q4] < y_ExplicitVarSizeWithFlags_Values[q4 + 1] + | q4 : int(1..3)]), + and([y_ExplicitVarSizeWithFlags_Flags[q5] = false -> y_ExplicitVarSizeWithFlags_Values[q5] = 2 | q5 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q6] | q6 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q7]) | q7 : int(1..4)]), + 1 <= sum([toInt(x_Occurrence[q9]) | q9 : int(2..5)]), + and([x_Occurrence[q18] -> + or([q20 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q20] = q18 + | q20 : int(1..4)]) + | q18 : int(2..5)]), + and([q22 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q22]] + | q22 : int(1..4)]), + 1 <= sum([toInt(y_Occurrence[q10]) | q10 : int(2..5)]), + and([y_Occurrence[q11] -> + or([y_ExplicitVarSizeWithFlags_Flags[q13] /\ y_ExplicitVarSizeWithFlags_Values[q13] = q11 | q13 : int(1..4)]) + | q11 : int(2..5)]), + and([y_ExplicitVarSizeWithFlags_Flags[q15] -> y_Occurrence[y_ExplicitVarSizeWithFlags_Values[q15]] + | q15 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_3_4_1_2-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_3_4_1_2-solution000001.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_4_1_2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_3_4_1_2-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_3_4_1_2-solution000002.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_4_1_2-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_3_4_1_2.eprime b/tests/exhaustive/basic/set09/expected/model_3_4_1_2.eprime new file mode 100644 index 0000000000..5d8608bb70 --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_4_1_2.eprime @@ -0,0 +1,48 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +find x_Occurrence: matrix indexed by [int(2..5)] of bool +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +branching on + [x_Occurrence, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithDummy, + y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values] +such that + and([q27 <= x_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithFlags_Flags[q28] -> + x_ExplicitVarSizeWithMarker_Values[q27] + 2 = y_ExplicitVarSizeWithFlags_Values[q28] + | q27 : int(1..4), q28 : int(1..4)]), + and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] + | q1 : int(1..3)]), + and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 2 | q2 : int(1..4)]), + 1 <= x_ExplicitVarSizeWithMarker_Marker, + and([y_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> + y_ExplicitVarSizeWithFlags_Values[q4] < y_ExplicitVarSizeWithFlags_Values[q4 + 1] + | q4 : int(1..3)]), + and([y_ExplicitVarSizeWithFlags_Flags[q5] = false -> y_ExplicitVarSizeWithFlags_Values[q5] = 2 | q5 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q6] | q6 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q7]) | q7 : int(1..4)]), + 1 <= sum([toInt(x_Occurrence[q9]) | q9 : int(2..5)]), + and([x_Occurrence[q22] -> + or([q24 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q24] = q22 + | q24 : int(1..4)]) + | q22 : int(2..5)]), + and([q26 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q26]] + | q26 : int(1..4)]), + and([y_ExplicitVarSizeWithDummy[q10] < y_ExplicitVarSizeWithDummy[q10 + 1] \/ y_ExplicitVarSizeWithDummy[q10] = 6 + | q10 : int(1..3)]), + and([y_ExplicitVarSizeWithDummy[q11] = 6 -> y_ExplicitVarSizeWithDummy[q11 + 1] = 6 | q11 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q12] != 6) | q12 : int(1..4)]), + and([y_ExplicitVarSizeWithDummy[q15] != 6 -> + or([y_ExplicitVarSizeWithFlags_Flags[q17] /\ + y_ExplicitVarSizeWithFlags_Values[q17] = y_ExplicitVarSizeWithDummy[q15] + | q17 : int(1..4)]) + | q15 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q19] -> + or([y_ExplicitVarSizeWithDummy[q21] != 6 /\ + y_ExplicitVarSizeWithDummy[q21] = y_ExplicitVarSizeWithFlags_Values[q19] + | q21 : int(1..4)]) + | q19 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_3_4_1_3-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_3_4_1_3-solution000001.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_4_1_3-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_3_4_1_3-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_3_4_1_3-solution000002.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_4_1_3-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_3_4_1_3.eprime b/tests/exhaustive/basic/set09/expected/model_3_4_1_3.eprime new file mode 100644 index 0000000000..0920bc13d0 --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_4_1_3.eprime @@ -0,0 +1,51 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +find x_Occurrence: matrix indexed by [int(2..5)] of bool +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_ExplicitVarSizeWithMarker_Marker: int(0..4) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +branching on + [x_Occurrence, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, + y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithFlags_Flags, + y_ExplicitVarSizeWithFlags_Values] +such that + and([q26 <= x_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithFlags_Flags[q27] -> + x_ExplicitVarSizeWithMarker_Values[q26] + 2 = y_ExplicitVarSizeWithFlags_Values[q27] + | q26 : int(1..4), q27 : int(1..4)]), + and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] + | q1 : int(1..3)]), + and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 2 | q2 : int(1..4)]), + 1 <= x_ExplicitVarSizeWithMarker_Marker, + and([y_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> + y_ExplicitVarSizeWithFlags_Values[q4] < y_ExplicitVarSizeWithFlags_Values[q4 + 1] + | q4 : int(1..3)]), + and([y_ExplicitVarSizeWithFlags_Flags[q5] = false -> y_ExplicitVarSizeWithFlags_Values[q5] = 2 | q5 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q6] | q6 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q7]) | q7 : int(1..4)]), + 1 <= sum([toInt(x_Occurrence[q9]) | q9 : int(2..5)]), + and([x_Occurrence[q21] -> + or([q23 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q23] = q21 + | q23 : int(1..4)]) + | q21 : int(2..5)]), + and([q25 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q25]] + | q25 : int(1..4)]), + and([q10 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> + y_ExplicitVarSizeWithMarker_Values[q10] < y_ExplicitVarSizeWithMarker_Values[q10 + 1] + | q10 : int(1..3)]), + and([q11 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q11] = 2 | q11 : int(1..4)]), + 1 <= y_ExplicitVarSizeWithMarker_Marker, + and([q14 <= y_ExplicitVarSizeWithMarker_Marker -> + or([y_ExplicitVarSizeWithFlags_Flags[q16] /\ + y_ExplicitVarSizeWithFlags_Values[q16] = y_ExplicitVarSizeWithMarker_Values[q14] + | q16 : int(1..4)]) + | q14 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q18] -> + or([q20 <= y_ExplicitVarSizeWithMarker_Marker /\ + y_ExplicitVarSizeWithMarker_Values[q20] = y_ExplicitVarSizeWithFlags_Values[q18] + | q20 : int(1..4)]) + | q18 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_3_4_1_4-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_3_4_1_4-solution000001.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_4_1_4-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_3_4_1_4-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_3_4_1_4-solution000002.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_4_1_4-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_3_4_1_4.eprime b/tests/exhaustive/basic/set09/expected/model_3_4_1_4.eprime new file mode 100644 index 0000000000..7ce0db61d8 --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_4_1_4.eprime @@ -0,0 +1,33 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +find x_Occurrence: matrix indexed by [int(2..5)] of bool +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +branching on + [x_Occurrence, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, + y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values] +such that + and([q15 <= x_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithFlags_Flags[q16] -> + x_ExplicitVarSizeWithMarker_Values[q15] + 2 = y_ExplicitVarSizeWithFlags_Values[q16] + | q15 : int(1..4), q16 : int(1..4)]), + and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] + | q1 : int(1..3)]), + and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 2 | q2 : int(1..4)]), + 1 <= x_ExplicitVarSizeWithMarker_Marker, + and([y_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> + y_ExplicitVarSizeWithFlags_Values[q4] < y_ExplicitVarSizeWithFlags_Values[q4 + 1] + | q4 : int(1..3)]), + and([y_ExplicitVarSizeWithFlags_Flags[q5] = false -> y_ExplicitVarSizeWithFlags_Values[q5] = 2 | q5 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q6] | q6 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q7]) | q7 : int(1..4)]), + 1 <= sum([toInt(x_Occurrence[q9]) | q9 : int(2..5)]), + and([x_Occurrence[q10] -> + or([q12 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q12] = q10 + | q12 : int(1..4)]) + | q10 : int(2..5)]), + and([q14 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q14]] + | q14 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_3_4_2_1-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_3_4_2_1-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_4_2_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_3_4_2_1-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_3_4_2_1-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_4_2_1-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_3_4_2_1.eprime b/tests/exhaustive/basic/set09/expected/model_3_4_2_1.eprime new file mode 100644 index 0000000000..61f44c9622 --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_4_2_1.eprime @@ -0,0 +1,47 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_Occurrence: matrix indexed by [int(2..5)] of bool +branching on + [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, y_Occurrence, + y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values] +such that + and([q27 <= x_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithFlags_Flags[q28] -> + x_ExplicitVarSizeWithMarker_Values[q27] + 2 = y_ExplicitVarSizeWithFlags_Values[q28] + | q27 : int(1..4), q28 : int(1..4)]), + and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] + | q1 : int(1..3)]), + and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 2 | q2 : int(1..4)]), + 1 <= x_ExplicitVarSizeWithMarker_Marker, + and([y_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> + y_ExplicitVarSizeWithFlags_Values[q4] < y_ExplicitVarSizeWithFlags_Values[q4 + 1] + | q4 : int(1..3)]), + and([y_ExplicitVarSizeWithFlags_Flags[q5] = false -> y_ExplicitVarSizeWithFlags_Values[q5] = 2 | q5 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q6] | q6 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q7]) | q7 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q9] < x_ExplicitVarSizeWithDummy[q9 + 1] \/ x_ExplicitVarSizeWithDummy[q9] = 6 + | q9 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q10] = 6 -> x_ExplicitVarSizeWithDummy[q10 + 1] = 6 | q10 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q11] != 6) | q11 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q14] != 6 -> + or([q16 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q16] = x_ExplicitVarSizeWithDummy[q14] + | q16 : int(1..4)]) + | q14 : int(1..4)]), + and([q18 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithDummy[q20] != 6 /\ + x_ExplicitVarSizeWithDummy[q20] = x_ExplicitVarSizeWithMarker_Values[q18] + | q20 : int(1..4)]) + | q18 : int(1..4)]), + 1 <= sum([toInt(y_Occurrence[q21]) | q21 : int(2..5)]), + and([y_Occurrence[q22] -> + or([y_ExplicitVarSizeWithFlags_Flags[q24] /\ y_ExplicitVarSizeWithFlags_Values[q24] = q22 | q24 : int(1..4)]) + | q22 : int(2..5)]), + and([y_ExplicitVarSizeWithFlags_Flags[q26] -> y_Occurrence[y_ExplicitVarSizeWithFlags_Values[q26]] + | q26 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_3_4_2_2-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_3_4_2_2-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_4_2_2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_3_4_2_2-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_3_4_2_2-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_4_2_2-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_3_4_2_2.eprime b/tests/exhaustive/basic/set09/expected/model_3_4_2_2.eprime new file mode 100644 index 0000000000..0fed7c779e --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_4_2_2.eprime @@ -0,0 +1,55 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +branching on + [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, + y_ExplicitVarSizeWithDummy, y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values] +such that + and([q33 <= x_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithFlags_Flags[q34] -> + x_ExplicitVarSizeWithMarker_Values[q33] + 2 = y_ExplicitVarSizeWithFlags_Values[q34] + | q33 : int(1..4), q34 : int(1..4)]), + and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] + | q1 : int(1..3)]), + and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 2 | q2 : int(1..4)]), + 1 <= x_ExplicitVarSizeWithMarker_Marker, + and([y_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> + y_ExplicitVarSizeWithFlags_Values[q4] < y_ExplicitVarSizeWithFlags_Values[q4 + 1] + | q4 : int(1..3)]), + and([y_ExplicitVarSizeWithFlags_Flags[q5] = false -> y_ExplicitVarSizeWithFlags_Values[q5] = 2 | q5 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q6] | q6 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q7]) | q7 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q9] < x_ExplicitVarSizeWithDummy[q9 + 1] \/ x_ExplicitVarSizeWithDummy[q9] = 6 + | q9 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q10] = 6 -> x_ExplicitVarSizeWithDummy[q10 + 1] = 6 | q10 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q11] != 6) | q11 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q14] != 6 -> + or([q16 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q16] = x_ExplicitVarSizeWithDummy[q14] + | q16 : int(1..4)]) + | q14 : int(1..4)]), + and([q18 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithDummy[q20] != 6 /\ + x_ExplicitVarSizeWithDummy[q20] = x_ExplicitVarSizeWithMarker_Values[q18] + | q20 : int(1..4)]) + | q18 : int(1..4)]), + and([y_ExplicitVarSizeWithDummy[q21] < y_ExplicitVarSizeWithDummy[q21 + 1] \/ y_ExplicitVarSizeWithDummy[q21] = 6 + | q21 : int(1..3)]), + and([y_ExplicitVarSizeWithDummy[q22] = 6 -> y_ExplicitVarSizeWithDummy[q22 + 1] = 6 | q22 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q23] != 6) | q23 : int(1..4)]), + and([y_ExplicitVarSizeWithDummy[q26] != 6 -> + or([y_ExplicitVarSizeWithFlags_Flags[q28] /\ + y_ExplicitVarSizeWithFlags_Values[q28] = y_ExplicitVarSizeWithDummy[q26] + | q28 : int(1..4)]) + | q26 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q30] -> + or([y_ExplicitVarSizeWithDummy[q32] != 6 /\ + y_ExplicitVarSizeWithDummy[q32] = y_ExplicitVarSizeWithFlags_Values[q30] + | q32 : int(1..4)]) + | q30 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_3_4_2_3-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_3_4_2_3-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_4_2_3-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_3_4_2_3-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_3_4_2_3-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_4_2_3-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_3_4_2_3.eprime b/tests/exhaustive/basic/set09/expected/model_3_4_2_3.eprime new file mode 100644 index 0000000000..0a78494f0e --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_4_2_3.eprime @@ -0,0 +1,58 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_ExplicitVarSizeWithMarker_Marker: int(0..4) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +branching on + [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, + y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithFlags_Flags, + y_ExplicitVarSizeWithFlags_Values] +such that + and([q32 <= x_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithFlags_Flags[q33] -> + x_ExplicitVarSizeWithMarker_Values[q32] + 2 = y_ExplicitVarSizeWithFlags_Values[q33] + | q32 : int(1..4), q33 : int(1..4)]), + and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] + | q1 : int(1..3)]), + and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 2 | q2 : int(1..4)]), + 1 <= x_ExplicitVarSizeWithMarker_Marker, + and([y_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> + y_ExplicitVarSizeWithFlags_Values[q4] < y_ExplicitVarSizeWithFlags_Values[q4 + 1] + | q4 : int(1..3)]), + and([y_ExplicitVarSizeWithFlags_Flags[q5] = false -> y_ExplicitVarSizeWithFlags_Values[q5] = 2 | q5 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q6] | q6 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q7]) | q7 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q9] < x_ExplicitVarSizeWithDummy[q9 + 1] \/ x_ExplicitVarSizeWithDummy[q9] = 6 + | q9 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q10] = 6 -> x_ExplicitVarSizeWithDummy[q10 + 1] = 6 | q10 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q11] != 6) | q11 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q14] != 6 -> + or([q16 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q16] = x_ExplicitVarSizeWithDummy[q14] + | q16 : int(1..4)]) + | q14 : int(1..4)]), + and([q18 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithDummy[q20] != 6 /\ + x_ExplicitVarSizeWithDummy[q20] = x_ExplicitVarSizeWithMarker_Values[q18] + | q20 : int(1..4)]) + | q18 : int(1..4)]), + and([q21 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> + y_ExplicitVarSizeWithMarker_Values[q21] < y_ExplicitVarSizeWithMarker_Values[q21 + 1] + | q21 : int(1..3)]), + and([q22 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q22] = 2 | q22 : int(1..4)]), + 1 <= y_ExplicitVarSizeWithMarker_Marker, + and([q25 <= y_ExplicitVarSizeWithMarker_Marker -> + or([y_ExplicitVarSizeWithFlags_Flags[q27] /\ + y_ExplicitVarSizeWithFlags_Values[q27] = y_ExplicitVarSizeWithMarker_Values[q25] + | q27 : int(1..4)]) + | q25 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q29] -> + or([q31 <= y_ExplicitVarSizeWithMarker_Marker /\ + y_ExplicitVarSizeWithMarker_Values[q31] = y_ExplicitVarSizeWithFlags_Values[q29] + | q31 : int(1..4)]) + | q29 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_3_4_2_4-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_3_4_2_4-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_4_2_4-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_3_4_2_4-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_3_4_2_4-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_4_2_4-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_3_4_2_4.eprime b/tests/exhaustive/basic/set09/expected/model_3_4_2_4.eprime new file mode 100644 index 0000000000..e10ef03824 --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_4_2_4.eprime @@ -0,0 +1,40 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +branching on + [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, + y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values] +such that + and([q21 <= x_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithFlags_Flags[q22] -> + x_ExplicitVarSizeWithMarker_Values[q21] + 2 = y_ExplicitVarSizeWithFlags_Values[q22] + | q21 : int(1..4), q22 : int(1..4)]), + and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] + | q1 : int(1..3)]), + and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 2 | q2 : int(1..4)]), + 1 <= x_ExplicitVarSizeWithMarker_Marker, + and([y_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> + y_ExplicitVarSizeWithFlags_Values[q4] < y_ExplicitVarSizeWithFlags_Values[q4 + 1] + | q4 : int(1..3)]), + and([y_ExplicitVarSizeWithFlags_Flags[q5] = false -> y_ExplicitVarSizeWithFlags_Values[q5] = 2 | q5 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q6] | q6 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q7]) | q7 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q9] < x_ExplicitVarSizeWithDummy[q9 + 1] \/ x_ExplicitVarSizeWithDummy[q9] = 6 + | q9 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q10] = 6 -> x_ExplicitVarSizeWithDummy[q10 + 1] = 6 | q10 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q11] != 6) | q11 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q14] != 6 -> + or([q16 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q16] = x_ExplicitVarSizeWithDummy[q14] + | q16 : int(1..4)]) + | q14 : int(1..4)]), + and([q18 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithDummy[q20] != 6 /\ + x_ExplicitVarSizeWithDummy[q20] = x_ExplicitVarSizeWithMarker_Values[q18] + | q20 : int(1..4)]) + | q18 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_3_4_3_1-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_3_4_3_1-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_4_3_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_3_4_3_1-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_3_4_3_1-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_4_3_1-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_3_4_3_1.eprime b/tests/exhaustive/basic/set09/expected/model_3_4_3_1.eprime new file mode 100644 index 0000000000..d7781435b7 --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_4_3_1.eprime @@ -0,0 +1,32 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_Occurrence: matrix indexed by [int(2..5)] of bool +branching on + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, y_Occurrence, + y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values] +such that + and([q15 <= x_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithFlags_Flags[q16] -> + x_ExplicitVarSizeWithMarker_Values[q15] + 2 = y_ExplicitVarSizeWithFlags_Values[q16] + | q15 : int(1..4), q16 : int(1..4)]), + and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] + | q1 : int(1..3)]), + and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 2 | q2 : int(1..4)]), + 1 <= x_ExplicitVarSizeWithMarker_Marker, + and([y_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> + y_ExplicitVarSizeWithFlags_Values[q4] < y_ExplicitVarSizeWithFlags_Values[q4 + 1] + | q4 : int(1..3)]), + and([y_ExplicitVarSizeWithFlags_Flags[q5] = false -> y_ExplicitVarSizeWithFlags_Values[q5] = 2 | q5 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q6] | q6 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q7]) | q7 : int(1..4)]), + 1 <= sum([toInt(y_Occurrence[q9]) | q9 : int(2..5)]), + and([y_Occurrence[q10] -> + or([y_ExplicitVarSizeWithFlags_Flags[q12] /\ y_ExplicitVarSizeWithFlags_Values[q12] = q10 | q12 : int(1..4)]) + | q10 : int(2..5)]), + and([y_ExplicitVarSizeWithFlags_Flags[q14] -> y_Occurrence[y_ExplicitVarSizeWithFlags_Values[q14]] + | q14 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_3_4_3_2-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_3_4_3_2-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_4_3_2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_3_4_3_2-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_3_4_3_2-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_4_3_2-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_3_4_3_2.eprime b/tests/exhaustive/basic/set09/expected/model_3_4_3_2.eprime new file mode 100644 index 0000000000..2ce2ee5eab --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_4_3_2.eprime @@ -0,0 +1,40 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +branching on + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithDummy, + y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values] +such that + and([q21 <= x_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithFlags_Flags[q22] -> + x_ExplicitVarSizeWithMarker_Values[q21] + 2 = y_ExplicitVarSizeWithFlags_Values[q22] + | q21 : int(1..4), q22 : int(1..4)]), + and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] + | q1 : int(1..3)]), + and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 2 | q2 : int(1..4)]), + 1 <= x_ExplicitVarSizeWithMarker_Marker, + and([y_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> + y_ExplicitVarSizeWithFlags_Values[q4] < y_ExplicitVarSizeWithFlags_Values[q4 + 1] + | q4 : int(1..3)]), + and([y_ExplicitVarSizeWithFlags_Flags[q5] = false -> y_ExplicitVarSizeWithFlags_Values[q5] = 2 | q5 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q6] | q6 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q7]) | q7 : int(1..4)]), + and([y_ExplicitVarSizeWithDummy[q9] < y_ExplicitVarSizeWithDummy[q9 + 1] \/ y_ExplicitVarSizeWithDummy[q9] = 6 + | q9 : int(1..3)]), + and([y_ExplicitVarSizeWithDummy[q10] = 6 -> y_ExplicitVarSizeWithDummy[q10 + 1] = 6 | q10 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q11] != 6) | q11 : int(1..4)]), + and([y_ExplicitVarSizeWithDummy[q14] != 6 -> + or([y_ExplicitVarSizeWithFlags_Flags[q16] /\ + y_ExplicitVarSizeWithFlags_Values[q16] = y_ExplicitVarSizeWithDummy[q14] + | q16 : int(1..4)]) + | q14 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q18] -> + or([y_ExplicitVarSizeWithDummy[q20] != 6 /\ + y_ExplicitVarSizeWithDummy[q20] = y_ExplicitVarSizeWithFlags_Values[q18] + | q20 : int(1..4)]) + | q18 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_3_4_3_3-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_3_4_3_3-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_4_3_3-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_3_4_3_3-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_3_4_3_3-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_4_3_3-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_3_4_3_3.eprime b/tests/exhaustive/basic/set09/expected/model_3_4_3_3.eprime new file mode 100644 index 0000000000..c121faa238 --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_4_3_3.eprime @@ -0,0 +1,42 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_ExplicitVarSizeWithMarker_Marker: int(0..4) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +branching on + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithMarker_Marker, + y_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values] +such that + and([q20 <= x_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithFlags_Flags[q21] -> + x_ExplicitVarSizeWithMarker_Values[q20] + 2 = y_ExplicitVarSizeWithFlags_Values[q21] + | q20 : int(1..4), q21 : int(1..4)]), + and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] + | q1 : int(1..3)]), + and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 2 | q2 : int(1..4)]), + 1 <= x_ExplicitVarSizeWithMarker_Marker, + and([y_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> + y_ExplicitVarSizeWithFlags_Values[q4] < y_ExplicitVarSizeWithFlags_Values[q4 + 1] + | q4 : int(1..3)]), + and([y_ExplicitVarSizeWithFlags_Flags[q5] = false -> y_ExplicitVarSizeWithFlags_Values[q5] = 2 | q5 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q6] | q6 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q7]) | q7 : int(1..4)]), + and([q9 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> + y_ExplicitVarSizeWithMarker_Values[q9] < y_ExplicitVarSizeWithMarker_Values[q9 + 1] + | q9 : int(1..3)]), + and([q10 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q10] = 2 | q10 : int(1..4)]), + 1 <= y_ExplicitVarSizeWithMarker_Marker, + and([q13 <= y_ExplicitVarSizeWithMarker_Marker -> + or([y_ExplicitVarSizeWithFlags_Flags[q15] /\ + y_ExplicitVarSizeWithFlags_Values[q15] = y_ExplicitVarSizeWithMarker_Values[q13] + | q15 : int(1..4)]) + | q13 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q17] -> + or([q19 <= y_ExplicitVarSizeWithMarker_Marker /\ + y_ExplicitVarSizeWithMarker_Values[q19] = y_ExplicitVarSizeWithFlags_Values[q17] + | q19 : int(1..4)]) + | q17 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_3_4_3_4-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_3_4_3_4-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_4_3_4-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_3_4_3_4-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_3_4_3_4-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_4_3_4-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_3_4_3_4.eprime b/tests/exhaustive/basic/set09/expected/model_3_4_3_4.eprime new file mode 100644 index 0000000000..ca62bca40e --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_4_3_4.eprime @@ -0,0 +1,25 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +branching on + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithFlags_Flags, + y_ExplicitVarSizeWithFlags_Values] +such that + and([q9 <= x_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithFlags_Flags[q10] -> + x_ExplicitVarSizeWithMarker_Values[q9] + 2 = y_ExplicitVarSizeWithFlags_Values[q10] + | q9 : int(1..4), q10 : int(1..4)]), + and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] + | q1 : int(1..3)]), + and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 2 | q2 : int(1..4)]), + 1 <= x_ExplicitVarSizeWithMarker_Marker, + and([y_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> + y_ExplicitVarSizeWithFlags_Values[q4] < y_ExplicitVarSizeWithFlags_Values[q4 + 1] + | q4 : int(1..3)]), + and([y_ExplicitVarSizeWithFlags_Flags[q5] = false -> y_ExplicitVarSizeWithFlags_Values[q5] = 2 | q5 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q6] | q6 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q7]) | q7 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_3_4_4_1-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_3_4_4_1-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_4_4_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_3_4_4_1-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_3_4_4_1-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_4_4_1-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_3_4_4_1.eprime b/tests/exhaustive/basic/set09/expected/model_3_4_4_1.eprime new file mode 100644 index 0000000000..196b11abfb --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_4_4_1.eprime @@ -0,0 +1,52 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_Occurrence: matrix indexed by [int(2..5)] of bool +branching on + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithMarker_Marker, + x_ExplicitVarSizeWithMarker_Values, y_Occurrence, y_ExplicitVarSizeWithFlags_Flags, + y_ExplicitVarSizeWithFlags_Values] +such that + and([q28 <= x_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithFlags_Flags[q29] -> + x_ExplicitVarSizeWithMarker_Values[q28] + 2 = y_ExplicitVarSizeWithFlags_Values[q29] + | q28 : int(1..4), q29 : int(1..4)]), + and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] + | q1 : int(1..3)]), + and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 2 | q2 : int(1..4)]), + 1 <= x_ExplicitVarSizeWithMarker_Marker, + and([y_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> + y_ExplicitVarSizeWithFlags_Values[q4] < y_ExplicitVarSizeWithFlags_Values[q4 + 1] + | q4 : int(1..3)]), + and([y_ExplicitVarSizeWithFlags_Flags[q5] = false -> y_ExplicitVarSizeWithFlags_Values[q5] = 2 | q5 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q6] | q6 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q7]) | q7 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q9 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q9] < x_ExplicitVarSizeWithFlags_Values[q9 + 1] + | q9 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q10] = false -> x_ExplicitVarSizeWithFlags_Values[q10] = 2 + | q10 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q11 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q11] | q11 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q12]) | q12 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q15] -> + or([q17 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q17] = x_ExplicitVarSizeWithFlags_Values[q15] + | q17 : int(1..4)]) + | q15 : int(1..4)]), + and([q19 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithFlags_Flags[q21] /\ + x_ExplicitVarSizeWithFlags_Values[q21] = x_ExplicitVarSizeWithMarker_Values[q19] + | q21 : int(1..4)]) + | q19 : int(1..4)]), + 1 <= sum([toInt(y_Occurrence[q22]) | q22 : int(2..5)]), + and([y_Occurrence[q23] -> + or([y_ExplicitVarSizeWithFlags_Flags[q25] /\ y_ExplicitVarSizeWithFlags_Values[q25] = q23 | q25 : int(1..4)]) + | q23 : int(2..5)]), + and([y_ExplicitVarSizeWithFlags_Flags[q27] -> y_Occurrence[y_ExplicitVarSizeWithFlags_Values[q27]] + | q27 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_3_4_4_2-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_3_4_4_2-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_4_4_2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_3_4_4_2-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_3_4_4_2-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_4_4_2-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_3_4_4_2.eprime b/tests/exhaustive/basic/set09/expected/model_3_4_4_2.eprime new file mode 100644 index 0000000000..fe5ba424a2 --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_4_4_2.eprime @@ -0,0 +1,60 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +branching on + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithMarker_Marker, + x_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithDummy, y_ExplicitVarSizeWithFlags_Flags, + y_ExplicitVarSizeWithFlags_Values] +such that + and([q34 <= x_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithFlags_Flags[q35] -> + x_ExplicitVarSizeWithMarker_Values[q34] + 2 = y_ExplicitVarSizeWithFlags_Values[q35] + | q34 : int(1..4), q35 : int(1..4)]), + and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] + | q1 : int(1..3)]), + and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 2 | q2 : int(1..4)]), + 1 <= x_ExplicitVarSizeWithMarker_Marker, + and([y_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> + y_ExplicitVarSizeWithFlags_Values[q4] < y_ExplicitVarSizeWithFlags_Values[q4 + 1] + | q4 : int(1..3)]), + and([y_ExplicitVarSizeWithFlags_Flags[q5] = false -> y_ExplicitVarSizeWithFlags_Values[q5] = 2 | q5 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q6] | q6 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q7]) | q7 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q9 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q9] < x_ExplicitVarSizeWithFlags_Values[q9 + 1] + | q9 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q10] = false -> x_ExplicitVarSizeWithFlags_Values[q10] = 2 + | q10 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q11 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q11] | q11 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q12]) | q12 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q15] -> + or([q17 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q17] = x_ExplicitVarSizeWithFlags_Values[q15] + | q17 : int(1..4)]) + | q15 : int(1..4)]), + and([q19 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithFlags_Flags[q21] /\ + x_ExplicitVarSizeWithFlags_Values[q21] = x_ExplicitVarSizeWithMarker_Values[q19] + | q21 : int(1..4)]) + | q19 : int(1..4)]), + and([y_ExplicitVarSizeWithDummy[q22] < y_ExplicitVarSizeWithDummy[q22 + 1] \/ y_ExplicitVarSizeWithDummy[q22] = 6 + | q22 : int(1..3)]), + and([y_ExplicitVarSizeWithDummy[q23] = 6 -> y_ExplicitVarSizeWithDummy[q23 + 1] = 6 | q23 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q24] != 6) | q24 : int(1..4)]), + and([y_ExplicitVarSizeWithDummy[q27] != 6 -> + or([y_ExplicitVarSizeWithFlags_Flags[q29] /\ + y_ExplicitVarSizeWithFlags_Values[q29] = y_ExplicitVarSizeWithDummy[q27] + | q29 : int(1..4)]) + | q27 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q31] -> + or([y_ExplicitVarSizeWithDummy[q33] != 6 /\ + y_ExplicitVarSizeWithDummy[q33] = y_ExplicitVarSizeWithFlags_Values[q31] + | q33 : int(1..4)]) + | q31 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_3_4_4_3-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_3_4_4_3-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_4_4_3-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_3_4_4_3-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_3_4_4_3-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_4_4_3-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_3_4_4_3.eprime b/tests/exhaustive/basic/set09/expected/model_3_4_4_3.eprime new file mode 100644 index 0000000000..6761996efd --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_4_4_3.eprime @@ -0,0 +1,62 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_ExplicitVarSizeWithMarker_Marker: int(0..4) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +branching on + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithMarker_Marker, + x_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values, + y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values] +such that + and([q33 <= x_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithFlags_Flags[q34] -> + x_ExplicitVarSizeWithMarker_Values[q33] + 2 = y_ExplicitVarSizeWithFlags_Values[q34] + | q33 : int(1..4), q34 : int(1..4)]), + and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] + | q1 : int(1..3)]), + and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 2 | q2 : int(1..4)]), + 1 <= x_ExplicitVarSizeWithMarker_Marker, + and([y_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> + y_ExplicitVarSizeWithFlags_Values[q4] < y_ExplicitVarSizeWithFlags_Values[q4 + 1] + | q4 : int(1..3)]), + and([y_ExplicitVarSizeWithFlags_Flags[q5] = false -> y_ExplicitVarSizeWithFlags_Values[q5] = 2 | q5 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q6] | q6 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q7]) | q7 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q9 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q9] < x_ExplicitVarSizeWithFlags_Values[q9 + 1] + | q9 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q10] = false -> x_ExplicitVarSizeWithFlags_Values[q10] = 2 + | q10 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q11 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q11] | q11 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q12]) | q12 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q15] -> + or([q17 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q17] = x_ExplicitVarSizeWithFlags_Values[q15] + | q17 : int(1..4)]) + | q15 : int(1..4)]), + and([q19 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithFlags_Flags[q21] /\ + x_ExplicitVarSizeWithFlags_Values[q21] = x_ExplicitVarSizeWithMarker_Values[q19] + | q21 : int(1..4)]) + | q19 : int(1..4)]), + and([q22 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> + y_ExplicitVarSizeWithMarker_Values[q22] < y_ExplicitVarSizeWithMarker_Values[q22 + 1] + | q22 : int(1..3)]), + and([q23 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q23] = 2 | q23 : int(1..4)]), + 1 <= y_ExplicitVarSizeWithMarker_Marker, + and([q26 <= y_ExplicitVarSizeWithMarker_Marker -> + or([y_ExplicitVarSizeWithFlags_Flags[q28] /\ + y_ExplicitVarSizeWithFlags_Values[q28] = y_ExplicitVarSizeWithMarker_Values[q26] + | q28 : int(1..4)]) + | q26 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q30] -> + or([q32 <= y_ExplicitVarSizeWithMarker_Marker /\ + y_ExplicitVarSizeWithMarker_Values[q32] = y_ExplicitVarSizeWithFlags_Values[q30] + | q32 : int(1..4)]) + | q30 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_3_4_4_4-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_3_4_4_4-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_4_4_4-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_3_4_4_4-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_3_4_4_4-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_4_4_4-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_3_4_4_4.eprime b/tests/exhaustive/basic/set09/expected/model_3_4_4_4.eprime new file mode 100644 index 0000000000..647b4c3d5f --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_3_4_4_4.eprime @@ -0,0 +1,44 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +branching on + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithMarker_Marker, + x_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values] +such that + and([q22 <= x_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithFlags_Flags[q23] -> + x_ExplicitVarSizeWithMarker_Values[q22] + 2 = y_ExplicitVarSizeWithFlags_Values[q23] + | q22 : int(1..4), q23 : int(1..4)]), + and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] + | q1 : int(1..3)]), + and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 2 | q2 : int(1..4)]), + 1 <= x_ExplicitVarSizeWithMarker_Marker, + and([y_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> + y_ExplicitVarSizeWithFlags_Values[q4] < y_ExplicitVarSizeWithFlags_Values[q4 + 1] + | q4 : int(1..3)]), + and([y_ExplicitVarSizeWithFlags_Flags[q5] = false -> y_ExplicitVarSizeWithFlags_Values[q5] = 2 | q5 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q6] | q6 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q7]) | q7 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q9 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q9] < x_ExplicitVarSizeWithFlags_Values[q9 + 1] + | q9 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q10] = false -> x_ExplicitVarSizeWithFlags_Values[q10] = 2 + | q10 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q11 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q11] | q11 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q12]) | q12 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q15] -> + or([q17 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q17] = x_ExplicitVarSizeWithFlags_Values[q15] + | q17 : int(1..4)]) + | q15 : int(1..4)]), + and([q19 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithFlags_Flags[q21] /\ + x_ExplicitVarSizeWithFlags_Values[q21] = x_ExplicitVarSizeWithMarker_Values[q19] + | q21 : int(1..4)]) + | q19 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_4_1_1_1-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_4_1_1_1-solution000001.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_1_1_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_4_1_1_1-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_4_1_1_1-solution000002.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_1_1_1-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_4_1_1_1.eprime b/tests/exhaustive/basic/set09/expected/model_4_1_1_1.eprime new file mode 100644 index 0000000000..3b3dd72895 --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_1_1_1.eprime @@ -0,0 +1,24 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +find x_Occurrence: matrix indexed by [int(2..5)] of bool +find y_Occurrence: matrix indexed by [int(2..5)] of bool +branching on [x_Occurrence, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, y_Occurrence] +such that + and([x_ExplicitVarSizeWithFlags_Flags[q13] /\ y_Occurrence[j] -> x_ExplicitVarSizeWithFlags_Values[q13] + 2 = j + | q13 : int(1..4), j : int(2..5)]), + and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 2 | q2 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]), + 1 <= sum([toInt(y_Occurrence[q6]) | q6 : int(2..5)]), + 1 <= sum([toInt(x_Occurrence[q7]) | q7 : int(2..5)]), + and([x_Occurrence[q8] -> + or([x_ExplicitVarSizeWithFlags_Flags[q10] /\ x_ExplicitVarSizeWithFlags_Values[q10] = q8 | q10 : int(1..4)]) + | q8 : int(2..5)]), + and([x_ExplicitVarSizeWithFlags_Flags[q12] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q12]] + | q12 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_4_1_1_2-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_4_1_1_2-solution000001.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_1_1_2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_4_1_1_2-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_4_1_1_2-solution000002.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_1_1_2-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_4_1_1_2.eprime b/tests/exhaustive/basic/set09/expected/model_4_1_1_2.eprime new file mode 100644 index 0000000000..c7b6641b99 --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_1_1_2.eprime @@ -0,0 +1,35 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +find x_Occurrence: matrix indexed by [int(2..5)] of bool +find y_Occurrence: matrix indexed by [int(2..5)] of bool +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +branching on + [x_Occurrence, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithDummy, + y_Occurrence] +such that + and([x_ExplicitVarSizeWithFlags_Flags[q22] /\ y_Occurrence[j] -> x_ExplicitVarSizeWithFlags_Values[q22] + 2 = j + | q22 : int(1..4), j : int(2..5)]), + and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 2 | q2 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]), + 1 <= sum([toInt(y_Occurrence[q6]) | q6 : int(2..5)]), + 1 <= sum([toInt(x_Occurrence[q7]) | q7 : int(2..5)]), + and([x_Occurrence[q17] -> + or([x_ExplicitVarSizeWithFlags_Flags[q19] /\ x_ExplicitVarSizeWithFlags_Values[q19] = q17 | q19 : int(1..4)]) + | q17 : int(2..5)]), + and([x_ExplicitVarSizeWithFlags_Flags[q21] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q21]] + | q21 : int(1..4)]), + and([y_ExplicitVarSizeWithDummy[q8] < y_ExplicitVarSizeWithDummy[q8 + 1] \/ y_ExplicitVarSizeWithDummy[q8] = 6 + | q8 : int(1..3)]), + and([y_ExplicitVarSizeWithDummy[q9] = 6 -> y_ExplicitVarSizeWithDummy[q9 + 1] = 6 | q9 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q10] != 6) | q10 : int(1..4)]), + and([y_ExplicitVarSizeWithDummy[q13] != 6 -> y_Occurrence[y_ExplicitVarSizeWithDummy[q13]] | q13 : int(1..4)]), + and([y_Occurrence[q14] -> + or([y_ExplicitVarSizeWithDummy[q16] != 6 /\ y_ExplicitVarSizeWithDummy[q16] = q14 | q16 : int(1..4)]) + | q14 : int(2..5)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_4_1_1_3-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_4_1_1_3-solution000001.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_1_1_3-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_4_1_1_3-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_4_1_1_3-solution000002.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_1_1_3-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_4_1_1_3.eprime b/tests/exhaustive/basic/set09/expected/model_4_1_1_3.eprime new file mode 100644 index 0000000000..8883ffc92f --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_1_1_3.eprime @@ -0,0 +1,39 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +find x_Occurrence: matrix indexed by [int(2..5)] of bool +find y_Occurrence: matrix indexed by [int(2..5)] of bool +find y_ExplicitVarSizeWithMarker_Marker: int(0..4) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +branching on + [x_Occurrence, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, + y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values, y_Occurrence] +such that + and([x_ExplicitVarSizeWithFlags_Flags[q21] /\ y_Occurrence[j] -> x_ExplicitVarSizeWithFlags_Values[q21] + 2 = j + | q21 : int(1..4), j : int(2..5)]), + and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 2 | q2 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]), + 1 <= sum([toInt(y_Occurrence[q6]) | q6 : int(2..5)]), + 1 <= sum([toInt(x_Occurrence[q7]) | q7 : int(2..5)]), + and([x_Occurrence[q16] -> + or([x_ExplicitVarSizeWithFlags_Flags[q18] /\ x_ExplicitVarSizeWithFlags_Values[q18] = q16 | q18 : int(1..4)]) + | q16 : int(2..5)]), + and([x_ExplicitVarSizeWithFlags_Flags[q20] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q20]] + | q20 : int(1..4)]), + and([q8 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> + y_ExplicitVarSizeWithMarker_Values[q8] < y_ExplicitVarSizeWithMarker_Values[q8 + 1] + | q8 : int(1..3)]), + and([q9 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q9] = 2 | q9 : int(1..4)]), + 1 <= y_ExplicitVarSizeWithMarker_Marker, + and([q12 <= y_ExplicitVarSizeWithMarker_Marker -> y_Occurrence[y_ExplicitVarSizeWithMarker_Values[q12]] + | q12 : int(1..4)]), + and([y_Occurrence[q13] -> + or([q15 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[q15] = q13 + | q15 : int(1..4)]) + | q13 : int(2..5)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_4_1_1_4-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_4_1_1_4-solution000001.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_1_1_4-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_4_1_1_4-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_4_1_1_4-solution000002.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_1_1_4-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_4_1_1_4.eprime b/tests/exhaustive/basic/set09/expected/model_4_1_1_4.eprime new file mode 100644 index 0000000000..e566516efd --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_1_1_4.eprime @@ -0,0 +1,39 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +find x_Occurrence: matrix indexed by [int(2..5)] of bool +find y_Occurrence: matrix indexed by [int(2..5)] of bool +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +branching on + [x_Occurrence, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, + y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values, y_Occurrence] +such that + and([x_ExplicitVarSizeWithFlags_Flags[q23] /\ y_Occurrence[j] -> x_ExplicitVarSizeWithFlags_Values[q23] + 2 = j + | q23 : int(1..4), j : int(2..5)]), + and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 2 | q2 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]), + 1 <= sum([toInt(y_Occurrence[q6]) | q6 : int(2..5)]), + 1 <= sum([toInt(x_Occurrence[q7]) | q7 : int(2..5)]), + and([x_Occurrence[q18] -> + or([x_ExplicitVarSizeWithFlags_Flags[q20] /\ x_ExplicitVarSizeWithFlags_Values[q20] = q18 | q20 : int(1..4)]) + | q18 : int(2..5)]), + and([x_ExplicitVarSizeWithFlags_Flags[q22] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q22]] + | q22 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q8 + 1] -> + y_ExplicitVarSizeWithFlags_Values[q8] < y_ExplicitVarSizeWithFlags_Values[q8 + 1] + | q8 : int(1..3)]), + and([y_ExplicitVarSizeWithFlags_Flags[q9] = false -> y_ExplicitVarSizeWithFlags_Values[q9] = 2 | q9 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q10 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q10] | q10 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q11]) | q11 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q14] -> y_Occurrence[y_ExplicitVarSizeWithFlags_Values[q14]] + | q14 : int(1..4)]), + and([y_Occurrence[q15] -> + or([y_ExplicitVarSizeWithFlags_Flags[q17] /\ y_ExplicitVarSizeWithFlags_Values[q17] = q15 | q17 : int(1..4)]) + | q15 : int(2..5)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_4_1_2_1-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_4_1_2_1-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_1_2_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_4_1_2_1-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_4_1_2_1-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_1_2_1-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_4_1_2_1.eprime b/tests/exhaustive/basic/set09/expected/model_4_1_2_1.eprime new file mode 100644 index 0000000000..afaea477ca --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_1_2_1.eprime @@ -0,0 +1,33 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +find y_Occurrence: matrix indexed by [int(2..5)] of bool +branching on + [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, y_Occurrence] +such that + and([x_ExplicitVarSizeWithFlags_Flags[q19] /\ y_Occurrence[j] -> x_ExplicitVarSizeWithFlags_Values[q19] + 2 = j + | q19 : int(1..4), j : int(2..5)]), + and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 2 | q2 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]), + 1 <= sum([toInt(y_Occurrence[q6]) | q6 : int(2..5)]), + and([x_ExplicitVarSizeWithDummy[q7] < x_ExplicitVarSizeWithDummy[q7 + 1] \/ x_ExplicitVarSizeWithDummy[q7] = 6 + | q7 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q8] = 6 -> x_ExplicitVarSizeWithDummy[q8 + 1] = 6 | q8 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q9] != 6) | q9 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q12] != 6 -> + or([x_ExplicitVarSizeWithFlags_Flags[q14] /\ + x_ExplicitVarSizeWithFlags_Values[q14] = x_ExplicitVarSizeWithDummy[q12] + | q14 : int(1..4)]) + | q12 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q16] -> + or([x_ExplicitVarSizeWithDummy[q18] != 6 /\ + x_ExplicitVarSizeWithDummy[q18] = x_ExplicitVarSizeWithFlags_Values[q16] + | q18 : int(1..4)]) + | q16 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_4_1_2_2-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_4_1_2_2-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_1_2_2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_4_1_2_2-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_4_1_2_2-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_1_2_2-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_4_1_2_2.eprime b/tests/exhaustive/basic/set09/expected/model_4_1_2_2.eprime new file mode 100644 index 0000000000..2de99626cb --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_1_2_2.eprime @@ -0,0 +1,43 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +find y_Occurrence: matrix indexed by [int(2..5)] of bool +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +branching on + [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, + y_ExplicitVarSizeWithDummy, y_Occurrence] +such that + and([x_ExplicitVarSizeWithFlags_Flags[q28] /\ y_Occurrence[j] -> x_ExplicitVarSizeWithFlags_Values[q28] + 2 = j + | q28 : int(1..4), j : int(2..5)]), + and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 2 | q2 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]), + 1 <= sum([toInt(y_Occurrence[q6]) | q6 : int(2..5)]), + and([x_ExplicitVarSizeWithDummy[q7] < x_ExplicitVarSizeWithDummy[q7 + 1] \/ x_ExplicitVarSizeWithDummy[q7] = 6 + | q7 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q8] = 6 -> x_ExplicitVarSizeWithDummy[q8 + 1] = 6 | q8 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q9] != 6) | q9 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q12] != 6 -> + or([x_ExplicitVarSizeWithFlags_Flags[q14] /\ + x_ExplicitVarSizeWithFlags_Values[q14] = x_ExplicitVarSizeWithDummy[q12] + | q14 : int(1..4)]) + | q12 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q16] -> + or([x_ExplicitVarSizeWithDummy[q18] != 6 /\ + x_ExplicitVarSizeWithDummy[q18] = x_ExplicitVarSizeWithFlags_Values[q16] + | q18 : int(1..4)]) + | q16 : int(1..4)]), + and([y_ExplicitVarSizeWithDummy[q19] < y_ExplicitVarSizeWithDummy[q19 + 1] \/ y_ExplicitVarSizeWithDummy[q19] = 6 + | q19 : int(1..3)]), + and([y_ExplicitVarSizeWithDummy[q20] = 6 -> y_ExplicitVarSizeWithDummy[q20 + 1] = 6 | q20 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q21] != 6) | q21 : int(1..4)]), + and([y_ExplicitVarSizeWithDummy[q24] != 6 -> y_Occurrence[y_ExplicitVarSizeWithDummy[q24]] | q24 : int(1..4)]), + and([y_Occurrence[q25] -> + or([y_ExplicitVarSizeWithDummy[q27] != 6 /\ y_ExplicitVarSizeWithDummy[q27] = q25 | q27 : int(1..4)]) + | q25 : int(2..5)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_4_1_2_3-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_4_1_2_3-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_1_2_3-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_4_1_2_3-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_4_1_2_3-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_1_2_3-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_4_1_2_3.eprime b/tests/exhaustive/basic/set09/expected/model_4_1_2_3.eprime new file mode 100644 index 0000000000..654da549aa --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_1_2_3.eprime @@ -0,0 +1,47 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +find y_Occurrence: matrix indexed by [int(2..5)] of bool +find y_ExplicitVarSizeWithMarker_Marker: int(0..4) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +branching on + [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, + y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values, y_Occurrence] +such that + and([x_ExplicitVarSizeWithFlags_Flags[q27] /\ y_Occurrence[j] -> x_ExplicitVarSizeWithFlags_Values[q27] + 2 = j + | q27 : int(1..4), j : int(2..5)]), + and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 2 | q2 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]), + 1 <= sum([toInt(y_Occurrence[q6]) | q6 : int(2..5)]), + and([x_ExplicitVarSizeWithDummy[q7] < x_ExplicitVarSizeWithDummy[q7 + 1] \/ x_ExplicitVarSizeWithDummy[q7] = 6 + | q7 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q8] = 6 -> x_ExplicitVarSizeWithDummy[q8 + 1] = 6 | q8 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q9] != 6) | q9 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q12] != 6 -> + or([x_ExplicitVarSizeWithFlags_Flags[q14] /\ + x_ExplicitVarSizeWithFlags_Values[q14] = x_ExplicitVarSizeWithDummy[q12] + | q14 : int(1..4)]) + | q12 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q16] -> + or([x_ExplicitVarSizeWithDummy[q18] != 6 /\ + x_ExplicitVarSizeWithDummy[q18] = x_ExplicitVarSizeWithFlags_Values[q16] + | q18 : int(1..4)]) + | q16 : int(1..4)]), + and([q19 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> + y_ExplicitVarSizeWithMarker_Values[q19] < y_ExplicitVarSizeWithMarker_Values[q19 + 1] + | q19 : int(1..3)]), + and([q20 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q20] = 2 | q20 : int(1..4)]), + 1 <= y_ExplicitVarSizeWithMarker_Marker, + and([q23 <= y_ExplicitVarSizeWithMarker_Marker -> y_Occurrence[y_ExplicitVarSizeWithMarker_Values[q23]] + | q23 : int(1..4)]), + and([y_Occurrence[q24] -> + or([q26 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[q26] = q24 + | q26 : int(1..4)]) + | q24 : int(2..5)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_4_1_2_4-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_4_1_2_4-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_1_2_4-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_4_1_2_4-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_4_1_2_4-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_1_2_4-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_4_1_2_4.eprime b/tests/exhaustive/basic/set09/expected/model_4_1_2_4.eprime new file mode 100644 index 0000000000..af1a93b8b4 --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_1_2_4.eprime @@ -0,0 +1,48 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +find y_Occurrence: matrix indexed by [int(2..5)] of bool +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +branching on + [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, + y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values, y_Occurrence] +such that + and([x_ExplicitVarSizeWithFlags_Flags[q29] /\ y_Occurrence[j] -> x_ExplicitVarSizeWithFlags_Values[q29] + 2 = j + | q29 : int(1..4), j : int(2..5)]), + and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 2 | q2 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]), + 1 <= sum([toInt(y_Occurrence[q6]) | q6 : int(2..5)]), + and([x_ExplicitVarSizeWithDummy[q7] < x_ExplicitVarSizeWithDummy[q7 + 1] \/ x_ExplicitVarSizeWithDummy[q7] = 6 + | q7 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q8] = 6 -> x_ExplicitVarSizeWithDummy[q8 + 1] = 6 | q8 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q9] != 6) | q9 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q12] != 6 -> + or([x_ExplicitVarSizeWithFlags_Flags[q14] /\ + x_ExplicitVarSizeWithFlags_Values[q14] = x_ExplicitVarSizeWithDummy[q12] + | q14 : int(1..4)]) + | q12 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q16] -> + or([x_ExplicitVarSizeWithDummy[q18] != 6 /\ + x_ExplicitVarSizeWithDummy[q18] = x_ExplicitVarSizeWithFlags_Values[q16] + | q18 : int(1..4)]) + | q16 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q19 + 1] -> + y_ExplicitVarSizeWithFlags_Values[q19] < y_ExplicitVarSizeWithFlags_Values[q19 + 1] + | q19 : int(1..3)]), + and([y_ExplicitVarSizeWithFlags_Flags[q20] = false -> y_ExplicitVarSizeWithFlags_Values[q20] = 2 + | q20 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q21 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q21] | q21 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q22]) | q22 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q25] -> y_Occurrence[y_ExplicitVarSizeWithFlags_Values[q25]] + | q25 : int(1..4)]), + and([y_Occurrence[q26] -> + or([y_ExplicitVarSizeWithFlags_Flags[q28] /\ y_ExplicitVarSizeWithFlags_Values[q28] = q26 | q28 : int(1..4)]) + | q26 : int(2..5)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_4_1_3_1-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_4_1_3_1-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_1_3_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_4_1_3_1-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_4_1_3_1-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_1_3_1-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_4_1_3_1.eprime b/tests/exhaustive/basic/set09/expected/model_4_1_3_1.eprime new file mode 100644 index 0000000000..2a4f8d9d12 --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_1_3_1.eprime @@ -0,0 +1,36 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_Occurrence: matrix indexed by [int(2..5)] of bool +branching on + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithFlags_Flags, + x_ExplicitVarSizeWithFlags_Values, y_Occurrence] +such that + and([x_ExplicitVarSizeWithFlags_Flags[q18] /\ y_Occurrence[j] -> x_ExplicitVarSizeWithFlags_Values[q18] + 2 = j + | q18 : int(1..4), j : int(2..5)]), + and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 2 | q2 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]), + 1 <= sum([toInt(y_Occurrence[q6]) | q6 : int(2..5)]), + and([q7 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q7] < x_ExplicitVarSizeWithMarker_Values[q7 + 1] + | q7 : int(1..3)]), + and([q8 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q8] = 2 | q8 : int(1..4)]), + 1 <= x_ExplicitVarSizeWithMarker_Marker, + and([q11 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithFlags_Flags[q13] /\ + x_ExplicitVarSizeWithFlags_Values[q13] = x_ExplicitVarSizeWithMarker_Values[q11] + | q13 : int(1..4)]) + | q11 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q15] -> + or([q17 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q17] = x_ExplicitVarSizeWithFlags_Values[q15] + | q17 : int(1..4)]) + | q15 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_4_1_3_2-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_4_1_3_2-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_1_3_2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_4_1_3_2-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_4_1_3_2-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_1_3_2-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_4_1_3_2.eprime b/tests/exhaustive/basic/set09/expected/model_4_1_3_2.eprime new file mode 100644 index 0000000000..237665c083 --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_1_3_2.eprime @@ -0,0 +1,45 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_Occurrence: matrix indexed by [int(2..5)] of bool +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +branching on + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithFlags_Flags, + x_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithDummy, y_Occurrence] +such that + and([x_ExplicitVarSizeWithFlags_Flags[q27] /\ y_Occurrence[j] -> x_ExplicitVarSizeWithFlags_Values[q27] + 2 = j + | q27 : int(1..4), j : int(2..5)]), + and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 2 | q2 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]), + 1 <= sum([toInt(y_Occurrence[q6]) | q6 : int(2..5)]), + and([q7 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q7] < x_ExplicitVarSizeWithMarker_Values[q7 + 1] + | q7 : int(1..3)]), + and([q8 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q8] = 2 | q8 : int(1..4)]), + 1 <= x_ExplicitVarSizeWithMarker_Marker, + and([q11 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithFlags_Flags[q13] /\ + x_ExplicitVarSizeWithFlags_Values[q13] = x_ExplicitVarSizeWithMarker_Values[q11] + | q13 : int(1..4)]) + | q11 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q15] -> + or([q17 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q17] = x_ExplicitVarSizeWithFlags_Values[q15] + | q17 : int(1..4)]) + | q15 : int(1..4)]), + and([y_ExplicitVarSizeWithDummy[q18] < y_ExplicitVarSizeWithDummy[q18 + 1] \/ y_ExplicitVarSizeWithDummy[q18] = 6 + | q18 : int(1..3)]), + and([y_ExplicitVarSizeWithDummy[q19] = 6 -> y_ExplicitVarSizeWithDummy[q19 + 1] = 6 | q19 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q20] != 6) | q20 : int(1..4)]), + and([y_ExplicitVarSizeWithDummy[q23] != 6 -> y_Occurrence[y_ExplicitVarSizeWithDummy[q23]] | q23 : int(1..4)]), + and([y_Occurrence[q24] -> + or([y_ExplicitVarSizeWithDummy[q26] != 6 /\ y_ExplicitVarSizeWithDummy[q26] = q24 | q26 : int(1..4)]) + | q24 : int(2..5)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_4_1_3_3-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_4_1_3_3-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_1_3_3-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_4_1_3_3-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_4_1_3_3-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_1_3_3-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_4_1_3_3.eprime b/tests/exhaustive/basic/set09/expected/model_4_1_3_3.eprime new file mode 100644 index 0000000000..78ff28ba58 --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_1_3_3.eprime @@ -0,0 +1,50 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_Occurrence: matrix indexed by [int(2..5)] of bool +find y_ExplicitVarSizeWithMarker_Marker: int(0..4) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +branching on + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithFlags_Flags, + x_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values, + y_Occurrence] +such that + and([x_ExplicitVarSizeWithFlags_Flags[q26] /\ y_Occurrence[j] -> x_ExplicitVarSizeWithFlags_Values[q26] + 2 = j + | q26 : int(1..4), j : int(2..5)]), + and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 2 | q2 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]), + 1 <= sum([toInt(y_Occurrence[q6]) | q6 : int(2..5)]), + and([q7 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q7] < x_ExplicitVarSizeWithMarker_Values[q7 + 1] + | q7 : int(1..3)]), + and([q8 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q8] = 2 | q8 : int(1..4)]), + 1 <= x_ExplicitVarSizeWithMarker_Marker, + and([q11 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithFlags_Flags[q13] /\ + x_ExplicitVarSizeWithFlags_Values[q13] = x_ExplicitVarSizeWithMarker_Values[q11] + | q13 : int(1..4)]) + | q11 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q15] -> + or([q17 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q17] = x_ExplicitVarSizeWithFlags_Values[q15] + | q17 : int(1..4)]) + | q15 : int(1..4)]), + and([q18 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> + y_ExplicitVarSizeWithMarker_Values[q18] < y_ExplicitVarSizeWithMarker_Values[q18 + 1] + | q18 : int(1..3)]), + and([q19 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q19] = 2 | q19 : int(1..4)]), + 1 <= y_ExplicitVarSizeWithMarker_Marker, + and([q22 <= y_ExplicitVarSizeWithMarker_Marker -> y_Occurrence[y_ExplicitVarSizeWithMarker_Values[q22]] + | q22 : int(1..4)]), + and([y_Occurrence[q23] -> + or([q25 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[q25] = q23 + | q25 : int(1..4)]) + | q23 : int(2..5)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_4_1_3_4-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_4_1_3_4-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_1_3_4-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_4_1_3_4-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_4_1_3_4-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_1_3_4-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_4_1_3_4.eprime b/tests/exhaustive/basic/set09/expected/model_4_1_3_4.eprime new file mode 100644 index 0000000000..e8221a747a --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_1_3_4.eprime @@ -0,0 +1,51 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_Occurrence: matrix indexed by [int(2..5)] of bool +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +branching on + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithFlags_Flags, + x_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values, + y_Occurrence] +such that + and([x_ExplicitVarSizeWithFlags_Flags[q28] /\ y_Occurrence[j] -> x_ExplicitVarSizeWithFlags_Values[q28] + 2 = j + | q28 : int(1..4), j : int(2..5)]), + and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 2 | q2 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]), + 1 <= sum([toInt(y_Occurrence[q6]) | q6 : int(2..5)]), + and([q7 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q7] < x_ExplicitVarSizeWithMarker_Values[q7 + 1] + | q7 : int(1..3)]), + and([q8 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q8] = 2 | q8 : int(1..4)]), + 1 <= x_ExplicitVarSizeWithMarker_Marker, + and([q11 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithFlags_Flags[q13] /\ + x_ExplicitVarSizeWithFlags_Values[q13] = x_ExplicitVarSizeWithMarker_Values[q11] + | q13 : int(1..4)]) + | q11 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q15] -> + or([q17 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q17] = x_ExplicitVarSizeWithFlags_Values[q15] + | q17 : int(1..4)]) + | q15 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q18 + 1] -> + y_ExplicitVarSizeWithFlags_Values[q18] < y_ExplicitVarSizeWithFlags_Values[q18 + 1] + | q18 : int(1..3)]), + and([y_ExplicitVarSizeWithFlags_Flags[q19] = false -> y_ExplicitVarSizeWithFlags_Values[q19] = 2 + | q19 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q20 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q20] | q20 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q21]) | q21 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q24] -> y_Occurrence[y_ExplicitVarSizeWithFlags_Values[q24]] + | q24 : int(1..4)]), + and([y_Occurrence[q25] -> + or([y_ExplicitVarSizeWithFlags_Flags[q27] /\ y_ExplicitVarSizeWithFlags_Values[q27] = q25 | q27 : int(1..4)]) + | q25 : int(2..5)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_4_1_4_1-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_4_1_4_1-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_1_4_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_4_1_4_1-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_4_1_4_1-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_1_4_1-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_4_1_4_1.eprime b/tests/exhaustive/basic/set09/expected/model_4_1_4_1.eprime new file mode 100644 index 0000000000..109e0f0711 --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_1_4_1.eprime @@ -0,0 +1,17 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_Occurrence: matrix indexed by [int(2..5)] of bool +branching on [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, y_Occurrence] +such that + and([x_ExplicitVarSizeWithFlags_Flags[q7] /\ y_Occurrence[j] -> x_ExplicitVarSizeWithFlags_Values[q7] + 2 = j + | q7 : int(1..4), j : int(2..5)]), + and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 2 | q2 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]), + 1 <= sum([toInt(y_Occurrence[q6]) | q6 : int(2..5)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_4_1_4_2-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_4_1_4_2-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_1_4_2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_4_1_4_2-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_4_1_4_2-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_1_4_2-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_4_1_4_2.eprime b/tests/exhaustive/basic/set09/expected/model_4_1_4_2.eprime new file mode 100644 index 0000000000..76ef2af84d --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_1_4_2.eprime @@ -0,0 +1,27 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_Occurrence: matrix indexed by [int(2..5)] of bool +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +branching on + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithDummy, y_Occurrence] +such that + and([x_ExplicitVarSizeWithFlags_Flags[q16] /\ y_Occurrence[j] -> x_ExplicitVarSizeWithFlags_Values[q16] + 2 = j + | q16 : int(1..4), j : int(2..5)]), + and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 2 | q2 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]), + 1 <= sum([toInt(y_Occurrence[q6]) | q6 : int(2..5)]), + and([y_ExplicitVarSizeWithDummy[q7] < y_ExplicitVarSizeWithDummy[q7 + 1] \/ y_ExplicitVarSizeWithDummy[q7] = 6 + | q7 : int(1..3)]), + and([y_ExplicitVarSizeWithDummy[q8] = 6 -> y_ExplicitVarSizeWithDummy[q8 + 1] = 6 | q8 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q9] != 6) | q9 : int(1..4)]), + and([y_ExplicitVarSizeWithDummy[q12] != 6 -> y_Occurrence[y_ExplicitVarSizeWithDummy[q12]] | q12 : int(1..4)]), + and([y_Occurrence[q13] -> + or([y_ExplicitVarSizeWithDummy[q15] != 6 /\ y_ExplicitVarSizeWithDummy[q15] = q13 | q15 : int(1..4)]) + | q13 : int(2..5)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_4_1_4_3-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_4_1_4_3-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_1_4_3-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_4_1_4_3-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_4_1_4_3-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_1_4_3-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_4_1_4_3.eprime b/tests/exhaustive/basic/set09/expected/model_4_1_4_3.eprime new file mode 100644 index 0000000000..c7bf7b7442 --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_1_4_3.eprime @@ -0,0 +1,32 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_Occurrence: matrix indexed by [int(2..5)] of bool +find y_ExplicitVarSizeWithMarker_Marker: int(0..4) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +branching on + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithMarker_Marker, + y_ExplicitVarSizeWithMarker_Values, y_Occurrence] +such that + and([x_ExplicitVarSizeWithFlags_Flags[q15] /\ y_Occurrence[j] -> x_ExplicitVarSizeWithFlags_Values[q15] + 2 = j + | q15 : int(1..4), j : int(2..5)]), + and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 2 | q2 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]), + 1 <= sum([toInt(y_Occurrence[q6]) | q6 : int(2..5)]), + and([q7 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> + y_ExplicitVarSizeWithMarker_Values[q7] < y_ExplicitVarSizeWithMarker_Values[q7 + 1] + | q7 : int(1..3)]), + and([q8 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q8] = 2 | q8 : int(1..4)]), + 1 <= y_ExplicitVarSizeWithMarker_Marker, + and([q11 <= y_ExplicitVarSizeWithMarker_Marker -> y_Occurrence[y_ExplicitVarSizeWithMarker_Values[q11]] + | q11 : int(1..4)]), + and([y_Occurrence[q12] -> + or([q14 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[q14] = q12 + | q14 : int(1..4)]) + | q12 : int(2..5)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_4_1_4_4-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_4_1_4_4-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_1_4_4-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_4_1_4_4-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_4_1_4_4-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_1_4_4-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_4_1_4_4.eprime b/tests/exhaustive/basic/set09/expected/model_4_1_4_4.eprime new file mode 100644 index 0000000000..8108a5b294 --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_1_4_4.eprime @@ -0,0 +1,32 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_Occurrence: matrix indexed by [int(2..5)] of bool +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +branching on + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithFlags_Flags, + y_ExplicitVarSizeWithFlags_Values, y_Occurrence] +such that + and([x_ExplicitVarSizeWithFlags_Flags[q17] /\ y_Occurrence[j] -> x_ExplicitVarSizeWithFlags_Values[q17] + 2 = j + | q17 : int(1..4), j : int(2..5)]), + and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 2 | q2 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]), + 1 <= sum([toInt(y_Occurrence[q6]) | q6 : int(2..5)]), + and([y_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> + y_ExplicitVarSizeWithFlags_Values[q7] < y_ExplicitVarSizeWithFlags_Values[q7 + 1] + | q7 : int(1..3)]), + and([y_ExplicitVarSizeWithFlags_Flags[q8] = false -> y_ExplicitVarSizeWithFlags_Values[q8] = 2 | q8 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q9 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q9] | q9 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q10]) | q10 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q13] -> y_Occurrence[y_ExplicitVarSizeWithFlags_Values[q13]] + | q13 : int(1..4)]), + and([y_Occurrence[q14] -> + or([y_ExplicitVarSizeWithFlags_Flags[q16] /\ y_ExplicitVarSizeWithFlags_Values[q16] = q14 | q16 : int(1..4)]) + | q14 : int(2..5)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_4_2_1_1-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_4_2_1_1-solution000001.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_2_1_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_4_2_1_1-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_4_2_1_1-solution000002.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_2_1_1-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_4_2_1_1.eprime b/tests/exhaustive/basic/set09/expected/model_4_2_1_1.eprime new file mode 100644 index 0000000000..58ed3249aa --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_2_1_1.eprime @@ -0,0 +1,36 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +find x_Occurrence: matrix indexed by [int(2..5)] of bool +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +find y_Occurrence: matrix indexed by [int(2..5)] of bool +branching on + [x_Occurrence, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, y_Occurrence, + y_ExplicitVarSizeWithDummy] +such that + and([x_ExplicitVarSizeWithFlags_Flags[q17] /\ y_ExplicitVarSizeWithDummy[q18] != 6 -> + x_ExplicitVarSizeWithFlags_Values[q17] + 2 = y_ExplicitVarSizeWithDummy[q18] + | q17 : int(1..4), q18 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 2 | q2 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]), + and([y_ExplicitVarSizeWithDummy[q6] < y_ExplicitVarSizeWithDummy[q6 + 1] \/ y_ExplicitVarSizeWithDummy[q6] = 6 + | q6 : int(1..3)]), + and([y_ExplicitVarSizeWithDummy[q7] = 6 -> y_ExplicitVarSizeWithDummy[q7 + 1] = 6 | q7 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q8] != 6) | q8 : int(1..4)]), + 1 <= sum([toInt(x_Occurrence[q10]) | q10 : int(2..5)]), + and([x_Occurrence[q19] -> + or([x_ExplicitVarSizeWithFlags_Flags[q21] /\ x_ExplicitVarSizeWithFlags_Values[q21] = q19 | q21 : int(1..4)]) + | q19 : int(2..5)]), + and([x_ExplicitVarSizeWithFlags_Flags[q23] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q23]] + | q23 : int(1..4)]), + 1 <= sum([toInt(y_Occurrence[q11]) | q11 : int(2..5)]), + and([y_Occurrence[q12] -> + or([y_ExplicitVarSizeWithDummy[q14] != 6 /\ y_ExplicitVarSizeWithDummy[q14] = q12 | q14 : int(1..4)]) + | q12 : int(2..5)]), + and([y_ExplicitVarSizeWithDummy[q16] != 6 -> y_Occurrence[y_ExplicitVarSizeWithDummy[q16]] | q16 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_4_2_1_2-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_4_2_1_2-solution000001.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_2_1_2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_4_2_1_2-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_4_2_1_2-solution000002.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_2_1_2-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_4_2_1_2.eprime b/tests/exhaustive/basic/set09/expected/model_4_2_1_2.eprime new file mode 100644 index 0000000000..b326331c8d --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_2_1_2.eprime @@ -0,0 +1,29 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +find x_Occurrence: matrix indexed by [int(2..5)] of bool +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +branching on + [x_Occurrence, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithDummy] +such that + and([x_ExplicitVarSizeWithFlags_Flags[q16] /\ y_ExplicitVarSizeWithDummy[q17] != 6 -> + x_ExplicitVarSizeWithFlags_Values[q16] + 2 = y_ExplicitVarSizeWithDummy[q17] + | q16 : int(1..4), q17 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 2 | q2 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]), + and([y_ExplicitVarSizeWithDummy[q6] < y_ExplicitVarSizeWithDummy[q6 + 1] \/ y_ExplicitVarSizeWithDummy[q6] = 6 + | q6 : int(1..3)]), + and([y_ExplicitVarSizeWithDummy[q7] = 6 -> y_ExplicitVarSizeWithDummy[q7 + 1] = 6 | q7 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q8] != 6) | q8 : int(1..4)]), + 1 <= sum([toInt(x_Occurrence[q10]) | q10 : int(2..5)]), + and([x_Occurrence[q11] -> + or([x_ExplicitVarSizeWithFlags_Flags[q13] /\ x_ExplicitVarSizeWithFlags_Values[q13] = q11 | q13 : int(1..4)]) + | q11 : int(2..5)]), + and([x_ExplicitVarSizeWithFlags_Flags[q15] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q15]] + | q15 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_4_2_1_3-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_4_2_1_3-solution000001.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_2_1_3-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_4_2_1_3-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_4_2_1_3-solution000002.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_2_1_3-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_4_2_1_3.eprime b/tests/exhaustive/basic/set09/expected/model_4_2_1_3.eprime new file mode 100644 index 0000000000..10b83edfd1 --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_2_1_3.eprime @@ -0,0 +1,47 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +find x_Occurrence: matrix indexed by [int(2..5)] of bool +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +find y_ExplicitVarSizeWithMarker_Marker: int(0..4) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +branching on + [x_Occurrence, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, + y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithDummy] +such that + and([x_ExplicitVarSizeWithFlags_Flags[q27] /\ y_ExplicitVarSizeWithDummy[q28] != 6 -> + x_ExplicitVarSizeWithFlags_Values[q27] + 2 = y_ExplicitVarSizeWithDummy[q28] + | q27 : int(1..4), q28 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 2 | q2 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]), + and([y_ExplicitVarSizeWithDummy[q6] < y_ExplicitVarSizeWithDummy[q6 + 1] \/ y_ExplicitVarSizeWithDummy[q6] = 6 + | q6 : int(1..3)]), + and([y_ExplicitVarSizeWithDummy[q7] = 6 -> y_ExplicitVarSizeWithDummy[q7 + 1] = 6 | q7 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q8] != 6) | q8 : int(1..4)]), + 1 <= sum([toInt(x_Occurrence[q10]) | q10 : int(2..5)]), + and([x_Occurrence[q22] -> + or([x_ExplicitVarSizeWithFlags_Flags[q24] /\ x_ExplicitVarSizeWithFlags_Values[q24] = q22 | q24 : int(1..4)]) + | q22 : int(2..5)]), + and([x_ExplicitVarSizeWithFlags_Flags[q26] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q26]] + | q26 : int(1..4)]), + and([q11 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> + y_ExplicitVarSizeWithMarker_Values[q11] < y_ExplicitVarSizeWithMarker_Values[q11 + 1] + | q11 : int(1..3)]), + and([q12 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q12] = 2 | q12 : int(1..4)]), + 1 <= y_ExplicitVarSizeWithMarker_Marker, + and([q15 <= y_ExplicitVarSizeWithMarker_Marker -> + or([y_ExplicitVarSizeWithDummy[q17] != 6 /\ + y_ExplicitVarSizeWithDummy[q17] = y_ExplicitVarSizeWithMarker_Values[q15] + | q17 : int(1..4)]) + | q15 : int(1..4)]), + and([y_ExplicitVarSizeWithDummy[q19] != 6 -> + or([q21 <= y_ExplicitVarSizeWithMarker_Marker /\ + y_ExplicitVarSizeWithMarker_Values[q21] = y_ExplicitVarSizeWithDummy[q19] + | q21 : int(1..4)]) + | q19 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_4_2_1_4-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_4_2_1_4-solution000001.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_2_1_4-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_4_2_1_4-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_4_2_1_4-solution000002.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_2_1_4-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_4_2_1_4.eprime b/tests/exhaustive/basic/set09/expected/model_4_2_1_4.eprime new file mode 100644 index 0000000000..9b32a426d0 --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_2_1_4.eprime @@ -0,0 +1,49 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +find x_Occurrence: matrix indexed by [int(2..5)] of bool +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +branching on + [x_Occurrence, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, + y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithDummy] +such that + and([x_ExplicitVarSizeWithFlags_Flags[q29] /\ y_ExplicitVarSizeWithDummy[q30] != 6 -> + x_ExplicitVarSizeWithFlags_Values[q29] + 2 = y_ExplicitVarSizeWithDummy[q30] + | q29 : int(1..4), q30 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 2 | q2 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]), + and([y_ExplicitVarSizeWithDummy[q6] < y_ExplicitVarSizeWithDummy[q6 + 1] \/ y_ExplicitVarSizeWithDummy[q6] = 6 + | q6 : int(1..3)]), + and([y_ExplicitVarSizeWithDummy[q7] = 6 -> y_ExplicitVarSizeWithDummy[q7 + 1] = 6 | q7 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q8] != 6) | q8 : int(1..4)]), + 1 <= sum([toInt(x_Occurrence[q10]) | q10 : int(2..5)]), + and([x_Occurrence[q24] -> + or([x_ExplicitVarSizeWithFlags_Flags[q26] /\ x_ExplicitVarSizeWithFlags_Values[q26] = q24 | q26 : int(1..4)]) + | q24 : int(2..5)]), + and([x_ExplicitVarSizeWithFlags_Flags[q28] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q28]] + | q28 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q11 + 1] -> + y_ExplicitVarSizeWithFlags_Values[q11] < y_ExplicitVarSizeWithFlags_Values[q11 + 1] + | q11 : int(1..3)]), + and([y_ExplicitVarSizeWithFlags_Flags[q12] = false -> y_ExplicitVarSizeWithFlags_Values[q12] = 2 + | q12 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q13 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q13] | q13 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q14]) | q14 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q17] -> + or([y_ExplicitVarSizeWithDummy[q19] != 6 /\ + y_ExplicitVarSizeWithDummy[q19] = y_ExplicitVarSizeWithFlags_Values[q17] + | q19 : int(1..4)]) + | q17 : int(1..4)]), + and([y_ExplicitVarSizeWithDummy[q21] != 6 -> + or([y_ExplicitVarSizeWithFlags_Flags[q23] /\ + y_ExplicitVarSizeWithFlags_Values[q23] = y_ExplicitVarSizeWithDummy[q21] + | q23 : int(1..4)]) + | q21 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_4_2_2_1-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_4_2_2_1-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_2_2_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_4_2_2_1-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_4_2_2_1-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_2_2_1-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_4_2_2_1.eprime b/tests/exhaustive/basic/set09/expected/model_4_2_2_1.eprime new file mode 100644 index 0000000000..04f00777cf --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_2_2_1.eprime @@ -0,0 +1,44 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +find y_Occurrence: matrix indexed by [int(2..5)] of bool +branching on + [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, y_Occurrence, + y_ExplicitVarSizeWithDummy] +such that + and([x_ExplicitVarSizeWithFlags_Flags[q28] /\ y_ExplicitVarSizeWithDummy[q29] != 6 -> + x_ExplicitVarSizeWithFlags_Values[q28] + 2 = y_ExplicitVarSizeWithDummy[q29] + | q28 : int(1..4), q29 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 2 | q2 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]), + and([y_ExplicitVarSizeWithDummy[q6] < y_ExplicitVarSizeWithDummy[q6 + 1] \/ y_ExplicitVarSizeWithDummy[q6] = 6 + | q6 : int(1..3)]), + and([y_ExplicitVarSizeWithDummy[q7] = 6 -> y_ExplicitVarSizeWithDummy[q7 + 1] = 6 | q7 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q8] != 6) | q8 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q10] < x_ExplicitVarSizeWithDummy[q10 + 1] \/ x_ExplicitVarSizeWithDummy[q10] = 6 + | q10 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q11] = 6 -> x_ExplicitVarSizeWithDummy[q11 + 1] = 6 | q11 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q12] != 6) | q12 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q15] != 6 -> + or([x_ExplicitVarSizeWithFlags_Flags[q17] /\ + x_ExplicitVarSizeWithFlags_Values[q17] = x_ExplicitVarSizeWithDummy[q15] + | q17 : int(1..4)]) + | q15 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q19] -> + or([x_ExplicitVarSizeWithDummy[q21] != 6 /\ + x_ExplicitVarSizeWithDummy[q21] = x_ExplicitVarSizeWithFlags_Values[q19] + | q21 : int(1..4)]) + | q19 : int(1..4)]), + 1 <= sum([toInt(y_Occurrence[q22]) | q22 : int(2..5)]), + and([y_Occurrence[q23] -> + or([y_ExplicitVarSizeWithDummy[q25] != 6 /\ y_ExplicitVarSizeWithDummy[q25] = q23 | q25 : int(1..4)]) + | q23 : int(2..5)]), + and([y_ExplicitVarSizeWithDummy[q27] != 6 -> y_Occurrence[y_ExplicitVarSizeWithDummy[q27]] | q27 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_4_2_2_2-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_4_2_2_2-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_2_2_2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_4_2_2_2-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_4_2_2_2-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_2_2_2-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_4_2_2_2.eprime b/tests/exhaustive/basic/set09/expected/model_4_2_2_2.eprime new file mode 100644 index 0000000000..6d1e92a973 --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_2_2_2.eprime @@ -0,0 +1,38 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +branching on + [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, + y_ExplicitVarSizeWithDummy] +such that + and([x_ExplicitVarSizeWithFlags_Flags[q22] /\ y_ExplicitVarSizeWithDummy[q23] != 6 -> + x_ExplicitVarSizeWithFlags_Values[q22] + 2 = y_ExplicitVarSizeWithDummy[q23] + | q22 : int(1..4), q23 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 2 | q2 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]), + and([y_ExplicitVarSizeWithDummy[q6] < y_ExplicitVarSizeWithDummy[q6 + 1] \/ y_ExplicitVarSizeWithDummy[q6] = 6 + | q6 : int(1..3)]), + and([y_ExplicitVarSizeWithDummy[q7] = 6 -> y_ExplicitVarSizeWithDummy[q7 + 1] = 6 | q7 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q8] != 6) | q8 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q10] < x_ExplicitVarSizeWithDummy[q10 + 1] \/ x_ExplicitVarSizeWithDummy[q10] = 6 + | q10 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q11] = 6 -> x_ExplicitVarSizeWithDummy[q11 + 1] = 6 | q11 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q12] != 6) | q12 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q15] != 6 -> + or([x_ExplicitVarSizeWithFlags_Flags[q17] /\ + x_ExplicitVarSizeWithFlags_Values[q17] = x_ExplicitVarSizeWithDummy[q15] + | q17 : int(1..4)]) + | q15 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q19] -> + or([x_ExplicitVarSizeWithDummy[q21] != 6 /\ + x_ExplicitVarSizeWithDummy[q21] = x_ExplicitVarSizeWithFlags_Values[q19] + | q21 : int(1..4)]) + | q19 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_4_2_2_3-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_4_2_2_3-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_2_2_3-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_4_2_2_3-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_4_2_2_3-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_2_2_3-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_4_2_2_3.eprime b/tests/exhaustive/basic/set09/expected/model_4_2_2_3.eprime new file mode 100644 index 0000000000..10a511c037 --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_2_2_3.eprime @@ -0,0 +1,55 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +find y_ExplicitVarSizeWithMarker_Marker: int(0..4) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +branching on + [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, + y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithDummy] +such that + and([x_ExplicitVarSizeWithFlags_Flags[q33] /\ y_ExplicitVarSizeWithDummy[q34] != 6 -> + x_ExplicitVarSizeWithFlags_Values[q33] + 2 = y_ExplicitVarSizeWithDummy[q34] + | q33 : int(1..4), q34 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 2 | q2 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]), + and([y_ExplicitVarSizeWithDummy[q6] < y_ExplicitVarSizeWithDummy[q6 + 1] \/ y_ExplicitVarSizeWithDummy[q6] = 6 + | q6 : int(1..3)]), + and([y_ExplicitVarSizeWithDummy[q7] = 6 -> y_ExplicitVarSizeWithDummy[q7 + 1] = 6 | q7 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q8] != 6) | q8 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q10] < x_ExplicitVarSizeWithDummy[q10 + 1] \/ x_ExplicitVarSizeWithDummy[q10] = 6 + | q10 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q11] = 6 -> x_ExplicitVarSizeWithDummy[q11 + 1] = 6 | q11 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q12] != 6) | q12 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q15] != 6 -> + or([x_ExplicitVarSizeWithFlags_Flags[q17] /\ + x_ExplicitVarSizeWithFlags_Values[q17] = x_ExplicitVarSizeWithDummy[q15] + | q17 : int(1..4)]) + | q15 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q19] -> + or([x_ExplicitVarSizeWithDummy[q21] != 6 /\ + x_ExplicitVarSizeWithDummy[q21] = x_ExplicitVarSizeWithFlags_Values[q19] + | q21 : int(1..4)]) + | q19 : int(1..4)]), + and([q22 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> + y_ExplicitVarSizeWithMarker_Values[q22] < y_ExplicitVarSizeWithMarker_Values[q22 + 1] + | q22 : int(1..3)]), + and([q23 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q23] = 2 | q23 : int(1..4)]), + 1 <= y_ExplicitVarSizeWithMarker_Marker, + and([q26 <= y_ExplicitVarSizeWithMarker_Marker -> + or([y_ExplicitVarSizeWithDummy[q28] != 6 /\ + y_ExplicitVarSizeWithDummy[q28] = y_ExplicitVarSizeWithMarker_Values[q26] + | q28 : int(1..4)]) + | q26 : int(1..4)]), + and([y_ExplicitVarSizeWithDummy[q30] != 6 -> + or([q32 <= y_ExplicitVarSizeWithMarker_Marker /\ + y_ExplicitVarSizeWithMarker_Values[q32] = y_ExplicitVarSizeWithDummy[q30] + | q32 : int(1..4)]) + | q30 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_4_2_2_4-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_4_2_2_4-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_2_2_4-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_4_2_2_4-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_4_2_2_4-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_2_2_4-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_4_2_2_4.eprime b/tests/exhaustive/basic/set09/expected/model_4_2_2_4.eprime new file mode 100644 index 0000000000..fbaabfe3f8 --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_2_2_4.eprime @@ -0,0 +1,57 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +branching on + [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, + y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithDummy] +such that + and([x_ExplicitVarSizeWithFlags_Flags[q35] /\ y_ExplicitVarSizeWithDummy[q36] != 6 -> + x_ExplicitVarSizeWithFlags_Values[q35] + 2 = y_ExplicitVarSizeWithDummy[q36] + | q35 : int(1..4), q36 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 2 | q2 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]), + and([y_ExplicitVarSizeWithDummy[q6] < y_ExplicitVarSizeWithDummy[q6 + 1] \/ y_ExplicitVarSizeWithDummy[q6] = 6 + | q6 : int(1..3)]), + and([y_ExplicitVarSizeWithDummy[q7] = 6 -> y_ExplicitVarSizeWithDummy[q7 + 1] = 6 | q7 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q8] != 6) | q8 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q10] < x_ExplicitVarSizeWithDummy[q10 + 1] \/ x_ExplicitVarSizeWithDummy[q10] = 6 + | q10 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q11] = 6 -> x_ExplicitVarSizeWithDummy[q11 + 1] = 6 | q11 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q12] != 6) | q12 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q15] != 6 -> + or([x_ExplicitVarSizeWithFlags_Flags[q17] /\ + x_ExplicitVarSizeWithFlags_Values[q17] = x_ExplicitVarSizeWithDummy[q15] + | q17 : int(1..4)]) + | q15 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q19] -> + or([x_ExplicitVarSizeWithDummy[q21] != 6 /\ + x_ExplicitVarSizeWithDummy[q21] = x_ExplicitVarSizeWithFlags_Values[q19] + | q21 : int(1..4)]) + | q19 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q22 + 1] -> + y_ExplicitVarSizeWithFlags_Values[q22] < y_ExplicitVarSizeWithFlags_Values[q22 + 1] + | q22 : int(1..3)]), + and([y_ExplicitVarSizeWithFlags_Flags[q23] = false -> y_ExplicitVarSizeWithFlags_Values[q23] = 2 + | q23 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q24 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q24] | q24 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q25]) | q25 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q28] -> + or([y_ExplicitVarSizeWithDummy[q30] != 6 /\ + y_ExplicitVarSizeWithDummy[q30] = y_ExplicitVarSizeWithFlags_Values[q28] + | q30 : int(1..4)]) + | q28 : int(1..4)]), + and([y_ExplicitVarSizeWithDummy[q32] != 6 -> + or([y_ExplicitVarSizeWithFlags_Flags[q34] /\ + y_ExplicitVarSizeWithFlags_Values[q34] = y_ExplicitVarSizeWithDummy[q32] + | q34 : int(1..4)]) + | q32 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_4_2_3_1-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_4_2_3_1-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_2_3_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_4_2_3_1-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_4_2_3_1-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_2_3_1-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_4_2_3_1.eprime b/tests/exhaustive/basic/set09/expected/model_4_2_3_1.eprime new file mode 100644 index 0000000000..457cc6deb1 --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_2_3_1.eprime @@ -0,0 +1,46 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +find y_Occurrence: matrix indexed by [int(2..5)] of bool +branching on + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithFlags_Flags, + x_ExplicitVarSizeWithFlags_Values, y_Occurrence, y_ExplicitVarSizeWithDummy] +such that + and([x_ExplicitVarSizeWithFlags_Flags[q27] /\ y_ExplicitVarSizeWithDummy[q28] != 6 -> + x_ExplicitVarSizeWithFlags_Values[q27] + 2 = y_ExplicitVarSizeWithDummy[q28] + | q27 : int(1..4), q28 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 2 | q2 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]), + and([y_ExplicitVarSizeWithDummy[q6] < y_ExplicitVarSizeWithDummy[q6 + 1] \/ y_ExplicitVarSizeWithDummy[q6] = 6 + | q6 : int(1..3)]), + and([y_ExplicitVarSizeWithDummy[q7] = 6 -> y_ExplicitVarSizeWithDummy[q7 + 1] = 6 | q7 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q8] != 6) | q8 : int(1..4)]), + and([q10 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q10] < x_ExplicitVarSizeWithMarker_Values[q10 + 1] + | q10 : int(1..3)]), + and([q11 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q11] = 2 | q11 : int(1..4)]), + 1 <= x_ExplicitVarSizeWithMarker_Marker, + and([q14 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithFlags_Flags[q16] /\ + x_ExplicitVarSizeWithFlags_Values[q16] = x_ExplicitVarSizeWithMarker_Values[q14] + | q16 : int(1..4)]) + | q14 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q18] -> + or([q20 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q20] = x_ExplicitVarSizeWithFlags_Values[q18] + | q20 : int(1..4)]) + | q18 : int(1..4)]), + 1 <= sum([toInt(y_Occurrence[q21]) | q21 : int(2..5)]), + and([y_Occurrence[q22] -> + or([y_ExplicitVarSizeWithDummy[q24] != 6 /\ y_ExplicitVarSizeWithDummy[q24] = q22 | q24 : int(1..4)]) + | q22 : int(2..5)]), + and([y_ExplicitVarSizeWithDummy[q26] != 6 -> y_Occurrence[y_ExplicitVarSizeWithDummy[q26]] | q26 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_4_2_3_2-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_4_2_3_2-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_2_3_2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_4_2_3_2-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_4_2_3_2-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_2_3_2-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_4_2_3_2.eprime b/tests/exhaustive/basic/set09/expected/model_4_2_3_2.eprime new file mode 100644 index 0000000000..1fdcd43cc3 --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_2_3_2.eprime @@ -0,0 +1,40 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +branching on + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithFlags_Flags, + x_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithDummy] +such that + and([x_ExplicitVarSizeWithFlags_Flags[q21] /\ y_ExplicitVarSizeWithDummy[q22] != 6 -> + x_ExplicitVarSizeWithFlags_Values[q21] + 2 = y_ExplicitVarSizeWithDummy[q22] + | q21 : int(1..4), q22 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 2 | q2 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]), + and([y_ExplicitVarSizeWithDummy[q6] < y_ExplicitVarSizeWithDummy[q6 + 1] \/ y_ExplicitVarSizeWithDummy[q6] = 6 + | q6 : int(1..3)]), + and([y_ExplicitVarSizeWithDummy[q7] = 6 -> y_ExplicitVarSizeWithDummy[q7 + 1] = 6 | q7 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q8] != 6) | q8 : int(1..4)]), + and([q10 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q10] < x_ExplicitVarSizeWithMarker_Values[q10 + 1] + | q10 : int(1..3)]), + and([q11 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q11] = 2 | q11 : int(1..4)]), + 1 <= x_ExplicitVarSizeWithMarker_Marker, + and([q14 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithFlags_Flags[q16] /\ + x_ExplicitVarSizeWithFlags_Values[q16] = x_ExplicitVarSizeWithMarker_Values[q14] + | q16 : int(1..4)]) + | q14 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q18] -> + or([q20 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q20] = x_ExplicitVarSizeWithFlags_Values[q18] + | q20 : int(1..4)]) + | q18 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_4_2_3_3-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_4_2_3_3-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_2_3_3-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_4_2_3_3-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_4_2_3_3-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_2_3_3-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_4_2_3_3.eprime b/tests/exhaustive/basic/set09/expected/model_4_2_3_3.eprime new file mode 100644 index 0000000000..18c16908d3 --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_2_3_3.eprime @@ -0,0 +1,58 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +find y_ExplicitVarSizeWithMarker_Marker: int(0..4) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +branching on + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithFlags_Flags, + x_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values, + y_ExplicitVarSizeWithDummy] +such that + and([x_ExplicitVarSizeWithFlags_Flags[q32] /\ y_ExplicitVarSizeWithDummy[q33] != 6 -> + x_ExplicitVarSizeWithFlags_Values[q32] + 2 = y_ExplicitVarSizeWithDummy[q33] + | q32 : int(1..4), q33 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 2 | q2 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]), + and([y_ExplicitVarSizeWithDummy[q6] < y_ExplicitVarSizeWithDummy[q6 + 1] \/ y_ExplicitVarSizeWithDummy[q6] = 6 + | q6 : int(1..3)]), + and([y_ExplicitVarSizeWithDummy[q7] = 6 -> y_ExplicitVarSizeWithDummy[q7 + 1] = 6 | q7 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q8] != 6) | q8 : int(1..4)]), + and([q10 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q10] < x_ExplicitVarSizeWithMarker_Values[q10 + 1] + | q10 : int(1..3)]), + and([q11 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q11] = 2 | q11 : int(1..4)]), + 1 <= x_ExplicitVarSizeWithMarker_Marker, + and([q14 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithFlags_Flags[q16] /\ + x_ExplicitVarSizeWithFlags_Values[q16] = x_ExplicitVarSizeWithMarker_Values[q14] + | q16 : int(1..4)]) + | q14 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q18] -> + or([q20 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q20] = x_ExplicitVarSizeWithFlags_Values[q18] + | q20 : int(1..4)]) + | q18 : int(1..4)]), + and([q21 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> + y_ExplicitVarSizeWithMarker_Values[q21] < y_ExplicitVarSizeWithMarker_Values[q21 + 1] + | q21 : int(1..3)]), + and([q22 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q22] = 2 | q22 : int(1..4)]), + 1 <= y_ExplicitVarSizeWithMarker_Marker, + and([q25 <= y_ExplicitVarSizeWithMarker_Marker -> + or([y_ExplicitVarSizeWithDummy[q27] != 6 /\ + y_ExplicitVarSizeWithDummy[q27] = y_ExplicitVarSizeWithMarker_Values[q25] + | q27 : int(1..4)]) + | q25 : int(1..4)]), + and([y_ExplicitVarSizeWithDummy[q29] != 6 -> + or([q31 <= y_ExplicitVarSizeWithMarker_Marker /\ + y_ExplicitVarSizeWithMarker_Values[q31] = y_ExplicitVarSizeWithDummy[q29] + | q31 : int(1..4)]) + | q29 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_4_2_3_4-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_4_2_3_4-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_2_3_4-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_4_2_3_4-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_4_2_3_4-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_2_3_4-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_4_2_3_4.eprime b/tests/exhaustive/basic/set09/expected/model_4_2_3_4.eprime new file mode 100644 index 0000000000..d099b0582b --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_2_3_4.eprime @@ -0,0 +1,60 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +branching on + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithFlags_Flags, + x_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values, + y_ExplicitVarSizeWithDummy] +such that + and([x_ExplicitVarSizeWithFlags_Flags[q34] /\ y_ExplicitVarSizeWithDummy[q35] != 6 -> + x_ExplicitVarSizeWithFlags_Values[q34] + 2 = y_ExplicitVarSizeWithDummy[q35] + | q34 : int(1..4), q35 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 2 | q2 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]), + and([y_ExplicitVarSizeWithDummy[q6] < y_ExplicitVarSizeWithDummy[q6 + 1] \/ y_ExplicitVarSizeWithDummy[q6] = 6 + | q6 : int(1..3)]), + and([y_ExplicitVarSizeWithDummy[q7] = 6 -> y_ExplicitVarSizeWithDummy[q7 + 1] = 6 | q7 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q8] != 6) | q8 : int(1..4)]), + and([q10 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q10] < x_ExplicitVarSizeWithMarker_Values[q10 + 1] + | q10 : int(1..3)]), + and([q11 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q11] = 2 | q11 : int(1..4)]), + 1 <= x_ExplicitVarSizeWithMarker_Marker, + and([q14 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithFlags_Flags[q16] /\ + x_ExplicitVarSizeWithFlags_Values[q16] = x_ExplicitVarSizeWithMarker_Values[q14] + | q16 : int(1..4)]) + | q14 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q18] -> + or([q20 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q20] = x_ExplicitVarSizeWithFlags_Values[q18] + | q20 : int(1..4)]) + | q18 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q21 + 1] -> + y_ExplicitVarSizeWithFlags_Values[q21] < y_ExplicitVarSizeWithFlags_Values[q21 + 1] + | q21 : int(1..3)]), + and([y_ExplicitVarSizeWithFlags_Flags[q22] = false -> y_ExplicitVarSizeWithFlags_Values[q22] = 2 + | q22 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q23 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q23] | q23 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q24]) | q24 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q27] -> + or([y_ExplicitVarSizeWithDummy[q29] != 6 /\ + y_ExplicitVarSizeWithDummy[q29] = y_ExplicitVarSizeWithFlags_Values[q27] + | q29 : int(1..4)]) + | q27 : int(1..4)]), + and([y_ExplicitVarSizeWithDummy[q31] != 6 -> + or([y_ExplicitVarSizeWithFlags_Flags[q33] /\ + y_ExplicitVarSizeWithFlags_Values[q33] = y_ExplicitVarSizeWithDummy[q31] + | q33 : int(1..4)]) + | q31 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_4_2_4_1-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_4_2_4_1-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_2_4_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_4_2_4_1-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_4_2_4_1-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_2_4_1-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_4_2_4_1.eprime b/tests/exhaustive/basic/set09/expected/model_4_2_4_1.eprime new file mode 100644 index 0000000000..f587016cd9 --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_2_4_1.eprime @@ -0,0 +1,28 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +find y_Occurrence: matrix indexed by [int(2..5)] of bool +branching on + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, y_Occurrence, y_ExplicitVarSizeWithDummy] +such that + and([x_ExplicitVarSizeWithFlags_Flags[q16] /\ y_ExplicitVarSizeWithDummy[q17] != 6 -> + x_ExplicitVarSizeWithFlags_Values[q16] + 2 = y_ExplicitVarSizeWithDummy[q17] + | q16 : int(1..4), q17 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 2 | q2 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]), + and([y_ExplicitVarSizeWithDummy[q6] < y_ExplicitVarSizeWithDummy[q6 + 1] \/ y_ExplicitVarSizeWithDummy[q6] = 6 + | q6 : int(1..3)]), + and([y_ExplicitVarSizeWithDummy[q7] = 6 -> y_ExplicitVarSizeWithDummy[q7 + 1] = 6 | q7 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q8] != 6) | q8 : int(1..4)]), + 1 <= sum([toInt(y_Occurrence[q10]) | q10 : int(2..5)]), + and([y_Occurrence[q11] -> + or([y_ExplicitVarSizeWithDummy[q13] != 6 /\ y_ExplicitVarSizeWithDummy[q13] = q11 | q13 : int(1..4)]) + | q11 : int(2..5)]), + and([y_ExplicitVarSizeWithDummy[q15] != 6 -> y_Occurrence[y_ExplicitVarSizeWithDummy[q15]] | q15 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_4_2_4_2-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_4_2_4_2-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_2_4_2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_4_2_4_2-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_4_2_4_2-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_2_4_2-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_4_2_4_2.eprime b/tests/exhaustive/basic/set09/expected/model_4_2_4_2.eprime new file mode 100644 index 0000000000..f30467528a --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_2_4_2.eprime @@ -0,0 +1,21 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +branching on [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithDummy] +such that + and([x_ExplicitVarSizeWithFlags_Flags[q10] /\ y_ExplicitVarSizeWithDummy[q11] != 6 -> + x_ExplicitVarSizeWithFlags_Values[q10] + 2 = y_ExplicitVarSizeWithDummy[q11] + | q10 : int(1..4), q11 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 2 | q2 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]), + and([y_ExplicitVarSizeWithDummy[q6] < y_ExplicitVarSizeWithDummy[q6 + 1] \/ y_ExplicitVarSizeWithDummy[q6] = 6 + | q6 : int(1..3)]), + and([y_ExplicitVarSizeWithDummy[q7] = 6 -> y_ExplicitVarSizeWithDummy[q7 + 1] = 6 | q7 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q8] != 6) | q8 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_4_2_4_3-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_4_2_4_3-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_2_4_3-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_4_2_4_3-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_4_2_4_3-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_2_4_3-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_4_2_4_3.eprime b/tests/exhaustive/basic/set09/expected/model_4_2_4_3.eprime new file mode 100644 index 0000000000..e871f919f3 --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_2_4_3.eprime @@ -0,0 +1,40 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +find y_ExplicitVarSizeWithMarker_Marker: int(0..4) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +branching on + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithMarker_Marker, + y_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithDummy] +such that + and([x_ExplicitVarSizeWithFlags_Flags[q21] /\ y_ExplicitVarSizeWithDummy[q22] != 6 -> + x_ExplicitVarSizeWithFlags_Values[q21] + 2 = y_ExplicitVarSizeWithDummy[q22] + | q21 : int(1..4), q22 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 2 | q2 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]), + and([y_ExplicitVarSizeWithDummy[q6] < y_ExplicitVarSizeWithDummy[q6 + 1] \/ y_ExplicitVarSizeWithDummy[q6] = 6 + | q6 : int(1..3)]), + and([y_ExplicitVarSizeWithDummy[q7] = 6 -> y_ExplicitVarSizeWithDummy[q7 + 1] = 6 | q7 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q8] != 6) | q8 : int(1..4)]), + and([q10 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> + y_ExplicitVarSizeWithMarker_Values[q10] < y_ExplicitVarSizeWithMarker_Values[q10 + 1] + | q10 : int(1..3)]), + and([q11 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q11] = 2 | q11 : int(1..4)]), + 1 <= y_ExplicitVarSizeWithMarker_Marker, + and([q14 <= y_ExplicitVarSizeWithMarker_Marker -> + or([y_ExplicitVarSizeWithDummy[q16] != 6 /\ + y_ExplicitVarSizeWithDummy[q16] = y_ExplicitVarSizeWithMarker_Values[q14] + | q16 : int(1..4)]) + | q14 : int(1..4)]), + and([y_ExplicitVarSizeWithDummy[q18] != 6 -> + or([q20 <= y_ExplicitVarSizeWithMarker_Marker /\ + y_ExplicitVarSizeWithMarker_Values[q20] = y_ExplicitVarSizeWithDummy[q18] + | q20 : int(1..4)]) + | q18 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_4_2_4_4-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_4_2_4_4-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_2_4_4-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_4_2_4_4-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_4_2_4_4-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_2_4_4-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_4_2_4_4.eprime b/tests/exhaustive/basic/set09/expected/model_4_2_4_4.eprime new file mode 100644 index 0000000000..8954f9bfa2 --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_2_4_4.eprime @@ -0,0 +1,42 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +branching on + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithFlags_Flags, + y_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithDummy] +such that + and([x_ExplicitVarSizeWithFlags_Flags[q23] /\ y_ExplicitVarSizeWithDummy[q24] != 6 -> + x_ExplicitVarSizeWithFlags_Values[q23] + 2 = y_ExplicitVarSizeWithDummy[q24] + | q23 : int(1..4), q24 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 2 | q2 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]), + and([y_ExplicitVarSizeWithDummy[q6] < y_ExplicitVarSizeWithDummy[q6 + 1] \/ y_ExplicitVarSizeWithDummy[q6] = 6 + | q6 : int(1..3)]), + and([y_ExplicitVarSizeWithDummy[q7] = 6 -> y_ExplicitVarSizeWithDummy[q7 + 1] = 6 | q7 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q8] != 6) | q8 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q10 + 1] -> + y_ExplicitVarSizeWithFlags_Values[q10] < y_ExplicitVarSizeWithFlags_Values[q10 + 1] + | q10 : int(1..3)]), + and([y_ExplicitVarSizeWithFlags_Flags[q11] = false -> y_ExplicitVarSizeWithFlags_Values[q11] = 2 + | q11 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q12 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q12] | q12 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q13]) | q13 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q16] -> + or([y_ExplicitVarSizeWithDummy[q18] != 6 /\ + y_ExplicitVarSizeWithDummy[q18] = y_ExplicitVarSizeWithFlags_Values[q16] + | q18 : int(1..4)]) + | q16 : int(1..4)]), + and([y_ExplicitVarSizeWithDummy[q20] != 6 -> + or([y_ExplicitVarSizeWithFlags_Flags[q22] /\ + y_ExplicitVarSizeWithFlags_Values[q22] = y_ExplicitVarSizeWithDummy[q20] + | q22 : int(1..4)]) + | q20 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_4_3_1_1-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_4_3_1_1-solution000001.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_3_1_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_4_3_1_1-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_4_3_1_1-solution000002.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_3_1_1-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_4_3_1_1.eprime b/tests/exhaustive/basic/set09/expected/model_4_3_1_1.eprime new file mode 100644 index 0000000000..e2ae63fc2c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_3_1_1.eprime @@ -0,0 +1,40 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +find x_Occurrence: matrix indexed by [int(2..5)] of bool +find y_ExplicitVarSizeWithMarker_Marker: int(0..4) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_Occurrence: matrix indexed by [int(2..5)] of bool +branching on + [x_Occurrence, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, y_Occurrence, + y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values] +such that + and([x_ExplicitVarSizeWithFlags_Flags[q16] /\ q17 <= y_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithFlags_Values[q16] + 2 = y_ExplicitVarSizeWithMarker_Values[q17] + | q16 : int(1..4), q17 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 2 | q2 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]), + and([q6 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> + y_ExplicitVarSizeWithMarker_Values[q6] < y_ExplicitVarSizeWithMarker_Values[q6 + 1] + | q6 : int(1..3)]), + and([q7 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q7] = 2 | q7 : int(1..4)]), + 1 <= y_ExplicitVarSizeWithMarker_Marker, + 1 <= sum([toInt(x_Occurrence[q9]) | q9 : int(2..5)]), + and([x_Occurrence[q18] -> + or([x_ExplicitVarSizeWithFlags_Flags[q20] /\ x_ExplicitVarSizeWithFlags_Values[q20] = q18 | q20 : int(1..4)]) + | q18 : int(2..5)]), + and([x_ExplicitVarSizeWithFlags_Flags[q22] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q22]] + | q22 : int(1..4)]), + 1 <= sum([toInt(y_Occurrence[q10]) | q10 : int(2..5)]), + and([y_Occurrence[q11] -> + or([q13 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[q13] = q11 + | q13 : int(1..4)]) + | q11 : int(2..5)]), + and([q15 <= y_ExplicitVarSizeWithMarker_Marker -> y_Occurrence[y_ExplicitVarSizeWithMarker_Values[q15]] + | q15 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_4_3_1_2-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_4_3_1_2-solution000001.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_3_1_2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_4_3_1_2-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_4_3_1_2-solution000002.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_3_1_2-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_4_3_1_2.eprime b/tests/exhaustive/basic/set09/expected/model_4_3_1_2.eprime new file mode 100644 index 0000000000..ae45352286 --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_3_1_2.eprime @@ -0,0 +1,47 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +find x_Occurrence: matrix indexed by [int(2..5)] of bool +find y_ExplicitVarSizeWithMarker_Marker: int(0..4) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +branching on + [x_Occurrence, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithDummy, + y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values] +such that + and([x_ExplicitVarSizeWithFlags_Flags[q27] /\ q28 <= y_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithFlags_Values[q27] + 2 = y_ExplicitVarSizeWithMarker_Values[q28] + | q27 : int(1..4), q28 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 2 | q2 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]), + and([q6 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> + y_ExplicitVarSizeWithMarker_Values[q6] < y_ExplicitVarSizeWithMarker_Values[q6 + 1] + | q6 : int(1..3)]), + and([q7 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q7] = 2 | q7 : int(1..4)]), + 1 <= y_ExplicitVarSizeWithMarker_Marker, + 1 <= sum([toInt(x_Occurrence[q9]) | q9 : int(2..5)]), + and([x_Occurrence[q22] -> + or([x_ExplicitVarSizeWithFlags_Flags[q24] /\ x_ExplicitVarSizeWithFlags_Values[q24] = q22 | q24 : int(1..4)]) + | q22 : int(2..5)]), + and([x_ExplicitVarSizeWithFlags_Flags[q26] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q26]] + | q26 : int(1..4)]), + and([y_ExplicitVarSizeWithDummy[q10] < y_ExplicitVarSizeWithDummy[q10 + 1] \/ y_ExplicitVarSizeWithDummy[q10] = 6 + | q10 : int(1..3)]), + and([y_ExplicitVarSizeWithDummy[q11] = 6 -> y_ExplicitVarSizeWithDummy[q11 + 1] = 6 | q11 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q12] != 6) | q12 : int(1..4)]), + and([y_ExplicitVarSizeWithDummy[q15] != 6 -> + or([q17 <= y_ExplicitVarSizeWithMarker_Marker /\ + y_ExplicitVarSizeWithMarker_Values[q17] = y_ExplicitVarSizeWithDummy[q15] + | q17 : int(1..4)]) + | q15 : int(1..4)]), + and([q19 <= y_ExplicitVarSizeWithMarker_Marker -> + or([y_ExplicitVarSizeWithDummy[q21] != 6 /\ + y_ExplicitVarSizeWithDummy[q21] = y_ExplicitVarSizeWithMarker_Values[q19] + | q21 : int(1..4)]) + | q19 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_4_3_1_3-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_4_3_1_3-solution000001.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_3_1_3-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_4_3_1_3-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_4_3_1_3-solution000002.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_3_1_3-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_4_3_1_3.eprime b/tests/exhaustive/basic/set09/expected/model_4_3_1_3.eprime new file mode 100644 index 0000000000..cd001ff305 --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_3_1_3.eprime @@ -0,0 +1,32 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +find x_Occurrence: matrix indexed by [int(2..5)] of bool +find y_ExplicitVarSizeWithMarker_Marker: int(0..4) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +branching on + [x_Occurrence, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, + y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values] +such that + and([x_ExplicitVarSizeWithFlags_Flags[q15] /\ q16 <= y_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithFlags_Values[q15] + 2 = y_ExplicitVarSizeWithMarker_Values[q16] + | q15 : int(1..4), q16 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 2 | q2 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]), + and([q6 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> + y_ExplicitVarSizeWithMarker_Values[q6] < y_ExplicitVarSizeWithMarker_Values[q6 + 1] + | q6 : int(1..3)]), + and([q7 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q7] = 2 | q7 : int(1..4)]), + 1 <= y_ExplicitVarSizeWithMarker_Marker, + 1 <= sum([toInt(x_Occurrence[q9]) | q9 : int(2..5)]), + and([x_Occurrence[q10] -> + or([x_ExplicitVarSizeWithFlags_Flags[q12] /\ x_ExplicitVarSizeWithFlags_Values[q12] = q10 | q12 : int(1..4)]) + | q10 : int(2..5)]), + and([x_ExplicitVarSizeWithFlags_Flags[q14] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q14]] + | q14 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_4_3_1_4-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_4_3_1_4-solution000001.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_3_1_4-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_4_3_1_4-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_4_3_1_4-solution000002.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_3_1_4-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_4_3_1_4.eprime b/tests/exhaustive/basic/set09/expected/model_4_3_1_4.eprime new file mode 100644 index 0000000000..c1ff4e46c8 --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_3_1_4.eprime @@ -0,0 +1,52 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +find x_Occurrence: matrix indexed by [int(2..5)] of bool +find y_ExplicitVarSizeWithMarker_Marker: int(0..4) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +branching on + [x_Occurrence, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, + y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithMarker_Marker, + y_ExplicitVarSizeWithMarker_Values] +such that + and([x_ExplicitVarSizeWithFlags_Flags[q28] /\ q29 <= y_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithFlags_Values[q28] + 2 = y_ExplicitVarSizeWithMarker_Values[q29] + | q28 : int(1..4), q29 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 2 | q2 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]), + and([q6 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> + y_ExplicitVarSizeWithMarker_Values[q6] < y_ExplicitVarSizeWithMarker_Values[q6 + 1] + | q6 : int(1..3)]), + and([q7 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q7] = 2 | q7 : int(1..4)]), + 1 <= y_ExplicitVarSizeWithMarker_Marker, + 1 <= sum([toInt(x_Occurrence[q9]) | q9 : int(2..5)]), + and([x_Occurrence[q23] -> + or([x_ExplicitVarSizeWithFlags_Flags[q25] /\ x_ExplicitVarSizeWithFlags_Values[q25] = q23 | q25 : int(1..4)]) + | q23 : int(2..5)]), + and([x_ExplicitVarSizeWithFlags_Flags[q27] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q27]] + | q27 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q10 + 1] -> + y_ExplicitVarSizeWithFlags_Values[q10] < y_ExplicitVarSizeWithFlags_Values[q10 + 1] + | q10 : int(1..3)]), + and([y_ExplicitVarSizeWithFlags_Flags[q11] = false -> y_ExplicitVarSizeWithFlags_Values[q11] = 2 + | q11 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q12 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q12] | q12 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q13]) | q13 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q16] -> + or([q18 <= y_ExplicitVarSizeWithMarker_Marker /\ + y_ExplicitVarSizeWithMarker_Values[q18] = y_ExplicitVarSizeWithFlags_Values[q16] + | q18 : int(1..4)]) + | q16 : int(1..4)]), + and([q20 <= y_ExplicitVarSizeWithMarker_Marker -> + or([y_ExplicitVarSizeWithFlags_Flags[q22] /\ + y_ExplicitVarSizeWithFlags_Values[q22] = y_ExplicitVarSizeWithMarker_Values[q20] + | q22 : int(1..4)]) + | q20 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_4_3_2_1-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_4_3_2_1-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_3_2_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_4_3_2_1-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_4_3_2_1-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_3_2_1-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_4_3_2_1.eprime b/tests/exhaustive/basic/set09/expected/model_4_3_2_1.eprime new file mode 100644 index 0000000000..ebbb2075a2 --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_3_2_1.eprime @@ -0,0 +1,48 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +find y_ExplicitVarSizeWithMarker_Marker: int(0..4) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_Occurrence: matrix indexed by [int(2..5)] of bool +branching on + [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, y_Occurrence, + y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values] +such that + and([x_ExplicitVarSizeWithFlags_Flags[q27] /\ q28 <= y_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithFlags_Values[q27] + 2 = y_ExplicitVarSizeWithMarker_Values[q28] + | q27 : int(1..4), q28 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 2 | q2 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]), + and([q6 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> + y_ExplicitVarSizeWithMarker_Values[q6] < y_ExplicitVarSizeWithMarker_Values[q6 + 1] + | q6 : int(1..3)]), + and([q7 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q7] = 2 | q7 : int(1..4)]), + 1 <= y_ExplicitVarSizeWithMarker_Marker, + and([x_ExplicitVarSizeWithDummy[q9] < x_ExplicitVarSizeWithDummy[q9 + 1] \/ x_ExplicitVarSizeWithDummy[q9] = 6 + | q9 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q10] = 6 -> x_ExplicitVarSizeWithDummy[q10 + 1] = 6 | q10 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q11] != 6) | q11 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q14] != 6 -> + or([x_ExplicitVarSizeWithFlags_Flags[q16] /\ + x_ExplicitVarSizeWithFlags_Values[q16] = x_ExplicitVarSizeWithDummy[q14] + | q16 : int(1..4)]) + | q14 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q18] -> + or([x_ExplicitVarSizeWithDummy[q20] != 6 /\ + x_ExplicitVarSizeWithDummy[q20] = x_ExplicitVarSizeWithFlags_Values[q18] + | q20 : int(1..4)]) + | q18 : int(1..4)]), + 1 <= sum([toInt(y_Occurrence[q21]) | q21 : int(2..5)]), + and([y_Occurrence[q22] -> + or([q24 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[q24] = q22 + | q24 : int(1..4)]) + | q22 : int(2..5)]), + and([q26 <= y_ExplicitVarSizeWithMarker_Marker -> y_Occurrence[y_ExplicitVarSizeWithMarker_Values[q26]] + | q26 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_4_3_2_2-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_4_3_2_2-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_3_2_2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_4_3_2_2-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_4_3_2_2-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_3_2_2-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_4_3_2_2.eprime b/tests/exhaustive/basic/set09/expected/model_4_3_2_2.eprime new file mode 100644 index 0000000000..96ae673549 --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_3_2_2.eprime @@ -0,0 +1,55 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +find y_ExplicitVarSizeWithMarker_Marker: int(0..4) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +branching on + [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, + y_ExplicitVarSizeWithDummy, y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values] +such that + and([x_ExplicitVarSizeWithFlags_Flags[q33] /\ q34 <= y_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithFlags_Values[q33] + 2 = y_ExplicitVarSizeWithMarker_Values[q34] + | q33 : int(1..4), q34 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 2 | q2 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]), + and([q6 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> + y_ExplicitVarSizeWithMarker_Values[q6] < y_ExplicitVarSizeWithMarker_Values[q6 + 1] + | q6 : int(1..3)]), + and([q7 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q7] = 2 | q7 : int(1..4)]), + 1 <= y_ExplicitVarSizeWithMarker_Marker, + and([x_ExplicitVarSizeWithDummy[q9] < x_ExplicitVarSizeWithDummy[q9 + 1] \/ x_ExplicitVarSizeWithDummy[q9] = 6 + | q9 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q10] = 6 -> x_ExplicitVarSizeWithDummy[q10 + 1] = 6 | q10 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q11] != 6) | q11 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q14] != 6 -> + or([x_ExplicitVarSizeWithFlags_Flags[q16] /\ + x_ExplicitVarSizeWithFlags_Values[q16] = x_ExplicitVarSizeWithDummy[q14] + | q16 : int(1..4)]) + | q14 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q18] -> + or([x_ExplicitVarSizeWithDummy[q20] != 6 /\ + x_ExplicitVarSizeWithDummy[q20] = x_ExplicitVarSizeWithFlags_Values[q18] + | q20 : int(1..4)]) + | q18 : int(1..4)]), + and([y_ExplicitVarSizeWithDummy[q21] < y_ExplicitVarSizeWithDummy[q21 + 1] \/ y_ExplicitVarSizeWithDummy[q21] = 6 + | q21 : int(1..3)]), + and([y_ExplicitVarSizeWithDummy[q22] = 6 -> y_ExplicitVarSizeWithDummy[q22 + 1] = 6 | q22 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q23] != 6) | q23 : int(1..4)]), + and([y_ExplicitVarSizeWithDummy[q26] != 6 -> + or([q28 <= y_ExplicitVarSizeWithMarker_Marker /\ + y_ExplicitVarSizeWithMarker_Values[q28] = y_ExplicitVarSizeWithDummy[q26] + | q28 : int(1..4)]) + | q26 : int(1..4)]), + and([q30 <= y_ExplicitVarSizeWithMarker_Marker -> + or([y_ExplicitVarSizeWithDummy[q32] != 6 /\ + y_ExplicitVarSizeWithDummy[q32] = y_ExplicitVarSizeWithMarker_Values[q30] + | q32 : int(1..4)]) + | q30 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_4_3_2_3-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_4_3_2_3-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_3_2_3-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_4_3_2_3-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_4_3_2_3-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_3_2_3-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_4_3_2_3.eprime b/tests/exhaustive/basic/set09/expected/model_4_3_2_3.eprime new file mode 100644 index 0000000000..6f50c8c681 --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_3_2_3.eprime @@ -0,0 +1,40 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +find y_ExplicitVarSizeWithMarker_Marker: int(0..4) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +branching on + [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, + y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values] +such that + and([x_ExplicitVarSizeWithFlags_Flags[q21] /\ q22 <= y_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithFlags_Values[q21] + 2 = y_ExplicitVarSizeWithMarker_Values[q22] + | q21 : int(1..4), q22 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 2 | q2 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]), + and([q6 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> + y_ExplicitVarSizeWithMarker_Values[q6] < y_ExplicitVarSizeWithMarker_Values[q6 + 1] + | q6 : int(1..3)]), + and([q7 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q7] = 2 | q7 : int(1..4)]), + 1 <= y_ExplicitVarSizeWithMarker_Marker, + and([x_ExplicitVarSizeWithDummy[q9] < x_ExplicitVarSizeWithDummy[q9 + 1] \/ x_ExplicitVarSizeWithDummy[q9] = 6 + | q9 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q10] = 6 -> x_ExplicitVarSizeWithDummy[q10 + 1] = 6 | q10 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q11] != 6) | q11 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q14] != 6 -> + or([x_ExplicitVarSizeWithFlags_Flags[q16] /\ + x_ExplicitVarSizeWithFlags_Values[q16] = x_ExplicitVarSizeWithDummy[q14] + | q16 : int(1..4)]) + | q14 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q18] -> + or([x_ExplicitVarSizeWithDummy[q20] != 6 /\ + x_ExplicitVarSizeWithDummy[q20] = x_ExplicitVarSizeWithFlags_Values[q18] + | q20 : int(1..4)]) + | q18 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_4_3_2_4-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_4_3_2_4-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_3_2_4-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_4_3_2_4-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_4_3_2_4-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_3_2_4-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_4_3_2_4.eprime b/tests/exhaustive/basic/set09/expected/model_4_3_2_4.eprime new file mode 100644 index 0000000000..a06fe066bf --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_3_2_4.eprime @@ -0,0 +1,60 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +find y_ExplicitVarSizeWithMarker_Marker: int(0..4) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +branching on + [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, + y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithMarker_Marker, + y_ExplicitVarSizeWithMarker_Values] +such that + and([x_ExplicitVarSizeWithFlags_Flags[q34] /\ q35 <= y_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithFlags_Values[q34] + 2 = y_ExplicitVarSizeWithMarker_Values[q35] + | q34 : int(1..4), q35 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 2 | q2 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]), + and([q6 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> + y_ExplicitVarSizeWithMarker_Values[q6] < y_ExplicitVarSizeWithMarker_Values[q6 + 1] + | q6 : int(1..3)]), + and([q7 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q7] = 2 | q7 : int(1..4)]), + 1 <= y_ExplicitVarSizeWithMarker_Marker, + and([x_ExplicitVarSizeWithDummy[q9] < x_ExplicitVarSizeWithDummy[q9 + 1] \/ x_ExplicitVarSizeWithDummy[q9] = 6 + | q9 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q10] = 6 -> x_ExplicitVarSizeWithDummy[q10 + 1] = 6 | q10 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q11] != 6) | q11 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q14] != 6 -> + or([x_ExplicitVarSizeWithFlags_Flags[q16] /\ + x_ExplicitVarSizeWithFlags_Values[q16] = x_ExplicitVarSizeWithDummy[q14] + | q16 : int(1..4)]) + | q14 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q18] -> + or([x_ExplicitVarSizeWithDummy[q20] != 6 /\ + x_ExplicitVarSizeWithDummy[q20] = x_ExplicitVarSizeWithFlags_Values[q18] + | q20 : int(1..4)]) + | q18 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q21 + 1] -> + y_ExplicitVarSizeWithFlags_Values[q21] < y_ExplicitVarSizeWithFlags_Values[q21 + 1] + | q21 : int(1..3)]), + and([y_ExplicitVarSizeWithFlags_Flags[q22] = false -> y_ExplicitVarSizeWithFlags_Values[q22] = 2 + | q22 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q23 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q23] | q23 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q24]) | q24 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q27] -> + or([q29 <= y_ExplicitVarSizeWithMarker_Marker /\ + y_ExplicitVarSizeWithMarker_Values[q29] = y_ExplicitVarSizeWithFlags_Values[q27] + | q29 : int(1..4)]) + | q27 : int(1..4)]), + and([q31 <= y_ExplicitVarSizeWithMarker_Marker -> + or([y_ExplicitVarSizeWithFlags_Flags[q33] /\ + y_ExplicitVarSizeWithFlags_Values[q33] = y_ExplicitVarSizeWithMarker_Values[q31] + | q33 : int(1..4)]) + | q31 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_4_3_3_1-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_4_3_3_1-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_3_3_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_4_3_3_1-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_4_3_3_1-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_3_3_1-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_4_3_3_1.eprime b/tests/exhaustive/basic/set09/expected/model_4_3_3_1.eprime new file mode 100644 index 0000000000..956990ea06 --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_3_3_1.eprime @@ -0,0 +1,51 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_ExplicitVarSizeWithMarker_Marker: int(0..4) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_Occurrence: matrix indexed by [int(2..5)] of bool +branching on + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithFlags_Flags, + x_ExplicitVarSizeWithFlags_Values, y_Occurrence, y_ExplicitVarSizeWithMarker_Marker, + y_ExplicitVarSizeWithMarker_Values] +such that + and([x_ExplicitVarSizeWithFlags_Flags[q26] /\ q27 <= y_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithFlags_Values[q26] + 2 = y_ExplicitVarSizeWithMarker_Values[q27] + | q26 : int(1..4), q27 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 2 | q2 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]), + and([q6 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> + y_ExplicitVarSizeWithMarker_Values[q6] < y_ExplicitVarSizeWithMarker_Values[q6 + 1] + | q6 : int(1..3)]), + and([q7 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q7] = 2 | q7 : int(1..4)]), + 1 <= y_ExplicitVarSizeWithMarker_Marker, + and([q9 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q9] < x_ExplicitVarSizeWithMarker_Values[q9 + 1] + | q9 : int(1..3)]), + and([q10 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q10] = 2 | q10 : int(1..4)]), + 1 <= x_ExplicitVarSizeWithMarker_Marker, + and([q13 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithFlags_Flags[q15] /\ + x_ExplicitVarSizeWithFlags_Values[q15] = x_ExplicitVarSizeWithMarker_Values[q13] + | q15 : int(1..4)]) + | q13 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q17] -> + or([q19 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q19] = x_ExplicitVarSizeWithFlags_Values[q17] + | q19 : int(1..4)]) + | q17 : int(1..4)]), + 1 <= sum([toInt(y_Occurrence[q20]) | q20 : int(2..5)]), + and([y_Occurrence[q21] -> + or([q23 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[q23] = q21 + | q23 : int(1..4)]) + | q21 : int(2..5)]), + and([q25 <= y_ExplicitVarSizeWithMarker_Marker -> y_Occurrence[y_ExplicitVarSizeWithMarker_Values[q25]] + | q25 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_4_3_3_2-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_4_3_3_2-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_3_3_2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_4_3_3_2-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_4_3_3_2-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_3_3_2-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_4_3_3_2.eprime b/tests/exhaustive/basic/set09/expected/model_4_3_3_2.eprime new file mode 100644 index 0000000000..76cc5a8aed --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_3_3_2.eprime @@ -0,0 +1,58 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_ExplicitVarSizeWithMarker_Marker: int(0..4) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +branching on + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithFlags_Flags, + x_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithDummy, y_ExplicitVarSizeWithMarker_Marker, + y_ExplicitVarSizeWithMarker_Values] +such that + and([x_ExplicitVarSizeWithFlags_Flags[q32] /\ q33 <= y_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithFlags_Values[q32] + 2 = y_ExplicitVarSizeWithMarker_Values[q33] + | q32 : int(1..4), q33 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 2 | q2 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]), + and([q6 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> + y_ExplicitVarSizeWithMarker_Values[q6] < y_ExplicitVarSizeWithMarker_Values[q6 + 1] + | q6 : int(1..3)]), + and([q7 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q7] = 2 | q7 : int(1..4)]), + 1 <= y_ExplicitVarSizeWithMarker_Marker, + and([q9 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q9] < x_ExplicitVarSizeWithMarker_Values[q9 + 1] + | q9 : int(1..3)]), + and([q10 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q10] = 2 | q10 : int(1..4)]), + 1 <= x_ExplicitVarSizeWithMarker_Marker, + and([q13 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithFlags_Flags[q15] /\ + x_ExplicitVarSizeWithFlags_Values[q15] = x_ExplicitVarSizeWithMarker_Values[q13] + | q15 : int(1..4)]) + | q13 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q17] -> + or([q19 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q19] = x_ExplicitVarSizeWithFlags_Values[q17] + | q19 : int(1..4)]) + | q17 : int(1..4)]), + and([y_ExplicitVarSizeWithDummy[q20] < y_ExplicitVarSizeWithDummy[q20 + 1] \/ y_ExplicitVarSizeWithDummy[q20] = 6 + | q20 : int(1..3)]), + and([y_ExplicitVarSizeWithDummy[q21] = 6 -> y_ExplicitVarSizeWithDummy[q21 + 1] = 6 | q21 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q22] != 6) | q22 : int(1..4)]), + and([y_ExplicitVarSizeWithDummy[q25] != 6 -> + or([q27 <= y_ExplicitVarSizeWithMarker_Marker /\ + y_ExplicitVarSizeWithMarker_Values[q27] = y_ExplicitVarSizeWithDummy[q25] + | q27 : int(1..4)]) + | q25 : int(1..4)]), + and([q29 <= y_ExplicitVarSizeWithMarker_Marker -> + or([y_ExplicitVarSizeWithDummy[q31] != 6 /\ + y_ExplicitVarSizeWithDummy[q31] = y_ExplicitVarSizeWithMarker_Values[q29] + | q31 : int(1..4)]) + | q29 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_4_3_3_3-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_4_3_3_3-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_3_3_3-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_4_3_3_3-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_4_3_3_3-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_3_3_3-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_4_3_3_3.eprime b/tests/exhaustive/basic/set09/expected/model_4_3_3_3.eprime new file mode 100644 index 0000000000..f90dae8a31 --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_3_3_3.eprime @@ -0,0 +1,42 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_ExplicitVarSizeWithMarker_Marker: int(0..4) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +branching on + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithFlags_Flags, + x_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values] +such that + and([x_ExplicitVarSizeWithFlags_Flags[q20] /\ q21 <= y_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithFlags_Values[q20] + 2 = y_ExplicitVarSizeWithMarker_Values[q21] + | q20 : int(1..4), q21 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 2 | q2 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]), + and([q6 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> + y_ExplicitVarSizeWithMarker_Values[q6] < y_ExplicitVarSizeWithMarker_Values[q6 + 1] + | q6 : int(1..3)]), + and([q7 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q7] = 2 | q7 : int(1..4)]), + 1 <= y_ExplicitVarSizeWithMarker_Marker, + and([q9 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q9] < x_ExplicitVarSizeWithMarker_Values[q9 + 1] + | q9 : int(1..3)]), + and([q10 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q10] = 2 | q10 : int(1..4)]), + 1 <= x_ExplicitVarSizeWithMarker_Marker, + and([q13 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithFlags_Flags[q15] /\ + x_ExplicitVarSizeWithFlags_Values[q15] = x_ExplicitVarSizeWithMarker_Values[q13] + | q15 : int(1..4)]) + | q13 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q17] -> + or([q19 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q19] = x_ExplicitVarSizeWithFlags_Values[q17] + | q19 : int(1..4)]) + | q17 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_4_3_3_4-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_4_3_3_4-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_3_3_4-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_4_3_3_4-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_4_3_3_4-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_3_3_4-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_4_3_3_4.eprime b/tests/exhaustive/basic/set09/expected/model_4_3_3_4.eprime new file mode 100644 index 0000000000..a3ac3373bb --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_3_3_4.eprime @@ -0,0 +1,62 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_ExplicitVarSizeWithMarker_Marker: int(0..4) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +branching on + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithFlags_Flags, + x_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values, + y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values] +such that + and([x_ExplicitVarSizeWithFlags_Flags[q33] /\ q34 <= y_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithFlags_Values[q33] + 2 = y_ExplicitVarSizeWithMarker_Values[q34] + | q33 : int(1..4), q34 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 2 | q2 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]), + and([q6 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> + y_ExplicitVarSizeWithMarker_Values[q6] < y_ExplicitVarSizeWithMarker_Values[q6 + 1] + | q6 : int(1..3)]), + and([q7 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q7] = 2 | q7 : int(1..4)]), + 1 <= y_ExplicitVarSizeWithMarker_Marker, + and([q9 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q9] < x_ExplicitVarSizeWithMarker_Values[q9 + 1] + | q9 : int(1..3)]), + and([q10 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q10] = 2 | q10 : int(1..4)]), + 1 <= x_ExplicitVarSizeWithMarker_Marker, + and([q13 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithFlags_Flags[q15] /\ + x_ExplicitVarSizeWithFlags_Values[q15] = x_ExplicitVarSizeWithMarker_Values[q13] + | q15 : int(1..4)]) + | q13 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q17] -> + or([q19 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q19] = x_ExplicitVarSizeWithFlags_Values[q17] + | q19 : int(1..4)]) + | q17 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q20 + 1] -> + y_ExplicitVarSizeWithFlags_Values[q20] < y_ExplicitVarSizeWithFlags_Values[q20 + 1] + | q20 : int(1..3)]), + and([y_ExplicitVarSizeWithFlags_Flags[q21] = false -> y_ExplicitVarSizeWithFlags_Values[q21] = 2 + | q21 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q22 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q22] | q22 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q23]) | q23 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q26] -> + or([q28 <= y_ExplicitVarSizeWithMarker_Marker /\ + y_ExplicitVarSizeWithMarker_Values[q28] = y_ExplicitVarSizeWithFlags_Values[q26] + | q28 : int(1..4)]) + | q26 : int(1..4)]), + and([q30 <= y_ExplicitVarSizeWithMarker_Marker -> + or([y_ExplicitVarSizeWithFlags_Flags[q32] /\ + y_ExplicitVarSizeWithFlags_Values[q32] = y_ExplicitVarSizeWithMarker_Values[q30] + | q32 : int(1..4)]) + | q30 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_4_3_4_1-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_4_3_4_1-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_3_4_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_4_3_4_1-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_4_3_4_1-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_3_4_1-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_4_3_4_1.eprime b/tests/exhaustive/basic/set09/expected/model_4_3_4_1.eprime new file mode 100644 index 0000000000..d57282a34a --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_3_4_1.eprime @@ -0,0 +1,33 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_ExplicitVarSizeWithMarker_Marker: int(0..4) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_Occurrence: matrix indexed by [int(2..5)] of bool +branching on + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, y_Occurrence, + y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values] +such that + and([x_ExplicitVarSizeWithFlags_Flags[q15] /\ q16 <= y_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithFlags_Values[q15] + 2 = y_ExplicitVarSizeWithMarker_Values[q16] + | q15 : int(1..4), q16 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 2 | q2 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]), + and([q6 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> + y_ExplicitVarSizeWithMarker_Values[q6] < y_ExplicitVarSizeWithMarker_Values[q6 + 1] + | q6 : int(1..3)]), + and([q7 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q7] = 2 | q7 : int(1..4)]), + 1 <= y_ExplicitVarSizeWithMarker_Marker, + 1 <= sum([toInt(y_Occurrence[q9]) | q9 : int(2..5)]), + and([y_Occurrence[q10] -> + or([q12 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[q12] = q10 + | q12 : int(1..4)]) + | q10 : int(2..5)]), + and([q14 <= y_ExplicitVarSizeWithMarker_Marker -> y_Occurrence[y_ExplicitVarSizeWithMarker_Values[q14]] + | q14 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_4_3_4_2-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_4_3_4_2-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_3_4_2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_4_3_4_2-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_4_3_4_2-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_3_4_2-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_4_3_4_2.eprime b/tests/exhaustive/basic/set09/expected/model_4_3_4_2.eprime new file mode 100644 index 0000000000..71131e9ed0 --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_3_4_2.eprime @@ -0,0 +1,40 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_ExplicitVarSizeWithMarker_Marker: int(0..4) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +branching on + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithDummy, + y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values] +such that + and([x_ExplicitVarSizeWithFlags_Flags[q21] /\ q22 <= y_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithFlags_Values[q21] + 2 = y_ExplicitVarSizeWithMarker_Values[q22] + | q21 : int(1..4), q22 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 2 | q2 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]), + and([q6 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> + y_ExplicitVarSizeWithMarker_Values[q6] < y_ExplicitVarSizeWithMarker_Values[q6 + 1] + | q6 : int(1..3)]), + and([q7 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q7] = 2 | q7 : int(1..4)]), + 1 <= y_ExplicitVarSizeWithMarker_Marker, + and([y_ExplicitVarSizeWithDummy[q9] < y_ExplicitVarSizeWithDummy[q9 + 1] \/ y_ExplicitVarSizeWithDummy[q9] = 6 + | q9 : int(1..3)]), + and([y_ExplicitVarSizeWithDummy[q10] = 6 -> y_ExplicitVarSizeWithDummy[q10 + 1] = 6 | q10 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q11] != 6) | q11 : int(1..4)]), + and([y_ExplicitVarSizeWithDummy[q14] != 6 -> + or([q16 <= y_ExplicitVarSizeWithMarker_Marker /\ + y_ExplicitVarSizeWithMarker_Values[q16] = y_ExplicitVarSizeWithDummy[q14] + | q16 : int(1..4)]) + | q14 : int(1..4)]), + and([q18 <= y_ExplicitVarSizeWithMarker_Marker -> + or([y_ExplicitVarSizeWithDummy[q20] != 6 /\ + y_ExplicitVarSizeWithDummy[q20] = y_ExplicitVarSizeWithMarker_Values[q18] + | q20 : int(1..4)]) + | q18 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_4_3_4_3-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_4_3_4_3-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_3_4_3-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_4_3_4_3-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_4_3_4_3-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_3_4_3-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_4_3_4_3.eprime b/tests/exhaustive/basic/set09/expected/model_4_3_4_3.eprime new file mode 100644 index 0000000000..926828d190 --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_3_4_3.eprime @@ -0,0 +1,25 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_ExplicitVarSizeWithMarker_Marker: int(0..4) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +branching on + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithMarker_Marker, + y_ExplicitVarSizeWithMarker_Values] +such that + and([x_ExplicitVarSizeWithFlags_Flags[q9] /\ q10 <= y_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithFlags_Values[q9] + 2 = y_ExplicitVarSizeWithMarker_Values[q10] + | q9 : int(1..4), q10 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 2 | q2 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]), + and([q6 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> + y_ExplicitVarSizeWithMarker_Values[q6] < y_ExplicitVarSizeWithMarker_Values[q6 + 1] + | q6 : int(1..3)]), + and([q7 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q7] = 2 | q7 : int(1..4)]), + 1 <= y_ExplicitVarSizeWithMarker_Marker + diff --git a/tests/exhaustive/basic/set09/expected/model_4_3_4_4-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_4_3_4_4-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_3_4_4-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_4_3_4_4-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_4_3_4_4-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_3_4_4-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_4_3_4_4.eprime b/tests/exhaustive/basic/set09/expected/model_4_3_4_4.eprime new file mode 100644 index 0000000000..e141685012 --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_3_4_4.eprime @@ -0,0 +1,44 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_ExplicitVarSizeWithMarker_Marker: int(0..4) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +branching on + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithFlags_Flags, + y_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values] +such that + and([x_ExplicitVarSizeWithFlags_Flags[q22] /\ q23 <= y_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithFlags_Values[q22] + 2 = y_ExplicitVarSizeWithMarker_Values[q23] + | q22 : int(1..4), q23 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 2 | q2 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]), + and([q6 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> + y_ExplicitVarSizeWithMarker_Values[q6] < y_ExplicitVarSizeWithMarker_Values[q6 + 1] + | q6 : int(1..3)]), + and([q7 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q7] = 2 | q7 : int(1..4)]), + 1 <= y_ExplicitVarSizeWithMarker_Marker, + and([y_ExplicitVarSizeWithFlags_Flags[q9 + 1] -> + y_ExplicitVarSizeWithFlags_Values[q9] < y_ExplicitVarSizeWithFlags_Values[q9 + 1] + | q9 : int(1..3)]), + and([y_ExplicitVarSizeWithFlags_Flags[q10] = false -> y_ExplicitVarSizeWithFlags_Values[q10] = 2 + | q10 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q11 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q11] | q11 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q12]) | q12 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q15] -> + or([q17 <= y_ExplicitVarSizeWithMarker_Marker /\ + y_ExplicitVarSizeWithMarker_Values[q17] = y_ExplicitVarSizeWithFlags_Values[q15] + | q17 : int(1..4)]) + | q15 : int(1..4)]), + and([q19 <= y_ExplicitVarSizeWithMarker_Marker -> + or([y_ExplicitVarSizeWithFlags_Flags[q21] /\ + y_ExplicitVarSizeWithFlags_Values[q21] = y_ExplicitVarSizeWithMarker_Values[q19] + | q21 : int(1..4)]) + | q19 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_4_4_1_1-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_4_4_1_1-solution000001.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_4_1_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_4_4_1_1-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_4_4_1_1-solution000002.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_4_1_1-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_4_4_1_1.eprime b/tests/exhaustive/basic/set09/expected/model_4_4_1_1.eprime new file mode 100644 index 0000000000..902354c009 --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_4_1_1.eprime @@ -0,0 +1,40 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +find x_Occurrence: matrix indexed by [int(2..5)] of bool +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_Occurrence: matrix indexed by [int(2..5)] of bool +branching on + [x_Occurrence, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, y_Occurrence, + y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values] +such that + and([x_ExplicitVarSizeWithFlags_Flags[q18] /\ y_ExplicitVarSizeWithFlags_Flags[q19] -> + x_ExplicitVarSizeWithFlags_Values[q18] + 2 = y_ExplicitVarSizeWithFlags_Values[q19] + | q18 : int(1..4), q19 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 2 | q2 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> + y_ExplicitVarSizeWithFlags_Values[q6] < y_ExplicitVarSizeWithFlags_Values[q6 + 1] + | q6 : int(1..3)]), + and([y_ExplicitVarSizeWithFlags_Flags[q7] = false -> y_ExplicitVarSizeWithFlags_Values[q7] = 2 | q7 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q8 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q8] | q8 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q9]) | q9 : int(1..4)]), + 1 <= sum([toInt(x_Occurrence[q11]) | q11 : int(2..5)]), + and([x_Occurrence[q20] -> + or([x_ExplicitVarSizeWithFlags_Flags[q22] /\ x_ExplicitVarSizeWithFlags_Values[q22] = q20 | q22 : int(1..4)]) + | q20 : int(2..5)]), + and([x_ExplicitVarSizeWithFlags_Flags[q24] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q24]] + | q24 : int(1..4)]), + 1 <= sum([toInt(y_Occurrence[q12]) | q12 : int(2..5)]), + and([y_Occurrence[q13] -> + or([y_ExplicitVarSizeWithFlags_Flags[q15] /\ y_ExplicitVarSizeWithFlags_Values[q15] = q13 | q15 : int(1..4)]) + | q13 : int(2..5)]), + and([y_ExplicitVarSizeWithFlags_Flags[q17] -> y_Occurrence[y_ExplicitVarSizeWithFlags_Values[q17]] + | q17 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_4_4_1_2-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_4_4_1_2-solution000001.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_4_1_2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_4_4_1_2-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_4_4_1_2-solution000002.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_4_1_2-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_4_4_1_2.eprime b/tests/exhaustive/basic/set09/expected/model_4_4_1_2.eprime new file mode 100644 index 0000000000..2093b2c8e5 --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_4_1_2.eprime @@ -0,0 +1,48 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +find x_Occurrence: matrix indexed by [int(2..5)] of bool +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +branching on + [x_Occurrence, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithDummy, + y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values] +such that + and([x_ExplicitVarSizeWithFlags_Flags[q29] /\ y_ExplicitVarSizeWithFlags_Flags[q30] -> + x_ExplicitVarSizeWithFlags_Values[q29] + 2 = y_ExplicitVarSizeWithFlags_Values[q30] + | q29 : int(1..4), q30 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 2 | q2 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> + y_ExplicitVarSizeWithFlags_Values[q6] < y_ExplicitVarSizeWithFlags_Values[q6 + 1] + | q6 : int(1..3)]), + and([y_ExplicitVarSizeWithFlags_Flags[q7] = false -> y_ExplicitVarSizeWithFlags_Values[q7] = 2 | q7 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q8 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q8] | q8 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q9]) | q9 : int(1..4)]), + 1 <= sum([toInt(x_Occurrence[q11]) | q11 : int(2..5)]), + and([x_Occurrence[q24] -> + or([x_ExplicitVarSizeWithFlags_Flags[q26] /\ x_ExplicitVarSizeWithFlags_Values[q26] = q24 | q26 : int(1..4)]) + | q24 : int(2..5)]), + and([x_ExplicitVarSizeWithFlags_Flags[q28] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q28]] + | q28 : int(1..4)]), + and([y_ExplicitVarSizeWithDummy[q12] < y_ExplicitVarSizeWithDummy[q12 + 1] \/ y_ExplicitVarSizeWithDummy[q12] = 6 + | q12 : int(1..3)]), + and([y_ExplicitVarSizeWithDummy[q13] = 6 -> y_ExplicitVarSizeWithDummy[q13 + 1] = 6 | q13 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q14] != 6) | q14 : int(1..4)]), + and([y_ExplicitVarSizeWithDummy[q17] != 6 -> + or([y_ExplicitVarSizeWithFlags_Flags[q19] /\ + y_ExplicitVarSizeWithFlags_Values[q19] = y_ExplicitVarSizeWithDummy[q17] + | q19 : int(1..4)]) + | q17 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q21] -> + or([y_ExplicitVarSizeWithDummy[q23] != 6 /\ + y_ExplicitVarSizeWithDummy[q23] = y_ExplicitVarSizeWithFlags_Values[q21] + | q23 : int(1..4)]) + | q21 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_4_4_1_3-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_4_4_1_3-solution000001.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_4_1_3-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_4_4_1_3-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_4_4_1_3-solution000002.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_4_1_3-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_4_4_1_3.eprime b/tests/exhaustive/basic/set09/expected/model_4_4_1_3.eprime new file mode 100644 index 0000000000..f2ea1ae61a --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_4_1_3.eprime @@ -0,0 +1,51 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +find x_Occurrence: matrix indexed by [int(2..5)] of bool +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_ExplicitVarSizeWithMarker_Marker: int(0..4) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +branching on + [x_Occurrence, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, + y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithFlags_Flags, + y_ExplicitVarSizeWithFlags_Values] +such that + and([x_ExplicitVarSizeWithFlags_Flags[q28] /\ y_ExplicitVarSizeWithFlags_Flags[q29] -> + x_ExplicitVarSizeWithFlags_Values[q28] + 2 = y_ExplicitVarSizeWithFlags_Values[q29] + | q28 : int(1..4), q29 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 2 | q2 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> + y_ExplicitVarSizeWithFlags_Values[q6] < y_ExplicitVarSizeWithFlags_Values[q6 + 1] + | q6 : int(1..3)]), + and([y_ExplicitVarSizeWithFlags_Flags[q7] = false -> y_ExplicitVarSizeWithFlags_Values[q7] = 2 | q7 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q8 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q8] | q8 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q9]) | q9 : int(1..4)]), + 1 <= sum([toInt(x_Occurrence[q11]) | q11 : int(2..5)]), + and([x_Occurrence[q23] -> + or([x_ExplicitVarSizeWithFlags_Flags[q25] /\ x_ExplicitVarSizeWithFlags_Values[q25] = q23 | q25 : int(1..4)]) + | q23 : int(2..5)]), + and([x_ExplicitVarSizeWithFlags_Flags[q27] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q27]] + | q27 : int(1..4)]), + and([q12 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> + y_ExplicitVarSizeWithMarker_Values[q12] < y_ExplicitVarSizeWithMarker_Values[q12 + 1] + | q12 : int(1..3)]), + and([q13 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q13] = 2 | q13 : int(1..4)]), + 1 <= y_ExplicitVarSizeWithMarker_Marker, + and([q16 <= y_ExplicitVarSizeWithMarker_Marker -> + or([y_ExplicitVarSizeWithFlags_Flags[q18] /\ + y_ExplicitVarSizeWithFlags_Values[q18] = y_ExplicitVarSizeWithMarker_Values[q16] + | q18 : int(1..4)]) + | q16 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q20] -> + or([q22 <= y_ExplicitVarSizeWithMarker_Marker /\ + y_ExplicitVarSizeWithMarker_Values[q22] = y_ExplicitVarSizeWithFlags_Values[q20] + | q22 : int(1..4)]) + | q20 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_4_4_1_4-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_4_4_1_4-solution000001.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_4_1_4-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_4_4_1_4-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_4_4_1_4-solution000002.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_4_1_4-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_4_4_1_4.eprime b/tests/exhaustive/basic/set09/expected/model_4_4_1_4.eprime new file mode 100644 index 0000000000..ca5e2cadb0 --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_4_1_4.eprime @@ -0,0 +1,33 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +find x_Occurrence: matrix indexed by [int(2..5)] of bool +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +branching on + [x_Occurrence, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, + y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values] +such that + and([x_ExplicitVarSizeWithFlags_Flags[q17] /\ y_ExplicitVarSizeWithFlags_Flags[q18] -> + x_ExplicitVarSizeWithFlags_Values[q17] + 2 = y_ExplicitVarSizeWithFlags_Values[q18] + | q17 : int(1..4), q18 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 2 | q2 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> + y_ExplicitVarSizeWithFlags_Values[q6] < y_ExplicitVarSizeWithFlags_Values[q6 + 1] + | q6 : int(1..3)]), + and([y_ExplicitVarSizeWithFlags_Flags[q7] = false -> y_ExplicitVarSizeWithFlags_Values[q7] = 2 | q7 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q8 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q8] | q8 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q9]) | q9 : int(1..4)]), + 1 <= sum([toInt(x_Occurrence[q11]) | q11 : int(2..5)]), + and([x_Occurrence[q12] -> + or([x_ExplicitVarSizeWithFlags_Flags[q14] /\ x_ExplicitVarSizeWithFlags_Values[q14] = q12 | q14 : int(1..4)]) + | q12 : int(2..5)]), + and([x_ExplicitVarSizeWithFlags_Flags[q16] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q16]] + | q16 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_4_4_2_1-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_4_4_2_1-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_4_2_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_4_4_2_1-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_4_4_2_1-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_4_2_1-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_4_4_2_1.eprime b/tests/exhaustive/basic/set09/expected/model_4_4_2_1.eprime new file mode 100644 index 0000000000..627fd329ca --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_4_2_1.eprime @@ -0,0 +1,48 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_Occurrence: matrix indexed by [int(2..5)] of bool +branching on + [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, y_Occurrence, + y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values] +such that + and([x_ExplicitVarSizeWithFlags_Flags[q29] /\ y_ExplicitVarSizeWithFlags_Flags[q30] -> + x_ExplicitVarSizeWithFlags_Values[q29] + 2 = y_ExplicitVarSizeWithFlags_Values[q30] + | q29 : int(1..4), q30 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 2 | q2 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> + y_ExplicitVarSizeWithFlags_Values[q6] < y_ExplicitVarSizeWithFlags_Values[q6 + 1] + | q6 : int(1..3)]), + and([y_ExplicitVarSizeWithFlags_Flags[q7] = false -> y_ExplicitVarSizeWithFlags_Values[q7] = 2 | q7 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q8 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q8] | q8 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q9]) | q9 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q11] < x_ExplicitVarSizeWithDummy[q11 + 1] \/ x_ExplicitVarSizeWithDummy[q11] = 6 + | q11 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q12] = 6 -> x_ExplicitVarSizeWithDummy[q12 + 1] = 6 | q12 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q13] != 6) | q13 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q16] != 6 -> + or([x_ExplicitVarSizeWithFlags_Flags[q18] /\ + x_ExplicitVarSizeWithFlags_Values[q18] = x_ExplicitVarSizeWithDummy[q16] + | q18 : int(1..4)]) + | q16 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q20] -> + or([x_ExplicitVarSizeWithDummy[q22] != 6 /\ + x_ExplicitVarSizeWithDummy[q22] = x_ExplicitVarSizeWithFlags_Values[q20] + | q22 : int(1..4)]) + | q20 : int(1..4)]), + 1 <= sum([toInt(y_Occurrence[q23]) | q23 : int(2..5)]), + and([y_Occurrence[q24] -> + or([y_ExplicitVarSizeWithFlags_Flags[q26] /\ y_ExplicitVarSizeWithFlags_Values[q26] = q24 | q26 : int(1..4)]) + | q24 : int(2..5)]), + and([y_ExplicitVarSizeWithFlags_Flags[q28] -> y_Occurrence[y_ExplicitVarSizeWithFlags_Values[q28]] + | q28 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_4_4_2_2-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_4_4_2_2-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_4_2_2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_4_4_2_2-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_4_4_2_2-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_4_2_2-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_4_4_2_2.eprime b/tests/exhaustive/basic/set09/expected/model_4_4_2_2.eprime new file mode 100644 index 0000000000..0002083a4b --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_4_2_2.eprime @@ -0,0 +1,56 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +branching on + [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, + y_ExplicitVarSizeWithDummy, y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values] +such that + and([x_ExplicitVarSizeWithFlags_Flags[q35] /\ y_ExplicitVarSizeWithFlags_Flags[q36] -> + x_ExplicitVarSizeWithFlags_Values[q35] + 2 = y_ExplicitVarSizeWithFlags_Values[q36] + | q35 : int(1..4), q36 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 2 | q2 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> + y_ExplicitVarSizeWithFlags_Values[q6] < y_ExplicitVarSizeWithFlags_Values[q6 + 1] + | q6 : int(1..3)]), + and([y_ExplicitVarSizeWithFlags_Flags[q7] = false -> y_ExplicitVarSizeWithFlags_Values[q7] = 2 | q7 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q8 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q8] | q8 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q9]) | q9 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q11] < x_ExplicitVarSizeWithDummy[q11 + 1] \/ x_ExplicitVarSizeWithDummy[q11] = 6 + | q11 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q12] = 6 -> x_ExplicitVarSizeWithDummy[q12 + 1] = 6 | q12 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q13] != 6) | q13 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q16] != 6 -> + or([x_ExplicitVarSizeWithFlags_Flags[q18] /\ + x_ExplicitVarSizeWithFlags_Values[q18] = x_ExplicitVarSizeWithDummy[q16] + | q18 : int(1..4)]) + | q16 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q20] -> + or([x_ExplicitVarSizeWithDummy[q22] != 6 /\ + x_ExplicitVarSizeWithDummy[q22] = x_ExplicitVarSizeWithFlags_Values[q20] + | q22 : int(1..4)]) + | q20 : int(1..4)]), + and([y_ExplicitVarSizeWithDummy[q23] < y_ExplicitVarSizeWithDummy[q23 + 1] \/ y_ExplicitVarSizeWithDummy[q23] = 6 + | q23 : int(1..3)]), + and([y_ExplicitVarSizeWithDummy[q24] = 6 -> y_ExplicitVarSizeWithDummy[q24 + 1] = 6 | q24 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q25] != 6) | q25 : int(1..4)]), + and([y_ExplicitVarSizeWithDummy[q28] != 6 -> + or([y_ExplicitVarSizeWithFlags_Flags[q30] /\ + y_ExplicitVarSizeWithFlags_Values[q30] = y_ExplicitVarSizeWithDummy[q28] + | q30 : int(1..4)]) + | q28 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q32] -> + or([y_ExplicitVarSizeWithDummy[q34] != 6 /\ + y_ExplicitVarSizeWithDummy[q34] = y_ExplicitVarSizeWithFlags_Values[q32] + | q34 : int(1..4)]) + | q32 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_4_4_2_3-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_4_4_2_3-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_4_2_3-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_4_4_2_3-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_4_4_2_3-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_4_2_3-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_4_4_2_3.eprime b/tests/exhaustive/basic/set09/expected/model_4_4_2_3.eprime new file mode 100644 index 0000000000..95276e3dcb --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_4_2_3.eprime @@ -0,0 +1,59 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_ExplicitVarSizeWithMarker_Marker: int(0..4) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +branching on + [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, + y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithFlags_Flags, + y_ExplicitVarSizeWithFlags_Values] +such that + and([x_ExplicitVarSizeWithFlags_Flags[q34] /\ y_ExplicitVarSizeWithFlags_Flags[q35] -> + x_ExplicitVarSizeWithFlags_Values[q34] + 2 = y_ExplicitVarSizeWithFlags_Values[q35] + | q34 : int(1..4), q35 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 2 | q2 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> + y_ExplicitVarSizeWithFlags_Values[q6] < y_ExplicitVarSizeWithFlags_Values[q6 + 1] + | q6 : int(1..3)]), + and([y_ExplicitVarSizeWithFlags_Flags[q7] = false -> y_ExplicitVarSizeWithFlags_Values[q7] = 2 | q7 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q8 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q8] | q8 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q9]) | q9 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q11] < x_ExplicitVarSizeWithDummy[q11 + 1] \/ x_ExplicitVarSizeWithDummy[q11] = 6 + | q11 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q12] = 6 -> x_ExplicitVarSizeWithDummy[q12 + 1] = 6 | q12 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q13] != 6) | q13 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q16] != 6 -> + or([x_ExplicitVarSizeWithFlags_Flags[q18] /\ + x_ExplicitVarSizeWithFlags_Values[q18] = x_ExplicitVarSizeWithDummy[q16] + | q18 : int(1..4)]) + | q16 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q20] -> + or([x_ExplicitVarSizeWithDummy[q22] != 6 /\ + x_ExplicitVarSizeWithDummy[q22] = x_ExplicitVarSizeWithFlags_Values[q20] + | q22 : int(1..4)]) + | q20 : int(1..4)]), + and([q23 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> + y_ExplicitVarSizeWithMarker_Values[q23] < y_ExplicitVarSizeWithMarker_Values[q23 + 1] + | q23 : int(1..3)]), + and([q24 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q24] = 2 | q24 : int(1..4)]), + 1 <= y_ExplicitVarSizeWithMarker_Marker, + and([q27 <= y_ExplicitVarSizeWithMarker_Marker -> + or([y_ExplicitVarSizeWithFlags_Flags[q29] /\ + y_ExplicitVarSizeWithFlags_Values[q29] = y_ExplicitVarSizeWithMarker_Values[q27] + | q29 : int(1..4)]) + | q27 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q31] -> + or([q33 <= y_ExplicitVarSizeWithMarker_Marker /\ + y_ExplicitVarSizeWithMarker_Values[q33] = y_ExplicitVarSizeWithFlags_Values[q31] + | q33 : int(1..4)]) + | q31 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_4_4_2_4-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_4_4_2_4-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_4_2_4-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_4_4_2_4-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_4_4_2_4-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_4_2_4-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_4_4_2_4.eprime b/tests/exhaustive/basic/set09/expected/model_4_4_2_4.eprime new file mode 100644 index 0000000000..05c62046ee --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_4_2_4.eprime @@ -0,0 +1,41 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +branching on + [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, + y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values] +such that + and([x_ExplicitVarSizeWithFlags_Flags[q23] /\ y_ExplicitVarSizeWithFlags_Flags[q24] -> + x_ExplicitVarSizeWithFlags_Values[q23] + 2 = y_ExplicitVarSizeWithFlags_Values[q24] + | q23 : int(1..4), q24 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 2 | q2 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> + y_ExplicitVarSizeWithFlags_Values[q6] < y_ExplicitVarSizeWithFlags_Values[q6 + 1] + | q6 : int(1..3)]), + and([y_ExplicitVarSizeWithFlags_Flags[q7] = false -> y_ExplicitVarSizeWithFlags_Values[q7] = 2 | q7 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q8 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q8] | q8 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q9]) | q9 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q11] < x_ExplicitVarSizeWithDummy[q11 + 1] \/ x_ExplicitVarSizeWithDummy[q11] = 6 + | q11 : int(1..3)]), + and([x_ExplicitVarSizeWithDummy[q12] = 6 -> x_ExplicitVarSizeWithDummy[q12 + 1] = 6 | q12 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithDummy[q13] != 6) | q13 : int(1..4)]), + and([x_ExplicitVarSizeWithDummy[q16] != 6 -> + or([x_ExplicitVarSizeWithFlags_Flags[q18] /\ + x_ExplicitVarSizeWithFlags_Values[q18] = x_ExplicitVarSizeWithDummy[q16] + | q18 : int(1..4)]) + | q16 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q20] -> + or([x_ExplicitVarSizeWithDummy[q22] != 6 /\ + x_ExplicitVarSizeWithDummy[q22] = x_ExplicitVarSizeWithFlags_Values[q20] + | q22 : int(1..4)]) + | q20 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_4_4_3_1-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_4_4_3_1-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_4_3_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_4_4_3_1-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_4_4_3_1-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_4_3_1-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_4_4_3_1.eprime b/tests/exhaustive/basic/set09/expected/model_4_4_3_1.eprime new file mode 100644 index 0000000000..310494b661 --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_4_3_1.eprime @@ -0,0 +1,51 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_Occurrence: matrix indexed by [int(2..5)] of bool +branching on + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithFlags_Flags, + x_ExplicitVarSizeWithFlags_Values, y_Occurrence, y_ExplicitVarSizeWithFlags_Flags, + y_ExplicitVarSizeWithFlags_Values] +such that + and([x_ExplicitVarSizeWithFlags_Flags[q28] /\ y_ExplicitVarSizeWithFlags_Flags[q29] -> + x_ExplicitVarSizeWithFlags_Values[q28] + 2 = y_ExplicitVarSizeWithFlags_Values[q29] + | q28 : int(1..4), q29 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 2 | q2 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> + y_ExplicitVarSizeWithFlags_Values[q6] < y_ExplicitVarSizeWithFlags_Values[q6 + 1] + | q6 : int(1..3)]), + and([y_ExplicitVarSizeWithFlags_Flags[q7] = false -> y_ExplicitVarSizeWithFlags_Values[q7] = 2 | q7 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q8 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q8] | q8 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q9]) | q9 : int(1..4)]), + and([q11 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q11] < x_ExplicitVarSizeWithMarker_Values[q11 + 1] + | q11 : int(1..3)]), + and([q12 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q12] = 2 | q12 : int(1..4)]), + 1 <= x_ExplicitVarSizeWithMarker_Marker, + and([q15 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithFlags_Flags[q17] /\ + x_ExplicitVarSizeWithFlags_Values[q17] = x_ExplicitVarSizeWithMarker_Values[q15] + | q17 : int(1..4)]) + | q15 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q19] -> + or([q21 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q21] = x_ExplicitVarSizeWithFlags_Values[q19] + | q21 : int(1..4)]) + | q19 : int(1..4)]), + 1 <= sum([toInt(y_Occurrence[q22]) | q22 : int(2..5)]), + and([y_Occurrence[q23] -> + or([y_ExplicitVarSizeWithFlags_Flags[q25] /\ y_ExplicitVarSizeWithFlags_Values[q25] = q23 | q25 : int(1..4)]) + | q23 : int(2..5)]), + and([y_ExplicitVarSizeWithFlags_Flags[q27] -> y_Occurrence[y_ExplicitVarSizeWithFlags_Values[q27]] + | q27 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_4_4_3_2-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_4_4_3_2-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_4_3_2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_4_4_3_2-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_4_4_3_2-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_4_3_2-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_4_4_3_2.eprime b/tests/exhaustive/basic/set09/expected/model_4_4_3_2.eprime new file mode 100644 index 0000000000..8fbea0fc93 --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_4_3_2.eprime @@ -0,0 +1,59 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +branching on + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithFlags_Flags, + x_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithDummy, y_ExplicitVarSizeWithFlags_Flags, + y_ExplicitVarSizeWithFlags_Values] +such that + and([x_ExplicitVarSizeWithFlags_Flags[q34] /\ y_ExplicitVarSizeWithFlags_Flags[q35] -> + x_ExplicitVarSizeWithFlags_Values[q34] + 2 = y_ExplicitVarSizeWithFlags_Values[q35] + | q34 : int(1..4), q35 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 2 | q2 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> + y_ExplicitVarSizeWithFlags_Values[q6] < y_ExplicitVarSizeWithFlags_Values[q6 + 1] + | q6 : int(1..3)]), + and([y_ExplicitVarSizeWithFlags_Flags[q7] = false -> y_ExplicitVarSizeWithFlags_Values[q7] = 2 | q7 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q8 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q8] | q8 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q9]) | q9 : int(1..4)]), + and([q11 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q11] < x_ExplicitVarSizeWithMarker_Values[q11 + 1] + | q11 : int(1..3)]), + and([q12 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q12] = 2 | q12 : int(1..4)]), + 1 <= x_ExplicitVarSizeWithMarker_Marker, + and([q15 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithFlags_Flags[q17] /\ + x_ExplicitVarSizeWithFlags_Values[q17] = x_ExplicitVarSizeWithMarker_Values[q15] + | q17 : int(1..4)]) + | q15 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q19] -> + or([q21 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q21] = x_ExplicitVarSizeWithFlags_Values[q19] + | q21 : int(1..4)]) + | q19 : int(1..4)]), + and([y_ExplicitVarSizeWithDummy[q22] < y_ExplicitVarSizeWithDummy[q22 + 1] \/ y_ExplicitVarSizeWithDummy[q22] = 6 + | q22 : int(1..3)]), + and([y_ExplicitVarSizeWithDummy[q23] = 6 -> y_ExplicitVarSizeWithDummy[q23 + 1] = 6 | q23 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q24] != 6) | q24 : int(1..4)]), + and([y_ExplicitVarSizeWithDummy[q27] != 6 -> + or([y_ExplicitVarSizeWithFlags_Flags[q29] /\ + y_ExplicitVarSizeWithFlags_Values[q29] = y_ExplicitVarSizeWithDummy[q27] + | q29 : int(1..4)]) + | q27 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q31] -> + or([y_ExplicitVarSizeWithDummy[q33] != 6 /\ + y_ExplicitVarSizeWithDummy[q33] = y_ExplicitVarSizeWithFlags_Values[q31] + | q33 : int(1..4)]) + | q31 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_4_4_3_3-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_4_4_3_3-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_4_3_3-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_4_4_3_3-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_4_4_3_3-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_4_3_3-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_4_4_3_3.eprime b/tests/exhaustive/basic/set09/expected/model_4_4_3_3.eprime new file mode 100644 index 0000000000..a1e6b33da9 --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_4_3_3.eprime @@ -0,0 +1,61 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_ExplicitVarSizeWithMarker_Marker: int(0..4) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +branching on + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithFlags_Flags, + x_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values, + y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values] +such that + and([x_ExplicitVarSizeWithFlags_Flags[q33] /\ y_ExplicitVarSizeWithFlags_Flags[q34] -> + x_ExplicitVarSizeWithFlags_Values[q33] + 2 = y_ExplicitVarSizeWithFlags_Values[q34] + | q33 : int(1..4), q34 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 2 | q2 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> + y_ExplicitVarSizeWithFlags_Values[q6] < y_ExplicitVarSizeWithFlags_Values[q6 + 1] + | q6 : int(1..3)]), + and([y_ExplicitVarSizeWithFlags_Flags[q7] = false -> y_ExplicitVarSizeWithFlags_Values[q7] = 2 | q7 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q8 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q8] | q8 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q9]) | q9 : int(1..4)]), + and([q11 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q11] < x_ExplicitVarSizeWithMarker_Values[q11 + 1] + | q11 : int(1..3)]), + and([q12 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q12] = 2 | q12 : int(1..4)]), + 1 <= x_ExplicitVarSizeWithMarker_Marker, + and([q15 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithFlags_Flags[q17] /\ + x_ExplicitVarSizeWithFlags_Values[q17] = x_ExplicitVarSizeWithMarker_Values[q15] + | q17 : int(1..4)]) + | q15 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q19] -> + or([q21 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q21] = x_ExplicitVarSizeWithFlags_Values[q19] + | q21 : int(1..4)]) + | q19 : int(1..4)]), + and([q22 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> + y_ExplicitVarSizeWithMarker_Values[q22] < y_ExplicitVarSizeWithMarker_Values[q22 + 1] + | q22 : int(1..3)]), + and([q23 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q23] = 2 | q23 : int(1..4)]), + 1 <= y_ExplicitVarSizeWithMarker_Marker, + and([q26 <= y_ExplicitVarSizeWithMarker_Marker -> + or([y_ExplicitVarSizeWithFlags_Flags[q28] /\ + y_ExplicitVarSizeWithFlags_Values[q28] = y_ExplicitVarSizeWithMarker_Values[q26] + | q28 : int(1..4)]) + | q26 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q30] -> + or([q32 <= y_ExplicitVarSizeWithMarker_Marker /\ + y_ExplicitVarSizeWithMarker_Values[q32] = y_ExplicitVarSizeWithFlags_Values[q30] + | q32 : int(1..4)]) + | q30 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_4_4_3_4-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_4_4_3_4-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_4_3_4-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_4_4_3_4-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_4_4_3_4-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_4_3_4-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_4_4_3_4.eprime b/tests/exhaustive/basic/set09/expected/model_4_4_3_4.eprime new file mode 100644 index 0000000000..fd4427c028 --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_4_3_4.eprime @@ -0,0 +1,43 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +find x_ExplicitVarSizeWithMarker_Marker: int(0..4) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +branching on + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithFlags_Flags, + x_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values] +such that + and([x_ExplicitVarSizeWithFlags_Flags[q22] /\ y_ExplicitVarSizeWithFlags_Flags[q23] -> + x_ExplicitVarSizeWithFlags_Values[q22] + 2 = y_ExplicitVarSizeWithFlags_Values[q23] + | q22 : int(1..4), q23 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 2 | q2 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> + y_ExplicitVarSizeWithFlags_Values[q6] < y_ExplicitVarSizeWithFlags_Values[q6 + 1] + | q6 : int(1..3)]), + and([y_ExplicitVarSizeWithFlags_Flags[q7] = false -> y_ExplicitVarSizeWithFlags_Values[q7] = 2 | q7 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q8 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q8] | q8 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q9]) | q9 : int(1..4)]), + and([q11 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q11] < x_ExplicitVarSizeWithMarker_Values[q11 + 1] + | q11 : int(1..3)]), + and([q12 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q12] = 2 | q12 : int(1..4)]), + 1 <= x_ExplicitVarSizeWithMarker_Marker, + and([q15 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithFlags_Flags[q17] /\ + x_ExplicitVarSizeWithFlags_Values[q17] = x_ExplicitVarSizeWithMarker_Values[q15] + | q17 : int(1..4)]) + | q15 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q19] -> + or([q21 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q21] = x_ExplicitVarSizeWithFlags_Values[q19] + | q21 : int(1..4)]) + | q19 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_4_4_4_1-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_4_4_4_1-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_4_4_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_4_4_4_1-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_4_4_4_1-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_4_4_1-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_4_4_4_1.eprime b/tests/exhaustive/basic/set09/expected/model_4_4_4_1.eprime new file mode 100644 index 0000000000..3dd731472f --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_4_4_1.eprime @@ -0,0 +1,33 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_Occurrence: matrix indexed by [int(2..5)] of bool +branching on + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, y_Occurrence, + y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values] +such that + and([x_ExplicitVarSizeWithFlags_Flags[q17] /\ y_ExplicitVarSizeWithFlags_Flags[q18] -> + x_ExplicitVarSizeWithFlags_Values[q17] + 2 = y_ExplicitVarSizeWithFlags_Values[q18] + | q17 : int(1..4), q18 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 2 | q2 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> + y_ExplicitVarSizeWithFlags_Values[q6] < y_ExplicitVarSizeWithFlags_Values[q6 + 1] + | q6 : int(1..3)]), + and([y_ExplicitVarSizeWithFlags_Flags[q7] = false -> y_ExplicitVarSizeWithFlags_Values[q7] = 2 | q7 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q8 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q8] | q8 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q9]) | q9 : int(1..4)]), + 1 <= sum([toInt(y_Occurrence[q11]) | q11 : int(2..5)]), + and([y_Occurrence[q12] -> + or([y_ExplicitVarSizeWithFlags_Flags[q14] /\ y_ExplicitVarSizeWithFlags_Values[q14] = q12 | q14 : int(1..4)]) + | q12 : int(2..5)]), + and([y_ExplicitVarSizeWithFlags_Flags[q16] -> y_Occurrence[y_ExplicitVarSizeWithFlags_Values[q16]] + | q16 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_4_4_4_2-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_4_4_4_2-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_4_4_2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_4_4_4_2-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_4_4_4_2-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_4_4_2-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_4_4_4_2.eprime b/tests/exhaustive/basic/set09/expected/model_4_4_4_2.eprime new file mode 100644 index 0000000000..256ad5b5d2 --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_4_4_2.eprime @@ -0,0 +1,41 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4)] of int(2..6) +branching on + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithDummy, + y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values] +such that + and([x_ExplicitVarSizeWithFlags_Flags[q23] /\ y_ExplicitVarSizeWithFlags_Flags[q24] -> + x_ExplicitVarSizeWithFlags_Values[q23] + 2 = y_ExplicitVarSizeWithFlags_Values[q24] + | q23 : int(1..4), q24 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 2 | q2 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> + y_ExplicitVarSizeWithFlags_Values[q6] < y_ExplicitVarSizeWithFlags_Values[q6 + 1] + | q6 : int(1..3)]), + and([y_ExplicitVarSizeWithFlags_Flags[q7] = false -> y_ExplicitVarSizeWithFlags_Values[q7] = 2 | q7 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q8 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q8] | q8 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q9]) | q9 : int(1..4)]), + and([y_ExplicitVarSizeWithDummy[q11] < y_ExplicitVarSizeWithDummy[q11 + 1] \/ y_ExplicitVarSizeWithDummy[q11] = 6 + | q11 : int(1..3)]), + and([y_ExplicitVarSizeWithDummy[q12] = 6 -> y_ExplicitVarSizeWithDummy[q12 + 1] = 6 | q12 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithDummy[q13] != 6) | q13 : int(1..4)]), + and([y_ExplicitVarSizeWithDummy[q16] != 6 -> + or([y_ExplicitVarSizeWithFlags_Flags[q18] /\ + y_ExplicitVarSizeWithFlags_Values[q18] = y_ExplicitVarSizeWithDummy[q16] + | q18 : int(1..4)]) + | q16 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q20] -> + or([y_ExplicitVarSizeWithDummy[q22] != 6 /\ + y_ExplicitVarSizeWithDummy[q22] = y_ExplicitVarSizeWithFlags_Values[q20] + | q22 : int(1..4)]) + | q20 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_4_4_4_3-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_4_4_4_3-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_4_4_3-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_4_4_4_3-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_4_4_4_3-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_4_4_3-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_4_4_4_3.eprime b/tests/exhaustive/basic/set09/expected/model_4_4_4_3.eprime new file mode 100644 index 0000000000..c694863719 --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_4_4_3.eprime @@ -0,0 +1,43 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_ExplicitVarSizeWithMarker_Marker: int(0..4) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4)] of int(2..5) +branching on + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithMarker_Marker, + y_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values] +such that + and([x_ExplicitVarSizeWithFlags_Flags[q22] /\ y_ExplicitVarSizeWithFlags_Flags[q23] -> + x_ExplicitVarSizeWithFlags_Values[q22] + 2 = y_ExplicitVarSizeWithFlags_Values[q23] + | q22 : int(1..4), q23 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 2 | q2 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> + y_ExplicitVarSizeWithFlags_Values[q6] < y_ExplicitVarSizeWithFlags_Values[q6 + 1] + | q6 : int(1..3)]), + and([y_ExplicitVarSizeWithFlags_Flags[q7] = false -> y_ExplicitVarSizeWithFlags_Values[q7] = 2 | q7 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q8 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q8] | q8 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q9]) | q9 : int(1..4)]), + and([q11 + 1 <= y_ExplicitVarSizeWithMarker_Marker -> + y_ExplicitVarSizeWithMarker_Values[q11] < y_ExplicitVarSizeWithMarker_Values[q11 + 1] + | q11 : int(1..3)]), + and([q12 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[q12] = 2 | q12 : int(1..4)]), + 1 <= y_ExplicitVarSizeWithMarker_Marker, + and([q15 <= y_ExplicitVarSizeWithMarker_Marker -> + or([y_ExplicitVarSizeWithFlags_Flags[q17] /\ + y_ExplicitVarSizeWithFlags_Values[q17] = y_ExplicitVarSizeWithMarker_Values[q15] + | q17 : int(1..4)]) + | q15 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q19] -> + or([q21 <= y_ExplicitVarSizeWithMarker_Marker /\ + y_ExplicitVarSizeWithMarker_Values[q21] = y_ExplicitVarSizeWithFlags_Values[q19] + | q21 : int(1..4)]) + | q19 : int(1..4)]) + diff --git a/tests/exhaustive/basic/set09/expected/model_4_4_4_4-solution000001.solution b/tests/exhaustive/basic/set09/expected/model_4_4_4_4-solution000001.solution new file mode 100644 index 0000000000..48003f5fce --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_4_4_4-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {2} +letting y be {4} diff --git a/tests/exhaustive/basic/set09/expected/model_4_4_4_4-solution000002.solution b/tests/exhaustive/basic/set09/expected/model_4_4_4_4-solution000002.solution new file mode 100644 index 0000000000..0b94905e4c --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_4_4_4-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {3} +letting y be {5} diff --git a/tests/exhaustive/basic/set09/expected/model_4_4_4_4.eprime b/tests/exhaustive/basic/set09/expected/model_4_4_4_4.eprime new file mode 100644 index 0000000000..1741be5b67 --- /dev/null +++ b/tests/exhaustive/basic/set09/expected/model_4_4_4_4.eprime @@ -0,0 +1,26 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..4)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..4)] of int(2..5) +branching on + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithFlags_Flags, + y_ExplicitVarSizeWithFlags_Values] +such that + and([x_ExplicitVarSizeWithFlags_Flags[q11] /\ y_ExplicitVarSizeWithFlags_Flags[q12] -> + x_ExplicitVarSizeWithFlags_Values[q11] + 2 = y_ExplicitVarSizeWithFlags_Values[q12] + | q11 : int(1..4), q12 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] + | q1 : int(1..3)]), + and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 2 | q2 : int(1..4)]), + and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..3)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q4]) | q4 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> + y_ExplicitVarSizeWithFlags_Values[q6] < y_ExplicitVarSizeWithFlags_Values[q6 + 1] + | q6 : int(1..3)]), + and([y_ExplicitVarSizeWithFlags_Flags[q7] = false -> y_ExplicitVarSizeWithFlags_Values[q7] = 2 | q7 : int(1..4)]), + and([y_ExplicitVarSizeWithFlags_Flags[q8 + 1] -> y_ExplicitVarSizeWithFlags_Flags[q8] | q8 : int(1..3)]), + 1 <= sum([toInt(y_ExplicitVarSizeWithFlags_Flags[q9]) | q9 : int(1..4)]) + diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_1-solution000001.solution b/tests/exhaustive/basic/setOfSet01/expected/model_1-solution000001.solution new file mode 100644 index 0000000000..1a734343d9 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet01/expected/model_1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {} diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_1-solution000002.solution b/tests/exhaustive/basic/setOfSet01/expected/model_1-solution000002.solution new file mode 100644 index 0000000000..7c5b3bfc58 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet01/expected/model_1-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {{}} diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_1-solution000003.solution b/tests/exhaustive/basic/setOfSet01/expected/model_1-solution000003.solution new file mode 100644 index 0000000000..550c68f48c --- /dev/null +++ b/tests/exhaustive/basic/setOfSet01/expected/model_1-solution000003.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting x be {{2}} +$ Visualisation for x +$ 2 + diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_1-solution000004.solution b/tests/exhaustive/basic/setOfSet01/expected/model_1-solution000004.solution new file mode 100644 index 0000000000..69bc828bbc --- /dev/null +++ b/tests/exhaustive/basic/setOfSet01/expected/model_1-solution000004.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting x be {{1}} +$ Visualisation for x +$ 1 + diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_1-solution000005.solution b/tests/exhaustive/basic/setOfSet01/expected/model_1-solution000005.solution new file mode 100644 index 0000000000..114bad5315 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet01/expected/model_1-solution000005.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting x be {{1, 2}} +$ Visualisation for x +$ 1 2 + diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_1-solution000006.solution b/tests/exhaustive/basic/setOfSet01/expected/model_1-solution000006.solution new file mode 100644 index 0000000000..c8946f3d06 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet01/expected/model_1-solution000006.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{}, {2}} +$ Visualisation for x +$ +$ 2 + diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_1-solution000007.solution b/tests/exhaustive/basic/setOfSet01/expected/model_1-solution000007.solution new file mode 100644 index 0000000000..3ec452354e --- /dev/null +++ b/tests/exhaustive/basic/setOfSet01/expected/model_1-solution000007.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{}, {1}} +$ Visualisation for x +$ +$ 1 + diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_1-solution000008.solution b/tests/exhaustive/basic/setOfSet01/expected/model_1-solution000008.solution new file mode 100644 index 0000000000..af16592c51 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet01/expected/model_1-solution000008.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{1}, {2}} +$ Visualisation for x +$ 1 +$ 2 + diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_1-solution000009.solution b/tests/exhaustive/basic/setOfSet01/expected/model_1-solution000009.solution new file mode 100644 index 0000000000..a6c0b6a43e --- /dev/null +++ b/tests/exhaustive/basic/setOfSet01/expected/model_1-solution000009.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{}, {1, 2}} +$ Visualisation for x +$ +$ 1 2 + diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_1-solution000010.solution b/tests/exhaustive/basic/setOfSet01/expected/model_1-solution000010.solution new file mode 100644 index 0000000000..9bf2af0712 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet01/expected/model_1-solution000010.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{1, 2}, {2}} +$ Visualisation for x +$ 1 2 +$ 2 + diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_1-solution000011.solution b/tests/exhaustive/basic/setOfSet01/expected/model_1-solution000011.solution new file mode 100644 index 0000000000..38937c9389 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet01/expected/model_1-solution000011.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{1}, {1, 2}} +$ Visualisation for x +$ 1 +$ 1 2 + diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_1-solution000012.solution b/tests/exhaustive/basic/setOfSet01/expected/model_1-solution000012.solution new file mode 100644 index 0000000000..f1a04b347c --- /dev/null +++ b/tests/exhaustive/basic/setOfSet01/expected/model_1-solution000012.solution @@ -0,0 +1,8 @@ +language Essence 1.3 + +letting x be {{}, {1}, {2}} +$ Visualisation for x +$ +$ 1 +$ 2 + diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_1-solution000013.solution b/tests/exhaustive/basic/setOfSet01/expected/model_1-solution000013.solution new file mode 100644 index 0000000000..b1673f700a --- /dev/null +++ b/tests/exhaustive/basic/setOfSet01/expected/model_1-solution000013.solution @@ -0,0 +1,8 @@ +language Essence 1.3 + +letting x be {{}, {1, 2}, {2}} +$ Visualisation for x +$ +$ 1 2 +$ 2 + diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_1-solution000014.solution b/tests/exhaustive/basic/setOfSet01/expected/model_1-solution000014.solution new file mode 100644 index 0000000000..8400fcb8c1 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet01/expected/model_1-solution000014.solution @@ -0,0 +1,8 @@ +language Essence 1.3 + +letting x be {{}, {1}, {1, 2}} +$ Visualisation for x +$ +$ 1 +$ 1 2 + diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_1-solution000015.solution b/tests/exhaustive/basic/setOfSet01/expected/model_1-solution000015.solution new file mode 100644 index 0000000000..7c7f2e98ea --- /dev/null +++ b/tests/exhaustive/basic/setOfSet01/expected/model_1-solution000015.solution @@ -0,0 +1,8 @@ +language Essence 1.3 + +letting x be {{1}, {1, 2}, {2}} +$ Visualisation for x +$ 1 +$ 1 2 +$ 2 + diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_1-solution000016.solution b/tests/exhaustive/basic/setOfSet01/expected/model_1-solution000016.solution new file mode 100644 index 0000000000..29f10f5fb0 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet01/expected/model_1-solution000016.solution @@ -0,0 +1,9 @@ +language Essence 1.3 + +letting x be {{}, {1}, {1, 2}, {2}} +$ Visualisation for x +$ +$ 1 +$ 1 2 +$ 2 + diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_1.eprime b/tests/exhaustive/basic/setOfSet01/expected/model_1.eprime new file mode 100644 index 0000000000..ec206e1289 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet01/expected/model_1.eprime @@ -0,0 +1,14 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarkerR2_Marker: int(0..4) +find x_ExplicitVarSizeWithMarkerR2_Values_Occurrence: matrix indexed by [int(1..4), int(1..2)] of bool +branching on [x_ExplicitVarSizeWithMarkerR2_Marker, x_ExplicitVarSizeWithMarkerR2_Values_Occurrence] +such that + and([q1 + 1 <= x_ExplicitVarSizeWithMarkerR2_Marker -> + [-toInt(x_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q1, q5]) | q5 : int(1..2)] x_ExplicitVarSizeWithMarkerR2_Marker -> + and([x_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q2, q7] = false | q7 : int(1..2)]) + | q2 : int(1..4)]) + diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_2-solution000001.solution b/tests/exhaustive/basic/setOfSet01/expected/model_2-solution000001.solution new file mode 100644 index 0000000000..1a734343d9 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet01/expected/model_2-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {} diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_2-solution000002.solution b/tests/exhaustive/basic/setOfSet01/expected/model_2-solution000002.solution new file mode 100644 index 0000000000..114bad5315 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet01/expected/model_2-solution000002.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting x be {{1, 2}} +$ Visualisation for x +$ 1 2 + diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_2-solution000003.solution b/tests/exhaustive/basic/setOfSet01/expected/model_2-solution000003.solution new file mode 100644 index 0000000000..69bc828bbc --- /dev/null +++ b/tests/exhaustive/basic/setOfSet01/expected/model_2-solution000003.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting x be {{1}} +$ Visualisation for x +$ 1 + diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_2-solution000004.solution b/tests/exhaustive/basic/setOfSet01/expected/model_2-solution000004.solution new file mode 100644 index 0000000000..550c68f48c --- /dev/null +++ b/tests/exhaustive/basic/setOfSet01/expected/model_2-solution000004.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting x be {{2}} +$ Visualisation for x +$ 2 + diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_2-solution000005.solution b/tests/exhaustive/basic/setOfSet01/expected/model_2-solution000005.solution new file mode 100644 index 0000000000..7c5b3bfc58 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet01/expected/model_2-solution000005.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {{}} diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_2-solution000006.solution b/tests/exhaustive/basic/setOfSet01/expected/model_2-solution000006.solution new file mode 100644 index 0000000000..38937c9389 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet01/expected/model_2-solution000006.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{1}, {1, 2}} +$ Visualisation for x +$ 1 +$ 1 2 + diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_2-solution000007.solution b/tests/exhaustive/basic/setOfSet01/expected/model_2-solution000007.solution new file mode 100644 index 0000000000..9bf2af0712 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet01/expected/model_2-solution000007.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{1, 2}, {2}} +$ Visualisation for x +$ 1 2 +$ 2 + diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_2-solution000008.solution b/tests/exhaustive/basic/setOfSet01/expected/model_2-solution000008.solution new file mode 100644 index 0000000000..a6c0b6a43e --- /dev/null +++ b/tests/exhaustive/basic/setOfSet01/expected/model_2-solution000008.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{}, {1, 2}} +$ Visualisation for x +$ +$ 1 2 + diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_2-solution000009.solution b/tests/exhaustive/basic/setOfSet01/expected/model_2-solution000009.solution new file mode 100644 index 0000000000..af16592c51 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet01/expected/model_2-solution000009.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{1}, {2}} +$ Visualisation for x +$ 1 +$ 2 + diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_2-solution000010.solution b/tests/exhaustive/basic/setOfSet01/expected/model_2-solution000010.solution new file mode 100644 index 0000000000..3ec452354e --- /dev/null +++ b/tests/exhaustive/basic/setOfSet01/expected/model_2-solution000010.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{}, {1}} +$ Visualisation for x +$ +$ 1 + diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_2-solution000011.solution b/tests/exhaustive/basic/setOfSet01/expected/model_2-solution000011.solution new file mode 100644 index 0000000000..c8946f3d06 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet01/expected/model_2-solution000011.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{}, {2}} +$ Visualisation for x +$ +$ 2 + diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_2-solution000012.solution b/tests/exhaustive/basic/setOfSet01/expected/model_2-solution000012.solution new file mode 100644 index 0000000000..7c7f2e98ea --- /dev/null +++ b/tests/exhaustive/basic/setOfSet01/expected/model_2-solution000012.solution @@ -0,0 +1,8 @@ +language Essence 1.3 + +letting x be {{1}, {1, 2}, {2}} +$ Visualisation for x +$ 1 +$ 1 2 +$ 2 + diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_2-solution000013.solution b/tests/exhaustive/basic/setOfSet01/expected/model_2-solution000013.solution new file mode 100644 index 0000000000..8400fcb8c1 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet01/expected/model_2-solution000013.solution @@ -0,0 +1,8 @@ +language Essence 1.3 + +letting x be {{}, {1}, {1, 2}} +$ Visualisation for x +$ +$ 1 +$ 1 2 + diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_2-solution000014.solution b/tests/exhaustive/basic/setOfSet01/expected/model_2-solution000014.solution new file mode 100644 index 0000000000..b1673f700a --- /dev/null +++ b/tests/exhaustive/basic/setOfSet01/expected/model_2-solution000014.solution @@ -0,0 +1,8 @@ +language Essence 1.3 + +letting x be {{}, {1, 2}, {2}} +$ Visualisation for x +$ +$ 1 2 +$ 2 + diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_2-solution000015.solution b/tests/exhaustive/basic/setOfSet01/expected/model_2-solution000015.solution new file mode 100644 index 0000000000..f1a04b347c --- /dev/null +++ b/tests/exhaustive/basic/setOfSet01/expected/model_2-solution000015.solution @@ -0,0 +1,8 @@ +language Essence 1.3 + +letting x be {{}, {1}, {2}} +$ Visualisation for x +$ +$ 1 +$ 2 + diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_2-solution000016.solution b/tests/exhaustive/basic/setOfSet01/expected/model_2-solution000016.solution new file mode 100644 index 0000000000..29f10f5fb0 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet01/expected/model_2-solution000016.solution @@ -0,0 +1,9 @@ +language Essence 1.3 + +letting x be {{}, {1}, {1, 2}, {2}} +$ Visualisation for x +$ +$ 1 +$ 1 2 +$ 2 + diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_2.eprime b/tests/exhaustive/basic/setOfSet01/expected/model_2.eprime new file mode 100644 index 0000000000..2bba65c207 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet01/expected/model_2.eprime @@ -0,0 +1,24 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarkerR6_Marker: int(0..4) +find x_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy: + matrix indexed by [int(1..4), int(1..2)] of int(1..3) +branching on [x_ExplicitVarSizeWithMarkerR6_Marker, x_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy] +such that + and([q1 + 1 <= x_ExplicitVarSizeWithMarkerR6_Marker -> + [x_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q1, q8] | q8 : int(1..2)] x_ExplicitVarSizeWithMarkerR6_Marker -> + and([x_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q2, q10] = 1 | q10 : int(1..2)]) + | q2 : int(1..4)]), + and([q3 <= x_ExplicitVarSizeWithMarkerR6_Marker -> + x_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q3, 1] < + x_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q3, 2] + \/ x_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q3, 1] = 3 + | q3 : int(1..4)]), + and([q3 <= x_ExplicitVarSizeWithMarkerR6_Marker -> + (x_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q3, 1] = 3 -> + x_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q3, 2] = 3) + | q3 : int(1..4)]) + diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_3-solution000001.solution b/tests/exhaustive/basic/setOfSet01/expected/model_3-solution000001.solution new file mode 100644 index 0000000000..1a734343d9 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet01/expected/model_3-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {} diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_3-solution000002.solution b/tests/exhaustive/basic/setOfSet01/expected/model_3-solution000002.solution new file mode 100644 index 0000000000..7c5b3bfc58 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet01/expected/model_3-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {{}} diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_3-solution000003.solution b/tests/exhaustive/basic/setOfSet01/expected/model_3-solution000003.solution new file mode 100644 index 0000000000..69bc828bbc --- /dev/null +++ b/tests/exhaustive/basic/setOfSet01/expected/model_3-solution000003.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting x be {{1}} +$ Visualisation for x +$ 1 + diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_3-solution000004.solution b/tests/exhaustive/basic/setOfSet01/expected/model_3-solution000004.solution new file mode 100644 index 0000000000..550c68f48c --- /dev/null +++ b/tests/exhaustive/basic/setOfSet01/expected/model_3-solution000004.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting x be {{2}} +$ Visualisation for x +$ 2 + diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_3-solution000005.solution b/tests/exhaustive/basic/setOfSet01/expected/model_3-solution000005.solution new file mode 100644 index 0000000000..114bad5315 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet01/expected/model_3-solution000005.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting x be {{1, 2}} +$ Visualisation for x +$ 1 2 + diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_3-solution000006.solution b/tests/exhaustive/basic/setOfSet01/expected/model_3-solution000006.solution new file mode 100644 index 0000000000..3ec452354e --- /dev/null +++ b/tests/exhaustive/basic/setOfSet01/expected/model_3-solution000006.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{}, {1}} +$ Visualisation for x +$ +$ 1 + diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_3-solution000007.solution b/tests/exhaustive/basic/setOfSet01/expected/model_3-solution000007.solution new file mode 100644 index 0000000000..c8946f3d06 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet01/expected/model_3-solution000007.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{}, {2}} +$ Visualisation for x +$ +$ 2 + diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_3-solution000008.solution b/tests/exhaustive/basic/setOfSet01/expected/model_3-solution000008.solution new file mode 100644 index 0000000000..a6c0b6a43e --- /dev/null +++ b/tests/exhaustive/basic/setOfSet01/expected/model_3-solution000008.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{}, {1, 2}} +$ Visualisation for x +$ +$ 1 2 + diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_3-solution000009.solution b/tests/exhaustive/basic/setOfSet01/expected/model_3-solution000009.solution new file mode 100644 index 0000000000..af16592c51 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet01/expected/model_3-solution000009.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{1}, {2}} +$ Visualisation for x +$ 1 +$ 2 + diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_3-solution000010.solution b/tests/exhaustive/basic/setOfSet01/expected/model_3-solution000010.solution new file mode 100644 index 0000000000..38937c9389 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet01/expected/model_3-solution000010.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{1}, {1, 2}} +$ Visualisation for x +$ 1 +$ 1 2 + diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_3-solution000011.solution b/tests/exhaustive/basic/setOfSet01/expected/model_3-solution000011.solution new file mode 100644 index 0000000000..9bf2af0712 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet01/expected/model_3-solution000011.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{1, 2}, {2}} +$ Visualisation for x +$ 1 2 +$ 2 + diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_3-solution000012.solution b/tests/exhaustive/basic/setOfSet01/expected/model_3-solution000012.solution new file mode 100644 index 0000000000..f1a04b347c --- /dev/null +++ b/tests/exhaustive/basic/setOfSet01/expected/model_3-solution000012.solution @@ -0,0 +1,8 @@ +language Essence 1.3 + +letting x be {{}, {1}, {2}} +$ Visualisation for x +$ +$ 1 +$ 2 + diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_3-solution000013.solution b/tests/exhaustive/basic/setOfSet01/expected/model_3-solution000013.solution new file mode 100644 index 0000000000..8400fcb8c1 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet01/expected/model_3-solution000013.solution @@ -0,0 +1,8 @@ +language Essence 1.3 + +letting x be {{}, {1}, {1, 2}} +$ Visualisation for x +$ +$ 1 +$ 1 2 + diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_3-solution000014.solution b/tests/exhaustive/basic/setOfSet01/expected/model_3-solution000014.solution new file mode 100644 index 0000000000..b1673f700a --- /dev/null +++ b/tests/exhaustive/basic/setOfSet01/expected/model_3-solution000014.solution @@ -0,0 +1,8 @@ +language Essence 1.3 + +letting x be {{}, {1, 2}, {2}} +$ Visualisation for x +$ +$ 1 2 +$ 2 + diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_3-solution000015.solution b/tests/exhaustive/basic/setOfSet01/expected/model_3-solution000015.solution new file mode 100644 index 0000000000..7c7f2e98ea --- /dev/null +++ b/tests/exhaustive/basic/setOfSet01/expected/model_3-solution000015.solution @@ -0,0 +1,8 @@ +language Essence 1.3 + +letting x be {{1}, {1, 2}, {2}} +$ Visualisation for x +$ 1 +$ 1 2 +$ 2 + diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_3-solution000016.solution b/tests/exhaustive/basic/setOfSet01/expected/model_3-solution000016.solution new file mode 100644 index 0000000000..29f10f5fb0 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet01/expected/model_3-solution000016.solution @@ -0,0 +1,9 @@ +language Essence 1.3 + +letting x be {{}, {1}, {1, 2}, {2}} +$ Visualisation for x +$ +$ 1 +$ 1 2 +$ 2 + diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_3.eprime.orig b/tests/exhaustive/basic/setOfSet01/expected/model_3.eprime.orig deleted file mode 100644 index a8557ffeaf..0000000000 --- a/tests/exhaustive/basic/setOfSet01/expected/model_3.eprime.orig +++ /dev/null @@ -1,34 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithMarkerR5_Marker: int(0..4) -find x_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker: matrix indexed by [int(1..4)] of int(0..2) -find x_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values: - matrix indexed by [int(1..4), int(1..2)] of int(1..2) -branching on - [x_ExplicitVarSizeWithMarkerR5_Marker, x_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker, - x_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values] -such that - and([q1 + 1 <= x_ExplicitVarSizeWithMarkerR5_Marker -> - flatten([[x_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q1]; int(1)], - [x_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q1, q7] | q7 : int(1..2)]; - int(1..2)]) - x_ExplicitVarSizeWithMarkerR5_Marker -> - x_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q2] = 0 /\ - and([x_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q2, q9] = 1 | q9 : int(1..2)]) - | q2 : int(1..4)]), - and([q3 <= x_ExplicitVarSizeWithMarkerR5_Marker -> - (2 <= x_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q3] -> - x_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q3, 1] < - x_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q3, 2]) - | q3 : int(1..4)]), - and([q3 <= x_ExplicitVarSizeWithMarkerR5_Marker -> - and([q5 > x_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q3] -> - x_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q3, q5] = 1 - | q5 : int(1..2)]) - | q3 : int(1..4)]) - diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_4-solution000001.solution b/tests/exhaustive/basic/setOfSet01/expected/model_4-solution000001.solution new file mode 100644 index 0000000000..1a734343d9 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet01/expected/model_4-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {} diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_4-solution000002.solution b/tests/exhaustive/basic/setOfSet01/expected/model_4-solution000002.solution new file mode 100644 index 0000000000..7c5b3bfc58 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet01/expected/model_4-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {{}} diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_4-solution000003.solution b/tests/exhaustive/basic/setOfSet01/expected/model_4-solution000003.solution new file mode 100644 index 0000000000..69bc828bbc --- /dev/null +++ b/tests/exhaustive/basic/setOfSet01/expected/model_4-solution000003.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting x be {{1}} +$ Visualisation for x +$ 1 + diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_4-solution000004.solution b/tests/exhaustive/basic/setOfSet01/expected/model_4-solution000004.solution new file mode 100644 index 0000000000..550c68f48c --- /dev/null +++ b/tests/exhaustive/basic/setOfSet01/expected/model_4-solution000004.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting x be {{2}} +$ Visualisation for x +$ 2 + diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_4-solution000005.solution b/tests/exhaustive/basic/setOfSet01/expected/model_4-solution000005.solution new file mode 100644 index 0000000000..114bad5315 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet01/expected/model_4-solution000005.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting x be {{1, 2}} +$ Visualisation for x +$ 1 2 + diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_4-solution000006.solution b/tests/exhaustive/basic/setOfSet01/expected/model_4-solution000006.solution new file mode 100644 index 0000000000..3ec452354e --- /dev/null +++ b/tests/exhaustive/basic/setOfSet01/expected/model_4-solution000006.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{}, {1}} +$ Visualisation for x +$ +$ 1 + diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_4-solution000007.solution b/tests/exhaustive/basic/setOfSet01/expected/model_4-solution000007.solution new file mode 100644 index 0000000000..c8946f3d06 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet01/expected/model_4-solution000007.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{}, {2}} +$ Visualisation for x +$ +$ 2 + diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_4-solution000008.solution b/tests/exhaustive/basic/setOfSet01/expected/model_4-solution000008.solution new file mode 100644 index 0000000000..af16592c51 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet01/expected/model_4-solution000008.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{1}, {2}} +$ Visualisation for x +$ 1 +$ 2 + diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_4-solution000009.solution b/tests/exhaustive/basic/setOfSet01/expected/model_4-solution000009.solution new file mode 100644 index 0000000000..a6c0b6a43e --- /dev/null +++ b/tests/exhaustive/basic/setOfSet01/expected/model_4-solution000009.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{}, {1, 2}} +$ Visualisation for x +$ +$ 1 2 + diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_4-solution000010.solution b/tests/exhaustive/basic/setOfSet01/expected/model_4-solution000010.solution new file mode 100644 index 0000000000..38937c9389 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet01/expected/model_4-solution000010.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{1}, {1, 2}} +$ Visualisation for x +$ 1 +$ 1 2 + diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_4-solution000011.solution b/tests/exhaustive/basic/setOfSet01/expected/model_4-solution000011.solution new file mode 100644 index 0000000000..9bf2af0712 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet01/expected/model_4-solution000011.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{1, 2}, {2}} +$ Visualisation for x +$ 1 2 +$ 2 + diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_4-solution000012.solution b/tests/exhaustive/basic/setOfSet01/expected/model_4-solution000012.solution new file mode 100644 index 0000000000..f1a04b347c --- /dev/null +++ b/tests/exhaustive/basic/setOfSet01/expected/model_4-solution000012.solution @@ -0,0 +1,8 @@ +language Essence 1.3 + +letting x be {{}, {1}, {2}} +$ Visualisation for x +$ +$ 1 +$ 2 + diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_4-solution000013.solution b/tests/exhaustive/basic/setOfSet01/expected/model_4-solution000013.solution new file mode 100644 index 0000000000..8400fcb8c1 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet01/expected/model_4-solution000013.solution @@ -0,0 +1,8 @@ +language Essence 1.3 + +letting x be {{}, {1}, {1, 2}} +$ Visualisation for x +$ +$ 1 +$ 1 2 + diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_4-solution000014.solution b/tests/exhaustive/basic/setOfSet01/expected/model_4-solution000014.solution new file mode 100644 index 0000000000..b1673f700a --- /dev/null +++ b/tests/exhaustive/basic/setOfSet01/expected/model_4-solution000014.solution @@ -0,0 +1,8 @@ +language Essence 1.3 + +letting x be {{}, {1, 2}, {2}} +$ Visualisation for x +$ +$ 1 2 +$ 2 + diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_4-solution000015.solution b/tests/exhaustive/basic/setOfSet01/expected/model_4-solution000015.solution new file mode 100644 index 0000000000..7c7f2e98ea --- /dev/null +++ b/tests/exhaustive/basic/setOfSet01/expected/model_4-solution000015.solution @@ -0,0 +1,8 @@ +language Essence 1.3 + +letting x be {{1}, {1, 2}, {2}} +$ Visualisation for x +$ 1 +$ 1 2 +$ 2 + diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_4-solution000016.solution b/tests/exhaustive/basic/setOfSet01/expected/model_4-solution000016.solution new file mode 100644 index 0000000000..29f10f5fb0 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet01/expected/model_4-solution000016.solution @@ -0,0 +1,9 @@ +language Essence 1.3 + +letting x be {{}, {1}, {1, 2}, {2}} +$ Visualisation for x +$ +$ 1 +$ 1 2 +$ 2 + diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_4.eprime b/tests/exhaustive/basic/setOfSet01/expected/model_4.eprime new file mode 100644 index 0000000000..979f6d52c7 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet01/expected/model_4.eprime @@ -0,0 +1,43 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarkerR4_Marker: int(0..4) +find x_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Flags: + matrix indexed by [int(1..4), int(1..2)] of bool +find x_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Values: + matrix indexed by [int(1..4), int(1..2)] of int(1..2) +branching on + [x_ExplicitVarSizeWithMarkerR4_Marker, x_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Flags, + x_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Values] +such that + and([q1 + 1 <= x_ExplicitVarSizeWithMarkerR4_Marker -> + flatten([flatten([[-toInt(x_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Flags[q1, q9]); + int(1)], + [x_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Values[q1, q9]; int(1)]; + int(1..2)]) + | q9 : int(1..2)]) + x_ExplicitVarSizeWithMarkerR4_Marker -> + and([x_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Flags[q2, q11] = false | q11 : int(1..2)]) + /\ and([x_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Values[q2, q12] = 1 | q12 : int(1..2)]) + | q2 : int(1..4)]), + and([q3 <= x_ExplicitVarSizeWithMarkerR4_Marker -> + (x_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Flags[q3, 2] -> + x_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Values[q3, 1] < + x_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Values[q3, 2]) + | q3 : int(1..4)]), + and([q3 <= x_ExplicitVarSizeWithMarkerR4_Marker -> + and([x_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Flags[q3, q5] = false -> + x_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Values[q3, q5] = 1 + | q5 : int(1..2)]) + | q3 : int(1..4)]), + and([q3 <= x_ExplicitVarSizeWithMarkerR4_Marker -> + (x_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Flags[q3, 2] -> + x_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Flags[q3, 1]) + | q3 : int(1..4)]) + diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_5-solution000001.solution b/tests/exhaustive/basic/setOfSet01/expected/model_5-solution000001.solution new file mode 100644 index 0000000000..1a734343d9 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet01/expected/model_5-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {} diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_5-solution000002.solution b/tests/exhaustive/basic/setOfSet01/expected/model_5-solution000002.solution new file mode 100644 index 0000000000..7c5b3bfc58 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet01/expected/model_5-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {{}} diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_5-solution000003.solution b/tests/exhaustive/basic/setOfSet01/expected/model_5-solution000003.solution new file mode 100644 index 0000000000..550c68f48c --- /dev/null +++ b/tests/exhaustive/basic/setOfSet01/expected/model_5-solution000003.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting x be {{2}} +$ Visualisation for x +$ 2 + diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_5-solution000004.solution b/tests/exhaustive/basic/setOfSet01/expected/model_5-solution000004.solution new file mode 100644 index 0000000000..69bc828bbc --- /dev/null +++ b/tests/exhaustive/basic/setOfSet01/expected/model_5-solution000004.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting x be {{1}} +$ Visualisation for x +$ 1 + diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_5-solution000005.solution b/tests/exhaustive/basic/setOfSet01/expected/model_5-solution000005.solution new file mode 100644 index 0000000000..114bad5315 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet01/expected/model_5-solution000005.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting x be {{1, 2}} +$ Visualisation for x +$ 1 2 + diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_5-solution000006.solution b/tests/exhaustive/basic/setOfSet01/expected/model_5-solution000006.solution new file mode 100644 index 0000000000..c8946f3d06 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet01/expected/model_5-solution000006.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{}, {2}} +$ Visualisation for x +$ +$ 2 + diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_5-solution000007.solution b/tests/exhaustive/basic/setOfSet01/expected/model_5-solution000007.solution new file mode 100644 index 0000000000..3ec452354e --- /dev/null +++ b/tests/exhaustive/basic/setOfSet01/expected/model_5-solution000007.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{}, {1}} +$ Visualisation for x +$ +$ 1 + diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_5-solution000008.solution b/tests/exhaustive/basic/setOfSet01/expected/model_5-solution000008.solution new file mode 100644 index 0000000000..af16592c51 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet01/expected/model_5-solution000008.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{1}, {2}} +$ Visualisation for x +$ 1 +$ 2 + diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_5-solution000009.solution b/tests/exhaustive/basic/setOfSet01/expected/model_5-solution000009.solution new file mode 100644 index 0000000000..a6c0b6a43e --- /dev/null +++ b/tests/exhaustive/basic/setOfSet01/expected/model_5-solution000009.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{}, {1, 2}} +$ Visualisation for x +$ +$ 1 2 + diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_5-solution000010.solution b/tests/exhaustive/basic/setOfSet01/expected/model_5-solution000010.solution new file mode 100644 index 0000000000..9bf2af0712 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet01/expected/model_5-solution000010.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{1, 2}, {2}} +$ Visualisation for x +$ 1 2 +$ 2 + diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_5-solution000011.solution b/tests/exhaustive/basic/setOfSet01/expected/model_5-solution000011.solution new file mode 100644 index 0000000000..38937c9389 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet01/expected/model_5-solution000011.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{1}, {1, 2}} +$ Visualisation for x +$ 1 +$ 1 2 + diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_5-solution000012.solution b/tests/exhaustive/basic/setOfSet01/expected/model_5-solution000012.solution new file mode 100644 index 0000000000..f1a04b347c --- /dev/null +++ b/tests/exhaustive/basic/setOfSet01/expected/model_5-solution000012.solution @@ -0,0 +1,8 @@ +language Essence 1.3 + +letting x be {{}, {1}, {2}} +$ Visualisation for x +$ +$ 1 +$ 2 + diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_5-solution000013.solution b/tests/exhaustive/basic/setOfSet01/expected/model_5-solution000013.solution new file mode 100644 index 0000000000..b1673f700a --- /dev/null +++ b/tests/exhaustive/basic/setOfSet01/expected/model_5-solution000013.solution @@ -0,0 +1,8 @@ +language Essence 1.3 + +letting x be {{}, {1, 2}, {2}} +$ Visualisation for x +$ +$ 1 2 +$ 2 + diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_5-solution000014.solution b/tests/exhaustive/basic/setOfSet01/expected/model_5-solution000014.solution new file mode 100644 index 0000000000..8400fcb8c1 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet01/expected/model_5-solution000014.solution @@ -0,0 +1,8 @@ +language Essence 1.3 + +letting x be {{}, {1}, {1, 2}} +$ Visualisation for x +$ +$ 1 +$ 1 2 + diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_5-solution000015.solution b/tests/exhaustive/basic/setOfSet01/expected/model_5-solution000015.solution new file mode 100644 index 0000000000..7c7f2e98ea --- /dev/null +++ b/tests/exhaustive/basic/setOfSet01/expected/model_5-solution000015.solution @@ -0,0 +1,8 @@ +language Essence 1.3 + +letting x be {{1}, {1, 2}, {2}} +$ Visualisation for x +$ 1 +$ 1 2 +$ 2 + diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_5-solution000016.solution b/tests/exhaustive/basic/setOfSet01/expected/model_5-solution000016.solution new file mode 100644 index 0000000000..29f10f5fb0 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet01/expected/model_5-solution000016.solution @@ -0,0 +1,9 @@ +language Essence 1.3 + +letting x be {{}, {1}, {1, 2}, {2}} +$ Visualisation for x +$ +$ 1 +$ 1 2 +$ 2 + diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_5.eprime b/tests/exhaustive/basic/setOfSet01/expected/model_5.eprime new file mode 100644 index 0000000000..f99416596c --- /dev/null +++ b/tests/exhaustive/basic/setOfSet01/expected/model_5.eprime @@ -0,0 +1,15 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlagsR2_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlagsR2_Values_Occurrence: matrix indexed by [int(1..4), int(1..2)] of bool +branching on [x_ExplicitVarSizeWithFlagsR2_Flags, x_ExplicitVarSizeWithFlagsR2_Values_Occurrence] +such that + and([x_ExplicitVarSizeWithFlagsR2_Flags[q1 + 1] -> + [-toInt(x_ExplicitVarSizeWithFlagsR2_Values_Occurrence[q1, q7]) | q7 : int(1..2)] + and([x_ExplicitVarSizeWithFlagsR2_Values_Occurrence[q2, q9] = false | q9 : int(1..2)]) + | q2 : int(1..4)]), + and([x_ExplicitVarSizeWithFlagsR2_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlagsR2_Flags[q3] | q3 : int(1..3)]) + diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_6-solution000001.solution b/tests/exhaustive/basic/setOfSet01/expected/model_6-solution000001.solution new file mode 100644 index 0000000000..1a734343d9 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet01/expected/model_6-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {} diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_6-solution000002.solution b/tests/exhaustive/basic/setOfSet01/expected/model_6-solution000002.solution new file mode 100644 index 0000000000..114bad5315 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet01/expected/model_6-solution000002.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting x be {{1, 2}} +$ Visualisation for x +$ 1 2 + diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_6-solution000003.solution b/tests/exhaustive/basic/setOfSet01/expected/model_6-solution000003.solution new file mode 100644 index 0000000000..69bc828bbc --- /dev/null +++ b/tests/exhaustive/basic/setOfSet01/expected/model_6-solution000003.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting x be {{1}} +$ Visualisation for x +$ 1 + diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_6-solution000004.solution b/tests/exhaustive/basic/setOfSet01/expected/model_6-solution000004.solution new file mode 100644 index 0000000000..550c68f48c --- /dev/null +++ b/tests/exhaustive/basic/setOfSet01/expected/model_6-solution000004.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting x be {{2}} +$ Visualisation for x +$ 2 + diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_6-solution000005.solution b/tests/exhaustive/basic/setOfSet01/expected/model_6-solution000005.solution new file mode 100644 index 0000000000..7c5b3bfc58 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet01/expected/model_6-solution000005.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {{}} diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_6-solution000006.solution b/tests/exhaustive/basic/setOfSet01/expected/model_6-solution000006.solution new file mode 100644 index 0000000000..38937c9389 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet01/expected/model_6-solution000006.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{1}, {1, 2}} +$ Visualisation for x +$ 1 +$ 1 2 + diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_6-solution000007.solution b/tests/exhaustive/basic/setOfSet01/expected/model_6-solution000007.solution new file mode 100644 index 0000000000..9bf2af0712 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet01/expected/model_6-solution000007.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{1, 2}, {2}} +$ Visualisation for x +$ 1 2 +$ 2 + diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_6-solution000008.solution b/tests/exhaustive/basic/setOfSet01/expected/model_6-solution000008.solution new file mode 100644 index 0000000000..a6c0b6a43e --- /dev/null +++ b/tests/exhaustive/basic/setOfSet01/expected/model_6-solution000008.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{}, {1, 2}} +$ Visualisation for x +$ +$ 1 2 + diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_6-solution000009.solution b/tests/exhaustive/basic/setOfSet01/expected/model_6-solution000009.solution new file mode 100644 index 0000000000..af16592c51 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet01/expected/model_6-solution000009.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{1}, {2}} +$ Visualisation for x +$ 1 +$ 2 + diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_6-solution000010.solution b/tests/exhaustive/basic/setOfSet01/expected/model_6-solution000010.solution new file mode 100644 index 0000000000..3ec452354e --- /dev/null +++ b/tests/exhaustive/basic/setOfSet01/expected/model_6-solution000010.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{}, {1}} +$ Visualisation for x +$ +$ 1 + diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_6-solution000011.solution b/tests/exhaustive/basic/setOfSet01/expected/model_6-solution000011.solution new file mode 100644 index 0000000000..c8946f3d06 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet01/expected/model_6-solution000011.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{}, {2}} +$ Visualisation for x +$ +$ 2 + diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_6-solution000012.solution b/tests/exhaustive/basic/setOfSet01/expected/model_6-solution000012.solution new file mode 100644 index 0000000000..7c7f2e98ea --- /dev/null +++ b/tests/exhaustive/basic/setOfSet01/expected/model_6-solution000012.solution @@ -0,0 +1,8 @@ +language Essence 1.3 + +letting x be {{1}, {1, 2}, {2}} +$ Visualisation for x +$ 1 +$ 1 2 +$ 2 + diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_6-solution000013.solution b/tests/exhaustive/basic/setOfSet01/expected/model_6-solution000013.solution new file mode 100644 index 0000000000..8400fcb8c1 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet01/expected/model_6-solution000013.solution @@ -0,0 +1,8 @@ +language Essence 1.3 + +letting x be {{}, {1}, {1, 2}} +$ Visualisation for x +$ +$ 1 +$ 1 2 + diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_6-solution000014.solution b/tests/exhaustive/basic/setOfSet01/expected/model_6-solution000014.solution new file mode 100644 index 0000000000..b1673f700a --- /dev/null +++ b/tests/exhaustive/basic/setOfSet01/expected/model_6-solution000014.solution @@ -0,0 +1,8 @@ +language Essence 1.3 + +letting x be {{}, {1, 2}, {2}} +$ Visualisation for x +$ +$ 1 2 +$ 2 + diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_6-solution000015.solution b/tests/exhaustive/basic/setOfSet01/expected/model_6-solution000015.solution new file mode 100644 index 0000000000..f1a04b347c --- /dev/null +++ b/tests/exhaustive/basic/setOfSet01/expected/model_6-solution000015.solution @@ -0,0 +1,8 @@ +language Essence 1.3 + +letting x be {{}, {1}, {2}} +$ Visualisation for x +$ +$ 1 +$ 2 + diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_6-solution000016.solution b/tests/exhaustive/basic/setOfSet01/expected/model_6-solution000016.solution new file mode 100644 index 0000000000..29f10f5fb0 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet01/expected/model_6-solution000016.solution @@ -0,0 +1,9 @@ +language Essence 1.3 + +letting x be {{}, {1}, {1, 2}, {2}} +$ Visualisation for x +$ +$ 1 +$ 1 2 +$ 2 + diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_6.eprime b/tests/exhaustive/basic/setOfSet01/expected/model_6.eprime new file mode 100644 index 0000000000..f1ff4362d3 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet01/expected/model_6.eprime @@ -0,0 +1,24 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlagsR6_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlagsR6_Values_ExplicitVarSizeWithDummy: matrix indexed by [int(1..4), int(1..2)] of int(1..3) +branching on [x_ExplicitVarSizeWithFlagsR6_Flags, x_ExplicitVarSizeWithFlagsR6_Values_ExplicitVarSizeWithDummy] +such that + and([x_ExplicitVarSizeWithFlagsR6_Flags[q1 + 1] -> + [x_ExplicitVarSizeWithFlagsR6_Values_ExplicitVarSizeWithDummy[q1, q10] | q10 : int(1..2)] + and([x_ExplicitVarSizeWithFlagsR6_Values_ExplicitVarSizeWithDummy[q2, q12] = 1 | q12 : int(1..2)]) + | q2 : int(1..4)]), + and([x_ExplicitVarSizeWithFlagsR6_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlagsR6_Flags[q3] | q3 : int(1..3)]), + and([x_ExplicitVarSizeWithFlagsR6_Flags[q5] -> + x_ExplicitVarSizeWithFlagsR6_Values_ExplicitVarSizeWithDummy[q5, 1] < + x_ExplicitVarSizeWithFlagsR6_Values_ExplicitVarSizeWithDummy[q5, 2] + \/ x_ExplicitVarSizeWithFlagsR6_Values_ExplicitVarSizeWithDummy[q5, 1] = 3 + | q5 : int(1..4)]), + and([x_ExplicitVarSizeWithFlagsR6_Flags[q5] -> + (x_ExplicitVarSizeWithFlagsR6_Values_ExplicitVarSizeWithDummy[q5, 1] = 3 -> + x_ExplicitVarSizeWithFlagsR6_Values_ExplicitVarSizeWithDummy[q5, 2] = 3) + | q5 : int(1..4)]) + diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_7-solution000001.solution b/tests/exhaustive/basic/setOfSet01/expected/model_7-solution000001.solution new file mode 100644 index 0000000000..1a734343d9 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet01/expected/model_7-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {} diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_7-solution000002.solution b/tests/exhaustive/basic/setOfSet01/expected/model_7-solution000002.solution new file mode 100644 index 0000000000..7c5b3bfc58 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet01/expected/model_7-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {{}} diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_7-solution000003.solution b/tests/exhaustive/basic/setOfSet01/expected/model_7-solution000003.solution new file mode 100644 index 0000000000..69bc828bbc --- /dev/null +++ b/tests/exhaustive/basic/setOfSet01/expected/model_7-solution000003.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting x be {{1}} +$ Visualisation for x +$ 1 + diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_7-solution000004.solution b/tests/exhaustive/basic/setOfSet01/expected/model_7-solution000004.solution new file mode 100644 index 0000000000..550c68f48c --- /dev/null +++ b/tests/exhaustive/basic/setOfSet01/expected/model_7-solution000004.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting x be {{2}} +$ Visualisation for x +$ 2 + diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_7-solution000005.solution b/tests/exhaustive/basic/setOfSet01/expected/model_7-solution000005.solution new file mode 100644 index 0000000000..114bad5315 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet01/expected/model_7-solution000005.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting x be {{1, 2}} +$ Visualisation for x +$ 1 2 + diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_7-solution000006.solution b/tests/exhaustive/basic/setOfSet01/expected/model_7-solution000006.solution new file mode 100644 index 0000000000..3ec452354e --- /dev/null +++ b/tests/exhaustive/basic/setOfSet01/expected/model_7-solution000006.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{}, {1}} +$ Visualisation for x +$ +$ 1 + diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_7-solution000007.solution b/tests/exhaustive/basic/setOfSet01/expected/model_7-solution000007.solution new file mode 100644 index 0000000000..c8946f3d06 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet01/expected/model_7-solution000007.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{}, {2}} +$ Visualisation for x +$ +$ 2 + diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_7-solution000008.solution b/tests/exhaustive/basic/setOfSet01/expected/model_7-solution000008.solution new file mode 100644 index 0000000000..a6c0b6a43e --- /dev/null +++ b/tests/exhaustive/basic/setOfSet01/expected/model_7-solution000008.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{}, {1, 2}} +$ Visualisation for x +$ +$ 1 2 + diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_7-solution000009.solution b/tests/exhaustive/basic/setOfSet01/expected/model_7-solution000009.solution new file mode 100644 index 0000000000..af16592c51 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet01/expected/model_7-solution000009.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{1}, {2}} +$ Visualisation for x +$ 1 +$ 2 + diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_7-solution000010.solution b/tests/exhaustive/basic/setOfSet01/expected/model_7-solution000010.solution new file mode 100644 index 0000000000..38937c9389 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet01/expected/model_7-solution000010.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{1}, {1, 2}} +$ Visualisation for x +$ 1 +$ 1 2 + diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_7-solution000011.solution b/tests/exhaustive/basic/setOfSet01/expected/model_7-solution000011.solution new file mode 100644 index 0000000000..9bf2af0712 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet01/expected/model_7-solution000011.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{1, 2}, {2}} +$ Visualisation for x +$ 1 2 +$ 2 + diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_7-solution000012.solution b/tests/exhaustive/basic/setOfSet01/expected/model_7-solution000012.solution new file mode 100644 index 0000000000..f1a04b347c --- /dev/null +++ b/tests/exhaustive/basic/setOfSet01/expected/model_7-solution000012.solution @@ -0,0 +1,8 @@ +language Essence 1.3 + +letting x be {{}, {1}, {2}} +$ Visualisation for x +$ +$ 1 +$ 2 + diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_7-solution000013.solution b/tests/exhaustive/basic/setOfSet01/expected/model_7-solution000013.solution new file mode 100644 index 0000000000..8400fcb8c1 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet01/expected/model_7-solution000013.solution @@ -0,0 +1,8 @@ +language Essence 1.3 + +letting x be {{}, {1}, {1, 2}} +$ Visualisation for x +$ +$ 1 +$ 1 2 + diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_7-solution000014.solution b/tests/exhaustive/basic/setOfSet01/expected/model_7-solution000014.solution new file mode 100644 index 0000000000..b1673f700a --- /dev/null +++ b/tests/exhaustive/basic/setOfSet01/expected/model_7-solution000014.solution @@ -0,0 +1,8 @@ +language Essence 1.3 + +letting x be {{}, {1, 2}, {2}} +$ Visualisation for x +$ +$ 1 2 +$ 2 + diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_7-solution000015.solution b/tests/exhaustive/basic/setOfSet01/expected/model_7-solution000015.solution new file mode 100644 index 0000000000..7c7f2e98ea --- /dev/null +++ b/tests/exhaustive/basic/setOfSet01/expected/model_7-solution000015.solution @@ -0,0 +1,8 @@ +language Essence 1.3 + +letting x be {{1}, {1, 2}, {2}} +$ Visualisation for x +$ 1 +$ 1 2 +$ 2 + diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_7-solution000016.solution b/tests/exhaustive/basic/setOfSet01/expected/model_7-solution000016.solution new file mode 100644 index 0000000000..29f10f5fb0 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet01/expected/model_7-solution000016.solution @@ -0,0 +1,9 @@ +language Essence 1.3 + +letting x be {{}, {1}, {1, 2}, {2}} +$ Visualisation for x +$ +$ 1 +$ 1 2 +$ 2 + diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_7.eprime.orig b/tests/exhaustive/basic/setOfSet01/expected/model_7.eprime.orig deleted file mode 100644 index e21b02711c..0000000000 --- a/tests/exhaustive/basic/setOfSet01/expected/model_7.eprime.orig +++ /dev/null @@ -1,35 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitVarSizeWithFlagsR5_Flags: matrix indexed by [int(1..4)] of bool -find x_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Marker: matrix indexed by [int(1..4)] of int(0..2) -find x_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Values: - matrix indexed by [int(1..4), int(1..2)] of int(1..2) -branching on - [x_ExplicitVarSizeWithFlagsR5_Flags, x_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Marker, - x_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Values] -such that - and([x_ExplicitVarSizeWithFlagsR5_Flags[q1 + 1] -> - flatten([[x_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Marker[q1]; int(1)], - [x_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Values[q1, q9] | q9 : int(1..2)]; - int(1..2)]) - - x_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Marker[q2] = 0 /\ - and([x_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Values[q2, q11] = 1 | q11 : int(1..2)]) - | q2 : int(1..4)]), - and([x_ExplicitVarSizeWithFlagsR5_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlagsR5_Flags[q3] | q3 : int(1..3)]), - and([x_ExplicitVarSizeWithFlagsR5_Flags[q5] -> - (2 <= x_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Marker[q5] -> - x_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Values[q5, 1] < - x_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Values[q5, 2]) - | q5 : int(1..4)]), - and([x_ExplicitVarSizeWithFlagsR5_Flags[q5] -> - and([q7 > x_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Marker[q5] -> - x_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Values[q5, q7] = 1 - | q7 : int(1..2)]) - | q5 : int(1..4)]) - diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_8-solution000001.solution b/tests/exhaustive/basic/setOfSet01/expected/model_8-solution000001.solution new file mode 100644 index 0000000000..1a734343d9 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet01/expected/model_8-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {} diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_8-solution000002.solution b/tests/exhaustive/basic/setOfSet01/expected/model_8-solution000002.solution new file mode 100644 index 0000000000..7c5b3bfc58 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet01/expected/model_8-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {{}} diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_8-solution000003.solution b/tests/exhaustive/basic/setOfSet01/expected/model_8-solution000003.solution new file mode 100644 index 0000000000..69bc828bbc --- /dev/null +++ b/tests/exhaustive/basic/setOfSet01/expected/model_8-solution000003.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting x be {{1}} +$ Visualisation for x +$ 1 + diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_8-solution000004.solution b/tests/exhaustive/basic/setOfSet01/expected/model_8-solution000004.solution new file mode 100644 index 0000000000..550c68f48c --- /dev/null +++ b/tests/exhaustive/basic/setOfSet01/expected/model_8-solution000004.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting x be {{2}} +$ Visualisation for x +$ 2 + diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_8-solution000005.solution b/tests/exhaustive/basic/setOfSet01/expected/model_8-solution000005.solution new file mode 100644 index 0000000000..114bad5315 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet01/expected/model_8-solution000005.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting x be {{1, 2}} +$ Visualisation for x +$ 1 2 + diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_8-solution000006.solution b/tests/exhaustive/basic/setOfSet01/expected/model_8-solution000006.solution new file mode 100644 index 0000000000..3ec452354e --- /dev/null +++ b/tests/exhaustive/basic/setOfSet01/expected/model_8-solution000006.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{}, {1}} +$ Visualisation for x +$ +$ 1 + diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_8-solution000007.solution b/tests/exhaustive/basic/setOfSet01/expected/model_8-solution000007.solution new file mode 100644 index 0000000000..c8946f3d06 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet01/expected/model_8-solution000007.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{}, {2}} +$ Visualisation for x +$ +$ 2 + diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_8-solution000008.solution b/tests/exhaustive/basic/setOfSet01/expected/model_8-solution000008.solution new file mode 100644 index 0000000000..af16592c51 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet01/expected/model_8-solution000008.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{1}, {2}} +$ Visualisation for x +$ 1 +$ 2 + diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_8-solution000009.solution b/tests/exhaustive/basic/setOfSet01/expected/model_8-solution000009.solution new file mode 100644 index 0000000000..a6c0b6a43e --- /dev/null +++ b/tests/exhaustive/basic/setOfSet01/expected/model_8-solution000009.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{}, {1, 2}} +$ Visualisation for x +$ +$ 1 2 + diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_8-solution000010.solution b/tests/exhaustive/basic/setOfSet01/expected/model_8-solution000010.solution new file mode 100644 index 0000000000..38937c9389 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet01/expected/model_8-solution000010.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{1}, {1, 2}} +$ Visualisation for x +$ 1 +$ 1 2 + diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_8-solution000011.solution b/tests/exhaustive/basic/setOfSet01/expected/model_8-solution000011.solution new file mode 100644 index 0000000000..9bf2af0712 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet01/expected/model_8-solution000011.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{1, 2}, {2}} +$ Visualisation for x +$ 1 2 +$ 2 + diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_8-solution000012.solution b/tests/exhaustive/basic/setOfSet01/expected/model_8-solution000012.solution new file mode 100644 index 0000000000..f1a04b347c --- /dev/null +++ b/tests/exhaustive/basic/setOfSet01/expected/model_8-solution000012.solution @@ -0,0 +1,8 @@ +language Essence 1.3 + +letting x be {{}, {1}, {2}} +$ Visualisation for x +$ +$ 1 +$ 2 + diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_8-solution000013.solution b/tests/exhaustive/basic/setOfSet01/expected/model_8-solution000013.solution new file mode 100644 index 0000000000..8400fcb8c1 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet01/expected/model_8-solution000013.solution @@ -0,0 +1,8 @@ +language Essence 1.3 + +letting x be {{}, {1}, {1, 2}} +$ Visualisation for x +$ +$ 1 +$ 1 2 + diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_8-solution000014.solution b/tests/exhaustive/basic/setOfSet01/expected/model_8-solution000014.solution new file mode 100644 index 0000000000..b1673f700a --- /dev/null +++ b/tests/exhaustive/basic/setOfSet01/expected/model_8-solution000014.solution @@ -0,0 +1,8 @@ +language Essence 1.3 + +letting x be {{}, {1, 2}, {2}} +$ Visualisation for x +$ +$ 1 2 +$ 2 + diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_8-solution000015.solution b/tests/exhaustive/basic/setOfSet01/expected/model_8-solution000015.solution new file mode 100644 index 0000000000..7c7f2e98ea --- /dev/null +++ b/tests/exhaustive/basic/setOfSet01/expected/model_8-solution000015.solution @@ -0,0 +1,8 @@ +language Essence 1.3 + +letting x be {{1}, {1, 2}, {2}} +$ Visualisation for x +$ 1 +$ 1 2 +$ 2 + diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_8-solution000016.solution b/tests/exhaustive/basic/setOfSet01/expected/model_8-solution000016.solution new file mode 100644 index 0000000000..29f10f5fb0 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet01/expected/model_8-solution000016.solution @@ -0,0 +1,9 @@ +language Essence 1.3 + +letting x be {{}, {1}, {1, 2}, {2}} +$ Visualisation for x +$ +$ 1 +$ 1 2 +$ 2 + diff --git a/tests/exhaustive/basic/setOfSet01/expected/model_8.eprime b/tests/exhaustive/basic/setOfSet01/expected/model_8.eprime new file mode 100644 index 0000000000..2e31cf9b1f --- /dev/null +++ b/tests/exhaustive/basic/setOfSet01/expected/model_8.eprime @@ -0,0 +1,44 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlagsR4_Flags: matrix indexed by [int(1..4)] of bool +find x_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Flags: + matrix indexed by [int(1..4), int(1..2)] of bool +find x_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Values: + matrix indexed by [int(1..4), int(1..2)] of int(1..2) +branching on + [x_ExplicitVarSizeWithFlagsR4_Flags, x_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Flags, + x_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Values] +such that + and([x_ExplicitVarSizeWithFlagsR4_Flags[q1 + 1] -> + flatten([flatten([[-toInt(x_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Flags[q1, q11]); + int(1)], + [x_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Values[q1, q11]; int(1)]; + int(1..2)]) + | q11 : int(1..2)]) + + and([x_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Flags[q2, q13] = false | q13 : int(1..2)]) /\ + and([x_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Values[q2, q14] = 1 | q14 : int(1..2)]) + | q2 : int(1..4)]), + and([x_ExplicitVarSizeWithFlagsR4_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlagsR4_Flags[q3] | q3 : int(1..3)]), + and([x_ExplicitVarSizeWithFlagsR4_Flags[q5] -> + (x_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Flags[q5, 2] -> + x_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Values[q5, 1] < + x_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Values[q5, 2]) + | q5 : int(1..4)]), + and([x_ExplicitVarSizeWithFlagsR4_Flags[q5] -> + and([x_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Flags[q5, q7] = false -> + x_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Values[q5, q7] = 1 + | q7 : int(1..2)]) + | q5 : int(1..4)]), + and([x_ExplicitVarSizeWithFlagsR4_Flags[q5] -> + (x_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Flags[q5, 2] -> + x_ExplicitVarSizeWithFlagsR4_Values_ExplicitVarSizeWithFlags_Flags[q5, 1]) + | q5 : int(1..4)]) + diff --git a/tests/exhaustive/basic/setOfSet02/expected/model_1_1-solution000002.solution b/tests/exhaustive/basic/setOfSet02/expected/model_1_1-solution000002.solution new file mode 100644 index 0000000000..707d6ddaf7 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet02/expected/model_1_1-solution000002.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{1, 2, 3}, {1, 3, 4}} +$ Visualisation for x +$ 1 2 3 +$ 1 3 4 + diff --git a/tests/exhaustive/basic/setOfSet02/expected/model_1_2-solution000002.solution b/tests/exhaustive/basic/setOfSet02/expected/model_1_2-solution000002.solution new file mode 100644 index 0000000000..707d6ddaf7 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet02/expected/model_1_2-solution000002.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{1, 2, 3}, {1, 3, 4}} +$ Visualisation for x +$ 1 2 3 +$ 1 3 4 + diff --git a/tests/exhaustive/basic/setOfSet02/expected/model_1_2.eprime.orig b/tests/exhaustive/basic/setOfSet02/expected/model_1_2.eprime.orig deleted file mode 100644 index 16addfde90..0000000000 --- a/tests/exhaustive/basic/setOfSet02/expected/model_1_2.eprime.orig +++ /dev/null @@ -1,26 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitR2_Occurrence: matrix indexed by [int(1..2), int(1..4)] of bool -find x_ExplicitR3_Explicit: matrix indexed by [int(1..2), int(1..3)] of int(1..4) -branching on [x_ExplicitR3_Explicit, x_ExplicitR2_Occurrence] -such that - or([and([x_ExplicitR2_Occurrence[q31, q32] -> or([1 = q32, 2 = q32, 3 = q32; int(1..3)]) | q32 : int(1..4)]) /\ - and([x_ExplicitR2_Occurrence[q31, 1], x_ExplicitR2_Occurrence[q31, 2], x_ExplicitR2_Occurrence[q31, 3]; - int(1..3)]) - | q31 : int(1..2)]), - [-toInt(x_ExplicitR2_Occurrence[1, q4]) | q4 : int(1..4)] or([x_ExplicitR3_Explicit[q13, q18] = q16 | q18 : int(1..3)]) - | q16 : int(1..4)]) - /\ and([x_ExplicitR2_Occurrence[q15, x_ExplicitR3_Explicit[q13, q20]] | q20 : int(1..3)]) - | q15 : int(1..2)]) - | q13 : int(1..2)]), - and([or([and([x_ExplicitR2_Occurrence[q22, x_ExplicitR3_Explicit[q24, q26]] | q26 : int(1..3)]) /\ - and([x_ExplicitR2_Occurrence[q22, q27] -> or([x_ExplicitR3_Explicit[q24, q29] = q27 | q29 : int(1..3)]) - | q27 : int(1..4)]) - | q24 : int(1..2)]) - | q22 : int(1..2)]) - diff --git a/tests/exhaustive/basic/setOfSet02/expected/model_2_1-solution000002.solution b/tests/exhaustive/basic/setOfSet02/expected/model_2_1-solution000002.solution new file mode 100644 index 0000000000..707d6ddaf7 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet02/expected/model_2_1-solution000002.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{1, 2, 3}, {1, 3, 4}} +$ Visualisation for x +$ 1 2 3 +$ 1 3 4 + diff --git a/tests/exhaustive/basic/setOfSet02/expected/model_2_1.eprime.orig b/tests/exhaustive/basic/setOfSet02/expected/model_2_1.eprime.orig deleted file mode 100644 index 443becc194..0000000000 --- a/tests/exhaustive/basic/setOfSet02/expected/model_2_1.eprime.orig +++ /dev/null @@ -1,32 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitR3_Explicit: matrix indexed by [int(1..2), int(1..3)] of int(1..4) -find x_ExplicitR2_Occurrence: matrix indexed by [int(1..2), int(1..4)] of bool -branching on [x_ExplicitR2_Occurrence, x_ExplicitR3_Explicit] -such that - or([and([or([1 = x_ExplicitR3_Explicit[q31, q33], 2 = x_ExplicitR3_Explicit[q31, q33], - 3 = x_ExplicitR3_Explicit[q31, q33]; - int(1..3)]) - | q33 : int(1..3)]) - /\ - and([or([x_ExplicitR3_Explicit[q31, q37] = 1 | q37 : int(1..3)]), - or([x_ExplicitR3_Explicit[q31, q39] = 2 | q39 : int(1..3)]), - or([x_ExplicitR3_Explicit[q31, q41] = 3 | q41 : int(1..3)]); - int(1..3)]) - | q31 : int(1..2)]), - [x_ExplicitR3_Explicit[1, q5] | q5 : int(1..3)] or([x_ExplicitR3_Explicit[q15, q20] = q18 | q20 : int(1..3)]) - | q18 : int(1..4)]) - | q15 : int(1..2)]) - | q13 : int(1..2)]), - and([or([and([x_ExplicitR2_Occurrence[q24, q25] -> or([x_ExplicitR3_Explicit[q22, q27] = q25 | q27 : int(1..3)]) - | q25 : int(1..4)]) - /\ and([x_ExplicitR2_Occurrence[q24, x_ExplicitR3_Explicit[q22, q29]] | q29 : int(1..3)]) - | q24 : int(1..2)]) - | q22 : int(1..2)]) - diff --git a/tests/exhaustive/basic/setOfSet02/expected/model_2_2-solution000002.solution b/tests/exhaustive/basic/setOfSet02/expected/model_2_2-solution000002.solution new file mode 100644 index 0000000000..707d6ddaf7 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet02/expected/model_2_2-solution000002.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{1, 2, 3}, {1, 3, 4}} +$ Visualisation for x +$ 1 2 3 +$ 1 3 4 + diff --git a/tests/exhaustive/basic/setOfSet02/expected/model_2_2.eprime.orig b/tests/exhaustive/basic/setOfSet02/expected/model_2_2.eprime.orig deleted file mode 100644 index 72c33b3766..0000000000 --- a/tests/exhaustive/basic/setOfSet02/expected/model_2_2.eprime.orig +++ /dev/null @@ -1,18 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitR3_Explicit: matrix indexed by [int(1..2), int(1..3)] of int(1..4) -branching on [x_ExplicitR3_Explicit] -such that - or([and([or([1 = x_ExplicitR3_Explicit[q8, q10], 2 = x_ExplicitR3_Explicit[q8, q10], - 3 = x_ExplicitR3_Explicit[q8, q10]; - int(1..3)]) - | q10 : int(1..3)]) - /\ - and([or([x_ExplicitR3_Explicit[q8, q14] = 1 | q14 : int(1..3)]), - or([x_ExplicitR3_Explicit[q8, q16] = 2 | q16 : int(1..3)]), - or([x_ExplicitR3_Explicit[q8, q18] = 3 | q18 : int(1..3)]); - int(1..3)]) - | q8 : int(1..2)]), - [x_ExplicitR3_Explicit[1, q5] | q5 : int(1..3)] >>>>>> master -======= [-toInt(x_ExplicitR2_Occurrence[1, q4]) | q4 : int(1..4)] >>>>>> main diff --git a/tests/exhaustive/basic/setOfSet03/expected/model_2.eprime.orig b/tests/exhaustive/basic/setOfSet03/expected/model_2.eprime.orig deleted file mode 100644 index 0c8fc4a8a1..0000000000 --- a/tests/exhaustive/basic/setOfSet03/expected/model_2.eprime.orig +++ /dev/null @@ -1,14 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitR3_Explicit: matrix indexed by [int(1..2), int(1..3)] of int(1..4) -branching on [x_ExplicitR3_Explicit] -such that - [x_ExplicitR3_Explicit[1, q5] | q5 : int(1..3)] >>>>>> master - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_1_1_1-solution000001.solution b/tests/exhaustive/basic/setOfSet04/expected/model_1_1_1-solution000001.solution new file mode 100644 index 0000000000..c8946f3d06 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_1_1_1-solution000001.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{}, {2}} +$ Visualisation for x +$ +$ 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_1_1_1-solution000002.solution b/tests/exhaustive/basic/setOfSet04/expected/model_1_1_1-solution000002.solution new file mode 100644 index 0000000000..3ec452354e --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_1_1_1-solution000002.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{}, {1}} +$ Visualisation for x +$ +$ 1 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_1_1_1-solution000003.solution b/tests/exhaustive/basic/setOfSet04/expected/model_1_1_1-solution000003.solution new file mode 100644 index 0000000000..af16592c51 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_1_1_1-solution000003.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{1}, {2}} +$ Visualisation for x +$ 1 +$ 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_1_1_1-solution000004.solution b/tests/exhaustive/basic/setOfSet04/expected/model_1_1_1-solution000004.solution new file mode 100644 index 0000000000..a6c0b6a43e --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_1_1_1-solution000004.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{}, {1, 2}} +$ Visualisation for x +$ +$ 1 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_1_1_1-solution000005.solution b/tests/exhaustive/basic/setOfSet04/expected/model_1_1_1-solution000005.solution new file mode 100644 index 0000000000..9bf2af0712 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_1_1_1-solution000005.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{1, 2}, {2}} +$ Visualisation for x +$ 1 2 +$ 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_1_1_1-solution000006.solution b/tests/exhaustive/basic/setOfSet04/expected/model_1_1_1-solution000006.solution new file mode 100644 index 0000000000..38937c9389 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_1_1_1-solution000006.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{1}, {1, 2}} +$ Visualisation for x +$ 1 +$ 1 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_1_1_1.eprime b/tests/exhaustive/basic/setOfSet04/expected/model_1_1_1.eprime new file mode 100644 index 0000000000..2aa55abc0e --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_1_1_1.eprime @@ -0,0 +1,9 @@ +language ESSENCE' 1.0 + +find x_ExplicitR2_Occurrence: matrix indexed by [int(1..2), int(1..2)] of bool +branching on [x_ExplicitR2_Occurrence] +such that + [-toInt(x_ExplicitR2_Occurrence[1, q4]) | q4 : int(1..2)] x_ExplicitR6_ExplicitVarSizeWithDummy[q7, q9 + 1] = 3 + | q9 : int(1..2)]) + | q7 : int(1..2)]), + and([sum([toInt(x_ExplicitR6_ExplicitVarSizeWithDummy[q7, q10] != 3) | q10 : int(1..3)]) <= 3 | q7 : int(1..2)]), + and([or([and([x_ExplicitR2_Occurrence[q17, q18] -> + or([x_ExplicitR6_ExplicitVarSizeWithDummy[q15, q20] != 3 /\ + x_ExplicitR6_ExplicitVarSizeWithDummy[q15, q20] = q18 + | q20 : int(1..3)]) + | q18 : int(1..2)]) + /\ + and([x_ExplicitR6_ExplicitVarSizeWithDummy[q15, q22] != 3 -> + x_ExplicitR2_Occurrence[q17, x_ExplicitR6_ExplicitVarSizeWithDummy[q15, q22]] + | q22 : int(1..3)]) + | q17 : int(1..2)]) + | q15 : int(1..2)]), + and([or([and([x_ExplicitR6_ExplicitVarSizeWithDummy[q26, q28] != 3 -> + x_ExplicitR2_Occurrence[q24, x_ExplicitR6_ExplicitVarSizeWithDummy[q26, q28]] + | q28 : int(1..3)]) + /\ + and([x_ExplicitR2_Occurrence[q24, q29] -> + or([x_ExplicitR6_ExplicitVarSizeWithDummy[q26, q31] != 3 /\ + x_ExplicitR6_ExplicitVarSizeWithDummy[q26, q31] = q29 + | q31 : int(1..3)]) + | q29 : int(1..2)]) + | q26 : int(1..2)]) + | q24 : int(1..2)]) + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_1_1_3-solution000001.solution b/tests/exhaustive/basic/setOfSet04/expected/model_1_1_3-solution000001.solution new file mode 100644 index 0000000000..3ec452354e --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_1_1_3-solution000001.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{}, {1}} +$ Visualisation for x +$ +$ 1 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_1_1_3-solution000002.solution b/tests/exhaustive/basic/setOfSet04/expected/model_1_1_3-solution000002.solution new file mode 100644 index 0000000000..c8946f3d06 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_1_1_3-solution000002.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{}, {2}} +$ Visualisation for x +$ +$ 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_1_1_3-solution000003.solution b/tests/exhaustive/basic/setOfSet04/expected/model_1_1_3-solution000003.solution new file mode 100644 index 0000000000..a6c0b6a43e --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_1_1_3-solution000003.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{}, {1, 2}} +$ Visualisation for x +$ +$ 1 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_1_1_3-solution000004.solution b/tests/exhaustive/basic/setOfSet04/expected/model_1_1_3-solution000004.solution new file mode 100644 index 0000000000..af16592c51 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_1_1_3-solution000004.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{1}, {2}} +$ Visualisation for x +$ 1 +$ 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_1_1_3-solution000005.solution b/tests/exhaustive/basic/setOfSet04/expected/model_1_1_3-solution000005.solution new file mode 100644 index 0000000000..38937c9389 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_1_1_3-solution000005.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{1}, {1, 2}} +$ Visualisation for x +$ 1 +$ 1 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_1_1_3-solution000006.solution b/tests/exhaustive/basic/setOfSet04/expected/model_1_1_3-solution000006.solution new file mode 100644 index 0000000000..9bf2af0712 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_1_1_3-solution000006.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{1, 2}, {2}} +$ Visualisation for x +$ 1 2 +$ 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_1_1_3.eprime.orig b/tests/exhaustive/basic/setOfSet04/expected/model_1_1_3.eprime.orig deleted file mode 100644 index cfc048dd79..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_1_1_3.eprime.orig +++ /dev/null @@ -1,52 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitR2_Occurrence: matrix indexed by [int(1..2), int(1..2)] of bool -find x_ExplicitR5_ExplicitVarSizeWithMarker_Marker: matrix indexed by [int(1..2)] of int(0..3) -find x_ExplicitR5_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..2), int(1..3)] of int(1..2) -branching on - [x_ExplicitR5_ExplicitVarSizeWithMarker_Marker, x_ExplicitR5_ExplicitVarSizeWithMarker_Values, - x_ExplicitR2_Occurrence] -such that - [-toInt(x_ExplicitR2_Occurrence[1, q4]) | q4 : int(1..2)] - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q7, q8] < - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q7, q8 + 1] - | q8 : int(1..2)]) - | q7 : int(1..2)]), - and([and([q9 > x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q7] -> - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q7, q9] = 1 - | q9 : int(1..3)]) - | q7 : int(1..2)]), - and([x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q7] <= 3 | q7 : int(1..2)]), - and([or([and([x_ExplicitR2_Occurrence[q16, q17] -> - or([q19 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q14] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q14, q19] = q17 - | q19 : int(1..3)]) - | q17 : int(1..2)]) - /\ - and([q21 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q14] -> - x_ExplicitR2_Occurrence[q16, x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q14, q21]] - | q21 : int(1..3)]) - | q16 : int(1..2)]) - | q14 : int(1..2)]), - and([or([and([q27 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q25] -> - x_ExplicitR2_Occurrence[q23, x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q25, q27]] - | q27 : int(1..3)]) - /\ - and([x_ExplicitR2_Occurrence[q23, q28] -> - or([q30 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q25] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q25, q30] = q28 - | q30 : int(1..3)]) - | q28 : int(1..2)]) - | q25 : int(1..2)]) - | q23 : int(1..2)]) - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_1_1_4-solution000001.solution b/tests/exhaustive/basic/setOfSet04/expected/model_1_1_4-solution000001.solution new file mode 100644 index 0000000000..3ec452354e --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_1_1_4-solution000001.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{}, {1}} +$ Visualisation for x +$ +$ 1 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_1_1_4-solution000002.solution b/tests/exhaustive/basic/setOfSet04/expected/model_1_1_4-solution000002.solution new file mode 100644 index 0000000000..c8946f3d06 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_1_1_4-solution000002.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{}, {2}} +$ Visualisation for x +$ +$ 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_1_1_4-solution000003.solution b/tests/exhaustive/basic/setOfSet04/expected/model_1_1_4-solution000003.solution new file mode 100644 index 0000000000..af16592c51 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_1_1_4-solution000003.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{1}, {2}} +$ Visualisation for x +$ 1 +$ 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_1_1_4-solution000004.solution b/tests/exhaustive/basic/setOfSet04/expected/model_1_1_4-solution000004.solution new file mode 100644 index 0000000000..a6c0b6a43e --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_1_1_4-solution000004.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{}, {1, 2}} +$ Visualisation for x +$ +$ 1 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_1_1_4-solution000005.solution b/tests/exhaustive/basic/setOfSet04/expected/model_1_1_4-solution000005.solution new file mode 100644 index 0000000000..38937c9389 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_1_1_4-solution000005.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{1}, {1, 2}} +$ Visualisation for x +$ 1 +$ 1 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_1_1_4-solution000006.solution b/tests/exhaustive/basic/setOfSet04/expected/model_1_1_4-solution000006.solution new file mode 100644 index 0000000000..9bf2af0712 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_1_1_4-solution000006.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{1, 2}, {2}} +$ Visualisation for x +$ 1 2 +$ 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_1_1_4.eprime b/tests/exhaustive/basic/setOfSet04/expected/model_1_1_4.eprime new file mode 100644 index 0000000000..47eebe1823 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_1_1_4.eprime @@ -0,0 +1,57 @@ +language ESSENCE' 1.0 + +find x_ExplicitR2_Occurrence: matrix indexed by [int(1..2), int(1..2)] of bool +find x_ExplicitR4_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..2), int(1..3)] of bool +find x_ExplicitR4_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..2), int(1..3)] of int(1..2) +branching on + [x_ExplicitR4_ExplicitVarSizeWithFlags_Flags, x_ExplicitR4_ExplicitVarSizeWithFlags_Values, x_ExplicitR2_Occurrence] +such that + [-toInt(x_ExplicitR2_Occurrence[1, q4]) | q4 : int(1..2)] + x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q7, q8] < + x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q7, q8 + 1] + | q8 : int(1..2)]) + | q7 : int(1..2)]), + and([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q7, q9] = false -> + x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q7, q9] = 1 + | q9 : int(1..3)]) + | q7 : int(1..2)]), + and([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q7, q10 + 1] -> + x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q7, q10] + | q10 : int(1..2)]) + | q7 : int(1..2)]), + and([sum([toInt(x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q7, q11]) | q11 : int(1..3)]) <= 3 | q7 : int(1..2)]), + and([or([and([x_ExplicitR2_Occurrence[q18, q19] -> + or([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q16, q21] /\ + x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q16, q21] = q19 + | q21 : int(1..3)]) + | q19 : int(1..2)]) + /\ + and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q16, q23] -> + x_ExplicitR2_Occurrence[q18, x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q16, q23]] + | q23 : int(1..3)]) + | q18 : int(1..2)]) + | q16 : int(1..2)]), + and([or([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q27, q29] -> + x_ExplicitR2_Occurrence[q25, x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q27, q29]] + | q29 : int(1..3)]) + /\ + and([x_ExplicitR2_Occurrence[q25, q30] -> + or([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q27, q32] /\ + x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q27, q32] = q30 + | q32 : int(1..3)]) + | q30 : int(1..2)]) + | q27 : int(1..2)]) + | q25 : int(1..2)]) + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_1_2_3-solution000001.solution b/tests/exhaustive/basic/setOfSet04/expected/model_1_2_3-solution000001.solution new file mode 100644 index 0000000000..3ec452354e --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_1_2_3-solution000001.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{}, {1}} +$ Visualisation for x +$ +$ 1 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_1_2_3-solution000002.solution b/tests/exhaustive/basic/setOfSet04/expected/model_1_2_3-solution000002.solution new file mode 100644 index 0000000000..c8946f3d06 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_1_2_3-solution000002.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{}, {2}} +$ Visualisation for x +$ +$ 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_1_2_3-solution000003.solution b/tests/exhaustive/basic/setOfSet04/expected/model_1_2_3-solution000003.solution new file mode 100644 index 0000000000..a6c0b6a43e --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_1_2_3-solution000003.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{}, {1, 2}} +$ Visualisation for x +$ +$ 1 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_1_2_3-solution000004.solution b/tests/exhaustive/basic/setOfSet04/expected/model_1_2_3-solution000004.solution new file mode 100644 index 0000000000..af16592c51 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_1_2_3-solution000004.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{1}, {2}} +$ Visualisation for x +$ 1 +$ 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_1_2_3-solution000005.solution b/tests/exhaustive/basic/setOfSet04/expected/model_1_2_3-solution000005.solution new file mode 100644 index 0000000000..38937c9389 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_1_2_3-solution000005.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{1}, {1, 2}} +$ Visualisation for x +$ 1 +$ 1 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_1_2_3-solution000006.solution b/tests/exhaustive/basic/setOfSet04/expected/model_1_2_3-solution000006.solution new file mode 100644 index 0000000000..9bf2af0712 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_1_2_3-solution000006.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{1, 2}, {2}} +$ Visualisation for x +$ 1 2 +$ 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_1_2_3.eprime.orig b/tests/exhaustive/basic/setOfSet04/expected/model_1_2_3.eprime.orig deleted file mode 100644 index 392506e889..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_1_2_3.eprime.orig +++ /dev/null @@ -1,115 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitR2_Occurrence: matrix indexed by [int(1..2), int(1..2)] of bool -find x_ExplicitR6_ExplicitVarSizeWithDummy: matrix indexed by [int(1..2), int(1..3)] of int(1..3) -find x_ExplicitR5_ExplicitVarSizeWithMarker_Marker: matrix indexed by [int(1..2)] of int(0..3) -find x_ExplicitR5_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..2), int(1..3)] of int(1..2) -branching on - [x_ExplicitR5_ExplicitVarSizeWithMarker_Marker, x_ExplicitR5_ExplicitVarSizeWithMarker_Values, - x_ExplicitR2_Occurrence, x_ExplicitR6_ExplicitVarSizeWithDummy] -such that - [-toInt(x_ExplicitR2_Occurrence[1, q4]) | q4 : int(1..2)] x_ExplicitR6_ExplicitVarSizeWithDummy[q7, q9 + 1] = 3 - | q9 : int(1..2)]) - | q7 : int(1..2)]), - and([sum([toInt(x_ExplicitR6_ExplicitVarSizeWithDummy[q7, q10] != 3) | q10 : int(1..3)]) <= 3 | q7 : int(1..2)]), - and([or([and([x_ExplicitR2_Occurrence[q17, q18] -> - or([x_ExplicitR6_ExplicitVarSizeWithDummy[q15, q20] != 3 /\ - x_ExplicitR6_ExplicitVarSizeWithDummy[q15, q20] = q18 - | q20 : int(1..3)]) - | q18 : int(1..2)]) - /\ - and([x_ExplicitR6_ExplicitVarSizeWithDummy[q15, q22] != 3 -> - x_ExplicitR2_Occurrence[q17, x_ExplicitR6_ExplicitVarSizeWithDummy[q15, q22]] - | q22 : int(1..3)]) - | q17 : int(1..2)]) - | q15 : int(1..2)]), - and([or([and([x_ExplicitR6_ExplicitVarSizeWithDummy[q26, q28] != 3 -> - x_ExplicitR2_Occurrence[q24, x_ExplicitR6_ExplicitVarSizeWithDummy[q26, q28]] - | q28 : int(1..3)]) - /\ - and([x_ExplicitR2_Occurrence[q24, q29] -> - or([x_ExplicitR6_ExplicitVarSizeWithDummy[q26, q31] != 3 /\ - x_ExplicitR6_ExplicitVarSizeWithDummy[q26, q31] = q29 - | q31 : int(1..3)]) - | q29 : int(1..2)]) - | q26 : int(1..2)]) - | q24 : int(1..2)]), - flatten([[x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[1]; int(1)], - [x_ExplicitR5_ExplicitVarSizeWithMarker_Values[1, q37] | q37 : int(1..3)]; - int(1..2)]) - - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q33, q34] < - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q33, q34 + 1] - | q34 : int(1..2)]) - | q33 : int(1..2)]), - and([and([q35 > x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q33] -> - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q33, q35] = 1 - | q35 : int(1..3)]) - | q33 : int(1..2)]), - and([x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q33] <= 3 | q33 : int(1..2)]), - and([or([and([x_ExplicitR2_Occurrence[q42, q43] -> - or([q45 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q40] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q40, q45] = q43 - | q45 : int(1..3)]) - | q43 : int(1..2)]) - /\ - and([q47 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q40] -> - x_ExplicitR2_Occurrence[q42, x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q40, q47]] - | q47 : int(1..3)]) - | q42 : int(1..2)]) - | q40 : int(1..2)]), - and([or([and([q53 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q51] -> - x_ExplicitR2_Occurrence[q49, x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q51, q53]] - | q53 : int(1..3)]) - /\ - and([x_ExplicitR2_Occurrence[q49, q54] -> - or([q56 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q51] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q51, q56] = q54 - | q56 : int(1..3)]) - | q54 : int(1..2)]) - | q51 : int(1..2)]) - | q49 : int(1..2)]), - and([or([and([x_ExplicitR6_ExplicitVarSizeWithDummy[q60, q62] != 3 -> - or([q64 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q58] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q58, q64] = - x_ExplicitR6_ExplicitVarSizeWithDummy[q60, q62] - | q64 : int(1..3)]) - | q62 : int(1..3)]) - /\ - and([q66 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q58] -> - or([x_ExplicitR6_ExplicitVarSizeWithDummy[q60, q68] != 3 /\ - x_ExplicitR6_ExplicitVarSizeWithDummy[q60, q68] = - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q58, q66] - | q68 : int(1..3)]) - | q66 : int(1..3)]) - | q60 : int(1..2)]) - | q58 : int(1..2)]), - and([or([and([q74 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q72] -> - or([x_ExplicitR6_ExplicitVarSizeWithDummy[q70, q76] != 3 /\ - x_ExplicitR6_ExplicitVarSizeWithDummy[q70, q76] = - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q72, q74] - | q76 : int(1..3)]) - | q74 : int(1..3)]) - /\ - and([x_ExplicitR6_ExplicitVarSizeWithDummy[q70, q78] != 3 -> - or([q80 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q72] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q72, q80] = - x_ExplicitR6_ExplicitVarSizeWithDummy[q70, q78] - | q80 : int(1..3)]) - | q78 : int(1..3)]) - | q72 : int(1..2)]) - | q70 : int(1..2)]) - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_1_2_4-solution000001.solution b/tests/exhaustive/basic/setOfSet04/expected/model_1_2_4-solution000001.solution new file mode 100644 index 0000000000..3ec452354e --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_1_2_4-solution000001.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{}, {1}} +$ Visualisation for x +$ +$ 1 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_1_2_4-solution000002.solution b/tests/exhaustive/basic/setOfSet04/expected/model_1_2_4-solution000002.solution new file mode 100644 index 0000000000..c8946f3d06 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_1_2_4-solution000002.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{}, {2}} +$ Visualisation for x +$ +$ 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_1_2_4-solution000003.solution b/tests/exhaustive/basic/setOfSet04/expected/model_1_2_4-solution000003.solution new file mode 100644 index 0000000000..af16592c51 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_1_2_4-solution000003.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{1}, {2}} +$ Visualisation for x +$ 1 +$ 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_1_2_4-solution000004.solution b/tests/exhaustive/basic/setOfSet04/expected/model_1_2_4-solution000004.solution new file mode 100644 index 0000000000..a6c0b6a43e --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_1_2_4-solution000004.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{}, {1, 2}} +$ Visualisation for x +$ +$ 1 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_1_2_4-solution000005.solution b/tests/exhaustive/basic/setOfSet04/expected/model_1_2_4-solution000005.solution new file mode 100644 index 0000000000..38937c9389 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_1_2_4-solution000005.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{1}, {1, 2}} +$ Visualisation for x +$ 1 +$ 1 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_1_2_4-solution000006.solution b/tests/exhaustive/basic/setOfSet04/expected/model_1_2_4-solution000006.solution new file mode 100644 index 0000000000..9bf2af0712 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_1_2_4-solution000006.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{1, 2}, {2}} +$ Visualisation for x +$ 1 2 +$ 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_1_2_4.eprime b/tests/exhaustive/basic/setOfSet04/expected/model_1_2_4.eprime new file mode 100644 index 0000000000..46fba1f2be --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_1_2_4.eprime @@ -0,0 +1,121 @@ +language ESSENCE' 1.0 + +find x_ExplicitR2_Occurrence: matrix indexed by [int(1..2), int(1..2)] of bool +find x_ExplicitR6_ExplicitVarSizeWithDummy: matrix indexed by [int(1..2), int(1..3)] of int(1..3) +find x_ExplicitR4_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..2), int(1..3)] of bool +find x_ExplicitR4_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..2), int(1..3)] of int(1..2) +branching on + [x_ExplicitR4_ExplicitVarSizeWithFlags_Flags, x_ExplicitR4_ExplicitVarSizeWithFlags_Values, x_ExplicitR2_Occurrence, + x_ExplicitR6_ExplicitVarSizeWithDummy] +such that + [-toInt(x_ExplicitR2_Occurrence[1, q4]) | q4 : int(1..2)] x_ExplicitR6_ExplicitVarSizeWithDummy[q7, q9 + 1] = 3 + | q9 : int(1..2)]) + | q7 : int(1..2)]), + and([sum([toInt(x_ExplicitR6_ExplicitVarSizeWithDummy[q7, q10] != 3) | q10 : int(1..3)]) <= 3 | q7 : int(1..2)]), + and([or([and([x_ExplicitR2_Occurrence[q17, q18] -> + or([x_ExplicitR6_ExplicitVarSizeWithDummy[q15, q20] != 3 /\ + x_ExplicitR6_ExplicitVarSizeWithDummy[q15, q20] = q18 + | q20 : int(1..3)]) + | q18 : int(1..2)]) + /\ + and([x_ExplicitR6_ExplicitVarSizeWithDummy[q15, q22] != 3 -> + x_ExplicitR2_Occurrence[q17, x_ExplicitR6_ExplicitVarSizeWithDummy[q15, q22]] + | q22 : int(1..3)]) + | q17 : int(1..2)]) + | q15 : int(1..2)]), + and([or([and([x_ExplicitR6_ExplicitVarSizeWithDummy[q26, q28] != 3 -> + x_ExplicitR2_Occurrence[q24, x_ExplicitR6_ExplicitVarSizeWithDummy[q26, q28]] + | q28 : int(1..3)]) + /\ + and([x_ExplicitR2_Occurrence[q24, q29] -> + or([x_ExplicitR6_ExplicitVarSizeWithDummy[q26, q31] != 3 /\ + x_ExplicitR6_ExplicitVarSizeWithDummy[q26, q31] = q29 + | q31 : int(1..3)]) + | q29 : int(1..2)]) + | q26 : int(1..2)]) + | q24 : int(1..2)]), + flatten([flatten([[-toInt(x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[1, q39]); int(1)], + [x_ExplicitR4_ExplicitVarSizeWithFlags_Values[1, q39]; int(1)]; + int(1..2)]) + | q39 : int(1..3)]) + + x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q33, q34] < + x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q33, q34 + 1] + | q34 : int(1..2)]) + | q33 : int(1..2)]), + and([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q33, q35] = false -> + x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q33, q35] = 1 + | q35 : int(1..3)]) + | q33 : int(1..2)]), + and([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q33, q36 + 1] -> + x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q33, q36] + | q36 : int(1..2)]) + | q33 : int(1..2)]), + and([sum([toInt(x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q33, q37]) | q37 : int(1..3)]) <= 3 | q33 : int(1..2)]), + and([or([and([x_ExplicitR2_Occurrence[q44, q45] -> + or([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q42, q47] /\ + x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q42, q47] = q45 + | q47 : int(1..3)]) + | q45 : int(1..2)]) + /\ + and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q42, q49] -> + x_ExplicitR2_Occurrence[q44, x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q42, q49]] + | q49 : int(1..3)]) + | q44 : int(1..2)]) + | q42 : int(1..2)]), + and([or([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q53, q55] -> + x_ExplicitR2_Occurrence[q51, x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q53, q55]] + | q55 : int(1..3)]) + /\ + and([x_ExplicitR2_Occurrence[q51, q56] -> + or([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q53, q58] /\ + x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q53, q58] = q56 + | q58 : int(1..3)]) + | q56 : int(1..2)]) + | q53 : int(1..2)]) + | q51 : int(1..2)]), + and([or([and([x_ExplicitR6_ExplicitVarSizeWithDummy[q62, q64] != 3 -> + or([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q60, q66] /\ + x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q60, q66] = + x_ExplicitR6_ExplicitVarSizeWithDummy[q62, q64] + | q66 : int(1..3)]) + | q64 : int(1..3)]) + /\ + and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q60, q68] -> + or([x_ExplicitR6_ExplicitVarSizeWithDummy[q62, q70] != 3 /\ + x_ExplicitR6_ExplicitVarSizeWithDummy[q62, q70] = + x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q60, q68] + | q70 : int(1..3)]) + | q68 : int(1..3)]) + | q62 : int(1..2)]) + | q60 : int(1..2)]), + and([or([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q74, q76] -> + or([x_ExplicitR6_ExplicitVarSizeWithDummy[q72, q78] != 3 /\ + x_ExplicitR6_ExplicitVarSizeWithDummy[q72, q78] = + x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q74, q76] + | q78 : int(1..3)]) + | q76 : int(1..3)]) + /\ + and([x_ExplicitR6_ExplicitVarSizeWithDummy[q72, q80] != 3 -> + or([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q74, q82] /\ + x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q74, q82] = + x_ExplicitR6_ExplicitVarSizeWithDummy[q72, q80] + | q82 : int(1..3)]) + | q80 : int(1..3)]) + | q74 : int(1..2)]) + | q72 : int(1..2)]) + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_1_3_1.eprime.orig b/tests/exhaustive/basic/setOfSet04/expected/model_1_3_1.eprime.orig deleted file mode 100644 index cfc048dd79..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_1_3_1.eprime.orig +++ /dev/null @@ -1,52 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitR2_Occurrence: matrix indexed by [int(1..2), int(1..2)] of bool -find x_ExplicitR5_ExplicitVarSizeWithMarker_Marker: matrix indexed by [int(1..2)] of int(0..3) -find x_ExplicitR5_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..2), int(1..3)] of int(1..2) -branching on - [x_ExplicitR5_ExplicitVarSizeWithMarker_Marker, x_ExplicitR5_ExplicitVarSizeWithMarker_Values, - x_ExplicitR2_Occurrence] -such that - [-toInt(x_ExplicitR2_Occurrence[1, q4]) | q4 : int(1..2)] - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q7, q8] < - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q7, q8 + 1] - | q8 : int(1..2)]) - | q7 : int(1..2)]), - and([and([q9 > x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q7] -> - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q7, q9] = 1 - | q9 : int(1..3)]) - | q7 : int(1..2)]), - and([x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q7] <= 3 | q7 : int(1..2)]), - and([or([and([x_ExplicitR2_Occurrence[q16, q17] -> - or([q19 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q14] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q14, q19] = q17 - | q19 : int(1..3)]) - | q17 : int(1..2)]) - /\ - and([q21 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q14] -> - x_ExplicitR2_Occurrence[q16, x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q14, q21]] - | q21 : int(1..3)]) - | q16 : int(1..2)]) - | q14 : int(1..2)]), - and([or([and([q27 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q25] -> - x_ExplicitR2_Occurrence[q23, x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q25, q27]] - | q27 : int(1..3)]) - /\ - and([x_ExplicitR2_Occurrence[q23, q28] -> - or([q30 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q25] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q25, q30] = q28 - | q30 : int(1..3)]) - | q28 : int(1..2)]) - | q25 : int(1..2)]) - | q23 : int(1..2)]) - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_1_3_2-solution000001.solution b/tests/exhaustive/basic/setOfSet04/expected/model_1_3_2-solution000001.solution new file mode 100644 index 0000000000..38937c9389 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_1_3_2-solution000001.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{1}, {1, 2}} +$ Visualisation for x +$ 1 +$ 1 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_1_3_2-solution000002.solution b/tests/exhaustive/basic/setOfSet04/expected/model_1_3_2-solution000002.solution new file mode 100644 index 0000000000..9bf2af0712 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_1_3_2-solution000002.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{1, 2}, {2}} +$ Visualisation for x +$ 1 2 +$ 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_1_3_2-solution000003.solution b/tests/exhaustive/basic/setOfSet04/expected/model_1_3_2-solution000003.solution new file mode 100644 index 0000000000..a6c0b6a43e --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_1_3_2-solution000003.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{}, {1, 2}} +$ Visualisation for x +$ +$ 1 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_1_3_2-solution000004.solution b/tests/exhaustive/basic/setOfSet04/expected/model_1_3_2-solution000004.solution new file mode 100644 index 0000000000..af16592c51 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_1_3_2-solution000004.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{1}, {2}} +$ Visualisation for x +$ 1 +$ 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_1_3_2-solution000005.solution b/tests/exhaustive/basic/setOfSet04/expected/model_1_3_2-solution000005.solution new file mode 100644 index 0000000000..3ec452354e --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_1_3_2-solution000005.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{}, {1}} +$ Visualisation for x +$ +$ 1 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_1_3_2-solution000006.solution b/tests/exhaustive/basic/setOfSet04/expected/model_1_3_2-solution000006.solution new file mode 100644 index 0000000000..c8946f3d06 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_1_3_2-solution000006.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{}, {2}} +$ Visualisation for x +$ +$ 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_1_3_2.eprime.orig b/tests/exhaustive/basic/setOfSet04/expected/model_1_3_2.eprime.orig deleted file mode 100644 index ee38a53845..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_1_3_2.eprime.orig +++ /dev/null @@ -1,116 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitR2_Occurrence: matrix indexed by [int(1..2), int(1..2)] of bool -find x_ExplicitR5_ExplicitVarSizeWithMarker_Marker: matrix indexed by [int(1..2)] of int(0..3) -find x_ExplicitR5_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..2), int(1..3)] of int(1..2) -find x_ExplicitR6_ExplicitVarSizeWithDummy: matrix indexed by [int(1..2), int(1..3)] of int(1..3) -branching on - [x_ExplicitR6_ExplicitVarSizeWithDummy, x_ExplicitR2_Occurrence, x_ExplicitR5_ExplicitVarSizeWithMarker_Marker, - x_ExplicitR5_ExplicitVarSizeWithMarker_Values] -such that - [-toInt(x_ExplicitR2_Occurrence[1, q4]) | q4 : int(1..2)] - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q7, q8] < - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q7, q8 + 1] - | q8 : int(1..2)]) - | q7 : int(1..2)]), - and([and([q9 > x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q7] -> - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q7, q9] = 1 - | q9 : int(1..3)]) - | q7 : int(1..2)]), - and([x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q7] <= 3 | q7 : int(1..2)]), - and([or([and([x_ExplicitR2_Occurrence[q16, q17] -> - or([q19 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q14] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q14, q19] = q17 - | q19 : int(1..3)]) - | q17 : int(1..2)]) - /\ - and([q21 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q14] -> - x_ExplicitR2_Occurrence[q16, x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q14, q21]] - | q21 : int(1..3)]) - | q16 : int(1..2)]) - | q14 : int(1..2)]), - and([or([and([q27 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q25] -> - x_ExplicitR2_Occurrence[q23, x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q25, q27]] - | q27 : int(1..3)]) - /\ - and([x_ExplicitR2_Occurrence[q23, q28] -> - or([q30 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q25] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q25, q30] = q28 - | q30 : int(1..3)]) - | q28 : int(1..2)]) - | q25 : int(1..2)]) - | q23 : int(1..2)]), - [x_ExplicitR6_ExplicitVarSizeWithDummy[1, q37] | q37 : int(1..3)] - x_ExplicitR6_ExplicitVarSizeWithDummy[q32, q34 + 1] = 3 - | q34 : int(1..2)]) - | q32 : int(1..2)]), - and([sum([toInt(x_ExplicitR6_ExplicitVarSizeWithDummy[q32, q35] != 3) | q35 : int(1..3)]) <= 3 | q32 : int(1..2)]), - and([or([and([x_ExplicitR2_Occurrence[q42, q43] -> - or([x_ExplicitR6_ExplicitVarSizeWithDummy[q40, q45] != 3 /\ - x_ExplicitR6_ExplicitVarSizeWithDummy[q40, q45] = q43 - | q45 : int(1..3)]) - | q43 : int(1..2)]) - /\ - and([x_ExplicitR6_ExplicitVarSizeWithDummy[q40, q47] != 3 -> - x_ExplicitR2_Occurrence[q42, x_ExplicitR6_ExplicitVarSizeWithDummy[q40, q47]] - | q47 : int(1..3)]) - | q42 : int(1..2)]) - | q40 : int(1..2)]), - and([or([and([x_ExplicitR6_ExplicitVarSizeWithDummy[q51, q53] != 3 -> - x_ExplicitR2_Occurrence[q49, x_ExplicitR6_ExplicitVarSizeWithDummy[q51, q53]] - | q53 : int(1..3)]) - /\ - and([x_ExplicitR2_Occurrence[q49, q54] -> - or([x_ExplicitR6_ExplicitVarSizeWithDummy[q51, q56] != 3 /\ - x_ExplicitR6_ExplicitVarSizeWithDummy[q51, q56] = q54 - | q56 : int(1..3)]) - | q54 : int(1..2)]) - | q51 : int(1..2)]) - | q49 : int(1..2)]), - and([or([and([q62 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q60] -> - or([x_ExplicitR6_ExplicitVarSizeWithDummy[q58, q64] != 3 /\ - x_ExplicitR6_ExplicitVarSizeWithDummy[q58, q64] = - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q60, q62] - | q64 : int(1..3)]) - | q62 : int(1..3)]) - /\ - and([x_ExplicitR6_ExplicitVarSizeWithDummy[q58, q66] != 3 -> - or([q68 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q60] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q60, q68] = - x_ExplicitR6_ExplicitVarSizeWithDummy[q58, q66] - | q68 : int(1..3)]) - | q66 : int(1..3)]) - | q60 : int(1..2)]) - | q58 : int(1..2)]), - and([or([and([x_ExplicitR6_ExplicitVarSizeWithDummy[q72, q74] != 3 -> - or([q76 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q70] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q70, q76] = - x_ExplicitR6_ExplicitVarSizeWithDummy[q72, q74] - | q76 : int(1..3)]) - | q74 : int(1..3)]) - /\ - and([q78 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q70] -> - or([x_ExplicitR6_ExplicitVarSizeWithDummy[q72, q80] != 3 /\ - x_ExplicitR6_ExplicitVarSizeWithDummy[q72, q80] = - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q70, q78] - | q80 : int(1..3)]) - | q78 : int(1..3)]) - | q72 : int(1..2)]) - | q70 : int(1..2)]) - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_1_3_3.eprime.orig b/tests/exhaustive/basic/setOfSet04/expected/model_1_3_3.eprime.orig deleted file mode 100644 index cfc048dd79..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_1_3_3.eprime.orig +++ /dev/null @@ -1,52 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitR2_Occurrence: matrix indexed by [int(1..2), int(1..2)] of bool -find x_ExplicitR5_ExplicitVarSizeWithMarker_Marker: matrix indexed by [int(1..2)] of int(0..3) -find x_ExplicitR5_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..2), int(1..3)] of int(1..2) -branching on - [x_ExplicitR5_ExplicitVarSizeWithMarker_Marker, x_ExplicitR5_ExplicitVarSizeWithMarker_Values, - x_ExplicitR2_Occurrence] -such that - [-toInt(x_ExplicitR2_Occurrence[1, q4]) | q4 : int(1..2)] - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q7, q8] < - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q7, q8 + 1] - | q8 : int(1..2)]) - | q7 : int(1..2)]), - and([and([q9 > x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q7] -> - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q7, q9] = 1 - | q9 : int(1..3)]) - | q7 : int(1..2)]), - and([x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q7] <= 3 | q7 : int(1..2)]), - and([or([and([x_ExplicitR2_Occurrence[q16, q17] -> - or([q19 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q14] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q14, q19] = q17 - | q19 : int(1..3)]) - | q17 : int(1..2)]) - /\ - and([q21 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q14] -> - x_ExplicitR2_Occurrence[q16, x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q14, q21]] - | q21 : int(1..3)]) - | q16 : int(1..2)]) - | q14 : int(1..2)]), - and([or([and([q27 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q25] -> - x_ExplicitR2_Occurrence[q23, x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q25, q27]] - | q27 : int(1..3)]) - /\ - and([x_ExplicitR2_Occurrence[q23, q28] -> - or([q30 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q25] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q25, q30] = q28 - | q30 : int(1..3)]) - | q28 : int(1..2)]) - | q25 : int(1..2)]) - | q23 : int(1..2)]) - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_1_3_4-solution000001.solution b/tests/exhaustive/basic/setOfSet04/expected/model_1_3_4-solution000001.solution new file mode 100644 index 0000000000..3ec452354e --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_1_3_4-solution000001.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{}, {1}} +$ Visualisation for x +$ +$ 1 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_1_3_4-solution000002.solution b/tests/exhaustive/basic/setOfSet04/expected/model_1_3_4-solution000002.solution new file mode 100644 index 0000000000..c8946f3d06 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_1_3_4-solution000002.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{}, {2}} +$ Visualisation for x +$ +$ 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_1_3_4-solution000003.solution b/tests/exhaustive/basic/setOfSet04/expected/model_1_3_4-solution000003.solution new file mode 100644 index 0000000000..af16592c51 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_1_3_4-solution000003.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{1}, {2}} +$ Visualisation for x +$ 1 +$ 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_1_3_4-solution000004.solution b/tests/exhaustive/basic/setOfSet04/expected/model_1_3_4-solution000004.solution new file mode 100644 index 0000000000..a6c0b6a43e --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_1_3_4-solution000004.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{}, {1, 2}} +$ Visualisation for x +$ +$ 1 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_1_3_4-solution000005.solution b/tests/exhaustive/basic/setOfSet04/expected/model_1_3_4-solution000005.solution new file mode 100644 index 0000000000..38937c9389 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_1_3_4-solution000005.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{1}, {1, 2}} +$ Visualisation for x +$ 1 +$ 1 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_1_3_4-solution000006.solution b/tests/exhaustive/basic/setOfSet04/expected/model_1_3_4-solution000006.solution new file mode 100644 index 0000000000..9bf2af0712 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_1_3_4-solution000006.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{1, 2}, {2}} +$ Visualisation for x +$ 1 2 +$ 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_1_3_4.eprime.orig b/tests/exhaustive/basic/setOfSet04/expected/model_1_3_4.eprime.orig deleted file mode 100644 index 852454b6db..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_1_3_4.eprime.orig +++ /dev/null @@ -1,129 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitR2_Occurrence: matrix indexed by [int(1..2), int(1..2)] of bool -find x_ExplicitR5_ExplicitVarSizeWithMarker_Marker: matrix indexed by [int(1..2)] of int(0..3) -find x_ExplicitR5_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..2), int(1..3)] of int(1..2) -find x_ExplicitR4_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..2), int(1..3)] of bool -find x_ExplicitR4_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..2), int(1..3)] of int(1..2) -branching on - [x_ExplicitR4_ExplicitVarSizeWithFlags_Flags, x_ExplicitR4_ExplicitVarSizeWithFlags_Values, x_ExplicitR2_Occurrence, - x_ExplicitR5_ExplicitVarSizeWithMarker_Marker, x_ExplicitR5_ExplicitVarSizeWithMarker_Values] -such that - [-toInt(x_ExplicitR2_Occurrence[1, q4]) | q4 : int(1..2)] - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q7, q8] < - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q7, q8 + 1] - | q8 : int(1..2)]) - | q7 : int(1..2)]), - and([and([q9 > x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q7] -> - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q7, q9] = 1 - | q9 : int(1..3)]) - | q7 : int(1..2)]), - and([x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q7] <= 3 | q7 : int(1..2)]), - and([or([and([x_ExplicitR2_Occurrence[q16, q17] -> - or([q19 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q14] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q14, q19] = q17 - | q19 : int(1..3)]) - | q17 : int(1..2)]) - /\ - and([q21 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q14] -> - x_ExplicitR2_Occurrence[q16, x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q14, q21]] - | q21 : int(1..3)]) - | q16 : int(1..2)]) - | q14 : int(1..2)]), - and([or([and([q27 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q25] -> - x_ExplicitR2_Occurrence[q23, x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q25, q27]] - | q27 : int(1..3)]) - /\ - and([x_ExplicitR2_Occurrence[q23, q28] -> - or([q30 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q25] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q25, q30] = q28 - | q30 : int(1..3)]) - | q28 : int(1..2)]) - | q25 : int(1..2)]) - | q23 : int(1..2)]), - flatten([flatten([[-toInt(x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[1, q38]); int(1)], - [x_ExplicitR4_ExplicitVarSizeWithFlags_Values[1, q38]; int(1)]; - int(1..2)]) - | q38 : int(1..3)]) - - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q32, q33] < - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q32, q33 + 1] - | q33 : int(1..2)]) - | q32 : int(1..2)]), - and([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q32, q34] = false -> - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q32, q34] = 1 - | q34 : int(1..3)]) - | q32 : int(1..2)]), - and([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q32, q35 + 1] -> - x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q32, q35] - | q35 : int(1..2)]) - | q32 : int(1..2)]), - and([sum([toInt(x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q32, q36]) | q36 : int(1..3)]) <= 3 | q32 : int(1..2)]), - and([or([and([x_ExplicitR2_Occurrence[q43, q44] -> - or([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q41, q46] /\ - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q41, q46] = q44 - | q46 : int(1..3)]) - | q44 : int(1..2)]) - /\ - and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q41, q48] -> - x_ExplicitR2_Occurrence[q43, x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q41, q48]] - | q48 : int(1..3)]) - | q43 : int(1..2)]) - | q41 : int(1..2)]), - and([or([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q52, q54] -> - x_ExplicitR2_Occurrence[q50, x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q52, q54]] - | q54 : int(1..3)]) - /\ - and([x_ExplicitR2_Occurrence[q50, q55] -> - or([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q52, q57] /\ - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q52, q57] = q55 - | q57 : int(1..3)]) - | q55 : int(1..2)]) - | q52 : int(1..2)]) - | q50 : int(1..2)]), - and([or([and([q63 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q61] -> - or([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q59, q65] /\ - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q59, q65] = - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q61, q63] - | q65 : int(1..3)]) - | q63 : int(1..3)]) - /\ - and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q59, q67] -> - or([q69 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q61] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q61, q69] = - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q59, q67] - | q69 : int(1..3)]) - | q67 : int(1..3)]) - | q61 : int(1..2)]) - | q59 : int(1..2)]), - and([or([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q73, q75] -> - or([q77 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q71] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q71, q77] = - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q73, q75] - | q77 : int(1..3)]) - | q75 : int(1..3)]) - /\ - and([q79 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q71] -> - or([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q73, q81] /\ - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q73, q81] = - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q71, q79] - | q81 : int(1..3)]) - | q79 : int(1..3)]) - | q73 : int(1..2)]) - | q71 : int(1..2)]) - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_1_4_2-solution000001.solution b/tests/exhaustive/basic/setOfSet04/expected/model_1_4_2-solution000001.solution new file mode 100644 index 0000000000..38937c9389 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_1_4_2-solution000001.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{1}, {1, 2}} +$ Visualisation for x +$ 1 +$ 1 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_1_4_2-solution000002.solution b/tests/exhaustive/basic/setOfSet04/expected/model_1_4_2-solution000002.solution new file mode 100644 index 0000000000..9bf2af0712 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_1_4_2-solution000002.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{1, 2}, {2}} +$ Visualisation for x +$ 1 2 +$ 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_1_4_2-solution000003.solution b/tests/exhaustive/basic/setOfSet04/expected/model_1_4_2-solution000003.solution new file mode 100644 index 0000000000..a6c0b6a43e --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_1_4_2-solution000003.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{}, {1, 2}} +$ Visualisation for x +$ +$ 1 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_1_4_2-solution000004.solution b/tests/exhaustive/basic/setOfSet04/expected/model_1_4_2-solution000004.solution new file mode 100644 index 0000000000..af16592c51 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_1_4_2-solution000004.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{1}, {2}} +$ Visualisation for x +$ 1 +$ 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_1_4_2-solution000005.solution b/tests/exhaustive/basic/setOfSet04/expected/model_1_4_2-solution000005.solution new file mode 100644 index 0000000000..3ec452354e --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_1_4_2-solution000005.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{}, {1}} +$ Visualisation for x +$ +$ 1 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_1_4_2-solution000006.solution b/tests/exhaustive/basic/setOfSet04/expected/model_1_4_2-solution000006.solution new file mode 100644 index 0000000000..c8946f3d06 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_1_4_2-solution000006.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{}, {2}} +$ Visualisation for x +$ +$ 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_1_4_3.eprime.orig b/tests/exhaustive/basic/setOfSet04/expected/model_1_4_2.eprime similarity index 50% rename from tests/exhaustive/basic/setOfSet04/expected/model_1_4_3.eprime.orig rename to tests/exhaustive/basic/setOfSet04/expected/model_1_4_2.eprime index 71a5adaa9b..cd957e819c 100644 --- a/tests/exhaustive/basic/setOfSet04/expected/model_1_4_3.eprime.orig +++ b/tests/exhaustive/basic/setOfSet04/expected/model_1_4_2.eprime @@ -3,11 +3,10 @@ language ESSENCE' 1.0 find x_ExplicitR2_Occurrence: matrix indexed by [int(1..2), int(1..2)] of bool find x_ExplicitR4_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..2), int(1..3)] of bool find x_ExplicitR4_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..2), int(1..3)] of int(1..2) -find x_ExplicitR5_ExplicitVarSizeWithMarker_Marker: matrix indexed by [int(1..2)] of int(0..3) -find x_ExplicitR5_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..2), int(1..3)] of int(1..2) +find x_ExplicitR6_ExplicitVarSizeWithDummy: matrix indexed by [int(1..2), int(1..3)] of int(1..3) branching on - [x_ExplicitR5_ExplicitVarSizeWithMarker_Marker, x_ExplicitR5_ExplicitVarSizeWithMarker_Values, - x_ExplicitR2_Occurrence, x_ExplicitR4_ExplicitVarSizeWithFlags_Flags, x_ExplicitR4_ExplicitVarSizeWithFlags_Values] + [x_ExplicitR6_ExplicitVarSizeWithDummy, x_ExplicitR2_Occurrence, x_ExplicitR4_ExplicitVarSizeWithFlags_Flags, + x_ExplicitR4_ExplicitVarSizeWithFlags_Values] such that [-toInt(x_ExplicitR2_Occurrence[1, q4]) | q4 : int(1..2)] - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q34, q35] < - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q34, q35 + 1] + [x_ExplicitR6_ExplicitVarSizeWithDummy[1, q39] | q39 : int(1..3)] x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q34] -> - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q34, q36] = 1 - | q36 : int(1..3)]) + and([and([x_ExplicitR6_ExplicitVarSizeWithDummy[q34, q36] = 3 -> + x_ExplicitR6_ExplicitVarSizeWithDummy[q34, q36 + 1] = 3 + | q36 : int(1..2)]) | q34 : int(1..2)]), - and([x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q34] <= 3 | q34 : int(1..2)]), - and([or([and([x_ExplicitR2_Occurrence[q43, q44] -> - or([q46 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q41] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q41, q46] = q44 - | q46 : int(1..3)]) - | q44 : int(1..2)]) + and([sum([toInt(x_ExplicitR6_ExplicitVarSizeWithDummy[q34, q37] != 3) | q37 : int(1..3)]) <= 3 | q34 : int(1..2)]), + and([or([and([x_ExplicitR2_Occurrence[q44, q45] -> + or([x_ExplicitR6_ExplicitVarSizeWithDummy[q42, q47] != 3 /\ + x_ExplicitR6_ExplicitVarSizeWithDummy[q42, q47] = q45 + | q47 : int(1..3)]) + | q45 : int(1..2)]) /\ - and([q48 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q41] -> - x_ExplicitR2_Occurrence[q43, x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q41, q48]] - | q48 : int(1..3)]) - | q43 : int(1..2)]) - | q41 : int(1..2)]), - and([or([and([q54 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q52] -> - x_ExplicitR2_Occurrence[q50, x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q52, q54]] - | q54 : int(1..3)]) + and([x_ExplicitR6_ExplicitVarSizeWithDummy[q42, q49] != 3 -> + x_ExplicitR2_Occurrence[q44, x_ExplicitR6_ExplicitVarSizeWithDummy[q42, q49]] + | q49 : int(1..3)]) + | q44 : int(1..2)]) + | q42 : int(1..2)]), + and([or([and([x_ExplicitR6_ExplicitVarSizeWithDummy[q53, q55] != 3 -> + x_ExplicitR2_Occurrence[q51, x_ExplicitR6_ExplicitVarSizeWithDummy[q53, q55]] + | q55 : int(1..3)]) /\ - and([x_ExplicitR2_Occurrence[q50, q55] -> - or([q57 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q52] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q52, q57] = q55 - | q57 : int(1..3)]) - | q55 : int(1..2)]) - | q52 : int(1..2)]) - | q50 : int(1..2)]), - and([or([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q61, q63] -> - or([q65 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q59] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q59, q65] = - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q61, q63] - | q65 : int(1..3)]) - | q63 : int(1..3)]) + and([x_ExplicitR2_Occurrence[q51, q56] -> + or([x_ExplicitR6_ExplicitVarSizeWithDummy[q53, q58] != 3 /\ + x_ExplicitR6_ExplicitVarSizeWithDummy[q53, q58] = q56 + | q58 : int(1..3)]) + | q56 : int(1..2)]) + | q53 : int(1..2)]) + | q51 : int(1..2)]), + and([or([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q62, q64] -> + or([x_ExplicitR6_ExplicitVarSizeWithDummy[q60, q66] != 3 /\ + x_ExplicitR6_ExplicitVarSizeWithDummy[q60, q66] = + x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q62, q64] + | q66 : int(1..3)]) + | q64 : int(1..3)]) /\ - and([q67 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q59] -> - or([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q61, q69] /\ - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q61, q69] = - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q59, q67] - | q69 : int(1..3)]) - | q67 : int(1..3)]) - | q61 : int(1..2)]) - | q59 : int(1..2)]), - and([or([and([q75 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q73] -> - or([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q71, q77] /\ - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q71, q77] = - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q73, q75] - | q77 : int(1..3)]) - | q75 : int(1..3)]) + and([x_ExplicitR6_ExplicitVarSizeWithDummy[q60, q68] != 3 -> + or([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q62, q70] /\ + x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q62, q70] = + x_ExplicitR6_ExplicitVarSizeWithDummy[q60, q68] + | q70 : int(1..3)]) + | q68 : int(1..3)]) + | q62 : int(1..2)]) + | q60 : int(1..2)]), + and([or([and([x_ExplicitR6_ExplicitVarSizeWithDummy[q74, q76] != 3 -> + or([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q72, q78] /\ + x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q72, q78] = + x_ExplicitR6_ExplicitVarSizeWithDummy[q74, q76] + | q78 : int(1..3)]) + | q76 : int(1..3)]) /\ - and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q71, q79] -> - or([q81 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q73] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q73, q81] = - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q71, q79] - | q81 : int(1..3)]) - | q79 : int(1..3)]) - | q73 : int(1..2)]) - | q71 : int(1..2)]) + and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q72, q80] -> + or([x_ExplicitR6_ExplicitVarSizeWithDummy[q74, q82] != 3 /\ + x_ExplicitR6_ExplicitVarSizeWithDummy[q74, q82] = + x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q72, q80] + | q82 : int(1..3)]) + | q80 : int(1..3)]) + | q74 : int(1..2)]) + | q72 : int(1..2)]) diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_1_4_3-solution000001.solution b/tests/exhaustive/basic/setOfSet04/expected/model_1_4_3-solution000001.solution new file mode 100644 index 0000000000..3ec452354e --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_1_4_3-solution000001.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{}, {1}} +$ Visualisation for x +$ +$ 1 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_1_4_3-solution000002.solution b/tests/exhaustive/basic/setOfSet04/expected/model_1_4_3-solution000002.solution new file mode 100644 index 0000000000..c8946f3d06 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_1_4_3-solution000002.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{}, {2}} +$ Visualisation for x +$ +$ 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_1_4_3-solution000003.solution b/tests/exhaustive/basic/setOfSet04/expected/model_1_4_3-solution000003.solution new file mode 100644 index 0000000000..a6c0b6a43e --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_1_4_3-solution000003.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{}, {1, 2}} +$ Visualisation for x +$ +$ 1 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_1_4_3-solution000004.solution b/tests/exhaustive/basic/setOfSet04/expected/model_1_4_3-solution000004.solution new file mode 100644 index 0000000000..af16592c51 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_1_4_3-solution000004.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{1}, {2}} +$ Visualisation for x +$ 1 +$ 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_1_4_3-solution000005.solution b/tests/exhaustive/basic/setOfSet04/expected/model_1_4_3-solution000005.solution new file mode 100644 index 0000000000..38937c9389 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_1_4_3-solution000005.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{1}, {1, 2}} +$ Visualisation for x +$ 1 +$ 1 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_1_4_3-solution000006.solution b/tests/exhaustive/basic/setOfSet04/expected/model_1_4_3-solution000006.solution new file mode 100644 index 0000000000..9bf2af0712 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_1_4_3-solution000006.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{1, 2}, {2}} +$ Visualisation for x +$ 1 2 +$ 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_2_1_1-solution000001.solution b/tests/exhaustive/basic/setOfSet04/expected/model_2_1_1-solution000001.solution new file mode 100644 index 0000000000..c8946f3d06 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_2_1_1-solution000001.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{}, {2}} +$ Visualisation for x +$ +$ 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_2_1_1-solution000002.solution b/tests/exhaustive/basic/setOfSet04/expected/model_2_1_1-solution000002.solution new file mode 100644 index 0000000000..3ec452354e --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_2_1_1-solution000002.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{}, {1}} +$ Visualisation for x +$ +$ 1 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_2_1_1-solution000003.solution b/tests/exhaustive/basic/setOfSet04/expected/model_2_1_1-solution000003.solution new file mode 100644 index 0000000000..af16592c51 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_2_1_1-solution000003.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{1}, {2}} +$ Visualisation for x +$ 1 +$ 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_2_1_1-solution000004.solution b/tests/exhaustive/basic/setOfSet04/expected/model_2_1_1-solution000004.solution new file mode 100644 index 0000000000..a6c0b6a43e --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_2_1_1-solution000004.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{}, {1, 2}} +$ Visualisation for x +$ +$ 1 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_2_1_1-solution000005.solution b/tests/exhaustive/basic/setOfSet04/expected/model_2_1_1-solution000005.solution new file mode 100644 index 0000000000..9bf2af0712 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_2_1_1-solution000005.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{1, 2}, {2}} +$ Visualisation for x +$ 1 2 +$ 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_2_1_1-solution000006.solution b/tests/exhaustive/basic/setOfSet04/expected/model_2_1_1-solution000006.solution new file mode 100644 index 0000000000..38937c9389 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_2_1_1-solution000006.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{1}, {1, 2}} +$ Visualisation for x +$ 1 +$ 1 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_2_1_1.eprime b/tests/exhaustive/basic/setOfSet04/expected/model_2_1_1.eprime new file mode 100644 index 0000000000..3b170dc84f --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_2_1_1.eprime @@ -0,0 +1,42 @@ +language ESSENCE' 1.0 + +find x_ExplicitR6_ExplicitVarSizeWithDummy: matrix indexed by [int(1..2), int(1..3)] of int(1..3) +find x_ExplicitR2_Occurrence: matrix indexed by [int(1..2), int(1..2)] of bool +branching on [x_ExplicitR2_Occurrence, x_ExplicitR6_ExplicitVarSizeWithDummy] +such that + [x_ExplicitR6_ExplicitVarSizeWithDummy[1, q7] | q7 : int(1..3)] x_ExplicitR6_ExplicitVarSizeWithDummy[q2, q4 + 1] = 3 + | q4 : int(1..2)]) + | q2 : int(1..2)]), + and([sum([toInt(x_ExplicitR6_ExplicitVarSizeWithDummy[q2, q5] != 3) | q5 : int(1..3)]) <= 3 | q2 : int(1..2)]), + [-toInt(x_ExplicitR2_Occurrence[1, q12]) | q12 : int(1..2)] + x_ExplicitR2_Occurrence[q15, x_ExplicitR6_ExplicitVarSizeWithDummy[q17, q19]] + | q19 : int(1..3)]) + /\ + and([x_ExplicitR2_Occurrence[q15, q20] -> + or([x_ExplicitR6_ExplicitVarSizeWithDummy[q17, q22] != 3 /\ + x_ExplicitR6_ExplicitVarSizeWithDummy[q17, q22] = q20 + | q22 : int(1..3)]) + | q20 : int(1..2)]) + | q17 : int(1..2)]) + | q15 : int(1..2)]), + and([or([and([x_ExplicitR2_Occurrence[q26, q27] -> + or([x_ExplicitR6_ExplicitVarSizeWithDummy[q24, q29] != 3 /\ + x_ExplicitR6_ExplicitVarSizeWithDummy[q24, q29] = q27 + | q29 : int(1..3)]) + | q27 : int(1..2)]) + /\ + and([x_ExplicitR6_ExplicitVarSizeWithDummy[q24, q31] != 3 -> + x_ExplicitR2_Occurrence[q26, x_ExplicitR6_ExplicitVarSizeWithDummy[q24, q31]] + | q31 : int(1..3)]) + | q26 : int(1..2)]) + | q24 : int(1..2)]) + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_2_1_3-solution000001.solution b/tests/exhaustive/basic/setOfSet04/expected/model_2_1_3-solution000001.solution new file mode 100644 index 0000000000..3ec452354e --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_2_1_3-solution000001.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{}, {1}} +$ Visualisation for x +$ +$ 1 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_2_1_3-solution000002.solution b/tests/exhaustive/basic/setOfSet04/expected/model_2_1_3-solution000002.solution new file mode 100644 index 0000000000..c8946f3d06 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_2_1_3-solution000002.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{}, {2}} +$ Visualisation for x +$ +$ 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_2_1_3-solution000003.solution b/tests/exhaustive/basic/setOfSet04/expected/model_2_1_3-solution000003.solution new file mode 100644 index 0000000000..a6c0b6a43e --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_2_1_3-solution000003.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{}, {1, 2}} +$ Visualisation for x +$ +$ 1 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_2_1_3-solution000004.solution b/tests/exhaustive/basic/setOfSet04/expected/model_2_1_3-solution000004.solution new file mode 100644 index 0000000000..af16592c51 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_2_1_3-solution000004.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{1}, {2}} +$ Visualisation for x +$ 1 +$ 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_2_1_3-solution000005.solution b/tests/exhaustive/basic/setOfSet04/expected/model_2_1_3-solution000005.solution new file mode 100644 index 0000000000..38937c9389 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_2_1_3-solution000005.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{1}, {1, 2}} +$ Visualisation for x +$ 1 +$ 1 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_2_1_3-solution000006.solution b/tests/exhaustive/basic/setOfSet04/expected/model_2_1_3-solution000006.solution new file mode 100644 index 0000000000..9bf2af0712 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_2_1_3-solution000006.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{1, 2}, {2}} +$ Visualisation for x +$ 1 2 +$ 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_2_1_3.eprime.orig b/tests/exhaustive/basic/setOfSet04/expected/model_2_1_3.eprime.orig deleted file mode 100644 index 3de66ab4d8..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_2_1_3.eprime.orig +++ /dev/null @@ -1,115 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitR6_ExplicitVarSizeWithDummy: matrix indexed by [int(1..2), int(1..3)] of int(1..3) -find x_ExplicitR2_Occurrence: matrix indexed by [int(1..2), int(1..2)] of bool -find x_ExplicitR5_ExplicitVarSizeWithMarker_Marker: matrix indexed by [int(1..2)] of int(0..3) -find x_ExplicitR5_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..2), int(1..3)] of int(1..2) -branching on - [x_ExplicitR5_ExplicitVarSizeWithMarker_Marker, x_ExplicitR5_ExplicitVarSizeWithMarker_Values, - x_ExplicitR6_ExplicitVarSizeWithDummy, x_ExplicitR2_Occurrence] -such that - [x_ExplicitR6_ExplicitVarSizeWithDummy[1, q7] | q7 : int(1..3)] x_ExplicitR6_ExplicitVarSizeWithDummy[q2, q4 + 1] = 3 - | q4 : int(1..2)]) - | q2 : int(1..2)]), - and([sum([toInt(x_ExplicitR6_ExplicitVarSizeWithDummy[q2, q5] != 3) | q5 : int(1..3)]) <= 3 | q2 : int(1..2)]), - [-toInt(x_ExplicitR2_Occurrence[1, q12]) | q12 : int(1..2)] - x_ExplicitR2_Occurrence[q15, x_ExplicitR6_ExplicitVarSizeWithDummy[q17, q19]] - | q19 : int(1..3)]) - /\ - and([x_ExplicitR2_Occurrence[q15, q20] -> - or([x_ExplicitR6_ExplicitVarSizeWithDummy[q17, q22] != 3 /\ - x_ExplicitR6_ExplicitVarSizeWithDummy[q17, q22] = q20 - | q22 : int(1..3)]) - | q20 : int(1..2)]) - | q17 : int(1..2)]) - | q15 : int(1..2)]), - and([or([and([x_ExplicitR2_Occurrence[q26, q27] -> - or([x_ExplicitR6_ExplicitVarSizeWithDummy[q24, q29] != 3 /\ - x_ExplicitR6_ExplicitVarSizeWithDummy[q24, q29] = q27 - | q29 : int(1..3)]) - | q27 : int(1..2)]) - /\ - and([x_ExplicitR6_ExplicitVarSizeWithDummy[q24, q31] != 3 -> - x_ExplicitR2_Occurrence[q26, x_ExplicitR6_ExplicitVarSizeWithDummy[q24, q31]] - | q31 : int(1..3)]) - | q26 : int(1..2)]) - | q24 : int(1..2)]), - flatten([[x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[1]; int(1)], - [x_ExplicitR5_ExplicitVarSizeWithMarker_Values[1, q37] | q37 : int(1..3)]; - int(1..2)]) - - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q33, q34] < - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q33, q34 + 1] - | q34 : int(1..2)]) - | q33 : int(1..2)]), - and([and([q35 > x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q33] -> - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q33, q35] = 1 - | q35 : int(1..3)]) - | q33 : int(1..2)]), - and([x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q33] <= 3 | q33 : int(1..2)]), - and([or([and([x_ExplicitR6_ExplicitVarSizeWithDummy[q42, q44] != 3 -> - or([q46 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q40] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q40, q46] = - x_ExplicitR6_ExplicitVarSizeWithDummy[q42, q44] - | q46 : int(1..3)]) - | q44 : int(1..3)]) - /\ - and([q48 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q40] -> - or([x_ExplicitR6_ExplicitVarSizeWithDummy[q42, q50] != 3 /\ - x_ExplicitR6_ExplicitVarSizeWithDummy[q42, q50] = - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q40, q48] - | q50 : int(1..3)]) - | q48 : int(1..3)]) - | q42 : int(1..2)]) - | q40 : int(1..2)]), - and([or([and([q56 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q54] -> - or([x_ExplicitR6_ExplicitVarSizeWithDummy[q52, q58] != 3 /\ - x_ExplicitR6_ExplicitVarSizeWithDummy[q52, q58] = - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q54, q56] - | q58 : int(1..3)]) - | q56 : int(1..3)]) - /\ - and([x_ExplicitR6_ExplicitVarSizeWithDummy[q52, q60] != 3 -> - or([q62 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q54] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q54, q62] = - x_ExplicitR6_ExplicitVarSizeWithDummy[q52, q60] - | q62 : int(1..3)]) - | q60 : int(1..3)]) - | q54 : int(1..2)]) - | q52 : int(1..2)]), - and([or([and([x_ExplicitR2_Occurrence[q66, q67] -> - or([q69 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q64] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q64, q69] = q67 - | q69 : int(1..3)]) - | q67 : int(1..2)]) - /\ - and([q71 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q64] -> - x_ExplicitR2_Occurrence[q66, x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q64, q71]] - | q71 : int(1..3)]) - | q66 : int(1..2)]) - | q64 : int(1..2)]), - and([or([and([q77 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q75] -> - x_ExplicitR2_Occurrence[q73, x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q75, q77]] - | q77 : int(1..3)]) - /\ - and([x_ExplicitR2_Occurrence[q73, q78] -> - or([q80 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q75] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q75, q80] = q78 - | q80 : int(1..3)]) - | q78 : int(1..2)]) - | q75 : int(1..2)]) - | q73 : int(1..2)]) - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_2_1_4-solution000001.solution b/tests/exhaustive/basic/setOfSet04/expected/model_2_1_4-solution000001.solution new file mode 100644 index 0000000000..3ec452354e --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_2_1_4-solution000001.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{}, {1}} +$ Visualisation for x +$ +$ 1 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_2_1_4-solution000002.solution b/tests/exhaustive/basic/setOfSet04/expected/model_2_1_4-solution000002.solution new file mode 100644 index 0000000000..c8946f3d06 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_2_1_4-solution000002.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{}, {2}} +$ Visualisation for x +$ +$ 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_2_1_4-solution000003.solution b/tests/exhaustive/basic/setOfSet04/expected/model_2_1_4-solution000003.solution new file mode 100644 index 0000000000..af16592c51 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_2_1_4-solution000003.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{1}, {2}} +$ Visualisation for x +$ 1 +$ 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_2_1_4-solution000004.solution b/tests/exhaustive/basic/setOfSet04/expected/model_2_1_4-solution000004.solution new file mode 100644 index 0000000000..a6c0b6a43e --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_2_1_4-solution000004.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{}, {1, 2}} +$ Visualisation for x +$ +$ 1 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_2_1_4-solution000005.solution b/tests/exhaustive/basic/setOfSet04/expected/model_2_1_4-solution000005.solution new file mode 100644 index 0000000000..38937c9389 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_2_1_4-solution000005.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{1}, {1, 2}} +$ Visualisation for x +$ 1 +$ 1 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_2_1_4-solution000006.solution b/tests/exhaustive/basic/setOfSet04/expected/model_2_1_4-solution000006.solution new file mode 100644 index 0000000000..9bf2af0712 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_2_1_4-solution000006.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{1, 2}, {2}} +$ Visualisation for x +$ 1 2 +$ 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_2_1_4.eprime b/tests/exhaustive/basic/setOfSet04/expected/model_2_1_4.eprime new file mode 100644 index 0000000000..169610bca6 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_2_1_4.eprime @@ -0,0 +1,121 @@ +language ESSENCE' 1.0 + +find x_ExplicitR6_ExplicitVarSizeWithDummy: matrix indexed by [int(1..2), int(1..3)] of int(1..3) +find x_ExplicitR2_Occurrence: matrix indexed by [int(1..2), int(1..2)] of bool +find x_ExplicitR4_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..2), int(1..3)] of bool +find x_ExplicitR4_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..2), int(1..3)] of int(1..2) +branching on + [x_ExplicitR4_ExplicitVarSizeWithFlags_Flags, x_ExplicitR4_ExplicitVarSizeWithFlags_Values, + x_ExplicitR6_ExplicitVarSizeWithDummy, x_ExplicitR2_Occurrence] +such that + [x_ExplicitR6_ExplicitVarSizeWithDummy[1, q7] | q7 : int(1..3)] x_ExplicitR6_ExplicitVarSizeWithDummy[q2, q4 + 1] = 3 + | q4 : int(1..2)]) + | q2 : int(1..2)]), + and([sum([toInt(x_ExplicitR6_ExplicitVarSizeWithDummy[q2, q5] != 3) | q5 : int(1..3)]) <= 3 | q2 : int(1..2)]), + [-toInt(x_ExplicitR2_Occurrence[1, q12]) | q12 : int(1..2)] + x_ExplicitR2_Occurrence[q15, x_ExplicitR6_ExplicitVarSizeWithDummy[q17, q19]] + | q19 : int(1..3)]) + /\ + and([x_ExplicitR2_Occurrence[q15, q20] -> + or([x_ExplicitR6_ExplicitVarSizeWithDummy[q17, q22] != 3 /\ + x_ExplicitR6_ExplicitVarSizeWithDummy[q17, q22] = q20 + | q22 : int(1..3)]) + | q20 : int(1..2)]) + | q17 : int(1..2)]) + | q15 : int(1..2)]), + and([or([and([x_ExplicitR2_Occurrence[q26, q27] -> + or([x_ExplicitR6_ExplicitVarSizeWithDummy[q24, q29] != 3 /\ + x_ExplicitR6_ExplicitVarSizeWithDummy[q24, q29] = q27 + | q29 : int(1..3)]) + | q27 : int(1..2)]) + /\ + and([x_ExplicitR6_ExplicitVarSizeWithDummy[q24, q31] != 3 -> + x_ExplicitR2_Occurrence[q26, x_ExplicitR6_ExplicitVarSizeWithDummy[q24, q31]] + | q31 : int(1..3)]) + | q26 : int(1..2)]) + | q24 : int(1..2)]), + flatten([flatten([[-toInt(x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[1, q39]); int(1)], + [x_ExplicitR4_ExplicitVarSizeWithFlags_Values[1, q39]; int(1)]; + int(1..2)]) + | q39 : int(1..3)]) + + x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q33, q34] < + x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q33, q34 + 1] + | q34 : int(1..2)]) + | q33 : int(1..2)]), + and([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q33, q35] = false -> + x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q33, q35] = 1 + | q35 : int(1..3)]) + | q33 : int(1..2)]), + and([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q33, q36 + 1] -> + x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q33, q36] + | q36 : int(1..2)]) + | q33 : int(1..2)]), + and([sum([toInt(x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q33, q37]) | q37 : int(1..3)]) <= 3 | q33 : int(1..2)]), + and([or([and([x_ExplicitR6_ExplicitVarSizeWithDummy[q44, q46] != 3 -> + or([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q42, q48] /\ + x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q42, q48] = + x_ExplicitR6_ExplicitVarSizeWithDummy[q44, q46] + | q48 : int(1..3)]) + | q46 : int(1..3)]) + /\ + and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q42, q50] -> + or([x_ExplicitR6_ExplicitVarSizeWithDummy[q44, q52] != 3 /\ + x_ExplicitR6_ExplicitVarSizeWithDummy[q44, q52] = + x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q42, q50] + | q52 : int(1..3)]) + | q50 : int(1..3)]) + | q44 : int(1..2)]) + | q42 : int(1..2)]), + and([or([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q56, q58] -> + or([x_ExplicitR6_ExplicitVarSizeWithDummy[q54, q60] != 3 /\ + x_ExplicitR6_ExplicitVarSizeWithDummy[q54, q60] = + x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q56, q58] + | q60 : int(1..3)]) + | q58 : int(1..3)]) + /\ + and([x_ExplicitR6_ExplicitVarSizeWithDummy[q54, q62] != 3 -> + or([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q56, q64] /\ + x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q56, q64] = + x_ExplicitR6_ExplicitVarSizeWithDummy[q54, q62] + | q64 : int(1..3)]) + | q62 : int(1..3)]) + | q56 : int(1..2)]) + | q54 : int(1..2)]), + and([or([and([x_ExplicitR2_Occurrence[q68, q69] -> + or([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q66, q71] /\ + x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q66, q71] = q69 + | q71 : int(1..3)]) + | q69 : int(1..2)]) + /\ + and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q66, q73] -> + x_ExplicitR2_Occurrence[q68, x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q66, q73]] + | q73 : int(1..3)]) + | q68 : int(1..2)]) + | q66 : int(1..2)]), + and([or([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q77, q79] -> + x_ExplicitR2_Occurrence[q75, x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q77, q79]] + | q79 : int(1..3)]) + /\ + and([x_ExplicitR2_Occurrence[q75, q80] -> + or([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q77, q82] /\ + x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q77, q82] = q80 + | q82 : int(1..3)]) + | q80 : int(1..2)]) + | q77 : int(1..2)]) + | q75 : int(1..2)]) + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_2_2_2-solution000001.solution b/tests/exhaustive/basic/setOfSet04/expected/model_2_2_2-solution000001.solution new file mode 100644 index 0000000000..38937c9389 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_2_2_2-solution000001.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{1}, {1, 2}} +$ Visualisation for x +$ 1 +$ 1 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_2_2_2-solution000002.solution b/tests/exhaustive/basic/setOfSet04/expected/model_2_2_2-solution000002.solution new file mode 100644 index 0000000000..9bf2af0712 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_2_2_2-solution000002.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{1, 2}, {2}} +$ Visualisation for x +$ 1 2 +$ 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_2_2_2-solution000003.solution b/tests/exhaustive/basic/setOfSet04/expected/model_2_2_2-solution000003.solution new file mode 100644 index 0000000000..a6c0b6a43e --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_2_2_2-solution000003.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{}, {1, 2}} +$ Visualisation for x +$ +$ 1 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_2_2_2-solution000004.solution b/tests/exhaustive/basic/setOfSet04/expected/model_2_2_2-solution000004.solution new file mode 100644 index 0000000000..af16592c51 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_2_2_2-solution000004.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{1}, {2}} +$ Visualisation for x +$ 1 +$ 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_2_2_2-solution000005.solution b/tests/exhaustive/basic/setOfSet04/expected/model_2_2_2-solution000005.solution new file mode 100644 index 0000000000..3ec452354e --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_2_2_2-solution000005.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{}, {1}} +$ Visualisation for x +$ +$ 1 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_2_2_2-solution000006.solution b/tests/exhaustive/basic/setOfSet04/expected/model_2_2_2-solution000006.solution new file mode 100644 index 0000000000..c8946f3d06 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_2_2_2-solution000006.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{}, {2}} +$ Visualisation for x +$ +$ 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_2_2_2.eprime b/tests/exhaustive/basic/setOfSet04/expected/model_2_2_2.eprime new file mode 100644 index 0000000000..82d1d04484 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_2_2_2.eprime @@ -0,0 +1,16 @@ +language ESSENCE' 1.0 + +find x_ExplicitR6_ExplicitVarSizeWithDummy: matrix indexed by [int(1..2), int(1..3)] of int(1..3) +branching on [x_ExplicitR6_ExplicitVarSizeWithDummy] +such that + [x_ExplicitR6_ExplicitVarSizeWithDummy[1, q7] | q7 : int(1..3)] x_ExplicitR6_ExplicitVarSizeWithDummy[q2, q4 + 1] = 3 + | q4 : int(1..2)]) + | q2 : int(1..2)]), + and([sum([toInt(x_ExplicitR6_ExplicitVarSizeWithDummy[q2, q5] != 3) | q5 : int(1..3)]) <= 3 | q2 : int(1..2)]) + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_2_2_3-solution000001.solution b/tests/exhaustive/basic/setOfSet04/expected/model_2_2_3-solution000001.solution new file mode 100644 index 0000000000..3ec452354e --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_2_2_3-solution000001.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{}, {1}} +$ Visualisation for x +$ +$ 1 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_2_2_3-solution000002.solution b/tests/exhaustive/basic/setOfSet04/expected/model_2_2_3-solution000002.solution new file mode 100644 index 0000000000..c8946f3d06 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_2_2_3-solution000002.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{}, {2}} +$ Visualisation for x +$ +$ 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_2_2_3-solution000003.solution b/tests/exhaustive/basic/setOfSet04/expected/model_2_2_3-solution000003.solution new file mode 100644 index 0000000000..a6c0b6a43e --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_2_2_3-solution000003.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{}, {1, 2}} +$ Visualisation for x +$ +$ 1 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_2_2_3-solution000004.solution b/tests/exhaustive/basic/setOfSet04/expected/model_2_2_3-solution000004.solution new file mode 100644 index 0000000000..af16592c51 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_2_2_3-solution000004.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{1}, {2}} +$ Visualisation for x +$ 1 +$ 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_2_2_3-solution000005.solution b/tests/exhaustive/basic/setOfSet04/expected/model_2_2_3-solution000005.solution new file mode 100644 index 0000000000..38937c9389 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_2_2_3-solution000005.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{1}, {1, 2}} +$ Visualisation for x +$ 1 +$ 1 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_2_2_3-solution000006.solution b/tests/exhaustive/basic/setOfSet04/expected/model_2_2_3-solution000006.solution new file mode 100644 index 0000000000..9bf2af0712 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_2_2_3-solution000006.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{1, 2}, {2}} +$ Visualisation for x +$ 1 2 +$ 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_2_2_3.eprime.orig b/tests/exhaustive/basic/setOfSet04/expected/model_2_2_3.eprime.orig deleted file mode 100644 index bdcbef4970..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_2_2_3.eprime.orig +++ /dev/null @@ -1,67 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitR6_ExplicitVarSizeWithDummy: matrix indexed by [int(1..2), int(1..3)] of int(1..3) -find x_ExplicitR5_ExplicitVarSizeWithMarker_Marker: matrix indexed by [int(1..2)] of int(0..3) -find x_ExplicitR5_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..2), int(1..3)] of int(1..2) -branching on - [x_ExplicitR5_ExplicitVarSizeWithMarker_Marker, x_ExplicitR5_ExplicitVarSizeWithMarker_Values, - x_ExplicitR6_ExplicitVarSizeWithDummy] -such that - [x_ExplicitR6_ExplicitVarSizeWithDummy[1, q7] | q7 : int(1..3)] x_ExplicitR6_ExplicitVarSizeWithDummy[q2, q4 + 1] = 3 - | q4 : int(1..2)]) - | q2 : int(1..2)]), - and([sum([toInt(x_ExplicitR6_ExplicitVarSizeWithDummy[q2, q5] != 3) | q5 : int(1..3)]) <= 3 | q2 : int(1..2)]), - flatten([[x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[1]; int(1)], - [x_ExplicitR5_ExplicitVarSizeWithMarker_Values[1, q14] | q14 : int(1..3)]; - int(1..2)]) - - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q10, q11] < - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q10, q11 + 1] - | q11 : int(1..2)]) - | q10 : int(1..2)]), - and([and([q12 > x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q10] -> - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q10, q12] = 1 - | q12 : int(1..3)]) - | q10 : int(1..2)]), - and([x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q10] <= 3 | q10 : int(1..2)]), - and([or([and([x_ExplicitR6_ExplicitVarSizeWithDummy[q19, q21] != 3 -> - or([q23 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q17] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q17, q23] = - x_ExplicitR6_ExplicitVarSizeWithDummy[q19, q21] - | q23 : int(1..3)]) - | q21 : int(1..3)]) - /\ - and([q25 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q17] -> - or([x_ExplicitR6_ExplicitVarSizeWithDummy[q19, q27] != 3 /\ - x_ExplicitR6_ExplicitVarSizeWithDummy[q19, q27] = - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q17, q25] - | q27 : int(1..3)]) - | q25 : int(1..3)]) - | q19 : int(1..2)]) - | q17 : int(1..2)]), - and([or([and([q33 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q31] -> - or([x_ExplicitR6_ExplicitVarSizeWithDummy[q29, q35] != 3 /\ - x_ExplicitR6_ExplicitVarSizeWithDummy[q29, q35] = - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q31, q33] - | q35 : int(1..3)]) - | q33 : int(1..3)]) - /\ - and([x_ExplicitR6_ExplicitVarSizeWithDummy[q29, q37] != 3 -> - or([q39 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q31] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q31, q39] = - x_ExplicitR6_ExplicitVarSizeWithDummy[q29, q37] - | q39 : int(1..3)]) - | q37 : int(1..3)]) - | q31 : int(1..2)]) - | q29 : int(1..2)]) - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_2_2_4-solution000001.solution b/tests/exhaustive/basic/setOfSet04/expected/model_2_2_4-solution000001.solution new file mode 100644 index 0000000000..3ec452354e --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_2_2_4-solution000001.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{}, {1}} +$ Visualisation for x +$ +$ 1 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_2_2_4-solution000002.solution b/tests/exhaustive/basic/setOfSet04/expected/model_2_2_4-solution000002.solution new file mode 100644 index 0000000000..c8946f3d06 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_2_2_4-solution000002.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{}, {2}} +$ Visualisation for x +$ +$ 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_2_2_4-solution000003.solution b/tests/exhaustive/basic/setOfSet04/expected/model_2_2_4-solution000003.solution new file mode 100644 index 0000000000..af16592c51 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_2_2_4-solution000003.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{1}, {2}} +$ Visualisation for x +$ 1 +$ 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_2_2_4-solution000004.solution b/tests/exhaustive/basic/setOfSet04/expected/model_2_2_4-solution000004.solution new file mode 100644 index 0000000000..a6c0b6a43e --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_2_2_4-solution000004.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{}, {1, 2}} +$ Visualisation for x +$ +$ 1 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_2_2_4-solution000005.solution b/tests/exhaustive/basic/setOfSet04/expected/model_2_2_4-solution000005.solution new file mode 100644 index 0000000000..38937c9389 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_2_2_4-solution000005.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{1}, {1, 2}} +$ Visualisation for x +$ 1 +$ 1 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_2_2_4-solution000006.solution b/tests/exhaustive/basic/setOfSet04/expected/model_2_2_4-solution000006.solution new file mode 100644 index 0000000000..9bf2af0712 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_2_2_4-solution000006.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{1, 2}, {2}} +$ Visualisation for x +$ 1 2 +$ 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_2_2_4.eprime b/tests/exhaustive/basic/setOfSet04/expected/model_2_2_4.eprime new file mode 100644 index 0000000000..247428fb21 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_2_2_4.eprime @@ -0,0 +1,73 @@ +language ESSENCE' 1.0 + +find x_ExplicitR6_ExplicitVarSizeWithDummy: matrix indexed by [int(1..2), int(1..3)] of int(1..3) +find x_ExplicitR4_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..2), int(1..3)] of bool +find x_ExplicitR4_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..2), int(1..3)] of int(1..2) +branching on + [x_ExplicitR4_ExplicitVarSizeWithFlags_Flags, x_ExplicitR4_ExplicitVarSizeWithFlags_Values, + x_ExplicitR6_ExplicitVarSizeWithDummy] +such that + [x_ExplicitR6_ExplicitVarSizeWithDummy[1, q7] | q7 : int(1..3)] x_ExplicitR6_ExplicitVarSizeWithDummy[q2, q4 + 1] = 3 + | q4 : int(1..2)]) + | q2 : int(1..2)]), + and([sum([toInt(x_ExplicitR6_ExplicitVarSizeWithDummy[q2, q5] != 3) | q5 : int(1..3)]) <= 3 | q2 : int(1..2)]), + flatten([flatten([[-toInt(x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[1, q16]); int(1)], + [x_ExplicitR4_ExplicitVarSizeWithFlags_Values[1, q16]; int(1)]; + int(1..2)]) + | q16 : int(1..3)]) + + x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q10, q11] < + x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q10, q11 + 1] + | q11 : int(1..2)]) + | q10 : int(1..2)]), + and([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q10, q12] = false -> + x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q10, q12] = 1 + | q12 : int(1..3)]) + | q10 : int(1..2)]), + and([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q10, q13 + 1] -> + x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q10, q13] + | q13 : int(1..2)]) + | q10 : int(1..2)]), + and([sum([toInt(x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q10, q14]) | q14 : int(1..3)]) <= 3 | q10 : int(1..2)]), + and([or([and([x_ExplicitR6_ExplicitVarSizeWithDummy[q21, q23] != 3 -> + or([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q19, q25] /\ + x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q19, q25] = + x_ExplicitR6_ExplicitVarSizeWithDummy[q21, q23] + | q25 : int(1..3)]) + | q23 : int(1..3)]) + /\ + and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q19, q27] -> + or([x_ExplicitR6_ExplicitVarSizeWithDummy[q21, q29] != 3 /\ + x_ExplicitR6_ExplicitVarSizeWithDummy[q21, q29] = + x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q19, q27] + | q29 : int(1..3)]) + | q27 : int(1..3)]) + | q21 : int(1..2)]) + | q19 : int(1..2)]), + and([or([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q33, q35] -> + or([x_ExplicitR6_ExplicitVarSizeWithDummy[q31, q37] != 3 /\ + x_ExplicitR6_ExplicitVarSizeWithDummy[q31, q37] = + x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q33, q35] + | q37 : int(1..3)]) + | q35 : int(1..3)]) + /\ + and([x_ExplicitR6_ExplicitVarSizeWithDummy[q31, q39] != 3 -> + or([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q33, q41] /\ + x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q33, q41] = + x_ExplicitR6_ExplicitVarSizeWithDummy[q31, q39] + | q41 : int(1..3)]) + | q39 : int(1..3)]) + | q33 : int(1..2)]) + | q31 : int(1..2)]) + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_2_3_1-solution000001.solution b/tests/exhaustive/basic/setOfSet04/expected/model_2_3_1-solution000001.solution new file mode 100644 index 0000000000..c8946f3d06 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_2_3_1-solution000001.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{}, {2}} +$ Visualisation for x +$ +$ 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_2_3_1-solution000002.solution b/tests/exhaustive/basic/setOfSet04/expected/model_2_3_1-solution000002.solution new file mode 100644 index 0000000000..3ec452354e --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_2_3_1-solution000002.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{}, {1}} +$ Visualisation for x +$ +$ 1 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_2_3_1-solution000003.solution b/tests/exhaustive/basic/setOfSet04/expected/model_2_3_1-solution000003.solution new file mode 100644 index 0000000000..af16592c51 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_2_3_1-solution000003.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{1}, {2}} +$ Visualisation for x +$ 1 +$ 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_2_3_1-solution000004.solution b/tests/exhaustive/basic/setOfSet04/expected/model_2_3_1-solution000004.solution new file mode 100644 index 0000000000..a6c0b6a43e --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_2_3_1-solution000004.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{}, {1, 2}} +$ Visualisation for x +$ +$ 1 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_2_3_1-solution000005.solution b/tests/exhaustive/basic/setOfSet04/expected/model_2_3_1-solution000005.solution new file mode 100644 index 0000000000..9bf2af0712 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_2_3_1-solution000005.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{1, 2}, {2}} +$ Visualisation for x +$ 1 2 +$ 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_2_3_1-solution000006.solution b/tests/exhaustive/basic/setOfSet04/expected/model_2_3_1-solution000006.solution new file mode 100644 index 0000000000..38937c9389 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_2_3_1-solution000006.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{1}, {1, 2}} +$ Visualisation for x +$ 1 +$ 1 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_2_3_1.eprime.orig b/tests/exhaustive/basic/setOfSet04/expected/model_2_3_1.eprime.orig deleted file mode 100644 index e268def585..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_2_3_1.eprime.orig +++ /dev/null @@ -1,115 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitR6_ExplicitVarSizeWithDummy: matrix indexed by [int(1..2), int(1..3)] of int(1..3) -find x_ExplicitR5_ExplicitVarSizeWithMarker_Marker: matrix indexed by [int(1..2)] of int(0..3) -find x_ExplicitR5_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..2), int(1..3)] of int(1..2) -find x_ExplicitR2_Occurrence: matrix indexed by [int(1..2), int(1..2)] of bool -branching on - [x_ExplicitR2_Occurrence, x_ExplicitR6_ExplicitVarSizeWithDummy, x_ExplicitR5_ExplicitVarSizeWithMarker_Marker, - x_ExplicitR5_ExplicitVarSizeWithMarker_Values] -such that - [x_ExplicitR6_ExplicitVarSizeWithDummy[1, q7] | q7 : int(1..3)] x_ExplicitR6_ExplicitVarSizeWithDummy[q2, q4 + 1] = 3 - | q4 : int(1..2)]) - | q2 : int(1..2)]), - and([sum([toInt(x_ExplicitR6_ExplicitVarSizeWithDummy[q2, q5] != 3) | q5 : int(1..3)]) <= 3 | q2 : int(1..2)]), - flatten([[x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[1]; int(1)], - [x_ExplicitR5_ExplicitVarSizeWithMarker_Values[1, q14] | q14 : int(1..3)]; - int(1..2)]) - - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q10, q11] < - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q10, q11 + 1] - | q11 : int(1..2)]) - | q10 : int(1..2)]), - and([and([q12 > x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q10] -> - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q10, q12] = 1 - | q12 : int(1..3)]) - | q10 : int(1..2)]), - and([x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q10] <= 3 | q10 : int(1..2)]), - and([or([and([x_ExplicitR6_ExplicitVarSizeWithDummy[q19, q21] != 3 -> - or([q23 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q17] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q17, q23] = - x_ExplicitR6_ExplicitVarSizeWithDummy[q19, q21] - | q23 : int(1..3)]) - | q21 : int(1..3)]) - /\ - and([q25 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q17] -> - or([x_ExplicitR6_ExplicitVarSizeWithDummy[q19, q27] != 3 /\ - x_ExplicitR6_ExplicitVarSizeWithDummy[q19, q27] = - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q17, q25] - | q27 : int(1..3)]) - | q25 : int(1..3)]) - | q19 : int(1..2)]) - | q17 : int(1..2)]), - and([or([and([q33 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q31] -> - or([x_ExplicitR6_ExplicitVarSizeWithDummy[q29, q35] != 3 /\ - x_ExplicitR6_ExplicitVarSizeWithDummy[q29, q35] = - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q31, q33] - | q35 : int(1..3)]) - | q33 : int(1..3)]) - /\ - and([x_ExplicitR6_ExplicitVarSizeWithDummy[q29, q37] != 3 -> - or([q39 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q31] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q31, q39] = - x_ExplicitR6_ExplicitVarSizeWithDummy[q29, q37] - | q39 : int(1..3)]) - | q37 : int(1..3)]) - | q31 : int(1..2)]) - | q29 : int(1..2)]), - [-toInt(x_ExplicitR2_Occurrence[1, q43]) | q43 : int(1..2)] - x_ExplicitR2_Occurrence[q46, x_ExplicitR6_ExplicitVarSizeWithDummy[q48, q50]] - | q50 : int(1..3)]) - /\ - and([x_ExplicitR2_Occurrence[q46, q51] -> - or([x_ExplicitR6_ExplicitVarSizeWithDummy[q48, q53] != 3 /\ - x_ExplicitR6_ExplicitVarSizeWithDummy[q48, q53] = q51 - | q53 : int(1..3)]) - | q51 : int(1..2)]) - | q48 : int(1..2)]) - | q46 : int(1..2)]), - and([or([and([x_ExplicitR2_Occurrence[q57, q58] -> - or([x_ExplicitR6_ExplicitVarSizeWithDummy[q55, q60] != 3 /\ - x_ExplicitR6_ExplicitVarSizeWithDummy[q55, q60] = q58 - | q60 : int(1..3)]) - | q58 : int(1..2)]) - /\ - and([x_ExplicitR6_ExplicitVarSizeWithDummy[q55, q62] != 3 -> - x_ExplicitR2_Occurrence[q57, x_ExplicitR6_ExplicitVarSizeWithDummy[q55, q62]] - | q62 : int(1..3)]) - | q57 : int(1..2)]) - | q55 : int(1..2)]), - and([or([and([q68 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q66] -> - x_ExplicitR2_Occurrence[q64, x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q66, q68]] - | q68 : int(1..3)]) - /\ - and([x_ExplicitR2_Occurrence[q64, q69] -> - or([q71 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q66] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q66, q71] = q69 - | q71 : int(1..3)]) - | q69 : int(1..2)]) - | q66 : int(1..2)]) - | q64 : int(1..2)]), - and([or([and([x_ExplicitR2_Occurrence[q75, q76] -> - or([q78 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q73] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q73, q78] = q76 - | q78 : int(1..3)]) - | q76 : int(1..2)]) - /\ - and([q80 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q73] -> - x_ExplicitR2_Occurrence[q75, x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q73, q80]] - | q80 : int(1..3)]) - | q75 : int(1..2)]) - | q73 : int(1..2)]) - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_2_3_2.eprime.orig b/tests/exhaustive/basic/setOfSet04/expected/model_2_3_2.eprime.orig deleted file mode 100644 index bdcbef4970..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_2_3_2.eprime.orig +++ /dev/null @@ -1,67 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitR6_ExplicitVarSizeWithDummy: matrix indexed by [int(1..2), int(1..3)] of int(1..3) -find x_ExplicitR5_ExplicitVarSizeWithMarker_Marker: matrix indexed by [int(1..2)] of int(0..3) -find x_ExplicitR5_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..2), int(1..3)] of int(1..2) -branching on - [x_ExplicitR5_ExplicitVarSizeWithMarker_Marker, x_ExplicitR5_ExplicitVarSizeWithMarker_Values, - x_ExplicitR6_ExplicitVarSizeWithDummy] -such that - [x_ExplicitR6_ExplicitVarSizeWithDummy[1, q7] | q7 : int(1..3)] x_ExplicitR6_ExplicitVarSizeWithDummy[q2, q4 + 1] = 3 - | q4 : int(1..2)]) - | q2 : int(1..2)]), - and([sum([toInt(x_ExplicitR6_ExplicitVarSizeWithDummy[q2, q5] != 3) | q5 : int(1..3)]) <= 3 | q2 : int(1..2)]), - flatten([[x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[1]; int(1)], - [x_ExplicitR5_ExplicitVarSizeWithMarker_Values[1, q14] | q14 : int(1..3)]; - int(1..2)]) - - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q10, q11] < - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q10, q11 + 1] - | q11 : int(1..2)]) - | q10 : int(1..2)]), - and([and([q12 > x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q10] -> - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q10, q12] = 1 - | q12 : int(1..3)]) - | q10 : int(1..2)]), - and([x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q10] <= 3 | q10 : int(1..2)]), - and([or([and([x_ExplicitR6_ExplicitVarSizeWithDummy[q19, q21] != 3 -> - or([q23 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q17] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q17, q23] = - x_ExplicitR6_ExplicitVarSizeWithDummy[q19, q21] - | q23 : int(1..3)]) - | q21 : int(1..3)]) - /\ - and([q25 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q17] -> - or([x_ExplicitR6_ExplicitVarSizeWithDummy[q19, q27] != 3 /\ - x_ExplicitR6_ExplicitVarSizeWithDummy[q19, q27] = - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q17, q25] - | q27 : int(1..3)]) - | q25 : int(1..3)]) - | q19 : int(1..2)]) - | q17 : int(1..2)]), - and([or([and([q33 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q31] -> - or([x_ExplicitR6_ExplicitVarSizeWithDummy[q29, q35] != 3 /\ - x_ExplicitR6_ExplicitVarSizeWithDummy[q29, q35] = - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q31, q33] - | q35 : int(1..3)]) - | q33 : int(1..3)]) - /\ - and([x_ExplicitR6_ExplicitVarSizeWithDummy[q29, q37] != 3 -> - or([q39 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q31] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q31, q39] = - x_ExplicitR6_ExplicitVarSizeWithDummy[q29, q37] - | q39 : int(1..3)]) - | q37 : int(1..3)]) - | q31 : int(1..2)]) - | q29 : int(1..2)]) - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_2_3_3.eprime.orig b/tests/exhaustive/basic/setOfSet04/expected/model_2_3_3.eprime.orig deleted file mode 100644 index bdcbef4970..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_2_3_3.eprime.orig +++ /dev/null @@ -1,67 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitR6_ExplicitVarSizeWithDummy: matrix indexed by [int(1..2), int(1..3)] of int(1..3) -find x_ExplicitR5_ExplicitVarSizeWithMarker_Marker: matrix indexed by [int(1..2)] of int(0..3) -find x_ExplicitR5_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..2), int(1..3)] of int(1..2) -branching on - [x_ExplicitR5_ExplicitVarSizeWithMarker_Marker, x_ExplicitR5_ExplicitVarSizeWithMarker_Values, - x_ExplicitR6_ExplicitVarSizeWithDummy] -such that - [x_ExplicitR6_ExplicitVarSizeWithDummy[1, q7] | q7 : int(1..3)] x_ExplicitR6_ExplicitVarSizeWithDummy[q2, q4 + 1] = 3 - | q4 : int(1..2)]) - | q2 : int(1..2)]), - and([sum([toInt(x_ExplicitR6_ExplicitVarSizeWithDummy[q2, q5] != 3) | q5 : int(1..3)]) <= 3 | q2 : int(1..2)]), - flatten([[x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[1]; int(1)], - [x_ExplicitR5_ExplicitVarSizeWithMarker_Values[1, q14] | q14 : int(1..3)]; - int(1..2)]) - - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q10, q11] < - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q10, q11 + 1] - | q11 : int(1..2)]) - | q10 : int(1..2)]), - and([and([q12 > x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q10] -> - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q10, q12] = 1 - | q12 : int(1..3)]) - | q10 : int(1..2)]), - and([x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q10] <= 3 | q10 : int(1..2)]), - and([or([and([x_ExplicitR6_ExplicitVarSizeWithDummy[q19, q21] != 3 -> - or([q23 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q17] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q17, q23] = - x_ExplicitR6_ExplicitVarSizeWithDummy[q19, q21] - | q23 : int(1..3)]) - | q21 : int(1..3)]) - /\ - and([q25 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q17] -> - or([x_ExplicitR6_ExplicitVarSizeWithDummy[q19, q27] != 3 /\ - x_ExplicitR6_ExplicitVarSizeWithDummy[q19, q27] = - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q17, q25] - | q27 : int(1..3)]) - | q25 : int(1..3)]) - | q19 : int(1..2)]) - | q17 : int(1..2)]), - and([or([and([q33 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q31] -> - or([x_ExplicitR6_ExplicitVarSizeWithDummy[q29, q35] != 3 /\ - x_ExplicitR6_ExplicitVarSizeWithDummy[q29, q35] = - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q31, q33] - | q35 : int(1..3)]) - | q33 : int(1..3)]) - /\ - and([x_ExplicitR6_ExplicitVarSizeWithDummy[q29, q37] != 3 -> - or([q39 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q31] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q31, q39] = - x_ExplicitR6_ExplicitVarSizeWithDummy[q29, q37] - | q39 : int(1..3)]) - | q37 : int(1..3)]) - | q31 : int(1..2)]) - | q29 : int(1..2)]) - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_2_3_4-solution000001.solution b/tests/exhaustive/basic/setOfSet04/expected/model_2_3_4-solution000001.solution new file mode 100644 index 0000000000..3ec452354e --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_2_3_4-solution000001.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{}, {1}} +$ Visualisation for x +$ +$ 1 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_2_3_4-solution000002.solution b/tests/exhaustive/basic/setOfSet04/expected/model_2_3_4-solution000002.solution new file mode 100644 index 0000000000..c8946f3d06 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_2_3_4-solution000002.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{}, {2}} +$ Visualisation for x +$ +$ 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_2_3_4-solution000003.solution b/tests/exhaustive/basic/setOfSet04/expected/model_2_3_4-solution000003.solution new file mode 100644 index 0000000000..af16592c51 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_2_3_4-solution000003.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{1}, {2}} +$ Visualisation for x +$ 1 +$ 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_2_3_4-solution000004.solution b/tests/exhaustive/basic/setOfSet04/expected/model_2_3_4-solution000004.solution new file mode 100644 index 0000000000..a6c0b6a43e --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_2_3_4-solution000004.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{}, {1, 2}} +$ Visualisation for x +$ +$ 1 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_2_3_4-solution000005.solution b/tests/exhaustive/basic/setOfSet04/expected/model_2_3_4-solution000005.solution new file mode 100644 index 0000000000..38937c9389 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_2_3_4-solution000005.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{1}, {1, 2}} +$ Visualisation for x +$ 1 +$ 1 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_2_3_4-solution000006.solution b/tests/exhaustive/basic/setOfSet04/expected/model_2_3_4-solution000006.solution new file mode 100644 index 0000000000..9bf2af0712 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_2_3_4-solution000006.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{1, 2}, {2}} +$ Visualisation for x +$ 1 2 +$ 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_2_3_4.eprime.orig b/tests/exhaustive/basic/setOfSet04/expected/model_2_3_4.eprime.orig deleted file mode 100644 index cfc3d08942..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_2_3_4.eprime.orig +++ /dev/null @@ -1,153 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitR6_ExplicitVarSizeWithDummy: matrix indexed by [int(1..2), int(1..3)] of int(1..3) -find x_ExplicitR5_ExplicitVarSizeWithMarker_Marker: matrix indexed by [int(1..2)] of int(0..3) -find x_ExplicitR5_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..2), int(1..3)] of int(1..2) -find x_ExplicitR4_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..2), int(1..3)] of bool -find x_ExplicitR4_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..2), int(1..3)] of int(1..2) -branching on - [x_ExplicitR4_ExplicitVarSizeWithFlags_Flags, x_ExplicitR4_ExplicitVarSizeWithFlags_Values, - x_ExplicitR6_ExplicitVarSizeWithDummy, x_ExplicitR5_ExplicitVarSizeWithMarker_Marker, - x_ExplicitR5_ExplicitVarSizeWithMarker_Values] -such that - [x_ExplicitR6_ExplicitVarSizeWithDummy[1, q7] | q7 : int(1..3)] x_ExplicitR6_ExplicitVarSizeWithDummy[q2, q4 + 1] = 3 - | q4 : int(1..2)]) - | q2 : int(1..2)]), - and([sum([toInt(x_ExplicitR6_ExplicitVarSizeWithDummy[q2, q5] != 3) | q5 : int(1..3)]) <= 3 | q2 : int(1..2)]), - flatten([[x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[1]; int(1)], - [x_ExplicitR5_ExplicitVarSizeWithMarker_Values[1, q14] | q14 : int(1..3)]; - int(1..2)]) - - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q10, q11] < - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q10, q11 + 1] - | q11 : int(1..2)]) - | q10 : int(1..2)]), - and([and([q12 > x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q10] -> - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q10, q12] = 1 - | q12 : int(1..3)]) - | q10 : int(1..2)]), - and([x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q10] <= 3 | q10 : int(1..2)]), - and([or([and([x_ExplicitR6_ExplicitVarSizeWithDummy[q19, q21] != 3 -> - or([q23 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q17] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q17, q23] = - x_ExplicitR6_ExplicitVarSizeWithDummy[q19, q21] - | q23 : int(1..3)]) - | q21 : int(1..3)]) - /\ - and([q25 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q17] -> - or([x_ExplicitR6_ExplicitVarSizeWithDummy[q19, q27] != 3 /\ - x_ExplicitR6_ExplicitVarSizeWithDummy[q19, q27] = - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q17, q25] - | q27 : int(1..3)]) - | q25 : int(1..3)]) - | q19 : int(1..2)]) - | q17 : int(1..2)]), - and([or([and([q33 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q31] -> - or([x_ExplicitR6_ExplicitVarSizeWithDummy[q29, q35] != 3 /\ - x_ExplicitR6_ExplicitVarSizeWithDummy[q29, q35] = - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q31, q33] - | q35 : int(1..3)]) - | q33 : int(1..3)]) - /\ - and([x_ExplicitR6_ExplicitVarSizeWithDummy[q29, q37] != 3 -> - or([q39 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q31] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q31, q39] = - x_ExplicitR6_ExplicitVarSizeWithDummy[q29, q37] - | q39 : int(1..3)]) - | q37 : int(1..3)]) - | q31 : int(1..2)]) - | q29 : int(1..2)]), - flatten([flatten([[-toInt(x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[1, q47]); int(1)], - [x_ExplicitR4_ExplicitVarSizeWithFlags_Values[1, q47]; int(1)]; - int(1..2)]) - | q47 : int(1..3)]) - - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q41, q42] < - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q41, q42 + 1] - | q42 : int(1..2)]) - | q41 : int(1..2)]), - and([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q41, q43] = false -> - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q41, q43] = 1 - | q43 : int(1..3)]) - | q41 : int(1..2)]), - and([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q41, q44 + 1] -> - x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q41, q44] - | q44 : int(1..2)]) - | q41 : int(1..2)]), - and([sum([toInt(x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q41, q45]) | q45 : int(1..3)]) <= 3 | q41 : int(1..2)]), - and([or([and([x_ExplicitR6_ExplicitVarSizeWithDummy[q52, q54] != 3 -> - or([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q50, q56] /\ - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q50, q56] = - x_ExplicitR6_ExplicitVarSizeWithDummy[q52, q54] - | q56 : int(1..3)]) - | q54 : int(1..3)]) - /\ - and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q50, q58] -> - or([x_ExplicitR6_ExplicitVarSizeWithDummy[q52, q60] != 3 /\ - x_ExplicitR6_ExplicitVarSizeWithDummy[q52, q60] = - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q50, q58] - | q60 : int(1..3)]) - | q58 : int(1..3)]) - | q52 : int(1..2)]) - | q50 : int(1..2)]), - and([or([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q64, q66] -> - or([x_ExplicitR6_ExplicitVarSizeWithDummy[q62, q68] != 3 /\ - x_ExplicitR6_ExplicitVarSizeWithDummy[q62, q68] = - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q64, q66] - | q68 : int(1..3)]) - | q66 : int(1..3)]) - /\ - and([x_ExplicitR6_ExplicitVarSizeWithDummy[q62, q70] != 3 -> - or([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q64, q72] /\ - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q64, q72] = - x_ExplicitR6_ExplicitVarSizeWithDummy[q62, q70] - | q72 : int(1..3)]) - | q70 : int(1..3)]) - | q64 : int(1..2)]) - | q62 : int(1..2)]), - and([or([and([q78 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q76] -> - or([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q74, q80] /\ - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q74, q80] = - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q76, q78] - | q80 : int(1..3)]) - | q78 : int(1..3)]) - /\ - and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q74, q82] -> - or([q84 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q76] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q76, q84] = - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q74, q82] - | q84 : int(1..3)]) - | q82 : int(1..3)]) - | q76 : int(1..2)]) - | q74 : int(1..2)]), - and([or([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q88, q90] -> - or([q92 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q86] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q86, q92] = - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q88, q90] - | q92 : int(1..3)]) - | q90 : int(1..3)]) - /\ - and([q94 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q86] -> - or([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q88, q96] /\ - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q88, q96] = - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q86, q94] - | q96 : int(1..3)]) - | q94 : int(1..3)]) - | q88 : int(1..2)]) - | q86 : int(1..2)]) - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_2_4_1-solution000001.solution b/tests/exhaustive/basic/setOfSet04/expected/model_2_4_1-solution000001.solution new file mode 100644 index 0000000000..c8946f3d06 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_2_4_1-solution000001.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{}, {2}} +$ Visualisation for x +$ +$ 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_2_4_1-solution000002.solution b/tests/exhaustive/basic/setOfSet04/expected/model_2_4_1-solution000002.solution new file mode 100644 index 0000000000..3ec452354e --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_2_4_1-solution000002.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{}, {1}} +$ Visualisation for x +$ +$ 1 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_2_4_1-solution000003.solution b/tests/exhaustive/basic/setOfSet04/expected/model_2_4_1-solution000003.solution new file mode 100644 index 0000000000..af16592c51 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_2_4_1-solution000003.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{1}, {2}} +$ Visualisation for x +$ 1 +$ 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_2_4_1-solution000004.solution b/tests/exhaustive/basic/setOfSet04/expected/model_2_4_1-solution000004.solution new file mode 100644 index 0000000000..a6c0b6a43e --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_2_4_1-solution000004.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{}, {1, 2}} +$ Visualisation for x +$ +$ 1 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_2_4_1-solution000005.solution b/tests/exhaustive/basic/setOfSet04/expected/model_2_4_1-solution000005.solution new file mode 100644 index 0000000000..9bf2af0712 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_2_4_1-solution000005.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{1, 2}, {2}} +$ Visualisation for x +$ 1 2 +$ 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_2_4_1-solution000006.solution b/tests/exhaustive/basic/setOfSet04/expected/model_2_4_1-solution000006.solution new file mode 100644 index 0000000000..38937c9389 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_2_4_1-solution000006.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{1}, {1, 2}} +$ Visualisation for x +$ 1 +$ 1 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_2_4_3.eprime.orig b/tests/exhaustive/basic/setOfSet04/expected/model_2_4_1.eprime similarity index 51% rename from tests/exhaustive/basic/setOfSet04/expected/model_2_4_3.eprime.orig rename to tests/exhaustive/basic/setOfSet04/expected/model_2_4_1.eprime index 08a9116fab..ed505c7c7d 100644 --- a/tests/exhaustive/basic/setOfSet04/expected/model_2_4_3.eprime.orig +++ b/tests/exhaustive/basic/setOfSet04/expected/model_2_4_1.eprime @@ -3,11 +3,9 @@ language ESSENCE' 1.0 find x_ExplicitR6_ExplicitVarSizeWithDummy: matrix indexed by [int(1..2), int(1..3)] of int(1..3) find x_ExplicitR4_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..2), int(1..3)] of bool find x_ExplicitR4_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..2), int(1..3)] of int(1..2) -find x_ExplicitR5_ExplicitVarSizeWithMarker_Marker: matrix indexed by [int(1..2)] of int(0..3) -find x_ExplicitR5_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..2), int(1..3)] of int(1..2) +find x_ExplicitR2_Occurrence: matrix indexed by [int(1..2), int(1..2)] of bool branching on - [x_ExplicitR5_ExplicitVarSizeWithMarker_Marker, x_ExplicitR5_ExplicitVarSizeWithMarker_Values, - x_ExplicitR6_ExplicitVarSizeWithDummy, x_ExplicitR4_ExplicitVarSizeWithFlags_Flags, + [x_ExplicitR2_Occurrence, x_ExplicitR6_ExplicitVarSizeWithDummy, x_ExplicitR4_ExplicitVarSizeWithFlags_Flags, x_ExplicitR4_ExplicitVarSizeWithFlags_Values] such that [x_ExplicitR6_ExplicitVarSizeWithDummy[1, q7] | q7 : int(1..3)] - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q43, q44] < - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q43, q44 + 1] - | q44 : int(1..2)]) - | q43 : int(1..2)]), - and([and([q45 > x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q43] -> - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q43, q45] = 1 - | q45 : int(1..3)]) - | q43 : int(1..2)]), - and([x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q43] <= 3 | q43 : int(1..2)]), - and([or([and([x_ExplicitR6_ExplicitVarSizeWithDummy[q52, q54] != 3 -> - or([q56 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q50] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q50, q56] = - x_ExplicitR6_ExplicitVarSizeWithDummy[q52, q54] - | q56 : int(1..3)]) - | q54 : int(1..3)]) + [-toInt(x_ExplicitR2_Occurrence[1, q45]) | q45 : int(1..2)] + x_ExplicitR2_Occurrence[q48, x_ExplicitR6_ExplicitVarSizeWithDummy[q50, q52]] + | q52 : int(1..3)]) /\ - and([q58 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q50] -> - or([x_ExplicitR6_ExplicitVarSizeWithDummy[q52, q60] != 3 /\ - x_ExplicitR6_ExplicitVarSizeWithDummy[q52, q60] = - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q50, q58] - | q60 : int(1..3)]) - | q58 : int(1..3)]) - | q52 : int(1..2)]) - | q50 : int(1..2)]), - and([or([and([q66 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q64] -> - or([x_ExplicitR6_ExplicitVarSizeWithDummy[q62, q68] != 3 /\ - x_ExplicitR6_ExplicitVarSizeWithDummy[q62, q68] = - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q64, q66] - | q68 : int(1..3)]) - | q66 : int(1..3)]) + and([x_ExplicitR2_Occurrence[q48, q53] -> + or([x_ExplicitR6_ExplicitVarSizeWithDummy[q50, q55] != 3 /\ + x_ExplicitR6_ExplicitVarSizeWithDummy[q50, q55] = q53 + | q55 : int(1..3)]) + | q53 : int(1..2)]) + | q50 : int(1..2)]) + | q48 : int(1..2)]), + and([or([and([x_ExplicitR2_Occurrence[q59, q60] -> + or([x_ExplicitR6_ExplicitVarSizeWithDummy[q57, q62] != 3 /\ + x_ExplicitR6_ExplicitVarSizeWithDummy[q57, q62] = q60 + | q62 : int(1..3)]) + | q60 : int(1..2)]) /\ - and([x_ExplicitR6_ExplicitVarSizeWithDummy[q62, q70] != 3 -> - or([q72 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q64] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q64, q72] = - x_ExplicitR6_ExplicitVarSizeWithDummy[q62, q70] - | q72 : int(1..3)]) + and([x_ExplicitR6_ExplicitVarSizeWithDummy[q57, q64] != 3 -> + x_ExplicitR2_Occurrence[q59, x_ExplicitR6_ExplicitVarSizeWithDummy[q57, q64]] + | q64 : int(1..3)]) + | q59 : int(1..2)]) + | q57 : int(1..2)]), + and([or([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q68, q70] -> + x_ExplicitR2_Occurrence[q66, x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q68, q70]] | q70 : int(1..3)]) - | q64 : int(1..2)]) - | q62 : int(1..2)]), - and([or([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q76, q78] -> - or([q80 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q74] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q74, q80] = - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q76, q78] + /\ + and([x_ExplicitR2_Occurrence[q66, q71] -> + or([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q68, q73] /\ + x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q68, q73] = q71 + | q73 : int(1..3)]) + | q71 : int(1..2)]) + | q68 : int(1..2)]) + | q66 : int(1..2)]), + and([or([and([x_ExplicitR2_Occurrence[q77, q78] -> + or([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q75, q80] /\ + x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q75, q80] = q78 | q80 : int(1..3)]) - | q78 : int(1..3)]) + | q78 : int(1..2)]) /\ - and([q82 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q74] -> - or([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q76, q84] /\ - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q76, q84] = - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q74, q82] - | q84 : int(1..3)]) + and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q75, q82] -> + x_ExplicitR2_Occurrence[q77, x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q75, q82]] | q82 : int(1..3)]) - | q76 : int(1..2)]) - | q74 : int(1..2)]), - and([or([and([q90 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q88] -> - or([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q86, q92] /\ - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q86, q92] = - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q88, q90] - | q92 : int(1..3)]) - | q90 : int(1..3)]) - /\ - and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q86, q94] -> - or([q96 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q88] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q88, q96] = - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q86, q94] - | q96 : int(1..3)]) - | q94 : int(1..3)]) - | q88 : int(1..2)]) - | q86 : int(1..2)]) + | q77 : int(1..2)]) + | q75 : int(1..2)]) diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_2_4_3-solution000001.solution b/tests/exhaustive/basic/setOfSet04/expected/model_2_4_3-solution000001.solution new file mode 100644 index 0000000000..3ec452354e --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_2_4_3-solution000001.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{}, {1}} +$ Visualisation for x +$ +$ 1 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_2_4_3-solution000002.solution b/tests/exhaustive/basic/setOfSet04/expected/model_2_4_3-solution000002.solution new file mode 100644 index 0000000000..c8946f3d06 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_2_4_3-solution000002.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{}, {2}} +$ Visualisation for x +$ +$ 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_2_4_3-solution000003.solution b/tests/exhaustive/basic/setOfSet04/expected/model_2_4_3-solution000003.solution new file mode 100644 index 0000000000..a6c0b6a43e --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_2_4_3-solution000003.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{}, {1, 2}} +$ Visualisation for x +$ +$ 1 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_2_4_3-solution000004.solution b/tests/exhaustive/basic/setOfSet04/expected/model_2_4_3-solution000004.solution new file mode 100644 index 0000000000..af16592c51 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_2_4_3-solution000004.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{1}, {2}} +$ Visualisation for x +$ 1 +$ 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_2_4_3-solution000005.solution b/tests/exhaustive/basic/setOfSet04/expected/model_2_4_3-solution000005.solution new file mode 100644 index 0000000000..38937c9389 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_2_4_3-solution000005.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{1}, {1, 2}} +$ Visualisation for x +$ 1 +$ 1 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_2_4_3-solution000006.solution b/tests/exhaustive/basic/setOfSet04/expected/model_2_4_3-solution000006.solution new file mode 100644 index 0000000000..9bf2af0712 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_2_4_3-solution000006.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{1, 2}, {2}} +$ Visualisation for x +$ 1 2 +$ 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_3_1_1-solution000001.solution b/tests/exhaustive/basic/setOfSet04/expected/model_3_1_1-solution000001.solution new file mode 100644 index 0000000000..c8946f3d06 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_3_1_1-solution000001.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{}, {2}} +$ Visualisation for x +$ +$ 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_3_1_1-solution000002.solution b/tests/exhaustive/basic/setOfSet04/expected/model_3_1_1-solution000002.solution new file mode 100644 index 0000000000..3ec452354e --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_3_1_1-solution000002.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{}, {1}} +$ Visualisation for x +$ +$ 1 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_3_1_1-solution000003.solution b/tests/exhaustive/basic/setOfSet04/expected/model_3_1_1-solution000003.solution new file mode 100644 index 0000000000..af16592c51 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_3_1_1-solution000003.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{1}, {2}} +$ Visualisation for x +$ 1 +$ 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_3_1_1-solution000004.solution b/tests/exhaustive/basic/setOfSet04/expected/model_3_1_1-solution000004.solution new file mode 100644 index 0000000000..a6c0b6a43e --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_3_1_1-solution000004.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{}, {1, 2}} +$ Visualisation for x +$ +$ 1 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_3_1_1-solution000005.solution b/tests/exhaustive/basic/setOfSet04/expected/model_3_1_1-solution000005.solution new file mode 100644 index 0000000000..9bf2af0712 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_3_1_1-solution000005.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{1, 2}, {2}} +$ Visualisation for x +$ 1 2 +$ 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_3_1_1-solution000006.solution b/tests/exhaustive/basic/setOfSet04/expected/model_3_1_1-solution000006.solution new file mode 100644 index 0000000000..38937c9389 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_3_1_1-solution000006.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{1}, {1, 2}} +$ Visualisation for x +$ 1 +$ 1 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_3_1_1.eprime.orig b/tests/exhaustive/basic/setOfSet04/expected/model_3_1_1.eprime.orig deleted file mode 100644 index 7d1e4bb4cf..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_3_1_1.eprime.orig +++ /dev/null @@ -1,52 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitR5_ExplicitVarSizeWithMarker_Marker: matrix indexed by [int(1..2)] of int(0..3) -find x_ExplicitR5_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..2), int(1..3)] of int(1..2) -find x_ExplicitR2_Occurrence: matrix indexed by [int(1..2), int(1..2)] of bool -branching on - [x_ExplicitR2_Occurrence, x_ExplicitR5_ExplicitVarSizeWithMarker_Marker, - x_ExplicitR5_ExplicitVarSizeWithMarker_Values] -such that - flatten([[x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[1]; int(1)], - [x_ExplicitR5_ExplicitVarSizeWithMarker_Values[1, q6] | q6 : int(1..3)]; - int(1..2)]) - - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q2, q3] < - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q2, q3 + 1] - | q3 : int(1..2)]) - | q2 : int(1..2)]), - and([and([q4 > x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q2] -> - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q2, q4] = 1 - | q4 : int(1..3)]) - | q2 : int(1..2)]), - and([x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q2] <= 3 | q2 : int(1..2)]), - [-toInt(x_ExplicitR2_Occurrence[1, q11]) | q11 : int(1..2)] - x_ExplicitR2_Occurrence[q14, x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q16, q18]] - | q18 : int(1..3)]) - /\ - and([x_ExplicitR2_Occurrence[q14, q19] -> - or([q21 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q16] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q16, q21] = q19 - | q21 : int(1..3)]) - | q19 : int(1..2)]) - | q16 : int(1..2)]) - | q14 : int(1..2)]), - and([or([and([x_ExplicitR2_Occurrence[q25, q26] -> - or([q28 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q23] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q23, q28] = q26 - | q28 : int(1..3)]) - | q26 : int(1..2)]) - /\ - and([q30 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q23] -> - x_ExplicitR2_Occurrence[q25, x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q23, q30]] - | q30 : int(1..3)]) - | q25 : int(1..2)]) - | q23 : int(1..2)]) - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_3_1_2-solution000001.solution b/tests/exhaustive/basic/setOfSet04/expected/model_3_1_2-solution000001.solution new file mode 100644 index 0000000000..38937c9389 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_3_1_2-solution000001.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{1}, {1, 2}} +$ Visualisation for x +$ 1 +$ 1 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_3_1_2-solution000002.solution b/tests/exhaustive/basic/setOfSet04/expected/model_3_1_2-solution000002.solution new file mode 100644 index 0000000000..9bf2af0712 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_3_1_2-solution000002.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{1, 2}, {2}} +$ Visualisation for x +$ 1 2 +$ 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_3_1_2-solution000003.solution b/tests/exhaustive/basic/setOfSet04/expected/model_3_1_2-solution000003.solution new file mode 100644 index 0000000000..a6c0b6a43e --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_3_1_2-solution000003.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{}, {1, 2}} +$ Visualisation for x +$ +$ 1 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_3_1_2-solution000004.solution b/tests/exhaustive/basic/setOfSet04/expected/model_3_1_2-solution000004.solution new file mode 100644 index 0000000000..af16592c51 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_3_1_2-solution000004.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{1}, {2}} +$ Visualisation for x +$ 1 +$ 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_3_1_2-solution000005.solution b/tests/exhaustive/basic/setOfSet04/expected/model_3_1_2-solution000005.solution new file mode 100644 index 0000000000..3ec452354e --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_3_1_2-solution000005.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{}, {1}} +$ Visualisation for x +$ +$ 1 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_3_1_2-solution000006.solution b/tests/exhaustive/basic/setOfSet04/expected/model_3_1_2-solution000006.solution new file mode 100644 index 0000000000..c8946f3d06 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_3_1_2-solution000006.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{}, {2}} +$ Visualisation for x +$ +$ 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_3_1_2.eprime.orig b/tests/exhaustive/basic/setOfSet04/expected/model_3_1_2.eprime.orig deleted file mode 100644 index 9dc0033744..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_3_1_2.eprime.orig +++ /dev/null @@ -1,116 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitR5_ExplicitVarSizeWithMarker_Marker: matrix indexed by [int(1..2)] of int(0..3) -find x_ExplicitR5_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..2), int(1..3)] of int(1..2) -find x_ExplicitR2_Occurrence: matrix indexed by [int(1..2), int(1..2)] of bool -find x_ExplicitR6_ExplicitVarSizeWithDummy: matrix indexed by [int(1..2), int(1..3)] of int(1..3) -branching on - [x_ExplicitR6_ExplicitVarSizeWithDummy, x_ExplicitR5_ExplicitVarSizeWithMarker_Marker, - x_ExplicitR5_ExplicitVarSizeWithMarker_Values, x_ExplicitR2_Occurrence] -such that - flatten([[x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[1]; int(1)], - [x_ExplicitR5_ExplicitVarSizeWithMarker_Values[1, q6] | q6 : int(1..3)]; - int(1..2)]) - - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q2, q3] < - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q2, q3 + 1] - | q3 : int(1..2)]) - | q2 : int(1..2)]), - and([and([q4 > x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q2] -> - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q2, q4] = 1 - | q4 : int(1..3)]) - | q2 : int(1..2)]), - and([x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q2] <= 3 | q2 : int(1..2)]), - [-toInt(x_ExplicitR2_Occurrence[1, q11]) | q11 : int(1..2)] - x_ExplicitR2_Occurrence[q14, x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q16, q18]] - | q18 : int(1..3)]) - /\ - and([x_ExplicitR2_Occurrence[q14, q19] -> - or([q21 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q16] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q16, q21] = q19 - | q21 : int(1..3)]) - | q19 : int(1..2)]) - | q16 : int(1..2)]) - | q14 : int(1..2)]), - and([or([and([x_ExplicitR2_Occurrence[q25, q26] -> - or([q28 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q23] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q23, q28] = q26 - | q28 : int(1..3)]) - | q26 : int(1..2)]) - /\ - and([q30 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q23] -> - x_ExplicitR2_Occurrence[q25, x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q23, q30]] - | q30 : int(1..3)]) - | q25 : int(1..2)]) - | q23 : int(1..2)]), - [x_ExplicitR6_ExplicitVarSizeWithDummy[1, q37] | q37 : int(1..3)] - x_ExplicitR6_ExplicitVarSizeWithDummy[q32, q34 + 1] = 3 - | q34 : int(1..2)]) - | q32 : int(1..2)]), - and([sum([toInt(x_ExplicitR6_ExplicitVarSizeWithDummy[q32, q35] != 3) | q35 : int(1..3)]) <= 3 | q32 : int(1..2)]), - and([or([and([q44 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q42] -> - or([x_ExplicitR6_ExplicitVarSizeWithDummy[q40, q46] != 3 /\ - x_ExplicitR6_ExplicitVarSizeWithDummy[q40, q46] = - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q42, q44] - | q46 : int(1..3)]) - | q44 : int(1..3)]) - /\ - and([x_ExplicitR6_ExplicitVarSizeWithDummy[q40, q48] != 3 -> - or([q50 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q42] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q42, q50] = - x_ExplicitR6_ExplicitVarSizeWithDummy[q40, q48] - | q50 : int(1..3)]) - | q48 : int(1..3)]) - | q42 : int(1..2)]) - | q40 : int(1..2)]), - and([or([and([x_ExplicitR6_ExplicitVarSizeWithDummy[q54, q56] != 3 -> - or([q58 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q52] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q52, q58] = - x_ExplicitR6_ExplicitVarSizeWithDummy[q54, q56] - | q58 : int(1..3)]) - | q56 : int(1..3)]) - /\ - and([q60 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q52] -> - or([x_ExplicitR6_ExplicitVarSizeWithDummy[q54, q62] != 3 /\ - x_ExplicitR6_ExplicitVarSizeWithDummy[q54, q62] = - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q52, q60] - | q62 : int(1..3)]) - | q60 : int(1..3)]) - | q54 : int(1..2)]) - | q52 : int(1..2)]), - and([or([and([x_ExplicitR2_Occurrence[q66, q67] -> - or([x_ExplicitR6_ExplicitVarSizeWithDummy[q64, q69] != 3 /\ - x_ExplicitR6_ExplicitVarSizeWithDummy[q64, q69] = q67 - | q69 : int(1..3)]) - | q67 : int(1..2)]) - /\ - and([x_ExplicitR6_ExplicitVarSizeWithDummy[q64, q71] != 3 -> - x_ExplicitR2_Occurrence[q66, x_ExplicitR6_ExplicitVarSizeWithDummy[q64, q71]] - | q71 : int(1..3)]) - | q66 : int(1..2)]) - | q64 : int(1..2)]), - and([or([and([x_ExplicitR6_ExplicitVarSizeWithDummy[q75, q77] != 3 -> - x_ExplicitR2_Occurrence[q73, x_ExplicitR6_ExplicitVarSizeWithDummy[q75, q77]] - | q77 : int(1..3)]) - /\ - and([x_ExplicitR2_Occurrence[q73, q78] -> - or([x_ExplicitR6_ExplicitVarSizeWithDummy[q75, q80] != 3 /\ - x_ExplicitR6_ExplicitVarSizeWithDummy[q75, q80] = q78 - | q80 : int(1..3)]) - | q78 : int(1..2)]) - | q75 : int(1..2)]) - | q73 : int(1..2)]) - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_3_1_3.eprime.orig b/tests/exhaustive/basic/setOfSet04/expected/model_3_1_3.eprime.orig deleted file mode 100644 index 7d1e4bb4cf..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_3_1_3.eprime.orig +++ /dev/null @@ -1,52 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitR5_ExplicitVarSizeWithMarker_Marker: matrix indexed by [int(1..2)] of int(0..3) -find x_ExplicitR5_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..2), int(1..3)] of int(1..2) -find x_ExplicitR2_Occurrence: matrix indexed by [int(1..2), int(1..2)] of bool -branching on - [x_ExplicitR2_Occurrence, x_ExplicitR5_ExplicitVarSizeWithMarker_Marker, - x_ExplicitR5_ExplicitVarSizeWithMarker_Values] -such that - flatten([[x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[1]; int(1)], - [x_ExplicitR5_ExplicitVarSizeWithMarker_Values[1, q6] | q6 : int(1..3)]; - int(1..2)]) - - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q2, q3] < - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q2, q3 + 1] - | q3 : int(1..2)]) - | q2 : int(1..2)]), - and([and([q4 > x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q2] -> - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q2, q4] = 1 - | q4 : int(1..3)]) - | q2 : int(1..2)]), - and([x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q2] <= 3 | q2 : int(1..2)]), - [-toInt(x_ExplicitR2_Occurrence[1, q11]) | q11 : int(1..2)] - x_ExplicitR2_Occurrence[q14, x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q16, q18]] - | q18 : int(1..3)]) - /\ - and([x_ExplicitR2_Occurrence[q14, q19] -> - or([q21 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q16] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q16, q21] = q19 - | q21 : int(1..3)]) - | q19 : int(1..2)]) - | q16 : int(1..2)]) - | q14 : int(1..2)]), - and([or([and([x_ExplicitR2_Occurrence[q25, q26] -> - or([q28 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q23] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q23, q28] = q26 - | q28 : int(1..3)]) - | q26 : int(1..2)]) - /\ - and([q30 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q23] -> - x_ExplicitR2_Occurrence[q25, x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q23, q30]] - | q30 : int(1..3)]) - | q25 : int(1..2)]) - | q23 : int(1..2)]) - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_3_1_4-solution000001.solution b/tests/exhaustive/basic/setOfSet04/expected/model_3_1_4-solution000001.solution new file mode 100644 index 0000000000..3ec452354e --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_3_1_4-solution000001.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{}, {1}} +$ Visualisation for x +$ +$ 1 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_3_1_4-solution000002.solution b/tests/exhaustive/basic/setOfSet04/expected/model_3_1_4-solution000002.solution new file mode 100644 index 0000000000..c8946f3d06 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_3_1_4-solution000002.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{}, {2}} +$ Visualisation for x +$ +$ 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_3_1_4-solution000003.solution b/tests/exhaustive/basic/setOfSet04/expected/model_3_1_4-solution000003.solution new file mode 100644 index 0000000000..af16592c51 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_3_1_4-solution000003.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{1}, {2}} +$ Visualisation for x +$ 1 +$ 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_3_1_4-solution000004.solution b/tests/exhaustive/basic/setOfSet04/expected/model_3_1_4-solution000004.solution new file mode 100644 index 0000000000..a6c0b6a43e --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_3_1_4-solution000004.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{}, {1, 2}} +$ Visualisation for x +$ +$ 1 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_3_1_4-solution000005.solution b/tests/exhaustive/basic/setOfSet04/expected/model_3_1_4-solution000005.solution new file mode 100644 index 0000000000..38937c9389 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_3_1_4-solution000005.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{1}, {1, 2}} +$ Visualisation for x +$ 1 +$ 1 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_3_1_4-solution000006.solution b/tests/exhaustive/basic/setOfSet04/expected/model_3_1_4-solution000006.solution new file mode 100644 index 0000000000..9bf2af0712 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_3_1_4-solution000006.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{1, 2}, {2}} +$ Visualisation for x +$ 1 2 +$ 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_3_1_4.eprime.orig b/tests/exhaustive/basic/setOfSet04/expected/model_3_1_4.eprime.orig deleted file mode 100644 index 54c36877e9..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_3_1_4.eprime.orig +++ /dev/null @@ -1,130 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitR5_ExplicitVarSizeWithMarker_Marker: matrix indexed by [int(1..2)] of int(0..3) -find x_ExplicitR5_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..2), int(1..3)] of int(1..2) -find x_ExplicitR2_Occurrence: matrix indexed by [int(1..2), int(1..2)] of bool -find x_ExplicitR4_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..2), int(1..3)] of bool -find x_ExplicitR4_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..2), int(1..3)] of int(1..2) -branching on - [x_ExplicitR4_ExplicitVarSizeWithFlags_Flags, x_ExplicitR4_ExplicitVarSizeWithFlags_Values, - x_ExplicitR5_ExplicitVarSizeWithMarker_Marker, x_ExplicitR5_ExplicitVarSizeWithMarker_Values, - x_ExplicitR2_Occurrence] -such that - flatten([[x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[1]; int(1)], - [x_ExplicitR5_ExplicitVarSizeWithMarker_Values[1, q6] | q6 : int(1..3)]; - int(1..2)]) - - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q2, q3] < - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q2, q3 + 1] - | q3 : int(1..2)]) - | q2 : int(1..2)]), - and([and([q4 > x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q2] -> - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q2, q4] = 1 - | q4 : int(1..3)]) - | q2 : int(1..2)]), - and([x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q2] <= 3 | q2 : int(1..2)]), - [-toInt(x_ExplicitR2_Occurrence[1, q11]) | q11 : int(1..2)] - x_ExplicitR2_Occurrence[q14, x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q16, q18]] - | q18 : int(1..3)]) - /\ - and([x_ExplicitR2_Occurrence[q14, q19] -> - or([q21 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q16] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q16, q21] = q19 - | q21 : int(1..3)]) - | q19 : int(1..2)]) - | q16 : int(1..2)]) - | q14 : int(1..2)]), - and([or([and([x_ExplicitR2_Occurrence[q25, q26] -> - or([q28 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q23] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q23, q28] = q26 - | q28 : int(1..3)]) - | q26 : int(1..2)]) - /\ - and([q30 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q23] -> - x_ExplicitR2_Occurrence[q25, x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q23, q30]] - | q30 : int(1..3)]) - | q25 : int(1..2)]) - | q23 : int(1..2)]), - flatten([flatten([[-toInt(x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[1, q38]); int(1)], - [x_ExplicitR4_ExplicitVarSizeWithFlags_Values[1, q38]; int(1)]; - int(1..2)]) - | q38 : int(1..3)]) - - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q32, q33] < - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q32, q33 + 1] - | q33 : int(1..2)]) - | q32 : int(1..2)]), - and([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q32, q34] = false -> - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q32, q34] = 1 - | q34 : int(1..3)]) - | q32 : int(1..2)]), - and([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q32, q35 + 1] -> - x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q32, q35] - | q35 : int(1..2)]) - | q32 : int(1..2)]), - and([sum([toInt(x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q32, q36]) | q36 : int(1..3)]) <= 3 | q32 : int(1..2)]), - and([or([and([q45 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q43] -> - or([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q41, q47] /\ - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q41, q47] = - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q43, q45] - | q47 : int(1..3)]) - | q45 : int(1..3)]) - /\ - and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q41, q49] -> - or([q51 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q43] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q43, q51] = - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q41, q49] - | q51 : int(1..3)]) - | q49 : int(1..3)]) - | q43 : int(1..2)]) - | q41 : int(1..2)]), - and([or([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q55, q57] -> - or([q59 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q53] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q53, q59] = - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q55, q57] - | q59 : int(1..3)]) - | q57 : int(1..3)]) - /\ - and([q61 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q53] -> - or([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q55, q63] /\ - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q55, q63] = - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q53, q61] - | q63 : int(1..3)]) - | q61 : int(1..3)]) - | q55 : int(1..2)]) - | q53 : int(1..2)]), - and([or([and([x_ExplicitR2_Occurrence[q67, q68] -> - or([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q65, q70] /\ - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q65, q70] = q68 - | q70 : int(1..3)]) - | q68 : int(1..2)]) - /\ - and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q65, q72] -> - x_ExplicitR2_Occurrence[q67, x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q65, q72]] - | q72 : int(1..3)]) - | q67 : int(1..2)]) - | q65 : int(1..2)]), - and([or([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q76, q78] -> - x_ExplicitR2_Occurrence[q74, x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q76, q78]] - | q78 : int(1..3)]) - /\ - and([x_ExplicitR2_Occurrence[q74, q79] -> - or([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q76, q81] /\ - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q76, q81] = q79 - | q81 : int(1..3)]) - | q79 : int(1..2)]) - | q76 : int(1..2)]) - | q74 : int(1..2)]) - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_3_2_1-solution000001.solution b/tests/exhaustive/basic/setOfSet04/expected/model_3_2_1-solution000001.solution new file mode 100644 index 0000000000..c8946f3d06 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_3_2_1-solution000001.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{}, {2}} +$ Visualisation for x +$ +$ 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_3_2_1-solution000002.solution b/tests/exhaustive/basic/setOfSet04/expected/model_3_2_1-solution000002.solution new file mode 100644 index 0000000000..3ec452354e --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_3_2_1-solution000002.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{}, {1}} +$ Visualisation for x +$ +$ 1 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_3_2_1-solution000003.solution b/tests/exhaustive/basic/setOfSet04/expected/model_3_2_1-solution000003.solution new file mode 100644 index 0000000000..af16592c51 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_3_2_1-solution000003.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{1}, {2}} +$ Visualisation for x +$ 1 +$ 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_3_2_1-solution000004.solution b/tests/exhaustive/basic/setOfSet04/expected/model_3_2_1-solution000004.solution new file mode 100644 index 0000000000..a6c0b6a43e --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_3_2_1-solution000004.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{}, {1, 2}} +$ Visualisation for x +$ +$ 1 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_3_2_1-solution000005.solution b/tests/exhaustive/basic/setOfSet04/expected/model_3_2_1-solution000005.solution new file mode 100644 index 0000000000..9bf2af0712 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_3_2_1-solution000005.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{1, 2}, {2}} +$ Visualisation for x +$ 1 2 +$ 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_3_2_1-solution000006.solution b/tests/exhaustive/basic/setOfSet04/expected/model_3_2_1-solution000006.solution new file mode 100644 index 0000000000..38937c9389 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_3_2_1-solution000006.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{1}, {1, 2}} +$ Visualisation for x +$ 1 +$ 1 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_3_2_1.eprime.orig b/tests/exhaustive/basic/setOfSet04/expected/model_3_2_1.eprime.orig deleted file mode 100644 index c66f4a4fb0..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_3_2_1.eprime.orig +++ /dev/null @@ -1,116 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitR5_ExplicitVarSizeWithMarker_Marker: matrix indexed by [int(1..2)] of int(0..3) -find x_ExplicitR5_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..2), int(1..3)] of int(1..2) -find x_ExplicitR6_ExplicitVarSizeWithDummy: matrix indexed by [int(1..2), int(1..3)] of int(1..3) -find x_ExplicitR2_Occurrence: matrix indexed by [int(1..2), int(1..2)] of bool -branching on - [x_ExplicitR2_Occurrence, x_ExplicitR5_ExplicitVarSizeWithMarker_Marker, - x_ExplicitR5_ExplicitVarSizeWithMarker_Values, x_ExplicitR6_ExplicitVarSizeWithDummy] -such that - flatten([[x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[1]; int(1)], - [x_ExplicitR5_ExplicitVarSizeWithMarker_Values[1, q6] | q6 : int(1..3)]; - int(1..2)]) - - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q2, q3] < - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q2, q3 + 1] - | q3 : int(1..2)]) - | q2 : int(1..2)]), - and([and([q4 > x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q2] -> - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q2, q4] = 1 - | q4 : int(1..3)]) - | q2 : int(1..2)]), - and([x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q2] <= 3 | q2 : int(1..2)]), - [x_ExplicitR6_ExplicitVarSizeWithDummy[1, q14] | q14 : int(1..3)] - x_ExplicitR6_ExplicitVarSizeWithDummy[q9, q11 + 1] = 3 - | q11 : int(1..2)]) - | q9 : int(1..2)]), - and([sum([toInt(x_ExplicitR6_ExplicitVarSizeWithDummy[q9, q12] != 3) | q12 : int(1..3)]) <= 3 | q9 : int(1..2)]), - and([or([and([q21 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q19] -> - or([x_ExplicitR6_ExplicitVarSizeWithDummy[q17, q23] != 3 /\ - x_ExplicitR6_ExplicitVarSizeWithDummy[q17, q23] = - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q19, q21] - | q23 : int(1..3)]) - | q21 : int(1..3)]) - /\ - and([x_ExplicitR6_ExplicitVarSizeWithDummy[q17, q25] != 3 -> - or([q27 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q19] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q19, q27] = - x_ExplicitR6_ExplicitVarSizeWithDummy[q17, q25] - | q27 : int(1..3)]) - | q25 : int(1..3)]) - | q19 : int(1..2)]) - | q17 : int(1..2)]), - and([or([and([x_ExplicitR6_ExplicitVarSizeWithDummy[q31, q33] != 3 -> - or([q35 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q29] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q29, q35] = - x_ExplicitR6_ExplicitVarSizeWithDummy[q31, q33] - | q35 : int(1..3)]) - | q33 : int(1..3)]) - /\ - and([q37 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q29] -> - or([x_ExplicitR6_ExplicitVarSizeWithDummy[q31, q39] != 3 /\ - x_ExplicitR6_ExplicitVarSizeWithDummy[q31, q39] = - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q29, q37] - | q39 : int(1..3)]) - | q37 : int(1..3)]) - | q31 : int(1..2)]) - | q29 : int(1..2)]), - [-toInt(x_ExplicitR2_Occurrence[1, q43]) | q43 : int(1..2)] - x_ExplicitR2_Occurrence[q46, x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q48, q50]] - | q50 : int(1..3)]) - /\ - and([x_ExplicitR2_Occurrence[q46, q51] -> - or([q53 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q48] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q48, q53] = q51 - | q53 : int(1..3)]) - | q51 : int(1..2)]) - | q48 : int(1..2)]) - | q46 : int(1..2)]), - and([or([and([x_ExplicitR2_Occurrence[q57, q58] -> - or([q60 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q55] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q55, q60] = q58 - | q60 : int(1..3)]) - | q58 : int(1..2)]) - /\ - and([q62 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q55] -> - x_ExplicitR2_Occurrence[q57, x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q55, q62]] - | q62 : int(1..3)]) - | q57 : int(1..2)]) - | q55 : int(1..2)]), - and([or([and([x_ExplicitR6_ExplicitVarSizeWithDummy[q66, q68] != 3 -> - x_ExplicitR2_Occurrence[q64, x_ExplicitR6_ExplicitVarSizeWithDummy[q66, q68]] - | q68 : int(1..3)]) - /\ - and([x_ExplicitR2_Occurrence[q64, q69] -> - or([x_ExplicitR6_ExplicitVarSizeWithDummy[q66, q71] != 3 /\ - x_ExplicitR6_ExplicitVarSizeWithDummy[q66, q71] = q69 - | q71 : int(1..3)]) - | q69 : int(1..2)]) - | q66 : int(1..2)]) - | q64 : int(1..2)]), - and([or([and([x_ExplicitR2_Occurrence[q75, q76] -> - or([x_ExplicitR6_ExplicitVarSizeWithDummy[q73, q78] != 3 /\ - x_ExplicitR6_ExplicitVarSizeWithDummy[q73, q78] = q76 - | q78 : int(1..3)]) - | q76 : int(1..2)]) - /\ - and([x_ExplicitR6_ExplicitVarSizeWithDummy[q73, q80] != 3 -> - x_ExplicitR2_Occurrence[q75, x_ExplicitR6_ExplicitVarSizeWithDummy[q73, q80]] - | q80 : int(1..3)]) - | q75 : int(1..2)]) - | q73 : int(1..2)]) - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_3_2_2-solution000001.solution b/tests/exhaustive/basic/setOfSet04/expected/model_3_2_2-solution000001.solution new file mode 100644 index 0000000000..38937c9389 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_3_2_2-solution000001.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{1}, {1, 2}} +$ Visualisation for x +$ 1 +$ 1 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_3_2_2-solution000002.solution b/tests/exhaustive/basic/setOfSet04/expected/model_3_2_2-solution000002.solution new file mode 100644 index 0000000000..9bf2af0712 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_3_2_2-solution000002.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{1, 2}, {2}} +$ Visualisation for x +$ 1 2 +$ 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_3_2_2-solution000003.solution b/tests/exhaustive/basic/setOfSet04/expected/model_3_2_2-solution000003.solution new file mode 100644 index 0000000000..a6c0b6a43e --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_3_2_2-solution000003.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{}, {1, 2}} +$ Visualisation for x +$ +$ 1 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_3_2_2-solution000004.solution b/tests/exhaustive/basic/setOfSet04/expected/model_3_2_2-solution000004.solution new file mode 100644 index 0000000000..af16592c51 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_3_2_2-solution000004.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{1}, {2}} +$ Visualisation for x +$ 1 +$ 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_3_2_2-solution000005.solution b/tests/exhaustive/basic/setOfSet04/expected/model_3_2_2-solution000005.solution new file mode 100644 index 0000000000..3ec452354e --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_3_2_2-solution000005.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{}, {1}} +$ Visualisation for x +$ +$ 1 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_3_2_2-solution000006.solution b/tests/exhaustive/basic/setOfSet04/expected/model_3_2_2-solution000006.solution new file mode 100644 index 0000000000..c8946f3d06 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_3_2_2-solution000006.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{}, {2}} +$ Visualisation for x +$ +$ 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_3_2_2.eprime.orig b/tests/exhaustive/basic/setOfSet04/expected/model_3_2_2.eprime.orig deleted file mode 100644 index f639c23ff2..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_3_2_2.eprime.orig +++ /dev/null @@ -1,68 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitR5_ExplicitVarSizeWithMarker_Marker: matrix indexed by [int(1..2)] of int(0..3) -find x_ExplicitR5_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..2), int(1..3)] of int(1..2) -find x_ExplicitR6_ExplicitVarSizeWithDummy: matrix indexed by [int(1..2), int(1..3)] of int(1..3) -branching on - [x_ExplicitR6_ExplicitVarSizeWithDummy, x_ExplicitR5_ExplicitVarSizeWithMarker_Marker, - x_ExplicitR5_ExplicitVarSizeWithMarker_Values] -such that - flatten([[x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[1]; int(1)], - [x_ExplicitR5_ExplicitVarSizeWithMarker_Values[1, q6] | q6 : int(1..3)]; - int(1..2)]) - - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q2, q3] < - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q2, q3 + 1] - | q3 : int(1..2)]) - | q2 : int(1..2)]), - and([and([q4 > x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q2] -> - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q2, q4] = 1 - | q4 : int(1..3)]) - | q2 : int(1..2)]), - and([x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q2] <= 3 | q2 : int(1..2)]), - [x_ExplicitR6_ExplicitVarSizeWithDummy[1, q14] | q14 : int(1..3)] - x_ExplicitR6_ExplicitVarSizeWithDummy[q9, q11 + 1] = 3 - | q11 : int(1..2)]) - | q9 : int(1..2)]), - and([sum([toInt(x_ExplicitR6_ExplicitVarSizeWithDummy[q9, q12] != 3) | q12 : int(1..3)]) <= 3 | q9 : int(1..2)]), - and([or([and([q21 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q19] -> - or([x_ExplicitR6_ExplicitVarSizeWithDummy[q17, q23] != 3 /\ - x_ExplicitR6_ExplicitVarSizeWithDummy[q17, q23] = - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q19, q21] - | q23 : int(1..3)]) - | q21 : int(1..3)]) - /\ - and([x_ExplicitR6_ExplicitVarSizeWithDummy[q17, q25] != 3 -> - or([q27 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q19] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q19, q27] = - x_ExplicitR6_ExplicitVarSizeWithDummy[q17, q25] - | q27 : int(1..3)]) - | q25 : int(1..3)]) - | q19 : int(1..2)]) - | q17 : int(1..2)]), - and([or([and([x_ExplicitR6_ExplicitVarSizeWithDummy[q31, q33] != 3 -> - or([q35 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q29] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q29, q35] = - x_ExplicitR6_ExplicitVarSizeWithDummy[q31, q33] - | q35 : int(1..3)]) - | q33 : int(1..3)]) - /\ - and([q37 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q29] -> - or([x_ExplicitR6_ExplicitVarSizeWithDummy[q31, q39] != 3 /\ - x_ExplicitR6_ExplicitVarSizeWithDummy[q31, q39] = - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q29, q37] - | q39 : int(1..3)]) - | q37 : int(1..3)]) - | q31 : int(1..2)]) - | q29 : int(1..2)]) - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_3_2_3.eprime.orig b/tests/exhaustive/basic/setOfSet04/expected/model_3_2_3.eprime.orig deleted file mode 100644 index f639c23ff2..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_3_2_3.eprime.orig +++ /dev/null @@ -1,68 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitR5_ExplicitVarSizeWithMarker_Marker: matrix indexed by [int(1..2)] of int(0..3) -find x_ExplicitR5_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..2), int(1..3)] of int(1..2) -find x_ExplicitR6_ExplicitVarSizeWithDummy: matrix indexed by [int(1..2), int(1..3)] of int(1..3) -branching on - [x_ExplicitR6_ExplicitVarSizeWithDummy, x_ExplicitR5_ExplicitVarSizeWithMarker_Marker, - x_ExplicitR5_ExplicitVarSizeWithMarker_Values] -such that - flatten([[x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[1]; int(1)], - [x_ExplicitR5_ExplicitVarSizeWithMarker_Values[1, q6] | q6 : int(1..3)]; - int(1..2)]) - - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q2, q3] < - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q2, q3 + 1] - | q3 : int(1..2)]) - | q2 : int(1..2)]), - and([and([q4 > x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q2] -> - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q2, q4] = 1 - | q4 : int(1..3)]) - | q2 : int(1..2)]), - and([x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q2] <= 3 | q2 : int(1..2)]), - [x_ExplicitR6_ExplicitVarSizeWithDummy[1, q14] | q14 : int(1..3)] - x_ExplicitR6_ExplicitVarSizeWithDummy[q9, q11 + 1] = 3 - | q11 : int(1..2)]) - | q9 : int(1..2)]), - and([sum([toInt(x_ExplicitR6_ExplicitVarSizeWithDummy[q9, q12] != 3) | q12 : int(1..3)]) <= 3 | q9 : int(1..2)]), - and([or([and([q21 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q19] -> - or([x_ExplicitR6_ExplicitVarSizeWithDummy[q17, q23] != 3 /\ - x_ExplicitR6_ExplicitVarSizeWithDummy[q17, q23] = - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q19, q21] - | q23 : int(1..3)]) - | q21 : int(1..3)]) - /\ - and([x_ExplicitR6_ExplicitVarSizeWithDummy[q17, q25] != 3 -> - or([q27 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q19] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q19, q27] = - x_ExplicitR6_ExplicitVarSizeWithDummy[q17, q25] - | q27 : int(1..3)]) - | q25 : int(1..3)]) - | q19 : int(1..2)]) - | q17 : int(1..2)]), - and([or([and([x_ExplicitR6_ExplicitVarSizeWithDummy[q31, q33] != 3 -> - or([q35 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q29] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q29, q35] = - x_ExplicitR6_ExplicitVarSizeWithDummy[q31, q33] - | q35 : int(1..3)]) - | q33 : int(1..3)]) - /\ - and([q37 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q29] -> - or([x_ExplicitR6_ExplicitVarSizeWithDummy[q31, q39] != 3 /\ - x_ExplicitR6_ExplicitVarSizeWithDummy[q31, q39] = - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q29, q37] - | q39 : int(1..3)]) - | q37 : int(1..3)]) - | q31 : int(1..2)]) - | q29 : int(1..2)]) - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_3_2_4-solution000001.solution b/tests/exhaustive/basic/setOfSet04/expected/model_3_2_4-solution000001.solution new file mode 100644 index 0000000000..3ec452354e --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_3_2_4-solution000001.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{}, {1}} +$ Visualisation for x +$ +$ 1 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_3_2_4-solution000002.solution b/tests/exhaustive/basic/setOfSet04/expected/model_3_2_4-solution000002.solution new file mode 100644 index 0000000000..c8946f3d06 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_3_2_4-solution000002.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{}, {2}} +$ Visualisation for x +$ +$ 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_3_2_4-solution000003.solution b/tests/exhaustive/basic/setOfSet04/expected/model_3_2_4-solution000003.solution new file mode 100644 index 0000000000..af16592c51 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_3_2_4-solution000003.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{1}, {2}} +$ Visualisation for x +$ 1 +$ 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_3_2_4-solution000004.solution b/tests/exhaustive/basic/setOfSet04/expected/model_3_2_4-solution000004.solution new file mode 100644 index 0000000000..a6c0b6a43e --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_3_2_4-solution000004.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{}, {1, 2}} +$ Visualisation for x +$ +$ 1 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_3_2_4-solution000005.solution b/tests/exhaustive/basic/setOfSet04/expected/model_3_2_4-solution000005.solution new file mode 100644 index 0000000000..38937c9389 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_3_2_4-solution000005.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{1}, {1, 2}} +$ Visualisation for x +$ 1 +$ 1 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_3_2_4-solution000006.solution b/tests/exhaustive/basic/setOfSet04/expected/model_3_2_4-solution000006.solution new file mode 100644 index 0000000000..9bf2af0712 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_3_2_4-solution000006.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{1, 2}, {2}} +$ Visualisation for x +$ 1 2 +$ 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_3_2_4.eprime.orig b/tests/exhaustive/basic/setOfSet04/expected/model_3_2_4.eprime.orig deleted file mode 100644 index 12d32c3c3f..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_3_2_4.eprime.orig +++ /dev/null @@ -1,154 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitR5_ExplicitVarSizeWithMarker_Marker: matrix indexed by [int(1..2)] of int(0..3) -find x_ExplicitR5_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..2), int(1..3)] of int(1..2) -find x_ExplicitR6_ExplicitVarSizeWithDummy: matrix indexed by [int(1..2), int(1..3)] of int(1..3) -find x_ExplicitR4_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..2), int(1..3)] of bool -find x_ExplicitR4_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..2), int(1..3)] of int(1..2) -branching on - [x_ExplicitR4_ExplicitVarSizeWithFlags_Flags, x_ExplicitR4_ExplicitVarSizeWithFlags_Values, - x_ExplicitR5_ExplicitVarSizeWithMarker_Marker, x_ExplicitR5_ExplicitVarSizeWithMarker_Values, - x_ExplicitR6_ExplicitVarSizeWithDummy] -such that - flatten([[x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[1]; int(1)], - [x_ExplicitR5_ExplicitVarSizeWithMarker_Values[1, q6] | q6 : int(1..3)]; - int(1..2)]) - - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q2, q3] < - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q2, q3 + 1] - | q3 : int(1..2)]) - | q2 : int(1..2)]), - and([and([q4 > x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q2] -> - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q2, q4] = 1 - | q4 : int(1..3)]) - | q2 : int(1..2)]), - and([x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q2] <= 3 | q2 : int(1..2)]), - [x_ExplicitR6_ExplicitVarSizeWithDummy[1, q14] | q14 : int(1..3)] - x_ExplicitR6_ExplicitVarSizeWithDummy[q9, q11 + 1] = 3 - | q11 : int(1..2)]) - | q9 : int(1..2)]), - and([sum([toInt(x_ExplicitR6_ExplicitVarSizeWithDummy[q9, q12] != 3) | q12 : int(1..3)]) <= 3 | q9 : int(1..2)]), - and([or([and([q21 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q19] -> - or([x_ExplicitR6_ExplicitVarSizeWithDummy[q17, q23] != 3 /\ - x_ExplicitR6_ExplicitVarSizeWithDummy[q17, q23] = - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q19, q21] - | q23 : int(1..3)]) - | q21 : int(1..3)]) - /\ - and([x_ExplicitR6_ExplicitVarSizeWithDummy[q17, q25] != 3 -> - or([q27 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q19] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q19, q27] = - x_ExplicitR6_ExplicitVarSizeWithDummy[q17, q25] - | q27 : int(1..3)]) - | q25 : int(1..3)]) - | q19 : int(1..2)]) - | q17 : int(1..2)]), - and([or([and([x_ExplicitR6_ExplicitVarSizeWithDummy[q31, q33] != 3 -> - or([q35 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q29] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q29, q35] = - x_ExplicitR6_ExplicitVarSizeWithDummy[q31, q33] - | q35 : int(1..3)]) - | q33 : int(1..3)]) - /\ - and([q37 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q29] -> - or([x_ExplicitR6_ExplicitVarSizeWithDummy[q31, q39] != 3 /\ - x_ExplicitR6_ExplicitVarSizeWithDummy[q31, q39] = - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q29, q37] - | q39 : int(1..3)]) - | q37 : int(1..3)]) - | q31 : int(1..2)]) - | q29 : int(1..2)]), - flatten([flatten([[-toInt(x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[1, q47]); int(1)], - [x_ExplicitR4_ExplicitVarSizeWithFlags_Values[1, q47]; int(1)]; - int(1..2)]) - | q47 : int(1..3)]) - - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q41, q42] < - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q41, q42 + 1] - | q42 : int(1..2)]) - | q41 : int(1..2)]), - and([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q41, q43] = false -> - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q41, q43] = 1 - | q43 : int(1..3)]) - | q41 : int(1..2)]), - and([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q41, q44 + 1] -> - x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q41, q44] - | q44 : int(1..2)]) - | q41 : int(1..2)]), - and([sum([toInt(x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q41, q45]) | q45 : int(1..3)]) <= 3 | q41 : int(1..2)]), - and([or([and([q54 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q52] -> - or([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q50, q56] /\ - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q50, q56] = - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q52, q54] - | q56 : int(1..3)]) - | q54 : int(1..3)]) - /\ - and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q50, q58] -> - or([q60 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q52] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q52, q60] = - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q50, q58] - | q60 : int(1..3)]) - | q58 : int(1..3)]) - | q52 : int(1..2)]) - | q50 : int(1..2)]), - and([or([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q64, q66] -> - or([q68 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q62] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q62, q68] = - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q64, q66] - | q68 : int(1..3)]) - | q66 : int(1..3)]) - /\ - and([q70 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q62] -> - or([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q64, q72] /\ - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q64, q72] = - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q62, q70] - | q72 : int(1..3)]) - | q70 : int(1..3)]) - | q64 : int(1..2)]) - | q62 : int(1..2)]), - and([or([and([x_ExplicitR6_ExplicitVarSizeWithDummy[q76, q78] != 3 -> - or([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q74, q80] /\ - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q74, q80] = - x_ExplicitR6_ExplicitVarSizeWithDummy[q76, q78] - | q80 : int(1..3)]) - | q78 : int(1..3)]) - /\ - and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q74, q82] -> - or([x_ExplicitR6_ExplicitVarSizeWithDummy[q76, q84] != 3 /\ - x_ExplicitR6_ExplicitVarSizeWithDummy[q76, q84] = - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q74, q82] - | q84 : int(1..3)]) - | q82 : int(1..3)]) - | q76 : int(1..2)]) - | q74 : int(1..2)]), - and([or([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q88, q90] -> - or([x_ExplicitR6_ExplicitVarSizeWithDummy[q86, q92] != 3 /\ - x_ExplicitR6_ExplicitVarSizeWithDummy[q86, q92] = - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q88, q90] - | q92 : int(1..3)]) - | q90 : int(1..3)]) - /\ - and([x_ExplicitR6_ExplicitVarSizeWithDummy[q86, q94] != 3 -> - or([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q88, q96] /\ - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q88, q96] = - x_ExplicitR6_ExplicitVarSizeWithDummy[q86, q94] - | q96 : int(1..3)]) - | q94 : int(1..3)]) - | q88 : int(1..2)]) - | q86 : int(1..2)]) - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_3_3_1.eprime.orig b/tests/exhaustive/basic/setOfSet04/expected/model_3_3_1.eprime.orig deleted file mode 100644 index 7d1e4bb4cf..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_3_3_1.eprime.orig +++ /dev/null @@ -1,52 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitR5_ExplicitVarSizeWithMarker_Marker: matrix indexed by [int(1..2)] of int(0..3) -find x_ExplicitR5_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..2), int(1..3)] of int(1..2) -find x_ExplicitR2_Occurrence: matrix indexed by [int(1..2), int(1..2)] of bool -branching on - [x_ExplicitR2_Occurrence, x_ExplicitR5_ExplicitVarSizeWithMarker_Marker, - x_ExplicitR5_ExplicitVarSizeWithMarker_Values] -such that - flatten([[x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[1]; int(1)], - [x_ExplicitR5_ExplicitVarSizeWithMarker_Values[1, q6] | q6 : int(1..3)]; - int(1..2)]) - - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q2, q3] < - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q2, q3 + 1] - | q3 : int(1..2)]) - | q2 : int(1..2)]), - and([and([q4 > x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q2] -> - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q2, q4] = 1 - | q4 : int(1..3)]) - | q2 : int(1..2)]), - and([x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q2] <= 3 | q2 : int(1..2)]), - [-toInt(x_ExplicitR2_Occurrence[1, q11]) | q11 : int(1..2)] - x_ExplicitR2_Occurrence[q14, x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q16, q18]] - | q18 : int(1..3)]) - /\ - and([x_ExplicitR2_Occurrence[q14, q19] -> - or([q21 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q16] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q16, q21] = q19 - | q21 : int(1..3)]) - | q19 : int(1..2)]) - | q16 : int(1..2)]) - | q14 : int(1..2)]), - and([or([and([x_ExplicitR2_Occurrence[q25, q26] -> - or([q28 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q23] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q23, q28] = q26 - | q28 : int(1..3)]) - | q26 : int(1..2)]) - /\ - and([q30 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q23] -> - x_ExplicitR2_Occurrence[q25, x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q23, q30]] - | q30 : int(1..3)]) - | q25 : int(1..2)]) - | q23 : int(1..2)]) - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_3_3_2.eprime.orig b/tests/exhaustive/basic/setOfSet04/expected/model_3_3_2.eprime.orig deleted file mode 100644 index f639c23ff2..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_3_3_2.eprime.orig +++ /dev/null @@ -1,68 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitR5_ExplicitVarSizeWithMarker_Marker: matrix indexed by [int(1..2)] of int(0..3) -find x_ExplicitR5_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..2), int(1..3)] of int(1..2) -find x_ExplicitR6_ExplicitVarSizeWithDummy: matrix indexed by [int(1..2), int(1..3)] of int(1..3) -branching on - [x_ExplicitR6_ExplicitVarSizeWithDummy, x_ExplicitR5_ExplicitVarSizeWithMarker_Marker, - x_ExplicitR5_ExplicitVarSizeWithMarker_Values] -such that - flatten([[x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[1]; int(1)], - [x_ExplicitR5_ExplicitVarSizeWithMarker_Values[1, q6] | q6 : int(1..3)]; - int(1..2)]) - - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q2, q3] < - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q2, q3 + 1] - | q3 : int(1..2)]) - | q2 : int(1..2)]), - and([and([q4 > x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q2] -> - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q2, q4] = 1 - | q4 : int(1..3)]) - | q2 : int(1..2)]), - and([x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q2] <= 3 | q2 : int(1..2)]), - [x_ExplicitR6_ExplicitVarSizeWithDummy[1, q14] | q14 : int(1..3)] - x_ExplicitR6_ExplicitVarSizeWithDummy[q9, q11 + 1] = 3 - | q11 : int(1..2)]) - | q9 : int(1..2)]), - and([sum([toInt(x_ExplicitR6_ExplicitVarSizeWithDummy[q9, q12] != 3) | q12 : int(1..3)]) <= 3 | q9 : int(1..2)]), - and([or([and([q21 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q19] -> - or([x_ExplicitR6_ExplicitVarSizeWithDummy[q17, q23] != 3 /\ - x_ExplicitR6_ExplicitVarSizeWithDummy[q17, q23] = - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q19, q21] - | q23 : int(1..3)]) - | q21 : int(1..3)]) - /\ - and([x_ExplicitR6_ExplicitVarSizeWithDummy[q17, q25] != 3 -> - or([q27 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q19] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q19, q27] = - x_ExplicitR6_ExplicitVarSizeWithDummy[q17, q25] - | q27 : int(1..3)]) - | q25 : int(1..3)]) - | q19 : int(1..2)]) - | q17 : int(1..2)]), - and([or([and([x_ExplicitR6_ExplicitVarSizeWithDummy[q31, q33] != 3 -> - or([q35 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q29] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q29, q35] = - x_ExplicitR6_ExplicitVarSizeWithDummy[q31, q33] - | q35 : int(1..3)]) - | q33 : int(1..3)]) - /\ - and([q37 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q29] -> - or([x_ExplicitR6_ExplicitVarSizeWithDummy[q31, q39] != 3 /\ - x_ExplicitR6_ExplicitVarSizeWithDummy[q31, q39] = - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q29, q37] - | q39 : int(1..3)]) - | q37 : int(1..3)]) - | q31 : int(1..2)]) - | q29 : int(1..2)]) - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_3_3_3-solution000001.solution b/tests/exhaustive/basic/setOfSet04/expected/model_3_3_3-solution000001.solution new file mode 100644 index 0000000000..3ec452354e --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_3_3_3-solution000001.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{}, {1}} +$ Visualisation for x +$ +$ 1 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_3_3_3-solution000002.solution b/tests/exhaustive/basic/setOfSet04/expected/model_3_3_3-solution000002.solution new file mode 100644 index 0000000000..c8946f3d06 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_3_3_3-solution000002.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{}, {2}} +$ Visualisation for x +$ +$ 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_3_3_3-solution000003.solution b/tests/exhaustive/basic/setOfSet04/expected/model_3_3_3-solution000003.solution new file mode 100644 index 0000000000..a6c0b6a43e --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_3_3_3-solution000003.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{}, {1, 2}} +$ Visualisation for x +$ +$ 1 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_3_3_3-solution000004.solution b/tests/exhaustive/basic/setOfSet04/expected/model_3_3_3-solution000004.solution new file mode 100644 index 0000000000..af16592c51 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_3_3_3-solution000004.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{1}, {2}} +$ Visualisation for x +$ 1 +$ 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_3_3_3-solution000005.solution b/tests/exhaustive/basic/setOfSet04/expected/model_3_3_3-solution000005.solution new file mode 100644 index 0000000000..38937c9389 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_3_3_3-solution000005.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{1}, {1, 2}} +$ Visualisation for x +$ 1 +$ 1 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_3_3_3-solution000006.solution b/tests/exhaustive/basic/setOfSet04/expected/model_3_3_3-solution000006.solution new file mode 100644 index 0000000000..9bf2af0712 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_3_3_3-solution000006.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{1, 2}, {2}} +$ Visualisation for x +$ 1 2 +$ 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_3_3_3.eprime.orig b/tests/exhaustive/basic/setOfSet04/expected/model_3_3_3.eprime.orig deleted file mode 100644 index 1dcefd1d46..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_3_3_3.eprime.orig +++ /dev/null @@ -1,24 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitR5_ExplicitVarSizeWithMarker_Marker: matrix indexed by [int(1..2)] of int(0..3) -find x_ExplicitR5_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..2), int(1..3)] of int(1..2) -branching on [x_ExplicitR5_ExplicitVarSizeWithMarker_Marker, x_ExplicitR5_ExplicitVarSizeWithMarker_Values] -such that - flatten([[x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[1]; int(1)], - [x_ExplicitR5_ExplicitVarSizeWithMarker_Values[1, q6] | q6 : int(1..3)]; - int(1..2)]) - - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q2, q3] < - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q2, q3 + 1] - | q3 : int(1..2)]) - | q2 : int(1..2)]), - and([and([q4 > x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q2] -> - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q2, q4] = 1 - | q4 : int(1..3)]) - | q2 : int(1..2)]), - and([x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q2] <= 3 | q2 : int(1..2)]) - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_3_3_4-solution000001.solution b/tests/exhaustive/basic/setOfSet04/expected/model_3_3_4-solution000001.solution new file mode 100644 index 0000000000..3ec452354e --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_3_3_4-solution000001.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{}, {1}} +$ Visualisation for x +$ +$ 1 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_3_3_4-solution000002.solution b/tests/exhaustive/basic/setOfSet04/expected/model_3_3_4-solution000002.solution new file mode 100644 index 0000000000..c8946f3d06 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_3_3_4-solution000002.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{}, {2}} +$ Visualisation for x +$ +$ 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_3_3_4-solution000003.solution b/tests/exhaustive/basic/setOfSet04/expected/model_3_3_4-solution000003.solution new file mode 100644 index 0000000000..af16592c51 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_3_3_4-solution000003.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{1}, {2}} +$ Visualisation for x +$ 1 +$ 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_3_3_4-solution000004.solution b/tests/exhaustive/basic/setOfSet04/expected/model_3_3_4-solution000004.solution new file mode 100644 index 0000000000..a6c0b6a43e --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_3_3_4-solution000004.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{}, {1, 2}} +$ Visualisation for x +$ +$ 1 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_3_3_4-solution000005.solution b/tests/exhaustive/basic/setOfSet04/expected/model_3_3_4-solution000005.solution new file mode 100644 index 0000000000..38937c9389 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_3_3_4-solution000005.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{1}, {1, 2}} +$ Visualisation for x +$ 1 +$ 1 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_3_3_4-solution000006.solution b/tests/exhaustive/basic/setOfSet04/expected/model_3_3_4-solution000006.solution new file mode 100644 index 0000000000..9bf2af0712 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_3_3_4-solution000006.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{1, 2}, {2}} +$ Visualisation for x +$ 1 2 +$ 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_3_3_4.eprime.orig b/tests/exhaustive/basic/setOfSet04/expected/model_3_3_4.eprime.orig deleted file mode 100644 index c767e19806..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_3_3_4.eprime.orig +++ /dev/null @@ -1,81 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitR5_ExplicitVarSizeWithMarker_Marker: matrix indexed by [int(1..2)] of int(0..3) -find x_ExplicitR5_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..2), int(1..3)] of int(1..2) -find x_ExplicitR4_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..2), int(1..3)] of bool -find x_ExplicitR4_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..2), int(1..3)] of int(1..2) -branching on - [x_ExplicitR4_ExplicitVarSizeWithFlags_Flags, x_ExplicitR4_ExplicitVarSizeWithFlags_Values, - x_ExplicitR5_ExplicitVarSizeWithMarker_Marker, x_ExplicitR5_ExplicitVarSizeWithMarker_Values] -such that - flatten([[x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[1]; int(1)], - [x_ExplicitR5_ExplicitVarSizeWithMarker_Values[1, q6] | q6 : int(1..3)]; - int(1..2)]) - - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q2, q3] < - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q2, q3 + 1] - | q3 : int(1..2)]) - | q2 : int(1..2)]), - and([and([q4 > x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q2] -> - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q2, q4] = 1 - | q4 : int(1..3)]) - | q2 : int(1..2)]), - and([x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q2] <= 3 | q2 : int(1..2)]), - flatten([flatten([[-toInt(x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[1, q15]); int(1)], - [x_ExplicitR4_ExplicitVarSizeWithFlags_Values[1, q15]; int(1)]; - int(1..2)]) - | q15 : int(1..3)]) - - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q9, q10] < - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q9, q10 + 1] - | q10 : int(1..2)]) - | q9 : int(1..2)]), - and([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q9, q11] = false -> - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q9, q11] = 1 - | q11 : int(1..3)]) - | q9 : int(1..2)]), - and([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q9, q12 + 1] -> - x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q9, q12] - | q12 : int(1..2)]) - | q9 : int(1..2)]), - and([sum([toInt(x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q9, q13]) | q13 : int(1..3)]) <= 3 | q9 : int(1..2)]), - and([or([and([q22 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q20] -> - or([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q18, q24] /\ - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q18, q24] = - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q20, q22] - | q24 : int(1..3)]) - | q22 : int(1..3)]) - /\ - and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q18, q26] -> - or([q28 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q20] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q20, q28] = - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q18, q26] - | q28 : int(1..3)]) - | q26 : int(1..3)]) - | q20 : int(1..2)]) - | q18 : int(1..2)]), - and([or([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q32, q34] -> - or([q36 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q30] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q30, q36] = - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q32, q34] - | q36 : int(1..3)]) - | q34 : int(1..3)]) - /\ - and([q38 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q30] -> - or([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q32, q40] /\ - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q32, q40] = - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q30, q38] - | q40 : int(1..3)]) - | q38 : int(1..3)]) - | q32 : int(1..2)]) - | q30 : int(1..2)]) - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_3_4_1-solution000001.solution b/tests/exhaustive/basic/setOfSet04/expected/model_3_4_1-solution000001.solution new file mode 100644 index 0000000000..c8946f3d06 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_3_4_1-solution000001.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{}, {2}} +$ Visualisation for x +$ +$ 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_3_4_1-solution000002.solution b/tests/exhaustive/basic/setOfSet04/expected/model_3_4_1-solution000002.solution new file mode 100644 index 0000000000..3ec452354e --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_3_4_1-solution000002.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{}, {1}} +$ Visualisation for x +$ +$ 1 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_3_4_1-solution000003.solution b/tests/exhaustive/basic/setOfSet04/expected/model_3_4_1-solution000003.solution new file mode 100644 index 0000000000..af16592c51 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_3_4_1-solution000003.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{1}, {2}} +$ Visualisation for x +$ 1 +$ 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_3_4_1-solution000004.solution b/tests/exhaustive/basic/setOfSet04/expected/model_3_4_1-solution000004.solution new file mode 100644 index 0000000000..a6c0b6a43e --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_3_4_1-solution000004.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{}, {1, 2}} +$ Visualisation for x +$ +$ 1 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_3_4_1-solution000005.solution b/tests/exhaustive/basic/setOfSet04/expected/model_3_4_1-solution000005.solution new file mode 100644 index 0000000000..9bf2af0712 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_3_4_1-solution000005.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{1, 2}, {2}} +$ Visualisation for x +$ 1 2 +$ 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_3_4_1-solution000006.solution b/tests/exhaustive/basic/setOfSet04/expected/model_3_4_1-solution000006.solution new file mode 100644 index 0000000000..38937c9389 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_3_4_1-solution000006.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{1}, {1, 2}} +$ Visualisation for x +$ 1 +$ 1 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_3_4_1.eprime.orig b/tests/exhaustive/basic/setOfSet04/expected/model_3_4_1.eprime.orig deleted file mode 100644 index cbaebe2e5e..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_3_4_1.eprime.orig +++ /dev/null @@ -1,130 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitR5_ExplicitVarSizeWithMarker_Marker: matrix indexed by [int(1..2)] of int(0..3) -find x_ExplicitR5_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..2), int(1..3)] of int(1..2) -find x_ExplicitR4_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..2), int(1..3)] of bool -find x_ExplicitR4_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..2), int(1..3)] of int(1..2) -find x_ExplicitR2_Occurrence: matrix indexed by [int(1..2), int(1..2)] of bool -branching on - [x_ExplicitR2_Occurrence, x_ExplicitR5_ExplicitVarSizeWithMarker_Marker, - x_ExplicitR5_ExplicitVarSizeWithMarker_Values, x_ExplicitR4_ExplicitVarSizeWithFlags_Flags, - x_ExplicitR4_ExplicitVarSizeWithFlags_Values] -such that - flatten([[x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[1]; int(1)], - [x_ExplicitR5_ExplicitVarSizeWithMarker_Values[1, q6] | q6 : int(1..3)]; - int(1..2)]) - - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q2, q3] < - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q2, q3 + 1] - | q3 : int(1..2)]) - | q2 : int(1..2)]), - and([and([q4 > x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q2] -> - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q2, q4] = 1 - | q4 : int(1..3)]) - | q2 : int(1..2)]), - and([x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q2] <= 3 | q2 : int(1..2)]), - flatten([flatten([[-toInt(x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[1, q15]); int(1)], - [x_ExplicitR4_ExplicitVarSizeWithFlags_Values[1, q15]; int(1)]; - int(1..2)]) - | q15 : int(1..3)]) - - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q9, q10] < - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q9, q10 + 1] - | q10 : int(1..2)]) - | q9 : int(1..2)]), - and([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q9, q11] = false -> - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q9, q11] = 1 - | q11 : int(1..3)]) - | q9 : int(1..2)]), - and([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q9, q12 + 1] -> - x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q9, q12] - | q12 : int(1..2)]) - | q9 : int(1..2)]), - and([sum([toInt(x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q9, q13]) | q13 : int(1..3)]) <= 3 | q9 : int(1..2)]), - and([or([and([q22 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q20] -> - or([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q18, q24] /\ - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q18, q24] = - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q20, q22] - | q24 : int(1..3)]) - | q22 : int(1..3)]) - /\ - and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q18, q26] -> - or([q28 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q20] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q20, q28] = - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q18, q26] - | q28 : int(1..3)]) - | q26 : int(1..3)]) - | q20 : int(1..2)]) - | q18 : int(1..2)]), - and([or([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q32, q34] -> - or([q36 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q30] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q30, q36] = - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q32, q34] - | q36 : int(1..3)]) - | q34 : int(1..3)]) - /\ - and([q38 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q30] -> - or([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q32, q40] /\ - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q32, q40] = - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q30, q38] - | q40 : int(1..3)]) - | q38 : int(1..3)]) - | q32 : int(1..2)]) - | q30 : int(1..2)]), - [-toInt(x_ExplicitR2_Occurrence[1, q44]) | q44 : int(1..2)] - x_ExplicitR2_Occurrence[q47, x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q49, q51]] - | q51 : int(1..3)]) - /\ - and([x_ExplicitR2_Occurrence[q47, q52] -> - or([q54 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q49] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q49, q54] = q52 - | q54 : int(1..3)]) - | q52 : int(1..2)]) - | q49 : int(1..2)]) - | q47 : int(1..2)]), - and([or([and([x_ExplicitR2_Occurrence[q58, q59] -> - or([q61 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q56] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q56, q61] = q59 - | q61 : int(1..3)]) - | q59 : int(1..2)]) - /\ - and([q63 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q56] -> - x_ExplicitR2_Occurrence[q58, x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q56, q63]] - | q63 : int(1..3)]) - | q58 : int(1..2)]) - | q56 : int(1..2)]), - and([or([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q67, q69] -> - x_ExplicitR2_Occurrence[q65, x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q67, q69]] - | q69 : int(1..3)]) - /\ - and([x_ExplicitR2_Occurrence[q65, q70] -> - or([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q67, q72] /\ - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q67, q72] = q70 - | q72 : int(1..3)]) - | q70 : int(1..2)]) - | q67 : int(1..2)]) - | q65 : int(1..2)]), - and([or([and([x_ExplicitR2_Occurrence[q76, q77] -> - or([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q74, q79] /\ - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q74, q79] = q77 - | q79 : int(1..3)]) - | q77 : int(1..2)]) - /\ - and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q74, q81] -> - x_ExplicitR2_Occurrence[q76, x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q74, q81]] - | q81 : int(1..3)]) - | q76 : int(1..2)]) - | q74 : int(1..2)]) - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_3_4_2-solution000001.solution b/tests/exhaustive/basic/setOfSet04/expected/model_3_4_2-solution000001.solution new file mode 100644 index 0000000000..38937c9389 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_3_4_2-solution000001.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{1}, {1, 2}} +$ Visualisation for x +$ 1 +$ 1 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_3_4_2-solution000002.solution b/tests/exhaustive/basic/setOfSet04/expected/model_3_4_2-solution000002.solution new file mode 100644 index 0000000000..9bf2af0712 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_3_4_2-solution000002.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{1, 2}, {2}} +$ Visualisation for x +$ 1 2 +$ 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_3_4_2-solution000003.solution b/tests/exhaustive/basic/setOfSet04/expected/model_3_4_2-solution000003.solution new file mode 100644 index 0000000000..a6c0b6a43e --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_3_4_2-solution000003.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{}, {1, 2}} +$ Visualisation for x +$ +$ 1 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_3_4_2-solution000004.solution b/tests/exhaustive/basic/setOfSet04/expected/model_3_4_2-solution000004.solution new file mode 100644 index 0000000000..af16592c51 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_3_4_2-solution000004.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{1}, {2}} +$ Visualisation for x +$ 1 +$ 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_3_4_2-solution000005.solution b/tests/exhaustive/basic/setOfSet04/expected/model_3_4_2-solution000005.solution new file mode 100644 index 0000000000..3ec452354e --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_3_4_2-solution000005.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{}, {1}} +$ Visualisation for x +$ +$ 1 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_3_4_2-solution000006.solution b/tests/exhaustive/basic/setOfSet04/expected/model_3_4_2-solution000006.solution new file mode 100644 index 0000000000..c8946f3d06 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_3_4_2-solution000006.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{}, {2}} +$ Visualisation for x +$ +$ 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_3_4_2.eprime.orig b/tests/exhaustive/basic/setOfSet04/expected/model_3_4_2.eprime.orig deleted file mode 100644 index 582cccb864..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_3_4_2.eprime.orig +++ /dev/null @@ -1,154 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitR5_ExplicitVarSizeWithMarker_Marker: matrix indexed by [int(1..2)] of int(0..3) -find x_ExplicitR5_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..2), int(1..3)] of int(1..2) -find x_ExplicitR4_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..2), int(1..3)] of bool -find x_ExplicitR4_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..2), int(1..3)] of int(1..2) -find x_ExplicitR6_ExplicitVarSizeWithDummy: matrix indexed by [int(1..2), int(1..3)] of int(1..3) -branching on - [x_ExplicitR6_ExplicitVarSizeWithDummy, x_ExplicitR5_ExplicitVarSizeWithMarker_Marker, - x_ExplicitR5_ExplicitVarSizeWithMarker_Values, x_ExplicitR4_ExplicitVarSizeWithFlags_Flags, - x_ExplicitR4_ExplicitVarSizeWithFlags_Values] -such that - flatten([[x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[1]; int(1)], - [x_ExplicitR5_ExplicitVarSizeWithMarker_Values[1, q6] | q6 : int(1..3)]; - int(1..2)]) - - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q2, q3] < - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q2, q3 + 1] - | q3 : int(1..2)]) - | q2 : int(1..2)]), - and([and([q4 > x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q2] -> - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q2, q4] = 1 - | q4 : int(1..3)]) - | q2 : int(1..2)]), - and([x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q2] <= 3 | q2 : int(1..2)]), - flatten([flatten([[-toInt(x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[1, q15]); int(1)], - [x_ExplicitR4_ExplicitVarSizeWithFlags_Values[1, q15]; int(1)]; - int(1..2)]) - | q15 : int(1..3)]) - - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q9, q10] < - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q9, q10 + 1] - | q10 : int(1..2)]) - | q9 : int(1..2)]), - and([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q9, q11] = false -> - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q9, q11] = 1 - | q11 : int(1..3)]) - | q9 : int(1..2)]), - and([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q9, q12 + 1] -> - x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q9, q12] - | q12 : int(1..2)]) - | q9 : int(1..2)]), - and([sum([toInt(x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q9, q13]) | q13 : int(1..3)]) <= 3 | q9 : int(1..2)]), - and([or([and([q22 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q20] -> - or([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q18, q24] /\ - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q18, q24] = - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q20, q22] - | q24 : int(1..3)]) - | q22 : int(1..3)]) - /\ - and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q18, q26] -> - or([q28 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q20] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q20, q28] = - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q18, q26] - | q28 : int(1..3)]) - | q26 : int(1..3)]) - | q20 : int(1..2)]) - | q18 : int(1..2)]), - and([or([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q32, q34] -> - or([q36 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q30] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q30, q36] = - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q32, q34] - | q36 : int(1..3)]) - | q34 : int(1..3)]) - /\ - and([q38 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q30] -> - or([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q32, q40] /\ - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q32, q40] = - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q30, q38] - | q40 : int(1..3)]) - | q38 : int(1..3)]) - | q32 : int(1..2)]) - | q30 : int(1..2)]), - [x_ExplicitR6_ExplicitVarSizeWithDummy[1, q47] | q47 : int(1..3)] - x_ExplicitR6_ExplicitVarSizeWithDummy[q42, q44 + 1] = 3 - | q44 : int(1..2)]) - | q42 : int(1..2)]), - and([sum([toInt(x_ExplicitR6_ExplicitVarSizeWithDummy[q42, q45] != 3) | q45 : int(1..3)]) <= 3 | q42 : int(1..2)]), - and([or([and([q54 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q52] -> - or([x_ExplicitR6_ExplicitVarSizeWithDummy[q50, q56] != 3 /\ - x_ExplicitR6_ExplicitVarSizeWithDummy[q50, q56] = - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q52, q54] - | q56 : int(1..3)]) - | q54 : int(1..3)]) - /\ - and([x_ExplicitR6_ExplicitVarSizeWithDummy[q50, q58] != 3 -> - or([q60 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q52] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q52, q60] = - x_ExplicitR6_ExplicitVarSizeWithDummy[q50, q58] - | q60 : int(1..3)]) - | q58 : int(1..3)]) - | q52 : int(1..2)]) - | q50 : int(1..2)]), - and([or([and([x_ExplicitR6_ExplicitVarSizeWithDummy[q64, q66] != 3 -> - or([q68 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q62] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q62, q68] = - x_ExplicitR6_ExplicitVarSizeWithDummy[q64, q66] - | q68 : int(1..3)]) - | q66 : int(1..3)]) - /\ - and([q70 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q62] -> - or([x_ExplicitR6_ExplicitVarSizeWithDummy[q64, q72] != 3 /\ - x_ExplicitR6_ExplicitVarSizeWithDummy[q64, q72] = - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q62, q70] - | q72 : int(1..3)]) - | q70 : int(1..3)]) - | q64 : int(1..2)]) - | q62 : int(1..2)]), - and([or([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q76, q78] -> - or([x_ExplicitR6_ExplicitVarSizeWithDummy[q74, q80] != 3 /\ - x_ExplicitR6_ExplicitVarSizeWithDummy[q74, q80] = - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q76, q78] - | q80 : int(1..3)]) - | q78 : int(1..3)]) - /\ - and([x_ExplicitR6_ExplicitVarSizeWithDummy[q74, q82] != 3 -> - or([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q76, q84] /\ - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q76, q84] = - x_ExplicitR6_ExplicitVarSizeWithDummy[q74, q82] - | q84 : int(1..3)]) - | q82 : int(1..3)]) - | q76 : int(1..2)]) - | q74 : int(1..2)]), - and([or([and([x_ExplicitR6_ExplicitVarSizeWithDummy[q88, q90] != 3 -> - or([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q86, q92] /\ - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q86, q92] = - x_ExplicitR6_ExplicitVarSizeWithDummy[q88, q90] - | q92 : int(1..3)]) - | q90 : int(1..3)]) - /\ - and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q86, q94] -> - or([x_ExplicitR6_ExplicitVarSizeWithDummy[q88, q96] != 3 /\ - x_ExplicitR6_ExplicitVarSizeWithDummy[q88, q96] = - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q86, q94] - | q96 : int(1..3)]) - | q94 : int(1..3)]) - | q88 : int(1..2)]) - | q86 : int(1..2)]) - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_3_4_3.eprime.orig b/tests/exhaustive/basic/setOfSet04/expected/model_3_4_3.eprime.orig deleted file mode 100644 index c767e19806..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_3_4_3.eprime.orig +++ /dev/null @@ -1,81 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitR5_ExplicitVarSizeWithMarker_Marker: matrix indexed by [int(1..2)] of int(0..3) -find x_ExplicitR5_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..2), int(1..3)] of int(1..2) -find x_ExplicitR4_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..2), int(1..3)] of bool -find x_ExplicitR4_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..2), int(1..3)] of int(1..2) -branching on - [x_ExplicitR4_ExplicitVarSizeWithFlags_Flags, x_ExplicitR4_ExplicitVarSizeWithFlags_Values, - x_ExplicitR5_ExplicitVarSizeWithMarker_Marker, x_ExplicitR5_ExplicitVarSizeWithMarker_Values] -such that - flatten([[x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[1]; int(1)], - [x_ExplicitR5_ExplicitVarSizeWithMarker_Values[1, q6] | q6 : int(1..3)]; - int(1..2)]) - - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q2, q3] < - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q2, q3 + 1] - | q3 : int(1..2)]) - | q2 : int(1..2)]), - and([and([q4 > x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q2] -> - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q2, q4] = 1 - | q4 : int(1..3)]) - | q2 : int(1..2)]), - and([x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q2] <= 3 | q2 : int(1..2)]), - flatten([flatten([[-toInt(x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[1, q15]); int(1)], - [x_ExplicitR4_ExplicitVarSizeWithFlags_Values[1, q15]; int(1)]; - int(1..2)]) - | q15 : int(1..3)]) - - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q9, q10] < - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q9, q10 + 1] - | q10 : int(1..2)]) - | q9 : int(1..2)]), - and([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q9, q11] = false -> - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q9, q11] = 1 - | q11 : int(1..3)]) - | q9 : int(1..2)]), - and([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q9, q12 + 1] -> - x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q9, q12] - | q12 : int(1..2)]) - | q9 : int(1..2)]), - and([sum([toInt(x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q9, q13]) | q13 : int(1..3)]) <= 3 | q9 : int(1..2)]), - and([or([and([q22 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q20] -> - or([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q18, q24] /\ - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q18, q24] = - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q20, q22] - | q24 : int(1..3)]) - | q22 : int(1..3)]) - /\ - and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q18, q26] -> - or([q28 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q20] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q20, q28] = - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q18, q26] - | q28 : int(1..3)]) - | q26 : int(1..3)]) - | q20 : int(1..2)]) - | q18 : int(1..2)]), - and([or([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q32, q34] -> - or([q36 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q30] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q30, q36] = - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q32, q34] - | q36 : int(1..3)]) - | q34 : int(1..3)]) - /\ - and([q38 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q30] -> - or([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q32, q40] /\ - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q32, q40] = - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q30, q38] - | q40 : int(1..3)]) - | q38 : int(1..3)]) - | q32 : int(1..2)]) - | q30 : int(1..2)]) - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_3_4_4.eprime.orig b/tests/exhaustive/basic/setOfSet04/expected/model_3_4_4.eprime.orig deleted file mode 100644 index c767e19806..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_3_4_4.eprime.orig +++ /dev/null @@ -1,81 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitR5_ExplicitVarSizeWithMarker_Marker: matrix indexed by [int(1..2)] of int(0..3) -find x_ExplicitR5_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..2), int(1..3)] of int(1..2) -find x_ExplicitR4_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..2), int(1..3)] of bool -find x_ExplicitR4_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..2), int(1..3)] of int(1..2) -branching on - [x_ExplicitR4_ExplicitVarSizeWithFlags_Flags, x_ExplicitR4_ExplicitVarSizeWithFlags_Values, - x_ExplicitR5_ExplicitVarSizeWithMarker_Marker, x_ExplicitR5_ExplicitVarSizeWithMarker_Values] -such that - flatten([[x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[1]; int(1)], - [x_ExplicitR5_ExplicitVarSizeWithMarker_Values[1, q6] | q6 : int(1..3)]; - int(1..2)]) - - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q2, q3] < - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q2, q3 + 1] - | q3 : int(1..2)]) - | q2 : int(1..2)]), - and([and([q4 > x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q2] -> - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q2, q4] = 1 - | q4 : int(1..3)]) - | q2 : int(1..2)]), - and([x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q2] <= 3 | q2 : int(1..2)]), - flatten([flatten([[-toInt(x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[1, q15]); int(1)], - [x_ExplicitR4_ExplicitVarSizeWithFlags_Values[1, q15]; int(1)]; - int(1..2)]) - | q15 : int(1..3)]) - - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q9, q10] < - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q9, q10 + 1] - | q10 : int(1..2)]) - | q9 : int(1..2)]), - and([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q9, q11] = false -> - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q9, q11] = 1 - | q11 : int(1..3)]) - | q9 : int(1..2)]), - and([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q9, q12 + 1] -> - x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q9, q12] - | q12 : int(1..2)]) - | q9 : int(1..2)]), - and([sum([toInt(x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q9, q13]) | q13 : int(1..3)]) <= 3 | q9 : int(1..2)]), - and([or([and([q22 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q20] -> - or([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q18, q24] /\ - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q18, q24] = - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q20, q22] - | q24 : int(1..3)]) - | q22 : int(1..3)]) - /\ - and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q18, q26] -> - or([q28 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q20] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q20, q28] = - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q18, q26] - | q28 : int(1..3)]) - | q26 : int(1..3)]) - | q20 : int(1..2)]) - | q18 : int(1..2)]), - and([or([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q32, q34] -> - or([q36 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q30] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q30, q36] = - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q32, q34] - | q36 : int(1..3)]) - | q34 : int(1..3)]) - /\ - and([q38 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q30] -> - or([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q32, q40] /\ - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q32, q40] = - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q30, q38] - | q40 : int(1..3)]) - | q38 : int(1..3)]) - | q32 : int(1..2)]) - | q30 : int(1..2)]) - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_4_1_1-solution000001.solution b/tests/exhaustive/basic/setOfSet04/expected/model_4_1_1-solution000001.solution new file mode 100644 index 0000000000..c8946f3d06 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_4_1_1-solution000001.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{}, {2}} +$ Visualisation for x +$ +$ 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_4_1_1-solution000002.solution b/tests/exhaustive/basic/setOfSet04/expected/model_4_1_1-solution000002.solution new file mode 100644 index 0000000000..3ec452354e --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_4_1_1-solution000002.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{}, {1}} +$ Visualisation for x +$ +$ 1 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_4_1_1-solution000003.solution b/tests/exhaustive/basic/setOfSet04/expected/model_4_1_1-solution000003.solution new file mode 100644 index 0000000000..af16592c51 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_4_1_1-solution000003.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{1}, {2}} +$ Visualisation for x +$ 1 +$ 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_4_1_1-solution000004.solution b/tests/exhaustive/basic/setOfSet04/expected/model_4_1_1-solution000004.solution new file mode 100644 index 0000000000..a6c0b6a43e --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_4_1_1-solution000004.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{}, {1, 2}} +$ Visualisation for x +$ +$ 1 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_4_1_1-solution000005.solution b/tests/exhaustive/basic/setOfSet04/expected/model_4_1_1-solution000005.solution new file mode 100644 index 0000000000..9bf2af0712 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_4_1_1-solution000005.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{1, 2}, {2}} +$ Visualisation for x +$ 1 2 +$ 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_4_1_1-solution000006.solution b/tests/exhaustive/basic/setOfSet04/expected/model_4_1_1-solution000006.solution new file mode 100644 index 0000000000..38937c9389 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_4_1_1-solution000006.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{1}, {1, 2}} +$ Visualisation for x +$ 1 +$ 1 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_4_1_1.eprime b/tests/exhaustive/basic/setOfSet04/expected/model_4_1_1.eprime new file mode 100644 index 0000000000..c7f842826d --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_4_1_1.eprime @@ -0,0 +1,57 @@ +language ESSENCE' 1.0 + +find x_ExplicitR4_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..2), int(1..3)] of bool +find x_ExplicitR4_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..2), int(1..3)] of int(1..2) +find x_ExplicitR2_Occurrence: matrix indexed by [int(1..2), int(1..2)] of bool +branching on + [x_ExplicitR2_Occurrence, x_ExplicitR4_ExplicitVarSizeWithFlags_Flags, x_ExplicitR4_ExplicitVarSizeWithFlags_Values] +such that + flatten([flatten([[-toInt(x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[1, q8]); int(1)], + [x_ExplicitR4_ExplicitVarSizeWithFlags_Values[1, q8]; int(1)]; + int(1..2)]) + | q8 : int(1..3)]) + + x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q2, q3] < + x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q2, q3 + 1] + | q3 : int(1..2)]) + | q2 : int(1..2)]), + and([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q2, q4] = false -> + x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q2, q4] = 1 + | q4 : int(1..3)]) + | q2 : int(1..2)]), + and([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q2, q5 + 1] -> + x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q2, q5] + | q5 : int(1..2)]) + | q2 : int(1..2)]), + and([sum([toInt(x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q2, q6]) | q6 : int(1..3)]) <= 3 | q2 : int(1..2)]), + [-toInt(x_ExplicitR2_Occurrence[1, q13]) | q13 : int(1..2)] + x_ExplicitR2_Occurrence[q16, x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q18, q20]] + | q20 : int(1..3)]) + /\ + and([x_ExplicitR2_Occurrence[q16, q21] -> + or([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q18, q23] /\ + x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q18, q23] = q21 + | q23 : int(1..3)]) + | q21 : int(1..2)]) + | q18 : int(1..2)]) + | q16 : int(1..2)]), + and([or([and([x_ExplicitR2_Occurrence[q27, q28] -> + or([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q25, q30] /\ + x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q25, q30] = q28 + | q30 : int(1..3)]) + | q28 : int(1..2)]) + /\ + and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q25, q32] -> + x_ExplicitR2_Occurrence[q27, x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q25, q32]] + | q32 : int(1..3)]) + | q27 : int(1..2)]) + | q25 : int(1..2)]) + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_4_1_2-solution000001.solution b/tests/exhaustive/basic/setOfSet04/expected/model_4_1_2-solution000001.solution new file mode 100644 index 0000000000..38937c9389 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_4_1_2-solution000001.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{1}, {1, 2}} +$ Visualisation for x +$ 1 +$ 1 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_4_1_2-solution000002.solution b/tests/exhaustive/basic/setOfSet04/expected/model_4_1_2-solution000002.solution new file mode 100644 index 0000000000..9bf2af0712 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_4_1_2-solution000002.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{1, 2}, {2}} +$ Visualisation for x +$ 1 2 +$ 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_4_1_2-solution000003.solution b/tests/exhaustive/basic/setOfSet04/expected/model_4_1_2-solution000003.solution new file mode 100644 index 0000000000..a6c0b6a43e --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_4_1_2-solution000003.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{}, {1, 2}} +$ Visualisation for x +$ +$ 1 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_4_1_2-solution000004.solution b/tests/exhaustive/basic/setOfSet04/expected/model_4_1_2-solution000004.solution new file mode 100644 index 0000000000..af16592c51 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_4_1_2-solution000004.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{1}, {2}} +$ Visualisation for x +$ 1 +$ 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_4_1_2-solution000005.solution b/tests/exhaustive/basic/setOfSet04/expected/model_4_1_2-solution000005.solution new file mode 100644 index 0000000000..3ec452354e --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_4_1_2-solution000005.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{}, {1}} +$ Visualisation for x +$ +$ 1 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_4_1_2-solution000006.solution b/tests/exhaustive/basic/setOfSet04/expected/model_4_1_2-solution000006.solution new file mode 100644 index 0000000000..c8946f3d06 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_4_1_2-solution000006.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{}, {2}} +$ Visualisation for x +$ +$ 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_4_1_3.eprime.orig b/tests/exhaustive/basic/setOfSet04/expected/model_4_1_2.eprime similarity index 50% rename from tests/exhaustive/basic/setOfSet04/expected/model_4_1_3.eprime.orig rename to tests/exhaustive/basic/setOfSet04/expected/model_4_1_2.eprime index 0af074b690..b766299560 100644 --- a/tests/exhaustive/basic/setOfSet04/expected/model_4_1_3.eprime.orig +++ b/tests/exhaustive/basic/setOfSet04/expected/model_4_1_2.eprime @@ -3,11 +3,10 @@ language ESSENCE' 1.0 find x_ExplicitR4_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..2), int(1..3)] of bool find x_ExplicitR4_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..2), int(1..3)] of int(1..2) find x_ExplicitR2_Occurrence: matrix indexed by [int(1..2), int(1..2)] of bool -find x_ExplicitR5_ExplicitVarSizeWithMarker_Marker: matrix indexed by [int(1..2)] of int(0..3) -find x_ExplicitR5_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..2), int(1..3)] of int(1..2) +find x_ExplicitR6_ExplicitVarSizeWithDummy: matrix indexed by [int(1..2), int(1..3)] of int(1..3) branching on - [x_ExplicitR5_ExplicitVarSizeWithMarker_Marker, x_ExplicitR5_ExplicitVarSizeWithMarker_Values, - x_ExplicitR4_ExplicitVarSizeWithFlags_Flags, x_ExplicitR4_ExplicitVarSizeWithFlags_Values, x_ExplicitR2_Occurrence] + [x_ExplicitR6_ExplicitVarSizeWithDummy, x_ExplicitR4_ExplicitVarSizeWithFlags_Flags, + x_ExplicitR4_ExplicitVarSizeWithFlags_Values, x_ExplicitR2_Occurrence] such that flatten([flatten([[-toInt(x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[1, q8]); int(1)], [x_ExplicitR4_ExplicitVarSizeWithFlags_Values[1, q8]; int(1)]; @@ -57,73 +56,67 @@ such that | q32 : int(1..3)]) | q27 : int(1..2)]) | q25 : int(1..2)]), - flatten([[x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[1]; int(1)], - [x_ExplicitR5_ExplicitVarSizeWithMarker_Values[1, q38] | q38 : int(1..3)]; - int(1..2)]) - - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q34, q35] < - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q34, q35 + 1] + [x_ExplicitR6_ExplicitVarSizeWithDummy[1, q39] | q39 : int(1..3)] x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q34] -> - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q34, q36] = 1 - | q36 : int(1..3)]) + and([and([x_ExplicitR6_ExplicitVarSizeWithDummy[q34, q36] = 3 -> + x_ExplicitR6_ExplicitVarSizeWithDummy[q34, q36 + 1] = 3 + | q36 : int(1..2)]) | q34 : int(1..2)]), - and([x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q34] <= 3 | q34 : int(1..2)]), - and([or([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q43, q45] -> - or([q47 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q41] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q41, q47] = - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q43, q45] - | q47 : int(1..3)]) - | q45 : int(1..3)]) + and([sum([toInt(x_ExplicitR6_ExplicitVarSizeWithDummy[q34, q37] != 3) | q37 : int(1..3)]) <= 3 | q34 : int(1..2)]), + and([or([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q44, q46] -> + or([x_ExplicitR6_ExplicitVarSizeWithDummy[q42, q48] != 3 /\ + x_ExplicitR6_ExplicitVarSizeWithDummy[q42, q48] = + x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q44, q46] + | q48 : int(1..3)]) + | q46 : int(1..3)]) /\ - and([q49 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q41] -> - or([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q43, q51] /\ - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q43, q51] = - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q41, q49] - | q51 : int(1..3)]) - | q49 : int(1..3)]) - | q43 : int(1..2)]) - | q41 : int(1..2)]), - and([or([and([q57 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q55] -> - or([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q53, q59] /\ - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q53, q59] = - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q55, q57] - | q59 : int(1..3)]) - | q57 : int(1..3)]) + and([x_ExplicitR6_ExplicitVarSizeWithDummy[q42, q50] != 3 -> + or([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q44, q52] /\ + x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q44, q52] = + x_ExplicitR6_ExplicitVarSizeWithDummy[q42, q50] + | q52 : int(1..3)]) + | q50 : int(1..3)]) + | q44 : int(1..2)]) + | q42 : int(1..2)]), + and([or([and([x_ExplicitR6_ExplicitVarSizeWithDummy[q56, q58] != 3 -> + or([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q54, q60] /\ + x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q54, q60] = + x_ExplicitR6_ExplicitVarSizeWithDummy[q56, q58] + | q60 : int(1..3)]) + | q58 : int(1..3)]) /\ - and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q53, q61] -> - or([q63 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q55] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q55, q63] = - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q53, q61] - | q63 : int(1..3)]) - | q61 : int(1..3)]) - | q55 : int(1..2)]) - | q53 : int(1..2)]), - and([or([and([x_ExplicitR2_Occurrence[q67, q68] -> - or([q70 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q65] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q65, q70] = q68 - | q70 : int(1..3)]) - | q68 : int(1..2)]) + and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q54, q62] -> + or([x_ExplicitR6_ExplicitVarSizeWithDummy[q56, q64] != 3 /\ + x_ExplicitR6_ExplicitVarSizeWithDummy[q56, q64] = + x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q54, q62] + | q64 : int(1..3)]) + | q62 : int(1..3)]) + | q56 : int(1..2)]) + | q54 : int(1..2)]), + and([or([and([x_ExplicitR2_Occurrence[q68, q69] -> + or([x_ExplicitR6_ExplicitVarSizeWithDummy[q66, q71] != 3 /\ + x_ExplicitR6_ExplicitVarSizeWithDummy[q66, q71] = q69 + | q71 : int(1..3)]) + | q69 : int(1..2)]) /\ - and([q72 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q65] -> - x_ExplicitR2_Occurrence[q67, x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q65, q72]] - | q72 : int(1..3)]) - | q67 : int(1..2)]) - | q65 : int(1..2)]), - and([or([and([q78 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q76] -> - x_ExplicitR2_Occurrence[q74, x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q76, q78]] - | q78 : int(1..3)]) + and([x_ExplicitR6_ExplicitVarSizeWithDummy[q66, q73] != 3 -> + x_ExplicitR2_Occurrence[q68, x_ExplicitR6_ExplicitVarSizeWithDummy[q66, q73]] + | q73 : int(1..3)]) + | q68 : int(1..2)]) + | q66 : int(1..2)]), + and([or([and([x_ExplicitR6_ExplicitVarSizeWithDummy[q77, q79] != 3 -> + x_ExplicitR2_Occurrence[q75, x_ExplicitR6_ExplicitVarSizeWithDummy[q77, q79]] + | q79 : int(1..3)]) /\ - and([x_ExplicitR2_Occurrence[q74, q79] -> - or([q81 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q76] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q76, q81] = q79 - | q81 : int(1..3)]) - | q79 : int(1..2)]) - | q76 : int(1..2)]) - | q74 : int(1..2)]) + and([x_ExplicitR2_Occurrence[q75, q80] -> + or([x_ExplicitR6_ExplicitVarSizeWithDummy[q77, q82] != 3 /\ + x_ExplicitR6_ExplicitVarSizeWithDummy[q77, q82] = q80 + | q82 : int(1..3)]) + | q80 : int(1..2)]) + | q77 : int(1..2)]) + | q75 : int(1..2)]) diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_4_1_3-solution000001.solution b/tests/exhaustive/basic/setOfSet04/expected/model_4_1_3-solution000001.solution new file mode 100644 index 0000000000..3ec452354e --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_4_1_3-solution000001.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{}, {1}} +$ Visualisation for x +$ +$ 1 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_4_1_3-solution000002.solution b/tests/exhaustive/basic/setOfSet04/expected/model_4_1_3-solution000002.solution new file mode 100644 index 0000000000..c8946f3d06 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_4_1_3-solution000002.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{}, {2}} +$ Visualisation for x +$ +$ 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_4_1_3-solution000003.solution b/tests/exhaustive/basic/setOfSet04/expected/model_4_1_3-solution000003.solution new file mode 100644 index 0000000000..a6c0b6a43e --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_4_1_3-solution000003.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{}, {1, 2}} +$ Visualisation for x +$ +$ 1 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_4_1_3-solution000004.solution b/tests/exhaustive/basic/setOfSet04/expected/model_4_1_3-solution000004.solution new file mode 100644 index 0000000000..af16592c51 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_4_1_3-solution000004.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{1}, {2}} +$ Visualisation for x +$ 1 +$ 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_4_1_3-solution000005.solution b/tests/exhaustive/basic/setOfSet04/expected/model_4_1_3-solution000005.solution new file mode 100644 index 0000000000..38937c9389 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_4_1_3-solution000005.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{1}, {1, 2}} +$ Visualisation for x +$ 1 +$ 1 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_4_1_3-solution000006.solution b/tests/exhaustive/basic/setOfSet04/expected/model_4_1_3-solution000006.solution new file mode 100644 index 0000000000..9bf2af0712 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_4_1_3-solution000006.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{1, 2}, {2}} +$ Visualisation for x +$ 1 2 +$ 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_4_2_1-solution000001.solution b/tests/exhaustive/basic/setOfSet04/expected/model_4_2_1-solution000001.solution new file mode 100644 index 0000000000..c8946f3d06 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_4_2_1-solution000001.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{}, {2}} +$ Visualisation for x +$ +$ 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_4_2_1-solution000002.solution b/tests/exhaustive/basic/setOfSet04/expected/model_4_2_1-solution000002.solution new file mode 100644 index 0000000000..3ec452354e --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_4_2_1-solution000002.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{}, {1}} +$ Visualisation for x +$ +$ 1 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_4_2_1-solution000003.solution b/tests/exhaustive/basic/setOfSet04/expected/model_4_2_1-solution000003.solution new file mode 100644 index 0000000000..af16592c51 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_4_2_1-solution000003.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{1}, {2}} +$ Visualisation for x +$ 1 +$ 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_4_2_1-solution000004.solution b/tests/exhaustive/basic/setOfSet04/expected/model_4_2_1-solution000004.solution new file mode 100644 index 0000000000..a6c0b6a43e --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_4_2_1-solution000004.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{}, {1, 2}} +$ Visualisation for x +$ +$ 1 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_4_2_1-solution000005.solution b/tests/exhaustive/basic/setOfSet04/expected/model_4_2_1-solution000005.solution new file mode 100644 index 0000000000..9bf2af0712 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_4_2_1-solution000005.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{1, 2}, {2}} +$ Visualisation for x +$ 1 2 +$ 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_4_2_1-solution000006.solution b/tests/exhaustive/basic/setOfSet04/expected/model_4_2_1-solution000006.solution new file mode 100644 index 0000000000..38937c9389 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_4_2_1-solution000006.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{1}, {1, 2}} +$ Visualisation for x +$ 1 +$ 1 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_4_2_3.eprime.orig b/tests/exhaustive/basic/setOfSet04/expected/model_4_2_1.eprime similarity index 51% rename from tests/exhaustive/basic/setOfSet04/expected/model_4_2_3.eprime.orig rename to tests/exhaustive/basic/setOfSet04/expected/model_4_2_1.eprime index 1c270ceec6..972c2b1a63 100644 --- a/tests/exhaustive/basic/setOfSet04/expected/model_4_2_3.eprime.orig +++ b/tests/exhaustive/basic/setOfSet04/expected/model_4_2_1.eprime @@ -3,11 +3,9 @@ language ESSENCE' 1.0 find x_ExplicitR4_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..2), int(1..3)] of bool find x_ExplicitR4_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..2), int(1..3)] of int(1..2) find x_ExplicitR6_ExplicitVarSizeWithDummy: matrix indexed by [int(1..2), int(1..3)] of int(1..3) -find x_ExplicitR5_ExplicitVarSizeWithMarker_Marker: matrix indexed by [int(1..2)] of int(0..3) -find x_ExplicitR5_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..2), int(1..3)] of int(1..2) +find x_ExplicitR2_Occurrence: matrix indexed by [int(1..2), int(1..2)] of bool branching on - [x_ExplicitR5_ExplicitVarSizeWithMarker_Marker, x_ExplicitR5_ExplicitVarSizeWithMarker_Values, - x_ExplicitR4_ExplicitVarSizeWithFlags_Flags, x_ExplicitR4_ExplicitVarSizeWithFlags_Values, + [x_ExplicitR2_Occurrence, x_ExplicitR4_ExplicitVarSizeWithFlags_Flags, x_ExplicitR4_ExplicitVarSizeWithFlags_Values, x_ExplicitR6_ExplicitVarSizeWithDummy] such that flatten([flatten([[-toInt(x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[1, q8]); int(1)], @@ -74,81 +72,51 @@ such that | q39 : int(1..3)]) | q33 : int(1..2)]) | q31 : int(1..2)]), - flatten([[x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[1]; int(1)], - [x_ExplicitR5_ExplicitVarSizeWithMarker_Values[1, q47] | q47 : int(1..3)]; - int(1..2)]) - - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q43, q44] < - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q43, q44 + 1] - | q44 : int(1..2)]) - | q43 : int(1..2)]), - and([and([q45 > x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q43] -> - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q43, q45] = 1 - | q45 : int(1..3)]) - | q43 : int(1..2)]), - and([x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q43] <= 3 | q43 : int(1..2)]), - and([or([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q52, q54] -> - or([q56 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q50] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q50, q56] = - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q52, q54] - | q56 : int(1..3)]) - | q54 : int(1..3)]) + [-toInt(x_ExplicitR2_Occurrence[1, q45]) | q45 : int(1..2)] + x_ExplicitR2_Occurrence[q48, x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q50, q52]] + | q52 : int(1..3)]) /\ - and([q58 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q50] -> - or([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q52, q60] /\ - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q52, q60] = - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q50, q58] - | q60 : int(1..3)]) - | q58 : int(1..3)]) - | q52 : int(1..2)]) - | q50 : int(1..2)]), - and([or([and([q66 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q64] -> - or([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q62, q68] /\ - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q62, q68] = - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q64, q66] - | q68 : int(1..3)]) - | q66 : int(1..3)]) + and([x_ExplicitR2_Occurrence[q48, q53] -> + or([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q50, q55] /\ + x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q50, q55] = q53 + | q55 : int(1..3)]) + | q53 : int(1..2)]) + | q50 : int(1..2)]) + | q48 : int(1..2)]), + and([or([and([x_ExplicitR2_Occurrence[q59, q60] -> + or([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q57, q62] /\ + x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q57, q62] = q60 + | q62 : int(1..3)]) + | q60 : int(1..2)]) /\ - and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q62, q70] -> - or([q72 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q64] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q64, q72] = - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q62, q70] - | q72 : int(1..3)]) + and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q57, q64] -> + x_ExplicitR2_Occurrence[q59, x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q57, q64]] + | q64 : int(1..3)]) + | q59 : int(1..2)]) + | q57 : int(1..2)]), + and([or([and([x_ExplicitR6_ExplicitVarSizeWithDummy[q68, q70] != 3 -> + x_ExplicitR2_Occurrence[q66, x_ExplicitR6_ExplicitVarSizeWithDummy[q68, q70]] | q70 : int(1..3)]) - | q64 : int(1..2)]) - | q62 : int(1..2)]), - and([or([and([x_ExplicitR6_ExplicitVarSizeWithDummy[q76, q78] != 3 -> - or([q80 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q74] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q74, q80] = - x_ExplicitR6_ExplicitVarSizeWithDummy[q76, q78] + /\ + and([x_ExplicitR2_Occurrence[q66, q71] -> + or([x_ExplicitR6_ExplicitVarSizeWithDummy[q68, q73] != 3 /\ + x_ExplicitR6_ExplicitVarSizeWithDummy[q68, q73] = q71 + | q73 : int(1..3)]) + | q71 : int(1..2)]) + | q68 : int(1..2)]) + | q66 : int(1..2)]), + and([or([and([x_ExplicitR2_Occurrence[q77, q78] -> + or([x_ExplicitR6_ExplicitVarSizeWithDummy[q75, q80] != 3 /\ + x_ExplicitR6_ExplicitVarSizeWithDummy[q75, q80] = q78 | q80 : int(1..3)]) - | q78 : int(1..3)]) + | q78 : int(1..2)]) /\ - and([q82 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q74] -> - or([x_ExplicitR6_ExplicitVarSizeWithDummy[q76, q84] != 3 /\ - x_ExplicitR6_ExplicitVarSizeWithDummy[q76, q84] = - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q74, q82] - | q84 : int(1..3)]) + and([x_ExplicitR6_ExplicitVarSizeWithDummy[q75, q82] != 3 -> + x_ExplicitR2_Occurrence[q77, x_ExplicitR6_ExplicitVarSizeWithDummy[q75, q82]] | q82 : int(1..3)]) - | q76 : int(1..2)]) - | q74 : int(1..2)]), - and([or([and([q90 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q88] -> - or([x_ExplicitR6_ExplicitVarSizeWithDummy[q86, q92] != 3 /\ - x_ExplicitR6_ExplicitVarSizeWithDummy[q86, q92] = - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q88, q90] - | q92 : int(1..3)]) - | q90 : int(1..3)]) - /\ - and([x_ExplicitR6_ExplicitVarSizeWithDummy[q86, q94] != 3 -> - or([q96 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q88] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q88, q96] = - x_ExplicitR6_ExplicitVarSizeWithDummy[q86, q94] - | q96 : int(1..3)]) - | q94 : int(1..3)]) - | q88 : int(1..2)]) - | q86 : int(1..2)]) + | q77 : int(1..2)]) + | q75 : int(1..2)]) diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_4_2_2-solution000001.solution b/tests/exhaustive/basic/setOfSet04/expected/model_4_2_2-solution000001.solution new file mode 100644 index 0000000000..38937c9389 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_4_2_2-solution000001.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{1}, {1, 2}} +$ Visualisation for x +$ 1 +$ 1 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_4_2_2-solution000002.solution b/tests/exhaustive/basic/setOfSet04/expected/model_4_2_2-solution000002.solution new file mode 100644 index 0000000000..9bf2af0712 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_4_2_2-solution000002.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{1, 2}, {2}} +$ Visualisation for x +$ 1 2 +$ 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_4_2_2-solution000003.solution b/tests/exhaustive/basic/setOfSet04/expected/model_4_2_2-solution000003.solution new file mode 100644 index 0000000000..a6c0b6a43e --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_4_2_2-solution000003.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{}, {1, 2}} +$ Visualisation for x +$ +$ 1 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_4_2_2-solution000004.solution b/tests/exhaustive/basic/setOfSet04/expected/model_4_2_2-solution000004.solution new file mode 100644 index 0000000000..af16592c51 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_4_2_2-solution000004.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{1}, {2}} +$ Visualisation for x +$ 1 +$ 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_4_2_2-solution000005.solution b/tests/exhaustive/basic/setOfSet04/expected/model_4_2_2-solution000005.solution new file mode 100644 index 0000000000..3ec452354e --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_4_2_2-solution000005.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{}, {1}} +$ Visualisation for x +$ +$ 1 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_4_2_2-solution000006.solution b/tests/exhaustive/basic/setOfSet04/expected/model_4_2_2-solution000006.solution new file mode 100644 index 0000000000..c8946f3d06 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_4_2_2-solution000006.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{}, {2}} +$ Visualisation for x +$ +$ 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_4_2_2.eprime b/tests/exhaustive/basic/setOfSet04/expected/model_4_2_2.eprime new file mode 100644 index 0000000000..048ac1ff0c --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_4_2_2.eprime @@ -0,0 +1,74 @@ +language ESSENCE' 1.0 + +find x_ExplicitR4_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..2), int(1..3)] of bool +find x_ExplicitR4_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..2), int(1..3)] of int(1..2) +find x_ExplicitR6_ExplicitVarSizeWithDummy: matrix indexed by [int(1..2), int(1..3)] of int(1..3) +branching on + [x_ExplicitR6_ExplicitVarSizeWithDummy, x_ExplicitR4_ExplicitVarSizeWithFlags_Flags, + x_ExplicitR4_ExplicitVarSizeWithFlags_Values] +such that + flatten([flatten([[-toInt(x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[1, q8]); int(1)], + [x_ExplicitR4_ExplicitVarSizeWithFlags_Values[1, q8]; int(1)]; + int(1..2)]) + | q8 : int(1..3)]) + + x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q2, q3] < + x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q2, q3 + 1] + | q3 : int(1..2)]) + | q2 : int(1..2)]), + and([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q2, q4] = false -> + x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q2, q4] = 1 + | q4 : int(1..3)]) + | q2 : int(1..2)]), + and([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q2, q5 + 1] -> + x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q2, q5] + | q5 : int(1..2)]) + | q2 : int(1..2)]), + and([sum([toInt(x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q2, q6]) | q6 : int(1..3)]) <= 3 | q2 : int(1..2)]), + [x_ExplicitR6_ExplicitVarSizeWithDummy[1, q16] | q16 : int(1..3)] + x_ExplicitR6_ExplicitVarSizeWithDummy[q11, q13 + 1] = 3 + | q13 : int(1..2)]) + | q11 : int(1..2)]), + and([sum([toInt(x_ExplicitR6_ExplicitVarSizeWithDummy[q11, q14] != 3) | q14 : int(1..3)]) <= 3 | q11 : int(1..2)]), + and([or([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q21, q23] -> + or([x_ExplicitR6_ExplicitVarSizeWithDummy[q19, q25] != 3 /\ + x_ExplicitR6_ExplicitVarSizeWithDummy[q19, q25] = + x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q21, q23] + | q25 : int(1..3)]) + | q23 : int(1..3)]) + /\ + and([x_ExplicitR6_ExplicitVarSizeWithDummy[q19, q27] != 3 -> + or([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q21, q29] /\ + x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q21, q29] = + x_ExplicitR6_ExplicitVarSizeWithDummy[q19, q27] + | q29 : int(1..3)]) + | q27 : int(1..3)]) + | q21 : int(1..2)]) + | q19 : int(1..2)]), + and([or([and([x_ExplicitR6_ExplicitVarSizeWithDummy[q33, q35] != 3 -> + or([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q31, q37] /\ + x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q31, q37] = + x_ExplicitR6_ExplicitVarSizeWithDummy[q33, q35] + | q37 : int(1..3)]) + | q35 : int(1..3)]) + /\ + and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q31, q39] -> + or([x_ExplicitR6_ExplicitVarSizeWithDummy[q33, q41] != 3 /\ + x_ExplicitR6_ExplicitVarSizeWithDummy[q33, q41] = + x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q31, q39] + | q41 : int(1..3)]) + | q39 : int(1..3)]) + | q33 : int(1..2)]) + | q31 : int(1..2)]) + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_4_2_3-solution000001.solution b/tests/exhaustive/basic/setOfSet04/expected/model_4_2_3-solution000001.solution new file mode 100644 index 0000000000..3ec452354e --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_4_2_3-solution000001.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{}, {1}} +$ Visualisation for x +$ +$ 1 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_4_2_3-solution000002.solution b/tests/exhaustive/basic/setOfSet04/expected/model_4_2_3-solution000002.solution new file mode 100644 index 0000000000..c8946f3d06 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_4_2_3-solution000002.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{}, {2}} +$ Visualisation for x +$ +$ 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_4_2_3-solution000003.solution b/tests/exhaustive/basic/setOfSet04/expected/model_4_2_3-solution000003.solution new file mode 100644 index 0000000000..a6c0b6a43e --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_4_2_3-solution000003.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{}, {1, 2}} +$ Visualisation for x +$ +$ 1 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_4_2_3-solution000004.solution b/tests/exhaustive/basic/setOfSet04/expected/model_4_2_3-solution000004.solution new file mode 100644 index 0000000000..af16592c51 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_4_2_3-solution000004.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{1}, {2}} +$ Visualisation for x +$ 1 +$ 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_4_2_3-solution000005.solution b/tests/exhaustive/basic/setOfSet04/expected/model_4_2_3-solution000005.solution new file mode 100644 index 0000000000..38937c9389 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_4_2_3-solution000005.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{1}, {1, 2}} +$ Visualisation for x +$ 1 +$ 1 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_4_2_3-solution000006.solution b/tests/exhaustive/basic/setOfSet04/expected/model_4_2_3-solution000006.solution new file mode 100644 index 0000000000..9bf2af0712 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_4_2_3-solution000006.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{1, 2}, {2}} +$ Visualisation for x +$ 1 2 +$ 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_4_3_1-solution000001.solution b/tests/exhaustive/basic/setOfSet04/expected/model_4_3_1-solution000001.solution new file mode 100644 index 0000000000..c8946f3d06 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_4_3_1-solution000001.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{}, {2}} +$ Visualisation for x +$ +$ 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_4_3_1-solution000002.solution b/tests/exhaustive/basic/setOfSet04/expected/model_4_3_1-solution000002.solution new file mode 100644 index 0000000000..3ec452354e --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_4_3_1-solution000002.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{}, {1}} +$ Visualisation for x +$ +$ 1 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_4_3_1-solution000003.solution b/tests/exhaustive/basic/setOfSet04/expected/model_4_3_1-solution000003.solution new file mode 100644 index 0000000000..af16592c51 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_4_3_1-solution000003.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{1}, {2}} +$ Visualisation for x +$ 1 +$ 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_4_3_1-solution000004.solution b/tests/exhaustive/basic/setOfSet04/expected/model_4_3_1-solution000004.solution new file mode 100644 index 0000000000..a6c0b6a43e --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_4_3_1-solution000004.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{}, {1, 2}} +$ Visualisation for x +$ +$ 1 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_4_3_1-solution000005.solution b/tests/exhaustive/basic/setOfSet04/expected/model_4_3_1-solution000005.solution new file mode 100644 index 0000000000..9bf2af0712 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_4_3_1-solution000005.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{1, 2}, {2}} +$ Visualisation for x +$ 1 2 +$ 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_4_3_1-solution000006.solution b/tests/exhaustive/basic/setOfSet04/expected/model_4_3_1-solution000006.solution new file mode 100644 index 0000000000..38937c9389 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_4_3_1-solution000006.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{1}, {1, 2}} +$ Visualisation for x +$ 1 +$ 1 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_4_3_1.eprime.orig b/tests/exhaustive/basic/setOfSet04/expected/model_4_3_1.eprime.orig deleted file mode 100644 index 31077f8cdf..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_4_3_1.eprime.orig +++ /dev/null @@ -1,129 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitR4_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..2), int(1..3)] of bool -find x_ExplicitR4_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..2), int(1..3)] of int(1..2) -find x_ExplicitR5_ExplicitVarSizeWithMarker_Marker: matrix indexed by [int(1..2)] of int(0..3) -find x_ExplicitR5_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..2), int(1..3)] of int(1..2) -find x_ExplicitR2_Occurrence: matrix indexed by [int(1..2), int(1..2)] of bool -branching on - [x_ExplicitR2_Occurrence, x_ExplicitR4_ExplicitVarSizeWithFlags_Flags, x_ExplicitR4_ExplicitVarSizeWithFlags_Values, - x_ExplicitR5_ExplicitVarSizeWithMarker_Marker, x_ExplicitR5_ExplicitVarSizeWithMarker_Values] -such that - flatten([flatten([[-toInt(x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[1, q8]); int(1)], - [x_ExplicitR4_ExplicitVarSizeWithFlags_Values[1, q8]; int(1)]; - int(1..2)]) - | q8 : int(1..3)]) - - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q2, q3] < - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q2, q3 + 1] - | q3 : int(1..2)]) - | q2 : int(1..2)]), - and([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q2, q4] = false -> - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q2, q4] = 1 - | q4 : int(1..3)]) - | q2 : int(1..2)]), - and([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q2, q5 + 1] -> - x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q2, q5] - | q5 : int(1..2)]) - | q2 : int(1..2)]), - and([sum([toInt(x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q2, q6]) | q6 : int(1..3)]) <= 3 | q2 : int(1..2)]), - flatten([[x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[1]; int(1)], - [x_ExplicitR5_ExplicitVarSizeWithMarker_Values[1, q15] | q15 : int(1..3)]; - int(1..2)]) - - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q11, q12] < - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q11, q12 + 1] - | q12 : int(1..2)]) - | q11 : int(1..2)]), - and([and([q13 > x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q11] -> - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q11, q13] = 1 - | q13 : int(1..3)]) - | q11 : int(1..2)]), - and([x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q11] <= 3 | q11 : int(1..2)]), - and([or([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q20, q22] -> - or([q24 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q18] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q18, q24] = - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q20, q22] - | q24 : int(1..3)]) - | q22 : int(1..3)]) - /\ - and([q26 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q18] -> - or([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q20, q28] /\ - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q20, q28] = - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q18, q26] - | q28 : int(1..3)]) - | q26 : int(1..3)]) - | q20 : int(1..2)]) - | q18 : int(1..2)]), - and([or([and([q34 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q32] -> - or([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q30, q36] /\ - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q30, q36] = - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q32, q34] - | q36 : int(1..3)]) - | q34 : int(1..3)]) - /\ - and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q30, q38] -> - or([q40 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q32] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q32, q40] = - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q30, q38] - | q40 : int(1..3)]) - | q38 : int(1..3)]) - | q32 : int(1..2)]) - | q30 : int(1..2)]), - [-toInt(x_ExplicitR2_Occurrence[1, q44]) | q44 : int(1..2)] - x_ExplicitR2_Occurrence[q47, x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q49, q51]] - | q51 : int(1..3)]) - /\ - and([x_ExplicitR2_Occurrence[q47, q52] -> - or([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q49, q54] /\ - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q49, q54] = q52 - | q54 : int(1..3)]) - | q52 : int(1..2)]) - | q49 : int(1..2)]) - | q47 : int(1..2)]), - and([or([and([x_ExplicitR2_Occurrence[q58, q59] -> - or([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q56, q61] /\ - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q56, q61] = q59 - | q61 : int(1..3)]) - | q59 : int(1..2)]) - /\ - and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q56, q63] -> - x_ExplicitR2_Occurrence[q58, x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q56, q63]] - | q63 : int(1..3)]) - | q58 : int(1..2)]) - | q56 : int(1..2)]), - and([or([and([q69 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q67] -> - x_ExplicitR2_Occurrence[q65, x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q67, q69]] - | q69 : int(1..3)]) - /\ - and([x_ExplicitR2_Occurrence[q65, q70] -> - or([q72 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q67] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q67, q72] = q70 - | q72 : int(1..3)]) - | q70 : int(1..2)]) - | q67 : int(1..2)]) - | q65 : int(1..2)]), - and([or([and([x_ExplicitR2_Occurrence[q76, q77] -> - or([q79 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q74] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q74, q79] = q77 - | q79 : int(1..3)]) - | q77 : int(1..2)]) - /\ - and([q81 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q74] -> - x_ExplicitR2_Occurrence[q76, x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q74, q81]] - | q81 : int(1..3)]) - | q76 : int(1..2)]) - | q74 : int(1..2)]) - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_4_3_2-solution000001.solution b/tests/exhaustive/basic/setOfSet04/expected/model_4_3_2-solution000001.solution new file mode 100644 index 0000000000..38937c9389 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_4_3_2-solution000001.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{1}, {1, 2}} +$ Visualisation for x +$ 1 +$ 1 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_4_3_2-solution000002.solution b/tests/exhaustive/basic/setOfSet04/expected/model_4_3_2-solution000002.solution new file mode 100644 index 0000000000..9bf2af0712 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_4_3_2-solution000002.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{1, 2}, {2}} +$ Visualisation for x +$ 1 2 +$ 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_4_3_2-solution000003.solution b/tests/exhaustive/basic/setOfSet04/expected/model_4_3_2-solution000003.solution new file mode 100644 index 0000000000..a6c0b6a43e --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_4_3_2-solution000003.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{}, {1, 2}} +$ Visualisation for x +$ +$ 1 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_4_3_2-solution000004.solution b/tests/exhaustive/basic/setOfSet04/expected/model_4_3_2-solution000004.solution new file mode 100644 index 0000000000..af16592c51 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_4_3_2-solution000004.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{1}, {2}} +$ Visualisation for x +$ 1 +$ 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_4_3_2-solution000005.solution b/tests/exhaustive/basic/setOfSet04/expected/model_4_3_2-solution000005.solution new file mode 100644 index 0000000000..3ec452354e --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_4_3_2-solution000005.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{}, {1}} +$ Visualisation for x +$ +$ 1 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_4_3_2-solution000006.solution b/tests/exhaustive/basic/setOfSet04/expected/model_4_3_2-solution000006.solution new file mode 100644 index 0000000000..c8946f3d06 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_4_3_2-solution000006.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{}, {2}} +$ Visualisation for x +$ +$ 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_4_3_2.eprime.orig b/tests/exhaustive/basic/setOfSet04/expected/model_4_3_2.eprime.orig deleted file mode 100644 index 3fdde0c3fc..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_4_3_2.eprime.orig +++ /dev/null @@ -1,154 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitR4_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..2), int(1..3)] of bool -find x_ExplicitR4_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..2), int(1..3)] of int(1..2) -find x_ExplicitR5_ExplicitVarSizeWithMarker_Marker: matrix indexed by [int(1..2)] of int(0..3) -find x_ExplicitR5_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..2), int(1..3)] of int(1..2) -find x_ExplicitR6_ExplicitVarSizeWithDummy: matrix indexed by [int(1..2), int(1..3)] of int(1..3) -branching on - [x_ExplicitR6_ExplicitVarSizeWithDummy, x_ExplicitR4_ExplicitVarSizeWithFlags_Flags, - x_ExplicitR4_ExplicitVarSizeWithFlags_Values, x_ExplicitR5_ExplicitVarSizeWithMarker_Marker, - x_ExplicitR5_ExplicitVarSizeWithMarker_Values] -such that - flatten([flatten([[-toInt(x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[1, q8]); int(1)], - [x_ExplicitR4_ExplicitVarSizeWithFlags_Values[1, q8]; int(1)]; - int(1..2)]) - | q8 : int(1..3)]) - - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q2, q3] < - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q2, q3 + 1] - | q3 : int(1..2)]) - | q2 : int(1..2)]), - and([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q2, q4] = false -> - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q2, q4] = 1 - | q4 : int(1..3)]) - | q2 : int(1..2)]), - and([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q2, q5 + 1] -> - x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q2, q5] - | q5 : int(1..2)]) - | q2 : int(1..2)]), - and([sum([toInt(x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q2, q6]) | q6 : int(1..3)]) <= 3 | q2 : int(1..2)]), - flatten([[x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[1]; int(1)], - [x_ExplicitR5_ExplicitVarSizeWithMarker_Values[1, q15] | q15 : int(1..3)]; - int(1..2)]) - - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q11, q12] < - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q11, q12 + 1] - | q12 : int(1..2)]) - | q11 : int(1..2)]), - and([and([q13 > x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q11] -> - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q11, q13] = 1 - | q13 : int(1..3)]) - | q11 : int(1..2)]), - and([x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q11] <= 3 | q11 : int(1..2)]), - and([or([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q20, q22] -> - or([q24 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q18] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q18, q24] = - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q20, q22] - | q24 : int(1..3)]) - | q22 : int(1..3)]) - /\ - and([q26 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q18] -> - or([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q20, q28] /\ - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q20, q28] = - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q18, q26] - | q28 : int(1..3)]) - | q26 : int(1..3)]) - | q20 : int(1..2)]) - | q18 : int(1..2)]), - and([or([and([q34 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q32] -> - or([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q30, q36] /\ - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q30, q36] = - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q32, q34] - | q36 : int(1..3)]) - | q34 : int(1..3)]) - /\ - and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q30, q38] -> - or([q40 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q32] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q32, q40] = - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q30, q38] - | q40 : int(1..3)]) - | q38 : int(1..3)]) - | q32 : int(1..2)]) - | q30 : int(1..2)]), - [x_ExplicitR6_ExplicitVarSizeWithDummy[1, q47] | q47 : int(1..3)] - x_ExplicitR6_ExplicitVarSizeWithDummy[q42, q44 + 1] = 3 - | q44 : int(1..2)]) - | q42 : int(1..2)]), - and([sum([toInt(x_ExplicitR6_ExplicitVarSizeWithDummy[q42, q45] != 3) | q45 : int(1..3)]) <= 3 | q42 : int(1..2)]), - and([or([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q52, q54] -> - or([x_ExplicitR6_ExplicitVarSizeWithDummy[q50, q56] != 3 /\ - x_ExplicitR6_ExplicitVarSizeWithDummy[q50, q56] = - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q52, q54] - | q56 : int(1..3)]) - | q54 : int(1..3)]) - /\ - and([x_ExplicitR6_ExplicitVarSizeWithDummy[q50, q58] != 3 -> - or([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q52, q60] /\ - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q52, q60] = - x_ExplicitR6_ExplicitVarSizeWithDummy[q50, q58] - | q60 : int(1..3)]) - | q58 : int(1..3)]) - | q52 : int(1..2)]) - | q50 : int(1..2)]), - and([or([and([x_ExplicitR6_ExplicitVarSizeWithDummy[q64, q66] != 3 -> - or([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q62, q68] /\ - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q62, q68] = - x_ExplicitR6_ExplicitVarSizeWithDummy[q64, q66] - | q68 : int(1..3)]) - | q66 : int(1..3)]) - /\ - and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q62, q70] -> - or([x_ExplicitR6_ExplicitVarSizeWithDummy[q64, q72] != 3 /\ - x_ExplicitR6_ExplicitVarSizeWithDummy[q64, q72] = - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q62, q70] - | q72 : int(1..3)]) - | q70 : int(1..3)]) - | q64 : int(1..2)]) - | q62 : int(1..2)]), - and([or([and([q78 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q76] -> - or([x_ExplicitR6_ExplicitVarSizeWithDummy[q74, q80] != 3 /\ - x_ExplicitR6_ExplicitVarSizeWithDummy[q74, q80] = - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q76, q78] - | q80 : int(1..3)]) - | q78 : int(1..3)]) - /\ - and([x_ExplicitR6_ExplicitVarSizeWithDummy[q74, q82] != 3 -> - or([q84 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q76] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q76, q84] = - x_ExplicitR6_ExplicitVarSizeWithDummy[q74, q82] - | q84 : int(1..3)]) - | q82 : int(1..3)]) - | q76 : int(1..2)]) - | q74 : int(1..2)]), - and([or([and([x_ExplicitR6_ExplicitVarSizeWithDummy[q88, q90] != 3 -> - or([q92 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q86] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q86, q92] = - x_ExplicitR6_ExplicitVarSizeWithDummy[q88, q90] - | q92 : int(1..3)]) - | q90 : int(1..3)]) - /\ - and([q94 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q86] -> - or([x_ExplicitR6_ExplicitVarSizeWithDummy[q88, q96] != 3 /\ - x_ExplicitR6_ExplicitVarSizeWithDummy[q88, q96] = - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q86, q94] - | q96 : int(1..3)]) - | q94 : int(1..3)]) - | q88 : int(1..2)]) - | q86 : int(1..2)]) - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_4_3_3-solution000001.solution b/tests/exhaustive/basic/setOfSet04/expected/model_4_3_3-solution000001.solution new file mode 100644 index 0000000000..3ec452354e --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_4_3_3-solution000001.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{}, {1}} +$ Visualisation for x +$ +$ 1 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_4_3_3-solution000002.solution b/tests/exhaustive/basic/setOfSet04/expected/model_4_3_3-solution000002.solution new file mode 100644 index 0000000000..c8946f3d06 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_4_3_3-solution000002.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{}, {2}} +$ Visualisation for x +$ +$ 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_4_3_3-solution000003.solution b/tests/exhaustive/basic/setOfSet04/expected/model_4_3_3-solution000003.solution new file mode 100644 index 0000000000..a6c0b6a43e --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_4_3_3-solution000003.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{}, {1, 2}} +$ Visualisation for x +$ +$ 1 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_4_3_3-solution000004.solution b/tests/exhaustive/basic/setOfSet04/expected/model_4_3_3-solution000004.solution new file mode 100644 index 0000000000..af16592c51 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_4_3_3-solution000004.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{1}, {2}} +$ Visualisation for x +$ 1 +$ 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_4_3_3-solution000005.solution b/tests/exhaustive/basic/setOfSet04/expected/model_4_3_3-solution000005.solution new file mode 100644 index 0000000000..38937c9389 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_4_3_3-solution000005.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{1}, {1, 2}} +$ Visualisation for x +$ 1 +$ 1 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_4_3_3-solution000006.solution b/tests/exhaustive/basic/setOfSet04/expected/model_4_3_3-solution000006.solution new file mode 100644 index 0000000000..9bf2af0712 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_4_3_3-solution000006.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{1, 2}, {2}} +$ Visualisation for x +$ 1 2 +$ 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_4_3_3.eprime.orig b/tests/exhaustive/basic/setOfSet04/expected/model_4_3_3.eprime.orig deleted file mode 100644 index 2987d02ac0..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_4_3_3.eprime.orig +++ /dev/null @@ -1,81 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitR4_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..2), int(1..3)] of bool -find x_ExplicitR4_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..2), int(1..3)] of int(1..2) -find x_ExplicitR5_ExplicitVarSizeWithMarker_Marker: matrix indexed by [int(1..2)] of int(0..3) -find x_ExplicitR5_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..2), int(1..3)] of int(1..2) -branching on - [x_ExplicitR5_ExplicitVarSizeWithMarker_Marker, x_ExplicitR5_ExplicitVarSizeWithMarker_Values, - x_ExplicitR4_ExplicitVarSizeWithFlags_Flags, x_ExplicitR4_ExplicitVarSizeWithFlags_Values] -such that - flatten([flatten([[-toInt(x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[1, q8]); int(1)], - [x_ExplicitR4_ExplicitVarSizeWithFlags_Values[1, q8]; int(1)]; - int(1..2)]) - | q8 : int(1..3)]) - - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q2, q3] < - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q2, q3 + 1] - | q3 : int(1..2)]) - | q2 : int(1..2)]), - and([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q2, q4] = false -> - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q2, q4] = 1 - | q4 : int(1..3)]) - | q2 : int(1..2)]), - and([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q2, q5 + 1] -> - x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q2, q5] - | q5 : int(1..2)]) - | q2 : int(1..2)]), - and([sum([toInt(x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q2, q6]) | q6 : int(1..3)]) <= 3 | q2 : int(1..2)]), - flatten([[x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[1]; int(1)], - [x_ExplicitR5_ExplicitVarSizeWithMarker_Values[1, q15] | q15 : int(1..3)]; - int(1..2)]) - - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q11, q12] < - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q11, q12 + 1] - | q12 : int(1..2)]) - | q11 : int(1..2)]), - and([and([q13 > x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q11] -> - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q11, q13] = 1 - | q13 : int(1..3)]) - | q11 : int(1..2)]), - and([x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q11] <= 3 | q11 : int(1..2)]), - and([or([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q20, q22] -> - or([q24 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q18] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q18, q24] = - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q20, q22] - | q24 : int(1..3)]) - | q22 : int(1..3)]) - /\ - and([q26 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q18] -> - or([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q20, q28] /\ - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q20, q28] = - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q18, q26] - | q28 : int(1..3)]) - | q26 : int(1..3)]) - | q20 : int(1..2)]) - | q18 : int(1..2)]), - and([or([and([q34 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q32] -> - or([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q30, q36] /\ - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q30, q36] = - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q32, q34] - | q36 : int(1..3)]) - | q34 : int(1..3)]) - /\ - and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q30, q38] -> - or([q40 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q32] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q32, q40] = - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q30, q38] - | q40 : int(1..3)]) - | q38 : int(1..3)]) - | q32 : int(1..2)]) - | q30 : int(1..2)]) - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_4_3_4.eprime.orig b/tests/exhaustive/basic/setOfSet04/expected/model_4_3_4.eprime.orig deleted file mode 100644 index 2987d02ac0..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_4_3_4.eprime.orig +++ /dev/null @@ -1,81 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitR4_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..2), int(1..3)] of bool -find x_ExplicitR4_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..2), int(1..3)] of int(1..2) -find x_ExplicitR5_ExplicitVarSizeWithMarker_Marker: matrix indexed by [int(1..2)] of int(0..3) -find x_ExplicitR5_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..2), int(1..3)] of int(1..2) -branching on - [x_ExplicitR5_ExplicitVarSizeWithMarker_Marker, x_ExplicitR5_ExplicitVarSizeWithMarker_Values, - x_ExplicitR4_ExplicitVarSizeWithFlags_Flags, x_ExplicitR4_ExplicitVarSizeWithFlags_Values] -such that - flatten([flatten([[-toInt(x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[1, q8]); int(1)], - [x_ExplicitR4_ExplicitVarSizeWithFlags_Values[1, q8]; int(1)]; - int(1..2)]) - | q8 : int(1..3)]) - - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q2, q3] < - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q2, q3 + 1] - | q3 : int(1..2)]) - | q2 : int(1..2)]), - and([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q2, q4] = false -> - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q2, q4] = 1 - | q4 : int(1..3)]) - | q2 : int(1..2)]), - and([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q2, q5 + 1] -> - x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q2, q5] - | q5 : int(1..2)]) - | q2 : int(1..2)]), - and([sum([toInt(x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q2, q6]) | q6 : int(1..3)]) <= 3 | q2 : int(1..2)]), - flatten([[x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[1]; int(1)], - [x_ExplicitR5_ExplicitVarSizeWithMarker_Values[1, q15] | q15 : int(1..3)]; - int(1..2)]) - - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q11, q12] < - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q11, q12 + 1] - | q12 : int(1..2)]) - | q11 : int(1..2)]), - and([and([q13 > x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q11] -> - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q11, q13] = 1 - | q13 : int(1..3)]) - | q11 : int(1..2)]), - and([x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q11] <= 3 | q11 : int(1..2)]), - and([or([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q20, q22] -> - or([q24 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q18] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q18, q24] = - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q20, q22] - | q24 : int(1..3)]) - | q22 : int(1..3)]) - /\ - and([q26 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q18] -> - or([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q20, q28] /\ - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q20, q28] = - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q18, q26] - | q28 : int(1..3)]) - | q26 : int(1..3)]) - | q20 : int(1..2)]) - | q18 : int(1..2)]), - and([or([and([q34 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q32] -> - or([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q30, q36] /\ - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q30, q36] = - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q32, q34] - | q36 : int(1..3)]) - | q34 : int(1..3)]) - /\ - and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q30, q38] -> - or([q40 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q32] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q32, q40] = - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q30, q38] - | q40 : int(1..3)]) - | q38 : int(1..3)]) - | q32 : int(1..2)]) - | q30 : int(1..2)]) - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_4_4_3.eprime.orig b/tests/exhaustive/basic/setOfSet04/expected/model_4_4_3.eprime.orig deleted file mode 100644 index 2987d02ac0..0000000000 --- a/tests/exhaustive/basic/setOfSet04/expected/model_4_4_3.eprime.orig +++ /dev/null @@ -1,81 +0,0 @@ -language ESSENCE' 1.0 - -find x_ExplicitR4_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..2), int(1..3)] of bool -find x_ExplicitR4_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..2), int(1..3)] of int(1..2) -find x_ExplicitR5_ExplicitVarSizeWithMarker_Marker: matrix indexed by [int(1..2)] of int(0..3) -find x_ExplicitR5_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..2), int(1..3)] of int(1..2) -branching on - [x_ExplicitR5_ExplicitVarSizeWithMarker_Marker, x_ExplicitR5_ExplicitVarSizeWithMarker_Values, - x_ExplicitR4_ExplicitVarSizeWithFlags_Flags, x_ExplicitR4_ExplicitVarSizeWithFlags_Values] -such that - flatten([flatten([[-toInt(x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[1, q8]); int(1)], - [x_ExplicitR4_ExplicitVarSizeWithFlags_Values[1, q8]; int(1)]; - int(1..2)]) - | q8 : int(1..3)]) - - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q2, q3] < - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q2, q3 + 1] - | q3 : int(1..2)]) - | q2 : int(1..2)]), - and([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q2, q4] = false -> - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q2, q4] = 1 - | q4 : int(1..3)]) - | q2 : int(1..2)]), - and([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q2, q5 + 1] -> - x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q2, q5] - | q5 : int(1..2)]) - | q2 : int(1..2)]), - and([sum([toInt(x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q2, q6]) | q6 : int(1..3)]) <= 3 | q2 : int(1..2)]), - flatten([[x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[1]; int(1)], - [x_ExplicitR5_ExplicitVarSizeWithMarker_Values[1, q15] | q15 : int(1..3)]; - int(1..2)]) - - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q11, q12] < - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q11, q12 + 1] - | q12 : int(1..2)]) - | q11 : int(1..2)]), - and([and([q13 > x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q11] -> - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q11, q13] = 1 - | q13 : int(1..3)]) - | q11 : int(1..2)]), - and([x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q11] <= 3 | q11 : int(1..2)]), - and([or([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q20, q22] -> - or([q24 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q18] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q18, q24] = - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q20, q22] - | q24 : int(1..3)]) - | q22 : int(1..3)]) - /\ - and([q26 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q18] -> - or([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q20, q28] /\ - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q20, q28] = - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q18, q26] - | q28 : int(1..3)]) - | q26 : int(1..3)]) - | q20 : int(1..2)]) - | q18 : int(1..2)]), - and([or([and([q34 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q32] -> - or([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q30, q36] /\ - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q30, q36] = - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q32, q34] - | q36 : int(1..3)]) - | q34 : int(1..3)]) - /\ - and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q30, q38] -> - or([q40 <= x_ExplicitR5_ExplicitVarSizeWithMarker_Marker[q32] /\ - x_ExplicitR5_ExplicitVarSizeWithMarker_Values[q32, q40] = - x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q30, q38] - | q40 : int(1..3)]) - | q38 : int(1..3)]) - | q32 : int(1..2)]) - | q30 : int(1..2)]) - diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_4_4_4-solution000001.solution b/tests/exhaustive/basic/setOfSet04/expected/model_4_4_4-solution000001.solution new file mode 100644 index 0000000000..3ec452354e --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_4_4_4-solution000001.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{}, {1}} +$ Visualisation for x +$ +$ 1 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_4_4_4-solution000002.solution b/tests/exhaustive/basic/setOfSet04/expected/model_4_4_4-solution000002.solution new file mode 100644 index 0000000000..c8946f3d06 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_4_4_4-solution000002.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{}, {2}} +$ Visualisation for x +$ +$ 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_4_4_4-solution000003.solution b/tests/exhaustive/basic/setOfSet04/expected/model_4_4_4-solution000003.solution new file mode 100644 index 0000000000..af16592c51 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_4_4_4-solution000003.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{1}, {2}} +$ Visualisation for x +$ 1 +$ 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_4_4_4-solution000004.solution b/tests/exhaustive/basic/setOfSet04/expected/model_4_4_4-solution000004.solution new file mode 100644 index 0000000000..a6c0b6a43e --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_4_4_4-solution000004.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{}, {1, 2}} +$ Visualisation for x +$ +$ 1 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_4_4_4-solution000005.solution b/tests/exhaustive/basic/setOfSet04/expected/model_4_4_4-solution000005.solution new file mode 100644 index 0000000000..38937c9389 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_4_4_4-solution000005.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{1}, {1, 2}} +$ Visualisation for x +$ 1 +$ 1 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_4_4_4-solution000006.solution b/tests/exhaustive/basic/setOfSet04/expected/model_4_4_4-solution000006.solution new file mode 100644 index 0000000000..9bf2af0712 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_4_4_4-solution000006.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting x be {{1, 2}, {2}} +$ Visualisation for x +$ 1 2 +$ 2 + diff --git a/tests/exhaustive/basic/setOfSet04/expected/model_4_4_4.eprime b/tests/exhaustive/basic/setOfSet04/expected/model_4_4_4.eprime new file mode 100644 index 0000000000..5fc6546276 --- /dev/null +++ b/tests/exhaustive/basic/setOfSet04/expected/model_4_4_4.eprime @@ -0,0 +1,30 @@ +language ESSENCE' 1.0 + +find x_ExplicitR4_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..2), int(1..3)] of bool +find x_ExplicitR4_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..2), int(1..3)] of int(1..2) +branching on [x_ExplicitR4_ExplicitVarSizeWithFlags_Flags, x_ExplicitR4_ExplicitVarSizeWithFlags_Values] +such that + flatten([flatten([[-toInt(x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[1, q8]); int(1)], + [x_ExplicitR4_ExplicitVarSizeWithFlags_Values[1, q8]; int(1)]; + int(1..2)]) + | q8 : int(1..3)]) + + x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q2, q3] < + x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q2, q3 + 1] + | q3 : int(1..2)]) + | q2 : int(1..2)]), + and([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q2, q4] = false -> + x_ExplicitR4_ExplicitVarSizeWithFlags_Values[q2, q4] = 1 + | q4 : int(1..3)]) + | q2 : int(1..2)]), + and([and([x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q2, q5 + 1] -> + x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q2, q5] + | q5 : int(1..2)]) + | q2 : int(1..2)]), + and([sum([toInt(x_ExplicitR4_ExplicitVarSizeWithFlags_Flags[q2, q6]) | q6 : int(1..3)]) <= 3 | q2 : int(1..2)]) + diff --git a/tests/exhaustive/basic/set_card_00/expected/model_1_1_1-solution000001.solution b/tests/exhaustive/basic/set_card_00/expected/model_1_1_1-solution000001.solution new file mode 100644 index 0000000000..6c0d0fdad8 --- /dev/null +++ b/tests/exhaustive/basic/set_card_00/expected/model_1_1_1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting s be {1} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_1_1_1-solution000002.solution b/tests/exhaustive/basic/set_card_00/expected/model_1_1_1-solution000002.solution new file mode 100644 index 0000000000..2ce5f2081f --- /dev/null +++ b/tests/exhaustive/basic/set_card_00/expected/model_1_1_1-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting s be {1, 2} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_1_1_1.eprime b/tests/exhaustive/basic/set_card_00/expected/model_1_1_1.eprime new file mode 100644 index 0000000000..8f7d21c6a2 --- /dev/null +++ b/tests/exhaustive/basic/set_card_00/expected/model_1_1_1.eprime @@ -0,0 +1,6 @@ +language ESSENCE' 1.0 + +find s_Occurrence: matrix indexed by [int(1..2)] of bool +branching on [s_Occurrence] +such that s_Occurrence[sum([toInt(s_Occurrence[q2]) | q2 : int(1..2)])] + diff --git a/tests/exhaustive/basic/set_card_00/expected/model_1_1_2-solution000001.solution b/tests/exhaustive/basic/set_card_00/expected/model_1_1_2-solution000001.solution new file mode 100644 index 0000000000..2ce5f2081f --- /dev/null +++ b/tests/exhaustive/basic/set_card_00/expected/model_1_1_2-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting s be {1, 2} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_1_1_2-solution000002.solution b/tests/exhaustive/basic/set_card_00/expected/model_1_1_2-solution000002.solution new file mode 100644 index 0000000000..6c0d0fdad8 --- /dev/null +++ b/tests/exhaustive/basic/set_card_00/expected/model_1_1_2-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting s be {1} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_1_1_2.eprime b/tests/exhaustive/basic/set_card_00/expected/model_1_1_2.eprime new file mode 100644 index 0000000000..854db40dcb --- /dev/null +++ b/tests/exhaustive/basic/set_card_00/expected/model_1_1_2.eprime @@ -0,0 +1,14 @@ +language ESSENCE' 1.0 + +find s_Occurrence: matrix indexed by [int(1..2)] of bool +find s_ExplicitVarSizeWithDummy: matrix indexed by [int(1..2)] of int(1..3) +branching on [s_ExplicitVarSizeWithDummy, s_Occurrence] +such that + s_Occurrence[sum([toInt(s_Occurrence[q11]) | q11 : int(1..2)])], + s_ExplicitVarSizeWithDummy[1] < s_ExplicitVarSizeWithDummy[2] \/ s_ExplicitVarSizeWithDummy[1] = 3, + s_ExplicitVarSizeWithDummy[1] = 3 -> s_ExplicitVarSizeWithDummy[2] = 3, + and([s_ExplicitVarSizeWithDummy[q7] != 3 -> s_Occurrence[s_ExplicitVarSizeWithDummy[q7]] | q7 : int(1..2)]), + and([s_Occurrence[q8] -> + or([s_ExplicitVarSizeWithDummy[q10] != 3 /\ s_ExplicitVarSizeWithDummy[q10] = q8 | q10 : int(1..2)]) + | q8 : int(1..2)]) + diff --git a/tests/exhaustive/basic/set_card_00/expected/model_1_1_3-solution000001.solution b/tests/exhaustive/basic/set_card_00/expected/model_1_1_3-solution000001.solution new file mode 100644 index 0000000000..6c0d0fdad8 --- /dev/null +++ b/tests/exhaustive/basic/set_card_00/expected/model_1_1_3-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting s be {1} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_1_1_3-solution000002.solution b/tests/exhaustive/basic/set_card_00/expected/model_1_1_3-solution000002.solution new file mode 100644 index 0000000000..2ce5f2081f --- /dev/null +++ b/tests/exhaustive/basic/set_card_00/expected/model_1_1_3-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting s be {1, 2} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_1_1_3.eprime b/tests/exhaustive/basic/set_card_00/expected/model_1_1_3.eprime new file mode 100644 index 0000000000..85f5801f04 --- /dev/null +++ b/tests/exhaustive/basic/set_card_00/expected/model_1_1_3.eprime @@ -0,0 +1,17 @@ +language ESSENCE' 1.0 + +find s_Occurrence: matrix indexed by [int(1..2)] of bool +find s_ExplicitVarSizeWithMarker_Marker: int(0..2) +find s_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..2)] of int(1..2) +branching on [s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithMarker_Values, s_Occurrence] +such that + s_Occurrence[sum([toInt(s_Occurrence[q10]) | q10 : int(1..2)])], + 2 <= s_ExplicitVarSizeWithMarker_Marker -> + s_ExplicitVarSizeWithMarker_Values[1] < s_ExplicitVarSizeWithMarker_Values[2], + and([q3 > s_ExplicitVarSizeWithMarker_Marker -> s_ExplicitVarSizeWithMarker_Values[q3] = 1 | q3 : int(1..2)]), + and([q6 <= s_ExplicitVarSizeWithMarker_Marker -> s_Occurrence[s_ExplicitVarSizeWithMarker_Values[q6]] + | q6 : int(1..2)]), + and([s_Occurrence[q7] -> + or([q9 <= s_ExplicitVarSizeWithMarker_Marker /\ s_ExplicitVarSizeWithMarker_Values[q9] = q7 | q9 : int(1..2)]) + | q7 : int(1..2)]) + diff --git a/tests/exhaustive/basic/set_card_00/expected/model_1_1_4-solution000001.solution b/tests/exhaustive/basic/set_card_00/expected/model_1_1_4-solution000001.solution new file mode 100644 index 0000000000..6c0d0fdad8 --- /dev/null +++ b/tests/exhaustive/basic/set_card_00/expected/model_1_1_4-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting s be {1} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_1_1_4-solution000002.solution b/tests/exhaustive/basic/set_card_00/expected/model_1_1_4-solution000002.solution new file mode 100644 index 0000000000..2ce5f2081f --- /dev/null +++ b/tests/exhaustive/basic/set_card_00/expected/model_1_1_4-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting s be {1, 2} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_1_1_4.eprime b/tests/exhaustive/basic/set_card_00/expected/model_1_1_4.eprime new file mode 100644 index 0000000000..3dd8d91baa --- /dev/null +++ b/tests/exhaustive/basic/set_card_00/expected/model_1_1_4.eprime @@ -0,0 +1,16 @@ +language ESSENCE' 1.0 + +find s_Occurrence: matrix indexed by [int(1..2)] of bool +find s_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..2)] of bool +find s_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..2)] of int(1..2) +branching on [s_ExplicitVarSizeWithFlags_Flags, s_ExplicitVarSizeWithFlags_Values, s_Occurrence] +such that + s_Occurrence[sum([toInt(s_Occurrence[q12]) | q12 : int(1..2)])], + s_ExplicitVarSizeWithFlags_Flags[2] -> s_ExplicitVarSizeWithFlags_Values[1] < s_ExplicitVarSizeWithFlags_Values[2], + and([s_ExplicitVarSizeWithFlags_Flags[q3] = false -> s_ExplicitVarSizeWithFlags_Values[q3] = 1 | q3 : int(1..2)]), + s_ExplicitVarSizeWithFlags_Flags[2] -> s_ExplicitVarSizeWithFlags_Flags[1], + and([s_ExplicitVarSizeWithFlags_Flags[q8] -> s_Occurrence[s_ExplicitVarSizeWithFlags_Values[q8]] | q8 : int(1..2)]), + and([s_Occurrence[q9] -> + or([s_ExplicitVarSizeWithFlags_Flags[q11] /\ s_ExplicitVarSizeWithFlags_Values[q11] = q9 | q11 : int(1..2)]) + | q9 : int(1..2)]) + diff --git a/tests/exhaustive/basic/set_card_00/expected/model_1_2_1-solution000001.solution b/tests/exhaustive/basic/set_card_00/expected/model_1_2_1-solution000001.solution new file mode 100644 index 0000000000..2ce5f2081f --- /dev/null +++ b/tests/exhaustive/basic/set_card_00/expected/model_1_2_1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting s be {1, 2} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_1_2_1-solution000002.solution b/tests/exhaustive/basic/set_card_00/expected/model_1_2_1-solution000002.solution new file mode 100644 index 0000000000..6c0d0fdad8 --- /dev/null +++ b/tests/exhaustive/basic/set_card_00/expected/model_1_2_1-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting s be {1} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_1_2_1.eprime b/tests/exhaustive/basic/set_card_00/expected/model_1_2_1.eprime new file mode 100644 index 0000000000..ed16639077 --- /dev/null +++ b/tests/exhaustive/basic/set_card_00/expected/model_1_2_1.eprime @@ -0,0 +1,16 @@ +language ESSENCE' 1.0 + +find s_Occurrence: matrix indexed by [int(1..2)] of bool +find s_ExplicitVarSizeWithDummy: matrix indexed by [int(1..2)] of int(1..3) +branching on [s_ExplicitVarSizeWithDummy, s_Occurrence] +such that + or([s_ExplicitVarSizeWithDummy[q12] != 3 /\ + s_ExplicitVarSizeWithDummy[q12] = sum([toInt(s_Occurrence[q13]) | q13 : int(1..2)]) + | q12 : int(1..2)]), + s_ExplicitVarSizeWithDummy[1] < s_ExplicitVarSizeWithDummy[2] \/ s_ExplicitVarSizeWithDummy[1] = 3, + s_ExplicitVarSizeWithDummy[1] = 3 -> s_ExplicitVarSizeWithDummy[2] = 3, + and([s_ExplicitVarSizeWithDummy[q7] != 3 -> s_Occurrence[s_ExplicitVarSizeWithDummy[q7]] | q7 : int(1..2)]), + and([s_Occurrence[q8] -> + or([s_ExplicitVarSizeWithDummy[q10] != 3 /\ s_ExplicitVarSizeWithDummy[q10] = q8 | q10 : int(1..2)]) + | q8 : int(1..2)]) + diff --git a/tests/exhaustive/basic/set_card_00/expected/model_1_2_3-solution000001.solution b/tests/exhaustive/basic/set_card_00/expected/model_1_2_3-solution000001.solution new file mode 100644 index 0000000000..6c0d0fdad8 --- /dev/null +++ b/tests/exhaustive/basic/set_card_00/expected/model_1_2_3-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting s be {1} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_1_2_3-solution000002.solution b/tests/exhaustive/basic/set_card_00/expected/model_1_2_3-solution000002.solution new file mode 100644 index 0000000000..2ce5f2081f --- /dev/null +++ b/tests/exhaustive/basic/set_card_00/expected/model_1_2_3-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting s be {1, 2} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_1_2_3.eprime b/tests/exhaustive/basic/set_card_00/expected/model_1_2_3.eprime new file mode 100644 index 0000000000..aee5d0059e --- /dev/null +++ b/tests/exhaustive/basic/set_card_00/expected/model_1_2_3.eprime @@ -0,0 +1,38 @@ +language ESSENCE' 1.0 + +find s_Occurrence: matrix indexed by [int(1..2)] of bool +find s_ExplicitVarSizeWithDummy: matrix indexed by [int(1..2)] of int(1..3) +find s_ExplicitVarSizeWithMarker_Marker: int(0..2) +find s_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..2)] of int(1..2) +branching on + [s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithMarker_Values, s_Occurrence, s_ExplicitVarSizeWithDummy] +such that + or([s_ExplicitVarSizeWithDummy[q28] != 3 /\ + s_ExplicitVarSizeWithDummy[q28] = sum([toInt(s_Occurrence[q29]) | q29 : int(1..2)]) + | q28 : int(1..2)]), + s_ExplicitVarSizeWithDummy[1] < s_ExplicitVarSizeWithDummy[2] \/ s_ExplicitVarSizeWithDummy[1] = 3, + s_ExplicitVarSizeWithDummy[1] = 3 -> s_ExplicitVarSizeWithDummy[2] = 3, + and([s_ExplicitVarSizeWithDummy[q7] != 3 -> s_Occurrence[s_ExplicitVarSizeWithDummy[q7]] | q7 : int(1..2)]), + and([s_Occurrence[q8] -> + or([s_ExplicitVarSizeWithDummy[q10] != 3 /\ s_ExplicitVarSizeWithDummy[q10] = q8 | q10 : int(1..2)]) + | q8 : int(1..2)]), + 2 <= s_ExplicitVarSizeWithMarker_Marker -> + s_ExplicitVarSizeWithMarker_Values[1] < s_ExplicitVarSizeWithMarker_Values[2], + and([q12 > s_ExplicitVarSizeWithMarker_Marker -> s_ExplicitVarSizeWithMarker_Values[q12] = 1 | q12 : int(1..2)]), + and([q15 <= s_ExplicitVarSizeWithMarker_Marker -> s_Occurrence[s_ExplicitVarSizeWithMarker_Values[q15]] + | q15 : int(1..2)]), + and([s_Occurrence[q16] -> + or([q18 <= s_ExplicitVarSizeWithMarker_Marker /\ s_ExplicitVarSizeWithMarker_Values[q18] = q16 + | q18 : int(1..2)]) + | q16 : int(1..2)]), + and([q20 <= s_ExplicitVarSizeWithMarker_Marker -> + or([s_ExplicitVarSizeWithDummy[q22] != 3 /\ + s_ExplicitVarSizeWithDummy[q22] = s_ExplicitVarSizeWithMarker_Values[q20] + | q22 : int(1..2)]) + | q20 : int(1..2)]), + and([s_ExplicitVarSizeWithDummy[q24] != 3 -> + or([q26 <= s_ExplicitVarSizeWithMarker_Marker /\ + s_ExplicitVarSizeWithMarker_Values[q26] = s_ExplicitVarSizeWithDummy[q24] + | q26 : int(1..2)]) + | q24 : int(1..2)]) + diff --git a/tests/exhaustive/basic/set_card_00/expected/model_1_2_4-solution000001.solution b/tests/exhaustive/basic/set_card_00/expected/model_1_2_4-solution000001.solution new file mode 100644 index 0000000000..6c0d0fdad8 --- /dev/null +++ b/tests/exhaustive/basic/set_card_00/expected/model_1_2_4-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting s be {1} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_1_2_4-solution000002.solution b/tests/exhaustive/basic/set_card_00/expected/model_1_2_4-solution000002.solution new file mode 100644 index 0000000000..2ce5f2081f --- /dev/null +++ b/tests/exhaustive/basic/set_card_00/expected/model_1_2_4-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting s be {1, 2} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_1_2_4.eprime b/tests/exhaustive/basic/set_card_00/expected/model_1_2_4.eprime new file mode 100644 index 0000000000..eb6c8281e0 --- /dev/null +++ b/tests/exhaustive/basic/set_card_00/expected/model_1_2_4.eprime @@ -0,0 +1,38 @@ +language ESSENCE' 1.0 + +find s_Occurrence: matrix indexed by [int(1..2)] of bool +find s_ExplicitVarSizeWithDummy: matrix indexed by [int(1..2)] of int(1..3) +find s_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..2)] of bool +find s_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..2)] of int(1..2) +branching on + [s_ExplicitVarSizeWithFlags_Flags, s_ExplicitVarSizeWithFlags_Values, s_Occurrence, s_ExplicitVarSizeWithDummy] +such that + or([s_ExplicitVarSizeWithDummy[q30] != 3 /\ + s_ExplicitVarSizeWithDummy[q30] = sum([toInt(s_Occurrence[q31]) | q31 : int(1..2)]) + | q30 : int(1..2)]), + s_ExplicitVarSizeWithDummy[1] < s_ExplicitVarSizeWithDummy[2] \/ s_ExplicitVarSizeWithDummy[1] = 3, + s_ExplicitVarSizeWithDummy[1] = 3 -> s_ExplicitVarSizeWithDummy[2] = 3, + and([s_ExplicitVarSizeWithDummy[q7] != 3 -> s_Occurrence[s_ExplicitVarSizeWithDummy[q7]] | q7 : int(1..2)]), + and([s_Occurrence[q8] -> + or([s_ExplicitVarSizeWithDummy[q10] != 3 /\ s_ExplicitVarSizeWithDummy[q10] = q8 | q10 : int(1..2)]) + | q8 : int(1..2)]), + s_ExplicitVarSizeWithFlags_Flags[2] -> s_ExplicitVarSizeWithFlags_Values[1] < s_ExplicitVarSizeWithFlags_Values[2], + and([s_ExplicitVarSizeWithFlags_Flags[q12] = false -> s_ExplicitVarSizeWithFlags_Values[q12] = 1 + | q12 : int(1..2)]), + s_ExplicitVarSizeWithFlags_Flags[2] -> s_ExplicitVarSizeWithFlags_Flags[1], + and([s_ExplicitVarSizeWithFlags_Flags[q17] -> s_Occurrence[s_ExplicitVarSizeWithFlags_Values[q17]] + | q17 : int(1..2)]), + and([s_Occurrence[q18] -> + or([s_ExplicitVarSizeWithFlags_Flags[q20] /\ s_ExplicitVarSizeWithFlags_Values[q20] = q18 | q20 : int(1..2)]) + | q18 : int(1..2)]), + and([s_ExplicitVarSizeWithFlags_Flags[q22] -> + or([s_ExplicitVarSizeWithDummy[q24] != 3 /\ + s_ExplicitVarSizeWithDummy[q24] = s_ExplicitVarSizeWithFlags_Values[q22] + | q24 : int(1..2)]) + | q22 : int(1..2)]), + and([s_ExplicitVarSizeWithDummy[q26] != 3 -> + or([s_ExplicitVarSizeWithFlags_Flags[q28] /\ + s_ExplicitVarSizeWithFlags_Values[q28] = s_ExplicitVarSizeWithDummy[q26] + | q28 : int(1..2)]) + | q26 : int(1..2)]) + diff --git a/tests/exhaustive/basic/set_card_00/expected/model_1_3_1-solution000001.solution b/tests/exhaustive/basic/set_card_00/expected/model_1_3_1-solution000001.solution new file mode 100644 index 0000000000..6c0d0fdad8 --- /dev/null +++ b/tests/exhaustive/basic/set_card_00/expected/model_1_3_1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting s be {1} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_1_3_1-solution000002.solution b/tests/exhaustive/basic/set_card_00/expected/model_1_3_1-solution000002.solution new file mode 100644 index 0000000000..2ce5f2081f --- /dev/null +++ b/tests/exhaustive/basic/set_card_00/expected/model_1_3_1-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting s be {1, 2} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_1_3_1.eprime b/tests/exhaustive/basic/set_card_00/expected/model_1_3_1.eprime new file mode 100644 index 0000000000..a11ed0ff5f --- /dev/null +++ b/tests/exhaustive/basic/set_card_00/expected/model_1_3_1.eprime @@ -0,0 +1,19 @@ +language ESSENCE' 1.0 + +find s_Occurrence: matrix indexed by [int(1..2)] of bool +find s_ExplicitVarSizeWithMarker_Marker: int(0..2) +find s_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..2)] of int(1..2) +branching on [s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithMarker_Values, s_Occurrence] +such that + or([q11 <= s_ExplicitVarSizeWithMarker_Marker /\ + s_ExplicitVarSizeWithMarker_Values[q11] = sum([toInt(s_Occurrence[q12]) | q12 : int(1..2)]) + | q11 : int(1..2)]), + 2 <= s_ExplicitVarSizeWithMarker_Marker -> + s_ExplicitVarSizeWithMarker_Values[1] < s_ExplicitVarSizeWithMarker_Values[2], + and([q3 > s_ExplicitVarSizeWithMarker_Marker -> s_ExplicitVarSizeWithMarker_Values[q3] = 1 | q3 : int(1..2)]), + and([q6 <= s_ExplicitVarSizeWithMarker_Marker -> s_Occurrence[s_ExplicitVarSizeWithMarker_Values[q6]] + | q6 : int(1..2)]), + and([s_Occurrence[q7] -> + or([q9 <= s_ExplicitVarSizeWithMarker_Marker /\ s_ExplicitVarSizeWithMarker_Values[q9] = q7 | q9 : int(1..2)]) + | q7 : int(1..2)]) + diff --git a/tests/exhaustive/basic/set_card_00/expected/model_1_3_2-solution000001.solution b/tests/exhaustive/basic/set_card_00/expected/model_1_3_2-solution000001.solution new file mode 100644 index 0000000000..2ce5f2081f --- /dev/null +++ b/tests/exhaustive/basic/set_card_00/expected/model_1_3_2-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting s be {1, 2} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_1_3_2-solution000002.solution b/tests/exhaustive/basic/set_card_00/expected/model_1_3_2-solution000002.solution new file mode 100644 index 0000000000..6c0d0fdad8 --- /dev/null +++ b/tests/exhaustive/basic/set_card_00/expected/model_1_3_2-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting s be {1} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_1_3_2.eprime b/tests/exhaustive/basic/set_card_00/expected/model_1_3_2.eprime new file mode 100644 index 0000000000..d5996222eb --- /dev/null +++ b/tests/exhaustive/basic/set_card_00/expected/model_1_3_2.eprime @@ -0,0 +1,37 @@ +language ESSENCE' 1.0 + +find s_Occurrence: matrix indexed by [int(1..2)] of bool +find s_ExplicitVarSizeWithMarker_Marker: int(0..2) +find s_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..2)] of int(1..2) +find s_ExplicitVarSizeWithDummy: matrix indexed by [int(1..2)] of int(1..3) +branching on + [s_ExplicitVarSizeWithDummy, s_Occurrence, s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithMarker_Values] +such that + or([q28 <= s_ExplicitVarSizeWithMarker_Marker /\ + s_ExplicitVarSizeWithMarker_Values[q28] = sum([toInt(s_Occurrence[q29]) | q29 : int(1..2)]) + | q28 : int(1..2)]), + 2 <= s_ExplicitVarSizeWithMarker_Marker -> + s_ExplicitVarSizeWithMarker_Values[1] < s_ExplicitVarSizeWithMarker_Values[2], + and([q3 > s_ExplicitVarSizeWithMarker_Marker -> s_ExplicitVarSizeWithMarker_Values[q3] = 1 | q3 : int(1..2)]), + and([q6 <= s_ExplicitVarSizeWithMarker_Marker -> s_Occurrence[s_ExplicitVarSizeWithMarker_Values[q6]] + | q6 : int(1..2)]), + and([s_Occurrence[q7] -> + or([q9 <= s_ExplicitVarSizeWithMarker_Marker /\ s_ExplicitVarSizeWithMarker_Values[q9] = q7 | q9 : int(1..2)]) + | q7 : int(1..2)]), + s_ExplicitVarSizeWithDummy[1] < s_ExplicitVarSizeWithDummy[2] \/ s_ExplicitVarSizeWithDummy[1] = 3, + s_ExplicitVarSizeWithDummy[1] = 3 -> s_ExplicitVarSizeWithDummy[2] = 3, + and([s_ExplicitVarSizeWithDummy[q15] != 3 -> s_Occurrence[s_ExplicitVarSizeWithDummy[q15]] | q15 : int(1..2)]), + and([s_Occurrence[q16] -> + or([s_ExplicitVarSizeWithDummy[q18] != 3 /\ s_ExplicitVarSizeWithDummy[q18] = q16 | q18 : int(1..2)]) + | q16 : int(1..2)]), + and([s_ExplicitVarSizeWithDummy[q20] != 3 -> + or([q22 <= s_ExplicitVarSizeWithMarker_Marker /\ + s_ExplicitVarSizeWithMarker_Values[q22] = s_ExplicitVarSizeWithDummy[q20] + | q22 : int(1..2)]) + | q20 : int(1..2)]), + and([q24 <= s_ExplicitVarSizeWithMarker_Marker -> + or([s_ExplicitVarSizeWithDummy[q26] != 3 /\ + s_ExplicitVarSizeWithDummy[q26] = s_ExplicitVarSizeWithMarker_Values[q24] + | q26 : int(1..2)]) + | q24 : int(1..2)]) + diff --git a/tests/exhaustive/basic/set_card_00/expected/model_1_3_4-solution000001.solution b/tests/exhaustive/basic/set_card_00/expected/model_1_3_4-solution000001.solution new file mode 100644 index 0000000000..6c0d0fdad8 --- /dev/null +++ b/tests/exhaustive/basic/set_card_00/expected/model_1_3_4-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting s be {1} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_1_3_4-solution000002.solution b/tests/exhaustive/basic/set_card_00/expected/model_1_3_4-solution000002.solution new file mode 100644 index 0000000000..2ce5f2081f --- /dev/null +++ b/tests/exhaustive/basic/set_card_00/expected/model_1_3_4-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting s be {1, 2} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_1_3_4.eprime b/tests/exhaustive/basic/set_card_00/expected/model_1_3_4.eprime new file mode 100644 index 0000000000..9de0cd975a --- /dev/null +++ b/tests/exhaustive/basic/set_card_00/expected/model_1_3_4.eprime @@ -0,0 +1,42 @@ +language ESSENCE' 1.0 + +find s_Occurrence: matrix indexed by [int(1..2)] of bool +find s_ExplicitVarSizeWithMarker_Marker: int(0..2) +find s_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..2)] of int(1..2) +find s_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..2)] of bool +find s_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..2)] of int(1..2) +branching on + [s_ExplicitVarSizeWithFlags_Flags, s_ExplicitVarSizeWithFlags_Values, s_Occurrence, + s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithMarker_Values] +such that + or([q29 <= s_ExplicitVarSizeWithMarker_Marker /\ + s_ExplicitVarSizeWithMarker_Values[q29] = sum([toInt(s_Occurrence[q30]) | q30 : int(1..2)]) + | q29 : int(1..2)]), + 2 <= s_ExplicitVarSizeWithMarker_Marker -> + s_ExplicitVarSizeWithMarker_Values[1] < s_ExplicitVarSizeWithMarker_Values[2], + and([q3 > s_ExplicitVarSizeWithMarker_Marker -> s_ExplicitVarSizeWithMarker_Values[q3] = 1 | q3 : int(1..2)]), + and([q6 <= s_ExplicitVarSizeWithMarker_Marker -> s_Occurrence[s_ExplicitVarSizeWithMarker_Values[q6]] + | q6 : int(1..2)]), + and([s_Occurrence[q7] -> + or([q9 <= s_ExplicitVarSizeWithMarker_Marker /\ s_ExplicitVarSizeWithMarker_Values[q9] = q7 | q9 : int(1..2)]) + | q7 : int(1..2)]), + s_ExplicitVarSizeWithFlags_Flags[2] -> s_ExplicitVarSizeWithFlags_Values[1] < s_ExplicitVarSizeWithFlags_Values[2], + and([s_ExplicitVarSizeWithFlags_Flags[q11] = false -> s_ExplicitVarSizeWithFlags_Values[q11] = 1 + | q11 : int(1..2)]), + s_ExplicitVarSizeWithFlags_Flags[2] -> s_ExplicitVarSizeWithFlags_Flags[1], + and([s_ExplicitVarSizeWithFlags_Flags[q16] -> s_Occurrence[s_ExplicitVarSizeWithFlags_Values[q16]] + | q16 : int(1..2)]), + and([s_Occurrence[q17] -> + or([s_ExplicitVarSizeWithFlags_Flags[q19] /\ s_ExplicitVarSizeWithFlags_Values[q19] = q17 | q19 : int(1..2)]) + | q17 : int(1..2)]), + and([s_ExplicitVarSizeWithFlags_Flags[q21] -> + or([q23 <= s_ExplicitVarSizeWithMarker_Marker /\ + s_ExplicitVarSizeWithMarker_Values[q23] = s_ExplicitVarSizeWithFlags_Values[q21] + | q23 : int(1..2)]) + | q21 : int(1..2)]), + and([q25 <= s_ExplicitVarSizeWithMarker_Marker -> + or([s_ExplicitVarSizeWithFlags_Flags[q27] /\ + s_ExplicitVarSizeWithFlags_Values[q27] = s_ExplicitVarSizeWithMarker_Values[q25] + | q27 : int(1..2)]) + | q25 : int(1..2)]) + diff --git a/tests/exhaustive/basic/set_card_00/expected/model_1_4_1-solution000001.solution b/tests/exhaustive/basic/set_card_00/expected/model_1_4_1-solution000001.solution new file mode 100644 index 0000000000..6c0d0fdad8 --- /dev/null +++ b/tests/exhaustive/basic/set_card_00/expected/model_1_4_1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting s be {1} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_1_4_1-solution000002.solution b/tests/exhaustive/basic/set_card_00/expected/model_1_4_1-solution000002.solution new file mode 100644 index 0000000000..2ce5f2081f --- /dev/null +++ b/tests/exhaustive/basic/set_card_00/expected/model_1_4_1-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting s be {1, 2} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_1_4_1.eprime b/tests/exhaustive/basic/set_card_00/expected/model_1_4_1.eprime new file mode 100644 index 0000000000..c94c0a316f --- /dev/null +++ b/tests/exhaustive/basic/set_card_00/expected/model_1_4_1.eprime @@ -0,0 +1,18 @@ +language ESSENCE' 1.0 + +find s_Occurrence: matrix indexed by [int(1..2)] of bool +find s_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..2)] of bool +find s_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..2)] of int(1..2) +branching on [s_ExplicitVarSizeWithFlags_Flags, s_ExplicitVarSizeWithFlags_Values, s_Occurrence] +such that + or([s_ExplicitVarSizeWithFlags_Flags[q13] /\ + s_ExplicitVarSizeWithFlags_Values[q13] = sum([toInt(s_Occurrence[q14]) | q14 : int(1..2)]) + | q13 : int(1..2)]), + s_ExplicitVarSizeWithFlags_Flags[2] -> s_ExplicitVarSizeWithFlags_Values[1] < s_ExplicitVarSizeWithFlags_Values[2], + and([s_ExplicitVarSizeWithFlags_Flags[q3] = false -> s_ExplicitVarSizeWithFlags_Values[q3] = 1 | q3 : int(1..2)]), + s_ExplicitVarSizeWithFlags_Flags[2] -> s_ExplicitVarSizeWithFlags_Flags[1], + and([s_ExplicitVarSizeWithFlags_Flags[q8] -> s_Occurrence[s_ExplicitVarSizeWithFlags_Values[q8]] | q8 : int(1..2)]), + and([s_Occurrence[q9] -> + or([s_ExplicitVarSizeWithFlags_Flags[q11] /\ s_ExplicitVarSizeWithFlags_Values[q11] = q9 | q11 : int(1..2)]) + | q9 : int(1..2)]) + diff --git a/tests/exhaustive/basic/set_card_00/expected/model_1_4_2-solution000001.solution b/tests/exhaustive/basic/set_card_00/expected/model_1_4_2-solution000001.solution new file mode 100644 index 0000000000..2ce5f2081f --- /dev/null +++ b/tests/exhaustive/basic/set_card_00/expected/model_1_4_2-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting s be {1, 2} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_1_4_2-solution000002.solution b/tests/exhaustive/basic/set_card_00/expected/model_1_4_2-solution000002.solution new file mode 100644 index 0000000000..6c0d0fdad8 --- /dev/null +++ b/tests/exhaustive/basic/set_card_00/expected/model_1_4_2-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting s be {1} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_1_4_2.eprime b/tests/exhaustive/basic/set_card_00/expected/model_1_4_2.eprime new file mode 100644 index 0000000000..42d80e559a --- /dev/null +++ b/tests/exhaustive/basic/set_card_00/expected/model_1_4_2.eprime @@ -0,0 +1,36 @@ +language ESSENCE' 1.0 + +find s_Occurrence: matrix indexed by [int(1..2)] of bool +find s_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..2)] of bool +find s_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..2)] of int(1..2) +find s_ExplicitVarSizeWithDummy: matrix indexed by [int(1..2)] of int(1..3) +branching on + [s_ExplicitVarSizeWithDummy, s_Occurrence, s_ExplicitVarSizeWithFlags_Flags, s_ExplicitVarSizeWithFlags_Values] +such that + or([s_ExplicitVarSizeWithFlags_Flags[q30] /\ + s_ExplicitVarSizeWithFlags_Values[q30] = sum([toInt(s_Occurrence[q31]) | q31 : int(1..2)]) + | q30 : int(1..2)]), + s_ExplicitVarSizeWithFlags_Flags[2] -> s_ExplicitVarSizeWithFlags_Values[1] < s_ExplicitVarSizeWithFlags_Values[2], + and([s_ExplicitVarSizeWithFlags_Flags[q3] = false -> s_ExplicitVarSizeWithFlags_Values[q3] = 1 | q3 : int(1..2)]), + s_ExplicitVarSizeWithFlags_Flags[2] -> s_ExplicitVarSizeWithFlags_Flags[1], + and([s_ExplicitVarSizeWithFlags_Flags[q8] -> s_Occurrence[s_ExplicitVarSizeWithFlags_Values[q8]] | q8 : int(1..2)]), + and([s_Occurrence[q9] -> + or([s_ExplicitVarSizeWithFlags_Flags[q11] /\ s_ExplicitVarSizeWithFlags_Values[q11] = q9 | q11 : int(1..2)]) + | q9 : int(1..2)]), + s_ExplicitVarSizeWithDummy[1] < s_ExplicitVarSizeWithDummy[2] \/ s_ExplicitVarSizeWithDummy[1] = 3, + s_ExplicitVarSizeWithDummy[1] = 3 -> s_ExplicitVarSizeWithDummy[2] = 3, + and([s_ExplicitVarSizeWithDummy[q17] != 3 -> s_Occurrence[s_ExplicitVarSizeWithDummy[q17]] | q17 : int(1..2)]), + and([s_Occurrence[q18] -> + or([s_ExplicitVarSizeWithDummy[q20] != 3 /\ s_ExplicitVarSizeWithDummy[q20] = q18 | q20 : int(1..2)]) + | q18 : int(1..2)]), + and([s_ExplicitVarSizeWithDummy[q22] != 3 -> + or([s_ExplicitVarSizeWithFlags_Flags[q24] /\ + s_ExplicitVarSizeWithFlags_Values[q24] = s_ExplicitVarSizeWithDummy[q22] + | q24 : int(1..2)]) + | q22 : int(1..2)]), + and([s_ExplicitVarSizeWithFlags_Flags[q26] -> + or([s_ExplicitVarSizeWithDummy[q28] != 3 /\ + s_ExplicitVarSizeWithDummy[q28] = s_ExplicitVarSizeWithFlags_Values[q26] + | q28 : int(1..2)]) + | q26 : int(1..2)]) + diff --git a/tests/exhaustive/basic/set_card_00/expected/model_1_4_3-solution000001.solution b/tests/exhaustive/basic/set_card_00/expected/model_1_4_3-solution000001.solution new file mode 100644 index 0000000000..6c0d0fdad8 --- /dev/null +++ b/tests/exhaustive/basic/set_card_00/expected/model_1_4_3-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting s be {1} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_1_4_3-solution000002.solution b/tests/exhaustive/basic/set_card_00/expected/model_1_4_3-solution000002.solution new file mode 100644 index 0000000000..2ce5f2081f --- /dev/null +++ b/tests/exhaustive/basic/set_card_00/expected/model_1_4_3-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting s be {1, 2} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_1_4_3.eprime b/tests/exhaustive/basic/set_card_00/expected/model_1_4_3.eprime new file mode 100644 index 0000000000..666b249b58 --- /dev/null +++ b/tests/exhaustive/basic/set_card_00/expected/model_1_4_3.eprime @@ -0,0 +1,41 @@ +language ESSENCE' 1.0 + +find s_Occurrence: matrix indexed by [int(1..2)] of bool +find s_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..2)] of bool +find s_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..2)] of int(1..2) +find s_ExplicitVarSizeWithMarker_Marker: int(0..2) +find s_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..2)] of int(1..2) +branching on + [s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithMarker_Values, s_Occurrence, + s_ExplicitVarSizeWithFlags_Flags, s_ExplicitVarSizeWithFlags_Values] +such that + or([s_ExplicitVarSizeWithFlags_Flags[q29] /\ + s_ExplicitVarSizeWithFlags_Values[q29] = sum([toInt(s_Occurrence[q30]) | q30 : int(1..2)]) + | q29 : int(1..2)]), + s_ExplicitVarSizeWithFlags_Flags[2] -> s_ExplicitVarSizeWithFlags_Values[1] < s_ExplicitVarSizeWithFlags_Values[2], + and([s_ExplicitVarSizeWithFlags_Flags[q3] = false -> s_ExplicitVarSizeWithFlags_Values[q3] = 1 | q3 : int(1..2)]), + s_ExplicitVarSizeWithFlags_Flags[2] -> s_ExplicitVarSizeWithFlags_Flags[1], + and([s_ExplicitVarSizeWithFlags_Flags[q8] -> s_Occurrence[s_ExplicitVarSizeWithFlags_Values[q8]] | q8 : int(1..2)]), + and([s_Occurrence[q9] -> + or([s_ExplicitVarSizeWithFlags_Flags[q11] /\ s_ExplicitVarSizeWithFlags_Values[q11] = q9 | q11 : int(1..2)]) + | q9 : int(1..2)]), + 2 <= s_ExplicitVarSizeWithMarker_Marker -> + s_ExplicitVarSizeWithMarker_Values[1] < s_ExplicitVarSizeWithMarker_Values[2], + and([q13 > s_ExplicitVarSizeWithMarker_Marker -> s_ExplicitVarSizeWithMarker_Values[q13] = 1 | q13 : int(1..2)]), + and([q16 <= s_ExplicitVarSizeWithMarker_Marker -> s_Occurrence[s_ExplicitVarSizeWithMarker_Values[q16]] + | q16 : int(1..2)]), + and([s_Occurrence[q17] -> + or([q19 <= s_ExplicitVarSizeWithMarker_Marker /\ s_ExplicitVarSizeWithMarker_Values[q19] = q17 + | q19 : int(1..2)]) + | q17 : int(1..2)]), + and([q21 <= s_ExplicitVarSizeWithMarker_Marker -> + or([s_ExplicitVarSizeWithFlags_Flags[q23] /\ + s_ExplicitVarSizeWithFlags_Values[q23] = s_ExplicitVarSizeWithMarker_Values[q21] + | q23 : int(1..2)]) + | q21 : int(1..2)]), + and([s_ExplicitVarSizeWithFlags_Flags[q25] -> + or([q27 <= s_ExplicitVarSizeWithMarker_Marker /\ + s_ExplicitVarSizeWithMarker_Values[q27] = s_ExplicitVarSizeWithFlags_Values[q25] + | q27 : int(1..2)]) + | q25 : int(1..2)]) + diff --git a/tests/exhaustive/basic/set_card_00/expected/model_2_1_1-solution000001.solution b/tests/exhaustive/basic/set_card_00/expected/model_2_1_1-solution000001.solution new file mode 100644 index 0000000000..6c0d0fdad8 --- /dev/null +++ b/tests/exhaustive/basic/set_card_00/expected/model_2_1_1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting s be {1} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_2_1_1-solution000002.solution b/tests/exhaustive/basic/set_card_00/expected/model_2_1_1-solution000002.solution new file mode 100644 index 0000000000..2ce5f2081f --- /dev/null +++ b/tests/exhaustive/basic/set_card_00/expected/model_2_1_1-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting s be {1, 2} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_2_1_1.eprime b/tests/exhaustive/basic/set_card_00/expected/model_2_1_1.eprime new file mode 100644 index 0000000000..776246603c --- /dev/null +++ b/tests/exhaustive/basic/set_card_00/expected/model_2_1_1.eprime @@ -0,0 +1,14 @@ +language ESSENCE' 1.0 + +find s_ExplicitVarSizeWithDummy: matrix indexed by [int(1..2)] of int(1..3) +find s_Occurrence: matrix indexed by [int(1..2)] of bool +branching on [s_Occurrence, s_ExplicitVarSizeWithDummy] +such that + s_Occurrence[sum([toInt(s_ExplicitVarSizeWithDummy[q7] != 3) | q7 : int(1..2)])], + s_ExplicitVarSizeWithDummy[1] < s_ExplicitVarSizeWithDummy[2] \/ s_ExplicitVarSizeWithDummy[1] = 3, + s_ExplicitVarSizeWithDummy[1] = 3 -> s_ExplicitVarSizeWithDummy[2] = 3, + and([s_Occurrence[q8] -> + or([s_ExplicitVarSizeWithDummy[q10] != 3 /\ s_ExplicitVarSizeWithDummy[q10] = q8 | q10 : int(1..2)]) + | q8 : int(1..2)]), + and([s_ExplicitVarSizeWithDummy[q12] != 3 -> s_Occurrence[s_ExplicitVarSizeWithDummy[q12]] | q12 : int(1..2)]) + diff --git a/tests/exhaustive/basic/set_card_00/expected/model_2_1_3-solution000001.solution b/tests/exhaustive/basic/set_card_00/expected/model_2_1_3-solution000001.solution new file mode 100644 index 0000000000..6c0d0fdad8 --- /dev/null +++ b/tests/exhaustive/basic/set_card_00/expected/model_2_1_3-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting s be {1} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_2_1_3-solution000002.solution b/tests/exhaustive/basic/set_card_00/expected/model_2_1_3-solution000002.solution new file mode 100644 index 0000000000..2ce5f2081f --- /dev/null +++ b/tests/exhaustive/basic/set_card_00/expected/model_2_1_3-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting s be {1, 2} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_2_1_3.eprime b/tests/exhaustive/basic/set_card_00/expected/model_2_1_3.eprime new file mode 100644 index 0000000000..58dcd8a0d9 --- /dev/null +++ b/tests/exhaustive/basic/set_card_00/expected/model_2_1_3.eprime @@ -0,0 +1,36 @@ +language ESSENCE' 1.0 + +find s_ExplicitVarSizeWithDummy: matrix indexed by [int(1..2)] of int(1..3) +find s_Occurrence: matrix indexed by [int(1..2)] of bool +find s_ExplicitVarSizeWithMarker_Marker: int(0..2) +find s_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..2)] of int(1..2) +branching on + [s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithMarker_Values, s_ExplicitVarSizeWithDummy, s_Occurrence] +such that + s_Occurrence[sum([toInt(s_ExplicitVarSizeWithDummy[q23] != 3) | q23 : int(1..2)])], + s_ExplicitVarSizeWithDummy[1] < s_ExplicitVarSizeWithDummy[2] \/ s_ExplicitVarSizeWithDummy[1] = 3, + s_ExplicitVarSizeWithDummy[1] = 3 -> s_ExplicitVarSizeWithDummy[2] = 3, + and([s_Occurrence[q24] -> + or([s_ExplicitVarSizeWithDummy[q26] != 3 /\ s_ExplicitVarSizeWithDummy[q26] = q24 | q26 : int(1..2)]) + | q24 : int(1..2)]), + and([s_ExplicitVarSizeWithDummy[q28] != 3 -> s_Occurrence[s_ExplicitVarSizeWithDummy[q28]] | q28 : int(1..2)]), + 2 <= s_ExplicitVarSizeWithMarker_Marker -> + s_ExplicitVarSizeWithMarker_Values[1] < s_ExplicitVarSizeWithMarker_Values[2], + and([q7 > s_ExplicitVarSizeWithMarker_Marker -> s_ExplicitVarSizeWithMarker_Values[q7] = 1 | q7 : int(1..2)]), + and([q10 <= s_ExplicitVarSizeWithMarker_Marker -> + or([s_ExplicitVarSizeWithDummy[q12] != 3 /\ + s_ExplicitVarSizeWithDummy[q12] = s_ExplicitVarSizeWithMarker_Values[q10] + | q12 : int(1..2)]) + | q10 : int(1..2)]), + and([s_ExplicitVarSizeWithDummy[q14] != 3 -> + or([q16 <= s_ExplicitVarSizeWithMarker_Marker /\ + s_ExplicitVarSizeWithMarker_Values[q16] = s_ExplicitVarSizeWithDummy[q14] + | q16 : int(1..2)]) + | q14 : int(1..2)]), + and([q18 <= s_ExplicitVarSizeWithMarker_Marker -> s_Occurrence[s_ExplicitVarSizeWithMarker_Values[q18]] + | q18 : int(1..2)]), + and([s_Occurrence[q19] -> + or([q21 <= s_ExplicitVarSizeWithMarker_Marker /\ s_ExplicitVarSizeWithMarker_Values[q21] = q19 + | q21 : int(1..2)]) + | q19 : int(1..2)]) + diff --git a/tests/exhaustive/basic/set_card_00/expected/model_2_1_4-solution000001.solution b/tests/exhaustive/basic/set_card_00/expected/model_2_1_4-solution000001.solution new file mode 100644 index 0000000000..6c0d0fdad8 --- /dev/null +++ b/tests/exhaustive/basic/set_card_00/expected/model_2_1_4-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting s be {1} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_2_1_4-solution000002.solution b/tests/exhaustive/basic/set_card_00/expected/model_2_1_4-solution000002.solution new file mode 100644 index 0000000000..2ce5f2081f --- /dev/null +++ b/tests/exhaustive/basic/set_card_00/expected/model_2_1_4-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting s be {1, 2} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_2_1_4.eprime b/tests/exhaustive/basic/set_card_00/expected/model_2_1_4.eprime new file mode 100644 index 0000000000..d91db06282 --- /dev/null +++ b/tests/exhaustive/basic/set_card_00/expected/model_2_1_4.eprime @@ -0,0 +1,35 @@ +language ESSENCE' 1.0 + +find s_ExplicitVarSizeWithDummy: matrix indexed by [int(1..2)] of int(1..3) +find s_Occurrence: matrix indexed by [int(1..2)] of bool +find s_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..2)] of bool +find s_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..2)] of int(1..2) +branching on + [s_ExplicitVarSizeWithFlags_Flags, s_ExplicitVarSizeWithFlags_Values, s_ExplicitVarSizeWithDummy, s_Occurrence] +such that + s_Occurrence[sum([toInt(s_ExplicitVarSizeWithDummy[q25] != 3) | q25 : int(1..2)])], + s_ExplicitVarSizeWithDummy[1] < s_ExplicitVarSizeWithDummy[2] \/ s_ExplicitVarSizeWithDummy[1] = 3, + s_ExplicitVarSizeWithDummy[1] = 3 -> s_ExplicitVarSizeWithDummy[2] = 3, + and([s_Occurrence[q26] -> + or([s_ExplicitVarSizeWithDummy[q28] != 3 /\ s_ExplicitVarSizeWithDummy[q28] = q26 | q28 : int(1..2)]) + | q26 : int(1..2)]), + and([s_ExplicitVarSizeWithDummy[q30] != 3 -> s_Occurrence[s_ExplicitVarSizeWithDummy[q30]] | q30 : int(1..2)]), + s_ExplicitVarSizeWithFlags_Flags[2] -> s_ExplicitVarSizeWithFlags_Values[1] < s_ExplicitVarSizeWithFlags_Values[2], + and([s_ExplicitVarSizeWithFlags_Flags[q7] = false -> s_ExplicitVarSizeWithFlags_Values[q7] = 1 | q7 : int(1..2)]), + s_ExplicitVarSizeWithFlags_Flags[2] -> s_ExplicitVarSizeWithFlags_Flags[1], + and([s_ExplicitVarSizeWithFlags_Flags[q12] -> + or([s_ExplicitVarSizeWithDummy[q14] != 3 /\ + s_ExplicitVarSizeWithDummy[q14] = s_ExplicitVarSizeWithFlags_Values[q12] + | q14 : int(1..2)]) + | q12 : int(1..2)]), + and([s_ExplicitVarSizeWithDummy[q16] != 3 -> + or([s_ExplicitVarSizeWithFlags_Flags[q18] /\ + s_ExplicitVarSizeWithFlags_Values[q18] = s_ExplicitVarSizeWithDummy[q16] + | q18 : int(1..2)]) + | q16 : int(1..2)]), + and([s_ExplicitVarSizeWithFlags_Flags[q20] -> s_Occurrence[s_ExplicitVarSizeWithFlags_Values[q20]] + | q20 : int(1..2)]), + and([s_Occurrence[q21] -> + or([s_ExplicitVarSizeWithFlags_Flags[q23] /\ s_ExplicitVarSizeWithFlags_Values[q23] = q21 | q23 : int(1..2)]) + | q21 : int(1..2)]) + diff --git a/tests/exhaustive/basic/set_card_00/expected/model_2_2_1-solution000001.solution b/tests/exhaustive/basic/set_card_00/expected/model_2_2_1-solution000001.solution new file mode 100644 index 0000000000..6c0d0fdad8 --- /dev/null +++ b/tests/exhaustive/basic/set_card_00/expected/model_2_2_1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting s be {1} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_2_2_1-solution000002.solution b/tests/exhaustive/basic/set_card_00/expected/model_2_2_1-solution000002.solution new file mode 100644 index 0000000000..2ce5f2081f --- /dev/null +++ b/tests/exhaustive/basic/set_card_00/expected/model_2_2_1-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting s be {1, 2} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_2_2_1.eprime b/tests/exhaustive/basic/set_card_00/expected/model_2_2_1.eprime new file mode 100644 index 0000000000..2130ba4508 --- /dev/null +++ b/tests/exhaustive/basic/set_card_00/expected/model_2_2_1.eprime @@ -0,0 +1,16 @@ +language ESSENCE' 1.0 + +find s_ExplicitVarSizeWithDummy: matrix indexed by [int(1..2)] of int(1..3) +find s_Occurrence: matrix indexed by [int(1..2)] of bool +branching on [s_Occurrence, s_ExplicitVarSizeWithDummy] +such that + or([s_ExplicitVarSizeWithDummy[q7] != 3 /\ + s_ExplicitVarSizeWithDummy[q7] = sum([toInt(s_ExplicitVarSizeWithDummy[q9] != 3) | q9 : int(1..2)]) + | q7 : int(1..2)]), + s_ExplicitVarSizeWithDummy[1] < s_ExplicitVarSizeWithDummy[2] \/ s_ExplicitVarSizeWithDummy[1] = 3, + s_ExplicitVarSizeWithDummy[1] = 3 -> s_ExplicitVarSizeWithDummy[2] = 3, + and([s_Occurrence[q10] -> + or([s_ExplicitVarSizeWithDummy[q12] != 3 /\ s_ExplicitVarSizeWithDummy[q12] = q10 | q12 : int(1..2)]) + | q10 : int(1..2)]), + and([s_ExplicitVarSizeWithDummy[q14] != 3 -> s_Occurrence[s_ExplicitVarSizeWithDummy[q14]] | q14 : int(1..2)]) + diff --git a/tests/exhaustive/basic/set_card_00/expected/model_2_2_2-solution000001.solution b/tests/exhaustive/basic/set_card_00/expected/model_2_2_2-solution000001.solution new file mode 100644 index 0000000000..2ce5f2081f --- /dev/null +++ b/tests/exhaustive/basic/set_card_00/expected/model_2_2_2-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting s be {1, 2} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_2_2_2-solution000002.solution b/tests/exhaustive/basic/set_card_00/expected/model_2_2_2-solution000002.solution new file mode 100644 index 0000000000..6c0d0fdad8 --- /dev/null +++ b/tests/exhaustive/basic/set_card_00/expected/model_2_2_2-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting s be {1} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_2_2_2.eprime b/tests/exhaustive/basic/set_card_00/expected/model_2_2_2.eprime new file mode 100644 index 0000000000..de77468609 --- /dev/null +++ b/tests/exhaustive/basic/set_card_00/expected/model_2_2_2.eprime @@ -0,0 +1,11 @@ +language ESSENCE' 1.0 + +find s_ExplicitVarSizeWithDummy: matrix indexed by [int(1..2)] of int(1..3) +branching on [s_ExplicitVarSizeWithDummy] +such that + or([s_ExplicitVarSizeWithDummy[q6] != 3 /\ + s_ExplicitVarSizeWithDummy[q6] = sum([toInt(s_ExplicitVarSizeWithDummy[q8] != 3) | q8 : int(1..2)]) + | q6 : int(1..2)]), + s_ExplicitVarSizeWithDummy[1] < s_ExplicitVarSizeWithDummy[2] \/ s_ExplicitVarSizeWithDummy[1] = 3, + s_ExplicitVarSizeWithDummy[1] = 3 -> s_ExplicitVarSizeWithDummy[2] = 3 + diff --git a/tests/exhaustive/basic/set_card_00/expected/model_2_2_3-solution000001.solution b/tests/exhaustive/basic/set_card_00/expected/model_2_2_3-solution000001.solution new file mode 100644 index 0000000000..6c0d0fdad8 --- /dev/null +++ b/tests/exhaustive/basic/set_card_00/expected/model_2_2_3-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting s be {1} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_2_2_3-solution000002.solution b/tests/exhaustive/basic/set_card_00/expected/model_2_2_3-solution000002.solution new file mode 100644 index 0000000000..2ce5f2081f --- /dev/null +++ b/tests/exhaustive/basic/set_card_00/expected/model_2_2_3-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting s be {1, 2} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_2_2_3.eprime b/tests/exhaustive/basic/set_card_00/expected/model_2_2_3.eprime new file mode 100644 index 0000000000..d78add42d0 --- /dev/null +++ b/tests/exhaustive/basic/set_card_00/expected/model_2_2_3.eprime @@ -0,0 +1,26 @@ +language ESSENCE' 1.0 + +find s_ExplicitVarSizeWithDummy: matrix indexed by [int(1..2)] of int(1..3) +find s_ExplicitVarSizeWithMarker_Marker: int(0..2) +find s_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..2)] of int(1..2) +branching on [s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithMarker_Values, s_ExplicitVarSizeWithDummy] +such that + or([s_ExplicitVarSizeWithDummy[q17] != 3 /\ + s_ExplicitVarSizeWithDummy[q17] = sum([toInt(s_ExplicitVarSizeWithDummy[q19] != 3) | q19 : int(1..2)]) + | q17 : int(1..2)]), + s_ExplicitVarSizeWithDummy[1] < s_ExplicitVarSizeWithDummy[2] \/ s_ExplicitVarSizeWithDummy[1] = 3, + s_ExplicitVarSizeWithDummy[1] = 3 -> s_ExplicitVarSizeWithDummy[2] = 3, + 2 <= s_ExplicitVarSizeWithMarker_Marker -> + s_ExplicitVarSizeWithMarker_Values[1] < s_ExplicitVarSizeWithMarker_Values[2], + and([q6 > s_ExplicitVarSizeWithMarker_Marker -> s_ExplicitVarSizeWithMarker_Values[q6] = 1 | q6 : int(1..2)]), + and([q9 <= s_ExplicitVarSizeWithMarker_Marker -> + or([s_ExplicitVarSizeWithDummy[q11] != 3 /\ + s_ExplicitVarSizeWithDummy[q11] = s_ExplicitVarSizeWithMarker_Values[q9] + | q11 : int(1..2)]) + | q9 : int(1..2)]), + and([s_ExplicitVarSizeWithDummy[q13] != 3 -> + or([q15 <= s_ExplicitVarSizeWithMarker_Marker /\ + s_ExplicitVarSizeWithMarker_Values[q15] = s_ExplicitVarSizeWithDummy[q13] + | q15 : int(1..2)]) + | q13 : int(1..2)]) + diff --git a/tests/exhaustive/basic/set_card_00/expected/model_2_2_4-solution000001.solution b/tests/exhaustive/basic/set_card_00/expected/model_2_2_4-solution000001.solution new file mode 100644 index 0000000000..6c0d0fdad8 --- /dev/null +++ b/tests/exhaustive/basic/set_card_00/expected/model_2_2_4-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting s be {1} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_2_2_4-solution000002.solution b/tests/exhaustive/basic/set_card_00/expected/model_2_2_4-solution000002.solution new file mode 100644 index 0000000000..2ce5f2081f --- /dev/null +++ b/tests/exhaustive/basic/set_card_00/expected/model_2_2_4-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting s be {1, 2} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_2_2_4.eprime b/tests/exhaustive/basic/set_card_00/expected/model_2_2_4.eprime new file mode 100644 index 0000000000..e0885d30f9 --- /dev/null +++ b/tests/exhaustive/basic/set_card_00/expected/model_2_2_4.eprime @@ -0,0 +1,26 @@ +language ESSENCE' 1.0 + +find s_ExplicitVarSizeWithDummy: matrix indexed by [int(1..2)] of int(1..3) +find s_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..2)] of bool +find s_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..2)] of int(1..2) +branching on [s_ExplicitVarSizeWithFlags_Flags, s_ExplicitVarSizeWithFlags_Values, s_ExplicitVarSizeWithDummy] +such that + or([s_ExplicitVarSizeWithDummy[q19] != 3 /\ + s_ExplicitVarSizeWithDummy[q19] = sum([toInt(s_ExplicitVarSizeWithDummy[q21] != 3) | q21 : int(1..2)]) + | q19 : int(1..2)]), + s_ExplicitVarSizeWithDummy[1] < s_ExplicitVarSizeWithDummy[2] \/ s_ExplicitVarSizeWithDummy[1] = 3, + s_ExplicitVarSizeWithDummy[1] = 3 -> s_ExplicitVarSizeWithDummy[2] = 3, + s_ExplicitVarSizeWithFlags_Flags[2] -> s_ExplicitVarSizeWithFlags_Values[1] < s_ExplicitVarSizeWithFlags_Values[2], + and([s_ExplicitVarSizeWithFlags_Flags[q6] = false -> s_ExplicitVarSizeWithFlags_Values[q6] = 1 | q6 : int(1..2)]), + s_ExplicitVarSizeWithFlags_Flags[2] -> s_ExplicitVarSizeWithFlags_Flags[1], + and([s_ExplicitVarSizeWithFlags_Flags[q11] -> + or([s_ExplicitVarSizeWithDummy[q13] != 3 /\ + s_ExplicitVarSizeWithDummy[q13] = s_ExplicitVarSizeWithFlags_Values[q11] + | q13 : int(1..2)]) + | q11 : int(1..2)]), + and([s_ExplicitVarSizeWithDummy[q15] != 3 -> + or([s_ExplicitVarSizeWithFlags_Flags[q17] /\ + s_ExplicitVarSizeWithFlags_Values[q17] = s_ExplicitVarSizeWithDummy[q15] + | q17 : int(1..2)]) + | q15 : int(1..2)]) + diff --git a/tests/exhaustive/basic/set_card_00/expected/model_2_3_1-solution000001.solution b/tests/exhaustive/basic/set_card_00/expected/model_2_3_1-solution000001.solution new file mode 100644 index 0000000000..6c0d0fdad8 --- /dev/null +++ b/tests/exhaustive/basic/set_card_00/expected/model_2_3_1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting s be {1} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_2_3_1-solution000002.solution b/tests/exhaustive/basic/set_card_00/expected/model_2_3_1-solution000002.solution new file mode 100644 index 0000000000..2ce5f2081f --- /dev/null +++ b/tests/exhaustive/basic/set_card_00/expected/model_2_3_1-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting s be {1, 2} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_2_3_1.eprime b/tests/exhaustive/basic/set_card_00/expected/model_2_3_1.eprime new file mode 100644 index 0000000000..bb65736cc9 --- /dev/null +++ b/tests/exhaustive/basic/set_card_00/expected/model_2_3_1.eprime @@ -0,0 +1,38 @@ +language ESSENCE' 1.0 + +find s_ExplicitVarSizeWithDummy: matrix indexed by [int(1..2)] of int(1..3) +find s_ExplicitVarSizeWithMarker_Marker: int(0..2) +find s_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..2)] of int(1..2) +find s_Occurrence: matrix indexed by [int(1..2)] of bool +branching on + [s_Occurrence, s_ExplicitVarSizeWithDummy, s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithMarker_Values] +such that + or([q18 <= s_ExplicitVarSizeWithMarker_Marker /\ + s_ExplicitVarSizeWithMarker_Values[q18] = sum([toInt(s_ExplicitVarSizeWithDummy[q20] != 3) | q20 : int(1..2)]) + | q18 : int(1..2)]), + s_ExplicitVarSizeWithDummy[1] < s_ExplicitVarSizeWithDummy[2] \/ s_ExplicitVarSizeWithDummy[1] = 3, + s_ExplicitVarSizeWithDummy[1] = 3 -> s_ExplicitVarSizeWithDummy[2] = 3, + 2 <= s_ExplicitVarSizeWithMarker_Marker -> + s_ExplicitVarSizeWithMarker_Values[1] < s_ExplicitVarSizeWithMarker_Values[2], + and([q6 > s_ExplicitVarSizeWithMarker_Marker -> s_ExplicitVarSizeWithMarker_Values[q6] = 1 | q6 : int(1..2)]), + and([q9 <= s_ExplicitVarSizeWithMarker_Marker -> + or([s_ExplicitVarSizeWithDummy[q11] != 3 /\ + s_ExplicitVarSizeWithDummy[q11] = s_ExplicitVarSizeWithMarker_Values[q9] + | q11 : int(1..2)]) + | q9 : int(1..2)]), + and([s_ExplicitVarSizeWithDummy[q13] != 3 -> + or([q15 <= s_ExplicitVarSizeWithMarker_Marker /\ + s_ExplicitVarSizeWithMarker_Values[q15] = s_ExplicitVarSizeWithDummy[q13] + | q15 : int(1..2)]) + | q13 : int(1..2)]), + and([s_Occurrence[q21] -> + or([s_ExplicitVarSizeWithDummy[q23] != 3 /\ s_ExplicitVarSizeWithDummy[q23] = q21 | q23 : int(1..2)]) + | q21 : int(1..2)]), + and([s_ExplicitVarSizeWithDummy[q25] != 3 -> s_Occurrence[s_ExplicitVarSizeWithDummy[q25]] | q25 : int(1..2)]), + and([s_Occurrence[q26] -> + or([q28 <= s_ExplicitVarSizeWithMarker_Marker /\ s_ExplicitVarSizeWithMarker_Values[q28] = q26 + | q28 : int(1..2)]) + | q26 : int(1..2)]), + and([q30 <= s_ExplicitVarSizeWithMarker_Marker -> s_Occurrence[s_ExplicitVarSizeWithMarker_Values[q30]] + | q30 : int(1..2)]) + diff --git a/tests/exhaustive/basic/set_card_00/expected/model_2_3_2-solution000001.solution b/tests/exhaustive/basic/set_card_00/expected/model_2_3_2-solution000001.solution new file mode 100644 index 0000000000..6c0d0fdad8 --- /dev/null +++ b/tests/exhaustive/basic/set_card_00/expected/model_2_3_2-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting s be {1} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_2_3_2-solution000002.solution b/tests/exhaustive/basic/set_card_00/expected/model_2_3_2-solution000002.solution new file mode 100644 index 0000000000..2ce5f2081f --- /dev/null +++ b/tests/exhaustive/basic/set_card_00/expected/model_2_3_2-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting s be {1, 2} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_2_3_2.eprime b/tests/exhaustive/basic/set_card_00/expected/model_2_3_2.eprime new file mode 100644 index 0000000000..ab23a453ce --- /dev/null +++ b/tests/exhaustive/basic/set_card_00/expected/model_2_3_2.eprime @@ -0,0 +1,26 @@ +language ESSENCE' 1.0 + +find s_ExplicitVarSizeWithDummy: matrix indexed by [int(1..2)] of int(1..3) +find s_ExplicitVarSizeWithMarker_Marker: int(0..2) +find s_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..2)] of int(1..2) +branching on [s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithMarker_Values, s_ExplicitVarSizeWithDummy] +such that + or([q17 <= s_ExplicitVarSizeWithMarker_Marker /\ + s_ExplicitVarSizeWithMarker_Values[q17] = sum([toInt(s_ExplicitVarSizeWithDummy[q19] != 3) | q19 : int(1..2)]) + | q17 : int(1..2)]), + s_ExplicitVarSizeWithDummy[1] < s_ExplicitVarSizeWithDummy[2] \/ s_ExplicitVarSizeWithDummy[1] = 3, + s_ExplicitVarSizeWithDummy[1] = 3 -> s_ExplicitVarSizeWithDummy[2] = 3, + 2 <= s_ExplicitVarSizeWithMarker_Marker -> + s_ExplicitVarSizeWithMarker_Values[1] < s_ExplicitVarSizeWithMarker_Values[2], + and([q6 > s_ExplicitVarSizeWithMarker_Marker -> s_ExplicitVarSizeWithMarker_Values[q6] = 1 | q6 : int(1..2)]), + and([q9 <= s_ExplicitVarSizeWithMarker_Marker -> + or([s_ExplicitVarSizeWithDummy[q11] != 3 /\ + s_ExplicitVarSizeWithDummy[q11] = s_ExplicitVarSizeWithMarker_Values[q9] + | q11 : int(1..2)]) + | q9 : int(1..2)]), + and([s_ExplicitVarSizeWithDummy[q13] != 3 -> + or([q15 <= s_ExplicitVarSizeWithMarker_Marker /\ + s_ExplicitVarSizeWithMarker_Values[q15] = s_ExplicitVarSizeWithDummy[q13] + | q15 : int(1..2)]) + | q13 : int(1..2)]) + diff --git a/tests/exhaustive/basic/set_card_00/expected/model_2_3_4-solution000001.solution b/tests/exhaustive/basic/set_card_00/expected/model_2_3_4-solution000001.solution new file mode 100644 index 0000000000..6c0d0fdad8 --- /dev/null +++ b/tests/exhaustive/basic/set_card_00/expected/model_2_3_4-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting s be {1} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_2_3_4-solution000002.solution b/tests/exhaustive/basic/set_card_00/expected/model_2_3_4-solution000002.solution new file mode 100644 index 0000000000..2ce5f2081f --- /dev/null +++ b/tests/exhaustive/basic/set_card_00/expected/model_2_3_4-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting s be {1, 2} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_2_3_4.eprime b/tests/exhaustive/basic/set_card_00/expected/model_2_3_4.eprime new file mode 100644 index 0000000000..b8027d9587 --- /dev/null +++ b/tests/exhaustive/basic/set_card_00/expected/model_2_3_4.eprime @@ -0,0 +1,54 @@ +language ESSENCE' 1.0 + +find s_ExplicitVarSizeWithDummy: matrix indexed by [int(1..2)] of int(1..3) +find s_ExplicitVarSizeWithMarker_Marker: int(0..2) +find s_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..2)] of int(1..2) +find s_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..2)] of bool +find s_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..2)] of int(1..2) +branching on + [s_ExplicitVarSizeWithFlags_Flags, s_ExplicitVarSizeWithFlags_Values, s_ExplicitVarSizeWithDummy, + s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithMarker_Values] +such that + or([q38 <= s_ExplicitVarSizeWithMarker_Marker /\ + s_ExplicitVarSizeWithMarker_Values[q38] = sum([toInt(s_ExplicitVarSizeWithDummy[q40] != 3) | q40 : int(1..2)]) + | q38 : int(1..2)]), + s_ExplicitVarSizeWithDummy[1] < s_ExplicitVarSizeWithDummy[2] \/ s_ExplicitVarSizeWithDummy[1] = 3, + s_ExplicitVarSizeWithDummy[1] = 3 -> s_ExplicitVarSizeWithDummy[2] = 3, + 2 <= s_ExplicitVarSizeWithMarker_Marker -> + s_ExplicitVarSizeWithMarker_Values[1] < s_ExplicitVarSizeWithMarker_Values[2], + and([q6 > s_ExplicitVarSizeWithMarker_Marker -> s_ExplicitVarSizeWithMarker_Values[q6] = 1 | q6 : int(1..2)]), + and([q9 <= s_ExplicitVarSizeWithMarker_Marker -> + or([s_ExplicitVarSizeWithDummy[q11] != 3 /\ + s_ExplicitVarSizeWithDummy[q11] = s_ExplicitVarSizeWithMarker_Values[q9] + | q11 : int(1..2)]) + | q9 : int(1..2)]), + and([s_ExplicitVarSizeWithDummy[q13] != 3 -> + or([q15 <= s_ExplicitVarSizeWithMarker_Marker /\ + s_ExplicitVarSizeWithMarker_Values[q15] = s_ExplicitVarSizeWithDummy[q13] + | q15 : int(1..2)]) + | q13 : int(1..2)]), + s_ExplicitVarSizeWithFlags_Flags[2] -> s_ExplicitVarSizeWithFlags_Values[1] < s_ExplicitVarSizeWithFlags_Values[2], + and([s_ExplicitVarSizeWithFlags_Flags[q17] = false -> s_ExplicitVarSizeWithFlags_Values[q17] = 1 + | q17 : int(1..2)]), + s_ExplicitVarSizeWithFlags_Flags[2] -> s_ExplicitVarSizeWithFlags_Flags[1], + and([s_ExplicitVarSizeWithFlags_Flags[q22] -> + or([s_ExplicitVarSizeWithDummy[q24] != 3 /\ + s_ExplicitVarSizeWithDummy[q24] = s_ExplicitVarSizeWithFlags_Values[q22] + | q24 : int(1..2)]) + | q22 : int(1..2)]), + and([s_ExplicitVarSizeWithDummy[q26] != 3 -> + or([s_ExplicitVarSizeWithFlags_Flags[q28] /\ + s_ExplicitVarSizeWithFlags_Values[q28] = s_ExplicitVarSizeWithDummy[q26] + | q28 : int(1..2)]) + | q26 : int(1..2)]), + and([s_ExplicitVarSizeWithFlags_Flags[q30] -> + or([q32 <= s_ExplicitVarSizeWithMarker_Marker /\ + s_ExplicitVarSizeWithMarker_Values[q32] = s_ExplicitVarSizeWithFlags_Values[q30] + | q32 : int(1..2)]) + | q30 : int(1..2)]), + and([q34 <= s_ExplicitVarSizeWithMarker_Marker -> + or([s_ExplicitVarSizeWithFlags_Flags[q36] /\ + s_ExplicitVarSizeWithFlags_Values[q36] = s_ExplicitVarSizeWithMarker_Values[q34] + | q36 : int(1..2)]) + | q34 : int(1..2)]) + diff --git a/tests/exhaustive/basic/set_card_00/expected/model_2_4_1-solution000001.solution b/tests/exhaustive/basic/set_card_00/expected/model_2_4_1-solution000001.solution new file mode 100644 index 0000000000..6c0d0fdad8 --- /dev/null +++ b/tests/exhaustive/basic/set_card_00/expected/model_2_4_1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting s be {1} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_2_4_1-solution000002.solution b/tests/exhaustive/basic/set_card_00/expected/model_2_4_1-solution000002.solution new file mode 100644 index 0000000000..2ce5f2081f --- /dev/null +++ b/tests/exhaustive/basic/set_card_00/expected/model_2_4_1-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting s be {1, 2} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_2_4_1.eprime b/tests/exhaustive/basic/set_card_00/expected/model_2_4_1.eprime new file mode 100644 index 0000000000..9b0944284e --- /dev/null +++ b/tests/exhaustive/basic/set_card_00/expected/model_2_4_1.eprime @@ -0,0 +1,37 @@ +language ESSENCE' 1.0 + +find s_ExplicitVarSizeWithDummy: matrix indexed by [int(1..2)] of int(1..3) +find s_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..2)] of bool +find s_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..2)] of int(1..2) +find s_Occurrence: matrix indexed by [int(1..2)] of bool +branching on + [s_Occurrence, s_ExplicitVarSizeWithDummy, s_ExplicitVarSizeWithFlags_Flags, s_ExplicitVarSizeWithFlags_Values] +such that + or([s_ExplicitVarSizeWithFlags_Flags[q30] /\ + s_ExplicitVarSizeWithFlags_Values[q30] = sum([toInt(s_ExplicitVarSizeWithDummy[q32] != 3) | q32 : int(1..2)]) + | q30 : int(1..2)]), + s_ExplicitVarSizeWithDummy[1] < s_ExplicitVarSizeWithDummy[2] \/ s_ExplicitVarSizeWithDummy[1] = 3, + s_ExplicitVarSizeWithDummy[1] = 3 -> s_ExplicitVarSizeWithDummy[2] = 3, + s_ExplicitVarSizeWithFlags_Flags[2] -> s_ExplicitVarSizeWithFlags_Values[1] < s_ExplicitVarSizeWithFlags_Values[2], + and([s_ExplicitVarSizeWithFlags_Flags[q6] = false -> s_ExplicitVarSizeWithFlags_Values[q6] = 1 | q6 : int(1..2)]), + s_ExplicitVarSizeWithFlags_Flags[2] -> s_ExplicitVarSizeWithFlags_Flags[1], + and([s_ExplicitVarSizeWithFlags_Flags[q11] -> + or([s_ExplicitVarSizeWithDummy[q13] != 3 /\ + s_ExplicitVarSizeWithDummy[q13] = s_ExplicitVarSizeWithFlags_Values[q11] + | q13 : int(1..2)]) + | q11 : int(1..2)]), + and([s_ExplicitVarSizeWithDummy[q15] != 3 -> + or([s_ExplicitVarSizeWithFlags_Flags[q17] /\ + s_ExplicitVarSizeWithFlags_Values[q17] = s_ExplicitVarSizeWithDummy[q15] + | q17 : int(1..2)]) + | q15 : int(1..2)]), + and([s_Occurrence[q19] -> + or([s_ExplicitVarSizeWithDummy[q21] != 3 /\ s_ExplicitVarSizeWithDummy[q21] = q19 | q21 : int(1..2)]) + | q19 : int(1..2)]), + and([s_ExplicitVarSizeWithDummy[q23] != 3 -> s_Occurrence[s_ExplicitVarSizeWithDummy[q23]] | q23 : int(1..2)]), + and([s_Occurrence[q24] -> + or([s_ExplicitVarSizeWithFlags_Flags[q26] /\ s_ExplicitVarSizeWithFlags_Values[q26] = q24 | q26 : int(1..2)]) + | q24 : int(1..2)]), + and([s_ExplicitVarSizeWithFlags_Flags[q28] -> s_Occurrence[s_ExplicitVarSizeWithFlags_Values[q28]] + | q28 : int(1..2)]) + diff --git a/tests/exhaustive/basic/set_card_00/expected/model_2_4_2-solution000001.solution b/tests/exhaustive/basic/set_card_00/expected/model_2_4_2-solution000001.solution new file mode 100644 index 0000000000..6c0d0fdad8 --- /dev/null +++ b/tests/exhaustive/basic/set_card_00/expected/model_2_4_2-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting s be {1} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_2_4_2-solution000002.solution b/tests/exhaustive/basic/set_card_00/expected/model_2_4_2-solution000002.solution new file mode 100644 index 0000000000..2ce5f2081f --- /dev/null +++ b/tests/exhaustive/basic/set_card_00/expected/model_2_4_2-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting s be {1, 2} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_2_4_2.eprime b/tests/exhaustive/basic/set_card_00/expected/model_2_4_2.eprime new file mode 100644 index 0000000000..52e3cd4bb4 --- /dev/null +++ b/tests/exhaustive/basic/set_card_00/expected/model_2_4_2.eprime @@ -0,0 +1,26 @@ +language ESSENCE' 1.0 + +find s_ExplicitVarSizeWithDummy: matrix indexed by [int(1..2)] of int(1..3) +find s_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..2)] of bool +find s_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..2)] of int(1..2) +branching on [s_ExplicitVarSizeWithFlags_Flags, s_ExplicitVarSizeWithFlags_Values, s_ExplicitVarSizeWithDummy] +such that + or([s_ExplicitVarSizeWithFlags_Flags[q19] /\ + s_ExplicitVarSizeWithFlags_Values[q19] = sum([toInt(s_ExplicitVarSizeWithDummy[q21] != 3) | q21 : int(1..2)]) + | q19 : int(1..2)]), + s_ExplicitVarSizeWithDummy[1] < s_ExplicitVarSizeWithDummy[2] \/ s_ExplicitVarSizeWithDummy[1] = 3, + s_ExplicitVarSizeWithDummy[1] = 3 -> s_ExplicitVarSizeWithDummy[2] = 3, + s_ExplicitVarSizeWithFlags_Flags[2] -> s_ExplicitVarSizeWithFlags_Values[1] < s_ExplicitVarSizeWithFlags_Values[2], + and([s_ExplicitVarSizeWithFlags_Flags[q6] = false -> s_ExplicitVarSizeWithFlags_Values[q6] = 1 | q6 : int(1..2)]), + s_ExplicitVarSizeWithFlags_Flags[2] -> s_ExplicitVarSizeWithFlags_Flags[1], + and([s_ExplicitVarSizeWithFlags_Flags[q11] -> + or([s_ExplicitVarSizeWithDummy[q13] != 3 /\ + s_ExplicitVarSizeWithDummy[q13] = s_ExplicitVarSizeWithFlags_Values[q11] + | q13 : int(1..2)]) + | q11 : int(1..2)]), + and([s_ExplicitVarSizeWithDummy[q15] != 3 -> + or([s_ExplicitVarSizeWithFlags_Flags[q17] /\ + s_ExplicitVarSizeWithFlags_Values[q17] = s_ExplicitVarSizeWithDummy[q15] + | q17 : int(1..2)]) + | q15 : int(1..2)]) + diff --git a/tests/exhaustive/basic/set_card_00/expected/model_2_4_3-solution000001.solution b/tests/exhaustive/basic/set_card_00/expected/model_2_4_3-solution000001.solution new file mode 100644 index 0000000000..6c0d0fdad8 --- /dev/null +++ b/tests/exhaustive/basic/set_card_00/expected/model_2_4_3-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting s be {1} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_2_4_3-solution000002.solution b/tests/exhaustive/basic/set_card_00/expected/model_2_4_3-solution000002.solution new file mode 100644 index 0000000000..2ce5f2081f --- /dev/null +++ b/tests/exhaustive/basic/set_card_00/expected/model_2_4_3-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting s be {1, 2} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_2_4_3.eprime b/tests/exhaustive/basic/set_card_00/expected/model_2_4_3.eprime new file mode 100644 index 0000000000..d77907f01f --- /dev/null +++ b/tests/exhaustive/basic/set_card_00/expected/model_2_4_3.eprime @@ -0,0 +1,53 @@ +language ESSENCE' 1.0 + +find s_ExplicitVarSizeWithDummy: matrix indexed by [int(1..2)] of int(1..3) +find s_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..2)] of bool +find s_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..2)] of int(1..2) +find s_ExplicitVarSizeWithMarker_Marker: int(0..2) +find s_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..2)] of int(1..2) +branching on + [s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithMarker_Values, s_ExplicitVarSizeWithDummy, + s_ExplicitVarSizeWithFlags_Flags, s_ExplicitVarSizeWithFlags_Values] +such that + or([s_ExplicitVarSizeWithFlags_Flags[q38] /\ + s_ExplicitVarSizeWithFlags_Values[q38] = sum([toInt(s_ExplicitVarSizeWithDummy[q40] != 3) | q40 : int(1..2)]) + | q38 : int(1..2)]), + s_ExplicitVarSizeWithDummy[1] < s_ExplicitVarSizeWithDummy[2] \/ s_ExplicitVarSizeWithDummy[1] = 3, + s_ExplicitVarSizeWithDummy[1] = 3 -> s_ExplicitVarSizeWithDummy[2] = 3, + s_ExplicitVarSizeWithFlags_Flags[2] -> s_ExplicitVarSizeWithFlags_Values[1] < s_ExplicitVarSizeWithFlags_Values[2], + and([s_ExplicitVarSizeWithFlags_Flags[q6] = false -> s_ExplicitVarSizeWithFlags_Values[q6] = 1 | q6 : int(1..2)]), + s_ExplicitVarSizeWithFlags_Flags[2] -> s_ExplicitVarSizeWithFlags_Flags[1], + and([s_ExplicitVarSizeWithFlags_Flags[q11] -> + or([s_ExplicitVarSizeWithDummy[q13] != 3 /\ + s_ExplicitVarSizeWithDummy[q13] = s_ExplicitVarSizeWithFlags_Values[q11] + | q13 : int(1..2)]) + | q11 : int(1..2)]), + and([s_ExplicitVarSizeWithDummy[q15] != 3 -> + or([s_ExplicitVarSizeWithFlags_Flags[q17] /\ + s_ExplicitVarSizeWithFlags_Values[q17] = s_ExplicitVarSizeWithDummy[q15] + | q17 : int(1..2)]) + | q15 : int(1..2)]), + 2 <= s_ExplicitVarSizeWithMarker_Marker -> + s_ExplicitVarSizeWithMarker_Values[1] < s_ExplicitVarSizeWithMarker_Values[2], + and([q19 > s_ExplicitVarSizeWithMarker_Marker -> s_ExplicitVarSizeWithMarker_Values[q19] = 1 | q19 : int(1..2)]), + and([q22 <= s_ExplicitVarSizeWithMarker_Marker -> + or([s_ExplicitVarSizeWithDummy[q24] != 3 /\ + s_ExplicitVarSizeWithDummy[q24] = s_ExplicitVarSizeWithMarker_Values[q22] + | q24 : int(1..2)]) + | q22 : int(1..2)]), + and([s_ExplicitVarSizeWithDummy[q26] != 3 -> + or([q28 <= s_ExplicitVarSizeWithMarker_Marker /\ + s_ExplicitVarSizeWithMarker_Values[q28] = s_ExplicitVarSizeWithDummy[q26] + | q28 : int(1..2)]) + | q26 : int(1..2)]), + and([q30 <= s_ExplicitVarSizeWithMarker_Marker -> + or([s_ExplicitVarSizeWithFlags_Flags[q32] /\ + s_ExplicitVarSizeWithFlags_Values[q32] = s_ExplicitVarSizeWithMarker_Values[q30] + | q32 : int(1..2)]) + | q30 : int(1..2)]), + and([s_ExplicitVarSizeWithFlags_Flags[q34] -> + or([q36 <= s_ExplicitVarSizeWithMarker_Marker /\ + s_ExplicitVarSizeWithMarker_Values[q36] = s_ExplicitVarSizeWithFlags_Values[q34] + | q36 : int(1..2)]) + | q34 : int(1..2)]) + diff --git a/tests/exhaustive/basic/set_card_00/expected/model_3_1_1-solution000001.solution b/tests/exhaustive/basic/set_card_00/expected/model_3_1_1-solution000001.solution new file mode 100644 index 0000000000..6c0d0fdad8 --- /dev/null +++ b/tests/exhaustive/basic/set_card_00/expected/model_3_1_1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting s be {1} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_3_1_1-solution000002.solution b/tests/exhaustive/basic/set_card_00/expected/model_3_1_1-solution000002.solution new file mode 100644 index 0000000000..2ce5f2081f --- /dev/null +++ b/tests/exhaustive/basic/set_card_00/expected/model_3_1_1-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting s be {1, 2} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_3_1_1.eprime b/tests/exhaustive/basic/set_card_00/expected/model_3_1_1.eprime new file mode 100644 index 0000000000..e844855cfd --- /dev/null +++ b/tests/exhaustive/basic/set_card_00/expected/model_3_1_1.eprime @@ -0,0 +1,17 @@ +language ESSENCE' 1.0 + +find s_ExplicitVarSizeWithMarker_Marker: int(0..2) +find s_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..2)] of int(1..2) +find s_Occurrence: matrix indexed by [int(1..2)] of bool +branching on [s_Occurrence, s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithMarker_Values] +such that + s_Occurrence[s_ExplicitVarSizeWithMarker_Marker], + 2 <= s_ExplicitVarSizeWithMarker_Marker -> + s_ExplicitVarSizeWithMarker_Values[1] < s_ExplicitVarSizeWithMarker_Values[2], + and([q2 > s_ExplicitVarSizeWithMarker_Marker -> s_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..2)]), + and([s_Occurrence[q5] -> + or([q7 <= s_ExplicitVarSizeWithMarker_Marker /\ s_ExplicitVarSizeWithMarker_Values[q7] = q5 | q7 : int(1..2)]) + | q5 : int(1..2)]), + and([q9 <= s_ExplicitVarSizeWithMarker_Marker -> s_Occurrence[s_ExplicitVarSizeWithMarker_Values[q9]] + | q9 : int(1..2)]) + diff --git a/tests/exhaustive/basic/set_card_00/expected/model_3_1_2-solution000001.solution b/tests/exhaustive/basic/set_card_00/expected/model_3_1_2-solution000001.solution new file mode 100644 index 0000000000..2ce5f2081f --- /dev/null +++ b/tests/exhaustive/basic/set_card_00/expected/model_3_1_2-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting s be {1, 2} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_3_1_2-solution000002.solution b/tests/exhaustive/basic/set_card_00/expected/model_3_1_2-solution000002.solution new file mode 100644 index 0000000000..6c0d0fdad8 --- /dev/null +++ b/tests/exhaustive/basic/set_card_00/expected/model_3_1_2-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting s be {1} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_3_1_2.eprime b/tests/exhaustive/basic/set_card_00/expected/model_3_1_2.eprime new file mode 100644 index 0000000000..14e09f9356 --- /dev/null +++ b/tests/exhaustive/basic/set_card_00/expected/model_3_1_2.eprime @@ -0,0 +1,36 @@ +language ESSENCE' 1.0 + +find s_ExplicitVarSizeWithMarker_Marker: int(0..2) +find s_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..2)] of int(1..2) +find s_Occurrence: matrix indexed by [int(1..2)] of bool +find s_ExplicitVarSizeWithDummy: matrix indexed by [int(1..2)] of int(1..3) +branching on + [s_ExplicitVarSizeWithDummy, s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithMarker_Values, s_Occurrence] +such that + s_Occurrence[s_ExplicitVarSizeWithMarker_Marker], + 2 <= s_ExplicitVarSizeWithMarker_Marker -> + s_ExplicitVarSizeWithMarker_Values[1] < s_ExplicitVarSizeWithMarker_Values[2], + and([q2 > s_ExplicitVarSizeWithMarker_Marker -> s_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..2)]), + and([s_Occurrence[q22] -> + or([q24 <= s_ExplicitVarSizeWithMarker_Marker /\ s_ExplicitVarSizeWithMarker_Values[q24] = q22 + | q24 : int(1..2)]) + | q22 : int(1..2)]), + and([q26 <= s_ExplicitVarSizeWithMarker_Marker -> s_Occurrence[s_ExplicitVarSizeWithMarker_Values[q26]] + | q26 : int(1..2)]), + s_ExplicitVarSizeWithDummy[1] < s_ExplicitVarSizeWithDummy[2] \/ s_ExplicitVarSizeWithDummy[1] = 3, + s_ExplicitVarSizeWithDummy[1] = 3 -> s_ExplicitVarSizeWithDummy[2] = 3, + and([s_ExplicitVarSizeWithDummy[q10] != 3 -> + or([q12 <= s_ExplicitVarSizeWithMarker_Marker /\ + s_ExplicitVarSizeWithMarker_Values[q12] = s_ExplicitVarSizeWithDummy[q10] + | q12 : int(1..2)]) + | q10 : int(1..2)]), + and([q14 <= s_ExplicitVarSizeWithMarker_Marker -> + or([s_ExplicitVarSizeWithDummy[q16] != 3 /\ + s_ExplicitVarSizeWithDummy[q16] = s_ExplicitVarSizeWithMarker_Values[q14] + | q16 : int(1..2)]) + | q14 : int(1..2)]), + and([s_ExplicitVarSizeWithDummy[q18] != 3 -> s_Occurrence[s_ExplicitVarSizeWithDummy[q18]] | q18 : int(1..2)]), + and([s_Occurrence[q19] -> + or([s_ExplicitVarSizeWithDummy[q21] != 3 /\ s_ExplicitVarSizeWithDummy[q21] = q19 | q21 : int(1..2)]) + | q19 : int(1..2)]) + diff --git a/tests/exhaustive/basic/set_card_00/expected/model_3_1_4-solution000001.solution b/tests/exhaustive/basic/set_card_00/expected/model_3_1_4-solution000001.solution new file mode 100644 index 0000000000..6c0d0fdad8 --- /dev/null +++ b/tests/exhaustive/basic/set_card_00/expected/model_3_1_4-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting s be {1} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_3_1_4-solution000002.solution b/tests/exhaustive/basic/set_card_00/expected/model_3_1_4-solution000002.solution new file mode 100644 index 0000000000..2ce5f2081f --- /dev/null +++ b/tests/exhaustive/basic/set_card_00/expected/model_3_1_4-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting s be {1, 2} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_3_1_4.eprime b/tests/exhaustive/basic/set_card_00/expected/model_3_1_4.eprime new file mode 100644 index 0000000000..9425709c75 --- /dev/null +++ b/tests/exhaustive/basic/set_card_00/expected/model_3_1_4.eprime @@ -0,0 +1,40 @@ +language ESSENCE' 1.0 + +find s_ExplicitVarSizeWithMarker_Marker: int(0..2) +find s_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..2)] of int(1..2) +find s_Occurrence: matrix indexed by [int(1..2)] of bool +find s_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..2)] of bool +find s_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..2)] of int(1..2) +branching on + [s_ExplicitVarSizeWithFlags_Flags, s_ExplicitVarSizeWithFlags_Values, s_ExplicitVarSizeWithMarker_Marker, + s_ExplicitVarSizeWithMarker_Values, s_Occurrence] +such that + s_Occurrence[s_ExplicitVarSizeWithMarker_Marker], + 2 <= s_ExplicitVarSizeWithMarker_Marker -> + s_ExplicitVarSizeWithMarker_Values[1] < s_ExplicitVarSizeWithMarker_Values[2], + and([q2 > s_ExplicitVarSizeWithMarker_Marker -> s_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..2)]), + and([s_Occurrence[q23] -> + or([q25 <= s_ExplicitVarSizeWithMarker_Marker /\ s_ExplicitVarSizeWithMarker_Values[q25] = q23 + | q25 : int(1..2)]) + | q23 : int(1..2)]), + and([q27 <= s_ExplicitVarSizeWithMarker_Marker -> s_Occurrence[s_ExplicitVarSizeWithMarker_Values[q27]] + | q27 : int(1..2)]), + s_ExplicitVarSizeWithFlags_Flags[2] -> s_ExplicitVarSizeWithFlags_Values[1] < s_ExplicitVarSizeWithFlags_Values[2], + and([s_ExplicitVarSizeWithFlags_Flags[q6] = false -> s_ExplicitVarSizeWithFlags_Values[q6] = 1 | q6 : int(1..2)]), + s_ExplicitVarSizeWithFlags_Flags[2] -> s_ExplicitVarSizeWithFlags_Flags[1], + and([s_ExplicitVarSizeWithFlags_Flags[q11] -> + or([q13 <= s_ExplicitVarSizeWithMarker_Marker /\ + s_ExplicitVarSizeWithMarker_Values[q13] = s_ExplicitVarSizeWithFlags_Values[q11] + | q13 : int(1..2)]) + | q11 : int(1..2)]), + and([q15 <= s_ExplicitVarSizeWithMarker_Marker -> + or([s_ExplicitVarSizeWithFlags_Flags[q17] /\ + s_ExplicitVarSizeWithFlags_Values[q17] = s_ExplicitVarSizeWithMarker_Values[q15] + | q17 : int(1..2)]) + | q15 : int(1..2)]), + and([s_ExplicitVarSizeWithFlags_Flags[q19] -> s_Occurrence[s_ExplicitVarSizeWithFlags_Values[q19]] + | q19 : int(1..2)]), + and([s_Occurrence[q20] -> + or([s_ExplicitVarSizeWithFlags_Flags[q22] /\ s_ExplicitVarSizeWithFlags_Values[q22] = q20 | q22 : int(1..2)]) + | q20 : int(1..2)]) + diff --git a/tests/exhaustive/basic/set_card_00/expected/model_3_2_1-solution000001.solution b/tests/exhaustive/basic/set_card_00/expected/model_3_2_1-solution000001.solution new file mode 100644 index 0000000000..6c0d0fdad8 --- /dev/null +++ b/tests/exhaustive/basic/set_card_00/expected/model_3_2_1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting s be {1} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_3_2_1-solution000002.solution b/tests/exhaustive/basic/set_card_00/expected/model_3_2_1-solution000002.solution new file mode 100644 index 0000000000..2ce5f2081f --- /dev/null +++ b/tests/exhaustive/basic/set_card_00/expected/model_3_2_1-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting s be {1, 2} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_3_2_1.eprime b/tests/exhaustive/basic/set_card_00/expected/model_3_2_1.eprime new file mode 100644 index 0000000000..3f3dfb7cd2 --- /dev/null +++ b/tests/exhaustive/basic/set_card_00/expected/model_3_2_1.eprime @@ -0,0 +1,37 @@ +language ESSENCE' 1.0 + +find s_ExplicitVarSizeWithMarker_Marker: int(0..2) +find s_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..2)] of int(1..2) +find s_ExplicitVarSizeWithDummy: matrix indexed by [int(1..2)] of int(1..3) +find s_Occurrence: matrix indexed by [int(1..2)] of bool +branching on + [s_Occurrence, s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithMarker_Values, s_ExplicitVarSizeWithDummy] +such that + or([s_ExplicitVarSizeWithDummy[q18] != 3 /\ s_ExplicitVarSizeWithDummy[q18] = s_ExplicitVarSizeWithMarker_Marker + | q18 : int(1..2)]), + 2 <= s_ExplicitVarSizeWithMarker_Marker -> + s_ExplicitVarSizeWithMarker_Values[1] < s_ExplicitVarSizeWithMarker_Values[2], + and([q2 > s_ExplicitVarSizeWithMarker_Marker -> s_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..2)]), + s_ExplicitVarSizeWithDummy[1] < s_ExplicitVarSizeWithDummy[2] \/ s_ExplicitVarSizeWithDummy[1] = 3, + s_ExplicitVarSizeWithDummy[1] = 3 -> s_ExplicitVarSizeWithDummy[2] = 3, + and([s_ExplicitVarSizeWithDummy[q9] != 3 -> + or([q11 <= s_ExplicitVarSizeWithMarker_Marker /\ + s_ExplicitVarSizeWithMarker_Values[q11] = s_ExplicitVarSizeWithDummy[q9] + | q11 : int(1..2)]) + | q9 : int(1..2)]), + and([q13 <= s_ExplicitVarSizeWithMarker_Marker -> + or([s_ExplicitVarSizeWithDummy[q15] != 3 /\ + s_ExplicitVarSizeWithDummy[q15] = s_ExplicitVarSizeWithMarker_Values[q13] + | q15 : int(1..2)]) + | q13 : int(1..2)]), + and([s_Occurrence[q19] -> + or([q21 <= s_ExplicitVarSizeWithMarker_Marker /\ s_ExplicitVarSizeWithMarker_Values[q21] = q19 + | q21 : int(1..2)]) + | q19 : int(1..2)]), + and([q23 <= s_ExplicitVarSizeWithMarker_Marker -> s_Occurrence[s_ExplicitVarSizeWithMarker_Values[q23]] + | q23 : int(1..2)]), + and([s_Occurrence[q24] -> + or([s_ExplicitVarSizeWithDummy[q26] != 3 /\ s_ExplicitVarSizeWithDummy[q26] = q24 | q26 : int(1..2)]) + | q24 : int(1..2)]), + and([s_ExplicitVarSizeWithDummy[q28] != 3 -> s_Occurrence[s_ExplicitVarSizeWithDummy[q28]] | q28 : int(1..2)]) + diff --git a/tests/exhaustive/basic/set_card_00/expected/model_3_2_2-solution000001.solution b/tests/exhaustive/basic/set_card_00/expected/model_3_2_2-solution000001.solution new file mode 100644 index 0000000000..2ce5f2081f --- /dev/null +++ b/tests/exhaustive/basic/set_card_00/expected/model_3_2_2-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting s be {1, 2} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_3_2_2-solution000002.solution b/tests/exhaustive/basic/set_card_00/expected/model_3_2_2-solution000002.solution new file mode 100644 index 0000000000..6c0d0fdad8 --- /dev/null +++ b/tests/exhaustive/basic/set_card_00/expected/model_3_2_2-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting s be {1} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_3_2_2.eprime b/tests/exhaustive/basic/set_card_00/expected/model_3_2_2.eprime new file mode 100644 index 0000000000..a9af356a26 --- /dev/null +++ b/tests/exhaustive/basic/set_card_00/expected/model_3_2_2.eprime @@ -0,0 +1,25 @@ +language ESSENCE' 1.0 + +find s_ExplicitVarSizeWithMarker_Marker: int(0..2) +find s_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..2)] of int(1..2) +find s_ExplicitVarSizeWithDummy: matrix indexed by [int(1..2)] of int(1..3) +branching on [s_ExplicitVarSizeWithDummy, s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithMarker_Values] +such that + or([s_ExplicitVarSizeWithDummy[q17] != 3 /\ s_ExplicitVarSizeWithDummy[q17] = s_ExplicitVarSizeWithMarker_Marker + | q17 : int(1..2)]), + 2 <= s_ExplicitVarSizeWithMarker_Marker -> + s_ExplicitVarSizeWithMarker_Values[1] < s_ExplicitVarSizeWithMarker_Values[2], + and([q2 > s_ExplicitVarSizeWithMarker_Marker -> s_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..2)]), + s_ExplicitVarSizeWithDummy[1] < s_ExplicitVarSizeWithDummy[2] \/ s_ExplicitVarSizeWithDummy[1] = 3, + s_ExplicitVarSizeWithDummy[1] = 3 -> s_ExplicitVarSizeWithDummy[2] = 3, + and([s_ExplicitVarSizeWithDummy[q9] != 3 -> + or([q11 <= s_ExplicitVarSizeWithMarker_Marker /\ + s_ExplicitVarSizeWithMarker_Values[q11] = s_ExplicitVarSizeWithDummy[q9] + | q11 : int(1..2)]) + | q9 : int(1..2)]), + and([q13 <= s_ExplicitVarSizeWithMarker_Marker -> + or([s_ExplicitVarSizeWithDummy[q15] != 3 /\ + s_ExplicitVarSizeWithDummy[q15] = s_ExplicitVarSizeWithMarker_Values[q13] + | q15 : int(1..2)]) + | q13 : int(1..2)]) + diff --git a/tests/exhaustive/basic/set_card_00/expected/model_3_2_4-solution000001.solution b/tests/exhaustive/basic/set_card_00/expected/model_3_2_4-solution000001.solution new file mode 100644 index 0000000000..6c0d0fdad8 --- /dev/null +++ b/tests/exhaustive/basic/set_card_00/expected/model_3_2_4-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting s be {1} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_3_2_4-solution000002.solution b/tests/exhaustive/basic/set_card_00/expected/model_3_2_4-solution000002.solution new file mode 100644 index 0000000000..2ce5f2081f --- /dev/null +++ b/tests/exhaustive/basic/set_card_00/expected/model_3_2_4-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting s be {1, 2} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_3_2_4.eprime b/tests/exhaustive/basic/set_card_00/expected/model_3_2_4.eprime new file mode 100644 index 0000000000..b4d1060382 --- /dev/null +++ b/tests/exhaustive/basic/set_card_00/expected/model_3_2_4.eprime @@ -0,0 +1,53 @@ +language ESSENCE' 1.0 + +find s_ExplicitVarSizeWithMarker_Marker: int(0..2) +find s_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..2)] of int(1..2) +find s_ExplicitVarSizeWithDummy: matrix indexed by [int(1..2)] of int(1..3) +find s_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..2)] of bool +find s_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..2)] of int(1..2) +branching on + [s_ExplicitVarSizeWithFlags_Flags, s_ExplicitVarSizeWithFlags_Values, s_ExplicitVarSizeWithMarker_Marker, + s_ExplicitVarSizeWithMarker_Values, s_ExplicitVarSizeWithDummy] +such that + or([s_ExplicitVarSizeWithDummy[q38] != 3 /\ s_ExplicitVarSizeWithDummy[q38] = s_ExplicitVarSizeWithMarker_Marker + | q38 : int(1..2)]), + 2 <= s_ExplicitVarSizeWithMarker_Marker -> + s_ExplicitVarSizeWithMarker_Values[1] < s_ExplicitVarSizeWithMarker_Values[2], + and([q2 > s_ExplicitVarSizeWithMarker_Marker -> s_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..2)]), + s_ExplicitVarSizeWithDummy[1] < s_ExplicitVarSizeWithDummy[2] \/ s_ExplicitVarSizeWithDummy[1] = 3, + s_ExplicitVarSizeWithDummy[1] = 3 -> s_ExplicitVarSizeWithDummy[2] = 3, + and([s_ExplicitVarSizeWithDummy[q9] != 3 -> + or([q11 <= s_ExplicitVarSizeWithMarker_Marker /\ + s_ExplicitVarSizeWithMarker_Values[q11] = s_ExplicitVarSizeWithDummy[q9] + | q11 : int(1..2)]) + | q9 : int(1..2)]), + and([q13 <= s_ExplicitVarSizeWithMarker_Marker -> + or([s_ExplicitVarSizeWithDummy[q15] != 3 /\ + s_ExplicitVarSizeWithDummy[q15] = s_ExplicitVarSizeWithMarker_Values[q13] + | q15 : int(1..2)]) + | q13 : int(1..2)]), + s_ExplicitVarSizeWithFlags_Flags[2] -> s_ExplicitVarSizeWithFlags_Values[1] < s_ExplicitVarSizeWithFlags_Values[2], + and([s_ExplicitVarSizeWithFlags_Flags[q17] = false -> s_ExplicitVarSizeWithFlags_Values[q17] = 1 + | q17 : int(1..2)]), + s_ExplicitVarSizeWithFlags_Flags[2] -> s_ExplicitVarSizeWithFlags_Flags[1], + and([s_ExplicitVarSizeWithFlags_Flags[q22] -> + or([q24 <= s_ExplicitVarSizeWithMarker_Marker /\ + s_ExplicitVarSizeWithMarker_Values[q24] = s_ExplicitVarSizeWithFlags_Values[q22] + | q24 : int(1..2)]) + | q22 : int(1..2)]), + and([q26 <= s_ExplicitVarSizeWithMarker_Marker -> + or([s_ExplicitVarSizeWithFlags_Flags[q28] /\ + s_ExplicitVarSizeWithFlags_Values[q28] = s_ExplicitVarSizeWithMarker_Values[q26] + | q28 : int(1..2)]) + | q26 : int(1..2)]), + and([s_ExplicitVarSizeWithFlags_Flags[q30] -> + or([s_ExplicitVarSizeWithDummy[q32] != 3 /\ + s_ExplicitVarSizeWithDummy[q32] = s_ExplicitVarSizeWithFlags_Values[q30] + | q32 : int(1..2)]) + | q30 : int(1..2)]), + and([s_ExplicitVarSizeWithDummy[q34] != 3 -> + or([s_ExplicitVarSizeWithFlags_Flags[q36] /\ + s_ExplicitVarSizeWithFlags_Values[q36] = s_ExplicitVarSizeWithDummy[q34] + | q36 : int(1..2)]) + | q34 : int(1..2)]) + diff --git a/tests/exhaustive/basic/set_card_00/expected/model_3_3_1-solution000001.solution b/tests/exhaustive/basic/set_card_00/expected/model_3_3_1-solution000001.solution new file mode 100644 index 0000000000..6c0d0fdad8 --- /dev/null +++ b/tests/exhaustive/basic/set_card_00/expected/model_3_3_1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting s be {1} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_3_3_1-solution000002.solution b/tests/exhaustive/basic/set_card_00/expected/model_3_3_1-solution000002.solution new file mode 100644 index 0000000000..2ce5f2081f --- /dev/null +++ b/tests/exhaustive/basic/set_card_00/expected/model_3_3_1-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting s be {1, 2} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_3_3_1.eprime b/tests/exhaustive/basic/set_card_00/expected/model_3_3_1.eprime new file mode 100644 index 0000000000..09493a4fe3 --- /dev/null +++ b/tests/exhaustive/basic/set_card_00/expected/model_3_3_1.eprime @@ -0,0 +1,19 @@ +language ESSENCE' 1.0 + +find s_ExplicitVarSizeWithMarker_Marker: int(0..2) +find s_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..2)] of int(1..2) +find s_Occurrence: matrix indexed by [int(1..2)] of bool +branching on [s_Occurrence, s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithMarker_Values] +such that + or([q6 <= s_ExplicitVarSizeWithMarker_Marker /\ + s_ExplicitVarSizeWithMarker_Values[q6] = s_ExplicitVarSizeWithMarker_Marker + | q6 : int(1..2)]), + 2 <= s_ExplicitVarSizeWithMarker_Marker -> + s_ExplicitVarSizeWithMarker_Values[1] < s_ExplicitVarSizeWithMarker_Values[2], + and([q2 > s_ExplicitVarSizeWithMarker_Marker -> s_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..2)]), + and([s_Occurrence[q7] -> + or([q9 <= s_ExplicitVarSizeWithMarker_Marker /\ s_ExplicitVarSizeWithMarker_Values[q9] = q7 | q9 : int(1..2)]) + | q7 : int(1..2)]), + and([q11 <= s_ExplicitVarSizeWithMarker_Marker -> s_Occurrence[s_ExplicitVarSizeWithMarker_Values[q11]] + | q11 : int(1..2)]) + diff --git a/tests/exhaustive/basic/set_card_00/expected/model_3_3_2-solution000001.solution b/tests/exhaustive/basic/set_card_00/expected/model_3_3_2-solution000001.solution new file mode 100644 index 0000000000..2ce5f2081f --- /dev/null +++ b/tests/exhaustive/basic/set_card_00/expected/model_3_3_2-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting s be {1, 2} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_3_3_2-solution000002.solution b/tests/exhaustive/basic/set_card_00/expected/model_3_3_2-solution000002.solution new file mode 100644 index 0000000000..6c0d0fdad8 --- /dev/null +++ b/tests/exhaustive/basic/set_card_00/expected/model_3_3_2-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting s be {1} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_3_3_2.eprime b/tests/exhaustive/basic/set_card_00/expected/model_3_3_2.eprime new file mode 100644 index 0000000000..2b66d82f1b --- /dev/null +++ b/tests/exhaustive/basic/set_card_00/expected/model_3_3_2.eprime @@ -0,0 +1,26 @@ +language ESSENCE' 1.0 + +find s_ExplicitVarSizeWithMarker_Marker: int(0..2) +find s_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..2)] of int(1..2) +find s_ExplicitVarSizeWithDummy: matrix indexed by [int(1..2)] of int(1..3) +branching on [s_ExplicitVarSizeWithDummy, s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithMarker_Values] +such that + or([q17 <= s_ExplicitVarSizeWithMarker_Marker /\ + s_ExplicitVarSizeWithMarker_Values[q17] = s_ExplicitVarSizeWithMarker_Marker + | q17 : int(1..2)]), + 2 <= s_ExplicitVarSizeWithMarker_Marker -> + s_ExplicitVarSizeWithMarker_Values[1] < s_ExplicitVarSizeWithMarker_Values[2], + and([q2 > s_ExplicitVarSizeWithMarker_Marker -> s_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..2)]), + s_ExplicitVarSizeWithDummy[1] < s_ExplicitVarSizeWithDummy[2] \/ s_ExplicitVarSizeWithDummy[1] = 3, + s_ExplicitVarSizeWithDummy[1] = 3 -> s_ExplicitVarSizeWithDummy[2] = 3, + and([s_ExplicitVarSizeWithDummy[q9] != 3 -> + or([q11 <= s_ExplicitVarSizeWithMarker_Marker /\ + s_ExplicitVarSizeWithMarker_Values[q11] = s_ExplicitVarSizeWithDummy[q9] + | q11 : int(1..2)]) + | q9 : int(1..2)]), + and([q13 <= s_ExplicitVarSizeWithMarker_Marker -> + or([s_ExplicitVarSizeWithDummy[q15] != 3 /\ + s_ExplicitVarSizeWithDummy[q15] = s_ExplicitVarSizeWithMarker_Values[q13] + | q15 : int(1..2)]) + | q13 : int(1..2)]) + diff --git a/tests/exhaustive/basic/set_card_00/expected/model_3_3_3-solution000001.solution b/tests/exhaustive/basic/set_card_00/expected/model_3_3_3-solution000001.solution new file mode 100644 index 0000000000..6c0d0fdad8 --- /dev/null +++ b/tests/exhaustive/basic/set_card_00/expected/model_3_3_3-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting s be {1} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_3_3_3-solution000002.solution b/tests/exhaustive/basic/set_card_00/expected/model_3_3_3-solution000002.solution new file mode 100644 index 0000000000..2ce5f2081f --- /dev/null +++ b/tests/exhaustive/basic/set_card_00/expected/model_3_3_3-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting s be {1, 2} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_3_3_3.eprime b/tests/exhaustive/basic/set_card_00/expected/model_3_3_3.eprime new file mode 100644 index 0000000000..8abe0820c9 --- /dev/null +++ b/tests/exhaustive/basic/set_card_00/expected/model_3_3_3.eprime @@ -0,0 +1,13 @@ +language ESSENCE' 1.0 + +find s_ExplicitVarSizeWithMarker_Marker: int(0..2) +find s_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..2)] of int(1..2) +branching on [s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithMarker_Values] +such that + or([q5 <= s_ExplicitVarSizeWithMarker_Marker /\ + s_ExplicitVarSizeWithMarker_Values[q5] = s_ExplicitVarSizeWithMarker_Marker + | q5 : int(1..2)]), + 2 <= s_ExplicitVarSizeWithMarker_Marker -> + s_ExplicitVarSizeWithMarker_Values[1] < s_ExplicitVarSizeWithMarker_Values[2], + and([q2 > s_ExplicitVarSizeWithMarker_Marker -> s_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..2)]) + diff --git a/tests/exhaustive/basic/set_card_00/expected/model_3_3_4-solution000001.solution b/tests/exhaustive/basic/set_card_00/expected/model_3_3_4-solution000001.solution new file mode 100644 index 0000000000..6c0d0fdad8 --- /dev/null +++ b/tests/exhaustive/basic/set_card_00/expected/model_3_3_4-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting s be {1} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_3_3_4-solution000002.solution b/tests/exhaustive/basic/set_card_00/expected/model_3_3_4-solution000002.solution new file mode 100644 index 0000000000..2ce5f2081f --- /dev/null +++ b/tests/exhaustive/basic/set_card_00/expected/model_3_3_4-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting s be {1, 2} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_3_3_4.eprime b/tests/exhaustive/basic/set_card_00/expected/model_3_3_4.eprime new file mode 100644 index 0000000000..4334952115 --- /dev/null +++ b/tests/exhaustive/basic/set_card_00/expected/model_3_3_4.eprime @@ -0,0 +1,30 @@ +language ESSENCE' 1.0 + +find s_ExplicitVarSizeWithMarker_Marker: int(0..2) +find s_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..2)] of int(1..2) +find s_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..2)] of bool +find s_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..2)] of int(1..2) +branching on + [s_ExplicitVarSizeWithFlags_Flags, s_ExplicitVarSizeWithFlags_Values, s_ExplicitVarSizeWithMarker_Marker, + s_ExplicitVarSizeWithMarker_Values] +such that + or([q18 <= s_ExplicitVarSizeWithMarker_Marker /\ + s_ExplicitVarSizeWithMarker_Values[q18] = s_ExplicitVarSizeWithMarker_Marker + | q18 : int(1..2)]), + 2 <= s_ExplicitVarSizeWithMarker_Marker -> + s_ExplicitVarSizeWithMarker_Values[1] < s_ExplicitVarSizeWithMarker_Values[2], + and([q2 > s_ExplicitVarSizeWithMarker_Marker -> s_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..2)]), + s_ExplicitVarSizeWithFlags_Flags[2] -> s_ExplicitVarSizeWithFlags_Values[1] < s_ExplicitVarSizeWithFlags_Values[2], + and([s_ExplicitVarSizeWithFlags_Flags[q5] = false -> s_ExplicitVarSizeWithFlags_Values[q5] = 1 | q5 : int(1..2)]), + s_ExplicitVarSizeWithFlags_Flags[2] -> s_ExplicitVarSizeWithFlags_Flags[1], + and([s_ExplicitVarSizeWithFlags_Flags[q10] -> + or([q12 <= s_ExplicitVarSizeWithMarker_Marker /\ + s_ExplicitVarSizeWithMarker_Values[q12] = s_ExplicitVarSizeWithFlags_Values[q10] + | q12 : int(1..2)]) + | q10 : int(1..2)]), + and([q14 <= s_ExplicitVarSizeWithMarker_Marker -> + or([s_ExplicitVarSizeWithFlags_Flags[q16] /\ + s_ExplicitVarSizeWithFlags_Values[q16] = s_ExplicitVarSizeWithMarker_Values[q14] + | q16 : int(1..2)]) + | q14 : int(1..2)]) + diff --git a/tests/exhaustive/basic/set_card_00/expected/model_3_4_1-solution000001.solution b/tests/exhaustive/basic/set_card_00/expected/model_3_4_1-solution000001.solution new file mode 100644 index 0000000000..6c0d0fdad8 --- /dev/null +++ b/tests/exhaustive/basic/set_card_00/expected/model_3_4_1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting s be {1} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_3_4_1-solution000002.solution b/tests/exhaustive/basic/set_card_00/expected/model_3_4_1-solution000002.solution new file mode 100644 index 0000000000..2ce5f2081f --- /dev/null +++ b/tests/exhaustive/basic/set_card_00/expected/model_3_4_1-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting s be {1, 2} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_3_4_1.eprime b/tests/exhaustive/basic/set_card_00/expected/model_3_4_1.eprime new file mode 100644 index 0000000000..e4660905d9 --- /dev/null +++ b/tests/exhaustive/basic/set_card_00/expected/model_3_4_1.eprime @@ -0,0 +1,42 @@ +language ESSENCE' 1.0 + +find s_ExplicitVarSizeWithMarker_Marker: int(0..2) +find s_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..2)] of int(1..2) +find s_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..2)] of bool +find s_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..2)] of int(1..2) +find s_Occurrence: matrix indexed by [int(1..2)] of bool +branching on + [s_Occurrence, s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithMarker_Values, + s_ExplicitVarSizeWithFlags_Flags, s_ExplicitVarSizeWithFlags_Values] +such that + or([s_ExplicitVarSizeWithFlags_Flags[q29] /\ + s_ExplicitVarSizeWithFlags_Values[q29] = s_ExplicitVarSizeWithMarker_Marker + | q29 : int(1..2)]), + 2 <= s_ExplicitVarSizeWithMarker_Marker -> + s_ExplicitVarSizeWithMarker_Values[1] < s_ExplicitVarSizeWithMarker_Values[2], + and([q2 > s_ExplicitVarSizeWithMarker_Marker -> s_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..2)]), + s_ExplicitVarSizeWithFlags_Flags[2] -> s_ExplicitVarSizeWithFlags_Values[1] < s_ExplicitVarSizeWithFlags_Values[2], + and([s_ExplicitVarSizeWithFlags_Flags[q5] = false -> s_ExplicitVarSizeWithFlags_Values[q5] = 1 | q5 : int(1..2)]), + s_ExplicitVarSizeWithFlags_Flags[2] -> s_ExplicitVarSizeWithFlags_Flags[1], + and([s_ExplicitVarSizeWithFlags_Flags[q10] -> + or([q12 <= s_ExplicitVarSizeWithMarker_Marker /\ + s_ExplicitVarSizeWithMarker_Values[q12] = s_ExplicitVarSizeWithFlags_Values[q10] + | q12 : int(1..2)]) + | q10 : int(1..2)]), + and([q14 <= s_ExplicitVarSizeWithMarker_Marker -> + or([s_ExplicitVarSizeWithFlags_Flags[q16] /\ + s_ExplicitVarSizeWithFlags_Values[q16] = s_ExplicitVarSizeWithMarker_Values[q14] + | q16 : int(1..2)]) + | q14 : int(1..2)]), + and([s_Occurrence[q18] -> + or([q20 <= s_ExplicitVarSizeWithMarker_Marker /\ s_ExplicitVarSizeWithMarker_Values[q20] = q18 + | q20 : int(1..2)]) + | q18 : int(1..2)]), + and([q22 <= s_ExplicitVarSizeWithMarker_Marker -> s_Occurrence[s_ExplicitVarSizeWithMarker_Values[q22]] + | q22 : int(1..2)]), + and([s_Occurrence[q23] -> + or([s_ExplicitVarSizeWithFlags_Flags[q25] /\ s_ExplicitVarSizeWithFlags_Values[q25] = q23 | q25 : int(1..2)]) + | q23 : int(1..2)]), + and([s_ExplicitVarSizeWithFlags_Flags[q27] -> s_Occurrence[s_ExplicitVarSizeWithFlags_Values[q27]] + | q27 : int(1..2)]) + diff --git a/tests/exhaustive/basic/set_card_00/expected/model_3_4_2-solution000001.solution b/tests/exhaustive/basic/set_card_00/expected/model_3_4_2-solution000001.solution new file mode 100644 index 0000000000..2ce5f2081f --- /dev/null +++ b/tests/exhaustive/basic/set_card_00/expected/model_3_4_2-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting s be {1, 2} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_3_4_2-solution000002.solution b/tests/exhaustive/basic/set_card_00/expected/model_3_4_2-solution000002.solution new file mode 100644 index 0000000000..6c0d0fdad8 --- /dev/null +++ b/tests/exhaustive/basic/set_card_00/expected/model_3_4_2-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting s be {1} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_3_4_2.eprime b/tests/exhaustive/basic/set_card_00/expected/model_3_4_2.eprime new file mode 100644 index 0000000000..5f852ee9cb --- /dev/null +++ b/tests/exhaustive/basic/set_card_00/expected/model_3_4_2.eprime @@ -0,0 +1,53 @@ +language ESSENCE' 1.0 + +find s_ExplicitVarSizeWithMarker_Marker: int(0..2) +find s_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..2)] of int(1..2) +find s_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..2)] of bool +find s_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..2)] of int(1..2) +find s_ExplicitVarSizeWithDummy: matrix indexed by [int(1..2)] of int(1..3) +branching on + [s_ExplicitVarSizeWithDummy, s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithMarker_Values, + s_ExplicitVarSizeWithFlags_Flags, s_ExplicitVarSizeWithFlags_Values] +such that + or([s_ExplicitVarSizeWithFlags_Flags[q38] /\ + s_ExplicitVarSizeWithFlags_Values[q38] = s_ExplicitVarSizeWithMarker_Marker + | q38 : int(1..2)]), + 2 <= s_ExplicitVarSizeWithMarker_Marker -> + s_ExplicitVarSizeWithMarker_Values[1] < s_ExplicitVarSizeWithMarker_Values[2], + and([q2 > s_ExplicitVarSizeWithMarker_Marker -> s_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..2)]), + s_ExplicitVarSizeWithFlags_Flags[2] -> s_ExplicitVarSizeWithFlags_Values[1] < s_ExplicitVarSizeWithFlags_Values[2], + and([s_ExplicitVarSizeWithFlags_Flags[q5] = false -> s_ExplicitVarSizeWithFlags_Values[q5] = 1 | q5 : int(1..2)]), + s_ExplicitVarSizeWithFlags_Flags[2] -> s_ExplicitVarSizeWithFlags_Flags[1], + and([s_ExplicitVarSizeWithFlags_Flags[q10] -> + or([q12 <= s_ExplicitVarSizeWithMarker_Marker /\ + s_ExplicitVarSizeWithMarker_Values[q12] = s_ExplicitVarSizeWithFlags_Values[q10] + | q12 : int(1..2)]) + | q10 : int(1..2)]), + and([q14 <= s_ExplicitVarSizeWithMarker_Marker -> + or([s_ExplicitVarSizeWithFlags_Flags[q16] /\ + s_ExplicitVarSizeWithFlags_Values[q16] = s_ExplicitVarSizeWithMarker_Values[q14] + | q16 : int(1..2)]) + | q14 : int(1..2)]), + s_ExplicitVarSizeWithDummy[1] < s_ExplicitVarSizeWithDummy[2] \/ s_ExplicitVarSizeWithDummy[1] = 3, + s_ExplicitVarSizeWithDummy[1] = 3 -> s_ExplicitVarSizeWithDummy[2] = 3, + and([s_ExplicitVarSizeWithDummy[q22] != 3 -> + or([q24 <= s_ExplicitVarSizeWithMarker_Marker /\ + s_ExplicitVarSizeWithMarker_Values[q24] = s_ExplicitVarSizeWithDummy[q22] + | q24 : int(1..2)]) + | q22 : int(1..2)]), + and([q26 <= s_ExplicitVarSizeWithMarker_Marker -> + or([s_ExplicitVarSizeWithDummy[q28] != 3 /\ + s_ExplicitVarSizeWithDummy[q28] = s_ExplicitVarSizeWithMarker_Values[q26] + | q28 : int(1..2)]) + | q26 : int(1..2)]), + and([s_ExplicitVarSizeWithDummy[q30] != 3 -> + or([s_ExplicitVarSizeWithFlags_Flags[q32] /\ + s_ExplicitVarSizeWithFlags_Values[q32] = s_ExplicitVarSizeWithDummy[q30] + | q32 : int(1..2)]) + | q30 : int(1..2)]), + and([s_ExplicitVarSizeWithFlags_Flags[q34] -> + or([s_ExplicitVarSizeWithDummy[q36] != 3 /\ + s_ExplicitVarSizeWithDummy[q36] = s_ExplicitVarSizeWithFlags_Values[q34] + | q36 : int(1..2)]) + | q34 : int(1..2)]) + diff --git a/tests/exhaustive/basic/set_card_00/expected/model_3_4_3-solution000001.solution b/tests/exhaustive/basic/set_card_00/expected/model_3_4_3-solution000001.solution new file mode 100644 index 0000000000..6c0d0fdad8 --- /dev/null +++ b/tests/exhaustive/basic/set_card_00/expected/model_3_4_3-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting s be {1} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_3_4_3-solution000002.solution b/tests/exhaustive/basic/set_card_00/expected/model_3_4_3-solution000002.solution new file mode 100644 index 0000000000..2ce5f2081f --- /dev/null +++ b/tests/exhaustive/basic/set_card_00/expected/model_3_4_3-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting s be {1, 2} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_3_4_3.eprime b/tests/exhaustive/basic/set_card_00/expected/model_3_4_3.eprime new file mode 100644 index 0000000000..1fd723eedd --- /dev/null +++ b/tests/exhaustive/basic/set_card_00/expected/model_3_4_3.eprime @@ -0,0 +1,30 @@ +language ESSENCE' 1.0 + +find s_ExplicitVarSizeWithMarker_Marker: int(0..2) +find s_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..2)] of int(1..2) +find s_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..2)] of bool +find s_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..2)] of int(1..2) +branching on + [s_ExplicitVarSizeWithFlags_Flags, s_ExplicitVarSizeWithFlags_Values, s_ExplicitVarSizeWithMarker_Marker, + s_ExplicitVarSizeWithMarker_Values] +such that + or([s_ExplicitVarSizeWithFlags_Flags[q18] /\ + s_ExplicitVarSizeWithFlags_Values[q18] = s_ExplicitVarSizeWithMarker_Marker + | q18 : int(1..2)]), + 2 <= s_ExplicitVarSizeWithMarker_Marker -> + s_ExplicitVarSizeWithMarker_Values[1] < s_ExplicitVarSizeWithMarker_Values[2], + and([q2 > s_ExplicitVarSizeWithMarker_Marker -> s_ExplicitVarSizeWithMarker_Values[q2] = 1 | q2 : int(1..2)]), + s_ExplicitVarSizeWithFlags_Flags[2] -> s_ExplicitVarSizeWithFlags_Values[1] < s_ExplicitVarSizeWithFlags_Values[2], + and([s_ExplicitVarSizeWithFlags_Flags[q5] = false -> s_ExplicitVarSizeWithFlags_Values[q5] = 1 | q5 : int(1..2)]), + s_ExplicitVarSizeWithFlags_Flags[2] -> s_ExplicitVarSizeWithFlags_Flags[1], + and([s_ExplicitVarSizeWithFlags_Flags[q10] -> + or([q12 <= s_ExplicitVarSizeWithMarker_Marker /\ + s_ExplicitVarSizeWithMarker_Values[q12] = s_ExplicitVarSizeWithFlags_Values[q10] + | q12 : int(1..2)]) + | q10 : int(1..2)]), + and([q14 <= s_ExplicitVarSizeWithMarker_Marker -> + or([s_ExplicitVarSizeWithFlags_Flags[q16] /\ + s_ExplicitVarSizeWithFlags_Values[q16] = s_ExplicitVarSizeWithMarker_Values[q14] + | q16 : int(1..2)]) + | q14 : int(1..2)]) + diff --git a/tests/exhaustive/basic/set_card_00/expected/model_4_1_1-solution000001.solution b/tests/exhaustive/basic/set_card_00/expected/model_4_1_1-solution000001.solution new file mode 100644 index 0000000000..6c0d0fdad8 --- /dev/null +++ b/tests/exhaustive/basic/set_card_00/expected/model_4_1_1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting s be {1} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_4_1_1-solution000002.solution b/tests/exhaustive/basic/set_card_00/expected/model_4_1_1-solution000002.solution new file mode 100644 index 0000000000..2ce5f2081f --- /dev/null +++ b/tests/exhaustive/basic/set_card_00/expected/model_4_1_1-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting s be {1, 2} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_4_1_1.eprime b/tests/exhaustive/basic/set_card_00/expected/model_4_1_1.eprime new file mode 100644 index 0000000000..0cf269a643 --- /dev/null +++ b/tests/exhaustive/basic/set_card_00/expected/model_4_1_1.eprime @@ -0,0 +1,17 @@ +language ESSENCE' 1.0 + +find s_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..2)] of bool +find s_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..2)] of int(1..2) +find s_Occurrence: matrix indexed by [int(1..2)] of bool +branching on [s_Occurrence, s_ExplicitVarSizeWithFlags_Flags, s_ExplicitVarSizeWithFlags_Values] +such that + s_Occurrence[sum([toInt(s_ExplicitVarSizeWithFlags_Flags[q13]) | q13 : int(1..2)])], + s_ExplicitVarSizeWithFlags_Flags[2] -> s_ExplicitVarSizeWithFlags_Values[1] < s_ExplicitVarSizeWithFlags_Values[2], + and([s_ExplicitVarSizeWithFlags_Flags[q2] = false -> s_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..2)]), + s_ExplicitVarSizeWithFlags_Flags[2] -> s_ExplicitVarSizeWithFlags_Flags[1], + and([s_Occurrence[q7] -> + or([s_ExplicitVarSizeWithFlags_Flags[q9] /\ s_ExplicitVarSizeWithFlags_Values[q9] = q7 | q9 : int(1..2)]) + | q7 : int(1..2)]), + and([s_ExplicitVarSizeWithFlags_Flags[q11] -> s_Occurrence[s_ExplicitVarSizeWithFlags_Values[q11]] + | q11 : int(1..2)]) + diff --git a/tests/exhaustive/basic/set_card_00/expected/model_4_1_2-solution000001.solution b/tests/exhaustive/basic/set_card_00/expected/model_4_1_2-solution000001.solution new file mode 100644 index 0000000000..2ce5f2081f --- /dev/null +++ b/tests/exhaustive/basic/set_card_00/expected/model_4_1_2-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting s be {1, 2} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_4_1_2-solution000002.solution b/tests/exhaustive/basic/set_card_00/expected/model_4_1_2-solution000002.solution new file mode 100644 index 0000000000..6c0d0fdad8 --- /dev/null +++ b/tests/exhaustive/basic/set_card_00/expected/model_4_1_2-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting s be {1} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_4_1_2.eprime b/tests/exhaustive/basic/set_card_00/expected/model_4_1_2.eprime new file mode 100644 index 0000000000..fe7fecdcc9 --- /dev/null +++ b/tests/exhaustive/basic/set_card_00/expected/model_4_1_2.eprime @@ -0,0 +1,35 @@ +language ESSENCE' 1.0 + +find s_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..2)] of bool +find s_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..2)] of int(1..2) +find s_Occurrence: matrix indexed by [int(1..2)] of bool +find s_ExplicitVarSizeWithDummy: matrix indexed by [int(1..2)] of int(1..3) +branching on + [s_ExplicitVarSizeWithDummy, s_ExplicitVarSizeWithFlags_Flags, s_ExplicitVarSizeWithFlags_Values, s_Occurrence] +such that + s_Occurrence[sum([toInt(s_ExplicitVarSizeWithFlags_Flags[q30]) | q30 : int(1..2)])], + s_ExplicitVarSizeWithFlags_Flags[2] -> s_ExplicitVarSizeWithFlags_Values[1] < s_ExplicitVarSizeWithFlags_Values[2], + and([s_ExplicitVarSizeWithFlags_Flags[q2] = false -> s_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..2)]), + s_ExplicitVarSizeWithFlags_Flags[2] -> s_ExplicitVarSizeWithFlags_Flags[1], + and([s_Occurrence[q24] -> + or([s_ExplicitVarSizeWithFlags_Flags[q26] /\ s_ExplicitVarSizeWithFlags_Values[q26] = q24 | q26 : int(1..2)]) + | q24 : int(1..2)]), + and([s_ExplicitVarSizeWithFlags_Flags[q28] -> s_Occurrence[s_ExplicitVarSizeWithFlags_Values[q28]] + | q28 : int(1..2)]), + s_ExplicitVarSizeWithDummy[1] < s_ExplicitVarSizeWithDummy[2] \/ s_ExplicitVarSizeWithDummy[1] = 3, + s_ExplicitVarSizeWithDummy[1] = 3 -> s_ExplicitVarSizeWithDummy[2] = 3, + and([s_ExplicitVarSizeWithDummy[q12] != 3 -> + or([s_ExplicitVarSizeWithFlags_Flags[q14] /\ + s_ExplicitVarSizeWithFlags_Values[q14] = s_ExplicitVarSizeWithDummy[q12] + | q14 : int(1..2)]) + | q12 : int(1..2)]), + and([s_ExplicitVarSizeWithFlags_Flags[q16] -> + or([s_ExplicitVarSizeWithDummy[q18] != 3 /\ + s_ExplicitVarSizeWithDummy[q18] = s_ExplicitVarSizeWithFlags_Values[q16] + | q18 : int(1..2)]) + | q16 : int(1..2)]), + and([s_ExplicitVarSizeWithDummy[q20] != 3 -> s_Occurrence[s_ExplicitVarSizeWithDummy[q20]] | q20 : int(1..2)]), + and([s_Occurrence[q21] -> + or([s_ExplicitVarSizeWithDummy[q23] != 3 /\ s_ExplicitVarSizeWithDummy[q23] = q21 | q23 : int(1..2)]) + | q21 : int(1..2)]) + diff --git a/tests/exhaustive/basic/set_card_00/expected/model_4_1_3-solution000001.solution b/tests/exhaustive/basic/set_card_00/expected/model_4_1_3-solution000001.solution new file mode 100644 index 0000000000..6c0d0fdad8 --- /dev/null +++ b/tests/exhaustive/basic/set_card_00/expected/model_4_1_3-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting s be {1} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_4_1_3-solution000002.solution b/tests/exhaustive/basic/set_card_00/expected/model_4_1_3-solution000002.solution new file mode 100644 index 0000000000..2ce5f2081f --- /dev/null +++ b/tests/exhaustive/basic/set_card_00/expected/model_4_1_3-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting s be {1, 2} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_4_1_3.eprime b/tests/exhaustive/basic/set_card_00/expected/model_4_1_3.eprime new file mode 100644 index 0000000000..63b024eb56 --- /dev/null +++ b/tests/exhaustive/basic/set_card_00/expected/model_4_1_3.eprime @@ -0,0 +1,40 @@ +language ESSENCE' 1.0 + +find s_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..2)] of bool +find s_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..2)] of int(1..2) +find s_Occurrence: matrix indexed by [int(1..2)] of bool +find s_ExplicitVarSizeWithMarker_Marker: int(0..2) +find s_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..2)] of int(1..2) +branching on + [s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithMarker_Values, s_ExplicitVarSizeWithFlags_Flags, + s_ExplicitVarSizeWithFlags_Values, s_Occurrence] +such that + s_Occurrence[sum([toInt(s_ExplicitVarSizeWithFlags_Flags[q29]) | q29 : int(1..2)])], + s_ExplicitVarSizeWithFlags_Flags[2] -> s_ExplicitVarSizeWithFlags_Values[1] < s_ExplicitVarSizeWithFlags_Values[2], + and([s_ExplicitVarSizeWithFlags_Flags[q2] = false -> s_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..2)]), + s_ExplicitVarSizeWithFlags_Flags[2] -> s_ExplicitVarSizeWithFlags_Flags[1], + and([s_Occurrence[q23] -> + or([s_ExplicitVarSizeWithFlags_Flags[q25] /\ s_ExplicitVarSizeWithFlags_Values[q25] = q23 | q25 : int(1..2)]) + | q23 : int(1..2)]), + and([s_ExplicitVarSizeWithFlags_Flags[q27] -> s_Occurrence[s_ExplicitVarSizeWithFlags_Values[q27]] + | q27 : int(1..2)]), + 2 <= s_ExplicitVarSizeWithMarker_Marker -> + s_ExplicitVarSizeWithMarker_Values[1] < s_ExplicitVarSizeWithMarker_Values[2], + and([q8 > s_ExplicitVarSizeWithMarker_Marker -> s_ExplicitVarSizeWithMarker_Values[q8] = 1 | q8 : int(1..2)]), + and([q11 <= s_ExplicitVarSizeWithMarker_Marker -> + or([s_ExplicitVarSizeWithFlags_Flags[q13] /\ + s_ExplicitVarSizeWithFlags_Values[q13] = s_ExplicitVarSizeWithMarker_Values[q11] + | q13 : int(1..2)]) + | q11 : int(1..2)]), + and([s_ExplicitVarSizeWithFlags_Flags[q15] -> + or([q17 <= s_ExplicitVarSizeWithMarker_Marker /\ + s_ExplicitVarSizeWithMarker_Values[q17] = s_ExplicitVarSizeWithFlags_Values[q15] + | q17 : int(1..2)]) + | q15 : int(1..2)]), + and([q19 <= s_ExplicitVarSizeWithMarker_Marker -> s_Occurrence[s_ExplicitVarSizeWithMarker_Values[q19]] + | q19 : int(1..2)]), + and([s_Occurrence[q20] -> + or([q22 <= s_ExplicitVarSizeWithMarker_Marker /\ s_ExplicitVarSizeWithMarker_Values[q22] = q20 + | q22 : int(1..2)]) + | q20 : int(1..2)]) + diff --git a/tests/exhaustive/basic/set_card_00/expected/model_4_2_1-solution000001.solution b/tests/exhaustive/basic/set_card_00/expected/model_4_2_1-solution000001.solution new file mode 100644 index 0000000000..6c0d0fdad8 --- /dev/null +++ b/tests/exhaustive/basic/set_card_00/expected/model_4_2_1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting s be {1} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_4_2_1-solution000002.solution b/tests/exhaustive/basic/set_card_00/expected/model_4_2_1-solution000002.solution new file mode 100644 index 0000000000..2ce5f2081f --- /dev/null +++ b/tests/exhaustive/basic/set_card_00/expected/model_4_2_1-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting s be {1, 2} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_4_2_1.eprime b/tests/exhaustive/basic/set_card_00/expected/model_4_2_1.eprime new file mode 100644 index 0000000000..07a85b32d6 --- /dev/null +++ b/tests/exhaustive/basic/set_card_00/expected/model_4_2_1.eprime @@ -0,0 +1,37 @@ +language ESSENCE' 1.0 + +find s_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..2)] of bool +find s_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..2)] of int(1..2) +find s_ExplicitVarSizeWithDummy: matrix indexed by [int(1..2)] of int(1..3) +find s_Occurrence: matrix indexed by [int(1..2)] of bool +branching on + [s_Occurrence, s_ExplicitVarSizeWithFlags_Flags, s_ExplicitVarSizeWithFlags_Values, s_ExplicitVarSizeWithDummy] +such that + or([s_ExplicitVarSizeWithDummy[q30] != 3 /\ + s_ExplicitVarSizeWithDummy[q30] = sum([toInt(s_ExplicitVarSizeWithFlags_Flags[q32]) | q32 : int(1..2)]) + | q30 : int(1..2)]), + s_ExplicitVarSizeWithFlags_Flags[2] -> s_ExplicitVarSizeWithFlags_Values[1] < s_ExplicitVarSizeWithFlags_Values[2], + and([s_ExplicitVarSizeWithFlags_Flags[q2] = false -> s_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..2)]), + s_ExplicitVarSizeWithFlags_Flags[2] -> s_ExplicitVarSizeWithFlags_Flags[1], + s_ExplicitVarSizeWithDummy[1] < s_ExplicitVarSizeWithDummy[2] \/ s_ExplicitVarSizeWithDummy[1] = 3, + s_ExplicitVarSizeWithDummy[1] = 3 -> s_ExplicitVarSizeWithDummy[2] = 3, + and([s_ExplicitVarSizeWithDummy[q11] != 3 -> + or([s_ExplicitVarSizeWithFlags_Flags[q13] /\ + s_ExplicitVarSizeWithFlags_Values[q13] = s_ExplicitVarSizeWithDummy[q11] + | q13 : int(1..2)]) + | q11 : int(1..2)]), + and([s_ExplicitVarSizeWithFlags_Flags[q15] -> + or([s_ExplicitVarSizeWithDummy[q17] != 3 /\ + s_ExplicitVarSizeWithDummy[q17] = s_ExplicitVarSizeWithFlags_Values[q15] + | q17 : int(1..2)]) + | q15 : int(1..2)]), + and([s_Occurrence[q19] -> + or([s_ExplicitVarSizeWithFlags_Flags[q21] /\ s_ExplicitVarSizeWithFlags_Values[q21] = q19 | q21 : int(1..2)]) + | q19 : int(1..2)]), + and([s_ExplicitVarSizeWithFlags_Flags[q23] -> s_Occurrence[s_ExplicitVarSizeWithFlags_Values[q23]] + | q23 : int(1..2)]), + and([s_Occurrence[q24] -> + or([s_ExplicitVarSizeWithDummy[q26] != 3 /\ s_ExplicitVarSizeWithDummy[q26] = q24 | q26 : int(1..2)]) + | q24 : int(1..2)]), + and([s_ExplicitVarSizeWithDummy[q28] != 3 -> s_Occurrence[s_ExplicitVarSizeWithDummy[q28]] | q28 : int(1..2)]) + diff --git a/tests/exhaustive/basic/set_card_00/expected/model_4_2_2-solution000001.solution b/tests/exhaustive/basic/set_card_00/expected/model_4_2_2-solution000001.solution new file mode 100644 index 0000000000..2ce5f2081f --- /dev/null +++ b/tests/exhaustive/basic/set_card_00/expected/model_4_2_2-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting s be {1, 2} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_4_2_2-solution000002.solution b/tests/exhaustive/basic/set_card_00/expected/model_4_2_2-solution000002.solution new file mode 100644 index 0000000000..6c0d0fdad8 --- /dev/null +++ b/tests/exhaustive/basic/set_card_00/expected/model_4_2_2-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting s be {1} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_4_2_2.eprime b/tests/exhaustive/basic/set_card_00/expected/model_4_2_2.eprime new file mode 100644 index 0000000000..f0da04a9ad --- /dev/null +++ b/tests/exhaustive/basic/set_card_00/expected/model_4_2_2.eprime @@ -0,0 +1,26 @@ +language ESSENCE' 1.0 + +find s_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..2)] of bool +find s_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..2)] of int(1..2) +find s_ExplicitVarSizeWithDummy: matrix indexed by [int(1..2)] of int(1..3) +branching on [s_ExplicitVarSizeWithDummy, s_ExplicitVarSizeWithFlags_Flags, s_ExplicitVarSizeWithFlags_Values] +such that + or([s_ExplicitVarSizeWithDummy[q19] != 3 /\ + s_ExplicitVarSizeWithDummy[q19] = sum([toInt(s_ExplicitVarSizeWithFlags_Flags[q21]) | q21 : int(1..2)]) + | q19 : int(1..2)]), + s_ExplicitVarSizeWithFlags_Flags[2] -> s_ExplicitVarSizeWithFlags_Values[1] < s_ExplicitVarSizeWithFlags_Values[2], + and([s_ExplicitVarSizeWithFlags_Flags[q2] = false -> s_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..2)]), + s_ExplicitVarSizeWithFlags_Flags[2] -> s_ExplicitVarSizeWithFlags_Flags[1], + s_ExplicitVarSizeWithDummy[1] < s_ExplicitVarSizeWithDummy[2] \/ s_ExplicitVarSizeWithDummy[1] = 3, + s_ExplicitVarSizeWithDummy[1] = 3 -> s_ExplicitVarSizeWithDummy[2] = 3, + and([s_ExplicitVarSizeWithDummy[q11] != 3 -> + or([s_ExplicitVarSizeWithFlags_Flags[q13] /\ + s_ExplicitVarSizeWithFlags_Values[q13] = s_ExplicitVarSizeWithDummy[q11] + | q13 : int(1..2)]) + | q11 : int(1..2)]), + and([s_ExplicitVarSizeWithFlags_Flags[q15] -> + or([s_ExplicitVarSizeWithDummy[q17] != 3 /\ + s_ExplicitVarSizeWithDummy[q17] = s_ExplicitVarSizeWithFlags_Values[q15] + | q17 : int(1..2)]) + | q15 : int(1..2)]) + diff --git a/tests/exhaustive/basic/set_card_00/expected/model_4_2_3-solution000001.solution b/tests/exhaustive/basic/set_card_00/expected/model_4_2_3-solution000001.solution new file mode 100644 index 0000000000..6c0d0fdad8 --- /dev/null +++ b/tests/exhaustive/basic/set_card_00/expected/model_4_2_3-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting s be {1} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_4_2_3-solution000002.solution b/tests/exhaustive/basic/set_card_00/expected/model_4_2_3-solution000002.solution new file mode 100644 index 0000000000..2ce5f2081f --- /dev/null +++ b/tests/exhaustive/basic/set_card_00/expected/model_4_2_3-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting s be {1, 2} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_4_2_3.eprime b/tests/exhaustive/basic/set_card_00/expected/model_4_2_3.eprime new file mode 100644 index 0000000000..a8dd578091 --- /dev/null +++ b/tests/exhaustive/basic/set_card_00/expected/model_4_2_3.eprime @@ -0,0 +1,53 @@ +language ESSENCE' 1.0 + +find s_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..2)] of bool +find s_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..2)] of int(1..2) +find s_ExplicitVarSizeWithDummy: matrix indexed by [int(1..2)] of int(1..3) +find s_ExplicitVarSizeWithMarker_Marker: int(0..2) +find s_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..2)] of int(1..2) +branching on + [s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithMarker_Values, s_ExplicitVarSizeWithFlags_Flags, + s_ExplicitVarSizeWithFlags_Values, s_ExplicitVarSizeWithDummy] +such that + or([s_ExplicitVarSizeWithDummy[q38] != 3 /\ + s_ExplicitVarSizeWithDummy[q38] = sum([toInt(s_ExplicitVarSizeWithFlags_Flags[q40]) | q40 : int(1..2)]) + | q38 : int(1..2)]), + s_ExplicitVarSizeWithFlags_Flags[2] -> s_ExplicitVarSizeWithFlags_Values[1] < s_ExplicitVarSizeWithFlags_Values[2], + and([s_ExplicitVarSizeWithFlags_Flags[q2] = false -> s_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..2)]), + s_ExplicitVarSizeWithFlags_Flags[2] -> s_ExplicitVarSizeWithFlags_Flags[1], + s_ExplicitVarSizeWithDummy[1] < s_ExplicitVarSizeWithDummy[2] \/ s_ExplicitVarSizeWithDummy[1] = 3, + s_ExplicitVarSizeWithDummy[1] = 3 -> s_ExplicitVarSizeWithDummy[2] = 3, + and([s_ExplicitVarSizeWithDummy[q11] != 3 -> + or([s_ExplicitVarSizeWithFlags_Flags[q13] /\ + s_ExplicitVarSizeWithFlags_Values[q13] = s_ExplicitVarSizeWithDummy[q11] + | q13 : int(1..2)]) + | q11 : int(1..2)]), + and([s_ExplicitVarSizeWithFlags_Flags[q15] -> + or([s_ExplicitVarSizeWithDummy[q17] != 3 /\ + s_ExplicitVarSizeWithDummy[q17] = s_ExplicitVarSizeWithFlags_Values[q15] + | q17 : int(1..2)]) + | q15 : int(1..2)]), + 2 <= s_ExplicitVarSizeWithMarker_Marker -> + s_ExplicitVarSizeWithMarker_Values[1] < s_ExplicitVarSizeWithMarker_Values[2], + and([q19 > s_ExplicitVarSizeWithMarker_Marker -> s_ExplicitVarSizeWithMarker_Values[q19] = 1 | q19 : int(1..2)]), + and([q22 <= s_ExplicitVarSizeWithMarker_Marker -> + or([s_ExplicitVarSizeWithFlags_Flags[q24] /\ + s_ExplicitVarSizeWithFlags_Values[q24] = s_ExplicitVarSizeWithMarker_Values[q22] + | q24 : int(1..2)]) + | q22 : int(1..2)]), + and([s_ExplicitVarSizeWithFlags_Flags[q26] -> + or([q28 <= s_ExplicitVarSizeWithMarker_Marker /\ + s_ExplicitVarSizeWithMarker_Values[q28] = s_ExplicitVarSizeWithFlags_Values[q26] + | q28 : int(1..2)]) + | q26 : int(1..2)]), + and([q30 <= s_ExplicitVarSizeWithMarker_Marker -> + or([s_ExplicitVarSizeWithDummy[q32] != 3 /\ + s_ExplicitVarSizeWithDummy[q32] = s_ExplicitVarSizeWithMarker_Values[q30] + | q32 : int(1..2)]) + | q30 : int(1..2)]), + and([s_ExplicitVarSizeWithDummy[q34] != 3 -> + or([q36 <= s_ExplicitVarSizeWithMarker_Marker /\ + s_ExplicitVarSizeWithMarker_Values[q36] = s_ExplicitVarSizeWithDummy[q34] + | q36 : int(1..2)]) + | q34 : int(1..2)]) + diff --git a/tests/exhaustive/basic/set_card_00/expected/model_4_3_1-solution000001.solution b/tests/exhaustive/basic/set_card_00/expected/model_4_3_1-solution000001.solution new file mode 100644 index 0000000000..6c0d0fdad8 --- /dev/null +++ b/tests/exhaustive/basic/set_card_00/expected/model_4_3_1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting s be {1} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_4_3_1-solution000002.solution b/tests/exhaustive/basic/set_card_00/expected/model_4_3_1-solution000002.solution new file mode 100644 index 0000000000..2ce5f2081f --- /dev/null +++ b/tests/exhaustive/basic/set_card_00/expected/model_4_3_1-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting s be {1, 2} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_4_3_1.eprime b/tests/exhaustive/basic/set_card_00/expected/model_4_3_1.eprime new file mode 100644 index 0000000000..b41daea4cc --- /dev/null +++ b/tests/exhaustive/basic/set_card_00/expected/model_4_3_1.eprime @@ -0,0 +1,42 @@ +language ESSENCE' 1.0 + +find s_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..2)] of bool +find s_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..2)] of int(1..2) +find s_ExplicitVarSizeWithMarker_Marker: int(0..2) +find s_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..2)] of int(1..2) +find s_Occurrence: matrix indexed by [int(1..2)] of bool +branching on + [s_Occurrence, s_ExplicitVarSizeWithFlags_Flags, s_ExplicitVarSizeWithFlags_Values, + s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithMarker_Values] +such that + or([q29 <= s_ExplicitVarSizeWithMarker_Marker /\ + s_ExplicitVarSizeWithMarker_Values[q29] = sum([toInt(s_ExplicitVarSizeWithFlags_Flags[q31]) | q31 : int(1..2)]) + | q29 : int(1..2)]), + s_ExplicitVarSizeWithFlags_Flags[2] -> s_ExplicitVarSizeWithFlags_Values[1] < s_ExplicitVarSizeWithFlags_Values[2], + and([s_ExplicitVarSizeWithFlags_Flags[q2] = false -> s_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..2)]), + s_ExplicitVarSizeWithFlags_Flags[2] -> s_ExplicitVarSizeWithFlags_Flags[1], + 2 <= s_ExplicitVarSizeWithMarker_Marker -> + s_ExplicitVarSizeWithMarker_Values[1] < s_ExplicitVarSizeWithMarker_Values[2], + and([q7 > s_ExplicitVarSizeWithMarker_Marker -> s_ExplicitVarSizeWithMarker_Values[q7] = 1 | q7 : int(1..2)]), + and([q10 <= s_ExplicitVarSizeWithMarker_Marker -> + or([s_ExplicitVarSizeWithFlags_Flags[q12] /\ + s_ExplicitVarSizeWithFlags_Values[q12] = s_ExplicitVarSizeWithMarker_Values[q10] + | q12 : int(1..2)]) + | q10 : int(1..2)]), + and([s_ExplicitVarSizeWithFlags_Flags[q14] -> + or([q16 <= s_ExplicitVarSizeWithMarker_Marker /\ + s_ExplicitVarSizeWithMarker_Values[q16] = s_ExplicitVarSizeWithFlags_Values[q14] + | q16 : int(1..2)]) + | q14 : int(1..2)]), + and([s_Occurrence[q18] -> + or([s_ExplicitVarSizeWithFlags_Flags[q20] /\ s_ExplicitVarSizeWithFlags_Values[q20] = q18 | q20 : int(1..2)]) + | q18 : int(1..2)]), + and([s_ExplicitVarSizeWithFlags_Flags[q22] -> s_Occurrence[s_ExplicitVarSizeWithFlags_Values[q22]] + | q22 : int(1..2)]), + and([s_Occurrence[q23] -> + or([q25 <= s_ExplicitVarSizeWithMarker_Marker /\ s_ExplicitVarSizeWithMarker_Values[q25] = q23 + | q25 : int(1..2)]) + | q23 : int(1..2)]), + and([q27 <= s_ExplicitVarSizeWithMarker_Marker -> s_Occurrence[s_ExplicitVarSizeWithMarker_Values[q27]] + | q27 : int(1..2)]) + diff --git a/tests/exhaustive/basic/set_card_00/expected/model_4_3_2-solution000001.solution b/tests/exhaustive/basic/set_card_00/expected/model_4_3_2-solution000001.solution new file mode 100644 index 0000000000..2ce5f2081f --- /dev/null +++ b/tests/exhaustive/basic/set_card_00/expected/model_4_3_2-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting s be {1, 2} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_4_3_2-solution000002.solution b/tests/exhaustive/basic/set_card_00/expected/model_4_3_2-solution000002.solution new file mode 100644 index 0000000000..6c0d0fdad8 --- /dev/null +++ b/tests/exhaustive/basic/set_card_00/expected/model_4_3_2-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting s be {1} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_4_3_2.eprime b/tests/exhaustive/basic/set_card_00/expected/model_4_3_2.eprime new file mode 100644 index 0000000000..6ad2dfa6b0 --- /dev/null +++ b/tests/exhaustive/basic/set_card_00/expected/model_4_3_2.eprime @@ -0,0 +1,53 @@ +language ESSENCE' 1.0 + +find s_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..2)] of bool +find s_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..2)] of int(1..2) +find s_ExplicitVarSizeWithMarker_Marker: int(0..2) +find s_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..2)] of int(1..2) +find s_ExplicitVarSizeWithDummy: matrix indexed by [int(1..2)] of int(1..3) +branching on + [s_ExplicitVarSizeWithDummy, s_ExplicitVarSizeWithFlags_Flags, s_ExplicitVarSizeWithFlags_Values, + s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithMarker_Values] +such that + or([q38 <= s_ExplicitVarSizeWithMarker_Marker /\ + s_ExplicitVarSizeWithMarker_Values[q38] = sum([toInt(s_ExplicitVarSizeWithFlags_Flags[q40]) | q40 : int(1..2)]) + | q38 : int(1..2)]), + s_ExplicitVarSizeWithFlags_Flags[2] -> s_ExplicitVarSizeWithFlags_Values[1] < s_ExplicitVarSizeWithFlags_Values[2], + and([s_ExplicitVarSizeWithFlags_Flags[q2] = false -> s_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..2)]), + s_ExplicitVarSizeWithFlags_Flags[2] -> s_ExplicitVarSizeWithFlags_Flags[1], + 2 <= s_ExplicitVarSizeWithMarker_Marker -> + s_ExplicitVarSizeWithMarker_Values[1] < s_ExplicitVarSizeWithMarker_Values[2], + and([q7 > s_ExplicitVarSizeWithMarker_Marker -> s_ExplicitVarSizeWithMarker_Values[q7] = 1 | q7 : int(1..2)]), + and([q10 <= s_ExplicitVarSizeWithMarker_Marker -> + or([s_ExplicitVarSizeWithFlags_Flags[q12] /\ + s_ExplicitVarSizeWithFlags_Values[q12] = s_ExplicitVarSizeWithMarker_Values[q10] + | q12 : int(1..2)]) + | q10 : int(1..2)]), + and([s_ExplicitVarSizeWithFlags_Flags[q14] -> + or([q16 <= s_ExplicitVarSizeWithMarker_Marker /\ + s_ExplicitVarSizeWithMarker_Values[q16] = s_ExplicitVarSizeWithFlags_Values[q14] + | q16 : int(1..2)]) + | q14 : int(1..2)]), + s_ExplicitVarSizeWithDummy[1] < s_ExplicitVarSizeWithDummy[2] \/ s_ExplicitVarSizeWithDummy[1] = 3, + s_ExplicitVarSizeWithDummy[1] = 3 -> s_ExplicitVarSizeWithDummy[2] = 3, + and([s_ExplicitVarSizeWithDummy[q22] != 3 -> + or([s_ExplicitVarSizeWithFlags_Flags[q24] /\ + s_ExplicitVarSizeWithFlags_Values[q24] = s_ExplicitVarSizeWithDummy[q22] + | q24 : int(1..2)]) + | q22 : int(1..2)]), + and([s_ExplicitVarSizeWithFlags_Flags[q26] -> + or([s_ExplicitVarSizeWithDummy[q28] != 3 /\ + s_ExplicitVarSizeWithDummy[q28] = s_ExplicitVarSizeWithFlags_Values[q26] + | q28 : int(1..2)]) + | q26 : int(1..2)]), + and([s_ExplicitVarSizeWithDummy[q30] != 3 -> + or([q32 <= s_ExplicitVarSizeWithMarker_Marker /\ + s_ExplicitVarSizeWithMarker_Values[q32] = s_ExplicitVarSizeWithDummy[q30] + | q32 : int(1..2)]) + | q30 : int(1..2)]), + and([q34 <= s_ExplicitVarSizeWithMarker_Marker -> + or([s_ExplicitVarSizeWithDummy[q36] != 3 /\ + s_ExplicitVarSizeWithDummy[q36] = s_ExplicitVarSizeWithMarker_Values[q34] + | q36 : int(1..2)]) + | q34 : int(1..2)]) + diff --git a/tests/exhaustive/basic/set_card_00/expected/model_4_3_3-solution000001.solution b/tests/exhaustive/basic/set_card_00/expected/model_4_3_3-solution000001.solution new file mode 100644 index 0000000000..6c0d0fdad8 --- /dev/null +++ b/tests/exhaustive/basic/set_card_00/expected/model_4_3_3-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting s be {1} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_4_3_3-solution000002.solution b/tests/exhaustive/basic/set_card_00/expected/model_4_3_3-solution000002.solution new file mode 100644 index 0000000000..2ce5f2081f --- /dev/null +++ b/tests/exhaustive/basic/set_card_00/expected/model_4_3_3-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting s be {1, 2} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_4_3_3.eprime b/tests/exhaustive/basic/set_card_00/expected/model_4_3_3.eprime new file mode 100644 index 0000000000..4bf46f85b1 --- /dev/null +++ b/tests/exhaustive/basic/set_card_00/expected/model_4_3_3.eprime @@ -0,0 +1,30 @@ +language ESSENCE' 1.0 + +find s_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..2)] of bool +find s_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..2)] of int(1..2) +find s_ExplicitVarSizeWithMarker_Marker: int(0..2) +find s_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..2)] of int(1..2) +branching on + [s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithMarker_Values, s_ExplicitVarSizeWithFlags_Flags, + s_ExplicitVarSizeWithFlags_Values] +such that + or([q18 <= s_ExplicitVarSizeWithMarker_Marker /\ + s_ExplicitVarSizeWithMarker_Values[q18] = sum([toInt(s_ExplicitVarSizeWithFlags_Flags[q20]) | q20 : int(1..2)]) + | q18 : int(1..2)]), + s_ExplicitVarSizeWithFlags_Flags[2] -> s_ExplicitVarSizeWithFlags_Values[1] < s_ExplicitVarSizeWithFlags_Values[2], + and([s_ExplicitVarSizeWithFlags_Flags[q2] = false -> s_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..2)]), + s_ExplicitVarSizeWithFlags_Flags[2] -> s_ExplicitVarSizeWithFlags_Flags[1], + 2 <= s_ExplicitVarSizeWithMarker_Marker -> + s_ExplicitVarSizeWithMarker_Values[1] < s_ExplicitVarSizeWithMarker_Values[2], + and([q7 > s_ExplicitVarSizeWithMarker_Marker -> s_ExplicitVarSizeWithMarker_Values[q7] = 1 | q7 : int(1..2)]), + and([q10 <= s_ExplicitVarSizeWithMarker_Marker -> + or([s_ExplicitVarSizeWithFlags_Flags[q12] /\ + s_ExplicitVarSizeWithFlags_Values[q12] = s_ExplicitVarSizeWithMarker_Values[q10] + | q12 : int(1..2)]) + | q10 : int(1..2)]), + and([s_ExplicitVarSizeWithFlags_Flags[q14] -> + or([q16 <= s_ExplicitVarSizeWithMarker_Marker /\ + s_ExplicitVarSizeWithMarker_Values[q16] = s_ExplicitVarSizeWithFlags_Values[q14] + | q16 : int(1..2)]) + | q14 : int(1..2)]) + diff --git a/tests/exhaustive/basic/set_card_00/expected/model_4_4_1-solution000001.solution b/tests/exhaustive/basic/set_card_00/expected/model_4_4_1-solution000001.solution new file mode 100644 index 0000000000..6c0d0fdad8 --- /dev/null +++ b/tests/exhaustive/basic/set_card_00/expected/model_4_4_1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting s be {1} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_4_4_1-solution000002.solution b/tests/exhaustive/basic/set_card_00/expected/model_4_4_1-solution000002.solution new file mode 100644 index 0000000000..2ce5f2081f --- /dev/null +++ b/tests/exhaustive/basic/set_card_00/expected/model_4_4_1-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting s be {1, 2} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_4_4_1.eprime b/tests/exhaustive/basic/set_card_00/expected/model_4_4_1.eprime new file mode 100644 index 0000000000..4b827d683c --- /dev/null +++ b/tests/exhaustive/basic/set_card_00/expected/model_4_4_1.eprime @@ -0,0 +1,19 @@ +language ESSENCE' 1.0 + +find s_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..2)] of bool +find s_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..2)] of int(1..2) +find s_Occurrence: matrix indexed by [int(1..2)] of bool +branching on [s_Occurrence, s_ExplicitVarSizeWithFlags_Flags, s_ExplicitVarSizeWithFlags_Values] +such that + or([s_ExplicitVarSizeWithFlags_Flags[q13] /\ + s_ExplicitVarSizeWithFlags_Values[q13] = sum([toInt(s_ExplicitVarSizeWithFlags_Flags[q15]) | q15 : int(1..2)]) + | q13 : int(1..2)]), + s_ExplicitVarSizeWithFlags_Flags[2] -> s_ExplicitVarSizeWithFlags_Values[1] < s_ExplicitVarSizeWithFlags_Values[2], + and([s_ExplicitVarSizeWithFlags_Flags[q2] = false -> s_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..2)]), + s_ExplicitVarSizeWithFlags_Flags[2] -> s_ExplicitVarSizeWithFlags_Flags[1], + and([s_Occurrence[q7] -> + or([s_ExplicitVarSizeWithFlags_Flags[q9] /\ s_ExplicitVarSizeWithFlags_Values[q9] = q7 | q9 : int(1..2)]) + | q7 : int(1..2)]), + and([s_ExplicitVarSizeWithFlags_Flags[q11] -> s_Occurrence[s_ExplicitVarSizeWithFlags_Values[q11]] + | q11 : int(1..2)]) + diff --git a/tests/exhaustive/basic/set_card_00/expected/model_4_4_2-solution000001.solution b/tests/exhaustive/basic/set_card_00/expected/model_4_4_2-solution000001.solution new file mode 100644 index 0000000000..2ce5f2081f --- /dev/null +++ b/tests/exhaustive/basic/set_card_00/expected/model_4_4_2-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting s be {1, 2} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_4_4_2-solution000002.solution b/tests/exhaustive/basic/set_card_00/expected/model_4_4_2-solution000002.solution new file mode 100644 index 0000000000..6c0d0fdad8 --- /dev/null +++ b/tests/exhaustive/basic/set_card_00/expected/model_4_4_2-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting s be {1} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_4_4_2.eprime b/tests/exhaustive/basic/set_card_00/expected/model_4_4_2.eprime new file mode 100644 index 0000000000..87dc67de4e --- /dev/null +++ b/tests/exhaustive/basic/set_card_00/expected/model_4_4_2.eprime @@ -0,0 +1,26 @@ +language ESSENCE' 1.0 + +find s_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..2)] of bool +find s_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..2)] of int(1..2) +find s_ExplicitVarSizeWithDummy: matrix indexed by [int(1..2)] of int(1..3) +branching on [s_ExplicitVarSizeWithDummy, s_ExplicitVarSizeWithFlags_Flags, s_ExplicitVarSizeWithFlags_Values] +such that + or([s_ExplicitVarSizeWithFlags_Flags[q19] /\ + s_ExplicitVarSizeWithFlags_Values[q19] = sum([toInt(s_ExplicitVarSizeWithFlags_Flags[q21]) | q21 : int(1..2)]) + | q19 : int(1..2)]), + s_ExplicitVarSizeWithFlags_Flags[2] -> s_ExplicitVarSizeWithFlags_Values[1] < s_ExplicitVarSizeWithFlags_Values[2], + and([s_ExplicitVarSizeWithFlags_Flags[q2] = false -> s_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..2)]), + s_ExplicitVarSizeWithFlags_Flags[2] -> s_ExplicitVarSizeWithFlags_Flags[1], + s_ExplicitVarSizeWithDummy[1] < s_ExplicitVarSizeWithDummy[2] \/ s_ExplicitVarSizeWithDummy[1] = 3, + s_ExplicitVarSizeWithDummy[1] = 3 -> s_ExplicitVarSizeWithDummy[2] = 3, + and([s_ExplicitVarSizeWithDummy[q11] != 3 -> + or([s_ExplicitVarSizeWithFlags_Flags[q13] /\ + s_ExplicitVarSizeWithFlags_Values[q13] = s_ExplicitVarSizeWithDummy[q11] + | q13 : int(1..2)]) + | q11 : int(1..2)]), + and([s_ExplicitVarSizeWithFlags_Flags[q15] -> + or([s_ExplicitVarSizeWithDummy[q17] != 3 /\ + s_ExplicitVarSizeWithDummy[q17] = s_ExplicitVarSizeWithFlags_Values[q15] + | q17 : int(1..2)]) + | q15 : int(1..2)]) + diff --git a/tests/exhaustive/basic/set_card_00/expected/model_4_4_3-solution000001.solution b/tests/exhaustive/basic/set_card_00/expected/model_4_4_3-solution000001.solution new file mode 100644 index 0000000000..6c0d0fdad8 --- /dev/null +++ b/tests/exhaustive/basic/set_card_00/expected/model_4_4_3-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting s be {1} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_4_4_3-solution000002.solution b/tests/exhaustive/basic/set_card_00/expected/model_4_4_3-solution000002.solution new file mode 100644 index 0000000000..2ce5f2081f --- /dev/null +++ b/tests/exhaustive/basic/set_card_00/expected/model_4_4_3-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting s be {1, 2} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_4_4_3.eprime b/tests/exhaustive/basic/set_card_00/expected/model_4_4_3.eprime new file mode 100644 index 0000000000..2634131abd --- /dev/null +++ b/tests/exhaustive/basic/set_card_00/expected/model_4_4_3.eprime @@ -0,0 +1,30 @@ +language ESSENCE' 1.0 + +find s_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..2)] of bool +find s_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..2)] of int(1..2) +find s_ExplicitVarSizeWithMarker_Marker: int(0..2) +find s_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..2)] of int(1..2) +branching on + [s_ExplicitVarSizeWithMarker_Marker, s_ExplicitVarSizeWithMarker_Values, s_ExplicitVarSizeWithFlags_Flags, + s_ExplicitVarSizeWithFlags_Values] +such that + or([s_ExplicitVarSizeWithFlags_Flags[q18] /\ + s_ExplicitVarSizeWithFlags_Values[q18] = sum([toInt(s_ExplicitVarSizeWithFlags_Flags[q20]) | q20 : int(1..2)]) + | q18 : int(1..2)]), + s_ExplicitVarSizeWithFlags_Flags[2] -> s_ExplicitVarSizeWithFlags_Values[1] < s_ExplicitVarSizeWithFlags_Values[2], + and([s_ExplicitVarSizeWithFlags_Flags[q2] = false -> s_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..2)]), + s_ExplicitVarSizeWithFlags_Flags[2] -> s_ExplicitVarSizeWithFlags_Flags[1], + 2 <= s_ExplicitVarSizeWithMarker_Marker -> + s_ExplicitVarSizeWithMarker_Values[1] < s_ExplicitVarSizeWithMarker_Values[2], + and([q7 > s_ExplicitVarSizeWithMarker_Marker -> s_ExplicitVarSizeWithMarker_Values[q7] = 1 | q7 : int(1..2)]), + and([q10 <= s_ExplicitVarSizeWithMarker_Marker -> + or([s_ExplicitVarSizeWithFlags_Flags[q12] /\ + s_ExplicitVarSizeWithFlags_Values[q12] = s_ExplicitVarSizeWithMarker_Values[q10] + | q12 : int(1..2)]) + | q10 : int(1..2)]), + and([s_ExplicitVarSizeWithFlags_Flags[q14] -> + or([q16 <= s_ExplicitVarSizeWithMarker_Marker /\ + s_ExplicitVarSizeWithMarker_Values[q16] = s_ExplicitVarSizeWithFlags_Values[q14] + | q16 : int(1..2)]) + | q14 : int(1..2)]) + diff --git a/tests/exhaustive/basic/set_card_00/expected/model_4_4_4-solution000001.solution b/tests/exhaustive/basic/set_card_00/expected/model_4_4_4-solution000001.solution new file mode 100644 index 0000000000..6c0d0fdad8 --- /dev/null +++ b/tests/exhaustive/basic/set_card_00/expected/model_4_4_4-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting s be {1} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_4_4_4-solution000002.solution b/tests/exhaustive/basic/set_card_00/expected/model_4_4_4-solution000002.solution new file mode 100644 index 0000000000..2ce5f2081f --- /dev/null +++ b/tests/exhaustive/basic/set_card_00/expected/model_4_4_4-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting s be {1, 2} diff --git a/tests/exhaustive/basic/set_card_00/expected/model_4_4_4.eprime b/tests/exhaustive/basic/set_card_00/expected/model_4_4_4.eprime new file mode 100644 index 0000000000..f18fbe001d --- /dev/null +++ b/tests/exhaustive/basic/set_card_00/expected/model_4_4_4.eprime @@ -0,0 +1,13 @@ +language ESSENCE' 1.0 + +find s_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..2)] of bool +find s_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..2)] of int(1..2) +branching on [s_ExplicitVarSizeWithFlags_Flags, s_ExplicitVarSizeWithFlags_Values] +such that + or([s_ExplicitVarSizeWithFlags_Flags[q7] /\ + s_ExplicitVarSizeWithFlags_Values[q7] = sum([toInt(s_ExplicitVarSizeWithFlags_Flags[q9]) | q9 : int(1..2)]) + | q7 : int(1..2)]), + s_ExplicitVarSizeWithFlags_Flags[2] -> s_ExplicitVarSizeWithFlags_Values[1] < s_ExplicitVarSizeWithFlags_Values[2], + and([s_ExplicitVarSizeWithFlags_Flags[q2] = false -> s_ExplicitVarSizeWithFlags_Values[q2] = 1 | q2 : int(1..2)]), + s_ExplicitVarSizeWithFlags_Flags[2] -> s_ExplicitVarSizeWithFlags_Flags[1] + diff --git a/tests/exhaustive/basic/set_card_02/expected/model_1_1_2.eprime b/tests/exhaustive/basic/set_card_02/expected/model_1_1_2.eprime index fdcdbffcf9..4983889ed3 100644 --- a/tests/exhaustive/basic/set_card_02/expected/model_1_1_2.eprime +++ b/tests/exhaustive/basic/set_card_02/expected/model_1_1_2.eprime @@ -4,17 +4,9 @@ find s_Explicit: matrix indexed by [int(1..2)] of int(1..2) find s_Occurrence: matrix indexed by [int(1..2)] of bool branching on [s_Occurrence, s_Explicit] such that -<<<<<<< HEAD - s_Occurrence[2], - 2 = sum([toInt(s_Occurrence[q1]) | q1 : int(1..2)]), - [s_Explicit[1]; int(1)] or([s_Explicit[q8] = q6 | q8 : int(1..2)]) | q6 : int(1..2)]) -======= or([s_Explicit[q10] = 2 | q10 : int(1..2)]), s_Explicit[1] < s_Explicit[2], 2 = sum([toInt(s_Occurrence[q3]) | q3 : int(1..2)]), and([s_Occurrence[q4] -> or([s_Explicit[q6] = q4 | q6 : int(1..2)]) | q4 : int(1..2)]), and([s_Occurrence[s_Explicit[q8]] | q8 : int(1..2)]) ->>>>>>> main diff --git a/tests/exhaustive/basic/set_card_02/expected/model_1_2_1.eprime b/tests/exhaustive/basic/set_card_02/expected/model_1_2_1.eprime index 827963e6ac..d14af629f8 100644 --- a/tests/exhaustive/basic/set_card_02/expected/model_1_2_1.eprime +++ b/tests/exhaustive/basic/set_card_02/expected/model_1_2_1.eprime @@ -4,17 +4,9 @@ find s_Explicit: matrix indexed by [int(1..2)] of int(1..2) find s_Occurrence: matrix indexed by [int(1..2)] of bool branching on [s_Occurrence, s_Explicit] such that -<<<<<<< HEAD - or([s_Explicit[q10] = 2 | q10 : int(1..2)]), - 2 = sum([toInt(s_Occurrence[q1]) | q1 : int(1..2)]), - [s_Explicit[1]; int(1)] or([s_Explicit[q8] = q6 | q8 : int(1..2)]) | q6 : int(1..2)]) -======= s_Occurrence[2], s_Explicit[1] < s_Explicit[2], 2 = sum([toInt(s_Occurrence[q3]) | q3 : int(1..2)]), and([s_Occurrence[q4] -> or([s_Explicit[q6] = q4 | q6 : int(1..2)]) | q4 : int(1..2)]), and([s_Occurrence[s_Explicit[q8]] | q8 : int(1..2)]) ->>>>>>> main diff --git a/tests/exhaustive/basic/set_card_02/expected/model_1_2_2.eprime b/tests/exhaustive/basic/set_card_02/expected/model_1_2_2.eprime deleted file mode 100644 index 5a2b11db7d..0000000000 --- a/tests/exhaustive/basic/set_card_02/expected/model_1_2_2.eprime +++ /dev/null @@ -1,12 +0,0 @@ -language ESSENCE' 1.0 - -find s_Occurrence: matrix indexed by [int(1..2)] of bool -find s_Explicit: matrix indexed by [int(1..2)] of int(1..2) -branching on [s_Explicit, s_Occurrence] -such that - or([s_Explicit[q10] = 2 | q10 : int(1..2)]), - 2 = sum([toInt(s_Occurrence[q1]) | q1 : int(1..2)]), - [s_Explicit[1]; int(1)] or([s_Explicit[q8] = q6 | q8 : int(1..2)]) | q6 : int(1..2)]) - diff --git a/tests/exhaustive/basic/set_card_02/expected/model_2_1_1.eprime b/tests/exhaustive/basic/set_card_02/expected/model_2_1_1.eprime index 9a8935286c..a433443261 100644 --- a/tests/exhaustive/basic/set_card_02/expected/model_2_1_1.eprime +++ b/tests/exhaustive/basic/set_card_02/expected/model_2_1_1.eprime @@ -4,17 +4,9 @@ find s_Occurrence: matrix indexed by [int(1..2)] of bool find s_Explicit: matrix indexed by [int(1..2)] of int(1..2) branching on [s_Explicit, s_Occurrence] such that -<<<<<<< HEAD - s_Occurrence[2], - [s_Explicit[1]; int(1)] or([s_Explicit[q6] = q4 | q6 : int(1..2)]) | q4 : int(1..2)]), - and([s_Occurrence[s_Explicit[q8]] | q8 : int(1..2)]) -======= or([s_Explicit[q10] = 2 | q10 : int(1..2)]), 2 = sum([toInt(s_Occurrence[q1]) | q1 : int(1..2)]), s_Explicit[1] < s_Explicit[2], and([s_Occurrence[s_Explicit[q5]] | q5 : int(1..2)]), and([s_Occurrence[q6] -> or([s_Explicit[q8] = q6 | q8 : int(1..2)]) | q6 : int(1..2)]) ->>>>>>> main diff --git a/tests/exhaustive/basic/set_card_02/expected/model_2_1_2.eprime b/tests/exhaustive/basic/set_card_02/expected/model_2_1_2.eprime deleted file mode 100644 index e61dce3c88..0000000000 --- a/tests/exhaustive/basic/set_card_02/expected/model_2_1_2.eprime +++ /dev/null @@ -1,12 +0,0 @@ -language ESSENCE' 1.0 - -find s_Explicit: matrix indexed by [int(1..2)] of int(1..2) -find s_Occurrence: matrix indexed by [int(1..2)] of bool -branching on [s_Occurrence, s_Explicit] -such that - s_Occurrence[2], - [s_Explicit[1]; int(1)] or([s_Explicit[q6] = q4 | q6 : int(1..2)]) | q4 : int(1..2)]), - and([s_Occurrence[s_Explicit[q8]] | q8 : int(1..2)]) - diff --git a/tests/exhaustive/basic/set_card_02/expected/model_2_2_1.eprime b/tests/exhaustive/basic/set_card_02/expected/model_2_2_1.eprime index 98808594ef..bf6cdb72a7 100644 --- a/tests/exhaustive/basic/set_card_02/expected/model_2_2_1.eprime +++ b/tests/exhaustive/basic/set_card_02/expected/model_2_2_1.eprime @@ -4,17 +4,9 @@ find s_Occurrence: matrix indexed by [int(1..2)] of bool find s_Explicit: matrix indexed by [int(1..2)] of int(1..2) branching on [s_Explicit, s_Occurrence] such that -<<<<<<< HEAD - or([s_Explicit[q10] = 2 | q10 : int(1..2)]), - [s_Explicit[1]; int(1)] or([s_Explicit[q6] = q4 | q6 : int(1..2)]) | q4 : int(1..2)]), - and([s_Occurrence[s_Explicit[q8]] | q8 : int(1..2)]) -======= s_Occurrence[2], 2 = sum([toInt(s_Occurrence[q1]) | q1 : int(1..2)]), s_Explicit[1] < s_Explicit[2], and([s_Occurrence[s_Explicit[q5]] | q5 : int(1..2)]), and([s_Occurrence[q6] -> or([s_Explicit[q8] = q6 | q8 : int(1..2)]) | q6 : int(1..2)]) ->>>>>>> main diff --git a/tests/exhaustive/basic/set_card_02/expected/model_2_2_2.eprime b/tests/exhaustive/basic/set_card_02/expected/model_2_2_2.eprime index 5559441056..0611d17d34 100644 --- a/tests/exhaustive/basic/set_card_02/expected/model_2_2_2.eprime +++ b/tests/exhaustive/basic/set_card_02/expected/model_2_2_2.eprime @@ -3,11 +3,6 @@ language ESSENCE' 1.0 find s_Occurrence: matrix indexed by [int(1..2)] of bool branching on [s_Occurrence] such that -<<<<<<< HEAD - or([s_Explicit[q4] = 2 | q4 : int(1..2)]), - [s_Explicit[1]; int(1)] >>>>>> main diff --git a/tests/exhaustive/basic/toSet_comprehension/expected/model_2.eprime b/tests/exhaustive/basic/toSet_comprehension/expected/model_2.eprime index 4003097cc5..244b218b6a 100644 --- a/tests/exhaustive/basic/toSet_comprehension/expected/model_2.eprime +++ b/tests/exhaustive/basic/toSet_comprehension/expected/model_2.eprime @@ -7,9 +7,8 @@ find x: int(n) find conjure_aux1_ExplicitVarSizeWithDummy: matrix indexed by [int(1..3)] of int(1..4) branching on [flags, val, x] such that - and([[conjure_aux1_ExplicitVarSizeWithDummy[q4]; int(1)] conjure_aux1_ExplicitVarSizeWithDummy[q5 + 1] = 4 | q5 : int(1..2)]), diff --git a/tests/exhaustive/basic/toSet_comprehension/expected/model_3.eprime b/tests/exhaustive/basic/toSet_comprehension/expected/model_3.eprime index 1124f64f1b..aa55c84836 100644 --- a/tests/exhaustive/basic/toSet_comprehension/expected/model_3.eprime +++ b/tests/exhaustive/basic/toSet_comprehension/expected/model_3.eprime @@ -9,8 +9,7 @@ find conjure_aux1_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..3) branching on [flags, val, x] such that and([q4 + 1 <= conjure_aux1_ExplicitVarSizeWithMarker_Marker -> - [conjure_aux1_ExplicitVarSizeWithMarker_Values[q4]; int(1)] conjure_aux1_ExplicitVarSizeWithMarker_Marker -> conjure_aux1_ExplicitVarSizeWithMarker_Values[q5] = 1 | q5 : int(1..3)]), diff --git a/tests/exhaustive/basic/toSet_comprehension/expected/model_4.eprime b/tests/exhaustive/basic/toSet_comprehension/expected/model_4.eprime index 4114f93599..9672c4965c 100644 --- a/tests/exhaustive/basic/toSet_comprehension/expected/model_4.eprime +++ b/tests/exhaustive/basic/toSet_comprehension/expected/model_4.eprime @@ -9,8 +9,7 @@ find conjure_aux1_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3)] branching on [flags, val, x] such that and([conjure_aux1_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> - [conjure_aux1_ExplicitVarSizeWithFlags_Values[q4]; int(1)] conjure_aux1_ExplicitVarSizeWithFlags_Values[q5] = 1 | q5 : int(1..3)]), diff --git a/tests/exhaustive/basic/typed01/expected/model_1_1_1_1-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_1_1_1_1-solution000001.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_1_1_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_1_1_1-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_1_1_1_1-solution000002.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_1_1_1-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_1_1_1-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_1_1_1_1-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_1_1_1-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_1_1_1.eprime b/tests/exhaustive/basic/typed01/expected/model_1_1_1_1.eprime new file mode 100644 index 0000000000..94c0d2b627 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_1_1_1.eprime @@ -0,0 +1,7 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(1)] of bool +find y_Occurrence: matrix indexed by [int(1)] of bool +branching on [x_Occurrence, y_Occurrence] +such that x_Occurrence[1] /\ y_Occurrence[1] -> false + diff --git a/tests/exhaustive/basic/typed01/expected/model_1_1_1_2-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_1_1_1_2-solution000001.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_1_1_2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_1_1_2-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_1_1_1_2-solution000002.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_1_1_2-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_1_1_2-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_1_1_1_2-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_1_1_2-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_1_1_2.eprime b/tests/exhaustive/basic/typed01/expected/model_1_1_1_2.eprime new file mode 100644 index 0000000000..bdbab746fd --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_1_1_2.eprime @@ -0,0 +1,11 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(1)] of bool +find y_Occurrence: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +branching on [x_Occurrence, y_ExplicitVarSizeWithDummy, y_Occurrence] +such that + x_Occurrence[1] /\ y_Occurrence[1] -> false, + y_ExplicitVarSizeWithDummy[1] != 2 -> y_Occurrence[y_ExplicitVarSizeWithDummy[1]], + y_Occurrence[1] -> y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = 1 + diff --git a/tests/exhaustive/basic/typed01/expected/model_1_1_1_3-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_1_1_1_3-solution000001.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_1_1_3-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_1_1_3-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_1_1_1_3-solution000002.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_1_1_3-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_1_1_3-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_1_1_1_3-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_1_1_3-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_1_1_3.eprime b/tests/exhaustive/basic/typed01/expected/model_1_1_1_3.eprime new file mode 100644 index 0000000000..c168e1afc0 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_1_1_3.eprime @@ -0,0 +1,13 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(1)] of bool +find y_Occurrence: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithMarker_Marker: int(0..1) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +branching on [x_Occurrence, y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values, y_Occurrence] +such that + x_Occurrence[1] /\ y_Occurrence[1] -> false, + 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, + 1 <= y_ExplicitVarSizeWithMarker_Marker -> y_Occurrence[y_ExplicitVarSizeWithMarker_Values[1]], + y_Occurrence[1] -> 1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = 1 + diff --git a/tests/exhaustive/basic/typed01/expected/model_1_1_1_4-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_1_1_1_4-solution000001.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_1_1_4-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_1_1_4-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_1_1_1_4-solution000002.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_1_1_4-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_1_1_4-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_1_1_1_4-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_1_1_4-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_1_1_4.eprime b/tests/exhaustive/basic/typed01/expected/model_1_1_1_4.eprime new file mode 100644 index 0000000000..f0ddb80973 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_1_1_4.eprime @@ -0,0 +1,13 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(1)] of bool +find y_Occurrence: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +branching on [x_Occurrence, y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values, y_Occurrence] +such that + x_Occurrence[1] /\ y_Occurrence[1] -> false, + y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, + y_ExplicitVarSizeWithFlags_Flags[1] -> y_Occurrence[y_ExplicitVarSizeWithFlags_Values[1]], + y_Occurrence[1] -> y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = 1 + diff --git a/tests/exhaustive/basic/typed01/expected/model_1_1_2_1-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_1_1_2_1-solution000001.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_1_2_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_1_2_1-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_1_1_2_1-solution000002.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_1_2_1-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_1_2_1-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_1_1_2_1-solution000003.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_1_2_1-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_1_2_1.eprime b/tests/exhaustive/basic/typed01/expected/model_1_1_2_1.eprime new file mode 100644 index 0000000000..0b9c355d3a --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_1_2_1.eprime @@ -0,0 +1,11 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(1)] of bool +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +find y_Occurrence: matrix indexed by [int(1)] of bool +branching on [x_ExplicitVarSizeWithDummy, x_Occurrence, y_Occurrence] +such that + x_Occurrence[1] /\ y_Occurrence[1] -> false, + x_ExplicitVarSizeWithDummy[1] != 2 -> x_Occurrence[x_ExplicitVarSizeWithDummy[1]], + x_Occurrence[1] -> x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = 1 + diff --git a/tests/exhaustive/basic/typed01/expected/model_1_1_2_2-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_1_1_2_2-solution000001.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_1_2_2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_1_2_2-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_1_1_2_2-solution000002.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_1_2_2-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_1_2_2-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_1_1_2_2-solution000003.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_1_2_2-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_1_2_2.eprime b/tests/exhaustive/basic/typed01/expected/model_1_1_2_2.eprime new file mode 100644 index 0000000000..927eca8795 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_1_2_2.eprime @@ -0,0 +1,14 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(1)] of bool +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +find y_Occurrence: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +branching on [x_ExplicitVarSizeWithDummy, x_Occurrence, y_ExplicitVarSizeWithDummy, y_Occurrence] +such that + x_Occurrence[1] /\ y_Occurrence[1] -> false, + x_ExplicitVarSizeWithDummy[1] != 2 -> x_Occurrence[x_ExplicitVarSizeWithDummy[1]], + x_Occurrence[1] -> x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = 1, + y_ExplicitVarSizeWithDummy[1] != 2 -> y_Occurrence[y_ExplicitVarSizeWithDummy[1]], + y_Occurrence[1] -> y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = 1 + diff --git a/tests/exhaustive/basic/typed01/expected/model_1_1_2_3-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_1_1_2_3-solution000001.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_1_2_3-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_1_2_3-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_1_1_2_3-solution000002.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_1_2_3-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_1_2_3-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_1_1_2_3-solution000003.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_1_2_3-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_1_2_3.eprime b/tests/exhaustive/basic/typed01/expected/model_1_1_2_3.eprime new file mode 100644 index 0000000000..56aa03eb37 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_1_2_3.eprime @@ -0,0 +1,18 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(1)] of bool +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +find y_Occurrence: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithMarker_Marker: int(0..1) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +branching on + [x_ExplicitVarSizeWithDummy, x_Occurrence, y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values, + y_Occurrence] +such that + x_Occurrence[1] /\ y_Occurrence[1] -> false, + x_ExplicitVarSizeWithDummy[1] != 2 -> x_Occurrence[x_ExplicitVarSizeWithDummy[1]], + x_Occurrence[1] -> x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = 1, + 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, + 1 <= y_ExplicitVarSizeWithMarker_Marker -> y_Occurrence[y_ExplicitVarSizeWithMarker_Values[1]], + y_Occurrence[1] -> 1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = 1 + diff --git a/tests/exhaustive/basic/typed01/expected/model_1_1_2_4-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_1_1_2_4-solution000001.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_1_2_4-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_1_2_4-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_1_1_2_4-solution000002.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_1_2_4-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_1_2_4-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_1_1_2_4-solution000003.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_1_2_4-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_1_2_4.eprime b/tests/exhaustive/basic/typed01/expected/model_1_1_2_4.eprime new file mode 100644 index 0000000000..2feadc3613 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_1_2_4.eprime @@ -0,0 +1,18 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(1)] of bool +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +find y_Occurrence: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +branching on + [x_ExplicitVarSizeWithDummy, x_Occurrence, y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values, + y_Occurrence] +such that + x_Occurrence[1] /\ y_Occurrence[1] -> false, + x_ExplicitVarSizeWithDummy[1] != 2 -> x_Occurrence[x_ExplicitVarSizeWithDummy[1]], + x_Occurrence[1] -> x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = 1, + y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, + y_ExplicitVarSizeWithFlags_Flags[1] -> y_Occurrence[y_ExplicitVarSizeWithFlags_Values[1]], + y_Occurrence[1] -> y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = 1 + diff --git a/tests/exhaustive/basic/typed01/expected/model_1_1_3_1-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_1_1_3_1-solution000001.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_1_3_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_1_3_1-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_1_1_3_1-solution000002.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_1_3_1-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_1_3_1-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_1_1_3_1-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_1_3_1-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_1_3_1.eprime b/tests/exhaustive/basic/typed01/expected/model_1_1_3_1.eprime new file mode 100644 index 0000000000..2c5a058d3e --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_1_3_1.eprime @@ -0,0 +1,13 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(1)] of bool +find x_ExplicitVarSizeWithMarker_Marker: int(0..1) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +find y_Occurrence: matrix indexed by [int(1)] of bool +branching on [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_Occurrence, y_Occurrence] +such that + x_Occurrence[1] /\ y_Occurrence[1] -> false, + 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, + 1 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[1]], + x_Occurrence[1] -> 1 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[1] = 1 + diff --git a/tests/exhaustive/basic/typed01/expected/model_1_1_3_2-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_1_1_3_2-solution000001.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_1_3_2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_1_3_2-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_1_1_3_2-solution000002.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_1_3_2-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_1_3_2-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_1_1_3_2-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_1_3_2-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_1_3_2.eprime b/tests/exhaustive/basic/typed01/expected/model_1_1_3_2.eprime new file mode 100644 index 0000000000..79607aae8e --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_1_3_2.eprime @@ -0,0 +1,18 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(1)] of bool +find x_ExplicitVarSizeWithMarker_Marker: int(0..1) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +find y_Occurrence: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +branching on + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_Occurrence, y_ExplicitVarSizeWithDummy, + y_Occurrence] +such that + x_Occurrence[1] /\ y_Occurrence[1] -> false, + 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, + 1 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[1]], + x_Occurrence[1] -> 1 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[1] = 1, + y_ExplicitVarSizeWithDummy[1] != 2 -> y_Occurrence[y_ExplicitVarSizeWithDummy[1]], + y_Occurrence[1] -> y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = 1 + diff --git a/tests/exhaustive/basic/typed01/expected/model_1_1_3_3-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_1_1_3_3-solution000001.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_1_3_3-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_1_3_3-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_1_1_3_3-solution000002.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_1_3_3-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_1_3_3-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_1_1_3_3-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_1_3_3-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_1_3_3.eprime b/tests/exhaustive/basic/typed01/expected/model_1_1_3_3.eprime new file mode 100644 index 0000000000..e4c42fc2e4 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_1_3_3.eprime @@ -0,0 +1,20 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(1)] of bool +find x_ExplicitVarSizeWithMarker_Marker: int(0..1) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +find y_Occurrence: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithMarker_Marker: int(0..1) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +branching on + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_Occurrence, + y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values, y_Occurrence] +such that + x_Occurrence[1] /\ y_Occurrence[1] -> false, + 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, + 1 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[1]], + x_Occurrence[1] -> 1 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[1] = 1, + 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, + 1 <= y_ExplicitVarSizeWithMarker_Marker -> y_Occurrence[y_ExplicitVarSizeWithMarker_Values[1]], + y_Occurrence[1] -> 1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = 1 + diff --git a/tests/exhaustive/basic/typed01/expected/model_1_1_3_4-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_1_1_3_4-solution000001.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_1_3_4-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_1_3_4-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_1_1_3_4-solution000002.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_1_3_4-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_1_3_4-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_1_1_3_4-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_1_3_4-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_1_3_4.eprime b/tests/exhaustive/basic/typed01/expected/model_1_1_3_4.eprime new file mode 100644 index 0000000000..6a78b5ae6b --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_1_3_4.eprime @@ -0,0 +1,20 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(1)] of bool +find x_ExplicitVarSizeWithMarker_Marker: int(0..1) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +find y_Occurrence: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +branching on + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_Occurrence, + y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values, y_Occurrence] +such that + x_Occurrence[1] /\ y_Occurrence[1] -> false, + 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, + 1 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[1]], + x_Occurrence[1] -> 1 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[1] = 1, + y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, + y_ExplicitVarSizeWithFlags_Flags[1] -> y_Occurrence[y_ExplicitVarSizeWithFlags_Values[1]], + y_Occurrence[1] -> y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = 1 + diff --git a/tests/exhaustive/basic/typed01/expected/model_1_1_4_1-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_1_1_4_1-solution000001.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_1_4_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_1_4_1-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_1_1_4_1-solution000002.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_1_4_1-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_1_4_1-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_1_1_4_1-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_1_4_1-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_1_4_1.eprime b/tests/exhaustive/basic/typed01/expected/model_1_1_4_1.eprime new file mode 100644 index 0000000000..4e002eba26 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_1_4_1.eprime @@ -0,0 +1,13 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(1)] of bool +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +find y_Occurrence: matrix indexed by [int(1)] of bool +branching on [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_Occurrence, y_Occurrence] +such that + x_Occurrence[1] /\ y_Occurrence[1] -> false, + x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, + x_ExplicitVarSizeWithFlags_Flags[1] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[1]], + x_Occurrence[1] -> x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = 1 + diff --git a/tests/exhaustive/basic/typed01/expected/model_1_1_4_2-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_1_1_4_2-solution000001.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_1_4_2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_1_4_2-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_1_1_4_2-solution000002.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_1_4_2-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_1_4_2-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_1_1_4_2-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_1_4_2-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_1_4_2.eprime b/tests/exhaustive/basic/typed01/expected/model_1_1_4_2.eprime new file mode 100644 index 0000000000..10f0ab252c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_1_4_2.eprime @@ -0,0 +1,18 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(1)] of bool +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +find y_Occurrence: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +branching on + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_Occurrence, y_ExplicitVarSizeWithDummy, + y_Occurrence] +such that + x_Occurrence[1] /\ y_Occurrence[1] -> false, + x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, + x_ExplicitVarSizeWithFlags_Flags[1] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[1]], + x_Occurrence[1] -> x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = 1, + y_ExplicitVarSizeWithDummy[1] != 2 -> y_Occurrence[y_ExplicitVarSizeWithDummy[1]], + y_Occurrence[1] -> y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = 1 + diff --git a/tests/exhaustive/basic/typed01/expected/model_1_1_4_3-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_1_1_4_3-solution000001.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_1_4_3-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_1_4_3-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_1_1_4_3-solution000002.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_1_4_3-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_1_4_3-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_1_1_4_3-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_1_4_3-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_1_4_3.eprime b/tests/exhaustive/basic/typed01/expected/model_1_1_4_3.eprime new file mode 100644 index 0000000000..bec813d72f --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_1_4_3.eprime @@ -0,0 +1,20 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(1)] of bool +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +find y_Occurrence: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithMarker_Marker: int(0..1) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +branching on + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_Occurrence, + y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values, y_Occurrence] +such that + x_Occurrence[1] /\ y_Occurrence[1] -> false, + x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, + x_ExplicitVarSizeWithFlags_Flags[1] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[1]], + x_Occurrence[1] -> x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = 1, + 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, + 1 <= y_ExplicitVarSizeWithMarker_Marker -> y_Occurrence[y_ExplicitVarSizeWithMarker_Values[1]], + y_Occurrence[1] -> 1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = 1 + diff --git a/tests/exhaustive/basic/typed01/expected/model_1_1_4_4-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_1_1_4_4-solution000001.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_1_4_4-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_1_4_4-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_1_1_4_4-solution000002.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_1_4_4-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_1_4_4-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_1_1_4_4-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_1_4_4-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_1_4_4.eprime b/tests/exhaustive/basic/typed01/expected/model_1_1_4_4.eprime new file mode 100644 index 0000000000..3d1696bc7d --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_1_4_4.eprime @@ -0,0 +1,20 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(1)] of bool +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +find y_Occurrence: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +branching on + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_Occurrence, + y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values, y_Occurrence] +such that + x_Occurrence[1] /\ y_Occurrence[1] -> false, + x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, + x_ExplicitVarSizeWithFlags_Flags[1] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[1]], + x_Occurrence[1] -> x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = 1, + y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, + y_ExplicitVarSizeWithFlags_Flags[1] -> y_Occurrence[y_ExplicitVarSizeWithFlags_Values[1]], + y_Occurrence[1] -> y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = 1 + diff --git a/tests/exhaustive/basic/typed01/expected/model_1_2_1_1-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_1_2_1_1-solution000001.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_2_1_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_2_1_1-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_1_2_1_1-solution000002.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_2_1_1-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_2_1_1-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_1_2_1_1-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_2_1_1-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_2_1_1.eprime b/tests/exhaustive/basic/typed01/expected/model_1_2_1_1.eprime new file mode 100644 index 0000000000..a11e9dfe09 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_2_1_1.eprime @@ -0,0 +1,11 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +find y_Occurrence: matrix indexed by [int(1)] of bool +branching on [x_Occurrence, y_Occurrence, y_ExplicitVarSizeWithDummy] +such that + x_Occurrence[1] /\ (y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = 1) -> false, + y_Occurrence[1] -> y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = 1, + y_ExplicitVarSizeWithDummy[1] != 2 -> y_Occurrence[y_ExplicitVarSizeWithDummy[1]] + diff --git a/tests/exhaustive/basic/typed01/expected/model_1_2_1_2-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_1_2_1_2-solution000001.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_2_1_2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_2_1_2-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_1_2_1_2-solution000002.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_2_1_2-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_2_1_2-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_1_2_1_2-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_2_1_2-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_2_1_2.eprime b/tests/exhaustive/basic/typed01/expected/model_1_2_1_2.eprime new file mode 100644 index 0000000000..f2ff753504 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_2_1_2.eprime @@ -0,0 +1,7 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +branching on [x_Occurrence, y_ExplicitVarSizeWithDummy] +such that x_Occurrence[1] /\ (y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = 1) -> false + diff --git a/tests/exhaustive/basic/typed01/expected/model_1_2_1_3-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_1_2_1_3-solution000001.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_2_1_3-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_2_1_3-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_1_2_1_3-solution000002.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_2_1_3-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_2_1_3-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_1_2_1_3-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_2_1_3-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_2_1_3.eprime b/tests/exhaustive/basic/typed01/expected/model_1_2_1_3.eprime new file mode 100644 index 0000000000..1efda9ae16 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_2_1_3.eprime @@ -0,0 +1,16 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +find y_ExplicitVarSizeWithMarker_Marker: int(0..1) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +branching on + [x_Occurrence, y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithDummy] +such that + x_Occurrence[1] /\ (y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = 1) -> false, + 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, + 1 <= y_ExplicitVarSizeWithMarker_Marker -> + y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = y_ExplicitVarSizeWithMarker_Values[1], + y_ExplicitVarSizeWithDummy[1] != 2 -> + 1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = y_ExplicitVarSizeWithDummy[1] + diff --git a/tests/exhaustive/basic/typed01/expected/model_1_2_1_4-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_1_2_1_4-solution000001.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_2_1_4-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_2_1_4-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_1_2_1_4-solution000002.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_2_1_4-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_2_1_4-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_1_2_1_4-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_2_1_4-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_2_1_4.eprime b/tests/exhaustive/basic/typed01/expected/model_1_2_1_4.eprime new file mode 100644 index 0000000000..afe11ceafd --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_2_1_4.eprime @@ -0,0 +1,16 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +branching on + [x_Occurrence, y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithDummy] +such that + x_Occurrence[1] /\ (y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = 1) -> false, + y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, + y_ExplicitVarSizeWithFlags_Flags[1] -> + y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = y_ExplicitVarSizeWithFlags_Values[1], + y_ExplicitVarSizeWithDummy[1] != 2 -> + y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = y_ExplicitVarSizeWithDummy[1] + diff --git a/tests/exhaustive/basic/typed01/expected/model_1_2_2_1-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_1_2_2_1-solution000001.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_2_2_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_2_2_1-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_1_2_2_1-solution000002.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_2_2_1-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_2_2_1-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_1_2_2_1-solution000003.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_2_2_1-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_2_2_1.eprime b/tests/exhaustive/basic/typed01/expected/model_1_2_2_1.eprime new file mode 100644 index 0000000000..19621229d3 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_2_2_1.eprime @@ -0,0 +1,14 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(1)] of bool +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +find y_Occurrence: matrix indexed by [int(1)] of bool +branching on [x_ExplicitVarSizeWithDummy, x_Occurrence, y_Occurrence, y_ExplicitVarSizeWithDummy] +such that + x_Occurrence[1] /\ (y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = 1) -> false, + x_ExplicitVarSizeWithDummy[1] != 2 -> x_Occurrence[x_ExplicitVarSizeWithDummy[1]], + x_Occurrence[1] -> x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = 1, + y_Occurrence[1] -> y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = 1, + y_ExplicitVarSizeWithDummy[1] != 2 -> y_Occurrence[y_ExplicitVarSizeWithDummy[1]] + diff --git a/tests/exhaustive/basic/typed01/expected/model_1_2_2_2-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_1_2_2_2-solution000001.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_2_2_2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_2_2_2-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_1_2_2_2-solution000002.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_2_2_2-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_2_2_2-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_1_2_2_2-solution000003.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_2_2_2-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_2_2_2.eprime b/tests/exhaustive/basic/typed01/expected/model_1_2_2_2.eprime new file mode 100644 index 0000000000..598c4469a5 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_2_2_2.eprime @@ -0,0 +1,11 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(1)] of bool +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +branching on [x_ExplicitVarSizeWithDummy, x_Occurrence, y_ExplicitVarSizeWithDummy] +such that + x_Occurrence[1] /\ (y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = 1) -> false, + x_ExplicitVarSizeWithDummy[1] != 2 -> x_Occurrence[x_ExplicitVarSizeWithDummy[1]], + x_Occurrence[1] -> x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = 1 + diff --git a/tests/exhaustive/basic/typed01/expected/model_1_2_2_3-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_1_2_2_3-solution000001.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_2_2_3-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_2_2_3-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_1_2_2_3-solution000002.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_2_2_3-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_2_2_3-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_1_2_2_3-solution000003.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_2_2_3-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_2_2_3.eprime b/tests/exhaustive/basic/typed01/expected/model_1_2_2_3.eprime new file mode 100644 index 0000000000..2778101db8 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_2_2_3.eprime @@ -0,0 +1,20 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(1)] of bool +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +find y_ExplicitVarSizeWithMarker_Marker: int(0..1) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +branching on + [x_ExplicitVarSizeWithDummy, x_Occurrence, y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values, + y_ExplicitVarSizeWithDummy] +such that + x_Occurrence[1] /\ (y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = 1) -> false, + x_ExplicitVarSizeWithDummy[1] != 2 -> x_Occurrence[x_ExplicitVarSizeWithDummy[1]], + x_Occurrence[1] -> x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = 1, + 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, + 1 <= y_ExplicitVarSizeWithMarker_Marker -> + y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = y_ExplicitVarSizeWithMarker_Values[1], + y_ExplicitVarSizeWithDummy[1] != 2 -> + 1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = y_ExplicitVarSizeWithDummy[1] + diff --git a/tests/exhaustive/basic/typed01/expected/model_1_2_2_4-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_1_2_2_4-solution000001.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_2_2_4-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_2_2_4-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_1_2_2_4-solution000002.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_2_2_4-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_2_2_4-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_1_2_2_4-solution000003.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_2_2_4-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_2_2_4.eprime b/tests/exhaustive/basic/typed01/expected/model_1_2_2_4.eprime new file mode 100644 index 0000000000..7a17794ceb --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_2_2_4.eprime @@ -0,0 +1,20 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(1)] of bool +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +branching on + [x_ExplicitVarSizeWithDummy, x_Occurrence, y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values, + y_ExplicitVarSizeWithDummy] +such that + x_Occurrence[1] /\ (y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = 1) -> false, + x_ExplicitVarSizeWithDummy[1] != 2 -> x_Occurrence[x_ExplicitVarSizeWithDummy[1]], + x_Occurrence[1] -> x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = 1, + y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, + y_ExplicitVarSizeWithFlags_Flags[1] -> + y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = y_ExplicitVarSizeWithFlags_Values[1], + y_ExplicitVarSizeWithDummy[1] != 2 -> + y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = y_ExplicitVarSizeWithDummy[1] + diff --git a/tests/exhaustive/basic/typed01/expected/model_1_2_3_1-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_1_2_3_1-solution000001.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_2_3_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_2_3_1-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_1_2_3_1-solution000002.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_2_3_1-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_2_3_1-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_1_2_3_1-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_2_3_1-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_2_3_1.eprime b/tests/exhaustive/basic/typed01/expected/model_1_2_3_1.eprime new file mode 100644 index 0000000000..740f1db56a --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_2_3_1.eprime @@ -0,0 +1,18 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(1)] of bool +find x_ExplicitVarSizeWithMarker_Marker: int(0..1) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +find y_Occurrence: matrix indexed by [int(1)] of bool +branching on + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_Occurrence, y_Occurrence, + y_ExplicitVarSizeWithDummy] +such that + x_Occurrence[1] /\ (y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = 1) -> false, + 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, + 1 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[1]], + x_Occurrence[1] -> 1 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[1] = 1, + y_Occurrence[1] -> y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = 1, + y_ExplicitVarSizeWithDummy[1] != 2 -> y_Occurrence[y_ExplicitVarSizeWithDummy[1]] + diff --git a/tests/exhaustive/basic/typed01/expected/model_1_2_3_2-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_1_2_3_2-solution000001.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_2_3_2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_2_3_2-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_1_2_3_2-solution000002.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_2_3_2-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_2_3_2-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_1_2_3_2-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_2_3_2-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_2_3_2.eprime b/tests/exhaustive/basic/typed01/expected/model_1_2_3_2.eprime new file mode 100644 index 0000000000..c4faccb2d1 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_2_3_2.eprime @@ -0,0 +1,14 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(1)] of bool +find x_ExplicitVarSizeWithMarker_Marker: int(0..1) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +branching on + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_Occurrence, y_ExplicitVarSizeWithDummy] +such that + x_Occurrence[1] /\ (y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = 1) -> false, + 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, + 1 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[1]], + x_Occurrence[1] -> 1 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[1] = 1 + diff --git a/tests/exhaustive/basic/typed01/expected/model_1_2_3_3-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_1_2_3_3-solution000001.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_2_3_3-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_2_3_3-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_1_2_3_3-solution000002.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_2_3_3-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_2_3_3-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_1_2_3_3-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_2_3_3-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_2_3_3.eprime b/tests/exhaustive/basic/typed01/expected/model_1_2_3_3.eprime new file mode 100644 index 0000000000..2c591401fc --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_2_3_3.eprime @@ -0,0 +1,22 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(1)] of bool +find x_ExplicitVarSizeWithMarker_Marker: int(0..1) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +find y_ExplicitVarSizeWithMarker_Marker: int(0..1) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +branching on + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_Occurrence, + y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithDummy] +such that + x_Occurrence[1] /\ (y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = 1) -> false, + 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, + 1 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[1]], + x_Occurrence[1] -> 1 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[1] = 1, + 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, + 1 <= y_ExplicitVarSizeWithMarker_Marker -> + y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = y_ExplicitVarSizeWithMarker_Values[1], + y_ExplicitVarSizeWithDummy[1] != 2 -> + 1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = y_ExplicitVarSizeWithDummy[1] + diff --git a/tests/exhaustive/basic/typed01/expected/model_1_2_3_4-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_1_2_3_4-solution000001.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_2_3_4-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_2_3_4-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_1_2_3_4-solution000002.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_2_3_4-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_2_3_4-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_1_2_3_4-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_2_3_4-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_2_3_4.eprime b/tests/exhaustive/basic/typed01/expected/model_1_2_3_4.eprime new file mode 100644 index 0000000000..065b1128ba --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_2_3_4.eprime @@ -0,0 +1,22 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(1)] of bool +find x_ExplicitVarSizeWithMarker_Marker: int(0..1) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +branching on + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_Occurrence, + y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithDummy] +such that + x_Occurrence[1] /\ (y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = 1) -> false, + 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, + 1 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[1]], + x_Occurrence[1] -> 1 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[1] = 1, + y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, + y_ExplicitVarSizeWithFlags_Flags[1] -> + y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = y_ExplicitVarSizeWithFlags_Values[1], + y_ExplicitVarSizeWithDummy[1] != 2 -> + y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = y_ExplicitVarSizeWithDummy[1] + diff --git a/tests/exhaustive/basic/typed01/expected/model_1_2_4_1-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_1_2_4_1-solution000001.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_2_4_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_2_4_1-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_1_2_4_1-solution000002.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_2_4_1-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_2_4_1-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_1_2_4_1-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_2_4_1-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_2_4_1.eprime b/tests/exhaustive/basic/typed01/expected/model_1_2_4_1.eprime new file mode 100644 index 0000000000..734b00c535 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_2_4_1.eprime @@ -0,0 +1,18 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(1)] of bool +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +find y_Occurrence: matrix indexed by [int(1)] of bool +branching on + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_Occurrence, y_Occurrence, + y_ExplicitVarSizeWithDummy] +such that + x_Occurrence[1] /\ (y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = 1) -> false, + x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, + x_ExplicitVarSizeWithFlags_Flags[1] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[1]], + x_Occurrence[1] -> x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = 1, + y_Occurrence[1] -> y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = 1, + y_ExplicitVarSizeWithDummy[1] != 2 -> y_Occurrence[y_ExplicitVarSizeWithDummy[1]] + diff --git a/tests/exhaustive/basic/typed01/expected/model_1_2_4_2-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_1_2_4_2-solution000001.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_2_4_2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_2_4_2-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_1_2_4_2-solution000002.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_2_4_2-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_2_4_2-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_1_2_4_2-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_2_4_2-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_2_4_2.eprime b/tests/exhaustive/basic/typed01/expected/model_1_2_4_2.eprime new file mode 100644 index 0000000000..af1b4633ab --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_2_4_2.eprime @@ -0,0 +1,14 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(1)] of bool +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +branching on + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_Occurrence, y_ExplicitVarSizeWithDummy] +such that + x_Occurrence[1] /\ (y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = 1) -> false, + x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, + x_ExplicitVarSizeWithFlags_Flags[1] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[1]], + x_Occurrence[1] -> x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = 1 + diff --git a/tests/exhaustive/basic/typed01/expected/model_1_2_4_3-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_1_2_4_3-solution000001.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_2_4_3-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_2_4_3-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_1_2_4_3-solution000002.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_2_4_3-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_2_4_3-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_1_2_4_3-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_2_4_3-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_2_4_3.eprime b/tests/exhaustive/basic/typed01/expected/model_1_2_4_3.eprime new file mode 100644 index 0000000000..5a5d396454 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_2_4_3.eprime @@ -0,0 +1,22 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(1)] of bool +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +find y_ExplicitVarSizeWithMarker_Marker: int(0..1) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +branching on + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_Occurrence, + y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithDummy] +such that + x_Occurrence[1] /\ (y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = 1) -> false, + x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, + x_ExplicitVarSizeWithFlags_Flags[1] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[1]], + x_Occurrence[1] -> x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = 1, + 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, + 1 <= y_ExplicitVarSizeWithMarker_Marker -> + y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = y_ExplicitVarSizeWithMarker_Values[1], + y_ExplicitVarSizeWithDummy[1] != 2 -> + 1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = y_ExplicitVarSizeWithDummy[1] + diff --git a/tests/exhaustive/basic/typed01/expected/model_1_2_4_4-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_1_2_4_4-solution000001.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_2_4_4-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_2_4_4-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_1_2_4_4-solution000002.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_2_4_4-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_2_4_4-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_1_2_4_4-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_2_4_4-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_2_4_4.eprime b/tests/exhaustive/basic/typed01/expected/model_1_2_4_4.eprime new file mode 100644 index 0000000000..38426c425d --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_2_4_4.eprime @@ -0,0 +1,22 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(1)] of bool +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +branching on + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_Occurrence, + y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithDummy] +such that + x_Occurrence[1] /\ (y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = 1) -> false, + x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, + x_ExplicitVarSizeWithFlags_Flags[1] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[1]], + x_Occurrence[1] -> x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = 1, + y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, + y_ExplicitVarSizeWithFlags_Flags[1] -> + y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = y_ExplicitVarSizeWithFlags_Values[1], + y_ExplicitVarSizeWithDummy[1] != 2 -> + y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = y_ExplicitVarSizeWithDummy[1] + diff --git a/tests/exhaustive/basic/typed01/expected/model_1_3_1_1-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_1_3_1_1-solution000001.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_3_1_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_3_1_1-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_1_3_1_1-solution000002.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_3_1_1-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_3_1_1-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_1_3_1_1-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_3_1_1-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_3_1_1.eprime b/tests/exhaustive/basic/typed01/expected/model_1_3_1_1.eprime new file mode 100644 index 0000000000..0e788a249a --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_3_1_1.eprime @@ -0,0 +1,13 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithMarker_Marker: int(0..1) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +find y_Occurrence: matrix indexed by [int(1)] of bool +branching on [x_Occurrence, y_Occurrence, y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values] +such that + x_Occurrence[1] /\ (1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = 1) -> false, + 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, + y_Occurrence[1] -> 1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = 1, + 1 <= y_ExplicitVarSizeWithMarker_Marker -> y_Occurrence[y_ExplicitVarSizeWithMarker_Values[1]] + diff --git a/tests/exhaustive/basic/typed01/expected/model_1_3_1_2-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_1_3_1_2-solution000001.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_3_1_2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_3_1_2-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_1_3_1_2-solution000002.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_3_1_2-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_3_1_2-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_1_3_1_2-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_3_1_2-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_3_1_2.eprime b/tests/exhaustive/basic/typed01/expected/model_1_3_1_2.eprime new file mode 100644 index 0000000000..bd9ff9b0f3 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_3_1_2.eprime @@ -0,0 +1,16 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithMarker_Marker: int(0..1) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +branching on + [x_Occurrence, y_ExplicitVarSizeWithDummy, y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values] +such that + x_Occurrence[1] /\ (1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = 1) -> false, + 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, + y_ExplicitVarSizeWithDummy[1] != 2 -> + 1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = y_ExplicitVarSizeWithDummy[1], + 1 <= y_ExplicitVarSizeWithMarker_Marker -> + y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = y_ExplicitVarSizeWithMarker_Values[1] + diff --git a/tests/exhaustive/basic/typed01/expected/model_1_3_1_3-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_1_3_1_3-solution000001.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_3_1_3-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_3_1_3-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_1_3_1_3-solution000002.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_3_1_3-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_3_1_3-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_1_3_1_3-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_3_1_3-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_3_1_3.eprime b/tests/exhaustive/basic/typed01/expected/model_1_3_1_3.eprime new file mode 100644 index 0000000000..b8082395cd --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_3_1_3.eprime @@ -0,0 +1,10 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithMarker_Marker: int(0..1) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +branching on [x_Occurrence, y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values] +such that + x_Occurrence[1] /\ (1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = 1) -> false, + 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1 + diff --git a/tests/exhaustive/basic/typed01/expected/model_1_3_1_4-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_1_3_1_4-solution000001.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_3_1_4-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_3_1_4-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_1_3_1_4-solution000002.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_3_1_4-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_3_1_4-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_1_3_1_4-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_3_1_4-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_3_1_4.eprime b/tests/exhaustive/basic/typed01/expected/model_1_3_1_4.eprime new file mode 100644 index 0000000000..4def58b75c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_3_1_4.eprime @@ -0,0 +1,20 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithMarker_Marker: int(0..1) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +branching on + [x_Occurrence, y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values, + y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values] +such that + x_Occurrence[1] /\ (1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = 1) -> false, + 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, + y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, + y_ExplicitVarSizeWithFlags_Flags[1] -> + 1 <= y_ExplicitVarSizeWithMarker_Marker /\ + y_ExplicitVarSizeWithMarker_Values[1] = y_ExplicitVarSizeWithFlags_Values[1], + 1 <= y_ExplicitVarSizeWithMarker_Marker -> + y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = y_ExplicitVarSizeWithMarker_Values[1] + diff --git a/tests/exhaustive/basic/typed01/expected/model_1_3_2_1-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_1_3_2_1-solution000001.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_3_2_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_3_2_1-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_1_3_2_1-solution000002.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_3_2_1-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_3_2_1-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_1_3_2_1-solution000003.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_3_2_1-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_3_2_1.eprime b/tests/exhaustive/basic/typed01/expected/model_1_3_2_1.eprime new file mode 100644 index 0000000000..d53864e2d5 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_3_2_1.eprime @@ -0,0 +1,18 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(1)] of bool +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +find y_ExplicitVarSizeWithMarker_Marker: int(0..1) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +find y_Occurrence: matrix indexed by [int(1)] of bool +branching on + [x_ExplicitVarSizeWithDummy, x_Occurrence, y_Occurrence, y_ExplicitVarSizeWithMarker_Marker, + y_ExplicitVarSizeWithMarker_Values] +such that + x_Occurrence[1] /\ (1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = 1) -> false, + 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, + x_ExplicitVarSizeWithDummy[1] != 2 -> x_Occurrence[x_ExplicitVarSizeWithDummy[1]], + x_Occurrence[1] -> x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = 1, + y_Occurrence[1] -> 1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = 1, + 1 <= y_ExplicitVarSizeWithMarker_Marker -> y_Occurrence[y_ExplicitVarSizeWithMarker_Values[1]] + diff --git a/tests/exhaustive/basic/typed01/expected/model_1_3_2_2-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_1_3_2_2-solution000001.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_3_2_2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_3_2_2-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_1_3_2_2-solution000002.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_3_2_2-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_3_2_2-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_1_3_2_2-solution000003.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_3_2_2-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_3_2_2.eprime b/tests/exhaustive/basic/typed01/expected/model_1_3_2_2.eprime new file mode 100644 index 0000000000..076023e23e --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_3_2_2.eprime @@ -0,0 +1,20 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(1)] of bool +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +find y_ExplicitVarSizeWithMarker_Marker: int(0..1) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +branching on + [x_ExplicitVarSizeWithDummy, x_Occurrence, y_ExplicitVarSizeWithDummy, y_ExplicitVarSizeWithMarker_Marker, + y_ExplicitVarSizeWithMarker_Values] +such that + x_Occurrence[1] /\ (1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = 1) -> false, + 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, + x_ExplicitVarSizeWithDummy[1] != 2 -> x_Occurrence[x_ExplicitVarSizeWithDummy[1]], + x_Occurrence[1] -> x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = 1, + y_ExplicitVarSizeWithDummy[1] != 2 -> + 1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = y_ExplicitVarSizeWithDummy[1], + 1 <= y_ExplicitVarSizeWithMarker_Marker -> + y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = y_ExplicitVarSizeWithMarker_Values[1] + diff --git a/tests/exhaustive/basic/typed01/expected/model_1_3_2_3-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_1_3_2_3-solution000001.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_3_2_3-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_3_2_3-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_1_3_2_3-solution000002.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_3_2_3-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_3_2_3-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_1_3_2_3-solution000003.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_3_2_3-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_3_2_3.eprime b/tests/exhaustive/basic/typed01/expected/model_1_3_2_3.eprime new file mode 100644 index 0000000000..b30170d39b --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_3_2_3.eprime @@ -0,0 +1,14 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(1)] of bool +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +find y_ExplicitVarSizeWithMarker_Marker: int(0..1) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +branching on + [x_ExplicitVarSizeWithDummy, x_Occurrence, y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values] +such that + x_Occurrence[1] /\ (1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = 1) -> false, + 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, + x_ExplicitVarSizeWithDummy[1] != 2 -> x_Occurrence[x_ExplicitVarSizeWithDummy[1]], + x_Occurrence[1] -> x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = 1 + diff --git a/tests/exhaustive/basic/typed01/expected/model_1_3_2_4-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_1_3_2_4-solution000001.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_3_2_4-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_3_2_4-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_1_3_2_4-solution000002.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_3_2_4-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_3_2_4-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_1_3_2_4-solution000003.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_3_2_4-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_3_2_4.eprime b/tests/exhaustive/basic/typed01/expected/model_1_3_2_4.eprime new file mode 100644 index 0000000000..b355a9ad86 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_3_2_4.eprime @@ -0,0 +1,23 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(1)] of bool +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +find y_ExplicitVarSizeWithMarker_Marker: int(0..1) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +branching on + [x_ExplicitVarSizeWithDummy, x_Occurrence, y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values, + y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values] +such that + x_Occurrence[1] /\ (1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = 1) -> false, + 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, + x_ExplicitVarSizeWithDummy[1] != 2 -> x_Occurrence[x_ExplicitVarSizeWithDummy[1]], + x_Occurrence[1] -> x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = 1, + y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, + y_ExplicitVarSizeWithFlags_Flags[1] -> + 1 <= y_ExplicitVarSizeWithMarker_Marker /\ + y_ExplicitVarSizeWithMarker_Values[1] = y_ExplicitVarSizeWithFlags_Values[1], + 1 <= y_ExplicitVarSizeWithMarker_Marker -> + y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = y_ExplicitVarSizeWithMarker_Values[1] + diff --git a/tests/exhaustive/basic/typed01/expected/model_1_3_3_1-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_1_3_3_1-solution000001.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_3_3_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_3_3_1-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_1_3_3_1-solution000002.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_3_3_1-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_3_3_1-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_1_3_3_1-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_3_3_1-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_3_3_1.eprime b/tests/exhaustive/basic/typed01/expected/model_1_3_3_1.eprime new file mode 100644 index 0000000000..db5c695212 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_3_3_1.eprime @@ -0,0 +1,20 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(1)] of bool +find x_ExplicitVarSizeWithMarker_Marker: int(0..1) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +find y_ExplicitVarSizeWithMarker_Marker: int(0..1) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +find y_Occurrence: matrix indexed by [int(1)] of bool +branching on + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_Occurrence, y_Occurrence, + y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values] +such that + x_Occurrence[1] /\ (1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = 1) -> false, + 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, + 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, + 1 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[1]], + x_Occurrence[1] -> 1 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[1] = 1, + y_Occurrence[1] -> 1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = 1, + 1 <= y_ExplicitVarSizeWithMarker_Marker -> y_Occurrence[y_ExplicitVarSizeWithMarker_Values[1]] + diff --git a/tests/exhaustive/basic/typed01/expected/model_1_3_3_2-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_1_3_3_2-solution000001.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_3_3_2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_3_3_2-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_1_3_3_2-solution000002.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_3_3_2-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_3_3_2-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_1_3_3_2-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_3_3_2-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_3_3_2.eprime b/tests/exhaustive/basic/typed01/expected/model_1_3_3_2.eprime new file mode 100644 index 0000000000..12bdab1c1e --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_3_3_2.eprime @@ -0,0 +1,22 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(1)] of bool +find x_ExplicitVarSizeWithMarker_Marker: int(0..1) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +find y_ExplicitVarSizeWithMarker_Marker: int(0..1) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +branching on + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_Occurrence, y_ExplicitVarSizeWithDummy, + y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values] +such that + x_Occurrence[1] /\ (1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = 1) -> false, + 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, + 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, + 1 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[1]], + x_Occurrence[1] -> 1 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[1] = 1, + y_ExplicitVarSizeWithDummy[1] != 2 -> + 1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = y_ExplicitVarSizeWithDummy[1], + 1 <= y_ExplicitVarSizeWithMarker_Marker -> + y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = y_ExplicitVarSizeWithMarker_Values[1] + diff --git a/tests/exhaustive/basic/typed01/expected/model_1_3_3_3-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_1_3_3_3-solution000001.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_3_3_3-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_3_3_3-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_1_3_3_3-solution000002.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_3_3_3-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_3_3_3-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_1_3_3_3-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_3_3_3-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_3_3_3.eprime b/tests/exhaustive/basic/typed01/expected/model_1_3_3_3.eprime new file mode 100644 index 0000000000..797ccd6052 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_3_3_3.eprime @@ -0,0 +1,17 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(1)] of bool +find x_ExplicitVarSizeWithMarker_Marker: int(0..1) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +find y_ExplicitVarSizeWithMarker_Marker: int(0..1) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +branching on + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_Occurrence, + y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values] +such that + x_Occurrence[1] /\ (1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = 1) -> false, + 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, + 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, + 1 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[1]], + x_Occurrence[1] -> 1 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[1] = 1 + diff --git a/tests/exhaustive/basic/typed01/expected/model_1_3_3_4-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_1_3_3_4-solution000001.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_3_3_4-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_3_3_4-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_1_3_3_4-solution000002.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_3_3_4-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_3_3_4-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_1_3_3_4-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_3_3_4-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_3_3_4.eprime b/tests/exhaustive/basic/typed01/expected/model_1_3_3_4.eprime new file mode 100644 index 0000000000..0fe2d482ea --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_3_3_4.eprime @@ -0,0 +1,26 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(1)] of bool +find x_ExplicitVarSizeWithMarker_Marker: int(0..1) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +find y_ExplicitVarSizeWithMarker_Marker: int(0..1) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +branching on + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_Occurrence, + y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithMarker_Marker, + y_ExplicitVarSizeWithMarker_Values] +such that + x_Occurrence[1] /\ (1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = 1) -> false, + 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, + 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, + 1 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[1]], + x_Occurrence[1] -> 1 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[1] = 1, + y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, + y_ExplicitVarSizeWithFlags_Flags[1] -> + 1 <= y_ExplicitVarSizeWithMarker_Marker /\ + y_ExplicitVarSizeWithMarker_Values[1] = y_ExplicitVarSizeWithFlags_Values[1], + 1 <= y_ExplicitVarSizeWithMarker_Marker -> + y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = y_ExplicitVarSizeWithMarker_Values[1] + diff --git a/tests/exhaustive/basic/typed01/expected/model_1_3_4_1-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_1_3_4_1-solution000001.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_3_4_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_3_4_1-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_1_3_4_1-solution000002.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_3_4_1-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_3_4_1-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_1_3_4_1-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_3_4_1-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_3_4_1.eprime b/tests/exhaustive/basic/typed01/expected/model_1_3_4_1.eprime new file mode 100644 index 0000000000..e0b90502fa --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_3_4_1.eprime @@ -0,0 +1,20 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(1)] of bool +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +find y_ExplicitVarSizeWithMarker_Marker: int(0..1) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +find y_Occurrence: matrix indexed by [int(1)] of bool +branching on + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_Occurrence, y_Occurrence, + y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values] +such that + x_Occurrence[1] /\ (1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = 1) -> false, + 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, + x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, + x_ExplicitVarSizeWithFlags_Flags[1] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[1]], + x_Occurrence[1] -> x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = 1, + y_Occurrence[1] -> 1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = 1, + 1 <= y_ExplicitVarSizeWithMarker_Marker -> y_Occurrence[y_ExplicitVarSizeWithMarker_Values[1]] + diff --git a/tests/exhaustive/basic/typed01/expected/model_1_3_4_2-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_1_3_4_2-solution000001.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_3_4_2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_3_4_2-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_1_3_4_2-solution000002.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_3_4_2-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_3_4_2-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_1_3_4_2-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_3_4_2-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_3_4_2.eprime b/tests/exhaustive/basic/typed01/expected/model_1_3_4_2.eprime new file mode 100644 index 0000000000..0ed8c94b10 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_3_4_2.eprime @@ -0,0 +1,22 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(1)] of bool +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +find y_ExplicitVarSizeWithMarker_Marker: int(0..1) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +branching on + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_Occurrence, y_ExplicitVarSizeWithDummy, + y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values] +such that + x_Occurrence[1] /\ (1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = 1) -> false, + 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, + x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, + x_ExplicitVarSizeWithFlags_Flags[1] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[1]], + x_Occurrence[1] -> x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = 1, + y_ExplicitVarSizeWithDummy[1] != 2 -> + 1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = y_ExplicitVarSizeWithDummy[1], + 1 <= y_ExplicitVarSizeWithMarker_Marker -> + y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = y_ExplicitVarSizeWithMarker_Values[1] + diff --git a/tests/exhaustive/basic/typed01/expected/model_1_3_4_3-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_1_3_4_3-solution000001.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_3_4_3-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_3_4_3-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_1_3_4_3-solution000002.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_3_4_3-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_3_4_3-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_1_3_4_3-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_3_4_3-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_3_4_3.eprime b/tests/exhaustive/basic/typed01/expected/model_1_3_4_3.eprime new file mode 100644 index 0000000000..5b9b136e78 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_3_4_3.eprime @@ -0,0 +1,17 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(1)] of bool +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +find y_ExplicitVarSizeWithMarker_Marker: int(0..1) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +branching on + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_Occurrence, + y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values] +such that + x_Occurrence[1] /\ (1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = 1) -> false, + 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, + x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, + x_ExplicitVarSizeWithFlags_Flags[1] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[1]], + x_Occurrence[1] -> x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = 1 + diff --git a/tests/exhaustive/basic/typed01/expected/model_1_3_4_4-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_1_3_4_4-solution000001.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_3_4_4-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_3_4_4-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_1_3_4_4-solution000002.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_3_4_4-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_3_4_4-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_1_3_4_4-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_3_4_4-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_3_4_4.eprime b/tests/exhaustive/basic/typed01/expected/model_1_3_4_4.eprime new file mode 100644 index 0000000000..e7751848d5 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_3_4_4.eprime @@ -0,0 +1,26 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(1)] of bool +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +find y_ExplicitVarSizeWithMarker_Marker: int(0..1) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +branching on + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_Occurrence, + y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithMarker_Marker, + y_ExplicitVarSizeWithMarker_Values] +such that + x_Occurrence[1] /\ (1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = 1) -> false, + 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, + x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, + x_ExplicitVarSizeWithFlags_Flags[1] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[1]], + x_Occurrence[1] -> x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = 1, + y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, + y_ExplicitVarSizeWithFlags_Flags[1] -> + 1 <= y_ExplicitVarSizeWithMarker_Marker /\ + y_ExplicitVarSizeWithMarker_Values[1] = y_ExplicitVarSizeWithFlags_Values[1], + 1 <= y_ExplicitVarSizeWithMarker_Marker -> + y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = y_ExplicitVarSizeWithMarker_Values[1] + diff --git a/tests/exhaustive/basic/typed01/expected/model_1_4_1_1-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_1_4_1_1-solution000001.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_4_1_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_4_1_1-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_1_4_1_1-solution000002.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_4_1_1-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_4_1_1-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_1_4_1_1-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_4_1_1-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_4_1_1.eprime b/tests/exhaustive/basic/typed01/expected/model_1_4_1_1.eprime new file mode 100644 index 0000000000..aed7683e32 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_4_1_1.eprime @@ -0,0 +1,13 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +find y_Occurrence: matrix indexed by [int(1)] of bool +branching on [x_Occurrence, y_Occurrence, y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values] +such that + x_Occurrence[1] /\ (y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = 1) -> false, + y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, + y_Occurrence[1] -> y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = 1, + y_ExplicitVarSizeWithFlags_Flags[1] -> y_Occurrence[y_ExplicitVarSizeWithFlags_Values[1]] + diff --git a/tests/exhaustive/basic/typed01/expected/model_1_4_1_2-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_1_4_1_2-solution000001.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_4_1_2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_4_1_2-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_1_4_1_2-solution000002.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_4_1_2-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_4_1_2-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_1_4_1_2-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_4_1_2-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_4_1_2.eprime b/tests/exhaustive/basic/typed01/expected/model_1_4_1_2.eprime new file mode 100644 index 0000000000..e0b60b66f0 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_4_1_2.eprime @@ -0,0 +1,16 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +branching on + [x_Occurrence, y_ExplicitVarSizeWithDummy, y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values] +such that + x_Occurrence[1] /\ (y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = 1) -> false, + y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, + y_ExplicitVarSizeWithDummy[1] != 2 -> + y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = y_ExplicitVarSizeWithDummy[1], + y_ExplicitVarSizeWithFlags_Flags[1] -> + y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = y_ExplicitVarSizeWithFlags_Values[1] + diff --git a/tests/exhaustive/basic/typed01/expected/model_1_4_1_3-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_1_4_1_3-solution000001.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_4_1_3-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_4_1_3-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_1_4_1_3-solution000002.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_4_1_3-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_4_1_3-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_1_4_1_3-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_4_1_3-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_4_1_3.eprime b/tests/exhaustive/basic/typed01/expected/model_1_4_1_3.eprime new file mode 100644 index 0000000000..3deed400be --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_4_1_3.eprime @@ -0,0 +1,20 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +find y_ExplicitVarSizeWithMarker_Marker: int(0..1) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +branching on + [x_Occurrence, y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values, + y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values] +such that + x_Occurrence[1] /\ (y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = 1) -> false, + y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, + 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, + 1 <= y_ExplicitVarSizeWithMarker_Marker -> + y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = y_ExplicitVarSizeWithMarker_Values[1], + y_ExplicitVarSizeWithFlags_Flags[1] -> + 1 <= y_ExplicitVarSizeWithMarker_Marker /\ + y_ExplicitVarSizeWithMarker_Values[1] = y_ExplicitVarSizeWithFlags_Values[1] + diff --git a/tests/exhaustive/basic/typed01/expected/model_1_4_1_4-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_1_4_1_4-solution000001.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_4_1_4-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_4_1_4-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_1_4_1_4-solution000002.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_4_1_4-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_4_1_4-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_1_4_1_4-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_4_1_4-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_4_1_4.eprime b/tests/exhaustive/basic/typed01/expected/model_1_4_1_4.eprime new file mode 100644 index 0000000000..3652c914ad --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_4_1_4.eprime @@ -0,0 +1,10 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +branching on [x_Occurrence, y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values] +such that + x_Occurrence[1] /\ (y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = 1) -> false, + y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1 + diff --git a/tests/exhaustive/basic/typed01/expected/model_1_4_2_1-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_1_4_2_1-solution000001.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_4_2_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_4_2_1-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_1_4_2_1-solution000002.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_4_2_1-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_4_2_1-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_1_4_2_1-solution000003.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_4_2_1-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_4_2_1.eprime b/tests/exhaustive/basic/typed01/expected/model_1_4_2_1.eprime new file mode 100644 index 0000000000..486abc3cff --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_4_2_1.eprime @@ -0,0 +1,18 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(1)] of bool +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +find y_Occurrence: matrix indexed by [int(1)] of bool +branching on + [x_ExplicitVarSizeWithDummy, x_Occurrence, y_Occurrence, y_ExplicitVarSizeWithFlags_Flags, + y_ExplicitVarSizeWithFlags_Values] +such that + x_Occurrence[1] /\ (y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = 1) -> false, + y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, + x_ExplicitVarSizeWithDummy[1] != 2 -> x_Occurrence[x_ExplicitVarSizeWithDummy[1]], + x_Occurrence[1] -> x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = 1, + y_Occurrence[1] -> y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = 1, + y_ExplicitVarSizeWithFlags_Flags[1] -> y_Occurrence[y_ExplicitVarSizeWithFlags_Values[1]] + diff --git a/tests/exhaustive/basic/typed01/expected/model_1_4_2_2-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_1_4_2_2-solution000001.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_4_2_2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_4_2_2-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_1_4_2_2-solution000002.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_4_2_2-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_4_2_2-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_1_4_2_2-solution000003.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_4_2_2-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_4_2_2.eprime b/tests/exhaustive/basic/typed01/expected/model_1_4_2_2.eprime new file mode 100644 index 0000000000..eb01c1c347 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_4_2_2.eprime @@ -0,0 +1,20 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(1)] of bool +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +branching on + [x_ExplicitVarSizeWithDummy, x_Occurrence, y_ExplicitVarSizeWithDummy, y_ExplicitVarSizeWithFlags_Flags, + y_ExplicitVarSizeWithFlags_Values] +such that + x_Occurrence[1] /\ (y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = 1) -> false, + y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, + x_ExplicitVarSizeWithDummy[1] != 2 -> x_Occurrence[x_ExplicitVarSizeWithDummy[1]], + x_Occurrence[1] -> x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = 1, + y_ExplicitVarSizeWithDummy[1] != 2 -> + y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = y_ExplicitVarSizeWithDummy[1], + y_ExplicitVarSizeWithFlags_Flags[1] -> + y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = y_ExplicitVarSizeWithFlags_Values[1] + diff --git a/tests/exhaustive/basic/typed01/expected/model_1_4_2_3-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_1_4_2_3-solution000001.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_4_2_3-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_4_2_3-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_1_4_2_3-solution000002.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_4_2_3-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_4_2_3-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_1_4_2_3-solution000003.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_4_2_3-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_4_2_3.eprime b/tests/exhaustive/basic/typed01/expected/model_1_4_2_3.eprime new file mode 100644 index 0000000000..b9db0c2490 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_4_2_3.eprime @@ -0,0 +1,23 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(1)] of bool +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +find y_ExplicitVarSizeWithMarker_Marker: int(0..1) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +branching on + [x_ExplicitVarSizeWithDummy, x_Occurrence, y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values, + y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values] +such that + x_Occurrence[1] /\ (y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = 1) -> false, + y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, + x_ExplicitVarSizeWithDummy[1] != 2 -> x_Occurrence[x_ExplicitVarSizeWithDummy[1]], + x_Occurrence[1] -> x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = 1, + 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, + 1 <= y_ExplicitVarSizeWithMarker_Marker -> + y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = y_ExplicitVarSizeWithMarker_Values[1], + y_ExplicitVarSizeWithFlags_Flags[1] -> + 1 <= y_ExplicitVarSizeWithMarker_Marker /\ + y_ExplicitVarSizeWithMarker_Values[1] = y_ExplicitVarSizeWithFlags_Values[1] + diff --git a/tests/exhaustive/basic/typed01/expected/model_1_4_2_4-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_1_4_2_4-solution000001.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_4_2_4-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_4_2_4-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_1_4_2_4-solution000002.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_4_2_4-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_4_2_4-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_1_4_2_4-solution000003.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_4_2_4-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_4_2_4.eprime b/tests/exhaustive/basic/typed01/expected/model_1_4_2_4.eprime new file mode 100644 index 0000000000..8dca479233 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_4_2_4.eprime @@ -0,0 +1,14 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(1)] of bool +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +branching on + [x_ExplicitVarSizeWithDummy, x_Occurrence, y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values] +such that + x_Occurrence[1] /\ (y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = 1) -> false, + y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, + x_ExplicitVarSizeWithDummy[1] != 2 -> x_Occurrence[x_ExplicitVarSizeWithDummy[1]], + x_Occurrence[1] -> x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = 1 + diff --git a/tests/exhaustive/basic/typed01/expected/model_1_4_3_1-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_1_4_3_1-solution000001.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_4_3_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_4_3_1-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_1_4_3_1-solution000002.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_4_3_1-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_4_3_1-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_1_4_3_1-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_4_3_1-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_4_3_1.eprime b/tests/exhaustive/basic/typed01/expected/model_1_4_3_1.eprime new file mode 100644 index 0000000000..46bbb31689 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_4_3_1.eprime @@ -0,0 +1,20 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(1)] of bool +find x_ExplicitVarSizeWithMarker_Marker: int(0..1) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +find y_Occurrence: matrix indexed by [int(1)] of bool +branching on + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_Occurrence, y_Occurrence, + y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values] +such that + x_Occurrence[1] /\ (y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = 1) -> false, + y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, + 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, + 1 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[1]], + x_Occurrence[1] -> 1 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[1] = 1, + y_Occurrence[1] -> y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = 1, + y_ExplicitVarSizeWithFlags_Flags[1] -> y_Occurrence[y_ExplicitVarSizeWithFlags_Values[1]] + diff --git a/tests/exhaustive/basic/typed01/expected/model_1_4_3_2-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_1_4_3_2-solution000001.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_4_3_2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_4_3_2-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_1_4_3_2-solution000002.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_4_3_2-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_4_3_2-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_1_4_3_2-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_4_3_2-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_4_3_2.eprime b/tests/exhaustive/basic/typed01/expected/model_1_4_3_2.eprime new file mode 100644 index 0000000000..d31a6fe728 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_4_3_2.eprime @@ -0,0 +1,22 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(1)] of bool +find x_ExplicitVarSizeWithMarker_Marker: int(0..1) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +branching on + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_Occurrence, y_ExplicitVarSizeWithDummy, + y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values] +such that + x_Occurrence[1] /\ (y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = 1) -> false, + y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, + 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, + 1 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[1]], + x_Occurrence[1] -> 1 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[1] = 1, + y_ExplicitVarSizeWithDummy[1] != 2 -> + y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = y_ExplicitVarSizeWithDummy[1], + y_ExplicitVarSizeWithFlags_Flags[1] -> + y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = y_ExplicitVarSizeWithFlags_Values[1] + diff --git a/tests/exhaustive/basic/typed01/expected/model_1_4_3_3-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_1_4_3_3-solution000001.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_4_3_3-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_4_3_3-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_1_4_3_3-solution000002.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_4_3_3-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_4_3_3-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_1_4_3_3-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_4_3_3-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_4_3_3.eprime b/tests/exhaustive/basic/typed01/expected/model_1_4_3_3.eprime new file mode 100644 index 0000000000..fc3f83dcff --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_4_3_3.eprime @@ -0,0 +1,26 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(1)] of bool +find x_ExplicitVarSizeWithMarker_Marker: int(0..1) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +find y_ExplicitVarSizeWithMarker_Marker: int(0..1) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +branching on + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_Occurrence, + y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithFlags_Flags, + y_ExplicitVarSizeWithFlags_Values] +such that + x_Occurrence[1] /\ (y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = 1) -> false, + y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, + 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, + 1 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[1]], + x_Occurrence[1] -> 1 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[1] = 1, + 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, + 1 <= y_ExplicitVarSizeWithMarker_Marker -> + y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = y_ExplicitVarSizeWithMarker_Values[1], + y_ExplicitVarSizeWithFlags_Flags[1] -> + 1 <= y_ExplicitVarSizeWithMarker_Marker /\ + y_ExplicitVarSizeWithMarker_Values[1] = y_ExplicitVarSizeWithFlags_Values[1] + diff --git a/tests/exhaustive/basic/typed01/expected/model_1_4_3_4-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_1_4_3_4-solution000001.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_4_3_4-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_4_3_4-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_1_4_3_4-solution000002.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_4_3_4-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_4_3_4-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_1_4_3_4-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_4_3_4-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_4_3_4.eprime b/tests/exhaustive/basic/typed01/expected/model_1_4_3_4.eprime new file mode 100644 index 0000000000..1ae9b4088c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_4_3_4.eprime @@ -0,0 +1,17 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(1)] of bool +find x_ExplicitVarSizeWithMarker_Marker: int(0..1) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +branching on + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_Occurrence, + y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values] +such that + x_Occurrence[1] /\ (y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = 1) -> false, + y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, + 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, + 1 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[1]], + x_Occurrence[1] -> 1 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[1] = 1 + diff --git a/tests/exhaustive/basic/typed01/expected/model_1_4_4_1-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_1_4_4_1-solution000001.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_4_4_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_4_4_1-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_1_4_4_1-solution000002.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_4_4_1-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_4_4_1-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_1_4_4_1-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_4_4_1-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_4_4_1.eprime b/tests/exhaustive/basic/typed01/expected/model_1_4_4_1.eprime new file mode 100644 index 0000000000..4b0a76d2ad --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_4_4_1.eprime @@ -0,0 +1,20 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(1)] of bool +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +find y_Occurrence: matrix indexed by [int(1)] of bool +branching on + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_Occurrence, y_Occurrence, + y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values] +such that + x_Occurrence[1] /\ (y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = 1) -> false, + y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, + x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, + x_ExplicitVarSizeWithFlags_Flags[1] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[1]], + x_Occurrence[1] -> x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = 1, + y_Occurrence[1] -> y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = 1, + y_ExplicitVarSizeWithFlags_Flags[1] -> y_Occurrence[y_ExplicitVarSizeWithFlags_Values[1]] + diff --git a/tests/exhaustive/basic/typed01/expected/model_1_4_4_2-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_1_4_4_2-solution000001.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_4_4_2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_4_4_2-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_1_4_4_2-solution000002.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_4_4_2-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_4_4_2-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_1_4_4_2-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_4_4_2-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_4_4_2.eprime b/tests/exhaustive/basic/typed01/expected/model_1_4_4_2.eprime new file mode 100644 index 0000000000..bc46971fe0 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_4_4_2.eprime @@ -0,0 +1,22 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(1)] of bool +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +branching on + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_Occurrence, y_ExplicitVarSizeWithDummy, + y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values] +such that + x_Occurrence[1] /\ (y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = 1) -> false, + y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, + x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, + x_ExplicitVarSizeWithFlags_Flags[1] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[1]], + x_Occurrence[1] -> x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = 1, + y_ExplicitVarSizeWithDummy[1] != 2 -> + y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = y_ExplicitVarSizeWithDummy[1], + y_ExplicitVarSizeWithFlags_Flags[1] -> + y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = y_ExplicitVarSizeWithFlags_Values[1] + diff --git a/tests/exhaustive/basic/typed01/expected/model_1_4_4_3-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_1_4_4_3-solution000001.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_4_4_3-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_4_4_3-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_1_4_4_3-solution000002.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_4_4_3-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_4_4_3-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_1_4_4_3-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_4_4_3-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_4_4_3.eprime b/tests/exhaustive/basic/typed01/expected/model_1_4_4_3.eprime new file mode 100644 index 0000000000..9245215595 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_4_4_3.eprime @@ -0,0 +1,26 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(1)] of bool +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +find y_ExplicitVarSizeWithMarker_Marker: int(0..1) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +branching on + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_Occurrence, + y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithFlags_Flags, + y_ExplicitVarSizeWithFlags_Values] +such that + x_Occurrence[1] /\ (y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = 1) -> false, + y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, + x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, + x_ExplicitVarSizeWithFlags_Flags[1] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[1]], + x_Occurrence[1] -> x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = 1, + 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, + 1 <= y_ExplicitVarSizeWithMarker_Marker -> + y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = y_ExplicitVarSizeWithMarker_Values[1], + y_ExplicitVarSizeWithFlags_Flags[1] -> + 1 <= y_ExplicitVarSizeWithMarker_Marker /\ + y_ExplicitVarSizeWithMarker_Values[1] = y_ExplicitVarSizeWithFlags_Values[1] + diff --git a/tests/exhaustive/basic/typed01/expected/model_1_4_4_4-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_1_4_4_4-solution000001.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_4_4_4-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_4_4_4-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_1_4_4_4-solution000002.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_4_4_4-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_4_4_4-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_1_4_4_4-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_4_4_4-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_1_4_4_4.eprime b/tests/exhaustive/basic/typed01/expected/model_1_4_4_4.eprime new file mode 100644 index 0000000000..cccfca44a7 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_1_4_4_4.eprime @@ -0,0 +1,17 @@ +language ESSENCE' 1.0 + +find x_Occurrence: matrix indexed by [int(1)] of bool +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +branching on + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_Occurrence, + y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values] +such that + x_Occurrence[1] /\ (y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = 1) -> false, + y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, + x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, + x_ExplicitVarSizeWithFlags_Flags[1] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[1]], + x_Occurrence[1] -> x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = 1 + diff --git a/tests/exhaustive/basic/typed01/expected/model_2_1_1_1-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_2_1_1_1-solution000001.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_1_1_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_1_1_1-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_2_1_1_1-solution000002.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_1_1_1-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_1_1_1-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_2_1_1_1-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_1_1_1-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_1_1_1.eprime b/tests/exhaustive/basic/typed01/expected/model_2_1_1_1.eprime new file mode 100644 index 0000000000..dea929fb85 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_1_1_1.eprime @@ -0,0 +1,11 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +find x_Occurrence: matrix indexed by [int(1)] of bool +find y_Occurrence: matrix indexed by [int(1)] of bool +branching on [x_Occurrence, x_ExplicitVarSizeWithDummy, y_Occurrence] +such that + x_ExplicitVarSizeWithDummy[1] != 2 /\ y_Occurrence[x_ExplicitVarSizeWithDummy[1]] -> false, + x_Occurrence[1] -> x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = 1, + x_ExplicitVarSizeWithDummy[1] != 2 -> x_Occurrence[x_ExplicitVarSizeWithDummy[1]] + diff --git a/tests/exhaustive/basic/typed01/expected/model_2_1_1_2-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_2_1_1_2-solution000001.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_1_1_2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_1_1_2-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_2_1_1_2-solution000002.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_1_1_2-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_1_1_2-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_2_1_1_2-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_1_1_2-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_1_1_2.eprime b/tests/exhaustive/basic/typed01/expected/model_2_1_1_2.eprime new file mode 100644 index 0000000000..1ebc638b04 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_1_1_2.eprime @@ -0,0 +1,14 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +find x_Occurrence: matrix indexed by [int(1)] of bool +find y_Occurrence: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +branching on [x_Occurrence, x_ExplicitVarSizeWithDummy, y_ExplicitVarSizeWithDummy, y_Occurrence] +such that + x_ExplicitVarSizeWithDummy[1] != 2 /\ y_Occurrence[x_ExplicitVarSizeWithDummy[1]] -> false, + x_Occurrence[1] -> x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = 1, + x_ExplicitVarSizeWithDummy[1] != 2 -> x_Occurrence[x_ExplicitVarSizeWithDummy[1]], + y_ExplicitVarSizeWithDummy[1] != 2 -> y_Occurrence[y_ExplicitVarSizeWithDummy[1]], + y_Occurrence[1] -> y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = 1 + diff --git a/tests/exhaustive/basic/typed01/expected/model_2_1_1_3-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_2_1_1_3-solution000001.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_1_1_3-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_1_1_3-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_2_1_1_3-solution000002.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_1_1_3-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_1_1_3-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_2_1_1_3-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_1_1_3-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_1_1_3.eprime b/tests/exhaustive/basic/typed01/expected/model_2_1_1_3.eprime new file mode 100644 index 0000000000..d367ac6332 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_1_1_3.eprime @@ -0,0 +1,18 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +find x_Occurrence: matrix indexed by [int(1)] of bool +find y_Occurrence: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithMarker_Marker: int(0..1) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +branching on + [x_Occurrence, x_ExplicitVarSizeWithDummy, y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values, + y_Occurrence] +such that + x_ExplicitVarSizeWithDummy[1] != 2 /\ y_Occurrence[x_ExplicitVarSizeWithDummy[1]] -> false, + x_Occurrence[1] -> x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = 1, + x_ExplicitVarSizeWithDummy[1] != 2 -> x_Occurrence[x_ExplicitVarSizeWithDummy[1]], + 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, + 1 <= y_ExplicitVarSizeWithMarker_Marker -> y_Occurrence[y_ExplicitVarSizeWithMarker_Values[1]], + y_Occurrence[1] -> 1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = 1 + diff --git a/tests/exhaustive/basic/typed01/expected/model_2_1_1_4-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_2_1_1_4-solution000001.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_1_1_4-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_1_1_4-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_2_1_1_4-solution000002.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_1_1_4-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_1_1_4-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_2_1_1_4-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_1_1_4-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_1_1_4.eprime b/tests/exhaustive/basic/typed01/expected/model_2_1_1_4.eprime new file mode 100644 index 0000000000..f956e74768 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_1_1_4.eprime @@ -0,0 +1,18 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +find x_Occurrence: matrix indexed by [int(1)] of bool +find y_Occurrence: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +branching on + [x_Occurrence, x_ExplicitVarSizeWithDummy, y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values, + y_Occurrence] +such that + x_ExplicitVarSizeWithDummy[1] != 2 /\ y_Occurrence[x_ExplicitVarSizeWithDummy[1]] -> false, + x_Occurrence[1] -> x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = 1, + x_ExplicitVarSizeWithDummy[1] != 2 -> x_Occurrence[x_ExplicitVarSizeWithDummy[1]], + y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, + y_ExplicitVarSizeWithFlags_Flags[1] -> y_Occurrence[y_ExplicitVarSizeWithFlags_Values[1]], + y_Occurrence[1] -> y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = 1 + diff --git a/tests/exhaustive/basic/typed01/expected/model_2_1_2_1-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_2_1_2_1-solution000001.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_1_2_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_1_2_1-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_2_1_2_1-solution000002.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_1_2_1-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_1_2_1-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_2_1_2_1-solution000003.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_1_2_1-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_1_2_1.eprime b/tests/exhaustive/basic/typed01/expected/model_2_1_2_1.eprime new file mode 100644 index 0000000000..b0c1489050 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_1_2_1.eprime @@ -0,0 +1,7 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +find y_Occurrence: matrix indexed by [int(1)] of bool +branching on [x_ExplicitVarSizeWithDummy, y_Occurrence] +such that x_ExplicitVarSizeWithDummy[1] != 2 /\ y_Occurrence[x_ExplicitVarSizeWithDummy[1]] -> false + diff --git a/tests/exhaustive/basic/typed01/expected/model_2_1_2_2-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_2_1_2_2-solution000001.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_1_2_2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_1_2_2-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_2_1_2_2-solution000002.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_1_2_2-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_1_2_2-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_2_1_2_2-solution000003.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_1_2_2-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_1_2_2.eprime b/tests/exhaustive/basic/typed01/expected/model_2_1_2_2.eprime new file mode 100644 index 0000000000..0715504126 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_1_2_2.eprime @@ -0,0 +1,11 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +find y_Occurrence: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +branching on [x_ExplicitVarSizeWithDummy, y_ExplicitVarSizeWithDummy, y_Occurrence] +such that + x_ExplicitVarSizeWithDummy[1] != 2 /\ y_Occurrence[x_ExplicitVarSizeWithDummy[1]] -> false, + y_ExplicitVarSizeWithDummy[1] != 2 -> y_Occurrence[y_ExplicitVarSizeWithDummy[1]], + y_Occurrence[1] -> y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = 1 + diff --git a/tests/exhaustive/basic/typed01/expected/model_2_1_2_3-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_2_1_2_3-solution000001.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_1_2_3-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_1_2_3-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_2_1_2_3-solution000002.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_1_2_3-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_1_2_3-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_2_1_2_3-solution000003.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_1_2_3-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_1_2_3.eprime b/tests/exhaustive/basic/typed01/expected/model_2_1_2_3.eprime new file mode 100644 index 0000000000..0e5b347379 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_1_2_3.eprime @@ -0,0 +1,14 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +find y_Occurrence: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithMarker_Marker: int(0..1) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +branching on + [x_ExplicitVarSizeWithDummy, y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values, y_Occurrence] +such that + x_ExplicitVarSizeWithDummy[1] != 2 /\ y_Occurrence[x_ExplicitVarSizeWithDummy[1]] -> false, + 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, + 1 <= y_ExplicitVarSizeWithMarker_Marker -> y_Occurrence[y_ExplicitVarSizeWithMarker_Values[1]], + y_Occurrence[1] -> 1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = 1 + diff --git a/tests/exhaustive/basic/typed01/expected/model_2_1_2_4-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_2_1_2_4-solution000001.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_1_2_4-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_1_2_4-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_2_1_2_4-solution000002.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_1_2_4-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_1_2_4-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_2_1_2_4-solution000003.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_1_2_4-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_1_2_4.eprime b/tests/exhaustive/basic/typed01/expected/model_2_1_2_4.eprime new file mode 100644 index 0000000000..92c235b315 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_1_2_4.eprime @@ -0,0 +1,14 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +find y_Occurrence: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +branching on + [x_ExplicitVarSizeWithDummy, y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values, y_Occurrence] +such that + x_ExplicitVarSizeWithDummy[1] != 2 /\ y_Occurrence[x_ExplicitVarSizeWithDummy[1]] -> false, + y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, + y_ExplicitVarSizeWithFlags_Flags[1] -> y_Occurrence[y_ExplicitVarSizeWithFlags_Values[1]], + y_Occurrence[1] -> y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = 1 + diff --git a/tests/exhaustive/basic/typed01/expected/model_2_1_3_1-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_2_1_3_1-solution000001.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_1_3_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_1_3_1-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_2_1_3_1-solution000002.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_1_3_1-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_1_3_1-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_2_1_3_1-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_1_3_1-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_1_3_1.eprime b/tests/exhaustive/basic/typed01/expected/model_2_1_3_1.eprime new file mode 100644 index 0000000000..5b9e809311 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_1_3_1.eprime @@ -0,0 +1,16 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +find x_ExplicitVarSizeWithMarker_Marker: int(0..1) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +find y_Occurrence: matrix indexed by [int(1)] of bool +branching on + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy, y_Occurrence] +such that + x_ExplicitVarSizeWithDummy[1] != 2 /\ y_Occurrence[x_ExplicitVarSizeWithDummy[1]] -> false, + 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithMarker_Values[1], + x_ExplicitVarSizeWithDummy[1] != 2 -> + 1 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithDummy[1] + diff --git a/tests/exhaustive/basic/typed01/expected/model_2_1_3_2-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_2_1_3_2-solution000001.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_1_3_2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_1_3_2-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_2_1_3_2-solution000002.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_1_3_2-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_1_3_2-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_2_1_3_2-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_1_3_2-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_1_3_2.eprime b/tests/exhaustive/basic/typed01/expected/model_2_1_3_2.eprime new file mode 100644 index 0000000000..82f4c5b4a8 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_1_3_2.eprime @@ -0,0 +1,20 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +find x_ExplicitVarSizeWithMarker_Marker: int(0..1) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +find y_Occurrence: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +branching on + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy, + y_ExplicitVarSizeWithDummy, y_Occurrence] +such that + x_ExplicitVarSizeWithDummy[1] != 2 /\ y_Occurrence[x_ExplicitVarSizeWithDummy[1]] -> false, + 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithMarker_Values[1], + x_ExplicitVarSizeWithDummy[1] != 2 -> + 1 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithDummy[1], + y_ExplicitVarSizeWithDummy[1] != 2 -> y_Occurrence[y_ExplicitVarSizeWithDummy[1]], + y_Occurrence[1] -> y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = 1 + diff --git a/tests/exhaustive/basic/typed01/expected/model_2_1_3_3-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_2_1_3_3-solution000001.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_1_3_3-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_1_3_3-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_2_1_3_3-solution000002.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_1_3_3-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_1_3_3-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_2_1_3_3-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_1_3_3-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_1_3_3.eprime b/tests/exhaustive/basic/typed01/expected/model_2_1_3_3.eprime new file mode 100644 index 0000000000..97a807ab7e --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_1_3_3.eprime @@ -0,0 +1,22 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +find x_ExplicitVarSizeWithMarker_Marker: int(0..1) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +find y_Occurrence: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithMarker_Marker: int(0..1) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +branching on + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy, + y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values, y_Occurrence] +such that + x_ExplicitVarSizeWithDummy[1] != 2 /\ y_Occurrence[x_ExplicitVarSizeWithDummy[1]] -> false, + 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithMarker_Values[1], + x_ExplicitVarSizeWithDummy[1] != 2 -> + 1 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithDummy[1], + 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, + 1 <= y_ExplicitVarSizeWithMarker_Marker -> y_Occurrence[y_ExplicitVarSizeWithMarker_Values[1]], + y_Occurrence[1] -> 1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = 1 + diff --git a/tests/exhaustive/basic/typed01/expected/model_2_1_3_4-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_2_1_3_4-solution000001.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_1_3_4-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_1_3_4-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_2_1_3_4-solution000002.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_1_3_4-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_1_3_4-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_2_1_3_4-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_1_3_4-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_1_3_4.eprime b/tests/exhaustive/basic/typed01/expected/model_2_1_3_4.eprime new file mode 100644 index 0000000000..643e77b708 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_1_3_4.eprime @@ -0,0 +1,22 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +find x_ExplicitVarSizeWithMarker_Marker: int(0..1) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +find y_Occurrence: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +branching on + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy, + y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values, y_Occurrence] +such that + x_ExplicitVarSizeWithDummy[1] != 2 /\ y_Occurrence[x_ExplicitVarSizeWithDummy[1]] -> false, + 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithMarker_Values[1], + x_ExplicitVarSizeWithDummy[1] != 2 -> + 1 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithDummy[1], + y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, + y_ExplicitVarSizeWithFlags_Flags[1] -> y_Occurrence[y_ExplicitVarSizeWithFlags_Values[1]], + y_Occurrence[1] -> y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = 1 + diff --git a/tests/exhaustive/basic/typed01/expected/model_2_1_4_1-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_2_1_4_1-solution000001.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_1_4_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_1_4_1-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_2_1_4_1-solution000002.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_1_4_1-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_1_4_1-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_2_1_4_1-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_1_4_1-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_1_4_1.eprime b/tests/exhaustive/basic/typed01/expected/model_2_1_4_1.eprime new file mode 100644 index 0000000000..9824eb9893 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_1_4_1.eprime @@ -0,0 +1,16 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +find y_Occurrence: matrix indexed by [int(1)] of bool +branching on + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy, y_Occurrence] +such that + x_ExplicitVarSizeWithDummy[1] != 2 /\ y_Occurrence[x_ExplicitVarSizeWithDummy[1]] -> false, + x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, + x_ExplicitVarSizeWithFlags_Flags[1] -> + x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithFlags_Values[1], + x_ExplicitVarSizeWithDummy[1] != 2 -> + x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithDummy[1] + diff --git a/tests/exhaustive/basic/typed01/expected/model_2_1_4_2-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_2_1_4_2-solution000001.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_1_4_2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_1_4_2-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_2_1_4_2-solution000002.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_1_4_2-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_1_4_2-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_2_1_4_2-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_1_4_2-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_1_4_2.eprime b/tests/exhaustive/basic/typed01/expected/model_2_1_4_2.eprime new file mode 100644 index 0000000000..435aee6b41 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_1_4_2.eprime @@ -0,0 +1,20 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +find y_Occurrence: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +branching on + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy, + y_ExplicitVarSizeWithDummy, y_Occurrence] +such that + x_ExplicitVarSizeWithDummy[1] != 2 /\ y_Occurrence[x_ExplicitVarSizeWithDummy[1]] -> false, + x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, + x_ExplicitVarSizeWithFlags_Flags[1] -> + x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithFlags_Values[1], + x_ExplicitVarSizeWithDummy[1] != 2 -> + x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithDummy[1], + y_ExplicitVarSizeWithDummy[1] != 2 -> y_Occurrence[y_ExplicitVarSizeWithDummy[1]], + y_Occurrence[1] -> y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = 1 + diff --git a/tests/exhaustive/basic/typed01/expected/model_2_1_4_3-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_2_1_4_3-solution000001.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_1_4_3-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_1_4_3-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_2_1_4_3-solution000002.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_1_4_3-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_1_4_3-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_2_1_4_3-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_1_4_3-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_1_4_3.eprime b/tests/exhaustive/basic/typed01/expected/model_2_1_4_3.eprime new file mode 100644 index 0000000000..bc6ee32138 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_1_4_3.eprime @@ -0,0 +1,22 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +find y_Occurrence: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithMarker_Marker: int(0..1) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +branching on + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy, + y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values, y_Occurrence] +such that + x_ExplicitVarSizeWithDummy[1] != 2 /\ y_Occurrence[x_ExplicitVarSizeWithDummy[1]] -> false, + x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, + x_ExplicitVarSizeWithFlags_Flags[1] -> + x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithFlags_Values[1], + x_ExplicitVarSizeWithDummy[1] != 2 -> + x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithDummy[1], + 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, + 1 <= y_ExplicitVarSizeWithMarker_Marker -> y_Occurrence[y_ExplicitVarSizeWithMarker_Values[1]], + y_Occurrence[1] -> 1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = 1 + diff --git a/tests/exhaustive/basic/typed01/expected/model_2_1_4_4-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_2_1_4_4-solution000001.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_1_4_4-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_1_4_4-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_2_1_4_4-solution000002.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_1_4_4-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_1_4_4-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_2_1_4_4-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_1_4_4-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_1_4_4.eprime b/tests/exhaustive/basic/typed01/expected/model_2_1_4_4.eprime new file mode 100644 index 0000000000..17f79cea52 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_1_4_4.eprime @@ -0,0 +1,22 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +find y_Occurrence: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +branching on + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy, + y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values, y_Occurrence] +such that + x_ExplicitVarSizeWithDummy[1] != 2 /\ y_Occurrence[x_ExplicitVarSizeWithDummy[1]] -> false, + x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, + x_ExplicitVarSizeWithFlags_Flags[1] -> + x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithFlags_Values[1], + x_ExplicitVarSizeWithDummy[1] != 2 -> + x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithDummy[1], + y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, + y_ExplicitVarSizeWithFlags_Flags[1] -> y_Occurrence[y_ExplicitVarSizeWithFlags_Values[1]], + y_Occurrence[1] -> y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = 1 + diff --git a/tests/exhaustive/basic/typed01/expected/model_2_2_1_1-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_2_2_1_1-solution000001.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_2_1_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_2_1_1-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_2_2_1_1-solution000002.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_2_1_1-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_2_1_1-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_2_2_1_1-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_2_1_1-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_2_1_1.eprime b/tests/exhaustive/basic/typed01/expected/model_2_2_1_1.eprime new file mode 100644 index 0000000000..55ea4f98eb --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_2_1_1.eprime @@ -0,0 +1,16 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +find x_Occurrence: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +find y_Occurrence: matrix indexed by [int(1)] of bool +branching on [x_Occurrence, x_ExplicitVarSizeWithDummy, y_Occurrence, y_ExplicitVarSizeWithDummy] +such that + x_ExplicitVarSizeWithDummy[1] != 2 /\ + (y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithDummy[1]) + -> false, + x_Occurrence[1] -> x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = 1, + x_ExplicitVarSizeWithDummy[1] != 2 -> x_Occurrence[x_ExplicitVarSizeWithDummy[1]], + y_Occurrence[1] -> y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = 1, + y_ExplicitVarSizeWithDummy[1] != 2 -> y_Occurrence[y_ExplicitVarSizeWithDummy[1]] + diff --git a/tests/exhaustive/basic/typed01/expected/model_2_2_1_2-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_2_2_1_2-solution000001.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_2_1_2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_2_1_2-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_2_2_1_2-solution000002.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_2_1_2-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_2_1_2-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_2_2_1_2-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_2_1_2-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_2_1_2.eprime b/tests/exhaustive/basic/typed01/expected/model_2_2_1_2.eprime new file mode 100644 index 0000000000..25e38b0597 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_2_1_2.eprime @@ -0,0 +1,13 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +find x_Occurrence: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +branching on [x_Occurrence, x_ExplicitVarSizeWithDummy, y_ExplicitVarSizeWithDummy] +such that + x_ExplicitVarSizeWithDummy[1] != 2 /\ + (y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithDummy[1]) + -> false, + x_Occurrence[1] -> x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = 1, + x_ExplicitVarSizeWithDummy[1] != 2 -> x_Occurrence[x_ExplicitVarSizeWithDummy[1]] + diff --git a/tests/exhaustive/basic/typed01/expected/model_2_2_1_3-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_2_2_1_3-solution000001.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_2_1_3-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_2_1_3-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_2_2_1_3-solution000002.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_2_1_3-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_2_1_3-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_2_2_1_3-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_2_1_3-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_2_1_3.eprime b/tests/exhaustive/basic/typed01/expected/model_2_2_1_3.eprime new file mode 100644 index 0000000000..dfe0d93806 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_2_1_3.eprime @@ -0,0 +1,22 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +find x_Occurrence: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +find y_ExplicitVarSizeWithMarker_Marker: int(0..1) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +branching on + [x_Occurrence, x_ExplicitVarSizeWithDummy, y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values, + y_ExplicitVarSizeWithDummy] +such that + x_ExplicitVarSizeWithDummy[1] != 2 /\ + (y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithDummy[1]) + -> false, + x_Occurrence[1] -> x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = 1, + x_ExplicitVarSizeWithDummy[1] != 2 -> x_Occurrence[x_ExplicitVarSizeWithDummy[1]], + 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, + 1 <= y_ExplicitVarSizeWithMarker_Marker -> + y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = y_ExplicitVarSizeWithMarker_Values[1], + y_ExplicitVarSizeWithDummy[1] != 2 -> + 1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = y_ExplicitVarSizeWithDummy[1] + diff --git a/tests/exhaustive/basic/typed01/expected/model_2_2_1_4-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_2_2_1_4-solution000001.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_2_1_4-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_2_1_4-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_2_2_1_4-solution000002.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_2_1_4-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_2_1_4-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_2_2_1_4-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_2_1_4-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_2_1_4.eprime b/tests/exhaustive/basic/typed01/expected/model_2_2_1_4.eprime new file mode 100644 index 0000000000..53929d788b --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_2_1_4.eprime @@ -0,0 +1,22 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +find x_Occurrence: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +branching on + [x_Occurrence, x_ExplicitVarSizeWithDummy, y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values, + y_ExplicitVarSizeWithDummy] +such that + x_ExplicitVarSizeWithDummy[1] != 2 /\ + (y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithDummy[1]) + -> false, + x_Occurrence[1] -> x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = 1, + x_ExplicitVarSizeWithDummy[1] != 2 -> x_Occurrence[x_ExplicitVarSizeWithDummy[1]], + y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, + y_ExplicitVarSizeWithFlags_Flags[1] -> + y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = y_ExplicitVarSizeWithFlags_Values[1], + y_ExplicitVarSizeWithDummy[1] != 2 -> + y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = y_ExplicitVarSizeWithDummy[1] + diff --git a/tests/exhaustive/basic/typed01/expected/model_2_2_2_1-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_2_2_2_1-solution000001.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_2_2_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_2_2_1-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_2_2_2_1-solution000002.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_2_2_1-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_2_2_1-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_2_2_2_1-solution000003.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_2_2_1-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_2_2_1.eprime b/tests/exhaustive/basic/typed01/expected/model_2_2_2_1.eprime new file mode 100644 index 0000000000..d7c4512020 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_2_2_1.eprime @@ -0,0 +1,13 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +find y_Occurrence: matrix indexed by [int(1)] of bool +branching on [x_ExplicitVarSizeWithDummy, y_Occurrence, y_ExplicitVarSizeWithDummy] +such that + x_ExplicitVarSizeWithDummy[1] != 2 /\ + (y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithDummy[1]) + -> false, + y_Occurrence[1] -> y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = 1, + y_ExplicitVarSizeWithDummy[1] != 2 -> y_Occurrence[y_ExplicitVarSizeWithDummy[1]] + diff --git a/tests/exhaustive/basic/typed01/expected/model_2_2_2_2-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_2_2_2_2-solution000001.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_2_2_2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_2_2_2-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_2_2_2_2-solution000002.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_2_2_2-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_2_2_2-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_2_2_2_2-solution000003.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_2_2_2-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_2_2_2.eprime b/tests/exhaustive/basic/typed01/expected/model_2_2_2_2.eprime new file mode 100644 index 0000000000..e0ffb03b92 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_2_2_2.eprime @@ -0,0 +1,10 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +branching on [x_ExplicitVarSizeWithDummy, y_ExplicitVarSizeWithDummy] +such that + x_ExplicitVarSizeWithDummy[1] != 2 /\ + (y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithDummy[1]) + -> false + diff --git a/tests/exhaustive/basic/typed01/expected/model_2_2_2_3-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_2_2_2_3-solution000001.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_2_2_3-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_2_2_3-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_2_2_2_3-solution000002.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_2_2_3-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_2_2_3-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_2_2_2_3-solution000003.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_2_2_3-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_2_2_3.eprime b/tests/exhaustive/basic/typed01/expected/model_2_2_2_3.eprime new file mode 100644 index 0000000000..f7ad4f3285 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_2_2_3.eprime @@ -0,0 +1,19 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +find y_ExplicitVarSizeWithMarker_Marker: int(0..1) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +branching on + [x_ExplicitVarSizeWithDummy, y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values, + y_ExplicitVarSizeWithDummy] +such that + x_ExplicitVarSizeWithDummy[1] != 2 /\ + (y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithDummy[1]) + -> false, + 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, + 1 <= y_ExplicitVarSizeWithMarker_Marker -> + y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = y_ExplicitVarSizeWithMarker_Values[1], + y_ExplicitVarSizeWithDummy[1] != 2 -> + 1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = y_ExplicitVarSizeWithDummy[1] + diff --git a/tests/exhaustive/basic/typed01/expected/model_2_2_2_4-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_2_2_2_4-solution000001.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_2_2_4-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_2_2_4-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_2_2_2_4-solution000002.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_2_2_4-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_2_2_4-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_2_2_2_4-solution000003.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_2_2_4-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_2_2_4.eprime b/tests/exhaustive/basic/typed01/expected/model_2_2_2_4.eprime new file mode 100644 index 0000000000..c471760f6e --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_2_2_4.eprime @@ -0,0 +1,19 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +branching on + [x_ExplicitVarSizeWithDummy, y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values, + y_ExplicitVarSizeWithDummy] +such that + x_ExplicitVarSizeWithDummy[1] != 2 /\ + (y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithDummy[1]) + -> false, + y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, + y_ExplicitVarSizeWithFlags_Flags[1] -> + y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = y_ExplicitVarSizeWithFlags_Values[1], + y_ExplicitVarSizeWithDummy[1] != 2 -> + y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = y_ExplicitVarSizeWithDummy[1] + diff --git a/tests/exhaustive/basic/typed01/expected/model_2_2_3_1-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_2_2_3_1-solution000001.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_2_3_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_2_3_1-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_2_2_3_1-solution000002.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_2_3_1-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_2_3_1-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_2_2_3_1-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_2_3_1-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_2_3_1.eprime b/tests/exhaustive/basic/typed01/expected/model_2_2_3_1.eprime new file mode 100644 index 0000000000..222d83cfca --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_2_3_1.eprime @@ -0,0 +1,22 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +find x_ExplicitVarSizeWithMarker_Marker: int(0..1) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +find y_Occurrence: matrix indexed by [int(1)] of bool +branching on + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy, y_Occurrence, + y_ExplicitVarSizeWithDummy] +such that + x_ExplicitVarSizeWithDummy[1] != 2 /\ + (y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithDummy[1]) + -> false, + 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithMarker_Values[1], + x_ExplicitVarSizeWithDummy[1] != 2 -> + 1 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithDummy[1], + y_Occurrence[1] -> y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = 1, + y_ExplicitVarSizeWithDummy[1] != 2 -> y_Occurrence[y_ExplicitVarSizeWithDummy[1]] + diff --git a/tests/exhaustive/basic/typed01/expected/model_2_2_3_2-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_2_2_3_2-solution000001.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_2_3_2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_2_3_2-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_2_2_3_2-solution000002.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_2_3_2-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_2_3_2-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_2_2_3_2-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_2_3_2-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_2_3_2.eprime b/tests/exhaustive/basic/typed01/expected/model_2_2_3_2.eprime new file mode 100644 index 0000000000..e9e1de7881 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_2_3_2.eprime @@ -0,0 +1,19 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +find x_ExplicitVarSizeWithMarker_Marker: int(0..1) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +branching on + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy, + y_ExplicitVarSizeWithDummy] +such that + x_ExplicitVarSizeWithDummy[1] != 2 /\ + (y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithDummy[1]) + -> false, + 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithMarker_Values[1], + x_ExplicitVarSizeWithDummy[1] != 2 -> + 1 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithDummy[1] + diff --git a/tests/exhaustive/basic/typed01/expected/model_2_2_3_3-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_2_2_3_3-solution000001.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_2_3_3-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_2_3_3-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_2_2_3_3-solution000002.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_2_3_3-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_2_3_3-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_2_2_3_3-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_2_3_3-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_2_3_3.eprime b/tests/exhaustive/basic/typed01/expected/model_2_2_3_3.eprime new file mode 100644 index 0000000000..648595c344 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_2_3_3.eprime @@ -0,0 +1,26 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +find x_ExplicitVarSizeWithMarker_Marker: int(0..1) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +find y_ExplicitVarSizeWithMarker_Marker: int(0..1) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +branching on + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy, + y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithDummy] +such that + x_ExplicitVarSizeWithDummy[1] != 2 /\ + (y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithDummy[1]) + -> false, + 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithMarker_Values[1], + x_ExplicitVarSizeWithDummy[1] != 2 -> + 1 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithDummy[1], + 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, + 1 <= y_ExplicitVarSizeWithMarker_Marker -> + y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = y_ExplicitVarSizeWithMarker_Values[1], + y_ExplicitVarSizeWithDummy[1] != 2 -> + 1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = y_ExplicitVarSizeWithDummy[1] + diff --git a/tests/exhaustive/basic/typed01/expected/model_2_2_3_4-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_2_2_3_4-solution000001.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_2_3_4-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_2_3_4-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_2_2_3_4-solution000002.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_2_3_4-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_2_3_4-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_2_2_3_4-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_2_3_4-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_2_3_4.eprime b/tests/exhaustive/basic/typed01/expected/model_2_2_3_4.eprime new file mode 100644 index 0000000000..e35ba1bf82 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_2_3_4.eprime @@ -0,0 +1,26 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +find x_ExplicitVarSizeWithMarker_Marker: int(0..1) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +branching on + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy, + y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithDummy] +such that + x_ExplicitVarSizeWithDummy[1] != 2 /\ + (y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithDummy[1]) + -> false, + 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithMarker_Values[1], + x_ExplicitVarSizeWithDummy[1] != 2 -> + 1 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithDummy[1], + y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, + y_ExplicitVarSizeWithFlags_Flags[1] -> + y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = y_ExplicitVarSizeWithFlags_Values[1], + y_ExplicitVarSizeWithDummy[1] != 2 -> + y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = y_ExplicitVarSizeWithDummy[1] + diff --git a/tests/exhaustive/basic/typed01/expected/model_2_2_4_1-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_2_2_4_1-solution000001.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_2_4_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_2_4_1-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_2_2_4_1-solution000002.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_2_4_1-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_2_4_1-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_2_2_4_1-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_2_4_1-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_2_4_1.eprime b/tests/exhaustive/basic/typed01/expected/model_2_2_4_1.eprime new file mode 100644 index 0000000000..5d354a1f60 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_2_4_1.eprime @@ -0,0 +1,22 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +find y_Occurrence: matrix indexed by [int(1)] of bool +branching on + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy, y_Occurrence, + y_ExplicitVarSizeWithDummy] +such that + x_ExplicitVarSizeWithDummy[1] != 2 /\ + (y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithDummy[1]) + -> false, + x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, + x_ExplicitVarSizeWithFlags_Flags[1] -> + x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithFlags_Values[1], + x_ExplicitVarSizeWithDummy[1] != 2 -> + x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithDummy[1], + y_Occurrence[1] -> y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = 1, + y_ExplicitVarSizeWithDummy[1] != 2 -> y_Occurrence[y_ExplicitVarSizeWithDummy[1]] + diff --git a/tests/exhaustive/basic/typed01/expected/model_2_2_4_2-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_2_2_4_2-solution000001.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_2_4_2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_2_4_2-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_2_2_4_2-solution000002.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_2_4_2-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_2_4_2-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_2_2_4_2-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_2_4_2-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_2_4_2.eprime b/tests/exhaustive/basic/typed01/expected/model_2_2_4_2.eprime new file mode 100644 index 0000000000..89bf10880d --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_2_4_2.eprime @@ -0,0 +1,19 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +branching on + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy, + y_ExplicitVarSizeWithDummy] +such that + x_ExplicitVarSizeWithDummy[1] != 2 /\ + (y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithDummy[1]) + -> false, + x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, + x_ExplicitVarSizeWithFlags_Flags[1] -> + x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithFlags_Values[1], + x_ExplicitVarSizeWithDummy[1] != 2 -> + x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithDummy[1] + diff --git a/tests/exhaustive/basic/typed01/expected/model_2_2_4_3-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_2_2_4_3-solution000001.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_2_4_3-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_2_4_3-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_2_2_4_3-solution000002.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_2_4_3-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_2_4_3-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_2_2_4_3-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_2_4_3-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_2_4_3.eprime b/tests/exhaustive/basic/typed01/expected/model_2_2_4_3.eprime new file mode 100644 index 0000000000..9fa68409e3 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_2_4_3.eprime @@ -0,0 +1,26 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +find y_ExplicitVarSizeWithMarker_Marker: int(0..1) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +branching on + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy, + y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithDummy] +such that + x_ExplicitVarSizeWithDummy[1] != 2 /\ + (y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithDummy[1]) + -> false, + x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, + x_ExplicitVarSizeWithFlags_Flags[1] -> + x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithFlags_Values[1], + x_ExplicitVarSizeWithDummy[1] != 2 -> + x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithDummy[1], + 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, + 1 <= y_ExplicitVarSizeWithMarker_Marker -> + y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = y_ExplicitVarSizeWithMarker_Values[1], + y_ExplicitVarSizeWithDummy[1] != 2 -> + 1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = y_ExplicitVarSizeWithDummy[1] + diff --git a/tests/exhaustive/basic/typed01/expected/model_2_2_4_4-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_2_2_4_4-solution000001.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_2_4_4-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_2_4_4-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_2_2_4_4-solution000002.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_2_4_4-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_2_4_4-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_2_2_4_4-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_2_4_4-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_2_4_4.eprime b/tests/exhaustive/basic/typed01/expected/model_2_2_4_4.eprime new file mode 100644 index 0000000000..f394d4106f --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_2_4_4.eprime @@ -0,0 +1,26 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +branching on + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy, + y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithDummy] +such that + x_ExplicitVarSizeWithDummy[1] != 2 /\ + (y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithDummy[1]) + -> false, + x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, + x_ExplicitVarSizeWithFlags_Flags[1] -> + x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithFlags_Values[1], + x_ExplicitVarSizeWithDummy[1] != 2 -> + x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithDummy[1], + y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, + y_ExplicitVarSizeWithFlags_Flags[1] -> + y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = y_ExplicitVarSizeWithFlags_Values[1], + y_ExplicitVarSizeWithDummy[1] != 2 -> + y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = y_ExplicitVarSizeWithDummy[1] + diff --git a/tests/exhaustive/basic/typed01/expected/model_2_3_1_1-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_2_3_1_1-solution000001.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_3_1_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_3_1_1-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_2_3_1_1-solution000002.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_3_1_1-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_3_1_1-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_2_3_1_1-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_3_1_1-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_3_1_1.eprime b/tests/exhaustive/basic/typed01/expected/model_2_3_1_1.eprime new file mode 100644 index 0000000000..9bd40c6627 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_3_1_1.eprime @@ -0,0 +1,20 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +find x_Occurrence: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithMarker_Marker: int(0..1) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +find y_Occurrence: matrix indexed by [int(1)] of bool +branching on + [x_Occurrence, x_ExplicitVarSizeWithDummy, y_Occurrence, y_ExplicitVarSizeWithMarker_Marker, + y_ExplicitVarSizeWithMarker_Values] +such that + x_ExplicitVarSizeWithDummy[1] != 2 /\ + (1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithDummy[1]) + -> false, + 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, + x_Occurrence[1] -> x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = 1, + x_ExplicitVarSizeWithDummy[1] != 2 -> x_Occurrence[x_ExplicitVarSizeWithDummy[1]], + y_Occurrence[1] -> 1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = 1, + 1 <= y_ExplicitVarSizeWithMarker_Marker -> y_Occurrence[y_ExplicitVarSizeWithMarker_Values[1]] + diff --git a/tests/exhaustive/basic/typed01/expected/model_2_3_1_2-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_2_3_1_2-solution000001.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_3_1_2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_3_1_2-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_2_3_1_2-solution000002.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_3_1_2-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_3_1_2-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_2_3_1_2-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_3_1_2-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_3_1_2.eprime b/tests/exhaustive/basic/typed01/expected/model_2_3_1_2.eprime new file mode 100644 index 0000000000..04ab19eb01 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_3_1_2.eprime @@ -0,0 +1,22 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +find x_Occurrence: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithMarker_Marker: int(0..1) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +branching on + [x_Occurrence, x_ExplicitVarSizeWithDummy, y_ExplicitVarSizeWithDummy, y_ExplicitVarSizeWithMarker_Marker, + y_ExplicitVarSizeWithMarker_Values] +such that + x_ExplicitVarSizeWithDummy[1] != 2 /\ + (1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithDummy[1]) + -> false, + 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, + x_Occurrence[1] -> x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = 1, + x_ExplicitVarSizeWithDummy[1] != 2 -> x_Occurrence[x_ExplicitVarSizeWithDummy[1]], + y_ExplicitVarSizeWithDummy[1] != 2 -> + 1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = y_ExplicitVarSizeWithDummy[1], + 1 <= y_ExplicitVarSizeWithMarker_Marker -> + y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = y_ExplicitVarSizeWithMarker_Values[1] + diff --git a/tests/exhaustive/basic/typed01/expected/model_2_3_1_3-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_2_3_1_3-solution000001.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_3_1_3-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_3_1_3-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_2_3_1_3-solution000002.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_3_1_3-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_3_1_3-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_2_3_1_3-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_3_1_3-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_3_1_3.eprime b/tests/exhaustive/basic/typed01/expected/model_2_3_1_3.eprime new file mode 100644 index 0000000000..f62ac8ebf8 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_3_1_3.eprime @@ -0,0 +1,16 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +find x_Occurrence: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithMarker_Marker: int(0..1) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +branching on + [x_Occurrence, x_ExplicitVarSizeWithDummy, y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values] +such that + x_ExplicitVarSizeWithDummy[1] != 2 /\ + (1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithDummy[1]) + -> false, + 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, + x_Occurrence[1] -> x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = 1, + x_ExplicitVarSizeWithDummy[1] != 2 -> x_Occurrence[x_ExplicitVarSizeWithDummy[1]] + diff --git a/tests/exhaustive/basic/typed01/expected/model_2_3_1_4-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_2_3_1_4-solution000001.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_3_1_4-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_3_1_4-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_2_3_1_4-solution000002.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_3_1_4-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_3_1_4-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_2_3_1_4-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_3_1_4-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_3_1_4.eprime b/tests/exhaustive/basic/typed01/expected/model_2_3_1_4.eprime new file mode 100644 index 0000000000..433e7e48da --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_3_1_4.eprime @@ -0,0 +1,25 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +find x_Occurrence: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithMarker_Marker: int(0..1) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +branching on + [x_Occurrence, x_ExplicitVarSizeWithDummy, y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values, + y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values] +such that + x_ExplicitVarSizeWithDummy[1] != 2 /\ + (1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithDummy[1]) + -> false, + 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, + x_Occurrence[1] -> x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = 1, + x_ExplicitVarSizeWithDummy[1] != 2 -> x_Occurrence[x_ExplicitVarSizeWithDummy[1]], + y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, + y_ExplicitVarSizeWithFlags_Flags[1] -> + 1 <= y_ExplicitVarSizeWithMarker_Marker /\ + y_ExplicitVarSizeWithMarker_Values[1] = y_ExplicitVarSizeWithFlags_Values[1], + 1 <= y_ExplicitVarSizeWithMarker_Marker -> + y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = y_ExplicitVarSizeWithMarker_Values[1] + diff --git a/tests/exhaustive/basic/typed01/expected/model_2_3_2_1-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_2_3_2_1-solution000001.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_3_2_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_3_2_1-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_2_3_2_1-solution000002.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_3_2_1-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_3_2_1-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_2_3_2_1-solution000003.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_3_2_1-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_3_2_1.eprime b/tests/exhaustive/basic/typed01/expected/model_2_3_2_1.eprime new file mode 100644 index 0000000000..c501d3da77 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_3_2_1.eprime @@ -0,0 +1,16 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +find y_ExplicitVarSizeWithMarker_Marker: int(0..1) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +find y_Occurrence: matrix indexed by [int(1)] of bool +branching on + [x_ExplicitVarSizeWithDummy, y_Occurrence, y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values] +such that + x_ExplicitVarSizeWithDummy[1] != 2 /\ + (1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithDummy[1]) + -> false, + 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, + y_Occurrence[1] -> 1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = 1, + 1 <= y_ExplicitVarSizeWithMarker_Marker -> y_Occurrence[y_ExplicitVarSizeWithMarker_Values[1]] + diff --git a/tests/exhaustive/basic/typed01/expected/model_2_3_2_2-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_2_3_2_2-solution000001.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_3_2_2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_3_2_2-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_2_3_2_2-solution000002.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_3_2_2-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_3_2_2-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_2_3_2_2-solution000003.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_3_2_2-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_3_2_2.eprime b/tests/exhaustive/basic/typed01/expected/model_2_3_2_2.eprime new file mode 100644 index 0000000000..eff11cdc36 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_3_2_2.eprime @@ -0,0 +1,19 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +find y_ExplicitVarSizeWithMarker_Marker: int(0..1) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +branching on + [x_ExplicitVarSizeWithDummy, y_ExplicitVarSizeWithDummy, y_ExplicitVarSizeWithMarker_Marker, + y_ExplicitVarSizeWithMarker_Values] +such that + x_ExplicitVarSizeWithDummy[1] != 2 /\ + (1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithDummy[1]) + -> false, + 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, + y_ExplicitVarSizeWithDummy[1] != 2 -> + 1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = y_ExplicitVarSizeWithDummy[1], + 1 <= y_ExplicitVarSizeWithMarker_Marker -> + y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = y_ExplicitVarSizeWithMarker_Values[1] + diff --git a/tests/exhaustive/basic/typed01/expected/model_2_3_2_3-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_2_3_2_3-solution000001.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_3_2_3-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_3_2_3-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_2_3_2_3-solution000002.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_3_2_3-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_3_2_3-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_2_3_2_3-solution000003.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_3_2_3-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_3_2_3.eprime b/tests/exhaustive/basic/typed01/expected/model_2_3_2_3.eprime new file mode 100644 index 0000000000..fb495deda8 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_3_2_3.eprime @@ -0,0 +1,12 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +find y_ExplicitVarSizeWithMarker_Marker: int(0..1) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +branching on [x_ExplicitVarSizeWithDummy, y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values] +such that + x_ExplicitVarSizeWithDummy[1] != 2 /\ + (1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithDummy[1]) + -> false, + 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1 + diff --git a/tests/exhaustive/basic/typed01/expected/model_2_3_2_4-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_2_3_2_4-solution000001.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_3_2_4-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_3_2_4-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_2_3_2_4-solution000002.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_3_2_4-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_3_2_4-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_2_3_2_4-solution000003.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_3_2_4-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_3_2_4.eprime b/tests/exhaustive/basic/typed01/expected/model_2_3_2_4.eprime new file mode 100644 index 0000000000..cea7c108f0 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_3_2_4.eprime @@ -0,0 +1,22 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +find y_ExplicitVarSizeWithMarker_Marker: int(0..1) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +branching on + [x_ExplicitVarSizeWithDummy, y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values, + y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values] +such that + x_ExplicitVarSizeWithDummy[1] != 2 /\ + (1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithDummy[1]) + -> false, + 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, + y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, + y_ExplicitVarSizeWithFlags_Flags[1] -> + 1 <= y_ExplicitVarSizeWithMarker_Marker /\ + y_ExplicitVarSizeWithMarker_Values[1] = y_ExplicitVarSizeWithFlags_Values[1], + 1 <= y_ExplicitVarSizeWithMarker_Marker -> + y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = y_ExplicitVarSizeWithMarker_Values[1] + diff --git a/tests/exhaustive/basic/typed01/expected/model_2_3_3_1-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_2_3_3_1-solution000001.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_3_3_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_3_3_1-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_2_3_3_1-solution000002.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_3_3_1-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_3_3_1-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_2_3_3_1-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_3_3_1-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_3_3_1.eprime b/tests/exhaustive/basic/typed01/expected/model_2_3_3_1.eprime new file mode 100644 index 0000000000..a96e186edc --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_3_3_1.eprime @@ -0,0 +1,24 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +find x_ExplicitVarSizeWithMarker_Marker: int(0..1) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +find y_ExplicitVarSizeWithMarker_Marker: int(0..1) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +find y_Occurrence: matrix indexed by [int(1)] of bool +branching on + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy, y_Occurrence, + y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values] +such that + x_ExplicitVarSizeWithDummy[1] != 2 /\ + (1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithDummy[1]) + -> false, + 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, + 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithMarker_Values[1], + x_ExplicitVarSizeWithDummy[1] != 2 -> + 1 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithDummy[1], + y_Occurrence[1] -> 1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = 1, + 1 <= y_ExplicitVarSizeWithMarker_Marker -> y_Occurrence[y_ExplicitVarSizeWithMarker_Values[1]] + diff --git a/tests/exhaustive/basic/typed01/expected/model_2_3_3_2-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_2_3_3_2-solution000001.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_3_3_2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_3_3_2-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_2_3_3_2-solution000002.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_3_3_2-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_3_3_2-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_2_3_3_2-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_3_3_2-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_3_3_2.eprime b/tests/exhaustive/basic/typed01/expected/model_2_3_3_2.eprime new file mode 100644 index 0000000000..f0f0f557c3 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_3_3_2.eprime @@ -0,0 +1,26 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +find x_ExplicitVarSizeWithMarker_Marker: int(0..1) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +find y_ExplicitVarSizeWithMarker_Marker: int(0..1) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +branching on + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy, + y_ExplicitVarSizeWithDummy, y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values] +such that + x_ExplicitVarSizeWithDummy[1] != 2 /\ + (1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithDummy[1]) + -> false, + 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, + 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithMarker_Values[1], + x_ExplicitVarSizeWithDummy[1] != 2 -> + 1 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithDummy[1], + y_ExplicitVarSizeWithDummy[1] != 2 -> + 1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = y_ExplicitVarSizeWithDummy[1], + 1 <= y_ExplicitVarSizeWithMarker_Marker -> + y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = y_ExplicitVarSizeWithMarker_Values[1] + diff --git a/tests/exhaustive/basic/typed01/expected/model_2_3_3_3-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_2_3_3_3-solution000001.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_3_3_3-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_3_3_3-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_2_3_3_3-solution000002.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_3_3_3-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_3_3_3-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_2_3_3_3-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_3_3_3-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_3_3_3.eprime b/tests/exhaustive/basic/typed01/expected/model_2_3_3_3.eprime new file mode 100644 index 0000000000..455d856d44 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_3_3_3.eprime @@ -0,0 +1,21 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +find x_ExplicitVarSizeWithMarker_Marker: int(0..1) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +find y_ExplicitVarSizeWithMarker_Marker: int(0..1) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +branching on + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy, + y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values] +such that + x_ExplicitVarSizeWithDummy[1] != 2 /\ + (1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithDummy[1]) + -> false, + 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, + 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithMarker_Values[1], + x_ExplicitVarSizeWithDummy[1] != 2 -> + 1 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithDummy[1] + diff --git a/tests/exhaustive/basic/typed01/expected/model_2_3_3_4-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_2_3_3_4-solution000001.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_3_3_4-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_3_3_4-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_2_3_3_4-solution000002.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_3_3_4-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_3_3_4-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_2_3_3_4-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_3_3_4-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_3_3_4.eprime b/tests/exhaustive/basic/typed01/expected/model_2_3_3_4.eprime new file mode 100644 index 0000000000..4d85bf465b --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_3_3_4.eprime @@ -0,0 +1,30 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +find x_ExplicitVarSizeWithMarker_Marker: int(0..1) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +find y_ExplicitVarSizeWithMarker_Marker: int(0..1) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +branching on + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy, + y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithMarker_Marker, + y_ExplicitVarSizeWithMarker_Values] +such that + x_ExplicitVarSizeWithDummy[1] != 2 /\ + (1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithDummy[1]) + -> false, + 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, + 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithMarker_Values[1], + x_ExplicitVarSizeWithDummy[1] != 2 -> + 1 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithDummy[1], + y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, + y_ExplicitVarSizeWithFlags_Flags[1] -> + 1 <= y_ExplicitVarSizeWithMarker_Marker /\ + y_ExplicitVarSizeWithMarker_Values[1] = y_ExplicitVarSizeWithFlags_Values[1], + 1 <= y_ExplicitVarSizeWithMarker_Marker -> + y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = y_ExplicitVarSizeWithMarker_Values[1] + diff --git a/tests/exhaustive/basic/typed01/expected/model_2_3_4_1-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_2_3_4_1-solution000001.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_3_4_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_3_4_1-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_2_3_4_1-solution000002.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_3_4_1-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_3_4_1-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_2_3_4_1-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_3_4_1-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_3_4_1.eprime b/tests/exhaustive/basic/typed01/expected/model_2_3_4_1.eprime new file mode 100644 index 0000000000..b51cd218eb --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_3_4_1.eprime @@ -0,0 +1,24 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +find y_ExplicitVarSizeWithMarker_Marker: int(0..1) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +find y_Occurrence: matrix indexed by [int(1)] of bool +branching on + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy, y_Occurrence, + y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values] +such that + x_ExplicitVarSizeWithDummy[1] != 2 /\ + (1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithDummy[1]) + -> false, + 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, + x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, + x_ExplicitVarSizeWithFlags_Flags[1] -> + x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithFlags_Values[1], + x_ExplicitVarSizeWithDummy[1] != 2 -> + x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithDummy[1], + y_Occurrence[1] -> 1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = 1, + 1 <= y_ExplicitVarSizeWithMarker_Marker -> y_Occurrence[y_ExplicitVarSizeWithMarker_Values[1]] + diff --git a/tests/exhaustive/basic/typed01/expected/model_2_3_4_2-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_2_3_4_2-solution000001.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_3_4_2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_3_4_2-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_2_3_4_2-solution000002.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_3_4_2-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_3_4_2-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_2_3_4_2-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_3_4_2-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_3_4_2.eprime b/tests/exhaustive/basic/typed01/expected/model_2_3_4_2.eprime new file mode 100644 index 0000000000..9a22181e07 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_3_4_2.eprime @@ -0,0 +1,26 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +find y_ExplicitVarSizeWithMarker_Marker: int(0..1) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +branching on + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy, + y_ExplicitVarSizeWithDummy, y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values] +such that + x_ExplicitVarSizeWithDummy[1] != 2 /\ + (1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithDummy[1]) + -> false, + 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, + x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, + x_ExplicitVarSizeWithFlags_Flags[1] -> + x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithFlags_Values[1], + x_ExplicitVarSizeWithDummy[1] != 2 -> + x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithDummy[1], + y_ExplicitVarSizeWithDummy[1] != 2 -> + 1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = y_ExplicitVarSizeWithDummy[1], + 1 <= y_ExplicitVarSizeWithMarker_Marker -> + y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = y_ExplicitVarSizeWithMarker_Values[1] + diff --git a/tests/exhaustive/basic/typed01/expected/model_2_3_4_3-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_2_3_4_3-solution000001.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_3_4_3-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_3_4_3-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_2_3_4_3-solution000002.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_3_4_3-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_3_4_3-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_2_3_4_3-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_3_4_3-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_3_4_3.eprime b/tests/exhaustive/basic/typed01/expected/model_2_3_4_3.eprime new file mode 100644 index 0000000000..38adccfc56 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_3_4_3.eprime @@ -0,0 +1,21 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +find y_ExplicitVarSizeWithMarker_Marker: int(0..1) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +branching on + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy, + y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values] +such that + x_ExplicitVarSizeWithDummy[1] != 2 /\ + (1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithDummy[1]) + -> false, + 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, + x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, + x_ExplicitVarSizeWithFlags_Flags[1] -> + x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithFlags_Values[1], + x_ExplicitVarSizeWithDummy[1] != 2 -> + x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithDummy[1] + diff --git a/tests/exhaustive/basic/typed01/expected/model_2_3_4_4-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_2_3_4_4-solution000001.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_3_4_4-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_3_4_4-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_2_3_4_4-solution000002.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_3_4_4-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_3_4_4-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_2_3_4_4-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_3_4_4-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_3_4_4.eprime b/tests/exhaustive/basic/typed01/expected/model_2_3_4_4.eprime new file mode 100644 index 0000000000..4eaa9ed45c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_3_4_4.eprime @@ -0,0 +1,30 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +find y_ExplicitVarSizeWithMarker_Marker: int(0..1) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +branching on + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy, + y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithMarker_Marker, + y_ExplicitVarSizeWithMarker_Values] +such that + x_ExplicitVarSizeWithDummy[1] != 2 /\ + (1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithDummy[1]) + -> false, + 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, + x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, + x_ExplicitVarSizeWithFlags_Flags[1] -> + x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithFlags_Values[1], + x_ExplicitVarSizeWithDummy[1] != 2 -> + x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithDummy[1], + y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, + y_ExplicitVarSizeWithFlags_Flags[1] -> + 1 <= y_ExplicitVarSizeWithMarker_Marker /\ + y_ExplicitVarSizeWithMarker_Values[1] = y_ExplicitVarSizeWithFlags_Values[1], + 1 <= y_ExplicitVarSizeWithMarker_Marker -> + y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = y_ExplicitVarSizeWithMarker_Values[1] + diff --git a/tests/exhaustive/basic/typed01/expected/model_2_4_1_1-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_2_4_1_1-solution000001.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_4_1_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_4_1_1-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_2_4_1_1-solution000002.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_4_1_1-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_4_1_1-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_2_4_1_1-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_4_1_1-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_4_1_1.eprime b/tests/exhaustive/basic/typed01/expected/model_2_4_1_1.eprime new file mode 100644 index 0000000000..27384abdaa --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_4_1_1.eprime @@ -0,0 +1,20 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +find x_Occurrence: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +find y_Occurrence: matrix indexed by [int(1)] of bool +branching on + [x_Occurrence, x_ExplicitVarSizeWithDummy, y_Occurrence, y_ExplicitVarSizeWithFlags_Flags, + y_ExplicitVarSizeWithFlags_Values] +such that + x_ExplicitVarSizeWithDummy[1] != 2 /\ + (y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithDummy[1]) + -> false, + y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, + x_Occurrence[1] -> x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = 1, + x_ExplicitVarSizeWithDummy[1] != 2 -> x_Occurrence[x_ExplicitVarSizeWithDummy[1]], + y_Occurrence[1] -> y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = 1, + y_ExplicitVarSizeWithFlags_Flags[1] -> y_Occurrence[y_ExplicitVarSizeWithFlags_Values[1]] + diff --git a/tests/exhaustive/basic/typed01/expected/model_2_4_1_2-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_2_4_1_2-solution000001.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_4_1_2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_4_1_2-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_2_4_1_2-solution000002.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_4_1_2-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_4_1_2-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_2_4_1_2-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_4_1_2-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_4_1_2.eprime b/tests/exhaustive/basic/typed01/expected/model_2_4_1_2.eprime new file mode 100644 index 0000000000..756d504a56 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_4_1_2.eprime @@ -0,0 +1,22 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +find x_Occurrence: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +branching on + [x_Occurrence, x_ExplicitVarSizeWithDummy, y_ExplicitVarSizeWithDummy, y_ExplicitVarSizeWithFlags_Flags, + y_ExplicitVarSizeWithFlags_Values] +such that + x_ExplicitVarSizeWithDummy[1] != 2 /\ + (y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithDummy[1]) + -> false, + y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, + x_Occurrence[1] -> x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = 1, + x_ExplicitVarSizeWithDummy[1] != 2 -> x_Occurrence[x_ExplicitVarSizeWithDummy[1]], + y_ExplicitVarSizeWithDummy[1] != 2 -> + y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = y_ExplicitVarSizeWithDummy[1], + y_ExplicitVarSizeWithFlags_Flags[1] -> + y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = y_ExplicitVarSizeWithFlags_Values[1] + diff --git a/tests/exhaustive/basic/typed01/expected/model_2_4_1_3-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_2_4_1_3-solution000001.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_4_1_3-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_4_1_3-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_2_4_1_3-solution000002.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_4_1_3-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_4_1_3-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_2_4_1_3-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_4_1_3-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_4_1_3.eprime b/tests/exhaustive/basic/typed01/expected/model_2_4_1_3.eprime new file mode 100644 index 0000000000..950474f419 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_4_1_3.eprime @@ -0,0 +1,25 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +find x_Occurrence: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +find y_ExplicitVarSizeWithMarker_Marker: int(0..1) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +branching on + [x_Occurrence, x_ExplicitVarSizeWithDummy, y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values, + y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values] +such that + x_ExplicitVarSizeWithDummy[1] != 2 /\ + (y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithDummy[1]) + -> false, + y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, + x_Occurrence[1] -> x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = 1, + x_ExplicitVarSizeWithDummy[1] != 2 -> x_Occurrence[x_ExplicitVarSizeWithDummy[1]], + 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, + 1 <= y_ExplicitVarSizeWithMarker_Marker -> + y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = y_ExplicitVarSizeWithMarker_Values[1], + y_ExplicitVarSizeWithFlags_Flags[1] -> + 1 <= y_ExplicitVarSizeWithMarker_Marker /\ + y_ExplicitVarSizeWithMarker_Values[1] = y_ExplicitVarSizeWithFlags_Values[1] + diff --git a/tests/exhaustive/basic/typed01/expected/model_2_4_1_4-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_2_4_1_4-solution000001.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_4_1_4-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_4_1_4-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_2_4_1_4-solution000002.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_4_1_4-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_4_1_4-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_2_4_1_4-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_4_1_4-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_4_1_4.eprime b/tests/exhaustive/basic/typed01/expected/model_2_4_1_4.eprime new file mode 100644 index 0000000000..b9abdd4e8a --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_4_1_4.eprime @@ -0,0 +1,16 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +find x_Occurrence: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +branching on + [x_Occurrence, x_ExplicitVarSizeWithDummy, y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values] +such that + x_ExplicitVarSizeWithDummy[1] != 2 /\ + (y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithDummy[1]) + -> false, + y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, + x_Occurrence[1] -> x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = 1, + x_ExplicitVarSizeWithDummy[1] != 2 -> x_Occurrence[x_ExplicitVarSizeWithDummy[1]] + diff --git a/tests/exhaustive/basic/typed01/expected/model_2_4_2_1-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_2_4_2_1-solution000001.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_4_2_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_4_2_1-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_2_4_2_1-solution000002.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_4_2_1-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_4_2_1-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_2_4_2_1-solution000003.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_4_2_1-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_4_2_1.eprime b/tests/exhaustive/basic/typed01/expected/model_2_4_2_1.eprime new file mode 100644 index 0000000000..9305aca214 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_4_2_1.eprime @@ -0,0 +1,16 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +find y_Occurrence: matrix indexed by [int(1)] of bool +branching on + [x_ExplicitVarSizeWithDummy, y_Occurrence, y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values] +such that + x_ExplicitVarSizeWithDummy[1] != 2 /\ + (y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithDummy[1]) + -> false, + y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, + y_Occurrence[1] -> y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = 1, + y_ExplicitVarSizeWithFlags_Flags[1] -> y_Occurrence[y_ExplicitVarSizeWithFlags_Values[1]] + diff --git a/tests/exhaustive/basic/typed01/expected/model_2_4_2_2-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_2_4_2_2-solution000001.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_4_2_2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_4_2_2-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_2_4_2_2-solution000002.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_4_2_2-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_4_2_2-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_2_4_2_2-solution000003.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_4_2_2-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_4_2_2.eprime b/tests/exhaustive/basic/typed01/expected/model_2_4_2_2.eprime new file mode 100644 index 0000000000..e767d28abb --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_4_2_2.eprime @@ -0,0 +1,19 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +branching on + [x_ExplicitVarSizeWithDummy, y_ExplicitVarSizeWithDummy, y_ExplicitVarSizeWithFlags_Flags, + y_ExplicitVarSizeWithFlags_Values] +such that + x_ExplicitVarSizeWithDummy[1] != 2 /\ + (y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithDummy[1]) + -> false, + y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, + y_ExplicitVarSizeWithDummy[1] != 2 -> + y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = y_ExplicitVarSizeWithDummy[1], + y_ExplicitVarSizeWithFlags_Flags[1] -> + y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = y_ExplicitVarSizeWithFlags_Values[1] + diff --git a/tests/exhaustive/basic/typed01/expected/model_2_4_2_3-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_2_4_2_3-solution000001.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_4_2_3-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_4_2_3-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_2_4_2_3-solution000002.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_4_2_3-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_4_2_3-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_2_4_2_3-solution000003.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_4_2_3-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_4_2_3.eprime b/tests/exhaustive/basic/typed01/expected/model_2_4_2_3.eprime new file mode 100644 index 0000000000..b7697fa29f --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_4_2_3.eprime @@ -0,0 +1,22 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +find y_ExplicitVarSizeWithMarker_Marker: int(0..1) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +branching on + [x_ExplicitVarSizeWithDummy, y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values, + y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values] +such that + x_ExplicitVarSizeWithDummy[1] != 2 /\ + (y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithDummy[1]) + -> false, + y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, + 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, + 1 <= y_ExplicitVarSizeWithMarker_Marker -> + y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = y_ExplicitVarSizeWithMarker_Values[1], + y_ExplicitVarSizeWithFlags_Flags[1] -> + 1 <= y_ExplicitVarSizeWithMarker_Marker /\ + y_ExplicitVarSizeWithMarker_Values[1] = y_ExplicitVarSizeWithFlags_Values[1] + diff --git a/tests/exhaustive/basic/typed01/expected/model_2_4_2_4-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_2_4_2_4-solution000001.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_4_2_4-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_4_2_4-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_2_4_2_4-solution000002.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_4_2_4-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_4_2_4-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_2_4_2_4-solution000003.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_4_2_4-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_4_2_4.eprime b/tests/exhaustive/basic/typed01/expected/model_2_4_2_4.eprime new file mode 100644 index 0000000000..81345e4ad5 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_4_2_4.eprime @@ -0,0 +1,12 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +branching on [x_ExplicitVarSizeWithDummy, y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values] +such that + x_ExplicitVarSizeWithDummy[1] != 2 /\ + (y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithDummy[1]) + -> false, + y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1 + diff --git a/tests/exhaustive/basic/typed01/expected/model_2_4_3_1-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_2_4_3_1-solution000001.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_4_3_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_4_3_1-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_2_4_3_1-solution000002.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_4_3_1-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_4_3_1-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_2_4_3_1-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_4_3_1-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_4_3_1.eprime b/tests/exhaustive/basic/typed01/expected/model_2_4_3_1.eprime new file mode 100644 index 0000000000..2d924bfba1 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_4_3_1.eprime @@ -0,0 +1,24 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +find x_ExplicitVarSizeWithMarker_Marker: int(0..1) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +find y_Occurrence: matrix indexed by [int(1)] of bool +branching on + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy, y_Occurrence, + y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values] +such that + x_ExplicitVarSizeWithDummy[1] != 2 /\ + (y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithDummy[1]) + -> false, + y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, + 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithMarker_Values[1], + x_ExplicitVarSizeWithDummy[1] != 2 -> + 1 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithDummy[1], + y_Occurrence[1] -> y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = 1, + y_ExplicitVarSizeWithFlags_Flags[1] -> y_Occurrence[y_ExplicitVarSizeWithFlags_Values[1]] + diff --git a/tests/exhaustive/basic/typed01/expected/model_2_4_3_2-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_2_4_3_2-solution000001.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_4_3_2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_4_3_2-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_2_4_3_2-solution000002.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_4_3_2-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_4_3_2-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_2_4_3_2-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_4_3_2-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_4_3_2.eprime b/tests/exhaustive/basic/typed01/expected/model_2_4_3_2.eprime new file mode 100644 index 0000000000..bef3b1d9e8 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_4_3_2.eprime @@ -0,0 +1,26 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +find x_ExplicitVarSizeWithMarker_Marker: int(0..1) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +branching on + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy, + y_ExplicitVarSizeWithDummy, y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values] +such that + x_ExplicitVarSizeWithDummy[1] != 2 /\ + (y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithDummy[1]) + -> false, + y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, + 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithMarker_Values[1], + x_ExplicitVarSizeWithDummy[1] != 2 -> + 1 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithDummy[1], + y_ExplicitVarSizeWithDummy[1] != 2 -> + y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = y_ExplicitVarSizeWithDummy[1], + y_ExplicitVarSizeWithFlags_Flags[1] -> + y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = y_ExplicitVarSizeWithFlags_Values[1] + diff --git a/tests/exhaustive/basic/typed01/expected/model_2_4_3_3-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_2_4_3_3-solution000001.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_4_3_3-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_4_3_3-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_2_4_3_3-solution000002.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_4_3_3-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_4_3_3-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_2_4_3_3-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_4_3_3-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_4_3_3.eprime b/tests/exhaustive/basic/typed01/expected/model_2_4_3_3.eprime new file mode 100644 index 0000000000..b8a64e76d1 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_4_3_3.eprime @@ -0,0 +1,30 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +find x_ExplicitVarSizeWithMarker_Marker: int(0..1) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +find y_ExplicitVarSizeWithMarker_Marker: int(0..1) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +branching on + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy, + y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithFlags_Flags, + y_ExplicitVarSizeWithFlags_Values] +such that + x_ExplicitVarSizeWithDummy[1] != 2 /\ + (y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithDummy[1]) + -> false, + y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, + 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithMarker_Values[1], + x_ExplicitVarSizeWithDummy[1] != 2 -> + 1 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithDummy[1], + 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, + 1 <= y_ExplicitVarSizeWithMarker_Marker -> + y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = y_ExplicitVarSizeWithMarker_Values[1], + y_ExplicitVarSizeWithFlags_Flags[1] -> + 1 <= y_ExplicitVarSizeWithMarker_Marker /\ + y_ExplicitVarSizeWithMarker_Values[1] = y_ExplicitVarSizeWithFlags_Values[1] + diff --git a/tests/exhaustive/basic/typed01/expected/model_2_4_3_4-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_2_4_3_4-solution000001.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_4_3_4-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_4_3_4-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_2_4_3_4-solution000002.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_4_3_4-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_4_3_4-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_2_4_3_4-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_4_3_4-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_4_3_4.eprime b/tests/exhaustive/basic/typed01/expected/model_2_4_3_4.eprime new file mode 100644 index 0000000000..73e37546d5 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_4_3_4.eprime @@ -0,0 +1,21 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +find x_ExplicitVarSizeWithMarker_Marker: int(0..1) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +branching on + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy, + y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values] +such that + x_ExplicitVarSizeWithDummy[1] != 2 /\ + (y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithDummy[1]) + -> false, + y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, + 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithMarker_Values[1], + x_ExplicitVarSizeWithDummy[1] != 2 -> + 1 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithDummy[1] + diff --git a/tests/exhaustive/basic/typed01/expected/model_2_4_4_1-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_2_4_4_1-solution000001.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_4_4_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_4_4_1-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_2_4_4_1-solution000002.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_4_4_1-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_4_4_1-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_2_4_4_1-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_4_4_1-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_4_4_1.eprime b/tests/exhaustive/basic/typed01/expected/model_2_4_4_1.eprime new file mode 100644 index 0000000000..f983f59967 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_4_4_1.eprime @@ -0,0 +1,24 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +find y_Occurrence: matrix indexed by [int(1)] of bool +branching on + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy, y_Occurrence, + y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values] +such that + x_ExplicitVarSizeWithDummy[1] != 2 /\ + (y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithDummy[1]) + -> false, + y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, + x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, + x_ExplicitVarSizeWithFlags_Flags[1] -> + x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithFlags_Values[1], + x_ExplicitVarSizeWithDummy[1] != 2 -> + x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithDummy[1], + y_Occurrence[1] -> y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = 1, + y_ExplicitVarSizeWithFlags_Flags[1] -> y_Occurrence[y_ExplicitVarSizeWithFlags_Values[1]] + diff --git a/tests/exhaustive/basic/typed01/expected/model_2_4_4_2-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_2_4_4_2-solution000001.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_4_4_2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_4_4_2-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_2_4_4_2-solution000002.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_4_4_2-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_4_4_2-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_2_4_4_2-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_4_4_2-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_4_4_2.eprime b/tests/exhaustive/basic/typed01/expected/model_2_4_4_2.eprime new file mode 100644 index 0000000000..d0265ea199 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_4_4_2.eprime @@ -0,0 +1,26 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +branching on + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy, + y_ExplicitVarSizeWithDummy, y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values] +such that + x_ExplicitVarSizeWithDummy[1] != 2 /\ + (y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithDummy[1]) + -> false, + y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, + x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, + x_ExplicitVarSizeWithFlags_Flags[1] -> + x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithFlags_Values[1], + x_ExplicitVarSizeWithDummy[1] != 2 -> + x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithDummy[1], + y_ExplicitVarSizeWithDummy[1] != 2 -> + y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = y_ExplicitVarSizeWithDummy[1], + y_ExplicitVarSizeWithFlags_Flags[1] -> + y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = y_ExplicitVarSizeWithFlags_Values[1] + diff --git a/tests/exhaustive/basic/typed01/expected/model_2_4_4_3-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_2_4_4_3-solution000001.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_4_4_3-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_4_4_3-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_2_4_4_3-solution000002.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_4_4_3-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_4_4_3-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_2_4_4_3-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_4_4_3-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_4_4_3.eprime b/tests/exhaustive/basic/typed01/expected/model_2_4_4_3.eprime new file mode 100644 index 0000000000..2d70798d52 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_4_4_3.eprime @@ -0,0 +1,30 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +find y_ExplicitVarSizeWithMarker_Marker: int(0..1) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +branching on + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy, + y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithFlags_Flags, + y_ExplicitVarSizeWithFlags_Values] +such that + x_ExplicitVarSizeWithDummy[1] != 2 /\ + (y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithDummy[1]) + -> false, + y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, + x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, + x_ExplicitVarSizeWithFlags_Flags[1] -> + x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithFlags_Values[1], + x_ExplicitVarSizeWithDummy[1] != 2 -> + x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithDummy[1], + 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, + 1 <= y_ExplicitVarSizeWithMarker_Marker -> + y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = y_ExplicitVarSizeWithMarker_Values[1], + y_ExplicitVarSizeWithFlags_Flags[1] -> + 1 <= y_ExplicitVarSizeWithMarker_Marker /\ + y_ExplicitVarSizeWithMarker_Values[1] = y_ExplicitVarSizeWithFlags_Values[1] + diff --git a/tests/exhaustive/basic/typed01/expected/model_2_4_4_4-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_2_4_4_4-solution000001.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_4_4_4-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_4_4_4-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_2_4_4_4-solution000002.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_4_4_4-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_4_4_4-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_2_4_4_4-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_4_4_4-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_2_4_4_4.eprime b/tests/exhaustive/basic/typed01/expected/model_2_4_4_4.eprime new file mode 100644 index 0000000000..eb8ed6d4d1 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_2_4_4_4.eprime @@ -0,0 +1,21 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +branching on + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy, + y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values] +such that + x_ExplicitVarSizeWithDummy[1] != 2 /\ + (y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithDummy[1]) + -> false, + y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, + x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, + x_ExplicitVarSizeWithFlags_Flags[1] -> + x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithFlags_Values[1], + x_ExplicitVarSizeWithDummy[1] != 2 -> + x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithDummy[1] + diff --git a/tests/exhaustive/basic/typed01/expected/model_3_1_1_1-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_3_1_1_1-solution000001.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_1_1_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_1_1_1-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_3_1_1_1-solution000002.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_1_1_1-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_1_1_1-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_3_1_1_1-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_1_1_1-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_1_1_1.eprime b/tests/exhaustive/basic/typed01/expected/model_3_1_1_1.eprime new file mode 100644 index 0000000000..b1f9d14f8a --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_1_1_1.eprime @@ -0,0 +1,13 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..1) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +find x_Occurrence: matrix indexed by [int(1)] of bool +find y_Occurrence: matrix indexed by [int(1)] of bool +branching on [x_Occurrence, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, y_Occurrence] +such that + 1 <= x_ExplicitVarSizeWithMarker_Marker /\ y_Occurrence[x_ExplicitVarSizeWithMarker_Values[1]] -> false, + 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, + x_Occurrence[1] -> 1 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[1] = 1, + 1 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[1]] + diff --git a/tests/exhaustive/basic/typed01/expected/model_3_1_1_2-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_3_1_1_2-solution000001.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_1_1_2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_1_1_2-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_3_1_1_2-solution000002.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_1_1_2-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_1_1_2-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_3_1_1_2-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_1_1_2-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_1_1_2.eprime b/tests/exhaustive/basic/typed01/expected/model_3_1_1_2.eprime new file mode 100644 index 0000000000..0e577a8eac --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_1_1_2.eprime @@ -0,0 +1,18 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..1) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +find x_Occurrence: matrix indexed by [int(1)] of bool +find y_Occurrence: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +branching on + [x_Occurrence, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithDummy, + y_Occurrence] +such that + 1 <= x_ExplicitVarSizeWithMarker_Marker /\ y_Occurrence[x_ExplicitVarSizeWithMarker_Values[1]] -> false, + 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, + x_Occurrence[1] -> 1 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[1] = 1, + 1 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[1]], + y_ExplicitVarSizeWithDummy[1] != 2 -> y_Occurrence[y_ExplicitVarSizeWithDummy[1]], + y_Occurrence[1] -> y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = 1 + diff --git a/tests/exhaustive/basic/typed01/expected/model_3_1_1_3-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_3_1_1_3-solution000001.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_1_1_3-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_1_1_3-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_3_1_1_3-solution000002.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_1_1_3-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_1_1_3-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_3_1_1_3-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_1_1_3-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_1_1_3.eprime b/tests/exhaustive/basic/typed01/expected/model_3_1_1_3.eprime new file mode 100644 index 0000000000..20840fd0f7 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_1_1_3.eprime @@ -0,0 +1,20 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..1) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +find x_Occurrence: matrix indexed by [int(1)] of bool +find y_Occurrence: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithMarker_Marker: int(0..1) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +branching on + [x_Occurrence, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, + y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values, y_Occurrence] +such that + 1 <= x_ExplicitVarSizeWithMarker_Marker /\ y_Occurrence[x_ExplicitVarSizeWithMarker_Values[1]] -> false, + 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, + x_Occurrence[1] -> 1 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[1] = 1, + 1 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[1]], + 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, + 1 <= y_ExplicitVarSizeWithMarker_Marker -> y_Occurrence[y_ExplicitVarSizeWithMarker_Values[1]], + y_Occurrence[1] -> 1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = 1 + diff --git a/tests/exhaustive/basic/typed01/expected/model_3_1_1_4-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_3_1_1_4-solution000001.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_1_1_4-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_1_1_4-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_3_1_1_4-solution000002.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_1_1_4-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_1_1_4-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_3_1_1_4-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_1_1_4-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_1_1_4.eprime b/tests/exhaustive/basic/typed01/expected/model_3_1_1_4.eprime new file mode 100644 index 0000000000..15ecf4d3a3 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_1_1_4.eprime @@ -0,0 +1,20 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..1) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +find x_Occurrence: matrix indexed by [int(1)] of bool +find y_Occurrence: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +branching on + [x_Occurrence, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, + y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values, y_Occurrence] +such that + 1 <= x_ExplicitVarSizeWithMarker_Marker /\ y_Occurrence[x_ExplicitVarSizeWithMarker_Values[1]] -> false, + 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, + x_Occurrence[1] -> 1 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[1] = 1, + 1 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[1]], + y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, + y_ExplicitVarSizeWithFlags_Flags[1] -> y_Occurrence[y_ExplicitVarSizeWithFlags_Values[1]], + y_Occurrence[1] -> y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = 1 + diff --git a/tests/exhaustive/basic/typed01/expected/model_3_1_2_1-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_3_1_2_1-solution000001.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_1_2_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_1_2_1-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_3_1_2_1-solution000002.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_1_2_1-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_1_2_1-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_3_1_2_1-solution000003.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_1_2_1-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_1_2_1.eprime b/tests/exhaustive/basic/typed01/expected/model_3_1_2_1.eprime new file mode 100644 index 0000000000..3232164034 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_1_2_1.eprime @@ -0,0 +1,16 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..1) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +find y_Occurrence: matrix indexed by [int(1)] of bool +branching on + [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, y_Occurrence] +such that + 1 <= x_ExplicitVarSizeWithMarker_Marker /\ y_Occurrence[x_ExplicitVarSizeWithMarker_Values[1]] -> false, + 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, + x_ExplicitVarSizeWithDummy[1] != 2 -> + 1 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithDummy[1], + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithMarker_Values[1] + diff --git a/tests/exhaustive/basic/typed01/expected/model_3_1_2_2-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_3_1_2_2-solution000001.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_1_2_2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_1_2_2-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_3_1_2_2-solution000002.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_1_2_2-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_1_2_2-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_3_1_2_2-solution000003.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_1_2_2-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_1_2_2.eprime b/tests/exhaustive/basic/typed01/expected/model_3_1_2_2.eprime new file mode 100644 index 0000000000..8198674706 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_1_2_2.eprime @@ -0,0 +1,20 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..1) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +find y_Occurrence: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +branching on + [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, + y_ExplicitVarSizeWithDummy, y_Occurrence] +such that + 1 <= x_ExplicitVarSizeWithMarker_Marker /\ y_Occurrence[x_ExplicitVarSizeWithMarker_Values[1]] -> false, + 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, + x_ExplicitVarSizeWithDummy[1] != 2 -> + 1 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithDummy[1], + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithMarker_Values[1], + y_ExplicitVarSizeWithDummy[1] != 2 -> y_Occurrence[y_ExplicitVarSizeWithDummy[1]], + y_Occurrence[1] -> y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = 1 + diff --git a/tests/exhaustive/basic/typed01/expected/model_3_1_2_3-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_3_1_2_3-solution000001.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_1_2_3-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_1_2_3-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_3_1_2_3-solution000002.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_1_2_3-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_1_2_3-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_3_1_2_3-solution000003.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_1_2_3-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_1_2_3.eprime b/tests/exhaustive/basic/typed01/expected/model_3_1_2_3.eprime new file mode 100644 index 0000000000..d85db5cc93 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_1_2_3.eprime @@ -0,0 +1,22 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..1) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +find y_Occurrence: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithMarker_Marker: int(0..1) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +branching on + [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, + y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values, y_Occurrence] +such that + 1 <= x_ExplicitVarSizeWithMarker_Marker /\ y_Occurrence[x_ExplicitVarSizeWithMarker_Values[1]] -> false, + 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, + x_ExplicitVarSizeWithDummy[1] != 2 -> + 1 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithDummy[1], + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithMarker_Values[1], + 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, + 1 <= y_ExplicitVarSizeWithMarker_Marker -> y_Occurrence[y_ExplicitVarSizeWithMarker_Values[1]], + y_Occurrence[1] -> 1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = 1 + diff --git a/tests/exhaustive/basic/typed01/expected/model_3_1_2_4-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_3_1_2_4-solution000001.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_1_2_4-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_1_2_4-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_3_1_2_4-solution000002.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_1_2_4-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_1_2_4-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_3_1_2_4-solution000003.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_1_2_4-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_1_2_4.eprime b/tests/exhaustive/basic/typed01/expected/model_3_1_2_4.eprime new file mode 100644 index 0000000000..6965500389 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_1_2_4.eprime @@ -0,0 +1,22 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..1) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +find y_Occurrence: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +branching on + [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, + y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values, y_Occurrence] +such that + 1 <= x_ExplicitVarSizeWithMarker_Marker /\ y_Occurrence[x_ExplicitVarSizeWithMarker_Values[1]] -> false, + 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, + x_ExplicitVarSizeWithDummy[1] != 2 -> + 1 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithDummy[1], + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithMarker_Values[1], + y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, + y_ExplicitVarSizeWithFlags_Flags[1] -> y_Occurrence[y_ExplicitVarSizeWithFlags_Values[1]], + y_Occurrence[1] -> y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = 1 + diff --git a/tests/exhaustive/basic/typed01/expected/model_3_1_3_1-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_3_1_3_1-solution000001.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_1_3_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_1_3_1-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_3_1_3_1-solution000002.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_1_3_1-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_1_3_1-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_3_1_3_1-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_1_3_1-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_1_3_1.eprime b/tests/exhaustive/basic/typed01/expected/model_3_1_3_1.eprime new file mode 100644 index 0000000000..f5c2cccdbc --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_1_3_1.eprime @@ -0,0 +1,10 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..1) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +find y_Occurrence: matrix indexed by [int(1)] of bool +branching on [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, y_Occurrence] +such that + 1 <= x_ExplicitVarSizeWithMarker_Marker /\ y_Occurrence[x_ExplicitVarSizeWithMarker_Values[1]] -> false, + 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1 + diff --git a/tests/exhaustive/basic/typed01/expected/model_3_1_3_2-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_3_1_3_2-solution000001.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_1_3_2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_1_3_2-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_3_1_3_2-solution000002.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_1_3_2-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_1_3_2-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_3_1_3_2-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_1_3_2-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_1_3_2.eprime b/tests/exhaustive/basic/typed01/expected/model_3_1_3_2.eprime new file mode 100644 index 0000000000..e1c3367190 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_1_3_2.eprime @@ -0,0 +1,14 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..1) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +find y_Occurrence: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +branching on + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithDummy, y_Occurrence] +such that + 1 <= x_ExplicitVarSizeWithMarker_Marker /\ y_Occurrence[x_ExplicitVarSizeWithMarker_Values[1]] -> false, + 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, + y_ExplicitVarSizeWithDummy[1] != 2 -> y_Occurrence[y_ExplicitVarSizeWithDummy[1]], + y_Occurrence[1] -> y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = 1 + diff --git a/tests/exhaustive/basic/typed01/expected/model_3_1_3_3-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_3_1_3_3-solution000001.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_1_3_3-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_1_3_3-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_3_1_3_3-solution000002.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_1_3_3-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_1_3_3-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_3_1_3_3-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_1_3_3-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_1_3_3.eprime b/tests/exhaustive/basic/typed01/expected/model_3_1_3_3.eprime new file mode 100644 index 0000000000..9f6c670ab3 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_1_3_3.eprime @@ -0,0 +1,17 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..1) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +find y_Occurrence: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithMarker_Marker: int(0..1) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +branching on + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithMarker_Marker, + y_ExplicitVarSizeWithMarker_Values, y_Occurrence] +such that + 1 <= x_ExplicitVarSizeWithMarker_Marker /\ y_Occurrence[x_ExplicitVarSizeWithMarker_Values[1]] -> false, + 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, + 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, + 1 <= y_ExplicitVarSizeWithMarker_Marker -> y_Occurrence[y_ExplicitVarSizeWithMarker_Values[1]], + y_Occurrence[1] -> 1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = 1 + diff --git a/tests/exhaustive/basic/typed01/expected/model_3_1_3_4-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_3_1_3_4-solution000001.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_1_3_4-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_1_3_4-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_3_1_3_4-solution000002.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_1_3_4-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_1_3_4-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_3_1_3_4-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_1_3_4-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_1_3_4.eprime b/tests/exhaustive/basic/typed01/expected/model_3_1_3_4.eprime new file mode 100644 index 0000000000..e9cad424f2 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_1_3_4.eprime @@ -0,0 +1,17 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..1) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +find y_Occurrence: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +branching on + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithFlags_Flags, + y_ExplicitVarSizeWithFlags_Values, y_Occurrence] +such that + 1 <= x_ExplicitVarSizeWithMarker_Marker /\ y_Occurrence[x_ExplicitVarSizeWithMarker_Values[1]] -> false, + 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, + y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, + y_ExplicitVarSizeWithFlags_Flags[1] -> y_Occurrence[y_ExplicitVarSizeWithFlags_Values[1]], + y_Occurrence[1] -> y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = 1 + diff --git a/tests/exhaustive/basic/typed01/expected/model_3_1_4_1-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_3_1_4_1-solution000001.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_1_4_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_1_4_1-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_3_1_4_1-solution000002.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_1_4_1-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_1_4_1-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_3_1_4_1-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_1_4_1-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_1_4_1.eprime b/tests/exhaustive/basic/typed01/expected/model_3_1_4_1.eprime new file mode 100644 index 0000000000..c9d42653f0 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_1_4_1.eprime @@ -0,0 +1,20 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..1) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +find y_Occurrence: matrix indexed by [int(1)] of bool +branching on + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithMarker_Marker, + x_ExplicitVarSizeWithMarker_Values, y_Occurrence] +such that + 1 <= x_ExplicitVarSizeWithMarker_Marker /\ y_Occurrence[x_ExplicitVarSizeWithMarker_Values[1]] -> false, + 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, + x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, + x_ExplicitVarSizeWithFlags_Flags[1] -> + 1 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithFlags_Values[1], + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithMarker_Values[1] + diff --git a/tests/exhaustive/basic/typed01/expected/model_3_1_4_2-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_3_1_4_2-solution000001.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_1_4_2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_1_4_2-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_3_1_4_2-solution000002.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_1_4_2-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_1_4_2-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_3_1_4_2-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_1_4_2-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_1_4_2.eprime b/tests/exhaustive/basic/typed01/expected/model_3_1_4_2.eprime new file mode 100644 index 0000000000..542fea04f9 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_1_4_2.eprime @@ -0,0 +1,23 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..1) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +find y_Occurrence: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +branching on + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithMarker_Marker, + x_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithDummy, y_Occurrence] +such that + 1 <= x_ExplicitVarSizeWithMarker_Marker /\ y_Occurrence[x_ExplicitVarSizeWithMarker_Values[1]] -> false, + 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, + x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, + x_ExplicitVarSizeWithFlags_Flags[1] -> + 1 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithFlags_Values[1], + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithMarker_Values[1], + y_ExplicitVarSizeWithDummy[1] != 2 -> y_Occurrence[y_ExplicitVarSizeWithDummy[1]], + y_Occurrence[1] -> y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = 1 + diff --git a/tests/exhaustive/basic/typed01/expected/model_3_1_4_3-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_3_1_4_3-solution000001.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_1_4_3-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_1_4_3-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_3_1_4_3-solution000002.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_1_4_3-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_1_4_3-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_3_1_4_3-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_1_4_3-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_1_4_3.eprime b/tests/exhaustive/basic/typed01/expected/model_3_1_4_3.eprime new file mode 100644 index 0000000000..15763695d1 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_1_4_3.eprime @@ -0,0 +1,26 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..1) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +find y_Occurrence: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithMarker_Marker: int(0..1) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +branching on + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithMarker_Marker, + x_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values, + y_Occurrence] +such that + 1 <= x_ExplicitVarSizeWithMarker_Marker /\ y_Occurrence[x_ExplicitVarSizeWithMarker_Values[1]] -> false, + 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, + x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, + x_ExplicitVarSizeWithFlags_Flags[1] -> + 1 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithFlags_Values[1], + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithMarker_Values[1], + 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, + 1 <= y_ExplicitVarSizeWithMarker_Marker -> y_Occurrence[y_ExplicitVarSizeWithMarker_Values[1]], + y_Occurrence[1] -> 1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = 1 + diff --git a/tests/exhaustive/basic/typed01/expected/model_3_1_4_4-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_3_1_4_4-solution000001.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_1_4_4-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_1_4_4-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_3_1_4_4-solution000002.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_1_4_4-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_1_4_4-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_3_1_4_4-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_1_4_4-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_1_4_4.eprime b/tests/exhaustive/basic/typed01/expected/model_3_1_4_4.eprime new file mode 100644 index 0000000000..4074e09614 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_1_4_4.eprime @@ -0,0 +1,26 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..1) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +find y_Occurrence: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +branching on + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithMarker_Marker, + x_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values, + y_Occurrence] +such that + 1 <= x_ExplicitVarSizeWithMarker_Marker /\ y_Occurrence[x_ExplicitVarSizeWithMarker_Values[1]] -> false, + 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, + x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, + x_ExplicitVarSizeWithFlags_Flags[1] -> + 1 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithFlags_Values[1], + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithMarker_Values[1], + y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, + y_ExplicitVarSizeWithFlags_Flags[1] -> y_Occurrence[y_ExplicitVarSizeWithFlags_Values[1]], + y_Occurrence[1] -> y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = 1 + diff --git a/tests/exhaustive/basic/typed01/expected/model_3_2_1_1-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_3_2_1_1-solution000001.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_2_1_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_2_1_1-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_3_2_1_1-solution000002.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_2_1_1-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_2_1_1-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_3_2_1_1-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_2_1_1-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_2_1_1.eprime b/tests/exhaustive/basic/typed01/expected/model_3_2_1_1.eprime new file mode 100644 index 0000000000..5b779b4b38 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_2_1_1.eprime @@ -0,0 +1,20 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..1) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +find x_Occurrence: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +find y_Occurrence: matrix indexed by [int(1)] of bool +branching on + [x_Occurrence, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, y_Occurrence, + y_ExplicitVarSizeWithDummy] +such that + 1 <= x_ExplicitVarSizeWithMarker_Marker /\ + (y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithMarker_Values[1]) + -> false, + 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, + x_Occurrence[1] -> 1 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[1] = 1, + 1 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[1]], + y_Occurrence[1] -> y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = 1, + y_ExplicitVarSizeWithDummy[1] != 2 -> y_Occurrence[y_ExplicitVarSizeWithDummy[1]] + diff --git a/tests/exhaustive/basic/typed01/expected/model_3_2_1_2-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_3_2_1_2-solution000001.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_2_1_2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_2_1_2-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_3_2_1_2-solution000002.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_2_1_2-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_2_1_2-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_3_2_1_2-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_2_1_2-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_2_1_2.eprime b/tests/exhaustive/basic/typed01/expected/model_3_2_1_2.eprime new file mode 100644 index 0000000000..3dc3f438fd --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_2_1_2.eprime @@ -0,0 +1,16 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..1) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +find x_Occurrence: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +branching on + [x_Occurrence, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithDummy] +such that + 1 <= x_ExplicitVarSizeWithMarker_Marker /\ + (y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithMarker_Values[1]) + -> false, + 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, + x_Occurrence[1] -> 1 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[1] = 1, + 1 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[1]] + diff --git a/tests/exhaustive/basic/typed01/expected/model_3_2_1_3-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_3_2_1_3-solution000001.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_2_1_3-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_2_1_3-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_3_2_1_3-solution000002.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_2_1_3-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_2_1_3-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_3_2_1_3-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_2_1_3-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_2_1_3.eprime b/tests/exhaustive/basic/typed01/expected/model_3_2_1_3.eprime new file mode 100644 index 0000000000..10e6959273 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_2_1_3.eprime @@ -0,0 +1,24 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..1) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +find x_Occurrence: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +find y_ExplicitVarSizeWithMarker_Marker: int(0..1) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +branching on + [x_Occurrence, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, + y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithDummy] +such that + 1 <= x_ExplicitVarSizeWithMarker_Marker /\ + (y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithMarker_Values[1]) + -> false, + 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, + x_Occurrence[1] -> 1 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[1] = 1, + 1 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[1]], + 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, + 1 <= y_ExplicitVarSizeWithMarker_Marker -> + y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = y_ExplicitVarSizeWithMarker_Values[1], + y_ExplicitVarSizeWithDummy[1] != 2 -> + 1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = y_ExplicitVarSizeWithDummy[1] + diff --git a/tests/exhaustive/basic/typed01/expected/model_3_2_1_4-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_3_2_1_4-solution000001.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_2_1_4-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_2_1_4-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_3_2_1_4-solution000002.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_2_1_4-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_2_1_4-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_3_2_1_4-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_2_1_4-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_2_1_4.eprime b/tests/exhaustive/basic/typed01/expected/model_3_2_1_4.eprime new file mode 100644 index 0000000000..eba2cf80d9 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_2_1_4.eprime @@ -0,0 +1,24 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..1) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +find x_Occurrence: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +branching on + [x_Occurrence, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, + y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithDummy] +such that + 1 <= x_ExplicitVarSizeWithMarker_Marker /\ + (y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithMarker_Values[1]) + -> false, + 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, + x_Occurrence[1] -> 1 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[1] = 1, + 1 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[1]], + y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, + y_ExplicitVarSizeWithFlags_Flags[1] -> + y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = y_ExplicitVarSizeWithFlags_Values[1], + y_ExplicitVarSizeWithDummy[1] != 2 -> + y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = y_ExplicitVarSizeWithDummy[1] + diff --git a/tests/exhaustive/basic/typed01/expected/model_3_2_2_1-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_3_2_2_1-solution000001.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_2_2_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_2_2_1-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_3_2_2_1-solution000002.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_2_2_1-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_2_2_1-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_3_2_2_1-solution000003.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_2_2_1-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_2_2_1.eprime b/tests/exhaustive/basic/typed01/expected/model_3_2_2_1.eprime new file mode 100644 index 0000000000..31c98c5012 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_2_2_1.eprime @@ -0,0 +1,22 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..1) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +find y_Occurrence: matrix indexed by [int(1)] of bool +branching on + [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, y_Occurrence, + y_ExplicitVarSizeWithDummy] +such that + 1 <= x_ExplicitVarSizeWithMarker_Marker /\ + (y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithMarker_Values[1]) + -> false, + 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, + x_ExplicitVarSizeWithDummy[1] != 2 -> + 1 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithDummy[1], + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithMarker_Values[1], + y_Occurrence[1] -> y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = 1, + y_ExplicitVarSizeWithDummy[1] != 2 -> y_Occurrence[y_ExplicitVarSizeWithDummy[1]] + diff --git a/tests/exhaustive/basic/typed01/expected/model_3_2_2_2-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_3_2_2_2-solution000001.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_2_2_2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_2_2_2-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_3_2_2_2-solution000002.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_2_2_2-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_2_2_2-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_3_2_2_2-solution000003.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_2_2_2-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_2_2_2.eprime b/tests/exhaustive/basic/typed01/expected/model_3_2_2_2.eprime new file mode 100644 index 0000000000..6e50969662 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_2_2_2.eprime @@ -0,0 +1,19 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..1) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +branching on + [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, + y_ExplicitVarSizeWithDummy] +such that + 1 <= x_ExplicitVarSizeWithMarker_Marker /\ + (y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithMarker_Values[1]) + -> false, + 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, + x_ExplicitVarSizeWithDummy[1] != 2 -> + 1 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithDummy[1], + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithMarker_Values[1] + diff --git a/tests/exhaustive/basic/typed01/expected/model_3_2_2_3-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_3_2_2_3-solution000001.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_2_2_3-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_2_2_3-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_3_2_2_3-solution000002.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_2_2_3-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_2_2_3-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_3_2_2_3-solution000003.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_2_2_3-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_2_2_3.eprime b/tests/exhaustive/basic/typed01/expected/model_3_2_2_3.eprime new file mode 100644 index 0000000000..23bf917fe5 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_2_2_3.eprime @@ -0,0 +1,26 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..1) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +find y_ExplicitVarSizeWithMarker_Marker: int(0..1) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +branching on + [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, + y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithDummy] +such that + 1 <= x_ExplicitVarSizeWithMarker_Marker /\ + (y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithMarker_Values[1]) + -> false, + 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, + x_ExplicitVarSizeWithDummy[1] != 2 -> + 1 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithDummy[1], + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithMarker_Values[1], + 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, + 1 <= y_ExplicitVarSizeWithMarker_Marker -> + y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = y_ExplicitVarSizeWithMarker_Values[1], + y_ExplicitVarSizeWithDummy[1] != 2 -> + 1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = y_ExplicitVarSizeWithDummy[1] + diff --git a/tests/exhaustive/basic/typed01/expected/model_3_2_2_4-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_3_2_2_4-solution000001.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_2_2_4-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_2_2_4-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_3_2_2_4-solution000002.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_2_2_4-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_2_2_4-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_3_2_2_4-solution000003.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_2_2_4-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_2_2_4.eprime b/tests/exhaustive/basic/typed01/expected/model_3_2_2_4.eprime new file mode 100644 index 0000000000..c20b43202e --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_2_2_4.eprime @@ -0,0 +1,26 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..1) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +branching on + [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, + y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithDummy] +such that + 1 <= x_ExplicitVarSizeWithMarker_Marker /\ + (y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithMarker_Values[1]) + -> false, + 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, + x_ExplicitVarSizeWithDummy[1] != 2 -> + 1 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithDummy[1], + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithMarker_Values[1], + y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, + y_ExplicitVarSizeWithFlags_Flags[1] -> + y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = y_ExplicitVarSizeWithFlags_Values[1], + y_ExplicitVarSizeWithDummy[1] != 2 -> + y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = y_ExplicitVarSizeWithDummy[1] + diff --git a/tests/exhaustive/basic/typed01/expected/model_3_2_3_1-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_3_2_3_1-solution000001.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_2_3_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_2_3_1-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_3_2_3_1-solution000002.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_2_3_1-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_2_3_1-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_3_2_3_1-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_2_3_1-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_2_3_1.eprime b/tests/exhaustive/basic/typed01/expected/model_3_2_3_1.eprime new file mode 100644 index 0000000000..616ec55e21 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_2_3_1.eprime @@ -0,0 +1,16 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..1) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +find y_Occurrence: matrix indexed by [int(1)] of bool +branching on + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, y_Occurrence, y_ExplicitVarSizeWithDummy] +such that + 1 <= x_ExplicitVarSizeWithMarker_Marker /\ + (y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithMarker_Values[1]) + -> false, + 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, + y_Occurrence[1] -> y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = 1, + y_ExplicitVarSizeWithDummy[1] != 2 -> y_Occurrence[y_ExplicitVarSizeWithDummy[1]] + diff --git a/tests/exhaustive/basic/typed01/expected/model_3_2_3_2-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_3_2_3_2-solution000001.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_2_3_2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_2_3_2-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_3_2_3_2-solution000002.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_2_3_2-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_2_3_2-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_3_2_3_2-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_2_3_2-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_2_3_2.eprime b/tests/exhaustive/basic/typed01/expected/model_3_2_3_2.eprime new file mode 100644 index 0000000000..e176e88df7 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_2_3_2.eprime @@ -0,0 +1,12 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..1) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +branching on [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithDummy] +such that + 1 <= x_ExplicitVarSizeWithMarker_Marker /\ + (y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithMarker_Values[1]) + -> false, + 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1 + diff --git a/tests/exhaustive/basic/typed01/expected/model_3_2_3_3-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_3_2_3_3-solution000001.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_2_3_3-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_2_3_3-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_3_2_3_3-solution000002.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_2_3_3-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_2_3_3-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_3_2_3_3-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_2_3_3-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_2_3_3.eprime b/tests/exhaustive/basic/typed01/expected/model_3_2_3_3.eprime new file mode 100644 index 0000000000..30b4ef921e --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_2_3_3.eprime @@ -0,0 +1,21 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..1) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +find y_ExplicitVarSizeWithMarker_Marker: int(0..1) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +branching on + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithMarker_Marker, + y_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithDummy] +such that + 1 <= x_ExplicitVarSizeWithMarker_Marker /\ + (y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithMarker_Values[1]) + -> false, + 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, + 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, + 1 <= y_ExplicitVarSizeWithMarker_Marker -> + y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = y_ExplicitVarSizeWithMarker_Values[1], + y_ExplicitVarSizeWithDummy[1] != 2 -> + 1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = y_ExplicitVarSizeWithDummy[1] + diff --git a/tests/exhaustive/basic/typed01/expected/model_3_2_3_4-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_3_2_3_4-solution000001.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_2_3_4-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_2_3_4-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_3_2_3_4-solution000002.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_2_3_4-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_2_3_4-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_3_2_3_4-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_2_3_4-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_2_3_4.eprime b/tests/exhaustive/basic/typed01/expected/model_3_2_3_4.eprime new file mode 100644 index 0000000000..f373170319 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_2_3_4.eprime @@ -0,0 +1,21 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..1) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +branching on + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithFlags_Flags, + y_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithDummy] +such that + 1 <= x_ExplicitVarSizeWithMarker_Marker /\ + (y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithMarker_Values[1]) + -> false, + 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, + y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, + y_ExplicitVarSizeWithFlags_Flags[1] -> + y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = y_ExplicitVarSizeWithFlags_Values[1], + y_ExplicitVarSizeWithDummy[1] != 2 -> + y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = y_ExplicitVarSizeWithDummy[1] + diff --git a/tests/exhaustive/basic/typed01/expected/model_3_2_4_1-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_3_2_4_1-solution000001.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_2_4_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_2_4_1-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_3_2_4_1-solution000002.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_2_4_1-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_2_4_1-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_3_2_4_1-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_2_4_1-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_2_4_1.eprime b/tests/exhaustive/basic/typed01/expected/model_3_2_4_1.eprime new file mode 100644 index 0000000000..1c3f33bddc --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_2_4_1.eprime @@ -0,0 +1,25 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..1) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +find y_Occurrence: matrix indexed by [int(1)] of bool +branching on + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithMarker_Marker, + x_ExplicitVarSizeWithMarker_Values, y_Occurrence, y_ExplicitVarSizeWithDummy] +such that + 1 <= x_ExplicitVarSizeWithMarker_Marker /\ + (y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithMarker_Values[1]) + -> false, + 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, + x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, + x_ExplicitVarSizeWithFlags_Flags[1] -> + 1 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithFlags_Values[1], + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithMarker_Values[1], + y_Occurrence[1] -> y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = 1, + y_ExplicitVarSizeWithDummy[1] != 2 -> y_Occurrence[y_ExplicitVarSizeWithDummy[1]] + diff --git a/tests/exhaustive/basic/typed01/expected/model_3_2_4_2-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_3_2_4_2-solution000001.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_2_4_2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_2_4_2-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_3_2_4_2-solution000002.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_2_4_2-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_2_4_2-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_3_2_4_2-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_2_4_2-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_2_4_2.eprime b/tests/exhaustive/basic/typed01/expected/model_3_2_4_2.eprime new file mode 100644 index 0000000000..bfb78df1a5 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_2_4_2.eprime @@ -0,0 +1,22 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..1) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +branching on + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithMarker_Marker, + x_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithDummy] +such that + 1 <= x_ExplicitVarSizeWithMarker_Marker /\ + (y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithMarker_Values[1]) + -> false, + 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, + x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, + x_ExplicitVarSizeWithFlags_Flags[1] -> + 1 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithFlags_Values[1], + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithMarker_Values[1] + diff --git a/tests/exhaustive/basic/typed01/expected/model_3_2_4_3-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_3_2_4_3-solution000001.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_2_4_3-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_2_4_3-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_3_2_4_3-solution000002.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_2_4_3-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_2_4_3-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_3_2_4_3-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_2_4_3-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_2_4_3.eprime b/tests/exhaustive/basic/typed01/expected/model_3_2_4_3.eprime new file mode 100644 index 0000000000..2516063bdd --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_2_4_3.eprime @@ -0,0 +1,30 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..1) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +find y_ExplicitVarSizeWithMarker_Marker: int(0..1) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +branching on + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithMarker_Marker, + x_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values, + y_ExplicitVarSizeWithDummy] +such that + 1 <= x_ExplicitVarSizeWithMarker_Marker /\ + (y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithMarker_Values[1]) + -> false, + 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, + x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, + x_ExplicitVarSizeWithFlags_Flags[1] -> + 1 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithFlags_Values[1], + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithMarker_Values[1], + 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, + 1 <= y_ExplicitVarSizeWithMarker_Marker -> + y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = y_ExplicitVarSizeWithMarker_Values[1], + y_ExplicitVarSizeWithDummy[1] != 2 -> + 1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = y_ExplicitVarSizeWithDummy[1] + diff --git a/tests/exhaustive/basic/typed01/expected/model_3_2_4_4-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_3_2_4_4-solution000001.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_2_4_4-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_2_4_4-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_3_2_4_4-solution000002.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_2_4_4-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_2_4_4-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_3_2_4_4-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_2_4_4-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_2_4_4.eprime b/tests/exhaustive/basic/typed01/expected/model_3_2_4_4.eprime new file mode 100644 index 0000000000..3404c37403 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_2_4_4.eprime @@ -0,0 +1,30 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..1) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +branching on + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithMarker_Marker, + x_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values, + y_ExplicitVarSizeWithDummy] +such that + 1 <= x_ExplicitVarSizeWithMarker_Marker /\ + (y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithMarker_Values[1]) + -> false, + 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, + x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, + x_ExplicitVarSizeWithFlags_Flags[1] -> + 1 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithFlags_Values[1], + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithMarker_Values[1], + y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, + y_ExplicitVarSizeWithFlags_Flags[1] -> + y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = y_ExplicitVarSizeWithFlags_Values[1], + y_ExplicitVarSizeWithDummy[1] != 2 -> + y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = y_ExplicitVarSizeWithDummy[1] + diff --git a/tests/exhaustive/basic/typed01/expected/model_3_3_1_1-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_3_3_1_1-solution000001.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_3_1_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_3_1_1-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_3_3_1_1-solution000002.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_3_1_1-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_3_1_1-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_3_3_1_1-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_3_1_1-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_3_1_1.eprime b/tests/exhaustive/basic/typed01/expected/model_3_3_1_1.eprime new file mode 100644 index 0000000000..6d3b73f10c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_3_1_1.eprime @@ -0,0 +1,23 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..1) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +find x_Occurrence: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithMarker_Marker: int(0..1) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +find y_Occurrence: matrix indexed by [int(1)] of bool +branching on + [x_Occurrence, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, y_Occurrence, + y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values] +such that + 1 <= x_ExplicitVarSizeWithMarker_Marker /\ + (1 <= y_ExplicitVarSizeWithMarker_Marker /\ + y_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithMarker_Values[1]) + -> false, + 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, + 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, + x_Occurrence[1] -> 1 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[1] = 1, + 1 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[1]], + y_Occurrence[1] -> 1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = 1, + 1 <= y_ExplicitVarSizeWithMarker_Marker -> y_Occurrence[y_ExplicitVarSizeWithMarker_Values[1]] + diff --git a/tests/exhaustive/basic/typed01/expected/model_3_3_1_2-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_3_3_1_2-solution000001.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_3_1_2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_3_1_2-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_3_3_1_2-solution000002.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_3_1_2-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_3_1_2-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_3_3_1_2-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_3_1_2-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_3_1_2.eprime b/tests/exhaustive/basic/typed01/expected/model_3_3_1_2.eprime new file mode 100644 index 0000000000..44439955a6 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_3_1_2.eprime @@ -0,0 +1,25 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..1) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +find x_Occurrence: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithMarker_Marker: int(0..1) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +branching on + [x_Occurrence, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithDummy, + y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values] +such that + 1 <= x_ExplicitVarSizeWithMarker_Marker /\ + (1 <= y_ExplicitVarSizeWithMarker_Marker /\ + y_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithMarker_Values[1]) + -> false, + 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, + 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, + x_Occurrence[1] -> 1 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[1] = 1, + 1 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[1]], + y_ExplicitVarSizeWithDummy[1] != 2 -> + 1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = y_ExplicitVarSizeWithDummy[1], + 1 <= y_ExplicitVarSizeWithMarker_Marker -> + y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = y_ExplicitVarSizeWithMarker_Values[1] + diff --git a/tests/exhaustive/basic/typed01/expected/model_3_3_1_3-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_3_3_1_3-solution000001.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_3_1_3-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_3_1_3-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_3_3_1_3-solution000002.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_3_1_3-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_3_1_3-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_3_3_1_3-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_3_1_3-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_3_1_3.eprime b/tests/exhaustive/basic/typed01/expected/model_3_3_1_3.eprime new file mode 100644 index 0000000000..2d0516dbc1 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_3_1_3.eprime @@ -0,0 +1,20 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..1) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +find x_Occurrence: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithMarker_Marker: int(0..1) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +branching on + [x_Occurrence, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, + y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values] +such that + 1 <= x_ExplicitVarSizeWithMarker_Marker /\ + (1 <= y_ExplicitVarSizeWithMarker_Marker /\ + y_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithMarker_Values[1]) + -> false, + 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, + 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, + x_Occurrence[1] -> 1 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[1] = 1, + 1 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[1]] + diff --git a/tests/exhaustive/basic/typed01/expected/model_3_3_1_4-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_3_3_1_4-solution000001.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_3_1_4-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_3_1_4-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_3_3_1_4-solution000002.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_3_1_4-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_3_1_4-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_3_3_1_4-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_3_1_4-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_3_1_4.eprime b/tests/exhaustive/basic/typed01/expected/model_3_3_1_4.eprime new file mode 100644 index 0000000000..13374c77fe --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_3_1_4.eprime @@ -0,0 +1,29 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..1) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +find x_Occurrence: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithMarker_Marker: int(0..1) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +branching on + [x_Occurrence, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, + y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithMarker_Marker, + y_ExplicitVarSizeWithMarker_Values] +such that + 1 <= x_ExplicitVarSizeWithMarker_Marker /\ + (1 <= y_ExplicitVarSizeWithMarker_Marker /\ + y_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithMarker_Values[1]) + -> false, + 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, + 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, + x_Occurrence[1] -> 1 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[1] = 1, + 1 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[1]], + y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, + y_ExplicitVarSizeWithFlags_Flags[1] -> + 1 <= y_ExplicitVarSizeWithMarker_Marker /\ + y_ExplicitVarSizeWithMarker_Values[1] = y_ExplicitVarSizeWithFlags_Values[1], + 1 <= y_ExplicitVarSizeWithMarker_Marker -> + y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = y_ExplicitVarSizeWithMarker_Values[1] + diff --git a/tests/exhaustive/basic/typed01/expected/model_3_3_2_1-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_3_3_2_1-solution000001.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_3_2_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_3_2_1-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_3_3_2_1-solution000002.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_3_2_1-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_3_2_1-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_3_3_2_1-solution000003.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_3_2_1-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_3_2_1.eprime b/tests/exhaustive/basic/typed01/expected/model_3_3_2_1.eprime new file mode 100644 index 0000000000..dc91372e8c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_3_2_1.eprime @@ -0,0 +1,25 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..1) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +find y_ExplicitVarSizeWithMarker_Marker: int(0..1) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +find y_Occurrence: matrix indexed by [int(1)] of bool +branching on + [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, y_Occurrence, + y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values] +such that + 1 <= x_ExplicitVarSizeWithMarker_Marker /\ + (1 <= y_ExplicitVarSizeWithMarker_Marker /\ + y_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithMarker_Values[1]) + -> false, + 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, + 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, + x_ExplicitVarSizeWithDummy[1] != 2 -> + 1 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithDummy[1], + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithMarker_Values[1], + y_Occurrence[1] -> 1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = 1, + 1 <= y_ExplicitVarSizeWithMarker_Marker -> y_Occurrence[y_ExplicitVarSizeWithMarker_Values[1]] + diff --git a/tests/exhaustive/basic/typed01/expected/model_3_3_2_2-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_3_3_2_2-solution000001.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_3_2_2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_3_2_2-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_3_3_2_2-solution000002.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_3_2_2-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_3_2_2-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_3_3_2_2-solution000003.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_3_2_2-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_3_2_2.eprime b/tests/exhaustive/basic/typed01/expected/model_3_3_2_2.eprime new file mode 100644 index 0000000000..f5fc445a12 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_3_2_2.eprime @@ -0,0 +1,27 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..1) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +find y_ExplicitVarSizeWithMarker_Marker: int(0..1) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +branching on + [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, + y_ExplicitVarSizeWithDummy, y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values] +such that + 1 <= x_ExplicitVarSizeWithMarker_Marker /\ + (1 <= y_ExplicitVarSizeWithMarker_Marker /\ + y_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithMarker_Values[1]) + -> false, + 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, + 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, + x_ExplicitVarSizeWithDummy[1] != 2 -> + 1 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithDummy[1], + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithMarker_Values[1], + y_ExplicitVarSizeWithDummy[1] != 2 -> + 1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = y_ExplicitVarSizeWithDummy[1], + 1 <= y_ExplicitVarSizeWithMarker_Marker -> + y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = y_ExplicitVarSizeWithMarker_Values[1] + diff --git a/tests/exhaustive/basic/typed01/expected/model_3_3_2_3-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_3_3_2_3-solution000001.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_3_2_3-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_3_2_3-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_3_3_2_3-solution000002.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_3_2_3-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_3_2_3-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_3_3_2_3-solution000003.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_3_2_3-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_3_2_3.eprime b/tests/exhaustive/basic/typed01/expected/model_3_3_2_3.eprime new file mode 100644 index 0000000000..68281a2f9a --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_3_2_3.eprime @@ -0,0 +1,22 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..1) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +find y_ExplicitVarSizeWithMarker_Marker: int(0..1) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +branching on + [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, + y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values] +such that + 1 <= x_ExplicitVarSizeWithMarker_Marker /\ + (1 <= y_ExplicitVarSizeWithMarker_Marker /\ + y_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithMarker_Values[1]) + -> false, + 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, + 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, + x_ExplicitVarSizeWithDummy[1] != 2 -> + 1 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithDummy[1], + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithMarker_Values[1] + diff --git a/tests/exhaustive/basic/typed01/expected/model_3_3_2_4-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_3_3_2_4-solution000001.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_3_2_4-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_3_2_4-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_3_3_2_4-solution000002.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_3_2_4-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_3_2_4-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_3_3_2_4-solution000003.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_3_2_4-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_3_2_4.eprime b/tests/exhaustive/basic/typed01/expected/model_3_3_2_4.eprime new file mode 100644 index 0000000000..7d7326d650 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_3_2_4.eprime @@ -0,0 +1,31 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..1) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +find y_ExplicitVarSizeWithMarker_Marker: int(0..1) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +branching on + [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, + y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithMarker_Marker, + y_ExplicitVarSizeWithMarker_Values] +such that + 1 <= x_ExplicitVarSizeWithMarker_Marker /\ + (1 <= y_ExplicitVarSizeWithMarker_Marker /\ + y_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithMarker_Values[1]) + -> false, + 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, + 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, + x_ExplicitVarSizeWithDummy[1] != 2 -> + 1 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithDummy[1], + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithMarker_Values[1], + y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, + y_ExplicitVarSizeWithFlags_Flags[1] -> + 1 <= y_ExplicitVarSizeWithMarker_Marker /\ + y_ExplicitVarSizeWithMarker_Values[1] = y_ExplicitVarSizeWithFlags_Values[1], + 1 <= y_ExplicitVarSizeWithMarker_Marker -> + y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = y_ExplicitVarSizeWithMarker_Values[1] + diff --git a/tests/exhaustive/basic/typed01/expected/model_3_3_3_1-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_3_3_3_1-solution000001.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_3_3_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_3_3_1-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_3_3_3_1-solution000002.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_3_3_1-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_3_3_1-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_3_3_3_1-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_3_3_1-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_3_3_1.eprime b/tests/exhaustive/basic/typed01/expected/model_3_3_3_1.eprime new file mode 100644 index 0000000000..8c1a3dd051 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_3_3_1.eprime @@ -0,0 +1,20 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..1) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +find y_ExplicitVarSizeWithMarker_Marker: int(0..1) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +find y_Occurrence: matrix indexed by [int(1)] of bool +branching on + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, y_Occurrence, + y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values] +such that + 1 <= x_ExplicitVarSizeWithMarker_Marker /\ + (1 <= y_ExplicitVarSizeWithMarker_Marker /\ + y_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithMarker_Values[1]) + -> false, + 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, + 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, + y_Occurrence[1] -> 1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = 1, + 1 <= y_ExplicitVarSizeWithMarker_Marker -> y_Occurrence[y_ExplicitVarSizeWithMarker_Values[1]] + diff --git a/tests/exhaustive/basic/typed01/expected/model_3_3_3_2-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_3_3_3_2-solution000001.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_3_3_2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_3_3_2-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_3_3_3_2-solution000002.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_3_3_2-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_3_3_2-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_3_3_3_2-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_3_3_2-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_3_3_2.eprime b/tests/exhaustive/basic/typed01/expected/model_3_3_3_2.eprime new file mode 100644 index 0000000000..ef312ab142 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_3_3_2.eprime @@ -0,0 +1,22 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..1) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +find y_ExplicitVarSizeWithMarker_Marker: int(0..1) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +branching on + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithDummy, + y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values] +such that + 1 <= x_ExplicitVarSizeWithMarker_Marker /\ + (1 <= y_ExplicitVarSizeWithMarker_Marker /\ + y_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithMarker_Values[1]) + -> false, + 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, + 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, + y_ExplicitVarSizeWithDummy[1] != 2 -> + 1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = y_ExplicitVarSizeWithDummy[1], + 1 <= y_ExplicitVarSizeWithMarker_Marker -> + y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = y_ExplicitVarSizeWithMarker_Values[1] + diff --git a/tests/exhaustive/basic/typed01/expected/model_3_3_3_3-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_3_3_3_3-solution000001.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_3_3_3-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_3_3_3-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_3_3_3_3-solution000002.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_3_3_3-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_3_3_3-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_3_3_3_3-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_3_3_3-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_3_3_3.eprime b/tests/exhaustive/basic/typed01/expected/model_3_3_3_3.eprime new file mode 100644 index 0000000000..51c528ccb0 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_3_3_3.eprime @@ -0,0 +1,17 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..1) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +find y_ExplicitVarSizeWithMarker_Marker: int(0..1) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +branching on + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithMarker_Marker, + y_ExplicitVarSizeWithMarker_Values] +such that + 1 <= x_ExplicitVarSizeWithMarker_Marker /\ + (1 <= y_ExplicitVarSizeWithMarker_Marker /\ + y_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithMarker_Values[1]) + -> false, + 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, + 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1 + diff --git a/tests/exhaustive/basic/typed01/expected/model_3_3_3_4-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_3_3_3_4-solution000001.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_3_3_4-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_3_3_4-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_3_3_3_4-solution000002.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_3_3_4-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_3_3_4-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_3_3_3_4-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_3_3_4-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_3_3_4.eprime b/tests/exhaustive/basic/typed01/expected/model_3_3_3_4.eprime new file mode 100644 index 0000000000..5bfbda5c04 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_3_3_4.eprime @@ -0,0 +1,25 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..1) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +find y_ExplicitVarSizeWithMarker_Marker: int(0..1) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +branching on + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithFlags_Flags, + y_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values] +such that + 1 <= x_ExplicitVarSizeWithMarker_Marker /\ + (1 <= y_ExplicitVarSizeWithMarker_Marker /\ + y_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithMarker_Values[1]) + -> false, + 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, + 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, + y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, + y_ExplicitVarSizeWithFlags_Flags[1] -> + 1 <= y_ExplicitVarSizeWithMarker_Marker /\ + y_ExplicitVarSizeWithMarker_Values[1] = y_ExplicitVarSizeWithFlags_Values[1], + 1 <= y_ExplicitVarSizeWithMarker_Marker -> + y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = y_ExplicitVarSizeWithMarker_Values[1] + diff --git a/tests/exhaustive/basic/typed01/expected/model_3_3_4_1-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_3_3_4_1-solution000001.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_3_4_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_3_4_1-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_3_3_4_1-solution000002.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_3_4_1-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_3_4_1-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_3_3_4_1-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_3_4_1-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_3_4_1.eprime b/tests/exhaustive/basic/typed01/expected/model_3_3_4_1.eprime new file mode 100644 index 0000000000..78ce007c35 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_3_4_1.eprime @@ -0,0 +1,29 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..1) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +find y_ExplicitVarSizeWithMarker_Marker: int(0..1) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +find y_Occurrence: matrix indexed by [int(1)] of bool +branching on + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithMarker_Marker, + x_ExplicitVarSizeWithMarker_Values, y_Occurrence, y_ExplicitVarSizeWithMarker_Marker, + y_ExplicitVarSizeWithMarker_Values] +such that + 1 <= x_ExplicitVarSizeWithMarker_Marker /\ + (1 <= y_ExplicitVarSizeWithMarker_Marker /\ + y_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithMarker_Values[1]) + -> false, + 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, + 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, + x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, + x_ExplicitVarSizeWithFlags_Flags[1] -> + 1 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithFlags_Values[1], + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithMarker_Values[1], + y_Occurrence[1] -> 1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = 1, + 1 <= y_ExplicitVarSizeWithMarker_Marker -> y_Occurrence[y_ExplicitVarSizeWithMarker_Values[1]] + diff --git a/tests/exhaustive/basic/typed01/expected/model_3_3_4_2-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_3_3_4_2-solution000001.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_3_4_2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_3_4_2-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_3_3_4_2-solution000002.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_3_4_2-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_3_4_2-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_3_3_4_2-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_3_4_2-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_3_4_2.eprime b/tests/exhaustive/basic/typed01/expected/model_3_3_4_2.eprime new file mode 100644 index 0000000000..2caba48cd3 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_3_4_2.eprime @@ -0,0 +1,31 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..1) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +find y_ExplicitVarSizeWithMarker_Marker: int(0..1) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +branching on + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithMarker_Marker, + x_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithDummy, y_ExplicitVarSizeWithMarker_Marker, + y_ExplicitVarSizeWithMarker_Values] +such that + 1 <= x_ExplicitVarSizeWithMarker_Marker /\ + (1 <= y_ExplicitVarSizeWithMarker_Marker /\ + y_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithMarker_Values[1]) + -> false, + 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, + 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, + x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, + x_ExplicitVarSizeWithFlags_Flags[1] -> + 1 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithFlags_Values[1], + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithMarker_Values[1], + y_ExplicitVarSizeWithDummy[1] != 2 -> + 1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = y_ExplicitVarSizeWithDummy[1], + 1 <= y_ExplicitVarSizeWithMarker_Marker -> + y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = y_ExplicitVarSizeWithMarker_Values[1] + diff --git a/tests/exhaustive/basic/typed01/expected/model_3_3_4_3-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_3_3_4_3-solution000001.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_3_4_3-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_3_4_3-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_3_3_4_3-solution000002.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_3_4_3-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_3_4_3-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_3_3_4_3-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_3_4_3-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_3_4_3.eprime b/tests/exhaustive/basic/typed01/expected/model_3_3_4_3.eprime new file mode 100644 index 0000000000..a85c4917ee --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_3_4_3.eprime @@ -0,0 +1,25 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..1) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +find y_ExplicitVarSizeWithMarker_Marker: int(0..1) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +branching on + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithMarker_Marker, + x_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values] +such that + 1 <= x_ExplicitVarSizeWithMarker_Marker /\ + (1 <= y_ExplicitVarSizeWithMarker_Marker /\ + y_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithMarker_Values[1]) + -> false, + 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, + 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, + x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, + x_ExplicitVarSizeWithFlags_Flags[1] -> + 1 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithFlags_Values[1], + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithMarker_Values[1] + diff --git a/tests/exhaustive/basic/typed01/expected/model_3_3_4_4-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_3_3_4_4-solution000001.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_3_4_4-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_3_4_4-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_3_3_4_4-solution000002.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_3_4_4-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_3_4_4-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_3_3_4_4-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_3_4_4-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_3_4_4.eprime b/tests/exhaustive/basic/typed01/expected/model_3_3_4_4.eprime new file mode 100644 index 0000000000..422f3c0a9c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_3_4_4.eprime @@ -0,0 +1,34 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..1) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +find y_ExplicitVarSizeWithMarker_Marker: int(0..1) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +branching on + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithMarker_Marker, + x_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values, + y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values] +such that + 1 <= x_ExplicitVarSizeWithMarker_Marker /\ + (1 <= y_ExplicitVarSizeWithMarker_Marker /\ + y_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithMarker_Values[1]) + -> false, + 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, + 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, + x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, + x_ExplicitVarSizeWithFlags_Flags[1] -> + 1 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithFlags_Values[1], + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithMarker_Values[1], + y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, + y_ExplicitVarSizeWithFlags_Flags[1] -> + 1 <= y_ExplicitVarSizeWithMarker_Marker /\ + y_ExplicitVarSizeWithMarker_Values[1] = y_ExplicitVarSizeWithFlags_Values[1], + 1 <= y_ExplicitVarSizeWithMarker_Marker -> + y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = y_ExplicitVarSizeWithMarker_Values[1] + diff --git a/tests/exhaustive/basic/typed01/expected/model_3_4_1_1-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_3_4_1_1-solution000001.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_4_1_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_4_1_1-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_3_4_1_1-solution000002.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_4_1_1-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_4_1_1-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_3_4_1_1-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_4_1_1-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_4_1_1.eprime b/tests/exhaustive/basic/typed01/expected/model_3_4_1_1.eprime new file mode 100644 index 0000000000..e866a42f00 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_4_1_1.eprime @@ -0,0 +1,23 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..1) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +find x_Occurrence: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +find y_Occurrence: matrix indexed by [int(1)] of bool +branching on + [x_Occurrence, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, y_Occurrence, + y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values] +such that + 1 <= x_ExplicitVarSizeWithMarker_Marker /\ + (y_ExplicitVarSizeWithFlags_Flags[1] /\ + y_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithMarker_Values[1]) + -> false, + 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, + y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, + x_Occurrence[1] -> 1 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[1] = 1, + 1 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[1]], + y_Occurrence[1] -> y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = 1, + y_ExplicitVarSizeWithFlags_Flags[1] -> y_Occurrence[y_ExplicitVarSizeWithFlags_Values[1]] + diff --git a/tests/exhaustive/basic/typed01/expected/model_3_4_1_2-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_3_4_1_2-solution000001.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_4_1_2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_4_1_2-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_3_4_1_2-solution000002.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_4_1_2-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_4_1_2-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_3_4_1_2-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_4_1_2-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_4_1_2.eprime b/tests/exhaustive/basic/typed01/expected/model_3_4_1_2.eprime new file mode 100644 index 0000000000..5eb12bb42d --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_4_1_2.eprime @@ -0,0 +1,25 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..1) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +find x_Occurrence: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +branching on + [x_Occurrence, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithDummy, + y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values] +such that + 1 <= x_ExplicitVarSizeWithMarker_Marker /\ + (y_ExplicitVarSizeWithFlags_Flags[1] /\ + y_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithMarker_Values[1]) + -> false, + 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, + y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, + x_Occurrence[1] -> 1 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[1] = 1, + 1 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[1]], + y_ExplicitVarSizeWithDummy[1] != 2 -> + y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = y_ExplicitVarSizeWithDummy[1], + y_ExplicitVarSizeWithFlags_Flags[1] -> + y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = y_ExplicitVarSizeWithFlags_Values[1] + diff --git a/tests/exhaustive/basic/typed01/expected/model_3_4_1_3-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_3_4_1_3-solution000001.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_4_1_3-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_4_1_3-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_3_4_1_3-solution000002.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_4_1_3-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_4_1_3-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_3_4_1_3-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_4_1_3-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_4_1_3.eprime b/tests/exhaustive/basic/typed01/expected/model_3_4_1_3.eprime new file mode 100644 index 0000000000..2ee31af242 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_4_1_3.eprime @@ -0,0 +1,29 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..1) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +find x_Occurrence: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +find y_ExplicitVarSizeWithMarker_Marker: int(0..1) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +branching on + [x_Occurrence, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, + y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithFlags_Flags, + y_ExplicitVarSizeWithFlags_Values] +such that + 1 <= x_ExplicitVarSizeWithMarker_Marker /\ + (y_ExplicitVarSizeWithFlags_Flags[1] /\ + y_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithMarker_Values[1]) + -> false, + 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, + y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, + x_Occurrence[1] -> 1 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[1] = 1, + 1 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[1]], + 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, + 1 <= y_ExplicitVarSizeWithMarker_Marker -> + y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = y_ExplicitVarSizeWithMarker_Values[1], + y_ExplicitVarSizeWithFlags_Flags[1] -> + 1 <= y_ExplicitVarSizeWithMarker_Marker /\ + y_ExplicitVarSizeWithMarker_Values[1] = y_ExplicitVarSizeWithFlags_Values[1] + diff --git a/tests/exhaustive/basic/typed01/expected/model_3_4_1_4-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_3_4_1_4-solution000001.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_4_1_4-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_4_1_4-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_3_4_1_4-solution000002.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_4_1_4-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_4_1_4-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_3_4_1_4-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_4_1_4-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_4_1_4.eprime b/tests/exhaustive/basic/typed01/expected/model_3_4_1_4.eprime new file mode 100644 index 0000000000..0da6db7905 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_4_1_4.eprime @@ -0,0 +1,20 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..1) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +find x_Occurrence: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +branching on + [x_Occurrence, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, + y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values] +such that + 1 <= x_ExplicitVarSizeWithMarker_Marker /\ + (y_ExplicitVarSizeWithFlags_Flags[1] /\ + y_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithMarker_Values[1]) + -> false, + 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, + y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, + x_Occurrence[1] -> 1 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[1] = 1, + 1 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[1]] + diff --git a/tests/exhaustive/basic/typed01/expected/model_3_4_2_1-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_3_4_2_1-solution000001.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_4_2_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_4_2_1-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_3_4_2_1-solution000002.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_4_2_1-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_4_2_1-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_3_4_2_1-solution000003.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_4_2_1-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_4_2_1.eprime b/tests/exhaustive/basic/typed01/expected/model_3_4_2_1.eprime new file mode 100644 index 0000000000..3ba13f3d49 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_4_2_1.eprime @@ -0,0 +1,25 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..1) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +find y_Occurrence: matrix indexed by [int(1)] of bool +branching on + [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, y_Occurrence, + y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values] +such that + 1 <= x_ExplicitVarSizeWithMarker_Marker /\ + (y_ExplicitVarSizeWithFlags_Flags[1] /\ + y_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithMarker_Values[1]) + -> false, + 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, + y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, + x_ExplicitVarSizeWithDummy[1] != 2 -> + 1 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithDummy[1], + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithMarker_Values[1], + y_Occurrence[1] -> y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = 1, + y_ExplicitVarSizeWithFlags_Flags[1] -> y_Occurrence[y_ExplicitVarSizeWithFlags_Values[1]] + diff --git a/tests/exhaustive/basic/typed01/expected/model_3_4_2_2-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_3_4_2_2-solution000001.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_4_2_2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_4_2_2-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_3_4_2_2-solution000002.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_4_2_2-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_4_2_2-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_3_4_2_2-solution000003.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_4_2_2-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_4_2_2.eprime b/tests/exhaustive/basic/typed01/expected/model_3_4_2_2.eprime new file mode 100644 index 0000000000..493690aa87 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_4_2_2.eprime @@ -0,0 +1,27 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..1) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +branching on + [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, + y_ExplicitVarSizeWithDummy, y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values] +such that + 1 <= x_ExplicitVarSizeWithMarker_Marker /\ + (y_ExplicitVarSizeWithFlags_Flags[1] /\ + y_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithMarker_Values[1]) + -> false, + 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, + y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, + x_ExplicitVarSizeWithDummy[1] != 2 -> + 1 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithDummy[1], + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithMarker_Values[1], + y_ExplicitVarSizeWithDummy[1] != 2 -> + y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = y_ExplicitVarSizeWithDummy[1], + y_ExplicitVarSizeWithFlags_Flags[1] -> + y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = y_ExplicitVarSizeWithFlags_Values[1] + diff --git a/tests/exhaustive/basic/typed01/expected/model_3_4_2_3-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_3_4_2_3-solution000001.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_4_2_3-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_4_2_3-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_3_4_2_3-solution000002.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_4_2_3-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_4_2_3-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_3_4_2_3-solution000003.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_4_2_3-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_4_2_3.eprime b/tests/exhaustive/basic/typed01/expected/model_3_4_2_3.eprime new file mode 100644 index 0000000000..1b189dfc27 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_4_2_3.eprime @@ -0,0 +1,31 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..1) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +find y_ExplicitVarSizeWithMarker_Marker: int(0..1) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +branching on + [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, + y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithFlags_Flags, + y_ExplicitVarSizeWithFlags_Values] +such that + 1 <= x_ExplicitVarSizeWithMarker_Marker /\ + (y_ExplicitVarSizeWithFlags_Flags[1] /\ + y_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithMarker_Values[1]) + -> false, + 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, + y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, + x_ExplicitVarSizeWithDummy[1] != 2 -> + 1 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithDummy[1], + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithMarker_Values[1], + 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, + 1 <= y_ExplicitVarSizeWithMarker_Marker -> + y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = y_ExplicitVarSizeWithMarker_Values[1], + y_ExplicitVarSizeWithFlags_Flags[1] -> + 1 <= y_ExplicitVarSizeWithMarker_Marker /\ + y_ExplicitVarSizeWithMarker_Values[1] = y_ExplicitVarSizeWithFlags_Values[1] + diff --git a/tests/exhaustive/basic/typed01/expected/model_3_4_2_4-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_3_4_2_4-solution000001.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_4_2_4-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_4_2_4-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_3_4_2_4-solution000002.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_4_2_4-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_4_2_4-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_3_4_2_4-solution000003.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_4_2_4-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_4_2_4.eprime b/tests/exhaustive/basic/typed01/expected/model_3_4_2_4.eprime new file mode 100644 index 0000000000..4a02c74755 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_4_2_4.eprime @@ -0,0 +1,22 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..1) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +branching on + [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, + y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values] +such that + 1 <= x_ExplicitVarSizeWithMarker_Marker /\ + (y_ExplicitVarSizeWithFlags_Flags[1] /\ + y_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithMarker_Values[1]) + -> false, + 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, + y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, + x_ExplicitVarSizeWithDummy[1] != 2 -> + 1 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithDummy[1], + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithMarker_Values[1] + diff --git a/tests/exhaustive/basic/typed01/expected/model_3_4_3_1-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_3_4_3_1-solution000001.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_4_3_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_4_3_1-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_3_4_3_1-solution000002.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_4_3_1-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_4_3_1-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_3_4_3_1-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_4_3_1-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_4_3_1.eprime b/tests/exhaustive/basic/typed01/expected/model_3_4_3_1.eprime new file mode 100644 index 0000000000..957e3308a9 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_4_3_1.eprime @@ -0,0 +1,20 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..1) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +find y_Occurrence: matrix indexed by [int(1)] of bool +branching on + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, y_Occurrence, + y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values] +such that + 1 <= x_ExplicitVarSizeWithMarker_Marker /\ + (y_ExplicitVarSizeWithFlags_Flags[1] /\ + y_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithMarker_Values[1]) + -> false, + 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, + y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, + y_Occurrence[1] -> y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = 1, + y_ExplicitVarSizeWithFlags_Flags[1] -> y_Occurrence[y_ExplicitVarSizeWithFlags_Values[1]] + diff --git a/tests/exhaustive/basic/typed01/expected/model_3_4_3_2-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_3_4_3_2-solution000001.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_4_3_2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_4_3_2-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_3_4_3_2-solution000002.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_4_3_2-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_4_3_2-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_3_4_3_2-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_4_3_2-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_4_3_2.eprime b/tests/exhaustive/basic/typed01/expected/model_3_4_3_2.eprime new file mode 100644 index 0000000000..d785a45f2e --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_4_3_2.eprime @@ -0,0 +1,22 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..1) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +branching on + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithDummy, + y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values] +such that + 1 <= x_ExplicitVarSizeWithMarker_Marker /\ + (y_ExplicitVarSizeWithFlags_Flags[1] /\ + y_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithMarker_Values[1]) + -> false, + 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, + y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, + y_ExplicitVarSizeWithDummy[1] != 2 -> + y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = y_ExplicitVarSizeWithDummy[1], + y_ExplicitVarSizeWithFlags_Flags[1] -> + y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = y_ExplicitVarSizeWithFlags_Values[1] + diff --git a/tests/exhaustive/basic/typed01/expected/model_3_4_3_3-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_3_4_3_3-solution000001.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_4_3_3-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_4_3_3-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_3_4_3_3-solution000002.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_4_3_3-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_4_3_3-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_3_4_3_3-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_4_3_3-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_4_3_3.eprime b/tests/exhaustive/basic/typed01/expected/model_3_4_3_3.eprime new file mode 100644 index 0000000000..d07a94b90a --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_4_3_3.eprime @@ -0,0 +1,25 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..1) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +find y_ExplicitVarSizeWithMarker_Marker: int(0..1) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +branching on + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithMarker_Marker, + y_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values] +such that + 1 <= x_ExplicitVarSizeWithMarker_Marker /\ + (y_ExplicitVarSizeWithFlags_Flags[1] /\ + y_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithMarker_Values[1]) + -> false, + 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, + y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, + 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, + 1 <= y_ExplicitVarSizeWithMarker_Marker -> + y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = y_ExplicitVarSizeWithMarker_Values[1], + y_ExplicitVarSizeWithFlags_Flags[1] -> + 1 <= y_ExplicitVarSizeWithMarker_Marker /\ + y_ExplicitVarSizeWithMarker_Values[1] = y_ExplicitVarSizeWithFlags_Values[1] + diff --git a/tests/exhaustive/basic/typed01/expected/model_3_4_3_4-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_3_4_3_4-solution000001.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_4_3_4-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_4_3_4-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_3_4_3_4-solution000002.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_4_3_4-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_4_3_4-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_3_4_3_4-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_4_3_4-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_4_3_4.eprime b/tests/exhaustive/basic/typed01/expected/model_3_4_3_4.eprime new file mode 100644 index 0000000000..bd5f878d61 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_4_3_4.eprime @@ -0,0 +1,17 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..1) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +branching on + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithFlags_Flags, + y_ExplicitVarSizeWithFlags_Values] +such that + 1 <= x_ExplicitVarSizeWithMarker_Marker /\ + (y_ExplicitVarSizeWithFlags_Flags[1] /\ + y_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithMarker_Values[1]) + -> false, + 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, + y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1 + diff --git a/tests/exhaustive/basic/typed01/expected/model_3_4_4_1-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_3_4_4_1-solution000001.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_4_4_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_4_4_1-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_3_4_4_1-solution000002.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_4_4_1-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_4_4_1-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_3_4_4_1-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_4_4_1-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_4_4_1.eprime b/tests/exhaustive/basic/typed01/expected/model_3_4_4_1.eprime new file mode 100644 index 0000000000..bd8649ff85 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_4_4_1.eprime @@ -0,0 +1,29 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..1) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +find y_Occurrence: matrix indexed by [int(1)] of bool +branching on + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithMarker_Marker, + x_ExplicitVarSizeWithMarker_Values, y_Occurrence, y_ExplicitVarSizeWithFlags_Flags, + y_ExplicitVarSizeWithFlags_Values] +such that + 1 <= x_ExplicitVarSizeWithMarker_Marker /\ + (y_ExplicitVarSizeWithFlags_Flags[1] /\ + y_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithMarker_Values[1]) + -> false, + 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, + y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, + x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, + x_ExplicitVarSizeWithFlags_Flags[1] -> + 1 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithFlags_Values[1], + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithMarker_Values[1], + y_Occurrence[1] -> y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = 1, + y_ExplicitVarSizeWithFlags_Flags[1] -> y_Occurrence[y_ExplicitVarSizeWithFlags_Values[1]] + diff --git a/tests/exhaustive/basic/typed01/expected/model_3_4_4_2-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_3_4_4_2-solution000001.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_4_4_2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_4_4_2-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_3_4_4_2-solution000002.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_4_4_2-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_4_4_2-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_3_4_4_2-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_4_4_2-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_4_4_2.eprime b/tests/exhaustive/basic/typed01/expected/model_3_4_4_2.eprime new file mode 100644 index 0000000000..28a0d6651c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_4_4_2.eprime @@ -0,0 +1,31 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..1) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +branching on + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithMarker_Marker, + x_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithDummy, y_ExplicitVarSizeWithFlags_Flags, + y_ExplicitVarSizeWithFlags_Values] +such that + 1 <= x_ExplicitVarSizeWithMarker_Marker /\ + (y_ExplicitVarSizeWithFlags_Flags[1] /\ + y_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithMarker_Values[1]) + -> false, + 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, + y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, + x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, + x_ExplicitVarSizeWithFlags_Flags[1] -> + 1 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithFlags_Values[1], + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithMarker_Values[1], + y_ExplicitVarSizeWithDummy[1] != 2 -> + y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = y_ExplicitVarSizeWithDummy[1], + y_ExplicitVarSizeWithFlags_Flags[1] -> + y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = y_ExplicitVarSizeWithFlags_Values[1] + diff --git a/tests/exhaustive/basic/typed01/expected/model_3_4_4_3-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_3_4_4_3-solution000001.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_4_4_3-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_4_4_3-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_3_4_4_3-solution000002.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_4_4_3-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_4_4_3-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_3_4_4_3-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_4_4_3-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_4_4_3.eprime b/tests/exhaustive/basic/typed01/expected/model_3_4_4_3.eprime new file mode 100644 index 0000000000..3211485200 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_4_4_3.eprime @@ -0,0 +1,34 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..1) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +find y_ExplicitVarSizeWithMarker_Marker: int(0..1) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +branching on + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithMarker_Marker, + x_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values, + y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values] +such that + 1 <= x_ExplicitVarSizeWithMarker_Marker /\ + (y_ExplicitVarSizeWithFlags_Flags[1] /\ + y_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithMarker_Values[1]) + -> false, + 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, + y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, + x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, + x_ExplicitVarSizeWithFlags_Flags[1] -> + 1 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithFlags_Values[1], + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithMarker_Values[1], + 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, + 1 <= y_ExplicitVarSizeWithMarker_Marker -> + y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = y_ExplicitVarSizeWithMarker_Values[1], + y_ExplicitVarSizeWithFlags_Flags[1] -> + 1 <= y_ExplicitVarSizeWithMarker_Marker /\ + y_ExplicitVarSizeWithMarker_Values[1] = y_ExplicitVarSizeWithFlags_Values[1] + diff --git a/tests/exhaustive/basic/typed01/expected/model_3_4_4_4-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_3_4_4_4-solution000001.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_4_4_4-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_4_4_4-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_3_4_4_4-solution000002.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_4_4_4-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_4_4_4-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_3_4_4_4-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_4_4_4-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_3_4_4_4.eprime b/tests/exhaustive/basic/typed01/expected/model_3_4_4_4.eprime new file mode 100644 index 0000000000..0fd26730a3 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_3_4_4_4.eprime @@ -0,0 +1,25 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithMarker_Marker: int(0..1) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +branching on + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithMarker_Marker, + x_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values] +such that + 1 <= x_ExplicitVarSizeWithMarker_Marker /\ + (y_ExplicitVarSizeWithFlags_Flags[1] /\ + y_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithMarker_Values[1]) + -> false, + 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, + y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, + x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, + x_ExplicitVarSizeWithFlags_Flags[1] -> + 1 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithFlags_Values[1], + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithMarker_Values[1] + diff --git a/tests/exhaustive/basic/typed01/expected/model_4_1_1_1-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_4_1_1_1-solution000001.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_1_1_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_1_1_1-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_4_1_1_1-solution000002.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_1_1_1-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_1_1_1-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_4_1_1_1-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_1_1_1-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_1_1_1.eprime b/tests/exhaustive/basic/typed01/expected/model_4_1_1_1.eprime new file mode 100644 index 0000000000..146f1578b5 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_1_1_1.eprime @@ -0,0 +1,13 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +find x_Occurrence: matrix indexed by [int(1)] of bool +find y_Occurrence: matrix indexed by [int(1)] of bool +branching on [x_Occurrence, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, y_Occurrence] +such that + x_ExplicitVarSizeWithFlags_Flags[1] /\ y_Occurrence[x_ExplicitVarSizeWithFlags_Values[1]] -> false, + x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, + x_Occurrence[1] -> x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = 1, + x_ExplicitVarSizeWithFlags_Flags[1] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[1]] + diff --git a/tests/exhaustive/basic/typed01/expected/model_4_1_1_2-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_4_1_1_2-solution000001.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_1_1_2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_1_1_2-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_4_1_1_2-solution000002.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_1_1_2-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_1_1_2-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_4_1_1_2-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_1_1_2-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_1_1_2.eprime b/tests/exhaustive/basic/typed01/expected/model_4_1_1_2.eprime new file mode 100644 index 0000000000..b5a88ded3f --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_1_1_2.eprime @@ -0,0 +1,18 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +find x_Occurrence: matrix indexed by [int(1)] of bool +find y_Occurrence: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +branching on + [x_Occurrence, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithDummy, + y_Occurrence] +such that + x_ExplicitVarSizeWithFlags_Flags[1] /\ y_Occurrence[x_ExplicitVarSizeWithFlags_Values[1]] -> false, + x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, + x_Occurrence[1] -> x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = 1, + x_ExplicitVarSizeWithFlags_Flags[1] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[1]], + y_ExplicitVarSizeWithDummy[1] != 2 -> y_Occurrence[y_ExplicitVarSizeWithDummy[1]], + y_Occurrence[1] -> y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = 1 + diff --git a/tests/exhaustive/basic/typed01/expected/model_4_1_1_3-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_4_1_1_3-solution000001.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_1_1_3-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_1_1_3-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_4_1_1_3-solution000002.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_1_1_3-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_1_1_3-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_4_1_1_3-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_1_1_3-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_1_1_3.eprime b/tests/exhaustive/basic/typed01/expected/model_4_1_1_3.eprime new file mode 100644 index 0000000000..0613ec22d1 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_1_1_3.eprime @@ -0,0 +1,20 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +find x_Occurrence: matrix indexed by [int(1)] of bool +find y_Occurrence: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithMarker_Marker: int(0..1) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +branching on + [x_Occurrence, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, + y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values, y_Occurrence] +such that + x_ExplicitVarSizeWithFlags_Flags[1] /\ y_Occurrence[x_ExplicitVarSizeWithFlags_Values[1]] -> false, + x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, + x_Occurrence[1] -> x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = 1, + x_ExplicitVarSizeWithFlags_Flags[1] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[1]], + 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, + 1 <= y_ExplicitVarSizeWithMarker_Marker -> y_Occurrence[y_ExplicitVarSizeWithMarker_Values[1]], + y_Occurrence[1] -> 1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = 1 + diff --git a/tests/exhaustive/basic/typed01/expected/model_4_1_1_4-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_4_1_1_4-solution000001.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_1_1_4-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_1_1_4-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_4_1_1_4-solution000002.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_1_1_4-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_1_1_4-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_4_1_1_4-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_1_1_4-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_1_1_4.eprime b/tests/exhaustive/basic/typed01/expected/model_4_1_1_4.eprime new file mode 100644 index 0000000000..65f046be5f --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_1_1_4.eprime @@ -0,0 +1,20 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +find x_Occurrence: matrix indexed by [int(1)] of bool +find y_Occurrence: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +branching on + [x_Occurrence, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, + y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values, y_Occurrence] +such that + x_ExplicitVarSizeWithFlags_Flags[1] /\ y_Occurrence[x_ExplicitVarSizeWithFlags_Values[1]] -> false, + x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, + x_Occurrence[1] -> x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = 1, + x_ExplicitVarSizeWithFlags_Flags[1] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[1]], + y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, + y_ExplicitVarSizeWithFlags_Flags[1] -> y_Occurrence[y_ExplicitVarSizeWithFlags_Values[1]], + y_Occurrence[1] -> y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = 1 + diff --git a/tests/exhaustive/basic/typed01/expected/model_4_1_2_1-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_4_1_2_1-solution000001.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_1_2_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_1_2_1-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_4_1_2_1-solution000002.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_1_2_1-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_1_2_1-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_4_1_2_1-solution000003.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_1_2_1-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_1_2_1.eprime b/tests/exhaustive/basic/typed01/expected/model_4_1_2_1.eprime new file mode 100644 index 0000000000..35a3f77d73 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_1_2_1.eprime @@ -0,0 +1,16 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +find y_Occurrence: matrix indexed by [int(1)] of bool +branching on + [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, y_Occurrence] +such that + x_ExplicitVarSizeWithFlags_Flags[1] /\ y_Occurrence[x_ExplicitVarSizeWithFlags_Values[1]] -> false, + x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, + x_ExplicitVarSizeWithDummy[1] != 2 -> + x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithDummy[1], + x_ExplicitVarSizeWithFlags_Flags[1] -> + x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithFlags_Values[1] + diff --git a/tests/exhaustive/basic/typed01/expected/model_4_1_2_2-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_4_1_2_2-solution000001.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_1_2_2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_1_2_2-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_4_1_2_2-solution000002.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_1_2_2-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_1_2_2-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_4_1_2_2-solution000003.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_1_2_2-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_1_2_2.eprime b/tests/exhaustive/basic/typed01/expected/model_4_1_2_2.eprime new file mode 100644 index 0000000000..4248fba7ca --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_1_2_2.eprime @@ -0,0 +1,20 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +find y_Occurrence: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +branching on + [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, + y_ExplicitVarSizeWithDummy, y_Occurrence] +such that + x_ExplicitVarSizeWithFlags_Flags[1] /\ y_Occurrence[x_ExplicitVarSizeWithFlags_Values[1]] -> false, + x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, + x_ExplicitVarSizeWithDummy[1] != 2 -> + x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithDummy[1], + x_ExplicitVarSizeWithFlags_Flags[1] -> + x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithFlags_Values[1], + y_ExplicitVarSizeWithDummy[1] != 2 -> y_Occurrence[y_ExplicitVarSizeWithDummy[1]], + y_Occurrence[1] -> y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = 1 + diff --git a/tests/exhaustive/basic/typed01/expected/model_4_1_2_3-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_4_1_2_3-solution000001.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_1_2_3-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_1_2_3-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_4_1_2_3-solution000002.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_1_2_3-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_1_2_3-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_4_1_2_3-solution000003.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_1_2_3-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_1_2_3.eprime b/tests/exhaustive/basic/typed01/expected/model_4_1_2_3.eprime new file mode 100644 index 0000000000..b9a7ce2420 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_1_2_3.eprime @@ -0,0 +1,22 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +find y_Occurrence: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithMarker_Marker: int(0..1) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +branching on + [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, + y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values, y_Occurrence] +such that + x_ExplicitVarSizeWithFlags_Flags[1] /\ y_Occurrence[x_ExplicitVarSizeWithFlags_Values[1]] -> false, + x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, + x_ExplicitVarSizeWithDummy[1] != 2 -> + x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithDummy[1], + x_ExplicitVarSizeWithFlags_Flags[1] -> + x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithFlags_Values[1], + 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, + 1 <= y_ExplicitVarSizeWithMarker_Marker -> y_Occurrence[y_ExplicitVarSizeWithMarker_Values[1]], + y_Occurrence[1] -> 1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = 1 + diff --git a/tests/exhaustive/basic/typed01/expected/model_4_1_2_4-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_4_1_2_4-solution000001.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_1_2_4-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_1_2_4-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_4_1_2_4-solution000002.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_1_2_4-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_1_2_4-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_4_1_2_4-solution000003.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_1_2_4-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_1_2_4.eprime b/tests/exhaustive/basic/typed01/expected/model_4_1_2_4.eprime new file mode 100644 index 0000000000..22a953d049 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_1_2_4.eprime @@ -0,0 +1,22 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +find y_Occurrence: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +branching on + [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, + y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values, y_Occurrence] +such that + x_ExplicitVarSizeWithFlags_Flags[1] /\ y_Occurrence[x_ExplicitVarSizeWithFlags_Values[1]] -> false, + x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, + x_ExplicitVarSizeWithDummy[1] != 2 -> + x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithDummy[1], + x_ExplicitVarSizeWithFlags_Flags[1] -> + x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithFlags_Values[1], + y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, + y_ExplicitVarSizeWithFlags_Flags[1] -> y_Occurrence[y_ExplicitVarSizeWithFlags_Values[1]], + y_Occurrence[1] -> y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = 1 + diff --git a/tests/exhaustive/basic/typed01/expected/model_4_1_3_1-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_4_1_3_1-solution000001.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_1_3_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_1_3_1-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_4_1_3_1-solution000002.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_1_3_1-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_1_3_1-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_4_1_3_1-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_1_3_1-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_1_3_1.eprime b/tests/exhaustive/basic/typed01/expected/model_4_1_3_1.eprime new file mode 100644 index 0000000000..b5825355dc --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_1_3_1.eprime @@ -0,0 +1,20 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +find x_ExplicitVarSizeWithMarker_Marker: int(0..1) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +find y_Occurrence: matrix indexed by [int(1)] of bool +branching on + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithFlags_Flags, + x_ExplicitVarSizeWithFlags_Values, y_Occurrence] +such that + x_ExplicitVarSizeWithFlags_Flags[1] /\ y_Occurrence[x_ExplicitVarSizeWithFlags_Values[1]] -> false, + x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, + 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithMarker_Values[1], + x_ExplicitVarSizeWithFlags_Flags[1] -> + 1 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithFlags_Values[1] + diff --git a/tests/exhaustive/basic/typed01/expected/model_4_1_3_2-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_4_1_3_2-solution000001.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_1_3_2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_1_3_2-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_4_1_3_2-solution000002.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_1_3_2-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_1_3_2-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_4_1_3_2-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_1_3_2-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_1_3_2.eprime b/tests/exhaustive/basic/typed01/expected/model_4_1_3_2.eprime new file mode 100644 index 0000000000..8d7d07b4a2 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_1_3_2.eprime @@ -0,0 +1,23 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +find x_ExplicitVarSizeWithMarker_Marker: int(0..1) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +find y_Occurrence: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +branching on + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithFlags_Flags, + x_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithDummy, y_Occurrence] +such that + x_ExplicitVarSizeWithFlags_Flags[1] /\ y_Occurrence[x_ExplicitVarSizeWithFlags_Values[1]] -> false, + x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, + 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithMarker_Values[1], + x_ExplicitVarSizeWithFlags_Flags[1] -> + 1 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithFlags_Values[1], + y_ExplicitVarSizeWithDummy[1] != 2 -> y_Occurrence[y_ExplicitVarSizeWithDummy[1]], + y_Occurrence[1] -> y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = 1 + diff --git a/tests/exhaustive/basic/typed01/expected/model_4_1_3_3-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_4_1_3_3-solution000001.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_1_3_3-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_1_3_3-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_4_1_3_3-solution000002.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_1_3_3-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_1_3_3-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_4_1_3_3-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_1_3_3-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_1_3_3.eprime b/tests/exhaustive/basic/typed01/expected/model_4_1_3_3.eprime new file mode 100644 index 0000000000..ff41c8db54 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_1_3_3.eprime @@ -0,0 +1,26 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +find x_ExplicitVarSizeWithMarker_Marker: int(0..1) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +find y_Occurrence: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithMarker_Marker: int(0..1) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +branching on + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithFlags_Flags, + x_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values, + y_Occurrence] +such that + x_ExplicitVarSizeWithFlags_Flags[1] /\ y_Occurrence[x_ExplicitVarSizeWithFlags_Values[1]] -> false, + x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, + 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithMarker_Values[1], + x_ExplicitVarSizeWithFlags_Flags[1] -> + 1 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithFlags_Values[1], + 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, + 1 <= y_ExplicitVarSizeWithMarker_Marker -> y_Occurrence[y_ExplicitVarSizeWithMarker_Values[1]], + y_Occurrence[1] -> 1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = 1 + diff --git a/tests/exhaustive/basic/typed01/expected/model_4_1_3_4-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_4_1_3_4-solution000001.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_1_3_4-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_1_3_4-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_4_1_3_4-solution000002.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_1_3_4-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_1_3_4-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_4_1_3_4-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_1_3_4-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_1_3_4.eprime b/tests/exhaustive/basic/typed01/expected/model_4_1_3_4.eprime new file mode 100644 index 0000000000..0f20e6b43f --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_1_3_4.eprime @@ -0,0 +1,26 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +find x_ExplicitVarSizeWithMarker_Marker: int(0..1) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +find y_Occurrence: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +branching on + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithFlags_Flags, + x_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values, + y_Occurrence] +such that + x_ExplicitVarSizeWithFlags_Flags[1] /\ y_Occurrence[x_ExplicitVarSizeWithFlags_Values[1]] -> false, + x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, + 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithMarker_Values[1], + x_ExplicitVarSizeWithFlags_Flags[1] -> + 1 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithFlags_Values[1], + y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, + y_ExplicitVarSizeWithFlags_Flags[1] -> y_Occurrence[y_ExplicitVarSizeWithFlags_Values[1]], + y_Occurrence[1] -> y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = 1 + diff --git a/tests/exhaustive/basic/typed01/expected/model_4_1_4_1-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_4_1_4_1-solution000001.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_1_4_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_1_4_1-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_4_1_4_1-solution000002.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_1_4_1-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_1_4_1-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_4_1_4_1-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_1_4_1-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_1_4_1.eprime b/tests/exhaustive/basic/typed01/expected/model_4_1_4_1.eprime new file mode 100644 index 0000000000..a83a129f9d --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_1_4_1.eprime @@ -0,0 +1,10 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +find y_Occurrence: matrix indexed by [int(1)] of bool +branching on [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, y_Occurrence] +such that + x_ExplicitVarSizeWithFlags_Flags[1] /\ y_Occurrence[x_ExplicitVarSizeWithFlags_Values[1]] -> false, + x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1 + diff --git a/tests/exhaustive/basic/typed01/expected/model_4_1_4_2-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_4_1_4_2-solution000001.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_1_4_2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_1_4_2-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_4_1_4_2-solution000002.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_1_4_2-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_1_4_2-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_4_1_4_2-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_1_4_2-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_1_4_2.eprime b/tests/exhaustive/basic/typed01/expected/model_4_1_4_2.eprime new file mode 100644 index 0000000000..9cba33315d --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_1_4_2.eprime @@ -0,0 +1,14 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +find y_Occurrence: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +branching on + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithDummy, y_Occurrence] +such that + x_ExplicitVarSizeWithFlags_Flags[1] /\ y_Occurrence[x_ExplicitVarSizeWithFlags_Values[1]] -> false, + x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, + y_ExplicitVarSizeWithDummy[1] != 2 -> y_Occurrence[y_ExplicitVarSizeWithDummy[1]], + y_Occurrence[1] -> y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = 1 + diff --git a/tests/exhaustive/basic/typed01/expected/model_4_1_4_3-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_4_1_4_3-solution000001.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_1_4_3-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_1_4_3-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_4_1_4_3-solution000002.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_1_4_3-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_1_4_3-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_4_1_4_3-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_1_4_3-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_1_4_3.eprime b/tests/exhaustive/basic/typed01/expected/model_4_1_4_3.eprime new file mode 100644 index 0000000000..f0d019484b --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_1_4_3.eprime @@ -0,0 +1,17 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +find y_Occurrence: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithMarker_Marker: int(0..1) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +branching on + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithMarker_Marker, + y_ExplicitVarSizeWithMarker_Values, y_Occurrence] +such that + x_ExplicitVarSizeWithFlags_Flags[1] /\ y_Occurrence[x_ExplicitVarSizeWithFlags_Values[1]] -> false, + x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, + 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, + 1 <= y_ExplicitVarSizeWithMarker_Marker -> y_Occurrence[y_ExplicitVarSizeWithMarker_Values[1]], + y_Occurrence[1] -> 1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = 1 + diff --git a/tests/exhaustive/basic/typed01/expected/model_4_1_4_4-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_4_1_4_4-solution000001.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_1_4_4-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_1_4_4-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_4_1_4_4-solution000002.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_1_4_4-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_1_4_4-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_4_1_4_4-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_1_4_4-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_1_4_4.eprime b/tests/exhaustive/basic/typed01/expected/model_4_1_4_4.eprime new file mode 100644 index 0000000000..0f279552c2 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_1_4_4.eprime @@ -0,0 +1,17 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +find y_Occurrence: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +branching on + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithFlags_Flags, + y_ExplicitVarSizeWithFlags_Values, y_Occurrence] +such that + x_ExplicitVarSizeWithFlags_Flags[1] /\ y_Occurrence[x_ExplicitVarSizeWithFlags_Values[1]] -> false, + x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, + y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, + y_ExplicitVarSizeWithFlags_Flags[1] -> y_Occurrence[y_ExplicitVarSizeWithFlags_Values[1]], + y_Occurrence[1] -> y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = 1 + diff --git a/tests/exhaustive/basic/typed01/expected/model_4_2_1_1-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_4_2_1_1-solution000001.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_2_1_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_2_1_1-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_4_2_1_1-solution000002.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_2_1_1-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_2_1_1-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_4_2_1_1-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_2_1_1-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_2_1_1.eprime b/tests/exhaustive/basic/typed01/expected/model_4_2_1_1.eprime new file mode 100644 index 0000000000..7af0d950bd --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_2_1_1.eprime @@ -0,0 +1,20 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +find x_Occurrence: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +find y_Occurrence: matrix indexed by [int(1)] of bool +branching on + [x_Occurrence, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, y_Occurrence, + y_ExplicitVarSizeWithDummy] +such that + x_ExplicitVarSizeWithFlags_Flags[1] /\ + (y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithFlags_Values[1]) + -> false, + x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, + x_Occurrence[1] -> x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = 1, + x_ExplicitVarSizeWithFlags_Flags[1] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[1]], + y_Occurrence[1] -> y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = 1, + y_ExplicitVarSizeWithDummy[1] != 2 -> y_Occurrence[y_ExplicitVarSizeWithDummy[1]] + diff --git a/tests/exhaustive/basic/typed01/expected/model_4_2_1_2-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_4_2_1_2-solution000001.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_2_1_2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_2_1_2-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_4_2_1_2-solution000002.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_2_1_2-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_2_1_2-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_4_2_1_2-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_2_1_2-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_2_1_2.eprime b/tests/exhaustive/basic/typed01/expected/model_4_2_1_2.eprime new file mode 100644 index 0000000000..7c872d9415 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_2_1_2.eprime @@ -0,0 +1,16 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +find x_Occurrence: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +branching on + [x_Occurrence, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithDummy] +such that + x_ExplicitVarSizeWithFlags_Flags[1] /\ + (y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithFlags_Values[1]) + -> false, + x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, + x_Occurrence[1] -> x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = 1, + x_ExplicitVarSizeWithFlags_Flags[1] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[1]] + diff --git a/tests/exhaustive/basic/typed01/expected/model_4_2_1_3-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_4_2_1_3-solution000001.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_2_1_3-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_2_1_3-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_4_2_1_3-solution000002.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_2_1_3-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_2_1_3-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_4_2_1_3-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_2_1_3-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_2_1_3.eprime b/tests/exhaustive/basic/typed01/expected/model_4_2_1_3.eprime new file mode 100644 index 0000000000..ff225c5a29 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_2_1_3.eprime @@ -0,0 +1,24 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +find x_Occurrence: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +find y_ExplicitVarSizeWithMarker_Marker: int(0..1) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +branching on + [x_Occurrence, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, + y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithDummy] +such that + x_ExplicitVarSizeWithFlags_Flags[1] /\ + (y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithFlags_Values[1]) + -> false, + x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, + x_Occurrence[1] -> x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = 1, + x_ExplicitVarSizeWithFlags_Flags[1] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[1]], + 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, + 1 <= y_ExplicitVarSizeWithMarker_Marker -> + y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = y_ExplicitVarSizeWithMarker_Values[1], + y_ExplicitVarSizeWithDummy[1] != 2 -> + 1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = y_ExplicitVarSizeWithDummy[1] + diff --git a/tests/exhaustive/basic/typed01/expected/model_4_2_1_4-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_4_2_1_4-solution000001.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_2_1_4-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_2_1_4-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_4_2_1_4-solution000002.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_2_1_4-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_2_1_4-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_4_2_1_4-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_2_1_4-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_2_1_4.eprime b/tests/exhaustive/basic/typed01/expected/model_4_2_1_4.eprime new file mode 100644 index 0000000000..819e4e33ed --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_2_1_4.eprime @@ -0,0 +1,24 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +find x_Occurrence: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +branching on + [x_Occurrence, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, + y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithDummy] +such that + x_ExplicitVarSizeWithFlags_Flags[1] /\ + (y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithFlags_Values[1]) + -> false, + x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, + x_Occurrence[1] -> x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = 1, + x_ExplicitVarSizeWithFlags_Flags[1] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[1]], + y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, + y_ExplicitVarSizeWithFlags_Flags[1] -> + y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = y_ExplicitVarSizeWithFlags_Values[1], + y_ExplicitVarSizeWithDummy[1] != 2 -> + y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = y_ExplicitVarSizeWithDummy[1] + diff --git a/tests/exhaustive/basic/typed01/expected/model_4_2_2_1-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_4_2_2_1-solution000001.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_2_2_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_2_2_1-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_4_2_2_1-solution000002.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_2_2_1-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_2_2_1-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_4_2_2_1-solution000003.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_2_2_1-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_2_2_1.eprime b/tests/exhaustive/basic/typed01/expected/model_4_2_2_1.eprime new file mode 100644 index 0000000000..c705186841 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_2_2_1.eprime @@ -0,0 +1,22 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +find y_Occurrence: matrix indexed by [int(1)] of bool +branching on + [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, y_Occurrence, + y_ExplicitVarSizeWithDummy] +such that + x_ExplicitVarSizeWithFlags_Flags[1] /\ + (y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithFlags_Values[1]) + -> false, + x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, + x_ExplicitVarSizeWithDummy[1] != 2 -> + x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithDummy[1], + x_ExplicitVarSizeWithFlags_Flags[1] -> + x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithFlags_Values[1], + y_Occurrence[1] -> y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = 1, + y_ExplicitVarSizeWithDummy[1] != 2 -> y_Occurrence[y_ExplicitVarSizeWithDummy[1]] + diff --git a/tests/exhaustive/basic/typed01/expected/model_4_2_2_2-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_4_2_2_2-solution000001.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_2_2_2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_2_2_2-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_4_2_2_2-solution000002.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_2_2_2-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_2_2_2-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_4_2_2_2-solution000003.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_2_2_2-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_2_2_2.eprime b/tests/exhaustive/basic/typed01/expected/model_4_2_2_2.eprime new file mode 100644 index 0000000000..6d6bdff10b --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_2_2_2.eprime @@ -0,0 +1,19 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +branching on + [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, + y_ExplicitVarSizeWithDummy] +such that + x_ExplicitVarSizeWithFlags_Flags[1] /\ + (y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithFlags_Values[1]) + -> false, + x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, + x_ExplicitVarSizeWithDummy[1] != 2 -> + x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithDummy[1], + x_ExplicitVarSizeWithFlags_Flags[1] -> + x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithFlags_Values[1] + diff --git a/tests/exhaustive/basic/typed01/expected/model_4_2_2_3-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_4_2_2_3-solution000001.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_2_2_3-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_2_2_3-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_4_2_2_3-solution000002.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_2_2_3-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_2_2_3-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_4_2_2_3-solution000003.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_2_2_3-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_2_2_3.eprime b/tests/exhaustive/basic/typed01/expected/model_4_2_2_3.eprime new file mode 100644 index 0000000000..b84dbce7a7 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_2_2_3.eprime @@ -0,0 +1,26 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +find y_ExplicitVarSizeWithMarker_Marker: int(0..1) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +branching on + [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, + y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithDummy] +such that + x_ExplicitVarSizeWithFlags_Flags[1] /\ + (y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithFlags_Values[1]) + -> false, + x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, + x_ExplicitVarSizeWithDummy[1] != 2 -> + x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithDummy[1], + x_ExplicitVarSizeWithFlags_Flags[1] -> + x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithFlags_Values[1], + 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, + 1 <= y_ExplicitVarSizeWithMarker_Marker -> + y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = y_ExplicitVarSizeWithMarker_Values[1], + y_ExplicitVarSizeWithDummy[1] != 2 -> + 1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = y_ExplicitVarSizeWithDummy[1] + diff --git a/tests/exhaustive/basic/typed01/expected/model_4_2_2_4-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_4_2_2_4-solution000001.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_2_2_4-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_2_2_4-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_4_2_2_4-solution000002.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_2_2_4-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_2_2_4-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_4_2_2_4-solution000003.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_2_2_4-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_2_2_4.eprime b/tests/exhaustive/basic/typed01/expected/model_4_2_2_4.eprime new file mode 100644 index 0000000000..9e0b55a0f7 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_2_2_4.eprime @@ -0,0 +1,26 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +branching on + [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, + y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithDummy] +such that + x_ExplicitVarSizeWithFlags_Flags[1] /\ + (y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithFlags_Values[1]) + -> false, + x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, + x_ExplicitVarSizeWithDummy[1] != 2 -> + x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithDummy[1], + x_ExplicitVarSizeWithFlags_Flags[1] -> + x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithFlags_Values[1], + y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, + y_ExplicitVarSizeWithFlags_Flags[1] -> + y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = y_ExplicitVarSizeWithFlags_Values[1], + y_ExplicitVarSizeWithDummy[1] != 2 -> + y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = y_ExplicitVarSizeWithDummy[1] + diff --git a/tests/exhaustive/basic/typed01/expected/model_4_2_3_1-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_4_2_3_1-solution000001.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_2_3_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_2_3_1-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_4_2_3_1-solution000002.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_2_3_1-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_2_3_1-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_4_2_3_1-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_2_3_1-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_2_3_1.eprime b/tests/exhaustive/basic/typed01/expected/model_4_2_3_1.eprime new file mode 100644 index 0000000000..6158689ebd --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_2_3_1.eprime @@ -0,0 +1,25 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +find x_ExplicitVarSizeWithMarker_Marker: int(0..1) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +find y_Occurrence: matrix indexed by [int(1)] of bool +branching on + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithFlags_Flags, + x_ExplicitVarSizeWithFlags_Values, y_Occurrence, y_ExplicitVarSizeWithDummy] +such that + x_ExplicitVarSizeWithFlags_Flags[1] /\ + (y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithFlags_Values[1]) + -> false, + x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, + 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithMarker_Values[1], + x_ExplicitVarSizeWithFlags_Flags[1] -> + 1 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithFlags_Values[1], + y_Occurrence[1] -> y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = 1, + y_ExplicitVarSizeWithDummy[1] != 2 -> y_Occurrence[y_ExplicitVarSizeWithDummy[1]] + diff --git a/tests/exhaustive/basic/typed01/expected/model_4_2_3_2-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_4_2_3_2-solution000001.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_2_3_2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_2_3_2-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_4_2_3_2-solution000002.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_2_3_2-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_2_3_2-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_4_2_3_2-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_2_3_2-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_2_3_2.eprime b/tests/exhaustive/basic/typed01/expected/model_4_2_3_2.eprime new file mode 100644 index 0000000000..af849df8be --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_2_3_2.eprime @@ -0,0 +1,22 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +find x_ExplicitVarSizeWithMarker_Marker: int(0..1) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +branching on + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithFlags_Flags, + x_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithDummy] +such that + x_ExplicitVarSizeWithFlags_Flags[1] /\ + (y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithFlags_Values[1]) + -> false, + x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, + 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithMarker_Values[1], + x_ExplicitVarSizeWithFlags_Flags[1] -> + 1 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithFlags_Values[1] + diff --git a/tests/exhaustive/basic/typed01/expected/model_4_2_3_3-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_4_2_3_3-solution000001.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_2_3_3-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_2_3_3-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_4_2_3_3-solution000002.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_2_3_3-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_2_3_3-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_4_2_3_3-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_2_3_3-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_2_3_3.eprime b/tests/exhaustive/basic/typed01/expected/model_4_2_3_3.eprime new file mode 100644 index 0000000000..730f8ef16d --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_2_3_3.eprime @@ -0,0 +1,30 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +find x_ExplicitVarSizeWithMarker_Marker: int(0..1) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +find y_ExplicitVarSizeWithMarker_Marker: int(0..1) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +branching on + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithFlags_Flags, + x_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values, + y_ExplicitVarSizeWithDummy] +such that + x_ExplicitVarSizeWithFlags_Flags[1] /\ + (y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithFlags_Values[1]) + -> false, + x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, + 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithMarker_Values[1], + x_ExplicitVarSizeWithFlags_Flags[1] -> + 1 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithFlags_Values[1], + 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, + 1 <= y_ExplicitVarSizeWithMarker_Marker -> + y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = y_ExplicitVarSizeWithMarker_Values[1], + y_ExplicitVarSizeWithDummy[1] != 2 -> + 1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = y_ExplicitVarSizeWithDummy[1] + diff --git a/tests/exhaustive/basic/typed01/expected/model_4_2_3_4-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_4_2_3_4-solution000001.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_2_3_4-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_2_3_4-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_4_2_3_4-solution000002.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_2_3_4-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_2_3_4-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_4_2_3_4-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_2_3_4-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_2_3_4.eprime b/tests/exhaustive/basic/typed01/expected/model_4_2_3_4.eprime new file mode 100644 index 0000000000..ada2b923a1 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_2_3_4.eprime @@ -0,0 +1,30 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +find x_ExplicitVarSizeWithMarker_Marker: int(0..1) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +branching on + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithFlags_Flags, + x_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values, + y_ExplicitVarSizeWithDummy] +such that + x_ExplicitVarSizeWithFlags_Flags[1] /\ + (y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithFlags_Values[1]) + -> false, + x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, + 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithMarker_Values[1], + x_ExplicitVarSizeWithFlags_Flags[1] -> + 1 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithFlags_Values[1], + y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, + y_ExplicitVarSizeWithFlags_Flags[1] -> + y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = y_ExplicitVarSizeWithFlags_Values[1], + y_ExplicitVarSizeWithDummy[1] != 2 -> + y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = y_ExplicitVarSizeWithDummy[1] + diff --git a/tests/exhaustive/basic/typed01/expected/model_4_2_4_1-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_4_2_4_1-solution000001.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_2_4_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_2_4_1-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_4_2_4_1-solution000002.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_2_4_1-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_2_4_1-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_4_2_4_1-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_2_4_1-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_2_4_1.eprime b/tests/exhaustive/basic/typed01/expected/model_4_2_4_1.eprime new file mode 100644 index 0000000000..dbc07862de --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_2_4_1.eprime @@ -0,0 +1,16 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +find y_Occurrence: matrix indexed by [int(1)] of bool +branching on + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, y_Occurrence, y_ExplicitVarSizeWithDummy] +such that + x_ExplicitVarSizeWithFlags_Flags[1] /\ + (y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithFlags_Values[1]) + -> false, + x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, + y_Occurrence[1] -> y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = 1, + y_ExplicitVarSizeWithDummy[1] != 2 -> y_Occurrence[y_ExplicitVarSizeWithDummy[1]] + diff --git a/tests/exhaustive/basic/typed01/expected/model_4_2_4_2-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_4_2_4_2-solution000001.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_2_4_2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_2_4_2-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_4_2_4_2-solution000002.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_2_4_2-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_2_4_2-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_4_2_4_2-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_2_4_2-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_2_4_2.eprime b/tests/exhaustive/basic/typed01/expected/model_4_2_4_2.eprime new file mode 100644 index 0000000000..9f155130a0 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_2_4_2.eprime @@ -0,0 +1,12 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +branching on [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithDummy] +such that + x_ExplicitVarSizeWithFlags_Flags[1] /\ + (y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithFlags_Values[1]) + -> false, + x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1 + diff --git a/tests/exhaustive/basic/typed01/expected/model_4_2_4_3-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_4_2_4_3-solution000001.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_2_4_3-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_2_4_3-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_4_2_4_3-solution000002.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_2_4_3-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_2_4_3-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_4_2_4_3-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_2_4_3-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_2_4_3.eprime b/tests/exhaustive/basic/typed01/expected/model_4_2_4_3.eprime new file mode 100644 index 0000000000..e1180d719b --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_2_4_3.eprime @@ -0,0 +1,21 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +find y_ExplicitVarSizeWithMarker_Marker: int(0..1) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +branching on + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithMarker_Marker, + y_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithDummy] +such that + x_ExplicitVarSizeWithFlags_Flags[1] /\ + (y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithFlags_Values[1]) + -> false, + x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, + 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, + 1 <= y_ExplicitVarSizeWithMarker_Marker -> + y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = y_ExplicitVarSizeWithMarker_Values[1], + y_ExplicitVarSizeWithDummy[1] != 2 -> + 1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = y_ExplicitVarSizeWithDummy[1] + diff --git a/tests/exhaustive/basic/typed01/expected/model_4_2_4_4-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_4_2_4_4-solution000001.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_2_4_4-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_2_4_4-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_4_2_4_4-solution000002.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_2_4_4-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_2_4_4-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_4_2_4_4-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_2_4_4-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_2_4_4.eprime b/tests/exhaustive/basic/typed01/expected/model_4_2_4_4.eprime new file mode 100644 index 0000000000..a53eedddb0 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_2_4_4.eprime @@ -0,0 +1,21 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +branching on + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithFlags_Flags, + y_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithDummy] +such that + x_ExplicitVarSizeWithFlags_Flags[1] /\ + (y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithFlags_Values[1]) + -> false, + x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, + y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, + y_ExplicitVarSizeWithFlags_Flags[1] -> + y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = y_ExplicitVarSizeWithFlags_Values[1], + y_ExplicitVarSizeWithDummy[1] != 2 -> + y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = y_ExplicitVarSizeWithDummy[1] + diff --git a/tests/exhaustive/basic/typed01/expected/model_4_3_1_1-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_4_3_1_1-solution000001.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_3_1_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_3_1_1-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_4_3_1_1-solution000002.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_3_1_1-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_3_1_1-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_4_3_1_1-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_3_1_1-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_3_1_1.eprime b/tests/exhaustive/basic/typed01/expected/model_4_3_1_1.eprime new file mode 100644 index 0000000000..dc647fb27d --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_3_1_1.eprime @@ -0,0 +1,23 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +find x_Occurrence: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithMarker_Marker: int(0..1) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +find y_Occurrence: matrix indexed by [int(1)] of bool +branching on + [x_Occurrence, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, y_Occurrence, + y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values] +such that + x_ExplicitVarSizeWithFlags_Flags[1] /\ + (1 <= y_ExplicitVarSizeWithMarker_Marker /\ + y_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithFlags_Values[1]) + -> false, + x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, + 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, + x_Occurrence[1] -> x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = 1, + x_ExplicitVarSizeWithFlags_Flags[1] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[1]], + y_Occurrence[1] -> 1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = 1, + 1 <= y_ExplicitVarSizeWithMarker_Marker -> y_Occurrence[y_ExplicitVarSizeWithMarker_Values[1]] + diff --git a/tests/exhaustive/basic/typed01/expected/model_4_3_1_2-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_4_3_1_2-solution000001.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_3_1_2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_3_1_2-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_4_3_1_2-solution000002.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_3_1_2-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_3_1_2-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_4_3_1_2-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_3_1_2-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_3_1_2.eprime b/tests/exhaustive/basic/typed01/expected/model_4_3_1_2.eprime new file mode 100644 index 0000000000..4ec2675a1c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_3_1_2.eprime @@ -0,0 +1,25 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +find x_Occurrence: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithMarker_Marker: int(0..1) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +branching on + [x_Occurrence, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithDummy, + y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values] +such that + x_ExplicitVarSizeWithFlags_Flags[1] /\ + (1 <= y_ExplicitVarSizeWithMarker_Marker /\ + y_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithFlags_Values[1]) + -> false, + x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, + 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, + x_Occurrence[1] -> x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = 1, + x_ExplicitVarSizeWithFlags_Flags[1] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[1]], + y_ExplicitVarSizeWithDummy[1] != 2 -> + 1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = y_ExplicitVarSizeWithDummy[1], + 1 <= y_ExplicitVarSizeWithMarker_Marker -> + y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = y_ExplicitVarSizeWithMarker_Values[1] + diff --git a/tests/exhaustive/basic/typed01/expected/model_4_3_1_3-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_4_3_1_3-solution000001.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_3_1_3-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_3_1_3-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_4_3_1_3-solution000002.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_3_1_3-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_3_1_3-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_4_3_1_3-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_3_1_3-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_3_1_3.eprime b/tests/exhaustive/basic/typed01/expected/model_4_3_1_3.eprime new file mode 100644 index 0000000000..32cfd157ad --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_3_1_3.eprime @@ -0,0 +1,20 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +find x_Occurrence: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithMarker_Marker: int(0..1) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +branching on + [x_Occurrence, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, + y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values] +such that + x_ExplicitVarSizeWithFlags_Flags[1] /\ + (1 <= y_ExplicitVarSizeWithMarker_Marker /\ + y_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithFlags_Values[1]) + -> false, + x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, + 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, + x_Occurrence[1] -> x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = 1, + x_ExplicitVarSizeWithFlags_Flags[1] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[1]] + diff --git a/tests/exhaustive/basic/typed01/expected/model_4_3_1_4-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_4_3_1_4-solution000001.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_3_1_4-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_3_1_4-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_4_3_1_4-solution000002.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_3_1_4-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_3_1_4-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_4_3_1_4-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_3_1_4-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_3_1_4.eprime b/tests/exhaustive/basic/typed01/expected/model_4_3_1_4.eprime new file mode 100644 index 0000000000..27811841d5 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_3_1_4.eprime @@ -0,0 +1,29 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +find x_Occurrence: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithMarker_Marker: int(0..1) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +branching on + [x_Occurrence, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, + y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithMarker_Marker, + y_ExplicitVarSizeWithMarker_Values] +such that + x_ExplicitVarSizeWithFlags_Flags[1] /\ + (1 <= y_ExplicitVarSizeWithMarker_Marker /\ + y_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithFlags_Values[1]) + -> false, + x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, + 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, + x_Occurrence[1] -> x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = 1, + x_ExplicitVarSizeWithFlags_Flags[1] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[1]], + y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, + y_ExplicitVarSizeWithFlags_Flags[1] -> + 1 <= y_ExplicitVarSizeWithMarker_Marker /\ + y_ExplicitVarSizeWithMarker_Values[1] = y_ExplicitVarSizeWithFlags_Values[1], + 1 <= y_ExplicitVarSizeWithMarker_Marker -> + y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = y_ExplicitVarSizeWithMarker_Values[1] + diff --git a/tests/exhaustive/basic/typed01/expected/model_4_3_2_1-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_4_3_2_1-solution000001.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_3_2_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_3_2_1-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_4_3_2_1-solution000002.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_3_2_1-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_3_2_1-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_4_3_2_1-solution000003.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_3_2_1-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_3_2_1.eprime b/tests/exhaustive/basic/typed01/expected/model_4_3_2_1.eprime new file mode 100644 index 0000000000..14d92f563c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_3_2_1.eprime @@ -0,0 +1,25 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +find y_ExplicitVarSizeWithMarker_Marker: int(0..1) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +find y_Occurrence: matrix indexed by [int(1)] of bool +branching on + [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, y_Occurrence, + y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values] +such that + x_ExplicitVarSizeWithFlags_Flags[1] /\ + (1 <= y_ExplicitVarSizeWithMarker_Marker /\ + y_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithFlags_Values[1]) + -> false, + x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, + 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, + x_ExplicitVarSizeWithDummy[1] != 2 -> + x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithDummy[1], + x_ExplicitVarSizeWithFlags_Flags[1] -> + x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithFlags_Values[1], + y_Occurrence[1] -> 1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = 1, + 1 <= y_ExplicitVarSizeWithMarker_Marker -> y_Occurrence[y_ExplicitVarSizeWithMarker_Values[1]] + diff --git a/tests/exhaustive/basic/typed01/expected/model_4_3_2_2-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_4_3_2_2-solution000001.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_3_2_2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_3_2_2-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_4_3_2_2-solution000002.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_3_2_2-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_3_2_2-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_4_3_2_2-solution000003.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_3_2_2-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_3_2_2.eprime b/tests/exhaustive/basic/typed01/expected/model_4_3_2_2.eprime new file mode 100644 index 0000000000..5d58c6fa0d --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_3_2_2.eprime @@ -0,0 +1,27 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +find y_ExplicitVarSizeWithMarker_Marker: int(0..1) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +branching on + [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, + y_ExplicitVarSizeWithDummy, y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values] +such that + x_ExplicitVarSizeWithFlags_Flags[1] /\ + (1 <= y_ExplicitVarSizeWithMarker_Marker /\ + y_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithFlags_Values[1]) + -> false, + x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, + 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, + x_ExplicitVarSizeWithDummy[1] != 2 -> + x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithDummy[1], + x_ExplicitVarSizeWithFlags_Flags[1] -> + x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithFlags_Values[1], + y_ExplicitVarSizeWithDummy[1] != 2 -> + 1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = y_ExplicitVarSizeWithDummy[1], + 1 <= y_ExplicitVarSizeWithMarker_Marker -> + y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = y_ExplicitVarSizeWithMarker_Values[1] + diff --git a/tests/exhaustive/basic/typed01/expected/model_4_3_2_3-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_4_3_2_3-solution000001.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_3_2_3-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_3_2_3-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_4_3_2_3-solution000002.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_3_2_3-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_3_2_3-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_4_3_2_3-solution000003.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_3_2_3-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_3_2_3.eprime b/tests/exhaustive/basic/typed01/expected/model_4_3_2_3.eprime new file mode 100644 index 0000000000..907a46b538 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_3_2_3.eprime @@ -0,0 +1,22 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +find y_ExplicitVarSizeWithMarker_Marker: int(0..1) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +branching on + [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, + y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values] +such that + x_ExplicitVarSizeWithFlags_Flags[1] /\ + (1 <= y_ExplicitVarSizeWithMarker_Marker /\ + y_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithFlags_Values[1]) + -> false, + x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, + 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, + x_ExplicitVarSizeWithDummy[1] != 2 -> + x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithDummy[1], + x_ExplicitVarSizeWithFlags_Flags[1] -> + x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithFlags_Values[1] + diff --git a/tests/exhaustive/basic/typed01/expected/model_4_3_2_4-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_4_3_2_4-solution000001.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_3_2_4-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_3_2_4-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_4_3_2_4-solution000002.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_3_2_4-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_3_2_4-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_4_3_2_4-solution000003.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_3_2_4-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_3_2_4.eprime b/tests/exhaustive/basic/typed01/expected/model_4_3_2_4.eprime new file mode 100644 index 0000000000..c6f53b014c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_3_2_4.eprime @@ -0,0 +1,31 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +find y_ExplicitVarSizeWithMarker_Marker: int(0..1) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +branching on + [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, + y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithMarker_Marker, + y_ExplicitVarSizeWithMarker_Values] +such that + x_ExplicitVarSizeWithFlags_Flags[1] /\ + (1 <= y_ExplicitVarSizeWithMarker_Marker /\ + y_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithFlags_Values[1]) + -> false, + x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, + 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, + x_ExplicitVarSizeWithDummy[1] != 2 -> + x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithDummy[1], + x_ExplicitVarSizeWithFlags_Flags[1] -> + x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithFlags_Values[1], + y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, + y_ExplicitVarSizeWithFlags_Flags[1] -> + 1 <= y_ExplicitVarSizeWithMarker_Marker /\ + y_ExplicitVarSizeWithMarker_Values[1] = y_ExplicitVarSizeWithFlags_Values[1], + 1 <= y_ExplicitVarSizeWithMarker_Marker -> + y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = y_ExplicitVarSizeWithMarker_Values[1] + diff --git a/tests/exhaustive/basic/typed01/expected/model_4_3_3_1-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_4_3_3_1-solution000001.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_3_3_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_3_3_1-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_4_3_3_1-solution000002.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_3_3_1-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_3_3_1-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_4_3_3_1-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_3_3_1-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_3_3_1.eprime b/tests/exhaustive/basic/typed01/expected/model_4_3_3_1.eprime new file mode 100644 index 0000000000..58d00ad5ee --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_3_3_1.eprime @@ -0,0 +1,29 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +find x_ExplicitVarSizeWithMarker_Marker: int(0..1) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +find y_ExplicitVarSizeWithMarker_Marker: int(0..1) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +find y_Occurrence: matrix indexed by [int(1)] of bool +branching on + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithFlags_Flags, + x_ExplicitVarSizeWithFlags_Values, y_Occurrence, y_ExplicitVarSizeWithMarker_Marker, + y_ExplicitVarSizeWithMarker_Values] +such that + x_ExplicitVarSizeWithFlags_Flags[1] /\ + (1 <= y_ExplicitVarSizeWithMarker_Marker /\ + y_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithFlags_Values[1]) + -> false, + x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, + 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, + 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithMarker_Values[1], + x_ExplicitVarSizeWithFlags_Flags[1] -> + 1 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithFlags_Values[1], + y_Occurrence[1] -> 1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = 1, + 1 <= y_ExplicitVarSizeWithMarker_Marker -> y_Occurrence[y_ExplicitVarSizeWithMarker_Values[1]] + diff --git a/tests/exhaustive/basic/typed01/expected/model_4_3_3_2-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_4_3_3_2-solution000001.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_3_3_2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_3_3_2-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_4_3_3_2-solution000002.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_3_3_2-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_3_3_2-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_4_3_3_2-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_3_3_2-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_3_3_2.eprime b/tests/exhaustive/basic/typed01/expected/model_4_3_3_2.eprime new file mode 100644 index 0000000000..bb5e3f245d --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_3_3_2.eprime @@ -0,0 +1,31 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +find x_ExplicitVarSizeWithMarker_Marker: int(0..1) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +find y_ExplicitVarSizeWithMarker_Marker: int(0..1) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +branching on + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithFlags_Flags, + x_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithDummy, y_ExplicitVarSizeWithMarker_Marker, + y_ExplicitVarSizeWithMarker_Values] +such that + x_ExplicitVarSizeWithFlags_Flags[1] /\ + (1 <= y_ExplicitVarSizeWithMarker_Marker /\ + y_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithFlags_Values[1]) + -> false, + x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, + 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, + 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithMarker_Values[1], + x_ExplicitVarSizeWithFlags_Flags[1] -> + 1 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithFlags_Values[1], + y_ExplicitVarSizeWithDummy[1] != 2 -> + 1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = y_ExplicitVarSizeWithDummy[1], + 1 <= y_ExplicitVarSizeWithMarker_Marker -> + y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = y_ExplicitVarSizeWithMarker_Values[1] + diff --git a/tests/exhaustive/basic/typed01/expected/model_4_3_3_3-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_4_3_3_3-solution000001.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_3_3_3-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_3_3_3-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_4_3_3_3-solution000002.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_3_3_3-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_3_3_3-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_4_3_3_3-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_3_3_3-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_3_3_3.eprime b/tests/exhaustive/basic/typed01/expected/model_4_3_3_3.eprime new file mode 100644 index 0000000000..0943a035ed --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_3_3_3.eprime @@ -0,0 +1,25 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +find x_ExplicitVarSizeWithMarker_Marker: int(0..1) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +find y_ExplicitVarSizeWithMarker_Marker: int(0..1) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +branching on + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithFlags_Flags, + x_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values] +such that + x_ExplicitVarSizeWithFlags_Flags[1] /\ + (1 <= y_ExplicitVarSizeWithMarker_Marker /\ + y_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithFlags_Values[1]) + -> false, + x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, + 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, + 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithMarker_Values[1], + x_ExplicitVarSizeWithFlags_Flags[1] -> + 1 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithFlags_Values[1] + diff --git a/tests/exhaustive/basic/typed01/expected/model_4_3_3_4-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_4_3_3_4-solution000001.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_3_3_4-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_3_3_4-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_4_3_3_4-solution000002.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_3_3_4-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_3_3_4-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_4_3_3_4-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_3_3_4-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_3_3_4.eprime b/tests/exhaustive/basic/typed01/expected/model_4_3_3_4.eprime new file mode 100644 index 0000000000..14ce80e263 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_3_3_4.eprime @@ -0,0 +1,34 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +find x_ExplicitVarSizeWithMarker_Marker: int(0..1) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +find y_ExplicitVarSizeWithMarker_Marker: int(0..1) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +branching on + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithFlags_Flags, + x_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values, + y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values] +such that + x_ExplicitVarSizeWithFlags_Flags[1] /\ + (1 <= y_ExplicitVarSizeWithMarker_Marker /\ + y_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithFlags_Values[1]) + -> false, + x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, + 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, + 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithMarker_Values[1], + x_ExplicitVarSizeWithFlags_Flags[1] -> + 1 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithFlags_Values[1], + y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, + y_ExplicitVarSizeWithFlags_Flags[1] -> + 1 <= y_ExplicitVarSizeWithMarker_Marker /\ + y_ExplicitVarSizeWithMarker_Values[1] = y_ExplicitVarSizeWithFlags_Values[1], + 1 <= y_ExplicitVarSizeWithMarker_Marker -> + y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = y_ExplicitVarSizeWithMarker_Values[1] + diff --git a/tests/exhaustive/basic/typed01/expected/model_4_3_4_1-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_4_3_4_1-solution000001.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_3_4_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_3_4_1-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_4_3_4_1-solution000002.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_3_4_1-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_3_4_1-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_4_3_4_1-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_3_4_1-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_3_4_1.eprime b/tests/exhaustive/basic/typed01/expected/model_4_3_4_1.eprime new file mode 100644 index 0000000000..c2e457ed45 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_3_4_1.eprime @@ -0,0 +1,20 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +find y_ExplicitVarSizeWithMarker_Marker: int(0..1) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +find y_Occurrence: matrix indexed by [int(1)] of bool +branching on + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, y_Occurrence, + y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values] +such that + x_ExplicitVarSizeWithFlags_Flags[1] /\ + (1 <= y_ExplicitVarSizeWithMarker_Marker /\ + y_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithFlags_Values[1]) + -> false, + x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, + 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, + y_Occurrence[1] -> 1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = 1, + 1 <= y_ExplicitVarSizeWithMarker_Marker -> y_Occurrence[y_ExplicitVarSizeWithMarker_Values[1]] + diff --git a/tests/exhaustive/basic/typed01/expected/model_4_3_4_2-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_4_3_4_2-solution000001.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_3_4_2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_3_4_2-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_4_3_4_2-solution000002.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_3_4_2-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_3_4_2-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_4_3_4_2-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_3_4_2-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_3_4_2.eprime b/tests/exhaustive/basic/typed01/expected/model_4_3_4_2.eprime new file mode 100644 index 0000000000..942d4718ca --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_3_4_2.eprime @@ -0,0 +1,22 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +find y_ExplicitVarSizeWithMarker_Marker: int(0..1) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +branching on + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithDummy, + y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values] +such that + x_ExplicitVarSizeWithFlags_Flags[1] /\ + (1 <= y_ExplicitVarSizeWithMarker_Marker /\ + y_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithFlags_Values[1]) + -> false, + x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, + 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, + y_ExplicitVarSizeWithDummy[1] != 2 -> + 1 <= y_ExplicitVarSizeWithMarker_Marker /\ y_ExplicitVarSizeWithMarker_Values[1] = y_ExplicitVarSizeWithDummy[1], + 1 <= y_ExplicitVarSizeWithMarker_Marker -> + y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = y_ExplicitVarSizeWithMarker_Values[1] + diff --git a/tests/exhaustive/basic/typed01/expected/model_4_3_4_3-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_4_3_4_3-solution000001.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_3_4_3-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_3_4_3-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_4_3_4_3-solution000002.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_3_4_3-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_3_4_3-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_4_3_4_3-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_3_4_3-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_3_4_3.eprime b/tests/exhaustive/basic/typed01/expected/model_4_3_4_3.eprime new file mode 100644 index 0000000000..9d46ed4c1c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_3_4_3.eprime @@ -0,0 +1,17 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +find y_ExplicitVarSizeWithMarker_Marker: int(0..1) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +branching on + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithMarker_Marker, + y_ExplicitVarSizeWithMarker_Values] +such that + x_ExplicitVarSizeWithFlags_Flags[1] /\ + (1 <= y_ExplicitVarSizeWithMarker_Marker /\ + y_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithFlags_Values[1]) + -> false, + x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, + 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1 + diff --git a/tests/exhaustive/basic/typed01/expected/model_4_3_4_4-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_4_3_4_4-solution000001.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_3_4_4-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_3_4_4-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_4_3_4_4-solution000002.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_3_4_4-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_3_4_4-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_4_3_4_4-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_3_4_4-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_3_4_4.eprime b/tests/exhaustive/basic/typed01/expected/model_4_3_4_4.eprime new file mode 100644 index 0000000000..fd5e21a212 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_3_4_4.eprime @@ -0,0 +1,25 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +find y_ExplicitVarSizeWithMarker_Marker: int(0..1) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +branching on + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithFlags_Flags, + y_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values] +such that + x_ExplicitVarSizeWithFlags_Flags[1] /\ + (1 <= y_ExplicitVarSizeWithMarker_Marker /\ + y_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithFlags_Values[1]) + -> false, + x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, + 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, + y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, + y_ExplicitVarSizeWithFlags_Flags[1] -> + 1 <= y_ExplicitVarSizeWithMarker_Marker /\ + y_ExplicitVarSizeWithMarker_Values[1] = y_ExplicitVarSizeWithFlags_Values[1], + 1 <= y_ExplicitVarSizeWithMarker_Marker -> + y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = y_ExplicitVarSizeWithMarker_Values[1] + diff --git a/tests/exhaustive/basic/typed01/expected/model_4_4_1_1-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_4_4_1_1-solution000001.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_4_1_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_4_1_1-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_4_4_1_1-solution000002.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_4_1_1-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_4_1_1-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_4_4_1_1-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_4_1_1-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_4_1_1.eprime b/tests/exhaustive/basic/typed01/expected/model_4_4_1_1.eprime new file mode 100644 index 0000000000..fac7863f69 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_4_1_1.eprime @@ -0,0 +1,22 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +find x_Occurrence: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +find y_Occurrence: matrix indexed by [int(1)] of bool +branching on + [x_Occurrence, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, y_Occurrence, + y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values] +such that + x_ExplicitVarSizeWithFlags_Flags[1] /\ + (y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithFlags_Values[1]) + -> false, + x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, + y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, + x_Occurrence[1] -> x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = 1, + x_ExplicitVarSizeWithFlags_Flags[1] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[1]], + y_Occurrence[1] -> y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = 1, + y_ExplicitVarSizeWithFlags_Flags[1] -> y_Occurrence[y_ExplicitVarSizeWithFlags_Values[1]] + diff --git a/tests/exhaustive/basic/typed01/expected/model_4_4_1_2-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_4_4_1_2-solution000001.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_4_1_2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_4_1_2-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_4_4_1_2-solution000002.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_4_1_2-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_4_1_2-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_4_4_1_2-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_4_1_2-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_4_1_2.eprime b/tests/exhaustive/basic/typed01/expected/model_4_4_1_2.eprime new file mode 100644 index 0000000000..4bf7e90c1b --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_4_1_2.eprime @@ -0,0 +1,24 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +find x_Occurrence: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +branching on + [x_Occurrence, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithDummy, + y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values] +such that + x_ExplicitVarSizeWithFlags_Flags[1] /\ + (y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithFlags_Values[1]) + -> false, + x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, + y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, + x_Occurrence[1] -> x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = 1, + x_ExplicitVarSizeWithFlags_Flags[1] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[1]], + y_ExplicitVarSizeWithDummy[1] != 2 -> + y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = y_ExplicitVarSizeWithDummy[1], + y_ExplicitVarSizeWithFlags_Flags[1] -> + y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = y_ExplicitVarSizeWithFlags_Values[1] + diff --git a/tests/exhaustive/basic/typed01/expected/model_4_4_1_3-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_4_4_1_3-solution000001.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_4_1_3-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_4_1_3-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_4_4_1_3-solution000002.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_4_1_3-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_4_1_3-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_4_4_1_3-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_4_1_3-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_4_1_3.eprime b/tests/exhaustive/basic/typed01/expected/model_4_4_1_3.eprime new file mode 100644 index 0000000000..22da5be87d --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_4_1_3.eprime @@ -0,0 +1,28 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +find x_Occurrence: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +find y_ExplicitVarSizeWithMarker_Marker: int(0..1) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +branching on + [x_Occurrence, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, + y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithFlags_Flags, + y_ExplicitVarSizeWithFlags_Values] +such that + x_ExplicitVarSizeWithFlags_Flags[1] /\ + (y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithFlags_Values[1]) + -> false, + x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, + y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, + x_Occurrence[1] -> x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = 1, + x_ExplicitVarSizeWithFlags_Flags[1] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[1]], + 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, + 1 <= y_ExplicitVarSizeWithMarker_Marker -> + y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = y_ExplicitVarSizeWithMarker_Values[1], + y_ExplicitVarSizeWithFlags_Flags[1] -> + 1 <= y_ExplicitVarSizeWithMarker_Marker /\ + y_ExplicitVarSizeWithMarker_Values[1] = y_ExplicitVarSizeWithFlags_Values[1] + diff --git a/tests/exhaustive/basic/typed01/expected/model_4_4_1_4-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_4_4_1_4-solution000001.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_4_1_4-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_4_1_4-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_4_4_1_4-solution000002.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_4_1_4-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_4_1_4-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_4_4_1_4-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_4_1_4-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_4_1_4.eprime b/tests/exhaustive/basic/typed01/expected/model_4_4_1_4.eprime new file mode 100644 index 0000000000..d10bd485ff --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_4_1_4.eprime @@ -0,0 +1,19 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +find x_Occurrence: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +branching on + [x_Occurrence, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, + y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values] +such that + x_ExplicitVarSizeWithFlags_Flags[1] /\ + (y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithFlags_Values[1]) + -> false, + x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, + y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, + x_Occurrence[1] -> x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = 1, + x_ExplicitVarSizeWithFlags_Flags[1] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[1]] + diff --git a/tests/exhaustive/basic/typed01/expected/model_4_4_2_1-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_4_4_2_1-solution000001.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_4_2_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_4_2_1-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_4_4_2_1-solution000002.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_4_2_1-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_4_2_1-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_4_4_2_1-solution000003.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_4_2_1-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_4_2_1.eprime b/tests/exhaustive/basic/typed01/expected/model_4_4_2_1.eprime new file mode 100644 index 0000000000..15f0335802 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_4_2_1.eprime @@ -0,0 +1,24 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +find y_Occurrence: matrix indexed by [int(1)] of bool +branching on + [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, y_Occurrence, + y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values] +such that + x_ExplicitVarSizeWithFlags_Flags[1] /\ + (y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithFlags_Values[1]) + -> false, + x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, + y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, + x_ExplicitVarSizeWithDummy[1] != 2 -> + x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithDummy[1], + x_ExplicitVarSizeWithFlags_Flags[1] -> + x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithFlags_Values[1], + y_Occurrence[1] -> y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = 1, + y_ExplicitVarSizeWithFlags_Flags[1] -> y_Occurrence[y_ExplicitVarSizeWithFlags_Values[1]] + diff --git a/tests/exhaustive/basic/typed01/expected/model_4_4_2_2-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_4_4_2_2-solution000001.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_4_2_2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_4_2_2-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_4_4_2_2-solution000002.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_4_2_2-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_4_2_2-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_4_4_2_2-solution000003.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_4_2_2-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_4_2_2.eprime b/tests/exhaustive/basic/typed01/expected/model_4_4_2_2.eprime new file mode 100644 index 0000000000..58f520e750 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_4_2_2.eprime @@ -0,0 +1,26 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +branching on + [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, + y_ExplicitVarSizeWithDummy, y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values] +such that + x_ExplicitVarSizeWithFlags_Flags[1] /\ + (y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithFlags_Values[1]) + -> false, + x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, + y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, + x_ExplicitVarSizeWithDummy[1] != 2 -> + x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithDummy[1], + x_ExplicitVarSizeWithFlags_Flags[1] -> + x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithFlags_Values[1], + y_ExplicitVarSizeWithDummy[1] != 2 -> + y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = y_ExplicitVarSizeWithDummy[1], + y_ExplicitVarSizeWithFlags_Flags[1] -> + y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = y_ExplicitVarSizeWithFlags_Values[1] + diff --git a/tests/exhaustive/basic/typed01/expected/model_4_4_2_3-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_4_4_2_3-solution000001.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_4_2_3-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_4_2_3-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_4_4_2_3-solution000002.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_4_2_3-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_4_2_3-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_4_4_2_3-solution000003.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_4_2_3-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_4_2_3.eprime b/tests/exhaustive/basic/typed01/expected/model_4_4_2_3.eprime new file mode 100644 index 0000000000..d112babb4a --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_4_2_3.eprime @@ -0,0 +1,30 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +find y_ExplicitVarSizeWithMarker_Marker: int(0..1) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +branching on + [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, + y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithFlags_Flags, + y_ExplicitVarSizeWithFlags_Values] +such that + x_ExplicitVarSizeWithFlags_Flags[1] /\ + (y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithFlags_Values[1]) + -> false, + x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, + y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, + x_ExplicitVarSizeWithDummy[1] != 2 -> + x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithDummy[1], + x_ExplicitVarSizeWithFlags_Flags[1] -> + x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithFlags_Values[1], + 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, + 1 <= y_ExplicitVarSizeWithMarker_Marker -> + y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = y_ExplicitVarSizeWithMarker_Values[1], + y_ExplicitVarSizeWithFlags_Flags[1] -> + 1 <= y_ExplicitVarSizeWithMarker_Marker /\ + y_ExplicitVarSizeWithMarker_Values[1] = y_ExplicitVarSizeWithFlags_Values[1] + diff --git a/tests/exhaustive/basic/typed01/expected/model_4_4_2_4-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_4_4_2_4-solution000001.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_4_2_4-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_4_2_4-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_4_4_2_4-solution000002.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_4_2_4-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_4_2_4-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_4_4_2_4-solution000003.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_4_2_4-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_4_2_4.eprime b/tests/exhaustive/basic/typed01/expected/model_4_4_2_4.eprime new file mode 100644 index 0000000000..b99521dc71 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_4_2_4.eprime @@ -0,0 +1,21 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +branching on + [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, + y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values] +such that + x_ExplicitVarSizeWithFlags_Flags[1] /\ + (y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithFlags_Values[1]) + -> false, + x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, + y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, + x_ExplicitVarSizeWithDummy[1] != 2 -> + x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithDummy[1], + x_ExplicitVarSizeWithFlags_Flags[1] -> + x_ExplicitVarSizeWithDummy[1] != 2 /\ x_ExplicitVarSizeWithDummy[1] = x_ExplicitVarSizeWithFlags_Values[1] + diff --git a/tests/exhaustive/basic/typed01/expected/model_4_4_3_1-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_4_4_3_1-solution000001.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_4_3_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_4_3_1-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_4_4_3_1-solution000002.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_4_3_1-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_4_3_1-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_4_4_3_1-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_4_3_1-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_4_3_1.eprime b/tests/exhaustive/basic/typed01/expected/model_4_4_3_1.eprime new file mode 100644 index 0000000000..618af31d11 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_4_3_1.eprime @@ -0,0 +1,28 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +find x_ExplicitVarSizeWithMarker_Marker: int(0..1) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +find y_Occurrence: matrix indexed by [int(1)] of bool +branching on + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithFlags_Flags, + x_ExplicitVarSizeWithFlags_Values, y_Occurrence, y_ExplicitVarSizeWithFlags_Flags, + y_ExplicitVarSizeWithFlags_Values] +such that + x_ExplicitVarSizeWithFlags_Flags[1] /\ + (y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithFlags_Values[1]) + -> false, + x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, + y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, + 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithMarker_Values[1], + x_ExplicitVarSizeWithFlags_Flags[1] -> + 1 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithFlags_Values[1], + y_Occurrence[1] -> y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = 1, + y_ExplicitVarSizeWithFlags_Flags[1] -> y_Occurrence[y_ExplicitVarSizeWithFlags_Values[1]] + diff --git a/tests/exhaustive/basic/typed01/expected/model_4_4_3_2-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_4_4_3_2-solution000001.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_4_3_2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_4_3_2-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_4_4_3_2-solution000002.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_4_3_2-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_4_3_2-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_4_4_3_2-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_4_3_2-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_4_3_2.eprime b/tests/exhaustive/basic/typed01/expected/model_4_4_3_2.eprime new file mode 100644 index 0000000000..9e776b20fa --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_4_3_2.eprime @@ -0,0 +1,30 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +find x_ExplicitVarSizeWithMarker_Marker: int(0..1) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +branching on + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithFlags_Flags, + x_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithDummy, y_ExplicitVarSizeWithFlags_Flags, + y_ExplicitVarSizeWithFlags_Values] +such that + x_ExplicitVarSizeWithFlags_Flags[1] /\ + (y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithFlags_Values[1]) + -> false, + x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, + y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, + 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithMarker_Values[1], + x_ExplicitVarSizeWithFlags_Flags[1] -> + 1 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithFlags_Values[1], + y_ExplicitVarSizeWithDummy[1] != 2 -> + y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = y_ExplicitVarSizeWithDummy[1], + y_ExplicitVarSizeWithFlags_Flags[1] -> + y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = y_ExplicitVarSizeWithFlags_Values[1] + diff --git a/tests/exhaustive/basic/typed01/expected/model_4_4_3_3-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_4_4_3_3-solution000001.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_4_3_3-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_4_3_3-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_4_4_3_3-solution000002.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_4_3_3-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_4_3_3-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_4_4_3_3-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_4_3_3-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_4_3_3.eprime b/tests/exhaustive/basic/typed01/expected/model_4_4_3_3.eprime new file mode 100644 index 0000000000..ed2298ccfb --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_4_3_3.eprime @@ -0,0 +1,33 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +find x_ExplicitVarSizeWithMarker_Marker: int(0..1) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +find y_ExplicitVarSizeWithMarker_Marker: int(0..1) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +branching on + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithFlags_Flags, + x_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithMarker_Marker, y_ExplicitVarSizeWithMarker_Values, + y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values] +such that + x_ExplicitVarSizeWithFlags_Flags[1] /\ + (y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithFlags_Values[1]) + -> false, + x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, + y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, + 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithMarker_Values[1], + x_ExplicitVarSizeWithFlags_Flags[1] -> + 1 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithFlags_Values[1], + 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, + 1 <= y_ExplicitVarSizeWithMarker_Marker -> + y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = y_ExplicitVarSizeWithMarker_Values[1], + y_ExplicitVarSizeWithFlags_Flags[1] -> + 1 <= y_ExplicitVarSizeWithMarker_Marker /\ + y_ExplicitVarSizeWithMarker_Values[1] = y_ExplicitVarSizeWithFlags_Values[1] + diff --git a/tests/exhaustive/basic/typed01/expected/model_4_4_3_4-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_4_4_3_4-solution000001.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_4_3_4-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_4_3_4-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_4_4_3_4-solution000002.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_4_3_4-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_4_3_4-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_4_4_3_4-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_4_3_4-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_4_3_4.eprime b/tests/exhaustive/basic/typed01/expected/model_4_4_3_4.eprime new file mode 100644 index 0000000000..8250b9e599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_4_3_4.eprime @@ -0,0 +1,24 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +find x_ExplicitVarSizeWithMarker_Marker: int(0..1) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +branching on + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithFlags_Flags, + x_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values] +such that + x_ExplicitVarSizeWithFlags_Flags[1] /\ + (y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithFlags_Values[1]) + -> false, + x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, + y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, + 1 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[1] = 1, + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithFlags_Flags[1] /\ x_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithMarker_Values[1], + x_ExplicitVarSizeWithFlags_Flags[1] -> + 1 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[1] = x_ExplicitVarSizeWithFlags_Values[1] + diff --git a/tests/exhaustive/basic/typed01/expected/model_4_4_4_1-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_4_4_4_1-solution000001.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_4_4_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_4_4_1-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_4_4_4_1-solution000002.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_4_4_1-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_4_4_1-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_4_4_4_1-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_4_4_1-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_4_4_1.eprime b/tests/exhaustive/basic/typed01/expected/model_4_4_4_1.eprime new file mode 100644 index 0000000000..dad4584015 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_4_4_1.eprime @@ -0,0 +1,19 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +find y_Occurrence: matrix indexed by [int(1)] of bool +branching on + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, y_Occurrence, + y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values] +such that + x_ExplicitVarSizeWithFlags_Flags[1] /\ + (y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithFlags_Values[1]) + -> false, + x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, + y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, + y_Occurrence[1] -> y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = 1, + y_ExplicitVarSizeWithFlags_Flags[1] -> y_Occurrence[y_ExplicitVarSizeWithFlags_Values[1]] + diff --git a/tests/exhaustive/basic/typed01/expected/model_4_4_4_2-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_4_4_4_2-solution000001.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_4_4_2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_4_4_2-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_4_4_4_2-solution000002.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_4_4_2-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_4_4_2-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_4_4_4_2-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_4_4_2-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_4_4_2.eprime b/tests/exhaustive/basic/typed01/expected/model_4_4_4_2.eprime new file mode 100644 index 0000000000..e1adf983e5 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_4_4_2.eprime @@ -0,0 +1,21 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +find y_ExplicitVarSizeWithDummy: matrix indexed by [int(1)] of int(1, 2) +branching on + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithDummy, + y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values] +such that + x_ExplicitVarSizeWithFlags_Flags[1] /\ + (y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithFlags_Values[1]) + -> false, + x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, + y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, + y_ExplicitVarSizeWithDummy[1] != 2 -> + y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = y_ExplicitVarSizeWithDummy[1], + y_ExplicitVarSizeWithFlags_Flags[1] -> + y_ExplicitVarSizeWithDummy[1] != 2 /\ y_ExplicitVarSizeWithDummy[1] = y_ExplicitVarSizeWithFlags_Values[1] + diff --git a/tests/exhaustive/basic/typed01/expected/model_4_4_4_3-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_4_4_4_3-solution000001.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_4_4_3-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_4_4_3-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_4_4_4_3-solution000002.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_4_4_3-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_4_4_3-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_4_4_4_3-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_4_4_3-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_4_4_3.eprime b/tests/exhaustive/basic/typed01/expected/model_4_4_4_3.eprime new file mode 100644 index 0000000000..6456aac8f4 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_4_4_3.eprime @@ -0,0 +1,24 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +find y_ExplicitVarSizeWithMarker_Marker: int(0..1) +find y_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1)] of int(1) +branching on + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithMarker_Marker, + y_ExplicitVarSizeWithMarker_Values, y_ExplicitVarSizeWithFlags_Flags, y_ExplicitVarSizeWithFlags_Values] +such that + x_ExplicitVarSizeWithFlags_Flags[1] /\ + (y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithFlags_Values[1]) + -> false, + x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, + y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1, + 1 > y_ExplicitVarSizeWithMarker_Marker -> y_ExplicitVarSizeWithMarker_Values[1] = 1, + 1 <= y_ExplicitVarSizeWithMarker_Marker -> + y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = y_ExplicitVarSizeWithMarker_Values[1], + y_ExplicitVarSizeWithFlags_Flags[1] -> + 1 <= y_ExplicitVarSizeWithMarker_Marker /\ + y_ExplicitVarSizeWithMarker_Values[1] = y_ExplicitVarSizeWithFlags_Values[1] + diff --git a/tests/exhaustive/basic/typed01/expected/model_4_4_4_4-solution000001.solution b/tests/exhaustive/basic/typed01/expected/model_4_4_4_4-solution000001.solution new file mode 100644 index 0000000000..a30dffc20c --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_4_4_4-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_4_4_4-solution000002.solution b/tests/exhaustive/basic/typed01/expected/model_4_4_4_4-solution000002.solution new file mode 100644 index 0000000000..9b282fd599 --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_4_4_4-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {} +letting y be {1} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_4_4_4-solution000003.solution b/tests/exhaustive/basic/typed01/expected/model_4_4_4_4-solution000003.solution new file mode 100644 index 0000000000..8437ede4ce --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_4_4_4-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting x be {1} +letting y be {} diff --git a/tests/exhaustive/basic/typed01/expected/model_4_4_4_4.eprime b/tests/exhaustive/basic/typed01/expected/model_4_4_4_4.eprime new file mode 100644 index 0000000000..137067773d --- /dev/null +++ b/tests/exhaustive/basic/typed01/expected/model_4_4_4_4.eprime @@ -0,0 +1,16 @@ +language ESSENCE' 1.0 + +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +find y_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1)] of bool +find y_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1)] of int(1) +branching on + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, y_ExplicitVarSizeWithFlags_Flags, + y_ExplicitVarSizeWithFlags_Values] +such that + x_ExplicitVarSizeWithFlags_Flags[1] /\ + (y_ExplicitVarSizeWithFlags_Flags[1] /\ y_ExplicitVarSizeWithFlags_Values[1] = x_ExplicitVarSizeWithFlags_Values[1]) + -> false, + x_ExplicitVarSizeWithFlags_Flags[1] = false -> x_ExplicitVarSizeWithFlags_Values[1] = 1, + y_ExplicitVarSizeWithFlags_Flags[1] = false -> y_ExplicitVarSizeWithFlags_Values[1] = 1 + From 31fccdaa7fe98b01e0c390f1a935ba4f45d44b04 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?=C3=96zg=C3=BCr=20Akg=C3=BCn?= Date: Mon, 26 Feb 2024 13:29:47 +0000 Subject: [PATCH 124/229] post-merge-test-update 2 --- .../expected/model-solution000001.solution | 28 + .../issues/102/expected/model.eprime.orig | 88 -- .../model_1_1-solution000001.solution | 6 + .../issues/166/expected/model_1_1.eprime.orig | 46 - .../model_1_2-solution000001.solution | 6 + .../issues/166/expected/model_1_2.eprime.orig | 83 -- .../model_1_3-solution000001.solution | 6 + .../issues/166/expected/model_1_3.eprime.orig | 88 -- .../model_1_4-solution000001.solution | 6 + .../issues/166/expected/model_1_4.eprime.orig | 92 -- .../model_2_1-solution000001.solution | 6 + .../issues/166/expected/model_2_1.eprime.orig | 139 -- .../model_2_2-solution000001.solution | 6 + .../issues/166/expected/model_2_2.eprime.orig | 111 -- .../model_2_3-solution000001.solution | 6 + .../issues/166/expected/model_2_3.eprime.orig | 159 --- .../model_2_4-solution000001.solution | 6 + .../issues/166/expected/model_2_4.eprime.orig | 163 --- .../model_3_1-solution000001.solution | 6 + .../issues/166/expected/model_3_1.eprime.orig | 148 -- .../model_3_2-solution000001.solution | 6 + .../issues/166/expected/model_3_2.eprime.orig | 166 --- .../model_3_3-solution000001.solution | 6 + .../issues/166/expected/model_3_3.eprime.orig | 118 -- .../model_3_4-solution000001.solution | 6 + .../issues/166/expected/model_3_4.eprime.orig | 173 --- .../model_4_1-solution000001.solution | 6 + .../issues/166/expected/model_4_1.eprime.orig | 154 --- .../model_4_2-solution000001.solution | 6 + .../issues/166/expected/model_4_2.eprime.orig | 169 --- .../model_4_3-solution000001.solution | 6 + .../issues/166/expected/model_4_3.eprime.orig | 172 --- .../model_4_4-solution000001.solution | 6 + .../issues/166/expected/model_4_4.eprime.orig | 121 -- .../issues/200/expected/model_1_2.eprime | 9 - .../issues/200/expected/model_2_1.eprime | 10 - .../issues/200/expected/model_2_2.eprime | 7 - .../model_1_1-1-solution000001.solution | 3 + .../212/expected/model_1_1-1.eprime-param | 6 + .../issues/212/expected/model_1_1.eprime | 14 + .../model_1_2-1-solution000001.solution | 3 + .../212/expected/model_1_2-1.eprime-param | 6 + .../issues/212/expected/model_1_2.eprime | 23 + .../model_1_3-1-solution000001.solution | 3 + .../212/expected/model_1_3-1.eprime-param | 6 + .../issues/212/expected/model_1_3.eprime | 26 + .../model_1_4-1-solution000001.solution | 3 + .../212/expected/model_1_4-1.eprime-param | 6 + .../issues/212/expected/model_1_4.eprime | 26 + .../model_2_1-1-solution000001.solution | 3 + .../212/expected/model_2_1-1.eprime-param | 6 + .../issues/212/expected/model_2_1.eprime | 25 + .../model_2_2-1-solution000001.solution | 3 + .../212/expected/model_2_2-1.eprime-param | 6 + .../issues/212/expected/model_2_2.eprime | 20 + .../model_2_3-1-solution000001.solution | 3 + .../212/expected/model_2_3-1.eprime-param | 6 + .../issues/212/expected/model_2_3.eprime | 36 + .../model_2_4-1-solution000001.solution | 3 + .../212/expected/model_2_4-1.eprime-param | 6 + .../issues/212/expected/model_2_4.eprime | 37 + .../model_3_1-1-solution000001.solution | 3 + .../212/expected/model_3_1-1.eprime-param | 6 + .../issues/212/expected/model_3_1.eprime | 29 + .../model_3_2-1-solution000001.solution | 3 + .../212/expected/model_3_2-1.eprime-param | 6 + .../issues/212/expected/model_3_2.eprime | 36 + .../model_3_3-1-solution000001.solution | 3 + .../212/expected/model_3_3-1.eprime-param | 6 + .../issues/212/expected/model_3_3.eprime | 22 + .../model_3_4-1-solution000001.solution | 3 + .../212/expected/model_3_4-1.eprime-param | 6 + .../issues/212/expected/model_3_4.eprime | 41 + .../model_4_1-1-solution000001.solution | 3 + .../212/expected/model_4_1-1.eprime-param | 6 + .../issues/212/expected/model_4_1.eprime | 29 + .../model_4_2-1-solution000001.solution | 3 + .../212/expected/model_4_2-1.eprime-param | 6 + .../issues/212/expected/model_4_2.eprime | 37 + .../model_4_3-1-solution000001.solution | 3 + .../212/expected/model_4_3-1.eprime-param | 6 + .../issues/212/expected/model_4_3.eprime | 41 + .../model_4_4-1-solution000001.solution | 3 + .../212/expected/model_4_4-1.eprime-param | 6 + .../issues/212/expected/model_4_4.eprime | 23 + .../issues/261/expected/model_1.eprime | 2 +- .../model_1_1-p1-solution000001.solution | 6 + .../model_1_1-p1-solution000002.solution | 7 + .../model_1_1-p1-solution000003.solution | 7 + .../model_1_1-p1-solution000004.solution | 7 + .../model_1_1-p1-solution000005.solution | 7 + .../model_1_1-p1-solution000006.solution | 7 + .../model_1_1-p1-solution000007.solution | 7 + .../model_1_1-p1-solution000008.solution | 7 + .../286/expected/model_1_1-p1.eprime-param | 3 + .../issues/286/expected/model_1_1.eprime | 43 + .../model_1_2-p1-solution000001.solution | 6 + .../model_1_2-p1-solution000002.solution | 7 + .../model_1_2-p1-solution000003.solution | 7 + .../model_1_2-p1-solution000004.solution | 7 + .../model_1_2-p1-solution000005.solution | 7 + .../model_1_2-p1-solution000006.solution | 7 + .../model_1_2-p1-solution000007.solution | 7 + .../model_1_2-p1-solution000008.solution | 7 + .../286/expected/model_1_2-p1.eprime-param | 3 + .../issues/286/expected/model_1_2.eprime | 122 ++ .../model_1_3-p1-solution000001.solution | 6 + .../model_1_3-p1-solution000002.solution | 7 + .../model_1_3-p1-solution000003.solution | 7 + .../model_1_3-p1-solution000004.solution | 7 + .../model_1_3-p1-solution000005.solution | 7 + .../model_1_3-p1-solution000006.solution | 7 + .../model_1_3-p1-solution000007.solution | 7 + .../model_1_3-p1-solution000008.solution | 7 + .../286/expected/model_1_3-p1.eprime-param | 3 + .../issues/286/expected/model_1_3.eprime.orig | 132 -- .../model_1_4-p1-solution000001.solution | 6 + .../model_1_4-p1-solution000002.solution | 7 + .../model_1_4-p1-solution000003.solution | 7 + .../model_1_4-p1-solution000004.solution | 7 + .../model_1_4-p1-solution000005.solution | 7 + .../model_1_4-p1-solution000006.solution | 7 + .../model_1_4-p1-solution000007.solution | 7 + .../model_1_4-p1-solution000008.solution | 7 + .../286/expected/model_1_4-p1.eprime-param | 3 + .../issues/286/expected/model_1_4.eprime | 91 ++ .../model_2_1-p1-solution000001.solution | 6 + .../model_2_1-p1-solution000002.solution | 7 + .../model_2_1-p1-solution000003.solution | 7 + .../model_2_1-p1-solution000004.solution | 7 + .../model_2_1-p1-solution000005.solution | 7 + .../model_2_1-p1-solution000006.solution | 7 + .../model_2_1-p1-solution000007.solution | 7 + .../model_2_1-p1-solution000008.solution | 7 + .../286/expected/model_2_1-p1.eprime-param | 3 + .../issues/286/expected/model_2_1.eprime | 122 ++ .../model_2_2-p1-solution000001.solution | 6 + .../model_2_2-p1-solution000002.solution | 7 + .../model_2_2-p1-solution000003.solution | 7 + .../model_2_2-p1-solution000004.solution | 7 + .../model_2_2-p1-solution000005.solution | 7 + .../model_2_2-p1-solution000006.solution | 7 + .../model_2_2-p1-solution000007.solution | 7 + .../model_2_2-p1-solution000008.solution | 7 + .../286/expected/model_2_2-p1.eprime-param | 3 + .../issues/286/expected/model_2_2.eprime | 65 + .../model_2_3-p1-solution000001.solution | 6 + .../model_2_3-p1-solution000002.solution | 7 + .../model_2_3-p1-solution000003.solution | 7 + .../model_2_3-p1-solution000004.solution | 7 + .../model_2_3-p1-solution000005.solution | 7 + .../model_2_3-p1-solution000006.solution | 7 + .../model_2_3-p1-solution000007.solution | 7 + .../model_2_3-p1-solution000008.solution | 7 + .../286/expected/model_2_3-p1.eprime-param | 3 + .../issues/286/expected/model_2_3.eprime.orig | 160 --- .../model_2_4-p1-solution000001.solution | 6 + .../model_2_4-p1-solution000002.solution | 7 + .../model_2_4-p1-solution000003.solution | 7 + .../model_2_4-p1-solution000004.solution | 7 + .../model_2_4-p1-solution000005.solution | 7 + .../model_2_4-p1-solution000006.solution | 7 + .../model_2_4-p1-solution000007.solution | 7 + .../model_2_4-p1-solution000008.solution | 7 + .../286/expected/model_2_4-p1.eprime-param | 3 + .../issues/286/expected/model_2_4.eprime | 121 ++ .../model_3_1-p1-solution000001.solution | 6 + .../model_3_1-p1-solution000002.solution | 7 + .../model_3_1-p1-solution000003.solution | 7 + .../model_3_1-p1-solution000004.solution | 7 + .../model_3_1-p1-solution000005.solution | 7 + .../model_3_1-p1-solution000006.solution | 7 + .../model_3_1-p1-solution000007.solution | 7 + .../model_3_1-p1-solution000008.solution | 7 + .../286/expected/model_3_1-p1.eprime-param | 3 + .../issues/286/expected/model_3_1.eprime.orig | 132 -- .../model_3_2-p1-solution000001.solution | 6 + .../model_3_2-p1-solution000002.solution | 7 + .../model_3_2-p1-solution000003.solution | 7 + .../model_3_2-p1-solution000004.solution | 7 + .../model_3_2-p1-solution000005.solution | 7 + .../model_3_2-p1-solution000006.solution | 7 + .../model_3_2-p1-solution000007.solution | 7 + .../model_3_2-p1-solution000008.solution | 7 + .../286/expected/model_3_2-p1.eprime-param | 3 + .../issues/286/expected/model_3_2.eprime.orig | 160 --- .../model_3_3-p1-solution000001.solution | 6 + .../model_3_3-p1-solution000002.solution | 7 + .../model_3_3-p1-solution000003.solution | 7 + .../model_3_3-p1-solution000004.solution | 7 + .../model_3_3-p1-solution000005.solution | 7 + .../model_3_3-p1-solution000006.solution | 7 + .../model_3_3-p1-solution000007.solution | 7 + .../model_3_3-p1-solution000008.solution | 7 + .../286/expected/model_3_3-p1.eprime-param | 3 + .../issues/286/expected/model_3_3.eprime.orig | 71 - .../model_3_4-p1-solution000001.solution | 6 + .../model_3_4-p1-solution000002.solution | 7 + .../model_3_4-p1-solution000003.solution | 7 + .../model_3_4-p1-solution000004.solution | 7 + .../model_3_4-p1-solution000005.solution | 7 + .../model_3_4-p1-solution000006.solution | 7 + .../model_3_4-p1-solution000007.solution | 7 + .../model_3_4-p1-solution000008.solution | 7 + .../286/expected/model_3_4-p1.eprime-param | 3 + .../issues/286/expected/model_3_4.eprime.orig | 131 -- .../model_4_1-p1-solution000001.solution | 6 + .../model_4_1-p1-solution000002.solution | 7 + .../model_4_1-p1-solution000003.solution | 7 + .../model_4_1-p1-solution000004.solution | 7 + .../model_4_1-p1-solution000005.solution | 7 + .../model_4_1-p1-solution000006.solution | 7 + .../model_4_1-p1-solution000007.solution | 7 + .../model_4_1-p1-solution000008.solution | 7 + .../286/expected/model_4_1-p1.eprime-param | 3 + .../issues/286/expected/model_4_1.eprime | 88 ++ .../model_4_2-p1-solution000001.solution | 6 + .../model_4_2-p1-solution000002.solution | 7 + .../model_4_2-p1-solution000003.solution | 7 + .../model_4_2-p1-solution000004.solution | 7 + .../model_4_2-p1-solution000005.solution | 7 + .../model_4_2-p1-solution000006.solution | 7 + .../model_4_2-p1-solution000007.solution | 7 + .../model_4_2-p1-solution000008.solution | 7 + .../286/expected/model_4_2-p1.eprime-param | 3 + .../issues/286/expected/model_4_2.eprime | 118 ++ .../model_4_3-p1-solution000001.solution | 6 + .../model_4_3-p1-solution000002.solution | 7 + .../model_4_3-p1-solution000003.solution | 7 + .../model_4_3-p1-solution000004.solution | 7 + .../model_4_3-p1-solution000005.solution | 7 + .../model_4_3-p1-solution000006.solution | 7 + .../model_4_3-p1-solution000007.solution | 7 + .../model_4_3-p1-solution000008.solution | 7 + .../286/expected/model_4_3-p1.eprime-param | 3 + .../issues/286/expected/model_4_3.eprime.orig | 129 -- .../model_4_4-p1-solution000001.solution | 6 + .../model_4_4-p1-solution000002.solution | 7 + .../model_4_4-p1-solution000003.solution | 7 + .../model_4_4-p1-solution000004.solution | 7 + .../model_4_4-p1-solution000005.solution | 7 + .../model_4_4-p1-solution000006.solution | 7 + .../model_4_4-p1-solution000007.solution | 7 + .../model_4_4-p1-solution000008.solution | 7 + .../286/expected/model_4_4-p1.eprime-param | 3 + .../issues/286/expected/model_4_4.eprime | 38 + .../model-cyc1-solution000001.solution | 3 + .../expected/model-cyc1.eprime-param | 6 + .../model-cyc2-solution000001.solution | 3 + .../expected/model-cyc2.eprime-param | 6 + .../model-non-solution000001.solution | 3 + .../expected/model-non.eprime-param | 6 + .../model-inst-solution000001.solution | 182 +++ .../expected/model-inst.eprime-param | 98 ++ .../gchq_2016/expected/model.eprime | 127 ++ .../model_1_1_1-p1-solution000001.solution | 3 + .../expected/model_1_1_1-p1.eprime-param | 7 + .../model_1_1_1-p2-solution000001.solution | 3 + .../model_1_1_1-p2-solution000002.solution | 3 + .../expected/model_1_1_1-p2.eprime-param | 7 + .../subsetSum/expected/model_1_1_1.eprime | 27 + .../model_1_1_2-p1-solution000001.solution | 3 + .../expected/model_1_1_2-p1.eprime-param | 7 + .../model_1_1_2-p2-solution000001.solution | 3 + .../model_1_1_2-p2-solution000002.solution | 3 + .../expected/model_1_1_2-p2.eprime-param | 7 + .../subsetSum/expected/model_1_1_2.eprime | 49 + .../model_1_2_1-p1-solution000001.solution | 3 + .../expected/model_1_2_1-p1.eprime-param | 7 + .../model_1_2_1-p2-solution000001.solution | 3 + .../model_1_2_1-p2-solution000002.solution | 3 + .../expected/model_1_2_1-p2.eprime-param | 7 + .../subsetSum/expected/model_1_2_1.eprime | 49 + .../model_2_1_1-p1-solution000001.solution | 3 + .../expected/model_2_1_1-p1.eprime-param | 7 + .../model_2_1_1-p2-solution000001.solution | 3 + .../model_2_1_1-p2-solution000002.solution | 3 + .../expected/model_2_1_1-p2.eprime-param | 7 + .../subsetSum/expected/model_2_1_1.eprime | 49 + .../model_2_2_1-p1-solution000001.solution | 3 + .../expected/model_2_2_1-p1.eprime-param | 7 + .../model_2_2_1-p2-solution000001.solution | 3 + .../model_2_2_1-p2-solution000002.solution | 3 + .../expected/model_2_2_1-p2.eprime-param | 7 + .../subsetSum/expected/model_2_2_1.eprime | 49 + .../model_2_2_2-p1-solution000001.solution | 3 + .../expected/model_2_2_2-p1.eprime-param | 7 + .../model_2_2_2-p2-solution000001.solution | 3 + .../model_2_2_2-p2-solution000002.solution | 3 + .../expected/model_2_2_2-p2.eprime-param | 7 + .../subsetSum/expected/model_2_2_2.eprime | 28 + .../expected/model-solution000001.solution | 4 + .../expected/model-solution000002.solution | 4 + .../expected/model-solution000003.solution | 4 + .../expected/model-solution000004.solution | 4 + .../expected/model-solution000005.solution | 4 + .../expected/model-solution000006.solution | 4 + .../expected/model-solution000007.solution | 4 + .../expected/model-solution000008.solution | 4 + .../expected/model-solution000009.solution | 4 + .../expected/model-solution000010.solution | 4 + .../expected/model-solution000011.solution | 4 + .../expected/model-solution000012.solution | 4 + .../expected/model-solution000013.solution | 4 + .../expected/model-solution000014.solution | 4 + .../expected/model-solution000015.solution | 4 + .../expected/model-solution000016.solution | 4 + .../expected/model-solution000017.solution | 4 + .../expected/model-solution000018.solution | 4 + .../expected/model-solution000019.solution | 4 + .../expected/model-solution000020.solution | 4 + .../expected/model-solution000021.solution | 4 + .../expected/model-solution000022.solution | 4 + .../expected/model-solution000023.solution | 4 + .../expected/model-solution000024.solution | 4 + .../expected/model-solution000025.solution | 4 + .../expected/model-solution000026.solution | 4 + .../expected/model-solution000027.solution | 4 + .../expected/model-solution000028.solution | 4 + .../expected/model-solution000029.solution | 4 + .../expected/model-solution000030.solution | 4 + .../expected/model-solution000031.solution | 4 + .../expected/model-solution000032.solution | 4 + .../expected/model-solution000033.solution | 4 + .../expected/model-solution000034.solution | 4 + .../expected/model-solution000035.solution | 4 + .../expected/model-solution000036.solution | 4 + .../expected/model.eprime | 91 ++ .../model_1_1_1_1-solution000001.solution | 4 + .../model_1_1_1_1-solution000002.solution | 4 + .../model_1_1_1_1-solution000003.solution | 4 + .../model_1_1_1_1-solution000004.solution | 4 + .../model_1_1_1_1-solution000005.solution | 4 + .../model_1_1_1_1-solution000006.solution | 4 + .../model_1_1_1_2-solution000001.solution | 4 + .../model_1_1_1_2-solution000002.solution | 4 + .../model_1_1_1_2-solution000003.solution | 4 + .../model_1_1_1_2-solution000004.solution | 4 + .../model_1_1_1_2-solution000005.solution | 4 + .../model_1_1_1_2-solution000006.solution | 4 + .../model_1_1_1_3-solution000001.solution | 4 + .../model_1_1_1_3-solution000002.solution | 4 + .../model_1_1_1_3-solution000003.solution | 4 + .../model_1_1_1_3-solution000004.solution | 4 + .../model_1_1_1_3-solution000005.solution | 4 + .../model_1_1_1_3-solution000006.solution | 4 + .../model_1_1_2_1-solution000001.solution | 4 + .../model_1_1_2_1-solution000002.solution | 4 + .../model_1_1_2_1-solution000003.solution | 4 + .../model_1_1_2_1-solution000004.solution | 4 + .../model_1_1_2_1-solution000005.solution | 4 + .../model_1_1_2_1-solution000006.solution | 4 + .../model_1_1_2_2-solution000001.solution | 4 + .../model_1_1_2_2-solution000002.solution | 4 + .../model_1_1_2_2-solution000003.solution | 4 + .../model_1_1_2_2-solution000004.solution | 4 + .../model_1_1_2_2-solution000005.solution | 4 + .../model_1_1_2_2-solution000006.solution | 4 + .../model_1_1_2_3-solution000001.solution | 4 + .../model_1_1_2_3-solution000002.solution | 4 + .../model_1_1_2_3-solution000003.solution | 4 + .../model_1_1_2_3-solution000004.solution | 4 + .../model_1_1_2_3-solution000005.solution | 4 + .../model_1_1_2_3-solution000006.solution | 4 + .../model_1_1_3_1-solution000001.solution | 4 + .../model_1_1_3_1-solution000002.solution | 4 + .../model_1_1_3_1-solution000003.solution | 4 + .../model_1_1_3_1-solution000004.solution | 4 + .../model_1_1_3_1-solution000005.solution | 4 + .../model_1_1_3_1-solution000006.solution | 4 + .../model_1_1_3_2-solution000001.solution | 4 + .../model_1_1_3_2-solution000002.solution | 4 + .../model_1_1_3_2-solution000003.solution | 4 + .../model_1_1_3_2-solution000004.solution | 4 + .../model_1_1_3_2-solution000005.solution | 4 + .../model_1_1_3_2-solution000006.solution | 4 + .../model_1_1_3_3-solution000001.solution | 4 + .../model_1_1_3_3-solution000002.solution | 4 + .../model_1_1_3_3-solution000003.solution | 4 + .../model_1_1_3_3-solution000004.solution | 4 + .../model_1_1_3_3-solution000005.solution | 4 + .../model_1_1_3_3-solution000006.solution | 4 + .../model_1_2_1_1-solution000001.solution | 4 + .../model_1_2_1_1-solution000002.solution | 4 + .../model_1_2_1_1-solution000003.solution | 4 + .../model_1_2_1_1-solution000004.solution | 4 + .../model_1_2_1_1-solution000005.solution | 4 + .../model_1_2_1_1-solution000006.solution | 4 + .../model_1_2_1_2-solution000001.solution | 4 + .../model_1_2_1_2-solution000002.solution | 4 + .../model_1_2_1_2-solution000003.solution | 4 + .../model_1_2_1_2-solution000004.solution | 4 + .../model_1_2_1_2-solution000005.solution | 4 + .../model_1_2_1_2-solution000006.solution | 4 + .../model_1_2_1_3-solution000001.solution | 4 + .../model_1_2_1_3-solution000002.solution | 4 + .../model_1_2_1_3-solution000003.solution | 4 + .../model_1_2_1_3-solution000004.solution | 4 + .../model_1_2_1_3-solution000005.solution | 4 + .../model_1_2_1_3-solution000006.solution | 4 + .../model_1_2_2_1-solution000001.solution | 4 + .../model_1_2_2_1-solution000002.solution | 4 + .../model_1_2_2_1-solution000003.solution | 4 + .../model_1_2_2_1-solution000004.solution | 4 + .../model_1_2_2_1-solution000005.solution | 4 + .../model_1_2_2_1-solution000006.solution | 4 + .../model_1_2_2_2-solution000001.solution | 4 + .../model_1_2_2_2-solution000002.solution | 4 + .../model_1_2_2_2-solution000003.solution | 4 + .../model_1_2_2_2-solution000004.solution | 4 + .../model_1_2_2_2-solution000005.solution | 4 + .../model_1_2_2_2-solution000006.solution | 4 + .../model_1_2_2_3-solution000001.solution | 4 + .../model_1_2_2_3-solution000002.solution | 4 + .../model_1_2_2_3-solution000003.solution | 4 + .../model_1_2_2_3-solution000004.solution | 4 + .../model_1_2_2_3-solution000005.solution | 4 + .../model_1_2_2_3-solution000006.solution | 4 + .../model_1_2_3_1-solution000001.solution | 4 + .../model_1_2_3_1-solution000002.solution | 4 + .../model_1_2_3_1-solution000003.solution | 4 + .../model_1_2_3_1-solution000004.solution | 4 + .../model_1_2_3_1-solution000005.solution | 4 + .../model_1_2_3_1-solution000006.solution | 4 + .../model_1_2_3_2-solution000001.solution | 4 + .../model_1_2_3_2-solution000002.solution | 4 + .../model_1_2_3_2-solution000003.solution | 4 + .../model_1_2_3_2-solution000004.solution | 4 + .../model_1_2_3_2-solution000005.solution | 4 + .../model_1_2_3_2-solution000006.solution | 4 + .../model_1_2_3_3-solution000001.solution | 4 + .../model_1_2_3_3-solution000002.solution | 4 + .../model_1_2_3_3-solution000003.solution | 4 + .../model_1_2_3_3-solution000004.solution | 4 + .../model_1_2_3_3-solution000005.solution | 4 + .../model_1_2_3_3-solution000006.solution | 4 + .../model_1_3_1_1-solution000001.solution | 4 + .../model_1_3_1_1-solution000002.solution | 4 + .../model_1_3_1_1-solution000003.solution | 4 + .../model_1_3_1_1-solution000004.solution | 4 + .../model_1_3_1_1-solution000005.solution | 4 + .../model_1_3_1_1-solution000006.solution | 4 + .../model_1_3_1_2-solution000001.solution | 4 + .../model_1_3_1_2-solution000002.solution | 4 + .../model_1_3_1_2-solution000003.solution | 4 + .../model_1_3_1_2-solution000004.solution | 4 + .../model_1_3_1_2-solution000005.solution | 4 + .../model_1_3_1_2-solution000006.solution | 4 + .../model_1_3_1_3-solution000001.solution | 4 + .../model_1_3_1_3-solution000002.solution | 4 + .../model_1_3_1_3-solution000003.solution | 4 + .../model_1_3_1_3-solution000004.solution | 4 + .../model_1_3_1_3-solution000005.solution | 4 + .../model_1_3_1_3-solution000006.solution | 4 + .../model_1_3_2_1-solution000001.solution | 4 + .../model_1_3_2_1-solution000002.solution | 4 + .../model_1_3_2_1-solution000003.solution | 4 + .../model_1_3_2_1-solution000004.solution | 4 + .../model_1_3_2_1-solution000005.solution | 4 + .../model_1_3_2_1-solution000006.solution | 4 + .../model_1_3_2_2-solution000001.solution | 4 + .../model_1_3_2_2-solution000002.solution | 4 + .../model_1_3_2_2-solution000003.solution | 4 + .../model_1_3_2_2-solution000004.solution | 4 + .../model_1_3_2_2-solution000005.solution | 4 + .../model_1_3_2_2-solution000006.solution | 4 + .../model_1_3_2_3-solution000001.solution | 4 + .../model_1_3_2_3-solution000002.solution | 4 + .../model_1_3_2_3-solution000003.solution | 4 + .../model_1_3_2_3-solution000004.solution | 4 + .../model_1_3_2_3-solution000005.solution | 4 + .../model_1_3_2_3-solution000006.solution | 4 + .../model_1_3_3_1-solution000001.solution | 4 + .../model_1_3_3_1-solution000002.solution | 4 + .../model_1_3_3_1-solution000003.solution | 4 + .../model_1_3_3_1-solution000004.solution | 4 + .../model_1_3_3_1-solution000005.solution | 4 + .../model_1_3_3_1-solution000006.solution | 4 + .../model_1_3_3_2-solution000001.solution | 4 + .../model_1_3_3_2-solution000002.solution | 4 + .../model_1_3_3_2-solution000003.solution | 4 + .../model_1_3_3_2-solution000004.solution | 4 + .../model_1_3_3_2-solution000005.solution | 4 + .../model_1_3_3_2-solution000006.solution | 4 + .../model_1_3_3_3-solution000001.solution | 4 + .../model_1_3_3_3-solution000002.solution | 4 + .../model_1_3_3_3-solution000003.solution | 4 + .../model_1_3_3_3-solution000004.solution | 4 + .../model_1_3_3_3-solution000005.solution | 4 + .../model_1_3_3_3-solution000006.solution | 4 + .../model_2_1_1_1-solution000001.solution | 4 + .../model_2_1_1_1-solution000002.solution | 4 + .../model_2_1_1_1-solution000003.solution | 4 + .../model_2_1_1_1-solution000004.solution | 4 + .../model_2_1_1_1-solution000005.solution | 4 + .../model_2_1_1_1-solution000006.solution | 4 + .../model_2_1_1_2-solution000001.solution | 4 + .../model_2_1_1_2-solution000002.solution | 4 + .../model_2_1_1_2-solution000003.solution | 4 + .../model_2_1_1_2-solution000004.solution | 4 + .../model_2_1_1_2-solution000005.solution | 4 + .../model_2_1_1_2-solution000006.solution | 4 + .../model_2_1_1_3-solution000001.solution | 4 + .../model_2_1_1_3-solution000002.solution | 4 + .../model_2_1_1_3-solution000003.solution | 4 + .../model_2_1_1_3-solution000004.solution | 4 + .../model_2_1_1_3-solution000005.solution | 4 + .../model_2_1_1_3-solution000006.solution | 4 + .../model_2_1_2_1-solution000001.solution | 4 + .../model_2_1_2_1-solution000002.solution | 4 + .../model_2_1_2_1-solution000003.solution | 4 + .../model_2_1_2_1-solution000004.solution | 4 + .../model_2_1_2_1-solution000005.solution | 4 + .../model_2_1_2_1-solution000006.solution | 4 + .../model_2_1_2_2-solution000001.solution | 4 + .../model_2_1_2_2-solution000002.solution | 4 + .../model_2_1_2_2-solution000003.solution | 4 + .../model_2_1_2_2-solution000004.solution | 4 + .../model_2_1_2_2-solution000005.solution | 4 + .../model_2_1_2_2-solution000006.solution | 4 + .../model_2_1_2_3-solution000001.solution | 4 + .../model_2_1_2_3-solution000002.solution | 4 + .../model_2_1_2_3-solution000003.solution | 4 + .../model_2_1_2_3-solution000004.solution | 4 + .../model_2_1_2_3-solution000005.solution | 4 + .../model_2_1_2_3-solution000006.solution | 4 + .../model_2_1_3_1-solution000001.solution | 4 + .../model_2_1_3_1-solution000002.solution | 4 + .../model_2_1_3_1-solution000003.solution | 4 + .../model_2_1_3_1-solution000004.solution | 4 + .../model_2_1_3_1-solution000005.solution | 4 + .../model_2_1_3_1-solution000006.solution | 4 + .../model_2_1_3_2-solution000001.solution | 4 + .../model_2_1_3_2-solution000002.solution | 4 + .../model_2_1_3_2-solution000003.solution | 4 + .../model_2_1_3_2-solution000004.solution | 4 + .../model_2_1_3_2-solution000005.solution | 4 + .../model_2_1_3_2-solution000006.solution | 4 + .../model_2_1_3_3-solution000001.solution | 4 + .../model_2_1_3_3-solution000002.solution | 4 + .../model_2_1_3_3-solution000003.solution | 4 + .../model_2_1_3_3-solution000004.solution | 4 + .../model_2_1_3_3-solution000005.solution | 4 + .../model_2_1_3_3-solution000006.solution | 4 + .../model_2_2_1_1-solution000001.solution | 4 + .../model_2_2_1_1-solution000002.solution | 4 + .../model_2_2_1_1-solution000003.solution | 4 + .../model_2_2_1_1-solution000004.solution | 4 + .../model_2_2_1_1-solution000005.solution | 4 + .../model_2_2_1_1-solution000006.solution | 4 + .../model_2_2_1_2-solution000001.solution | 4 + .../model_2_2_1_2-solution000002.solution | 4 + .../model_2_2_1_2-solution000003.solution | 4 + .../model_2_2_1_2-solution000004.solution | 4 + .../model_2_2_1_2-solution000005.solution | 4 + .../model_2_2_1_2-solution000006.solution | 4 + .../model_2_2_1_3-solution000001.solution | 4 + .../model_2_2_1_3-solution000002.solution | 4 + .../model_2_2_1_3-solution000003.solution | 4 + .../model_2_2_1_3-solution000004.solution | 4 + .../model_2_2_1_3-solution000005.solution | 4 + .../model_2_2_1_3-solution000006.solution | 4 + .../model_2_2_2_1-solution000001.solution | 4 + .../model_2_2_2_1-solution000002.solution | 4 + .../model_2_2_2_1-solution000003.solution | 4 + .../model_2_2_2_1-solution000004.solution | 4 + .../model_2_2_2_1-solution000005.solution | 4 + .../model_2_2_2_1-solution000006.solution | 4 + .../model_2_2_2_2-solution000001.solution | 4 + .../model_2_2_2_2-solution000002.solution | 4 + .../model_2_2_2_2-solution000003.solution | 4 + .../model_2_2_2_2-solution000004.solution | 4 + .../model_2_2_2_2-solution000005.solution | 4 + .../model_2_2_2_2-solution000006.solution | 4 + .../expected/model_2_2_2_2.eprime | 66 + .../model_2_2_2_3-solution000001.solution | 4 + .../model_2_2_2_3-solution000002.solution | 4 + .../model_2_2_2_3-solution000003.solution | 4 + .../model_2_2_2_3-solution000004.solution | 4 + .../model_2_2_2_3-solution000005.solution | 4 + .../model_2_2_2_3-solution000006.solution | 4 + .../expected/model_2_2_2_3.eprime | 75 + .../model_2_2_3_1-solution000001.solution | 4 + .../model_2_2_3_1-solution000002.solution | 4 + .../model_2_2_3_1-solution000003.solution | 4 + .../model_2_2_3_1-solution000004.solution | 4 + .../model_2_2_3_1-solution000005.solution | 4 + .../model_2_2_3_1-solution000006.solution | 4 + .../model_2_2_3_2-solution000001.solution | 4 + .../model_2_2_3_2-solution000002.solution | 4 + .../model_2_2_3_2-solution000003.solution | 4 + .../model_2_2_3_2-solution000004.solution | 4 + .../model_2_2_3_2-solution000005.solution | 4 + .../model_2_2_3_2-solution000006.solution | 4 + .../expected/model_2_2_3_2.eprime | 75 + .../model_2_2_3_3-solution000001.solution | 4 + .../model_2_2_3_3-solution000002.solution | 4 + .../model_2_2_3_3-solution000003.solution | 4 + .../model_2_2_3_3-solution000004.solution | 4 + .../model_2_2_3_3-solution000005.solution | 4 + .../model_2_2_3_3-solution000006.solution | 4 + .../expected/model_2_2_3_3.eprime | 84 ++ .../model_2_3_1_1-solution000001.solution | 4 + .../model_2_3_1_1-solution000002.solution | 4 + .../model_2_3_1_1-solution000003.solution | 4 + .../model_2_3_1_1-solution000004.solution | 4 + .../model_2_3_1_1-solution000005.solution | 4 + .../model_2_3_1_1-solution000006.solution | 4 + .../model_2_3_1_2-solution000001.solution | 4 + .../model_2_3_1_2-solution000002.solution | 4 + .../model_2_3_1_2-solution000003.solution | 4 + .../model_2_3_1_2-solution000004.solution | 4 + .../model_2_3_1_2-solution000005.solution | 4 + .../model_2_3_1_2-solution000006.solution | 4 + .../model_2_3_1_3-solution000001.solution | 4 + .../model_2_3_1_3-solution000002.solution | 4 + .../model_2_3_1_3-solution000003.solution | 4 + .../model_2_3_1_3-solution000004.solution | 4 + .../model_2_3_1_3-solution000005.solution | 4 + .../model_2_3_1_3-solution000006.solution | 4 + .../model_2_3_2_1-solution000001.solution | 4 + .../model_2_3_2_1-solution000002.solution | 4 + .../model_2_3_2_1-solution000003.solution | 4 + .../model_2_3_2_1-solution000004.solution | 4 + .../model_2_3_2_1-solution000005.solution | 4 + .../model_2_3_2_1-solution000006.solution | 4 + .../model_2_3_2_2-solution000001.solution | 4 + .../model_2_3_2_2-solution000002.solution | 4 + .../model_2_3_2_2-solution000003.solution | 4 + .../model_2_3_2_2-solution000004.solution | 4 + .../model_2_3_2_2-solution000005.solution | 4 + .../model_2_3_2_2-solution000006.solution | 4 + .../expected/model_2_3_2_2.eprime | 53 + .../model_2_3_2_3-solution000001.solution | 4 + .../model_2_3_2_3-solution000002.solution | 4 + .../model_2_3_2_3-solution000003.solution | 4 + .../model_2_3_2_3-solution000004.solution | 4 + .../model_2_3_2_3-solution000005.solution | 4 + .../model_2_3_2_3-solution000006.solution | 4 + .../expected/model_2_3_2_3.eprime | 41 + .../model_2_3_3_1-solution000001.solution | 4 + .../model_2_3_3_1-solution000002.solution | 4 + .../model_2_3_3_1-solution000003.solution | 4 + .../model_2_3_3_1-solution000004.solution | 4 + .../model_2_3_3_1-solution000005.solution | 4 + .../model_2_3_3_1-solution000006.solution | 4 + .../model_2_3_3_2-solution000001.solution | 4 + .../model_2_3_3_2-solution000002.solution | 4 + .../model_2_3_3_2-solution000003.solution | 4 + .../model_2_3_3_2-solution000004.solution | 4 + .../model_2_3_3_2-solution000005.solution | 4 + .../model_2_3_3_2-solution000006.solution | 4 + .../expected/model_2_3_3_2.eprime | 62 + .../model_2_3_3_3-solution000001.solution | 4 + .../model_2_3_3_3-solution000002.solution | 4 + .../model_2_3_3_3-solution000003.solution | 4 + .../model_2_3_3_3-solution000004.solution | 4 + .../model_2_3_3_3-solution000005.solution | 4 + .../model_2_3_3_3-solution000006.solution | 4 + .../expected/model_2_3_3_3.eprime | 50 + .../model_3_1_1_1-solution000001.solution | 4 + .../model_3_1_1_1-solution000002.solution | 4 + .../model_3_1_1_1-solution000003.solution | 4 + .../model_3_1_1_1-solution000004.solution | 4 + .../model_3_1_1_1-solution000005.solution | 4 + .../model_3_1_1_1-solution000006.solution | 4 + .../model_3_1_1_2-solution000001.solution | 4 + .../model_3_1_1_2-solution000002.solution | 4 + .../model_3_1_1_2-solution000003.solution | 4 + .../model_3_1_1_2-solution000004.solution | 4 + .../model_3_1_1_2-solution000005.solution | 4 + .../model_3_1_1_2-solution000006.solution | 4 + .../model_3_1_1_3-solution000001.solution | 4 + .../model_3_1_1_3-solution000002.solution | 4 + .../model_3_1_1_3-solution000003.solution | 4 + .../model_3_1_1_3-solution000004.solution | 4 + .../model_3_1_1_3-solution000005.solution | 4 + .../model_3_1_1_3-solution000006.solution | 4 + .../model_3_1_2_1-solution000001.solution | 4 + .../model_3_1_2_1-solution000002.solution | 4 + .../model_3_1_2_1-solution000003.solution | 4 + .../model_3_1_2_1-solution000004.solution | 4 + .../model_3_1_2_1-solution000005.solution | 4 + .../model_3_1_2_1-solution000006.solution | 4 + .../model_3_1_2_2-solution000001.solution | 4 + .../model_3_1_2_2-solution000002.solution | 4 + .../model_3_1_2_2-solution000003.solution | 4 + .../model_3_1_2_2-solution000004.solution | 4 + .../model_3_1_2_2-solution000005.solution | 4 + .../model_3_1_2_2-solution000006.solution | 4 + .../model_3_1_2_3-solution000001.solution | 4 + .../model_3_1_2_3-solution000002.solution | 4 + .../model_3_1_2_3-solution000003.solution | 4 + .../model_3_1_2_3-solution000004.solution | 4 + .../model_3_1_2_3-solution000005.solution | 4 + .../model_3_1_2_3-solution000006.solution | 4 + .../model_3_1_3_1-solution000001.solution | 4 + .../model_3_1_3_1-solution000002.solution | 4 + .../model_3_1_3_1-solution000003.solution | 4 + .../model_3_1_3_1-solution000004.solution | 4 + .../model_3_1_3_1-solution000005.solution | 4 + .../model_3_1_3_1-solution000006.solution | 4 + .../model_3_1_3_2-solution000001.solution | 4 + .../model_3_1_3_2-solution000002.solution | 4 + .../model_3_1_3_2-solution000003.solution | 4 + .../model_3_1_3_2-solution000004.solution | 4 + .../model_3_1_3_2-solution000005.solution | 4 + .../model_3_1_3_2-solution000006.solution | 4 + .../model_3_1_3_3-solution000001.solution | 4 + .../model_3_1_3_3-solution000002.solution | 4 + .../model_3_1_3_3-solution000003.solution | 4 + .../model_3_1_3_3-solution000004.solution | 4 + .../model_3_1_3_3-solution000005.solution | 4 + .../model_3_1_3_3-solution000006.solution | 4 + .../model_3_2_1_1-solution000001.solution | 4 + .../model_3_2_1_1-solution000002.solution | 4 + .../model_3_2_1_1-solution000003.solution | 4 + .../model_3_2_1_1-solution000004.solution | 4 + .../model_3_2_1_1-solution000005.solution | 4 + .../model_3_2_1_1-solution000006.solution | 4 + .../model_3_2_1_2-solution000001.solution | 4 + .../model_3_2_1_2-solution000002.solution | 4 + .../model_3_2_1_2-solution000003.solution | 4 + .../model_3_2_1_2-solution000004.solution | 4 + .../model_3_2_1_2-solution000005.solution | 4 + .../model_3_2_1_2-solution000006.solution | 4 + .../model_3_2_1_3-solution000001.solution | 4 + .../model_3_2_1_3-solution000002.solution | 4 + .../model_3_2_1_3-solution000003.solution | 4 + .../model_3_2_1_3-solution000004.solution | 4 + .../model_3_2_1_3-solution000005.solution | 4 + .../model_3_2_1_3-solution000006.solution | 4 + .../model_3_2_2_1-solution000001.solution | 4 + .../model_3_2_2_1-solution000002.solution | 4 + .../model_3_2_2_1-solution000003.solution | 4 + .../model_3_2_2_1-solution000004.solution | 4 + .../model_3_2_2_1-solution000005.solution | 4 + .../model_3_2_2_1-solution000006.solution | 4 + .../model_3_2_2_2-solution000001.solution | 4 + .../model_3_2_2_2-solution000002.solution | 4 + .../model_3_2_2_2-solution000003.solution | 4 + .../model_3_2_2_2-solution000004.solution | 4 + .../model_3_2_2_2-solution000005.solution | 4 + .../model_3_2_2_2-solution000006.solution | 4 + .../expected/model_3_2_2_2.eprime | 56 + .../model_3_2_2_3-solution000001.solution | 4 + .../model_3_2_2_3-solution000002.solution | 4 + .../model_3_2_2_3-solution000003.solution | 4 + .../model_3_2_2_3-solution000004.solution | 4 + .../model_3_2_2_3-solution000005.solution | 4 + .../model_3_2_2_3-solution000006.solution | 4 + .../expected/model_3_2_2_3.eprime | 65 + .../model_3_2_3_1-solution000001.solution | 4 + .../model_3_2_3_1-solution000002.solution | 4 + .../model_3_2_3_1-solution000003.solution | 4 + .../model_3_2_3_1-solution000004.solution | 4 + .../model_3_2_3_1-solution000005.solution | 4 + .../model_3_2_3_1-solution000006.solution | 4 + .../model_3_2_3_2-solution000001.solution | 4 + .../model_3_2_3_2-solution000002.solution | 4 + .../model_3_2_3_2-solution000003.solution | 4 + .../model_3_2_3_2-solution000004.solution | 4 + .../model_3_2_3_2-solution000005.solution | 4 + .../model_3_2_3_2-solution000006.solution | 4 + .../expected/model_3_2_3_2.eprime | 44 + .../model_3_2_3_3-solution000001.solution | 4 + .../model_3_2_3_3-solution000002.solution | 4 + .../model_3_2_3_3-solution000003.solution | 4 + .../model_3_2_3_3-solution000004.solution | 4 + .../model_3_2_3_3-solution000005.solution | 4 + .../model_3_2_3_3-solution000006.solution | 4 + .../expected/model_3_2_3_3.eprime | 53 + .../model_3_3_1_1-solution000001.solution | 4 + .../model_3_3_1_1-solution000002.solution | 4 + .../model_3_3_1_1-solution000003.solution | 4 + .../model_3_3_1_1-solution000004.solution | 4 + .../model_3_3_1_1-solution000005.solution | 4 + .../model_3_3_1_1-solution000006.solution | 4 + .../model_3_3_1_2-solution000001.solution | 4 + .../model_3_3_1_2-solution000002.solution | 4 + .../model_3_3_1_2-solution000003.solution | 4 + .../model_3_3_1_2-solution000004.solution | 4 + .../model_3_3_1_2-solution000005.solution | 4 + .../model_3_3_1_2-solution000006.solution | 4 + .../model_3_3_1_3-solution000001.solution | 4 + .../model_3_3_1_3-solution000002.solution | 4 + .../model_3_3_1_3-solution000003.solution | 4 + .../model_3_3_1_3-solution000004.solution | 4 + .../model_3_3_1_3-solution000005.solution | 4 + .../model_3_3_1_3-solution000006.solution | 4 + .../model_3_3_2_1-solution000001.solution | 4 + .../model_3_3_2_1-solution000002.solution | 4 + .../model_3_3_2_1-solution000003.solution | 4 + .../model_3_3_2_1-solution000004.solution | 4 + .../model_3_3_2_1-solution000005.solution | 4 + .../model_3_3_2_1-solution000006.solution | 4 + .../model_3_3_2_2-solution000001.solution | 4 + .../model_3_3_2_2-solution000002.solution | 4 + .../model_3_3_2_2-solution000003.solution | 4 + .../model_3_3_2_2-solution000004.solution | 4 + .../model_3_3_2_2-solution000005.solution | 4 + .../model_3_3_2_2-solution000006.solution | 4 + .../expected/model_3_3_2_2.eprime | 47 + .../model_3_3_2_3-solution000001.solution | 4 + .../model_3_3_2_3-solution000002.solution | 4 + .../model_3_3_2_3-solution000003.solution | 4 + .../model_3_3_2_3-solution000004.solution | 4 + .../model_3_3_2_3-solution000005.solution | 4 + .../model_3_3_2_3-solution000006.solution | 4 + .../expected/model_3_3_2_3.eprime | 34 + .../model_3_3_3_1-solution000001.solution | 4 + .../model_3_3_3_1-solution000002.solution | 4 + .../model_3_3_3_1-solution000003.solution | 4 + .../model_3_3_3_1-solution000004.solution | 4 + .../model_3_3_3_1-solution000005.solution | 4 + .../model_3_3_3_1-solution000006.solution | 4 + .../model_3_3_3_2-solution000001.solution | 4 + .../model_3_3_3_2-solution000002.solution | 4 + .../model_3_3_3_2-solution000003.solution | 4 + .../model_3_3_3_2-solution000004.solution | 4 + .../model_3_3_3_2-solution000005.solution | 4 + .../model_3_3_3_2-solution000006.solution | 4 + .../expected/model_3_3_3_2.eprime | 34 + .../model_3_3_3_3-solution000001.solution | 4 + .../model_3_3_3_3-solution000002.solution | 4 + .../model_3_3_3_3-solution000003.solution | 4 + .../model_3_3_3_3-solution000004.solution | 4 + .../model_3_3_3_3-solution000005.solution | 4 + .../model_3_3_3_3-solution000006.solution | 4 + .../expected/model_3_3_3_3.eprime | 24 + .../model_1_1-solution000001.solution | 11 + .../expected/model_1_1.eprime | 324 +++++ .../model_1_2-solution000001.solution | 11 + .../expected/model_1_2.eprime | 787 +++++++++++ .../model_1_3-solution000001.solution | 11 + .../expected/model_1_3.eprime.orig | 856 ------------ .../model_1_4-solution000001.solution | 11 + .../expected/model_1_4.eprime | 382 +++++ .../model_2_1-solution000001.solution | 11 + .../expected/model_2_1.eprime | 761 ++++++++++ .../model_2_2-solution000001.solution | 11 + .../expected/model_2_2.eprime | 949 +++++++++++++ .../model_2_3-solution000001.solution | 11 + .../expected/model_2_3.eprime.orig | 1208 ---------------- .../model_2_4-solution000001.solution | 11 + .../expected/model_2_4.eprime | 809 +++++++++++ .../model_3_1-solution000001.solution | 11 + .../expected/model_3_1.eprime.orig | 852 ------------ .../model_3_2-solution000001.solution | 11 + .../expected/model_3_2.eprime.orig | 1228 ----------------- .../model_3_3-solution000001.solution | 11 + .../expected/model_3_3.eprime.orig | 1127 --------------- .../model_3_4-solution000001.solution | 11 + .../expected/model_3_4.eprime.orig | 906 ------------ .../model_4_1-solution000001.solution | 11 + .../expected/model_4_1.eprime | 373 +++++ .../model_4_2-solution000001.solution | 11 + .../expected/model_4_2.eprime | 827 +++++++++++ .../model_4_3-solution000001.solution | 11 + .../expected/model_4_3.eprime.orig | 901 ------------ .../model_4_4-solution000001.solution | 11 + .../expected/model_4_4.eprime | 394 ++++++ .../expected/model-solution000001.solution | 7 + .../expected/model-solution000002.solution | 7 + .../expected/model-solution000003.solution | 8 + .../expected/model-solution000004.solution | 7 + .../expected/model-solution000005.solution | 8 + .../expected/model-solution000006.solution | 8 + .../expected/model-solution000007.solution | 9 + .../expected/model-solution000008.solution | 7 + .../expected/model-solution000009.solution | 8 + .../expected/model-solution000010.solution | 8 + .../expected/model-solution000011.solution | 9 + .../expected/model-solution000012.solution | 8 + .../expected/model-solution000013.solution | 9 + .../expected/model-solution000014.solution | 9 + .../expected/model-solution000015.solution | 10 + .../expected/model-solution000016.solution | 10 + .../expected/model-solution000017.solution | 11 + .../expected/model-solution000018.solution | 10 + .../expected/model-solution000019.solution | 11 + .../expected/model-solution000020.solution | 11 + .../expected/model-solution000021.solution | 12 + .../expected/model-solution000022.solution | 10 + .../expected/model-solution000023.solution | 11 + .../expected/model-solution000024.solution | 11 + .../expected/model-solution000025.solution | 12 + .../expected/model-solution000026.solution | 11 + .../expected/model-solution000027.solution | 12 + .../expected/model-solution000028.solution | 12 + .../expected/model-solution000029.solution | 13 + .../expected/model-solution000030.solution | 11 + .../expected/model-solution000031.solution | 10 + .../expected/model-solution000032.solution | 11 + .../expected/model-solution000033.solution | 11 + .../expected/model-solution000034.solution | 12 + .../expected/model-solution000035.solution | 10 + .../expected/model-solution000036.solution | 11 + .../expected/model-solution000037.solution | 11 + .../expected/model-solution000038.solution | 12 + .../expected/model-solution000039.solution | 11 + .../expected/model-solution000040.solution | 12 + .../expected/model-solution000041.solution | 12 + .../expected/model-solution000042.solution | 13 + .../expected/model-solution000043.solution | 11 + .../expected/model-solution000044.solution | 12 + .../expected/model-solution000045.solution | 12 + .../expected/model-solution000046.solution | 13 + .../expected/model-solution000047.solution | 11 + .../expected/model-solution000048.solution | 12 + .../expected/model-solution000049.solution | 12 + .../expected/model-solution000050.solution | 13 + .../expected/model-solution000051.solution | 12 + .../expected/model-solution000052.solution | 13 + .../expected/model-solution000053.solution | 13 + .../expected/model-solution000054.solution | 14 + .../expected/model-solution000055.solution | 11 + .../expected/model-solution000056.solution | 11 + .../expected/model-solution000057.solution | 12 + .../expected/model-solution000058.solution | 10 + .../expected/model-solution000059.solution | 11 + .../expected/model-solution000060.solution | 11 + .../expected/model-solution000061.solution | 12 + .../expected/model-solution000062.solution | 11 + .../expected/model-solution000063.solution | 12 + .../expected/model-solution000064.solution | 12 + .../expected/model-solution000065.solution | 13 + .../expected/model-solution000066.solution | 12 + .../expected/model-solution000067.solution | 13 + .../expected/model-solution000068.solution | 11 + .../expected/model-solution000069.solution | 12 + .../expected/model-solution000070.solution | 12 + .../expected/model-solution000071.solution | 13 + .../expected/model-solution000072.solution | 12 + .../expected/model-solution000073.solution | 13 + .../expected/model-solution000074.solution | 13 + .../expected/model-solution000075.solution | 14 + .../expected/model-solution000076.solution | 13 + .../expected/model-solution000077.solution | 11 + .../expected/model-solution000078.solution | 12 + .../expected/model-solution000079.solution | 12 + .../expected/model-solution000080.solution | 13 + .../expected/model-solution000081.solution | 12 + .../expected/model-solution000082.solution | 13 + .../expected/model-solution000083.solution | 13 + .../expected/model-solution000084.solution | 14 + .../expected/model-solution000085.solution | 12 + .../expected/model-solution000086.solution | 13 + .../expected/model-solution000087.solution | 13 + .../expected/model-solution000088.solution | 14 + .../expected/model-solution000089.solution | 13 + .../expected/model-solution000090.solution | 14 + .../expected/model-solution000091.solution | 14 + .../expected/model-solution000092.solution | 15 + .../expected/model-solution000093.solution | 11 + .../expected/model-solution000094.solution | 11 + .../expected/model-solution000095.solution | 12 + .../expected/model-solution000096.solution | 11 + .../expected/model-solution000097.solution | 12 + .../expected/model-solution000098.solution | 12 + .../expected/model-solution000099.solution | 13 + .../expected/model-solution000100.solution | 12 + .../expected/model-solution000101.solution | 13 + .../expected/model-solution000102.solution | 12 + .../expected/model-solution000103.solution | 13 + .../expected/model-solution000104.solution | 13 + .../expected/model-solution000105.solution | 14 + .../expected/model-solution000106.solution | 13 + .../expected/model-solution000107.solution | 12 + .../expected/model-solution000108.solution | 13 + .../expected/model-solution000109.solution | 13 + .../expected/model-solution000110.solution | 14 + .../expected/model-solution000111.solution | 13 + .../expected/model-solution000112.solution | 14 + .../expected/model-solution000113.solution | 14 + .../expected/model-solution000114.solution | 15 + .../expected/model-solution000115.solution | 13 + .../expected/model-solution000116.solution | 13 + .../expected/model-solution000117.solution | 14 + .../expected/model-solution000118.solution | 14 + .../expected/model-solution000119.solution | 15 + .../expected/model-solution000120.solution | 15 + .../expected/model.eprime | 62 + .../model.expected.json | 8 +- .../stdout.expected | 8 +- .../model.expected.json | 2 +- .../stdout.expected | 2 +- .../model.expected.json | 6 +- .../stdout.expected | 6 +- .../model.expected.json | 6 +- .../stdout.expected | 6 +- .../model.expected.json | 2 +- .../stdout.expected | 2 +- .../model.expected.json | 8 +- .../stdout.expected | 8 +- .../model.expected.json | 2 +- .../stdout.expected | 2 +- .../model.expected.json | 8 +- .../stdout.expected | 8 +- .../model.expected.json | 2 +- .../stdout.expected | 2 +- .../model.expected.json | 2 +- .../stdout.expected | 2 +- .../model.expected.json | 6 +- .../stdout.expected | 6 +- .../model.expected.json | 10 +- .../stdout.expected | 10 +- .../model.expected.json | 10 +- .../stdout.expected | 10 +- .../model.expected.json | 2 +- .../stdout.expected | 2 +- .../model.expected.json | 4 +- .../stdout.expected | 4 +- .../model.expected.json | 2 +- .../stdout.expected | 2 +- .../model.expected.json | 8 +- .../stdout.expected | 8 +- .../model.expected.json | 6 +- .../stdout.expected | 6 +- .../model.expected.json | 6 +- .../stdout.expected | 6 +- .../model.expected.json | 8 +- .../stdout.expected | 9 +- .../model.expected.json | 2 +- .../stdout.expected | 2 +- .../model.expected.json | 8 +- .../stdout.expected | 8 +- .../model.expected.json | 6 +- .../stdout.expected | 6 +- .../model.expected.json | 10 +- .../stdout.expected | 10 +- .../model.expected.json | 4 +- .../stdout.expected | 4 +- .../model.expected.json | 2 +- .../stdout.expected | 2 +- .../model.expected.json | 4 +- .../stdout.expected | 4 +- .../model.expected.json | 4 +- .../stdout.expected | 4 +- .../model.expected.json | 4 +- .../stdout.expected | 4 +- .../model.expected.json | 2 +- .../stdout.expected | 2 +- .../model.expected.json | 4 +- .../stdout.expected | 4 +- .../model.expected.json | 2 +- .../stdout.expected | 2 +- .../model.expected.json | 2 +- .../stdout.expected | 2 +- .../model.expected.json | 2 +- .../stdout.expected | 2 +- .../model.expected.json | 6 +- .../stdout.expected | 6 +- .../model.expected.json | 6 +- .../stdout.expected | 6 +- .../model.expected.json | 4 +- .../stdout.expected | 4 +- .../model.expected.json | 8 +- .../stdout.expected | 8 +- .../model.expected.json | 2 +- .../stdout.expected | 2 +- .../model.expected.json | 2 +- .../stdout.expected | 2 +- .../model.expected.json | 8 +- .../stdout.expected | 8 +- .../model.expected.json | 4 +- .../stdout.expected | 4 +- .../model.expected.json | 2 +- .../stdout.expected | 2 +- .../model.expected.json | 4 +- .../stdout.expected | 4 +- .../model.expected.json | 2 +- .../stdout.expected | 2 +- .../model.expected.json | 2 +- .../stdout.expected | 2 +- .../model.expected.json | 2 +- .../stdout.expected | 2 +- .../model.expected.json | 6 +- .../stdout.expected | 7 +- .../model.expected.json | 4 +- .../stdout.expected | 4 +- .../model.expected.json | 4 +- .../stdout.expected | 4 +- .../model.expected.json | 8 +- .../stdout.expected | 8 +- .../model.expected.json | 8 +- .../stdout.expected | 8 +- .../model.expected.json | 6 +- .../stdout.expected | 6 +- .../model.expected.json | 2 +- .../stdout.expected | 2 +- .../model.expected.json | 2 +- .../stdout.expected | 2 +- .../model.expected.json | 2 +- .../stdout.expected | 2 +- .../model.expected.json | 4 +- .../stdout.expected | 4 +- .../model.expected.json | 6 +- .../stdout.expected | 6 +- .../model.expected.json | 4 +- .../stdout.expected | 4 +- .../model.expected.json | 4 +- .../stdout.expected | 4 +- .../model.expected.json | 6 +- .../stdout.expected | 6 +- .../model.expected.json | 8 +- .../stdout.expected | 8 +- .../model.expected.json | 8 +- .../stdout.expected | 8 +- .../model.expected.json | 4 +- .../stdout.expected | 4 +- .../model.expected.json | 8 +- .../stdout.expected | 8 +- .../model.expected.json | 10 +- .../stdout.expected | 10 +- .../model.expected.json | 6 +- .../stdout.expected | 6 +- .../model.expected.json | 2 +- .../stdout.expected | 2 +- .../model.expected.json | 6 +- .../stdout.expected | 6 +- .../model.expected.json | 6 +- .../stdout.expected | 6 +- .../model.expected.json | 4 +- .../stdout.expected | 4 +- .../model.expected.json | 2 +- .../stdout.expected | 2 +- .../model.expected.json | 8 +- .../stdout.expected | 8 +- .../model.expected.json | 4 +- .../stdout.expected | 4 +- .../model.expected.json | 2 +- .../stdout.expected | 2 +- .../model.expected.json | 4 +- .../stdout.expected | 4 +- .../model.expected.json | 10 +- .../stdout.expected | 10 +- .../model.expected.json | 8 +- .../stdout.expected | 8 +- .../model.expected.json | 8 +- .../stdout.expected | 8 +- .../model.expected.json | 14 +- .../stdout.expected | 14 +- .../model.expected.json | 6 +- .../stdout.expected | 6 +- .../model.expected.json | 4 +- .../stdout.expected | 4 +- .../model.expected.json | 2 +- .../stdout.expected | 2 +- .../model.expected.json | 4 +- .../stdout.expected | 4 +- .../model.expected.json | 4 +- .../stdout.expected | 4 +- .../model.expected.json | 4 +- .../stdout.expected | 4 +- .../model.expected.json | 4 +- .../stdout.expected | 4 +- .../model.expected.json | 6 +- .../stdout.expected | 6 +- .../model.expected.json | 8 +- .../stdout.expected | 8 +- .../model.expected.json | 4 +- .../stdout.expected | 4 +- .../model.expected.json | 6 +- .../stdout.expected | 6 +- .../model.expected.json | 6 +- .../stdout.expected | 6 +- .../model.expected.json | 2 +- .../stdout.expected | 2 +- .../model.expected.json | 4 +- .../stdout.expected | 4 +- .../model.expected.json | 4 +- .../stdout.expected | 4 +- .../model.expected.json | 2 +- .../stdout.expected | 2 +- .../model.expected.json | 4 +- .../stdout.expected | 4 +- .../model.expected.json | 4 +- .../stdout.expected | 4 +- .../model.expected.json | 6 +- .../stdout.expected | 6 +- .../model.expected.json | 8 +- .../stdout.expected | 8 +- .../model.expected.json | 4 +- .../stdout.expected | 4 +- .../model.expected.json | 2 +- .../stdout.expected | 2 +- .../model.expected.json | 8 +- .../stdout.expected | 8 +- .../model.expected.json | 4 +- .../stdout.expected | 4 +- .../model.expected.json | 4 +- .../stdout.expected | 4 +- .../model.expected.json | 6 +- .../stdout.expected | 6 +- .../model.expected.json | 2 +- .../stdout.expected | 2 +- .../model.expected.json | 4 +- .../stdout.expected | 4 +- .../model.expected.json | 6 +- .../stdout.expected | 6 +- .../model.expected.json | 2 +- .../stdout.expected | 2 +- .../model.expected.json | 2 +- .../stdout.expected | 2 +- .../model.expected.json | 4 +- .../stdout.expected | 4 +- .../model.expected.json | 10 +- .../stdout.expected | 10 +- .../model.expected.json | 6 +- .../stdout.expected | 6 +- .../model.expected.json | 6 +- .../stdout.expected | 6 +- .../model.expected.json | 2 +- .../stdout.expected | 2 +- .../model.expected.json | 8 +- .../stdout.expected | 8 +- .../model.expected.json | 6 +- .../stdout.expected | 6 +- .../model.expected.json | 4 +- .../stdout.expected | 5 +- .../model.expected.json | 8 +- .../stdout.expected | 8 +- .../model.expected.json | 8 +- .../stdout.expected | 8 +- .../model.expected.json | 8 +- .../stdout.expected | 8 +- .../model.expected.json | 8 +- .../stdout.expected | 8 +- .../model.expected.json | 6 +- .../stdout.expected | 6 +- .../model.expected.json | 6 +- .../stdout.expected | 6 +- .../model.expected.json | 2 +- .../stdout.expected | 2 +- .../model.expected.json | 4 +- .../stdout.expected | 4 +- .../model.expected.json | 6 +- .../stdout.expected | 6 +- .../model.expected.json | 8 +- .../stdout.expected | 8 +- .../model.expected.json | 2 +- .../stdout.expected | 2 +- .../model.expected.json | 6 +- .../stdout.expected | 6 +- .../model.expected.json | 6 +- .../stdout.expected | 6 +- .../model.expected.json | 8 +- .../stdout.expected | 8 +- .../model.expected.json | 8 +- .../stdout.expected | 8 +- .../model.expected.json | 6 +- .../stdout.expected | 6 +- .../model.expected.json | 6 +- .../stdout.expected | 6 +- .../model.expected.json | 10 +- .../stdout.expected | 11 +- .../model.expected.json | 4 +- .../stdout.expected | 4 +- .../model.expected.json | 8 +- .../stdout.expected | 8 +- .../model.expected.json | 4 +- .../stdout.expected | 4 +- .../model.expected.json | 2 +- .../stdout.expected | 2 +- .../model.expected.json | 4 +- .../stdout.expected | 4 +- .../model.expected.json | 2 +- .../stdout.expected | 2 +- .../model.expected.json | 4 +- .../stdout.expected | 4 +- .../model.expected.json | 4 +- .../stdout.expected | 4 +- .../model.expected.json | 2 +- .../stdout.expected | 2 +- .../model.expected.json | 8 +- .../stdout.expected | 8 +- .../model.expected.json | 8 +- .../stdout.expected | 8 +- .../model.expected.json | 2 +- .../stdout.expected | 2 +- .../model.expected.json | 6 +- .../stdout.expected | 6 +- .../model.expected.json | 2 +- .../stdout.expected | 2 +- .../model.expected.json | 2 +- .../stdout.expected | 2 +- .../model.expected.json | 6 +- .../stdout.expected | 6 +- .../model.expected.json | 10 +- .../stdout.expected | 10 +- .../model.expected.json | 8 +- .../stdout.expected | 8 +- .../model.expected.json | 2 +- .../stdout.expected | 2 +- .../model.expected.json | 6 +- .../stdout.expected | 6 +- .../model.expected.json | 6 +- .../stdout.expected | 6 +- .../model.expected.json | 4 +- .../stdout.expected | 4 +- .../model.expected.json | 6 +- .../stdout.expected | 6 +- .../model.expected.json | 2 +- .../stdout.expected | 3 +- .../model.expected.json | 2 +- .../stdout.expected | 2 +- .../model.expected.json | 2 +- .../stdout.expected | 2 +- .../model.expected.json | 6 +- .../stdout.expected | 6 +- .../model.expected.json | 4 +- .../stdout.expected | 4 +- .../model.expected.json | 4 +- .../stdout.expected | 4 +- .../model.expected.json | 2 +- .../stdout.expected | 2 +- .../model.expected.json | 8 +- .../stdout.expected | 8 +- .../model.expected.json | 4 +- .../stdout.expected | 4 +- .../model.expected.json | 10 +- .../stdout.expected | 10 +- .../model.expected.json | 4 +- .../stdout.expected | 4 +- .../model.expected.json | 4 +- .../stdout.expected | 4 +- .../model.expected.json | 4 +- .../stdout.expected | 4 +- .../model.expected.json | 4 +- .../stdout.expected | 4 +- .../model.expected.json | 4 +- .../stdout.expected | 4 +- .../model.expected.json | 4 +- .../stdout.expected | 4 +- .../model.expected.json | 2 +- .../stdout.expected | 2 +- .../model.expected.json | 4 +- .../stdout.expected | 4 +- .../model.expected.json | 6 +- .../stdout.expected | 6 +- .../model.expected.json | 8 +- .../stdout.expected | 8 +- .../model.expected.json | 6 +- .../stdout.expected | 6 +- .../model.expected.json | 4 +- .../stdout.expected | 4 +- .../model.expected.json | 8 +- .../stdout.expected | 8 +- .../model.expected.json | 10 +- .../stdout.expected | 10 +- .../model.expected.json | 4 +- .../stdout.expected | 4 +- .../model.expected.json | 4 +- .../stdout.expected | 4 +- .../model.expected.json | 10 +- .../stdout.expected | 10 +- .../model.expected.json | 6 +- .../stdout.expected | 7 +- .../model.expected.json | 4 +- .../stdout.expected | 4 +- .../model.expected.json | 6 +- .../stdout.expected | 6 +- .../model.expected.json | 6 +- .../stdout.expected | 6 +- .../model.expected.json | 8 +- .../stdout.expected | 8 +- .../model.expected.json | 6 +- .../stdout.expected | 6 +- .../model.expected.json | 2 +- .../stdout.expected | 2 +- .../model.expected.json | 8 +- .../stdout.expected | 8 +- .../model.expected.json | 8 +- .../stdout.expected | 8 +- .../model.expected.json | 12 +- .../stdout.expected | 12 +- .../model.expected.json | 2 +- .../stdout.expected | 2 +- .../model.expected.json | 4 +- .../stdout.expected | 4 +- .../model.expected.json | 2 +- .../stdout.expected | 2 +- .../model.expected.json | 4 +- .../stdout.expected | 4 +- .../model.expected.json | 6 +- .../stdout.expected | 6 +- .../model.expected.json | 6 +- .../stdout.expected | 6 +- .../model.expected.json | 2 +- .../stdout.expected | 2 +- .../model.expected.json | 8 +- .../stdout.expected | 8 +- .../model.expected.json | 6 +- .../stdout.expected | 6 +- .../model.expected.json | 10 +- .../stdout.expected | 10 +- .../model.expected.json | 6 +- .../stdout.expected | 6 +- .../model.expected.json | 14 +- .../stdout.expected | 14 +- .../model.expected.json | 8 +- .../stdout.expected | 8 +- .../model.expected.json | 6 +- .../stdout.expected | 6 +- .../model.expected.json | 2 +- .../stdout.expected | 2 +- .../model.expected.json | 6 +- .../stdout.expected | 6 +- .../model.expected.json | 6 +- .../stdout.expected | 6 +- .../model.expected.json | 2 +- .../stdout.expected | 2 +- .../model.expected.json | 8 +- .../stdout.expected | 8 +- .../model.expected.json | 4 +- .../stdout.expected | 4 +- .../model.expected.json | 8 +- .../stdout.expected | 8 +- .../model.expected.json | 4 +- .../stdout.expected | 4 +- .../model.expected.json | 8 +- .../stdout.expected | 8 +- .../model.expected.json | 4 +- .../stdout.expected | 4 +- .../model.expected.json | 2 +- .../stdout.expected | 2 +- .../model.expected.json | 6 +- .../stdout.expected | 6 +- .../model.expected.json | 2 +- .../stdout.expected | 2 +- .../model.expected.json | 2 +- .../stdout.expected | 2 +- .../model.expected.json | 2 +- .../stdout.expected | 2 +- .../model.expected.json | 6 +- .../stdout.expected | 6 +- .../model.expected.json | 6 +- .../stdout.expected | 6 +- .../model.expected.json | 8 +- .../stdout.expected | 8 +- .../model.expected.json | 6 +- .../stdout.expected | 6 +- .../model.expected.json | 6 +- .../stdout.expected | 6 +- .../model.expected.json | 8 +- .../stdout.expected | 8 +- .../model.expected.json | 4 +- .../stdout.expected | 4 +- .../model.expected.json | 2 +- .../stdout.expected | 2 +- .../model.expected.json | 2 +- .../stdout.expected | 2 +- .../model.expected.json | 4 +- .../stdout.expected | 4 +- .../model.expected.json | 4 +- .../stdout.expected | 4 +- .../model.expected.json | 4 +- .../stdout.expected | 4 +- .../model.expected.json | 8 +- .../stdout.expected | 8 +- .../model.expected.json | 10 +- .../stdout.expected | 10 +- .../model.expected.json | 6 +- .../stdout.expected | 6 +- .../model.expected.json | 4 +- .../stdout.expected | 4 +- .../model.expected.json | 2 +- .../stdout.expected | 2 +- .../model.expected.json | 8 +- .../stdout.expected | 8 +- .../model.expected.json | 4 +- .../stdout.expected | 4 +- .../model.expected.json | 4 +- .../stdout.expected | 4 +- .../model.expected.json | 2 +- .../stdout.expected | 2 +- .../model.expected.json | 6 +- .../stdout.expected | 6 +- .../model.expected.json | 6 +- .../stdout.expected | 7 +- .../model.expected.json | 2 +- .../stdout.expected | 2 +- .../model.expected.json | 8 +- .../stdout.expected | 8 +- .../model.expected.json | 4 +- .../stdout.expected | 4 +- .../model.expected.json | 4 +- .../stdout.expected | 4 +- .../model.expected.json | 6 +- .../stdout.expected | 6 +- .../model.expected.json | 6 +- .../stdout.expected | 6 +- .../model.expected.json | 8 +- .../stdout.expected | 8 +- .../model.expected.json | 4 +- .../stdout.expected | 4 +- .../model.expected.json | 2 +- .../stdout.expected | 2 +- .../model.expected.json | 8 +- .../stdout.expected | 8 +- .../model.expected.json | 6 +- .../stdout.expected | 6 +- .../model.expected.json | 2 +- .../stdout.expected | 2 +- .../model.expected.json | 6 +- .../stdout.expected | 6 +- .../model.expected.json | 4 +- .../stdout.expected | 4 +- .../model.expected.json | 2 +- .../stdout.expected | 2 +- .../model.expected.json | 4 +- .../stdout.expected | 4 +- .../model.expected.json | 2 +- .../stdout.expected | 2 +- .../model.expected.json | 4 +- .../stdout.expected | 4 +- .../model.expected.json | 6 +- .../stdout.expected | 6 +- .../model.expected.json | 4 +- .../stdout.expected | 4 +- .../model.expected.json | 6 +- .../stdout.expected | 6 +- .../model.expected.json | 6 +- .../stdout.expected | 6 +- .../model.expected.json | 4 +- .../stdout.expected | 4 +- .../model.expected.json | 4 +- .../stdout.expected | 4 +- .../model.expected.json | 2 +- .../stdout.expected | 2 +- .../model.expected.json | 4 +- .../stdout.expected | 4 +- .../model.expected.json | 2 +- .../stdout.expected | 2 +- .../model.expected.json | 2 +- .../stdout.expected | 2 +- .../model.expected.json | 4 +- .../stdout.expected | 4 +- .../model.expected.json | 2 +- .../stdout.expected | 2 +- .../model.expected.json | 10 +- .../stdout.expected | 10 +- .../model.expected.json | 8 +- .../stdout.expected | 9 +- .../model.expected.json | 6 +- .../stdout.expected | 6 +- .../model.expected.json | 8 +- .../stdout.expected | 8 +- .../model.expected.json | 2 +- .../stdout.expected | 2 +- .../model.expected.json | 2 +- .../stdout.expected | 2 +- .../model.expected.json | 6 +- .../stdout.expected | 6 +- .../model.expected.json | 4 +- .../stdout.expected | 4 +- .../model.expected.json | 8 +- .../stdout.expected | 8 +- .../model.expected.json | 2 +- .../stdout.expected | 2 +- .../model.expected.json | 2 +- .../stdout.expected | 2 +- .../model.expected.json | 2 +- .../stdout.expected | 2 +- .../model.expected.json | 10 +- .../stdout.expected | 10 +- .../model.expected.json | 8 +- .../stdout.expected | 9 +- .../605~1436581770_45/model.expected.json | 2 +- .../autogen/605~1436581770_45/stdout.expected | 2 +- 1571 files changed, 15079 insertions(+), 11709 deletions(-) create mode 100644 tests/exhaustive/issues/102/expected/model-solution000001.solution delete mode 100644 tests/exhaustive/issues/102/expected/model.eprime.orig create mode 100644 tests/exhaustive/issues/166/expected/model_1_1-solution000001.solution delete mode 100644 tests/exhaustive/issues/166/expected/model_1_1.eprime.orig create mode 100644 tests/exhaustive/issues/166/expected/model_1_2-solution000001.solution delete mode 100644 tests/exhaustive/issues/166/expected/model_1_2.eprime.orig create mode 100644 tests/exhaustive/issues/166/expected/model_1_3-solution000001.solution delete mode 100644 tests/exhaustive/issues/166/expected/model_1_3.eprime.orig create mode 100644 tests/exhaustive/issues/166/expected/model_1_4-solution000001.solution delete mode 100644 tests/exhaustive/issues/166/expected/model_1_4.eprime.orig create mode 100644 tests/exhaustive/issues/166/expected/model_2_1-solution000001.solution delete mode 100644 tests/exhaustive/issues/166/expected/model_2_1.eprime.orig create mode 100644 tests/exhaustive/issues/166/expected/model_2_2-solution000001.solution delete mode 100644 tests/exhaustive/issues/166/expected/model_2_2.eprime.orig create mode 100644 tests/exhaustive/issues/166/expected/model_2_3-solution000001.solution delete mode 100644 tests/exhaustive/issues/166/expected/model_2_3.eprime.orig create mode 100644 tests/exhaustive/issues/166/expected/model_2_4-solution000001.solution delete mode 100644 tests/exhaustive/issues/166/expected/model_2_4.eprime.orig create mode 100644 tests/exhaustive/issues/166/expected/model_3_1-solution000001.solution delete mode 100644 tests/exhaustive/issues/166/expected/model_3_1.eprime.orig create mode 100644 tests/exhaustive/issues/166/expected/model_3_2-solution000001.solution delete mode 100644 tests/exhaustive/issues/166/expected/model_3_2.eprime.orig create mode 100644 tests/exhaustive/issues/166/expected/model_3_3-solution000001.solution delete mode 100644 tests/exhaustive/issues/166/expected/model_3_3.eprime.orig create mode 100644 tests/exhaustive/issues/166/expected/model_3_4-solution000001.solution delete mode 100644 tests/exhaustive/issues/166/expected/model_3_4.eprime.orig create mode 100644 tests/exhaustive/issues/166/expected/model_4_1-solution000001.solution delete mode 100644 tests/exhaustive/issues/166/expected/model_4_1.eprime.orig create mode 100644 tests/exhaustive/issues/166/expected/model_4_2-solution000001.solution delete mode 100644 tests/exhaustive/issues/166/expected/model_4_2.eprime.orig create mode 100644 tests/exhaustive/issues/166/expected/model_4_3-solution000001.solution delete mode 100644 tests/exhaustive/issues/166/expected/model_4_3.eprime.orig create mode 100644 tests/exhaustive/issues/166/expected/model_4_4-solution000001.solution delete mode 100644 tests/exhaustive/issues/166/expected/model_4_4.eprime.orig create mode 100644 tests/exhaustive/issues/212/expected/model_1_1-1-solution000001.solution create mode 100644 tests/exhaustive/issues/212/expected/model_1_1-1.eprime-param create mode 100644 tests/exhaustive/issues/212/expected/model_1_1.eprime create mode 100644 tests/exhaustive/issues/212/expected/model_1_2-1-solution000001.solution create mode 100644 tests/exhaustive/issues/212/expected/model_1_2-1.eprime-param create mode 100644 tests/exhaustive/issues/212/expected/model_1_2.eprime create mode 100644 tests/exhaustive/issues/212/expected/model_1_3-1-solution000001.solution create mode 100644 tests/exhaustive/issues/212/expected/model_1_3-1.eprime-param create mode 100644 tests/exhaustive/issues/212/expected/model_1_3.eprime create mode 100644 tests/exhaustive/issues/212/expected/model_1_4-1-solution000001.solution create mode 100644 tests/exhaustive/issues/212/expected/model_1_4-1.eprime-param create mode 100644 tests/exhaustive/issues/212/expected/model_1_4.eprime create mode 100644 tests/exhaustive/issues/212/expected/model_2_1-1-solution000001.solution create mode 100644 tests/exhaustive/issues/212/expected/model_2_1-1.eprime-param create mode 100644 tests/exhaustive/issues/212/expected/model_2_1.eprime create mode 100644 tests/exhaustive/issues/212/expected/model_2_2-1-solution000001.solution create mode 100644 tests/exhaustive/issues/212/expected/model_2_2-1.eprime-param create mode 100644 tests/exhaustive/issues/212/expected/model_2_2.eprime create mode 100644 tests/exhaustive/issues/212/expected/model_2_3-1-solution000001.solution create mode 100644 tests/exhaustive/issues/212/expected/model_2_3-1.eprime-param create mode 100644 tests/exhaustive/issues/212/expected/model_2_3.eprime create mode 100644 tests/exhaustive/issues/212/expected/model_2_4-1-solution000001.solution create mode 100644 tests/exhaustive/issues/212/expected/model_2_4-1.eprime-param create mode 100644 tests/exhaustive/issues/212/expected/model_2_4.eprime create mode 100644 tests/exhaustive/issues/212/expected/model_3_1-1-solution000001.solution create mode 100644 tests/exhaustive/issues/212/expected/model_3_1-1.eprime-param create mode 100644 tests/exhaustive/issues/212/expected/model_3_1.eprime create mode 100644 tests/exhaustive/issues/212/expected/model_3_2-1-solution000001.solution create mode 100644 tests/exhaustive/issues/212/expected/model_3_2-1.eprime-param create mode 100644 tests/exhaustive/issues/212/expected/model_3_2.eprime create mode 100644 tests/exhaustive/issues/212/expected/model_3_3-1-solution000001.solution create mode 100644 tests/exhaustive/issues/212/expected/model_3_3-1.eprime-param create mode 100644 tests/exhaustive/issues/212/expected/model_3_3.eprime create mode 100644 tests/exhaustive/issues/212/expected/model_3_4-1-solution000001.solution create mode 100644 tests/exhaustive/issues/212/expected/model_3_4-1.eprime-param create mode 100644 tests/exhaustive/issues/212/expected/model_3_4.eprime create mode 100644 tests/exhaustive/issues/212/expected/model_4_1-1-solution000001.solution create mode 100644 tests/exhaustive/issues/212/expected/model_4_1-1.eprime-param create mode 100644 tests/exhaustive/issues/212/expected/model_4_1.eprime create mode 100644 tests/exhaustive/issues/212/expected/model_4_2-1-solution000001.solution create mode 100644 tests/exhaustive/issues/212/expected/model_4_2-1.eprime-param create mode 100644 tests/exhaustive/issues/212/expected/model_4_2.eprime create mode 100644 tests/exhaustive/issues/212/expected/model_4_3-1-solution000001.solution create mode 100644 tests/exhaustive/issues/212/expected/model_4_3-1.eprime-param create mode 100644 tests/exhaustive/issues/212/expected/model_4_3.eprime create mode 100644 tests/exhaustive/issues/212/expected/model_4_4-1-solution000001.solution create mode 100644 tests/exhaustive/issues/212/expected/model_4_4-1.eprime-param create mode 100644 tests/exhaustive/issues/212/expected/model_4_4.eprime create mode 100644 tests/exhaustive/issues/286/expected/model_1_1-p1-solution000001.solution create mode 100644 tests/exhaustive/issues/286/expected/model_1_1-p1-solution000002.solution create mode 100644 tests/exhaustive/issues/286/expected/model_1_1-p1-solution000003.solution create mode 100644 tests/exhaustive/issues/286/expected/model_1_1-p1-solution000004.solution create mode 100644 tests/exhaustive/issues/286/expected/model_1_1-p1-solution000005.solution create mode 100644 tests/exhaustive/issues/286/expected/model_1_1-p1-solution000006.solution create mode 100644 tests/exhaustive/issues/286/expected/model_1_1-p1-solution000007.solution create mode 100644 tests/exhaustive/issues/286/expected/model_1_1-p1-solution000008.solution create mode 100644 tests/exhaustive/issues/286/expected/model_1_1-p1.eprime-param create mode 100644 tests/exhaustive/issues/286/expected/model_1_1.eprime create mode 100644 tests/exhaustive/issues/286/expected/model_1_2-p1-solution000001.solution create mode 100644 tests/exhaustive/issues/286/expected/model_1_2-p1-solution000002.solution create mode 100644 tests/exhaustive/issues/286/expected/model_1_2-p1-solution000003.solution create mode 100644 tests/exhaustive/issues/286/expected/model_1_2-p1-solution000004.solution create mode 100644 tests/exhaustive/issues/286/expected/model_1_2-p1-solution000005.solution create mode 100644 tests/exhaustive/issues/286/expected/model_1_2-p1-solution000006.solution create mode 100644 tests/exhaustive/issues/286/expected/model_1_2-p1-solution000007.solution create mode 100644 tests/exhaustive/issues/286/expected/model_1_2-p1-solution000008.solution create mode 100644 tests/exhaustive/issues/286/expected/model_1_2-p1.eprime-param create mode 100644 tests/exhaustive/issues/286/expected/model_1_2.eprime create mode 100644 tests/exhaustive/issues/286/expected/model_1_3-p1-solution000001.solution create mode 100644 tests/exhaustive/issues/286/expected/model_1_3-p1-solution000002.solution create mode 100644 tests/exhaustive/issues/286/expected/model_1_3-p1-solution000003.solution create mode 100644 tests/exhaustive/issues/286/expected/model_1_3-p1-solution000004.solution create mode 100644 tests/exhaustive/issues/286/expected/model_1_3-p1-solution000005.solution create mode 100644 tests/exhaustive/issues/286/expected/model_1_3-p1-solution000006.solution create mode 100644 tests/exhaustive/issues/286/expected/model_1_3-p1-solution000007.solution create mode 100644 tests/exhaustive/issues/286/expected/model_1_3-p1-solution000008.solution create mode 100644 tests/exhaustive/issues/286/expected/model_1_3-p1.eprime-param delete mode 100644 tests/exhaustive/issues/286/expected/model_1_3.eprime.orig create mode 100644 tests/exhaustive/issues/286/expected/model_1_4-p1-solution000001.solution create mode 100644 tests/exhaustive/issues/286/expected/model_1_4-p1-solution000002.solution create mode 100644 tests/exhaustive/issues/286/expected/model_1_4-p1-solution000003.solution create mode 100644 tests/exhaustive/issues/286/expected/model_1_4-p1-solution000004.solution create mode 100644 tests/exhaustive/issues/286/expected/model_1_4-p1-solution000005.solution create mode 100644 tests/exhaustive/issues/286/expected/model_1_4-p1-solution000006.solution create mode 100644 tests/exhaustive/issues/286/expected/model_1_4-p1-solution000007.solution create mode 100644 tests/exhaustive/issues/286/expected/model_1_4-p1-solution000008.solution create mode 100644 tests/exhaustive/issues/286/expected/model_1_4-p1.eprime-param create mode 100644 tests/exhaustive/issues/286/expected/model_1_4.eprime create mode 100644 tests/exhaustive/issues/286/expected/model_2_1-p1-solution000001.solution create mode 100644 tests/exhaustive/issues/286/expected/model_2_1-p1-solution000002.solution create mode 100644 tests/exhaustive/issues/286/expected/model_2_1-p1-solution000003.solution create mode 100644 tests/exhaustive/issues/286/expected/model_2_1-p1-solution000004.solution create mode 100644 tests/exhaustive/issues/286/expected/model_2_1-p1-solution000005.solution create mode 100644 tests/exhaustive/issues/286/expected/model_2_1-p1-solution000006.solution create mode 100644 tests/exhaustive/issues/286/expected/model_2_1-p1-solution000007.solution create mode 100644 tests/exhaustive/issues/286/expected/model_2_1-p1-solution000008.solution create mode 100644 tests/exhaustive/issues/286/expected/model_2_1-p1.eprime-param create mode 100644 tests/exhaustive/issues/286/expected/model_2_1.eprime create mode 100644 tests/exhaustive/issues/286/expected/model_2_2-p1-solution000001.solution create mode 100644 tests/exhaustive/issues/286/expected/model_2_2-p1-solution000002.solution create mode 100644 tests/exhaustive/issues/286/expected/model_2_2-p1-solution000003.solution create mode 100644 tests/exhaustive/issues/286/expected/model_2_2-p1-solution000004.solution create mode 100644 tests/exhaustive/issues/286/expected/model_2_2-p1-solution000005.solution create mode 100644 tests/exhaustive/issues/286/expected/model_2_2-p1-solution000006.solution create mode 100644 tests/exhaustive/issues/286/expected/model_2_2-p1-solution000007.solution create mode 100644 tests/exhaustive/issues/286/expected/model_2_2-p1-solution000008.solution create mode 100644 tests/exhaustive/issues/286/expected/model_2_2-p1.eprime-param create mode 100644 tests/exhaustive/issues/286/expected/model_2_2.eprime create mode 100644 tests/exhaustive/issues/286/expected/model_2_3-p1-solution000001.solution create mode 100644 tests/exhaustive/issues/286/expected/model_2_3-p1-solution000002.solution create mode 100644 tests/exhaustive/issues/286/expected/model_2_3-p1-solution000003.solution create mode 100644 tests/exhaustive/issues/286/expected/model_2_3-p1-solution000004.solution create mode 100644 tests/exhaustive/issues/286/expected/model_2_3-p1-solution000005.solution create mode 100644 tests/exhaustive/issues/286/expected/model_2_3-p1-solution000006.solution create mode 100644 tests/exhaustive/issues/286/expected/model_2_3-p1-solution000007.solution create mode 100644 tests/exhaustive/issues/286/expected/model_2_3-p1-solution000008.solution create mode 100644 tests/exhaustive/issues/286/expected/model_2_3-p1.eprime-param delete mode 100644 tests/exhaustive/issues/286/expected/model_2_3.eprime.orig create mode 100644 tests/exhaustive/issues/286/expected/model_2_4-p1-solution000001.solution create mode 100644 tests/exhaustive/issues/286/expected/model_2_4-p1-solution000002.solution create mode 100644 tests/exhaustive/issues/286/expected/model_2_4-p1-solution000003.solution create mode 100644 tests/exhaustive/issues/286/expected/model_2_4-p1-solution000004.solution create mode 100644 tests/exhaustive/issues/286/expected/model_2_4-p1-solution000005.solution create mode 100644 tests/exhaustive/issues/286/expected/model_2_4-p1-solution000006.solution create mode 100644 tests/exhaustive/issues/286/expected/model_2_4-p1-solution000007.solution create mode 100644 tests/exhaustive/issues/286/expected/model_2_4-p1-solution000008.solution create mode 100644 tests/exhaustive/issues/286/expected/model_2_4-p1.eprime-param create mode 100644 tests/exhaustive/issues/286/expected/model_2_4.eprime create mode 100644 tests/exhaustive/issues/286/expected/model_3_1-p1-solution000001.solution create mode 100644 tests/exhaustive/issues/286/expected/model_3_1-p1-solution000002.solution create mode 100644 tests/exhaustive/issues/286/expected/model_3_1-p1-solution000003.solution create mode 100644 tests/exhaustive/issues/286/expected/model_3_1-p1-solution000004.solution create mode 100644 tests/exhaustive/issues/286/expected/model_3_1-p1-solution000005.solution create mode 100644 tests/exhaustive/issues/286/expected/model_3_1-p1-solution000006.solution create mode 100644 tests/exhaustive/issues/286/expected/model_3_1-p1-solution000007.solution create mode 100644 tests/exhaustive/issues/286/expected/model_3_1-p1-solution000008.solution create mode 100644 tests/exhaustive/issues/286/expected/model_3_1-p1.eprime-param delete mode 100644 tests/exhaustive/issues/286/expected/model_3_1.eprime.orig create mode 100644 tests/exhaustive/issues/286/expected/model_3_2-p1-solution000001.solution create mode 100644 tests/exhaustive/issues/286/expected/model_3_2-p1-solution000002.solution create mode 100644 tests/exhaustive/issues/286/expected/model_3_2-p1-solution000003.solution create mode 100644 tests/exhaustive/issues/286/expected/model_3_2-p1-solution000004.solution create mode 100644 tests/exhaustive/issues/286/expected/model_3_2-p1-solution000005.solution create mode 100644 tests/exhaustive/issues/286/expected/model_3_2-p1-solution000006.solution create mode 100644 tests/exhaustive/issues/286/expected/model_3_2-p1-solution000007.solution create mode 100644 tests/exhaustive/issues/286/expected/model_3_2-p1-solution000008.solution create mode 100644 tests/exhaustive/issues/286/expected/model_3_2-p1.eprime-param delete mode 100644 tests/exhaustive/issues/286/expected/model_3_2.eprime.orig create mode 100644 tests/exhaustive/issues/286/expected/model_3_3-p1-solution000001.solution create mode 100644 tests/exhaustive/issues/286/expected/model_3_3-p1-solution000002.solution create mode 100644 tests/exhaustive/issues/286/expected/model_3_3-p1-solution000003.solution create mode 100644 tests/exhaustive/issues/286/expected/model_3_3-p1-solution000004.solution create mode 100644 tests/exhaustive/issues/286/expected/model_3_3-p1-solution000005.solution create mode 100644 tests/exhaustive/issues/286/expected/model_3_3-p1-solution000006.solution create mode 100644 tests/exhaustive/issues/286/expected/model_3_3-p1-solution000007.solution create mode 100644 tests/exhaustive/issues/286/expected/model_3_3-p1-solution000008.solution create mode 100644 tests/exhaustive/issues/286/expected/model_3_3-p1.eprime-param delete mode 100644 tests/exhaustive/issues/286/expected/model_3_3.eprime.orig create mode 100644 tests/exhaustive/issues/286/expected/model_3_4-p1-solution000001.solution create mode 100644 tests/exhaustive/issues/286/expected/model_3_4-p1-solution000002.solution create mode 100644 tests/exhaustive/issues/286/expected/model_3_4-p1-solution000003.solution create mode 100644 tests/exhaustive/issues/286/expected/model_3_4-p1-solution000004.solution create mode 100644 tests/exhaustive/issues/286/expected/model_3_4-p1-solution000005.solution create mode 100644 tests/exhaustive/issues/286/expected/model_3_4-p1-solution000006.solution create mode 100644 tests/exhaustive/issues/286/expected/model_3_4-p1-solution000007.solution create mode 100644 tests/exhaustive/issues/286/expected/model_3_4-p1-solution000008.solution create mode 100644 tests/exhaustive/issues/286/expected/model_3_4-p1.eprime-param delete mode 100644 tests/exhaustive/issues/286/expected/model_3_4.eprime.orig create mode 100644 tests/exhaustive/issues/286/expected/model_4_1-p1-solution000001.solution create mode 100644 tests/exhaustive/issues/286/expected/model_4_1-p1-solution000002.solution create mode 100644 tests/exhaustive/issues/286/expected/model_4_1-p1-solution000003.solution create mode 100644 tests/exhaustive/issues/286/expected/model_4_1-p1-solution000004.solution create mode 100644 tests/exhaustive/issues/286/expected/model_4_1-p1-solution000005.solution create mode 100644 tests/exhaustive/issues/286/expected/model_4_1-p1-solution000006.solution create mode 100644 tests/exhaustive/issues/286/expected/model_4_1-p1-solution000007.solution create mode 100644 tests/exhaustive/issues/286/expected/model_4_1-p1-solution000008.solution create mode 100644 tests/exhaustive/issues/286/expected/model_4_1-p1.eprime-param create mode 100644 tests/exhaustive/issues/286/expected/model_4_1.eprime create mode 100644 tests/exhaustive/issues/286/expected/model_4_2-p1-solution000001.solution create mode 100644 tests/exhaustive/issues/286/expected/model_4_2-p1-solution000002.solution create mode 100644 tests/exhaustive/issues/286/expected/model_4_2-p1-solution000003.solution create mode 100644 tests/exhaustive/issues/286/expected/model_4_2-p1-solution000004.solution create mode 100644 tests/exhaustive/issues/286/expected/model_4_2-p1-solution000005.solution create mode 100644 tests/exhaustive/issues/286/expected/model_4_2-p1-solution000006.solution create mode 100644 tests/exhaustive/issues/286/expected/model_4_2-p1-solution000007.solution create mode 100644 tests/exhaustive/issues/286/expected/model_4_2-p1-solution000008.solution create mode 100644 tests/exhaustive/issues/286/expected/model_4_2-p1.eprime-param create mode 100644 tests/exhaustive/issues/286/expected/model_4_2.eprime create mode 100644 tests/exhaustive/issues/286/expected/model_4_3-p1-solution000001.solution create mode 100644 tests/exhaustive/issues/286/expected/model_4_3-p1-solution000002.solution create mode 100644 tests/exhaustive/issues/286/expected/model_4_3-p1-solution000003.solution create mode 100644 tests/exhaustive/issues/286/expected/model_4_3-p1-solution000004.solution create mode 100644 tests/exhaustive/issues/286/expected/model_4_3-p1-solution000005.solution create mode 100644 tests/exhaustive/issues/286/expected/model_4_3-p1-solution000006.solution create mode 100644 tests/exhaustive/issues/286/expected/model_4_3-p1-solution000007.solution create mode 100644 tests/exhaustive/issues/286/expected/model_4_3-p1-solution000008.solution create mode 100644 tests/exhaustive/issues/286/expected/model_4_3-p1.eprime-param delete mode 100644 tests/exhaustive/issues/286/expected/model_4_3.eprime.orig create mode 100644 tests/exhaustive/issues/286/expected/model_4_4-p1-solution000001.solution create mode 100644 tests/exhaustive/issues/286/expected/model_4_4-p1-solution000002.solution create mode 100644 tests/exhaustive/issues/286/expected/model_4_4-p1-solution000003.solution create mode 100644 tests/exhaustive/issues/286/expected/model_4_4-p1-solution000004.solution create mode 100644 tests/exhaustive/issues/286/expected/model_4_4-p1-solution000005.solution create mode 100644 tests/exhaustive/issues/286/expected/model_4_4-p1-solution000006.solution create mode 100644 tests/exhaustive/issues/286/expected/model_4_4-p1-solution000007.solution create mode 100644 tests/exhaustive/issues/286/expected/model_4_4-p1-solution000008.solution create mode 100644 tests/exhaustive/issues/286/expected/model_4_4-p1.eprime-param create mode 100644 tests/exhaustive/issues/286/expected/model_4_4.eprime create mode 100644 tests/exhaustive/mildly_interesting/cyclic_graph/expected/model-cyc1-solution000001.solution create mode 100644 tests/exhaustive/mildly_interesting/cyclic_graph/expected/model-cyc1.eprime-param create mode 100644 tests/exhaustive/mildly_interesting/cyclic_graph/expected/model-cyc2-solution000001.solution create mode 100644 tests/exhaustive/mildly_interesting/cyclic_graph/expected/model-cyc2.eprime-param create mode 100644 tests/exhaustive/mildly_interesting/cyclic_graph/expected/model-non-solution000001.solution create mode 100644 tests/exhaustive/mildly_interesting/cyclic_graph/expected/model-non.eprime-param create mode 100644 tests/exhaustive/mildly_interesting/gchq_2016/expected/model-inst-solution000001.solution create mode 100644 tests/exhaustive/mildly_interesting/gchq_2016/expected/model-inst.eprime-param create mode 100644 tests/exhaustive/mildly_interesting/gchq_2016/expected/model.eprime create mode 100644 tests/exhaustive/mildly_interesting/subsetSum/expected/model_1_1_1-p1-solution000001.solution create mode 100644 tests/exhaustive/mildly_interesting/subsetSum/expected/model_1_1_1-p1.eprime-param create mode 100644 tests/exhaustive/mildly_interesting/subsetSum/expected/model_1_1_1-p2-solution000001.solution create mode 100644 tests/exhaustive/mildly_interesting/subsetSum/expected/model_1_1_1-p2-solution000002.solution create mode 100644 tests/exhaustive/mildly_interesting/subsetSum/expected/model_1_1_1-p2.eprime-param create mode 100644 tests/exhaustive/mildly_interesting/subsetSum/expected/model_1_1_1.eprime create mode 100644 tests/exhaustive/mildly_interesting/subsetSum/expected/model_1_1_2-p1-solution000001.solution create mode 100644 tests/exhaustive/mildly_interesting/subsetSum/expected/model_1_1_2-p1.eprime-param create mode 100644 tests/exhaustive/mildly_interesting/subsetSum/expected/model_1_1_2-p2-solution000001.solution create mode 100644 tests/exhaustive/mildly_interesting/subsetSum/expected/model_1_1_2-p2-solution000002.solution create mode 100644 tests/exhaustive/mildly_interesting/subsetSum/expected/model_1_1_2-p2.eprime-param create mode 100644 tests/exhaustive/mildly_interesting/subsetSum/expected/model_1_1_2.eprime create mode 100644 tests/exhaustive/mildly_interesting/subsetSum/expected/model_1_2_1-p1-solution000001.solution create mode 100644 tests/exhaustive/mildly_interesting/subsetSum/expected/model_1_2_1-p1.eprime-param create mode 100644 tests/exhaustive/mildly_interesting/subsetSum/expected/model_1_2_1-p2-solution000001.solution create mode 100644 tests/exhaustive/mildly_interesting/subsetSum/expected/model_1_2_1-p2-solution000002.solution create mode 100644 tests/exhaustive/mildly_interesting/subsetSum/expected/model_1_2_1-p2.eprime-param create mode 100644 tests/exhaustive/mildly_interesting/subsetSum/expected/model_1_2_1.eprime create mode 100644 tests/exhaustive/mildly_interesting/subsetSum/expected/model_2_1_1-p1-solution000001.solution create mode 100644 tests/exhaustive/mildly_interesting/subsetSum/expected/model_2_1_1-p1.eprime-param create mode 100644 tests/exhaustive/mildly_interesting/subsetSum/expected/model_2_1_1-p2-solution000001.solution create mode 100644 tests/exhaustive/mildly_interesting/subsetSum/expected/model_2_1_1-p2-solution000002.solution create mode 100644 tests/exhaustive/mildly_interesting/subsetSum/expected/model_2_1_1-p2.eprime-param create mode 100644 tests/exhaustive/mildly_interesting/subsetSum/expected/model_2_1_1.eprime create mode 100644 tests/exhaustive/mildly_interesting/subsetSum/expected/model_2_2_1-p1-solution000001.solution create mode 100644 tests/exhaustive/mildly_interesting/subsetSum/expected/model_2_2_1-p1.eprime-param create mode 100644 tests/exhaustive/mildly_interesting/subsetSum/expected/model_2_2_1-p2-solution000001.solution create mode 100644 tests/exhaustive/mildly_interesting/subsetSum/expected/model_2_2_1-p2-solution000002.solution create mode 100644 tests/exhaustive/mildly_interesting/subsetSum/expected/model_2_2_1-p2.eprime-param create mode 100644 tests/exhaustive/mildly_interesting/subsetSum/expected/model_2_2_1.eprime create mode 100644 tests/exhaustive/mildly_interesting/subsetSum/expected/model_2_2_2-p1-solution000001.solution create mode 100644 tests/exhaustive/mildly_interesting/subsetSum/expected/model_2_2_2-p1.eprime-param create mode 100644 tests/exhaustive/mildly_interesting/subsetSum/expected/model_2_2_2-p2-solution000001.solution create mode 100644 tests/exhaustive/mildly_interesting/subsetSum/expected/model_2_2_2-p2-solution000002.solution create mode 100644 tests/exhaustive/mildly_interesting/subsetSum/expected/model_2_2_2-p2.eprime-param create mode 100644 tests/exhaustive/mildly_interesting/subsetSum/expected/model_2_2_2.eprime create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000001.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000002.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000003.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000004.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000005.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000006.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000007.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000008.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000009.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000010.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000011.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000012.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000013.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000014.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000015.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000016.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000017.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000018.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000019.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000020.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000021.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000022.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000023.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000024.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000025.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000026.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000027.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000028.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000029.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000030.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000031.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000032.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000033.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000034.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000035.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000036.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model.eprime create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_1_1-solution000001.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_1_1-solution000002.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_1_1-solution000003.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_1_1-solution000004.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_1_1-solution000005.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_1_1-solution000006.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_1_2-solution000001.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_1_2-solution000002.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_1_2-solution000003.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_1_2-solution000004.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_1_2-solution000005.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_1_2-solution000006.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_1_3-solution000001.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_1_3-solution000002.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_1_3-solution000003.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_1_3-solution000004.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_1_3-solution000005.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_1_3-solution000006.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_2_1-solution000001.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_2_1-solution000002.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_2_1-solution000003.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_2_1-solution000004.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_2_1-solution000005.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_2_1-solution000006.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_2_2-solution000001.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_2_2-solution000002.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_2_2-solution000003.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_2_2-solution000004.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_2_2-solution000005.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_2_2-solution000006.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_2_3-solution000001.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_2_3-solution000002.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_2_3-solution000003.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_2_3-solution000004.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_2_3-solution000005.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_2_3-solution000006.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_3_1-solution000001.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_3_1-solution000002.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_3_1-solution000003.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_3_1-solution000004.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_3_1-solution000005.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_3_1-solution000006.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_3_2-solution000001.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_3_2-solution000002.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_3_2-solution000003.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_3_2-solution000004.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_3_2-solution000005.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_3_2-solution000006.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_3_3-solution000001.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_3_3-solution000002.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_3_3-solution000003.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_3_3-solution000004.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_3_3-solution000005.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_3_3-solution000006.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_1_1-solution000001.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_1_1-solution000002.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_1_1-solution000003.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_1_1-solution000004.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_1_1-solution000005.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_1_1-solution000006.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_1_2-solution000001.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_1_2-solution000002.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_1_2-solution000003.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_1_2-solution000004.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_1_2-solution000005.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_1_2-solution000006.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_1_3-solution000001.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_1_3-solution000002.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_1_3-solution000003.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_1_3-solution000004.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_1_3-solution000005.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_1_3-solution000006.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_2_1-solution000001.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_2_1-solution000002.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_2_1-solution000003.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_2_1-solution000004.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_2_1-solution000005.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_2_1-solution000006.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_2_2-solution000001.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_2_2-solution000002.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_2_2-solution000003.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_2_2-solution000004.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_2_2-solution000005.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_2_2-solution000006.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_2_3-solution000001.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_2_3-solution000002.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_2_3-solution000003.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_2_3-solution000004.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_2_3-solution000005.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_2_3-solution000006.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_3_1-solution000001.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_3_1-solution000002.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_3_1-solution000003.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_3_1-solution000004.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_3_1-solution000005.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_3_1-solution000006.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_3_2-solution000001.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_3_2-solution000002.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_3_2-solution000003.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_3_2-solution000004.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_3_2-solution000005.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_3_2-solution000006.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_3_3-solution000001.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_3_3-solution000002.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_3_3-solution000003.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_3_3-solution000004.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_3_3-solution000005.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_3_3-solution000006.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_1_1-solution000001.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_1_1-solution000002.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_1_1-solution000003.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_1_1-solution000004.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_1_1-solution000005.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_1_1-solution000006.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_1_2-solution000001.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_1_2-solution000002.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_1_2-solution000003.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_1_2-solution000004.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_1_2-solution000005.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_1_2-solution000006.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_1_3-solution000001.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_1_3-solution000002.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_1_3-solution000003.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_1_3-solution000004.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_1_3-solution000005.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_1_3-solution000006.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_2_1-solution000001.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_2_1-solution000002.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_2_1-solution000003.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_2_1-solution000004.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_2_1-solution000005.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_2_1-solution000006.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_2_2-solution000001.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_2_2-solution000002.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_2_2-solution000003.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_2_2-solution000004.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_2_2-solution000005.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_2_2-solution000006.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_2_3-solution000001.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_2_3-solution000002.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_2_3-solution000003.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_2_3-solution000004.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_2_3-solution000005.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_2_3-solution000006.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_3_1-solution000001.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_3_1-solution000002.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_3_1-solution000003.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_3_1-solution000004.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_3_1-solution000005.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_3_1-solution000006.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_3_2-solution000001.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_3_2-solution000002.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_3_2-solution000003.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_3_2-solution000004.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_3_2-solution000005.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_3_2-solution000006.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_3_3-solution000001.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_3_3-solution000002.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_3_3-solution000003.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_3_3-solution000004.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_3_3-solution000005.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_3_3-solution000006.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_1_1-solution000001.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_1_1-solution000002.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_1_1-solution000003.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_1_1-solution000004.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_1_1-solution000005.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_1_1-solution000006.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_1_2-solution000001.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_1_2-solution000002.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_1_2-solution000003.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_1_2-solution000004.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_1_2-solution000005.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_1_2-solution000006.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_1_3-solution000001.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_1_3-solution000002.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_1_3-solution000003.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_1_3-solution000004.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_1_3-solution000005.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_1_3-solution000006.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_2_1-solution000001.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_2_1-solution000002.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_2_1-solution000003.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_2_1-solution000004.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_2_1-solution000005.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_2_1-solution000006.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_2_2-solution000001.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_2_2-solution000002.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_2_2-solution000003.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_2_2-solution000004.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_2_2-solution000005.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_2_2-solution000006.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_2_3-solution000001.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_2_3-solution000002.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_2_3-solution000003.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_2_3-solution000004.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_2_3-solution000005.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_2_3-solution000006.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_3_1-solution000001.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_3_1-solution000002.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_3_1-solution000003.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_3_1-solution000004.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_3_1-solution000005.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_3_1-solution000006.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_3_2-solution000001.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_3_2-solution000002.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_3_2-solution000003.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_3_2-solution000004.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_3_2-solution000005.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_3_2-solution000006.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_3_3-solution000001.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_3_3-solution000002.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_3_3-solution000003.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_3_3-solution000004.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_3_3-solution000005.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_3_3-solution000006.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_1_1-solution000001.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_1_1-solution000002.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_1_1-solution000003.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_1_1-solution000004.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_1_1-solution000005.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_1_1-solution000006.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_1_2-solution000001.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_1_2-solution000002.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_1_2-solution000003.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_1_2-solution000004.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_1_2-solution000005.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_1_2-solution000006.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_1_3-solution000001.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_1_3-solution000002.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_1_3-solution000003.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_1_3-solution000004.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_1_3-solution000005.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_1_3-solution000006.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_2_1-solution000001.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_2_1-solution000002.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_2_1-solution000003.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_2_1-solution000004.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_2_1-solution000005.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_2_1-solution000006.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_2_2-solution000001.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_2_2-solution000002.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_2_2-solution000003.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_2_2-solution000004.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_2_2-solution000005.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_2_2-solution000006.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_2_2.eprime create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_2_3-solution000001.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_2_3-solution000002.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_2_3-solution000003.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_2_3-solution000004.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_2_3-solution000005.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_2_3-solution000006.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_2_3.eprime create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_3_1-solution000001.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_3_1-solution000002.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_3_1-solution000003.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_3_1-solution000004.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_3_1-solution000005.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_3_1-solution000006.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_3_2-solution000001.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_3_2-solution000002.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_3_2-solution000003.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_3_2-solution000004.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_3_2-solution000005.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_3_2-solution000006.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_3_2.eprime create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_3_3-solution000001.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_3_3-solution000002.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_3_3-solution000003.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_3_3-solution000004.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_3_3-solution000005.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_3_3-solution000006.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_3_3.eprime create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_1_1-solution000001.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_1_1-solution000002.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_1_1-solution000003.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_1_1-solution000004.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_1_1-solution000005.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_1_1-solution000006.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_1_2-solution000001.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_1_2-solution000002.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_1_2-solution000003.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_1_2-solution000004.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_1_2-solution000005.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_1_2-solution000006.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_1_3-solution000001.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_1_3-solution000002.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_1_3-solution000003.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_1_3-solution000004.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_1_3-solution000005.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_1_3-solution000006.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_2_1-solution000001.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_2_1-solution000002.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_2_1-solution000003.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_2_1-solution000004.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_2_1-solution000005.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_2_1-solution000006.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_2_2-solution000001.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_2_2-solution000002.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_2_2-solution000003.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_2_2-solution000004.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_2_2-solution000005.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_2_2-solution000006.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_2_2.eprime create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_2_3-solution000001.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_2_3-solution000002.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_2_3-solution000003.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_2_3-solution000004.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_2_3-solution000005.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_2_3-solution000006.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_2_3.eprime create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_3_1-solution000001.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_3_1-solution000002.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_3_1-solution000003.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_3_1-solution000004.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_3_1-solution000005.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_3_1-solution000006.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_3_2-solution000001.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_3_2-solution000002.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_3_2-solution000003.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_3_2-solution000004.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_3_2-solution000005.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_3_2-solution000006.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_3_2.eprime create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_3_3-solution000001.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_3_3-solution000002.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_3_3-solution000003.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_3_3-solution000004.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_3_3-solution000005.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_3_3-solution000006.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_3_3.eprime create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_1_1-solution000001.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_1_1-solution000002.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_1_1-solution000003.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_1_1-solution000004.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_1_1-solution000005.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_1_1-solution000006.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_1_2-solution000001.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_1_2-solution000002.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_1_2-solution000003.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_1_2-solution000004.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_1_2-solution000005.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_1_2-solution000006.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_1_3-solution000001.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_1_3-solution000002.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_1_3-solution000003.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_1_3-solution000004.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_1_3-solution000005.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_1_3-solution000006.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_2_1-solution000001.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_2_1-solution000002.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_2_1-solution000003.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_2_1-solution000004.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_2_1-solution000005.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_2_1-solution000006.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_2_2-solution000001.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_2_2-solution000002.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_2_2-solution000003.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_2_2-solution000004.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_2_2-solution000005.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_2_2-solution000006.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_2_3-solution000001.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_2_3-solution000002.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_2_3-solution000003.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_2_3-solution000004.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_2_3-solution000005.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_2_3-solution000006.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_3_1-solution000001.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_3_1-solution000002.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_3_1-solution000003.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_3_1-solution000004.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_3_1-solution000005.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_3_1-solution000006.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_3_2-solution000001.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_3_2-solution000002.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_3_2-solution000003.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_3_2-solution000004.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_3_2-solution000005.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_3_2-solution000006.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_3_3-solution000001.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_3_3-solution000002.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_3_3-solution000003.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_3_3-solution000004.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_3_3-solution000005.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_3_3-solution000006.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_1_1-solution000001.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_1_1-solution000002.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_1_1-solution000003.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_1_1-solution000004.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_1_1-solution000005.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_1_1-solution000006.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_1_2-solution000001.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_1_2-solution000002.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_1_2-solution000003.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_1_2-solution000004.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_1_2-solution000005.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_1_2-solution000006.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_1_3-solution000001.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_1_3-solution000002.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_1_3-solution000003.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_1_3-solution000004.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_1_3-solution000005.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_1_3-solution000006.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_2_1-solution000001.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_2_1-solution000002.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_2_1-solution000003.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_2_1-solution000004.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_2_1-solution000005.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_2_1-solution000006.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_2_2-solution000001.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_2_2-solution000002.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_2_2-solution000003.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_2_2-solution000004.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_2_2-solution000005.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_2_2-solution000006.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_2_2.eprime create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_2_3-solution000001.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_2_3-solution000002.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_2_3-solution000003.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_2_3-solution000004.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_2_3-solution000005.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_2_3-solution000006.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_2_3.eprime create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_3_1-solution000001.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_3_1-solution000002.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_3_1-solution000003.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_3_1-solution000004.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_3_1-solution000005.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_3_1-solution000006.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_3_2-solution000001.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_3_2-solution000002.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_3_2-solution000003.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_3_2-solution000004.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_3_2-solution000005.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_3_2-solution000006.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_3_2.eprime create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_3_3-solution000001.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_3_3-solution000002.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_3_3-solution000003.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_3_3-solution000004.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_3_3-solution000005.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_3_3-solution000006.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_3_3.eprime create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_1_1-solution000001.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_1_1-solution000002.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_1_1-solution000003.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_1_1-solution000004.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_1_1-solution000005.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_1_1-solution000006.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_1_2-solution000001.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_1_2-solution000002.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_1_2-solution000003.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_1_2-solution000004.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_1_2-solution000005.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_1_2-solution000006.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_1_3-solution000001.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_1_3-solution000002.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_1_3-solution000003.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_1_3-solution000004.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_1_3-solution000005.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_1_3-solution000006.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_2_1-solution000001.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_2_1-solution000002.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_2_1-solution000003.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_2_1-solution000004.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_2_1-solution000005.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_2_1-solution000006.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_2_2-solution000001.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_2_2-solution000002.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_2_2-solution000003.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_2_2-solution000004.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_2_2-solution000005.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_2_2-solution000006.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_2_2.eprime create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_2_3-solution000001.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_2_3-solution000002.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_2_3-solution000003.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_2_3-solution000004.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_2_3-solution000005.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_2_3-solution000006.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_2_3.eprime create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_3_1-solution000001.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_3_1-solution000002.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_3_1-solution000003.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_3_1-solution000004.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_3_1-solution000005.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_3_1-solution000006.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_3_2-solution000001.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_3_2-solution000002.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_3_2-solution000003.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_3_2-solution000004.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_3_2-solution000005.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_3_2-solution000006.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_3_2.eprime create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_3_3-solution000001.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_3_3-solution000002.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_3_3-solution000003.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_3_3-solution000004.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_3_3-solution000005.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_3_3-solution000006.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_3_3.eprime create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_1_1-solution000001.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_1_1.eprime create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_1_2-solution000001.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_1_2.eprime create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_1_3-solution000001.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_1_3.eprime.orig create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_1_4-solution000001.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_1_4.eprime create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_2_1-solution000001.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_2_1.eprime create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_2_2-solution000001.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_2_2.eprime create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_2_3-solution000001.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_2_3.eprime.orig create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_2_4-solution000001.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_2_4.eprime create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_3_1-solution000001.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_3_1.eprime.orig create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_3_2-solution000001.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_3_2.eprime.orig create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_3_3-solution000001.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_3_3.eprime.orig create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_3_4-solution000001.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_3_4.eprime.orig create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_4_1-solution000001.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_4_1.eprime create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_4_2-solution000001.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_4_2.eprime create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_4_3-solution000001.solution delete mode 100644 tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_4_3.eprime.orig create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_4_4-solution000001.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_4_4.eprime create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000001.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000002.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000003.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000004.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000005.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000006.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000007.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000008.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000009.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000010.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000011.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000012.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000013.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000014.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000015.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000016.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000017.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000018.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000019.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000020.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000021.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000022.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000023.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000024.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000025.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000026.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000027.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000028.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000029.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000030.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000031.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000032.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000033.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000034.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000035.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000036.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000037.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000038.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000039.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000040.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000041.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000042.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000043.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000044.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000045.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000046.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000047.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000048.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000049.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000050.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000051.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000052.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000053.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000054.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000055.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000056.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000057.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000058.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000059.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000060.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000061.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000062.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000063.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000064.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000065.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000066.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000067.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000068.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000069.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000070.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000071.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000072.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000073.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000074.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000075.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000076.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000077.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000078.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000079.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000080.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000081.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000082.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000083.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000084.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000085.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000086.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000087.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000088.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000089.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000090.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000091.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000092.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000093.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000094.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000095.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000096.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000097.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000098.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000099.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000100.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000101.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000102.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000103.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000104.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000105.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000106.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000107.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000108.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000109.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000110.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000111.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000112.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000113.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000114.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000115.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000116.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000117.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000118.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000119.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000120.solution create mode 100644 tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model.eprime diff --git a/tests/exhaustive/issues/102/expected/model-solution000001.solution b/tests/exhaustive/issues/102/expected/model-solution000001.solution new file mode 100644 index 0000000000..f632708ff2 --- /dev/null +++ b/tests/exhaustive/issues/102/expected/model-solution000001.solution @@ -0,0 +1,28 @@ +language Essence 1.3 + +letting actions be sequence((8, 5, 5), (5, 3, 3), (3, 8, 3), (5, 3, 2), (8, 5, 5), (5, 3, 1), (3, 8, 3)) +$ Visualisation for actions +$ 8 5 5 +$ 5 3 3 +$ 3 8 3 +$ 5 3 2 +$ 8 5 5 +$ 5 3 1 +$ 3 8 3 + +letting nbActions be 7 +letting states be + sequence(function(3 --> 0, 5 --> 0, 8 --> 8), function(3 --> 0, 5 --> 5, 8 --> 3), + function(3 --> 3, 5 --> 2, 8 --> 3), function(3 --> 0, 5 --> 2, 8 --> 6), + function(3 --> 2, 5 --> 0, 8 --> 6), function(3 --> 2, 5 --> 5, 8 --> 1), + function(3 --> 3, 5 --> 4, 8 --> 1), function(3 --> 0, 5 --> 4, 8 --> 4)) +$ Visualisation for states +$ 0 0 8 +$ 0 5 3 +$ 3 2 3 +$ 0 2 6 +$ 2 0 6 +$ 2 5 1 +$ 3 4 1 +$ 0 4 4 + diff --git a/tests/exhaustive/issues/102/expected/model.eprime.orig b/tests/exhaustive/issues/102/expected/model.eprime.orig deleted file mode 100644 index 2fdb0966d5..0000000000 --- a/tests/exhaustive/issues/102/expected/model.eprime.orig +++ /dev/null @@ -1,88 +0,0 @@ -language ESSENCE' 1.0 - -letting HORIZON be 10 -find actions_ExplicitBounded_Length: int(0..10) -find actions_ExplicitBounded_Values_1: matrix indexed by [int(1..10)] of int(3, 5, 8) -find actions_ExplicitBounded_Values_2: matrix indexed by [int(1..10)] of int(3, 5, 8) -find actions_ExplicitBounded_Values_3: matrix indexed by [int(1..10)] of int(1..8) -letting let1 be 8 -find states_ExplicitBoundedR10_Length: int(0..10) -find states_ExplicitBoundedR10_Values_Function1D: matrix indexed by [int(1..10), int(3, 5, 8)] of int(0..8) -find nbActions: int(7) -branching on - [actions_ExplicitBounded_Length, actions_ExplicitBounded_Values_1, actions_ExplicitBounded_Values_2, - actions_ExplicitBounded_Values_3, states_ExplicitBoundedR10_Length, states_ExplicitBoundedR10_Values_Function1D, - nbActions] -such that - actions_ExplicitBounded_Length = states_ExplicitBoundedR10_Length - 1, - and([q34 <= actions_ExplicitBounded_Length -> - actions_ExplicitBounded_Values_1[q34] != actions_ExplicitBounded_Values_2[q34] - | q34 : int(1..10)]), - and([q11 <= actions_ExplicitBounded_Length -> - actions_ExplicitBounded_Values_3[q11] <= - states_ExplicitBoundedR10_Values_Function1D[q11, actions_ExplicitBounded_Values_1[q11]] - /\ q11 <= states_ExplicitBoundedR10_Length - | q11 : int(1..10)]), - and([q36 <= states_ExplicitBoundedR10_Length -> - and([sum([states_ExplicitBoundedR10_Values_Function1D[q36, q37] | q37 : int(3, 5, 8), q37 = b]) <= b /\ - or([q38 = b | q38 : int(3, 5, 8)]) - | b : int(3, 5, 8)]) - | q36 : int(1..10)]), - and([q13 <= actions_ExplicitBounded_Length -> - and([states_ExplicitBoundedR10_Values_Function1D[q13, actions_ExplicitBounded_Values_1[q13]] - - actions_ExplicitBounded_Values_3[q13] - = states_ExplicitBoundedR10_Values_Function1D[q13 + 1, actions_ExplicitBounded_Values_1[q13]], - q13 <= states_ExplicitBoundedR10_Length, q13 + 1 <= states_ExplicitBoundedR10_Length; - int(1..3)]) - | q13 : int(1..10)]), - and([q15 <= actions_ExplicitBounded_Length -> - and([states_ExplicitBoundedR10_Values_Function1D[q15, actions_ExplicitBounded_Values_2[q15]] + - actions_ExplicitBounded_Values_3[q15] - = states_ExplicitBoundedR10_Values_Function1D[q15 + 1, actions_ExplicitBounded_Values_2[q15]], - q15 <= states_ExplicitBoundedR10_Length, q15 + 1 <= states_ExplicitBoundedR10_Length; - int(1..3)]) - | q15 : int(1..10)]), - and([q18 <= actions_ExplicitBounded_Length -> - and([!(actions_ExplicitBounded_Values_1[q18] = b \/ actions_ExplicitBounded_Values_2[q18] = b) -> - and([states_ExplicitBoundedR10_Values_Function1D[q18, b] = - states_ExplicitBoundedR10_Values_Function1D[q18 + 1, b], - q18 <= states_ExplicitBoundedR10_Length, q18 + 1 <= states_ExplicitBoundedR10_Length; - int(1..3)]) - | b : int(3, 5, 8)]) - | q18 : int(1..10)]), - and([q20 <= actions_ExplicitBounded_Length -> - states_ExplicitBoundedR10_Values_Function1D[q20 + 1, actions_ExplicitBounded_Values_1[q20]] = 0 /\ - q20 + 1 <= states_ExplicitBoundedR10_Length - \/ - states_ExplicitBoundedR10_Values_Function1D[q20 + 1, actions_ExplicitBounded_Values_2[q20]] = - actions_ExplicitBounded_Values_2[q20] - /\ q20 + 1 <= states_ExplicitBoundedR10_Length - | q20 : int(1..10)]), - and([sum([sum([0 | 3 = q22]), sum([0 | 5 = q22]), sum([8 | 8 = q22]); int(1..3)]) = - states_ExplicitBoundedR10_Values_Function1D[1, q22] - /\ or([3 = q22, 5 = q22, 8 = q22; int(1..3)]) - | q22 : int(3, 5, 8)]), - states_ExplicitBoundedR10_Values_Function1D[1, 3] = 0, - states_ExplicitBoundedR10_Values_Function1D[1, 5] = 0, - states_ExplicitBoundedR10_Values_Function1D[1, 8] = 8, - 1 <= states_ExplicitBoundedR10_Length, - and([sum([sum([0 | 3 = q28]), sum([4 | 5 = q28]), sum([4 | 8 = q28]); int(1..3)]) = - states_ExplicitBoundedR10_Values_Function1D[states_ExplicitBoundedR10_Length, q28] - /\ or([3 = q28, 5 = q28, 8 = q28; int(1..3)]) - | q28 : int(3, 5, 8)]), - states_ExplicitBoundedR10_Values_Function1D[states_ExplicitBoundedR10_Length, 3] = 0, - states_ExplicitBoundedR10_Values_Function1D[states_ExplicitBoundedR10_Length, 5] = 4, - states_ExplicitBoundedR10_Values_Function1D[states_ExplicitBoundedR10_Length, 8] = 4, - states_ExplicitBoundedR10_Length <= states_ExplicitBoundedR10_Length, - 7 = actions_ExplicitBounded_Length, - and([q1 > states_ExplicitBoundedR10_Length -> - and([states_ExplicitBoundedR10_Values_Function1D[q1, q4] = 0 | q4 : int(3, 5, 8)]) - | q1 : int(1..10)]), - states_ExplicitBoundedR10_Length <= 10, - and([q5 > actions_ExplicitBounded_Length -> - and([actions_ExplicitBounded_Values_1[q5] = 3, actions_ExplicitBounded_Values_2[q5] = 3, - actions_ExplicitBounded_Values_3[q5] = 1; - int(1..3)]) - | q5 : int(1..10)]), - actions_ExplicitBounded_Length <= 10 - diff --git a/tests/exhaustive/issues/166/expected/model_1_1-solution000001.solution b/tests/exhaustive/issues/166/expected/model_1_1-solution000001.solution new file mode 100644 index 0000000000..15cf35802e --- /dev/null +++ b/tests/exhaustive/issues/166/expected/model_1_1-solution000001.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting y be + tuple ([(10, function(1 --> {1, 2}, 2 --> {1}, 3 --> {}), 33), + (11, function(1 --> {1, 2}, 2 --> {1}, 3 --> {}), 55); + int(1..2)]) diff --git a/tests/exhaustive/issues/166/expected/model_1_1.eprime.orig b/tests/exhaustive/issues/166/expected/model_1_1.eprime.orig deleted file mode 100644 index 7199fd0ce5..0000000000 --- a/tests/exhaustive/issues/166/expected/model_1_1.eprime.orig +++ /dev/null @@ -1,46 +0,0 @@ -language ESSENCE' 1.0 - -find y_1_1: matrix indexed by [int(1, 2)] of int(10, 11) -find y_1_2_Function1DR2_Occurrence: matrix indexed by [int(1, 2), int(1..3), int(1, 2)] of bool -find y_1_3: matrix indexed by [int(1, 2)] of int(33, 55) -branching on [y_1_1, y_1_2_Function1DR2_Occurrence, y_1_3] -such that - and([and([y_1_1[q4] = [10, 11; int(1..2)][q4], - and([and([y_1_2_Function1DR2_Occurrence[q4, q7, 1] | 1 = q4, 1 = q7]) /\ - and([y_1_2_Function1DR2_Occurrence[q4, q7, 2] | 1 = q4, 1 = q7]) - /\ and([y_1_2_Function1DR2_Occurrence[q4, q7, 1] | 1 = q4, 2 = q7]) - /\ - (and([y_1_2_Function1DR2_Occurrence[q4, q7, 1] | 2 = q4, 1 = q7]) /\ - and([y_1_2_Function1DR2_Occurrence[q4, q7, 2] | 2 = q4, 1 = q7]) - /\ and([y_1_2_Function1DR2_Occurrence[q4, q7, 1] | 2 = q4, 2 = q7])) - /\ - and([y_1_2_Function1DR2_Occurrence[q4, q7, q13] -> - or([1 = q13 | 1 = q4, 1 = q7]) \/ or([2 = q13 | 1 = q4, 1 = q7]) \/ - or([1 = q13 | 1 = q4, 2 = q7]) - \/ - (or([1 = q13 | 2 = q4, 1 = q7]) \/ or([2 = q13 | 2 = q4, 1 = q7]) \/ - or([1 = q13 | 2 = q4, 2 = q7])) - | q13 : int(1, 2)]) - | q7 : int(1..3)]) - /\ - (and([and([and([y_1_2_Function1DR2_Occurrence[q4, 1, q19] -> 1 = q19 \/ 2 = q19 | q19 : int(1, 2)]) /\ - (y_1_2_Function1DR2_Occurrence[q4, 1, 1] /\ y_1_2_Function1DR2_Occurrence[q4, 1, 2]) - | 1 = q4]), - and([and([y_1_2_Function1DR2_Occurrence[q4, 2, q19] -> 1 = q19 | q19 : int(1, 2)]) /\ - y_1_2_Function1DR2_Occurrence[q4, 2, 1] - | 1 = q4]), - and([and([y_1_2_Function1DR2_Occurrence[q4, 3, q19] -> false | q19 : int(1, 2)]) | 1 = q4]); - int(1..3)]) - /\ - and([and([and([y_1_2_Function1DR2_Occurrence[q4, 1, q21] -> 1 = q21 \/ 2 = q21 | q21 : int(1, 2)]) /\ - (y_1_2_Function1DR2_Occurrence[q4, 1, 1] /\ y_1_2_Function1DR2_Occurrence[q4, 1, 2]) - | 2 = q4]), - and([and([y_1_2_Function1DR2_Occurrence[q4, 2, q21] -> 1 = q21 | q21 : int(1, 2)]) /\ - y_1_2_Function1DR2_Occurrence[q4, 2, 1] - | 2 = q4]), - and([and([y_1_2_Function1DR2_Occurrence[q4, 3, q21] -> false | q21 : int(1, 2)]) | 2 = q4]); - int(1..3)])), - y_1_3[q4] = [33, 55; int(1..2)][q4]; - int(1..3)]) - | q4 : int(1, 2)]) - diff --git a/tests/exhaustive/issues/166/expected/model_1_2-solution000001.solution b/tests/exhaustive/issues/166/expected/model_1_2-solution000001.solution new file mode 100644 index 0000000000..15cf35802e --- /dev/null +++ b/tests/exhaustive/issues/166/expected/model_1_2-solution000001.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting y be + tuple ([(10, function(1 --> {1, 2}, 2 --> {1}, 3 --> {}), 33), + (11, function(1 --> {1, 2}, 2 --> {1}, 3 --> {}), 55); + int(1..2)]) diff --git a/tests/exhaustive/issues/166/expected/model_1_2.eprime.orig b/tests/exhaustive/issues/166/expected/model_1_2.eprime.orig deleted file mode 100644 index 03fb76651e..0000000000 --- a/tests/exhaustive/issues/166/expected/model_1_2.eprime.orig +++ /dev/null @@ -1,83 +0,0 @@ -language ESSENCE' 1.0 - -find y_1_1: matrix indexed by [int(1, 2)] of int(10, 11) -find y_1_2_Function1DR2_Occurrence: matrix indexed by [int(1, 2), int(1..3), int(1, 2)] of bool -find y_1_3: matrix indexed by [int(1, 2)] of int(33, 55) -find y_1_2_Function1DR6_ExplicitVarSizeWithDummy: matrix indexed by [int(1, 2), int(1..3), int(1..2)] of int(1, 2, 3) -branching on [y_1_1, y_1_2_Function1DR6_ExplicitVarSizeWithDummy, y_1_3, y_1_2_Function1DR2_Occurrence] -such that - and([and([y_1_1[q25] = [10, 11; int(1..2)][q25], - and([and([y_1_2_Function1DR2_Occurrence[q25, q28, 1] | 1 = q25, 1 = q28]) /\ - and([y_1_2_Function1DR2_Occurrence[q25, q28, 2] | 1 = q25, 1 = q28]) - /\ and([y_1_2_Function1DR2_Occurrence[q25, q28, 1] | 1 = q25, 2 = q28]) - /\ - (and([y_1_2_Function1DR2_Occurrence[q25, q28, 1] | 2 = q25, 1 = q28]) /\ - and([y_1_2_Function1DR2_Occurrence[q25, q28, 2] | 2 = q25, 1 = q28]) - /\ and([y_1_2_Function1DR2_Occurrence[q25, q28, 1] | 2 = q25, 2 = q28])) - /\ - and([y_1_2_Function1DR2_Occurrence[q25, q28, q34] -> - or([1 = q34 | 1 = q25, 1 = q28]) \/ or([2 = q34 | 1 = q25, 1 = q28]) \/ - or([1 = q34 | 1 = q25, 2 = q28]) - \/ - (or([1 = q34 | 2 = q25, 1 = q28]) \/ or([2 = q34 | 2 = q25, 1 = q28]) \/ - or([1 = q34 | 2 = q25, 2 = q28])) - | q34 : int(1, 2)]) - | q28 : int(1..3)]) - /\ - (and([and([and([y_1_2_Function1DR2_Occurrence[q25, 1, q40] -> 1 = q40 \/ 2 = q40 | q40 : int(1, 2)]) /\ - (y_1_2_Function1DR2_Occurrence[q25, 1, 1] /\ y_1_2_Function1DR2_Occurrence[q25, 1, 2]) - | 1 = q25]), - and([and([y_1_2_Function1DR2_Occurrence[q25, 2, q40] -> 1 = q40 | q40 : int(1, 2)]) /\ - y_1_2_Function1DR2_Occurrence[q25, 2, 1] - | 1 = q25]), - and([and([y_1_2_Function1DR2_Occurrence[q25, 3, q40] -> false | q40 : int(1, 2)]) | 1 = q25]); - int(1..3)]) - /\ - and([and([and([y_1_2_Function1DR2_Occurrence[q25, 1, q42] -> 1 = q42 \/ 2 = q42 | q42 : int(1, 2)]) /\ - (y_1_2_Function1DR2_Occurrence[q25, 1, 1] /\ y_1_2_Function1DR2_Occurrence[q25, 1, 2]) - | 2 = q25]), - and([and([y_1_2_Function1DR2_Occurrence[q25, 2, q42] -> 1 = q42 | q42 : int(1, 2)]) /\ - y_1_2_Function1DR2_Occurrence[q25, 2, 1] - | 2 = q25]), - and([and([y_1_2_Function1DR2_Occurrence[q25, 3, q42] -> false | q42 : int(1, 2)]) | 2 = q25]); - int(1..3)])), - y_1_3[q25] = [33, 55; int(1..2)][q25]; - int(1..3)]) - | q25 : int(1, 2)]), - and([and([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q4, q5, 1] < - y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q4, q5, 2] - \/ y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q4, q5, 1] = 3 - | q5 : int(1..3)]) - | q4 : int(1, 2)]), - and([and([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q4, q5, 1] = 3 -> - y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q4, q5, 2] = 3 - | q5 : int(1..3)]) - | q4 : int(1, 2)]), - and([and([y_1_1[q10] = y_1_1[q10], - and([and([y_1_2_Function1DR2_Occurrence[q10, q13, q14] -> - or([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q10, q13, q16] != 3 /\ - y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q10, q13, q16] = q14 - | q16 : int(1..2)]) - | q14 : int(1, 2)]) - /\ - and([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q10, q13, q18] != 3 -> - y_1_2_Function1DR2_Occurrence - [q10, q13, y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q10, q13, q18]] - | q18 : int(1..2)]) - | q13 : int(1..3)]) - /\ - and([and([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q10, q19, q21] != 3 -> - y_1_2_Function1DR2_Occurrence - [q10, q19, y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q10, q19, q21]] - | q21 : int(1..2)]) - /\ - and([y_1_2_Function1DR2_Occurrence[q10, q19, q22] -> - or([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q10, q19, q24] != 3 /\ - y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q10, q19, q24] = q22 - | q24 : int(1..2)]) - | q22 : int(1, 2)]) - | q19 : int(1..3)]), - y_1_3[q10] = y_1_3[q10]; - int(1..3)]) - | q10 : int(1, 2)]) - diff --git a/tests/exhaustive/issues/166/expected/model_1_3-solution000001.solution b/tests/exhaustive/issues/166/expected/model_1_3-solution000001.solution new file mode 100644 index 0000000000..15cf35802e --- /dev/null +++ b/tests/exhaustive/issues/166/expected/model_1_3-solution000001.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting y be + tuple ([(10, function(1 --> {1, 2}, 2 --> {1}, 3 --> {}), 33), + (11, function(1 --> {1, 2}, 2 --> {1}, 3 --> {}), 55); + int(1..2)]) diff --git a/tests/exhaustive/issues/166/expected/model_1_3.eprime.orig b/tests/exhaustive/issues/166/expected/model_1_3.eprime.orig deleted file mode 100644 index f7d0ce6fe6..0000000000 --- a/tests/exhaustive/issues/166/expected/model_1_3.eprime.orig +++ /dev/null @@ -1,88 +0,0 @@ -language ESSENCE' 1.0 - -find y_1_1: matrix indexed by [int(1, 2)] of int(10, 11) -find y_1_2_Function1DR2_Occurrence: matrix indexed by [int(1, 2), int(1..3), int(1, 2)] of bool -find y_1_3: matrix indexed by [int(1, 2)] of int(33, 55) -find y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker: matrix indexed by [int(1, 2), int(1..3)] of int(0..2) -find y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values: - matrix indexed by [int(1, 2), int(1..3), int(1..2)] of int(1, 2) -branching on - [y_1_1, y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker, y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values, - y_1_3, y_1_2_Function1DR2_Occurrence] -such that - and([and([y_1_1[q24] = [10, 11; int(1..2)][q24], - and([and([y_1_2_Function1DR2_Occurrence[q24, q27, 1] | 1 = q24, 1 = q27]) /\ - and([y_1_2_Function1DR2_Occurrence[q24, q27, 2] | 1 = q24, 1 = q27]) - /\ and([y_1_2_Function1DR2_Occurrence[q24, q27, 1] | 1 = q24, 2 = q27]) - /\ - (and([y_1_2_Function1DR2_Occurrence[q24, q27, 1] | 2 = q24, 1 = q27]) /\ - and([y_1_2_Function1DR2_Occurrence[q24, q27, 2] | 2 = q24, 1 = q27]) - /\ and([y_1_2_Function1DR2_Occurrence[q24, q27, 1] | 2 = q24, 2 = q27])) - /\ - and([y_1_2_Function1DR2_Occurrence[q24, q27, q33] -> - or([1 = q33 | 1 = q24, 1 = q27]) \/ or([2 = q33 | 1 = q24, 1 = q27]) \/ - or([1 = q33 | 1 = q24, 2 = q27]) - \/ - (or([1 = q33 | 2 = q24, 1 = q27]) \/ or([2 = q33 | 2 = q24, 1 = q27]) \/ - or([1 = q33 | 2 = q24, 2 = q27])) - | q33 : int(1, 2)]) - | q27 : int(1..3)]) - /\ - (and([and([and([y_1_2_Function1DR2_Occurrence[q24, 1, q39] -> 1 = q39 \/ 2 = q39 | q39 : int(1, 2)]) /\ - (y_1_2_Function1DR2_Occurrence[q24, 1, 1] /\ y_1_2_Function1DR2_Occurrence[q24, 1, 2]) - | 1 = q24]), - and([and([y_1_2_Function1DR2_Occurrence[q24, 2, q39] -> 1 = q39 | q39 : int(1, 2)]) /\ - y_1_2_Function1DR2_Occurrence[q24, 2, 1] - | 1 = q24]), - and([and([y_1_2_Function1DR2_Occurrence[q24, 3, q39] -> false | q39 : int(1, 2)]) | 1 = q24]); - int(1..3)]) - /\ - and([and([and([y_1_2_Function1DR2_Occurrence[q24, 1, q41] -> 1 = q41 \/ 2 = q41 | q41 : int(1, 2)]) /\ - (y_1_2_Function1DR2_Occurrence[q24, 1, 1] /\ y_1_2_Function1DR2_Occurrence[q24, 1, 2]) - | 2 = q24]), - and([and([y_1_2_Function1DR2_Occurrence[q24, 2, q41] -> 1 = q41 | q41 : int(1, 2)]) /\ - y_1_2_Function1DR2_Occurrence[q24, 2, 1] - | 2 = q24]), - and([and([y_1_2_Function1DR2_Occurrence[q24, 3, q41] -> false | q41 : int(1, 2)]) | 2 = q24]); - int(1..3)])), - y_1_3[q24] = [33, 55; int(1..2)][q24]; - int(1..3)]) - | q24 : int(1, 2)]), - and([and([2 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q4, q5] -> - y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q4, q5, 1] < - y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q4, q5, 2] - | q5 : int(1..3)]) - | q4 : int(1, 2)]), - and([and([and([q7 > y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q4, q5] -> - y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q4, q5, q7] = 1 - | q7 : int(1..2)]) - | q5 : int(1..3)]) - | q4 : int(1, 2)]), - and([and([y_1_1[q9] = y_1_1[q9], - and([and([y_1_2_Function1DR2_Occurrence[q9, q12, q13] -> - or([q15 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q9, q12] /\ - y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q9, q12, q15] = q13 - | q15 : int(1..2)]) - | q13 : int(1, 2)]) - /\ - and([q17 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q9, q12] -> - y_1_2_Function1DR2_Occurrence - [q9, q12, y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q9, q12, q17]] - | q17 : int(1..2)]) - | q12 : int(1..3)]) - /\ - and([and([q20 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q9, q18] -> - y_1_2_Function1DR2_Occurrence - [q9, q18, y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q9, q18, q20]] - | q20 : int(1..2)]) - /\ - and([y_1_2_Function1DR2_Occurrence[q9, q18, q21] -> - or([q23 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q9, q18] /\ - y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q9, q18, q23] = q21 - | q23 : int(1..2)]) - | q21 : int(1, 2)]) - | q18 : int(1..3)]), - y_1_3[q9] = y_1_3[q9]; - int(1..3)]) - | q9 : int(1, 2)]) - diff --git a/tests/exhaustive/issues/166/expected/model_1_4-solution000001.solution b/tests/exhaustive/issues/166/expected/model_1_4-solution000001.solution new file mode 100644 index 0000000000..15cf35802e --- /dev/null +++ b/tests/exhaustive/issues/166/expected/model_1_4-solution000001.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting y be + tuple ([(10, function(1 --> {1, 2}, 2 --> {1}, 3 --> {}), 33), + (11, function(1 --> {1, 2}, 2 --> {1}, 3 --> {}), 55); + int(1..2)]) diff --git a/tests/exhaustive/issues/166/expected/model_1_4.eprime.orig b/tests/exhaustive/issues/166/expected/model_1_4.eprime.orig deleted file mode 100644 index 4e9afcbfc1..0000000000 --- a/tests/exhaustive/issues/166/expected/model_1_4.eprime.orig +++ /dev/null @@ -1,92 +0,0 @@ -language ESSENCE' 1.0 - -find y_1_1: matrix indexed by [int(1, 2)] of int(10, 11) -find y_1_2_Function1DR2_Occurrence: matrix indexed by [int(1, 2), int(1..3), int(1, 2)] of bool -find y_1_3: matrix indexed by [int(1, 2)] of int(33, 55) -find y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1, 2), int(1..3), int(1..2)] of bool -find y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values: - matrix indexed by [int(1, 2), int(1..3), int(1..2)] of int(1, 2) -branching on - [y_1_1, y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags, y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values, - y_1_3, y_1_2_Function1DR2_Occurrence] -such that - and([and([y_1_1[q26] = [10, 11; int(1..2)][q26], - and([and([y_1_2_Function1DR2_Occurrence[q26, q29, 1] | 1 = q26, 1 = q29]) /\ - and([y_1_2_Function1DR2_Occurrence[q26, q29, 2] | 1 = q26, 1 = q29]) - /\ and([y_1_2_Function1DR2_Occurrence[q26, q29, 1] | 1 = q26, 2 = q29]) - /\ - (and([y_1_2_Function1DR2_Occurrence[q26, q29, 1] | 2 = q26, 1 = q29]) /\ - and([y_1_2_Function1DR2_Occurrence[q26, q29, 2] | 2 = q26, 1 = q29]) - /\ and([y_1_2_Function1DR2_Occurrence[q26, q29, 1] | 2 = q26, 2 = q29])) - /\ - and([y_1_2_Function1DR2_Occurrence[q26, q29, q35] -> - or([1 = q35 | 1 = q26, 1 = q29]) \/ or([2 = q35 | 1 = q26, 1 = q29]) \/ - or([1 = q35 | 1 = q26, 2 = q29]) - \/ - (or([1 = q35 | 2 = q26, 1 = q29]) \/ or([2 = q35 | 2 = q26, 1 = q29]) \/ - or([1 = q35 | 2 = q26, 2 = q29])) - | q35 : int(1, 2)]) - | q29 : int(1..3)]) - /\ - (and([and([and([y_1_2_Function1DR2_Occurrence[q26, 1, q41] -> 1 = q41 \/ 2 = q41 | q41 : int(1, 2)]) /\ - (y_1_2_Function1DR2_Occurrence[q26, 1, 1] /\ y_1_2_Function1DR2_Occurrence[q26, 1, 2]) - | 1 = q26]), - and([and([y_1_2_Function1DR2_Occurrence[q26, 2, q41] -> 1 = q41 | q41 : int(1, 2)]) /\ - y_1_2_Function1DR2_Occurrence[q26, 2, 1] - | 1 = q26]), - and([and([y_1_2_Function1DR2_Occurrence[q26, 3, q41] -> false | q41 : int(1, 2)]) | 1 = q26]); - int(1..3)]) - /\ - and([and([and([y_1_2_Function1DR2_Occurrence[q26, 1, q43] -> 1 = q43 \/ 2 = q43 | q43 : int(1, 2)]) /\ - (y_1_2_Function1DR2_Occurrence[q26, 1, 1] /\ y_1_2_Function1DR2_Occurrence[q26, 1, 2]) - | 2 = q26]), - and([and([y_1_2_Function1DR2_Occurrence[q26, 2, q43] -> 1 = q43 | q43 : int(1, 2)]) /\ - y_1_2_Function1DR2_Occurrence[q26, 2, 1] - | 2 = q26]), - and([and([y_1_2_Function1DR2_Occurrence[q26, 3, q43] -> false | q43 : int(1, 2)]) | 2 = q26]); - int(1..3)])), - y_1_3[q26] = [33, 55; int(1..2)][q26]; - int(1..3)]) - | q26 : int(1, 2)]), - and([and([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q4, q5, 2] -> - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q4, q5, 1] < - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q4, q5, 2] - | q5 : int(1..3)]) - | q4 : int(1, 2)]), - and([and([and([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q4, q5, q7] = false -> - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q4, q5, q7] = 1 - | q7 : int(1..2)]) - | q5 : int(1..3)]) - | q4 : int(1, 2)]), - and([and([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q4, q5, 2] -> - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q4, q5, 1] - | q5 : int(1..3)]) - | q4 : int(1, 2)]), - and([and([y_1_1[q11] = y_1_1[q11], - and([and([y_1_2_Function1DR2_Occurrence[q11, q14, q15] -> - or([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q11, q14, q17] /\ - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q11, q14, q17] = q15 - | q17 : int(1..2)]) - | q15 : int(1, 2)]) - /\ - and([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q11, q14, q19] -> - y_1_2_Function1DR2_Occurrence - [q11, q14, y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q11, q14, q19]] - | q19 : int(1..2)]) - | q14 : int(1..3)]) - /\ - and([and([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q11, q20, q22] -> - y_1_2_Function1DR2_Occurrence - [q11, q20, y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q11, q20, q22]] - | q22 : int(1..2)]) - /\ - and([y_1_2_Function1DR2_Occurrence[q11, q20, q23] -> - or([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q11, q20, q25] /\ - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q11, q20, q25] = q23 - | q25 : int(1..2)]) - | q23 : int(1, 2)]) - | q20 : int(1..3)]), - y_1_3[q11] = y_1_3[q11]; - int(1..3)]) - | q11 : int(1, 2)]) - diff --git a/tests/exhaustive/issues/166/expected/model_2_1-solution000001.solution b/tests/exhaustive/issues/166/expected/model_2_1-solution000001.solution new file mode 100644 index 0000000000..15cf35802e --- /dev/null +++ b/tests/exhaustive/issues/166/expected/model_2_1-solution000001.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting y be + tuple ([(10, function(1 --> {1, 2}, 2 --> {1}, 3 --> {}), 33), + (11, function(1 --> {1, 2}, 2 --> {1}, 3 --> {}), 55); + int(1..2)]) diff --git a/tests/exhaustive/issues/166/expected/model_2_1.eprime.orig b/tests/exhaustive/issues/166/expected/model_2_1.eprime.orig deleted file mode 100644 index 48f869f112..0000000000 --- a/tests/exhaustive/issues/166/expected/model_2_1.eprime.orig +++ /dev/null @@ -1,139 +0,0 @@ -language ESSENCE' 1.0 - -find y_1_1: matrix indexed by [int(1, 2)] of int(10, 11) -find y_1_2_Function1DR6_ExplicitVarSizeWithDummy: matrix indexed by [int(1, 2), int(1..3), int(1..2)] of int(1, 2, 3) -find y_1_3: matrix indexed by [int(1, 2)] of int(33, 55) -find y_1_2_Function1DR2_Occurrence: matrix indexed by [int(1, 2), int(1..3), int(1, 2)] of bool -branching on [y_1_1, y_1_2_Function1DR2_Occurrence, y_1_3, y_1_2_Function1DR6_ExplicitVarSizeWithDummy] -such that - and([and([y_1_1[q10] = [10, 11; int(1..2)][q10], - and([and([or([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q10, q13, q19] != 3 /\ - y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q10, q13, q19] = 1 - | q19 : int(1..2)]) - | 1 = q10, 1 = q13]) - /\ - and([or([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q10, q13, q21] != 3 /\ - y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q10, q13, q21] = 2 - | q21 : int(1..2)]) - | 1 = q10, 1 = q13]) - /\ - and([or([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q10, q13, q23] != 3 /\ - y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q10, q13, q23] = 1 - | q23 : int(1..2)]) - | 1 = q10, 2 = q13]) - /\ - (and([or([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q10, q13, q26] != 3 /\ - y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q10, q13, q26] = 1 - | q26 : int(1..2)]) - | 2 = q10, 1 = q13]) - /\ - and([or([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q10, q13, q28] != 3 /\ - y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q10, q13, q28] = 2 - | q28 : int(1..2)]) - | 2 = q10, 1 = q13]) - /\ - and([or([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q10, q13, q30] != 3 /\ - y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q10, q13, q30] = 1 - | q30 : int(1..2)]) - | 2 = q10, 2 = q13])) - /\ - and([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q10, q13, q32] != 3 -> - or([1 = y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q10, q13, q32] | 1 = q10, 1 = q13]) \/ - or([2 = y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q10, q13, q32] | 1 = q10, 1 = q13]) - \/ or([1 = y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q10, q13, q32] | 1 = q10, 2 = q13]) - \/ - (or([1 = y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q10, q13, q32] | 2 = q10, 1 = q13]) \/ - or([2 = y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q10, q13, q32] | 2 = q10, 1 = q13]) - \/ or([1 = y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q10, q13, q32] | 2 = q10, 2 = q13])) - | q32 : int(1..2)]) - | q13 : int(1..3)]) - /\ - (and([and([and([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q10, 1, q39] != 3 -> - 1 = y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q10, 1, q39] \/ - 2 = y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q10, 1, q39] - | q39 : int(1..2)]) - /\ - (or([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q10, 1, q42] != 3 /\ - y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q10, 1, q42] = 1 - | q42 : int(1..2)]) - /\ - or([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q10, 1, q42] != 3 /\ - y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q10, 1, q42] = 2 - | q42 : int(1..2)])) - | 1 = q10]), - and([and([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q10, 2, q39] != 3 -> - 1 = y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q10, 2, q39] - | q39 : int(1..2)]) - /\ - or([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q10, 2, q42] != 3 /\ - y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q10, 2, q42] = 1 - | q42 : int(1..2)]) - | 1 = q10]), - and([and([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q10, 3, q39] != 3 -> false | q39 : int(1..2)]) - | 1 = q10]); - int(1..3)]) - /\ - and([and([and([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q10, 1, q44] != 3 -> - 1 = y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q10, 1, q44] \/ - 2 = y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q10, 1, q44] - | q44 : int(1..2)]) - /\ - (or([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q10, 1, q47] != 3 /\ - y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q10, 1, q47] = 1 - | q47 : int(1..2)]) - /\ - or([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q10, 1, q47] != 3 /\ - y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q10, 1, q47] = 2 - | q47 : int(1..2)])) - | 2 = q10]), - and([and([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q10, 2, q44] != 3 -> - 1 = y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q10, 2, q44] - | q44 : int(1..2)]) - /\ - or([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q10, 2, q47] != 3 /\ - y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q10, 2, q47] = 1 - | q47 : int(1..2)]) - | 2 = q10]), - and([and([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q10, 3, q44] != 3 -> false | q44 : int(1..2)]) - | 2 = q10]); - int(1..3)])), - y_1_3[q10] = [33, 55; int(1..2)][q10]; - int(1..3)]) - | q10 : int(1, 2)]), - and([and([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q1, q2, 1] < - y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q1, q2, 2] - \/ y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q1, q2, 1] = 3 - | q2 : int(1..3)]) - | q1 : int(1, 2)]), - and([and([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q1, q2, 1] = 3 -> - y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q1, q2, 2] = 3 - | q2 : int(1..3)]) - | q1 : int(1, 2)]), - and([and([y_1_1[q56] = y_1_1[q56], - and([and([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q56, q59, q61] != 3 -> - y_1_2_Function1DR2_Occurrence - [q56, q59, y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q56, q59, q61]] - | q61 : int(1..2)]) - /\ - and([y_1_2_Function1DR2_Occurrence[q56, q59, q62] -> - or([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q56, q59, q64] != 3 /\ - y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q56, q59, q64] = q62 - | q64 : int(1..2)]) - | q62 : int(1, 2)]) - | q59 : int(1..3)]) - /\ - and([and([y_1_2_Function1DR2_Occurrence[q56, q65, q66] -> - or([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q56, q65, q68] != 3 /\ - y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q56, q65, q68] = q66 - | q68 : int(1..2)]) - | q66 : int(1, 2)]) - /\ - and([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q56, q65, q70] != 3 -> - y_1_2_Function1DR2_Occurrence - [q56, q65, y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q56, q65, q70]] - | q70 : int(1..2)]) - | q65 : int(1..3)]), - y_1_3[q56] = y_1_3[q56]; - int(1..3)]) - | q56 : int(1, 2)]) - diff --git a/tests/exhaustive/issues/166/expected/model_2_2-solution000001.solution b/tests/exhaustive/issues/166/expected/model_2_2-solution000001.solution new file mode 100644 index 0000000000..15cf35802e --- /dev/null +++ b/tests/exhaustive/issues/166/expected/model_2_2-solution000001.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting y be + tuple ([(10, function(1 --> {1, 2}, 2 --> {1}, 3 --> {}), 33), + (11, function(1 --> {1, 2}, 2 --> {1}, 3 --> {}), 55); + int(1..2)]) diff --git a/tests/exhaustive/issues/166/expected/model_2_2.eprime.orig b/tests/exhaustive/issues/166/expected/model_2_2.eprime.orig deleted file mode 100644 index 882d24f70f..0000000000 --- a/tests/exhaustive/issues/166/expected/model_2_2.eprime.orig +++ /dev/null @@ -1,111 +0,0 @@ -language ESSENCE' 1.0 - -find y_1_1: matrix indexed by [int(1, 2)] of int(10, 11) -find y_1_2_Function1DR6_ExplicitVarSizeWithDummy: matrix indexed by [int(1, 2), int(1..3), int(1..2)] of int(1, 2, 3) -find y_1_3: matrix indexed by [int(1, 2)] of int(33, 55) -branching on [y_1_1, y_1_2_Function1DR6_ExplicitVarSizeWithDummy, y_1_3] -such that - and([and([y_1_1[q7] = [10, 11; int(1..2)][q7], - and([and([or([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q7, q10, q16] != 3 /\ - y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q7, q10, q16] = 1 - | q16 : int(1..2)]) - | 1 = q7, 1 = q10]) - /\ - and([or([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q7, q10, q18] != 3 /\ - y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q7, q10, q18] = 2 - | q18 : int(1..2)]) - | 1 = q7, 1 = q10]) - /\ - and([or([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q7, q10, q20] != 3 /\ - y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q7, q10, q20] = 1 - | q20 : int(1..2)]) - | 1 = q7, 2 = q10]) - /\ - (and([or([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q7, q10, q23] != 3 /\ - y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q7, q10, q23] = 1 - | q23 : int(1..2)]) - | 2 = q7, 1 = q10]) - /\ - and([or([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q7, q10, q25] != 3 /\ - y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q7, q10, q25] = 2 - | q25 : int(1..2)]) - | 2 = q7, 1 = q10]) - /\ - and([or([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q7, q10, q27] != 3 /\ - y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q7, q10, q27] = 1 - | q27 : int(1..2)]) - | 2 = q7, 2 = q10])) - /\ - and([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q7, q10, q29] != 3 -> - or([1 = y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q7, q10, q29] | 1 = q7, 1 = q10]) \/ - or([2 = y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q7, q10, q29] | 1 = q7, 1 = q10]) - \/ or([1 = y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q7, q10, q29] | 1 = q7, 2 = q10]) - \/ - (or([1 = y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q7, q10, q29] | 2 = q7, 1 = q10]) \/ - or([2 = y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q7, q10, q29] | 2 = q7, 1 = q10]) - \/ or([1 = y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q7, q10, q29] | 2 = q7, 2 = q10])) - | q29 : int(1..2)]) - | q10 : int(1..3)]) - /\ - (and([and([and([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q7, 1, q36] != 3 -> - 1 = y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q7, 1, q36] \/ - 2 = y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q7, 1, q36] - | q36 : int(1..2)]) - /\ - (or([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q7, 1, q39] != 3 /\ - y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q7, 1, q39] = 1 - | q39 : int(1..2)]) - /\ - or([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q7, 1, q39] != 3 /\ - y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q7, 1, q39] = 2 - | q39 : int(1..2)])) - | 1 = q7]), - and([and([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q7, 2, q36] != 3 -> - 1 = y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q7, 2, q36] - | q36 : int(1..2)]) - /\ - or([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q7, 2, q39] != 3 /\ - y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q7, 2, q39] = 1 - | q39 : int(1..2)]) - | 1 = q7]), - and([and([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q7, 3, q36] != 3 -> false | q36 : int(1..2)]) - | 1 = q7]); - int(1..3)]) - /\ - and([and([and([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q7, 1, q41] != 3 -> - 1 = y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q7, 1, q41] \/ - 2 = y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q7, 1, q41] - | q41 : int(1..2)]) - /\ - (or([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q7, 1, q44] != 3 /\ - y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q7, 1, q44] = 1 - | q44 : int(1..2)]) - /\ - or([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q7, 1, q44] != 3 /\ - y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q7, 1, q44] = 2 - | q44 : int(1..2)])) - | 2 = q7]), - and([and([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q7, 2, q41] != 3 -> - 1 = y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q7, 2, q41] - | q41 : int(1..2)]) - /\ - or([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q7, 2, q44] != 3 /\ - y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q7, 2, q44] = 1 - | q44 : int(1..2)]) - | 2 = q7]), - and([and([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q7, 3, q41] != 3 -> false | q41 : int(1..2)]) - | 2 = q7]); - int(1..3)])), - y_1_3[q7] = [33, 55; int(1..2)][q7]; - int(1..3)]) - | q7 : int(1, 2)]), - and([and([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q1, q2, 1] < - y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q1, q2, 2] - \/ y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q1, q2, 1] = 3 - | q2 : int(1..3)]) - | q1 : int(1, 2)]), - and([and([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q1, q2, 1] = 3 -> - y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q1, q2, 2] = 3 - | q2 : int(1..3)]) - | q1 : int(1, 2)]) - diff --git a/tests/exhaustive/issues/166/expected/model_2_3-solution000001.solution b/tests/exhaustive/issues/166/expected/model_2_3-solution000001.solution new file mode 100644 index 0000000000..15cf35802e --- /dev/null +++ b/tests/exhaustive/issues/166/expected/model_2_3-solution000001.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting y be + tuple ([(10, function(1 --> {1, 2}, 2 --> {1}, 3 --> {}), 33), + (11, function(1 --> {1, 2}, 2 --> {1}, 3 --> {}), 55); + int(1..2)]) diff --git a/tests/exhaustive/issues/166/expected/model_2_3.eprime.orig b/tests/exhaustive/issues/166/expected/model_2_3.eprime.orig deleted file mode 100644 index fc24bf17b7..0000000000 --- a/tests/exhaustive/issues/166/expected/model_2_3.eprime.orig +++ /dev/null @@ -1,159 +0,0 @@ -language ESSENCE' 1.0 - -find y_1_1: matrix indexed by [int(1, 2)] of int(10, 11) -find y_1_2_Function1DR6_ExplicitVarSizeWithDummy: matrix indexed by [int(1, 2), int(1..3), int(1..2)] of int(1, 2, 3) -find y_1_3: matrix indexed by [int(1, 2)] of int(33, 55) -find y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker: matrix indexed by [int(1, 2), int(1..3)] of int(0..2) -find y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values: - matrix indexed by [int(1, 2), int(1..3), int(1..2)] of int(1, 2) -branching on - [y_1_1, y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker, y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values, - y_1_3, y_1_2_Function1DR6_ExplicitVarSizeWithDummy] -such that - and([and([y_1_1[q33] = [10, 11; int(1..2)][q33], - and([and([or([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q33, q36, q42] != 3 /\ - y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q33, q36, q42] = 1 - | q42 : int(1..2)]) - | 1 = q33, 1 = q36]) - /\ - and([or([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q33, q36, q44] != 3 /\ - y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q33, q36, q44] = 2 - | q44 : int(1..2)]) - | 1 = q33, 1 = q36]) - /\ - and([or([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q33, q36, q46] != 3 /\ - y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q33, q36, q46] = 1 - | q46 : int(1..2)]) - | 1 = q33, 2 = q36]) - /\ - (and([or([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q33, q36, q49] != 3 /\ - y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q33, q36, q49] = 1 - | q49 : int(1..2)]) - | 2 = q33, 1 = q36]) - /\ - and([or([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q33, q36, q51] != 3 /\ - y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q33, q36, q51] = 2 - | q51 : int(1..2)]) - | 2 = q33, 1 = q36]) - /\ - and([or([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q33, q36, q53] != 3 /\ - y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q33, q36, q53] = 1 - | q53 : int(1..2)]) - | 2 = q33, 2 = q36])) - /\ - and([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q33, q36, q55] != 3 -> - or([1 = y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q33, q36, q55] | 1 = q33, 1 = q36]) \/ - or([2 = y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q33, q36, q55] | 1 = q33, 1 = q36]) - \/ or([1 = y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q33, q36, q55] | 1 = q33, 2 = q36]) - \/ - (or([1 = y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q33, q36, q55] | 2 = q33, 1 = q36]) \/ - or([2 = y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q33, q36, q55] | 2 = q33, 1 = q36]) - \/ or([1 = y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q33, q36, q55] | 2 = q33, 2 = q36])) - | q55 : int(1..2)]) - | q36 : int(1..3)]) - /\ - (and([and([and([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q33, 1, q62] != 3 -> - 1 = y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q33, 1, q62] \/ - 2 = y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q33, 1, q62] - | q62 : int(1..2)]) - /\ - (or([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q33, 1, q65] != 3 /\ - y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q33, 1, q65] = 1 - | q65 : int(1..2)]) - /\ - or([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q33, 1, q65] != 3 /\ - y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q33, 1, q65] = 2 - | q65 : int(1..2)])) - | 1 = q33]), - and([and([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q33, 2, q62] != 3 -> - 1 = y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q33, 2, q62] - | q62 : int(1..2)]) - /\ - or([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q33, 2, q65] != 3 /\ - y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q33, 2, q65] = 1 - | q65 : int(1..2)]) - | 1 = q33]), - and([and([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q33, 3, q62] != 3 -> false | q62 : int(1..2)]) - | 1 = q33]); - int(1..3)]) - /\ - and([and([and([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q33, 1, q67] != 3 -> - 1 = y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q33, 1, q67] \/ - 2 = y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q33, 1, q67] - | q67 : int(1..2)]) - /\ - (or([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q33, 1, q70] != 3 /\ - y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q33, 1, q70] = 1 - | q70 : int(1..2)]) - /\ - or([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q33, 1, q70] != 3 /\ - y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q33, 1, q70] = 2 - | q70 : int(1..2)])) - | 2 = q33]), - and([and([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q33, 2, q67] != 3 -> - 1 = y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q33, 2, q67] - | q67 : int(1..2)]) - /\ - or([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q33, 2, q70] != 3 /\ - y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q33, 2, q70] = 1 - | q70 : int(1..2)]) - | 2 = q33]), - and([and([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q33, 3, q67] != 3 -> false | q67 : int(1..2)]) - | 2 = q33]); - int(1..3)])), - y_1_3[q33] = [33, 55; int(1..2)][q33]; - int(1..3)]) - | q33 : int(1, 2)]), - and([and([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q1, q2, 1] < - y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q1, q2, 2] - \/ y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q1, q2, 1] = 3 - | q2 : int(1..3)]) - | q1 : int(1, 2)]), - and([and([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q1, q2, 1] = 3 -> - y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q1, q2, 2] = 3 - | q2 : int(1..3)]) - | q1 : int(1, 2)]), - and([and([2 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q7, q8] -> - y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q7, q8, 1] < - y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q7, q8, 2] - | q8 : int(1..3)]) - | q7 : int(1, 2)]), - and([and([and([q10 > y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q7, q8] -> - y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q7, q8, q10] = 1 - | q10 : int(1..2)]) - | q8 : int(1..3)]) - | q7 : int(1, 2)]), - and([and([y_1_1[q12] = y_1_1[q12], - and([and([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q12, q15, q17] != 3 -> - or([q19 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q12, q15] /\ - y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q12, q15, q19] = - y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q12, q15, q17] - | q19 : int(1..2)]) - | q17 : int(1..2)]) - /\ - and([q21 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q12, q15] -> - or([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q12, q15, q23] != 3 /\ - y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q12, q15, q23] = - y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q12, q15, q21] - | q23 : int(1..2)]) - | q21 : int(1..2)]) - | q15 : int(1..3)]) - /\ - and([and([q26 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q12, q24] -> - or([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q12, q24, q28] != 3 /\ - y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q12, q24, q28] = - y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q12, q24, q26] - | q28 : int(1..2)]) - | q26 : int(1..2)]) - /\ - and([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q12, q24, q30] != 3 -> - or([q32 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q12, q24] /\ - y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q12, q24, q32] = - y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q12, q24, q30] - | q32 : int(1..2)]) - | q30 : int(1..2)]) - | q24 : int(1..3)]), - y_1_3[q12] = y_1_3[q12]; - int(1..3)]) - | q12 : int(1, 2)]) - diff --git a/tests/exhaustive/issues/166/expected/model_2_4-solution000001.solution b/tests/exhaustive/issues/166/expected/model_2_4-solution000001.solution new file mode 100644 index 0000000000..15cf35802e --- /dev/null +++ b/tests/exhaustive/issues/166/expected/model_2_4-solution000001.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting y be + tuple ([(10, function(1 --> {1, 2}, 2 --> {1}, 3 --> {}), 33), + (11, function(1 --> {1, 2}, 2 --> {1}, 3 --> {}), 55); + int(1..2)]) diff --git a/tests/exhaustive/issues/166/expected/model_2_4.eprime.orig b/tests/exhaustive/issues/166/expected/model_2_4.eprime.orig deleted file mode 100644 index abe826fdd7..0000000000 --- a/tests/exhaustive/issues/166/expected/model_2_4.eprime.orig +++ /dev/null @@ -1,163 +0,0 @@ -language ESSENCE' 1.0 - -find y_1_1: matrix indexed by [int(1, 2)] of int(10, 11) -find y_1_2_Function1DR6_ExplicitVarSizeWithDummy: matrix indexed by [int(1, 2), int(1..3), int(1..2)] of int(1, 2, 3) -find y_1_3: matrix indexed by [int(1, 2)] of int(33, 55) -find y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1, 2), int(1..3), int(1..2)] of bool -find y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values: - matrix indexed by [int(1, 2), int(1..3), int(1..2)] of int(1, 2) -branching on - [y_1_1, y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags, y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values, - y_1_3, y_1_2_Function1DR6_ExplicitVarSizeWithDummy] -such that - and([and([y_1_1[q35] = [10, 11; int(1..2)][q35], - and([and([or([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q35, q38, q44] != 3 /\ - y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q35, q38, q44] = 1 - | q44 : int(1..2)]) - | 1 = q35, 1 = q38]) - /\ - and([or([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q35, q38, q46] != 3 /\ - y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q35, q38, q46] = 2 - | q46 : int(1..2)]) - | 1 = q35, 1 = q38]) - /\ - and([or([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q35, q38, q48] != 3 /\ - y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q35, q38, q48] = 1 - | q48 : int(1..2)]) - | 1 = q35, 2 = q38]) - /\ - (and([or([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q35, q38, q51] != 3 /\ - y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q35, q38, q51] = 1 - | q51 : int(1..2)]) - | 2 = q35, 1 = q38]) - /\ - and([or([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q35, q38, q53] != 3 /\ - y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q35, q38, q53] = 2 - | q53 : int(1..2)]) - | 2 = q35, 1 = q38]) - /\ - and([or([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q35, q38, q55] != 3 /\ - y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q35, q38, q55] = 1 - | q55 : int(1..2)]) - | 2 = q35, 2 = q38])) - /\ - and([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q35, q38, q57] != 3 -> - or([1 = y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q35, q38, q57] | 1 = q35, 1 = q38]) \/ - or([2 = y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q35, q38, q57] | 1 = q35, 1 = q38]) - \/ or([1 = y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q35, q38, q57] | 1 = q35, 2 = q38]) - \/ - (or([1 = y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q35, q38, q57] | 2 = q35, 1 = q38]) \/ - or([2 = y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q35, q38, q57] | 2 = q35, 1 = q38]) - \/ or([1 = y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q35, q38, q57] | 2 = q35, 2 = q38])) - | q57 : int(1..2)]) - | q38 : int(1..3)]) - /\ - (and([and([and([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q35, 1, q64] != 3 -> - 1 = y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q35, 1, q64] \/ - 2 = y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q35, 1, q64] - | q64 : int(1..2)]) - /\ - (or([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q35, 1, q67] != 3 /\ - y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q35, 1, q67] = 1 - | q67 : int(1..2)]) - /\ - or([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q35, 1, q67] != 3 /\ - y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q35, 1, q67] = 2 - | q67 : int(1..2)])) - | 1 = q35]), - and([and([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q35, 2, q64] != 3 -> - 1 = y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q35, 2, q64] - | q64 : int(1..2)]) - /\ - or([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q35, 2, q67] != 3 /\ - y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q35, 2, q67] = 1 - | q67 : int(1..2)]) - | 1 = q35]), - and([and([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q35, 3, q64] != 3 -> false | q64 : int(1..2)]) - | 1 = q35]); - int(1..3)]) - /\ - and([and([and([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q35, 1, q69] != 3 -> - 1 = y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q35, 1, q69] \/ - 2 = y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q35, 1, q69] - | q69 : int(1..2)]) - /\ - (or([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q35, 1, q72] != 3 /\ - y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q35, 1, q72] = 1 - | q72 : int(1..2)]) - /\ - or([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q35, 1, q72] != 3 /\ - y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q35, 1, q72] = 2 - | q72 : int(1..2)])) - | 2 = q35]), - and([and([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q35, 2, q69] != 3 -> - 1 = y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q35, 2, q69] - | q69 : int(1..2)]) - /\ - or([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q35, 2, q72] != 3 /\ - y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q35, 2, q72] = 1 - | q72 : int(1..2)]) - | 2 = q35]), - and([and([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q35, 3, q69] != 3 -> false | q69 : int(1..2)]) - | 2 = q35]); - int(1..3)])), - y_1_3[q35] = [33, 55; int(1..2)][q35]; - int(1..3)]) - | q35 : int(1, 2)]), - and([and([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q1, q2, 1] < - y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q1, q2, 2] - \/ y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q1, q2, 1] = 3 - | q2 : int(1..3)]) - | q1 : int(1, 2)]), - and([and([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q1, q2, 1] = 3 -> - y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q1, q2, 2] = 3 - | q2 : int(1..3)]) - | q1 : int(1, 2)]), - and([and([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q7, q8, 2] -> - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q7, q8, 1] < - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q7, q8, 2] - | q8 : int(1..3)]) - | q7 : int(1, 2)]), - and([and([and([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q7, q8, q10] = false -> - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q7, q8, q10] = 1 - | q10 : int(1..2)]) - | q8 : int(1..3)]) - | q7 : int(1, 2)]), - and([and([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q7, q8, 2] -> - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q7, q8, 1] - | q8 : int(1..3)]) - | q7 : int(1, 2)]), - and([and([y_1_1[q14] = y_1_1[q14], - and([and([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q14, q17, q19] != 3 -> - or([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q14, q17, q21] /\ - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q14, q17, q21] = - y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q14, q17, q19] - | q21 : int(1..2)]) - | q19 : int(1..2)]) - /\ - and([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q14, q17, q23] -> - or([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q14, q17, q25] != 3 /\ - y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q14, q17, q25] = - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q14, q17, q23] - | q25 : int(1..2)]) - | q23 : int(1..2)]) - | q17 : int(1..3)]) - /\ - and([and([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q14, q26, q28] -> - or([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q14, q26, q30] != 3 /\ - y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q14, q26, q30] = - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q14, q26, q28] - | q30 : int(1..2)]) - | q28 : int(1..2)]) - /\ - and([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q14, q26, q32] != 3 -> - or([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q14, q26, q34] /\ - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q14, q26, q34] = - y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q14, q26, q32] - | q34 : int(1..2)]) - | q32 : int(1..2)]) - | q26 : int(1..3)]), - y_1_3[q14] = y_1_3[q14]; - int(1..3)]) - | q14 : int(1, 2)]) - diff --git a/tests/exhaustive/issues/166/expected/model_3_1-solution000001.solution b/tests/exhaustive/issues/166/expected/model_3_1-solution000001.solution new file mode 100644 index 0000000000..15cf35802e --- /dev/null +++ b/tests/exhaustive/issues/166/expected/model_3_1-solution000001.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting y be + tuple ([(10, function(1 --> {1, 2}, 2 --> {1}, 3 --> {}), 33), + (11, function(1 --> {1, 2}, 2 --> {1}, 3 --> {}), 55); + int(1..2)]) diff --git a/tests/exhaustive/issues/166/expected/model_3_1.eprime.orig b/tests/exhaustive/issues/166/expected/model_3_1.eprime.orig deleted file mode 100644 index 1ce6c6503c..0000000000 --- a/tests/exhaustive/issues/166/expected/model_3_1.eprime.orig +++ /dev/null @@ -1,148 +0,0 @@ -language ESSENCE' 1.0 - -find y_1_1: matrix indexed by [int(1, 2)] of int(10, 11) -find y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker: matrix indexed by [int(1, 2), int(1..3)] of int(0..2) -find y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values: - matrix indexed by [int(1, 2), int(1..3), int(1..2)] of int(1, 2) -find y_1_3: matrix indexed by [int(1, 2)] of int(33, 55) -find y_1_2_Function1DR2_Occurrence: matrix indexed by [int(1, 2), int(1..3), int(1, 2)] of bool -branching on - [y_1_1, y_1_2_Function1DR2_Occurrence, y_1_3, y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker, - y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values] -such that - and([and([y_1_1[q9] = [10, 11; int(1..2)][q9], - and([and([or([q18 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q9, q12] /\ - y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q9, q12, q18] = 1 - | q18 : int(1..2)]) - | 1 = q9, 1 = q12]) - /\ - and([or([q20 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q9, q12] /\ - y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q9, q12, q20] = 2 - | q20 : int(1..2)]) - | 1 = q9, 1 = q12]) - /\ - and([or([q22 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q9, q12] /\ - y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q9, q12, q22] = 1 - | q22 : int(1..2)]) - | 1 = q9, 2 = q12]) - /\ - (and([or([q25 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q9, q12] /\ - y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q9, q12, q25] = 1 - | q25 : int(1..2)]) - | 2 = q9, 1 = q12]) - /\ - and([or([q27 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q9, q12] /\ - y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q9, q12, q27] = 2 - | q27 : int(1..2)]) - | 2 = q9, 1 = q12]) - /\ - and([or([q29 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q9, q12] /\ - y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q9, q12, q29] = 1 - | q29 : int(1..2)]) - | 2 = q9, 2 = q12])) - /\ - and([q31 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q9, q12] -> - or([1 = y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q9, q12, q31] | 1 = q9, 1 = q12]) \/ - or([2 = y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q9, q12, q31] | 1 = q9, 1 = q12]) - \/ or([1 = y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q9, q12, q31] | 1 = q9, 2 = q12]) - \/ - (or([1 = y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q9, q12, q31] | 2 = q9, 1 = q12]) - \/ - or([2 = y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q9, q12, q31] | 2 = q9, 1 = q12]) - \/ - or([1 = y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q9, q12, q31] | 2 = q9, 2 = q12])) - | q31 : int(1..2)]) - | q12 : int(1..3)]) - /\ - (and([and([and([q38 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q9, 1] -> - 1 = y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q9, 1, q38] \/ - 2 = y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q9, 1, q38] - | q38 : int(1..2)]) - /\ - (or([q41 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q9, 1] /\ - y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q9, 1, q41] = 1 - | q41 : int(1..2)]) - /\ - or([q41 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q9, 1] /\ - y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q9, 1, q41] = 2 - | q41 : int(1..2)])) - | 1 = q9]), - and([and([q38 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q9, 2] -> - 1 = y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q9, 2, q38] - | q38 : int(1..2)]) - /\ - or([q41 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q9, 2] /\ - y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q9, 2, q41] = 1 - | q41 : int(1..2)]) - | 1 = q9]), - and([and([q38 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q9, 3] -> false - | q38 : int(1..2)]) - | 1 = q9]); - int(1..3)]) - /\ - and([and([and([q43 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q9, 1] -> - 1 = y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q9, 1, q43] \/ - 2 = y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q9, 1, q43] - | q43 : int(1..2)]) - /\ - (or([q46 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q9, 1] /\ - y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q9, 1, q46] = 1 - | q46 : int(1..2)]) - /\ - or([q46 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q9, 1] /\ - y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q9, 1, q46] = 2 - | q46 : int(1..2)])) - | 2 = q9]), - and([and([q43 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q9, 2] -> - 1 = y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q9, 2, q43] - | q43 : int(1..2)]) - /\ - or([q46 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q9, 2] /\ - y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q9, 2, q46] = 1 - | q46 : int(1..2)]) - | 2 = q9]), - and([and([q43 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q9, 3] -> false - | q43 : int(1..2)]) - | 2 = q9]); - int(1..3)])), - y_1_3[q9] = [33, 55; int(1..2)][q9]; - int(1..3)]) - | q9 : int(1, 2)]), - and([and([2 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q1, q2] -> - y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q1, q2, 1] < - y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q1, q2, 2] - | q2 : int(1..3)]) - | q1 : int(1, 2)]), - and([and([and([q4 > y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q1, q2] -> - y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q1, q2, q4] = 1 - | q4 : int(1..2)]) - | q2 : int(1..3)]) - | q1 : int(1, 2)]), - and([and([y_1_1[q55] = y_1_1[q55], - and([and([q60 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q55, q58] -> - y_1_2_Function1DR2_Occurrence - [q55, q58, y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q55, q58, q60]] - | q60 : int(1..2)]) - /\ - and([y_1_2_Function1DR2_Occurrence[q55, q58, q61] -> - or([q63 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q55, q58] /\ - y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q55, q58, q63] = q61 - | q63 : int(1..2)]) - | q61 : int(1, 2)]) - | q58 : int(1..3)]) - /\ - and([and([y_1_2_Function1DR2_Occurrence[q55, q64, q65] -> - or([q67 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q55, q64] /\ - y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q55, q64, q67] = q65 - | q67 : int(1..2)]) - | q65 : int(1, 2)]) - /\ - and([q69 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q55, q64] -> - y_1_2_Function1DR2_Occurrence - [q55, q64, y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q55, q64, q69]] - | q69 : int(1..2)]) - | q64 : int(1..3)]), - y_1_3[q55] = y_1_3[q55]; - int(1..3)]) - | q55 : int(1, 2)]) - diff --git a/tests/exhaustive/issues/166/expected/model_3_2-solution000001.solution b/tests/exhaustive/issues/166/expected/model_3_2-solution000001.solution new file mode 100644 index 0000000000..15cf35802e --- /dev/null +++ b/tests/exhaustive/issues/166/expected/model_3_2-solution000001.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting y be + tuple ([(10, function(1 --> {1, 2}, 2 --> {1}, 3 --> {}), 33), + (11, function(1 --> {1, 2}, 2 --> {1}, 3 --> {}), 55); + int(1..2)]) diff --git a/tests/exhaustive/issues/166/expected/model_3_2.eprime.orig b/tests/exhaustive/issues/166/expected/model_3_2.eprime.orig deleted file mode 100644 index 72459ac480..0000000000 --- a/tests/exhaustive/issues/166/expected/model_3_2.eprime.orig +++ /dev/null @@ -1,166 +0,0 @@ -language ESSENCE' 1.0 - -find y_1_1: matrix indexed by [int(1, 2)] of int(10, 11) -find y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker: matrix indexed by [int(1, 2), int(1..3)] of int(0..2) -find y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values: - matrix indexed by [int(1, 2), int(1..3), int(1..2)] of int(1, 2) -find y_1_3: matrix indexed by [int(1, 2)] of int(33, 55) -find y_1_2_Function1DR6_ExplicitVarSizeWithDummy: matrix indexed by [int(1, 2), int(1..3), int(1..2)] of int(1, 2, 3) -branching on - [y_1_1, y_1_2_Function1DR6_ExplicitVarSizeWithDummy, y_1_3, y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker, - y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values] -such that - and([and([y_1_1[q33] = [10, 11; int(1..2)][q33], - and([and([or([q42 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q33, q36] /\ - y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q33, q36, q42] = 1 - | q42 : int(1..2)]) - | 1 = q33, 1 = q36]) - /\ - and([or([q44 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q33, q36] /\ - y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q33, q36, q44] = 2 - | q44 : int(1..2)]) - | 1 = q33, 1 = q36]) - /\ - and([or([q46 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q33, q36] /\ - y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q33, q36, q46] = 1 - | q46 : int(1..2)]) - | 1 = q33, 2 = q36]) - /\ - (and([or([q49 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q33, q36] /\ - y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q33, q36, q49] = 1 - | q49 : int(1..2)]) - | 2 = q33, 1 = q36]) - /\ - and([or([q51 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q33, q36] /\ - y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q33, q36, q51] = 2 - | q51 : int(1..2)]) - | 2 = q33, 1 = q36]) - /\ - and([or([q53 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q33, q36] /\ - y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q33, q36, q53] = 1 - | q53 : int(1..2)]) - | 2 = q33, 2 = q36])) - /\ - and([q55 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q33, q36] -> - or([1 = y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q33, q36, q55] | 1 = q33, 1 = q36]) - \/ - or([2 = y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q33, q36, q55] | 1 = q33, 1 = q36]) - \/ - or([1 = y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q33, q36, q55] | 1 = q33, 2 = q36]) - \/ - (or([1 = y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q33, q36, q55] | 2 = q33, 1 = q36]) - \/ - or([2 = y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q33, q36, q55] | 2 = q33, 1 = q36]) - \/ - or([1 = y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q33, q36, q55] - | 2 = q33, 2 = q36])) - | q55 : int(1..2)]) - | q36 : int(1..3)]) - /\ - (and([and([and([q62 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q33, 1] -> - 1 = y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q33, 1, q62] \/ - 2 = y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q33, 1, q62] - | q62 : int(1..2)]) - /\ - (or([q65 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q33, 1] /\ - y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q33, 1, q65] = 1 - | q65 : int(1..2)]) - /\ - or([q65 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q33, 1] /\ - y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q33, 1, q65] = 2 - | q65 : int(1..2)])) - | 1 = q33]), - and([and([q62 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q33, 2] -> - 1 = y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q33, 2, q62] - | q62 : int(1..2)]) - /\ - or([q65 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q33, 2] /\ - y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q33, 2, q65] = 1 - | q65 : int(1..2)]) - | 1 = q33]), - and([and([q62 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q33, 3] -> false - | q62 : int(1..2)]) - | 1 = q33]); - int(1..3)]) - /\ - and([and([and([q67 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q33, 1] -> - 1 = y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q33, 1, q67] \/ - 2 = y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q33, 1, q67] - | q67 : int(1..2)]) - /\ - (or([q70 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q33, 1] /\ - y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q33, 1, q70] = 1 - | q70 : int(1..2)]) - /\ - or([q70 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q33, 1] /\ - y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q33, 1, q70] = 2 - | q70 : int(1..2)])) - | 2 = q33]), - and([and([q67 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q33, 2] -> - 1 = y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q33, 2, q67] - | q67 : int(1..2)]) - /\ - or([q70 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q33, 2] /\ - y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q33, 2, q70] = 1 - | q70 : int(1..2)]) - | 2 = q33]), - and([and([q67 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q33, 3] -> false - | q67 : int(1..2)]) - | 2 = q33]); - int(1..3)])), - y_1_3[q33] = [33, 55; int(1..2)][q33]; - int(1..3)]) - | q33 : int(1, 2)]), - and([and([2 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q1, q2] -> - y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q1, q2, 1] < - y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q1, q2, 2] - | q2 : int(1..3)]) - | q1 : int(1, 2)]), - and([and([and([q4 > y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q1, q2] -> - y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q1, q2, q4] = 1 - | q4 : int(1..2)]) - | q2 : int(1..3)]) - | q1 : int(1, 2)]), - and([and([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q6, q7, 1] < - y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q6, q7, 2] - \/ y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q6, q7, 1] = 3 - | q7 : int(1..3)]) - | q6 : int(1, 2)]), - and([and([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q6, q7, 1] = 3 -> - y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q6, q7, 2] = 3 - | q7 : int(1..3)]) - | q6 : int(1, 2)]), - and([and([y_1_1[q12] = y_1_1[q12], - and([and([q17 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q12, q15] -> - or([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q12, q15, q19] != 3 /\ - y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q12, q15, q19] = - y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q12, q15, q17] - | q19 : int(1..2)]) - | q17 : int(1..2)]) - /\ - and([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q12, q15, q21] != 3 -> - or([q23 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q12, q15] /\ - y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q12, q15, q23] = - y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q12, q15, q21] - | q23 : int(1..2)]) - | q21 : int(1..2)]) - | q15 : int(1..3)]) - /\ - and([and([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q12, q24, q26] != 3 -> - or([q28 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q12, q24] /\ - y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q12, q24, q28] = - y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q12, q24, q26] - | q28 : int(1..2)]) - | q26 : int(1..2)]) - /\ - and([q30 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q12, q24] -> - or([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q12, q24, q32] != 3 /\ - y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q12, q24, q32] = - y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q12, q24, q30] - | q32 : int(1..2)]) - | q30 : int(1..2)]) - | q24 : int(1..3)]), - y_1_3[q12] = y_1_3[q12]; - int(1..3)]) - | q12 : int(1, 2)]) - diff --git a/tests/exhaustive/issues/166/expected/model_3_3-solution000001.solution b/tests/exhaustive/issues/166/expected/model_3_3-solution000001.solution new file mode 100644 index 0000000000..15cf35802e --- /dev/null +++ b/tests/exhaustive/issues/166/expected/model_3_3-solution000001.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting y be + tuple ([(10, function(1 --> {1, 2}, 2 --> {1}, 3 --> {}), 33), + (11, function(1 --> {1, 2}, 2 --> {1}, 3 --> {}), 55); + int(1..2)]) diff --git a/tests/exhaustive/issues/166/expected/model_3_3.eprime.orig b/tests/exhaustive/issues/166/expected/model_3_3.eprime.orig deleted file mode 100644 index f9b537481c..0000000000 --- a/tests/exhaustive/issues/166/expected/model_3_3.eprime.orig +++ /dev/null @@ -1,118 +0,0 @@ -language ESSENCE' 1.0 - -find y_1_1: matrix indexed by [int(1, 2)] of int(10, 11) -find y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker: matrix indexed by [int(1, 2), int(1..3)] of int(0..2) -find y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values: - matrix indexed by [int(1, 2), int(1..3), int(1..2)] of int(1, 2) -find y_1_3: matrix indexed by [int(1, 2)] of int(33, 55) -branching on - [y_1_1, y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker, y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values, - y_1_3] -such that - and([and([y_1_1[q6] = [10, 11; int(1..2)][q6], - and([and([or([q15 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q6, q9] /\ - y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q6, q9, q15] = 1 - | q15 : int(1..2)]) - | 1 = q6, 1 = q9]) - /\ - and([or([q17 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q6, q9] /\ - y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q6, q9, q17] = 2 - | q17 : int(1..2)]) - | 1 = q6, 1 = q9]) - /\ - and([or([q19 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q6, q9] /\ - y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q6, q9, q19] = 1 - | q19 : int(1..2)]) - | 1 = q6, 2 = q9]) - /\ - (and([or([q22 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q6, q9] /\ - y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q6, q9, q22] = 1 - | q22 : int(1..2)]) - | 2 = q6, 1 = q9]) - /\ - and([or([q24 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q6, q9] /\ - y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q6, q9, q24] = 2 - | q24 : int(1..2)]) - | 2 = q6, 1 = q9]) - /\ - and([or([q26 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q6, q9] /\ - y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q6, q9, q26] = 1 - | q26 : int(1..2)]) - | 2 = q6, 2 = q9])) - /\ - and([q28 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q6, q9] -> - or([1 = y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q6, q9, q28] | 1 = q6, 1 = q9]) \/ - or([2 = y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q6, q9, q28] | 1 = q6, 1 = q9]) - \/ or([1 = y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q6, q9, q28] | 1 = q6, 2 = q9]) - \/ - (or([1 = y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q6, q9, q28] | 2 = q6, 1 = q9]) \/ - or([2 = y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q6, q9, q28] | 2 = q6, 1 = q9]) - \/ or([1 = y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q6, q9, q28] | 2 = q6, 2 = q9])) - | q28 : int(1..2)]) - | q9 : int(1..3)]) - /\ - (and([and([and([q35 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q6, 1] -> - 1 = y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q6, 1, q35] \/ - 2 = y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q6, 1, q35] - | q35 : int(1..2)]) - /\ - (or([q38 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q6, 1] /\ - y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q6, 1, q38] = 1 - | q38 : int(1..2)]) - /\ - or([q38 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q6, 1] /\ - y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q6, 1, q38] = 2 - | q38 : int(1..2)])) - | 1 = q6]), - and([and([q35 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q6, 2] -> - 1 = y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q6, 2, q35] - | q35 : int(1..2)]) - /\ - or([q38 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q6, 2] /\ - y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q6, 2, q38] = 1 - | q38 : int(1..2)]) - | 1 = q6]), - and([and([q35 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q6, 3] -> false - | q35 : int(1..2)]) - | 1 = q6]); - int(1..3)]) - /\ - and([and([and([q40 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q6, 1] -> - 1 = y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q6, 1, q40] \/ - 2 = y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q6, 1, q40] - | q40 : int(1..2)]) - /\ - (or([q43 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q6, 1] /\ - y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q6, 1, q43] = 1 - | q43 : int(1..2)]) - /\ - or([q43 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q6, 1] /\ - y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q6, 1, q43] = 2 - | q43 : int(1..2)])) - | 2 = q6]), - and([and([q40 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q6, 2] -> - 1 = y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q6, 2, q40] - | q40 : int(1..2)]) - /\ - or([q43 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q6, 2] /\ - y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q6, 2, q43] = 1 - | q43 : int(1..2)]) - | 2 = q6]), - and([and([q40 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q6, 3] -> false - | q40 : int(1..2)]) - | 2 = q6]); - int(1..3)])), - y_1_3[q6] = [33, 55; int(1..2)][q6]; - int(1..3)]) - | q6 : int(1, 2)]), - and([and([2 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q1, q2] -> - y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q1, q2, 1] < - y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q1, q2, 2] - | q2 : int(1..3)]) - | q1 : int(1, 2)]), - and([and([and([q4 > y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q1, q2] -> - y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q1, q2, q4] = 1 - | q4 : int(1..2)]) - | q2 : int(1..3)]) - | q1 : int(1, 2)]) - diff --git a/tests/exhaustive/issues/166/expected/model_3_4-solution000001.solution b/tests/exhaustive/issues/166/expected/model_3_4-solution000001.solution new file mode 100644 index 0000000000..15cf35802e --- /dev/null +++ b/tests/exhaustive/issues/166/expected/model_3_4-solution000001.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting y be + tuple ([(10, function(1 --> {1, 2}, 2 --> {1}, 3 --> {}), 33), + (11, function(1 --> {1, 2}, 2 --> {1}, 3 --> {}), 55); + int(1..2)]) diff --git a/tests/exhaustive/issues/166/expected/model_3_4.eprime.orig b/tests/exhaustive/issues/166/expected/model_3_4.eprime.orig deleted file mode 100644 index 10a65c931f..0000000000 --- a/tests/exhaustive/issues/166/expected/model_3_4.eprime.orig +++ /dev/null @@ -1,173 +0,0 @@ -language ESSENCE' 1.0 - -find y_1_1: matrix indexed by [int(1, 2)] of int(10, 11) -find y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker: matrix indexed by [int(1, 2), int(1..3)] of int(0..2) -find y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values: - matrix indexed by [int(1, 2), int(1..3), int(1..2)] of int(1, 2) -find y_1_3: matrix indexed by [int(1, 2)] of int(33, 55) -find y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1, 2), int(1..3), int(1..2)] of bool -find y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values: - matrix indexed by [int(1, 2), int(1..3), int(1..2)] of int(1, 2) -branching on - [y_1_1, y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags, y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values, - y_1_3, y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker, y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values] -such that - and([and([y_1_1[q34] = [10, 11; int(1..2)][q34], - and([and([or([q43 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q34, q37] /\ - y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q34, q37, q43] = 1 - | q43 : int(1..2)]) - | 1 = q34, 1 = q37]) - /\ - and([or([q45 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q34, q37] /\ - y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q34, q37, q45] = 2 - | q45 : int(1..2)]) - | 1 = q34, 1 = q37]) - /\ - and([or([q47 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q34, q37] /\ - y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q34, q37, q47] = 1 - | q47 : int(1..2)]) - | 1 = q34, 2 = q37]) - /\ - (and([or([q50 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q34, q37] /\ - y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q34, q37, q50] = 1 - | q50 : int(1..2)]) - | 2 = q34, 1 = q37]) - /\ - and([or([q52 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q34, q37] /\ - y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q34, q37, q52] = 2 - | q52 : int(1..2)]) - | 2 = q34, 1 = q37]) - /\ - and([or([q54 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q34, q37] /\ - y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q34, q37, q54] = 1 - | q54 : int(1..2)]) - | 2 = q34, 2 = q37])) - /\ - and([q56 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q34, q37] -> - or([1 = y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q34, q37, q56] | 1 = q34, 1 = q37]) - \/ - or([2 = y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q34, q37, q56] | 1 = q34, 1 = q37]) - \/ - or([1 = y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q34, q37, q56] | 1 = q34, 2 = q37]) - \/ - (or([1 = y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q34, q37, q56] | 2 = q34, 1 = q37]) - \/ - or([2 = y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q34, q37, q56] | 2 = q34, 1 = q37]) - \/ - or([1 = y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q34, q37, q56] - | 2 = q34, 2 = q37])) - | q56 : int(1..2)]) - | q37 : int(1..3)]) - /\ - (and([and([and([q63 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q34, 1] -> - 1 = y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q34, 1, q63] \/ - 2 = y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q34, 1, q63] - | q63 : int(1..2)]) - /\ - (or([q66 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q34, 1] /\ - y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q34, 1, q66] = 1 - | q66 : int(1..2)]) - /\ - or([q66 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q34, 1] /\ - y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q34, 1, q66] = 2 - | q66 : int(1..2)])) - | 1 = q34]), - and([and([q63 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q34, 2] -> - 1 = y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q34, 2, q63] - | q63 : int(1..2)]) - /\ - or([q66 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q34, 2] /\ - y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q34, 2, q66] = 1 - | q66 : int(1..2)]) - | 1 = q34]), - and([and([q63 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q34, 3] -> false - | q63 : int(1..2)]) - | 1 = q34]); - int(1..3)]) - /\ - and([and([and([q68 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q34, 1] -> - 1 = y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q34, 1, q68] \/ - 2 = y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q34, 1, q68] - | q68 : int(1..2)]) - /\ - (or([q71 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q34, 1] /\ - y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q34, 1, q71] = 1 - | q71 : int(1..2)]) - /\ - or([q71 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q34, 1] /\ - y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q34, 1, q71] = 2 - | q71 : int(1..2)])) - | 2 = q34]), - and([and([q68 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q34, 2] -> - 1 = y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q34, 2, q68] - | q68 : int(1..2)]) - /\ - or([q71 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q34, 2] /\ - y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q34, 2, q71] = 1 - | q71 : int(1..2)]) - | 2 = q34]), - and([and([q68 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q34, 3] -> false - | q68 : int(1..2)]) - | 2 = q34]); - int(1..3)])), - y_1_3[q34] = [33, 55; int(1..2)][q34]; - int(1..3)]) - | q34 : int(1, 2)]), - and([and([2 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q1, q2] -> - y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q1, q2, 1] < - y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q1, q2, 2] - | q2 : int(1..3)]) - | q1 : int(1, 2)]), - and([and([and([q4 > y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q1, q2] -> - y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q1, q2, q4] = 1 - | q4 : int(1..2)]) - | q2 : int(1..3)]) - | q1 : int(1, 2)]), - and([and([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q6, q7, 2] -> - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q6, q7, 1] < - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q6, q7, 2] - | q7 : int(1..3)]) - | q6 : int(1, 2)]), - and([and([and([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q6, q7, q9] = false -> - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q6, q7, q9] = 1 - | q9 : int(1..2)]) - | q7 : int(1..3)]) - | q6 : int(1, 2)]), - and([and([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q6, q7, 2] -> - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q6, q7, 1] - | q7 : int(1..3)]) - | q6 : int(1, 2)]), - and([and([y_1_1[q13] = y_1_1[q13], - and([and([q18 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q13, q16] -> - or([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q13, q16, q20] /\ - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q13, q16, q20] = - y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q13, q16, q18] - | q20 : int(1..2)]) - | q18 : int(1..2)]) - /\ - and([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q13, q16, q22] -> - or([q24 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q13, q16] /\ - y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q13, q16, q24] = - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q13, q16, q22] - | q24 : int(1..2)]) - | q22 : int(1..2)]) - | q16 : int(1..3)]) - /\ - and([and([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q13, q25, q27] -> - or([q29 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q13, q25] /\ - y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q13, q25, q29] = - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q13, q25, q27] - | q29 : int(1..2)]) - | q27 : int(1..2)]) - /\ - and([q31 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q13, q25] -> - or([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q13, q25, q33] /\ - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q13, q25, q33] = - y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q13, q25, q31] - | q33 : int(1..2)]) - | q31 : int(1..2)]) - | q25 : int(1..3)]), - y_1_3[q13] = y_1_3[q13]; - int(1..3)]) - | q13 : int(1, 2)]) - diff --git a/tests/exhaustive/issues/166/expected/model_4_1-solution000001.solution b/tests/exhaustive/issues/166/expected/model_4_1-solution000001.solution new file mode 100644 index 0000000000..15cf35802e --- /dev/null +++ b/tests/exhaustive/issues/166/expected/model_4_1-solution000001.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting y be + tuple ([(10, function(1 --> {1, 2}, 2 --> {1}, 3 --> {}), 33), + (11, function(1 --> {1, 2}, 2 --> {1}, 3 --> {}), 55); + int(1..2)]) diff --git a/tests/exhaustive/issues/166/expected/model_4_1.eprime.orig b/tests/exhaustive/issues/166/expected/model_4_1.eprime.orig deleted file mode 100644 index 8ff2e45e2f..0000000000 --- a/tests/exhaustive/issues/166/expected/model_4_1.eprime.orig +++ /dev/null @@ -1,154 +0,0 @@ -language ESSENCE' 1.0 - -find y_1_1: matrix indexed by [int(1, 2)] of int(10, 11) -find y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1, 2), int(1..3), int(1..2)] of bool -find y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values: - matrix indexed by [int(1, 2), int(1..3), int(1..2)] of int(1, 2) -find y_1_3: matrix indexed by [int(1, 2)] of int(33, 55) -find y_1_2_Function1DR2_Occurrence: matrix indexed by [int(1, 2), int(1..3), int(1, 2)] of bool -branching on - [y_1_1, y_1_2_Function1DR2_Occurrence, y_1_3, y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags, - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values] -such that - and([and([y_1_1[q11] = [10, 11; int(1..2)][q11], - and([and([or([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q11, q14, q20] /\ - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q11, q14, q20] = 1 - | q20 : int(1..2)]) - | 1 = q11, 1 = q14]) - /\ - and([or([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q11, q14, q22] /\ - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q11, q14, q22] = 2 - | q22 : int(1..2)]) - | 1 = q11, 1 = q14]) - /\ - and([or([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q11, q14, q24] /\ - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q11, q14, q24] = 1 - | q24 : int(1..2)]) - | 1 = q11, 2 = q14]) - /\ - (and([or([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q11, q14, q27] /\ - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q11, q14, q27] = 1 - | q27 : int(1..2)]) - | 2 = q11, 1 = q14]) - /\ - and([or([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q11, q14, q29] /\ - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q11, q14, q29] = 2 - | q29 : int(1..2)]) - | 2 = q11, 1 = q14]) - /\ - and([or([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q11, q14, q31] /\ - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q11, q14, q31] = 1 - | q31 : int(1..2)]) - | 2 = q11, 2 = q14])) - /\ - and([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q11, q14, q33] -> - or([1 = y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q11, q14, q33] | 1 = q11, 1 = q14]) - \/ - or([2 = y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q11, q14, q33] | 1 = q11, 1 = q14]) - \/ - or([1 = y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q11, q14, q33] | 1 = q11, 2 = q14]) - \/ - (or([1 = y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q11, q14, q33] | 2 = q11, 1 = q14]) - \/ - or([2 = y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q11, q14, q33] | 2 = q11, 1 = q14]) - \/ - or([1 = y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q11, q14, q33] | 2 = q11, 2 = q14])) - | q33 : int(1..2)]) - | q14 : int(1..3)]) - /\ - (and([and([and([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q11, 1, q40] -> - 1 = y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q11, 1, q40] \/ - 2 = y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q11, 1, q40] - | q40 : int(1..2)]) - /\ - (or([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q11, 1, q43] /\ - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q11, 1, q43] = 1 - | q43 : int(1..2)]) - /\ - or([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q11, 1, q43] /\ - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q11, 1, q43] = 2 - | q43 : int(1..2)])) - | 1 = q11]), - and([and([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q11, 2, q40] -> - 1 = y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q11, 2, q40] - | q40 : int(1..2)]) - /\ - or([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q11, 2, q43] /\ - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q11, 2, q43] = 1 - | q43 : int(1..2)]) - | 1 = q11]), - and([and([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q11, 3, q40] -> false - | q40 : int(1..2)]) - | 1 = q11]); - int(1..3)]) - /\ - and([and([and([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q11, 1, q45] -> - 1 = y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q11, 1, q45] \/ - 2 = y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q11, 1, q45] - | q45 : int(1..2)]) - /\ - (or([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q11, 1, q48] /\ - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q11, 1, q48] = 1 - | q48 : int(1..2)]) - /\ - or([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q11, 1, q48] /\ - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q11, 1, q48] = 2 - | q48 : int(1..2)])) - | 2 = q11]), - and([and([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q11, 2, q45] -> - 1 = y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q11, 2, q45] - | q45 : int(1..2)]) - /\ - or([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q11, 2, q48] /\ - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q11, 2, q48] = 1 - | q48 : int(1..2)]) - | 2 = q11]), - and([and([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q11, 3, q45] -> false - | q45 : int(1..2)]) - | 2 = q11]); - int(1..3)])), - y_1_3[q11] = [33, 55; int(1..2)][q11]; - int(1..3)]) - | q11 : int(1, 2)]), - and([and([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q1, q2, 2] -> - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q1, q2, 1] < - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q1, q2, 2] - | q2 : int(1..3)]) - | q1 : int(1, 2)]), - and([and([and([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q1, q2, q4] = false -> - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q1, q2, q4] = 1 - | q4 : int(1..2)]) - | q2 : int(1..3)]) - | q1 : int(1, 2)]), - and([and([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q1, q2, 2] -> - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q1, q2, 1] - | q2 : int(1..3)]) - | q1 : int(1, 2)]), - and([and([y_1_1[q57] = y_1_1[q57], - and([and([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q57, q60, q62] -> - y_1_2_Function1DR2_Occurrence - [q57, q60, y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q57, q60, q62]] - | q62 : int(1..2)]) - /\ - and([y_1_2_Function1DR2_Occurrence[q57, q60, q63] -> - or([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q57, q60, q65] /\ - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q57, q60, q65] = q63 - | q65 : int(1..2)]) - | q63 : int(1, 2)]) - | q60 : int(1..3)]) - /\ - and([and([y_1_2_Function1DR2_Occurrence[q57, q66, q67] -> - or([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q57, q66, q69] /\ - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q57, q66, q69] = q67 - | q69 : int(1..2)]) - | q67 : int(1, 2)]) - /\ - and([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q57, q66, q71] -> - y_1_2_Function1DR2_Occurrence - [q57, q66, y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q57, q66, q71]] - | q71 : int(1..2)]) - | q66 : int(1..3)]), - y_1_3[q57] = y_1_3[q57]; - int(1..3)]) - | q57 : int(1, 2)]) - diff --git a/tests/exhaustive/issues/166/expected/model_4_2-solution000001.solution b/tests/exhaustive/issues/166/expected/model_4_2-solution000001.solution new file mode 100644 index 0000000000..15cf35802e --- /dev/null +++ b/tests/exhaustive/issues/166/expected/model_4_2-solution000001.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting y be + tuple ([(10, function(1 --> {1, 2}, 2 --> {1}, 3 --> {}), 33), + (11, function(1 --> {1, 2}, 2 --> {1}, 3 --> {}), 55); + int(1..2)]) diff --git a/tests/exhaustive/issues/166/expected/model_4_2.eprime.orig b/tests/exhaustive/issues/166/expected/model_4_2.eprime.orig deleted file mode 100644 index 69c1bf0cc6..0000000000 --- a/tests/exhaustive/issues/166/expected/model_4_2.eprime.orig +++ /dev/null @@ -1,169 +0,0 @@ -language ESSENCE' 1.0 - -find y_1_1: matrix indexed by [int(1, 2)] of int(10, 11) -find y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1, 2), int(1..3), int(1..2)] of bool -find y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values: - matrix indexed by [int(1, 2), int(1..3), int(1..2)] of int(1, 2) -find y_1_3: matrix indexed by [int(1, 2)] of int(33, 55) -find y_1_2_Function1DR6_ExplicitVarSizeWithDummy: matrix indexed by [int(1, 2), int(1..3), int(1..2)] of int(1, 2, 3) -branching on - [y_1_1, y_1_2_Function1DR6_ExplicitVarSizeWithDummy, y_1_3, y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags, - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values] -such that - and([and([y_1_1[q35] = [10, 11; int(1..2)][q35], - and([and([or([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q35, q38, q44] /\ - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q35, q38, q44] = 1 - | q44 : int(1..2)]) - | 1 = q35, 1 = q38]) - /\ - and([or([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q35, q38, q46] /\ - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q35, q38, q46] = 2 - | q46 : int(1..2)]) - | 1 = q35, 1 = q38]) - /\ - and([or([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q35, q38, q48] /\ - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q35, q38, q48] = 1 - | q48 : int(1..2)]) - | 1 = q35, 2 = q38]) - /\ - (and([or([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q35, q38, q51] /\ - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q35, q38, q51] = 1 - | q51 : int(1..2)]) - | 2 = q35, 1 = q38]) - /\ - and([or([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q35, q38, q53] /\ - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q35, q38, q53] = 2 - | q53 : int(1..2)]) - | 2 = q35, 1 = q38]) - /\ - and([or([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q35, q38, q55] /\ - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q35, q38, q55] = 1 - | q55 : int(1..2)]) - | 2 = q35, 2 = q38])) - /\ - and([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q35, q38, q57] -> - or([1 = y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q35, q38, q57] | 1 = q35, 1 = q38]) - \/ - or([2 = y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q35, q38, q57] | 1 = q35, 1 = q38]) - \/ - or([1 = y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q35, q38, q57] | 1 = q35, 2 = q38]) - \/ - (or([1 = y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q35, q38, q57] | 2 = q35, 1 = q38]) - \/ - or([2 = y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q35, q38, q57] | 2 = q35, 1 = q38]) - \/ - or([1 = y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q35, q38, q57] | 2 = q35, 2 = q38])) - | q57 : int(1..2)]) - | q38 : int(1..3)]) - /\ - (and([and([and([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q35, 1, q64] -> - 1 = y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q35, 1, q64] \/ - 2 = y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q35, 1, q64] - | q64 : int(1..2)]) - /\ - (or([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q35, 1, q67] /\ - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q35, 1, q67] = 1 - | q67 : int(1..2)]) - /\ - or([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q35, 1, q67] /\ - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q35, 1, q67] = 2 - | q67 : int(1..2)])) - | 1 = q35]), - and([and([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q35, 2, q64] -> - 1 = y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q35, 2, q64] - | q64 : int(1..2)]) - /\ - or([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q35, 2, q67] /\ - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q35, 2, q67] = 1 - | q67 : int(1..2)]) - | 1 = q35]), - and([and([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q35, 3, q64] -> false - | q64 : int(1..2)]) - | 1 = q35]); - int(1..3)]) - /\ - and([and([and([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q35, 1, q69] -> - 1 = y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q35, 1, q69] \/ - 2 = y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q35, 1, q69] - | q69 : int(1..2)]) - /\ - (or([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q35, 1, q72] /\ - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q35, 1, q72] = 1 - | q72 : int(1..2)]) - /\ - or([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q35, 1, q72] /\ - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q35, 1, q72] = 2 - | q72 : int(1..2)])) - | 2 = q35]), - and([and([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q35, 2, q69] -> - 1 = y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q35, 2, q69] - | q69 : int(1..2)]) - /\ - or([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q35, 2, q72] /\ - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q35, 2, q72] = 1 - | q72 : int(1..2)]) - | 2 = q35]), - and([and([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q35, 3, q69] -> false - | q69 : int(1..2)]) - | 2 = q35]); - int(1..3)])), - y_1_3[q35] = [33, 55; int(1..2)][q35]; - int(1..3)]) - | q35 : int(1, 2)]), - and([and([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q1, q2, 2] -> - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q1, q2, 1] < - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q1, q2, 2] - | q2 : int(1..3)]) - | q1 : int(1, 2)]), - and([and([and([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q1, q2, q4] = false -> - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q1, q2, q4] = 1 - | q4 : int(1..2)]) - | q2 : int(1..3)]) - | q1 : int(1, 2)]), - and([and([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q1, q2, 2] -> - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q1, q2, 1] - | q2 : int(1..3)]) - | q1 : int(1, 2)]), - and([and([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q8, q9, 1] < - y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q8, q9, 2] - \/ y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q8, q9, 1] = 3 - | q9 : int(1..3)]) - | q8 : int(1, 2)]), - and([and([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q8, q9, 1] = 3 -> - y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q8, q9, 2] = 3 - | q9 : int(1..3)]) - | q8 : int(1, 2)]), - and([and([y_1_1[q14] = y_1_1[q14], - and([and([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q14, q17, q19] -> - or([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q14, q17, q21] != 3 /\ - y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q14, q17, q21] = - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q14, q17, q19] - | q21 : int(1..2)]) - | q19 : int(1..2)]) - /\ - and([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q14, q17, q23] != 3 -> - or([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q14, q17, q25] /\ - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q14, q17, q25] = - y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q14, q17, q23] - | q25 : int(1..2)]) - | q23 : int(1..2)]) - | q17 : int(1..3)]) - /\ - and([and([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q14, q26, q28] != 3 -> - or([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q14, q26, q30] /\ - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q14, q26, q30] = - y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q14, q26, q28] - | q30 : int(1..2)]) - | q28 : int(1..2)]) - /\ - and([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q14, q26, q32] -> - or([y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q14, q26, q34] != 3 /\ - y_1_2_Function1DR6_ExplicitVarSizeWithDummy[q14, q26, q34] = - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q14, q26, q32] - | q34 : int(1..2)]) - | q32 : int(1..2)]) - | q26 : int(1..3)]), - y_1_3[q14] = y_1_3[q14]; - int(1..3)]) - | q14 : int(1, 2)]) - diff --git a/tests/exhaustive/issues/166/expected/model_4_3-solution000001.solution b/tests/exhaustive/issues/166/expected/model_4_3-solution000001.solution new file mode 100644 index 0000000000..15cf35802e --- /dev/null +++ b/tests/exhaustive/issues/166/expected/model_4_3-solution000001.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting y be + tuple ([(10, function(1 --> {1, 2}, 2 --> {1}, 3 --> {}), 33), + (11, function(1 --> {1, 2}, 2 --> {1}, 3 --> {}), 55); + int(1..2)]) diff --git a/tests/exhaustive/issues/166/expected/model_4_3.eprime.orig b/tests/exhaustive/issues/166/expected/model_4_3.eprime.orig deleted file mode 100644 index 9b108c2e09..0000000000 --- a/tests/exhaustive/issues/166/expected/model_4_3.eprime.orig +++ /dev/null @@ -1,172 +0,0 @@ -language ESSENCE' 1.0 - -find y_1_1: matrix indexed by [int(1, 2)] of int(10, 11) -find y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1, 2), int(1..3), int(1..2)] of bool -find y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values: - matrix indexed by [int(1, 2), int(1..3), int(1..2)] of int(1, 2) -find y_1_3: matrix indexed by [int(1, 2)] of int(33, 55) -find y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker: matrix indexed by [int(1, 2), int(1..3)] of int(0..2) -find y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values: - matrix indexed by [int(1, 2), int(1..3), int(1..2)] of int(1, 2) -branching on - [y_1_1, y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker, y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values, - y_1_3, y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags, y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values] -such that - and([and([y_1_1[q34] = [10, 11; int(1..2)][q34], - and([and([or([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q34, q37, q43] /\ - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q34, q37, q43] = 1 - | q43 : int(1..2)]) - | 1 = q34, 1 = q37]) - /\ - and([or([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q34, q37, q45] /\ - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q34, q37, q45] = 2 - | q45 : int(1..2)]) - | 1 = q34, 1 = q37]) - /\ - and([or([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q34, q37, q47] /\ - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q34, q37, q47] = 1 - | q47 : int(1..2)]) - | 1 = q34, 2 = q37]) - /\ - (and([or([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q34, q37, q50] /\ - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q34, q37, q50] = 1 - | q50 : int(1..2)]) - | 2 = q34, 1 = q37]) - /\ - and([or([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q34, q37, q52] /\ - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q34, q37, q52] = 2 - | q52 : int(1..2)]) - | 2 = q34, 1 = q37]) - /\ - and([or([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q34, q37, q54] /\ - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q34, q37, q54] = 1 - | q54 : int(1..2)]) - | 2 = q34, 2 = q37])) - /\ - and([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q34, q37, q56] -> - or([1 = y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q34, q37, q56] | 1 = q34, 1 = q37]) - \/ - or([2 = y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q34, q37, q56] | 1 = q34, 1 = q37]) - \/ - or([1 = y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q34, q37, q56] | 1 = q34, 2 = q37]) - \/ - (or([1 = y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q34, q37, q56] | 2 = q34, 1 = q37]) - \/ - or([2 = y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q34, q37, q56] | 2 = q34, 1 = q37]) - \/ - or([1 = y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q34, q37, q56] | 2 = q34, 2 = q37])) - | q56 : int(1..2)]) - | q37 : int(1..3)]) - /\ - (and([and([and([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q34, 1, q63] -> - 1 = y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q34, 1, q63] \/ - 2 = y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q34, 1, q63] - | q63 : int(1..2)]) - /\ - (or([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q34, 1, q66] /\ - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q34, 1, q66] = 1 - | q66 : int(1..2)]) - /\ - or([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q34, 1, q66] /\ - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q34, 1, q66] = 2 - | q66 : int(1..2)])) - | 1 = q34]), - and([and([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q34, 2, q63] -> - 1 = y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q34, 2, q63] - | q63 : int(1..2)]) - /\ - or([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q34, 2, q66] /\ - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q34, 2, q66] = 1 - | q66 : int(1..2)]) - | 1 = q34]), - and([and([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q34, 3, q63] -> false - | q63 : int(1..2)]) - | 1 = q34]); - int(1..3)]) - /\ - and([and([and([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q34, 1, q68] -> - 1 = y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q34, 1, q68] \/ - 2 = y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q34, 1, q68] - | q68 : int(1..2)]) - /\ - (or([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q34, 1, q71] /\ - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q34, 1, q71] = 1 - | q71 : int(1..2)]) - /\ - or([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q34, 1, q71] /\ - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q34, 1, q71] = 2 - | q71 : int(1..2)])) - | 2 = q34]), - and([and([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q34, 2, q68] -> - 1 = y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q34, 2, q68] - | q68 : int(1..2)]) - /\ - or([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q34, 2, q71] /\ - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q34, 2, q71] = 1 - | q71 : int(1..2)]) - | 2 = q34]), - and([and([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q34, 3, q68] -> false - | q68 : int(1..2)]) - | 2 = q34]); - int(1..3)])), - y_1_3[q34] = [33, 55; int(1..2)][q34]; - int(1..3)]) - | q34 : int(1, 2)]), - and([and([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q1, q2, 2] -> - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q1, q2, 1] < - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q1, q2, 2] - | q2 : int(1..3)]) - | q1 : int(1, 2)]), - and([and([and([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q1, q2, q4] = false -> - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q1, q2, q4] = 1 - | q4 : int(1..2)]) - | q2 : int(1..3)]) - | q1 : int(1, 2)]), - and([and([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q1, q2, 2] -> - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q1, q2, 1] - | q2 : int(1..3)]) - | q1 : int(1, 2)]), - and([and([2 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q8, q9] -> - y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q8, q9, 1] < - y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q8, q9, 2] - | q9 : int(1..3)]) - | q8 : int(1, 2)]), - and([and([and([q11 > y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q8, q9] -> - y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q8, q9, q11] = 1 - | q11 : int(1..2)]) - | q9 : int(1..3)]) - | q8 : int(1, 2)]), - and([and([y_1_1[q13] = y_1_1[q13], - and([and([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q13, q16, q18] -> - or([q20 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q13, q16] /\ - y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q13, q16, q20] = - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q13, q16, q18] - | q20 : int(1..2)]) - | q18 : int(1..2)]) - /\ - and([q22 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q13, q16] -> - or([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q13, q16, q24] /\ - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q13, q16, q24] = - y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q13, q16, q22] - | q24 : int(1..2)]) - | q22 : int(1..2)]) - | q16 : int(1..3)]) - /\ - and([and([q27 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q13, q25] -> - or([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q13, q25, q29] /\ - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q13, q25, q29] = - y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q13, q25, q27] - | q29 : int(1..2)]) - | q27 : int(1..2)]) - /\ - and([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q13, q25, q31] -> - or([q33 <= y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Marker[q13, q25] /\ - y_1_2_Function1DR5_ExplicitVarSizeWithMarker_Values[q13, q25, q33] = - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q13, q25, q31] - | q33 : int(1..2)]) - | q31 : int(1..2)]) - | q25 : int(1..3)]), - y_1_3[q13] = y_1_3[q13]; - int(1..3)]) - | q13 : int(1, 2)]) - diff --git a/tests/exhaustive/issues/166/expected/model_4_4-solution000001.solution b/tests/exhaustive/issues/166/expected/model_4_4-solution000001.solution new file mode 100644 index 0000000000..15cf35802e --- /dev/null +++ b/tests/exhaustive/issues/166/expected/model_4_4-solution000001.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting y be + tuple ([(10, function(1 --> {1, 2}, 2 --> {1}, 3 --> {}), 33), + (11, function(1 --> {1, 2}, 2 --> {1}, 3 --> {}), 55); + int(1..2)]) diff --git a/tests/exhaustive/issues/166/expected/model_4_4.eprime.orig b/tests/exhaustive/issues/166/expected/model_4_4.eprime.orig deleted file mode 100644 index 9dd300ffd7..0000000000 --- a/tests/exhaustive/issues/166/expected/model_4_4.eprime.orig +++ /dev/null @@ -1,121 +0,0 @@ -language ESSENCE' 1.0 - -find y_1_1: matrix indexed by [int(1, 2)] of int(10, 11) -find y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1, 2), int(1..3), int(1..2)] of bool -find y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values: - matrix indexed by [int(1, 2), int(1..3), int(1..2)] of int(1, 2) -find y_1_3: matrix indexed by [int(1, 2)] of int(33, 55) -branching on - [y_1_1, y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags, y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values, - y_1_3] -such that - and([and([y_1_1[q8] = [10, 11; int(1..2)][q8], - and([and([or([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q8, q11, q17] /\ - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q8, q11, q17] = 1 - | q17 : int(1..2)]) - | 1 = q8, 1 = q11]) - /\ - and([or([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q8, q11, q19] /\ - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q8, q11, q19] = 2 - | q19 : int(1..2)]) - | 1 = q8, 1 = q11]) - /\ - and([or([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q8, q11, q21] /\ - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q8, q11, q21] = 1 - | q21 : int(1..2)]) - | 1 = q8, 2 = q11]) - /\ - (and([or([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q8, q11, q24] /\ - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q8, q11, q24] = 1 - | q24 : int(1..2)]) - | 2 = q8, 1 = q11]) - /\ - and([or([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q8, q11, q26] /\ - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q8, q11, q26] = 2 - | q26 : int(1..2)]) - | 2 = q8, 1 = q11]) - /\ - and([or([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q8, q11, q28] /\ - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q8, q11, q28] = 1 - | q28 : int(1..2)]) - | 2 = q8, 2 = q11])) - /\ - and([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q8, q11, q30] -> - or([1 = y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q8, q11, q30] | 1 = q8, 1 = q11]) \/ - or([2 = y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q8, q11, q30] | 1 = q8, 1 = q11]) - \/ or([1 = y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q8, q11, q30] | 1 = q8, 2 = q11]) - \/ - (or([1 = y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q8, q11, q30] | 2 = q8, 1 = q11]) \/ - or([2 = y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q8, q11, q30] | 2 = q8, 1 = q11]) - \/ - or([1 = y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q8, q11, q30] | 2 = q8, 2 = q11])) - | q30 : int(1..2)]) - | q11 : int(1..3)]) - /\ - (and([and([and([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q8, 1, q37] -> - 1 = y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q8, 1, q37] \/ - 2 = y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q8, 1, q37] - | q37 : int(1..2)]) - /\ - (or([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q8, 1, q40] /\ - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q8, 1, q40] = 1 - | q40 : int(1..2)]) - /\ - or([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q8, 1, q40] /\ - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q8, 1, q40] = 2 - | q40 : int(1..2)])) - | 1 = q8]), - and([and([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q8, 2, q37] -> - 1 = y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q8, 2, q37] - | q37 : int(1..2)]) - /\ - or([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q8, 2, q40] /\ - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q8, 2, q40] = 1 - | q40 : int(1..2)]) - | 1 = q8]), - and([and([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q8, 3, q37] -> false | q37 : int(1..2)]) - | 1 = q8]); - int(1..3)]) - /\ - and([and([and([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q8, 1, q42] -> - 1 = y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q8, 1, q42] \/ - 2 = y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q8, 1, q42] - | q42 : int(1..2)]) - /\ - (or([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q8, 1, q45] /\ - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q8, 1, q45] = 1 - | q45 : int(1..2)]) - /\ - or([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q8, 1, q45] /\ - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q8, 1, q45] = 2 - | q45 : int(1..2)])) - | 2 = q8]), - and([and([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q8, 2, q42] -> - 1 = y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q8, 2, q42] - | q42 : int(1..2)]) - /\ - or([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q8, 2, q45] /\ - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q8, 2, q45] = 1 - | q45 : int(1..2)]) - | 2 = q8]), - and([and([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q8, 3, q42] -> false | q42 : int(1..2)]) - | 2 = q8]); - int(1..3)])), - y_1_3[q8] = [33, 55; int(1..2)][q8]; - int(1..3)]) - | q8 : int(1, 2)]), - and([and([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q1, q2, 2] -> - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q1, q2, 1] < - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q1, q2, 2] - | q2 : int(1..3)]) - | q1 : int(1, 2)]), - and([and([and([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q1, q2, q4] = false -> - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Values[q1, q2, q4] = 1 - | q4 : int(1..2)]) - | q2 : int(1..3)]) - | q1 : int(1, 2)]), - and([and([y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q1, q2, 2] -> - y_1_2_Function1DR4_ExplicitVarSizeWithFlags_Flags[q1, q2, 1] - | q2 : int(1..3)]) - | q1 : int(1, 2)]) - diff --git a/tests/exhaustive/issues/200/expected/model_1_2.eprime b/tests/exhaustive/issues/200/expected/model_1_2.eprime index b07ac8079b..681dbb21e1 100644 --- a/tests/exhaustive/issues/200/expected/model_1_2.eprime +++ b/tests/exhaustive/issues/200/expected/model_1_2.eprime @@ -6,14 +6,6 @@ find quasigroup_Explicit: matrix indexed by [int(1..5)] of int(0..4) find quasigroup_Occurrence: matrix indexed by [int(0..4)] of bool branching on [quasigroup_Occurrence, quasigroup_Explicit] such that -<<<<<<< HEAD - and([quasigroup_Occurrence[a] /\ quasigroup_Occurrence[b] -> a * b * (b * a) = a - | a : int(0..4), b : int(0..4), b > a]), - 5 = sum([toInt(quasigroup_Occurrence[q1]) | q1 : int(0..4)]), - and([[quasigroup_Explicit[q2]; int(1)] or([quasigroup_Explicit[q8] = q6 | q8 : int(1..5)]) | q6 : int(0..4)]) -======= and([quasigroup_Explicit[q11] * quasigroup_Explicit[q12] * (quasigroup_Explicit[q12] * quasigroup_Explicit[q11]) = quasigroup_Explicit[q11] | q11 : int(1..5), q12 : int(1..5), q12 > q11]), @@ -21,5 +13,4 @@ such that 5 = sum([toInt(quasigroup_Occurrence[q3]) | q3 : int(0..4)]), and([quasigroup_Occurrence[q4] -> or([quasigroup_Explicit[q6] = q4 | q6 : int(1..5)]) | q4 : int(0..4)]), and([quasigroup_Occurrence[quasigroup_Explicit[q8]] | q8 : int(1..5)]) ->>>>>>> main diff --git a/tests/exhaustive/issues/200/expected/model_2_1.eprime b/tests/exhaustive/issues/200/expected/model_2_1.eprime index 7782685892..698b9815ac 100644 --- a/tests/exhaustive/issues/200/expected/model_2_1.eprime +++ b/tests/exhaustive/issues/200/expected/model_2_1.eprime @@ -6,20 +6,10 @@ find quasigroup_Occurrence: matrix indexed by [int(0..4)] of bool find quasigroup_Explicit: matrix indexed by [int(1..5)] of int(0..4) branching on [quasigroup_Explicit, quasigroup_Occurrence] such that -<<<<<<< HEAD - and([quasigroup_Explicit[q11] * quasigroup_Explicit[q12] * (quasigroup_Explicit[q12] * quasigroup_Explicit[q11]) = - quasigroup_Explicit[q11] - | q11 : int(1..5), q12 : int(1..5), q12 > q11]), - and([[quasigroup_Explicit[q1]; int(1)] or([quasigroup_Explicit[q6] = q4 | q6 : int(1..5)]) | q4 : int(0..4)]), - and([quasigroup_Occurrence[quasigroup_Explicit[q8]] | q8 : int(1..5)]) -======= and([quasigroup_Occurrence[a] /\ quasigroup_Occurrence[b] -> a * b * (b * a) = a | a : int(0..4), b : int(0..4), b > a]), 5 = sum([toInt(quasigroup_Occurrence[q1]) | q1 : int(0..4)]), and([quasigroup_Explicit[q2] < quasigroup_Explicit[q2 + 1] | q2 : int(1..4)]), and([quasigroup_Occurrence[quasigroup_Explicit[q5]] | q5 : int(1..5)]), and([quasigroup_Occurrence[q6] -> or([quasigroup_Explicit[q8] = q6 | q8 : int(1..5)]) | q6 : int(0..4)]) ->>>>>>> main diff --git a/tests/exhaustive/issues/200/expected/model_2_2.eprime b/tests/exhaustive/issues/200/expected/model_2_2.eprime index 8467680992..c63510ba9a 100644 --- a/tests/exhaustive/issues/200/expected/model_2_2.eprime +++ b/tests/exhaustive/issues/200/expected/model_2_2.eprime @@ -5,14 +5,7 @@ letting let1 be 4 find quasigroup_Occurrence: matrix indexed by [int(0..4)] of bool branching on [quasigroup_Occurrence] such that -<<<<<<< HEAD - and([quasigroup_Explicit[q5] * quasigroup_Explicit[q6] * (quasigroup_Explicit[q6] * quasigroup_Explicit[q5]) = - quasigroup_Explicit[q5] - | q5 : int(1..5), q6 : int(1..5), q6 > q5]), - and([[quasigroup_Explicit[q1]; int(1)] a * b * (b * a) = a | a : int(0..4), b : int(0..4), b > a]), 5 = sum([toInt(quasigroup_Occurrence[q1]) | q1 : int(0..4)]) ->>>>>>> main diff --git a/tests/exhaustive/issues/212/expected/model_1_1-1-solution000001.solution b/tests/exhaustive/issues/212/expected/model_1_1-1-solution000001.solution new file mode 100644 index 0000000000..de5cc861ad --- /dev/null +++ b/tests/exhaustive/issues/212/expected/model_1_1-1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1} diff --git a/tests/exhaustive/issues/212/expected/model_1_1-1.eprime-param b/tests/exhaustive/issues/212/expected/model_1_1-1.eprime-param new file mode 100644 index 0000000000..c50b6e81fd --- /dev/null +++ b/tests/exhaustive/issues/212/expected/model_1_1-1.eprime-param @@ -0,0 +1,6 @@ +language ESSENCE' 1.0 + +letting a_Explicit be [1, 2; int(1..2)] +letting b_Explicit be [1, 3; int(1..2)] +letting fin1 be 2 +letting fin2 be 2 diff --git a/tests/exhaustive/issues/212/expected/model_1_1.eprime b/tests/exhaustive/issues/212/expected/model_1_1.eprime new file mode 100644 index 0000000000..7d498e9f22 --- /dev/null +++ b/tests/exhaustive/issues/212/expected/model_1_1.eprime @@ -0,0 +1,14 @@ +language ESSENCE' 1.0 + +given fin1: int +given a_Explicit: matrix indexed by [int(1..fin1)] of int(0..5) +given fin2: int +given b_Explicit: matrix indexed by [int(1..fin2)] of int(0..5) +find x_Occurrence: matrix indexed by [int(0..5)] of bool +branching on [x_Occurrence] +such that + and([x_Occurrence[q2] -> + or([a_Explicit[q4] = q2 | q4 : int(1..fin1), or([b_Explicit[q6] = a_Explicit[q4] | q6 : int(1..fin2)])]) + | q2 : int(0..5)]), + and([x_Occurrence[a_Explicit[q8]] | q8 : int(1..fin1), or([b_Explicit[q10] = a_Explicit[q8] | q10 : int(1..fin2)])]) + diff --git a/tests/exhaustive/issues/212/expected/model_1_2-1-solution000001.solution b/tests/exhaustive/issues/212/expected/model_1_2-1-solution000001.solution new file mode 100644 index 0000000000..de5cc861ad --- /dev/null +++ b/tests/exhaustive/issues/212/expected/model_1_2-1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1} diff --git a/tests/exhaustive/issues/212/expected/model_1_2-1.eprime-param b/tests/exhaustive/issues/212/expected/model_1_2-1.eprime-param new file mode 100644 index 0000000000..c50b6e81fd --- /dev/null +++ b/tests/exhaustive/issues/212/expected/model_1_2-1.eprime-param @@ -0,0 +1,6 @@ +language ESSENCE' 1.0 + +letting a_Explicit be [1, 2; int(1..2)] +letting b_Explicit be [1, 3; int(1..2)] +letting fin1 be 2 +letting fin2 be 2 diff --git a/tests/exhaustive/issues/212/expected/model_1_2.eprime b/tests/exhaustive/issues/212/expected/model_1_2.eprime new file mode 100644 index 0000000000..f65c809e22 --- /dev/null +++ b/tests/exhaustive/issues/212/expected/model_1_2.eprime @@ -0,0 +1,23 @@ +language ESSENCE' 1.0 + +given fin1: int +given a_Explicit: matrix indexed by [int(1..fin1)] of int(0..5) +given fin2: int +given b_Explicit: matrix indexed by [int(1..fin2)] of int(0..5) +find x_Occurrence: matrix indexed by [int(0..5)] of bool +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..6)] of int(0..6) +branching on [x_ExplicitVarSizeWithDummy, x_Occurrence] +such that + and([x_Occurrence[q11] -> + or([a_Explicit[q13] = q11 | q13 : int(1..fin1), or([b_Explicit[q15] = a_Explicit[q13] | q15 : int(1..fin2)])]) + | q11 : int(0..5)]), + and([x_Occurrence[a_Explicit[q17]] + | q17 : int(1..fin1), or([b_Explicit[q19] = a_Explicit[q17] | q19 : int(1..fin2)])]), + and([x_ExplicitVarSizeWithDummy[q2] < x_ExplicitVarSizeWithDummy[q2 + 1] \/ x_ExplicitVarSizeWithDummy[q2] = 6 + | q2 : int(1..5)]), + and([x_ExplicitVarSizeWithDummy[q3] = 6 -> x_ExplicitVarSizeWithDummy[q3 + 1] = 6 | q3 : int(1..5)]), + and([x_ExplicitVarSizeWithDummy[q7] != 6 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q7]] | q7 : int(1..6)]), + and([x_Occurrence[q8] -> + or([x_ExplicitVarSizeWithDummy[q10] != 6 /\ x_ExplicitVarSizeWithDummy[q10] = q8 | q10 : int(1..6)]) + | q8 : int(0..5)]) + diff --git a/tests/exhaustive/issues/212/expected/model_1_3-1-solution000001.solution b/tests/exhaustive/issues/212/expected/model_1_3-1-solution000001.solution new file mode 100644 index 0000000000..de5cc861ad --- /dev/null +++ b/tests/exhaustive/issues/212/expected/model_1_3-1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1} diff --git a/tests/exhaustive/issues/212/expected/model_1_3-1.eprime-param b/tests/exhaustive/issues/212/expected/model_1_3-1.eprime-param new file mode 100644 index 0000000000..c50b6e81fd --- /dev/null +++ b/tests/exhaustive/issues/212/expected/model_1_3-1.eprime-param @@ -0,0 +1,6 @@ +language ESSENCE' 1.0 + +letting a_Explicit be [1, 2; int(1..2)] +letting b_Explicit be [1, 3; int(1..2)] +letting fin1 be 2 +letting fin2 be 2 diff --git a/tests/exhaustive/issues/212/expected/model_1_3.eprime b/tests/exhaustive/issues/212/expected/model_1_3.eprime new file mode 100644 index 0000000000..801bf91d9f --- /dev/null +++ b/tests/exhaustive/issues/212/expected/model_1_3.eprime @@ -0,0 +1,26 @@ +language ESSENCE' 1.0 + +given fin1: int +given a_Explicit: matrix indexed by [int(1..fin1)] of int(0..5) +given fin2: int +given b_Explicit: matrix indexed by [int(1..fin2)] of int(0..5) +find x_Occurrence: matrix indexed by [int(0..5)] of bool +find x_ExplicitVarSizeWithMarker_Marker: int(0..6) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..6)] of int(0..5) +branching on [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_Occurrence] +such that + and([x_Occurrence[q10] -> + or([a_Explicit[q12] = q10 | q12 : int(1..fin1), or([b_Explicit[q14] = a_Explicit[q12] | q14 : int(1..fin2)])]) + | q10 : int(0..5)]), + and([x_Occurrence[a_Explicit[q16]] + | q16 : int(1..fin1), or([b_Explicit[q18] = a_Explicit[q16] | q18 : int(1..fin2)])]), + and([q2 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q2] < x_ExplicitVarSizeWithMarker_Values[q2 + 1] + | q2 : int(1..5)]), + and([q3 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q3] = 0 | q3 : int(1..6)]), + and([q6 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q6]] + | q6 : int(1..6)]), + and([x_Occurrence[q7] -> + or([q9 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q9] = q7 | q9 : int(1..6)]) + | q7 : int(0..5)]) + diff --git a/tests/exhaustive/issues/212/expected/model_1_4-1-solution000001.solution b/tests/exhaustive/issues/212/expected/model_1_4-1-solution000001.solution new file mode 100644 index 0000000000..de5cc861ad --- /dev/null +++ b/tests/exhaustive/issues/212/expected/model_1_4-1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1} diff --git a/tests/exhaustive/issues/212/expected/model_1_4-1.eprime-param b/tests/exhaustive/issues/212/expected/model_1_4-1.eprime-param new file mode 100644 index 0000000000..c50b6e81fd --- /dev/null +++ b/tests/exhaustive/issues/212/expected/model_1_4-1.eprime-param @@ -0,0 +1,6 @@ +language ESSENCE' 1.0 + +letting a_Explicit be [1, 2; int(1..2)] +letting b_Explicit be [1, 3; int(1..2)] +letting fin1 be 2 +letting fin2 be 2 diff --git a/tests/exhaustive/issues/212/expected/model_1_4.eprime b/tests/exhaustive/issues/212/expected/model_1_4.eprime new file mode 100644 index 0000000000..ebe5228775 --- /dev/null +++ b/tests/exhaustive/issues/212/expected/model_1_4.eprime @@ -0,0 +1,26 @@ +language ESSENCE' 1.0 + +given fin1: int +given a_Explicit: matrix indexed by [int(1..fin1)] of int(0..5) +given fin2: int +given b_Explicit: matrix indexed by [int(1..fin2)] of int(0..5) +find x_Occurrence: matrix indexed by [int(0..5)] of bool +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..6)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..6)] of int(0..5) +branching on [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_Occurrence] +such that + and([x_Occurrence[q12] -> + or([a_Explicit[q14] = q12 | q14 : int(1..fin1), or([b_Explicit[q16] = a_Explicit[q14] | q16 : int(1..fin2)])]) + | q12 : int(0..5)]), + and([x_Occurrence[a_Explicit[q18]] + | q18 : int(1..fin1), or([b_Explicit[q20] = a_Explicit[q18] | q20 : int(1..fin2)])]), + and([x_ExplicitVarSizeWithFlags_Flags[q2 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q2] < x_ExplicitVarSizeWithFlags_Values[q2 + 1] + | q2 : int(1..5)]), + and([x_ExplicitVarSizeWithFlags_Flags[q3] = false -> x_ExplicitVarSizeWithFlags_Values[q3] = 0 | q3 : int(1..6)]), + and([x_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q4] | q4 : int(1..5)]), + and([x_ExplicitVarSizeWithFlags_Flags[q8] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q8]] | q8 : int(1..6)]), + and([x_Occurrence[q9] -> + or([x_ExplicitVarSizeWithFlags_Flags[q11] /\ x_ExplicitVarSizeWithFlags_Values[q11] = q9 | q11 : int(1..6)]) + | q9 : int(0..5)]) + diff --git a/tests/exhaustive/issues/212/expected/model_2_1-1-solution000001.solution b/tests/exhaustive/issues/212/expected/model_2_1-1-solution000001.solution new file mode 100644 index 0000000000..de5cc861ad --- /dev/null +++ b/tests/exhaustive/issues/212/expected/model_2_1-1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1} diff --git a/tests/exhaustive/issues/212/expected/model_2_1-1.eprime-param b/tests/exhaustive/issues/212/expected/model_2_1-1.eprime-param new file mode 100644 index 0000000000..c50b6e81fd --- /dev/null +++ b/tests/exhaustive/issues/212/expected/model_2_1-1.eprime-param @@ -0,0 +1,6 @@ +language ESSENCE' 1.0 + +letting a_Explicit be [1, 2; int(1..2)] +letting b_Explicit be [1, 3; int(1..2)] +letting fin1 be 2 +letting fin2 be 2 diff --git a/tests/exhaustive/issues/212/expected/model_2_1.eprime b/tests/exhaustive/issues/212/expected/model_2_1.eprime new file mode 100644 index 0000000000..30e87e71e8 --- /dev/null +++ b/tests/exhaustive/issues/212/expected/model_2_1.eprime @@ -0,0 +1,25 @@ +language ESSENCE' 1.0 + +given fin1: int +given a_Explicit: matrix indexed by [int(1..fin1)] of int(0..5) +given fin2: int +given b_Explicit: matrix indexed by [int(1..fin2)] of int(0..5) +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..6)] of int(0..6) +find x_Occurrence: matrix indexed by [int(0..5)] of bool +branching on [x_Occurrence, x_ExplicitVarSizeWithDummy] +such that + and([x_ExplicitVarSizeWithDummy[q7] != 6 -> + or([a_Explicit[q9] = x_ExplicitVarSizeWithDummy[q7] + | q9 : int(1..fin1), or([b_Explicit[q11] = a_Explicit[q9] | q11 : int(1..fin2)])]) + | q7 : int(1..6)]), + and([or([x_ExplicitVarSizeWithDummy[q15] != 6 /\ x_ExplicitVarSizeWithDummy[q15] = a_Explicit[q13] + | q15 : int(1..6)]) + | q13 : int(1..fin1), or([b_Explicit[q17] = a_Explicit[q13] | q17 : int(1..fin2)])]), + and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 6 + | q1 : int(1..5)]), + and([x_ExplicitVarSizeWithDummy[q2] = 6 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 6 | q2 : int(1..5)]), + and([x_Occurrence[q18] -> + or([x_ExplicitVarSizeWithDummy[q20] != 6 /\ x_ExplicitVarSizeWithDummy[q20] = q18 | q20 : int(1..6)]) + | q18 : int(0..5)]), + and([x_ExplicitVarSizeWithDummy[q22] != 6 -> x_Occurrence[x_ExplicitVarSizeWithDummy[q22]] | q22 : int(1..6)]) + diff --git a/tests/exhaustive/issues/212/expected/model_2_2-1-solution000001.solution b/tests/exhaustive/issues/212/expected/model_2_2-1-solution000001.solution new file mode 100644 index 0000000000..de5cc861ad --- /dev/null +++ b/tests/exhaustive/issues/212/expected/model_2_2-1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1} diff --git a/tests/exhaustive/issues/212/expected/model_2_2-1.eprime-param b/tests/exhaustive/issues/212/expected/model_2_2-1.eprime-param new file mode 100644 index 0000000000..c50b6e81fd --- /dev/null +++ b/tests/exhaustive/issues/212/expected/model_2_2-1.eprime-param @@ -0,0 +1,6 @@ +language ESSENCE' 1.0 + +letting a_Explicit be [1, 2; int(1..2)] +letting b_Explicit be [1, 3; int(1..2)] +letting fin1 be 2 +letting fin2 be 2 diff --git a/tests/exhaustive/issues/212/expected/model_2_2.eprime b/tests/exhaustive/issues/212/expected/model_2_2.eprime new file mode 100644 index 0000000000..2046be1123 --- /dev/null +++ b/tests/exhaustive/issues/212/expected/model_2_2.eprime @@ -0,0 +1,20 @@ +language ESSENCE' 1.0 + +given fin1: int +given a_Explicit: matrix indexed by [int(1..fin1)] of int(0..5) +given fin2: int +given b_Explicit: matrix indexed by [int(1..fin2)] of int(0..5) +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..6)] of int(0..6) +branching on [x_ExplicitVarSizeWithDummy] +such that + and([x_ExplicitVarSizeWithDummy[q6] != 6 -> + or([a_Explicit[q8] = x_ExplicitVarSizeWithDummy[q6] + | q8 : int(1..fin1), or([b_Explicit[q10] = a_Explicit[q8] | q10 : int(1..fin2)])]) + | q6 : int(1..6)]), + and([or([x_ExplicitVarSizeWithDummy[q14] != 6 /\ x_ExplicitVarSizeWithDummy[q14] = a_Explicit[q12] + | q14 : int(1..6)]) + | q12 : int(1..fin1), or([b_Explicit[q16] = a_Explicit[q12] | q16 : int(1..fin2)])]), + and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 6 + | q1 : int(1..5)]), + and([x_ExplicitVarSizeWithDummy[q2] = 6 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 6 | q2 : int(1..5)]) + diff --git a/tests/exhaustive/issues/212/expected/model_2_3-1-solution000001.solution b/tests/exhaustive/issues/212/expected/model_2_3-1-solution000001.solution new file mode 100644 index 0000000000..de5cc861ad --- /dev/null +++ b/tests/exhaustive/issues/212/expected/model_2_3-1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1} diff --git a/tests/exhaustive/issues/212/expected/model_2_3-1.eprime-param b/tests/exhaustive/issues/212/expected/model_2_3-1.eprime-param new file mode 100644 index 0000000000..c50b6e81fd --- /dev/null +++ b/tests/exhaustive/issues/212/expected/model_2_3-1.eprime-param @@ -0,0 +1,6 @@ +language ESSENCE' 1.0 + +letting a_Explicit be [1, 2; int(1..2)] +letting b_Explicit be [1, 3; int(1..2)] +letting fin1 be 2 +letting fin2 be 2 diff --git a/tests/exhaustive/issues/212/expected/model_2_3.eprime b/tests/exhaustive/issues/212/expected/model_2_3.eprime new file mode 100644 index 0000000000..93e3af90d4 --- /dev/null +++ b/tests/exhaustive/issues/212/expected/model_2_3.eprime @@ -0,0 +1,36 @@ +language ESSENCE' 1.0 + +given fin1: int +given a_Explicit: matrix indexed by [int(1..fin1)] of int(0..5) +given fin2: int +given b_Explicit: matrix indexed by [int(1..fin2)] of int(0..5) +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..6)] of int(0..6) +find x_ExplicitVarSizeWithMarker_Marker: int(0..6) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..6)] of int(0..5) +branching on [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithDummy] +such that + and([x_ExplicitVarSizeWithDummy[q17] != 6 -> + or([a_Explicit[q19] = x_ExplicitVarSizeWithDummy[q17] + | q19 : int(1..fin1), or([b_Explicit[q21] = a_Explicit[q19] | q21 : int(1..fin2)])]) + | q17 : int(1..6)]), + and([or([x_ExplicitVarSizeWithDummy[q25] != 6 /\ x_ExplicitVarSizeWithDummy[q25] = a_Explicit[q23] + | q25 : int(1..6)]) + | q23 : int(1..fin1), or([b_Explicit[q27] = a_Explicit[q23] | q27 : int(1..fin2)])]), + and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 6 + | q1 : int(1..5)]), + and([x_ExplicitVarSizeWithDummy[q2] = 6 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 6 | q2 : int(1..5)]), + and([q5 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q5] < x_ExplicitVarSizeWithMarker_Values[q5 + 1] + | q5 : int(1..5)]), + and([q6 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q6] = 0 | q6 : int(1..6)]), + and([q9 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithDummy[q11] != 6 /\ + x_ExplicitVarSizeWithDummy[q11] = x_ExplicitVarSizeWithMarker_Values[q9] + | q11 : int(1..6)]) + | q9 : int(1..6)]), + and([x_ExplicitVarSizeWithDummy[q13] != 6 -> + or([q15 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q15] = x_ExplicitVarSizeWithDummy[q13] + | q15 : int(1..6)]) + | q13 : int(1..6)]) + diff --git a/tests/exhaustive/issues/212/expected/model_2_4-1-solution000001.solution b/tests/exhaustive/issues/212/expected/model_2_4-1-solution000001.solution new file mode 100644 index 0000000000..de5cc861ad --- /dev/null +++ b/tests/exhaustive/issues/212/expected/model_2_4-1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1} diff --git a/tests/exhaustive/issues/212/expected/model_2_4-1.eprime-param b/tests/exhaustive/issues/212/expected/model_2_4-1.eprime-param new file mode 100644 index 0000000000..c50b6e81fd --- /dev/null +++ b/tests/exhaustive/issues/212/expected/model_2_4-1.eprime-param @@ -0,0 +1,6 @@ +language ESSENCE' 1.0 + +letting a_Explicit be [1, 2; int(1..2)] +letting b_Explicit be [1, 3; int(1..2)] +letting fin1 be 2 +letting fin2 be 2 diff --git a/tests/exhaustive/issues/212/expected/model_2_4.eprime b/tests/exhaustive/issues/212/expected/model_2_4.eprime new file mode 100644 index 0000000000..a7493d7565 --- /dev/null +++ b/tests/exhaustive/issues/212/expected/model_2_4.eprime @@ -0,0 +1,37 @@ +language ESSENCE' 1.0 + +given fin1: int +given a_Explicit: matrix indexed by [int(1..fin1)] of int(0..5) +given fin2: int +given b_Explicit: matrix indexed by [int(1..fin2)] of int(0..5) +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..6)] of int(0..6) +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..6)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..6)] of int(0..5) +branching on [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithDummy] +such that + and([x_ExplicitVarSizeWithDummy[q19] != 6 -> + or([a_Explicit[q21] = x_ExplicitVarSizeWithDummy[q19] + | q21 : int(1..fin1), or([b_Explicit[q23] = a_Explicit[q21] | q23 : int(1..fin2)])]) + | q19 : int(1..6)]), + and([or([x_ExplicitVarSizeWithDummy[q27] != 6 /\ x_ExplicitVarSizeWithDummy[q27] = a_Explicit[q25] + | q27 : int(1..6)]) + | q25 : int(1..fin1), or([b_Explicit[q29] = a_Explicit[q25] | q29 : int(1..fin2)])]), + and([x_ExplicitVarSizeWithDummy[q1] < x_ExplicitVarSizeWithDummy[q1 + 1] \/ x_ExplicitVarSizeWithDummy[q1] = 6 + | q1 : int(1..5)]), + and([x_ExplicitVarSizeWithDummy[q2] = 6 -> x_ExplicitVarSizeWithDummy[q2 + 1] = 6 | q2 : int(1..5)]), + and([x_ExplicitVarSizeWithFlags_Flags[q5 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q5] < x_ExplicitVarSizeWithFlags_Values[q5 + 1] + | q5 : int(1..5)]), + and([x_ExplicitVarSizeWithFlags_Flags[q6] = false -> x_ExplicitVarSizeWithFlags_Values[q6] = 0 | q6 : int(1..6)]), + and([x_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q7] | q7 : int(1..5)]), + and([x_ExplicitVarSizeWithFlags_Flags[q11] -> + or([x_ExplicitVarSizeWithDummy[q13] != 6 /\ + x_ExplicitVarSizeWithDummy[q13] = x_ExplicitVarSizeWithFlags_Values[q11] + | q13 : int(1..6)]) + | q11 : int(1..6)]), + and([x_ExplicitVarSizeWithDummy[q15] != 6 -> + or([x_ExplicitVarSizeWithFlags_Flags[q17] /\ + x_ExplicitVarSizeWithFlags_Values[q17] = x_ExplicitVarSizeWithDummy[q15] + | q17 : int(1..6)]) + | q15 : int(1..6)]) + diff --git a/tests/exhaustive/issues/212/expected/model_3_1-1-solution000001.solution b/tests/exhaustive/issues/212/expected/model_3_1-1-solution000001.solution new file mode 100644 index 0000000000..de5cc861ad --- /dev/null +++ b/tests/exhaustive/issues/212/expected/model_3_1-1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1} diff --git a/tests/exhaustive/issues/212/expected/model_3_1-1.eprime-param b/tests/exhaustive/issues/212/expected/model_3_1-1.eprime-param new file mode 100644 index 0000000000..c50b6e81fd --- /dev/null +++ b/tests/exhaustive/issues/212/expected/model_3_1-1.eprime-param @@ -0,0 +1,6 @@ +language ESSENCE' 1.0 + +letting a_Explicit be [1, 2; int(1..2)] +letting b_Explicit be [1, 3; int(1..2)] +letting fin1 be 2 +letting fin2 be 2 diff --git a/tests/exhaustive/issues/212/expected/model_3_1.eprime b/tests/exhaustive/issues/212/expected/model_3_1.eprime new file mode 100644 index 0000000000..6308f8ed0c --- /dev/null +++ b/tests/exhaustive/issues/212/expected/model_3_1.eprime @@ -0,0 +1,29 @@ +language ESSENCE' 1.0 + +given fin1: int +given a_Explicit: matrix indexed by [int(1..fin1)] of int(0..5) +given fin2: int +given b_Explicit: matrix indexed by [int(1..fin2)] of int(0..5) +find x_ExplicitVarSizeWithMarker_Marker: int(0..6) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..6)] of int(0..5) +find x_Occurrence: matrix indexed by [int(0..5)] of bool +branching on [x_Occurrence, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] +such that + and([q6 <= x_ExplicitVarSizeWithMarker_Marker -> + or([a_Explicit[q8] = x_ExplicitVarSizeWithMarker_Values[q6] + | q8 : int(1..fin1), or([b_Explicit[q10] = a_Explicit[q8] | q10 : int(1..fin2)])]) + | q6 : int(1..6)]), + and([or([q14 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q14] = a_Explicit[q12] + | q14 : int(1..6)]) + | q12 : int(1..fin1), or([b_Explicit[q16] = a_Explicit[q12] | q16 : int(1..fin2)])]), + and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] + | q1 : int(1..5)]), + and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 0 | q2 : int(1..6)]), + and([x_Occurrence[q17] -> + or([q19 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q19] = q17 + | q19 : int(1..6)]) + | q17 : int(0..5)]), + and([q21 <= x_ExplicitVarSizeWithMarker_Marker -> x_Occurrence[x_ExplicitVarSizeWithMarker_Values[q21]] + | q21 : int(1..6)]) + diff --git a/tests/exhaustive/issues/212/expected/model_3_2-1-solution000001.solution b/tests/exhaustive/issues/212/expected/model_3_2-1-solution000001.solution new file mode 100644 index 0000000000..de5cc861ad --- /dev/null +++ b/tests/exhaustive/issues/212/expected/model_3_2-1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1} diff --git a/tests/exhaustive/issues/212/expected/model_3_2-1.eprime-param b/tests/exhaustive/issues/212/expected/model_3_2-1.eprime-param new file mode 100644 index 0000000000..c50b6e81fd --- /dev/null +++ b/tests/exhaustive/issues/212/expected/model_3_2-1.eprime-param @@ -0,0 +1,6 @@ +language ESSENCE' 1.0 + +letting a_Explicit be [1, 2; int(1..2)] +letting b_Explicit be [1, 3; int(1..2)] +letting fin1 be 2 +letting fin2 be 2 diff --git a/tests/exhaustive/issues/212/expected/model_3_2.eprime b/tests/exhaustive/issues/212/expected/model_3_2.eprime new file mode 100644 index 0000000000..364eb0520f --- /dev/null +++ b/tests/exhaustive/issues/212/expected/model_3_2.eprime @@ -0,0 +1,36 @@ +language ESSENCE' 1.0 + +given fin1: int +given a_Explicit: matrix indexed by [int(1..fin1)] of int(0..5) +given fin2: int +given b_Explicit: matrix indexed by [int(1..fin2)] of int(0..5) +find x_ExplicitVarSizeWithMarker_Marker: int(0..6) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..6)] of int(0..5) +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..6)] of int(0..6) +branching on [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] +such that + and([q17 <= x_ExplicitVarSizeWithMarker_Marker -> + or([a_Explicit[q19] = x_ExplicitVarSizeWithMarker_Values[q17] + | q19 : int(1..fin1), or([b_Explicit[q21] = a_Explicit[q19] | q21 : int(1..fin2)])]) + | q17 : int(1..6)]), + and([or([q25 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q25] = a_Explicit[q23] + | q25 : int(1..6)]) + | q23 : int(1..fin1), or([b_Explicit[q27] = a_Explicit[q23] | q27 : int(1..fin2)])]), + and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] + | q1 : int(1..5)]), + and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 0 | q2 : int(1..6)]), + and([x_ExplicitVarSizeWithDummy[q4] < x_ExplicitVarSizeWithDummy[q4 + 1] \/ x_ExplicitVarSizeWithDummy[q4] = 6 + | q4 : int(1..5)]), + and([x_ExplicitVarSizeWithDummy[q5] = 6 -> x_ExplicitVarSizeWithDummy[q5 + 1] = 6 | q5 : int(1..5)]), + and([x_ExplicitVarSizeWithDummy[q9] != 6 -> + or([q11 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q11] = x_ExplicitVarSizeWithDummy[q9] + | q11 : int(1..6)]) + | q9 : int(1..6)]), + and([q13 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithDummy[q15] != 6 /\ + x_ExplicitVarSizeWithDummy[q15] = x_ExplicitVarSizeWithMarker_Values[q13] + | q15 : int(1..6)]) + | q13 : int(1..6)]) + diff --git a/tests/exhaustive/issues/212/expected/model_3_3-1-solution000001.solution b/tests/exhaustive/issues/212/expected/model_3_3-1-solution000001.solution new file mode 100644 index 0000000000..de5cc861ad --- /dev/null +++ b/tests/exhaustive/issues/212/expected/model_3_3-1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1} diff --git a/tests/exhaustive/issues/212/expected/model_3_3-1.eprime-param b/tests/exhaustive/issues/212/expected/model_3_3-1.eprime-param new file mode 100644 index 0000000000..c50b6e81fd --- /dev/null +++ b/tests/exhaustive/issues/212/expected/model_3_3-1.eprime-param @@ -0,0 +1,6 @@ +language ESSENCE' 1.0 + +letting a_Explicit be [1, 2; int(1..2)] +letting b_Explicit be [1, 3; int(1..2)] +letting fin1 be 2 +letting fin2 be 2 diff --git a/tests/exhaustive/issues/212/expected/model_3_3.eprime b/tests/exhaustive/issues/212/expected/model_3_3.eprime new file mode 100644 index 0000000000..c3326d4adb --- /dev/null +++ b/tests/exhaustive/issues/212/expected/model_3_3.eprime @@ -0,0 +1,22 @@ +language ESSENCE' 1.0 + +given fin1: int +given a_Explicit: matrix indexed by [int(1..fin1)] of int(0..5) +given fin2: int +given b_Explicit: matrix indexed by [int(1..fin2)] of int(0..5) +find x_ExplicitVarSizeWithMarker_Marker: int(0..6) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..6)] of int(0..5) +branching on [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] +such that + and([q5 <= x_ExplicitVarSizeWithMarker_Marker -> + or([a_Explicit[q7] = x_ExplicitVarSizeWithMarker_Values[q5] + | q7 : int(1..fin1), or([b_Explicit[q9] = a_Explicit[q7] | q9 : int(1..fin2)])]) + | q5 : int(1..6)]), + and([or([q13 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q13] = a_Explicit[q11] + | q13 : int(1..6)]) + | q11 : int(1..fin1), or([b_Explicit[q15] = a_Explicit[q11] | q15 : int(1..fin2)])]), + and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] + | q1 : int(1..5)]), + and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 0 | q2 : int(1..6)]) + diff --git a/tests/exhaustive/issues/212/expected/model_3_4-1-solution000001.solution b/tests/exhaustive/issues/212/expected/model_3_4-1-solution000001.solution new file mode 100644 index 0000000000..de5cc861ad --- /dev/null +++ b/tests/exhaustive/issues/212/expected/model_3_4-1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1} diff --git a/tests/exhaustive/issues/212/expected/model_3_4-1.eprime-param b/tests/exhaustive/issues/212/expected/model_3_4-1.eprime-param new file mode 100644 index 0000000000..c50b6e81fd --- /dev/null +++ b/tests/exhaustive/issues/212/expected/model_3_4-1.eprime-param @@ -0,0 +1,6 @@ +language ESSENCE' 1.0 + +letting a_Explicit be [1, 2; int(1..2)] +letting b_Explicit be [1, 3; int(1..2)] +letting fin1 be 2 +letting fin2 be 2 diff --git a/tests/exhaustive/issues/212/expected/model_3_4.eprime b/tests/exhaustive/issues/212/expected/model_3_4.eprime new file mode 100644 index 0000000000..eefd4567b9 --- /dev/null +++ b/tests/exhaustive/issues/212/expected/model_3_4.eprime @@ -0,0 +1,41 @@ +language ESSENCE' 1.0 + +given fin1: int +given a_Explicit: matrix indexed by [int(1..fin1)] of int(0..5) +given fin2: int +given b_Explicit: matrix indexed by [int(1..fin2)] of int(0..5) +find x_ExplicitVarSizeWithMarker_Marker: int(0..6) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..6)] of int(0..5) +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..6)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..6)] of int(0..5) +branching on + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithMarker_Marker, + x_ExplicitVarSizeWithMarker_Values] +such that + and([q18 <= x_ExplicitVarSizeWithMarker_Marker -> + or([a_Explicit[q20] = x_ExplicitVarSizeWithMarker_Values[q18] + | q20 : int(1..fin1), or([b_Explicit[q22] = a_Explicit[q20] | q22 : int(1..fin2)])]) + | q18 : int(1..6)]), + and([or([q26 <= x_ExplicitVarSizeWithMarker_Marker /\ x_ExplicitVarSizeWithMarker_Values[q26] = a_Explicit[q24] + | q26 : int(1..6)]) + | q24 : int(1..fin1), or([b_Explicit[q28] = a_Explicit[q24] | q28 : int(1..fin2)])]), + and([q1 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q1] < x_ExplicitVarSizeWithMarker_Values[q1 + 1] + | q1 : int(1..5)]), + and([q2 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q2] = 0 | q2 : int(1..6)]), + and([x_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q4] < x_ExplicitVarSizeWithFlags_Values[q4 + 1] + | q4 : int(1..5)]), + and([x_ExplicitVarSizeWithFlags_Flags[q5] = false -> x_ExplicitVarSizeWithFlags_Values[q5] = 0 | q5 : int(1..6)]), + and([x_ExplicitVarSizeWithFlags_Flags[q6 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q6] | q6 : int(1..5)]), + and([x_ExplicitVarSizeWithFlags_Flags[q10] -> + or([q12 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q12] = x_ExplicitVarSizeWithFlags_Values[q10] + | q12 : int(1..6)]) + | q10 : int(1..6)]), + and([q14 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithFlags_Flags[q16] /\ + x_ExplicitVarSizeWithFlags_Values[q16] = x_ExplicitVarSizeWithMarker_Values[q14] + | q16 : int(1..6)]) + | q14 : int(1..6)]) + diff --git a/tests/exhaustive/issues/212/expected/model_4_1-1-solution000001.solution b/tests/exhaustive/issues/212/expected/model_4_1-1-solution000001.solution new file mode 100644 index 0000000000..de5cc861ad --- /dev/null +++ b/tests/exhaustive/issues/212/expected/model_4_1-1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1} diff --git a/tests/exhaustive/issues/212/expected/model_4_1-1.eprime-param b/tests/exhaustive/issues/212/expected/model_4_1-1.eprime-param new file mode 100644 index 0000000000..c50b6e81fd --- /dev/null +++ b/tests/exhaustive/issues/212/expected/model_4_1-1.eprime-param @@ -0,0 +1,6 @@ +language ESSENCE' 1.0 + +letting a_Explicit be [1, 2; int(1..2)] +letting b_Explicit be [1, 3; int(1..2)] +letting fin1 be 2 +letting fin2 be 2 diff --git a/tests/exhaustive/issues/212/expected/model_4_1.eprime b/tests/exhaustive/issues/212/expected/model_4_1.eprime new file mode 100644 index 0000000000..3f9ecf24e4 --- /dev/null +++ b/tests/exhaustive/issues/212/expected/model_4_1.eprime @@ -0,0 +1,29 @@ +language ESSENCE' 1.0 + +given fin1: int +given a_Explicit: matrix indexed by [int(1..fin1)] of int(0..5) +given fin2: int +given b_Explicit: matrix indexed by [int(1..fin2)] of int(0..5) +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..6)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..6)] of int(0..5) +find x_Occurrence: matrix indexed by [int(0..5)] of bool +branching on [x_Occurrence, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] +such that + and([x_ExplicitVarSizeWithFlags_Flags[q8] -> + or([a_Explicit[q10] = x_ExplicitVarSizeWithFlags_Values[q8] + | q10 : int(1..fin1), or([b_Explicit[q12] = a_Explicit[q10] | q12 : int(1..fin2)])]) + | q8 : int(1..6)]), + and([or([x_ExplicitVarSizeWithFlags_Flags[q16] /\ x_ExplicitVarSizeWithFlags_Values[q16] = a_Explicit[q14] + | q16 : int(1..6)]) + | q14 : int(1..fin1), or([b_Explicit[q18] = a_Explicit[q14] | q18 : int(1..fin2)])]), + and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] + | q1 : int(1..5)]), + and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 0 | q2 : int(1..6)]), + and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..5)]), + and([x_Occurrence[q19] -> + or([x_ExplicitVarSizeWithFlags_Flags[q21] /\ x_ExplicitVarSizeWithFlags_Values[q21] = q19 | q21 : int(1..6)]) + | q19 : int(0..5)]), + and([x_ExplicitVarSizeWithFlags_Flags[q23] -> x_Occurrence[x_ExplicitVarSizeWithFlags_Values[q23]] + | q23 : int(1..6)]) + diff --git a/tests/exhaustive/issues/212/expected/model_4_2-1-solution000001.solution b/tests/exhaustive/issues/212/expected/model_4_2-1-solution000001.solution new file mode 100644 index 0000000000..de5cc861ad --- /dev/null +++ b/tests/exhaustive/issues/212/expected/model_4_2-1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1} diff --git a/tests/exhaustive/issues/212/expected/model_4_2-1.eprime-param b/tests/exhaustive/issues/212/expected/model_4_2-1.eprime-param new file mode 100644 index 0000000000..c50b6e81fd --- /dev/null +++ b/tests/exhaustive/issues/212/expected/model_4_2-1.eprime-param @@ -0,0 +1,6 @@ +language ESSENCE' 1.0 + +letting a_Explicit be [1, 2; int(1..2)] +letting b_Explicit be [1, 3; int(1..2)] +letting fin1 be 2 +letting fin2 be 2 diff --git a/tests/exhaustive/issues/212/expected/model_4_2.eprime b/tests/exhaustive/issues/212/expected/model_4_2.eprime new file mode 100644 index 0000000000..4d34fb6bca --- /dev/null +++ b/tests/exhaustive/issues/212/expected/model_4_2.eprime @@ -0,0 +1,37 @@ +language ESSENCE' 1.0 + +given fin1: int +given a_Explicit: matrix indexed by [int(1..fin1)] of int(0..5) +given fin2: int +given b_Explicit: matrix indexed by [int(1..fin2)] of int(0..5) +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..6)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..6)] of int(0..5) +find x_ExplicitVarSizeWithDummy: matrix indexed by [int(1..6)] of int(0..6) +branching on [x_ExplicitVarSizeWithDummy, x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] +such that + and([x_ExplicitVarSizeWithFlags_Flags[q19] -> + or([a_Explicit[q21] = x_ExplicitVarSizeWithFlags_Values[q19] + | q21 : int(1..fin1), or([b_Explicit[q23] = a_Explicit[q21] | q23 : int(1..fin2)])]) + | q19 : int(1..6)]), + and([or([x_ExplicitVarSizeWithFlags_Flags[q27] /\ x_ExplicitVarSizeWithFlags_Values[q27] = a_Explicit[q25] + | q27 : int(1..6)]) + | q25 : int(1..fin1), or([b_Explicit[q29] = a_Explicit[q25] | q29 : int(1..fin2)])]), + and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] + | q1 : int(1..5)]), + and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 0 | q2 : int(1..6)]), + and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..5)]), + and([x_ExplicitVarSizeWithDummy[q6] < x_ExplicitVarSizeWithDummy[q6 + 1] \/ x_ExplicitVarSizeWithDummy[q6] = 6 + | q6 : int(1..5)]), + and([x_ExplicitVarSizeWithDummy[q7] = 6 -> x_ExplicitVarSizeWithDummy[q7 + 1] = 6 | q7 : int(1..5)]), + and([x_ExplicitVarSizeWithDummy[q11] != 6 -> + or([x_ExplicitVarSizeWithFlags_Flags[q13] /\ + x_ExplicitVarSizeWithFlags_Values[q13] = x_ExplicitVarSizeWithDummy[q11] + | q13 : int(1..6)]) + | q11 : int(1..6)]), + and([x_ExplicitVarSizeWithFlags_Flags[q15] -> + or([x_ExplicitVarSizeWithDummy[q17] != 6 /\ + x_ExplicitVarSizeWithDummy[q17] = x_ExplicitVarSizeWithFlags_Values[q15] + | q17 : int(1..6)]) + | q15 : int(1..6)]) + diff --git a/tests/exhaustive/issues/212/expected/model_4_3-1-solution000001.solution b/tests/exhaustive/issues/212/expected/model_4_3-1-solution000001.solution new file mode 100644 index 0000000000..de5cc861ad --- /dev/null +++ b/tests/exhaustive/issues/212/expected/model_4_3-1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1} diff --git a/tests/exhaustive/issues/212/expected/model_4_3-1.eprime-param b/tests/exhaustive/issues/212/expected/model_4_3-1.eprime-param new file mode 100644 index 0000000000..c50b6e81fd --- /dev/null +++ b/tests/exhaustive/issues/212/expected/model_4_3-1.eprime-param @@ -0,0 +1,6 @@ +language ESSENCE' 1.0 + +letting a_Explicit be [1, 2; int(1..2)] +letting b_Explicit be [1, 3; int(1..2)] +letting fin1 be 2 +letting fin2 be 2 diff --git a/tests/exhaustive/issues/212/expected/model_4_3.eprime b/tests/exhaustive/issues/212/expected/model_4_3.eprime new file mode 100644 index 0000000000..44a997c6a7 --- /dev/null +++ b/tests/exhaustive/issues/212/expected/model_4_3.eprime @@ -0,0 +1,41 @@ +language ESSENCE' 1.0 + +given fin1: int +given a_Explicit: matrix indexed by [int(1..fin1)] of int(0..5) +given fin2: int +given b_Explicit: matrix indexed by [int(1..fin2)] of int(0..5) +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..6)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..6)] of int(0..5) +find x_ExplicitVarSizeWithMarker_Marker: int(0..6) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..6)] of int(0..5) +branching on + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithFlags_Flags, + x_ExplicitVarSizeWithFlags_Values] +such that + and([x_ExplicitVarSizeWithFlags_Flags[q18] -> + or([a_Explicit[q20] = x_ExplicitVarSizeWithFlags_Values[q18] + | q20 : int(1..fin1), or([b_Explicit[q22] = a_Explicit[q20] | q22 : int(1..fin2)])]) + | q18 : int(1..6)]), + and([or([x_ExplicitVarSizeWithFlags_Flags[q26] /\ x_ExplicitVarSizeWithFlags_Values[q26] = a_Explicit[q24] + | q26 : int(1..6)]) + | q24 : int(1..fin1), or([b_Explicit[q28] = a_Explicit[q24] | q28 : int(1..fin2)])]), + and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] + | q1 : int(1..5)]), + and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 0 | q2 : int(1..6)]), + and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..5)]), + and([q6 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q6] < x_ExplicitVarSizeWithMarker_Values[q6 + 1] + | q6 : int(1..5)]), + and([q7 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q7] = 0 | q7 : int(1..6)]), + and([q10 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithFlags_Flags[q12] /\ + x_ExplicitVarSizeWithFlags_Values[q12] = x_ExplicitVarSizeWithMarker_Values[q10] + | q12 : int(1..6)]) + | q10 : int(1..6)]), + and([x_ExplicitVarSizeWithFlags_Flags[q14] -> + or([q16 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q16] = x_ExplicitVarSizeWithFlags_Values[q14] + | q16 : int(1..6)]) + | q14 : int(1..6)]) + diff --git a/tests/exhaustive/issues/212/expected/model_4_4-1-solution000001.solution b/tests/exhaustive/issues/212/expected/model_4_4-1-solution000001.solution new file mode 100644 index 0000000000..de5cc861ad --- /dev/null +++ b/tests/exhaustive/issues/212/expected/model_4_4-1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {1} diff --git a/tests/exhaustive/issues/212/expected/model_4_4-1.eprime-param b/tests/exhaustive/issues/212/expected/model_4_4-1.eprime-param new file mode 100644 index 0000000000..c50b6e81fd --- /dev/null +++ b/tests/exhaustive/issues/212/expected/model_4_4-1.eprime-param @@ -0,0 +1,6 @@ +language ESSENCE' 1.0 + +letting a_Explicit be [1, 2; int(1..2)] +letting b_Explicit be [1, 3; int(1..2)] +letting fin1 be 2 +letting fin2 be 2 diff --git a/tests/exhaustive/issues/212/expected/model_4_4.eprime b/tests/exhaustive/issues/212/expected/model_4_4.eprime new file mode 100644 index 0000000000..fa1f37afc2 --- /dev/null +++ b/tests/exhaustive/issues/212/expected/model_4_4.eprime @@ -0,0 +1,23 @@ +language ESSENCE' 1.0 + +given fin1: int +given a_Explicit: matrix indexed by [int(1..fin1)] of int(0..5) +given fin2: int +given b_Explicit: matrix indexed by [int(1..fin2)] of int(0..5) +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..6)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..6)] of int(0..5) +branching on [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] +such that + and([x_ExplicitVarSizeWithFlags_Flags[q7] -> + or([a_Explicit[q9] = x_ExplicitVarSizeWithFlags_Values[q7] + | q9 : int(1..fin1), or([b_Explicit[q11] = a_Explicit[q9] | q11 : int(1..fin2)])]) + | q7 : int(1..6)]), + and([or([x_ExplicitVarSizeWithFlags_Flags[q15] /\ x_ExplicitVarSizeWithFlags_Values[q15] = a_Explicit[q13] + | q15 : int(1..6)]) + | q13 : int(1..fin1), or([b_Explicit[q17] = a_Explicit[q13] | q17 : int(1..fin2)])]), + and([x_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q1] < x_ExplicitVarSizeWithFlags_Values[q1 + 1] + | q1 : int(1..5)]), + and([x_ExplicitVarSizeWithFlags_Flags[q2] = false -> x_ExplicitVarSizeWithFlags_Values[q2] = 0 | q2 : int(1..6)]), + and([x_ExplicitVarSizeWithFlags_Flags[q3 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q3] | q3 : int(1..5)]) + diff --git a/tests/exhaustive/issues/261/expected/model_1.eprime b/tests/exhaustive/issues/261/expected/model_1.eprime index 6693ff9f73..a27aa5863f 100644 --- a/tests/exhaustive/issues/261/expected/model_1.eprime +++ b/tests/exhaustive/issues/261/expected/model_1.eprime @@ -8,7 +8,7 @@ branching on [a_Function1DPartial_Flags, a_Function1DPartial_Values] such that and([a_Function1DPartial_Flags[q1] /\ a_Function1DPartial_Flags[q2] -> a_Function1DPartial_Values[q1] != a_Function1DPartial_Values[q2] - | q1 : int(0..let1), q2 : int(0..let1), [q1; int(1)] a_Function1DPartial_Values[q5] = 1 | q5 : int(0..let1)]) diff --git a/tests/exhaustive/issues/286/expected/model_1_1-p1-solution000001.solution b/tests/exhaustive/issues/286/expected/model_1_1-p1-solution000001.solution new file mode 100644 index 0000000000..8f7fa48018 --- /dev/null +++ b/tests/exhaustive/issues/286/expected/model_1_1-p1-solution000001.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting p be partition({1, 2, 3, 4}) +$ Visualisation for p +$ 1 2 3 4 + diff --git a/tests/exhaustive/issues/286/expected/model_1_1-p1-solution000002.solution b/tests/exhaustive/issues/286/expected/model_1_1-p1-solution000002.solution new file mode 100644 index 0000000000..cd8086fa4a --- /dev/null +++ b/tests/exhaustive/issues/286/expected/model_1_1-p1-solution000002.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting p be partition({1}, {2, 3, 4}) +$ Visualisation for p +$ 1 +$ 2 3 4 + diff --git a/tests/exhaustive/issues/286/expected/model_1_1-p1-solution000003.solution b/tests/exhaustive/issues/286/expected/model_1_1-p1-solution000003.solution new file mode 100644 index 0000000000..69d6c9f6be --- /dev/null +++ b/tests/exhaustive/issues/286/expected/model_1_1-p1-solution000003.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting p be partition({1, 4}, {2, 3}) +$ Visualisation for p +$ 1 4 +$ 2 3 + diff --git a/tests/exhaustive/issues/286/expected/model_1_1-p1-solution000004.solution b/tests/exhaustive/issues/286/expected/model_1_1-p1-solution000004.solution new file mode 100644 index 0000000000..dafa529443 --- /dev/null +++ b/tests/exhaustive/issues/286/expected/model_1_1-p1-solution000004.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting p be partition({1, 3}, {2, 4}) +$ Visualisation for p +$ 1 3 +$ 2 4 + diff --git a/tests/exhaustive/issues/286/expected/model_1_1-p1-solution000005.solution b/tests/exhaustive/issues/286/expected/model_1_1-p1-solution000005.solution new file mode 100644 index 0000000000..0368fc950b --- /dev/null +++ b/tests/exhaustive/issues/286/expected/model_1_1-p1-solution000005.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting p be partition({1, 3, 4}, {2}) +$ Visualisation for p +$ 1 3 4 +$ 2 + diff --git a/tests/exhaustive/issues/286/expected/model_1_1-p1-solution000006.solution b/tests/exhaustive/issues/286/expected/model_1_1-p1-solution000006.solution new file mode 100644 index 0000000000..1507fcc0c1 --- /dev/null +++ b/tests/exhaustive/issues/286/expected/model_1_1-p1-solution000006.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting p be partition({1, 2}, {3, 4}) +$ Visualisation for p +$ 1 2 +$ 3 4 + diff --git a/tests/exhaustive/issues/286/expected/model_1_1-p1-solution000007.solution b/tests/exhaustive/issues/286/expected/model_1_1-p1-solution000007.solution new file mode 100644 index 0000000000..7781800dc4 --- /dev/null +++ b/tests/exhaustive/issues/286/expected/model_1_1-p1-solution000007.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting p be partition({1, 2, 4}, {3}) +$ Visualisation for p +$ 1 2 4 +$ 3 + diff --git a/tests/exhaustive/issues/286/expected/model_1_1-p1-solution000008.solution b/tests/exhaustive/issues/286/expected/model_1_1-p1-solution000008.solution new file mode 100644 index 0000000000..556f2c0ecc --- /dev/null +++ b/tests/exhaustive/issues/286/expected/model_1_1-p1-solution000008.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting p be partition({1, 2, 3}, {4}) +$ Visualisation for p +$ 1 2 3 +$ 4 + diff --git a/tests/exhaustive/issues/286/expected/model_1_1-p1.eprime-param b/tests/exhaustive/issues/286/expected/model_1_1-p1.eprime-param new file mode 100644 index 0000000000..85954307ca --- /dev/null +++ b/tests/exhaustive/issues/286/expected/model_1_1-p1.eprime-param @@ -0,0 +1,3 @@ +language ESSENCE' 1.0 + +letting b be 4 diff --git a/tests/exhaustive/issues/286/expected/model_1_1.eprime b/tests/exhaustive/issues/286/expected/model_1_1.eprime new file mode 100644 index 0000000000..aa35b895fb --- /dev/null +++ b/tests/exhaustive/issues/286/expected/model_1_1.eprime @@ -0,0 +1,43 @@ +language ESSENCE' 1.0 + +given b: int +find p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker: int(0..b) +find p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence: matrix indexed by [int(1..b), int(1..b)] of bool +branching on + [p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker, + p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence] +such that + sum([toInt(q19 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker) | q19 : int(1..b)]) <= + sum([1 | q20_ExplicitVarSizeWithDummy : matrix indexed by [int(1..b)] of int(1..b + 1), + and([q20_ExplicitVarSizeWithDummy[q21] < q20_ExplicitVarSizeWithDummy[q21 + 1] \/ + q20_ExplicitVarSizeWithDummy[q21] = b + 1 + | q21 : int(1..b - 1)]), + and([q20_ExplicitVarSizeWithDummy[q22] = b + 1 -> q20_ExplicitVarSizeWithDummy[q22 + 1] = b + 1 + | q22 : int(1..b - 1)])]) + / 8, + and([1 = + sum([toInt(q9 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ + p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q9, q1]) + | q9 : int(1..b)]) + | q1 : int(1..b)]), + and([q15 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> + sum([toInt(p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q15, q16]) | q16 : int(1..b)]) >= 1 + | q15 : int(1..b)]), + and([q4 + 1 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> + [-toInt(p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q4, q10]) | q10 : int(1..b)] p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> + and([p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q5, q12] = false | q12 : int(1..b)]) + | q5 : int(1..b)]), + p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker <= b, + and([q6 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> + sum([toInt(p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q6, q7]) | q7 : int(1..b)]) <= b + | q6 : int(1..b)]), + b = + sum([toInt(q13 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker) * + catchUndef(sum([toInt(p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q13, q14]) + | q14 : int(1..b)]), + 0) + | q13 : int(1..b)]) + diff --git a/tests/exhaustive/issues/286/expected/model_1_2-p1-solution000001.solution b/tests/exhaustive/issues/286/expected/model_1_2-p1-solution000001.solution new file mode 100644 index 0000000000..8f7fa48018 --- /dev/null +++ b/tests/exhaustive/issues/286/expected/model_1_2-p1-solution000001.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting p be partition({1, 2, 3, 4}) +$ Visualisation for p +$ 1 2 3 4 + diff --git a/tests/exhaustive/issues/286/expected/model_1_2-p1-solution000002.solution b/tests/exhaustive/issues/286/expected/model_1_2-p1-solution000002.solution new file mode 100644 index 0000000000..556f2c0ecc --- /dev/null +++ b/tests/exhaustive/issues/286/expected/model_1_2-p1-solution000002.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting p be partition({1, 2, 3}, {4}) +$ Visualisation for p +$ 1 2 3 +$ 4 + diff --git a/tests/exhaustive/issues/286/expected/model_1_2-p1-solution000003.solution b/tests/exhaustive/issues/286/expected/model_1_2-p1-solution000003.solution new file mode 100644 index 0000000000..7781800dc4 --- /dev/null +++ b/tests/exhaustive/issues/286/expected/model_1_2-p1-solution000003.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting p be partition({1, 2, 4}, {3}) +$ Visualisation for p +$ 1 2 4 +$ 3 + diff --git a/tests/exhaustive/issues/286/expected/model_1_2-p1-solution000004.solution b/tests/exhaustive/issues/286/expected/model_1_2-p1-solution000004.solution new file mode 100644 index 0000000000..1507fcc0c1 --- /dev/null +++ b/tests/exhaustive/issues/286/expected/model_1_2-p1-solution000004.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting p be partition({1, 2}, {3, 4}) +$ Visualisation for p +$ 1 2 +$ 3 4 + diff --git a/tests/exhaustive/issues/286/expected/model_1_2-p1-solution000005.solution b/tests/exhaustive/issues/286/expected/model_1_2-p1-solution000005.solution new file mode 100644 index 0000000000..0368fc950b --- /dev/null +++ b/tests/exhaustive/issues/286/expected/model_1_2-p1-solution000005.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting p be partition({1, 3, 4}, {2}) +$ Visualisation for p +$ 1 3 4 +$ 2 + diff --git a/tests/exhaustive/issues/286/expected/model_1_2-p1-solution000006.solution b/tests/exhaustive/issues/286/expected/model_1_2-p1-solution000006.solution new file mode 100644 index 0000000000..dafa529443 --- /dev/null +++ b/tests/exhaustive/issues/286/expected/model_1_2-p1-solution000006.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting p be partition({1, 3}, {2, 4}) +$ Visualisation for p +$ 1 3 +$ 2 4 + diff --git a/tests/exhaustive/issues/286/expected/model_1_2-p1-solution000007.solution b/tests/exhaustive/issues/286/expected/model_1_2-p1-solution000007.solution new file mode 100644 index 0000000000..69d6c9f6be --- /dev/null +++ b/tests/exhaustive/issues/286/expected/model_1_2-p1-solution000007.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting p be partition({1, 4}, {2, 3}) +$ Visualisation for p +$ 1 4 +$ 2 3 + diff --git a/tests/exhaustive/issues/286/expected/model_1_2-p1-solution000008.solution b/tests/exhaustive/issues/286/expected/model_1_2-p1-solution000008.solution new file mode 100644 index 0000000000..cd8086fa4a --- /dev/null +++ b/tests/exhaustive/issues/286/expected/model_1_2-p1-solution000008.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting p be partition({1}, {2, 3, 4}) +$ Visualisation for p +$ 1 +$ 2 3 4 + diff --git a/tests/exhaustive/issues/286/expected/model_1_2-p1.eprime-param b/tests/exhaustive/issues/286/expected/model_1_2-p1.eprime-param new file mode 100644 index 0000000000..85954307ca --- /dev/null +++ b/tests/exhaustive/issues/286/expected/model_1_2-p1.eprime-param @@ -0,0 +1,3 @@ +language ESSENCE' 1.0 + +letting b be 4 diff --git a/tests/exhaustive/issues/286/expected/model_1_2.eprime b/tests/exhaustive/issues/286/expected/model_1_2.eprime new file mode 100644 index 0000000000..6777d21139 --- /dev/null +++ b/tests/exhaustive/issues/286/expected/model_1_2.eprime @@ -0,0 +1,122 @@ +language ESSENCE' 1.0 + +given b: int +find p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker: int(0..b) +find p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence: matrix indexed by [int(1..b), int(1..b)] of bool +find p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker: int(0..b) +find p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy: + matrix indexed by [int(1..b), int(1..b)] of int(1..b + 1) +branching on + [p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker, + p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy, + p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker, + p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence] +such that + sum([toInt(q63 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker) | q63 : int(1..b)]) <= + sum([1 | q64_ExplicitVarSizeWithDummy : matrix indexed by [int(1..b)] of int(1..b + 1), + and([q64_ExplicitVarSizeWithDummy[q65] < q64_ExplicitVarSizeWithDummy[q65 + 1] \/ + q64_ExplicitVarSizeWithDummy[q65] = b + 1 + | q65 : int(1..b - 1)]), + and([q64_ExplicitVarSizeWithDummy[q66] = b + 1 -> q64_ExplicitVarSizeWithDummy[q66 + 1] = b + 1 + | q66 : int(1..b - 1)])]) + / 8, + and([1 = + sum([toInt(q20 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ + p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q20, q1]) + | q20 : int(1..b)]) + | q1 : int(1..b)]), + and([q52 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> + sum([toInt(p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q52, q53]) | q53 : int(1..b)]) >= 1 + | q52 : int(1..b)]), + and([q4 + 1 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> + [-toInt(p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q4, q21]) | q21 : int(1..b)] p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> + and([p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q5, q23] = false | q23 : int(1..b)]) + | q5 : int(1..b)]), + p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker <= b, + and([q6 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> + sum([toInt(p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q6, q7]) | q7 : int(1..b)]) <= b + | q6 : int(1..b)]), + b = + sum([toInt(q54 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker) * + catchUndef(sum([toInt(p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q54, q55]) + | q55 : int(1..b)]), + 0) + | q54 : int(1..b)]), + alldifferent_except([toInt(q56 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ + p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q56, q57] != + b + 1) + * + catchUndef(p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q56, q57], + 0) + | q56 : int(1..b), q57 : int(1..b)], + 0), + and([q58 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> + sum([toInt(p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q58, q60] != b + 1) + | q60 : int(1..b)]) + >= 1 + | q58 : int(1..b)]), + and([q12 + 1 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> + [p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q12, q24] | q24 : int(1..b)] p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> + and([p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q13, q26] = 1 + | q26 : int(1..b)]) + | q13 : int(1..b)]), + p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker <= b, + and([q14 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> + and([p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q14, q15] < + p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q14, q15 + 1] + \/ p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q14, q15] = b + 1 + | q15 : int(1..b - 1)]) + | q14 : int(1..b)]), + and([q14 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> + and([p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q14, q16] = b + 1 -> + p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q14, q16 + 1] = b + 1 + | q16 : int(1..b - 1)]) + | q14 : int(1..b)]), + and([q14 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> + sum([toInt(p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q14, q17] != b + 1) + | q17 : int(1..b)]) + <= b + | q14 : int(1..b)]), + b = + sum([toInt(q27 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker) * + catchUndef(sum([toInt(p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q27, q29] != + b + 1) + | q29 : int(1..b)]), + 0) + | q27 : int(1..b)]), + and([q32 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> + or([q35 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ + (and([p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q35, q36] -> + or([p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q32, q38] != b + 1 + /\ p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q32, q38] = q36 + | q38 : int(1..b)]) + | q36 : int(1..b)]) + /\ + and([p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q32, q40] != b + 1 -> + p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence + [q35, p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q32, q40]] + | q40 : int(1..b)])) + | q35 : int(1..b)]) + | q32 : int(1..b)]), + and([q43 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> + or([q46 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ + (and([p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q46, q48] != b + 1 -> + p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence + [q43, p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q46, q48]] + | q48 : int(1..b)]) + /\ + and([p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q43, q49] -> + or([p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q46, q51] != b + 1 + /\ p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q46, q51] = q49 + | q51 : int(1..b)]) + | q49 : int(1..b)])) + | q46 : int(1..b)]) + | q43 : int(1..b)]) + diff --git a/tests/exhaustive/issues/286/expected/model_1_3-p1-solution000001.solution b/tests/exhaustive/issues/286/expected/model_1_3-p1-solution000001.solution new file mode 100644 index 0000000000..8f7fa48018 --- /dev/null +++ b/tests/exhaustive/issues/286/expected/model_1_3-p1-solution000001.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting p be partition({1, 2, 3, 4}) +$ Visualisation for p +$ 1 2 3 4 + diff --git a/tests/exhaustive/issues/286/expected/model_1_3-p1-solution000002.solution b/tests/exhaustive/issues/286/expected/model_1_3-p1-solution000002.solution new file mode 100644 index 0000000000..cd8086fa4a --- /dev/null +++ b/tests/exhaustive/issues/286/expected/model_1_3-p1-solution000002.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting p be partition({1}, {2, 3, 4}) +$ Visualisation for p +$ 1 +$ 2 3 4 + diff --git a/tests/exhaustive/issues/286/expected/model_1_3-p1-solution000003.solution b/tests/exhaustive/issues/286/expected/model_1_3-p1-solution000003.solution new file mode 100644 index 0000000000..0368fc950b --- /dev/null +++ b/tests/exhaustive/issues/286/expected/model_1_3-p1-solution000003.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting p be partition({1, 3, 4}, {2}) +$ Visualisation for p +$ 1 3 4 +$ 2 + diff --git a/tests/exhaustive/issues/286/expected/model_1_3-p1-solution000004.solution b/tests/exhaustive/issues/286/expected/model_1_3-p1-solution000004.solution new file mode 100644 index 0000000000..7781800dc4 --- /dev/null +++ b/tests/exhaustive/issues/286/expected/model_1_3-p1-solution000004.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting p be partition({1, 2, 4}, {3}) +$ Visualisation for p +$ 1 2 4 +$ 3 + diff --git a/tests/exhaustive/issues/286/expected/model_1_3-p1-solution000005.solution b/tests/exhaustive/issues/286/expected/model_1_3-p1-solution000005.solution new file mode 100644 index 0000000000..556f2c0ecc --- /dev/null +++ b/tests/exhaustive/issues/286/expected/model_1_3-p1-solution000005.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting p be partition({1, 2, 3}, {4}) +$ Visualisation for p +$ 1 2 3 +$ 4 + diff --git a/tests/exhaustive/issues/286/expected/model_1_3-p1-solution000006.solution b/tests/exhaustive/issues/286/expected/model_1_3-p1-solution000006.solution new file mode 100644 index 0000000000..1507fcc0c1 --- /dev/null +++ b/tests/exhaustive/issues/286/expected/model_1_3-p1-solution000006.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting p be partition({1, 2}, {3, 4}) +$ Visualisation for p +$ 1 2 +$ 3 4 + diff --git a/tests/exhaustive/issues/286/expected/model_1_3-p1-solution000007.solution b/tests/exhaustive/issues/286/expected/model_1_3-p1-solution000007.solution new file mode 100644 index 0000000000..dafa529443 --- /dev/null +++ b/tests/exhaustive/issues/286/expected/model_1_3-p1-solution000007.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting p be partition({1, 3}, {2, 4}) +$ Visualisation for p +$ 1 3 +$ 2 4 + diff --git a/tests/exhaustive/issues/286/expected/model_1_3-p1-solution000008.solution b/tests/exhaustive/issues/286/expected/model_1_3-p1-solution000008.solution new file mode 100644 index 0000000000..69d6c9f6be --- /dev/null +++ b/tests/exhaustive/issues/286/expected/model_1_3-p1-solution000008.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting p be partition({1, 4}, {2, 3}) +$ Visualisation for p +$ 1 4 +$ 2 3 + diff --git a/tests/exhaustive/issues/286/expected/model_1_3-p1.eprime-param b/tests/exhaustive/issues/286/expected/model_1_3-p1.eprime-param new file mode 100644 index 0000000000..85954307ca --- /dev/null +++ b/tests/exhaustive/issues/286/expected/model_1_3-p1.eprime-param @@ -0,0 +1,3 @@ +language ESSENCE' 1.0 + +letting b be 4 diff --git a/tests/exhaustive/issues/286/expected/model_1_3.eprime.orig b/tests/exhaustive/issues/286/expected/model_1_3.eprime.orig deleted file mode 100644 index dd27a70525..0000000000 --- a/tests/exhaustive/issues/286/expected/model_1_3.eprime.orig +++ /dev/null @@ -1,132 +0,0 @@ -language ESSENCE' 1.0 - -given b: int -find p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker: int(0..b) -find p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence: matrix indexed by [int(1..b), int(1..b)] of bool -find p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker: int(0..b) -find p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker: - matrix indexed by [int(1..b)] of int(0..b) -find p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values: - matrix indexed by [int(1..b), int(1..b)] of int(1..b) -branching on - [p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker, - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker, - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values, - p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker, - p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence] -such that - sum([toInt(q58 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker) | q58 : int(1..b)]) <= - sum([1 | q59_ExplicitVarSizeWithDummy : matrix indexed by [int(1..b)] of int(1..b + 1), - and([q59_ExplicitVarSizeWithDummy[q60] < q59_ExplicitVarSizeWithDummy[q60 + 1] \/ - q59_ExplicitVarSizeWithDummy[q60] = b + 1 - | q60 : int(1..b - 1)]), - and([q59_ExplicitVarSizeWithDummy[q61] = b + 1 -> q59_ExplicitVarSizeWithDummy[q61 + 1] = b + 1 - | q61 : int(1..b - 1)])]) - / 8, - and([1 = - sum([toInt(q19 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ - p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q19, q1]) - | q19 : int(1..b)]) - | q1 : int(1..b)]), - and([q49 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> - sum([toInt(p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q49, q50]) | q50 : int(1..b)]) >= 1 - | q49 : int(1..b)]), - and([q4 + 1 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> - [-toInt(p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q4, q20]) | q20 : int(1..b)] p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> - and([p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q5, q22] = false | q22 : int(1..b)]) - | q5 : int(1..b)]), - p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker <= b, - and([q6 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> - sum([toInt(p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q6, q7]) | q7 : int(1..b)]) <= b - | q6 : int(1..b)]), - b = - sum([toInt(q51 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker) * - catchUndef(sum([toInt(p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q51, q52]) - | q52 : int(1..b)]), - 0) - | q51 : int(1..b)]), - alldifferent_except([toInt(q53 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - q54 <= - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q53]) - * - catchUndef(p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q53, q54], - 0) - | q53 : int(1..b), q54 : int(1..b)], - 0), - and([q55 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q55] >= 1 - | q55 : int(1..b)]), - and([q12 + 1 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - flatten([[p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q12]; int(1)], - [p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q12, q23] - | q23 : int(1..b)]; - int(1..2)]) - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q13] = 0 /\ - and([p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q13, q25] = 1 - | q25 : int(1..b)]) - | q13 : int(1..b)]), - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker <= b, - and([q14 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - and([q15 + 1 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q14] -> - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q14, q15] < - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q14, q15 + 1] - | q15 : int(1..b - 1)]) - | q14 : int(1..b)]), - and([q14 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - and([q16 > p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q14] -> - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q14, q16] = 1 - | q16 : int(1..b)]) - | q14 : int(1..b)]), - and([q14 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q14] <= b - | q14 : int(1..b)]), - b = - sum([toInt(q26 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker) * - catchUndef(p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q26], 0) - | q26 : int(1..b)]), - and([q29 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - or([q32 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ - (and([p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q32, q33] -> - or([q35 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q29] - /\ - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q29, q35] = - q33 | q35 : int(1..b)]) - | q33 : int(1..b)]) - /\ - and([q37 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q29] -> - p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence - [q32, - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q29, q37]] - | q37 : int(1..b)])) - | q32 : int(1..b)]) - | q29 : int(1..b)]), - and([q40 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> - or([q43 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - (and([q45 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q43] -> - p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence - [q40, - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q43, q45]] - | q45 : int(1..b)]) - /\ - and([p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q40, q46] -> - or([q48 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q43] - /\ - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q43, q48] = - q46 | q48 : int(1..b)]) - | q46 : int(1..b)])) - | q43 : int(1..b)]) - | q40 : int(1..b)]) - diff --git a/tests/exhaustive/issues/286/expected/model_1_4-p1-solution000001.solution b/tests/exhaustive/issues/286/expected/model_1_4-p1-solution000001.solution new file mode 100644 index 0000000000..8f7fa48018 --- /dev/null +++ b/tests/exhaustive/issues/286/expected/model_1_4-p1-solution000001.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting p be partition({1, 2, 3, 4}) +$ Visualisation for p +$ 1 2 3 4 + diff --git a/tests/exhaustive/issues/286/expected/model_1_4-p1-solution000002.solution b/tests/exhaustive/issues/286/expected/model_1_4-p1-solution000002.solution new file mode 100644 index 0000000000..556f2c0ecc --- /dev/null +++ b/tests/exhaustive/issues/286/expected/model_1_4-p1-solution000002.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting p be partition({1, 2, 3}, {4}) +$ Visualisation for p +$ 1 2 3 +$ 4 + diff --git a/tests/exhaustive/issues/286/expected/model_1_4-p1-solution000003.solution b/tests/exhaustive/issues/286/expected/model_1_4-p1-solution000003.solution new file mode 100644 index 0000000000..7781800dc4 --- /dev/null +++ b/tests/exhaustive/issues/286/expected/model_1_4-p1-solution000003.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting p be partition({1, 2, 4}, {3}) +$ Visualisation for p +$ 1 2 4 +$ 3 + diff --git a/tests/exhaustive/issues/286/expected/model_1_4-p1-solution000004.solution b/tests/exhaustive/issues/286/expected/model_1_4-p1-solution000004.solution new file mode 100644 index 0000000000..1507fcc0c1 --- /dev/null +++ b/tests/exhaustive/issues/286/expected/model_1_4-p1-solution000004.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting p be partition({1, 2}, {3, 4}) +$ Visualisation for p +$ 1 2 +$ 3 4 + diff --git a/tests/exhaustive/issues/286/expected/model_1_4-p1-solution000005.solution b/tests/exhaustive/issues/286/expected/model_1_4-p1-solution000005.solution new file mode 100644 index 0000000000..0368fc950b --- /dev/null +++ b/tests/exhaustive/issues/286/expected/model_1_4-p1-solution000005.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting p be partition({1, 3, 4}, {2}) +$ Visualisation for p +$ 1 3 4 +$ 2 + diff --git a/tests/exhaustive/issues/286/expected/model_1_4-p1-solution000006.solution b/tests/exhaustive/issues/286/expected/model_1_4-p1-solution000006.solution new file mode 100644 index 0000000000..dafa529443 --- /dev/null +++ b/tests/exhaustive/issues/286/expected/model_1_4-p1-solution000006.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting p be partition({1, 3}, {2, 4}) +$ Visualisation for p +$ 1 3 +$ 2 4 + diff --git a/tests/exhaustive/issues/286/expected/model_1_4-p1-solution000007.solution b/tests/exhaustive/issues/286/expected/model_1_4-p1-solution000007.solution new file mode 100644 index 0000000000..69d6c9f6be --- /dev/null +++ b/tests/exhaustive/issues/286/expected/model_1_4-p1-solution000007.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting p be partition({1, 4}, {2, 3}) +$ Visualisation for p +$ 1 4 +$ 2 3 + diff --git a/tests/exhaustive/issues/286/expected/model_1_4-p1-solution000008.solution b/tests/exhaustive/issues/286/expected/model_1_4-p1-solution000008.solution new file mode 100644 index 0000000000..cd8086fa4a --- /dev/null +++ b/tests/exhaustive/issues/286/expected/model_1_4-p1-solution000008.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting p be partition({1}, {2, 3, 4}) +$ Visualisation for p +$ 1 +$ 2 3 4 + diff --git a/tests/exhaustive/issues/286/expected/model_1_4-p1.eprime-param b/tests/exhaustive/issues/286/expected/model_1_4-p1.eprime-param new file mode 100644 index 0000000000..85954307ca --- /dev/null +++ b/tests/exhaustive/issues/286/expected/model_1_4-p1.eprime-param @@ -0,0 +1,3 @@ +language ESSENCE' 1.0 + +letting b be 4 diff --git a/tests/exhaustive/issues/286/expected/model_1_4.eprime b/tests/exhaustive/issues/286/expected/model_1_4.eprime new file mode 100644 index 0000000000..263a7836c6 --- /dev/null +++ b/tests/exhaustive/issues/286/expected/model_1_4.eprime @@ -0,0 +1,91 @@ +language ESSENCE' 1.0 + +given b: int +find p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker: int(0..b) +find p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence: matrix indexed by [int(1..b), int(1..b)] of bool +find p_PartitionOccurrence_NumParts: int(1..b) +find p_PartitionOccurrence_WhichPart: matrix indexed by [int(1..b)] of int(1..b) +find p_PartitionOccurrence_PartSizes: matrix indexed by [int(1..b)] of int(0..b) +find p_PartitionOccurrence_FirstIndex: matrix indexed by [int(1..b)] of int(1..b) +branching on + [p_PartitionOccurrence_NumParts, p_PartitionOccurrence_WhichPart, p_PartitionOccurrence_PartSizes, + p_PartitionOccurrence_FirstIndex, p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker, + p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence] +such that + sum([toInt(q51 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker) | q51 : int(1..b)]) <= + sum([1 | q52_ExplicitVarSizeWithDummy : matrix indexed by [int(1..b)] of int(1..b + 1), + and([q52_ExplicitVarSizeWithDummy[q53] < q52_ExplicitVarSizeWithDummy[q53 + 1] \/ + q52_ExplicitVarSizeWithDummy[q53] = b + 1 + | q53 : int(1..b - 1)]), + and([q52_ExplicitVarSizeWithDummy[q54] = b + 1 -> q52_ExplicitVarSizeWithDummy[q54 + 1] = b + 1 + | q54 : int(1..b - 1)])]) + / 8, + and([1 = + sum([toInt(q19 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ + p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q19, q1]) + | q19 : int(1..b)]) + | q1 : int(1..b)]), + and([q45 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> + sum([toInt(p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q45, q46]) | q46 : int(1..b)]) >= 1 + | q45 : int(1..b)]), + and([q4 + 1 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> + [-toInt(p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q4, q20]) | q20 : int(1..b)] p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> + and([p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q5, q22] = false | q22 : int(1..b)]) + | q5 : int(1..b)]), + p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker <= b, + and([q6 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> + sum([toInt(p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q6, q7]) | q7 : int(1..b)]) <= b + | q6 : int(1..b)]), + b = + sum([toInt(q47 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker) * + catchUndef(sum([toInt(p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q47, q48]) + | q48 : int(1..b)]), + 0) + | q47 : int(1..b)]), + and([q9 <= p_PartitionOccurrence_NumParts -> p_PartitionOccurrence_PartSizes[q9] <= b | q9 : int(1..b)]), + and([q9 > p_PartitionOccurrence_NumParts -> p_PartitionOccurrence_PartSizes[q9] = 0 | q9 : int(1..b)]), + p_PartitionOccurrence_NumParts <= b, + and([q10 <= p_PartitionOccurrence_NumParts -> or([p_PartitionOccurrence_WhichPart[q11] = q10 | q11 : int(1..b)]) + | q10 : int(3..b)]), + p_PartitionOccurrence_NumParts = max([p_PartitionOccurrence_WhichPart[q12] | q12 : int(1..b)]), + and([p_PartitionOccurrence_PartSizes[q13] = + sum([toInt(p_PartitionOccurrence_WhichPart[q14] = q13) | q14 : int(1..b)]) + | q13 : int(1..b)]), + and([q15 <= p_PartitionOccurrence_NumParts -> + and([p_PartitionOccurrence_WhichPart[q16] = q15 -> p_PartitionOccurrence_FirstIndex[q15] <= q16 + | q16 : int(1..b)]) + | q15 : int(1..b)]), + and([q15 <= p_PartitionOccurrence_NumParts -> + or([p_PartitionOccurrence_WhichPart[q16] = q15 /\ p_PartitionOccurrence_FirstIndex[q15] = q16 + | q16 : int(1..b)]) + | q15 : int(1..b)]), + and([q15 > p_PartitionOccurrence_NumParts -> p_PartitionOccurrence_FirstIndex[q15] = 1 | q15 : int(1..b)]), + and([q17 <= p_PartitionOccurrence_NumParts /\ q18 <= p_PartitionOccurrence_NumParts -> + (q17 < q18 <-> p_PartitionOccurrence_FirstIndex[q17] < p_PartitionOccurrence_FirstIndex[q18]) + | q17 : int(1..b), q18 : int(1..b)]), + and([q24 <= p_PartitionOccurrence_NumParts -> + or([q28 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ + (and([p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q28, q29] -> + or([p_PartitionOccurrence_WhichPart[q31] = q24 /\ q31 = q29 | q31 : int(1..b)]) + | q29 : int(1..b)]) + /\ + and([p_PartitionOccurrence_WhichPart[q33] = q24 -> + p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q28, q33] + | q33 : int(1..b)])) + | q28 : int(1..b)]) + | q24 : int(1..b)]), + and([q36 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> + or([q38 <= p_PartitionOccurrence_NumParts /\ + (and([p_PartitionOccurrence_WhichPart[q41] = q38 -> + p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q36, q41] + | q41 : int(1..b)]) + /\ + and([p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q36, q42] -> + or([p_PartitionOccurrence_WhichPart[q44] = q38 /\ q44 = q42 | q44 : int(1..b)]) + | q42 : int(1..b)])) + | q38 : int(1..b)]) + | q36 : int(1..b)]) + diff --git a/tests/exhaustive/issues/286/expected/model_2_1-p1-solution000001.solution b/tests/exhaustive/issues/286/expected/model_2_1-p1-solution000001.solution new file mode 100644 index 0000000000..8f7fa48018 --- /dev/null +++ b/tests/exhaustive/issues/286/expected/model_2_1-p1-solution000001.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting p be partition({1, 2, 3, 4}) +$ Visualisation for p +$ 1 2 3 4 + diff --git a/tests/exhaustive/issues/286/expected/model_2_1-p1-solution000002.solution b/tests/exhaustive/issues/286/expected/model_2_1-p1-solution000002.solution new file mode 100644 index 0000000000..cd8086fa4a --- /dev/null +++ b/tests/exhaustive/issues/286/expected/model_2_1-p1-solution000002.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting p be partition({1}, {2, 3, 4}) +$ Visualisation for p +$ 1 +$ 2 3 4 + diff --git a/tests/exhaustive/issues/286/expected/model_2_1-p1-solution000003.solution b/tests/exhaustive/issues/286/expected/model_2_1-p1-solution000003.solution new file mode 100644 index 0000000000..69d6c9f6be --- /dev/null +++ b/tests/exhaustive/issues/286/expected/model_2_1-p1-solution000003.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting p be partition({1, 4}, {2, 3}) +$ Visualisation for p +$ 1 4 +$ 2 3 + diff --git a/tests/exhaustive/issues/286/expected/model_2_1-p1-solution000004.solution b/tests/exhaustive/issues/286/expected/model_2_1-p1-solution000004.solution new file mode 100644 index 0000000000..dafa529443 --- /dev/null +++ b/tests/exhaustive/issues/286/expected/model_2_1-p1-solution000004.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting p be partition({1, 3}, {2, 4}) +$ Visualisation for p +$ 1 3 +$ 2 4 + diff --git a/tests/exhaustive/issues/286/expected/model_2_1-p1-solution000005.solution b/tests/exhaustive/issues/286/expected/model_2_1-p1-solution000005.solution new file mode 100644 index 0000000000..0368fc950b --- /dev/null +++ b/tests/exhaustive/issues/286/expected/model_2_1-p1-solution000005.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting p be partition({1, 3, 4}, {2}) +$ Visualisation for p +$ 1 3 4 +$ 2 + diff --git a/tests/exhaustive/issues/286/expected/model_2_1-p1-solution000006.solution b/tests/exhaustive/issues/286/expected/model_2_1-p1-solution000006.solution new file mode 100644 index 0000000000..1507fcc0c1 --- /dev/null +++ b/tests/exhaustive/issues/286/expected/model_2_1-p1-solution000006.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting p be partition({1, 2}, {3, 4}) +$ Visualisation for p +$ 1 2 +$ 3 4 + diff --git a/tests/exhaustive/issues/286/expected/model_2_1-p1-solution000007.solution b/tests/exhaustive/issues/286/expected/model_2_1-p1-solution000007.solution new file mode 100644 index 0000000000..7781800dc4 --- /dev/null +++ b/tests/exhaustive/issues/286/expected/model_2_1-p1-solution000007.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting p be partition({1, 2, 4}, {3}) +$ Visualisation for p +$ 1 2 4 +$ 3 + diff --git a/tests/exhaustive/issues/286/expected/model_2_1-p1-solution000008.solution b/tests/exhaustive/issues/286/expected/model_2_1-p1-solution000008.solution new file mode 100644 index 0000000000..556f2c0ecc --- /dev/null +++ b/tests/exhaustive/issues/286/expected/model_2_1-p1-solution000008.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting p be partition({1, 2, 3}, {4}) +$ Visualisation for p +$ 1 2 3 +$ 4 + diff --git a/tests/exhaustive/issues/286/expected/model_2_1-p1.eprime-param b/tests/exhaustive/issues/286/expected/model_2_1-p1.eprime-param new file mode 100644 index 0000000000..85954307ca --- /dev/null +++ b/tests/exhaustive/issues/286/expected/model_2_1-p1.eprime-param @@ -0,0 +1,3 @@ +language ESSENCE' 1.0 + +letting b be 4 diff --git a/tests/exhaustive/issues/286/expected/model_2_1.eprime b/tests/exhaustive/issues/286/expected/model_2_1.eprime new file mode 100644 index 0000000000..cd032fe57a --- /dev/null +++ b/tests/exhaustive/issues/286/expected/model_2_1.eprime @@ -0,0 +1,122 @@ +language ESSENCE' 1.0 + +given b: int +find p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker: int(0..b) +find p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy: + matrix indexed by [int(1..b), int(1..b)] of int(1..b + 1) +find p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker: int(0..b) +find p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence: matrix indexed by [int(1..b), int(1..b)] of bool +branching on + [p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker, + p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence, + p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker, + p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy] +such that + sum([toInt(q63 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker) | q63 : int(1..b)]) <= + sum([1 | q64_ExplicitVarSizeWithDummy : matrix indexed by [int(1..b)] of int(1..b + 1), + and([q64_ExplicitVarSizeWithDummy[q65] < q64_ExplicitVarSizeWithDummy[q65 + 1] \/ + q64_ExplicitVarSizeWithDummy[q65] = b + 1 + | q65 : int(1..b - 1)]), + and([q64_ExplicitVarSizeWithDummy[q66] = b + 1 -> q64_ExplicitVarSizeWithDummy[q66 + 1] = b + 1 + | q66 : int(1..b - 1)])]) + / 8, + alldifferent_except([toInt(q51 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ + p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q51, q52] != + b + 1) + * + catchUndef(p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q51, q52], + 0) + | q51 : int(1..b), q52 : int(1..b)], + 0), + and([q53 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> + sum([toInt(p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q53, q55] != b + 1) + | q55 : int(1..b)]) + >= 1 + | q53 : int(1..b)]), + and([q4 + 1 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> + [p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q4, q20] | q20 : int(1..b)] p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> + and([p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q5, q22] = 1 + | q22 : int(1..b)]) + | q5 : int(1..b)]), + p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker <= b, + and([q6 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> + and([p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q6, q7] < + p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q6, q7 + 1] + \/ p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q6, q7] = b + 1 + | q7 : int(1..b - 1)]) + | q6 : int(1..b)]), + and([q6 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> + and([p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q6, q8] = b + 1 -> + p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q6, q8 + 1] = b + 1 + | q8 : int(1..b - 1)]) + | q6 : int(1..b)]), + and([q6 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> + sum([toInt(p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q6, q9] != b + 1) + | q9 : int(1..b)]) + <= b + | q6 : int(1..b)]), + b = + sum([toInt(q56 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker) * + catchUndef(sum([toInt(p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q56, q58] != + b + 1) + | q58 : int(1..b)]), + 0) + | q56 : int(1..b)]), + and([1 = + sum([toInt(q23 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ + p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q23, q12]) + | q23 : int(1..b)]) + | q12 : int(1..b)]), + and([q59 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> + sum([toInt(p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q59, q60]) | q60 : int(1..b)]) >= 1 + | q59 : int(1..b)]), + and([q15 + 1 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> + [-toInt(p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q15, q24]) | q24 : int(1..b)] p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> + and([p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q16, q26] = false | q26 : int(1..b)]) + | q16 : int(1..b)]), + p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker <= b, + and([q17 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> + sum([toInt(p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q17, q18]) | q18 : int(1..b)]) <= b + | q17 : int(1..b)]), + b = + sum([toInt(q27 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker) * + catchUndef(sum([toInt(p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q27, q28]) + | q28 : int(1..b)]), + 0) + | q27 : int(1..b)]), + and([q31 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> + or([q34 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ + (and([p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q34, q36] != b + 1 -> + p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence + [q31, p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q34, q36]] + | q36 : int(1..b)]) + /\ + and([p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q31, q37] -> + or([p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q34, q39] != b + 1 + /\ p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q34, q39] = q37 + | q39 : int(1..b)]) + | q37 : int(1..b)])) + | q34 : int(1..b)]) + | q31 : int(1..b)]), + and([q42 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> + or([q45 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ + (and([p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q45, q46] -> + or([p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q42, q48] != b + 1 + /\ p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q42, q48] = q46 + | q48 : int(1..b)]) + | q46 : int(1..b)]) + /\ + and([p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q42, q50] != b + 1 -> + p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence + [q45, p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q42, q50]] + | q50 : int(1..b)])) + | q45 : int(1..b)]) + | q42 : int(1..b)]) + diff --git a/tests/exhaustive/issues/286/expected/model_2_2-p1-solution000001.solution b/tests/exhaustive/issues/286/expected/model_2_2-p1-solution000001.solution new file mode 100644 index 0000000000..8f7fa48018 --- /dev/null +++ b/tests/exhaustive/issues/286/expected/model_2_2-p1-solution000001.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting p be partition({1, 2, 3, 4}) +$ Visualisation for p +$ 1 2 3 4 + diff --git a/tests/exhaustive/issues/286/expected/model_2_2-p1-solution000002.solution b/tests/exhaustive/issues/286/expected/model_2_2-p1-solution000002.solution new file mode 100644 index 0000000000..556f2c0ecc --- /dev/null +++ b/tests/exhaustive/issues/286/expected/model_2_2-p1-solution000002.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting p be partition({1, 2, 3}, {4}) +$ Visualisation for p +$ 1 2 3 +$ 4 + diff --git a/tests/exhaustive/issues/286/expected/model_2_2-p1-solution000003.solution b/tests/exhaustive/issues/286/expected/model_2_2-p1-solution000003.solution new file mode 100644 index 0000000000..7781800dc4 --- /dev/null +++ b/tests/exhaustive/issues/286/expected/model_2_2-p1-solution000003.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting p be partition({1, 2, 4}, {3}) +$ Visualisation for p +$ 1 2 4 +$ 3 + diff --git a/tests/exhaustive/issues/286/expected/model_2_2-p1-solution000004.solution b/tests/exhaustive/issues/286/expected/model_2_2-p1-solution000004.solution new file mode 100644 index 0000000000..1507fcc0c1 --- /dev/null +++ b/tests/exhaustive/issues/286/expected/model_2_2-p1-solution000004.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting p be partition({1, 2}, {3, 4}) +$ Visualisation for p +$ 1 2 +$ 3 4 + diff --git a/tests/exhaustive/issues/286/expected/model_2_2-p1-solution000005.solution b/tests/exhaustive/issues/286/expected/model_2_2-p1-solution000005.solution new file mode 100644 index 0000000000..0368fc950b --- /dev/null +++ b/tests/exhaustive/issues/286/expected/model_2_2-p1-solution000005.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting p be partition({1, 3, 4}, {2}) +$ Visualisation for p +$ 1 3 4 +$ 2 + diff --git a/tests/exhaustive/issues/286/expected/model_2_2-p1-solution000006.solution b/tests/exhaustive/issues/286/expected/model_2_2-p1-solution000006.solution new file mode 100644 index 0000000000..dafa529443 --- /dev/null +++ b/tests/exhaustive/issues/286/expected/model_2_2-p1-solution000006.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting p be partition({1, 3}, {2, 4}) +$ Visualisation for p +$ 1 3 +$ 2 4 + diff --git a/tests/exhaustive/issues/286/expected/model_2_2-p1-solution000007.solution b/tests/exhaustive/issues/286/expected/model_2_2-p1-solution000007.solution new file mode 100644 index 0000000000..69d6c9f6be --- /dev/null +++ b/tests/exhaustive/issues/286/expected/model_2_2-p1-solution000007.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting p be partition({1, 4}, {2, 3}) +$ Visualisation for p +$ 1 4 +$ 2 3 + diff --git a/tests/exhaustive/issues/286/expected/model_2_2-p1-solution000008.solution b/tests/exhaustive/issues/286/expected/model_2_2-p1-solution000008.solution new file mode 100644 index 0000000000..cd8086fa4a --- /dev/null +++ b/tests/exhaustive/issues/286/expected/model_2_2-p1-solution000008.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting p be partition({1}, {2, 3, 4}) +$ Visualisation for p +$ 1 +$ 2 3 4 + diff --git a/tests/exhaustive/issues/286/expected/model_2_2-p1.eprime-param b/tests/exhaustive/issues/286/expected/model_2_2-p1.eprime-param new file mode 100644 index 0000000000..85954307ca --- /dev/null +++ b/tests/exhaustive/issues/286/expected/model_2_2-p1.eprime-param @@ -0,0 +1,3 @@ +language ESSENCE' 1.0 + +letting b be 4 diff --git a/tests/exhaustive/issues/286/expected/model_2_2.eprime b/tests/exhaustive/issues/286/expected/model_2_2.eprime new file mode 100644 index 0000000000..8d40391ff8 --- /dev/null +++ b/tests/exhaustive/issues/286/expected/model_2_2.eprime @@ -0,0 +1,65 @@ +language ESSENCE' 1.0 + +given b: int +find p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker: int(0..b) +find p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy: + matrix indexed by [int(1..b), int(1..b)] of int(1..b + 1) +branching on + [p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker, + p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy] +such that + sum([toInt(q25 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker) | q25 : int(1..b)]) <= + sum([1 | q26_ExplicitVarSizeWithDummy : matrix indexed by [int(1..b)] of int(1..b + 1), + and([q26_ExplicitVarSizeWithDummy[q27] < q26_ExplicitVarSizeWithDummy[q27 + 1] \/ + q26_ExplicitVarSizeWithDummy[q27] = b + 1 + | q27 : int(1..b - 1)]), + and([q26_ExplicitVarSizeWithDummy[q28] = b + 1 -> q26_ExplicitVarSizeWithDummy[q28 + 1] = b + 1 + | q28 : int(1..b - 1)])]) + / 8, + alldifferent_except([toInt(q18 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ + p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q18, q19] != + b + 1) + * + catchUndef(p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q18, q19], + 0) + | q18 : int(1..b), q19 : int(1..b)], + 0), + and([q20 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> + sum([toInt(p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q20, q22] != b + 1) + | q22 : int(1..b)]) + >= 1 + | q20 : int(1..b)]), + and([q4 + 1 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> + [p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q4, q12] | q12 : int(1..b)] p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> + and([p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q5, q14] = 1 + | q14 : int(1..b)]) + | q5 : int(1..b)]), + p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker <= b, + and([q6 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> + and([p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q6, q7] < + p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q6, q7 + 1] + \/ p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q6, q7] = b + 1 + | q7 : int(1..b - 1)]) + | q6 : int(1..b)]), + and([q6 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> + and([p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q6, q8] = b + 1 -> + p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q6, q8 + 1] = b + 1 + | q8 : int(1..b - 1)]) + | q6 : int(1..b)]), + and([q6 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> + sum([toInt(p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q6, q9] != b + 1) + | q9 : int(1..b)]) + <= b + | q6 : int(1..b)]), + b = + sum([toInt(q15 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker) * + catchUndef(sum([toInt(p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q15, q17] != + b + 1) + | q17 : int(1..b)]), + 0) + | q15 : int(1..b)]) + diff --git a/tests/exhaustive/issues/286/expected/model_2_3-p1-solution000001.solution b/tests/exhaustive/issues/286/expected/model_2_3-p1-solution000001.solution new file mode 100644 index 0000000000..8f7fa48018 --- /dev/null +++ b/tests/exhaustive/issues/286/expected/model_2_3-p1-solution000001.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting p be partition({1, 2, 3, 4}) +$ Visualisation for p +$ 1 2 3 4 + diff --git a/tests/exhaustive/issues/286/expected/model_2_3-p1-solution000002.solution b/tests/exhaustive/issues/286/expected/model_2_3-p1-solution000002.solution new file mode 100644 index 0000000000..cd8086fa4a --- /dev/null +++ b/tests/exhaustive/issues/286/expected/model_2_3-p1-solution000002.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting p be partition({1}, {2, 3, 4}) +$ Visualisation for p +$ 1 +$ 2 3 4 + diff --git a/tests/exhaustive/issues/286/expected/model_2_3-p1-solution000003.solution b/tests/exhaustive/issues/286/expected/model_2_3-p1-solution000003.solution new file mode 100644 index 0000000000..0368fc950b --- /dev/null +++ b/tests/exhaustive/issues/286/expected/model_2_3-p1-solution000003.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting p be partition({1, 3, 4}, {2}) +$ Visualisation for p +$ 1 3 4 +$ 2 + diff --git a/tests/exhaustive/issues/286/expected/model_2_3-p1-solution000004.solution b/tests/exhaustive/issues/286/expected/model_2_3-p1-solution000004.solution new file mode 100644 index 0000000000..7781800dc4 --- /dev/null +++ b/tests/exhaustive/issues/286/expected/model_2_3-p1-solution000004.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting p be partition({1, 2, 4}, {3}) +$ Visualisation for p +$ 1 2 4 +$ 3 + diff --git a/tests/exhaustive/issues/286/expected/model_2_3-p1-solution000005.solution b/tests/exhaustive/issues/286/expected/model_2_3-p1-solution000005.solution new file mode 100644 index 0000000000..556f2c0ecc --- /dev/null +++ b/tests/exhaustive/issues/286/expected/model_2_3-p1-solution000005.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting p be partition({1, 2, 3}, {4}) +$ Visualisation for p +$ 1 2 3 +$ 4 + diff --git a/tests/exhaustive/issues/286/expected/model_2_3-p1-solution000006.solution b/tests/exhaustive/issues/286/expected/model_2_3-p1-solution000006.solution new file mode 100644 index 0000000000..1507fcc0c1 --- /dev/null +++ b/tests/exhaustive/issues/286/expected/model_2_3-p1-solution000006.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting p be partition({1, 2}, {3, 4}) +$ Visualisation for p +$ 1 2 +$ 3 4 + diff --git a/tests/exhaustive/issues/286/expected/model_2_3-p1-solution000007.solution b/tests/exhaustive/issues/286/expected/model_2_3-p1-solution000007.solution new file mode 100644 index 0000000000..dafa529443 --- /dev/null +++ b/tests/exhaustive/issues/286/expected/model_2_3-p1-solution000007.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting p be partition({1, 3}, {2, 4}) +$ Visualisation for p +$ 1 3 +$ 2 4 + diff --git a/tests/exhaustive/issues/286/expected/model_2_3-p1-solution000008.solution b/tests/exhaustive/issues/286/expected/model_2_3-p1-solution000008.solution new file mode 100644 index 0000000000..69d6c9f6be --- /dev/null +++ b/tests/exhaustive/issues/286/expected/model_2_3-p1-solution000008.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting p be partition({1, 4}, {2, 3}) +$ Visualisation for p +$ 1 4 +$ 2 3 + diff --git a/tests/exhaustive/issues/286/expected/model_2_3-p1.eprime-param b/tests/exhaustive/issues/286/expected/model_2_3-p1.eprime-param new file mode 100644 index 0000000000..85954307ca --- /dev/null +++ b/tests/exhaustive/issues/286/expected/model_2_3-p1.eprime-param @@ -0,0 +1,3 @@ +language ESSENCE' 1.0 + +letting b be 4 diff --git a/tests/exhaustive/issues/286/expected/model_2_3.eprime.orig b/tests/exhaustive/issues/286/expected/model_2_3.eprime.orig deleted file mode 100644 index 4e4bb4ee37..0000000000 --- a/tests/exhaustive/issues/286/expected/model_2_3.eprime.orig +++ /dev/null @@ -1,160 +0,0 @@ -language ESSENCE' 1.0 - -given b: int -find p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker: int(0..b) -find p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy: - matrix indexed by [int(1..b), int(1..b)] of int(1..b + 1) -find p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker: int(0..b) -find p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker: - matrix indexed by [int(1..b)] of int(0..b) -find p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values: - matrix indexed by [int(1..b), int(1..b)] of int(1..b) -branching on - [p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker, - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker, - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values, - p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker, - p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy] -such that - sum([toInt(q70 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker) | q70 : int(1..b)]) <= - sum([1 | q71_ExplicitVarSizeWithDummy : matrix indexed by [int(1..b)] of int(1..b + 1), - and([q71_ExplicitVarSizeWithDummy[q72] < q71_ExplicitVarSizeWithDummy[q72 + 1] \/ - q71_ExplicitVarSizeWithDummy[q72] = b + 1 - | q72 : int(1..b - 1)]), - and([q71_ExplicitVarSizeWithDummy[q73] = b + 1 -> q71_ExplicitVarSizeWithDummy[q73 + 1] = b + 1 - | q73 : int(1..b - 1)])]) - / 8, - alldifferent_except([toInt(q57 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ - p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q57, q58] != - b + 1) - * - catchUndef(p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q57, q58], - 0) - | q57 : int(1..b), q58 : int(1..b)], - 0), - and([q59 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - sum([toInt(p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q59, q61] != b + 1) - | q61 : int(1..b)]) - >= 1 - | q59 : int(1..b)]), - and([q4 + 1 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - [p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q4, q22] | q22 : int(1..b)] p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - and([p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q5, q24] = 1 - | q24 : int(1..b)]) - | q5 : int(1..b)]), - p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker <= b, - and([q6 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - and([p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q6, q7] < - p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q6, q7 + 1] - \/ p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q6, q7] = b + 1 - | q7 : int(1..b - 1)]) - | q6 : int(1..b)]), - and([q6 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - and([p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q6, q8] = b + 1 -> - p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q6, q8 + 1] = b + 1 - | q8 : int(1..b - 1)]) - | q6 : int(1..b)]), - and([q6 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - sum([toInt(p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q6, q9] != b + 1) - | q9 : int(1..b)]) - <= b - | q6 : int(1..b)]), - b = - sum([toInt(q62 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker) * - catchUndef(sum([toInt(p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q62, q64] != - b + 1) - | q64 : int(1..b)]), - 0) - | q62 : int(1..b)]), - alldifferent_except([toInt(q65 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - q66 <= - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q65]) - * - catchUndef(p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q65, q66], - 0) - | q65 : int(1..b), q66 : int(1..b)], - 0), - and([q67 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q67] >= 1 - | q67 : int(1..b)]), - and([q15 + 1 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - flatten([[p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q15]; int(1)], - [p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q15, q25] - | q25 : int(1..b)]; - int(1..2)]) - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q16] = 0 /\ - and([p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q16, q27] = 1 - | q27 : int(1..b)]) - | q16 : int(1..b)]), - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker <= b, - and([q17 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - and([q18 + 1 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q17] -> - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q17, q18] < - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q17, q18 + 1] - | q18 : int(1..b - 1)]) - | q17 : int(1..b)]), - and([q17 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - and([q19 > p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q17] -> - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q17, q19] = 1 - | q19 : int(1..b)]) - | q17 : int(1..b)]), - and([q17 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q17] <= b - | q17 : int(1..b)]), - b = - sum([toInt(q28 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker) * - catchUndef(p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q28], 0) - | q28 : int(1..b)]), - and([q31 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - or([q34 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ - (and([p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q34, q36] != b + 1 -> - or([q38 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q31] - /\ - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q31, q38] = - p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q34, q36] - | q38 : int(1..b)]) - | q36 : int(1..b)]) - /\ - and([q40 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q31] -> - or([p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q34, q42] != b + 1 - /\ - p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q34, q42] = - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q31, q40] - | q42 : int(1..b)]) - | q40 : int(1..b)])) - | q34 : int(1..b)]) - | q31 : int(1..b)]), - and([q45 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - or([q48 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - (and([q50 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q48] -> - or([p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q45, q52] != b + 1 - /\ - p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q45, q52] = - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q48, q50] - | q52 : int(1..b)]) - | q50 : int(1..b)]) - /\ - and([p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q45, q54] != b + 1 -> - or([q56 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q48] - /\ - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q48, q56] = - p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q45, q54] - | q56 : int(1..b)]) - | q54 : int(1..b)])) - | q48 : int(1..b)]) - | q45 : int(1..b)]) - diff --git a/tests/exhaustive/issues/286/expected/model_2_4-p1-solution000001.solution b/tests/exhaustive/issues/286/expected/model_2_4-p1-solution000001.solution new file mode 100644 index 0000000000..8f7fa48018 --- /dev/null +++ b/tests/exhaustive/issues/286/expected/model_2_4-p1-solution000001.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting p be partition({1, 2, 3, 4}) +$ Visualisation for p +$ 1 2 3 4 + diff --git a/tests/exhaustive/issues/286/expected/model_2_4-p1-solution000002.solution b/tests/exhaustive/issues/286/expected/model_2_4-p1-solution000002.solution new file mode 100644 index 0000000000..556f2c0ecc --- /dev/null +++ b/tests/exhaustive/issues/286/expected/model_2_4-p1-solution000002.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting p be partition({1, 2, 3}, {4}) +$ Visualisation for p +$ 1 2 3 +$ 4 + diff --git a/tests/exhaustive/issues/286/expected/model_2_4-p1-solution000003.solution b/tests/exhaustive/issues/286/expected/model_2_4-p1-solution000003.solution new file mode 100644 index 0000000000..7781800dc4 --- /dev/null +++ b/tests/exhaustive/issues/286/expected/model_2_4-p1-solution000003.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting p be partition({1, 2, 4}, {3}) +$ Visualisation for p +$ 1 2 4 +$ 3 + diff --git a/tests/exhaustive/issues/286/expected/model_2_4-p1-solution000004.solution b/tests/exhaustive/issues/286/expected/model_2_4-p1-solution000004.solution new file mode 100644 index 0000000000..1507fcc0c1 --- /dev/null +++ b/tests/exhaustive/issues/286/expected/model_2_4-p1-solution000004.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting p be partition({1, 2}, {3, 4}) +$ Visualisation for p +$ 1 2 +$ 3 4 + diff --git a/tests/exhaustive/issues/286/expected/model_2_4-p1-solution000005.solution b/tests/exhaustive/issues/286/expected/model_2_4-p1-solution000005.solution new file mode 100644 index 0000000000..0368fc950b --- /dev/null +++ b/tests/exhaustive/issues/286/expected/model_2_4-p1-solution000005.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting p be partition({1, 3, 4}, {2}) +$ Visualisation for p +$ 1 3 4 +$ 2 + diff --git a/tests/exhaustive/issues/286/expected/model_2_4-p1-solution000006.solution b/tests/exhaustive/issues/286/expected/model_2_4-p1-solution000006.solution new file mode 100644 index 0000000000..dafa529443 --- /dev/null +++ b/tests/exhaustive/issues/286/expected/model_2_4-p1-solution000006.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting p be partition({1, 3}, {2, 4}) +$ Visualisation for p +$ 1 3 +$ 2 4 + diff --git a/tests/exhaustive/issues/286/expected/model_2_4-p1-solution000007.solution b/tests/exhaustive/issues/286/expected/model_2_4-p1-solution000007.solution new file mode 100644 index 0000000000..69d6c9f6be --- /dev/null +++ b/tests/exhaustive/issues/286/expected/model_2_4-p1-solution000007.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting p be partition({1, 4}, {2, 3}) +$ Visualisation for p +$ 1 4 +$ 2 3 + diff --git a/tests/exhaustive/issues/286/expected/model_2_4-p1-solution000008.solution b/tests/exhaustive/issues/286/expected/model_2_4-p1-solution000008.solution new file mode 100644 index 0000000000..cd8086fa4a --- /dev/null +++ b/tests/exhaustive/issues/286/expected/model_2_4-p1-solution000008.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting p be partition({1}, {2, 3, 4}) +$ Visualisation for p +$ 1 +$ 2 3 4 + diff --git a/tests/exhaustive/issues/286/expected/model_2_4-p1.eprime-param b/tests/exhaustive/issues/286/expected/model_2_4-p1.eprime-param new file mode 100644 index 0000000000..85954307ca --- /dev/null +++ b/tests/exhaustive/issues/286/expected/model_2_4-p1.eprime-param @@ -0,0 +1,3 @@ +language ESSENCE' 1.0 + +letting b be 4 diff --git a/tests/exhaustive/issues/286/expected/model_2_4.eprime b/tests/exhaustive/issues/286/expected/model_2_4.eprime new file mode 100644 index 0000000000..f24fc7e366 --- /dev/null +++ b/tests/exhaustive/issues/286/expected/model_2_4.eprime @@ -0,0 +1,121 @@ +language ESSENCE' 1.0 + +given b: int +find p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker: int(0..b) +find p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy: + matrix indexed by [int(1..b), int(1..b)] of int(1..b + 1) +find p_PartitionOccurrence_NumParts: int(1..b) +find p_PartitionOccurrence_WhichPart: matrix indexed by [int(1..b)] of int(1..b) +find p_PartitionOccurrence_PartSizes: matrix indexed by [int(1..b)] of int(0..b) +find p_PartitionOccurrence_FirstIndex: matrix indexed by [int(1..b)] of int(1..b) +branching on + [p_PartitionOccurrence_NumParts, p_PartitionOccurrence_WhichPart, p_PartitionOccurrence_PartSizes, + p_PartitionOccurrence_FirstIndex, p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker, + p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy] +such that + sum([toInt(q63 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker) | q63 : int(1..b)]) <= + sum([1 | q64_ExplicitVarSizeWithDummy : matrix indexed by [int(1..b)] of int(1..b + 1), + and([q64_ExplicitVarSizeWithDummy[q65] < q64_ExplicitVarSizeWithDummy[q65 + 1] \/ + q64_ExplicitVarSizeWithDummy[q65] = b + 1 + | q65 : int(1..b - 1)]), + and([q64_ExplicitVarSizeWithDummy[q66] = b + 1 -> q64_ExplicitVarSizeWithDummy[q66 + 1] = b + 1 + | q66 : int(1..b - 1)])]) + / 8, + alldifferent_except([toInt(q53 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ + p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q53, q54] != + b + 1) + * + catchUndef(p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q53, q54], + 0) + | q53 : int(1..b), q54 : int(1..b)], + 0), + and([q55 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> + sum([toInt(p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q55, q57] != b + 1) + | q57 : int(1..b)]) + >= 1 + | q55 : int(1..b)]), + and([q4 + 1 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> + [p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q4, q22] | q22 : int(1..b)] p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> + and([p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q5, q24] = 1 + | q24 : int(1..b)]) + | q5 : int(1..b)]), + p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker <= b, + and([q6 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> + and([p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q6, q7] < + p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q6, q7 + 1] + \/ p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q6, q7] = b + 1 + | q7 : int(1..b - 1)]) + | q6 : int(1..b)]), + and([q6 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> + and([p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q6, q8] = b + 1 -> + p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q6, q8 + 1] = b + 1 + | q8 : int(1..b - 1)]) + | q6 : int(1..b)]), + and([q6 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> + sum([toInt(p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q6, q9] != b + 1) + | q9 : int(1..b)]) + <= b + | q6 : int(1..b)]), + b = + sum([toInt(q58 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker) * + catchUndef(sum([toInt(p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q58, q60] != + b + 1) + | q60 : int(1..b)]), + 0) + | q58 : int(1..b)]), + and([q12 <= p_PartitionOccurrence_NumParts -> p_PartitionOccurrence_PartSizes[q12] <= b | q12 : int(1..b)]), + and([q12 > p_PartitionOccurrence_NumParts -> p_PartitionOccurrence_PartSizes[q12] = 0 | q12 : int(1..b)]), + p_PartitionOccurrence_NumParts <= b, + and([q13 <= p_PartitionOccurrence_NumParts -> or([p_PartitionOccurrence_WhichPart[q14] = q13 | q14 : int(1..b)]) + | q13 : int(3..b)]), + p_PartitionOccurrence_NumParts = max([p_PartitionOccurrence_WhichPart[q15] | q15 : int(1..b)]), + and([p_PartitionOccurrence_PartSizes[q16] = + sum([toInt(p_PartitionOccurrence_WhichPart[q17] = q16) | q17 : int(1..b)]) + | q16 : int(1..b)]), + and([q18 <= p_PartitionOccurrence_NumParts -> + and([p_PartitionOccurrence_WhichPart[q19] = q18 -> p_PartitionOccurrence_FirstIndex[q18] <= q19 + | q19 : int(1..b)]) + | q18 : int(1..b)]), + and([q18 <= p_PartitionOccurrence_NumParts -> + or([p_PartitionOccurrence_WhichPart[q19] = q18 /\ p_PartitionOccurrence_FirstIndex[q18] = q19 + | q19 : int(1..b)]) + | q18 : int(1..b)]), + and([q18 > p_PartitionOccurrence_NumParts -> p_PartitionOccurrence_FirstIndex[q18] = 1 | q18 : int(1..b)]), + and([q20 <= p_PartitionOccurrence_NumParts /\ q21 <= p_PartitionOccurrence_NumParts -> + (q20 < q21 <-> p_PartitionOccurrence_FirstIndex[q20] < p_PartitionOccurrence_FirstIndex[q21]) + | q20 : int(1..b), q21 : int(1..b)]), + and([q26 <= p_PartitionOccurrence_NumParts -> + or([q30 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ + (and([p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q30, q32] != b + 1 -> + or([p_PartitionOccurrence_WhichPart[q34] = q26 /\ + q34 = p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q30, q32] + | q34 : int(1..b)]) + | q32 : int(1..b)]) + /\ + and([p_PartitionOccurrence_WhichPart[q36] = q26 -> + or([p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q30, q38] != b + 1 + /\ p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q30, q38] = q36 + | q38 : int(1..b)]) + | q36 : int(1..b)])) + | q30 : int(1..b)]) + | q26 : int(1..b)]), + and([q41 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> + or([q43 <= p_PartitionOccurrence_NumParts /\ + (and([p_PartitionOccurrence_WhichPart[q46] = q43 -> + or([p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q41, q48] != b + 1 + /\ p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q41, q48] = q46 + | q48 : int(1..b)]) + | q46 : int(1..b)]) + /\ + and([p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q41, q50] != b + 1 -> + or([p_PartitionOccurrence_WhichPart[q52] = q43 /\ + q52 = p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q41, q50] + | q52 : int(1..b)]) + | q50 : int(1..b)])) + | q43 : int(1..b)]) + | q41 : int(1..b)]) + diff --git a/tests/exhaustive/issues/286/expected/model_3_1-p1-solution000001.solution b/tests/exhaustive/issues/286/expected/model_3_1-p1-solution000001.solution new file mode 100644 index 0000000000..8f7fa48018 --- /dev/null +++ b/tests/exhaustive/issues/286/expected/model_3_1-p1-solution000001.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting p be partition({1, 2, 3, 4}) +$ Visualisation for p +$ 1 2 3 4 + diff --git a/tests/exhaustive/issues/286/expected/model_3_1-p1-solution000002.solution b/tests/exhaustive/issues/286/expected/model_3_1-p1-solution000002.solution new file mode 100644 index 0000000000..cd8086fa4a --- /dev/null +++ b/tests/exhaustive/issues/286/expected/model_3_1-p1-solution000002.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting p be partition({1}, {2, 3, 4}) +$ Visualisation for p +$ 1 +$ 2 3 4 + diff --git a/tests/exhaustive/issues/286/expected/model_3_1-p1-solution000003.solution b/tests/exhaustive/issues/286/expected/model_3_1-p1-solution000003.solution new file mode 100644 index 0000000000..69d6c9f6be --- /dev/null +++ b/tests/exhaustive/issues/286/expected/model_3_1-p1-solution000003.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting p be partition({1, 4}, {2, 3}) +$ Visualisation for p +$ 1 4 +$ 2 3 + diff --git a/tests/exhaustive/issues/286/expected/model_3_1-p1-solution000004.solution b/tests/exhaustive/issues/286/expected/model_3_1-p1-solution000004.solution new file mode 100644 index 0000000000..dafa529443 --- /dev/null +++ b/tests/exhaustive/issues/286/expected/model_3_1-p1-solution000004.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting p be partition({1, 3}, {2, 4}) +$ Visualisation for p +$ 1 3 +$ 2 4 + diff --git a/tests/exhaustive/issues/286/expected/model_3_1-p1-solution000005.solution b/tests/exhaustive/issues/286/expected/model_3_1-p1-solution000005.solution new file mode 100644 index 0000000000..0368fc950b --- /dev/null +++ b/tests/exhaustive/issues/286/expected/model_3_1-p1-solution000005.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting p be partition({1, 3, 4}, {2}) +$ Visualisation for p +$ 1 3 4 +$ 2 + diff --git a/tests/exhaustive/issues/286/expected/model_3_1-p1-solution000006.solution b/tests/exhaustive/issues/286/expected/model_3_1-p1-solution000006.solution new file mode 100644 index 0000000000..1507fcc0c1 --- /dev/null +++ b/tests/exhaustive/issues/286/expected/model_3_1-p1-solution000006.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting p be partition({1, 2}, {3, 4}) +$ Visualisation for p +$ 1 2 +$ 3 4 + diff --git a/tests/exhaustive/issues/286/expected/model_3_1-p1-solution000007.solution b/tests/exhaustive/issues/286/expected/model_3_1-p1-solution000007.solution new file mode 100644 index 0000000000..7781800dc4 --- /dev/null +++ b/tests/exhaustive/issues/286/expected/model_3_1-p1-solution000007.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting p be partition({1, 2, 4}, {3}) +$ Visualisation for p +$ 1 2 4 +$ 3 + diff --git a/tests/exhaustive/issues/286/expected/model_3_1-p1-solution000008.solution b/tests/exhaustive/issues/286/expected/model_3_1-p1-solution000008.solution new file mode 100644 index 0000000000..556f2c0ecc --- /dev/null +++ b/tests/exhaustive/issues/286/expected/model_3_1-p1-solution000008.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting p be partition({1, 2, 3}, {4}) +$ Visualisation for p +$ 1 2 3 +$ 4 + diff --git a/tests/exhaustive/issues/286/expected/model_3_1-p1.eprime-param b/tests/exhaustive/issues/286/expected/model_3_1-p1.eprime-param new file mode 100644 index 0000000000..85954307ca --- /dev/null +++ b/tests/exhaustive/issues/286/expected/model_3_1-p1.eprime-param @@ -0,0 +1,3 @@ +language ESSENCE' 1.0 + +letting b be 4 diff --git a/tests/exhaustive/issues/286/expected/model_3_1.eprime.orig b/tests/exhaustive/issues/286/expected/model_3_1.eprime.orig deleted file mode 100644 index dd5e035a04..0000000000 --- a/tests/exhaustive/issues/286/expected/model_3_1.eprime.orig +++ /dev/null @@ -1,132 +0,0 @@ -language ESSENCE' 1.0 - -given b: int -find p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker: int(0..b) -find p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker: - matrix indexed by [int(1..b)] of int(0..b) -find p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values: - matrix indexed by [int(1..b), int(1..b)] of int(1..b) -find p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker: int(0..b) -find p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence: matrix indexed by [int(1..b), int(1..b)] of bool -branching on - [p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker, - p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence, - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker, - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker, - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values] -such that - sum([toInt(q58 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker) | q58 : int(1..b)]) <= - sum([1 | q59_ExplicitVarSizeWithDummy : matrix indexed by [int(1..b)] of int(1..b + 1), - and([q59_ExplicitVarSizeWithDummy[q60] < q59_ExplicitVarSizeWithDummy[q60 + 1] \/ - q59_ExplicitVarSizeWithDummy[q60] = b + 1 - | q60 : int(1..b - 1)]), - and([q59_ExplicitVarSizeWithDummy[q61] = b + 1 -> q59_ExplicitVarSizeWithDummy[q61 + 1] = b + 1 - | q61 : int(1..b - 1)])]) - / 8, - alldifferent_except([toInt(q50 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - q51 <= - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q50]) - * - catchUndef(p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q50, q51], - 0) - | q50 : int(1..b), q51 : int(1..b)], - 0), - and([q52 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q52] >= 1 - | q52 : int(1..b)]), - and([q4 + 1 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - flatten([[p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q4]; int(1)], - [p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q4, q19] - | q19 : int(1..b)]; - int(1..2)]) - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q5] = 0 /\ - and([p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q5, q21] = 1 - | q21 : int(1..b)]) - | q5 : int(1..b)]), - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker <= b, - and([q6 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - and([q7 + 1 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q6] -> - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q6, q7] < - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q6, q7 + 1] - | q7 : int(1..b - 1)]) - | q6 : int(1..b)]), - and([q6 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - and([q8 > p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q6] -> - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q6, q8] = 1 - | q8 : int(1..b)]) - | q6 : int(1..b)]), - and([q6 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q6] <= b - | q6 : int(1..b)]), - b = - sum([toInt(q53 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker) * - catchUndef(p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q53], 0) - | q53 : int(1..b)]), - and([1 = - sum([toInt(q22 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ - p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q22, q11]) - | q22 : int(1..b)]) - | q11 : int(1..b)]), - and([q54 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> - sum([toInt(p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q54, q55]) | q55 : int(1..b)]) >= 1 - | q54 : int(1..b)]), - and([q14 + 1 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> - [-toInt(p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q14, q23]) | q23 : int(1..b)] p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> - and([p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q15, q25] = false | q25 : int(1..b)]) - | q15 : int(1..b)]), - p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker <= b, - and([q16 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> - sum([toInt(p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q16, q17]) | q17 : int(1..b)]) <= b - | q16 : int(1..b)]), - b = - sum([toInt(q26 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker) * - catchUndef(sum([toInt(p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q26, q27]) - | q27 : int(1..b)]), - 0) - | q26 : int(1..b)]), - and([q30 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> - or([q33 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - (and([q35 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q33] -> - p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence - [q30, - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q33, q35]] - | q35 : int(1..b)]) - /\ - and([p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q30, q36] -> - or([q38 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q33] - /\ - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q33, q38] = - q36 | q38 : int(1..b)]) - | q36 : int(1..b)])) - | q33 : int(1..b)]) - | q30 : int(1..b)]), - and([q41 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - or([q44 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ - (and([p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q44, q45] -> - or([q47 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q41] - /\ - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q41, q47] = - q45 | q47 : int(1..b)]) - | q45 : int(1..b)]) - /\ - and([q49 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q41] -> - p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence - [q44, - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q41, q49]] - | q49 : int(1..b)])) - | q44 : int(1..b)]) - | q41 : int(1..b)]) - diff --git a/tests/exhaustive/issues/286/expected/model_3_2-p1-solution000001.solution b/tests/exhaustive/issues/286/expected/model_3_2-p1-solution000001.solution new file mode 100644 index 0000000000..8f7fa48018 --- /dev/null +++ b/tests/exhaustive/issues/286/expected/model_3_2-p1-solution000001.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting p be partition({1, 2, 3, 4}) +$ Visualisation for p +$ 1 2 3 4 + diff --git a/tests/exhaustive/issues/286/expected/model_3_2-p1-solution000002.solution b/tests/exhaustive/issues/286/expected/model_3_2-p1-solution000002.solution new file mode 100644 index 0000000000..556f2c0ecc --- /dev/null +++ b/tests/exhaustive/issues/286/expected/model_3_2-p1-solution000002.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting p be partition({1, 2, 3}, {4}) +$ Visualisation for p +$ 1 2 3 +$ 4 + diff --git a/tests/exhaustive/issues/286/expected/model_3_2-p1-solution000003.solution b/tests/exhaustive/issues/286/expected/model_3_2-p1-solution000003.solution new file mode 100644 index 0000000000..7781800dc4 --- /dev/null +++ b/tests/exhaustive/issues/286/expected/model_3_2-p1-solution000003.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting p be partition({1, 2, 4}, {3}) +$ Visualisation for p +$ 1 2 4 +$ 3 + diff --git a/tests/exhaustive/issues/286/expected/model_3_2-p1-solution000004.solution b/tests/exhaustive/issues/286/expected/model_3_2-p1-solution000004.solution new file mode 100644 index 0000000000..1507fcc0c1 --- /dev/null +++ b/tests/exhaustive/issues/286/expected/model_3_2-p1-solution000004.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting p be partition({1, 2}, {3, 4}) +$ Visualisation for p +$ 1 2 +$ 3 4 + diff --git a/tests/exhaustive/issues/286/expected/model_3_2-p1-solution000005.solution b/tests/exhaustive/issues/286/expected/model_3_2-p1-solution000005.solution new file mode 100644 index 0000000000..0368fc950b --- /dev/null +++ b/tests/exhaustive/issues/286/expected/model_3_2-p1-solution000005.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting p be partition({1, 3, 4}, {2}) +$ Visualisation for p +$ 1 3 4 +$ 2 + diff --git a/tests/exhaustive/issues/286/expected/model_3_2-p1-solution000006.solution b/tests/exhaustive/issues/286/expected/model_3_2-p1-solution000006.solution new file mode 100644 index 0000000000..dafa529443 --- /dev/null +++ b/tests/exhaustive/issues/286/expected/model_3_2-p1-solution000006.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting p be partition({1, 3}, {2, 4}) +$ Visualisation for p +$ 1 3 +$ 2 4 + diff --git a/tests/exhaustive/issues/286/expected/model_3_2-p1-solution000007.solution b/tests/exhaustive/issues/286/expected/model_3_2-p1-solution000007.solution new file mode 100644 index 0000000000..69d6c9f6be --- /dev/null +++ b/tests/exhaustive/issues/286/expected/model_3_2-p1-solution000007.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting p be partition({1, 4}, {2, 3}) +$ Visualisation for p +$ 1 4 +$ 2 3 + diff --git a/tests/exhaustive/issues/286/expected/model_3_2-p1-solution000008.solution b/tests/exhaustive/issues/286/expected/model_3_2-p1-solution000008.solution new file mode 100644 index 0000000000..cd8086fa4a --- /dev/null +++ b/tests/exhaustive/issues/286/expected/model_3_2-p1-solution000008.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting p be partition({1}, {2, 3, 4}) +$ Visualisation for p +$ 1 +$ 2 3 4 + diff --git a/tests/exhaustive/issues/286/expected/model_3_2-p1.eprime-param b/tests/exhaustive/issues/286/expected/model_3_2-p1.eprime-param new file mode 100644 index 0000000000..85954307ca --- /dev/null +++ b/tests/exhaustive/issues/286/expected/model_3_2-p1.eprime-param @@ -0,0 +1,3 @@ +language ESSENCE' 1.0 + +letting b be 4 diff --git a/tests/exhaustive/issues/286/expected/model_3_2.eprime.orig b/tests/exhaustive/issues/286/expected/model_3_2.eprime.orig deleted file mode 100644 index ca91efa6d5..0000000000 --- a/tests/exhaustive/issues/286/expected/model_3_2.eprime.orig +++ /dev/null @@ -1,160 +0,0 @@ -language ESSENCE' 1.0 - -given b: int -find p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker: int(0..b) -find p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker: - matrix indexed by [int(1..b)] of int(0..b) -find p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values: - matrix indexed by [int(1..b), int(1..b)] of int(1..b) -find p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker: int(0..b) -find p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy: - matrix indexed by [int(1..b), int(1..b)] of int(1..b + 1) -branching on - [p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker, - p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy, - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker, - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker, - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values] -such that - sum([toInt(q70 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker) | q70 : int(1..b)]) <= - sum([1 | q71_ExplicitVarSizeWithDummy : matrix indexed by [int(1..b)] of int(1..b + 1), - and([q71_ExplicitVarSizeWithDummy[q72] < q71_ExplicitVarSizeWithDummy[q72 + 1] \/ - q71_ExplicitVarSizeWithDummy[q72] = b + 1 - | q72 : int(1..b - 1)]), - and([q71_ExplicitVarSizeWithDummy[q73] = b + 1 -> q71_ExplicitVarSizeWithDummy[q73 + 1] = b + 1 - | q73 : int(1..b - 1)])]) - / 8, - alldifferent_except([toInt(q59 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - q60 <= - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q59]) - * - catchUndef(p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q59, q60], - 0) - | q59 : int(1..b), q60 : int(1..b)], - 0), - and([q61 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q61] >= 1 - | q61 : int(1..b)]), - and([q4 + 1 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - flatten([[p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q4]; int(1)], - [p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q4, q22] - | q22 : int(1..b)]; - int(1..2)]) - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q5] = 0 /\ - and([p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q5, q24] = 1 - | q24 : int(1..b)]) - | q5 : int(1..b)]), - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker <= b, - and([q6 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - and([q7 + 1 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q6] -> - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q6, q7] < - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q6, q7 + 1] - | q7 : int(1..b - 1)]) - | q6 : int(1..b)]), - and([q6 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - and([q8 > p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q6] -> - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q6, q8] = 1 - | q8 : int(1..b)]) - | q6 : int(1..b)]), - and([q6 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q6] <= b - | q6 : int(1..b)]), - b = - sum([toInt(q62 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker) * - catchUndef(p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q62], 0) - | q62 : int(1..b)]), - alldifferent_except([toInt(q63 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ - p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q63, q64] != - b + 1) - * - catchUndef(p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q63, q64], - 0) - | q63 : int(1..b), q64 : int(1..b)], - 0), - and([q65 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - sum([toInt(p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q65, q67] != b + 1) - | q67 : int(1..b)]) - >= 1 - | q65 : int(1..b)]), - and([q14 + 1 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - [p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q14, q25] | q25 : int(1..b)] p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - and([p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q15, q27] = 1 - | q27 : int(1..b)]) - | q15 : int(1..b)]), - p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker <= b, - and([q16 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - and([p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q16, q17] < - p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q16, q17 + 1] - \/ p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q16, q17] = b + 1 - | q17 : int(1..b - 1)]) - | q16 : int(1..b)]), - and([q16 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - and([p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q16, q18] = b + 1 -> - p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q16, q18 + 1] = b + 1 - | q18 : int(1..b - 1)]) - | q16 : int(1..b)]), - and([q16 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - sum([toInt(p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q16, q19] != b + 1) - | q19 : int(1..b)]) - <= b - | q16 : int(1..b)]), - b = - sum([toInt(q28 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker) * - catchUndef(sum([toInt(p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q28, q30] != - b + 1) - | q30 : int(1..b)]), - 0) - | q28 : int(1..b)]), - and([q33 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - or([q36 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - (and([q38 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q36] -> - or([p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q33, q40] != b + 1 - /\ - p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q33, q40] = - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q36, q38] - | q40 : int(1..b)]) - | q38 : int(1..b)]) - /\ - and([p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q33, q42] != b + 1 -> - or([q44 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q36] - /\ - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q36, q44] = - p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q33, q42] - | q44 : int(1..b)]) - | q42 : int(1..b)])) - | q36 : int(1..b)]) - | q33 : int(1..b)]), - and([q47 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - or([q50 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ - (and([p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q50, q52] != b + 1 -> - or([q54 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q47] - /\ - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q47, q54] = - p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q50, q52] - | q54 : int(1..b)]) - | q52 : int(1..b)]) - /\ - and([q56 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q47] -> - or([p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q50, q58] != b + 1 - /\ - p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q50, q58] = - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q47, q56] - | q58 : int(1..b)]) - | q56 : int(1..b)])) - | q50 : int(1..b)]) - | q47 : int(1..b)]) - diff --git a/tests/exhaustive/issues/286/expected/model_3_3-p1-solution000001.solution b/tests/exhaustive/issues/286/expected/model_3_3-p1-solution000001.solution new file mode 100644 index 0000000000..8f7fa48018 --- /dev/null +++ b/tests/exhaustive/issues/286/expected/model_3_3-p1-solution000001.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting p be partition({1, 2, 3, 4}) +$ Visualisation for p +$ 1 2 3 4 + diff --git a/tests/exhaustive/issues/286/expected/model_3_3-p1-solution000002.solution b/tests/exhaustive/issues/286/expected/model_3_3-p1-solution000002.solution new file mode 100644 index 0000000000..cd8086fa4a --- /dev/null +++ b/tests/exhaustive/issues/286/expected/model_3_3-p1-solution000002.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting p be partition({1}, {2, 3, 4}) +$ Visualisation for p +$ 1 +$ 2 3 4 + diff --git a/tests/exhaustive/issues/286/expected/model_3_3-p1-solution000003.solution b/tests/exhaustive/issues/286/expected/model_3_3-p1-solution000003.solution new file mode 100644 index 0000000000..0368fc950b --- /dev/null +++ b/tests/exhaustive/issues/286/expected/model_3_3-p1-solution000003.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting p be partition({1, 3, 4}, {2}) +$ Visualisation for p +$ 1 3 4 +$ 2 + diff --git a/tests/exhaustive/issues/286/expected/model_3_3-p1-solution000004.solution b/tests/exhaustive/issues/286/expected/model_3_3-p1-solution000004.solution new file mode 100644 index 0000000000..7781800dc4 --- /dev/null +++ b/tests/exhaustive/issues/286/expected/model_3_3-p1-solution000004.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting p be partition({1, 2, 4}, {3}) +$ Visualisation for p +$ 1 2 4 +$ 3 + diff --git a/tests/exhaustive/issues/286/expected/model_3_3-p1-solution000005.solution b/tests/exhaustive/issues/286/expected/model_3_3-p1-solution000005.solution new file mode 100644 index 0000000000..556f2c0ecc --- /dev/null +++ b/tests/exhaustive/issues/286/expected/model_3_3-p1-solution000005.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting p be partition({1, 2, 3}, {4}) +$ Visualisation for p +$ 1 2 3 +$ 4 + diff --git a/tests/exhaustive/issues/286/expected/model_3_3-p1-solution000006.solution b/tests/exhaustive/issues/286/expected/model_3_3-p1-solution000006.solution new file mode 100644 index 0000000000..1507fcc0c1 --- /dev/null +++ b/tests/exhaustive/issues/286/expected/model_3_3-p1-solution000006.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting p be partition({1, 2}, {3, 4}) +$ Visualisation for p +$ 1 2 +$ 3 4 + diff --git a/tests/exhaustive/issues/286/expected/model_3_3-p1-solution000007.solution b/tests/exhaustive/issues/286/expected/model_3_3-p1-solution000007.solution new file mode 100644 index 0000000000..dafa529443 --- /dev/null +++ b/tests/exhaustive/issues/286/expected/model_3_3-p1-solution000007.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting p be partition({1, 3}, {2, 4}) +$ Visualisation for p +$ 1 3 +$ 2 4 + diff --git a/tests/exhaustive/issues/286/expected/model_3_3-p1-solution000008.solution b/tests/exhaustive/issues/286/expected/model_3_3-p1-solution000008.solution new file mode 100644 index 0000000000..69d6c9f6be --- /dev/null +++ b/tests/exhaustive/issues/286/expected/model_3_3-p1-solution000008.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting p be partition({1, 4}, {2, 3}) +$ Visualisation for p +$ 1 4 +$ 2 3 + diff --git a/tests/exhaustive/issues/286/expected/model_3_3-p1.eprime-param b/tests/exhaustive/issues/286/expected/model_3_3-p1.eprime-param new file mode 100644 index 0000000000..85954307ca --- /dev/null +++ b/tests/exhaustive/issues/286/expected/model_3_3-p1.eprime-param @@ -0,0 +1,3 @@ +language ESSENCE' 1.0 + +letting b be 4 diff --git a/tests/exhaustive/issues/286/expected/model_3_3.eprime.orig b/tests/exhaustive/issues/286/expected/model_3_3.eprime.orig deleted file mode 100644 index 22f502666a..0000000000 --- a/tests/exhaustive/issues/286/expected/model_3_3.eprime.orig +++ /dev/null @@ -1,71 +0,0 @@ -language ESSENCE' 1.0 - -given b: int -find p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker: int(0..b) -find p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker: - matrix indexed by [int(1..b)] of int(0..b) -find p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values: - matrix indexed by [int(1..b), int(1..b)] of int(1..b) -branching on - [p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker, - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker, - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values] -such that - sum([toInt(q20 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker) | q20 : int(1..b)]) <= - sum([1 | q21_ExplicitVarSizeWithDummy : matrix indexed by [int(1..b)] of int(1..b + 1), - and([q21_ExplicitVarSizeWithDummy[q22] < q21_ExplicitVarSizeWithDummy[q22 + 1] \/ - q21_ExplicitVarSizeWithDummy[q22] = b + 1 - | q22 : int(1..b - 1)]), - and([q21_ExplicitVarSizeWithDummy[q23] = b + 1 -> q21_ExplicitVarSizeWithDummy[q23 + 1] = b + 1 - | q23 : int(1..b - 1)])]) - / 8, - alldifferent_except([toInt(q15 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - q16 <= - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q15]) - * - catchUndef(p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q15, q16], - 0) - | q15 : int(1..b), q16 : int(1..b)], - 0), - and([q17 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q17] >= 1 - | q17 : int(1..b)]), - and([q4 + 1 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - flatten([[p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q4]; int(1)], - [p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q4, q11] - | q11 : int(1..b)]; - int(1..2)]) - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q5] = 0 /\ - and([p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q5, q13] = 1 - | q13 : int(1..b)]) - | q5 : int(1..b)]), - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker <= b, - and([q6 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - and([q7 + 1 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q6] -> - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q6, q7] < - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q6, q7 + 1] - | q7 : int(1..b - 1)]) - | q6 : int(1..b)]), - and([q6 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - and([q8 > p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q6] -> - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q6, q8] = 1 - | q8 : int(1..b)]) - | q6 : int(1..b)]), - and([q6 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q6] <= b - | q6 : int(1..b)]), - b = - sum([toInt(q14 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker) * - catchUndef(p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q14], 0) - | q14 : int(1..b)]) - diff --git a/tests/exhaustive/issues/286/expected/model_3_4-p1-solution000001.solution b/tests/exhaustive/issues/286/expected/model_3_4-p1-solution000001.solution new file mode 100644 index 0000000000..8f7fa48018 --- /dev/null +++ b/tests/exhaustive/issues/286/expected/model_3_4-p1-solution000001.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting p be partition({1, 2, 3, 4}) +$ Visualisation for p +$ 1 2 3 4 + diff --git a/tests/exhaustive/issues/286/expected/model_3_4-p1-solution000002.solution b/tests/exhaustive/issues/286/expected/model_3_4-p1-solution000002.solution new file mode 100644 index 0000000000..556f2c0ecc --- /dev/null +++ b/tests/exhaustive/issues/286/expected/model_3_4-p1-solution000002.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting p be partition({1, 2, 3}, {4}) +$ Visualisation for p +$ 1 2 3 +$ 4 + diff --git a/tests/exhaustive/issues/286/expected/model_3_4-p1-solution000003.solution b/tests/exhaustive/issues/286/expected/model_3_4-p1-solution000003.solution new file mode 100644 index 0000000000..7781800dc4 --- /dev/null +++ b/tests/exhaustive/issues/286/expected/model_3_4-p1-solution000003.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting p be partition({1, 2, 4}, {3}) +$ Visualisation for p +$ 1 2 4 +$ 3 + diff --git a/tests/exhaustive/issues/286/expected/model_3_4-p1-solution000004.solution b/tests/exhaustive/issues/286/expected/model_3_4-p1-solution000004.solution new file mode 100644 index 0000000000..1507fcc0c1 --- /dev/null +++ b/tests/exhaustive/issues/286/expected/model_3_4-p1-solution000004.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting p be partition({1, 2}, {3, 4}) +$ Visualisation for p +$ 1 2 +$ 3 4 + diff --git a/tests/exhaustive/issues/286/expected/model_3_4-p1-solution000005.solution b/tests/exhaustive/issues/286/expected/model_3_4-p1-solution000005.solution new file mode 100644 index 0000000000..0368fc950b --- /dev/null +++ b/tests/exhaustive/issues/286/expected/model_3_4-p1-solution000005.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting p be partition({1, 3, 4}, {2}) +$ Visualisation for p +$ 1 3 4 +$ 2 + diff --git a/tests/exhaustive/issues/286/expected/model_3_4-p1-solution000006.solution b/tests/exhaustive/issues/286/expected/model_3_4-p1-solution000006.solution new file mode 100644 index 0000000000..dafa529443 --- /dev/null +++ b/tests/exhaustive/issues/286/expected/model_3_4-p1-solution000006.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting p be partition({1, 3}, {2, 4}) +$ Visualisation for p +$ 1 3 +$ 2 4 + diff --git a/tests/exhaustive/issues/286/expected/model_3_4-p1-solution000007.solution b/tests/exhaustive/issues/286/expected/model_3_4-p1-solution000007.solution new file mode 100644 index 0000000000..69d6c9f6be --- /dev/null +++ b/tests/exhaustive/issues/286/expected/model_3_4-p1-solution000007.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting p be partition({1, 4}, {2, 3}) +$ Visualisation for p +$ 1 4 +$ 2 3 + diff --git a/tests/exhaustive/issues/286/expected/model_3_4-p1-solution000008.solution b/tests/exhaustive/issues/286/expected/model_3_4-p1-solution000008.solution new file mode 100644 index 0000000000..cd8086fa4a --- /dev/null +++ b/tests/exhaustive/issues/286/expected/model_3_4-p1-solution000008.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting p be partition({1}, {2, 3, 4}) +$ Visualisation for p +$ 1 +$ 2 3 4 + diff --git a/tests/exhaustive/issues/286/expected/model_3_4-p1.eprime-param b/tests/exhaustive/issues/286/expected/model_3_4-p1.eprime-param new file mode 100644 index 0000000000..85954307ca --- /dev/null +++ b/tests/exhaustive/issues/286/expected/model_3_4-p1.eprime-param @@ -0,0 +1,3 @@ +language ESSENCE' 1.0 + +letting b be 4 diff --git a/tests/exhaustive/issues/286/expected/model_3_4.eprime.orig b/tests/exhaustive/issues/286/expected/model_3_4.eprime.orig deleted file mode 100644 index 6e0f9e3295..0000000000 --- a/tests/exhaustive/issues/286/expected/model_3_4.eprime.orig +++ /dev/null @@ -1,131 +0,0 @@ -language ESSENCE' 1.0 - -given b: int -find p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker: int(0..b) -find p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker: - matrix indexed by [int(1..b)] of int(0..b) -find p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values: - matrix indexed by [int(1..b), int(1..b)] of int(1..b) -find p_PartitionOccurrence_NumParts: int(1..b) -find p_PartitionOccurrence_WhichPart: matrix indexed by [int(1..b)] of int(1..b) -find p_PartitionOccurrence_PartSizes: matrix indexed by [int(1..b)] of int(0..b) -find p_PartitionOccurrence_FirstIndex: matrix indexed by [int(1..b)] of int(1..b) -branching on - [p_PartitionOccurrence_NumParts, p_PartitionOccurrence_WhichPart, p_PartitionOccurrence_PartSizes, - p_PartitionOccurrence_FirstIndex, p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker, - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker, - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values] -such that - sum([toInt(q58 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker) | q58 : int(1..b)]) <= - sum([1 | q59_ExplicitVarSizeWithDummy : matrix indexed by [int(1..b)] of int(1..b + 1), - and([q59_ExplicitVarSizeWithDummy[q60] < q59_ExplicitVarSizeWithDummy[q60 + 1] \/ - q59_ExplicitVarSizeWithDummy[q60] = b + 1 - | q60 : int(1..b - 1)]), - and([q59_ExplicitVarSizeWithDummy[q61] = b + 1 -> q59_ExplicitVarSizeWithDummy[q61 + 1] = b + 1 - | q61 : int(1..b - 1)])]) - / 8, - alldifferent_except([toInt(q52 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - q53 <= - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q52]) - * - catchUndef(p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q52, q53], - 0) - | q52 : int(1..b), q53 : int(1..b)], - 0), - and([q54 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q54] >= 1 - | q54 : int(1..b)]), - and([q4 + 1 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - flatten([[p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q4]; int(1)], - [p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q4, q21] - | q21 : int(1..b)]; - int(1..2)]) - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q5] = 0 /\ - and([p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q5, q23] = 1 - | q23 : int(1..b)]) - | q5 : int(1..b)]), - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker <= b, - and([q6 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - and([q7 + 1 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q6] -> - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q6, q7] < - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q6, q7 + 1] - | q7 : int(1..b - 1)]) - | q6 : int(1..b)]), - and([q6 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - and([q8 > p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q6] -> - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q6, q8] = 1 - | q8 : int(1..b)]) - | q6 : int(1..b)]), - and([q6 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q6] <= b - | q6 : int(1..b)]), - b = - sum([toInt(q55 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker) * - catchUndef(p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q55], 0) - | q55 : int(1..b)]), - and([q11 <= p_PartitionOccurrence_NumParts -> p_PartitionOccurrence_PartSizes[q11] <= b | q11 : int(1..b)]), - and([q11 > p_PartitionOccurrence_NumParts -> p_PartitionOccurrence_PartSizes[q11] = 0 | q11 : int(1..b)]), - p_PartitionOccurrence_NumParts <= b, - and([q12 <= p_PartitionOccurrence_NumParts -> or([p_PartitionOccurrence_WhichPart[q13] = q12 | q13 : int(1..b)]) - | q12 : int(3..b)]), - p_PartitionOccurrence_NumParts = max([p_PartitionOccurrence_WhichPart[q14] | q14 : int(1..b)]), - and([p_PartitionOccurrence_PartSizes[q15] = - sum([toInt(p_PartitionOccurrence_WhichPart[q16] = q15) | q16 : int(1..b)]) - | q15 : int(1..b)]), - and([q17 <= p_PartitionOccurrence_NumParts -> - and([p_PartitionOccurrence_WhichPart[q18] = q17 -> p_PartitionOccurrence_FirstIndex[q17] <= q18 - | q18 : int(1..b)]) - | q17 : int(1..b)]), - and([q17 <= p_PartitionOccurrence_NumParts -> - or([p_PartitionOccurrence_WhichPart[q18] = q17 /\ p_PartitionOccurrence_FirstIndex[q17] = q18 - | q18 : int(1..b)]) - | q17 : int(1..b)]), - and([q17 > p_PartitionOccurrence_NumParts -> p_PartitionOccurrence_FirstIndex[q17] = 1 | q17 : int(1..b)]), - and([q19 <= p_PartitionOccurrence_NumParts /\ q20 <= p_PartitionOccurrence_NumParts -> - (q19 < q20 <-> p_PartitionOccurrence_FirstIndex[q19] < p_PartitionOccurrence_FirstIndex[q20]) - | q19 : int(1..b), q20 : int(1..b)]), - and([q25 <= p_PartitionOccurrence_NumParts -> - or([q29 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - (and([q31 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q29] -> - or([p_PartitionOccurrence_WhichPart[q33] = q25 /\ - q33 = - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q29, q31] - | q33 : int(1..b)]) - | q31 : int(1..b)]) - /\ - and([p_PartitionOccurrence_WhichPart[q35] = q25 -> - or([q37 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q29] - /\ - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q29, q37] = - q35 | q37 : int(1..b)]) - | q35 : int(1..b)])) - | q29 : int(1..b)]) - | q25 : int(1..b)]), - and([q40 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - or([q42 <= p_PartitionOccurrence_NumParts /\ - (and([p_PartitionOccurrence_WhichPart[q45] = q42 -> - or([q47 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q40] - /\ - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q40, q47] = - q45 | q47 : int(1..b)]) - | q45 : int(1..b)]) - /\ - and([q49 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q40] -> - or([p_PartitionOccurrence_WhichPart[q51] = q42 /\ - q51 = - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q40, q49] - | q51 : int(1..b)]) - | q49 : int(1..b)])) - | q42 : int(1..b)]) - | q40 : int(1..b)]) - diff --git a/tests/exhaustive/issues/286/expected/model_4_1-p1-solution000001.solution b/tests/exhaustive/issues/286/expected/model_4_1-p1-solution000001.solution new file mode 100644 index 0000000000..8f7fa48018 --- /dev/null +++ b/tests/exhaustive/issues/286/expected/model_4_1-p1-solution000001.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting p be partition({1, 2, 3, 4}) +$ Visualisation for p +$ 1 2 3 4 + diff --git a/tests/exhaustive/issues/286/expected/model_4_1-p1-solution000002.solution b/tests/exhaustive/issues/286/expected/model_4_1-p1-solution000002.solution new file mode 100644 index 0000000000..cd8086fa4a --- /dev/null +++ b/tests/exhaustive/issues/286/expected/model_4_1-p1-solution000002.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting p be partition({1}, {2, 3, 4}) +$ Visualisation for p +$ 1 +$ 2 3 4 + diff --git a/tests/exhaustive/issues/286/expected/model_4_1-p1-solution000003.solution b/tests/exhaustive/issues/286/expected/model_4_1-p1-solution000003.solution new file mode 100644 index 0000000000..69d6c9f6be --- /dev/null +++ b/tests/exhaustive/issues/286/expected/model_4_1-p1-solution000003.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting p be partition({1, 4}, {2, 3}) +$ Visualisation for p +$ 1 4 +$ 2 3 + diff --git a/tests/exhaustive/issues/286/expected/model_4_1-p1-solution000004.solution b/tests/exhaustive/issues/286/expected/model_4_1-p1-solution000004.solution new file mode 100644 index 0000000000..dafa529443 --- /dev/null +++ b/tests/exhaustive/issues/286/expected/model_4_1-p1-solution000004.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting p be partition({1, 3}, {2, 4}) +$ Visualisation for p +$ 1 3 +$ 2 4 + diff --git a/tests/exhaustive/issues/286/expected/model_4_1-p1-solution000005.solution b/tests/exhaustive/issues/286/expected/model_4_1-p1-solution000005.solution new file mode 100644 index 0000000000..0368fc950b --- /dev/null +++ b/tests/exhaustive/issues/286/expected/model_4_1-p1-solution000005.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting p be partition({1, 3, 4}, {2}) +$ Visualisation for p +$ 1 3 4 +$ 2 + diff --git a/tests/exhaustive/issues/286/expected/model_4_1-p1-solution000006.solution b/tests/exhaustive/issues/286/expected/model_4_1-p1-solution000006.solution new file mode 100644 index 0000000000..1507fcc0c1 --- /dev/null +++ b/tests/exhaustive/issues/286/expected/model_4_1-p1-solution000006.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting p be partition({1, 2}, {3, 4}) +$ Visualisation for p +$ 1 2 +$ 3 4 + diff --git a/tests/exhaustive/issues/286/expected/model_4_1-p1-solution000007.solution b/tests/exhaustive/issues/286/expected/model_4_1-p1-solution000007.solution new file mode 100644 index 0000000000..7781800dc4 --- /dev/null +++ b/tests/exhaustive/issues/286/expected/model_4_1-p1-solution000007.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting p be partition({1, 2, 4}, {3}) +$ Visualisation for p +$ 1 2 4 +$ 3 + diff --git a/tests/exhaustive/issues/286/expected/model_4_1-p1-solution000008.solution b/tests/exhaustive/issues/286/expected/model_4_1-p1-solution000008.solution new file mode 100644 index 0000000000..556f2c0ecc --- /dev/null +++ b/tests/exhaustive/issues/286/expected/model_4_1-p1-solution000008.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting p be partition({1, 2, 3}, {4}) +$ Visualisation for p +$ 1 2 3 +$ 4 + diff --git a/tests/exhaustive/issues/286/expected/model_4_1-p1.eprime-param b/tests/exhaustive/issues/286/expected/model_4_1-p1.eprime-param new file mode 100644 index 0000000000..85954307ca --- /dev/null +++ b/tests/exhaustive/issues/286/expected/model_4_1-p1.eprime-param @@ -0,0 +1,3 @@ +language ESSENCE' 1.0 + +letting b be 4 diff --git a/tests/exhaustive/issues/286/expected/model_4_1.eprime b/tests/exhaustive/issues/286/expected/model_4_1.eprime new file mode 100644 index 0000000000..361ef22b1b --- /dev/null +++ b/tests/exhaustive/issues/286/expected/model_4_1.eprime @@ -0,0 +1,88 @@ +language ESSENCE' 1.0 + +given b: int +find p_PartitionOccurrence_NumParts: int(1..b) +find p_PartitionOccurrence_WhichPart: matrix indexed by [int(1..b)] of int(1..b) +find p_PartitionOccurrence_PartSizes: matrix indexed by [int(1..b)] of int(0..b) +find p_PartitionOccurrence_FirstIndex: matrix indexed by [int(1..b)] of int(1..b) +find p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker: int(0..b) +find p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence: matrix indexed by [int(1..b), int(1..b)] of bool +branching on + [p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker, + p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence, p_PartitionOccurrence_NumParts, + p_PartitionOccurrence_WhichPart, p_PartitionOccurrence_PartSizes, p_PartitionOccurrence_FirstIndex] +such that + sum([toInt(q50 <= p_PartitionOccurrence_NumParts) | q50 : int(1..b)]) <= + sum([1 | q52_ExplicitVarSizeWithDummy : matrix indexed by [int(1..b)] of int(1..b + 1), + and([q52_ExplicitVarSizeWithDummy[q53] < q52_ExplicitVarSizeWithDummy[q53 + 1] \/ + q52_ExplicitVarSizeWithDummy[q53] = b + 1 + | q53 : int(1..b - 1)]), + and([q52_ExplicitVarSizeWithDummy[q54] = b + 1 -> q52_ExplicitVarSizeWithDummy[q54 + 1] = b + 1 + | q54 : int(1..b - 1)])]) + / 8, + and([q1 <= p_PartitionOccurrence_NumParts -> p_PartitionOccurrence_PartSizes[q1] <= b | q1 : int(1..b)]), + and([q1 > p_PartitionOccurrence_NumParts -> p_PartitionOccurrence_PartSizes[q1] = 0 | q1 : int(1..b)]), + p_PartitionOccurrence_NumParts <= b, + and([q2 <= p_PartitionOccurrence_NumParts -> or([p_PartitionOccurrence_WhichPart[q3] = q2 | q3 : int(1..b)]) + | q2 : int(3..b)]), + p_PartitionOccurrence_NumParts = max([p_PartitionOccurrence_WhichPart[q4] | q4 : int(1..b)]), + and([p_PartitionOccurrence_PartSizes[q5] = sum([toInt(p_PartitionOccurrence_WhichPart[q6] = q5) | q6 : int(1..b)]) + | q5 : int(1..b)]), + and([q7 <= p_PartitionOccurrence_NumParts -> + and([p_PartitionOccurrence_WhichPart[q8] = q7 -> p_PartitionOccurrence_FirstIndex[q7] <= q8 | q8 : int(1..b)]) + | q7 : int(1..b)]), + and([q7 <= p_PartitionOccurrence_NumParts -> + or([p_PartitionOccurrence_WhichPart[q8] = q7 /\ p_PartitionOccurrence_FirstIndex[q7] = q8 | q8 : int(1..b)]) + | q7 : int(1..b)]), + and([q7 > p_PartitionOccurrence_NumParts -> p_PartitionOccurrence_FirstIndex[q7] = 1 | q7 : int(1..b)]), + and([q9 <= p_PartitionOccurrence_NumParts /\ q10 <= p_PartitionOccurrence_NumParts -> + (q9 < q10 <-> p_PartitionOccurrence_FirstIndex[q9] < p_PartitionOccurrence_FirstIndex[q10]) + | q9 : int(1..b), q10 : int(1..b)]), + and([1 = + sum([toInt(q19 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ + p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q19, q11]) + | q19 : int(1..b)]) + | q11 : int(1..b)]), + and([q47 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> + sum([toInt(p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q47, q48]) | q48 : int(1..b)]) >= 1 + | q47 : int(1..b)]), + and([q14 + 1 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> + [-toInt(p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q14, q20]) | q20 : int(1..b)] p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> + and([p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q15, q22] = false | q22 : int(1..b)]) + | q15 : int(1..b)]), + p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker <= b, + and([q16 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> + sum([toInt(p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q16, q17]) | q17 : int(1..b)]) <= b + | q16 : int(1..b)]), + b = + sum([toInt(q23 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker) * + catchUndef(sum([toInt(p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q23, q24]) + | q24 : int(1..b)]), + 0) + | q23 : int(1..b)]), + and([q27 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> + or([q29 <= p_PartitionOccurrence_NumParts /\ + (and([p_PartitionOccurrence_WhichPart[q32] = q29 -> + p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q27, q32] + | q32 : int(1..b)]) + /\ + and([p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q27, q33] -> + or([p_PartitionOccurrence_WhichPart[q35] = q29 /\ q35 = q33 | q35 : int(1..b)]) + | q33 : int(1..b)])) + | q29 : int(1..b)]) + | q27 : int(1..b)]), + and([q37 <= p_PartitionOccurrence_NumParts -> + or([q41 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ + (and([p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q41, q42] -> + or([p_PartitionOccurrence_WhichPart[q44] = q37 /\ q44 = q42 | q44 : int(1..b)]) + | q42 : int(1..b)]) + /\ + and([p_PartitionOccurrence_WhichPart[q46] = q37 -> + p_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q41, q46] + | q46 : int(1..b)])) + | q41 : int(1..b)]) + | q37 : int(1..b)]) + diff --git a/tests/exhaustive/issues/286/expected/model_4_2-p1-solution000001.solution b/tests/exhaustive/issues/286/expected/model_4_2-p1-solution000001.solution new file mode 100644 index 0000000000..8f7fa48018 --- /dev/null +++ b/tests/exhaustive/issues/286/expected/model_4_2-p1-solution000001.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting p be partition({1, 2, 3, 4}) +$ Visualisation for p +$ 1 2 3 4 + diff --git a/tests/exhaustive/issues/286/expected/model_4_2-p1-solution000002.solution b/tests/exhaustive/issues/286/expected/model_4_2-p1-solution000002.solution new file mode 100644 index 0000000000..556f2c0ecc --- /dev/null +++ b/tests/exhaustive/issues/286/expected/model_4_2-p1-solution000002.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting p be partition({1, 2, 3}, {4}) +$ Visualisation for p +$ 1 2 3 +$ 4 + diff --git a/tests/exhaustive/issues/286/expected/model_4_2-p1-solution000003.solution b/tests/exhaustive/issues/286/expected/model_4_2-p1-solution000003.solution new file mode 100644 index 0000000000..7781800dc4 --- /dev/null +++ b/tests/exhaustive/issues/286/expected/model_4_2-p1-solution000003.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting p be partition({1, 2, 4}, {3}) +$ Visualisation for p +$ 1 2 4 +$ 3 + diff --git a/tests/exhaustive/issues/286/expected/model_4_2-p1-solution000004.solution b/tests/exhaustive/issues/286/expected/model_4_2-p1-solution000004.solution new file mode 100644 index 0000000000..1507fcc0c1 --- /dev/null +++ b/tests/exhaustive/issues/286/expected/model_4_2-p1-solution000004.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting p be partition({1, 2}, {3, 4}) +$ Visualisation for p +$ 1 2 +$ 3 4 + diff --git a/tests/exhaustive/issues/286/expected/model_4_2-p1-solution000005.solution b/tests/exhaustive/issues/286/expected/model_4_2-p1-solution000005.solution new file mode 100644 index 0000000000..0368fc950b --- /dev/null +++ b/tests/exhaustive/issues/286/expected/model_4_2-p1-solution000005.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting p be partition({1, 3, 4}, {2}) +$ Visualisation for p +$ 1 3 4 +$ 2 + diff --git a/tests/exhaustive/issues/286/expected/model_4_2-p1-solution000006.solution b/tests/exhaustive/issues/286/expected/model_4_2-p1-solution000006.solution new file mode 100644 index 0000000000..dafa529443 --- /dev/null +++ b/tests/exhaustive/issues/286/expected/model_4_2-p1-solution000006.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting p be partition({1, 3}, {2, 4}) +$ Visualisation for p +$ 1 3 +$ 2 4 + diff --git a/tests/exhaustive/issues/286/expected/model_4_2-p1-solution000007.solution b/tests/exhaustive/issues/286/expected/model_4_2-p1-solution000007.solution new file mode 100644 index 0000000000..69d6c9f6be --- /dev/null +++ b/tests/exhaustive/issues/286/expected/model_4_2-p1-solution000007.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting p be partition({1, 4}, {2, 3}) +$ Visualisation for p +$ 1 4 +$ 2 3 + diff --git a/tests/exhaustive/issues/286/expected/model_4_2-p1-solution000008.solution b/tests/exhaustive/issues/286/expected/model_4_2-p1-solution000008.solution new file mode 100644 index 0000000000..cd8086fa4a --- /dev/null +++ b/tests/exhaustive/issues/286/expected/model_4_2-p1-solution000008.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting p be partition({1}, {2, 3, 4}) +$ Visualisation for p +$ 1 +$ 2 3 4 + diff --git a/tests/exhaustive/issues/286/expected/model_4_2-p1.eprime-param b/tests/exhaustive/issues/286/expected/model_4_2-p1.eprime-param new file mode 100644 index 0000000000..85954307ca --- /dev/null +++ b/tests/exhaustive/issues/286/expected/model_4_2-p1.eprime-param @@ -0,0 +1,3 @@ +language ESSENCE' 1.0 + +letting b be 4 diff --git a/tests/exhaustive/issues/286/expected/model_4_2.eprime b/tests/exhaustive/issues/286/expected/model_4_2.eprime new file mode 100644 index 0000000000..6786740b4a --- /dev/null +++ b/tests/exhaustive/issues/286/expected/model_4_2.eprime @@ -0,0 +1,118 @@ +language ESSENCE' 1.0 + +given b: int +find p_PartitionOccurrence_NumParts: int(1..b) +find p_PartitionOccurrence_WhichPart: matrix indexed by [int(1..b)] of int(1..b) +find p_PartitionOccurrence_PartSizes: matrix indexed by [int(1..b)] of int(0..b) +find p_PartitionOccurrence_FirstIndex: matrix indexed by [int(1..b)] of int(1..b) +find p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker: int(0..b) +find p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy: + matrix indexed by [int(1..b), int(1..b)] of int(1..b + 1) +branching on + [p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker, + p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy, p_PartitionOccurrence_NumParts, + p_PartitionOccurrence_WhichPart, p_PartitionOccurrence_PartSizes, p_PartitionOccurrence_FirstIndex] +such that + sum([toInt(q62 <= p_PartitionOccurrence_NumParts) | q62 : int(1..b)]) <= + sum([1 | q64_ExplicitVarSizeWithDummy : matrix indexed by [int(1..b)] of int(1..b + 1), + and([q64_ExplicitVarSizeWithDummy[q65] < q64_ExplicitVarSizeWithDummy[q65 + 1] \/ + q64_ExplicitVarSizeWithDummy[q65] = b + 1 + | q65 : int(1..b - 1)]), + and([q64_ExplicitVarSizeWithDummy[q66] = b + 1 -> q64_ExplicitVarSizeWithDummy[q66 + 1] = b + 1 + | q66 : int(1..b - 1)])]) + / 8, + and([q1 <= p_PartitionOccurrence_NumParts -> p_PartitionOccurrence_PartSizes[q1] <= b | q1 : int(1..b)]), + and([q1 > p_PartitionOccurrence_NumParts -> p_PartitionOccurrence_PartSizes[q1] = 0 | q1 : int(1..b)]), + p_PartitionOccurrence_NumParts <= b, + and([q2 <= p_PartitionOccurrence_NumParts -> or([p_PartitionOccurrence_WhichPart[q3] = q2 | q3 : int(1..b)]) + | q2 : int(3..b)]), + p_PartitionOccurrence_NumParts = max([p_PartitionOccurrence_WhichPart[q4] | q4 : int(1..b)]), + and([p_PartitionOccurrence_PartSizes[q5] = sum([toInt(p_PartitionOccurrence_WhichPart[q6] = q5) | q6 : int(1..b)]) + | q5 : int(1..b)]), + and([q7 <= p_PartitionOccurrence_NumParts -> + and([p_PartitionOccurrence_WhichPart[q8] = q7 -> p_PartitionOccurrence_FirstIndex[q7] <= q8 | q8 : int(1..b)]) + | q7 : int(1..b)]), + and([q7 <= p_PartitionOccurrence_NumParts -> + or([p_PartitionOccurrence_WhichPart[q8] = q7 /\ p_PartitionOccurrence_FirstIndex[q7] = q8 | q8 : int(1..b)]) + | q7 : int(1..b)]), + and([q7 > p_PartitionOccurrence_NumParts -> p_PartitionOccurrence_FirstIndex[q7] = 1 | q7 : int(1..b)]), + and([q9 <= p_PartitionOccurrence_NumParts /\ q10 <= p_PartitionOccurrence_NumParts -> + (q9 < q10 <-> p_PartitionOccurrence_FirstIndex[q9] < p_PartitionOccurrence_FirstIndex[q10]) + | q9 : int(1..b), q10 : int(1..b)]), + alldifferent_except([toInt(q56 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ + p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q56, q57] != + b + 1) + * + catchUndef(p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q56, q57], + 0) + | q56 : int(1..b), q57 : int(1..b)], + 0), + and([q58 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> + sum([toInt(p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q58, q60] != b + 1) + | q60 : int(1..b)]) + >= 1 + | q58 : int(1..b)]), + and([q14 + 1 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> + [p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q14, q22] | q22 : int(1..b)] p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> + and([p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q15, q24] = 1 + | q24 : int(1..b)]) + | q15 : int(1..b)]), + p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker <= b, + and([q16 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> + and([p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q16, q17] < + p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q16, q17 + 1] + \/ p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q16, q17] = b + 1 + | q17 : int(1..b - 1)]) + | q16 : int(1..b)]), + and([q16 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> + and([p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q16, q18] = b + 1 -> + p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q16, q18 + 1] = b + 1 + | q18 : int(1..b - 1)]) + | q16 : int(1..b)]), + and([q16 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> + sum([toInt(p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q16, q19] != b + 1) + | q19 : int(1..b)]) + <= b + | q16 : int(1..b)]), + b = + sum([toInt(q25 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker) * + catchUndef(sum([toInt(p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q25, q27] != + b + 1) + | q27 : int(1..b)]), + 0) + | q25 : int(1..b)]), + and([q30 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> + or([q32 <= p_PartitionOccurrence_NumParts /\ + (and([p_PartitionOccurrence_WhichPart[q35] = q32 -> + or([p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q30, q37] != b + 1 + /\ p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q30, q37] = q35 + | q37 : int(1..b)]) + | q35 : int(1..b)]) + /\ + and([p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q30, q39] != b + 1 -> + or([p_PartitionOccurrence_WhichPart[q41] = q32 /\ + q41 = p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q30, q39] + | q41 : int(1..b)]) + | q39 : int(1..b)])) + | q32 : int(1..b)]) + | q30 : int(1..b)]), + and([q43 <= p_PartitionOccurrence_NumParts -> + or([q47 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ + (and([p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q47, q49] != b + 1 -> + or([p_PartitionOccurrence_WhichPart[q51] = q43 /\ + q51 = p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q47, q49] + | q51 : int(1..b)]) + | q49 : int(1..b)]) + /\ + and([p_PartitionOccurrence_WhichPart[q53] = q43 -> + or([p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q47, q55] != b + 1 + /\ p_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q47, q55] = q53 + | q55 : int(1..b)]) + | q53 : int(1..b)])) + | q47 : int(1..b)]) + | q43 : int(1..b)]) + diff --git a/tests/exhaustive/issues/286/expected/model_4_3-p1-solution000001.solution b/tests/exhaustive/issues/286/expected/model_4_3-p1-solution000001.solution new file mode 100644 index 0000000000..8f7fa48018 --- /dev/null +++ b/tests/exhaustive/issues/286/expected/model_4_3-p1-solution000001.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting p be partition({1, 2, 3, 4}) +$ Visualisation for p +$ 1 2 3 4 + diff --git a/tests/exhaustive/issues/286/expected/model_4_3-p1-solution000002.solution b/tests/exhaustive/issues/286/expected/model_4_3-p1-solution000002.solution new file mode 100644 index 0000000000..cd8086fa4a --- /dev/null +++ b/tests/exhaustive/issues/286/expected/model_4_3-p1-solution000002.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting p be partition({1}, {2, 3, 4}) +$ Visualisation for p +$ 1 +$ 2 3 4 + diff --git a/tests/exhaustive/issues/286/expected/model_4_3-p1-solution000003.solution b/tests/exhaustive/issues/286/expected/model_4_3-p1-solution000003.solution new file mode 100644 index 0000000000..0368fc950b --- /dev/null +++ b/tests/exhaustive/issues/286/expected/model_4_3-p1-solution000003.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting p be partition({1, 3, 4}, {2}) +$ Visualisation for p +$ 1 3 4 +$ 2 + diff --git a/tests/exhaustive/issues/286/expected/model_4_3-p1-solution000004.solution b/tests/exhaustive/issues/286/expected/model_4_3-p1-solution000004.solution new file mode 100644 index 0000000000..7781800dc4 --- /dev/null +++ b/tests/exhaustive/issues/286/expected/model_4_3-p1-solution000004.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting p be partition({1, 2, 4}, {3}) +$ Visualisation for p +$ 1 2 4 +$ 3 + diff --git a/tests/exhaustive/issues/286/expected/model_4_3-p1-solution000005.solution b/tests/exhaustive/issues/286/expected/model_4_3-p1-solution000005.solution new file mode 100644 index 0000000000..556f2c0ecc --- /dev/null +++ b/tests/exhaustive/issues/286/expected/model_4_3-p1-solution000005.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting p be partition({1, 2, 3}, {4}) +$ Visualisation for p +$ 1 2 3 +$ 4 + diff --git a/tests/exhaustive/issues/286/expected/model_4_3-p1-solution000006.solution b/tests/exhaustive/issues/286/expected/model_4_3-p1-solution000006.solution new file mode 100644 index 0000000000..1507fcc0c1 --- /dev/null +++ b/tests/exhaustive/issues/286/expected/model_4_3-p1-solution000006.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting p be partition({1, 2}, {3, 4}) +$ Visualisation for p +$ 1 2 +$ 3 4 + diff --git a/tests/exhaustive/issues/286/expected/model_4_3-p1-solution000007.solution b/tests/exhaustive/issues/286/expected/model_4_3-p1-solution000007.solution new file mode 100644 index 0000000000..dafa529443 --- /dev/null +++ b/tests/exhaustive/issues/286/expected/model_4_3-p1-solution000007.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting p be partition({1, 3}, {2, 4}) +$ Visualisation for p +$ 1 3 +$ 2 4 + diff --git a/tests/exhaustive/issues/286/expected/model_4_3-p1-solution000008.solution b/tests/exhaustive/issues/286/expected/model_4_3-p1-solution000008.solution new file mode 100644 index 0000000000..69d6c9f6be --- /dev/null +++ b/tests/exhaustive/issues/286/expected/model_4_3-p1-solution000008.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting p be partition({1, 4}, {2, 3}) +$ Visualisation for p +$ 1 4 +$ 2 3 + diff --git a/tests/exhaustive/issues/286/expected/model_4_3-p1.eprime-param b/tests/exhaustive/issues/286/expected/model_4_3-p1.eprime-param new file mode 100644 index 0000000000..85954307ca --- /dev/null +++ b/tests/exhaustive/issues/286/expected/model_4_3-p1.eprime-param @@ -0,0 +1,3 @@ +language ESSENCE' 1.0 + +letting b be 4 diff --git a/tests/exhaustive/issues/286/expected/model_4_3.eprime.orig b/tests/exhaustive/issues/286/expected/model_4_3.eprime.orig deleted file mode 100644 index 69b657a99f..0000000000 --- a/tests/exhaustive/issues/286/expected/model_4_3.eprime.orig +++ /dev/null @@ -1,129 +0,0 @@ -language ESSENCE' 1.0 - -given b: int -find p_PartitionOccurrence_NumParts: int(1..b) -find p_PartitionOccurrence_WhichPart: matrix indexed by [int(1..b)] of int(1..b) -find p_PartitionOccurrence_PartSizes: matrix indexed by [int(1..b)] of int(0..b) -find p_PartitionOccurrence_FirstIndex: matrix indexed by [int(1..b)] of int(1..b) -find p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker: int(0..b) -find p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker: - matrix indexed by [int(1..b)] of int(0..b) -find p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values: - matrix indexed by [int(1..b), int(1..b)] of int(1..b) -branching on - [p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker, - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker, - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values, - p_PartitionOccurrence_NumParts, p_PartitionOccurrence_WhichPart, p_PartitionOccurrence_PartSizes, - p_PartitionOccurrence_FirstIndex] -such that - sum([toInt(q57 <= p_PartitionOccurrence_NumParts) | q57 : int(1..b)]) <= - sum([1 | q59_ExplicitVarSizeWithDummy : matrix indexed by [int(1..b)] of int(1..b + 1), - and([q59_ExplicitVarSizeWithDummy[q60] < q59_ExplicitVarSizeWithDummy[q60 + 1] \/ - q59_ExplicitVarSizeWithDummy[q60] = b + 1 - | q60 : int(1..b - 1)]), - and([q59_ExplicitVarSizeWithDummy[q61] = b + 1 -> q59_ExplicitVarSizeWithDummy[q61 + 1] = b + 1 - | q61 : int(1..b - 1)])]) - / 8, - and([q1 <= p_PartitionOccurrence_NumParts -> p_PartitionOccurrence_PartSizes[q1] <= b | q1 : int(1..b)]), - and([q1 > p_PartitionOccurrence_NumParts -> p_PartitionOccurrence_PartSizes[q1] = 0 | q1 : int(1..b)]), - p_PartitionOccurrence_NumParts <= b, - and([q2 <= p_PartitionOccurrence_NumParts -> or([p_PartitionOccurrence_WhichPart[q3] = q2 | q3 : int(1..b)]) - | q2 : int(3..b)]), - p_PartitionOccurrence_NumParts = max([p_PartitionOccurrence_WhichPart[q4] | q4 : int(1..b)]), - and([p_PartitionOccurrence_PartSizes[q5] = sum([toInt(p_PartitionOccurrence_WhichPart[q6] = q5) | q6 : int(1..b)]) - | q5 : int(1..b)]), - and([q7 <= p_PartitionOccurrence_NumParts -> - and([p_PartitionOccurrence_WhichPart[q8] = q7 -> p_PartitionOccurrence_FirstIndex[q7] <= q8 | q8 : int(1..b)]) - | q7 : int(1..b)]), - and([q7 <= p_PartitionOccurrence_NumParts -> - or([p_PartitionOccurrence_WhichPart[q8] = q7 /\ p_PartitionOccurrence_FirstIndex[q7] = q8 | q8 : int(1..b)]) - | q7 : int(1..b)]), - and([q7 > p_PartitionOccurrence_NumParts -> p_PartitionOccurrence_FirstIndex[q7] = 1 | q7 : int(1..b)]), - and([q9 <= p_PartitionOccurrence_NumParts /\ q10 <= p_PartitionOccurrence_NumParts -> - (q9 < q10 <-> p_PartitionOccurrence_FirstIndex[q9] < p_PartitionOccurrence_FirstIndex[q10]) - | q9 : int(1..b), q10 : int(1..b)]), - alldifferent_except([toInt(q53 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - q54 <= - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q53]) - * - catchUndef(p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q53, q54], - 0) - | q53 : int(1..b), q54 : int(1..b)], - 0), - and([q55 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q55] >= 1 - | q55 : int(1..b)]), - and([q14 + 1 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - flatten([[p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q14]; int(1)], - [p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q14, q21] - | q21 : int(1..b)]; - int(1..2)]) - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q15] = 0 /\ - and([p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q15, q23] = 1 - | q23 : int(1..b)]) - | q15 : int(1..b)]), - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker <= b, - and([q16 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - and([q17 + 1 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q16] -> - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q16, q17] < - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q16, q17 + 1] - | q17 : int(1..b - 1)]) - | q16 : int(1..b)]), - and([q16 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - and([q18 > p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q16] -> - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q16, q18] = 1 - | q18 : int(1..b)]) - | q16 : int(1..b)]), - and([q16 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q16] <= b - | q16 : int(1..b)]), - b = - sum([toInt(q24 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker) * - catchUndef(p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q24], 0) - | q24 : int(1..b)]), - and([q27 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - or([q29 <= p_PartitionOccurrence_NumParts /\ - (and([p_PartitionOccurrence_WhichPart[q32] = q29 -> - or([q34 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q27] - /\ - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q27, q34] = - q32 | q34 : int(1..b)]) - | q32 : int(1..b)]) - /\ - and([q36 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q27] -> - or([p_PartitionOccurrence_WhichPart[q38] = q29 /\ - q38 = - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q27, q36] - | q38 : int(1..b)]) - | q36 : int(1..b)])) - | q29 : int(1..b)]) - | q27 : int(1..b)]), - and([q40 <= p_PartitionOccurrence_NumParts -> - or([q44 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - (and([q46 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q44] -> - or([p_PartitionOccurrence_WhichPart[q48] = q40 /\ - q48 = - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q44, q46] - | q48 : int(1..b)]) - | q46 : int(1..b)]) - /\ - and([p_PartitionOccurrence_WhichPart[q50] = q40 -> - or([q52 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q44] - /\ - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q44, q52] = - q50 | q52 : int(1..b)]) - | q50 : int(1..b)])) - | q44 : int(1..b)]) - | q40 : int(1..b)]) - diff --git a/tests/exhaustive/issues/286/expected/model_4_4-p1-solution000001.solution b/tests/exhaustive/issues/286/expected/model_4_4-p1-solution000001.solution new file mode 100644 index 0000000000..8f7fa48018 --- /dev/null +++ b/tests/exhaustive/issues/286/expected/model_4_4-p1-solution000001.solution @@ -0,0 +1,6 @@ +language Essence 1.3 + +letting p be partition({1, 2, 3, 4}) +$ Visualisation for p +$ 1 2 3 4 + diff --git a/tests/exhaustive/issues/286/expected/model_4_4-p1-solution000002.solution b/tests/exhaustive/issues/286/expected/model_4_4-p1-solution000002.solution new file mode 100644 index 0000000000..556f2c0ecc --- /dev/null +++ b/tests/exhaustive/issues/286/expected/model_4_4-p1-solution000002.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting p be partition({1, 2, 3}, {4}) +$ Visualisation for p +$ 1 2 3 +$ 4 + diff --git a/tests/exhaustive/issues/286/expected/model_4_4-p1-solution000003.solution b/tests/exhaustive/issues/286/expected/model_4_4-p1-solution000003.solution new file mode 100644 index 0000000000..7781800dc4 --- /dev/null +++ b/tests/exhaustive/issues/286/expected/model_4_4-p1-solution000003.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting p be partition({1, 2, 4}, {3}) +$ Visualisation for p +$ 1 2 4 +$ 3 + diff --git a/tests/exhaustive/issues/286/expected/model_4_4-p1-solution000004.solution b/tests/exhaustive/issues/286/expected/model_4_4-p1-solution000004.solution new file mode 100644 index 0000000000..1507fcc0c1 --- /dev/null +++ b/tests/exhaustive/issues/286/expected/model_4_4-p1-solution000004.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting p be partition({1, 2}, {3, 4}) +$ Visualisation for p +$ 1 2 +$ 3 4 + diff --git a/tests/exhaustive/issues/286/expected/model_4_4-p1-solution000005.solution b/tests/exhaustive/issues/286/expected/model_4_4-p1-solution000005.solution new file mode 100644 index 0000000000..0368fc950b --- /dev/null +++ b/tests/exhaustive/issues/286/expected/model_4_4-p1-solution000005.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting p be partition({1, 3, 4}, {2}) +$ Visualisation for p +$ 1 3 4 +$ 2 + diff --git a/tests/exhaustive/issues/286/expected/model_4_4-p1-solution000006.solution b/tests/exhaustive/issues/286/expected/model_4_4-p1-solution000006.solution new file mode 100644 index 0000000000..dafa529443 --- /dev/null +++ b/tests/exhaustive/issues/286/expected/model_4_4-p1-solution000006.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting p be partition({1, 3}, {2, 4}) +$ Visualisation for p +$ 1 3 +$ 2 4 + diff --git a/tests/exhaustive/issues/286/expected/model_4_4-p1-solution000007.solution b/tests/exhaustive/issues/286/expected/model_4_4-p1-solution000007.solution new file mode 100644 index 0000000000..69d6c9f6be --- /dev/null +++ b/tests/exhaustive/issues/286/expected/model_4_4-p1-solution000007.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting p be partition({1, 4}, {2, 3}) +$ Visualisation for p +$ 1 4 +$ 2 3 + diff --git a/tests/exhaustive/issues/286/expected/model_4_4-p1-solution000008.solution b/tests/exhaustive/issues/286/expected/model_4_4-p1-solution000008.solution new file mode 100644 index 0000000000..cd8086fa4a --- /dev/null +++ b/tests/exhaustive/issues/286/expected/model_4_4-p1-solution000008.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting p be partition({1}, {2, 3, 4}) +$ Visualisation for p +$ 1 +$ 2 3 4 + diff --git a/tests/exhaustive/issues/286/expected/model_4_4-p1.eprime-param b/tests/exhaustive/issues/286/expected/model_4_4-p1.eprime-param new file mode 100644 index 0000000000..85954307ca --- /dev/null +++ b/tests/exhaustive/issues/286/expected/model_4_4-p1.eprime-param @@ -0,0 +1,3 @@ +language ESSENCE' 1.0 + +letting b be 4 diff --git a/tests/exhaustive/issues/286/expected/model_4_4.eprime b/tests/exhaustive/issues/286/expected/model_4_4.eprime new file mode 100644 index 0000000000..5a6173b451 --- /dev/null +++ b/tests/exhaustive/issues/286/expected/model_4_4.eprime @@ -0,0 +1,38 @@ +language ESSENCE' 1.0 + +given b: int +find p_PartitionOccurrence_NumParts: int(1..b) +find p_PartitionOccurrence_WhichPart: matrix indexed by [int(1..b)] of int(1..b) +find p_PartitionOccurrence_PartSizes: matrix indexed by [int(1..b)] of int(0..b) +find p_PartitionOccurrence_FirstIndex: matrix indexed by [int(1..b)] of int(1..b) +branching on + [p_PartitionOccurrence_NumParts, p_PartitionOccurrence_WhichPart, p_PartitionOccurrence_PartSizes, + p_PartitionOccurrence_FirstIndex] +such that + sum([toInt(q12 <= p_PartitionOccurrence_NumParts) | q12 : int(1..b)]) <= + sum([1 | q14_ExplicitVarSizeWithDummy : matrix indexed by [int(1..b)] of int(1..b + 1), + and([q14_ExplicitVarSizeWithDummy[q15] < q14_ExplicitVarSizeWithDummy[q15 + 1] \/ + q14_ExplicitVarSizeWithDummy[q15] = b + 1 + | q15 : int(1..b - 1)]), + and([q14_ExplicitVarSizeWithDummy[q16] = b + 1 -> q14_ExplicitVarSizeWithDummy[q16 + 1] = b + 1 + | q16 : int(1..b - 1)])]) + / 8, + and([q1 <= p_PartitionOccurrence_NumParts -> p_PartitionOccurrence_PartSizes[q1] <= b | q1 : int(1..b)]), + and([q1 > p_PartitionOccurrence_NumParts -> p_PartitionOccurrence_PartSizes[q1] = 0 | q1 : int(1..b)]), + p_PartitionOccurrence_NumParts <= b, + and([q2 <= p_PartitionOccurrence_NumParts -> or([p_PartitionOccurrence_WhichPart[q3] = q2 | q3 : int(1..b)]) + | q2 : int(3..b)]), + p_PartitionOccurrence_NumParts = max([p_PartitionOccurrence_WhichPart[q4] | q4 : int(1..b)]), + and([p_PartitionOccurrence_PartSizes[q5] = sum([toInt(p_PartitionOccurrence_WhichPart[q6] = q5) | q6 : int(1..b)]) + | q5 : int(1..b)]), + and([q7 <= p_PartitionOccurrence_NumParts -> + and([p_PartitionOccurrence_WhichPart[q8] = q7 -> p_PartitionOccurrence_FirstIndex[q7] <= q8 | q8 : int(1..b)]) + | q7 : int(1..b)]), + and([q7 <= p_PartitionOccurrence_NumParts -> + or([p_PartitionOccurrence_WhichPart[q8] = q7 /\ p_PartitionOccurrence_FirstIndex[q7] = q8 | q8 : int(1..b)]) + | q7 : int(1..b)]), + and([q7 > p_PartitionOccurrence_NumParts -> p_PartitionOccurrence_FirstIndex[q7] = 1 | q7 : int(1..b)]), + and([q9 <= p_PartitionOccurrence_NumParts /\ q10 <= p_PartitionOccurrence_NumParts -> + (q9 < q10 <-> p_PartitionOccurrence_FirstIndex[q9] < p_PartitionOccurrence_FirstIndex[q10]) + | q9 : int(1..b), q10 : int(1..b)]) + diff --git a/tests/exhaustive/mildly_interesting/cyclic_graph/expected/model-cyc1-solution000001.solution b/tests/exhaustive/mildly_interesting/cyclic_graph/expected/model-cyc1-solution000001.solution new file mode 100644 index 0000000000..04a3a6738a --- /dev/null +++ b/tests/exhaustive/mildly_interesting/cyclic_graph/expected/model-cyc1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting b be 0 diff --git a/tests/exhaustive/mildly_interesting/cyclic_graph/expected/model-cyc1.eprime-param b/tests/exhaustive/mildly_interesting/cyclic_graph/expected/model-cyc1.eprime-param new file mode 100644 index 0000000000..3c6853085f --- /dev/null +++ b/tests/exhaustive/mildly_interesting/cyclic_graph/expected/model-cyc1.eprime-param @@ -0,0 +1,6 @@ +language ESSENCE' 1.0 + +letting n be 5 +letting g_RelationAsSet_Explicit_1 be [1, 2; int(1..2)] +letting g_RelationAsSet_Explicit_2 be [2, 1; int(1..2)] +letting fin1 be 2 diff --git a/tests/exhaustive/mildly_interesting/cyclic_graph/expected/model-cyc2-solution000001.solution b/tests/exhaustive/mildly_interesting/cyclic_graph/expected/model-cyc2-solution000001.solution new file mode 100644 index 0000000000..04a3a6738a --- /dev/null +++ b/tests/exhaustive/mildly_interesting/cyclic_graph/expected/model-cyc2-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting b be 0 diff --git a/tests/exhaustive/mildly_interesting/cyclic_graph/expected/model-cyc2.eprime-param b/tests/exhaustive/mildly_interesting/cyclic_graph/expected/model-cyc2.eprime-param new file mode 100644 index 0000000000..a9b1ce1d7f --- /dev/null +++ b/tests/exhaustive/mildly_interesting/cyclic_graph/expected/model-cyc2.eprime-param @@ -0,0 +1,6 @@ +language ESSENCE' 1.0 + +letting n be 5 +letting g_RelationAsSet_Explicit_1 be [1, 2, 3; int(1..3)] +letting g_RelationAsSet_Explicit_2 be [2, 3, 1; int(1..3)] +letting fin1 be 3 diff --git a/tests/exhaustive/mildly_interesting/cyclic_graph/expected/model-non-solution000001.solution b/tests/exhaustive/mildly_interesting/cyclic_graph/expected/model-non-solution000001.solution new file mode 100644 index 0000000000..04a3a6738a --- /dev/null +++ b/tests/exhaustive/mildly_interesting/cyclic_graph/expected/model-non-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting b be 0 diff --git a/tests/exhaustive/mildly_interesting/cyclic_graph/expected/model-non.eprime-param b/tests/exhaustive/mildly_interesting/cyclic_graph/expected/model-non.eprime-param new file mode 100644 index 0000000000..651096c47a --- /dev/null +++ b/tests/exhaustive/mildly_interesting/cyclic_graph/expected/model-non.eprime-param @@ -0,0 +1,6 @@ +language ESSENCE' 1.0 + +letting n be 5 +letting g_RelationAsSet_Explicit_1 be [1, 2; int(1..2)] +letting g_RelationAsSet_Explicit_2 be [2, 3; int(1..2)] +letting fin1 be 2 diff --git a/tests/exhaustive/mildly_interesting/gchq_2016/expected/model-inst-solution000001.solution b/tests/exhaustive/mildly_interesting/gchq_2016/expected/model-inst-solution000001.solution new file mode 100644 index 0000000000..4ad15df1dd --- /dev/null +++ b/tests/exhaustive/mildly_interesting/gchq_2016/expected/model-inst-solution000001.solution @@ -0,0 +1,182 @@ +language Essence 1.3 + +letting bitmap be + [[true, true, true, true, true, true, true, false, true, true, true, false, false, false, true, false, true, + false, true, true, true, true, true, true, true; + int(1..25)], + [true, false, false, false, false, false, true, false, true, true, false, true, true, false, false, false, + false, false, true, false, false, false, false, false, true; + int(1..25)], + [true, false, true, true, true, false, true, false, false, false, false, false, true, true, true, false, true, + false, true, false, true, true, true, false, true; + int(1..25)], + [true, false, true, true, true, false, true, false, true, false, false, true, true, true, true, true, true, + false, true, false, true, true, true, false, true; + int(1..25)], + [true, false, true, true, true, false, true, false, false, true, true, true, true, true, false, true, true, + false, true, false, true, true, true, false, true; + int(1..25)], + [true, false, false, false, false, false, true, false, false, true, true, false, false, false, false, false, + false, false, true, false, false, false, false, false, true; + int(1..25)], + [true, true, true, true, true, true, true, false, true, false, true, false, true, false, true, false, true, + false, true, true, true, true, true, true, true; + int(1..25)], + [false, false, false, false, false, false, false, false, true, true, true, false, false, false, true, true, + true, false, false, false, false, false, false, false, false; + int(1..25)], + [true, false, true, true, false, true, true, true, false, false, true, false, true, false, true, true, true, + false, true, false, false, true, false, true, true; + int(1..25)], + [true, false, true, false, false, false, false, false, false, true, true, true, false, true, true, false, + false, false, false, true, false, false, false, true, false; + int(1..25)], + [false, true, true, true, true, false, true, false, true, true, true, true, false, true, true, false, true, + false, false, false, false, true, true, false, false; + int(1..25)], + [false, true, false, true, false, false, false, true, false, false, false, true, false, true, false, true, + true, true, true, false, true, false, true, true, true; + int(1..25)], + [false, false, true, true, false, false, true, false, true, false, true, false, false, false, false, false, + false, true, true, false, true, true, true, true, true; + int(1..25)], + [false, false, false, true, true, true, false, true, true, false, true, true, false, true, true, true, true, + true, true, false, true, true, true, false, true; + int(1..25)], + [true, false, true, true, true, true, true, true, true, true, true, false, true, false, true, false, false, + true, true, false, false, false, false, true, false; + int(1..25)], + [false, true, true, false, true, false, false, true, true, false, false, false, true, true, false, true, true, + true, false, false, false, false, false, true, false; + int(1..25)], + [true, true, true, false, true, false, true, false, true, false, false, true, false, false, false, false, true, + true, true, true, true, false, true, false, false; + int(1..25)], + [false, false, false, false, false, false, false, false, true, false, false, false, true, true, false, true, + true, false, false, false, true, true, true, true, true; + int(1..25)], + [true, true, true, true, true, true, true, false, true, false, false, true, true, false, false, false, true, + false, true, false, true, false, true, true, true; + int(1..25)], + [true, false, false, false, false, false, true, false, true, true, false, false, true, false, false, true, + true, false, false, false, true, true, false, true, false; + int(1..25)], + [true, false, true, true, true, false, true, false, false, false, true, true, true, true, false, false, true, + true, true, true, true, false, false, true, false; + int(1..25)], + [true, false, true, true, true, false, true, false, true, true, true, false, true, true, true, true, true, + true, true, true, true, true, false, true, true; + int(1..25)], + [true, false, true, true, true, false, true, false, true, false, false, true, true, true, true, true, true, + false, true, true, true, true, true, true, false; + int(1..25)], + [true, false, false, false, false, false, true, false, false, true, true, false, false, false, false, false, + false, true, false, true, false, true, true, false, false; + int(1..25)], + [true, true, true, true, true, true, true, false, true, true, false, false, false, true, false, true, true, + false, false, false, true, true, true, true, true; + int(1..25)]; + int(1..25)] +$ Visualisation for bitmap +$ T T T T T T T _ T T T _ _ _ T _ T _ T T T T T T T +$ T _ _ _ _ _ T _ T T _ T T _ _ _ _ _ T _ _ _ _ _ T +$ T _ T T T _ T _ _ _ _ _ T T T _ T _ T _ T T T _ T +$ T _ T T T _ T _ T _ _ T T T T T T _ T _ T T T _ T +$ T _ T T T _ T _ _ T T T T T _ T T _ T _ T T T _ T +$ T _ _ _ _ _ T _ _ T T _ _ _ _ _ _ _ T _ _ _ _ _ T +$ T T T T T T T _ T _ T _ T _ T _ T _ T T T T T T T +$ _ _ _ _ _ _ _ _ T T T _ _ _ T T T _ _ _ _ _ _ _ _ +$ T _ T T _ T T T _ _ T _ T _ T T T _ T _ _ T _ T T +$ T _ T _ _ _ _ _ _ T T T _ T T _ _ _ _ T _ _ _ T _ +$ _ T T T T _ T _ T T T T _ T T _ T _ _ _ _ T T _ _ +$ _ T _ T _ _ _ T _ _ _ T _ T _ T T T T _ T _ T T T +$ _ _ T T _ _ T _ T _ T _ _ _ _ _ _ T T _ T T T T T +$ _ _ _ T T T _ T T _ T T _ T T T T T T _ T T T _ T +$ T _ T T T T T T T T T _ T _ T _ _ T T _ _ _ _ T _ +$ _ T T _ T _ _ T T _ _ _ T T _ T T T _ _ _ _ _ T _ +$ T T T _ T _ T _ T _ _ T _ _ _ _ T T T T T _ T _ _ +$ _ _ _ _ _ _ _ _ T _ _ _ T T _ T T _ _ _ T T T T T +$ T T T T T T T _ T _ _ T T _ _ _ T _ T _ T _ T T T +$ T _ _ _ _ _ T _ T T _ _ T _ _ T T _ _ _ T T _ T _ +$ T _ T T T _ T _ _ _ T T T T _ _ T T T T T _ _ T _ +$ T _ T T T _ T _ T T T _ T T T T T T T T T T _ T T +$ T _ T T T _ T _ T _ _ T T T T T T _ T T T T T T _ +$ T _ _ _ _ _ T _ _ T T _ _ _ _ _ _ T _ T _ T T _ _ +$ T T T T T T T _ T T _ _ _ T _ T T _ _ _ T T T T T + +letting horizontalLocs be + [sequence(1, 9, 15, 17, 19), sequence(1, 7, 9, 12, 19, 25), sequence(1, 3, 7, 13, 17, 19, 21, 25), + sequence(1, 3, 7, 9, 12, 19, 21, 25), sequence(1, 3, 7, 10, 16, 19, 21, 25), sequence(1, 7, 10, 19, 25), + sequence(1, 9, 11, 13, 15, 17, 19), sequence(9, 15), sequence(1, 3, 6, 11, 13, 15, 19, 22, 24), + sequence(1, 3, 10, 14, 20, 24), sequence(2, 7, 9, 14, 17, 22), sequence(2, 4, 8, 12, 14, 16, 21, 23), + sequence(3, 7, 9, 11, 18, 21), sequence(4, 8, 11, 14, 21, 25), sequence(1, 3, 13, 15, 18, 24), + sequence(2, 5, 8, 13, 16, 24), sequence(1, 5, 7, 9, 12, 17, 23), sequence(9, 13, 16, 21), + sequence(1, 9, 12, 17, 19, 21, 23), sequence(1, 7, 9, 13, 16, 21, 24), sequence(1, 3, 7, 11, 17, 24), + sequence(1, 3, 7, 9, 13, 24), sequence(1, 3, 7, 9, 12, 19), sequence(1, 7, 10, 18, 20, 22), + sequence(1, 9, 14, 16, 21); + int(1..25)] +$ Visualisation for horizontalLocs +$ 1 9 15 17 19 +$ 1 7 9 12 19 25 +$ 1 3 7 13 17 19 21 25 +$ 1 3 7 9 12 19 21 25 +$ 1 3 7 10 16 19 21 25 +$ 1 7 10 19 25 +$ 1 9 11 13 15 17 19 +$ 9 15 +$ 1 3 6 11 13 15 19 22 24 +$ 1 3 10 14 20 24 +$ 2 7 9 14 17 22 +$ 2 4 8 12 14 16 21 23 +$ 3 7 9 11 18 21 +$ 4 8 11 14 21 25 +$ 1 3 13 15 18 24 +$ 2 5 8 13 16 24 +$ 1 5 7 9 12 17 23 +$ 9 13 16 21 +$ 1 9 12 17 19 21 23 +$ 1 7 9 13 16 21 24 +$ 1 3 7 11 17 24 +$ 1 3 7 9 13 24 +$ 1 3 7 9 12 19 +$ 1 7 10 18 20 22 +$ 1 9 14 16 21 + +letting verticalLocs be + [sequence(1, 9, 15, 17, 19), sequence(1, 7, 11, 16, 19, 25), sequence(1, 3, 7, 9, 13, 15, 19, 21, 25), + sequence(1, 3, 7, 9, 11, 19, 21, 25), sequence(1, 3, 7, 11, 14, 19, 21, 25), sequence(1, 7, 9, 14, 19, 25), + sequence(1, 9, 11, 13, 15, 17, 19), sequence(9, 12, 14), sequence(1, 4, 7, 11, 13, 22, 25), + sequence(1, 5, 8, 10, 15, 20, 22, 24), sequence(1, 5, 13, 21, 24), sequence(2, 4, 10, 14, 17, 19, 21, 23), + sequence(2, 7, 9, 15, 18), sequence(3, 10, 14, 16, 18, 21, 25), sequence(1, 3, 7, 14, 22), + sequence(4, 8, 12, 14, 16, 18, 20, 22, 25), sequence(1, 3, 7, 11, 14, 16, 25), sequence(12, 21, 24), + sequence(1, 9, 12, 17, 19, 21), sequence(1, 7, 10, 17, 21), sequence(1, 3, 7, 12, 17, 25), + sequence(1, 3, 7, 9, 11, 13, 18, 20, 22), sequence(1, 3, 7, 11, 17, 23), sequence(1, 7, 9, 12, 15, 18, 25), + sequence(1, 9, 12, 18, 22, 25); + int(1..25)] +$ Visualisation for verticalLocs +$ 1 9 15 17 19 +$ 1 7 11 16 19 25 +$ 1 3 7 9 13 15 19 21 25 +$ 1 3 7 9 11 19 21 25 +$ 1 3 7 11 14 19 21 25 +$ 1 7 9 14 19 25 +$ 1 9 11 13 15 17 19 +$ 9 12 14 +$ 1 4 7 11 13 22 25 +$ 1 5 8 10 15 20 22 24 +$ 1 5 13 21 24 +$ 2 4 10 14 17 19 21 23 +$ 2 7 9 15 18 +$ 3 10 14 16 18 21 25 +$ 1 3 7 14 22 +$ 4 8 12 14 16 18 20 22 25 +$ 1 3 7 11 14 16 25 +$ 12 21 24 +$ 1 9 12 17 19 21 +$ 1 7 10 17 21 +$ 1 3 7 12 17 25 +$ 1 3 7 9 11 13 18 20 22 +$ 1 3 7 11 17 23 +$ 1 7 9 12 15 18 25 +$ 1 9 12 18 22 25 + diff --git a/tests/exhaustive/mildly_interesting/gchq_2016/expected/model-inst.eprime-param b/tests/exhaustive/mildly_interesting/gchq_2016/expected/model-inst.eprime-param new file mode 100644 index 0000000000..9712bd75a8 --- /dev/null +++ b/tests/exhaustive/mildly_interesting/gchq_2016/expected/model-inst.eprime-param @@ -0,0 +1,98 @@ +language ESSENCE' 1.0 + +letting n be 25 +letting horizontalClues_ExplicitBounded_Length be + [5, 6, 8, 8, 8, 5, 7, 2, 9, 6, 6, 8, 6, 6, 6, 6, 7, 4, 7, 7, 6, 6, 6, 6, 5; int(1..25)] +letting horizontalClues_ExplicitBounded_Values be + [[7, 3, 1, 1, 7, 1, 1, 1, 1; int(1..9)], [1, 1, 2, 2, 1, 1, 1, 1, 1; int(1..9)], + [1, 3, 1, 3, 1, 1, 3, 1, 1; int(1..9)], [1, 3, 1, 1, 6, 1, 3, 1, 1; int(1..9)], + [1, 3, 1, 5, 2, 1, 3, 1, 1; int(1..9)], [1, 1, 2, 1, 1, 1, 1, 1, 1; int(1..9)], + [7, 1, 1, 1, 1, 1, 7, 1, 1; int(1..9)], [3, 3, 1, 1, 1, 1, 1, 1, 1; int(1..9)], + [1, 2, 3, 1, 1, 3, 1, 1, 2; int(1..9)], [1, 1, 3, 2, 1, 1, 1, 1, 1; int(1..9)], + [4, 1, 4, 2, 1, 2, 1, 1, 1; int(1..9)], [1, 1, 1, 1, 1, 4, 1, 3, 1; int(1..9)], + [2, 1, 1, 1, 2, 5, 1, 1, 1; int(1..9)], [3, 2, 2, 6, 3, 1, 1, 1, 1; int(1..9)], + [1, 9, 1, 1, 2, 1, 1, 1, 1; int(1..9)], [2, 1, 2, 2, 3, 1, 1, 1, 1; int(1..9)], + [3, 1, 1, 1, 1, 5, 1, 1, 1; int(1..9)], [1, 2, 2, 5, 1, 1, 1, 1, 1; int(1..9)], + [7, 1, 2, 1, 1, 1, 3, 1, 1; int(1..9)], [1, 1, 2, 1, 2, 2, 1, 1, 1; int(1..9)], + [1, 3, 1, 4, 5, 1, 1, 1, 1; int(1..9)], [1, 3, 1, 3, 10, 2, 1, 1, 1; int(1..9)], + [1, 3, 1, 1, 6, 6, 1, 1, 1; int(1..9)], [1, 1, 2, 1, 1, 2, 1, 1, 1; int(1..9)], + [7, 2, 1, 2, 5, 1, 1, 1, 1; int(1..9)]; + int(1..25)] +$ Visualisation for horizontalClues_ExplicitBounded_Values +$ 7 3 1 1 7 1 1 1 1 +$ 1 1 2 2 1 1 1 1 1 +$ 1 3 1 3 1 1 3 1 1 +$ 1 3 1 1 6 1 3 1 1 +$ 1 3 1 5 2 1 3 1 1 +$ 1 1 2 1 1 1 1 1 1 +$ 7 1 1 1 1 1 7 1 1 +$ 3 3 1 1 1 1 1 1 1 +$ 1 2 3 1 1 3 1 1 2 +$ 1 1 3 2 1 1 1 1 1 +$ 4 1 4 2 1 2 1 1 1 +$ 1 1 1 1 1 4 1 3 1 +$ 2 1 1 1 2 5 1 1 1 +$ 3 2 2 6 3 1 1 1 1 +$ 1 9 1 1 2 1 1 1 1 +$ 2 1 2 2 3 1 1 1 1 +$ 3 1 1 1 1 5 1 1 1 +$ 1 2 2 5 1 1 1 1 1 +$ 7 1 2 1 1 1 3 1 1 +$ 1 1 2 1 2 2 1 1 1 +$ 1 3 1 4 5 1 1 1 1 +$ 1 3 1 3 10 2 1 1 1 +$ 1 3 1 1 6 6 1 1 1 +$ 1 1 2 1 1 2 1 1 1 +$ 7 2 1 2 5 1 1 1 1 + +letting verticalClues_ExplicitBounded_Length be + [5, 6, 9, 8, 8, 6, 7, 3, 7, 8, 5, 8, 5, 7, 5, 9, 7, 3, 6, 5, 6, 9, 6, 7, 6; int(1..25)] +letting verticalClues_ExplicitBounded_Values be + [[7, 2, 1, 1, 7, 1, 1, 1, 1; int(1..9)], [1, 1, 2, 2, 1, 1, 1, 1, 1; int(1..9)], + [1, 3, 1, 3, 1, 3, 1, 3, 1; int(1..9)], [1, 3, 1, 1, 5, 1, 3, 1, 1; int(1..9)], + [1, 3, 1, 1, 4, 1, 3, 1, 1; int(1..9)], [1, 1, 1, 2, 1, 1, 1, 1, 1; int(1..9)], + [7, 1, 1, 1, 1, 1, 7, 1, 1; int(1..9)], [1, 1, 3, 1, 1, 1, 1, 1, 1; int(1..9)], + [2, 1, 2, 1, 8, 2, 1, 1, 1; int(1..9)], [2, 2, 1, 2, 1, 1, 1, 2, 1; int(1..9)], + [1, 7, 3, 2, 1, 1, 1, 1, 1; int(1..9)], [1, 2, 3, 1, 1, 1, 1, 1, 1; int(1..9)], + [4, 1, 1, 2, 6, 1, 1, 1, 1; int(1..9)], [3, 3, 1, 1, 1, 3, 1, 1, 1; int(1..9)], + [1, 2, 5, 2, 2, 1, 1, 1, 1; int(1..9)], [2, 2, 1, 1, 1, 1, 1, 2, 1; int(1..9)], + [1, 3, 3, 2, 1, 8, 1, 1, 1; int(1..9)], [6, 2, 1, 1, 1, 1, 1, 1, 1; int(1..9)], + [7, 1, 4, 1, 1, 3, 1, 1, 1; int(1..9)], [1, 1, 1, 1, 4, 1, 1, 1, 1; int(1..9)], + [1, 3, 1, 3, 7, 1, 1, 1, 1; int(1..9)], [1, 3, 1, 1, 1, 2, 1, 1, 4; int(1..9)], + [1, 3, 1, 4, 3, 3, 1, 1, 1; int(1..9)], [1, 1, 2, 2, 2, 6, 1, 1, 1; int(1..9)], + [7, 1, 3, 2, 1, 1, 1, 1, 1; int(1..9)]; + int(1..25)] +$ Visualisation for verticalClues_ExplicitBounded_Values +$ 7 2 1 1 7 1 1 1 1 +$ 1 1 2 2 1 1 1 1 1 +$ 1 3 1 3 1 3 1 3 1 +$ 1 3 1 1 5 1 3 1 1 +$ 1 3 1 1 4 1 3 1 1 +$ 1 1 1 2 1 1 1 1 1 +$ 7 1 1 1 1 1 7 1 1 +$ 1 1 3 1 1 1 1 1 1 +$ 2 1 2 1 8 2 1 1 1 +$ 2 2 1 2 1 1 1 2 1 +$ 1 7 3 2 1 1 1 1 1 +$ 1 2 3 1 1 1 1 1 1 +$ 4 1 1 2 6 1 1 1 1 +$ 3 3 1 1 1 3 1 1 1 +$ 1 2 5 2 2 1 1 1 1 +$ 2 2 1 1 1 1 1 2 1 +$ 1 3 3 2 1 8 1 1 1 +$ 6 2 1 1 1 1 1 1 1 +$ 7 1 4 1 1 3 1 1 1 +$ 1 1 1 1 4 1 1 1 1 +$ 1 3 1 3 7 1 1 1 1 +$ 1 3 1 1 1 2 1 1 4 +$ 1 3 1 4 3 3 1 1 1 +$ 1 1 2 2 2 6 1 1 1 +$ 7 1 3 2 1 1 1 1 1 + +letting prefilled_Explicit_1 be + [4, 4, 4, 4, 4, 9, 9, 9, 9, 9, 9, 17, 17, 17, 17, 22, 22, 22, 22, 22, 22, 22; int(1..22)] +letting prefilled_Explicit_2 be + [4, 5, 13, 14, 22, 7, 8, 11, 15, 16, 19, 7, 12, 17, 21, 4, 5, 10, 11, 16, 21, 22; int(1..22)] +letting fin1 be 9 +letting fin2 be 9 +letting fin3 be 22 diff --git a/tests/exhaustive/mildly_interesting/gchq_2016/expected/model.eprime b/tests/exhaustive/mildly_interesting/gchq_2016/expected/model.eprime new file mode 100644 index 0000000000..d06f46d615 --- /dev/null +++ b/tests/exhaustive/mildly_interesting/gchq_2016/expected/model.eprime @@ -0,0 +1,127 @@ +language ESSENCE' 1.0 + +given n: int +given fin1: int +given horizontalClues_ExplicitBounded_Length: matrix indexed by [int(1..n)] of int(0..fin1) +given horizontalClues_ExplicitBounded_Values: matrix indexed by [int(1..n), int(1..fin1)] of int(1..n) +find horizontalLocs_ExplicitBounded_Length: matrix indexed by [int(1..n)] of int(0..n) +find horizontalLocs_ExplicitBounded_Values: matrix indexed by [int(1..n), int(1..n)] of int(1..n) +given fin2: int +given verticalClues_ExplicitBounded_Length: matrix indexed by [int(1..n)] of int(0..fin2) +given verticalClues_ExplicitBounded_Values: matrix indexed by [int(1..n), int(1..fin2)] of int(1..n) +find verticalLocs_ExplicitBounded_Length: matrix indexed by [int(1..n)] of int(0..n) +find verticalLocs_ExplicitBounded_Values: matrix indexed by [int(1..n), int(1..n)] of int(1..n) +find bitmap: matrix indexed by [int(1..n), int(1..n)] of bool +given fin3: int +given prefilled_Explicit_1: matrix indexed by [int(1..fin3)] of int(1..n) +given prefilled_Explicit_2: matrix indexed by [int(1..fin3)] of int(1..n) +branching on + [horizontalLocs_ExplicitBounded_Length, horizontalLocs_ExplicitBounded_Values, verticalLocs_ExplicitBounded_Length, + verticalLocs_ExplicitBounded_Values, bitmap] +such that + and([horizontalLocs_ExplicitBounded_Length[row] = horizontalClues_ExplicitBounded_Length[row] | row : int(1..n)]), + and([and([and([horizontalLocs_ExplicitBounded_Values[row, q10] > + horizontalLocs_ExplicitBounded_Values[row, q10 - 1] + + horizontalClues_ExplicitBounded_Values[row, q10 - 1], + q10 <= horizontalLocs_ExplicitBounded_Length[row], + q10 - 1 <= horizontalLocs_ExplicitBounded_Length[row], + q10 - 1 <= horizontalClues_ExplicitBounded_Length[row]; + int(1..4)]) + | q10 : int(1..fin1), q10 <= horizontalClues_ExplicitBounded_Length[row], q10 > 1]) + | row : int(1..n)]), + and([verticalLocs_ExplicitBounded_Length[col] = verticalClues_ExplicitBounded_Length[col] | col : int(1..n)]), + and([and([and([verticalLocs_ExplicitBounded_Values[col, q12] > + verticalLocs_ExplicitBounded_Values[col, q12 - 1] + + verticalClues_ExplicitBounded_Values[col, q12 - 1], + q12 <= verticalLocs_ExplicitBounded_Length[col], q12 - 1 <= verticalLocs_ExplicitBounded_Length[col], + q12 - 1 <= verticalClues_ExplicitBounded_Length[col]; + int(1..4)]) + | q12 : int(1..fin2), q12 <= verticalClues_ExplicitBounded_Length[col], q12 > 1]) + | col : int(1..n)]), + and([bitmap[prefilled_Explicit_1[q14], prefilled_Explicit_2[q14]] | q14 : int(1..fin3)]), + and([and([i >= horizontalLocs_ExplicitBounded_Values[row, index] /\ + index <= horizontalLocs_ExplicitBounded_Length[row] + /\ + and([i <= + horizontalLocs_ExplicitBounded_Values[row, index] + + horizontalClues_ExplicitBounded_Values[row, index] + - 1, + index <= horizontalLocs_ExplicitBounded_Length[row], + index <= horizontalClues_ExplicitBounded_Length[row]; + int(1..3)]) + -> bitmap[row, i] + | i : int(1..n)]) + /\ + and([i < horizontalLocs_ExplicitBounded_Values[row, index] /\ + index <= horizontalLocs_ExplicitBounded_Length[row] + -> bitmap[row, i] = false + | i : int(1..n), index = 1]) + /\ + and([and([i > + horizontalLocs_ExplicitBounded_Values[row, index] + + horizontalClues_ExplicitBounded_Values[row, index] + - 1, + index <= horizontalLocs_ExplicitBounded_Length[row], + index <= horizontalClues_ExplicitBounded_Length[row]; + int(1..3)]) + -> bitmap[row, i] = false + | i : int(1..n), index = horizontalClues_ExplicitBounded_Length[row]]) + /\ + and([and([i > + horizontalLocs_ExplicitBounded_Values[row, index] + + horizontalClues_ExplicitBounded_Values[row, index] + - 1, + index <= horizontalLocs_ExplicitBounded_Length[row], + index <= horizontalClues_ExplicitBounded_Length[row]; + int(1..3)]) + /\ + (i < horizontalLocs_ExplicitBounded_Values[row, index + 1] /\ + index + 1 <= horizontalLocs_ExplicitBounded_Length[row]) + -> bitmap[row, i] = false + | i : int(1..n), index < horizontalClues_ExplicitBounded_Length[row]]) + | row : int(1..n), index : int(1..n), index <= horizontalClues_ExplicitBounded_Length[row]]), + and([and([i >= verticalLocs_ExplicitBounded_Values[col, index] /\ index <= verticalLocs_ExplicitBounded_Length[col] + /\ + and([i <= + verticalLocs_ExplicitBounded_Values[col, index] + verticalClues_ExplicitBounded_Values[col, index] - + 1, + index <= verticalLocs_ExplicitBounded_Length[col], + index <= verticalClues_ExplicitBounded_Length[col]; + int(1..3)]) + -> bitmap[i, col] + | i : int(1..n)]) + /\ + and([i < verticalLocs_ExplicitBounded_Values[col, index] /\ index <= verticalLocs_ExplicitBounded_Length[col] + -> bitmap[i, col] = false + | i : int(1..n), index = 1]) + /\ + and([and([i > + verticalLocs_ExplicitBounded_Values[col, index] + verticalClues_ExplicitBounded_Values[col, index] - + 1, + index <= verticalLocs_ExplicitBounded_Length[col], + index <= verticalClues_ExplicitBounded_Length[col]; + int(1..3)]) + -> bitmap[i, col] = false + | i : int(1..n), index = verticalClues_ExplicitBounded_Length[col]]) + /\ + and([and([i > + verticalLocs_ExplicitBounded_Values[col, index] + verticalClues_ExplicitBounded_Values[col, index] - + 1, + index <= verticalLocs_ExplicitBounded_Length[col], + index <= verticalClues_ExplicitBounded_Length[col]; + int(1..3)]) + /\ + (i < verticalLocs_ExplicitBounded_Values[col, index + 1] /\ + index + 1 <= verticalLocs_ExplicitBounded_Length[col]) + -> bitmap[i, col] = false + | i : int(1..n), index < verticalClues_ExplicitBounded_Length[col]]) + | col : int(1..n), index : int(1..n), index <= verticalClues_ExplicitBounded_Length[col]]), + and([and([q4 > horizontalLocs_ExplicitBounded_Length[q3] -> horizontalLocs_ExplicitBounded_Values[q3, q4] = 1 + | q4 : int(1..n)]) + | q3 : int(1..n)]), + and([horizontalLocs_ExplicitBounded_Length[q3] <= n | q3 : int(1..n)]), + and([and([q7 > verticalLocs_ExplicitBounded_Length[q6] -> verticalLocs_ExplicitBounded_Values[q6, q7] = 1 + | q7 : int(1..n)]) + | q6 : int(1..n)]), + and([verticalLocs_ExplicitBounded_Length[q6] <= n | q6 : int(1..n)]) + diff --git a/tests/exhaustive/mildly_interesting/subsetSum/expected/model_1_1_1-p1-solution000001.solution b/tests/exhaustive/mildly_interesting/subsetSum/expected/model_1_1_1-p1-solution000001.solution new file mode 100644 index 0000000000..273ab9e077 --- /dev/null +++ b/tests/exhaustive/mildly_interesting/subsetSum/expected/model_1_1_1-p1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {-3, -2, 5} diff --git a/tests/exhaustive/mildly_interesting/subsetSum/expected/model_1_1_1-p1.eprime-param b/tests/exhaustive/mildly_interesting/subsetSum/expected/model_1_1_1-p1.eprime-param new file mode 100644 index 0000000000..b1ce145328 --- /dev/null +++ b/tests/exhaustive/mildly_interesting/subsetSum/expected/model_1_1_1-p1.eprime-param @@ -0,0 +1,7 @@ +language ESSENCE' 1.0 + +letting nums_Explicit be [-7, -3, -2, 5, 8; int(1..5)] +letting s be 0 +letting fin1 be 5 +letting fin2 be -7 +letting fin3 be 8 diff --git a/tests/exhaustive/mildly_interesting/subsetSum/expected/model_1_1_1-p2-solution000001.solution b/tests/exhaustive/mildly_interesting/subsetSum/expected/model_1_1_1-p2-solution000001.solution new file mode 100644 index 0000000000..102034e8e6 --- /dev/null +++ b/tests/exhaustive/mildly_interesting/subsetSum/expected/model_1_1_1-p2-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {-5, 1, 4} diff --git a/tests/exhaustive/mildly_interesting/subsetSum/expected/model_1_1_1-p2-solution000002.solution b/tests/exhaustive/mildly_interesting/subsetSum/expected/model_1_1_1-p2-solution000002.solution new file mode 100644 index 0000000000..3192b721eb --- /dev/null +++ b/tests/exhaustive/mildly_interesting/subsetSum/expected/model_1_1_1-p2-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {-5, 2, 3} diff --git a/tests/exhaustive/mildly_interesting/subsetSum/expected/model_1_1_1-p2.eprime-param b/tests/exhaustive/mildly_interesting/subsetSum/expected/model_1_1_1-p2.eprime-param new file mode 100644 index 0000000000..2d232d7d8a --- /dev/null +++ b/tests/exhaustive/mildly_interesting/subsetSum/expected/model_1_1_1-p2.eprime-param @@ -0,0 +1,7 @@ +language ESSENCE' 1.0 + +letting nums_Explicit be [-5, 1, 2, 3, 4; int(1..5)] +letting s be 0 +letting fin1 be 5 +letting fin2 be -5 +letting fin3 be 4 diff --git a/tests/exhaustive/mildly_interesting/subsetSum/expected/model_1_1_1.eprime b/tests/exhaustive/mildly_interesting/subsetSum/expected/model_1_1_1.eprime new file mode 100644 index 0000000000..0193b6f90b --- /dev/null +++ b/tests/exhaustive/mildly_interesting/subsetSum/expected/model_1_1_1.eprime @@ -0,0 +1,27 @@ +language ESSENCE' 1.0 + +given s: int +given fin1: int +given fin2: int +given fin3: int +given nums_Explicit: matrix indexed by [int(1..fin1)] of int(fin2..fin3) +letting let1 be fin1 +letting let2 be [nums_Explicit[q5] | q5 : int(1..fin1)] +find x_ExplicitVarSizeWithMarker_Marker: int(0..let1) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..let1)] of int(let2) +branching on [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values] +such that + and([q8 <= x_ExplicitVarSizeWithMarker_Marker -> + or([nums_Explicit[q10] = x_ExplicitVarSizeWithMarker_Values[q8] | q10 : int(1..fin1)]) + | q8 : int(1..let1)]), + s = + sum([toInt(q6 <= x_ExplicitVarSizeWithMarker_Marker) * catchUndef(x_ExplicitVarSizeWithMarker_Values[q6], 0) + | q6 : int(1..let1)]), + and([q2 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q2] < x_ExplicitVarSizeWithMarker_Values[q2 + 1] + | q2 : int(1..let1 - 1)]), + and([q3 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q3] = min(let2) + | q3 : int(1..let1)]), + 1 <= x_ExplicitVarSizeWithMarker_Marker, + x_ExplicitVarSizeWithMarker_Marker <= let1 + diff --git a/tests/exhaustive/mildly_interesting/subsetSum/expected/model_1_1_2-p1-solution000001.solution b/tests/exhaustive/mildly_interesting/subsetSum/expected/model_1_1_2-p1-solution000001.solution new file mode 100644 index 0000000000..273ab9e077 --- /dev/null +++ b/tests/exhaustive/mildly_interesting/subsetSum/expected/model_1_1_2-p1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {-3, -2, 5} diff --git a/tests/exhaustive/mildly_interesting/subsetSum/expected/model_1_1_2-p1.eprime-param b/tests/exhaustive/mildly_interesting/subsetSum/expected/model_1_1_2-p1.eprime-param new file mode 100644 index 0000000000..b1ce145328 --- /dev/null +++ b/tests/exhaustive/mildly_interesting/subsetSum/expected/model_1_1_2-p1.eprime-param @@ -0,0 +1,7 @@ +language ESSENCE' 1.0 + +letting nums_Explicit be [-7, -3, -2, 5, 8; int(1..5)] +letting s be 0 +letting fin1 be 5 +letting fin2 be -7 +letting fin3 be 8 diff --git a/tests/exhaustive/mildly_interesting/subsetSum/expected/model_1_1_2-p2-solution000001.solution b/tests/exhaustive/mildly_interesting/subsetSum/expected/model_1_1_2-p2-solution000001.solution new file mode 100644 index 0000000000..102034e8e6 --- /dev/null +++ b/tests/exhaustive/mildly_interesting/subsetSum/expected/model_1_1_2-p2-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {-5, 1, 4} diff --git a/tests/exhaustive/mildly_interesting/subsetSum/expected/model_1_1_2-p2-solution000002.solution b/tests/exhaustive/mildly_interesting/subsetSum/expected/model_1_1_2-p2-solution000002.solution new file mode 100644 index 0000000000..3192b721eb --- /dev/null +++ b/tests/exhaustive/mildly_interesting/subsetSum/expected/model_1_1_2-p2-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {-5, 2, 3} diff --git a/tests/exhaustive/mildly_interesting/subsetSum/expected/model_1_1_2-p2.eprime-param b/tests/exhaustive/mildly_interesting/subsetSum/expected/model_1_1_2-p2.eprime-param new file mode 100644 index 0000000000..2d232d7d8a --- /dev/null +++ b/tests/exhaustive/mildly_interesting/subsetSum/expected/model_1_1_2-p2.eprime-param @@ -0,0 +1,7 @@ +language ESSENCE' 1.0 + +letting nums_Explicit be [-5, 1, 2, 3, 4; int(1..5)] +letting s be 0 +letting fin1 be 5 +letting fin2 be -5 +letting fin3 be 4 diff --git a/tests/exhaustive/mildly_interesting/subsetSum/expected/model_1_1_2.eprime b/tests/exhaustive/mildly_interesting/subsetSum/expected/model_1_1_2.eprime new file mode 100644 index 0000000000..f7a55a9331 --- /dev/null +++ b/tests/exhaustive/mildly_interesting/subsetSum/expected/model_1_1_2.eprime @@ -0,0 +1,49 @@ +language ESSENCE' 1.0 + +given s: int +given fin1: int +given fin2: int +given fin3: int +given nums_Explicit: matrix indexed by [int(1..fin1)] of int(fin2..fin3) +letting let1 be fin1 +letting let2 be [nums_Explicit[q18] | q18 : int(1..fin1)] +find x_ExplicitVarSizeWithMarker_Marker: int(0..let1) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..let1)] of int(let2) +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..let1)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..let1)] of int(let2) +branching on + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithMarker_Marker, + x_ExplicitVarSizeWithMarker_Values] +such that + and([q21 <= x_ExplicitVarSizeWithMarker_Marker -> + or([nums_Explicit[q23] = x_ExplicitVarSizeWithMarker_Values[q21] | q23 : int(1..fin1)]) + | q21 : int(1..let1)]), + s = + sum([toInt(q19 <= x_ExplicitVarSizeWithMarker_Marker) * catchUndef(x_ExplicitVarSizeWithMarker_Values[q19], 0) + | q19 : int(1..let1)]), + and([q2 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q2] < x_ExplicitVarSizeWithMarker_Values[q2 + 1] + | q2 : int(1..let1 - 1)]), + and([q3 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q3] = min(let2) + | q3 : int(1..let1)]), + 1 <= x_ExplicitVarSizeWithMarker_Marker, + x_ExplicitVarSizeWithMarker_Marker <= let1, + and([x_ExplicitVarSizeWithFlags_Flags[q5 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q5] < x_ExplicitVarSizeWithFlags_Values[q5 + 1] + | q5 : int(1..let1 - 1)]), + and([x_ExplicitVarSizeWithFlags_Flags[q6] = false -> x_ExplicitVarSizeWithFlags_Values[q6] = min(let2) + | q6 : int(1..let1)]), + and([x_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q7] | q7 : int(1..let1 - 1)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q8]) | q8 : int(1..let1)]), + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q8]) | q8 : int(1..let1)]) <= let1, + and([x_ExplicitVarSizeWithFlags_Flags[q11] -> + or([q13 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q13] = x_ExplicitVarSizeWithFlags_Values[q11] + | q13 : int(1..let1)]) + | q11 : int(1..let1)]), + and([q15 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithFlags_Flags[q17] /\ + x_ExplicitVarSizeWithFlags_Values[q17] = x_ExplicitVarSizeWithMarker_Values[q15] + | q17 : int(1..let1)]) + | q15 : int(1..let1)]) + diff --git a/tests/exhaustive/mildly_interesting/subsetSum/expected/model_1_2_1-p1-solution000001.solution b/tests/exhaustive/mildly_interesting/subsetSum/expected/model_1_2_1-p1-solution000001.solution new file mode 100644 index 0000000000..273ab9e077 --- /dev/null +++ b/tests/exhaustive/mildly_interesting/subsetSum/expected/model_1_2_1-p1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {-3, -2, 5} diff --git a/tests/exhaustive/mildly_interesting/subsetSum/expected/model_1_2_1-p1.eprime-param b/tests/exhaustive/mildly_interesting/subsetSum/expected/model_1_2_1-p1.eprime-param new file mode 100644 index 0000000000..b1ce145328 --- /dev/null +++ b/tests/exhaustive/mildly_interesting/subsetSum/expected/model_1_2_1-p1.eprime-param @@ -0,0 +1,7 @@ +language ESSENCE' 1.0 + +letting nums_Explicit be [-7, -3, -2, 5, 8; int(1..5)] +letting s be 0 +letting fin1 be 5 +letting fin2 be -7 +letting fin3 be 8 diff --git a/tests/exhaustive/mildly_interesting/subsetSum/expected/model_1_2_1-p2-solution000001.solution b/tests/exhaustive/mildly_interesting/subsetSum/expected/model_1_2_1-p2-solution000001.solution new file mode 100644 index 0000000000..102034e8e6 --- /dev/null +++ b/tests/exhaustive/mildly_interesting/subsetSum/expected/model_1_2_1-p2-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {-5, 1, 4} diff --git a/tests/exhaustive/mildly_interesting/subsetSum/expected/model_1_2_1-p2-solution000002.solution b/tests/exhaustive/mildly_interesting/subsetSum/expected/model_1_2_1-p2-solution000002.solution new file mode 100644 index 0000000000..3192b721eb --- /dev/null +++ b/tests/exhaustive/mildly_interesting/subsetSum/expected/model_1_2_1-p2-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {-5, 2, 3} diff --git a/tests/exhaustive/mildly_interesting/subsetSum/expected/model_1_2_1-p2.eprime-param b/tests/exhaustive/mildly_interesting/subsetSum/expected/model_1_2_1-p2.eprime-param new file mode 100644 index 0000000000..2d232d7d8a --- /dev/null +++ b/tests/exhaustive/mildly_interesting/subsetSum/expected/model_1_2_1-p2.eprime-param @@ -0,0 +1,7 @@ +language ESSENCE' 1.0 + +letting nums_Explicit be [-5, 1, 2, 3, 4; int(1..5)] +letting s be 0 +letting fin1 be 5 +letting fin2 be -5 +letting fin3 be 4 diff --git a/tests/exhaustive/mildly_interesting/subsetSum/expected/model_1_2_1.eprime b/tests/exhaustive/mildly_interesting/subsetSum/expected/model_1_2_1.eprime new file mode 100644 index 0000000000..55b8aa4153 --- /dev/null +++ b/tests/exhaustive/mildly_interesting/subsetSum/expected/model_1_2_1.eprime @@ -0,0 +1,49 @@ +language ESSENCE' 1.0 + +given s: int +given fin1: int +given fin2: int +given fin3: int +given nums_Explicit: matrix indexed by [int(1..fin1)] of int(fin2..fin3) +letting let1 be fin1 +letting let2 be [nums_Explicit[q18] | q18 : int(1..fin1)] +find x_ExplicitVarSizeWithMarker_Marker: int(0..let1) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..let1)] of int(let2) +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..let1)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..let1)] of int(let2) +branching on + [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values, x_ExplicitVarSizeWithMarker_Marker, + x_ExplicitVarSizeWithMarker_Values] +such that + and([q21 <= x_ExplicitVarSizeWithMarker_Marker -> + or([nums_Explicit[q23] = x_ExplicitVarSizeWithMarker_Values[q21] | q23 : int(1..fin1)]) + | q21 : int(1..let1)]), + s = + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q19]) * catchUndef(x_ExplicitVarSizeWithFlags_Values[q19], 0) + | q19 : int(1..let1)]), + and([q2 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q2] < x_ExplicitVarSizeWithMarker_Values[q2 + 1] + | q2 : int(1..let1 - 1)]), + and([q3 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q3] = min(let2) + | q3 : int(1..let1)]), + 1 <= x_ExplicitVarSizeWithMarker_Marker, + x_ExplicitVarSizeWithMarker_Marker <= let1, + and([x_ExplicitVarSizeWithFlags_Flags[q5 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q5] < x_ExplicitVarSizeWithFlags_Values[q5 + 1] + | q5 : int(1..let1 - 1)]), + and([x_ExplicitVarSizeWithFlags_Flags[q6] = false -> x_ExplicitVarSizeWithFlags_Values[q6] = min(let2) + | q6 : int(1..let1)]), + and([x_ExplicitVarSizeWithFlags_Flags[q7 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q7] | q7 : int(1..let1 - 1)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q8]) | q8 : int(1..let1)]), + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q8]) | q8 : int(1..let1)]) <= let1, + and([x_ExplicitVarSizeWithFlags_Flags[q11] -> + or([q13 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q13] = x_ExplicitVarSizeWithFlags_Values[q11] + | q13 : int(1..let1)]) + | q11 : int(1..let1)]), + and([q15 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithFlags_Flags[q17] /\ + x_ExplicitVarSizeWithFlags_Values[q17] = x_ExplicitVarSizeWithMarker_Values[q15] + | q17 : int(1..let1)]) + | q15 : int(1..let1)]) + diff --git a/tests/exhaustive/mildly_interesting/subsetSum/expected/model_2_1_1-p1-solution000001.solution b/tests/exhaustive/mildly_interesting/subsetSum/expected/model_2_1_1-p1-solution000001.solution new file mode 100644 index 0000000000..273ab9e077 --- /dev/null +++ b/tests/exhaustive/mildly_interesting/subsetSum/expected/model_2_1_1-p1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {-3, -2, 5} diff --git a/tests/exhaustive/mildly_interesting/subsetSum/expected/model_2_1_1-p1.eprime-param b/tests/exhaustive/mildly_interesting/subsetSum/expected/model_2_1_1-p1.eprime-param new file mode 100644 index 0000000000..b1ce145328 --- /dev/null +++ b/tests/exhaustive/mildly_interesting/subsetSum/expected/model_2_1_1-p1.eprime-param @@ -0,0 +1,7 @@ +language ESSENCE' 1.0 + +letting nums_Explicit be [-7, -3, -2, 5, 8; int(1..5)] +letting s be 0 +letting fin1 be 5 +letting fin2 be -7 +letting fin3 be 8 diff --git a/tests/exhaustive/mildly_interesting/subsetSum/expected/model_2_1_1-p2-solution000001.solution b/tests/exhaustive/mildly_interesting/subsetSum/expected/model_2_1_1-p2-solution000001.solution new file mode 100644 index 0000000000..102034e8e6 --- /dev/null +++ b/tests/exhaustive/mildly_interesting/subsetSum/expected/model_2_1_1-p2-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {-5, 1, 4} diff --git a/tests/exhaustive/mildly_interesting/subsetSum/expected/model_2_1_1-p2-solution000002.solution b/tests/exhaustive/mildly_interesting/subsetSum/expected/model_2_1_1-p2-solution000002.solution new file mode 100644 index 0000000000..3192b721eb --- /dev/null +++ b/tests/exhaustive/mildly_interesting/subsetSum/expected/model_2_1_1-p2-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {-5, 2, 3} diff --git a/tests/exhaustive/mildly_interesting/subsetSum/expected/model_2_1_1-p2.eprime-param b/tests/exhaustive/mildly_interesting/subsetSum/expected/model_2_1_1-p2.eprime-param new file mode 100644 index 0000000000..2d232d7d8a --- /dev/null +++ b/tests/exhaustive/mildly_interesting/subsetSum/expected/model_2_1_1-p2.eprime-param @@ -0,0 +1,7 @@ +language ESSENCE' 1.0 + +letting nums_Explicit be [-5, 1, 2, 3, 4; int(1..5)] +letting s be 0 +letting fin1 be 5 +letting fin2 be -5 +letting fin3 be 4 diff --git a/tests/exhaustive/mildly_interesting/subsetSum/expected/model_2_1_1.eprime b/tests/exhaustive/mildly_interesting/subsetSum/expected/model_2_1_1.eprime new file mode 100644 index 0000000000..b7ee7c510e --- /dev/null +++ b/tests/exhaustive/mildly_interesting/subsetSum/expected/model_2_1_1.eprime @@ -0,0 +1,49 @@ +language ESSENCE' 1.0 + +given s: int +given fin1: int +given fin2: int +given fin3: int +given nums_Explicit: matrix indexed by [int(1..fin1)] of int(fin2..fin3) +letting let1 be fin1 +letting let2 be [nums_Explicit[q18] | q18 : int(1..fin1)] +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..let1)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..let1)] of int(let2) +find x_ExplicitVarSizeWithMarker_Marker: int(0..let1) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..let1)] of int(let2) +branching on + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithFlags_Flags, + x_ExplicitVarSizeWithFlags_Values] +such that + and([x_ExplicitVarSizeWithFlags_Flags[q21] -> + or([nums_Explicit[q23] = x_ExplicitVarSizeWithFlags_Values[q21] | q23 : int(1..fin1)]) + | q21 : int(1..let1)]), + s = + sum([toInt(q19 <= x_ExplicitVarSizeWithMarker_Marker) * catchUndef(x_ExplicitVarSizeWithMarker_Values[q19], 0) + | q19 : int(1..let1)]), + and([x_ExplicitVarSizeWithFlags_Flags[q2 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q2] < x_ExplicitVarSizeWithFlags_Values[q2 + 1] + | q2 : int(1..let1 - 1)]), + and([x_ExplicitVarSizeWithFlags_Flags[q3] = false -> x_ExplicitVarSizeWithFlags_Values[q3] = min(let2) + | q3 : int(1..let1)]), + and([x_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q4] | q4 : int(1..let1 - 1)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q5]) | q5 : int(1..let1)]), + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q5]) | q5 : int(1..let1)]) <= let1, + and([q7 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q7] < x_ExplicitVarSizeWithMarker_Values[q7 + 1] + | q7 : int(1..let1 - 1)]), + and([q8 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q8] = min(let2) + | q8 : int(1..let1)]), + 1 <= x_ExplicitVarSizeWithMarker_Marker, + x_ExplicitVarSizeWithMarker_Marker <= let1, + and([q11 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithFlags_Flags[q13] /\ + x_ExplicitVarSizeWithFlags_Values[q13] = x_ExplicitVarSizeWithMarker_Values[q11] + | q13 : int(1..let1)]) + | q11 : int(1..let1)]), + and([x_ExplicitVarSizeWithFlags_Flags[q15] -> + or([q17 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q17] = x_ExplicitVarSizeWithFlags_Values[q15] + | q17 : int(1..let1)]) + | q15 : int(1..let1)]) + diff --git a/tests/exhaustive/mildly_interesting/subsetSum/expected/model_2_2_1-p1-solution000001.solution b/tests/exhaustive/mildly_interesting/subsetSum/expected/model_2_2_1-p1-solution000001.solution new file mode 100644 index 0000000000..273ab9e077 --- /dev/null +++ b/tests/exhaustive/mildly_interesting/subsetSum/expected/model_2_2_1-p1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {-3, -2, 5} diff --git a/tests/exhaustive/mildly_interesting/subsetSum/expected/model_2_2_1-p1.eprime-param b/tests/exhaustive/mildly_interesting/subsetSum/expected/model_2_2_1-p1.eprime-param new file mode 100644 index 0000000000..b1ce145328 --- /dev/null +++ b/tests/exhaustive/mildly_interesting/subsetSum/expected/model_2_2_1-p1.eprime-param @@ -0,0 +1,7 @@ +language ESSENCE' 1.0 + +letting nums_Explicit be [-7, -3, -2, 5, 8; int(1..5)] +letting s be 0 +letting fin1 be 5 +letting fin2 be -7 +letting fin3 be 8 diff --git a/tests/exhaustive/mildly_interesting/subsetSum/expected/model_2_2_1-p2-solution000001.solution b/tests/exhaustive/mildly_interesting/subsetSum/expected/model_2_2_1-p2-solution000001.solution new file mode 100644 index 0000000000..102034e8e6 --- /dev/null +++ b/tests/exhaustive/mildly_interesting/subsetSum/expected/model_2_2_1-p2-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {-5, 1, 4} diff --git a/tests/exhaustive/mildly_interesting/subsetSum/expected/model_2_2_1-p2-solution000002.solution b/tests/exhaustive/mildly_interesting/subsetSum/expected/model_2_2_1-p2-solution000002.solution new file mode 100644 index 0000000000..3192b721eb --- /dev/null +++ b/tests/exhaustive/mildly_interesting/subsetSum/expected/model_2_2_1-p2-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {-5, 2, 3} diff --git a/tests/exhaustive/mildly_interesting/subsetSum/expected/model_2_2_1-p2.eprime-param b/tests/exhaustive/mildly_interesting/subsetSum/expected/model_2_2_1-p2.eprime-param new file mode 100644 index 0000000000..2d232d7d8a --- /dev/null +++ b/tests/exhaustive/mildly_interesting/subsetSum/expected/model_2_2_1-p2.eprime-param @@ -0,0 +1,7 @@ +language ESSENCE' 1.0 + +letting nums_Explicit be [-5, 1, 2, 3, 4; int(1..5)] +letting s be 0 +letting fin1 be 5 +letting fin2 be -5 +letting fin3 be 4 diff --git a/tests/exhaustive/mildly_interesting/subsetSum/expected/model_2_2_1.eprime b/tests/exhaustive/mildly_interesting/subsetSum/expected/model_2_2_1.eprime new file mode 100644 index 0000000000..36c7029a44 --- /dev/null +++ b/tests/exhaustive/mildly_interesting/subsetSum/expected/model_2_2_1.eprime @@ -0,0 +1,49 @@ +language ESSENCE' 1.0 + +given s: int +given fin1: int +given fin2: int +given fin3: int +given nums_Explicit: matrix indexed by [int(1..fin1)] of int(fin2..fin3) +letting let1 be fin1 +letting let2 be [nums_Explicit[q18] | q18 : int(1..fin1)] +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..let1)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..let1)] of int(let2) +find x_ExplicitVarSizeWithMarker_Marker: int(0..let1) +find x_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..let1)] of int(let2) +branching on + [x_ExplicitVarSizeWithMarker_Marker, x_ExplicitVarSizeWithMarker_Values, x_ExplicitVarSizeWithFlags_Flags, + x_ExplicitVarSizeWithFlags_Values] +such that + and([x_ExplicitVarSizeWithFlags_Flags[q21] -> + or([nums_Explicit[q23] = x_ExplicitVarSizeWithFlags_Values[q21] | q23 : int(1..fin1)]) + | q21 : int(1..let1)]), + s = + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q19]) * catchUndef(x_ExplicitVarSizeWithFlags_Values[q19], 0) + | q19 : int(1..let1)]), + and([x_ExplicitVarSizeWithFlags_Flags[q2 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q2] < x_ExplicitVarSizeWithFlags_Values[q2 + 1] + | q2 : int(1..let1 - 1)]), + and([x_ExplicitVarSizeWithFlags_Flags[q3] = false -> x_ExplicitVarSizeWithFlags_Values[q3] = min(let2) + | q3 : int(1..let1)]), + and([x_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q4] | q4 : int(1..let1 - 1)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q5]) | q5 : int(1..let1)]), + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q5]) | q5 : int(1..let1)]) <= let1, + and([q7 + 1 <= x_ExplicitVarSizeWithMarker_Marker -> + x_ExplicitVarSizeWithMarker_Values[q7] < x_ExplicitVarSizeWithMarker_Values[q7 + 1] + | q7 : int(1..let1 - 1)]), + and([q8 > x_ExplicitVarSizeWithMarker_Marker -> x_ExplicitVarSizeWithMarker_Values[q8] = min(let2) + | q8 : int(1..let1)]), + 1 <= x_ExplicitVarSizeWithMarker_Marker, + x_ExplicitVarSizeWithMarker_Marker <= let1, + and([q11 <= x_ExplicitVarSizeWithMarker_Marker -> + or([x_ExplicitVarSizeWithFlags_Flags[q13] /\ + x_ExplicitVarSizeWithFlags_Values[q13] = x_ExplicitVarSizeWithMarker_Values[q11] + | q13 : int(1..let1)]) + | q11 : int(1..let1)]), + and([x_ExplicitVarSizeWithFlags_Flags[q15] -> + or([q17 <= x_ExplicitVarSizeWithMarker_Marker /\ + x_ExplicitVarSizeWithMarker_Values[q17] = x_ExplicitVarSizeWithFlags_Values[q15] + | q17 : int(1..let1)]) + | q15 : int(1..let1)]) + diff --git a/tests/exhaustive/mildly_interesting/subsetSum/expected/model_2_2_2-p1-solution000001.solution b/tests/exhaustive/mildly_interesting/subsetSum/expected/model_2_2_2-p1-solution000001.solution new file mode 100644 index 0000000000..273ab9e077 --- /dev/null +++ b/tests/exhaustive/mildly_interesting/subsetSum/expected/model_2_2_2-p1-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {-3, -2, 5} diff --git a/tests/exhaustive/mildly_interesting/subsetSum/expected/model_2_2_2-p1.eprime-param b/tests/exhaustive/mildly_interesting/subsetSum/expected/model_2_2_2-p1.eprime-param new file mode 100644 index 0000000000..b1ce145328 --- /dev/null +++ b/tests/exhaustive/mildly_interesting/subsetSum/expected/model_2_2_2-p1.eprime-param @@ -0,0 +1,7 @@ +language ESSENCE' 1.0 + +letting nums_Explicit be [-7, -3, -2, 5, 8; int(1..5)] +letting s be 0 +letting fin1 be 5 +letting fin2 be -7 +letting fin3 be 8 diff --git a/tests/exhaustive/mildly_interesting/subsetSum/expected/model_2_2_2-p2-solution000001.solution b/tests/exhaustive/mildly_interesting/subsetSum/expected/model_2_2_2-p2-solution000001.solution new file mode 100644 index 0000000000..102034e8e6 --- /dev/null +++ b/tests/exhaustive/mildly_interesting/subsetSum/expected/model_2_2_2-p2-solution000001.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {-5, 1, 4} diff --git a/tests/exhaustive/mildly_interesting/subsetSum/expected/model_2_2_2-p2-solution000002.solution b/tests/exhaustive/mildly_interesting/subsetSum/expected/model_2_2_2-p2-solution000002.solution new file mode 100644 index 0000000000..3192b721eb --- /dev/null +++ b/tests/exhaustive/mildly_interesting/subsetSum/expected/model_2_2_2-p2-solution000002.solution @@ -0,0 +1,3 @@ +language Essence 1.3 + +letting x be {-5, 2, 3} diff --git a/tests/exhaustive/mildly_interesting/subsetSum/expected/model_2_2_2-p2.eprime-param b/tests/exhaustive/mildly_interesting/subsetSum/expected/model_2_2_2-p2.eprime-param new file mode 100644 index 0000000000..2d232d7d8a --- /dev/null +++ b/tests/exhaustive/mildly_interesting/subsetSum/expected/model_2_2_2-p2.eprime-param @@ -0,0 +1,7 @@ +language ESSENCE' 1.0 + +letting nums_Explicit be [-5, 1, 2, 3, 4; int(1..5)] +letting s be 0 +letting fin1 be 5 +letting fin2 be -5 +letting fin3 be 4 diff --git a/tests/exhaustive/mildly_interesting/subsetSum/expected/model_2_2_2.eprime b/tests/exhaustive/mildly_interesting/subsetSum/expected/model_2_2_2.eprime new file mode 100644 index 0000000000..e242a71db7 --- /dev/null +++ b/tests/exhaustive/mildly_interesting/subsetSum/expected/model_2_2_2.eprime @@ -0,0 +1,28 @@ +language ESSENCE' 1.0 + +given s: int +given fin1: int +given fin2: int +given fin3: int +given nums_Explicit: matrix indexed by [int(1..fin1)] of int(fin2..fin3) +letting let1 be fin1 +letting let2 be [nums_Explicit[q7] | q7 : int(1..fin1)] +find x_ExplicitVarSizeWithFlags_Flags: matrix indexed by [int(1..let1)] of bool +find x_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..let1)] of int(let2) +branching on [x_ExplicitVarSizeWithFlags_Flags, x_ExplicitVarSizeWithFlags_Values] +such that + and([x_ExplicitVarSizeWithFlags_Flags[q10] -> + or([nums_Explicit[q12] = x_ExplicitVarSizeWithFlags_Values[q10] | q12 : int(1..fin1)]) + | q10 : int(1..let1)]), + s = + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q8]) * catchUndef(x_ExplicitVarSizeWithFlags_Values[q8], 0) + | q8 : int(1..let1)]), + and([x_ExplicitVarSizeWithFlags_Flags[q2 + 1] -> + x_ExplicitVarSizeWithFlags_Values[q2] < x_ExplicitVarSizeWithFlags_Values[q2 + 1] + | q2 : int(1..let1 - 1)]), + and([x_ExplicitVarSizeWithFlags_Flags[q3] = false -> x_ExplicitVarSizeWithFlags_Values[q3] = min(let2) + | q3 : int(1..let1)]), + and([x_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q4] | q4 : int(1..let1 - 1)]), + 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q5]) | q5 : int(1..let1)]), + sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q5]) | q5 : int(1..let1)]) <= let1 + diff --git a/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000001.solution new file mode 100644 index 0000000000..534774871a --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be function() +letting b be function(2 --> false) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000002.solution b/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000002.solution new file mode 100644 index 0000000000..9346e1754b --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be function() +letting b be function(2 --> true) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000003.solution b/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000003.solution new file mode 100644 index 0000000000..74b1a6d481 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be function() +letting b be function(1 --> false) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000004.solution b/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000004.solution new file mode 100644 index 0000000000..4a96af448e --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000004.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be function() +letting b be function(1 --> true) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000005.solution b/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000005.solution new file mode 100644 index 0000000000..0e18364d45 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000005.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be function() +letting b be function(1 --> false, 2 --> false) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000006.solution b/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000006.solution new file mode 100644 index 0000000000..a342f9b86e --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000006.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be function() +letting b be function(1 --> false, 2 --> true) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000007.solution b/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000007.solution new file mode 100644 index 0000000000..5677d2b395 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000007.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be function() +letting b be function(1 --> true, 2 --> false) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000008.solution b/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000008.solution new file mode 100644 index 0000000000..2df313a9bf --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000008.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be function() +letting b be function(1 --> true, 2 --> true) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000009.solution b/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000009.solution new file mode 100644 index 0000000000..58fbafa57e --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000009.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be function(2 --> false) +letting b be function(1 --> false) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000010.solution b/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000010.solution new file mode 100644 index 0000000000..789b9c90d3 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000010.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be function(2 --> false) +letting b be function(1 --> true) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000011.solution b/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000011.solution new file mode 100644 index 0000000000..2edff105b5 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000011.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be function(2 --> false) +letting b be function(1 --> false, 2 --> false) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000012.solution b/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000012.solution new file mode 100644 index 0000000000..74e94168a0 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000012.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be function(2 --> false) +letting b be function(1 --> false, 2 --> true) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000013.solution b/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000013.solution new file mode 100644 index 0000000000..093bdec177 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000013.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be function(2 --> false) +letting b be function(1 --> true, 2 --> false) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000014.solution b/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000014.solution new file mode 100644 index 0000000000..7f91bef76e --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000014.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be function(2 --> false) +letting b be function(1 --> true, 2 --> true) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000015.solution b/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000015.solution new file mode 100644 index 0000000000..2d31ea87c0 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000015.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be function(2 --> true) +letting b be function(2 --> false) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000016.solution b/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000016.solution new file mode 100644 index 0000000000..39c8593d69 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000016.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be function(2 --> true) +letting b be function(1 --> false) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000017.solution b/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000017.solution new file mode 100644 index 0000000000..a0d0c36916 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000017.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be function(2 --> true) +letting b be function(1 --> true) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000018.solution b/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000018.solution new file mode 100644 index 0000000000..f9ea159aa2 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000018.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be function(2 --> true) +letting b be function(1 --> false, 2 --> false) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000019.solution b/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000019.solution new file mode 100644 index 0000000000..957cf9fb82 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000019.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be function(2 --> true) +letting b be function(1 --> false, 2 --> true) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000020.solution b/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000020.solution new file mode 100644 index 0000000000..3f9decd735 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000020.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be function(2 --> true) +letting b be function(1 --> true, 2 --> false) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000021.solution b/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000021.solution new file mode 100644 index 0000000000..46ef148b20 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000021.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be function(2 --> true) +letting b be function(1 --> true, 2 --> true) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000022.solution b/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000022.solution new file mode 100644 index 0000000000..2452e99fe4 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000022.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be function(1 --> false) +letting b be function(1 --> false, 2 --> false) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000023.solution b/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000023.solution new file mode 100644 index 0000000000..d7ded0c4b6 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000023.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be function(1 --> false) +letting b be function(1 --> false, 2 --> true) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000024.solution b/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000024.solution new file mode 100644 index 0000000000..dd8080c849 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000024.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be function(1 --> true) +letting b be function(1 --> false) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000025.solution b/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000025.solution new file mode 100644 index 0000000000..270ba7d5b7 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000025.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be function(1 --> true) +letting b be function(1 --> false, 2 --> false) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000026.solution b/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000026.solution new file mode 100644 index 0000000000..9081271d97 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000026.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be function(1 --> true) +letting b be function(1 --> false, 2 --> true) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000027.solution b/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000027.solution new file mode 100644 index 0000000000..75603c59ea --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000027.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be function(1 --> true) +letting b be function(1 --> true, 2 --> false) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000028.solution b/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000028.solution new file mode 100644 index 0000000000..3784cc005f --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000028.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be function(1 --> true) +letting b be function(1 --> true, 2 --> true) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000029.solution b/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000029.solution new file mode 100644 index 0000000000..3e724ff0d1 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000029.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be function(1 --> false, 2 --> true) +letting b be function(1 --> false, 2 --> false) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000030.solution b/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000030.solution new file mode 100644 index 0000000000..e63fb8f776 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000030.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be function(1 --> true, 2 --> false) +letting b be function(1 --> false) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000031.solution b/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000031.solution new file mode 100644 index 0000000000..80da5627ce --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000031.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be function(1 --> true, 2 --> false) +letting b be function(1 --> false, 2 --> false) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000032.solution b/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000032.solution new file mode 100644 index 0000000000..6944fdbfc9 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000032.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be function(1 --> true, 2 --> false) +letting b be function(1 --> false, 2 --> true) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000033.solution b/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000033.solution new file mode 100644 index 0000000000..2143a4e6fe --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000033.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be function(1 --> true, 2 --> true) +letting b be function(1 --> false) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000034.solution b/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000034.solution new file mode 100644 index 0000000000..e9eb65412b --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000034.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be function(1 --> true, 2 --> true) +letting b be function(1 --> false, 2 --> false) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000035.solution b/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000035.solution new file mode 100644 index 0000000000..0e6e174af5 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000035.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be function(1 --> true, 2 --> true) +letting b be function(1 --> false, 2 --> true) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000036.solution b/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000036.solution new file mode 100644 index 0000000000..cd636fd528 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model-solution000036.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be function(1 --> true, 2 --> true) +letting b be function(1 --> true, 2 --> false) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model.eprime b/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model.eprime new file mode 100644 index 0000000000..18f14caf88 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_function_01/expected/model.eprime @@ -0,0 +1,91 @@ +language ESSENCE' 1.0 + +find a_Function1DPartial_Flags: matrix indexed by [int(1..2)] of bool +find a_Function1DPartial_Values: matrix indexed by [int(1..2)] of bool +find b_Function1DPartial_Flags: matrix indexed by [int(1..2)] of bool +find b_Function1DPartial_Values: matrix indexed by [int(1..2)] of bool +branching on + [a_Function1DPartial_Flags, a_Function1DPartial_Values, b_Function1DPartial_Flags, b_Function1DPartial_Values] +such that + or([a_Function1DPartial_Flags[q9] /\ + (sum([toInt(a_Function1DPartial_Flags[q30]) * + catchUndef(toInt(q30 = q9 /\ a_Function1DPartial_Values[q30] = a_Function1DPartial_Values[q9]), 0) + | q30 : int(1..2)]) + < + sum([toInt(b_Function1DPartial_Flags[q32]) * + catchUndef(toInt(q32 = q9 /\ b_Function1DPartial_Values[q32] = a_Function1DPartial_Values[q9]), 0) + | q32 : int(1..2)]) + /\ + (and([a_Function1DPartial_Flags[q33] /\ + (q33 < q9 \/ q33 = q9 /\ a_Function1DPartial_Values[q33] < a_Function1DPartial_Values[q9]) + -> + sum([toInt(a_Function1DPartial_Flags[q42]) * + catchUndef(toInt(q42 = q33 /\ a_Function1DPartial_Values[q42] = a_Function1DPartial_Values[q33]), 0) + | q42 : int(1..2)]) + = + sum([toInt(b_Function1DPartial_Flags[q44]) * + catchUndef(toInt(q44 = q33 /\ b_Function1DPartial_Values[q44] = a_Function1DPartial_Values[q33]), 0) + | q44 : int(1..2)]) + | q33 : int(1..2)]) + /\ + and([and([b_Function1DPartial_Flags[q34], + !or([a_Function1DPartial_Flags[q40] /\ + (q40 = q34 /\ a_Function1DPartial_Values[q40] = b_Function1DPartial_Values[q34]) + | q40 : int(1..2)]), + q34 < q9 \/ q34 = q9 /\ b_Function1DPartial_Values[q34] < a_Function1DPartial_Values[q9]; + int(1..3)]) + -> + sum([toInt(a_Function1DPartial_Flags[q36]) * + catchUndef(toInt(q36 = q34 /\ a_Function1DPartial_Values[q36] = b_Function1DPartial_Values[q34]), 0) + | q36 : int(1..2)]) + = + sum([toInt(b_Function1DPartial_Flags[q38]) * + catchUndef(toInt(q38 = q34 /\ b_Function1DPartial_Values[q38] = b_Function1DPartial_Values[q34]), 0) + | q38 : int(1..2)]) + | q34 : int(1..2)]))) + | q9 : int(1..2)]) + \/ + or([b_Function1DPartial_Flags[q10] /\ + !or([a_Function1DPartial_Flags[q28] /\ + (q28 = q10 /\ a_Function1DPartial_Values[q28] = b_Function1DPartial_Values[q10]) + | q28 : int(1..2)]) + /\ + (sum([toInt(a_Function1DPartial_Flags[q12]) * + catchUndef(toInt(q12 = q10 /\ a_Function1DPartial_Values[q12] = b_Function1DPartial_Values[q10]), 0) + | q12 : int(1..2)]) + < + sum([toInt(b_Function1DPartial_Flags[q14]) * + catchUndef(toInt(q14 = q10 /\ b_Function1DPartial_Values[q14] = b_Function1DPartial_Values[q10]), 0) + | q14 : int(1..2)]) + /\ + (and([a_Function1DPartial_Flags[q15] /\ + (q15 < q10 \/ q15 = q10 /\ a_Function1DPartial_Values[q15] < b_Function1DPartial_Values[q10]) + -> + sum([toInt(a_Function1DPartial_Flags[q24]) * + catchUndef(toInt(q24 = q15 /\ a_Function1DPartial_Values[q24] = a_Function1DPartial_Values[q15]), 0) + | q24 : int(1..2)]) + = + sum([toInt(b_Function1DPartial_Flags[q26]) * + catchUndef(toInt(q26 = q15 /\ b_Function1DPartial_Values[q26] = a_Function1DPartial_Values[q15]), 0) + | q26 : int(1..2)]) + | q15 : int(1..2)]) + /\ + and([and([b_Function1DPartial_Flags[q16], + !or([a_Function1DPartial_Flags[q22] /\ + (q22 = q16 /\ a_Function1DPartial_Values[q22] = b_Function1DPartial_Values[q16]) + | q22 : int(1..2)]), + q16 < q10 \/ q16 = q10 /\ b_Function1DPartial_Values[q16] < b_Function1DPartial_Values[q10]; + int(1..3)]) + -> + sum([toInt(a_Function1DPartial_Flags[q18]) * + catchUndef(toInt(q18 = q16 /\ a_Function1DPartial_Values[q18] = b_Function1DPartial_Values[q16]), 0) + | q18 : int(1..2)]) + = + sum([toInt(b_Function1DPartial_Flags[q20]) * + catchUndef(toInt(q20 = q16 /\ b_Function1DPartial_Values[q20] = b_Function1DPartial_Values[q16]), 0) + | q20 : int(1..2)]) + | q16 : int(1..2)]))) + | q10 : int(1..2)]), + and([a_Function1DPartial_Flags[q1] = false -> a_Function1DPartial_Values[q1] = false | q1 : int(1..2)]), + and([b_Function1DPartial_Flags[q4] = false -> b_Function1DPartial_Values[q4] = false | q4 : int(1..2)]) + diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_1_1-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_1_1-solution000001.solution new file mode 100644 index 0000000000..5e2caa751c --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_1_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 2, 2) +letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_1_1-solution000002.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_1_1-solution000002.solution new file mode 100644 index 0000000000..1b4b5b08a6 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_1_1-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 2, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_1_1-solution000003.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_1_1-solution000003.solution new file mode 100644 index 0000000000..621d5f6edc --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_1_1-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 1, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_1_1-solution000004.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_1_1-solution000004.solution new file mode 100644 index 0000000000..15472caf03 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_1_1-solution000004.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 2, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_1_1-solution000005.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_1_1-solution000005.solution new file mode 100644 index 0000000000..ff56905e23 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_1_1-solution000005.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_1_1-solution000006.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_1_1-solution000006.solution new file mode 100644 index 0000000000..d56a0bbcdc --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_1_1-solution000006.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_1_2-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_1_2-solution000001.solution new file mode 100644 index 0000000000..1b4b5b08a6 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_1_2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 2, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_1_2-solution000002.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_1_2-solution000002.solution new file mode 100644 index 0000000000..5e2caa751c --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_1_2-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 2, 2) +letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_1_2-solution000003.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_1_2-solution000003.solution new file mode 100644 index 0000000000..621d5f6edc --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_1_2-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 1, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_1_2-solution000004.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_1_2-solution000004.solution new file mode 100644 index 0000000000..d56a0bbcdc --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_1_2-solution000004.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_1_2-solution000005.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_1_2-solution000005.solution new file mode 100644 index 0000000000..ff56905e23 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_1_2-solution000005.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_1_2-solution000006.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_1_2-solution000006.solution new file mode 100644 index 0000000000..15472caf03 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_1_2-solution000006.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 2, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_1_3-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_1_3-solution000001.solution new file mode 100644 index 0000000000..5e2caa751c --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_1_3-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 2, 2) +letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_1_3-solution000002.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_1_3-solution000002.solution new file mode 100644 index 0000000000..1b4b5b08a6 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_1_3-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 2, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_1_3-solution000003.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_1_3-solution000003.solution new file mode 100644 index 0000000000..621d5f6edc --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_1_3-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 1, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_1_3-solution000004.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_1_3-solution000004.solution new file mode 100644 index 0000000000..15472caf03 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_1_3-solution000004.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 2, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_1_3-solution000005.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_1_3-solution000005.solution new file mode 100644 index 0000000000..ff56905e23 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_1_3-solution000005.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_1_3-solution000006.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_1_3-solution000006.solution new file mode 100644 index 0000000000..d56a0bbcdc --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_1_3-solution000006.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_2_1-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_2_1-solution000001.solution new file mode 100644 index 0000000000..621d5f6edc --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_2_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 1, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_2_1-solution000002.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_2_1-solution000002.solution new file mode 100644 index 0000000000..5e2caa751c --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_2_1-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 2, 2) +letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_2_1-solution000003.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_2_1-solution000003.solution new file mode 100644 index 0000000000..1b4b5b08a6 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_2_1-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 2, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_2_1-solution000004.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_2_1-solution000004.solution new file mode 100644 index 0000000000..15472caf03 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_2_1-solution000004.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 2, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_2_1-solution000005.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_2_1-solution000005.solution new file mode 100644 index 0000000000..ff56905e23 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_2_1-solution000005.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_2_1-solution000006.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_2_1-solution000006.solution new file mode 100644 index 0000000000..d56a0bbcdc --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_2_1-solution000006.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_2_2-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_2_2-solution000001.solution new file mode 100644 index 0000000000..621d5f6edc --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_2_2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 1, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_2_2-solution000002.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_2_2-solution000002.solution new file mode 100644 index 0000000000..1b4b5b08a6 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_2_2-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 2, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_2_2-solution000003.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_2_2-solution000003.solution new file mode 100644 index 0000000000..5e2caa751c --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_2_2-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 2, 2) +letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_2_2-solution000004.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_2_2-solution000004.solution new file mode 100644 index 0000000000..d56a0bbcdc --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_2_2-solution000004.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_2_2-solution000005.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_2_2-solution000005.solution new file mode 100644 index 0000000000..ff56905e23 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_2_2-solution000005.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_2_2-solution000006.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_2_2-solution000006.solution new file mode 100644 index 0000000000..15472caf03 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_2_2-solution000006.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 2, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_2_3-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_2_3-solution000001.solution new file mode 100644 index 0000000000..621d5f6edc --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_2_3-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 1, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_2_3-solution000002.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_2_3-solution000002.solution new file mode 100644 index 0000000000..5e2caa751c --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_2_3-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 2, 2) +letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_2_3-solution000003.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_2_3-solution000003.solution new file mode 100644 index 0000000000..1b4b5b08a6 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_2_3-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 2, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_2_3-solution000004.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_2_3-solution000004.solution new file mode 100644 index 0000000000..15472caf03 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_2_3-solution000004.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 2, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_2_3-solution000005.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_2_3-solution000005.solution new file mode 100644 index 0000000000..ff56905e23 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_2_3-solution000005.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_2_3-solution000006.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_2_3-solution000006.solution new file mode 100644 index 0000000000..d56a0bbcdc --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_2_3-solution000006.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_3_1-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_3_1-solution000001.solution new file mode 100644 index 0000000000..15472caf03 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_3_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 2, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_3_1-solution000002.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_3_1-solution000002.solution new file mode 100644 index 0000000000..ff56905e23 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_3_1-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_3_1-solution000003.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_3_1-solution000003.solution new file mode 100644 index 0000000000..d56a0bbcdc --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_3_1-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_3_1-solution000004.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_3_1-solution000004.solution new file mode 100644 index 0000000000..5e2caa751c --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_3_1-solution000004.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 2, 2) +letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_3_1-solution000005.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_3_1-solution000005.solution new file mode 100644 index 0000000000..1b4b5b08a6 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_3_1-solution000005.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 2, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_3_1-solution000006.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_3_1-solution000006.solution new file mode 100644 index 0000000000..621d5f6edc --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_3_1-solution000006.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 1, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_3_2-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_3_2-solution000001.solution new file mode 100644 index 0000000000..d56a0bbcdc --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_3_2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_3_2-solution000002.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_3_2-solution000002.solution new file mode 100644 index 0000000000..ff56905e23 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_3_2-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_3_2-solution000003.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_3_2-solution000003.solution new file mode 100644 index 0000000000..15472caf03 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_3_2-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 2, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_3_2-solution000004.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_3_2-solution000004.solution new file mode 100644 index 0000000000..1b4b5b08a6 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_3_2-solution000004.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 2, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_3_2-solution000005.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_3_2-solution000005.solution new file mode 100644 index 0000000000..5e2caa751c --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_3_2-solution000005.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 2, 2) +letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_3_2-solution000006.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_3_2-solution000006.solution new file mode 100644 index 0000000000..621d5f6edc --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_3_2-solution000006.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 1, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_3_3-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_3_3-solution000001.solution new file mode 100644 index 0000000000..15472caf03 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_3_3-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 2, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_3_3-solution000002.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_3_3-solution000002.solution new file mode 100644 index 0000000000..ff56905e23 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_3_3-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_3_3-solution000003.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_3_3-solution000003.solution new file mode 100644 index 0000000000..d56a0bbcdc --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_3_3-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_3_3-solution000004.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_3_3-solution000004.solution new file mode 100644 index 0000000000..5e2caa751c --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_3_3-solution000004.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 2, 2) +letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_3_3-solution000005.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_3_3-solution000005.solution new file mode 100644 index 0000000000..1b4b5b08a6 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_3_3-solution000005.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 2, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_3_3-solution000006.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_3_3-solution000006.solution new file mode 100644 index 0000000000..621d5f6edc --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_1_3_3-solution000006.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 1, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_1_1-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_1_1-solution000001.solution new file mode 100644 index 0000000000..5e2caa751c --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_1_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 2, 2) +letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_1_1-solution000002.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_1_1-solution000002.solution new file mode 100644 index 0000000000..1b4b5b08a6 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_1_1-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 2, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_1_1-solution000003.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_1_1-solution000003.solution new file mode 100644 index 0000000000..621d5f6edc --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_1_1-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 1, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_1_1-solution000004.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_1_1-solution000004.solution new file mode 100644 index 0000000000..15472caf03 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_1_1-solution000004.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 2, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_1_1-solution000005.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_1_1-solution000005.solution new file mode 100644 index 0000000000..ff56905e23 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_1_1-solution000005.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_1_1-solution000006.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_1_1-solution000006.solution new file mode 100644 index 0000000000..d56a0bbcdc --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_1_1-solution000006.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_1_2-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_1_2-solution000001.solution new file mode 100644 index 0000000000..1b4b5b08a6 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_1_2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 2, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_1_2-solution000002.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_1_2-solution000002.solution new file mode 100644 index 0000000000..5e2caa751c --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_1_2-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 2, 2) +letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_1_2-solution000003.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_1_2-solution000003.solution new file mode 100644 index 0000000000..621d5f6edc --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_1_2-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 1, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_1_2-solution000004.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_1_2-solution000004.solution new file mode 100644 index 0000000000..d56a0bbcdc --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_1_2-solution000004.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_1_2-solution000005.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_1_2-solution000005.solution new file mode 100644 index 0000000000..ff56905e23 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_1_2-solution000005.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_1_2-solution000006.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_1_2-solution000006.solution new file mode 100644 index 0000000000..15472caf03 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_1_2-solution000006.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 2, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_1_3-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_1_3-solution000001.solution new file mode 100644 index 0000000000..5e2caa751c --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_1_3-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 2, 2) +letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_1_3-solution000002.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_1_3-solution000002.solution new file mode 100644 index 0000000000..1b4b5b08a6 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_1_3-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 2, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_1_3-solution000003.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_1_3-solution000003.solution new file mode 100644 index 0000000000..621d5f6edc --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_1_3-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 1, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_1_3-solution000004.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_1_3-solution000004.solution new file mode 100644 index 0000000000..15472caf03 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_1_3-solution000004.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 2, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_1_3-solution000005.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_1_3-solution000005.solution new file mode 100644 index 0000000000..ff56905e23 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_1_3-solution000005.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_1_3-solution000006.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_1_3-solution000006.solution new file mode 100644 index 0000000000..d56a0bbcdc --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_1_3-solution000006.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_2_1-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_2_1-solution000001.solution new file mode 100644 index 0000000000..621d5f6edc --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_2_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 1, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_2_1-solution000002.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_2_1-solution000002.solution new file mode 100644 index 0000000000..5e2caa751c --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_2_1-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 2, 2) +letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_2_1-solution000003.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_2_1-solution000003.solution new file mode 100644 index 0000000000..1b4b5b08a6 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_2_1-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 2, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_2_1-solution000004.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_2_1-solution000004.solution new file mode 100644 index 0000000000..15472caf03 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_2_1-solution000004.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 2, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_2_1-solution000005.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_2_1-solution000005.solution new file mode 100644 index 0000000000..ff56905e23 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_2_1-solution000005.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_2_1-solution000006.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_2_1-solution000006.solution new file mode 100644 index 0000000000..d56a0bbcdc --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_2_1-solution000006.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_2_2-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_2_2-solution000001.solution new file mode 100644 index 0000000000..621d5f6edc --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_2_2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 1, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_2_2-solution000002.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_2_2-solution000002.solution new file mode 100644 index 0000000000..1b4b5b08a6 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_2_2-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 2, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_2_2-solution000003.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_2_2-solution000003.solution new file mode 100644 index 0000000000..5e2caa751c --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_2_2-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 2, 2) +letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_2_2-solution000004.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_2_2-solution000004.solution new file mode 100644 index 0000000000..d56a0bbcdc --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_2_2-solution000004.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_2_2-solution000005.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_2_2-solution000005.solution new file mode 100644 index 0000000000..ff56905e23 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_2_2-solution000005.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_2_2-solution000006.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_2_2-solution000006.solution new file mode 100644 index 0000000000..15472caf03 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_2_2-solution000006.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 2, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_2_3-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_2_3-solution000001.solution new file mode 100644 index 0000000000..621d5f6edc --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_2_3-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 1, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_2_3-solution000002.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_2_3-solution000002.solution new file mode 100644 index 0000000000..5e2caa751c --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_2_3-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 2, 2) +letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_2_3-solution000003.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_2_3-solution000003.solution new file mode 100644 index 0000000000..1b4b5b08a6 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_2_3-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 2, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_2_3-solution000004.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_2_3-solution000004.solution new file mode 100644 index 0000000000..15472caf03 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_2_3-solution000004.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 2, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_2_3-solution000005.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_2_3-solution000005.solution new file mode 100644 index 0000000000..ff56905e23 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_2_3-solution000005.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_2_3-solution000006.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_2_3-solution000006.solution new file mode 100644 index 0000000000..d56a0bbcdc --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_2_3-solution000006.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_3_1-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_3_1-solution000001.solution new file mode 100644 index 0000000000..15472caf03 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_3_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 2, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_3_1-solution000002.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_3_1-solution000002.solution new file mode 100644 index 0000000000..ff56905e23 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_3_1-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_3_1-solution000003.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_3_1-solution000003.solution new file mode 100644 index 0000000000..d56a0bbcdc --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_3_1-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_3_1-solution000004.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_3_1-solution000004.solution new file mode 100644 index 0000000000..5e2caa751c --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_3_1-solution000004.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 2, 2) +letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_3_1-solution000005.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_3_1-solution000005.solution new file mode 100644 index 0000000000..1b4b5b08a6 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_3_1-solution000005.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 2, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_3_1-solution000006.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_3_1-solution000006.solution new file mode 100644 index 0000000000..621d5f6edc --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_3_1-solution000006.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 1, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_3_2-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_3_2-solution000001.solution new file mode 100644 index 0000000000..d56a0bbcdc --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_3_2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_3_2-solution000002.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_3_2-solution000002.solution new file mode 100644 index 0000000000..ff56905e23 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_3_2-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_3_2-solution000003.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_3_2-solution000003.solution new file mode 100644 index 0000000000..15472caf03 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_3_2-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 2, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_3_2-solution000004.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_3_2-solution000004.solution new file mode 100644 index 0000000000..1b4b5b08a6 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_3_2-solution000004.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 2, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_3_2-solution000005.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_3_2-solution000005.solution new file mode 100644 index 0000000000..5e2caa751c --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_3_2-solution000005.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 2, 2) +letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_3_2-solution000006.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_3_2-solution000006.solution new file mode 100644 index 0000000000..621d5f6edc --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_3_2-solution000006.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 1, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_3_3-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_3_3-solution000001.solution new file mode 100644 index 0000000000..15472caf03 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_3_3-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 2, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_3_3-solution000002.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_3_3-solution000002.solution new file mode 100644 index 0000000000..ff56905e23 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_3_3-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_3_3-solution000003.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_3_3-solution000003.solution new file mode 100644 index 0000000000..d56a0bbcdc --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_3_3-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_3_3-solution000004.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_3_3-solution000004.solution new file mode 100644 index 0000000000..5e2caa751c --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_3_3-solution000004.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 2, 2) +letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_3_3-solution000005.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_3_3-solution000005.solution new file mode 100644 index 0000000000..1b4b5b08a6 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_3_3-solution000005.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 2, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_3_3-solution000006.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_3_3-solution000006.solution new file mode 100644 index 0000000000..621d5f6edc --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_2_3_3-solution000006.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 1, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_1_1-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_1_1-solution000001.solution new file mode 100644 index 0000000000..5e2caa751c --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_1_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 2, 2) +letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_1_1-solution000002.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_1_1-solution000002.solution new file mode 100644 index 0000000000..1b4b5b08a6 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_1_1-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 2, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_1_1-solution000003.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_1_1-solution000003.solution new file mode 100644 index 0000000000..621d5f6edc --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_1_1-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 1, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_1_1-solution000004.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_1_1-solution000004.solution new file mode 100644 index 0000000000..15472caf03 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_1_1-solution000004.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 2, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_1_1-solution000005.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_1_1-solution000005.solution new file mode 100644 index 0000000000..ff56905e23 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_1_1-solution000005.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_1_1-solution000006.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_1_1-solution000006.solution new file mode 100644 index 0000000000..d56a0bbcdc --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_1_1-solution000006.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_1_2-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_1_2-solution000001.solution new file mode 100644 index 0000000000..1b4b5b08a6 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_1_2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 2, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_1_2-solution000002.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_1_2-solution000002.solution new file mode 100644 index 0000000000..5e2caa751c --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_1_2-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 2, 2) +letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_1_2-solution000003.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_1_2-solution000003.solution new file mode 100644 index 0000000000..621d5f6edc --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_1_2-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 1, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_1_2-solution000004.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_1_2-solution000004.solution new file mode 100644 index 0000000000..d56a0bbcdc --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_1_2-solution000004.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_1_2-solution000005.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_1_2-solution000005.solution new file mode 100644 index 0000000000..ff56905e23 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_1_2-solution000005.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_1_2-solution000006.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_1_2-solution000006.solution new file mode 100644 index 0000000000..15472caf03 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_1_2-solution000006.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 2, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_1_3-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_1_3-solution000001.solution new file mode 100644 index 0000000000..5e2caa751c --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_1_3-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 2, 2) +letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_1_3-solution000002.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_1_3-solution000002.solution new file mode 100644 index 0000000000..1b4b5b08a6 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_1_3-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 2, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_1_3-solution000003.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_1_3-solution000003.solution new file mode 100644 index 0000000000..621d5f6edc --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_1_3-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 1, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_1_3-solution000004.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_1_3-solution000004.solution new file mode 100644 index 0000000000..15472caf03 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_1_3-solution000004.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 2, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_1_3-solution000005.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_1_3-solution000005.solution new file mode 100644 index 0000000000..ff56905e23 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_1_3-solution000005.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_1_3-solution000006.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_1_3-solution000006.solution new file mode 100644 index 0000000000..d56a0bbcdc --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_1_3-solution000006.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_2_1-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_2_1-solution000001.solution new file mode 100644 index 0000000000..621d5f6edc --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_2_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 1, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_2_1-solution000002.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_2_1-solution000002.solution new file mode 100644 index 0000000000..5e2caa751c --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_2_1-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 2, 2) +letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_2_1-solution000003.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_2_1-solution000003.solution new file mode 100644 index 0000000000..1b4b5b08a6 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_2_1-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 2, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_2_1-solution000004.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_2_1-solution000004.solution new file mode 100644 index 0000000000..15472caf03 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_2_1-solution000004.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 2, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_2_1-solution000005.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_2_1-solution000005.solution new file mode 100644 index 0000000000..ff56905e23 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_2_1-solution000005.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_2_1-solution000006.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_2_1-solution000006.solution new file mode 100644 index 0000000000..d56a0bbcdc --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_2_1-solution000006.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_2_2-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_2_2-solution000001.solution new file mode 100644 index 0000000000..621d5f6edc --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_2_2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 1, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_2_2-solution000002.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_2_2-solution000002.solution new file mode 100644 index 0000000000..1b4b5b08a6 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_2_2-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 2, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_2_2-solution000003.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_2_2-solution000003.solution new file mode 100644 index 0000000000..5e2caa751c --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_2_2-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 2, 2) +letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_2_2-solution000004.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_2_2-solution000004.solution new file mode 100644 index 0000000000..d56a0bbcdc --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_2_2-solution000004.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_2_2-solution000005.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_2_2-solution000005.solution new file mode 100644 index 0000000000..ff56905e23 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_2_2-solution000005.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_2_2-solution000006.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_2_2-solution000006.solution new file mode 100644 index 0000000000..15472caf03 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_2_2-solution000006.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 2, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_2_3-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_2_3-solution000001.solution new file mode 100644 index 0000000000..621d5f6edc --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_2_3-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 1, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_2_3-solution000002.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_2_3-solution000002.solution new file mode 100644 index 0000000000..5e2caa751c --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_2_3-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 2, 2) +letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_2_3-solution000003.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_2_3-solution000003.solution new file mode 100644 index 0000000000..1b4b5b08a6 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_2_3-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 2, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_2_3-solution000004.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_2_3-solution000004.solution new file mode 100644 index 0000000000..15472caf03 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_2_3-solution000004.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 2, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_2_3-solution000005.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_2_3-solution000005.solution new file mode 100644 index 0000000000..ff56905e23 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_2_3-solution000005.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_2_3-solution000006.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_2_3-solution000006.solution new file mode 100644 index 0000000000..d56a0bbcdc --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_2_3-solution000006.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_3_1-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_3_1-solution000001.solution new file mode 100644 index 0000000000..15472caf03 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_3_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 2, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_3_1-solution000002.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_3_1-solution000002.solution new file mode 100644 index 0000000000..ff56905e23 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_3_1-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_3_1-solution000003.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_3_1-solution000003.solution new file mode 100644 index 0000000000..d56a0bbcdc --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_3_1-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_3_1-solution000004.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_3_1-solution000004.solution new file mode 100644 index 0000000000..5e2caa751c --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_3_1-solution000004.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 2, 2) +letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_3_1-solution000005.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_3_1-solution000005.solution new file mode 100644 index 0000000000..1b4b5b08a6 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_3_1-solution000005.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 2, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_3_1-solution000006.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_3_1-solution000006.solution new file mode 100644 index 0000000000..621d5f6edc --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_3_1-solution000006.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 1, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_3_2-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_3_2-solution000001.solution new file mode 100644 index 0000000000..d56a0bbcdc --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_3_2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_3_2-solution000002.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_3_2-solution000002.solution new file mode 100644 index 0000000000..ff56905e23 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_3_2-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_3_2-solution000003.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_3_2-solution000003.solution new file mode 100644 index 0000000000..15472caf03 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_3_2-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 2, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_3_2-solution000004.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_3_2-solution000004.solution new file mode 100644 index 0000000000..1b4b5b08a6 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_3_2-solution000004.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 2, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_3_2-solution000005.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_3_2-solution000005.solution new file mode 100644 index 0000000000..5e2caa751c --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_3_2-solution000005.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 2, 2) +letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_3_2-solution000006.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_3_2-solution000006.solution new file mode 100644 index 0000000000..621d5f6edc --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_3_2-solution000006.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 1, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_3_3-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_3_3-solution000001.solution new file mode 100644 index 0000000000..15472caf03 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_3_3-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 2, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_3_3-solution000002.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_3_3-solution000002.solution new file mode 100644 index 0000000000..ff56905e23 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_3_3-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_3_3-solution000003.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_3_3-solution000003.solution new file mode 100644 index 0000000000..d56a0bbcdc --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_3_3-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_3_3-solution000004.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_3_3-solution000004.solution new file mode 100644 index 0000000000..5e2caa751c --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_3_3-solution000004.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 2, 2) +letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_3_3-solution000005.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_3_3-solution000005.solution new file mode 100644 index 0000000000..1b4b5b08a6 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_3_3-solution000005.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 2, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_3_3-solution000006.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_3_3-solution000006.solution new file mode 100644 index 0000000000..621d5f6edc --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_1_3_3_3-solution000006.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 1, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_1_1-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_1_1-solution000001.solution new file mode 100644 index 0000000000..5e2caa751c --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_1_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 2, 2) +letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_1_1-solution000002.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_1_1-solution000002.solution new file mode 100644 index 0000000000..1b4b5b08a6 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_1_1-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 2, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_1_1-solution000003.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_1_1-solution000003.solution new file mode 100644 index 0000000000..621d5f6edc --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_1_1-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 1, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_1_1-solution000004.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_1_1-solution000004.solution new file mode 100644 index 0000000000..15472caf03 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_1_1-solution000004.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 2, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_1_1-solution000005.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_1_1-solution000005.solution new file mode 100644 index 0000000000..ff56905e23 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_1_1-solution000005.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_1_1-solution000006.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_1_1-solution000006.solution new file mode 100644 index 0000000000..d56a0bbcdc --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_1_1-solution000006.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_1_2-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_1_2-solution000001.solution new file mode 100644 index 0000000000..1b4b5b08a6 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_1_2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 2, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_1_2-solution000002.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_1_2-solution000002.solution new file mode 100644 index 0000000000..5e2caa751c --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_1_2-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 2, 2) +letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_1_2-solution000003.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_1_2-solution000003.solution new file mode 100644 index 0000000000..621d5f6edc --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_1_2-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 1, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_1_2-solution000004.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_1_2-solution000004.solution new file mode 100644 index 0000000000..d56a0bbcdc --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_1_2-solution000004.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_1_2-solution000005.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_1_2-solution000005.solution new file mode 100644 index 0000000000..ff56905e23 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_1_2-solution000005.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_1_2-solution000006.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_1_2-solution000006.solution new file mode 100644 index 0000000000..15472caf03 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_1_2-solution000006.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 2, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_1_3-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_1_3-solution000001.solution new file mode 100644 index 0000000000..5e2caa751c --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_1_3-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 2, 2) +letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_1_3-solution000002.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_1_3-solution000002.solution new file mode 100644 index 0000000000..1b4b5b08a6 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_1_3-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 2, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_1_3-solution000003.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_1_3-solution000003.solution new file mode 100644 index 0000000000..621d5f6edc --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_1_3-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 1, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_1_3-solution000004.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_1_3-solution000004.solution new file mode 100644 index 0000000000..15472caf03 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_1_3-solution000004.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 2, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_1_3-solution000005.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_1_3-solution000005.solution new file mode 100644 index 0000000000..ff56905e23 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_1_3-solution000005.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_1_3-solution000006.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_1_3-solution000006.solution new file mode 100644 index 0000000000..d56a0bbcdc --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_1_3-solution000006.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_2_1-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_2_1-solution000001.solution new file mode 100644 index 0000000000..621d5f6edc --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_2_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 1, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_2_1-solution000002.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_2_1-solution000002.solution new file mode 100644 index 0000000000..5e2caa751c --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_2_1-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 2, 2) +letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_2_1-solution000003.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_2_1-solution000003.solution new file mode 100644 index 0000000000..1b4b5b08a6 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_2_1-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 2, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_2_1-solution000004.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_2_1-solution000004.solution new file mode 100644 index 0000000000..15472caf03 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_2_1-solution000004.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 2, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_2_1-solution000005.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_2_1-solution000005.solution new file mode 100644 index 0000000000..ff56905e23 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_2_1-solution000005.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_2_1-solution000006.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_2_1-solution000006.solution new file mode 100644 index 0000000000..d56a0bbcdc --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_2_1-solution000006.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_2_2-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_2_2-solution000001.solution new file mode 100644 index 0000000000..621d5f6edc --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_2_2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 1, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_2_2-solution000002.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_2_2-solution000002.solution new file mode 100644 index 0000000000..1b4b5b08a6 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_2_2-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 2, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_2_2-solution000003.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_2_2-solution000003.solution new file mode 100644 index 0000000000..5e2caa751c --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_2_2-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 2, 2) +letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_2_2-solution000004.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_2_2-solution000004.solution new file mode 100644 index 0000000000..d56a0bbcdc --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_2_2-solution000004.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_2_2-solution000005.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_2_2-solution000005.solution new file mode 100644 index 0000000000..ff56905e23 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_2_2-solution000005.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_2_2-solution000006.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_2_2-solution000006.solution new file mode 100644 index 0000000000..15472caf03 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_2_2-solution000006.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 2, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_2_3-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_2_3-solution000001.solution new file mode 100644 index 0000000000..621d5f6edc --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_2_3-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 1, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_2_3-solution000002.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_2_3-solution000002.solution new file mode 100644 index 0000000000..5e2caa751c --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_2_3-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 2, 2) +letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_2_3-solution000003.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_2_3-solution000003.solution new file mode 100644 index 0000000000..1b4b5b08a6 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_2_3-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 2, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_2_3-solution000004.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_2_3-solution000004.solution new file mode 100644 index 0000000000..15472caf03 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_2_3-solution000004.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 2, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_2_3-solution000005.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_2_3-solution000005.solution new file mode 100644 index 0000000000..ff56905e23 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_2_3-solution000005.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_2_3-solution000006.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_2_3-solution000006.solution new file mode 100644 index 0000000000..d56a0bbcdc --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_2_3-solution000006.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_3_1-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_3_1-solution000001.solution new file mode 100644 index 0000000000..15472caf03 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_3_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 2, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_3_1-solution000002.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_3_1-solution000002.solution new file mode 100644 index 0000000000..ff56905e23 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_3_1-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_3_1-solution000003.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_3_1-solution000003.solution new file mode 100644 index 0000000000..d56a0bbcdc --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_3_1-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_3_1-solution000004.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_3_1-solution000004.solution new file mode 100644 index 0000000000..5e2caa751c --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_3_1-solution000004.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 2, 2) +letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_3_1-solution000005.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_3_1-solution000005.solution new file mode 100644 index 0000000000..1b4b5b08a6 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_3_1-solution000005.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 2, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_3_1-solution000006.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_3_1-solution000006.solution new file mode 100644 index 0000000000..621d5f6edc --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_3_1-solution000006.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 1, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_3_2-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_3_2-solution000001.solution new file mode 100644 index 0000000000..d56a0bbcdc --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_3_2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_3_2-solution000002.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_3_2-solution000002.solution new file mode 100644 index 0000000000..ff56905e23 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_3_2-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_3_2-solution000003.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_3_2-solution000003.solution new file mode 100644 index 0000000000..15472caf03 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_3_2-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 2, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_3_2-solution000004.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_3_2-solution000004.solution new file mode 100644 index 0000000000..1b4b5b08a6 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_3_2-solution000004.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 2, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_3_2-solution000005.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_3_2-solution000005.solution new file mode 100644 index 0000000000..5e2caa751c --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_3_2-solution000005.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 2, 2) +letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_3_2-solution000006.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_3_2-solution000006.solution new file mode 100644 index 0000000000..621d5f6edc --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_3_2-solution000006.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 1, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_3_3-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_3_3-solution000001.solution new file mode 100644 index 0000000000..15472caf03 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_3_3-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 2, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_3_3-solution000002.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_3_3-solution000002.solution new file mode 100644 index 0000000000..ff56905e23 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_3_3-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_3_3-solution000003.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_3_3-solution000003.solution new file mode 100644 index 0000000000..d56a0bbcdc --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_3_3-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_3_3-solution000004.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_3_3-solution000004.solution new file mode 100644 index 0000000000..5e2caa751c --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_3_3-solution000004.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 2, 2) +letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_3_3-solution000005.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_3_3-solution000005.solution new file mode 100644 index 0000000000..1b4b5b08a6 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_3_3-solution000005.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 2, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_3_3-solution000006.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_3_3-solution000006.solution new file mode 100644 index 0000000000..621d5f6edc --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_1_3_3-solution000006.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 1, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_1_1-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_1_1-solution000001.solution new file mode 100644 index 0000000000..5e2caa751c --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_1_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 2, 2) +letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_1_1-solution000002.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_1_1-solution000002.solution new file mode 100644 index 0000000000..1b4b5b08a6 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_1_1-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 2, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_1_1-solution000003.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_1_1-solution000003.solution new file mode 100644 index 0000000000..621d5f6edc --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_1_1-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 1, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_1_1-solution000004.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_1_1-solution000004.solution new file mode 100644 index 0000000000..15472caf03 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_1_1-solution000004.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 2, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_1_1-solution000005.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_1_1-solution000005.solution new file mode 100644 index 0000000000..ff56905e23 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_1_1-solution000005.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_1_1-solution000006.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_1_1-solution000006.solution new file mode 100644 index 0000000000..d56a0bbcdc --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_1_1-solution000006.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_1_2-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_1_2-solution000001.solution new file mode 100644 index 0000000000..1b4b5b08a6 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_1_2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 2, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_1_2-solution000002.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_1_2-solution000002.solution new file mode 100644 index 0000000000..5e2caa751c --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_1_2-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 2, 2) +letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_1_2-solution000003.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_1_2-solution000003.solution new file mode 100644 index 0000000000..621d5f6edc --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_1_2-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 1, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_1_2-solution000004.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_1_2-solution000004.solution new file mode 100644 index 0000000000..d56a0bbcdc --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_1_2-solution000004.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_1_2-solution000005.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_1_2-solution000005.solution new file mode 100644 index 0000000000..ff56905e23 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_1_2-solution000005.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_1_2-solution000006.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_1_2-solution000006.solution new file mode 100644 index 0000000000..15472caf03 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_1_2-solution000006.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 2, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_1_3-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_1_3-solution000001.solution new file mode 100644 index 0000000000..5e2caa751c --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_1_3-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 2, 2) +letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_1_3-solution000002.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_1_3-solution000002.solution new file mode 100644 index 0000000000..1b4b5b08a6 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_1_3-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 2, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_1_3-solution000003.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_1_3-solution000003.solution new file mode 100644 index 0000000000..621d5f6edc --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_1_3-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 1, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_1_3-solution000004.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_1_3-solution000004.solution new file mode 100644 index 0000000000..15472caf03 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_1_3-solution000004.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 2, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_1_3-solution000005.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_1_3-solution000005.solution new file mode 100644 index 0000000000..ff56905e23 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_1_3-solution000005.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_1_3-solution000006.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_1_3-solution000006.solution new file mode 100644 index 0000000000..d56a0bbcdc --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_1_3-solution000006.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_2_1-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_2_1-solution000001.solution new file mode 100644 index 0000000000..621d5f6edc --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_2_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 1, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_2_1-solution000002.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_2_1-solution000002.solution new file mode 100644 index 0000000000..5e2caa751c --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_2_1-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 2, 2) +letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_2_1-solution000003.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_2_1-solution000003.solution new file mode 100644 index 0000000000..1b4b5b08a6 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_2_1-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 2, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_2_1-solution000004.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_2_1-solution000004.solution new file mode 100644 index 0000000000..15472caf03 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_2_1-solution000004.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 2, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_2_1-solution000005.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_2_1-solution000005.solution new file mode 100644 index 0000000000..ff56905e23 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_2_1-solution000005.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_2_1-solution000006.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_2_1-solution000006.solution new file mode 100644 index 0000000000..d56a0bbcdc --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_2_1-solution000006.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_2_2-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_2_2-solution000001.solution new file mode 100644 index 0000000000..621d5f6edc --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_2_2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 1, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_2_2-solution000002.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_2_2-solution000002.solution new file mode 100644 index 0000000000..1b4b5b08a6 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_2_2-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 2, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_2_2-solution000003.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_2_2-solution000003.solution new file mode 100644 index 0000000000..5e2caa751c --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_2_2-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 2, 2) +letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_2_2-solution000004.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_2_2-solution000004.solution new file mode 100644 index 0000000000..d56a0bbcdc --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_2_2-solution000004.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_2_2-solution000005.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_2_2-solution000005.solution new file mode 100644 index 0000000000..ff56905e23 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_2_2-solution000005.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_2_2-solution000006.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_2_2-solution000006.solution new file mode 100644 index 0000000000..15472caf03 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_2_2-solution000006.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 2, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_2_2.eprime b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_2_2.eprime new file mode 100644 index 0000000000..24067a2f5e --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_2_2.eprime @@ -0,0 +1,66 @@ +language ESSENCE' 1.0 + +find a_ExplicitWithRepetition_Flag: int(3) +find a_ExplicitWithRepetition_Values: matrix indexed by [int(1..3)] of int(1..2) +find b_ExplicitWithRepetition_Flag: int(3) +find b_ExplicitWithRepetition_Values: matrix indexed by [int(1..3)] of int(1..2) +branching on + [a_ExplicitWithRepetition_Flag, a_ExplicitWithRepetition_Values, b_ExplicitWithRepetition_Flag, + b_ExplicitWithRepetition_Values] +such that + or([sum([toInt(a_ExplicitWithRepetition_Values[q34] = a_ExplicitWithRepetition_Values[q13]) + | q34 : int(1..3), q34 <= 3]) + < + sum([toInt(b_ExplicitWithRepetition_Values[q36] = a_ExplicitWithRepetition_Values[q13]) + | q36 : int(1..3), q36 <= 3]) + /\ + (and([a_ExplicitWithRepetition_Values[q37] < a_ExplicitWithRepetition_Values[q13] -> + sum([toInt(a_ExplicitWithRepetition_Values[q46] = a_ExplicitWithRepetition_Values[q37]) + | q46 : int(1..3), q46 <= 3]) + = + sum([toInt(b_ExplicitWithRepetition_Values[q48] = a_ExplicitWithRepetition_Values[q37]) + | q48 : int(1..3), q48 <= 3]) + | q37 : int(1..3), q37 <= 3]) + /\ + and([!or([a_ExplicitWithRepetition_Values[q40] = b_ExplicitWithRepetition_Values[q38] + | q40 : int(1..3), q40 <= 3]) + /\ b_ExplicitWithRepetition_Values[q38] < a_ExplicitWithRepetition_Values[q13] + -> + sum([toInt(a_ExplicitWithRepetition_Values[q42] = b_ExplicitWithRepetition_Values[q38]) + | q42 : int(1..3), q42 <= 3]) + = + sum([toInt(b_ExplicitWithRepetition_Values[q44] = b_ExplicitWithRepetition_Values[q38]) + | q44 : int(1..3), q44 <= 3]) + | q38 : int(1..3), q38 <= 3])) + | q13 : int(1..3), q13 <= 3]) + \/ + or([!or([a_ExplicitWithRepetition_Values[q16] = b_ExplicitWithRepetition_Values[q14] | q16 : int(1..3), q16 <= 3]) + /\ + (sum([toInt(a_ExplicitWithRepetition_Values[q18] = b_ExplicitWithRepetition_Values[q14]) + | q18 : int(1..3), q18 <= 3]) + < + sum([toInt(b_ExplicitWithRepetition_Values[q20] = b_ExplicitWithRepetition_Values[q14]) + | q20 : int(1..3), q20 <= 3]) + /\ + (and([a_ExplicitWithRepetition_Values[q21] < b_ExplicitWithRepetition_Values[q14] -> + sum([toInt(a_ExplicitWithRepetition_Values[q30] = a_ExplicitWithRepetition_Values[q21]) + | q30 : int(1..3), q30 <= 3]) + = + sum([toInt(b_ExplicitWithRepetition_Values[q32] = a_ExplicitWithRepetition_Values[q21]) + | q32 : int(1..3), q32 <= 3]) + | q21 : int(1..3), q21 <= 3]) + /\ + and([!or([a_ExplicitWithRepetition_Values[q24] = b_ExplicitWithRepetition_Values[q22] + | q24 : int(1..3), q24 <= 3]) + /\ b_ExplicitWithRepetition_Values[q22] < b_ExplicitWithRepetition_Values[q14] + -> + sum([toInt(a_ExplicitWithRepetition_Values[q26] = b_ExplicitWithRepetition_Values[q22]) + | q26 : int(1..3), q26 <= 3]) + = + sum([toInt(b_ExplicitWithRepetition_Values[q28] = b_ExplicitWithRepetition_Values[q22]) + | q28 : int(1..3), q28 <= 3]) + | q22 : int(1..3), q22 <= 3]))) + | q14 : int(1..3), q14 <= 3]), + and([a_ExplicitWithRepetition_Values[q1] <= a_ExplicitWithRepetition_Values[q1 + 1] | q1 : int(1..2), q1 + 1 <= 3]), + and([b_ExplicitWithRepetition_Values[q6] <= b_ExplicitWithRepetition_Values[q6 + 1] | q6 : int(1..2), q6 + 1 <= 3]) + diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_2_3-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_2_3-solution000001.solution new file mode 100644 index 0000000000..621d5f6edc --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_2_3-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 1, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_2_3-solution000002.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_2_3-solution000002.solution new file mode 100644 index 0000000000..5e2caa751c --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_2_3-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 2, 2) +letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_2_3-solution000003.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_2_3-solution000003.solution new file mode 100644 index 0000000000..1b4b5b08a6 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_2_3-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 2, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_2_3-solution000004.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_2_3-solution000004.solution new file mode 100644 index 0000000000..15472caf03 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_2_3-solution000004.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 2, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_2_3-solution000005.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_2_3-solution000005.solution new file mode 100644 index 0000000000..ff56905e23 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_2_3-solution000005.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_2_3-solution000006.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_2_3-solution000006.solution new file mode 100644 index 0000000000..d56a0bbcdc --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_2_3-solution000006.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_2_3.eprime b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_2_3.eprime new file mode 100644 index 0000000000..3c8a938e45 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_2_3.eprime @@ -0,0 +1,75 @@ +language ESSENCE' 1.0 + +find a_ExplicitWithRepetition_Flag: int(3) +find a_ExplicitWithRepetition_Values: matrix indexed by [int(1..3)] of int(1..2) +find b_ExplicitWithRepetition_Flag: int(3) +find b_ExplicitWithRepetition_Values: matrix indexed by [int(1..3)] of int(1..2) +find b_MOccurrence: matrix indexed by [int(1..2)] of int(0..3) +branching on + [a_ExplicitWithRepetition_Flag, a_ExplicitWithRepetition_Values, b_MOccurrence, b_ExplicitWithRepetition_Flag, + b_ExplicitWithRepetition_Values] +such that + or([sum([toInt(a_ExplicitWithRepetition_Values[q42] = a_ExplicitWithRepetition_Values[q21]) + | q42 : int(1..3), q42 <= 3]) + < + sum([toInt(b_ExplicitWithRepetition_Values[q44] = a_ExplicitWithRepetition_Values[q21]) + | q44 : int(1..3), q44 <= 3]) + /\ + (and([a_ExplicitWithRepetition_Values[q45] < a_ExplicitWithRepetition_Values[q21] -> + sum([toInt(a_ExplicitWithRepetition_Values[q54] = a_ExplicitWithRepetition_Values[q45]) + | q54 : int(1..3), q54 <= 3]) + = + sum([toInt(b_ExplicitWithRepetition_Values[q56] = a_ExplicitWithRepetition_Values[q45]) + | q56 : int(1..3), q56 <= 3]) + | q45 : int(1..3), q45 <= 3]) + /\ + and([!or([a_ExplicitWithRepetition_Values[q48] = b_ExplicitWithRepetition_Values[q46] + | q48 : int(1..3), q48 <= 3]) + /\ b_ExplicitWithRepetition_Values[q46] < a_ExplicitWithRepetition_Values[q21] + -> + sum([toInt(a_ExplicitWithRepetition_Values[q50] = b_ExplicitWithRepetition_Values[q46]) + | q50 : int(1..3), q50 <= 3]) + = + sum([toInt(b_ExplicitWithRepetition_Values[q52] = b_ExplicitWithRepetition_Values[q46]) + | q52 : int(1..3), q52 <= 3]) + | q46 : int(1..3), q46 <= 3])) + | q21 : int(1..3), q21 <= 3]) + \/ + or([!or([a_ExplicitWithRepetition_Values[q24] = b_ExplicitWithRepetition_Values[q22] | q24 : int(1..3), q24 <= 3]) + /\ + (sum([toInt(a_ExplicitWithRepetition_Values[q26] = b_ExplicitWithRepetition_Values[q22]) + | q26 : int(1..3), q26 <= 3]) + < + sum([toInt(b_ExplicitWithRepetition_Values[q28] = b_ExplicitWithRepetition_Values[q22]) + | q28 : int(1..3), q28 <= 3]) + /\ + (and([a_ExplicitWithRepetition_Values[q29] < b_ExplicitWithRepetition_Values[q22] -> + sum([toInt(a_ExplicitWithRepetition_Values[q38] = a_ExplicitWithRepetition_Values[q29]) + | q38 : int(1..3), q38 <= 3]) + = + sum([toInt(b_ExplicitWithRepetition_Values[q40] = a_ExplicitWithRepetition_Values[q29]) + | q40 : int(1..3), q40 <= 3]) + | q29 : int(1..3), q29 <= 3]) + /\ + and([!or([a_ExplicitWithRepetition_Values[q32] = b_ExplicitWithRepetition_Values[q30] + | q32 : int(1..3), q32 <= 3]) + /\ b_ExplicitWithRepetition_Values[q30] < b_ExplicitWithRepetition_Values[q22] + -> + sum([toInt(a_ExplicitWithRepetition_Values[q34] = b_ExplicitWithRepetition_Values[q30]) + | q34 : int(1..3), q34 <= 3]) + = + sum([toInt(b_ExplicitWithRepetition_Values[q36] = b_ExplicitWithRepetition_Values[q30]) + | q36 : int(1..3), q36 <= 3]) + | q30 : int(1..3), q30 <= 3]))) + | q22 : int(1..3), q22 <= 3]), + and([a_ExplicitWithRepetition_Values[q1] <= a_ExplicitWithRepetition_Values[q1 + 1] | q1 : int(1..2), q1 + 1 <= 3]), + and([b_ExplicitWithRepetition_Values[q6] <= b_ExplicitWithRepetition_Values[q6 + 1] | q6 : int(1..2), q6 + 1 <= 3]), + 3 = sum([b_MOccurrence[q11] | q11 : int(1..2)]), + and([b_MOccurrence[q13] > 0 -> + b_MOccurrence[q13] = sum([toInt(b_ExplicitWithRepetition_Values[q15] = q13) | q15 : int(1..3), q15 <= 3]) + | q13 : int(1..2)]), + and([b_MOccurrence[b_ExplicitWithRepetition_Values[q16]] = + sum([toInt(b_ExplicitWithRepetition_Values[q18] = b_ExplicitWithRepetition_Values[q16]) + | q18 : int(1..3), q18 <= 3]) + | q16 : int(1..3), q16 <= 3]) + diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_3_1-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_3_1-solution000001.solution new file mode 100644 index 0000000000..15472caf03 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_3_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 2, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_3_1-solution000002.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_3_1-solution000002.solution new file mode 100644 index 0000000000..ff56905e23 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_3_1-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_3_1-solution000003.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_3_1-solution000003.solution new file mode 100644 index 0000000000..d56a0bbcdc --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_3_1-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_3_1-solution000004.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_3_1-solution000004.solution new file mode 100644 index 0000000000..5e2caa751c --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_3_1-solution000004.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 2, 2) +letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_3_1-solution000005.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_3_1-solution000005.solution new file mode 100644 index 0000000000..1b4b5b08a6 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_3_1-solution000005.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 2, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_3_1-solution000006.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_3_1-solution000006.solution new file mode 100644 index 0000000000..621d5f6edc --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_3_1-solution000006.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 1, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_3_2-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_3_2-solution000001.solution new file mode 100644 index 0000000000..d56a0bbcdc --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_3_2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_3_2-solution000002.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_3_2-solution000002.solution new file mode 100644 index 0000000000..ff56905e23 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_3_2-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_3_2-solution000003.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_3_2-solution000003.solution new file mode 100644 index 0000000000..15472caf03 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_3_2-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 2, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_3_2-solution000004.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_3_2-solution000004.solution new file mode 100644 index 0000000000..1b4b5b08a6 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_3_2-solution000004.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 2, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_3_2-solution000005.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_3_2-solution000005.solution new file mode 100644 index 0000000000..5e2caa751c --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_3_2-solution000005.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 2, 2) +letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_3_2-solution000006.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_3_2-solution000006.solution new file mode 100644 index 0000000000..621d5f6edc --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_3_2-solution000006.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 1, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_3_2.eprime b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_3_2.eprime new file mode 100644 index 0000000000..f152965fd1 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_3_2.eprime @@ -0,0 +1,75 @@ +language ESSENCE' 1.0 + +find a_ExplicitWithRepetition_Flag: int(3) +find a_ExplicitWithRepetition_Values: matrix indexed by [int(1..3)] of int(1..2) +find a_MOccurrence: matrix indexed by [int(1..2)] of int(0..3) +find b_ExplicitWithRepetition_Flag: int(3) +find b_ExplicitWithRepetition_Values: matrix indexed by [int(1..3)] of int(1..2) +branching on + [a_MOccurrence, a_ExplicitWithRepetition_Flag, a_ExplicitWithRepetition_Values, b_ExplicitWithRepetition_Flag, + b_ExplicitWithRepetition_Values] +such that + or([sum([toInt(a_ExplicitWithRepetition_Values[q42] = a_ExplicitWithRepetition_Values[q21]) + | q42 : int(1..3), q42 <= 3]) + < + sum([toInt(b_ExplicitWithRepetition_Values[q44] = a_ExplicitWithRepetition_Values[q21]) + | q44 : int(1..3), q44 <= 3]) + /\ + (and([a_ExplicitWithRepetition_Values[q45] < a_ExplicitWithRepetition_Values[q21] -> + sum([toInt(a_ExplicitWithRepetition_Values[q54] = a_ExplicitWithRepetition_Values[q45]) + | q54 : int(1..3), q54 <= 3]) + = + sum([toInt(b_ExplicitWithRepetition_Values[q56] = a_ExplicitWithRepetition_Values[q45]) + | q56 : int(1..3), q56 <= 3]) + | q45 : int(1..3), q45 <= 3]) + /\ + and([!or([a_ExplicitWithRepetition_Values[q48] = b_ExplicitWithRepetition_Values[q46] + | q48 : int(1..3), q48 <= 3]) + /\ b_ExplicitWithRepetition_Values[q46] < a_ExplicitWithRepetition_Values[q21] + -> + sum([toInt(a_ExplicitWithRepetition_Values[q50] = b_ExplicitWithRepetition_Values[q46]) + | q50 : int(1..3), q50 <= 3]) + = + sum([toInt(b_ExplicitWithRepetition_Values[q52] = b_ExplicitWithRepetition_Values[q46]) + | q52 : int(1..3), q52 <= 3]) + | q46 : int(1..3), q46 <= 3])) + | q21 : int(1..3), q21 <= 3]) + \/ + or([!or([a_ExplicitWithRepetition_Values[q24] = b_ExplicitWithRepetition_Values[q22] | q24 : int(1..3), q24 <= 3]) + /\ + (sum([toInt(a_ExplicitWithRepetition_Values[q26] = b_ExplicitWithRepetition_Values[q22]) + | q26 : int(1..3), q26 <= 3]) + < + sum([toInt(b_ExplicitWithRepetition_Values[q28] = b_ExplicitWithRepetition_Values[q22]) + | q28 : int(1..3), q28 <= 3]) + /\ + (and([a_ExplicitWithRepetition_Values[q29] < b_ExplicitWithRepetition_Values[q22] -> + sum([toInt(a_ExplicitWithRepetition_Values[q38] = a_ExplicitWithRepetition_Values[q29]) + | q38 : int(1..3), q38 <= 3]) + = + sum([toInt(b_ExplicitWithRepetition_Values[q40] = a_ExplicitWithRepetition_Values[q29]) + | q40 : int(1..3), q40 <= 3]) + | q29 : int(1..3), q29 <= 3]) + /\ + and([!or([a_ExplicitWithRepetition_Values[q32] = b_ExplicitWithRepetition_Values[q30] + | q32 : int(1..3), q32 <= 3]) + /\ b_ExplicitWithRepetition_Values[q30] < b_ExplicitWithRepetition_Values[q22] + -> + sum([toInt(a_ExplicitWithRepetition_Values[q34] = b_ExplicitWithRepetition_Values[q30]) + | q34 : int(1..3), q34 <= 3]) + = + sum([toInt(b_ExplicitWithRepetition_Values[q36] = b_ExplicitWithRepetition_Values[q30]) + | q36 : int(1..3), q36 <= 3]) + | q30 : int(1..3), q30 <= 3]))) + | q22 : int(1..3), q22 <= 3]), + and([a_ExplicitWithRepetition_Values[q1] <= a_ExplicitWithRepetition_Values[q1 + 1] | q1 : int(1..2), q1 + 1 <= 3]), + and([b_ExplicitWithRepetition_Values[q6] <= b_ExplicitWithRepetition_Values[q6 + 1] | q6 : int(1..2), q6 + 1 <= 3]), + 3 = sum([a_MOccurrence[q11] | q11 : int(1..2)]), + and([a_MOccurrence[q13] > 0 -> + a_MOccurrence[q13] = sum([toInt(a_ExplicitWithRepetition_Values[q15] = q13) | q15 : int(1..3), q15 <= 3]) + | q13 : int(1..2)]), + and([a_MOccurrence[a_ExplicitWithRepetition_Values[q16]] = + sum([toInt(a_ExplicitWithRepetition_Values[q18] = a_ExplicitWithRepetition_Values[q16]) + | q18 : int(1..3), q18 <= 3]) + | q16 : int(1..3), q16 <= 3]) + diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_3_3-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_3_3-solution000001.solution new file mode 100644 index 0000000000..15472caf03 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_3_3-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 2, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_3_3-solution000002.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_3_3-solution000002.solution new file mode 100644 index 0000000000..ff56905e23 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_3_3-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_3_3-solution000003.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_3_3-solution000003.solution new file mode 100644 index 0000000000..d56a0bbcdc --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_3_3-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_3_3-solution000004.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_3_3-solution000004.solution new file mode 100644 index 0000000000..5e2caa751c --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_3_3-solution000004.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 2, 2) +letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_3_3-solution000005.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_3_3-solution000005.solution new file mode 100644 index 0000000000..1b4b5b08a6 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_3_3-solution000005.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 2, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_3_3-solution000006.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_3_3-solution000006.solution new file mode 100644 index 0000000000..621d5f6edc --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_3_3-solution000006.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 1, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_3_3.eprime b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_3_3.eprime new file mode 100644 index 0000000000..bc2ecdfcfe --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_2_3_3.eprime @@ -0,0 +1,84 @@ +language ESSENCE' 1.0 + +find a_ExplicitWithRepetition_Flag: int(3) +find a_ExplicitWithRepetition_Values: matrix indexed by [int(1..3)] of int(1..2) +find a_MOccurrence: matrix indexed by [int(1..2)] of int(0..3) +find b_ExplicitWithRepetition_Flag: int(3) +find b_ExplicitWithRepetition_Values: matrix indexed by [int(1..3)] of int(1..2) +find b_MOccurrence: matrix indexed by [int(1..2)] of int(0..3) +branching on + [a_MOccurrence, a_ExplicitWithRepetition_Flag, a_ExplicitWithRepetition_Values, b_MOccurrence, + b_ExplicitWithRepetition_Flag, b_ExplicitWithRepetition_Values] +such that + or([sum([toInt(a_ExplicitWithRepetition_Values[q50] = a_ExplicitWithRepetition_Values[q29]) + | q50 : int(1..3), q50 <= 3]) + < + sum([toInt(b_ExplicitWithRepetition_Values[q52] = a_ExplicitWithRepetition_Values[q29]) + | q52 : int(1..3), q52 <= 3]) + /\ + (and([a_ExplicitWithRepetition_Values[q53] < a_ExplicitWithRepetition_Values[q29] -> + sum([toInt(a_ExplicitWithRepetition_Values[q62] = a_ExplicitWithRepetition_Values[q53]) + | q62 : int(1..3), q62 <= 3]) + = + sum([toInt(b_ExplicitWithRepetition_Values[q64] = a_ExplicitWithRepetition_Values[q53]) + | q64 : int(1..3), q64 <= 3]) + | q53 : int(1..3), q53 <= 3]) + /\ + and([!or([a_ExplicitWithRepetition_Values[q56] = b_ExplicitWithRepetition_Values[q54] + | q56 : int(1..3), q56 <= 3]) + /\ b_ExplicitWithRepetition_Values[q54] < a_ExplicitWithRepetition_Values[q29] + -> + sum([toInt(a_ExplicitWithRepetition_Values[q58] = b_ExplicitWithRepetition_Values[q54]) + | q58 : int(1..3), q58 <= 3]) + = + sum([toInt(b_ExplicitWithRepetition_Values[q60] = b_ExplicitWithRepetition_Values[q54]) + | q60 : int(1..3), q60 <= 3]) + | q54 : int(1..3), q54 <= 3])) + | q29 : int(1..3), q29 <= 3]) + \/ + or([!or([a_ExplicitWithRepetition_Values[q32] = b_ExplicitWithRepetition_Values[q30] | q32 : int(1..3), q32 <= 3]) + /\ + (sum([toInt(a_ExplicitWithRepetition_Values[q34] = b_ExplicitWithRepetition_Values[q30]) + | q34 : int(1..3), q34 <= 3]) + < + sum([toInt(b_ExplicitWithRepetition_Values[q36] = b_ExplicitWithRepetition_Values[q30]) + | q36 : int(1..3), q36 <= 3]) + /\ + (and([a_ExplicitWithRepetition_Values[q37] < b_ExplicitWithRepetition_Values[q30] -> + sum([toInt(a_ExplicitWithRepetition_Values[q46] = a_ExplicitWithRepetition_Values[q37]) + | q46 : int(1..3), q46 <= 3]) + = + sum([toInt(b_ExplicitWithRepetition_Values[q48] = a_ExplicitWithRepetition_Values[q37]) + | q48 : int(1..3), q48 <= 3]) + | q37 : int(1..3), q37 <= 3]) + /\ + and([!or([a_ExplicitWithRepetition_Values[q40] = b_ExplicitWithRepetition_Values[q38] + | q40 : int(1..3), q40 <= 3]) + /\ b_ExplicitWithRepetition_Values[q38] < b_ExplicitWithRepetition_Values[q30] + -> + sum([toInt(a_ExplicitWithRepetition_Values[q42] = b_ExplicitWithRepetition_Values[q38]) + | q42 : int(1..3), q42 <= 3]) + = + sum([toInt(b_ExplicitWithRepetition_Values[q44] = b_ExplicitWithRepetition_Values[q38]) + | q44 : int(1..3), q44 <= 3]) + | q38 : int(1..3), q38 <= 3]))) + | q30 : int(1..3), q30 <= 3]), + and([a_ExplicitWithRepetition_Values[q1] <= a_ExplicitWithRepetition_Values[q1 + 1] | q1 : int(1..2), q1 + 1 <= 3]), + and([b_ExplicitWithRepetition_Values[q6] <= b_ExplicitWithRepetition_Values[q6 + 1] | q6 : int(1..2), q6 + 1 <= 3]), + 3 = sum([a_MOccurrence[q11] | q11 : int(1..2)]), + and([a_MOccurrence[q21] > 0 -> + a_MOccurrence[q21] = sum([toInt(a_ExplicitWithRepetition_Values[q23] = q21) | q23 : int(1..3), q23 <= 3]) + | q21 : int(1..2)]), + and([a_MOccurrence[a_ExplicitWithRepetition_Values[q24]] = + sum([toInt(a_ExplicitWithRepetition_Values[q26] = a_ExplicitWithRepetition_Values[q24]) + | q26 : int(1..3), q26 <= 3]) + | q24 : int(1..3), q24 <= 3]), + 3 = sum([b_MOccurrence[q12] | q12 : int(1..2)]), + and([b_MOccurrence[q14] > 0 -> + b_MOccurrence[q14] = sum([toInt(b_ExplicitWithRepetition_Values[q16] = q14) | q16 : int(1..3), q16 <= 3]) + | q14 : int(1..2)]), + and([b_MOccurrence[b_ExplicitWithRepetition_Values[q17]] = + sum([toInt(b_ExplicitWithRepetition_Values[q19] = b_ExplicitWithRepetition_Values[q17]) + | q19 : int(1..3), q19 <= 3]) + | q17 : int(1..3), q17 <= 3]) + diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_1_1-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_1_1-solution000001.solution new file mode 100644 index 0000000000..5e2caa751c --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_1_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 2, 2) +letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_1_1-solution000002.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_1_1-solution000002.solution new file mode 100644 index 0000000000..1b4b5b08a6 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_1_1-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 2, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_1_1-solution000003.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_1_1-solution000003.solution new file mode 100644 index 0000000000..621d5f6edc --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_1_1-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 1, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_1_1-solution000004.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_1_1-solution000004.solution new file mode 100644 index 0000000000..15472caf03 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_1_1-solution000004.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 2, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_1_1-solution000005.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_1_1-solution000005.solution new file mode 100644 index 0000000000..ff56905e23 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_1_1-solution000005.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_1_1-solution000006.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_1_1-solution000006.solution new file mode 100644 index 0000000000..d56a0bbcdc --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_1_1-solution000006.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_1_2-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_1_2-solution000001.solution new file mode 100644 index 0000000000..1b4b5b08a6 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_1_2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 2, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_1_2-solution000002.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_1_2-solution000002.solution new file mode 100644 index 0000000000..5e2caa751c --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_1_2-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 2, 2) +letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_1_2-solution000003.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_1_2-solution000003.solution new file mode 100644 index 0000000000..621d5f6edc --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_1_2-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 1, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_1_2-solution000004.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_1_2-solution000004.solution new file mode 100644 index 0000000000..d56a0bbcdc --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_1_2-solution000004.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_1_2-solution000005.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_1_2-solution000005.solution new file mode 100644 index 0000000000..ff56905e23 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_1_2-solution000005.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_1_2-solution000006.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_1_2-solution000006.solution new file mode 100644 index 0000000000..15472caf03 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_1_2-solution000006.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 2, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_1_3-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_1_3-solution000001.solution new file mode 100644 index 0000000000..5e2caa751c --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_1_3-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 2, 2) +letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_1_3-solution000002.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_1_3-solution000002.solution new file mode 100644 index 0000000000..1b4b5b08a6 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_1_3-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 2, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_1_3-solution000003.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_1_3-solution000003.solution new file mode 100644 index 0000000000..621d5f6edc --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_1_3-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 1, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_1_3-solution000004.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_1_3-solution000004.solution new file mode 100644 index 0000000000..15472caf03 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_1_3-solution000004.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 2, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_1_3-solution000005.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_1_3-solution000005.solution new file mode 100644 index 0000000000..ff56905e23 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_1_3-solution000005.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_1_3-solution000006.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_1_3-solution000006.solution new file mode 100644 index 0000000000..d56a0bbcdc --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_1_3-solution000006.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_2_1-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_2_1-solution000001.solution new file mode 100644 index 0000000000..621d5f6edc --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_2_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 1, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_2_1-solution000002.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_2_1-solution000002.solution new file mode 100644 index 0000000000..5e2caa751c --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_2_1-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 2, 2) +letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_2_1-solution000003.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_2_1-solution000003.solution new file mode 100644 index 0000000000..1b4b5b08a6 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_2_1-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 2, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_2_1-solution000004.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_2_1-solution000004.solution new file mode 100644 index 0000000000..15472caf03 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_2_1-solution000004.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 2, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_2_1-solution000005.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_2_1-solution000005.solution new file mode 100644 index 0000000000..ff56905e23 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_2_1-solution000005.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_2_1-solution000006.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_2_1-solution000006.solution new file mode 100644 index 0000000000..d56a0bbcdc --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_2_1-solution000006.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_2_2-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_2_2-solution000001.solution new file mode 100644 index 0000000000..621d5f6edc --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_2_2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 1, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_2_2-solution000002.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_2_2-solution000002.solution new file mode 100644 index 0000000000..1b4b5b08a6 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_2_2-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 2, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_2_2-solution000003.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_2_2-solution000003.solution new file mode 100644 index 0000000000..5e2caa751c --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_2_2-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 2, 2) +letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_2_2-solution000004.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_2_2-solution000004.solution new file mode 100644 index 0000000000..d56a0bbcdc --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_2_2-solution000004.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_2_2-solution000005.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_2_2-solution000005.solution new file mode 100644 index 0000000000..ff56905e23 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_2_2-solution000005.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_2_2-solution000006.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_2_2-solution000006.solution new file mode 100644 index 0000000000..15472caf03 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_2_2-solution000006.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 2, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_2_2.eprime b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_2_2.eprime new file mode 100644 index 0000000000..d9e532d5b0 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_2_2.eprime @@ -0,0 +1,53 @@ +language ESSENCE' 1.0 + +find a_ExplicitWithRepetition_Flag: int(3) +find a_ExplicitWithRepetition_Values: matrix indexed by [int(1..3)] of int(1..2) +find b_MOccurrence: matrix indexed by [int(1..2)] of int(0..3) +find b_ExplicitWithRepetition_Flag: int(3) +find b_ExplicitWithRepetition_Values: matrix indexed by [int(1..3)] of int(1..2) +branching on + [a_ExplicitWithRepetition_Flag, a_ExplicitWithRepetition_Values, b_ExplicitWithRepetition_Flag, + b_ExplicitWithRepetition_Values, b_MOccurrence] +such that + or([sum([toInt(a_ExplicitWithRepetition_Values[q28] = a_ExplicitWithRepetition_Values[q29]) + | q28 : int(1..3), q28 <= 3]) + < b_MOccurrence[a_ExplicitWithRepetition_Values[q29]] + /\ + (and([a_ExplicitWithRepetition_Values[q23] < a_ExplicitWithRepetition_Values[q29] -> + sum([toInt(a_ExplicitWithRepetition_Values[q22] = a_ExplicitWithRepetition_Values[q23]) + | q22 : int(1..3), q22 <= 3]) + = b_MOccurrence[a_ExplicitWithRepetition_Values[q23]] + | q23 : int(1..3), q23 <= 3]) + /\ + and([q26 < a_ExplicitWithRepetition_Values[q29] -> + (b_MOccurrence[q26] > 0 /\ !or([a_ExplicitWithRepetition_Values[q25] = q26 | q25 : int(1..3), q25 <= 3]) + -> + sum([toInt(a_ExplicitWithRepetition_Values[q22] = q26) | q22 : int(1..3), q22 <= 3]) = + b_MOccurrence[q26]) + | q26 : int(1..2)])) + | q29 : int(1..3), q29 <= 3]) + \/ + or([b_MOccurrence[q32] > 0 /\ !or([a_ExplicitWithRepetition_Values[q31] = q32 | q31 : int(1..3), q31 <= 3]) /\ + (sum([toInt(a_ExplicitWithRepetition_Values[q28] = q32) | q28 : int(1..3), q28 <= 3]) < b_MOccurrence[q32] /\ + (and([a_ExplicitWithRepetition_Values[q23] < q32 -> + sum([toInt(a_ExplicitWithRepetition_Values[q22] = a_ExplicitWithRepetition_Values[q23]) + | q22 : int(1..3), q22 <= 3]) + = b_MOccurrence[a_ExplicitWithRepetition_Values[q23]] + | q23 : int(1..3), q23 <= 3]) + /\ + and([b_MOccurrence[q26] > 0 /\ !or([a_ExplicitWithRepetition_Values[q25] = q26 | q25 : int(1..3), q25 <= 3]) + -> + sum([toInt(a_ExplicitWithRepetition_Values[q22] = q26) | q22 : int(1..3), q22 <= 3]) = b_MOccurrence[q26] + | q26 : int(1..2), q26 < q32]))) + | q32 : int(1..2)]), + and([a_ExplicitWithRepetition_Values[q1] <= a_ExplicitWithRepetition_Values[q1 + 1] | q1 : int(1..2), q1 + 1 <= 3]), + 3 = sum([b_MOccurrence[q6] | q6 : int(1..2)]), + and([b_ExplicitWithRepetition_Values[q7] <= b_ExplicitWithRepetition_Values[q7 + 1] | q7 : int(1..2), q7 + 1 <= 3]), + and([sum([toInt(b_ExplicitWithRepetition_Values[q15] = b_ExplicitWithRepetition_Values[q13]) + | q15 : int(1..3), q15 <= 3]) + = b_MOccurrence[b_ExplicitWithRepetition_Values[q13]] + | q13 : int(1..3), q13 <= 3]), + and([b_MOccurrence[q16] > 0 -> + sum([toInt(b_ExplicitWithRepetition_Values[q18] = q16) | q18 : int(1..3), q18 <= 3]) = b_MOccurrence[q16] + | q16 : int(1..2)]) + diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_2_3-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_2_3-solution000001.solution new file mode 100644 index 0000000000..621d5f6edc --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_2_3-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 1, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_2_3-solution000002.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_2_3-solution000002.solution new file mode 100644 index 0000000000..5e2caa751c --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_2_3-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 2, 2) +letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_2_3-solution000003.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_2_3-solution000003.solution new file mode 100644 index 0000000000..1b4b5b08a6 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_2_3-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 2, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_2_3-solution000004.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_2_3-solution000004.solution new file mode 100644 index 0000000000..15472caf03 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_2_3-solution000004.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 2, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_2_3-solution000005.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_2_3-solution000005.solution new file mode 100644 index 0000000000..ff56905e23 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_2_3-solution000005.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_2_3-solution000006.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_2_3-solution000006.solution new file mode 100644 index 0000000000..d56a0bbcdc --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_2_3-solution000006.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_2_3.eprime b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_2_3.eprime new file mode 100644 index 0000000000..3857dbf52e --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_2_3.eprime @@ -0,0 +1,41 @@ +language ESSENCE' 1.0 + +find a_ExplicitWithRepetition_Flag: int(3) +find a_ExplicitWithRepetition_Values: matrix indexed by [int(1..3)] of int(1..2) +find b_MOccurrence: matrix indexed by [int(1..2)] of int(0..3) +branching on [a_ExplicitWithRepetition_Flag, a_ExplicitWithRepetition_Values, b_MOccurrence] +such that + or([sum([toInt(a_ExplicitWithRepetition_Values[q16] = a_ExplicitWithRepetition_Values[q17]) + | q16 : int(1..3), q16 <= 3]) + < b_MOccurrence[a_ExplicitWithRepetition_Values[q17]] + /\ + (and([a_ExplicitWithRepetition_Values[q11] < a_ExplicitWithRepetition_Values[q17] -> + sum([toInt(a_ExplicitWithRepetition_Values[q10] = a_ExplicitWithRepetition_Values[q11]) + | q10 : int(1..3), q10 <= 3]) + = b_MOccurrence[a_ExplicitWithRepetition_Values[q11]] + | q11 : int(1..3), q11 <= 3]) + /\ + and([q14 < a_ExplicitWithRepetition_Values[q17] -> + (b_MOccurrence[q14] > 0 /\ !or([a_ExplicitWithRepetition_Values[q13] = q14 | q13 : int(1..3), q13 <= 3]) + -> + sum([toInt(a_ExplicitWithRepetition_Values[q10] = q14) | q10 : int(1..3), q10 <= 3]) = + b_MOccurrence[q14]) + | q14 : int(1..2)])) + | q17 : int(1..3), q17 <= 3]) + \/ + or([b_MOccurrence[q20] > 0 /\ !or([a_ExplicitWithRepetition_Values[q19] = q20 | q19 : int(1..3), q19 <= 3]) /\ + (sum([toInt(a_ExplicitWithRepetition_Values[q16] = q20) | q16 : int(1..3), q16 <= 3]) < b_MOccurrence[q20] /\ + (and([a_ExplicitWithRepetition_Values[q11] < q20 -> + sum([toInt(a_ExplicitWithRepetition_Values[q10] = a_ExplicitWithRepetition_Values[q11]) + | q10 : int(1..3), q10 <= 3]) + = b_MOccurrence[a_ExplicitWithRepetition_Values[q11]] + | q11 : int(1..3), q11 <= 3]) + /\ + and([b_MOccurrence[q14] > 0 /\ !or([a_ExplicitWithRepetition_Values[q13] = q14 | q13 : int(1..3), q13 <= 3]) + -> + sum([toInt(a_ExplicitWithRepetition_Values[q10] = q14) | q10 : int(1..3), q10 <= 3]) = b_MOccurrence[q14] + | q14 : int(1..2), q14 < q20]))) + | q20 : int(1..2)]), + and([a_ExplicitWithRepetition_Values[q1] <= a_ExplicitWithRepetition_Values[q1 + 1] | q1 : int(1..2), q1 + 1 <= 3]), + 3 = sum([b_MOccurrence[q6] | q6 : int(1..2)]) + diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_3_1-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_3_1-solution000001.solution new file mode 100644 index 0000000000..15472caf03 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_3_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 2, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_3_1-solution000002.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_3_1-solution000002.solution new file mode 100644 index 0000000000..ff56905e23 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_3_1-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_3_1-solution000003.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_3_1-solution000003.solution new file mode 100644 index 0000000000..d56a0bbcdc --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_3_1-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_3_1-solution000004.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_3_1-solution000004.solution new file mode 100644 index 0000000000..5e2caa751c --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_3_1-solution000004.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 2, 2) +letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_3_1-solution000005.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_3_1-solution000005.solution new file mode 100644 index 0000000000..1b4b5b08a6 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_3_1-solution000005.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 2, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_3_1-solution000006.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_3_1-solution000006.solution new file mode 100644 index 0000000000..621d5f6edc --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_3_1-solution000006.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 1, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_3_2-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_3_2-solution000001.solution new file mode 100644 index 0000000000..d56a0bbcdc --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_3_2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_3_2-solution000002.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_3_2-solution000002.solution new file mode 100644 index 0000000000..ff56905e23 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_3_2-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_3_2-solution000003.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_3_2-solution000003.solution new file mode 100644 index 0000000000..15472caf03 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_3_2-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 2, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_3_2-solution000004.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_3_2-solution000004.solution new file mode 100644 index 0000000000..1b4b5b08a6 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_3_2-solution000004.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 2, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_3_2-solution000005.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_3_2-solution000005.solution new file mode 100644 index 0000000000..5e2caa751c --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_3_2-solution000005.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 2, 2) +letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_3_2-solution000006.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_3_2-solution000006.solution new file mode 100644 index 0000000000..621d5f6edc --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_3_2-solution000006.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 1, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_3_2.eprime b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_3_2.eprime new file mode 100644 index 0000000000..f5bfe69d73 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_3_2.eprime @@ -0,0 +1,62 @@ +language ESSENCE' 1.0 + +find a_ExplicitWithRepetition_Flag: int(3) +find a_ExplicitWithRepetition_Values: matrix indexed by [int(1..3)] of int(1..2) +find a_MOccurrence: matrix indexed by [int(1..2)] of int(0..3) +find b_MOccurrence: matrix indexed by [int(1..2)] of int(0..3) +find b_ExplicitWithRepetition_Flag: int(3) +find b_ExplicitWithRepetition_Values: matrix indexed by [int(1..3)] of int(1..2) +branching on + [a_MOccurrence, a_ExplicitWithRepetition_Flag, a_ExplicitWithRepetition_Values, b_ExplicitWithRepetition_Flag, + b_ExplicitWithRepetition_Values, b_MOccurrence] +such that + or([sum([toInt(a_ExplicitWithRepetition_Values[q36] = a_ExplicitWithRepetition_Values[q37]) + | q36 : int(1..3), q36 <= 3]) + < b_MOccurrence[a_ExplicitWithRepetition_Values[q37]] + /\ + (and([a_ExplicitWithRepetition_Values[q31] < a_ExplicitWithRepetition_Values[q37] -> + sum([toInt(a_ExplicitWithRepetition_Values[q30] = a_ExplicitWithRepetition_Values[q31]) + | q30 : int(1..3), q30 <= 3]) + = b_MOccurrence[a_ExplicitWithRepetition_Values[q31]] + | q31 : int(1..3), q31 <= 3]) + /\ + and([q34 < a_ExplicitWithRepetition_Values[q37] -> + (b_MOccurrence[q34] > 0 /\ !or([a_ExplicitWithRepetition_Values[q33] = q34 | q33 : int(1..3), q33 <= 3]) + -> + sum([toInt(a_ExplicitWithRepetition_Values[q30] = q34) | q30 : int(1..3), q30 <= 3]) = + b_MOccurrence[q34]) + | q34 : int(1..2)])) + | q37 : int(1..3), q37 <= 3]) + \/ + or([b_MOccurrence[q40] > 0 /\ !or([a_ExplicitWithRepetition_Values[q39] = q40 | q39 : int(1..3), q39 <= 3]) /\ + (sum([toInt(a_ExplicitWithRepetition_Values[q36] = q40) | q36 : int(1..3), q36 <= 3]) < b_MOccurrence[q40] /\ + (and([a_ExplicitWithRepetition_Values[q31] < q40 -> + sum([toInt(a_ExplicitWithRepetition_Values[q30] = a_ExplicitWithRepetition_Values[q31]) + | q30 : int(1..3), q30 <= 3]) + = b_MOccurrence[a_ExplicitWithRepetition_Values[q31]] + | q31 : int(1..3), q31 <= 3]) + /\ + and([b_MOccurrence[q34] > 0 /\ !or([a_ExplicitWithRepetition_Values[q33] = q34 | q33 : int(1..3), q33 <= 3]) + -> + sum([toInt(a_ExplicitWithRepetition_Values[q30] = q34) | q30 : int(1..3), q30 <= 3]) = b_MOccurrence[q34] + | q34 : int(1..2), q34 < q40]))) + | q40 : int(1..2)]), + and([a_ExplicitWithRepetition_Values[q1] <= a_ExplicitWithRepetition_Values[q1 + 1] | q1 : int(1..2), q1 + 1 <= 3]), + 3 = sum([b_MOccurrence[q6] | q6 : int(1..2)]), + 3 = sum([a_MOccurrence[q7] | q7 : int(1..2)]), + and([a_MOccurrence[q21] > 0 -> + a_MOccurrence[q21] = sum([toInt(a_ExplicitWithRepetition_Values[q23] = q21) | q23 : int(1..3), q23 <= 3]) + | q21 : int(1..2)]), + and([a_MOccurrence[a_ExplicitWithRepetition_Values[q24]] = + sum([toInt(a_ExplicitWithRepetition_Values[q26] = a_ExplicitWithRepetition_Values[q24]) + | q26 : int(1..3), q26 <= 3]) + | q24 : int(1..3), q24 <= 3]), + and([b_ExplicitWithRepetition_Values[q8] <= b_ExplicitWithRepetition_Values[q8 + 1] | q8 : int(1..2), q8 + 1 <= 3]), + and([sum([toInt(b_ExplicitWithRepetition_Values[q16] = b_ExplicitWithRepetition_Values[q14]) + | q16 : int(1..3), q16 <= 3]) + = b_MOccurrence[b_ExplicitWithRepetition_Values[q14]] + | q14 : int(1..3), q14 <= 3]), + and([b_MOccurrence[q17] > 0 -> + sum([toInt(b_ExplicitWithRepetition_Values[q19] = q17) | q19 : int(1..3), q19 <= 3]) = b_MOccurrence[q17] + | q17 : int(1..2)]) + diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_3_3-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_3_3-solution000001.solution new file mode 100644 index 0000000000..15472caf03 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_3_3-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 2, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_3_3-solution000002.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_3_3-solution000002.solution new file mode 100644 index 0000000000..ff56905e23 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_3_3-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_3_3-solution000003.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_3_3-solution000003.solution new file mode 100644 index 0000000000..d56a0bbcdc --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_3_3-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_3_3-solution000004.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_3_3-solution000004.solution new file mode 100644 index 0000000000..5e2caa751c --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_3_3-solution000004.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 2, 2) +letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_3_3-solution000005.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_3_3-solution000005.solution new file mode 100644 index 0000000000..1b4b5b08a6 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_3_3-solution000005.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 2, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_3_3-solution000006.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_3_3-solution000006.solution new file mode 100644 index 0000000000..621d5f6edc --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_3_3-solution000006.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 1, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_3_3.eprime b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_3_3.eprime new file mode 100644 index 0000000000..f51cd8c9ab --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_2_3_3_3.eprime @@ -0,0 +1,50 @@ +language ESSENCE' 1.0 + +find a_ExplicitWithRepetition_Flag: int(3) +find a_ExplicitWithRepetition_Values: matrix indexed by [int(1..3)] of int(1..2) +find a_MOccurrence: matrix indexed by [int(1..2)] of int(0..3) +find b_MOccurrence: matrix indexed by [int(1..2)] of int(0..3) +branching on [a_MOccurrence, a_ExplicitWithRepetition_Flag, a_ExplicitWithRepetition_Values, b_MOccurrence] +such that + or([sum([toInt(a_ExplicitWithRepetition_Values[q24] = a_ExplicitWithRepetition_Values[q25]) + | q24 : int(1..3), q24 <= 3]) + < b_MOccurrence[a_ExplicitWithRepetition_Values[q25]] + /\ + (and([a_ExplicitWithRepetition_Values[q19] < a_ExplicitWithRepetition_Values[q25] -> + sum([toInt(a_ExplicitWithRepetition_Values[q18] = a_ExplicitWithRepetition_Values[q19]) + | q18 : int(1..3), q18 <= 3]) + = b_MOccurrence[a_ExplicitWithRepetition_Values[q19]] + | q19 : int(1..3), q19 <= 3]) + /\ + and([q22 < a_ExplicitWithRepetition_Values[q25] -> + (b_MOccurrence[q22] > 0 /\ !or([a_ExplicitWithRepetition_Values[q21] = q22 | q21 : int(1..3), q21 <= 3]) + -> + sum([toInt(a_ExplicitWithRepetition_Values[q18] = q22) | q18 : int(1..3), q18 <= 3]) = + b_MOccurrence[q22]) + | q22 : int(1..2)])) + | q25 : int(1..3), q25 <= 3]) + \/ + or([b_MOccurrence[q28] > 0 /\ !or([a_ExplicitWithRepetition_Values[q27] = q28 | q27 : int(1..3), q27 <= 3]) /\ + (sum([toInt(a_ExplicitWithRepetition_Values[q24] = q28) | q24 : int(1..3), q24 <= 3]) < b_MOccurrence[q28] /\ + (and([a_ExplicitWithRepetition_Values[q19] < q28 -> + sum([toInt(a_ExplicitWithRepetition_Values[q18] = a_ExplicitWithRepetition_Values[q19]) + | q18 : int(1..3), q18 <= 3]) + = b_MOccurrence[a_ExplicitWithRepetition_Values[q19]] + | q19 : int(1..3), q19 <= 3]) + /\ + and([b_MOccurrence[q22] > 0 /\ !or([a_ExplicitWithRepetition_Values[q21] = q22 | q21 : int(1..3), q21 <= 3]) + -> + sum([toInt(a_ExplicitWithRepetition_Values[q18] = q22) | q18 : int(1..3), q18 <= 3]) = b_MOccurrence[q22] + | q22 : int(1..2), q22 < q28]))) + | q28 : int(1..2)]), + and([a_ExplicitWithRepetition_Values[q1] <= a_ExplicitWithRepetition_Values[q1 + 1] | q1 : int(1..2), q1 + 1 <= 3]), + 3 = sum([b_MOccurrence[q6] | q6 : int(1..2)]), + 3 = sum([a_MOccurrence[q7] | q7 : int(1..2)]), + and([a_MOccurrence[q9] > 0 -> + a_MOccurrence[q9] = sum([toInt(a_ExplicitWithRepetition_Values[q11] = q9) | q11 : int(1..3), q11 <= 3]) + | q9 : int(1..2)]), + and([a_MOccurrence[a_ExplicitWithRepetition_Values[q12]] = + sum([toInt(a_ExplicitWithRepetition_Values[q14] = a_ExplicitWithRepetition_Values[q12]) + | q14 : int(1..3), q14 <= 3]) + | q12 : int(1..3), q12 <= 3]) + diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_1_1-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_1_1-solution000001.solution new file mode 100644 index 0000000000..5e2caa751c --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_1_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 2, 2) +letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_1_1-solution000002.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_1_1-solution000002.solution new file mode 100644 index 0000000000..1b4b5b08a6 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_1_1-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 2, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_1_1-solution000003.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_1_1-solution000003.solution new file mode 100644 index 0000000000..621d5f6edc --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_1_1-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 1, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_1_1-solution000004.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_1_1-solution000004.solution new file mode 100644 index 0000000000..15472caf03 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_1_1-solution000004.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 2, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_1_1-solution000005.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_1_1-solution000005.solution new file mode 100644 index 0000000000..ff56905e23 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_1_1-solution000005.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_1_1-solution000006.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_1_1-solution000006.solution new file mode 100644 index 0000000000..d56a0bbcdc --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_1_1-solution000006.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_1_2-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_1_2-solution000001.solution new file mode 100644 index 0000000000..1b4b5b08a6 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_1_2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 2, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_1_2-solution000002.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_1_2-solution000002.solution new file mode 100644 index 0000000000..5e2caa751c --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_1_2-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 2, 2) +letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_1_2-solution000003.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_1_2-solution000003.solution new file mode 100644 index 0000000000..621d5f6edc --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_1_2-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 1, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_1_2-solution000004.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_1_2-solution000004.solution new file mode 100644 index 0000000000..d56a0bbcdc --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_1_2-solution000004.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_1_2-solution000005.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_1_2-solution000005.solution new file mode 100644 index 0000000000..ff56905e23 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_1_2-solution000005.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_1_2-solution000006.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_1_2-solution000006.solution new file mode 100644 index 0000000000..15472caf03 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_1_2-solution000006.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 2, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_1_3-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_1_3-solution000001.solution new file mode 100644 index 0000000000..5e2caa751c --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_1_3-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 2, 2) +letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_1_3-solution000002.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_1_3-solution000002.solution new file mode 100644 index 0000000000..1b4b5b08a6 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_1_3-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 2, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_1_3-solution000003.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_1_3-solution000003.solution new file mode 100644 index 0000000000..621d5f6edc --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_1_3-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 1, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_1_3-solution000004.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_1_3-solution000004.solution new file mode 100644 index 0000000000..15472caf03 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_1_3-solution000004.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 2, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_1_3-solution000005.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_1_3-solution000005.solution new file mode 100644 index 0000000000..ff56905e23 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_1_3-solution000005.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_1_3-solution000006.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_1_3-solution000006.solution new file mode 100644 index 0000000000..d56a0bbcdc --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_1_3-solution000006.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_2_1-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_2_1-solution000001.solution new file mode 100644 index 0000000000..621d5f6edc --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_2_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 1, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_2_1-solution000002.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_2_1-solution000002.solution new file mode 100644 index 0000000000..5e2caa751c --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_2_1-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 2, 2) +letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_2_1-solution000003.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_2_1-solution000003.solution new file mode 100644 index 0000000000..1b4b5b08a6 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_2_1-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 2, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_2_1-solution000004.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_2_1-solution000004.solution new file mode 100644 index 0000000000..15472caf03 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_2_1-solution000004.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 2, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_2_1-solution000005.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_2_1-solution000005.solution new file mode 100644 index 0000000000..ff56905e23 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_2_1-solution000005.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_2_1-solution000006.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_2_1-solution000006.solution new file mode 100644 index 0000000000..d56a0bbcdc --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_2_1-solution000006.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_2_2-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_2_2-solution000001.solution new file mode 100644 index 0000000000..621d5f6edc --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_2_2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 1, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_2_2-solution000002.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_2_2-solution000002.solution new file mode 100644 index 0000000000..1b4b5b08a6 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_2_2-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 2, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_2_2-solution000003.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_2_2-solution000003.solution new file mode 100644 index 0000000000..5e2caa751c --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_2_2-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 2, 2) +letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_2_2-solution000004.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_2_2-solution000004.solution new file mode 100644 index 0000000000..d56a0bbcdc --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_2_2-solution000004.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_2_2-solution000005.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_2_2-solution000005.solution new file mode 100644 index 0000000000..ff56905e23 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_2_2-solution000005.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_2_2-solution000006.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_2_2-solution000006.solution new file mode 100644 index 0000000000..15472caf03 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_2_2-solution000006.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 2, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_2_3-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_2_3-solution000001.solution new file mode 100644 index 0000000000..621d5f6edc --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_2_3-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 1, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_2_3-solution000002.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_2_3-solution000002.solution new file mode 100644 index 0000000000..5e2caa751c --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_2_3-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 2, 2) +letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_2_3-solution000003.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_2_3-solution000003.solution new file mode 100644 index 0000000000..1b4b5b08a6 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_2_3-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 2, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_2_3-solution000004.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_2_3-solution000004.solution new file mode 100644 index 0000000000..15472caf03 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_2_3-solution000004.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 2, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_2_3-solution000005.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_2_3-solution000005.solution new file mode 100644 index 0000000000..ff56905e23 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_2_3-solution000005.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_2_3-solution000006.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_2_3-solution000006.solution new file mode 100644 index 0000000000..d56a0bbcdc --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_2_3-solution000006.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_3_1-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_3_1-solution000001.solution new file mode 100644 index 0000000000..15472caf03 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_3_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 2, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_3_1-solution000002.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_3_1-solution000002.solution new file mode 100644 index 0000000000..ff56905e23 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_3_1-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_3_1-solution000003.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_3_1-solution000003.solution new file mode 100644 index 0000000000..d56a0bbcdc --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_3_1-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_3_1-solution000004.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_3_1-solution000004.solution new file mode 100644 index 0000000000..5e2caa751c --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_3_1-solution000004.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 2, 2) +letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_3_1-solution000005.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_3_1-solution000005.solution new file mode 100644 index 0000000000..1b4b5b08a6 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_3_1-solution000005.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 2, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_3_1-solution000006.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_3_1-solution000006.solution new file mode 100644 index 0000000000..621d5f6edc --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_3_1-solution000006.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 1, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_3_2-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_3_2-solution000001.solution new file mode 100644 index 0000000000..d56a0bbcdc --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_3_2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_3_2-solution000002.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_3_2-solution000002.solution new file mode 100644 index 0000000000..ff56905e23 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_3_2-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_3_2-solution000003.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_3_2-solution000003.solution new file mode 100644 index 0000000000..15472caf03 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_3_2-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 2, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_3_2-solution000004.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_3_2-solution000004.solution new file mode 100644 index 0000000000..1b4b5b08a6 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_3_2-solution000004.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 2, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_3_2-solution000005.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_3_2-solution000005.solution new file mode 100644 index 0000000000..5e2caa751c --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_3_2-solution000005.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 2, 2) +letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_3_2-solution000006.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_3_2-solution000006.solution new file mode 100644 index 0000000000..621d5f6edc --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_3_2-solution000006.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 1, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_3_3-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_3_3-solution000001.solution new file mode 100644 index 0000000000..15472caf03 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_3_3-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 2, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_3_3-solution000002.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_3_3-solution000002.solution new file mode 100644 index 0000000000..ff56905e23 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_3_3-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_3_3-solution000003.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_3_3-solution000003.solution new file mode 100644 index 0000000000..d56a0bbcdc --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_3_3-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_3_3-solution000004.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_3_3-solution000004.solution new file mode 100644 index 0000000000..5e2caa751c --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_3_3-solution000004.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 2, 2) +letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_3_3-solution000005.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_3_3-solution000005.solution new file mode 100644 index 0000000000..1b4b5b08a6 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_3_3-solution000005.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 2, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_3_3-solution000006.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_3_3-solution000006.solution new file mode 100644 index 0000000000..621d5f6edc --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_1_3_3-solution000006.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 1, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_1_1-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_1_1-solution000001.solution new file mode 100644 index 0000000000..5e2caa751c --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_1_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 2, 2) +letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_1_1-solution000002.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_1_1-solution000002.solution new file mode 100644 index 0000000000..1b4b5b08a6 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_1_1-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 2, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_1_1-solution000003.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_1_1-solution000003.solution new file mode 100644 index 0000000000..621d5f6edc --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_1_1-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 1, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_1_1-solution000004.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_1_1-solution000004.solution new file mode 100644 index 0000000000..15472caf03 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_1_1-solution000004.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 2, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_1_1-solution000005.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_1_1-solution000005.solution new file mode 100644 index 0000000000..ff56905e23 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_1_1-solution000005.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_1_1-solution000006.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_1_1-solution000006.solution new file mode 100644 index 0000000000..d56a0bbcdc --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_1_1-solution000006.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_1_2-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_1_2-solution000001.solution new file mode 100644 index 0000000000..1b4b5b08a6 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_1_2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 2, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_1_2-solution000002.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_1_2-solution000002.solution new file mode 100644 index 0000000000..5e2caa751c --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_1_2-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 2, 2) +letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_1_2-solution000003.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_1_2-solution000003.solution new file mode 100644 index 0000000000..621d5f6edc --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_1_2-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 1, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_1_2-solution000004.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_1_2-solution000004.solution new file mode 100644 index 0000000000..d56a0bbcdc --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_1_2-solution000004.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_1_2-solution000005.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_1_2-solution000005.solution new file mode 100644 index 0000000000..ff56905e23 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_1_2-solution000005.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_1_2-solution000006.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_1_2-solution000006.solution new file mode 100644 index 0000000000..15472caf03 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_1_2-solution000006.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 2, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_1_3-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_1_3-solution000001.solution new file mode 100644 index 0000000000..5e2caa751c --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_1_3-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 2, 2) +letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_1_3-solution000002.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_1_3-solution000002.solution new file mode 100644 index 0000000000..1b4b5b08a6 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_1_3-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 2, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_1_3-solution000003.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_1_3-solution000003.solution new file mode 100644 index 0000000000..621d5f6edc --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_1_3-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 1, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_1_3-solution000004.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_1_3-solution000004.solution new file mode 100644 index 0000000000..15472caf03 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_1_3-solution000004.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 2, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_1_3-solution000005.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_1_3-solution000005.solution new file mode 100644 index 0000000000..ff56905e23 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_1_3-solution000005.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_1_3-solution000006.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_1_3-solution000006.solution new file mode 100644 index 0000000000..d56a0bbcdc --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_1_3-solution000006.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_2_1-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_2_1-solution000001.solution new file mode 100644 index 0000000000..621d5f6edc --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_2_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 1, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_2_1-solution000002.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_2_1-solution000002.solution new file mode 100644 index 0000000000..5e2caa751c --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_2_1-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 2, 2) +letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_2_1-solution000003.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_2_1-solution000003.solution new file mode 100644 index 0000000000..1b4b5b08a6 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_2_1-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 2, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_2_1-solution000004.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_2_1-solution000004.solution new file mode 100644 index 0000000000..15472caf03 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_2_1-solution000004.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 2, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_2_1-solution000005.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_2_1-solution000005.solution new file mode 100644 index 0000000000..ff56905e23 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_2_1-solution000005.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_2_1-solution000006.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_2_1-solution000006.solution new file mode 100644 index 0000000000..d56a0bbcdc --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_2_1-solution000006.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_2_2-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_2_2-solution000001.solution new file mode 100644 index 0000000000..621d5f6edc --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_2_2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 1, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_2_2-solution000002.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_2_2-solution000002.solution new file mode 100644 index 0000000000..1b4b5b08a6 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_2_2-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 2, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_2_2-solution000003.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_2_2-solution000003.solution new file mode 100644 index 0000000000..5e2caa751c --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_2_2-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 2, 2) +letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_2_2-solution000004.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_2_2-solution000004.solution new file mode 100644 index 0000000000..d56a0bbcdc --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_2_2-solution000004.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_2_2-solution000005.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_2_2-solution000005.solution new file mode 100644 index 0000000000..ff56905e23 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_2_2-solution000005.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_2_2-solution000006.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_2_2-solution000006.solution new file mode 100644 index 0000000000..15472caf03 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_2_2-solution000006.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 2, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_2_2.eprime b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_2_2.eprime new file mode 100644 index 0000000000..559348a46a --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_2_2.eprime @@ -0,0 +1,56 @@ +language ESSENCE' 1.0 + +find a_MOccurrence: matrix indexed by [int(1..2)] of int(0..3) +find a_ExplicitWithRepetition_Flag: int(3) +find a_ExplicitWithRepetition_Values: matrix indexed by [int(1..3)] of int(1..2) +find b_ExplicitWithRepetition_Flag: int(3) +find b_ExplicitWithRepetition_Values: matrix indexed by [int(1..3)] of int(1..2) +branching on + [a_ExplicitWithRepetition_Flag, a_ExplicitWithRepetition_Values, a_MOccurrence, b_ExplicitWithRepetition_Flag, + b_ExplicitWithRepetition_Values] +such that + or([a_MOccurrence[q32] > 0 /\ + (a_MOccurrence[q32] < sum([toInt(b_ExplicitWithRepetition_Values[q22] = q32) | q22 : int(1..3), q22 <= 3]) /\ + (and([a_MOccurrence[q28] > 0 -> + a_MOccurrence[q28] = sum([toInt(b_ExplicitWithRepetition_Values[q24] = q28) | q24 : int(1..3), q24 <= 3]) + | q28 : int(1..2), q28 < q32]) + /\ + and([!or([a_MOccurrence[q27] > 0 /\ q27 = b_ExplicitWithRepetition_Values[q25] | q27 : int(1..2)]) /\ + b_ExplicitWithRepetition_Values[q25] < q32 + -> + a_MOccurrence[b_ExplicitWithRepetition_Values[q25]] = + sum([toInt(b_ExplicitWithRepetition_Values[q24] = b_ExplicitWithRepetition_Values[q25]) + | q24 : int(1..3), q24 <= 3]) + | q25 : int(1..3), q25 <= 3]))) + | q32 : int(1..2)]) + \/ + or([!or([a_MOccurrence[q31] > 0 /\ q31 = b_ExplicitWithRepetition_Values[q29] | q31 : int(1..2)]) /\ + (a_MOccurrence[b_ExplicitWithRepetition_Values[q29]] < + sum([toInt(b_ExplicitWithRepetition_Values[q22] = b_ExplicitWithRepetition_Values[q29]) + | q22 : int(1..3), q22 <= 3]) + /\ + (and([q28 < b_ExplicitWithRepetition_Values[q29] -> + (a_MOccurrence[q28] > 0 -> + a_MOccurrence[q28] = + sum([toInt(b_ExplicitWithRepetition_Values[q24] = q28) | q24 : int(1..3), q24 <= 3])) + | q28 : int(1..2)]) + /\ + and([!or([a_MOccurrence[q27] > 0 /\ q27 = b_ExplicitWithRepetition_Values[q25] | q27 : int(1..2)]) /\ + b_ExplicitWithRepetition_Values[q25] < b_ExplicitWithRepetition_Values[q29] + -> + a_MOccurrence[b_ExplicitWithRepetition_Values[q25]] = + sum([toInt(b_ExplicitWithRepetition_Values[q24] = b_ExplicitWithRepetition_Values[q25]) + | q24 : int(1..3), q24 <= 3]) + | q25 : int(1..3), q25 <= 3]))) + | q29 : int(1..3), q29 <= 3]), + 3 = sum([a_MOccurrence[q1] | q1 : int(1..2)]), + and([b_ExplicitWithRepetition_Values[q2] <= b_ExplicitWithRepetition_Values[q2 + 1] | q2 : int(1..2), q2 + 1 <= 3]), + and([a_ExplicitWithRepetition_Values[q7] <= a_ExplicitWithRepetition_Values[q7 + 1] | q7 : int(1..2), q7 + 1 <= 3]), + and([sum([toInt(a_ExplicitWithRepetition_Values[q15] = a_ExplicitWithRepetition_Values[q13]) + | q15 : int(1..3), q15 <= 3]) + = a_MOccurrence[a_ExplicitWithRepetition_Values[q13]] + | q13 : int(1..3), q13 <= 3]), + and([a_MOccurrence[q16] > 0 -> + sum([toInt(a_ExplicitWithRepetition_Values[q18] = q16) | q18 : int(1..3), q18 <= 3]) = a_MOccurrence[q16] + | q16 : int(1..2)]) + diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_2_3-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_2_3-solution000001.solution new file mode 100644 index 0000000000..621d5f6edc --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_2_3-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 1, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_2_3-solution000002.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_2_3-solution000002.solution new file mode 100644 index 0000000000..5e2caa751c --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_2_3-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 2, 2) +letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_2_3-solution000003.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_2_3-solution000003.solution new file mode 100644 index 0000000000..1b4b5b08a6 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_2_3-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 2, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_2_3-solution000004.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_2_3-solution000004.solution new file mode 100644 index 0000000000..15472caf03 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_2_3-solution000004.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 2, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_2_3-solution000005.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_2_3-solution000005.solution new file mode 100644 index 0000000000..ff56905e23 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_2_3-solution000005.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_2_3-solution000006.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_2_3-solution000006.solution new file mode 100644 index 0000000000..d56a0bbcdc --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_2_3-solution000006.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_2_3.eprime b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_2_3.eprime new file mode 100644 index 0000000000..86fe846f2a --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_2_3.eprime @@ -0,0 +1,65 @@ +language ESSENCE' 1.0 + +find a_MOccurrence: matrix indexed by [int(1..2)] of int(0..3) +find a_ExplicitWithRepetition_Flag: int(3) +find a_ExplicitWithRepetition_Values: matrix indexed by [int(1..3)] of int(1..2) +find b_ExplicitWithRepetition_Flag: int(3) +find b_ExplicitWithRepetition_Values: matrix indexed by [int(1..3)] of int(1..2) +find b_MOccurrence: matrix indexed by [int(1..2)] of int(0..3) +branching on + [a_ExplicitWithRepetition_Flag, a_ExplicitWithRepetition_Values, a_MOccurrence, b_MOccurrence, + b_ExplicitWithRepetition_Flag, b_ExplicitWithRepetition_Values] +such that + or([a_MOccurrence[q40] > 0 /\ + (a_MOccurrence[q40] < sum([toInt(b_ExplicitWithRepetition_Values[q30] = q40) | q30 : int(1..3), q30 <= 3]) /\ + (and([a_MOccurrence[q36] > 0 -> + a_MOccurrence[q36] = sum([toInt(b_ExplicitWithRepetition_Values[q32] = q36) | q32 : int(1..3), q32 <= 3]) + | q36 : int(1..2), q36 < q40]) + /\ + and([!or([a_MOccurrence[q35] > 0 /\ q35 = b_ExplicitWithRepetition_Values[q33] | q35 : int(1..2)]) /\ + b_ExplicitWithRepetition_Values[q33] < q40 + -> + a_MOccurrence[b_ExplicitWithRepetition_Values[q33]] = + sum([toInt(b_ExplicitWithRepetition_Values[q32] = b_ExplicitWithRepetition_Values[q33]) + | q32 : int(1..3), q32 <= 3]) + | q33 : int(1..3), q33 <= 3]))) + | q40 : int(1..2)]) + \/ + or([!or([a_MOccurrence[q39] > 0 /\ q39 = b_ExplicitWithRepetition_Values[q37] | q39 : int(1..2)]) /\ + (a_MOccurrence[b_ExplicitWithRepetition_Values[q37]] < + sum([toInt(b_ExplicitWithRepetition_Values[q30] = b_ExplicitWithRepetition_Values[q37]) + | q30 : int(1..3), q30 <= 3]) + /\ + (and([q36 < b_ExplicitWithRepetition_Values[q37] -> + (a_MOccurrence[q36] > 0 -> + a_MOccurrence[q36] = + sum([toInt(b_ExplicitWithRepetition_Values[q32] = q36) | q32 : int(1..3), q32 <= 3])) + | q36 : int(1..2)]) + /\ + and([!or([a_MOccurrence[q35] > 0 /\ q35 = b_ExplicitWithRepetition_Values[q33] | q35 : int(1..2)]) /\ + b_ExplicitWithRepetition_Values[q33] < b_ExplicitWithRepetition_Values[q37] + -> + a_MOccurrence[b_ExplicitWithRepetition_Values[q33]] = + sum([toInt(b_ExplicitWithRepetition_Values[q32] = b_ExplicitWithRepetition_Values[q33]) + | q32 : int(1..3), q32 <= 3]) + | q33 : int(1..3), q33 <= 3]))) + | q37 : int(1..3), q37 <= 3]), + 3 = sum([a_MOccurrence[q1] | q1 : int(1..2)]), + and([b_ExplicitWithRepetition_Values[q2] <= b_ExplicitWithRepetition_Values[q2 + 1] | q2 : int(1..2), q2 + 1 <= 3]), + and([a_ExplicitWithRepetition_Values[q7] <= a_ExplicitWithRepetition_Values[q7 + 1] | q7 : int(1..2), q7 + 1 <= 3]), + and([sum([toInt(a_ExplicitWithRepetition_Values[q15] = a_ExplicitWithRepetition_Values[q13]) + | q15 : int(1..3), q15 <= 3]) + = a_MOccurrence[a_ExplicitWithRepetition_Values[q13]] + | q13 : int(1..3), q13 <= 3]), + and([a_MOccurrence[q16] > 0 -> + sum([toInt(a_ExplicitWithRepetition_Values[q18] = q16) | q18 : int(1..3), q18 <= 3]) = a_MOccurrence[q16] + | q16 : int(1..2)]), + 3 = sum([b_MOccurrence[q19] | q19 : int(1..2)]), + and([b_MOccurrence[q21] > 0 -> + b_MOccurrence[q21] = sum([toInt(b_ExplicitWithRepetition_Values[q23] = q21) | q23 : int(1..3), q23 <= 3]) + | q21 : int(1..2)]), + and([b_MOccurrence[b_ExplicitWithRepetition_Values[q24]] = + sum([toInt(b_ExplicitWithRepetition_Values[q26] = b_ExplicitWithRepetition_Values[q24]) + | q26 : int(1..3), q26 <= 3]) + | q24 : int(1..3), q24 <= 3]) + diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_3_1-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_3_1-solution000001.solution new file mode 100644 index 0000000000..15472caf03 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_3_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 2, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_3_1-solution000002.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_3_1-solution000002.solution new file mode 100644 index 0000000000..ff56905e23 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_3_1-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_3_1-solution000003.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_3_1-solution000003.solution new file mode 100644 index 0000000000..d56a0bbcdc --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_3_1-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_3_1-solution000004.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_3_1-solution000004.solution new file mode 100644 index 0000000000..5e2caa751c --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_3_1-solution000004.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 2, 2) +letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_3_1-solution000005.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_3_1-solution000005.solution new file mode 100644 index 0000000000..1b4b5b08a6 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_3_1-solution000005.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 2, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_3_1-solution000006.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_3_1-solution000006.solution new file mode 100644 index 0000000000..621d5f6edc --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_3_1-solution000006.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 1, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_3_2-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_3_2-solution000001.solution new file mode 100644 index 0000000000..d56a0bbcdc --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_3_2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_3_2-solution000002.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_3_2-solution000002.solution new file mode 100644 index 0000000000..ff56905e23 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_3_2-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_3_2-solution000003.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_3_2-solution000003.solution new file mode 100644 index 0000000000..15472caf03 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_3_2-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 2, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_3_2-solution000004.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_3_2-solution000004.solution new file mode 100644 index 0000000000..1b4b5b08a6 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_3_2-solution000004.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 2, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_3_2-solution000005.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_3_2-solution000005.solution new file mode 100644 index 0000000000..5e2caa751c --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_3_2-solution000005.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 2, 2) +letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_3_2-solution000006.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_3_2-solution000006.solution new file mode 100644 index 0000000000..621d5f6edc --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_3_2-solution000006.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 1, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_3_2.eprime b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_3_2.eprime new file mode 100644 index 0000000000..5fd762ddea --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_3_2.eprime @@ -0,0 +1,44 @@ +language ESSENCE' 1.0 + +find a_MOccurrence: matrix indexed by [int(1..2)] of int(0..3) +find b_ExplicitWithRepetition_Flag: int(3) +find b_ExplicitWithRepetition_Values: matrix indexed by [int(1..3)] of int(1..2) +branching on [a_MOccurrence, b_ExplicitWithRepetition_Flag, b_ExplicitWithRepetition_Values] +such that + or([a_MOccurrence[q20] > 0 /\ + (a_MOccurrence[q20] < sum([toInt(b_ExplicitWithRepetition_Values[q10] = q20) | q10 : int(1..3), q10 <= 3]) /\ + (and([a_MOccurrence[q16] > 0 -> + a_MOccurrence[q16] = sum([toInt(b_ExplicitWithRepetition_Values[q12] = q16) | q12 : int(1..3), q12 <= 3]) + | q16 : int(1..2), q16 < q20]) + /\ + and([!or([a_MOccurrence[q15] > 0 /\ q15 = b_ExplicitWithRepetition_Values[q13] | q15 : int(1..2)]) /\ + b_ExplicitWithRepetition_Values[q13] < q20 + -> + a_MOccurrence[b_ExplicitWithRepetition_Values[q13]] = + sum([toInt(b_ExplicitWithRepetition_Values[q12] = b_ExplicitWithRepetition_Values[q13]) + | q12 : int(1..3), q12 <= 3]) + | q13 : int(1..3), q13 <= 3]))) + | q20 : int(1..2)]) + \/ + or([!or([a_MOccurrence[q19] > 0 /\ q19 = b_ExplicitWithRepetition_Values[q17] | q19 : int(1..2)]) /\ + (a_MOccurrence[b_ExplicitWithRepetition_Values[q17]] < + sum([toInt(b_ExplicitWithRepetition_Values[q10] = b_ExplicitWithRepetition_Values[q17]) + | q10 : int(1..3), q10 <= 3]) + /\ + (and([q16 < b_ExplicitWithRepetition_Values[q17] -> + (a_MOccurrence[q16] > 0 -> + a_MOccurrence[q16] = + sum([toInt(b_ExplicitWithRepetition_Values[q12] = q16) | q12 : int(1..3), q12 <= 3])) + | q16 : int(1..2)]) + /\ + and([!or([a_MOccurrence[q15] > 0 /\ q15 = b_ExplicitWithRepetition_Values[q13] | q15 : int(1..2)]) /\ + b_ExplicitWithRepetition_Values[q13] < b_ExplicitWithRepetition_Values[q17] + -> + a_MOccurrence[b_ExplicitWithRepetition_Values[q13]] = + sum([toInt(b_ExplicitWithRepetition_Values[q12] = b_ExplicitWithRepetition_Values[q13]) + | q12 : int(1..3), q12 <= 3]) + | q13 : int(1..3), q13 <= 3]))) + | q17 : int(1..3), q17 <= 3]), + 3 = sum([a_MOccurrence[q1] | q1 : int(1..2)]), + and([b_ExplicitWithRepetition_Values[q2] <= b_ExplicitWithRepetition_Values[q2 + 1] | q2 : int(1..2), q2 + 1 <= 3]) + diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_3_3-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_3_3-solution000001.solution new file mode 100644 index 0000000000..15472caf03 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_3_3-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 2, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_3_3-solution000002.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_3_3-solution000002.solution new file mode 100644 index 0000000000..ff56905e23 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_3_3-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_3_3-solution000003.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_3_3-solution000003.solution new file mode 100644 index 0000000000..d56a0bbcdc --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_3_3-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_3_3-solution000004.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_3_3-solution000004.solution new file mode 100644 index 0000000000..5e2caa751c --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_3_3-solution000004.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 2, 2) +letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_3_3-solution000005.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_3_3-solution000005.solution new file mode 100644 index 0000000000..1b4b5b08a6 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_3_3-solution000005.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 2, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_3_3-solution000006.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_3_3-solution000006.solution new file mode 100644 index 0000000000..621d5f6edc --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_3_3-solution000006.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 1, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_3_3.eprime b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_3_3.eprime new file mode 100644 index 0000000000..58c3cfbb72 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_2_3_3.eprime @@ -0,0 +1,53 @@ +language ESSENCE' 1.0 + +find a_MOccurrence: matrix indexed by [int(1..2)] of int(0..3) +find b_ExplicitWithRepetition_Flag: int(3) +find b_ExplicitWithRepetition_Values: matrix indexed by [int(1..3)] of int(1..2) +find b_MOccurrence: matrix indexed by [int(1..2)] of int(0..3) +branching on [a_MOccurrence, b_MOccurrence, b_ExplicitWithRepetition_Flag, b_ExplicitWithRepetition_Values] +such that + or([a_MOccurrence[q28] > 0 /\ + (a_MOccurrence[q28] < sum([toInt(b_ExplicitWithRepetition_Values[q18] = q28) | q18 : int(1..3), q18 <= 3]) /\ + (and([a_MOccurrence[q24] > 0 -> + a_MOccurrence[q24] = sum([toInt(b_ExplicitWithRepetition_Values[q20] = q24) | q20 : int(1..3), q20 <= 3]) + | q24 : int(1..2), q24 < q28]) + /\ + and([!or([a_MOccurrence[q23] > 0 /\ q23 = b_ExplicitWithRepetition_Values[q21] | q23 : int(1..2)]) /\ + b_ExplicitWithRepetition_Values[q21] < q28 + -> + a_MOccurrence[b_ExplicitWithRepetition_Values[q21]] = + sum([toInt(b_ExplicitWithRepetition_Values[q20] = b_ExplicitWithRepetition_Values[q21]) + | q20 : int(1..3), q20 <= 3]) + | q21 : int(1..3), q21 <= 3]))) + | q28 : int(1..2)]) + \/ + or([!or([a_MOccurrence[q27] > 0 /\ q27 = b_ExplicitWithRepetition_Values[q25] | q27 : int(1..2)]) /\ + (a_MOccurrence[b_ExplicitWithRepetition_Values[q25]] < + sum([toInt(b_ExplicitWithRepetition_Values[q18] = b_ExplicitWithRepetition_Values[q25]) + | q18 : int(1..3), q18 <= 3]) + /\ + (and([q24 < b_ExplicitWithRepetition_Values[q25] -> + (a_MOccurrence[q24] > 0 -> + a_MOccurrence[q24] = + sum([toInt(b_ExplicitWithRepetition_Values[q20] = q24) | q20 : int(1..3), q20 <= 3])) + | q24 : int(1..2)]) + /\ + and([!or([a_MOccurrence[q23] > 0 /\ q23 = b_ExplicitWithRepetition_Values[q21] | q23 : int(1..2)]) /\ + b_ExplicitWithRepetition_Values[q21] < b_ExplicitWithRepetition_Values[q25] + -> + a_MOccurrence[b_ExplicitWithRepetition_Values[q21]] = + sum([toInt(b_ExplicitWithRepetition_Values[q20] = b_ExplicitWithRepetition_Values[q21]) + | q20 : int(1..3), q20 <= 3]) + | q21 : int(1..3), q21 <= 3]))) + | q25 : int(1..3), q25 <= 3]), + 3 = sum([a_MOccurrence[q1] | q1 : int(1..2)]), + and([b_ExplicitWithRepetition_Values[q2] <= b_ExplicitWithRepetition_Values[q2 + 1] | q2 : int(1..2), q2 + 1 <= 3]), + 3 = sum([b_MOccurrence[q7] | q7 : int(1..2)]), + and([b_MOccurrence[q9] > 0 -> + b_MOccurrence[q9] = sum([toInt(b_ExplicitWithRepetition_Values[q11] = q9) | q11 : int(1..3), q11 <= 3]) + | q9 : int(1..2)]), + and([b_MOccurrence[b_ExplicitWithRepetition_Values[q12]] = + sum([toInt(b_ExplicitWithRepetition_Values[q14] = b_ExplicitWithRepetition_Values[q12]) + | q14 : int(1..3), q14 <= 3]) + | q12 : int(1..3), q12 <= 3]) + diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_1_1-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_1_1-solution000001.solution new file mode 100644 index 0000000000..5e2caa751c --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_1_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 2, 2) +letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_1_1-solution000002.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_1_1-solution000002.solution new file mode 100644 index 0000000000..1b4b5b08a6 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_1_1-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 2, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_1_1-solution000003.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_1_1-solution000003.solution new file mode 100644 index 0000000000..621d5f6edc --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_1_1-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 1, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_1_1-solution000004.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_1_1-solution000004.solution new file mode 100644 index 0000000000..15472caf03 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_1_1-solution000004.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 2, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_1_1-solution000005.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_1_1-solution000005.solution new file mode 100644 index 0000000000..ff56905e23 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_1_1-solution000005.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_1_1-solution000006.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_1_1-solution000006.solution new file mode 100644 index 0000000000..d56a0bbcdc --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_1_1-solution000006.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_1_2-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_1_2-solution000001.solution new file mode 100644 index 0000000000..1b4b5b08a6 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_1_2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 2, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_1_2-solution000002.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_1_2-solution000002.solution new file mode 100644 index 0000000000..5e2caa751c --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_1_2-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 2, 2) +letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_1_2-solution000003.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_1_2-solution000003.solution new file mode 100644 index 0000000000..621d5f6edc --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_1_2-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 1, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_1_2-solution000004.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_1_2-solution000004.solution new file mode 100644 index 0000000000..d56a0bbcdc --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_1_2-solution000004.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_1_2-solution000005.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_1_2-solution000005.solution new file mode 100644 index 0000000000..ff56905e23 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_1_2-solution000005.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_1_2-solution000006.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_1_2-solution000006.solution new file mode 100644 index 0000000000..15472caf03 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_1_2-solution000006.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 2, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_1_3-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_1_3-solution000001.solution new file mode 100644 index 0000000000..5e2caa751c --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_1_3-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 2, 2) +letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_1_3-solution000002.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_1_3-solution000002.solution new file mode 100644 index 0000000000..1b4b5b08a6 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_1_3-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 2, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_1_3-solution000003.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_1_3-solution000003.solution new file mode 100644 index 0000000000..621d5f6edc --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_1_3-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 1, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_1_3-solution000004.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_1_3-solution000004.solution new file mode 100644 index 0000000000..15472caf03 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_1_3-solution000004.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 2, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_1_3-solution000005.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_1_3-solution000005.solution new file mode 100644 index 0000000000..ff56905e23 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_1_3-solution000005.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_1_3-solution000006.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_1_3-solution000006.solution new file mode 100644 index 0000000000..d56a0bbcdc --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_1_3-solution000006.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_2_1-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_2_1-solution000001.solution new file mode 100644 index 0000000000..621d5f6edc --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_2_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 1, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_2_1-solution000002.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_2_1-solution000002.solution new file mode 100644 index 0000000000..5e2caa751c --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_2_1-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 2, 2) +letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_2_1-solution000003.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_2_1-solution000003.solution new file mode 100644 index 0000000000..1b4b5b08a6 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_2_1-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 2, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_2_1-solution000004.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_2_1-solution000004.solution new file mode 100644 index 0000000000..15472caf03 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_2_1-solution000004.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 2, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_2_1-solution000005.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_2_1-solution000005.solution new file mode 100644 index 0000000000..ff56905e23 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_2_1-solution000005.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_2_1-solution000006.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_2_1-solution000006.solution new file mode 100644 index 0000000000..d56a0bbcdc --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_2_1-solution000006.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_2_2-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_2_2-solution000001.solution new file mode 100644 index 0000000000..621d5f6edc --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_2_2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 1, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_2_2-solution000002.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_2_2-solution000002.solution new file mode 100644 index 0000000000..1b4b5b08a6 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_2_2-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 2, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_2_2-solution000003.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_2_2-solution000003.solution new file mode 100644 index 0000000000..5e2caa751c --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_2_2-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 2, 2) +letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_2_2-solution000004.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_2_2-solution000004.solution new file mode 100644 index 0000000000..d56a0bbcdc --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_2_2-solution000004.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_2_2-solution000005.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_2_2-solution000005.solution new file mode 100644 index 0000000000..ff56905e23 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_2_2-solution000005.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_2_2-solution000006.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_2_2-solution000006.solution new file mode 100644 index 0000000000..15472caf03 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_2_2-solution000006.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 2, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_2_2.eprime b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_2_2.eprime new file mode 100644 index 0000000000..3433c44d83 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_2_2.eprime @@ -0,0 +1,47 @@ +language ESSENCE' 1.0 + +find a_MOccurrence: matrix indexed by [int(1..2)] of int(0..3) +find a_ExplicitWithRepetition_Flag: int(3) +find a_ExplicitWithRepetition_Values: matrix indexed by [int(1..3)] of int(1..2) +find b_MOccurrence: matrix indexed by [int(1..2)] of int(0..3) +find b_ExplicitWithRepetition_Flag: int(3) +find b_ExplicitWithRepetition_Values: matrix indexed by [int(1..3)] of int(1..2) +branching on + [a_ExplicitWithRepetition_Flag, a_ExplicitWithRepetition_Values, a_MOccurrence, b_ExplicitWithRepetition_Flag, + b_ExplicitWithRepetition_Values, b_MOccurrence] +such that + or([a_MOccurrence[q35] > 0 /\ + (a_MOccurrence[q35] < b_MOccurrence[q35] /\ + (and([a_MOccurrence[q31] > 0 -> a_MOccurrence[q31] = b_MOccurrence[q31] | q31 : int(1..2), q31 < q35]) /\ + and([b_MOccurrence[q32] > 0 /\ !or([a_MOccurrence[q30] > 0 /\ q30 = q32 | q30 : int(1..2)]) -> + a_MOccurrence[q32] = b_MOccurrence[q32] + | q32 : int(1..2), q32 < q35]))) + | q35 : int(1..2)]) + \/ + or([b_MOccurrence[q36] > 0 /\ !or([a_MOccurrence[q34] > 0 /\ q34 = q36 | q34 : int(1..2)]) /\ + (a_MOccurrence[q36] < b_MOccurrence[q36] /\ + (and([a_MOccurrence[q31] > 0 -> a_MOccurrence[q31] = b_MOccurrence[q31] | q31 : int(1..2), q31 < q36]) /\ + and([b_MOccurrence[q32] > 0 /\ !or([a_MOccurrence[q30] > 0 /\ q30 = q32 | q30 : int(1..2)]) -> + a_MOccurrence[q32] = b_MOccurrence[q32] + | q32 : int(1..2), q32 < q36]))) + | q36 : int(1..2)]), + 3 = sum([a_MOccurrence[q1] | q1 : int(1..2)]), + 3 = sum([b_MOccurrence[q2] | q2 : int(1..2)]), + and([a_ExplicitWithRepetition_Values[q3] <= a_ExplicitWithRepetition_Values[q3 + 1] | q3 : int(1..2), q3 + 1 <= 3]), + and([sum([toInt(a_ExplicitWithRepetition_Values[q11] = a_ExplicitWithRepetition_Values[q9]) + | q11 : int(1..3), q11 <= 3]) + = a_MOccurrence[a_ExplicitWithRepetition_Values[q9]] + | q9 : int(1..3), q9 <= 3]), + and([a_MOccurrence[q12] > 0 -> + sum([toInt(a_ExplicitWithRepetition_Values[q14] = q12) | q14 : int(1..3), q14 <= 3]) = a_MOccurrence[q12] + | q12 : int(1..2)]), + and([b_ExplicitWithRepetition_Values[q15] <= b_ExplicitWithRepetition_Values[q15 + 1] + | q15 : int(1..2), q15 + 1 <= 3]), + and([sum([toInt(b_ExplicitWithRepetition_Values[q23] = b_ExplicitWithRepetition_Values[q21]) + | q23 : int(1..3), q23 <= 3]) + = b_MOccurrence[b_ExplicitWithRepetition_Values[q21]] + | q21 : int(1..3), q21 <= 3]), + and([b_MOccurrence[q24] > 0 -> + sum([toInt(b_ExplicitWithRepetition_Values[q26] = q24) | q26 : int(1..3), q26 <= 3]) = b_MOccurrence[q24] + | q24 : int(1..2)]) + diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_2_3-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_2_3-solution000001.solution new file mode 100644 index 0000000000..621d5f6edc --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_2_3-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 1, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_2_3-solution000002.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_2_3-solution000002.solution new file mode 100644 index 0000000000..5e2caa751c --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_2_3-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 2, 2) +letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_2_3-solution000003.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_2_3-solution000003.solution new file mode 100644 index 0000000000..1b4b5b08a6 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_2_3-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 2, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_2_3-solution000004.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_2_3-solution000004.solution new file mode 100644 index 0000000000..15472caf03 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_2_3-solution000004.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 2, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_2_3-solution000005.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_2_3-solution000005.solution new file mode 100644 index 0000000000..ff56905e23 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_2_3-solution000005.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_2_3-solution000006.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_2_3-solution000006.solution new file mode 100644 index 0000000000..d56a0bbcdc --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_2_3-solution000006.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_2_3.eprime b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_2_3.eprime new file mode 100644 index 0000000000..fe7f6d1d79 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_2_3.eprime @@ -0,0 +1,34 @@ +language ESSENCE' 1.0 + +find a_MOccurrence: matrix indexed by [int(1..2)] of int(0..3) +find a_ExplicitWithRepetition_Flag: int(3) +find a_ExplicitWithRepetition_Values: matrix indexed by [int(1..3)] of int(1..2) +find b_MOccurrence: matrix indexed by [int(1..2)] of int(0..3) +branching on [a_ExplicitWithRepetition_Flag, a_ExplicitWithRepetition_Values, a_MOccurrence, b_MOccurrence] +such that + or([a_MOccurrence[q23] > 0 /\ + (a_MOccurrence[q23] < b_MOccurrence[q23] /\ + (and([a_MOccurrence[q19] > 0 -> a_MOccurrence[q19] = b_MOccurrence[q19] | q19 : int(1..2), q19 < q23]) /\ + and([b_MOccurrence[q20] > 0 /\ !or([a_MOccurrence[q18] > 0 /\ q18 = q20 | q18 : int(1..2)]) -> + a_MOccurrence[q20] = b_MOccurrence[q20] + | q20 : int(1..2), q20 < q23]))) + | q23 : int(1..2)]) + \/ + or([b_MOccurrence[q24] > 0 /\ !or([a_MOccurrence[q22] > 0 /\ q22 = q24 | q22 : int(1..2)]) /\ + (a_MOccurrence[q24] < b_MOccurrence[q24] /\ + (and([a_MOccurrence[q19] > 0 -> a_MOccurrence[q19] = b_MOccurrence[q19] | q19 : int(1..2), q19 < q24]) /\ + and([b_MOccurrence[q20] > 0 /\ !or([a_MOccurrence[q18] > 0 /\ q18 = q20 | q18 : int(1..2)]) -> + a_MOccurrence[q20] = b_MOccurrence[q20] + | q20 : int(1..2), q20 < q24]))) + | q24 : int(1..2)]), + 3 = sum([a_MOccurrence[q1] | q1 : int(1..2)]), + 3 = sum([b_MOccurrence[q2] | q2 : int(1..2)]), + and([a_ExplicitWithRepetition_Values[q3] <= a_ExplicitWithRepetition_Values[q3 + 1] | q3 : int(1..2), q3 + 1 <= 3]), + and([sum([toInt(a_ExplicitWithRepetition_Values[q11] = a_ExplicitWithRepetition_Values[q9]) + | q11 : int(1..3), q11 <= 3]) + = a_MOccurrence[a_ExplicitWithRepetition_Values[q9]] + | q9 : int(1..3), q9 <= 3]), + and([a_MOccurrence[q12] > 0 -> + sum([toInt(a_ExplicitWithRepetition_Values[q14] = q12) | q14 : int(1..3), q14 <= 3]) = a_MOccurrence[q12] + | q12 : int(1..2)]) + diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_3_1-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_3_1-solution000001.solution new file mode 100644 index 0000000000..15472caf03 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_3_1-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 2, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_3_1-solution000002.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_3_1-solution000002.solution new file mode 100644 index 0000000000..ff56905e23 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_3_1-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_3_1-solution000003.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_3_1-solution000003.solution new file mode 100644 index 0000000000..d56a0bbcdc --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_3_1-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_3_1-solution000004.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_3_1-solution000004.solution new file mode 100644 index 0000000000..5e2caa751c --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_3_1-solution000004.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 2, 2) +letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_3_1-solution000005.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_3_1-solution000005.solution new file mode 100644 index 0000000000..1b4b5b08a6 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_3_1-solution000005.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 2, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_3_1-solution000006.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_3_1-solution000006.solution new file mode 100644 index 0000000000..621d5f6edc --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_3_1-solution000006.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 1, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_3_2-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_3_2-solution000001.solution new file mode 100644 index 0000000000..d56a0bbcdc --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_3_2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_3_2-solution000002.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_3_2-solution000002.solution new file mode 100644 index 0000000000..ff56905e23 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_3_2-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_3_2-solution000003.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_3_2-solution000003.solution new file mode 100644 index 0000000000..15472caf03 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_3_2-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 2, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_3_2-solution000004.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_3_2-solution000004.solution new file mode 100644 index 0000000000..1b4b5b08a6 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_3_2-solution000004.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 2, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_3_2-solution000005.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_3_2-solution000005.solution new file mode 100644 index 0000000000..5e2caa751c --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_3_2-solution000005.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 2, 2) +letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_3_2-solution000006.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_3_2-solution000006.solution new file mode 100644 index 0000000000..621d5f6edc --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_3_2-solution000006.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 1, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_3_2.eprime b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_3_2.eprime new file mode 100644 index 0000000000..fbd4f2c5d9 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_3_2.eprime @@ -0,0 +1,34 @@ +language ESSENCE' 1.0 + +find a_MOccurrence: matrix indexed by [int(1..2)] of int(0..3) +find b_MOccurrence: matrix indexed by [int(1..2)] of int(0..3) +find b_ExplicitWithRepetition_Flag: int(3) +find b_ExplicitWithRepetition_Values: matrix indexed by [int(1..3)] of int(1..2) +branching on [a_MOccurrence, b_ExplicitWithRepetition_Flag, b_ExplicitWithRepetition_Values, b_MOccurrence] +such that + or([a_MOccurrence[q23] > 0 /\ + (a_MOccurrence[q23] < b_MOccurrence[q23] /\ + (and([a_MOccurrence[q19] > 0 -> a_MOccurrence[q19] = b_MOccurrence[q19] | q19 : int(1..2), q19 < q23]) /\ + and([b_MOccurrence[q20] > 0 /\ !or([a_MOccurrence[q18] > 0 /\ q18 = q20 | q18 : int(1..2)]) -> + a_MOccurrence[q20] = b_MOccurrence[q20] + | q20 : int(1..2), q20 < q23]))) + | q23 : int(1..2)]) + \/ + or([b_MOccurrence[q24] > 0 /\ !or([a_MOccurrence[q22] > 0 /\ q22 = q24 | q22 : int(1..2)]) /\ + (a_MOccurrence[q24] < b_MOccurrence[q24] /\ + (and([a_MOccurrence[q19] > 0 -> a_MOccurrence[q19] = b_MOccurrence[q19] | q19 : int(1..2), q19 < q24]) /\ + and([b_MOccurrence[q20] > 0 /\ !or([a_MOccurrence[q18] > 0 /\ q18 = q20 | q18 : int(1..2)]) -> + a_MOccurrence[q20] = b_MOccurrence[q20] + | q20 : int(1..2), q20 < q24]))) + | q24 : int(1..2)]), + 3 = sum([a_MOccurrence[q1] | q1 : int(1..2)]), + 3 = sum([b_MOccurrence[q2] | q2 : int(1..2)]), + and([b_ExplicitWithRepetition_Values[q3] <= b_ExplicitWithRepetition_Values[q3 + 1] | q3 : int(1..2), q3 + 1 <= 3]), + and([sum([toInt(b_ExplicitWithRepetition_Values[q11] = b_ExplicitWithRepetition_Values[q9]) + | q11 : int(1..3), q11 <= 3]) + = b_MOccurrence[b_ExplicitWithRepetition_Values[q9]] + | q9 : int(1..3), q9 <= 3]), + and([b_MOccurrence[q12] > 0 -> + sum([toInt(b_ExplicitWithRepetition_Values[q14] = q12) | q14 : int(1..3), q14 <= 3]) = b_MOccurrence[q12] + | q12 : int(1..2)]) + diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_3_3-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_3_3-solution000001.solution new file mode 100644 index 0000000000..15472caf03 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_3_3-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 2, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_3_3-solution000002.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_3_3-solution000002.solution new file mode 100644 index 0000000000..ff56905e23 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_3_3-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_3_3-solution000003.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_3_3-solution000003.solution new file mode 100644 index 0000000000..d56a0bbcdc --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_3_3-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(2, 2, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_3_3-solution000004.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_3_3-solution000004.solution new file mode 100644 index 0000000000..5e2caa751c --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_3_3-solution000004.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 2, 2) +letting b be mset(1, 1, 2) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_3_3-solution000005.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_3_3-solution000005.solution new file mode 100644 index 0000000000..1b4b5b08a6 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_3_3-solution000005.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 2, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_3_3-solution000006.solution b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_3_3-solution000006.solution new file mode 100644 index 0000000000..621d5f6edc --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_3_3-solution000006.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting a be mset(1, 1, 2) +letting b be mset(1, 1, 1) diff --git a/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_3_3.eprime b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_3_3.eprime new file mode 100644 index 0000000000..735a032370 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_mset_01/expected/model_3_3_3_3.eprime @@ -0,0 +1,24 @@ +language ESSENCE' 1.0 + +find a_MOccurrence: matrix indexed by [int(1..2)] of int(0..3) +find b_MOccurrence: matrix indexed by [int(1..2)] of int(0..3) +branching on [a_MOccurrence, b_MOccurrence] +such that + or([a_MOccurrence[q11] > 0 /\ + (a_MOccurrence[q11] < b_MOccurrence[q11] /\ + (and([a_MOccurrence[q7] > 0 -> a_MOccurrence[q7] = b_MOccurrence[q7] | q7 : int(1..2), q7 < q11]) /\ + and([b_MOccurrence[q8] > 0 /\ !or([a_MOccurrence[q6] > 0 /\ q6 = q8 | q6 : int(1..2)]) -> + a_MOccurrence[q8] = b_MOccurrence[q8] + | q8 : int(1..2), q8 < q11]))) + | q11 : int(1..2)]) + \/ + or([b_MOccurrence[q12] > 0 /\ !or([a_MOccurrence[q10] > 0 /\ q10 = q12 | q10 : int(1..2)]) /\ + (a_MOccurrence[q12] < b_MOccurrence[q12] /\ + (and([a_MOccurrence[q7] > 0 -> a_MOccurrence[q7] = b_MOccurrence[q7] | q7 : int(1..2), q7 < q12]) /\ + and([b_MOccurrence[q8] > 0 /\ !or([a_MOccurrence[q6] > 0 /\ q6 = q8 | q6 : int(1..2)]) -> + a_MOccurrence[q8] = b_MOccurrence[q8] + | q8 : int(1..2), q8 < q12]))) + | q12 : int(1..2)]), + 3 = sum([a_MOccurrence[q1] | q1 : int(1..2)]), + 3 = sum([b_MOccurrence[q2] | q2 : int(1..2)]) + diff --git a/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_1_1-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_1_1-solution000001.solution new file mode 100644 index 0000000000..cde05d5274 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_1_1-solution000001.solution @@ -0,0 +1,11 @@ +language Essence 1.3 + +letting a be partition({1, 2}) +$ Visualisation for a +$ 1 2 + +letting b be partition({1}, {2}) +$ Visualisation for b +$ 1 +$ 2 + diff --git a/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_1_1.eprime b/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_1_1.eprime new file mode 100644 index 0000000000..5999cb42ac --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_1_1.eprime @@ -0,0 +1,324 @@ +language ESSENCE' 1.0 + +find a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker: int(0..2) +find a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence: matrix indexed by [int(1..2), int(1..2)] of bool +find b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker: int(0..2) +find b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence: matrix indexed by [int(1..2), int(1..2)] of bool +branching on + [a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker, + a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence, + b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker, + b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence] +such that + or([q36 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ + (toInt(or([q95 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ + and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q95, q96] = + a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q36, q96] + | q96 : int(1..2)]) + | q95 : int(1..2)])) + < + toInt(or([q100 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ + and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q100, q101] = + a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q36, q101] + | q101 : int(1..2)]) + | q100 : int(1..2)])) + /\ + (and([q104 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ + (or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q104, q137] /\ + (toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q104, q137]) < + toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q36, q137]) + /\ + (and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q104, q138] -> + toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q104, q138]) = + toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q36, q138]) + | q138 : int(1..2), q138 < q137]) + /\ + and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q36, q138] /\ + !or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q104, q141] /\ + q141 = q138 + | q141 : int(1..2)]) + -> + toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q104, q138]) = + toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q36, q138]) + | q138 : int(1..2), q138 < q137]))) + | q137 : int(1..2)]) + \/ + or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q36, q137] /\ + !or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q104, q140] /\ q140 = q137 + | q140 : int(1..2)]) + /\ + (toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q104, q137]) < + toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q36, q137]) + /\ + (and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q104, q138] -> + toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q104, q138]) = + toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q36, q138]) + | q138 : int(1..2), q138 < q137]) + /\ + and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q36, q138] /\ + !or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q104, q139] /\ + q139 = q138 + | q139 : int(1..2)]) + -> + toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q104, q138]) = + toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q36, q138]) + | q138 : int(1..2), q138 < q137]))) + | q137 : int(1..2)])) + -> + toInt(or([q129 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ + and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q129, q130] = + a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q104, q130] + | q130 : int(1..2)]) + | q129 : int(1..2)])) + = + toInt(or([q134 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ + and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q134, q135] = + a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q104, q135] + | q135 : int(1..2)]) + | q134 : int(1..2)])) + | q104 : int(1..2)]) + /\ + and([and([q106 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker, + !or([q119 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ + and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q119, q120] = + b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q106, q120] + | q120 : int(1..2)]) + | q119 : int(1..2)]), + or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q106, q122] /\ + (toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q106, q122]) < + toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q36, q122]) + /\ + (and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q106, q123] -> + toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q106, q123]) = + toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q36, q123]) + | q123 : int(1..2), q123 < q122]) + /\ + and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q36, q123] /\ + !or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q106, q126] /\ + q126 = q123 + | q126 : int(1..2)]) + -> + toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q106, q123]) = + toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q36, q123]) + | q123 : int(1..2), q123 < q122]))) + | q122 : int(1..2)]) + \/ + or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q36, q122] /\ + !or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q106, q125] /\ q125 = q122 + | q125 : int(1..2)]) + /\ + (toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q106, q122]) < + toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q36, q122]) + /\ + (and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q106, q123] -> + toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q106, q123]) = + toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q36, q123]) + | q123 : int(1..2), q123 < q122]) + /\ + and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q36, q123] /\ + !or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q106, q124] /\ + q124 = q123 + | q124 : int(1..2)]) + -> + toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q106, q123]) = + toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q36, q123]) + | q123 : int(1..2), q123 < q122]))) + | q122 : int(1..2)]); + int(1..3)]) + -> + toInt(or([q109 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ + and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q109, q110] = + b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q106, q110] + | q110 : int(1..2)]) + | q109 : int(1..2)])) + = + toInt(or([q114 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ + and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q114, q115] = + b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q106, q115] + | q115 : int(1..2)]) + | q114 : int(1..2)])) + | q106 : int(1..2)]))) + | q36 : int(1..2)]) + \/ + or([q38 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ + !or([q90 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ + and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q90, q91] = + b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q38, q91] + | q91 : int(1..2)]) + | q90 : int(1..2)]) + /\ + (toInt(or([q41 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ + and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q41, q42] = + b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q38, q42] + | q42 : int(1..2)]) + | q41 : int(1..2)])) + < + toInt(or([q46 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ + and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q46, q47] = + b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q38, q47] + | q47 : int(1..2)]) + | q46 : int(1..2)])) + /\ + (and([q50 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ + (or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q50, q83] /\ + (toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q50, q83]) < + toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q38, q83]) + /\ + (and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q50, q84] -> + toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q50, q84]) = + toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q38, q84]) + | q84 : int(1..2), q84 < q83]) + /\ + and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q38, q84] /\ + !or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q50, q87] /\ q87 = q84 + | q87 : int(1..2)]) + -> + toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q50, q84]) = + toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q38, q84]) + | q84 : int(1..2), q84 < q83]))) + | q83 : int(1..2)]) + \/ + or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q38, q83] /\ + !or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q50, q86] /\ q86 = q83 + | q86 : int(1..2)]) + /\ + (toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q50, q83]) < + toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q38, q83]) + /\ + (and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q50, q84] -> + toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q50, q84]) = + toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q38, q84]) + | q84 : int(1..2), q84 < q83]) + /\ + and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q38, q84] /\ + !or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q50, q85] /\ q85 = q84 + | q85 : int(1..2)]) + -> + toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q50, q84]) = + toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q38, q84]) + | q84 : int(1..2), q84 < q83]))) + | q83 : int(1..2)])) + -> + toInt(or([q75 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ + and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q75, q76] = + a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q50, q76] + | q76 : int(1..2)]) + | q75 : int(1..2)])) + = + toInt(or([q80 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ + and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q80, q81] = + a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q50, q81] + | q81 : int(1..2)]) + | q80 : int(1..2)])) + | q50 : int(1..2)]) + /\ + and([and([q52 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker, + !or([q65 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ + and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q65, q66] = + b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q52, q66] + | q66 : int(1..2)]) + | q65 : int(1..2)]), + or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q52, q68] /\ + (toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q52, q68]) < + toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q38, q68]) + /\ + (and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q52, q69] -> + toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q52, q69]) = + toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q38, q69]) + | q69 : int(1..2), q69 < q68]) + /\ + and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q38, q69] /\ + !or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q52, q72] /\ + q72 = q69 + | q72 : int(1..2)]) + -> + toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q52, q69]) = + toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q38, q69]) + | q69 : int(1..2), q69 < q68]))) + | q68 : int(1..2)]) + \/ + or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q38, q68] /\ + !or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q52, q71] /\ q71 = q68 + | q71 : int(1..2)]) + /\ + (toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q52, q68]) < + toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q38, q68]) + /\ + (and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q52, q69] -> + toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q52, q69]) = + toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q38, q69]) + | q69 : int(1..2), q69 < q68]) + /\ + and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q38, q69] /\ + !or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q52, q70] /\ + q70 = q69 + | q70 : int(1..2)]) + -> + toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q52, q69]) = + toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q38, q69]) + | q69 : int(1..2), q69 < q68]))) + | q68 : int(1..2)]); + int(1..3)]) + -> + toInt(or([q55 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ + and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q55, q56] = + b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q52, q56] + | q56 : int(1..2)]) + | q55 : int(1..2)])) + = + toInt(or([q60 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ + and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q60, q61] = + b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q52, q61] + | q61 : int(1..2)]) + | q60 : int(1..2)])) + | q52 : int(1..2)]))) + | q38 : int(1..2)]), + and([1 = + sum([toInt(q27 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ + a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q27, q1]) + | q27 : int(1..2)]) + | q1 : int(1..2)]), + and([q31 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> + sum([toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q31, q32]) | q32 : int(1..2)]) >= 1 + | q31 : int(1..2)]), + 2 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> + [-toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[1, q9]) | q9 : int(1..2)] a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> + and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q5, q11] = false | q11 : int(1..2)]) + | q5 : int(1..2)]), + a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker <= 2, + and([q6 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> + sum([toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q6, q7]) | q7 : int(1..2)]) <= 2 + | q6 : int(1..2)]), + 2 = + sum([toInt(q12 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker) * + catchUndef(sum([toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q12, q13]) + | q13 : int(1..2)]), + 0) + | q12 : int(1..2)]), + and([1 = + sum([toInt(q28 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ + b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q28, q14]) + | q28 : int(1..2)]) + | q14 : int(1..2)]), + and([q29 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> + sum([toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q29, q30]) | q30 : int(1..2)]) >= 1 + | q29 : int(1..2)]), + 2 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> + [-toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[1, q22]) | q22 : int(1..2)] b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> + and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q18, q24] = false | q24 : int(1..2)]) + | q18 : int(1..2)]), + b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker <= 2, + and([q19 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> + sum([toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q19, q20]) | q20 : int(1..2)]) <= 2 + | q19 : int(1..2)]), + 2 = + sum([toInt(q25 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker) * + catchUndef(sum([toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q25, q26]) + | q26 : int(1..2)]), + 0) + | q25 : int(1..2)]) + diff --git a/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_1_2-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_1_2-solution000001.solution new file mode 100644 index 0000000000..cde05d5274 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_1_2-solution000001.solution @@ -0,0 +1,11 @@ +language Essence 1.3 + +letting a be partition({1, 2}) +$ Visualisation for a +$ 1 2 + +letting b be partition({1}, {2}) +$ Visualisation for b +$ 1 +$ 2 + diff --git a/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_1_2.eprime b/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_1_2.eprime new file mode 100644 index 0000000000..6ac5a9636a --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_1_2.eprime @@ -0,0 +1,787 @@ +language ESSENCE' 1.0 + +find a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker: int(0..2) +find a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence: matrix indexed by [int(1..2), int(1..2)] of bool +find b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker: int(0..2) +find b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy: + matrix indexed by [int(1..2), int(1..2)] of int(1..3) +branching on + [a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker, + a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence, + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker, + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy] +such that + or([q42 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ + (toInt(or([q164 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ + and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q164, q165] = + a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q42, q165] + | q165 : int(1..2)]) + | q164 : int(1..2)])) + < + toInt(or([q169 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ + (and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q169, q171] != 3 + -> + a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence + [q42, + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q169, q171]] + | q171 : int(1..2)]) + /\ + and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q42, q172] -> + or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q169, q174] != + 3 + /\ + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q169, q174] = + q172 + | q174 : int(1..2)]) + | q172 : int(1..2)])) + | q169 : int(1..2)])) + /\ + (and([q176 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ + (or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q176, q236] /\ + (toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q176, q236]) < + toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q42, q236]) + /\ + (and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q176, q237] -> + toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q176, q237]) = + toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q42, q237]) + | q237 : int(1..2), q237 < q236]) + /\ + and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q42, q237] /\ + !or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q176, q240] /\ + q240 = q237 + | q240 : int(1..2)]) + -> + toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q176, q237]) = + toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q42, q237]) + | q237 : int(1..2), q237 < q236]))) + | q236 : int(1..2)]) + \/ + or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q42, q236] /\ + !or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q176, q239] /\ q239 = q236 + | q239 : int(1..2)]) + /\ + (toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q176, q236]) < + toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q42, q236]) + /\ + (and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q176, q237] -> + toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q176, q237]) = + toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q42, q237]) + | q237 : int(1..2), q237 < q236]) + /\ + and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q42, q237] /\ + !or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q176, q238] /\ + q238 = q237 + | q238 : int(1..2)]) + -> + toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q176, q237]) = + toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q42, q237]) + | q237 : int(1..2), q237 < q236]))) + | q236 : int(1..2)])) + -> + toInt(or([q225 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ + and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q225, q226] = + a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q176, q226] + | q226 : int(1..2)]) + | q225 : int(1..2)])) + = + toInt(or([q230 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ + (and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q230, q232] + != 3 + -> + a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence + [q176, + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q230, q232]] + | q232 : int(1..2)]) + /\ + and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q176, q233] -> + or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q230, q235] + != 3 + /\ + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q230, q235] + = q233 + | q235 : int(1..2)]) + | q233 : int(1..2)])) + | q230 : int(1..2)])) + | q176 : int(1..2)]) + /\ + and([and([q178 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker, + !or([q194 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ + (and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q194, q195] -> + or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q178, q197] + != 3 + /\ + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q178, q197] + = q195 + | q197 : int(1..2)]) + | q195 : int(1..2)]) + /\ + and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q178, q199] + != 3 + -> + a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence + [q194, + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q178, q199]] + | q199 : int(1..2)])) + | q194 : int(1..2)]), + or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q178, q202] != 3 /\ + (toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q178, q215] + != 3 + /\ + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q178, q215] + = + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q178, q202] + | q215 : int(1..2)])) + < + toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence + [q42, + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q178, q202]]) + /\ + (and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q178, q216] + != 3 + /\ + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q178, q216] + < + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q178, q202] + -> + toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q178, q222] + != 3 + /\ + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q178, q222] + = + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q178, q216] + | q222 : int(1..2)])) + = + toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence + [q42, + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q178, q216]]) + | q216 : int(1..2)]) + /\ + and([and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q42, q201], + !or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q178, q220] + != 3 + /\ + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q178, q220] + = q201 + | q220 : int(1..2)]), + q201 < + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q178, q202]; + int(1..3)]) + -> + toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q178, q218] + != 3 + /\ + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q178, q218] + = q201 + | q218 : int(1..2)])) + = toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q42, q201]) + | q201 : int(1..2)]))) + | q202 : int(1..2)]) + \/ + or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q42, q200] /\ + !or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q178, q213] != + 3 + /\ + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q178, q213] = + q200 + | q213 : int(1..2)]) + /\ + (toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q178, q204] + != 3 + /\ + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q178, q204] + = q200 + | q204 : int(1..2)])) + < toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q42, q200]) + /\ + (and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q178, q205] + != 3 + /\ + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q178, q205] + < q200 + -> + toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q178, q211] + != 3 + /\ + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q178, q211] + = + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q178, q205] + | q211 : int(1..2)])) + = + toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence + [q42, + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q178, q205]]) + | q205 : int(1..2)]) + /\ + and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q42, q201] /\ + !or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q178, q209] + != 3 + /\ + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q178, q209] + = q201 + | q209 : int(1..2)]) + -> + toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q178, q207] + != 3 + /\ + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q178, q207] + = q201 + | q207 : int(1..2)])) + = toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q42, q201]) + | q201 : int(1..2), q201 < q200]))) + | q200 : int(1..2)]); + int(1..3)]) + -> + toInt(or([q181 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ + (and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q181, q182] -> + or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q178, q184] + != 3 + /\ + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q178, q184] + = q182 + | q184 : int(1..2)]) + | q182 : int(1..2)]) + /\ + and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q178, q186] + != 3 + -> + a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence + [q181, + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q178, q186]] + | q186 : int(1..2)])) + | q181 : int(1..2)])) + = + toInt(or([q189 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ + and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q189, q190] = + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q178, q190] + | q190 : int(1..2)]) + | q189 : int(1..2)])) + | q178 : int(1..2)]))) + | q42 : int(1..2)]) + \/ + or([q44 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ + !or([q156 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ + (and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q156, q157] -> + or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q44, q159] != 3 /\ + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q44, q159] = q157 + | q159 : int(1..2)]) + | q157 : int(1..2)]) + /\ + and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q44, q161] != 3 -> + a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence + [q156, b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q44, q161]] + | q161 : int(1..2)])) + | q156 : int(1..2)]) + /\ + (toInt(or([q47 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ + (and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q47, q48] -> + or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q44, q50] != 3 + /\ + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q44, q50] = + q48 | q50 : int(1..2)]) + | q48 : int(1..2)]) + /\ + and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q44, q52] != 3 -> + a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence + [q47, + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q44, q52]] + | q52 : int(1..2)])) + | q47 : int(1..2)])) + < + toInt(or([q55 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ + and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q55, q56] = + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q44, q56] + | q56 : int(1..2)]) + | q55 : int(1..2)])) + /\ + (and([q59 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ + (or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q59, q134] /\ + (toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q59, q134]) < + toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q44, q147] + != 3 + /\ + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q44, q147] = + q134 + | q147 : int(1..2)])) + /\ + (and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q59, q135] -> + toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q59, q135]) = + toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q44, q153] + != 3 + /\ + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q44, q153] + = q135 + | q153 : int(1..2)])) + | q135 : int(1..2), q135 < q134]) + /\ + and([and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q44, q148] + != 3, + !or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q59, q149] /\ + q149 = + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q44, q148] + | q149 : int(1..2)]), + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q44, q148] + < q134; + int(1..3)]) + -> + toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence + [q59, + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q44, q148]]) + = + toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q44, q151] + != 3 + /\ + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q44, q151] + = + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q44, q148] + | q151 : int(1..2)])) + | q148 : int(1..2)]))) + | q134 : int(1..2)]) + \/ + or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q44, q136] != 3 /\ + !or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q59, q137] /\ + q137 = b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q44, q136] + | q137 : int(1..2)]) + /\ + (toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence + [q59, + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q44, q136]]) + < + toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q44, q139] + != 3 + /\ + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q44, q139] = + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q44, q136] + | q139 : int(1..2)])) + /\ + (and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q59, q135] /\ + q135 < + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q44, q136] + -> + toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q59, q135]) = + toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q44, q145] + != 3 + /\ + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q44, q145] + = q135 + | q145 : int(1..2)])) + | q135 : int(1..2)]) + /\ + and([and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q44, q140] + != 3, + !or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q59, q141] /\ + q141 = + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q44, q140] + | q141 : int(1..2)]), + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q44, q140] + < + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q44, q136]; + int(1..3)]) + -> + toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence + [q59, + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q44, q140]]) + = + toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q44, q143] + != 3 + /\ + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q44, q143] + = + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q44, q140] + | q143 : int(1..2)])) + | q140 : int(1..2)]))) + | q136 : int(1..2)])) + -> + toInt(or([q123 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ + and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q123, q124] = + a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q59, q124] + | q124 : int(1..2)]) + | q123 : int(1..2)])) + = + toInt(or([q128 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ + (and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q128, q130] + != 3 + -> + a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence + [q59, + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q128, q130]] + | q130 : int(1..2)]) + /\ + and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q59, q131] -> + or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q128, q133] + != 3 + /\ + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q128, q133] + = q131 + | q133 : int(1..2)]) + | q131 : int(1..2)])) + | q128 : int(1..2)])) + | q59 : int(1..2)]) + /\ + and([and([q61 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker, + !or([q77 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ + (and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q77, q78] -> + or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q61, q80] + != 3 + /\ + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q61, q80] + = q78 + | q80 : int(1..2)]) + | q78 : int(1..2)]) + /\ + and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q61, q82] != + 3 + -> + a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence + [q77, + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q61, q82]] + | q82 : int(1..2)])) + | q77 : int(1..2)]), + or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q61, q85] != 3 /\ + (toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q61, q106] + != 3 + /\ + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q61, q106] + = + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q61, q85] + | q106 : int(1..2)])) + < + toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q44, q108] + != 3 + /\ + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q44, q108] + = + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q61, q85] + | q108 : int(1..2)])) + /\ + (and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q61, q109] + != 3 + /\ + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q61, q109] < + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q61, q85] + -> + toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q61, q118] + != 3 + /\ + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q61, q118] + = + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q61, q109] + | q118 : int(1..2)])) + = + toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q44, q120] + != 3 + /\ + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q44, q120] + = + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q61, q109] + | q120 : int(1..2)])) + | q109 : int(1..2)]) + /\ + and([and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q44, q110] + != 3, + !or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q61, q112] + != 3 + /\ + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q61, q112] + = + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q44, q110] + | q112 : int(1..2)]), + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q44, q110] + < + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q61, q85]; + int(1..3)]) + -> + toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q61, q114] + != 3 + /\ + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q61, q114] + = + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q44, q110] + | q114 : int(1..2)])) + = + toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q44, q116] + != 3 + /\ + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q44, q116] + = + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q44, q110] + | q116 : int(1..2)])) + | q110 : int(1..2)]))) + | q85 : int(1..2)]) + \/ + or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q44, q86] != 3 /\ + !or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q61, q88] != 3 + /\ + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q61, q88] = + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q44, q86] + | q88 : int(1..2)]) + /\ + (toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q61, q90] + != 3 + /\ + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q61, q90] + = + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q44, q86] + | q90 : int(1..2)])) + < + toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q44, q92] + != 3 + /\ + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q44, q92] + = + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q44, q86] + | q92 : int(1..2)])) + /\ + (and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q61, q93] != + 3 + /\ + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q61, q93] < + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q44, q86] + -> + toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q61, q102] + != 3 + /\ + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q61, q102] + = + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q61, q93] + | q102 : int(1..2)])) + = + toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q44, q104] + != 3 + /\ + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q44, q104] + = + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q61, q93] + | q104 : int(1..2)])) + | q93 : int(1..2)]) + /\ + and([and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q44, q94] + != 3, + !or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q61, q96] + != 3 + /\ + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q61, q96] + = + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q44, q94] + | q96 : int(1..2)]), + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q44, q94] + < + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q44, q86]; + int(1..3)]) + -> + toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q61, q98] + != 3 + /\ + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q61, q98] + = + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q44, q94] + | q98 : int(1..2)])) + = + toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q44, q100] + != 3 + /\ + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q44, q100] + = + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q44, q94] + | q100 : int(1..2)])) + | q94 : int(1..2)]))) + | q86 : int(1..2)]); + int(1..3)]) + -> + toInt(or([q64 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ + (and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q64, q65] -> + or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q61, q67] + != 3 + /\ + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q61, q67] + = q65 + | q67 : int(1..2)]) + | q65 : int(1..2)]) + /\ + and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q61, q69] != + 3 + -> + a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence + [q64, + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q61, q69]] + | q69 : int(1..2)])) + | q64 : int(1..2)])) + = + toInt(or([q72 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ + and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q72, q73] = + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q61, q73] + | q73 : int(1..2)]) + | q72 : int(1..2)])) + | q61 : int(1..2)]))) + | q44 : int(1..2)]), + and([1 = + sum([toInt(q30 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ + a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q30, q1]) + | q30 : int(1..2)]) + | q1 : int(1..2)]), + and([q32 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> + sum([toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q32, q33]) | q33 : int(1..2)]) >= 1 + | q32 : int(1..2)]), + 2 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> + [-toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[1, q9]) | q9 : int(1..2)] a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> + and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q5, q11] = false | q11 : int(1..2)]) + | q5 : int(1..2)]), + a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker <= 2, + and([q6 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> + sum([toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q6, q7]) | q7 : int(1..2)]) <= 2 + | q6 : int(1..2)]), + 2 = + sum([toInt(q12 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker) * + catchUndef(sum([toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q12, q13]) + | q13 : int(1..2)]), + 0) + | q12 : int(1..2)]), + alldifferent_except([toInt(q34 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q34, q35] != + 3) + * + catchUndef(b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q34, q35], + 0) + | q34 : int(1..2), q35 : int(1..2)], + 0), + and([q36 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> + sum([toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q36, q38] != 3) + | q38 : int(1..2)]) + >= 1 + | q36 : int(1..2)]), + 2 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> + [b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[1, q25] | q25 : int(1..2)] b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> + and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q18, q31] = 1 + | q31 : int(1..2)]) + | q18 : int(1..2)]), + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker <= 2, + and([q19 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q19, 1] < + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q19, 2] + \/ b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q19, 1] = 3 + | q19 : int(1..2)]), + and([q19 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> + (b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q19, 1] = 3 -> + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q19, 2] = 3) + | q19 : int(1..2)]), + and([q19 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> + sum([toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q19, q22] != 3) + | q22 : int(1..2)]) + <= 2 + | q19 : int(1..2)]), + 2 = + sum([toInt(q27 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker) * + catchUndef(sum([toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q27, q29] != + 3) + | q29 : int(1..2)]), + 0) + | q27 : int(1..2)]) + diff --git a/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_1_3-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_1_3-solution000001.solution new file mode 100644 index 0000000000..cde05d5274 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_1_3-solution000001.solution @@ -0,0 +1,11 @@ +language Essence 1.3 + +letting a be partition({1, 2}) +$ Visualisation for a +$ 1 2 + +letting b be partition({1}, {2}) +$ Visualisation for b +$ 1 +$ 2 + diff --git a/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_1_3.eprime.orig b/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_1_3.eprime.orig deleted file mode 100644 index 83a08f385a..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_1_3.eprime.orig +++ /dev/null @@ -1,856 +0,0 @@ -language ESSENCE' 1.0 - -find a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker: int(0..2) -find a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence: matrix indexed by [int(1..2), int(1..2)] of bool -find b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker: int(0..2) -find b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker: - matrix indexed by [int(1..2)] of int(0..2) -find b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values: - matrix indexed by [int(1..2), int(1..2)] of int(1..2) -branching on - [a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker, - a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence, - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker, - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker, - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values] -such that - or([q37 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ - (toInt(or([q159 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ - and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q159, q160] = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q37, q160] - | q160 : int(1..2)]) - | q159 : int(1..2)])) - < - toInt(or([q164 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - (and([q166 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q164] - -> - a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence - [q37, - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q164, q166]] - | q166 : int(1..2)]) - /\ - and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q37, q167] -> - or([q169 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q164] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q164, q169] - = q167 - | q169 : int(1..2)]) - | q167 : int(1..2)])) - | q164 : int(1..2)])) - /\ - (and([q171 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ - (or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q171, q231] /\ - (toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q171, q231]) < - toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q37, q231]) - /\ - (and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q171, q232] -> - toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q171, q232]) = - toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q37, q232]) - | q232 : int(1..2), q232 < q231]) - /\ - and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q37, q232] /\ - !or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q171, q235] /\ - q235 = q232 - | q235 : int(1..2)]) - -> - toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q171, q232]) = - toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q37, q232]) - | q232 : int(1..2), q232 < q231]))) - | q231 : int(1..2)]) - \/ - or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q37, q231] /\ - !or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q171, q234] /\ q234 = q231 - | q234 : int(1..2)]) - /\ - (toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q171, q231]) < - toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q37, q231]) - /\ - (and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q171, q232] -> - toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q171, q232]) = - toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q37, q232]) - | q232 : int(1..2), q232 < q231]) - /\ - and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q37, q232] /\ - !or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q171, q233] /\ - q233 = q232 - | q233 : int(1..2)]) - -> - toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q171, q232]) = - toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q37, q232]) - | q232 : int(1..2), q232 < q231]))) - | q231 : int(1..2)])) - -> - toInt(or([q220 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ - and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q220, q221] = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q171, q221] - | q221 : int(1..2)]) - | q220 : int(1..2)])) - = - toInt(or([q225 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - (and([q227 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q225] - -> - a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence - [q171, - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q225, q227]] - | q227 : int(1..2)]) - /\ - and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q171, q228] -> - or([q230 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q225] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q225, q230] - = q228 - | q230 : int(1..2)]) - | q228 : int(1..2)])) - | q225 : int(1..2)])) - | q171 : int(1..2)]) - /\ - and([and([q173 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker, - !or([q189 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ - (and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q189, q190] -> - or([q192 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q173] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q173, q192] - = q190 - | q192 : int(1..2)]) - | q190 : int(1..2)]) - /\ - and([q194 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q173] - -> - a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence - [q189, - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q173, q194]] - | q194 : int(1..2)])) - | q189 : int(1..2)]), - or([q197 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q173] - /\ - (toInt(or([q210 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q173] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q173, q210] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q173, q197] - | q210 : int(1..2)])) - < - toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence - [q37, - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q173, q197]]) - /\ - (and([q211 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q173] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q173, q211] - < - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q173, q197] - -> - toInt(or([q217 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q173] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q173, q217] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q173, q211] - | q217 : int(1..2)])) - = - toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence - [q37, - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q173, q211]]) - | q211 : int(1..2)]) - /\ - and([and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q37, q196], - !or([q215 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q173] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q173, q215] - = q196 - | q215 : int(1..2)]), - q196 < - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q173, q197]; - int(1..3)]) - -> - toInt(or([q213 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q173] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q173, q213] - = q196 - | q213 : int(1..2)])) - = toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q37, q196]) - | q196 : int(1..2)]))) - | q197 : int(1..2)]) - \/ - or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q37, q195] /\ - !or([q208 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q173] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q173, q208] - = q195 - | q208 : int(1..2)]) - /\ - (toInt(or([q199 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q173] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q173, q199] - = q195 - | q199 : int(1..2)])) - < toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q37, q195]) - /\ - (and([q200 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q173] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q173, q200] - < q195 - -> - toInt(or([q206 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q173] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q173, q206] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q173, q200] - | q206 : int(1..2)])) - = - toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence - [q37, - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q173, q200]]) - | q200 : int(1..2)]) - /\ - and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q37, q196] /\ - !or([q204 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q173] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q173, q204] - = q196 - | q204 : int(1..2)]) - -> - toInt(or([q202 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q173] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q173, q202] - = q196 - | q202 : int(1..2)])) - = toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q37, q196]) - | q196 : int(1..2), q196 < q195]))) - | q195 : int(1..2)]); - int(1..3)]) - -> - toInt(or([q176 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ - (and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q176, q177] -> - or([q179 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q173] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q173, q179] - = q177 - | q179 : int(1..2)]) - | q177 : int(1..2)]) - /\ - and([q181 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q173] - -> - a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence - [q176, - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q173, q181]] - | q181 : int(1..2)])) - | q176 : int(1..2)])) - = - toInt(or([q184 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - (b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q184] = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q173] - /\ - and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q184, q185] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q173, q185] - | q185 : int(1..2)])) - | q184 : int(1..2)])) - | q173 : int(1..2)]))) - | q37 : int(1..2)]) - \/ - or([q39 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - !or([q151 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ - (and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q151, q152] -> - or([q154 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q39] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q39, q154] = - q152 - | q154 : int(1..2)]) - | q152 : int(1..2)]) - /\ - and([q156 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q39] -> - a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence - [q151, - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q39, q156]] - | q156 : int(1..2)])) - | q151 : int(1..2)]) - /\ - (toInt(or([q42 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ - (and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q42, q43] -> - or([q45 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q39] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q39, q45] - = q43 - | q45 : int(1..2)]) - | q43 : int(1..2)]) - /\ - and([q47 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q39] - -> - a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence - [q42, - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q39, q47]] - | q47 : int(1..2)])) - | q42 : int(1..2)])) - < - toInt(or([q50 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - (b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q50] = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q39] - /\ - and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q50, q51] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q39, q51] - | q51 : int(1..2)])) - | q50 : int(1..2)])) - /\ - (and([q54 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ - (or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q54, q129] /\ - (toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q54, q129]) < - toInt(or([q142 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q39] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q39, q142] - = q129 - | q142 : int(1..2)])) - /\ - (and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q54, q130] -> - toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q54, q130]) = - toInt(or([q148 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q39] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q39, q148] - = q130 - | q148 : int(1..2)])) - | q130 : int(1..2), q130 < q129]) - /\ - and([and([q143 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q39], - !or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q54, q146] /\ - q146 = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q39, q143] - | q146 : int(1..2)]), - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q39, q143] - < q129; - int(1..3)]) - -> - toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence - [q54, - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q39, q143]]) - = - toInt(or([q145 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q39] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q39, q145] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q39, q143] - | q145 : int(1..2)])) - | q143 : int(1..2)]))) - | q129 : int(1..2)]) - \/ - or([q131 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q39] /\ - !or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q54, q140] /\ - q140 = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q39, q131] - | q140 : int(1..2)]) - /\ - (toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence - [q54, - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q39, q131]]) - < - toInt(or([q133 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q39] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q39, q133] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q39, q131] - | q133 : int(1..2)])) - /\ - (and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q54, q130] /\ - q130 < - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q39, q131] - -> - toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q54, q130]) = - toInt(or([q139 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q39] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q39, q139] - = q130 - | q139 : int(1..2)])) - | q130 : int(1..2)]) - /\ - and([and([q134 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q39], - !or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q54, q137] /\ - q137 = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q39, q134] - | q137 : int(1..2)]), - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q39, q134] - < - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q39, q131]; - int(1..3)]) - -> - toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence - [q54, - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q39, q134]]) - = - toInt(or([q136 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q39] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q39, q136] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q39, q134] - | q136 : int(1..2)])) - | q134 : int(1..2)]))) - | q131 : int(1..2)])) - -> - toInt(or([q118 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ - and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q118, q119] = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q54, q119] - | q119 : int(1..2)]) - | q118 : int(1..2)])) - = - toInt(or([q123 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - (and([q125 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q123] - -> - a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence - [q54, - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q123, q125]] - | q125 : int(1..2)]) - /\ - and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q54, q126] -> - or([q128 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q123] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q123, q128] - = q126 - | q128 : int(1..2)]) - | q126 : int(1..2)])) - | q123 : int(1..2)])) - | q54 : int(1..2)]) - /\ - and([and([q56 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker, - !or([q72 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ - (and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q72, q73] -> - or([q75 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q56] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q56, q75] - = q73 - | q75 : int(1..2)]) - | q73 : int(1..2)]) - /\ - and([q77 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q56] - -> - a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence - [q72, - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q56, q77]] - | q77 : int(1..2)])) - | q72 : int(1..2)]), - or([q80 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q56] - /\ - (toInt(or([q101 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q56] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q56, q101] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q56, q80] - | q101 : int(1..2)])) - < - toInt(or([q103 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q39] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q39, q103] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q56, q80] - | q103 : int(1..2)])) - /\ - (and([q104 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q56] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q56, q104] - < - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q56, q80] - -> - toInt(or([q113 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q56] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q56, q113] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q56, q104] - | q113 : int(1..2)])) - = - toInt(or([q115 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q39] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q39, q115] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q56, q104] - | q115 : int(1..2)])) - | q104 : int(1..2)]) - /\ - and([and([q105 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q39], - !or([q111 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q56] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q56, q111] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q39, q105] - | q111 : int(1..2)]), - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q39, q105] - < - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q56, q80]; - int(1..3)]) - -> - toInt(or([q107 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q56] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q56, q107] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q39, q105] - | q107 : int(1..2)])) - = - toInt(or([q109 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q39] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q39, q109] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q39, q105] - | q109 : int(1..2)])) - | q105 : int(1..2)]))) - | q80 : int(1..2)]) - \/ - or([q81 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q39] - /\ - !or([q99 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q56] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q56, q99] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q39, q81] - | q99 : int(1..2)]) - /\ - (toInt(or([q83 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q56] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q56, q83] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q39, q81] - | q83 : int(1..2)])) - < - toInt(or([q85 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q39] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q39, q85] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q39, q81] - | q85 : int(1..2)])) - /\ - (and([q86 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q56] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q56, q86] - < - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q39, q81] - -> - toInt(or([q95 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q56] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q56, q95] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q56, q86] - | q95 : int(1..2)])) - = - toInt(or([q97 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q39] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q39, q97] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q56, q86] - | q97 : int(1..2)])) - | q86 : int(1..2)]) - /\ - and([and([q87 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q39], - !or([q93 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q56] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q56, q93] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q39, q87] - | q93 : int(1..2)]), - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q39, q87] - < - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q39, q81]; - int(1..3)]) - -> - toInt(or([q89 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q56] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q56, q89] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q39, q87] - | q89 : int(1..2)])) - = - toInt(or([q91 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q39] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q39, q91] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q39, q87] - | q91 : int(1..2)])) - | q87 : int(1..2)]))) - | q81 : int(1..2)]); - int(1..3)]) - -> - toInt(or([q59 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ - (and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q59, q60] -> - or([q62 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q56] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q56, q62] - = q60 - | q62 : int(1..2)]) - | q60 : int(1..2)]) - /\ - and([q64 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q56] - -> - a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence - [q59, - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q56, q64]] - | q64 : int(1..2)])) - | q59 : int(1..2)])) - = - toInt(or([q67 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - (b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q67] = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q56] - /\ - and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q67, q68] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q56, q68] - | q68 : int(1..2)])) - | q67 : int(1..2)])) - | q56 : int(1..2)]))) - | q39 : int(1..2)]), - and([1 = - sum([toInt(q27 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q27, q1]) - | q27 : int(1..2)]) - | q1 : int(1..2)]), - and([q29 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> - sum([toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q29, q30]) | q30 : int(1..2)]) >= 1 - | q29 : int(1..2)]), - 2 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> - [-toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[1, q9]) | q9 : int(1..2)] a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> - and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q5, q11] = false | q11 : int(1..2)]) - | q5 : int(1..2)]), - a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker <= 2, - and([q6 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> - sum([toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q6, q7]) | q7 : int(1..2)]) <= 2 - | q6 : int(1..2)]), - 2 = - sum([toInt(q12 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker) * - catchUndef(sum([toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q12, q13]) - | q13 : int(1..2)]), - 0) - | q12 : int(1..2)]), - alldifferent_except([toInt(q31 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - q32 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q31]) - * - catchUndef(b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q31, q32], - 0) - | q31 : int(1..2), q32 : int(1..2)], - 0), - and([q33 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q33] >= 1 - | q33 : int(1..2)]), - 2 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - flatten([[b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[1]; int(1)], - [b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[1, q24] - | q24 : int(1..2)]; - int(1..2)]) - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q18] = 0 /\ - and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q18, q28] = 1 - | q28 : int(1..2)]) - | q18 : int(1..2)]), - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker <= 2, - and([q19 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - (2 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q19] -> - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q19, 1] < - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q19, 2]) - | q19 : int(1..2)]), - and([q19 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - and([q21 > b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q19] -> - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q19, q21] = 1 - | q21 : int(1..2)]) - | q19 : int(1..2)]), - and([q19 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q19] <= 2 - | q19 : int(1..2)]), - 2 = - sum([toInt(q26 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker) * - catchUndef(b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q26], 0) - | q26 : int(1..2)]) - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_1_4-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_1_4-solution000001.solution new file mode 100644 index 0000000000..cde05d5274 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_1_4-solution000001.solution @@ -0,0 +1,11 @@ +language Essence 1.3 + +letting a be partition({1, 2}) +$ Visualisation for a +$ 1 2 + +letting b be partition({1}, {2}) +$ Visualisation for b +$ 1 +$ 2 + diff --git a/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_1_4.eprime b/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_1_4.eprime new file mode 100644 index 0000000000..5e65b4ba3b --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_1_4.eprime @@ -0,0 +1,382 @@ +language ESSENCE' 1.0 + +find a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker: int(0..2) +find a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence: matrix indexed by [int(1..2), int(1..2)] of bool +find b_PartitionOccurrence_NumParts: int(1..2) +find b_PartitionOccurrence_WhichPart: matrix indexed by [int(1..2)] of int(1..2) +find b_PartitionOccurrence_PartSizes: matrix indexed by [int(1..2)] of int(0..2) +find b_PartitionOccurrence_FirstIndex: matrix indexed by [int(1..2)] of int(1..2) +branching on + [a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker, + a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence, b_PartitionOccurrence_NumParts, + b_PartitionOccurrence_WhichPart, b_PartitionOccurrence_PartSizes, b_PartitionOccurrence_FirstIndex] +such that + or([q30 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ + (toInt(or([q144 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ + and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q144, q145] = + a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q30, q145] + | q145 : int(1..2)]) + | q144 : int(1..2)])) + < + toInt(or([q148 <= b_PartitionOccurrence_NumParts /\ + (and([b_PartitionOccurrence_WhichPart[q151] = q148 -> + a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q30, q151] + | q151 : int(1..2)]) + /\ + and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q30, q152] -> + or([b_PartitionOccurrence_WhichPart[q154] = q148 /\ q154 = q152 | q154 : int(1..2)]) + | q152 : int(1..2)])) + | q148 : int(1..2)])) + /\ + (and([q156 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ + (or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q156, q222] /\ + (toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q156, q222]) < + toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q30, q222]) + /\ + (and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q156, q223] -> + toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q156, q223]) = + toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q30, q223]) + | q223 : int(1..2), q223 < q222]) + /\ + and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q30, q223] /\ + !or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q156, q226] /\ + q226 = q223 + | q226 : int(1..2)]) + -> + toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q156, q223]) = + toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q30, q223]) + | q223 : int(1..2), q223 < q222]))) + | q222 : int(1..2)]) + \/ + or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q30, q222] /\ + !or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q156, q225] /\ q225 = q222 + | q225 : int(1..2)]) + /\ + (toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q156, q222]) < + toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q30, q222]) + /\ + (and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q156, q223] -> + toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q156, q223]) = + toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q30, q223]) + | q223 : int(1..2), q223 < q222]) + /\ + and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q30, q223] /\ + !or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q156, q224] /\ + q224 = q223 + | q224 : int(1..2)]) + -> + toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q156, q223]) = + toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q30, q223]) + | q223 : int(1..2), q223 < q222]))) + | q222 : int(1..2)])) + -> + toInt(or([q211 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ + and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q211, q212] = + a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q156, q212] + | q212 : int(1..2)]) + | q211 : int(1..2)])) + = + toInt(or([q215 <= b_PartitionOccurrence_NumParts /\ + (and([b_PartitionOccurrence_WhichPart[q218] = q215 -> + a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q156, q218] + | q218 : int(1..2)]) + /\ + and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q156, q219] -> + or([b_PartitionOccurrence_WhichPart[q221] = q215 /\ q221 = q219 | q221 : int(1..2)]) + | q219 : int(1..2)])) + | q215 : int(1..2)])) + | q156 : int(1..2)]) + /\ + and([and([q157 <= b_PartitionOccurrence_NumParts, + !or([q172 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ + (and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q172, q173] -> + or([b_PartitionOccurrence_WhichPart[q175] = q157 /\ q175 = q173 | q175 : int(1..2)]) + | q173 : int(1..2)]) + /\ + and([b_PartitionOccurrence_WhichPart[q177] = q157 -> + a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q172, q177] + | q177 : int(1..2)])) + | q172 : int(1..2)]), + or([b_PartitionOccurrence_WhichPart[q180] = q157 /\ + (sum([toInt(b_PartitionOccurrence_WhichPart[q193] = q157) * catchUndef(toInt(q193 = q180), 0) + | q193 : int(1..2)]) + < toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q30, q180]) + /\ + (and([b_PartitionOccurrence_WhichPart[q194] = q157 -> + sum([toInt(b_PartitionOccurrence_WhichPart[q200] = q157) * + catchUndef(toInt(q200 = q194), 0) + | q200 : int(1..2)]) + = toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q30, q194]) + | q194 : int(1..2), q194 < q180]) + /\ + and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q30, q179] /\ + !or([b_PartitionOccurrence_WhichPart[q198] = q157 /\ q198 = q179 | q198 : int(1..2)]) + -> + sum([toInt(b_PartitionOccurrence_WhichPart[q196] = q157) * + catchUndef(toInt(q196 = q179), 0) + | q196 : int(1..2)]) + = toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q30, q179]) + | q179 : int(1..2), q179 < q180]))) + | q180 : int(1..2)]) + \/ + or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q30, q178] /\ + !or([b_PartitionOccurrence_WhichPart[q191] = q157 /\ q191 = q178 | q191 : int(1..2)]) + /\ + (sum([toInt(b_PartitionOccurrence_WhichPart[q182] = q157) * catchUndef(toInt(q182 = q178), 0) + | q182 : int(1..2)]) + < toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q30, q178]) + /\ + (and([b_PartitionOccurrence_WhichPart[q183] = q157 -> + sum([toInt(b_PartitionOccurrence_WhichPart[q189] = q157) * + catchUndef(toInt(q189 = q183), 0) + | q189 : int(1..2)]) + = toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q30, q183]) + | q183 : int(1..2), q183 < q178]) + /\ + and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q30, q179] /\ + !or([b_PartitionOccurrence_WhichPart[q187] = q157 /\ q187 = q179 | q187 : int(1..2)]) + -> + sum([toInt(b_PartitionOccurrence_WhichPart[q185] = q157) * + catchUndef(toInt(q185 = q179), 0) + | q185 : int(1..2)]) + = toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q30, q179]) + | q179 : int(1..2), q179 < q178]))) + | q178 : int(1..2)]); + int(1..3)]) + -> + toInt(or([q203 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ + (and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q203, q204] -> + or([b_PartitionOccurrence_WhichPart[q206] = q157 /\ q206 = q204 | q206 : int(1..2)]) + | q204 : int(1..2)]) + /\ + and([b_PartitionOccurrence_WhichPart[q208] = q157 -> + a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q203, q208] + | q208 : int(1..2)])) + | q203 : int(1..2)])) + = + toInt(or([q160 <= b_PartitionOccurrence_NumParts /\ + (and([b_PartitionOccurrence_WhichPart[q163] = q160 -> + or([b_PartitionOccurrence_WhichPart[q165] = q157 /\ q165 = q163 | q165 : int(1..2)]) + | q163 : int(1..2)]) + /\ + and([b_PartitionOccurrence_WhichPart[q167] = q157 -> + or([b_PartitionOccurrence_WhichPart[q169] = q160 /\ q169 = q167 | q169 : int(1..2)]) + | q167 : int(1..2)])) + | q160 : int(1..2)])) + | q157 : int(1..2)]))) + | q30 : int(1..2)]) + \/ + or([q31 <= b_PartitionOccurrence_NumParts /\ + !or([q136 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ + (and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q136, q137] -> + or([b_PartitionOccurrence_WhichPart[q139] = q31 /\ q139 = q137 | q139 : int(1..2)]) + | q137 : int(1..2)]) + /\ + and([b_PartitionOccurrence_WhichPart[q141] = q31 -> + a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q136, q141] + | q141 : int(1..2)])) + | q136 : int(1..2)]) + /\ + (toInt(or([q128 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ + (and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q128, q129] -> + or([b_PartitionOccurrence_WhichPart[q131] = q31 /\ q131 = q129 | q131 : int(1..2)]) + | q129 : int(1..2)]) + /\ + and([b_PartitionOccurrence_WhichPart[q133] = q31 -> + a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q128, q133] + | q133 : int(1..2)])) + | q128 : int(1..2)])) + < + toInt(or([q34 <= b_PartitionOccurrence_NumParts /\ + (and([b_PartitionOccurrence_WhichPart[q37] = q34 -> + or([b_PartitionOccurrence_WhichPart[q39] = q31 /\ q39 = q37 | q39 : int(1..2)]) + | q37 : int(1..2)]) + /\ + and([b_PartitionOccurrence_WhichPart[q41] = q31 -> + or([b_PartitionOccurrence_WhichPart[q43] = q34 /\ q43 = q41 | q43 : int(1..2)]) + | q41 : int(1..2)])) + | q34 : int(1..2)])) + /\ + (and([q65 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ + (or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q65, q44] /\ + (toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q65, q44]) < + sum([toInt(b_PartitionOccurrence_WhichPart[q57] = q31) * catchUndef(toInt(q57 = q44), 0) + | q57 : int(1..2)]) + /\ + (and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q65, q45] -> + toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q65, q45]) = + sum([toInt(b_PartitionOccurrence_WhichPart[q63] = q31) * catchUndef(toInt(q63 = q45), 0) + | q63 : int(1..2)]) + | q45 : int(1..2), q45 < q44]) + /\ + and([!or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q65, q61] /\ q61 = q58 + | q61 : int(1..2)]) + -> + (b_PartitionOccurrence_WhichPart[q58] = q31 -> + toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q65, q58]) = + sum([toInt(b_PartitionOccurrence_WhichPart[q60] = q31) * catchUndef(toInt(q60 = q58), 0) + | q60 : int(1..2)])) + | q58 : int(1..2), q58 < q44]))) + | q44 : int(1..2)]) + \/ + or([!or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q65, q55] /\ q55 = q46 + | q55 : int(1..2)]) + /\ + (b_PartitionOccurrence_WhichPart[q46] = q31 /\ + (toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q65, q46]) < + sum([toInt(b_PartitionOccurrence_WhichPart[q48] = q31) * catchUndef(toInt(q48 = q46), 0) + | q48 : int(1..2)]) + /\ + (and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q65, q45] -> + toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q65, q45]) = + sum([toInt(b_PartitionOccurrence_WhichPart[q54] = q31) * catchUndef(toInt(q54 = q45), 0) + | q54 : int(1..2)]) + | q45 : int(1..2), q45 < q46]) + /\ + and([!or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q65, q52] /\ q52 = q49 + | q52 : int(1..2)]) + -> + (b_PartitionOccurrence_WhichPart[q49] = q31 -> + toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q65, q49]) = + sum([toInt(b_PartitionOccurrence_WhichPart[q51] = q31) * catchUndef(toInt(q51 = q49), 0) + | q51 : int(1..2)])) + | q49 : int(1..2), q49 < q46])))) + | q46 : int(1..2)])) + -> + toInt(or([q115 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ + and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q115, q116] = + a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q65, q116] + | q116 : int(1..2)]) + | q115 : int(1..2)])) + = + toInt(or([q119 <= b_PartitionOccurrence_NumParts /\ + (and([b_PartitionOccurrence_WhichPart[q122] = q119 -> + a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q65, q122] + | q122 : int(1..2)]) + /\ + and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q65, q123] -> + or([b_PartitionOccurrence_WhichPart[q125] = q119 /\ q125 = q123 | q125 : int(1..2)]) + | q123 : int(1..2)])) + | q119 : int(1..2)])) + | q65 : int(1..2)]) + /\ + and([and([q66 <= b_PartitionOccurrence_NumParts, + !or([q81 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ + (and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q81, q82] -> + or([b_PartitionOccurrence_WhichPart[q84] = q66 /\ q84 = q82 | q84 : int(1..2)]) + | q82 : int(1..2)]) + /\ + and([b_PartitionOccurrence_WhichPart[q86] = q66 -> + a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q81, q86] + | q86 : int(1..2)])) + | q81 : int(1..2)]), + or([b_PartitionOccurrence_WhichPart[q95] = q66 /\ + (toInt(or([b_PartitionOccurrence_WhichPart[q88] = q66 /\ q88 = q95 | q88 : int(1..2)])) < + sum([toInt(b_PartitionOccurrence_WhichPart[q57] = q31) * catchUndef(toInt(q57 = q95), 0) + | q57 : int(1..2)]) + /\ + (and([b_PartitionOccurrence_WhichPart[q91] = q66 -> + toInt(or([b_PartitionOccurrence_WhichPart[q90] = q66 /\ q90 = q91 | q90 : int(1..2)])) = + sum([toInt(b_PartitionOccurrence_WhichPart[q63] = q31) * catchUndef(toInt(q63 = q91), 0) + | q63 : int(1..2)]) + | q91 : int(1..2), q91 < q95]) + /\ + and([!or([b_PartitionOccurrence_WhichPart[q94] = q66 /\ q94 = q58 | q94 : int(1..2)]) -> + (b_PartitionOccurrence_WhichPart[q58] = q31 -> + toInt(or([b_PartitionOccurrence_WhichPart[q93] = q66 /\ q93 = q58 | q93 : int(1..2)])) = + sum([toInt(b_PartitionOccurrence_WhichPart[q60] = q31) * catchUndef(toInt(q60 = q58), 0) + | q60 : int(1..2)])) + | q58 : int(1..2), q58 < q95]))) + | q95 : int(1..2)]) + \/ + or([!or([b_PartitionOccurrence_WhichPart[q104] = q66 /\ q104 = q46 | q104 : int(1..2)]) /\ + (b_PartitionOccurrence_WhichPart[q46] = q31 /\ + (toInt(or([b_PartitionOccurrence_WhichPart[q97] = q66 /\ q97 = q46 | q97 : int(1..2)])) < + sum([toInt(b_PartitionOccurrence_WhichPart[q48] = q31) * catchUndef(toInt(q48 = q46), 0) + | q48 : int(1..2)]) + /\ + (and([b_PartitionOccurrence_WhichPart[q100] = q66 -> + toInt(or([b_PartitionOccurrence_WhichPart[q99] = q66 /\ q99 = q100 | q99 : int(1..2)])) + = + sum([toInt(b_PartitionOccurrence_WhichPart[q54] = q31) * + catchUndef(toInt(q54 = q100), 0) + | q54 : int(1..2)]) + | q100 : int(1..2), q100 < q46]) + /\ + and([!or([b_PartitionOccurrence_WhichPart[q103] = q66 /\ q103 = q49 | q103 : int(1..2)]) -> + (b_PartitionOccurrence_WhichPart[q49] = q31 -> + toInt(or([b_PartitionOccurrence_WhichPart[q102] = q66 /\ q102 = q49 + | q102 : int(1..2)])) + = + sum([toInt(b_PartitionOccurrence_WhichPart[q51] = q31) * + catchUndef(toInt(q51 = q49), 0) + | q51 : int(1..2)])) + | q49 : int(1..2), q49 < q46])))) + | q46 : int(1..2)]); + int(1..3)]) + -> + toInt(or([q107 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ + (and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q107, q108] -> + or([b_PartitionOccurrence_WhichPart[q110] = q66 /\ q110 = q108 | q110 : int(1..2)]) + | q108 : int(1..2)]) + /\ + and([b_PartitionOccurrence_WhichPart[q112] = q66 -> + a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q107, q112] + | q112 : int(1..2)])) + | q107 : int(1..2)])) + = + toInt(or([q69 <= b_PartitionOccurrence_NumParts /\ + (and([b_PartitionOccurrence_WhichPart[q72] = q69 -> + or([b_PartitionOccurrence_WhichPart[q74] = q66 /\ q74 = q72 | q74 : int(1..2)]) + | q72 : int(1..2)]) + /\ + and([b_PartitionOccurrence_WhichPart[q76] = q66 -> + or([b_PartitionOccurrence_WhichPart[q78] = q69 /\ q78 = q76 | q78 : int(1..2)]) + | q76 : int(1..2)])) + | q69 : int(1..2)])) + | q66 : int(1..2)]))) + | q31 : int(1..2)]), + and([1 = + sum([toInt(q24 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ + a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q24, q1]) + | q24 : int(1..2)]) + | q1 : int(1..2)]), + and([q25 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> + sum([toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q25, q26]) | q26 : int(1..2)]) >= 1 + | q25 : int(1..2)]), + 2 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> + [-toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[1, q9]) | q9 : int(1..2)] a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> + and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q5, q11] = false | q11 : int(1..2)]) + | q5 : int(1..2)]), + a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker <= 2, + and([q6 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> + sum([toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q6, q7]) | q7 : int(1..2)]) <= 2 + | q6 : int(1..2)]), + 2 = + sum([toInt(q12 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker) * + catchUndef(sum([toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q12, q13]) + | q13 : int(1..2)]), + 0) + | q12 : int(1..2)]), + and([q14 <= b_PartitionOccurrence_NumParts -> b_PartitionOccurrence_PartSizes[q14] <= 2 | q14 : int(1..2)]), + and([q14 > b_PartitionOccurrence_NumParts -> b_PartitionOccurrence_PartSizes[q14] = 0 | q14 : int(1..2)]), + b_PartitionOccurrence_NumParts <= 2, + b_PartitionOccurrence_NumParts = max([b_PartitionOccurrence_WhichPart[q17] | q17 : int(1..2)]), + and([b_PartitionOccurrence_PartSizes[q18] = + sum([toInt(b_PartitionOccurrence_WhichPart[q19] = q18) | q19 : int(1..2)]) + | q18 : int(1..2)]), + and([q20 <= b_PartitionOccurrence_NumParts -> + and([b_PartitionOccurrence_WhichPart[q21] = q20 -> b_PartitionOccurrence_FirstIndex[q20] <= q21 + | q21 : int(1..2)]) + | q20 : int(1..2)]), + and([q20 <= b_PartitionOccurrence_NumParts -> + or([b_PartitionOccurrence_WhichPart[q21] = q20 /\ b_PartitionOccurrence_FirstIndex[q20] = q21 + | q21 : int(1..2)]) + | q20 : int(1..2)]), + and([q20 > b_PartitionOccurrence_NumParts -> b_PartitionOccurrence_FirstIndex[q20] = 1 | q20 : int(1..2)]), + and([q22 <= b_PartitionOccurrence_NumParts /\ q23 <= b_PartitionOccurrence_NumParts -> + (q22 < q23 <-> b_PartitionOccurrence_FirstIndex[q22] < b_PartitionOccurrence_FirstIndex[q23]) + | q22 : int(1..2), q23 : int(1..2)]) + diff --git a/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_2_1-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_2_1-solution000001.solution new file mode 100644 index 0000000000..cde05d5274 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_2_1-solution000001.solution @@ -0,0 +1,11 @@ +language Essence 1.3 + +letting a be partition({1, 2}) +$ Visualisation for a +$ 1 2 + +letting b be partition({1}, {2}) +$ Visualisation for b +$ 1 +$ 2 + diff --git a/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_2_1.eprime b/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_2_1.eprime new file mode 100644 index 0000000000..917ebeb2c9 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_2_1.eprime @@ -0,0 +1,761 @@ +language ESSENCE' 1.0 + +find a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker: int(0..2) +find a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy: + matrix indexed by [int(1..2), int(1..2)] of int(1..3) +find b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker: int(0..2) +find b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence: matrix indexed by [int(1..2), int(1..2)] of bool +branching on + [a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker, + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy, + b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker, + b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence] +such that + or([q42 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ + (toInt(or([q134 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ + and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q134, q135] = + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q42, q135] + | q135 : int(1..2)]) + | q134 : int(1..2)])) + < + toInt(or([q139 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ + (and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q139, q140] -> + or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q42, q142] != + 3 + /\ + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q42, q142] = + q140 + | q142 : int(1..2)]) + | q140 : int(1..2)]) + /\ + and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q42, q144] != 3 -> + b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence + [q139, + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q42, q144]] + | q144 : int(1..2)])) + | q139 : int(1..2)])) + /\ + (and([q146 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ + (or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q146, q205] != 3 /\ + (toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q146, q226] + != 3 + /\ + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q146, q226] + = + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q146, q205] + | q226 : int(1..2)])) + < + toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q42, q228] + != 3 + /\ + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q42, q228] = + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q146, q205] + | q228 : int(1..2)])) + /\ + (and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q146, q229] != 3 + /\ + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q146, q229] < + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q146, q205] + -> + toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q146, q238] + != 3 + /\ + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q146, q238] + = + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q146, q229] + | q238 : int(1..2)])) + = + toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q42, q240] + != 3 + /\ + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q42, q240] + = + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q146, q229] + | q240 : int(1..2)])) + | q229 : int(1..2)]) + /\ + and([and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q42, q230] + != 3, + !or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q146, q232] + != 3 + /\ + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q146, q232] + = + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q42, q230] + | q232 : int(1..2)]), + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q42, q230] + < + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q146, q205]; + int(1..3)]) + -> + toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q146, q234] + != 3 + /\ + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q146, q234] + = + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q42, q230] + | q234 : int(1..2)])) + = + toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q42, q236] + != 3 + /\ + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q42, q236] + = + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q42, q230] + | q236 : int(1..2)])) + | q230 : int(1..2)]))) + | q205 : int(1..2)]) + \/ + or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q42, q206] != 3 /\ + !or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q146, q208] != 3 + /\ + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q146, q208] = + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q42, q206] + | q208 : int(1..2)]) + /\ + (toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q146, q210] + != 3 + /\ + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q146, q210] + = a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q42, q206] + | q210 : int(1..2)])) + < + toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q42, q212] + != 3 + /\ + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q42, q212] = + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q42, q206] + | q212 : int(1..2)])) + /\ + (and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q146, q213] != 3 + /\ + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q146, q213] < + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q42, q206] + -> + toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q146, q222] + != 3 + /\ + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q146, q222] + = + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q146, q213] + | q222 : int(1..2)])) + = + toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q42, q224] + != 3 + /\ + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q42, q224] + = + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q146, q213] + | q224 : int(1..2)])) + | q213 : int(1..2)]) + /\ + and([and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q42, q214] + != 3, + !or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q146, q216] + != 3 + /\ + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q146, q216] + = + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q42, q214] + | q216 : int(1..2)]), + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q42, q214] + < + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q42, q206]; + int(1..3)]) + -> + toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q146, q218] + != 3 + /\ + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q146, q218] + = + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q42, q214] + | q218 : int(1..2)])) + = + toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q42, q220] + != 3 + /\ + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q42, q220] + = + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q42, q214] + | q220 : int(1..2)])) + | q214 : int(1..2)]))) + | q206 : int(1..2)])) + -> + toInt(or([q192 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ + and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q192, q193] = + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q146, q193] + | q193 : int(1..2)]) + | q192 : int(1..2)])) + = + toInt(or([q197 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ + (and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q197, q198] -> + or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q146, q200] + != 3 + /\ + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q146, q200] + = q198 + | q200 : int(1..2)]) + | q198 : int(1..2)]) + /\ + and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q146, q202] + != 3 + -> + b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence + [q197, + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q146, q202]] + | q202 : int(1..2)])) + | q197 : int(1..2)])) + | q146 : int(1..2)]) + /\ + and([and([q148 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker, + !or([q164 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ + (and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q164, q166] + != 3 + -> + b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence + [q148, + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q164, q166]] + | q166 : int(1..2)]) + /\ + and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q148, q167] -> + or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q164, q169] + != 3 + /\ + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q164, q169] + = q167 + | q169 : int(1..2)]) + | q167 : int(1..2)])) + | q164 : int(1..2)]), + or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q148, q170] /\ + (toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q148, q170]) < + toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q42, q183] + != 3 + /\ + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q42, q183] + = q170 + | q183 : int(1..2)])) + /\ + (and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q148, q171] -> + toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q148, q171]) = + toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q42, q189] + != 3 + /\ + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q42, q189] + = q171 + | q189 : int(1..2)])) + | q171 : int(1..2), q171 < q170]) + /\ + and([and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q42, q184] + != 3, + !or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q148, q185] /\ + q185 = + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q42, q184] + | q185 : int(1..2)]), + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q42, q184] + < q170; + int(1..3)]) + -> + toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence + [q148, + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q42, q184]]) + = + toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q42, q187] + != 3 + /\ + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q42, q187] + = + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q42, q184] + | q187 : int(1..2)])) + | q184 : int(1..2)]))) + | q170 : int(1..2)]) + \/ + or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q42, q172] != 3 /\ + !or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q148, q173] /\ + q173 = + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q42, q172] + | q173 : int(1..2)]) + /\ + (toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence + [q148, + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q42, q172]]) + < + toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q42, q175] + != 3 + /\ + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q42, q175] + = + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q42, q172] + | q175 : int(1..2)])) + /\ + (and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q148, q171] /\ + q171 < + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q42, q172] + -> + toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q148, q171]) = + toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q42, q181] + != 3 + /\ + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q42, q181] + = q171 + | q181 : int(1..2)])) + | q171 : int(1..2)]) + /\ + and([and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q42, q176] + != 3, + !or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q148, q177] /\ + q177 = + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q42, q176] + | q177 : int(1..2)]), + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q42, q176] + < + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q42, q172]; + int(1..3)]) + -> + toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence + [q148, + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q42, q176]]) + = + toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q42, q179] + != 3 + /\ + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q42, q179] + = + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q42, q176] + | q179 : int(1..2)])) + | q176 : int(1..2)]))) + | q172 : int(1..2)]); + int(1..3)]) + -> + toInt(or([q151 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ + (and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q151, q153] + != 3 + -> + b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence + [q148, + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q151, q153]] + | q153 : int(1..2)]) + /\ + and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q148, q154] -> + or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q151, q156] + != 3 + /\ + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q151, q156] + = q154 + | q156 : int(1..2)]) + | q154 : int(1..2)])) + | q151 : int(1..2)])) + = + toInt(or([q159 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ + and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q159, q160] = + b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q148, q160] + | q160 : int(1..2)]) + | q159 : int(1..2)])) + | q148 : int(1..2)]))) + | q42 : int(1..2)]) + \/ + or([q44 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ + !or([q126 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ + (and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q126, q128] != 3 -> + b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence + [q44, a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q126, q128]] + | q128 : int(1..2)]) + /\ + and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q44, q129] -> + or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q126, q131] != 3 /\ + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q126, q131] = q129 + | q131 : int(1..2)]) + | q129 : int(1..2)])) + | q126 : int(1..2)]) + /\ + (toInt(or([q47 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ + (and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q47, q49] != 3 -> + b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence + [q44, + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q47, q49]] + | q49 : int(1..2)]) + /\ + and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q44, q50] -> + or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q47, q52] != 3 + /\ + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q47, q52] = + q50 | q52 : int(1..2)]) + | q50 : int(1..2)])) + | q47 : int(1..2)])) + < + toInt(or([q55 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ + and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q55, q56] = + b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q44, q56] + | q56 : int(1..2)]) + | q55 : int(1..2)])) + /\ + (and([q59 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ + (or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q59, q103] != 3 /\ + (toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q59, q116] + != 3 + /\ + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q59, q116] = + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q59, q103] + | q116 : int(1..2)])) + < + toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence + [q44, + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q59, q103]]) + /\ + (and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q59, q117] != 3 + /\ + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q59, q117] < + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q59, q103] + -> + toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q59, q123] + != 3 + /\ + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q59, q123] + = + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q59, q117] + | q123 : int(1..2)])) + = + toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence + [q44, + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q59, q117]]) + | q117 : int(1..2)]) + /\ + and([and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q44, q102], + !or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q59, q121] + != 3 + /\ + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q59, q121] + = q102 + | q121 : int(1..2)]), + q102 < + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q59, q103]; + int(1..3)]) + -> + toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q59, q119] + != 3 + /\ + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q59, q119] + = q102 + | q119 : int(1..2)])) + = toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q44, q102]) + | q102 : int(1..2)]))) + | q103 : int(1..2)]) + \/ + or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q44, q101] /\ + !or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q59, q114] != 3 /\ + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q59, q114] = q101 + | q114 : int(1..2)]) + /\ + (toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q59, q105] + != 3 + /\ + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q59, q105] = + q101 + | q105 : int(1..2)])) + < toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q44, q101]) + /\ + (and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q59, q106] != 3 + /\ + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q59, q106] < + q101 + -> + toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q59, q112] + != 3 + /\ + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q59, q112] + = + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q59, q106] + | q112 : int(1..2)])) + = + toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence + [q44, + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q59, q106]]) + | q106 : int(1..2)]) + /\ + and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q44, q102] /\ + !or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q59, q110] + != 3 + /\ + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q59, q110] + = q102 + | q110 : int(1..2)]) + -> + toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q59, q108] + != 3 + /\ + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q59, q108] + = q102 + | q108 : int(1..2)])) + = toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q44, q102]) + | q102 : int(1..2), q102 < q101]))) + | q101 : int(1..2)])) + -> + toInt(or([q90 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ + and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q90, q91] = + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q59, q91] + | q91 : int(1..2)]) + | q90 : int(1..2)])) + = + toInt(or([q95 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ + (and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q95, q96] -> + or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q59, q98] + != 3 + /\ + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q59, q98] + = q96 + | q98 : int(1..2)]) + | q96 : int(1..2)]) + /\ + and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q59, q100] + != 3 + -> + b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence + [q95, + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q59, q100]] + | q100 : int(1..2)])) + | q95 : int(1..2)])) + | q59 : int(1..2)]) + /\ + and([and([q61 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker, + !or([q77 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ + (and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q77, q79] != + 3 + -> + b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence + [q61, + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q77, q79]] + | q79 : int(1..2)]) + /\ + and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q61, q80] -> + or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q77, q82] + != 3 + /\ + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q77, q82] + = q80 + | q82 : int(1..2)]) + | q80 : int(1..2)])) + | q77 : int(1..2)]), + or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q61, q83] /\ + (toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q61, q83]) < + toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q44, q83]) + /\ + (and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q61, q84] -> + toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q61, q84]) = + toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q44, q84]) + | q84 : int(1..2), q84 < q83]) + /\ + and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q44, q84] /\ + !or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q61, q87] /\ + q87 = q84 + | q87 : int(1..2)]) + -> + toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q61, q84]) = + toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q44, q84]) + | q84 : int(1..2), q84 < q83]))) + | q83 : int(1..2)]) + \/ + or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q44, q83] /\ + !or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q61, q86] /\ q86 = q83 + | q86 : int(1..2)]) + /\ + (toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q61, q83]) < + toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q44, q83]) + /\ + (and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q61, q84] -> + toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q61, q84]) = + toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q44, q84]) + | q84 : int(1..2), q84 < q83]) + /\ + and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q44, q84] /\ + !or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q61, q85] /\ + q85 = q84 + | q85 : int(1..2)]) + -> + toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q61, q84]) = + toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q44, q84]) + | q84 : int(1..2), q84 < q83]))) + | q83 : int(1..2)]); + int(1..3)]) + -> + toInt(or([q64 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ + (and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q64, q66] != + 3 + -> + b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence + [q61, + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q64, q66]] + | q66 : int(1..2)]) + /\ + and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q61, q67] -> + or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q64, q69] + != 3 + /\ + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q64, q69] + = q67 + | q69 : int(1..2)]) + | q67 : int(1..2)])) + | q64 : int(1..2)])) + = + toInt(or([q72 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ + and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q72, q73] = + b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q61, q73] + | q73 : int(1..2)]) + | q72 : int(1..2)])) + | q61 : int(1..2)]))) + | q44 : int(1..2)]), + alldifferent_except([toInt(q34 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q34, q35] != + 3) + * + catchUndef(a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q34, q35], + 0) + | q34 : int(1..2), q35 : int(1..2)], + 0), + and([q36 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> + sum([toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q36, q38] != 3) + | q38 : int(1..2)]) + >= 1 + | q36 : int(1..2)]), + 2 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> + [a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[1, q12] | q12 : int(1..2)] a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> + and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q5, q30] = 1 + | q30 : int(1..2)]) + | q5 : int(1..2)]), + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker <= 2, + and([q6 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q6, 1] < + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q6, 2] + \/ a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q6, 1] = 3 + | q6 : int(1..2)]), + and([q6 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> + (a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q6, 1] = 3 -> + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q6, 2] = 3) + | q6 : int(1..2)]), + and([q6 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> + sum([toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q6, q9] != 3) + | q9 : int(1..2)]) + <= 2 + | q6 : int(1..2)]), + 2 = + sum([toInt(q14 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker) * + catchUndef(sum([toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q14, q16] != + 3) + | q16 : int(1..2)]), + 0) + | q14 : int(1..2)]), + and([1 = + sum([toInt(q31 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ + b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q31, q17]) + | q31 : int(1..2)]) + | q17 : int(1..2)]), + and([q32 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> + sum([toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q32, q33]) | q33 : int(1..2)]) >= 1 + | q32 : int(1..2)]), + 2 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> + [-toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[1, q25]) | q25 : int(1..2)] b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> + and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q21, q27] = false | q27 : int(1..2)]) + | q21 : int(1..2)]), + b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker <= 2, + and([q22 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> + sum([toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q22, q23]) | q23 : int(1..2)]) <= 2 + | q22 : int(1..2)]), + 2 = + sum([toInt(q28 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker) * + catchUndef(sum([toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q28, q29]) + | q29 : int(1..2)]), + 0) + | q28 : int(1..2)]) + diff --git a/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_2_2-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_2_2-solution000001.solution new file mode 100644 index 0000000000..cde05d5274 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_2_2-solution000001.solution @@ -0,0 +1,11 @@ +language Essence 1.3 + +letting a be partition({1, 2}) +$ Visualisation for a +$ 1 2 + +letting b be partition({1}, {2}) +$ Visualisation for b +$ 1 +$ 2 + diff --git a/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_2_2.eprime b/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_2_2.eprime new file mode 100644 index 0000000000..2f788f30c5 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_2_2.eprime @@ -0,0 +1,949 @@ +language ESSENCE' 1.0 + +find a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker: int(0..2) +find a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy: + matrix indexed by [int(1..2), int(1..2)] of int(1..3) +find b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker: int(0..2) +find b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy: + matrix indexed by [int(1..2), int(1..2)] of int(1..3) +branching on + [a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker, + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy, + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker, + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy] +such that + or([q48 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ + (toInt(or([q173 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ + and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q173, q174] = + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q48, q174] + | q174 : int(1..2)]) + | q173 : int(1..2)])) + < + toInt(or([q178 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ + and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q178, q179] = + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q48, q179] + | q179 : int(1..2)]) + | q178 : int(1..2)])) + /\ + (and([q182 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ + (or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q182, q250] != 3 /\ + (toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q182, q271] + != 3 + /\ + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q182, q271] + = + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q182, q250] + | q271 : int(1..2)])) + < + toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q48, q273] + != 3 + /\ + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q48, q273] = + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q182, q250] + | q273 : int(1..2)])) + /\ + (and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q182, q274] != 3 + /\ + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q182, q274] < + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q182, q250] + -> + toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q182, q283] + != 3 + /\ + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q182, q283] + = + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q182, q274] + | q283 : int(1..2)])) + = + toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q48, q285] + != 3 + /\ + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q48, q285] + = + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q182, q274] + | q285 : int(1..2)])) + | q274 : int(1..2)]) + /\ + and([and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q48, q275] + != 3, + !or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q182, q277] + != 3 + /\ + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q182, q277] + = + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q48, q275] + | q277 : int(1..2)]), + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q48, q275] + < + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q182, q250]; + int(1..3)]) + -> + toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q182, q279] + != 3 + /\ + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q182, q279] + = + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q48, q275] + | q279 : int(1..2)])) + = + toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q48, q281] + != 3 + /\ + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q48, q281] + = + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q48, q275] + | q281 : int(1..2)])) + | q275 : int(1..2)]))) + | q250 : int(1..2)]) + \/ + or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q48, q251] != 3 /\ + !or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q182, q253] != 3 + /\ + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q182, q253] = + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q48, q251] + | q253 : int(1..2)]) + /\ + (toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q182, q255] + != 3 + /\ + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q182, q255] + = a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q48, q251] + | q255 : int(1..2)])) + < + toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q48, q257] + != 3 + /\ + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q48, q257] = + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q48, q251] + | q257 : int(1..2)])) + /\ + (and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q182, q258] != 3 + /\ + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q182, q258] < + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q48, q251] + -> + toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q182, q267] + != 3 + /\ + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q182, q267] + = + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q182, q258] + | q267 : int(1..2)])) + = + toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q48, q269] + != 3 + /\ + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q48, q269] + = + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q182, q258] + | q269 : int(1..2)])) + | q258 : int(1..2)]) + /\ + and([and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q48, q259] + != 3, + !or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q182, q261] + != 3 + /\ + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q182, q261] + = + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q48, q259] + | q261 : int(1..2)]), + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q48, q259] + < + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q48, q251]; + int(1..3)]) + -> + toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q182, q263] + != 3 + /\ + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q182, q263] + = + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q48, q259] + | q263 : int(1..2)])) + = + toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q48, q265] + != 3 + /\ + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q48, q265] + = + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q48, q259] + | q265 : int(1..2)])) + | q259 : int(1..2)]))) + | q251 : int(1..2)])) + -> + toInt(or([q240 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ + and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q240, q241] = + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q182, q241] + | q241 : int(1..2)]) + | q240 : int(1..2)])) + = + toInt(or([q245 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ + and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q245, q246] = + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q182, q246] + | q246 : int(1..2)]) + | q245 : int(1..2)])) + | q182 : int(1..2)]) + /\ + and([and([q184 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker, + !or([q197 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ + and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q197, q198] = + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q184, q198] + | q198 : int(1..2)]) + | q197 : int(1..2)]), + or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q184, q202] != 3 /\ + (toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q184, q223] + != 3 + /\ + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q184, q223] + = + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q184, q202] + | q223 : int(1..2)])) + < + toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q48, q225] + != 3 + /\ + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q48, q225] + = + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q184, q202] + | q225 : int(1..2)])) + /\ + (and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q184, q226] + != 3 + /\ + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q184, q226] + < + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q184, q202] + -> + toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q184, q235] + != 3 + /\ + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q184, q235] + = + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q184, q226] + | q235 : int(1..2)])) + = + toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q48, q237] + != 3 + /\ + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q48, q237] + = + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q184, q226] + | q237 : int(1..2)])) + | q226 : int(1..2)]) + /\ + and([and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q48, q227] + != 3, + !or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q184, q229] + != 3 + /\ + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q184, q229] + = + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q48, q227] + | q229 : int(1..2)]), + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q48, q227] + < + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q184, q202]; + int(1..3)]) + -> + toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q184, q231] + != 3 + /\ + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q184, q231] + = + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q48, q227] + | q231 : int(1..2)])) + = + toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q48, q233] + != 3 + /\ + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q48, q233] + = + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q48, q227] + | q233 : int(1..2)])) + | q227 : int(1..2)]))) + | q202 : int(1..2)]) + \/ + or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q48, q203] != 3 /\ + !or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q184, q205] != + 3 + /\ + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q184, q205] = + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q48, q203] + | q205 : int(1..2)]) + /\ + (toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q184, q207] + != 3 + /\ + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q184, q207] + = + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q48, q203] + | q207 : int(1..2)])) + < + toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q48, q209] + != 3 + /\ + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q48, q209] + = + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q48, q203] + | q209 : int(1..2)])) + /\ + (and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q184, q210] + != 3 + /\ + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q184, q210] + < a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q48, q203] + -> + toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q184, q219] + != 3 + /\ + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q184, q219] + = + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q184, q210] + | q219 : int(1..2)])) + = + toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q48, q221] + != 3 + /\ + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q48, q221] + = + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q184, q210] + | q221 : int(1..2)])) + | q210 : int(1..2)]) + /\ + and([and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q48, q211] + != 3, + !or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q184, q213] + != 3 + /\ + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q184, q213] + = + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q48, q211] + | q213 : int(1..2)]), + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q48, q211] + < + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q48, q203]; + int(1..3)]) + -> + toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q184, q215] + != 3 + /\ + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q184, q215] + = + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q48, q211] + | q215 : int(1..2)])) + = + toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q48, q217] + != 3 + /\ + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q48, q217] + = + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q48, q211] + | q217 : int(1..2)])) + | q211 : int(1..2)]))) + | q203 : int(1..2)]); + int(1..3)]) + -> + toInt(or([q187 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ + and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q187, q188] = + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q184, q188] + | q188 : int(1..2)]) + | q187 : int(1..2)])) + = + toInt(or([q192 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ + and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q192, q193] = + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q184, q193] + | q193 : int(1..2)]) + | q192 : int(1..2)])) + | q184 : int(1..2)]))) + | q48 : int(1..2)]) + \/ + or([q50 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ + !or([q168 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ + and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q168, q169] = + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q50, q169] + | q169 : int(1..2)]) + | q168 : int(1..2)]) + /\ + (toInt(or([q53 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ + and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q53, q54] = + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q50, q54] + | q54 : int(1..2)]) + | q53 : int(1..2)])) + < + toInt(or([q58 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ + and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q58, q59] = + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q50, q59] + | q59 : int(1..2)]) + | q58 : int(1..2)])) + /\ + (and([q62 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ + (or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q62, q130] != 3 /\ + (toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q62, q151] + != 3 + /\ + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q62, q151] = + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q62, q130] + | q151 : int(1..2)])) + < + toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q50, q153] + != 3 + /\ + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q50, q153] = + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q62, q130] + | q153 : int(1..2)])) + /\ + (and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q62, q154] != 3 + /\ + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q62, q154] < + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q62, q130] + -> + toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q62, q163] + != 3 + /\ + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q62, q163] + = + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q62, q154] + | q163 : int(1..2)])) + = + toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q50, q165] + != 3 + /\ + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q50, q165] + = + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q62, q154] + | q165 : int(1..2)])) + | q154 : int(1..2)]) + /\ + and([and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q50, q155] + != 3, + !or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q62, q157] + != 3 + /\ + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q62, q157] + = + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q50, q155] + | q157 : int(1..2)]), + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q50, q155] + < + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q62, q130]; + int(1..3)]) + -> + toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q62, q159] + != 3 + /\ + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q62, q159] + = + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q50, q155] + | q159 : int(1..2)])) + = + toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q50, q161] + != 3 + /\ + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q50, q161] + = + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q50, q155] + | q161 : int(1..2)])) + | q155 : int(1..2)]))) + | q130 : int(1..2)]) + \/ + or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q50, q131] != 3 /\ + !or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q62, q133] != 3 /\ + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q62, q133] = + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q50, q131] + | q133 : int(1..2)]) + /\ + (toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q62, q135] + != 3 + /\ + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q62, q135] = + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q50, q131] + | q135 : int(1..2)])) + < + toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q50, q137] + != 3 + /\ + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q50, q137] = + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q50, q131] + | q137 : int(1..2)])) + /\ + (and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q62, q138] != 3 + /\ + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q62, q138] < + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q50, q131] + -> + toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q62, q147] + != 3 + /\ + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q62, q147] + = + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q62, q138] + | q147 : int(1..2)])) + = + toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q50, q149] + != 3 + /\ + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q50, q149] + = + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q62, q138] + | q149 : int(1..2)])) + | q138 : int(1..2)]) + /\ + and([and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q50, q139] + != 3, + !or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q62, q141] + != 3 + /\ + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q62, q141] + = + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q50, q139] + | q141 : int(1..2)]), + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q50, q139] + < + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q50, q131]; + int(1..3)]) + -> + toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q62, q143] + != 3 + /\ + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q62, q143] + = + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q50, q139] + | q143 : int(1..2)])) + = + toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q50, q145] + != 3 + /\ + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q50, q145] + = + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q50, q139] + | q145 : int(1..2)])) + | q139 : int(1..2)]))) + | q131 : int(1..2)])) + -> + toInt(or([q120 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ + and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q120, q121] = + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q62, q121] + | q121 : int(1..2)]) + | q120 : int(1..2)])) + = + toInt(or([q125 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ + and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q125, q126] = + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q62, q126] + | q126 : int(1..2)]) + | q125 : int(1..2)])) + | q62 : int(1..2)]) + /\ + and([and([q64 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker, + !or([q77 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ + and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q77, q78] = + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q64, q78] + | q78 : int(1..2)]) + | q77 : int(1..2)]), + or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q64, q82] != 3 /\ + (toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q64, q103] + != 3 + /\ + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q64, q103] + = + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q64, q82] + | q103 : int(1..2)])) + < + toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q50, q105] + != 3 + /\ + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q50, q105] + = + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q64, q82] + | q105 : int(1..2)])) + /\ + (and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q64, q106] + != 3 + /\ + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q64, q106] < + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q64, q82] + -> + toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q64, q115] + != 3 + /\ + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q64, q115] + = + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q64, q106] + | q115 : int(1..2)])) + = + toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q50, q117] + != 3 + /\ + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q50, q117] + = + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q64, q106] + | q117 : int(1..2)])) + | q106 : int(1..2)]) + /\ + and([and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q50, q107] + != 3, + !or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q64, q109] + != 3 + /\ + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q64, q109] + = + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q50, q107] + | q109 : int(1..2)]), + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q50, q107] + < + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q64, q82]; + int(1..3)]) + -> + toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q64, q111] + != 3 + /\ + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q64, q111] + = + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q50, q107] + | q111 : int(1..2)])) + = + toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q50, q113] + != 3 + /\ + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q50, q113] + = + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q50, q107] + | q113 : int(1..2)])) + | q107 : int(1..2)]))) + | q82 : int(1..2)]) + \/ + or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q50, q83] != 3 /\ + !or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q64, q85] != 3 + /\ + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q64, q85] = + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q50, q83] + | q85 : int(1..2)]) + /\ + (toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q64, q87] + != 3 + /\ + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q64, q87] + = + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q50, q83] + | q87 : int(1..2)])) + < + toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q50, q89] + != 3 + /\ + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q50, q89] + = + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q50, q83] + | q89 : int(1..2)])) + /\ + (and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q64, q90] != + 3 + /\ + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q64, q90] < + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q50, q83] + -> + toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q64, q99] + != 3 + /\ + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q64, q99] + = + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q64, q90] + | q99 : int(1..2)])) + = + toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q50, q101] + != 3 + /\ + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q50, q101] + = + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q64, q90] + | q101 : int(1..2)])) + | q90 : int(1..2)]) + /\ + and([and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q50, q91] + != 3, + !or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q64, q93] + != 3 + /\ + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q64, q93] + = + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q50, q91] + | q93 : int(1..2)]), + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q50, q91] + < + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q50, q83]; + int(1..3)]) + -> + toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q64, q95] + != 3 + /\ + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q64, q95] + = + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q50, q91] + | q95 : int(1..2)])) + = + toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q50, q97] + != 3 + /\ + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q50, q97] + = + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q50, q91] + | q97 : int(1..2)])) + | q91 : int(1..2)]))) + | q83 : int(1..2)]); + int(1..3)]) + -> + toInt(or([q67 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ + and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q67, q68] = + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q64, q68] + | q68 : int(1..2)]) + | q67 : int(1..2)])) + = + toInt(or([q72 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ + and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q72, q73] = + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q64, q73] + | q73 : int(1..2)]) + | q72 : int(1..2)])) + | q64 : int(1..2)]))) + | q50 : int(1..2)]), + alldifferent_except([toInt(q35 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q35, q36] != + 3) + * + catchUndef(a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q35, q36], + 0) + | q35 : int(1..2), q36 : int(1..2)], + 0), + and([q37 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> + sum([toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q37, q39] != 3) + | q39 : int(1..2)]) + >= 1 + | q37 : int(1..2)]), + 2 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> + [a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[1, q12] | q12 : int(1..2)] a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> + and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q5, q33] = 1 + | q33 : int(1..2)]) + | q5 : int(1..2)]), + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker <= 2, + and([q6 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q6, 1] < + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q6, 2] + \/ a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q6, 1] = 3 + | q6 : int(1..2)]), + and([q6 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> + (a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q6, 1] = 3 -> + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q6, 2] = 3) + | q6 : int(1..2)]), + and([q6 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> + sum([toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q6, q9] != 3) + | q9 : int(1..2)]) + <= 2 + | q6 : int(1..2)]), + 2 = + sum([toInt(q14 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker) * + catchUndef(sum([toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q14, q16] != + 3) + | q16 : int(1..2)]), + 0) + | q14 : int(1..2)]), + alldifferent_except([toInt(q40 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q40, q41] != + 3) + * + catchUndef(b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q40, q41], + 0) + | q40 : int(1..2), q41 : int(1..2)], + 0), + and([q42 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> + sum([toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q42, q44] != 3) + | q44 : int(1..2)]) + >= 1 + | q42 : int(1..2)]), + 2 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> + [b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[1, q28] | q28 : int(1..2)] b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> + and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q21, q34] = 1 + | q34 : int(1..2)]) + | q21 : int(1..2)]), + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker <= 2, + and([q22 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q22, 1] < + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q22, 2] + \/ b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q22, 1] = 3 + | q22 : int(1..2)]), + and([q22 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> + (b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q22, 1] = 3 -> + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q22, 2] = 3) + | q22 : int(1..2)]), + and([q22 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> + sum([toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q22, q25] != 3) + | q25 : int(1..2)]) + <= 2 + | q22 : int(1..2)]), + 2 = + sum([toInt(q30 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker) * + catchUndef(sum([toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q30, q32] != + 3) + | q32 : int(1..2)]), + 0) + | q30 : int(1..2)]) + diff --git a/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_2_3-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_2_3-solution000001.solution new file mode 100644 index 0000000000..cde05d5274 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_2_3-solution000001.solution @@ -0,0 +1,11 @@ +language Essence 1.3 + +letting a be partition({1, 2}) +$ Visualisation for a +$ 1 2 + +letting b be partition({1}, {2}) +$ Visualisation for b +$ 1 +$ 2 + diff --git a/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_2_3.eprime.orig b/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_2_3.eprime.orig deleted file mode 100644 index bf1e91cfd4..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_2_3.eprime.orig +++ /dev/null @@ -1,1208 +0,0 @@ -language ESSENCE' 1.0 - -find a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker: int(0..2) -find a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy: - matrix indexed by [int(1..2), int(1..2)] of int(1..3) -find b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker: int(0..2) -find b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker: - matrix indexed by [int(1..2)] of int(0..2) -find b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values: - matrix indexed by [int(1..2), int(1..2)] of int(1..2) -branching on - [a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker, - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy, - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker, - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker, - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values] -such that - or([q43 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ - (toInt(or([q198 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ - and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q198, q199] = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q43, q199] - | q199 : int(1..2)]) - | q198 : int(1..2)])) - < - toInt(or([q203 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - (and([q205 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q203] - -> - or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q43, q207] != - 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q43, q207] = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q203, q205] - | q207 : int(1..2)]) - | q205 : int(1..2)]) - /\ - and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q43, q209] != 3 -> - or([q211 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q203] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q203, q211] - = a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q43, q209] - | q211 : int(1..2)]) - | q209 : int(1..2)])) - | q203 : int(1..2)])) - /\ - (and([q213 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ - (or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q213, q299] != 3 /\ - (toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q213, q320] - != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q213, q320] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q213, q299] - | q320 : int(1..2)])) - < - toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q43, q322] - != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q43, q322] = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q213, q299] - | q322 : int(1..2)])) - /\ - (and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q213, q323] != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q213, q323] < - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q213, q299] - -> - toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q213, q332] - != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q213, q332] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q213, q323] - | q332 : int(1..2)])) - = - toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q43, q334] - != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q43, q334] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q213, q323] - | q334 : int(1..2)])) - | q323 : int(1..2)]) - /\ - and([and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q43, q324] - != 3, - !or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q213, q326] - != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q213, q326] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q43, q324] - | q326 : int(1..2)]), - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q43, q324] - < - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q213, q299]; - int(1..3)]) - -> - toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q213, q328] - != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q213, q328] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q43, q324] - | q328 : int(1..2)])) - = - toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q43, q330] - != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q43, q330] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q43, q324] - | q330 : int(1..2)])) - | q324 : int(1..2)]))) - | q299 : int(1..2)]) - \/ - or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q43, q300] != 3 /\ - !or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q213, q302] != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q213, q302] = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q43, q300] - | q302 : int(1..2)]) - /\ - (toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q213, q304] - != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q213, q304] - = a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q43, q300] - | q304 : int(1..2)])) - < - toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q43, q306] - != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q43, q306] = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q43, q300] - | q306 : int(1..2)])) - /\ - (and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q213, q307] != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q213, q307] < - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q43, q300] - -> - toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q213, q316] - != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q213, q316] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q213, q307] - | q316 : int(1..2)])) - = - toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q43, q318] - != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q43, q318] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q213, q307] - | q318 : int(1..2)])) - | q307 : int(1..2)]) - /\ - and([and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q43, q308] - != 3, - !or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q213, q310] - != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q213, q310] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q43, q308] - | q310 : int(1..2)]), - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q43, q308] - < - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q43, q300]; - int(1..3)]) - -> - toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q213, q312] - != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q213, q312] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q43, q308] - | q312 : int(1..2)])) - = - toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q43, q314] - != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q43, q314] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q43, q308] - | q314 : int(1..2)])) - | q308 : int(1..2)]))) - | q300 : int(1..2)])) - -> - toInt(or([q283 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ - and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q283, q284] = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q213, q284] - | q284 : int(1..2)]) - | q283 : int(1..2)])) - = - toInt(or([q288 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - (and([q290 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q288] - -> - or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q213, q292] - != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q213, q292] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q288, q290] - | q292 : int(1..2)]) - | q290 : int(1..2)]) - /\ - and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q213, q294] - != 3 - -> - or([q296 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q288] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q288, q296] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q213, q294] - | q296 : int(1..2)]) - | q294 : int(1..2)])) - | q288 : int(1..2)])) - | q213 : int(1..2)]) - /\ - and([and([q215 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker, - !or([q234 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ - (and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q234, q236] - != 3 - -> - or([q238 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q215] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q215, q238] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q234, q236] - | q238 : int(1..2)]) - | q236 : int(1..2)]) - /\ - and([q240 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q215] - -> - or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q234, q242] - != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q234, q242] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q215, q240] - | q242 : int(1..2)]) - | q240 : int(1..2)])) - | q234 : int(1..2)]), - or([q245 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q215] - /\ - (toInt(or([q266 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q215] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q215, q266] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q215, q245] - | q266 : int(1..2)])) - < - toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q43, q268] - != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q43, q268] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q215, q245] - | q268 : int(1..2)])) - /\ - (and([q269 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q215] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q215, q269] - < - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q215, q245] - -> - toInt(or([q278 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q215] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q215, q278] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q215, q269] - | q278 : int(1..2)])) - = - toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q43, q280] - != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q43, q280] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q215, q269] - | q280 : int(1..2)])) - | q269 : int(1..2)]) - /\ - and([and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q43, q270] - != 3, - !or([q272 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q215] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q215, q272] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q43, q270] - | q272 : int(1..2)]), - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q43, q270] - < - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q215, q245]; - int(1..3)]) - -> - toInt(or([q274 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q215] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q215, q274] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q43, q270] - | q274 : int(1..2)])) - = - toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q43, q276] - != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q43, q276] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q43, q270] - | q276 : int(1..2)])) - | q270 : int(1..2)]))) - | q245 : int(1..2)]) - \/ - or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q43, q246] != 3 /\ - !or([q248 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q215] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q215, q248] - = a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q43, q246] - | q248 : int(1..2)]) - /\ - (toInt(or([q250 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q215] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q215, q250] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q43, q246] - | q250 : int(1..2)])) - < - toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q43, q252] - != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q43, q252] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q43, q246] - | q252 : int(1..2)])) - /\ - (and([q253 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q215] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q215, q253] - < a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q43, q246] - -> - toInt(or([q262 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q215] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q215, q262] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q215, q253] - | q262 : int(1..2)])) - = - toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q43, q264] - != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q43, q264] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q215, q253] - | q264 : int(1..2)])) - | q253 : int(1..2)]) - /\ - and([and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q43, q254] - != 3, - !or([q256 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q215] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q215, q256] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q43, q254] - | q256 : int(1..2)]), - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q43, q254] - < - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q43, q246]; - int(1..3)]) - -> - toInt(or([q258 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q215] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q215, q258] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q43, q254] - | q258 : int(1..2)])) - = - toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q43, q260] - != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q43, q260] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q43, q254] - | q260 : int(1..2)])) - | q254 : int(1..2)]))) - | q246 : int(1..2)]); - int(1..3)]) - -> - toInt(or([q218 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ - (and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q218, q220] - != 3 - -> - or([q222 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q215] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q215, q222] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q218, q220] - | q222 : int(1..2)]) - | q220 : int(1..2)]) - /\ - and([q224 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q215] - -> - or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q218, q226] - != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q218, q226] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q215, q224] - | q226 : int(1..2)]) - | q224 : int(1..2)])) - | q218 : int(1..2)])) - = - toInt(or([q229 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - (b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q229] = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q215] - /\ - and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q229, q230] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q215, q230] - | q230 : int(1..2)])) - | q229 : int(1..2)])) - | q215 : int(1..2)]))) - | q43 : int(1..2)]) - \/ - or([q45 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - !or([q187 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ - (and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q187, q189] != 3 -> - or([q191 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q45] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q45, q191] = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q187, q189] - | q191 : int(1..2)]) - | q189 : int(1..2)]) - /\ - and([q193 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q45] -> - or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q187, q195] != 3 /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q187, q195] = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q45, q193] - | q195 : int(1..2)]) - | q193 : int(1..2)])) - | q187 : int(1..2)]) - /\ - (toInt(or([q48 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ - (and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q48, q50] != 3 -> - or([q52 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q45] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q45, q52] - = a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q48, q50] - | q52 : int(1..2)]) - | q50 : int(1..2)]) - /\ - and([q54 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q45] - -> - or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q48, q56] != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q48, q56] = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q45, q54] - | q56 : int(1..2)]) - | q54 : int(1..2)])) - | q48 : int(1..2)])) - < - toInt(or([q59 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - (b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q59] = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q45] - /\ - and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q59, q60] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q45, q60] - | q60 : int(1..2)])) - | q59 : int(1..2)])) - /\ - (and([q63 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ - (or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q63, q149] != 3 /\ - (toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q63, q170] - != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q63, q170] = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q63, q149] - | q170 : int(1..2)])) - < - toInt(or([q172 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q45] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q45, q172] - = a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q63, q149] - | q172 : int(1..2)])) - /\ - (and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q63, q173] != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q63, q173] < - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q63, q149] - -> - toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q63, q182] - != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q63, q182] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q63, q173] - | q182 : int(1..2)])) - = - toInt(or([q184 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q45] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q45, q184] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q63, q173] - | q184 : int(1..2)])) - | q173 : int(1..2)]) - /\ - and([and([q174 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q45], - !or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q63, q180] - != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q63, q180] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q45, q174] - | q180 : int(1..2)]), - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q45, q174] - < - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q63, q149]; - int(1..3)]) - -> - toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q63, q176] - != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q63, q176] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q45, q174] - | q176 : int(1..2)])) - = - toInt(or([q178 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q45] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q45, q178] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q45, q174] - | q178 : int(1..2)])) - | q174 : int(1..2)]))) - | q149 : int(1..2)]) - \/ - or([q150 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q45] /\ - !or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q63, q168] != 3 /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q63, q168] = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q45, q150] - | q168 : int(1..2)]) - /\ - (toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q63, q152] - != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q63, q152] = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q45, q150] - | q152 : int(1..2)])) - < - toInt(or([q154 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q45] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q45, q154] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q45, q150] - | q154 : int(1..2)])) - /\ - (and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q63, q155] != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q63, q155] < - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q45, q150] - -> - toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q63, q164] - != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q63, q164] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q63, q155] - | q164 : int(1..2)])) - = - toInt(or([q166 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q45] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q45, q166] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q63, q155] - | q166 : int(1..2)])) - | q155 : int(1..2)]) - /\ - and([and([q156 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q45], - !or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q63, q162] - != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q63, q162] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q45, q156] - | q162 : int(1..2)]), - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q45, q156] - < - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q45, q150]; - int(1..3)]) - -> - toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q63, q158] - != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q63, q158] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q45, q156] - | q158 : int(1..2)])) - = - toInt(or([q160 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q45] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q45, q160] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q45, q156] - | q160 : int(1..2)])) - | q156 : int(1..2)]))) - | q150 : int(1..2)])) - -> - toInt(or([q133 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ - and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q133, q134] = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q63, q134] - | q134 : int(1..2)]) - | q133 : int(1..2)])) - = - toInt(or([q138 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - (and([q140 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q138] - -> - or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q63, q142] - != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q63, q142] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q138, q140] - | q142 : int(1..2)]) - | q140 : int(1..2)]) - /\ - and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q63, q144] - != 3 - -> - or([q146 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q138] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q138, q146] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q63, q144] - | q146 : int(1..2)]) - | q144 : int(1..2)])) - | q138 : int(1..2)])) - | q63 : int(1..2)]) - /\ - and([and([q65 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker, - !or([q84 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ - (and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q84, q86] != - 3 - -> - or([q88 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q65] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q65, q88] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q84, q86] - | q88 : int(1..2)]) - | q86 : int(1..2)]) - /\ - and([q90 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q65] - -> - or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q84, q92] - != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q84, q92] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q65, q90] - | q92 : int(1..2)]) - | q90 : int(1..2)])) - | q84 : int(1..2)]), - or([q95 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q65] - /\ - (toInt(or([q116 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q65] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q65, q116] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q65, q95] - | q116 : int(1..2)])) - < - toInt(or([q118 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q45] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q45, q118] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q65, q95] - | q118 : int(1..2)])) - /\ - (and([q119 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q65] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q65, q119] - < - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q65, q95] - -> - toInt(or([q128 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q65] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q65, q128] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q65, q119] - | q128 : int(1..2)])) - = - toInt(or([q130 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q45] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q45, q130] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q65, q119] - | q130 : int(1..2)])) - | q119 : int(1..2)]) - /\ - and([and([q120 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q45], - !or([q126 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q65] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q65, q126] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q45, q120] - | q126 : int(1..2)]), - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q45, q120] - < - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q65, q95]; - int(1..3)]) - -> - toInt(or([q122 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q65] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q65, q122] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q45, q120] - | q122 : int(1..2)])) - = - toInt(or([q124 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q45] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q45, q124] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q45, q120] - | q124 : int(1..2)])) - | q120 : int(1..2)]))) - | q95 : int(1..2)]) - \/ - or([q96 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q45] - /\ - !or([q114 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q65] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q65, q114] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q45, q96] - | q114 : int(1..2)]) - /\ - (toInt(or([q98 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q65] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q65, q98] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q45, q96] - | q98 : int(1..2)])) - < - toInt(or([q100 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q45] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q45, q100] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q45, q96] - | q100 : int(1..2)])) - /\ - (and([q101 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q65] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q65, q101] - < - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q45, q96] - -> - toInt(or([q110 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q65] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q65, q110] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q65, q101] - | q110 : int(1..2)])) - = - toInt(or([q112 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q45] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q45, q112] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q65, q101] - | q112 : int(1..2)])) - | q101 : int(1..2)]) - /\ - and([and([q102 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q45], - !or([q108 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q65] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q65, q108] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q45, q102] - | q108 : int(1..2)]), - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q45, q102] - < - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q45, q96]; - int(1..3)]) - -> - toInt(or([q104 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q65] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q65, q104] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q45, q102] - | q104 : int(1..2)])) - = - toInt(or([q106 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q45] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q45, q106] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q45, q102] - | q106 : int(1..2)])) - | q102 : int(1..2)]))) - | q96 : int(1..2)]); - int(1..3)]) - -> - toInt(or([q68 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ - (and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q68, q70] != - 3 - -> - or([q72 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q65] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q65, q72] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q68, q70] - | q72 : int(1..2)]) - | q70 : int(1..2)]) - /\ - and([q74 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q65] - -> - or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q68, q76] - != 3 - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q68, q76] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q65, q74] - | q76 : int(1..2)]) - | q74 : int(1..2)])) - | q68 : int(1..2)])) - = - toInt(or([q79 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - (b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q79] = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q65] - /\ - and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q79, q80] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q65, q80] - | q80 : int(1..2)])) - | q79 : int(1..2)])) - | q65 : int(1..2)]))) - | q45 : int(1..2)]), - alldifferent_except([toInt(q32 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q32, q33] != - 3) - * - catchUndef(a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q32, q33], - 0) - | q32 : int(1..2), q33 : int(1..2)], - 0), - and([q34 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - sum([toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q34, q36] != 3) - | q36 : int(1..2)]) - >= 1 - | q34 : int(1..2)]), - 2 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - [a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[1, q12] | q12 : int(1..2)] a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q5, q30] = 1 - | q30 : int(1..2)]) - | q5 : int(1..2)]), - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker <= 2, - and([q6 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q6, 1] < - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q6, 2] - \/ a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q6, 1] = 3 - | q6 : int(1..2)]), - and([q6 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - (a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q6, 1] = 3 -> - a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q6, 2] = 3) - | q6 : int(1..2)]), - and([q6 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - sum([toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q6, q9] != 3) - | q9 : int(1..2)]) - <= 2 - | q6 : int(1..2)]), - 2 = - sum([toInt(q14 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker) * - catchUndef(sum([toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q14, q16] != - 3) - | q16 : int(1..2)]), - 0) - | q14 : int(1..2)]), - alldifferent_except([toInt(q37 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - q38 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q37]) - * - catchUndef(b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q37, q38], - 0) - | q37 : int(1..2), q38 : int(1..2)], - 0), - and([q39 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q39] >= 1 - | q39 : int(1..2)]), - 2 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - flatten([[b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[1]; int(1)], - [b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[1, q27] - | q27 : int(1..2)]; - int(1..2)]) - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q21] = 0 /\ - and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q21, q31] = 1 - | q31 : int(1..2)]) - | q21 : int(1..2)]), - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker <= 2, - and([q22 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - (2 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q22] -> - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q22, 1] < - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q22, 2]) - | q22 : int(1..2)]), - and([q22 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - and([q24 > b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q22] -> - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q22, q24] = 1 - | q24 : int(1..2)]) - | q22 : int(1..2)]), - and([q22 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q22] <= 2 - | q22 : int(1..2)]), - 2 = - sum([toInt(q29 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker) * - catchUndef(b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q29], 0) - | q29 : int(1..2)]) - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_2_4-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_2_4-solution000001.solution new file mode 100644 index 0000000000..cde05d5274 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_2_4-solution000001.solution @@ -0,0 +1,11 @@ +language Essence 1.3 + +letting a be partition({1, 2}) +$ Visualisation for a +$ 1 2 + +letting b be partition({1}, {2}) +$ Visualisation for b +$ 1 +$ 2 + diff --git a/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_2_4.eprime b/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_2_4.eprime new file mode 100644 index 0000000000..99d329b649 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_2_4.eprime @@ -0,0 +1,809 @@ +language ESSENCE' 1.0 + +find a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker: int(0..2) +find a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy: + matrix indexed by [int(1..2), int(1..2)] of int(1..3) +find b_PartitionOccurrence_NumParts: int(1..2) +find b_PartitionOccurrence_WhichPart: matrix indexed by [int(1..2)] of int(1..2) +find b_PartitionOccurrence_PartSizes: matrix indexed by [int(1..2)] of int(0..2) +find b_PartitionOccurrence_FirstIndex: matrix indexed by [int(1..2)] of int(1..2) +branching on + [a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker, + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy, b_PartitionOccurrence_NumParts, + b_PartitionOccurrence_WhichPart, b_PartitionOccurrence_PartSizes, b_PartitionOccurrence_FirstIndex] +such that + or([q36 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ + (toInt(or([q183 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ + and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q183, q184] = + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q36, q184] + | q184 : int(1..2)]) + | q183 : int(1..2)])) + < + toInt(or([q187 <= b_PartitionOccurrence_NumParts /\ + (and([b_PartitionOccurrence_WhichPart[q190] = q187 -> + or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q36, q192] != + 3 + /\ + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q36, q192] = + q190 + | q192 : int(1..2)]) + | q190 : int(1..2)]) + /\ + and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q36, q194] != 3 -> + or([b_PartitionOccurrence_WhichPart[q196] = q187 /\ + q196 = + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q36, q194] + | q196 : int(1..2)]) + | q194 : int(1..2)])) + | q187 : int(1..2)])) + /\ + (and([q198 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ + (or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q198, q290] != 3 /\ + (toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q198, q311] + != 3 + /\ + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q198, q311] + = + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q198, q290] + | q311 : int(1..2)])) + < + toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q36, q313] + != 3 + /\ + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q36, q313] = + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q198, q290] + | q313 : int(1..2)])) + /\ + (and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q198, q314] != 3 + /\ + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q198, q314] < + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q198, q290] + -> + toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q198, q323] + != 3 + /\ + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q198, q323] + = + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q198, q314] + | q323 : int(1..2)])) + = + toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q36, q325] + != 3 + /\ + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q36, q325] + = + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q198, q314] + | q325 : int(1..2)])) + | q314 : int(1..2)]) + /\ + and([and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q36, q315] + != 3, + !or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q198, q317] + != 3 + /\ + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q198, q317] + = + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q36, q315] + | q317 : int(1..2)]), + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q36, q315] + < + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q198, q290]; + int(1..3)]) + -> + toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q198, q319] + != 3 + /\ + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q198, q319] + = + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q36, q315] + | q319 : int(1..2)])) + = + toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q36, q321] + != 3 + /\ + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q36, q321] + = + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q36, q315] + | q321 : int(1..2)])) + | q315 : int(1..2)]))) + | q290 : int(1..2)]) + \/ + or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q36, q291] != 3 /\ + !or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q198, q293] != 3 + /\ + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q198, q293] = + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q36, q291] + | q293 : int(1..2)]) + /\ + (toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q198, q295] + != 3 + /\ + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q198, q295] + = a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q36, q291] + | q295 : int(1..2)])) + < + toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q36, q297] + != 3 + /\ + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q36, q297] = + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q36, q291] + | q297 : int(1..2)])) + /\ + (and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q198, q298] != 3 + /\ + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q198, q298] < + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q36, q291] + -> + toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q198, q307] + != 3 + /\ + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q198, q307] + = + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q198, q298] + | q307 : int(1..2)])) + = + toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q36, q309] + != 3 + /\ + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q36, q309] + = + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q198, q298] + | q309 : int(1..2)])) + | q298 : int(1..2)]) + /\ + and([and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q36, q299] + != 3, + !or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q198, q301] + != 3 + /\ + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q198, q301] + = + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q36, q299] + | q301 : int(1..2)]), + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q36, q299] + < + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q36, q291]; + int(1..3)]) + -> + toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q198, q303] + != 3 + /\ + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q198, q303] + = + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q36, q299] + | q303 : int(1..2)])) + = + toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q36, q305] + != 3 + /\ + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q36, q305] + = + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q36, q299] + | q305 : int(1..2)])) + | q299 : int(1..2)]))) + | q291 : int(1..2)])) + -> + toInt(or([q274 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ + and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q274, q275] = + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q198, q275] + | q275 : int(1..2)]) + | q274 : int(1..2)])) + = + toInt(or([q278 <= b_PartitionOccurrence_NumParts /\ + (and([b_PartitionOccurrence_WhichPart[q281] = q278 -> + or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q198, q283] + != 3 + /\ + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q198, q283] + = q281 + | q283 : int(1..2)]) + | q281 : int(1..2)]) + /\ + and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q198, q285] + != 3 + -> + or([b_PartitionOccurrence_WhichPart[q287] = q278 /\ + q287 = + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q198, q285] + | q287 : int(1..2)]) + | q285 : int(1..2)])) + | q278 : int(1..2)])) + | q198 : int(1..2)]) + /\ + and([and([q199 <= b_PartitionOccurrence_NumParts, + !or([q214 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ + (and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q214, q216] + != 3 + -> + or([b_PartitionOccurrence_WhichPart[q218] = q199 /\ + q218 = + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q214, q216] + | q218 : int(1..2)]) + | q216 : int(1..2)]) + /\ + and([b_PartitionOccurrence_WhichPart[q220] = q199 -> + or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q214, q222] + != 3 + /\ + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q214, q222] + = q220 + | q222 : int(1..2)]) + | q220 : int(1..2)])) + | q214 : int(1..2)]), + or([b_PartitionOccurrence_WhichPart[q225] = q199 /\ + (sum([toInt(b_PartitionOccurrence_WhichPart[q246] = q199) * catchUndef(toInt(q246 = q225), 0) + | q246 : int(1..2)]) + < + toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q36, q248] + != 3 + /\ + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q36, q248] + = q225 + | q248 : int(1..2)])) + /\ + (and([b_PartitionOccurrence_WhichPart[q249] = q199 -> + sum([toInt(b_PartitionOccurrence_WhichPart[q258] = q199) * + catchUndef(toInt(q258 = q249), 0) + | q258 : int(1..2)]) + = + toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q36, q260] + != 3 + /\ + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q36, q260] + = q249 + | q260 : int(1..2)])) + | q249 : int(1..2), q249 < q225]) + /\ + and([and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q36, q250] + != 3, + !or([b_PartitionOccurrence_WhichPart[q252] = q199 /\ + q252 = + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q36, q250] + | q252 : int(1..2)]), + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q36, q250] + < q225; + int(1..3)]) + -> + sum([toInt(b_PartitionOccurrence_WhichPart[q254] = q199) * + catchUndef(toInt(q254 = + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q36, q250]), + 0) + | q254 : int(1..2)]) + = + toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q36, q256] + != 3 + /\ + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q36, q256] + = + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q36, q250] + | q256 : int(1..2)])) + | q250 : int(1..2)]))) + | q225 : int(1..2)]) + \/ + or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q36, q226] != 3 /\ + !or([b_PartitionOccurrence_WhichPart[q228] = q199 /\ + q228 = + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q36, q226] + | q228 : int(1..2)]) + /\ + (sum([toInt(b_PartitionOccurrence_WhichPart[q230] = q199) * + catchUndef(toInt(q230 = + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q36, q226]), + 0) + | q230 : int(1..2)]) + < + toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q36, q232] + != 3 + /\ + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q36, q232] + = + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q36, q226] + | q232 : int(1..2)])) + /\ + (and([b_PartitionOccurrence_WhichPart[q233] = q199 /\ + q233 < + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q36, q226] + -> + sum([toInt(b_PartitionOccurrence_WhichPart[q242] = q199) * + catchUndef(toInt(q242 = q233), 0) + | q242 : int(1..2)]) + = + toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q36, q244] + != 3 + /\ + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q36, q244] + = q233 + | q244 : int(1..2)])) + | q233 : int(1..2)]) + /\ + and([and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q36, q234] + != 3, + !or([b_PartitionOccurrence_WhichPart[q236] = q199 /\ + q236 = + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q36, q234] + | q236 : int(1..2)]), + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q36, q234] + < + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q36, q226]; + int(1..3)]) + -> + sum([toInt(b_PartitionOccurrence_WhichPart[q238] = q199) * + catchUndef(toInt(q238 = + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q36, q234]), + 0) + | q238 : int(1..2)]) + = + toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q36, q240] + != 3 + /\ + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q36, q240] + = + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q36, q234] + | q240 : int(1..2)])) + | q234 : int(1..2)]))) + | q226 : int(1..2)]); + int(1..3)]) + -> + toInt(or([q263 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ + (and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q263, q265] + != 3 + -> + or([b_PartitionOccurrence_WhichPart[q267] = q199 /\ + q267 = + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q263, q265] + | q267 : int(1..2)]) + | q265 : int(1..2)]) + /\ + and([b_PartitionOccurrence_WhichPart[q269] = q199 -> + or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q263, q271] + != 3 + /\ + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q263, q271] + = q269 + | q271 : int(1..2)]) + | q269 : int(1..2)])) + | q263 : int(1..2)])) + = + toInt(or([q202 <= b_PartitionOccurrence_NumParts /\ + (and([b_PartitionOccurrence_WhichPart[q205] = q202 -> + or([b_PartitionOccurrence_WhichPart[q207] = q199 /\ q207 = q205 | q207 : int(1..2)]) + | q205 : int(1..2)]) + /\ + and([b_PartitionOccurrence_WhichPart[q209] = q199 -> + or([b_PartitionOccurrence_WhichPart[q211] = q202 /\ q211 = q209 | q211 : int(1..2)]) + | q209 : int(1..2)])) + | q202 : int(1..2)])) + | q199 : int(1..2)]))) + | q36 : int(1..2)]) + \/ + or([q37 <= b_PartitionOccurrence_NumParts /\ + !or([q172 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ + (and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q172, q174] != 3 -> + or([b_PartitionOccurrence_WhichPart[q176] = q37 /\ + q176 = a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q172, q174] + | q176 : int(1..2)]) + | q174 : int(1..2)]) + /\ + and([b_PartitionOccurrence_WhichPart[q178] = q37 -> + or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q172, q180] != 3 /\ + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q172, q180] = q178 + | q180 : int(1..2)]) + | q178 : int(1..2)])) + | q172 : int(1..2)]) + /\ + (toInt(or([q161 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ + (and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q161, q163] != 3 + -> + or([b_PartitionOccurrence_WhichPart[q165] = q37 /\ + q165 = + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q161, q163] + | q165 : int(1..2)]) + | q163 : int(1..2)]) + /\ + and([b_PartitionOccurrence_WhichPart[q167] = q37 -> + or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q161, q169] != + 3 + /\ + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q161, q169] = + q167 + | q169 : int(1..2)]) + | q167 : int(1..2)])) + | q161 : int(1..2)])) + < + toInt(or([q40 <= b_PartitionOccurrence_NumParts /\ + (and([b_PartitionOccurrence_WhichPart[q43] = q40 -> + or([b_PartitionOccurrence_WhichPart[q45] = q37 /\ q45 = q43 | q45 : int(1..2)]) + | q43 : int(1..2)]) + /\ + and([b_PartitionOccurrence_WhichPart[q47] = q37 -> + or([b_PartitionOccurrence_WhichPart[q49] = q40 /\ q49 = q47 | q49 : int(1..2)]) + | q47 : int(1..2)])) + | q40 : int(1..2)])) + /\ + (and([q71 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ + (or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q71, q72] != 3 /\ + (toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q71, q80] != + 3 + /\ + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q71, q80] = + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q71, q72] + | q80 : int(1..2)])) + < + sum([toInt(b_PartitionOccurrence_WhichPart[q63] = q37) * + catchUndef(toInt(q63 = + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q71, q72]), + 0) + | q63 : int(1..2)]) + /\ + (and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q71, q73] != 3 + /\ + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q71, q73] < + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q71, q72] + -> + toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q71, q75] + != 3 + /\ + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q71, q75] + = + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q71, q73] + | q75 : int(1..2)])) + = + sum([toInt(b_PartitionOccurrence_WhichPart[q69] = q37) * + catchUndef(toInt(q69 = + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q71, q73]), + 0) + | q69 : int(1..2)]) + | q73 : int(1..2)]) + /\ + and([!or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q71, q76] + != 3 + /\ + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q71, q76] = + q64 | q76 : int(1..2)]) + /\ + q64 < a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q71, q72] + -> + (b_PartitionOccurrence_WhichPart[q64] = q37 -> + toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q71, q78] + != 3 + /\ + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q71, q78] + = q64 + | q78 : int(1..2)])) + = + sum([toInt(b_PartitionOccurrence_WhichPart[q66] = q37) * catchUndef(toInt(q66 = q64), 0) + | q66 : int(1..2)])) + | q64 : int(1..2)]))) + | q72 : int(1..2)]) + \/ + or([!or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q71, q89] != 3 /\ + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q71, q89] = q52 + | q89 : int(1..2)]) + /\ + (b_PartitionOccurrence_WhichPart[q52] = q37 /\ + (toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q71, q88] + != 3 + /\ + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q71, q88] = + q52 | q88 : int(1..2)])) + < + sum([toInt(b_PartitionOccurrence_WhichPart[q54] = q37) * catchUndef(toInt(q54 = q52), 0) + | q54 : int(1..2)]) + /\ + (and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q71, q81] != 3 + /\ + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q71, q81] < q52 + -> + toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q71, q83] + != 3 + /\ + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q71, q83] + = + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q71, q81] + | q83 : int(1..2)])) + = + sum([toInt(b_PartitionOccurrence_WhichPart[q60] = q37) * + catchUndef(toInt(q60 = + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q71, q81]), + 0) + | q60 : int(1..2)]) + | q81 : int(1..2)]) + /\ + and([!or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q71, q84] + != 3 + /\ + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q71, q84] + = q55 + | q84 : int(1..2)]) + -> + (b_PartitionOccurrence_WhichPart[q55] = q37 -> + toInt(or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q71, q86] + != 3 + /\ + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q71, q86] + = q55 + | q86 : int(1..2)])) + = + sum([toInt(b_PartitionOccurrence_WhichPart[q57] = q37) * catchUndef(toInt(q57 = q55), 0) + | q57 : int(1..2)])) + | q55 : int(1..2), q55 < q52])))) + | q52 : int(1..2)])) + -> + toInt(or([q145 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ + and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q145, q146] = + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q71, q146] + | q146 : int(1..2)]) + | q145 : int(1..2)])) + = + toInt(or([q149 <= b_PartitionOccurrence_NumParts /\ + (and([b_PartitionOccurrence_WhichPart[q152] = q149 -> + or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q71, q154] + != 3 + /\ + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q71, q154] + = q152 + | q154 : int(1..2)]) + | q152 : int(1..2)]) + /\ + and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q71, q156] + != 3 + -> + or([b_PartitionOccurrence_WhichPart[q158] = q149 /\ + q158 = + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q71, q156] + | q158 : int(1..2)]) + | q156 : int(1..2)])) + | q149 : int(1..2)])) + | q71 : int(1..2)]) + /\ + and([and([q90 <= b_PartitionOccurrence_NumParts, + !or([q105 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ + (and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q105, q107] + != 3 + -> + or([b_PartitionOccurrence_WhichPart[q109] = q90 /\ + q109 = + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q105, q107] + | q109 : int(1..2)]) + | q107 : int(1..2)]) + /\ + and([b_PartitionOccurrence_WhichPart[q111] = q90 -> + or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q105, q113] + != 3 + /\ + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q105, q113] + = q111 + | q113 : int(1..2)]) + | q111 : int(1..2)])) + | q105 : int(1..2)]), + or([b_PartitionOccurrence_WhichPart[q122] = q90 /\ + (toInt(or([b_PartitionOccurrence_WhichPart[q115] = q90 /\ q115 = q122 | q115 : int(1..2)])) < + sum([toInt(b_PartitionOccurrence_WhichPart[q63] = q37) * catchUndef(toInt(q63 = q122), 0) + | q63 : int(1..2)]) + /\ + (and([b_PartitionOccurrence_WhichPart[q118] = q90 -> + toInt(or([b_PartitionOccurrence_WhichPart[q117] = q90 /\ q117 = q118 + | q117 : int(1..2)])) + = + sum([toInt(b_PartitionOccurrence_WhichPart[q69] = q37) * catchUndef(toInt(q69 = q118), 0) + | q69 : int(1..2)]) + | q118 : int(1..2), q118 < q122]) + /\ + and([!or([b_PartitionOccurrence_WhichPart[q121] = q90 /\ q121 = q64 | q121 : int(1..2)]) -> + (b_PartitionOccurrence_WhichPart[q64] = q37 -> + toInt(or([b_PartitionOccurrence_WhichPart[q120] = q90 /\ q120 = q64 + | q120 : int(1..2)])) + = + sum([toInt(b_PartitionOccurrence_WhichPart[q66] = q37) * catchUndef(toInt(q66 = q64), 0) + | q66 : int(1..2)])) + | q64 : int(1..2), q64 < q122]))) + | q122 : int(1..2)]) + \/ + or([!or([b_PartitionOccurrence_WhichPart[q131] = q90 /\ q131 = q52 | q131 : int(1..2)]) /\ + (b_PartitionOccurrence_WhichPart[q52] = q37 /\ + (toInt(or([b_PartitionOccurrence_WhichPart[q124] = q90 /\ q124 = q52 | q124 : int(1..2)])) < + sum([toInt(b_PartitionOccurrence_WhichPart[q54] = q37) * catchUndef(toInt(q54 = q52), 0) + | q54 : int(1..2)]) + /\ + (and([b_PartitionOccurrence_WhichPart[q127] = q90 -> + toInt(or([b_PartitionOccurrence_WhichPart[q126] = q90 /\ q126 = q127 + | q126 : int(1..2)])) + = + sum([toInt(b_PartitionOccurrence_WhichPart[q60] = q37) * + catchUndef(toInt(q60 = q127), 0) + | q60 : int(1..2)]) + | q127 : int(1..2), q127 < q52]) + /\ + and([!or([b_PartitionOccurrence_WhichPart[q130] = q90 /\ q130 = q55 | q130 : int(1..2)]) -> + (b_PartitionOccurrence_WhichPart[q55] = q37 -> + toInt(or([b_PartitionOccurrence_WhichPart[q129] = q90 /\ q129 = q55 + | q129 : int(1..2)])) + = + sum([toInt(b_PartitionOccurrence_WhichPart[q57] = q37) * + catchUndef(toInt(q57 = q55), 0) + | q57 : int(1..2)])) + | q55 : int(1..2), q55 < q52])))) + | q52 : int(1..2)]); + int(1..3)]) + -> + toInt(or([q134 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ + (and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q134, q136] + != 3 + -> + or([b_PartitionOccurrence_WhichPart[q138] = q90 /\ + q138 = + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q134, q136] + | q138 : int(1..2)]) + | q136 : int(1..2)]) + /\ + and([b_PartitionOccurrence_WhichPart[q140] = q90 -> + or([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q134, q142] + != 3 + /\ + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q134, q142] + = q140 + | q142 : int(1..2)]) + | q140 : int(1..2)])) + | q134 : int(1..2)])) + = + toInt(or([q93 <= b_PartitionOccurrence_NumParts /\ + (and([b_PartitionOccurrence_WhichPart[q96] = q93 -> + or([b_PartitionOccurrence_WhichPart[q98] = q90 /\ q98 = q96 | q98 : int(1..2)]) + | q96 : int(1..2)]) + /\ + and([b_PartitionOccurrence_WhichPart[q100] = q90 -> + or([b_PartitionOccurrence_WhichPart[q102] = q93 /\ q102 = q100 | q102 : int(1..2)]) + | q100 : int(1..2)])) + | q93 : int(1..2)])) + | q90 : int(1..2)]))) + | q37 : int(1..2)]), + alldifferent_except([toInt(q28 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q28, q29] != + 3) + * + catchUndef(a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q28, q29], + 0) + | q28 : int(1..2), q29 : int(1..2)], + 0), + and([q30 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> + sum([toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q30, q32] != 3) + | q32 : int(1..2)]) + >= 1 + | q30 : int(1..2)]), + 2 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> + [a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[1, q12] | q12 : int(1..2)] a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> + and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q5, q27] = 1 + | q27 : int(1..2)]) + | q5 : int(1..2)]), + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker <= 2, + and([q6 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q6, 1] < + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q6, 2] + \/ a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q6, 1] = 3 + | q6 : int(1..2)]), + and([q6 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> + (a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q6, 1] = 3 -> + a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q6, 2] = 3) + | q6 : int(1..2)]), + and([q6 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> + sum([toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q6, q9] != 3) + | q9 : int(1..2)]) + <= 2 + | q6 : int(1..2)]), + 2 = + sum([toInt(q14 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker) * + catchUndef(sum([toInt(a_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q14, q16] != + 3) + | q16 : int(1..2)]), + 0) + | q14 : int(1..2)]), + and([q17 <= b_PartitionOccurrence_NumParts -> b_PartitionOccurrence_PartSizes[q17] <= 2 | q17 : int(1..2)]), + and([q17 > b_PartitionOccurrence_NumParts -> b_PartitionOccurrence_PartSizes[q17] = 0 | q17 : int(1..2)]), + b_PartitionOccurrence_NumParts <= 2, + b_PartitionOccurrence_NumParts = max([b_PartitionOccurrence_WhichPart[q20] | q20 : int(1..2)]), + and([b_PartitionOccurrence_PartSizes[q21] = + sum([toInt(b_PartitionOccurrence_WhichPart[q22] = q21) | q22 : int(1..2)]) + | q21 : int(1..2)]), + and([q23 <= b_PartitionOccurrence_NumParts -> + and([b_PartitionOccurrence_WhichPart[q24] = q23 -> b_PartitionOccurrence_FirstIndex[q23] <= q24 + | q24 : int(1..2)]) + | q23 : int(1..2)]), + and([q23 <= b_PartitionOccurrence_NumParts -> + or([b_PartitionOccurrence_WhichPart[q24] = q23 /\ b_PartitionOccurrence_FirstIndex[q23] = q24 + | q24 : int(1..2)]) + | q23 : int(1..2)]), + and([q23 > b_PartitionOccurrence_NumParts -> b_PartitionOccurrence_FirstIndex[q23] = 1 | q23 : int(1..2)]), + and([q25 <= b_PartitionOccurrence_NumParts /\ q26 <= b_PartitionOccurrence_NumParts -> + (q25 < q26 <-> b_PartitionOccurrence_FirstIndex[q25] < b_PartitionOccurrence_FirstIndex[q26]) + | q25 : int(1..2), q26 : int(1..2)]) + diff --git a/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_3_1-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_3_1-solution000001.solution new file mode 100644 index 0000000000..cde05d5274 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_3_1-solution000001.solution @@ -0,0 +1,11 @@ +language Essence 1.3 + +letting a be partition({1, 2}) +$ Visualisation for a +$ 1 2 + +letting b be partition({1}, {2}) +$ Visualisation for b +$ 1 +$ 2 + diff --git a/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_3_1.eprime.orig b/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_3_1.eprime.orig deleted file mode 100644 index 72047fad24..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_3_1.eprime.orig +++ /dev/null @@ -1,852 +0,0 @@ -language ESSENCE' 1.0 - -find a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker: int(0..2) -find a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker: - matrix indexed by [int(1..2)] of int(0..2) -find a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values: - matrix indexed by [int(1..2), int(1..2)] of int(1..2) -find b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker: int(0..2) -find b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence: matrix indexed by [int(1..2), int(1..2)] of bool -branching on - [a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker, - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker, - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values, - b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker, - b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence] -such that - or([q37 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - (toInt(or([q129 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - (a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q129] = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q37] - /\ - and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q129, q130] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q37, q130] - | q130 : int(1..2)])) - | q129 : int(1..2)])) - < - toInt(or([q134 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ - (and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q134, q135] -> - or([q137 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q37] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q37, q137] - = q135 - | q137 : int(1..2)]) - | q135 : int(1..2)]) - /\ - and([q139 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q37] - -> - b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence - [q134, - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q37, q139]] - | q139 : int(1..2)])) - | q134 : int(1..2)])) - /\ - (and([q141 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - (or([q200 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q141] - /\ - (toInt(or([q221 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q141] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q141, q221] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q141, q200] - | q221 : int(1..2)])) - < - toInt(or([q223 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q37] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q37, q223] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q141, q200] - | q223 : int(1..2)])) - /\ - (and([q224 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q141] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q141, q224] - < - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q141, q200] - -> - toInt(or([q233 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q141] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q141, q233] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q141, q224] - | q233 : int(1..2)])) - = - toInt(or([q235 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q37] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q37, q235] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q141, q224] - | q235 : int(1..2)])) - | q224 : int(1..2)]) - /\ - and([and([q225 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q37], - !or([q231 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q141] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q141, q231] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q37, q225] - | q231 : int(1..2)]), - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q37, q225] - < - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q141, q200]; - int(1..3)]) - -> - toInt(or([q227 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q141] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q141, q227] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q37, q225] - | q227 : int(1..2)])) - = - toInt(or([q229 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q37] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q37, q229] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q37, q225] - | q229 : int(1..2)])) - | q225 : int(1..2)]))) - | q200 : int(1..2)]) - \/ - or([q201 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q37] /\ - !or([q219 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q141] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q141, q219] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q37, q201] - | q219 : int(1..2)]) - /\ - (toInt(or([q203 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q141] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q141, q203] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q37, q201] - | q203 : int(1..2)])) - < - toInt(or([q205 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q37] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q37, q205] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q37, q201] - | q205 : int(1..2)])) - /\ - (and([q206 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q141] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q141, q206] - < - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q37, q201] - -> - toInt(or([q215 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q141] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q141, q215] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q141, q206] - | q215 : int(1..2)])) - = - toInt(or([q217 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q37] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q37, q217] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q141, q206] - | q217 : int(1..2)])) - | q206 : int(1..2)]) - /\ - and([and([q207 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q37], - !or([q213 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q141] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q141, q213] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q37, q207] - | q213 : int(1..2)]), - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q37, q207] - < - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q37, q201]; - int(1..3)]) - -> - toInt(or([q209 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q141] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q141, q209] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q37, q207] - | q209 : int(1..2)])) - = - toInt(or([q211 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q37] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q37, q211] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q37, q207] - | q211 : int(1..2)])) - | q207 : int(1..2)]))) - | q201 : int(1..2)])) - -> - toInt(or([q187 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - (a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q187] = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q141] - /\ - and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q187, q188] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q141, q188] - | q188 : int(1..2)])) - | q187 : int(1..2)])) - = - toInt(or([q192 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ - (and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q192, q193] -> - or([q195 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q141] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q141, q195] - = q193 - | q195 : int(1..2)]) - | q193 : int(1..2)]) - /\ - and([q197 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q141] - -> - b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence - [q192, - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q141, q197]] - | q197 : int(1..2)])) - | q192 : int(1..2)])) - | q141 : int(1..2)]) - /\ - and([and([q143 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker, - !or([q159 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - (and([q161 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q159] - -> - b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence - [q143, - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q159, q161]] - | q161 : int(1..2)]) - /\ - and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q143, q162] -> - or([q164 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q159] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q159, q164] - = q162 - | q164 : int(1..2)]) - | q162 : int(1..2)])) - | q159 : int(1..2)]), - or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q143, q165] /\ - (toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q143, q165]) < - toInt(or([q178 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q37] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q37, q178] - = q165 - | q178 : int(1..2)])) - /\ - (and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q143, q166] -> - toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q143, q166]) = - toInt(or([q184 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q37] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q37, q184] - = q166 - | q184 : int(1..2)])) - | q166 : int(1..2), q166 < q165]) - /\ - and([and([q179 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q37], - !or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q143, q182] /\ - q182 = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q37, q179] - | q182 : int(1..2)]), - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q37, q179] - < q165; - int(1..3)]) - -> - toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence - [q143, - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q37, q179]]) - = - toInt(or([q181 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q37] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q37, q181] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q37, q179] - | q181 : int(1..2)])) - | q179 : int(1..2)]))) - | q165 : int(1..2)]) - \/ - or([q167 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q37] - /\ - !or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q143, q176] /\ - q176 = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q37, q167] - | q176 : int(1..2)]) - /\ - (toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence - [q143, - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q37, q167]]) - < - toInt(or([q169 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q37] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q37, q169] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q37, q167] - | q169 : int(1..2)])) - /\ - (and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q143, q166] /\ - q166 < - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q37, q167] - -> - toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q143, q166]) = - toInt(or([q175 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q37] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q37, q175] - = q166 - | q175 : int(1..2)])) - | q166 : int(1..2)]) - /\ - and([and([q170 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q37], - !or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q143, q173] /\ - q173 = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q37, q170] - | q173 : int(1..2)]), - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q37, q170] - < - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q37, q167]; - int(1..3)]) - -> - toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence - [q143, - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q37, q170]]) - = - toInt(or([q172 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q37] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q37, q172] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q37, q170] - | q172 : int(1..2)])) - | q170 : int(1..2)]))) - | q167 : int(1..2)]); - int(1..3)]) - -> - toInt(or([q146 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - (and([q148 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q146] - -> - b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence - [q143, - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q146, q148]] - | q148 : int(1..2)]) - /\ - and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q143, q149] -> - or([q151 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q146] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q146, q151] - = q149 - | q151 : int(1..2)]) - | q149 : int(1..2)])) - | q146 : int(1..2)])) - = - toInt(or([q154 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ - and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q154, q155] = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q143, q155] - | q155 : int(1..2)]) - | q154 : int(1..2)])) - | q143 : int(1..2)]))) - | q37 : int(1..2)]) - \/ - or([q39 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ - !or([q121 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - (and([q123 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q121] -> - b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence - [q39, - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q121, q123]] - | q123 : int(1..2)]) - /\ - and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q39, q124] -> - or([q126 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q121] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q121, q126] - = q124 - | q126 : int(1..2)]) - | q124 : int(1..2)])) - | q121 : int(1..2)]) - /\ - (toInt(or([q42 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - (and([q44 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q42] - -> - b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence - [q39, - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q42, q44]] - | q44 : int(1..2)]) - /\ - and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q39, q45] -> - or([q47 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q42] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q42, q47] - = q45 - | q47 : int(1..2)]) - | q45 : int(1..2)])) - | q42 : int(1..2)])) - < - toInt(or([q50 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ - and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q50, q51] = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q39, q51] - | q51 : int(1..2)]) - | q50 : int(1..2)])) - /\ - (and([q54 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - (or([q98 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q54] /\ - (toInt(or([q111 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q54] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q54, q111] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q54, q98] - | q111 : int(1..2)])) - < - toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence - [q39, - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q54, q98]]) - /\ - (and([q112 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q54] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q54, q112] - < - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q54, q98] - -> - toInt(or([q118 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q54] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q54, q118] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q54, q112] - | q118 : int(1..2)])) - = - toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence - [q39, - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q54, q112]]) - | q112 : int(1..2)]) - /\ - and([and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q39, q97], - !or([q116 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q54] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q54, q116] - = q97 - | q116 : int(1..2)]), - q97 < - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q54, q98]; - int(1..3)]) - -> - toInt(or([q114 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q54] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q54, q114] - = q97 - | q114 : int(1..2)])) - = toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q39, q97]) - | q97 : int(1..2)]))) - | q98 : int(1..2)]) - \/ - or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q39, q96] /\ - !or([q109 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q54] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q54, q109] - = q96 - | q109 : int(1..2)]) - /\ - (toInt(or([q100 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q54] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q54, q100] - = q96 - | q100 : int(1..2)])) - < toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q39, q96]) - /\ - (and([q101 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q54] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q54, q101] - < q96 - -> - toInt(or([q107 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q54] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q54, q107] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q54, q101] - | q107 : int(1..2)])) - = - toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence - [q39, - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q54, q101]]) - | q101 : int(1..2)]) - /\ - and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q39, q97] /\ - !or([q105 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q54] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q54, q105] - = q97 - | q105 : int(1..2)]) - -> - toInt(or([q103 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q54] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q54, q103] - = q97 - | q103 : int(1..2)])) - = toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q39, q97]) - | q97 : int(1..2), q97 < q96]))) - | q96 : int(1..2)])) - -> - toInt(or([q85 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - (a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q85] = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q54] - /\ - and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q85, q86] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q54, q86] - | q86 : int(1..2)])) - | q85 : int(1..2)])) - = - toInt(or([q90 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ - (and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q90, q91] -> - or([q93 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q54] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q54, q93] - = q91 - | q93 : int(1..2)]) - | q91 : int(1..2)]) - /\ - and([q95 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q54] - -> - b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence - [q90, - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q54, q95]] - | q95 : int(1..2)])) - | q90 : int(1..2)])) - | q54 : int(1..2)]) - /\ - and([and([q56 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker, - !or([q72 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - (and([q74 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q72] - -> - b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence - [q56, - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q72, q74]] - | q74 : int(1..2)]) - /\ - and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q56, q75] -> - or([q77 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q72] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q72, q77] - = q75 - | q77 : int(1..2)]) - | q75 : int(1..2)])) - | q72 : int(1..2)]), - or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q56, q78] /\ - (toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q56, q78]) < - toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q39, q78]) - /\ - (and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q56, q79] -> - toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q56, q79]) = - toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q39, q79]) - | q79 : int(1..2), q79 < q78]) - /\ - and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q39, q79] /\ - !or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q56, q82] /\ - q82 = q79 - | q82 : int(1..2)]) - -> - toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q56, q79]) = - toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q39, q79]) - | q79 : int(1..2), q79 < q78]))) - | q78 : int(1..2)]) - \/ - or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q39, q78] /\ - !or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q56, q81] /\ q81 = q78 - | q81 : int(1..2)]) - /\ - (toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q56, q78]) < - toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q39, q78]) - /\ - (and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q56, q79] -> - toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q56, q79]) = - toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q39, q79]) - | q79 : int(1..2), q79 < q78]) - /\ - and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q39, q79] /\ - !or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q56, q80] /\ - q80 = q79 - | q80 : int(1..2)]) - -> - toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q56, q79]) = - toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q39, q79]) - | q79 : int(1..2), q79 < q78]))) - | q78 : int(1..2)]); - int(1..3)]) - -> - toInt(or([q59 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - (and([q61 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q59] - -> - b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence - [q56, - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q59, q61]] - | q61 : int(1..2)]) - /\ - and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q56, q62] -> - or([q64 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q59] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q59, q64] - = q62 - | q64 : int(1..2)]) - | q62 : int(1..2)])) - | q59 : int(1..2)])) - = - toInt(or([q67 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ - and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q67, q68] = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q56, q68] - | q68 : int(1..2)]) - | q67 : int(1..2)])) - | q56 : int(1..2)]))) - | q39 : int(1..2)]), - alldifferent_except([toInt(q31 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - q32 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q31]) - * - catchUndef(a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q31, q32], - 0) - | q31 : int(1..2), q32 : int(1..2)], - 0), - and([q33 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q33] >= 1 - | q33 : int(1..2)]), - 2 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - flatten([[a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[1]; int(1)], - [a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[1, q11] - | q11 : int(1..2)]; - int(1..2)]) - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q5] = 0 /\ - and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q5, q27] = 1 - | q27 : int(1..2)]) - | q5 : int(1..2)]), - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker <= 2, - and([q6 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - (2 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q6] -> - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q6, 1] < - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q6, 2]) - | q6 : int(1..2)]), - and([q6 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - and([q8 > a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q6] -> - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q6, q8] = 1 - | q8 : int(1..2)]) - | q6 : int(1..2)]), - and([q6 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q6] <= 2 - | q6 : int(1..2)]), - 2 = - sum([toInt(q13 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker) * - catchUndef(a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q13], 0) - | q13 : int(1..2)]), - and([1 = - sum([toInt(q28 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q28, q14]) - | q28 : int(1..2)]) - | q14 : int(1..2)]), - and([q29 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> - sum([toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q29, q30]) | q30 : int(1..2)]) >= 1 - | q29 : int(1..2)]), - 2 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> - [-toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[1, q22]) | q22 : int(1..2)] b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> - and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q18, q24] = false | q24 : int(1..2)]) - | q18 : int(1..2)]), - b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker <= 2, - and([q19 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> - sum([toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q19, q20]) | q20 : int(1..2)]) <= 2 - | q19 : int(1..2)]), - 2 = - sum([toInt(q25 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker) * - catchUndef(sum([toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q25, q26]) - | q26 : int(1..2)]), - 0) - | q25 : int(1..2)]) - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_3_2-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_3_2-solution000001.solution new file mode 100644 index 0000000000..cde05d5274 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_3_2-solution000001.solution @@ -0,0 +1,11 @@ +language Essence 1.3 + +letting a be partition({1, 2}) +$ Visualisation for a +$ 1 2 + +letting b be partition({1}, {2}) +$ Visualisation for b +$ 1 +$ 2 + diff --git a/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_3_2.eprime.orig b/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_3_2.eprime.orig deleted file mode 100644 index c88908f280..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_3_2.eprime.orig +++ /dev/null @@ -1,1228 +0,0 @@ -language ESSENCE' 1.0 - -find a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker: int(0..2) -find a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker: - matrix indexed by [int(1..2)] of int(0..2) -find a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values: - matrix indexed by [int(1..2), int(1..2)] of int(1..2) -find b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker: int(0..2) -find b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy: - matrix indexed by [int(1..2), int(1..2)] of int(1..3) -branching on - [a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker, - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker, - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values, - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker, - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy] -such that - or([q43 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - (toInt(or([q198 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - (a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q198] = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q43] - /\ - and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q198, q199] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q43, q199] - | q199 : int(1..2)])) - | q198 : int(1..2)])) - < - toInt(or([q203 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ - (and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q203, q205] != 3 - -> - or([q207 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q43] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q43, q207] - = b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q203, q205] - | q207 : int(1..2)]) - | q205 : int(1..2)]) - /\ - and([q209 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q43] - -> - or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q203, q211] != - 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q203, q211] = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q43, q209] - | q211 : int(1..2)]) - | q209 : int(1..2)])) - | q203 : int(1..2)])) - /\ - (and([q213 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - (or([q299 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q213] - /\ - (toInt(or([q320 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q213] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q213, q320] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q213, q299] - | q320 : int(1..2)])) - < - toInt(or([q322 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q43] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q43, q322] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q213, q299] - | q322 : int(1..2)])) - /\ - (and([q323 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q213] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q213, q323] - < - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q213, q299] - -> - toInt(or([q332 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q213] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q213, q332] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q213, q323] - | q332 : int(1..2)])) - = - toInt(or([q334 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q43] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q43, q334] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q213, q323] - | q334 : int(1..2)])) - | q323 : int(1..2)]) - /\ - and([and([q324 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q43], - !or([q330 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q213] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q213, q330] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q43, q324] - | q330 : int(1..2)]), - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q43, q324] - < - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q213, q299]; - int(1..3)]) - -> - toInt(or([q326 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q213] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q213, q326] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q43, q324] - | q326 : int(1..2)])) - = - toInt(or([q328 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q43] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q43, q328] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q43, q324] - | q328 : int(1..2)])) - | q324 : int(1..2)]))) - | q299 : int(1..2)]) - \/ - or([q300 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q43] /\ - !or([q318 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q213] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q213, q318] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q43, q300] - | q318 : int(1..2)]) - /\ - (toInt(or([q302 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q213] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q213, q302] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q43, q300] - | q302 : int(1..2)])) - < - toInt(or([q304 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q43] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q43, q304] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q43, q300] - | q304 : int(1..2)])) - /\ - (and([q305 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q213] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q213, q305] - < - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q43, q300] - -> - toInt(or([q314 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q213] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q213, q314] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q213, q305] - | q314 : int(1..2)])) - = - toInt(or([q316 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q43] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q43, q316] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q213, q305] - | q316 : int(1..2)])) - | q305 : int(1..2)]) - /\ - and([and([q306 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q43], - !or([q312 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q213] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q213, q312] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q43, q306] - | q312 : int(1..2)]), - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q43, q306] - < - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q43, q300]; - int(1..3)]) - -> - toInt(or([q308 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q213] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q213, q308] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q43, q306] - | q308 : int(1..2)])) - = - toInt(or([q310 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q43] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q43, q310] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q43, q306] - | q310 : int(1..2)])) - | q306 : int(1..2)]))) - | q300 : int(1..2)])) - -> - toInt(or([q283 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - (a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q283] = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q213] - /\ - and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q283, q284] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q213, q284] - | q284 : int(1..2)])) - | q283 : int(1..2)])) - = - toInt(or([q288 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ - (and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q288, q290] - != 3 - -> - or([q292 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q213] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q213, q292] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q288, q290] - | q292 : int(1..2)]) - | q290 : int(1..2)]) - /\ - and([q294 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q213] - -> - or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q288, q296] - != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q288, q296] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q213, q294] - | q296 : int(1..2)]) - | q294 : int(1..2)])) - | q288 : int(1..2)])) - | q213 : int(1..2)]) - /\ - and([and([q215 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker, - !or([q234 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - (and([q236 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q234] - -> - or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q215, q238] - != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q215, q238] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q234, q236] - | q238 : int(1..2)]) - | q236 : int(1..2)]) - /\ - and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q215, q240] - != 3 - -> - or([q242 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q234] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q234, q242] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q215, q240] - | q242 : int(1..2)]) - | q240 : int(1..2)])) - | q234 : int(1..2)]), - or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q215, q245] != 3 /\ - (toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q215, q266] - != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q215, q266] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q215, q245] - | q266 : int(1..2)])) - < - toInt(or([q268 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q43] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q43, q268] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q215, q245] - | q268 : int(1..2)])) - /\ - (and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q215, q269] - != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q215, q269] - < - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q215, q245] - -> - toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q215, q278] - != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q215, q278] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q215, q269] - | q278 : int(1..2)])) - = - toInt(or([q280 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q43] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q43, q280] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q215, q269] - | q280 : int(1..2)])) - | q269 : int(1..2)]) - /\ - and([and([q270 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q43], - !or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q215, q276] - != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q215, q276] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q43, q270] - | q276 : int(1..2)]), - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q43, q270] - < - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q215, q245]; - int(1..3)]) - -> - toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q215, q272] - != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q215, q272] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q43, q270] - | q272 : int(1..2)])) - = - toInt(or([q274 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q43] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q43, q274] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q43, q270] - | q274 : int(1..2)])) - | q270 : int(1..2)]))) - | q245 : int(1..2)]) - \/ - or([q246 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q43] - /\ - !or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q215, q264] != - 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q215, q264] = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q43, q246] - | q264 : int(1..2)]) - /\ - (toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q215, q248] - != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q215, q248] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q43, q246] - | q248 : int(1..2)])) - < - toInt(or([q250 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q43] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q43, q250] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q43, q246] - | q250 : int(1..2)])) - /\ - (and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q215, q251] - != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q215, q251] - < - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q43, q246] - -> - toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q215, q260] - != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q215, q260] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q215, q251] - | q260 : int(1..2)])) - = - toInt(or([q262 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q43] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q43, q262] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q215, q251] - | q262 : int(1..2)])) - | q251 : int(1..2)]) - /\ - and([and([q252 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q43], - !or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q215, q258] - != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q215, q258] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q43, q252] - | q258 : int(1..2)]), - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q43, q252] - < - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q43, q246]; - int(1..3)]) - -> - toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q215, q254] - != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q215, q254] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q43, q252] - | q254 : int(1..2)])) - = - toInt(or([q256 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q43] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q43, q256] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q43, q252] - | q256 : int(1..2)])) - | q252 : int(1..2)]))) - | q246 : int(1..2)]); - int(1..3)]) - -> - toInt(or([q218 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - (and([q220 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q218] - -> - or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q215, q222] - != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q215, q222] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q218, q220] - | q222 : int(1..2)]) - | q220 : int(1..2)]) - /\ - and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q215, q224] - != 3 - -> - or([q226 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q218] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q218, q226] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q215, q224] - | q226 : int(1..2)]) - | q224 : int(1..2)])) - | q218 : int(1..2)])) - = - toInt(or([q229 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ - and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q229, q230] = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q215, q230] - | q230 : int(1..2)]) - | q229 : int(1..2)])) - | q215 : int(1..2)]))) - | q43 : int(1..2)]) - \/ - or([q45 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ - !or([q187 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - (and([q189 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q187] -> - or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q45, q191] != 3 /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q45, q191] = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q187, q189] - | q191 : int(1..2)]) - | q189 : int(1..2)]) - /\ - and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q45, q193] != 3 -> - or([q195 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q187] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q187, q195] - = b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q45, q193] - | q195 : int(1..2)]) - | q193 : int(1..2)])) - | q187 : int(1..2)]) - /\ - (toInt(or([q48 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - (and([q50 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q48] - -> - or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q45, q52] != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q45, q52] = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q48, q50] - | q52 : int(1..2)]) - | q50 : int(1..2)]) - /\ - and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q45, q54] != 3 -> - or([q56 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q48] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q48, q56] - = b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q45, q54] - | q56 : int(1..2)]) - | q54 : int(1..2)])) - | q48 : int(1..2)])) - < - toInt(or([q59 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ - and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q59, q60] = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q45, q60] - | q60 : int(1..2)]) - | q59 : int(1..2)])) - /\ - (and([q63 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - (or([q149 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q63] /\ - (toInt(or([q170 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q63] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q63, q170] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q63, q149] - | q170 : int(1..2)])) - < - toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q45, q172] - != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q45, q172] = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q63, q149] - | q172 : int(1..2)])) - /\ - (and([q173 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q63] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q63, q173] - < - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q63, q149] - -> - toInt(or([q182 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q63] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q63, q182] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q63, q173] - | q182 : int(1..2)])) - = - toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q45, q184] - != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q45, q184] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q63, q173] - | q184 : int(1..2)])) - | q173 : int(1..2)]) - /\ - and([and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q45, q174] - != 3, - !or([q176 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q63] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q63, q176] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q45, q174] - | q176 : int(1..2)]), - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q45, q174] - < - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q63, q149]; - int(1..3)]) - -> - toInt(or([q178 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q63] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q63, q178] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q45, q174] - | q178 : int(1..2)])) - = - toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q45, q180] - != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q45, q180] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q45, q174] - | q180 : int(1..2)])) - | q174 : int(1..2)]))) - | q149 : int(1..2)]) - \/ - or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q45, q150] != 3 /\ - !or([q152 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q63] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q63, q152] - = b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q45, q150] - | q152 : int(1..2)]) - /\ - (toInt(or([q154 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q63] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q63, q154] - = b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q45, q150] - | q154 : int(1..2)])) - < - toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q45, q156] - != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q45, q156] = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q45, q150] - | q156 : int(1..2)])) - /\ - (and([q157 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q63] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q63, q157] - < b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q45, q150] - -> - toInt(or([q166 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q63] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q63, q166] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q63, q157] - | q166 : int(1..2)])) - = - toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q45, q168] - != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q45, q168] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q63, q157] - | q168 : int(1..2)])) - | q157 : int(1..2)]) - /\ - and([and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q45, q158] - != 3, - !or([q160 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q63] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q63, q160] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q45, q158] - | q160 : int(1..2)]), - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q45, q158] - < - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q45, q150]; - int(1..3)]) - -> - toInt(or([q162 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q63] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q63, q162] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q45, q158] - | q162 : int(1..2)])) - = - toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q45, q164] - != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q45, q164] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q45, q158] - | q164 : int(1..2)])) - | q158 : int(1..2)]))) - | q150 : int(1..2)])) - -> - toInt(or([q133 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - (a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q133] = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q63] - /\ - and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q133, q134] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q63, q134] - | q134 : int(1..2)])) - | q133 : int(1..2)])) - = - toInt(or([q138 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ - (and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q138, q140] - != 3 - -> - or([q142 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q63] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q63, q142] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q138, q140] - | q142 : int(1..2)]) - | q140 : int(1..2)]) - /\ - and([q144 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q63] - -> - or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q138, q146] - != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q138, q146] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q63, q144] - | q146 : int(1..2)]) - | q144 : int(1..2)])) - | q138 : int(1..2)])) - | q63 : int(1..2)]) - /\ - and([and([q65 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker, - !or([q84 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - (and([q86 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q84] - -> - or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q65, q88] - != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q65, q88] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q84, q86] - | q88 : int(1..2)]) - | q86 : int(1..2)]) - /\ - and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q65, q90] != - 3 - -> - or([q92 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q84] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q84, q92] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q65, q90] - | q92 : int(1..2)]) - | q90 : int(1..2)])) - | q84 : int(1..2)]), - or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q65, q95] != 3 /\ - (toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q65, q116] - != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q65, q116] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q65, q95] - | q116 : int(1..2)])) - < - toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q45, q118] - != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q45, q118] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q65, q95] - | q118 : int(1..2)])) - /\ - (and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q65, q119] - != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q65, q119] < - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q65, q95] - -> - toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q65, q128] - != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q65, q128] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q65, q119] - | q128 : int(1..2)])) - = - toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q45, q130] - != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q45, q130] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q65, q119] - | q130 : int(1..2)])) - | q119 : int(1..2)]) - /\ - and([and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q45, q120] - != 3, - !or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q65, q122] - != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q65, q122] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q45, q120] - | q122 : int(1..2)]), - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q45, q120] - < - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q65, q95]; - int(1..3)]) - -> - toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q65, q124] - != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q65, q124] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q45, q120] - | q124 : int(1..2)])) - = - toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q45, q126] - != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q45, q126] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q45, q120] - | q126 : int(1..2)])) - | q120 : int(1..2)]))) - | q95 : int(1..2)]) - \/ - or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q45, q96] != 3 /\ - !or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q65, q98] != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q65, q98] = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q45, q96] - | q98 : int(1..2)]) - /\ - (toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q65, q100] - != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q65, q100] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q45, q96] - | q100 : int(1..2)])) - < - toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q45, q102] - != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q45, q102] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q45, q96] - | q102 : int(1..2)])) - /\ - (and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q65, q103] - != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q65, q103] < - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q45, q96] - -> - toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q65, q112] - != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q65, q112] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q65, q103] - | q112 : int(1..2)])) - = - toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q45, q114] - != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q45, q114] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q65, q103] - | q114 : int(1..2)])) - | q103 : int(1..2)]) - /\ - and([and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q45, q104] - != 3, - !or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q65, q106] - != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q65, q106] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q45, q104] - | q106 : int(1..2)]), - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q45, q104] - < - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q45, q96]; - int(1..3)]) - -> - toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q65, q108] - != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q65, q108] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q45, q104] - | q108 : int(1..2)])) - = - toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q45, q110] - != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q45, q110] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q45, q104] - | q110 : int(1..2)])) - | q104 : int(1..2)]))) - | q96 : int(1..2)]); - int(1..3)]) - -> - toInt(or([q68 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - (and([q70 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q68] - -> - or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q65, q72] - != 3 - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q65, q72] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q68, q70] - | q72 : int(1..2)]) - | q70 : int(1..2)]) - /\ - and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q65, q74] != - 3 - -> - or([q76 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q68] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q68, q76] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q65, q74] - | q76 : int(1..2)]) - | q74 : int(1..2)])) - | q68 : int(1..2)])) - = - toInt(or([q79 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ - and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q79, q80] = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q65, q80] - | q80 : int(1..2)]) - | q79 : int(1..2)])) - | q65 : int(1..2)]))) - | q45 : int(1..2)]), - alldifferent_except([toInt(q32 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - q33 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q32]) - * - catchUndef(a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q32, q33], - 0) - | q32 : int(1..2), q33 : int(1..2)], - 0), - and([q34 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q34] >= 1 - | q34 : int(1..2)]), - 2 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - flatten([[a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[1]; int(1)], - [a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[1, q11] - | q11 : int(1..2)]; - int(1..2)]) - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q5] = 0 /\ - and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q5, q30] = 1 - | q30 : int(1..2)]) - | q5 : int(1..2)]), - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker <= 2, - and([q6 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - (2 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q6] -> - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q6, 1] < - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q6, 2]) - | q6 : int(1..2)]), - and([q6 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - and([q8 > a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q6] -> - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q6, q8] = 1 - | q8 : int(1..2)]) - | q6 : int(1..2)]), - and([q6 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q6] <= 2 - | q6 : int(1..2)]), - 2 = - sum([toInt(q13 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker) * - catchUndef(a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q13], 0) - | q13 : int(1..2)]), - alldifferent_except([toInt(q35 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q35, q36] != - 3) - * - catchUndef(b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy - [q35, q36], - 0) - | q35 : int(1..2), q36 : int(1..2)], - 0), - and([q37 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - sum([toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q37, q39] != 3) - | q39 : int(1..2)]) - >= 1 - | q37 : int(1..2)]), - 2 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - [b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[1, q25] | q25 : int(1..2)] b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q18, q31] = 1 - | q31 : int(1..2)]) - | q18 : int(1..2)]), - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker <= 2, - and([q19 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q19, 1] < - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q19, 2] - \/ b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q19, 1] = 3 - | q19 : int(1..2)]), - and([q19 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - (b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q19, 1] = 3 -> - b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q19, 2] = 3) - | q19 : int(1..2)]), - and([q19 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - sum([toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q19, q22] != 3) - | q22 : int(1..2)]) - <= 2 - | q19 : int(1..2)]), - 2 = - sum([toInt(q27 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker) * - catchUndef(sum([toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q27, q29] != - 3) - | q29 : int(1..2)]), - 0) - | q27 : int(1..2)]) - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_3_3-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_3_3-solution000001.solution new file mode 100644 index 0000000000..cde05d5274 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_3_3-solution000001.solution @@ -0,0 +1,11 @@ +language Essence 1.3 + +letting a be partition({1, 2}) +$ Visualisation for a +$ 1 2 + +letting b be partition({1}, {2}) +$ Visualisation for b +$ 1 +$ 2 + diff --git a/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_3_3.eprime.orig b/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_3_3.eprime.orig deleted file mode 100644 index 849d1cad80..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_3_3.eprime.orig +++ /dev/null @@ -1,1127 +0,0 @@ -language ESSENCE' 1.0 - -find a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker: int(0..2) -find a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker: - matrix indexed by [int(1..2)] of int(0..2) -find a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values: - matrix indexed by [int(1..2), int(1..2)] of int(1..2) -find b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker: int(0..2) -find b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker: - matrix indexed by [int(1..2)] of int(0..2) -find b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values: - matrix indexed by [int(1..2), int(1..2)] of int(1..2) -branching on - [a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker, - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker, - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values, - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker, - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker, - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values] -such that - or([q38 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - (toInt(or([q163 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - (a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q163] = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q38] - /\ - and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q163, q164] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q38, q164] - | q164 : int(1..2)])) - | q163 : int(1..2)])) - < - toInt(or([q168 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - (b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q168] = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q38] - /\ - and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q168, q169] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q38, q169] - | q169 : int(1..2)])) - | q168 : int(1..2)])) - /\ - (and([q172 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - (or([q240 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q172] - /\ - (toInt(or([q261 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q172] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q172, q261] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q172, q240] - | q261 : int(1..2)])) - < - toInt(or([q263 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q38] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q38, q263] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q172, q240] - | q263 : int(1..2)])) - /\ - (and([q264 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q172] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q172, q264] - < - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q172, q240] - -> - toInt(or([q273 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q172] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q172, q273] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q172, q264] - | q273 : int(1..2)])) - = - toInt(or([q275 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q38] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q38, q275] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q172, q264] - | q275 : int(1..2)])) - | q264 : int(1..2)]) - /\ - and([and([q265 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q38], - !or([q271 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q172] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q172, q271] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q38, q265] - | q271 : int(1..2)]), - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q38, q265] - < - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q172, q240]; - int(1..3)]) - -> - toInt(or([q267 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q172] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q172, q267] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q38, q265] - | q267 : int(1..2)])) - = - toInt(or([q269 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q38] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q38, q269] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q38, q265] - | q269 : int(1..2)])) - | q265 : int(1..2)]))) - | q240 : int(1..2)]) - \/ - or([q241 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q38] /\ - !or([q259 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q172] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q172, q259] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q38, q241] - | q259 : int(1..2)]) - /\ - (toInt(or([q243 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q172] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q172, q243] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q38, q241] - | q243 : int(1..2)])) - < - toInt(or([q245 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q38] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q38, q245] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q38, q241] - | q245 : int(1..2)])) - /\ - (and([q246 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q172] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q172, q246] - < - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q38, q241] - -> - toInt(or([q255 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q172] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q172, q255] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q172, q246] - | q255 : int(1..2)])) - = - toInt(or([q257 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q38] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q38, q257] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q172, q246] - | q257 : int(1..2)])) - | q246 : int(1..2)]) - /\ - and([and([q247 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q38], - !or([q253 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q172] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q172, q253] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q38, q247] - | q253 : int(1..2)]), - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q38, q247] - < - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q38, q241]; - int(1..3)]) - -> - toInt(or([q249 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q172] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q172, q249] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q38, q247] - | q249 : int(1..2)])) - = - toInt(or([q251 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q38] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q38, q251] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q38, q247] - | q251 : int(1..2)])) - | q247 : int(1..2)]))) - | q241 : int(1..2)])) - -> - toInt(or([q230 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - (a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q230] = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q172] - /\ - and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q230, q231] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q172, q231] - | q231 : int(1..2)])) - | q230 : int(1..2)])) - = - toInt(or([q235 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - (b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q235] = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q172] - /\ - and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q235, q236] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q172, q236] - | q236 : int(1..2)])) - | q235 : int(1..2)])) - | q172 : int(1..2)]) - /\ - and([and([q174 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker, - !or([q187 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - (a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q187] = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q174] - /\ - and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q187, q188] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q174, q188] - | q188 : int(1..2)])) - | q187 : int(1..2)]), - or([q192 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q174] - /\ - (toInt(or([q213 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q174] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q174, q213] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q174, q192] - | q213 : int(1..2)])) - < - toInt(or([q215 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q38] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q38, q215] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q174, q192] - | q215 : int(1..2)])) - /\ - (and([q216 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q174] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q174, q216] - < - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q174, q192] - -> - toInt(or([q225 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q174] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q174, q225] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q174, q216] - | q225 : int(1..2)])) - = - toInt(or([q227 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q38] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q38, q227] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q174, q216] - | q227 : int(1..2)])) - | q216 : int(1..2)]) - /\ - and([and([q217 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q38], - !or([q223 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q174] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q174, q223] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q38, q217] - | q223 : int(1..2)]), - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q38, q217] - < - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q174, q192]; - int(1..3)]) - -> - toInt(or([q219 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q174] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q174, q219] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q38, q217] - | q219 : int(1..2)])) - = - toInt(or([q221 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q38] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q38, q221] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q38, q217] - | q221 : int(1..2)])) - | q217 : int(1..2)]))) - | q192 : int(1..2)]) - \/ - or([q193 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q38] - /\ - !or([q211 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q174] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q174, q211] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q38, q193] - | q211 : int(1..2)]) - /\ - (toInt(or([q195 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q174] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q174, q195] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q38, q193] - | q195 : int(1..2)])) - < - toInt(or([q197 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q38] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q38, q197] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q38, q193] - | q197 : int(1..2)])) - /\ - (and([q198 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q174] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q174, q198] - < - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q38, q193] - -> - toInt(or([q207 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q174] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q174, q207] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q174, q198] - | q207 : int(1..2)])) - = - toInt(or([q209 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q38] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q38, q209] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q174, q198] - | q209 : int(1..2)])) - | q198 : int(1..2)]) - /\ - and([and([q199 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q38], - !or([q205 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q174] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q174, q205] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q38, q199] - | q205 : int(1..2)]), - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q38, q199] - < - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q38, q193]; - int(1..3)]) - -> - toInt(or([q201 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q174] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q174, q201] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q38, q199] - | q201 : int(1..2)])) - = - toInt(or([q203 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q38] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q38, q203] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q38, q199] - | q203 : int(1..2)])) - | q199 : int(1..2)]))) - | q193 : int(1..2)]); - int(1..3)]) - -> - toInt(or([q177 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - (a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q177] = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q174] - /\ - and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q177, q178] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q174, q178] - | q178 : int(1..2)])) - | q177 : int(1..2)])) - = - toInt(or([q182 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - (b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q182] = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q174] - /\ - and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q182, q183] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q174, q183] - | q183 : int(1..2)])) - | q182 : int(1..2)])) - | q174 : int(1..2)]))) - | q38 : int(1..2)]) - \/ - or([q40 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - !or([q158 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - (a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q158] = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q40] - /\ - and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q158, q159] = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q40, q159] - | q159 : int(1..2)])) - | q158 : int(1..2)]) - /\ - (toInt(or([q43 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - (a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q43] = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q40] - /\ - and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q43, q44] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q40, q44] - | q44 : int(1..2)])) - | q43 : int(1..2)])) - < - toInt(or([q48 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - (b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q48] = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q40] - /\ - and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q48, q49] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q40, q49] - | q49 : int(1..2)])) - | q48 : int(1..2)])) - /\ - (and([q52 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - (or([q120 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q52] /\ - (toInt(or([q141 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q52] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q52, q141] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q52, q120] - | q141 : int(1..2)])) - < - toInt(or([q143 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q40] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q40, q143] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q52, q120] - | q143 : int(1..2)])) - /\ - (and([q144 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q52] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q52, q144] - < - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q52, q120] - -> - toInt(or([q153 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q52] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q52, q153] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q52, q144] - | q153 : int(1..2)])) - = - toInt(or([q155 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q40] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q40, q155] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q52, q144] - | q155 : int(1..2)])) - | q144 : int(1..2)]) - /\ - and([and([q145 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q40], - !or([q151 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q52] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q52, q151] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q40, q145] - | q151 : int(1..2)]), - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q40, q145] - < - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q52, q120]; - int(1..3)]) - -> - toInt(or([q147 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q52] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q52, q147] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q40, q145] - | q147 : int(1..2)])) - = - toInt(or([q149 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q40] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q40, q149] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q40, q145] - | q149 : int(1..2)])) - | q145 : int(1..2)]))) - | q120 : int(1..2)]) - \/ - or([q121 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q40] /\ - !or([q139 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q52] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q52, q139] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q40, q121] - | q139 : int(1..2)]) - /\ - (toInt(or([q123 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q52] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q52, q123] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q40, q121] - | q123 : int(1..2)])) - < - toInt(or([q125 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q40] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q40, q125] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q40, q121] - | q125 : int(1..2)])) - /\ - (and([q126 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q52] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q52, q126] - < - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q40, q121] - -> - toInt(or([q135 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q52] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q52, q135] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q52, q126] - | q135 : int(1..2)])) - = - toInt(or([q137 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q40] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q40, q137] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q52, q126] - | q137 : int(1..2)])) - | q126 : int(1..2)]) - /\ - and([and([q127 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q40], - !or([q133 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q52] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q52, q133] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q40, q127] - | q133 : int(1..2)]), - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q40, q127] - < - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q40, q121]; - int(1..3)]) - -> - toInt(or([q129 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q52] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q52, q129] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q40, q127] - | q129 : int(1..2)])) - = - toInt(or([q131 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q40] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q40, q131] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q40, q127] - | q131 : int(1..2)])) - | q127 : int(1..2)]))) - | q121 : int(1..2)])) - -> - toInt(or([q110 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - (a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q110] = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q52] - /\ - and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q110, q111] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q52, q111] - | q111 : int(1..2)])) - | q110 : int(1..2)])) - = - toInt(or([q115 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - (b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q115] = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q52] - /\ - and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q115, q116] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q52, q116] - | q116 : int(1..2)])) - | q115 : int(1..2)])) - | q52 : int(1..2)]) - /\ - and([and([q54 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker, - !or([q67 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - (a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q67] = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q54] - /\ - and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q67, q68] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q54, q68] - | q68 : int(1..2)])) - | q67 : int(1..2)]), - or([q72 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q54] - /\ - (toInt(or([q93 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q54] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q54, q93] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q54, q72] - | q93 : int(1..2)])) - < - toInt(or([q95 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q40] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q40, q95] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q54, q72] - | q95 : int(1..2)])) - /\ - (and([q96 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q54] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q54, q96] - < - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q54, q72] - -> - toInt(or([q105 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q54] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q54, q105] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q54, q96] - | q105 : int(1..2)])) - = - toInt(or([q107 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q40] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q40, q107] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q54, q96] - | q107 : int(1..2)])) - | q96 : int(1..2)]) - /\ - and([and([q97 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q40], - !or([q103 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q54] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q54, q103] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q40, q97] - | q103 : int(1..2)]), - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q40, q97] - < - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q54, q72]; - int(1..3)]) - -> - toInt(or([q99 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q54] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q54, q99] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q40, q97] - | q99 : int(1..2)])) - = - toInt(or([q101 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q40] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q40, q101] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q40, q97] - | q101 : int(1..2)])) - | q97 : int(1..2)]))) - | q72 : int(1..2)]) - \/ - or([q73 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q40] - /\ - !or([q91 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q54] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q54, q91] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q40, q73] - | q91 : int(1..2)]) - /\ - (toInt(or([q75 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q54] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q54, q75] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q40, q73] - | q75 : int(1..2)])) - < - toInt(or([q77 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q40] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q40, q77] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q40, q73] - | q77 : int(1..2)])) - /\ - (and([q78 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q54] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q54, q78] - < - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q40, q73] - -> - toInt(or([q87 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q54] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q54, q87] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q54, q78] - | q87 : int(1..2)])) - = - toInt(or([q89 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q40] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q40, q89] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q54, q78] - | q89 : int(1..2)])) - | q78 : int(1..2)]) - /\ - and([and([q79 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q40], - !or([q85 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q54] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q54, q85] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q40, q79] - | q85 : int(1..2)]), - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q40, q79] - < - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q40, q73]; - int(1..3)]) - -> - toInt(or([q81 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q54] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q54, q81] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q40, q79] - | q81 : int(1..2)])) - = - toInt(or([q83 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q40] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q40, q83] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q40, q79] - | q83 : int(1..2)])) - | q79 : int(1..2)]))) - | q73 : int(1..2)]); - int(1..3)]) - -> - toInt(or([q57 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - (a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q57] = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q54] - /\ - and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q57, q58] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q54, q58] - | q58 : int(1..2)])) - | q57 : int(1..2)])) - = - toInt(or([q62 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - (b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q62] = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q54] - /\ - and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q62, q63] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q54, q63] - | q63 : int(1..2)])) - | q62 : int(1..2)])) - | q54 : int(1..2)]))) - | q40 : int(1..2)]), - alldifferent_except([toInt(q29 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - q30 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q29]) - * - catchUndef(a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q29, q30], - 0) - | q29 : int(1..2), q30 : int(1..2)], - 0), - and([q31 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q31] >= 1 - | q31 : int(1..2)]), - 2 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - flatten([[a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[1]; int(1)], - [a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[1, q11] - | q11 : int(1..2)]; - int(1..2)]) - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q5] = 0 /\ - and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q5, q27] = 1 - | q27 : int(1..2)]) - | q5 : int(1..2)]), - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker <= 2, - and([q6 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - (2 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q6] -> - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q6, 1] < - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q6, 2]) - | q6 : int(1..2)]), - and([q6 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - and([q8 > a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q6] -> - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q6, q8] = 1 - | q8 : int(1..2)]) - | q6 : int(1..2)]), - and([q6 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q6] <= 2 - | q6 : int(1..2)]), - 2 = - sum([toInt(q13 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker) * - catchUndef(a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q13], 0) - | q13 : int(1..2)]), - alldifferent_except([toInt(q32 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - q33 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q32]) - * - catchUndef(b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q32, q33], - 0) - | q32 : int(1..2), q33 : int(1..2)], - 0), - and([q34 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q34] >= 1 - | q34 : int(1..2)]), - 2 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - flatten([[b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[1]; int(1)], - [b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[1, q24] - | q24 : int(1..2)]; - int(1..2)]) - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q18] = 0 /\ - and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q18, q28] = 1 - | q28 : int(1..2)]) - | q18 : int(1..2)]), - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker <= 2, - and([q19 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - (2 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q19] -> - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q19, 1] < - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q19, 2]) - | q19 : int(1..2)]), - and([q19 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - and([q21 > b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q19] -> - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q19, q21] = 1 - | q21 : int(1..2)]) - | q19 : int(1..2)]), - and([q19 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q19] <= 2 - | q19 : int(1..2)]), - 2 = - sum([toInt(q26 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker) * - catchUndef(b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q26], 0) - | q26 : int(1..2)]) - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_3_4-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_3_4-solution000001.solution new file mode 100644 index 0000000000..cde05d5274 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_3_4-solution000001.solution @@ -0,0 +1,11 @@ +language Essence 1.3 + +letting a be partition({1, 2}) +$ Visualisation for a +$ 1 2 + +letting b be partition({1}, {2}) +$ Visualisation for b +$ 1 +$ 2 + diff --git a/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_3_4.eprime.orig b/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_3_4.eprime.orig deleted file mode 100644 index 9842c459d7..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_3_4.eprime.orig +++ /dev/null @@ -1,906 +0,0 @@ -language ESSENCE' 1.0 - -find a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker: int(0..2) -find a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker: - matrix indexed by [int(1..2)] of int(0..2) -find a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values: - matrix indexed by [int(1..2), int(1..2)] of int(1..2) -find b_PartitionOccurrence_NumParts: int(1..2) -find b_PartitionOccurrence_WhichPart: matrix indexed by [int(1..2)] of int(1..2) -find b_PartitionOccurrence_PartSizes: matrix indexed by [int(1..2)] of int(0..2) -find b_PartitionOccurrence_FirstIndex: matrix indexed by [int(1..2)] of int(1..2) -branching on - [a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker, - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker, - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values, - b_PartitionOccurrence_NumParts, b_PartitionOccurrence_WhichPart, b_PartitionOccurrence_PartSizes, - b_PartitionOccurrence_FirstIndex] -such that - or([q31 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - (toInt(or([q178 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - (a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q178] = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q31] - /\ - and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q178, q179] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q31, q179] - | q179 : int(1..2)])) - | q178 : int(1..2)])) - < - toInt(or([q182 <= b_PartitionOccurrence_NumParts /\ - (and([b_PartitionOccurrence_WhichPart[q185] = q182 -> - or([q187 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q31] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q31, q187] - = q185 - | q187 : int(1..2)]) - | q185 : int(1..2)]) - /\ - and([q189 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q31] - -> - or([b_PartitionOccurrence_WhichPart[q191] = q182 /\ - q191 = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q31, q189] - | q191 : int(1..2)]) - | q189 : int(1..2)])) - | q182 : int(1..2)])) - /\ - (and([q193 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - (or([q285 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q193] - /\ - (toInt(or([q306 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q193] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q193, q306] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q193, q285] - | q306 : int(1..2)])) - < - toInt(or([q308 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q31] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q31, q308] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q193, q285] - | q308 : int(1..2)])) - /\ - (and([q309 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q193] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q193, q309] - < - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q193, q285] - -> - toInt(or([q318 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q193] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q193, q318] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q193, q309] - | q318 : int(1..2)])) - = - toInt(or([q320 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q31] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q31, q320] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q193, q309] - | q320 : int(1..2)])) - | q309 : int(1..2)]) - /\ - and([and([q310 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q31], - !or([q316 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q193] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q193, q316] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q31, q310] - | q316 : int(1..2)]), - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q31, q310] - < - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q193, q285]; - int(1..3)]) - -> - toInt(or([q312 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q193] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q193, q312] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q31, q310] - | q312 : int(1..2)])) - = - toInt(or([q314 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q31] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q31, q314] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q31, q310] - | q314 : int(1..2)])) - | q310 : int(1..2)]))) - | q285 : int(1..2)]) - \/ - or([q286 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q31] /\ - !or([q304 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q193] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q193, q304] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q31, q286] - | q304 : int(1..2)]) - /\ - (toInt(or([q288 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q193] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q193, q288] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q31, q286] - | q288 : int(1..2)])) - < - toInt(or([q290 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q31] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q31, q290] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q31, q286] - | q290 : int(1..2)])) - /\ - (and([q291 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q193] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q193, q291] - < - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q31, q286] - -> - toInt(or([q300 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q193] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q193, q300] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q193, q291] - | q300 : int(1..2)])) - = - toInt(or([q302 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q31] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q31, q302] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q193, q291] - | q302 : int(1..2)])) - | q291 : int(1..2)]) - /\ - and([and([q292 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q31], - !or([q298 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q193] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q193, q298] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q31, q292] - | q298 : int(1..2)]), - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q31, q292] - < - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q31, q286]; - int(1..3)]) - -> - toInt(or([q294 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q193] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q193, q294] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q31, q292] - | q294 : int(1..2)])) - = - toInt(or([q296 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q31] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q31, q296] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q31, q292] - | q296 : int(1..2)])) - | q292 : int(1..2)]))) - | q286 : int(1..2)])) - -> - toInt(or([q269 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - (a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q269] = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q193] - /\ - and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q269, q270] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q193, q270] - | q270 : int(1..2)])) - | q269 : int(1..2)])) - = - toInt(or([q273 <= b_PartitionOccurrence_NumParts /\ - (and([b_PartitionOccurrence_WhichPart[q276] = q273 -> - or([q278 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q193] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q193, q278] - = q276 - | q278 : int(1..2)]) - | q276 : int(1..2)]) - /\ - and([q280 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q193] - -> - or([b_PartitionOccurrence_WhichPart[q282] = q273 /\ - q282 = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q193, q280] - | q282 : int(1..2)]) - | q280 : int(1..2)])) - | q273 : int(1..2)])) - | q193 : int(1..2)]) - /\ - and([and([q194 <= b_PartitionOccurrence_NumParts, - !or([q209 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - (and([q211 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q209] - -> - or([b_PartitionOccurrence_WhichPart[q213] = q194 /\ - q213 = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q209, q211] - | q213 : int(1..2)]) - | q211 : int(1..2)]) - /\ - and([b_PartitionOccurrence_WhichPart[q215] = q194 -> - or([q217 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q209] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q209, q217] - = q215 - | q217 : int(1..2)]) - | q215 : int(1..2)])) - | q209 : int(1..2)]), - or([b_PartitionOccurrence_WhichPart[q220] = q194 /\ - (sum([toInt(b_PartitionOccurrence_WhichPart[q241] = q194) * catchUndef(toInt(q241 = q220), 0) - | q241 : int(1..2)]) - < - toInt(or([q243 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q31] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q31, q243] - = q220 - | q243 : int(1..2)])) - /\ - (and([b_PartitionOccurrence_WhichPart[q244] = q194 -> - sum([toInt(b_PartitionOccurrence_WhichPart[q253] = q194) * - catchUndef(toInt(q253 = q244), 0) - | q253 : int(1..2)]) - = - toInt(or([q255 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q31] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q31, q255] - = q244 - | q255 : int(1..2)])) - | q244 : int(1..2), q244 < q220]) - /\ - and([and([q245 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q31], - !or([b_PartitionOccurrence_WhichPart[q251] = q194 /\ - q251 = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q31, q245] - | q251 : int(1..2)]), - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q31, q245] - < q220; - int(1..3)]) - -> - sum([toInt(b_PartitionOccurrence_WhichPart[q247] = q194) * - catchUndef(toInt(q247 = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q31, q245]), - 0) - | q247 : int(1..2)]) - = - toInt(or([q249 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q31] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q31, q249] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q31, q245] - | q249 : int(1..2)])) - | q245 : int(1..2)]))) - | q220 : int(1..2)]) - \/ - or([q221 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q31] - /\ - !or([b_PartitionOccurrence_WhichPart[q239] = q194 /\ - q239 = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q31, q221] - | q239 : int(1..2)]) - /\ - (sum([toInt(b_PartitionOccurrence_WhichPart[q223] = q194) * - catchUndef(toInt(q223 = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q31, q221]), - 0) - | q223 : int(1..2)]) - < - toInt(or([q225 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q31] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q31, q225] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q31, q221] - | q225 : int(1..2)])) - /\ - (and([b_PartitionOccurrence_WhichPart[q226] = q194 /\ - q226 < - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q31, q221] - -> - sum([toInt(b_PartitionOccurrence_WhichPart[q235] = q194) * - catchUndef(toInt(q235 = q226), 0) - | q235 : int(1..2)]) - = - toInt(or([q237 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q31] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q31, q237] - = q226 - | q237 : int(1..2)])) - | q226 : int(1..2)]) - /\ - and([and([q227 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q31], - !or([b_PartitionOccurrence_WhichPart[q233] = q194 /\ - q233 = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q31, q227] - | q233 : int(1..2)]), - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q31, q227] - < - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q31, q221]; - int(1..3)]) - -> - sum([toInt(b_PartitionOccurrence_WhichPart[q229] = q194) * - catchUndef(toInt(q229 = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q31, q227]), - 0) - | q229 : int(1..2)]) - = - toInt(or([q231 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q31] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q31, q231] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q31, q227] - | q231 : int(1..2)])) - | q227 : int(1..2)]))) - | q221 : int(1..2)]); - int(1..3)]) - -> - toInt(or([q258 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - (and([q260 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q258] - -> - or([b_PartitionOccurrence_WhichPart[q262] = q194 /\ - q262 = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q258, q260] - | q262 : int(1..2)]) - | q260 : int(1..2)]) - /\ - and([b_PartitionOccurrence_WhichPart[q264] = q194 -> - or([q266 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q258] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q258, q266] - = q264 - | q266 : int(1..2)]) - | q264 : int(1..2)])) - | q258 : int(1..2)])) - = - toInt(or([q197 <= b_PartitionOccurrence_NumParts /\ - (and([b_PartitionOccurrence_WhichPart[q200] = q197 -> - or([b_PartitionOccurrence_WhichPart[q202] = q194 /\ q202 = q200 | q202 : int(1..2)]) - | q200 : int(1..2)]) - /\ - and([b_PartitionOccurrence_WhichPart[q204] = q194 -> - or([b_PartitionOccurrence_WhichPart[q206] = q197 /\ q206 = q204 | q206 : int(1..2)]) - | q204 : int(1..2)])) - | q197 : int(1..2)])) - | q194 : int(1..2)]))) - | q31 : int(1..2)]) - \/ - or([q32 <= b_PartitionOccurrence_NumParts /\ - !or([q167 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - (and([q169 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q167] -> - or([b_PartitionOccurrence_WhichPart[q171] = q32 /\ - q171 = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q167, q169] - | q171 : int(1..2)]) - | q169 : int(1..2)]) - /\ - and([b_PartitionOccurrence_WhichPart[q173] = q32 -> - or([q175 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q167] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q167, q175] - = q173 - | q175 : int(1..2)]) - | q173 : int(1..2)])) - | q167 : int(1..2)]) - /\ - (toInt(or([q156 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - (and([q158 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q156] - -> - or([b_PartitionOccurrence_WhichPart[q160] = q32 /\ - q160 = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q156, q158] - | q160 : int(1..2)]) - | q158 : int(1..2)]) - /\ - and([b_PartitionOccurrence_WhichPart[q162] = q32 -> - or([q164 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q156] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q156, q164] - = q162 - | q164 : int(1..2)]) - | q162 : int(1..2)])) - | q156 : int(1..2)])) - < - toInt(or([q35 <= b_PartitionOccurrence_NumParts /\ - (and([b_PartitionOccurrence_WhichPart[q38] = q35 -> - or([b_PartitionOccurrence_WhichPart[q40] = q32 /\ q40 = q38 | q40 : int(1..2)]) - | q38 : int(1..2)]) - /\ - and([b_PartitionOccurrence_WhichPart[q42] = q32 -> - or([b_PartitionOccurrence_WhichPart[q44] = q35 /\ q44 = q42 | q44 : int(1..2)]) - | q42 : int(1..2)])) - | q35 : int(1..2)])) - /\ - (and([q66 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - (or([q67 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q66] /\ - (toInt(or([q75 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q66] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q66, q75] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q66, q67] - | q75 : int(1..2)])) - < - sum([toInt(b_PartitionOccurrence_WhichPart[q58] = q32) * - catchUndef(toInt(q58 = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q66, q67]), - 0) - | q58 : int(1..2)]) - /\ - (and([q68 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q66] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q66, q68] - < - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q66, q67] - -> - toInt(or([q70 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q66] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q66, q70] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q66, q68] - | q70 : int(1..2)])) - = - sum([toInt(b_PartitionOccurrence_WhichPart[q64] = q32) * - catchUndef(toInt(q64 = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q66, q68]), - 0) - | q64 : int(1..2)]) - | q68 : int(1..2)]) - /\ - and([!or([q71 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q66] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q66, q71] - = q59 - | q71 : int(1..2)]) - /\ - q59 < - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q66, q67] - -> - (b_PartitionOccurrence_WhichPart[q59] = q32 -> - toInt(or([q73 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q66] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q66, q73] - = q59 - | q73 : int(1..2)])) - = - sum([toInt(b_PartitionOccurrence_WhichPart[q61] = q32) * catchUndef(toInt(q61 = q59), 0) - | q61 : int(1..2)])) - | q59 : int(1..2)]))) - | q67 : int(1..2)]) - \/ - or([!or([q84 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q66] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q66, q84] - = q47 - | q84 : int(1..2)]) - /\ - (b_PartitionOccurrence_WhichPart[q47] = q32 /\ - (toInt(or([q83 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q66] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q66, q83] - = q47 - | q83 : int(1..2)])) - < - sum([toInt(b_PartitionOccurrence_WhichPart[q49] = q32) * catchUndef(toInt(q49 = q47), 0) - | q49 : int(1..2)]) - /\ - (and([q76 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q66] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q66, q76] - < q47 - -> - toInt(or([q78 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q66] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q66, q78] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q66, q76] - | q78 : int(1..2)])) - = - sum([toInt(b_PartitionOccurrence_WhichPart[q55] = q32) * - catchUndef(toInt(q55 = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q66, q76]), - 0) - | q55 : int(1..2)]) - | q76 : int(1..2)]) - /\ - and([!or([q79 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q66] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q66, q79] - = q50 - | q79 : int(1..2)]) - -> - (b_PartitionOccurrence_WhichPart[q50] = q32 -> - toInt(or([q81 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q66] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q66, q81] - = q50 - | q81 : int(1..2)])) - = - sum([toInt(b_PartitionOccurrence_WhichPart[q52] = q32) * catchUndef(toInt(q52 = q50), 0) - | q52 : int(1..2)])) - | q50 : int(1..2), q50 < q47])))) - | q47 : int(1..2)])) - -> - toInt(or([q140 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - (a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q140] = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q66] - /\ - and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q140, q141] - = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q66, q141] - | q141 : int(1..2)])) - | q140 : int(1..2)])) - = - toInt(or([q144 <= b_PartitionOccurrence_NumParts /\ - (and([b_PartitionOccurrence_WhichPart[q147] = q144 -> - or([q149 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q66] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q66, q149] - = q147 - | q149 : int(1..2)]) - | q147 : int(1..2)]) - /\ - and([q151 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q66] - -> - or([b_PartitionOccurrence_WhichPart[q153] = q144 /\ - q153 = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q66, q151] - | q153 : int(1..2)]) - | q151 : int(1..2)])) - | q144 : int(1..2)])) - | q66 : int(1..2)]) - /\ - and([and([q85 <= b_PartitionOccurrence_NumParts, - !or([q100 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - (and([q102 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q100] - -> - or([b_PartitionOccurrence_WhichPart[q104] = q85 /\ - q104 = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q100, q102] - | q104 : int(1..2)]) - | q102 : int(1..2)]) - /\ - and([b_PartitionOccurrence_WhichPart[q106] = q85 -> - or([q108 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q100] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q100, q108] - = q106 - | q108 : int(1..2)]) - | q106 : int(1..2)])) - | q100 : int(1..2)]), - or([b_PartitionOccurrence_WhichPart[q117] = q85 /\ - (toInt(or([b_PartitionOccurrence_WhichPart[q110] = q85 /\ q110 = q117 | q110 : int(1..2)])) < - sum([toInt(b_PartitionOccurrence_WhichPart[q58] = q32) * catchUndef(toInt(q58 = q117), 0) - | q58 : int(1..2)]) - /\ - (and([b_PartitionOccurrence_WhichPart[q113] = q85 -> - toInt(or([b_PartitionOccurrence_WhichPart[q112] = q85 /\ q112 = q113 - | q112 : int(1..2)])) - = - sum([toInt(b_PartitionOccurrence_WhichPart[q64] = q32) * catchUndef(toInt(q64 = q113), 0) - | q64 : int(1..2)]) - | q113 : int(1..2), q113 < q117]) - /\ - and([!or([b_PartitionOccurrence_WhichPart[q116] = q85 /\ q116 = q59 | q116 : int(1..2)]) -> - (b_PartitionOccurrence_WhichPart[q59] = q32 -> - toInt(or([b_PartitionOccurrence_WhichPart[q115] = q85 /\ q115 = q59 - | q115 : int(1..2)])) - = - sum([toInt(b_PartitionOccurrence_WhichPart[q61] = q32) * catchUndef(toInt(q61 = q59), 0) - | q61 : int(1..2)])) - | q59 : int(1..2), q59 < q117]))) - | q117 : int(1..2)]) - \/ - or([!or([b_PartitionOccurrence_WhichPart[q126] = q85 /\ q126 = q47 | q126 : int(1..2)]) /\ - (b_PartitionOccurrence_WhichPart[q47] = q32 /\ - (toInt(or([b_PartitionOccurrence_WhichPart[q119] = q85 /\ q119 = q47 | q119 : int(1..2)])) < - sum([toInt(b_PartitionOccurrence_WhichPart[q49] = q32) * catchUndef(toInt(q49 = q47), 0) - | q49 : int(1..2)]) - /\ - (and([b_PartitionOccurrence_WhichPart[q122] = q85 -> - toInt(or([b_PartitionOccurrence_WhichPart[q121] = q85 /\ q121 = q122 - | q121 : int(1..2)])) - = - sum([toInt(b_PartitionOccurrence_WhichPart[q55] = q32) * - catchUndef(toInt(q55 = q122), 0) - | q55 : int(1..2)]) - | q122 : int(1..2), q122 < q47]) - /\ - and([!or([b_PartitionOccurrence_WhichPart[q125] = q85 /\ q125 = q50 | q125 : int(1..2)]) -> - (b_PartitionOccurrence_WhichPart[q50] = q32 -> - toInt(or([b_PartitionOccurrence_WhichPart[q124] = q85 /\ q124 = q50 - | q124 : int(1..2)])) - = - sum([toInt(b_PartitionOccurrence_WhichPart[q52] = q32) * - catchUndef(toInt(q52 = q50), 0) - | q52 : int(1..2)])) - | q50 : int(1..2), q50 < q47])))) - | q47 : int(1..2)]); - int(1..3)]) - -> - toInt(or([q129 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - (and([q131 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q129] - -> - or([b_PartitionOccurrence_WhichPart[q133] = q85 /\ - q133 = - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q129, q131] - | q133 : int(1..2)]) - | q131 : int(1..2)]) - /\ - and([b_PartitionOccurrence_WhichPart[q135] = q85 -> - or([q137 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q129] - /\ - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q129, q137] - = q135 - | q137 : int(1..2)]) - | q135 : int(1..2)])) - | q129 : int(1..2)])) - = - toInt(or([q88 <= b_PartitionOccurrence_NumParts /\ - (and([b_PartitionOccurrence_WhichPart[q91] = q88 -> - or([b_PartitionOccurrence_WhichPart[q93] = q85 /\ q93 = q91 | q93 : int(1..2)]) - | q91 : int(1..2)]) - /\ - and([b_PartitionOccurrence_WhichPart[q95] = q85 -> - or([b_PartitionOccurrence_WhichPart[q97] = q88 /\ q97 = q95 | q97 : int(1..2)]) - | q95 : int(1..2)])) - | q88 : int(1..2)])) - | q85 : int(1..2)]))) - | q32 : int(1..2)]), - alldifferent_except([toInt(q25 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - q26 <= - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q25]) - * - catchUndef(a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q25, q26], - 0) - | q25 : int(1..2), q26 : int(1..2)], - 0), - and([q27 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q27] >= 1 - | q27 : int(1..2)]), - 2 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - flatten([[a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[1]; int(1)], - [a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[1, q11] - | q11 : int(1..2)]; - int(1..2)]) - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q5] = 0 /\ - and([a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q5, q24] = 1 - | q24 : int(1..2)]) - | q5 : int(1..2)]), - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker <= 2, - and([q6 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - (2 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q6] -> - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q6, 1] < - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q6, 2]) - | q6 : int(1..2)]), - and([q6 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - and([q8 > a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q6] -> - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q6, q8] = 1 - | q8 : int(1..2)]) - | q6 : int(1..2)]), - and([q6 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q6] <= 2 - | q6 : int(1..2)]), - 2 = - sum([toInt(q13 <= a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker) * - catchUndef(a_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q13], 0) - | q13 : int(1..2)]), - and([q14 <= b_PartitionOccurrence_NumParts -> b_PartitionOccurrence_PartSizes[q14] <= 2 | q14 : int(1..2)]), - and([q14 > b_PartitionOccurrence_NumParts -> b_PartitionOccurrence_PartSizes[q14] = 0 | q14 : int(1..2)]), - b_PartitionOccurrence_NumParts <= 2, - b_PartitionOccurrence_NumParts = max([b_PartitionOccurrence_WhichPart[q17] | q17 : int(1..2)]), - and([b_PartitionOccurrence_PartSizes[q18] = - sum([toInt(b_PartitionOccurrence_WhichPart[q19] = q18) | q19 : int(1..2)]) - | q18 : int(1..2)]), - and([q20 <= b_PartitionOccurrence_NumParts -> - and([b_PartitionOccurrence_WhichPart[q21] = q20 -> b_PartitionOccurrence_FirstIndex[q20] <= q21 - | q21 : int(1..2)]) - | q20 : int(1..2)]), - and([q20 <= b_PartitionOccurrence_NumParts -> - or([b_PartitionOccurrence_WhichPart[q21] = q20 /\ b_PartitionOccurrence_FirstIndex[q20] = q21 - | q21 : int(1..2)]) - | q20 : int(1..2)]), - and([q20 > b_PartitionOccurrence_NumParts -> b_PartitionOccurrence_FirstIndex[q20] = 1 | q20 : int(1..2)]), - and([q22 <= b_PartitionOccurrence_NumParts /\ q23 <= b_PartitionOccurrence_NumParts -> - (q22 < q23 <-> b_PartitionOccurrence_FirstIndex[q22] < b_PartitionOccurrence_FirstIndex[q23]) - | q22 : int(1..2), q23 : int(1..2)]) - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_4_1-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_4_1-solution000001.solution new file mode 100644 index 0000000000..cde05d5274 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_4_1-solution000001.solution @@ -0,0 +1,11 @@ +language Essence 1.3 + +letting a be partition({1, 2}) +$ Visualisation for a +$ 1 2 + +letting b be partition({1}, {2}) +$ Visualisation for b +$ 1 +$ 2 + diff --git a/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_4_1.eprime b/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_4_1.eprime new file mode 100644 index 0000000000..5216e84b83 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_4_1.eprime @@ -0,0 +1,373 @@ +language ESSENCE' 1.0 + +find a_PartitionOccurrence_NumParts: int(1..2) +find a_PartitionOccurrence_WhichPart: matrix indexed by [int(1..2)] of int(1..2) +find a_PartitionOccurrence_PartSizes: matrix indexed by [int(1..2)] of int(0..2) +find a_PartitionOccurrence_FirstIndex: matrix indexed by [int(1..2)] of int(1..2) +find b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker: int(0..2) +find b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence: matrix indexed by [int(1..2), int(1..2)] of bool +branching on + [a_PartitionOccurrence_NumParts, a_PartitionOccurrence_WhichPart, a_PartitionOccurrence_PartSizes, + a_PartitionOccurrence_FirstIndex, b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker, + b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence] +such that + or([q29 <= a_PartitionOccurrence_NumParts /\ + (toInt(or([q122 <= a_PartitionOccurrence_NumParts /\ + (and([a_PartitionOccurrence_WhichPart[q125] = q122 -> + or([a_PartitionOccurrence_WhichPart[q127] = q29 /\ q127 = q125 | q127 : int(1..2)]) + | q125 : int(1..2)]) + /\ + and([a_PartitionOccurrence_WhichPart[q129] = q29 -> + or([a_PartitionOccurrence_WhichPart[q131] = q122 /\ q131 = q129 | q131 : int(1..2)]) + | q129 : int(1..2)])) + | q122 : int(1..2)])) + < + toInt(or([q33 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ + (and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q33, q34] -> + or([a_PartitionOccurrence_WhichPart[q36] = q29 /\ q36 = q34 | q36 : int(1..2)]) + | q34 : int(1..2)]) + /\ + and([a_PartitionOccurrence_WhichPart[q38] = q29 -> + b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q33, q38] + | q38 : int(1..2)])) + | q33 : int(1..2)])) + /\ + (and([q59 <= a_PartitionOccurrence_NumParts /\ + (or([a_PartitionOccurrence_WhichPart[q77] = q59 /\ + (toInt(or([a_PartitionOccurrence_WhichPart[q70] = q59 /\ q70 = q77 | q70 : int(1..2)])) < + sum([toInt(a_PartitionOccurrence_WhichPart[q52] = q29) * catchUndef(toInt(q52 = q77), 0) + | q52 : int(1..2)]) + /\ + (and([a_PartitionOccurrence_WhichPart[q73] = q59 -> + toInt(or([a_PartitionOccurrence_WhichPart[q72] = q59 /\ q72 = q73 | q72 : int(1..2)])) = + sum([toInt(a_PartitionOccurrence_WhichPart[q58] = q29) * catchUndef(toInt(q58 = q73), 0) + | q58 : int(1..2)]) + | q73 : int(1..2), q73 < q77]) + /\ + and([!or([a_PartitionOccurrence_WhichPart[q76] = q59 /\ q76 = q53 | q76 : int(1..2)]) -> + (a_PartitionOccurrence_WhichPart[q53] = q29 -> + toInt(or([a_PartitionOccurrence_WhichPart[q75] = q59 /\ q75 = q53 | q75 : int(1..2)])) = + sum([toInt(a_PartitionOccurrence_WhichPart[q55] = q29) * catchUndef(toInt(q55 = q53), 0) + | q55 : int(1..2)])) + | q53 : int(1..2), q53 < q77]))) + | q77 : int(1..2)]) + \/ + or([!or([a_PartitionOccurrence_WhichPart[q86] = q59 /\ q86 = q41 | q86 : int(1..2)]) /\ + (a_PartitionOccurrence_WhichPart[q41] = q29 /\ + (toInt(or([a_PartitionOccurrence_WhichPart[q79] = q59 /\ q79 = q41 | q79 : int(1..2)])) < + sum([toInt(a_PartitionOccurrence_WhichPart[q43] = q29) * catchUndef(toInt(q43 = q41), 0) + | q43 : int(1..2)]) + /\ + (and([a_PartitionOccurrence_WhichPart[q82] = q59 -> + toInt(or([a_PartitionOccurrence_WhichPart[q81] = q59 /\ q81 = q82 | q81 : int(1..2)])) = + sum([toInt(a_PartitionOccurrence_WhichPart[q49] = q29) * catchUndef(toInt(q49 = q82), 0) + | q49 : int(1..2)]) + | q82 : int(1..2), q82 < q41]) + /\ + and([!or([a_PartitionOccurrence_WhichPart[q85] = q59 /\ q85 = q44 | q85 : int(1..2)]) -> + (a_PartitionOccurrence_WhichPart[q44] = q29 -> + toInt(or([a_PartitionOccurrence_WhichPart[q84] = q59 /\ q84 = q44 | q84 : int(1..2)])) = + sum([toInt(a_PartitionOccurrence_WhichPart[q46] = q29) * catchUndef(toInt(q46 = q44), 0) + | q46 : int(1..2)])) + | q44 : int(1..2), q44 < q41])))) + | q41 : int(1..2)])) + -> + toInt(or([q111 <= a_PartitionOccurrence_NumParts /\ + (and([a_PartitionOccurrence_WhichPart[q114] = q111 -> + or([a_PartitionOccurrence_WhichPart[q116] = q59 /\ q116 = q114 | q116 : int(1..2)]) + | q114 : int(1..2)]) + /\ + and([a_PartitionOccurrence_WhichPart[q118] = q59 -> + or([a_PartitionOccurrence_WhichPart[q120] = q111 /\ q120 = q118 | q120 : int(1..2)]) + | q118 : int(1..2)])) + | q111 : int(1..2)])) + = + toInt(or([q63 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ + (and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q63, q64] -> + or([a_PartitionOccurrence_WhichPart[q66] = q59 /\ q66 = q64 | q66 : int(1..2)]) + | q64 : int(1..2)]) + /\ + and([a_PartitionOccurrence_WhichPart[q68] = q59 -> + b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q63, q68] + | q68 : int(1..2)])) + | q63 : int(1..2)])) + | q59 : int(1..2)]) + /\ + and([and([q88 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker, + !or([q103 <= a_PartitionOccurrence_NumParts /\ + (and([a_PartitionOccurrence_WhichPart[q106] = q103 -> + b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q88, q106] + | q106 : int(1..2)]) + /\ + and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q88, q107] -> + or([a_PartitionOccurrence_WhichPart[q109] = q103 /\ q109 = q107 | q109 : int(1..2)]) + | q107 : int(1..2)])) + | q103 : int(1..2)]), + or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q88, q39] /\ + (toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q88, q39]) < + sum([toInt(a_PartitionOccurrence_WhichPart[q52] = q29) * catchUndef(toInt(q52 = q39), 0) + | q52 : int(1..2)]) + /\ + (and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q88, q40] -> + toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q88, q40]) = + sum([toInt(a_PartitionOccurrence_WhichPart[q58] = q29) * catchUndef(toInt(q58 = q40), 0) + | q58 : int(1..2)]) + | q40 : int(1..2), q40 < q39]) + /\ + and([!or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q88, q56] /\ + q56 = q53 + | q56 : int(1..2)]) + -> + (a_PartitionOccurrence_WhichPart[q53] = q29 -> + toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q88, q53]) = + sum([toInt(a_PartitionOccurrence_WhichPart[q55] = q29) * catchUndef(toInt(q55 = q53), 0) + | q55 : int(1..2)])) + | q53 : int(1..2), q53 < q39]))) + | q39 : int(1..2)]) + \/ + or([!or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q88, q50] /\ q50 = q41 + | q50 : int(1..2)]) + /\ + (a_PartitionOccurrence_WhichPart[q41] = q29 /\ + (toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q88, q41]) < + sum([toInt(a_PartitionOccurrence_WhichPart[q43] = q29) * catchUndef(toInt(q43 = q41), 0) + | q43 : int(1..2)]) + /\ + (and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q88, q40] -> + toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q88, q40]) = + sum([toInt(a_PartitionOccurrence_WhichPart[q49] = q29) * catchUndef(toInt(q49 = q40), 0) + | q49 : int(1..2)]) + | q40 : int(1..2), q40 < q41]) + /\ + and([!or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q88, q47] /\ + q47 = q44 + | q47 : int(1..2)]) + -> + (a_PartitionOccurrence_WhichPart[q44] = q29 -> + toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q88, q44]) = + sum([toInt(a_PartitionOccurrence_WhichPart[q46] = q29) * + catchUndef(toInt(q46 = q44), 0) + | q46 : int(1..2)])) + | q44 : int(1..2), q44 < q41])))) + | q41 : int(1..2)]); + int(1..3)]) + -> + toInt(or([q90 <= a_PartitionOccurrence_NumParts /\ + (and([a_PartitionOccurrence_WhichPart[q93] = q90 -> + b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q88, q93] + | q93 : int(1..2)]) + /\ + and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q88, q94] -> + or([a_PartitionOccurrence_WhichPart[q96] = q90 /\ q96 = q94 | q96 : int(1..2)]) + | q94 : int(1..2)])) + | q90 : int(1..2)])) + = + toInt(or([q99 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ + and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q99, q100] = + b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q88, q100] + | q100 : int(1..2)]) + | q99 : int(1..2)])) + | q88 : int(1..2)]))) + | q29 : int(1..2)]) + \/ + or([q133 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ + !or([q220 <= a_PartitionOccurrence_NumParts /\ + (and([a_PartitionOccurrence_WhichPart[q223] = q220 -> + b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q133, q223] + | q223 : int(1..2)]) + /\ + and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q133, q224] -> + or([a_PartitionOccurrence_WhichPart[q226] = q220 /\ q226 = q224 | q226 : int(1..2)]) + | q224 : int(1..2)])) + | q220 : int(1..2)]) + /\ + (toInt(or([q135 <= a_PartitionOccurrence_NumParts /\ + (and([a_PartitionOccurrence_WhichPart[q138] = q135 -> + b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q133, q138] + | q138 : int(1..2)]) + /\ + and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q133, q139] -> + or([a_PartitionOccurrence_WhichPart[q141] = q135 /\ q141 = q139 | q141 : int(1..2)]) + | q139 : int(1..2)])) + | q135 : int(1..2)])) + < + toInt(or([q144 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ + and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q144, q145] = + b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q133, q145] + | q145 : int(1..2)]) + | q144 : int(1..2)])) + /\ + (and([q147 <= a_PartitionOccurrence_NumParts /\ + (or([a_PartitionOccurrence_WhichPart[q159] = q147 /\ + (sum([toInt(a_PartitionOccurrence_WhichPart[q172] = q147) * catchUndef(toInt(q172 = q159), 0) + | q172 : int(1..2)]) + < toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q133, q159]) + /\ + (and([a_PartitionOccurrence_WhichPart[q173] = q147 -> + sum([toInt(a_PartitionOccurrence_WhichPart[q179] = q147) * catchUndef(toInt(q179 = q173), 0) + | q179 : int(1..2)]) + = toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q133, q173]) + | q173 : int(1..2), q173 < q159]) + /\ + and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q133, q158] /\ + !or([a_PartitionOccurrence_WhichPart[q177] = q147 /\ q177 = q158 | q177 : int(1..2)]) + -> + sum([toInt(a_PartitionOccurrence_WhichPart[q175] = q147) * catchUndef(toInt(q175 = q158), 0) + | q175 : int(1..2)]) + = toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q133, q158]) + | q158 : int(1..2), q158 < q159]))) + | q159 : int(1..2)]) + \/ + or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q133, q157] /\ + !or([a_PartitionOccurrence_WhichPart[q170] = q147 /\ q170 = q157 | q170 : int(1..2)]) + /\ + (sum([toInt(a_PartitionOccurrence_WhichPart[q161] = q147) * catchUndef(toInt(q161 = q157), 0) + | q161 : int(1..2)]) + < toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q133, q157]) + /\ + (and([a_PartitionOccurrence_WhichPart[q162] = q147 -> + sum([toInt(a_PartitionOccurrence_WhichPart[q168] = q147) * catchUndef(toInt(q168 = q162), 0) + | q168 : int(1..2)]) + = toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q133, q162]) + | q162 : int(1..2), q162 < q157]) + /\ + and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q133, q158] /\ + !or([a_PartitionOccurrence_WhichPart[q166] = q147 /\ q166 = q158 | q166 : int(1..2)]) + -> + sum([toInt(a_PartitionOccurrence_WhichPart[q164] = q147) * catchUndef(toInt(q164 = q158), 0) + | q164 : int(1..2)]) + = toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q133, q158]) + | q158 : int(1..2), q158 < q157]))) + | q157 : int(1..2)])) + -> + toInt(or([q209 <= a_PartitionOccurrence_NumParts /\ + (and([a_PartitionOccurrence_WhichPart[q212] = q209 -> + or([a_PartitionOccurrence_WhichPart[q214] = q147 /\ q214 = q212 | q214 : int(1..2)]) + | q212 : int(1..2)]) + /\ + and([a_PartitionOccurrence_WhichPart[q216] = q147 -> + or([a_PartitionOccurrence_WhichPart[q218] = q209 /\ q218 = q216 | q218 : int(1..2)]) + | q216 : int(1..2)])) + | q209 : int(1..2)])) + = + toInt(or([q151 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ + (and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q151, q152] -> + or([a_PartitionOccurrence_WhichPart[q154] = q147 /\ q154 = q152 | q154 : int(1..2)]) + | q152 : int(1..2)]) + /\ + and([a_PartitionOccurrence_WhichPart[q156] = q147 -> + b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q151, q156] + | q156 : int(1..2)])) + | q151 : int(1..2)])) + | q147 : int(1..2)]) + /\ + and([and([q181 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker, + !or([q196 <= a_PartitionOccurrence_NumParts /\ + (and([a_PartitionOccurrence_WhichPart[q199] = q196 -> + b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q181, q199] + | q199 : int(1..2)]) + /\ + and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q181, q200] -> + or([a_PartitionOccurrence_WhichPart[q202] = q196 /\ q202 = q200 | q202 : int(1..2)]) + | q200 : int(1..2)])) + | q196 : int(1..2)]), + or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q181, q203] /\ + (toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q181, q203]) < + toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q133, q203]) + /\ + (and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q181, q204] -> + toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q181, q204]) = + toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q133, q204]) + | q204 : int(1..2), q204 < q203]) + /\ + and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q133, q204] /\ + !or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q181, q207] /\ + q207 = q204 + | q207 : int(1..2)]) + -> + toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q181, q204]) = + toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q133, q204]) + | q204 : int(1..2), q204 < q203]))) + | q203 : int(1..2)]) + \/ + or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q133, q203] /\ + !or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q181, q206] /\ q206 = q203 + | q206 : int(1..2)]) + /\ + (toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q181, q203]) < + toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q133, q203]) + /\ + (and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q181, q204] -> + toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q181, q204]) = + toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q133, q204]) + | q204 : int(1..2), q204 < q203]) + /\ + and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q133, q204] /\ + !or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q181, q205] /\ + q205 = q204 + | q205 : int(1..2)]) + -> + toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q181, q204]) = + toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q133, q204]) + | q204 : int(1..2), q204 < q203]))) + | q203 : int(1..2)]); + int(1..3)]) + -> + toInt(or([q183 <= a_PartitionOccurrence_NumParts /\ + (and([a_PartitionOccurrence_WhichPart[q186] = q183 -> + b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q181, q186] + | q186 : int(1..2)]) + /\ + and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q181, q187] -> + or([a_PartitionOccurrence_WhichPart[q189] = q183 /\ q189 = q187 | q189 : int(1..2)]) + | q187 : int(1..2)])) + | q183 : int(1..2)])) + = + toInt(or([q192 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ + and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q192, q193] = + b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q181, q193] + | q193 : int(1..2)]) + | q192 : int(1..2)])) + | q181 : int(1..2)]))) + | q133 : int(1..2)]), + and([q1 <= a_PartitionOccurrence_NumParts -> a_PartitionOccurrence_PartSizes[q1] <= 2 | q1 : int(1..2)]), + and([q1 > a_PartitionOccurrence_NumParts -> a_PartitionOccurrence_PartSizes[q1] = 0 | q1 : int(1..2)]), + a_PartitionOccurrence_NumParts <= 2, + a_PartitionOccurrence_NumParts = max([a_PartitionOccurrence_WhichPart[q4] | q4 : int(1..2)]), + and([a_PartitionOccurrence_PartSizes[q5] = sum([toInt(a_PartitionOccurrence_WhichPart[q6] = q5) | q6 : int(1..2)]) + | q5 : int(1..2)]), + and([q7 <= a_PartitionOccurrence_NumParts -> + and([a_PartitionOccurrence_WhichPart[q8] = q7 -> a_PartitionOccurrence_FirstIndex[q7] <= q8 | q8 : int(1..2)]) + | q7 : int(1..2)]), + and([q7 <= a_PartitionOccurrence_NumParts -> + or([a_PartitionOccurrence_WhichPart[q8] = q7 /\ a_PartitionOccurrence_FirstIndex[q7] = q8 | q8 : int(1..2)]) + | q7 : int(1..2)]), + and([q7 > a_PartitionOccurrence_NumParts -> a_PartitionOccurrence_FirstIndex[q7] = 1 | q7 : int(1..2)]), + and([q9 <= a_PartitionOccurrence_NumParts /\ q10 <= a_PartitionOccurrence_NumParts -> + (q9 < q10 <-> a_PartitionOccurrence_FirstIndex[q9] < a_PartitionOccurrence_FirstIndex[q10]) + | q9 : int(1..2), q10 : int(1..2)]), + and([1 = + sum([toInt(q24 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker /\ + b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q24, q11]) + | q24 : int(1..2)]) + | q11 : int(1..2)]), + and([q25 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> + sum([toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q25, q26]) | q26 : int(1..2)]) >= 1 + | q25 : int(1..2)]), + 2 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> + [-toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[1, q19]) | q19 : int(1..2)] b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> + and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q15, q21] = false | q21 : int(1..2)]) + | q15 : int(1..2)]), + b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker <= 2, + and([q16 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> + sum([toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q16, q17]) | q17 : int(1..2)]) <= 2 + | q16 : int(1..2)]), + 2 = + sum([toInt(q22 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker) * + catchUndef(sum([toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q22, q23]) + | q23 : int(1..2)]), + 0) + | q22 : int(1..2)]) + diff --git a/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_4_2-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_4_2-solution000001.solution new file mode 100644 index 0000000000..cde05d5274 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_4_2-solution000001.solution @@ -0,0 +1,11 @@ +language Essence 1.3 + +letting a be partition({1, 2}) +$ Visualisation for a +$ 1 2 + +letting b be partition({1}, {2}) +$ Visualisation for b +$ 1 +$ 2 + diff --git a/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_4_2.eprime b/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_4_2.eprime new file mode 100644 index 0000000000..4fdad05487 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_4_2.eprime @@ -0,0 +1,827 @@ +language ESSENCE' 1.0 + +find a_PartitionOccurrence_NumParts: int(1..2) +find a_PartitionOccurrence_WhichPart: matrix indexed by [int(1..2)] of int(1..2) +find a_PartitionOccurrence_PartSizes: matrix indexed by [int(1..2)] of int(0..2) +find a_PartitionOccurrence_FirstIndex: matrix indexed by [int(1..2)] of int(1..2) +find b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker: int(0..2) +find b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy: + matrix indexed by [int(1..2), int(1..2)] of int(1..3) +branching on + [a_PartitionOccurrence_NumParts, a_PartitionOccurrence_WhichPart, a_PartitionOccurrence_PartSizes, + a_PartitionOccurrence_FirstIndex, b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker, + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy] +such that + or([q35 <= a_PartitionOccurrence_NumParts /\ + (toInt(or([q158 <= a_PartitionOccurrence_NumParts /\ + (and([a_PartitionOccurrence_WhichPart[q161] = q158 -> + or([a_PartitionOccurrence_WhichPart[q163] = q35 /\ q163 = q161 | q163 : int(1..2)]) + | q161 : int(1..2)]) + /\ + and([a_PartitionOccurrence_WhichPart[q165] = q35 -> + or([a_PartitionOccurrence_WhichPart[q167] = q158 /\ q167 = q165 | q167 : int(1..2)]) + | q165 : int(1..2)])) + | q158 : int(1..2)])) + < + toInt(or([q39 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ + (and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q39, q41] != 3 -> + or([a_PartitionOccurrence_WhichPart[q43] = q35 /\ + q43 = + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q39, q41] + | q43 : int(1..2)]) + | q41 : int(1..2)]) + /\ + and([a_PartitionOccurrence_WhichPart[q45] = q35 -> + or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q39, q47] != 3 + /\ + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q39, q47] = + q45 | q47 : int(1..2)]) + | q45 : int(1..2)])) + | q39 : int(1..2)])) + /\ + (and([q68 <= a_PartitionOccurrence_NumParts /\ + (or([a_PartitionOccurrence_WhichPart[q89] = q68 /\ + (toInt(or([a_PartitionOccurrence_WhichPart[q82] = q68 /\ q82 = q89 | q82 : int(1..2)])) < + sum([toInt(a_PartitionOccurrence_WhichPart[q61] = q35) * catchUndef(toInt(q61 = q89), 0) + | q61 : int(1..2)]) + /\ + (and([a_PartitionOccurrence_WhichPart[q85] = q68 -> + toInt(or([a_PartitionOccurrence_WhichPart[q84] = q68 /\ q84 = q85 | q84 : int(1..2)])) = + sum([toInt(a_PartitionOccurrence_WhichPart[q67] = q35) * catchUndef(toInt(q67 = q85), 0) + | q67 : int(1..2)]) + | q85 : int(1..2), q85 < q89]) + /\ + and([!or([a_PartitionOccurrence_WhichPart[q88] = q68 /\ q88 = q62 | q88 : int(1..2)]) -> + (a_PartitionOccurrence_WhichPart[q62] = q35 -> + toInt(or([a_PartitionOccurrence_WhichPart[q87] = q68 /\ q87 = q62 | q87 : int(1..2)])) = + sum([toInt(a_PartitionOccurrence_WhichPart[q64] = q35) * catchUndef(toInt(q64 = q62), 0) + | q64 : int(1..2)])) + | q62 : int(1..2), q62 < q89]))) + | q89 : int(1..2)]) + \/ + or([!or([a_PartitionOccurrence_WhichPart[q98] = q68 /\ q98 = q50 | q98 : int(1..2)]) /\ + (a_PartitionOccurrence_WhichPart[q50] = q35 /\ + (toInt(or([a_PartitionOccurrence_WhichPart[q91] = q68 /\ q91 = q50 | q91 : int(1..2)])) < + sum([toInt(a_PartitionOccurrence_WhichPart[q52] = q35) * catchUndef(toInt(q52 = q50), 0) + | q52 : int(1..2)]) + /\ + (and([a_PartitionOccurrence_WhichPart[q94] = q68 -> + toInt(or([a_PartitionOccurrence_WhichPart[q93] = q68 /\ q93 = q94 | q93 : int(1..2)])) = + sum([toInt(a_PartitionOccurrence_WhichPart[q58] = q35) * catchUndef(toInt(q58 = q94), 0) + | q58 : int(1..2)]) + | q94 : int(1..2), q94 < q50]) + /\ + and([!or([a_PartitionOccurrence_WhichPart[q97] = q68 /\ q97 = q53 | q97 : int(1..2)]) -> + (a_PartitionOccurrence_WhichPart[q53] = q35 -> + toInt(or([a_PartitionOccurrence_WhichPart[q96] = q68 /\ q96 = q53 | q96 : int(1..2)])) = + sum([toInt(a_PartitionOccurrence_WhichPart[q55] = q35) * catchUndef(toInt(q55 = q53), 0) + | q55 : int(1..2)])) + | q53 : int(1..2), q53 < q50])))) + | q50 : int(1..2)])) + -> + toInt(or([q147 <= a_PartitionOccurrence_NumParts /\ + (and([a_PartitionOccurrence_WhichPart[q150] = q147 -> + or([a_PartitionOccurrence_WhichPart[q152] = q68 /\ q152 = q150 | q152 : int(1..2)]) + | q150 : int(1..2)]) + /\ + and([a_PartitionOccurrence_WhichPart[q154] = q68 -> + or([a_PartitionOccurrence_WhichPart[q156] = q147 /\ q156 = q154 | q156 : int(1..2)]) + | q154 : int(1..2)])) + | q147 : int(1..2)])) + = + toInt(or([q72 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ + (and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q72, q74] != + 3 + -> + or([a_PartitionOccurrence_WhichPart[q76] = q68 /\ + q76 = + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q72, q74] + | q76 : int(1..2)]) + | q74 : int(1..2)]) + /\ + and([a_PartitionOccurrence_WhichPart[q78] = q68 -> + or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q72, q80] + != 3 + /\ + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q72, q80] + = q78 + | q80 : int(1..2)]) + | q78 : int(1..2)])) + | q72 : int(1..2)])) + | q68 : int(1..2)]) + /\ + and([and([q100 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker, + !or([q136 <= a_PartitionOccurrence_NumParts /\ + (and([a_PartitionOccurrence_WhichPart[q139] = q136 -> + or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q100, q141] + != 3 + /\ + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q100, q141] + = q139 + | q141 : int(1..2)]) + | q139 : int(1..2)]) + /\ + and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q100, q143] + != 3 + -> + or([a_PartitionOccurrence_WhichPart[q145] = q136 /\ + q145 = + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q100, q143] + | q145 : int(1..2)]) + | q143 : int(1..2)])) + | q136 : int(1..2)]), + or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q100, q101] != 3 /\ + (toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q100, q109] + != 3 + /\ + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q100, q109] + = + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q100, q101] + | q109 : int(1..2)])) + < + sum([toInt(a_PartitionOccurrence_WhichPart[q61] = q35) * + catchUndef(toInt(q61 = + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q100, q101]), + 0) + | q61 : int(1..2)]) + /\ + (and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q100, q102] + != 3 + /\ + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q100, q102] + < + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q100, q101] + -> + toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q100, q104] + != 3 + /\ + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q100, q104] + = + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q100, q102] + | q104 : int(1..2)])) + = + sum([toInt(a_PartitionOccurrence_WhichPart[q67] = q35) * + catchUndef(toInt(q67 = + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q100, q102]), + 0) + | q67 : int(1..2)]) + | q102 : int(1..2)]) + /\ + and([!or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q100, q105] + != 3 + /\ + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q100, q105] + = q62 + | q105 : int(1..2)]) + /\ + q62 < + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q100, q101] + -> + (a_PartitionOccurrence_WhichPart[q62] = q35 -> + toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q100, q107] + != 3 + /\ + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q100, q107] + = q62 + | q107 : int(1..2)])) + = + sum([toInt(a_PartitionOccurrence_WhichPart[q64] = q35) * catchUndef(toInt(q64 = q62), 0) + | q64 : int(1..2)])) + | q62 : int(1..2)]))) + | q101 : int(1..2)]) + \/ + or([!or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q100, q118] != + 3 + /\ + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q100, q118] = + q50 | q118 : int(1..2)]) + /\ + (a_PartitionOccurrence_WhichPart[q50] = q35 /\ + (toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q100, q117] + != 3 + /\ + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q100, q117] + = q50 + | q117 : int(1..2)])) + < + sum([toInt(a_PartitionOccurrence_WhichPart[q52] = q35) * catchUndef(toInt(q52 = q50), 0) + | q52 : int(1..2)]) + /\ + (and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q100, q110] + != 3 + /\ + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q100, q110] + < q50 + -> + toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q100, q112] + != 3 + /\ + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q100, q112] + = + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q100, q110] + | q112 : int(1..2)])) + = + sum([toInt(a_PartitionOccurrence_WhichPart[q58] = q35) * + catchUndef(toInt(q58 = + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q100, q110]), + 0) + | q58 : int(1..2)]) + | q110 : int(1..2)]) + /\ + and([!or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q100, q113] + != 3 + /\ + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q100, q113] + = q53 + | q113 : int(1..2)]) + -> + (a_PartitionOccurrence_WhichPart[q53] = q35 -> + toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q100, q115] + != 3 + /\ + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q100, q115] + = q53 + | q115 : int(1..2)])) + = + sum([toInt(a_PartitionOccurrence_WhichPart[q55] = q35) * + catchUndef(toInt(q55 = q53), 0) + | q55 : int(1..2)])) + | q53 : int(1..2), q53 < q50])))) + | q50 : int(1..2)]); + int(1..3)]) + -> + toInt(or([q120 <= a_PartitionOccurrence_NumParts /\ + (and([a_PartitionOccurrence_WhichPart[q123] = q120 -> + or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q100, q125] + != 3 + /\ + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q100, q125] + = q123 + | q125 : int(1..2)]) + | q123 : int(1..2)]) + /\ + and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q100, q127] + != 3 + -> + or([a_PartitionOccurrence_WhichPart[q129] = q120 /\ + q129 = + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q100, q127] + | q129 : int(1..2)]) + | q127 : int(1..2)])) + | q120 : int(1..2)])) + = + toInt(or([q132 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ + and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q132, q133] = + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q100, q133] + | q133 : int(1..2)]) + | q132 : int(1..2)])) + | q100 : int(1..2)]))) + | q35 : int(1..2)]) + \/ + or([q169 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ + !or([q316 <= a_PartitionOccurrence_NumParts /\ + (and([a_PartitionOccurrence_WhichPart[q319] = q316 -> + or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q169, q321] != 3 /\ + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q169, q321] = q319 + | q321 : int(1..2)]) + | q319 : int(1..2)]) + /\ + and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q169, q323] != 3 -> + or([a_PartitionOccurrence_WhichPart[q325] = q316 /\ + q325 = b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q169, q323] + | q325 : int(1..2)]) + | q323 : int(1..2)])) + | q316 : int(1..2)]) + /\ + (toInt(or([q171 <= a_PartitionOccurrence_NumParts /\ + (and([a_PartitionOccurrence_WhichPart[q174] = q171 -> + or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q169, q176] != + 3 + /\ + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q169, q176] = + q174 + | q176 : int(1..2)]) + | q174 : int(1..2)]) + /\ + and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q169, q178] != 3 + -> + or([a_PartitionOccurrence_WhichPart[q180] = q171 /\ + q180 = + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q169, q178] + | q180 : int(1..2)]) + | q178 : int(1..2)])) + | q171 : int(1..2)])) + < + toInt(or([q183 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ + and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q183, q184] = + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q169, q184] + | q184 : int(1..2)]) + | q183 : int(1..2)])) + /\ + (and([q186 <= a_PartitionOccurrence_NumParts /\ + (or([a_PartitionOccurrence_WhichPart[q201] = q186 /\ + (sum([toInt(a_PartitionOccurrence_WhichPart[q222] = q186) * catchUndef(toInt(q222 = q201), 0) + | q222 : int(1..2)]) + < + toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q169, q224] + != 3 + /\ + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q169, q224] + = q201 + | q224 : int(1..2)])) + /\ + (and([a_PartitionOccurrence_WhichPart[q225] = q186 -> + sum([toInt(a_PartitionOccurrence_WhichPart[q234] = q186) * catchUndef(toInt(q234 = q225), 0) + | q234 : int(1..2)]) + = + toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q169, q236] + != 3 + /\ + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q169, q236] + = q225 + | q236 : int(1..2)])) + | q225 : int(1..2), q225 < q201]) + /\ + and([and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q169, q226] + != 3, + !or([a_PartitionOccurrence_WhichPart[q228] = q186 /\ + q228 = + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q169, q226] + | q228 : int(1..2)]), + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q169, q226] + < q201; + int(1..3)]) + -> + sum([toInt(a_PartitionOccurrence_WhichPart[q230] = q186) * + catchUndef(toInt(q230 = + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q169, q226]), + 0) + | q230 : int(1..2)]) + = + toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q169, q232] + != 3 + /\ + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q169, q232] + = + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q169, q226] + | q232 : int(1..2)])) + | q226 : int(1..2)]))) + | q201 : int(1..2)]) + \/ + or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q169, q202] != 3 /\ + !or([a_PartitionOccurrence_WhichPart[q204] = q186 /\ + q204 = b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q169, q202] + | q204 : int(1..2)]) + /\ + (sum([toInt(a_PartitionOccurrence_WhichPart[q206] = q186) * + catchUndef(toInt(q206 = + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q169, q202]), + 0) + | q206 : int(1..2)]) + < + toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q169, q208] + != 3 + /\ + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q169, q208] + = + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q169, q202] + | q208 : int(1..2)])) + /\ + (and([a_PartitionOccurrence_WhichPart[q209] = q186 /\ + q209 < + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q169, q202] + -> + sum([toInt(a_PartitionOccurrence_WhichPart[q218] = q186) * catchUndef(toInt(q218 = q209), 0) + | q218 : int(1..2)]) + = + toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q169, q220] + != 3 + /\ + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q169, q220] + = q209 + | q220 : int(1..2)])) + | q209 : int(1..2)]) + /\ + and([and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q169, q210] + != 3, + !or([a_PartitionOccurrence_WhichPart[q212] = q186 /\ + q212 = + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q169, q210] + | q212 : int(1..2)]), + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q169, q210] + < + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q169, q202]; + int(1..3)]) + -> + sum([toInt(a_PartitionOccurrence_WhichPart[q214] = q186) * + catchUndef(toInt(q214 = + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q169, q210]), + 0) + | q214 : int(1..2)]) + = + toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q169, q216] + != 3 + /\ + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q169, q216] + = + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q169, q210] + | q216 : int(1..2)])) + | q210 : int(1..2)]))) + | q202 : int(1..2)])) + -> + toInt(or([q305 <= a_PartitionOccurrence_NumParts /\ + (and([a_PartitionOccurrence_WhichPart[q308] = q305 -> + or([a_PartitionOccurrence_WhichPart[q310] = q186 /\ q310 = q308 | q310 : int(1..2)]) + | q308 : int(1..2)]) + /\ + and([a_PartitionOccurrence_WhichPart[q312] = q186 -> + or([a_PartitionOccurrence_WhichPart[q314] = q305 /\ q314 = q312 | q314 : int(1..2)]) + | q312 : int(1..2)])) + | q305 : int(1..2)])) + = + toInt(or([q190 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ + (and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q190, q192] + != 3 + -> + or([a_PartitionOccurrence_WhichPart[q194] = q186 /\ + q194 = + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q190, q192] + | q194 : int(1..2)]) + | q192 : int(1..2)]) + /\ + and([a_PartitionOccurrence_WhichPart[q196] = q186 -> + or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q190, q198] + != 3 + /\ + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q190, q198] + = q196 + | q198 : int(1..2)]) + | q196 : int(1..2)])) + | q190 : int(1..2)])) + | q186 : int(1..2)]) + /\ + and([and([q238 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker, + !or([q256 <= a_PartitionOccurrence_NumParts /\ + (and([a_PartitionOccurrence_WhichPart[q259] = q256 -> + or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q238, q261] + != 3 + /\ + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q238, q261] + = q259 + | q261 : int(1..2)]) + | q259 : int(1..2)]) + /\ + and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q238, q263] + != 3 + -> + or([a_PartitionOccurrence_WhichPart[q265] = q256 /\ + q265 = + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q238, q263] + | q265 : int(1..2)]) + | q263 : int(1..2)])) + | q256 : int(1..2)]), + or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q238, q268] != 3 /\ + (toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q238, q289] + != 3 + /\ + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q238, q289] + = + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q238, q268] + | q289 : int(1..2)])) + < + toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q169, q291] + != 3 + /\ + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q169, q291] + = + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q238, q268] + | q291 : int(1..2)])) + /\ + (and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q238, q292] + != 3 + /\ + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q238, q292] + < + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q238, q268] + -> + toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q238, q301] + != 3 + /\ + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q238, q301] + = + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q238, q292] + | q301 : int(1..2)])) + = + toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q169, q303] + != 3 + /\ + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q169, q303] + = + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q238, q292] + | q303 : int(1..2)])) + | q292 : int(1..2)]) + /\ + and([and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q169, q293] + != 3, + !or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q238, q295] + != 3 + /\ + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q238, q295] + = + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q169, q293] + | q295 : int(1..2)]), + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q169, q293] + < + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q238, q268]; + int(1..3)]) + -> + toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q238, q297] + != 3 + /\ + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q238, q297] + = + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q169, q293] + | q297 : int(1..2)])) + = + toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q169, q299] + != 3 + /\ + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q169, q299] + = + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q169, q293] + | q299 : int(1..2)])) + | q293 : int(1..2)]))) + | q268 : int(1..2)]) + \/ + or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q169, q269] != 3 /\ + !or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q238, q271] != + 3 + /\ + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q238, q271] = + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q169, q269] + | q271 : int(1..2)]) + /\ + (toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q238, q273] + != 3 + /\ + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q238, q273] + = + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q169, q269] + | q273 : int(1..2)])) + < + toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q169, q275] + != 3 + /\ + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q169, q275] + = + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q169, q269] + | q275 : int(1..2)])) + /\ + (and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q238, q276] + != 3 + /\ + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q238, q276] + < + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q169, q269] + -> + toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q238, q285] + != 3 + /\ + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q238, q285] + = + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q238, q276] + | q285 : int(1..2)])) + = + toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q169, q287] + != 3 + /\ + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q169, q287] + = + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q238, q276] + | q287 : int(1..2)])) + | q276 : int(1..2)]) + /\ + and([and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q169, q277] + != 3, + !or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q238, q279] + != 3 + /\ + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q238, q279] + = + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q169, q277] + | q279 : int(1..2)]), + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q169, q277] + < + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q169, q269]; + int(1..3)]) + -> + toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q238, q281] + != 3 + /\ + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q238, q281] + = + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q169, q277] + | q281 : int(1..2)])) + = + toInt(or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q169, q283] + != 3 + /\ + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q169, q283] + = + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q169, q277] + | q283 : int(1..2)])) + | q277 : int(1..2)]))) + | q269 : int(1..2)]); + int(1..3)]) + -> + toInt(or([q240 <= a_PartitionOccurrence_NumParts /\ + (and([a_PartitionOccurrence_WhichPart[q243] = q240 -> + or([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q238, q245] + != 3 + /\ + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q238, q245] + = q243 + | q245 : int(1..2)]) + | q243 : int(1..2)]) + /\ + and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q238, q247] + != 3 + -> + or([a_PartitionOccurrence_WhichPart[q249] = q240 /\ + q249 = + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q238, q247] + | q249 : int(1..2)]) + | q247 : int(1..2)])) + | q240 : int(1..2)])) + = + toInt(or([q252 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ + and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q252, q253] = + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q238, q253] + | q253 : int(1..2)]) + | q252 : int(1..2)])) + | q238 : int(1..2)]))) + | q169 : int(1..2)]), + and([q1 <= a_PartitionOccurrence_NumParts -> a_PartitionOccurrence_PartSizes[q1] <= 2 | q1 : int(1..2)]), + and([q1 > a_PartitionOccurrence_NumParts -> a_PartitionOccurrence_PartSizes[q1] = 0 | q1 : int(1..2)]), + a_PartitionOccurrence_NumParts <= 2, + a_PartitionOccurrence_NumParts = max([a_PartitionOccurrence_WhichPart[q4] | q4 : int(1..2)]), + and([a_PartitionOccurrence_PartSizes[q5] = sum([toInt(a_PartitionOccurrence_WhichPart[q6] = q5) | q6 : int(1..2)]) + | q5 : int(1..2)]), + and([q7 <= a_PartitionOccurrence_NumParts -> + and([a_PartitionOccurrence_WhichPart[q8] = q7 -> a_PartitionOccurrence_FirstIndex[q7] <= q8 | q8 : int(1..2)]) + | q7 : int(1..2)]), + and([q7 <= a_PartitionOccurrence_NumParts -> + or([a_PartitionOccurrence_WhichPart[q8] = q7 /\ a_PartitionOccurrence_FirstIndex[q7] = q8 | q8 : int(1..2)]) + | q7 : int(1..2)]), + and([q7 > a_PartitionOccurrence_NumParts -> a_PartitionOccurrence_FirstIndex[q7] = 1 | q7 : int(1..2)]), + and([q9 <= a_PartitionOccurrence_NumParts /\ q10 <= a_PartitionOccurrence_NumParts -> + (q9 < q10 <-> a_PartitionOccurrence_FirstIndex[q9] < a_PartitionOccurrence_FirstIndex[q10]) + | q9 : int(1..2), q10 : int(1..2)]), + alldifferent_except([toInt(q28 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker /\ + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q28, q29] != + 3) + * + catchUndef(b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy + [q28, q29], + 0) + | q28 : int(1..2), q29 : int(1..2)], + 0), + and([q30 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> + sum([toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q30, q32] != 3) + | q32 : int(1..2)]) + >= 1 + | q30 : int(1..2)]), + 2 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> + [b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[1, q22] | q22 : int(1..2)] b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> + and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q15, q27] = 1 + | q27 : int(1..2)]) + | q15 : int(1..2)]), + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker <= 2, + and([q16 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q16, 1] < + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q16, 2] + \/ b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q16, 1] = 3 + | q16 : int(1..2)]), + and([q16 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> + (b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q16, 1] = 3 -> + b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q16, 2] = 3) + | q16 : int(1..2)]), + and([q16 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> + sum([toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q16, q19] != 3) + | q19 : int(1..2)]) + <= 2 + | q16 : int(1..2)]), + 2 = + sum([toInt(q24 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker) * + catchUndef(sum([toInt(b_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q24, q26] != + 3) + | q26 : int(1..2)]), + 0) + | q24 : int(1..2)]) + diff --git a/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_4_3-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_4_3-solution000001.solution new file mode 100644 index 0000000000..cde05d5274 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_4_3-solution000001.solution @@ -0,0 +1,11 @@ +language Essence 1.3 + +letting a be partition({1, 2}) +$ Visualisation for a +$ 1 2 + +letting b be partition({1}, {2}) +$ Visualisation for b +$ 1 +$ 2 + diff --git a/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_4_3.eprime.orig b/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_4_3.eprime.orig deleted file mode 100644 index d77a6dce81..0000000000 --- a/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_4_3.eprime.orig +++ /dev/null @@ -1,901 +0,0 @@ -language ESSENCE' 1.0 - -find a_PartitionOccurrence_NumParts: int(1..2) -find a_PartitionOccurrence_WhichPart: matrix indexed by [int(1..2)] of int(1..2) -find a_PartitionOccurrence_PartSizes: matrix indexed by [int(1..2)] of int(0..2) -find a_PartitionOccurrence_FirstIndex: matrix indexed by [int(1..2)] of int(1..2) -find b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker: int(0..2) -find b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker: - matrix indexed by [int(1..2)] of int(0..2) -find b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values: - matrix indexed by [int(1..2), int(1..2)] of int(1..2) -branching on - [a_PartitionOccurrence_NumParts, a_PartitionOccurrence_WhichPart, a_PartitionOccurrence_PartSizes, - a_PartitionOccurrence_FirstIndex, b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker, - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker, - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values] -such that - or([q30 <= a_PartitionOccurrence_NumParts /\ - (toInt(or([q153 <= a_PartitionOccurrence_NumParts /\ - (and([a_PartitionOccurrence_WhichPart[q156] = q153 -> - or([a_PartitionOccurrence_WhichPart[q158] = q30 /\ q158 = q156 | q158 : int(1..2)]) - | q156 : int(1..2)]) - /\ - and([a_PartitionOccurrence_WhichPart[q160] = q30 -> - or([a_PartitionOccurrence_WhichPart[q162] = q153 /\ q162 = q160 | q162 : int(1..2)]) - | q160 : int(1..2)])) - | q153 : int(1..2)])) - < - toInt(or([q34 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - (and([q36 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q34] - -> - or([a_PartitionOccurrence_WhichPart[q38] = q30 /\ - q38 = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q34, q36] - | q38 : int(1..2)]) - | q36 : int(1..2)]) - /\ - and([a_PartitionOccurrence_WhichPart[q40] = q30 -> - or([q42 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q34] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q34, q42] - = q40 - | q42 : int(1..2)]) - | q40 : int(1..2)])) - | q34 : int(1..2)])) - /\ - (and([q63 <= a_PartitionOccurrence_NumParts /\ - (or([a_PartitionOccurrence_WhichPart[q84] = q63 /\ - (toInt(or([a_PartitionOccurrence_WhichPart[q77] = q63 /\ q77 = q84 | q77 : int(1..2)])) < - sum([toInt(a_PartitionOccurrence_WhichPart[q56] = q30) * catchUndef(toInt(q56 = q84), 0) - | q56 : int(1..2)]) - /\ - (and([a_PartitionOccurrence_WhichPart[q80] = q63 -> - toInt(or([a_PartitionOccurrence_WhichPart[q79] = q63 /\ q79 = q80 | q79 : int(1..2)])) = - sum([toInt(a_PartitionOccurrence_WhichPart[q62] = q30) * catchUndef(toInt(q62 = q80), 0) - | q62 : int(1..2)]) - | q80 : int(1..2), q80 < q84]) - /\ - and([!or([a_PartitionOccurrence_WhichPart[q83] = q63 /\ q83 = q57 | q83 : int(1..2)]) -> - (a_PartitionOccurrence_WhichPart[q57] = q30 -> - toInt(or([a_PartitionOccurrence_WhichPart[q82] = q63 /\ q82 = q57 | q82 : int(1..2)])) = - sum([toInt(a_PartitionOccurrence_WhichPart[q59] = q30) * catchUndef(toInt(q59 = q57), 0) - | q59 : int(1..2)])) - | q57 : int(1..2), q57 < q84]))) - | q84 : int(1..2)]) - \/ - or([!or([a_PartitionOccurrence_WhichPart[q93] = q63 /\ q93 = q45 | q93 : int(1..2)]) /\ - (a_PartitionOccurrence_WhichPart[q45] = q30 /\ - (toInt(or([a_PartitionOccurrence_WhichPart[q86] = q63 /\ q86 = q45 | q86 : int(1..2)])) < - sum([toInt(a_PartitionOccurrence_WhichPart[q47] = q30) * catchUndef(toInt(q47 = q45), 0) - | q47 : int(1..2)]) - /\ - (and([a_PartitionOccurrence_WhichPart[q89] = q63 -> - toInt(or([a_PartitionOccurrence_WhichPart[q88] = q63 /\ q88 = q89 | q88 : int(1..2)])) = - sum([toInt(a_PartitionOccurrence_WhichPart[q53] = q30) * catchUndef(toInt(q53 = q89), 0) - | q53 : int(1..2)]) - | q89 : int(1..2), q89 < q45]) - /\ - and([!or([a_PartitionOccurrence_WhichPart[q92] = q63 /\ q92 = q48 | q92 : int(1..2)]) -> - (a_PartitionOccurrence_WhichPart[q48] = q30 -> - toInt(or([a_PartitionOccurrence_WhichPart[q91] = q63 /\ q91 = q48 | q91 : int(1..2)])) = - sum([toInt(a_PartitionOccurrence_WhichPart[q50] = q30) * catchUndef(toInt(q50 = q48), 0) - | q50 : int(1..2)])) - | q48 : int(1..2), q48 < q45])))) - | q45 : int(1..2)])) - -> - toInt(or([q142 <= a_PartitionOccurrence_NumParts /\ - (and([a_PartitionOccurrence_WhichPart[q145] = q142 -> - or([a_PartitionOccurrence_WhichPart[q147] = q63 /\ q147 = q145 | q147 : int(1..2)]) - | q145 : int(1..2)]) - /\ - and([a_PartitionOccurrence_WhichPart[q149] = q63 -> - or([a_PartitionOccurrence_WhichPart[q151] = q142 /\ q151 = q149 | q151 : int(1..2)]) - | q149 : int(1..2)])) - | q142 : int(1..2)])) - = - toInt(or([q67 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - (and([q69 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q67] - -> - or([a_PartitionOccurrence_WhichPart[q71] = q63 /\ - q71 = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q67, q69] - | q71 : int(1..2)]) - | q69 : int(1..2)]) - /\ - and([a_PartitionOccurrence_WhichPart[q73] = q63 -> - or([q75 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q67] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q67, q75] - = q73 - | q75 : int(1..2)]) - | q73 : int(1..2)])) - | q67 : int(1..2)])) - | q63 : int(1..2)]) - /\ - and([and([q95 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker, - !or([q131 <= a_PartitionOccurrence_NumParts /\ - (and([a_PartitionOccurrence_WhichPart[q134] = q131 -> - or([q136 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q95] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q95, q136] - = q134 - | q136 : int(1..2)]) - | q134 : int(1..2)]) - /\ - and([q138 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q95] - -> - or([a_PartitionOccurrence_WhichPart[q140] = q131 /\ - q140 = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q95, q138] - | q140 : int(1..2)]) - | q138 : int(1..2)])) - | q131 : int(1..2)]), - or([q96 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q95] - /\ - (toInt(or([q104 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q95] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q95, q104] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q95, q96] - | q104 : int(1..2)])) - < - sum([toInt(a_PartitionOccurrence_WhichPart[q56] = q30) * - catchUndef(toInt(q56 = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q95, q96]), - 0) - | q56 : int(1..2)]) - /\ - (and([q97 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q95] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q95, q97] - < - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q95, q96] - -> - toInt(or([q99 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q95] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q95, q99] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q95, q97] - | q99 : int(1..2)])) - = - sum([toInt(a_PartitionOccurrence_WhichPart[q62] = q30) * - catchUndef(toInt(q62 = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q95, q97]), - 0) - | q62 : int(1..2)]) - | q97 : int(1..2)]) - /\ - and([!or([q100 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q95] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q95, q100] - = q57 - | q100 : int(1..2)]) - /\ - q57 < - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q95, q96] - -> - (a_PartitionOccurrence_WhichPart[q57] = q30 -> - toInt(or([q102 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q95] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q95, q102] - = q57 - | q102 : int(1..2)])) - = - sum([toInt(a_PartitionOccurrence_WhichPart[q59] = q30) * catchUndef(toInt(q59 = q57), 0) - | q59 : int(1..2)])) - | q57 : int(1..2)]))) - | q96 : int(1..2)]) - \/ - or([!or([q113 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q95] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q95, q113] - = q45 - | q113 : int(1..2)]) - /\ - (a_PartitionOccurrence_WhichPart[q45] = q30 /\ - (toInt(or([q112 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q95] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q95, q112] - = q45 - | q112 : int(1..2)])) - < - sum([toInt(a_PartitionOccurrence_WhichPart[q47] = q30) * catchUndef(toInt(q47 = q45), 0) - | q47 : int(1..2)]) - /\ - (and([q105 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q95] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q95, q105] - < q45 - -> - toInt(or([q107 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q95] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q95, q107] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q95, q105] - | q107 : int(1..2)])) - = - sum([toInt(a_PartitionOccurrence_WhichPart[q53] = q30) * - catchUndef(toInt(q53 = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q95, q105]), - 0) - | q53 : int(1..2)]) - | q105 : int(1..2)]) - /\ - and([!or([q108 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q95] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q95, q108] - = q48 - | q108 : int(1..2)]) - -> - (a_PartitionOccurrence_WhichPart[q48] = q30 -> - toInt(or([q110 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q95] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q95, q110] - = q48 - | q110 : int(1..2)])) - = - sum([toInt(a_PartitionOccurrence_WhichPart[q50] = q30) * - catchUndef(toInt(q50 = q48), 0) - | q50 : int(1..2)])) - | q48 : int(1..2), q48 < q45])))) - | q45 : int(1..2)]); - int(1..3)]) - -> - toInt(or([q115 <= a_PartitionOccurrence_NumParts /\ - (and([a_PartitionOccurrence_WhichPart[q118] = q115 -> - or([q120 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q95] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q95, q120] - = q118 - | q120 : int(1..2)]) - | q118 : int(1..2)]) - /\ - and([q122 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q95] - -> - or([a_PartitionOccurrence_WhichPart[q124] = q115 /\ - q124 = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q95, q122] - | q124 : int(1..2)]) - | q122 : int(1..2)])) - | q115 : int(1..2)])) - = - toInt(or([q127 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - (b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q127] = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q95] - /\ - and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q127, q128] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q95, q128] - | q128 : int(1..2)])) - | q127 : int(1..2)])) - | q95 : int(1..2)]))) - | q30 : int(1..2)]) - \/ - or([q164 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - !or([q311 <= a_PartitionOccurrence_NumParts /\ - (and([a_PartitionOccurrence_WhichPart[q314] = q311 -> - or([q316 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q164] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q164, q316] - = q314 - | q316 : int(1..2)]) - | q314 : int(1..2)]) - /\ - and([q318 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q164] -> - or([a_PartitionOccurrence_WhichPart[q320] = q311 /\ - q320 = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q164, q318] - | q320 : int(1..2)]) - | q318 : int(1..2)])) - | q311 : int(1..2)]) - /\ - (toInt(or([q166 <= a_PartitionOccurrence_NumParts /\ - (and([a_PartitionOccurrence_WhichPart[q169] = q166 -> - or([q171 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q164] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q164, q171] - = q169 - | q171 : int(1..2)]) - | q169 : int(1..2)]) - /\ - and([q173 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q164] - -> - or([a_PartitionOccurrence_WhichPart[q175] = q166 /\ - q175 = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q164, q173] - | q175 : int(1..2)]) - | q173 : int(1..2)])) - | q166 : int(1..2)])) - < - toInt(or([q178 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - (b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q178] = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q164] - /\ - and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q178, q179] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q164, q179] - | q179 : int(1..2)])) - | q178 : int(1..2)])) - /\ - (and([q181 <= a_PartitionOccurrence_NumParts /\ - (or([a_PartitionOccurrence_WhichPart[q196] = q181 /\ - (sum([toInt(a_PartitionOccurrence_WhichPart[q217] = q181) * catchUndef(toInt(q217 = q196), 0) - | q217 : int(1..2)]) - < - toInt(or([q219 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q164] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q164, q219] - = q196 - | q219 : int(1..2)])) - /\ - (and([a_PartitionOccurrence_WhichPart[q220] = q181 -> - sum([toInt(a_PartitionOccurrence_WhichPart[q229] = q181) * catchUndef(toInt(q229 = q220), 0) - | q229 : int(1..2)]) - = - toInt(or([q231 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q164] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q164, q231] - = q220 - | q231 : int(1..2)])) - | q220 : int(1..2), q220 < q196]) - /\ - and([and([q221 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q164], - !or([a_PartitionOccurrence_WhichPart[q227] = q181 /\ - q227 = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q164, q221] - | q227 : int(1..2)]), - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q164, q221] - < q196; - int(1..3)]) - -> - sum([toInt(a_PartitionOccurrence_WhichPart[q223] = q181) * - catchUndef(toInt(q223 = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q164, q221]), - 0) - | q223 : int(1..2)]) - = - toInt(or([q225 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q164] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q164, q225] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q164, q221] - | q225 : int(1..2)])) - | q221 : int(1..2)]))) - | q196 : int(1..2)]) - \/ - or([q197 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q164] - /\ - !or([a_PartitionOccurrence_WhichPart[q215] = q181 /\ - q215 = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q164, q197] - | q215 : int(1..2)]) - /\ - (sum([toInt(a_PartitionOccurrence_WhichPart[q199] = q181) * - catchUndef(toInt(q199 = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q164, q197]), - 0) - | q199 : int(1..2)]) - < - toInt(or([q201 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q164] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q164, q201] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q164, q197] - | q201 : int(1..2)])) - /\ - (and([a_PartitionOccurrence_WhichPart[q202] = q181 /\ - q202 < - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q164, q197] - -> - sum([toInt(a_PartitionOccurrence_WhichPart[q211] = q181) * catchUndef(toInt(q211 = q202), 0) - | q211 : int(1..2)]) - = - toInt(or([q213 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q164] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q164, q213] - = q202 - | q213 : int(1..2)])) - | q202 : int(1..2)]) - /\ - and([and([q203 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q164], - !or([a_PartitionOccurrence_WhichPart[q209] = q181 /\ - q209 = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q164, q203] - | q209 : int(1..2)]), - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q164, q203] - < - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q164, q197]; - int(1..3)]) - -> - sum([toInt(a_PartitionOccurrence_WhichPart[q205] = q181) * - catchUndef(toInt(q205 = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q164, q203]), - 0) - | q205 : int(1..2)]) - = - toInt(or([q207 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q164] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q164, q207] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q164, q203] - | q207 : int(1..2)])) - | q203 : int(1..2)]))) - | q197 : int(1..2)])) - -> - toInt(or([q300 <= a_PartitionOccurrence_NumParts /\ - (and([a_PartitionOccurrence_WhichPart[q303] = q300 -> - or([a_PartitionOccurrence_WhichPart[q305] = q181 /\ q305 = q303 | q305 : int(1..2)]) - | q303 : int(1..2)]) - /\ - and([a_PartitionOccurrence_WhichPart[q307] = q181 -> - or([a_PartitionOccurrence_WhichPart[q309] = q300 /\ q309 = q307 | q309 : int(1..2)]) - | q307 : int(1..2)])) - | q300 : int(1..2)])) - = - toInt(or([q185 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - (and([q187 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q185] - -> - or([a_PartitionOccurrence_WhichPart[q189] = q181 /\ - q189 = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q185, q187] - | q189 : int(1..2)]) - | q187 : int(1..2)]) - /\ - and([a_PartitionOccurrence_WhichPart[q191] = q181 -> - or([q193 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q185] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q185, q193] - = q191 - | q193 : int(1..2)]) - | q191 : int(1..2)])) - | q185 : int(1..2)])) - | q181 : int(1..2)]) - /\ - and([and([q233 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker, - !or([q251 <= a_PartitionOccurrence_NumParts /\ - (and([a_PartitionOccurrence_WhichPart[q254] = q251 -> - or([q256 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q233] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q233, q256] - = q254 - | q256 : int(1..2)]) - | q254 : int(1..2)]) - /\ - and([q258 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q233] - -> - or([a_PartitionOccurrence_WhichPart[q260] = q251 /\ - q260 = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q233, q258] - | q260 : int(1..2)]) - | q258 : int(1..2)])) - | q251 : int(1..2)]), - or([q263 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q233] - /\ - (toInt(or([q284 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q233] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q233, q284] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q233, q263] - | q284 : int(1..2)])) - < - toInt(or([q286 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q164] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q164, q286] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q233, q263] - | q286 : int(1..2)])) - /\ - (and([q287 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q233] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q233, q287] - < - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q233, q263] - -> - toInt(or([q296 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q233] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q233, q296] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q233, q287] - | q296 : int(1..2)])) - = - toInt(or([q298 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q164] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q164, q298] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q233, q287] - | q298 : int(1..2)])) - | q287 : int(1..2)]) - /\ - and([and([q288 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q164], - !or([q294 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q233] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q233, q294] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q164, q288] - | q294 : int(1..2)]), - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q164, q288] - < - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q233, q263]; - int(1..3)]) - -> - toInt(or([q290 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q233] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q233, q290] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q164, q288] - | q290 : int(1..2)])) - = - toInt(or([q292 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q164] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q164, q292] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q164, q288] - | q292 : int(1..2)])) - | q288 : int(1..2)]))) - | q263 : int(1..2)]) - \/ - or([q264 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q164] - /\ - !or([q282 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q233] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q233, q282] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q164, q264] - | q282 : int(1..2)]) - /\ - (toInt(or([q266 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q233] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q233, q266] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q164, q264] - | q266 : int(1..2)])) - < - toInt(or([q268 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q164] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q164, q268] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q164, q264] - | q268 : int(1..2)])) - /\ - (and([q269 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q233] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q233, q269] - < - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q164, q264] - -> - toInt(or([q278 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q233] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q233, q278] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q233, q269] - | q278 : int(1..2)])) - = - toInt(or([q280 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q164] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q164, q280] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q233, q269] - | q280 : int(1..2)])) - | q269 : int(1..2)]) - /\ - and([and([q270 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q164], - !or([q276 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q233] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q233, q276] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q164, q270] - | q276 : int(1..2)]), - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q164, q270] - < - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q164, q264]; - int(1..3)]) - -> - toInt(or([q272 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q233] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q233, q272] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q164, q270] - | q272 : int(1..2)])) - = - toInt(or([q274 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q164] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q164, q274] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q164, q270] - | q274 : int(1..2)])) - | q270 : int(1..2)]))) - | q264 : int(1..2)]); - int(1..3)]) - -> - toInt(or([q235 <= a_PartitionOccurrence_NumParts /\ - (and([a_PartitionOccurrence_WhichPart[q238] = q235 -> - or([q240 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q233] - /\ - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q233, q240] - = q238 - | q240 : int(1..2)]) - | q238 : int(1..2)]) - /\ - and([q242 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q233] - -> - or([a_PartitionOccurrence_WhichPart[q244] = q235 /\ - q244 = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q233, q242] - | q244 : int(1..2)]) - | q242 : int(1..2)])) - | q235 : int(1..2)])) - = - toInt(or([q247 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - (b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q247] = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q233] - /\ - and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q247, q248] - = - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q233, q248] - | q248 : int(1..2)])) - | q247 : int(1..2)])) - | q233 : int(1..2)]))) - | q164 : int(1..2)]), - and([q1 <= a_PartitionOccurrence_NumParts -> a_PartitionOccurrence_PartSizes[q1] <= 2 | q1 : int(1..2)]), - and([q1 > a_PartitionOccurrence_NumParts -> a_PartitionOccurrence_PartSizes[q1] = 0 | q1 : int(1..2)]), - a_PartitionOccurrence_NumParts <= 2, - a_PartitionOccurrence_NumParts = max([a_PartitionOccurrence_WhichPart[q4] | q4 : int(1..2)]), - and([a_PartitionOccurrence_PartSizes[q5] = sum([toInt(a_PartitionOccurrence_WhichPart[q6] = q5) | q6 : int(1..2)]) - | q5 : int(1..2)]), - and([q7 <= a_PartitionOccurrence_NumParts -> - and([a_PartitionOccurrence_WhichPart[q8] = q7 -> a_PartitionOccurrence_FirstIndex[q7] <= q8 | q8 : int(1..2)]) - | q7 : int(1..2)]), - and([q7 <= a_PartitionOccurrence_NumParts -> - or([a_PartitionOccurrence_WhichPart[q8] = q7 /\ a_PartitionOccurrence_FirstIndex[q7] = q8 | q8 : int(1..2)]) - | q7 : int(1..2)]), - and([q7 > a_PartitionOccurrence_NumParts -> a_PartitionOccurrence_FirstIndex[q7] = 1 | q7 : int(1..2)]), - and([q9 <= a_PartitionOccurrence_NumParts /\ q10 <= a_PartitionOccurrence_NumParts -> - (q9 < q10 <-> a_PartitionOccurrence_FirstIndex[q9] < a_PartitionOccurrence_FirstIndex[q10]) - | q9 : int(1..2), q10 : int(1..2)]), - alldifferent_except([toInt(q25 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - q26 <= - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker - [q25]) - * - catchUndef(b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q25, q26], - 0) - | q25 : int(1..2), q26 : int(1..2)], - 0), - and([q27 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q27] >= 1 - | q27 : int(1..2)]), - 2 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - flatten([[b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[1]; int(1)], - [b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[1, q21] - | q21 : int(1..2)]; - int(1..2)]) - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q15] = 0 /\ - and([b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q15, q24] = 1 - | q24 : int(1..2)]) - | q15 : int(1..2)]), - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker <= 2, - and([q16 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - (2 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q16] -> - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q16, 1] < - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q16, 2]) - | q16 : int(1..2)]), - and([q16 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - and([q18 > b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q16] -> - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q16, q18] = 1 - | q18 : int(1..2)]) - | q16 : int(1..2)]), - and([q16 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q16] <= 2 - | q16 : int(1..2)]), - 2 = - sum([toInt(q23 <= b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker) * - catchUndef(b_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q23], 0) - | q23 : int(1..2)]) - diff --git a/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_4_4-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_4_4-solution000001.solution new file mode 100644 index 0000000000..cde05d5274 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_4_4-solution000001.solution @@ -0,0 +1,11 @@ +language Essence 1.3 + +letting a be partition({1, 2}) +$ Visualisation for a +$ 1 2 + +letting b be partition({1}, {2}) +$ Visualisation for b +$ 1 +$ 2 + diff --git a/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_4_4.eprime b/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_4_4.eprime new file mode 100644 index 0000000000..c027a58750 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_partition_01/expected/model_4_4.eprime @@ -0,0 +1,394 @@ +language ESSENCE' 1.0 + +find a_PartitionOccurrence_NumParts: int(1..2) +find a_PartitionOccurrence_WhichPart: matrix indexed by [int(1..2)] of int(1..2) +find a_PartitionOccurrence_PartSizes: matrix indexed by [int(1..2)] of int(0..2) +find a_PartitionOccurrence_FirstIndex: matrix indexed by [int(1..2)] of int(1..2) +find b_PartitionOccurrence_NumParts: int(1..2) +find b_PartitionOccurrence_WhichPart: matrix indexed by [int(1..2)] of int(1..2) +find b_PartitionOccurrence_PartSizes: matrix indexed by [int(1..2)] of int(0..2) +find b_PartitionOccurrence_FirstIndex: matrix indexed by [int(1..2)] of int(1..2) +branching on + [a_PartitionOccurrence_NumParts, a_PartitionOccurrence_WhichPart, a_PartitionOccurrence_PartSizes, + a_PartitionOccurrence_FirstIndex, b_PartitionOccurrence_NumParts, b_PartitionOccurrence_WhichPart, + b_PartitionOccurrence_PartSizes, b_PartitionOccurrence_FirstIndex] +such that + or([q23 <= a_PartitionOccurrence_NumParts /\ + (toInt(or([q152 <= a_PartitionOccurrence_NumParts /\ + (and([a_PartitionOccurrence_WhichPart[q155] = q152 -> + or([a_PartitionOccurrence_WhichPart[q157] = q23 /\ q157 = q155 | q157 : int(1..2)]) + | q155 : int(1..2)]) + /\ + and([a_PartitionOccurrence_WhichPart[q159] = q23 -> + or([a_PartitionOccurrence_WhichPart[q161] = q152 /\ q161 = q159 | q161 : int(1..2)]) + | q159 : int(1..2)])) + | q152 : int(1..2)])) + < + toInt(or([q26 <= b_PartitionOccurrence_NumParts /\ + (and([b_PartitionOccurrence_WhichPart[q29] = q26 -> + or([a_PartitionOccurrence_WhichPart[q31] = q23 /\ q31 = q29 | q31 : int(1..2)]) + | q29 : int(1..2)]) + /\ + and([a_PartitionOccurrence_WhichPart[q33] = q23 -> + or([b_PartitionOccurrence_WhichPart[q35] = q26 /\ q35 = q33 | q35 : int(1..2)]) + | q33 : int(1..2)])) + | q26 : int(1..2)])) + /\ + (and([q56 <= a_PartitionOccurrence_NumParts /\ + (or([a_PartitionOccurrence_WhichPart[q77] = q56 /\ + (toInt(or([a_PartitionOccurrence_WhichPart[q70] = q56 /\ q70 = q77 | q70 : int(1..2)])) < + sum([toInt(a_PartitionOccurrence_WhichPart[q49] = q23) * catchUndef(toInt(q49 = q77), 0) + | q49 : int(1..2)]) + /\ + (and([a_PartitionOccurrence_WhichPart[q73] = q56 -> + toInt(or([a_PartitionOccurrence_WhichPart[q72] = q56 /\ q72 = q73 | q72 : int(1..2)])) = + sum([toInt(a_PartitionOccurrence_WhichPart[q55] = q23) * catchUndef(toInt(q55 = q73), 0) + | q55 : int(1..2)]) + | q73 : int(1..2), q73 < q77]) + /\ + and([!or([a_PartitionOccurrence_WhichPart[q76] = q56 /\ q76 = q50 | q76 : int(1..2)]) -> + (a_PartitionOccurrence_WhichPart[q50] = q23 -> + toInt(or([a_PartitionOccurrence_WhichPart[q75] = q56 /\ q75 = q50 | q75 : int(1..2)])) = + sum([toInt(a_PartitionOccurrence_WhichPart[q52] = q23) * catchUndef(toInt(q52 = q50), 0) + | q52 : int(1..2)])) + | q50 : int(1..2), q50 < q77]))) + | q77 : int(1..2)]) + \/ + or([!or([a_PartitionOccurrence_WhichPart[q86] = q56 /\ q86 = q38 | q86 : int(1..2)]) /\ + (a_PartitionOccurrence_WhichPart[q38] = q23 /\ + (toInt(or([a_PartitionOccurrence_WhichPart[q79] = q56 /\ q79 = q38 | q79 : int(1..2)])) < + sum([toInt(a_PartitionOccurrence_WhichPart[q40] = q23) * catchUndef(toInt(q40 = q38), 0) + | q40 : int(1..2)]) + /\ + (and([a_PartitionOccurrence_WhichPart[q82] = q56 -> + toInt(or([a_PartitionOccurrence_WhichPart[q81] = q56 /\ q81 = q82 | q81 : int(1..2)])) = + sum([toInt(a_PartitionOccurrence_WhichPart[q46] = q23) * catchUndef(toInt(q46 = q82), 0) + | q46 : int(1..2)]) + | q82 : int(1..2), q82 < q38]) + /\ + and([!or([a_PartitionOccurrence_WhichPart[q85] = q56 /\ q85 = q41 | q85 : int(1..2)]) -> + (a_PartitionOccurrence_WhichPart[q41] = q23 -> + toInt(or([a_PartitionOccurrence_WhichPart[q84] = q56 /\ q84 = q41 | q84 : int(1..2)])) = + sum([toInt(a_PartitionOccurrence_WhichPart[q43] = q23) * catchUndef(toInt(q43 = q41), 0) + | q43 : int(1..2)])) + | q41 : int(1..2), q41 < q38])))) + | q38 : int(1..2)])) + -> + toInt(or([q141 <= a_PartitionOccurrence_NumParts /\ + (and([a_PartitionOccurrence_WhichPart[q144] = q141 -> + or([a_PartitionOccurrence_WhichPart[q146] = q56 /\ q146 = q144 | q146 : int(1..2)]) + | q144 : int(1..2)]) + /\ + and([a_PartitionOccurrence_WhichPart[q148] = q56 -> + or([a_PartitionOccurrence_WhichPart[q150] = q141 /\ q150 = q148 | q150 : int(1..2)]) + | q148 : int(1..2)])) + | q141 : int(1..2)])) + = + toInt(or([q59 <= b_PartitionOccurrence_NumParts /\ + (and([b_PartitionOccurrence_WhichPart[q62] = q59 -> + or([a_PartitionOccurrence_WhichPart[q64] = q56 /\ q64 = q62 | q64 : int(1..2)]) + | q62 : int(1..2)]) + /\ + and([a_PartitionOccurrence_WhichPart[q66] = q56 -> + or([b_PartitionOccurrence_WhichPart[q68] = q59 /\ q68 = q66 | q68 : int(1..2)]) + | q66 : int(1..2)])) + | q59 : int(1..2)])) + | q56 : int(1..2)]) + /\ + and([and([q87 <= b_PartitionOccurrence_NumParts, + !or([q101 <= a_PartitionOccurrence_NumParts /\ + (and([a_PartitionOccurrence_WhichPart[q104] = q101 -> + or([b_PartitionOccurrence_WhichPart[q106] = q87 /\ q106 = q104 | q106 : int(1..2)]) + | q104 : int(1..2)]) + /\ + and([b_PartitionOccurrence_WhichPart[q108] = q87 -> + or([a_PartitionOccurrence_WhichPart[q110] = q101 /\ q110 = q108 | q110 : int(1..2)]) + | q108 : int(1..2)])) + | q101 : int(1..2)]), + or([b_PartitionOccurrence_WhichPart[q119] = q87 /\ + (toInt(or([b_PartitionOccurrence_WhichPart[q112] = q87 /\ q112 = q119 | q112 : int(1..2)])) < + sum([toInt(a_PartitionOccurrence_WhichPart[q49] = q23) * catchUndef(toInt(q49 = q119), 0) + | q49 : int(1..2)]) + /\ + (and([b_PartitionOccurrence_WhichPart[q115] = q87 -> + toInt(or([b_PartitionOccurrence_WhichPart[q114] = q87 /\ q114 = q115 + | q114 : int(1..2)])) + = + sum([toInt(a_PartitionOccurrence_WhichPart[q55] = q23) * catchUndef(toInt(q55 = q115), 0) + | q55 : int(1..2)]) + | q115 : int(1..2), q115 < q119]) + /\ + and([!or([b_PartitionOccurrence_WhichPart[q118] = q87 /\ q118 = q50 | q118 : int(1..2)]) -> + (a_PartitionOccurrence_WhichPart[q50] = q23 -> + toInt(or([b_PartitionOccurrence_WhichPart[q117] = q87 /\ q117 = q50 + | q117 : int(1..2)])) + = + sum([toInt(a_PartitionOccurrence_WhichPart[q52] = q23) * catchUndef(toInt(q52 = q50), 0) + | q52 : int(1..2)])) + | q50 : int(1..2), q50 < q119]))) + | q119 : int(1..2)]) + \/ + or([!or([b_PartitionOccurrence_WhichPart[q128] = q87 /\ q128 = q38 | q128 : int(1..2)]) /\ + (a_PartitionOccurrence_WhichPart[q38] = q23 /\ + (toInt(or([b_PartitionOccurrence_WhichPart[q121] = q87 /\ q121 = q38 | q121 : int(1..2)])) < + sum([toInt(a_PartitionOccurrence_WhichPart[q40] = q23) * catchUndef(toInt(q40 = q38), 0) + | q40 : int(1..2)]) + /\ + (and([b_PartitionOccurrence_WhichPart[q124] = q87 -> + toInt(or([b_PartitionOccurrence_WhichPart[q123] = q87 /\ q123 = q124 + | q123 : int(1..2)])) + = + sum([toInt(a_PartitionOccurrence_WhichPart[q46] = q23) * + catchUndef(toInt(q46 = q124), 0) + | q46 : int(1..2)]) + | q124 : int(1..2), q124 < q38]) + /\ + and([!or([b_PartitionOccurrence_WhichPart[q127] = q87 /\ q127 = q41 | q127 : int(1..2)]) -> + (a_PartitionOccurrence_WhichPart[q41] = q23 -> + toInt(or([b_PartitionOccurrence_WhichPart[q126] = q87 /\ q126 = q41 + | q126 : int(1..2)])) + = + sum([toInt(a_PartitionOccurrence_WhichPart[q43] = q23) * + catchUndef(toInt(q43 = q41), 0) + | q43 : int(1..2)])) + | q41 : int(1..2), q41 < q38])))) + | q38 : int(1..2)]); + int(1..3)]) + -> + toInt(or([q130 <= a_PartitionOccurrence_NumParts /\ + (and([a_PartitionOccurrence_WhichPart[q133] = q130 -> + or([b_PartitionOccurrence_WhichPart[q135] = q87 /\ q135 = q133 | q135 : int(1..2)]) + | q133 : int(1..2)]) + /\ + and([b_PartitionOccurrence_WhichPart[q137] = q87 -> + or([a_PartitionOccurrence_WhichPart[q139] = q130 /\ q139 = q137 | q139 : int(1..2)]) + | q137 : int(1..2)])) + | q130 : int(1..2)])) + = + toInt(or([q90 <= b_PartitionOccurrence_NumParts /\ + (and([b_PartitionOccurrence_WhichPart[q93] = q90 -> + or([b_PartitionOccurrence_WhichPart[q95] = q87 /\ q95 = q93 | q95 : int(1..2)]) + | q93 : int(1..2)]) + /\ + and([b_PartitionOccurrence_WhichPart[q97] = q87 -> + or([b_PartitionOccurrence_WhichPart[q99] = q90 /\ q99 = q97 | q99 : int(1..2)]) + | q97 : int(1..2)])) + | q90 : int(1..2)])) + | q87 : int(1..2)]))) + | q23 : int(1..2)]) + \/ + or([q162 <= b_PartitionOccurrence_NumParts /\ + !or([q302 <= a_PartitionOccurrence_NumParts /\ + (and([a_PartitionOccurrence_WhichPart[q305] = q302 -> + or([b_PartitionOccurrence_WhichPart[q307] = q162 /\ q307 = q305 | q307 : int(1..2)]) + | q305 : int(1..2)]) + /\ + and([b_PartitionOccurrence_WhichPart[q309] = q162 -> + or([a_PartitionOccurrence_WhichPart[q311] = q302 /\ q311 = q309 | q311 : int(1..2)]) + | q309 : int(1..2)])) + | q302 : int(1..2)]) + /\ + (toInt(or([q291 <= a_PartitionOccurrence_NumParts /\ + (and([a_PartitionOccurrence_WhichPart[q294] = q291 -> + or([b_PartitionOccurrence_WhichPart[q296] = q162 /\ q296 = q294 | q296 : int(1..2)]) + | q294 : int(1..2)]) + /\ + and([b_PartitionOccurrence_WhichPart[q298] = q162 -> + or([a_PartitionOccurrence_WhichPart[q300] = q291 /\ q300 = q298 | q300 : int(1..2)]) + | q298 : int(1..2)])) + | q291 : int(1..2)])) + < + toInt(or([q165 <= b_PartitionOccurrence_NumParts /\ + (and([b_PartitionOccurrence_WhichPart[q168] = q165 -> + or([b_PartitionOccurrence_WhichPart[q170] = q162 /\ q170 = q168 | q170 : int(1..2)]) + | q168 : int(1..2)]) + /\ + and([b_PartitionOccurrence_WhichPart[q172] = q162 -> + or([b_PartitionOccurrence_WhichPart[q174] = q165 /\ q174 = q172 | q174 : int(1..2)]) + | q172 : int(1..2)])) + | q165 : int(1..2)])) + /\ + (and([q195 <= a_PartitionOccurrence_NumParts /\ + (or([a_PartitionOccurrence_WhichPart[q216] = q195 /\ + (toInt(or([a_PartitionOccurrence_WhichPart[q209] = q195 /\ q209 = q216 | q209 : int(1..2)])) < + sum([toInt(b_PartitionOccurrence_WhichPart[q188] = q162) * catchUndef(toInt(q188 = q216), 0) + | q188 : int(1..2)]) + /\ + (and([a_PartitionOccurrence_WhichPart[q212] = q195 -> + toInt(or([a_PartitionOccurrence_WhichPart[q211] = q195 /\ q211 = q212 | q211 : int(1..2)])) = + sum([toInt(b_PartitionOccurrence_WhichPart[q194] = q162) * catchUndef(toInt(q194 = q212), 0) + | q194 : int(1..2)]) + | q212 : int(1..2), q212 < q216]) + /\ + and([!or([a_PartitionOccurrence_WhichPart[q215] = q195 /\ q215 = q189 | q215 : int(1..2)]) -> + (b_PartitionOccurrence_WhichPart[q189] = q162 -> + toInt(or([a_PartitionOccurrence_WhichPart[q214] = q195 /\ q214 = q189 | q214 : int(1..2)])) + = + sum([toInt(b_PartitionOccurrence_WhichPart[q191] = q162) * catchUndef(toInt(q191 = q189), 0) + | q191 : int(1..2)])) + | q189 : int(1..2), q189 < q216]))) + | q216 : int(1..2)]) + \/ + or([!or([a_PartitionOccurrence_WhichPart[q225] = q195 /\ q225 = q177 | q225 : int(1..2)]) /\ + (b_PartitionOccurrence_WhichPart[q177] = q162 /\ + (toInt(or([a_PartitionOccurrence_WhichPart[q218] = q195 /\ q218 = q177 | q218 : int(1..2)])) < + sum([toInt(b_PartitionOccurrence_WhichPart[q179] = q162) * catchUndef(toInt(q179 = q177), 0) + | q179 : int(1..2)]) + /\ + (and([a_PartitionOccurrence_WhichPart[q221] = q195 -> + toInt(or([a_PartitionOccurrence_WhichPart[q220] = q195 /\ q220 = q221 | q220 : int(1..2)])) + = + sum([toInt(b_PartitionOccurrence_WhichPart[q185] = q162) * catchUndef(toInt(q185 = q221), 0) + | q185 : int(1..2)]) + | q221 : int(1..2), q221 < q177]) + /\ + and([!or([a_PartitionOccurrence_WhichPart[q224] = q195 /\ q224 = q180 | q224 : int(1..2)]) -> + (b_PartitionOccurrence_WhichPart[q180] = q162 -> + toInt(or([a_PartitionOccurrence_WhichPart[q223] = q195 /\ q223 = q180 | q223 : int(1..2)])) + = + sum([toInt(b_PartitionOccurrence_WhichPart[q182] = q162) * + catchUndef(toInt(q182 = q180), 0) + | q182 : int(1..2)])) + | q180 : int(1..2), q180 < q177])))) + | q177 : int(1..2)])) + -> + toInt(or([q280 <= a_PartitionOccurrence_NumParts /\ + (and([a_PartitionOccurrence_WhichPart[q283] = q280 -> + or([a_PartitionOccurrence_WhichPart[q285] = q195 /\ q285 = q283 | q285 : int(1..2)]) + | q283 : int(1..2)]) + /\ + and([a_PartitionOccurrence_WhichPart[q287] = q195 -> + or([a_PartitionOccurrence_WhichPart[q289] = q280 /\ q289 = q287 | q289 : int(1..2)]) + | q287 : int(1..2)])) + | q280 : int(1..2)])) + = + toInt(or([q198 <= b_PartitionOccurrence_NumParts /\ + (and([b_PartitionOccurrence_WhichPart[q201] = q198 -> + or([a_PartitionOccurrence_WhichPart[q203] = q195 /\ q203 = q201 | q203 : int(1..2)]) + | q201 : int(1..2)]) + /\ + and([a_PartitionOccurrence_WhichPart[q205] = q195 -> + or([b_PartitionOccurrence_WhichPart[q207] = q198 /\ q207 = q205 | q207 : int(1..2)]) + | q205 : int(1..2)])) + | q198 : int(1..2)])) + | q195 : int(1..2)]) + /\ + and([and([q226 <= b_PartitionOccurrence_NumParts, + !or([q240 <= a_PartitionOccurrence_NumParts /\ + (and([a_PartitionOccurrence_WhichPart[q243] = q240 -> + or([b_PartitionOccurrence_WhichPart[q245] = q226 /\ q245 = q243 | q245 : int(1..2)]) + | q243 : int(1..2)]) + /\ + and([b_PartitionOccurrence_WhichPart[q247] = q226 -> + or([a_PartitionOccurrence_WhichPart[q249] = q240 /\ q249 = q247 | q249 : int(1..2)]) + | q247 : int(1..2)])) + | q240 : int(1..2)]), + or([b_PartitionOccurrence_WhichPart[q258] = q226 /\ + (toInt(or([b_PartitionOccurrence_WhichPart[q251] = q226 /\ q251 = q258 | q251 : int(1..2)])) < + sum([toInt(b_PartitionOccurrence_WhichPart[q188] = q162) * catchUndef(toInt(q188 = q258), 0) + | q188 : int(1..2)]) + /\ + (and([b_PartitionOccurrence_WhichPart[q254] = q226 -> + toInt(or([b_PartitionOccurrence_WhichPart[q253] = q226 /\ q253 = q254 + | q253 : int(1..2)])) + = + sum([toInt(b_PartitionOccurrence_WhichPart[q194] = q162) * + catchUndef(toInt(q194 = q254), 0) + | q194 : int(1..2)]) + | q254 : int(1..2), q254 < q258]) + /\ + and([!or([b_PartitionOccurrence_WhichPart[q257] = q226 /\ q257 = q189 | q257 : int(1..2)]) -> + (b_PartitionOccurrence_WhichPart[q189] = q162 -> + toInt(or([b_PartitionOccurrence_WhichPart[q256] = q226 /\ q256 = q189 + | q256 : int(1..2)])) + = + sum([toInt(b_PartitionOccurrence_WhichPart[q191] = q162) * + catchUndef(toInt(q191 = q189), 0) + | q191 : int(1..2)])) + | q189 : int(1..2), q189 < q258]))) + | q258 : int(1..2)]) + \/ + or([!or([b_PartitionOccurrence_WhichPart[q267] = q226 /\ q267 = q177 | q267 : int(1..2)]) /\ + (b_PartitionOccurrence_WhichPart[q177] = q162 /\ + (toInt(or([b_PartitionOccurrence_WhichPart[q260] = q226 /\ q260 = q177 | q260 : int(1..2)])) < + sum([toInt(b_PartitionOccurrence_WhichPart[q179] = q162) * catchUndef(toInt(q179 = q177), 0) + | q179 : int(1..2)]) + /\ + (and([b_PartitionOccurrence_WhichPart[q263] = q226 -> + toInt(or([b_PartitionOccurrence_WhichPart[q262] = q226 /\ q262 = q263 + | q262 : int(1..2)])) + = + sum([toInt(b_PartitionOccurrence_WhichPart[q185] = q162) * + catchUndef(toInt(q185 = q263), 0) + | q185 : int(1..2)]) + | q263 : int(1..2), q263 < q177]) + /\ + and([!or([b_PartitionOccurrence_WhichPart[q266] = q226 /\ q266 = q180 | q266 : int(1..2)]) -> + (b_PartitionOccurrence_WhichPart[q180] = q162 -> + toInt(or([b_PartitionOccurrence_WhichPart[q265] = q226 /\ q265 = q180 + | q265 : int(1..2)])) + = + sum([toInt(b_PartitionOccurrence_WhichPart[q182] = q162) * + catchUndef(toInt(q182 = q180), 0) + | q182 : int(1..2)])) + | q180 : int(1..2), q180 < q177])))) + | q177 : int(1..2)]); + int(1..3)]) + -> + toInt(or([q269 <= a_PartitionOccurrence_NumParts /\ + (and([a_PartitionOccurrence_WhichPart[q272] = q269 -> + or([b_PartitionOccurrence_WhichPart[q274] = q226 /\ q274 = q272 | q274 : int(1..2)]) + | q272 : int(1..2)]) + /\ + and([b_PartitionOccurrence_WhichPart[q276] = q226 -> + or([a_PartitionOccurrence_WhichPart[q278] = q269 /\ q278 = q276 | q278 : int(1..2)]) + | q276 : int(1..2)])) + | q269 : int(1..2)])) + = + toInt(or([q229 <= b_PartitionOccurrence_NumParts /\ + (and([b_PartitionOccurrence_WhichPart[q232] = q229 -> + or([b_PartitionOccurrence_WhichPart[q234] = q226 /\ q234 = q232 | q234 : int(1..2)]) + | q232 : int(1..2)]) + /\ + and([b_PartitionOccurrence_WhichPart[q236] = q226 -> + or([b_PartitionOccurrence_WhichPart[q238] = q229 /\ q238 = q236 | q238 : int(1..2)]) + | q236 : int(1..2)])) + | q229 : int(1..2)])) + | q226 : int(1..2)]))) + | q162 : int(1..2)]), + and([q1 <= a_PartitionOccurrence_NumParts -> a_PartitionOccurrence_PartSizes[q1] <= 2 | q1 : int(1..2)]), + and([q1 > a_PartitionOccurrence_NumParts -> a_PartitionOccurrence_PartSizes[q1] = 0 | q1 : int(1..2)]), + a_PartitionOccurrence_NumParts <= 2, + a_PartitionOccurrence_NumParts = max([a_PartitionOccurrence_WhichPart[q4] | q4 : int(1..2)]), + and([a_PartitionOccurrence_PartSizes[q5] = sum([toInt(a_PartitionOccurrence_WhichPart[q6] = q5) | q6 : int(1..2)]) + | q5 : int(1..2)]), + and([q7 <= a_PartitionOccurrence_NumParts -> + and([a_PartitionOccurrence_WhichPart[q8] = q7 -> a_PartitionOccurrence_FirstIndex[q7] <= q8 | q8 : int(1..2)]) + | q7 : int(1..2)]), + and([q7 <= a_PartitionOccurrence_NumParts -> + or([a_PartitionOccurrence_WhichPart[q8] = q7 /\ a_PartitionOccurrence_FirstIndex[q7] = q8 | q8 : int(1..2)]) + | q7 : int(1..2)]), + and([q7 > a_PartitionOccurrence_NumParts -> a_PartitionOccurrence_FirstIndex[q7] = 1 | q7 : int(1..2)]), + and([q9 <= a_PartitionOccurrence_NumParts /\ q10 <= a_PartitionOccurrence_NumParts -> + (q9 < q10 <-> a_PartitionOccurrence_FirstIndex[q9] < a_PartitionOccurrence_FirstIndex[q10]) + | q9 : int(1..2), q10 : int(1..2)]), + and([q11 <= b_PartitionOccurrence_NumParts -> b_PartitionOccurrence_PartSizes[q11] <= 2 | q11 : int(1..2)]), + and([q11 > b_PartitionOccurrence_NumParts -> b_PartitionOccurrence_PartSizes[q11] = 0 | q11 : int(1..2)]), + b_PartitionOccurrence_NumParts <= 2, + b_PartitionOccurrence_NumParts = max([b_PartitionOccurrence_WhichPart[q14] | q14 : int(1..2)]), + and([b_PartitionOccurrence_PartSizes[q15] = + sum([toInt(b_PartitionOccurrence_WhichPart[q16] = q15) | q16 : int(1..2)]) + | q15 : int(1..2)]), + and([q17 <= b_PartitionOccurrence_NumParts -> + and([b_PartitionOccurrence_WhichPart[q18] = q17 -> b_PartitionOccurrence_FirstIndex[q17] <= q18 + | q18 : int(1..2)]) + | q17 : int(1..2)]), + and([q17 <= b_PartitionOccurrence_NumParts -> + or([b_PartitionOccurrence_WhichPart[q18] = q17 /\ b_PartitionOccurrence_FirstIndex[q17] = q18 + | q18 : int(1..2)]) + | q17 : int(1..2)]), + and([q17 > b_PartitionOccurrence_NumParts -> b_PartitionOccurrence_FirstIndex[q17] = 1 | q17 : int(1..2)]), + and([q19 <= b_PartitionOccurrence_NumParts /\ q20 <= b_PartitionOccurrence_NumParts -> + (q19 < q20 <-> b_PartitionOccurrence_FirstIndex[q19] < b_PartitionOccurrence_FirstIndex[q20]) + | q19 : int(1..2), q20 : int(1..2)]) + diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000001.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000001.solution new file mode 100644 index 0000000000..9b50bb2ed2 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000001.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting a be relation() +letting b be relation((2, true)) +$ Visualisation for b +$ 2 T + diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000002.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000002.solution new file mode 100644 index 0000000000..e05e181325 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000002.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting a be relation() +letting b be relation((2, false)) +$ Visualisation for b +$ 2 _ + diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000003.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000003.solution new file mode 100644 index 0000000000..a14764841f --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000003.solution @@ -0,0 +1,8 @@ +language Essence 1.3 + +letting a be relation() +letting b be relation((2, false), (2, true)) +$ Visualisation for b +$ 2 _ +$ 2 T + diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000004.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000004.solution new file mode 100644 index 0000000000..2d2025d4dc --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000004.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting a be relation() +letting b be relation((1, true)) +$ Visualisation for b +$ 1 T + diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000005.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000005.solution new file mode 100644 index 0000000000..9e94a7fc99 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000005.solution @@ -0,0 +1,8 @@ +language Essence 1.3 + +letting a be relation() +letting b be relation((1, true), (2, true)) +$ Visualisation for b +$ 1 T +$ 2 T + diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000006.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000006.solution new file mode 100644 index 0000000000..a23fdb9592 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000006.solution @@ -0,0 +1,8 @@ +language Essence 1.3 + +letting a be relation() +letting b be relation((1, true), (2, false)) +$ Visualisation for b +$ 1 T +$ 2 _ + diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000007.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000007.solution new file mode 100644 index 0000000000..c6e284fe39 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000007.solution @@ -0,0 +1,9 @@ +language Essence 1.3 + +letting a be relation() +letting b be relation((1, true), (2, false), (2, true)) +$ Visualisation for b +$ 1 T +$ 2 _ +$ 2 T + diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000008.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000008.solution new file mode 100644 index 0000000000..b9ac1ab260 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000008.solution @@ -0,0 +1,7 @@ +language Essence 1.3 + +letting a be relation() +letting b be relation((1, false)) +$ Visualisation for b +$ 1 _ + diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000009.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000009.solution new file mode 100644 index 0000000000..4c3b9b516b --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000009.solution @@ -0,0 +1,8 @@ +language Essence 1.3 + +letting a be relation() +letting b be relation((1, false), (2, true)) +$ Visualisation for b +$ 1 _ +$ 2 T + diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000010.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000010.solution new file mode 100644 index 0000000000..390eb51d64 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000010.solution @@ -0,0 +1,8 @@ +language Essence 1.3 + +letting a be relation() +letting b be relation((1, false), (2, false)) +$ Visualisation for b +$ 1 _ +$ 2 _ + diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000011.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000011.solution new file mode 100644 index 0000000000..5f6b5bb3eb --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000011.solution @@ -0,0 +1,9 @@ +language Essence 1.3 + +letting a be relation() +letting b be relation((1, false), (2, false), (2, true)) +$ Visualisation for b +$ 1 _ +$ 2 _ +$ 2 T + diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000012.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000012.solution new file mode 100644 index 0000000000..96b3f7a61d --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000012.solution @@ -0,0 +1,8 @@ +language Essence 1.3 + +letting a be relation() +letting b be relation((1, false), (1, true)) +$ Visualisation for b +$ 1 _ +$ 1 T + diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000013.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000013.solution new file mode 100644 index 0000000000..7c1b31979c --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000013.solution @@ -0,0 +1,9 @@ +language Essence 1.3 + +letting a be relation() +letting b be relation((1, false), (1, true), (2, true)) +$ Visualisation for b +$ 1 _ +$ 1 T +$ 2 T + diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000014.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000014.solution new file mode 100644 index 0000000000..df3bcc7d19 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000014.solution @@ -0,0 +1,9 @@ +language Essence 1.3 + +letting a be relation() +letting b be relation((1, false), (1, true), (2, false)) +$ Visualisation for b +$ 1 _ +$ 1 T +$ 2 _ + diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000015.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000015.solution new file mode 100644 index 0000000000..57c4c4d4cc --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000015.solution @@ -0,0 +1,10 @@ +language Essence 1.3 + +letting a be relation() +letting b be relation((1, false), (1, true), (2, false), (2, true)) +$ Visualisation for b +$ 1 _ +$ 1 T +$ 2 _ +$ 2 T + diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000016.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000016.solution new file mode 100644 index 0000000000..d6c83fac87 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000016.solution @@ -0,0 +1,10 @@ +language Essence 1.3 + +letting a be relation((2, true)) +$ Visualisation for a +$ 2 T + +letting b be relation((2, false)) +$ Visualisation for b +$ 2 _ + diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000017.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000017.solution new file mode 100644 index 0000000000..2e03b77f68 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000017.solution @@ -0,0 +1,11 @@ +language Essence 1.3 + +letting a be relation((2, true)) +$ Visualisation for a +$ 2 T + +letting b be relation((2, false), (2, true)) +$ Visualisation for b +$ 2 _ +$ 2 T + diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000018.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000018.solution new file mode 100644 index 0000000000..5a8a614393 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000018.solution @@ -0,0 +1,10 @@ +language Essence 1.3 + +letting a be relation((2, true)) +$ Visualisation for a +$ 2 T + +letting b be relation((1, true)) +$ Visualisation for b +$ 1 T + diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000019.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000019.solution new file mode 100644 index 0000000000..827334e801 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000019.solution @@ -0,0 +1,11 @@ +language Essence 1.3 + +letting a be relation((2, true)) +$ Visualisation for a +$ 2 T + +letting b be relation((1, true), (2, true)) +$ Visualisation for b +$ 1 T +$ 2 T + diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000020.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000020.solution new file mode 100644 index 0000000000..ff0da926b6 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000020.solution @@ -0,0 +1,11 @@ +language Essence 1.3 + +letting a be relation((2, true)) +$ Visualisation for a +$ 2 T + +letting b be relation((1, true), (2, false)) +$ Visualisation for b +$ 1 T +$ 2 _ + diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000021.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000021.solution new file mode 100644 index 0000000000..6e71bd9351 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000021.solution @@ -0,0 +1,12 @@ +language Essence 1.3 + +letting a be relation((2, true)) +$ Visualisation for a +$ 2 T + +letting b be relation((1, true), (2, false), (2, true)) +$ Visualisation for b +$ 1 T +$ 2 _ +$ 2 T + diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000022.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000022.solution new file mode 100644 index 0000000000..632f76f414 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000022.solution @@ -0,0 +1,10 @@ +language Essence 1.3 + +letting a be relation((2, true)) +$ Visualisation for a +$ 2 T + +letting b be relation((1, false)) +$ Visualisation for b +$ 1 _ + diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000023.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000023.solution new file mode 100644 index 0000000000..59e96b0a9d --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000023.solution @@ -0,0 +1,11 @@ +language Essence 1.3 + +letting a be relation((2, true)) +$ Visualisation for a +$ 2 T + +letting b be relation((1, false), (2, true)) +$ Visualisation for b +$ 1 _ +$ 2 T + diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000024.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000024.solution new file mode 100644 index 0000000000..cb604edb99 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000024.solution @@ -0,0 +1,11 @@ +language Essence 1.3 + +letting a be relation((2, true)) +$ Visualisation for a +$ 2 T + +letting b be relation((1, false), (2, false)) +$ Visualisation for b +$ 1 _ +$ 2 _ + diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000025.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000025.solution new file mode 100644 index 0000000000..b5fdc4c3d5 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000025.solution @@ -0,0 +1,12 @@ +language Essence 1.3 + +letting a be relation((2, true)) +$ Visualisation for a +$ 2 T + +letting b be relation((1, false), (2, false), (2, true)) +$ Visualisation for b +$ 1 _ +$ 2 _ +$ 2 T + diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000026.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000026.solution new file mode 100644 index 0000000000..73274c8b53 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000026.solution @@ -0,0 +1,11 @@ +language Essence 1.3 + +letting a be relation((2, true)) +$ Visualisation for a +$ 2 T + +letting b be relation((1, false), (1, true)) +$ Visualisation for b +$ 1 _ +$ 1 T + diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000027.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000027.solution new file mode 100644 index 0000000000..740843554e --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000027.solution @@ -0,0 +1,12 @@ +language Essence 1.3 + +letting a be relation((2, true)) +$ Visualisation for a +$ 2 T + +letting b be relation((1, false), (1, true), (2, true)) +$ Visualisation for b +$ 1 _ +$ 1 T +$ 2 T + diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000028.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000028.solution new file mode 100644 index 0000000000..29f3289516 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000028.solution @@ -0,0 +1,12 @@ +language Essence 1.3 + +letting a be relation((2, true)) +$ Visualisation for a +$ 2 T + +letting b be relation((1, false), (1, true), (2, false)) +$ Visualisation for b +$ 1 _ +$ 1 T +$ 2 _ + diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000029.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000029.solution new file mode 100644 index 0000000000..fdeebbf013 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000029.solution @@ -0,0 +1,13 @@ +language Essence 1.3 + +letting a be relation((2, true)) +$ Visualisation for a +$ 2 T + +letting b be relation((1, false), (1, true), (2, false), (2, true)) +$ Visualisation for b +$ 1 _ +$ 1 T +$ 2 _ +$ 2 T + diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000030.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000030.solution new file mode 100644 index 0000000000..eaccbb5373 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000030.solution @@ -0,0 +1,11 @@ +language Essence 1.3 + +letting a be relation((2, false)) +$ Visualisation for a +$ 2 _ + +letting b be relation((2, false), (2, true)) +$ Visualisation for b +$ 2 _ +$ 2 T + diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000031.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000031.solution new file mode 100644 index 0000000000..3eaa95be98 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000031.solution @@ -0,0 +1,10 @@ +language Essence 1.3 + +letting a be relation((2, false)) +$ Visualisation for a +$ 2 _ + +letting b be relation((1, true)) +$ Visualisation for b +$ 1 T + diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000032.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000032.solution new file mode 100644 index 0000000000..d5abbfe57c --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000032.solution @@ -0,0 +1,11 @@ +language Essence 1.3 + +letting a be relation((2, false)) +$ Visualisation for a +$ 2 _ + +letting b be relation((1, true), (2, true)) +$ Visualisation for b +$ 1 T +$ 2 T + diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000033.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000033.solution new file mode 100644 index 0000000000..d9f72172e5 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000033.solution @@ -0,0 +1,11 @@ +language Essence 1.3 + +letting a be relation((2, false)) +$ Visualisation for a +$ 2 _ + +letting b be relation((1, true), (2, false)) +$ Visualisation for b +$ 1 T +$ 2 _ + diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000034.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000034.solution new file mode 100644 index 0000000000..57c910c0e2 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000034.solution @@ -0,0 +1,12 @@ +language Essence 1.3 + +letting a be relation((2, false)) +$ Visualisation for a +$ 2 _ + +letting b be relation((1, true), (2, false), (2, true)) +$ Visualisation for b +$ 1 T +$ 2 _ +$ 2 T + diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000035.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000035.solution new file mode 100644 index 0000000000..24b2054619 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000035.solution @@ -0,0 +1,10 @@ +language Essence 1.3 + +letting a be relation((2, false)) +$ Visualisation for a +$ 2 _ + +letting b be relation((1, false)) +$ Visualisation for b +$ 1 _ + diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000036.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000036.solution new file mode 100644 index 0000000000..bef7f6af5e --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000036.solution @@ -0,0 +1,11 @@ +language Essence 1.3 + +letting a be relation((2, false)) +$ Visualisation for a +$ 2 _ + +letting b be relation((1, false), (2, true)) +$ Visualisation for b +$ 1 _ +$ 2 T + diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000037.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000037.solution new file mode 100644 index 0000000000..03d588c94a --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000037.solution @@ -0,0 +1,11 @@ +language Essence 1.3 + +letting a be relation((2, false)) +$ Visualisation for a +$ 2 _ + +letting b be relation((1, false), (2, false)) +$ Visualisation for b +$ 1 _ +$ 2 _ + diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000038.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000038.solution new file mode 100644 index 0000000000..0cee2c9e7b --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000038.solution @@ -0,0 +1,12 @@ +language Essence 1.3 + +letting a be relation((2, false)) +$ Visualisation for a +$ 2 _ + +letting b be relation((1, false), (2, false), (2, true)) +$ Visualisation for b +$ 1 _ +$ 2 _ +$ 2 T + diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000039.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000039.solution new file mode 100644 index 0000000000..886c2f905b --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000039.solution @@ -0,0 +1,11 @@ +language Essence 1.3 + +letting a be relation((2, false)) +$ Visualisation for a +$ 2 _ + +letting b be relation((1, false), (1, true)) +$ Visualisation for b +$ 1 _ +$ 1 T + diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000040.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000040.solution new file mode 100644 index 0000000000..769d0184ce --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000040.solution @@ -0,0 +1,12 @@ +language Essence 1.3 + +letting a be relation((2, false)) +$ Visualisation for a +$ 2 _ + +letting b be relation((1, false), (1, true), (2, true)) +$ Visualisation for b +$ 1 _ +$ 1 T +$ 2 T + diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000041.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000041.solution new file mode 100644 index 0000000000..5f5262aec4 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000041.solution @@ -0,0 +1,12 @@ +language Essence 1.3 + +letting a be relation((2, false)) +$ Visualisation for a +$ 2 _ + +letting b be relation((1, false), (1, true), (2, false)) +$ Visualisation for b +$ 1 _ +$ 1 T +$ 2 _ + diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000042.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000042.solution new file mode 100644 index 0000000000..11990b806d --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000042.solution @@ -0,0 +1,13 @@ +language Essence 1.3 + +letting a be relation((2, false)) +$ Visualisation for a +$ 2 _ + +letting b be relation((1, false), (1, true), (2, false), (2, true)) +$ Visualisation for b +$ 1 _ +$ 1 T +$ 2 _ +$ 2 T + diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000043.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000043.solution new file mode 100644 index 0000000000..aacbe14a36 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000043.solution @@ -0,0 +1,11 @@ +language Essence 1.3 + +letting a be relation((2, false), (2, true)) +$ Visualisation for a +$ 2 _ +$ 2 T + +letting b be relation((1, true)) +$ Visualisation for b +$ 1 T + diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000044.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000044.solution new file mode 100644 index 0000000000..b15348099a --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000044.solution @@ -0,0 +1,12 @@ +language Essence 1.3 + +letting a be relation((2, false), (2, true)) +$ Visualisation for a +$ 2 _ +$ 2 T + +letting b be relation((1, true), (2, true)) +$ Visualisation for b +$ 1 T +$ 2 T + diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000045.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000045.solution new file mode 100644 index 0000000000..3b8561efe4 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000045.solution @@ -0,0 +1,12 @@ +language Essence 1.3 + +letting a be relation((2, false), (2, true)) +$ Visualisation for a +$ 2 _ +$ 2 T + +letting b be relation((1, true), (2, false)) +$ Visualisation for b +$ 1 T +$ 2 _ + diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000046.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000046.solution new file mode 100644 index 0000000000..c8c72a43bf --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000046.solution @@ -0,0 +1,13 @@ +language Essence 1.3 + +letting a be relation((2, false), (2, true)) +$ Visualisation for a +$ 2 _ +$ 2 T + +letting b be relation((1, true), (2, false), (2, true)) +$ Visualisation for b +$ 1 T +$ 2 _ +$ 2 T + diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000047.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000047.solution new file mode 100644 index 0000000000..1e024d6569 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000047.solution @@ -0,0 +1,11 @@ +language Essence 1.3 + +letting a be relation((2, false), (2, true)) +$ Visualisation for a +$ 2 _ +$ 2 T + +letting b be relation((1, false)) +$ Visualisation for b +$ 1 _ + diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000048.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000048.solution new file mode 100644 index 0000000000..689794b9e5 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000048.solution @@ -0,0 +1,12 @@ +language Essence 1.3 + +letting a be relation((2, false), (2, true)) +$ Visualisation for a +$ 2 _ +$ 2 T + +letting b be relation((1, false), (2, true)) +$ Visualisation for b +$ 1 _ +$ 2 T + diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000049.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000049.solution new file mode 100644 index 0000000000..d53edacbed --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000049.solution @@ -0,0 +1,12 @@ +language Essence 1.3 + +letting a be relation((2, false), (2, true)) +$ Visualisation for a +$ 2 _ +$ 2 T + +letting b be relation((1, false), (2, false)) +$ Visualisation for b +$ 1 _ +$ 2 _ + diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000050.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000050.solution new file mode 100644 index 0000000000..2ffb1e0713 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000050.solution @@ -0,0 +1,13 @@ +language Essence 1.3 + +letting a be relation((2, false), (2, true)) +$ Visualisation for a +$ 2 _ +$ 2 T + +letting b be relation((1, false), (2, false), (2, true)) +$ Visualisation for b +$ 1 _ +$ 2 _ +$ 2 T + diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000051.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000051.solution new file mode 100644 index 0000000000..45ae15ca2f --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000051.solution @@ -0,0 +1,12 @@ +language Essence 1.3 + +letting a be relation((2, false), (2, true)) +$ Visualisation for a +$ 2 _ +$ 2 T + +letting b be relation((1, false), (1, true)) +$ Visualisation for b +$ 1 _ +$ 1 T + diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000052.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000052.solution new file mode 100644 index 0000000000..e34aca5265 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000052.solution @@ -0,0 +1,13 @@ +language Essence 1.3 + +letting a be relation((2, false), (2, true)) +$ Visualisation for a +$ 2 _ +$ 2 T + +letting b be relation((1, false), (1, true), (2, true)) +$ Visualisation for b +$ 1 _ +$ 1 T +$ 2 T + diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000053.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000053.solution new file mode 100644 index 0000000000..0650195dfa --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000053.solution @@ -0,0 +1,13 @@ +language Essence 1.3 + +letting a be relation((2, false), (2, true)) +$ Visualisation for a +$ 2 _ +$ 2 T + +letting b be relation((1, false), (1, true), (2, false)) +$ Visualisation for b +$ 1 _ +$ 1 T +$ 2 _ + diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000054.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000054.solution new file mode 100644 index 0000000000..d005ee72f3 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000054.solution @@ -0,0 +1,14 @@ +language Essence 1.3 + +letting a be relation((2, false), (2, true)) +$ Visualisation for a +$ 2 _ +$ 2 T + +letting b be relation((1, false), (1, true), (2, false), (2, true)) +$ Visualisation for b +$ 1 _ +$ 1 T +$ 2 _ +$ 2 T + diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000055.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000055.solution new file mode 100644 index 0000000000..b97e565a71 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000055.solution @@ -0,0 +1,11 @@ +language Essence 1.3 + +letting a be relation((1, true)) +$ Visualisation for a +$ 1 T + +letting b be relation((1, true), (2, true)) +$ Visualisation for b +$ 1 T +$ 2 T + diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000056.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000056.solution new file mode 100644 index 0000000000..1c2c273c2b --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000056.solution @@ -0,0 +1,11 @@ +language Essence 1.3 + +letting a be relation((1, true)) +$ Visualisation for a +$ 1 T + +letting b be relation((1, true), (2, false)) +$ Visualisation for b +$ 1 T +$ 2 _ + diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000057.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000057.solution new file mode 100644 index 0000000000..d22929e033 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000057.solution @@ -0,0 +1,12 @@ +language Essence 1.3 + +letting a be relation((1, true)) +$ Visualisation for a +$ 1 T + +letting b be relation((1, true), (2, false), (2, true)) +$ Visualisation for b +$ 1 T +$ 2 _ +$ 2 T + diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000058.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000058.solution new file mode 100644 index 0000000000..131f4ca60d --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000058.solution @@ -0,0 +1,10 @@ +language Essence 1.3 + +letting a be relation((1, true)) +$ Visualisation for a +$ 1 T + +letting b be relation((1, false)) +$ Visualisation for b +$ 1 _ + diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000059.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000059.solution new file mode 100644 index 0000000000..cdc3c8c342 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000059.solution @@ -0,0 +1,11 @@ +language Essence 1.3 + +letting a be relation((1, true)) +$ Visualisation for a +$ 1 T + +letting b be relation((1, false), (2, true)) +$ Visualisation for b +$ 1 _ +$ 2 T + diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000060.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000060.solution new file mode 100644 index 0000000000..e96d5802a8 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000060.solution @@ -0,0 +1,11 @@ +language Essence 1.3 + +letting a be relation((1, true)) +$ Visualisation for a +$ 1 T + +letting b be relation((1, false), (2, false)) +$ Visualisation for b +$ 1 _ +$ 2 _ + diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000061.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000061.solution new file mode 100644 index 0000000000..bef89da48c --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000061.solution @@ -0,0 +1,12 @@ +language Essence 1.3 + +letting a be relation((1, true)) +$ Visualisation for a +$ 1 T + +letting b be relation((1, false), (2, false), (2, true)) +$ Visualisation for b +$ 1 _ +$ 2 _ +$ 2 T + diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000062.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000062.solution new file mode 100644 index 0000000000..ea0c4dbf09 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000062.solution @@ -0,0 +1,11 @@ +language Essence 1.3 + +letting a be relation((1, true)) +$ Visualisation for a +$ 1 T + +letting b be relation((1, false), (1, true)) +$ Visualisation for b +$ 1 _ +$ 1 T + diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000063.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000063.solution new file mode 100644 index 0000000000..ffe8162de3 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000063.solution @@ -0,0 +1,12 @@ +language Essence 1.3 + +letting a be relation((1, true)) +$ Visualisation for a +$ 1 T + +letting b be relation((1, false), (1, true), (2, true)) +$ Visualisation for b +$ 1 _ +$ 1 T +$ 2 T + diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000064.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000064.solution new file mode 100644 index 0000000000..40a475eb0a --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000064.solution @@ -0,0 +1,12 @@ +language Essence 1.3 + +letting a be relation((1, true)) +$ Visualisation for a +$ 1 T + +letting b be relation((1, false), (1, true), (2, false)) +$ Visualisation for b +$ 1 _ +$ 1 T +$ 2 _ + diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000065.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000065.solution new file mode 100644 index 0000000000..bb4a540328 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000065.solution @@ -0,0 +1,13 @@ +language Essence 1.3 + +letting a be relation((1, true)) +$ Visualisation for a +$ 1 T + +letting b be relation((1, false), (1, true), (2, false), (2, true)) +$ Visualisation for b +$ 1 _ +$ 1 T +$ 2 _ +$ 2 T + diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000066.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000066.solution new file mode 100644 index 0000000000..a6d6d0a1d9 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000066.solution @@ -0,0 +1,12 @@ +language Essence 1.3 + +letting a be relation((1, true), (2, true)) +$ Visualisation for a +$ 1 T +$ 2 T + +letting b be relation((1, true), (2, false)) +$ Visualisation for b +$ 1 T +$ 2 _ + diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000067.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000067.solution new file mode 100644 index 0000000000..30730a76db --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000067.solution @@ -0,0 +1,13 @@ +language Essence 1.3 + +letting a be relation((1, true), (2, true)) +$ Visualisation for a +$ 1 T +$ 2 T + +letting b be relation((1, true), (2, false), (2, true)) +$ Visualisation for b +$ 1 T +$ 2 _ +$ 2 T + diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000068.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000068.solution new file mode 100644 index 0000000000..2bda2ef994 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000068.solution @@ -0,0 +1,11 @@ +language Essence 1.3 + +letting a be relation((1, true), (2, true)) +$ Visualisation for a +$ 1 T +$ 2 T + +letting b be relation((1, false)) +$ Visualisation for b +$ 1 _ + diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000069.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000069.solution new file mode 100644 index 0000000000..edaea295f4 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000069.solution @@ -0,0 +1,12 @@ +language Essence 1.3 + +letting a be relation((1, true), (2, true)) +$ Visualisation for a +$ 1 T +$ 2 T + +letting b be relation((1, false), (2, true)) +$ Visualisation for b +$ 1 _ +$ 2 T + diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000070.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000070.solution new file mode 100644 index 0000000000..e7e730d42e --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000070.solution @@ -0,0 +1,12 @@ +language Essence 1.3 + +letting a be relation((1, true), (2, true)) +$ Visualisation for a +$ 1 T +$ 2 T + +letting b be relation((1, false), (2, false)) +$ Visualisation for b +$ 1 _ +$ 2 _ + diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000071.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000071.solution new file mode 100644 index 0000000000..d35c2856a3 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000071.solution @@ -0,0 +1,13 @@ +language Essence 1.3 + +letting a be relation((1, true), (2, true)) +$ Visualisation for a +$ 1 T +$ 2 T + +letting b be relation((1, false), (2, false), (2, true)) +$ Visualisation for b +$ 1 _ +$ 2 _ +$ 2 T + diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000072.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000072.solution new file mode 100644 index 0000000000..2cafa9ec51 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000072.solution @@ -0,0 +1,12 @@ +language Essence 1.3 + +letting a be relation((1, true), (2, true)) +$ Visualisation for a +$ 1 T +$ 2 T + +letting b be relation((1, false), (1, true)) +$ Visualisation for b +$ 1 _ +$ 1 T + diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000073.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000073.solution new file mode 100644 index 0000000000..c6c6295627 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000073.solution @@ -0,0 +1,13 @@ +language Essence 1.3 + +letting a be relation((1, true), (2, true)) +$ Visualisation for a +$ 1 T +$ 2 T + +letting b be relation((1, false), (1, true), (2, true)) +$ Visualisation for b +$ 1 _ +$ 1 T +$ 2 T + diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000074.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000074.solution new file mode 100644 index 0000000000..15d97d4729 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000074.solution @@ -0,0 +1,13 @@ +language Essence 1.3 + +letting a be relation((1, true), (2, true)) +$ Visualisation for a +$ 1 T +$ 2 T + +letting b be relation((1, false), (1, true), (2, false)) +$ Visualisation for b +$ 1 _ +$ 1 T +$ 2 _ + diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000075.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000075.solution new file mode 100644 index 0000000000..0697674c24 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000075.solution @@ -0,0 +1,14 @@ +language Essence 1.3 + +letting a be relation((1, true), (2, true)) +$ Visualisation for a +$ 1 T +$ 2 T + +letting b be relation((1, false), (1, true), (2, false), (2, true)) +$ Visualisation for b +$ 1 _ +$ 1 T +$ 2 _ +$ 2 T + diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000076.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000076.solution new file mode 100644 index 0000000000..296759f9b3 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000076.solution @@ -0,0 +1,13 @@ +language Essence 1.3 + +letting a be relation((1, true), (2, false)) +$ Visualisation for a +$ 1 T +$ 2 _ + +letting b be relation((1, true), (2, false), (2, true)) +$ Visualisation for b +$ 1 T +$ 2 _ +$ 2 T + diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000077.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000077.solution new file mode 100644 index 0000000000..4ea598db58 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000077.solution @@ -0,0 +1,11 @@ +language Essence 1.3 + +letting a be relation((1, true), (2, false)) +$ Visualisation for a +$ 1 T +$ 2 _ + +letting b be relation((1, false)) +$ Visualisation for b +$ 1 _ + diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000078.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000078.solution new file mode 100644 index 0000000000..0537b5fb9e --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000078.solution @@ -0,0 +1,12 @@ +language Essence 1.3 + +letting a be relation((1, true), (2, false)) +$ Visualisation for a +$ 1 T +$ 2 _ + +letting b be relation((1, false), (2, true)) +$ Visualisation for b +$ 1 _ +$ 2 T + diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000079.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000079.solution new file mode 100644 index 0000000000..cb0d5e93ae --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000079.solution @@ -0,0 +1,12 @@ +language Essence 1.3 + +letting a be relation((1, true), (2, false)) +$ Visualisation for a +$ 1 T +$ 2 _ + +letting b be relation((1, false), (2, false)) +$ Visualisation for b +$ 1 _ +$ 2 _ + diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000080.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000080.solution new file mode 100644 index 0000000000..71bf1f4226 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000080.solution @@ -0,0 +1,13 @@ +language Essence 1.3 + +letting a be relation((1, true), (2, false)) +$ Visualisation for a +$ 1 T +$ 2 _ + +letting b be relation((1, false), (2, false), (2, true)) +$ Visualisation for b +$ 1 _ +$ 2 _ +$ 2 T + diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000081.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000081.solution new file mode 100644 index 0000000000..4a56054133 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000081.solution @@ -0,0 +1,12 @@ +language Essence 1.3 + +letting a be relation((1, true), (2, false)) +$ Visualisation for a +$ 1 T +$ 2 _ + +letting b be relation((1, false), (1, true)) +$ Visualisation for b +$ 1 _ +$ 1 T + diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000082.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000082.solution new file mode 100644 index 0000000000..0afa181179 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000082.solution @@ -0,0 +1,13 @@ +language Essence 1.3 + +letting a be relation((1, true), (2, false)) +$ Visualisation for a +$ 1 T +$ 2 _ + +letting b be relation((1, false), (1, true), (2, true)) +$ Visualisation for b +$ 1 _ +$ 1 T +$ 2 T + diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000083.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000083.solution new file mode 100644 index 0000000000..a556323487 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000083.solution @@ -0,0 +1,13 @@ +language Essence 1.3 + +letting a be relation((1, true), (2, false)) +$ Visualisation for a +$ 1 T +$ 2 _ + +letting b be relation((1, false), (1, true), (2, false)) +$ Visualisation for b +$ 1 _ +$ 1 T +$ 2 _ + diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000084.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000084.solution new file mode 100644 index 0000000000..847e586971 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000084.solution @@ -0,0 +1,14 @@ +language Essence 1.3 + +letting a be relation((1, true), (2, false)) +$ Visualisation for a +$ 1 T +$ 2 _ + +letting b be relation((1, false), (1, true), (2, false), (2, true)) +$ Visualisation for b +$ 1 _ +$ 1 T +$ 2 _ +$ 2 T + diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000085.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000085.solution new file mode 100644 index 0000000000..8b71d47ea9 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000085.solution @@ -0,0 +1,12 @@ +language Essence 1.3 + +letting a be relation((1, true), (2, false), (2, true)) +$ Visualisation for a +$ 1 T +$ 2 _ +$ 2 T + +letting b be relation((1, false)) +$ Visualisation for b +$ 1 _ + diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000086.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000086.solution new file mode 100644 index 0000000000..918b7b8edd --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000086.solution @@ -0,0 +1,13 @@ +language Essence 1.3 + +letting a be relation((1, true), (2, false), (2, true)) +$ Visualisation for a +$ 1 T +$ 2 _ +$ 2 T + +letting b be relation((1, false), (2, true)) +$ Visualisation for b +$ 1 _ +$ 2 T + diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000087.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000087.solution new file mode 100644 index 0000000000..ca6ddd39f8 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000087.solution @@ -0,0 +1,13 @@ +language Essence 1.3 + +letting a be relation((1, true), (2, false), (2, true)) +$ Visualisation for a +$ 1 T +$ 2 _ +$ 2 T + +letting b be relation((1, false), (2, false)) +$ Visualisation for b +$ 1 _ +$ 2 _ + diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000088.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000088.solution new file mode 100644 index 0000000000..dca6353d9f --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000088.solution @@ -0,0 +1,14 @@ +language Essence 1.3 + +letting a be relation((1, true), (2, false), (2, true)) +$ Visualisation for a +$ 1 T +$ 2 _ +$ 2 T + +letting b be relation((1, false), (2, false), (2, true)) +$ Visualisation for b +$ 1 _ +$ 2 _ +$ 2 T + diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000089.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000089.solution new file mode 100644 index 0000000000..984e3636be --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000089.solution @@ -0,0 +1,13 @@ +language Essence 1.3 + +letting a be relation((1, true), (2, false), (2, true)) +$ Visualisation for a +$ 1 T +$ 2 _ +$ 2 T + +letting b be relation((1, false), (1, true)) +$ Visualisation for b +$ 1 _ +$ 1 T + diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000090.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000090.solution new file mode 100644 index 0000000000..5b5350f84d --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000090.solution @@ -0,0 +1,14 @@ +language Essence 1.3 + +letting a be relation((1, true), (2, false), (2, true)) +$ Visualisation for a +$ 1 T +$ 2 _ +$ 2 T + +letting b be relation((1, false), (1, true), (2, true)) +$ Visualisation for b +$ 1 _ +$ 1 T +$ 2 T + diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000091.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000091.solution new file mode 100644 index 0000000000..8c4f2ec1d5 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000091.solution @@ -0,0 +1,14 @@ +language Essence 1.3 + +letting a be relation((1, true), (2, false), (2, true)) +$ Visualisation for a +$ 1 T +$ 2 _ +$ 2 T + +letting b be relation((1, false), (1, true), (2, false)) +$ Visualisation for b +$ 1 _ +$ 1 T +$ 2 _ + diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000092.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000092.solution new file mode 100644 index 0000000000..3d9f447820 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000092.solution @@ -0,0 +1,15 @@ +language Essence 1.3 + +letting a be relation((1, true), (2, false), (2, true)) +$ Visualisation for a +$ 1 T +$ 2 _ +$ 2 T + +letting b be relation((1, false), (1, true), (2, false), (2, true)) +$ Visualisation for b +$ 1 _ +$ 1 T +$ 2 _ +$ 2 T + diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000093.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000093.solution new file mode 100644 index 0000000000..20ba97a49b --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000093.solution @@ -0,0 +1,11 @@ +language Essence 1.3 + +letting a be relation((1, false)) +$ Visualisation for a +$ 1 _ + +letting b be relation((1, false), (2, true)) +$ Visualisation for b +$ 1 _ +$ 2 T + diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000094.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000094.solution new file mode 100644 index 0000000000..a6299cb56e --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000094.solution @@ -0,0 +1,11 @@ +language Essence 1.3 + +letting a be relation((1, false)) +$ Visualisation for a +$ 1 _ + +letting b be relation((1, false), (2, false)) +$ Visualisation for b +$ 1 _ +$ 2 _ + diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000095.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000095.solution new file mode 100644 index 0000000000..68ef4a2d32 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000095.solution @@ -0,0 +1,12 @@ +language Essence 1.3 + +letting a be relation((1, false)) +$ Visualisation for a +$ 1 _ + +letting b be relation((1, false), (2, false), (2, true)) +$ Visualisation for b +$ 1 _ +$ 2 _ +$ 2 T + diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000096.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000096.solution new file mode 100644 index 0000000000..9191690a29 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000096.solution @@ -0,0 +1,11 @@ +language Essence 1.3 + +letting a be relation((1, false)) +$ Visualisation for a +$ 1 _ + +letting b be relation((1, false), (1, true)) +$ Visualisation for b +$ 1 _ +$ 1 T + diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000097.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000097.solution new file mode 100644 index 0000000000..be125318a4 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000097.solution @@ -0,0 +1,12 @@ +language Essence 1.3 + +letting a be relation((1, false)) +$ Visualisation for a +$ 1 _ + +letting b be relation((1, false), (1, true), (2, true)) +$ Visualisation for b +$ 1 _ +$ 1 T +$ 2 T + diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000098.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000098.solution new file mode 100644 index 0000000000..3ee2e652e1 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000098.solution @@ -0,0 +1,12 @@ +language Essence 1.3 + +letting a be relation((1, false)) +$ Visualisation for a +$ 1 _ + +letting b be relation((1, false), (1, true), (2, false)) +$ Visualisation for b +$ 1 _ +$ 1 T +$ 2 _ + diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000099.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000099.solution new file mode 100644 index 0000000000..100fb99ae9 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000099.solution @@ -0,0 +1,13 @@ +language Essence 1.3 + +letting a be relation((1, false)) +$ Visualisation for a +$ 1 _ + +letting b be relation((1, false), (1, true), (2, false), (2, true)) +$ Visualisation for b +$ 1 _ +$ 1 T +$ 2 _ +$ 2 T + diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000100.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000100.solution new file mode 100644 index 0000000000..fe1c124d6b --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000100.solution @@ -0,0 +1,12 @@ +language Essence 1.3 + +letting a be relation((1, false), (2, true)) +$ Visualisation for a +$ 1 _ +$ 2 T + +letting b be relation((1, false), (2, false)) +$ Visualisation for b +$ 1 _ +$ 2 _ + diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000101.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000101.solution new file mode 100644 index 0000000000..45605841d1 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000101.solution @@ -0,0 +1,13 @@ +language Essence 1.3 + +letting a be relation((1, false), (2, true)) +$ Visualisation for a +$ 1 _ +$ 2 T + +letting b be relation((1, false), (2, false), (2, true)) +$ Visualisation for b +$ 1 _ +$ 2 _ +$ 2 T + diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000102.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000102.solution new file mode 100644 index 0000000000..5b09524f76 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000102.solution @@ -0,0 +1,12 @@ +language Essence 1.3 + +letting a be relation((1, false), (2, true)) +$ Visualisation for a +$ 1 _ +$ 2 T + +letting b be relation((1, false), (1, true)) +$ Visualisation for b +$ 1 _ +$ 1 T + diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000103.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000103.solution new file mode 100644 index 0000000000..289bf90bb7 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000103.solution @@ -0,0 +1,13 @@ +language Essence 1.3 + +letting a be relation((1, false), (2, true)) +$ Visualisation for a +$ 1 _ +$ 2 T + +letting b be relation((1, false), (1, true), (2, true)) +$ Visualisation for b +$ 1 _ +$ 1 T +$ 2 T + diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000104.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000104.solution new file mode 100644 index 0000000000..acdc5ef598 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000104.solution @@ -0,0 +1,13 @@ +language Essence 1.3 + +letting a be relation((1, false), (2, true)) +$ Visualisation for a +$ 1 _ +$ 2 T + +letting b be relation((1, false), (1, true), (2, false)) +$ Visualisation for b +$ 1 _ +$ 1 T +$ 2 _ + diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000105.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000105.solution new file mode 100644 index 0000000000..c38106e519 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000105.solution @@ -0,0 +1,14 @@ +language Essence 1.3 + +letting a be relation((1, false), (2, true)) +$ Visualisation for a +$ 1 _ +$ 2 T + +letting b be relation((1, false), (1, true), (2, false), (2, true)) +$ Visualisation for b +$ 1 _ +$ 1 T +$ 2 _ +$ 2 T + diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000106.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000106.solution new file mode 100644 index 0000000000..4a64f01e99 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000106.solution @@ -0,0 +1,13 @@ +language Essence 1.3 + +letting a be relation((1, false), (2, false)) +$ Visualisation for a +$ 1 _ +$ 2 _ + +letting b be relation((1, false), (2, false), (2, true)) +$ Visualisation for b +$ 1 _ +$ 2 _ +$ 2 T + diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000107.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000107.solution new file mode 100644 index 0000000000..9ec48a3bc7 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000107.solution @@ -0,0 +1,12 @@ +language Essence 1.3 + +letting a be relation((1, false), (2, false)) +$ Visualisation for a +$ 1 _ +$ 2 _ + +letting b be relation((1, false), (1, true)) +$ Visualisation for b +$ 1 _ +$ 1 T + diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000108.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000108.solution new file mode 100644 index 0000000000..8531b893a9 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000108.solution @@ -0,0 +1,13 @@ +language Essence 1.3 + +letting a be relation((1, false), (2, false)) +$ Visualisation for a +$ 1 _ +$ 2 _ + +letting b be relation((1, false), (1, true), (2, true)) +$ Visualisation for b +$ 1 _ +$ 1 T +$ 2 T + diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000109.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000109.solution new file mode 100644 index 0000000000..e41a986c0c --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000109.solution @@ -0,0 +1,13 @@ +language Essence 1.3 + +letting a be relation((1, false), (2, false)) +$ Visualisation for a +$ 1 _ +$ 2 _ + +letting b be relation((1, false), (1, true), (2, false)) +$ Visualisation for b +$ 1 _ +$ 1 T +$ 2 _ + diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000110.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000110.solution new file mode 100644 index 0000000000..f39c9292d8 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000110.solution @@ -0,0 +1,14 @@ +language Essence 1.3 + +letting a be relation((1, false), (2, false)) +$ Visualisation for a +$ 1 _ +$ 2 _ + +letting b be relation((1, false), (1, true), (2, false), (2, true)) +$ Visualisation for b +$ 1 _ +$ 1 T +$ 2 _ +$ 2 T + diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000111.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000111.solution new file mode 100644 index 0000000000..0801593375 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000111.solution @@ -0,0 +1,13 @@ +language Essence 1.3 + +letting a be relation((1, false), (2, false), (2, true)) +$ Visualisation for a +$ 1 _ +$ 2 _ +$ 2 T + +letting b be relation((1, false), (1, true)) +$ Visualisation for b +$ 1 _ +$ 1 T + diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000112.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000112.solution new file mode 100644 index 0000000000..8604ea0029 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000112.solution @@ -0,0 +1,14 @@ +language Essence 1.3 + +letting a be relation((1, false), (2, false), (2, true)) +$ Visualisation for a +$ 1 _ +$ 2 _ +$ 2 T + +letting b be relation((1, false), (1, true), (2, true)) +$ Visualisation for b +$ 1 _ +$ 1 T +$ 2 T + diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000113.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000113.solution new file mode 100644 index 0000000000..13ec11e78c --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000113.solution @@ -0,0 +1,14 @@ +language Essence 1.3 + +letting a be relation((1, false), (2, false), (2, true)) +$ Visualisation for a +$ 1 _ +$ 2 _ +$ 2 T + +letting b be relation((1, false), (1, true), (2, false)) +$ Visualisation for b +$ 1 _ +$ 1 T +$ 2 _ + diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000114.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000114.solution new file mode 100644 index 0000000000..5df1f52cfb --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000114.solution @@ -0,0 +1,15 @@ +language Essence 1.3 + +letting a be relation((1, false), (2, false), (2, true)) +$ Visualisation for a +$ 1 _ +$ 2 _ +$ 2 T + +letting b be relation((1, false), (1, true), (2, false), (2, true)) +$ Visualisation for b +$ 1 _ +$ 1 T +$ 2 _ +$ 2 T + diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000115.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000115.solution new file mode 100644 index 0000000000..08d44b1cbc --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000115.solution @@ -0,0 +1,13 @@ +language Essence 1.3 + +letting a be relation((1, false), (1, true)) +$ Visualisation for a +$ 1 _ +$ 1 T + +letting b be relation((1, false), (1, true), (2, true)) +$ Visualisation for b +$ 1 _ +$ 1 T +$ 2 T + diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000116.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000116.solution new file mode 100644 index 0000000000..61c43b3425 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000116.solution @@ -0,0 +1,13 @@ +language Essence 1.3 + +letting a be relation((1, false), (1, true)) +$ Visualisation for a +$ 1 _ +$ 1 T + +letting b be relation((1, false), (1, true), (2, false)) +$ Visualisation for b +$ 1 _ +$ 1 T +$ 2 _ + diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000117.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000117.solution new file mode 100644 index 0000000000..53b30afee2 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000117.solution @@ -0,0 +1,14 @@ +language Essence 1.3 + +letting a be relation((1, false), (1, true)) +$ Visualisation for a +$ 1 _ +$ 1 T + +letting b be relation((1, false), (1, true), (2, false), (2, true)) +$ Visualisation for b +$ 1 _ +$ 1 T +$ 2 _ +$ 2 T + diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000118.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000118.solution new file mode 100644 index 0000000000..f9f326b9b0 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000118.solution @@ -0,0 +1,14 @@ +language Essence 1.3 + +letting a be relation((1, false), (1, true), (2, true)) +$ Visualisation for a +$ 1 _ +$ 1 T +$ 2 T + +letting b be relation((1, false), (1, true), (2, false)) +$ Visualisation for b +$ 1 _ +$ 1 T +$ 2 _ + diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000119.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000119.solution new file mode 100644 index 0000000000..1bbce78897 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000119.solution @@ -0,0 +1,15 @@ +language Essence 1.3 + +letting a be relation((1, false), (1, true), (2, true)) +$ Visualisation for a +$ 1 _ +$ 1 T +$ 2 T + +letting b be relation((1, false), (1, true), (2, false), (2, true)) +$ Visualisation for b +$ 1 _ +$ 1 T +$ 2 _ +$ 2 T + diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000120.solution b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000120.solution new file mode 100644 index 0000000000..0e39505c9e --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model-solution000120.solution @@ -0,0 +1,15 @@ +language Essence 1.3 + +letting a be relation((1, false), (1, true), (2, false)) +$ Visualisation for a +$ 1 _ +$ 1 T +$ 2 _ + +letting b be relation((1, false), (1, true), (2, false), (2, true)) +$ Visualisation for b +$ 1 _ +$ 1 T +$ 2 _ +$ 2 T + diff --git a/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model.eprime b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model.eprime new file mode 100644 index 0000000000..02a8b92b47 --- /dev/null +++ b/tests/exhaustive/tildeOrd/tildeOrd_relation_01/expected/model.eprime @@ -0,0 +1,62 @@ +language ESSENCE' 1.0 + +find a_RelationAsMatrix: matrix indexed by [int(1..2), bool] of bool +find b_RelationAsMatrix: matrix indexed by [int(1..2), bool] of bool +branching on [a_RelationAsMatrix, b_RelationAsMatrix] +such that + or([a_RelationAsMatrix[q7_1, q7_2] /\ + (sum([toInt(a_RelationAsMatrix[q23_1, q23_2]) * catchUndef(toInt(q23_1 = q7_1 /\ q23_2 = q7_2), 0) + | q23_1 : int(1..2), q23_2 : bool]) + < + sum([toInt(b_RelationAsMatrix[q9_1, q9_2]) * catchUndef(toInt(q9_1 = q7_1 /\ q9_2 = q7_2), 0) + | q9_1 : int(1..2), q9_2 : bool]) + /\ + (and([a_RelationAsMatrix[q10_1, q10_2] -> + sum([toInt(a_RelationAsMatrix[q21_1, q21_2]) * catchUndef(toInt(q21_1 = q10_1 /\ q21_2 = q10_2), 0) + | q21_1 : int(1..2), q21_2 : bool]) + = + sum([toInt(b_RelationAsMatrix[q12_1, q12_2]) * catchUndef(toInt(q12_1 = q10_1 /\ q12_2 = q10_2), 0) + | q12_1 : int(1..2), q12_2 : bool]) + | q10_1 : int(1..2), q10_2 : bool, q10_1 < q7_1 \/ q10_1 = q7_1 /\ q10_2 < q7_2]) + /\ + and([b_RelationAsMatrix[q13_1, q13_2] /\ + !or([a_RelationAsMatrix[q17_1, q17_2] /\ (q17_1 = q13_1 /\ q17_2 = q13_2) + | q17_1 : int(1..2), q17_2 : bool]) + -> + sum([toInt(a_RelationAsMatrix[q19_1, q19_2]) * catchUndef(toInt(q19_1 = q13_1 /\ q19_2 = q13_2), 0) + | q19_1 : int(1..2), q19_2 : bool]) + = + sum([toInt(b_RelationAsMatrix[q15_1, q15_2]) * catchUndef(toInt(q15_1 = q13_1 /\ q15_2 = q13_2), 0) + | q15_1 : int(1..2), q15_2 : bool]) + | q13_1 : int(1..2), q13_2 : bool, q13_1 < q7_1 \/ q13_1 = q7_1 /\ q13_2 < q7_2]))) + | q7_1 : int(1..2), q7_2 : bool]) + \/ + or([b_RelationAsMatrix[q24_1, q24_2] /\ + !or([a_RelationAsMatrix[q42_1, q42_2] /\ (q42_1 = q24_1 /\ q42_2 = q24_2) | q42_1 : int(1..2), q42_2 : bool]) + /\ + (sum([toInt(a_RelationAsMatrix[q40_1, q40_2]) * catchUndef(toInt(q40_1 = q24_1 /\ q40_2 = q24_2), 0) + | q40_1 : int(1..2), q40_2 : bool]) + < + sum([toInt(b_RelationAsMatrix[q26_1, q26_2]) * catchUndef(toInt(q26_1 = q24_1 /\ q26_2 = q24_2), 0) + | q26_1 : int(1..2), q26_2 : bool]) + /\ + (and([a_RelationAsMatrix[q27_1, q27_2] -> + sum([toInt(a_RelationAsMatrix[q38_1, q38_2]) * catchUndef(toInt(q38_1 = q27_1 /\ q38_2 = q27_2), 0) + | q38_1 : int(1..2), q38_2 : bool]) + = + sum([toInt(b_RelationAsMatrix[q29_1, q29_2]) * catchUndef(toInt(q29_1 = q27_1 /\ q29_2 = q27_2), 0) + | q29_1 : int(1..2), q29_2 : bool]) + | q27_1 : int(1..2), q27_2 : bool, q27_1 < q24_1 \/ q27_1 = q24_1 /\ q27_2 < q24_2]) + /\ + and([b_RelationAsMatrix[q30_1, q30_2] /\ + !or([a_RelationAsMatrix[q34_1, q34_2] /\ (q34_1 = q30_1 /\ q34_2 = q30_2) + | q34_1 : int(1..2), q34_2 : bool]) + -> + sum([toInt(a_RelationAsMatrix[q36_1, q36_2]) * catchUndef(toInt(q36_1 = q30_1 /\ q36_2 = q30_2), 0) + | q36_1 : int(1..2), q36_2 : bool]) + = + sum([toInt(b_RelationAsMatrix[q32_1, q32_2]) * catchUndef(toInt(q32_1 = q30_1 /\ q32_2 = q30_2), 0) + | q32_1 : int(1..2), q32_2 : bool]) + | q30_1 : int(1..2), q30_2 : bool, q30_1 < q24_1 \/ q30_1 = q24_1 /\ q30_2 < q24_2]))) + | q24_1 : int(1..2), q24_2 : bool]) + diff --git a/tests/parse_print/autogen-bilals-fixed/00f3f6e00d6aaa0c44f7a7bfaeabf301/model.expected.json b/tests/parse_print/autogen-bilals-fixed/00f3f6e00d6aaa0c44f7a7bfaeabf301/model.expected.json index 3b8e1c73f5..f2bd73bf78 100644 --- a/tests/parse_print/autogen-bilals-fixed/00f3f6e00d6aaa0c44f7a7bfaeabf301/model.expected.json +++ b/tests/parse_print/autogen-bilals-fixed/00f3f6e00d6aaa0c44f7a7bfaeabf301/model.expected.json @@ -1167,7 +1167,7 @@ []}, 2]}}]}]]}, [{"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpFlatten": [null, @@ -1349,7 +1349,7 @@ []}, 2]}}]}]]}]}}]]}}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpFlatten": [null, @@ -1606,7 +1606,7 @@ [{"TagInt": []}, 2]}}]}]]}, [{"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": @@ -1719,7 +1719,7 @@ []}, 2]}}}}]}}]}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": diff --git a/tests/parse_print/autogen-bilals-fixed/00f3f6e00d6aaa0c44f7a7bfaeabf301/stdout.expected b/tests/parse_print/autogen-bilals-fixed/00f3f6e00d6aaa0c44f7a7bfaeabf301/stdout.expected index 11ec8f266d..e0529f8cab 100644 --- a/tests/parse_print/autogen-bilals-fixed/00f3f6e00d6aaa0c44f7a7bfaeabf301/stdout.expected +++ b/tests/parse_print/autogen-bilals-fixed/00f3f6e00d6aaa0c44f7a7bfaeabf301/stdout.expected @@ -71,7 +71,7 @@ such that /\ (flatten(var1_PartitionAsSet_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMarker_Values_Function1DPartial_Flags [q5, .., ..]) - var1_PartitionAsSet_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMarker_Values_Function1DPartial_Flags [q7, 1, ..] - var2_PartitionAsSet_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMarker_Values_Function1DPartial_Flags [q1, q2, ..] - var3_PartitionAsSet_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMarker_Values_Function1DPartial_Flags [q1, q2, ..] - matrix indexed by [int] of int`), mset(false)) diff --git a/tests/parse_print/autogen-bilals-fixed/075527221a657e78d6f1c0a6a335371f/model.expected.json b/tests/parse_print/autogen-bilals-fixed/075527221a657e78d6f1c0a6a335371f/model.expected.json index e9f7882e98..7f04593f9d 100644 --- a/tests/parse_print/autogen-bilals-fixed/075527221a657e78d6f1c0a6a335371f/model.expected.json +++ b/tests/parse_print/autogen-bilals-fixed/075527221a657e78d6f1c0a6a335371f/model.expected.json @@ -82,7 +82,7 @@ {"ConstantInt": [{"TagInt": []}, 2]}}]}]]}, [{"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": diff --git a/tests/parse_print/autogen-bilals-fixed/075527221a657e78d6f1c0a6a335371f/stdout.expected b/tests/parse_print/autogen-bilals-fixed/075527221a657e78d6f1c0a6a335371f/stdout.expected index e7f3cdfab4..f75f7437eb 100644 --- a/tests/parse_print/autogen-bilals-fixed/075527221a657e78d6f1c0a6a335371f/stdout.expected +++ b/tests/parse_print/autogen-bilals-fixed/075527221a657e78d6f1c0a6a335371f/stdout.expected @@ -6,7 +6,7 @@ find var1_FunctionAsRelation_RelationAsSet_ExplicitVarSizeWithMarker_Values_1_Oc find var1_FunctionAsRelation_RelationAsSet_ExplicitVarSizeWithMarker_Values_2: matrix indexed by [int(1..3)] of bool such that and([q1 + 1 <= var1_FunctionAsRelation_RelationAsSet_ExplicitVarSizeWithMarker_Marker -> - var1_FunctionAsRelation_RelationAsSet_ExplicitVarSizeWithMarker_Values_1_Occurrence[q1, ..] diff --git a/tests/parse_print/autogen-bilals-fixed/084959e428c16c5485c7775b20480e40/model.expected.json b/tests/parse_print/autogen-bilals-fixed/084959e428c16c5485c7775b20480e40/model.expected.json index 42fa4725c1..0e8958c797 100644 --- a/tests/parse_print/autogen-bilals-fixed/084959e428c16c5485c7775b20480e40/model.expected.json +++ b/tests/parse_print/autogen-bilals-fixed/084959e428c16c5485c7775b20480e40/model.expected.json @@ -124,7 +124,7 @@ {"Reference": [{"Name": "var1_ExplicitVarSizeWithMarker_Marker"}, null]}]}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": @@ -849,7 +849,7 @@ {"ConstantInt": [{"TagInt": []}, 2]}}]}]]}, [{"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpFlatten": [null, @@ -1022,7 +1022,7 @@ []}, 5]}}]}]]}]}}]]}}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpFlatten": [null, diff --git a/tests/parse_print/autogen-bilals-fixed/084959e428c16c5485c7775b20480e40/stdout.expected b/tests/parse_print/autogen-bilals-fixed/084959e428c16c5485c7775b20480e40/stdout.expected index d33df27036..fff55f0ca1 100644 --- a/tests/parse_print/autogen-bilals-fixed/084959e428c16c5485c7775b20480e40/stdout.expected +++ b/tests/parse_print/autogen-bilals-fixed/084959e428c16c5485c7775b20480e40/stdout.expected @@ -10,7 +10,7 @@ find var2_PartitionAsSet_ExplicitVarSizeWithMarker_Values_Explicit_ExplicitVarSi such that false, and([q1 + 1 <= var1_ExplicitVarSizeWithMarker_Marker -> - var1_ExplicitVarSizeWithMarker_Values_Function1D[q1, ..] var1_ExplicitVarSizeWithMarker_Marker -> @@ -54,7 +54,7 @@ such that and([q10 + 1 <= var2_PartitionAsSet_ExplicitVarSizeWithMarker_Marker -> flatten(var2_PartitionAsSet_ExplicitVarSizeWithMarker_Values_Explicit_ExplicitVarSizeWithFlags_Flags [q10, .., ..]) - - q_4_ExplicitVarSizeWithMarker_Values_Function1DPartial_Flags[q1, ..] q_4_ExplicitVarSizeWithMarker_Marker -> @@ -53,7 +53,7 @@ such that var1_PartitionAsSet_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMarker_Marker[q3] = var1_PartitionAsSet_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMarker_Marker[q3 + 1] /\ - var1_PartitionAsSet_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMarker_Values[q3, ..] var1_PartitionAsSet_ExplicitVarSizeWithMarker_Marker -> @@ -73,14 +73,14 @@ such that | q4 : int(1..3)]) | q3 : int(1..8)]), and([var2_ExplicitVarSizeWithFlags_Flags[q5 + 1] -> - var2_ExplicitVarSizeWithFlags_Values_Function1DPartial_Flags[q5, ..] diff --git a/tests/parse_print/autogen-bilals-fixed/0896777a9c9ec7a2944d17b0f832af27/model.expected.json b/tests/parse_print/autogen-bilals-fixed/0896777a9c9ec7a2944d17b0f832af27/model.expected.json index 6711c93083..92e0454dac 100644 --- a/tests/parse_print/autogen-bilals-fixed/0896777a9c9ec7a2944d17b0f832af27/model.expected.json +++ b/tests/parse_print/autogen-bilals-fixed/0896777a9c9ec7a2944d17b0f832af27/model.expected.json @@ -1361,7 +1361,7 @@ []}, 2]}}]}]]}, [{"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpFlatten": [null, @@ -1560,7 +1560,7 @@ []}, 16]}}]}]]}]}}]]}}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpFlatten": [null, @@ -1888,7 +1888,7 @@ []}, 2]}}]}]]}, [{"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": @@ -2063,7 +2063,7 @@ []}, 2]}}}]]}]}}]]}}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": @@ -2534,7 +2534,7 @@ {"Reference": [{"Name": "var6_PartitionAsSet_ExplicitVarSizeWithMarker_Marker"}, null]}]}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": diff --git a/tests/parse_print/autogen-bilals-fixed/0896777a9c9ec7a2944d17b0f832af27/stdout.expected b/tests/parse_print/autogen-bilals-fixed/0896777a9c9ec7a2944d17b0f832af27/stdout.expected index dfbe7aac8f..ec29df0b41 100644 --- a/tests/parse_print/autogen-bilals-fixed/0896777a9c9ec7a2944d17b0f832af27/stdout.expected +++ b/tests/parse_print/autogen-bilals-fixed/0896777a9c9ec7a2944d17b0f832af27/stdout.expected @@ -84,7 +84,7 @@ such that /\ (flatten(var4_PartitionAsSet_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMarker_Values_Function1DPartial_Flags [q8, .., ..]) - var4_PartitionAsSet_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMarker_Values_Function1DPartial_Flags [q10, q11, ..] - = 1 | q31 : int(1..2)]), 2 <= var6_PartitionAsSet_ExplicitVarSizeWithMarker_Marker -> - var6_PartitionAsSet_ExplicitVarSizeWithMarker_Values_Occurrence[1, ..] var6_PartitionAsSet_ExplicitVarSizeWithMarker_Marker -> var6_PartitionAsSet_ExplicitVarSizeWithMarker_Values_Occurrence[q22, 2] = false diff --git a/tests/parse_print/autogen-bilals-fixed/09ac2051b1e1a54e1b7a3b051b78bcd3/model.expected.json b/tests/parse_print/autogen-bilals-fixed/09ac2051b1e1a54e1b7a3b051b78bcd3/model.expected.json index 685665ce7f..cc055bcb21 100644 --- a/tests/parse_print/autogen-bilals-fixed/09ac2051b1e1a54e1b7a3b051b78bcd3/model.expected.json +++ b/tests/parse_print/autogen-bilals-fixed/09ac2051b1e1a54e1b7a3b051b78bcd3/model.expected.json @@ -22,7 +22,7 @@ {"Constant": {"ConstantBool": false}}]]}}, {"Op": {"MkOpToInt": {"Reference": [{"Name": "var1"}, null]}}}]}}, {"Op": - {"MkOpLexLeq": + {"MkOpDotLeq": [{"Constant": {"ConstantAbstract": {"AbsLitMatrix": diff --git a/tests/parse_print/autogen-bilals-fixed/09ac2051b1e1a54e1b7a3b051b78bcd3/stdout.expected b/tests/parse_print/autogen-bilals-fixed/09ac2051b1e1a54e1b7a3b051b78bcd3/stdout.expected index 69797ff12e..c17f44bf91 100644 --- a/tests/parse_print/autogen-bilals-fixed/09ac2051b1e1a54e1b7a3b051b78bcd3/stdout.expected +++ b/tests/parse_print/autogen-bilals-fixed/09ac2051b1e1a54e1b7a3b051b78bcd3/stdout.expected @@ -3,4 +3,4 @@ language Essence 1.3 find var1: bool such that [var1, var1, true, var1, false; int(10, 2..5)][toInt(var1)], - [false, false, true; int(1..3)] <=lex [var1, var1, false; int(9, 7, 5)] + [false, false, true; int(1..3)] .<= [var1, var1, false; int(9, 7, 5)] diff --git a/tests/parse_print/autogen-bilals-fixed/0a4c5d1f2a6f82e1a72b0732362906b6/model.expected.json b/tests/parse_print/autogen-bilals-fixed/0a4c5d1f2a6f82e1a72b0732362906b6/model.expected.json index 0af4102cbe..0708a5f68e 100644 --- a/tests/parse_print/autogen-bilals-fixed/0a4c5d1f2a6f82e1a72b0732362906b6/model.expected.json +++ b/tests/parse_print/autogen-bilals-fixed/0a4c5d1f2a6f82e1a72b0732362906b6/model.expected.json @@ -659,7 +659,7 @@ {"ConstantInt": [{"TagInt": []}, 2]}}]}]]}, [{"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpFlatten": [null, @@ -832,7 +832,7 @@ []}, 5]}}]}]]}]}}]]}}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpFlatten": [null, diff --git a/tests/parse_print/autogen-bilals-fixed/0a4c5d1f2a6f82e1a72b0732362906b6/stdout.expected b/tests/parse_print/autogen-bilals-fixed/0a4c5d1f2a6f82e1a72b0732362906b6/stdout.expected index 801d252cd0..187620bd7f 100644 --- a/tests/parse_print/autogen-bilals-fixed/0a4c5d1f2a6f82e1a72b0732362906b6/stdout.expected +++ b/tests/parse_print/autogen-bilals-fixed/0a4c5d1f2a6f82e1a72b0732362906b6/stdout.expected @@ -40,7 +40,7 @@ such that and([q4 + 1 <= var2_PartitionAsSet_ExplicitVarSizeWithMarker_Marker -> flatten(var2_PartitionAsSet_ExplicitVarSizeWithMarker_Values_Explicit_ExplicitVarSizeWithFlags_Flags [q4, .., ..]) - @@ -29,10 +29,10 @@ such that | q23 : int(1..2)]) | q21 : int(1..2)]) /\ - (var1_RelationAsSet_Explicit_2_ExplicitVarSizeWithFlags_Flags[1, ..] var1_RelationAsSet_Explicit_1_ExplicitVarSizeWithFlags_Values[q2, 1] < diff --git a/tests/parse_print/autogen-bilals-fixed/0d757bbc1bf600cc00cccc23dd0dbabb/model.expected.json b/tests/parse_print/autogen-bilals-fixed/0d757bbc1bf600cc00cccc23dd0dbabb/model.expected.json index 3994f27611..0ddcbedffa 100644 --- a/tests/parse_print/autogen-bilals-fixed/0d757bbc1bf600cc00cccc23dd0dbabb/model.expected.json +++ b/tests/parse_print/autogen-bilals-fixed/0d757bbc1bf600cc00cccc23dd0dbabb/model.expected.json @@ -125,7 +125,7 @@ []}, 2]}}]}]]}, [{"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": @@ -177,7 +177,7 @@ null, null]}}]}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": @@ -229,7 +229,7 @@ null, null]}}]}}]]}}}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpFlatten": [null, diff --git a/tests/parse_print/autogen-bilals-fixed/0d757bbc1bf600cc00cccc23dd0dbabb/stdout.expected b/tests/parse_print/autogen-bilals-fixed/0d757bbc1bf600cc00cccc23dd0dbabb/stdout.expected index 534630128c..897e768def 100644 --- a/tests/parse_print/autogen-bilals-fixed/0d757bbc1bf600cc00cccc23dd0dbabb/stdout.expected +++ b/tests/parse_print/autogen-bilals-fixed/0d757bbc1bf600cc00cccc23dd0dbabb/stdout.expected @@ -10,18 +10,18 @@ find var2_FunctionAsRelation_RelationAsSet_ExplicitVarSizeWithMarker_Values_2_Re such that and([q1 + 1 <= var2_FunctionAsRelation_RelationAsSet_ExplicitVarSizeWithMarker_Marker -> var2_FunctionAsRelation_RelationAsSet_ExplicitVarSizeWithMarker_Values_1_ExplicitVarSizeWithFlags_Flags[q1, ..] - var1_FunctionAsRelation_RelationAsSet_ExplicitVarSizeWithMarker_Values_1_ExplicitVarSizeWithFlags_Flags[q1, ..] - var2_1_PartitionAsSet_ExplicitVarSizeWithMarker_Marker -> diff --git a/tests/parse_print/autogen-bilals-fixed/10c99281fb90ea99297131629d79951b/model.expected.json b/tests/parse_print/autogen-bilals-fixed/10c99281fb90ea99297131629d79951b/model.expected.json index 3ba84da3f5..0c32b3f55a 100644 --- a/tests/parse_print/autogen-bilals-fixed/10c99281fb90ea99297131629d79951b/model.expected.json +++ b/tests/parse_print/autogen-bilals-fixed/10c99281fb90ea99297131629d79951b/model.expected.json @@ -109,7 +109,7 @@ {"ConstantInt": [{"TagInt": []}, 2]}}]}]]}, [{"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpFlatten": [null, @@ -282,7 +282,7 @@ []}, 4]}}]}]]}]}}]]}}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpFlatten": [null, @@ -617,7 +617,7 @@ [{"TagInt": []}, 2]}}]}]]}, [{"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": @@ -768,7 +768,7 @@ []}, 1]}}]}}]}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpFlatten": [null, diff --git a/tests/parse_print/autogen-bilals-fixed/10c99281fb90ea99297131629d79951b/stdout.expected b/tests/parse_print/autogen-bilals-fixed/10c99281fb90ea99297131629d79951b/stdout.expected index bda2c30910..b63161e0db 100644 --- a/tests/parse_print/autogen-bilals-fixed/10c99281fb90ea99297131629d79951b/stdout.expected +++ b/tests/parse_print/autogen-bilals-fixed/10c99281fb90ea99297131629d79951b/stdout.expected @@ -7,8 +7,7 @@ find var1_ExplicitVarSizeWithFlags_Values_RelationAsSet_Explicit_1_RelationAsSet matrix indexed by [int(1..5), int(1..4), int(1), int(1..3)] of bool such that and([var1_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - flatten(var1_ExplicitVarSizeWithFlags_Values_RelationAsSet_Explicit_1_RelationAsSet_Explicit_1[q1, .., ..]) - - and([var1_ExplicitVarSizeWithFlags_Values_RelationAsSet_Explicit_1_RelationAsSet_Explicit_1[q5, q6, ..] var3_PartitionAsSet_ExplicitVarSizeWithMarker_Marker -> diff --git a/tests/parse_print/autogen-bilals-fixed/1191a8fe91feb6b1ae455420e223bf6e/model.expected.json b/tests/parse_print/autogen-bilals-fixed/1191a8fe91feb6b1ae455420e223bf6e/model.expected.json index ecb58f110b..000183606d 100644 --- a/tests/parse_print/autogen-bilals-fixed/1191a8fe91feb6b1ae455420e223bf6e/model.expected.json +++ b/tests/parse_print/autogen-bilals-fixed/1191a8fe91feb6b1ae455420e223bf6e/model.expected.json @@ -336,7 +336,7 @@ null]}, {"Constant": {"ConstantInt": [{"TagInt": []}, 1]}}]}}]}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": @@ -508,7 +508,7 @@ {"ConstantInt": [{"TagInt": []}, 2]}}]}]]}, [{"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": @@ -642,7 +642,7 @@ {"DomainBool": []}]}}]]}}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": @@ -1278,7 +1278,7 @@ []}, 1]}}]]}}}}]}}]}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": diff --git a/tests/parse_print/autogen-bilals-fixed/1191a8fe91feb6b1ae455420e223bf6e/stdout.expected b/tests/parse_print/autogen-bilals-fixed/1191a8fe91feb6b1ae455420e223bf6e/stdout.expected index 9e05388a52..addf1cc77f 100644 --- a/tests/parse_print/autogen-bilals-fixed/1191a8fe91feb6b1ae455420e223bf6e/stdout.expected +++ b/tests/parse_print/autogen-bilals-fixed/1191a8fe91feb6b1ae455420e223bf6e/stdout.expected @@ -28,7 +28,7 @@ such that var1_PartitionAsSet_ExplicitR5_ExplicitVarSizeWithMarker_Marker[1], var1_PartitionAsSet_ExplicitR5_ExplicitVarSizeWithMarker_Marker[1] >= 1, and([q8 + 1 <= var1_PartitionAsSet_ExplicitR5_ExplicitVarSizeWithMarker_Marker[1] -> - var1_PartitionAsSet_ExplicitR5_ExplicitVarSizeWithMarker_Values[1, q8, ..] var1_PartitionAsSet_ExplicitR5_ExplicitVarSizeWithMarker_Marker[1] -> @@ -36,14 +36,14 @@ such that | q9 : int(1..24)]), var1_PartitionAsSet_ExplicitR5_ExplicitVarSizeWithMarker_Marker[1] <= 24, and([q13 + 1 <= var2_ExplicitVarSizeWithMarkerR10_Marker -> - var2_ExplicitVarSizeWithMarkerR10_Values_Function1DPartial_Flags[q13, ..] var2_ExplicitVarSizeWithMarkerR10_Marker -> @@ -85,7 +85,7 @@ such that var4_1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q34] = var4_1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q34 + 1] /\ - var4_1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q34, ..] var4_1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> diff --git a/tests/parse_print/autogen-bilals-fixed/1291155001a2b89117838f7032c4ab5e/model.expected.json b/tests/parse_print/autogen-bilals-fixed/1291155001a2b89117838f7032c4ab5e/model.expected.json index 7d01e23c4f..c02f80949f 100644 --- a/tests/parse_print/autogen-bilals-fixed/1291155001a2b89117838f7032c4ab5e/model.expected.json +++ b/tests/parse_print/autogen-bilals-fixed/1291155001a2b89117838f7032c4ab5e/model.expected.json @@ -1201,7 +1201,7 @@ []}, 1]}}]]}}}}]}}]}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": @@ -1769,7 +1769,7 @@ {"ConstantInt": [{"TagInt": []}, 2]}}]}]]}, [{"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": @@ -1903,7 +1903,7 @@ {"DomainBool": []}]}}]]}}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": diff --git a/tests/parse_print/autogen-bilals-fixed/1291155001a2b89117838f7032c4ab5e/stdout.expected b/tests/parse_print/autogen-bilals-fixed/1291155001a2b89117838f7032c4ab5e/stdout.expected index e036979c02..ba08b39147 100644 --- a/tests/parse_print/autogen-bilals-fixed/1291155001a2b89117838f7032c4ab5e/stdout.expected +++ b/tests/parse_print/autogen-bilals-fixed/1291155001a2b89117838f7032c4ab5e/stdout.expected @@ -95,7 +95,7 @@ such that var2_1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q7] = var2_1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q7 + 1] /\ - var2_1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q7, ..] var2_1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> @@ -124,14 +124,14 @@ such that and([var4_1_ExplicitWithFlags_Flags[q17] = 0 \/ var4_1_ExplicitWithFlags_Flags[q17] >= 0 | q17 : int(1..3)]), 3 = sum([var4_1_ExplicitWithFlags_Flags[q18] | q18 : int(1..3)]), and([var5_ExplicitWithFlagsR10_Flags[q20 + 1] > 0 -> - var5_ExplicitWithFlagsR10_Values_Function1DPartial_Flags[q20, ..] diff --git a/tests/parse_print/autogen-bilals-fixed/13700d10e259531c00b3ea61a5a5222e/model.expected.json b/tests/parse_print/autogen-bilals-fixed/13700d10e259531c00b3ea61a5a5222e/model.expected.json index 92ce2a1904..8e9473edfb 100644 --- a/tests/parse_print/autogen-bilals-fixed/13700d10e259531c00b3ea61a5a5222e/model.expected.json +++ b/tests/parse_print/autogen-bilals-fixed/13700d10e259531c00b3ea61a5a5222e/model.expected.json @@ -245,7 +245,7 @@ {"ConstantInt": [{"TagInt": []}, 2]}}]}]]}, [{"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": @@ -1095,7 +1095,7 @@ []}, 1]}}]]}}}}]}}]}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": @@ -2010,7 +2010,7 @@ []}, 2]}}]}]]}, [{"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": @@ -2160,7 +2160,7 @@ []}, 4]}}]}]]}]}}]]}}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpFlatten": [null, @@ -2592,7 +2592,7 @@ []}, 1]}}]]}}}}]}}]}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": diff --git a/tests/parse_print/autogen-bilals-fixed/13700d10e259531c00b3ea61a5a5222e/stdout.expected b/tests/parse_print/autogen-bilals-fixed/13700d10e259531c00b3ea61a5a5222e/stdout.expected index 6e7ebca664..f5ade1fd55 100644 --- a/tests/parse_print/autogen-bilals-fixed/13700d10e259531c00b3ea61a5a5222e/stdout.expected +++ b/tests/parse_print/autogen-bilals-fixed/13700d10e259531c00b3ea61a5a5222e/stdout.expected @@ -25,7 +25,7 @@ find var5_PartitionAsSet_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMar find var6: int(-1..1) such that and([q1 + 1 <= var2_RelationAsSet_ExplicitVarSizeWithMarker_Marker -> - var2_RelationAsSet_ExplicitVarSizeWithMarker_Values_1_Occurrence[q1, ..] @@ -69,7 +69,7 @@ such that var4_2_PartitionAsSet_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMarker_Marker[q9] = var4_2_PartitionAsSet_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMarker_Marker[q9 + 1] /\ - var4_2_PartitionAsSet_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMarker_Values[q9, ..] var4_2_PartitionAsSet_ExplicitVarSizeWithMarker_Marker -> @@ -129,7 +129,7 @@ such that /\ (var5_PartitionAsSet_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMarker_Marker [q19, ..] - - var1_FunctionAsRelation_RelationAsSet_ExplicitVarSizeWithMarker_Values_1_Occurrence[q1, ..] @@ -19,7 +19,7 @@ such that var1_FunctionAsRelation_RelationAsSet_ExplicitVarSizeWithMarker_Values_1_Occurrence[q1, q19] | q19 : int(3..5, 0)]) /\ - var1_FunctionAsRelation_RelationAsSet_ExplicitVarSizeWithMarker_Values_2[q1, ..] var1_FunctionAsRelation_RelationAsSet_ExplicitVarSizeWithMarker_Marker -> diff --git a/tests/parse_print/autogen-bilals-fixed/13eda547bb0b8ccccb4b8cc348f66d91/model.expected.json b/tests/parse_print/autogen-bilals-fixed/13eda547bb0b8ccccb4b8cc348f66d91/model.expected.json index 69da04eb26..cb7c86d016 100644 --- a/tests/parse_print/autogen-bilals-fixed/13eda547bb0b8ccccb4b8cc348f66d91/model.expected.json +++ b/tests/parse_print/autogen-bilals-fixed/13eda547bb0b8ccccb4b8cc348f66d91/model.expected.json @@ -1050,7 +1050,7 @@ [{"Constant": {"ConstantAbstract": {"AbsLitMSet": []}}}, {"TypeMSet": {"TypeBool": []}}]}]}}]}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Comprehension": [{"Reference": [{"Name": "l_4"}, null]}, [{"Generator": {"GenDomainNoRepr": [{"Single": {"Name": "l_3"}}, {"DomainBool": []}]}}, diff --git a/tests/parse_print/autogen-bilals-fixed/13eda547bb0b8ccccb4b8cc348f66d91/stdout.expected b/tests/parse_print/autogen-bilals-fixed/13eda547bb0b8ccccb4b8cc348f66d91/stdout.expected index abfb46f0f3..01207ecd5e 100644 --- a/tests/parse_print/autogen-bilals-fixed/13eda547bb0b8ccccb4b8cc348f66d91/stdout.expected +++ b/tests/parse_print/autogen-bilals-fixed/13eda547bb0b8ccccb4b8cc348f66d91/stdout.expected @@ -80,4 +80,4 @@ such that (relation() : `relation of (tuple(int))`)}, [l_2 | l_1 : bool, l_2 : bool, true] [freq(mset(mset(true), (mset() : `mset of bool`), (mset() : `mset of bool`)), (mset() : `mset of bool`))], - [l_4 | l_3 : bool, l_4 : bool, l_4] - var1_FunctionAsRelation_RelationAsSet_ExplicitVarSizeWithMarker_Values_1_Function1DPartial_Flags[q1, ..] var5_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Marker[q10] < @@ -24,7 +24,7 @@ such that var5_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Marker[q10] = var5_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Marker[q10 + 1] /\ - var5_ExplicitVarSizeWithFlagsR5_Values_ExplicitVarSizeWithMarker_Values[q10, ..] diff --git a/tests/parse_print/autogen-bilals-fixed/176498a86f4f6aa56d13e84f835917e5/model.expected.json b/tests/parse_print/autogen-bilals-fixed/176498a86f4f6aa56d13e84f835917e5/model.expected.json index ada5d1446c..c0eecbdcca 100644 --- a/tests/parse_print/autogen-bilals-fixed/176498a86f4f6aa56d13e84f835917e5/model.expected.json +++ b/tests/parse_print/autogen-bilals-fixed/176498a86f4f6aa56d13e84f835917e5/model.expected.json @@ -238,7 +238,7 @@ []}, 1]}}]]}}}}]}}]}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": @@ -678,7 +678,7 @@ []}, 2]}}]}]]}]}}]]}}}]]}}}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": diff --git a/tests/parse_print/autogen-bilals-fixed/176498a86f4f6aa56d13e84f835917e5/stdout.expected b/tests/parse_print/autogen-bilals-fixed/176498a86f4f6aa56d13e84f835917e5/stdout.expected index bd3995eeac..39b1c7a6db 100644 --- a/tests/parse_print/autogen-bilals-fixed/176498a86f4f6aa56d13e84f835917e5/stdout.expected +++ b/tests/parse_print/autogen-bilals-fixed/176498a86f4f6aa56d13e84f835917e5/stdout.expected @@ -20,7 +20,7 @@ such that /\ var1_FunctionAsRelation_RelationAsSet_ExplicitVarSizeWithMarker_Values_1_ExplicitVarSizeWithMarker_Values [q1, ..] - var1_FunctionAsRelation_RelationAsSet_ExplicitVarSizeWithMarker_Marker -> diff --git a/tests/parse_print/autogen-bilals-fixed/183ea55a9258e18d69a7b15d4f823c67/model.expected.json b/tests/parse_print/autogen-bilals-fixed/183ea55a9258e18d69a7b15d4f823c67/model.expected.json index f987214317..f538545442 100644 --- a/tests/parse_print/autogen-bilals-fixed/183ea55a9258e18d69a7b15d4f823c67/model.expected.json +++ b/tests/parse_print/autogen-bilals-fixed/183ea55a9258e18d69a7b15d4f823c67/model.expected.json @@ -418,7 +418,7 @@ [{"TypeInt": {"TagInt": []}}, {"TypeFunction": [{"TypeInt": {"TagInt": []}}, {"TypeBool": []}]}]}}]}]}}, {"Op": - {"MkOpLexLeq": + {"MkOpDotLeq": [{"Op": {"MkOpImage": [{"Constant": diff --git a/tests/parse_print/autogen-bilals-fixed/183ea55a9258e18d69a7b15d4f823c67/stdout.expected b/tests/parse_print/autogen-bilals-fixed/183ea55a9258e18d69a7b15d4f823c67/stdout.expected index ea4fbaff95..03685881c5 100644 --- a/tests/parse_print/autogen-bilals-fixed/183ea55a9258e18d69a7b15d4f823c67/stdout.expected +++ b/tests/parse_print/autogen-bilals-fixed/183ea55a9258e18d69a7b15d4f823c67/stdout.expected @@ -56,7 +56,7 @@ such that mset(false, true) --> [0, 3, 1; int(4, 3, 6)], mset(true) --> [3; int(2)], mset(false, false, false) --> [5, 2, 0; int(1, 7..8)]), (mset() : `mset of bool`)) - <=lex + .<= image(function(relation((true, 2), (false, 2), (false, 3)) --> [3, 2, 2, 0, 4; int(11, 2, 5..7)], relation((true, 0), (false, 4)) --> [0; int(0)], relation((false, 0)) --> [3, 5, 3, 3; int(2, 7, 5, 0)], diff --git a/tests/parse_print/autogen-bilals-fixed/18bf9a38ee59e4bcaebd478b9f980662/model.expected.json b/tests/parse_print/autogen-bilals-fixed/18bf9a38ee59e4bcaebd478b9f980662/model.expected.json index b191c9d248..83dc283a4c 100644 --- a/tests/parse_print/autogen-bilals-fixed/18bf9a38ee59e4bcaebd478b9f980662/model.expected.json +++ b/tests/parse_print/autogen-bilals-fixed/18bf9a38ee59e4bcaebd478b9f980662/model.expected.json @@ -238,7 +238,7 @@ []}, 1]}}]]}}}}]}}]}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": @@ -678,7 +678,7 @@ []}, 2]}}]}]]}]}}]]}}}]]}}}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": diff --git a/tests/parse_print/autogen-bilals-fixed/18bf9a38ee59e4bcaebd478b9f980662/stdout.expected b/tests/parse_print/autogen-bilals-fixed/18bf9a38ee59e4bcaebd478b9f980662/stdout.expected index 4203d34567..22101efcf2 100644 --- a/tests/parse_print/autogen-bilals-fixed/18bf9a38ee59e4bcaebd478b9f980662/stdout.expected +++ b/tests/parse_print/autogen-bilals-fixed/18bf9a38ee59e4bcaebd478b9f980662/stdout.expected @@ -20,7 +20,7 @@ such that /\ var1_FunctionAsRelation_RelationAsSet_ExplicitVarSizeWithMarker_Values_1_ExplicitVarSizeWithMarker_Values [q1, ..] - var1_FunctionAsRelation_RelationAsSet_ExplicitVarSizeWithMarker_Marker -> diff --git a/tests/parse_print/autogen-bilals-fixed/1a4f723156644e60a38ec0e325765e17/model.expected.json b/tests/parse_print/autogen-bilals-fixed/1a4f723156644e60a38ec0e325765e17/model.expected.json index 050ed6c04a..1dd6e04c93 100644 --- a/tests/parse_print/autogen-bilals-fixed/1a4f723156644e60a38ec0e325765e17/model.expected.json +++ b/tests/parse_print/autogen-bilals-fixed/1a4f723156644e60a38ec0e325765e17/model.expected.json @@ -175,7 +175,7 @@ {"ConstantInt": [{"TagInt": []}, 4]}}}]]}]}}]]}}}, {"Constant": {"ConstantInt": [{"TagInt": []}, 3]}}]}}, {"Op": - {"MkOpLexLeq": + {"MkOpDotLeq": [{"Op": {"MkOpImage": [{"AbstractLiteral": diff --git a/tests/parse_print/autogen-bilals-fixed/1a4f723156644e60a38ec0e325765e17/stdout.expected b/tests/parse_print/autogen-bilals-fixed/1a4f723156644e60a38ec0e325765e17/stdout.expected index 3407e1c78e..88597481ca 100644 --- a/tests/parse_print/autogen-bilals-fixed/1a4f723156644e60a38ec0e325765e17/stdout.expected +++ b/tests/parse_print/autogen-bilals-fixed/1a4f723156644e60a38ec0e325765e17/stdout.expected @@ -17,7 +17,7 @@ such that image(function(mset(1, 4) --> [0, 1, 0; int(3, 5, 1)], (mset() : `mset of int`) --> [1, 4; int(5, 0)], mset(1, 5, 2) --> [4, 4, 2, 4, 1; int(8..10, 4, 14)]), toMSet({0, 1})) - <=lex [l_3 | l_2 : int(0..3, 5), l_3 : int(5, 4)], + .<= [l_3 | l_2 : int(0..3, 5), l_3 : int(5, 4)], true, or([l_4 | l_4 : bool, l_5 : bool, l_4]), mset(mset([2, 1, 3, 5, 4; int(0, 2..3, 15, 4)], [1, 1, 5, 1, 4; int(2..6)], [2, 3, 0, 3, 3; int(5, 3, 9, 14, 6)])) diff --git a/tests/parse_print/autogen-bilals-fixed/1abb07c9ef975b96bf575bfbe8f442b5/model.expected.json b/tests/parse_print/autogen-bilals-fixed/1abb07c9ef975b96bf575bfbe8f442b5/model.expected.json index d52041a5ef..391382dac9 100644 --- a/tests/parse_print/autogen-bilals-fixed/1abb07c9ef975b96bf575bfbe8f442b5/model.expected.json +++ b/tests/parse_print/autogen-bilals-fixed/1abb07c9ef975b96bf575bfbe8f442b5/model.expected.json @@ -218,7 +218,7 @@ "var3_PartitionAsSet_ExplicitVarSizeWithMarker_Marker"}, null]}]}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": diff --git a/tests/parse_print/autogen-bilals-fixed/1abb07c9ef975b96bf575bfbe8f442b5/stdout.expected b/tests/parse_print/autogen-bilals-fixed/1abb07c9ef975b96bf575bfbe8f442b5/stdout.expected index 0a704d4883..bd86021830 100644 --- a/tests/parse_print/autogen-bilals-fixed/1abb07c9ef975b96bf575bfbe8f442b5/stdout.expected +++ b/tests/parse_print/autogen-bilals-fixed/1abb07c9ef975b96bf575bfbe8f442b5/stdout.expected @@ -19,7 +19,7 @@ such that sum([var3_PartitionAsSet_ExplicitVarSizeWithMarker_Values_Occurrence[q19, q20] | q20 : int(2..4, 1)]) >= 1 | q19 : int(1..16)]), and([q9 + 1 <= var3_PartitionAsSet_ExplicitVarSizeWithMarker_Marker -> - var3_PartitionAsSet_ExplicitVarSizeWithMarker_Values_Occurrence[q9, ..] var3_PartitionAsSet_ExplicitVarSizeWithMarker_Marker -> diff --git a/tests/parse_print/autogen-bilals-fixed/1b6c1179b1a92bd88edaeed5c5bfb398/model.expected.json b/tests/parse_print/autogen-bilals-fixed/1b6c1179b1a92bd88edaeed5c5bfb398/model.expected.json index 9f8eab60a1..50f2d9698e 100644 --- a/tests/parse_print/autogen-bilals-fixed/1b6c1179b1a92bd88edaeed5c5bfb398/model.expected.json +++ b/tests/parse_print/autogen-bilals-fixed/1b6c1179b1a92bd88edaeed5c5bfb398/model.expected.json @@ -317,7 +317,7 @@ []}, 1]}}]]}}}}]}}]}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpFlatten": [null, diff --git a/tests/parse_print/autogen-bilals-fixed/1b6c1179b1a92bd88edaeed5c5bfb398/stdout.expected b/tests/parse_print/autogen-bilals-fixed/1b6c1179b1a92bd88edaeed5c5bfb398/stdout.expected index 57afdc3778..9695536f7f 100644 --- a/tests/parse_print/autogen-bilals-fixed/1b6c1179b1a92bd88edaeed5c5bfb398/stdout.expected +++ b/tests/parse_print/autogen-bilals-fixed/1b6c1179b1a92bd88edaeed5c5bfb398/stdout.expected @@ -28,7 +28,7 @@ such that /\ flatten(var2_PartitionAsSetR6_ExplicitVarSizeWithMarkerR5R6_Values_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy [q4, .., ..]) - = 1 | q53 : int(1..4)]), and([q7 + 1 <= var2_1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - var2_1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q7, ..] var2_1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> @@ -115,14 +115,14 @@ such that and([var4_1_ExplicitWithFlags_Flags[q18] = 0 \/ var4_1_ExplicitWithFlags_Flags[q18] >= 0 | q18 : int(1..3)]), 3 = sum([var4_1_ExplicitWithFlags_Flags[q19] | q19 : int(1..3)]), and([q21 + 1 <= var5_ExplicitWithRepetitionR10_Flag -> - var5_ExplicitWithRepetitionR10_Values_Function1DPartial_Flags[q21, ..] var5_ExplicitWithRepetitionR10_Flag -> diff --git a/tests/parse_print/autogen-bilals-fixed/1e3c2ea5eb1b0a1eb092e59c73e21e65/model.expected.json b/tests/parse_print/autogen-bilals-fixed/1e3c2ea5eb1b0a1eb092e59c73e21e65/model.expected.json index 0af0c6af6e..6d7ffeaea7 100644 --- a/tests/parse_print/autogen-bilals-fixed/1e3c2ea5eb1b0a1eb092e59c73e21e65/model.expected.json +++ b/tests/parse_print/autogen-bilals-fixed/1e3c2ea5eb1b0a1eb092e59c73e21e65/model.expected.json @@ -342,7 +342,7 @@ null]}, {"Constant": {"ConstantInt": [{"TagInt": []}, 1]}}]}}]}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": @@ -514,7 +514,7 @@ {"ConstantInt": [{"TagInt": []}, 2]}}]}]]}, [{"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": @@ -648,7 +648,7 @@ {"DomainBool": []}]}}]]}}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": diff --git a/tests/parse_print/autogen-bilals-fixed/1e3c2ea5eb1b0a1eb092e59c73e21e65/stdout.expected b/tests/parse_print/autogen-bilals-fixed/1e3c2ea5eb1b0a1eb092e59c73e21e65/stdout.expected index 2a191d4fef..b2bbbebb3d 100644 --- a/tests/parse_print/autogen-bilals-fixed/1e3c2ea5eb1b0a1eb092e59c73e21e65/stdout.expected +++ b/tests/parse_print/autogen-bilals-fixed/1e3c2ea5eb1b0a1eb092e59c73e21e65/stdout.expected @@ -27,7 +27,7 @@ such that var1_PartitionAsSet_ExplicitR5_ExplicitVarSizeWithMarker_Marker[1], var1_PartitionAsSet_ExplicitR5_ExplicitVarSizeWithMarker_Marker[1] >= 1, and([q8 + 1 <= var1_PartitionAsSet_ExplicitR5_ExplicitVarSizeWithMarker_Marker[1] -> - var1_PartitionAsSet_ExplicitR5_ExplicitVarSizeWithMarker_Values[1, q8, ..] var1_PartitionAsSet_ExplicitR5_ExplicitVarSizeWithMarker_Marker[1] -> @@ -35,14 +35,14 @@ such that | q9 : int(1..24)]), var1_PartitionAsSet_ExplicitR5_ExplicitVarSizeWithMarker_Marker[1] <= 24, and([var2_ExplicitVarSizeWithFlagsR10_Flags[q13 + 1] -> - var2_ExplicitVarSizeWithFlagsR10_Values_Function1DPartial_Flags[q13, ..] diff --git a/tests/parse_print/autogen-bilals-fixed/200d78834a42ebeb6f12a80d41000004/model.expected.json b/tests/parse_print/autogen-bilals-fixed/200d78834a42ebeb6f12a80d41000004/model.expected.json index d8f834f1d4..d0df0b72cb 100644 --- a/tests/parse_print/autogen-bilals-fixed/200d78834a42ebeb6f12a80d41000004/model.expected.json +++ b/tests/parse_print/autogen-bilals-fixed/200d78834a42ebeb6f12a80d41000004/model.expected.json @@ -889,7 +889,7 @@ {"ConstantInt": [{"TagInt": []}, 2]}}]}]]}, [{"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": @@ -1063,7 +1063,7 @@ []}, 2]}}]}]]}]}}]]}}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": diff --git a/tests/parse_print/autogen-bilals-fixed/200d78834a42ebeb6f12a80d41000004/stdout.expected b/tests/parse_print/autogen-bilals-fixed/200d78834a42ebeb6f12a80d41000004/stdout.expected index de0c254e7c..8b2adbe215 100644 --- a/tests/parse_print/autogen-bilals-fixed/200d78834a42ebeb6f12a80d41000004/stdout.expected +++ b/tests/parse_print/autogen-bilals-fixed/200d78834a42ebeb6f12a80d41000004/stdout.expected @@ -60,7 +60,7 @@ such that | q38 : int(1..4)]), 3 <= var1_PartitionAsSet_ExplicitVarSizeWithMarker_Marker, 1 <= var1_PartitionAsSet_ExplicitVarSizeWithMarker_Marker -> - and([var1_PartitionAsSet_ExplicitVarSizeWithMarker_Values_Explicit_ExplicitVarSizeWithFlags_Flags[1, q9, ..] diff --git a/tests/parse_print/autogen-bilals-fixed/208ec24add8f7b331f0829f7296b04c7/model.expected.json b/tests/parse_print/autogen-bilals-fixed/208ec24add8f7b331f0829f7296b04c7/model.expected.json index 739bc00b3c..0f71b9c086 100644 --- a/tests/parse_print/autogen-bilals-fixed/208ec24add8f7b331f0829f7296b04c7/model.expected.json +++ b/tests/parse_print/autogen-bilals-fixed/208ec24add8f7b331f0829f7296b04c7/model.expected.json @@ -850,7 +850,7 @@ []}, 2]}}]}]]}, [{"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": @@ -1000,7 +1000,7 @@ []}, 4]}}]}]]}]}}]]}}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpFlatten": [null, @@ -1431,7 +1431,7 @@ []}, 1]}}]]}}}}]}}]}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": @@ -2202,7 +2202,7 @@ []}, 1]}}]]}}}}]}}]}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": diff --git a/tests/parse_print/autogen-bilals-fixed/208ec24add8f7b331f0829f7296b04c7/stdout.expected b/tests/parse_print/autogen-bilals-fixed/208ec24add8f7b331f0829f7296b04c7/stdout.expected index 351437d100..531a0e03b1 100644 --- a/tests/parse_print/autogen-bilals-fixed/208ec24add8f7b331f0829f7296b04c7/stdout.expected +++ b/tests/parse_print/autogen-bilals-fixed/208ec24add8f7b331f0829f7296b04c7/stdout.expected @@ -67,7 +67,7 @@ such that /\ (var1_PartitionAsSet_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMarker_Marker [q5, ..] - var4_PartitionAsSet_ExplicitVarSizeWithMarker_Marker -> diff --git a/tests/parse_print/autogen-bilals-fixed/20a87ed854619dfbc1f01b026e5db67b/model.expected.json b/tests/parse_print/autogen-bilals-fixed/20a87ed854619dfbc1f01b026e5db67b/model.expected.json index b617e629af..e5b5083f6e 100644 --- a/tests/parse_print/autogen-bilals-fixed/20a87ed854619dfbc1f01b026e5db67b/model.expected.json +++ b/tests/parse_print/autogen-bilals-fixed/20a87ed854619dfbc1f01b026e5db67b/model.expected.json @@ -469,7 +469,7 @@ {"AbstractLiteral": {"AbsLitRelation": [[{"Op": - {"MkOpLexLeq": + {"MkOpDotLeq": [{"Comprehension": [{"Reference": [{"Name": "l_2"}, null]}, [{"Generator": diff --git a/tests/parse_print/autogen-bilals-fixed/20a87ed854619dfbc1f01b026e5db67b/stdout.expected b/tests/parse_print/autogen-bilals-fixed/20a87ed854619dfbc1f01b026e5db67b/stdout.expected index af2c769789..bd6bcb116c 100644 --- a/tests/parse_print/autogen-bilals-fixed/20a87ed854619dfbc1f01b026e5db67b/stdout.expected +++ b/tests/parse_print/autogen-bilals-fixed/20a87ed854619dfbc1f01b026e5db67b/stdout.expected @@ -39,7 +39,7 @@ such that ([true; int(2)], partition({true, false, true, true}), mset(false))); int(0)])) subsetEq - relation(([l_2 | l_2 : bool, l_3 : bool, l_3 <= false, l_2] <=lex [5 >= 0 | l_4 : bool, l_5 : bool], + relation(([l_2 | l_2 : bool, l_3 : bool, l_3 <= false, l_2] .<= [5 >= 0 | l_4 : bool, l_5 : bool], ([] : `matrix indexed by [int] of relation of (matrix indexed by [int] of bool * partition from bool * mset of bool)`)), (inverse(function(relation(tuple (true)) --> (false, true, true, false), diff --git a/tests/parse_print/autogen-bilals-fixed/21be920dffbaacd7e2b6b06b72cb75c0/model.expected.json b/tests/parse_print/autogen-bilals-fixed/21be920dffbaacd7e2b6b06b72cb75c0/model.expected.json index b10551db1c..b42d9d8f5d 100644 --- a/tests/parse_print/autogen-bilals-fixed/21be920dffbaacd7e2b6b06b72cb75c0/model.expected.json +++ b/tests/parse_print/autogen-bilals-fixed/21be920dffbaacd7e2b6b06b72cb75c0/model.expected.json @@ -909,7 +909,7 @@ {"Condition": {"Reference": [{"Name": "l_2"}, null]}}, {"Condition": {"Reference": [{"Name": "l_2"}, null]}}]]}}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Comprehension": [{"Reference": [{"Name": "l_4"}, null]}, [{"Generator": diff --git a/tests/parse_print/autogen-bilals-fixed/21be920dffbaacd7e2b6b06b72cb75c0/stdout.expected b/tests/parse_print/autogen-bilals-fixed/21be920dffbaacd7e2b6b06b72cb75c0/stdout.expected index 9c6a86a0b2..2a0599880c 100644 --- a/tests/parse_print/autogen-bilals-fixed/21be920dffbaacd7e2b6b06b72cb75c0/stdout.expected +++ b/tests/parse_print/autogen-bilals-fixed/21be920dffbaacd7e2b6b06b72cb75c0/stdout.expected @@ -61,5 +61,5 @@ such that function((5, false, 4, 4) --> mset(0, 5, 0), (5, true, 4, 0) --> mset(5), (0, false, 5, 5) --> mset(2, 0, 4), (2, true, 0, 1) --> (mset() : `mset of int`)))), or([l_2 | l_1 : bool, l_2 : bool, l_2, l_2]), - [l_4 | l_3 : int(3, 5), l_4 : int(1..2, 3)] var1_PartitionAsSet_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMarker_Values_Function1DPartial_Flags [q1, q2, ..] - - and([var1_PartitionAsSet_ExplicitVarSizeWithMarker_Values_Explicit_ExplicitVarSizeWithFlags_Flags[1, q9, ..] diff --git a/tests/parse_print/autogen-bilals-fixed/23f59fd02b1d9c3816b417a8727e418c/model.expected.json b/tests/parse_print/autogen-bilals-fixed/23f59fd02b1d9c3816b417a8727e418c/model.expected.json index e14d70140b..27893ba094 100644 --- a/tests/parse_print/autogen-bilals-fixed/23f59fd02b1d9c3816b417a8727e418c/model.expected.json +++ b/tests/parse_print/autogen-bilals-fixed/23f59fd02b1d9c3816b417a8727e418c/model.expected.json @@ -296,7 +296,7 @@ "var2_PartitionAsSet_ExplicitVarSizeWithMarker_Marker"}, null]}]}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpFlatten": [null, diff --git a/tests/parse_print/autogen-bilals-fixed/23f59fd02b1d9c3816b417a8727e418c/stdout.expected b/tests/parse_print/autogen-bilals-fixed/23f59fd02b1d9c3816b417a8727e418c/stdout.expected index 43bb597b16..d9ffb4cc15 100644 --- a/tests/parse_print/autogen-bilals-fixed/23f59fd02b1d9c3816b417a8727e418c/stdout.expected +++ b/tests/parse_print/autogen-bilals-fixed/23f59fd02b1d9c3816b417a8727e418c/stdout.expected @@ -17,7 +17,7 @@ such that | q1_Occurrence : matrix indexed by [int(2, 1..2)] of bool, sum([q1_Occurrence[q10] | q10 : int(2, 1..2)]) <= 5]), and([q4 + 1 <= var2_PartitionAsSet_ExplicitVarSizeWithMarker_Marker -> - flatten(var2_PartitionAsSet_ExplicitVarSizeWithMarker_Values_Explicit_Occurrence[q4, .., ..]) var2_PartitionAsSet_ExplicitVarSizeWithMarker_Marker -> diff --git a/tests/parse_print/autogen-bilals-fixed/256afa47464e2a7d839a0636d335714b/model.expected.json b/tests/parse_print/autogen-bilals-fixed/256afa47464e2a7d839a0636d335714b/model.expected.json index 56b2b309ba..5330d79341 100644 --- a/tests/parse_print/autogen-bilals-fixed/256afa47464e2a7d839a0636d335714b/model.expected.json +++ b/tests/parse_print/autogen-bilals-fixed/256afa47464e2a7d839a0636d335714b/model.expected.json @@ -153,7 +153,7 @@ {"ConstantInt": [{"TagInt": []}, 2]}}]}]]}, [{"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": @@ -1281,7 +1281,7 @@ []}, 1]}}]]}}}}]}}]}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": diff --git a/tests/parse_print/autogen-bilals-fixed/256afa47464e2a7d839a0636d335714b/stdout.expected b/tests/parse_print/autogen-bilals-fixed/256afa47464e2a7d839a0636d335714b/stdout.expected index 39789b4b80..76b67d12b9 100644 --- a/tests/parse_print/autogen-bilals-fixed/256afa47464e2a7d839a0636d335714b/stdout.expected +++ b/tests/parse_print/autogen-bilals-fixed/256afa47464e2a7d839a0636d335714b/stdout.expected @@ -15,7 +15,7 @@ find var2_2_Function1DPartial_Values: matrix indexed by [int(0, 4..5)] of int(0) find var2_3: bool such that and([q1 + 1 <= var1_FunctionAsRelation_RelationAsSet_ExplicitVarSizeWithMarker_Marker -> - var1_FunctionAsRelation_RelationAsSet_ExplicitVarSizeWithMarker_Values_1_Occurrence[q1, ..] @@ -71,7 +71,7 @@ such that var2_1_PartitionAsSet_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMarker_Marker[q11] = var2_1_PartitionAsSet_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMarker_Marker[q11 + 1] /\ - var2_1_PartitionAsSet_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMarker_Values[q11, ..] var2_1_PartitionAsSet_ExplicitVarSizeWithMarker_Marker -> diff --git a/tests/parse_print/autogen-bilals-fixed/25c731b81cdfba9a1930f6d921e9fc53/model.expected.json b/tests/parse_print/autogen-bilals-fixed/25c731b81cdfba9a1930f6d921e9fc53/model.expected.json index 9b45c678f8..14b6f8ffe7 100644 --- a/tests/parse_print/autogen-bilals-fixed/25c731b81cdfba9a1930f6d921e9fc53/model.expected.json +++ b/tests/parse_print/autogen-bilals-fixed/25c731b81cdfba9a1930f6d921e9fc53/model.expected.json @@ -8,7 +8,7 @@ [{"Declaration": {"FindOrGiven": ["Find", {"Name": "unused"}, {"DomainBool": []}]}}, {"SuchThat": [{"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Comprehension": [{"Constant": {"ConstantBool": false}}, [{"Generator": {"GenDomainNoRepr": [{"Single": {"Name": "l_1"}}, {"DomainBool": []}]}}]]}, diff --git a/tests/parse_print/autogen-bilals-fixed/25c731b81cdfba9a1930f6d921e9fc53/stdout.expected b/tests/parse_print/autogen-bilals-fixed/25c731b81cdfba9a1930f6d921e9fc53/stdout.expected index 509f5acfbb..04eed9979e 100644 --- a/tests/parse_print/autogen-bilals-fixed/25c731b81cdfba9a1930f6d921e9fc53/stdout.expected +++ b/tests/parse_print/autogen-bilals-fixed/25c731b81cdfba9a1930f6d921e9fc53/stdout.expected @@ -1,4 +1,4 @@ language Essence 1.3 find unused: bool -such that [false | l_1 : bool] [0; int(1)]), relation((false, 4))) +such that [5; int(1)] .<= image(function(relation((false, 1)) --> [0; int(1)]), relation((false, 4))) diff --git a/tests/parse_print/autogen-bilals-fixed/2910579caa938519c953fccd48611fee/model.expected.json b/tests/parse_print/autogen-bilals-fixed/2910579caa938519c953fccd48611fee/model.expected.json index 85d420f923..e7aa026345 100644 --- a/tests/parse_print/autogen-bilals-fixed/2910579caa938519c953fccd48611fee/model.expected.json +++ b/tests/parse_print/autogen-bilals-fixed/2910579caa938519c953fccd48611fee/model.expected.json @@ -87,7 +87,7 @@ [{"Constant": {"ConstantInt": [{"TagInt": []}, 1]}}, {"Constant": {"ConstantInt": [{"TagInt": []}, 2]}}]}]]}, [{"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": @@ -179,7 +179,7 @@ []}, 2]}}]}]]}, [{"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": @@ -211,7 +211,7 @@ null, null]}}]}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": diff --git a/tests/parse_print/autogen-bilals-fixed/2910579caa938519c953fccd48611fee/stdout.expected b/tests/parse_print/autogen-bilals-fixed/2910579caa938519c953fccd48611fee/stdout.expected index 0df25e7b2a..9775e5c800 100644 --- a/tests/parse_print/autogen-bilals-fixed/2910579caa938519c953fccd48611fee/stdout.expected +++ b/tests/parse_print/autogen-bilals-fixed/2910579caa938519c953fccd48611fee/stdout.expected @@ -9,17 +9,16 @@ find var1_FunctionAsRelation_RelationAsSet_ExplicitVarSizeWithMarker_Values_2_Ex matrix indexed by [int(1..2), int(1..0)] of bool such that 2 <= var1_FunctionAsRelation_RelationAsSet_ExplicitVarSizeWithMarker_Marker -> - var1_FunctionAsRelation_RelationAsSet_ExplicitVarSizeWithMarker_Values_1[1, ..] var1_FunctionAsRelation_RelationAsSet_ExplicitVarSizeWithMarker_Marker -> var1_FunctionAsRelation_RelationAsSet_ExplicitVarSizeWithMarker_Values_1[q2, 3] = false diff --git a/tests/parse_print/autogen-bilals-fixed/2abab26b761b711b383086f57689adc5/model.expected.json b/tests/parse_print/autogen-bilals-fixed/2abab26b761b711b383086f57689adc5/model.expected.json index 7fb0cc5c74..d4f675e746 100644 --- a/tests/parse_print/autogen-bilals-fixed/2abab26b761b711b383086f57689adc5/model.expected.json +++ b/tests/parse_print/autogen-bilals-fixed/2abab26b761b711b383086f57689adc5/model.expected.json @@ -599,7 +599,7 @@ []}, 2]}}]}]]}, [{"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": @@ -751,7 +751,7 @@ []}, 4]}}}]]}]}}]]}}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": diff --git a/tests/parse_print/autogen-bilals-fixed/2abab26b761b711b383086f57689adc5/stdout.expected b/tests/parse_print/autogen-bilals-fixed/2abab26b761b711b383086f57689adc5/stdout.expected index b9fdf38dad..eb58c775bd 100644 --- a/tests/parse_print/autogen-bilals-fixed/2abab26b761b711b383086f57689adc5/stdout.expected +++ b/tests/parse_print/autogen-bilals-fixed/2abab26b761b711b383086f57689adc5/stdout.expected @@ -42,7 +42,7 @@ such that | q28 : int(-4, 4)]) | q1 : int(1..7)]), and([q1 + 1 <= var1_FunctionAsRelation_RelationAsSet_ExplicitVarSizeWithMarker_Marker -> - var1_FunctionAsRelation_RelationAsSet_ExplicitVarSizeWithMarker_Values_1_Function1DPartial_Flags[q1, ..] = 1, and([q6 + 1 <= var1_PartitionAsSet_Explicit_ExplicitVarSizeWithMarker_Marker[1] -> - var1_PartitionAsSet_Explicit_ExplicitVarSizeWithMarker_Values_Function1D[1, q6, ..] var1_PartitionAsSet_Explicit_ExplicitVarSizeWithMarker_Marker[1] -> @@ -34,7 +34,7 @@ such that | q8 : int(1..256)]), and([q8 <= var1_PartitionAsSet_Explicit_ExplicitVarSizeWithMarker_Marker[1] -> false | q8 : int(1..256)]), 2 <= var3_ExplicitVarSizeWithMarker_Marker -> - flatten(var3_ExplicitVarSizeWithMarker_Values_RelationAsMatrix[1, .., .., .., ..]) var3_ExplicitVarSizeWithMarker_Marker -> and([and([and([and([var3_ExplicitVarSizeWithMarker_Values_RelationAsMatrix[q11, q37, q38, q39, q40] = false diff --git a/tests/parse_print/autogen-bilals-fixed/2cb879c833748cef779f84df872b0d71/model.expected.json b/tests/parse_print/autogen-bilals-fixed/2cb879c833748cef779f84df872b0d71/model.expected.json index 9ac3d3aa5d..eb9454aaf0 100644 --- a/tests/parse_print/autogen-bilals-fixed/2cb879c833748cef779f84df872b0d71/model.expected.json +++ b/tests/parse_print/autogen-bilals-fixed/2cb879c833748cef779f84df872b0d71/model.expected.json @@ -1947,7 +1947,7 @@ []}, 2]}}]}]]}, [{"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpFlatten": [null, @@ -2146,7 +2146,7 @@ []}, 16]}}]}]]}]}}]]}}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpFlatten": [null, @@ -2473,7 +2473,7 @@ []}, 2]}}]}]]}, [{"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": @@ -2648,7 +2648,7 @@ []}, 3]}}}]]}]}}]]}}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": diff --git a/tests/parse_print/autogen-bilals-fixed/2cb879c833748cef779f84df872b0d71/stdout.expected b/tests/parse_print/autogen-bilals-fixed/2cb879c833748cef779f84df872b0d71/stdout.expected index 71b944507c..42b85e6b25 100644 --- a/tests/parse_print/autogen-bilals-fixed/2cb879c833748cef779f84df872b0d71/stdout.expected +++ b/tests/parse_print/autogen-bilals-fixed/2cb879c833748cef779f84df872b0d71/stdout.expected @@ -116,7 +116,7 @@ such that /\ (flatten(var1_PartitionAsSet_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMarker_Values_Function1DPartial_Flags [q1, .., ..]) - var1_PartitionAsSet_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMarker_Values_Function1DPartial_Flags [q1, q2, ..] - - var1_FunctionAsRelationR2R4_RelationAsSetR2R4_ExplicitVarSizeWithMarkerR2R4_Values_1_Occurrence[q6, ..] - (var1_FunctionAsRelationR2R4_RelationAsSetR2R4_ExplicitVarSizeWithMarkerR2R4_Values_1_Occurrence[q30, ..] or([var1_FunctionAsRelationR2R4_RelationAsSetR2R4_ExplicitVarSizeWithMarkerR2R4_Values_2_ExplicitVarSizeWithFlags_Flags diff --git a/tests/parse_print/autogen-bilals-fixed/3092be0de62c362cd1c49042c585105f/model.expected.json b/tests/parse_print/autogen-bilals-fixed/3092be0de62c362cd1c49042c585105f/model.expected.json index 340986ca17..b459e3232d 100644 --- a/tests/parse_print/autogen-bilals-fixed/3092be0de62c362cd1c49042c585105f/model.expected.json +++ b/tests/parse_print/autogen-bilals-fixed/3092be0de62c362cd1c49042c585105f/model.expected.json @@ -251,7 +251,7 @@ []}, 2]}}]}]]}, [{"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": @@ -401,7 +401,7 @@ []}, 4]}}]}]]}]}}]]}}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpFlatten": [null, @@ -1278,7 +1278,7 @@ []}, 1]}}]]}}}}]}}]}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": diff --git a/tests/parse_print/autogen-bilals-fixed/3092be0de62c362cd1c49042c585105f/stdout.expected b/tests/parse_print/autogen-bilals-fixed/3092be0de62c362cd1c49042c585105f/stdout.expected index 2e4ec29a18..cc6e6b9b89 100644 --- a/tests/parse_print/autogen-bilals-fixed/3092be0de62c362cd1c49042c585105f/stdout.expected +++ b/tests/parse_print/autogen-bilals-fixed/3092be0de62c362cd1c49042c585105f/stdout.expected @@ -19,7 +19,7 @@ such that /\ (var1_ExplicitVarSizeWithFlags_Values_PartitionAsSet_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMarker_Marker [q1, ..] - diff --git a/tests/parse_print/autogen-bilals-fixed/32ba15f900d2899e277de2884b82db33/model.expected.json b/tests/parse_print/autogen-bilals-fixed/32ba15f900d2899e277de2884b82db33/model.expected.json index 3b1daf1c1c..4a20e5115a 100644 --- a/tests/parse_print/autogen-bilals-fixed/32ba15f900d2899e277de2884b82db33/model.expected.json +++ b/tests/parse_print/autogen-bilals-fixed/32ba15f900d2899e277de2884b82db33/model.expected.json @@ -8,7 +8,7 @@ [{"Declaration": {"FindOrGiven": ["Find", {"Name": "unused"}, {"DomainBool": []}]}}, {"SuchThat": [{"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": diff --git a/tests/parse_print/autogen-bilals-fixed/32ba15f900d2899e277de2884b82db33/stdout.expected b/tests/parse_print/autogen-bilals-fixed/32ba15f900d2899e277de2884b82db33/stdout.expected index 05ae18456c..624d31a534 100644 --- a/tests/parse_print/autogen-bilals-fixed/32ba15f900d2899e277de2884b82db33/stdout.expected +++ b/tests/parse_print/autogen-bilals-fixed/32ba15f900d2899e277de2884b82db33/stdout.expected @@ -1,4 +1,4 @@ language ESSENCE' 1.0 find unused: bool -such that [[false; int(1)]; int(1)][0, ..] var1_PartitionAsSet_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMarker_Values_Occurrence [q7, q8, ..] - var4_PartitionAsSet_ExplicitVarSizeWithMarker_Marker -> diff --git a/tests/parse_print/autogen-bilals-fixed/35a9b9aabd733bd1da92dcfbbafbb0e0/model.expected.json b/tests/parse_print/autogen-bilals-fixed/35a9b9aabd733bd1da92dcfbbafbb0e0/model.expected.json index 45a3ee31aa..85ec64e0a4 100644 --- a/tests/parse_print/autogen-bilals-fixed/35a9b9aabd733bd1da92dcfbbafbb0e0/model.expected.json +++ b/tests/parse_print/autogen-bilals-fixed/35a9b9aabd733bd1da92dcfbbafbb0e0/model.expected.json @@ -771,7 +771,7 @@ []}, 2]}}]}]]}, [{"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": @@ -923,7 +923,7 @@ []}, 4]}}}]]}]}}]]}}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": diff --git a/tests/parse_print/autogen-bilals-fixed/35a9b9aabd733bd1da92dcfbbafbb0e0/stdout.expected b/tests/parse_print/autogen-bilals-fixed/35a9b9aabd733bd1da92dcfbbafbb0e0/stdout.expected index d7ac28c526..edaab7f682 100644 --- a/tests/parse_print/autogen-bilals-fixed/35a9b9aabd733bd1da92dcfbbafbb0e0/stdout.expected +++ b/tests/parse_print/autogen-bilals-fixed/35a9b9aabd733bd1da92dcfbbafbb0e0/stdout.expected @@ -50,7 +50,7 @@ such that | q35 : int(1..2)]) | q1 : int(1..7)]), and([q1 + 1 <= var1_FunctionAsRelation_RelationAsSet_ExplicitVarSizeWithMarker_Marker -> - var1_FunctionAsRelation_RelationAsSet_ExplicitVarSizeWithMarker_Values_1_Function1DPartial_Flags[q1, ..] - var1_FunctionAsRelation_RelationAsSet_ExplicitVarSizeWithMarker_Values_1_Occurrence[q1, ..] @@ -69,7 +69,7 @@ such that var2_1_PartitionAsSet_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMarker_Marker[q11] = var2_1_PartitionAsSet_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMarker_Marker[q11 + 1] /\ - var2_1_PartitionAsSet_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMarker_Values[q11, ..] var2_1_PartitionAsSet_ExplicitVarSizeWithMarker_Marker -> diff --git a/tests/parse_print/autogen-bilals-fixed/35bd3096c398059a5f4e2e9de6159866/model.expected.json b/tests/parse_print/autogen-bilals-fixed/35bd3096c398059a5f4e2e9de6159866/model.expected.json index d04b3cadfe..d10cbb3449 100644 --- a/tests/parse_print/autogen-bilals-fixed/35bd3096c398059a5f4e2e9de6159866/model.expected.json +++ b/tests/parse_print/autogen-bilals-fixed/35bd3096c398059a5f4e2e9de6159866/model.expected.json @@ -763,7 +763,7 @@ []}, 2]}}]}]]}, [{"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": @@ -931,7 +931,7 @@ []}, 2]}}]}]]}, [{"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": @@ -1081,7 +1081,7 @@ []}, 2]}}]}]]}]}}]]}}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": diff --git a/tests/parse_print/autogen-bilals-fixed/35bd3096c398059a5f4e2e9de6159866/stdout.expected b/tests/parse_print/autogen-bilals-fixed/35bd3096c398059a5f4e2e9de6159866/stdout.expected index 157a1281c1..a4bca77b17 100644 --- a/tests/parse_print/autogen-bilals-fixed/35bd3096c398059a5f4e2e9de6159866/stdout.expected +++ b/tests/parse_print/autogen-bilals-fixed/35bd3096c398059a5f4e2e9de6159866/stdout.expected @@ -64,21 +64,21 @@ such that var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q4] = var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q4 + 1] /\ - (var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values_1[q4, ..] var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> diff --git a/tests/parse_print/autogen-bilals-fixed/360166fcf3210cf2cc730698c7561f1a/model.expected.json b/tests/parse_print/autogen-bilals-fixed/360166fcf3210cf2cc730698c7561f1a/model.expected.json index 8248f46ead..6363625608 100644 --- a/tests/parse_print/autogen-bilals-fixed/360166fcf3210cf2cc730698c7561f1a/model.expected.json +++ b/tests/parse_print/autogen-bilals-fixed/360166fcf3210cf2cc730698c7561f1a/model.expected.json @@ -1576,7 +1576,7 @@ []}, 2]}}]}]]}, [{"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpFlatten": [null, @@ -1775,7 +1775,7 @@ []}, 16]}}]}]]}]}}]]}}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpFlatten": [null, @@ -2102,7 +2102,7 @@ []}, 2]}}]}]]}, [{"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": @@ -2277,7 +2277,7 @@ []}, 4]}}}]]}]}}]]}}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": diff --git a/tests/parse_print/autogen-bilals-fixed/360166fcf3210cf2cc730698c7561f1a/stdout.expected b/tests/parse_print/autogen-bilals-fixed/360166fcf3210cf2cc730698c7561f1a/stdout.expected index a422048919..fc83819916 100644 --- a/tests/parse_print/autogen-bilals-fixed/360166fcf3210cf2cc730698c7561f1a/stdout.expected +++ b/tests/parse_print/autogen-bilals-fixed/360166fcf3210cf2cc730698c7561f1a/stdout.expected @@ -94,7 +94,7 @@ such that /\ (flatten(var1_PartitionAsSet_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMarker_Values_Function1DPartial_Flags [q1, .., ..]) - var1_PartitionAsSet_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMarker_Values_Function1DPartial_Flags [q1, q2, ..] - - var1_FunctionAsRelationR2R4_RelationAsSetR2R4_ExplicitVarSizeWithMarkerR2R4_Values_1_Occurrence[q6, ..] - (var1_FunctionAsRelationR2R4_RelationAsSetR2R4_ExplicitVarSizeWithMarkerR2R4_Values_1_Occurrence[q34, ..] or([var1_FunctionAsRelationR2R4_RelationAsSetR2R4_ExplicitVarSizeWithMarkerR2R4_Values_2_ExplicitVarSizeWithFlags_Flags diff --git a/tests/parse_print/autogen-bilals-fixed/36adf65748e3aabfd49290654b8b9ec2/model.expected.json b/tests/parse_print/autogen-bilals-fixed/36adf65748e3aabfd49290654b8b9ec2/model.expected.json index 75fbfae968..43e3da629e 100644 --- a/tests/parse_print/autogen-bilals-fixed/36adf65748e3aabfd49290654b8b9ec2/model.expected.json +++ b/tests/parse_print/autogen-bilals-fixed/36adf65748e3aabfd49290654b8b9ec2/model.expected.json @@ -803,7 +803,7 @@ []}, 2]}}]}]]}, [{"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": @@ -955,7 +955,7 @@ []}, 4]}}}]]}]}}]]}}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": diff --git a/tests/parse_print/autogen-bilals-fixed/36adf65748e3aabfd49290654b8b9ec2/stdout.expected b/tests/parse_print/autogen-bilals-fixed/36adf65748e3aabfd49290654b8b9ec2/stdout.expected index 4f39b51b19..de6fbc1b18 100644 --- a/tests/parse_print/autogen-bilals-fixed/36adf65748e3aabfd49290654b8b9ec2/stdout.expected +++ b/tests/parse_print/autogen-bilals-fixed/36adf65748e3aabfd49290654b8b9ec2/stdout.expected @@ -53,7 +53,7 @@ such that | q36 : int(-4, 4)]) | q1 : int(1..7)]), and([q1 + 1 <= var1_FunctionAsRelation_RelationAsSet_ExplicitVarSizeWithMarker_Marker -> - var1_FunctionAsRelation_RelationAsSet_ExplicitVarSizeWithMarker_Values_1_Function1DPartial_Flags[q1, ..] var1_PartitionAsSet_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMarker_Values_Function1DPartial_Flags [q1, q2, ..] - - var1_ExplicitVarSizeWithFlags_Values_ExplicitVarSizeWithFlags_Flags[q1, ..] @@ -87,7 +87,7 @@ such that /\ flatten(var2_PartitionAsSet_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMarker_Values_RelationAsMatrix [q16, .., .., .., ..]) - flatten(var2_PartitionAsSet_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMarker_Values_RelationAsMatrix [q18, q19, .., .., ..]) - var2_1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> @@ -133,14 +133,14 @@ such that | q16 : int(1..9)]), 3 = var4_1_ExplicitWithRepetition_Flag, and([q23 + 1 <= var5_ExplicitWithRepetitionR10_Flag -> - var5_ExplicitWithRepetitionR10_Values_Function1DPartial_Flags[q23, ..] var5_ExplicitWithRepetitionR10_Flag -> diff --git a/tests/parse_print/autogen-bilals-fixed/39fc0816e0aea89208c87fa4d39edf4d/model.expected.json b/tests/parse_print/autogen-bilals-fixed/39fc0816e0aea89208c87fa4d39edf4d/model.expected.json index df5126ea45..4d0e7be533 100644 --- a/tests/parse_print/autogen-bilals-fixed/39fc0816e0aea89208c87fa4d39edf4d/model.expected.json +++ b/tests/parse_print/autogen-bilals-fixed/39fc0816e0aea89208c87fa4d39edf4d/model.expected.json @@ -177,7 +177,7 @@ {"TypeMSet": {"TypeMSet": {"TypeInt": {"TagInt": []}}}}]}, {"Constant": {"ConstantAbstract": {"AbsLitMSet": [{"ConstantBool": true}]}}}]]}}]}}, {"Op": - {"MkOpLexLeq": + {"MkOpDotLeq": [{"Op": {"MkOpImage": [{"Constant": diff --git a/tests/parse_print/autogen-bilals-fixed/39fc0816e0aea89208c87fa4d39edf4d/stdout.expected b/tests/parse_print/autogen-bilals-fixed/39fc0816e0aea89208c87fa4d39edf4d/stdout.expected index 21303d225c..ae1c46d924 100644 --- a/tests/parse_print/autogen-bilals-fixed/39fc0816e0aea89208c87fa4d39edf4d/stdout.expected +++ b/tests/parse_print/autogen-bilals-fixed/39fc0816e0aea89208c87fa4d39edf4d/stdout.expected @@ -20,7 +20,7 @@ such that (mset() : `mset of mset of int`) --> mset(true)), image(function([1, 0; int(3, 0)] --> [false, true, false, false, false; int(3, 15, 0, 4, 2)]), [5, 2 - 5; int(2, 5)]) - <=lex [l_2 | l_1 : bool, l_2 : bool, and(([] : `matrix indexed by [int] of bool`)), l_2], + .<= [l_2 | l_1 : bool, l_2 : bool, and(([] : `matrix indexed by [int] of bool`)), l_2], image(function((tuple (0), false, false, partition({true}, {false})) --> true, (tuple (4), true = false, true, partition({false, true, true})) --> true > false, (tuple (1), false, false, diff --git a/tests/parse_print/autogen-bilals-fixed/3b5e1803eab57ae500a891f3bfadce58/model.expected.json b/tests/parse_print/autogen-bilals-fixed/3b5e1803eab57ae500a891f3bfadce58/model.expected.json index 39e78c1152..6123827764 100644 --- a/tests/parse_print/autogen-bilals-fixed/3b5e1803eab57ae500a891f3bfadce58/model.expected.json +++ b/tests/parse_print/autogen-bilals-fixed/3b5e1803eab57ae500a891f3bfadce58/model.expected.json @@ -306,7 +306,7 @@ []}, 2]}}]}]]}, [{"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": @@ -456,7 +456,7 @@ []}, 4]}}]}]]}]}}]]}}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpFlatten": [null, @@ -1333,7 +1333,7 @@ []}, 1]}}]]}}}}]}}]}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": diff --git a/tests/parse_print/autogen-bilals-fixed/3b5e1803eab57ae500a891f3bfadce58/stdout.expected b/tests/parse_print/autogen-bilals-fixed/3b5e1803eab57ae500a891f3bfadce58/stdout.expected index 5f31abe877..788f7df3ec 100644 --- a/tests/parse_print/autogen-bilals-fixed/3b5e1803eab57ae500a891f3bfadce58/stdout.expected +++ b/tests/parse_print/autogen-bilals-fixed/3b5e1803eab57ae500a891f3bfadce58/stdout.expected @@ -24,7 +24,7 @@ such that /\ (var1_ExplicitVarSizeWithFlags_Values_PartitionAsSet_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMarker_Marker [q1, ..] - @@ -35,10 +35,10 @@ such that | q20 : int(1..2)]) | q18 : int(1..2)]) /\ - (var1_RelationAsSet_ExplicitVarSizeWithMarker_Values_2_ExplicitVarSizeWithFlags_Flags[q1, ..] var1_RelationAsSet_ExplicitVarSizeWithMarker_Marker -> diff --git a/tests/parse_print/autogen-bilals-fixed/3d535f0ac7272986482b759dae43c292/model.expected.json b/tests/parse_print/autogen-bilals-fixed/3d535f0ac7272986482b759dae43c292/model.expected.json index b76e94f5d2..186f1d5c2c 100644 --- a/tests/parse_print/autogen-bilals-fixed/3d535f0ac7272986482b759dae43c292/model.expected.json +++ b/tests/parse_print/autogen-bilals-fixed/3d535f0ac7272986482b759dae43c292/model.expected.json @@ -657,7 +657,7 @@ {"ConstantInt": [{"TagInt": []}, 2]}}]}]]}, [{"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": @@ -783,7 +783,7 @@ []}, 1]}}]}}]}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpFlatten": [null, diff --git a/tests/parse_print/autogen-bilals-fixed/3d535f0ac7272986482b759dae43c292/stdout.expected b/tests/parse_print/autogen-bilals-fixed/3d535f0ac7272986482b759dae43c292/stdout.expected index 1704873bff..5f930df9f2 100644 --- a/tests/parse_print/autogen-bilals-fixed/3d535f0ac7272986482b759dae43c292/stdout.expected +++ b/tests/parse_print/autogen-bilals-fixed/3d535f0ac7272986482b759dae43c292/stdout.expected @@ -40,7 +40,7 @@ such that | q14 : int(1..4)]), sum([q1_ExplicitVarSizeWithFlags_Flags[q15] | q15 : int(1..5)]) <= 5]), and([q4 + 1 <= var2_PartitionAsSet_ExplicitVarSizeWithMarker_Marker -> - var2_PartitionAsSet_ExplicitVarSizeWithMarker_Values_Explicit_ExplicitVarSizeWithMarker_Marker[q4, ..] = 1 | q17 : int(1..16)]), and([q6 + 1 <= var2_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> - var2_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q6, ..] var2_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> diff --git a/tests/parse_print/autogen-bilals-fixed/3f487c8189ea7cd34b26c9482423c22f/model.expected.json b/tests/parse_print/autogen-bilals-fixed/3f487c8189ea7cd34b26c9482423c22f/model.expected.json index 0aa09fc13f..34a68942c2 100644 --- a/tests/parse_print/autogen-bilals-fixed/3f487c8189ea7cd34b26c9482423c22f/model.expected.json +++ b/tests/parse_print/autogen-bilals-fixed/3f487c8189ea7cd34b26c9482423c22f/model.expected.json @@ -2047,7 +2047,7 @@ []}, 2]}}]}]]}, [{"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpFlatten": [null, @@ -2255,7 +2255,7 @@ []}, 16]}}]}]]}]}}]]}}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpFlatten": [null, @@ -2600,7 +2600,7 @@ []}, 2]}}]}]]}, [{"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": @@ -2784,7 +2784,7 @@ []}, 4]}}}}]}]]}]}}]]}}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": diff --git a/tests/parse_print/autogen-bilals-fixed/3f487c8189ea7cd34b26c9482423c22f/stdout.expected b/tests/parse_print/autogen-bilals-fixed/3f487c8189ea7cd34b26c9482423c22f/stdout.expected index 3527753bd8..dafe07cfaf 100644 --- a/tests/parse_print/autogen-bilals-fixed/3f487c8189ea7cd34b26c9482423c22f/stdout.expected +++ b/tests/parse_print/autogen-bilals-fixed/3f487c8189ea7cd34b26c9482423c22f/stdout.expected @@ -112,7 +112,7 @@ such that /\ (flatten(var1_PartitionAsSet_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMarker_Values_Function1DPartial_Flags [q1, .., ..]) - var1_PartitionAsSet_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMarker_Values_Function1DPartial_Flags [q1, q2, ..] - @@ -77,7 +77,7 @@ such that var3_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q20] = var3_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q20 + 1] /\ - var3_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values_1[q20, ..] var3_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> diff --git a/tests/parse_print/autogen-bilals-fixed/40c777188c96f06f23b379634df5be19/model.expected.json b/tests/parse_print/autogen-bilals-fixed/40c777188c96f06f23b379634df5be19/model.expected.json index 907a163aa2..4624ae7092 100644 --- a/tests/parse_print/autogen-bilals-fixed/40c777188c96f06f23b379634df5be19/model.expected.json +++ b/tests/parse_print/autogen-bilals-fixed/40c777188c96f06f23b379634df5be19/model.expected.json @@ -28,7 +28,7 @@ [{"ConstantBool": false}, {"ConstantBool": true}, {"ConstantBool": true}]}}}]}}, {"Constant": {"ConstantBool": true}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Constant": {"ConstantAbstract": {"AbsLitMatrix": diff --git a/tests/parse_print/autogen-bilals-fixed/40c777188c96f06f23b379634df5be19/stdout.expected b/tests/parse_print/autogen-bilals-fixed/40c777188c96f06f23b379634df5be19/stdout.expected index d090321f9b..99f90e3ebb 100644 --- a/tests/parse_print/autogen-bilals-fixed/40c777188c96f06f23b379634df5be19/stdout.expected +++ b/tests/parse_print/autogen-bilals-fixed/40c777188c96f06f23b379634df5be19/stdout.expected @@ -4,4 +4,4 @@ find var1: set (maxSize -0) of partition (numParts 5, partSize 3) from bool such that {true, false} = {false, true, true}, true, - [false, false, true, false; int(6..9)] = 0 | q17 : int(1..3)]), 3 = sum([var4_1_ExplicitWithFlags_Flags[q18] | q18 : int(1..3)]), and([q20 + 1 <= var5_ExplicitWithRepetitionR10_Flag -> - var5_ExplicitWithRepetitionR10_Values_Function1DPartial_Flags[q20, ..] var5_ExplicitWithRepetitionR10_Flag -> diff --git a/tests/parse_print/autogen-bilals-fixed/4280cfb278486b51961b41fb8309b68d/model.expected.json b/tests/parse_print/autogen-bilals-fixed/4280cfb278486b51961b41fb8309b68d/model.expected.json index 164282cd6f..c9e4c16a3d 100644 --- a/tests/parse_print/autogen-bilals-fixed/4280cfb278486b51961b41fb8309b68d/model.expected.json +++ b/tests/parse_print/autogen-bilals-fixed/4280cfb278486b51961b41fb8309b68d/model.expected.json @@ -182,7 +182,7 @@ []}, 2]}}]}]]}, [{"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": @@ -319,7 +319,7 @@ {"DomainBool": []}]}}]]}}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": @@ -934,7 +934,7 @@ []}, 1]}}]]}}}}]}}]}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": @@ -1313,7 +1313,7 @@ {"ConstantInt": [{"TagInt": []}, 2]}}]}]]}, [{"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": @@ -1447,7 +1447,7 @@ {"DomainBool": []}]}}]]}}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": diff --git a/tests/parse_print/autogen-bilals-fixed/4280cfb278486b51961b41fb8309b68d/stdout.expected b/tests/parse_print/autogen-bilals-fixed/4280cfb278486b51961b41fb8309b68d/stdout.expected index f54ea3e828..f94579258f 100644 --- a/tests/parse_print/autogen-bilals-fixed/4280cfb278486b51961b41fb8309b68d/stdout.expected +++ b/tests/parse_print/autogen-bilals-fixed/4280cfb278486b51961b41fb8309b68d/stdout.expected @@ -17,14 +17,14 @@ such that q_4_ExplicitVarSizeWithFlags_Values_Function1DPartial_Values : matrix indexed by [int(1..4), bool] of int(5), and([q_4_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - q_4_ExplicitVarSizeWithFlags_Values_Function1DPartial_Flags[q1, ..] @@ -55,7 +55,7 @@ such that var1_PartitionAsSet_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMarker_Marker[q3] = var1_PartitionAsSet_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMarker_Marker[q3 + 1] /\ - var1_PartitionAsSet_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMarker_Values[q3, ..] var1_PartitionAsSet_ExplicitVarSizeWithMarker_Marker -> @@ -75,14 +75,14 @@ such that | q4 : int(1..3)]) | q3 : int(1..8)]), and([q5 + 1 <= var2_ExplicitVarSizeWithMarker_Marker -> - var2_ExplicitVarSizeWithMarker_Values_Function1DPartial_Flags[q5, ..] var2_ExplicitVarSizeWithMarker_Marker -> diff --git a/tests/parse_print/autogen-bilals-fixed/42c5a23fafc955d441461af4184f86f2/model.expected.json b/tests/parse_print/autogen-bilals-fixed/42c5a23fafc955d441461af4184f86f2/model.expected.json index 823fcccae9..ee60d9f92e 100644 --- a/tests/parse_print/autogen-bilals-fixed/42c5a23fafc955d441461af4184f86f2/model.expected.json +++ b/tests/parse_print/autogen-bilals-fixed/42c5a23fafc955d441461af4184f86f2/model.expected.json @@ -1564,7 +1564,7 @@ []}, 2]}}]}]]}, [{"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpFlatten": [null, @@ -1746,7 +1746,7 @@ []}, 2]}}]}]]}]}}]]}}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpFlatten": [null, @@ -2003,7 +2003,7 @@ [{"TagInt": []}, 2]}}]}]]}, [{"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": @@ -2116,7 +2116,7 @@ []}, 2]}}}}]}}]}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": diff --git a/tests/parse_print/autogen-bilals-fixed/42c5a23fafc955d441461af4184f86f2/stdout.expected b/tests/parse_print/autogen-bilals-fixed/42c5a23fafc955d441461af4184f86f2/stdout.expected index fe55a1778f..554efdccde 100644 --- a/tests/parse_print/autogen-bilals-fixed/42c5a23fafc955d441461af4184f86f2/stdout.expected +++ b/tests/parse_print/autogen-bilals-fixed/42c5a23fafc955d441461af4184f86f2/stdout.expected @@ -97,7 +97,7 @@ such that /\ (flatten(var1_PartitionAsSet_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMarker_Values_Function1DPartial_Flags [q5, .., ..]) - var1_PartitionAsSet_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMarker_Values_Function1DPartial_Flags [q7, 1, ..] - @@ -94,7 +94,7 @@ such that var4_2_PartitionAsSet_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMarker_Marker[q11] = var4_2_PartitionAsSet_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMarker_Marker[q11 + 1] /\ - var4_2_PartitionAsSet_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMarker_Values[q11, ..] var4_2_PartitionAsSet_ExplicitVarSizeWithMarker_Marker -> @@ -146,7 +146,7 @@ such that /\ flatten(var5_PartitionAsSet_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMarker_Values_Occurrence [q21, .., ..]) - var5_PartitionAsSet_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMarker_Values_Occurrence [q23, q24, ..] - - var2_RelationAsSet_ExplicitVarSizeWithMarker_Values_1_ExplicitVarSizeWithFlags_Flags[q1, ..] @@ -103,7 +103,7 @@ such that var4_2_PartitionAsSet_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMarker_Marker[q13] = var4_2_PartitionAsSet_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMarker_Marker[q13 + 1] /\ - var4_2_PartitionAsSet_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMarker_Values[q13, ..] var4_2_PartitionAsSet_ExplicitVarSizeWithMarker_Marker -> @@ -162,7 +162,7 @@ such that /\ (flatten(var5_PartitionAsSet_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithFlags_Flags [q23, .., ..]) - var5_PartitionAsSet_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithFlags_Flags [q25, q26, ..] - var4_ExplicitVarSizeWithMarkerR18_Marker -> diff --git a/tests/parse_print/autogen-bilals-fixed/461bdf3c29b2f09b541034b080952550/model.expected.json b/tests/parse_print/autogen-bilals-fixed/461bdf3c29b2f09b541034b080952550/model.expected.json index 5acc08338c..98d37946fe 100644 --- a/tests/parse_print/autogen-bilals-fixed/461bdf3c29b2f09b541034b080952550/model.expected.json +++ b/tests/parse_print/autogen-bilals-fixed/461bdf3c29b2f09b541034b080952550/model.expected.json @@ -172,7 +172,7 @@ {"ConstantInt": [{"TagInt": []}, 1]}}]]}}}}]}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": @@ -424,7 +424,7 @@ {"ConstantInt": [{"TagInt": []}, 1]}}]]}}}}]}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": diff --git a/tests/parse_print/autogen-bilals-fixed/461bdf3c29b2f09b541034b080952550/stdout.expected b/tests/parse_print/autogen-bilals-fixed/461bdf3c29b2f09b541034b080952550/stdout.expected index 3d813a24e4..0971ddb11e 100644 --- a/tests/parse_print/autogen-bilals-fixed/461bdf3c29b2f09b541034b080952550/stdout.expected +++ b/tests/parse_print/autogen-bilals-fixed/461bdf3c29b2f09b541034b080952550/stdout.expected @@ -14,7 +14,7 @@ find var6_ExplicitVarSizeWithFlags_Values: matrix indexed by [int(1..3), int(0, such that var4, and([var2_ExplicitVarSizeWithFlags_Flags[q10 + 1] -> - var2_ExplicitVarSizeWithFlags_Values[q10, ..] and([var2_ExplicitVarSizeWithFlags_Values[q11, q31] = false | q31 : int(4, 5)]) @@ -26,7 +26,7 @@ such that var5_ExplicitVarSizeWithFlags_Flags[1] >= -4, 1 = var5_ExplicitVarSizeWithFlags_Flags[1], and([var6_ExplicitVarSizeWithFlags_Flags[q25 + 1] -> - var6_ExplicitVarSizeWithFlags_Values[q25, ..] and([var6_ExplicitVarSizeWithFlags_Values[q26, q32] = false | q32 : int(0, 1)]) diff --git a/tests/parse_print/autogen-bilals-fixed/463c263b7ca3948dadc72aac12f03675/model.expected.json b/tests/parse_print/autogen-bilals-fixed/463c263b7ca3948dadc72aac12f03675/model.expected.json index 2f57961704..53cda086c3 100644 --- a/tests/parse_print/autogen-bilals-fixed/463c263b7ca3948dadc72aac12f03675/model.expected.json +++ b/tests/parse_print/autogen-bilals-fixed/463c263b7ca3948dadc72aac12f03675/model.expected.json @@ -8,7 +8,7 @@ [{"Declaration": {"FindOrGiven": ["Find", {"Name": "unused"}, {"DomainBool": []}]}}, {"SuchThat": [{"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Constant": {"ConstantAbstract": {"AbsLitMatrix": diff --git a/tests/parse_print/autogen-bilals-fixed/463c263b7ca3948dadc72aac12f03675/stdout.expected b/tests/parse_print/autogen-bilals-fixed/463c263b7ca3948dadc72aac12f03675/stdout.expected index 7aa872dd7e..b5ea3208e3 100644 --- a/tests/parse_print/autogen-bilals-fixed/463c263b7ca3948dadc72aac12f03675/stdout.expected +++ b/tests/parse_print/autogen-bilals-fixed/463c263b7ca3948dadc72aac12f03675/stdout.expected @@ -1,4 +1,4 @@ language Essence 1.3 find unused: bool -such that [false; int(1)] [true; int(1)]), [false; int(1)]) +such that [false; int(1)] .< image(function([true; int(1)] --> [true; int(1)]), [false; int(1)]) diff --git a/tests/parse_print/autogen-bilals-fixed/48929a67dab909763280169f5d4632b9/model.expected.json b/tests/parse_print/autogen-bilals-fixed/48929a67dab909763280169f5d4632b9/model.expected.json index d586b2e968..c464c92ddd 100644 --- a/tests/parse_print/autogen-bilals-fixed/48929a67dab909763280169f5d4632b9/model.expected.json +++ b/tests/parse_print/autogen-bilals-fixed/48929a67dab909763280169f5d4632b9/model.expected.json @@ -240,7 +240,7 @@ []}, 2]}}]}]]}, [{"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": @@ -293,7 +293,7 @@ null, null]}}]}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpFlatten": [null, diff --git a/tests/parse_print/autogen-bilals-fixed/48929a67dab909763280169f5d4632b9/stdout.expected b/tests/parse_print/autogen-bilals-fixed/48929a67dab909763280169f5d4632b9/stdout.expected index 0530f0a4f9..9df5b951b4 100644 --- a/tests/parse_print/autogen-bilals-fixed/48929a67dab909763280169f5d4632b9/stdout.expected +++ b/tests/parse_print/autogen-bilals-fixed/48929a67dab909763280169f5d4632b9/stdout.expected @@ -17,13 +17,13 @@ such that /\ (var1_ExplicitVarSizeWithFlags_Values_PartitionAsSet_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMarker_Marker [q1, ..] - var2_1_PartitionAsSet_ExplicitVarSizeWithMarker_Marker -> diff --git a/tests/parse_print/autogen-bilals-fixed/499e079eb49364e5f37956fbd5635887/model.expected.json b/tests/parse_print/autogen-bilals-fixed/499e079eb49364e5f37956fbd5635887/model.expected.json index deb3598acf..0a9287f40e 100644 --- a/tests/parse_print/autogen-bilals-fixed/499e079eb49364e5f37956fbd5635887/model.expected.json +++ b/tests/parse_print/autogen-bilals-fixed/499e079eb49364e5f37956fbd5635887/model.expected.json @@ -805,7 +805,7 @@ []}, 2]}}]}]]}, [{"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": @@ -957,7 +957,7 @@ []}, 4]}}}]]}]}}]]}}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": diff --git a/tests/parse_print/autogen-bilals-fixed/499e079eb49364e5f37956fbd5635887/stdout.expected b/tests/parse_print/autogen-bilals-fixed/499e079eb49364e5f37956fbd5635887/stdout.expected index 99fdc9d2fe..b460ffe778 100644 --- a/tests/parse_print/autogen-bilals-fixed/499e079eb49364e5f37956fbd5635887/stdout.expected +++ b/tests/parse_print/autogen-bilals-fixed/499e079eb49364e5f37956fbd5635887/stdout.expected @@ -53,7 +53,7 @@ such that | q39 : int(1..2)]) | q1 : int(1..7)]), and([q1 + 1 <= var1_FunctionAsRelation_RelationAsSet_ExplicitVarSizeWithMarker_Marker -> - var1_FunctionAsRelation_RelationAsSet_ExplicitVarSizeWithMarker_Values_1_Function1DPartial_Flags[q1, ..] var2_1_PartitionAsSet_ExplicitVarSizeWithMarker_Marker -> diff --git a/tests/parse_print/autogen-bilals-fixed/49c6df33edfc97e3f0f7b81aa6940880/model.expected.json b/tests/parse_print/autogen-bilals-fixed/49c6df33edfc97e3f0f7b81aa6940880/model.expected.json index 3b47073f8f..78477a6e6d 100644 --- a/tests/parse_print/autogen-bilals-fixed/49c6df33edfc97e3f0f7b81aa6940880/model.expected.json +++ b/tests/parse_print/autogen-bilals-fixed/49c6df33edfc97e3f0f7b81aa6940880/model.expected.json @@ -151,7 +151,7 @@ []}, 2]}}]}}]}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": @@ -490,7 +490,7 @@ [{"TagInt": []}, 2]}}]}]]}, [{"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": @@ -520,7 +520,7 @@ 2]}}]}}, null, null]}}]}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": diff --git a/tests/parse_print/autogen-bilals-fixed/49c6df33edfc97e3f0f7b81aa6940880/stdout.expected b/tests/parse_print/autogen-bilals-fixed/49c6df33edfc97e3f0f7b81aa6940880/stdout.expected index 31a91dee5e..9ec7510dc6 100644 --- a/tests/parse_print/autogen-bilals-fixed/49c6df33edfc97e3f0f7b81aa6940880/stdout.expected +++ b/tests/parse_print/autogen-bilals-fixed/49c6df33edfc97e3f0f7b81aa6940880/stdout.expected @@ -11,7 +11,7 @@ such that var1_RelationAsSet_Explicit_1_ExplicitVarSizeWithMarker_Marker[1] = var1_RelationAsSet_Explicit_1_ExplicitVarSizeWithMarker_Marker[2] /\ - var1_RelationAsSet_Explicit_1_ExplicitVarSizeWithMarker_Values[1, ..] @@ -28,10 +28,10 @@ such that | q19 : int(1..2)]) | q17 : int(1..2)]) /\ - (var1_RelationAsSet_Explicit_2_ExplicitVarSizeWithFlags_Flags[1, ..] var1_RelationAsSet_Explicit_1_ExplicitVarSizeWithMarker_Values[q2, 1] < diff --git a/tests/parse_print/autogen-bilals-fixed/4a598ea5ec7744cc20c3a53601371daf/model.expected.json b/tests/parse_print/autogen-bilals-fixed/4a598ea5ec7744cc20c3a53601371daf/model.expected.json index 6d71c18c54..49df3f8549 100644 --- a/tests/parse_print/autogen-bilals-fixed/4a598ea5ec7744cc20c3a53601371daf/model.expected.json +++ b/tests/parse_print/autogen-bilals-fixed/4a598ea5ec7744cc20c3a53601371daf/model.expected.json @@ -1372,7 +1372,7 @@ []}, 2]}}]}]]}, [{"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpFlatten": [null, @@ -1554,7 +1554,7 @@ []}, 2]}}]}]]}]}}]]}}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpFlatten": [null, @@ -1811,7 +1811,7 @@ [{"TagInt": []}, 2]}}]}]]}, [{"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": @@ -1924,7 +1924,7 @@ []}, 2]}}}}]}}]}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": diff --git a/tests/parse_print/autogen-bilals-fixed/4a598ea5ec7744cc20c3a53601371daf/stdout.expected b/tests/parse_print/autogen-bilals-fixed/4a598ea5ec7744cc20c3a53601371daf/stdout.expected index b5984218b1..669a5b2e33 100644 --- a/tests/parse_print/autogen-bilals-fixed/4a598ea5ec7744cc20c3a53601371daf/stdout.expected +++ b/tests/parse_print/autogen-bilals-fixed/4a598ea5ec7744cc20c3a53601371daf/stdout.expected @@ -85,7 +85,7 @@ such that /\ (flatten(var1_PartitionAsSet_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMarker_Values_Function1DPartial_Flags [q5, .., ..]) - var1_PartitionAsSet_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMarker_Values_Function1DPartial_Flags [q7, 1, ..] - var3_2_PartitionAsSet_ExplicitVarSizeWithMarker_Marker -> @@ -77,7 +77,7 @@ such that var3_4_PartitionAsSet_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMarker_Marker[q2] = var3_4_PartitionAsSet_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMarker_Marker[q2 + 1] /\ - var3_4_PartitionAsSet_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMarker_Values[q2, ..] var3_4_PartitionAsSet_ExplicitVarSizeWithMarker_Marker -> diff --git a/tests/parse_print/autogen-bilals-fixed/4b23607e697a7b33b7855bb9e6d8e164/model.expected.json b/tests/parse_print/autogen-bilals-fixed/4b23607e697a7b33b7855bb9e6d8e164/model.expected.json index 22be24e4a2..479ccb279e 100644 --- a/tests/parse_print/autogen-bilals-fixed/4b23607e697a7b33b7855bb9e6d8e164/model.expected.json +++ b/tests/parse_print/autogen-bilals-fixed/4b23607e697a7b33b7855bb9e6d8e164/model.expected.json @@ -815,7 +815,7 @@ []}, 2]}}]}]]}, [{"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": @@ -983,7 +983,7 @@ []}, 2]}}]}]]}, [{"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": @@ -1133,7 +1133,7 @@ []}, 2]}}]}]]}]}}]]}}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": diff --git a/tests/parse_print/autogen-bilals-fixed/4b23607e697a7b33b7855bb9e6d8e164/stdout.expected b/tests/parse_print/autogen-bilals-fixed/4b23607e697a7b33b7855bb9e6d8e164/stdout.expected index ecff948fc0..a62a7bec4d 100644 --- a/tests/parse_print/autogen-bilals-fixed/4b23607e697a7b33b7855bb9e6d8e164/stdout.expected +++ b/tests/parse_print/autogen-bilals-fixed/4b23607e697a7b33b7855bb9e6d8e164/stdout.expected @@ -68,21 +68,21 @@ such that var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q4] = var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q4 + 1] /\ - (var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values_1[q4, ..] var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> diff --git a/tests/parse_print/autogen-bilals-fixed/4be21fd12a8819847cbd51dea1e370a3/model.expected.json b/tests/parse_print/autogen-bilals-fixed/4be21fd12a8819847cbd51dea1e370a3/model.expected.json index 7dd0b2d4bd..e192e37360 100644 --- a/tests/parse_print/autogen-bilals-fixed/4be21fd12a8819847cbd51dea1e370a3/model.expected.json +++ b/tests/parse_print/autogen-bilals-fixed/4be21fd12a8819847cbd51dea1e370a3/model.expected.json @@ -180,7 +180,7 @@ []}, 2]}}]}]]}, [{"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": @@ -232,7 +232,7 @@ null, null]}}]}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": @@ -284,7 +284,7 @@ null, null]}}]}}]]}}}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpFlatten": [null, diff --git a/tests/parse_print/autogen-bilals-fixed/4be21fd12a8819847cbd51dea1e370a3/stdout.expected b/tests/parse_print/autogen-bilals-fixed/4be21fd12a8819847cbd51dea1e370a3/stdout.expected index 0c5576a336..3e70532e56 100644 --- a/tests/parse_print/autogen-bilals-fixed/4be21fd12a8819847cbd51dea1e370a3/stdout.expected +++ b/tests/parse_print/autogen-bilals-fixed/4be21fd12a8819847cbd51dea1e370a3/stdout.expected @@ -17,18 +17,18 @@ such that var4, and([q4 + 1 <= var2_FunctionAsRelation_RelationAsSet_ExplicitVarSizeWithMarker_Marker -> var2_FunctionAsRelation_RelationAsSet_ExplicitVarSizeWithMarker_Values_1_ExplicitVarSizeWithFlags_Flags[q4, ..] - false), var1 <=lex [true; int(1)]) +such that image(function(true --> false), var1 .<= [true; int(1)]) diff --git a/tests/parse_print/autogen-bilals-fixed/4f9ae4ffb009a3b226c8414061bd362f/model.expected.json b/tests/parse_print/autogen-bilals-fixed/4f9ae4ffb009a3b226c8414061bd362f/model.expected.json index d7330d88ff..28102d11da 100644 --- a/tests/parse_print/autogen-bilals-fixed/4f9ae4ffb009a3b226c8414061bd362f/model.expected.json +++ b/tests/parse_print/autogen-bilals-fixed/4f9ae4ffb009a3b226c8414061bd362f/model.expected.json @@ -557,7 +557,7 @@ []}, 2]}}]}]]}, [{"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": @@ -709,7 +709,7 @@ []}, 4]}}}]]}]}}]]}}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": diff --git a/tests/parse_print/autogen-bilals-fixed/4f9ae4ffb009a3b226c8414061bd362f/stdout.expected b/tests/parse_print/autogen-bilals-fixed/4f9ae4ffb009a3b226c8414061bd362f/stdout.expected index 6ad4698c71..4d41bfec15 100644 --- a/tests/parse_print/autogen-bilals-fixed/4f9ae4ffb009a3b226c8414061bd362f/stdout.expected +++ b/tests/parse_print/autogen-bilals-fixed/4f9ae4ffb009a3b226c8414061bd362f/stdout.expected @@ -38,7 +38,7 @@ such that | q28 : int(-4, 4)]) | q1 : int(1..7)]), and([q1 + 1 <= var1_FunctionAsRelation_RelationAsSet_ExplicitVarSizeWithMarker_Marker -> - var1_FunctionAsRelation_RelationAsSet_ExplicitVarSizeWithMarker_Values_1_Function1DPartial_Flags[q1, ..] @@ -79,7 +79,7 @@ such that var3_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q19] = var3_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q19 + 1] /\ - var3_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values_1[q19, ..] var3_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> diff --git a/tests/parse_print/autogen-bilals-fixed/54c995d240bca20d3853847acef38f4b/model.expected.json b/tests/parse_print/autogen-bilals-fixed/54c995d240bca20d3853847acef38f4b/model.expected.json index b471c9d6b8..db19f8b5c6 100644 --- a/tests/parse_print/autogen-bilals-fixed/54c995d240bca20d3853847acef38f4b/model.expected.json +++ b/tests/parse_print/autogen-bilals-fixed/54c995d240bca20d3853847acef38f4b/model.expected.json @@ -1071,7 +1071,7 @@ []}, 2]}}]}]]}, [{"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": @@ -1223,7 +1223,7 @@ []}, 4]}}}]]}]}}]]}}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": diff --git a/tests/parse_print/autogen-bilals-fixed/54c995d240bca20d3853847acef38f4b/stdout.expected b/tests/parse_print/autogen-bilals-fixed/54c995d240bca20d3853847acef38f4b/stdout.expected index 1cc1151af3..cbcb3a31f6 100644 --- a/tests/parse_print/autogen-bilals-fixed/54c995d240bca20d3853847acef38f4b/stdout.expected +++ b/tests/parse_print/autogen-bilals-fixed/54c995d240bca20d3853847acef38f4b/stdout.expected @@ -63,7 +63,7 @@ such that | q47 : int(1..2)]) | q1 : int(1..7)]), and([q1 + 1 <= var1_FunctionAsRelation_RelationAsSet_ExplicitVarSizeWithMarker_Marker -> - var1_FunctionAsRelation_RelationAsSet_ExplicitVarSizeWithMarker_Values_1_Function1DPartial_Flags[q1, ..] - var1_ExplicitWithRepetitionR4_Values_ExplicitVarSizeWithFlags_Flags[q1, ..] var1_ExplicitWithRepetitionR4_Flag -> @@ -82,7 +82,7 @@ such that var2_RelationAsSetR9_ExplicitVarSizeWithMarkerR9_Values_1[q25, q26] = var2_RelationAsSetR9_ExplicitVarSizeWithMarkerR9_Values_1[q25, q26 + 1] /\ - var2_RelationAsSetR9_ExplicitVarSizeWithMarkerR9_Values_2_Function1D[q25, q26, ..] var1_PartitionAsSet_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMarker_Values_Function1DPartial_Flags [q1, q2, ..] - var1_PartitionAsSet_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithFlags_Flags [q6, q7, ..] - - var2_ExplicitVarSizeWithMarker_Values[q10, ..] var2_ExplicitVarSizeWithMarker_Marker -> and([var2_ExplicitVarSizeWithMarker_Values[q11, q27] = false | q27 : int(4, 5)]) @@ -25,7 +25,7 @@ such that var5_ExplicitVarSizeWithFlags_Flags[1] >= -4, 1 = var5_ExplicitVarSizeWithFlags_Flags[1], and([q23 + 1 <= var6_ExplicitVarSizeWithMarker_Marker -> - var6_ExplicitVarSizeWithMarker_Values[q23, ..] var6_ExplicitVarSizeWithMarker_Marker -> and([var6_ExplicitVarSizeWithMarker_Values[q24, q28] = false | q28 : int(0, 1)]) diff --git a/tests/parse_print/autogen-bilals-fixed/5f8abcfb913c155e5fcf9aad1689ee48/model.expected.json b/tests/parse_print/autogen-bilals-fixed/5f8abcfb913c155e5fcf9aad1689ee48/model.expected.json index 10f2d43a31..9c1b5c4c19 100644 --- a/tests/parse_print/autogen-bilals-fixed/5f8abcfb913c155e5fcf9aad1689ee48/model.expected.json +++ b/tests/parse_print/autogen-bilals-fixed/5f8abcfb913c155e5fcf9aad1689ee48/model.expected.json @@ -354,7 +354,7 @@ []}, 1]}}]]}}}}]}}]}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": @@ -1032,7 +1032,7 @@ []}, 1]}}]]}}}}]}}]}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": diff --git a/tests/parse_print/autogen-bilals-fixed/5f8abcfb913c155e5fcf9aad1689ee48/stdout.expected b/tests/parse_print/autogen-bilals-fixed/5f8abcfb913c155e5fcf9aad1689ee48/stdout.expected index 9a52e4b7cd..753a7627af 100644 --- a/tests/parse_print/autogen-bilals-fixed/5f8abcfb913c155e5fcf9aad1689ee48/stdout.expected +++ b/tests/parse_print/autogen-bilals-fixed/5f8abcfb913c155e5fcf9aad1689ee48/stdout.expected @@ -33,7 +33,7 @@ such that var1_ExplicitVarSizeWithMarkerR8_Values_ExplicitWithRepetition_Flag[q1] = var1_ExplicitVarSizeWithMarkerR8_Values_ExplicitWithRepetition_Flag[q1 + 1] /\ - var1_ExplicitVarSizeWithMarkerR8_Values_ExplicitWithRepetition_Values[q1, ..] var1_ExplicitVarSizeWithMarkerR8_Marker -> @@ -78,7 +78,7 @@ such that var3_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q17] = var3_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q17 + 1] /\ - var3_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values_1[q17, ..] var3_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> diff --git a/tests/parse_print/autogen-bilals-fixed/603465a931823cf8433459de2d015883/model.expected.json b/tests/parse_print/autogen-bilals-fixed/603465a931823cf8433459de2d015883/model.expected.json index 7406b6dbcf..f22ab4b65e 100644 --- a/tests/parse_print/autogen-bilals-fixed/603465a931823cf8433459de2d015883/model.expected.json +++ b/tests/parse_print/autogen-bilals-fixed/603465a931823cf8433459de2d015883/model.expected.json @@ -813,7 +813,7 @@ []}, 2]}}]}]]}, [{"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": @@ -981,7 +981,7 @@ []}, 2]}}]}]]}, [{"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": @@ -1131,7 +1131,7 @@ []}, 2]}}]}]]}]}}]]}}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": diff --git a/tests/parse_print/autogen-bilals-fixed/603465a931823cf8433459de2d015883/stdout.expected b/tests/parse_print/autogen-bilals-fixed/603465a931823cf8433459de2d015883/stdout.expected index 26ab55f995..e3de862ffe 100644 --- a/tests/parse_print/autogen-bilals-fixed/603465a931823cf8433459de2d015883/stdout.expected +++ b/tests/parse_print/autogen-bilals-fixed/603465a931823cf8433459de2d015883/stdout.expected @@ -68,21 +68,21 @@ such that var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q4] = var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q4 + 1] /\ - (var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values_1[q4, ..] var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> diff --git a/tests/parse_print/autogen-bilals-fixed/612a3b4f1e02d37d3c58b3ade9b248ef/model.expected.json b/tests/parse_print/autogen-bilals-fixed/612a3b4f1e02d37d3c58b3ade9b248ef/model.expected.json index a4750f341d..34456ab204 100644 --- a/tests/parse_print/autogen-bilals-fixed/612a3b4f1e02d37d3c58b3ade9b248ef/model.expected.json +++ b/tests/parse_print/autogen-bilals-fixed/612a3b4f1e02d37d3c58b3ade9b248ef/model.expected.json @@ -35,7 +35,7 @@ [{"ConstantBool": true}, {"ConstantInt": [{"TagInt": []}, 4]}], [{"ConstantBool": true}, {"ConstantInt": [{"TagInt": []}, 0]}]]}}}]}}, {"Op": - {"MkOpLexLeq": + {"MkOpDotLeq": [{"Constant": {"ConstantAbstract": {"AbsLitMatrix": diff --git a/tests/parse_print/autogen-bilals-fixed/612a3b4f1e02d37d3c58b3ade9b248ef/stdout.expected b/tests/parse_print/autogen-bilals-fixed/612a3b4f1e02d37d3c58b3ade9b248ef/stdout.expected index f822e02678..1ba4fe8315 100644 --- a/tests/parse_print/autogen-bilals-fixed/612a3b4f1e02d37d3c58b3ade9b248ef/stdout.expected +++ b/tests/parse_print/autogen-bilals-fixed/612a3b4f1e02d37d3c58b3ade9b248ef/stdout.expected @@ -5,7 +5,7 @@ such that 3 - 5 > var1, false, (function() : `function bool --> int`) = function(true --> 0, true --> 4, true --> 0), - [false, true, true, false; int(6..9)] <=lex [true, true, false, false, false; int(10..11, 1..3)], + [false, true, true, false; int(6..9)] .<= [true, true, false, false, false; int(10..11, 1..3)], image(function(5 --> true), 3 / var1), true in mset(false), false diff --git a/tests/parse_print/autogen-bilals-fixed/62efe6787e7be32b6775a9054b5e7a90/model.expected.json b/tests/parse_print/autogen-bilals-fixed/62efe6787e7be32b6775a9054b5e7a90/model.expected.json index 623a159818..a966dff4c5 100644 --- a/tests/parse_print/autogen-bilals-fixed/62efe6787e7be32b6775a9054b5e7a90/model.expected.json +++ b/tests/parse_print/autogen-bilals-fixed/62efe6787e7be32b6775a9054b5e7a90/model.expected.json @@ -327,7 +327,7 @@ {"ConstantInt": [{"TagInt": []}, 2]}}]}]]}, [{"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpFlatten": [null, @@ -500,7 +500,7 @@ []}, 3]}}]}]]}]}}]]}}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpFlatten": [null, diff --git a/tests/parse_print/autogen-bilals-fixed/62efe6787e7be32b6775a9054b5e7a90/stdout.expected b/tests/parse_print/autogen-bilals-fixed/62efe6787e7be32b6775a9054b5e7a90/stdout.expected index 5b7490cce7..eeda9f43d2 100644 --- a/tests/parse_print/autogen-bilals-fixed/62efe6787e7be32b6775a9054b5e7a90/stdout.expected +++ b/tests/parse_print/autogen-bilals-fixed/62efe6787e7be32b6775a9054b5e7a90/stdout.expected @@ -27,7 +27,7 @@ such that and([q13 + 1 <= var2_PartitionAsSet_ExplicitVarSizeWithMarker_Marker -> flatten(var2_PartitionAsSet_ExplicitVarSizeWithMarker_Values_Explicit_ExplicitVarSizeWithFlags_Flags [q13, .., ..]) - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> diff --git a/tests/parse_print/autogen-bilals-fixed/67856b9617d62beaf659a45708f21210/model.expected.json b/tests/parse_print/autogen-bilals-fixed/67856b9617d62beaf659a45708f21210/model.expected.json index 8a0cb6b07c..787e707bc0 100644 --- a/tests/parse_print/autogen-bilals-fixed/67856b9617d62beaf659a45708f21210/model.expected.json +++ b/tests/parse_print/autogen-bilals-fixed/67856b9617d62beaf659a45708f21210/model.expected.json @@ -317,7 +317,7 @@ []}, 1]}}]]}}}}]}}]}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpFlatten": [null, diff --git a/tests/parse_print/autogen-bilals-fixed/67856b9617d62beaf659a45708f21210/stdout.expected b/tests/parse_print/autogen-bilals-fixed/67856b9617d62beaf659a45708f21210/stdout.expected index 5b4c650c63..1e0b91a649 100644 --- a/tests/parse_print/autogen-bilals-fixed/67856b9617d62beaf659a45708f21210/stdout.expected +++ b/tests/parse_print/autogen-bilals-fixed/67856b9617d62beaf659a45708f21210/stdout.expected @@ -28,7 +28,7 @@ such that /\ flatten(var2_PartitionAsSetR6_ExplicitVarSizeWithMarkerR5R6_Values_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy [q4, .., ..]) - - flatten(var2_ExplicitVarSizeWithFlags_Values_RelationAsMatrix[q8, .., ..]) diff --git a/tests/parse_print/autogen-bilals-fixed/688d9c5f26c404975d660fcdd262858c/model.expected.json b/tests/parse_print/autogen-bilals-fixed/688d9c5f26c404975d660fcdd262858c/model.expected.json index adf06b2103..53e48cac0e 100644 --- a/tests/parse_print/autogen-bilals-fixed/688d9c5f26c404975d660fcdd262858c/model.expected.json +++ b/tests/parse_print/autogen-bilals-fixed/688d9c5f26c404975d660fcdd262858c/model.expected.json @@ -765,7 +765,7 @@ []}, 2]}}]}]]}, [{"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": @@ -917,7 +917,7 @@ []}, 4]}}}]]}]}}]]}}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": diff --git a/tests/parse_print/autogen-bilals-fixed/688d9c5f26c404975d660fcdd262858c/stdout.expected b/tests/parse_print/autogen-bilals-fixed/688d9c5f26c404975d660fcdd262858c/stdout.expected index c44ab7259e..97f900e3fc 100644 --- a/tests/parse_print/autogen-bilals-fixed/688d9c5f26c404975d660fcdd262858c/stdout.expected +++ b/tests/parse_print/autogen-bilals-fixed/688d9c5f26c404975d660fcdd262858c/stdout.expected @@ -49,7 +49,7 @@ such that | q38 : int(-4, 4)]) | q1 : int(1..7)]), and([q1 + 1 <= var1_FunctionAsRelation_RelationAsSet_ExplicitVarSizeWithMarker_Marker -> - var1_FunctionAsRelation_RelationAsSet_ExplicitVarSizeWithMarker_Values_1_Function1DPartial_Flags[q1, ..] - q_4_ExplicitVarSizeWithMarker_Values_Function1DPartial_Flags[q1, ..] q_4_ExplicitVarSizeWithMarker_Marker -> @@ -53,7 +53,7 @@ such that var1_PartitionAsSet_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMarker_Marker[q3] = var1_PartitionAsSet_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMarker_Marker[q3 + 1] /\ - var1_PartitionAsSet_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMarker_Values[q3, ..] var1_PartitionAsSet_ExplicitVarSizeWithMarker_Marker -> @@ -73,14 +73,14 @@ such that | q4 : int(1..3)]) | q3 : int(1..8)]), and([q5 + 1 <= var2_ExplicitVarSizeWithMarker_Marker -> - var2_ExplicitVarSizeWithMarker_Values_Function1DPartial_Flags[q5, ..] var2_ExplicitVarSizeWithMarker_Marker -> diff --git a/tests/parse_print/autogen-bilals-fixed/6d234926de4bf3efc85ef76d53a68827/model.expected.json b/tests/parse_print/autogen-bilals-fixed/6d234926de4bf3efc85ef76d53a68827/model.expected.json index 0538d40b86..0f1bb76d8a 100644 --- a/tests/parse_print/autogen-bilals-fixed/6d234926de4bf3efc85ef76d53a68827/model.expected.json +++ b/tests/parse_print/autogen-bilals-fixed/6d234926de4bf3efc85ef76d53a68827/model.expected.json @@ -717,7 +717,7 @@ []}, 2]}}]}]]}, [{"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": @@ -885,7 +885,7 @@ []}, 2]}}]}]]}, [{"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": @@ -1035,7 +1035,7 @@ []}, 2]}}]}]]}]}}]]}}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": diff --git a/tests/parse_print/autogen-bilals-fixed/6d234926de4bf3efc85ef76d53a68827/stdout.expected b/tests/parse_print/autogen-bilals-fixed/6d234926de4bf3efc85ef76d53a68827/stdout.expected index 34ddd64ade..ca05df2bfe 100644 --- a/tests/parse_print/autogen-bilals-fixed/6d234926de4bf3efc85ef76d53a68827/stdout.expected +++ b/tests/parse_print/autogen-bilals-fixed/6d234926de4bf3efc85ef76d53a68827/stdout.expected @@ -61,21 +61,21 @@ such that var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q4] = var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q4 + 1] /\ - (var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values_1[q4, ..] var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> diff --git a/tests/parse_print/autogen-bilals-fixed/6e78775adcfd98bd61ddfa72523d20d7/model.expected.json b/tests/parse_print/autogen-bilals-fixed/6e78775adcfd98bd61ddfa72523d20d7/model.expected.json index 5d02abc2ea..a4eb890e6e 100644 --- a/tests/parse_print/autogen-bilals-fixed/6e78775adcfd98bd61ddfa72523d20d7/model.expected.json +++ b/tests/parse_print/autogen-bilals-fixed/6e78775adcfd98bd61ddfa72523d20d7/model.expected.json @@ -757,7 +757,7 @@ []}, 2]}}]}]]}, [{"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": @@ -925,7 +925,7 @@ []}, 2]}}]}]]}, [{"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": @@ -1075,7 +1075,7 @@ []}, 2]}}]}]]}]}}]]}}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": diff --git a/tests/parse_print/autogen-bilals-fixed/6e78775adcfd98bd61ddfa72523d20d7/stdout.expected b/tests/parse_print/autogen-bilals-fixed/6e78775adcfd98bd61ddfa72523d20d7/stdout.expected index e53500b0ae..0e1cfbd0a8 100644 --- a/tests/parse_print/autogen-bilals-fixed/6e78775adcfd98bd61ddfa72523d20d7/stdout.expected +++ b/tests/parse_print/autogen-bilals-fixed/6e78775adcfd98bd61ddfa72523d20d7/stdout.expected @@ -64,21 +64,21 @@ such that var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q4] = var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q4 + 1] /\ - (var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values_1[q4, ..] var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> diff --git a/tests/parse_print/autogen-bilals-fixed/6f115e6ceb931de245d1914a7238a5e1/model.expected.json b/tests/parse_print/autogen-bilals-fixed/6f115e6ceb931de245d1914a7238a5e1/model.expected.json index e756e55968..c893ef83dd 100644 --- a/tests/parse_print/autogen-bilals-fixed/6f115e6ceb931de245d1914a7238a5e1/model.expected.json +++ b/tests/parse_print/autogen-bilals-fixed/6f115e6ceb931de245d1914a7238a5e1/model.expected.json @@ -311,7 +311,7 @@ []}, 1]}}]]}}}}]}}]}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpFlatten": [null, diff --git a/tests/parse_print/autogen-bilals-fixed/6f115e6ceb931de245d1914a7238a5e1/stdout.expected b/tests/parse_print/autogen-bilals-fixed/6f115e6ceb931de245d1914a7238a5e1/stdout.expected index 0be6908d7a..e777e6024a 100644 --- a/tests/parse_print/autogen-bilals-fixed/6f115e6ceb931de245d1914a7238a5e1/stdout.expected +++ b/tests/parse_print/autogen-bilals-fixed/6f115e6ceb931de245d1914a7238a5e1/stdout.expected @@ -28,7 +28,7 @@ such that /\ flatten(var2_PartitionAsSetR6_ExplicitVarSizeWithMarkerR5R6_Values_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy [q4, .., ..]) - var3_PartitionAsSet_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMarker_Values_Function1DPartial_Flags [q1, q2, ..] - - var1_ExplicitVarSizeWithFlagsR7_Values_ExplicitWithFlags_Flags[q1, ..] @@ -85,7 +85,7 @@ such that var3_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q22] = var3_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q22 + 1] /\ - var3_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values_1[q22, ..] var3_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> diff --git a/tests/parse_print/autogen-bilals-fixed/73472b413e1c687c0430a8719e4f016b/model.expected.json b/tests/parse_print/autogen-bilals-fixed/73472b413e1c687c0430a8719e4f016b/model.expected.json index 05d8c1c747..b3fbeed6bb 100644 --- a/tests/parse_print/autogen-bilals-fixed/73472b413e1c687c0430a8719e4f016b/model.expected.json +++ b/tests/parse_print/autogen-bilals-fixed/73472b413e1c687c0430a8719e4f016b/model.expected.json @@ -130,7 +130,7 @@ [{"TagInt": []}, 2]}}]}}]}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpFlatten": [null, @@ -336,7 +336,7 @@ [{"Name": "q5"}, null]}]}}]}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": diff --git a/tests/parse_print/autogen-bilals-fixed/73472b413e1c687c0430a8719e4f016b/stdout.expected b/tests/parse_print/autogen-bilals-fixed/73472b413e1c687c0430a8719e4f016b/stdout.expected index 0217af90df..84209e9d01 100644 --- a/tests/parse_print/autogen-bilals-fixed/73472b413e1c687c0430a8719e4f016b/stdout.expected +++ b/tests/parse_print/autogen-bilals-fixed/73472b413e1c687c0430a8719e4f016b/stdout.expected @@ -13,8 +13,7 @@ such that var6_ExplicitVarSizeWithFlags_Values_PartitionAsSet_ExplicitVarSizeWithMarker_Marker[1] = var6_ExplicitVarSizeWithFlags_Values_PartitionAsSet_ExplicitVarSizeWithMarker_Marker[2] /\ - flatten(var6_ExplicitVarSizeWithFlags_Values_PartitionAsSet_ExplicitVarSizeWithMarker_Values_Explicit[1, .., ..]) - var6_ExplicitVarSizeWithFlags_Values_PartitionAsSet_ExplicitVarSizeWithMarker_Marker[q2] = 0 @@ -28,7 +27,7 @@ such that and([var6_ExplicitVarSizeWithFlags_Flags[q5] -> and([q9 + 1 <= var6_ExplicitVarSizeWithFlags_Values_PartitionAsSet_ExplicitVarSizeWithMarker_Marker[q5] -> var6_ExplicitVarSizeWithFlags_Values_PartitionAsSet_ExplicitVarSizeWithMarker_Values_Explicit[q5, q9, ..] - var2_PartitionAsSet_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMarker_Values_Function1DPartial_Flags [q7, q8, ..] - - var1_RelationAsSet_ExplicitVarSizeWithMarker_Values_1_ExplicitVarSizeWithFlags_Flags[q1, ..] @@ -35,10 +35,10 @@ such that | q24 : int(1..2)]) | q22 : int(1..2)]) /\ - (var1_RelationAsSet_ExplicitVarSizeWithMarker_Values_2_ExplicitVarSizeWithFlags_Flags[q1, ..] var1_RelationAsSet_ExplicitVarSizeWithMarker_Marker -> diff --git a/tests/parse_print/autogen-bilals-fixed/77bf93b23c2e5269471d3e07d2d0eff3/model.expected.json b/tests/parse_print/autogen-bilals-fixed/77bf93b23c2e5269471d3e07d2d0eff3/model.expected.json index 17620e9782..f6dc1054ff 100644 --- a/tests/parse_print/autogen-bilals-fixed/77bf93b23c2e5269471d3e07d2d0eff3/model.expected.json +++ b/tests/parse_print/autogen-bilals-fixed/77bf93b23c2e5269471d3e07d2d0eff3/model.expected.json @@ -1705,7 +1705,7 @@ []}, 2]}}]}]]}, [{"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpFlatten": [null, @@ -1891,7 +1891,7 @@ []}, 16]}}]}]]}]}}]]}}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpFlatten": [null, @@ -2194,7 +2194,7 @@ []}, 2]}}]}]]}, [{"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": @@ -2356,7 +2356,7 @@ {"DomainBool": []}]}}]]}}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": diff --git a/tests/parse_print/autogen-bilals-fixed/77bf93b23c2e5269471d3e07d2d0eff3/stdout.expected b/tests/parse_print/autogen-bilals-fixed/77bf93b23c2e5269471d3e07d2d0eff3/stdout.expected index 4cca3cbb8c..d1d9c39af9 100644 --- a/tests/parse_print/autogen-bilals-fixed/77bf93b23c2e5269471d3e07d2d0eff3/stdout.expected +++ b/tests/parse_print/autogen-bilals-fixed/77bf93b23c2e5269471d3e07d2d0eff3/stdout.expected @@ -109,7 +109,7 @@ such that /\ (flatten(var2_PartitionAsSet_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMarker_Values_Function1DPartial_Flags [q1, .., ..]) - var2_PartitionAsSet_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMarker_Values_Function1DPartial_Flags [q1, q2, ..] - var1_PartitionAsSet_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMarker_Values_Function1DPartial_Flags [q7, 1, ..] - - var1_FunctionAsRelationR3R5_RelationAsSetR3R5_ExplicitVarSizeWithMarkerR3R5_Values_1_Explicit[q6, ..] - (var1_FunctionAsRelationR3R5_RelationAsSetR3R5_ExplicitVarSizeWithMarkerR3R5_Values_1_Explicit[q31, ..] or([q34 <= diff --git a/tests/parse_print/autogen-bilals-fixed/788102a4292eb30458166a213f53d06b/model.expected.json b/tests/parse_print/autogen-bilals-fixed/788102a4292eb30458166a213f53d06b/model.expected.json index 839eb42c6a..c899adaded 100644 --- a/tests/parse_print/autogen-bilals-fixed/788102a4292eb30458166a213f53d06b/model.expected.json +++ b/tests/parse_print/autogen-bilals-fixed/788102a4292eb30458166a213f53d06b/model.expected.json @@ -768,7 +768,7 @@ []}, 2]}}]}]]}, [{"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": @@ -936,7 +936,7 @@ []}, 2]}}]}]]}, [{"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": @@ -1086,7 +1086,7 @@ []}, 2]}}]}]]}]}}]]}}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": diff --git a/tests/parse_print/autogen-bilals-fixed/788102a4292eb30458166a213f53d06b/stdout.expected b/tests/parse_print/autogen-bilals-fixed/788102a4292eb30458166a213f53d06b/stdout.expected index 74512812d0..06f78c0d76 100644 --- a/tests/parse_print/autogen-bilals-fixed/788102a4292eb30458166a213f53d06b/stdout.expected +++ b/tests/parse_print/autogen-bilals-fixed/788102a4292eb30458166a213f53d06b/stdout.expected @@ -64,21 +64,21 @@ such that var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q4] = var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q4 + 1] /\ - (var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values_1[q4, ..] var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> diff --git a/tests/parse_print/autogen-bilals-fixed/7916e2376c2f7a027a1836f83d31e41f/model.expected.json b/tests/parse_print/autogen-bilals-fixed/7916e2376c2f7a027a1836f83d31e41f/model.expected.json index be487c6480..1fc710f9a1 100644 --- a/tests/parse_print/autogen-bilals-fixed/7916e2376c2f7a027a1836f83d31e41f/model.expected.json +++ b/tests/parse_print/autogen-bilals-fixed/7916e2376c2f7a027a1836f83d31e41f/model.expected.json @@ -260,7 +260,7 @@ null]}, {"Constant": {"ConstantInt": [{"TagInt": []}, 1]}}]}}]}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": diff --git a/tests/parse_print/autogen-bilals-fixed/7916e2376c2f7a027a1836f83d31e41f/stdout.expected b/tests/parse_print/autogen-bilals-fixed/7916e2376c2f7a027a1836f83d31e41f/stdout.expected index 4c7e23483b..18dec19900 100644 --- a/tests/parse_print/autogen-bilals-fixed/7916e2376c2f7a027a1836f83d31e41f/stdout.expected +++ b/tests/parse_print/autogen-bilals-fixed/7916e2376c2f7a027a1836f83d31e41f/stdout.expected @@ -17,7 +17,7 @@ such that | q1_Function1D : matrix indexed by [bool] of int(3..5, 4), allDiff(q1_Function1D), false, true]), var1_PartitionAsSet_Explicit_ExplicitVarSizeWithMarker_Marker[1] >= 1, and([q6 + 1 <= var1_PartitionAsSet_Explicit_ExplicitVarSizeWithMarker_Marker[1] -> - var1_PartitionAsSet_Explicit_ExplicitVarSizeWithMarker_Values_Function1D[1, q6, ..] var1_PartitionAsSet_Explicit_ExplicitVarSizeWithMarker_Marker[1] -> diff --git a/tests/parse_print/autogen-bilals-fixed/7b0c8abe457f0fb2a4ff0e27c5acc7ef/model.expected.json b/tests/parse_print/autogen-bilals-fixed/7b0c8abe457f0fb2a4ff0e27c5acc7ef/model.expected.json index 35b0894e16..d854497213 100644 --- a/tests/parse_print/autogen-bilals-fixed/7b0c8abe457f0fb2a4ff0e27c5acc7ef/model.expected.json +++ b/tests/parse_print/autogen-bilals-fixed/7b0c8abe457f0fb2a4ff0e27c5acc7ef/model.expected.json @@ -365,7 +365,7 @@ []}, 1]}}]]}}}}]}}]}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpFlatten": [null, @@ -481,7 +481,7 @@ {"Reference": [{"Name": "q5"}, null]}]}}]}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": diff --git a/tests/parse_print/autogen-bilals-fixed/7b0c8abe457f0fb2a4ff0e27c5acc7ef/stdout.expected b/tests/parse_print/autogen-bilals-fixed/7b0c8abe457f0fb2a4ff0e27c5acc7ef/stdout.expected index d7f96daccb..498be02bb9 100644 --- a/tests/parse_print/autogen-bilals-fixed/7b0c8abe457f0fb2a4ff0e27c5acc7ef/stdout.expected +++ b/tests/parse_print/autogen-bilals-fixed/7b0c8abe457f0fb2a4ff0e27c5acc7ef/stdout.expected @@ -23,11 +23,11 @@ such that var1_PartitionAsSet_Explicit_ExplicitVarSizeWithMarker_Marker[q4] = var1_PartitionAsSet_Explicit_ExplicitVarSizeWithMarker_Marker[q4 + 1] /\ - flatten(var1_PartitionAsSet_Explicit_ExplicitVarSizeWithMarker_Values_Function1D[q4, .., ..]) - var1_PartitionAsSet_Explicit_ExplicitVarSizeWithMarker_Values_Function1D[q5, q6, ..] - var1_FunctionAsRelationR3R4_RelationAsSetR3R4_ExplicitVarSizeWithMarkerR3R4_Values_1_Explicit[q6, ..] - (var1_FunctionAsRelationR3R4_RelationAsSetR3R4_ExplicitVarSizeWithMarkerR3R4_Values_1_Explicit[q36, ..] or([var1_FunctionAsRelationR3R4_RelationAsSetR3R4_ExplicitVarSizeWithMarkerR3R4_Values_2_ExplicitVarSizeWithFlags_Flags diff --git a/tests/parse_print/autogen-bilals-fixed/7c756ce0724280ed59c97a84dd82e7c0/model.expected.json b/tests/parse_print/autogen-bilals-fixed/7c756ce0724280ed59c97a84dd82e7c0/model.expected.json index a30b54b4cb..7dbb233ea4 100644 --- a/tests/parse_print/autogen-bilals-fixed/7c756ce0724280ed59c97a84dd82e7c0/model.expected.json +++ b/tests/parse_print/autogen-bilals-fixed/7c756ce0724280ed59c97a84dd82e7c0/model.expected.json @@ -107,7 +107,7 @@ [{"Constant": {"ConstantAbstract": {"AbsLitTuple": [{"ConstantBool": false}]}}}, {"Constant": {"ConstantInt": [{"TagInt": []}, 1]}}]}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Comprehension": [{"Reference": [{"Name": "l_2"}, null]}, [{"Generator": diff --git a/tests/parse_print/autogen-bilals-fixed/7c756ce0724280ed59c97a84dd82e7c0/stdout.expected b/tests/parse_print/autogen-bilals-fixed/7c756ce0724280ed59c97a84dd82e7c0/stdout.expected index 20b79e6531..15268c3875 100644 --- a/tests/parse_print/autogen-bilals-fixed/7c756ce0724280ed59c97a84dd82e7c0/stdout.expected +++ b/tests/parse_print/autogen-bilals-fixed/7c756ce0724280ed59c97a84dd82e7c0/stdout.expected @@ -7,4 +7,4 @@ find var3: partition (maxNumParts 0, maxPartSize 2) from int(1, 5), matrix indexed by [int(5, 5)] of bool) find var4: set (minSize -3) of partition (maxNumParts 0, minPartSize 4) from int(2, 2) find var5: set (minSize 5, maxSize 5) of tuple (int(2, 4)) -such that tuple (false)[1] > ([l_2 | l_1 : int(4, 2), l_2 : int(2, 5), true] ([l_2 | l_1 : int(4, 2), l_2 : int(2, 5), true] .< [l_3 | l_3 : int(4..5, 4)]) diff --git a/tests/parse_print/autogen-bilals-fixed/7c9328a9df7d3971ebc02d3a5d032831/model.expected.json b/tests/parse_print/autogen-bilals-fixed/7c9328a9df7d3971ebc02d3a5d032831/model.expected.json index 5bd43c414b..edb8b17a05 100644 --- a/tests/parse_print/autogen-bilals-fixed/7c9328a9df7d3971ebc02d3a5d032831/model.expected.json +++ b/tests/parse_print/autogen-bilals-fixed/7c9328a9df7d3971ebc02d3a5d032831/model.expected.json @@ -1076,7 +1076,7 @@ "var2_1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker"}, null]}]}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": @@ -1709,7 +1709,7 @@ {"ConstantInt": [{"TagInt": []}, 2]}}]}]]}, [{"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": @@ -1843,7 +1843,7 @@ {"DomainBool": []}]}}]]}}}, {"Op": - {"MkOpLexLeq": + {"MkOpDotLeq": [{"Op": {"MkOpSlicing": [{"Op": diff --git a/tests/parse_print/autogen-bilals-fixed/7c9328a9df7d3971ebc02d3a5d032831/stdout.expected b/tests/parse_print/autogen-bilals-fixed/7c9328a9df7d3971ebc02d3a5d032831/stdout.expected index f03c45f9ee..96dddd522f 100644 --- a/tests/parse_print/autogen-bilals-fixed/7c9328a9df7d3971ebc02d3a5d032831/stdout.expected +++ b/tests/parse_print/autogen-bilals-fixed/7c9328a9df7d3971ebc02d3a5d032831/stdout.expected @@ -82,7 +82,7 @@ such that >= 1 | q56 : int(1..4)]), and([q7 + 1 <= var2_1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - var2_1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q7, ..] var2_1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> @@ -120,14 +120,14 @@ such that | q17 : int(1..9)]), 3 = var4_1_ExplicitWithRepetition_Flag, and([q24 + 1 <= var5_ExplicitWithRepetitionR10_Flag -> - var5_ExplicitWithRepetitionR10_Values_Function1DPartial_Flags[q24, ..] var5_ExplicitWithRepetitionR10_Flag -> diff --git a/tests/parse_print/autogen-bilals-fixed/7cc8838035af5627767687a2a0dd2023/model.expected.json b/tests/parse_print/autogen-bilals-fixed/7cc8838035af5627767687a2a0dd2023/model.expected.json index a55719fe16..aac0dce5ba 100644 --- a/tests/parse_print/autogen-bilals-fixed/7cc8838035af5627767687a2a0dd2023/model.expected.json +++ b/tests/parse_print/autogen-bilals-fixed/7cc8838035af5627767687a2a0dd2023/model.expected.json @@ -261,7 +261,7 @@ {"ConstantInt": [{"TagInt": []}, 2]}}]}]]}, [{"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": @@ -407,7 +407,7 @@ []}, 3]}}]}]]}]}}]]}}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": @@ -1300,7 +1300,7 @@ []}, 1]}}]]}}}}]}}]}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": diff --git a/tests/parse_print/autogen-bilals-fixed/7cc8838035af5627767687a2a0dd2023/stdout.expected b/tests/parse_print/autogen-bilals-fixed/7cc8838035af5627767687a2a0dd2023/stdout.expected index 07c80f3e68..b092d585fd 100644 --- a/tests/parse_print/autogen-bilals-fixed/7cc8838035af5627767687a2a0dd2023/stdout.expected +++ b/tests/parse_print/autogen-bilals-fixed/7cc8838035af5627767687a2a0dd2023/stdout.expected @@ -27,14 +27,14 @@ such that given2, given1, and([var1_ExplicitVarSizeWithFlagsR7_Flags[q1 + 1] -> - var1_ExplicitVarSizeWithFlagsR7_Values_ExplicitWithFlags_Flags[q1, ..] @@ -83,7 +83,7 @@ such that var3_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q23] = var3_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q23 + 1] /\ - var3_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values_1[q23, ..] var3_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> diff --git a/tests/parse_print/autogen-bilals-fixed/7eeaf2347f1bf8b83db5d0b7c15483e6/model.expected.json b/tests/parse_print/autogen-bilals-fixed/7eeaf2347f1bf8b83db5d0b7c15483e6/model.expected.json index 5db717ffee..ca8bf65fec 100644 --- a/tests/parse_print/autogen-bilals-fixed/7eeaf2347f1bf8b83db5d0b7c15483e6/model.expected.json +++ b/tests/parse_print/autogen-bilals-fixed/7eeaf2347f1bf8b83db5d0b7c15483e6/model.expected.json @@ -1754,7 +1754,7 @@ []}, 2]}}]}]]}, [{"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpFlatten": [null, @@ -1940,7 +1940,7 @@ []}, 16]}}]}]]}]}}]]}}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpFlatten": [null, @@ -2241,7 +2241,7 @@ []}, 2]}}]}]]}, [{"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": @@ -2403,7 +2403,7 @@ {"DomainBool": []}]}}]]}}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": diff --git a/tests/parse_print/autogen-bilals-fixed/7eeaf2347f1bf8b83db5d0b7c15483e6/stdout.expected b/tests/parse_print/autogen-bilals-fixed/7eeaf2347f1bf8b83db5d0b7c15483e6/stdout.expected index 05f3eb9b51..9546096121 100644 --- a/tests/parse_print/autogen-bilals-fixed/7eeaf2347f1bf8b83db5d0b7c15483e6/stdout.expected +++ b/tests/parse_print/autogen-bilals-fixed/7eeaf2347f1bf8b83db5d0b7c15483e6/stdout.expected @@ -114,7 +114,7 @@ such that /\ (flatten(var3_PartitionAsSet_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMarker_Values_Function1DPartial_Flags [q1, .., ..]) - var3_PartitionAsSet_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMarker_Values_Function1DPartial_Flags [q1, q2, ..] - var3_PartitionAsSet_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMarker_Values_Function1DPartial_Flags [q1, q2, ..] - - var1_FunctionAsRelationR3R5_RelationAsSetR3R5_ExplicitVarSizeWithMarkerR3R5_Values_1_Explicit[q6, ..] - (var1_FunctionAsRelationR3R5_RelationAsSetR3R5_ExplicitVarSizeWithMarkerR3R5_Values_1_Explicit[q31, ..] or([q34 <= diff --git a/tests/parse_print/autogen-bilals-fixed/827f1d4ebd57ab718caa032cc8b297fc/model.expected.json b/tests/parse_print/autogen-bilals-fixed/827f1d4ebd57ab718caa032cc8b297fc/model.expected.json index b67746d024..9e216cb486 100644 --- a/tests/parse_print/autogen-bilals-fixed/827f1d4ebd57ab718caa032cc8b297fc/model.expected.json +++ b/tests/parse_print/autogen-bilals-fixed/827f1d4ebd57ab718caa032cc8b297fc/model.expected.json @@ -132,7 +132,7 @@ []}, 2]}}]}]]}, [{"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": @@ -281,7 +281,7 @@ []}, 2]}}]}]]}]}}]]}}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": @@ -721,7 +721,7 @@ []}, 2]}}]}]]}]}}]]}}}]]}}}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": diff --git a/tests/parse_print/autogen-bilals-fixed/827f1d4ebd57ab718caa032cc8b297fc/stdout.expected b/tests/parse_print/autogen-bilals-fixed/827f1d4ebd57ab718caa032cc8b297fc/stdout.expected index dd178e25b3..7cc4bab1b3 100644 --- a/tests/parse_print/autogen-bilals-fixed/827f1d4ebd57ab718caa032cc8b297fc/stdout.expected +++ b/tests/parse_print/autogen-bilals-fixed/827f1d4ebd57ab718caa032cc8b297fc/stdout.expected @@ -11,7 +11,7 @@ such that false, and([q1 + 1 <= var1_FunctionAsRelation_RelationAsSet_ExplicitVarSizeWithMarker_Marker -> var1_FunctionAsRelation_RelationAsSet_ExplicitVarSizeWithMarker_Values_1_ExplicitVarSizeWithFlags_Flags[q1, ..] - var1_FunctionAsRelation_RelationAsSet_ExplicitVarSizeWithMarker_Marker -> diff --git a/tests/parse_print/autogen-bilals-fixed/8367e8de71de185d6acf3e859e23a37b/model.expected.json b/tests/parse_print/autogen-bilals-fixed/8367e8de71de185d6acf3e859e23a37b/model.expected.json index 23c4d83c28..fe0385d6d4 100644 --- a/tests/parse_print/autogen-bilals-fixed/8367e8de71de185d6acf3e859e23a37b/model.expected.json +++ b/tests/parse_print/autogen-bilals-fixed/8367e8de71de185d6acf3e859e23a37b/model.expected.json @@ -684,7 +684,7 @@ {"ConstantInt": [{"TagInt": []}, 1]}}]}}]}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": @@ -966,7 +966,7 @@ {"ConstantInt": [{"TagInt": []}, 2]}}]}]]}, [{"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": @@ -1100,7 +1100,7 @@ {"DomainBool": []}]}}]]}}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": @@ -1601,7 +1601,7 @@ {"ConstantInt": [{"TagInt": []}, 2]}}]}]]}, [{"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": @@ -1753,7 +1753,7 @@ []}, 4]}}]}]]}]}}]]}}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": diff --git a/tests/parse_print/autogen-bilals-fixed/8367e8de71de185d6acf3e859e23a37b/stdout.expected b/tests/parse_print/autogen-bilals-fixed/8367e8de71de185d6acf3e859e23a37b/stdout.expected index ed2dec1bc6..0b430a5d86 100644 --- a/tests/parse_print/autogen-bilals-fixed/8367e8de71de185d6acf3e859e23a37b/stdout.expected +++ b/tests/parse_print/autogen-bilals-fixed/8367e8de71de185d6acf3e859e23a37b/stdout.expected @@ -56,8 +56,7 @@ such that | q61 : int(1..4)]), 1 <= var1_ExplicitVarSizeWithMarker_Marker -> and([q9 + 1 <= var1_ExplicitVarSizeWithMarker_Values_PartitionAsSet_ExplicitVarSizeWithMarker_Marker[1] -> - var1_ExplicitVarSizeWithMarker_Values_PartitionAsSet_ExplicitVarSizeWithMarker_Values_Occurrence[1, q9, ..] - @@ -77,14 +76,14 @@ such that <= 0 | q11 : int(1..4)]), and([var3_ExplicitVarSizeWithFlags_Flags[q32 + 1] -> - var3_ExplicitVarSizeWithFlags_Values_Function1DPartial_Flags[q32, ..] @@ -111,14 +110,14 @@ such that 0 = sum([toInt(var3_ExplicitVarSizeWithFlags_Values_Function1DPartial_Flags[q36, q40]) | q40 : bool]) | q36 : int(1..3)]), and([var4_ExplicitVarSizeWithFlags_Flags[q42 + 1] -> - var4_ExplicitVarSizeWithFlags_Values_Function1DPartial_Flags[q42, ..] diff --git a/tests/parse_print/autogen-bilals-fixed/83e79dafff20cf8bb9bbf4e0e4da6ed2/model.expected.json b/tests/parse_print/autogen-bilals-fixed/83e79dafff20cf8bb9bbf4e0e4da6ed2/model.expected.json index fe6bdcca01..210cc2b0bc 100644 --- a/tests/parse_print/autogen-bilals-fixed/83e79dafff20cf8bb9bbf4e0e4da6ed2/model.expected.json +++ b/tests/parse_print/autogen-bilals-fixed/83e79dafff20cf8bb9bbf4e0e4da6ed2/model.expected.json @@ -902,7 +902,7 @@ []}, 2]}}]}]]}, [{"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": @@ -1039,7 +1039,7 @@ {"DomainBool": []}]}}]]}}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": diff --git a/tests/parse_print/autogen-bilals-fixed/83e79dafff20cf8bb9bbf4e0e4da6ed2/stdout.expected b/tests/parse_print/autogen-bilals-fixed/83e79dafff20cf8bb9bbf4e0e4da6ed2/stdout.expected index 2c2a5d6d33..1e0f4343cb 100644 --- a/tests/parse_print/autogen-bilals-fixed/83e79dafff20cf8bb9bbf4e0e4da6ed2/stdout.expected +++ b/tests/parse_print/autogen-bilals-fixed/83e79dafff20cf8bb9bbf4e0e4da6ed2/stdout.expected @@ -60,7 +60,7 @@ such that | q42 : int(1..2)]) | q1 : int(1..31)]), and([q1 + 1 <= var1_FunctionAsRelation_RelationAsSet_ExplicitVarSizeWithMarker_Marker -> - var1_FunctionAsRelation_RelationAsSet_ExplicitVarSizeWithMarker_Values_1_Function1DPartial_Flags[q1, ..] var1_ExplicitVarSizeWithFlags_Values_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithFlags_Flags [q5, q6, ..] - - var2_ExplicitVarSizeWithMarker_Values[q10, ..] var2_ExplicitVarSizeWithMarker_Marker -> and([var2_ExplicitVarSizeWithMarker_Values[q11, q29] = false | q29 : int(4, 5)]) @@ -25,7 +25,7 @@ such that var5_ExplicitVarSizeWithFlags_Flags[1] >= -4, 1 = var5_ExplicitVarSizeWithFlags_Flags[1], and([var6_ExplicitVarSizeWithFlags_Flags[q23 + 1] -> - var6_ExplicitVarSizeWithFlags_Values[q23, ..] and([var6_ExplicitVarSizeWithFlags_Values[q24, q30] = false | q30 : int(0, 1)]) diff --git a/tests/parse_print/autogen-bilals-fixed/86302603127c6befda9307b173096b8d/model.expected.json b/tests/parse_print/autogen-bilals-fixed/86302603127c6befda9307b173096b8d/model.expected.json index 33e81ac444..69d1741fd9 100644 --- a/tests/parse_print/autogen-bilals-fixed/86302603127c6befda9307b173096b8d/model.expected.json +++ b/tests/parse_print/autogen-bilals-fixed/86302603127c6befda9307b173096b8d/model.expected.json @@ -601,7 +601,7 @@ []}, 1]}}]]}}}}]}}]}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": diff --git a/tests/parse_print/autogen-bilals-fixed/86302603127c6befda9307b173096b8d/stdout.expected b/tests/parse_print/autogen-bilals-fixed/86302603127c6befda9307b173096b8d/stdout.expected index a9442c9cc2..23b5151cf3 100644 --- a/tests/parse_print/autogen-bilals-fixed/86302603127c6befda9307b173096b8d/stdout.expected +++ b/tests/parse_print/autogen-bilals-fixed/86302603127c6befda9307b173096b8d/stdout.expected @@ -48,7 +48,7 @@ such that var3_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q10] = var3_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q10 + 1] /\ - var3_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q10, ..] var3_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> diff --git a/tests/parse_print/autogen-bilals-fixed/877d629f542f55f0f97157cd8c1654fe/model.expected.json b/tests/parse_print/autogen-bilals-fixed/877d629f542f55f0f97157cd8c1654fe/model.expected.json index eb76f4307d..2d2b41eef9 100644 --- a/tests/parse_print/autogen-bilals-fixed/877d629f542f55f0f97157cd8c1654fe/model.expected.json +++ b/tests/parse_print/autogen-bilals-fixed/877d629f542f55f0f97157cd8c1654fe/model.expected.json @@ -906,7 +906,7 @@ []}, 2]}}]}]]}, [{"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": @@ -1043,7 +1043,7 @@ {"DomainBool": []}]}}]]}}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": diff --git a/tests/parse_print/autogen-bilals-fixed/877d629f542f55f0f97157cd8c1654fe/stdout.expected b/tests/parse_print/autogen-bilals-fixed/877d629f542f55f0f97157cd8c1654fe/stdout.expected index eb626634fd..44705dfc24 100644 --- a/tests/parse_print/autogen-bilals-fixed/877d629f542f55f0f97157cd8c1654fe/stdout.expected +++ b/tests/parse_print/autogen-bilals-fixed/877d629f542f55f0f97157cd8c1654fe/stdout.expected @@ -60,7 +60,7 @@ such that | q42 : int(1..2)]) | q1 : int(1..31)]), and([q1 + 1 <= var1_FunctionAsRelation_RelationAsSet_ExplicitVarSizeWithMarker_Marker -> - var1_FunctionAsRelation_RelationAsSet_ExplicitVarSizeWithMarker_Values_1_Function1DPartial_Flags[q1, ..] [5; int(1)]), (false, 1)) <=lex [0; int(1)] +such that image(function((true, 2) --> [5; int(1)]), (false, 1)) .<= [0; int(1)] diff --git a/tests/parse_print/autogen-bilals-fixed/88fb8c6b9616da911eaa4532629f05d7/model.expected.json b/tests/parse_print/autogen-bilals-fixed/88fb8c6b9616da911eaa4532629f05d7/model.expected.json index fc7bdd76e7..614ffbbec4 100644 --- a/tests/parse_print/autogen-bilals-fixed/88fb8c6b9616da911eaa4532629f05d7/model.expected.json +++ b/tests/parse_print/autogen-bilals-fixed/88fb8c6b9616da911eaa4532629f05d7/model.expected.json @@ -428,7 +428,7 @@ []}, 1]}}]]}}}}]}}]}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpFlatten": [null, @@ -681,7 +681,7 @@ [{"Name": "q6"}, null]}]}}]}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": diff --git a/tests/parse_print/autogen-bilals-fixed/88fb8c6b9616da911eaa4532629f05d7/stdout.expected b/tests/parse_print/autogen-bilals-fixed/88fb8c6b9616da911eaa4532629f05d7/stdout.expected index ba882a9fab..aca0039f65 100644 --- a/tests/parse_print/autogen-bilals-fixed/88fb8c6b9616da911eaa4532629f05d7/stdout.expected +++ b/tests/parse_print/autogen-bilals-fixed/88fb8c6b9616da911eaa4532629f05d7/stdout.expected @@ -26,7 +26,7 @@ such that var2_PartitionAsSet_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMarker_Marker[q4] = var2_PartitionAsSet_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMarker_Marker[q4 + 1] /\ - flatten(var2_PartitionAsSet_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMarker_Values[q4, .., ..]) var2_PartitionAsSet_ExplicitVarSizeWithMarker_Marker -> @@ -37,7 +37,7 @@ such that | q5 : int(1..16)]), and([q6 <= var2_PartitionAsSet_ExplicitVarSizeWithMarker_Marker -> and([q7 + 1 <= var2_PartitionAsSet_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMarker_Marker[q6] -> - var2_PartitionAsSet_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMarker_Values[q6, q7, ..] [false, false, true, false; int(2, 4..6)] <=lex [true, false, true; int(2..3, 8)], + image(function({{true}} --> [false, false, true, false; int(2, 4..6)] .<= [true, false, true; int(2..3, 8)], ({} : `set of set of bool`) --> apart({false}, partition({true, false})), {({} : `set of bool`), {true}} --> {false, false} subset {true, false}), {{true} intersect {true, false, true}, party(false >= true, partition({false, false}))}), and([l_3 | l_3 : bool, l_4 : bool, l_3]), (function(mset(2, 0, 3) --> mset(0, 4), mset(4) --> mset(4), mset(1, 3, 4) --> (mset() : `mset of int`)) supset function(mset(3, 3, 1) --> (mset() : `mset of int`), (mset() : `mset of int`) --> mset(1, 2, 2))) - < (flatten([true, false, true, false; int(3..6)]) <=lex [false < true, true <= true; int(4..5)]), + < (flatten([true, false, true, false; int(3..6)]) .<= [false < true, true <= true; int(4..5)]), [tuple (false), tuple (true), tuple (false), tuple (true); int(4, 10, 11, 9)] [([] : `matrix indexed by [int] of int`)[factorial(4)], 1] diff --git a/tests/parse_print/autogen-bilals-fixed/8b18b9af68196441a501019b9212cb97/model.expected.json b/tests/parse_print/autogen-bilals-fixed/8b18b9af68196441a501019b9212cb97/model.expected.json index 00e66c444b..c539c62f5b 100644 --- a/tests/parse_print/autogen-bilals-fixed/8b18b9af68196441a501019b9212cb97/model.expected.json +++ b/tests/parse_print/autogen-bilals-fixed/8b18b9af68196441a501019b9212cb97/model.expected.json @@ -8,7 +8,7 @@ [{"Declaration": {"FindOrGiven": ["Find", {"Name": "unused"}, {"DomainBool": []}]}}, {"SuchThat": [{"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Constant": {"ConstantAbstract": {"AbsLitMatrix": diff --git a/tests/parse_print/autogen-bilals-fixed/8b18b9af68196441a501019b9212cb97/stdout.expected b/tests/parse_print/autogen-bilals-fixed/8b18b9af68196441a501019b9212cb97/stdout.expected index f8851e03dc..d618302d30 100644 --- a/tests/parse_print/autogen-bilals-fixed/8b18b9af68196441a501019b9212cb97/stdout.expected +++ b/tests/parse_print/autogen-bilals-fixed/8b18b9af68196441a501019b9212cb97/stdout.expected @@ -1,4 +1,4 @@ language ESSENCE' 1.0 find unused: bool -such that [false, false; int(1..2)] var1_PartitionAsSet_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMarker_Values_Function1DPartial_Flags [q1, q2, ..] - var1_PartitionAsSet_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMarker_Values_Function1DPartial_Flags [q1, q2, ..] - = 1 | q26 : int(1..2)]), 2 <= var2_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - var2_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[1, ..] var2_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> and([var2_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q10, q19] = 2 diff --git a/tests/parse_print/autogen-bilals-fixed/8e57797389036cafd59682f3b212615f/model.expected.json b/tests/parse_print/autogen-bilals-fixed/8e57797389036cafd59682f3b212615f/model.expected.json index 10deb060bb..01841adc73 100644 --- a/tests/parse_print/autogen-bilals-fixed/8e57797389036cafd59682f3b212615f/model.expected.json +++ b/tests/parse_print/autogen-bilals-fixed/8e57797389036cafd59682f3b212615f/model.expected.json @@ -193,7 +193,7 @@ []}, 2]}}]}]]}, [{"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": @@ -342,7 +342,7 @@ []}, 6]}}]}]]}]}}]]}}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": @@ -2065,7 +2065,7 @@ []}, 1]}}]]}}}}]}}]}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": diff --git a/tests/parse_print/autogen-bilals-fixed/8e57797389036cafd59682f3b212615f/stdout.expected b/tests/parse_print/autogen-bilals-fixed/8e57797389036cafd59682f3b212615f/stdout.expected index 56a9fef731..0f59a09111 100644 --- a/tests/parse_print/autogen-bilals-fixed/8e57797389036cafd59682f3b212615f/stdout.expected +++ b/tests/parse_print/autogen-bilals-fixed/8e57797389036cafd59682f3b212615f/stdout.expected @@ -18,7 +18,7 @@ find var2_3: bool such that and([q1 + 1 <= var1_FunctionAsRelation_RelationAsSet_ExplicitVarSizeWithMarker_Marker -> var1_FunctionAsRelation_RelationAsSet_ExplicitVarSizeWithMarker_Values_1_ExplicitVarSizeWithFlags_Flags[q1, ..] - var2_1_PartitionAsSet_ExplicitVarSizeWithMarker_Marker -> diff --git a/tests/parse_print/autogen-bilals-fixed/8e7aea1c1a683206e6a897c6ad5d8bd3/model.expected.json b/tests/parse_print/autogen-bilals-fixed/8e7aea1c1a683206e6a897c6ad5d8bd3/model.expected.json index 5a4d47f51d..fb22bb4096 100644 --- a/tests/parse_print/autogen-bilals-fixed/8e7aea1c1a683206e6a897c6ad5d8bd3/model.expected.json +++ b/tests/parse_print/autogen-bilals-fixed/8e7aea1c1a683206e6a897c6ad5d8bd3/model.expected.json @@ -228,7 +228,7 @@ []}, 1]}}]]}}}}]}}]}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": diff --git a/tests/parse_print/autogen-bilals-fixed/8e7aea1c1a683206e6a897c6ad5d8bd3/stdout.expected b/tests/parse_print/autogen-bilals-fixed/8e7aea1c1a683206e6a897c6ad5d8bd3/stdout.expected index d802bfd091..f00ce52598 100644 --- a/tests/parse_print/autogen-bilals-fixed/8e7aea1c1a683206e6a897c6ad5d8bd3/stdout.expected +++ b/tests/parse_print/autogen-bilals-fixed/8e7aea1c1a683206e6a897c6ad5d8bd3/stdout.expected @@ -18,7 +18,7 @@ such that /\ var1_FunctionAsRelation_RelationAsSet_ExplicitVarSizeWithMarker_Values_1_ExplicitVarSizeWithMarker_Values [q1, ..] - true, false --> false, true --> false, true --> false, true --> true)), (partition({3}, {3, 4, 3, 5, 3}, {1, 4, 5, 1, 3}, {2, 2}, {1, 1}), tuple (true), ({} : `set of bool`), function(true --> false, false --> true, false --> true, false --> false)))), - flatten(flatten([false, false, false, false, true; int(3, 6, 2, 10, 1)])) ([] : `matrix indexed by [int] of bool`), [false; int(1)] --> [false, false; int(3, 0)], [true, false, true; int(6..8)] --> [true, false, false, false; int(2..3, 0, 11)], diff --git a/tests/parse_print/autogen-bilals-fixed/8f501dda2021fc3c7c4e001157f1e6e6/model.expected.json b/tests/parse_print/autogen-bilals-fixed/8f501dda2021fc3c7c4e001157f1e6e6/model.expected.json index 1ec4a6f1a7..f905840d1e 100644 --- a/tests/parse_print/autogen-bilals-fixed/8f501dda2021fc3c7c4e001157f1e6e6/model.expected.json +++ b/tests/parse_print/autogen-bilals-fixed/8f501dda2021fc3c7c4e001157f1e6e6/model.expected.json @@ -173,7 +173,7 @@ {"ConstantInt": [{"TagInt": []}, 2]}}]}]]}, [{"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": @@ -319,7 +319,7 @@ []}, 4]}}]}]]}]}}]]}}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": @@ -918,7 +918,7 @@ {"ConstantInt": [{"TagInt": []}, 1]}}]]}}}}]}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpFlatten": [null, diff --git a/tests/parse_print/autogen-bilals-fixed/8f501dda2021fc3c7c4e001157f1e6e6/stdout.expected b/tests/parse_print/autogen-bilals-fixed/8f501dda2021fc3c7c4e001157f1e6e6/stdout.expected index 0d50f819e4..952724484f 100644 --- a/tests/parse_print/autogen-bilals-fixed/8f501dda2021fc3c7c4e001157f1e6e6/stdout.expected +++ b/tests/parse_print/autogen-bilals-fixed/8f501dda2021fc3c7c4e001157f1e6e6/stdout.expected @@ -15,14 +15,14 @@ find var6: int(1..4, 4..5) maximising var4 such that and([q1 + 1 <= var1_ExplicitVarSizeWithMarker_Marker -> - var1_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithFlags_Flags[q1, ..] var1_ExplicitVarSizeWithMarker_Marker -> @@ -53,7 +53,7 @@ such that 4 = sum([var1_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithFlags_Flags[q3, q8] | q8 : int(1..4)]) | q3 : int(1..81)]), and([var2_ExplicitVarSizeWithFlags_Flags[q10 + 1] -> - flatten(var2_ExplicitVarSizeWithFlags_Values_RelationAsMatrix[q10, .., ..]) diff --git a/tests/parse_print/autogen-bilals-fixed/90320206b02563fde63fe692179aedbe/model.expected.json b/tests/parse_print/autogen-bilals-fixed/90320206b02563fde63fe692179aedbe/model.expected.json index a8f7728352..13eda9f509 100644 --- a/tests/parse_print/autogen-bilals-fixed/90320206b02563fde63fe692179aedbe/model.expected.json +++ b/tests/parse_print/autogen-bilals-fixed/90320206b02563fde63fe692179aedbe/model.expected.json @@ -160,7 +160,7 @@ []}, 2]}}]}]]}, [{"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": @@ -297,7 +297,7 @@ {"DomainBool": []}]}}]]}}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": @@ -704,7 +704,7 @@ "var1_PartitionAsSet_ExplicitVarSizeWithMarker_Marker"}, null]}]}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": @@ -847,7 +847,7 @@ {"ConstantInt": [{"TagInt": []}, 2]}}]}]]}, [{"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": @@ -981,7 +981,7 @@ {"DomainBool": []}]}}]]}}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": diff --git a/tests/parse_print/autogen-bilals-fixed/90320206b02563fde63fe692179aedbe/stdout.expected b/tests/parse_print/autogen-bilals-fixed/90320206b02563fde63fe692179aedbe/stdout.expected index 839fbffedc..98ce331156 100644 --- a/tests/parse_print/autogen-bilals-fixed/90320206b02563fde63fe692179aedbe/stdout.expected +++ b/tests/parse_print/autogen-bilals-fixed/90320206b02563fde63fe692179aedbe/stdout.expected @@ -14,14 +14,14 @@ such that q_4_ExplicitVarSizeWithMarker_Values_Function1DPartial_Values : matrix indexed by [int(1..4), bool] of int(5), and([q1 + 1 <= q_4_ExplicitVarSizeWithMarker_Marker -> - q_4_ExplicitVarSizeWithMarker_Values_Function1DPartial_Flags[q1, ..] q_4_ExplicitVarSizeWithMarker_Marker -> @@ -42,21 +42,21 @@ such that sum([toInt(var1_PartitionAsSet_ExplicitVarSizeWithMarker_Values_Occurrence[q21, q24]) | q24 : int(0..2)]) >= 1 | q21 : int(1..8)]), and([q10 + 1 <= var1_PartitionAsSet_ExplicitVarSizeWithMarker_Marker -> - var1_PartitionAsSet_ExplicitVarSizeWithMarker_Values_Occurrence[q10, ..] var1_PartitionAsSet_ExplicitVarSizeWithMarker_Marker -> and([var1_PartitionAsSet_ExplicitVarSizeWithMarker_Values_Occurrence[q11, q29] = false | q29 : int(0..2)]) | q11 : int(1..8)]), and([q14 + 1 <= var2_ExplicitVarSizeWithMarker_Marker -> - var2_ExplicitVarSizeWithMarker_Values_Function1DPartial_Flags[q14, ..] var2_ExplicitVarSizeWithMarker_Marker -> diff --git a/tests/parse_print/autogen-bilals-fixed/90955ca420084f220878f52c9a1671bc/model.expected.json b/tests/parse_print/autogen-bilals-fixed/90955ca420084f220878f52c9a1671bc/model.expected.json index b3e5780050..a10a165fbe 100644 --- a/tests/parse_print/autogen-bilals-fixed/90955ca420084f220878f52c9a1671bc/model.expected.json +++ b/tests/parse_print/autogen-bilals-fixed/90955ca420084f220878f52c9a1671bc/model.expected.json @@ -1753,7 +1753,7 @@ []}, 2]}}]}]]}, [{"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpFlatten": [null, @@ -1939,7 +1939,7 @@ []}, 16]}}]}]]}]}}]]}}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpFlatten": [null, @@ -2240,7 +2240,7 @@ []}, 2]}}]}]]}, [{"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": @@ -2402,7 +2402,7 @@ {"DomainBool": []}]}}]]}}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": diff --git a/tests/parse_print/autogen-bilals-fixed/90955ca420084f220878f52c9a1671bc/stdout.expected b/tests/parse_print/autogen-bilals-fixed/90955ca420084f220878f52c9a1671bc/stdout.expected index 18e97d1ded..ea8f6b3c0b 100644 --- a/tests/parse_print/autogen-bilals-fixed/90955ca420084f220878f52c9a1671bc/stdout.expected +++ b/tests/parse_print/autogen-bilals-fixed/90955ca420084f220878f52c9a1671bc/stdout.expected @@ -114,7 +114,7 @@ such that /\ (flatten(var2_PartitionAsSet_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMarker_Values_Function1DPartial_Flags [q1, .., ..]) - var2_PartitionAsSet_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMarker_Values_Function1DPartial_Flags [q1, q2, ..] - var2_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> diff --git a/tests/parse_print/autogen-bilals-fixed/93284da4a4bcb0b65f9af4e148349956/model.expected.json b/tests/parse_print/autogen-bilals-fixed/93284da4a4bcb0b65f9af4e148349956/model.expected.json index 05bff5672c..b9f3c69c0e 100644 --- a/tests/parse_print/autogen-bilals-fixed/93284da4a4bcb0b65f9af4e148349956/model.expected.json +++ b/tests/parse_print/autogen-bilals-fixed/93284da4a4bcb0b65f9af4e148349956/model.expected.json @@ -370,7 +370,7 @@ []}, 2]}}]}]]}, [{"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": @@ -520,7 +520,7 @@ []}, 3]}}]}]]}]}}]]}}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpFlatten": [null, @@ -1384,7 +1384,7 @@ []}, 1]}}]]}}}}]}}]}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": diff --git a/tests/parse_print/autogen-bilals-fixed/93284da4a4bcb0b65f9af4e148349956/stdout.expected b/tests/parse_print/autogen-bilals-fixed/93284da4a4bcb0b65f9af4e148349956/stdout.expected index bfa0c27df4..d171bbc065 100644 --- a/tests/parse_print/autogen-bilals-fixed/93284da4a4bcb0b65f9af4e148349956/stdout.expected +++ b/tests/parse_print/autogen-bilals-fixed/93284da4a4bcb0b65f9af4e148349956/stdout.expected @@ -34,7 +34,7 @@ such that /\ (var4_ExplicitVarSizeWithFlagsR17R5R5_Values_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker [q3, ..] - - var5_ExplicitVarSizeWithMarkerR4_Values_ExplicitVarSizeWithFlags_Flags[q12, ..] var5_ExplicitVarSizeWithMarkerR4_Marker -> diff --git a/tests/parse_print/autogen-bilals-fixed/951d3c18901f9994c032518bb08cd59c/model.expected.json b/tests/parse_print/autogen-bilals-fixed/951d3c18901f9994c032518bb08cd59c/model.expected.json index 8f0fa1b196..cfe12d659a 100644 --- a/tests/parse_print/autogen-bilals-fixed/951d3c18901f9994c032518bb08cd59c/model.expected.json +++ b/tests/parse_print/autogen-bilals-fixed/951d3c18901f9994c032518bb08cd59c/model.expected.json @@ -92,7 +92,7 @@ {"ConstantInt": [{"TagInt": []}, 2]}}]}]]}, [{"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": @@ -347,7 +347,7 @@ []}, 0]}}}]]}]}}]]}}}]]}}}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": diff --git a/tests/parse_print/autogen-bilals-fixed/951d3c18901f9994c032518bb08cd59c/stdout.expected b/tests/parse_print/autogen-bilals-fixed/951d3c18901f9994c032518bb08cd59c/stdout.expected index 67138d9c53..2cb7fc7036 100644 --- a/tests/parse_print/autogen-bilals-fixed/951d3c18901f9994c032518bb08cd59c/stdout.expected +++ b/tests/parse_print/autogen-bilals-fixed/951d3c18901f9994c032518bb08cd59c/stdout.expected @@ -8,7 +8,7 @@ find var1_FunctionAsRelation_RelationAsSet_ExplicitVarSizeWithMarker_Values_2: such that false, and([q1 + 1 <= var1_FunctionAsRelation_RelationAsSet_ExplicitVarSizeWithMarker_Marker -> - var1_FunctionAsRelation_RelationAsSet_ExplicitVarSizeWithMarker_Values_1_Occurrence[q1, ..] @@ -19,7 +19,7 @@ such that var1_FunctionAsRelation_RelationAsSet_ExplicitVarSizeWithMarker_Values_1_Occurrence[q1, q21] | q21 : int(3..5, 0)]) /\ - var1_FunctionAsRelation_RelationAsSet_ExplicitVarSizeWithMarker_Values_2[q1, ..] var1_FunctionAsRelation_RelationAsSet_ExplicitVarSizeWithMarker_Marker -> diff --git a/tests/parse_print/autogen-bilals-fixed/95673ede51a7abf39744fbcc1b3524b5/model.expected.json b/tests/parse_print/autogen-bilals-fixed/95673ede51a7abf39744fbcc1b3524b5/model.expected.json index 43024d3395..7edf959aca 100644 --- a/tests/parse_print/autogen-bilals-fixed/95673ede51a7abf39744fbcc1b3524b5/model.expected.json +++ b/tests/parse_print/autogen-bilals-fixed/95673ede51a7abf39744fbcc1b3524b5/model.expected.json @@ -1010,7 +1010,7 @@ "var2_1_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker"}, null]}]}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": @@ -1436,7 +1436,7 @@ {"ConstantInt": [{"TagInt": []}, 2]}}]}]]}, [{"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": @@ -1570,7 +1570,7 @@ {"DomainBool": []}]}}]]}}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": diff --git a/tests/parse_print/autogen-bilals-fixed/95673ede51a7abf39744fbcc1b3524b5/stdout.expected b/tests/parse_print/autogen-bilals-fixed/95673ede51a7abf39744fbcc1b3524b5/stdout.expected index 5ea6ed4099..2e4e7d4190 100644 --- a/tests/parse_print/autogen-bilals-fixed/95673ede51a7abf39744fbcc1b3524b5/stdout.expected +++ b/tests/parse_print/autogen-bilals-fixed/95673ede51a7abf39744fbcc1b3524b5/stdout.expected @@ -78,7 +78,7 @@ such that >= 1 | q34 : int(1..4)]), and([q7 + 1 <= var2_1_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> - var2_1_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q7, ..] var2_1_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> @@ -96,14 +96,14 @@ such that and([var4_1_ExplicitWithFlags_Flags[q15] = 0 \/ var4_1_ExplicitWithFlags_Flags[q15] >= 0 | q15 : int(1..3)]), 3 = sum([var4_1_ExplicitWithFlags_Flags[q16] | q16 : int(1..3)]), and([var5_ExplicitWithFlagsR10_Flags[q18 + 1] > 0 -> - var5_ExplicitWithFlagsR10_Values_Function1DPartial_Flags[q18, ..] diff --git a/tests/parse_print/autogen-bilals-fixed/9766d2cb8dbc532f788d40e27b2a738f/model.expected.json b/tests/parse_print/autogen-bilals-fixed/9766d2cb8dbc532f788d40e27b2a738f/model.expected.json index cdb14e8bcf..d5f9d4ed80 100644 --- a/tests/parse_print/autogen-bilals-fixed/9766d2cb8dbc532f788d40e27b2a738f/model.expected.json +++ b/tests/parse_print/autogen-bilals-fixed/9766d2cb8dbc532f788d40e27b2a738f/model.expected.json @@ -333,7 +333,7 @@ [{"Constant": {"ConstantBool": false}}, {"Constant": {"ConstantBool": false}}]}}]}}, {"Op": - {"MkOpLexLeq": + {"MkOpDotLeq": [{"Constant": {"ConstantAbstract": {"AbsLitMatrix": diff --git a/tests/parse_print/autogen-bilals-fixed/9766d2cb8dbc532f788d40e27b2a738f/stdout.expected b/tests/parse_print/autogen-bilals-fixed/9766d2cb8dbc532f788d40e27b2a738f/stdout.expected index 19bb7628f8..8fa99572a0 100644 --- a/tests/parse_print/autogen-bilals-fixed/9766d2cb8dbc532f788d40e27b2a738f/stdout.expected +++ b/tests/parse_print/autogen-bilals-fixed/9766d2cb8dbc532f788d40e27b2a738f/stdout.expected @@ -20,5 +20,4 @@ such that or([l_1 | l_1 : bool, l_1]), max(var2) in party(4 / 2, partition({1, 2, 1, 1, 4}, {2, 1, 5, 5}, {2, 3, 0, 3}, {3, 1})), true, - ((false -> true) <-> false <= false) -> - [true; int(2)] <=lex [false, true, false, true, false; int(11..12, 7, 13, 14)] + ((false -> true) <-> false <= false) -> [true; int(2)] .<= [false, true, false, true, false; int(11..12, 7, 13, 14)] diff --git a/tests/parse_print/autogen-bilals-fixed/979854a979c1d69c3dc6653f5b2db319/model.expected.json b/tests/parse_print/autogen-bilals-fixed/979854a979c1d69c3dc6653f5b2db319/model.expected.json index 10397619fc..53e8e2225a 100644 --- a/tests/parse_print/autogen-bilals-fixed/979854a979c1d69c3dc6653f5b2db319/model.expected.json +++ b/tests/parse_print/autogen-bilals-fixed/979854a979c1d69c3dc6653f5b2db319/model.expected.json @@ -228,7 +228,7 @@ []}, 1]}}]]}}}}]}}]}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": diff --git a/tests/parse_print/autogen-bilals-fixed/979854a979c1d69c3dc6653f5b2db319/stdout.expected b/tests/parse_print/autogen-bilals-fixed/979854a979c1d69c3dc6653f5b2db319/stdout.expected index bfeded6799..735d7d8696 100644 --- a/tests/parse_print/autogen-bilals-fixed/979854a979c1d69c3dc6653f5b2db319/stdout.expected +++ b/tests/parse_print/autogen-bilals-fixed/979854a979c1d69c3dc6653f5b2db319/stdout.expected @@ -18,7 +18,7 @@ such that /\ var1_FunctionAsRelation_RelationAsSet_ExplicitVarSizeWithMarker_Values_1_ExplicitVarSizeWithMarker_Values [q1, ..] - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> diff --git a/tests/parse_print/autogen-bilals-fixed/9abdea7380788d3969dc2640d22d213c/model.expected.json b/tests/parse_print/autogen-bilals-fixed/9abdea7380788d3969dc2640d22d213c/model.expected.json index e05cb698f4..828ac9af8d 100644 --- a/tests/parse_print/autogen-bilals-fixed/9abdea7380788d3969dc2640d22d213c/model.expected.json +++ b/tests/parse_print/autogen-bilals-fixed/9abdea7380788d3969dc2640d22d213c/model.expected.json @@ -61,7 +61,7 @@ {"Op": {"MkOpLt": [{"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Constant": {"ConstantAbstract": {"AbsLitMatrix": @@ -253,7 +253,7 @@ {"ConstantBool": true}]]}}]]}}}]]}}}}, {"Constant": {"ConstantBool": true}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpIndexing": [{"Constant": diff --git a/tests/parse_print/autogen-bilals-fixed/9abdea7380788d3969dc2640d22d213c/stdout.expected b/tests/parse_print/autogen-bilals-fixed/9abdea7380788d3969dc2640d22d213c/stdout.expected index bfea6941e1..9fab0cd435 100644 --- a/tests/parse_print/autogen-bilals-fixed/9abdea7380788d3969dc2640d22d213c/stdout.expected +++ b/tests/parse_print/autogen-bilals-fixed/9abdea7380788d3969dc2640d22d213c/stdout.expected @@ -6,7 +6,7 @@ such that ((relation((true, false, true, false)), mset(true, false, false), (partition() : `partition from int`)) != (relation((false, false, true, false)), mset(true), partition({5, 2, 1, 2}))) != - (([true, false; int(5, 4)] relation((true, false, true), (false, true, false), (false, true, true))), @@ -33,7 +33,7 @@ such that true, [[true, true; int(0..1)], [true, true, true; int(1..2, 8)], [true; int(1)]; int(2, 4..5)] [freq(mset(false), false <= true)] - - var1_FunctionAsRelation_RelationAsSet_ExplicitVarSizeWithMarker_Values_1_Function1DPartial_Flags[q1, ..] = 1 | q24 : int(1..16)]), and([q6 + 1 <= var2_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - var2_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q6, ..] var2_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> diff --git a/tests/parse_print/autogen-bilals-fixed/9c55294c0d3d31ba76c9c8253bef3ef8/model.expected.json b/tests/parse_print/autogen-bilals-fixed/9c55294c0d3d31ba76c9c8253bef3ef8/model.expected.json index 2db34ff027..0fbbc8d3ad 100644 --- a/tests/parse_print/autogen-bilals-fixed/9c55294c0d3d31ba76c9c8253bef3ef8/model.expected.json +++ b/tests/parse_print/autogen-bilals-fixed/9c55294c0d3d31ba76c9c8253bef3ef8/model.expected.json @@ -338,7 +338,7 @@ null]}, {"Constant": {"ConstantInt": [{"TagInt": []}, 1]}}]}}]}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": @@ -510,7 +510,7 @@ {"ConstantInt": [{"TagInt": []}, 2]}}]}]]}, [{"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": @@ -644,7 +644,7 @@ {"DomainBool": []}]}}]]}}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": @@ -1280,7 +1280,7 @@ []}, 1]}}]]}}}}]}}]}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": diff --git a/tests/parse_print/autogen-bilals-fixed/9c55294c0d3d31ba76c9c8253bef3ef8/stdout.expected b/tests/parse_print/autogen-bilals-fixed/9c55294c0d3d31ba76c9c8253bef3ef8/stdout.expected index 9610a40a28..710f797707 100644 --- a/tests/parse_print/autogen-bilals-fixed/9c55294c0d3d31ba76c9c8253bef3ef8/stdout.expected +++ b/tests/parse_print/autogen-bilals-fixed/9c55294c0d3d31ba76c9c8253bef3ef8/stdout.expected @@ -28,7 +28,7 @@ such that var1_PartitionAsSet_ExplicitR5_ExplicitVarSizeWithMarker_Marker[1], var1_PartitionAsSet_ExplicitR5_ExplicitVarSizeWithMarker_Marker[1] >= 1, and([q8 + 1 <= var1_PartitionAsSet_ExplicitR5_ExplicitVarSizeWithMarker_Marker[1] -> - var1_PartitionAsSet_ExplicitR5_ExplicitVarSizeWithMarker_Values[1, q8, ..] var1_PartitionAsSet_ExplicitR5_ExplicitVarSizeWithMarker_Marker[1] -> @@ -36,14 +36,14 @@ such that | q9 : int(1..24)]), var1_PartitionAsSet_ExplicitR5_ExplicitVarSizeWithMarker_Marker[1] <= 24, and([q13 + 1 <= var2_ExplicitVarSizeWithMarkerR10_Marker -> - var2_ExplicitVarSizeWithMarkerR10_Values_Function1DPartial_Flags[q13, ..] var2_ExplicitVarSizeWithMarkerR10_Marker -> @@ -85,7 +85,7 @@ such that var4_1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q36] = var4_1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q36 + 1] /\ - var4_1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q36, ..] var4_1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> diff --git a/tests/parse_print/autogen-bilals-fixed/9d9440d946dd0a2494f8ad0ef44d90e4/model.expected.json b/tests/parse_print/autogen-bilals-fixed/9d9440d946dd0a2494f8ad0ef44d90e4/model.expected.json index b06913dbb8..298485443c 100644 --- a/tests/parse_print/autogen-bilals-fixed/9d9440d946dd0a2494f8ad0ef44d90e4/model.expected.json +++ b/tests/parse_print/autogen-bilals-fixed/9d9440d946dd0a2494f8ad0ef44d90e4/model.expected.json @@ -360,7 +360,7 @@ []}, 1]}}]]}}}}]}}]}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": @@ -1030,7 +1030,7 @@ []}, 1]}}]]}}}}]}}]}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": diff --git a/tests/parse_print/autogen-bilals-fixed/9d9440d946dd0a2494f8ad0ef44d90e4/stdout.expected b/tests/parse_print/autogen-bilals-fixed/9d9440d946dd0a2494f8ad0ef44d90e4/stdout.expected index 7d206bc108..3cd7f308f5 100644 --- a/tests/parse_print/autogen-bilals-fixed/9d9440d946dd0a2494f8ad0ef44d90e4/stdout.expected +++ b/tests/parse_print/autogen-bilals-fixed/9d9440d946dd0a2494f8ad0ef44d90e4/stdout.expected @@ -33,7 +33,7 @@ such that var1_ExplicitVarSizeWithMarkerR8_Values_ExplicitWithRepetition_Flag[q1] = var1_ExplicitVarSizeWithMarkerR8_Values_ExplicitWithRepetition_Flag[q1 + 1] /\ - var1_ExplicitVarSizeWithMarkerR8_Values_ExplicitWithRepetition_Values[q1, ..] var1_ExplicitVarSizeWithMarkerR8_Marker -> @@ -76,7 +76,7 @@ such that var3_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q18] = var3_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q18 + 1] /\ - var3_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values_1[q18, ..] var3_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> diff --git a/tests/parse_print/autogen-bilals-fixed/9f0da0c4289dcd010e92c8ab6d50b07a/model.expected.json b/tests/parse_print/autogen-bilals-fixed/9f0da0c4289dcd010e92c8ab6d50b07a/model.expected.json index 7970eb6869..4f4ca42d87 100644 --- a/tests/parse_print/autogen-bilals-fixed/9f0da0c4289dcd010e92c8ab6d50b07a/model.expected.json +++ b/tests/parse_print/autogen-bilals-fixed/9f0da0c4289dcd010e92c8ab6d50b07a/model.expected.json @@ -124,7 +124,7 @@ {"ConstantInt": [{"TagInt": []}, 2]}}]}]]}, [{"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": @@ -288,7 +288,7 @@ []}, 2]}}]}]]}, [{"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpFlatten": [null, @@ -466,7 +466,7 @@ []}, 5]}}]}]]}]}}]]}}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpFlatten": [null, @@ -857,7 +857,7 @@ []}, 2]}}]}]]}, [{"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": @@ -1011,7 +1011,7 @@ []}, 1]}}]}}]}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": diff --git a/tests/parse_print/autogen-bilals-fixed/9f0da0c4289dcd010e92c8ab6d50b07a/stdout.expected b/tests/parse_print/autogen-bilals-fixed/9f0da0c4289dcd010e92c8ab6d50b07a/stdout.expected index a928ecdd3d..ff38c3bcf0 100644 --- a/tests/parse_print/autogen-bilals-fixed/9f0da0c4289dcd010e92c8ab6d50b07a/stdout.expected +++ b/tests/parse_print/autogen-bilals-fixed/9f0da0c4289dcd010e92c8ab6d50b07a/stdout.expected @@ -9,7 +9,7 @@ find var1_ExplicitVarSizeWithFlags_Values_ExplicitVarSizeWithFlags_Values_Explic matrix indexed by [int(1..3), int(1..5), int(1)] of bool such that and([var1_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - var1_ExplicitVarSizeWithFlags_Values_ExplicitVarSizeWithFlags_Flags[q1, ..] var1_ExplicitVarSizeWithFlags_Values_ExplicitVarSizeWithFlags_Values_ExplicitVarSizeWithFlags_Flags [q5, q6, ..] - - var1_FunctionAsRelation_RelationAsSet_ExplicitVarSizeWithMarker_Values_1_Function1DPartial_Flags[q1, ..] var1_1_PartitionAsSet_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMarker_Values_Function1D [q6, q7, ..] - - flatten(var1_RelationAsSetR15_ExplicitVarSizeWithMarkerR15_Values_1_RelationAsMatrix[q1, .., ..]) var1_RelationAsSetR15_ExplicitVarSizeWithMarkerR15_Marker -> @@ -54,7 +54,7 @@ such that var2_RelationAsSet_ExplicitVarSizeWithMarker_Values_2[q8] = var2_RelationAsSet_ExplicitVarSizeWithMarker_Values_2[q8 + 1] /\ - var2_RelationAsSet_ExplicitVarSizeWithMarker_Values_3[q8, ..] var2_RelationAsSet_ExplicitVarSizeWithMarker_Marker -> diff --git a/tests/parse_print/autogen-bilals-fixed/a278490eff4c7aaa3efb73ab7cb5a355/model.expected.json b/tests/parse_print/autogen-bilals-fixed/a278490eff4c7aaa3efb73ab7cb5a355/model.expected.json index 9795616ce5..f1fad67520 100644 --- a/tests/parse_print/autogen-bilals-fixed/a278490eff4c7aaa3efb73ab7cb5a355/model.expected.json +++ b/tests/parse_print/autogen-bilals-fixed/a278490eff4c7aaa3efb73ab7cb5a355/model.expected.json @@ -379,7 +379,7 @@ {"ConstantInt": [{"TagInt": []}, 2]}}]}]]}, [{"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": @@ -549,7 +549,7 @@ []}, 2]}}]}]]}, [{"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": diff --git a/tests/parse_print/autogen-bilals-fixed/a278490eff4c7aaa3efb73ab7cb5a355/stdout.expected b/tests/parse_print/autogen-bilals-fixed/a278490eff4c7aaa3efb73ab7cb5a355/stdout.expected index e8b020727f..f11700e67e 100644 --- a/tests/parse_print/autogen-bilals-fixed/a278490eff4c7aaa3efb73ab7cb5a355/stdout.expected +++ b/tests/parse_print/autogen-bilals-fixed/a278490eff4c7aaa3efb73ab7cb5a355/stdout.expected @@ -22,14 +22,14 @@ such that | q10 : int(1..9)]), 3 <= sum([var3_2_ExplicitVarSizeWithFlags_Flags[q12] | q12 : int(1..10)]), and([q14 + 1 <= var4_RelationAsSet_ExplicitVarSizeWithMarker_Marker -> - var4_RelationAsSet_ExplicitVarSizeWithMarker_Values_1[q14, ..] flatten(var2_PartitionAsSet_ExplicitVarSizeWithMarker_Values_Explicit_ExplicitVarSizeWithFlags_Flags [q13, .., ..]) - var1_FunctionAsRelation_RelationAsSet_ExplicitVarSizeWithMarker_Values_1_ExplicitVarSizeWithFlags_Flags[q1, ..] - - flatten(var2_ExplicitVarSizeWithMarker_Values_RelationAsMatrix[q8, .., ..]) var2_ExplicitVarSizeWithMarker_Marker -> diff --git a/tests/parse_print/autogen-bilals-fixed/a34c8275c1d9524a08d2ec1d329ed35a/model.expected.json b/tests/parse_print/autogen-bilals-fixed/a34c8275c1d9524a08d2ec1d329ed35a/model.expected.json index 3014a28020..300839392b 100644 --- a/tests/parse_print/autogen-bilals-fixed/a34c8275c1d9524a08d2ec1d329ed35a/model.expected.json +++ b/tests/parse_print/autogen-bilals-fixed/a34c8275c1d9524a08d2ec1d329ed35a/model.expected.json @@ -910,7 +910,7 @@ []}, 2]}}]}]]}, [{"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": @@ -1047,7 +1047,7 @@ {"DomainBool": []}]}}]]}}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": diff --git a/tests/parse_print/autogen-bilals-fixed/a34c8275c1d9524a08d2ec1d329ed35a/stdout.expected b/tests/parse_print/autogen-bilals-fixed/a34c8275c1d9524a08d2ec1d329ed35a/stdout.expected index 5f2b88f884..52d88fba1f 100644 --- a/tests/parse_print/autogen-bilals-fixed/a34c8275c1d9524a08d2ec1d329ed35a/stdout.expected +++ b/tests/parse_print/autogen-bilals-fixed/a34c8275c1d9524a08d2ec1d329ed35a/stdout.expected @@ -60,7 +60,7 @@ such that | q45 : int(1..2)]) | q1 : int(1..31)]), and([q1 + 1 <= var1_FunctionAsRelation_RelationAsSet_ExplicitVarSizeWithMarker_Marker -> - var1_FunctionAsRelation_RelationAsSet_ExplicitVarSizeWithMarker_Values_1_Function1DPartial_Flags[q1, ..] = 1 | q56 : int(1..4)]), and([q7 + 1 <= var2_1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - var2_1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q7, ..] var2_1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> @@ -124,14 +124,14 @@ such that | q17 : int(1..9)]), 3 = var4_1_ExplicitWithRepetition_Flag, and([q24 + 1 <= var5_ExplicitWithRepetitionR10_Flag -> - var5_ExplicitWithRepetitionR10_Values_Function1DPartial_Flags[q24, ..] var5_ExplicitWithRepetitionR10_Flag -> diff --git a/tests/parse_print/autogen-bilals-fixed/a370966830e4e6e3d5c258cbed1908e2/model.expected.json b/tests/parse_print/autogen-bilals-fixed/a370966830e4e6e3d5c258cbed1908e2/model.expected.json index 24cc1e8a16..a460c6c7c6 100644 --- a/tests/parse_print/autogen-bilals-fixed/a370966830e4e6e3d5c258cbed1908e2/model.expected.json +++ b/tests/parse_print/autogen-bilals-fixed/a370966830e4e6e3d5c258cbed1908e2/model.expected.json @@ -1879,7 +1879,7 @@ []}, 2]}}]}]]}, [{"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpFlatten": [null, @@ -2078,7 +2078,7 @@ []}, 16]}}]}]]}]}}]]}}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpFlatten": [null, @@ -2405,7 +2405,7 @@ []}, 2]}}]}]]}, [{"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": @@ -2580,7 +2580,7 @@ []}, 4]}}}]]}]}}]]}}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": diff --git a/tests/parse_print/autogen-bilals-fixed/a370966830e4e6e3d5c258cbed1908e2/stdout.expected b/tests/parse_print/autogen-bilals-fixed/a370966830e4e6e3d5c258cbed1908e2/stdout.expected index 539dbc6eba..59e87fc369 100644 --- a/tests/parse_print/autogen-bilals-fixed/a370966830e4e6e3d5c258cbed1908e2/stdout.expected +++ b/tests/parse_print/autogen-bilals-fixed/a370966830e4e6e3d5c258cbed1908e2/stdout.expected @@ -113,7 +113,7 @@ such that /\ (flatten(var1_PartitionAsSet_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMarker_Values_Function1DPartial_Flags [q1, .., ..]) - var1_PartitionAsSet_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMarker_Values_Function1DPartial_Flags [q1, q2, ..] - = 1 | q37 : int(1..4)]), and([q7 + 1 <= var2_1_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> - var2_1_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q7, ..] var2_1_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> @@ -109,14 +109,14 @@ such that | q14 : int(1..9)]), 3 = var4_1_ExplicitWithRepetition_Flag, and([var5_ExplicitWithFlagsR10_Flags[q21 + 1] > 0 -> - var5_ExplicitWithFlagsR10_Values_Function1DPartial_Flags[q21, ..] diff --git a/tests/parse_print/autogen-bilals-fixed/a569624863aa273c01c6312a624723f1/model.expected.json b/tests/parse_print/autogen-bilals-fixed/a569624863aa273c01c6312a624723f1/model.expected.json index ce2662ebec..89229fae34 100644 --- a/tests/parse_print/autogen-bilals-fixed/a569624863aa273c01c6312a624723f1/model.expected.json +++ b/tests/parse_print/autogen-bilals-fixed/a569624863aa273c01c6312a624723f1/model.expected.json @@ -759,7 +759,7 @@ []}, 1]}}]]}}}}]}}]}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": @@ -1330,7 +1330,7 @@ []}, 1]}}]]}}}}]}}]}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": diff --git a/tests/parse_print/autogen-bilals-fixed/a569624863aa273c01c6312a624723f1/stdout.expected b/tests/parse_print/autogen-bilals-fixed/a569624863aa273c01c6312a624723f1/stdout.expected index ebe55665f5..29e31c88f1 100644 --- a/tests/parse_print/autogen-bilals-fixed/a569624863aa273c01c6312a624723f1/stdout.expected +++ b/tests/parse_print/autogen-bilals-fixed/a569624863aa273c01c6312a624723f1/stdout.expected @@ -49,7 +49,7 @@ such that var3_2_PartitionAsSet_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMarker_Marker[q3] = var3_2_PartitionAsSet_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMarker_Marker[q3 + 1] /\ - var3_2_PartitionAsSet_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMarker_Values[q3, ..] var3_2_PartitionAsSet_ExplicitVarSizeWithMarker_Marker -> @@ -84,7 +84,7 @@ such that var3_4_PartitionAsSet_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMarker_Marker[q3] = var3_4_PartitionAsSet_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMarker_Marker[q3 + 1] /\ - var3_4_PartitionAsSet_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMarker_Values[q3, ..] var3_4_PartitionAsSet_ExplicitVarSizeWithMarker_Marker -> diff --git a/tests/parse_print/autogen-bilals-fixed/a5da41200401440fbed34793aaf4a1f9/model.expected.json b/tests/parse_print/autogen-bilals-fixed/a5da41200401440fbed34793aaf4a1f9/model.expected.json index 5585fa748d..d12f26ea00 100644 --- a/tests/parse_print/autogen-bilals-fixed/a5da41200401440fbed34793aaf4a1f9/model.expected.json +++ b/tests/parse_print/autogen-bilals-fixed/a5da41200401440fbed34793aaf4a1f9/model.expected.json @@ -2252,7 +2252,7 @@ []}, 2]}}]}]]}, [{"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpFlatten": [null, @@ -2450,7 +2450,7 @@ []}, 8]}}]}]]}]}}]]}}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpFlatten": [null, @@ -2775,7 +2775,7 @@ []}, 2]}}]}]]}, [{"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": @@ -2949,7 +2949,7 @@ []}, 4]}}]}]]}]}}]]}}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": diff --git a/tests/parse_print/autogen-bilals-fixed/a5da41200401440fbed34793aaf4a1f9/stdout.expected b/tests/parse_print/autogen-bilals-fixed/a5da41200401440fbed34793aaf4a1f9/stdout.expected index 5b122fbfd3..8b58571f36 100644 --- a/tests/parse_print/autogen-bilals-fixed/a5da41200401440fbed34793aaf4a1f9/stdout.expected +++ b/tests/parse_print/autogen-bilals-fixed/a5da41200401440fbed34793aaf4a1f9/stdout.expected @@ -125,7 +125,7 @@ such that /\ (flatten(var2_PartitionAsSet_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMarker_Values_Function1DPartial_Flags [q5, .., ..]) - var2_PartitionAsSet_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMarker_Values_Function1DPartial_Flags [q7, q8, ..] - @@ -96,7 +96,7 @@ such that var4_2_PartitionAsSet_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMarker_Marker[q11] = var4_2_PartitionAsSet_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMarker_Marker[q11 + 1] /\ - var4_2_PartitionAsSet_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMarker_Values[q11, ..] var4_2_PartitionAsSet_ExplicitVarSizeWithMarker_Marker -> @@ -156,7 +156,7 @@ such that /\ (var5_PartitionAsSet_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMarker_Marker [q21, ..] - - var2_PartitionAsSet_ExplicitVarSizeWithMarker_Values_Explicit_ExplicitVarSizeWithMarker_Marker[q4, ..] - var1_FunctionAsRelation_RelationAsSet_ExplicitVarSizeWithMarker_Values_1_Function1DPartial_Flags[q1, ..] var1_PartitionAsSet_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithFlags_Flags [q7, q8, ..] - var4_PartitionAsSet_ExplicitVarSizeWithMarker_Marker -> diff --git a/tests/parse_print/autogen-bilals-fixed/ab828d5a7f3d31d42bf66810cab3da9b/model.expected.json b/tests/parse_print/autogen-bilals-fixed/ab828d5a7f3d31d42bf66810cab3da9b/model.expected.json index e88e8e2a78..9d618fc74e 100644 --- a/tests/parse_print/autogen-bilals-fixed/ab828d5a7f3d31d42bf66810cab3da9b/model.expected.json +++ b/tests/parse_print/autogen-bilals-fixed/ab828d5a7f3d31d42bf66810cab3da9b/model.expected.json @@ -722,7 +722,7 @@ []}, 1]}}]]}}}}]}}]}}]]}}}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": @@ -994,7 +994,7 @@ [{"TagInt": []}, 2]}}]}}]}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpFlatten": [null, @@ -1201,7 +1201,7 @@ [{"Name": "q11"}, null]}]}}]}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": diff --git a/tests/parse_print/autogen-bilals-fixed/ab828d5a7f3d31d42bf66810cab3da9b/stdout.expected b/tests/parse_print/autogen-bilals-fixed/ab828d5a7f3d31d42bf66810cab3da9b/stdout.expected index b998173ff1..8f0421eefb 100644 --- a/tests/parse_print/autogen-bilals-fixed/ab828d5a7f3d31d42bf66810cab3da9b/stdout.expected +++ b/tests/parse_print/autogen-bilals-fixed/ab828d5a7f3d31d42bf66810cab3da9b/stdout.expected @@ -42,7 +42,7 @@ such that var5_RelationAsSet_ExplicitVarSizeWithMarker_Values_1_3[q3 + 1]; int(1..3)]) /\ - var5_RelationAsSet_ExplicitVarSizeWithMarker_Values_2[q3, ..] var5_RelationAsSet_ExplicitVarSizeWithMarker_Marker -> @@ -60,8 +60,7 @@ such that var6_ExplicitVarSizeWithFlags_Values_PartitionAsSet_ExplicitVarSizeWithMarker_Marker[1] = var6_ExplicitVarSizeWithFlags_Values_PartitionAsSet_ExplicitVarSizeWithMarker_Marker[2] /\ - flatten(var6_ExplicitVarSizeWithFlags_Values_PartitionAsSet_ExplicitVarSizeWithMarker_Values_Explicit[1, .., ..]) - var6_ExplicitVarSizeWithFlags_Values_PartitionAsSet_ExplicitVarSizeWithMarker_Marker[q8] = 0 @@ -76,7 +75,7 @@ such that and([q15 + 1 <= var6_ExplicitVarSizeWithFlags_Values_PartitionAsSet_ExplicitVarSizeWithMarker_Marker[q11] -> var6_ExplicitVarSizeWithFlags_Values_PartitionAsSet_ExplicitVarSizeWithMarker_Values_Explicit [q11, q15, ..] - var2_FunctionAsRelation_RelationAsSet_ExplicitVarSizeWithMarker_Values_1_ExplicitVarSizeWithFlags_Flags[q1, ..] - var1_PartitionAsSet_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMarker_Values_Occurrence [q7, q8, ..] - var4_PartitionAsSet_ExplicitVarSizeWithMarker_Marker -> diff --git a/tests/parse_print/autogen-bilals-fixed/ae18a4a435dc69d385d04a00db890160/model.expected.json b/tests/parse_print/autogen-bilals-fixed/ae18a4a435dc69d385d04a00db890160/model.expected.json index e81b8215c5..86aa99faba 100644 --- a/tests/parse_print/autogen-bilals-fixed/ae18a4a435dc69d385d04a00db890160/model.expected.json +++ b/tests/parse_print/autogen-bilals-fixed/ae18a4a435dc69d385d04a00db890160/model.expected.json @@ -2259,7 +2259,7 @@ []}, 2]}}]}]]}, [{"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpFlatten": [null, @@ -2461,7 +2461,7 @@ []}, 16]}}]}]]}]}}]]}}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpFlatten": [null, @@ -2796,7 +2796,7 @@ []}, 2]}}]}]]}, [{"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": @@ -2974,7 +2974,7 @@ []}, 1]}}}}]}]]}]}}]]}}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": diff --git a/tests/parse_print/autogen-bilals-fixed/ae18a4a435dc69d385d04a00db890160/stdout.expected b/tests/parse_print/autogen-bilals-fixed/ae18a4a435dc69d385d04a00db890160/stdout.expected index ea4784a032..6abdce5627 100644 --- a/tests/parse_print/autogen-bilals-fixed/ae18a4a435dc69d385d04a00db890160/stdout.expected +++ b/tests/parse_print/autogen-bilals-fixed/ae18a4a435dc69d385d04a00db890160/stdout.expected @@ -122,7 +122,7 @@ such that /\ (flatten(var3_PartitionAsSet_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMarker_Values_Function1DPartial_Flags [q1, .., ..]) - var3_PartitionAsSet_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMarker_Values_Function1DPartial_Flags [q1, q2, ..] - - var1_ExplicitVarSizeWithMarker_Values_Function1D[q1, ..] var1_ExplicitVarSizeWithMarker_Marker -> @@ -56,7 +56,7 @@ such that and([q10 + 1 <= var2_PartitionAsSet_ExplicitVarSizeWithMarker_Marker -> flatten(var2_PartitionAsSet_ExplicitVarSizeWithMarker_Values_Explicit_ExplicitVarSizeWithFlags_Flags [q10, .., ..]) - var3_PartitionAsSet_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMarker_Values_Function1DPartial_Flags [q1, q2, ..] - var1_PartitionAsSet_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMarker_Values_Function1DPartial_Flags [q7, q8, ..] - - var2_RelationAsSet_ExplicitVarSizeWithMarker_Values_1_Occurrence[q1, ..] @@ -69,7 +69,7 @@ such that var4_2_PartitionAsSet_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMarker_Marker[q9] = var4_2_PartitionAsSet_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMarker_Marker[q9 + 1] /\ - var4_2_PartitionAsSet_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMarker_Values[q9, ..] var4_2_PartitionAsSet_ExplicitVarSizeWithMarker_Marker -> @@ -128,7 +128,7 @@ such that /\ (flatten(var5_PartitionAsSet_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithFlags_Flags [q19, .., ..]) - var5_PartitionAsSet_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithFlags_Flags [q21, q22, ..] - tuple (mset(false, false)), false --> tuple (mset(true, false, false))), - [4 | l_1 : int(5, 3), l_2 : int(3, 4)] <=lex [3, 4, 1, 0; int(1, 6..8)]) + [4 | l_1 : int(5, 3), l_2 : int(3, 4)] .<= [3, 4, 1, 0; int(1, 6..8)]) [1] supsetEq mset(true), (function() : `function relation of (mset of bool * diff --git a/tests/parse_print/autogen-bilals-fixed/b3e5efec04851a6556b23a0d4a9f50d0/model.expected.json b/tests/parse_print/autogen-bilals-fixed/b3e5efec04851a6556b23a0d4a9f50d0/model.expected.json index 52df3312dc..9d67882db0 100644 --- a/tests/parse_print/autogen-bilals-fixed/b3e5efec04851a6556b23a0d4a9f50d0/model.expected.json +++ b/tests/parse_print/autogen-bilals-fixed/b3e5efec04851a6556b23a0d4a9f50d0/model.expected.json @@ -322,7 +322,7 @@ null]}, {"Constant": {"ConstantInt": [{"TagInt": []}, 1]}}]}}]}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": @@ -506,7 +506,7 @@ [{"Reference": [{"Name": "var3_ExplicitVarSizeWithFlags_Flags"}, null]}, {"Constant": {"ConstantInt": [{"TagInt": []}, 2]}}]}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpFlatten": [null, diff --git a/tests/parse_print/autogen-bilals-fixed/b3e5efec04851a6556b23a0d4a9f50d0/stdout.expected b/tests/parse_print/autogen-bilals-fixed/b3e5efec04851a6556b23a0d4a9f50d0/stdout.expected index 9fa1ad0d4d..d636d0b2ef 100644 --- a/tests/parse_print/autogen-bilals-fixed/b3e5efec04851a6556b23a0d4a9f50d0/stdout.expected +++ b/tests/parse_print/autogen-bilals-fixed/b3e5efec04851a6556b23a0d4a9f50d0/stdout.expected @@ -23,7 +23,7 @@ such that | q1_Function1D : matrix indexed by [bool] of int(3..5, 4), allDiff(q1_Function1D), false, true]), var1_PartitionAsSet_Explicit_ExplicitVarSizeWithMarker_Marker[1] >= 1, and([q6 + 1 <= var1_PartitionAsSet_Explicit_ExplicitVarSizeWithMarker_Marker[1] -> - var1_PartitionAsSet_Explicit_ExplicitVarSizeWithMarker_Values_Function1D[1, q6, ..] var1_PartitionAsSet_Explicit_ExplicitVarSizeWithMarker_Marker[1] -> @@ -34,7 +34,7 @@ such that | q8 : int(1..256)]), and([q8 <= var1_PartitionAsSet_Explicit_ExplicitVarSizeWithMarker_Marker[1] -> false | q8 : int(1..256)]), var3_ExplicitVarSizeWithFlags_Flags[2] -> - flatten(var3_ExplicitVarSizeWithFlags_Values_RelationAsMatrix[1, .., .., .., ..]) and([and([and([and([var3_ExplicitVarSizeWithFlags_Values_RelationAsMatrix[q11, q39, q40, q41, q42] = false diff --git a/tests/parse_print/autogen-bilals-fixed/b427cac47c65e49ff32c22d2b3e8c19b/model.expected.json b/tests/parse_print/autogen-bilals-fixed/b427cac47c65e49ff32c22d2b3e8c19b/model.expected.json index 0a6c723840..49d2cdb9fd 100644 --- a/tests/parse_print/autogen-bilals-fixed/b427cac47c65e49ff32c22d2b3e8c19b/model.expected.json +++ b/tests/parse_print/autogen-bilals-fixed/b427cac47c65e49ff32c22d2b3e8c19b/model.expected.json @@ -16,7 +16,7 @@ {"Constant": {"ConstantInt": [{"TagInt": []}, 5]}}]}]]}]}}, {"SuchThat": [{"Op": - {"MkOpLexLeq": + {"MkOpDotLeq": [{"Op": {"MkOpSlicing": [{"Op": diff --git a/tests/parse_print/autogen-bilals-fixed/b427cac47c65e49ff32c22d2b3e8c19b/stdout.expected b/tests/parse_print/autogen-bilals-fixed/b427cac47c65e49ff32c22d2b3e8c19b/stdout.expected index 697cca78f3..91e0514cd1 100644 --- a/tests/parse_print/autogen-bilals-fixed/b427cac47c65e49ff32c22d2b3e8c19b/stdout.expected +++ b/tests/parse_print/autogen-bilals-fixed/b427cac47c65e49ff32c22d2b3e8c19b/stdout.expected @@ -2,4 +2,4 @@ language ESSENCE' 1.0 find var1: int(2, 3..5) such that - [[true, false, false, true; int(1, 3, 9, 11)], [true, true; int(0, 5)]; int(1..2)][var1, ..] <=lex [true; int(1)] + [[true, false, false, true; int(1, 3, 9, 11)], [true, true; int(0, 5)]; int(1..2)][var1, ..] .<= [true; int(1)] diff --git a/tests/parse_print/autogen-bilals-fixed/b6716decf75eddda33df3ec06f7cc400/model.expected.json b/tests/parse_print/autogen-bilals-fixed/b6716decf75eddda33df3ec06f7cc400/model.expected.json index cac13990b8..4147d70942 100644 --- a/tests/parse_print/autogen-bilals-fixed/b6716decf75eddda33df3ec06f7cc400/model.expected.json +++ b/tests/parse_print/autogen-bilals-fixed/b6716decf75eddda33df3ec06f7cc400/model.expected.json @@ -113,7 +113,7 @@ {"DomainBool": []}]}]}]}}, {"SuchThat": [{"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"AbstractLiteral": {"AbsLitMatrix": [{"DomainInt": @@ -278,7 +278,7 @@ []}, 1]}}]]}}}}]}}]}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": diff --git a/tests/parse_print/autogen-bilals-fixed/b6716decf75eddda33df3ec06f7cc400/stdout.expected b/tests/parse_print/autogen-bilals-fixed/b6716decf75eddda33df3ec06f7cc400/stdout.expected index 2617f0057d..0d7b517c48 100644 --- a/tests/parse_print/autogen-bilals-fixed/b6716decf75eddda33df3ec06f7cc400/stdout.expected +++ b/tests/parse_print/autogen-bilals-fixed/b6716decf75eddda33df3ec06f7cc400/stdout.expected @@ -16,7 +16,7 @@ find var5_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker: find var5_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values: matrix indexed by [int(1..4), int(1..5)] of bool such that - [var3; int(0)] var5_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q10] < @@ -25,7 +25,7 @@ such that var5_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q10] = var5_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q10 + 1] /\ - var5_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q10, ..] var5_ExplicitVarSizeWithMarkerR5_Marker -> diff --git a/tests/parse_print/autogen-bilals-fixed/b68ea8a7e4351cdfc4b3b75bb6582893/model.expected.json b/tests/parse_print/autogen-bilals-fixed/b68ea8a7e4351cdfc4b3b75bb6582893/model.expected.json index 309bef0f51..7064101836 100644 --- a/tests/parse_print/autogen-bilals-fixed/b68ea8a7e4351cdfc4b3b75bb6582893/model.expected.json +++ b/tests/parse_print/autogen-bilals-fixed/b68ea8a7e4351cdfc4b3b75bb6582893/model.expected.json @@ -175,7 +175,7 @@ {"ConstantInt": [{"TagInt": []}, 2]}}]}]]}, [{"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": @@ -321,7 +321,7 @@ []}, 4]}}]}]]}]}}]]}}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": @@ -981,7 +981,7 @@ {"ConstantInt": [{"TagInt": []}, 1]}}]]}}}}]}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpFlatten": [null, diff --git a/tests/parse_print/autogen-bilals-fixed/b68ea8a7e4351cdfc4b3b75bb6582893/stdout.expected b/tests/parse_print/autogen-bilals-fixed/b68ea8a7e4351cdfc4b3b75bb6582893/stdout.expected index 31bf895de3..b892763179 100644 --- a/tests/parse_print/autogen-bilals-fixed/b68ea8a7e4351cdfc4b3b75bb6582893/stdout.expected +++ b/tests/parse_print/autogen-bilals-fixed/b68ea8a7e4351cdfc4b3b75bb6582893/stdout.expected @@ -15,14 +15,14 @@ find var6: int(1..4, 4..5) maximising var4 such that and([var1_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - var1_ExplicitVarSizeWithFlags_Values_ExplicitVarSizeWithFlags_Flags[q1, ..] @@ -54,7 +54,7 @@ such that 4 = sum([var1_ExplicitVarSizeWithFlags_Values_ExplicitVarSizeWithFlags_Flags[q5, q10] | q10 : int(1..4)]) | q5 : int(1..81)]), and([var2_ExplicitVarSizeWithFlags_Flags[q12 + 1] -> - flatten(var2_ExplicitVarSizeWithFlags_Values_RelationAsMatrix[q12, .., ..]) diff --git a/tests/parse_print/autogen-bilals-fixed/b7ca13696cd34ed7006ef9dfac6d66ff/model.expected.json b/tests/parse_print/autogen-bilals-fixed/b7ca13696cd34ed7006ef9dfac6d66ff/model.expected.json index 71f87ae5f2..885665ffc3 100644 --- a/tests/parse_print/autogen-bilals-fixed/b7ca13696cd34ed7006ef9dfac6d66ff/model.expected.json +++ b/tests/parse_print/autogen-bilals-fixed/b7ca13696cd34ed7006ef9dfac6d66ff/model.expected.json @@ -719,7 +719,7 @@ []}, 2]}}]}]]}, [{"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": @@ -887,7 +887,7 @@ []}, 2]}}]}]]}, [{"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": @@ -1037,7 +1037,7 @@ []}, 2]}}]}]]}]}}]]}}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": diff --git a/tests/parse_print/autogen-bilals-fixed/b7ca13696cd34ed7006ef9dfac6d66ff/stdout.expected b/tests/parse_print/autogen-bilals-fixed/b7ca13696cd34ed7006ef9dfac6d66ff/stdout.expected index 72ee58e035..4209951005 100644 --- a/tests/parse_print/autogen-bilals-fixed/b7ca13696cd34ed7006ef9dfac6d66ff/stdout.expected +++ b/tests/parse_print/autogen-bilals-fixed/b7ca13696cd34ed7006ef9dfac6d66ff/stdout.expected @@ -61,21 +61,21 @@ such that var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q4] = var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q4 + 1] /\ - (var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values_1[q4, ..] var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> diff --git a/tests/parse_print/autogen-bilals-fixed/b7eff6ada58015f7994346e5ca41950c/model.expected.json b/tests/parse_print/autogen-bilals-fixed/b7eff6ada58015f7994346e5ca41950c/model.expected.json index 3928072a60..875d7b1734 100644 --- a/tests/parse_print/autogen-bilals-fixed/b7eff6ada58015f7994346e5ca41950c/model.expected.json +++ b/tests/parse_print/autogen-bilals-fixed/b7eff6ada58015f7994346e5ca41950c/model.expected.json @@ -311,7 +311,7 @@ []}, 1]}}]]}}}}]}}]}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpFlatten": [null, diff --git a/tests/parse_print/autogen-bilals-fixed/b7eff6ada58015f7994346e5ca41950c/stdout.expected b/tests/parse_print/autogen-bilals-fixed/b7eff6ada58015f7994346e5ca41950c/stdout.expected index c8e0477966..6c3ce9238c 100644 --- a/tests/parse_print/autogen-bilals-fixed/b7eff6ada58015f7994346e5ca41950c/stdout.expected +++ b/tests/parse_print/autogen-bilals-fixed/b7eff6ada58015f7994346e5ca41950c/stdout.expected @@ -28,7 +28,7 @@ such that /\ flatten(var2_PartitionAsSetR2_ExplicitVarSizeWithMarkerR5R2_Values_ExplicitVarSizeWithMarkerR2_Values_Occurrence [q4, .., ..]) - var1_PartitionAsSet_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMarker_Values_Function1DPartial_Flags [q1, q2, ..] - - var1_ExplicitVarSizeWithFlags_Values_ExplicitVarSizeWithFlags_Flags[q1, ..] @@ -55,7 +55,7 @@ such that 4 = sum([var1_ExplicitVarSizeWithFlags_Values_ExplicitVarSizeWithFlags_Flags[q5, q10] | q10 : int(1..4)]) | q5 : int(1..81)]), and([q12 + 1 <= var2_ExplicitVarSizeWithMarker_Marker -> - flatten(var2_ExplicitVarSizeWithMarker_Values_RelationAsMatrix[q12, .., ..]) var2_ExplicitVarSizeWithMarker_Marker -> diff --git a/tests/parse_print/autogen-bilals-fixed/be5b5a644521be5b55c6a12c503cad3a/model.expected.json b/tests/parse_print/autogen-bilals-fixed/be5b5a644521be5b55c6a12c503cad3a/model.expected.json index 4853fbbcd8..87aa5bd213 100644 --- a/tests/parse_print/autogen-bilals-fixed/be5b5a644521be5b55c6a12c503cad3a/model.expected.json +++ b/tests/parse_print/autogen-bilals-fixed/be5b5a644521be5b55c6a12c503cad3a/model.expected.json @@ -1974,7 +1974,7 @@ []}, 2]}}]}]]}, [{"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpFlatten": [null, @@ -2173,7 +2173,7 @@ []}, 16]}}]}]]}]}}]]}}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpFlatten": [null, @@ -2501,7 +2501,7 @@ []}, 2]}}]}]]}, [{"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": @@ -2676,7 +2676,7 @@ []}, 2]}}}]]}]}}]]}}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": @@ -3147,7 +3147,7 @@ {"Reference": [{"Name": "var6_PartitionAsSet_ExplicitVarSizeWithMarker_Marker"}, null]}]}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": diff --git a/tests/parse_print/autogen-bilals-fixed/be5b5a644521be5b55c6a12c503cad3a/stdout.expected b/tests/parse_print/autogen-bilals-fixed/be5b5a644521be5b55c6a12c503cad3a/stdout.expected index 6a6255e8e6..a8c9bfbd1f 100644 --- a/tests/parse_print/autogen-bilals-fixed/be5b5a644521be5b55c6a12c503cad3a/stdout.expected +++ b/tests/parse_print/autogen-bilals-fixed/be5b5a644521be5b55c6a12c503cad3a/stdout.expected @@ -121,7 +121,7 @@ such that /\ (flatten(var4_PartitionAsSet_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMarker_Values_Function1DPartial_Flags [q8, .., ..]) - var4_PartitionAsSet_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMarker_Values_Function1DPartial_Flags [q10, q11, ..] - = 1 | q31 : int(1..2)]), 2 <= var6_PartitionAsSet_ExplicitVarSizeWithMarker_Marker -> - var6_PartitionAsSet_ExplicitVarSizeWithMarker_Values_Occurrence[1, ..] var6_PartitionAsSet_ExplicitVarSizeWithMarker_Marker -> var6_PartitionAsSet_ExplicitVarSizeWithMarker_Values_Occurrence[q22, 2] = false diff --git a/tests/parse_print/autogen-bilals-fixed/bfd00aba95070795c7a808361a3c495d/model.expected.json b/tests/parse_print/autogen-bilals-fixed/bfd00aba95070795c7a808361a3c495d/model.expected.json index 8bc4e36404..6b92b8bb48 100644 --- a/tests/parse_print/autogen-bilals-fixed/bfd00aba95070795c7a808361a3c495d/model.expected.json +++ b/tests/parse_print/autogen-bilals-fixed/bfd00aba95070795c7a808361a3c495d/model.expected.json @@ -124,7 +124,7 @@ {"ConstantInt": [{"TagInt": []}, 1]}}]]}}}}]}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": @@ -993,7 +993,7 @@ {"ConstantInt": [{"TagInt": []}, 2]}}]}]]}, [{"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": @@ -1119,7 +1119,7 @@ []}, 1]}}]}}]}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpFlatten": [null, diff --git a/tests/parse_print/autogen-bilals-fixed/bfd00aba95070795c7a808361a3c495d/stdout.expected b/tests/parse_print/autogen-bilals-fixed/bfd00aba95070795c7a808361a3c495d/stdout.expected index 8bb338a69c..74f7f4d49c 100644 --- a/tests/parse_print/autogen-bilals-fixed/bfd00aba95070795c7a808361a3c495d/stdout.expected +++ b/tests/parse_print/autogen-bilals-fixed/bfd00aba95070795c7a808361a3c495d/stdout.expected @@ -10,7 +10,7 @@ find var2_PartitionAsSet_ExplicitVarSizeWithMarker_Values_Explicit_ExplicitVarSi such that false, and([var1_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - var1_ExplicitVarSizeWithFlags_Values_Function1D[q1, ..] @@ -56,7 +56,7 @@ such that | q22 : int(1..4)]), sum([q9_ExplicitVarSizeWithFlags_Flags[q23] | q23 : int(1..5)]) <= 5]), and([q12 + 1 <= var2_PartitionAsSet_ExplicitVarSizeWithMarker_Marker -> - var2_PartitionAsSet_ExplicitVarSizeWithMarker_Values_Explicit_ExplicitVarSizeWithMarker_Marker[q12, ..] - var2_RelationAsSet_ExplicitVarSizeWithMarker_Values_1_ExplicitVarSizeWithFlags_Flags[q1, ..] @@ -103,7 +103,7 @@ such that var4_2_PartitionAsSet_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMarker_Marker[q13] = var4_2_PartitionAsSet_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMarker_Marker[q13 + 1] /\ - var4_2_PartitionAsSet_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMarker_Values[q13, ..] var4_2_PartitionAsSet_ExplicitVarSizeWithMarker_Marker -> @@ -161,7 +161,7 @@ such that /\ (flatten(var5_PartitionAsSet_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithFlags_Flags [q23, .., ..]) - var5_PartitionAsSet_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithFlags_Flags [q25, q26, ..] - var2_PartitionAsSet_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMarker_Values_Function1DPartial_Flags [q1, q2, ..] - - var1_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithFlags_Flags[q1, ..] var1_ExplicitVarSizeWithMarker_Marker -> @@ -54,7 +54,7 @@ such that 4 = sum([var1_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithFlags_Flags[q3, q8] | q8 : int(1..4)]) | q3 : int(1..81)]), and([q10 + 1 <= var2_ExplicitVarSizeWithMarker_Marker -> - flatten(var2_ExplicitVarSizeWithMarker_Values_RelationAsMatrix[q10, .., ..]) var2_ExplicitVarSizeWithMarker_Marker -> diff --git a/tests/parse_print/autogen-bilals-fixed/c3841e1877c34e8e5bfd1c1837d307e1/model.expected.json b/tests/parse_print/autogen-bilals-fixed/c3841e1877c34e8e5bfd1c1837d307e1/model.expected.json index c1d953cda6..510238b8f8 100644 --- a/tests/parse_print/autogen-bilals-fixed/c3841e1877c34e8e5bfd1c1837d307e1/model.expected.json +++ b/tests/parse_print/autogen-bilals-fixed/c3841e1877c34e8e5bfd1c1837d307e1/model.expected.json @@ -514,7 +514,7 @@ []}, 1]}}]]}}}}]}}]}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": diff --git a/tests/parse_print/autogen-bilals-fixed/c3841e1877c34e8e5bfd1c1837d307e1/stdout.expected b/tests/parse_print/autogen-bilals-fixed/c3841e1877c34e8e5bfd1c1837d307e1/stdout.expected index 63dba63459..5c785b6adb 100644 --- a/tests/parse_print/autogen-bilals-fixed/c3841e1877c34e8e5bfd1c1837d307e1/stdout.expected +++ b/tests/parse_print/autogen-bilals-fixed/c3841e1877c34e8e5bfd1c1837d307e1/stdout.expected @@ -38,7 +38,7 @@ such that var3_PartitionAsSet_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMarker_Marker[q17] = var3_PartitionAsSet_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMarker_Marker[q17 + 1] /\ - var3_PartitionAsSet_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMarker_Values[q17, ..] var3_PartitionAsSet_ExplicitVarSizeWithMarker_Marker -> diff --git a/tests/parse_print/autogen-bilals-fixed/c423e819384eec3bed63a038add27ca6/model.expected.json b/tests/parse_print/autogen-bilals-fixed/c423e819384eec3bed63a038add27ca6/model.expected.json index c5c4581ff8..3bd27752bf 100644 --- a/tests/parse_print/autogen-bilals-fixed/c423e819384eec3bed63a038add27ca6/model.expected.json +++ b/tests/parse_print/autogen-bilals-fixed/c423e819384eec3bed63a038add27ca6/model.expected.json @@ -774,7 +774,7 @@ []}, 2]}}]}]]}, [{"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": @@ -942,7 +942,7 @@ []}, 2]}}]}]]}, [{"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": @@ -1092,7 +1092,7 @@ []}, 2]}}]}]]}]}}]]}}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": diff --git a/tests/parse_print/autogen-bilals-fixed/c423e819384eec3bed63a038add27ca6/stdout.expected b/tests/parse_print/autogen-bilals-fixed/c423e819384eec3bed63a038add27ca6/stdout.expected index ddcfe824bf..8292e042d8 100644 --- a/tests/parse_print/autogen-bilals-fixed/c423e819384eec3bed63a038add27ca6/stdout.expected +++ b/tests/parse_print/autogen-bilals-fixed/c423e819384eec3bed63a038add27ca6/stdout.expected @@ -65,21 +65,21 @@ such that var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q4] = var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q4 + 1] /\ - (var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values_1[q4, ..] var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> diff --git a/tests/parse_print/autogen-bilals-fixed/c5272f0460d36d154f10770be9088fa4/model.expected.json b/tests/parse_print/autogen-bilals-fixed/c5272f0460d36d154f10770be9088fa4/model.expected.json index b93cd20285..cbace51b93 100644 --- a/tests/parse_print/autogen-bilals-fixed/c5272f0460d36d154f10770be9088fa4/model.expected.json +++ b/tests/parse_print/autogen-bilals-fixed/c5272f0460d36d154f10770be9088fa4/model.expected.json @@ -725,7 +725,7 @@ []}, 2]}}]}]]}, [{"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": @@ -893,7 +893,7 @@ []}, 2]}}]}]]}, [{"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": @@ -1043,7 +1043,7 @@ []}, 2]}}]}]]}]}}]]}}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": diff --git a/tests/parse_print/autogen-bilals-fixed/c5272f0460d36d154f10770be9088fa4/stdout.expected b/tests/parse_print/autogen-bilals-fixed/c5272f0460d36d154f10770be9088fa4/stdout.expected index a9866e458c..83568a8a93 100644 --- a/tests/parse_print/autogen-bilals-fixed/c5272f0460d36d154f10770be9088fa4/stdout.expected +++ b/tests/parse_print/autogen-bilals-fixed/c5272f0460d36d154f10770be9088fa4/stdout.expected @@ -61,21 +61,21 @@ such that var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q4] = var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q4 + 1] /\ - (var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values_1[q4, ..] var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> diff --git a/tests/parse_print/autogen-bilals-fixed/c539dc840839e54f8d3d5ca53104102f/model.expected.json b/tests/parse_print/autogen-bilals-fixed/c539dc840839e54f8d3d5ca53104102f/model.expected.json index e73d40bf5f..b6ea832176 100644 --- a/tests/parse_print/autogen-bilals-fixed/c539dc840839e54f8d3d5ca53104102f/model.expected.json +++ b/tests/parse_print/autogen-bilals-fixed/c539dc840839e54f8d3d5ca53104102f/model.expected.json @@ -452,7 +452,7 @@ "var2_PartitionAsSet_ExplicitVarSizeWithMarker_Marker"}, null]}]}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpFlatten": [null, diff --git a/tests/parse_print/autogen-bilals-fixed/c539dc840839e54f8d3d5ca53104102f/stdout.expected b/tests/parse_print/autogen-bilals-fixed/c539dc840839e54f8d3d5ca53104102f/stdout.expected index 727b2021bf..3f51becb42 100644 --- a/tests/parse_print/autogen-bilals-fixed/c539dc840839e54f8d3d5ca53104102f/stdout.expected +++ b/tests/parse_print/autogen-bilals-fixed/c539dc840839e54f8d3d5ca53104102f/stdout.expected @@ -25,7 +25,7 @@ such that | q11 : int(1..5)]), q1_ExplicitVarSizeWithMarker_Marker <= 5]), and([q4 + 1 <= var2_PartitionAsSet_ExplicitVarSizeWithMarker_Marker -> - flatten(var2_PartitionAsSet_ExplicitVarSizeWithMarker_Values_Explicit_Occurrence[q4, .., ..]) var2_PartitionAsSet_ExplicitVarSizeWithMarker_Marker -> diff --git a/tests/parse_print/autogen-bilals-fixed/c6f07fc1b59d5295892164e99ab6b192/model.expected.json b/tests/parse_print/autogen-bilals-fixed/c6f07fc1b59d5295892164e99ab6b192/model.expected.json index 9675ba369d..99d6b08a08 100644 --- a/tests/parse_print/autogen-bilals-fixed/c6f07fc1b59d5295892164e99ab6b192/model.expected.json +++ b/tests/parse_print/autogen-bilals-fixed/c6f07fc1b59d5295892164e99ab6b192/model.expected.json @@ -277,7 +277,7 @@ {"ConstantInt": [{"TagInt": []}, 2]}}]}]]}, [{"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": @@ -344,7 +344,7 @@ []}, 2]}}]}]]}, [{"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": @@ -493,7 +493,7 @@ []}, 2]}}]}]]}]}}]]}}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": @@ -978,7 +978,7 @@ {"Op": {"MkOpImply": [{"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": diff --git a/tests/parse_print/autogen-bilals-fixed/c6f07fc1b59d5295892164e99ab6b192/stdout.expected b/tests/parse_print/autogen-bilals-fixed/c6f07fc1b59d5295892164e99ab6b192/stdout.expected index 782d7dc730..9ac6fbcd50 100644 --- a/tests/parse_print/autogen-bilals-fixed/c6f07fc1b59d5295892164e99ab6b192/stdout.expected +++ b/tests/parse_print/autogen-bilals-fixed/c6f07fc1b59d5295892164e99ab6b192/stdout.expected @@ -27,12 +27,12 @@ find var3_RelationAsSetR15_ExplicitVarSizeWithMarkerR15_Values_1_RelationAsMatri such that false, and([q6 + 1 <= var1_FunctionAsRelationR3R4_RelationAsSetR3R4_ExplicitVarSizeWithMarkerR3R4_Marker -> - var1_FunctionAsRelationR3R4_RelationAsSetR3R4_ExplicitVarSizeWithMarkerR3R4_Values_1_Explicit[q6, ..] - (var1_FunctionAsRelationR3R4_RelationAsSetR3R4_ExplicitVarSizeWithMarkerR3R4_Values_1_Explicit[q36, ..] or([var1_FunctionAsRelationR3R4_RelationAsSetR3R4_ExplicitVarSizeWithMarkerR3R4_Values_2_ExplicitVarSizeWithFlags_Flags diff --git a/tests/parse_print/autogen-bilals-fixed/c7a05c6406dc0bf72a24b7344bf05115/model.expected.json b/tests/parse_print/autogen-bilals-fixed/c7a05c6406dc0bf72a24b7344bf05115/model.expected.json index 08674ecb0e..f772e16a4b 100644 --- a/tests/parse_print/autogen-bilals-fixed/c7a05c6406dc0bf72a24b7344bf05115/model.expected.json +++ b/tests/parse_print/autogen-bilals-fixed/c7a05c6406dc0bf72a24b7344bf05115/model.expected.json @@ -102,7 +102,7 @@ []}, 2]}}]}]]}, [{"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": @@ -239,7 +239,7 @@ {"DomainBool": []}]}}]]}}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": diff --git a/tests/parse_print/autogen-bilals-fixed/c7a05c6406dc0bf72a24b7344bf05115/stdout.expected b/tests/parse_print/autogen-bilals-fixed/c7a05c6406dc0bf72a24b7344bf05115/stdout.expected index 913bf6f6e0..a28bd2a035 100644 --- a/tests/parse_print/autogen-bilals-fixed/c7a05c6406dc0bf72a24b7344bf05115/stdout.expected +++ b/tests/parse_print/autogen-bilals-fixed/c7a05c6406dc0bf72a24b7344bf05115/stdout.expected @@ -9,14 +9,14 @@ such that q_4_ExplicitVarSizeWithMarker_Values_Function1DPartial_Values : matrix indexed by [int(1..4), bool] of int(5), and([q1 + 1 <= q_4_ExplicitVarSizeWithMarker_Marker -> - q_4_ExplicitVarSizeWithMarker_Values_Function1DPartial_Flags[q1, ..] q_4_ExplicitVarSizeWithMarker_Marker -> diff --git a/tests/parse_print/autogen-bilals-fixed/c7bab02871b463a4b24d6530e2009c74/model.expected.json b/tests/parse_print/autogen-bilals-fixed/c7bab02871b463a4b24d6530e2009c74/model.expected.json index 0291ff2fe3..f9d6ca3c6f 100644 --- a/tests/parse_print/autogen-bilals-fixed/c7bab02871b463a4b24d6530e2009c74/model.expected.json +++ b/tests/parse_print/autogen-bilals-fixed/c7bab02871b463a4b24d6530e2009c74/model.expected.json @@ -866,7 +866,7 @@ []}, 2]}}]}]]}, [{"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": @@ -1016,7 +1016,7 @@ []}, 4]}}]}]]}]}}]]}}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpFlatten": [null, @@ -1447,7 +1447,7 @@ []}, 1]}}]]}}}}]}}]}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": @@ -2218,7 +2218,7 @@ []}, 1]}}]]}}}}]}}]}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": diff --git a/tests/parse_print/autogen-bilals-fixed/c7bab02871b463a4b24d6530e2009c74/stdout.expected b/tests/parse_print/autogen-bilals-fixed/c7bab02871b463a4b24d6530e2009c74/stdout.expected index d38c523af2..3e43b314b3 100644 --- a/tests/parse_print/autogen-bilals-fixed/c7bab02871b463a4b24d6530e2009c74/stdout.expected +++ b/tests/parse_print/autogen-bilals-fixed/c7bab02871b463a4b24d6530e2009c74/stdout.expected @@ -68,7 +68,7 @@ such that /\ (var1_PartitionAsSet_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMarker_Marker [q5, ..] - var4_PartitionAsSet_ExplicitVarSizeWithMarker_Marker -> diff --git a/tests/parse_print/autogen-bilals-fixed/c863e1aefc22489efd92991f527ae5a2/model.expected.json b/tests/parse_print/autogen-bilals-fixed/c863e1aefc22489efd92991f527ae5a2/model.expected.json index 05bd6f12c4..d8ed65b665 100644 --- a/tests/parse_print/autogen-bilals-fixed/c863e1aefc22489efd92991f527ae5a2/model.expected.json +++ b/tests/parse_print/autogen-bilals-fixed/c863e1aefc22489efd92991f527ae5a2/model.expected.json @@ -1037,7 +1037,7 @@ []}, 2]}}]}]]}, [{"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": @@ -1189,7 +1189,7 @@ []}, 4]}}}]]}]}}]]}}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": diff --git a/tests/parse_print/autogen-bilals-fixed/c863e1aefc22489efd92991f527ae5a2/stdout.expected b/tests/parse_print/autogen-bilals-fixed/c863e1aefc22489efd92991f527ae5a2/stdout.expected index bcc9374af4..5cf8d80cad 100644 --- a/tests/parse_print/autogen-bilals-fixed/c863e1aefc22489efd92991f527ae5a2/stdout.expected +++ b/tests/parse_print/autogen-bilals-fixed/c863e1aefc22489efd92991f527ae5a2/stdout.expected @@ -60,7 +60,7 @@ such that | q45 : int(1..2)]) | q1 : int(1..7)]), and([q1 + 1 <= var1_FunctionAsRelation_RelationAsSet_ExplicitVarSizeWithMarker_Marker -> - var1_FunctionAsRelation_RelationAsSet_ExplicitVarSizeWithMarker_Values_1_Function1DPartial_Flags[q1, ..] var1_PartitionAsSet_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMarker_Values_Function1DPartial_Flags [q1, q2, ..] - - var1_ExplicitVarSizeWithMarker_Values_Function1D[q1, ..] var1_ExplicitVarSizeWithMarker_Marker -> @@ -43,7 +43,7 @@ such that | q18 : int(1..4)]), sum([q7_ExplicitVarSizeWithFlags_Flags[q19] | q19 : int(1..5)]) <= 5]), and([q10 + 1 <= var2_PartitionAsSet_ExplicitVarSizeWithMarker_Marker -> - flatten(var2_PartitionAsSet_ExplicitVarSizeWithMarker_Values_Explicit_Occurrence[q10, .., ..]) var2_PartitionAsSet_ExplicitVarSizeWithMarker_Marker -> diff --git a/tests/parse_print/autogen-bilals-fixed/c8cc670b809293626467998d149a92ca/model.expected.json b/tests/parse_print/autogen-bilals-fixed/c8cc670b809293626467998d149a92ca/model.expected.json index 55fc966ebe..ab35a675ab 100644 --- a/tests/parse_print/autogen-bilals-fixed/c8cc670b809293626467998d149a92ca/model.expected.json +++ b/tests/parse_print/autogen-bilals-fixed/c8cc670b809293626467998d149a92ca/model.expected.json @@ -78,7 +78,7 @@ [{"Reference": [{"Name": "var4"}, null]}, {"Constant": {"ConstantInt": [{"TagInt": []}, 5]}}]}}, {"Op": {"MkOpNeq": [{"Reference": [{"Name": "var1"}, null]}, {"Reference": [{"Name": "var1"}, null]}]}}, {"Op": - {"MkOpLexLeq": + {"MkOpDotLeq": [{"Constant": {"ConstantAbstract": {"AbsLitMatrix": diff --git a/tests/parse_print/autogen-bilals-fixed/c8cc670b809293626467998d149a92ca/stdout.expected b/tests/parse_print/autogen-bilals-fixed/c8cc670b809293626467998d149a92ca/stdout.expected index 005369057e..5703c715ef 100644 --- a/tests/parse_print/autogen-bilals-fixed/c8cc670b809293626467998d149a92ca/stdout.expected +++ b/tests/parse_print/autogen-bilals-fixed/c8cc670b809293626467998d149a92ca/stdout.expected @@ -12,4 +12,4 @@ such that relation(tuple (false), tuple (false), tuple (false), tuple (false), tuple (true)), image(var4, 5), var1 != var1, - [0; int(0)] <=lex [3, 1, 1, 5, 3; int(10, 1, 0, 15, 12)] + [0; int(0)] .<= [3, 1, 1, 5, 3; int(10, 1, 0, 15, 12)] diff --git a/tests/parse_print/autogen-bilals-fixed/c96d788458c4c7e3247f608a018776aa/model.expected.json b/tests/parse_print/autogen-bilals-fixed/c96d788458c4c7e3247f608a018776aa/model.expected.json index ecbb085bff..7568208a73 100644 --- a/tests/parse_print/autogen-bilals-fixed/c96d788458c4c7e3247f608a018776aa/model.expected.json +++ b/tests/parse_print/autogen-bilals-fixed/c96d788458c4c7e3247f608a018776aa/model.expected.json @@ -1174,7 +1174,7 @@ []}, 1]}}]]}}}}]}}]}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": @@ -1817,7 +1817,7 @@ {"ConstantInt": [{"TagInt": []}, 2]}}]}]]}, [{"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": @@ -1951,7 +1951,7 @@ {"DomainBool": []}]}}]]}}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": diff --git a/tests/parse_print/autogen-bilals-fixed/c96d788458c4c7e3247f608a018776aa/stdout.expected b/tests/parse_print/autogen-bilals-fixed/c96d788458c4c7e3247f608a018776aa/stdout.expected index f3a96939ae..60d533013d 100644 --- a/tests/parse_print/autogen-bilals-fixed/c96d788458c4c7e3247f608a018776aa/stdout.expected +++ b/tests/parse_print/autogen-bilals-fixed/c96d788458c4c7e3247f608a018776aa/stdout.expected @@ -91,7 +91,7 @@ such that var2_1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q7] = var2_1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q7 + 1] /\ - var2_1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q7, ..] var2_1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> @@ -129,14 +129,14 @@ such that | q16 : int(1..9)]), 3 = var4_1_ExplicitWithRepetition_Flag, and([var5_ExplicitWithFlagsR10_Flags[q23 + 1] > 0 -> - var5_ExplicitWithFlagsR10_Values_Function1DPartial_Flags[q23, ..] diff --git a/tests/parse_print/autogen-bilals-fixed/c9e1cd7a71dc9c900ce717378a2e7326/model.expected.json b/tests/parse_print/autogen-bilals-fixed/c9e1cd7a71dc9c900ce717378a2e7326/model.expected.json index 06f252e437..cd12454008 100644 --- a/tests/parse_print/autogen-bilals-fixed/c9e1cd7a71dc9c900ce717378a2e7326/model.expected.json +++ b/tests/parse_print/autogen-bilals-fixed/c9e1cd7a71dc9c900ce717378a2e7326/model.expected.json @@ -535,7 +535,7 @@ "var2_PartitionAsSet_ExplicitVarSizeWithMarker_Marker"}, null]}]}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpFlatten": [null, diff --git a/tests/parse_print/autogen-bilals-fixed/c9e1cd7a71dc9c900ce717378a2e7326/stdout.expected b/tests/parse_print/autogen-bilals-fixed/c9e1cd7a71dc9c900ce717378a2e7326/stdout.expected index 9eb0e8b86a..921521d3b8 100644 --- a/tests/parse_print/autogen-bilals-fixed/c9e1cd7a71dc9c900ce717378a2e7326/stdout.expected +++ b/tests/parse_print/autogen-bilals-fixed/c9e1cd7a71dc9c900ce717378a2e7326/stdout.expected @@ -27,7 +27,7 @@ such that | q12 : int(1..4)]), sum([q1_ExplicitVarSizeWithFlags_Flags[q13] | q13 : int(1..5)]) <= 5]), and([q4 + 1 <= var2_PartitionAsSet_ExplicitVarSizeWithMarker_Marker -> - flatten(var2_PartitionAsSet_ExplicitVarSizeWithMarker_Values_Explicit_Occurrence[q4, .., ..]) var2_PartitionAsSet_ExplicitVarSizeWithMarker_Marker -> diff --git a/tests/parse_print/autogen-bilals-fixed/cad537c995fb03554a83b3fb49b715bc/model.expected.json b/tests/parse_print/autogen-bilals-fixed/cad537c995fb03554a83b3fb49b715bc/model.expected.json index c354b3d25f..576a7ba787 100644 --- a/tests/parse_print/autogen-bilals-fixed/cad537c995fb03554a83b3fb49b715bc/model.expected.json +++ b/tests/parse_print/autogen-bilals-fixed/cad537c995fb03554a83b3fb49b715bc/model.expected.json @@ -447,7 +447,7 @@ []}, 2]}}]}}]}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": diff --git a/tests/parse_print/autogen-bilals-fixed/cad537c995fb03554a83b3fb49b715bc/stdout.expected b/tests/parse_print/autogen-bilals-fixed/cad537c995fb03554a83b3fb49b715bc/stdout.expected index 0349005cb7..2fdbebdf52 100644 --- a/tests/parse_print/autogen-bilals-fixed/cad537c995fb03554a83b3fb49b715bc/stdout.expected +++ b/tests/parse_print/autogen-bilals-fixed/cad537c995fb03554a83b3fb49b715bc/stdout.expected @@ -31,7 +31,7 @@ such that var1_PartitionAsSet_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMarker_Marker[q1, 1] = var1_PartitionAsSet_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMarker_Marker[q1, 2] /\ - var1_PartitionAsSet_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMarker_Values[q1, 1, ..] var1_PartitionAsSet_ExplicitVarSizeWithMarker_Marker[q1] -> diff --git a/tests/parse_print/autogen-bilals-fixed/cc2192ed7f68debf33abcbf2de08eff2/model.expected.json b/tests/parse_print/autogen-bilals-fixed/cc2192ed7f68debf33abcbf2de08eff2/model.expected.json index 5b62d1d141..475a4c9838 100644 --- a/tests/parse_print/autogen-bilals-fixed/cc2192ed7f68debf33abcbf2de08eff2/model.expected.json +++ b/tests/parse_print/autogen-bilals-fixed/cc2192ed7f68debf33abcbf2de08eff2/model.expected.json @@ -166,7 +166,7 @@ {"ConstantAbstract": {"AbsLitFunction": [[{"ConstantBool": true}, {"ConstantBool": false}]]}}}, {"Op": - {"MkOpLexLeq": + {"MkOpDotLeq": [{"Reference": [{"Name": "var1"}, null]}, {"Constant": {"ConstantAbstract": diff --git a/tests/parse_print/autogen-bilals-fixed/cc2192ed7f68debf33abcbf2de08eff2/stdout.expected b/tests/parse_print/autogen-bilals-fixed/cc2192ed7f68debf33abcbf2de08eff2/stdout.expected index b8769711bb..fa63577a7b 100644 --- a/tests/parse_print/autogen-bilals-fixed/cc2192ed7f68debf33abcbf2de08eff2/stdout.expected +++ b/tests/parse_print/autogen-bilals-fixed/cc2192ed7f68debf33abcbf2de08eff2/stdout.expected @@ -22,7 +22,7 @@ such that {false}), partition({false, true, false, true}, {false}); int(4..6)]), - image(function(true --> false), var1 <=lex [true, true, true; int(2, 4, 0)]), + image(function(true --> false), var1 .<= [true, true, true; int(2, 4, 0)]), image(function({true} --> false, {true} --> false), {true <-> false}), together({relation((true, true))}, partition({relation((true, false), (false, true), (false, false), (false, false), (true, true)), diff --git a/tests/parse_print/autogen-bilals-fixed/d1f9f5646ad02f51e81ccd962c936011/model.expected.json b/tests/parse_print/autogen-bilals-fixed/d1f9f5646ad02f51e81ccd962c936011/model.expected.json index 5a6d114f22..daed1f375d 100644 --- a/tests/parse_print/autogen-bilals-fixed/d1f9f5646ad02f51e81ccd962c936011/model.expected.json +++ b/tests/parse_print/autogen-bilals-fixed/d1f9f5646ad02f51e81ccd962c936011/model.expected.json @@ -255,7 +255,7 @@ {"ConstantInt": [{"TagInt": []}, 2]}}]}]]}, [{"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": @@ -401,7 +401,7 @@ []}, 3]}}]}]]}]}}]]}}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": @@ -1239,7 +1239,7 @@ []}, 1]}}]]}}}}]}}]}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": diff --git a/tests/parse_print/autogen-bilals-fixed/d1f9f5646ad02f51e81ccd962c936011/stdout.expected b/tests/parse_print/autogen-bilals-fixed/d1f9f5646ad02f51e81ccd962c936011/stdout.expected index f913a48e6b..834252d1ff 100644 --- a/tests/parse_print/autogen-bilals-fixed/d1f9f5646ad02f51e81ccd962c936011/stdout.expected +++ b/tests/parse_print/autogen-bilals-fixed/d1f9f5646ad02f51e81ccd962c936011/stdout.expected @@ -27,14 +27,14 @@ such that given2, given1, and([q1 + 1 <= var1_ExplicitVarSizeWithMarkerR7_Marker -> - var1_ExplicitVarSizeWithMarkerR7_Values_ExplicitWithFlags_Flags[q1, ..] var1_ExplicitVarSizeWithMarkerR7_Marker -> @@ -84,7 +84,7 @@ such that var3_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q20] = var3_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q20 + 1] /\ - var3_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values_1[q20, ..] var3_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> diff --git a/tests/parse_print/autogen-bilals-fixed/d1ffc6dc30ae73ba44e3f9c55d3e1636/model.expected.json b/tests/parse_print/autogen-bilals-fixed/d1ffc6dc30ae73ba44e3f9c55d3e1636/model.expected.json index e1735cbbd8..5df6fab58f 100644 --- a/tests/parse_print/autogen-bilals-fixed/d1ffc6dc30ae73ba44e3f9c55d3e1636/model.expected.json +++ b/tests/parse_print/autogen-bilals-fixed/d1ffc6dc30ae73ba44e3f9c55d3e1636/model.expected.json @@ -712,7 +712,7 @@ []}, 2]}}]}]]}, [{"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": @@ -880,7 +880,7 @@ []}, 2]}}]}]]}, [{"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": @@ -1030,7 +1030,7 @@ []}, 2]}}]}]]}]}}]]}}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": diff --git a/tests/parse_print/autogen-bilals-fixed/d1ffc6dc30ae73ba44e3f9c55d3e1636/stdout.expected b/tests/parse_print/autogen-bilals-fixed/d1ffc6dc30ae73ba44e3f9c55d3e1636/stdout.expected index 3f23b7a2bd..f8d3236f26 100644 --- a/tests/parse_print/autogen-bilals-fixed/d1ffc6dc30ae73ba44e3f9c55d3e1636/stdout.expected +++ b/tests/parse_print/autogen-bilals-fixed/d1ffc6dc30ae73ba44e3f9c55d3e1636/stdout.expected @@ -61,21 +61,21 @@ such that var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q4] = var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q4 + 1] /\ - (var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values_1[q4, ..] var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> diff --git a/tests/parse_print/autogen-bilals-fixed/d20ff5e630ee919f1fcc726ea14f1e21/model.expected.json b/tests/parse_print/autogen-bilals-fixed/d20ff5e630ee919f1fcc726ea14f1e21/model.expected.json index 85f967837d..8f3d2c10af 100644 --- a/tests/parse_print/autogen-bilals-fixed/d20ff5e630ee919f1fcc726ea14f1e21/model.expected.json +++ b/tests/parse_print/autogen-bilals-fixed/d20ff5e630ee919f1fcc726ea14f1e21/model.expected.json @@ -1188,7 +1188,7 @@ []}, 2]}}]}]]}, [{"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpFlatten": [null, @@ -1370,7 +1370,7 @@ []}, 2]}}]}]]}]}}]]}}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpFlatten": [null, @@ -1627,7 +1627,7 @@ [{"TagInt": []}, 2]}}]}]]}, [{"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": @@ -1740,7 +1740,7 @@ []}, 2]}}}}]}}]}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": diff --git a/tests/parse_print/autogen-bilals-fixed/d20ff5e630ee919f1fcc726ea14f1e21/stdout.expected b/tests/parse_print/autogen-bilals-fixed/d20ff5e630ee919f1fcc726ea14f1e21/stdout.expected index 2717126c74..013faee70e 100644 --- a/tests/parse_print/autogen-bilals-fixed/d20ff5e630ee919f1fcc726ea14f1e21/stdout.expected +++ b/tests/parse_print/autogen-bilals-fixed/d20ff5e630ee919f1fcc726ea14f1e21/stdout.expected @@ -72,7 +72,7 @@ such that /\ (flatten(var1_PartitionAsSet_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMarker_Values_Function1DPartial_Flags [q5, .., ..]) - var1_PartitionAsSet_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMarker_Values_Function1DPartial_Flags [q7, 1, ..] - var1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> diff --git a/tests/parse_print/autogen-bilals-fixed/d3909eeb253333c473b61058dd67f690/model.expected.json b/tests/parse_print/autogen-bilals-fixed/d3909eeb253333c473b61058dd67f690/model.expected.json index f495f15673..e7f1cd3a8c 100644 --- a/tests/parse_print/autogen-bilals-fixed/d3909eeb253333c473b61058dd67f690/model.expected.json +++ b/tests/parse_print/autogen-bilals-fixed/d3909eeb253333c473b61058dd67f690/model.expected.json @@ -1180,7 +1180,7 @@ []}, 1]}}]]}}}}]}}]}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": @@ -1748,7 +1748,7 @@ {"ConstantInt": [{"TagInt": []}, 2]}}]}]]}, [{"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": @@ -1882,7 +1882,7 @@ {"DomainBool": []}]}}]]}}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": diff --git a/tests/parse_print/autogen-bilals-fixed/d3909eeb253333c473b61058dd67f690/stdout.expected b/tests/parse_print/autogen-bilals-fixed/d3909eeb253333c473b61058dd67f690/stdout.expected index d23a49091e..a0caf7e8f9 100644 --- a/tests/parse_print/autogen-bilals-fixed/d3909eeb253333c473b61058dd67f690/stdout.expected +++ b/tests/parse_print/autogen-bilals-fixed/d3909eeb253333c473b61058dd67f690/stdout.expected @@ -91,7 +91,7 @@ such that var2_1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q7] = var2_1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q7 + 1] /\ - var2_1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q7, ..] var2_1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> @@ -120,14 +120,14 @@ such that and([var4_1_ExplicitWithFlags_Flags[q17] = 0 \/ var4_1_ExplicitWithFlags_Flags[q17] >= 0 | q17 : int(1..3)]), 3 = sum([var4_1_ExplicitWithFlags_Flags[q18] | q18 : int(1..3)]), and([var5_ExplicitWithFlagsR10_Flags[q20 + 1] > 0 -> - var5_ExplicitWithFlagsR10_Values_Function1DPartial_Flags[q20, ..] diff --git a/tests/parse_print/autogen-bilals-fixed/d548102740c166c94c1585976df85834/model.expected.json b/tests/parse_print/autogen-bilals-fixed/d548102740c166c94c1585976df85834/model.expected.json index f234c91e1f..8346626346 100644 --- a/tests/parse_print/autogen-bilals-fixed/d548102740c166c94c1585976df85834/model.expected.json +++ b/tests/parse_print/autogen-bilals-fixed/d548102740c166c94c1585976df85834/model.expected.json @@ -1396,7 +1396,7 @@ []}, 2]}}]}]]}, [{"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpFlatten": [null, @@ -1578,7 +1578,7 @@ []}, 2]}}]}]]}]}}]]}}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpFlatten": [null, @@ -1835,7 +1835,7 @@ [{"TagInt": []}, 2]}}]}]]}, [{"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": @@ -1948,7 +1948,7 @@ []}, 2]}}}}]}}]}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": diff --git a/tests/parse_print/autogen-bilals-fixed/d548102740c166c94c1585976df85834/stdout.expected b/tests/parse_print/autogen-bilals-fixed/d548102740c166c94c1585976df85834/stdout.expected index ab7b98cbfd..d501f81198 100644 --- a/tests/parse_print/autogen-bilals-fixed/d548102740c166c94c1585976df85834/stdout.expected +++ b/tests/parse_print/autogen-bilals-fixed/d548102740c166c94c1585976df85834/stdout.expected @@ -87,7 +87,7 @@ such that /\ (flatten(var1_PartitionAsSet_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMarker_Values_Function1DPartial_Flags [q5, .., ..]) - var1_PartitionAsSet_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMarker_Values_Function1DPartial_Flags [q7, 1, ..] - - and([var1_PartitionAsSet_ExplicitVarSizeWithMarker_Values_Explicit_ExplicitVarSizeWithFlags_Flags[1, q9, ..] diff --git a/tests/parse_print/autogen-bilals-fixed/d6b3494aaacb9f588de0875051f0040c/model.expected.json b/tests/parse_print/autogen-bilals-fixed/d6b3494aaacb9f588de0875051f0040c/model.expected.json index 4db830b35a..e95de6d77c 100644 --- a/tests/parse_print/autogen-bilals-fixed/d6b3494aaacb9f588de0875051f0040c/model.expected.json +++ b/tests/parse_print/autogen-bilals-fixed/d6b3494aaacb9f588de0875051f0040c/model.expected.json @@ -82,7 +82,7 @@ {"ConstantInt": [{"TagInt": []}, 2]}}]}]]}, [{"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": diff --git a/tests/parse_print/autogen-bilals-fixed/d6b3494aaacb9f588de0875051f0040c/stdout.expected b/tests/parse_print/autogen-bilals-fixed/d6b3494aaacb9f588de0875051f0040c/stdout.expected index 82e876ac62..e4bce96cb4 100644 --- a/tests/parse_print/autogen-bilals-fixed/d6b3494aaacb9f588de0875051f0040c/stdout.expected +++ b/tests/parse_print/autogen-bilals-fixed/d6b3494aaacb9f588de0875051f0040c/stdout.expected @@ -6,7 +6,7 @@ find var1_FunctionAsRelation_RelationAsSet_ExplicitVarSizeWithMarker_Values_1_Oc find var1_FunctionAsRelation_RelationAsSet_ExplicitVarSizeWithMarker_Values_2: matrix indexed by [int(1..3)] of bool such that and([q1 + 1 <= var1_FunctionAsRelation_RelationAsSet_ExplicitVarSizeWithMarker_Marker -> - var1_FunctionAsRelation_RelationAsSet_ExplicitVarSizeWithMarker_Values_1_Occurrence[q1, ..] diff --git a/tests/parse_print/autogen-bilals-fixed/d75b01e01b11eb07e4bc4fbd71ce3b5e/model.expected.json b/tests/parse_print/autogen-bilals-fixed/d75b01e01b11eb07e4bc4fbd71ce3b5e/model.expected.json index c81ec98be4..b2010bb56d 100644 --- a/tests/parse_print/autogen-bilals-fixed/d75b01e01b11eb07e4bc4fbd71ce3b5e/model.expected.json +++ b/tests/parse_print/autogen-bilals-fixed/d75b01e01b11eb07e4bc4fbd71ce3b5e/model.expected.json @@ -377,7 +377,7 @@ []}, 1]}}]]}}}}]}}]}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": diff --git a/tests/parse_print/autogen-bilals-fixed/d75b01e01b11eb07e4bc4fbd71ce3b5e/stdout.expected b/tests/parse_print/autogen-bilals-fixed/d75b01e01b11eb07e4bc4fbd71ce3b5e/stdout.expected index 31875ee263..4bb6136eaf 100644 --- a/tests/parse_print/autogen-bilals-fixed/d75b01e01b11eb07e4bc4fbd71ce3b5e/stdout.expected +++ b/tests/parse_print/autogen-bilals-fixed/d75b01e01b11eb07e4bc4fbd71ce3b5e/stdout.expected @@ -34,7 +34,7 @@ such that var2_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q5] = var2_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q5 + 1] /\ - var2_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q5, ..] var2_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> diff --git a/tests/parse_print/autogen-bilals-fixed/d7d816b10a6f459ed78f1bd604bca06f/model.expected.json b/tests/parse_print/autogen-bilals-fixed/d7d816b10a6f459ed78f1bd604bca06f/model.expected.json index 00cd5dc1e8..2ed1c94ec0 100644 --- a/tests/parse_print/autogen-bilals-fixed/d7d816b10a6f459ed78f1bd604bca06f/model.expected.json +++ b/tests/parse_print/autogen-bilals-fixed/d7d816b10a6f459ed78f1bd604bca06f/model.expected.json @@ -574,7 +574,7 @@ {"ConstantInt": [{"TagInt": []}, 2]}}]}]]}, [{"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": @@ -700,7 +700,7 @@ []}, 1]}}]}}]}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpFlatten": [null, diff --git a/tests/parse_print/autogen-bilals-fixed/d7d816b10a6f459ed78f1bd604bca06f/stdout.expected b/tests/parse_print/autogen-bilals-fixed/d7d816b10a6f459ed78f1bd604bca06f/stdout.expected index 216a6cd82e..8ce3a147bb 100644 --- a/tests/parse_print/autogen-bilals-fixed/d7d816b10a6f459ed78f1bd604bca06f/stdout.expected +++ b/tests/parse_print/autogen-bilals-fixed/d7d816b10a6f459ed78f1bd604bca06f/stdout.expected @@ -38,7 +38,7 @@ such that | q13 : int(1..5)]), q1_ExplicitVarSizeWithMarker_Marker <= 5]), and([q4 + 1 <= var2_PartitionAsSet_ExplicitVarSizeWithMarker_Marker -> - var2_PartitionAsSet_ExplicitVarSizeWithMarker_Values_Explicit_ExplicitVarSizeWithMarker_Marker[q4, ..] - var1_FunctionAsRelation_RelationAsSet_ExplicitVarSizeWithMarker_Values_1_Function1DPartial_Flags[q1, ..] = 1, and([q8 + 1 <= var1_PartitionAsSet_ExplicitR5_ExplicitVarSizeWithMarker_Marker[1] -> - var1_PartitionAsSet_ExplicitR5_ExplicitVarSizeWithMarker_Values[1, q8, ..] var1_PartitionAsSet_ExplicitR5_ExplicitVarSizeWithMarker_Marker[1] -> @@ -36,14 +36,14 @@ such that | q9 : int(1..24)]), var1_PartitionAsSet_ExplicitR5_ExplicitVarSizeWithMarker_Marker[1] <= 24, and([var2_ExplicitVarSizeWithFlagsR10_Flags[q13 + 1] -> - var2_ExplicitVarSizeWithFlagsR10_Values_Function1DPartial_Flags[q13, ..] @@ -87,7 +87,7 @@ such that var4_1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q36] = var4_1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q36 + 1] /\ - var4_1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q36, ..] var4_1_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> diff --git a/tests/parse_print/autogen-bilals-fixed/dad7b9b0bdd9e288f1dc3b19ec96c213/model.expected.json b/tests/parse_print/autogen-bilals-fixed/dad7b9b0bdd9e288f1dc3b19ec96c213/model.expected.json index 52ed1e52b5..1b4daf6cc4 100644 --- a/tests/parse_print/autogen-bilals-fixed/dad7b9b0bdd9e288f1dc3b19ec96c213/model.expected.json +++ b/tests/parse_print/autogen-bilals-fixed/dad7b9b0bdd9e288f1dc3b19ec96c213/model.expected.json @@ -868,7 +868,7 @@ []}, 2]}}]}]]}, [{"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpFlatten": [null, @@ -1066,7 +1066,7 @@ []}, 4]}}]}]]}]}}]]}}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpFlatten": [null, @@ -1391,7 +1391,7 @@ []}, 2]}}]}]]}, [{"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": @@ -1565,7 +1565,7 @@ []}, 2]}}]}]]}]}}]]}}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": @@ -2464,7 +2464,7 @@ []}, 1]}}]]}}}}]}}]}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": diff --git a/tests/parse_print/autogen-bilals-fixed/dad7b9b0bdd9e288f1dc3b19ec96c213/stdout.expected b/tests/parse_print/autogen-bilals-fixed/dad7b9b0bdd9e288f1dc3b19ec96c213/stdout.expected index 1924962a91..27690b8dcb 100644 --- a/tests/parse_print/autogen-bilals-fixed/dad7b9b0bdd9e288f1dc3b19ec96c213/stdout.expected +++ b/tests/parse_print/autogen-bilals-fixed/dad7b9b0bdd9e288f1dc3b19ec96c213/stdout.expected @@ -66,7 +66,7 @@ such that /\ (flatten(var1_PartitionAsSet_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithFlags_Flags [q5, .., ..]) - var1_PartitionAsSet_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithFlags_Flags [q7, q8, ..] - var4_PartitionAsSet_ExplicitVarSizeWithMarker_Marker -> diff --git a/tests/parse_print/autogen-bilals-fixed/dbc08914b7c5505e1136cc21ac9d5125/model.expected.json b/tests/parse_print/autogen-bilals-fixed/dbc08914b7c5505e1136cc21ac9d5125/model.expected.json index 7039c7a25c..5aea320a15 100644 --- a/tests/parse_print/autogen-bilals-fixed/dbc08914b7c5505e1136cc21ac9d5125/model.expected.json +++ b/tests/parse_print/autogen-bilals-fixed/dbc08914b7c5505e1136cc21ac9d5125/model.expected.json @@ -995,7 +995,7 @@ "var2_1_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker"}, null]}]}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": @@ -1488,7 +1488,7 @@ {"ConstantInt": [{"TagInt": []}, 2]}}]}]]}, [{"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": @@ -1622,7 +1622,7 @@ {"DomainBool": []}]}}]]}}}, {"Op": - {"MkOpLexLeq": + {"MkOpDotLeq": [{"Op": {"MkOpSlicing": [{"Op": diff --git a/tests/parse_print/autogen-bilals-fixed/dbc08914b7c5505e1136cc21ac9d5125/stdout.expected b/tests/parse_print/autogen-bilals-fixed/dbc08914b7c5505e1136cc21ac9d5125/stdout.expected index a6cc6b79d9..989247e44a 100644 --- a/tests/parse_print/autogen-bilals-fixed/dbc08914b7c5505e1136cc21ac9d5125/stdout.expected +++ b/tests/parse_print/autogen-bilals-fixed/dbc08914b7c5505e1136cc21ac9d5125/stdout.expected @@ -78,7 +78,7 @@ such that >= 1 | q51 : int(1..4)]), and([q7 + 1 <= var2_1_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> - var2_1_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q7, ..] var2_1_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> @@ -105,14 +105,14 @@ such that | q14 : int(1..9)]), 3 = var4_1_ExplicitWithRepetition_Flag, and([q21 + 1 <= var5_ExplicitWithRepetitionR10_Flag -> - var5_ExplicitWithRepetitionR10_Values_Function1DPartial_Flags[q21, ..] var5_ExplicitWithRepetitionR10_Flag -> diff --git a/tests/parse_print/autogen-bilals-fixed/de9716a7ff65a1574f48f0b1858be3bd/model.expected.json b/tests/parse_print/autogen-bilals-fixed/de9716a7ff65a1574f48f0b1858be3bd/model.expected.json index ab0dbcc494..65f9859bad 100644 --- a/tests/parse_print/autogen-bilals-fixed/de9716a7ff65a1574f48f0b1858be3bd/model.expected.json +++ b/tests/parse_print/autogen-bilals-fixed/de9716a7ff65a1574f48f0b1858be3bd/model.expected.json @@ -943,7 +943,7 @@ []}, 2]}}]}]]}, [{"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": @@ -1080,7 +1080,7 @@ {"DomainBool": []}]}}]]}}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": diff --git a/tests/parse_print/autogen-bilals-fixed/de9716a7ff65a1574f48f0b1858be3bd/stdout.expected b/tests/parse_print/autogen-bilals-fixed/de9716a7ff65a1574f48f0b1858be3bd/stdout.expected index 2bc4c8fb5b..a40953a2ad 100644 --- a/tests/parse_print/autogen-bilals-fixed/de9716a7ff65a1574f48f0b1858be3bd/stdout.expected +++ b/tests/parse_print/autogen-bilals-fixed/de9716a7ff65a1574f48f0b1858be3bd/stdout.expected @@ -61,7 +61,7 @@ such that | q47 : int(1..2)]) | q1 : int(1..31)]), and([q1 + 1 <= var1_FunctionAsRelation_RelationAsSet_ExplicitVarSizeWithMarker_Marker -> - var1_FunctionAsRelation_RelationAsSet_ExplicitVarSizeWithMarker_Values_1_Function1DPartial_Flags[q1, ..] var2_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> diff --git a/tests/parse_print/autogen-bilals-fixed/dec056eee47fd05a251225b16b62ab64/model.expected.json b/tests/parse_print/autogen-bilals-fixed/dec056eee47fd05a251225b16b62ab64/model.expected.json index 68fe789331..db03d648e8 100644 --- a/tests/parse_print/autogen-bilals-fixed/dec056eee47fd05a251225b16b62ab64/model.expected.json +++ b/tests/parse_print/autogen-bilals-fixed/dec056eee47fd05a251225b16b62ab64/model.expected.json @@ -526,7 +526,7 @@ []}, 1]}}]]}}}}]}}]}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpFlatten": [null, @@ -642,7 +642,7 @@ {"Reference": [{"Name": "q5"}, null]}]}}]}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": @@ -1054,7 +1054,7 @@ "var4_2_PartitionAsSet_ExplicitVarSizeWithMarker_Marker"}, null]}]}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": @@ -1353,7 +1353,7 @@ []}, 1]}}]]}}}}]}}]}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": diff --git a/tests/parse_print/autogen-bilals-fixed/dec056eee47fd05a251225b16b62ab64/stdout.expected b/tests/parse_print/autogen-bilals-fixed/dec056eee47fd05a251225b16b62ab64/stdout.expected index 56f45f956c..7f619a18f9 100644 --- a/tests/parse_print/autogen-bilals-fixed/dec056eee47fd05a251225b16b62ab64/stdout.expected +++ b/tests/parse_print/autogen-bilals-fixed/dec056eee47fd05a251225b16b62ab64/stdout.expected @@ -39,11 +39,11 @@ such that var1_PartitionAsSet_Explicit_ExplicitVarSizeWithMarker_Marker[q4] = var1_PartitionAsSet_Explicit_ExplicitVarSizeWithMarker_Marker[q4 + 1] /\ - flatten(var1_PartitionAsSet_Explicit_ExplicitVarSizeWithMarker_Values_Function1D[q4, .., ..]) - var1_PartitionAsSet_Explicit_ExplicitVarSizeWithMarker_Values_Function1D[q5, q6, ..] - var4_2_PartitionAsSet_ExplicitVarSizeWithMarker_Values_Explicit[q35, ..] var4_2_PartitionAsSet_ExplicitVarSizeWithMarker_Marker -> @@ -87,7 +87,7 @@ such that var4_3_PartitionAsSet_Explicit_ExplicitVarSizeWithMarker_Marker[q43] = var4_3_PartitionAsSet_Explicit_ExplicitVarSizeWithMarker_Marker[q43 + 1] /\ - var4_3_PartitionAsSet_Explicit_ExplicitVarSizeWithMarker_Values[q43, ..] var4_3_PartitionAsSet_Explicit_ExplicitVarSizeWithMarker_Marker[q44] -> diff --git a/tests/parse_print/autogen-bilals-fixed/e02f77cea3324e91d885d1f3fe504cd4/model.expected.json b/tests/parse_print/autogen-bilals-fixed/e02f77cea3324e91d885d1f3fe504cd4/model.expected.json index 33559136c8..643284a6ad 100644 --- a/tests/parse_print/autogen-bilals-fixed/e02f77cea3324e91d885d1f3fe504cd4/model.expected.json +++ b/tests/parse_print/autogen-bilals-fixed/e02f77cea3324e91d885d1f3fe504cd4/model.expected.json @@ -122,7 +122,7 @@ []}, 2]}}]}]]}, [{"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": @@ -271,7 +271,7 @@ []}, 2]}}]}]]}]}}]]}}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": diff --git a/tests/parse_print/autogen-bilals-fixed/e02f77cea3324e91d885d1f3fe504cd4/stdout.expected b/tests/parse_print/autogen-bilals-fixed/e02f77cea3324e91d885d1f3fe504cd4/stdout.expected index 247f15e7d8..1cf378dc0b 100644 --- a/tests/parse_print/autogen-bilals-fixed/e02f77cea3324e91d885d1f3fe504cd4/stdout.expected +++ b/tests/parse_print/autogen-bilals-fixed/e02f77cea3324e91d885d1f3fe504cd4/stdout.expected @@ -9,7 +9,7 @@ find var1_FunctionAsRelation_RelationAsSet_ExplicitVarSizeWithMarker_Values_2: m such that and([q1 + 1 <= var1_FunctionAsRelation_RelationAsSet_ExplicitVarSizeWithMarker_Marker -> var1_FunctionAsRelation_RelationAsSet_ExplicitVarSizeWithMarker_Values_1_ExplicitVarSizeWithFlags_Flags[q1, ..] - - var1_FunctionAsRelation_RelationAsSet_ExplicitVarSizeWithMarker_Values_1_Function1DPartial_Flags[q1, ..] and([q7 + 1 <= var2_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[1] -> - var2_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[1, q7, ..] diff --git a/tests/parse_print/autogen-bilals-fixed/e21cd7b0f710515a79d787945d809a81/model.expected.json b/tests/parse_print/autogen-bilals-fixed/e21cd7b0f710515a79d787945d809a81/model.expected.json index 89a0c4299d..e5934a553e 100644 --- a/tests/parse_print/autogen-bilals-fixed/e21cd7b0f710515a79d787945d809a81/model.expected.json +++ b/tests/parse_print/autogen-bilals-fixed/e21cd7b0f710515a79d787945d809a81/model.expected.json @@ -253,7 +253,7 @@ {"ConstantInt": [{"TagInt": []}, 2]}}]}]]}, [{"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": @@ -399,7 +399,7 @@ []}, 3]}}]}]]}]}}]]}}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": @@ -1237,7 +1237,7 @@ []}, 1]}}]]}}}}]}}]}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": diff --git a/tests/parse_print/autogen-bilals-fixed/e21cd7b0f710515a79d787945d809a81/stdout.expected b/tests/parse_print/autogen-bilals-fixed/e21cd7b0f710515a79d787945d809a81/stdout.expected index 2601150149..335350abbe 100644 --- a/tests/parse_print/autogen-bilals-fixed/e21cd7b0f710515a79d787945d809a81/stdout.expected +++ b/tests/parse_print/autogen-bilals-fixed/e21cd7b0f710515a79d787945d809a81/stdout.expected @@ -27,14 +27,14 @@ such that given2, given1, and([q1 + 1 <= var1_ExplicitVarSizeWithMarkerR7_Marker -> - var1_ExplicitVarSizeWithMarkerR7_Values_ExplicitWithFlags_Flags[q1, ..] var1_ExplicitVarSizeWithMarkerR7_Marker -> @@ -84,7 +84,7 @@ such that var3_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q20] = var3_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q20 + 1] /\ - var3_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values_1[q20, ..] var3_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> diff --git a/tests/parse_print/autogen-bilals-fixed/e31e8258961a4a8fa32e4eb491491bdc/model.expected.json b/tests/parse_print/autogen-bilals-fixed/e31e8258961a4a8fa32e4eb491491bdc/model.expected.json index c722bb7aa6..7932acb80a 100644 --- a/tests/parse_print/autogen-bilals-fixed/e31e8258961a4a8fa32e4eb491491bdc/model.expected.json +++ b/tests/parse_print/autogen-bilals-fixed/e31e8258961a4a8fa32e4eb491491bdc/model.expected.json @@ -107,7 +107,7 @@ [{"Constant": {"ConstantInt": [{"TagInt": []}, 1]}}, {"Constant": {"ConstantInt": [{"TagInt": []}, 2]}}]}]]}, [{"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": @@ -225,7 +225,7 @@ []}, 2]}}]}]]}, [{"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": @@ -257,7 +257,7 @@ null, null]}}]}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": diff --git a/tests/parse_print/autogen-bilals-fixed/e31e8258961a4a8fa32e4eb491491bdc/stdout.expected b/tests/parse_print/autogen-bilals-fixed/e31e8258961a4a8fa32e4eb491491bdc/stdout.expected index 0fba244841..d355acd51a 100644 --- a/tests/parse_print/autogen-bilals-fixed/e31e8258961a4a8fa32e4eb491491bdc/stdout.expected +++ b/tests/parse_print/autogen-bilals-fixed/e31e8258961a4a8fa32e4eb491491bdc/stdout.expected @@ -10,18 +10,17 @@ find var1_FunctionAsRelation_RelationAsSet_ExplicitVarSizeWithMarker_Values_2_Ex find var2_RelationAsMatrix: matrix indexed by [int(4, 5), bool, bool, bool, bool] of bool such that 2 <= var1_FunctionAsRelation_RelationAsSet_ExplicitVarSizeWithMarker_Marker -> - var1_FunctionAsRelation_RelationAsSet_ExplicitVarSizeWithMarker_Values_1[1, ..] var1_FunctionAsRelation_RelationAsSet_ExplicitVarSizeWithMarker_Marker -> and([var1_FunctionAsRelation_RelationAsSet_ExplicitVarSizeWithMarker_Values_1[q2, q38] = false diff --git a/tests/parse_print/autogen-bilals-fixed/e33c5a4b1eca296873386a312774d872/model.expected.json b/tests/parse_print/autogen-bilals-fixed/e33c5a4b1eca296873386a312774d872/model.expected.json index 34c6107eb9..56e28caaad 100644 --- a/tests/parse_print/autogen-bilals-fixed/e33c5a4b1eca296873386a312774d872/model.expected.json +++ b/tests/parse_print/autogen-bilals-fixed/e33c5a4b1eca296873386a312774d872/model.expected.json @@ -57,7 +57,7 @@ {"Constant": {"ConstantInt": [{"TagInt": []}, 5]}}]}]]}]}]}]}}, {"SuchThat": [{"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Comprehension": [{"Reference": [{"Name": "l_1"}, null]}, [{"Generator": {"GenDomainNoRepr": [{"Single": {"Name": "l_1"}}, {"DomainBool": []}]}}]]}, diff --git a/tests/parse_print/autogen-bilals-fixed/e33c5a4b1eca296873386a312774d872/stdout.expected b/tests/parse_print/autogen-bilals-fixed/e33c5a4b1eca296873386a312774d872/stdout.expected index dba7e22f7d..f96d16b7c5 100644 --- a/tests/parse_print/autogen-bilals-fixed/e33c5a4b1eca296873386a312774d872/stdout.expected +++ b/tests/parse_print/autogen-bilals-fixed/e33c5a4b1eca296873386a312774d872/stdout.expected @@ -4,5 +4,5 @@ find var1: mset (minSize factorial(3), maxOccur 5 - 2) of mset (size 0, minOccur find var2: partition (maxNumParts 2, minPartSize 4, maxPartSize 5, regular) from matrix indexed by [int(2, 5)] of int(5, 5) such that - [l_1 | l_1 : bool] var1_1_PartitionAsSet_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMarker_Values_Function1D [q6, q7, ..] - 0 -> - var1_2_ExplicitVarSizeWithFlags_Values_Function1DPartial_Flags[q11, ..] diff --git a/tests/parse_print/autogen-bilals-fixed/e5ef686faac39c34b542eec223509aa8/model.expected.json b/tests/parse_print/autogen-bilals-fixed/e5ef686faac39c34b542eec223509aa8/model.expected.json index 7f1afcd48c..b97859243d 100644 --- a/tests/parse_print/autogen-bilals-fixed/e5ef686faac39c34b542eec223509aa8/model.expected.json +++ b/tests/parse_print/autogen-bilals-fixed/e5ef686faac39c34b542eec223509aa8/model.expected.json @@ -785,7 +785,7 @@ []}, 2]}}]}]]}, [{"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": @@ -937,7 +937,7 @@ []}, 4]}}}]]}]}}]]}}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": diff --git a/tests/parse_print/autogen-bilals-fixed/e5ef686faac39c34b542eec223509aa8/stdout.expected b/tests/parse_print/autogen-bilals-fixed/e5ef686faac39c34b542eec223509aa8/stdout.expected index 221b9fcf88..2a04076e7e 100644 --- a/tests/parse_print/autogen-bilals-fixed/e5ef686faac39c34b542eec223509aa8/stdout.expected +++ b/tests/parse_print/autogen-bilals-fixed/e5ef686faac39c34b542eec223509aa8/stdout.expected @@ -51,7 +51,7 @@ such that | q37 : int(1..2)]) | q1 : int(1..7)]), and([q1 + 1 <= var1_FunctionAsRelation_RelationAsSet_ExplicitVarSizeWithMarker_Marker -> - var1_FunctionAsRelation_RelationAsSet_ExplicitVarSizeWithMarker_Values_1_Function1DPartial_Flags[q1, ..] - var1_ExplicitVarSizeWithMarkerR7_Values_ExplicitWithFlags_Flags[q1, ..] var1_ExplicitVarSizeWithMarkerR7_Marker -> @@ -82,7 +82,7 @@ such that var3_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q21] = var3_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q21 + 1] /\ - var3_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values_1[q21, ..] var3_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> diff --git a/tests/parse_print/autogen-bilals-fixed/e7a6d29d4285dcfdd7daddc00be2c882/model.expected.json b/tests/parse_print/autogen-bilals-fixed/e7a6d29d4285dcfdd7daddc00be2c882/model.expected.json index 2a7778a066..ed29ce8955 100644 --- a/tests/parse_print/autogen-bilals-fixed/e7a6d29d4285dcfdd7daddc00be2c882/model.expected.json +++ b/tests/parse_print/autogen-bilals-fixed/e7a6d29d4285dcfdd7daddc00be2c882/model.expected.json @@ -271,7 +271,7 @@ {"ConstantInt": [{"TagInt": []}, 2]}}]}]]}, [{"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": @@ -652,7 +652,7 @@ []}, 1]}}]]}}}}]}}]}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": @@ -1234,7 +1234,7 @@ {"Op": {"MkOpImply": [{"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": diff --git a/tests/parse_print/autogen-bilals-fixed/e7a6d29d4285dcfdd7daddc00be2c882/stdout.expected b/tests/parse_print/autogen-bilals-fixed/e7a6d29d4285dcfdd7daddc00be2c882/stdout.expected index d2b3fc1e96..c5eee5bb9f 100644 --- a/tests/parse_print/autogen-bilals-fixed/e7a6d29d4285dcfdd7daddc00be2c882/stdout.expected +++ b/tests/parse_print/autogen-bilals-fixed/e7a6d29d4285dcfdd7daddc00be2c882/stdout.expected @@ -27,7 +27,7 @@ find var3_RelationAsSetR15_ExplicitVarSizeWithMarkerR15_Values_1_RelationAsMatri such that false, and([q6 + 1 <= var1_FunctionAsRelationR2R5_RelationAsSetR2R5_ExplicitVarSizeWithMarkerR2R5_Marker -> - var1_FunctionAsRelationR2R5_RelationAsSetR2R5_ExplicitVarSizeWithMarkerR2R5_Values_1_Occurrence[q6, ..] - (var1_FunctionAsRelationR2R5_RelationAsSetR2R5_ExplicitVarSizeWithMarkerR2R5_Values_1_Occurrence[q29, ..] or([q32 <= diff --git a/tests/parse_print/autogen-bilals-fixed/e7f89fcbcdbd0a79caefef0e87678c8d/model.expected.json b/tests/parse_print/autogen-bilals-fixed/e7f89fcbcdbd0a79caefef0e87678c8d/model.expected.json index f858f124ef..97fa4cb94d 100644 --- a/tests/parse_print/autogen-bilals-fixed/e7f89fcbcdbd0a79caefef0e87678c8d/model.expected.json +++ b/tests/parse_print/autogen-bilals-fixed/e7f89fcbcdbd0a79caefef0e87678c8d/model.expected.json @@ -2258,7 +2258,7 @@ []}, 2]}}]}]]}, [{"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpFlatten": [null, @@ -2460,7 +2460,7 @@ []}, 16]}}]}]]}]}}]]}}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpFlatten": [null, @@ -2795,7 +2795,7 @@ []}, 2]}}]}]]}, [{"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": @@ -2973,7 +2973,7 @@ []}, 1]}}}}]}]]}]}}]]}}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": diff --git a/tests/parse_print/autogen-bilals-fixed/e7f89fcbcdbd0a79caefef0e87678c8d/stdout.expected b/tests/parse_print/autogen-bilals-fixed/e7f89fcbcdbd0a79caefef0e87678c8d/stdout.expected index 514c2d330f..b173af69c1 100644 --- a/tests/parse_print/autogen-bilals-fixed/e7f89fcbcdbd0a79caefef0e87678c8d/stdout.expected +++ b/tests/parse_print/autogen-bilals-fixed/e7f89fcbcdbd0a79caefef0e87678c8d/stdout.expected @@ -122,7 +122,7 @@ such that /\ (flatten(var3_PartitionAsSet_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMarker_Values_Function1DPartial_Flags [q1, .., ..]) - var3_PartitionAsSet_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMarker_Values_Function1DPartial_Flags [q1, q2, ..] - or([false, false, false, true, false; int(11..12, 3, 0, 8)]), - flatten([0, 2, 0, 2, 1; int(12..13, 7, 6, 8)]) + flatten([0, 2, 0, 2, 1; int(12..13, 7, 6, 8)]) .< [2 % 2, 3 ** 0, -2; int(0..2)], + [false; int(0)] .< [false; int(1)] -> together({false, true, false}, partition({false}, {true}, {false, true, false}, {false, false, true, false, true})) diff --git a/tests/parse_print/autogen-bilals-fixed/e94042e71ae4aca4b2dcbe6a1c03eeb5/model.expected.json b/tests/parse_print/autogen-bilals-fixed/e94042e71ae4aca4b2dcbe6a1c03eeb5/model.expected.json index 04792e5eb5..5132374507 100644 --- a/tests/parse_print/autogen-bilals-fixed/e94042e71ae4aca4b2dcbe6a1c03eeb5/model.expected.json +++ b/tests/parse_print/autogen-bilals-fixed/e94042e71ae4aca4b2dcbe6a1c03eeb5/model.expected.json @@ -283,7 +283,7 @@ 1]}}]]}}}}]}}, {"Constant": {"ConstantInt": [{"TagInt": []}, 0]}}]}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": diff --git a/tests/parse_print/autogen-bilals-fixed/e94042e71ae4aca4b2dcbe6a1c03eeb5/stdout.expected b/tests/parse_print/autogen-bilals-fixed/e94042e71ae4aca4b2dcbe6a1c03eeb5/stdout.expected index a06b896120..b0eb6c0a7a 100644 --- a/tests/parse_print/autogen-bilals-fixed/e94042e71ae4aca4b2dcbe6a1c03eeb5/stdout.expected +++ b/tests/parse_print/autogen-bilals-fixed/e94042e71ae4aca4b2dcbe6a1c03eeb5/stdout.expected @@ -18,7 +18,7 @@ such that | q12 : int(1..nrings)]) | q11 : int(1..fin1)]), and([network_ExplicitWithFlagsR2_Flags[q1 + 1] > 0 -> - network_ExplicitWithFlagsR2_Values_Occurrence[q1, ..] diff --git a/tests/parse_print/autogen-bilals-fixed/e94f81e31dce6a8efb7cdffe25cc7a9a/model.expected.json b/tests/parse_print/autogen-bilals-fixed/e94f81e31dce6a8efb7cdffe25cc7a9a/model.expected.json index 1000b745a1..c8ba26e0df 100644 --- a/tests/parse_print/autogen-bilals-fixed/e94f81e31dce6a8efb7cdffe25cc7a9a/model.expected.json +++ b/tests/parse_print/autogen-bilals-fixed/e94f81e31dce6a8efb7cdffe25cc7a9a/model.expected.json @@ -165,7 +165,7 @@ {"ConstantInt": [{"TagInt": []}, 2]}}]}]]}, [{"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": @@ -215,7 +215,7 @@ 1]}}]]}}}}]}}, null, null]}}]}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": @@ -698,7 +698,7 @@ [{"TagInt": []}, 2]}}]}}]}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpFlatten": [null, @@ -926,7 +926,7 @@ [{"Name": "q20"}, null]}]}}]}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": diff --git a/tests/parse_print/autogen-bilals-fixed/e94f81e31dce6a8efb7cdffe25cc7a9a/stdout.expected b/tests/parse_print/autogen-bilals-fixed/e94f81e31dce6a8efb7cdffe25cc7a9a/stdout.expected index 2cf3448a65..5b0211d599 100644 --- a/tests/parse_print/autogen-bilals-fixed/e94f81e31dce6a8efb7cdffe25cc7a9a/stdout.expected +++ b/tests/parse_print/autogen-bilals-fixed/e94f81e31dce6a8efb7cdffe25cc7a9a/stdout.expected @@ -13,10 +13,10 @@ find var2_PartitionAsSet_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMar such that false, and([var1_ExplicitVarSizeWithFlags_Flags[q1 + 1] > 0 -> - var1_ExplicitVarSizeWithFlags_Values_ExplicitVarSizeWithFlags_Flags[q1, ..] 0 -> var1_ExplicitVarSizeWithFlags_Flags[q3] > 0 @@ -48,7 +48,7 @@ such that var2_PartitionAsSet_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMarker_Marker[1] = var2_PartitionAsSet_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMarker_Marker[2] /\ - flatten(var2_PartitionAsSet_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMarker_Values[1, .., ..]) var2_PartitionAsSet_ExplicitVarSizeWithMarker_Marker -> var2_PartitionAsSet_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMarker_Marker[q19] = 0 /\ @@ -59,7 +59,7 @@ such that var2_PartitionAsSet_ExplicitVarSizeWithMarker_Marker <= 2, and([q20 <= var2_PartitionAsSet_ExplicitVarSizeWithMarker_Marker -> and([q21 + 1 <= var2_PartitionAsSet_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMarker_Marker[q20] -> - var2_PartitionAsSet_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMarker_Values[q20, q21, ..] = 1 | q42 : int(1..4)]), and([q7 + 1 <= var2_1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> - var2_1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy[q7, ..] var2_1_PartitionAsSet_ExplicitVarSizeWithMarkerR6_Marker -> @@ -124,14 +124,14 @@ such that | q17 : int(1..9)]), 3 = var4_1_ExplicitWithRepetition_Flag, and([var5_ExplicitWithFlagsR10_Flags[q24 + 1] > 0 -> - var5_ExplicitWithFlagsR10_Values_Function1DPartial_Flags[q24, ..] diff --git a/tests/parse_print/autogen-bilals-fixed/eb0e88cd958943e2e87a5ade86710827/model.expected.json b/tests/parse_print/autogen-bilals-fixed/eb0e88cd958943e2e87a5ade86710827/model.expected.json index acf1251b7a..f54a8a3be3 100644 --- a/tests/parse_print/autogen-bilals-fixed/eb0e88cd958943e2e87a5ade86710827/model.expected.json +++ b/tests/parse_print/autogen-bilals-fixed/eb0e88cd958943e2e87a5ade86710827/model.expected.json @@ -542,7 +542,7 @@ {"AbstractLiteral": {"AbsLitRelation": [[{"Op": - {"MkOpLexLeq": + {"MkOpDotLeq": [{"Constant": {"ConstantAbstract": {"AbsLitMatrix": diff --git a/tests/parse_print/autogen-bilals-fixed/eb0e88cd958943e2e87a5ade86710827/stdout.expected b/tests/parse_print/autogen-bilals-fixed/eb0e88cd958943e2e87a5ade86710827/stdout.expected index 89ad42c451..c86893edf1 100644 --- a/tests/parse_print/autogen-bilals-fixed/eb0e88cd958943e2e87a5ade86710827/stdout.expected +++ b/tests/parse_print/autogen-bilals-fixed/eb0e88cd958943e2e87a5ade86710827/stdout.expected @@ -66,7 +66,7 @@ such that mset(true)}, {(mset() : `mset of bool`), mset(true, false), mset(false)}))), flatten([mset(true), mset(true), mset(false); int(2..3, 6)]) - --> relation(([false, true, false, false, true; int(3, 7..10)] <=lex [false; int(2)], + --> relation(([false, true, false, false, true; int(3, 7..10)] .<= [false; int(2)], partition({relation(tuple (false), tuple (false), tuple (true)), relation(tuple (true), tuple (false), tuple (false)), relation(tuple (false))}, diff --git a/tests/parse_print/autogen-bilals-fixed/eb22d7172ced999f8568dccf4a1a3d94/model.expected.json b/tests/parse_print/autogen-bilals-fixed/eb22d7172ced999f8568dccf4a1a3d94/model.expected.json index bdda6165f7..bc5bc0c590 100644 --- a/tests/parse_print/autogen-bilals-fixed/eb22d7172ced999f8568dccf4a1a3d94/model.expected.json +++ b/tests/parse_print/autogen-bilals-fixed/eb22d7172ced999f8568dccf4a1a3d94/model.expected.json @@ -304,7 +304,7 @@ []}, 2]}}]}]]}, [{"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": @@ -454,7 +454,7 @@ []}, 4]}}]}]]}]}}]]}}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpFlatten": [null, @@ -1331,7 +1331,7 @@ []}, 1]}}]]}}}}]}}]}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": diff --git a/tests/parse_print/autogen-bilals-fixed/eb22d7172ced999f8568dccf4a1a3d94/stdout.expected b/tests/parse_print/autogen-bilals-fixed/eb22d7172ced999f8568dccf4a1a3d94/stdout.expected index 708a50b442..ae08994656 100644 --- a/tests/parse_print/autogen-bilals-fixed/eb22d7172ced999f8568dccf4a1a3d94/stdout.expected +++ b/tests/parse_print/autogen-bilals-fixed/eb22d7172ced999f8568dccf4a1a3d94/stdout.expected @@ -24,7 +24,7 @@ such that /\ (var1_ExplicitVarSizeWithFlags_Values_PartitionAsSet_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMarker_Marker [q1, ..] - - var5_ExplicitWithRepetitionR10_Values_Function1DPartial_Flags[q23, ..] var5_ExplicitWithRepetitionR10_Flag -> diff --git a/tests/parse_print/autogen-bilals-fixed/ec9aed752e5eeb363b644516fc85dd8f/model.expected.json b/tests/parse_print/autogen-bilals-fixed/ec9aed752e5eeb363b644516fc85dd8f/model.expected.json index 6e24c82c47..5048544557 100644 --- a/tests/parse_print/autogen-bilals-fixed/ec9aed752e5eeb363b644516fc85dd8f/model.expected.json +++ b/tests/parse_print/autogen-bilals-fixed/ec9aed752e5eeb363b644516fc85dd8f/model.expected.json @@ -311,7 +311,7 @@ []}, 1]}}]]}}}}]}}]}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpFlatten": [null, diff --git a/tests/parse_print/autogen-bilals-fixed/ec9aed752e5eeb363b644516fc85dd8f/stdout.expected b/tests/parse_print/autogen-bilals-fixed/ec9aed752e5eeb363b644516fc85dd8f/stdout.expected index 3bb7e8e104..8cd3428686 100644 --- a/tests/parse_print/autogen-bilals-fixed/ec9aed752e5eeb363b644516fc85dd8f/stdout.expected +++ b/tests/parse_print/autogen-bilals-fixed/ec9aed752e5eeb363b644516fc85dd8f/stdout.expected @@ -28,7 +28,7 @@ such that /\ flatten(var2_PartitionAsSetR2_ExplicitVarSizeWithMarkerR5R2_Values_ExplicitVarSizeWithMarkerR2_Values_Occurrence [q4, .., ..]) - - var1_FunctionAsRelation_RelationAsSet_ExplicitVarSizeWithMarker_Values_1[q1, ..] var1_FunctionAsRelation_RelationAsSet_ExplicitVarSizeWithMarker_Marker -> diff --git a/tests/parse_print/autogen-bilals-fixed/ed529213e4789b79a6929c96d89b6eb2/model.expected.json b/tests/parse_print/autogen-bilals-fixed/ed529213e4789b79a6929c96d89b6eb2/model.expected.json index b262d56aca..2fd3115022 100644 --- a/tests/parse_print/autogen-bilals-fixed/ed529213e4789b79a6929c96d89b6eb2/model.expected.json +++ b/tests/parse_print/autogen-bilals-fixed/ed529213e4789b79a6929c96d89b6eb2/model.expected.json @@ -224,7 +224,7 @@ "var3_PartitionAsSet_ExplicitVarSizeWithMarker_Marker"}, null]}]}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": diff --git a/tests/parse_print/autogen-bilals-fixed/ed529213e4789b79a6929c96d89b6eb2/stdout.expected b/tests/parse_print/autogen-bilals-fixed/ed529213e4789b79a6929c96d89b6eb2/stdout.expected index 5649e48049..b93555a35d 100644 --- a/tests/parse_print/autogen-bilals-fixed/ed529213e4789b79a6929c96d89b6eb2/stdout.expected +++ b/tests/parse_print/autogen-bilals-fixed/ed529213e4789b79a6929c96d89b6eb2/stdout.expected @@ -21,7 +21,7 @@ such that sum([var3_PartitionAsSet_ExplicitVarSizeWithMarker_Values_Occurrence[q17, q18] | q18 : int(2..4, 1)]) >= 1 | q17 : int(1..16)]), and([q7 + 1 <= var3_PartitionAsSet_ExplicitVarSizeWithMarker_Marker -> - var3_PartitionAsSet_ExplicitVarSizeWithMarker_Values_Occurrence[q7, ..] var3_PartitionAsSet_ExplicitVarSizeWithMarker_Marker -> diff --git a/tests/parse_print/autogen-bilals-fixed/ed6e2ac3457110fd811f7f6066338883/model.expected.json b/tests/parse_print/autogen-bilals-fixed/ed6e2ac3457110fd811f7f6066338883/model.expected.json index c9b800ba45..29f07ed70e 100644 --- a/tests/parse_print/autogen-bilals-fixed/ed6e2ac3457110fd811f7f6066338883/model.expected.json +++ b/tests/parse_print/autogen-bilals-fixed/ed6e2ac3457110fd811f7f6066338883/model.expected.json @@ -420,7 +420,7 @@ {"ConstantInt": [{"TagInt": []}, 2]}}]}]]}, [{"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpFlatten": [null, @@ -593,7 +593,7 @@ []}, 5]}}]}]]}]}}]]}}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpFlatten": [null, diff --git a/tests/parse_print/autogen-bilals-fixed/ed6e2ac3457110fd811f7f6066338883/stdout.expected b/tests/parse_print/autogen-bilals-fixed/ed6e2ac3457110fd811f7f6066338883/stdout.expected index dfa095ed69..ef6f91da9b 100644 --- a/tests/parse_print/autogen-bilals-fixed/ed6e2ac3457110fd811f7f6066338883/stdout.expected +++ b/tests/parse_print/autogen-bilals-fixed/ed6e2ac3457110fd811f7f6066338883/stdout.expected @@ -31,7 +31,7 @@ such that and([q4 + 1 <= var2_PartitionAsSet_ExplicitVarSizeWithMarker_Marker -> flatten(var2_PartitionAsSet_ExplicitVarSizeWithMarker_Values_Explicit_ExplicitVarSizeWithFlags_Flags [q4, .., ..]) - - var1_ExplicitVarSizeWithFlags_Values_Function1D[q1, ..] @@ -54,7 +54,7 @@ such that | q21 : int(1..5)]), q9_ExplicitVarSizeWithMarker_Marker <= 5]), and([q12 + 1 <= var2_PartitionAsSet_ExplicitVarSizeWithMarker_Marker -> - var2_PartitionAsSet_ExplicitVarSizeWithMarker_Values_Explicit_ExplicitVarSizeWithMarker_Marker[q12, ..] flatten(var2_PartitionAsSet_ExplicitVarSizeWithMarker_Values_Explicit_ExplicitVarSizeWithFlags_Flags [q4, .., ..]) - var1_FunctionAsRelation_RelationAsSet_ExplicitVarSizeWithMarker_Values_1_ExplicitVarSizeWithFlags_Flags[q1, ..] - var1_FunctionAsRelation_RelationAsSet_ExplicitVarSizeWithMarker_Marker -> diff --git a/tests/parse_print/autogen-bilals-fixed/eee79bab97319cb6a1cfb2a945bcc1a6/model.expected.json b/tests/parse_print/autogen-bilals-fixed/eee79bab97319cb6a1cfb2a945bcc1a6/model.expected.json index d185d120ea..cd6ee9b3a8 100644 --- a/tests/parse_print/autogen-bilals-fixed/eee79bab97319cb6a1cfb2a945bcc1a6/model.expected.json +++ b/tests/parse_print/autogen-bilals-fixed/eee79bab97319cb6a1cfb2a945bcc1a6/model.expected.json @@ -271,7 +271,7 @@ {"ConstantInt": [{"TagInt": []}, 2]}}]}]]}, [{"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": @@ -652,7 +652,7 @@ []}, 1]}}]]}}}}]}}]}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": @@ -1342,7 +1342,7 @@ {"Op": {"MkOpImply": [{"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": diff --git a/tests/parse_print/autogen-bilals-fixed/eee79bab97319cb6a1cfb2a945bcc1a6/stdout.expected b/tests/parse_print/autogen-bilals-fixed/eee79bab97319cb6a1cfb2a945bcc1a6/stdout.expected index 3526d1286f..180d32c374 100644 --- a/tests/parse_print/autogen-bilals-fixed/eee79bab97319cb6a1cfb2a945bcc1a6/stdout.expected +++ b/tests/parse_print/autogen-bilals-fixed/eee79bab97319cb6a1cfb2a945bcc1a6/stdout.expected @@ -27,7 +27,7 @@ find var3_RelationAsSetR15_ExplicitVarSizeWithMarkerR15_Values_1_RelationAsMatri such that false, and([q6 + 1 <= var1_FunctionAsRelationR2R5_RelationAsSetR2R5_ExplicitVarSizeWithMarkerR2R5_Marker -> - var1_FunctionAsRelationR2R5_RelationAsSetR2R5_ExplicitVarSizeWithMarkerR2R5_Values_1_Occurrence[q6, ..] - (var1_FunctionAsRelationR2R5_RelationAsSetR2R5_ExplicitVarSizeWithMarkerR2R5_Values_1_Occurrence[q25, ..] or([q28 <= diff --git a/tests/parse_print/autogen-bilals-fixed/ef336eba26eb0a9a90de40b18d840b84/model.expected.json b/tests/parse_print/autogen-bilals-fixed/ef336eba26eb0a9a90de40b18d840b84/model.expected.json index d7d4371979..ce46917679 100644 --- a/tests/parse_print/autogen-bilals-fixed/ef336eba26eb0a9a90de40b18d840b84/model.expected.json +++ b/tests/parse_print/autogen-bilals-fixed/ef336eba26eb0a9a90de40b18d840b84/model.expected.json @@ -76,7 +76,7 @@ {"ConstantInt": [{"TagInt": []}, 2]}}]}]]}, [{"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": @@ -210,7 +210,7 @@ {"DomainBool": []}]}}]]}}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": diff --git a/tests/parse_print/autogen-bilals-fixed/ef336eba26eb0a9a90de40b18d840b84/stdout.expected b/tests/parse_print/autogen-bilals-fixed/ef336eba26eb0a9a90de40b18d840b84/stdout.expected index 386e83cec2..0ba10f9849 100644 --- a/tests/parse_print/autogen-bilals-fixed/ef336eba26eb0a9a90de40b18d840b84/stdout.expected +++ b/tests/parse_print/autogen-bilals-fixed/ef336eba26eb0a9a90de40b18d840b84/stdout.expected @@ -5,14 +5,14 @@ find var3_ExplicitVarSizeWithFlags_Values_Function1DPartial_Flags: matrix indexe find var3_ExplicitVarSizeWithFlags_Values_Function1DPartial_Values: matrix indexed by [int(1..3), bool] of bool such that and([var3_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - var3_ExplicitVarSizeWithFlags_Values_Function1DPartial_Flags[q1, ..] diff --git a/tests/parse_print/autogen-bilals-fixed/ef47512eb208c3dc333c0f019cdd3b41/model.expected.json b/tests/parse_print/autogen-bilals-fixed/ef47512eb208c3dc333c0f019cdd3b41/model.expected.json index c2d467ae11..a2e21ca53b 100644 --- a/tests/parse_print/autogen-bilals-fixed/ef47512eb208c3dc333c0f019cdd3b41/model.expected.json +++ b/tests/parse_print/autogen-bilals-fixed/ef47512eb208c3dc333c0f019cdd3b41/model.expected.json @@ -144,7 +144,7 @@ {"TypeSet": {"TypeInt": {"TagInt": []}}}, {"TypeMatrix": [{"TypeInt": {"TagInt": []}}, {"TypeBool": []}]}]}}]}]}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Constant": {"ConstantAbstract": {"AbsLitMatrix": @@ -319,7 +319,7 @@ {"ConstantInt": [{"TagInt": []}, 1]}, {"ConstantInt": [{"TagInt": []}, 3]}]]}}}]]}}]}}, {"Op": - {"MkOpLexLeq": + {"MkOpDotLeq": [{"Comprehension": [{"Reference": [{"Name": "l_2"}, null]}, [{"Generator": diff --git a/tests/parse_print/autogen-bilals-fixed/ef47512eb208c3dc333c0f019cdd3b41/stdout.expected b/tests/parse_print/autogen-bilals-fixed/ef47512eb208c3dc333c0f019cdd3b41/stdout.expected index d187cc6af3..cf6803770f 100644 --- a/tests/parse_print/autogen-bilals-fixed/ef47512eb208c3dc333c0f019cdd3b41/stdout.expected +++ b/tests/parse_print/autogen-bilals-fixed/ef47512eb208c3dc333c0f019cdd3b41/stdout.expected @@ -13,7 +13,7 @@ such that true, ([false; int(0)], (false, 1), {5, 3}, [true, false; int(0..1)]) in (mset() : `mset of (matrix indexed by [int] of bool, (bool, int), set of int, matrix indexed by [int] of bool)`), - [true; int(2)] partition({1 % 3, 0 % 1, 3}, {1, 0}, {0, 3}, {2 - 3}, {factorial(1), 5 - 0}), image(function(true --> true, false --> true, true --> true), true) --> partition({3, 5, 0, 5}, {3}, {5, 0, 1, 3}, {2, 1, 3}))), - [l_2 | l_1 : int(5, 0), l_2 : int(5, 1..5), false, true] <=lex + [l_2 | l_1 : int(5, 0), l_2 : int(5, 1..5), false, true] .<= image((function() : `function mset of bool --> matrix indexed by [int] of int`), mset(false)) diff --git a/tests/parse_print/autogen-bilals-fixed/f0da1b32d64901550697edd2a56acbb1/model.expected.json b/tests/parse_print/autogen-bilals-fixed/f0da1b32d64901550697edd2a56acbb1/model.expected.json index 7a869bf691..0c35c6d467 100644 --- a/tests/parse_print/autogen-bilals-fixed/f0da1b32d64901550697edd2a56acbb1/model.expected.json +++ b/tests/parse_print/autogen-bilals-fixed/f0da1b32d64901550697edd2a56acbb1/model.expected.json @@ -8,7 +8,7 @@ [{"Declaration": {"FindOrGiven": ["Find", {"Name": "unused"}, {"DomainBool": []}]}}, {"SuchThat": [{"Op": - {"MkOpLexLeq": + {"MkOpDotLeq": [{"Op": {"MkOpImage": [{"Constant": diff --git a/tests/parse_print/autogen-bilals-fixed/f0da1b32d64901550697edd2a56acbb1/stdout.expected b/tests/parse_print/autogen-bilals-fixed/f0da1b32d64901550697edd2a56acbb1/stdout.expected index 15728085d8..1b141cdf4c 100644 --- a/tests/parse_print/autogen-bilals-fixed/f0da1b32d64901550697edd2a56acbb1/stdout.expected +++ b/tests/parse_print/autogen-bilals-fixed/f0da1b32d64901550697edd2a56acbb1/stdout.expected @@ -1,4 +1,4 @@ language Essence 1.3 find unused: bool -such that image(function(mset(4) --> [2; int(1)]), mset(3)) <=lex [l_3 | l_3 : int(5, 4)] +such that image(function(mset(4) --> [2; int(1)]), mset(3)) .<= [l_3 | l_3 : int(5, 4)] diff --git a/tests/parse_print/autogen-bilals-fixed/f0fc2fcf48b2784adbc82bebe8debe1d/model.expected.json b/tests/parse_print/autogen-bilals-fixed/f0fc2fcf48b2784adbc82bebe8debe1d/model.expected.json index 489aa8d5dd..1171cd7eb9 100644 --- a/tests/parse_print/autogen-bilals-fixed/f0fc2fcf48b2784adbc82bebe8debe1d/model.expected.json +++ b/tests/parse_print/autogen-bilals-fixed/f0fc2fcf48b2784adbc82bebe8debe1d/model.expected.json @@ -356,7 +356,7 @@ []}, 2]}}]}]]}, [{"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": @@ -409,7 +409,7 @@ null, null]}}]}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpFlatten": [null, diff --git a/tests/parse_print/autogen-bilals-fixed/f0fc2fcf48b2784adbc82bebe8debe1d/stdout.expected b/tests/parse_print/autogen-bilals-fixed/f0fc2fcf48b2784adbc82bebe8debe1d/stdout.expected index 72c83a9605..32d6042046 100644 --- a/tests/parse_print/autogen-bilals-fixed/f0fc2fcf48b2784adbc82bebe8debe1d/stdout.expected +++ b/tests/parse_print/autogen-bilals-fixed/f0fc2fcf48b2784adbc82bebe8debe1d/stdout.expected @@ -30,13 +30,13 @@ such that /\ (var2_PartitionAsSetR5_ExplicitVarSizeWithMarkerR5R5_Values_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker [q4, ..] - false, var2 --> true, var2 --> false, var1 --> true, var2 --> true), var1), diff --git a/tests/parse_print/autogen-bilals-fixed/f1fd537fecc6c852b01a571e701d7e59/model.expected.json b/tests/parse_print/autogen-bilals-fixed/f1fd537fecc6c852b01a571e701d7e59/model.expected.json index bb0dc52a3f..a8e4acfecc 100644 --- a/tests/parse_print/autogen-bilals-fixed/f1fd537fecc6c852b01a571e701d7e59/model.expected.json +++ b/tests/parse_print/autogen-bilals-fixed/f1fd537fecc6c852b01a571e701d7e59/model.expected.json @@ -128,7 +128,7 @@ [{"TagInt": []}, 2]}}]}}]}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpFlatten": [null, @@ -320,7 +320,7 @@ [{"Name": "q3"}, null]}]}}]}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": diff --git a/tests/parse_print/autogen-bilals-fixed/f1fd537fecc6c852b01a571e701d7e59/stdout.expected b/tests/parse_print/autogen-bilals-fixed/f1fd537fecc6c852b01a571e701d7e59/stdout.expected index e46782d9ae..ee17ed3ef0 100644 --- a/tests/parse_print/autogen-bilals-fixed/f1fd537fecc6c852b01a571e701d7e59/stdout.expected +++ b/tests/parse_print/autogen-bilals-fixed/f1fd537fecc6c852b01a571e701d7e59/stdout.expected @@ -14,7 +14,7 @@ such that var6_ExplicitVarSizeWithMarker_Values_PartitionAsSet_ExplicitVarSizeWithMarker_Marker[2] /\ flatten(var6_ExplicitVarSizeWithMarker_Values_PartitionAsSet_ExplicitVarSizeWithMarker_Values_Explicit[1, .., ..]) - var6_ExplicitVarSizeWithMarker_Marker -> var6_ExplicitVarSizeWithMarker_Values_PartitionAsSet_ExplicitVarSizeWithMarker_Marker[q2] = 0 @@ -27,7 +27,7 @@ such that and([q3 <= var6_ExplicitVarSizeWithMarker_Marker -> and([q7 + 1 <= var6_ExplicitVarSizeWithMarker_Values_PartitionAsSet_ExplicitVarSizeWithMarker_Marker[q3] -> var6_ExplicitVarSizeWithMarker_Values_PartitionAsSet_ExplicitVarSizeWithMarker_Values_Explicit[q3, q7, ..] - [false, true, false, false, false; int(3, 15, 0, 4, 2)]), [5; int(1)]) <=lex + image(function([1, 0; int(3, 0)] --> [false, true, false, false, false; int(3, 15, 0, 4, 2)]), [5; int(1)]) .<= [false | l_1 : bool] diff --git a/tests/parse_print/autogen-bilals-fixed/f2f725a26126338e19e3f08ef990f1da/model.expected.json b/tests/parse_print/autogen-bilals-fixed/f2f725a26126338e19e3f08ef990f1da/model.expected.json index 98730901f6..6dfb2f2b9d 100644 --- a/tests/parse_print/autogen-bilals-fixed/f2f725a26126338e19e3f08ef990f1da/model.expected.json +++ b/tests/parse_print/autogen-bilals-fixed/f2f725a26126338e19e3f08ef990f1da/model.expected.json @@ -1738,7 +1738,7 @@ []}, 2]}}]}]]}, [{"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpFlatten": [null, @@ -1937,7 +1937,7 @@ []}, 16]}}]}]]}]}}]]}}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpFlatten": [null, @@ -2265,7 +2265,7 @@ []}, 2]}}]}]]}, [{"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": @@ -2440,7 +2440,7 @@ []}, 2]}}}]]}]}}]]}}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": @@ -2911,7 +2911,7 @@ {"Reference": [{"Name": "var6_PartitionAsSet_ExplicitVarSizeWithMarker_Marker"}, null]}]}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": diff --git a/tests/parse_print/autogen-bilals-fixed/f2f725a26126338e19e3f08ef990f1da/stdout.expected b/tests/parse_print/autogen-bilals-fixed/f2f725a26126338e19e3f08ef990f1da/stdout.expected index 653f345f0b..7c47b4270e 100644 --- a/tests/parse_print/autogen-bilals-fixed/f2f725a26126338e19e3f08ef990f1da/stdout.expected +++ b/tests/parse_print/autogen-bilals-fixed/f2f725a26126338e19e3f08ef990f1da/stdout.expected @@ -107,7 +107,7 @@ such that /\ (flatten(var4_PartitionAsSet_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMarker_Values_Function1DPartial_Flags [q8, .., ..]) - var4_PartitionAsSet_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMarker_Values_Function1DPartial_Flags [q10, q11, ..] - = 1 | q31 : int(1..2)]), 2 <= var6_PartitionAsSet_ExplicitVarSizeWithMarker_Marker -> - var6_PartitionAsSet_ExplicitVarSizeWithMarker_Values_Occurrence[1, ..] var6_PartitionAsSet_ExplicitVarSizeWithMarker_Marker -> var6_PartitionAsSet_ExplicitVarSizeWithMarker_Values_Occurrence[q22, 2] = false diff --git a/tests/parse_print/autogen-bilals-fixed/f3b4b055e266a994218c9c7c4772d7db/model.expected.json b/tests/parse_print/autogen-bilals-fixed/f3b4b055e266a994218c9c7c4772d7db/model.expected.json index f954afaaa1..a702c49ee3 100644 --- a/tests/parse_print/autogen-bilals-fixed/f3b4b055e266a994218c9c7c4772d7db/model.expected.json +++ b/tests/parse_print/autogen-bilals-fixed/f3b4b055e266a994218c9c7c4772d7db/model.expected.json @@ -109,7 +109,7 @@ {"ConstantInt": [{"TagInt": []}, 2]}}]}]]}, [{"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpFlatten": [null, @@ -282,7 +282,7 @@ []}, 7]}}]}]]}]}}]]}}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpFlatten": [null, @@ -611,7 +611,7 @@ [{"TagInt": []}, 2]}}]}]]}, [{"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": @@ -762,7 +762,7 @@ []}, 1]}}]}}]}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpFlatten": [null, diff --git a/tests/parse_print/autogen-bilals-fixed/f3b4b055e266a994218c9c7c4772d7db/stdout.expected b/tests/parse_print/autogen-bilals-fixed/f3b4b055e266a994218c9c7c4772d7db/stdout.expected index 9a7f6637e9..aa3cecaee7 100644 --- a/tests/parse_print/autogen-bilals-fixed/f3b4b055e266a994218c9c7c4772d7db/stdout.expected +++ b/tests/parse_print/autogen-bilals-fixed/f3b4b055e266a994218c9c7c4772d7db/stdout.expected @@ -7,8 +7,7 @@ find var1_ExplicitVarSizeWithFlags_Values_RelationAsSet_Explicit_1_RelationAsSet matrix indexed by [int(1..5), int(1..7), int(1), int(1..3)] of bool such that and([var1_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - flatten(var1_ExplicitVarSizeWithFlags_Values_RelationAsSet_Explicit_1_RelationAsSet_Explicit_1[q1, .., ..]) - - and([var1_ExplicitVarSizeWithFlags_Values_RelationAsSet_Explicit_1_RelationAsSet_Explicit_1[q5, q6, ..] var5_RelationAsSet_ExplicitVarSizeWithMarker_Marker -> @@ -61,7 +61,7 @@ such that var6_ExplicitVarSizeWithMarker_Values_PartitionAsSet_ExplicitVarSizeWithMarker_Marker[2] /\ flatten(var6_ExplicitVarSizeWithMarker_Values_PartitionAsSet_ExplicitVarSizeWithMarker_Values_Explicit[1, .., ..]) - var6_ExplicitVarSizeWithMarker_Marker -> var6_ExplicitVarSizeWithMarker_Values_PartitionAsSet_ExplicitVarSizeWithMarker_Marker[q8] = 0 @@ -75,7 +75,7 @@ such that and([q13 + 1 <= var6_ExplicitVarSizeWithMarker_Values_PartitionAsSet_ExplicitVarSizeWithMarker_Marker[q9] -> var6_ExplicitVarSizeWithMarker_Values_PartitionAsSet_ExplicitVarSizeWithMarker_Values_Explicit [q9, q13, ..] - var1_PartitionAsSet_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMarker_Values_Function1DPartial_Flags [q1, q2, ..] - = false, true > false], false diff --git a/tests/parse_print/autogen-bilals-fixed/f57b3d11bf42b1452c009a9c008864fd/model.expected.json b/tests/parse_print/autogen-bilals-fixed/f57b3d11bf42b1452c009a9c008864fd/model.expected.json index 1d258bdbb8..2e217e27b2 100644 --- a/tests/parse_print/autogen-bilals-fixed/f57b3d11bf42b1452c009a9c008864fd/model.expected.json +++ b/tests/parse_print/autogen-bilals-fixed/f57b3d11bf42b1452c009a9c008864fd/model.expected.json @@ -311,7 +311,7 @@ []}, 1]}}]]}}}}]}}]}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpFlatten": [null, diff --git a/tests/parse_print/autogen-bilals-fixed/f57b3d11bf42b1452c009a9c008864fd/stdout.expected b/tests/parse_print/autogen-bilals-fixed/f57b3d11bf42b1452c009a9c008864fd/stdout.expected index 5967080945..a12a3e34b3 100644 --- a/tests/parse_print/autogen-bilals-fixed/f57b3d11bf42b1452c009a9c008864fd/stdout.expected +++ b/tests/parse_print/autogen-bilals-fixed/f57b3d11bf42b1452c009a9c008864fd/stdout.expected @@ -28,7 +28,7 @@ such that /\ flatten(var2_PartitionAsSetR6_ExplicitVarSizeWithMarkerR5R6_Values_ExplicitVarSizeWithMarkerR6_Values_ExplicitVarSizeWithDummy [q4, .., ..]) - = 1 | q34 : int(1..4)]), and([q7 + 1 <= var2_1_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> - var2_1_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q7, ..] var2_1_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker -> @@ -100,14 +100,14 @@ such that and([var4_1_ExplicitWithFlags_Flags[q15] = 0 \/ var4_1_ExplicitWithFlags_Flags[q15] >= 0 | q15 : int(1..3)]), 3 = sum([var4_1_ExplicitWithFlags_Flags[q16] | q16 : int(1..3)]), and([var5_ExplicitWithFlagsR10_Flags[q18 + 1] > 0 -> - var5_ExplicitWithFlagsR10_Values_Function1DPartial_Flags[q18, ..] diff --git a/tests/parse_print/autogen-bilals-fixed/f6f3227d62d29091577943cbcc8b7b7f/model.expected.json b/tests/parse_print/autogen-bilals-fixed/f6f3227d62d29091577943cbcc8b7b7f/model.expected.json index 2e59f83190..84558de08c 100644 --- a/tests/parse_print/autogen-bilals-fixed/f6f3227d62d29091577943cbcc8b7b7f/model.expected.json +++ b/tests/parse_print/autogen-bilals-fixed/f6f3227d62d29091577943cbcc8b7b7f/model.expected.json @@ -94,7 +94,7 @@ {"Reference": [{"Name": "var1_ExplicitVarSizeWithMarker_Marker"}, null]}]}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": @@ -725,7 +725,7 @@ "var2_PartitionAsSet_ExplicitVarSizeWithMarker_Marker"}, null]}]}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpFlatten": [null, diff --git a/tests/parse_print/autogen-bilals-fixed/f6f3227d62d29091577943cbcc8b7b7f/stdout.expected b/tests/parse_print/autogen-bilals-fixed/f6f3227d62d29091577943cbcc8b7b7f/stdout.expected index 70e3e3eee5..9da2d2454d 100644 --- a/tests/parse_print/autogen-bilals-fixed/f6f3227d62d29091577943cbcc8b7b7f/stdout.expected +++ b/tests/parse_print/autogen-bilals-fixed/f6f3227d62d29091577943cbcc8b7b7f/stdout.expected @@ -8,7 +8,7 @@ find var2_PartitionAsSet_ExplicitVarSizeWithMarker_Values_Explicit_Occurrence: such that false, and([q1 + 1 <= var1_ExplicitVarSizeWithMarker_Marker -> - var1_ExplicitVarSizeWithMarker_Values_Function1D[q1, ..] var1_ExplicitVarSizeWithMarker_Marker -> @@ -41,7 +41,7 @@ such that | q17 : int(1..5)]), q7_ExplicitVarSizeWithMarker_Marker <= 5]), and([q10 + 1 <= var2_PartitionAsSet_ExplicitVarSizeWithMarker_Marker -> - flatten(var2_PartitionAsSet_ExplicitVarSizeWithMarker_Values_Explicit_Occurrence[q10, .., ..]) var2_PartitionAsSet_ExplicitVarSizeWithMarker_Marker -> diff --git a/tests/parse_print/autogen-bilals-fixed/f7faf3149f0cc222402ea4da0e2865f1/model.expected.json b/tests/parse_print/autogen-bilals-fixed/f7faf3149f0cc222402ea4da0e2865f1/model.expected.json index 37bef21343..e61019485e 100644 --- a/tests/parse_print/autogen-bilals-fixed/f7faf3149f0cc222402ea4da0e2865f1/model.expected.json +++ b/tests/parse_print/autogen-bilals-fixed/f7faf3149f0cc222402ea4da0e2865f1/model.expected.json @@ -2134,7 +2134,7 @@ []}, 2]}}]}]]}, [{"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpFlatten": [null, @@ -2336,7 +2336,7 @@ []}, 16]}}]}]]}]}}]]}}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpFlatten": [null, @@ -2671,7 +2671,7 @@ []}, 2]}}]}]]}, [{"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": @@ -2849,7 +2849,7 @@ []}, 1]}}}}]}]]}]}}]]}}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": diff --git a/tests/parse_print/autogen-bilals-fixed/f7faf3149f0cc222402ea4da0e2865f1/stdout.expected b/tests/parse_print/autogen-bilals-fixed/f7faf3149f0cc222402ea4da0e2865f1/stdout.expected index 7decabd21e..473e22141b 100644 --- a/tests/parse_print/autogen-bilals-fixed/f7faf3149f0cc222402ea4da0e2865f1/stdout.expected +++ b/tests/parse_print/autogen-bilals-fixed/f7faf3149f0cc222402ea4da0e2865f1/stdout.expected @@ -114,7 +114,7 @@ such that /\ (flatten(var3_PartitionAsSet_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMarker_Values_Function1DPartial_Flags [q1, .., ..]) - var3_PartitionAsSet_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMarker_Values_Function1DPartial_Flags [q1, q2, ..] - var2_PartitionAsSet_ExplicitVarSizeWithMarker_Marker -> var2_PartitionAsSet_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMarker_Marker[q1] = 0 /\ diff --git a/tests/parse_print/autogen-bilals-fixed/f8551d2ded7dfbb7f4fc2fefcfe32146/model.expected.json b/tests/parse_print/autogen-bilals-fixed/f8551d2ded7dfbb7f4fc2fefcfe32146/model.expected.json index fd704a86d6..04c37f41a0 100644 --- a/tests/parse_print/autogen-bilals-fixed/f8551d2ded7dfbb7f4fc2fefcfe32146/model.expected.json +++ b/tests/parse_print/autogen-bilals-fixed/f8551d2ded7dfbb7f4fc2fefcfe32146/model.expected.json @@ -18,7 +18,7 @@ [{"Constant": {"ConstantBool": false}}, {"Constant": {"ConstantBool": false}}, {"Constant": {"ConstantBool": false}}, {"Op": - {"MkOpLexLeq": + {"MkOpDotLeq": [{"Op": {"MkOpImage": [{"AbstractLiteral": diff --git a/tests/parse_print/autogen-bilals-fixed/f8551d2ded7dfbb7f4fc2fefcfe32146/stdout.expected b/tests/parse_print/autogen-bilals-fixed/f8551d2ded7dfbb7f4fc2fefcfe32146/stdout.expected index 94e07b851d..f32a68864a 100644 --- a/tests/parse_print/autogen-bilals-fixed/f8551d2ded7dfbb7f4fc2fefcfe32146/stdout.expected +++ b/tests/parse_print/autogen-bilals-fixed/f8551d2ded7dfbb7f4fc2fefcfe32146/stdout.expected @@ -8,6 +8,6 @@ such that image(function((false, 1) --> [2, 0, 2, 4, 3; int(13..14, 12, 1, 9)], (true, 4) --> [0, 2, 4, 3; int(11, 6, 8, 2)], (true, 5) --> ([] : `matrix indexed by [int] of int`)), (false <-> false, factorial(1))) - <=lex [4, 0, 4, 4; int(7, 2..3, 8)], + .<= [4, 0, 4, 4; int(7, 2..3, 8)], false maximising var1 diff --git a/tests/parse_print/autogen-bilals-fixed/fbfe220f5450d8f205a3e3e9ec02f054/model.expected.json b/tests/parse_print/autogen-bilals-fixed/fbfe220f5450d8f205a3e3e9ec02f054/model.expected.json index 1883d4bd97..fd16e522a1 100644 --- a/tests/parse_print/autogen-bilals-fixed/fbfe220f5450d8f205a3e3e9ec02f054/model.expected.json +++ b/tests/parse_print/autogen-bilals-fixed/fbfe220f5450d8f205a3e3e9ec02f054/model.expected.json @@ -8,7 +8,7 @@ [{"Declaration": {"FindOrGiven": ["Find", {"Name": "unused"}, {"DomainBool": []}]}}, {"SuchThat": [{"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": diff --git a/tests/parse_print/autogen-bilals-fixed/fbfe220f5450d8f205a3e3e9ec02f054/stdout.expected b/tests/parse_print/autogen-bilals-fixed/fbfe220f5450d8f205a3e3e9ec02f054/stdout.expected index 0ddb296e3c..005570405e 100644 --- a/tests/parse_print/autogen-bilals-fixed/fbfe220f5450d8f205a3e3e9ec02f054/stdout.expected +++ b/tests/parse_print/autogen-bilals-fixed/fbfe220f5450d8f205a3e3e9ec02f054/stdout.expected @@ -1,4 +1,4 @@ language ESSENCE' 1.0 find unused: bool -such that [[true; int(1)]; int(1)][2, ..] - q_4_ExplicitVarSizeWithFlags_Values_Function1DPartial_Flags[q1, ..] @@ -55,7 +55,7 @@ such that var1_PartitionAsSet_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMarker_Marker[q3] = var1_PartitionAsSet_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMarker_Marker[q3 + 1] /\ - var1_PartitionAsSet_ExplicitVarSizeWithMarker_Values_ExplicitVarSizeWithMarker_Values[q3, ..] var1_PartitionAsSet_ExplicitVarSizeWithMarker_Marker -> @@ -75,14 +75,14 @@ such that | q4 : int(1..3)]) | q3 : int(1..8)]), and([var2_ExplicitVarSizeWithFlags_Flags[q5 + 1] -> - var2_ExplicitVarSizeWithFlags_Values_Function1DPartial_Flags[q5, ..] diff --git a/tests/parse_print/autogen-bilals-fixed/ff226931c79ca27e68e71f211b4aa84e/model.expected.json b/tests/parse_print/autogen-bilals-fixed/ff226931c79ca27e68e71f211b4aa84e/model.expected.json index e275addb05..0d80fdf899 100644 --- a/tests/parse_print/autogen-bilals-fixed/ff226931c79ca27e68e71f211b4aa84e/model.expected.json +++ b/tests/parse_print/autogen-bilals-fixed/ff226931c79ca27e68e71f211b4aa84e/model.expected.json @@ -109,7 +109,7 @@ {"ConstantInt": [{"TagInt": []}, 2]}}]}]]}, [{"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpFlatten": [null, @@ -282,7 +282,7 @@ []}, 4]}}]}]]}]}}]]}}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpFlatten": [null, @@ -611,7 +611,7 @@ [{"TagInt": []}, 2]}}]}]]}, [{"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpSlicing": [{"Op": @@ -762,7 +762,7 @@ []}, 1]}}]}}]}}, {"Op": - {"MkOpLexLt": + {"MkOpDotLt": [{"Op": {"MkOpFlatten": [null, diff --git a/tests/parse_print/autogen-bilals-fixed/ff226931c79ca27e68e71f211b4aa84e/stdout.expected b/tests/parse_print/autogen-bilals-fixed/ff226931c79ca27e68e71f211b4aa84e/stdout.expected index 838842c34b..9bef4d149d 100644 --- a/tests/parse_print/autogen-bilals-fixed/ff226931c79ca27e68e71f211b4aa84e/stdout.expected +++ b/tests/parse_print/autogen-bilals-fixed/ff226931c79ca27e68e71f211b4aa84e/stdout.expected @@ -7,8 +7,7 @@ find var1_ExplicitVarSizeWithFlags_Values_RelationAsSet_Explicit_1_RelationAsSet matrix indexed by [int(1..5), int(1..4), int(1), int(1..3)] of bool such that and([var1_ExplicitVarSizeWithFlags_Flags[q1 + 1] -> - flatten(var1_ExplicitVarSizeWithFlags_Values_RelationAsSet_Explicit_1_RelationAsSet_Explicit_1[q1, .., ..]) - - and([var1_ExplicitVarSizeWithFlags_Values_RelationAsSet_Explicit_1_RelationAsSet_Explicit_1[q5, q6, ..] = var1, true, From 8c49cf8211d0de77f99282af4daa1ecdbf16feba Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?=C3=96zg=C3=BCr=20Akg=C3=BCn?= Date: Mon, 26 Feb 2024 14:08:44 +0000 Subject: [PATCH 125/229] always update stack.yaml --- Makefile | 1 + 1 file changed, 1 insertion(+) diff --git a/Makefile b/Makefile index c525a22eca..c5ad1c17ca 100644 --- a/Makefile +++ b/Makefile @@ -63,6 +63,7 @@ test: stack test --test-arguments '--hide-successes --limit-time ${LIMIT_TIME}';\ fi +.PHONY: stack.yaml stack.yaml: etc/hs-deps/stack-${GHC_VERSION}.yaml @cp etc/hs-deps/stack-${GHC_VERSION}.yaml stack.yaml From a2d23c5fd6032a93c5f2285b5874dc4140d1486a Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?=C3=96zg=C3=BCr=20Akg=C3=BCn?= Date: Tue, 27 Feb 2024 14:34:54 +0000 Subject: [PATCH 126/229] remove fastbuild.sh --- fastbuild.sh | 1 - 1 file changed, 1 deletion(-) delete mode 100644 fastbuild.sh diff --git a/fastbuild.sh b/fastbuild.sh deleted file mode 100644 index 4feed6a0e0..0000000000 --- a/fastbuild.sh +++ /dev/null @@ -1 +0,0 @@ -stack install --fast From d5fd545b9a677ab72e30bb067673bb3370d2fe33 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?=C3=96zg=C3=BCr=20Akg=C3=BCn?= Date: Tue, 27 Feb 2024 14:37:20 +0000 Subject: [PATCH 127/229] remove redundant files --- src/Conjure/Language/Constant_BACKUP_23009.hs | 535 -------- src/Conjure/Language/Constant_BASE_23009.hs | 518 -------- src/Conjure/Language/Constant_LOCAL_23009.hs | 534 -------- src/Conjure/Language/Constant_REMOTE_23009.hs | 337 ----- src/Conjure/Language/Domain_BACKUP_22702.hs | 1079 ----------------- src/Conjure/Language/Domain_BASE_22702.hs | 1013 ---------------- src/Conjure/Language/Domain_LOCAL_22702.hs | 1044 ---------------- src/Conjure/Language/Domain_REMOTE_22702.hs | 1029 ---------------- 8 files changed, 6089 deletions(-) delete mode 100644 src/Conjure/Language/Constant_BACKUP_23009.hs delete mode 100644 src/Conjure/Language/Constant_BASE_23009.hs delete mode 100644 src/Conjure/Language/Constant_LOCAL_23009.hs delete mode 100644 src/Conjure/Language/Constant_REMOTE_23009.hs delete mode 100644 src/Conjure/Language/Domain_BACKUP_22702.hs delete mode 100644 src/Conjure/Language/Domain_BASE_22702.hs delete mode 100644 src/Conjure/Language/Domain_LOCAL_22702.hs delete mode 100644 src/Conjure/Language/Domain_REMOTE_22702.hs diff --git a/src/Conjure/Language/Constant_BACKUP_23009.hs b/src/Conjure/Language/Constant_BACKUP_23009.hs deleted file mode 100644 index fcd2b6c26d..0000000000 --- a/src/Conjure/Language/Constant_BACKUP_23009.hs +++ /dev/null @@ -1,535 +0,0 @@ -{-# LANGUAGE DeriveGeneric, DeriveDataTypeable #-} - -module Conjure.Language.Constant - ( Constant(..) - , valuesInIntDomain - , normaliseConstant - , mkUndef, isUndef - , emptyCollection - , viewConstantBool - , viewConstantInt - , viewConstantTuple - , viewConstantRecord - , viewConstantVariant - , viewConstantMatrix - , viewConstantSet - , viewConstantMSet - , viewConstantFunction - , viewConstantSequence - , viewConstantRelation - , viewConstantPartition - , viewConstantPermutation - , reDomConst - ) where - --- conjure -import Conjure.Prelude -import Conjure.Bug -import Conjure.Language.Name -import Conjure.Language.Domain -import Conjure.Language.Type -import Conjure.Language.AbstractLiteral - -import Conjure.Language.DomainSizeOf -import Conjure.Language.TypeOf -import Conjure.Language.AdHoc -import Conjure.Language.Pretty - --- base -import Data.Data ( toConstr, constrIndex ) - --- QuickCheck -import Test.QuickCheck ( Arbitrary(..), oneof ) - - -data Constant - = ConstantBool Bool - | ConstantInt IntTag Integer - | ConstantEnum Name {- name for the enum domain -} - [Name] {- values in the enum domain -} - Name {- the literal -} - | ConstantField Name Type -- the name of a field of Record or Variant and its type - | ConstantAbstract (AbstractLiteral Constant) - | DomainInConstant (Domain () Constant) - | TypedConstant Constant Type - | ConstantUndefined Text Type -- never use this for a bool - -- use false instead for them - deriving (Show, Data, Typeable, Generic) - -instance Eq Constant where - a == b = compare a b == EQ - --- implementing the Eq&Ord instances by hand, because we want to special case the TypedConstant constructor -instance Ord Constant where - - -- do not use type info when comparing - compare (TypedConstant a _) (TypedConstant b _) = compare a b - compare (TypedConstant a _) b = compare a b - compare a (TypedConstant b _) = compare a b - - -- the "usual" comparisons - compare (ConstantBool a) (ConstantBool b) = compare a b - compare (ConstantInt _ a) (ConstantInt _ b) = compare a b - compare (ConstantEnum _ aVals aVal) (ConstantEnum _ bVals bVal) = - compare (elemIndex aVal aVals, aVal) (elemIndex bVal bVals, bVal) - compare (ConstantField a1 a2) (ConstantField b1 b2) = compare (a1,a2) (b1,b2) - compare (ConstantAbstract a) (ConstantAbstract b) = compare a b - compare (DomainInConstant a) (DomainInConstant b) = compare a b - compare (ConstantUndefined a1 a2) (ConstantUndefined b1 b2) = compare (a1,a2) (b1,b2) - - -- if the constructors do not match - compare a b = compare (constrIndex (toConstr a)) (constrIndex (toConstr b)) - -instance Serialize Constant -instance Hashable Constant -instance ToJSON Constant where toJSON = genericToJSON jsonOptions -instance FromJSON Constant where parseJSON = genericParseJSON jsonOptions - -instance Arbitrary Constant where - arbitrary = oneof - [ ConstantBool <$> arbitrary - , ConstantInt TagInt <$> arbitrary - ] - -instance TypeOf Constant where - typeOf ConstantBool{} = return TypeBool - typeOf (ConstantInt t _) = return (TypeInt t) - typeOf (ConstantEnum defn _ _ ) = return (TypeEnum defn) - typeOf (ConstantField _ ty) = return ty - typeOf (ConstantAbstract x ) = typeOf x - typeOf (DomainInConstant dom) = typeOfDomain dom - typeOf (TypedConstant _ ty) = return ty - typeOf (ConstantUndefined _ ty) = return ty - -instance DomainSizeOf Constant Integer where - domainSizeOf DomainBool{} = return 2 - domainSizeOf (DomainIntE x) = bug ("not implemented, domainSizeOf DomainIntE" <+> pretty (show x)) - domainSizeOf (DomainInt _ rs) = domainSizeOfRanges rs - domainSizeOf DomainEnum{} = fail "domainSizeOf: Unknown for given enum." - domainSizeOf (DomainTuple ds) = product <$> mapM domainSizeOf ds - domainSizeOf (DomainMatrix index inner) = intPow <$> domainSizeOf inner <*> domainSizeOf index - domainSizeOf d@(DomainSet _ (SetAttr attrs) inner) = - case attrs of - SizeAttr_None -> do - innerSize <- domainSizeOf inner - return (2 `intPow` innerSize) - SizeAttr_Size (ConstantInt _ size) -> do - innerSize <- domainSizeOf inner - return (nchoosek (product . enumFromTo 1) innerSize size) - SizeAttr_MinSize{} -> do - -- TODO: we can do better here - innerSize <- domainSizeOf inner - return (2 `intPow` innerSize) - SizeAttr_MaxSize (ConstantInt _ maxSize) -> do - innerSize <- domainSizeOf inner - return $ sum [ nchoosek (product . enumFromTo 1) innerSize k | k <- [0 .. maxSize] ] - SizeAttr_MinMaxSize (ConstantInt _ minSize) (ConstantInt _ maxSize) -> do - innerSize <- domainSizeOf inner - return $ sum [ nchoosek (product . enumFromTo 1) innerSize k | k <- [minSize .. maxSize] ] - _ -> fail ("domainSizeOf{Constant}" <+> pretty d) - domainSizeOf DomainMSet {} = bug "not implemented: domainSizeOf DomainMSet" - domainSizeOf DomainFunction {} = bug "not implemented: domainSizeOf DomainFunction" - domainSizeOf DomainRelation {} = bug "not implemented: domainSizeOf DomainRelation" - domainSizeOf DomainPartition {} = bug "not implemented: domainSizeOf DomainPartition" - domainSizeOf _ = bug "not implemented: domainSizeOf" - -emptyCollection :: Constant -> Bool -emptyCollection ConstantBool{} = False -emptyCollection ConstantInt{} = False -emptyCollection ConstantEnum{} = False -emptyCollection ConstantField{} = False -emptyCollection (ConstantAbstract x) = emptyCollectionAbsLit x -emptyCollection DomainInConstant{} = False -emptyCollection (TypedConstant x _) = emptyCollection x -emptyCollection ConstantUndefined{} = False - -intPow :: Integer -> Integer -> Integer -intPow = (^) - -domainSizeOfRanges :: MonadFail m => [Range Constant] -> m Integer -domainSizeOfRanges = fmap genericLength . valuesInIntDomain - -instance DomainSizeOf Constant Constant where - domainSizeOf = fmap (ConstantInt TagInt) . domainSizeOf - -instance Pretty Constant where - - -- hack, oh sweet hack! - -- print a domain instead of a type when printing an empty matrix literal. - -- this means we print "int()" instead of "int" inside the index of a matrix type - -- SR expects it this way... - pretty (TypedConstant (ConstantAbstract (AbsLitMatrix _ [])) ty) = - let - pretty' (TypeMatrix index innerNested) - = "matrix indexed by" <+> prettyList prBrackets "," (map pretty' indices) - <+> "of" <+> pretty inner - where - (indices,inner) = first (index:) $ collect innerNested - collect (TypeMatrix i j) = first (i:) $ collect j - collect x = ([],x) - pretty' TypeInt{} = "int()" - pretty' t = pretty t - in - prParens $ "[] : `" <> pretty' ty <> "`" - - pretty (ConstantBool False) = "false" - pretty (ConstantBool True ) = "true" - pretty (ConstantInt _ x ) = pretty x - pretty (ConstantEnum _ _ x) = pretty x - pretty (ConstantField n _) = pretty n - pretty (ConstantAbstract x) = pretty x - pretty (DomainInConstant d) = "`" <> pretty d <> "`" - pretty (TypedConstant x ty) = prParens $ pretty x <+> ":" <+> "`" <> pretty ty <> "`" - pretty (ConstantUndefined reason ty) = "undefined" <> prParens (pretty reason <+> ":" <+> "`" <> pretty ty <> "`") - -instance ExpressionLike Constant where - fromInt = ConstantInt TagInt - fromIntWithTag i t = ConstantInt t i - intOut _ (ConstantInt _ x) = return x - intOut doc c = fail $ vcat [ "Expecting an integer, but found:" <+> pretty c - , "Called from:" <+> doc - ] - - fromBool = ConstantBool - boolOut (ConstantBool x) = return x - boolOut ConstantUndefined{} = return False - boolOut c = fail ("Expecting a boolean, but found:" <+> pretty c) - - fromList xs = ConstantAbstract $ AbsLitMatrix (mkDomainIntB 1 (fromInt $ genericLength xs)) xs - listOut (ConstantAbstract (AbsLitMatrix _ xs)) = return xs - listOut c = fail ("Expecting a matrix literal, but found:" <+> pretty c) - -instance ReferenceContainer Constant where - fromName name = bug ("ReferenceContainer{Constant} fromName --" <+> pretty name) - nameOut (ConstantField nm _) = return nm - nameOut p = bug ("ReferenceContainer{Constant} nameOut --" <+> pretty p) - -instance DomainContainer Constant (Domain ()) where - fromDomain = DomainInConstant - domainOut (DomainInConstant dom) = return dom - domainOut _ = fail "domainOut{Constant}" - -mkUndef :: Type -> Doc -> Constant -mkUndef TypeBool _ = ConstantBool False -mkUndef ty reason = ConstantUndefined (stringToText $ show reason) ty - -isUndef :: Constant -> Bool -isUndef ConstantUndefined{} = True -isUndef _ = False - -normaliseConstant :: Constant -> Constant -normaliseConstant x@ConstantBool{} = x -normaliseConstant x@ConstantInt{} = x -normaliseConstant x@ConstantEnum{} = x -normaliseConstant x@ConstantField{} = x -normaliseConstant (ConstantAbstract x) = ConstantAbstract (normaliseAbsLit normaliseConstant x) -normaliseConstant (DomainInConstant d) = DomainInConstant (normaliseDomain normaliseConstant d) -normaliseConstant (TypedConstant c ty) = TypedConstant (normaliseConstant c) ty -normaliseConstant x@ConstantUndefined{} = x - -instance Num Constant where - ConstantInt _ x + ConstantInt _ y = ConstantInt TagInt (x+y) - x + y = bug $ vcat [ "Num Constant (+)", "x:" <+> pretty x, "y:" <+> pretty y ] - ConstantInt _ x - ConstantInt _ y = ConstantInt TagInt (x-y) - x - y = bug $ vcat [ "Num Constant (-)", "x:" <+> pretty x, "y:" <+> pretty y ] - ConstantInt _ x * ConstantInt _ y = ConstantInt TagInt (x*y) - x * y = bug $ vcat [ "Num Constant (*)", "x:" <+> pretty x, "y:" <+> pretty y ] - abs (ConstantInt t x) = ConstantInt t (abs x) - abs x = bug $ vcat [ "Num Constant abs", "x:" <+> pretty x ] - signum (ConstantInt t x) = ConstantInt t (signum x) - signum x = bug $ vcat [ "Num Constant signum", "x:" <+> pretty x ] - fromInteger = ConstantInt TagInt . fromInteger - - -valuesInIntDomain :: MonadFail m => [Range Constant] -> m [Integer] -valuesInIntDomain ranges = - if isFinite - then return allValues - else fail $ "Expected finite integer ranges, but got:" <++> prettyList id "," ranges - - where - - allRanges :: [Maybe [Integer]] - allRanges = - [ vals - | r <- ranges - , let vals = case r of - RangeSingle (ConstantInt _ x) -> return [x] - RangeBounded (ConstantInt _ l) (ConstantInt _ u) -> return [l..u] - _ -> Nothing - ] - - isFinite :: Bool - isFinite = Nothing `notElem` allRanges - - allValues :: [Integer] - allValues = sortNub $ concat $ catMaybes allRanges - - -<<<<<<< HEAD --- | Assuming both the value and the domain are normalised --- TODO: make this stricter, but write failing test cases first! -validateConstantForDomain :: forall m r . (MonadFail m, Pretty r) => Name -> Constant -> Domain r Constant -> m () - -validateConstantForDomain _ ConstantBool{} DomainBool{} = return () - -validateConstantForDomain _ _ (DomainInt _ []) = return () -- no restrictions - -validateConstantForDomain name c@(ConstantInt cTag i) d@(DomainInt dTag rs) | cTag == dTag = - let - intInRange RangeOpen = True - intInRange (RangeSingle (ConstantInt _ a)) = i == a - intInRange (RangeLowerBounded (ConstantInt _ a)) = i >= a - intInRange (RangeUpperBounded (ConstantInt _ a)) = i <= a - intInRange (RangeBounded (ConstantInt _ a) (ConstantInt _ b)) = i >= a && i <= b - intInRange _ = False - in unless (any intInRange rs) (constantNotInDomain name c d) - -validateConstantForDomain _ (ConstantInt _ i) (DomainUnnamed _ (ConstantInt _ a)) | i >= 1 && i <= a = return () - -validateConstantForDomain _ _ (DomainEnum _ Nothing _) = return () -- no restrictions -validateConstantForDomain name c d@(DomainEnum _ _ Nothing) = - fail $ vcat [ "validateConstantForDomain: enum not handled" - , pretty name - , pretty c - , pretty d - ] -validateConstantForDomain name - c@(ConstantInt cTag _) - d@(DomainEnum _ (Just ranges) (Just mp)) = nested c d $ do - let - -- lu :: MonadFail m => Name -> m Constant - lu (ConstantEnum _ _ nm) = - case lookup nm mp of - Nothing -> fail $ "No value for:" <+> pretty nm - Just v -> return (ConstantInt cTag v) - lu (ConstantInt t v) = return (ConstantInt t v) - lu x = fail $ "validateConstantForDomain.lu" <+> pretty x - - -- lu2 :: MonadFail m => Range Name -> m (Range Constant) - lu2 = mapM lu - - rs <- mapM lu2 ranges - validateConstantForDomain name c (DomainInt cTag rs :: Domain r Constant) - -validateConstantForDomain name - c@(ConstantAbstract (AbsLitTuple cs)) - d@(DomainTuple ds) = nested c d $ zipWithM_ (validateConstantForDomain name) cs ds - -validateConstantForDomain name - c@(ConstantAbstract (AbsLitRecord (sortOn fst -> cs))) - d@(DomainRecord (sortOn fst -> ds)) - | map fst cs == map fst ds - = nested c d $ zipWithM_ (validateConstantForDomain name) (map snd cs) (map snd ds) - | otherwise - = constantNotInDomain name c d - -validateConstantForDomain name - c@(ConstantAbstract (AbsLitVariant _ n c')) - d@(DomainVariant ds) - | Just d' <- lookup n ds - = nested c d $ validateConstantForDomain name c' d' - | otherwise - = constantNotInDomain name c d - -validateConstantForDomain name - c@(ConstantAbstract (AbsLitMatrix cIndex vals)) - d@(DomainMatrix dIndex dInner) = do - nested c d $ - mapM_ (\ val -> validateConstantForDomain name val dInner ) vals - let - isEmptyIntDomain (DomainInt _ []) = True - isEmptyIntDomain _ = False - unless (cIndex == dIndex || isEmptyIntDomain cIndex) $ fail $ vcat - [ "The indices do not match between the value and the domain." - , "Value :" <+> pretty c - , "Domain:" <+> pretty d - ] - -validateConstantForDomain name - c@(ConstantAbstract (AbsLitSet vals)) - d@(DomainSet _ (SetAttr sizeAttr) dInner) = do - let cardinalityOK = case sizeAttr of - SizeAttr_None -> True - SizeAttr_Size (ConstantInt _ s) -> s == genericLength vals - SizeAttr_MinSize (ConstantInt _ s) -> s <= genericLength vals - SizeAttr_MaxSize (ConstantInt _ s) -> genericLength vals <= s - SizeAttr_MinMaxSize (ConstantInt _ smin) (ConstantInt _ smax) -> - smin <= genericLength vals && genericLength vals <= smax - _ -> False - unless cardinalityOK $ fail $ vcat - [ "The value is not a member of the domain." - , "Value :" <+> pretty c - , "Domain:" <+> pretty d - , "Reason: Domain attributes are not satisfied." - , "Specifically:" <+> pretty sizeAttr - ] - nested c d $ mapM_ (\ val -> validateConstantForDomain name val dInner ) vals - -validateConstantForDomain name - c@(ConstantAbstract (AbsLitMSet vals)) - d@(DomainMSet _ (MSetAttr sizeAttr occurAttr) dInner) = do - let cardinalityOK = case sizeAttr of - SizeAttr_None -> True - SizeAttr_Size (ConstantInt _ s) -> s == genericLength vals - SizeAttr_MinSize (ConstantInt _ s) -> s <= genericLength vals - SizeAttr_MaxSize (ConstantInt _ s) -> genericLength vals <= s - SizeAttr_MinMaxSize (ConstantInt _ smin) (ConstantInt _ smax) -> - smin <= genericLength vals && genericLength vals <= smax - _ -> False - unless cardinalityOK $ fail $ vcat - [ "The value is not a member of the domain." - , "Value :" <+> pretty c - , "Domain:" <+> pretty d - , "Reason: Domain attributes are not satisfied." - , "Specifically:" <+> pretty sizeAttr - ] - let occurOK = case occurAttr of - OccurAttr_None -> True - OccurAttr_MinOccur (ConstantInt _ s) -> and [ s <= occ | (_, occ) <- histogram vals ] - OccurAttr_MaxOccur (ConstantInt _ s) -> and [ occ <= s | (_, occ) <- histogram vals ] - OccurAttr_MinMaxOccur (ConstantInt _ smin) (ConstantInt _ smax) -> - and [ smin <= occ && occ <= smax | (_, occ) <- histogram vals ] - _ -> False - unless occurOK $ fail $ vcat - [ "The value is not a member of the domain." - , "Value :" <+> pretty c - , "Domain:" <+> pretty d - , "Reason: Domain attributes are not satisfied." - , "Specifically:" <+> pretty occurAttr - ] - nested c d $ mapM_ (\ val -> validateConstantForDomain name val dInner ) vals - -validateConstantForDomain name - c@(ConstantAbstract (AbsLitFunction vals)) - d@(DomainFunction _ _ dFrom dTo) = nested c d $ do - mapM_ (\ val -> validateConstantForDomain name (fst val) dFrom) vals - mapM_ (\ val -> validateConstantForDomain name (snd val) dTo ) vals - -validateConstantForDomain name - c@(ConstantAbstract (AbsLitSequence vals)) - d@(DomainSequence _ _ dInner) = nested c d $ - mapM_ (\ val -> validateConstantForDomain name val dInner ) vals - -validateConstantForDomain name - c@(ConstantAbstract (AbsLitRelation valss)) - d@(DomainRelation _ _ dInners) = nested c d $ - forM_ valss $ \ vals -> - zipWithM_ (validateConstantForDomain name) vals dInners - -validateConstantForDomain name - c@(ConstantAbstract (AbsLitPartition valss)) - d@(DomainPartition _ _ dInner) = nested c d $ - mapM_ (\ val -> validateConstantForDomain name val dInner ) (concat valss) -validateConstantForDomain name - c@(ConstantAbstract (AbsLitPermutation valss)) - d@(DomainPermutation _ _ dInner) = nested c d $ - mapM_ (\ val -> validateConstantForDomain name val dInner ) (concat valss) -validateConstantForDomain name c@(TypedConstant c' _) d = nested c d $ validateConstantForDomain name c' d - -validateConstantForDomain name c d = constantNotInDomain name c d - - -nested :: (MonadFail m, Pretty r) => Constant -> Domain r Constant -> Either Doc () -> m () -nested _ _ Right{} = return () -nested c d (Left err) = fail $ vcat - [ "The value is not a member of the domain." - , "Value :" <+> pretty c - , "Domain:" <+> pretty d - , "Reason:" - , nest 4 err - ] - -constantNotInDomain :: (MonadFail m, Pretty r) => Name -> Constant -> Domain r Constant -> m () -constantNotInDomain n c d = fail $ vcat - [ "The value is not a member of the domain." - , "Name :" <+> pretty n - , "Value :" <+> pretty c - , "Domain:" <+> pretty d - ] - - -======= ->>>>>>> master -viewConstantBool :: MonadFail m => Constant -> m Bool -viewConstantBool (ConstantBool i) = return i -viewConstantBool (ConstantInt _ 0) = return False -viewConstantBool (ConstantInt _ 1) = return True -viewConstantBool constant = fail ("Expecting a boolean, but got:" <++> pretty constant) - -viewConstantInt :: MonadFail m => Constant -> m Integer -viewConstantInt (ConstantInt _ i) = return i -viewConstantInt constant = fail ("Expecting an integer, but got:" <++> pretty constant) - -viewConstantTuple :: MonadFail m => Constant -> m [Constant] -viewConstantTuple (ConstantAbstract (AbsLitTuple xs)) = return xs -viewConstantTuple (TypedConstant c _) = viewConstantTuple c -viewConstantTuple constant = fail ("Expecting a tuple, but got:" <++> pretty constant) - -viewConstantRecord :: MonadFail m => Constant -> m [(Name, Constant)] -viewConstantRecord (ConstantAbstract (AbsLitRecord xs)) = return xs -viewConstantRecord (TypedConstant c _) = viewConstantRecord c -viewConstantRecord constant = fail ("Expecting a record, but got:" <++> pretty constant) - -viewConstantVariant :: MonadFail m => Constant -> m (Maybe [(Name, Domain () Constant)], Name, Constant) -viewConstantVariant (ConstantAbstract (AbsLitVariant lu nm x)) = return (lu, nm, x) -viewConstantVariant (TypedConstant c _) = viewConstantVariant c -viewConstantVariant constant = fail ("Expecting a variant, but got:" <++> pretty constant) - -viewConstantMatrix :: MonadFail m => Constant -> m (Domain () Constant, [Constant]) -viewConstantMatrix (ConstantAbstract (AbsLitMatrix ind xs)) = return (ind, xs) -viewConstantMatrix (TypedConstant c _) = viewConstantMatrix c -viewConstantMatrix constant = fail ("Expecting a matrix, but got:" <++> pretty constant) - -viewConstantSet :: MonadFail m => Constant -> m [Constant] -viewConstantSet (ConstantAbstract (AbsLitSet xs)) = return xs -viewConstantSet (TypedConstant c _) = viewConstantSet c -viewConstantSet constant = fail ("Expecting a set, but got:" <++> pretty constant) - -viewConstantMSet :: MonadFail m => Constant -> m [Constant] -viewConstantMSet (ConstantAbstract (AbsLitMSet xs)) = return xs -viewConstantMSet (TypedConstant c _) = viewConstantMSet c -viewConstantMSet constant = fail ("Expecting an mset, but got:" <++> pretty constant) - -viewConstantFunction :: MonadFail m => Constant -> m [(Constant, Constant)] -viewConstantFunction (ConstantAbstract (AbsLitFunction xs)) = return xs -viewConstantFunction (TypedConstant c _) = viewConstantFunction c -viewConstantFunction constant = do - let - suggestion = case constant of - ConstantAbstract (AbsLitMatrix (DomainInt _ rs) vals) -> do - froms <- valuesInIntDomain rs - return $ Just $ pretty $ AbsLitFunction (zip (map (ConstantInt TagInt) froms) vals) - _ -> return Nothing - suggestion >>= \case - Nothing -> fail ("Expecting a function, but got:" <++> pretty constant) - Just sug -> fail (vcat [ "Expecting a function, but got:" <++> pretty constant - , "Maybe you meant:" <++> sug - ]) - -viewConstantSequence :: MonadFail m => Constant -> m [Constant] -viewConstantSequence (ConstantAbstract (AbsLitSequence xs)) = return xs -viewConstantSequence (TypedConstant c _) = viewConstantSequence c -viewConstantSequence constant = fail ("Expecting a sequence, but got:" <++> pretty constant) - -viewConstantRelation :: MonadFail m => Constant -> m [[Constant]] -viewConstantRelation (ConstantAbstract (AbsLitRelation xs)) = return xs -viewConstantRelation (TypedConstant c _) = viewConstantRelation c -viewConstantRelation constant = fail ("Expecting a relation, but got:" <++> pretty constant) - -viewConstantPartition :: MonadFail m => Constant -> m [[Constant]] -viewConstantPartition (ConstantAbstract (AbsLitPartition xs)) = return xs -viewConstantPartition (TypedConstant c _) = viewConstantPartition c -viewConstantPartition constant = fail ("Expecting a partition, but got:" <++> pretty constant) - -viewConstantPermutation :: MonadFail m => Constant -> m [[Constant]] -viewConstantPermutation (ConstantAbstract (AbsLitPermutation xs)) = return xs -viewConstantPermutation (TypedConstant c _) = viewConstantPermutation c -viewConstantPermutation constant = fail ("Expecting a permutation, but got:" <++> pretty constant) - - -reDomConst :: Domain () Constant -> Domain () Constant -reDomConst cns = case cns of - DomainInt t _ -> reTag t cns - _ -> cns - diff --git a/src/Conjure/Language/Constant_BASE_23009.hs b/src/Conjure/Language/Constant_BASE_23009.hs deleted file mode 100644 index fdeaaccadd..0000000000 --- a/src/Conjure/Language/Constant_BASE_23009.hs +++ /dev/null @@ -1,518 +0,0 @@ -{-# LANGUAGE DeriveGeneric, DeriveDataTypeable #-} -{-# LANGUAGE ViewPatterns #-} - -module Conjure.Language.Constant - ( Constant(..) - , valuesInIntDomain - , normaliseConstant - , validateConstantForDomain - , mkUndef, isUndef - , emptyCollection - , viewConstantBool - , viewConstantInt - , viewConstantTuple - , viewConstantRecord - , viewConstantVariant - , viewConstantMatrix - , viewConstantSet - , viewConstantMSet - , viewConstantFunction - , viewConstantSequence - , viewConstantRelation - , viewConstantPartition - ) where - --- conjure -import Conjure.Prelude -import Conjure.Bug -import Conjure.Language.Name -import Conjure.Language.Domain -import Conjure.Language.Type -import Conjure.Language.AbstractLiteral - -import Conjure.Language.DomainSizeOf -import Conjure.Language.TypeOf -import Conjure.Language.AdHoc -import Conjure.Language.Pretty - --- base -import Data.Data ( toConstr, constrIndex ) - --- QuickCheck -import Test.QuickCheck ( Arbitrary(..), oneof ) - - -data Constant - = ConstantBool Bool - | ConstantInt IntTag Integer - | ConstantEnum Name {- name for the enum domain -} - [Name] {- values in the enum domain -} - Name {- the literal -} - | ConstantField Name Type -- the name of a field of Record or Variant and its type - | ConstantAbstract (AbstractLiteral Constant) - | DomainInConstant (Domain () Constant) - | TypedConstant Constant Type - | ConstantUndefined Text Type -- never use this for a bool - -- use false instead for them - deriving (Show, Data, Typeable, Generic) - -instance Eq Constant where - a == b = compare a b == EQ - --- implementing the Eq&Ord instances by hand, because we want to special case the TypedConstant constructor -instance Ord Constant where - - -- do not use type info when comparing - compare (TypedConstant a _) (TypedConstant b _) = compare a b - compare (TypedConstant a _) b = compare a b - compare a (TypedConstant b _) = compare a b - - -- the "usual" comparisons - compare (ConstantBool a) (ConstantBool b) = compare a b - compare (ConstantInt _ a) (ConstantInt _ b) = compare a b - compare (ConstantEnum _ aVals aVal) (ConstantEnum _ bVals bVal) = - compare (elemIndex aVal aVals, aVal) (elemIndex bVal bVals, bVal) - compare (ConstantField a1 a2) (ConstantField b1 b2) = compare (a1,a2) (b1,b2) - compare (ConstantAbstract a) (ConstantAbstract b) = compare a b - compare (DomainInConstant a) (DomainInConstant b) = compare a b - compare (ConstantUndefined a1 a2) (ConstantUndefined b1 b2) = compare (a1,a2) (b1,b2) - - -- if the constructors do not match - compare a b = compare (constrIndex (toConstr a)) (constrIndex (toConstr b)) - -instance Serialize Constant -instance Hashable Constant -instance ToJSON Constant where toJSON = genericToJSON jsonOptions -instance FromJSON Constant where parseJSON = genericParseJSON jsonOptions - -instance Arbitrary Constant where - arbitrary = oneof - [ ConstantBool <$> arbitrary - , ConstantInt TagInt <$> arbitrary - ] - -instance TypeOf Constant where - typeOf ConstantBool{} = return TypeBool - typeOf (ConstantInt t _) = return (TypeInt t) - typeOf (ConstantEnum defn _ _ ) = return (TypeEnum defn) - typeOf (ConstantField _ ty) = return ty - typeOf (ConstantAbstract x ) = typeOf x - typeOf (DomainInConstant dom) = typeOf dom - typeOf (TypedConstant _ ty) = return ty - typeOf (ConstantUndefined _ ty) = return ty - -instance DomainSizeOf Constant Integer where - domainSizeOf DomainBool{} = return 2 - domainSizeOf (DomainIntE x) = bug ("not implemented, domainSizeOf DomainIntE" <+> pretty (show x)) - domainSizeOf (DomainInt _ rs) = domainSizeOfRanges rs - domainSizeOf DomainEnum{} = fail "domainSizeOf: Unknown for given enum." - domainSizeOf (DomainTuple ds) = product <$> mapM domainSizeOf ds - domainSizeOf (DomainMatrix index inner) = intPow <$> domainSizeOf inner <*> domainSizeOf index - domainSizeOf d@(DomainSet _ (SetAttr attrs) inner) = - case attrs of - SizeAttr_None -> do - innerSize <- domainSizeOf inner - return (2 `intPow` innerSize) - SizeAttr_Size (ConstantInt _ size) -> do - innerSize <- domainSizeOf inner - return (nchoosek (product . enumFromTo 1) innerSize size) - SizeAttr_MinSize{} -> do - -- TODO: we can do better here - innerSize <- domainSizeOf inner - return (2 `intPow` innerSize) - SizeAttr_MaxSize (ConstantInt _ maxSize) -> do - innerSize <- domainSizeOf inner - return $ sum [ nchoosek (product . enumFromTo 1) innerSize k | k <- [0 .. maxSize] ] - SizeAttr_MinMaxSize (ConstantInt _ minSize) (ConstantInt _ maxSize) -> do - innerSize <- domainSizeOf inner - return $ sum [ nchoosek (product . enumFromTo 1) innerSize k | k <- [minSize .. maxSize] ] - _ -> fail ("domainSizeOf{Constant}" <+> pretty d) - domainSizeOf DomainMSet {} = bug "not implemented: domainSizeOf DomainMSet" - domainSizeOf DomainFunction {} = bug "not implemented: domainSizeOf DomainFunction" - domainSizeOf DomainRelation {} = bug "not implemented: domainSizeOf DomainRelation" - domainSizeOf DomainPartition {} = bug "not implemented: domainSizeOf DomainPartition" - domainSizeOf _ = bug "not implemented: domainSizeOf" - -emptyCollection :: Constant -> Bool -emptyCollection ConstantBool{} = False -emptyCollection ConstantInt{} = False -emptyCollection ConstantEnum{} = False -emptyCollection ConstantField{} = False -emptyCollection (ConstantAbstract x) = emptyCollectionAbsLit x -emptyCollection DomainInConstant{} = False -emptyCollection (TypedConstant x _) = emptyCollection x -emptyCollection ConstantUndefined{} = False - -intPow :: Integer -> Integer -> Integer -intPow = (^) - -domainSizeOfRanges :: MonadFail m => [Range Constant] -> m Integer -domainSizeOfRanges = fmap genericLength . valuesInIntDomain - -instance DomainSizeOf Constant Constant where - domainSizeOf = fmap (ConstantInt TagInt) . domainSizeOf - -instance Pretty Constant where - - -- hack, oh sweet hack! - -- print a domain instead of a type when printing an empty matrix literal. - -- this means we print "int()" instead of "int" inside the index of a matrix type - -- SR expects it this way... - pretty (TypedConstant (ConstantAbstract (AbsLitMatrix _ [])) ty) = - let - pretty' (TypeMatrix index innerNested) - = "matrix indexed by" <+> prettyList prBrackets "," (map pretty' indices) - <+> "of" <+> pretty inner - where - (indices,inner) = first (index:) $ collect innerNested - collect (TypeMatrix i j) = first (i:) $ collect j - collect x = ([],x) - pretty' TypeInt{} = "int()" - pretty' t = pretty t - in - prParens $ "[] : `" <> pretty' ty <> "`" - - pretty (ConstantBool False) = "false" - pretty (ConstantBool True ) = "true" - pretty (ConstantInt _ x ) = pretty x - pretty (ConstantEnum _ _ x) = pretty x - pretty (ConstantField n _) = pretty n - pretty (ConstantAbstract x) = pretty x - pretty (DomainInConstant d) = "`" <> pretty d <> "`" - pretty (TypedConstant x ty) = prParens $ pretty x <+> ":" <+> "`" <> pretty ty <> "`" - pretty (ConstantUndefined reason ty) = "undefined" <> prParens (pretty reason <+> ":" <+> "`" <> pretty ty <> "`") - -instance ExpressionLike Constant where - fromInt = ConstantInt TagInt - fromIntWithTag i t = ConstantInt t i - intOut _ (ConstantInt _ x) = return x - intOut doc c = fail $ vcat [ "Expecting an integer, but found:" <+> pretty c - , "Called from:" <+> doc - ] - - fromBool = ConstantBool - boolOut (ConstantBool x) = return x - boolOut ConstantUndefined{} = return False - boolOut c = fail ("Expecting a boolean, but found:" <+> pretty c) - - fromList xs = ConstantAbstract $ AbsLitMatrix (mkDomainIntB 1 (fromInt $ genericLength xs)) xs - listOut (ConstantAbstract (AbsLitMatrix _ xs)) = return xs - listOut c = fail ("Expecting a matrix literal, but found:" <+> pretty c) - -instance ReferenceContainer Constant where - fromName name = bug ("ReferenceContainer{Constant} fromName --" <+> pretty name) - nameOut (ConstantField nm _) = return nm - nameOut p = bug ("ReferenceContainer{Constant} nameOut --" <+> pretty p) - -instance DomainContainer Constant (Domain ()) where - fromDomain = DomainInConstant - domainOut (DomainInConstant dom) = return dom - domainOut _ = fail "domainOut{Constant}" - -mkUndef :: Type -> Doc -> Constant -mkUndef TypeBool _ = ConstantBool False -mkUndef ty reason = ConstantUndefined (stringToText $ show reason) ty - -isUndef :: Constant -> Bool -isUndef ConstantUndefined{} = True -isUndef _ = False - -normaliseConstant :: Constant -> Constant -normaliseConstant x@ConstantBool{} = x -normaliseConstant x@ConstantInt{} = x -normaliseConstant x@ConstantEnum{} = x -normaliseConstant x@ConstantField{} = x -normaliseConstant (ConstantAbstract x) = ConstantAbstract (normaliseAbsLit normaliseConstant x) -normaliseConstant (DomainInConstant d) = DomainInConstant (normaliseDomain normaliseConstant d) -normaliseConstant (TypedConstant c ty) = TypedConstant (normaliseConstant c) ty -normaliseConstant x@ConstantUndefined{} = x - -instance Num Constant where - ConstantInt _ x + ConstantInt _ y = ConstantInt TagInt (x+y) - x + y = bug $ vcat [ "Num Constant (+)", "x:" <+> pretty x, "y:" <+> pretty y ] - ConstantInt _ x - ConstantInt _ y = ConstantInt TagInt (x-y) - x - y = bug $ vcat [ "Num Constant (-)", "x:" <+> pretty x, "y:" <+> pretty y ] - ConstantInt _ x * ConstantInt _ y = ConstantInt TagInt (x*y) - x * y = bug $ vcat [ "Num Constant (*)", "x:" <+> pretty x, "y:" <+> pretty y ] - abs (ConstantInt t x) = ConstantInt t (abs x) - abs x = bug $ vcat [ "Num Constant abs", "x:" <+> pretty x ] - signum (ConstantInt t x) = ConstantInt t (signum x) - signum x = bug $ vcat [ "Num Constant signum", "x:" <+> pretty x ] - fromInteger = ConstantInt TagInt . fromInteger - - -valuesInIntDomain :: MonadFail m => [Range Constant] -> m [Integer] -valuesInIntDomain ranges = - if isFinite - then return allValues - else fail $ "Expected finite integer ranges, but got:" <++> prettyList id "," ranges - - where - - allRanges :: [Maybe [Integer]] - allRanges = - [ vals - | r <- ranges - , let vals = case r of - RangeSingle (ConstantInt _ x) -> return [x] - RangeBounded (ConstantInt _ l) (ConstantInt _ u) -> return [l..u] - _ -> Nothing - ] - - isFinite :: Bool - isFinite = Nothing `notElem` allRanges - - allValues :: [Integer] - allValues = sortNub $ concat $ catMaybes allRanges - - --- | Assuming both the value and the domain are normalised --- TODO: make this stricter, but write failing test cases first! -validateConstantForDomain :: forall m r . (MonadFail m, Pretty r) => Name -> Constant -> Domain r Constant -> m () - -validateConstantForDomain _ ConstantBool{} DomainBool{} = return () - -validateConstantForDomain _ _ (DomainInt _ []) = return () -- no restrictions - -validateConstantForDomain name c@(ConstantInt cTag i) d@(DomainInt dTag rs) | cTag == dTag = - let - intInRange RangeOpen = True - intInRange (RangeSingle (ConstantInt _ a)) = i == a - intInRange (RangeLowerBounded (ConstantInt _ a)) = i >= a - intInRange (RangeUpperBounded (ConstantInt _ a)) = i <= a - intInRange (RangeBounded (ConstantInt _ a) (ConstantInt _ b)) = i >= a && i <= b - intInRange _ = False - in unless (any intInRange rs) (constantNotInDomain name c d) - -validateConstantForDomain _ (ConstantInt _ i) (DomainUnnamed _ (ConstantInt _ a)) | i >= 1 && i <= a = return () - -validateConstantForDomain _ _ (DomainEnum _ Nothing _) = return () -- no restrictions -validateConstantForDomain name c d@(DomainEnum _ _ Nothing) = - fail $ vcat [ "validateConstantForDomain: enum not handled" - , pretty name - , pretty c - , pretty d - ] -validateConstantForDomain name - c@(ConstantInt cTag _) - d@(DomainEnum _ (Just ranges) (Just mp)) = nested c d $ do - let - -- lu :: MonadFail m => Name -> m Constant - lu (ConstantEnum _ _ nm) = - case lookup nm mp of - Nothing -> fail $ "No value for:" <+> pretty nm - Just v -> return (ConstantInt cTag v) - lu (ConstantInt t v) = return (ConstantInt t v) - lu x = fail $ "validateConstantForDomain.lu" <+> pretty x - - -- lu2 :: MonadFail m => Range Name -> m (Range Constant) - lu2 = mapM lu - - rs <- mapM lu2 ranges - validateConstantForDomain name c (DomainInt cTag rs :: Domain r Constant) - -validateConstantForDomain name - c@(ConstantAbstract (AbsLitTuple cs)) - d@(DomainTuple ds) = nested c d $ zipWithM_ (validateConstantForDomain name) cs ds - -validateConstantForDomain name - c@(ConstantAbstract (AbsLitRecord (sortOn fst -> cs))) - d@(DomainRecord (sortOn fst -> ds)) - | map fst cs == map fst ds - = nested c d $ zipWithM_ (validateConstantForDomain name) (map snd cs) (map snd ds) - | otherwise - = constantNotInDomain name c d - -validateConstantForDomain name - c@(ConstantAbstract (AbsLitVariant _ n c')) - d@(DomainVariant ds) - | Just d' <- lookup n ds - = nested c d $ validateConstantForDomain name c' d' - | otherwise - = constantNotInDomain name c d - -validateConstantForDomain name - c@(ConstantAbstract (AbsLitMatrix cIndex vals)) - d@(DomainMatrix dIndex dInner) = do - nested c d $ - mapM_ (\ val -> validateConstantForDomain name val dInner ) vals - let - isEmptyIntDomain (DomainInt _ []) = True - isEmptyIntDomain _ = False - unless (cIndex == dIndex || isEmptyIntDomain cIndex) $ fail $ vcat - [ "The indices do not match between the value and the domain." - , "Value :" <+> pretty c - , "Domain:" <+> pretty d - ] - -validateConstantForDomain name - c@(ConstantAbstract (AbsLitSet vals)) - d@(DomainSet _ (SetAttr sizeAttr) dInner) = do - let cardinalityOK = case sizeAttr of - SizeAttr_None -> True - SizeAttr_Size (ConstantInt _ s) -> s == genericLength vals - SizeAttr_MinSize (ConstantInt _ s) -> s <= genericLength vals - SizeAttr_MaxSize (ConstantInt _ s) -> genericLength vals <= s - SizeAttr_MinMaxSize (ConstantInt _ smin) (ConstantInt _ smax) -> - smin <= genericLength vals && genericLength vals <= smax - _ -> False - unless cardinalityOK $ fail $ vcat - [ "The value is not a member of the domain." - , "Value :" <+> pretty c - , "Domain:" <+> pretty d - , "Reason: Domain attributes are not satisfied." - , "Specifically:" <+> pretty sizeAttr - ] - nested c d $ mapM_ (\ val -> validateConstantForDomain name val dInner ) vals - -validateConstantForDomain name - c@(ConstantAbstract (AbsLitMSet vals)) - d@(DomainMSet _ (MSetAttr sizeAttr occurAttr) dInner) = do - let cardinalityOK = case sizeAttr of - SizeAttr_None -> True - SizeAttr_Size (ConstantInt _ s) -> s == genericLength vals - SizeAttr_MinSize (ConstantInt _ s) -> s <= genericLength vals - SizeAttr_MaxSize (ConstantInt _ s) -> genericLength vals <= s - SizeAttr_MinMaxSize (ConstantInt _ smin) (ConstantInt _ smax) -> - smin <= genericLength vals && genericLength vals <= smax - _ -> False - unless cardinalityOK $ fail $ vcat - [ "The value is not a member of the domain." - , "Value :" <+> pretty c - , "Domain:" <+> pretty d - , "Reason: Domain attributes are not satisfied." - , "Specifically:" <+> pretty sizeAttr - ] - let occurOK = case occurAttr of - OccurAttr_None -> True - OccurAttr_MinOccur (ConstantInt _ s) -> and [ s <= occ | (_, occ) <- histogram vals ] - OccurAttr_MaxOccur (ConstantInt _ s) -> and [ occ <= s | (_, occ) <- histogram vals ] - OccurAttr_MinMaxOccur (ConstantInt _ smin) (ConstantInt _ smax) -> - and [ smin <= occ && occ <= smax | (_, occ) <- histogram vals ] - _ -> False - unless occurOK $ fail $ vcat - [ "The value is not a member of the domain." - , "Value :" <+> pretty c - , "Domain:" <+> pretty d - , "Reason: Domain attributes are not satisfied." - , "Specifically:" <+> pretty occurAttr - ] - nested c d $ mapM_ (\ val -> validateConstantForDomain name val dInner ) vals - -validateConstantForDomain name - c@(ConstantAbstract (AbsLitFunction vals)) - d@(DomainFunction _ _ dFrom dTo) = nested c d $ do - mapM_ (\ val -> validateConstantForDomain name (fst val) dFrom) vals - mapM_ (\ val -> validateConstantForDomain name (snd val) dTo ) vals - -validateConstantForDomain name - c@(ConstantAbstract (AbsLitSequence vals)) - d@(DomainSequence _ _ dInner) = nested c d $ - mapM_ (\ val -> validateConstantForDomain name val dInner ) vals - -validateConstantForDomain name - c@(ConstantAbstract (AbsLitRelation valss)) - d@(DomainRelation _ _ dInners) = nested c d $ - forM_ valss $ \ vals -> - zipWithM_ (validateConstantForDomain name) vals dInners - -validateConstantForDomain name - c@(ConstantAbstract (AbsLitPartition valss)) - d@(DomainPartition _ _ dInner) = nested c d $ - mapM_ (\ val -> validateConstantForDomain name val dInner ) (concat valss) - -validateConstantForDomain name c@(TypedConstant c' _) d = nested c d $ validateConstantForDomain name c' d - -validateConstantForDomain name c d = constantNotInDomain name c d - - -nested :: (MonadFail m, Pretty r) => Constant -> Domain r Constant -> Either Doc () -> m () -nested _ _ Right{} = return () -nested c d (Left err) = fail $ vcat - [ "The value is not a member of the domain." - , "Value :" <+> pretty c - , "Domain:" <+> pretty d - , "Reason:" - , nest 4 err - ] - -constantNotInDomain :: (MonadFail m, Pretty r) => Name -> Constant -> Domain r Constant -> m () -constantNotInDomain n c d = fail $ vcat - [ "The value is not a member of the domain." - , "Name :" <+> pretty n - , "Value :" <+> pretty c - , "Domain:" <+> pretty d - ] - - -viewConstantBool :: MonadFail m => Constant -> m Bool -viewConstantBool (ConstantBool i) = return i -viewConstantBool (ConstantInt _ 0) = return False -viewConstantBool (ConstantInt _ 1) = return True -viewConstantBool constant = fail ("Expecting a boolean, but got:" <++> pretty constant) - -viewConstantInt :: MonadFail m => Constant -> m Integer -viewConstantInt (ConstantInt _ i) = return i -viewConstantInt constant = fail ("Expecting an integer, but got:" <++> pretty constant) - -viewConstantTuple :: MonadFail m => Constant -> m [Constant] -viewConstantTuple (ConstantAbstract (AbsLitTuple xs)) = return xs -viewConstantTuple (TypedConstant c _) = viewConstantTuple c -viewConstantTuple constant = fail ("Expecting a tuple, but got:" <++> pretty constant) - -viewConstantRecord :: MonadFail m => Constant -> m [(Name, Constant)] -viewConstantRecord (ConstantAbstract (AbsLitRecord xs)) = return xs -viewConstantRecord (TypedConstant c _) = viewConstantRecord c -viewConstantRecord constant = fail ("Expecting a record, but got:" <++> pretty constant) - -viewConstantVariant :: MonadFail m => Constant -> m (Maybe [(Name, Domain () Constant)], Name, Constant) -viewConstantVariant (ConstantAbstract (AbsLitVariant lu nm x)) = return (lu, nm, x) -viewConstantVariant (TypedConstant c _) = viewConstantVariant c -viewConstantVariant constant = fail ("Expecting a variant, but got:" <++> pretty constant) - -viewConstantMatrix :: MonadFail m => Constant -> m (Domain () Constant, [Constant]) -viewConstantMatrix (ConstantAbstract (AbsLitMatrix ind xs)) = return (ind, xs) -viewConstantMatrix (TypedConstant c _) = viewConstantMatrix c -viewConstantMatrix constant = fail ("Expecting a matrix, but got:" <++> pretty constant) - -viewConstantSet :: MonadFail m => Constant -> m [Constant] -viewConstantSet (ConstantAbstract (AbsLitSet xs)) = return xs -viewConstantSet (TypedConstant c _) = viewConstantSet c -viewConstantSet constant = fail ("Expecting a set, but got:" <++> pretty constant) - -viewConstantMSet :: MonadFail m => Constant -> m [Constant] -viewConstantMSet (ConstantAbstract (AbsLitMSet xs)) = return xs -viewConstantMSet (TypedConstant c _) = viewConstantMSet c -viewConstantMSet constant = fail ("Expecting an mset, but got:" <++> pretty constant) - -viewConstantFunction :: MonadFail m => Constant -> m [(Constant, Constant)] -viewConstantFunction (ConstantAbstract (AbsLitFunction xs)) = return xs -viewConstantFunction (TypedConstant c _) = viewConstantFunction c -viewConstantFunction constant = do - let - suggestion = case constant of - ConstantAbstract (AbsLitMatrix (DomainInt _ rs) vals) -> do - froms <- valuesInIntDomain rs - return $ Just $ pretty $ AbsLitFunction (zip (map (ConstantInt TagInt) froms) vals) - _ -> return Nothing - suggestion >>= \case - Nothing -> fail ("Expecting a function, but got:" <++> pretty constant) - Just sug -> fail (vcat [ "Expecting a function, but got:" <++> pretty constant - , "Maybe you meant:" <++> sug - ]) - -viewConstantSequence :: MonadFail m => Constant -> m [Constant] -viewConstantSequence (ConstantAbstract (AbsLitSequence xs)) = return xs -viewConstantSequence (TypedConstant c _) = viewConstantSequence c -viewConstantSequence constant = fail ("Expecting a sequence, but got:" <++> pretty constant) - -viewConstantRelation :: MonadFail m => Constant -> m [[Constant]] -viewConstantRelation (ConstantAbstract (AbsLitRelation xs)) = return xs -viewConstantRelation (TypedConstant c _) = viewConstantRelation c -viewConstantRelation constant = fail ("Expecting a relation, but got:" <++> pretty constant) - -viewConstantPartition :: MonadFail m => Constant -> m [[Constant]] -viewConstantPartition (ConstantAbstract (AbsLitPartition xs)) = return xs -viewConstantPartition (TypedConstant c _) = viewConstantPartition c -viewConstantPartition constant = fail ("Expecting a partition, but got:" <++> pretty constant) - diff --git a/src/Conjure/Language/Constant_LOCAL_23009.hs b/src/Conjure/Language/Constant_LOCAL_23009.hs deleted file mode 100644 index 2fcf67e975..0000000000 --- a/src/Conjure/Language/Constant_LOCAL_23009.hs +++ /dev/null @@ -1,534 +0,0 @@ -{-# LANGUAGE DeriveGeneric, DeriveDataTypeable #-} -{-# LANGUAGE ViewPatterns #-} - -module Conjure.Language.Constant - ( Constant(..) - , valuesInIntDomain - , normaliseConstant - , validateConstantForDomain - , mkUndef, isUndef - , emptyCollection - , viewConstantBool - , viewConstantInt - , viewConstantTuple - , viewConstantRecord - , viewConstantVariant - , viewConstantMatrix - , viewConstantSet - , viewConstantMSet - , viewConstantFunction - , viewConstantSequence - , viewConstantRelation - , viewConstantPartition - , viewConstantPermutation - , reDomConst - ) where - --- conjure -import Conjure.Prelude -import Conjure.Bug -import Conjure.Language.Name -import Conjure.Language.Domain -import Conjure.Language.Type -import Conjure.Language.AbstractLiteral - -import Conjure.Language.DomainSizeOf -import Conjure.Language.TypeOf -import Conjure.Language.AdHoc -import Conjure.Language.Pretty - --- base -import Data.Data ( toConstr, constrIndex ) - --- QuickCheck -import Test.QuickCheck ( Arbitrary(..), oneof ) - - -data Constant - = ConstantBool Bool - | ConstantInt IntTag Integer - | ConstantEnum Name {- name for the enum domain -} - [Name] {- values in the enum domain -} - Name {- the literal -} - | ConstantField Name Type -- the name of a field of Record or Variant and its type - | ConstantAbstract (AbstractLiteral Constant) - | DomainInConstant (Domain () Constant) - | TypedConstant Constant Type - | ConstantUndefined Text Type -- never use this for a bool - -- use false instead for them - deriving (Show, Data, Typeable, Generic) - -instance Eq Constant where - a == b = compare a b == EQ - --- implementing the Eq&Ord instances by hand, because we want to special case the TypedConstant constructor -instance Ord Constant where - - -- do not use type info when comparing - compare (TypedConstant a _) (TypedConstant b _) = compare a b - compare (TypedConstant a _) b = compare a b - compare a (TypedConstant b _) = compare a b - - -- the "usual" comparisons - compare (ConstantBool a) (ConstantBool b) = compare a b - compare (ConstantInt _ a) (ConstantInt _ b) = compare a b - compare (ConstantEnum _ aVals aVal) (ConstantEnum _ bVals bVal) = - compare (elemIndex aVal aVals, aVal) (elemIndex bVal bVals, bVal) - compare (ConstantField a1 a2) (ConstantField b1 b2) = compare (a1,a2) (b1,b2) - compare (ConstantAbstract a) (ConstantAbstract b) = compare a b - compare (DomainInConstant a) (DomainInConstant b) = compare a b - compare (ConstantUndefined a1 a2) (ConstantUndefined b1 b2) = compare (a1,a2) (b1,b2) - - -- if the constructors do not match - compare a b = compare (constrIndex (toConstr a)) (constrIndex (toConstr b)) - -instance Serialize Constant -instance Hashable Constant -instance ToJSON Constant where toJSON = genericToJSON jsonOptions -instance FromJSON Constant where parseJSON = genericParseJSON jsonOptions - -instance Arbitrary Constant where - arbitrary = oneof - [ ConstantBool <$> arbitrary - , ConstantInt TagInt <$> arbitrary - ] - -instance TypeOf Constant where - typeOf ConstantBool{} = return TypeBool - typeOf (ConstantInt t _) = return (TypeInt t) - typeOf (ConstantEnum defn _ _ ) = return (TypeEnum defn) - typeOf (ConstantField _ ty) = return ty - typeOf (ConstantAbstract x ) = typeOf x - typeOf (DomainInConstant dom) = typeOf dom - typeOf (TypedConstant _ ty) = return ty - typeOf (ConstantUndefined _ ty) = return ty - -instance DomainSizeOf Constant Integer where - domainSizeOf DomainBool{} = return 2 - domainSizeOf (DomainIntE x) = bug ("not implemented, domainSizeOf DomainIntE" <+> pretty (show x)) - domainSizeOf (DomainInt _ rs) = domainSizeOfRanges rs - domainSizeOf DomainEnum{} = fail "domainSizeOf: Unknown for given enum." - domainSizeOf (DomainTuple ds) = product <$> mapM domainSizeOf ds - domainSizeOf (DomainMatrix index inner) = intPow <$> domainSizeOf inner <*> domainSizeOf index - domainSizeOf d@(DomainSet _ (SetAttr attrs) inner) = - case attrs of - SizeAttr_None -> do - innerSize <- domainSizeOf inner - return (2 `intPow` innerSize) - SizeAttr_Size (ConstantInt _ size) -> do - innerSize <- domainSizeOf inner - return (nchoosek (product . enumFromTo 1) innerSize size) - SizeAttr_MinSize{} -> do - -- TODO: we can do better here - innerSize <- domainSizeOf inner - return (2 `intPow` innerSize) - SizeAttr_MaxSize (ConstantInt _ maxSize) -> do - innerSize <- domainSizeOf inner - return $ sum [ nchoosek (product . enumFromTo 1) innerSize k | k <- [0 .. maxSize] ] - SizeAttr_MinMaxSize (ConstantInt _ minSize) (ConstantInt _ maxSize) -> do - innerSize <- domainSizeOf inner - return $ sum [ nchoosek (product . enumFromTo 1) innerSize k | k <- [minSize .. maxSize] ] - _ -> fail ("domainSizeOf{Constant}" <+> pretty d) - domainSizeOf DomainMSet {} = bug "not implemented: domainSizeOf DomainMSet" - domainSizeOf DomainFunction {} = bug "not implemented: domainSizeOf DomainFunction" - domainSizeOf DomainRelation {} = bug "not implemented: domainSizeOf DomainRelation" - domainSizeOf DomainPartition {} = bug "not implemented: domainSizeOf DomainPartition" - domainSizeOf _ = bug "not implemented: domainSizeOf" - -emptyCollection :: Constant -> Bool -emptyCollection ConstantBool{} = False -emptyCollection ConstantInt{} = False -emptyCollection ConstantEnum{} = False -emptyCollection ConstantField{} = False -emptyCollection (ConstantAbstract x) = emptyCollectionAbsLit x -emptyCollection DomainInConstant{} = False -emptyCollection (TypedConstant x _) = emptyCollection x -emptyCollection ConstantUndefined{} = False - -intPow :: Integer -> Integer -> Integer -intPow = (^) - -domainSizeOfRanges :: MonadFail m => [Range Constant] -> m Integer -domainSizeOfRanges = fmap genericLength . valuesInIntDomain - -instance DomainSizeOf Constant Constant where - domainSizeOf = fmap (ConstantInt TagInt) . domainSizeOf - -instance Pretty Constant where - - -- hack, oh sweet hack! - -- print a domain instead of a type when printing an empty matrix literal. - -- this means we print "int()" instead of "int" inside the index of a matrix type - -- SR expects it this way... - pretty (TypedConstant (ConstantAbstract (AbsLitMatrix _ [])) ty) = - let - pretty' (TypeMatrix index innerNested) - = "matrix indexed by" <+> prettyList prBrackets "," (map pretty' indices) - <+> "of" <+> pretty inner - where - (indices,inner) = first (index:) $ collect innerNested - collect (TypeMatrix i j) = first (i:) $ collect j - collect x = ([],x) - pretty' TypeInt{} = "int()" - pretty' t = pretty t - in - prParens $ "[] : `" <> pretty' ty <> "`" - - pretty (ConstantBool False) = "false" - pretty (ConstantBool True ) = "true" - pretty (ConstantInt _ x ) = pretty x - pretty (ConstantEnum _ _ x) = pretty x - pretty (ConstantField n _) = pretty n - pretty (ConstantAbstract x) = pretty x - pretty (DomainInConstant d) = "`" <> pretty d <> "`" - pretty (TypedConstant x ty) = prParens $ pretty x <+> ":" <+> "`" <> pretty ty <> "`" - pretty (ConstantUndefined reason ty) = "undefined" <> prParens (pretty reason <+> ":" <+> "`" <> pretty ty <> "`") - -instance ExpressionLike Constant where - fromInt = ConstantInt TagInt - fromIntWithTag i t = ConstantInt t i - intOut _ (ConstantInt _ x) = return x - intOut doc c = fail $ vcat [ "Expecting an integer, but found:" <+> pretty c - , "Called from:" <+> doc - ] - - fromBool = ConstantBool - boolOut (ConstantBool x) = return x - boolOut ConstantUndefined{} = return False - boolOut c = fail ("Expecting a boolean, but found:" <+> pretty c) - - fromList xs = ConstantAbstract $ AbsLitMatrix (mkDomainIntB 1 (fromInt $ genericLength xs)) xs - listOut (ConstantAbstract (AbsLitMatrix _ xs)) = return xs - listOut c = fail ("Expecting a matrix literal, but found:" <+> pretty c) - -instance ReferenceContainer Constant where - fromName name = bug ("ReferenceContainer{Constant} fromName --" <+> pretty name) - nameOut (ConstantField nm _) = return nm - nameOut p = bug ("ReferenceContainer{Constant} nameOut --" <+> pretty p) - -instance DomainContainer Constant (Domain ()) where - fromDomain = DomainInConstant - domainOut (DomainInConstant dom) = return dom - domainOut _ = fail "domainOut{Constant}" - -mkUndef :: Type -> Doc -> Constant -mkUndef TypeBool _ = ConstantBool False -mkUndef ty reason = ConstantUndefined (stringToText $ show reason) ty - -isUndef :: Constant -> Bool -isUndef ConstantUndefined{} = True -isUndef _ = False - -normaliseConstant :: Constant -> Constant -normaliseConstant x@ConstantBool{} = x -normaliseConstant x@ConstantInt{} = x -normaliseConstant x@ConstantEnum{} = x -normaliseConstant x@ConstantField{} = x -normaliseConstant (ConstantAbstract x) = ConstantAbstract (normaliseAbsLit normaliseConstant x) -normaliseConstant (DomainInConstant d) = DomainInConstant (normaliseDomain normaliseConstant d) -normaliseConstant (TypedConstant c ty) = TypedConstant (normaliseConstant c) ty -normaliseConstant x@ConstantUndefined{} = x - -instance Num Constant where - ConstantInt _ x + ConstantInt _ y = ConstantInt TagInt (x+y) - x + y = bug $ vcat [ "Num Constant (+)", "x:" <+> pretty x, "y:" <+> pretty y ] - ConstantInt _ x - ConstantInt _ y = ConstantInt TagInt (x-y) - x - y = bug $ vcat [ "Num Constant (-)", "x:" <+> pretty x, "y:" <+> pretty y ] - ConstantInt _ x * ConstantInt _ y = ConstantInt TagInt (x*y) - x * y = bug $ vcat [ "Num Constant (*)", "x:" <+> pretty x, "y:" <+> pretty y ] - abs (ConstantInt t x) = ConstantInt t (abs x) - abs x = bug $ vcat [ "Num Constant abs", "x:" <+> pretty x ] - signum (ConstantInt t x) = ConstantInt t (signum x) - signum x = bug $ vcat [ "Num Constant signum", "x:" <+> pretty x ] - fromInteger = ConstantInt TagInt . fromInteger - - -valuesInIntDomain :: MonadFail m => [Range Constant] -> m [Integer] -valuesInIntDomain ranges = - if isFinite - then return allValues - else fail $ "Expected finite integer ranges, but got:" <++> prettyList id "," ranges - - where - - allRanges :: [Maybe [Integer]] - allRanges = - [ vals - | r <- ranges - , let vals = case r of - RangeSingle (ConstantInt _ x) -> return [x] - RangeBounded (ConstantInt _ l) (ConstantInt _ u) -> return [l..u] - _ -> Nothing - ] - - isFinite :: Bool - isFinite = Nothing `notElem` allRanges - - allValues :: [Integer] - allValues = sortNub $ concat $ catMaybes allRanges - - --- | Assuming both the value and the domain are normalised --- TODO: make this stricter, but write failing test cases first! -validateConstantForDomain :: forall m r . (MonadFail m, Pretty r) => Name -> Constant -> Domain r Constant -> m () - -validateConstantForDomain _ ConstantBool{} DomainBool{} = return () - -validateConstantForDomain _ _ (DomainInt _ []) = return () -- no restrictions - -validateConstantForDomain name c@(ConstantInt cTag i) d@(DomainInt dTag rs) | cTag == dTag = - let - intInRange RangeOpen = True - intInRange (RangeSingle (ConstantInt _ a)) = i == a - intInRange (RangeLowerBounded (ConstantInt _ a)) = i >= a - intInRange (RangeUpperBounded (ConstantInt _ a)) = i <= a - intInRange (RangeBounded (ConstantInt _ a) (ConstantInt _ b)) = i >= a && i <= b - intInRange _ = False - in unless (any intInRange rs) (constantNotInDomain name c d) - -validateConstantForDomain _ (ConstantInt _ i) (DomainUnnamed _ (ConstantInt _ a)) | i >= 1 && i <= a = return () - -validateConstantForDomain _ _ (DomainEnum _ Nothing _) = return () -- no restrictions -validateConstantForDomain name c d@(DomainEnum _ _ Nothing) = - fail $ vcat [ "validateConstantForDomain: enum not handled" - , pretty name - , pretty c - , pretty d - ] -validateConstantForDomain name - c@(ConstantInt cTag _) - d@(DomainEnum _ (Just ranges) (Just mp)) = nested c d $ do - let - -- lu :: MonadFail m => Name -> m Constant - lu (ConstantEnum _ _ nm) = - case lookup nm mp of - Nothing -> fail $ "No value for:" <+> pretty nm - Just v -> return (ConstantInt cTag v) - lu (ConstantInt t v) = return (ConstantInt t v) - lu x = fail $ "validateConstantForDomain.lu" <+> pretty x - - -- lu2 :: MonadFail m => Range Name -> m (Range Constant) - lu2 = mapM lu - - rs <- mapM lu2 ranges - validateConstantForDomain name c (DomainInt cTag rs :: Domain r Constant) - -validateConstantForDomain name - c@(ConstantAbstract (AbsLitTuple cs)) - d@(DomainTuple ds) = nested c d $ zipWithM_ (validateConstantForDomain name) cs ds - -validateConstantForDomain name - c@(ConstantAbstract (AbsLitRecord (sortOn fst -> cs))) - d@(DomainRecord (sortOn fst -> ds)) - | map fst cs == map fst ds - = nested c d $ zipWithM_ (validateConstantForDomain name) (map snd cs) (map snd ds) - | otherwise - = constantNotInDomain name c d - -validateConstantForDomain name - c@(ConstantAbstract (AbsLitVariant _ n c')) - d@(DomainVariant ds) - | Just d' <- lookup n ds - = nested c d $ validateConstantForDomain name c' d' - | otherwise - = constantNotInDomain name c d - -validateConstantForDomain name - c@(ConstantAbstract (AbsLitMatrix cIndex vals)) - d@(DomainMatrix dIndex dInner) = do - nested c d $ - mapM_ (\ val -> validateConstantForDomain name val dInner ) vals - let - isEmptyIntDomain (DomainInt _ []) = True - isEmptyIntDomain _ = False - unless (cIndex == dIndex || isEmptyIntDomain cIndex) $ fail $ vcat - [ "The indices do not match between the value and the domain." - , "Value :" <+> pretty c - , "Domain:" <+> pretty d - ] - -validateConstantForDomain name - c@(ConstantAbstract (AbsLitSet vals)) - d@(DomainSet _ (SetAttr sizeAttr) dInner) = do - let cardinalityOK = case sizeAttr of - SizeAttr_None -> True - SizeAttr_Size (ConstantInt _ s) -> s == genericLength vals - SizeAttr_MinSize (ConstantInt _ s) -> s <= genericLength vals - SizeAttr_MaxSize (ConstantInt _ s) -> genericLength vals <= s - SizeAttr_MinMaxSize (ConstantInt _ smin) (ConstantInt _ smax) -> - smin <= genericLength vals && genericLength vals <= smax - _ -> False - unless cardinalityOK $ fail $ vcat - [ "The value is not a member of the domain." - , "Value :" <+> pretty c - , "Domain:" <+> pretty d - , "Reason: Domain attributes are not satisfied." - , "Specifically:" <+> pretty sizeAttr - ] - nested c d $ mapM_ (\ val -> validateConstantForDomain name val dInner ) vals - -validateConstantForDomain name - c@(ConstantAbstract (AbsLitMSet vals)) - d@(DomainMSet _ (MSetAttr sizeAttr occurAttr) dInner) = do - let cardinalityOK = case sizeAttr of - SizeAttr_None -> True - SizeAttr_Size (ConstantInt _ s) -> s == genericLength vals - SizeAttr_MinSize (ConstantInt _ s) -> s <= genericLength vals - SizeAttr_MaxSize (ConstantInt _ s) -> genericLength vals <= s - SizeAttr_MinMaxSize (ConstantInt _ smin) (ConstantInt _ smax) -> - smin <= genericLength vals && genericLength vals <= smax - _ -> False - unless cardinalityOK $ fail $ vcat - [ "The value is not a member of the domain." - , "Value :" <+> pretty c - , "Domain:" <+> pretty d - , "Reason: Domain attributes are not satisfied." - , "Specifically:" <+> pretty sizeAttr - ] - let occurOK = case occurAttr of - OccurAttr_None -> True - OccurAttr_MinOccur (ConstantInt _ s) -> and [ s <= occ | (_, occ) <- histogram vals ] - OccurAttr_MaxOccur (ConstantInt _ s) -> and [ occ <= s | (_, occ) <- histogram vals ] - OccurAttr_MinMaxOccur (ConstantInt _ smin) (ConstantInt _ smax) -> - and [ smin <= occ && occ <= smax | (_, occ) <- histogram vals ] - _ -> False - unless occurOK $ fail $ vcat - [ "The value is not a member of the domain." - , "Value :" <+> pretty c - , "Domain:" <+> pretty d - , "Reason: Domain attributes are not satisfied." - , "Specifically:" <+> pretty occurAttr - ] - nested c d $ mapM_ (\ val -> validateConstantForDomain name val dInner ) vals - -validateConstantForDomain name - c@(ConstantAbstract (AbsLitFunction vals)) - d@(DomainFunction _ _ dFrom dTo) = nested c d $ do - mapM_ (\ val -> validateConstantForDomain name (fst val) dFrom) vals - mapM_ (\ val -> validateConstantForDomain name (snd val) dTo ) vals - -validateConstantForDomain name - c@(ConstantAbstract (AbsLitSequence vals)) - d@(DomainSequence _ _ dInner) = nested c d $ - mapM_ (\ val -> validateConstantForDomain name val dInner ) vals - -validateConstantForDomain name - c@(ConstantAbstract (AbsLitRelation valss)) - d@(DomainRelation _ _ dInners) = nested c d $ - forM_ valss $ \ vals -> - zipWithM_ (validateConstantForDomain name) vals dInners - -validateConstantForDomain name - c@(ConstantAbstract (AbsLitPartition valss)) - d@(DomainPartition _ _ dInner) = nested c d $ - mapM_ (\ val -> validateConstantForDomain name val dInner ) (concat valss) -validateConstantForDomain name - c@(ConstantAbstract (AbsLitPermutation valss)) - d@(DomainPermutation _ _ dInner) = nested c d $ - mapM_ (\ val -> validateConstantForDomain name val dInner ) (concat valss) -validateConstantForDomain name c@(TypedConstant c' _) d = nested c d $ validateConstantForDomain name c' d - -validateConstantForDomain name c d = constantNotInDomain name c d - - -nested :: (MonadFail m, Pretty r) => Constant -> Domain r Constant -> Either Doc () -> m () -nested _ _ Right{} = return () -nested c d (Left err) = fail $ vcat - [ "The value is not a member of the domain." - , "Value :" <+> pretty c - , "Domain:" <+> pretty d - , "Reason:" - , nest 4 err - ] - -constantNotInDomain :: (MonadFail m, Pretty r) => Name -> Constant -> Domain r Constant -> m () -constantNotInDomain n c d = fail $ vcat - [ "The value is not a member of the domain." - , "Name :" <+> pretty n - , "Value :" <+> pretty c - , "Domain:" <+> pretty d - ] - - -viewConstantBool :: MonadFail m => Constant -> m Bool -viewConstantBool (ConstantBool i) = return i -viewConstantBool (ConstantInt _ 0) = return False -viewConstantBool (ConstantInt _ 1) = return True -viewConstantBool constant = fail ("Expecting a boolean, but got:" <++> pretty constant) - -viewConstantInt :: MonadFail m => Constant -> m Integer -viewConstantInt (ConstantInt _ i) = return i -viewConstantInt constant = fail ("Expecting an integer, but got:" <++> pretty constant) - -viewConstantTuple :: MonadFail m => Constant -> m [Constant] -viewConstantTuple (ConstantAbstract (AbsLitTuple xs)) = return xs -viewConstantTuple (TypedConstant c _) = viewConstantTuple c -viewConstantTuple constant = fail ("Expecting a tuple, but got:" <++> pretty constant) - -viewConstantRecord :: MonadFail m => Constant -> m [(Name, Constant)] -viewConstantRecord (ConstantAbstract (AbsLitRecord xs)) = return xs -viewConstantRecord (TypedConstant c _) = viewConstantRecord c -viewConstantRecord constant = fail ("Expecting a record, but got:" <++> pretty constant) - -viewConstantVariant :: MonadFail m => Constant -> m (Maybe [(Name, Domain () Constant)], Name, Constant) -viewConstantVariant (ConstantAbstract (AbsLitVariant lu nm x)) = return (lu, nm, x) -viewConstantVariant (TypedConstant c _) = viewConstantVariant c -viewConstantVariant constant = fail ("Expecting a variant, but got:" <++> pretty constant) - -viewConstantMatrix :: MonadFail m => Constant -> m (Domain () Constant, [Constant]) -viewConstantMatrix (ConstantAbstract (AbsLitMatrix ind xs)) = return (ind, xs) -viewConstantMatrix (TypedConstant c _) = viewConstantMatrix c -viewConstantMatrix constant = fail ("Expecting a matrix, but got:" <++> pretty constant) - -viewConstantSet :: MonadFail m => Constant -> m [Constant] -viewConstantSet (ConstantAbstract (AbsLitSet xs)) = return xs -viewConstantSet (TypedConstant c _) = viewConstantSet c -viewConstantSet constant = fail ("Expecting a set, but got:" <++> pretty constant) - -viewConstantMSet :: MonadFail m => Constant -> m [Constant] -viewConstantMSet (ConstantAbstract (AbsLitMSet xs)) = return xs -viewConstantMSet (TypedConstant c _) = viewConstantMSet c -viewConstantMSet constant = fail ("Expecting an mset, but got:" <++> pretty constant) - -viewConstantFunction :: MonadFail m => Constant -> m [(Constant, Constant)] -viewConstantFunction (ConstantAbstract (AbsLitFunction xs)) = return xs -viewConstantFunction (TypedConstant c _) = viewConstantFunction c -viewConstantFunction constant = do - let - suggestion = case constant of - ConstantAbstract (AbsLitMatrix (DomainInt _ rs) vals) -> do - froms <- valuesInIntDomain rs - return $ Just $ pretty $ AbsLitFunction (zip (map (ConstantInt TagInt) froms) vals) - _ -> return Nothing - suggestion >>= \case - Nothing -> fail ("Expecting a function, but got:" <++> pretty constant) - Just sug -> fail (vcat [ "Expecting a function, but got:" <++> pretty constant - , "Maybe you meant:" <++> sug - ]) - -viewConstantSequence :: MonadFail m => Constant -> m [Constant] -viewConstantSequence (ConstantAbstract (AbsLitSequence xs)) = return xs -viewConstantSequence (TypedConstant c _) = viewConstantSequence c -viewConstantSequence constant = fail ("Expecting a sequence, but got:" <++> pretty constant) - -viewConstantRelation :: MonadFail m => Constant -> m [[Constant]] -viewConstantRelation (ConstantAbstract (AbsLitRelation xs)) = return xs -viewConstantRelation (TypedConstant c _) = viewConstantRelation c -viewConstantRelation constant = fail ("Expecting a relation, but got:" <++> pretty constant) - -viewConstantPartition :: MonadFail m => Constant -> m [[Constant]] -viewConstantPartition (ConstantAbstract (AbsLitPartition xs)) = return xs -viewConstantPartition (TypedConstant c _) = viewConstantPartition c -viewConstantPartition constant = fail ("Expecting a partition, but got:" <++> pretty constant) - -viewConstantPermutation :: MonadFail m => Constant -> m [[Constant]] -viewConstantPermutation (ConstantAbstract (AbsLitPermutation xs)) = return xs -viewConstantPermutation (TypedConstant c _) = viewConstantPermutation c -viewConstantPermutation constant = fail ("Expecting a permutation, but got:" <++> pretty constant) - - -reDomConst :: Domain () Constant -> Domain () Constant -reDomConst cns = case cns of - DomainInt t _ -> reTag t cns - _ -> cns - diff --git a/src/Conjure/Language/Constant_REMOTE_23009.hs b/src/Conjure/Language/Constant_REMOTE_23009.hs deleted file mode 100644 index ed56acaa74..0000000000 --- a/src/Conjure/Language/Constant_REMOTE_23009.hs +++ /dev/null @@ -1,337 +0,0 @@ -{-# LANGUAGE DeriveGeneric, DeriveDataTypeable #-} - -module Conjure.Language.Constant - ( Constant(..) - , valuesInIntDomain - , normaliseConstant - , mkUndef, isUndef - , emptyCollection - , viewConstantBool - , viewConstantInt - , viewConstantTuple - , viewConstantRecord - , viewConstantVariant - , viewConstantMatrix - , viewConstantSet - , viewConstantMSet - , viewConstantFunction - , viewConstantSequence - , viewConstantRelation - , viewConstantPartition - ) where - --- conjure -import Conjure.Prelude -import Conjure.Bug -import Conjure.Language.Name -import Conjure.Language.Domain -import Conjure.Language.Type -import Conjure.Language.AbstractLiteral - -import Conjure.Language.DomainSizeOf -import Conjure.Language.TypeOf -import Conjure.Language.AdHoc -import Conjure.Language.Pretty - --- base -import Data.Data ( toConstr, constrIndex ) - --- QuickCheck -import Test.QuickCheck ( Arbitrary(..), oneof ) - - -data Constant - = ConstantBool Bool - | ConstantInt IntTag Integer - | ConstantEnum Name {- name for the enum domain -} - [Name] {- values in the enum domain -} - Name {- the literal -} - | ConstantField Name Type -- the name of a field of Record or Variant and its type - | ConstantAbstract (AbstractLiteral Constant) - | DomainInConstant (Domain () Constant) - | TypedConstant Constant Type - | ConstantUndefined Text Type -- never use this for a bool - -- use false instead for them - deriving (Show, Data, Typeable, Generic) - -instance Eq Constant where - a == b = compare a b == EQ - --- implementing the Eq&Ord instances by hand, because we want to special case the TypedConstant constructor -instance Ord Constant where - - -- do not use type info when comparing - compare (TypedConstant a _) (TypedConstant b _) = compare a b - compare (TypedConstant a _) b = compare a b - compare a (TypedConstant b _) = compare a b - - -- the "usual" comparisons - compare (ConstantBool a) (ConstantBool b) = compare a b - compare (ConstantInt _ a) (ConstantInt _ b) = compare a b - compare (ConstantEnum _ aVals aVal) (ConstantEnum _ bVals bVal) = - compare (elemIndex aVal aVals, aVal) (elemIndex bVal bVals, bVal) - compare (ConstantField a1 a2) (ConstantField b1 b2) = compare (a1,a2) (b1,b2) - compare (ConstantAbstract a) (ConstantAbstract b) = compare a b - compare (DomainInConstant a) (DomainInConstant b) = compare a b - compare (ConstantUndefined a1 a2) (ConstantUndefined b1 b2) = compare (a1,a2) (b1,b2) - - -- if the constructors do not match - compare a b = compare (constrIndex (toConstr a)) (constrIndex (toConstr b)) - -instance Serialize Constant -instance Hashable Constant -instance ToJSON Constant where toJSON = genericToJSON jsonOptions -instance FromJSON Constant where parseJSON = genericParseJSON jsonOptions - -instance Arbitrary Constant where - arbitrary = oneof - [ ConstantBool <$> arbitrary - , ConstantInt TagInt <$> arbitrary - ] - -instance TypeOf Constant where - typeOf ConstantBool{} = return TypeBool - typeOf (ConstantInt t _) = return (TypeInt t) - typeOf (ConstantEnum defn _ _ ) = return (TypeEnum defn) - typeOf (ConstantField _ ty) = return ty - typeOf (ConstantAbstract x ) = typeOf x - typeOf (DomainInConstant dom) = typeOfDomain dom - typeOf (TypedConstant _ ty) = return ty - typeOf (ConstantUndefined _ ty) = return ty - -instance DomainSizeOf Constant Integer where - domainSizeOf DomainBool{} = return 2 - domainSizeOf (DomainIntE x) = bug ("not implemented, domainSizeOf DomainIntE" <+> pretty (show x)) - domainSizeOf (DomainInt _ rs) = domainSizeOfRanges rs - domainSizeOf DomainEnum{} = fail "domainSizeOf: Unknown for given enum." - domainSizeOf (DomainTuple ds) = product <$> mapM domainSizeOf ds - domainSizeOf (DomainMatrix index inner) = intPow <$> domainSizeOf inner <*> domainSizeOf index - domainSizeOf d@(DomainSet _ (SetAttr attrs) inner) = - case attrs of - SizeAttr_None -> do - innerSize <- domainSizeOf inner - return (2 `intPow` innerSize) - SizeAttr_Size (ConstantInt _ size) -> do - innerSize <- domainSizeOf inner - return (nchoosek (product . enumFromTo 1) innerSize size) - SizeAttr_MinSize{} -> do - -- TODO: we can do better here - innerSize <- domainSizeOf inner - return (2 `intPow` innerSize) - SizeAttr_MaxSize (ConstantInt _ maxSize) -> do - innerSize <- domainSizeOf inner - return $ sum [ nchoosek (product . enumFromTo 1) innerSize k | k <- [0 .. maxSize] ] - SizeAttr_MinMaxSize (ConstantInt _ minSize) (ConstantInt _ maxSize) -> do - innerSize <- domainSizeOf inner - return $ sum [ nchoosek (product . enumFromTo 1) innerSize k | k <- [minSize .. maxSize] ] - _ -> fail ("domainSizeOf{Constant}" <+> pretty d) - domainSizeOf DomainMSet {} = bug "not implemented: domainSizeOf DomainMSet" - domainSizeOf DomainFunction {} = bug "not implemented: domainSizeOf DomainFunction" - domainSizeOf DomainRelation {} = bug "not implemented: domainSizeOf DomainRelation" - domainSizeOf DomainPartition {} = bug "not implemented: domainSizeOf DomainPartition" - domainSizeOf _ = bug "not implemented: domainSizeOf" - -emptyCollection :: Constant -> Bool -emptyCollection ConstantBool{} = False -emptyCollection ConstantInt{} = False -emptyCollection ConstantEnum{} = False -emptyCollection ConstantField{} = False -emptyCollection (ConstantAbstract x) = emptyCollectionAbsLit x -emptyCollection DomainInConstant{} = False -emptyCollection (TypedConstant x _) = emptyCollection x -emptyCollection ConstantUndefined{} = False - -intPow :: Integer -> Integer -> Integer -intPow = (^) - -domainSizeOfRanges :: MonadFail m => [Range Constant] -> m Integer -domainSizeOfRanges = fmap genericLength . valuesInIntDomain - -instance DomainSizeOf Constant Constant where - domainSizeOf = fmap (ConstantInt TagInt) . domainSizeOf - -instance Pretty Constant where - - -- hack, oh sweet hack! - -- print a domain instead of a type when printing an empty matrix literal. - -- this means we print "int()" instead of "int" inside the index of a matrix type - -- SR expects it this way... - pretty (TypedConstant (ConstantAbstract (AbsLitMatrix _ [])) ty) = - let - pretty' (TypeMatrix index innerNested) - = "matrix indexed by" <+> prettyList prBrackets "," (map pretty' indices) - <+> "of" <+> pretty inner - where - (indices,inner) = first (index:) $ collect innerNested - collect (TypeMatrix i j) = first (i:) $ collect j - collect x = ([],x) - pretty' TypeInt{} = "int()" - pretty' t = pretty t - in - prParens $ "[] : `" <> pretty' ty <> "`" - - pretty (ConstantBool False) = "false" - pretty (ConstantBool True ) = "true" - pretty (ConstantInt _ x ) = pretty x - pretty (ConstantEnum _ _ x) = pretty x - pretty (ConstantField n _) = pretty n - pretty (ConstantAbstract x) = pretty x - pretty (DomainInConstant d) = "`" <> pretty d <> "`" - pretty (TypedConstant x ty) = prParens $ pretty x <+> ":" <+> "`" <> pretty ty <> "`" - pretty (ConstantUndefined reason ty) = "undefined" <> prParens (pretty reason <+> ":" <+> "`" <> pretty ty <> "`") - -instance ExpressionLike Constant where - fromInt = ConstantInt TagInt - fromIntWithTag i t = ConstantInt t i - intOut _ (ConstantInt _ x) = return x - intOut doc c = fail $ vcat [ "Expecting an integer, but found:" <+> pretty c - , "Called from:" <+> doc - ] - - fromBool = ConstantBool - boolOut (ConstantBool x) = return x - boolOut ConstantUndefined{} = return False - boolOut c = fail ("Expecting a boolean, but found:" <+> pretty c) - - fromList xs = ConstantAbstract $ AbsLitMatrix (mkDomainIntB 1 (fromInt $ genericLength xs)) xs - listOut (ConstantAbstract (AbsLitMatrix _ xs)) = return xs - listOut c = fail ("Expecting a matrix literal, but found:" <+> pretty c) - -instance ReferenceContainer Constant where - fromName name = bug ("ReferenceContainer{Constant} fromName --" <+> pretty name) - nameOut (ConstantField nm _) = return nm - nameOut p = bug ("ReferenceContainer{Constant} nameOut --" <+> pretty p) - -instance DomainContainer Constant (Domain ()) where - fromDomain = DomainInConstant - domainOut (DomainInConstant dom) = return dom - domainOut _ = fail "domainOut{Constant}" - -mkUndef :: Type -> Doc -> Constant -mkUndef TypeBool _ = ConstantBool False -mkUndef ty reason = ConstantUndefined (stringToText $ show reason) ty - -isUndef :: Constant -> Bool -isUndef ConstantUndefined{} = True -isUndef _ = False - -normaliseConstant :: Constant -> Constant -normaliseConstant x@ConstantBool{} = x -normaliseConstant x@ConstantInt{} = x -normaliseConstant x@ConstantEnum{} = x -normaliseConstant x@ConstantField{} = x -normaliseConstant (ConstantAbstract x) = ConstantAbstract (normaliseAbsLit normaliseConstant x) -normaliseConstant (DomainInConstant d) = DomainInConstant (normaliseDomain normaliseConstant d) -normaliseConstant (TypedConstant c ty) = TypedConstant (normaliseConstant c) ty -normaliseConstant x@ConstantUndefined{} = x - -instance Num Constant where - ConstantInt _ x + ConstantInt _ y = ConstantInt TagInt (x+y) - x + y = bug $ vcat [ "Num Constant (+)", "x:" <+> pretty x, "y:" <+> pretty y ] - ConstantInt _ x - ConstantInt _ y = ConstantInt TagInt (x-y) - x - y = bug $ vcat [ "Num Constant (-)", "x:" <+> pretty x, "y:" <+> pretty y ] - ConstantInt _ x * ConstantInt _ y = ConstantInt TagInt (x*y) - x * y = bug $ vcat [ "Num Constant (*)", "x:" <+> pretty x, "y:" <+> pretty y ] - abs (ConstantInt t x) = ConstantInt t (abs x) - abs x = bug $ vcat [ "Num Constant abs", "x:" <+> pretty x ] - signum (ConstantInt t x) = ConstantInt t (signum x) - signum x = bug $ vcat [ "Num Constant signum", "x:" <+> pretty x ] - fromInteger = ConstantInt TagInt . fromInteger - - -valuesInIntDomain :: MonadFail m => [Range Constant] -> m [Integer] -valuesInIntDomain ranges = - if isFinite - then return allValues - else fail $ "Expected finite integer ranges, but got:" <++> prettyList id "," ranges - - where - - allRanges :: [Maybe [Integer]] - allRanges = - [ vals - | r <- ranges - , let vals = case r of - RangeSingle (ConstantInt _ x) -> return [x] - RangeBounded (ConstantInt _ l) (ConstantInt _ u) -> return [l..u] - _ -> Nothing - ] - - isFinite :: Bool - isFinite = Nothing `notElem` allRanges - - allValues :: [Integer] - allValues = sortNub $ concat $ catMaybes allRanges - - -viewConstantBool :: MonadFail m => Constant -> m Bool -viewConstantBool (ConstantBool i) = return i -viewConstantBool (ConstantInt _ 0) = return False -viewConstantBool (ConstantInt _ 1) = return True -viewConstantBool constant = fail ("Expecting a boolean, but got:" <++> pretty constant) - -viewConstantInt :: MonadFail m => Constant -> m Integer -viewConstantInt (ConstantInt _ i) = return i -viewConstantInt constant = fail ("Expecting an integer, but got:" <++> pretty constant) - -viewConstantTuple :: MonadFail m => Constant -> m [Constant] -viewConstantTuple (ConstantAbstract (AbsLitTuple xs)) = return xs -viewConstantTuple (TypedConstant c _) = viewConstantTuple c -viewConstantTuple constant = fail ("Expecting a tuple, but got:" <++> pretty constant) - -viewConstantRecord :: MonadFail m => Constant -> m [(Name, Constant)] -viewConstantRecord (ConstantAbstract (AbsLitRecord xs)) = return xs -viewConstantRecord (TypedConstant c _) = viewConstantRecord c -viewConstantRecord constant = fail ("Expecting a record, but got:" <++> pretty constant) - -viewConstantVariant :: MonadFail m => Constant -> m (Maybe [(Name, Domain () Constant)], Name, Constant) -viewConstantVariant (ConstantAbstract (AbsLitVariant lu nm x)) = return (lu, nm, x) -viewConstantVariant (TypedConstant c _) = viewConstantVariant c -viewConstantVariant constant = fail ("Expecting a variant, but got:" <++> pretty constant) - -viewConstantMatrix :: MonadFail m => Constant -> m (Domain () Constant, [Constant]) -viewConstantMatrix (ConstantAbstract (AbsLitMatrix ind xs)) = return (ind, xs) -viewConstantMatrix (TypedConstant c _) = viewConstantMatrix c -viewConstantMatrix constant = fail ("Expecting a matrix, but got:" <++> pretty constant) - -viewConstantSet :: MonadFail m => Constant -> m [Constant] -viewConstantSet (ConstantAbstract (AbsLitSet xs)) = return xs -viewConstantSet (TypedConstant c _) = viewConstantSet c -viewConstantSet constant = fail ("Expecting a set, but got:" <++> pretty constant) - -viewConstantMSet :: MonadFail m => Constant -> m [Constant] -viewConstantMSet (ConstantAbstract (AbsLitMSet xs)) = return xs -viewConstantMSet (TypedConstant c _) = viewConstantMSet c -viewConstantMSet constant = fail ("Expecting an mset, but got:" <++> pretty constant) - -viewConstantFunction :: MonadFail m => Constant -> m [(Constant, Constant)] -viewConstantFunction (ConstantAbstract (AbsLitFunction xs)) = return xs -viewConstantFunction (TypedConstant c _) = viewConstantFunction c -viewConstantFunction constant = do - let - suggestion = case constant of - ConstantAbstract (AbsLitMatrix (DomainInt _ rs) vals) -> do - froms <- valuesInIntDomain rs - return $ Just $ pretty $ AbsLitFunction (zip (map (ConstantInt TagInt) froms) vals) - _ -> return Nothing - suggestion >>= \case - Nothing -> fail ("Expecting a function, but got:" <++> pretty constant) - Just sug -> fail (vcat [ "Expecting a function, but got:" <++> pretty constant - , "Maybe you meant:" <++> sug - ]) - -viewConstantSequence :: MonadFail m => Constant -> m [Constant] -viewConstantSequence (ConstantAbstract (AbsLitSequence xs)) = return xs -viewConstantSequence (TypedConstant c _) = viewConstantSequence c -viewConstantSequence constant = fail ("Expecting a sequence, but got:" <++> pretty constant) - -viewConstantRelation :: MonadFail m => Constant -> m [[Constant]] -viewConstantRelation (ConstantAbstract (AbsLitRelation xs)) = return xs -viewConstantRelation (TypedConstant c _) = viewConstantRelation c -viewConstantRelation constant = fail ("Expecting a relation, but got:" <++> pretty constant) - -viewConstantPartition :: MonadFail m => Constant -> m [[Constant]] -viewConstantPartition (ConstantAbstract (AbsLitPartition xs)) = return xs -viewConstantPartition (TypedConstant c _) = viewConstantPartition c -viewConstantPartition constant = fail ("Expecting a partition, but got:" <++> pretty constant) - diff --git a/src/Conjure/Language/Domain_BACKUP_22702.hs b/src/Conjure/Language/Domain_BACKUP_22702.hs deleted file mode 100644 index 9164000946..0000000000 --- a/src/Conjure/Language/Domain_BACKUP_22702.hs +++ /dev/null @@ -1,1079 +0,0 @@ -{-# LANGUAGE DeriveGeneric, DeriveDataTypeable, DeriveFunctor, DeriveTraversable, DeriveFoldable #-} -{-# LANGUAGE TupleSections #-} -{-# LANGUAGE NoMonomorphismRestriction #-} -{-# LANGUAGE ViewPatterns #-} - -module Conjure.Language.Domain - ( Domain(..) - , HasRepresentation(..) - , Range(..), rangesInts - , SetAttr(..), SizeAttr(..), getMaxFrom_SizeAttr - , MSetAttr(..), OccurAttr(..), getMaxFrom_OccurAttr - , FunctionAttr(..), PartialityAttr(..), JectivityAttr(..) - , SequenceAttr(..) - , RelationAttr(..), BinaryRelationAttrs(..), BinaryRelationAttr(..) - , PartitionAttr(..) - , PermutationAttr(..) - , AttrName(..) - , DomainAttributes(..), DomainAttribute(..) -- only for parsing - , textToRepresentation, representationToShortText, representationToFullText - , isPrimitiveDomain, domainCanIndexMatrix, getIndices - , Tree(..), reprTree, reprAtTopLevel, applyReprTree - , reprTreeEncoded - , forgetRepr, changeRepr, defRepr - , mkDomainBool, mkDomainInt, mkDomainIntB, mkDomainIntBTagged, mkDomainAny - , typeOfDomain - , readBinRel, binRelToAttrName - , normaliseDomain, normaliseRange - , innerDomainOf - , singletonDomainInt - , matrixNumDimsD - ) where - --- conjure -import Conjure.Prelude -import Conjure.Bug -import Conjure.Language.Name -import Conjure.Language.Type -import Conjure.Language.TypeOf -import Conjure.Language.AdHoc -import Conjure.Language.Pretty - --- base -import qualified Data.Semigroup as Semigroup ( (<>) ) - --- QuickCheck -import Test.QuickCheck ( Arbitrary(..), choose, oneof, vectorOf, sized ) - --- containers -import Data.Set as S ( Set, empty, toList, union ) - --- syb -import Data.Data ( toConstr, constrIndex ) - - -data Domain r x - = DomainAny Text Type - | DomainBool - | DomainIntE x - | DomainInt IntTag [Range x] - | DomainEnum - Name - (Maybe [Range x]) -- subset of values for this domain - -- Nothing *only* when GivenDomainDefnEnum and not LettingDomainDefnEnum - (Maybe [(Name, Integer)]) -- the mapping to integers, if available - | DomainUnnamed Name x - | DomainTuple [Domain r x] - | DomainRecord [(Name, Domain r x)] - | DomainVariant [(Name, Domain r x)] - | DomainMatrix (Domain () x) (Domain r x) - | DomainSet r (SetAttr x) (Domain r x) - | DomainMSet r (MSetAttr x) (Domain r x) - | DomainFunction r (FunctionAttr x) (Domain r x) (Domain r x) - | DomainSequence r (SequenceAttr x) (Domain r x) - | DomainRelation r (RelationAttr x) [Domain r x] - | DomainPartition r (PartitionAttr x) (Domain r x) - | DomainPermutation r (PermutationAttr x) (Domain r x) - | DomainOp Name [Domain r x] - | DomainReference Name (Maybe (Domain r x)) - | DomainMetaVar String - deriving (Eq, Ord, Show, Data, Functor, Traversable, Foldable, Typeable, Generic) - -instance (VarSymBreakingDescription x, ToJSON r) => VarSymBreakingDescription (Domain r x) where - varSymBreakingDescription domain = toJSON $ fmap varSymBreakingDescription domain - -mkDomainBool :: Domain () x -mkDomainBool = DomainBool - -mkDomainInt :: [Range x] -> Domain () x -mkDomainInt = DomainInt TagInt - -mkDomainIntB :: x -> x -> Domain () x -mkDomainIntB l u = DomainInt TagInt [RangeBounded l u] - -mkDomainIntBTagged :: IntTag -> x -> x -> Domain () x -mkDomainIntBTagged t l u = DomainInt t [RangeBounded l u] - -mkDomainAny :: Doc -> Type -> Domain r x -mkDomainAny reason = DomainAny (stringToText $ show reason) - -instance (Serialize r, Serialize x) => Serialize (Domain r x) -instance (Hashable r, Hashable x) => Hashable (Domain r x) -instance (ToJSON r, ToJSON x) => ToJSON (Domain r x) where toJSON = genericToJSON jsonOptions -instance (FromJSON r, FromJSON x) => FromJSON (Domain r x) where parseJSON = genericParseJSON jsonOptions - -instance Arbitrary x => Arbitrary (Domain r x) where - arbitrary = sized f - where - f 0 = oneof [ return DomainBool - , DomainInt TagInt <$> arbitrary - -- , DomainEnum <$> arbitrary <*> arbitrary - ] - f s = do - arity <- choose (2 :: Int, 10) - DomainTuple <$> vectorOf arity (f (div s 10)) - shrink DomainBool = [] - shrink (DomainInt _ []) = [DomainBool] - shrink (DomainInt t [r]) = DomainBool : DomainInt t [] : [DomainInt t [r'] | r' <- shrink r] - shrink (DomainInt t rs) = [DomainInt t (init rs)] - shrink _ = [] - - -typeOfDomain :: - MonadFail m => - Pretty r => - TypeOf x => - Pretty x => - (?typeCheckerMode :: TypeCheckerMode) => - Domain r x -> m Type -typeOfDomain (DomainAny _ ty) = return ty -typeOfDomain DomainBool = return TypeBool -typeOfDomain d@(DomainIntE x) = do - ty <- typeOf x - case ty of - TypeInt{} -> return () -- pre recoverDomainInt - TypeList TypeInt{} -> return () - TypeMatrix _ TypeInt{} -> return () - TypeSet TypeInt{} -> return () - _ -> fail $ vcat [ "Expected an integer, but got:" <++> pretty ty - , "In domain:" <+> pretty d - ] - return (TypeInt TagInt) -typeOfDomain d@(DomainInt t rs) = do - forM_ rs $ \ r -> forM_ r $ \ x -> do - ty <- typeOf x - case ty of - TypeInt{} -> return () - _ -> fail $ vcat [ "Expected an integer, but got:" <++> pretty ty - , "For:" <+> pretty x - , "In domain:" <+> pretty d - ] - return (TypeInt t) -typeOfDomain (DomainEnum defn _ _ ) = return (TypeEnum defn) -typeOfDomain (DomainUnnamed defn _ ) = return (TypeUnnamed defn) -typeOfDomain (DomainTuple xs ) = TypeTuple <$> mapM typeOfDomain xs -typeOfDomain (DomainRecord xs ) = TypeRecord <$> sequence [ do t <- typeOfDomain d ; return (n, t) - | (n,d) <- xs ] -typeOfDomain (DomainVariant xs ) = TypeVariant <$> sequence [ do t <- typeOfDomain d ; return (n, t) - | (n,d) <- xs ] -<<<<<<< HEAD -typeOfDomain (DomainMatrix ind inn ) = TypeMatrix <$> typeOf ind <*> typeOf inn -typeOfDomain (DomainSet _ _ x ) = TypeSet <$> typeOf x -typeOfDomain (DomainMSet _ _ x ) = TypeMSet <$> typeOf x -typeOfDomain (DomainFunction _ _ x y) = TypeFunction <$> typeOf x <*> typeOf y -typeOfDomain (DomainSequence _ _ x ) = TypeSequence <$> typeOf x -typeOfDomain (DomainRelation _ _ xs ) = TypeRelation <$> mapM typeOf xs -typeOfDomain (DomainPartition _ _ x ) = TypePartition <$> typeOf x -typeOfDomain (DomainPermutation _ _ x ) = TypePermutation <$> typeOf x -======= -typeOfDomain (DomainMatrix ind inn ) = TypeMatrix <$> typeOfDomain ind <*> typeOfDomain inn -typeOfDomain (DomainSet _ _ x ) = TypeSet <$> typeOfDomain x -typeOfDomain (DomainMSet _ _ x ) = TypeMSet <$> typeOfDomain x -typeOfDomain (DomainFunction _ _ x y) = TypeFunction <$> typeOfDomain x <*> typeOfDomain y -typeOfDomain (DomainSequence _ _ x ) = TypeSequence <$> typeOfDomain x -typeOfDomain (DomainRelation _ _ xs ) = TypeRelation <$> mapM typeOfDomain xs -typeOfDomain (DomainPartition _ _ x ) = TypePartition <$> typeOfDomain x ->>>>>>> master -typeOfDomain p@(DomainOp _ ds) = do - ts <- mapM typeOfDomain ds - if typesUnify ts - then return (mostDefined ts) - else fail ("Type error in" <+> pretty p) -typeOfDomain (DomainReference _ (Just d)) = typeOfDomain d -typeOfDomain (DomainReference nm Nothing) = bug $ "typeOfDomain: DomainReference" <+> pretty nm -typeOfDomain (DomainMetaVar nm) = bug $ "typeOfDomain: DomainMetaVar &" <> pretty nm - -forgetRepr :: Domain r x -> Domain () x -forgetRepr = defRepr - -defRepr :: Default r2 => Domain r x -> Domain r2 x -defRepr = changeRepr def - -changeRepr :: r2 -> Domain r x -> Domain r2 x -changeRepr rep = go - where - go (DomainAny t ty) = DomainAny t ty - go DomainBool = DomainBool - go (DomainIntE x) = DomainIntE x - go (DomainInt t rs) = DomainInt t rs - go (DomainEnum defn rs mp) = DomainEnum defn rs mp - go (DomainUnnamed defn s) = DomainUnnamed defn s - go (DomainTuple ds) = DomainTuple (map go ds) - go (DomainRecord xs) = DomainRecord (map (second go) xs) - go (DomainVariant xs) = DomainVariant (map (second go) xs) - go (DomainMatrix index inner) = DomainMatrix index (go inner) - go (DomainSet _ attr d) = - DomainSet rep attr (go d) - go (DomainMSet _ attr d) = - DomainMSet rep attr (go d) - go (DomainFunction _ attr d1 d2) = - DomainFunction rep attr (go d1) (go d2) - go (DomainSequence _ attr d) = - DomainSequence rep attr (go d) - go (DomainRelation _ attr ds) = - DomainRelation rep attr (map go ds) - go (DomainPartition _ attr d) = DomainPartition rep attr (go d) - go (DomainPermutation _ attr d) = DomainPermutation rep attr (go d) - go (DomainOp op ds) = DomainOp op (map go ds) - go (DomainReference x r) = DomainReference x (fmap go r) - go (DomainMetaVar x) = DomainMetaVar x - - -data Tree a = Tree { rootLabel :: a, subForest :: [Tree a] } - deriving (Eq, Ord, Show, Data, Functor, Traversable, Foldable, Typeable, Generic) - -instance Serialize a => Serialize (Tree a) -instance Hashable a => Hashable (Tree a) -instance ToJSON a => ToJSON (Tree a) where toJSON = genericToJSON jsonOptions -instance FromJSON a => FromJSON (Tree a) where parseJSON = genericParseJSON jsonOptions - --- | This is to be used when defining `Conjure.Representations.Internal.mkOutName`. --- Reason is to avoid sharing variables for parts of the same decision variable with differing representations. --- Example case: --- (1) find x : set {A} of (int(a..b) , set {B} of int(c..d)) --- (2) find x : set {A} of (int(a..b) , set {C} of int(c..d)) --- Here x_1's should not be shared! --- If they are, the channelling and symmetry breaking constraints will clash and solutions will be lost. -reprTreeEncoded :: Domain HasRepresentation x -> Text -reprTreeEncoded = mconcat . enc1 . reprTree - where - enc1 (Tree lbl sub) = - maybe - (bug "reprTreeEncoded: top-most representation is Nothing") - representationToShortText - lbl - : concatMap enc sub - enc (Tree lbl sub) = - maybe [] representationConstrIndex lbl - ++ concatMap enc sub - -reprTree :: Domain r x -> Tree (Maybe r) -reprTree DomainAny{} = Tree Nothing [] -reprTree DomainBool{} = Tree Nothing [] -reprTree DomainIntE{} = Tree Nothing [] -reprTree DomainInt{} = Tree Nothing [] -reprTree DomainEnum{} = Tree Nothing [] -reprTree DomainUnnamed{} = Tree Nothing [] -reprTree (DomainTuple as ) = Tree Nothing (map reprTree as) -reprTree (DomainRecord as ) = Tree Nothing (map (reprTree . snd) as) -reprTree (DomainVariant as) = Tree Nothing (map (reprTree . snd) as) -reprTree (DomainMatrix _ a) = Tree Nothing [reprTree a] -reprTree (DomainSet r _ a ) = Tree (Just r) [reprTree a] -reprTree (DomainMSet r _ a ) = Tree (Just r) [reprTree a] -reprTree (DomainFunction r _ a b) = Tree (Just r) [reprTree a, reprTree b] -reprTree (DomainSequence r _ a ) = Tree (Just r) [reprTree a] -reprTree (DomainRelation r _ as ) = Tree (Just r) (map reprTree as) -reprTree (DomainPartition r _ a ) = Tree (Just r) [reprTree a] -reprTree (DomainPermutation r _ a) = Tree (Just r) [reprTree a] -reprTree DomainOp{} = Tree Nothing [] -reprTree DomainReference{} = Tree Nothing [] -reprTree DomainMetaVar{} = Tree Nothing [] - -reprAtTopLevel :: Domain r x -> Maybe r -reprAtTopLevel = rootLabel . reprTree - -applyReprTree :: (MonadFail m, Pretty x, Pretty r2, Default r) => Domain r2 x -> Tree (Maybe r) -> m (Domain r x) -applyReprTree dom@DomainBool{} (Tree Nothing []) = return (defRepr dom) -applyReprTree dom@DomainInt{} (Tree Nothing []) = return (defRepr dom) -applyReprTree dom@DomainIntE{} (Tree Nothing []) = return (defRepr dom) -applyReprTree dom@DomainEnum{} (Tree Nothing []) = return (defRepr dom) -applyReprTree dom@DomainUnnamed{} (Tree Nothing []) = return (defRepr dom) -applyReprTree (DomainTuple as ) (Tree Nothing asRepr) = - DomainTuple <$> zipWithM applyReprTree as asRepr -applyReprTree (DomainRecord as ) (Tree Nothing asRepr) = - (DomainRecord . zip (map fst as)) <$> zipWithM applyReprTree (map snd as) asRepr -applyReprTree (DomainVariant as) (Tree Nothing asRepr) = - (DomainVariant . zip (map fst as)) <$> zipWithM applyReprTree (map snd as) asRepr -applyReprTree (DomainMatrix b a) (Tree Nothing [aRepr]) = DomainMatrix b <$> applyReprTree a aRepr -applyReprTree (DomainSet _ attr a ) (Tree (Just r) [aRepr]) = DomainSet r attr <$> applyReprTree a aRepr -applyReprTree (DomainMSet _ attr a ) (Tree (Just r) [aRepr]) = DomainMSet r attr <$> applyReprTree a aRepr -applyReprTree (DomainFunction _ attr a b) (Tree (Just r) [aRepr, bRepr]) = DomainFunction r attr <$> applyReprTree a aRepr <*> applyReprTree b bRepr -applyReprTree (DomainSequence _ attr a ) (Tree (Just r) [aRepr]) = DomainSequence r attr <$> applyReprTree a aRepr -applyReprTree (DomainRelation _ attr as ) (Tree (Just r) asRepr) = DomainRelation r attr <$> zipWithM applyReprTree as asRepr -applyReprTree (DomainPartition _ attr a ) (Tree (Just r) [aRepr]) = DomainPartition r attr <$> applyReprTree a aRepr -applyReprTree (DomainPermutation _ attr a ) (Tree (Just r) [aRepr]) = DomainPermutation r attr <$> applyReprTree a aRepr -applyReprTree dom@DomainOp{} (Tree Nothing []) = return (defRepr dom) -applyReprTree dom@DomainReference{} (Tree Nothing []) = return (defRepr dom) -applyReprTree dom@DomainMetaVar{} (Tree Nothing []) = return (defRepr dom) -applyReprTree dom _ = fail $ "applyReprTree:" <++> pretty dom - -isPrimitiveDomain :: Domain r x -> Bool -isPrimitiveDomain DomainBool{} = True -isPrimitiveDomain DomainIntE{} = True -isPrimitiveDomain DomainInt{} = True -isPrimitiveDomain (DomainMatrix index inner) = and [isPrimitiveDomain index, isPrimitiveDomain inner] -isPrimitiveDomain _ = False - -getIndices :: Domain r x -> ([Domain () x], Domain r x) -getIndices (DomainMatrix index inner) = first (index:) (getIndices inner) -getIndices d = ([], d) - -domainCanIndexMatrix :: Domain r x -> Bool -domainCanIndexMatrix DomainBool{} = True -domainCanIndexMatrix DomainInt {} = True -domainCanIndexMatrix DomainIntE{} = True -domainCanIndexMatrix DomainEnum{} = True -domainCanIndexMatrix _ = False - - --------------------------------------------------------------------------------- --- attribute-as-constraint handling -------------------------------------------- --------------------------------------------------------------------------------- - -data AttrName - = AttrName_size - | AttrName_minSize - | AttrName_maxSize - | AttrName_minOccur - | AttrName_maxOccur - | AttrName_numParts - | AttrName_minNumParts - | AttrName_maxNumParts - | AttrName_partSize - | AttrName_minPartSize - | AttrName_maxPartSize - | AttrName_total - | AttrName_injective - | AttrName_surjective - | AttrName_bijective - | AttrName_regular - -- bin rel ones - | AttrName_reflexive - | AttrName_irreflexive - | AttrName_coreflexive - | AttrName_symmetric - | AttrName_antiSymmetric - | AttrName_aSymmetric - | AttrName_transitive - | AttrName_connex - | AttrName_Euclidean - | AttrName_serial - | AttrName_equivalence - | AttrName_partialOrder - deriving (Eq, Ord, Show, Data, Typeable, Generic) - -instance Serialize AttrName -instance Hashable AttrName -instance ToJSON AttrName where toJSON = genericToJSON jsonOptions -instance FromJSON AttrName where parseJSON = genericParseJSON jsonOptions - -instance Pretty AttrName where - pretty AttrName_size = "size" - pretty AttrName_minSize = "minSize" - pretty AttrName_maxSize = "maxSize" - pretty AttrName_minOccur = "minOccur" - pretty AttrName_maxOccur = "maxOccur" - pretty AttrName_numParts = "numParts" - pretty AttrName_minNumParts = "minNumParts" - pretty AttrName_maxNumParts = "maxNumParts" - pretty AttrName_partSize = "partSize" - pretty AttrName_minPartSize = "minPartSize" - pretty AttrName_maxPartSize = "maxPartSize" - pretty AttrName_total = "total" - pretty AttrName_injective = "injective" - pretty AttrName_surjective = "surjective" - pretty AttrName_bijective = "bijective" - pretty AttrName_regular = "regular" - pretty AttrName_reflexive = "reflexive" - pretty AttrName_irreflexive = "irreflexive" - pretty AttrName_coreflexive = "coreflexive" - pretty AttrName_symmetric = "symmetric" - pretty AttrName_antiSymmetric = "antiSymmetric" - pretty AttrName_aSymmetric = "aSymmetric" - pretty AttrName_transitive = "transitive" - pretty AttrName_connex = "connex" - pretty AttrName_Euclidean = "Euclidean" - pretty AttrName_serial = "serial" - pretty AttrName_equivalence = "equivalence" - pretty AttrName_partialOrder = "partialOrder" - -instance IsString AttrName where - fromString "size" = AttrName_size - fromString "minSize" = AttrName_minSize - fromString "maxSize" = AttrName_maxSize - fromString "minOccur" = AttrName_minOccur - fromString "maxOccur" = AttrName_maxOccur - fromString "numParts" = AttrName_numParts - fromString "minNumParts" = AttrName_minNumParts - fromString "maxNumParts" = AttrName_maxNumParts - fromString "partSize" = AttrName_partSize - fromString "minPartSize" = AttrName_minPartSize - fromString "maxPartSize" = AttrName_maxPartSize - fromString "total" = AttrName_total - fromString "injective" = AttrName_injective - fromString "surjective" = AttrName_surjective - fromString "bijective" = AttrName_bijective - fromString "regular" = AttrName_regular - fromString "reflexive" = AttrName_reflexive - fromString "irreflexive" = AttrName_irreflexive - fromString "coreflexive" = AttrName_coreflexive - fromString "symmetric" = AttrName_symmetric - fromString "antiSymmetric" = AttrName_antiSymmetric - fromString "aSymmetric" = AttrName_aSymmetric - fromString "transitive" = AttrName_transitive - fromString "connex" = AttrName_connex - fromString "Euclidean" = AttrName_Euclidean - fromString "serial" = AttrName_serial - fromString "equivalence" = AttrName_equivalence - fromString "partialOrder" = AttrName_partialOrder - fromString s = bug $ "fromString{AttrName}:" <+> pretty s - - --------------------------------------------------------------------------------- --- attribute definitions ------------------------------------------------------- --------------------------------------------------------------------------------- - -data SetAttr a = SetAttr (SizeAttr a) - deriving (Eq, Ord, Show, Data, Functor, Traversable, Foldable, Typeable, Generic) -instance Serialize a => Serialize (SetAttr a) -instance Hashable a => Hashable (SetAttr a) -instance ToJSON a => ToJSON (SetAttr a) where toJSON = genericToJSON jsonOptions -instance FromJSON a => FromJSON (SetAttr a) where parseJSON = genericParseJSON jsonOptions -instance Default (SetAttr a) where def = SetAttr def -instance Pretty a => Pretty (SetAttr a) where - pretty (SetAttr SizeAttr_None) = prEmpty - pretty (SetAttr a) = prParens (pretty a) - - -data SizeAttr a - = SizeAttr_None - | SizeAttr_Size a - | SizeAttr_MinSize a - | SizeAttr_MaxSize a - | SizeAttr_MinMaxSize a a - deriving (Eq, Ord, Show, Data, Functor, Traversable, Foldable, Typeable, Generic) -instance Serialize a => Serialize (SizeAttr a) -instance Hashable a => Hashable (SizeAttr a) -instance ToJSON a => ToJSON (SizeAttr a) where toJSON = genericToJSON jsonOptions -instance FromJSON a => FromJSON (SizeAttr a) where parseJSON = genericParseJSON jsonOptions -instance Default (SizeAttr a) where def = SizeAttr_None -instance Pretty a => Pretty (SizeAttr a) where - pretty SizeAttr_None = prEmpty - pretty (SizeAttr_Size x ) = "size" <+> pretty x - pretty (SizeAttr_MinSize x ) = "minSize" <+> pretty x - pretty (SizeAttr_MaxSize x ) = "maxSize" <+> pretty x - pretty (SizeAttr_MinMaxSize x y) = "minSize" <+> pretty x <> ", maxSize" <+> pretty y - - -getMaxFrom_SizeAttr :: MonadFail m => SizeAttr a -> m a -getMaxFrom_SizeAttr (SizeAttr_Size n) = return n -getMaxFrom_SizeAttr (SizeAttr_MaxSize n) = return n -getMaxFrom_SizeAttr (SizeAttr_MinMaxSize _ n) = return n -getMaxFrom_SizeAttr _ = fail "getMaxFrom_SizeAttr" - - -data MSetAttr a = MSetAttr (SizeAttr a) (OccurAttr a) - deriving (Eq, Ord, Show, Data, Functor, Traversable, Foldable, Typeable, Generic) -instance Serialize a => Serialize (MSetAttr a) -instance Hashable a => Hashable (MSetAttr a) -instance ToJSON a => ToJSON (MSetAttr a) where toJSON = genericToJSON jsonOptions -instance FromJSON a => FromJSON (MSetAttr a) where parseJSON = genericParseJSON jsonOptions -instance Default (MSetAttr a) where def = MSetAttr def def -instance Pretty a => Pretty (MSetAttr a) where - pretty (MSetAttr a b) = - let inside = filter (/=prEmpty) [ pretty a - , pretty b - ] - in if null inside - then prEmpty - else prettyList prParens "," inside - - -data OccurAttr a - = OccurAttr_None - | OccurAttr_MinOccur a - | OccurAttr_MaxOccur a - | OccurAttr_MinMaxOccur a a - deriving (Eq, Ord, Show, Data, Functor, Traversable, Foldable, Typeable, Generic) -instance Serialize a => Serialize (OccurAttr a) -instance Hashable a => Hashable (OccurAttr a) -instance ToJSON a => ToJSON (OccurAttr a) where toJSON = genericToJSON jsonOptions -instance FromJSON a => FromJSON (OccurAttr a) where parseJSON = genericParseJSON jsonOptions -instance Default (OccurAttr a) where def = OccurAttr_None -instance Pretty a => Pretty (OccurAttr a) where - pretty OccurAttr_None = prEmpty - pretty (OccurAttr_MinOccur x ) = "minOccur" <+> pretty x - pretty (OccurAttr_MaxOccur x ) = "maxOccur" <+> pretty x - pretty (OccurAttr_MinMaxOccur x y) = "minOccur" <+> pretty x <> ", maxOccur" <+> pretty y - - -getMaxFrom_OccurAttr :: MonadFail m => OccurAttr a -> m a -getMaxFrom_OccurAttr (OccurAttr_MaxOccur n) = return n -getMaxFrom_OccurAttr (OccurAttr_MinMaxOccur _ n) = return n -getMaxFrom_OccurAttr _ = fail "getMaxFrom_OccurAttr" - - -data FunctionAttr x - = FunctionAttr (SizeAttr x) PartialityAttr JectivityAttr - deriving (Eq, Ord, Show, Data, Functor, Traversable, Foldable, Typeable, Generic) -instance Serialize a => Serialize (FunctionAttr a) -instance Hashable a => Hashable (FunctionAttr a) -instance ToJSON a => ToJSON (FunctionAttr a) where toJSON = genericToJSON jsonOptions -instance FromJSON a => FromJSON (FunctionAttr a) where parseJSON = genericParseJSON jsonOptions -instance Default (FunctionAttr a) where def = FunctionAttr def def def -instance Pretty a => Pretty (FunctionAttr a) where - pretty (FunctionAttr a b c) = - let inside = filter (/=prEmpty) [pretty a, pretty b, pretty c] - in if null inside - then prEmpty - else prettyList prParens "," inside - - -data PartialityAttr - = PartialityAttr_Partial - | PartialityAttr_Total - deriving (Eq, Ord, Show, Data, Typeable, Generic) -instance Serialize PartialityAttr -instance Hashable PartialityAttr -instance ToJSON PartialityAttr where toJSON = genericToJSON jsonOptions -instance FromJSON PartialityAttr where parseJSON = genericParseJSON jsonOptions -instance Default PartialityAttr where def = PartialityAttr_Partial -instance Pretty PartialityAttr where - pretty PartialityAttr_Partial = prEmpty -- partial is the default - pretty PartialityAttr_Total = "total" - - -data JectivityAttr - = JectivityAttr_None - | JectivityAttr_Injective - | JectivityAttr_Surjective - | JectivityAttr_Bijective - deriving (Eq, Ord, Show, Data, Typeable, Generic) -instance Serialize JectivityAttr -instance Hashable JectivityAttr -instance ToJSON JectivityAttr where toJSON = genericToJSON jsonOptions -instance FromJSON JectivityAttr where parseJSON = genericParseJSON jsonOptions -instance Default JectivityAttr where def = JectivityAttr_None -instance Pretty JectivityAttr where - pretty JectivityAttr_None = prEmpty - pretty JectivityAttr_Injective = "injective" - pretty JectivityAttr_Surjective = "surjective" - pretty JectivityAttr_Bijective = "bijective" - - -data SequenceAttr x - = SequenceAttr (SizeAttr x) JectivityAttr - deriving (Eq, Ord, Show, Data, Functor, Traversable, Foldable, Typeable, Generic) -instance Serialize a => Serialize (SequenceAttr a) -instance Hashable a => Hashable (SequenceAttr a) -instance ToJSON a => ToJSON (SequenceAttr a) where toJSON = genericToJSON jsonOptions -instance FromJSON a => FromJSON (SequenceAttr a) where parseJSON = genericParseJSON jsonOptions -instance Default (SequenceAttr a) where def = SequenceAttr def def -instance Pretty a => Pretty (SequenceAttr a) where - pretty (SequenceAttr a b) = - let inside = filter (/=prEmpty) [pretty a, pretty b] - in if null inside - then prEmpty - else prettyList prParens "," inside - - -data RelationAttr a = RelationAttr (SizeAttr a) BinaryRelationAttrs - deriving (Eq, Ord, Show, Data, Functor, Traversable, Foldable, Typeable, Generic) -instance Serialize a => Serialize (RelationAttr a) -instance Hashable a => Hashable (RelationAttr a) -instance ToJSON a => ToJSON (RelationAttr a) where toJSON = genericToJSON jsonOptions -instance FromJSON a => FromJSON (RelationAttr a) where parseJSON = genericParseJSON jsonOptions -instance Default (RelationAttr a) where def = RelationAttr def def -instance Pretty a => Pretty (RelationAttr a) where - pretty (RelationAttr a b) = - let inside = filter (/=prEmpty) [pretty a, pretty b] - in if null inside - then prEmpty - else prettyList prParens "," inside - - -data BinaryRelationAttrs = BinaryRelationAttrs (S.Set BinaryRelationAttr) - deriving (Eq, Ord, Show, Data, Typeable, Generic) -instance Serialize BinaryRelationAttrs -instance Hashable BinaryRelationAttrs where hashWithSalt salt (BinaryRelationAttrs a) = hashWithSalt salt (S.toList a) -instance ToJSON BinaryRelationAttrs where toJSON = genericToJSON jsonOptions -instance FromJSON BinaryRelationAttrs where parseJSON = genericParseJSON jsonOptions -instance Default BinaryRelationAttrs where def = BinaryRelationAttrs S.empty -instance Pretty BinaryRelationAttrs where - pretty (BinaryRelationAttrs attrs) = prettyList id "," (S.toList attrs) -instance Semigroup BinaryRelationAttrs where - (<>) = mappend -instance Monoid BinaryRelationAttrs where - mempty = BinaryRelationAttrs def - mappend (BinaryRelationAttrs a) (BinaryRelationAttrs b) = BinaryRelationAttrs (S.union a b) - - -data BinaryRelationAttr - = BinRelAttr_Reflexive - | BinRelAttr_Irreflexive - | BinRelAttr_Coreflexive - | BinRelAttr_Symmetric - | BinRelAttr_AntiSymmetric - | BinRelAttr_ASymmetric - | BinRelAttr_Transitive - | BinRelAttr_Total - | BinRelAttr_Connex - | BinRelAttr_Euclidean - | BinRelAttr_Serial - | BinRelAttr_Equivalence - | BinRelAttr_PartialOrder - deriving (Eq, Ord, Show, Data, Typeable, Generic) -instance Serialize BinaryRelationAttr -instance Hashable BinaryRelationAttr -instance ToJSON BinaryRelationAttr where toJSON = genericToJSON jsonOptions -instance FromJSON BinaryRelationAttr where parseJSON = genericParseJSON jsonOptions -instance Pretty BinaryRelationAttr where - pretty BinRelAttr_Reflexive = "reflexive" - pretty BinRelAttr_Irreflexive = "irreflexive" - pretty BinRelAttr_Coreflexive = "coreflexive" - pretty BinRelAttr_Symmetric = "symmetric" - pretty BinRelAttr_AntiSymmetric = "antiSymmetric" - pretty BinRelAttr_ASymmetric = "aSymmetric" - pretty BinRelAttr_Transitive = "transitive" - pretty BinRelAttr_Total = "total" - pretty BinRelAttr_Connex = "connex" - pretty BinRelAttr_Euclidean = "Euclidean" - pretty BinRelAttr_Serial = "serial" - pretty BinRelAttr_Equivalence = "equivalence" - pretty BinRelAttr_PartialOrder = "partialOrder" - -readBinRel :: MonadFail m => AttrName -> m BinaryRelationAttr -readBinRel AttrName_reflexive = return BinRelAttr_Reflexive -readBinRel AttrName_irreflexive = return BinRelAttr_Irreflexive -readBinRel AttrName_coreflexive = return BinRelAttr_Coreflexive -readBinRel AttrName_symmetric = return BinRelAttr_Symmetric -readBinRel AttrName_antiSymmetric = return BinRelAttr_AntiSymmetric -readBinRel AttrName_aSymmetric = return BinRelAttr_ASymmetric -readBinRel AttrName_transitive = return BinRelAttr_Transitive -readBinRel AttrName_total = return BinRelAttr_Total -readBinRel AttrName_connex = return BinRelAttr_Connex -readBinRel AttrName_Euclidean = return BinRelAttr_Euclidean -readBinRel AttrName_serial = return BinRelAttr_Serial -readBinRel AttrName_equivalence = return BinRelAttr_Equivalence -readBinRel AttrName_partialOrder = return BinRelAttr_PartialOrder -readBinRel a = fail $ "Not a binary relation attribute:" <+> pretty a - -binRelToAttrName :: BinaryRelationAttr -> AttrName -binRelToAttrName BinRelAttr_Reflexive = AttrName_reflexive -binRelToAttrName BinRelAttr_Irreflexive = AttrName_irreflexive -binRelToAttrName BinRelAttr_Coreflexive = AttrName_coreflexive -binRelToAttrName BinRelAttr_Symmetric = AttrName_symmetric -binRelToAttrName BinRelAttr_AntiSymmetric = AttrName_antiSymmetric -binRelToAttrName BinRelAttr_ASymmetric = AttrName_aSymmetric -binRelToAttrName BinRelAttr_Transitive = AttrName_transitive -binRelToAttrName BinRelAttr_Total = AttrName_total -binRelToAttrName BinRelAttr_Connex = AttrName_connex -binRelToAttrName BinRelAttr_Euclidean = AttrName_Euclidean -binRelToAttrName BinRelAttr_Serial = AttrName_serial -binRelToAttrName BinRelAttr_Equivalence = AttrName_equivalence -binRelToAttrName BinRelAttr_PartialOrder = AttrName_partialOrder - --- reflexive forAll x : T . rel(x,x) --- irreflexive forAll x : T . !rel(x,x) --- coreflexive forAll x,y : T . rel(x,y) -> x = y --- --- symmetric forAll x,y : T . rel(x,y) -> rel(y,x) --- antisymmetric forAll x,y : T . rel(x,y) /\ rel(y,x) -> x = y --- asymmetric forAll x,y : T . rel(x,y) -> !rel(y,x) --- --- transitive forAll x,y,z : T . rel(x,y) /\ rel(y,z) -> rel(x,z) --- --- total forAll x,y : T . rel(x,y) \/ rel(y,x) --- connex forAll x,y : T . rel(x,y) \/ rel(y,x) \/ x = y --- Euclidean forAll x,y,z : T . rel(x,y) /\ rel(x,z) -> rel(y,z) --- serial forAll x : T . exists y : T . rel(x,y) --- equivalence reflexive + symmetric + transitive --- partialOrder reflexive + antisymmetric + transitive - - -data PartitionAttr a = PartitionAttr - { partsNum :: SizeAttr a - , partsSize :: SizeAttr a - , isRegular :: Bool - } - deriving (Eq, Ord, Show, Data, Functor, Traversable, Foldable, Typeable, Generic) -instance Serialize a => Serialize (PartitionAttr a) -instance Hashable a => Hashable (PartitionAttr a) -instance ToJSON a => ToJSON (PartitionAttr a) where toJSON = genericToJSON jsonOptions -instance FromJSON a => FromJSON (PartitionAttr a) where parseJSON = genericParseJSON jsonOptions -instance Default (PartitionAttr a) where def = PartitionAttr def def False -instance Pretty a => Pretty (PartitionAttr a) where - pretty (PartitionAttr a b c) = - let inside = filter (/=prEmpty) [ prettyNum a - , prettySize b - , prettyReg c - ] - - prettyNum SizeAttr_None = prEmpty - prettyNum (SizeAttr_Size x ) = "numParts" <+> pretty x - prettyNum (SizeAttr_MinSize x ) = "minNumParts" <+> pretty x - prettyNum (SizeAttr_MaxSize x ) = "maxNumParts" <+> pretty x - prettyNum (SizeAttr_MinMaxSize x y) = "minNumParts" <+> pretty x <> ", maxNumParts" <+> pretty y - - prettySize SizeAttr_None = prEmpty - prettySize (SizeAttr_Size x ) = "partSize" <+> pretty x - prettySize (SizeAttr_MinSize x ) = "minPartSize" <+> pretty x - prettySize (SizeAttr_MaxSize x ) = "maxPartSize" <+> pretty x - prettySize (SizeAttr_MinMaxSize x y) = "minPartSize" <+> pretty x <> ", maxPartSize" <+> pretty y - - prettyReg False = prEmpty - prettyReg True = "regular" - - in if null inside - then prEmpty - else prettyList prParens "," inside - - - -data PermutationAttr x - = PermutationAttr (SizeAttr x) - deriving (Eq, Ord, Show, Data, Functor, Traversable, Foldable, Typeable, Generic) -instance Serialize a => Serialize (PermutationAttr a) -instance Hashable a => Hashable (PermutationAttr a) -instance ToJSON a => ToJSON (PermutationAttr a) where toJSON = genericToJSON jsonOptions -instance FromJSON a => FromJSON (PermutationAttr a) where parseJSON = genericParseJSON jsonOptions -instance Default (PermutationAttr a) where def = PermutationAttr def -instance Pretty a => Pretty (PermutationAttr a) where - pretty (PermutationAttr a ) = - let inside = filter (/=prEmpty) [pretty a] - in if null inside - then prEmpty - else prettyList prParens "," inside - - - - -data DomainAttributes a = DomainAttributes [DomainAttribute a] - deriving (Eq, Ord, Show, Data, Functor, Traversable, Foldable, Typeable, Generic) - -instance Serialize a => Serialize (DomainAttributes a) -instance Hashable a => Hashable (DomainAttributes a) -instance ToJSON a => ToJSON (DomainAttributes a) where toJSON = genericToJSON jsonOptions -instance FromJSON a => FromJSON (DomainAttributes a) where parseJSON = genericParseJSON jsonOptions - -instance Default (DomainAttributes a) where - def = DomainAttributes [] - - -data DomainAttribute a - = DAName Name - | DANameValue Name a - | DADotDot - deriving (Eq, Ord, Show, Data, Functor, Traversable, Foldable, Typeable, Generic) - -instance Serialize a => Serialize (DomainAttribute a) -instance Hashable a => Hashable (DomainAttribute a) -instance ToJSON a => ToJSON (DomainAttribute a) where toJSON = genericToJSON jsonOptions -instance FromJSON a => FromJSON (DomainAttribute a) where parseJSON = genericParseJSON jsonOptions - - -data Range a - = RangeOpen - | RangeSingle a - | RangeLowerBounded a - | RangeUpperBounded a - | RangeBounded a a - deriving (Eq, Ord, Show, Data, Functor, Traversable, Foldable, Typeable, Generic) - -instance Serialize a => Serialize (Range a) -instance Hashable a => Hashable (Range a) -instance ToJSON a => ToJSON (Range a) where toJSON = genericToJSON jsonOptions -instance FromJSON a => FromJSON (Range a) where parseJSON = genericParseJSON jsonOptions - -instance Arbitrary a => Arbitrary (Range a) where - arbitrary = oneof - [ return RangeOpen - , RangeSingle <$> arbitrary - , RangeLowerBounded <$> arbitrary - , RangeUpperBounded <$> arbitrary - , RangeBounded <$> arbitrary <*> arbitrary - ] - -rangesInts :: (MonadFail m, ExpressionLike c) => [Range c] -> m [Integer] -rangesInts = fmap (sortNub . concat) . mapM rangeInts - where - rangeInts (RangeSingle x) = return <$> intOut "rangeInts 1" x - rangeInts (RangeBounded x y) = do x' <- intOut "rangeInts 2" x - y' <- intOut "rangeInts 3" y - return [x' .. y'] - rangeInts _ = fail "Infinite range (or not an integer range)" - -expandRanges :: ExpressionLike c => [Range c] -> [Range c] -expandRanges r = - case rangesInts r of - Nothing -> r - Just [] -> [] - Just is -> - if [ minimum is .. maximum is ] == is - then [RangeBounded (fromInt (minimum is)) (fromInt (maximum is))] - else map (RangeSingle . fromInt) is - - -data HasRepresentation - = NoRepresentation - - | Set_Occurrence - | Set_Explicit - | Set_ExplicitVarSizeWithFlags - | Set_ExplicitVarSizeWithMarker - | Set_ExplicitVarSizeWithDummy - - | MSet_Occurrence - | MSet_ExplicitWithFlags - | MSet_ExplicitWithRepetition - - | Function_1D - | Function_1DPartial - | Function_ND - | Function_NDPartial - | Function_AsRelation HasRepresentation -- carries: representation for the inner relation - - | Sequence_ExplicitBounded - - | Relation_AsMatrix - | Relation_AsSet HasRepresentation -- carries: representation for the inner set - - | Partition_AsSet HasRepresentation HasRepresentation -- carries: representations for the inner sets - | Partition_Occurrence - | Permutation_AsFunction - - deriving (Eq, Ord, Show, Data, Typeable, Generic) - -instance Serialize HasRepresentation -instance Hashable HasRepresentation -instance ToJSON HasRepresentation where toJSON = genericToJSON jsonOptions -instance FromJSON HasRepresentation where parseJSON = genericParseJSON jsonOptions - -instance Default HasRepresentation where - def = NoRepresentation - -representationConstrIndex :: HasRepresentation -> [Text] -representationConstrIndex r = oneLevel r : concatMap representationConstrIndex (children r) - where - oneLevel :: HasRepresentation -> Text - oneLevel = stringToText . ("R"++) . show . constrIndex . toConstr - -instance (Pretty r, Pretty a) => Pretty (Domain r a) where - - pretty DomainAny{} = "?" - - pretty DomainBool = "bool" - - pretty (DomainIntE x) = "int" <> prParens (pretty x) - - pretty (DomainInt (TagEnum nm) _) = pretty nm - pretty (DomainInt (TagUnnamed nm) _) = pretty nm - - pretty (DomainInt _ []) = "int" -<<<<<<< HEAD - - pretty (DomainInt _ ranges) = "int" <> prettyList prParens "," ranges - -======= - pretty (DomainInt _ ranges) = "int" <> prettyList prParens "," ranges - ->>>>>>> master - pretty (DomainEnum name (Just ranges) _) = pretty name <> prettyList prParens "," ranges - - pretty (DomainEnum name _ _) = pretty name - - pretty (DomainUnnamed name _) = pretty name - - pretty (DomainTuple inners) - = (if length inners < 2 then "tuple" else prEmpty) - <+> prettyList prParens "," inners - - pretty (DomainRecord xs) = "record" <+> prettyList prBraces "," - [ pretty nm <+> ":" <+> pretty d | (nm, d) <- xs ] - - pretty (DomainVariant xs) = "variant" <+> prettyList prBraces "," - [ pretty nm <+> ":" <+> pretty d | (nm, d) <- xs ] - - pretty (DomainMatrix index innerNested) - = "matrix indexed by" <+> prettyList prBrackets "," indices - <+> "of" <+> pretty inner - where - (indices,inner) = first (index:) $ collect innerNested - collect (DomainMatrix i j) = first (i:) $ collect j - collect x = ([],x) - - pretty (DomainSet r attrs inner) = - hang ("set" <+> prettyAttrs r attrs <+> "of") 4 (pretty inner) - - pretty (DomainMSet r attrs inner) = - hang ("mset" <+> prettyAttrs r attrs <+> "of") 4 (pretty inner) - - pretty (DomainFunction r attrs innerFrom innerTo) = - hang ("function" <+> prettyAttrs r attrs) 4 $ - hang (pretty innerFrom) 4 $ - "-->" <+> pretty innerTo - - pretty (DomainSequence r attrs inner) = - hang ("sequence" <+> prettyAttrs r attrs <+> "of") 4 (pretty inner) - - pretty (DomainRelation r attrs inners) - = hang ("relation" <+> prettyAttrs r attrs <+> "of") 4 (prettyList prParens " *" inners) - - pretty (DomainPartition r attrs inner) - = hang ("partition" <+> prettyAttrs r attrs <+> "from") 4 (pretty inner) - pretty (DomainPermutation r attrs inner) = hang ("permutation" <+> prettyAttrs r attrs <+> "of") 4 (pretty inner) - - pretty d@DomainOp{} = pretty (show d) - - pretty (DomainReference x _) = pretty x - - pretty (DomainMetaVar x) = "&" <> pretty x - - -prettyAttrs :: (Pretty a, Pretty b) => a -> b -> Doc -prettyAttrs a bs = - let prettya = pretty a - in if prettya == "()" - then pretty bs - else prBraces prettya <+> pretty bs - -instance Pretty a => Pretty (DomainAttributes a) where - pretty (DomainAttributes []) = prEmpty - pretty (DomainAttributes attrs) = prettyList prParens "," attrs - -instance Pretty a => Pretty (DomainAttribute a) where - pretty (DAName name) = pretty name - pretty (DANameValue name value) = pretty name <+> pretty value - pretty DADotDot = ".." - -instance Pretty a => Pretty (Range a) where - pretty RangeOpen = ".." - pretty (RangeSingle x) = pretty x - pretty (RangeLowerBounded x) = pretty x <> ".." - pretty (RangeUpperBounded x) = ".." <> pretty x - pretty (RangeBounded x y) | show (pretty x) == show (pretty y) = pretty x - pretty (RangeBounded x y) = pretty x <> ".." <> pretty y - -instance Pretty HasRepresentation where - pretty NoRepresentation = "∅" - pretty r = pretty (representationToFullText r) - -textToRepresentation :: Text -> [HasRepresentation] -> Maybe HasRepresentation -textToRepresentation t [] | t == "Occurrence" = return Set_Occurrence -textToRepresentation t [] | t == "Explicit" = return Set_Explicit -textToRepresentation t [] | t == "ExplicitVarSizeWithFlags" = return Set_ExplicitVarSizeWithFlags -textToRepresentation t [] | t == "ExplicitVarSizeWithMarker" = return Set_ExplicitVarSizeWithMarker -textToRepresentation t [] | t == "ExplicitVarSizeWithDummy" = return Set_ExplicitVarSizeWithDummy -textToRepresentation t [] | t == "MOccurrence" = return MSet_Occurrence -textToRepresentation t [] | t == "ExplicitWithFlags" = return MSet_ExplicitWithFlags -textToRepresentation t [] | t == "ExplicitWithRepetition" = return MSet_ExplicitWithRepetition -textToRepresentation t [] | t == "Function1D" = return Function_1D -textToRepresentation t [] | t == "Function1DPartial" = return Function_1DPartial -textToRepresentation t [] | t == "FunctionND" = return Function_ND -textToRepresentation t [] | t == "FunctionNDPartial" = return Function_NDPartial -textToRepresentation t [repr] | t == "FunctionAsRelation" = return (Function_AsRelation repr) -textToRepresentation t [] | t == "ExplicitBounded" = return Sequence_ExplicitBounded -textToRepresentation t [] | t == "RelationAsMatrix" = return Relation_AsMatrix -textToRepresentation t [repr] | t == "RelationAsSet" = return (Relation_AsSet repr) -textToRepresentation t [repr1, repr2] | t == "PartitionAsSet" = return (Partition_AsSet repr1 repr2) -textToRepresentation t [] | t == "PartitionOccurrence" = return Partition_Occurrence -<<<<<<< HEAD -textToRepresentation t [] | t == "PermutationAsFunction" = return Permutation_AsFunction -textToRepresentation t _ = bug ("textToRepresentation:" <+> pretty t) -======= -textToRepresentation _ _ = Nothing ->>>>>>> master - -representationToShortText :: HasRepresentation -> Text -representationToShortText Set_Occurrence = "Occurrence" -representationToShortText Set_Explicit = "Explicit" -representationToShortText Set_ExplicitVarSizeWithFlags = "ExplicitVarSizeWithFlags" -representationToShortText Set_ExplicitVarSizeWithMarker = "ExplicitVarSizeWithMarker" -representationToShortText Set_ExplicitVarSizeWithDummy = "ExplicitVarSizeWithDummy" -representationToShortText MSet_Occurrence = "MOccurrence" -representationToShortText MSet_ExplicitWithFlags = "ExplicitWithFlags" -representationToShortText MSet_ExplicitWithRepetition = "ExplicitWithRepetition" -representationToShortText Function_1D = "Function1D" -representationToShortText Function_1DPartial = "Function1DPartial" -representationToShortText Function_ND = "FunctionND" -representationToShortText Function_NDPartial = "FunctionNDPartial" -representationToShortText Function_AsRelation{} = "FunctionAsRelation" -representationToShortText Sequence_ExplicitBounded = "ExplicitBounded" -representationToShortText Relation_AsMatrix = "RelationAsMatrix" -representationToShortText Relation_AsSet{} = "RelationAsSet" -representationToShortText Partition_AsSet{} = "PartitionAsSet" -representationToShortText Partition_Occurrence = "PartitionOccurrence" -representationToShortText Permutation_AsFunction = "PermutationAsFunction" -representationToShortText r = bug ("representationToShortText:" <+> pretty (show r)) - -representationToFullText :: HasRepresentation -> Text -representationToFullText (Function_AsRelation repr) = mconcat [ "FunctionAsRelation" - , "[" - , representationToFullText repr - , "]" - ] -representationToFullText (Relation_AsSet repr) = mconcat [ "RelationAsSet" - , "[" - , representationToFullText repr - , "]" - ] -representationToFullText (Partition_AsSet repr1 repr2) = mconcat [ "PartitionAsSet" - , "[" - , representationToFullText repr1 - , "," - , representationToFullText repr2 - , "]" - ] -representationToFullText r = representationToShortText r - - -normaliseDomain :: (Ord c, ExpressionLike c) => (c -> c) -> Domain r c -> Domain r c -normaliseDomain _norm DomainBool = DomainBool -normaliseDomain norm (DomainInt t rs ) = DomainInt t $ sort $ map (normaliseRange norm) (expandRanges rs) -normaliseDomain _norm (DomainEnum n Nothing mp) = DomainEnum n Nothing mp -normaliseDomain _norm (DomainEnum n (Just rs) mp) = DomainEnum n (Just $ sort rs) mp -normaliseDomain norm (DomainUnnamed n x ) = DomainUnnamed n (norm x) -normaliseDomain norm (DomainRecord doms ) = DomainRecord [ (n, normaliseDomain norm d) - | (n, d) <- doms ] -normaliseDomain norm (DomainVariant doms ) = DomainVariant [ (n, normaliseDomain norm d) - | (n, d) <- doms ] -normaliseDomain norm (DomainTuple doms ) = DomainTuple $ map (normaliseDomain norm) doms -normaliseDomain norm (DomainMatrix dom1 dom2) = DomainMatrix (normaliseDomain norm dom1) - (normaliseDomain norm dom2) -normaliseDomain norm (DomainSet r attr dom ) = DomainSet r (fmap norm attr) - (normaliseDomain norm dom) -normaliseDomain norm (DomainMSet r attr dom ) = DomainMSet r (fmap norm attr) - (normaliseDomain norm dom) -normaliseDomain norm (DomainFunction r attr dom1 dom2) = DomainFunction r (fmap norm attr) - (normaliseDomain norm dom1) - (normaliseDomain norm dom2) -normaliseDomain norm (DomainSequence r attr dom ) = DomainSequence r (fmap norm attr) - (normaliseDomain norm dom) -normaliseDomain norm (DomainRelation r attr doms ) = DomainRelation r (fmap norm attr) - (map (normaliseDomain norm) doms) -normaliseDomain norm (DomainPartition r attr dom ) = DomainPartition r (fmap norm attr) - (normaliseDomain norm dom) -normaliseDomain _norm d = d - -normaliseRange :: (c -> c) -> Range c -> Range c -normaliseRange _norm RangeOpen = RangeOpen -normaliseRange norm (RangeSingle x) = RangeBounded (norm x) (norm x) -normaliseRange norm (RangeLowerBounded x) = RangeLowerBounded (norm x) -normaliseRange norm (RangeUpperBounded x) = RangeUpperBounded (norm x) -normaliseRange norm (RangeBounded x y) = RangeBounded (norm x) (norm y) - -innerDomainOf :: (MonadFail m, Show x) => Domain () x -> m (Domain () x) -innerDomainOf (DomainMatrix _ t) = return t -innerDomainOf (DomainSet _ _ t) = return t -innerDomainOf (DomainMSet _ _ t) = return t -innerDomainOf (DomainFunction _ _ a b) = return (DomainTuple [a,b]) -innerDomainOf (DomainRelation _ _ ts) = return (DomainTuple ts) -innerDomainOf (DomainPartition _ _ t) = return (DomainSet () def t) -innerDomainOf t = fail ("innerDomainOf:" <+> pretty (show t)) - -singletonDomainInt :: (Eq x, CanBeAnAlias x) => Domain r x -> Maybe x -singletonDomainInt (DomainInt _ [RangeSingle a]) = Just a -singletonDomainInt (DomainInt _ [RangeBounded a b]) = - let - followAlias (isAlias -> Just x) = followAlias x - followAlias x = x - in - if followAlias a == followAlias b - then Just a - else Nothing -singletonDomainInt _ = Nothing - -matrixNumDimsD :: Domain r x -> Int -matrixNumDimsD (DomainMatrix _ t) = 1 + matrixNumDimsD t -matrixNumDimsD _ = 0 - diff --git a/src/Conjure/Language/Domain_BASE_22702.hs b/src/Conjure/Language/Domain_BASE_22702.hs deleted file mode 100644 index c3ad69408c..0000000000 --- a/src/Conjure/Language/Domain_BASE_22702.hs +++ /dev/null @@ -1,1013 +0,0 @@ -{-# LANGUAGE DeriveGeneric, DeriveDataTypeable, DeriveFunctor, DeriveTraversable, DeriveFoldable #-} -{-# LANGUAGE TupleSections #-} -{-# LANGUAGE NoMonomorphismRestriction #-} -{-# LANGUAGE ViewPatterns #-} - -module Conjure.Language.Domain - ( Domain(..) - , HasRepresentation(..) - , Range(..), rangesInts - , SetAttr(..), SizeAttr(..), getMaxFrom_SizeAttr - , MSetAttr(..), OccurAttr(..), getMaxFrom_OccurAttr - , FunctionAttr(..), PartialityAttr(..), JectivityAttr(..) - , SequenceAttr(..) - , RelationAttr(..), BinaryRelationAttrs(..), BinaryRelationAttr(..) - , PartitionAttr(..) - , AttrName(..) - , DomainAttributes(..), DomainAttribute(..) -- only for parsing - , textToRepresentation, representationToShortText, representationToFullText - , isPrimitiveDomain, domainCanIndexMatrix, getIndices - , Tree(..), reprTree, reprAtTopLevel, applyReprTree - , reprTreeEncoded - , forgetRepr, changeRepr, defRepr - , mkDomainBool, mkDomainInt, mkDomainIntB, mkDomainIntBTagged, mkDomainAny - , typeOfDomain - , readBinRel - , normaliseDomain, normaliseRange - , innerDomainOf - , singletonDomainInt - , matrixNumDimsD - ) where - --- conjure -import Conjure.Prelude -import Conjure.Bug -import Conjure.Language.Name -import Conjure.Language.Type -import Conjure.Language.TypeOf -import Conjure.Language.AdHoc -import Conjure.Language.Pretty - --- base -import qualified Data.Semigroup as Semigroup ( (<>) ) - --- QuickCheck -import Test.QuickCheck ( Arbitrary(..), choose, oneof, vectorOf, sized ) - --- containers -import Data.Set as S ( Set, empty, toList, union ) - --- syb -import Data.Data ( toConstr, constrIndex ) - - -data Domain r x - = DomainAny Text Type - | DomainBool - | DomainIntE x - | DomainInt IntTag [Range x] - | DomainEnum - Name - (Maybe [Range x]) -- subset of values for this domain - -- Nothing *only* when GivenDomainDefnEnum and not LettingDomainDefnEnum - (Maybe [(Name, Integer)]) -- the mapping to integers, if available - | DomainUnnamed Name x - | DomainTuple [Domain r x] - | DomainRecord [(Name, Domain r x)] - | DomainVariant [(Name, Domain r x)] - | DomainMatrix (Domain () x) (Domain r x) - | DomainSet r (SetAttr x) (Domain r x) - | DomainMSet r (MSetAttr x) (Domain r x) - | DomainFunction r (FunctionAttr x) (Domain r x) (Domain r x) - | DomainSequence r (SequenceAttr x) (Domain r x) - | DomainRelation r (RelationAttr x) [Domain r x] - | DomainPartition r (PartitionAttr x) (Domain r x) - | DomainOp Name [Domain r x] - | DomainReference Name (Maybe (Domain r x)) - | DomainMetaVar String - deriving (Eq, Ord, Show, Data, Functor, Traversable, Foldable, Typeable, Generic) - -instance (VarSymBreakingDescription x, ToJSON r) => VarSymBreakingDescription (Domain r x) where - varSymBreakingDescription domain = toJSON $ fmap varSymBreakingDescription domain - -mkDomainBool :: Domain () x -mkDomainBool = DomainBool - -mkDomainInt :: [Range x] -> Domain () x -mkDomainInt = DomainInt TagInt - -mkDomainIntB :: x -> x -> Domain () x -mkDomainIntB l u = DomainInt TagInt [RangeBounded l u] - -mkDomainIntBTagged :: IntTag -> x -> x -> Domain () x -mkDomainIntBTagged t l u = DomainInt t [RangeBounded l u] - -mkDomainAny :: Doc -> Type -> Domain r x -mkDomainAny reason = DomainAny (stringToText $ show reason) - -instance (Serialize r, Serialize x) => Serialize (Domain r x) -instance (Hashable r, Hashable x) => Hashable (Domain r x) -instance (ToJSON r, ToJSON x) => ToJSON (Domain r x) where toJSON = genericToJSON jsonOptions -instance (FromJSON r, FromJSON x) => FromJSON (Domain r x) where parseJSON = genericParseJSON jsonOptions - -instance Arbitrary x => Arbitrary (Domain r x) where - arbitrary = sized f - where - f 0 = oneof [ return DomainBool - , DomainInt TagInt <$> arbitrary - -- , DomainEnum <$> arbitrary <*> arbitrary - ] - f s = do - arity <- choose (2 :: Int, 10) - DomainTuple <$> vectorOf arity (f (div s 10)) - shrink DomainBool = [] - shrink (DomainInt _ []) = [DomainBool] - shrink (DomainInt t [r]) = DomainBool : DomainInt t [] : [DomainInt t [r'] | r' <- shrink r] - shrink (DomainInt t rs) = [DomainInt t (init rs)] - shrink _ = [] - -instance (Pretty r, TypeOf x, Pretty x) => TypeOf (Domain r x) where - typeOf = typeOfDomain - -typeOfDomain :: - MonadFail m => - Pretty r => - TypeOf x => - Pretty x => - (?typeCheckerMode :: TypeCheckerMode) => - Domain r x -> m Type -typeOfDomain (DomainAny _ ty) = return ty -typeOfDomain DomainBool = return TypeBool -typeOfDomain d@(DomainIntE x) = do - ty <- typeOf x - case ty of - TypeInt{} -> return () -- pre recoverDomainInt - TypeList TypeInt{} -> return () - TypeMatrix _ TypeInt{} -> return () - TypeSet TypeInt{} -> return () - _ -> fail $ vcat [ "Expected an integer, but got:" <++> pretty ty - , "In domain:" <+> pretty d - ] - return (TypeInt TagInt) -typeOfDomain d@(DomainInt t rs) = do - forM_ rs $ \ r -> forM_ r $ \ x -> do - ty <- typeOf x - case ty of - TypeInt{} -> return () - _ -> fail $ vcat [ "Expected an integer, but got:" <++> pretty ty - , "For:" <+> pretty x - , "In domain:" <+> pretty d - ] - return (TypeInt t) -typeOfDomain (DomainEnum defn _ _ ) = return (TypeEnum defn) -typeOfDomain (DomainUnnamed defn _ ) = return (TypeUnnamed defn) -typeOfDomain (DomainTuple xs ) = TypeTuple <$> mapM typeOf xs -typeOfDomain (DomainRecord xs ) = TypeRecord <$> sequence [ do t <- typeOf d ; return (n, t) - | (n,d) <- xs ] -typeOfDomain (DomainVariant xs ) = TypeVariant <$> sequence [ do t <- typeOf d ; return (n, t) - | (n,d) <- xs ] -typeOfDomain (DomainMatrix ind inn ) = TypeMatrix <$> typeOf ind <*> typeOf inn -typeOfDomain (DomainSet _ _ x ) = TypeSet <$> typeOf x -typeOfDomain (DomainMSet _ _ x ) = TypeMSet <$> typeOf x -typeOfDomain (DomainFunction _ _ x y) = TypeFunction <$> typeOf x <*> typeOf y -typeOfDomain (DomainSequence _ _ x ) = TypeSequence <$> typeOf x -typeOfDomain (DomainRelation _ _ xs ) = TypeRelation <$> mapM typeOf xs -typeOfDomain (DomainPartition _ _ x ) = TypePartition <$> typeOf x -typeOfDomain p@(DomainOp _ ds) = do - ts <- mapM typeOfDomain ds - if typesUnify ts - then return (mostDefined ts) - else fail ("Type error in" <+> pretty p) -typeOfDomain (DomainReference _ (Just d)) = typeOf d -typeOfDomain (DomainReference nm Nothing) = bug $ "typeOf: DomainReference" <+> pretty nm -typeOfDomain (DomainMetaVar nm) = bug $ "typeOf: DomainMetaVar &" <> pretty nm - -forgetRepr :: Domain r x -> Domain () x -forgetRepr = defRepr - -defRepr :: Default r2 => Domain r x -> Domain r2 x -defRepr = changeRepr def - -changeRepr :: r2 -> Domain r x -> Domain r2 x -changeRepr rep = go - where - go (DomainAny t ty) = DomainAny t ty - go DomainBool = DomainBool - go (DomainIntE x) = DomainIntE x - go (DomainInt t rs) = DomainInt t rs - go (DomainEnum defn rs mp) = DomainEnum defn rs mp - go (DomainUnnamed defn s) = DomainUnnamed defn s - go (DomainTuple ds) = DomainTuple (map go ds) - go (DomainRecord xs) = DomainRecord (map (second go) xs) - go (DomainVariant xs) = DomainVariant (map (second go) xs) - go (DomainMatrix index inner) = DomainMatrix index (go inner) - go (DomainSet _ attr d) = - DomainSet rep attr (go d) - go (DomainMSet _ attr d) = - DomainMSet rep attr (go d) - go (DomainFunction _ attr d1 d2) = - DomainFunction rep attr (go d1) (go d2) - go (DomainSequence _ attr d) = - DomainSequence rep attr (go d) - go (DomainRelation _ attr ds) = - DomainRelation rep attr (map go ds) - go (DomainPartition _ attr d) = - DomainPartition rep attr (go d) - go (DomainOp op ds) = DomainOp op (map go ds) - go (DomainReference x r) = DomainReference x (fmap go r) - go (DomainMetaVar x) = DomainMetaVar x - - -data Tree a = Tree { rootLabel :: a, subForest :: [Tree a] } - deriving (Eq, Ord, Show, Data, Functor, Traversable, Foldable, Typeable, Generic) - -instance Serialize a => Serialize (Tree a) -instance Hashable a => Hashable (Tree a) -instance ToJSON a => ToJSON (Tree a) where toJSON = genericToJSON jsonOptions -instance FromJSON a => FromJSON (Tree a) where parseJSON = genericParseJSON jsonOptions - --- | This is to be used when defining `Conjure.Representations.Internal.mkOutName`. --- Reason is to avoid sharing variables for parts of the same decision variable with differing representations. --- Example case: --- (1) find x : set {A} of (int(a..b) , set {B} of int(c..d)) --- (2) find x : set {A} of (int(a..b) , set {C} of int(c..d)) --- Here x_1's should not be shared! --- If they are, the channelling and symmetry breaking constraints will clash and solutions will be lost. -reprTreeEncoded :: Domain HasRepresentation x -> Text -reprTreeEncoded = mconcat . enc1 . reprTree - where - enc1 (Tree lbl sub) = - maybe - (bug "reprTreeEncoded: top-most representation is Nothing") - representationToShortText - lbl - : concatMap enc sub - enc (Tree lbl sub) = - maybe [] representationConstrIndex lbl - ++ concatMap enc sub - -reprTree :: Domain r x -> Tree (Maybe r) -reprTree DomainAny{} = Tree Nothing [] -reprTree DomainBool{} = Tree Nothing [] -reprTree DomainIntE{} = Tree Nothing [] -reprTree DomainInt{} = Tree Nothing [] -reprTree DomainEnum{} = Tree Nothing [] -reprTree DomainUnnamed{} = Tree Nothing [] -reprTree (DomainTuple as ) = Tree Nothing (map reprTree as) -reprTree (DomainRecord as ) = Tree Nothing (map (reprTree . snd) as) -reprTree (DomainVariant as) = Tree Nothing (map (reprTree . snd) as) -reprTree (DomainMatrix _ a) = Tree Nothing [reprTree a] -reprTree (DomainSet r _ a ) = Tree (Just r) [reprTree a] -reprTree (DomainMSet r _ a ) = Tree (Just r) [reprTree a] -reprTree (DomainFunction r _ a b) = Tree (Just r) [reprTree a, reprTree b] -reprTree (DomainSequence r _ a ) = Tree (Just r) [reprTree a] -reprTree (DomainRelation r _ as ) = Tree (Just r) (map reprTree as) -reprTree (DomainPartition r _ a ) = Tree (Just r) [reprTree a] -reprTree DomainOp{} = Tree Nothing [] -reprTree DomainReference{} = Tree Nothing [] -reprTree DomainMetaVar{} = Tree Nothing [] - -reprAtTopLevel :: Domain r x -> Maybe r -reprAtTopLevel = rootLabel . reprTree - -applyReprTree :: (MonadFail m, Pretty x, Pretty r2, Default r) => Domain r2 x -> Tree (Maybe r) -> m (Domain r x) -applyReprTree dom@DomainBool{} (Tree Nothing []) = return (defRepr dom) -applyReprTree dom@DomainInt{} (Tree Nothing []) = return (defRepr dom) -applyReprTree dom@DomainIntE{} (Tree Nothing []) = return (defRepr dom) -applyReprTree dom@DomainEnum{} (Tree Nothing []) = return (defRepr dom) -applyReprTree dom@DomainUnnamed{} (Tree Nothing []) = return (defRepr dom) -applyReprTree (DomainTuple as ) (Tree Nothing asRepr) = - DomainTuple <$> zipWithM applyReprTree as asRepr -applyReprTree (DomainRecord as ) (Tree Nothing asRepr) = - (DomainRecord . zip (map fst as)) <$> zipWithM applyReprTree (map snd as) asRepr -applyReprTree (DomainVariant as) (Tree Nothing asRepr) = - (DomainVariant . zip (map fst as)) <$> zipWithM applyReprTree (map snd as) asRepr -applyReprTree (DomainMatrix b a) (Tree Nothing [aRepr]) = DomainMatrix b <$> applyReprTree a aRepr -applyReprTree (DomainSet _ attr a ) (Tree (Just r) [aRepr]) = DomainSet r attr <$> applyReprTree a aRepr -applyReprTree (DomainMSet _ attr a ) (Tree (Just r) [aRepr]) = DomainMSet r attr <$> applyReprTree a aRepr -applyReprTree (DomainFunction _ attr a b) (Tree (Just r) [aRepr, bRepr]) = DomainFunction r attr <$> applyReprTree a aRepr <*> applyReprTree b bRepr -applyReprTree (DomainSequence _ attr a ) (Tree (Just r) [aRepr]) = DomainSequence r attr <$> applyReprTree a aRepr -applyReprTree (DomainRelation _ attr as ) (Tree (Just r) asRepr) = DomainRelation r attr <$> zipWithM applyReprTree as asRepr -applyReprTree (DomainPartition _ attr a ) (Tree (Just r) [aRepr]) = DomainPartition r attr <$> applyReprTree a aRepr -applyReprTree dom@DomainOp{} (Tree Nothing []) = return (defRepr dom) -applyReprTree dom@DomainReference{} (Tree Nothing []) = return (defRepr dom) -applyReprTree dom@DomainMetaVar{} (Tree Nothing []) = return (defRepr dom) -applyReprTree dom _ = fail $ "applyReprTree:" <++> pretty dom - -isPrimitiveDomain :: Domain r x -> Bool -isPrimitiveDomain DomainBool{} = True -isPrimitiveDomain DomainIntE{} = True -isPrimitiveDomain DomainInt{} = True -isPrimitiveDomain (DomainMatrix index inner) = and [isPrimitiveDomain index, isPrimitiveDomain inner] -isPrimitiveDomain _ = False - -getIndices :: Domain r x -> ([Domain () x], Domain r x) -getIndices (DomainMatrix index inner) = first (index:) (getIndices inner) -getIndices d = ([], d) - -domainCanIndexMatrix :: Domain r x -> Bool -domainCanIndexMatrix DomainBool{} = True -domainCanIndexMatrix DomainInt {} = True -domainCanIndexMatrix DomainIntE{} = True -domainCanIndexMatrix DomainEnum{} = True -domainCanIndexMatrix _ = False - - --------------------------------------------------------------------------------- --- attribute-as-constraint handling -------------------------------------------- --------------------------------------------------------------------------------- - -data AttrName - = AttrName_size - | AttrName_minSize - | AttrName_maxSize - | AttrName_minOccur - | AttrName_maxOccur - | AttrName_numParts - | AttrName_minNumParts - | AttrName_maxNumParts - | AttrName_partSize - | AttrName_minPartSize - | AttrName_maxPartSize - | AttrName_total - | AttrName_injective - | AttrName_surjective - | AttrName_bijective - | AttrName_regular - -- bin rel ones - | AttrName_reflexive - | AttrName_irreflexive - | AttrName_coreflexive - | AttrName_symmetric - | AttrName_antiSymmetric - | AttrName_aSymmetric - | AttrName_transitive - | AttrName_connex - | AttrName_Euclidean - | AttrName_serial - | AttrName_equivalence - | AttrName_partialOrder - deriving (Eq, Ord, Show, Data, Typeable, Generic) - -instance Serialize AttrName -instance Hashable AttrName -instance ToJSON AttrName where toJSON = genericToJSON jsonOptions -instance FromJSON AttrName where parseJSON = genericParseJSON jsonOptions - -instance Pretty AttrName where - pretty AttrName_size = "size" - pretty AttrName_minSize = "minSize" - pretty AttrName_maxSize = "maxSize" - pretty AttrName_minOccur = "minOccur" - pretty AttrName_maxOccur = "maxOccur" - pretty AttrName_numParts = "numParts" - pretty AttrName_minNumParts = "minNumParts" - pretty AttrName_maxNumParts = "maxNumParts" - pretty AttrName_partSize = "partSize" - pretty AttrName_minPartSize = "minPartSize" - pretty AttrName_maxPartSize = "maxPartSize" - pretty AttrName_total = "total" - pretty AttrName_injective = "injective" - pretty AttrName_surjective = "surjective" - pretty AttrName_bijective = "bijective" - pretty AttrName_regular = "regular" - pretty AttrName_reflexive = "reflexive" - pretty AttrName_irreflexive = "irreflexive" - pretty AttrName_coreflexive = "coreflexive" - pretty AttrName_symmetric = "symmetric" - pretty AttrName_antiSymmetric = "antiSymmetric" - pretty AttrName_aSymmetric = "aSymmetric" - pretty AttrName_transitive = "transitive" - pretty AttrName_connex = "connex" - pretty AttrName_Euclidean = "Euclidean" - pretty AttrName_serial = "serial" - pretty AttrName_equivalence = "equivalence" - pretty AttrName_partialOrder = "partialOrder" - -instance IsString AttrName where - fromString "size" = AttrName_size - fromString "minSize" = AttrName_minSize - fromString "maxSize" = AttrName_maxSize - fromString "minOccur" = AttrName_minOccur - fromString "maxOccur" = AttrName_maxOccur - fromString "numParts" = AttrName_numParts - fromString "minNumParts" = AttrName_minNumParts - fromString "maxNumParts" = AttrName_maxNumParts - fromString "partSize" = AttrName_partSize - fromString "minPartSize" = AttrName_minPartSize - fromString "maxPartSize" = AttrName_maxPartSize - fromString "total" = AttrName_total - fromString "injective" = AttrName_injective - fromString "surjective" = AttrName_surjective - fromString "bijective" = AttrName_bijective - fromString "regular" = AttrName_regular - fromString "reflexive" = AttrName_reflexive - fromString "irreflexive" = AttrName_irreflexive - fromString "coreflexive" = AttrName_coreflexive - fromString "symmetric" = AttrName_symmetric - fromString "antiSymmetric" = AttrName_antiSymmetric - fromString "aSymmetric" = AttrName_aSymmetric - fromString "transitive" = AttrName_transitive - fromString "connex" = AttrName_connex - fromString "Euclidean" = AttrName_Euclidean - fromString "serial" = AttrName_serial - fromString "equivalence" = AttrName_equivalence - fromString "partialOrder" = AttrName_partialOrder - fromString s = bug $ "fromString{AttrName}:" <+> pretty s - - --------------------------------------------------------------------------------- --- attribute definitions ------------------------------------------------------- --------------------------------------------------------------------------------- - -data SetAttr a = SetAttr (SizeAttr a) - deriving (Eq, Ord, Show, Data, Functor, Traversable, Foldable, Typeable, Generic) -instance Serialize a => Serialize (SetAttr a) -instance Hashable a => Hashable (SetAttr a) -instance ToJSON a => ToJSON (SetAttr a) where toJSON = genericToJSON jsonOptions -instance FromJSON a => FromJSON (SetAttr a) where parseJSON = genericParseJSON jsonOptions -instance Default (SetAttr a) where def = SetAttr def -instance Pretty a => Pretty (SetAttr a) where - pretty (SetAttr SizeAttr_None) = prEmpty - pretty (SetAttr a) = prParens (pretty a) - - -data SizeAttr a - = SizeAttr_None - | SizeAttr_Size a - | SizeAttr_MinSize a - | SizeAttr_MaxSize a - | SizeAttr_MinMaxSize a a - deriving (Eq, Ord, Show, Data, Functor, Traversable, Foldable, Typeable, Generic) -instance Serialize a => Serialize (SizeAttr a) -instance Hashable a => Hashable (SizeAttr a) -instance ToJSON a => ToJSON (SizeAttr a) where toJSON = genericToJSON jsonOptions -instance FromJSON a => FromJSON (SizeAttr a) where parseJSON = genericParseJSON jsonOptions -instance Default (SizeAttr a) where def = SizeAttr_None -instance Pretty a => Pretty (SizeAttr a) where - pretty SizeAttr_None = prEmpty - pretty (SizeAttr_Size x ) = "size" <+> pretty x - pretty (SizeAttr_MinSize x ) = "minSize" <+> pretty x - pretty (SizeAttr_MaxSize x ) = "maxSize" <+> pretty x - pretty (SizeAttr_MinMaxSize x y) = "minSize" <+> pretty x <> ", maxSize" <+> pretty y - - -getMaxFrom_SizeAttr :: MonadFail m => SizeAttr a -> m a -getMaxFrom_SizeAttr (SizeAttr_Size n) = return n -getMaxFrom_SizeAttr (SizeAttr_MaxSize n) = return n -getMaxFrom_SizeAttr (SizeAttr_MinMaxSize _ n) = return n -getMaxFrom_SizeAttr _ = fail "getMaxFrom_SizeAttr" - - -data MSetAttr a = MSetAttr (SizeAttr a) (OccurAttr a) - deriving (Eq, Ord, Show, Data, Functor, Traversable, Foldable, Typeable, Generic) -instance Serialize a => Serialize (MSetAttr a) -instance Hashable a => Hashable (MSetAttr a) -instance ToJSON a => ToJSON (MSetAttr a) where toJSON = genericToJSON jsonOptions -instance FromJSON a => FromJSON (MSetAttr a) where parseJSON = genericParseJSON jsonOptions -instance Default (MSetAttr a) where def = MSetAttr def def -instance Pretty a => Pretty (MSetAttr a) where - pretty (MSetAttr a b) = - let inside = filter (/=prEmpty) [ pretty a - , pretty b - ] - in if null inside - then prEmpty - else prettyList prParens "," inside - - -data OccurAttr a - = OccurAttr_None - | OccurAttr_MinOccur a - | OccurAttr_MaxOccur a - | OccurAttr_MinMaxOccur a a - deriving (Eq, Ord, Show, Data, Functor, Traversable, Foldable, Typeable, Generic) -instance Serialize a => Serialize (OccurAttr a) -instance Hashable a => Hashable (OccurAttr a) -instance ToJSON a => ToJSON (OccurAttr a) where toJSON = genericToJSON jsonOptions -instance FromJSON a => FromJSON (OccurAttr a) where parseJSON = genericParseJSON jsonOptions -instance Default (OccurAttr a) where def = OccurAttr_None -instance Pretty a => Pretty (OccurAttr a) where - pretty OccurAttr_None = prEmpty - pretty (OccurAttr_MinOccur x ) = "minOccur" <+> pretty x - pretty (OccurAttr_MaxOccur x ) = "maxOccur" <+> pretty x - pretty (OccurAttr_MinMaxOccur x y) = "minOccur" <+> pretty x <> ", maxOccur" <+> pretty y - - -getMaxFrom_OccurAttr :: MonadFail m => OccurAttr a -> m a -getMaxFrom_OccurAttr (OccurAttr_MaxOccur n) = return n -getMaxFrom_OccurAttr (OccurAttr_MinMaxOccur _ n) = return n -getMaxFrom_OccurAttr _ = fail "getMaxFrom_OccurAttr" - - -data FunctionAttr x - = FunctionAttr (SizeAttr x) PartialityAttr JectivityAttr - deriving (Eq, Ord, Show, Data, Functor, Traversable, Foldable, Typeable, Generic) -instance Serialize a => Serialize (FunctionAttr a) -instance Hashable a => Hashable (FunctionAttr a) -instance ToJSON a => ToJSON (FunctionAttr a) where toJSON = genericToJSON jsonOptions -instance FromJSON a => FromJSON (FunctionAttr a) where parseJSON = genericParseJSON jsonOptions -instance Default (FunctionAttr a) where def = FunctionAttr def def def -instance Pretty a => Pretty (FunctionAttr a) where - pretty (FunctionAttr a b c) = - let inside = filter (/=prEmpty) [pretty a, pretty b, pretty c] - in if null inside - then prEmpty - else prettyList prParens "," inside - - -data PartialityAttr - = PartialityAttr_Partial - | PartialityAttr_Total - deriving (Eq, Ord, Show, Data, Typeable, Generic) -instance Serialize PartialityAttr -instance Hashable PartialityAttr -instance ToJSON PartialityAttr where toJSON = genericToJSON jsonOptions -instance FromJSON PartialityAttr where parseJSON = genericParseJSON jsonOptions -instance Default PartialityAttr where def = PartialityAttr_Partial -instance Pretty PartialityAttr where - pretty PartialityAttr_Partial = prEmpty -- partial is the default - pretty PartialityAttr_Total = "total" - - -data JectivityAttr - = JectivityAttr_None - | JectivityAttr_Injective - | JectivityAttr_Surjective - | JectivityAttr_Bijective - deriving (Eq, Ord, Show, Data, Typeable, Generic) -instance Serialize JectivityAttr -instance Hashable JectivityAttr -instance ToJSON JectivityAttr where toJSON = genericToJSON jsonOptions -instance FromJSON JectivityAttr where parseJSON = genericParseJSON jsonOptions -instance Default JectivityAttr where def = JectivityAttr_None -instance Pretty JectivityAttr where - pretty JectivityAttr_None = prEmpty - pretty JectivityAttr_Injective = "injective" - pretty JectivityAttr_Surjective = "surjective" - pretty JectivityAttr_Bijective = "bijective" - - -data SequenceAttr x - = SequenceAttr (SizeAttr x) JectivityAttr - deriving (Eq, Ord, Show, Data, Functor, Traversable, Foldable, Typeable, Generic) -instance Serialize a => Serialize (SequenceAttr a) -instance Hashable a => Hashable (SequenceAttr a) -instance ToJSON a => ToJSON (SequenceAttr a) where toJSON = genericToJSON jsonOptions -instance FromJSON a => FromJSON (SequenceAttr a) where parseJSON = genericParseJSON jsonOptions -instance Default (SequenceAttr a) where def = SequenceAttr def def -instance Pretty a => Pretty (SequenceAttr a) where - pretty (SequenceAttr a b) = - let inside = filter (/=prEmpty) [pretty a, pretty b] - in if null inside - then prEmpty - else prettyList prParens "," inside - - -data RelationAttr a = RelationAttr (SizeAttr a) BinaryRelationAttrs - deriving (Eq, Ord, Show, Data, Functor, Traversable, Foldable, Typeable, Generic) -instance Serialize a => Serialize (RelationAttr a) -instance Hashable a => Hashable (RelationAttr a) -instance ToJSON a => ToJSON (RelationAttr a) where toJSON = genericToJSON jsonOptions -instance FromJSON a => FromJSON (RelationAttr a) where parseJSON = genericParseJSON jsonOptions -instance Default (RelationAttr a) where def = RelationAttr def def -instance Pretty a => Pretty (RelationAttr a) where - pretty (RelationAttr a b) = - let inside = filter (/=prEmpty) [pretty a, pretty b] - in if null inside - then prEmpty - else prettyList prParens "," inside - - -data BinaryRelationAttrs = BinaryRelationAttrs (S.Set BinaryRelationAttr) - deriving (Eq, Ord, Show, Data, Typeable, Generic) -instance Serialize BinaryRelationAttrs -instance Hashable BinaryRelationAttrs where hashWithSalt salt (BinaryRelationAttrs a) = hashWithSalt salt (S.toList a) -instance ToJSON BinaryRelationAttrs where toJSON = genericToJSON jsonOptions -instance FromJSON BinaryRelationAttrs where parseJSON = genericParseJSON jsonOptions -instance Default BinaryRelationAttrs where def = BinaryRelationAttrs S.empty -instance Pretty BinaryRelationAttrs where - pretty (BinaryRelationAttrs attrs) = prettyList id "," (S.toList attrs) -instance Semigroup BinaryRelationAttrs where - (<>) = mappend -instance Monoid BinaryRelationAttrs where - mempty = BinaryRelationAttrs def - mappend (BinaryRelationAttrs a) (BinaryRelationAttrs b) = BinaryRelationAttrs (S.union a b) - - -data BinaryRelationAttr - = BinRelAttr_Reflexive - | BinRelAttr_Irreflexive - | BinRelAttr_Coreflexive - | BinRelAttr_Symmetric - | BinRelAttr_AntiSymmetric - | BinRelAttr_ASymmetric - | BinRelAttr_Transitive - | BinRelAttr_Total - | BinRelAttr_Connex - | BinRelAttr_Euclidean - | BinRelAttr_Serial - | BinRelAttr_Equivalence - | BinRelAttr_PartialOrder - deriving (Eq, Ord, Show, Data, Typeable, Generic) -instance Serialize BinaryRelationAttr -instance Hashable BinaryRelationAttr -instance ToJSON BinaryRelationAttr where toJSON = genericToJSON jsonOptions -instance FromJSON BinaryRelationAttr where parseJSON = genericParseJSON jsonOptions -instance Pretty BinaryRelationAttr where - pretty BinRelAttr_Reflexive = "reflexive" - pretty BinRelAttr_Irreflexive = "irreflexive" - pretty BinRelAttr_Coreflexive = "coreflexive" - pretty BinRelAttr_Symmetric = "symmetric" - pretty BinRelAttr_AntiSymmetric = "antiSymmetric" - pretty BinRelAttr_ASymmetric = "aSymmetric" - pretty BinRelAttr_Transitive = "transitive" - pretty BinRelAttr_Total = "total" - pretty BinRelAttr_Connex = "connex" - pretty BinRelAttr_Euclidean = "Euclidean" - pretty BinRelAttr_Serial = "serial" - pretty BinRelAttr_Equivalence = "equivalence" - pretty BinRelAttr_PartialOrder = "partialOrder" - -readBinRel :: MonadFail m => AttrName -> m BinaryRelationAttr -readBinRel AttrName_reflexive = return BinRelAttr_Reflexive -readBinRel AttrName_irreflexive = return BinRelAttr_Irreflexive -readBinRel AttrName_coreflexive = return BinRelAttr_Coreflexive -readBinRel AttrName_symmetric = return BinRelAttr_Symmetric -readBinRel AttrName_antiSymmetric = return BinRelAttr_AntiSymmetric -readBinRel AttrName_aSymmetric = return BinRelAttr_ASymmetric -readBinRel AttrName_transitive = return BinRelAttr_Transitive -readBinRel AttrName_total = return BinRelAttr_Total -readBinRel AttrName_connex = return BinRelAttr_Connex -readBinRel AttrName_Euclidean = return BinRelAttr_Euclidean -readBinRel AttrName_serial = return BinRelAttr_Serial -readBinRel AttrName_equivalence = return BinRelAttr_Equivalence -readBinRel AttrName_partialOrder = return BinRelAttr_PartialOrder -readBinRel a = fail $ "Not a binary relation attribute:" <+> pretty a - --- reflexive forAll x : T . rel(x,x) --- irreflexive forAll x : T . !rel(x,x) --- coreflexive forAll x,y : T . rel(x,y) -> x = y --- --- symmetric forAll x,y : T . rel(x,y) -> rel(y,x) --- antisymmetric forAll x,y : T . rel(x,y) /\ rel(y,x) -> x = y --- asymmetric forAll x,y : T . rel(x,y) -> !rel(y,x) --- --- transitive forAll x,y,z : T . rel(x,y) /\ rel(y,z) -> rel(x,z) --- --- total forAll x,y : T . rel(x,y) \/ rel(y,x) --- connex forAll x,y : T . rel(x,y) \/ rel(y,x) \/ x = y --- Euclidean forAll x,y,z : T . rel(x,y) /\ rel(x,z) -> rel(y,z) --- serial forAll x : T . exists y : T . rel(x,y) --- equivalence reflexive + symmetric + transitive --- partialOrder reflexive + antisymmetric + transitive - - -data PartitionAttr a = PartitionAttr - { partsNum :: SizeAttr a - , partsSize :: SizeAttr a - , isRegular :: Bool - } - deriving (Eq, Ord, Show, Data, Functor, Traversable, Foldable, Typeable, Generic) -instance Serialize a => Serialize (PartitionAttr a) -instance Hashable a => Hashable (PartitionAttr a) -instance ToJSON a => ToJSON (PartitionAttr a) where toJSON = genericToJSON jsonOptions -instance FromJSON a => FromJSON (PartitionAttr a) where parseJSON = genericParseJSON jsonOptions -instance Default (PartitionAttr a) where def = PartitionAttr def def False -instance Pretty a => Pretty (PartitionAttr a) where - pretty (PartitionAttr a b c) = - let inside = filter (/=prEmpty) [ prettyNum a - , prettySize b - , prettyReg c - ] - - prettyNum SizeAttr_None = prEmpty - prettyNum (SizeAttr_Size x ) = "numParts" <+> pretty x - prettyNum (SizeAttr_MinSize x ) = "minNumParts" <+> pretty x - prettyNum (SizeAttr_MaxSize x ) = "maxNumParts" <+> pretty x - prettyNum (SizeAttr_MinMaxSize x y) = "minNumParts" <+> pretty x <> ", maxNumParts" <+> pretty y - - prettySize SizeAttr_None = prEmpty - prettySize (SizeAttr_Size x ) = "partSize" <+> pretty x - prettySize (SizeAttr_MinSize x ) = "minPartSize" <+> pretty x - prettySize (SizeAttr_MaxSize x ) = "maxPartSize" <+> pretty x - prettySize (SizeAttr_MinMaxSize x y) = "minPartSize" <+> pretty x <> ", maxPartSize" <+> pretty y - - prettyReg False = prEmpty - prettyReg True = "regular" - - in if null inside - then prEmpty - else prettyList prParens "," inside - - -data DomainAttributes a = DomainAttributes [DomainAttribute a] - deriving (Eq, Ord, Show, Data, Functor, Traversable, Foldable, Typeable, Generic) - -instance Serialize a => Serialize (DomainAttributes a) -instance Hashable a => Hashable (DomainAttributes a) -instance ToJSON a => ToJSON (DomainAttributes a) where toJSON = genericToJSON jsonOptions -instance FromJSON a => FromJSON (DomainAttributes a) where parseJSON = genericParseJSON jsonOptions - -instance Default (DomainAttributes a) where - def = DomainAttributes [] - - -data DomainAttribute a - = DAName Name - | DANameValue Name a - | DADotDot - deriving (Eq, Ord, Show, Data, Functor, Traversable, Foldable, Typeable, Generic) - -instance Serialize a => Serialize (DomainAttribute a) -instance Hashable a => Hashable (DomainAttribute a) -instance ToJSON a => ToJSON (DomainAttribute a) where toJSON = genericToJSON jsonOptions -instance FromJSON a => FromJSON (DomainAttribute a) where parseJSON = genericParseJSON jsonOptions - - -data Range a - = RangeOpen - | RangeSingle a - | RangeLowerBounded a - | RangeUpperBounded a - | RangeBounded a a - deriving (Eq, Ord, Show, Data, Functor, Traversable, Foldable, Typeable, Generic) - -instance Serialize a => Serialize (Range a) -instance Hashable a => Hashable (Range a) -instance ToJSON a => ToJSON (Range a) where toJSON = genericToJSON jsonOptions -instance FromJSON a => FromJSON (Range a) where parseJSON = genericParseJSON jsonOptions - -instance Arbitrary a => Arbitrary (Range a) where - arbitrary = oneof - [ return RangeOpen - , RangeSingle <$> arbitrary - , RangeLowerBounded <$> arbitrary - , RangeUpperBounded <$> arbitrary - , RangeBounded <$> arbitrary <*> arbitrary - ] - -rangesInts :: (MonadFail m, ExpressionLike c) => [Range c] -> m [Integer] -rangesInts = fmap (sortNub . concat) . mapM rangeInts - where - rangeInts (RangeSingle x) = return <$> intOut "rangeInts 1" x - rangeInts (RangeBounded x y) = do x' <- intOut "rangeInts 2" x - y' <- intOut "rangeInts 3" y - return [x' .. y'] - rangeInts _ = fail "Infinite range (or not an integer range)" - -expandRanges :: ExpressionLike c => [Range c] -> [Range c] -expandRanges r = - case rangesInts r of - Nothing -> r - Just [] -> [] - Just is -> - if [ minimum is .. maximum is ] == is - then [RangeBounded (fromInt (minimum is)) (fromInt (maximum is))] - else map (RangeSingle . fromInt) is - - -data HasRepresentation - = NoRepresentation - - | Set_Occurrence - | Set_Explicit - | Set_ExplicitVarSizeWithFlags - | Set_ExplicitVarSizeWithMarker - | Set_ExplicitVarSizeWithDummy - - | MSet_Occurrence - | MSet_ExplicitWithFlags - | MSet_ExplicitWithRepetition - - | Function_1D - | Function_1DPartial - | Function_ND - | Function_NDPartial - | Function_AsRelation HasRepresentation -- carries: representation for the inner relation - - | Sequence_ExplicitBounded - - | Relation_AsMatrix - | Relation_AsSet HasRepresentation -- carries: representation for the inner set - - | Partition_AsSet HasRepresentation HasRepresentation -- carries: representations for the inner sets - | Partition_Occurrence - - deriving (Eq, Ord, Show, Data, Typeable, Generic) - -instance Serialize HasRepresentation -instance Hashable HasRepresentation -instance ToJSON HasRepresentation where toJSON = genericToJSON jsonOptions -instance FromJSON HasRepresentation where parseJSON = genericParseJSON jsonOptions - -instance Default HasRepresentation where - def = NoRepresentation - -representationConstrIndex :: HasRepresentation -> [Text] -representationConstrIndex r = oneLevel r : concatMap representationConstrIndex (children r) - where - oneLevel :: HasRepresentation -> Text - oneLevel = stringToText . ("R"++) . show . constrIndex . toConstr - -instance (Pretty r, Pretty a) => Pretty (Domain r a) where - - pretty DomainAny{} = "?" - - pretty DomainBool = "bool" - - pretty (DomainIntE x) = "int" <> prParens (pretty x) - - pretty (DomainInt _ []) = "int" - pretty (DomainInt _ ranges) = "int" <> prettyList prParens "," ranges - - pretty (DomainEnum name (Just ranges) _) = pretty name <> prettyList prParens "," ranges - pretty (DomainEnum name _ _) = pretty name - - pretty (DomainUnnamed name _) = pretty name - - pretty (DomainTuple inners) - = (if length inners < 2 then "tuple" else prEmpty) - <+> prettyList prParens "," inners - - pretty (DomainRecord xs) = "record" <+> prettyList prBraces "," - [ pretty nm <+> ":" <+> pretty d | (nm, d) <- xs ] - - pretty (DomainVariant xs) = "variant" <+> prettyList prBraces "," - [ pretty nm <+> ":" <+> pretty d | (nm, d) <- xs ] - - pretty (DomainMatrix index innerNested) - = "matrix indexed by" <+> prettyList prBrackets "," indices - <+> "of" <+> pretty inner - where - (indices,inner) = first (index:) $ collect innerNested - collect (DomainMatrix i j) = first (i:) $ collect j - collect x = ([],x) - - pretty (DomainSet r attrs inner) = - hang ("set" <+> prettyAttrs r attrs <+> "of") 4 (pretty inner) - - pretty (DomainMSet r attrs inner) = - hang ("mset" <+> prettyAttrs r attrs <+> "of") 4 (pretty inner) - - pretty (DomainFunction r attrs innerFrom innerTo) = - hang ("function" <+> prettyAttrs r attrs) 4 $ - hang (pretty innerFrom) 4 $ - "-->" <+> pretty innerTo - - pretty (DomainSequence r attrs inner) = - hang ("sequence" <+> prettyAttrs r attrs <+> "of") 4 (pretty inner) - - pretty (DomainRelation r attrs inners) - = hang ("relation" <+> prettyAttrs r attrs <+> "of") 4 (prettyList prParens " *" inners) - - pretty (DomainPartition r attrs inner) - = hang ("partition" <+> prettyAttrs r attrs <+> "from") 4 (pretty inner) - - pretty d@DomainOp{} = pretty (show d) - - pretty (DomainReference x _) = pretty x - - pretty (DomainMetaVar x) = "&" <> pretty x - - -prettyAttrs :: (Pretty a, Pretty b) => a -> b -> Doc -prettyAttrs a bs = - let prettya = pretty a - in if prettya == "()" - then pretty bs - else prBraces prettya <+> pretty bs - -instance Pretty a => Pretty (DomainAttributes a) where - pretty (DomainAttributes []) = prEmpty - pretty (DomainAttributes attrs) = prettyList prParens "," attrs - -instance Pretty a => Pretty (DomainAttribute a) where - pretty (DAName name) = pretty name - pretty (DANameValue name value) = pretty name <+> pretty value - pretty DADotDot = ".." - -instance Pretty a => Pretty (Range a) where - pretty RangeOpen = ".." - pretty (RangeSingle x) = pretty x - pretty (RangeLowerBounded x) = pretty x <> ".." - pretty (RangeUpperBounded x) = ".." <> pretty x - pretty (RangeBounded x y) | show (pretty x) == show (pretty y) = pretty x - pretty (RangeBounded x y) = pretty x <> ".." <> pretty y - -instance Pretty HasRepresentation where - pretty NoRepresentation = "∅" - pretty r = pretty (representationToFullText r) - -textToRepresentation :: Text -> [HasRepresentation] -> Maybe HasRepresentation -textToRepresentation t [] | t == "Occurrence" = return Set_Occurrence -textToRepresentation t [] | t == "Explicit" = return Set_Explicit -textToRepresentation t [] | t == "ExplicitVarSizeWithFlags" = return Set_ExplicitVarSizeWithFlags -textToRepresentation t [] | t == "ExplicitVarSizeWithMarker" = return Set_ExplicitVarSizeWithMarker -textToRepresentation t [] | t == "ExplicitVarSizeWithDummy" = return Set_ExplicitVarSizeWithDummy -textToRepresentation t [] | t == "MOccurrence" = return MSet_Occurrence -textToRepresentation t [] | t == "ExplicitWithFlags" = return MSet_ExplicitWithFlags -textToRepresentation t [] | t == "ExplicitWithRepetition" = return MSet_ExplicitWithRepetition -textToRepresentation t [] | t == "Function1D" = return Function_1D -textToRepresentation t [] | t == "Function1DPartial" = return Function_1DPartial -textToRepresentation t [] | t == "FunctionND" = return Function_ND -textToRepresentation t [] | t == "FunctionNDPartial" = return Function_NDPartial -textToRepresentation t [repr] | t == "FunctionAsRelation" = return (Function_AsRelation repr) -textToRepresentation t [] | t == "ExplicitBounded" = return Sequence_ExplicitBounded -textToRepresentation t [] | t == "RelationAsMatrix" = return Relation_AsMatrix -textToRepresentation t [repr] | t == "RelationAsSet" = return (Relation_AsSet repr) -textToRepresentation t [repr1, repr2] | t == "PartitionAsSet" = return (Partition_AsSet repr1 repr2) -textToRepresentation t [] | t == "PartitionOccurrence" = return Partition_Occurrence -textToRepresentation t _ = bug ("textToRepresentation:" <+> pretty t) - -representationToShortText :: HasRepresentation -> Text -representationToShortText Set_Occurrence = "Occurrence" -representationToShortText Set_Explicit = "Explicit" -representationToShortText Set_ExplicitVarSizeWithFlags = "ExplicitVarSizeWithFlags" -representationToShortText Set_ExplicitVarSizeWithMarker = "ExplicitVarSizeWithMarker" -representationToShortText Set_ExplicitVarSizeWithDummy = "ExplicitVarSizeWithDummy" -representationToShortText MSet_Occurrence = "MOccurrence" -representationToShortText MSet_ExplicitWithFlags = "ExplicitWithFlags" -representationToShortText MSet_ExplicitWithRepetition = "ExplicitWithRepetition" -representationToShortText Function_1D = "Function1D" -representationToShortText Function_1DPartial = "Function1DPartial" -representationToShortText Function_ND = "FunctionND" -representationToShortText Function_NDPartial = "FunctionNDPartial" -representationToShortText Function_AsRelation{} = "FunctionAsRelation" -representationToShortText Sequence_ExplicitBounded = "ExplicitBounded" -representationToShortText Relation_AsMatrix = "RelationAsMatrix" -representationToShortText Relation_AsSet{} = "RelationAsSet" -representationToShortText Partition_AsSet{} = "PartitionAsSet" -representationToShortText Partition_Occurrence = "PartitionOccurrence" -representationToShortText r = bug ("representationToShortText:" <+> pretty (show r)) - -representationToFullText :: HasRepresentation -> Text -representationToFullText (Function_AsRelation repr) = mconcat [ "FunctionAsRelation" - , "[" - , representationToFullText repr - , "]" - ] -representationToFullText (Relation_AsSet repr) = mconcat [ "RelationAsSet" - , "[" - , representationToFullText repr - , "]" - ] -representationToFullText (Partition_AsSet repr1 repr2) = mconcat [ "PartitionAsSet" - , "[" - , representationToFullText repr1 - , "," - , representationToFullText repr2 - , "]" - ] -representationToFullText r = representationToShortText r - - -normaliseDomain :: (Ord c, ExpressionLike c) => (c -> c) -> Domain r c -> Domain r c -normaliseDomain _norm DomainBool = DomainBool -normaliseDomain norm (DomainInt t rs ) = DomainInt t $ sort $ map (normaliseRange norm) (expandRanges rs) -normaliseDomain _norm (DomainEnum n Nothing mp) = DomainEnum n Nothing mp -normaliseDomain _norm (DomainEnum n (Just rs) mp) = DomainEnum n (Just $ sort rs) mp -normaliseDomain norm (DomainUnnamed n x ) = DomainUnnamed n (norm x) -normaliseDomain norm (DomainRecord doms ) = DomainRecord [ (n, normaliseDomain norm d) - | (n, d) <- doms ] -normaliseDomain norm (DomainVariant doms ) = DomainVariant [ (n, normaliseDomain norm d) - | (n, d) <- doms ] -normaliseDomain norm (DomainTuple doms ) = DomainTuple $ map (normaliseDomain norm) doms -normaliseDomain norm (DomainMatrix dom1 dom2) = DomainMatrix (normaliseDomain norm dom1) - (normaliseDomain norm dom2) -normaliseDomain norm (DomainSet r attr dom ) = DomainSet r (fmap norm attr) - (normaliseDomain norm dom) -normaliseDomain norm (DomainMSet r attr dom ) = DomainMSet r (fmap norm attr) - (normaliseDomain norm dom) -normaliseDomain norm (DomainFunction r attr dom1 dom2) = DomainFunction r (fmap norm attr) - (normaliseDomain norm dom1) - (normaliseDomain norm dom2) -normaliseDomain norm (DomainSequence r attr dom ) = DomainSequence r (fmap norm attr) - (normaliseDomain norm dom) -normaliseDomain norm (DomainRelation r attr doms ) = DomainRelation r (fmap norm attr) - (map (normaliseDomain norm) doms) -normaliseDomain norm (DomainPartition r attr dom ) = DomainPartition r (fmap norm attr) - (normaliseDomain norm dom) -normaliseDomain _norm d = d - -normaliseRange :: (c -> c) -> Range c -> Range c -normaliseRange _norm RangeOpen = RangeOpen -normaliseRange norm (RangeSingle x) = RangeBounded (norm x) (norm x) -normaliseRange norm (RangeLowerBounded x) = RangeLowerBounded (norm x) -normaliseRange norm (RangeUpperBounded x) = RangeUpperBounded (norm x) -normaliseRange norm (RangeBounded x y) = RangeBounded (norm x) (norm y) - -innerDomainOf :: (MonadFail m, Show x) => Domain () x -> m (Domain () x) -innerDomainOf (DomainMatrix _ t) = return t -innerDomainOf (DomainSet _ _ t) = return t -innerDomainOf (DomainMSet _ _ t) = return t -innerDomainOf (DomainFunction _ _ a b) = return (DomainTuple [a,b]) -innerDomainOf (DomainRelation _ _ ts) = return (DomainTuple ts) -innerDomainOf (DomainPartition _ _ t) = return (DomainSet () def t) -innerDomainOf t = fail ("innerDomainOf:" <+> pretty (show t)) - -singletonDomainInt :: (Eq x, CanBeAnAlias x) => Domain r x -> Maybe x -singletonDomainInt (DomainInt _ [RangeSingle a]) = Just a -singletonDomainInt (DomainInt _ [RangeBounded a b]) = - let - followAlias (isAlias -> Just x) = followAlias x - followAlias x = x - in - if followAlias a == followAlias b - then Just a - else Nothing -singletonDomainInt _ = Nothing - -matrixNumDimsD :: Domain r x -> Int -matrixNumDimsD (DomainMatrix _ t) = 1 + matrixNumDimsD t -matrixNumDimsD _ = 0 diff --git a/src/Conjure/Language/Domain_LOCAL_22702.hs b/src/Conjure/Language/Domain_LOCAL_22702.hs deleted file mode 100644 index d5cfb8d6c9..0000000000 --- a/src/Conjure/Language/Domain_LOCAL_22702.hs +++ /dev/null @@ -1,1044 +0,0 @@ -{-# LANGUAGE DeriveGeneric, DeriveDataTypeable, DeriveFunctor, DeriveTraversable, DeriveFoldable #-} -{-# LANGUAGE TupleSections #-} -{-# LANGUAGE NoMonomorphismRestriction #-} -{-# LANGUAGE ViewPatterns #-} - -module Conjure.Language.Domain - ( Domain(..) - , HasRepresentation(..) - , Range(..), rangesInts - , SetAttr(..), SizeAttr(..), getMaxFrom_SizeAttr - , MSetAttr(..), OccurAttr(..), getMaxFrom_OccurAttr - , FunctionAttr(..), PartialityAttr(..), JectivityAttr(..) - , SequenceAttr(..) - , RelationAttr(..), BinaryRelationAttrs(..), BinaryRelationAttr(..) - , PartitionAttr(..) - , PermutationAttr(..) - , AttrName(..) - , DomainAttributes(..), DomainAttribute(..) -- only for parsing - , textToRepresentation, representationToShortText, representationToFullText - , isPrimitiveDomain, domainCanIndexMatrix, getIndices - , Tree(..), reprTree, reprAtTopLevel, applyReprTree - , reprTreeEncoded - , forgetRepr, changeRepr, defRepr - , mkDomainBool, mkDomainInt, mkDomainIntB, mkDomainIntBTagged, mkDomainAny - , typeOfDomain - , readBinRel - , normaliseDomain, normaliseRange - , innerDomainOf - , singletonDomainInt - , matrixNumDimsD - ) where - --- conjure -import Conjure.Prelude -import Conjure.Bug -import Conjure.Language.Name -import Conjure.Language.Type -import Conjure.Language.TypeOf -import Conjure.Language.AdHoc -import Conjure.Language.Pretty - --- base -import qualified Data.Semigroup as Semigroup ( (<>) ) - --- QuickCheck -import Test.QuickCheck ( Arbitrary(..), choose, oneof, vectorOf, sized ) - --- containers -import Data.Set as S ( Set, empty, toList, union ) - --- syb -import Data.Data ( toConstr, constrIndex ) - - -data Domain r x - = DomainAny Text Type - | DomainBool - | DomainIntE x - | DomainInt IntTag [Range x] - | DomainEnum - Name - (Maybe [Range x]) -- subset of values for this domain - -- Nothing *only* when GivenDomainDefnEnum and not LettingDomainDefnEnum - (Maybe [(Name, Integer)]) -- the mapping to integers, if available - | DomainUnnamed Name x - | DomainTuple [Domain r x] - | DomainRecord [(Name, Domain r x)] - | DomainVariant [(Name, Domain r x)] - | DomainMatrix (Domain () x) (Domain r x) - | DomainSet r (SetAttr x) (Domain r x) - | DomainMSet r (MSetAttr x) (Domain r x) - | DomainFunction r (FunctionAttr x) (Domain r x) (Domain r x) - | DomainSequence r (SequenceAttr x) (Domain r x) - | DomainRelation r (RelationAttr x) [Domain r x] - | DomainPartition r (PartitionAttr x) (Domain r x) - | DomainPermutation r (PermutationAttr x) (Domain r x) - | DomainOp Name [Domain r x] - | DomainReference Name (Maybe (Domain r x)) - | DomainMetaVar String - deriving (Eq, Ord, Show, Data, Functor, Traversable, Foldable, Typeable, Generic) - -instance (VarSymBreakingDescription x, ToJSON r) => VarSymBreakingDescription (Domain r x) where - varSymBreakingDescription domain = toJSON $ fmap varSymBreakingDescription domain - -mkDomainBool :: Domain () x -mkDomainBool = DomainBool - -mkDomainInt :: [Range x] -> Domain () x -mkDomainInt = DomainInt TagInt - -mkDomainIntB :: x -> x -> Domain () x -mkDomainIntB l u = DomainInt TagInt [RangeBounded l u] - -mkDomainIntBTagged :: IntTag -> x -> x -> Domain () x -mkDomainIntBTagged t l u = DomainInt t [RangeBounded l u] - -mkDomainAny :: Doc -> Type -> Domain r x -mkDomainAny reason = DomainAny (stringToText $ show reason) - -instance (Serialize r, Serialize x) => Serialize (Domain r x) -instance (Hashable r, Hashable x) => Hashable (Domain r x) -instance (ToJSON r, ToJSON x) => ToJSON (Domain r x) where toJSON = genericToJSON jsonOptions -instance (FromJSON r, FromJSON x) => FromJSON (Domain r x) where parseJSON = genericParseJSON jsonOptions - -instance Arbitrary x => Arbitrary (Domain r x) where - arbitrary = sized f - where - f 0 = oneof [ return DomainBool - , DomainInt TagInt <$> arbitrary - -- , DomainEnum <$> arbitrary <*> arbitrary - ] - f s = do - arity <- choose (2 :: Int, 10) - DomainTuple <$> vectorOf arity (f (div s 10)) - shrink DomainBool = [] - shrink (DomainInt _ []) = [DomainBool] - shrink (DomainInt t [r]) = DomainBool : DomainInt t [] : [DomainInt t [r'] | r' <- shrink r] - shrink (DomainInt t rs) = [DomainInt t (init rs)] - shrink _ = [] - -instance (Pretty r, TypeOf x, Pretty x) => TypeOf (Domain r x) where - typeOf = typeOfDomain - -typeOfDomain :: - MonadFail m => - Pretty r => - TypeOf x => - Pretty x => - (?typeCheckerMode :: TypeCheckerMode) => - Domain r x -> m Type -typeOfDomain (DomainAny _ ty) = return ty -typeOfDomain DomainBool = return TypeBool -typeOfDomain d@(DomainIntE x) = do - ty <- typeOf x - case ty of - TypeInt{} -> return () -- pre recoverDomainInt - TypeList TypeInt{} -> return () - TypeMatrix _ TypeInt{} -> return () - TypeSet TypeInt{} -> return () - _ -> fail $ vcat [ "Expected an integer, but got:" <++> pretty ty - , "In domain:" <+> pretty d - ] - return (TypeInt TagInt) -typeOfDomain d@(DomainInt t rs) = do - forM_ rs $ \ r -> forM_ r $ \ x -> do - ty <- typeOf x - case ty of - TypeInt{} -> return () - _ -> fail $ vcat [ "Expected an integer, but got:" <++> pretty ty - , "For:" <+> pretty x - , "In domain:" <+> pretty d - ] - return (TypeInt t) -typeOfDomain (DomainEnum defn _ _ ) = return (TypeEnum defn) -typeOfDomain (DomainUnnamed defn _ ) = return (TypeUnnamed defn) -typeOfDomain (DomainTuple xs ) = TypeTuple <$> mapM typeOf xs -typeOfDomain (DomainRecord xs ) = TypeRecord <$> sequence [ do t <- typeOf d ; return (n, t) - | (n,d) <- xs ] -typeOfDomain (DomainVariant xs ) = TypeVariant <$> sequence [ do t <- typeOf d ; return (n, t) - | (n,d) <- xs ] -typeOfDomain (DomainMatrix ind inn ) = TypeMatrix <$> typeOf ind <*> typeOf inn -typeOfDomain (DomainSet _ _ x ) = TypeSet <$> typeOf x -typeOfDomain (DomainMSet _ _ x ) = TypeMSet <$> typeOf x -typeOfDomain (DomainFunction _ _ x y) = TypeFunction <$> typeOf x <*> typeOf y -typeOfDomain (DomainSequence _ _ x ) = TypeSequence <$> typeOf x -typeOfDomain (DomainRelation _ _ xs ) = TypeRelation <$> mapM typeOf xs -typeOfDomain (DomainPartition _ _ x ) = TypePartition <$> typeOf x -typeOfDomain (DomainPermutation _ _ x ) = TypePermutation <$> typeOf x -typeOfDomain p@(DomainOp _ ds) = do - ts <- mapM typeOfDomain ds - if typesUnify ts - then return (mostDefined ts) - else fail ("Type error in" <+> pretty p) -typeOfDomain (DomainReference _ (Just d)) = typeOf d -typeOfDomain (DomainReference nm Nothing) = bug $ "typeOf: DomainReference" <+> pretty nm -typeOfDomain (DomainMetaVar nm) = bug $ "typeOf: DomainMetaVar &" <> pretty nm - -forgetRepr :: Domain r x -> Domain () x -forgetRepr = defRepr - -defRepr :: Default r2 => Domain r x -> Domain r2 x -defRepr = changeRepr def - -changeRepr :: r2 -> Domain r x -> Domain r2 x -changeRepr rep = go - where - go (DomainAny t ty) = DomainAny t ty - go DomainBool = DomainBool - go (DomainIntE x) = DomainIntE x - go (DomainInt t rs) = DomainInt t rs - go (DomainEnum defn rs mp) = DomainEnum defn rs mp - go (DomainUnnamed defn s) = DomainUnnamed defn s - go (DomainTuple ds) = DomainTuple (map go ds) - go (DomainRecord xs) = DomainRecord (map (second go) xs) - go (DomainVariant xs) = DomainVariant (map (second go) xs) - go (DomainMatrix index inner) = DomainMatrix index (go inner) - go (DomainSet _ attr d) = - DomainSet rep attr (go d) - go (DomainMSet _ attr d) = - DomainMSet rep attr (go d) - go (DomainFunction _ attr d1 d2) = - DomainFunction rep attr (go d1) (go d2) - go (DomainSequence _ attr d) = - DomainSequence rep attr (go d) - go (DomainRelation _ attr ds) = - DomainRelation rep attr (map go ds) - go (DomainPartition _ attr d) = DomainPartition rep attr (go d) - go (DomainPermutation _ attr d) = DomainPermutation rep attr (go d) - go (DomainOp op ds) = DomainOp op (map go ds) - go (DomainReference x r) = DomainReference x (fmap go r) - go (DomainMetaVar x) = DomainMetaVar x - - -data Tree a = Tree { rootLabel :: a, subForest :: [Tree a] } - deriving (Eq, Ord, Show, Data, Functor, Traversable, Foldable, Typeable, Generic) - -instance Serialize a => Serialize (Tree a) -instance Hashable a => Hashable (Tree a) -instance ToJSON a => ToJSON (Tree a) where toJSON = genericToJSON jsonOptions -instance FromJSON a => FromJSON (Tree a) where parseJSON = genericParseJSON jsonOptions - --- | This is to be used when defining `Conjure.Representations.Internal.mkOutName`. --- Reason is to avoid sharing variables for parts of the same decision variable with differing representations. --- Example case: --- (1) find x : set {A} of (int(a..b) , set {B} of int(c..d)) --- (2) find x : set {A} of (int(a..b) , set {C} of int(c..d)) --- Here x_1's should not be shared! --- If they are, the channelling and symmetry breaking constraints will clash and solutions will be lost. -reprTreeEncoded :: Domain HasRepresentation x -> Text -reprTreeEncoded = mconcat . enc1 . reprTree - where - enc1 (Tree lbl sub) = - maybe - (bug "reprTreeEncoded: top-most representation is Nothing") - representationToShortText - lbl - : concatMap enc sub - enc (Tree lbl sub) = - maybe [] representationConstrIndex lbl - ++ concatMap enc sub - -reprTree :: Domain r x -> Tree (Maybe r) -reprTree DomainAny{} = Tree Nothing [] -reprTree DomainBool{} = Tree Nothing [] -reprTree DomainIntE{} = Tree Nothing [] -reprTree DomainInt{} = Tree Nothing [] -reprTree DomainEnum{} = Tree Nothing [] -reprTree DomainUnnamed{} = Tree Nothing [] -reprTree (DomainTuple as ) = Tree Nothing (map reprTree as) -reprTree (DomainRecord as ) = Tree Nothing (map (reprTree . snd) as) -reprTree (DomainVariant as) = Tree Nothing (map (reprTree . snd) as) -reprTree (DomainMatrix _ a) = Tree Nothing [reprTree a] -reprTree (DomainSet r _ a ) = Tree (Just r) [reprTree a] -reprTree (DomainMSet r _ a ) = Tree (Just r) [reprTree a] -reprTree (DomainFunction r _ a b) = Tree (Just r) [reprTree a, reprTree b] -reprTree (DomainSequence r _ a ) = Tree (Just r) [reprTree a] -reprTree (DomainRelation r _ as ) = Tree (Just r) (map reprTree as) -reprTree (DomainPartition r _ a ) = Tree (Just r) [reprTree a] -reprTree (DomainPermutation r _ a) = Tree (Just r) [reprTree a] -reprTree DomainOp{} = Tree Nothing [] -reprTree DomainReference{} = Tree Nothing [] -reprTree DomainMetaVar{} = Tree Nothing [] - -reprAtTopLevel :: Domain r x -> Maybe r -reprAtTopLevel = rootLabel . reprTree - -applyReprTree :: (MonadFail m, Pretty x, Pretty r2, Default r) => Domain r2 x -> Tree (Maybe r) -> m (Domain r x) -applyReprTree dom@DomainBool{} (Tree Nothing []) = return (defRepr dom) -applyReprTree dom@DomainInt{} (Tree Nothing []) = return (defRepr dom) -applyReprTree dom@DomainIntE{} (Tree Nothing []) = return (defRepr dom) -applyReprTree dom@DomainEnum{} (Tree Nothing []) = return (defRepr dom) -applyReprTree dom@DomainUnnamed{} (Tree Nothing []) = return (defRepr dom) -applyReprTree (DomainTuple as ) (Tree Nothing asRepr) = - DomainTuple <$> zipWithM applyReprTree as asRepr -applyReprTree (DomainRecord as ) (Tree Nothing asRepr) = - (DomainRecord . zip (map fst as)) <$> zipWithM applyReprTree (map snd as) asRepr -applyReprTree (DomainVariant as) (Tree Nothing asRepr) = - (DomainVariant . zip (map fst as)) <$> zipWithM applyReprTree (map snd as) asRepr -applyReprTree (DomainMatrix b a) (Tree Nothing [aRepr]) = DomainMatrix b <$> applyReprTree a aRepr -applyReprTree (DomainSet _ attr a ) (Tree (Just r) [aRepr]) = DomainSet r attr <$> applyReprTree a aRepr -applyReprTree (DomainMSet _ attr a ) (Tree (Just r) [aRepr]) = DomainMSet r attr <$> applyReprTree a aRepr -applyReprTree (DomainFunction _ attr a b) (Tree (Just r) [aRepr, bRepr]) = DomainFunction r attr <$> applyReprTree a aRepr <*> applyReprTree b bRepr -applyReprTree (DomainSequence _ attr a ) (Tree (Just r) [aRepr]) = DomainSequence r attr <$> applyReprTree a aRepr -applyReprTree (DomainRelation _ attr as ) (Tree (Just r) asRepr) = DomainRelation r attr <$> zipWithM applyReprTree as asRepr -applyReprTree (DomainPartition _ attr a ) (Tree (Just r) [aRepr]) = DomainPartition r attr <$> applyReprTree a aRepr -applyReprTree (DomainPermutation _ attr a ) (Tree (Just r) [aRepr]) = DomainPermutation r attr <$> applyReprTree a aRepr -applyReprTree dom@DomainOp{} (Tree Nothing []) = return (defRepr dom) -applyReprTree dom@DomainReference{} (Tree Nothing []) = return (defRepr dom) -applyReprTree dom@DomainMetaVar{} (Tree Nothing []) = return (defRepr dom) -applyReprTree dom _ = fail $ "applyReprTree:" <++> pretty dom - -isPrimitiveDomain :: Domain r x -> Bool -isPrimitiveDomain DomainBool{} = True -isPrimitiveDomain DomainIntE{} = True -isPrimitiveDomain DomainInt{} = True -isPrimitiveDomain (DomainMatrix index inner) = and [isPrimitiveDomain index, isPrimitiveDomain inner] -isPrimitiveDomain _ = False - -getIndices :: Domain r x -> ([Domain () x], Domain r x) -getIndices (DomainMatrix index inner) = first (index:) (getIndices inner) -getIndices d = ([], d) - -domainCanIndexMatrix :: Domain r x -> Bool -domainCanIndexMatrix DomainBool{} = True -domainCanIndexMatrix DomainInt {} = True -domainCanIndexMatrix DomainIntE{} = True -domainCanIndexMatrix DomainEnum{} = True -domainCanIndexMatrix _ = False - - --------------------------------------------------------------------------------- --- attribute-as-constraint handling -------------------------------------------- --------------------------------------------------------------------------------- - -data AttrName - = AttrName_size - | AttrName_minSize - | AttrName_maxSize - | AttrName_minOccur - | AttrName_maxOccur - | AttrName_numParts - | AttrName_minNumParts - | AttrName_maxNumParts - | AttrName_partSize - | AttrName_minPartSize - | AttrName_maxPartSize - | AttrName_total - | AttrName_injective - | AttrName_surjective - | AttrName_bijective - | AttrName_regular - -- bin rel ones - | AttrName_reflexive - | AttrName_irreflexive - | AttrName_coreflexive - | AttrName_symmetric - | AttrName_antiSymmetric - | AttrName_aSymmetric - | AttrName_transitive - | AttrName_connex - | AttrName_Euclidean - | AttrName_serial - | AttrName_equivalence - | AttrName_partialOrder - deriving (Eq, Ord, Show, Data, Typeable, Generic) - -instance Serialize AttrName -instance Hashable AttrName -instance ToJSON AttrName where toJSON = genericToJSON jsonOptions -instance FromJSON AttrName where parseJSON = genericParseJSON jsonOptions - -instance Pretty AttrName where - pretty AttrName_size = "size" - pretty AttrName_minSize = "minSize" - pretty AttrName_maxSize = "maxSize" - pretty AttrName_minOccur = "minOccur" - pretty AttrName_maxOccur = "maxOccur" - pretty AttrName_numParts = "numParts" - pretty AttrName_minNumParts = "minNumParts" - pretty AttrName_maxNumParts = "maxNumParts" - pretty AttrName_partSize = "partSize" - pretty AttrName_minPartSize = "minPartSize" - pretty AttrName_maxPartSize = "maxPartSize" - pretty AttrName_total = "total" - pretty AttrName_injective = "injective" - pretty AttrName_surjective = "surjective" - pretty AttrName_bijective = "bijective" - pretty AttrName_regular = "regular" - pretty AttrName_reflexive = "reflexive" - pretty AttrName_irreflexive = "irreflexive" - pretty AttrName_coreflexive = "coreflexive" - pretty AttrName_symmetric = "symmetric" - pretty AttrName_antiSymmetric = "antiSymmetric" - pretty AttrName_aSymmetric = "aSymmetric" - pretty AttrName_transitive = "transitive" - pretty AttrName_connex = "connex" - pretty AttrName_Euclidean = "Euclidean" - pretty AttrName_serial = "serial" - pretty AttrName_equivalence = "equivalence" - pretty AttrName_partialOrder = "partialOrder" - -instance IsString AttrName where - fromString "size" = AttrName_size - fromString "minSize" = AttrName_minSize - fromString "maxSize" = AttrName_maxSize - fromString "minOccur" = AttrName_minOccur - fromString "maxOccur" = AttrName_maxOccur - fromString "numParts" = AttrName_numParts - fromString "minNumParts" = AttrName_minNumParts - fromString "maxNumParts" = AttrName_maxNumParts - fromString "partSize" = AttrName_partSize - fromString "minPartSize" = AttrName_minPartSize - fromString "maxPartSize" = AttrName_maxPartSize - fromString "total" = AttrName_total - fromString "injective" = AttrName_injective - fromString "surjective" = AttrName_surjective - fromString "bijective" = AttrName_bijective - fromString "regular" = AttrName_regular - fromString "reflexive" = AttrName_reflexive - fromString "irreflexive" = AttrName_irreflexive - fromString "coreflexive" = AttrName_coreflexive - fromString "symmetric" = AttrName_symmetric - fromString "antiSymmetric" = AttrName_antiSymmetric - fromString "aSymmetric" = AttrName_aSymmetric - fromString "transitive" = AttrName_transitive - fromString "connex" = AttrName_connex - fromString "Euclidean" = AttrName_Euclidean - fromString "serial" = AttrName_serial - fromString "equivalence" = AttrName_equivalence - fromString "partialOrder" = AttrName_partialOrder - fromString s = bug $ "fromString{AttrName}:" <+> pretty s - - --------------------------------------------------------------------------------- --- attribute definitions ------------------------------------------------------- --------------------------------------------------------------------------------- - -data SetAttr a = SetAttr (SizeAttr a) - deriving (Eq, Ord, Show, Data, Functor, Traversable, Foldable, Typeable, Generic) -instance Serialize a => Serialize (SetAttr a) -instance Hashable a => Hashable (SetAttr a) -instance ToJSON a => ToJSON (SetAttr a) where toJSON = genericToJSON jsonOptions -instance FromJSON a => FromJSON (SetAttr a) where parseJSON = genericParseJSON jsonOptions -instance Default (SetAttr a) where def = SetAttr def -instance Pretty a => Pretty (SetAttr a) where - pretty (SetAttr SizeAttr_None) = prEmpty - pretty (SetAttr a) = prParens (pretty a) - - -data SizeAttr a - = SizeAttr_None - | SizeAttr_Size a - | SizeAttr_MinSize a - | SizeAttr_MaxSize a - | SizeAttr_MinMaxSize a a - deriving (Eq, Ord, Show, Data, Functor, Traversable, Foldable, Typeable, Generic) -instance Serialize a => Serialize (SizeAttr a) -instance Hashable a => Hashable (SizeAttr a) -instance ToJSON a => ToJSON (SizeAttr a) where toJSON = genericToJSON jsonOptions -instance FromJSON a => FromJSON (SizeAttr a) where parseJSON = genericParseJSON jsonOptions -instance Default (SizeAttr a) where def = SizeAttr_None -instance Pretty a => Pretty (SizeAttr a) where - pretty SizeAttr_None = prEmpty - pretty (SizeAttr_Size x ) = "size" <+> pretty x - pretty (SizeAttr_MinSize x ) = "minSize" <+> pretty x - pretty (SizeAttr_MaxSize x ) = "maxSize" <+> pretty x - pretty (SizeAttr_MinMaxSize x y) = "minSize" <+> pretty x <> ", maxSize" <+> pretty y - - -getMaxFrom_SizeAttr :: MonadFail m => SizeAttr a -> m a -getMaxFrom_SizeAttr (SizeAttr_Size n) = return n -getMaxFrom_SizeAttr (SizeAttr_MaxSize n) = return n -getMaxFrom_SizeAttr (SizeAttr_MinMaxSize _ n) = return n -getMaxFrom_SizeAttr _ = fail "getMaxFrom_SizeAttr" - - -data MSetAttr a = MSetAttr (SizeAttr a) (OccurAttr a) - deriving (Eq, Ord, Show, Data, Functor, Traversable, Foldable, Typeable, Generic) -instance Serialize a => Serialize (MSetAttr a) -instance Hashable a => Hashable (MSetAttr a) -instance ToJSON a => ToJSON (MSetAttr a) where toJSON = genericToJSON jsonOptions -instance FromJSON a => FromJSON (MSetAttr a) where parseJSON = genericParseJSON jsonOptions -instance Default (MSetAttr a) where def = MSetAttr def def -instance Pretty a => Pretty (MSetAttr a) where - pretty (MSetAttr a b) = - let inside = filter (/=prEmpty) [ pretty a - , pretty b - ] - in if null inside - then prEmpty - else prettyList prParens "," inside - - -data OccurAttr a - = OccurAttr_None - | OccurAttr_MinOccur a - | OccurAttr_MaxOccur a - | OccurAttr_MinMaxOccur a a - deriving (Eq, Ord, Show, Data, Functor, Traversable, Foldable, Typeable, Generic) -instance Serialize a => Serialize (OccurAttr a) -instance Hashable a => Hashable (OccurAttr a) -instance ToJSON a => ToJSON (OccurAttr a) where toJSON = genericToJSON jsonOptions -instance FromJSON a => FromJSON (OccurAttr a) where parseJSON = genericParseJSON jsonOptions -instance Default (OccurAttr a) where def = OccurAttr_None -instance Pretty a => Pretty (OccurAttr a) where - pretty OccurAttr_None = prEmpty - pretty (OccurAttr_MinOccur x ) = "minOccur" <+> pretty x - pretty (OccurAttr_MaxOccur x ) = "maxOccur" <+> pretty x - pretty (OccurAttr_MinMaxOccur x y) = "minOccur" <+> pretty x <> ", maxOccur" <+> pretty y - - -getMaxFrom_OccurAttr :: MonadFail m => OccurAttr a -> m a -getMaxFrom_OccurAttr (OccurAttr_MaxOccur n) = return n -getMaxFrom_OccurAttr (OccurAttr_MinMaxOccur _ n) = return n -getMaxFrom_OccurAttr _ = fail "getMaxFrom_OccurAttr" - - -data FunctionAttr x - = FunctionAttr (SizeAttr x) PartialityAttr JectivityAttr - deriving (Eq, Ord, Show, Data, Functor, Traversable, Foldable, Typeable, Generic) -instance Serialize a => Serialize (FunctionAttr a) -instance Hashable a => Hashable (FunctionAttr a) -instance ToJSON a => ToJSON (FunctionAttr a) where toJSON = genericToJSON jsonOptions -instance FromJSON a => FromJSON (FunctionAttr a) where parseJSON = genericParseJSON jsonOptions -instance Default (FunctionAttr a) where def = FunctionAttr def def def -instance Pretty a => Pretty (FunctionAttr a) where - pretty (FunctionAttr a b c) = - let inside = filter (/=prEmpty) [pretty a, pretty b, pretty c] - in if null inside - then prEmpty - else prettyList prParens "," inside - - -data PartialityAttr - = PartialityAttr_Partial - | PartialityAttr_Total - deriving (Eq, Ord, Show, Data, Typeable, Generic) -instance Serialize PartialityAttr -instance Hashable PartialityAttr -instance ToJSON PartialityAttr where toJSON = genericToJSON jsonOptions -instance FromJSON PartialityAttr where parseJSON = genericParseJSON jsonOptions -instance Default PartialityAttr where def = PartialityAttr_Partial -instance Pretty PartialityAttr where - pretty PartialityAttr_Partial = prEmpty -- partial is the default - pretty PartialityAttr_Total = "total" - - -data JectivityAttr - = JectivityAttr_None - | JectivityAttr_Injective - | JectivityAttr_Surjective - | JectivityAttr_Bijective - deriving (Eq, Ord, Show, Data, Typeable, Generic) -instance Serialize JectivityAttr -instance Hashable JectivityAttr -instance ToJSON JectivityAttr where toJSON = genericToJSON jsonOptions -instance FromJSON JectivityAttr where parseJSON = genericParseJSON jsonOptions -instance Default JectivityAttr where def = JectivityAttr_None -instance Pretty JectivityAttr where - pretty JectivityAttr_None = prEmpty - pretty JectivityAttr_Injective = "injective" - pretty JectivityAttr_Surjective = "surjective" - pretty JectivityAttr_Bijective = "bijective" - - -data SequenceAttr x - = SequenceAttr (SizeAttr x) JectivityAttr - deriving (Eq, Ord, Show, Data, Functor, Traversable, Foldable, Typeable, Generic) -instance Serialize a => Serialize (SequenceAttr a) -instance Hashable a => Hashable (SequenceAttr a) -instance ToJSON a => ToJSON (SequenceAttr a) where toJSON = genericToJSON jsonOptions -instance FromJSON a => FromJSON (SequenceAttr a) where parseJSON = genericParseJSON jsonOptions -instance Default (SequenceAttr a) where def = SequenceAttr def def -instance Pretty a => Pretty (SequenceAttr a) where - pretty (SequenceAttr a b) = - let inside = filter (/=prEmpty) [pretty a, pretty b] - in if null inside - then prEmpty - else prettyList prParens "," inside - - -data RelationAttr a = RelationAttr (SizeAttr a) BinaryRelationAttrs - deriving (Eq, Ord, Show, Data, Functor, Traversable, Foldable, Typeable, Generic) -instance Serialize a => Serialize (RelationAttr a) -instance Hashable a => Hashable (RelationAttr a) -instance ToJSON a => ToJSON (RelationAttr a) where toJSON = genericToJSON jsonOptions -instance FromJSON a => FromJSON (RelationAttr a) where parseJSON = genericParseJSON jsonOptions -instance Default (RelationAttr a) where def = RelationAttr def def -instance Pretty a => Pretty (RelationAttr a) where - pretty (RelationAttr a b) = - let inside = filter (/=prEmpty) [pretty a, pretty b] - in if null inside - then prEmpty - else prettyList prParens "," inside - - -data BinaryRelationAttrs = BinaryRelationAttrs (S.Set BinaryRelationAttr) - deriving (Eq, Ord, Show, Data, Typeable, Generic) -instance Serialize BinaryRelationAttrs -instance Hashable BinaryRelationAttrs where hashWithSalt salt (BinaryRelationAttrs a) = hashWithSalt salt (S.toList a) -instance ToJSON BinaryRelationAttrs where toJSON = genericToJSON jsonOptions -instance FromJSON BinaryRelationAttrs where parseJSON = genericParseJSON jsonOptions -instance Default BinaryRelationAttrs where def = BinaryRelationAttrs S.empty -instance Pretty BinaryRelationAttrs where - pretty (BinaryRelationAttrs attrs) = prettyList id "," (S.toList attrs) -instance Semigroup BinaryRelationAttrs where - (<>) = mappend -instance Monoid BinaryRelationAttrs where - mempty = BinaryRelationAttrs def - mappend (BinaryRelationAttrs a) (BinaryRelationAttrs b) = BinaryRelationAttrs (S.union a b) - - -data BinaryRelationAttr - = BinRelAttr_Reflexive - | BinRelAttr_Irreflexive - | BinRelAttr_Coreflexive - | BinRelAttr_Symmetric - | BinRelAttr_AntiSymmetric - | BinRelAttr_ASymmetric - | BinRelAttr_Transitive - | BinRelAttr_Total - | BinRelAttr_Connex - | BinRelAttr_Euclidean - | BinRelAttr_Serial - | BinRelAttr_Equivalence - | BinRelAttr_PartialOrder - deriving (Eq, Ord, Show, Data, Typeable, Generic) -instance Serialize BinaryRelationAttr -instance Hashable BinaryRelationAttr -instance ToJSON BinaryRelationAttr where toJSON = genericToJSON jsonOptions -instance FromJSON BinaryRelationAttr where parseJSON = genericParseJSON jsonOptions -instance Pretty BinaryRelationAttr where - pretty BinRelAttr_Reflexive = "reflexive" - pretty BinRelAttr_Irreflexive = "irreflexive" - pretty BinRelAttr_Coreflexive = "coreflexive" - pretty BinRelAttr_Symmetric = "symmetric" - pretty BinRelAttr_AntiSymmetric = "antiSymmetric" - pretty BinRelAttr_ASymmetric = "aSymmetric" - pretty BinRelAttr_Transitive = "transitive" - pretty BinRelAttr_Total = "total" - pretty BinRelAttr_Connex = "connex" - pretty BinRelAttr_Euclidean = "Euclidean" - pretty BinRelAttr_Serial = "serial" - pretty BinRelAttr_Equivalence = "equivalence" - pretty BinRelAttr_PartialOrder = "partialOrder" - -readBinRel :: MonadFail m => AttrName -> m BinaryRelationAttr -readBinRel AttrName_reflexive = return BinRelAttr_Reflexive -readBinRel AttrName_irreflexive = return BinRelAttr_Irreflexive -readBinRel AttrName_coreflexive = return BinRelAttr_Coreflexive -readBinRel AttrName_symmetric = return BinRelAttr_Symmetric -readBinRel AttrName_antiSymmetric = return BinRelAttr_AntiSymmetric -readBinRel AttrName_aSymmetric = return BinRelAttr_ASymmetric -readBinRel AttrName_transitive = return BinRelAttr_Transitive -readBinRel AttrName_total = return BinRelAttr_Total -readBinRel AttrName_connex = return BinRelAttr_Connex -readBinRel AttrName_Euclidean = return BinRelAttr_Euclidean -readBinRel AttrName_serial = return BinRelAttr_Serial -readBinRel AttrName_equivalence = return BinRelAttr_Equivalence -readBinRel AttrName_partialOrder = return BinRelAttr_PartialOrder -readBinRel a = fail $ "Not a binary relation attribute:" <+> pretty a - --- reflexive forAll x : T . rel(x,x) --- irreflexive forAll x : T . !rel(x,x) --- coreflexive forAll x,y : T . rel(x,y) -> x = y --- --- symmetric forAll x,y : T . rel(x,y) -> rel(y,x) --- antisymmetric forAll x,y : T . rel(x,y) /\ rel(y,x) -> x = y --- asymmetric forAll x,y : T . rel(x,y) -> !rel(y,x) --- --- transitive forAll x,y,z : T . rel(x,y) /\ rel(y,z) -> rel(x,z) --- --- total forAll x,y : T . rel(x,y) \/ rel(y,x) --- connex forAll x,y : T . rel(x,y) \/ rel(y,x) \/ x = y --- Euclidean forAll x,y,z : T . rel(x,y) /\ rel(x,z) -> rel(y,z) --- serial forAll x : T . exists y : T . rel(x,y) --- equivalence reflexive + symmetric + transitive --- partialOrder reflexive + antisymmetric + transitive - - -data PartitionAttr a = PartitionAttr - { partsNum :: SizeAttr a - , partsSize :: SizeAttr a - , isRegular :: Bool - } - deriving (Eq, Ord, Show, Data, Functor, Traversable, Foldable, Typeable, Generic) -instance Serialize a => Serialize (PartitionAttr a) -instance Hashable a => Hashable (PartitionAttr a) -instance ToJSON a => ToJSON (PartitionAttr a) where toJSON = genericToJSON jsonOptions -instance FromJSON a => FromJSON (PartitionAttr a) where parseJSON = genericParseJSON jsonOptions -instance Default (PartitionAttr a) where def = PartitionAttr def def False -instance Pretty a => Pretty (PartitionAttr a) where - pretty (PartitionAttr a b c) = - let inside = filter (/=prEmpty) [ prettyNum a - , prettySize b - , prettyReg c - ] - - prettyNum SizeAttr_None = prEmpty - prettyNum (SizeAttr_Size x ) = "numParts" <+> pretty x - prettyNum (SizeAttr_MinSize x ) = "minNumParts" <+> pretty x - prettyNum (SizeAttr_MaxSize x ) = "maxNumParts" <+> pretty x - prettyNum (SizeAttr_MinMaxSize x y) = "minNumParts" <+> pretty x <> ", maxNumParts" <+> pretty y - - prettySize SizeAttr_None = prEmpty - prettySize (SizeAttr_Size x ) = "partSize" <+> pretty x - prettySize (SizeAttr_MinSize x ) = "minPartSize" <+> pretty x - prettySize (SizeAttr_MaxSize x ) = "maxPartSize" <+> pretty x - prettySize (SizeAttr_MinMaxSize x y) = "minPartSize" <+> pretty x <> ", maxPartSize" <+> pretty y - - prettyReg False = prEmpty - prettyReg True = "regular" - - in if null inside - then prEmpty - else prettyList prParens "," inside - - - -data PermutationAttr x - = PermutationAttr (SizeAttr x) - deriving (Eq, Ord, Show, Data, Functor, Traversable, Foldable, Typeable, Generic) -instance Serialize a => Serialize (PermutationAttr a) -instance Hashable a => Hashable (PermutationAttr a) -instance ToJSON a => ToJSON (PermutationAttr a) where toJSON = genericToJSON jsonOptions -instance FromJSON a => FromJSON (PermutationAttr a) where parseJSON = genericParseJSON jsonOptions -instance Default (PermutationAttr a) where def = PermutationAttr def -instance Pretty a => Pretty (PermutationAttr a) where - pretty (PermutationAttr a ) = - let inside = filter (/=prEmpty) [pretty a] - in if null inside - then prEmpty - else prettyList prParens "," inside - - - - -data DomainAttributes a = DomainAttributes [DomainAttribute a] - deriving (Eq, Ord, Show, Data, Functor, Traversable, Foldable, Typeable, Generic) - -instance Serialize a => Serialize (DomainAttributes a) -instance Hashable a => Hashable (DomainAttributes a) -instance ToJSON a => ToJSON (DomainAttributes a) where toJSON = genericToJSON jsonOptions -instance FromJSON a => FromJSON (DomainAttributes a) where parseJSON = genericParseJSON jsonOptions - -instance Default (DomainAttributes a) where - def = DomainAttributes [] - - -data DomainAttribute a - = DAName Name - | DANameValue Name a - | DADotDot - deriving (Eq, Ord, Show, Data, Functor, Traversable, Foldable, Typeable, Generic) - -instance Serialize a => Serialize (DomainAttribute a) -instance Hashable a => Hashable (DomainAttribute a) -instance ToJSON a => ToJSON (DomainAttribute a) where toJSON = genericToJSON jsonOptions -instance FromJSON a => FromJSON (DomainAttribute a) where parseJSON = genericParseJSON jsonOptions - - -data Range a - = RangeOpen - | RangeSingle a - | RangeLowerBounded a - | RangeUpperBounded a - | RangeBounded a a - deriving (Eq, Ord, Show, Data, Functor, Traversable, Foldable, Typeable, Generic) - -instance Serialize a => Serialize (Range a) -instance Hashable a => Hashable (Range a) -instance ToJSON a => ToJSON (Range a) where toJSON = genericToJSON jsonOptions -instance FromJSON a => FromJSON (Range a) where parseJSON = genericParseJSON jsonOptions - -instance Arbitrary a => Arbitrary (Range a) where - arbitrary = oneof - [ return RangeOpen - , RangeSingle <$> arbitrary - , RangeLowerBounded <$> arbitrary - , RangeUpperBounded <$> arbitrary - , RangeBounded <$> arbitrary <*> arbitrary - ] - -rangesInts :: (MonadFail m, ExpressionLike c) => [Range c] -> m [Integer] -rangesInts = fmap (sortNub . concat) . mapM rangeInts - where - rangeInts (RangeSingle x) = return <$> intOut "rangeInts 1" x - rangeInts (RangeBounded x y) = do x' <- intOut "rangeInts 2" x - y' <- intOut "rangeInts 3" y - return [x' .. y'] - rangeInts _ = fail "Infinite range (or not an integer range)" - -expandRanges :: ExpressionLike c => [Range c] -> [Range c] -expandRanges r = - case rangesInts r of - Nothing -> r - Just [] -> [] - Just is -> - if [ minimum is .. maximum is ] == is - then [RangeBounded (fromInt (minimum is)) (fromInt (maximum is))] - else map (RangeSingle . fromInt) is - - -data HasRepresentation - = NoRepresentation - - | Set_Occurrence - | Set_Explicit - | Set_ExplicitVarSizeWithFlags - | Set_ExplicitVarSizeWithMarker - | Set_ExplicitVarSizeWithDummy - - | MSet_Occurrence - | MSet_ExplicitWithFlags - | MSet_ExplicitWithRepetition - - | Function_1D - | Function_1DPartial - | Function_ND - | Function_NDPartial - | Function_AsRelation HasRepresentation -- carries: representation for the inner relation - - | Sequence_ExplicitBounded - - | Relation_AsMatrix - | Relation_AsSet HasRepresentation -- carries: representation for the inner set - - | Partition_AsSet HasRepresentation HasRepresentation -- carries: representations for the inner sets - | Partition_Occurrence - | Permutation_AsFunction - - deriving (Eq, Ord, Show, Data, Typeable, Generic) - -instance Serialize HasRepresentation -instance Hashable HasRepresentation -instance ToJSON HasRepresentation where toJSON = genericToJSON jsonOptions -instance FromJSON HasRepresentation where parseJSON = genericParseJSON jsonOptions - -instance Default HasRepresentation where - def = NoRepresentation - -representationConstrIndex :: HasRepresentation -> [Text] -representationConstrIndex r = oneLevel r : concatMap representationConstrIndex (children r) - where - oneLevel :: HasRepresentation -> Text - oneLevel = stringToText . ("R"++) . show . constrIndex . toConstr - -instance (Pretty r, Pretty a) => Pretty (Domain r a) where - - pretty DomainAny{} = "?" - - pretty DomainBool = "bool" - - pretty (DomainIntE x) = "int" <> prParens (pretty x) - - pretty (DomainInt _ []) = "int" - - pretty (DomainInt _ ranges) = "int" <> prettyList prParens "," ranges - - pretty (DomainEnum name (Just ranges) _) = pretty name <> prettyList prParens "," ranges - - pretty (DomainEnum name _ _) = pretty name - - pretty (DomainUnnamed name _) = pretty name - - pretty (DomainTuple inners) - = (if length inners < 2 then "tuple" else prEmpty) - <+> prettyList prParens "," inners - - pretty (DomainRecord xs) = "record" <+> prettyList prBraces "," - [ pretty nm <+> ":" <+> pretty d | (nm, d) <- xs ] - - pretty (DomainVariant xs) = "variant" <+> prettyList prBraces "," - [ pretty nm <+> ":" <+> pretty d | (nm, d) <- xs ] - - pretty (DomainMatrix index innerNested) - = "matrix indexed by" <+> prettyList prBrackets "," indices - <+> "of" <+> pretty inner - where - (indices,inner) = first (index:) $ collect innerNested - collect (DomainMatrix i j) = first (i:) $ collect j - collect x = ([],x) - - pretty (DomainSet r attrs inner) = - hang ("set" <+> prettyAttrs r attrs <+> "of") 4 (pretty inner) - - pretty (DomainMSet r attrs inner) = - hang ("mset" <+> prettyAttrs r attrs <+> "of") 4 (pretty inner) - - pretty (DomainFunction r attrs innerFrom innerTo) = - hang ("function" <+> prettyAttrs r attrs) 4 $ - hang (pretty innerFrom) 4 $ - "-->" <+> pretty innerTo - - pretty (DomainSequence r attrs inner) = - hang ("sequence" <+> prettyAttrs r attrs <+> "of") 4 (pretty inner) - - pretty (DomainRelation r attrs inners) - = hang ("relation" <+> prettyAttrs r attrs <+> "of") 4 (prettyList prParens " *" inners) - - pretty (DomainPartition r attrs inner) - = hang ("partition" <+> prettyAttrs r attrs <+> "from") 4 (pretty inner) - pretty (DomainPermutation r attrs inner) = hang ("permutation" <+> prettyAttrs r attrs <+> "of") 4 (pretty inner) - - pretty d@DomainOp{} = pretty (show d) - - pretty (DomainReference x _) = pretty x - - pretty (DomainMetaVar x) = "&" <> pretty x - - -prettyAttrs :: (Pretty a, Pretty b) => a -> b -> Doc -prettyAttrs a bs = - let prettya = pretty a - in if prettya == "()" - then pretty bs - else prBraces prettya <+> pretty bs - -instance Pretty a => Pretty (DomainAttributes a) where - pretty (DomainAttributes []) = prEmpty - pretty (DomainAttributes attrs) = prettyList prParens "," attrs - -instance Pretty a => Pretty (DomainAttribute a) where - pretty (DAName name) = pretty name - pretty (DANameValue name value) = pretty name <+> pretty value - pretty DADotDot = ".." - -instance Pretty a => Pretty (Range a) where - pretty RangeOpen = ".." - pretty (RangeSingle x) = pretty x - pretty (RangeLowerBounded x) = pretty x <> ".." - pretty (RangeUpperBounded x) = ".." <> pretty x - pretty (RangeBounded x y) | show (pretty x) == show (pretty y) = pretty x - pretty (RangeBounded x y) = pretty x <> ".." <> pretty y - -instance Pretty HasRepresentation where - pretty NoRepresentation = "∅" - pretty r = pretty (representationToFullText r) - -textToRepresentation :: Text -> [HasRepresentation] -> Maybe HasRepresentation -textToRepresentation t [] | t == "Occurrence" = return Set_Occurrence -textToRepresentation t [] | t == "Explicit" = return Set_Explicit -textToRepresentation t [] | t == "ExplicitVarSizeWithFlags" = return Set_ExplicitVarSizeWithFlags -textToRepresentation t [] | t == "ExplicitVarSizeWithMarker" = return Set_ExplicitVarSizeWithMarker -textToRepresentation t [] | t == "ExplicitVarSizeWithDummy" = return Set_ExplicitVarSizeWithDummy -textToRepresentation t [] | t == "MOccurrence" = return MSet_Occurrence -textToRepresentation t [] | t == "ExplicitWithFlags" = return MSet_ExplicitWithFlags -textToRepresentation t [] | t == "ExplicitWithRepetition" = return MSet_ExplicitWithRepetition -textToRepresentation t [] | t == "Function1D" = return Function_1D -textToRepresentation t [] | t == "Function1DPartial" = return Function_1DPartial -textToRepresentation t [] | t == "FunctionND" = return Function_ND -textToRepresentation t [] | t == "FunctionNDPartial" = return Function_NDPartial -textToRepresentation t [repr] | t == "FunctionAsRelation" = return (Function_AsRelation repr) -textToRepresentation t [] | t == "ExplicitBounded" = return Sequence_ExplicitBounded -textToRepresentation t [] | t == "RelationAsMatrix" = return Relation_AsMatrix -textToRepresentation t [repr] | t == "RelationAsSet" = return (Relation_AsSet repr) -textToRepresentation t [repr1, repr2] | t == "PartitionAsSet" = return (Partition_AsSet repr1 repr2) -textToRepresentation t [] | t == "PartitionOccurrence" = return Partition_Occurrence -textToRepresentation t [] | t == "PermutationAsFunction" = return Permutation_AsFunction -textToRepresentation t _ = bug ("textToRepresentation:" <+> pretty t) - -representationToShortText :: HasRepresentation -> Text -representationToShortText Set_Occurrence = "Occurrence" -representationToShortText Set_Explicit = "Explicit" -representationToShortText Set_ExplicitVarSizeWithFlags = "ExplicitVarSizeWithFlags" -representationToShortText Set_ExplicitVarSizeWithMarker = "ExplicitVarSizeWithMarker" -representationToShortText Set_ExplicitVarSizeWithDummy = "ExplicitVarSizeWithDummy" -representationToShortText MSet_Occurrence = "MOccurrence" -representationToShortText MSet_ExplicitWithFlags = "ExplicitWithFlags" -representationToShortText MSet_ExplicitWithRepetition = "ExplicitWithRepetition" -representationToShortText Function_1D = "Function1D" -representationToShortText Function_1DPartial = "Function1DPartial" -representationToShortText Function_ND = "FunctionND" -representationToShortText Function_NDPartial = "FunctionNDPartial" -representationToShortText Function_AsRelation{} = "FunctionAsRelation" -representationToShortText Sequence_ExplicitBounded = "ExplicitBounded" -representationToShortText Relation_AsMatrix = "RelationAsMatrix" -representationToShortText Relation_AsSet{} = "RelationAsSet" -representationToShortText Partition_AsSet{} = "PartitionAsSet" -representationToShortText Partition_Occurrence = "PartitionOccurrence" -representationToShortText Permutation_AsFunction = "PermutationAsFunction" -representationToShortText r = bug ("representationToShortText:" <+> pretty (show r)) - -representationToFullText :: HasRepresentation -> Text -representationToFullText (Function_AsRelation repr) = mconcat [ "FunctionAsRelation" - , "[" - , representationToFullText repr - , "]" - ] -representationToFullText (Relation_AsSet repr) = mconcat [ "RelationAsSet" - , "[" - , representationToFullText repr - , "]" - ] -representationToFullText (Partition_AsSet repr1 repr2) = mconcat [ "PartitionAsSet" - , "[" - , representationToFullText repr1 - , "," - , representationToFullText repr2 - , "]" - ] -representationToFullText r = representationToShortText r - - -normaliseDomain :: (Ord c, ExpressionLike c) => (c -> c) -> Domain r c -> Domain r c -normaliseDomain _norm DomainBool = DomainBool -normaliseDomain norm (DomainInt t rs ) = DomainInt t $ sort $ map (normaliseRange norm) (expandRanges rs) -normaliseDomain _norm (DomainEnum n Nothing mp) = DomainEnum n Nothing mp -normaliseDomain _norm (DomainEnum n (Just rs) mp) = DomainEnum n (Just $ sort rs) mp -normaliseDomain norm (DomainUnnamed n x ) = DomainUnnamed n (norm x) -normaliseDomain norm (DomainRecord doms ) = DomainRecord [ (n, normaliseDomain norm d) - | (n, d) <- doms ] -normaliseDomain norm (DomainVariant doms ) = DomainVariant [ (n, normaliseDomain norm d) - | (n, d) <- doms ] -normaliseDomain norm (DomainTuple doms ) = DomainTuple $ map (normaliseDomain norm) doms -normaliseDomain norm (DomainMatrix dom1 dom2) = DomainMatrix (normaliseDomain norm dom1) - (normaliseDomain norm dom2) -normaliseDomain norm (DomainSet r attr dom ) = DomainSet r (fmap norm attr) - (normaliseDomain norm dom) -normaliseDomain norm (DomainMSet r attr dom ) = DomainMSet r (fmap norm attr) - (normaliseDomain norm dom) -normaliseDomain norm (DomainFunction r attr dom1 dom2) = DomainFunction r (fmap norm attr) - (normaliseDomain norm dom1) - (normaliseDomain norm dom2) -normaliseDomain norm (DomainSequence r attr dom ) = DomainSequence r (fmap norm attr) - (normaliseDomain norm dom) -normaliseDomain norm (DomainRelation r attr doms ) = DomainRelation r (fmap norm attr) - (map (normaliseDomain norm) doms) -normaliseDomain norm (DomainPartition r attr dom ) = DomainPartition r (fmap norm attr) - (normaliseDomain norm dom) -normaliseDomain _norm d = d - -normaliseRange :: (c -> c) -> Range c -> Range c -normaliseRange _norm RangeOpen = RangeOpen -normaliseRange norm (RangeSingle x) = RangeBounded (norm x) (norm x) -normaliseRange norm (RangeLowerBounded x) = RangeLowerBounded (norm x) -normaliseRange norm (RangeUpperBounded x) = RangeUpperBounded (norm x) -normaliseRange norm (RangeBounded x y) = RangeBounded (norm x) (norm y) - -innerDomainOf :: (MonadFail m, Show x) => Domain () x -> m (Domain () x) -innerDomainOf (DomainMatrix _ t) = return t -innerDomainOf (DomainSet _ _ t) = return t -innerDomainOf (DomainMSet _ _ t) = return t -innerDomainOf (DomainFunction _ _ a b) = return (DomainTuple [a,b]) -innerDomainOf (DomainRelation _ _ ts) = return (DomainTuple ts) -innerDomainOf (DomainPartition _ _ t) = return (DomainSet () def t) -innerDomainOf t = fail ("innerDomainOf:" <+> pretty (show t)) - -singletonDomainInt :: (Eq x, CanBeAnAlias x) => Domain r x -> Maybe x -singletonDomainInt (DomainInt _ [RangeSingle a]) = Just a -singletonDomainInt (DomainInt _ [RangeBounded a b]) = - let - followAlias (isAlias -> Just x) = followAlias x - followAlias x = x - in - if followAlias a == followAlias b - then Just a - else Nothing -singletonDomainInt _ = Nothing - -matrixNumDimsD :: Domain r x -> Int -matrixNumDimsD (DomainMatrix _ t) = 1 + matrixNumDimsD t -matrixNumDimsD _ = 0 - diff --git a/src/Conjure/Language/Domain_REMOTE_22702.hs b/src/Conjure/Language/Domain_REMOTE_22702.hs deleted file mode 100644 index 8de4bc5dec..0000000000 --- a/src/Conjure/Language/Domain_REMOTE_22702.hs +++ /dev/null @@ -1,1029 +0,0 @@ -{-# LANGUAGE DeriveGeneric, DeriveDataTypeable, DeriveFunctor, DeriveTraversable, DeriveFoldable #-} -{-# LANGUAGE TupleSections #-} -{-# LANGUAGE NoMonomorphismRestriction #-} -{-# LANGUAGE ViewPatterns #-} - -module Conjure.Language.Domain - ( Domain(..) - , HasRepresentation(..) - , Range(..), rangesInts - , SetAttr(..), SizeAttr(..), getMaxFrom_SizeAttr - , MSetAttr(..), OccurAttr(..), getMaxFrom_OccurAttr - , FunctionAttr(..), PartialityAttr(..), JectivityAttr(..) - , SequenceAttr(..) - , RelationAttr(..), BinaryRelationAttrs(..), BinaryRelationAttr(..) - , PartitionAttr(..) - , AttrName(..) - , DomainAttributes(..), DomainAttribute(..) -- only for parsing - , textToRepresentation, representationToShortText, representationToFullText - , isPrimitiveDomain, domainCanIndexMatrix, getIndices - , Tree(..), reprTree, reprAtTopLevel, applyReprTree - , reprTreeEncoded - , forgetRepr, changeRepr, defRepr - , mkDomainBool, mkDomainInt, mkDomainIntB, mkDomainIntBTagged, mkDomainAny - , typeOfDomain - , readBinRel, binRelToAttrName - , normaliseDomain, normaliseRange - , innerDomainOf - , singletonDomainInt - , matrixNumDimsD - ) where - --- conjure -import Conjure.Prelude -import Conjure.Bug -import Conjure.Language.Name -import Conjure.Language.Type -import Conjure.Language.TypeOf -import Conjure.Language.AdHoc -import Conjure.Language.Pretty - --- base -import qualified Data.Semigroup as Semigroup ( (<>) ) - --- QuickCheck -import Test.QuickCheck ( Arbitrary(..), choose, oneof, vectorOf, sized ) - --- containers -import Data.Set as S ( Set, empty, toList, union ) - --- syb -import Data.Data ( toConstr, constrIndex ) - - -data Domain r x - = DomainAny Text Type - | DomainBool - | DomainIntE x - | DomainInt IntTag [Range x] - | DomainEnum - Name - (Maybe [Range x]) -- subset of values for this domain - -- Nothing *only* when GivenDomainDefnEnum and not LettingDomainDefnEnum - (Maybe [(Name, Integer)]) -- the mapping to integers, if available - | DomainUnnamed Name x - | DomainTuple [Domain r x] - | DomainRecord [(Name, Domain r x)] - | DomainVariant [(Name, Domain r x)] - | DomainMatrix (Domain () x) (Domain r x) - | DomainSet r (SetAttr x) (Domain r x) - | DomainMSet r (MSetAttr x) (Domain r x) - | DomainFunction r (FunctionAttr x) (Domain r x) (Domain r x) - | DomainSequence r (SequenceAttr x) (Domain r x) - | DomainRelation r (RelationAttr x) [Domain r x] - | DomainPartition r (PartitionAttr x) (Domain r x) - | DomainOp Name [Domain r x] - | DomainReference Name (Maybe (Domain r x)) - | DomainMetaVar String - deriving (Eq, Ord, Show, Data, Functor, Traversable, Foldable, Typeable, Generic) - -instance (VarSymBreakingDescription x, ToJSON r) => VarSymBreakingDescription (Domain r x) where - varSymBreakingDescription domain = toJSON $ fmap varSymBreakingDescription domain - -mkDomainBool :: Domain () x -mkDomainBool = DomainBool - -mkDomainInt :: [Range x] -> Domain () x -mkDomainInt = DomainInt TagInt - -mkDomainIntB :: x -> x -> Domain () x -mkDomainIntB l u = DomainInt TagInt [RangeBounded l u] - -mkDomainIntBTagged :: IntTag -> x -> x -> Domain () x -mkDomainIntBTagged t l u = DomainInt t [RangeBounded l u] - -mkDomainAny :: Doc -> Type -> Domain r x -mkDomainAny reason = DomainAny (stringToText $ show reason) - -instance (Serialize r, Serialize x) => Serialize (Domain r x) -instance (Hashable r, Hashable x) => Hashable (Domain r x) -instance (ToJSON r, ToJSON x) => ToJSON (Domain r x) where toJSON = genericToJSON jsonOptions -instance (FromJSON r, FromJSON x) => FromJSON (Domain r x) where parseJSON = genericParseJSON jsonOptions - -instance Arbitrary x => Arbitrary (Domain r x) where - arbitrary = sized f - where - f 0 = oneof [ return DomainBool - , DomainInt TagInt <$> arbitrary - -- , DomainEnum <$> arbitrary <*> arbitrary - ] - f s = do - arity <- choose (2 :: Int, 10) - DomainTuple <$> vectorOf arity (f (div s 10)) - shrink DomainBool = [] - shrink (DomainInt _ []) = [DomainBool] - shrink (DomainInt t [r]) = DomainBool : DomainInt t [] : [DomainInt t [r'] | r' <- shrink r] - shrink (DomainInt t rs) = [DomainInt t (init rs)] - shrink _ = [] - - -typeOfDomain :: - MonadFail m => - Pretty r => - TypeOf x => - Pretty x => - (?typeCheckerMode :: TypeCheckerMode) => - Domain r x -> m Type -typeOfDomain (DomainAny _ ty) = return ty -typeOfDomain DomainBool = return TypeBool -typeOfDomain d@(DomainIntE x) = do - ty <- typeOf x - case ty of - TypeInt{} -> return () -- pre recoverDomainInt - TypeList TypeInt{} -> return () - TypeMatrix _ TypeInt{} -> return () - TypeSet TypeInt{} -> return () - _ -> fail $ vcat [ "Expected an integer, but got:" <++> pretty ty - , "In domain:" <+> pretty d - ] - return (TypeInt TagInt) -typeOfDomain d@(DomainInt t rs) = do - forM_ rs $ \ r -> forM_ r $ \ x -> do - ty <- typeOf x - case ty of - TypeInt{} -> return () - _ -> fail $ vcat [ "Expected an integer, but got:" <++> pretty ty - , "For:" <+> pretty x - , "In domain:" <+> pretty d - ] - return (TypeInt t) -typeOfDomain (DomainEnum defn _ _ ) = return (TypeEnum defn) -typeOfDomain (DomainUnnamed defn _ ) = return (TypeUnnamed defn) -typeOfDomain (DomainTuple xs ) = TypeTuple <$> mapM typeOfDomain xs -typeOfDomain (DomainRecord xs ) = TypeRecord <$> sequence [ do t <- typeOfDomain d ; return (n, t) - | (n,d) <- xs ] -typeOfDomain (DomainVariant xs ) = TypeVariant <$> sequence [ do t <- typeOfDomain d ; return (n, t) - | (n,d) <- xs ] -typeOfDomain (DomainMatrix ind inn ) = TypeMatrix <$> typeOfDomain ind <*> typeOfDomain inn -typeOfDomain (DomainSet _ _ x ) = TypeSet <$> typeOfDomain x -typeOfDomain (DomainMSet _ _ x ) = TypeMSet <$> typeOfDomain x -typeOfDomain (DomainFunction _ _ x y) = TypeFunction <$> typeOfDomain x <*> typeOfDomain y -typeOfDomain (DomainSequence _ _ x ) = TypeSequence <$> typeOfDomain x -typeOfDomain (DomainRelation _ _ xs ) = TypeRelation <$> mapM typeOfDomain xs -typeOfDomain (DomainPartition _ _ x ) = TypePartition <$> typeOfDomain x -typeOfDomain p@(DomainOp _ ds) = do - ts <- mapM typeOfDomain ds - if typesUnify ts - then return (mostDefined ts) - else fail ("Type error in" <+> pretty p) -typeOfDomain (DomainReference _ (Just d)) = typeOfDomain d -typeOfDomain (DomainReference nm Nothing) = bug $ "typeOfDomain: DomainReference" <+> pretty nm -typeOfDomain (DomainMetaVar nm) = bug $ "typeOfDomain: DomainMetaVar &" <> pretty nm - -forgetRepr :: Domain r x -> Domain () x -forgetRepr = defRepr - -defRepr :: Default r2 => Domain r x -> Domain r2 x -defRepr = changeRepr def - -changeRepr :: r2 -> Domain r x -> Domain r2 x -changeRepr rep = go - where - go (DomainAny t ty) = DomainAny t ty - go DomainBool = DomainBool - go (DomainIntE x) = DomainIntE x - go (DomainInt t rs) = DomainInt t rs - go (DomainEnum defn rs mp) = DomainEnum defn rs mp - go (DomainUnnamed defn s) = DomainUnnamed defn s - go (DomainTuple ds) = DomainTuple (map go ds) - go (DomainRecord xs) = DomainRecord (map (second go) xs) - go (DomainVariant xs) = DomainVariant (map (second go) xs) - go (DomainMatrix index inner) = DomainMatrix index (go inner) - go (DomainSet _ attr d) = - DomainSet rep attr (go d) - go (DomainMSet _ attr d) = - DomainMSet rep attr (go d) - go (DomainFunction _ attr d1 d2) = - DomainFunction rep attr (go d1) (go d2) - go (DomainSequence _ attr d) = - DomainSequence rep attr (go d) - go (DomainRelation _ attr ds) = - DomainRelation rep attr (map go ds) - go (DomainPartition _ attr d) = - DomainPartition rep attr (go d) - go (DomainOp op ds) = DomainOp op (map go ds) - go (DomainReference x r) = DomainReference x (fmap go r) - go (DomainMetaVar x) = DomainMetaVar x - - -data Tree a = Tree { rootLabel :: a, subForest :: [Tree a] } - deriving (Eq, Ord, Show, Data, Functor, Traversable, Foldable, Typeable, Generic) - -instance Serialize a => Serialize (Tree a) -instance Hashable a => Hashable (Tree a) -instance ToJSON a => ToJSON (Tree a) where toJSON = genericToJSON jsonOptions -instance FromJSON a => FromJSON (Tree a) where parseJSON = genericParseJSON jsonOptions - --- | This is to be used when defining `Conjure.Representations.Internal.mkOutName`. --- Reason is to avoid sharing variables for parts of the same decision variable with differing representations. --- Example case: --- (1) find x : set {A} of (int(a..b) , set {B} of int(c..d)) --- (2) find x : set {A} of (int(a..b) , set {C} of int(c..d)) --- Here x_1's should not be shared! --- If they are, the channelling and symmetry breaking constraints will clash and solutions will be lost. -reprTreeEncoded :: Domain HasRepresentation x -> Text -reprTreeEncoded = mconcat . enc1 . reprTree - where - enc1 (Tree lbl sub) = - maybe - (bug "reprTreeEncoded: top-most representation is Nothing") - representationToShortText - lbl - : concatMap enc sub - enc (Tree lbl sub) = - maybe [] representationConstrIndex lbl - ++ concatMap enc sub - -reprTree :: Domain r x -> Tree (Maybe r) -reprTree DomainAny{} = Tree Nothing [] -reprTree DomainBool{} = Tree Nothing [] -reprTree DomainIntE{} = Tree Nothing [] -reprTree DomainInt{} = Tree Nothing [] -reprTree DomainEnum{} = Tree Nothing [] -reprTree DomainUnnamed{} = Tree Nothing [] -reprTree (DomainTuple as ) = Tree Nothing (map reprTree as) -reprTree (DomainRecord as ) = Tree Nothing (map (reprTree . snd) as) -reprTree (DomainVariant as) = Tree Nothing (map (reprTree . snd) as) -reprTree (DomainMatrix _ a) = Tree Nothing [reprTree a] -reprTree (DomainSet r _ a ) = Tree (Just r) [reprTree a] -reprTree (DomainMSet r _ a ) = Tree (Just r) [reprTree a] -reprTree (DomainFunction r _ a b) = Tree (Just r) [reprTree a, reprTree b] -reprTree (DomainSequence r _ a ) = Tree (Just r) [reprTree a] -reprTree (DomainRelation r _ as ) = Tree (Just r) (map reprTree as) -reprTree (DomainPartition r _ a ) = Tree (Just r) [reprTree a] -reprTree DomainOp{} = Tree Nothing [] -reprTree DomainReference{} = Tree Nothing [] -reprTree DomainMetaVar{} = Tree Nothing [] - -reprAtTopLevel :: Domain r x -> Maybe r -reprAtTopLevel = rootLabel . reprTree - -applyReprTree :: (MonadFail m, Pretty x, Pretty r2, Default r) => Domain r2 x -> Tree (Maybe r) -> m (Domain r x) -applyReprTree dom@DomainBool{} (Tree Nothing []) = return (defRepr dom) -applyReprTree dom@DomainInt{} (Tree Nothing []) = return (defRepr dom) -applyReprTree dom@DomainIntE{} (Tree Nothing []) = return (defRepr dom) -applyReprTree dom@DomainEnum{} (Tree Nothing []) = return (defRepr dom) -applyReprTree dom@DomainUnnamed{} (Tree Nothing []) = return (defRepr dom) -applyReprTree (DomainTuple as ) (Tree Nothing asRepr) = - DomainTuple <$> zipWithM applyReprTree as asRepr -applyReprTree (DomainRecord as ) (Tree Nothing asRepr) = - (DomainRecord . zip (map fst as)) <$> zipWithM applyReprTree (map snd as) asRepr -applyReprTree (DomainVariant as) (Tree Nothing asRepr) = - (DomainVariant . zip (map fst as)) <$> zipWithM applyReprTree (map snd as) asRepr -applyReprTree (DomainMatrix b a) (Tree Nothing [aRepr]) = DomainMatrix b <$> applyReprTree a aRepr -applyReprTree (DomainSet _ attr a ) (Tree (Just r) [aRepr]) = DomainSet r attr <$> applyReprTree a aRepr -applyReprTree (DomainMSet _ attr a ) (Tree (Just r) [aRepr]) = DomainMSet r attr <$> applyReprTree a aRepr -applyReprTree (DomainFunction _ attr a b) (Tree (Just r) [aRepr, bRepr]) = DomainFunction r attr <$> applyReprTree a aRepr <*> applyReprTree b bRepr -applyReprTree (DomainSequence _ attr a ) (Tree (Just r) [aRepr]) = DomainSequence r attr <$> applyReprTree a aRepr -applyReprTree (DomainRelation _ attr as ) (Tree (Just r) asRepr) = DomainRelation r attr <$> zipWithM applyReprTree as asRepr -applyReprTree (DomainPartition _ attr a ) (Tree (Just r) [aRepr]) = DomainPartition r attr <$> applyReprTree a aRepr -applyReprTree dom@DomainOp{} (Tree Nothing []) = return (defRepr dom) -applyReprTree dom@DomainReference{} (Tree Nothing []) = return (defRepr dom) -applyReprTree dom@DomainMetaVar{} (Tree Nothing []) = return (defRepr dom) -applyReprTree dom _ = fail $ "applyReprTree:" <++> pretty dom - -isPrimitiveDomain :: Domain r x -> Bool -isPrimitiveDomain DomainBool{} = True -isPrimitiveDomain DomainIntE{} = True -isPrimitiveDomain DomainInt{} = True -isPrimitiveDomain (DomainMatrix index inner) = and [isPrimitiveDomain index, isPrimitiveDomain inner] -isPrimitiveDomain _ = False - -getIndices :: Domain r x -> ([Domain () x], Domain r x) -getIndices (DomainMatrix index inner) = first (index:) (getIndices inner) -getIndices d = ([], d) - -domainCanIndexMatrix :: Domain r x -> Bool -domainCanIndexMatrix DomainBool{} = True -domainCanIndexMatrix DomainInt {} = True -domainCanIndexMatrix DomainIntE{} = True -domainCanIndexMatrix DomainEnum{} = True -domainCanIndexMatrix _ = False - - --------------------------------------------------------------------------------- --- attribute-as-constraint handling -------------------------------------------- --------------------------------------------------------------------------------- - -data AttrName - = AttrName_size - | AttrName_minSize - | AttrName_maxSize - | AttrName_minOccur - | AttrName_maxOccur - | AttrName_numParts - | AttrName_minNumParts - | AttrName_maxNumParts - | AttrName_partSize - | AttrName_minPartSize - | AttrName_maxPartSize - | AttrName_total - | AttrName_injective - | AttrName_surjective - | AttrName_bijective - | AttrName_regular - -- bin rel ones - | AttrName_reflexive - | AttrName_irreflexive - | AttrName_coreflexive - | AttrName_symmetric - | AttrName_antiSymmetric - | AttrName_aSymmetric - | AttrName_transitive - | AttrName_connex - | AttrName_Euclidean - | AttrName_serial - | AttrName_equivalence - | AttrName_partialOrder - deriving (Eq, Ord, Show, Data, Typeable, Generic) - -instance Serialize AttrName -instance Hashable AttrName -instance ToJSON AttrName where toJSON = genericToJSON jsonOptions -instance FromJSON AttrName where parseJSON = genericParseJSON jsonOptions - -instance Pretty AttrName where - pretty AttrName_size = "size" - pretty AttrName_minSize = "minSize" - pretty AttrName_maxSize = "maxSize" - pretty AttrName_minOccur = "minOccur" - pretty AttrName_maxOccur = "maxOccur" - pretty AttrName_numParts = "numParts" - pretty AttrName_minNumParts = "minNumParts" - pretty AttrName_maxNumParts = "maxNumParts" - pretty AttrName_partSize = "partSize" - pretty AttrName_minPartSize = "minPartSize" - pretty AttrName_maxPartSize = "maxPartSize" - pretty AttrName_total = "total" - pretty AttrName_injective = "injective" - pretty AttrName_surjective = "surjective" - pretty AttrName_bijective = "bijective" - pretty AttrName_regular = "regular" - pretty AttrName_reflexive = "reflexive" - pretty AttrName_irreflexive = "irreflexive" - pretty AttrName_coreflexive = "coreflexive" - pretty AttrName_symmetric = "symmetric" - pretty AttrName_antiSymmetric = "antiSymmetric" - pretty AttrName_aSymmetric = "aSymmetric" - pretty AttrName_transitive = "transitive" - pretty AttrName_connex = "connex" - pretty AttrName_Euclidean = "Euclidean" - pretty AttrName_serial = "serial" - pretty AttrName_equivalence = "equivalence" - pretty AttrName_partialOrder = "partialOrder" - -instance IsString AttrName where - fromString "size" = AttrName_size - fromString "minSize" = AttrName_minSize - fromString "maxSize" = AttrName_maxSize - fromString "minOccur" = AttrName_minOccur - fromString "maxOccur" = AttrName_maxOccur - fromString "numParts" = AttrName_numParts - fromString "minNumParts" = AttrName_minNumParts - fromString "maxNumParts" = AttrName_maxNumParts - fromString "partSize" = AttrName_partSize - fromString "minPartSize" = AttrName_minPartSize - fromString "maxPartSize" = AttrName_maxPartSize - fromString "total" = AttrName_total - fromString "injective" = AttrName_injective - fromString "surjective" = AttrName_surjective - fromString "bijective" = AttrName_bijective - fromString "regular" = AttrName_regular - fromString "reflexive" = AttrName_reflexive - fromString "irreflexive" = AttrName_irreflexive - fromString "coreflexive" = AttrName_coreflexive - fromString "symmetric" = AttrName_symmetric - fromString "antiSymmetric" = AttrName_antiSymmetric - fromString "aSymmetric" = AttrName_aSymmetric - fromString "transitive" = AttrName_transitive - fromString "connex" = AttrName_connex - fromString "Euclidean" = AttrName_Euclidean - fromString "serial" = AttrName_serial - fromString "equivalence" = AttrName_equivalence - fromString "partialOrder" = AttrName_partialOrder - fromString s = bug $ "fromString{AttrName}:" <+> pretty s - - --------------------------------------------------------------------------------- --- attribute definitions ------------------------------------------------------- --------------------------------------------------------------------------------- - -data SetAttr a = SetAttr (SizeAttr a) - deriving (Eq, Ord, Show, Data, Functor, Traversable, Foldable, Typeable, Generic) -instance Serialize a => Serialize (SetAttr a) -instance Hashable a => Hashable (SetAttr a) -instance ToJSON a => ToJSON (SetAttr a) where toJSON = genericToJSON jsonOptions -instance FromJSON a => FromJSON (SetAttr a) where parseJSON = genericParseJSON jsonOptions -instance Default (SetAttr a) where def = SetAttr def -instance Pretty a => Pretty (SetAttr a) where - pretty (SetAttr SizeAttr_None) = prEmpty - pretty (SetAttr a) = prParens (pretty a) - - -data SizeAttr a - = SizeAttr_None - | SizeAttr_Size a - | SizeAttr_MinSize a - | SizeAttr_MaxSize a - | SizeAttr_MinMaxSize a a - deriving (Eq, Ord, Show, Data, Functor, Traversable, Foldable, Typeable, Generic) -instance Serialize a => Serialize (SizeAttr a) -instance Hashable a => Hashable (SizeAttr a) -instance ToJSON a => ToJSON (SizeAttr a) where toJSON = genericToJSON jsonOptions -instance FromJSON a => FromJSON (SizeAttr a) where parseJSON = genericParseJSON jsonOptions -instance Default (SizeAttr a) where def = SizeAttr_None -instance Pretty a => Pretty (SizeAttr a) where - pretty SizeAttr_None = prEmpty - pretty (SizeAttr_Size x ) = "size" <+> pretty x - pretty (SizeAttr_MinSize x ) = "minSize" <+> pretty x - pretty (SizeAttr_MaxSize x ) = "maxSize" <+> pretty x - pretty (SizeAttr_MinMaxSize x y) = "minSize" <+> pretty x <> ", maxSize" <+> pretty y - - -getMaxFrom_SizeAttr :: MonadFail m => SizeAttr a -> m a -getMaxFrom_SizeAttr (SizeAttr_Size n) = return n -getMaxFrom_SizeAttr (SizeAttr_MaxSize n) = return n -getMaxFrom_SizeAttr (SizeAttr_MinMaxSize _ n) = return n -getMaxFrom_SizeAttr _ = fail "getMaxFrom_SizeAttr" - - -data MSetAttr a = MSetAttr (SizeAttr a) (OccurAttr a) - deriving (Eq, Ord, Show, Data, Functor, Traversable, Foldable, Typeable, Generic) -instance Serialize a => Serialize (MSetAttr a) -instance Hashable a => Hashable (MSetAttr a) -instance ToJSON a => ToJSON (MSetAttr a) where toJSON = genericToJSON jsonOptions -instance FromJSON a => FromJSON (MSetAttr a) where parseJSON = genericParseJSON jsonOptions -instance Default (MSetAttr a) where def = MSetAttr def def -instance Pretty a => Pretty (MSetAttr a) where - pretty (MSetAttr a b) = - let inside = filter (/=prEmpty) [ pretty a - , pretty b - ] - in if null inside - then prEmpty - else prettyList prParens "," inside - - -data OccurAttr a - = OccurAttr_None - | OccurAttr_MinOccur a - | OccurAttr_MaxOccur a - | OccurAttr_MinMaxOccur a a - deriving (Eq, Ord, Show, Data, Functor, Traversable, Foldable, Typeable, Generic) -instance Serialize a => Serialize (OccurAttr a) -instance Hashable a => Hashable (OccurAttr a) -instance ToJSON a => ToJSON (OccurAttr a) where toJSON = genericToJSON jsonOptions -instance FromJSON a => FromJSON (OccurAttr a) where parseJSON = genericParseJSON jsonOptions -instance Default (OccurAttr a) where def = OccurAttr_None -instance Pretty a => Pretty (OccurAttr a) where - pretty OccurAttr_None = prEmpty - pretty (OccurAttr_MinOccur x ) = "minOccur" <+> pretty x - pretty (OccurAttr_MaxOccur x ) = "maxOccur" <+> pretty x - pretty (OccurAttr_MinMaxOccur x y) = "minOccur" <+> pretty x <> ", maxOccur" <+> pretty y - - -getMaxFrom_OccurAttr :: MonadFail m => OccurAttr a -> m a -getMaxFrom_OccurAttr (OccurAttr_MaxOccur n) = return n -getMaxFrom_OccurAttr (OccurAttr_MinMaxOccur _ n) = return n -getMaxFrom_OccurAttr _ = fail "getMaxFrom_OccurAttr" - - -data FunctionAttr x - = FunctionAttr (SizeAttr x) PartialityAttr JectivityAttr - deriving (Eq, Ord, Show, Data, Functor, Traversable, Foldable, Typeable, Generic) -instance Serialize a => Serialize (FunctionAttr a) -instance Hashable a => Hashable (FunctionAttr a) -instance ToJSON a => ToJSON (FunctionAttr a) where toJSON = genericToJSON jsonOptions -instance FromJSON a => FromJSON (FunctionAttr a) where parseJSON = genericParseJSON jsonOptions -instance Default (FunctionAttr a) where def = FunctionAttr def def def -instance Pretty a => Pretty (FunctionAttr a) where - pretty (FunctionAttr a b c) = - let inside = filter (/=prEmpty) [pretty a, pretty b, pretty c] - in if null inside - then prEmpty - else prettyList prParens "," inside - - -data PartialityAttr - = PartialityAttr_Partial - | PartialityAttr_Total - deriving (Eq, Ord, Show, Data, Typeable, Generic) -instance Serialize PartialityAttr -instance Hashable PartialityAttr -instance ToJSON PartialityAttr where toJSON = genericToJSON jsonOptions -instance FromJSON PartialityAttr where parseJSON = genericParseJSON jsonOptions -instance Default PartialityAttr where def = PartialityAttr_Partial -instance Pretty PartialityAttr where - pretty PartialityAttr_Partial = prEmpty -- partial is the default - pretty PartialityAttr_Total = "total" - - -data JectivityAttr - = JectivityAttr_None - | JectivityAttr_Injective - | JectivityAttr_Surjective - | JectivityAttr_Bijective - deriving (Eq, Ord, Show, Data, Typeable, Generic) -instance Serialize JectivityAttr -instance Hashable JectivityAttr -instance ToJSON JectivityAttr where toJSON = genericToJSON jsonOptions -instance FromJSON JectivityAttr where parseJSON = genericParseJSON jsonOptions -instance Default JectivityAttr where def = JectivityAttr_None -instance Pretty JectivityAttr where - pretty JectivityAttr_None = prEmpty - pretty JectivityAttr_Injective = "injective" - pretty JectivityAttr_Surjective = "surjective" - pretty JectivityAttr_Bijective = "bijective" - - -data SequenceAttr x - = SequenceAttr (SizeAttr x) JectivityAttr - deriving (Eq, Ord, Show, Data, Functor, Traversable, Foldable, Typeable, Generic) -instance Serialize a => Serialize (SequenceAttr a) -instance Hashable a => Hashable (SequenceAttr a) -instance ToJSON a => ToJSON (SequenceAttr a) where toJSON = genericToJSON jsonOptions -instance FromJSON a => FromJSON (SequenceAttr a) where parseJSON = genericParseJSON jsonOptions -instance Default (SequenceAttr a) where def = SequenceAttr def def -instance Pretty a => Pretty (SequenceAttr a) where - pretty (SequenceAttr a b) = - let inside = filter (/=prEmpty) [pretty a, pretty b] - in if null inside - then prEmpty - else prettyList prParens "," inside - - -data RelationAttr a = RelationAttr (SizeAttr a) BinaryRelationAttrs - deriving (Eq, Ord, Show, Data, Functor, Traversable, Foldable, Typeable, Generic) -instance Serialize a => Serialize (RelationAttr a) -instance Hashable a => Hashable (RelationAttr a) -instance ToJSON a => ToJSON (RelationAttr a) where toJSON = genericToJSON jsonOptions -instance FromJSON a => FromJSON (RelationAttr a) where parseJSON = genericParseJSON jsonOptions -instance Default (RelationAttr a) where def = RelationAttr def def -instance Pretty a => Pretty (RelationAttr a) where - pretty (RelationAttr a b) = - let inside = filter (/=prEmpty) [pretty a, pretty b] - in if null inside - then prEmpty - else prettyList prParens "," inside - - -data BinaryRelationAttrs = BinaryRelationAttrs (S.Set BinaryRelationAttr) - deriving (Eq, Ord, Show, Data, Typeable, Generic) -instance Serialize BinaryRelationAttrs -instance Hashable BinaryRelationAttrs where hashWithSalt salt (BinaryRelationAttrs a) = hashWithSalt salt (S.toList a) -instance ToJSON BinaryRelationAttrs where toJSON = genericToJSON jsonOptions -instance FromJSON BinaryRelationAttrs where parseJSON = genericParseJSON jsonOptions -instance Default BinaryRelationAttrs where def = BinaryRelationAttrs S.empty -instance Pretty BinaryRelationAttrs where - pretty (BinaryRelationAttrs attrs) = prettyList id "," (S.toList attrs) -instance Semigroup BinaryRelationAttrs where - (<>) = mappend -instance Monoid BinaryRelationAttrs where - mempty = BinaryRelationAttrs def - mappend (BinaryRelationAttrs a) (BinaryRelationAttrs b) = BinaryRelationAttrs (S.union a b) - - -data BinaryRelationAttr - = BinRelAttr_Reflexive - | BinRelAttr_Irreflexive - | BinRelAttr_Coreflexive - | BinRelAttr_Symmetric - | BinRelAttr_AntiSymmetric - | BinRelAttr_ASymmetric - | BinRelAttr_Transitive - | BinRelAttr_Total - | BinRelAttr_Connex - | BinRelAttr_Euclidean - | BinRelAttr_Serial - | BinRelAttr_Equivalence - | BinRelAttr_PartialOrder - deriving (Eq, Ord, Show, Data, Typeable, Generic) -instance Serialize BinaryRelationAttr -instance Hashable BinaryRelationAttr -instance ToJSON BinaryRelationAttr where toJSON = genericToJSON jsonOptions -instance FromJSON BinaryRelationAttr where parseJSON = genericParseJSON jsonOptions -instance Pretty BinaryRelationAttr where - pretty BinRelAttr_Reflexive = "reflexive" - pretty BinRelAttr_Irreflexive = "irreflexive" - pretty BinRelAttr_Coreflexive = "coreflexive" - pretty BinRelAttr_Symmetric = "symmetric" - pretty BinRelAttr_AntiSymmetric = "antiSymmetric" - pretty BinRelAttr_ASymmetric = "aSymmetric" - pretty BinRelAttr_Transitive = "transitive" - pretty BinRelAttr_Total = "total" - pretty BinRelAttr_Connex = "connex" - pretty BinRelAttr_Euclidean = "Euclidean" - pretty BinRelAttr_Serial = "serial" - pretty BinRelAttr_Equivalence = "equivalence" - pretty BinRelAttr_PartialOrder = "partialOrder" - -readBinRel :: MonadFail m => AttrName -> m BinaryRelationAttr -readBinRel AttrName_reflexive = return BinRelAttr_Reflexive -readBinRel AttrName_irreflexive = return BinRelAttr_Irreflexive -readBinRel AttrName_coreflexive = return BinRelAttr_Coreflexive -readBinRel AttrName_symmetric = return BinRelAttr_Symmetric -readBinRel AttrName_antiSymmetric = return BinRelAttr_AntiSymmetric -readBinRel AttrName_aSymmetric = return BinRelAttr_ASymmetric -readBinRel AttrName_transitive = return BinRelAttr_Transitive -readBinRel AttrName_total = return BinRelAttr_Total -readBinRel AttrName_connex = return BinRelAttr_Connex -readBinRel AttrName_Euclidean = return BinRelAttr_Euclidean -readBinRel AttrName_serial = return BinRelAttr_Serial -readBinRel AttrName_equivalence = return BinRelAttr_Equivalence -readBinRel AttrName_partialOrder = return BinRelAttr_PartialOrder -readBinRel a = fail $ "Not a binary relation attribute:" <+> pretty a - -binRelToAttrName :: BinaryRelationAttr -> AttrName -binRelToAttrName BinRelAttr_Reflexive = AttrName_reflexive -binRelToAttrName BinRelAttr_Irreflexive = AttrName_irreflexive -binRelToAttrName BinRelAttr_Coreflexive = AttrName_coreflexive -binRelToAttrName BinRelAttr_Symmetric = AttrName_symmetric -binRelToAttrName BinRelAttr_AntiSymmetric = AttrName_antiSymmetric -binRelToAttrName BinRelAttr_ASymmetric = AttrName_aSymmetric -binRelToAttrName BinRelAttr_Transitive = AttrName_transitive -binRelToAttrName BinRelAttr_Total = AttrName_total -binRelToAttrName BinRelAttr_Connex = AttrName_connex -binRelToAttrName BinRelAttr_Euclidean = AttrName_Euclidean -binRelToAttrName BinRelAttr_Serial = AttrName_serial -binRelToAttrName BinRelAttr_Equivalence = AttrName_equivalence -binRelToAttrName BinRelAttr_PartialOrder = AttrName_partialOrder - --- reflexive forAll x : T . rel(x,x) --- irreflexive forAll x : T . !rel(x,x) --- coreflexive forAll x,y : T . rel(x,y) -> x = y --- --- symmetric forAll x,y : T . rel(x,y) -> rel(y,x) --- antisymmetric forAll x,y : T . rel(x,y) /\ rel(y,x) -> x = y --- asymmetric forAll x,y : T . rel(x,y) -> !rel(y,x) --- --- transitive forAll x,y,z : T . rel(x,y) /\ rel(y,z) -> rel(x,z) --- --- total forAll x,y : T . rel(x,y) \/ rel(y,x) --- connex forAll x,y : T . rel(x,y) \/ rel(y,x) \/ x = y --- Euclidean forAll x,y,z : T . rel(x,y) /\ rel(x,z) -> rel(y,z) --- serial forAll x : T . exists y : T . rel(x,y) --- equivalence reflexive + symmetric + transitive --- partialOrder reflexive + antisymmetric + transitive - - -data PartitionAttr a = PartitionAttr - { partsNum :: SizeAttr a - , partsSize :: SizeAttr a - , isRegular :: Bool - } - deriving (Eq, Ord, Show, Data, Functor, Traversable, Foldable, Typeable, Generic) -instance Serialize a => Serialize (PartitionAttr a) -instance Hashable a => Hashable (PartitionAttr a) -instance ToJSON a => ToJSON (PartitionAttr a) where toJSON = genericToJSON jsonOptions -instance FromJSON a => FromJSON (PartitionAttr a) where parseJSON = genericParseJSON jsonOptions -instance Default (PartitionAttr a) where def = PartitionAttr def def False -instance Pretty a => Pretty (PartitionAttr a) where - pretty (PartitionAttr a b c) = - let inside = filter (/=prEmpty) [ prettyNum a - , prettySize b - , prettyReg c - ] - - prettyNum SizeAttr_None = prEmpty - prettyNum (SizeAttr_Size x ) = "numParts" <+> pretty x - prettyNum (SizeAttr_MinSize x ) = "minNumParts" <+> pretty x - prettyNum (SizeAttr_MaxSize x ) = "maxNumParts" <+> pretty x - prettyNum (SizeAttr_MinMaxSize x y) = "minNumParts" <+> pretty x <> ", maxNumParts" <+> pretty y - - prettySize SizeAttr_None = prEmpty - prettySize (SizeAttr_Size x ) = "partSize" <+> pretty x - prettySize (SizeAttr_MinSize x ) = "minPartSize" <+> pretty x - prettySize (SizeAttr_MaxSize x ) = "maxPartSize" <+> pretty x - prettySize (SizeAttr_MinMaxSize x y) = "minPartSize" <+> pretty x <> ", maxPartSize" <+> pretty y - - prettyReg False = prEmpty - prettyReg True = "regular" - - in if null inside - then prEmpty - else prettyList prParens "," inside - - -data DomainAttributes a = DomainAttributes [DomainAttribute a] - deriving (Eq, Ord, Show, Data, Functor, Traversable, Foldable, Typeable, Generic) - -instance Serialize a => Serialize (DomainAttributes a) -instance Hashable a => Hashable (DomainAttributes a) -instance ToJSON a => ToJSON (DomainAttributes a) where toJSON = genericToJSON jsonOptions -instance FromJSON a => FromJSON (DomainAttributes a) where parseJSON = genericParseJSON jsonOptions - -instance Default (DomainAttributes a) where - def = DomainAttributes [] - - -data DomainAttribute a - = DAName Name - | DANameValue Name a - | DADotDot - deriving (Eq, Ord, Show, Data, Functor, Traversable, Foldable, Typeable, Generic) - -instance Serialize a => Serialize (DomainAttribute a) -instance Hashable a => Hashable (DomainAttribute a) -instance ToJSON a => ToJSON (DomainAttribute a) where toJSON = genericToJSON jsonOptions -instance FromJSON a => FromJSON (DomainAttribute a) where parseJSON = genericParseJSON jsonOptions - - -data Range a - = RangeOpen - | RangeSingle a - | RangeLowerBounded a - | RangeUpperBounded a - | RangeBounded a a - deriving (Eq, Ord, Show, Data, Functor, Traversable, Foldable, Typeable, Generic) - -instance Serialize a => Serialize (Range a) -instance Hashable a => Hashable (Range a) -instance ToJSON a => ToJSON (Range a) where toJSON = genericToJSON jsonOptions -instance FromJSON a => FromJSON (Range a) where parseJSON = genericParseJSON jsonOptions - -instance Arbitrary a => Arbitrary (Range a) where - arbitrary = oneof - [ return RangeOpen - , RangeSingle <$> arbitrary - , RangeLowerBounded <$> arbitrary - , RangeUpperBounded <$> arbitrary - , RangeBounded <$> arbitrary <*> arbitrary - ] - -rangesInts :: (MonadFail m, ExpressionLike c) => [Range c] -> m [Integer] -rangesInts = fmap (sortNub . concat) . mapM rangeInts - where - rangeInts (RangeSingle x) = return <$> intOut "rangeInts 1" x - rangeInts (RangeBounded x y) = do x' <- intOut "rangeInts 2" x - y' <- intOut "rangeInts 3" y - return [x' .. y'] - rangeInts _ = fail "Infinite range (or not an integer range)" - -expandRanges :: ExpressionLike c => [Range c] -> [Range c] -expandRanges r = - case rangesInts r of - Nothing -> r - Just [] -> [] - Just is -> - if [ minimum is .. maximum is ] == is - then [RangeBounded (fromInt (minimum is)) (fromInt (maximum is))] - else map (RangeSingle . fromInt) is - - -data HasRepresentation - = NoRepresentation - - | Set_Occurrence - | Set_Explicit - | Set_ExplicitVarSizeWithFlags - | Set_ExplicitVarSizeWithMarker - | Set_ExplicitVarSizeWithDummy - - | MSet_Occurrence - | MSet_ExplicitWithFlags - | MSet_ExplicitWithRepetition - - | Function_1D - | Function_1DPartial - | Function_ND - | Function_NDPartial - | Function_AsRelation HasRepresentation -- carries: representation for the inner relation - - | Sequence_ExplicitBounded - - | Relation_AsMatrix - | Relation_AsSet HasRepresentation -- carries: representation for the inner set - - | Partition_AsSet HasRepresentation HasRepresentation -- carries: representations for the inner sets - | Partition_Occurrence - - deriving (Eq, Ord, Show, Data, Typeable, Generic) - -instance Serialize HasRepresentation -instance Hashable HasRepresentation -instance ToJSON HasRepresentation where toJSON = genericToJSON jsonOptions -instance FromJSON HasRepresentation where parseJSON = genericParseJSON jsonOptions - -instance Default HasRepresentation where - def = NoRepresentation - -representationConstrIndex :: HasRepresentation -> [Text] -representationConstrIndex r = oneLevel r : concatMap representationConstrIndex (children r) - where - oneLevel :: HasRepresentation -> Text - oneLevel = stringToText . ("R"++) . show . constrIndex . toConstr - -instance (Pretty r, Pretty a) => Pretty (Domain r a) where - - pretty DomainAny{} = "?" - - pretty DomainBool = "bool" - - pretty (DomainIntE x) = "int" <> prParens (pretty x) - - pretty (DomainInt (TagEnum nm) _) = pretty nm - pretty (DomainInt (TagUnnamed nm) _) = pretty nm - - pretty (DomainInt _ []) = "int" - pretty (DomainInt _ ranges) = "int" <> prettyList prParens "," ranges - - pretty (DomainEnum name (Just ranges) _) = pretty name <> prettyList prParens "," ranges - pretty (DomainEnum name _ _) = pretty name - - pretty (DomainUnnamed name _) = pretty name - - pretty (DomainTuple inners) - = (if length inners < 2 then "tuple" else prEmpty) - <+> prettyList prParens "," inners - - pretty (DomainRecord xs) = "record" <+> prettyList prBraces "," - [ pretty nm <+> ":" <+> pretty d | (nm, d) <- xs ] - - pretty (DomainVariant xs) = "variant" <+> prettyList prBraces "," - [ pretty nm <+> ":" <+> pretty d | (nm, d) <- xs ] - - pretty (DomainMatrix index innerNested) - = "matrix indexed by" <+> prettyList prBrackets "," indices - <+> "of" <+> pretty inner - where - (indices,inner) = first (index:) $ collect innerNested - collect (DomainMatrix i j) = first (i:) $ collect j - collect x = ([],x) - - pretty (DomainSet r attrs inner) = - hang ("set" <+> prettyAttrs r attrs <+> "of") 4 (pretty inner) - - pretty (DomainMSet r attrs inner) = - hang ("mset" <+> prettyAttrs r attrs <+> "of") 4 (pretty inner) - - pretty (DomainFunction r attrs innerFrom innerTo) = - hang ("function" <+> prettyAttrs r attrs) 4 $ - hang (pretty innerFrom) 4 $ - "-->" <+> pretty innerTo - - pretty (DomainSequence r attrs inner) = - hang ("sequence" <+> prettyAttrs r attrs <+> "of") 4 (pretty inner) - - pretty (DomainRelation r attrs inners) - = hang ("relation" <+> prettyAttrs r attrs <+> "of") 4 (prettyList prParens " *" inners) - - pretty (DomainPartition r attrs inner) - = hang ("partition" <+> prettyAttrs r attrs <+> "from") 4 (pretty inner) - - pretty d@DomainOp{} = pretty (show d) - - pretty (DomainReference x _) = pretty x - - pretty (DomainMetaVar x) = "&" <> pretty x - - -prettyAttrs :: (Pretty a, Pretty b) => a -> b -> Doc -prettyAttrs a bs = - let prettya = pretty a - in if prettya == "()" - then pretty bs - else prBraces prettya <+> pretty bs - -instance Pretty a => Pretty (DomainAttributes a) where - pretty (DomainAttributes []) = prEmpty - pretty (DomainAttributes attrs) = prettyList prParens "," attrs - -instance Pretty a => Pretty (DomainAttribute a) where - pretty (DAName name) = pretty name - pretty (DANameValue name value) = pretty name <+> pretty value - pretty DADotDot = ".." - -instance Pretty a => Pretty (Range a) where - pretty RangeOpen = ".." - pretty (RangeSingle x) = pretty x - pretty (RangeLowerBounded x) = pretty x <> ".." - pretty (RangeUpperBounded x) = ".." <> pretty x - pretty (RangeBounded x y) | show (pretty x) == show (pretty y) = pretty x - pretty (RangeBounded x y) = pretty x <> ".." <> pretty y - -instance Pretty HasRepresentation where - pretty NoRepresentation = "∅" - pretty r = pretty (representationToFullText r) - -textToRepresentation :: Text -> [HasRepresentation] -> Maybe HasRepresentation -textToRepresentation t [] | t == "Occurrence" = return Set_Occurrence -textToRepresentation t [] | t == "Explicit" = return Set_Explicit -textToRepresentation t [] | t == "ExplicitVarSizeWithFlags" = return Set_ExplicitVarSizeWithFlags -textToRepresentation t [] | t == "ExplicitVarSizeWithMarker" = return Set_ExplicitVarSizeWithMarker -textToRepresentation t [] | t == "ExplicitVarSizeWithDummy" = return Set_ExplicitVarSizeWithDummy -textToRepresentation t [] | t == "MOccurrence" = return MSet_Occurrence -textToRepresentation t [] | t == "ExplicitWithFlags" = return MSet_ExplicitWithFlags -textToRepresentation t [] | t == "ExplicitWithRepetition" = return MSet_ExplicitWithRepetition -textToRepresentation t [] | t == "Function1D" = return Function_1D -textToRepresentation t [] | t == "Function1DPartial" = return Function_1DPartial -textToRepresentation t [] | t == "FunctionND" = return Function_ND -textToRepresentation t [] | t == "FunctionNDPartial" = return Function_NDPartial -textToRepresentation t [repr] | t == "FunctionAsRelation" = return (Function_AsRelation repr) -textToRepresentation t [] | t == "ExplicitBounded" = return Sequence_ExplicitBounded -textToRepresentation t [] | t == "RelationAsMatrix" = return Relation_AsMatrix -textToRepresentation t [repr] | t == "RelationAsSet" = return (Relation_AsSet repr) -textToRepresentation t [repr1, repr2] | t == "PartitionAsSet" = return (Partition_AsSet repr1 repr2) -textToRepresentation t [] | t == "PartitionOccurrence" = return Partition_Occurrence -textToRepresentation _ _ = Nothing - -representationToShortText :: HasRepresentation -> Text -representationToShortText Set_Occurrence = "Occurrence" -representationToShortText Set_Explicit = "Explicit" -representationToShortText Set_ExplicitVarSizeWithFlags = "ExplicitVarSizeWithFlags" -representationToShortText Set_ExplicitVarSizeWithMarker = "ExplicitVarSizeWithMarker" -representationToShortText Set_ExplicitVarSizeWithDummy = "ExplicitVarSizeWithDummy" -representationToShortText MSet_Occurrence = "MOccurrence" -representationToShortText MSet_ExplicitWithFlags = "ExplicitWithFlags" -representationToShortText MSet_ExplicitWithRepetition = "ExplicitWithRepetition" -representationToShortText Function_1D = "Function1D" -representationToShortText Function_1DPartial = "Function1DPartial" -representationToShortText Function_ND = "FunctionND" -representationToShortText Function_NDPartial = "FunctionNDPartial" -representationToShortText Function_AsRelation{} = "FunctionAsRelation" -representationToShortText Sequence_ExplicitBounded = "ExplicitBounded" -representationToShortText Relation_AsMatrix = "RelationAsMatrix" -representationToShortText Relation_AsSet{} = "RelationAsSet" -representationToShortText Partition_AsSet{} = "PartitionAsSet" -representationToShortText Partition_Occurrence = "PartitionOccurrence" -representationToShortText r = bug ("representationToShortText:" <+> pretty (show r)) - -representationToFullText :: HasRepresentation -> Text -representationToFullText (Function_AsRelation repr) = mconcat [ "FunctionAsRelation" - , "[" - , representationToFullText repr - , "]" - ] -representationToFullText (Relation_AsSet repr) = mconcat [ "RelationAsSet" - , "[" - , representationToFullText repr - , "]" - ] -representationToFullText (Partition_AsSet repr1 repr2) = mconcat [ "PartitionAsSet" - , "[" - , representationToFullText repr1 - , "," - , representationToFullText repr2 - , "]" - ] -representationToFullText r = representationToShortText r - - -normaliseDomain :: (Ord c, ExpressionLike c) => (c -> c) -> Domain r c -> Domain r c -normaliseDomain _norm DomainBool = DomainBool -normaliseDomain norm (DomainInt t rs ) = DomainInt t $ sort $ map (normaliseRange norm) (expandRanges rs) -normaliseDomain _norm (DomainEnum n Nothing mp) = DomainEnum n Nothing mp -normaliseDomain _norm (DomainEnum n (Just rs) mp) = DomainEnum n (Just $ sort rs) mp -normaliseDomain norm (DomainUnnamed n x ) = DomainUnnamed n (norm x) -normaliseDomain norm (DomainRecord doms ) = DomainRecord [ (n, normaliseDomain norm d) - | (n, d) <- doms ] -normaliseDomain norm (DomainVariant doms ) = DomainVariant [ (n, normaliseDomain norm d) - | (n, d) <- doms ] -normaliseDomain norm (DomainTuple doms ) = DomainTuple $ map (normaliseDomain norm) doms -normaliseDomain norm (DomainMatrix dom1 dom2) = DomainMatrix (normaliseDomain norm dom1) - (normaliseDomain norm dom2) -normaliseDomain norm (DomainSet r attr dom ) = DomainSet r (fmap norm attr) - (normaliseDomain norm dom) -normaliseDomain norm (DomainMSet r attr dom ) = DomainMSet r (fmap norm attr) - (normaliseDomain norm dom) -normaliseDomain norm (DomainFunction r attr dom1 dom2) = DomainFunction r (fmap norm attr) - (normaliseDomain norm dom1) - (normaliseDomain norm dom2) -normaliseDomain norm (DomainSequence r attr dom ) = DomainSequence r (fmap norm attr) - (normaliseDomain norm dom) -normaliseDomain norm (DomainRelation r attr doms ) = DomainRelation r (fmap norm attr) - (map (normaliseDomain norm) doms) -normaliseDomain norm (DomainPartition r attr dom ) = DomainPartition r (fmap norm attr) - (normaliseDomain norm dom) -normaliseDomain _norm d = d - -normaliseRange :: (c -> c) -> Range c -> Range c -normaliseRange _norm RangeOpen = RangeOpen -normaliseRange norm (RangeSingle x) = RangeBounded (norm x) (norm x) -normaliseRange norm (RangeLowerBounded x) = RangeLowerBounded (norm x) -normaliseRange norm (RangeUpperBounded x) = RangeUpperBounded (norm x) -normaliseRange norm (RangeBounded x y) = RangeBounded (norm x) (norm y) - -innerDomainOf :: (MonadFail m, Show x) => Domain () x -> m (Domain () x) -innerDomainOf (DomainMatrix _ t) = return t -innerDomainOf (DomainSet _ _ t) = return t -innerDomainOf (DomainMSet _ _ t) = return t -innerDomainOf (DomainFunction _ _ a b) = return (DomainTuple [a,b]) -innerDomainOf (DomainRelation _ _ ts) = return (DomainTuple ts) -innerDomainOf (DomainPartition _ _ t) = return (DomainSet () def t) -innerDomainOf t = fail ("innerDomainOf:" <+> pretty (show t)) - -singletonDomainInt :: (Eq x, CanBeAnAlias x) => Domain r x -> Maybe x -singletonDomainInt (DomainInt _ [RangeSingle a]) = Just a -singletonDomainInt (DomainInt _ [RangeBounded a b]) = - let - followAlias (isAlias -> Just x) = followAlias x - followAlias x = x - in - if followAlias a == followAlias b - then Just a - else Nothing -singletonDomainInt _ = Nothing - -matrixNumDimsD :: Domain r x -> Int -matrixNumDimsD (DomainMatrix _ t) = 1 + matrixNumDimsD t -matrixNumDimsD _ = 0 From f18b7fae6f06524ef6bf538dd0b38cbe5aaf521e Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?=C3=96zg=C3=BCr=20Akg=C3=BCn?= Date: Tue, 27 Feb 2024 14:45:26 +0000 Subject: [PATCH 128/229] bring back the call to prologue --- src/Conjure/UI/MainHelper.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/src/Conjure/UI/MainHelper.hs b/src/Conjure/UI/MainHelper.hs index cd9202c42a..3b57f1f312 100644 --- a/src/Conjure/UI/MainHelper.hs +++ b/src/Conjure/UI/MainHelper.hs @@ -9,7 +9,7 @@ import Conjure.UI ( UI(..), OutputFormat(..) ) import Conjure.UI.IO ( readModel, readModelFromFile, readModelFromStdin , readModelInfoFromFile, readParamOrSolutionFromFile , writeModel ) -import Conjure.UI.Model ( parseStrategy, outputModels, modelRepresentationsJSON ) +import Conjure.UI.Model ( parseStrategy, outputModels, modelRepresentationsJSON, prologue ) import qualified Conjure.UI.Model as Config ( Config(..) ) import Conjure.UI.TranslateParameter ( translateParameter ) import Conjure.UI.TranslateSolution ( translateSolution ) @@ -279,7 +279,7 @@ mainWithArgs config@Solve{..} = do when (solver `elem` ["bc_minisat_all", "nbc_minisat_all"] && nbSolutions /= "all") $ userErr1 "The solvers bc_minisat_all and nbc_minisat_all only work with --number-of-solutions=all" essenceM_beforeNR <- readModelFromFile essence - essenceM <- resolveNames essenceM_beforeNR + essenceM <- prologue def essenceM_beforeNR unless (null [ () | Objective{} <- mStatements essenceM ]) $ do -- this is an optimisation problem when (nbSolutions == "all" || nbSolutions /= "1") $ userErr1 ("Not supported for optimisation problems: --number-of-solutions=" <> pretty nbSolutions) From eff909a103a8030730b3ae49338f52a7571c557b Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?=C3=96zg=C3=BCr=20Akg=C3=BCn?= Date: Tue, 27 Feb 2024 14:51:38 +0000 Subject: [PATCH 129/229] avoid enumerateInConstant --- src/Conjure/Language/EvaluateOp.hs | 4 +--- 1 file changed, 1 insertion(+), 3 deletions(-) diff --git a/src/Conjure/Language/EvaluateOp.hs b/src/Conjure/Language/EvaluateOp.hs index f708125038..ebcb393eb6 100644 --- a/src/Conjure/Language/EvaluateOp.hs +++ b/src/Conjure/Language/EvaluateOp.hs @@ -221,9 +221,7 @@ instance EvaluateOp OpIn where return $ ConstantBool $ elem c $ map (\ (i,j) -> ConstantAbstract $ AbsLitTuple [i,j] ) cs evaluateOp (OpIn c (viewConstantRelation -> Just cs)) = return $ ConstantBool $ elem c $ map (ConstantAbstract . AbsLitTuple) cs - evaluateOp (OpIn c coll) = do - vals <- enumerateInConstant coll - return $ ConstantBool $ elem c vals + evaluateOp op = na $ "evaluateOp{OpIn}:" <++> pretty (show op) instance EvaluateOp OpIndexing where evaluateOp p@(OpIndexing m i) | isUndef i = do From 25b277ecbc572359464f5853d5d16dceaf1d3626 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?=C3=96zg=C3=BCr=20Akg=C3=BCn?= Date: Tue, 27 Feb 2024 14:53:55 +0000 Subject: [PATCH 130/229] remove aux file --- etc/build/stack-9.4.yaml | 8 -------- etc/hs-deps/stack-9.0.yaml | 2 +- 2 files changed, 1 insertion(+), 9 deletions(-) delete mode 100644 etc/build/stack-9.4.yaml diff --git a/etc/build/stack-9.4.yaml b/etc/build/stack-9.4.yaml deleted file mode 100644 index 5aab728052..0000000000 --- a/etc/build/stack-9.4.yaml +++ /dev/null @@ -1,8 +0,0 @@ -resolver: lts-21.12 -packages: -- '.' -system-ghc: true -install-ghc: true -extra-deps: -- lsp-1.6.0.0 -- lsp-types-1.6.0.0 diff --git a/etc/hs-deps/stack-9.0.yaml b/etc/hs-deps/stack-9.0.yaml index 9af60f939b..231e232317 100644 --- a/etc/hs-deps/stack-9.0.yaml +++ b/etc/hs-deps/stack-9.0.yaml @@ -4,4 +4,4 @@ packages: system-ghc: true install-ghc: true extra-deps: -- megaparsec-9.3.0 +- megaparsec-9.3.0 \ No newline at end of file From cd7db7b5893034f880f22ebcb12fdb52d0009136 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?=C3=96zg=C3=BCr=20Akg=C3=BCn?= Date: Tue, 27 Feb 2024 15:09:49 +0000 Subject: [PATCH 131/229] format --- src/Conjure/Language/Expression/Op.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Conjure/Language/Expression/Op.hs b/src/Conjure/Language/Expression/Op.hs index 90adf3b393..0d8728b674 100644 --- a/src/Conjure/Language/Expression/Op.hs +++ b/src/Conjure/Language/Expression/Op.hs @@ -132,7 +132,7 @@ mkOp op xs = case op of L_party -> inject $ MkOpParty $ OpParty (arg xs 0 "party") (arg xs 1 "party") L_participants -> inject $ MkOpParticipants $ OpParticipants (arg xs 0 "participants") - L_compose -> inject $ MkOpCompose $ OpCompose (arg xs 0 "compose") + L_compose -> inject $ MkOpCompose $ OpCompose (arg xs 0 "compose") (arg xs 1 "compose") L_active -> inject $ MkOpActive $ OpActive (arg xs 0 "active") From 11a422bc92ffa2b736ace539b701dd186810d918 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?=C3=96zg=C3=BCr=20Akg=C3=BCn?= Date: Tue, 27 Feb 2024 15:12:47 +0000 Subject: [PATCH 132/229] remove comment --- src/Conjure/Language/Expression/Op/ToSet.hs | 2 -- 1 file changed, 2 deletions(-) diff --git a/src/Conjure/Language/Expression/Op/ToSet.hs b/src/Conjure/Language/Expression/Op/ToSet.hs index 0f732b4a1c..c23cc123ee 100644 --- a/src/Conjure/Language/Expression/Op/ToSet.hs +++ b/src/Conjure/Language/Expression/Op/ToSet.hs @@ -10,8 +10,6 @@ import qualified Data.Aeson.KeyMap as KM import qualified Data.Vector as V -- vector ---import Data.Permutation - data OpToSet x = OpToSet Bool -- True means we can assume there won't be any duplicates From 82f0102fe6512f80a3d577c481c75f64d52afae7 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?=C3=96zg=C3=BCr=20Akg=C3=BCn?= Date: Tue, 27 Feb 2024 15:39:19 +0000 Subject: [PATCH 133/229] tidy up --- src/Conjure/Language/Parser.hs | 8 -------- 1 file changed, 8 deletions(-) diff --git a/src/Conjure/Language/Parser.hs b/src/Conjure/Language/Parser.hs index 69072a1db2..4afaf08b2d 100644 --- a/src/Conjure/Language/Parser.hs +++ b/src/Conjure/Language/Parser.hs @@ -16,16 +16,8 @@ module Conjure.Language.Parser ) where --- conjure - --- text - import Conjure.Language.AST.ASTParser (ParserError, parseProgram, runASTParser) import Conjure.Language.AST.ASTParser qualified as P --- containers --- import qualified Data.Set as S ( null, fromList, toList ) - --- import Conjure.Language.AST.Helpers (ParserState) import Conjure.Language.AST.Helpers qualified as P import Conjure.Language.AST.Reformer (HighLevelTree (..), flatten) import Conjure.Language.AST.Syntax (DomainNode, ProgramTree) From 07db46c801a46a7020d5a18213fafdd237e0d111 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?=C3=96zg=C3=BCr=20Akg=C3=BCn?= Date: Tue, 27 Feb 2024 15:40:54 +0000 Subject: [PATCH 134/229] tidy up --- src/Conjure/Language/ParserC.hs | 22 +++++++++------------- 1 file changed, 9 insertions(+), 13 deletions(-) diff --git a/src/Conjure/Language/ParserC.hs b/src/Conjure/Language/ParserC.hs index 54927275f1..c4ede18e79 100644 --- a/src/Conjure/Language/ParserC.hs +++ b/src/Conjure/Language/ParserC.hs @@ -1,20 +1,16 @@ {-# LANGUAGE RecordWildCards #-} -module Conjure.Language.ParserC ( - parseModel ) where +module Conjure.Language.ParserC + ( parseModel, + ) +where --- conjure -import Conjure.Prelude -import Conjure.Language.Definition - -import qualified Conjure.Language.Validator as V +import Conjure.Language.AST.ASTParser (parseProgram) import Conjure.Language.AST.Syntax (ProgramTree) +import Conjure.Language.Definition import Conjure.Language.Parser (Pipeline) -import Conjure.Language.AST.ASTParser (parseProgram) - - - - +import Conjure.Language.Validator qualified as V +import Conjure.Prelude parseModel :: Pipeline ProgramTree Model -parseModel = (parseProgram,V.validateModel,False) +parseModel = (parseProgram, V.validateModel, False) From 2e674ced7ccd8f24d3d1a2fb919ef64337f26f94 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?=C3=96zg=C3=BCr=20Akg=C3=BCn?= Date: Wed, 28 Feb 2024 12:32:27 +0000 Subject: [PATCH 135/229] symmetryOrdering --- src/Conjure/Representations.hs | 167 ++++++++++++++------------------- 1 file changed, 69 insertions(+), 98 deletions(-) diff --git a/src/Conjure/Representations.hs b/src/Conjure/Representations.hs index 0480c64013..41de7fada9 100644 --- a/src/Conjure/Representations.hs +++ b/src/Conjure/Representations.hs @@ -142,101 +142,72 @@ symmetryOrdering :: EnumerateDomain m => (?typeCheckerMode :: TypeCheckerMode) => Expression -> m Expression --- <<<<<<< HEAD ---symmetryOrdering inp' = do --- let constBool (ConstantBool True) = ConstantInt TagInt 1 --- constBool (ConstantBool False) = ConstantInt TagInt 0 --- constBool x = x --- inp = transformBi constBool inp' --- ta <- typeOf inp --- case ta of --- TypeBool -> return [essence| [-toInt(&inp)] |] --- TypeInt{} -> return [essence| [&inp] |] --- TypeList TypeInt{} -> return inp --- TypeMatrix TypeInt{} TypeInt{} -> return inp --- _ -> do --- case inp of --- -- Constant x -> so_onConstant x --- -- AbstractLiteral _ -> return inp --- Constant (ConstantAbstract x) -> do --- case x of --- AbsLitTuple xs -> do --- soVals <- sequence (symmetryOrdering <$> (Constant <$> xs)) --- return $ fromList soVals --- AbsLitMatrix _ xs -> do --- soVals <- sequence (symmetryOrdering <$> (Constant <$> xs)) --- return $ fromList soVals --- _ -> bug ("symmetryOrdering: AbstractLiteral:" <++> pretty (show inp) <++> pretty (inp)) --- Constant (ConstantBool b) -> return [essence| -toInt(&inp) |] --- AbstractLiteral x -> do --- case x of --- AbsLitTuple xs -> do --- soVals <- sequence (symmetryOrdering <$> xs) --- return $ AbstractLiteral $ AbsLitTuple soVals --- AbsLitMatrix d xs -> do --- soVals <- sequence (symmetryOrdering <$> xs) --- return $ AbstractLiteral $ AbsLitMatrix d soVals --- _ -> bug ("symmetryOrdering: AbstractLiteral:" <++> pretty (show inp) <++> pretty (inp)) --- --- --- Reference _ (Just refTo) -> do --- case refTo of --- Alias x -> symmetryOrdering x --- InComprehension{} -> bug ("symmetryOrdering.InComprehension:" <++> pretty (show inp)) --- DeclNoRepr{} -> bug ("symmetryOrdering.DeclNoRepr:" <++> pretty (show inp)) --- DeclHasRepr _forg _name domain -> symmetryOrderingDispatch downX1 inp domain --- RecordField{} -> bug ("symmetryOrdering.RecordField:" <++> pretty (show inp)) --- VariantField{} -> bug ("symmetryOrdering.VariantField:" <++> pretty (show inp)) --- Op op -> case op of --- MkOpIndexing (OpIndexing m _) -> do --- --- ty <- typeOf m --- case ty of --- TypeMatrix{} -> return () --- TypeList{} -> return () --- _ -> bug $ "[symmetryOrdering.onOp, not a TypeMatrix or TypeList]" <+> vcat [pretty ty, pretty op] --- mDom <- domainOfR m --- case mDom of --- DomainMatrix _ domainInner -> symmetryOrderingDispatch downX1 inp domainInner --- _ -> bug ("symmetryOrdering, not DomainMatrix:" <++> pretty (show op)) --- MkOpImage (OpImage p x) -> do --- so <- symmetryOrdering x --- return [essence| image(&p, &so) |] --- _ -> bug ("symmetryOrdering, no OpIndexing:" <++> pretty (show op)) --- Comprehension body stmts -> do --- xs <- symmetryOrdering body --- return $ make opFlatten $ Comprehension xs stmts --- -- x@WithLocals{} -> bug ("downX1:" <++> pretty (show x)) --- _ -> bug ("symmetryOrdering:" <++> pretty (show inp) <++> pretty (inp)) --- ======= -symmetryOrdering inp = - case inp of - -- Constant x -> so_onConstant x - -- AbstractLiteral x - Reference _ (Just refTo) -> do - case refTo of - Alias x -> symmetryOrdering x - InComprehension{} -> bug ("symmetryOrdering.InComprehension:" <++> pretty (show inp)) - DeclNoRepr{} -> bug ("symmetryOrdering.DeclNoRepr:" <++> pretty (show inp)) - DeclHasRepr _forg _name domain -> symmetryOrderingDispatch downX1 inp domain - RecordField{} -> bug ("symmetryOrdering.RecordField:" <++> pretty (show inp)) - VariantField{} -> bug ("symmetryOrdering.VariantField:" <++> pretty (show inp)) - Op op -> case op of - MkOpIndexing (OpIndexing m _) -> do - ty <- typeOf m - case ty of - TypeMatrix{} -> return () - TypeList{} -> return () - _ -> bug $ "[symmetryOrdering.onOp, not a TypeMatrix or TypeList]" <+> vcat [pretty ty, pretty op] - mDom <- domainOfR m - case mDom of - DomainMatrix _ domainInner -> symmetryOrderingDispatch downX1 inp domainInner - _ -> bug ("symmetryOrdering, not DomainMatrix:" <++> pretty (show op)) - _ -> bug ("symmetryOrdering, unhandled Op:" <++> pretty (show op)) - -- Comprehension body stmts -> do - -- xs <- downX1 body - -- return [Comprehension x stmts | x <- xs] - -- x@WithLocals{} -> bug ("downX1:" <++> pretty (show x)) - _ -> bug ("symmetryOrdering:" <++> pretty (show inp)) - - +symmetryOrdering inp' = do + let constBool (ConstantBool True) = ConstantInt TagInt 1 + constBool (ConstantBool False) = ConstantInt TagInt 0 + constBool x = x + inp = transformBi constBool inp' + ta <- typeOf inp + case ta of + TypeBool -> return [essence| [-toInt(&inp)] |] + TypeInt{} -> return [essence| [&inp] |] + TypeList TypeInt{} -> return inp + TypeMatrix TypeInt{} TypeInt{} -> return inp + _ -> do + case inp of + -- Constant x -> so_onConstant x + -- AbstractLiteral _ -> return inp + + Constant ConstantBool{} -> return [essence| -toInt(&inp) |] + + Constant (ConstantAbstract x) -> do + case x of + AbsLitTuple xs -> do + soVals <- mapM symmetryOrdering (Constant <$> xs) + return $ fromList soVals + AbsLitMatrix _ xs -> do + soVals <- mapM symmetryOrdering (Constant <$> xs) + return $ fromList soVals + _ -> bug ("symmetryOrdering: AbstractLiteral:" <++> pretty (show inp) <++> pretty inp) + + AbstractLiteral x -> do + case x of + AbsLitTuple xs -> do + soVals <- mapM symmetryOrdering xs + return $ AbstractLiteral $ AbsLitTuple soVals + AbsLitMatrix d xs -> do + soVals <- mapM symmetryOrdering xs + return $ AbstractLiteral $ AbsLitMatrix d soVals + _ -> bug ("symmetryOrdering: AbstractLiteral:" <++> pretty (show inp) <++> pretty inp) + + Reference _ (Just refTo) -> do + case refTo of + Alias x -> symmetryOrdering x + InComprehension{} -> bug ("symmetryOrdering.InComprehension:" <++> pretty (show inp)) + DeclNoRepr{} -> bug ("symmetryOrdering.DeclNoRepr:" <++> pretty (show inp)) + DeclHasRepr _forg _name domain -> symmetryOrderingDispatch downX1 inp domain + RecordField{} -> bug ("symmetryOrdering.RecordField:" <++> pretty (show inp)) + VariantField{} -> bug ("symmetryOrdering.VariantField:" <++> pretty (show inp)) + + Op op -> case op of + MkOpIndexing (OpIndexing m _) -> do + + ty <- typeOf m + case ty of + TypeMatrix{} -> return () + TypeList{} -> return () + _ -> bug $ "[symmetryOrdering.onOp, not a TypeMatrix or TypeList]" <+> vcat [pretty ty, pretty op] + mDom <- domainOfR m + case mDom of + DomainMatrix _ domainInner -> symmetryOrderingDispatch downX1 inp domainInner + _ -> bug ("symmetryOrdering, not DomainMatrix:" <++> pretty (show op)) + MkOpImage (OpImage p x) -> do + so <- symmetryOrdering x + return [essence| image(&p, &so) |] + _ -> bug ("symmetryOrdering, no OpIndexing:" <++> pretty (show op)) + + Comprehension body stmts -> do + xs <- symmetryOrdering body + return $ make opFlatten $ Comprehension xs stmts + + _ -> bug ("symmetryOrdering:" <++> pretty (show inp) <++> pretty inp) From c6227ebadb9ececc40d64dea3621dcc8fffaad4a Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?=C3=96zg=C3=BCr=20Akg=C3=BCn?= Date: Wed, 28 Feb 2024 12:32:40 +0000 Subject: [PATCH 136/229] validator to ignore int tags --- src/Conjure/Process/ValidateConstantForDomain.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Conjure/Process/ValidateConstantForDomain.hs b/src/Conjure/Process/ValidateConstantForDomain.hs index c083bed498..8a1f2049f6 100644 --- a/src/Conjure/Process/ValidateConstantForDomain.hs +++ b/src/Conjure/Process/ValidateConstantForDomain.hs @@ -33,7 +33,7 @@ validateConstantForDomain _ (viewConstantBool -> Just _) DomainBool{} = return ( validateConstantForDomain _ _ (DomainInt _ []) = return () -- no restrictions -validateConstantForDomain name c@(viewConstantIntWithTag -> Just (cTag, i)) d@(DomainInt dTag rs) | cTag == dTag = +validateConstantForDomain name c@(viewConstantIntWithTag -> Just (_cTag, i)) d@(DomainInt _dTag rs) = let intInRange RangeOpen = True intInRange (RangeSingle (ConstantInt _ a)) = i == a From 599d1bb375a8ce592914e2d056d756a0b0724b13 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?=C3=96zg=C3=BCr=20Akg=C3=BCn?= Date: Wed, 28 Feb 2024 12:34:20 +0000 Subject: [PATCH 137/229] another testcase fix --- .../issues/263/expected/model-p2-solution000001.solution | 4 ++++ tests/exhaustive/issues/263/expected/model-p2.eprime-param | 3 +++ 2 files changed, 7 insertions(+) create mode 100644 tests/exhaustive/issues/263/expected/model-p2-solution000001.solution create mode 100644 tests/exhaustive/issues/263/expected/model-p2.eprime-param diff --git a/tests/exhaustive/issues/263/expected/model-p2-solution000001.solution b/tests/exhaustive/issues/263/expected/model-p2-solution000001.solution new file mode 100644 index 0000000000..ac8c733f23 --- /dev/null +++ b/tests/exhaustive/issues/263/expected/model-p2-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting O be new type enum {O_1, O_2} +letting f be function(O_1 --> O_1, O_2 --> O_2) diff --git a/tests/exhaustive/issues/263/expected/model-p2.eprime-param b/tests/exhaustive/issues/263/expected/model-p2.eprime-param new file mode 100644 index 0000000000..15cca3e147 --- /dev/null +++ b/tests/exhaustive/issues/263/expected/model-p2.eprime-param @@ -0,0 +1,3 @@ +language ESSENCE' 1.0 + +letting v be 2 From 43b294f3595321e0f9f79b81b753e76fcce5ad53 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?=C3=96zg=C3=BCr=20Akg=C3=BCn?= Date: Wed, 28 Feb 2024 14:28:45 +0000 Subject: [PATCH 138/229] a few more passing tests --- .../gcf-inputs.solution | 3 -- .../basic/letting-arithmetic/letting.solution | 3 -- .../partitions/partition-01/apart.solution | 4 -- .../basic/tuples/tuple-index/tuple.solution | 4 -- tests/custom/issues/383/stdout.expected | 2 +- tests/custom/issues/459/stderr.expected | 2 +- .../autogen/gen26_3/expected/model.eprime | 2 +- .../issues/182/expected/model.eprime | 37 +++++++++---------- 8 files changed, 20 insertions(+), 37 deletions(-) diff --git a/tests/custom/STARIS_2022/basic/greatest-common-factor/gcf-inputs.solution b/tests/custom/STARIS_2022/basic/greatest-common-factor/gcf-inputs.solution index db745d9b9d..68bf6ab330 100644 --- a/tests/custom/STARIS_2022/basic/greatest-common-factor/gcf-inputs.solution +++ b/tests/custom/STARIS_2022/basic/greatest-common-factor/gcf-inputs.solution @@ -1,6 +1,3 @@ language Essence 1.3 -<<<<<<<< HEAD:tests/exhaustive/basic/perms/01_representation/enum/0003_given_permutation_in_param_2_cycle/expected/model-permutation-solution000001.solution -======== letting z be 6 ->>>>>>>> main:tests/custom/STARIS_2022/basic/greatest-common-factor/gcf-inputs.solution diff --git a/tests/custom/STARIS_2022/basic/letting-arithmetic/letting.solution b/tests/custom/STARIS_2022/basic/letting-arithmetic/letting.solution index b08ed022d6..a838675173 100644 --- a/tests/custom/STARIS_2022/basic/letting-arithmetic/letting.solution +++ b/tests/custom/STARIS_2022/basic/letting-arithmetic/letting.solution @@ -1,6 +1,3 @@ language Essence 1.3 -<<<<<<<< HEAD:tests/exhaustive/basic/perms/01_representation/enum/0004_given_permutation_in_param_2_cycle/expected/model-permutation-solution000001.solution -======== letting b be 5 ->>>>>>>> main:tests/custom/STARIS_2022/basic/letting-arithmetic/letting.solution diff --git a/tests/custom/STARIS_2022/basic/partitions/partition-01/apart.solution b/tests/custom/STARIS_2022/basic/partitions/partition-01/apart.solution index d2566910f7..4d2259d4d4 100644 --- a/tests/custom/STARIS_2022/basic/partitions/partition-01/apart.solution +++ b/tests/custom/STARIS_2022/basic/partitions/partition-01/apart.solution @@ -1,7 +1,3 @@ language Essence 1.3 -<<<<<<<< HEAD:tests/exhaustive/basic/perms/05_equality/enum/0001_given_permutations_in_param/expected/model-permutation-solution000001.solution -letting b be true -======== letting a be false ->>>>>>>> main:tests/custom/STARIS_2022/basic/partitions/partition-01/apart.solution diff --git a/tests/custom/STARIS_2022/basic/tuples/tuple-index/tuple.solution b/tests/custom/STARIS_2022/basic/tuples/tuple-index/tuple.solution index 5667f45a23..be10adf4bc 100644 --- a/tests/custom/STARIS_2022/basic/tuples/tuple-index/tuple.solution +++ b/tests/custom/STARIS_2022/basic/tuples/tuple-index/tuple.solution @@ -1,7 +1,3 @@ language Essence 1.3 -<<<<<<<< HEAD:tests/exhaustive/basic/perms/05_equality/int/0001_given_permutations_in_param/expected/model-permutation-solution000001.solution -letting b be true -======== letting x be true ->>>>>>>> main:tests/custom/STARIS_2022/basic/tuples/tuple-index/tuple.solution diff --git a/tests/custom/issues/383/stdout.expected b/tests/custom/issues/383/stdout.expected index 70e36bd72b..56a927a1c7 100644 --- a/tests/custom/issues/383/stdout.expected +++ b/tests/custom/issues/383/stdout.expected @@ -59,6 +59,6 @@ Error: 10 | find c : colours such that c = |toSet([ f(u) | u : vertices ])| | ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ Type error: - Expected: colours + Expected: unnamed:colours Got: int diff --git a/tests/custom/issues/459/stderr.expected b/tests/custom/issues/459/stderr.expected index 7cb7b5a5b1..0d70778ffd 100644 --- a/tests/custom/issues/459/stderr.expected +++ b/tests/custom/issues/459/stderr.expected @@ -1,5 +1,5 @@ Error: In a letting statement: letting s be domain int(S) Error: - Expected an integer, but got: set of direction + Expected an integer, but got: set of enum:direction In domain: int(S) diff --git a/tests/exhaustive/autogen/gen26_3/expected/model.eprime b/tests/exhaustive/autogen/gen26_3/expected/model.eprime index 7a5abf9891..49815d0709 100644 --- a/tests/exhaustive/autogen/gen26_3/expected/model.eprime +++ b/tests/exhaustive/autogen/gen26_3/expected/model.eprime @@ -17,7 +17,7 @@ branching on such that false, var3_PartitionAsSet_ExplicitR5_ExplicitVarSizeWithMarker_Marker[1] = - sum([toInt(q31 <= var3_PartitionAsSet_ExplicitR5_ExplicitVarSizeWithMarker_Marker[1]) | q31 : int(1..let2)]), + sum([toInt(q29 <= var3_PartitionAsSet_ExplicitR5_ExplicitVarSizeWithMarker_Marker[1]) | q29 : int(1..let2)]), var3_PartitionAsSet_ExplicitR5_ExplicitVarSizeWithMarker_Marker[1] >= 1, var3_PartitionAsSet_ExplicitR5_ExplicitVarSizeWithMarker_Marker[1] <= let2, 4096 = var3_PartitionAsSet_ExplicitR5_ExplicitVarSizeWithMarker_Marker[1] diff --git a/tests/exhaustive/issues/182/expected/model.eprime b/tests/exhaustive/issues/182/expected/model.eprime index 42f89e0671..18c701db1d 100644 --- a/tests/exhaustive/issues/182/expected/model.eprime +++ b/tests/exhaustive/issues/182/expected/model.eprime @@ -13,19 +13,19 @@ branching on p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values] such that and([1 = - sum([toInt(q23 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ - or([q25 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q23] + sum([toInt(q21 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker /\ + or([q23 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q21] /\ and([p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values - [q23, q25, q26] - = q1[q26] - | q26 : int(1..2)]) - | q25 : int(1..4)])) - | q23 : int(1..4)]) + [q21, q23, q24] + = q1[q24] + | q24 : int(1..2)]) + | q23 : int(1..4)])) + | q21 : int(1..4)]) | q1 : matrix indexed by [int(1..2)] of int(1..2)]), - and([q28 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> - p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q28] >= 1 - | q28 : int(1..4)]), + and([q26 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> + p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q26] >= 1 + | q26 : int(1..4)]), and([q4 + 1 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> flatten([[p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q4]; int(1)], flatten([[p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values @@ -51,24 +51,21 @@ such that p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker <= 4, and([q6 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> and([q7 + 1 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q6] -> - [p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q6, q7, q18] - | q18 : int(1..2)] - and([q8 > p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q6] -> - and([p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q6, q8, q20] = 1 - | q20 : int(1..2)]) + and([p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q6, q8, q18] = 1 + | q18 : int(1..2)]) | q8 : int(1..4)]) | q6 : int(1..4)]), and([q6 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q6] <= 4 | q6 : int(1..4)]), 4 = - sum([toInt(q21 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker) * - catchUndef(p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q21], 0) - | q21 : int(1..4)]) + sum([toInt(q19 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker) * + catchUndef(p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q19], 0) + | q19 : int(1..4)]) From e1142c740fc1c0a2cddb921d575d20afb8b25e72 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?=C3=96zg=C3=BCr=20Akg=C3=BCn?= Date: Wed, 28 Feb 2024 19:08:39 +0000 Subject: [PATCH 139/229] adding general support for permutations (parsing/domainOf etc) --- src/Conjure/Language/AST/ASTParser.hs | 21 ++- src/Conjure/Language/AST/Reformer.hs | 6 + src/Conjure/Language/AST/Syntax.hs | 18 +- src/Conjure/Language/Lexemes.hs | 1 + src/Conjure/Language/Validator.hs | 32 +++- src/Conjure/Process/FiniteGivens.hs | 3 + src/Conjure/Representations/Combined.hs | 2 +- src/Conjure/Representations/Permutation.hs | 135 -------------- .../Permutation/PermutationAsFunction.hs | 166 ++++++++++++++++++ src/Conjure/UI/Model.hs | 1 - 10 files changed, 237 insertions(+), 148 deletions(-) delete mode 100644 src/Conjure/Representations/Permutation.hs create mode 100644 src/Conjure/Representations/Permutation/PermutationAsFunction.hs diff --git a/src/Conjure/Language/AST/ASTParser.hs b/src/Conjure/Language/AST/ASTParser.hs index 5cedebfd99..841ea83032 100644 --- a/src/Conjure/Language/AST/ASTParser.hs +++ b/src/Conjure/Language/AST/ASTParser.hs @@ -25,7 +25,7 @@ import Data.Text qualified as T import Data.Text.Lazy qualified as L import Text.Megaparsec -newtype ParserError = ParserError (Doc) +newtype ParserError = ParserError Doc deriving (Show) runASTParser :: (HighLevelTree a) => Parser a -> ETokenStream -> Either ParserError a @@ -281,6 +281,7 @@ parseLiteral = parseMSetLiteral, parseFunctionLiteral, parseSequenceLiteral, + parsePermutationLiteral, parseRelationLiteral, parsePartitionLiteral ] @@ -358,6 +359,12 @@ parseSequenceLiteral = do members <- parenList (commaList parseExpression) return $ SequenceLiteral lSeq members +parsePermutationLiteral :: Parser LiteralNode +parsePermutationLiteral = do + lPer <- need L_permutation + members <- parenList (commaList parsePermutationElem) + return $ PermutationLiteral lPer members + parseRelationLiteral :: Parser LiteralNode parseRelationLiteral = do lRel <- need L_relation @@ -380,6 +387,15 @@ parsePartitionLiteral = do members <- parenList (commaList parsePartitionElem) return $ PartitionLiteral lPartition members +parsePermutationElem :: Parser PermutationElemNode +parsePermutationElem = try $ do + lOpen <- needWeak L_OpenParen + exprs <- commaList parseExpression + let Seq xs = exprs + guard (length xs >= 2) + lClose <- want L_CloseParen + return $ PermutationElemNode $ ListNode lOpen exprs lClose + parsePartitionElem :: Parser PartitionElemNode parsePartitionElem = PartitionElemNode <$> parseList L_OpenCurly L_CloseCurly (commaList parseExpression) @@ -610,7 +626,6 @@ parseSpecialCase = do exp1 <- parseExpression lAt <- need L_At (decsl, p2) <- manyTill_ parseTopLevel (need L_CloseCurly) - return $ ExprWithDecls p1 exp1 lAt decsl p2 parseIntDomain :: Parser DomainNode @@ -703,7 +718,7 @@ parseSequenceDomain = do parsePermutationDomain :: Parser DomainNode parsePermutationDomain = do lPermutation <- need L_permutation --- attributes <- optional parseAttributes + -- attributes <- optional parseAttributes lOf <- want L_of domain <- parseDomain return $ PermutationDomainNode lPermutation Nothing lOf domain diff --git a/src/Conjure/Language/AST/Reformer.hs b/src/Conjure/Language/AST/Reformer.hs index d545823f8a..a69d462a4d 100644 --- a/src/Conjure/Language/AST/Reformer.hs +++ b/src/Conjure/Language/AST/Reformer.hs @@ -140,9 +140,13 @@ instance HighLevelTree LiteralNode where MSetLiteral lt ln -> makeTree lt <> makeTree ln FunctionLiteral lt ln -> makeTree lt <> makeTree ln SequenceLiteral lt ln -> makeTree lt <> makeTree ln + PermutationLiteral lt ln -> makeTree lt <> makeTree ln RelationLiteral lt ln -> makeTree lt <> makeTree ln PartitionLiteral lt ln -> makeTree lt <> makeTree ln +instance HighLevelTree PermutationElemNode where + makeTree (PermutationElemNode ln) = makeTree ln + instance HighLevelTree PartitionElemNode where makeTree (PartitionElemNode ln) = makeTree ln @@ -337,6 +341,8 @@ instance HighLevelTree (ListNode ArrowPairNode) where makeTree = taggedList ICIdentifier instance HighLevelTree (ListNode RelationElemNode) where makeTree = taggedList ICIdentifier +instance HighLevelTree (ListNode PermutationElemNode) where + makeTree = taggedList ICIdentifier instance HighLevelTree (ListNode PartitionElemNode) where makeTree = taggedList ICIdentifier instance HighLevelTree (ListNode NamedDomainNode) where diff --git a/src/Conjure/Language/AST/Syntax.hs b/src/Conjure/Language/AST/Syntax.hs index 0a7647e8aa..7d7ee90858 100644 --- a/src/Conjure/Language/AST/Syntax.hs +++ b/src/Conjure/Language/AST/Syntax.hs @@ -393,6 +393,7 @@ data LiteralNode | MSetLiteral SToken (ListNode ExpressionNode) | FunctionLiteral SToken (ListNode ArrowPairNode) | SequenceLiteral SToken (ListNode ExpressionNode) + | PermutationLiteral SToken (ListNode PermutationElemNode) | RelationLiteral SToken (ListNode RelationElemNode) | PartitionLiteral SToken (ListNode PartitionElemNode) deriving (Show, Data) @@ -410,6 +411,7 @@ instance Pretty LiteralNode where MSetLiteral lt ln -> pretty lt <> pretty ln FunctionLiteral lt ln -> pretty lt <> pretty ln SequenceLiteral lt ln -> pretty lt <> pretty ln + PermutationLiteral lt ln -> pretty lt <> pretty ln RelationLiteral lt ln -> pretty lt <> pretty ln PartitionLiteral lt ln -> pretty lt <> pretty ln @@ -467,6 +469,13 @@ instance Null RelationElemNode where isMissing (RelationElemNodeLabeled lt) = isMissing lt isMissing (RelationElemNodeShort st) = isMissing st +newtype PermutationElemNode = PermutationElemNode (ListNode ExpressionNode) + deriving (Show, Data) +instance Pretty PermutationElemNode where + pretty (PermutationElemNode l) = pretty l +instance Null PermutationElemNode where + isMissing (PermutationElemNode l) = isMissing l + newtype PartitionElemNode = PartitionElemNode (ListNode ExpressionNode) deriving (Show, Data) instance Pretty PartitionElemNode where @@ -589,6 +598,7 @@ instance Pretty PostfixOpNode where data IndexerNode = Indexer deriving (Show, Data) + data ListNode itemType = ListNode { lOpBracket :: LToken , items :: Sequence itemType @@ -596,13 +606,6 @@ data ListNode itemType = ListNode } deriving (Show, Data) --- prettyList :: Pretty a => ListNode a > Doc --- prettyList (ListNode start es end) = group $ align $ cat $ --- [ --- pretty start , --- flatAlt (indent 4 $ pretty es) (pretty es) , --- pretty end --- ] instance Pretty a => Pretty (ListNode a) where pretty (ListNode start es end) = group $ @@ -615,6 +618,7 @@ instance Pretty a => Pretty (ListNode a) where instance (Null a) => Null (ListNode a) where isMissing (ListNode l1 s l2) = isMissing l1 && isMissing s && isMissing l2 + newtype Sequence itemType = Seq { elems :: [SeqElem itemType] } diff --git a/src/Conjure/Language/Lexemes.hs b/src/Conjure/Language/Lexemes.hs index d8d2061378..da629c50ca 100644 --- a/src/Conjure/Language/Lexemes.hs +++ b/src/Conjure/Language/Lexemes.hs @@ -359,6 +359,7 @@ lexemes = sortBy (flip (comparing (T.length . fst))) $ map swap , ( L_surjective, "surjective" ) , ( L_bijective, "bijective" ) , ( L_sequence, "sequence" ) + , ( L_permutation, "permutation" ) , ( L_relation, "relation") , ( L_reflexive, "reflexive") , ( L_irreflexive, "irreflexive") diff --git a/src/Conjure/Language/Validator.hs b/src/Conjure/Language/Validator.hs index 6e969ccac5..9cd32e3f56 100644 --- a/src/Conjure/Language/Validator.hs +++ b/src/Conjure/Language/Validator.hs @@ -730,7 +730,7 @@ validateDomain dm = setCategoryLimit (CatParameter, "Domain") $ case dm of l1 `isA` TtType putDocs TypeD "permutation" l1 l2 `isA'` TtSubKeyword - validateSequenceDomain attrs dom + validatePermutationDomain attrs dom RelationDomainNode l1 attrs l2 doms -> do l1 `isA` TtType putDocs TypeD "relation" l1 @@ -854,6 +854,16 @@ validateDomain dm = setCategoryLimit (CatParameter, "Domain") $ case dm of Nothing -> return def (t, dom') <- typeSplit <$> validateDomain dom return . Typed (TypeSequence t) $ DomainSequence repr attrs' dom' + + validatePermutationDomain :: Maybe (ListNode AttributeNode) -> DomainNode -> ValidatorS TypedDomain + validatePermutationDomain attrs dom = do + let repr = () + attrs' <- case attrs of + Just a -> validatePermutationAttributes a + Nothing -> return def + (t, dom') <- typeSplit <$> validateDomain dom + return . Typed (TypePermutation t) $ DomainPermutation repr attrs' dom' + validateRelationDomain :: Maybe (ListNode AttributeNode) -> ListNode DomainNode -> ValidatorS TypedDomain validateRelationDomain attrs doms = do let repr = () @@ -863,6 +873,7 @@ validateDomain dm = setCategoryLimit (CatParameter, "Domain") $ case dm of (ts, doms') <- unzip . map typeSplit <$> validateList_ validateDomain doms return . Typed (TypeRelation ts) $ DomainRelation repr attrs' doms' + validatePartitionDomain :: Maybe (ListNode AttributeNode) -> DomainNode -> ValidatorS TypedDomain validatePartitionDomain attrs dom = do let repr = () @@ -971,6 +982,12 @@ validateSeqAttributes atts = do jectivity <- validateJectivityAttributes attrs return $ SequenceAttr size jectivity +validatePermutationAttributes :: ListNode AttributeNode -> ValidatorS (PermutationAttr Expression) +validatePermutationAttributes atts = do + attrs <- catMaybes <$> validateList_ (validateAttributeNode setValidAttrs) atts + size <- validateSizeAttributes attrs + return $ PermutationAttr size + validateRelationAttributes :: ListNode AttributeNode -> ValidatorS (RelationAttr Expression) validateRelationAttributes atts = do setContextFrom atts @@ -1458,6 +1475,7 @@ validateLiteral litNode = case litNode of MSetLiteral lt ls -> lt `isA` TtType >> validateMSetLiteral ls FunctionLiteral lt ln -> lt `isA` TtType >> validateFunctionLiteral ln SequenceLiteral lt ln -> lt `isA` TtType >> validateSequenceLiteral ln + PermutationLiteral lt ln -> lt `isA` TtType >> validatePermutationLiteral ln RelationLiteral lt ln -> lt `isA` TtType >> validateRelationLiteral ln PartitionLiteral lt ln -> lt `isA` TtType >> validatePartitionLiteral ln @@ -1467,6 +1485,18 @@ validateSequenceLiteral x = do let lType = TypeSequence t return . Typed lType $ mkAbstractLiteral $ AbsLitSequence ss +validatePermutationLiteral :: ListNode PermutationElemNode -> ValidatorS (Typed Expression) +validatePermutationLiteral x = do + members <- validateList validatePermutationElem x + (t, xs) <- typeSplit <$> sameType members + let eType = TypePermutation t + return $ Typed eType (mkAbstractLiteral $ AbsLitPermutation xs) + where + validatePermutationElem :: PermutationElemNode -> ValidatorS (Typed [Expression]) + validatePermutationElem (PermutationElemNode exprs) = do + xs <- validateExprList exprs + sameType xs + validateRelationLiteral :: ListNode RelationElemNode -> ValidatorS (Typed Expression) validateRelationLiteral ln = do ms <- validateList validateRelationMember ln diff --git a/src/Conjure/Process/FiniteGivens.hs b/src/Conjure/Process/FiniteGivens.hs index cd1011a9f5..eda607de53 100644 --- a/src/Conjure/Process/FiniteGivens.hs +++ b/src/Conjure/Process/FiniteGivens.hs @@ -122,12 +122,14 @@ mkFinite d@DomainMatrix{} = mkFiniteOutermost d mkFinite d@DomainSet{} = mkFiniteOutermost d mkFinite d@DomainMSet{} = mkFiniteOutermost d mkFinite d@DomainSequence{} = mkFiniteOutermost d +mkFinite d@DomainPermutation{} = mkFiniteOutermost d mkFinite d@DomainFunction{} = mkFiniteOutermost d mkFinite d@DomainRelation{} = mkFiniteOutermost d mkFinite d@DomainPartition{} = mkFiniteOutermost d mkFinite d = return (d, [], const (return [])) +-- TODO add permutation support mkFiniteOutermost :: MonadFailDoc m => MonadState Int m => @@ -359,6 +361,7 @@ mkFiniteOutermost (DomainPartition () (PartitionAttr _ _ isRegularAttr) inner) = mkFiniteOutermost d = return (d, [], const (return [])) +-- TODO add permutation support mkFiniteInner :: MonadFailDoc m => MonadState Int m => diff --git a/src/Conjure/Representations/Combined.hs b/src/Conjure/Representations/Combined.hs index ee1c2366c4..b3d1ad8c6e 100644 --- a/src/Conjure/Representations/Combined.hs +++ b/src/Conjure/Representations/Combined.hs @@ -36,11 +36,11 @@ import Conjure.Representations.Function.FunctionNDPartial import Conjure.Representations.Function.FunctionNDPartialDummy import Conjure.Representations.Function.FunctionAsRelation import Conjure.Representations.Sequence.ExplicitBounded +import Conjure.Representations.Permutation.PermutationAsFunction import Conjure.Representations.Relation.RelationAsMatrix import Conjure.Representations.Relation.RelationAsSet import Conjure.Representations.Partition.Occurrence import Conjure.Representations.Partition.PartitionAsSet -import Conjure.Representations.Permutation -- | Refine (down) a domain, outputting refinement expressions (X) one level (1). diff --git a/src/Conjure/Representations/Permutation.hs b/src/Conjure/Representations/Permutation.hs deleted file mode 100644 index 72cce25824..0000000000 --- a/src/Conjure/Representations/Permutation.hs +++ /dev/null @@ -1,135 +0,0 @@ -{-# LANGUAGE RecordWildCards #-} -{-# LANGUAGE QuasiQuotes #-} -{-# LANGUAGE ViewPatterns #-} -{-# LANGUAGE Rank2Types #-} - -module Conjure.Representations.Permutation ( permutationAsFunction ) where - --- conjure -import Conjure.Prelude -import Conjure.Util.Permutation -import Conjure.Language -import Conjure.Language.DomainSizeOf -import Conjure.Language.Expression.DomainSizeOf () -import Conjure.Representations.Internal -import Conjure.Representations.Common -import Conjure.Process.Enumerate - - -permutationAsFunction - :: forall m . (MonadFail m, NameGen m, EnumerateDomain m) - => (forall x . DispatchFunction m x) - -> Representation m -permutationAsFunction dispatch = Representation chck downD structuralCons downC up symmetryOrdering - where - chck :: TypeOf_ReprCheck m - chck f (DomainPermutation _ s innerDomain) - | domainCanIndexMatrix innerDomain - = map (DomainPermutation Permutation_AsFunction s) <$> f innerDomain - chck _ _ = return [] - - outName :: Domain HasRepresentation x -> Name -> Name - outName name domain = mkOutName (Just "PermutationFunction") name domain - - - - outDomain :: (DomainSizeOf x x, Pretty x) => Domain HasRepresentation x -> m (Domain HasRepresentation x) - outDomain (DomainPermutation Permutation_AsFunction _ innerDomain) = do - s <- domainSizeOf innerDomain - return (DomainFunction (Function_1D) - (FunctionAttr (SizeAttr_Size s) PartialityAttr_Total JectivityAttr_Bijective) innerDomain innerDomain) - outDomain domain = na $ vcat [ "{outDomain} PermutationAsFunction" - , "domain:" <+> pretty domain - ] - - - downD :: TypeOf_DownD m - downD (name, domain@(DomainPermutation Permutation_AsFunction _ innerDomain)) - | domainCanIndexMatrix innerDomain = do - m <- domainSizeOf innerDomain - return $ Just - [ ( outName domain name - , DomainFunction (Function_1D) - (FunctionAttr (SizeAttr_Size m) PartialityAttr_Total JectivityAttr_Bijective) innerDomain innerDomain - ) - ] - downD _ = na "{downD} AsFunction" - - - structuralCons :: TypeOf_Structural m - structuralCons f downX1 inDom@(DomainPermutation _ (PermutationAttr s) innerDom) - = return $ \inpFun -> do - refs <- downX1 inpFun - case refs of - [fun] -> do - outDom <- outDomain inDom - innerStructuralConsGen <- f outDom - (iPat, i) <- quantifiedVarOverDomain (forgetRepr innerDom) - concat <$> sequence [ innerStructuralConsGen fun - , return $ mkSizeCons s [essence| - sum([ toInt(&i != image(&fun, &i)) | &iPat : &innerDom ]) - |] - ] - _ -> na $ vcat [ "{structuralCons} PermutationAsFunction" - , pretty inDom - ] - structuralCons _ _ inDom = - na $ vcat [ "{structuralCons} PermutationAsFunction" - , pretty inDom - ] - - downC :: TypeOf_DownC m - downC ( name - , inDom@(DomainPermutation Permutation_AsFunction _ innerDom) - , ConstantAbstract (AbsLitPermutation vals) - ) = do - outDom <- outDomain inDom - enumDo <- enumerateDomain $ forgetRepr innerDom - case fromCycles vals of - Right perm -> - rDownC - (dispatch outDom) - ( outName inDom name - , outDom - , ConstantAbstract $ AbsLitFunction $ zip enumDo (toFunction perm <$> enumDo) - ) - Left (PermutationError err) -> failDoc $ "PermutationError: " <+> stringToDoc err - - downC (name, domain, constant) = na $ vcat [ "{downC} PermutationAsFunction" - , "name:" <+> pretty name - , "domain:" <+> pretty domain - , "constant:" <+> pretty constant - ] - - - up :: TypeOf_Up m - up ctxt ( name - , domain@(DomainPermutation Permutation_AsFunction{} _ _)) = do - case ( lookup (outName domain name) ctxt) of - (Just (ConstantAbstract (AbsLitFunction f))) -> do - case toCyclesCanonical <$> fromRelation f of - Right cycles -> - return (name, ConstantAbstract (AbsLitPermutation cycles)) - Left (PermutationError err) -> failDoc $ vcat $ - [ "PermutationError: " <+> stringToDoc err - , "No value for:" <+> pretty (outName domain name) - , "When working on:" <+> pretty name - , "With domain:" <+> pretty domain - ] ++ - ("Bindings in context:" : prettyContext ctxt) - _ -> failDoc $ vcat $ - [ "No value for:" <+> pretty (outName domain name) - , "When working on:" <+> pretty name - , "With domain:" <+> pretty domain - ] ++ - ("Bindings in context:" : prettyContext ctxt) - up _ (name, domain) = na $ vcat [ "{up} PermutationAsFunction" - , "name:" <+> pretty name - , "domain:" <+> pretty domain - ] - - symmetryOrdering :: TypeOf_SymmetryOrdering m - symmetryOrdering innerSO downX1 inp domain = do - [x] <- downX1 inp - Just [(_, xDomain)] <- downD ("SO", domain) - innerSO downX1 x xDomain diff --git a/src/Conjure/Representations/Permutation/PermutationAsFunction.hs b/src/Conjure/Representations/Permutation/PermutationAsFunction.hs new file mode 100644 index 0000000000..8170b0be50 --- /dev/null +++ b/src/Conjure/Representations/Permutation/PermutationAsFunction.hs @@ -0,0 +1,166 @@ +{-# LANGUAGE QuasiQuotes #-} +{-# LANGUAGE Rank2Types #-} +{-# LANGUAGE RecordWildCards #-} +{-# LANGUAGE ViewPatterns #-} + +module Conjure.Representations.Permutation.PermutationAsFunction (permutationAsFunction) where + +-- conjure + +import Conjure.Language +import Conjure.Language.DomainSizeOf +import Conjure.Language.Expression.DomainSizeOf () +import Conjure.Prelude +import Conjure.Process.Enumerate +import Conjure.Representations.Common +import Conjure.Representations.Internal +import Conjure.Util.Permutation + +permutationAsFunction :: + forall m. + (MonadFail m, NameGen m, EnumerateDomain m) => + (forall x. DispatchFunction m x) -> + Representation m +permutationAsFunction dispatch = Representation chck downD structuralCons downC up symmetryOrdering + where + chck :: TypeOf_ReprCheck m + chck f (DomainPermutation _ s innerDomain) + | domainCanIndexMatrix innerDomain = + map (DomainPermutation Permutation_AsFunction s) <$> f innerDomain + chck _ _ = return [] + + outName :: Domain HasRepresentation x -> Name -> Name + outName = mkOutName (Just "PermutationFunction") + + outDomain :: (DomainSizeOf x x, Pretty x) => Domain HasRepresentation x -> m (Domain HasRepresentation x) + outDomain (DomainPermutation Permutation_AsFunction _ innerDomain) = do + s <- domainSizeOf innerDomain + return + ( DomainFunction + Function_1D + (FunctionAttr (SizeAttr_Size s) PartialityAttr_Total JectivityAttr_Bijective) + innerDomain + innerDomain + ) + outDomain domain = + na $ + vcat + [ "{outDomain} PermutationAsFunction", + "domain:" <+> pretty domain + ] + + downD :: TypeOf_DownD m + downD (name, domain@(DomainPermutation Permutation_AsFunction _ innerDomain)) + | domainCanIndexMatrix innerDomain = do + m <- domainSizeOf innerDomain + return $ + Just + [ ( outName domain name, + DomainFunction + Function_1D + (FunctionAttr (SizeAttr_Size m) PartialityAttr_Total JectivityAttr_Bijective) + innerDomain + innerDomain + ) + ] + downD _ = na "{downD} AsFunction" + + structuralCons :: TypeOf_Structural m + structuralCons f downX1 inDom@(DomainPermutation _ (PermutationAttr s) innerDom) = + return $ \inpFun -> do + refs <- downX1 inpFun + case refs of + [fun] -> do + outDom <- outDomain inDom + innerStructuralConsGen <- f outDom + (iPat, i) <- quantifiedVarOverDomain (forgetRepr innerDom) + concat + <$> sequence + [ innerStructuralConsGen fun, + return $ + mkSizeCons + s + [essence| + sum([ toInt(&i != image(&fun, &i)) | &iPat : &innerDom ]) + |] + ] + _ -> + na $ + vcat + [ "{structuralCons} PermutationAsFunction", + pretty inDom + ] + structuralCons _ _ inDom = + na $ + vcat + [ "{structuralCons} PermutationAsFunction", + pretty inDom + ] + + downC :: TypeOf_DownC m + downC + ( name, + inDom@(DomainPermutation Permutation_AsFunction _ innerDom), + ConstantAbstract (AbsLitPermutation vals) + ) = do + outDom <- outDomain inDom + enumDo <- enumerateDomain $ forgetRepr innerDom + case fromCycles vals of + Right perm -> + rDownC + (dispatch outDom) + ( outName inDom name, + outDom, + ConstantAbstract $ AbsLitFunction $ zip enumDo (toFunction perm <$> enumDo) + ) + Left (PermutationError err) -> failDoc $ "PermutationError: " <+> stringToDoc err + downC (name, domain, constant) = + na $ + vcat + [ "{downC} PermutationAsFunction", + "name:" <+> pretty name, + "domain:" <+> pretty domain, + "constant:" <+> pretty constant + ] + + up :: TypeOf_Up m + up + ctxt + ( name, + domain@(DomainPermutation Permutation_AsFunction {} _ _) + ) = do + case lookup (outName domain name) ctxt of + (Just (ConstantAbstract (AbsLitFunction f))) -> do + case toCyclesCanonical <$> fromRelation f of + Right cycles -> + return (name, ConstantAbstract (AbsLitPermutation cycles)) + Left (PermutationError err) -> + failDoc $ + vcat $ + [ "PermutationError: " <+> stringToDoc err, + "No value for:" <+> pretty (outName domain name), + "When working on:" <+> pretty name, + "With domain:" <+> pretty domain + ] + ++ ("Bindings in context:" : prettyContext ctxt) + _ -> + failDoc $ + vcat $ + [ "No value for:" <+> pretty (outName domain name), + "When working on:" <+> pretty name, + "With domain:" <+> pretty domain + ] + ++ ("Bindings in context:" : prettyContext ctxt) + up _ (name, domain) = + na $ + vcat + [ "{up} PermutationAsFunction", + "name:" <+> pretty name, + "domain:" <+> pretty domain + ] + + symmetryOrdering :: TypeOf_SymmetryOrdering m + symmetryOrdering innerSO downX1 inp domain = do + [x] <- downX1 inp + Just [(_, xDomain)] <- downD ("SO", domain) + innerSO downX1 x xDomain diff --git a/src/Conjure/UI/Model.hs b/src/Conjure/UI/Model.hs index b3fddcf8f4..395fe0321e 100644 --- a/src/Conjure/UI/Model.hs +++ b/src/Conjure/UI/Model.hs @@ -2884,7 +2884,6 @@ addUnnamedSymmetryBreaking mode model = do USBComplete -> let applied = buildPermutationChain perms varsTuple thisAuxTuple = mkAuxTuple auxSuffix - dVars = map fst (allDecVarsAux auxSuffix) in nestInBubbles varsTuple 1 (zip dVars newDecls) [essence| &thisAuxTuple = &applied |] From f002f241abf7c522b43a582d78961ec1ead9a5ed Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?=C3=96zg=C3=BCr=20Akg=C3=BCn?= Date: Wed, 28 Feb 2024 19:10:39 +0000 Subject: [PATCH 140/229] moved the permutation representation module --- conjure-cp.cabal | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/conjure-cp.cabal b/conjure-cp.cabal index 0a503847af..af130db38c 100644 --- a/conjure-cp.cabal +++ b/conjure-cp.cabal @@ -189,11 +189,11 @@ Library , Conjure.Representations.Function.FunctionNDPartialDummy , Conjure.Representations.Function.FunctionAsRelation , Conjure.Representations.Sequence.ExplicitBounded + , Conjure.Representations.Permutation.PermutationAsFunction , Conjure.Representations.Relation.RelationAsMatrix , Conjure.Representations.Relation.RelationAsSet , Conjure.Representations.Partition.Occurrence , Conjure.Representations.Partition.PartitionAsSet - , Conjure.Representations.Permutation -- definitions of rules , Conjure.Rules.Definition From efb43eb4b3ed187918016274939a2cd96aa88f7d Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?=C3=96zg=C3=BCr=20Akg=C3=BCn?= Date: Wed, 28 Feb 2024 23:23:01 +0000 Subject: [PATCH 141/229] parse permutation attributes and validate permutations --- src/Conjure/Language/AST/ASTParser.hs | 4 ++-- src/Conjure/Language/Validator.hs | 3 ++- .../0006_find_permutation_size_0_of_int1_4/stdout.expected | 2 +- .../enum/0007_letting_permutation_be_empty/stdout.expected | 2 +- .../0006_find_permutation_size_0_of_int1_4/stdout.expected | 2 +- .../int/0007_letting_permutation_be_empty/stdout.expected | 2 +- .../0006_find_permutation_size_0_of_int1_4/stdout.expected | 2 +- .../unnamed/0007_letting_permutation_be_empty/stdout.expected | 2 +- 8 files changed, 10 insertions(+), 9 deletions(-) diff --git a/src/Conjure/Language/AST/ASTParser.hs b/src/Conjure/Language/AST/ASTParser.hs index 841ea83032..98d5eed1c3 100644 --- a/src/Conjure/Language/AST/ASTParser.hs +++ b/src/Conjure/Language/AST/ASTParser.hs @@ -718,10 +718,10 @@ parseSequenceDomain = do parsePermutationDomain :: Parser DomainNode parsePermutationDomain = do lPermutation <- need L_permutation - -- attributes <- optional parseAttributes + attributes <- optional parseAttributes lOf <- want L_of domain <- parseDomain - return $ PermutationDomainNode lPermutation Nothing lOf domain + return $ PermutationDomainNode lPermutation attributes lOf domain parseRelation :: Parser DomainNode parseRelation = do diff --git a/src/Conjure/Language/Validator.hs b/src/Conjure/Language/Validator.hs index 9cd32e3f56..f30f3a28b2 100644 --- a/src/Conjure/Language/Validator.hs +++ b/src/Conjure/Language/Validator.hs @@ -1102,9 +1102,10 @@ validateExpression expr = do TypeMSet {} -> return () TypeFunction {} -> return () TypeSequence {} -> return () + TypePermutation {} -> return () TypeRelation {} -> return () TypePartition {} -> return () - _ -> contextTypeError $ ComplexTypeError "Int or collection" t + _ -> contextTypeError $ ComplexTypeError "integer or collection" t validateFlexibleExpression :: ExpressionNode -> ValidatorS (Kind, Expression) validateFlexibleExpression (IdentifierNode name) = do diff --git a/tests/custom/permutations/01_representation/enum/0006_find_permutation_size_0_of_int1_4/stdout.expected b/tests/custom/permutations/01_representation/enum/0006_find_permutation_size_0_of_int1_4/stdout.expected index 573892e500..b4f1327bab 100644 --- a/tests/custom/permutations/01_representation/enum/0006_find_permutation_size_0_of_int1_4/stdout.expected +++ b/tests/custom/permutations/01_representation/enum/0006_find_permutation_size_0_of_int1_4/stdout.expected @@ -4,7 +4,7 @@ Saved under: conjure-output Savile Row: model000001.eprime Running minion for domain filtering. Running solver: minion -Copying solution to: permutation.solution +Copying solution to: permutation-000001.solution language Essence 1.3 letting p be permutation() diff --git a/tests/custom/permutations/01_representation/enum/0007_letting_permutation_be_empty/stdout.expected b/tests/custom/permutations/01_representation/enum/0007_letting_permutation_be_empty/stdout.expected index 0d4e03724a..ec07b6eae6 100644 --- a/tests/custom/permutations/01_representation/enum/0007_letting_permutation_be_empty/stdout.expected +++ b/tests/custom/permutations/01_representation/enum/0007_letting_permutation_be_empty/stdout.expected @@ -4,6 +4,6 @@ Saved under: conjure-output Savile Row: model000001.eprime Running minion for domain filtering. Running solver: minion -Copying solution to: permutation.solution +Copying solution to: permutation-000001.solution language Essence 1.3 diff --git a/tests/custom/permutations/01_representation/int/0006_find_permutation_size_0_of_int1_4/stdout.expected b/tests/custom/permutations/01_representation/int/0006_find_permutation_size_0_of_int1_4/stdout.expected index 573892e500..b4f1327bab 100644 --- a/tests/custom/permutations/01_representation/int/0006_find_permutation_size_0_of_int1_4/stdout.expected +++ b/tests/custom/permutations/01_representation/int/0006_find_permutation_size_0_of_int1_4/stdout.expected @@ -4,7 +4,7 @@ Saved under: conjure-output Savile Row: model000001.eprime Running minion for domain filtering. Running solver: minion -Copying solution to: permutation.solution +Copying solution to: permutation-000001.solution language Essence 1.3 letting p be permutation() diff --git a/tests/custom/permutations/01_representation/int/0007_letting_permutation_be_empty/stdout.expected b/tests/custom/permutations/01_representation/int/0007_letting_permutation_be_empty/stdout.expected index 0d4e03724a..ec07b6eae6 100644 --- a/tests/custom/permutations/01_representation/int/0007_letting_permutation_be_empty/stdout.expected +++ b/tests/custom/permutations/01_representation/int/0007_letting_permutation_be_empty/stdout.expected @@ -4,6 +4,6 @@ Saved under: conjure-output Savile Row: model000001.eprime Running minion for domain filtering. Running solver: minion -Copying solution to: permutation.solution +Copying solution to: permutation-000001.solution language Essence 1.3 diff --git a/tests/custom/permutations/01_representation/unnamed/0006_find_permutation_size_0_of_int1_4/stdout.expected b/tests/custom/permutations/01_representation/unnamed/0006_find_permutation_size_0_of_int1_4/stdout.expected index b653a04f8e..bd08d5f4ce 100644 --- a/tests/custom/permutations/01_representation/unnamed/0006_find_permutation_size_0_of_int1_4/stdout.expected +++ b/tests/custom/permutations/01_representation/unnamed/0006_find_permutation_size_0_of_int1_4/stdout.expected @@ -4,7 +4,7 @@ Saved under: conjure-output Savile Row: model000001.eprime Running minion for domain filtering. Running solver: minion -Copying solution to: permutation.solution +Copying solution to: permutation-000001.solution language Essence 1.3 letting n be new type enum {n_1, n_2, n_3, n_4} diff --git a/tests/custom/permutations/01_representation/unnamed/0007_letting_permutation_be_empty/stdout.expected b/tests/custom/permutations/01_representation/unnamed/0007_letting_permutation_be_empty/stdout.expected index 0d4e03724a..ec07b6eae6 100644 --- a/tests/custom/permutations/01_representation/unnamed/0007_letting_permutation_be_empty/stdout.expected +++ b/tests/custom/permutations/01_representation/unnamed/0007_letting_permutation_be_empty/stdout.expected @@ -4,6 +4,6 @@ Saved under: conjure-output Savile Row: model000001.eprime Running minion for domain filtering. Running solver: minion -Copying solution to: permutation.solution +Copying solution to: permutation-000001.solution language Essence 1.3 From 51d0b0bbaa2a0b16cbf78726c37db80b975d5e75 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?=C3=96zg=C3=BCr=20Akg=C3=BCn?= Date: Fri, 1 Mar 2024 09:41:02 +0000 Subject: [PATCH 142/229] some more tests passing --- .../0001_given_permutation_given_enum/stdout.expected | 10 +++++----- .../0004_given_permutation_find_enum/stdout.expected | 6 +++++- .../0005_find_permutation_given_enums/stdout.expected | 10 +++++----- .../stdout.expected | 10 +++++----- .../0001_given_permutation_given_int/stdout.expected | 10 +++++----- .../0004_given_permutation_find_int/stdout.expected | 6 +++++- .../0005_find_permutation_given_ints/stdout.expected | 10 +++++----- .../0006_letting_permutation_given_int/stdout.expected | 10 +++++----- .../0001_given_permutations_in_param/stdout.expected | 8 +++++++- .../enum/0003_letting_and_find/stdout.expected | 10 +++++----- .../0001_given_permutations_in_param/stdout.expected | 8 +++++++- .../int/0003_letting_and_find/stdout.expected | 10 +++++----- .../int/0005_find_composition/stdout.expected | 2 +- .../int/0006_find_composition/stdout.expected | 2 +- .../0010_given_partition_of_enum_BUG/stderr.expected | 6 ------ .../0010_given_partition_of_enum_BUG/stdout.expected | 5 +++++ .../0020_find_partition_of_enum_BUG/stderr.expected | 7 ------- .../0020_find_partition_of_enum_BUG/stdout.expected | 9 +++++++++ .../expected/model-cyc1-solution000001.solution | 7 ------- .../expected/model-cyc2-solution000001.solution | 6 ------ .../permutation-permutation.solution | 2 ++ .../permutation.eprime-param | 3 +++ .../expected/model-permutation-solution000001.solution | 4 ---- .../expected/model-permutation-solution000001.solution | 4 ---- .../expected/model-permutation-solution000001.solution | 4 ---- .../expected/model-permutation-solution000001.solution | 4 ---- .../expected/model-permutation-solution000001.solution | 4 ---- .../expected/model-permutation-solution000001.solution | 4 ---- 28 files changed, 85 insertions(+), 96 deletions(-) delete mode 100644 tests/custom/permutations/17_transform_partition/enum/0010_given_partition_of_enum_BUG/stderr.expected delete mode 100644 tests/custom/permutations/17_transform_partition/enum/0020_find_partition_of_enum_BUG/stderr.expected delete mode 100644 tests/exhaustive/basic/perms/01_representation/enum/0001_given_permutation_in_param/expected/model-cyc1-solution000001.solution delete mode 100644 tests/exhaustive/basic/perms/01_representation/enum/0001_given_permutation_in_param/expected/model-cyc2-solution000001.solution create mode 100644 tests/exhaustive/basic/perms/01_representation/enum/0001_given_permutation_in_param/permutation-permutation.solution create mode 100644 tests/exhaustive/basic/perms/01_representation/enum/0001_given_permutation_in_param/permutation.eprime-param diff --git a/tests/custom/permutations/04_image/enum/0001_given_permutation_given_enum/stdout.expected b/tests/custom/permutations/04_image/enum/0001_given_permutation_given_enum/stdout.expected index bd9c885558..96238bbb42 100644 --- a/tests/custom/permutations/04_image/enum/0001_given_permutation_given_enum/stdout.expected +++ b/tests/custom/permutations/04_image/enum/0001_given_permutation_given_enum/stdout.expected @@ -1,17 +1,17 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime permutation2.param +Savile Row: model000001.eprime permutation.param Running minion for domain filtering. Running solver: minion -Savile Row: model000001.eprime permutation.param +Savile Row: model000001.eprime permutation2.param Running minion for domain filtering. Running solver: minion -Copying solution to: permutation-permutation2.solution Copying solution to: permutation-permutation.solution +Copying solution to: permutation-permutation2.solution language Essence 1.3 -letting j be E6 +letting j be E3 language Essence 1.3 -letting j be E3 +letting j be E6 diff --git a/tests/custom/permutations/04_image/enum/0004_given_permutation_find_enum/stdout.expected b/tests/custom/permutations/04_image/enum/0004_given_permutation_find_enum/stdout.expected index 75ee4f23cb..ca4b67273f 100644 --- a/tests/custom/permutations/04_image/enum/0004_given_permutation_find_enum/stdout.expected +++ b/tests/custom/permutations/04_image/enum/0004_given_permutation_find_enum/stdout.expected @@ -2,9 +2,13 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output Savile Row: model000001.eprime permutation2.essence +Running minion for domain filtering. +Running solver: minion Savile Row: model000001.eprime permutation.param -Copying solution to: permutation-permutation2.solution +Running minion for domain filtering. +Running solver: minion Copying solution to: permutation-permutation.solution +Copying solution to: permutation-permutation2.solution language Essence 1.3 letting i be E1 diff --git a/tests/custom/permutations/04_image/enum/0005_find_permutation_given_enums/stdout.expected b/tests/custom/permutations/04_image/enum/0005_find_permutation_given_enums/stdout.expected index c98e25b9b7..89fe444110 100644 --- a/tests/custom/permutations/04_image/enum/0005_find_permutation_given_enums/stdout.expected +++ b/tests/custom/permutations/04_image/enum/0005_find_permutation_given_enums/stdout.expected @@ -1,17 +1,17 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime permutation2.param +Savile Row: model000001.eprime permutation.param Running minion for domain filtering. Running solver: minion -Savile Row: model000001.eprime permutation.param +Savile Row: model000001.eprime permutation2.param Running minion for domain filtering. Running solver: minion -Copying solution to: permutation-permutation2.solution Copying solution to: permutation-permutation.solution +Copying solution to: permutation-permutation2.solution language Essence 1.3 -letting p be permutation((E4, E5, E6)) +letting p be permutation((E3, E5, E4)) language Essence 1.3 -letting p be permutation((E3, E5, E4)) +letting p be permutation((E4, E5, E6)) diff --git a/tests/custom/permutations/04_image/enum/0006_letting_permutation_given_enum/stdout.expected b/tests/custom/permutations/04_image/enum/0006_letting_permutation_given_enum/stdout.expected index bd9c885558..96238bbb42 100644 --- a/tests/custom/permutations/04_image/enum/0006_letting_permutation_given_enum/stdout.expected +++ b/tests/custom/permutations/04_image/enum/0006_letting_permutation_given_enum/stdout.expected @@ -1,17 +1,17 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime permutation2.param +Savile Row: model000001.eprime permutation.param Running minion for domain filtering. Running solver: minion -Savile Row: model000001.eprime permutation.param +Savile Row: model000001.eprime permutation2.param Running minion for domain filtering. Running solver: minion -Copying solution to: permutation-permutation2.solution Copying solution to: permutation-permutation.solution +Copying solution to: permutation-permutation2.solution language Essence 1.3 -letting j be E6 +letting j be E3 language Essence 1.3 -letting j be E3 +letting j be E6 diff --git a/tests/custom/permutations/04_image/int/0001_given_permutation_given_int/stdout.expected b/tests/custom/permutations/04_image/int/0001_given_permutation_given_int/stdout.expected index e104d62518..1b04c05ccd 100644 --- a/tests/custom/permutations/04_image/int/0001_given_permutation_given_int/stdout.expected +++ b/tests/custom/permutations/04_image/int/0001_given_permutation_given_int/stdout.expected @@ -1,17 +1,17 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime permutation2.param +Savile Row: model000001.eprime permutation.param Running minion for domain filtering. Running solver: minion -Savile Row: model000001.eprime permutation.param +Savile Row: model000001.eprime permutation2.param Running minion for domain filtering. Running solver: minion -Copying solution to: permutation-permutation2.solution Copying solution to: permutation-permutation.solution +Copying solution to: permutation-permutation2.solution language Essence 1.3 -letting j be 6 +letting j be 3 language Essence 1.3 -letting j be 3 +letting j be 6 diff --git a/tests/custom/permutations/04_image/int/0004_given_permutation_find_int/stdout.expected b/tests/custom/permutations/04_image/int/0004_given_permutation_find_int/stdout.expected index 5ddaa104a4..ddc463d77a 100644 --- a/tests/custom/permutations/04_image/int/0004_given_permutation_find_int/stdout.expected +++ b/tests/custom/permutations/04_image/int/0004_given_permutation_find_int/stdout.expected @@ -2,9 +2,13 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output Savile Row: model000001.eprime permutation2.essence +Running minion for domain filtering. +Running solver: minion Savile Row: model000001.eprime permutation.param -Copying solution to: permutation-permutation2.solution +Running minion for domain filtering. +Running solver: minion Copying solution to: permutation-permutation.solution +Copying solution to: permutation-permutation2.solution language Essence 1.3 letting i be 1 diff --git a/tests/custom/permutations/04_image/int/0005_find_permutation_given_ints/stdout.expected b/tests/custom/permutations/04_image/int/0005_find_permutation_given_ints/stdout.expected index 6ed590db5c..12ea6f63e6 100644 --- a/tests/custom/permutations/04_image/int/0005_find_permutation_given_ints/stdout.expected +++ b/tests/custom/permutations/04_image/int/0005_find_permutation_given_ints/stdout.expected @@ -1,17 +1,17 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime permutation2.param +Savile Row: model000001.eprime permutation.param Running minion for domain filtering. Running solver: minion -Savile Row: model000001.eprime permutation.param +Savile Row: model000001.eprime permutation2.param Running minion for domain filtering. Running solver: minion -Copying solution to: permutation-permutation2.solution Copying solution to: permutation-permutation.solution +Copying solution to: permutation-permutation2.solution language Essence 1.3 -letting p be permutation((1, 2, 4)) +letting p be permutation((2, 4, 3)) language Essence 1.3 -letting p be permutation((2, 4, 3)) +letting p be permutation((1, 2, 4)) diff --git a/tests/custom/permutations/04_image/int/0006_letting_permutation_given_int/stdout.expected b/tests/custom/permutations/04_image/int/0006_letting_permutation_given_int/stdout.expected index e104d62518..1b04c05ccd 100644 --- a/tests/custom/permutations/04_image/int/0006_letting_permutation_given_int/stdout.expected +++ b/tests/custom/permutations/04_image/int/0006_letting_permutation_given_int/stdout.expected @@ -1,17 +1,17 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime permutation2.param +Savile Row: model000001.eprime permutation.param Running minion for domain filtering. Running solver: minion -Savile Row: model000001.eprime permutation.param +Savile Row: model000001.eprime permutation2.param Running minion for domain filtering. Running solver: minion -Copying solution to: permutation-permutation2.solution Copying solution to: permutation-permutation.solution +Copying solution to: permutation-permutation2.solution language Essence 1.3 -letting j be 6 +letting j be 3 language Essence 1.3 -letting j be 3 +letting j be 6 diff --git a/tests/custom/permutations/07_compose/enum/0001_given_permutations_in_param/stdout.expected b/tests/custom/permutations/07_compose/enum/0001_given_permutations_in_param/stdout.expected index 5034947736..0cba00099a 100644 --- a/tests/custom/permutations/07_compose/enum/0001_given_permutations_in_param/stdout.expected +++ b/tests/custom/permutations/07_compose/enum/0001_given_permutations_in_param/stdout.expected @@ -2,11 +2,17 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output Savile Row: model000001.eprime permutation2.essence +Running minion for domain filtering. +Running solver: minion Savile Row: model000001.eprime permutation3.essence +Running minion for domain filtering. +Running solver: minion Savile Row: model000001.eprime permutation.param +Running minion for domain filtering. +Running solver: minion +Copying solution to: permutation-permutation.solution Copying solution to: permutation-permutation2.solution Copying solution to: permutation-permutation3.solution -Copying solution to: permutation-permutation.solution language Essence 1.3 letting b be true diff --git a/tests/custom/permutations/07_compose/enum/0003_letting_and_find/stdout.expected b/tests/custom/permutations/07_compose/enum/0003_letting_and_find/stdout.expected index 0b64fe4a88..b911917b76 100644 --- a/tests/custom/permutations/07_compose/enum/0003_letting_and_find/stdout.expected +++ b/tests/custom/permutations/07_compose/enum/0003_letting_and_find/stdout.expected @@ -1,17 +1,17 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime permutation2.param +Savile Row: model000001.eprime permutation.param Running minion for domain filtering. Running solver: minion -Savile Row: model000001.eprime permutation.param +Savile Row: model000001.eprime permutation2.param Running minion for domain filtering. Running solver: minion -Copying solution to: permutation-permutation2.solution Copying solution to: permutation-permutation.solution +Copying solution to: permutation-permutation2.solution language Essence 1.3 -letting p be permutation((E2, E3)) +letting p be permutation((E2, E4, E3)) language Essence 1.3 -letting p be permutation((E2, E4, E3)) +letting p be permutation((E2, E3)) diff --git a/tests/custom/permutations/07_compose/int/0001_given_permutations_in_param/stdout.expected b/tests/custom/permutations/07_compose/int/0001_given_permutations_in_param/stdout.expected index 5034947736..0cba00099a 100644 --- a/tests/custom/permutations/07_compose/int/0001_given_permutations_in_param/stdout.expected +++ b/tests/custom/permutations/07_compose/int/0001_given_permutations_in_param/stdout.expected @@ -2,11 +2,17 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output Savile Row: model000001.eprime permutation2.essence +Running minion for domain filtering. +Running solver: minion Savile Row: model000001.eprime permutation3.essence +Running minion for domain filtering. +Running solver: minion Savile Row: model000001.eprime permutation.param +Running minion for domain filtering. +Running solver: minion +Copying solution to: permutation-permutation.solution Copying solution to: permutation-permutation2.solution Copying solution to: permutation-permutation3.solution -Copying solution to: permutation-permutation.solution language Essence 1.3 letting b be true diff --git a/tests/custom/permutations/07_compose/int/0003_letting_and_find/stdout.expected b/tests/custom/permutations/07_compose/int/0003_letting_and_find/stdout.expected index 024ae71ed2..68b324a340 100644 --- a/tests/custom/permutations/07_compose/int/0003_letting_and_find/stdout.expected +++ b/tests/custom/permutations/07_compose/int/0003_letting_and_find/stdout.expected @@ -1,17 +1,17 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime permutation2.param +Savile Row: model000001.eprime permutation.param Running minion for domain filtering. Running solver: minion -Savile Row: model000001.eprime permutation.param +Savile Row: model000001.eprime permutation2.param Running minion for domain filtering. Running solver: minion -Copying solution to: permutation-permutation2.solution Copying solution to: permutation-permutation.solution +Copying solution to: permutation-permutation2.solution language Essence 1.3 -letting p be permutation((2, 3)) +letting p be permutation((2, 4, 3)) language Essence 1.3 -letting p be permutation((2, 4, 3)) +letting p be permutation((2, 3)) diff --git a/tests/custom/permutations/07_compose/int/0005_find_composition/stdout.expected b/tests/custom/permutations/07_compose/int/0005_find_composition/stdout.expected index fa2c7dec5e..4af103b583 100644 --- a/tests/custom/permutations/07_compose/int/0005_find_composition/stdout.expected +++ b/tests/custom/permutations/07_compose/int/0005_find_composition/stdout.expected @@ -4,7 +4,7 @@ Saved under: conjure-output Savile Row: model000001.eprime Running minion for domain filtering. Running solver: minion -Copying solution to: permutation.solution +Copying solution to: permutation-000001.solution language Essence 1.3 letting c be permutation((1, 2), (3, 4)) diff --git a/tests/custom/permutations/07_compose/int/0006_find_composition/stdout.expected b/tests/custom/permutations/07_compose/int/0006_find_composition/stdout.expected index 3d95995ea1..16606b00a4 100644 --- a/tests/custom/permutations/07_compose/int/0006_find_composition/stdout.expected +++ b/tests/custom/permutations/07_compose/int/0006_find_composition/stdout.expected @@ -4,7 +4,7 @@ Saved under: conjure-output Savile Row: model000001.eprime Running minion for domain filtering. Running solver: minion -Copying solution to: permutation.solution +Copying solution to: permutation-000001.solution language Essence 1.3 letting c be permutation((1, 2, 4, 3)) diff --git a/tests/custom/permutations/17_transform_partition/enum/0010_given_partition_of_enum_BUG/stderr.expected b/tests/custom/permutations/17_transform_partition/enum/0010_given_partition_of_enum_BUG/stderr.expected deleted file mode 100644 index 3ebb6892ff..0000000000 --- a/tests/custom/permutations/17_transform_partition/enum/0010_given_partition_of_enum_BUG/stderr.expected +++ /dev/null @@ -1,6 +0,0 @@ -Error: - No value for: n_EnumSize - Bindings in context: - s: partition({1, 2}, {3, 4}) - n: `n` -cat: conjure-output/*.solution: No such file or directory diff --git a/tests/custom/permutations/17_transform_partition/enum/0010_given_partition_of_enum_BUG/stdout.expected b/tests/custom/permutations/17_transform_partition/enum/0010_given_partition_of_enum_BUG/stdout.expected index a1634e8c4c..5647c94283 100644 --- a/tests/custom/permutations/17_transform_partition/enum/0010_given_partition_of_enum_BUG/stdout.expected +++ b/tests/custom/permutations/17_transform_partition/enum/0010_given_partition_of_enum_BUG/stdout.expected @@ -2,3 +2,8 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output Savile Row: model000001.eprime permutation.param +Running minion for domain filtering. +Running solver: minion +Copying solution to: permutation-permutation.solution +language Essence 1.3 + diff --git a/tests/custom/permutations/17_transform_partition/enum/0020_find_partition_of_enum_BUG/stderr.expected b/tests/custom/permutations/17_transform_partition/enum/0020_find_partition_of_enum_BUG/stderr.expected deleted file mode 100644 index 3365ae2ca0..0000000000 --- a/tests/custom/permutations/17_transform_partition/enum/0020_find_partition_of_enum_BUG/stderr.expected +++ /dev/null @@ -1,7 +0,0 @@ -Error: - Savile Row stdout: ERROR: Identifier not defined: n_EnumSize - - Savile Row stderr: ERROR: Failed type checking:find sn_PartitionAsSet_ExplicitVarSizeWithMarkerR2_Marker: int(0..n_EnumSize) - - Savile Row exit-code: 1 -cat: conjure-output/*.solution: No such file or directory diff --git a/tests/custom/permutations/17_transform_partition/enum/0020_find_partition_of_enum_BUG/stdout.expected b/tests/custom/permutations/17_transform_partition/enum/0020_find_partition_of_enum_BUG/stdout.expected index c557beda73..6101b6ec19 100644 --- a/tests/custom/permutations/17_transform_partition/enum/0020_find_partition_of_enum_BUG/stdout.expected +++ b/tests/custom/permutations/17_transform_partition/enum/0020_find_partition_of_enum_BUG/stdout.expected @@ -2,3 +2,12 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output Savile Row: model000001.eprime +Running minion for domain filtering. +Running solver: minion +Copying solution to: permutation.solution +language Essence 1.3 + +letting sn be partition({E1, E2, E3, E4}) +$ Visualisation for sn +$ E1 E2 E3 E4 + diff --git a/tests/exhaustive/basic/perms/01_representation/enum/0001_given_permutation_in_param/expected/model-cyc1-solution000001.solution b/tests/exhaustive/basic/perms/01_representation/enum/0001_given_permutation_in_param/expected/model-cyc1-solution000001.solution deleted file mode 100644 index 48e4ad805b..0000000000 --- a/tests/exhaustive/basic/perms/01_representation/enum/0001_given_permutation_in_param/expected/model-cyc1-solution000001.solution +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -<<<<<<<< HEAD:tests/exhaustive/basic/perms/04_image/enum/0001_given_permutation_given_enum/expected/model-permutation-solution000001.solution -letting j be E3 -======== -letting b be 0 ->>>>>>>> main:tests/exhaustive/basic/perms/01_representation/enum/0001_given_permutation_in_param/expected/model-cyc1-solution000001.solution diff --git a/tests/exhaustive/basic/perms/01_representation/enum/0001_given_permutation_in_param/expected/model-cyc2-solution000001.solution b/tests/exhaustive/basic/perms/01_representation/enum/0001_given_permutation_in_param/expected/model-cyc2-solution000001.solution deleted file mode 100644 index 96d228c2e4..0000000000 --- a/tests/exhaustive/basic/perms/01_representation/enum/0001_given_permutation_in_param/expected/model-cyc2-solution000001.solution +++ /dev/null @@ -1,6 +0,0 @@ -language Essence 1.3 - -<<<<<<<< HEAD:tests/exhaustive/basic/perms/01_representation/enum/0002_given_permutation_in_param/expected/model-permutation-solution000001.solution -======== -letting b be 0 ->>>>>>>> main:tests/exhaustive/basic/perms/01_representation/enum/0001_given_permutation_in_param/expected/model-cyc2-solution000001.solution diff --git a/tests/exhaustive/basic/perms/01_representation/enum/0001_given_permutation_in_param/permutation-permutation.solution b/tests/exhaustive/basic/perms/01_representation/enum/0001_given_permutation_in_param/permutation-permutation.solution new file mode 100644 index 0000000000..fa3c1c5e86 --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/enum/0001_given_permutation_in_param/permutation-permutation.solution @@ -0,0 +1,2 @@ +language Essence 1.3 + diff --git a/tests/exhaustive/basic/perms/01_representation/enum/0001_given_permutation_in_param/permutation.eprime-param b/tests/exhaustive/basic/perms/01_representation/enum/0001_given_permutation_in_param/permutation.eprime-param new file mode 100644 index 0000000000..c2bddee0e8 --- /dev/null +++ b/tests/exhaustive/basic/perms/01_representation/enum/0001_given_permutation_in_param/permutation.eprime-param @@ -0,0 +1,3 @@ +language ESSENCE' 1.0 + +letting p_PermutationAsFunction_PermutationFunction_Function1D be [3, 2, 4, 1; int(1..4)] diff --git a/tests/exhaustive/basic/perms/01_representation/enum/0002_given_permutation_in_param/expected/model-permutation-solution000001.solution b/tests/exhaustive/basic/perms/01_representation/enum/0002_given_permutation_in_param/expected/model-permutation-solution000001.solution index 96d228c2e4..fa3c1c5e86 100644 --- a/tests/exhaustive/basic/perms/01_representation/enum/0002_given_permutation_in_param/expected/model-permutation-solution000001.solution +++ b/tests/exhaustive/basic/perms/01_representation/enum/0002_given_permutation_in_param/expected/model-permutation-solution000001.solution @@ -1,6 +1,2 @@ language Essence 1.3 -<<<<<<<< HEAD:tests/exhaustive/basic/perms/01_representation/enum/0002_given_permutation_in_param/expected/model-permutation-solution000001.solution -======== -letting b be 0 ->>>>>>>> main:tests/exhaustive/basic/perms/01_representation/enum/0001_given_permutation_in_param/expected/model-cyc2-solution000001.solution diff --git a/tests/exhaustive/basic/perms/01_representation/enum/0003_given_permutation_in_param_2_cycle/expected/model-permutation-solution000001.solution b/tests/exhaustive/basic/perms/01_representation/enum/0003_given_permutation_in_param_2_cycle/expected/model-permutation-solution000001.solution index db745d9b9d..fa3c1c5e86 100644 --- a/tests/exhaustive/basic/perms/01_representation/enum/0003_given_permutation_in_param_2_cycle/expected/model-permutation-solution000001.solution +++ b/tests/exhaustive/basic/perms/01_representation/enum/0003_given_permutation_in_param_2_cycle/expected/model-permutation-solution000001.solution @@ -1,6 +1,2 @@ language Essence 1.3 -<<<<<<<< HEAD:tests/exhaustive/basic/perms/01_representation/enum/0003_given_permutation_in_param_2_cycle/expected/model-permutation-solution000001.solution -======== -letting z be 6 ->>>>>>>> main:tests/custom/STARIS_2022/basic/greatest-common-factor/gcf-inputs.solution diff --git a/tests/exhaustive/basic/perms/01_representation/enum/0004_given_permutation_in_param_2_cycle/expected/model-permutation-solution000001.solution b/tests/exhaustive/basic/perms/01_representation/enum/0004_given_permutation_in_param_2_cycle/expected/model-permutation-solution000001.solution index b08ed022d6..fa3c1c5e86 100644 --- a/tests/exhaustive/basic/perms/01_representation/enum/0004_given_permutation_in_param_2_cycle/expected/model-permutation-solution000001.solution +++ b/tests/exhaustive/basic/perms/01_representation/enum/0004_given_permutation_in_param_2_cycle/expected/model-permutation-solution000001.solution @@ -1,6 +1,2 @@ language Essence 1.3 -<<<<<<<< HEAD:tests/exhaustive/basic/perms/01_representation/enum/0004_given_permutation_in_param_2_cycle/expected/model-permutation-solution000001.solution -======== -letting b be 5 ->>>>>>>> main:tests/custom/STARIS_2022/basic/letting-arithmetic/letting.solution diff --git a/tests/exhaustive/basic/perms/04_image/enum/0001_given_permutation_given_enum/expected/model-permutation-solution000001.solution b/tests/exhaustive/basic/perms/04_image/enum/0001_given_permutation_given_enum/expected/model-permutation-solution000001.solution index 48e4ad805b..23c353363e 100644 --- a/tests/exhaustive/basic/perms/04_image/enum/0001_given_permutation_given_enum/expected/model-permutation-solution000001.solution +++ b/tests/exhaustive/basic/perms/04_image/enum/0001_given_permutation_given_enum/expected/model-permutation-solution000001.solution @@ -1,7 +1,3 @@ language Essence 1.3 -<<<<<<<< HEAD:tests/exhaustive/basic/perms/04_image/enum/0001_given_permutation_given_enum/expected/model-permutation-solution000001.solution letting j be E3 -======== -letting b be 0 ->>>>>>>> main:tests/exhaustive/basic/perms/01_representation/enum/0001_given_permutation_in_param/expected/model-cyc1-solution000001.solution diff --git a/tests/exhaustive/basic/perms/05_equality/enum/0001_given_permutations_in_param/expected/model-permutation-solution000001.solution b/tests/exhaustive/basic/perms/05_equality/enum/0001_given_permutations_in_param/expected/model-permutation-solution000001.solution index d2566910f7..6d3576ecbf 100644 --- a/tests/exhaustive/basic/perms/05_equality/enum/0001_given_permutations_in_param/expected/model-permutation-solution000001.solution +++ b/tests/exhaustive/basic/perms/05_equality/enum/0001_given_permutations_in_param/expected/model-permutation-solution000001.solution @@ -1,7 +1,3 @@ language Essence 1.3 -<<<<<<<< HEAD:tests/exhaustive/basic/perms/05_equality/enum/0001_given_permutations_in_param/expected/model-permutation-solution000001.solution letting b be true -======== -letting a be false ->>>>>>>> main:tests/custom/STARIS_2022/basic/partitions/partition-01/apart.solution diff --git a/tests/exhaustive/basic/perms/05_equality/int/0001_given_permutations_in_param/expected/model-permutation-solution000001.solution b/tests/exhaustive/basic/perms/05_equality/int/0001_given_permutations_in_param/expected/model-permutation-solution000001.solution index 5667f45a23..6d3576ecbf 100644 --- a/tests/exhaustive/basic/perms/05_equality/int/0001_given_permutations_in_param/expected/model-permutation-solution000001.solution +++ b/tests/exhaustive/basic/perms/05_equality/int/0001_given_permutations_in_param/expected/model-permutation-solution000001.solution @@ -1,7 +1,3 @@ language Essence 1.3 -<<<<<<<< HEAD:tests/exhaustive/basic/perms/05_equality/int/0001_given_permutations_in_param/expected/model-permutation-solution000001.solution letting b be true -======== -letting x be true ->>>>>>>> main:tests/custom/STARIS_2022/basic/tuples/tuple-index/tuple.solution From 8c3b7c1b07de48501743dbda01668e4d8296f686 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?=C3=96zg=C3=BCr=20Akg=C3=BCn?= Date: Sun, 3 Mar 2024 15:54:24 +0000 Subject: [PATCH 143/229] type checking of permutation inverse and a few more passing tests --- src/Conjure/Language/Validator.hs | 21 +++++++--- .../01_representation/accept_these.sh | 32 -------------- .../01_representation/runthese.sh | 1 - .../02_cardinality/accept_these.sh | 7 ---- .../permutations/02_cardinality/runthese.sh | 1 - .../03_generators/accept_these.sh | 11 ----- .../permutations/03_generators/runthese.sh | 1 - .../permutations/04_image/accept_these.sh | 42 ------------------- .../custom/permutations/04_image/runthese.sh | 1 - .../permutations/05_equality/accept_these.sh | 15 ------- .../permutations/05_equality/runthese.sh | 1 - .../permutations/06_inverse/accept_these.sh | 25 ----------- .../stdout.expected | 10 ++--- .../stdout.expected | 10 ++--- .../0003_given_equal_letting/stdout.expected | 6 ++- .../0004_letting_equal_given/stdout.expected | 10 ++--- .../0004_letting_equal_given/stdout.expected | 10 ++--- .../permutations/06_inverse/runthese.sh | 1 - .../permutations/07_compose/accept_these.sh | 38 ----------------- .../permutations/07_compose/runthese.sh | 1 - .../permutations/08_transform_set/runthese.sh | 1 - .../permutations/09_defined/accept_these.sh | 12 ------ .../permutations/09_defined/runthese.sh | 1 - .../10_transform_tuple/accept_these.sh | 12 ------ .../10_transform_tuple/runthese.sh | 1 - .../11_transform_relation/accept_these.sh | 9 ---- .../11_transform_relation/runthese.sh | 1 - .../12_transform_list/accept_these.sh | 8 ---- .../12_transform_list/runthese.sh | 1 - .../13_transform_function/accept_these.sh | 7 ---- .../13_transform_function/runthese.sh | 1 - .../14_transform_sequence/accept_these.sh | 7 ---- .../14_transform_sequence/runthese.sh | 1 - .../15_transform_mset/accept_these.sh | 11 ----- .../15_transform_mset/runthese.sh | 1 - .../16_transform_permutation/accept_these.sh | 11 ----- .../16_transform_permutation/runthese.sh | 1 - .../17_transform_partition/accept_these.sh | 7 ---- .../17_transform_partition/runthese.sh | 1 - .../18_transform_matrix/runthese.sh | 1 - .../permutations/19_complications/runthese.sh | 1 - .../permutations/20_counting/runthese.sh | 1 - .../21_superpermutations/runthese.sh | 1 - .../22_tagged_ints/accept_these.sh | 25 ----------- .../permutations/22_tagged_ints/runthese.sh | 1 - .../23_image_set_dotlt/runthese.sh | 1 - .../24_image_comprehension_dotlt/runthese.sh | 1 - tests/custom/permutations/runthese.sh | 1 - .../expected/model-solution000001.solution | 0 .../int/{ => extra}/expected/model.eprime | 0 .../05_equality/int/{ => extra}/new.essence | 0 .../expected/model-solution000001.solution | 4 ++ .../expected/model-solution000002.solution | 4 ++ .../expected/model-solution000003.solution | 4 ++ .../expected/model-solution000004.solution | 4 ++ .../expected/model-solution000005.solution | 4 ++ .../expected/model-solution000006.solution | 4 ++ .../expected/model-solution000007.solution | 4 ++ .../expected/model-solution000008.solution | 4 ++ .../expected/model-solution000009.solution | 4 ++ .../expected/model-solution000010.solution | 4 ++ .../expected/model-solution000011.solution | 4 ++ .../expected/model-solution000012.solution | 4 ++ .../expected/model-solution000013.solution | 4 ++ .../expected/model-solution000014.solution | 4 ++ .../expected/model-solution000015.solution | 4 ++ .../expected/model-solution000016.solution | 4 ++ .../expected/model-solution000017.solution | 4 ++ .../expected/model-solution000018.solution | 4 ++ .../expected/model-solution000019.solution | 4 ++ .../expected/model-solution000020.solution | 4 ++ .../expected/model-solution000021.solution | 4 ++ .../expected/model-solution000022.solution | 4 ++ .../expected/model-solution000023.solution | 4 ++ .../expected/model-solution000024.solution | 4 ++ .../0005_find_eq_find/expected/model.eprime | 30 +++++++++++++ 76 files changed, 166 insertions(+), 331 deletions(-) delete mode 100644 tests/custom/permutations/01_representation/accept_these.sh delete mode 100644 tests/custom/permutations/01_representation/runthese.sh delete mode 100644 tests/custom/permutations/02_cardinality/accept_these.sh delete mode 100644 tests/custom/permutations/02_cardinality/runthese.sh delete mode 100644 tests/custom/permutations/03_generators/accept_these.sh delete mode 100644 tests/custom/permutations/03_generators/runthese.sh delete mode 100644 tests/custom/permutations/04_image/accept_these.sh delete mode 100644 tests/custom/permutations/04_image/runthese.sh delete mode 100644 tests/custom/permutations/05_equality/accept_these.sh delete mode 100644 tests/custom/permutations/05_equality/runthese.sh delete mode 100644 tests/custom/permutations/06_inverse/accept_these.sh delete mode 100644 tests/custom/permutations/06_inverse/runthese.sh delete mode 100644 tests/custom/permutations/07_compose/accept_these.sh delete mode 100644 tests/custom/permutations/07_compose/runthese.sh delete mode 100644 tests/custom/permutations/08_transform_set/runthese.sh delete mode 100644 tests/custom/permutations/09_defined/accept_these.sh delete mode 100644 tests/custom/permutations/09_defined/runthese.sh delete mode 100644 tests/custom/permutations/10_transform_tuple/accept_these.sh delete mode 100644 tests/custom/permutations/10_transform_tuple/runthese.sh delete mode 100644 tests/custom/permutations/11_transform_relation/accept_these.sh delete mode 100644 tests/custom/permutations/11_transform_relation/runthese.sh delete mode 100644 tests/custom/permutations/12_transform_list/accept_these.sh delete mode 100644 tests/custom/permutations/12_transform_list/runthese.sh delete mode 100644 tests/custom/permutations/13_transform_function/accept_these.sh delete mode 100644 tests/custom/permutations/13_transform_function/runthese.sh delete mode 100644 tests/custom/permutations/14_transform_sequence/accept_these.sh delete mode 100644 tests/custom/permutations/14_transform_sequence/runthese.sh delete mode 100644 tests/custom/permutations/15_transform_mset/accept_these.sh delete mode 100644 tests/custom/permutations/15_transform_mset/runthese.sh delete mode 100644 tests/custom/permutations/16_transform_permutation/accept_these.sh delete mode 100644 tests/custom/permutations/16_transform_permutation/runthese.sh delete mode 100644 tests/custom/permutations/17_transform_partition/accept_these.sh delete mode 100644 tests/custom/permutations/17_transform_partition/runthese.sh delete mode 100644 tests/custom/permutations/18_transform_matrix/runthese.sh delete mode 100644 tests/custom/permutations/19_complications/runthese.sh delete mode 100644 tests/custom/permutations/20_counting/runthese.sh delete mode 100644 tests/custom/permutations/21_superpermutations/runthese.sh delete mode 100644 tests/custom/permutations/22_tagged_ints/accept_these.sh delete mode 100644 tests/custom/permutations/22_tagged_ints/runthese.sh delete mode 100644 tests/custom/permutations/23_image_set_dotlt/runthese.sh delete mode 100644 tests/custom/permutations/24_image_comprehension_dotlt/runthese.sh delete mode 100644 tests/custom/permutations/runthese.sh rename tests/exhaustive/basic/perms/05_equality/int/{ => extra}/expected/model-solution000001.solution (100%) rename tests/exhaustive/basic/perms/05_equality/int/{ => extra}/expected/model.eprime (100%) rename tests/exhaustive/basic/perms/05_equality/int/{ => extra}/new.essence (100%) create mode 100644 tests/exhaustive/basic/perms/06_inverse/int/0005_find_eq_find/expected/model-solution000001.solution create mode 100644 tests/exhaustive/basic/perms/06_inverse/int/0005_find_eq_find/expected/model-solution000002.solution create mode 100644 tests/exhaustive/basic/perms/06_inverse/int/0005_find_eq_find/expected/model-solution000003.solution create mode 100644 tests/exhaustive/basic/perms/06_inverse/int/0005_find_eq_find/expected/model-solution000004.solution create mode 100644 tests/exhaustive/basic/perms/06_inverse/int/0005_find_eq_find/expected/model-solution000005.solution create mode 100644 tests/exhaustive/basic/perms/06_inverse/int/0005_find_eq_find/expected/model-solution000006.solution create mode 100644 tests/exhaustive/basic/perms/06_inverse/int/0005_find_eq_find/expected/model-solution000007.solution create mode 100644 tests/exhaustive/basic/perms/06_inverse/int/0005_find_eq_find/expected/model-solution000008.solution create mode 100644 tests/exhaustive/basic/perms/06_inverse/int/0005_find_eq_find/expected/model-solution000009.solution create mode 100644 tests/exhaustive/basic/perms/06_inverse/int/0005_find_eq_find/expected/model-solution000010.solution create mode 100644 tests/exhaustive/basic/perms/06_inverse/int/0005_find_eq_find/expected/model-solution000011.solution create mode 100644 tests/exhaustive/basic/perms/06_inverse/int/0005_find_eq_find/expected/model-solution000012.solution create mode 100644 tests/exhaustive/basic/perms/06_inverse/int/0005_find_eq_find/expected/model-solution000013.solution create mode 100644 tests/exhaustive/basic/perms/06_inverse/int/0005_find_eq_find/expected/model-solution000014.solution create mode 100644 tests/exhaustive/basic/perms/06_inverse/int/0005_find_eq_find/expected/model-solution000015.solution create mode 100644 tests/exhaustive/basic/perms/06_inverse/int/0005_find_eq_find/expected/model-solution000016.solution create mode 100644 tests/exhaustive/basic/perms/06_inverse/int/0005_find_eq_find/expected/model-solution000017.solution create mode 100644 tests/exhaustive/basic/perms/06_inverse/int/0005_find_eq_find/expected/model-solution000018.solution create mode 100644 tests/exhaustive/basic/perms/06_inverse/int/0005_find_eq_find/expected/model-solution000019.solution create mode 100644 tests/exhaustive/basic/perms/06_inverse/int/0005_find_eq_find/expected/model-solution000020.solution create mode 100644 tests/exhaustive/basic/perms/06_inverse/int/0005_find_eq_find/expected/model-solution000021.solution create mode 100644 tests/exhaustive/basic/perms/06_inverse/int/0005_find_eq_find/expected/model-solution000022.solution create mode 100644 tests/exhaustive/basic/perms/06_inverse/int/0005_find_eq_find/expected/model-solution000023.solution create mode 100644 tests/exhaustive/basic/perms/06_inverse/int/0005_find_eq_find/expected/model-solution000024.solution create mode 100644 tests/exhaustive/basic/perms/06_inverse/int/0005_find_eq_find/expected/model.eprime diff --git a/src/Conjure/Language/Validator.hs b/src/Conjure/Language/Validator.hs index f30f3a28b2..6cb074ef7e 100644 --- a/src/Conjure/Language/Validator.hs +++ b/src/Conjure/Language/Validator.hs @@ -1665,6 +1665,7 @@ projectionType r t = case t of TypeSet ty -> return ty TypeMSet ty -> return ty TypeSequence ty -> return $ TypeTuple [tInt, ty] + TypePermutation ty -> return $ TypeTuple [ty, ty] TypeRelation ts -> return $ TypeTuple ts TypePartition ty -> return $ TypeSet ty TypeFunction fr to -> return $ TypeTuple [fr, to] @@ -1677,7 +1678,8 @@ projectionTypeDomain _ t = case t of -- TODO check and do properly TypeUnnamed (Name n) -> return $ TypeInt $ TagUnnamed n _ -> return t --- _ -> (raiseTypeError $ r SemanticError (pack $ "Domain of type " ++ (show $pretty t) ++ " cannot be projected in a comprehension")) >> return TypeAny +-- _ -> (raiseTypeError $ r SemanticError (pack $ "Domain of type " ++ (show $pretty t) ++ " cannot be projected in a comprehension")) >> return TypeAny + mkAbstractLiteral :: AbstractLiteral Expression -> Expression mkAbstractLiteral x = case e2c (AbstractLiteral x) of Nothing -> AbstractLiteral x @@ -2408,10 +2410,15 @@ functionOps l = case l of (TypeFunction fi fo, TypeFunction gi go) -> (mostDefinedS [fi, go], mostDefinedS [fo, gi]) (TypeFunction fi fo, _) -> (fi, fo) (_, TypeFunction gi go) -> (gi, go) + (TypePermutation ta, TypePermutation tb) -> (mostDefinedS [ta, tb], mostDefinedS [ta, tb]) + (TypePermutation ta, _) -> (ta, ta) + (_, TypePermutation ta) -> (ta, ta) _ -> (TypeAny, TypeAny) - a' <- unifyTypesFailing (TypeFunction fIn fOut) (r1, a) - b' <- unifyTypesFailing (TypeFunction fOut fIn) (r2, b) - return $ if null a' || null b' then Nothing else Just () + return (Just ()) + -- a' <- unifyTypesFailing (TypeFunction fIn fOut) (r1, a) + -- b' <- unifyTypesFailing (TypeFunction fOut fIn) (r2, b) + -- return $ if null a' || null b' then Nothing else Just () + setPartArgs :: SArg -> SArg -> Validator () setPartArgs (r1, a) (r2, b) = do let t = case (typeOf_ a, typeOf_ b) of @@ -2500,7 +2507,8 @@ functionOps l = case l of TypeAny -> return $ Just TypeAny TypeFunction a _ -> return $ Just a TypeSequence _ -> return $ Just tInt - _ -> Nothing <$ raiseTypeError (r1 ComplexTypeError "Function or Sequence" t1) + TypePermutation a -> return $ Just a + _ -> Nothing <$ raiseTypeError (r1 ComplexTypeError "function, sequence or permutation" t1) case from of Just f -> unifyTypes f r2 >> return (pure ()) Nothing -> return Nothing @@ -2527,8 +2535,9 @@ functionOps l = case l of funcSeq (r, typeOf_ -> t') = case t' of TypeAny -> return $ pure () TypeSequence _ -> return $ pure () + TypePermutation _ -> return $ pure () TypeFunction _ _ -> return $ pure () - _ -> invalid $ r ComplexTypeError "Function or Sequence" t' + _ -> invalid $ r ComplexTypeError "function, sequence or permutation" t' funcDomain :: Maybe Type -> Maybe Type funcDomain (Just (TypeFunction a _)) = Just a funcDomain (Just (TypeSequence _)) = Just tInt diff --git a/tests/custom/permutations/01_representation/accept_these.sh b/tests/custom/permutations/01_representation/accept_these.sh deleted file mode 100644 index fff9433bfb..0000000000 --- a/tests/custom/permutations/01_representation/accept_these.sh +++ /dev/null @@ -1,32 +0,0 @@ -sh ../../acceptOutput.sh enum/0008_find_permutation_of_int1_4 -sh ../../acceptOutput.sh enum/0009_letting_permutation_in_model -sh ../../acceptOutput.sh enum/0005_find_permutation_size_4_of_int1_4 -sh ../../acceptOutput.sh enum/0002_given_permutation_in_param -sh ../../acceptOutput.sh enum/0006_find_permutation_size_0_of_int1_4 -sh ../../acceptOutput.sh enum/0011_find_permutation_minSize_2_of_int1_3 -sh ../../acceptOutput.sh enum/0003_given_permutation_in_param_2_cycle -sh ../../acceptOutput.sh enum/0010_find_permutation_maxSize_2_of_int1_3 -sh ../../acceptOutput.sh enum/0007_letting_permutation_be_empty -sh ../../acceptOutput.sh enum/0004_given_permutation_in_param_2_cycle -sh ../../acceptOutput.sh enum/0012_find_permutation_maxSize_3_minSize_2_of_int1_4 -sh ../../acceptOutput.sh enum/0001_given_permutation_in_param -sh ../../acceptOutput.sh int/0008_find_permutation_of_int1_4 -sh ../../acceptOutput.sh int/0009_letting_permutation_in_model -sh ../../acceptOutput.sh int/0005_find_permutation_size_4_of_int1_4 -sh ../../acceptOutput.sh int/0002_given_permutation_in_param -sh ../../acceptOutput.sh int/0006_find_permutation_size_0_of_int1_4 -sh ../../acceptOutput.sh int/0011_find_permutation_minSize_2_of_int1_3 -sh ../../acceptOutput.sh int/0003_given_permutation_in_param_2_cycle -sh ../../acceptOutput.sh int/0010_find_permutation_maxSize_2_of_int1_3 -sh ../../acceptOutput.sh int/0007_letting_permutation_be_empty -sh ../../acceptOutput.sh int/0004_given_permutation_in_param_2_cycle -sh ../../acceptOutput.sh int/0012_find_permutation_maxSize_3_minSize_2_of_int1_4 -sh ../../acceptOutput.sh int/0001_given_permutation_in_param -sh ../../acceptOutput.sh unnamed/0008_find_permutation_of_int1_4 -sh ../../acceptOutput.sh unnamed/0005_find_permutation_size_4_of_int1_4 -sh ../../acceptOutput.sh unnamed/0006_find_permutation_size_0_of_int1_4 -sh ../../acceptOutput.sh unnamed/0011_find_permutation_minSize_2_of_int1_3 -sh ../../acceptOutput.sh unnamed/0010_find_permutation_maxSize_2_of_int1_3 -sh ../../acceptOutput.sh unnamed/0007_letting_permutation_be_empty -sh ../../acceptOutput.sh unnamed/0012_find_permutation_maxSize_3_minSize_2_of_int1_4 - diff --git a/tests/custom/permutations/01_representation/runthese.sh b/tests/custom/permutations/01_representation/runthese.sh deleted file mode 100644 index 1cc0572a12..0000000000 --- a/tests/custom/permutations/01_representation/runthese.sh +++ /dev/null @@ -1 +0,0 @@ -stack build --copy-bins --test --test-arguments "-p custom.permutations.01_representation" diff --git a/tests/custom/permutations/02_cardinality/accept_these.sh b/tests/custom/permutations/02_cardinality/accept_these.sh deleted file mode 100644 index 4d42ea8bae..0000000000 --- a/tests/custom/permutations/02_cardinality/accept_these.sh +++ /dev/null @@ -1,7 +0,0 @@ -sh ../../acceptOutput.sh enum/0002_letting_permutation_in_model -sh ../../acceptOutput.sh enum/0003_find_permutation -sh ../../acceptOutput.sh enum/0001_given_permutation_in_param -sh ../../acceptOutput.sh int/0002_letting_permutation_in_model -sh ../../acceptOutput.sh int/0003_find_permutation -sh ../../acceptOutput.sh int/0001_given_permutation_in_param -sh ../../acceptOutput.sh unnamed/0003_find_permutation diff --git a/tests/custom/permutations/02_cardinality/runthese.sh b/tests/custom/permutations/02_cardinality/runthese.sh deleted file mode 100644 index d087e47838..0000000000 --- a/tests/custom/permutations/02_cardinality/runthese.sh +++ /dev/null @@ -1 +0,0 @@ -stack build --copy-bins --test --test-arguments "-p custom.permutations.02_cardinality" diff --git a/tests/custom/permutations/03_generators/accept_these.sh b/tests/custom/permutations/03_generators/accept_these.sh deleted file mode 100644 index e7d6661003..0000000000 --- a/tests/custom/permutations/03_generators/accept_these.sh +++ /dev/null @@ -1,11 +0,0 @@ -sh ../../acceptOutput.sh enum/0001_given_permutation_in_generator -sh ../../acceptOutput.sh enum/0002_letting_permutation_in_generator -sh ../../acceptOutput.sh enum/0003_find_permutation_in_generator -sh ../../acceptOutput.sh enum/0004_find_permutation_in_generator -sh ../../acceptOutput.sh int/0004_find_permutation_in_forall -sh ../../acceptOutput.sh int/0001_given_permutation_in_generator -sh ../../acceptOutput.sh int/0002_letting_permutation_in_generator -sh ../../acceptOutput.sh int/0005_find_permutation_in_forall -sh ../../acceptOutput.sh int/0003_find_permutation_in_generator -sh ../../acceptOutput.sh unnamed/0003_find_permutation_in_generator - diff --git a/tests/custom/permutations/03_generators/runthese.sh b/tests/custom/permutations/03_generators/runthese.sh deleted file mode 100644 index 953e3eacd0..0000000000 --- a/tests/custom/permutations/03_generators/runthese.sh +++ /dev/null @@ -1 +0,0 @@ -stack build --copy-bins --test --test-arguments "-p custom.permutations.03_generators" diff --git a/tests/custom/permutations/04_image/accept_these.sh b/tests/custom/permutations/04_image/accept_these.sh deleted file mode 100644 index cce6c030cc..0000000000 --- a/tests/custom/permutations/04_image/accept_these.sh +++ /dev/null @@ -1,42 +0,0 @@ -sh ../../acceptOutput.sh enum/0001_given_permutation_given_enum -sh ../../acceptOutput.sh enum/0007_find_permutation_find_enums -sh ../../acceptOutput.sh enum/0006_letting_permutation_given_enum -sh ../../acceptOutput.sh enum/0002_given_permutation_letting_enum -# sh ../../acceptOutput.sh enum/0004_given_permutation_find_enum ) -# TODO - why this error when run.sh appears to work fine?! -# Running -# Checking stderr -# src/test/Conjure/Custom/hs86 -# unexpected stderr -# Error -# permutation/essence31 -# unexpected find -# expecting end of input or letting statement -# find i n -# ^ -# cat conjure-output/*/solution No such file or directory -# was expecting -sh ../../acceptOutput.sh enum/0003_given_permutation_letting_enum -sh ../../acceptOutput.sh enum/0005_find_permutation_given_enums -sh ../../acceptOutput.sh int/0002_given_permutation_letting_int -sh ../../acceptOutput.sh int/0007_find_permutation_find_ints -# sh ../../acceptOutput.sh int/0004_given_permutation_find_int ) -# TODO - why this error when run.sh appears to work fine?! -# Running -# Checking stderr -# src/test/Conjure/Custom/hs86 -# unexpected stderr -# Error -# permutation/essence11 -# unexpected find -# expecting end of input, language, or letting statement -# find i int(0//10) -# ^ -# cat conjure-output/*/solution No such file or directory -# was expecting -sh ../../acceptOutput.sh int/0005_find_permutation_given_ints -sh ../../acceptOutput.sh int/0003_given_permutation_letting_int -sh ../../acceptOutput.sh int/0006_letting_permutation_given_int -sh ../../acceptOutput.sh int/0001_given_permutation_given_int -sh ../../acceptOutput.sh unnamed/0007_find_permutation_find_unnameds - diff --git a/tests/custom/permutations/04_image/runthese.sh b/tests/custom/permutations/04_image/runthese.sh deleted file mode 100644 index 42c6fb5f7b..0000000000 --- a/tests/custom/permutations/04_image/runthese.sh +++ /dev/null @@ -1 +0,0 @@ -stack build --copy-bins --test --test-arguments "-p custom.permutations.04_image" diff --git a/tests/custom/permutations/05_equality/accept_these.sh b/tests/custom/permutations/05_equality/accept_these.sh deleted file mode 100644 index 18aea096a3..0000000000 --- a/tests/custom/permutations/05_equality/accept_these.sh +++ /dev/null @@ -1,15 +0,0 @@ -sh ../../acceptOutput.sh enum/0002_given_permutations_in_param -sh ../../acceptOutput.sh enum/0004_letting_equal_given -sh ../../acceptOutput.sh enum/0003_given_equal_letting -sh ../../acceptOutput.sh enum/0005_find_eq_find -sh ../../acceptOutput.sh enum/0006_in_comprehension -sh ../../acceptOutput.sh enum/0001_given_permutations_in_param -sh ../../acceptOutput.sh int/0002_given_permutations_in_param -sh ../../acceptOutput.sh int/0007_letting_equal_letting -sh ../../acceptOutput.sh int/0004_letting_equal_given -sh ../../acceptOutput.sh int/0003_given_equal_letting -sh ../../acceptOutput.sh int/0005_find_eq_find -sh ../../acceptOutput.sh int/0006_in_comprehension -sh ../../acceptOutput.sh int/0001_given_permutations_in_param -sh ../../acceptOutput.sh unnamed/0005_find_eq_find -sh ../../acceptOutput.sh unnamed/0006_in_comprehension diff --git a/tests/custom/permutations/05_equality/runthese.sh b/tests/custom/permutations/05_equality/runthese.sh deleted file mode 100644 index 1c9834ccee..0000000000 --- a/tests/custom/permutations/05_equality/runthese.sh +++ /dev/null @@ -1 +0,0 @@ -stack build --copy-bins --test --test-arguments "-p custom.permutations.05_equality" diff --git a/tests/custom/permutations/06_inverse/accept_these.sh b/tests/custom/permutations/06_inverse/accept_these.sh deleted file mode 100644 index 2ec1ca0ecd..0000000000 --- a/tests/custom/permutations/06_inverse/accept_these.sh +++ /dev/null @@ -1,25 +0,0 @@ -sh ../../acceptOutput.sh enum/0002_given_permutations_in_param -sh ../../acceptOutput.sh enum/0004_letting_equal_given -sh ../../acceptOutput.sh enum/0005_find_eq_find -sh ../../acceptOutput.sh enum/0001_given_permutations_in_param -sh ../../acceptOutput.sh int/0002_given_permutations_in_param -sh ../../acceptOutput.sh int/0004_letting_equal_given -sh ../../acceptOutput.sh int/0003_given_equal_letting -sh ../../acceptOutput.sh int/0005_find_eq_find -sh ../../acceptOutput.sh int/0001_given_permutations_in_param -sh ../../acceptOutput.sh unnamed/0005_find_inverse_find -# permutations.06_inverse.enum.0003_given_equal_letting: FAIL (0.38s) -# TODO - what's wrong here? -# Running -# Checking stderr -# src/test/Conjure/Custom.hs:86: -# unexpected stderr: -# Error: -# permutation.essence:3:1: -# unexpected given -# expecting end of input or letting statement -# given p : permutation of n -# ^ -# cat: conjure-output/*.solution: No such file or directory -# was expecting: - diff --git a/tests/custom/permutations/06_inverse/enum/0001_given_permutations_in_param/stdout.expected b/tests/custom/permutations/06_inverse/enum/0001_given_permutations_in_param/stdout.expected index 5628c4ea9d..509db792c4 100644 --- a/tests/custom/permutations/06_inverse/enum/0001_given_permutations_in_param/stdout.expected +++ b/tests/custom/permutations/06_inverse/enum/0001_given_permutations_in_param/stdout.expected @@ -1,17 +1,17 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime permutation2.param +Savile Row: model000001.eprime permutation.param Running minion for domain filtering. Running solver: minion -Savile Row: model000001.eprime permutation.param +Savile Row: model000001.eprime permutation2.param Running minion for domain filtering. Running solver: minion -Copying solution to: permutation-permutation2.solution Copying solution to: permutation-permutation.solution +Copying solution to: permutation-permutation2.solution language Essence 1.3 -letting b be true +letting b be false language Essence 1.3 -letting b be false +letting b be true diff --git a/tests/custom/permutations/06_inverse/enum/0002_given_permutations_in_param/stdout.expected b/tests/custom/permutations/06_inverse/enum/0002_given_permutations_in_param/stdout.expected index 5628c4ea9d..509db792c4 100644 --- a/tests/custom/permutations/06_inverse/enum/0002_given_permutations_in_param/stdout.expected +++ b/tests/custom/permutations/06_inverse/enum/0002_given_permutations_in_param/stdout.expected @@ -1,17 +1,17 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime permutation2.param +Savile Row: model000001.eprime permutation.param Running minion for domain filtering. Running solver: minion -Savile Row: model000001.eprime permutation.param +Savile Row: model000001.eprime permutation2.param Running minion for domain filtering. Running solver: minion -Copying solution to: permutation-permutation2.solution Copying solution to: permutation-permutation.solution +Copying solution to: permutation-permutation2.solution language Essence 1.3 -letting b be true +letting b be false language Essence 1.3 -letting b be false +letting b be true diff --git a/tests/custom/permutations/06_inverse/enum/0003_given_equal_letting/stdout.expected b/tests/custom/permutations/06_inverse/enum/0003_given_equal_letting/stdout.expected index f8cb0c5eb2..ad056a321b 100644 --- a/tests/custom/permutations/06_inverse/enum/0003_given_equal_letting/stdout.expected +++ b/tests/custom/permutations/06_inverse/enum/0003_given_equal_letting/stdout.expected @@ -2,9 +2,13 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output Savile Row: model000001.eprime permutation2.essence +Running minion for domain filtering. +Running solver: minion Savile Row: model000001.eprime permutation.param -Copying solution to: permutation-permutation2.solution +Running minion for domain filtering. +Running solver: minion Copying solution to: permutation-permutation.solution +Copying solution to: permutation-permutation2.solution language Essence 1.3 letting b be false diff --git a/tests/custom/permutations/06_inverse/enum/0004_letting_equal_given/stdout.expected b/tests/custom/permutations/06_inverse/enum/0004_letting_equal_given/stdout.expected index 5628c4ea9d..509db792c4 100644 --- a/tests/custom/permutations/06_inverse/enum/0004_letting_equal_given/stdout.expected +++ b/tests/custom/permutations/06_inverse/enum/0004_letting_equal_given/stdout.expected @@ -1,17 +1,17 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime permutation2.param +Savile Row: model000001.eprime permutation.param Running minion for domain filtering. Running solver: minion -Savile Row: model000001.eprime permutation.param +Savile Row: model000001.eprime permutation2.param Running minion for domain filtering. Running solver: minion -Copying solution to: permutation-permutation2.solution Copying solution to: permutation-permutation.solution +Copying solution to: permutation-permutation2.solution language Essence 1.3 -letting b be true +letting b be false language Essence 1.3 -letting b be false +letting b be true diff --git a/tests/custom/permutations/06_inverse/int/0004_letting_equal_given/stdout.expected b/tests/custom/permutations/06_inverse/int/0004_letting_equal_given/stdout.expected index 5628c4ea9d..509db792c4 100644 --- a/tests/custom/permutations/06_inverse/int/0004_letting_equal_given/stdout.expected +++ b/tests/custom/permutations/06_inverse/int/0004_letting_equal_given/stdout.expected @@ -1,17 +1,17 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime permutation2.param +Savile Row: model000001.eprime permutation.param Running minion for domain filtering. Running solver: minion -Savile Row: model000001.eprime permutation.param +Savile Row: model000001.eprime permutation2.param Running minion for domain filtering. Running solver: minion -Copying solution to: permutation-permutation2.solution Copying solution to: permutation-permutation.solution +Copying solution to: permutation-permutation2.solution language Essence 1.3 -letting b be true +letting b be false language Essence 1.3 -letting b be false +letting b be true diff --git a/tests/custom/permutations/06_inverse/runthese.sh b/tests/custom/permutations/06_inverse/runthese.sh deleted file mode 100644 index 1048702814..0000000000 --- a/tests/custom/permutations/06_inverse/runthese.sh +++ /dev/null @@ -1 +0,0 @@ -stack build --copy-bins --test --test-arguments "-p custom.permutations.06_inverse" diff --git a/tests/custom/permutations/07_compose/accept_these.sh b/tests/custom/permutations/07_compose/accept_these.sh deleted file mode 100644 index a140956cdb..0000000000 --- a/tests/custom/permutations/07_compose/accept_these.sh +++ /dev/null @@ -1,38 +0,0 @@ - sh ../../acceptOutput.sh enum/0002_given_and_letting - sh ../../acceptOutput.sh enum/0003_letting_and_find - sh ../../acceptOutput.sh enum/0004_find_and_find - sh ../../acceptOutput.sh int/0002_given_and_letting - sh ../../acceptOutput.sh int/0005_find_composition - sh ../../acceptOutput.sh int/0003_letting_and_find - sh ../../acceptOutput.sh int/0004_find_and_find - sh ../../acceptOutput.sh int/0002_letting_and_given - sh ../../acceptOutput.sh int/0006_find_composition - sh ../../acceptOutput.sh unnamed/0004_find_and_find - -# TODO what's wrong here? -# permutations.07_compose.enum.0001_given_permutations_in_param: -# Running -# Checking stderr -# src/test/Conjure/Custom.hs:86: -# unexpected stderr: -# Error: -# permutation.essence:3:1: -# unexpected given -# expecting end of input or letting statement -# given p : permutation of n -# ^ -# cat: conjure-output/*.solution: No such file or directory -# was expecting: -# permutations.07_compose.int.0001_given_permutations_in_param: FAIL (0.31s) -# Running -# Checking stderr -# src/test/Conjure/Custom.hs:86: -# unexpected stderr: -# Error: -# permutation.essence:3:1: -# unexpected given -# expecting end of input, letting statement, or rest of letting statement -# given p : permutation of int(1..n) -# ^ -# cat: conjure-output/*.solution: No such file or directory -# was expecting: diff --git a/tests/custom/permutations/07_compose/runthese.sh b/tests/custom/permutations/07_compose/runthese.sh deleted file mode 100644 index 9537d9e1f4..0000000000 --- a/tests/custom/permutations/07_compose/runthese.sh +++ /dev/null @@ -1 +0,0 @@ -stack build --copy-bins --test --test-arguments "-p custom.permutations.07_compose" diff --git a/tests/custom/permutations/08_transform_set/runthese.sh b/tests/custom/permutations/08_transform_set/runthese.sh deleted file mode 100644 index 91bb9cd7a2..0000000000 --- a/tests/custom/permutations/08_transform_set/runthese.sh +++ /dev/null @@ -1 +0,0 @@ -stack build --copy-bins --test --test-arguments "-p custom.permutations.08_transform_set" diff --git a/tests/custom/permutations/09_defined/accept_these.sh b/tests/custom/permutations/09_defined/accept_these.sh deleted file mode 100644 index 379ca74a6a..0000000000 --- a/tests/custom/permutations/09_defined/accept_these.sh +++ /dev/null @@ -1,12 +0,0 @@ -sh ../../acceptOutput.sh enum/0005_find_permutation -sh ../../acceptOutput.sh enum/0003_given_permutation -sh ../../acceptOutput.sh enum/0004_given_permutation -sh ../../acceptOutput.sh enum/0002_letting_permutation -sh ../../acceptOutput.sh enum/0001_letting_permutation -sh ../../acceptOutput.sh int/0005_find_permutation -sh ../../acceptOutput.sh int/0003_given_permutation -sh ../../acceptOutput.sh int/0004_given_permutation -sh ../../acceptOutput.sh int/0002_letting_permutation -sh ../../acceptOutput.sh int/0001_letting_permutation -sh ../../acceptOutput.sh unnamed/0005_find_permutation - diff --git a/tests/custom/permutations/09_defined/runthese.sh b/tests/custom/permutations/09_defined/runthese.sh deleted file mode 100644 index ed2756d059..0000000000 --- a/tests/custom/permutations/09_defined/runthese.sh +++ /dev/null @@ -1 +0,0 @@ -stack build --copy-bins --test --test-arguments "-p custom.permutations.09_defined" diff --git a/tests/custom/permutations/10_transform_tuple/accept_these.sh b/tests/custom/permutations/10_transform_tuple/accept_these.sh deleted file mode 100644 index 7c343ae8f8..0000000000 --- a/tests/custom/permutations/10_transform_tuple/accept_these.sh +++ /dev/null @@ -1,12 +0,0 @@ -sh ../../acceptOutput.sh enum/0004_given_permutation_find_tuple_find_tuple -sh ../../acceptOutput.sh enum/0005_find_permutation_find_tuple_find_tuple -sh ../../acceptOutput.sh enum/0003_given_permutation_given_tuple_find_tuple -sh ../../acceptOutput.sh enum/0001_letting_permutation_given_tuple_find_tuple -sh ../../acceptOutput.sh enum/0002_letting_permutation_given_tuple_find_tuple -sh ../../acceptOutput.sh int/0004_given_permutation_find_tuple_find_tuple -sh ../../acceptOutput.sh int/0005_find_permutation_find_tuple_find_tuple -sh ../../acceptOutput.sh int/0003_given_permutation_given_tuple_find_tuple -sh ../../acceptOutput.sh int/0001_letting_permutation_given_tuple_find_tuple -sh ../../acceptOutput.sh int/0002_letting_permutation_given_tuple_find_tuple -sh ../../acceptOutput.sh unnamed/0005_find_permutation_find_tuple_find_tuple - diff --git a/tests/custom/permutations/10_transform_tuple/runthese.sh b/tests/custom/permutations/10_transform_tuple/runthese.sh deleted file mode 100644 index 20a2d14ad1..0000000000 --- a/tests/custom/permutations/10_transform_tuple/runthese.sh +++ /dev/null @@ -1 +0,0 @@ -stack build --copy-bins --test --test-arguments "-p custom.permutations.10_transform_tuple" diff --git a/tests/custom/permutations/11_transform_relation/accept_these.sh b/tests/custom/permutations/11_transform_relation/accept_these.sh deleted file mode 100644 index c1260104cd..0000000000 --- a/tests/custom/permutations/11_transform_relation/accept_these.sh +++ /dev/null @@ -1,9 +0,0 @@ -sh ../../acceptOutput.sh enum/0040_find_permutation_find_relation -sh ../../acceptOutput.sh enum/0010_given_permutation_letting_relation -sh ../../acceptOutput.sh enum/0030_find_permutation_given_relation -sh ../../acceptOutput.sh enum/0020_letting_permutation_letting_relation -sh ../../acceptOutput.sh int/0040_find_permutation_find_relation -sh ../../acceptOutput.sh int/0010_given_permutation_letting_relation -sh ../../acceptOutput.sh int/0030_find_permutation_given_relation -sh ../../acceptOutput.sh int/0020_letting_permutation_letting_relation -sh ../../acceptOutput.sh unnamed/0040_find_permutation_find_relation diff --git a/tests/custom/permutations/11_transform_relation/runthese.sh b/tests/custom/permutations/11_transform_relation/runthese.sh deleted file mode 100644 index f3c89d1cfc..0000000000 --- a/tests/custom/permutations/11_transform_relation/runthese.sh +++ /dev/null @@ -1 +0,0 @@ -stack build --copy-bins --test --test-arguments "-p custom.permutations.11_transform_relation" diff --git a/tests/custom/permutations/12_transform_list/accept_these.sh b/tests/custom/permutations/12_transform_list/accept_these.sh deleted file mode 100644 index 12b0d9c7bb..0000000000 --- a/tests/custom/permutations/12_transform_list/accept_these.sh +++ /dev/null @@ -1,8 +0,0 @@ -sh ../../acceptOutput.sh enum/0010_given_permutation -sh ../../acceptOutput.sh enum/0030_find_permutation -sh ../../acceptOutput.sh enum/0020_letting_permutation -sh ../../acceptOutput.sh int/0010_given_permutation -sh ../../acceptOutput.sh int/0030_find_permutation -sh ../../acceptOutput.sh int/0020_letting_permutation -sh ../../acceptOutput.sh unnamed/0030_find_permutation - diff --git a/tests/custom/permutations/12_transform_list/runthese.sh b/tests/custom/permutations/12_transform_list/runthese.sh deleted file mode 100644 index 307bef7089..0000000000 --- a/tests/custom/permutations/12_transform_list/runthese.sh +++ /dev/null @@ -1 +0,0 @@ -stack build --copy-bins --test --test-arguments "-p custom.permutations.12_transform_list" diff --git a/tests/custom/permutations/13_transform_function/accept_these.sh b/tests/custom/permutations/13_transform_function/accept_these.sh deleted file mode 100644 index c3e2a349fe..0000000000 --- a/tests/custom/permutations/13_transform_function/accept_these.sh +++ /dev/null @@ -1,7 +0,0 @@ -sh ../../acceptOutput.sh enum/0010_given_permutation -sh ../../acceptOutput.sh enum/0030_find_permutation -sh ../../acceptOutput.sh enum/0020_letting_permutation -sh ../../acceptOutput.sh int/0010_given_permutation -sh ../../acceptOutput.sh int/0030_find_permutation -sh ../../acceptOutput.sh int/0020_letting_permutation -sh ../../acceptOutput.sh unnamed/0030_find_permutation diff --git a/tests/custom/permutations/13_transform_function/runthese.sh b/tests/custom/permutations/13_transform_function/runthese.sh deleted file mode 100644 index 5b2f8993b8..0000000000 --- a/tests/custom/permutations/13_transform_function/runthese.sh +++ /dev/null @@ -1 +0,0 @@ -stack build --copy-bins --test --test-arguments "-p custom.permutations.13_transform_function" diff --git a/tests/custom/permutations/14_transform_sequence/accept_these.sh b/tests/custom/permutations/14_transform_sequence/accept_these.sh deleted file mode 100644 index c3e2a349fe..0000000000 --- a/tests/custom/permutations/14_transform_sequence/accept_these.sh +++ /dev/null @@ -1,7 +0,0 @@ -sh ../../acceptOutput.sh enum/0010_given_permutation -sh ../../acceptOutput.sh enum/0030_find_permutation -sh ../../acceptOutput.sh enum/0020_letting_permutation -sh ../../acceptOutput.sh int/0010_given_permutation -sh ../../acceptOutput.sh int/0030_find_permutation -sh ../../acceptOutput.sh int/0020_letting_permutation -sh ../../acceptOutput.sh unnamed/0030_find_permutation diff --git a/tests/custom/permutations/14_transform_sequence/runthese.sh b/tests/custom/permutations/14_transform_sequence/runthese.sh deleted file mode 100644 index ae75fa1461..0000000000 --- a/tests/custom/permutations/14_transform_sequence/runthese.sh +++ /dev/null @@ -1 +0,0 @@ -stack build --copy-bins --test --test-arguments "-p custom.permutations.14_transform_sequence" diff --git a/tests/custom/permutations/15_transform_mset/accept_these.sh b/tests/custom/permutations/15_transform_mset/accept_these.sh deleted file mode 100644 index 417ffb1e43..0000000000 --- a/tests/custom/permutations/15_transform_mset/accept_these.sh +++ /dev/null @@ -1,11 +0,0 @@ -sh ../../acceptOutput.sh enum/0050_find_permutation_given_mset_find_mset -sh ../../acceptOutput.sh enum/0030_letting_permutation_find_msets -sh ../../acceptOutput.sh enum/0040_find_permutation_find_msets -sh ../../acceptOutput.sh enum/0020_given_permutation_find_msets -sh ../../acceptOutput.sh enum/0010_given_permutation_letting_mset -sh ../../acceptOutput.sh int/0050_find_permutation_given_mset_find_mset -sh ../../acceptOutput.sh int/0030_letting_permutation_find_msets -sh ../../acceptOutput.sh int/0040_find_permutation_find_msets -sh ../../acceptOutput.sh int/0020_given_permutation_find_msets -sh ../../acceptOutput.sh int/0010_given_permutation_letting_mset -sh ../../acceptOutput.sh unnamed/0004_find_permutation_find_msets diff --git a/tests/custom/permutations/15_transform_mset/runthese.sh b/tests/custom/permutations/15_transform_mset/runthese.sh deleted file mode 100644 index 2448831e35..0000000000 --- a/tests/custom/permutations/15_transform_mset/runthese.sh +++ /dev/null @@ -1 +0,0 @@ -stack build --copy-bins --test --test-arguments "-p custom.permutations.15_transform_mset" diff --git a/tests/custom/permutations/16_transform_permutation/accept_these.sh b/tests/custom/permutations/16_transform_permutation/accept_these.sh deleted file mode 100644 index 94e622f20b..0000000000 --- a/tests/custom/permutations/16_transform_permutation/accept_these.sh +++ /dev/null @@ -1,11 +0,0 @@ -sh ../../acceptOutput.sh enum/0040_find_permutation_find_permutations -sh ../../acceptOutput.sh enum/0050_find_permutation_given_permutation_find_permutation -sh ../../acceptOutput.sh enum/0010_given_permutation_letting_permutation -sh ../../acceptOutput.sh enum/0020_given_permutation_find_permutations -sh ../../acceptOutput.sh enum/0030_letting_permutation_find_permutations -sh ../../acceptOutput.sh int/0040_find_permutation_find_permutations -sh ../../acceptOutput.sh int/0050_find_permutation_given_permutation_find_permutation -sh ../../acceptOutput.sh int/0010_given_permutation_letting_permutation -sh ../../acceptOutput.sh int/0020_given_permutation_find_permutations -sh ../../acceptOutput.sh int/0030_letting_permutation_find_permutations -sh ../../acceptOutput.sh unnamed/0004_find_permutation_find_permutations diff --git a/tests/custom/permutations/16_transform_permutation/runthese.sh b/tests/custom/permutations/16_transform_permutation/runthese.sh deleted file mode 100644 index 5b0a16dc53..0000000000 --- a/tests/custom/permutations/16_transform_permutation/runthese.sh +++ /dev/null @@ -1 +0,0 @@ -stack build --copy-bins --test --test-arguments "-p custom.permutations.16_transform_permutation" diff --git a/tests/custom/permutations/17_transform_partition/accept_these.sh b/tests/custom/permutations/17_transform_partition/accept_these.sh deleted file mode 100644 index 9ce41ef5fb..0000000000 --- a/tests/custom/permutations/17_transform_partition/accept_these.sh +++ /dev/null @@ -1,7 +0,0 @@ -sh ../../acceptOutput.sh enum/0010_given_partition_of_enum_BUG -sh ../../acceptOutput.sh int/0020_given_permutation_find_partitions -sh ../../acceptOutput.sh int/0040_find_permutation_find_partitions -sh ../../acceptOutput.sh int/0030_letting_permutation_find_partitions -sh ../../acceptOutput.sh int/0010_given_permutation_partition_find_partition -sh ../../acceptOutput.sh int/0050_find_permutation_given_partition_find_partition -sh ../../acceptOutput.sh unnamed/0010_find_partition_of_unnamed diff --git a/tests/custom/permutations/17_transform_partition/runthese.sh b/tests/custom/permutations/17_transform_partition/runthese.sh deleted file mode 100644 index 43b2e440cb..0000000000 --- a/tests/custom/permutations/17_transform_partition/runthese.sh +++ /dev/null @@ -1 +0,0 @@ -stack build --copy-bins --test --test-arguments "-p custom.permutations.17_transform_partition" diff --git a/tests/custom/permutations/18_transform_matrix/runthese.sh b/tests/custom/permutations/18_transform_matrix/runthese.sh deleted file mode 100644 index 97ae7aac12..0000000000 --- a/tests/custom/permutations/18_transform_matrix/runthese.sh +++ /dev/null @@ -1 +0,0 @@ -stack build --copy-bins --test --test-arguments "-p custom.permutations.18_transform_matrix" diff --git a/tests/custom/permutations/19_complications/runthese.sh b/tests/custom/permutations/19_complications/runthese.sh deleted file mode 100644 index 2ccb69181c..0000000000 --- a/tests/custom/permutations/19_complications/runthese.sh +++ /dev/null @@ -1 +0,0 @@ -stack build --copy-bins --test --test-arguments "-p custom.permutations.19_complications" diff --git a/tests/custom/permutations/20_counting/runthese.sh b/tests/custom/permutations/20_counting/runthese.sh deleted file mode 100644 index c09b909f62..0000000000 --- a/tests/custom/permutations/20_counting/runthese.sh +++ /dev/null @@ -1 +0,0 @@ -stack build --copy-bins --test --test-arguments "-p custom.permutations.20_counting" diff --git a/tests/custom/permutations/21_superpermutations/runthese.sh b/tests/custom/permutations/21_superpermutations/runthese.sh deleted file mode 100644 index 515dc85742..0000000000 --- a/tests/custom/permutations/21_superpermutations/runthese.sh +++ /dev/null @@ -1 +0,0 @@ -stack build --copy-bins --test --test-arguments "-p custom.permutations.21_superpermutations" diff --git a/tests/custom/permutations/22_tagged_ints/accept_these.sh b/tests/custom/permutations/22_tagged_ints/accept_these.sh deleted file mode 100644 index 3de55fa726..0000000000 --- a/tests/custom/permutations/22_tagged_ints/accept_these.sh +++ /dev/null @@ -1,25 +0,0 @@ -sh ../../acceptOutput.sh int/prod/0001_same_tags_works -sh ../../acceptOutput.sh int/prod/0003_const_tagged_works -sh ../../acceptOutput.sh int/pred/0003_const_tagged_works -sh ../../acceptOutput.sh int/div/0001_same_tags_works -sh ../../acceptOutput.sh int/div/0003_const_tagged_works -sh ../../acceptOutput.sh int/succ/0003_const_tagged_works -sh ../../acceptOutput.sh int/minus/0001_same_tags_works -sh ../../acceptOutput.sh int/minus/0003_const_tagged_works -sh ../../acceptOutput.sh int/leq/0003_const_tagged_works -sh ../../acceptOutput.sh int/neg/0001_same_tags_works -sh ../../acceptOutput.sh int/neg/0003_const_tagged_works -sh ../../acceptOutput.sh int/factorial/0003_const_tagged_works -sh ../../acceptOutput.sh int/0002_permute_tagged -sh ../../acceptOutput.sh int/max/0003_const_tagged_works -sh ../../acceptOutput.sh int/max/0001_same_tags_work -sh ../../acceptOutput.sh int/sum/0001_same_tags_works -sh ../../acceptOutput.sh int/sum/0003_const_tagged_works -sh ../../acceptOutput.sh int/lt/0003_const_tagged_works -sh ../../acceptOutput.sh int/0003_tagged_lits_in_param -sh ../../acceptOutput.sh int/0001_permute_untagged -sh ../../acceptOutput.sh int/min/0003_const_tagged_works -sh ../../acceptOutput.sh int/min/0001_same_tags_work -sh ../../acceptOutput.sh int/mod/0001_same_tags_works -sh ../../acceptOutput.sh int/mod/0003_const_tagged_works -sh ../../acceptOutput.sh int/geq/0003_const_tagged_works diff --git a/tests/custom/permutations/22_tagged_ints/runthese.sh b/tests/custom/permutations/22_tagged_ints/runthese.sh deleted file mode 100644 index 388ae0e9f2..0000000000 --- a/tests/custom/permutations/22_tagged_ints/runthese.sh +++ /dev/null @@ -1 +0,0 @@ -stack build --copy-bins --test --test-arguments "-p custom.permutations.22_tagged_ints" diff --git a/tests/custom/permutations/23_image_set_dotlt/runthese.sh b/tests/custom/permutations/23_image_set_dotlt/runthese.sh deleted file mode 100644 index 19a4d4fbd4..0000000000 --- a/tests/custom/permutations/23_image_set_dotlt/runthese.sh +++ /dev/null @@ -1 +0,0 @@ -stack build --copy-bins --test --test-arguments "-p custom.permutations.23" diff --git a/tests/custom/permutations/24_image_comprehension_dotlt/runthese.sh b/tests/custom/permutations/24_image_comprehension_dotlt/runthese.sh deleted file mode 100644 index 9b679c9d7d..0000000000 --- a/tests/custom/permutations/24_image_comprehension_dotlt/runthese.sh +++ /dev/null @@ -1 +0,0 @@ -stack build --copy-bins --test --test-arguments "-p custom.permutations.24" diff --git a/tests/custom/permutations/runthese.sh b/tests/custom/permutations/runthese.sh deleted file mode 100644 index 179fecc442..0000000000 --- a/tests/custom/permutations/runthese.sh +++ /dev/null @@ -1 +0,0 @@ -stack build --copy-bins --test --test-arguments "-p custom.permutations" diff --git a/tests/exhaustive/basic/perms/05_equality/int/expected/model-solution000001.solution b/tests/exhaustive/basic/perms/05_equality/int/extra/expected/model-solution000001.solution similarity index 100% rename from tests/exhaustive/basic/perms/05_equality/int/expected/model-solution000001.solution rename to tests/exhaustive/basic/perms/05_equality/int/extra/expected/model-solution000001.solution diff --git a/tests/exhaustive/basic/perms/05_equality/int/expected/model.eprime b/tests/exhaustive/basic/perms/05_equality/int/extra/expected/model.eprime similarity index 100% rename from tests/exhaustive/basic/perms/05_equality/int/expected/model.eprime rename to tests/exhaustive/basic/perms/05_equality/int/extra/expected/model.eprime diff --git a/tests/exhaustive/basic/perms/05_equality/int/new.essence b/tests/exhaustive/basic/perms/05_equality/int/extra/new.essence similarity index 100% rename from tests/exhaustive/basic/perms/05_equality/int/new.essence rename to tests/exhaustive/basic/perms/05_equality/int/extra/new.essence diff --git a/tests/exhaustive/basic/perms/06_inverse/int/0005_find_eq_find/expected/model-solution000001.solution b/tests/exhaustive/basic/perms/06_inverse/int/0005_find_eq_find/expected/model-solution000001.solution new file mode 100644 index 0000000000..5e99ad7a05 --- /dev/null +++ b/tests/exhaustive/basic/perms/06_inverse/int/0005_find_eq_find/expected/model-solution000001.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting p be permutation() +letting q be permutation() diff --git a/tests/exhaustive/basic/perms/06_inverse/int/0005_find_eq_find/expected/model-solution000002.solution b/tests/exhaustive/basic/perms/06_inverse/int/0005_find_eq_find/expected/model-solution000002.solution new file mode 100644 index 0000000000..d51a2f2ed6 --- /dev/null +++ b/tests/exhaustive/basic/perms/06_inverse/int/0005_find_eq_find/expected/model-solution000002.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting p be permutation((3, 4)) +letting q be permutation((3, 4)) diff --git a/tests/exhaustive/basic/perms/06_inverse/int/0005_find_eq_find/expected/model-solution000003.solution b/tests/exhaustive/basic/perms/06_inverse/int/0005_find_eq_find/expected/model-solution000003.solution new file mode 100644 index 0000000000..5c3302f8db --- /dev/null +++ b/tests/exhaustive/basic/perms/06_inverse/int/0005_find_eq_find/expected/model-solution000003.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting p be permutation((2, 3)) +letting q be permutation((2, 3)) diff --git a/tests/exhaustive/basic/perms/06_inverse/int/0005_find_eq_find/expected/model-solution000004.solution b/tests/exhaustive/basic/perms/06_inverse/int/0005_find_eq_find/expected/model-solution000004.solution new file mode 100644 index 0000000000..3b2afcfc83 --- /dev/null +++ b/tests/exhaustive/basic/perms/06_inverse/int/0005_find_eq_find/expected/model-solution000004.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting p be permutation((2, 3, 4)) +letting q be permutation((2, 4, 3)) diff --git a/tests/exhaustive/basic/perms/06_inverse/int/0005_find_eq_find/expected/model-solution000005.solution b/tests/exhaustive/basic/perms/06_inverse/int/0005_find_eq_find/expected/model-solution000005.solution new file mode 100644 index 0000000000..dad51fcd4c --- /dev/null +++ b/tests/exhaustive/basic/perms/06_inverse/int/0005_find_eq_find/expected/model-solution000005.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting p be permutation((2, 4, 3)) +letting q be permutation((2, 3, 4)) diff --git a/tests/exhaustive/basic/perms/06_inverse/int/0005_find_eq_find/expected/model-solution000006.solution b/tests/exhaustive/basic/perms/06_inverse/int/0005_find_eq_find/expected/model-solution000006.solution new file mode 100644 index 0000000000..9aed2f67de --- /dev/null +++ b/tests/exhaustive/basic/perms/06_inverse/int/0005_find_eq_find/expected/model-solution000006.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting p be permutation((2, 4)) +letting q be permutation((2, 4)) diff --git a/tests/exhaustive/basic/perms/06_inverse/int/0005_find_eq_find/expected/model-solution000007.solution b/tests/exhaustive/basic/perms/06_inverse/int/0005_find_eq_find/expected/model-solution000007.solution new file mode 100644 index 0000000000..5760f6393a --- /dev/null +++ b/tests/exhaustive/basic/perms/06_inverse/int/0005_find_eq_find/expected/model-solution000007.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting p be permutation((1, 2)) +letting q be permutation((1, 2)) diff --git a/tests/exhaustive/basic/perms/06_inverse/int/0005_find_eq_find/expected/model-solution000008.solution b/tests/exhaustive/basic/perms/06_inverse/int/0005_find_eq_find/expected/model-solution000008.solution new file mode 100644 index 0000000000..57925fc124 --- /dev/null +++ b/tests/exhaustive/basic/perms/06_inverse/int/0005_find_eq_find/expected/model-solution000008.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting p be permutation((1, 2), (3, 4)) +letting q be permutation((1, 2), (3, 4)) diff --git a/tests/exhaustive/basic/perms/06_inverse/int/0005_find_eq_find/expected/model-solution000009.solution b/tests/exhaustive/basic/perms/06_inverse/int/0005_find_eq_find/expected/model-solution000009.solution new file mode 100644 index 0000000000..ed01ea12f0 --- /dev/null +++ b/tests/exhaustive/basic/perms/06_inverse/int/0005_find_eq_find/expected/model-solution000009.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting p be permutation((1, 2, 3)) +letting q be permutation((1, 3, 2)) diff --git a/tests/exhaustive/basic/perms/06_inverse/int/0005_find_eq_find/expected/model-solution000010.solution b/tests/exhaustive/basic/perms/06_inverse/int/0005_find_eq_find/expected/model-solution000010.solution new file mode 100644 index 0000000000..a4cbf995e9 --- /dev/null +++ b/tests/exhaustive/basic/perms/06_inverse/int/0005_find_eq_find/expected/model-solution000010.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting p be permutation((1, 2, 3, 4)) +letting q be permutation((1, 4, 3, 2)) diff --git a/tests/exhaustive/basic/perms/06_inverse/int/0005_find_eq_find/expected/model-solution000011.solution b/tests/exhaustive/basic/perms/06_inverse/int/0005_find_eq_find/expected/model-solution000011.solution new file mode 100644 index 0000000000..66a2f1e65b --- /dev/null +++ b/tests/exhaustive/basic/perms/06_inverse/int/0005_find_eq_find/expected/model-solution000011.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting p be permutation((1, 2, 4, 3)) +letting q be permutation((1, 3, 4, 2)) diff --git a/tests/exhaustive/basic/perms/06_inverse/int/0005_find_eq_find/expected/model-solution000012.solution b/tests/exhaustive/basic/perms/06_inverse/int/0005_find_eq_find/expected/model-solution000012.solution new file mode 100644 index 0000000000..cee7944cc6 --- /dev/null +++ b/tests/exhaustive/basic/perms/06_inverse/int/0005_find_eq_find/expected/model-solution000012.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting p be permutation((1, 2, 4)) +letting q be permutation((1, 4, 2)) diff --git a/tests/exhaustive/basic/perms/06_inverse/int/0005_find_eq_find/expected/model-solution000013.solution b/tests/exhaustive/basic/perms/06_inverse/int/0005_find_eq_find/expected/model-solution000013.solution new file mode 100644 index 0000000000..ee19383ab3 --- /dev/null +++ b/tests/exhaustive/basic/perms/06_inverse/int/0005_find_eq_find/expected/model-solution000013.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting p be permutation((1, 3, 2)) +letting q be permutation((1, 2, 3)) diff --git a/tests/exhaustive/basic/perms/06_inverse/int/0005_find_eq_find/expected/model-solution000014.solution b/tests/exhaustive/basic/perms/06_inverse/int/0005_find_eq_find/expected/model-solution000014.solution new file mode 100644 index 0000000000..af5b4b29f3 --- /dev/null +++ b/tests/exhaustive/basic/perms/06_inverse/int/0005_find_eq_find/expected/model-solution000014.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting p be permutation((1, 3, 4, 2)) +letting q be permutation((1, 2, 4, 3)) diff --git a/tests/exhaustive/basic/perms/06_inverse/int/0005_find_eq_find/expected/model-solution000015.solution b/tests/exhaustive/basic/perms/06_inverse/int/0005_find_eq_find/expected/model-solution000015.solution new file mode 100644 index 0000000000..e622738f3b --- /dev/null +++ b/tests/exhaustive/basic/perms/06_inverse/int/0005_find_eq_find/expected/model-solution000015.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting p be permutation((1, 3)) +letting q be permutation((1, 3)) diff --git a/tests/exhaustive/basic/perms/06_inverse/int/0005_find_eq_find/expected/model-solution000016.solution b/tests/exhaustive/basic/perms/06_inverse/int/0005_find_eq_find/expected/model-solution000016.solution new file mode 100644 index 0000000000..7cb1a3391f --- /dev/null +++ b/tests/exhaustive/basic/perms/06_inverse/int/0005_find_eq_find/expected/model-solution000016.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting p be permutation((1, 3, 4)) +letting q be permutation((1, 4, 3)) diff --git a/tests/exhaustive/basic/perms/06_inverse/int/0005_find_eq_find/expected/model-solution000017.solution b/tests/exhaustive/basic/perms/06_inverse/int/0005_find_eq_find/expected/model-solution000017.solution new file mode 100644 index 0000000000..ed94b069c6 --- /dev/null +++ b/tests/exhaustive/basic/perms/06_inverse/int/0005_find_eq_find/expected/model-solution000017.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting p be permutation((1, 3), (2, 4)) +letting q be permutation((1, 3), (2, 4)) diff --git a/tests/exhaustive/basic/perms/06_inverse/int/0005_find_eq_find/expected/model-solution000018.solution b/tests/exhaustive/basic/perms/06_inverse/int/0005_find_eq_find/expected/model-solution000018.solution new file mode 100644 index 0000000000..3a66e67752 --- /dev/null +++ b/tests/exhaustive/basic/perms/06_inverse/int/0005_find_eq_find/expected/model-solution000018.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting p be permutation((1, 3, 2, 4)) +letting q be permutation((1, 4, 2, 3)) diff --git a/tests/exhaustive/basic/perms/06_inverse/int/0005_find_eq_find/expected/model-solution000019.solution b/tests/exhaustive/basic/perms/06_inverse/int/0005_find_eq_find/expected/model-solution000019.solution new file mode 100644 index 0000000000..83b0838785 --- /dev/null +++ b/tests/exhaustive/basic/perms/06_inverse/int/0005_find_eq_find/expected/model-solution000019.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting p be permutation((1, 4, 3, 2)) +letting q be permutation((1, 2, 3, 4)) diff --git a/tests/exhaustive/basic/perms/06_inverse/int/0005_find_eq_find/expected/model-solution000020.solution b/tests/exhaustive/basic/perms/06_inverse/int/0005_find_eq_find/expected/model-solution000020.solution new file mode 100644 index 0000000000..5b7380b66b --- /dev/null +++ b/tests/exhaustive/basic/perms/06_inverse/int/0005_find_eq_find/expected/model-solution000020.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting p be permutation((1, 4, 2)) +letting q be permutation((1, 2, 4)) diff --git a/tests/exhaustive/basic/perms/06_inverse/int/0005_find_eq_find/expected/model-solution000021.solution b/tests/exhaustive/basic/perms/06_inverse/int/0005_find_eq_find/expected/model-solution000021.solution new file mode 100644 index 0000000000..1618387ea6 --- /dev/null +++ b/tests/exhaustive/basic/perms/06_inverse/int/0005_find_eq_find/expected/model-solution000021.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting p be permutation((1, 4, 3)) +letting q be permutation((1, 3, 4)) diff --git a/tests/exhaustive/basic/perms/06_inverse/int/0005_find_eq_find/expected/model-solution000022.solution b/tests/exhaustive/basic/perms/06_inverse/int/0005_find_eq_find/expected/model-solution000022.solution new file mode 100644 index 0000000000..a9675be6a3 --- /dev/null +++ b/tests/exhaustive/basic/perms/06_inverse/int/0005_find_eq_find/expected/model-solution000022.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting p be permutation((1, 4)) +letting q be permutation((1, 4)) diff --git a/tests/exhaustive/basic/perms/06_inverse/int/0005_find_eq_find/expected/model-solution000023.solution b/tests/exhaustive/basic/perms/06_inverse/int/0005_find_eq_find/expected/model-solution000023.solution new file mode 100644 index 0000000000..e820c11b06 --- /dev/null +++ b/tests/exhaustive/basic/perms/06_inverse/int/0005_find_eq_find/expected/model-solution000023.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting p be permutation((1, 4, 2, 3)) +letting q be permutation((1, 3, 2, 4)) diff --git a/tests/exhaustive/basic/perms/06_inverse/int/0005_find_eq_find/expected/model-solution000024.solution b/tests/exhaustive/basic/perms/06_inverse/int/0005_find_eq_find/expected/model-solution000024.solution new file mode 100644 index 0000000000..fa74c1f6bc --- /dev/null +++ b/tests/exhaustive/basic/perms/06_inverse/int/0005_find_eq_find/expected/model-solution000024.solution @@ -0,0 +1,4 @@ +language Essence 1.3 + +letting p be permutation((1, 4), (2, 3)) +letting q be permutation((1, 4), (2, 3)) diff --git a/tests/exhaustive/basic/perms/06_inverse/int/0005_find_eq_find/expected/model.eprime b/tests/exhaustive/basic/perms/06_inverse/int/0005_find_eq_find/expected/model.eprime new file mode 100644 index 0000000000..190fb337e8 --- /dev/null +++ b/tests/exhaustive/basic/perms/06_inverse/int/0005_find_eq_find/expected/model.eprime @@ -0,0 +1,30 @@ +language ESSENCE' 1.0 + +find p_PermutationAsFunction_PermutationFunction_Function1D: matrix indexed by [int(1..4)] of int(1..4) +find q_PermutationAsFunction_PermutationFunction_Function1D: matrix indexed by [int(1..4)] of int(1..4) +branching on + [p_PermutationAsFunction_PermutationFunction_Function1D, q_PermutationAsFunction_PermutationFunction_Function1D] +such that + and([q17 != p_PermutationAsFunction_PermutationFunction_Function1D[q17] -> + [p_PermutationAsFunction_PermutationFunction_Function1D[q17], + catchUndef(q_PermutationAsFunction_PermutationFunction_Function1D + [p_PermutationAsFunction_PermutationFunction_Function1D[q17]], + 0); + int(1..2)] + [toInt(or([q15 = p_PermutationAsFunction_PermutationFunction_Function1D[q17] | q15 : int(1..4)])) + 1] + = q17 + | q17 : int(1..4)]), + and([q25 != q_PermutationAsFunction_PermutationFunction_Function1D[q25] -> + [q_PermutationAsFunction_PermutationFunction_Function1D[q25], + catchUndef(p_PermutationAsFunction_PermutationFunction_Function1D + [q_PermutationAsFunction_PermutationFunction_Function1D[q25]], + 0); + int(1..2)] + [toInt(or([q23 = q_PermutationAsFunction_PermutationFunction_Function1D[q25] | q23 : int(1..4)])) + 1] + = q25 + | q25 : int(1..4)]), + allDiff(p_PermutationAsFunction_PermutationFunction_Function1D), + and([or([p_PermutationAsFunction_PermutationFunction_Function1D[q3] = q2 | q3 : int(1..4)]) | q2 : int(1..4)]), + allDiff(q_PermutationAsFunction_PermutationFunction_Function1D), + and([or([q_PermutationAsFunction_PermutationFunction_Function1D[q7] = q6 | q7 : int(1..4)]) | q6 : int(1..4)]) + From 19740abe172ed8e079fb647b89fce90101d6c11a Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?=C3=96zg=C3=BCr=20Akg=C3=BCn?= Date: Sun, 3 Mar 2024 15:57:20 +0000 Subject: [PATCH 144/229] remove redundant files --- etc/testdata/specs/matrixes.essence | 7 ------- etc/testdata/specs/matrixes2.essence | 6 ------ etc/testdata/specs/n3.essence | 7 ------- etc/testdata/specs/set-of-lettings.essence | 13 ------------- etc/upTests/___simple/matrixes_of_tuples.essence | 7 ------- etc/upTests/_matrix_of_tuples/different.essence | 7 ------- etc/upTests/matrixes2.essence | 6 ------ 7 files changed, 53 deletions(-) delete mode 100644 etc/testdata/specs/matrixes.essence delete mode 100644 etc/testdata/specs/matrixes2.essence delete mode 100644 etc/testdata/specs/n3.essence delete mode 100644 etc/testdata/specs/set-of-lettings.essence delete mode 100644 etc/upTests/___simple/matrixes_of_tuples.essence delete mode 100644 etc/upTests/_matrix_of_tuples/different.essence delete mode 100644 etc/upTests/matrixes2.essence diff --git a/etc/testdata/specs/matrixes.essence b/etc/testdata/specs/matrixes.essence deleted file mode 100644 index 2d433e2ae0..0000000000 --- a/etc/testdata/specs/matrixes.essence +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 2.0 - -find x : matrix indexed by [int(1..2)] of (int(3,5), int(6,7)) -such that - x[1][1] = 3, - x[2] = (5,7), - x[1][2] = 6, diff --git a/etc/testdata/specs/matrixes2.essence b/etc/testdata/specs/matrixes2.essence deleted file mode 100644 index 2ea6902ce2..0000000000 --- a/etc/testdata/specs/matrixes2.essence +++ /dev/null @@ -1,6 +0,0 @@ -language Essence 2.0 - -find x : matrix indexed by [int(1..2)] of set(minSize 1) of int(6..8) -such that - x[1] = {6}, - x[2] = {7,8} diff --git a/etc/testdata/specs/n3.essence b/etc/testdata/specs/n3.essence deleted file mode 100644 index 88c40e7399..0000000000 --- a/etc/testdata/specs/n3.essence +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 2.0 - -find x : set (minSize 1) of set (minSize 1) of int(1..1) -find n : int(1..1) - -such that - forAll i in x . forAll j in i . j =1 diff --git a/etc/testdata/specs/set-of-lettings.essence b/etc/testdata/specs/set-of-lettings.essence deleted file mode 100644 index fffc4e0feb..0000000000 --- a/etc/testdata/specs/set-of-lettings.essence +++ /dev/null @@ -1,13 +0,0 @@ -language Essence 2.0 - -letting V be domain int(1..n) -letting SS be domain set of V -letting n be 3 -letting CC be domain set of tuple (V, SS) - -find x : set of tuple (V,int(1..n),int(1..4)) -find y : CC - -such that - (2,3,4) in x, - (1,{3}) in y diff --git a/etc/upTests/___simple/matrixes_of_tuples.essence b/etc/upTests/___simple/matrixes_of_tuples.essence deleted file mode 100644 index 2d433e2ae0..0000000000 --- a/etc/upTests/___simple/matrixes_of_tuples.essence +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 2.0 - -find x : matrix indexed by [int(1..2)] of (int(3,5), int(6,7)) -such that - x[1][1] = 3, - x[2] = (5,7), - x[1][2] = 6, diff --git a/etc/upTests/_matrix_of_tuples/different.essence b/etc/upTests/_matrix_of_tuples/different.essence deleted file mode 100644 index 874dc75ebf..0000000000 --- a/etc/upTests/_matrix_of_tuples/different.essence +++ /dev/null @@ -1,7 +0,0 @@ -language Essence 1.3 - -find x : matrix indexed by [int(1..2)] of (int(3,5), int(6,7)) -such that - x[1][1] = 3, - x[2] = (5,7), - x[1][2] = 6, diff --git a/etc/upTests/matrixes2.essence b/etc/upTests/matrixes2.essence deleted file mode 100644 index 2ea6902ce2..0000000000 --- a/etc/upTests/matrixes2.essence +++ /dev/null @@ -1,6 +0,0 @@ -language Essence 2.0 - -find x : matrix indexed by [int(1..2)] of set(minSize 1) of int(6..8) -such that - x[1] = {6}, - x[2] = {7,8} From f37d1acba8a40433ec0f7be3c7fd2a56832201a1 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?=C3=96zg=C3=BCr=20Akg=C3=BCn?= Date: Sun, 3 Mar 2024 15:57:52 +0000 Subject: [PATCH 145/229] perutation inverse --- src/Conjure/Language/Validator.hs | 22 +++++++++------------- 1 file changed, 9 insertions(+), 13 deletions(-) diff --git a/src/Conjure/Language/Validator.hs b/src/Conjure/Language/Validator.hs index 6cb074ef7e..7aa8db3687 100644 --- a/src/Conjure/Language/Validator.hs +++ b/src/Conjure/Language/Validator.hs @@ -2405,19 +2405,15 @@ functionOps l = case l of return $ if null a' || null b' then Nothing else Just () inverseArgs :: SArg -> SArg -> Validator () - inverseArgs (r1, a) (r2, b) = do - let (fIn, fOut) = case (typeOf_ a, typeOf_ b) of - (TypeFunction fi fo, TypeFunction gi go) -> (mostDefinedS [fi, go], mostDefinedS [fo, gi]) - (TypeFunction fi fo, _) -> (fi, fo) - (_, TypeFunction gi go) -> (gi, go) - (TypePermutation ta, TypePermutation tb) -> (mostDefinedS [ta, tb], mostDefinedS [ta, tb]) - (TypePermutation ta, _) -> (ta, ta) - (_, TypePermutation ta) -> (ta, ta) - _ -> (TypeAny, TypeAny) - return (Just ()) - -- a' <- unifyTypesFailing (TypeFunction fIn fOut) (r1, a) - -- b' <- unifyTypesFailing (TypeFunction fOut fIn) (r2, b) - -- return $ if null a' || null b' then Nothing else Just () + inverseArgs (_r1, a) (_r2, b) = + case (typeOf_ a, typeOf_ b) of + (TypeFunction{}, TypeFunction{}) -> return (Just ()) + (TypeFunction{}, _) -> return (Just ()) + (_, TypeFunction{}) -> return (Just ()) + (TypePermutation{}, TypePermutation{}) -> return (Just ()) + (TypePermutation{}, _) -> return (Just ()) + (_, TypePermutation{}) -> return (Just ()) + _ -> return Nothing setPartArgs :: SArg -> SArg -> Validator () setPartArgs (r1, a) (r2, b) = do From 1e695724a1aa65dc8402366ef946443c6aaddbed Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?=C3=96zg=C3=BCr=20Akg=C3=BCn?= Date: Sun, 3 Mar 2024 18:59:53 +0000 Subject: [PATCH 146/229] stylistic changes --- src/Conjure/Util/Permutation.hs | 26 +++++++++++--------------- 1 file changed, 11 insertions(+), 15 deletions(-) diff --git a/src/Conjure/Util/Permutation.hs b/src/Conjure/Util/Permutation.hs index 6c9276fb1c..58a7d8f41f 100644 --- a/src/Conjure/Util/Permutation.hs +++ b/src/Conjure/Util/Permutation.hs @@ -38,17 +38,17 @@ import Data.Semigroup ( (<>) ) -- | The Permutation constructor is for internal use only. -- To construct a permutation use any of the smart constructors. -data Permutation a = Permutation [(a, a)] deriving (Show) +newtype Permutation a = Permutation [(a, a)] deriving (Show) -- | Equality tests that permutations contain the same permuted values. instance (Eq a) => Eq (Permutation a) where - (==) (Permutation l) (Permutation r) = all id [e `elem` r | e <- l] + (==) (Permutation l) (Permutation r) = and [e `elem` r | e <- l] -- | Permutations compose as a semigroup in the same way they would compose if you composed them as functions. instance (Eq a) => Semigroup (Permutation a) where (<>) pl@(Permutation l) pr@(Permutation r) = - let flatten z = join $ ((\(x, y) -> [x, y]) <$> z) - elemsofp = nub $ (flatten l) ++ (flatten r) + let flatten z = (z >>= (\(x, y) -> [x, y])) + elemsofp = nub $ flatten l ++ flatten r permfunc = toFunction pl . toFunction pr in case fromRelation (zip elemsofp (permfunc <$> elemsofp)) of Left _ -> @@ -69,8 +69,7 @@ instance (Eq a) => Monoid (Permutation a) where --------------------------Error Type-------------------------------------------------- -- | There may be an error detailing why the permutation computation has failed. -data PermutationError - = PermutationError String +newtype PermutationError = PermutationError String deriving (Eq, Show) -- | Create a Permutation from disjoint cycles. @@ -81,7 +80,7 @@ fromCycles c = Left $ PermutationError "Data.Permutation.fromCycles: Cycles contain a duplicate element" - else Right $ Permutation $ join $ cycleToTuples <$> c + else Right $ Permutation $ c >>= cycleToTuples where cycleToTuples :: [a] -> [(a, a)] cycleToTuples [] = [] @@ -93,7 +92,7 @@ fromCycles c = -- (e.g. fromRelation [(1,2),(2,1),(3,3)] == fromRelation [(1,2),(2,1)]). fromRelation :: (Eq a) => [(a, a)] -> Either PermutationError (Permutation a) fromRelation r = - let perm = Permutation $ filter (\(x, y) -> x /= y) r + let perm = Permutation $ filter (uncurry (/=)) r in if isBijective $ Permutation r then Right perm else @@ -118,10 +117,7 @@ fromTwoLineForm (t, b) = -- | Gets the permutation as a function. toFunction :: (Eq a) => Permutation a -> (a -> a) -toFunction (Permutation p) = \v -> - case lookup v p of - Nothing -> v - Just so -> so +toFunction (Permutation p) v = fromMaybe v (lookup v p) -- | Convert the permutation to cycle form. toCycles :: (Eq a) => Permutation a -> [[a]] @@ -206,7 +202,7 @@ isBijective (Permutation p) = let (l, r) = unzip p in (length (nub l) == length (nub r)) && (length (nub l) == length l) - && (l \\ r == []) + && (null (l \\ r)) -------------------------CycleFinder Monad--------------------------------------------- @@ -244,7 +240,7 @@ mapsOnto i = do cyclesFound :: (Eq a) => CycleFinder a Bool cyclesFound = do (w, _, m) <- get - return (w == [] && m == []) + return (null w && null m) -- | Returns the cycles. returnCycles :: CycleFinder a [[a]] @@ -264,7 +260,7 @@ startNewCycle = do nextCycleElem :: (Eq a) => CycleFinder a () nextCycleElem = do (w, c, m) <- get - let w_last = head $ reverse w + let w_last = last w next <- mapsOnto w_last let filt = filter (/= (w_last, next)) m if next == head w From ff1d64bc6018a2afcb59afaa10cfc378041f30c2 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?=C3=96zg=C3=BCr=20Akg=C3=BCn?= Date: Sun, 3 Mar 2024 19:00:12 +0000 Subject: [PATCH 147/229] in and inverse evaluator --- src/Conjure/Language/EvaluateOp.hs | 10 ++++ src/Conjure/Language/Validator.hs | 5 +- src/test/Conjure/ParsePrint.hs | 94 +++++++++++++++--------------- 3 files changed, 60 insertions(+), 49 deletions(-) diff --git a/src/Conjure/Language/EvaluateOp.hs b/src/Conjure/Language/EvaluateOp.hs index ebcb393eb6..f75e77515a 100644 --- a/src/Conjure/Language/EvaluateOp.hs +++ b/src/Conjure/Language/EvaluateOp.hs @@ -219,6 +219,12 @@ instance EvaluateOp OpIn where evaluateOp (OpIn c (viewConstantMSet -> Just cs)) = return $ ConstantBool $ elem c cs evaluateOp (OpIn c (viewConstantFunction -> Just cs)) = return $ ConstantBool $ elem c $ map (\ (i,j) -> ConstantAbstract $ AbsLitTuple [i,j] ) cs + evaluateOp op@(OpIn (viewConstantTuple -> Just [a,b]) (viewConstantPermutation -> Just xss)) = + case fromCycles xss of + Right p -> do + let f = toFunction p + return $ ConstantBool $ f a == b + _ -> na $ "evaluateOp{OpIn}:" <++> pretty (show op) evaluateOp (OpIn c (viewConstantRelation -> Just cs)) = return $ ConstantBool $ elem c $ map (ConstantAbstract . AbsLitTuple) cs evaluateOp op = na $ "evaluateOp{OpIn}:" <++> pretty (show op) @@ -299,6 +305,10 @@ instance EvaluateOp OpInverse where return $ ConstantBool $ and $ concat [ [ (j,i) `elem` ys | (i,j) <- xs ] , [ (j,i) `elem` xs | (i,j) <- ys ] ] + evaluateOp op@(OpInverse (viewConstantPermutation -> Just xss) (viewConstantPermutation -> Just yss)) = + case (fromCycles xss, fromCycles yss) of + (Right px, Right py) -> return $ ConstantBool $ px == inverse py + _ -> na $ "evaluateOp{OpInverse}:" <++> pretty (show op) evaluateOp op = na $ "evaluateOp{OpInverse}:" <++> pretty (show op) instance EvaluateOp OpLeq where diff --git a/src/Conjure/Language/Validator.hs b/src/Conjure/Language/Validator.hs index 7aa8db3687..ace27652a4 100644 --- a/src/Conjure/Language/Validator.hs +++ b/src/Conjure/Language/Validator.hs @@ -1317,6 +1317,9 @@ validatePostfixOp (ApplicationNode args) = return $ \exp -> do TypeFunction _ _ -> do args' <- validateList (validateExpression >=> \(Typed t' e') -> return (simple t', e')) args validateFuncOp L_image ((reg, (simple t, e)) : args') + TypePermutation _ -> do + args' <- validateList (validateExpression >=> \(Typed t' e') -> return (simple t', e')) args + validateFuncOp L_image ((reg, (simple t, e)) : args') TypeSequence _ -> do args' <- validateList (validateExpression >=> \(Typed t' e') -> return (simple t', e')) args validateFuncOp L_image ((reg, (simple t, e)) : args') @@ -1327,7 +1330,7 @@ validatePostfixOp (ApplicationNode args) = return $ \exp -> do iType <- case t of TypeRelation ts -> checkProjectionArgs ts ys _ -> do - raiseTypeError $ symbolRegion exp ComplexTypeError "Relation or function" t + raiseTypeError $ symbolRegion exp ComplexTypeError "function, permutation or relation" t let ts = map (maybe TypeAny (typeOf_ . snd)) ys return $ TypeRelation ts let op = Op $ MkOpRelationProj $ OpRelationProj e (map (untype . snd <$>) ys) diff --git a/src/test/Conjure/ParsePrint.hs b/src/test/Conjure/ParsePrint.hs index 76ab94abdf..d46b69b3b7 100644 --- a/src/test/Conjure/ParsePrint.hs +++ b/src/test/Conjure/ParsePrint.hs @@ -105,54 +105,52 @@ testSingleDir TestDirFiles{..} = testCaseSteps (map (\ch -> if ch == '/' then '. readIfExists :: FilePath -> IO String readIfExists f = fromMaybe "" <$> readFileIfExists f - e <- do - step "Checking stderr" - stderrG <- fixWindowsPaths <$> readIfExists (tBaseDir "stderr") - stderrE <- readIfExists (tBaseDir "stderr.expected") - unless (stderrE == stderrG) $ - assertFailure $ - renderNormal $ - vcat - [ "unexpected stderr:" <++> pretty stderrG - , "was expecting: " <++> pretty stderrE - ] - return stderrE - unless (e /= "") $ do - do - step "Checking Generated Representation" - stdoutG <- fixWindowsPaths <$> readIfExists (tBaseDir "model.json") - stdoutE <- readIfExists (tBaseDir "model.expected.json") - let diffs = do - jGiven <- stringToJson stdoutG - jReference <- stringToJson stdoutE - let Patch ds = diff jGiven jReference - return ds - case diffs of - Nothing -> assertFailure $ "JSON parser error in" ++ stdoutE - Just [] -> return () - Just ops -> assertFailure $ renderNormal $ vcat ["Difference in json:" <++> vcat (map (stringToDoc . show) ops)] - do - step "Checking stdout" - stdoutG <- fixWindowsPaths <$> readIfExists (tBaseDir "stdout") - stdoutE <- readIfExists (tBaseDir "stdout.expected") - unless (stdoutE == stdoutG) $ - assertFailure $ - renderNormal $ - vcat - [ "unexpected stdout:" <++> pretty stdoutG - , "was expecting: " <++> pretty stdoutE - ] - do - step "Checking Types" - stdoutE <- fixWindowsPaths <$> readIfExists (tBaseDir "typecheck") - stdoutG <- readIfExists (tBaseDir "typecheck.expected") - unless (stdoutE == stdoutG) $ - assertFailure $ - renderNormal $ - vcat - [ "unexpected typeError:" <++> pretty stdoutG - , "was expecting: " <++> pretty stdoutE - ] + + step "Checking stderr" + stderrG <- fixWindowsPaths <$> readIfExists (tBaseDir "stderr") + stderrE <- readIfExists (tBaseDir "stderr.expected") + unless (stderrE == stderrG) $ + assertFailure $ + renderNormal $ + vcat + [ "unexpected stderr:" <++> pretty stderrG + , "was expecting: " <++> pretty stderrE + ] + + step "Checking stdout" + stdoutG <- fixWindowsPaths <$> readIfExists (tBaseDir "stdout") + stdoutE <- readIfExists (tBaseDir "stdout.expected") + unless (stdoutE == stdoutG) $ + assertFailure $ + renderNormal $ + vcat + [ "unexpected stdout:" <++> pretty stdoutG + , "was expecting: " <++> pretty stdoutE + ] + + step "Checking Generated Representation" + modelG <- fixWindowsPaths <$> readIfExists (tBaseDir "model.json") + modelE <- readIfExists (tBaseDir "model.expected.json") + let diffs = do + jGiven <- stringToJson modelG + jReference <- stringToJson modelE + let Patch ds = diff jGiven jReference + return ds + case diffs of + Nothing -> assertFailure $ "JSON parser error in" ++ modelE + Just [] -> return () + Just ops -> assertFailure $ renderNormal $ vcat ["Difference in json:" <++> vcat (map (stringToDoc . show) ops)] + + step "Checking Types" + typecheckE <- fixWindowsPaths <$> readIfExists (tBaseDir "typecheck") + typecheckG <- readIfExists (tBaseDir "typecheck.expected") + unless (typecheckE == typecheckG) $ + assertFailure $ + renderNormal $ + vcat + [ "unexpected typeError:" <++> pretty typecheckG + , "was expecting: " <++> pretty typecheckE + ] stringToJson :: String -> Maybe JSON.Value stringToJson "" = Just JSON.emptyObject From aa05f13959fdf2c72240c25ad9781e71280d04d7 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?=C3=96zg=C3=BCr=20Akg=C3=BCn?= Date: Sun, 3 Mar 2024 19:03:22 +0000 Subject: [PATCH 148/229] a few more passing tests --- .../defined-type-error/stderr.expected | 4 ++-- .../inverse-type-error/stderr.expected | 10 ++-------- .../range-type-error/stderr.expected | 2 +- .../stdout.expected | 2 ++ 4 files changed, 7 insertions(+), 11 deletions(-) diff --git a/tests/custom/STARIS_2022/operation-type-errors/defined-type-error/stderr.expected b/tests/custom/STARIS_2022/operation-type-errors/defined-type-error/stderr.expected index 5dc4af199f..7ba7b24326 100644 --- a/tests/custom/STARIS_2022/operation-type-errors/defined-type-error/stderr.expected +++ b/tests/custom/STARIS_2022/operation-type-errors/defined-type-error/stderr.expected @@ -4,7 +4,7 @@ Error: 2 | such that b = (defined(1) = defined(1)) | ^ Type error: - Expected: "Function or Sequence" + Expected: "function, sequence or permutation" Got: int defined-type-error.essence:2:37: @@ -12,6 +12,6 @@ defined-type-error.essence:2:37: 2 | such that b = (defined(1) = defined(1)) | ^ Type error: - Expected: "Function or Sequence" + Expected: "function, sequence or permutation" Got: int diff --git a/tests/custom/STARIS_2022/operation-type-errors/inverse-type-error/stderr.expected b/tests/custom/STARIS_2022/operation-type-errors/inverse-type-error/stderr.expected index c1fe5031d7..8a7c9eb006 100644 --- a/tests/custom/STARIS_2022/operation-type-errors/inverse-type-error/stderr.expected +++ b/tests/custom/STARIS_2022/operation-type-errors/inverse-type-error/stderr.expected @@ -1,9 +1,3 @@ Error: - inverse-type-error.essence:2:39: - | -2 | such that a = inverse(function(0-->1),function(false-->true)) - | ^^^^^^^^^^^^^^^^^^^^^^ -Type error: - Expected: function int --> int - Got: function bool --> bool - + In a 'such that' statement: a = inverse(function(0 --> 1), function(false --> true)) + Error: Type error in inverse(function(0 --> 1), function(false --> true)) diff --git a/tests/custom/STARIS_2022/operation-type-errors/range-type-error/stderr.expected b/tests/custom/STARIS_2022/operation-type-errors/range-type-error/stderr.expected index 9e0f2d251c..88664f9923 100644 --- a/tests/custom/STARIS_2022/operation-type-errors/range-type-error/stderr.expected +++ b/tests/custom/STARIS_2022/operation-type-errors/range-type-error/stderr.expected @@ -4,6 +4,6 @@ Error: 2 | such that s = range(5) | ^ Type error: - Expected: "Function or Sequence" + Expected: "function, sequence or permutation" Got: int diff --git a/tests/custom/permutations/18_transform_matrix/unnamed/0040_find_permutation_find_matrices/stdout.expected b/tests/custom/permutations/18_transform_matrix/unnamed/0040_find_permutation_find_matrices/stdout.expected index 43462dbf17..85aa7acb0b 100644 --- a/tests/custom/permutations/18_transform_matrix/unnamed/0040_find_permutation_find_matrices/stdout.expected +++ b/tests/custom/permutations/18_transform_matrix/unnamed/0040_find_permutation_find_matrices/stdout.expected @@ -2,6 +2,8 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output Savile Row: model000001.eprime +Running minion for domain filtering. +Running solver: minion Copying solution to: permutation.solution language Essence 1.3 From b68c5329defe9178b78a353e8e00d4e8b9d52ada Mon Sep 17 00:00:00 2001 From: Chris Jefferson Date: Sat, 16 Mar 2024 12:52:50 +0800 Subject: [PATCH 149/229] Disable very slow permutation tests for a while --- .../21_superpermutations/0010_size_3/run.sh | 7 +++--- .../0010_size_3/stdout.expected | 22 +------------------ .../21_superpermutations/0020_size_3/run.sh | 7 +++--- .../0020_size_3/stdout.expected | 11 +--------- 4 files changed, 10 insertions(+), 37 deletions(-) diff --git a/tests/custom/permutations/21_superpermutations/0010_size_3/run.sh b/tests/custom/permutations/21_superpermutations/0010_size_3/run.sh index 4194275f38..1c075d12ce 100755 --- a/tests/custom/permutations/21_superpermutations/0010_size_3/run.sh +++ b/tests/custom/permutations/21_superpermutations/0010_size_3/run.sh @@ -1,3 +1,4 @@ -conjure solve *.essence *.param -cat conjure-output/*.solution -rm -rf conjure-output *.solution +#conjure solve *.essence *.param +#cat conjure-output/*.solution +#rm -rf conjure-output *.solution +echo TODO: Speed up test \ No newline at end of file diff --git a/tests/custom/permutations/21_superpermutations/0010_size_3/stdout.expected b/tests/custom/permutations/21_superpermutations/0010_size_3/stdout.expected index 3d1ad910f5..0fa471805e 100644 --- a/tests/custom/permutations/21_superpermutations/0010_size_3/stdout.expected +++ b/tests/custom/permutations/21_superpermutations/0010_size_3/stdout.expected @@ -1,21 +1 @@ -Generating models for permutation.essence -Generated models: model000001.eprime -Saved under: conjure-output -Savile Row: model000001.eprime permutation.param -Running minion for domain filtering. -Running solver: minion -Copying solution to: permutation-permutation.solution -language Essence 1.3 - -letting qs be - {sequence(1, 1, 1), sequence(1, 1, 2), sequence(1, 1, 3), sequence(1, 2, 3), sequence(1, 3, 1), - sequence(3, 1, 1)} -$ Visualisation for qs -$ 1 1 1 -$ 1 1 2 -$ 1 1 3 -$ 1 2 3 -$ 1 3 1 -$ 3 1 1 - -letting superperm be sequence(1, 1, 1, 3, 1, 1, 2, 3) +TODO: Speed up test diff --git a/tests/custom/permutations/21_superpermutations/0020_size_3/run.sh b/tests/custom/permutations/21_superpermutations/0020_size_3/run.sh index 4194275f38..1c075d12ce 100755 --- a/tests/custom/permutations/21_superpermutations/0020_size_3/run.sh +++ b/tests/custom/permutations/21_superpermutations/0020_size_3/run.sh @@ -1,3 +1,4 @@ -conjure solve *.essence *.param -cat conjure-output/*.solution -rm -rf conjure-output *.solution +#conjure solve *.essence *.param +#cat conjure-output/*.solution +#rm -rf conjure-output *.solution +echo TODO: Speed up test \ No newline at end of file diff --git a/tests/custom/permutations/21_superpermutations/0020_size_3/stdout.expected b/tests/custom/permutations/21_superpermutations/0020_size_3/stdout.expected index 78e7a506c7..0fa471805e 100644 --- a/tests/custom/permutations/21_superpermutations/0020_size_3/stdout.expected +++ b/tests/custom/permutations/21_superpermutations/0020_size_3/stdout.expected @@ -1,10 +1 @@ -Generating models for permutation.essence -Generated models: model000001.eprime -Saved under: conjure-output -Savile Row: model000001.eprime permutation.param -Running minion for domain filtering. -Running solver: minion -Copying solution to: permutation-permutation.solution -language Essence 1.3 - -letting superperm be sequence(1, 2, 3, 1, 2, 1, 3, 2, 1) +TODO: Speed up test From a034e9dc4836d85f3b849a90bb59630b89329ffc Mon Sep 17 00:00:00 2001 From: Chris Jefferson Date: Sat, 16 Mar 2024 13:40:00 +0800 Subject: [PATCH 150/229] Add rule for permutation disequality --- src/Conjure/Rules/Horizontal/Permutation.hs | 10 ++++++++++ src/Conjure/UI/Model.hs | 1 + 2 files changed, 11 insertions(+) diff --git a/src/Conjure/Rules/Horizontal/Permutation.hs b/src/Conjure/Rules/Horizontal/Permutation.hs index d35ee208dd..e0d89ce926 100644 --- a/src/Conjure/Rules/Horizontal/Permutation.hs +++ b/src/Conjure/Rules/Horizontal/Permutation.hs @@ -41,6 +41,16 @@ rule_Equality = "permutation-equality" `namedRule` theRule where , return [essence| toSet(&p) = toSet(&q) |] ) +rule_Disequality :: Rule +rule_Disequality = "permutation-disequality" `namedRule` theRule where + theRule e = do + (p,q) <- match opNeq e + TypePermutation{} <- typeOf p + TypePermutation{} <- typeOf q + return ( "Horizontal rule for permutation disequality" + , return [essence| toSet(&p) != toSet(&q) |] + ) + rule_Comprehension :: Rule rule_Comprehension = "permutation-comprehension" `namedRule` theRule where diff --git a/src/Conjure/UI/Model.hs b/src/Conjure/UI/Model.hs index 395fe0321e..57e7f4d465 100644 --- a/src/Conjure/UI/Model.hs +++ b/src/Conjure/UI/Model.hs @@ -1537,6 +1537,7 @@ horizontalRules :: [Rule] horizontalRules = [ Horizontal.Permutation.rule_Cardinality_Literal , Horizontal.Permutation.rule_Equality + , Horizontal.Permutation.rule_Disequality , Horizontal.Permutation.rule_Comprehension , Horizontal.Permutation.rule_Compose_Image From 8d5d53a043525ebf16cc996bdaea294ec03fc718 Mon Sep 17 00:00:00 2001 From: Chris Jefferson Date: Sat, 16 Mar 2024 15:41:41 +0800 Subject: [PATCH 151/229] Make test stable --- .../run.sh | 2 +- .../stdout.expected | 55 ++++ .../run.sh | 6 +- .../stdout.expected | 254 +++++++++++++----- 4 files changed, 253 insertions(+), 64 deletions(-) diff --git a/tests/custom/permutations/16_transform_permutation/int/0020_given_permutation_find_permutations/run.sh b/tests/custom/permutations/16_transform_permutation/int/0020_given_permutation_find_permutations/run.sh index aab5d44c6e..d555f9da56 100755 --- a/tests/custom/permutations/16_transform_permutation/int/0020_given_permutation_find_permutations/run.sh +++ b/tests/custom/permutations/16_transform_permutation/int/0020_given_permutation_find_permutations/run.sh @@ -1,3 +1,3 @@ -conjure solve *.essence *.param --number-of-solutions=10 +conjure solve *.essence *.param --number-of-solutions=all cat conjure-output/*.solution rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/16_transform_permutation/int/0020_given_permutation_find_permutations/stdout.expected b/tests/custom/permutations/16_transform_permutation/int/0020_given_permutation_find_permutations/stdout.expected index c447fefe90..948e9688f8 100644 --- a/tests/custom/permutations/16_transform_permutation/int/0020_given_permutation_find_permutations/stdout.expected +++ b/tests/custom/permutations/16_transform_permutation/int/0020_given_permutation_find_permutations/stdout.expected @@ -14,6 +14,17 @@ Copying solution to: permutation-permutation-000007.solution Copying solution to: permutation-permutation-000008.solution Copying solution to: permutation-permutation-000009.solution Copying solution to: permutation-permutation-000010.solution +Copying solution to: permutation-permutation-000011.solution +Copying solution to: permutation-permutation-000012.solution +Copying solution to: permutation-permutation-000013.solution +Copying solution to: permutation-permutation-000014.solution +Copying solution to: permutation-permutation-000015.solution +Copying solution to: permutation-permutation-000016.solution +Copying solution to: permutation-permutation-000017.solution +Copying solution to: permutation-permutation-000018.solution +Copying solution to: permutation-permutation-000019.solution +Copying solution to: permutation-permutation-000020.solution +Copying solution to: permutation-permutation-000021.solution language Essence 1.3 letting s be permutation((3, 4)) @@ -54,3 +65,47 @@ language Essence 1.3 letting s be permutation((1, 2, 4, 3)) letting sn be permutation((1, 4, 3, 2)) +language Essence 1.3 + +letting s be permutation((1, 2, 4)) +letting sn be permutation((1, 3, 2)) +language Essence 1.3 + +letting s be permutation((1, 3, 2)) +letting sn be permutation((2, 3, 4)) +language Essence 1.3 + +letting s be permutation((1, 3, 4, 2)) +letting sn be permutation((1, 2, 3, 4)) +language Essence 1.3 + +letting s be permutation((1, 3)) +letting sn be permutation((3, 4)) +language Essence 1.3 + +letting s be permutation((1, 3), (2, 4)) +letting sn be permutation((1, 2), (3, 4)) +language Essence 1.3 + +letting s be permutation((1, 3, 2, 4)) +letting sn be permutation((1, 3, 4, 2)) +language Essence 1.3 + +letting s be permutation((1, 4, 3, 2)) +letting sn be permutation((1, 4, 2, 3)) +language Essence 1.3 + +letting s be permutation((1, 4, 2)) +letting sn be permutation((1, 2, 3)) +language Essence 1.3 + +letting s be permutation((1, 4)) +letting sn be permutation((1, 3)) +language Essence 1.3 + +letting s be permutation((1, 4, 2, 3)) +letting sn be permutation((1, 2, 4, 3)) +language Essence 1.3 + +letting s be permutation((1, 4), (2, 3)) +letting sn be permutation((1, 3), (2, 4)) diff --git a/tests/custom/permutations/16_transform_permutation/int/0040_find_permutation_find_permutations/run.sh b/tests/custom/permutations/16_transform_permutation/int/0040_find_permutation_find_permutations/run.sh index 03373df6cb..e77b06dda6 100755 --- a/tests/custom/permutations/16_transform_permutation/int/0040_find_permutation_find_permutations/run.sh +++ b/tests/custom/permutations/16_transform_permutation/int/0040_find_permutation_find_permutations/run.sh @@ -1,3 +1,3 @@ -conjure solve *.essence --number-of-solutions=10 -cat conjure-output/*.solution -rm -rf conjure-output *.solution +conjure solve --number-of-solutions=all --solutions-in-one-file --output-format=jsonstream *.essence +cat *.json | LC_ALL=C sort +rm -rf conjure-output *solutions* diff --git a/tests/custom/permutations/16_transform_permutation/int/0040_find_permutation_find_permutations/stdout.expected b/tests/custom/permutations/16_transform_permutation/int/0040_find_permutation_find_permutations/stdout.expected index 615c9a835f..d5fea9ade6 100644 --- a/tests/custom/permutations/16_transform_permutation/int/0040_find_permutation_find_permutations/stdout.expected +++ b/tests/custom/permutations/16_transform_permutation/int/0040_find_permutation_find_permutations/stdout.expected @@ -4,63 +4,197 @@ Saved under: conjure-output Savile Row: model000001.eprime Running minion for domain filtering. Running solver: minion -Copying solution to: permutation-000001.solution -Copying solution to: permutation-000002.solution -Copying solution to: permutation-000003.solution -Copying solution to: permutation-000004.solution -Copying solution to: permutation-000005.solution -Copying solution to: permutation-000006.solution -Copying solution to: permutation-000007.solution -Copying solution to: permutation-000008.solution -Copying solution to: permutation-000009.solution -Copying solution to: permutation-000010.solution -language Essence 1.3 - -letting p be permutation((2, 3, 4)) -letting s be permutation() -letting sn be permutation() -language Essence 1.3 - -letting p be permutation((2, 3, 4)) -letting s be permutation((3, 4)) -letting sn be permutation((2, 4)) -language Essence 1.3 - -letting p be permutation((2, 3, 4)) -letting s be permutation((2, 3)) -letting sn be permutation((3, 4)) -language Essence 1.3 - -letting p be permutation((2, 3, 4)) -letting s be permutation((2, 3, 4)) -letting sn be permutation((2, 3, 4)) -language Essence 1.3 - -letting p be permutation((2, 3, 4)) -letting s be permutation((2, 4, 3)) -letting sn be permutation((2, 4, 3)) -language Essence 1.3 - -letting p be permutation((2, 3, 4)) -letting s be permutation((2, 4)) -letting sn be permutation((2, 3)) -language Essence 1.3 - -letting p be permutation((2, 3, 4)) -letting s be permutation((1, 2)) -letting sn be permutation((1, 3)) -language Essence 1.3 - -letting p be permutation((2, 3, 4)) -letting s be permutation((1, 2), (3, 4)) -letting sn be permutation((1, 3), (2, 4)) -language Essence 1.3 - -letting p be permutation((2, 3, 4)) -letting s be permutation((1, 2, 3)) -letting sn be permutation((1, 3, 4)) -language Essence 1.3 - -letting p be permutation((2, 3, 4)) -letting s be permutation((1, 2, 3, 4)) -letting sn be permutation((1, 3, 4, 2)) +Copying solution to: permutation.solutions +Copying solution to: permutation.solutions.json +{"p": [[1, 2, 3]], "s": [[1, 2, 3, 4]], "sn": [[1, 4, 2, 3]]} +{"p": [[1, 2, 3]], "s": [[1, 2, 3]], "sn": [[1, 2, 3]]} +{"p": [[1, 2, 3]], "s": [[1, 2, 4, 3]], "sn": [[1, 2, 3, 4]]} +{"p": [[1, 2, 3]], "s": [[1, 2, 4]], "sn": [[2, 3, 4]]} +{"p": [[1, 2, 3]], "s": [[1, 2], [3, 4]], "sn": [[1, 4], [2, 3]]} +{"p": [[1, 2, 3]], "s": [[1, 2]], "sn": [[2, 3]]} +{"p": [[1, 2, 3]], "s": [[1, 3, 2, 4]], "sn": [[1, 3, 4, 2]]} +{"p": [[1, 2, 3]], "s": [[1, 3, 2]], "sn": [[1, 3, 2]]} +{"p": [[1, 2, 3]], "s": [[1, 3, 4, 2]], "sn": [[1, 4, 3, 2]]} +{"p": [[1, 2, 3]], "s": [[1, 3, 4]], "sn": [[1, 4, 2]]} +{"p": [[1, 2, 3]], "s": [[1, 3], [2, 4]], "sn": [[1, 2], [3, 4]]} +{"p": [[1, 2, 3]], "s": [[1, 3]], "sn": [[1, 2]]} +{"p": [[1, 2, 3]], "s": [[1, 4, 2, 3]], "sn": [[1, 2, 4, 3]]} +{"p": [[1, 2, 3]], "s": [[1, 4, 2]], "sn": [[2, 4, 3]]} +{"p": [[1, 2, 3]], "s": [[1, 4, 3, 2]], "sn": [[1, 3, 2, 4]]} +{"p": [[1, 2, 3]], "s": [[1, 4, 3]], "sn": [[1, 2, 4]]} +{"p": [[1, 2, 3]], "s": [[1, 4], [2, 3]], "sn": [[1, 3], [2, 4]]} +{"p": [[1, 2, 3]], "s": [[1, 4]], "sn": [[2, 4]]} +{"p": [[1, 2, 3]], "s": [[2, 3, 4]], "sn": [[1, 4, 3]]} +{"p": [[1, 2, 3]], "s": [[2, 3]], "sn": [[1, 3]]} +{"p": [[1, 2, 3]], "s": [[2, 4, 3]], "sn": [[1, 3, 4]]} +{"p": [[1, 2, 3]], "s": [[2, 4]], "sn": [[3, 4]]} +{"p": [[1, 2, 3]], "s": [[3, 4]], "sn": [[1, 4]]} +{"p": [[1, 2, 3]], "s": [], "sn": []} +{"p": [[1, 2, 4]], "s": [[1, 2, 3, 4]], "sn": [[1, 2, 4, 3]]} +{"p": [[1, 2, 4]], "s": [[1, 2, 3]], "sn": [[2, 4, 3]]} +{"p": [[1, 2, 4]], "s": [[1, 2, 4, 3]], "sn": [[1, 3, 2, 4]]} +{"p": [[1, 2, 4]], "s": [[1, 2, 4]], "sn": [[1, 2, 4]]} +{"p": [[1, 2, 4]], "s": [[1, 2], [3, 4]], "sn": [[1, 3], [2, 4]]} +{"p": [[1, 2, 4]], "s": [[1, 2]], "sn": [[2, 4]]} +{"p": [[1, 2, 4]], "s": [[1, 3, 2, 4]], "sn": [[1, 2, 3, 4]]} +{"p": [[1, 2, 4]], "s": [[1, 3, 2]], "sn": [[2, 3, 4]]} +{"p": [[1, 2, 4]], "s": [[1, 3, 4, 2]], "sn": [[1, 4, 2, 3]]} +{"p": [[1, 2, 4]], "s": [[1, 3, 4]], "sn": [[1, 2, 3]]} +{"p": [[1, 2, 4]], "s": [[1, 3], [2, 4]], "sn": [[1, 4], [2, 3]]} +{"p": [[1, 2, 4]], "s": [[1, 3]], "sn": [[2, 3]]} +{"p": [[1, 2, 4]], "s": [[1, 4, 2, 3]], "sn": [[1, 4, 3, 2]]} +{"p": [[1, 2, 4]], "s": [[1, 4, 2]], "sn": [[1, 4, 2]]} +{"p": [[1, 2, 4]], "s": [[1, 4, 3, 2]], "sn": [[1, 3, 4, 2]]} +{"p": [[1, 2, 4]], "s": [[1, 4, 3]], "sn": [[1, 3, 2]]} +{"p": [[1, 2, 4]], "s": [[1, 4], [2, 3]], "sn": [[1, 2], [3, 4]]} +{"p": [[1, 2, 4]], "s": [[1, 4]], "sn": [[1, 2]]} +{"p": [[1, 2, 4]], "s": [[2, 3, 4]], "sn": [[1, 4, 3]]} +{"p": [[1, 2, 4]], "s": [[2, 3]], "sn": [[3, 4]]} +{"p": [[1, 2, 4]], "s": [[2, 4, 3]], "sn": [[1, 3, 4]]} +{"p": [[1, 2, 4]], "s": [[2, 4]], "sn": [[1, 4]]} +{"p": [[1, 2, 4]], "s": [[3, 4]], "sn": [[1, 3]]} +{"p": [[1, 2, 4]], "s": [], "sn": []} +{"p": [[1, 3, 2]], "s": [[1, 2, 3, 4]], "sn": [[1, 2, 4, 3]]} +{"p": [[1, 3, 2]], "s": [[1, 2, 3]], "sn": [[1, 2, 3]]} +{"p": [[1, 3, 2]], "s": [[1, 2, 4, 3]], "sn": [[1, 4, 2, 3]]} +{"p": [[1, 3, 2]], "s": [[1, 2, 4]], "sn": [[1, 4, 3]]} +{"p": [[1, 3, 2]], "s": [[1, 2], [3, 4]], "sn": [[1, 3], [2, 4]]} +{"p": [[1, 3, 2]], "s": [[1, 2]], "sn": [[1, 3]]} +{"p": [[1, 3, 2]], "s": [[1, 3, 2, 4]], "sn": [[1, 4, 3, 2]]} +{"p": [[1, 3, 2]], "s": [[1, 3, 2]], "sn": [[1, 3, 2]]} +{"p": [[1, 3, 2]], "s": [[1, 3, 4, 2]], "sn": [[1, 3, 2, 4]]} +{"p": [[1, 3, 2]], "s": [[1, 3, 4]], "sn": [[2, 4, 3]]} +{"p": [[1, 3, 2]], "s": [[1, 3], [2, 4]], "sn": [[1, 4], [2, 3]]} +{"p": [[1, 3, 2]], "s": [[1, 3]], "sn": [[2, 3]]} +{"p": [[1, 3, 2]], "s": [[1, 4, 2, 3]], "sn": [[1, 2, 3, 4]]} +{"p": [[1, 3, 2]], "s": [[1, 4, 2]], "sn": [[1, 3, 4]]} +{"p": [[1, 3, 2]], "s": [[1, 4, 3, 2]], "sn": [[1, 3, 4, 2]]} +{"p": [[1, 3, 2]], "s": [[1, 4, 3]], "sn": [[2, 3, 4]]} +{"p": [[1, 3, 2]], "s": [[1, 4], [2, 3]], "sn": [[1, 2], [3, 4]]} +{"p": [[1, 3, 2]], "s": [[1, 4]], "sn": [[3, 4]]} +{"p": [[1, 3, 2]], "s": [[2, 3, 4]], "sn": [[1, 2, 4]]} +{"p": [[1, 3, 2]], "s": [[2, 3]], "sn": [[1, 2]]} +{"p": [[1, 3, 2]], "s": [[2, 4, 3]], "sn": [[1, 4, 2]]} +{"p": [[1, 3, 2]], "s": [[2, 4]], "sn": [[1, 4]]} +{"p": [[1, 3, 2]], "s": [[3, 4]], "sn": [[2, 4]]} +{"p": [[1, 3, 2]], "s": [], "sn": []} +{"p": [[1, 3, 4]], "s": [[1, 2, 3, 4]], "sn": [[1, 3, 2, 4]]} +{"p": [[1, 3, 4]], "s": [[1, 2, 3]], "sn": [[2, 4, 3]]} +{"p": [[1, 3, 4]], "s": [[1, 2, 4, 3]], "sn": [[1, 4, 3, 2]]} +{"p": [[1, 3, 4]], "s": [[1, 2, 4]], "sn": [[1, 3, 2]]} +{"p": [[1, 3, 4]], "s": [[1, 2], [3, 4]], "sn": [[1, 4], [2, 3]]} +{"p": [[1, 3, 4]], "s": [[1, 2]], "sn": [[2, 3]]} +{"p": [[1, 3, 4]], "s": [[1, 3, 2, 4]], "sn": [[1, 3, 4, 2]]} +{"p": [[1, 3, 4]], "s": [[1, 3, 2]], "sn": [[2, 3, 4]]} +{"p": [[1, 3, 4]], "s": [[1, 3, 4, 2]], "sn": [[1, 2, 3, 4]]} +{"p": [[1, 3, 4]], "s": [[1, 3, 4]], "sn": [[1, 3, 4]]} +{"p": [[1, 3, 4]], "s": [[1, 3], [2, 4]], "sn": [[1, 2], [3, 4]]} +{"p": [[1, 3, 4]], "s": [[1, 3]], "sn": [[3, 4]]} +{"p": [[1, 3, 4]], "s": [[1, 4, 2, 3]], "sn": [[1, 2, 4, 3]]} +{"p": [[1, 3, 4]], "s": [[1, 4, 2]], "sn": [[1, 2, 3]]} +{"p": [[1, 3, 4]], "s": [[1, 4, 3, 2]], "sn": [[1, 4, 2, 3]]} +{"p": [[1, 3, 4]], "s": [[1, 4, 3]], "sn": [[1, 4, 3]]} +{"p": [[1, 3, 4]], "s": [[1, 4], [2, 3]], "sn": [[1, 3], [2, 4]]} +{"p": [[1, 3, 4]], "s": [[1, 4]], "sn": [[1, 3]]} +{"p": [[1, 3, 4]], "s": [[2, 3, 4]], "sn": [[1, 2, 4]]} +{"p": [[1, 3, 4]], "s": [[2, 3]], "sn": [[2, 4]]} +{"p": [[1, 3, 4]], "s": [[2, 4, 3]], "sn": [[1, 4, 2]]} +{"p": [[1, 3, 4]], "s": [[2, 4]], "sn": [[1, 2]]} +{"p": [[1, 3, 4]], "s": [[3, 4]], "sn": [[1, 4]]} +{"p": [[1, 3, 4]], "s": [], "sn": []} +{"p": [[1, 4, 2]], "s": [[1, 2, 3, 4]], "sn": [[1, 3, 2, 4]]} +{"p": [[1, 4, 2]], "s": [[1, 2, 3]], "sn": [[1, 3, 4]]} +{"p": [[1, 4, 2]], "s": [[1, 2, 4, 3]], "sn": [[1, 2, 3, 4]]} +{"p": [[1, 4, 2]], "s": [[1, 2, 4]], "sn": [[1, 2, 4]]} +{"p": [[1, 4, 2]], "s": [[1, 2], [3, 4]], "sn": [[1, 4], [2, 3]]} +{"p": [[1, 4, 2]], "s": [[1, 2]], "sn": [[1, 4]]} +{"p": [[1, 4, 2]], "s": [[1, 3, 2, 4]], "sn": [[1, 2, 4, 3]]} +{"p": [[1, 4, 2]], "s": [[1, 3, 2]], "sn": [[1, 4, 3]]} +{"p": [[1, 4, 2]], "s": [[1, 3, 4, 2]], "sn": [[1, 4, 3, 2]]} +{"p": [[1, 4, 2]], "s": [[1, 3, 4]], "sn": [[2, 4, 3]]} +{"p": [[1, 4, 2]], "s": [[1, 3], [2, 4]], "sn": [[1, 2], [3, 4]]} +{"p": [[1, 4, 2]], "s": [[1, 3]], "sn": [[3, 4]]} +{"p": [[1, 4, 2]], "s": [[1, 4, 2, 3]], "sn": [[1, 3, 4, 2]]} +{"p": [[1, 4, 2]], "s": [[1, 4, 2]], "sn": [[1, 4, 2]]} +{"p": [[1, 4, 2]], "s": [[1, 4, 3, 2]], "sn": [[1, 4, 2, 3]]} +{"p": [[1, 4, 2]], "s": [[1, 4, 3]], "sn": [[2, 3, 4]]} +{"p": [[1, 4, 2]], "s": [[1, 4], [2, 3]], "sn": [[1, 3], [2, 4]]} +{"p": [[1, 4, 2]], "s": [[1, 4]], "sn": [[2, 4]]} +{"p": [[1, 4, 2]], "s": [[2, 3, 4]], "sn": [[1, 3, 2]]} +{"p": [[1, 4, 2]], "s": [[2, 3]], "sn": [[1, 3]]} +{"p": [[1, 4, 2]], "s": [[2, 4, 3]], "sn": [[1, 2, 3]]} +{"p": [[1, 4, 2]], "s": [[2, 4]], "sn": [[1, 2]]} +{"p": [[1, 4, 2]], "s": [[3, 4]], "sn": [[2, 3]]} +{"p": [[1, 4, 2]], "s": [], "sn": []} +{"p": [[1, 4, 3]], "s": [[1, 2, 3, 4]], "sn": [[1, 3, 4, 2]]} +{"p": [[1, 4, 3]], "s": [[1, 2, 3]], "sn": [[1, 4, 2]]} +{"p": [[1, 4, 3]], "s": [[1, 2, 4, 3]], "sn": [[1, 4, 2, 3]]} +{"p": [[1, 4, 3]], "s": [[1, 2, 4]], "sn": [[2, 3, 4]]} +{"p": [[1, 4, 3]], "s": [[1, 2], [3, 4]], "sn": [[1, 3], [2, 4]]} +{"p": [[1, 4, 3]], "s": [[1, 2]], "sn": [[2, 4]]} +{"p": [[1, 4, 3]], "s": [[1, 3, 2, 4]], "sn": [[1, 2, 3, 4]]} +{"p": [[1, 4, 3]], "s": [[1, 3, 2]], "sn": [[1, 2, 4]]} +{"p": [[1, 4, 3]], "s": [[1, 3, 4, 2]], "sn": [[1, 3, 2, 4]]} +{"p": [[1, 4, 3]], "s": [[1, 3, 4]], "sn": [[1, 3, 4]]} +{"p": [[1, 4, 3]], "s": [[1, 3], [2, 4]], "sn": [[1, 4], [2, 3]]} +{"p": [[1, 4, 3]], "s": [[1, 3]], "sn": [[1, 4]]} +{"p": [[1, 4, 3]], "s": [[1, 4, 2, 3]], "sn": [[1, 4, 3, 2]]} +{"p": [[1, 4, 3]], "s": [[1, 4, 2]], "sn": [[2, 4, 3]]} +{"p": [[1, 4, 3]], "s": [[1, 4, 3, 2]], "sn": [[1, 2, 4, 3]]} +{"p": [[1, 4, 3]], "s": [[1, 4, 3]], "sn": [[1, 4, 3]]} +{"p": [[1, 4, 3]], "s": [[1, 4], [2, 3]], "sn": [[1, 2], [3, 4]]} +{"p": [[1, 4, 3]], "s": [[1, 4]], "sn": [[3, 4]]} +{"p": [[1, 4, 3]], "s": [[2, 3, 4]], "sn": [[1, 3, 2]]} +{"p": [[1, 4, 3]], "s": [[2, 3]], "sn": [[1, 2]]} +{"p": [[1, 4, 3]], "s": [[2, 4, 3]], "sn": [[1, 2, 3]]} +{"p": [[1, 4, 3]], "s": [[2, 4]], "sn": [[2, 3]]} +{"p": [[1, 4, 3]], "s": [[3, 4]], "sn": [[1, 3]]} +{"p": [[1, 4, 3]], "s": [], "sn": []} +{"p": [[2, 3, 4]], "s": [[1, 2, 3, 4]], "sn": [[1, 3, 4, 2]]} +{"p": [[2, 3, 4]], "s": [[1, 2, 3]], "sn": [[1, 3, 4]]} +{"p": [[2, 3, 4]], "s": [[1, 2, 4, 3]], "sn": [[1, 3, 2, 4]]} +{"p": [[2, 3, 4]], "s": [[1, 2, 4]], "sn": [[1, 3, 2]]} +{"p": [[2, 3, 4]], "s": [[1, 2], [3, 4]], "sn": [[1, 3], [2, 4]]} +{"p": [[2, 3, 4]], "s": [[1, 2]], "sn": [[1, 3]]} +{"p": [[2, 3, 4]], "s": [[1, 3, 2, 4]], "sn": [[1, 4, 3, 2]]} +{"p": [[2, 3, 4]], "s": [[1, 3, 2]], "sn": [[1, 4, 3]]} +{"p": [[2, 3, 4]], "s": [[1, 3, 4, 2]], "sn": [[1, 4, 2, 3]]} +{"p": [[2, 3, 4]], "s": [[1, 3, 4]], "sn": [[1, 4, 2]]} +{"p": [[2, 3, 4]], "s": [[1, 3], [2, 4]], "sn": [[1, 4], [2, 3]]} +{"p": [[2, 3, 4]], "s": [[1, 3]], "sn": [[1, 4]]} +{"p": [[2, 3, 4]], "s": [[1, 4, 2, 3]], "sn": [[1, 2, 3, 4]]} +{"p": [[2, 3, 4]], "s": [[1, 4, 2]], "sn": [[1, 2, 3]]} +{"p": [[2, 3, 4]], "s": [[1, 4, 3, 2]], "sn": [[1, 2, 4, 3]]} +{"p": [[2, 3, 4]], "s": [[1, 4, 3]], "sn": [[1, 2, 4]]} +{"p": [[2, 3, 4]], "s": [[1, 4], [2, 3]], "sn": [[1, 2], [3, 4]]} +{"p": [[2, 3, 4]], "s": [[1, 4]], "sn": [[1, 2]]} +{"p": [[2, 3, 4]], "s": [[2, 3, 4]], "sn": [[2, 3, 4]]} +{"p": [[2, 3, 4]], "s": [[2, 3]], "sn": [[3, 4]]} +{"p": [[2, 3, 4]], "s": [[2, 4, 3]], "sn": [[2, 4, 3]]} +{"p": [[2, 3, 4]], "s": [[2, 4]], "sn": [[2, 3]]} +{"p": [[2, 3, 4]], "s": [[3, 4]], "sn": [[2, 4]]} +{"p": [[2, 3, 4]], "s": [], "sn": []} +{"p": [[2, 4, 3]], "s": [[1, 2, 3, 4]], "sn": [[1, 4, 2, 3]]} +{"p": [[2, 4, 3]], "s": [[1, 2, 3]], "sn": [[1, 4, 2]]} +{"p": [[2, 4, 3]], "s": [[1, 2, 4, 3]], "sn": [[1, 4, 3, 2]]} +{"p": [[2, 4, 3]], "s": [[1, 2, 4]], "sn": [[1, 4, 3]]} +{"p": [[2, 4, 3]], "s": [[1, 2], [3, 4]], "sn": [[1, 4], [2, 3]]} +{"p": [[2, 4, 3]], "s": [[1, 2]], "sn": [[1, 4]]} +{"p": [[2, 4, 3]], "s": [[1, 3, 2, 4]], "sn": [[1, 2, 4, 3]]} +{"p": [[2, 4, 3]], "s": [[1, 3, 2]], "sn": [[1, 2, 4]]} +{"p": [[2, 4, 3]], "s": [[1, 3, 4, 2]], "sn": [[1, 2, 3, 4]]} +{"p": [[2, 4, 3]], "s": [[1, 3, 4]], "sn": [[1, 2, 3]]} +{"p": [[2, 4, 3]], "s": [[1, 3], [2, 4]], "sn": [[1, 2], [3, 4]]} +{"p": [[2, 4, 3]], "s": [[1, 3]], "sn": [[1, 2]]} +{"p": [[2, 4, 3]], "s": [[1, 4, 2, 3]], "sn": [[1, 3, 4, 2]]} +{"p": [[2, 4, 3]], "s": [[1, 4, 2]], "sn": [[1, 3, 4]]} +{"p": [[2, 4, 3]], "s": [[1, 4, 3, 2]], "sn": [[1, 3, 2, 4]]} +{"p": [[2, 4, 3]], "s": [[1, 4, 3]], "sn": [[1, 3, 2]]} +{"p": [[2, 4, 3]], "s": [[1, 4], [2, 3]], "sn": [[1, 3], [2, 4]]} +{"p": [[2, 4, 3]], "s": [[1, 4]], "sn": [[1, 3]]} +{"p": [[2, 4, 3]], "s": [[2, 3, 4]], "sn": [[2, 3, 4]]} +{"p": [[2, 4, 3]], "s": [[2, 3]], "sn": [[2, 4]]} +{"p": [[2, 4, 3]], "s": [[2, 4, 3]], "sn": [[2, 4, 3]]} +{"p": [[2, 4, 3]], "s": [[2, 4]], "sn": [[3, 4]]} +{"p": [[2, 4, 3]], "s": [[3, 4]], "sn": [[2, 3]]} +{"p": [[2, 4, 3]], "s": [], "sn": []} From 62a3adf79de29da40eedd66c56e073fb41a24b3c Mon Sep 17 00:00:00 2001 From: Chris Jefferson Date: Tue, 19 Mar 2024 18:35:31 +0800 Subject: [PATCH 152/229] Fix broken test --- .../permutation.essence | 4 +- .../run.sh | 6 +- .../stdout.expected | 106 +++++++++++++++++- 3 files changed, 105 insertions(+), 11 deletions(-) diff --git a/tests/custom/permutations/18_transform_matrix/enum/0040_find_permutation_find_matrices/permutation.essence b/tests/custom/permutations/18_transform_matrix/enum/0040_find_permutation_find_matrices/permutation.essence index 2806ade22a..4b57afdd48 100644 --- a/tests/custom/permutations/18_transform_matrix/enum/0040_find_permutation_find_matrices/permutation.essence +++ b/tests/custom/permutations/18_transform_matrix/enum/0040_find_permutation_find_matrices/permutation.essence @@ -1,8 +1,8 @@ letting n be new type enum {e_5,e_6,e_7,e_8} find p : permutation (size 3) of n -find s : matrix indexed by [int(1..4)] of n -find t : matrix indexed by [int(1..4)] of n +find s : matrix indexed by [int(1..2)] of n +find t : matrix indexed by [int(1..2)] of n such that t = transform(p,s) /\ allDiff(s) diff --git a/tests/custom/permutations/18_transform_matrix/enum/0040_find_permutation_find_matrices/run.sh b/tests/custom/permutations/18_transform_matrix/enum/0040_find_permutation_find_matrices/run.sh index a1691af90c..10ed17da89 100755 --- a/tests/custom/permutations/18_transform_matrix/enum/0040_find_permutation_find_matrices/run.sh +++ b/tests/custom/permutations/18_transform_matrix/enum/0040_find_permutation_find_matrices/run.sh @@ -1,3 +1,3 @@ -conjure solve *.essence -cat conjure-output/*.solution -rm -rf conjure-output *.solution +conjure solve --number-of-solutions=all --solutions-in-one-file --output-format=jsonstream *.essence +cat *.json | LC_ALL=C sort +rm -rf conjure-output *solutions* \ No newline at end of file diff --git a/tests/custom/permutations/18_transform_matrix/enum/0040_find_permutation_find_matrices/stdout.expected b/tests/custom/permutations/18_transform_matrix/enum/0040_find_permutation_find_matrices/stdout.expected index e5c8cc1bb7..2342f944c1 100644 --- a/tests/custom/permutations/18_transform_matrix/enum/0040_find_permutation_find_matrices/stdout.expected +++ b/tests/custom/permutations/18_transform_matrix/enum/0040_find_permutation_find_matrices/stdout.expected @@ -2,9 +2,103 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output Savile Row: model000001.eprime -Copying solution to: permutation.solution -language Essence 1.3 - -letting p be permutation((e_6, e_7, e_8)) -letting s be [e_5, e_6, e_7, e_8; int(1..4)] -letting t be [e_5, e_7, e_8, e_6; int(1..4)] +Running minion for domain filtering. +Running solver: minion +Copying solution to: permutation.solutions +Copying solution to: permutation.solutions.json +{"p": [["e_5", "e_6", "e_7"]], "s": {"1": "e_5", "2": "e_6"}, "t": {"1": "e_6", "2": "e_7"}} +{"p": [["e_5", "e_6", "e_7"]], "s": {"1": "e_5", "2": "e_7"}, "t": {"1": "e_6", "2": "e_5"}} +{"p": [["e_5", "e_6", "e_7"]], "s": {"1": "e_5", "2": "e_8"}, "t": {"1": "e_6", "2": "e_8"}} +{"p": [["e_5", "e_6", "e_7"]], "s": {"1": "e_6", "2": "e_5"}, "t": {"1": "e_7", "2": "e_6"}} +{"p": [["e_5", "e_6", "e_7"]], "s": {"1": "e_6", "2": "e_7"}, "t": {"1": "e_7", "2": "e_5"}} +{"p": [["e_5", "e_6", "e_7"]], "s": {"1": "e_6", "2": "e_8"}, "t": {"1": "e_7", "2": "e_8"}} +{"p": [["e_5", "e_6", "e_7"]], "s": {"1": "e_7", "2": "e_5"}, "t": {"1": "e_5", "2": "e_6"}} +{"p": [["e_5", "e_6", "e_7"]], "s": {"1": "e_7", "2": "e_6"}, "t": {"1": "e_5", "2": "e_7"}} +{"p": [["e_5", "e_6", "e_7"]], "s": {"1": "e_7", "2": "e_8"}, "t": {"1": "e_5", "2": "e_8"}} +{"p": [["e_5", "e_6", "e_7"]], "s": {"1": "e_8", "2": "e_5"}, "t": {"1": "e_8", "2": "e_6"}} +{"p": [["e_5", "e_6", "e_7"]], "s": {"1": "e_8", "2": "e_6"}, "t": {"1": "e_8", "2": "e_7"}} +{"p": [["e_5", "e_6", "e_7"]], "s": {"1": "e_8", "2": "e_7"}, "t": {"1": "e_8", "2": "e_5"}} +{"p": [["e_5", "e_6", "e_8"]], "s": {"1": "e_5", "2": "e_6"}, "t": {"1": "e_6", "2": "e_8"}} +{"p": [["e_5", "e_6", "e_8"]], "s": {"1": "e_5", "2": "e_7"}, "t": {"1": "e_6", "2": "e_7"}} +{"p": [["e_5", "e_6", "e_8"]], "s": {"1": "e_5", "2": "e_8"}, "t": {"1": "e_6", "2": "e_5"}} +{"p": [["e_5", "e_6", "e_8"]], "s": {"1": "e_6", "2": "e_5"}, "t": {"1": "e_8", "2": "e_6"}} +{"p": [["e_5", "e_6", "e_8"]], "s": {"1": "e_6", "2": "e_7"}, "t": {"1": "e_8", "2": "e_7"}} +{"p": [["e_5", "e_6", "e_8"]], "s": {"1": "e_6", "2": "e_8"}, "t": {"1": "e_8", "2": "e_5"}} +{"p": [["e_5", "e_6", "e_8"]], "s": {"1": "e_7", "2": "e_5"}, "t": {"1": "e_7", "2": "e_6"}} +{"p": [["e_5", "e_6", "e_8"]], "s": {"1": "e_7", "2": "e_6"}, "t": {"1": "e_7", "2": "e_8"}} +{"p": [["e_5", "e_6", "e_8"]], "s": {"1": "e_7", "2": "e_8"}, "t": {"1": "e_7", "2": "e_5"}} +{"p": [["e_5", "e_6", "e_8"]], "s": {"1": "e_8", "2": "e_5"}, "t": {"1": "e_5", "2": "e_6"}} +{"p": [["e_5", "e_6", "e_8"]], "s": {"1": "e_8", "2": "e_6"}, "t": {"1": "e_5", "2": "e_8"}} +{"p": [["e_5", "e_6", "e_8"]], "s": {"1": "e_8", "2": "e_7"}, "t": {"1": "e_5", "2": "e_7"}} +{"p": [["e_5", "e_7", "e_6"]], "s": {"1": "e_5", "2": "e_6"}, "t": {"1": "e_7", "2": "e_5"}} +{"p": [["e_5", "e_7", "e_6"]], "s": {"1": "e_5", "2": "e_7"}, "t": {"1": "e_7", "2": "e_6"}} +{"p": [["e_5", "e_7", "e_6"]], "s": {"1": "e_5", "2": "e_8"}, "t": {"1": "e_7", "2": "e_8"}} +{"p": [["e_5", "e_7", "e_6"]], "s": {"1": "e_6", "2": "e_5"}, "t": {"1": "e_5", "2": "e_7"}} +{"p": [["e_5", "e_7", "e_6"]], "s": {"1": "e_6", "2": "e_7"}, "t": {"1": "e_5", "2": "e_6"}} +{"p": [["e_5", "e_7", "e_6"]], "s": {"1": "e_6", "2": "e_8"}, "t": {"1": "e_5", "2": "e_8"}} +{"p": [["e_5", "e_7", "e_6"]], "s": {"1": "e_7", "2": "e_5"}, "t": {"1": "e_6", "2": "e_7"}} +{"p": [["e_5", "e_7", "e_6"]], "s": {"1": "e_7", "2": "e_6"}, "t": {"1": "e_6", "2": "e_5"}} +{"p": [["e_5", "e_7", "e_6"]], "s": {"1": "e_7", "2": "e_8"}, "t": {"1": "e_6", "2": "e_8"}} +{"p": [["e_5", "e_7", "e_6"]], "s": {"1": "e_8", "2": "e_5"}, "t": {"1": "e_8", "2": "e_7"}} +{"p": [["e_5", "e_7", "e_6"]], "s": {"1": "e_8", "2": "e_6"}, "t": {"1": "e_8", "2": "e_5"}} +{"p": [["e_5", "e_7", "e_6"]], "s": {"1": "e_8", "2": "e_7"}, "t": {"1": "e_8", "2": "e_6"}} +{"p": [["e_5", "e_7", "e_8"]], "s": {"1": "e_5", "2": "e_6"}, "t": {"1": "e_7", "2": "e_6"}} +{"p": [["e_5", "e_7", "e_8"]], "s": {"1": "e_5", "2": "e_7"}, "t": {"1": "e_7", "2": "e_8"}} +{"p": [["e_5", "e_7", "e_8"]], "s": {"1": "e_5", "2": "e_8"}, "t": {"1": "e_7", "2": "e_5"}} +{"p": [["e_5", "e_7", "e_8"]], "s": {"1": "e_6", "2": "e_5"}, "t": {"1": "e_6", "2": "e_7"}} +{"p": [["e_5", "e_7", "e_8"]], "s": {"1": "e_6", "2": "e_7"}, "t": {"1": "e_6", "2": "e_8"}} +{"p": [["e_5", "e_7", "e_8"]], "s": {"1": "e_6", "2": "e_8"}, "t": {"1": "e_6", "2": "e_5"}} +{"p": [["e_5", "e_7", "e_8"]], "s": {"1": "e_7", "2": "e_5"}, "t": {"1": "e_8", "2": "e_7"}} +{"p": [["e_5", "e_7", "e_8"]], "s": {"1": "e_7", "2": "e_6"}, "t": {"1": "e_8", "2": "e_6"}} +{"p": [["e_5", "e_7", "e_8"]], "s": {"1": "e_7", "2": "e_8"}, "t": {"1": "e_8", "2": "e_5"}} +{"p": [["e_5", "e_7", "e_8"]], "s": {"1": "e_8", "2": "e_5"}, "t": {"1": "e_5", "2": "e_7"}} +{"p": [["e_5", "e_7", "e_8"]], "s": {"1": "e_8", "2": "e_6"}, "t": {"1": "e_5", "2": "e_6"}} +{"p": [["e_5", "e_7", "e_8"]], "s": {"1": "e_8", "2": "e_7"}, "t": {"1": "e_5", "2": "e_8"}} +{"p": [["e_5", "e_8", "e_6"]], "s": {"1": "e_5", "2": "e_6"}, "t": {"1": "e_8", "2": "e_5"}} +{"p": [["e_5", "e_8", "e_6"]], "s": {"1": "e_5", "2": "e_7"}, "t": {"1": "e_8", "2": "e_7"}} +{"p": [["e_5", "e_8", "e_6"]], "s": {"1": "e_5", "2": "e_8"}, "t": {"1": "e_8", "2": "e_6"}} +{"p": [["e_5", "e_8", "e_6"]], "s": {"1": "e_6", "2": "e_5"}, "t": {"1": "e_5", "2": "e_8"}} +{"p": [["e_5", "e_8", "e_6"]], "s": {"1": "e_6", "2": "e_7"}, "t": {"1": "e_5", "2": "e_7"}} +{"p": [["e_5", "e_8", "e_6"]], "s": {"1": "e_6", "2": "e_8"}, "t": {"1": "e_5", "2": "e_6"}} +{"p": [["e_5", "e_8", "e_6"]], "s": {"1": "e_7", "2": "e_5"}, "t": {"1": "e_7", "2": "e_8"}} +{"p": [["e_5", "e_8", "e_6"]], "s": {"1": "e_7", "2": "e_6"}, "t": {"1": "e_7", "2": "e_5"}} +{"p": [["e_5", "e_8", "e_6"]], "s": {"1": "e_7", "2": "e_8"}, "t": {"1": "e_7", "2": "e_6"}} +{"p": [["e_5", "e_8", "e_6"]], "s": {"1": "e_8", "2": "e_5"}, "t": {"1": "e_6", "2": "e_8"}} +{"p": [["e_5", "e_8", "e_6"]], "s": {"1": "e_8", "2": "e_6"}, "t": {"1": "e_6", "2": "e_5"}} +{"p": [["e_5", "e_8", "e_6"]], "s": {"1": "e_8", "2": "e_7"}, "t": {"1": "e_6", "2": "e_7"}} +{"p": [["e_5", "e_8", "e_7"]], "s": {"1": "e_5", "2": "e_6"}, "t": {"1": "e_8", "2": "e_6"}} +{"p": [["e_5", "e_8", "e_7"]], "s": {"1": "e_5", "2": "e_7"}, "t": {"1": "e_8", "2": "e_5"}} +{"p": [["e_5", "e_8", "e_7"]], "s": {"1": "e_5", "2": "e_8"}, "t": {"1": "e_8", "2": "e_7"}} +{"p": [["e_5", "e_8", "e_7"]], "s": {"1": "e_6", "2": "e_5"}, "t": {"1": "e_6", "2": "e_8"}} +{"p": [["e_5", "e_8", "e_7"]], "s": {"1": "e_6", "2": "e_7"}, "t": {"1": "e_6", "2": "e_5"}} +{"p": [["e_5", "e_8", "e_7"]], "s": {"1": "e_6", "2": "e_8"}, "t": {"1": "e_6", "2": "e_7"}} +{"p": [["e_5", "e_8", "e_7"]], "s": {"1": "e_7", "2": "e_5"}, "t": {"1": "e_5", "2": "e_8"}} +{"p": [["e_5", "e_8", "e_7"]], "s": {"1": "e_7", "2": "e_6"}, "t": {"1": "e_5", "2": "e_6"}} +{"p": [["e_5", "e_8", "e_7"]], "s": {"1": "e_7", "2": "e_8"}, "t": {"1": "e_5", "2": "e_7"}} +{"p": [["e_5", "e_8", "e_7"]], "s": {"1": "e_8", "2": "e_5"}, "t": {"1": "e_7", "2": "e_8"}} +{"p": [["e_5", "e_8", "e_7"]], "s": {"1": "e_8", "2": "e_6"}, "t": {"1": "e_7", "2": "e_6"}} +{"p": [["e_5", "e_8", "e_7"]], "s": {"1": "e_8", "2": "e_7"}, "t": {"1": "e_7", "2": "e_5"}} +{"p": [["e_6", "e_7", "e_8"]], "s": {"1": "e_5", "2": "e_6"}, "t": {"1": "e_5", "2": "e_7"}} +{"p": [["e_6", "e_7", "e_8"]], "s": {"1": "e_5", "2": "e_7"}, "t": {"1": "e_5", "2": "e_8"}} +{"p": [["e_6", "e_7", "e_8"]], "s": {"1": "e_5", "2": "e_8"}, "t": {"1": "e_5", "2": "e_6"}} +{"p": [["e_6", "e_7", "e_8"]], "s": {"1": "e_6", "2": "e_5"}, "t": {"1": "e_7", "2": "e_5"}} +{"p": [["e_6", "e_7", "e_8"]], "s": {"1": "e_6", "2": "e_7"}, "t": {"1": "e_7", "2": "e_8"}} +{"p": [["e_6", "e_7", "e_8"]], "s": {"1": "e_6", "2": "e_8"}, "t": {"1": "e_7", "2": "e_6"}} +{"p": [["e_6", "e_7", "e_8"]], "s": {"1": "e_7", "2": "e_5"}, "t": {"1": "e_8", "2": "e_5"}} +{"p": [["e_6", "e_7", "e_8"]], "s": {"1": "e_7", "2": "e_6"}, "t": {"1": "e_8", "2": "e_7"}} +{"p": [["e_6", "e_7", "e_8"]], "s": {"1": "e_7", "2": "e_8"}, "t": {"1": "e_8", "2": "e_6"}} +{"p": [["e_6", "e_7", "e_8"]], "s": {"1": "e_8", "2": "e_5"}, "t": {"1": "e_6", "2": "e_5"}} +{"p": [["e_6", "e_7", "e_8"]], "s": {"1": "e_8", "2": "e_6"}, "t": {"1": "e_6", "2": "e_7"}} +{"p": [["e_6", "e_7", "e_8"]], "s": {"1": "e_8", "2": "e_7"}, "t": {"1": "e_6", "2": "e_8"}} +{"p": [["e_6", "e_8", "e_7"]], "s": {"1": "e_5", "2": "e_6"}, "t": {"1": "e_5", "2": "e_8"}} +{"p": [["e_6", "e_8", "e_7"]], "s": {"1": "e_5", "2": "e_7"}, "t": {"1": "e_5", "2": "e_6"}} +{"p": [["e_6", "e_8", "e_7"]], "s": {"1": "e_5", "2": "e_8"}, "t": {"1": "e_5", "2": "e_7"}} +{"p": [["e_6", "e_8", "e_7"]], "s": {"1": "e_6", "2": "e_5"}, "t": {"1": "e_8", "2": "e_5"}} +{"p": [["e_6", "e_8", "e_7"]], "s": {"1": "e_6", "2": "e_7"}, "t": {"1": "e_8", "2": "e_6"}} +{"p": [["e_6", "e_8", "e_7"]], "s": {"1": "e_6", "2": "e_8"}, "t": {"1": "e_8", "2": "e_7"}} +{"p": [["e_6", "e_8", "e_7"]], "s": {"1": "e_7", "2": "e_5"}, "t": {"1": "e_6", "2": "e_5"}} +{"p": [["e_6", "e_8", "e_7"]], "s": {"1": "e_7", "2": "e_6"}, "t": {"1": "e_6", "2": "e_8"}} +{"p": [["e_6", "e_8", "e_7"]], "s": {"1": "e_7", "2": "e_8"}, "t": {"1": "e_6", "2": "e_7"}} +{"p": [["e_6", "e_8", "e_7"]], "s": {"1": "e_8", "2": "e_5"}, "t": {"1": "e_7", "2": "e_5"}} +{"p": [["e_6", "e_8", "e_7"]], "s": {"1": "e_8", "2": "e_6"}, "t": {"1": "e_7", "2": "e_8"}} +{"p": [["e_6", "e_8", "e_7"]], "s": {"1": "e_8", "2": "e_7"}, "t": {"1": "e_7", "2": "e_6"}} From b9e8fd9da8678fbb7084c5141007f5c4d8a554ac Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?=C3=96zg=C3=BCr=20Akg=C3=BCn?= Date: Tue, 9 Apr 2024 10:54:37 +0100 Subject: [PATCH 153/229] lint --- src/Conjure/Language/Lenses.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/src/Conjure/Language/Lenses.hs b/src/Conjure/Language/Lenses.hs index 0e1b6c85ff..2a9805160f 100644 --- a/src/Conjure/Language/Lenses.hs +++ b/src/Conjure/Language/Lenses.hs @@ -27,7 +27,7 @@ followAliases m (isAlias -> Just x) = followAliases m x followAliases m x = m x tryMatch :: (Proxy Maybe -> (a, b -> Maybe c)) -> b -> Maybe c -tryMatch f = match f +tryMatch = match matchOr :: c -> (Proxy Maybe -> (a, b -> Maybe c)) -> b -> c matchOr defOut f inp = fromMaybe defOut (match f inp) @@ -1374,7 +1374,7 @@ functionLiteral _ = permutationLiteral :: (MonadFailDoc m, ?typeCheckerMode :: TypeCheckerMode) - => Proxy (m :: * -> *) + => Proxy (m :: T.Type -> T.Type ) -> ( Type -> [[Expression]] -> Expression , Expression -> m (Type, [[Expression]]) ) From bf5afdce7e4a725963b26d170054dc6af88b8263 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?=C3=96zg=C3=BCr=20Akg=C3=BCn?= Date: Tue, 9 Apr 2024 10:54:52 +0100 Subject: [PATCH 154/229] missing case in domainNeedsRepresentation --- src/Conjure/Language/ModelStats.hs | 1 + 1 file changed, 1 insertion(+) diff --git a/src/Conjure/Language/ModelStats.hs b/src/Conjure/Language/ModelStats.hs index de37bc9f2e..e8b8b95e69 100644 --- a/src/Conjure/Language/ModelStats.hs +++ b/src/Conjure/Language/ModelStats.hs @@ -67,6 +67,7 @@ domainNeedsRepresentation DomainFunction{} = True domainNeedsRepresentation DomainSequence{} = True domainNeedsRepresentation DomainRelation{} = True domainNeedsRepresentation DomainPartition{} = True +domainNeedsRepresentation DomainPermutation{} = True domainNeedsRepresentation (DomainReference _ (Just _)) = True domainNeedsRepresentation d = bug $ "domainNeedsRepresentation:" <+> pretty (show d) From 506780bc69882e473e1124681139e027ceacdf5b Mon Sep 17 00:00:00 2001 From: Chris Jefferson Date: Wed, 10 Apr 2024 08:43:39 +0800 Subject: [PATCH 155/229] Use 'transform', not 'image', to apply permutations? --- src/Conjure/UI/Model.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Conjure/UI/Model.hs b/src/Conjure/UI/Model.hs index 57e7f4d465..19e43333d3 100644 --- a/src/Conjure/UI/Model.hs +++ b/src/Conjure/UI/Model.hs @@ -2868,7 +2868,7 @@ addUnnamedSymmetryBreaking mode model = do buildPermutationChain [] vars = vars buildPermutationChain (p:ps) vars = let applied = buildPermutationChain ps vars - in [essence| image(&p, &applied) |] + in [essence| transform(&p, &applied) |] nestInBubbles :: Expression -> Int -> [(Expression,Statement)] -> Expression -> Expression nestInBubbles _ _ [] expr = expr From bd1d588000408850f7ff17c9d77ff14f1b2ab478 Mon Sep 17 00:00:00 2001 From: Chris Jefferson Date: Wed, 10 Apr 2024 10:12:19 +0800 Subject: [PATCH 156/229] Add a SimpleJSON output for unnamed types --- src/Conjure/Language/Expression.hs | 12 ++++++++++++ 1 file changed, 12 insertions(+) diff --git a/src/Conjure/Language/Expression.hs b/src/Conjure/Language/Expression.hs index 4c961c7ebb..89600757b9 100644 --- a/src/Conjure/Language/Expression.hs +++ b/src/Conjure/Language/Expression.hs @@ -165,9 +165,21 @@ instance SimpleJSON Declaration where Letting nm x -> do x' <- toSimpleJSON x return $ JSON.Object $ KM.fromList [(fromString (renderNormal nm), x')] + LettingDomainDefnEnum nm x -> do + x' <- toSimpleJSON x + return $ JSON.Object $ KM.fromList [(fromString (renderNormal nm), x')] _ -> noToSimpleJSON d fromSimpleJSON = noFromSimpleJSON "Declaration" +instance SimpleJSON Name where + toSimpleJSON n = + case n of + Name nm -> do + return $ JSON.String nm + _ -> noToSimpleJSON n + + fromSimpleJSON = noFromSimpleJSON "Name" + instance ToFromMiniZinc Declaration where toMiniZinc st = case st of From 576ce706670eb2fc86a3f036d84a02004ed3b37b Mon Sep 17 00:00:00 2001 From: Chris Jefferson Date: Wed, 10 Apr 2024 14:14:04 +0800 Subject: [PATCH 157/229] Need to quantify over permutations, not sequences, for symmetry breaking --- src/Conjure/UI/Model.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/src/Conjure/UI/Model.hs b/src/Conjure/UI/Model.hs index 19e43333d3..f0264d1e1e 100644 --- a/src/Conjure/UI/Model.hs +++ b/src/Conjure/UI/Model.hs @@ -2945,7 +2945,7 @@ addUnnamedSymmetryBreaking mode model = do let applied = combinedPermApply auxSuffix (perm:perms) return [essence| and([ &applied - | &iPat : sequence of &u + | &iPat : permutation of &u ]) |] mkGenerator_AllPermutations auxSuffix perms ((u, _uSize):us) = do @@ -2954,7 +2954,7 @@ addUnnamedSymmetryBreaking mode model = do applied <- mkGenerator_AllPermutations auxSuffix (perm:perms) us return [essence| and([ &applied - | &iPat : sequence of &u + | &iPat : permutation of &u ]) |] From c86104b09485659a96c02e2c41dc134544eac696 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?=C3=96zg=C3=BCr=20Akg=C3=BCn?= Date: Fri, 12 Apr 2024 09:51:04 +0100 Subject: [PATCH 158/229] add minimum_int_value_in_domain --- src/Conjure/Rules/DontCare.hs | 40 +++++++++++++++++++++++------------ 1 file changed, 26 insertions(+), 14 deletions(-) diff --git a/src/Conjure/Rules/DontCare.hs b/src/Conjure/Rules/DontCare.hs index 799b2a1dec..d117cd86a7 100644 --- a/src/Conjure/Rules/DontCare.hs +++ b/src/Conjure/Rules/DontCare.hs @@ -1,4 +1,6 @@ {-# LANGUAGE QuasiQuotes #-} +{-# OPTIONS_GHC -Wno-unrecognised-pragmas #-} +{-# HLINT ignore "Use camelCase" #-} module Conjure.Rules.DontCare where @@ -17,23 +19,33 @@ rule_Bool = "dontCare-bool" `namedRule` theRule where ) +minimum_int_value_in_domain :: + MonadFail m => + MonadFailDoc m => + NameGen m => + (?typeCheckerMode::TypeCheckerMode) => + Expression -> m Expression +minimum_int_value_in_domain x = do + TypeInt t <- typeOf x + xDomain <- domainOf x + let raiseBug = bug ("dontCare on domain:" <+> pretty xDomain) + return $ reTag t $ case xDomain of + DomainInt _ [] -> raiseBug + DomainInt _ (r:_) -> case r of + RangeOpen -> raiseBug + RangeSingle v -> v + RangeLowerBounded v -> v + RangeUpperBounded v -> v + RangeBounded v _ -> v + DomainIntE v -> [essence| min(&v) |] + _ -> raiseBug + + rule_Int :: Rule rule_Int = "dontCare-int" `namedRule` theRule where theRule p = do - x <- match opDontCare p - TypeInt t <- typeOf x - xDomain <- domainOf x - let raiseBug = bug ("dontCare on domain:" <+> pretty xDomain) - let val = reTag t $ case xDomain of - DomainInt _ [] -> raiseBug - DomainInt _ (r:_) -> case r of - RangeOpen -> raiseBug - RangeSingle v -> v - RangeLowerBounded v -> v - RangeUpperBounded v -> v - RangeBounded v _ -> v - DomainIntE v -> [essence| min(&v) |] - _ -> raiseBug + x <- match opDontCare p + val <- minimum_int_value_in_domain x return ( "dontCare value for this integer is" <+> pretty val , return $ make opEq x val From f5537a8e73b16d1703fb62e0e750732c43e9ff9a Mon Sep 17 00:00:00 2001 From: Chris Jefferson Date: Wed, 10 Apr 2024 14:15:22 +0800 Subject: [PATCH 159/229] Add some dotlt tests --- tests/custom/dotlt/basic/enum/model.essence | 9 ++ tests/custom/dotlt/basic/enum/run.sh | 3 + tests/custom/dotlt/basic/enum/stdout.expected | 14 ++ tests/custom/dotlt/basic/int/model.essence | 7 + tests/custom/dotlt/basic/int/run.sh | 3 + tests/custom/dotlt/basic/int/stdout.expected | 14 ++ .../custom/dotlt/basic/unnamed/model.essence | 9 ++ tests/custom/dotlt/basic/unnamed/run.sh | 3 + .../dotlt/basic/unnamed/stdout.expected | 18 +++ tests/custom/dotlt/matrix/enum/model.essence | 9 ++ tests/custom/dotlt/matrix/enum/run.sh | 3 + .../custom/dotlt/matrix/enum/stdout.expected | 53 +++++++ tests/custom/dotlt/matrix/int/model.essence | 7 + tests/custom/dotlt/matrix/int/run.sh | 3 + tests/custom/dotlt/matrix/int/stdout.expected | 53 +++++++ .../custom/dotlt/matrix/unnamed/model.essence | 9 ++ tests/custom/dotlt/matrix/unnamed/run.sh | 3 + .../dotlt/matrix/unnamed/stdout.expected | 144 ++++++++++++++++++ tests/custom/dotlt/set/enum/model.essence | 9 ++ tests/custom/dotlt/set/enum/run.sh | 3 + tests/custom/dotlt/set/enum/stdout.expected | 44 ++++++ tests/custom/dotlt/set/int/model.essence | 7 + tests/custom/dotlt/set/int/run.sh | 3 + tests/custom/dotlt/set/int/stdout.expected | 44 ++++++ tests/custom/dotlt/set/unnamed/model.essence | 9 ++ tests/custom/dotlt/set/unnamed/run.sh | 3 + .../custom/dotlt/set/unnamed/stdout.expected | 144 ++++++++++++++++++ tests/custom/dotlt/tuple/enum/model.essence | 9 ++ tests/custom/dotlt/tuple/enum/run.sh | 3 + tests/custom/dotlt/tuple/enum/stdout.expected | 14 ++ tests/custom/dotlt/tuple/int/model.essence | 7 + tests/custom/dotlt/tuple/int/run.sh | 3 + tests/custom/dotlt/tuple/int/stdout.expected | 14 ++ .../custom/dotlt/tuple/unnamed/model.essence | 9 ++ tests/custom/dotlt/tuple/unnamed/run.sh | 3 + .../dotlt/tuple/unnamed/stdout.expected | 18 +++ 36 files changed, 710 insertions(+) create mode 100644 tests/custom/dotlt/basic/enum/model.essence create mode 100755 tests/custom/dotlt/basic/enum/run.sh create mode 100644 tests/custom/dotlt/basic/enum/stdout.expected create mode 100644 tests/custom/dotlt/basic/int/model.essence create mode 100755 tests/custom/dotlt/basic/int/run.sh create mode 100644 tests/custom/dotlt/basic/int/stdout.expected create mode 100644 tests/custom/dotlt/basic/unnamed/model.essence create mode 100755 tests/custom/dotlt/basic/unnamed/run.sh create mode 100644 tests/custom/dotlt/basic/unnamed/stdout.expected create mode 100644 tests/custom/dotlt/matrix/enum/model.essence create mode 100755 tests/custom/dotlt/matrix/enum/run.sh create mode 100644 tests/custom/dotlt/matrix/enum/stdout.expected create mode 100644 tests/custom/dotlt/matrix/int/model.essence create mode 100755 tests/custom/dotlt/matrix/int/run.sh create mode 100644 tests/custom/dotlt/matrix/int/stdout.expected create mode 100644 tests/custom/dotlt/matrix/unnamed/model.essence create mode 100755 tests/custom/dotlt/matrix/unnamed/run.sh create mode 100644 tests/custom/dotlt/matrix/unnamed/stdout.expected create mode 100644 tests/custom/dotlt/set/enum/model.essence create mode 100755 tests/custom/dotlt/set/enum/run.sh create mode 100644 tests/custom/dotlt/set/enum/stdout.expected create mode 100644 tests/custom/dotlt/set/int/model.essence create mode 100755 tests/custom/dotlt/set/int/run.sh create mode 100644 tests/custom/dotlt/set/int/stdout.expected create mode 100644 tests/custom/dotlt/set/unnamed/model.essence create mode 100755 tests/custom/dotlt/set/unnamed/run.sh create mode 100644 tests/custom/dotlt/set/unnamed/stdout.expected create mode 100644 tests/custom/dotlt/tuple/enum/model.essence create mode 100755 tests/custom/dotlt/tuple/enum/run.sh create mode 100644 tests/custom/dotlt/tuple/enum/stdout.expected create mode 100644 tests/custom/dotlt/tuple/int/model.essence create mode 100755 tests/custom/dotlt/tuple/int/run.sh create mode 100644 tests/custom/dotlt/tuple/int/stdout.expected create mode 100644 tests/custom/dotlt/tuple/unnamed/model.essence create mode 100755 tests/custom/dotlt/tuple/unnamed/run.sh create mode 100644 tests/custom/dotlt/tuple/unnamed/stdout.expected diff --git a/tests/custom/dotlt/basic/enum/model.essence b/tests/custom/dotlt/basic/enum/model.essence new file mode 100644 index 0000000000..8c3ee058b1 --- /dev/null +++ b/tests/custom/dotlt/basic/enum/model.essence @@ -0,0 +1,9 @@ +letting e be new type enum {e1,e2,e3} + +find i: e +find j: e + +such that + +i .<= j + diff --git a/tests/custom/dotlt/basic/enum/run.sh b/tests/custom/dotlt/basic/enum/run.sh new file mode 100755 index 0000000000..10ed17da89 --- /dev/null +++ b/tests/custom/dotlt/basic/enum/run.sh @@ -0,0 +1,3 @@ +conjure solve --number-of-solutions=all --solutions-in-one-file --output-format=jsonstream *.essence +cat *.json | LC_ALL=C sort +rm -rf conjure-output *solutions* \ No newline at end of file diff --git a/tests/custom/dotlt/basic/enum/stdout.expected b/tests/custom/dotlt/basic/enum/stdout.expected new file mode 100644 index 0000000000..57b7795950 --- /dev/null +++ b/tests/custom/dotlt/basic/enum/stdout.expected @@ -0,0 +1,14 @@ +Generating models for model.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Running minion for domain filtering. +Running solver: minion +Copying solution to: model.solutions +Copying solution to: model.solutions.json +{"i": "e1", "j": "e1"} +{"i": "e1", "j": "e2"} +{"i": "e1", "j": "e3"} +{"i": "e2", "j": "e2"} +{"i": "e2", "j": "e3"} +{"i": "e3", "j": "e3"} diff --git a/tests/custom/dotlt/basic/int/model.essence b/tests/custom/dotlt/basic/int/model.essence new file mode 100644 index 0000000000..afab003cc7 --- /dev/null +++ b/tests/custom/dotlt/basic/int/model.essence @@ -0,0 +1,7 @@ +find i: int(1..3) +find j: int(1..3) + +such that + +i .<= j + diff --git a/tests/custom/dotlt/basic/int/run.sh b/tests/custom/dotlt/basic/int/run.sh new file mode 100755 index 0000000000..10ed17da89 --- /dev/null +++ b/tests/custom/dotlt/basic/int/run.sh @@ -0,0 +1,3 @@ +conjure solve --number-of-solutions=all --solutions-in-one-file --output-format=jsonstream *.essence +cat *.json | LC_ALL=C sort +rm -rf conjure-output *solutions* \ No newline at end of file diff --git a/tests/custom/dotlt/basic/int/stdout.expected b/tests/custom/dotlt/basic/int/stdout.expected new file mode 100644 index 0000000000..38f48fb5e6 --- /dev/null +++ b/tests/custom/dotlt/basic/int/stdout.expected @@ -0,0 +1,14 @@ +Generating models for model.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Running minion for domain filtering. +Running solver: minion +Copying solution to: model.solutions +Copying solution to: model.solutions.json +{"i": 1, "j": 1} +{"i": 1, "j": 2} +{"i": 1, "j": 3} +{"i": 2, "j": 2} +{"i": 2, "j": 3} +{"i": 3, "j": 3} diff --git a/tests/custom/dotlt/basic/unnamed/model.essence b/tests/custom/dotlt/basic/unnamed/model.essence new file mode 100644 index 0000000000..8431ccd76d --- /dev/null +++ b/tests/custom/dotlt/basic/unnamed/model.essence @@ -0,0 +1,9 @@ +letting e be new type of size 4 + +find i: e +find j: e + +such that + +i .<= j + diff --git a/tests/custom/dotlt/basic/unnamed/run.sh b/tests/custom/dotlt/basic/unnamed/run.sh new file mode 100755 index 0000000000..10ed17da89 --- /dev/null +++ b/tests/custom/dotlt/basic/unnamed/run.sh @@ -0,0 +1,3 @@ +conjure solve --number-of-solutions=all --solutions-in-one-file --output-format=jsonstream *.essence +cat *.json | LC_ALL=C sort +rm -rf conjure-output *solutions* \ No newline at end of file diff --git a/tests/custom/dotlt/basic/unnamed/stdout.expected b/tests/custom/dotlt/basic/unnamed/stdout.expected new file mode 100644 index 0000000000..276da5a986 --- /dev/null +++ b/tests/custom/dotlt/basic/unnamed/stdout.expected @@ -0,0 +1,18 @@ +Generating models for model.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Running minion for domain filtering. +Running solver: minion +Copying solution to: model.solutions +Copying solution to: model.solutions.json +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": "e_1", "j": "e_1"} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": "e_1", "j": "e_2"} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": "e_1", "j": "e_3"} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": "e_1", "j": "e_4"} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": "e_2", "j": "e_2"} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": "e_2", "j": "e_3"} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": "e_2", "j": "e_4"} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": "e_3", "j": "e_3"} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": "e_3", "j": "e_4"} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": "e_4", "j": "e_4"} diff --git a/tests/custom/dotlt/matrix/enum/model.essence b/tests/custom/dotlt/matrix/enum/model.essence new file mode 100644 index 0000000000..d81c2c8718 --- /dev/null +++ b/tests/custom/dotlt/matrix/enum/model.essence @@ -0,0 +1,9 @@ +letting e be new type enum {e1,e2,e3} + +find i: matrix indexed by [int(1..2)] of e +find j: matrix indexed by [int(1..2)] of e + +such that + +i .<= j + diff --git a/tests/custom/dotlt/matrix/enum/run.sh b/tests/custom/dotlt/matrix/enum/run.sh new file mode 100755 index 0000000000..10ed17da89 --- /dev/null +++ b/tests/custom/dotlt/matrix/enum/run.sh @@ -0,0 +1,3 @@ +conjure solve --number-of-solutions=all --solutions-in-one-file --output-format=jsonstream *.essence +cat *.json | LC_ALL=C sort +rm -rf conjure-output *solutions* \ No newline at end of file diff --git a/tests/custom/dotlt/matrix/enum/stdout.expected b/tests/custom/dotlt/matrix/enum/stdout.expected new file mode 100644 index 0000000000..a4b0057bef --- /dev/null +++ b/tests/custom/dotlt/matrix/enum/stdout.expected @@ -0,0 +1,53 @@ +Generating models for model.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Running minion for domain filtering. +Running solver: minion +Copying solution to: model.solutions +Copying solution to: model.solutions.json +{"i": {"1": "e1", "2": "e1"}, "j": {"1": "e1", "2": "e1"}} +{"i": {"1": "e1", "2": "e1"}, "j": {"1": "e1", "2": "e2"}} +{"i": {"1": "e1", "2": "e1"}, "j": {"1": "e1", "2": "e3"}} +{"i": {"1": "e1", "2": "e1"}, "j": {"1": "e2", "2": "e1"}} +{"i": {"1": "e1", "2": "e1"}, "j": {"1": "e2", "2": "e2"}} +{"i": {"1": "e1", "2": "e1"}, "j": {"1": "e2", "2": "e3"}} +{"i": {"1": "e1", "2": "e1"}, "j": {"1": "e3", "2": "e1"}} +{"i": {"1": "e1", "2": "e1"}, "j": {"1": "e3", "2": "e2"}} +{"i": {"1": "e1", "2": "e1"}, "j": {"1": "e3", "2": "e3"}} +{"i": {"1": "e1", "2": "e2"}, "j": {"1": "e1", "2": "e2"}} +{"i": {"1": "e1", "2": "e2"}, "j": {"1": "e1", "2": "e3"}} +{"i": {"1": "e1", "2": "e2"}, "j": {"1": "e2", "2": "e1"}} +{"i": {"1": "e1", "2": "e2"}, "j": {"1": "e2", "2": "e2"}} +{"i": {"1": "e1", "2": "e2"}, "j": {"1": "e2", "2": "e3"}} +{"i": {"1": "e1", "2": "e2"}, "j": {"1": "e3", "2": "e1"}} +{"i": {"1": "e1", "2": "e2"}, "j": {"1": "e3", "2": "e2"}} +{"i": {"1": "e1", "2": "e2"}, "j": {"1": "e3", "2": "e3"}} +{"i": {"1": "e1", "2": "e3"}, "j": {"1": "e1", "2": "e3"}} +{"i": {"1": "e1", "2": "e3"}, "j": {"1": "e2", "2": "e1"}} +{"i": {"1": "e1", "2": "e3"}, "j": {"1": "e2", "2": "e2"}} +{"i": {"1": "e1", "2": "e3"}, "j": {"1": "e2", "2": "e3"}} +{"i": {"1": "e1", "2": "e3"}, "j": {"1": "e3", "2": "e1"}} +{"i": {"1": "e1", "2": "e3"}, "j": {"1": "e3", "2": "e2"}} +{"i": {"1": "e1", "2": "e3"}, "j": {"1": "e3", "2": "e3"}} +{"i": {"1": "e2", "2": "e1"}, "j": {"1": "e2", "2": "e1"}} +{"i": {"1": "e2", "2": "e1"}, "j": {"1": "e2", "2": "e2"}} +{"i": {"1": "e2", "2": "e1"}, "j": {"1": "e2", "2": "e3"}} +{"i": {"1": "e2", "2": "e1"}, "j": {"1": "e3", "2": "e1"}} +{"i": {"1": "e2", "2": "e1"}, "j": {"1": "e3", "2": "e2"}} +{"i": {"1": "e2", "2": "e1"}, "j": {"1": "e3", "2": "e3"}} +{"i": {"1": "e2", "2": "e2"}, "j": {"1": "e2", "2": "e2"}} +{"i": {"1": "e2", "2": "e2"}, "j": {"1": "e2", "2": "e3"}} +{"i": {"1": "e2", "2": "e2"}, "j": {"1": "e3", "2": "e1"}} +{"i": {"1": "e2", "2": "e2"}, "j": {"1": "e3", "2": "e2"}} +{"i": {"1": "e2", "2": "e2"}, "j": {"1": "e3", "2": "e3"}} +{"i": {"1": "e2", "2": "e3"}, "j": {"1": "e2", "2": "e3"}} +{"i": {"1": "e2", "2": "e3"}, "j": {"1": "e3", "2": "e1"}} +{"i": {"1": "e2", "2": "e3"}, "j": {"1": "e3", "2": "e2"}} +{"i": {"1": "e2", "2": "e3"}, "j": {"1": "e3", "2": "e3"}} +{"i": {"1": "e3", "2": "e1"}, "j": {"1": "e3", "2": "e1"}} +{"i": {"1": "e3", "2": "e1"}, "j": {"1": "e3", "2": "e2"}} +{"i": {"1": "e3", "2": "e1"}, "j": {"1": "e3", "2": "e3"}} +{"i": {"1": "e3", "2": "e2"}, "j": {"1": "e3", "2": "e2"}} +{"i": {"1": "e3", "2": "e2"}, "j": {"1": "e3", "2": "e3"}} +{"i": {"1": "e3", "2": "e3"}, "j": {"1": "e3", "2": "e3"}} diff --git a/tests/custom/dotlt/matrix/int/model.essence b/tests/custom/dotlt/matrix/int/model.essence new file mode 100644 index 0000000000..5bc065f58a --- /dev/null +++ b/tests/custom/dotlt/matrix/int/model.essence @@ -0,0 +1,7 @@ +find i: matrix indexed by [int(1..2)] of int(1..3) +find j: matrix indexed by [int(1..2)] of int(1..3) + +such that + +i .<= j + diff --git a/tests/custom/dotlt/matrix/int/run.sh b/tests/custom/dotlt/matrix/int/run.sh new file mode 100755 index 0000000000..10ed17da89 --- /dev/null +++ b/tests/custom/dotlt/matrix/int/run.sh @@ -0,0 +1,3 @@ +conjure solve --number-of-solutions=all --solutions-in-one-file --output-format=jsonstream *.essence +cat *.json | LC_ALL=C sort +rm -rf conjure-output *solutions* \ No newline at end of file diff --git a/tests/custom/dotlt/matrix/int/stdout.expected b/tests/custom/dotlt/matrix/int/stdout.expected new file mode 100644 index 0000000000..8b80802066 --- /dev/null +++ b/tests/custom/dotlt/matrix/int/stdout.expected @@ -0,0 +1,53 @@ +Generating models for model.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Running minion for domain filtering. +Running solver: minion +Copying solution to: model.solutions +Copying solution to: model.solutions.json +{"i": {"1": 1, "2": 1}, "j": {"1": 1, "2": 1}} +{"i": {"1": 1, "2": 1}, "j": {"1": 1, "2": 2}} +{"i": {"1": 1, "2": 1}, "j": {"1": 1, "2": 3}} +{"i": {"1": 1, "2": 1}, "j": {"1": 2, "2": 1}} +{"i": {"1": 1, "2": 1}, "j": {"1": 2, "2": 2}} +{"i": {"1": 1, "2": 1}, "j": {"1": 2, "2": 3}} +{"i": {"1": 1, "2": 1}, "j": {"1": 3, "2": 1}} +{"i": {"1": 1, "2": 1}, "j": {"1": 3, "2": 2}} +{"i": {"1": 1, "2": 1}, "j": {"1": 3, "2": 3}} +{"i": {"1": 1, "2": 2}, "j": {"1": 1, "2": 2}} +{"i": {"1": 1, "2": 2}, "j": {"1": 1, "2": 3}} +{"i": {"1": 1, "2": 2}, "j": {"1": 2, "2": 1}} +{"i": {"1": 1, "2": 2}, "j": {"1": 2, "2": 2}} +{"i": {"1": 1, "2": 2}, "j": {"1": 2, "2": 3}} +{"i": {"1": 1, "2": 2}, "j": {"1": 3, "2": 1}} +{"i": {"1": 1, "2": 2}, "j": {"1": 3, "2": 2}} +{"i": {"1": 1, "2": 2}, "j": {"1": 3, "2": 3}} +{"i": {"1": 1, "2": 3}, "j": {"1": 1, "2": 3}} +{"i": {"1": 1, "2": 3}, "j": {"1": 2, "2": 1}} +{"i": {"1": 1, "2": 3}, "j": {"1": 2, "2": 2}} +{"i": {"1": 1, "2": 3}, "j": {"1": 2, "2": 3}} +{"i": {"1": 1, "2": 3}, "j": {"1": 3, "2": 1}} +{"i": {"1": 1, "2": 3}, "j": {"1": 3, "2": 2}} +{"i": {"1": 1, "2": 3}, "j": {"1": 3, "2": 3}} +{"i": {"1": 2, "2": 1}, "j": {"1": 2, "2": 1}} +{"i": {"1": 2, "2": 1}, "j": {"1": 2, "2": 2}} +{"i": {"1": 2, "2": 1}, "j": {"1": 2, "2": 3}} +{"i": {"1": 2, "2": 1}, "j": {"1": 3, "2": 1}} +{"i": {"1": 2, "2": 1}, "j": {"1": 3, "2": 2}} +{"i": {"1": 2, "2": 1}, "j": {"1": 3, "2": 3}} +{"i": {"1": 2, "2": 2}, "j": {"1": 2, "2": 2}} +{"i": {"1": 2, "2": 2}, "j": {"1": 2, "2": 3}} +{"i": {"1": 2, "2": 2}, "j": {"1": 3, "2": 1}} +{"i": {"1": 2, "2": 2}, "j": {"1": 3, "2": 2}} +{"i": {"1": 2, "2": 2}, "j": {"1": 3, "2": 3}} +{"i": {"1": 2, "2": 3}, "j": {"1": 2, "2": 3}} +{"i": {"1": 2, "2": 3}, "j": {"1": 3, "2": 1}} +{"i": {"1": 2, "2": 3}, "j": {"1": 3, "2": 2}} +{"i": {"1": 2, "2": 3}, "j": {"1": 3, "2": 3}} +{"i": {"1": 3, "2": 1}, "j": {"1": 3, "2": 1}} +{"i": {"1": 3, "2": 1}, "j": {"1": 3, "2": 2}} +{"i": {"1": 3, "2": 1}, "j": {"1": 3, "2": 3}} +{"i": {"1": 3, "2": 2}, "j": {"1": 3, "2": 2}} +{"i": {"1": 3, "2": 2}, "j": {"1": 3, "2": 3}} +{"i": {"1": 3, "2": 3}, "j": {"1": 3, "2": 3}} diff --git a/tests/custom/dotlt/matrix/unnamed/model.essence b/tests/custom/dotlt/matrix/unnamed/model.essence new file mode 100644 index 0000000000..93ab30b12f --- /dev/null +++ b/tests/custom/dotlt/matrix/unnamed/model.essence @@ -0,0 +1,9 @@ +letting e be new type of size 4 + +find i: matrix indexed by [int(1..2)] of e +find j: matrix indexed by [int(1..2)] of e + +such that + +i .<= j + diff --git a/tests/custom/dotlt/matrix/unnamed/run.sh b/tests/custom/dotlt/matrix/unnamed/run.sh new file mode 100755 index 0000000000..10ed17da89 --- /dev/null +++ b/tests/custom/dotlt/matrix/unnamed/run.sh @@ -0,0 +1,3 @@ +conjure solve --number-of-solutions=all --solutions-in-one-file --output-format=jsonstream *.essence +cat *.json | LC_ALL=C sort +rm -rf conjure-output *solutions* \ No newline at end of file diff --git a/tests/custom/dotlt/matrix/unnamed/stdout.expected b/tests/custom/dotlt/matrix/unnamed/stdout.expected new file mode 100644 index 0000000000..16000a3172 --- /dev/null +++ b/tests/custom/dotlt/matrix/unnamed/stdout.expected @@ -0,0 +1,144 @@ +Generating models for model.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Running minion for domain filtering. +Running solver: minion +Copying solution to: model.solutions +Copying solution to: model.solutions.json +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": {"1": "e_1", "2": "e_1"}, "j": {"1": "e_1", "2": "e_1"}} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": {"1": "e_1", "2": "e_1"}, "j": {"1": "e_1", "2": "e_2"}} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": {"1": "e_1", "2": "e_1"}, "j": {"1": "e_1", "2": "e_3"}} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": {"1": "e_1", "2": "e_1"}, "j": {"1": "e_1", "2": "e_4"}} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": {"1": "e_1", "2": "e_1"}, "j": {"1": "e_2", "2": "e_1"}} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": {"1": "e_1", "2": "e_1"}, "j": {"1": "e_2", "2": "e_2"}} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": {"1": "e_1", "2": "e_1"}, "j": {"1": "e_2", "2": "e_3"}} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": {"1": "e_1", "2": "e_1"}, "j": {"1": "e_2", "2": "e_4"}} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": {"1": "e_1", "2": "e_1"}, "j": {"1": "e_3", "2": "e_1"}} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": {"1": "e_1", "2": "e_1"}, "j": {"1": "e_3", "2": "e_2"}} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": {"1": "e_1", "2": "e_1"}, "j": {"1": "e_3", "2": "e_3"}} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": {"1": "e_1", "2": "e_1"}, "j": {"1": "e_3", "2": "e_4"}} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": {"1": "e_1", "2": "e_1"}, "j": {"1": "e_4", "2": "e_1"}} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": {"1": "e_1", "2": "e_1"}, "j": {"1": "e_4", "2": "e_2"}} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": {"1": "e_1", "2": "e_1"}, "j": {"1": "e_4", "2": "e_3"}} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": {"1": "e_1", "2": "e_1"}, "j": {"1": "e_4", "2": "e_4"}} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": {"1": "e_1", "2": "e_2"}, "j": {"1": "e_1", "2": "e_2"}} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": {"1": "e_1", "2": "e_2"}, "j": {"1": "e_1", "2": "e_3"}} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": {"1": "e_1", "2": "e_2"}, "j": {"1": "e_1", "2": "e_4"}} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": {"1": "e_1", "2": "e_2"}, "j": {"1": "e_2", "2": "e_1"}} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": {"1": "e_1", "2": "e_2"}, "j": {"1": "e_2", "2": "e_2"}} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": {"1": "e_1", "2": "e_2"}, "j": {"1": "e_2", "2": "e_3"}} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": {"1": "e_1", "2": "e_2"}, "j": {"1": "e_2", "2": "e_4"}} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": {"1": "e_1", "2": "e_2"}, "j": {"1": "e_3", "2": "e_1"}} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": {"1": "e_1", "2": "e_2"}, "j": {"1": "e_3", "2": "e_2"}} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": {"1": "e_1", "2": "e_2"}, "j": {"1": "e_3", "2": "e_3"}} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": {"1": "e_1", "2": "e_2"}, "j": {"1": "e_3", "2": "e_4"}} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": {"1": "e_1", "2": "e_2"}, "j": {"1": "e_4", "2": "e_1"}} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": {"1": "e_1", "2": "e_2"}, "j": {"1": "e_4", "2": "e_2"}} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": {"1": "e_1", "2": "e_2"}, "j": {"1": "e_4", "2": "e_3"}} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": {"1": "e_1", "2": "e_2"}, "j": {"1": "e_4", "2": "e_4"}} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": {"1": "e_1", "2": "e_3"}, "j": {"1": "e_1", "2": "e_3"}} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": {"1": "e_1", "2": "e_3"}, "j": {"1": "e_1", "2": "e_4"}} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": {"1": "e_1", "2": "e_3"}, "j": {"1": "e_2", "2": "e_1"}} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": {"1": "e_1", "2": "e_3"}, "j": {"1": "e_2", "2": "e_2"}} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": {"1": "e_1", "2": "e_3"}, "j": {"1": "e_2", "2": "e_3"}} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": {"1": "e_1", "2": "e_3"}, "j": {"1": "e_2", "2": "e_4"}} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": {"1": "e_1", "2": "e_3"}, "j": {"1": "e_3", "2": "e_1"}} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": {"1": "e_1", "2": "e_3"}, "j": {"1": "e_3", "2": "e_2"}} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": {"1": "e_1", "2": "e_3"}, "j": {"1": "e_3", "2": "e_3"}} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": {"1": "e_1", "2": "e_3"}, "j": {"1": "e_3", "2": "e_4"}} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": {"1": "e_1", "2": "e_3"}, "j": {"1": "e_4", "2": "e_1"}} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": {"1": "e_1", "2": "e_3"}, "j": {"1": "e_4", "2": "e_2"}} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": {"1": "e_1", "2": "e_3"}, "j": {"1": "e_4", "2": "e_3"}} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": {"1": "e_1", "2": "e_3"}, "j": {"1": "e_4", "2": "e_4"}} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": {"1": "e_1", "2": "e_4"}, "j": {"1": "e_1", "2": "e_4"}} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": {"1": "e_1", "2": "e_4"}, "j": {"1": "e_2", "2": "e_1"}} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": {"1": "e_1", "2": "e_4"}, "j": {"1": "e_2", "2": "e_2"}} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": {"1": "e_1", "2": "e_4"}, "j": {"1": "e_2", "2": "e_3"}} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": {"1": "e_1", "2": "e_4"}, "j": {"1": "e_2", "2": "e_4"}} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": {"1": "e_1", "2": "e_4"}, "j": {"1": "e_3", "2": "e_1"}} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": {"1": "e_1", "2": "e_4"}, "j": {"1": "e_3", "2": "e_2"}} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": {"1": "e_1", "2": "e_4"}, "j": {"1": "e_3", "2": "e_3"}} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": {"1": "e_1", "2": "e_4"}, "j": {"1": "e_3", "2": "e_4"}} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": {"1": "e_1", "2": "e_4"}, "j": {"1": "e_4", "2": "e_1"}} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": {"1": "e_1", "2": "e_4"}, "j": {"1": "e_4", "2": "e_2"}} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": {"1": "e_1", "2": "e_4"}, "j": {"1": "e_4", "2": "e_3"}} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": {"1": "e_1", "2": "e_4"}, "j": {"1": "e_4", "2": "e_4"}} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": {"1": "e_2", "2": "e_1"}, "j": {"1": "e_2", "2": "e_1"}} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": {"1": "e_2", "2": "e_1"}, "j": {"1": "e_2", "2": "e_2"}} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": {"1": "e_2", "2": "e_1"}, "j": {"1": "e_2", "2": "e_3"}} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": {"1": "e_2", "2": "e_1"}, "j": {"1": "e_2", "2": "e_4"}} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": {"1": "e_2", "2": "e_1"}, "j": {"1": "e_3", "2": "e_1"}} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": {"1": "e_2", "2": "e_1"}, "j": {"1": "e_3", "2": "e_2"}} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": {"1": "e_2", "2": "e_1"}, "j": {"1": "e_3", "2": "e_3"}} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": {"1": "e_2", "2": "e_1"}, "j": {"1": "e_3", "2": "e_4"}} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": {"1": "e_2", "2": "e_1"}, "j": {"1": "e_4", "2": "e_1"}} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": {"1": "e_2", "2": "e_1"}, "j": {"1": "e_4", "2": "e_2"}} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": {"1": "e_2", "2": "e_1"}, "j": {"1": "e_4", "2": "e_3"}} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": {"1": "e_2", "2": "e_1"}, "j": {"1": "e_4", "2": "e_4"}} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": {"1": "e_2", "2": "e_2"}, "j": {"1": "e_2", "2": "e_2"}} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": {"1": "e_2", "2": "e_2"}, "j": {"1": "e_2", "2": "e_3"}} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": {"1": "e_2", "2": "e_2"}, "j": {"1": "e_2", "2": "e_4"}} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": {"1": "e_2", "2": "e_2"}, "j": {"1": "e_3", "2": "e_1"}} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": {"1": "e_2", "2": "e_2"}, "j": {"1": "e_3", "2": "e_2"}} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": {"1": "e_2", "2": "e_2"}, "j": {"1": "e_3", "2": "e_3"}} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": {"1": "e_2", "2": "e_2"}, "j": {"1": "e_3", "2": "e_4"}} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": {"1": "e_2", "2": "e_2"}, "j": {"1": "e_4", "2": "e_1"}} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": {"1": "e_2", "2": "e_2"}, "j": {"1": "e_4", "2": "e_2"}} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": {"1": "e_2", "2": "e_2"}, "j": {"1": "e_4", "2": "e_3"}} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": {"1": "e_2", "2": "e_2"}, "j": {"1": "e_4", "2": "e_4"}} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": {"1": "e_2", "2": "e_3"}, "j": {"1": "e_2", "2": "e_3"}} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": {"1": "e_2", "2": "e_3"}, "j": {"1": "e_2", "2": "e_4"}} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": {"1": "e_2", "2": "e_3"}, "j": {"1": "e_3", "2": "e_1"}} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": {"1": "e_2", "2": "e_3"}, "j": {"1": "e_3", "2": "e_2"}} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": {"1": "e_2", "2": "e_3"}, "j": {"1": "e_3", "2": "e_3"}} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": {"1": "e_2", "2": "e_3"}, "j": {"1": "e_3", "2": "e_4"}} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": {"1": "e_2", "2": "e_3"}, "j": {"1": "e_4", "2": "e_1"}} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": {"1": "e_2", "2": "e_3"}, "j": {"1": "e_4", "2": "e_2"}} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": {"1": "e_2", "2": "e_3"}, "j": {"1": "e_4", "2": "e_3"}} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": {"1": "e_2", "2": "e_3"}, "j": {"1": "e_4", "2": "e_4"}} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": {"1": "e_2", "2": "e_4"}, "j": {"1": "e_2", "2": "e_4"}} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": {"1": "e_2", "2": "e_4"}, "j": {"1": "e_3", "2": "e_1"}} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": {"1": "e_2", "2": "e_4"}, "j": {"1": "e_3", "2": "e_2"}} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": {"1": "e_2", "2": "e_4"}, "j": {"1": "e_3", "2": "e_3"}} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": {"1": "e_2", "2": "e_4"}, "j": {"1": "e_3", "2": "e_4"}} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": {"1": "e_2", "2": "e_4"}, "j": {"1": "e_4", "2": "e_1"}} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": {"1": "e_2", "2": "e_4"}, "j": {"1": "e_4", "2": "e_2"}} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": {"1": "e_2", "2": "e_4"}, "j": {"1": "e_4", "2": "e_3"}} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": {"1": "e_2", "2": "e_4"}, "j": {"1": "e_4", "2": "e_4"}} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": {"1": "e_3", "2": "e_1"}, "j": {"1": "e_3", "2": "e_1"}} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": {"1": "e_3", "2": "e_1"}, "j": {"1": "e_3", "2": "e_2"}} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": {"1": "e_3", "2": "e_1"}, "j": {"1": "e_3", "2": "e_3"}} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": {"1": "e_3", "2": "e_1"}, "j": {"1": "e_3", "2": "e_4"}} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": {"1": "e_3", "2": "e_1"}, "j": {"1": "e_4", "2": "e_1"}} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": {"1": "e_3", "2": "e_1"}, "j": {"1": "e_4", "2": "e_2"}} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": {"1": "e_3", "2": "e_1"}, "j": {"1": "e_4", "2": "e_3"}} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": {"1": "e_3", "2": "e_1"}, "j": {"1": "e_4", "2": "e_4"}} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": {"1": "e_3", "2": "e_2"}, "j": {"1": "e_3", "2": "e_2"}} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": {"1": "e_3", "2": "e_2"}, "j": {"1": "e_3", "2": "e_3"}} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": {"1": "e_3", "2": "e_2"}, "j": {"1": "e_3", "2": "e_4"}} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": {"1": "e_3", "2": "e_2"}, "j": {"1": "e_4", "2": "e_1"}} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": {"1": "e_3", "2": "e_2"}, "j": {"1": "e_4", "2": "e_2"}} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": {"1": "e_3", "2": "e_2"}, "j": {"1": "e_4", "2": "e_3"}} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": {"1": "e_3", "2": "e_2"}, "j": {"1": "e_4", "2": "e_4"}} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": {"1": "e_3", "2": "e_3"}, "j": {"1": "e_3", "2": "e_3"}} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": {"1": "e_3", "2": "e_3"}, "j": {"1": "e_3", "2": "e_4"}} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": {"1": "e_3", "2": "e_3"}, "j": {"1": "e_4", "2": "e_1"}} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": {"1": "e_3", "2": "e_3"}, "j": {"1": "e_4", "2": "e_2"}} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": {"1": "e_3", "2": "e_3"}, "j": {"1": "e_4", "2": "e_3"}} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": {"1": "e_3", "2": "e_3"}, "j": {"1": "e_4", "2": "e_4"}} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": {"1": "e_3", "2": "e_4"}, "j": {"1": "e_3", "2": "e_4"}} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": {"1": "e_3", "2": "e_4"}, "j": {"1": "e_4", "2": "e_1"}} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": {"1": "e_3", "2": "e_4"}, "j": {"1": "e_4", "2": "e_2"}} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": {"1": "e_3", "2": "e_4"}, "j": {"1": "e_4", "2": "e_3"}} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": {"1": "e_3", "2": "e_4"}, "j": {"1": "e_4", "2": "e_4"}} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": {"1": "e_4", "2": "e_1"}, "j": {"1": "e_4", "2": "e_1"}} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": {"1": "e_4", "2": "e_1"}, "j": {"1": "e_4", "2": "e_2"}} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": {"1": "e_4", "2": "e_1"}, "j": {"1": "e_4", "2": "e_3"}} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": {"1": "e_4", "2": "e_1"}, "j": {"1": "e_4", "2": "e_4"}} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": {"1": "e_4", "2": "e_2"}, "j": {"1": "e_4", "2": "e_2"}} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": {"1": "e_4", "2": "e_2"}, "j": {"1": "e_4", "2": "e_3"}} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": {"1": "e_4", "2": "e_2"}, "j": {"1": "e_4", "2": "e_4"}} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": {"1": "e_4", "2": "e_3"}, "j": {"1": "e_4", "2": "e_3"}} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": {"1": "e_4", "2": "e_3"}, "j": {"1": "e_4", "2": "e_4"}} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": {"1": "e_4", "2": "e_4"}, "j": {"1": "e_4", "2": "e_4"}} diff --git a/tests/custom/dotlt/set/enum/model.essence b/tests/custom/dotlt/set/enum/model.essence new file mode 100644 index 0000000000..14b369e8fe --- /dev/null +++ b/tests/custom/dotlt/set/enum/model.essence @@ -0,0 +1,9 @@ +letting e be new type enum {e1,e2,e3} + +find i: set of e +find j: set of e + +such that + +i .<= j + diff --git a/tests/custom/dotlt/set/enum/run.sh b/tests/custom/dotlt/set/enum/run.sh new file mode 100755 index 0000000000..10ed17da89 --- /dev/null +++ b/tests/custom/dotlt/set/enum/run.sh @@ -0,0 +1,3 @@ +conjure solve --number-of-solutions=all --solutions-in-one-file --output-format=jsonstream *.essence +cat *.json | LC_ALL=C sort +rm -rf conjure-output *solutions* \ No newline at end of file diff --git a/tests/custom/dotlt/set/enum/stdout.expected b/tests/custom/dotlt/set/enum/stdout.expected new file mode 100644 index 0000000000..ecb819b09d --- /dev/null +++ b/tests/custom/dotlt/set/enum/stdout.expected @@ -0,0 +1,44 @@ +Generating models for model.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Running minion for domain filtering. +Running solver: minion +Copying solution to: model.solutions +Copying solution to: model.solutions.json +{"i": ["e1", "e2", "e3"], "j": ["e1", "e2", "e3"]} +{"i": ["e1", "e2", "e3"], "j": ["e1", "e2"]} +{"i": ["e1", "e2", "e3"], "j": ["e1", "e3"]} +{"i": ["e1", "e2", "e3"], "j": ["e1"]} +{"i": ["e1", "e2", "e3"], "j": ["e2", "e3"]} +{"i": ["e1", "e2", "e3"], "j": ["e2"]} +{"i": ["e1", "e2", "e3"], "j": ["e3"]} +{"i": ["e1", "e2", "e3"], "j": []} +{"i": ["e1", "e2"], "j": ["e1", "e2"]} +{"i": ["e1", "e2"], "j": ["e1", "e3"]} +{"i": ["e1", "e2"], "j": ["e1"]} +{"i": ["e1", "e2"], "j": ["e2", "e3"]} +{"i": ["e1", "e2"], "j": ["e2"]} +{"i": ["e1", "e2"], "j": ["e3"]} +{"i": ["e1", "e2"], "j": []} +{"i": ["e1", "e3"], "j": ["e1", "e3"]} +{"i": ["e1", "e3"], "j": ["e1"]} +{"i": ["e1", "e3"], "j": ["e2", "e3"]} +{"i": ["e1", "e3"], "j": ["e2"]} +{"i": ["e1", "e3"], "j": ["e3"]} +{"i": ["e1", "e3"], "j": []} +{"i": ["e1"], "j": ["e1"]} +{"i": ["e1"], "j": ["e2", "e3"]} +{"i": ["e1"], "j": ["e2"]} +{"i": ["e1"], "j": ["e3"]} +{"i": ["e1"], "j": []} +{"i": ["e2", "e3"], "j": ["e2", "e3"]} +{"i": ["e2", "e3"], "j": ["e2"]} +{"i": ["e2", "e3"], "j": ["e3"]} +{"i": ["e2", "e3"], "j": []} +{"i": ["e2"], "j": ["e2"]} +{"i": ["e2"], "j": ["e3"]} +{"i": ["e2"], "j": []} +{"i": ["e3"], "j": ["e3"]} +{"i": ["e3"], "j": []} +{"i": [], "j": []} diff --git a/tests/custom/dotlt/set/int/model.essence b/tests/custom/dotlt/set/int/model.essence new file mode 100644 index 0000000000..9c779a7c4d --- /dev/null +++ b/tests/custom/dotlt/set/int/model.essence @@ -0,0 +1,7 @@ +find i: set of int(1..3) +find j: set of int(1..3) + +such that + +i .<= j + diff --git a/tests/custom/dotlt/set/int/run.sh b/tests/custom/dotlt/set/int/run.sh new file mode 100755 index 0000000000..10ed17da89 --- /dev/null +++ b/tests/custom/dotlt/set/int/run.sh @@ -0,0 +1,3 @@ +conjure solve --number-of-solutions=all --solutions-in-one-file --output-format=jsonstream *.essence +cat *.json | LC_ALL=C sort +rm -rf conjure-output *solutions* \ No newline at end of file diff --git a/tests/custom/dotlt/set/int/stdout.expected b/tests/custom/dotlt/set/int/stdout.expected new file mode 100644 index 0000000000..ec78bd6e2a --- /dev/null +++ b/tests/custom/dotlt/set/int/stdout.expected @@ -0,0 +1,44 @@ +Generating models for model.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Running minion for domain filtering. +Running solver: minion +Copying solution to: model.solutions +Copying solution to: model.solutions.json +{"i": [1, 2, 3], "j": [1, 2, 3]} +{"i": [1, 2, 3], "j": [1, 2]} +{"i": [1, 2, 3], "j": [1, 3]} +{"i": [1, 2, 3], "j": [1]} +{"i": [1, 2, 3], "j": [2, 3]} +{"i": [1, 2, 3], "j": [2]} +{"i": [1, 2, 3], "j": [3]} +{"i": [1, 2, 3], "j": []} +{"i": [1, 2], "j": [1, 2]} +{"i": [1, 2], "j": [1, 3]} +{"i": [1, 2], "j": [1]} +{"i": [1, 2], "j": [2, 3]} +{"i": [1, 2], "j": [2]} +{"i": [1, 2], "j": [3]} +{"i": [1, 2], "j": []} +{"i": [1, 3], "j": [1, 3]} +{"i": [1, 3], "j": [1]} +{"i": [1, 3], "j": [2, 3]} +{"i": [1, 3], "j": [2]} +{"i": [1, 3], "j": [3]} +{"i": [1, 3], "j": []} +{"i": [1], "j": [1]} +{"i": [1], "j": [2, 3]} +{"i": [1], "j": [2]} +{"i": [1], "j": [3]} +{"i": [1], "j": []} +{"i": [2, 3], "j": [2, 3]} +{"i": [2, 3], "j": [2]} +{"i": [2, 3], "j": [3]} +{"i": [2, 3], "j": []} +{"i": [2], "j": [2]} +{"i": [2], "j": [3]} +{"i": [2], "j": []} +{"i": [3], "j": [3]} +{"i": [3], "j": []} +{"i": [], "j": []} diff --git a/tests/custom/dotlt/set/unnamed/model.essence b/tests/custom/dotlt/set/unnamed/model.essence new file mode 100644 index 0000000000..56e7db6898 --- /dev/null +++ b/tests/custom/dotlt/set/unnamed/model.essence @@ -0,0 +1,9 @@ +letting e be new type of size 4 + +find i: set of e +find j: set of e + +such that + +i .<= j + diff --git a/tests/custom/dotlt/set/unnamed/run.sh b/tests/custom/dotlt/set/unnamed/run.sh new file mode 100755 index 0000000000..10ed17da89 --- /dev/null +++ b/tests/custom/dotlt/set/unnamed/run.sh @@ -0,0 +1,3 @@ +conjure solve --number-of-solutions=all --solutions-in-one-file --output-format=jsonstream *.essence +cat *.json | LC_ALL=C sort +rm -rf conjure-output *solutions* \ No newline at end of file diff --git a/tests/custom/dotlt/set/unnamed/stdout.expected b/tests/custom/dotlt/set/unnamed/stdout.expected new file mode 100644 index 0000000000..b63b73e417 --- /dev/null +++ b/tests/custom/dotlt/set/unnamed/stdout.expected @@ -0,0 +1,144 @@ +Generating models for model.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Running minion for domain filtering. +Running solver: minion +Copying solution to: model.solutions +Copying solution to: model.solutions.json +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": ["e_1", "e_2", "e_3", "e_4"], "j": ["e_1", "e_2", "e_3", "e_4"]} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": ["e_1", "e_2", "e_3", "e_4"], "j": ["e_1", "e_2", "e_3"]} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": ["e_1", "e_2", "e_3", "e_4"], "j": ["e_1", "e_2", "e_4"]} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": ["e_1", "e_2", "e_3", "e_4"], "j": ["e_1", "e_2"]} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": ["e_1", "e_2", "e_3", "e_4"], "j": ["e_1", "e_3", "e_4"]} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": ["e_1", "e_2", "e_3", "e_4"], "j": ["e_1", "e_3"]} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": ["e_1", "e_2", "e_3", "e_4"], "j": ["e_1", "e_4"]} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": ["e_1", "e_2", "e_3", "e_4"], "j": ["e_1"]} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": ["e_1", "e_2", "e_3", "e_4"], "j": ["e_2", "e_3", "e_4"]} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": ["e_1", "e_2", "e_3", "e_4"], "j": ["e_2", "e_3"]} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": ["e_1", "e_2", "e_3", "e_4"], "j": ["e_2", "e_4"]} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": ["e_1", "e_2", "e_3", "e_4"], "j": ["e_2"]} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": ["e_1", "e_2", "e_3", "e_4"], "j": ["e_3", "e_4"]} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": ["e_1", "e_2", "e_3", "e_4"], "j": ["e_3"]} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": ["e_1", "e_2", "e_3", "e_4"], "j": ["e_4"]} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": ["e_1", "e_2", "e_3", "e_4"], "j": []} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": ["e_1", "e_2", "e_3"], "j": ["e_1", "e_2", "e_3"]} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": ["e_1", "e_2", "e_3"], "j": ["e_1", "e_2", "e_4"]} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": ["e_1", "e_2", "e_3"], "j": ["e_1", "e_2"]} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": ["e_1", "e_2", "e_3"], "j": ["e_1", "e_3", "e_4"]} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": ["e_1", "e_2", "e_3"], "j": ["e_1", "e_3"]} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": ["e_1", "e_2", "e_3"], "j": ["e_1", "e_4"]} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": ["e_1", "e_2", "e_3"], "j": ["e_1"]} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": ["e_1", "e_2", "e_3"], "j": ["e_2", "e_3", "e_4"]} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": ["e_1", "e_2", "e_3"], "j": ["e_2", "e_3"]} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": ["e_1", "e_2", "e_3"], "j": ["e_2", "e_4"]} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": ["e_1", "e_2", "e_3"], "j": ["e_2"]} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": ["e_1", "e_2", "e_3"], "j": ["e_3", "e_4"]} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": ["e_1", "e_2", "e_3"], "j": ["e_3"]} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": ["e_1", "e_2", "e_3"], "j": ["e_4"]} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": ["e_1", "e_2", "e_3"], "j": []} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": ["e_1", "e_2", "e_4"], "j": ["e_1", "e_2", "e_4"]} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": ["e_1", "e_2", "e_4"], "j": ["e_1", "e_2"]} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": ["e_1", "e_2", "e_4"], "j": ["e_1", "e_3", "e_4"]} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": ["e_1", "e_2", "e_4"], "j": ["e_1", "e_3"]} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": ["e_1", "e_2", "e_4"], "j": ["e_1", "e_4"]} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": ["e_1", "e_2", "e_4"], "j": ["e_1"]} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": ["e_1", "e_2", "e_4"], "j": ["e_2", "e_3", "e_4"]} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": ["e_1", "e_2", "e_4"], "j": ["e_2", "e_3"]} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": ["e_1", "e_2", "e_4"], "j": ["e_2", "e_4"]} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": ["e_1", "e_2", "e_4"], "j": ["e_2"]} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": ["e_1", "e_2", "e_4"], "j": ["e_3", "e_4"]} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": ["e_1", "e_2", "e_4"], "j": ["e_3"]} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": ["e_1", "e_2", "e_4"], "j": ["e_4"]} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": ["e_1", "e_2", "e_4"], "j": []} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": ["e_1", "e_2"], "j": ["e_1", "e_2"]} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": ["e_1", "e_2"], "j": ["e_1", "e_3", "e_4"]} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": ["e_1", "e_2"], "j": ["e_1", "e_3"]} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": ["e_1", "e_2"], "j": ["e_1", "e_4"]} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": ["e_1", "e_2"], "j": ["e_1"]} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": ["e_1", "e_2"], "j": ["e_2", "e_3", "e_4"]} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": ["e_1", "e_2"], "j": ["e_2", "e_3"]} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": ["e_1", "e_2"], "j": ["e_2", "e_4"]} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": ["e_1", "e_2"], "j": ["e_2"]} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": ["e_1", "e_2"], "j": ["e_3", "e_4"]} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": ["e_1", "e_2"], "j": ["e_3"]} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": ["e_1", "e_2"], "j": ["e_4"]} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": ["e_1", "e_2"], "j": []} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": ["e_1", "e_3", "e_4"], "j": ["e_1", "e_3", "e_4"]} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": ["e_1", "e_3", "e_4"], "j": ["e_1", "e_3"]} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": ["e_1", "e_3", "e_4"], "j": ["e_1", "e_4"]} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": ["e_1", "e_3", "e_4"], "j": ["e_1"]} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": ["e_1", "e_3", "e_4"], "j": ["e_2", "e_3", "e_4"]} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": ["e_1", "e_3", "e_4"], "j": ["e_2", "e_3"]} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": ["e_1", "e_3", "e_4"], "j": ["e_2", "e_4"]} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": ["e_1", "e_3", "e_4"], "j": ["e_2"]} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": ["e_1", "e_3", "e_4"], "j": ["e_3", "e_4"]} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": ["e_1", "e_3", "e_4"], "j": ["e_3"]} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": ["e_1", "e_3", "e_4"], "j": ["e_4"]} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": ["e_1", "e_3", "e_4"], "j": []} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": ["e_1", "e_3"], "j": ["e_1", "e_3"]} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": ["e_1", "e_3"], "j": ["e_1", "e_4"]} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": ["e_1", "e_3"], "j": ["e_1"]} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": ["e_1", "e_3"], "j": ["e_2", "e_3", "e_4"]} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": ["e_1", "e_3"], "j": ["e_2", "e_3"]} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": ["e_1", "e_3"], "j": ["e_2", "e_4"]} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": ["e_1", "e_3"], "j": ["e_2"]} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": ["e_1", "e_3"], "j": ["e_3", "e_4"]} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": ["e_1", "e_3"], "j": ["e_3"]} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": ["e_1", "e_3"], "j": ["e_4"]} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": ["e_1", "e_3"], "j": []} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": ["e_1", "e_4"], "j": ["e_1", "e_4"]} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": ["e_1", "e_4"], "j": ["e_1"]} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": ["e_1", "e_4"], "j": ["e_2", "e_3", "e_4"]} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": ["e_1", "e_4"], "j": ["e_2", "e_3"]} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": ["e_1", "e_4"], "j": ["e_2", "e_4"]} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": ["e_1", "e_4"], "j": ["e_2"]} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": ["e_1", "e_4"], "j": ["e_3", "e_4"]} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": ["e_1", "e_4"], "j": ["e_3"]} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": ["e_1", "e_4"], "j": ["e_4"]} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": ["e_1", "e_4"], "j": []} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": ["e_1"], "j": ["e_1"]} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": ["e_1"], "j": ["e_2", "e_3", "e_4"]} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": ["e_1"], "j": ["e_2", "e_3"]} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": ["e_1"], "j": ["e_2", "e_4"]} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": ["e_1"], "j": ["e_2"]} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": ["e_1"], "j": ["e_3", "e_4"]} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": ["e_1"], "j": ["e_3"]} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": ["e_1"], "j": ["e_4"]} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": ["e_1"], "j": []} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": ["e_2", "e_3", "e_4"], "j": ["e_2", "e_3", "e_4"]} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": ["e_2", "e_3", "e_4"], "j": ["e_2", "e_3"]} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": ["e_2", "e_3", "e_4"], "j": ["e_2", "e_4"]} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": ["e_2", "e_3", "e_4"], "j": ["e_2"]} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": ["e_2", "e_3", "e_4"], "j": ["e_3", "e_4"]} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": ["e_2", "e_3", "e_4"], "j": ["e_3"]} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": ["e_2", "e_3", "e_4"], "j": ["e_4"]} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": ["e_2", "e_3", "e_4"], "j": []} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": ["e_2", "e_3"], "j": ["e_2", "e_3"]} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": ["e_2", "e_3"], "j": ["e_2", "e_4"]} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": ["e_2", "e_3"], "j": ["e_2"]} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": ["e_2", "e_3"], "j": ["e_3", "e_4"]} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": ["e_2", "e_3"], "j": ["e_3"]} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": ["e_2", "e_3"], "j": ["e_4"]} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": ["e_2", "e_3"], "j": []} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": ["e_2", "e_4"], "j": ["e_2", "e_4"]} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": ["e_2", "e_4"], "j": ["e_2"]} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": ["e_2", "e_4"], "j": ["e_3", "e_4"]} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": ["e_2", "e_4"], "j": ["e_3"]} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": ["e_2", "e_4"], "j": ["e_4"]} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": ["e_2", "e_4"], "j": []} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": ["e_2"], "j": ["e_2"]} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": ["e_2"], "j": ["e_3", "e_4"]} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": ["e_2"], "j": ["e_3"]} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": ["e_2"], "j": ["e_4"]} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": ["e_2"], "j": []} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": ["e_3", "e_4"], "j": ["e_3", "e_4"]} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": ["e_3", "e_4"], "j": ["e_3"]} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": ["e_3", "e_4"], "j": ["e_4"]} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": ["e_3", "e_4"], "j": []} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": ["e_3"], "j": ["e_3"]} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": ["e_3"], "j": ["e_4"]} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": ["e_3"], "j": []} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": ["e_4"], "j": ["e_4"]} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": ["e_4"], "j": []} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": [], "j": []} diff --git a/tests/custom/dotlt/tuple/enum/model.essence b/tests/custom/dotlt/tuple/enum/model.essence new file mode 100644 index 0000000000..ef232bf311 --- /dev/null +++ b/tests/custom/dotlt/tuple/enum/model.essence @@ -0,0 +1,9 @@ +letting e be new type enum {e1,e2,e3} + +find i: e +find j: e + +such that + +(i,i) .<= (j,j) + diff --git a/tests/custom/dotlt/tuple/enum/run.sh b/tests/custom/dotlt/tuple/enum/run.sh new file mode 100755 index 0000000000..10ed17da89 --- /dev/null +++ b/tests/custom/dotlt/tuple/enum/run.sh @@ -0,0 +1,3 @@ +conjure solve --number-of-solutions=all --solutions-in-one-file --output-format=jsonstream *.essence +cat *.json | LC_ALL=C sort +rm -rf conjure-output *solutions* \ No newline at end of file diff --git a/tests/custom/dotlt/tuple/enum/stdout.expected b/tests/custom/dotlt/tuple/enum/stdout.expected new file mode 100644 index 0000000000..57b7795950 --- /dev/null +++ b/tests/custom/dotlt/tuple/enum/stdout.expected @@ -0,0 +1,14 @@ +Generating models for model.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Running minion for domain filtering. +Running solver: minion +Copying solution to: model.solutions +Copying solution to: model.solutions.json +{"i": "e1", "j": "e1"} +{"i": "e1", "j": "e2"} +{"i": "e1", "j": "e3"} +{"i": "e2", "j": "e2"} +{"i": "e2", "j": "e3"} +{"i": "e3", "j": "e3"} diff --git a/tests/custom/dotlt/tuple/int/model.essence b/tests/custom/dotlt/tuple/int/model.essence new file mode 100644 index 0000000000..5d1e556376 --- /dev/null +++ b/tests/custom/dotlt/tuple/int/model.essence @@ -0,0 +1,7 @@ +find i: int(1..3) +find j: int(1..3) + +such that + +(i,i) .<= (j,j) + diff --git a/tests/custom/dotlt/tuple/int/run.sh b/tests/custom/dotlt/tuple/int/run.sh new file mode 100755 index 0000000000..10ed17da89 --- /dev/null +++ b/tests/custom/dotlt/tuple/int/run.sh @@ -0,0 +1,3 @@ +conjure solve --number-of-solutions=all --solutions-in-one-file --output-format=jsonstream *.essence +cat *.json | LC_ALL=C sort +rm -rf conjure-output *solutions* \ No newline at end of file diff --git a/tests/custom/dotlt/tuple/int/stdout.expected b/tests/custom/dotlt/tuple/int/stdout.expected new file mode 100644 index 0000000000..38f48fb5e6 --- /dev/null +++ b/tests/custom/dotlt/tuple/int/stdout.expected @@ -0,0 +1,14 @@ +Generating models for model.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Running minion for domain filtering. +Running solver: minion +Copying solution to: model.solutions +Copying solution to: model.solutions.json +{"i": 1, "j": 1} +{"i": 1, "j": 2} +{"i": 1, "j": 3} +{"i": 2, "j": 2} +{"i": 2, "j": 3} +{"i": 3, "j": 3} diff --git a/tests/custom/dotlt/tuple/unnamed/model.essence b/tests/custom/dotlt/tuple/unnamed/model.essence new file mode 100644 index 0000000000..a256ceebcd --- /dev/null +++ b/tests/custom/dotlt/tuple/unnamed/model.essence @@ -0,0 +1,9 @@ +letting e be new type of size 4 + +find i: e +find j: e + +such that + +(i,i) .<= (j,j) + diff --git a/tests/custom/dotlt/tuple/unnamed/run.sh b/tests/custom/dotlt/tuple/unnamed/run.sh new file mode 100755 index 0000000000..10ed17da89 --- /dev/null +++ b/tests/custom/dotlt/tuple/unnamed/run.sh @@ -0,0 +1,3 @@ +conjure solve --number-of-solutions=all --solutions-in-one-file --output-format=jsonstream *.essence +cat *.json | LC_ALL=C sort +rm -rf conjure-output *solutions* \ No newline at end of file diff --git a/tests/custom/dotlt/tuple/unnamed/stdout.expected b/tests/custom/dotlt/tuple/unnamed/stdout.expected new file mode 100644 index 0000000000..276da5a986 --- /dev/null +++ b/tests/custom/dotlt/tuple/unnamed/stdout.expected @@ -0,0 +1,18 @@ +Generating models for model.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Running minion for domain filtering. +Running solver: minion +Copying solution to: model.solutions +Copying solution to: model.solutions.json +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": "e_1", "j": "e_1"} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": "e_1", "j": "e_2"} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": "e_1", "j": "e_3"} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": "e_1", "j": "e_4"} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": "e_2", "j": "e_2"} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": "e_2", "j": "e_3"} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": "e_2", "j": "e_4"} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": "e_3", "j": "e_3"} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": "e_3", "j": "e_4"} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": "e_4", "j": "e_4"} From 960b806a615a7c67cf4ed6bc0a126fad66806e52 Mon Sep 17 00:00:00 2001 From: Chris Jefferson Date: Fri, 12 Apr 2024 17:27:49 +0800 Subject: [PATCH 160/229] Handle invalid permutation application --- src/Conjure/Rules/Horizontal/Permutation.hs | 4 +++- 1 file changed, 3 insertions(+), 1 deletion(-) diff --git a/src/Conjure/Rules/Horizontal/Permutation.hs b/src/Conjure/Rules/Horizontal/Permutation.hs index e0d89ce926..234166afe9 100644 --- a/src/Conjure/Rules/Horizontal/Permutation.hs +++ b/src/Conjure/Rules/Horizontal/Permutation.hs @@ -2,6 +2,7 @@ module Conjure.Rules.Horizontal.Permutation where import Conjure.Rules.Import import Conjure.Util.Permutation (size, toCycles, fromCycles, toFunction) +import Conjure.Rules.DontCare rule_Cardinality_Literal :: Rule rule_Cardinality_Literal = "permutation-cardinality-literal" `namedRule` theRule where @@ -151,10 +152,11 @@ rule_Image_Literal = "permutation-image-literal" `namedRule` theRule where (fromInt (fromIntegral (length srtdel))) matLit = make matrixLiteral (TypeMatrix (TypeInt TagInt) inner) matIdx ([ [essence| &i |] ] ++ (f <$> srtdel)) + minval <- minimum_int_value_in_domain i return ( "Horizontal rule for permutation literal application to a single value (image), AsFunction representation" , do - return [essence| &matLit[&indexr] |] + return [essence| catchUndef(&matLit[&indexr], &minval) |] ) else failDoc $ "Permutation applied to a type its inner does not unify with" From 707836cf6346e2af89142ea46f78b97129aadfc5 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?=C3=96zg=C3=BCr=20Akg=C3=BCn?= Date: Fri, 12 Apr 2024 10:43:28 +0100 Subject: [PATCH 161/229] fix how the bubble expression is generated for complete unnamed symmetry breaking --- src/Conjure/UI/Model.hs | 43 +++++++++++++++-------------------------- 1 file changed, 16 insertions(+), 27 deletions(-) diff --git a/src/Conjure/UI/Model.hs b/src/Conjure/UI/Model.hs index f0264d1e1e..623d85395d 100644 --- a/src/Conjure/UI/Model.hs +++ b/src/Conjure/UI/Model.hs @@ -363,9 +363,7 @@ remainingWIP :: ModelWIP -> m [Question] remainingWIP config (StartOver model) - | Just modelZipper <- mkModelZipper model = do - qs <- remaining config modelZipper (mInfo model) - return qs + | Just modelZipper <- mkModelZipper model = remaining config modelZipper (mInfo model) | otherwise = return [] remainingWIP config wip@(TryThisFirst modelZipper info) = do qs <- remaining config modelZipper info @@ -927,7 +925,7 @@ updateDeclarations model = do let usedAfter :: Bool usedAfter = nbUses nm afters > 0 - + nbComplexLiterals :: Int nbComplexLiterals = sum [ case y of @@ -983,7 +981,7 @@ checkIfAllRefined m | Just modelZipper <- mkModelZipper m = do -- we let returnMsg x = return $ "" : ("Not refined:" <+> pretty (hole x)) - <+> stringToDoc(show (hole x)) + <+> stringToDoc (show (hole x)) : [ nest 4 ("Context #" <> pretty i <> ":" <+> pretty c) | (i, c) <- zip allNats (tail (ascendants x)) ] @@ -994,7 +992,7 @@ checkIfAllRefined m | Just modelZipper <- mkModelZipper m = do -- we | not (isPrimitiveDomain dom) -> return $ "" : ("Not refined:" <+> pretty (hole x)) - <+> stringToDoc(show (hole x)) + <+> stringToDoc (show (hole x)) : ("Domain :" <+> pretty dom) : [ nest 4 ("Context #" <> pretty i <> ":" <+> pretty c) | (i, c) <- zip allNats (tail (ascendants x)) @@ -1036,10 +1034,10 @@ checkIfAllRefined m | Just modelZipper <- mkModelZipper m = do -- we ] [essence| &_ .< &_ |] -> return ["", ("Not refined:" <+> pretty (hole x)) - <+> stringToDoc(show (hole x))] + <+> stringToDoc (show (hole x))] [essence| &_ .<= &_ |] -> return ["", ("Not refined:" <+> pretty (hole x)) - <+> stringToDoc(show (hole x))] + <+> stringToDoc (show (hole x))] _ -> return [] unless (null fails) (bug (vcat fails)) return m @@ -1212,12 +1210,12 @@ lexSingletons model = do case (matchSingleton l, matchSingleton r) of (Nothing, Nothing) -> return [essence| &l return [essence| &ls < &rs |] - _ -> bug $ "lexSingleton: match inconsistent" + _ -> bug $ "lexSingleton: match inconsistent" onExpr [essence| &l <=lex &r |] = case (matchSingleton l, matchSingleton r) of (Nothing, Nothing) -> return [essence| &l <=lex &r |] (Just ls, Just rs) -> return [essence| &ls <= &rs |] - _ -> bug $ "lexSingleton: match inconsistent" + _ -> bug $ "lexSingleton: match inconsistent" onExpr x = return x matchSingleton :: (?typeCheckerMode :: TypeCheckerMode) => Expression -> Maybe Expression @@ -1547,7 +1545,7 @@ horizontalRules = , Horizontal.Permutation.rule_Defined_Literal , Horizontal.Permutation.rule_Image_Literal , Horizontal.Permutation.rule_In - , Horizontal.Permutation.rule_Permutation_Inverse + , Horizontal.Permutation.rule_Permutation_Inverse @@ -2126,7 +2124,7 @@ rule_Flatten_Lex = "flatten-lex" `namedRule` theRule where return ( "Flatten Lex Lt" , return [essence| &fa <=lex &fb |] ) - theRule _ = na "rule_Flatten_Lex" + theRule _ = na "rule_Flatten_Lex" reject_flat a b = do ta <- typeOf a tb <- typeOf b @@ -2136,14 +2134,14 @@ rule_Flatten_Lex = "flatten-lex" `namedRule` theRule where (TypeMatrix TypeBool TypeBool, _) -> na "rule_Flatten_Lex" (TypeList TypeInt{}, _) -> - na "rule_Flatten_Lex" + na "rule_Flatten_Lex" (TypeMatrix TypeInt{} TypeInt{}, _) -> na "rule_Flatten_Lex" (TypeList TypeBool, _) -> - na "rule_Flatten_Lex" + na "rule_Flatten_Lex" (TypeMatrix TypeInt{} TypeBool, _) -> na "rule_Flatten_Lex" - _ -> return () + _ -> return () flatten a = do ta <- typeOf a @@ -2870,13 +2868,6 @@ addUnnamedSymmetryBreaking mode model = do let applied = buildPermutationChain ps vars in [essence| transform(&p, &applied) |] - nestInBubbles :: Expression -> Int -> [(Expression,Statement)] -> Expression -> Expression - nestInBubbles _ _ [] expr = expr - nestInBubbles modl i (fv:auxVars) expr = - let v = fst fv - ii = fromInt (fromIntegral i) - in WithLocals [essence| &modl[&ii] .<= &v |] (AuxiliaryVars ((snd fv):[SuchThat [nestInBubbles modl (i + 1) auxVars expr]])) - combinedPermApply auxSuffix perms = case quickOrComplete of USBQuick -> @@ -2885,9 +2876,7 @@ addUnnamedSymmetryBreaking mode model = do USBComplete -> let applied = buildPermutationChain perms varsTuple thisAuxTuple = mkAuxTuple auxSuffix - dVars = map fst (allDecVarsAux auxSuffix) - in nestInBubbles varsTuple 1 (zip dVars newDecls) - [essence| &thisAuxTuple = &applied |] + in WithLocals [essence| &varsTuple .<= &thisAuxTuple |] $ AuxiliaryVars (newDecls ++ [ SuchThat [ [essence| &thisAuxTuple = &applied |] ] ]) mkGenerator_Consecutive _ _ [] = bug "must have at least one unnamed type" mkGenerator_Consecutive auxSuffix perms [(u, uSize)] = do @@ -2966,10 +2955,10 @@ addUnnamedSymmetryBreaking mode model = do newCons <- case independentlyOrAltogether of USBIndependently -> do - xs <- (sequence + xs <- sequence [ mkGenerator uName [] [(u, uSize)] | (u@(DomainReference uName _), uSize) <- allUnnamedTypes - ]) + ] return [SuchThat xs] USBAltogether -> do cons <- mkGenerator "all" [] allUnnamedTypes From 94be5ba2a83ad012c8aaa010d183e114e819ff19 Mon Sep 17 00:00:00 2001 From: Chris Jefferson Date: Fri, 12 Apr 2024 17:28:04 +0800 Subject: [PATCH 162/229] Add symmetry tests --- .../symmetry/basic/one-var/model.essence | 3 + tests/custom/symmetry/basic/one-var/run.sh | 10 + .../symmetry/basic/one-var/stdout.expected | 181 ++++++++++++++++ .../symmetry/basic/two-type/model.essence | 5 + tests/custom/symmetry/basic/two-type/run.sh | 10 + .../symmetry/basic/two-type/stdout.expected | 90 ++++++++ .../symmetry/basic/two-var/model.essence | 4 + tests/custom/symmetry/basic/two-var/run.sh | 10 + .../symmetry/basic/two-var/stdout.expected | 203 ++++++++++++++++++ 9 files changed, 516 insertions(+) create mode 100644 tests/custom/symmetry/basic/one-var/model.essence create mode 100755 tests/custom/symmetry/basic/one-var/run.sh create mode 100644 tests/custom/symmetry/basic/one-var/stdout.expected create mode 100644 tests/custom/symmetry/basic/two-type/model.essence create mode 100755 tests/custom/symmetry/basic/two-type/run.sh create mode 100644 tests/custom/symmetry/basic/two-type/stdout.expected create mode 100644 tests/custom/symmetry/basic/two-var/model.essence create mode 100755 tests/custom/symmetry/basic/two-var/run.sh create mode 100644 tests/custom/symmetry/basic/two-var/stdout.expected diff --git a/tests/custom/symmetry/basic/one-var/model.essence b/tests/custom/symmetry/basic/one-var/model.essence new file mode 100644 index 0000000000..0d4da834f3 --- /dev/null +++ b/tests/custom/symmetry/basic/one-var/model.essence @@ -0,0 +1,3 @@ +letting e be new type of size 4 + +find i: e \ No newline at end of file diff --git a/tests/custom/symmetry/basic/one-var/run.sh b/tests/custom/symmetry/basic/one-var/run.sh new file mode 100755 index 0000000000..0ca7a7af18 --- /dev/null +++ b/tests/custom/symmetry/basic/one-var/run.sh @@ -0,0 +1,10 @@ +for sym in Quick Complete; do + for amount in Consecutive AllPairs AllPermutations; do + for combine in Independently Altogether; do + echo $sym-$amount-$combine + conjure solve --number-of-solutions=all --solutions-in-one-file --output-format=jsonstream --unnamed-symmetry-breaking=$sym-$amount-$combine *.essence 2>&1 + cat *.json | LC_ALL=C sort + rm -rf conjure-output *solutions* + done + done +done \ No newline at end of file diff --git a/tests/custom/symmetry/basic/one-var/stdout.expected b/tests/custom/symmetry/basic/one-var/stdout.expected new file mode 100644 index 0000000000..7b7d184068 --- /dev/null +++ b/tests/custom/symmetry/basic/one-var/stdout.expected @@ -0,0 +1,181 @@ +Quick-Consecutive-Independently +Using cached models. +Savile Row: model000001.eprime +Running minion for domain filtering. +Running solver: minion +Copying solution to: model.solutions +Copying solution to: model.solutions.json +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": "e_1"} +Quick-Consecutive-Altogether +Adding the following unnamed symmetry breaking constraints: + such that + and([tuple (i) .<= + transform(permutation((q1, succ(q1))), tuple (i)) + | q1 : e, q1 < 4]) +Generating models for model.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Running minion for domain filtering. +Running solver: minion +Copying solution to: model.solutions +Copying solution to: model.solutions.json +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": "e_1"} +Quick-AllPairs-Independently +Adding the following unnamed symmetry breaking constraints: + such that + and([tuple (i) .<= transform(permutation((q1, q2)), tuple (i)) + | q1 : e, q2 : e, q1 < q2]) +Generating models for model.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Running minion for domain filtering. +Running solver: minion +Copying solution to: model.solutions +Copying solution to: model.solutions.json +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": "e_1"} +Quick-AllPairs-Altogether +Adding the following unnamed symmetry breaking constraints: + such that + and([tuple (i) .<= transform(permutation((q1, q2)), tuple (i)) + | q1 : e, q2 : e, q1 < q2]) +Generating models for model.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Running minion for domain filtering. +Running solver: minion +Copying solution to: model.solutions +Copying solution to: model.solutions.json +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": "e_1"} +Quick-AllPermutations-Independently +Adding the following unnamed symmetry breaking constraints: + such that + and([tuple (i) .<= transform(q1, tuple (i)) + | q1 : permutation of e]) +Generating models for model.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Running minion for domain filtering. +Running solver: minion +Copying solution to: model.solutions +Copying solution to: model.solutions.json +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": "e_1"} +Quick-AllPermutations-Altogether +Adding the following unnamed symmetry breaking constraints: + such that + and([tuple (i) .<= transform(q1, tuple (i)) + | q1 : permutation of e]) +Generating models for model.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Running minion for domain filtering. +Running solver: minion +Copying solution to: model.solutions +Copying solution to: model.solutions.json +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": "e_1"} +Complete-Consecutive-Independently +Adding the following unnamed symmetry breaking constraints: + such that + and([{ tuple (i) .<= tuple (i_auxFor_e) + @ find i_auxFor_e: e + such that + tuple (i_auxFor_e) = + transform(permutation((q1, succ(q1))), tuple (i)) + } | q1 : e, q1 < 4]) +Generating models for model.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Running minion for domain filtering. +Running solver: minion +Copying solution to: model.solutions +Copying solution to: model.solutions.json +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": "e_1"} +Complete-Consecutive-Altogether +Adding the following unnamed symmetry breaking constraints: + such that + and([{ tuple (i) .<= tuple (i_auxFor_all) + @ find i_auxFor_all: e + such that + tuple (i_auxFor_all) = + transform(permutation((q1, succ(q1))), tuple (i)) + } | q1 : e, q1 < 4]) +Generating models for model.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Running minion for domain filtering. +Running solver: minion +Copying solution to: model.solutions +Copying solution to: model.solutions.json +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": "e_1"} +Complete-AllPairs-Independently +Adding the following unnamed symmetry breaking constraints: + such that + and([{ tuple (i) .<= tuple (i_auxFor_e) + @ find i_auxFor_e: e + such that + tuple (i_auxFor_e) = transform(permutation((q1, q2)), tuple (i)) + } | q1 : e, q2 : e, q1 < q2]) +Generating models for model.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Running minion for domain filtering. +Running solver: minion +Copying solution to: model.solutions +Copying solution to: model.solutions.json +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": "e_1"} +Complete-AllPairs-Altogether +Adding the following unnamed symmetry breaking constraints: + such that + and([{ tuple (i) .<= tuple (i_auxFor_all) + @ find i_auxFor_all: e + such that + tuple (i_auxFor_all) = transform(permutation((q1, q2)), tuple (i)) + } | q1 : e, q2 : e, q1 < q2]) +Generating models for model.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Running minion for domain filtering. +Running solver: minion +Copying solution to: model.solutions +Copying solution to: model.solutions.json +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": "e_1"} +Complete-AllPermutations-Independently +Adding the following unnamed symmetry breaking constraints: + such that + and([{ tuple (i) .<= tuple (i_auxFor_e) + @ find i_auxFor_e: e + such that tuple (i_auxFor_e) = transform(q1, tuple (i)) + } | q1 : permutation of e]) +Generating models for model.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Running minion for domain filtering. +Running solver: minion +Copying solution to: model.solutions +Copying solution to: model.solutions.json +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": "e_1"} +Complete-AllPermutations-Altogether +Adding the following unnamed symmetry breaking constraints: + such that + and([{ tuple (i) .<= tuple (i_auxFor_all) + @ find i_auxFor_all: e + such that tuple (i_auxFor_all) = transform(q1, tuple (i)) + } | q1 : permutation of e]) +Generating models for model.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Running minion for domain filtering. +Running solver: minion +Copying solution to: model.solutions +Copying solution to: model.solutions.json +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": "e_1"} diff --git a/tests/custom/symmetry/basic/two-type/model.essence b/tests/custom/symmetry/basic/two-type/model.essence new file mode 100644 index 0000000000..a541c3d4ea --- /dev/null +++ b/tests/custom/symmetry/basic/two-type/model.essence @@ -0,0 +1,5 @@ +letting e be new type of size 4 +letting f be new type of size 4 + +find i: e +find j: f diff --git a/tests/custom/symmetry/basic/two-type/run.sh b/tests/custom/symmetry/basic/two-type/run.sh new file mode 100755 index 0000000000..0ca7a7af18 --- /dev/null +++ b/tests/custom/symmetry/basic/two-type/run.sh @@ -0,0 +1,10 @@ +for sym in Quick Complete; do + for amount in Consecutive AllPairs AllPermutations; do + for combine in Independently Altogether; do + echo $sym-$amount-$combine + conjure solve --number-of-solutions=all --solutions-in-one-file --output-format=jsonstream --unnamed-symmetry-breaking=$sym-$amount-$combine *.essence 2>&1 + cat *.json | LC_ALL=C sort + rm -rf conjure-output *solutions* + done + done +done \ No newline at end of file diff --git a/tests/custom/symmetry/basic/two-type/stdout.expected b/tests/custom/symmetry/basic/two-type/stdout.expected new file mode 100644 index 0000000000..979dd7b1c5 --- /dev/null +++ b/tests/custom/symmetry/basic/two-type/stdout.expected @@ -0,0 +1,90 @@ +Quick-Consecutive-Independently +Adding the following unnamed symmetry breaking constraints: + such that + and([(i, j) .<= transform(permutation((q1, succ(q1))), (i, j)) + | q1 : e, q1 < 4]), + and([(i, j) .<= transform(permutation((q2, succ(q2))), (i, j)) + | q2 : f, q2 < 4]) +Generating models for model.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Running minion for domain filtering. +Running solver: minion +Copying solution to: model.solutions +Copying solution to: model.solutions.json +{"e": ["e_1", "e_2", "e_3", "e_4"], "f": ["f_1", "f_2", "f_3", "f_4"], "i": "e_1", "j": "f_1"} +Quick-Consecutive-Altogether +Adding the following unnamed symmetry breaking constraints: + such that + and([and([(i, j) .<= + transform(permutation((q2, succ(q2))), + transform(permutation((q1, succ(q1))), (i, j))) + | q2 : f, q2 < 4]) + | q1 : e, q1 < 4]) +Generating models for model.essence +conjure: This should never happen, sorry! + +However, it did happen, so it must be a bug. Please report it to us! + +Conjure is actively maintained, we will get back to you as soon as possible. +You can help us by providing a minimal failing example. + +Also include the repository version for this build: unknown + +Issue tracker: http://github.com/conjure-cp/conjure/issues + + +dontCare on domain: f + +CallStack (from HasCallStack): + error, called at src/Conjure/Bug.hs:17:15 in conjure-cp-2.5.1-DjTx4wiFQ6I2X2qEEdPm4W:Conjure.Bug + bug, called at src/Conjure/Rules/DontCare.hs:31:20 in conjure-cp-2.5.1-DjTx4wiFQ6I2X2qEEdPm4W:Conjure.Rules.DontCare +Quick-AllPairs-Independently +Adding the following unnamed symmetry breaking constraints: + such that + and([(i, j) .<= transform(permutation((q1, q2)), (i, j)) + | q1 : e, q2 : e, q1 < q2]), + and([(i, j) .<= transform(permutation((q3, q4)), (i, j)) + | q3 : f, q4 : f, q3 < q4]) +Generating models for model.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Running minion for domain filtering. +Running solver: minion +Copying solution to: model.solutions +Copying solution to: model.solutions.json +{"e": ["e_1", "e_2", "e_3", "e_4"], "f": ["f_1", "f_2", "f_3", "f_4"], "i": "e_1", "j": "f_1"} +Quick-AllPairs-Altogether +Adding the following unnamed symmetry breaking constraints: + such that + and([and([(i, j) .<= + transform(permutation((q3, q4)), + transform(permutation((q1, q2)), (i, j))) + | q3 : f, q4 : f, q3 < q4]) + | q1 : e, q2 : e, q1 < q2]) +Generating models for model.essence +conjure: This should never happen, sorry! + +However, it did happen, so it must be a bug. Please report it to us! + +Conjure is actively maintained, we will get back to you as soon as possible. +You can help us by providing a minimal failing example. + +Also include the repository version for this build: unknown + +Issue tracker: http://github.com/conjure-cp/conjure/issues + + +dontCare on domain: f + +CallStack (from HasCallStack): + error, called at src/Conjure/Bug.hs:17:15 in conjure-cp-2.5.1-DjTx4wiFQ6I2X2qEEdPm4W:Conjure.Bug + bug, called at src/Conjure/Rules/DontCare.hs:31:20 in conjure-cp-2.5.1-DjTx4wiFQ6I2X2qEEdPm4W:Conjure.Rules.DontCare +Quick-AllPermutations-Independently +Adding the following unnamed symmetry breaking constraints: + such that + and([(i, j) .<= transform(q1, (i, j)) | q1 : permutation of e]), + and([(i, j) .<= transform(q2, (i, j)) | q2 : permutation of f]) +Generating models for model.essence diff --git a/tests/custom/symmetry/basic/two-var/model.essence b/tests/custom/symmetry/basic/two-var/model.essence new file mode 100644 index 0000000000..09ffd8e5de --- /dev/null +++ b/tests/custom/symmetry/basic/two-var/model.essence @@ -0,0 +1,4 @@ +letting e be new type of size 4 + +find i: e +find j: e diff --git a/tests/custom/symmetry/basic/two-var/run.sh b/tests/custom/symmetry/basic/two-var/run.sh new file mode 100755 index 0000000000..0ca7a7af18 --- /dev/null +++ b/tests/custom/symmetry/basic/two-var/run.sh @@ -0,0 +1,10 @@ +for sym in Quick Complete; do + for amount in Consecutive AllPairs AllPermutations; do + for combine in Independently Altogether; do + echo $sym-$amount-$combine + conjure solve --number-of-solutions=all --solutions-in-one-file --output-format=jsonstream --unnamed-symmetry-breaking=$sym-$amount-$combine *.essence 2>&1 + cat *.json | LC_ALL=C sort + rm -rf conjure-output *solutions* + done + done +done \ No newline at end of file diff --git a/tests/custom/symmetry/basic/two-var/stdout.expected b/tests/custom/symmetry/basic/two-var/stdout.expected new file mode 100644 index 0000000000..5c05e77f4b --- /dev/null +++ b/tests/custom/symmetry/basic/two-var/stdout.expected @@ -0,0 +1,203 @@ +Quick-Consecutive-Independently +Adding the following unnamed symmetry breaking constraints: + such that + and([(i, j) .<= transform(permutation((q1, succ(q1))), (i, j)) + | q1 : e, q1 < 4]) +Generating models for model.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Running minion for domain filtering. +Running solver: minion +Copying solution to: model.solutions +Copying solution to: model.solutions.json +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": "e_1", "j": "e_1"} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": "e_1", "j": "e_2"} +Quick-Consecutive-Altogether +Adding the following unnamed symmetry breaking constraints: + such that + and([(i, j) .<= transform(permutation((q1, succ(q1))), (i, j)) + | q1 : e, q1 < 4]) +Generating models for model.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Running minion for domain filtering. +Running solver: minion +Copying solution to: model.solutions +Copying solution to: model.solutions.json +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": "e_1", "j": "e_1"} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": "e_1", "j": "e_2"} +Quick-AllPairs-Independently +Adding the following unnamed symmetry breaking constraints: + such that + and([(i, j) .<= transform(permutation((q1, q2)), (i, j)) + | q1 : e, q2 : e, q1 < q2]) +Generating models for model.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Running minion for domain filtering. +Running solver: minion +Copying solution to: model.solutions +Copying solution to: model.solutions.json +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": "e_1", "j": "e_1"} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": "e_1", "j": "e_2"} +Quick-AllPairs-Altogether +Adding the following unnamed symmetry breaking constraints: + such that + and([(i, j) .<= transform(permutation((q1, q2)), (i, j)) + | q1 : e, q2 : e, q1 < q2]) +Generating models for model.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Running minion for domain filtering. +Running solver: minion +Copying solution to: model.solutions +Copying solution to: model.solutions.json +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": "e_1", "j": "e_1"} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": "e_1", "j": "e_2"} +Quick-AllPermutations-Independently +Adding the following unnamed symmetry breaking constraints: + such that + and([(i, j) .<= transform(q1, (i, j)) | q1 : permutation of e]) +Generating models for model.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Running minion for domain filtering. +Running solver: minion +Copying solution to: model.solutions +Copying solution to: model.solutions.json +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": "e_1", "j": "e_1"} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": "e_1", "j": "e_2"} +Quick-AllPermutations-Altogether +Adding the following unnamed symmetry breaking constraints: + such that + and([(i, j) .<= transform(q1, (i, j)) | q1 : permutation of e]) +Generating models for model.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Running minion for domain filtering. +Running solver: minion +Copying solution to: model.solutions +Copying solution to: model.solutions.json +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": "e_1", "j": "e_1"} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": "e_1", "j": "e_2"} +Complete-Consecutive-Independently +Adding the following unnamed symmetry breaking constraints: + such that + and([{ (i, j) .<= (i_auxFor_e, j_auxFor_e) + @ find i_auxFor_e: e + find j_auxFor_e: e + such that + (i_auxFor_e, j_auxFor_e) = + transform(permutation((q1, succ(q1))), (i, j)) + } | q1 : e, q1 < 4]) +Generating models for model.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Running minion for domain filtering. +Running solver: minion +Copying solution to: model.solutions +Copying solution to: model.solutions.json +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": "e_1", "j": "e_1"} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": "e_1", "j": "e_2"} +Complete-Consecutive-Altogether +Adding the following unnamed symmetry breaking constraints: + such that + and([{ (i, j) .<= (i_auxFor_all, j_auxFor_all) + @ find i_auxFor_all: e + find j_auxFor_all: e + such that + (i_auxFor_all, j_auxFor_all) = + transform(permutation((q1, succ(q1))), (i, j)) + } | q1 : e, q1 < 4]) +Generating models for model.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Running minion for domain filtering. +Running solver: minion +Copying solution to: model.solutions +Copying solution to: model.solutions.json +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": "e_1", "j": "e_1"} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": "e_1", "j": "e_2"} +Complete-AllPairs-Independently +Adding the following unnamed symmetry breaking constraints: + such that + and([{ (i, j) .<= (i_auxFor_e, j_auxFor_e) + @ find i_auxFor_e: e + find j_auxFor_e: e + such that + (i_auxFor_e, j_auxFor_e) = transform(permutation((q1, q2)), (i, j)) + } | q1 : e, q2 : e, q1 < q2]) +Generating models for model.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Running minion for domain filtering. +Running solver: minion +Copying solution to: model.solutions +Copying solution to: model.solutions.json +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": "e_1", "j": "e_1"} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": "e_1", "j": "e_2"} +Complete-AllPairs-Altogether +Adding the following unnamed symmetry breaking constraints: + such that + and([{ (i, j) .<= (i_auxFor_all, j_auxFor_all) + @ find i_auxFor_all: e + find j_auxFor_all: e + such that + (i_auxFor_all, j_auxFor_all) = + transform(permutation((q1, q2)), (i, j)) + } | q1 : e, q2 : e, q1 < q2]) +Generating models for model.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Running minion for domain filtering. +Running solver: minion +Copying solution to: model.solutions +Copying solution to: model.solutions.json +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": "e_1", "j": "e_1"} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": "e_1", "j": "e_2"} +Complete-AllPermutations-Independently +Adding the following unnamed symmetry breaking constraints: + such that + and([{ (i, j) .<= (i_auxFor_e, j_auxFor_e) + @ find i_auxFor_e: e + find j_auxFor_e: e + such that (i_auxFor_e, j_auxFor_e) = transform(q1, (i, j)) + } | q1 : permutation of e]) +Generating models for model.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Running minion for domain filtering. +Running solver: minion +Copying solution to: model.solutions +Copying solution to: model.solutions.json +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": "e_1", "j": "e_1"} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": "e_1", "j": "e_2"} +Complete-AllPermutations-Altogether +Adding the following unnamed symmetry breaking constraints: + such that + and([{ (i, j) .<= (i_auxFor_all, j_auxFor_all) + @ find i_auxFor_all: e + find j_auxFor_all: e + such that (i_auxFor_all, j_auxFor_all) = transform(q1, (i, j)) + } | q1 : permutation of e]) +Generating models for model.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Running minion for domain filtering. +Running solver: minion +Copying solution to: model.solutions +Copying solution to: model.solutions.json +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": "e_1", "j": "e_1"} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": "e_1", "j": "e_2"} From 573ad6d611e1177b59cbdbbb94019f72f4ed80aa Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?=C3=96zg=C3=BCr=20Akg=C3=BCn?= Date: Sat, 13 Apr 2024 21:28:37 +0100 Subject: [PATCH 163/229] add a hlint.yaml file --- .hlint.yaml | 6 ++++++ src/Conjure/Language/Lexemes.hs | 1 - src/Conjure/Language/Lexer.hs | 1 - src/Conjure/Representations/Internal.hs | 1 - src/Conjure/UI/Model.hs | 1 - 5 files changed, 6 insertions(+), 4 deletions(-) create mode 100644 .hlint.yaml diff --git a/.hlint.yaml b/.hlint.yaml new file mode 100644 index 0000000000..875940b254 --- /dev/null +++ b/.hlint.yaml @@ -0,0 +1,6 @@ +- ignore: {name: Use camelCase} +- ignore: {name: Reduce duplication} +- ignore: {name: Use &&} +- ignore: {name: Use ++} +- ignore: {name: Redundant return} +- ignore: {name: Monad law, left identity} diff --git a/src/Conjure/Language/Lexemes.hs b/src/Conjure/Language/Lexemes.hs index da629c50ca..9b2ad862b7 100644 --- a/src/Conjure/Language/Lexemes.hs +++ b/src/Conjure/Language/Lexemes.hs @@ -1,7 +1,6 @@ {-# LANGUAGE DeriveGeneric #-} {-# LANGUAGE DeriveDataTypeable #-} {-# OPTIONS_GHC -Wno-unrecognised-pragmas #-} -{-# HLINT ignore "Use camelCase" #-} module Conjure.Language.Lexemes where diff --git a/src/Conjure/Language/Lexer.hs b/src/Conjure/Language/Lexer.hs index 73c86b4764..cadf31c894 100644 --- a/src/Conjure/Language/Lexer.hs +++ b/src/Conjure/Language/Lexer.hs @@ -7,7 +7,6 @@ {-# LANGUAGE DeriveGeneric #-} {-# LANGUAGE TypeFamilies #-} {-# OPTIONS_GHC -Wno-unrecognised-pragmas #-} -{-# HLINT ignore "Use camelCase" #-} module Conjure.Language.Lexer ( Lexeme(..) diff --git a/src/Conjure/Representations/Internal.hs b/src/Conjure/Representations/Internal.hs index a74b46d6b4..d77f28ce79 100644 --- a/src/Conjure/Representations/Internal.hs +++ b/src/Conjure/Representations/Internal.hs @@ -1,7 +1,6 @@ {-# LANGUAGE Rank2Types #-} {-# LANGUAGE KindSignatures #-} {-# OPTIONS_GHC -Wno-unrecognised-pragmas #-} -{-# HLINT ignore "Use camelCase" #-} module Conjure.Representations.Internal ( Representation(..) diff --git a/src/Conjure/UI/Model.hs b/src/Conjure/UI/Model.hs index 623d85395d..c58e0d7460 100644 --- a/src/Conjure/UI/Model.hs +++ b/src/Conjure/UI/Model.hs @@ -3,7 +3,6 @@ {-# LANGUAGE QuasiQuotes #-} {-# LANGUAGE RecordWildCards #-} {-# OPTIONS_GHC -Wno-unrecognised-pragmas #-} -{-# HLINT ignore "Use camelCase" #-} module Conjure.UI.Model ( outputModels From b04e6aae4b225715966b479f3bf56420727d282a Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?=C3=96zg=C3=BCr=20Akg=C3=BCn?= Date: Sat, 13 Apr 2024 21:28:50 +0100 Subject: [PATCH 164/229] test: stop as soon as one case fails --- tests/custom/symmetry/basic/two-type/run.sh | 5 +++++ 1 file changed, 5 insertions(+) diff --git a/tests/custom/symmetry/basic/two-type/run.sh b/tests/custom/symmetry/basic/two-type/run.sh index 0ca7a7af18..eafbf7ed3e 100755 --- a/tests/custom/symmetry/basic/two-type/run.sh +++ b/tests/custom/symmetry/basic/two-type/run.sh @@ -1,3 +1,8 @@ +#!/bin/bash + +set -o errexit +set -o nounset + for sym in Quick Complete; do for amount in Consecutive AllPairs AllPermutations; do for combine in Independently Altogether; do From 1697e5e5696727096cc4ad187689f85d0e2c8474 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?=C3=96zg=C3=BCr=20Akg=C3=BCn?= Date: Sat, 13 Apr 2024 21:30:28 +0100 Subject: [PATCH 165/229] remove minimum_int_value_in_domain -- we already had minOfDomain --- src/Conjure/Rules/DontCare.hs | 25 ++------------------- src/Conjure/Rules/Horizontal/Permutation.hs | 3 ++- 2 files changed, 4 insertions(+), 24 deletions(-) diff --git a/src/Conjure/Rules/DontCare.hs b/src/Conjure/Rules/DontCare.hs index d117cd86a7..bddb8cdbe4 100644 --- a/src/Conjure/Rules/DontCare.hs +++ b/src/Conjure/Rules/DontCare.hs @@ -19,33 +19,12 @@ rule_Bool = "dontCare-bool" `namedRule` theRule where ) -minimum_int_value_in_domain :: - MonadFail m => - MonadFailDoc m => - NameGen m => - (?typeCheckerMode::TypeCheckerMode) => - Expression -> m Expression -minimum_int_value_in_domain x = do - TypeInt t <- typeOf x - xDomain <- domainOf x - let raiseBug = bug ("dontCare on domain:" <+> pretty xDomain) - return $ reTag t $ case xDomain of - DomainInt _ [] -> raiseBug - DomainInt _ (r:_) -> case r of - RangeOpen -> raiseBug - RangeSingle v -> v - RangeLowerBounded v -> v - RangeUpperBounded v -> v - RangeBounded v _ -> v - DomainIntE v -> [essence| min(&v) |] - _ -> raiseBug - - rule_Int :: Rule rule_Int = "dontCare-int" `namedRule` theRule where theRule p = do x <- match opDontCare p - val <- minimum_int_value_in_domain x + xDomain <- domainOf x + val <- minOfDomain xDomain return ( "dontCare value for this integer is" <+> pretty val , return $ make opEq x val diff --git a/src/Conjure/Rules/Horizontal/Permutation.hs b/src/Conjure/Rules/Horizontal/Permutation.hs index 234166afe9..9abdd8735f 100644 --- a/src/Conjure/Rules/Horizontal/Permutation.hs +++ b/src/Conjure/Rules/Horizontal/Permutation.hs @@ -152,7 +152,8 @@ rule_Image_Literal = "permutation-image-literal" `namedRule` theRule where (fromInt (fromIntegral (length srtdel))) matLit = make matrixLiteral (TypeMatrix (TypeInt TagInt) inner) matIdx ([ [essence| &i |] ] ++ (f <$> srtdel)) - minval <- minimum_int_value_in_domain i + iDomain <- domainOf i + minval <- minOfDomain iDomain return ( "Horizontal rule for permutation literal application to a single value (image), AsFunction representation" , do From ecd1a0ec39cea8622777886c67dede49634febf3 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?=C3=96zg=C3=BCr=20Akg=C3=BCn?= Date: Sat, 13 Apr 2024 21:33:13 +0100 Subject: [PATCH 166/229] rm -rf conjure-output at the beginning too --- tests/custom/symmetry/basic/two-type/run.sh | 4 +++- 1 file changed, 3 insertions(+), 1 deletion(-) diff --git a/tests/custom/symmetry/basic/two-type/run.sh b/tests/custom/symmetry/basic/two-type/run.sh index eafbf7ed3e..31f6c27bb1 100755 --- a/tests/custom/symmetry/basic/two-type/run.sh +++ b/tests/custom/symmetry/basic/two-type/run.sh @@ -3,13 +3,15 @@ set -o errexit set -o nounset +rm -rf conjure-output *solutions + for sym in Quick Complete; do for amount in Consecutive AllPairs AllPermutations; do for combine in Independently Altogether; do echo $sym-$amount-$combine conjure solve --number-of-solutions=all --solutions-in-one-file --output-format=jsonstream --unnamed-symmetry-breaking=$sym-$amount-$combine *.essence 2>&1 cat *.json | LC_ALL=C sort - rm -rf conjure-output *solutions* + rm -rf conjure-output *solutions done done done \ No newline at end of file From e77962993f1e4c6f702f295ba59cba885522e02e Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?=C3=96zg=C3=BCr=20Akg=C3=BCn?= Date: Sat, 13 Apr 2024 21:56:11 +0100 Subject: [PATCH 167/229] remove redundant import --- src/Conjure/Rules/Horizontal/Permutation.hs | 1 - 1 file changed, 1 deletion(-) diff --git a/src/Conjure/Rules/Horizontal/Permutation.hs b/src/Conjure/Rules/Horizontal/Permutation.hs index 9abdd8735f..97bff2cd8f 100644 --- a/src/Conjure/Rules/Horizontal/Permutation.hs +++ b/src/Conjure/Rules/Horizontal/Permutation.hs @@ -2,7 +2,6 @@ module Conjure.Rules.Horizontal.Permutation where import Conjure.Rules.Import import Conjure.Util.Permutation (size, toCycles, fromCycles, toFunction) -import Conjure.Rules.DontCare rule_Cardinality_Literal :: Rule rule_Cardinality_Literal = "permutation-cardinality-literal" `namedRule` theRule where From 0bc784ecfd9b3ac9707641372fbf101de88e577f Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?=C3=96zg=C3=BCr=20Akg=C3=BCn?= Date: Sat, 13 Apr 2024 21:56:27 +0100 Subject: [PATCH 168/229] improve log-successes: also print the output expression --- src/Conjure/UI/Model.hs | 14 ++++++++------ 1 file changed, 8 insertions(+), 6 deletions(-) diff --git a/src/Conjure/UI/Model.hs b/src/Conjure/UI/Model.hs index c58e0d7460..72623981c8 100644 --- a/src/Conjure/UI/Model.hs +++ b/src/Conjure/UI/Model.hs @@ -1328,11 +1328,7 @@ applicableRules Config{..} rulesAtLevel x = do , " on:" <+> pretty (hole x) , " message:" <+> failed ] - Right ys -> logSuccess $ vcat - [ "rule applied:" <+> rule - , " on:" <+> pretty (hole x) - , " message:" <+> vcat (map ruleResultDescr ys) - ] + Right _ -> return () return [ (name, res {ruleResult = ruleResult'}) | (name, Right ress) <- mys , res <- ress @@ -1361,7 +1357,13 @@ applicableRules Config{..} rulesAtLevel x = do , "Rule output (show):" <+> pretty (show rResult) , "The error :" <+> err ] - Right r -> return r + Right r -> do + logSuccess $ vcat + [ "rule applied:" <+> name + , " on:" <+> pretty (hole x) + , " output:" <+> pretty r + ] + return r ] From b34940945f55134f1d6e763bb31fa668b2401529 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?=C3=96zg=C3=BCr=20Akg=C3=BCn?= Date: Sat, 13 Apr 2024 21:56:37 +0100 Subject: [PATCH 169/229] hlint and reformat --- src/Conjure/Rules/Transform.hs | 1024 +++++++++++++++++--------------- 1 file changed, 550 insertions(+), 474 deletions(-) diff --git a/src/Conjure/Rules/Transform.hs b/src/Conjure/Rules/Transform.hs index 5f6a71fe3b..6e10912ec4 100644 --- a/src/Conjure/Rules/Transform.hs +++ b/src/Conjure/Rules/Transform.hs @@ -1,532 +1,608 @@ {-# LANGUAGE QuasiQuotes #-} +{-# OPTIONS_GHC -Wno-unrecognised-pragmas #-} + module Conjure.Rules.Transform (rules_Transform) where -import Conjure.Rules.Vertical.Variant (onTagged) -import Conjure.Rules.Import +import Conjure.Rules.Import +import Conjure.Rules.Vertical.Variant (onTagged) rules_Transform :: [Rule] -rules_Transform = - [ rule_Transform_Sequence_Literal - , rule_Transform_Functorially - , rule_Transform_Comprehension - , rule_Transform_Product_Types - , rule_Transform_Matrix - , rule_Transform_Partition - , rule_Transform_Sequence - , rule_Transform_Sequence_Defined - , rule_Transformed_Indexing - , rule_Lift_Transformed_Indexing - , rule_Transform_Indexing - , rule_Transform_Unifying - - , rule_Transform_Variant_Literal - , rule_Transform_Variant_Eq - , rule_Transform_Variant_Neq - , rule_Transform_Variant_Lt - , rule_Transform_Variant_Leq - , rule_Transformed_Variant_Index - , rule_Transformed_Variant_Active +rules_Transform = + [ rule_Transform_Sequence_Literal, + rule_Transform_Functorially, + rule_Transform_Comprehension, + rule_Transform_Product_Types, + rule_Transform_Matrix, + rule_Transform_Partition, + rule_Transform_Sequence, + rule_Transform_Sequence_Defined, + rule_Transformed_Indexing, + rule_Lift_Transformed_Indexing, + rule_Transform_Indexing, + rule_Transform_Unifying, + rule_Transform_Variant_Literal, + rule_Transform_Variant_Eq, + rule_Transform_Variant_Neq, + rule_Transform_Variant_Lt, + rule_Transform_Variant_Leq, + rule_Transformed_Variant_Index, + rule_Transformed_Variant_Active ] - rule_Transform_Functorially :: Rule -rule_Transform_Functorially = "transform-functorially" `namedRule` theRule where - theRule (Comprehension body gensOrConds) = do - (gocBefore, (pat, x), gocAfter) <- matchFirst gensOrConds $ \ goc -> case goc of - Generator (GenInExpr (Single pat) expr) -> - return (pat, matchDefs [opToSet, opToMSet] expr) - _ -> na "rule_Transform_Functorially" - (morphism, y) <- match opTransform x - ty <- typeOf y - inn <- morphing =<< typeOf morphism - if let ?typeCheckerMode = StronglyTyped in ty `containsTypeFunctorially` inn - then - return - ( "Horizontal rule for transform of functorially" - , do - (dPat, d) <- quantifiedVar - return (Comprehension body $ - gocBefore - ++ [Generator (GenInExpr dPat [essence| &y |])] - ++ ((ComprehensionLetting (Single pat) [essence| - transform(&morphism, &d) |] ):gocAfter) - ) - ) - else na "rule_Transform_Functorially" - theRule _ = na "rule_Transform_Functorially" - +rule_Transform_Functorially = "transform-functorially" `namedRule` theRule + where + theRule (Comprehension body gensOrConds) = do + (gocBefore, (pat, x), gocAfter) <- matchFirst gensOrConds $ \case + Generator (GenInExpr (Single pat) expr) -> + return (pat, matchDefs [opToSet, opToMSet] expr) + _ -> na "rule_Transform_Functorially" + (morphism, y) <- match opTransform x + ty <- typeOf y + inn <- morphing =<< typeOf morphism + if let ?typeCheckerMode = StronglyTyped in ty `containsTypeFunctorially` inn + then + return + ( "Horizontal rule for transform of functorially", + do + (dPat, d) <- quantifiedVar + return + ( Comprehension body + $ gocBefore + ++ [Generator (GenInExpr dPat [essence| &y |])] + ++ ( ComprehensionLetting + (Single pat) + [essence| + transform(&morphism, &d) |] + : gocAfter + ) + ) + ) + else na "rule_Transform_Functorially" + theRule _ = na "rule_Transform_Functorially" rule_Transform_Comprehension :: Rule -rule_Transform_Comprehension = "transform-comprehension" `namedRule` theRule where - theRule x = do - (morphism, cmp@(Comprehension body gensOrConds)) <- match opTransform x - ty <- typeOf cmp - inn <- morphing =<< typeOf morphism - if let ?typeCheckerMode = StronglyTyped in ty `containsType` inn - then - return ( "Horizontal rule for transform comprehension" - , do - gox <- sequence (transformOverGenOrCond morphism <$> gensOrConds) - return $ Comprehension [essence| +rule_Transform_Comprehension = "transform-comprehension" `namedRule` theRule + where + theRule x = do + (morphism, cmp@(Comprehension body gensOrConds)) <- match opTransform x + ty <- typeOf cmp + inn <- morphing =<< typeOf morphism + if let ?typeCheckerMode = StronglyTyped in ty `containsType` inn + then + return + ( "Horizontal rule for transform comprehension", + do + gox <- mapM (transformOverGenOrCond morphism) gensOrConds + return + $ Comprehension + [essence| transform(&morphism, &body) - |] (join gox) - ) - else na "rule_Transform_Comprehension" - transformOverGenOrCond m (Generator g) = transformOverGenerator m g - transformOverGenOrCond m (Condition e) = - return [Condition [essence| transform(&m,&e) |]] - transformOverGenOrCond m (ComprehensionLetting pat e) = - return [ComprehensionLetting pat [essence| transform(&m,&e) |]] - - transformOverGenerator m (GenDomainHasRepr a d) = do - (Single nm, n) <- quantifiedVarOverDomain $ forgetRepr d - return [Generator (GenDomainHasRepr nm d) - ,ComprehensionLetting (Single a) [essence| transform(&m, &n) |] - ] - transformOverGenerator m (GenInExpr a e) = - return [Generator (GenInExpr a [essence| transform(&m,&e) |])] - transformOverGenerator m (GenDomainNoRepr absPat d) = do - (rPat, ns) <- clonePattern absPat - return $ [Generator (GenDomainNoRepr rPat d)] - ++ ((\(pat,exp) -> - ComprehensionLetting (Single pat) [essence| transform(&m,&exp) |] - ) <$> ns) - - clonePattern (Single name) = do - (nPat, n) <- quantifiedVar - return (nPat,[(name, n)]) - clonePattern (AbsPatTuple pats) = do - rec <- sequence (clonePattern <$> pats) - return ( AbsPatTuple $ fst <$> rec - , join $ snd <$> rec) - clonePattern (AbsPatMatrix pats) = do - rec <- sequence (clonePattern <$> pats) - return ( AbsPatMatrix $ fst <$> rec - , join $ snd <$> rec) - clonePattern (AbsPatSet pats) = do - rec <- sequence (clonePattern <$> pats) - return ( AbsPatSet $ fst <$> rec - , join $ snd <$> rec) - clonePattern _ = - bug "rule_Transform_Comprehension: clonePattern: unsupported Abstract Pattern" - + |] + (join gox) + ) + else na "rule_Transform_Comprehension" + transformOverGenOrCond m (Generator g) = transformOverGenerator m g + transformOverGenOrCond m (Condition e) = + return [Condition [essence| transform(&m,&e) |]] + transformOverGenOrCond m (ComprehensionLetting pat e) = + return [ComprehensionLetting pat [essence| transform(&m,&e) |]] + + transformOverGenerator m (GenDomainHasRepr a d) = do + (Single nm, n) <- quantifiedVarOverDomain $ forgetRepr d + return + [ Generator (GenDomainHasRepr nm d), + ComprehensionLetting (Single a) [essence| transform(&m, &n) |] + ] + transformOverGenerator m (GenInExpr a e) = + return [Generator (GenInExpr a [essence| transform(&m,&e) |])] + transformOverGenerator m (GenDomainNoRepr absPat d) = do + (rPat, ns) <- clonePattern absPat + return + $ Generator (GenDomainNoRepr rPat d) + : ( ( \(pat, exp) -> + ComprehensionLetting (Single pat) [essence| transform(&m,&exp) |] + ) + <$> ns + ) + + clonePattern (Single name) = do + (nPat, n) <- quantifiedVar + return (nPat, [(name, n)]) + clonePattern (AbsPatTuple pats) = do + rec <- mapM clonePattern pats + return + ( AbsPatTuple $ fst <$> rec, + snd =<< rec + ) + clonePattern (AbsPatMatrix pats) = do + rec <- mapM clonePattern pats + return + ( AbsPatMatrix $ fst <$> rec, + snd =<< rec + ) + clonePattern (AbsPatSet pats) = do + rec <- mapM clonePattern pats + return + ( AbsPatSet $ fst <$> rec, + snd =<< rec + ) + clonePattern _ = + bug "rule_Transform_Comprehension: clonePattern: unsupported Abstract Pattern" rule_Transform_Product_Types :: Rule -rule_Transform_Product_Types = "transform-product-types" `namedRule` theRule where - theRule [essence| transform(&morphism, &i) |] = do - inn <- morphing =<< typeOf morphism - ti <- typeOf i - if let ?typeCheckerMode = StronglyTyped in ti `containsProductType` inn - then case ti of - (TypeTuple tint) -> do - let tupleIndexTransform indx = - let indexexpr = Constant (ConstantInt TagInt indx) - in [essence| transform(&morphism, &i[&indexexpr]) |] - tupleExpression = - AbstractLiteral $ AbsLitTuple - $ (tupleIndexTransform <$> [1..(fromIntegral $ length tint)]) - return - ( "Horizontal rule for transform of tuple" - , return tupleExpression - ) - (TypeRecord namet) -> do - let recordIndexTransform indx = - let indexexpr = Reference (fst indx) - $ Just $ RecordField (fst indx) (snd indx) - in (fst indx, [essence| transform(&morphism, &i[&indexexpr]) |]) - recordExpression = AbstractLiteral $ AbsLitRecord - $ (recordIndexTransform <$> namet) - return - ( "Horizontal rule for transform of record" - , return recordExpression - ) - _ -> bug "rule_Transform_Product_Types this is a bug" - else na "rule_Transform_Product_Types" - theRule _ = na "rule_Transform_Product_Types" - +rule_Transform_Product_Types = "transform-product-types" `namedRule` theRule + where + theRule [essence| transform(&morphism, &i) |] = do + inn <- morphing =<< typeOf morphism + ti <- typeOf i + if let ?typeCheckerMode = StronglyTyped in ti `containsProductType` inn + then case ti of + (TypeTuple tint) -> do + let tupleIndexTransform indx = + let indexexpr = Constant (ConstantInt TagInt indx) + in [essence| transform(&morphism, &i[&indexexpr]) |] + tupleExpression = + AbstractLiteral + $ AbsLitTuple + $ tupleIndexTransform + <$> [1 .. (fromIntegral $ length tint)] + return + ( "Horizontal rule for transform of tuple", + return tupleExpression + ) + (TypeRecord namet) -> do + let recordIndexTransform indx = + let indexexpr = + Reference (fst indx) + $ Just + $ uncurry RecordField indx + in (fst indx, [essence| transform(&morphism, &i[&indexexpr]) |]) + recordExpression = + AbstractLiteral + $ AbsLitRecord + $ recordIndexTransform + <$> namet + return + ( "Horizontal rule for transform of record", + return recordExpression + ) + _ -> bug "rule_Transform_Product_Types this is a bug" + else na "rule_Transform_Product_Types" + theRule _ = na "rule_Transform_Product_Types" rule_Transform_Matrix :: Rule -rule_Transform_Matrix = "transform-matrix" `namedRule` theRule where - theRule (Comprehension body gensOrConds) = do - (gocBefore, (pat, exp), gocAfter) <- matchFirst gensOrConds $ \ goc -> case goc of - Generator (GenInExpr (Single pat) expr) -> return (pat, expr) - _ -> na "rule_Transform_Matrix" - (morphism, matexp) <- match opTransform exp - DomainMatrix domIndx _ <- domainOf matexp - ty <- typeOf matexp - inn <- morphing =<< typeOf morphism - if let ?typeCheckerMode = StronglyTyped in ty `containsType` inn - then return - ( "Horizontal rule for transform matrix in comprehension generator" - , do - (dPat, d) <- quantifiedVar - (Single mName, m) <- quantifiedVar - (Single iName, i) <- quantifiedVar - return (Comprehension body $ - gocBefore - ++ [Generator (GenDomainNoRepr dPat (forgetRepr domIndx))] - ++ [ComprehensionLetting (Single iName) [essence| transform(&morphism, &d) |]] - ++ [ComprehensionLetting (Single mName) [essence| &matexp[&i] |]] - ++ [ComprehensionLetting (Single pat) [essence| transform(&morphism, &m) |]] - ++ gocAfter) - ) - else na "rule_Transform_Matrix" - theRule _ = na "rule_Transform_Matrix" - +rule_Transform_Matrix = "transform-matrix" `namedRule` theRule + where + theRule (Comprehension body gensOrConds) = do + (gocBefore, (pat, exp), gocAfter) <- matchFirst gensOrConds $ \case + Generator (GenInExpr (Single pat) expr) -> return (pat, expr) + _ -> na "rule_Transform_Matrix" + (morphism, matexp) <- match opTransform exp + DomainMatrix domIndx _ <- domainOf matexp + ty <- typeOf matexp + inn <- morphing =<< typeOf morphism + if let ?typeCheckerMode = StronglyTyped in ty `containsType` inn + then + return + ( "Horizontal rule for transform matrix in comprehension generator", + do + (dPat, d) <- quantifiedVar + (Single mName, m) <- quantifiedVar + (Single iName, i) <- quantifiedVar + return + ( Comprehension body + $ gocBefore + ++ [Generator (GenDomainNoRepr dPat (forgetRepr domIndx))] + ++ [ComprehensionLetting (Single iName) [essence| transform(&morphism, &d) |]] + ++ [ComprehensionLetting (Single mName) [essence| &matexp[&i] |]] + ++ [ComprehensionLetting (Single pat) [essence| transform(&morphism, &m) |]] + ++ gocAfter + ) + ) + else na "rule_Transform_Matrix" + theRule _ = na "rule_Transform_Matrix" rule_Transform_Partition :: Rule -rule_Transform_Partition = "transform-partition" `namedRule` theRule where - theRule (Comprehension body gensOrConds) = do - (gocBefore, (pat, x), gocAfter) <- matchFirst gensOrConds $ \ goc -> case goc of - Generator (GenInExpr (Single pat) expr) -> return (pat, expr) - _ -> na "rule_Transform_Partition" - z <- match opParts x - (morphism, y) <- match opTransform z - ty <- typeOf y - case ty of TypePartition{} -> return () ; _ -> na "only applies to partitions" - inn <- morphing =<< typeOf morphism - if let ?typeCheckerMode = StronglyTyped in ty `containsType` inn - then do - return - ( "Horizontal rule for transform of partition" - , do - (dPat, d) <- quantifiedVar - return (Comprehension body $ - gocBefore - ++ [Generator (GenInExpr dPat [essence| parts(&y) |])] - ++ ((ComprehensionLetting (Single pat) [essence| transform(&morphism, &d) |] ):gocAfter) - ) - ) - else na "rule_Transform_Partition" - theRule _ = na "rule_Transform_Partition" - +rule_Transform_Partition = "transform-partition" `namedRule` theRule + where + theRule (Comprehension body gensOrConds) = do + (gocBefore, (pat, x), gocAfter) <- matchFirst gensOrConds $ \case + Generator (GenInExpr (Single pat) expr) -> return (pat, expr) + _ -> na "rule_Transform_Partition" + z <- match opParts x + (morphism, y) <- match opTransform z + ty <- typeOf y + case ty of TypePartition {} -> return (); _ -> na "only applies to partitions" + inn <- morphing =<< typeOf morphism + if let ?typeCheckerMode = StronglyTyped in ty `containsType` inn + then do + return + ( "Horizontal rule for transform of partition", + do + (dPat, d) <- quantifiedVar + return + ( Comprehension body + $ gocBefore + ++ [Generator (GenInExpr dPat [essence| parts(&y) |])] + ++ (ComprehensionLetting (Single pat) [essence| transform(&morphism, &d) |] : gocAfter) + ) + ) + else na "rule_Transform_Partition" + theRule _ = na "rule_Transform_Partition" rule_Transform_Sequence :: Rule -rule_Transform_Sequence = "transform-sequence" `namedRule` theRule where - theRule (Comprehension body gensOrConds) = do - (gocBefore, (pat, x), gocAfter) <- matchFirst gensOrConds $ \ goc -> case goc of - Generator (GenInExpr (Single pat) expr) -> - return (pat, matchDefs [opToSet, opToMSet] expr) - _ -> na "rule_Transform_Sequence" - (morphism, y) <- match opTransform x - ty <- typeOf y - case ty of TypeSequence{} -> return () ; _ -> na "only applies to sequences" - inn <- morphing =<< typeOf morphism - if let ?typeCheckerMode = StronglyTyped in ty `containsType` inn - then do - return - ( "Horizontal rule for transform of sequence" - , do - (dPat, d) <- quantifiedVar - return (Comprehension body $ - gocBefore - ++ [Generator (GenInExpr dPat [essence| &y |])] - ++ ((ComprehensionLetting (Single pat) [essence| - (&d[1], transform(&morphism, &d[2])) |] ):gocAfter) - ) - - ) - else na "rule_Transform_Sequence" - theRule _ = na "rule_Transform_Sequence" - +rule_Transform_Sequence = "transform-sequence" `namedRule` theRule + where + theRule (Comprehension body gensOrConds) = do + (gocBefore, (pat, x), gocAfter) <- matchFirst gensOrConds $ \case + Generator (GenInExpr (Single pat) expr) -> + return (pat, matchDefs [opToSet, opToMSet] expr) + _ -> na "rule_Transform_Sequence" + (morphism, y) <- match opTransform x + ty <- typeOf y + case ty of TypeSequence {} -> return (); _ -> na "only applies to sequences" + inn <- morphing =<< typeOf morphism + if let ?typeCheckerMode = StronglyTyped in ty `containsType` inn + then do + return + ( "Horizontal rule for transform of sequence", + do + (dPat, d) <- quantifiedVar + return + ( Comprehension body + $ gocBefore + ++ [Generator (GenInExpr dPat [essence| &y |])] + ++ ( ComprehensionLetting + (Single pat) + [essence| + (&d[1], transform(&morphism, &d[2])) |] + : gocAfter + ) + ) + ) + else na "rule_Transform_Sequence" + theRule _ = na "rule_Transform_Sequence" rule_Transform_Sequence_Defined :: Rule -rule_Transform_Sequence_Defined = "transform-sequence-defined" `namedRule` theRule where - theRule (Comprehension body gensOrConds) = do - (gocBefore, (pat, x), gocAfter) <- matchFirst gensOrConds $ \ goc -> case goc of - Generator (GenInExpr pat@Single{} expr) -> - return (pat, matchDefs [opToSet, opToMSet] expr) - _ -> na "rule_Transform_Sequence_Defined" - defi <- match opDefined x - (morphism, y) <- match opTransform defi - ty <- typeOf y - case ty of TypeSequence{} -> return () ; _ -> na "only applies to sequences" - inn <- morphing =<< typeOf morphism - if let ?typeCheckerMode = StronglyTyped in ty `containsType` inn - then do - return - ( "Horizontal rule for transform of sequence defined" - , do - return (Comprehension body $ - gocBefore - ++ [Generator (GenInExpr pat [essence| defined(&y) |])] - ++ gocAfter - ) - ) - else na "rule_Transform_Sequence_Defined" - theRule _ = na "rule_Transform_Sequence_Defined" - +rule_Transform_Sequence_Defined = "transform-sequence-defined" `namedRule` theRule + where + theRule (Comprehension body gensOrConds) = do + (gocBefore, (pat, x), gocAfter) <- matchFirst gensOrConds $ \case + Generator (GenInExpr pat@Single {} expr) -> + return (pat, matchDefs [opToSet, opToMSet] expr) + _ -> na "rule_Transform_Sequence_Defined" + defi <- match opDefined x + (morphism, y) <- match opTransform defi + ty <- typeOf y + case ty of TypeSequence {} -> return (); _ -> na "only applies to sequences" + inn <- morphing =<< typeOf morphism + if let ?typeCheckerMode = StronglyTyped in ty `containsType` inn + then do + return + ( "Horizontal rule for transform of sequence defined", + do + return + ( Comprehension body + $ gocBefore + ++ [Generator (GenInExpr pat [essence| defined(&y) |])] + ++ gocAfter + ) + ) + else na "rule_Transform_Sequence_Defined" + theRule _ = na "rule_Transform_Sequence_Defined" rule_Transformed_Indexing :: Rule -rule_Transformed_Indexing = "transformed-indexing" `namedRule` theRule where - theRule (Comprehension body gensOrConds) = do - (gocBefore, (pat, exp), gocAfter) <- matchFirst gensOrConds $ \ goc -> case goc of - Generator (GenInExpr (Single pat) expr) -> return (pat, expr) - _ -> na "rule_Transformed_Indexing" - (matexp, indexer) <- match opIndexing exp - (morphism, mat) <- match opTransform matexp - ty <- typeOf mat - inn <- morphing =<< typeOf morphism - if let ?typeCheckerMode = StronglyTyped in ty `containsType` inn - then do - return - ( "Horizontal rule for transformed indexing" - , do - (Single mName, m) <- quantifiedVar - return (Comprehension body $ - gocBefore - ++ [ComprehensionLetting (Single mName) [essence| &matexp[&indexer] |]] - - ++ [ComprehensionLetting (Single pat) [essence| transform(&morphism, &m) |]] - ++ gocAfter) - ) - else na "rule_Transformed_Indexing" - theRule _ = na "rule_Transformed_Indexing" - +rule_Transformed_Indexing = "transformed-indexing" `namedRule` theRule + where + theRule (Comprehension body gensOrConds) = do + (gocBefore, (pat, exp), gocAfter) <- matchFirst gensOrConds $ \case + Generator (GenInExpr (Single pat) expr) -> return (pat, expr) + _ -> na "rule_Transformed_Indexing" + (matexp, indexer) <- match opIndexing exp + (morphism, mat) <- match opTransform matexp + ty <- typeOf mat + inn <- morphing =<< typeOf morphism + if let ?typeCheckerMode = StronglyTyped in ty `containsType` inn + then do + return + ( "Horizontal rule for transformed indexing", + do + (Single mName, m) <- quantifiedVar + return + ( Comprehension body + $ gocBefore + ++ [ComprehensionLetting (Single mName) [essence| &matexp[&indexer] |]] + ++ [ComprehensionLetting (Single pat) [essence| transform(&morphism, &m) |]] + ++ gocAfter + ) + ) + else na "rule_Transformed_Indexing" + theRule _ = na "rule_Transformed_Indexing" rule_Lift_Transformed_Indexing :: Rule -rule_Lift_Transformed_Indexing = "lift-transformed-indexing" `namedRule` theRule where - matchIndexing :: (?typeCheckerMode :: TypeCheckerMode) - => Expression - -> Maybe (Expression, Expression, Expression, Expression) - matchIndexing exp = do - (matexp, indexer) <- match opIndexing exp - (morphism, mat) <- match opTransform matexp - return (exp, morphism, mat, indexer) - - liftIndexing (exp, morphism, mat, indexer) = do - (Single nm, m) <- quantifiedVar - return ( (exp, [essence| transform(&morphism, &m) |]) - , ComprehensionLetting (Single nm) [essence| &mat[&indexer] |]) - - transformBody bdy [] = bdy - transformBody bdy ((orig, repl):rest) = - let nbdy = transformBi (\e -> if e == orig - then repl - else e) bdy - in transformBody nbdy rest - - theRule (Comprehension body gensOrConds) = do - let matched = catMaybes [matchIndexing exp | exp <- universeBi body] - case matched of - [] -> na "rule_Lift_Transformed_Indexing: nothing to lift" - _ -> do - replacements <- sequence (liftIndexing <$> matched) - return ( "Horizontal rule for lift transformed indexing" - , return (Comprehension (transformBody body (fst <$> replacements)) $ - gensOrConds ++ (snd <$> replacements)) - ) - theRule _ = na "rule_Lift_Transformed_Indexing" +rule_Lift_Transformed_Indexing = "lift-transformed-indexing" `namedRule` theRule + where + matchIndexing :: + (?typeCheckerMode :: TypeCheckerMode) => + Expression -> + Maybe (Expression, Expression, Expression, Expression) + matchIndexing exp = do + (matexp, indexer) <- match opIndexing exp + (morphism, mat) <- match opTransform matexp + return (exp, morphism, mat, indexer) + + liftIndexing (exp, morphism, mat, indexer) = do + (Single nm, m) <- quantifiedVar + return + ( (exp, [essence| transform(&morphism, &m) |]), + ComprehensionLetting (Single nm) [essence| &mat[&indexer] |] + ) + transformBody bdy [] = bdy + transformBody bdy ((orig, repl) : rest) = + let nbdy = + transformBi + ( \e -> + if e == orig + then repl + else e + ) + bdy + in transformBody nbdy rest + + theRule (Comprehension body gensOrConds) = do + let matched = catMaybes [matchIndexing exp | exp <- universeBi body] + case matched of + [] -> na "rule_Lift_Transformed_Indexing: nothing to lift" + _ -> do + replacements <- mapM liftIndexing matched + return + ( "Horizontal rule for lift transformed indexing", + return + ( Comprehension (transformBody body (fst <$> replacements)) + $ gensOrConds + ++ (snd <$> replacements) + ) + ) + theRule _ = na "rule_Lift_Transformed_Indexing" rule_Transform_Indexing :: Rule -rule_Transform_Indexing = "transform-indexing" `namedRule` theRule where - theRule (Comprehension body gensOrConds) = do - (gocBefore, (pat, expr), gocAfter) <- matchFirst gensOrConds $ \ goc -> case goc of - Generator (GenInExpr pat expr) -> return (pat, expr) - _ -> na "rule_Transform_Indexing" - (morphism, matexp) <- match opTransform expr - (mat, indexer) <- match opIndexing matexp - ty <- typeOf mat - inn <- morphing =<< typeOf morphism - if let ?typeCheckerMode = StronglyTyped in ty `containsType` inn - then do - return - ( "Horizontal rule for transform indexing" - , do - (Single mName, m) <- quantifiedVar - (Single iName, i) <- quantifiedVar - return (Comprehension body $ - gocBefore - ++ [ComprehensionLetting (Single iName) [essence| transform(&morphism, &indexer) |]] - ++ [ComprehensionLetting (Single mName) [essence| &mat[&i] |]] - - ++ [Generator (GenInExpr pat [essence| transform(&morphism, &m) |])] - ++ gocAfter) - ) - else na "rule_Transform_Indexing" - theRule _ = na "rule_Transform_Indexing" - - -rule_Transform_Unifying :: Rule -rule_Transform_Unifying = "transform-unifying" `namedRule` theRule where - theRule [essence| transform(&morphism, &i) |] = do - inner <- morphing =<< typeOf morphism - typeI <- typeOf i - if let ?typeCheckerMode = StronglyTyped in typesUnify [inner, typeI] - then return ( "Horizontal rule for transform unifying" - , return [essence| image(&morphism, &i) |] +rule_Transform_Indexing = "transform-indexing" `namedRule` theRule + where + theRule (Comprehension body gensOrConds) = do + (gocBefore, (pat, expr), gocAfter) <- matchFirst gensOrConds $ \case + Generator (GenInExpr pat expr) -> return (pat, expr) + _ -> na "rule_Transform_Indexing" + (morphism, matexp) <- match opTransform expr + (mat, indexer) <- match opIndexing matexp + ty <- typeOf mat + inn <- morphing =<< typeOf morphism + if let ?typeCheckerMode = StronglyTyped in ty `containsType` inn + then do + return + ( "Horizontal rule for transform indexing", + do + (Single mName, m) <- quantifiedVar + (Single iName, i) <- quantifiedVar + return + ( Comprehension body + $ gocBefore + ++ [ComprehensionLetting (Single iName) [essence| transform(&morphism, &indexer) |]] + ++ [ComprehensionLetting (Single mName) [essence| &mat[&i] |]] + ++ [Generator (GenInExpr pat [essence| transform(&morphism, &m) |])] + ++ gocAfter ) - else if let ?typeCheckerMode = StronglyTyped in typeI `containsType` inner - then na "rule_Transform_Unifying" - else return ( "Horizontal rule for transform shortcut" - , do - return [essence| &i |] - ) - theRule _ = na "rule_Transform_Unifying" + ) + else na "rule_Transform_Indexing" + theRule _ = na "rule_Transform_Indexing" +rule_Transform_Unifying :: Rule +rule_Transform_Unifying = "transform-unifying" `namedRule` theRule + where + theRule [essence| transform(&morphism, &i) |] = do + inner <- morphing =<< typeOf morphism + typeI <- typeOf i + if let ?typeCheckerMode = StronglyTyped in typesUnify [inner, typeI] + then + return + ( "Horizontal rule for transform unifying", + return [essence| image(&morphism, &i) |] + ) + else + if let ?typeCheckerMode = StronglyTyped in typeI `containsType` inner + then na "rule_Transform_Unifying" + else + return + ( "Horizontal rule for transform shortcut", + do + return [essence| &i |] + ) + theRule _ = na "rule_Transform_Unifying" rule_Transform_Sequence_Literal :: Rule -rule_Transform_Sequence_Literal = "transform-sequence-literal" `namedRule` theRule where - theRule p = do - _ <- match opTransform p - let (x, rx) = matchManyTransforms p - (_, as) <- match sequenceLiteral x - return ( "Horizontal rule for transform sequence literal" - , return $ AbstractLiteral $ AbsLitSequence $ rx <$> as - ) +rule_Transform_Sequence_Literal = "transform-sequence-literal" `namedRule` theRule + where + theRule p = do + _ <- match opTransform p + let (x, rx) = matchManyTransforms p + (_, as) <- match sequenceLiteral x + return + ( "Horizontal rule for transform sequence literal", + return $ AbstractLiteral $ AbsLitSequence $ rx <$> as + ) rule_Transform_Variant_Literal :: Rule -rule_Transform_Variant_Literal = "transform-variant-literal" `namedRule` theRule where - theRule p = do - _ <- match opTransform p - let (x, rx) = matchManyTransforms p - case x of - AbstractLiteral (AbsLitVariant d n a) -> - return ( "Horizontal rule for transform variant literal" - , return $ AbstractLiteral $ AbsLitVariant d n $ rx a - ) - _ -> na "rule_Transform_Variant_Literal" - +rule_Transform_Variant_Literal = "transform-variant-literal" `namedRule` theRule + where + theRule p = do + _ <- match opTransform p + let (x, rx) = matchManyTransforms p + case x of + AbstractLiteral (AbsLitVariant d n a) -> + return + ( "Horizontal rule for transform variant literal", + return $ AbstractLiteral $ AbsLitVariant d n $ rx a + ) + _ -> na "rule_Transform_Variant_Literal" -atLeastOneTransform :: MonadFailDoc m => (Expression, Expression) -> m () -atLeastOneTransform (l,r) = do +atLeastOneTransform :: (MonadFailDoc m) => (Expression, Expression) -> m () +atLeastOneTransform (l, r) = do case (match opTransform l, match opTransform r) of (Nothing, Nothing) -> na "no transforms on either side" - _ -> return () + _ -> return () -matchManyTransforms :: Expression - -> (Expression, Expression -> Expression) +matchManyTransforms :: + Expression -> + (Expression, Expression -> Expression) matchManyTransforms exp = case match opTransform exp of Nothing -> (exp, id) Just (morphism, so) -> let (nexp, ntrans) = matchManyTransforms so - in ( nexp - , \x -> let nx = ntrans x in [essence| transform(&morphism, &nx) |]) + in ( nexp, + \x -> let nx = ntrans x in [essence| transform(&morphism, &nx) |] + ) rule_Transform_Variant_Eq :: Rule -rule_Transform_Variant_Eq = "transform-variant-eq" `namedRule` theRule where - theRule p = do - (l,r) <- match opEq p - atLeastOneTransform (l,r) - let (x, rx) = matchManyTransforms l - let (y, ry) = matchManyTransforms r - TypeVariant{} <- typeOf x - TypeVariant{} <- typeOf y - (xWhich:xs) <- downX1 x - (yWhich:ys) <- downX1 y - return ( "Vertical rule for right transformed variant equality" - , return $ make opAnd $ fromList - [ [essence| &xWhich = &yWhich |] - , onTagged (make opEq) xWhich (rx <$> xs) (ry<$> ys) - ] - ) - +rule_Transform_Variant_Eq = "transform-variant-eq" `namedRule` theRule + where + theRule p = do + (l, r) <- match opEq p + atLeastOneTransform (l, r) + let (x, rx) = matchManyTransforms l + let (y, ry) = matchManyTransforms r + TypeVariant {} <- typeOf x + TypeVariant {} <- typeOf y + (xWhich : xs) <- downX1 x + (yWhich : ys) <- downX1 y + return + ( "Vertical rule for right transformed variant equality", + return + $ make opAnd + $ fromList + [ [essence| &xWhich = &yWhich |], + onTagged (make opEq) xWhich (rx <$> xs) (ry <$> ys) + ] + ) rule_Transform_Variant_Neq :: Rule -rule_Transform_Variant_Neq = "transform-variant-neq" `namedRule` theRule where - theRule p = do - (l,r) <- match opNeq p - atLeastOneTransform (l,r) - let (x, rx) = matchManyTransforms l - let (y, ry) = matchManyTransforms r - TypeVariant{} <- typeOf x - TypeVariant{} <- typeOf y - (xWhich:xs) <- downX1 x - (yWhich:ys) <- downX1 y - return ( "Vertical rule for right transformed variant nequality" - , return $ make opOr $ fromList - [ [essence| &xWhich != &yWhich |] - , make opAnd $ fromList - [ [essence| &xWhich = &yWhich |] - , onTagged (make opNeq) xWhich (rx <$> xs) (ry<$> ys) - ] - ] - ) - +rule_Transform_Variant_Neq = "transform-variant-neq" `namedRule` theRule + where + theRule p = do + (l, r) <- match opNeq p + atLeastOneTransform (l, r) + let (x, rx) = matchManyTransforms l + let (y, ry) = matchManyTransforms r + TypeVariant {} <- typeOf x + TypeVariant {} <- typeOf y + (xWhich : xs) <- downX1 x + (yWhich : ys) <- downX1 y + return + ( "Vertical rule for right transformed variant nequality", + return + $ make opOr + $ fromList + [ [essence| &xWhich != &yWhich |], + make opAnd + $ fromList + [ [essence| &xWhich = &yWhich |], + onTagged (make opNeq) xWhich (rx <$> xs) (ry <$> ys) + ] + ] + ) rule_Transform_Variant_Lt :: Rule -rule_Transform_Variant_Lt = "transform-variant-lt" `namedRule` theRule where - theRule p = do - (l,r) <- match opLt p - atLeastOneTransform (l,r) - let (x, rx) = matchManyTransforms l - let (y, ry) = matchManyTransforms r - TypeVariant{} <- typeOf x - TypeVariant{} <- typeOf y - (xWhich:xs) <- downX1 x - (yWhich:ys) <- downX1 y - return ( "Vertical rule for right transformed variant less than" - , return $ make opOr $ fromList - [ [essence| &xWhich < &yWhich |] - , make opAnd $ fromList - [ [essence| &xWhich = &yWhich |] - , onTagged (make opLt) xWhich (rx <$> xs) (ry<$> ys) - ] - ] - ) +rule_Transform_Variant_Lt = "transform-variant-lt" `namedRule` theRule + where + theRule p = do + (l, r) <- match opLt p + atLeastOneTransform (l, r) + let (x, rx) = matchManyTransforms l + let (y, ry) = matchManyTransforms r + TypeVariant {} <- typeOf x + TypeVariant {} <- typeOf y + (xWhich : xs) <- downX1 x + (yWhich : ys) <- downX1 y + return + ( "Vertical rule for right transformed variant less than", + return + $ make opOr + $ fromList + [ [essence| &xWhich < &yWhich |], + make opAnd + $ fromList + [ [essence| &xWhich = &yWhich |], + onTagged (make opLt) xWhich (rx <$> xs) (ry <$> ys) + ] + ] + ) rule_Transform_Variant_Leq :: Rule -rule_Transform_Variant_Leq = "transform-variant-leq" `namedRule` theRule where - theRule p = do - (l,r) <- match opLeq p - atLeastOneTransform (l,r) - let (x, rx) = matchManyTransforms l - let (y, ry) = matchManyTransforms r - TypeVariant{} <- typeOf x - TypeVariant{} <- typeOf y - (xWhich:xs) <- downX1 x - (yWhich:ys) <- downX1 y - return ( "Vertical rule for right transformed variant less than eq" - , return $ make opOr $ fromList - [ [essence| &xWhich < &yWhich |] - , make opAnd $ fromList - [ [essence| &xWhich = &yWhich |] - , onTagged (make opLeq) xWhich (rx <$> xs) (ry<$> ys) - ] - ] - ) +rule_Transform_Variant_Leq = "transform-variant-leq" `namedRule` theRule + where + theRule p = do + (l, r) <- match opLeq p + atLeastOneTransform (l, r) + let (x, rx) = matchManyTransforms l + let (y, ry) = matchManyTransforms r + TypeVariant {} <- typeOf x + TypeVariant {} <- typeOf y + (xWhich : xs) <- downX1 x + (yWhich : ys) <- downX1 y + return + ( "Vertical rule for right transformed variant less than eq", + return + $ make opOr + $ fromList + [ [essence| &xWhich < &yWhich |], + make opAnd + $ fromList + [ [essence| &xWhich = &yWhich |], + onTagged (make opLeq) xWhich (rx <$> xs) (ry <$> ys) + ] + ] + ) rule_Transformed_Variant_Index :: Rule -rule_Transformed_Variant_Index = "transformed-variant-index" `namedRule` theRule where +rule_Transformed_Variant_Index = "transformed-variant-index" `namedRule` theRule + where theRule p = do - (l,arg) <- match opIndexing p - atLeastOneTransform (l,l) - let (x, rx) = matchManyTransforms l - TypeVariant ds <- typeOf x - (xWhich:xs) <- downX1 x - name <- nameOut arg - argInt <- - case elemIndex name (map fst ds) of - Nothing -> failDoc "Variant indexing, not a member of the type." - Just argInt -> return argInt - return - ( "Variant indexing on:" <+> pretty p - , return $ WithLocals - (rx (atNote "Variant indexing" xs argInt)) - (DefinednessConstraints - [ [essence| &xWhich = &argInt2 |] + (l, arg) <- match opIndexing p + atLeastOneTransform (l, l) + let (x, rx) = matchManyTransforms l + TypeVariant ds <- typeOf x + (xWhich : xs) <- downX1 x + name <- nameOut arg + argInt <- + case elemIndex name (map fst ds) of + Nothing -> failDoc "Variant indexing, not a member of the type." + Just argInt -> return argInt + return + ( "Variant indexing on:" <+> pretty p, + return + $ WithLocals + (rx (atNote "Variant indexing" xs argInt)) + ( DefinednessConstraints + [ [essence| &xWhich = &argInt2 |] | let argInt2 = fromInt (fromIntegral (argInt + 1)) - ]) - ) - + ] + ) + ) rule_Transformed_Variant_Active :: Rule -rule_Transformed_Variant_Active = "transformed-variant-active" `namedRule` theRule where +rule_Transformed_Variant_Active = "transformed-variant-active" `namedRule` theRule + where theRule p = do - (l,name) <- match opActive p - atLeastOneTransform (l,l) - let (x, _) = matchManyTransforms l - TypeVariant ds <- typeOf x - (xWhich:_) <- downX1 x - argInt <- case elemIndex name (map fst ds) of - Nothing -> failDoc "Variant indexing, not a member of the type." - Just argInt -> return $ fromInt $ fromIntegral $ argInt + 1 - return - ( "Variant active on:" <+> pretty p - , return $ [essence| &xWhich = &argInt |] - ) - - - + (l, name) <- match opActive p + atLeastOneTransform (l, l) + let (x, _) = matchManyTransforms l + TypeVariant ds <- typeOf x + (xWhich : _) <- downX1 x + argInt <- case elemIndex name (map fst ds) of + Nothing -> failDoc "Variant indexing, not a member of the type." + Just argInt -> return $ fromInt $ fromIntegral $ argInt + 1 + return + ( "Variant active on:" <+> pretty p, + return [essence| &xWhich = &argInt |] + ) From 2bf2a366f06c31690a94a64bc9a878128902715b Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?=C3=96zg=C3=BCr=20Akg=C3=BCn?= Date: Sat, 13 Apr 2024 22:55:29 +0100 Subject: [PATCH 170/229] hlint --- src/Conjure/Rules/BubbleUp.hs | 6 +++--- 1 file changed, 3 insertions(+), 3 deletions(-) diff --git a/src/Conjure/Rules/BubbleUp.hs b/src/Conjure/Rules/BubbleUp.hs index 45eaeb3605..7b6b75c9e6 100644 --- a/src/Conjure/Rules/BubbleUp.hs +++ b/src/Conjure/Rules/BubbleUp.hs @@ -80,7 +80,7 @@ rule_NotBoolYet = "bubble-up-NotBoolYet" `namedRule` theRule where TypeBool -> na "rule_NotBoolYet" _ -> return () - forM_ gensOrConds $ \ goc -> case goc of + forM_ gensOrConds $ \case Generator GenDomainHasRepr{} -> return () Generator {} -> na "rule_NotBoolYet" -- no other generators, only GenDomainHasRepr Condition {} -> return () @@ -131,7 +131,7 @@ rule_ConditionInsideGeneratorDomain :: Rule rule_ConditionInsideGeneratorDomain = "bubble-up-ConditionInsideGeneratorDomain" `namedRule` theRule where theRule (Comprehension body gensOrConds) = do - (gocBefore, (goc', newConditions), gocAfter) <- matchFirst gensOrConds $ \ goc -> case goc of + (gocBefore, (goc', newConditions), gocAfter) <- matchFirst gensOrConds $ \case Generator (GenDomainHasRepr pat domain@DomainInt{}) -> do let f (WithLocals x (DefinednessConstraints cons)) = do @@ -208,7 +208,7 @@ rule_LiftVars = "bubble-up-LiftVars" `namedRule` theRule where let declsLifted = [ Declaration (FindOrGiven LocalFind nm domLifted) | (nm, dom) <- decls - , let domLifted = foldr (\ i j -> DomainMatrix (forgetRepr i) j ) dom indexDomains + , let domLifted = foldr (DomainMatrix . forgetRepr) dom indexDomains ] let consLifted = From 2b1eb714b24efc09a4f8b130d6b4907329e5bcc4 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?=C3=96zg=C3=BCr=20Akg=C3=BCn?= Date: Sat, 13 Apr 2024 23:10:05 +0100 Subject: [PATCH 171/229] rm solution json files too --- tests/custom/symmetry/basic/two-type/run.sh | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/tests/custom/symmetry/basic/two-type/run.sh b/tests/custom/symmetry/basic/two-type/run.sh index 31f6c27bb1..820e5e8de0 100755 --- a/tests/custom/symmetry/basic/two-type/run.sh +++ b/tests/custom/symmetry/basic/two-type/run.sh @@ -3,7 +3,7 @@ set -o errexit set -o nounset -rm -rf conjure-output *solutions +rm -rf conjure-output *solutions* for sym in Quick Complete; do for amount in Consecutive AllPairs AllPermutations; do @@ -11,7 +11,7 @@ for sym in Quick Complete; do echo $sym-$amount-$combine conjure solve --number-of-solutions=all --solutions-in-one-file --output-format=jsonstream --unnamed-symmetry-breaking=$sym-$amount-$combine *.essence 2>&1 cat *.json | LC_ALL=C sort - rm -rf conjure-output *solutions + rm -rf conjure-output *solutions* done done done \ No newline at end of file From 79a49086dfc38b232d256df760f8c8b3c5620633 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?=C3=96zg=C3=BCr=20Akg=C3=BCn?= Date: Sat, 13 Apr 2024 23:10:28 +0100 Subject: [PATCH 172/229] bugfix: bubbling up through comprehensions that contain lettings --- src/Conjure/Rules/BubbleUp.hs | 11 +++++------ 1 file changed, 5 insertions(+), 6 deletions(-) diff --git a/src/Conjure/Rules/BubbleUp.hs b/src/Conjure/Rules/BubbleUp.hs index 7b6b75c9e6..d644712823 100644 --- a/src/Conjure/Rules/BubbleUp.hs +++ b/src/Conjure/Rules/BubbleUp.hs @@ -192,13 +192,12 @@ rule_LiftVars = "bubble-up-LiftVars" `namedRule` theRule where -- discard for now (_conditions, generators) <- fmap mconcat $ forM gensOrConds $ \ goc -> case goc of Condition{} -> return ([goc], []) - ComprehensionLetting{} -> return ([goc], []) - Generator (GenDomainHasRepr patName domain) -> return ([], [(patName, domain)]) + ComprehensionLetting{} -> return ([], [goc]) + Generator (GenDomainHasRepr _ _) -> return ([], [goc]) _ -> na "rule_LiftVars" - - let patRefs = [ Reference patName Nothing | (patName, _) <- generators ] - let indexDomains = map snd generators + let patRefs = [ Reference patName Nothing | Generator (GenDomainHasRepr patName _domain) <- generators ] + let indexDomains = [domain | Generator (GenDomainHasRepr _patName domain) <- generators ] let upd (Reference nm _) | nm `elem` map fst decls = let r = Reference nm Nothing @@ -212,7 +211,7 @@ rule_LiftVars = "bubble-up-LiftVars" `namedRule` theRule where ] let consLifted = - [ make opAnd $ Comprehension c [Generator (GenDomainHasRepr n d) | (n,d) <- generators] + [ make opAnd $ Comprehension c generators | c <- transformBi upd cons ] From bfb10dab86feda82a5dcca5bb67b5e9e5ebd1782 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?=C3=96zg=C3=BCr=20Akg=C3=BCn?= Date: Sat, 13 Apr 2024 23:34:09 +0100 Subject: [PATCH 173/229] fixes test cases --- .../symmetry/basic/one-var/stdout.expected | 9 +- .../symmetry/basic/two-type/stdout.expected | 218 +++++++++++++++--- 2 files changed, 192 insertions(+), 35 deletions(-) diff --git a/tests/custom/symmetry/basic/one-var/stdout.expected b/tests/custom/symmetry/basic/one-var/stdout.expected index 7b7d184068..ac93f25c7e 100644 --- a/tests/custom/symmetry/basic/one-var/stdout.expected +++ b/tests/custom/symmetry/basic/one-var/stdout.expected @@ -1,5 +1,12 @@ Quick-Consecutive-Independently -Using cached models. +Adding the following unnamed symmetry breaking constraints: + such that + and([tuple (i) .<= + transform(permutation((q1, succ(q1))), tuple (i)) + | q1 : e, q1 < 4]) +Generating models for model.essence +Generated models: model000001.eprime +Saved under: conjure-output Savile Row: model000001.eprime Running minion for domain filtering. Running solver: minion diff --git a/tests/custom/symmetry/basic/two-type/stdout.expected b/tests/custom/symmetry/basic/two-type/stdout.expected index 979dd7b1c5..b63bbd272b 100644 --- a/tests/custom/symmetry/basic/two-type/stdout.expected +++ b/tests/custom/symmetry/basic/two-type/stdout.expected @@ -23,23 +23,14 @@ Adding the following unnamed symmetry breaking constraints: | q2 : f, q2 < 4]) | q1 : e, q1 < 4]) Generating models for model.essence -conjure: This should never happen, sorry! - -However, it did happen, so it must be a bug. Please report it to us! - -Conjure is actively maintained, we will get back to you as soon as possible. -You can help us by providing a minimal failing example. - -Also include the repository version for this build: unknown - -Issue tracker: http://github.com/conjure-cp/conjure/issues - - -dontCare on domain: f - -CallStack (from HasCallStack): - error, called at src/Conjure/Bug.hs:17:15 in conjure-cp-2.5.1-DjTx4wiFQ6I2X2qEEdPm4W:Conjure.Bug - bug, called at src/Conjure/Rules/DontCare.hs:31:20 in conjure-cp-2.5.1-DjTx4wiFQ6I2X2qEEdPm4W:Conjure.Rules.DontCare +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Running minion for domain filtering. +Running solver: minion +Copying solution to: model.solutions +Copying solution to: model.solutions.json +{"e": ["e_1", "e_2", "e_3", "e_4"], "f": ["f_1", "f_2", "f_3", "f_4"], "i": "e_1", "j": "f_1"} Quick-AllPairs-Independently Adding the following unnamed symmetry breaking constraints: such that @@ -65,26 +56,185 @@ Adding the following unnamed symmetry breaking constraints: | q3 : f, q4 : f, q3 < q4]) | q1 : e, q2 : e, q1 < q2]) Generating models for model.essence -conjure: This should never happen, sorry! - -However, it did happen, so it must be a bug. Please report it to us! - -Conjure is actively maintained, we will get back to you as soon as possible. -You can help us by providing a minimal failing example. - -Also include the repository version for this build: unknown - -Issue tracker: http://github.com/conjure-cp/conjure/issues - - -dontCare on domain: f - -CallStack (from HasCallStack): - error, called at src/Conjure/Bug.hs:17:15 in conjure-cp-2.5.1-DjTx4wiFQ6I2X2qEEdPm4W:Conjure.Bug - bug, called at src/Conjure/Rules/DontCare.hs:31:20 in conjure-cp-2.5.1-DjTx4wiFQ6I2X2qEEdPm4W:Conjure.Rules.DontCare +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Running minion for domain filtering. +Running solver: minion +Copying solution to: model.solutions +Copying solution to: model.solutions.json +{"e": ["e_1", "e_2", "e_3", "e_4"], "f": ["f_1", "f_2", "f_3", "f_4"], "i": "e_1", "j": "f_1"} Quick-AllPermutations-Independently Adding the following unnamed symmetry breaking constraints: such that and([(i, j) .<= transform(q1, (i, j)) | q1 : permutation of e]), and([(i, j) .<= transform(q2, (i, j)) | q2 : permutation of f]) Generating models for model.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Running minion for domain filtering. +Running solver: minion +Copying solution to: model.solutions +Copying solution to: model.solutions.json +{"e": ["e_1", "e_2", "e_3", "e_4"], "f": ["f_1", "f_2", "f_3", "f_4"], "i": "e_1", "j": "f_1"} +Quick-AllPermutations-Altogether +Adding the following unnamed symmetry breaking constraints: + such that + and([and([(i, j) .<= transform(q2, transform(q1, (i, j))) + | q2 : permutation of f]) + | q1 : permutation of e]) +Generating models for model.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Running minion for domain filtering. +Running solver: minion +Copying solution to: model.solutions +Copying solution to: model.solutions.json +{"e": ["e_1", "e_2", "e_3", "e_4"], "f": ["f_1", "f_2", "f_3", "f_4"], "i": "e_1", "j": "f_1"} +Complete-Consecutive-Independently +Adding the following unnamed symmetry breaking constraints: + such that + and([{ (i, j) .<= (i_auxFor_e, j_auxFor_e) + @ find i_auxFor_e: e + find i_auxFor_f: e + find j_auxFor_e: f + find j_auxFor_f: f + such that + (i_auxFor_e, j_auxFor_e) = + transform(permutation((q1, succ(q1))), (i, j)) + } | q1 : e, q1 < 4]), + and([{ (i, j) .<= (i_auxFor_f, j_auxFor_f) + @ find i_auxFor_e: e + find i_auxFor_f: e + find j_auxFor_e: f + find j_auxFor_f: f + such that + (i_auxFor_f, j_auxFor_f) = + transform(permutation((q2, succ(q2))), (i, j)) + } | q2 : f, q2 < 4]) +Generating models for model.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Running minion for domain filtering. +Running solver: minion +Copying solution to: model.solutions +Copying solution to: model.solutions.json +{"e": ["e_1", "e_2", "e_3", "e_4"], "f": ["f_1", "f_2", "f_3", "f_4"], "i": "e_1", "j": "f_1"} +Complete-Consecutive-Altogether +Adding the following unnamed symmetry breaking constraints: + such that + and([and([{ (i, j) .<= (i_auxFor_all, j_auxFor_all) + @ find i_auxFor_all: e + find j_auxFor_all: f + such that + (i_auxFor_all, j_auxFor_all) = + transform(permutation((q2, succ(q2))), + transform(permutation((q1, succ(q1))), (i, j))) + } | q2 : f, q2 < 4]) + | q1 : e, q1 < 4]) +Generating models for model.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Running minion for domain filtering. +Running solver: minion +Copying solution to: model.solutions +Copying solution to: model.solutions.json +{"e": ["e_1", "e_2", "e_3", "e_4"], "f": ["f_1", "f_2", "f_3", "f_4"], "i": "e_1", "j": "f_1"} +Complete-AllPairs-Independently +Adding the following unnamed symmetry breaking constraints: + such that + and([{ (i, j) .<= (i_auxFor_e, j_auxFor_e) + @ find i_auxFor_e: e + find i_auxFor_f: e + find j_auxFor_e: f + find j_auxFor_f: f + such that + (i_auxFor_e, j_auxFor_e) = transform(permutation((q1, q2)), (i, j)) + } | q1 : e, q2 : e, q1 < q2]), + and([{ (i, j) .<= (i_auxFor_f, j_auxFor_f) + @ find i_auxFor_e: e + find i_auxFor_f: e + find j_auxFor_e: f + find j_auxFor_f: f + such that + (i_auxFor_f, j_auxFor_f) = transform(permutation((q3, q4)), (i, j)) + } | q3 : f, q4 : f, q3 < q4]) +Generating models for model.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Running minion for domain filtering. +Running solver: minion +Copying solution to: model.solutions +Copying solution to: model.solutions.json +{"e": ["e_1", "e_2", "e_3", "e_4"], "f": ["f_1", "f_2", "f_3", "f_4"], "i": "e_1", "j": "f_1"} +Complete-AllPairs-Altogether +Adding the following unnamed symmetry breaking constraints: + such that + and([and([{ (i, j) .<= (i_auxFor_all, j_auxFor_all) + @ find i_auxFor_all: e + find j_auxFor_all: f + such that + (i_auxFor_all, j_auxFor_all) = + transform(permutation((q3, q4)), + transform(permutation((q1, q2)), (i, j))) + } | q3 : f, q4 : f, q3 < q4]) + | q1 : e, q2 : e, q1 < q2]) +Generating models for model.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Running minion for domain filtering. +Running solver: minion +Copying solution to: model.solutions +Copying solution to: model.solutions.json +{"e": ["e_1", "e_2", "e_3", "e_4"], "f": ["f_1", "f_2", "f_3", "f_4"], "i": "e_1", "j": "f_1"} +Complete-AllPermutations-Independently +Adding the following unnamed symmetry breaking constraints: + such that + and([{ (i, j) .<= (i_auxFor_e, j_auxFor_e) + @ find i_auxFor_e: e + find i_auxFor_f: e + find j_auxFor_e: f + find j_auxFor_f: f + such that (i_auxFor_e, j_auxFor_e) = transform(q1, (i, j)) + } | q1 : permutation of e]), + and([{ (i, j) .<= (i_auxFor_f, j_auxFor_f) + @ find i_auxFor_e: e + find i_auxFor_f: e + find j_auxFor_e: f + find j_auxFor_f: f + such that (i_auxFor_f, j_auxFor_f) = transform(q2, (i, j)) + } | q2 : permutation of f]) +Generating models for model.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Running minion for domain filtering. +Running solver: minion +Copying solution to: model.solutions +Copying solution to: model.solutions.json +{"e": ["e_1", "e_2", "e_3", "e_4"], "f": ["f_1", "f_2", "f_3", "f_4"], "i": "e_1", "j": "f_1"} +Complete-AllPermutations-Altogether +Adding the following unnamed symmetry breaking constraints: + such that + and([and([{ (i, j) .<= (i_auxFor_all, j_auxFor_all) + @ find i_auxFor_all: e + find j_auxFor_all: f + such that + (i_auxFor_all, j_auxFor_all) = transform(q2, transform(q1, (i, j))) + } | q2 : permutation of f]) + | q1 : permutation of e]) +Generating models for model.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Running minion for domain filtering. +Running solver: minion +Copying solution to: model.solutions +Copying solution to: model.solutions.json +{"e": ["e_1", "e_2", "e_3", "e_4"], "f": ["f_1", "f_2", "f_3", "f_4"], "i": "e_1", "j": "f_1"} From dae54d871e9cb19828ef92516b46316adfb71ecc Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?=C3=96zg=C3=BCr=20Akg=C3=BCn?= Date: Sun, 14 Apr 2024 00:09:05 +0100 Subject: [PATCH 174/229] edit the acceptOutput.sh scritps to take multiple dirs --- tests/custom/acceptOutput.sh | 30 ++++++++++---------- tests/exhaustive/acceptOutput.sh | 30 ++++++++++---------- tests/parse_print/acceptOutput.sh | 46 +++++++++++++++---------------- 3 files changed, 53 insertions(+), 53 deletions(-) diff --git a/tests/custom/acceptOutput.sh b/tests/custom/acceptOutput.sh index f8d958770a..cdd3913798 100755 --- a/tests/custom/acceptOutput.sh +++ b/tests/custom/acceptOutput.sh @@ -3,18 +3,18 @@ set -o errexit set -o nounset -TESTCASE="$1" - -if [ -d "${TESTCASE}" ] && [ -f "${TESTCASE}/run.sh" ] ; then - echo "Accepting the output of ${TESTCASE}" - touch "${TESTCASE}"/stdout "${TESTCASE}"/stderr - cp "${TESTCASE}"/stdout "${TESTCASE}"/stdout.expected - cp "${TESTCASE}"/stderr "${TESTCASE}"/stderr.expected - find \ - "${TESTCASE}"/stdout \ - "${TESTCASE}"/stderr \ - "${TESTCASE}"/stdout.expected \ - "${TESTCASE}"/stderr.expected \ - -size 0 \ - -exec rm {} \; -fi +for TESTCASE in $*; do + if [ -d "${TESTCASE}" ] && [ -f "${TESTCASE}/run.sh" ] ; then + echo "Accepting the output of ${TESTCASE}" + touch "${TESTCASE}"/stdout "${TESTCASE}"/stderr + cp "${TESTCASE}"/stdout "${TESTCASE}"/stdout.expected + cp "${TESTCASE}"/stderr "${TESTCASE}"/stderr.expected + find \ + "${TESTCASE}"/stdout \ + "${TESTCASE}"/stderr \ + "${TESTCASE}"/stdout.expected \ + "${TESTCASE}"/stderr.expected \ + -size 0 \ + -exec rm {} \; + fi +done diff --git a/tests/exhaustive/acceptOutput.sh b/tests/exhaustive/acceptOutput.sh index 135412560b..682820c767 100755 --- a/tests/exhaustive/acceptOutput.sh +++ b/tests/exhaustive/acceptOutput.sh @@ -4,19 +4,19 @@ set -o errexit set -o nounset shopt -s nullglob # for the loop -TESTCASE="$1" - -if [ -d "${TESTCASE}" ]; then - NUM_ESSENCE=$(ls "${TESTCASE}/"*.essence 2> /dev/null | wc -l | tr -d ' ') - NUM_INVALID=$(ls "${TESTCASE}/invalid" 2> /dev/null | wc -l | tr -d ' ') - if [ "$NUM_ESSENCE" -eq "1" ] && [ "$NUM_INVALID" -eq 0 ]; then - echo "Accepting the output of ${TESTCASE}" - rm -rf "${TESTCASE}"/expected - mkdir -p "${TESTCASE}"/expected - for file in "${TESTCASE}"/outputs/*.eprime "${TESTCASE}"/outputs/*.solution "${TESTCASE}"/outputs/*.eprime-param ; do - cp $file "${TESTCASE}"/expected/ - done - parallel --no-notice "[ -f {} ] && (cat {} | grep -v '\\$' > {}.temp ; mv {}.temp {})" \ - ::: "${TESTCASE}"/expected/*.eprime +for TESTCASE in $*; do + if [ -d "${TESTCASE}" ]; then + NUM_ESSENCE=$(ls "${TESTCASE}/"*.essence 2> /dev/null | wc -l | tr -d ' ') + NUM_INVALID=$(ls "${TESTCASE}/invalid" 2> /dev/null | wc -l | tr -d ' ') + if [ "$NUM_ESSENCE" -eq "1" ] && [ "$NUM_INVALID" -eq 0 ]; then + echo "Accepting the output of ${TESTCASE}" + rm -rf "${TESTCASE}"/expected + mkdir -p "${TESTCASE}"/expected + for file in "${TESTCASE}"/outputs/*.eprime "${TESTCASE}"/outputs/*.solution "${TESTCASE}"/outputs/*.eprime-param ; do + cp $file "${TESTCASE}"/expected/ + done + parallel --no-notice "[ -f {} ] && (cat {} | grep -v '\\$' > {}.temp ; mv {}.temp {})" \ + ::: "${TESTCASE}"/expected/*.eprime + fi fi -fi +done diff --git a/tests/parse_print/acceptOutput.sh b/tests/parse_print/acceptOutput.sh index f232f5c46a..34750a81d1 100755 --- a/tests/parse_print/acceptOutput.sh +++ b/tests/parse_print/acceptOutput.sh @@ -3,27 +3,27 @@ set -o errexit set -o nounset -TESTCASE="$1" - -if [ -d "${TESTCASE}" ]; then - NUM=$(ls "${TESTCASE}/"*.essence 2> /dev/null | grep -v disabled.essence | wc -l | tr -d ' ') - if [ "$NUM" -eq "1" ]; then - echo "Accepting the output of ${TESTCASE}" - touch "${TESTCASE}"/stdout "${TESTCASE}"/model.json "${TESTCASE}"/stderr "${TESTCASE}"/typecheck - cp "${TESTCASE}"/stdout "${TESTCASE}"/stdout.expected - cp "${TESTCASE}"/model.json "${TESTCASE}"/model.expected.json - cp "${TESTCASE}"/stderr "${TESTCASE}"/stderr.expected - cp "${TESTCASE}"/typecheck "${TESTCASE}"/typecheck.expected - find \ - "${TESTCASE}"/stdout \ - "${TESTCASE}"/model.json \ - "${TESTCASE}"/stderr \ - "${TESTCASE}"/typecheck \ - "${TESTCASE}"/stdout.expected \ - "${TESTCASE}"/model.expected.json \ - "${TESTCASE}"/stderr.expected \ - "${TESTCASE}"/typecheck.expected \ - -size 0 \ - -exec rm {} \; +for TESTCASE in $*; do + if [ -d "${TESTCASE}" ]; then + NUM=$(ls "${TESTCASE}/"*.essence 2> /dev/null | grep -v disabled.essence | wc -l | tr -d ' ') + if [ "$NUM" -eq "1" ]; then + echo "Accepting the output of ${TESTCASE}" + touch "${TESTCASE}"/stdout "${TESTCASE}"/model.json "${TESTCASE}"/stderr "${TESTCASE}"/typecheck + cp "${TESTCASE}"/stdout "${TESTCASE}"/stdout.expected + cp "${TESTCASE}"/model.json "${TESTCASE}"/model.expected.json + cp "${TESTCASE}"/stderr "${TESTCASE}"/stderr.expected + cp "${TESTCASE}"/typecheck "${TESTCASE}"/typecheck.expected + find \ + "${TESTCASE}"/stdout \ + "${TESTCASE}"/model.json \ + "${TESTCASE}"/stderr \ + "${TESTCASE}"/typecheck \ + "${TESTCASE}"/stdout.expected \ + "${TESTCASE}"/model.expected.json \ + "${TESTCASE}"/stderr.expected \ + "${TESTCASE}"/typecheck.expected \ + -size 0 \ + -exec rm {} \; + fi fi -fi +done From 528563faf4aee41ba39c8e89b61ff2c6ee62c691 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?=C3=96zg=C3=BCr=20Akg=C3=BCn?= Date: Sun, 14 Apr 2024 00:09:15 +0100 Subject: [PATCH 175/229] stop at first failure --- tests/custom/symmetry/basic/one-var/run.sh | 7 +++++++ tests/custom/symmetry/basic/two-var/run.sh | 7 +++++++ 2 files changed, 14 insertions(+) diff --git a/tests/custom/symmetry/basic/one-var/run.sh b/tests/custom/symmetry/basic/one-var/run.sh index 0ca7a7af18..820e5e8de0 100755 --- a/tests/custom/symmetry/basic/one-var/run.sh +++ b/tests/custom/symmetry/basic/one-var/run.sh @@ -1,3 +1,10 @@ +#!/bin/bash + +set -o errexit +set -o nounset + +rm -rf conjure-output *solutions* + for sym in Quick Complete; do for amount in Consecutive AllPairs AllPermutations; do for combine in Independently Altogether; do diff --git a/tests/custom/symmetry/basic/two-var/run.sh b/tests/custom/symmetry/basic/two-var/run.sh index 0ca7a7af18..820e5e8de0 100755 --- a/tests/custom/symmetry/basic/two-var/run.sh +++ b/tests/custom/symmetry/basic/two-var/run.sh @@ -1,3 +1,10 @@ +#!/bin/bash + +set -o errexit +set -o nounset + +rm -rf conjure-output *solutions* + for sym in Quick Complete; do for amount in Consecutive AllPairs AllPermutations; do for combine in Independently Altogether; do From 23a93188f1d10b297f13feb4448a5ac62a710175 Mon Sep 17 00:00:00 2001 From: Chris Jefferson Date: Sun, 14 Apr 2024 10:27:50 +0800 Subject: [PATCH 176/229] Add set tests --- .../custom/symmetry/set/one-var/model.essence | 3 + tests/custom/symmetry/set/one-var/run.sh | 17 ++ .../symmetry/set/one-var/stdout.expected | 181 ++++++++++++++++ .../symmetry/set/two-type/model.essence | 5 + tests/custom/symmetry/set/two-type/run.sh | 17 ++ .../symmetry/set/two-type/stdout.expected | 90 ++++++++ .../custom/symmetry/set/two-var/model.essence | 4 + tests/custom/symmetry/set/two-var/run.sh | 17 ++ .../symmetry/set/two-var/stdout.expected | 203 ++++++++++++++++++ 9 files changed, 537 insertions(+) create mode 100644 tests/custom/symmetry/set/one-var/model.essence create mode 100755 tests/custom/symmetry/set/one-var/run.sh create mode 100644 tests/custom/symmetry/set/one-var/stdout.expected create mode 100644 tests/custom/symmetry/set/two-type/model.essence create mode 100755 tests/custom/symmetry/set/two-type/run.sh create mode 100644 tests/custom/symmetry/set/two-type/stdout.expected create mode 100644 tests/custom/symmetry/set/two-var/model.essence create mode 100755 tests/custom/symmetry/set/two-var/run.sh create mode 100644 tests/custom/symmetry/set/two-var/stdout.expected diff --git a/tests/custom/symmetry/set/one-var/model.essence b/tests/custom/symmetry/set/one-var/model.essence new file mode 100644 index 0000000000..0f7b8b8ac2 --- /dev/null +++ b/tests/custom/symmetry/set/one-var/model.essence @@ -0,0 +1,3 @@ +letting e be new type of size 4 + +find i: set of e \ No newline at end of file diff --git a/tests/custom/symmetry/set/one-var/run.sh b/tests/custom/symmetry/set/one-var/run.sh new file mode 100755 index 0000000000..7d423ef67a --- /dev/null +++ b/tests/custom/symmetry/set/one-var/run.sh @@ -0,0 +1,17 @@ +#!/bin/bash + +set -o errexit +set -o nounset + +rm -rf conjure-output *solutions* + +for sym in Complete; do + for amount in Consecutive AllPairs AllPermutations; do + for combine in Independently Altogether; do + echo $sym-$amount-$combine + conjure solve --number-of-solutions=all --solutions-in-one-file --output-format=jsonstream --unnamed-symmetry-breaking=$sym-$amount-$combine *.essence 2>&1 + cat *.json | LC_ALL=C sort + rm -rf conjure-output *solutions* + done + done +done \ No newline at end of file diff --git a/tests/custom/symmetry/set/one-var/stdout.expected b/tests/custom/symmetry/set/one-var/stdout.expected new file mode 100644 index 0000000000..7b7d184068 --- /dev/null +++ b/tests/custom/symmetry/set/one-var/stdout.expected @@ -0,0 +1,181 @@ +Quick-Consecutive-Independently +Using cached models. +Savile Row: model000001.eprime +Running minion for domain filtering. +Running solver: minion +Copying solution to: model.solutions +Copying solution to: model.solutions.json +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": "e_1"} +Quick-Consecutive-Altogether +Adding the following unnamed symmetry breaking constraints: + such that + and([tuple (i) .<= + transform(permutation((q1, succ(q1))), tuple (i)) + | q1 : e, q1 < 4]) +Generating models for model.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Running minion for domain filtering. +Running solver: minion +Copying solution to: model.solutions +Copying solution to: model.solutions.json +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": "e_1"} +Quick-AllPairs-Independently +Adding the following unnamed symmetry breaking constraints: + such that + and([tuple (i) .<= transform(permutation((q1, q2)), tuple (i)) + | q1 : e, q2 : e, q1 < q2]) +Generating models for model.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Running minion for domain filtering. +Running solver: minion +Copying solution to: model.solutions +Copying solution to: model.solutions.json +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": "e_1"} +Quick-AllPairs-Altogether +Adding the following unnamed symmetry breaking constraints: + such that + and([tuple (i) .<= transform(permutation((q1, q2)), tuple (i)) + | q1 : e, q2 : e, q1 < q2]) +Generating models for model.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Running minion for domain filtering. +Running solver: minion +Copying solution to: model.solutions +Copying solution to: model.solutions.json +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": "e_1"} +Quick-AllPermutations-Independently +Adding the following unnamed symmetry breaking constraints: + such that + and([tuple (i) .<= transform(q1, tuple (i)) + | q1 : permutation of e]) +Generating models for model.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Running minion for domain filtering. +Running solver: minion +Copying solution to: model.solutions +Copying solution to: model.solutions.json +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": "e_1"} +Quick-AllPermutations-Altogether +Adding the following unnamed symmetry breaking constraints: + such that + and([tuple (i) .<= transform(q1, tuple (i)) + | q1 : permutation of e]) +Generating models for model.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Running minion for domain filtering. +Running solver: minion +Copying solution to: model.solutions +Copying solution to: model.solutions.json +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": "e_1"} +Complete-Consecutive-Independently +Adding the following unnamed symmetry breaking constraints: + such that + and([{ tuple (i) .<= tuple (i_auxFor_e) + @ find i_auxFor_e: e + such that + tuple (i_auxFor_e) = + transform(permutation((q1, succ(q1))), tuple (i)) + } | q1 : e, q1 < 4]) +Generating models for model.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Running minion for domain filtering. +Running solver: minion +Copying solution to: model.solutions +Copying solution to: model.solutions.json +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": "e_1"} +Complete-Consecutive-Altogether +Adding the following unnamed symmetry breaking constraints: + such that + and([{ tuple (i) .<= tuple (i_auxFor_all) + @ find i_auxFor_all: e + such that + tuple (i_auxFor_all) = + transform(permutation((q1, succ(q1))), tuple (i)) + } | q1 : e, q1 < 4]) +Generating models for model.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Running minion for domain filtering. +Running solver: minion +Copying solution to: model.solutions +Copying solution to: model.solutions.json +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": "e_1"} +Complete-AllPairs-Independently +Adding the following unnamed symmetry breaking constraints: + such that + and([{ tuple (i) .<= tuple (i_auxFor_e) + @ find i_auxFor_e: e + such that + tuple (i_auxFor_e) = transform(permutation((q1, q2)), tuple (i)) + } | q1 : e, q2 : e, q1 < q2]) +Generating models for model.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Running minion for domain filtering. +Running solver: minion +Copying solution to: model.solutions +Copying solution to: model.solutions.json +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": "e_1"} +Complete-AllPairs-Altogether +Adding the following unnamed symmetry breaking constraints: + such that + and([{ tuple (i) .<= tuple (i_auxFor_all) + @ find i_auxFor_all: e + such that + tuple (i_auxFor_all) = transform(permutation((q1, q2)), tuple (i)) + } | q1 : e, q2 : e, q1 < q2]) +Generating models for model.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Running minion for domain filtering. +Running solver: minion +Copying solution to: model.solutions +Copying solution to: model.solutions.json +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": "e_1"} +Complete-AllPermutations-Independently +Adding the following unnamed symmetry breaking constraints: + such that + and([{ tuple (i) .<= tuple (i_auxFor_e) + @ find i_auxFor_e: e + such that tuple (i_auxFor_e) = transform(q1, tuple (i)) + } | q1 : permutation of e]) +Generating models for model.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Running minion for domain filtering. +Running solver: minion +Copying solution to: model.solutions +Copying solution to: model.solutions.json +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": "e_1"} +Complete-AllPermutations-Altogether +Adding the following unnamed symmetry breaking constraints: + such that + and([{ tuple (i) .<= tuple (i_auxFor_all) + @ find i_auxFor_all: e + such that tuple (i_auxFor_all) = transform(q1, tuple (i)) + } | q1 : permutation of e]) +Generating models for model.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Running minion for domain filtering. +Running solver: minion +Copying solution to: model.solutions +Copying solution to: model.solutions.json +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": "e_1"} diff --git a/tests/custom/symmetry/set/two-type/model.essence b/tests/custom/symmetry/set/two-type/model.essence new file mode 100644 index 0000000000..a541c3d4ea --- /dev/null +++ b/tests/custom/symmetry/set/two-type/model.essence @@ -0,0 +1,5 @@ +letting e be new type of size 4 +letting f be new type of size 4 + +find i: e +find j: f diff --git a/tests/custom/symmetry/set/two-type/run.sh b/tests/custom/symmetry/set/two-type/run.sh new file mode 100755 index 0000000000..820e5e8de0 --- /dev/null +++ b/tests/custom/symmetry/set/two-type/run.sh @@ -0,0 +1,17 @@ +#!/bin/bash + +set -o errexit +set -o nounset + +rm -rf conjure-output *solutions* + +for sym in Quick Complete; do + for amount in Consecutive AllPairs AllPermutations; do + for combine in Independently Altogether; do + echo $sym-$amount-$combine + conjure solve --number-of-solutions=all --solutions-in-one-file --output-format=jsonstream --unnamed-symmetry-breaking=$sym-$amount-$combine *.essence 2>&1 + cat *.json | LC_ALL=C sort + rm -rf conjure-output *solutions* + done + done +done \ No newline at end of file diff --git a/tests/custom/symmetry/set/two-type/stdout.expected b/tests/custom/symmetry/set/two-type/stdout.expected new file mode 100644 index 0000000000..979dd7b1c5 --- /dev/null +++ b/tests/custom/symmetry/set/two-type/stdout.expected @@ -0,0 +1,90 @@ +Quick-Consecutive-Independently +Adding the following unnamed symmetry breaking constraints: + such that + and([(i, j) .<= transform(permutation((q1, succ(q1))), (i, j)) + | q1 : e, q1 < 4]), + and([(i, j) .<= transform(permutation((q2, succ(q2))), (i, j)) + | q2 : f, q2 < 4]) +Generating models for model.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Running minion for domain filtering. +Running solver: minion +Copying solution to: model.solutions +Copying solution to: model.solutions.json +{"e": ["e_1", "e_2", "e_3", "e_4"], "f": ["f_1", "f_2", "f_3", "f_4"], "i": "e_1", "j": "f_1"} +Quick-Consecutive-Altogether +Adding the following unnamed symmetry breaking constraints: + such that + and([and([(i, j) .<= + transform(permutation((q2, succ(q2))), + transform(permutation((q1, succ(q1))), (i, j))) + | q2 : f, q2 < 4]) + | q1 : e, q1 < 4]) +Generating models for model.essence +conjure: This should never happen, sorry! + +However, it did happen, so it must be a bug. Please report it to us! + +Conjure is actively maintained, we will get back to you as soon as possible. +You can help us by providing a minimal failing example. + +Also include the repository version for this build: unknown + +Issue tracker: http://github.com/conjure-cp/conjure/issues + + +dontCare on domain: f + +CallStack (from HasCallStack): + error, called at src/Conjure/Bug.hs:17:15 in conjure-cp-2.5.1-DjTx4wiFQ6I2X2qEEdPm4W:Conjure.Bug + bug, called at src/Conjure/Rules/DontCare.hs:31:20 in conjure-cp-2.5.1-DjTx4wiFQ6I2X2qEEdPm4W:Conjure.Rules.DontCare +Quick-AllPairs-Independently +Adding the following unnamed symmetry breaking constraints: + such that + and([(i, j) .<= transform(permutation((q1, q2)), (i, j)) + | q1 : e, q2 : e, q1 < q2]), + and([(i, j) .<= transform(permutation((q3, q4)), (i, j)) + | q3 : f, q4 : f, q3 < q4]) +Generating models for model.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Running minion for domain filtering. +Running solver: minion +Copying solution to: model.solutions +Copying solution to: model.solutions.json +{"e": ["e_1", "e_2", "e_3", "e_4"], "f": ["f_1", "f_2", "f_3", "f_4"], "i": "e_1", "j": "f_1"} +Quick-AllPairs-Altogether +Adding the following unnamed symmetry breaking constraints: + such that + and([and([(i, j) .<= + transform(permutation((q3, q4)), + transform(permutation((q1, q2)), (i, j))) + | q3 : f, q4 : f, q3 < q4]) + | q1 : e, q2 : e, q1 < q2]) +Generating models for model.essence +conjure: This should never happen, sorry! + +However, it did happen, so it must be a bug. Please report it to us! + +Conjure is actively maintained, we will get back to you as soon as possible. +You can help us by providing a minimal failing example. + +Also include the repository version for this build: unknown + +Issue tracker: http://github.com/conjure-cp/conjure/issues + + +dontCare on domain: f + +CallStack (from HasCallStack): + error, called at src/Conjure/Bug.hs:17:15 in conjure-cp-2.5.1-DjTx4wiFQ6I2X2qEEdPm4W:Conjure.Bug + bug, called at src/Conjure/Rules/DontCare.hs:31:20 in conjure-cp-2.5.1-DjTx4wiFQ6I2X2qEEdPm4W:Conjure.Rules.DontCare +Quick-AllPermutations-Independently +Adding the following unnamed symmetry breaking constraints: + such that + and([(i, j) .<= transform(q1, (i, j)) | q1 : permutation of e]), + and([(i, j) .<= transform(q2, (i, j)) | q2 : permutation of f]) +Generating models for model.essence diff --git a/tests/custom/symmetry/set/two-var/model.essence b/tests/custom/symmetry/set/two-var/model.essence new file mode 100644 index 0000000000..09ffd8e5de --- /dev/null +++ b/tests/custom/symmetry/set/two-var/model.essence @@ -0,0 +1,4 @@ +letting e be new type of size 4 + +find i: e +find j: e diff --git a/tests/custom/symmetry/set/two-var/run.sh b/tests/custom/symmetry/set/two-var/run.sh new file mode 100755 index 0000000000..820e5e8de0 --- /dev/null +++ b/tests/custom/symmetry/set/two-var/run.sh @@ -0,0 +1,17 @@ +#!/bin/bash + +set -o errexit +set -o nounset + +rm -rf conjure-output *solutions* + +for sym in Quick Complete; do + for amount in Consecutive AllPairs AllPermutations; do + for combine in Independently Altogether; do + echo $sym-$amount-$combine + conjure solve --number-of-solutions=all --solutions-in-one-file --output-format=jsonstream --unnamed-symmetry-breaking=$sym-$amount-$combine *.essence 2>&1 + cat *.json | LC_ALL=C sort + rm -rf conjure-output *solutions* + done + done +done \ No newline at end of file diff --git a/tests/custom/symmetry/set/two-var/stdout.expected b/tests/custom/symmetry/set/two-var/stdout.expected new file mode 100644 index 0000000000..5c05e77f4b --- /dev/null +++ b/tests/custom/symmetry/set/two-var/stdout.expected @@ -0,0 +1,203 @@ +Quick-Consecutive-Independently +Adding the following unnamed symmetry breaking constraints: + such that + and([(i, j) .<= transform(permutation((q1, succ(q1))), (i, j)) + | q1 : e, q1 < 4]) +Generating models for model.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Running minion for domain filtering. +Running solver: minion +Copying solution to: model.solutions +Copying solution to: model.solutions.json +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": "e_1", "j": "e_1"} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": "e_1", "j": "e_2"} +Quick-Consecutive-Altogether +Adding the following unnamed symmetry breaking constraints: + such that + and([(i, j) .<= transform(permutation((q1, succ(q1))), (i, j)) + | q1 : e, q1 < 4]) +Generating models for model.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Running minion for domain filtering. +Running solver: minion +Copying solution to: model.solutions +Copying solution to: model.solutions.json +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": "e_1", "j": "e_1"} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": "e_1", "j": "e_2"} +Quick-AllPairs-Independently +Adding the following unnamed symmetry breaking constraints: + such that + and([(i, j) .<= transform(permutation((q1, q2)), (i, j)) + | q1 : e, q2 : e, q1 < q2]) +Generating models for model.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Running minion for domain filtering. +Running solver: minion +Copying solution to: model.solutions +Copying solution to: model.solutions.json +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": "e_1", "j": "e_1"} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": "e_1", "j": "e_2"} +Quick-AllPairs-Altogether +Adding the following unnamed symmetry breaking constraints: + such that + and([(i, j) .<= transform(permutation((q1, q2)), (i, j)) + | q1 : e, q2 : e, q1 < q2]) +Generating models for model.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Running minion for domain filtering. +Running solver: minion +Copying solution to: model.solutions +Copying solution to: model.solutions.json +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": "e_1", "j": "e_1"} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": "e_1", "j": "e_2"} +Quick-AllPermutations-Independently +Adding the following unnamed symmetry breaking constraints: + such that + and([(i, j) .<= transform(q1, (i, j)) | q1 : permutation of e]) +Generating models for model.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Running minion for domain filtering. +Running solver: minion +Copying solution to: model.solutions +Copying solution to: model.solutions.json +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": "e_1", "j": "e_1"} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": "e_1", "j": "e_2"} +Quick-AllPermutations-Altogether +Adding the following unnamed symmetry breaking constraints: + such that + and([(i, j) .<= transform(q1, (i, j)) | q1 : permutation of e]) +Generating models for model.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Running minion for domain filtering. +Running solver: minion +Copying solution to: model.solutions +Copying solution to: model.solutions.json +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": "e_1", "j": "e_1"} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": "e_1", "j": "e_2"} +Complete-Consecutive-Independently +Adding the following unnamed symmetry breaking constraints: + such that + and([{ (i, j) .<= (i_auxFor_e, j_auxFor_e) + @ find i_auxFor_e: e + find j_auxFor_e: e + such that + (i_auxFor_e, j_auxFor_e) = + transform(permutation((q1, succ(q1))), (i, j)) + } | q1 : e, q1 < 4]) +Generating models for model.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Running minion for domain filtering. +Running solver: minion +Copying solution to: model.solutions +Copying solution to: model.solutions.json +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": "e_1", "j": "e_1"} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": "e_1", "j": "e_2"} +Complete-Consecutive-Altogether +Adding the following unnamed symmetry breaking constraints: + such that + and([{ (i, j) .<= (i_auxFor_all, j_auxFor_all) + @ find i_auxFor_all: e + find j_auxFor_all: e + such that + (i_auxFor_all, j_auxFor_all) = + transform(permutation((q1, succ(q1))), (i, j)) + } | q1 : e, q1 < 4]) +Generating models for model.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Running minion for domain filtering. +Running solver: minion +Copying solution to: model.solutions +Copying solution to: model.solutions.json +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": "e_1", "j": "e_1"} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": "e_1", "j": "e_2"} +Complete-AllPairs-Independently +Adding the following unnamed symmetry breaking constraints: + such that + and([{ (i, j) .<= (i_auxFor_e, j_auxFor_e) + @ find i_auxFor_e: e + find j_auxFor_e: e + such that + (i_auxFor_e, j_auxFor_e) = transform(permutation((q1, q2)), (i, j)) + } | q1 : e, q2 : e, q1 < q2]) +Generating models for model.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Running minion for domain filtering. +Running solver: minion +Copying solution to: model.solutions +Copying solution to: model.solutions.json +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": "e_1", "j": "e_1"} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": "e_1", "j": "e_2"} +Complete-AllPairs-Altogether +Adding the following unnamed symmetry breaking constraints: + such that + and([{ (i, j) .<= (i_auxFor_all, j_auxFor_all) + @ find i_auxFor_all: e + find j_auxFor_all: e + such that + (i_auxFor_all, j_auxFor_all) = + transform(permutation((q1, q2)), (i, j)) + } | q1 : e, q2 : e, q1 < q2]) +Generating models for model.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Running minion for domain filtering. +Running solver: minion +Copying solution to: model.solutions +Copying solution to: model.solutions.json +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": "e_1", "j": "e_1"} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": "e_1", "j": "e_2"} +Complete-AllPermutations-Independently +Adding the following unnamed symmetry breaking constraints: + such that + and([{ (i, j) .<= (i_auxFor_e, j_auxFor_e) + @ find i_auxFor_e: e + find j_auxFor_e: e + such that (i_auxFor_e, j_auxFor_e) = transform(q1, (i, j)) + } | q1 : permutation of e]) +Generating models for model.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Running minion for domain filtering. +Running solver: minion +Copying solution to: model.solutions +Copying solution to: model.solutions.json +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": "e_1", "j": "e_1"} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": "e_1", "j": "e_2"} +Complete-AllPermutations-Altogether +Adding the following unnamed symmetry breaking constraints: + such that + and([{ (i, j) .<= (i_auxFor_all, j_auxFor_all) + @ find i_auxFor_all: e + find j_auxFor_all: e + such that (i_auxFor_all, j_auxFor_all) = transform(q1, (i, j)) + } | q1 : permutation of e]) +Generating models for model.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: model000001.eprime +Running minion for domain filtering. +Running solver: minion +Copying solution to: model.solutions +Copying solution to: model.solutions.json +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": "e_1", "j": "e_1"} +{"e": ["e_1", "e_2", "e_3", "e_4"], "i": "e_1", "j": "e_2"} From ca742f6c116560f7e8df17488c76dc489ac8ec4b Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?=C3=96zg=C3=BCr=20Akg=C3=BCn?= Date: Wed, 26 Jun 2024 10:18:33 +0100 Subject: [PATCH 177/229] adding quickPermutationOrder --- .vscode/settings.json | 5 + conjure-cp.cabal | 1 + src/Conjure/Compute/DomainOf.hs | 4 + src/Conjure/Language/EvaluateOp.hs | 4 +- src/Conjure/Language/Expression/Op.hs | 1 + .../Language/Expression/Op/Internal/Common.hs | 1 + .../Expression/Op/QuickPermutationOrder.hs | 63 ++++++++ src/Conjure/Language/Lexemes.hs | 4 + src/Conjure/Language/Validator.hs | 38 +++-- src/Conjure/Rules/DontCare.hs | 12 +- src/Conjure/UI/Model.hs | 141 +++++++++++------- tests/custom/symmetry/set/one-var/run.sh | 3 +- 12 files changed, 202 insertions(+), 75 deletions(-) create mode 100644 .vscode/settings.json create mode 100644 src/Conjure/Language/Expression/Op/QuickPermutationOrder.hs diff --git a/.vscode/settings.json b/.vscode/settings.json new file mode 100644 index 0000000000..9e6a46f913 --- /dev/null +++ b/.vscode/settings.json @@ -0,0 +1,5 @@ +{ + "haskell.plugin.hlint.config.flags": [ + "--hint=.hlint.yaml" + ], +} \ No newline at end of file diff --git a/conjure-cp.cabal b/conjure-cp.cabal index af130db38c..1107b14113 100644 --- a/conjure-cp.cabal +++ b/conjure-cp.cabal @@ -64,6 +64,7 @@ Library , Conjure.Language.Expression.Op.Compose , Conjure.Language.Expression.Op.AttributeAsConstraint , Conjure.Language.Expression.Op.CatchUndef + , Conjure.Language.Expression.Op.QuickPermutationOrder , Conjure.Language.Expression.Op.Defined , Conjure.Language.Expression.Op.Div , Conjure.Language.Expression.Op.DontCare diff --git a/src/Conjure/Compute/DomainOf.hs b/src/Conjure/Compute/DomainOf.hs index 4f268716e8..8410d64cc7 100644 --- a/src/Conjure/Compute/DomainOf.hs +++ b/src/Conjure/Compute/DomainOf.hs @@ -180,6 +180,7 @@ instance (DomainOf x, TypeOf x, Pretty x, ExpressionLike x, Domain () x :< x, Do domainOf (MkOpTwoBars x) = domainOf x domainOf (MkOpUnion x) = domainOf x domainOf (MkOpXor x) = domainOf x + domainOf (MkOpQuickPermutationOrder x) = domainOf x indexDomainsOf (MkOpActive x) = indexDomainsOf x indexDomainsOf (MkOpAllDiff x) = indexDomainsOf x @@ -258,6 +259,7 @@ instance (DomainOf x, TypeOf x, Pretty x, ExpressionLike x, Domain () x :< x, Do indexDomainsOf (MkOpTwoBars x) = indexDomainsOf x indexDomainsOf (MkOpUnion x) = indexDomainsOf x indexDomainsOf (MkOpXor x) = indexDomainsOf x + indexDomainsOf (MkOpQuickPermutationOrder x) = indexDomainsOf x instance DomainOf Constant where domainOf ConstantBool{} = return DomainBool @@ -692,3 +694,5 @@ instance (Pretty x, TypeOf x, Domain () x :< x) => DomainOf (OpTwoBars x) where instance (Pretty x, TypeOf x) => DomainOf (OpUnion x) where domainOf op = mkDomainAny ("OpUnion:" <++> pretty op) <$> typeOf op +instance DomainOf (OpQuickPermutationOrder x) where + domainOf _ = return DomainBool diff --git a/src/Conjure/Language/EvaluateOp.hs b/src/Conjure/Language/EvaluateOp.hs index f75e77515a..142811f3ae 100644 --- a/src/Conjure/Language/EvaluateOp.hs +++ b/src/Conjure/Language/EvaluateOp.hs @@ -837,6 +837,8 @@ instance EvaluateOp OpXor where evaluateOp (OpXor x) = ConstantBool . xor <$> boolsOut x where xor xs = odd (length [ () | True <- xs ]) +instance EvaluateOp OpQuickPermutationOrder where + evaluateOp op = na $ "evaluateOp{OpQuickPermutationOrder}:" <++> pretty (show op) boolsOut :: MonadFailDoc m => Constant -> m [Bool] boolsOut (viewConstantMatrix -> Just (_, cs)) = concatMapM boolsOut cs @@ -1030,4 +1032,4 @@ instance EvaluateOp Op where evaluateOp (MkOpTwoBars x) = evaluateOp x evaluateOp (MkOpUnion x) = evaluateOp x evaluateOp (MkOpXor x) = evaluateOp x - + evaluateOp (MkOpQuickPermutationOrder x) = evaluateOp x diff --git a/src/Conjure/Language/Expression/Op.hs b/src/Conjure/Language/Expression/Op.hs index 0d8728b674..c897a27aee 100644 --- a/src/Conjure/Language/Expression/Op.hs +++ b/src/Conjure/Language/Expression/Op.hs @@ -104,6 +104,7 @@ mkOp op xs = case op of (arg xs 1 "allDiffExcept") L_catchUndef -> inject $ MkOpCatchUndef $ OpCatchUndef (arg xs 0 "catchUndef") (arg xs 1 "catchUndef") + L_quickPermutationOrder -> inject $ MkOpQuickPermutationOrder $ OpQuickPermutationOrder (arg xs 0 "quickPermutationOrder") (arg xs 1 "quickPermutationOrder") L_dontCare -> inject $ MkOpDontCare $ OpDontCare (arg xs 0 "dontCare") L_toSet -> inject $ MkOpToSet $ OpToSet False (arg xs 0 "toSet") L_toMSet -> inject $ MkOpToMSet $ OpToMSet (arg xs 0 "toMSet") diff --git a/src/Conjure/Language/Expression/Op/Internal/Common.hs b/src/Conjure/Language/Expression/Op/Internal/Common.hs index 780e35af91..7e2e264a1a 100644 --- a/src/Conjure/Language/Expression/Op/Internal/Common.hs +++ b/src/Conjure/Language/Expression/Op/Internal/Common.hs @@ -292,6 +292,7 @@ functionals = , L_atleast , L_atmost , L_catchUndef + , L_quickPermutationOrder , L_dontCare , L_hist , L_factorial diff --git a/src/Conjure/Language/Expression/Op/QuickPermutationOrder.hs b/src/Conjure/Language/Expression/Op/QuickPermutationOrder.hs new file mode 100644 index 0000000000..f0881f6d7e --- /dev/null +++ b/src/Conjure/Language/Expression/Op/QuickPermutationOrder.hs @@ -0,0 +1,63 @@ +{-# LANGUAGE DeriveDataTypeable #-} +{-# LANGUAGE DeriveFoldable #-} +{-# LANGUAGE DeriveFunctor #-} +{-# LANGUAGE DeriveGeneric #-} +{-# LANGUAGE DeriveTraversable #-} +{-# LANGUAGE InstanceSigs #-} + +module Conjure.Language.Expression.Op.QuickPermutationOrder where + +import Conjure.Language.Expression.Op.Internal.Common +import Conjure.Prelude +import Data.Aeson qualified as JSON -- aeson +import Data.Aeson.KeyMap qualified as KM +import Data.Vector qualified as V -- vector + + +-- first argument: the value (x) +-- second argument: the tuple of permutations to apply (ps) +-- the effect is a subset of: x .<= transform(ps, x) +data OpQuickPermutationOrder x = OpQuickPermutationOrder x x + deriving (Eq, Ord, Show, Data, Functor, Traversable, Foldable, Typeable, Generic) + +instance (Serialize x) => Serialize (OpQuickPermutationOrder x) + +instance (Hashable x) => Hashable (OpQuickPermutationOrder x) + +instance (ToJSON x) => ToJSON (OpQuickPermutationOrder x) where toJSON :: ToJSON x => OpQuickPermutationOrder x -> JSON.Value + toJSON = genericToJSON jsonOptions + +instance (FromJSON x) => FromJSON (OpQuickPermutationOrder x) where parseJSON = genericParseJSON jsonOptions + +instance (TypeOf x, Pretty x, ExpressionLike x) => TypeOf (OpQuickPermutationOrder x) where + typeOf p@(OpQuickPermutationOrder x perm) = do + _tyX <- typeOf x + case listOut perm of + Just perms -> do + forM_ perms $ \ pe -> do + tyP <- typeOf pe + case tyP of + TypePermutation {} -> return () + _ -> raiseTypeError p + _ -> raiseTypeError p + return TypeBool + +instance SimplifyOp OpQuickPermutationOrder x where + simplifyOp _ = na "simplifyOp{OpQuickPermutationOrder}" + +instance (Pretty x) => Pretty (OpQuickPermutationOrder x) where + prettyPrec _ (OpQuickPermutationOrder a b) = "quickPermutationOrder" <> prettyList prParens "," [a, b] + +instance (VarSymBreakingDescription x, ExpressionLike x) => VarSymBreakingDescription (OpQuickPermutationOrder x) where + varSymBreakingDescription (OpQuickPermutationOrder x y) = + JSON.Object + $ KM.fromList + [ ("type", JSON.String "OpQuickPermutationOrder"), + ( "children", + JSON.Array + $ V.fromList + [ varSymBreakingDescription x, + varSymBreakingDescription y + ] + ) + ] diff --git a/src/Conjure/Language/Lexemes.hs b/src/Conjure/Language/Lexemes.hs index 9b2ad862b7..93ea3d8322 100644 --- a/src/Conjure/Language/Lexemes.hs +++ b/src/Conjure/Language/Lexemes.hs @@ -166,6 +166,8 @@ data Lexeme | L_catchUndef + | L_quickPermutationOrder + -- matrix only operators | L_flatten | L_concatenate @@ -428,6 +430,8 @@ lexemes = sortBy (flip (comparing (T.length . fst))) $ map swap , ( L_dontCare, "dontCare" ) , ( L_catchUndef, "catchUndef" ) + , ( L_quickPermutationOrder, "quickPermutationOrder" ) + , ( L_flatten, "flatten" ) , ( L_concatenate, "concatenate" ) , ( L_normIndices, "normIndices" ) diff --git a/src/Conjure/Language/Validator.hs b/src/Conjure/Language/Validator.hs index ace27652a4..1b5a3d21f7 100644 --- a/src/Conjure/Language/Validator.hs +++ b/src/Conjure/Language/Validator.hs @@ -2186,6 +2186,7 @@ functionOps l = case l of L_allDiff -> unFuncV listOrMatrix (const $ pure TypeBool) L_alldifferent_except -> biFuncV (indep listOrMatrix enumerable) (const2 TypeBool) L_catchUndef -> biFuncV unifies (\a b -> pure $ mostDefinedS $ catMaybes [a, b]) + L_quickPermutationOrder -> biFunc quickPermutationOrderArgs quickPermutationOrderTypes L_dontCare -> unFunc anyType (const $ pure TypeBool) L_toSet -> unFuncV toSetArgs typeToSet L_toMSet -> unFuncV toMSetArgs typeToMSet @@ -2379,6 +2380,14 @@ functionOps l = case l of Just (Kind ValueType {} (TypeFunction _ to')) -> to' _ -> TypeAny + -- TODO: validate + quickPermutationOrderArgs :: Arg -> Arg -> Validator () + quickPermutationOrderArgs _ _ = return (pure ()) + + -- TODO + quickPermutationOrderTypes :: Maybe (Kind, Expression) -> Maybe (Kind, Expression) -> Maybe Type + quickPermutationOrderTypes _ _ = Just TypeBool + imSetArgs :: SArg -> SArg -> Validator () imSetArgs (r1, a) (r2, b) = do let t = case (typeOf_ a, typeOf_ b) of @@ -2388,6 +2397,7 @@ functionOps l = case l of a' <- unifyTypesFailing (TypeFunction t TypeAny) (r1, a) b' <- unifyTypesFailing t (r2, b) return $ if null a' || null b' then Nothing else Just () + preImageArgs :: SArg -> SArg -> Validator () preImageArgs (r1, a) (r2, b) = do let t = case (typeOf_ a, typeOf_ b) of @@ -2410,13 +2420,13 @@ functionOps l = case l of inverseArgs :: SArg -> SArg -> Validator () inverseArgs (_r1, a) (_r2, b) = case (typeOf_ a, typeOf_ b) of - (TypeFunction{}, TypeFunction{}) -> return (Just ()) - (TypeFunction{}, _) -> return (Just ()) - (_, TypeFunction{}) -> return (Just ()) - (TypePermutation{}, TypePermutation{}) -> return (Just ()) - (TypePermutation{}, _) -> return (Just ()) - (_, TypePermutation{}) -> return (Just ()) - _ -> return Nothing + (TypeFunction {}, TypeFunction {}) -> return (Just ()) + (TypeFunction {}, _) -> return (Just ()) + (_, TypeFunction {}) -> return (Just ()) + (TypePermutation {}, TypePermutation {}) -> return (Just ()) + (TypePermutation {}, _) -> return (Just ()) + (_, TypePermutation {}) -> return (Just ()) + _ -> return Nothing setPartArgs :: SArg -> SArg -> Validator () setPartArgs (r1, a) (r2, b) = do @@ -2436,6 +2446,7 @@ functionOps l = case l of Just (TypePartition t) -> t _ -> TypeAny return $ TypeSet $ mostDefinedS [at', bt] + partsType :: Maybe Type -> Maybe Type partsType (Just (TypePartition a)) = Just $ TypeSet $ TypeSet a partsType (Just TypeAny) = Just $ TypeSet $ TypeSet TypeAny @@ -2464,6 +2475,7 @@ functionOps l = case l of TypeEnum {} -> valid TypeAny -> valid _ -> invalid $ r ComplexTypeError "Domain of int-like or matrix of int-like" t + minMaxType :: Maybe (Kind, a) -> Maybe Type minMaxType (Just (Kind DomainType t@(TypeInt {}), _)) = Just t minMaxType (Just (Kind DomainType (TypeEnum (Name nm)), _)) = Just . TypeInt $ TagEnum nm @@ -2483,9 +2495,11 @@ functionOps l = case l of typeToSet :: Maybe Type -> Maybe Type typeToSet (Just t) = Just . TypeSet $ fromMaybe TypeAny (tMembers t) typeToSet _ = Just $ TypeSet TypeAny + typeToMSet :: Maybe Type -> Maybe Type typeToMSet (Just t) = Just . TypeMSet $ fromMaybe TypeAny (tMembers t) typeToMSet _ = Just $ TypeMSet TypeAny + typeToRelation :: Maybe Type -> Maybe Type typeToRelation (Just (TypeFunction i j)) = Just $ TypeRelation [i, j] typeToRelation (Just TypeAny) = Just $ TypeRelation [TypeAny, TypeAny] @@ -2512,9 +2526,9 @@ functionOps l = case l of Just f -> unifyTypes f r2 >> return (pure ()) Nothing -> return Nothing + -- TODO: validate composeArgs :: SArg -> SArg -> Validator () composeArgs _ _ = return (pure ()) - -- TODO: validate compose sumArgs :: SArg -> Validator () sumArgs (r, typeOf_ -> t') = do @@ -2525,11 +2539,11 @@ functionOps l = case l of TypeSet t -> return t TypeMSet t -> return t _ -> TypeAny <$ raiseTypeError (r ComplexTypeError "Matrix or Set" t') - case t of TypeAny -> return $ pure () TypeInt TagInt -> return $ pure () _ -> Nothing <$ raiseTypeError (r ComplexTypeError "Integer elements" t) + funcSeq :: SArg -> Validator () funcSeq (r, typeOf_ -> t') = case t' of TypeAny -> return $ pure () @@ -2537,14 +2551,17 @@ functionOps l = case l of TypePermutation _ -> return $ pure () TypeFunction _ _ -> return $ pure () _ -> invalid $ r ComplexTypeError "function, sequence or permutation" t' + funcDomain :: Maybe Type -> Maybe Type funcDomain (Just (TypeFunction a _)) = Just a funcDomain (Just (TypeSequence _)) = Just tInt funcDomain _ = Just TypeAny + funcRange :: Maybe Type -> Maybe Type funcRange (Just (TypeFunction _ b)) = Just b funcRange (Just ((TypeSequence b))) = Just b funcRange _ = Just TypeAny + part :: SArg -> Validator () part (r, typeOf_ -> t) = case t of TypeAny -> valid @@ -2558,11 +2575,13 @@ functionOps l = case l of TypeMatrix _ _ -> return $ pure () TypeAny -> return $ pure () _ -> invalid $ r ComplexTypeError "Matrix, List or MSet" a + histType :: Maybe Type -> Maybe Type histType (Just ((TypeMSet a))) = Just $ TypeMatrix tInt $ TypeTuple [a, tInt] histType (Just ((TypeMatrix _ a))) = Just $ TypeMatrix tInt $ TypeTuple [a, tInt] histType (Just ((TypeList a))) = Just $ TypeMatrix tInt $ TypeTuple [a, tInt] histType _ = Just $ TypeMatrix tInt $ TypeTuple [TypeAny, tInt] + enumerable :: SArg -> Validator () enumerable (r, typeOf_ -> t) = case t of TypeAny -> return $ pure () @@ -2571,6 +2590,7 @@ functionOps l = case l of TypeEnum {} -> return $ pure () TypeBool -> return $ pure () _ -> invalid $ r ComplexTypeError "int enum or bool" t + enumerableType :: Maybe Type -> Maybe Type enumerableType (Just t@(TypeInt TagInt)) = Just t enumerableType (Just t@(TypeInt (TagEnum _))) = Just t diff --git a/src/Conjure/Rules/DontCare.hs b/src/Conjure/Rules/DontCare.hs index bddb8cdbe4..4daf7ddebe 100644 --- a/src/Conjure/Rules/DontCare.hs +++ b/src/Conjure/Rules/DontCare.hs @@ -99,12 +99,12 @@ rule_Abstract = "dontCare-abstract" `namedRule` theRule where x <- match opDontCare p ty <- typeOf x case ty of - TypeSet {} -> return () - TypeMSet {} -> return () - TypeSequence {} -> return () - TypeFunction {} -> return () - TypeRelation {} -> return () - TypePartition{} -> return () + TypeSet {} -> return () + TypeMSet {} -> return () + TypeSequence {} -> return () + TypeFunction {} -> return () + TypeRelation {} -> return () + TypePartition{} -> return () _ -> na "not a known abstract domain" hasRepresentation x xs <- downX1 x diff --git a/src/Conjure/UI/Model.hs b/src/Conjure/UI/Model.hs index 72623981c8..24e8de6672 100644 --- a/src/Conjure/UI/Model.hs +++ b/src/Conjure/UI/Model.hs @@ -1743,7 +1743,8 @@ delayedRules = ] , [ rule_ReducerToComprehension ] - , [ rule_DotLtLeq + , [ rule_QuickPermutationOrder + , rule_DotLtLeq , rule_Flatten_Lex ] ] @@ -2082,6 +2083,28 @@ rule_Neq = "identical-domain-neq" `namedRule` theRule where ) +rule_QuickPermutationOrder :: Rule +rule_QuickPermutationOrder = "generic-QuickPermutationOrder" `namedRule` theRule where + theRule p@[essence| quickPermutationOrder(&x, &ps) |] = do + case listOut ps of + Just [perm] -> + return + ( "Generic vertical rule for quickPermutationOrder:" <+> pretty perm + , return [essence| &x .<= transform(&perm, &x) |] + ) + _ -> na "rule_QuickPermutationOrder - not implemented for multiple permutations yet" + -- traceM $ show $ "HERE x " <+> pretty x + -- traceM $ show $ "HERE ps" <+> pretty ps + -- x_ord <- symmetryOrdering x + -- x_perm <- symmetryOrdering [essence| transform(&ps, &x) |] + -- traceM $ show $ "HERE x_perm" <+> pretty x_perm + -- return + -- ( "Generic vertical rule for quickPermutationOrder:" <+> pretty p + -- , return [essence| &x_ord <=lex &x_perm |] + -- ) + theRule _ = na "rule_QuickPermutationOrder" + + rule_DotLtLeq :: Rule rule_DotLtLeq = "generic-DotLtLeq" `namedRule` theRule where theRule p = do @@ -2156,7 +2179,7 @@ rule_Flatten_Lex = "flatten-lex" `namedRule` theRule where AbstractLiteral x -> do case x of AbsLitTuple xs -> do - fxs <- sequence (flatten <$> xs) + fxs <- mapM flatten xs let flatxs = fromList fxs return [essence| flatten(&flatxs) |] _ -> bug $ "rule_FlattenLex: flatten isn't defined for this abslit fellow..." @@ -2166,7 +2189,7 @@ rule_Flatten_Lex = "flatten-lex" `namedRule` theRule where ConstantAbstract ca -> case ca of AbsLitTuple xs -> do - fxs <- sequence (flatten <$> (Constant <$> xs)) + fxs <- mapM flatten (Constant <$> xs) let flatxs = fromList fxs return [essence| flatten(&flatxs) |] _ -> bug $ "rule_FlattenLex: flatten isn't defined for this constant fellow..." @@ -2177,9 +2200,9 @@ rule_Flatten_Lex = "flatten-lex" `namedRule` theRule where (oName, o) <- quantifiedVar flatten $ Comprehension o [ComprehensionLetting oName a] _ -> do - ps <- sequence $ (\(i,_) -> do + ps <- mapM (\(i,_) -> do (Single nm, tm) <- quantifiedVar - return (i,nm,tm)) <$> (zip [1..] ts) + return (i,nm,tm)) (zip [1..] ts) let lts = (\(i,nm,_tm) -> ComprehensionLetting (Single nm) [essence| &a[&i] |]) <$> ps tup = AbstractLiteral $ AbsLitTuple $ (\(_,_,tm) -> tm) <$> ps flatten $ Comprehension tup lts @@ -2188,7 +2211,7 @@ rule_Flatten_Lex = "flatten-lex" `namedRule` theRule where AbstractLiteral x -> do case x of AbsLitMatrix _ xs -> do - fxs <- sequence (flatten <$> xs) + fxs <- mapM flatten xs let flatxs = fromList fxs return [essence| flatten(&flatxs) |] _ -> bug $ "rule_FlattenLex: flatten isn't defined for this abslit fellow..." @@ -2200,7 +2223,7 @@ rule_Flatten_Lex = "flatten-lex" `namedRule` theRule where AbsLitMatrix _ [] -> return [essence| ([] : `matrix indexed by [int()] of int`) |] AbsLitMatrix _ xs -> do - fxs <- sequence (flatten <$> (Constant <$> xs)) + fxs <- mapM flatten (Constant <$> xs) let flatxs = fromList fxs return [essence| flatten(&flatxs) |] _ -> bug $ "rule_FlattenLex: flatten isn't defined for this constant fellow..." @@ -2592,7 +2615,7 @@ rule_AttributeToConstraint = "attribute-to-constraint" `namedRule` theRule where timedF :: MonadIO m => String -> (a -> m b) -> a -> m b -timedF name comp = \ a -> timeItNamed name (comp a) +timedF name comp a = timeItNamed name (comp a) evaluateModel :: @@ -2823,20 +2846,20 @@ addUnnamedSymmetryBreaking mode model = do | Declaration (FindOrGiven Find nm domain) <- mStatements model ] - allDecVarsAux auxSuffix = - [ (Reference (mconcat [nm, "_auxFor_", auxSuffix]) Nothing, domain) - | Declaration (FindOrGiven Find nm domain) <- mStatements model - ] + -- allDecVarsAux auxSuffix = + -- [ (Reference (mconcat [nm, "_auxFor_", auxSuffix]) Nothing, domain) + -- | Declaration (FindOrGiven Find nm domain) <- mStatements model + -- ] varsTuple = AbstractLiteral $ AbsLitTuple $ map fst allDecVars - mkAuxTuple auxSuffix = AbstractLiteral $ AbsLitTuple $ map fst (allDecVarsAux auxSuffix) + -- mkAuxTuple auxSuffix = AbstractLiteral $ AbsLitTuple $ map fst (allDecVarsAux auxSuffix) -- traceM $ show $ "Unnamed types in this model:" <++> prettyList id "," allUnnamedTypes -- traceM $ show $ "Unnamed decision variables in this model:" <++> prettyList id "," allDecVars -- 3 axis of doom - -- 1. Quick/Complete. Quick is x .<= p(x) - -- Complete is x .<= y /\ y = p(x) + -- 1. Quick/Complete. Quick is quickPermutationOrder(x, p) -- this is an efficient subset of x .<= p(x) + -- Complete is x .<= p(x) -- 2. Scope. Consecutive -- AllPairs -- AllPermutations @@ -2845,22 +2868,22 @@ addUnnamedSymmetryBreaking mode model = do case mode of Nothing -> return model Just (UnnamedSymmetryBreaking quickOrComplete usbScope independentlyOrAltogether) -> do - let newDecls = - case quickOrComplete of - USBQuick -> [] - USBComplete -> - case independentlyOrAltogether of - USBIndependently -> - [ Declaration (FindOrGiven LocalFind nm' domain) - | Declaration (FindOrGiven Find nm domain) <- mStatements model - , (DomainReference uName _, _) <- allUnnamedTypes - , let nm' = mconcat [nm, "_auxFor_", uName] - ] - USBAltogether -> - [ Declaration (FindOrGiven LocalFind nm' domain) - | Declaration (FindOrGiven Find nm domain) <- mStatements model - , let nm' = mconcat [nm, "_auxFor_all"] - ] + -- let newDecls = + -- case quickOrComplete of + -- USBQuick -> [] + -- USBComplete -> + -- case independentlyOrAltogether of + -- USBIndependently -> + -- [ Declaration (FindOrGiven LocalFind nm' domain) + -- | Declaration (FindOrGiven Find nm domain) <- mStatements model + -- , (DomainReference uName _, _) <- allUnnamedTypes + -- , let nm' = mconcat [nm, "_auxFor_", uName] + -- ] + -- USBAltogether -> + -- [ Declaration (FindOrGiven LocalFind nm' domain) + -- | Declaration (FindOrGiven Find nm domain) <- mStatements model + -- , let nm' = mconcat [nm, "_auxFor_all"] + -- ] let @@ -2869,31 +2892,33 @@ addUnnamedSymmetryBreaking mode model = do let applied = buildPermutationChain ps vars in [essence| transform(&p, &applied) |] - combinedPermApply auxSuffix perms = + -- x .<= transform(p1, transform(p2, x)) + -- quickPermutationOrder(x, p) to mean s subset of `x .<= transform(p,x)` + + combinedPermApply perms = case quickOrComplete of USBQuick -> - let applied = buildPermutationChain perms varsTuple - in [essence| &varsTuple .<= &applied |] + let p = fromList perms + in [essence| quickPermutationOrder(&varsTuple, &p) |] USBComplete -> let applied = buildPermutationChain perms varsTuple - thisAuxTuple = mkAuxTuple auxSuffix - in WithLocals [essence| &varsTuple .<= &thisAuxTuple |] $ AuxiliaryVars (newDecls ++ [ SuchThat [ [essence| &thisAuxTuple = &applied |] ] ]) + in [essence| &varsTuple .<= &applied |] - mkGenerator_Consecutive _ _ [] = bug "must have at least one unnamed type" - mkGenerator_Consecutive auxSuffix perms [(u, uSize)] = do + mkGenerator_Consecutive _ [] = bug "must have at least one unnamed type" + mkGenerator_Consecutive perms [(u, uSize)] = do (iPat, i) <- quantifiedVar let perm = [essence| permutation((&i, succ(&i))) |] - let applied = combinedPermApply auxSuffix (perm:perms) + let applied = combinedPermApply (perm:perms) return [essence| and([ &applied | &iPat : &u , &i < &uSize ]) |] - mkGenerator_Consecutive auxSuffix perms ((u, uSize):us) = do + mkGenerator_Consecutive perms ((u, uSize):us) = do (iPat, i) <- quantifiedVar let perm = [essence| permutation((&i, succ(&i))) |] - applied <- mkGenerator_Consecutive auxSuffix (perm:perms) us + applied <- mkGenerator_Consecutive (perm:perms) us return [essence| and([ &applied | &iPat : &u @@ -2902,12 +2927,12 @@ addUnnamedSymmetryBreaking mode model = do |] - mkGenerator_AllPairs _ _ [] = bug "must have at least one unnamed type" - mkGenerator_AllPairs auxSuffix perms [(u, _uSize)] = do + mkGenerator_AllPairs _ [] = bug "must have at least one unnamed type" + mkGenerator_AllPairs perms [(u, _uSize)] = do (iPat, i) <- quantifiedVar (jPat, j) <- quantifiedVar let perm = [essence| permutation((&i, &j)) |] - let applied = combinedPermApply auxSuffix (perm:perms) + let applied = combinedPermApply (perm:perms) return [essence| and([ &applied | &iPat : &u @@ -2915,11 +2940,11 @@ addUnnamedSymmetryBreaking mode model = do , &i < &j ]) |] - mkGenerator_AllPairs auxSuffix perms ((u, _uSize):us) = do + mkGenerator_AllPairs perms ((u, _uSize):us) = do (iPat, i) <- quantifiedVar (jPat, j) <- quantifiedVar let perm = [essence| permutation((&i, &j)) |] - applied <- mkGenerator_AllPairs auxSuffix (perm:perms) us + applied <- mkGenerator_AllPairs (perm:perms) us return [essence| and([ &applied | &iPat : &u @@ -2928,41 +2953,41 @@ addUnnamedSymmetryBreaking mode model = do ]) |] - mkGenerator_AllPermutations _ _ [] = bug "must have at least one unnamed type" - mkGenerator_AllPermutations auxSuffix perms [(u, _uSize)] = do + mkGenerator_AllPermutations _ [] = bug "must have at least one unnamed type" + mkGenerator_AllPermutations perms [(u, _uSize)] = do (iPat, i) <- quantifiedVar let perm = i - let applied = combinedPermApply auxSuffix (perm:perms) + let applied = combinedPermApply (perm:perms) return [essence| and([ &applied | &iPat : permutation of &u ]) |] - mkGenerator_AllPermutations auxSuffix perms ((u, _uSize):us) = do + mkGenerator_AllPermutations perms ((u, _uSize):us) = do (iPat, i) <- quantifiedVar let perm = i - applied <- mkGenerator_AllPermutations auxSuffix (perm:perms) us + applied <- mkGenerator_AllPermutations (perm:perms) us return [essence| and([ &applied | &iPat : permutation of &u ]) |] - mkGenerator auxSuffix perms us = + mkGenerator perms us = case usbScope of - USBConsecutive -> mkGenerator_Consecutive auxSuffix perms us - USBAllPairs -> mkGenerator_AllPairs auxSuffix perms us - USBAllPermutations -> mkGenerator_AllPermutations auxSuffix perms us + USBConsecutive -> mkGenerator_Consecutive perms us + USBAllPairs -> mkGenerator_AllPairs perms us + USBAllPermutations -> mkGenerator_AllPermutations perms us newCons <- case independentlyOrAltogether of USBIndependently -> do xs <- sequence - [ mkGenerator uName [] [(u, uSize)] - | (u@(DomainReference uName _), uSize) <- allUnnamedTypes + [ mkGenerator [] [(u, uSize)] + | (u@DomainReference{}, uSize) <- allUnnamedTypes ] return [SuchThat xs] USBAltogether -> do - cons <- mkGenerator "all" [] allUnnamedTypes + cons <- mkGenerator [] allUnnamedTypes return [SuchThat [cons]] let stmts = newCons diff --git a/tests/custom/symmetry/set/one-var/run.sh b/tests/custom/symmetry/set/one-var/run.sh index 7d423ef67a..910dd84367 100755 --- a/tests/custom/symmetry/set/one-var/run.sh +++ b/tests/custom/symmetry/set/one-var/run.sh @@ -5,10 +5,11 @@ set -o nounset rm -rf conjure-output *solutions* -for sym in Complete; do +for sym in Quick Complete; do for amount in Consecutive AllPairs AllPermutations; do for combine in Independently Altogether; do echo $sym-$amount-$combine + echo conjure solve --number-of-solutions=all --solutions-in-one-file --output-format=jsonstream --unnamed-symmetry-breaking=$sym-$amount-$combine *.essence conjure solve --number-of-solutions=all --solutions-in-one-file --output-format=jsonstream --unnamed-symmetry-breaking=$sym-$amount-$combine *.essence 2>&1 cat *.json | LC_ALL=C sort rm -rf conjure-output *solutions* From 1e7b4283fac332603da7629277b8c4f4a483aef1 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?=C3=96zg=C3=BCr=20Akg=C3=BCn?= Date: Wed, 23 Oct 2024 21:54:09 +0100 Subject: [PATCH 178/229] lint --- src/Conjure/UI/MainHelper.hs | 2 +- src/Conjure/Util/Permutation.hs | 2 +- 2 files changed, 2 insertions(+), 2 deletions(-) diff --git a/src/Conjure/UI/MainHelper.hs b/src/Conjure/UI/MainHelper.hs index 0993321e28..2ec5ba6d56 100644 --- a/src/Conjure/UI/MainHelper.hs +++ b/src/Conjure/UI/MainHelper.hs @@ -767,7 +767,7 @@ mainWithArgs_Modelling modelNamePrefix Modelling{..} portfolioSize modelHashesBe , "Got:" <+> pretty unnamedSymmetryBreaking ] - trail <- if (followModel /= "") + trail <- if followModel /= "" then miTrailGeneralised . mInfo <$> readModelInfoFromFile followModel else return [] diff --git a/src/Conjure/Util/Permutation.hs b/src/Conjure/Util/Permutation.hs index 58a7d8f41f..a235c2de2a 100644 --- a/src/Conjure/Util/Permutation.hs +++ b/src/Conjure/Util/Permutation.hs @@ -202,7 +202,7 @@ isBijective (Permutation p) = let (l, r) = unzip p in (length (nub l) == length (nub r)) && (length (nub l) == length l) - && (null (l \\ r)) + && null (l \\ r) -------------------------CycleFinder Monad--------------------------------------------- From 906508fe1e12756bf1d61a87465c96ba012c8c90 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?=C3=96zg=C3=BCr=20Akg=C3=BCn?= Date: Wed, 23 Oct 2024 22:39:46 +0100 Subject: [PATCH 179/229] lint --- .../Representations/Function/FunctionAsRelation.hs | 8 ++++---- 1 file changed, 4 insertions(+), 4 deletions(-) diff --git a/src/Conjure/Representations/Function/FunctionAsRelation.hs b/src/Conjure/Representations/Function/FunctionAsRelation.hs index f3046c68fb..860eb26d27 100644 --- a/src/Conjure/Representations/Function/FunctionAsRelation.hs +++ b/src/Conjure/Representations/Function/FunctionAsRelation.hs @@ -69,7 +69,7 @@ functionAsRelation dispatch reprOptions = Representation chck downD structuralCo PartialityAttr_Partial -> do (iPat, i) <- quantifiedVar (jPat, j) <- quantifiedVar - return $ return $ -- list + return $ return [essence| $ enforcing that it is indeed a function forAll {&iPat, &jPat} subsetEq toSet(&rel) . @@ -78,7 +78,7 @@ functionAsRelation dispatch reprOptions = Representation chck downD structuralCo PartialityAttr_Total -> do (iPat, i) <- quantifiedVar (jPat, j) <- quantifiedVar - return $ return $ -- list + return $ return [essence| forAll &iPat : &innerDomainFr . 1 = sum([ 1 @@ -96,7 +96,7 @@ functionAsRelation dispatch reprOptions = Representation chck downD structuralCo injectiveCons rel = do (iPat, i) <- quantifiedVar (jPat, j) <- quantifiedVar - return $ return $ -- list + return $ return [essence| and([ &i[1] .< &j[1] -> &i[2] != &j[2] | &iPat <- &rel @@ -107,7 +107,7 @@ functionAsRelation dispatch reprOptions = Representation chck downD structuralCo surjectiveCons rel = do (iPat, i) <- quantifiedVar (jPat, j) <- quantifiedVar - return $ return $ -- list + return $ return [essence| forAll &iPat : &innerDomainTo . exists &jPat in &rel . From 8c56b47404de62d46838b7206a6009f3cf94909a Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?=C3=96zg=C3=BCr=20Akg=C3=BCn?= Date: Wed, 23 Oct 2024 22:40:15 +0100 Subject: [PATCH 180/229] remembering the inverse of all perms --- .../Permutation/PermutationAsFunction.hs | 104 ++++++++++-------- src/Conjure/Rules/Vertical/Permutation.hs | 10 +- 2 files changed, 66 insertions(+), 48 deletions(-) diff --git a/src/Conjure/Representations/Permutation/PermutationAsFunction.hs b/src/Conjure/Representations/Permutation/PermutationAsFunction.hs index 8170b0be50..419ecb20dd 100644 --- a/src/Conjure/Representations/Permutation/PermutationAsFunction.hs +++ b/src/Conjure/Representations/Permutation/PermutationAsFunction.hs @@ -18,7 +18,7 @@ import Conjure.Util.Permutation permutationAsFunction :: forall m. - (MonadFail m, NameGen m, EnumerateDomain m) => + (MonadFailDoc m, NameGen m, EnumerateDomain m) => (forall x. DispatchFunction m x) -> Representation m permutationAsFunction dispatch = Representation chck downD structuralCons downC up symmetryOrdering @@ -29,8 +29,11 @@ permutationAsFunction dispatch = Representation chck downD structuralCons downC map (DomainPermutation Permutation_AsFunction s) <$> f innerDomain chck _ _ = return [] - outName :: Domain HasRepresentation x -> Name -> Name - outName = mkOutName (Just "PermutationFunction") + outNameF :: Domain HasRepresentation x -> Name -> Name + outNameF = mkOutName (Just "PermutationFunction_forwards") + + outNameB :: Domain HasRepresentation x -> Name -> Name + outNameB = mkOutName (Just "PermutationFunction_backwards") outDomain :: (DomainSizeOf x x, Pretty x) => Domain HasRepresentation x -> m (Domain HasRepresentation x) outDomain (DomainPermutation Permutation_AsFunction _ innerDomain) = do @@ -43,8 +46,8 @@ permutationAsFunction dispatch = Representation chck downD structuralCons downC innerDomain ) outDomain domain = - na $ - vcat + na + $ vcat [ "{outDomain} PermutationAsFunction", "domain:" <+> pretty domain ] @@ -53,9 +56,16 @@ permutationAsFunction dispatch = Representation chck downD structuralCons downC downD (name, domain@(DomainPermutation Permutation_AsFunction _ innerDomain)) | domainCanIndexMatrix innerDomain = do m <- domainSizeOf innerDomain - return $ - Just - [ ( outName domain name, + return + $ Just + [ ( outNameF domain name, + DomainFunction + Function_1D + (FunctionAttr (SizeAttr_Size m) PartialityAttr_Total JectivityAttr_Bijective) + innerDomain + innerDomain + ), + ( outNameB domain name, DomainFunction Function_1D (FunctionAttr (SizeAttr_Size m) PartialityAttr_Total JectivityAttr_Bijective) @@ -70,29 +80,27 @@ permutationAsFunction dispatch = Representation chck downD structuralCons downC return $ \inpFun -> do refs <- downX1 inpFun case refs of - [fun] -> do + [forw, back] -> do outDom <- outDomain inDom innerStructuralConsGen <- f outDom (iPat, i) <- quantifiedVarOverDomain (forgetRepr innerDom) concat <$> sequence - [ innerStructuralConsGen fun, - return $ - mkSizeCons - s - [essence| - sum([ toInt(&i != image(&fun, &i)) | &iPat : &innerDom ]) - |] + [ innerStructuralConsGen forw, + innerStructuralConsGen back, + return $ mkSizeCons s [essence| sum([ toInt(&i != image(&forw, &i)) | &iPat : &innerDom ]) |], + return [[essence| forAll &iPat : &innerDom . &back(&forw(&i)) = &i |]], + return [[essence| forAll &iPat : &innerDom . &forw(&back(&i)) = &i |]] ] _ -> - na $ - vcat + na + $ vcat [ "{structuralCons} PermutationAsFunction", pretty inDom ] structuralCons _ _ inDom = - na $ - vcat + na + $ vcat [ "{structuralCons} PermutationAsFunction", pretty inDom ] @@ -105,18 +113,28 @@ permutationAsFunction dispatch = Representation chck downD structuralCons downC ) = do outDom <- outDomain inDom enumDo <- enumerateDomain $ forgetRepr innerDom - case fromCycles vals of - Right perm -> - rDownC - (dispatch outDom) - ( outName inDom name, - outDom, - ConstantAbstract $ AbsLitFunction $ zip enumDo (toFunction perm <$> enumDo) - ) - Left (PermutationError err) -> failDoc $ "PermutationError: " <+> stringToDoc err + case (fromCycles vals, inverse <$> fromCycles vals) of + (Right perm1, Right perm2) -> do + out1 <- + rDownC + (dispatch outDom) + ( outNameF inDom name, + outDom, + ConstantAbstract $ AbsLitFunction $ zip enumDo (toFunction perm1 <$> enumDo) + ) + out2 <- + rDownC + (dispatch outDom) + ( outNameB inDom name, + outDom, + ConstantAbstract $ AbsLitFunction $ zip enumDo (toFunction perm2 <$> enumDo) + ) + return $ Just (fromMaybe [] out1 ++ fromMaybe [] out2) + (Left (PermutationError err), _) -> failDoc $ "PermutationError: " <+> stringToDoc err + (_, Left (PermutationError err)) -> failDoc $ "PermutationError: " <+> stringToDoc err downC (name, domain, constant) = - na $ - vcat + na + $ vcat [ "{downC} PermutationAsFunction", "name:" <+> pretty name, "domain:" <+> pretty domain, @@ -129,31 +147,31 @@ permutationAsFunction dispatch = Representation chck downD structuralCons downC ( name, domain@(DomainPermutation Permutation_AsFunction {} _ _) ) = do - case lookup (outName domain name) ctxt of + case lookup (outNameF domain name) ctxt of (Just (ConstantAbstract (AbsLitFunction f))) -> do case toCyclesCanonical <$> fromRelation f of Right cycles -> return (name, ConstantAbstract (AbsLitPermutation cycles)) Left (PermutationError err) -> - failDoc $ - vcat $ - [ "PermutationError: " <+> stringToDoc err, - "No value for:" <+> pretty (outName domain name), + failDoc + $ vcat + $ [ "PermutationError: " <+> stringToDoc err, + "No value for:" <+> pretty (outNameF domain name), "When working on:" <+> pretty name, "With domain:" <+> pretty domain ] - ++ ("Bindings in context:" : prettyContext ctxt) + ++ ("Bindings in context:" : prettyContext ctxt) _ -> - failDoc $ - vcat $ - [ "No value for:" <+> pretty (outName domain name), + failDoc + $ vcat + $ [ "No value for:" <+> pretty (outNameF domain name), "When working on:" <+> pretty name, "With domain:" <+> pretty domain ] - ++ ("Bindings in context:" : prettyContext ctxt) + ++ ("Bindings in context:" : prettyContext ctxt) up _ (name, domain) = - na $ - vcat + na + $ vcat [ "{up} PermutationAsFunction", "name:" <+> pretty name, "domain:" <+> pretty domain diff --git a/src/Conjure/Rules/Vertical/Permutation.hs b/src/Conjure/Rules/Vertical/Permutation.hs index f9fc22174b..36d16ab834 100644 --- a/src/Conjure/Rules/Vertical/Permutation.hs +++ b/src/Conjure/Rules/Vertical/Permutation.hs @@ -9,7 +9,7 @@ rule_Cardinality = "permutation-cardinality" `namedRule` theRule where TypePermutation{} <- typeOf p Permutation_AsFunction <- representationOf p DomainPermutation _ _ innerDom <- domainOf p - [fun] <- downX1 p + [fun, _] <- downX1 p return ( "Vertical rule for permutation cardinality, AsFunction representation." , do @@ -25,7 +25,7 @@ rule_Defined = "permutation-defined" `namedRule` theRule where p <- match opDefined po TypePermutation{} <- typeOf p Permutation_AsFunction <- representationOf p - [fun] <- downX1 p + [fun, _] <- downX1 p return ( "Vertical rule for permutation defined, AsFunction representation." , do @@ -37,12 +37,12 @@ rule_Defined = "permutation-defined" `namedRule` theRule where rule_Comprehension :: Rule rule_Comprehension = "permutation-comprehension-tuples{AsFunction}" `namedRule` theRule where theRule (Comprehension body gensOrConds) = do - (gocBefore, (pat, perm), gocAfter) <- matchFirst gensOrConds $ \ goc -> case goc of + (gocBefore, (pat, perm), gocAfter) <- matchFirst gensOrConds $ \case Generator (GenInExpr pat expr) -> return (pat, matchDefs [opToSet] expr) _ -> na "rule_Comprehension" - TypePermutation{} <- typeOf perm + TypePermutation{} <- typeOf perm Permutation_AsFunction <- representationOf perm - [f] <- downX1 perm + [f, _] <- downX1 perm return ( "Vertical rule for permutation-comprehension" , do From 2eef5468779f15fb394c9cccc4ca7fe573b4c803 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?=C3=96zg=C3=BCr=20Akg=C3=BCn?= Date: Wed, 23 Oct 2024 22:52:30 +0100 Subject: [PATCH 181/229] move the permutation rules about and fix one (forw, back) bug/regression --- conjure-cp.cabal | 2 +- src/Conjure/Rules/Horizontal/Permutation.hs | 298 ++++++++++-------- src/Conjure/Rules/Vertical/Permutation.hs | 85 ----- .../Permutation/PermutationAsFunction.hs | 92 ++++++ 4 files changed, 256 insertions(+), 221 deletions(-) delete mode 100644 src/Conjure/Rules/Vertical/Permutation.hs create mode 100644 src/Conjure/Rules/Vertical/Permutation/PermutationAsFunction.hs diff --git a/conjure-cp.cabal b/conjure-cp.cabal index 306acb4f38..181149c977 100644 --- a/conjure-cp.cabal +++ b/conjure-cp.cabal @@ -239,7 +239,7 @@ Library , Conjure.Rules.Transform , Conjure.Rules.Horizontal.Permutation - , Conjure.Rules.Vertical.Permutation + , Conjure.Rules.Vertical.Permutation.PermutationAsFunction , Conjure.Rules.BubbleUp , Conjure.Rules.DontCare diff --git a/src/Conjure/Rules/Horizontal/Permutation.hs b/src/Conjure/Rules/Horizontal/Permutation.hs index 97bff2cd8f..e741fe3d53 100644 --- a/src/Conjure/Rules/Horizontal/Permutation.hs +++ b/src/Conjure/Rules/Horizontal/Permutation.hs @@ -1,164 +1,192 @@ {-# LANGUAGE QuasiQuotes #-} + module Conjure.Rules.Horizontal.Permutation where + import Conjure.Rules.Import -import Conjure.Util.Permutation (size, toCycles, fromCycles, toFunction) +import Conjure.Util.Permutation (fromCycles, size, toCycles, toFunction) rule_Cardinality_Literal :: Rule -rule_Cardinality_Literal = "permutation-cardinality-literal" `namedRule` theRule where - theRule p' = do - p <- match opTwoBars p' - (TypePermutation _, elems) <- match permutationLiteral p - let i' = Constant . ConstantInt TagInt . fromIntegral . size <$> fromCycles elems - case i' of - Left er -> failDoc $ "Permutation literal invalid." <++> stringToDoc (show er) - Right i -> return - ( "Vertical rule for permutation cardinality, AsFunction representation." - , do - return [essence| &i |] - ) +rule_Cardinality_Literal = "permutation-cardinality-literal" `namedRule` theRule + where + theRule p' = do + p <- match opTwoBars p' + (TypePermutation _, elems) <- match permutationLiteral p + let i' = Constant . ConstantInt TagInt . fromIntegral . size <$> fromCycles elems + case i' of + Left er -> failDoc $ "Permutation literal invalid." <++> stringToDoc (show er) + Right i -> + return + ( "Horizontal rule for permutation cardinality, AsFunction representation.", + do + return [essence| &i |] + ) rule_Defined_Literal :: Rule -rule_Defined_Literal = "permutation-defined-literal" `namedRule` theRule where - theRule p' = do - p <- match opDefined p' - (TypePermutation _, elems) <- match permutationLiteral p - let i' = (AbstractLiteral . AbsLitSet . nub . join . toCycles) <$> fromCycles elems - case i' of - Left er -> failDoc $ "Permutation literal invalid." <++> stringToDoc (show er) - Right i -> return - ( "Vertical rule for permutation defined, AsFunction representation." - , do - return [essence| &i |] - ) +rule_Defined_Literal = "permutation-defined-literal" `namedRule` theRule + where + theRule p' = do + p <- match opDefined p' + (TypePermutation _, elems) <- match permutationLiteral p + let i' = AbstractLiteral . AbsLitSet . nub . join . toCycles <$> fromCycles elems + case i' of + Left er -> failDoc $ "Permutation literal invalid." <++> stringToDoc (show er) + Right i -> + return + ( "Horizontal rule for permutation defined, AsFunction representation.", + do + return [essence| &i |] + ) rule_Equality :: Rule -rule_Equality = "permutation-equality" `namedRule` theRule where - theRule e = do - (p,q) <- match opEq e - TypePermutation{} <- typeOf p - TypePermutation{} <- typeOf q - return ( "Horizontal rule for permutation equality" - , return [essence| toSet(&p) = toSet(&q) |] - ) +rule_Equality = "permutation-equality" `namedRule` theRule + where + theRule e = do + (p, q) <- match opEq e + TypePermutation {} <- typeOf p + TypePermutation {} <- typeOf q + return + ( "Horizontal rule for permutation equality", + return [essence| toSet(&p) = toSet(&q) |] + ) rule_Disequality :: Rule -rule_Disequality = "permutation-disequality" `namedRule` theRule where - theRule e = do - (p,q) <- match opNeq e - TypePermutation{} <- typeOf p - TypePermutation{} <- typeOf q - return ( "Horizontal rule for permutation disequality" - , return [essence| toSet(&p) != toSet(&q) |] - ) - +rule_Disequality = "permutation-disequality" `namedRule` theRule + where + theRule e = do + (p, q) <- match opNeq e + TypePermutation {} <- typeOf p + TypePermutation {} <- typeOf q + return + ( "Horizontal rule for permutation disequality", + return [essence| toSet(&p) != toSet(&q) |] + ) rule_Comprehension :: Rule -rule_Comprehension = "permutation-comprehension" `namedRule` theRule where - theRule (Comprehension body gensOrConds) = do - (gocBefore, (pat, perm), gocAfter) <- matchFirst gensOrConds $ \ goc -> case goc of - Generator (GenInExpr pat expr) -> return (pat, matchDefs [opToSet] expr) - _ -> na "rule_Comprehension" - (TypePermutation inner, elems) <- match permutationLiteral perm - DomainPermutation _ _ innerD <- domainOf perm - let f' = toFunction <$> fromCycles elems - case f' of - Left er -> failDoc $ "Permutation literal invalid." <++> stringToDoc (show er) - Right f -> do - let outLiteral = make matrixLiteral - (TypeMatrix (TypeInt TagInt) (TypeTuple [inner,inner])) innerD - [ AbstractLiteral (AbsLitTuple [de - ,f de]) - | de <- join elems - ] - return - ( "Vertical rule for permutation-comprehension" - , do - return $ Comprehension body - $ gocBefore - ++ [ Generator (GenInExpr pat [essence| &outLiteral|]) - ] - ++ gocAfter - ) +rule_Comprehension = "permutation-comprehension" `namedRule` theRule + where + theRule (Comprehension body gensOrConds) = do + (gocBefore, (pat, perm), gocAfter) <- matchFirst gensOrConds $ \case + Generator (GenInExpr pat expr) -> return (pat, matchDefs [opToSet] expr) + _ -> na "rule_Comprehension" + (TypePermutation inner, elems) <- match permutationLiteral perm + DomainPermutation _ _ innerD <- domainOf perm + let f' = toFunction <$> fromCycles elems + case f' of + Left er -> failDoc $ "Permutation literal invalid." <++> stringToDoc (show er) + Right f -> do + let outLiteral = + make + matrixLiteral + (TypeMatrix (TypeInt TagInt) (TypeTuple [inner, inner])) + innerD + [ AbstractLiteral + ( AbsLitTuple + [ de, + f de + ] + ) + | de <- join elems + ] + return + ( "Horizontal rule for permutation-comprehension", + do + return + $ Comprehension body + $ gocBefore + ++ [ Generator (GenInExpr pat [essence| &outLiteral|]) + ] + ++ gocAfter + ) theRule _ = na "rule_Comprehension" - rule_In :: Rule -rule_In = "permutation-in" `namedRule` theRule where +rule_In = "permutation-in" `namedRule` theRule + where theRule p = do - (x,s) <- match opIn p - TypePermutation{} <- typeOf s - -- do not apply this rule to quantified variables - -- or else we might miss the opportunity to apply a more specific vertical rule - if referenceToComprehensionVar s - then na "rule_In" - else return () - return - ( "Horizontal rule for permutation-in." - , do - (iPat, i) <- quantifiedVar - return [essence| exists &iPat in &s . &i = &x |] - ) + (x, s) <- match opIn p + TypePermutation {} <- typeOf s + -- do not apply this rule to quantified variables + -- or else we might miss the opportunity to apply a more specific vertical rule + when (referenceToComprehensionVar s) $ na "rule_In" + return + ( "Horizontal rule for permutation-in.", + do + (iPat, i) <- quantifiedVar + return [essence| exists &iPat in &s . &i = &x |] + ) rule_Permutation_Inverse :: Rule -rule_Permutation_Inverse = "permutation-inverse" `namedRule` theRule where +rule_Permutation_Inverse = "permutation-inverse" `namedRule` theRule + where theRule [essence| inverse(&p1, &p2)|] = do - TypePermutation{} <- typeOf p1 - TypePermutation{} <- typeOf p2 - return - ( "Vertical rule for permutation-inverse" - , do - (iPat, i) <- quantifiedVar - return [essence| + TypePermutation {} <- typeOf p1 + TypePermutation {} <- typeOf p2 + return + ( "Horizontal rule for permutation-inverse", + do + (iPat, i) <- quantifiedVar + return + [essence| (forAll &iPat in &p1 . image(&p2,&i[2]) = &i[1]) /\ (forAll &iPat in &p2 . image(&p1,&i[2]) = &i[1]) - |] - ) + |] + ) theRule _ = na "rule_Permutation_Inverse" rule_Compose_Image :: Rule -rule_Compose_Image = "permutation-compose-image" `namedRule` theRule where - theRule [essence| image(compose(&g, &h),&i) |] = do - TypePermutation innerG <- typeOf g - TypePermutation innerH <- typeOf g - typeI <- typeOf i - if let ?typeCheckerMode = StronglyTyped in typesUnify [innerG, innerH, typeI] - then return - ( "Horizontal rule for image of permutation composition" - , do - return [essence| image(&g, image(&h,&i)) |] +rule_Compose_Image = "permutation-compose-image" `namedRule` theRule + where + theRule [essence| image(compose(&g, &h),&i) |] = do + TypePermutation innerG <- typeOf g + TypePermutation innerH <- typeOf g + typeI <- typeOf i + if let ?typeCheckerMode = StronglyTyped in typesUnify [innerG, innerH, typeI] + then + return + ( "Horizontal rule for image of permutation composition", + do + return [essence| image(&g, image(&h,&i)) |] ) - else na "rule_Compose_Image" - theRule _ = na "rule_Compose_Image" - + else na "rule_Compose_Image" + theRule _ = na "rule_Compose_Image" rule_Image_Literal :: Rule -rule_Image_Literal = "permutation-image-literal" `namedRule` theRule where - theRule [essence| image(&p, &i) |] = do - (TypePermutation inner, elems) <- match permutationLiteral p - typeI <- typeOf i - let f' = toFunction <$> fromCycles elems - case f' of - Left er -> failDoc $ "Permutation literal invalid." <++> stringToDoc (show er) - Right f -> do - if let ?typeCheckerMode = StronglyTyped in typesUnify [inner, typeI] - then do - let srtdel = sortBy compare (join elems) - indexr = (\x -> [essence| sum(&x) |]) - (fromList ((\(n,q) -> [essence| toInt(&q = &i) * &n |]) - <$> (zip [1..] srtdel))) - matIdx = mkDomainIntB (fromInt 0) - (fromInt (fromIntegral (length srtdel))) - matLit = make matrixLiteral (TypeMatrix (TypeInt TagInt) inner) - matIdx ([ [essence| &i |] ] ++ (f <$> srtdel)) - iDomain <- domainOf i - minval <- minOfDomain iDomain - return - ( "Horizontal rule for permutation literal application to a single value (image), AsFunction representation" - , do - return [essence| catchUndef(&matLit[&indexr], &minval) |] - - ) - else failDoc $ "Permutation applied to a type its inner does not unify with" - theRule _ = na "rule_Image_Literal" - +rule_Image_Literal = "permutation-image-literal" `namedRule` theRule + where + theRule [essence| image(&p, &i) |] = do + (TypePermutation inner, elems) <- match permutationLiteral p + typeI <- typeOf i + let f' = toFunction <$> fromCycles elems + case f' of + Left er -> failDoc $ "Permutation literal invalid." <++> stringToDoc (show er) + Right f -> do + if let ?typeCheckerMode = StronglyTyped in typesUnify [inner, typeI] + then do + let srtdel = sort (join elems) + indexr = + (\x -> [essence| sum(&x) |]) + ( fromList + ( (\(n, q) -> [essence| toInt(&q = &i) * &n |]) + <$> zip [1 ..] srtdel + ) + ) + matIdx = + mkDomainIntB + (fromInt 0) + (fromInt (fromIntegral (length srtdel))) + matLit = + make + matrixLiteral + (TypeMatrix (TypeInt TagInt) inner) + matIdx + ([essence| &i |] : (f <$> srtdel)) + iDomain <- domainOf i + minval <- minOfDomain iDomain + return + ( "Horizontal rule for permutation literal application to a single value (image), AsFunction representation", + do + return [essence| catchUndef(&matLit[&indexr], &minval) |] + ) + else failDoc "Permutation applied to a type its inner does not unify with" + theRule _ = na "rule_Image_Literal" diff --git a/src/Conjure/Rules/Vertical/Permutation.hs b/src/Conjure/Rules/Vertical/Permutation.hs deleted file mode 100644 index 36d16ab834..0000000000 --- a/src/Conjure/Rules/Vertical/Permutation.hs +++ /dev/null @@ -1,85 +0,0 @@ -{-# LANGUAGE QuasiQuotes #-} -module Conjure.Rules.Vertical.Permutation where -import Conjure.Rules.Import - -rule_Cardinality :: Rule -rule_Cardinality = "permutation-cardinality" `namedRule` theRule where - theRule po = do - p <- match opTwoBars po - TypePermutation{} <- typeOf p - Permutation_AsFunction <- representationOf p - DomainPermutation _ _ innerDom <- domainOf p - [fun, _] <- downX1 p - return - ( "Vertical rule for permutation cardinality, AsFunction representation." - , do - (iPat, i) <- quantifiedVarOverDomain (forgetRepr innerDom) - return $ [essence| - sum([ toInt(&i != image(&fun, &i)) | &iPat : &innerDom ]) - |] - ) - -rule_Defined :: Rule -rule_Defined = "permutation-defined" `namedRule` theRule where - theRule po = do - p <- match opDefined po - TypePermutation{} <- typeOf p - Permutation_AsFunction <- representationOf p - [fun, _] <- downX1 p - return - ( "Vertical rule for permutation defined, AsFunction representation." - , do - return [essence| defined(&fun) |] - ) - - - -rule_Comprehension :: Rule -rule_Comprehension = "permutation-comprehension-tuples{AsFunction}" `namedRule` theRule where - theRule (Comprehension body gensOrConds) = do - (gocBefore, (pat, perm), gocAfter) <- matchFirst gensOrConds $ \case - Generator (GenInExpr pat expr) -> return (pat, matchDefs [opToSet] expr) - _ -> na "rule_Comprehension" - TypePermutation{} <- typeOf perm - Permutation_AsFunction <- representationOf perm - [f, _] <- downX1 perm - return - ( "Vertical rule for permutation-comprehension" - , do - (lPat, l) <- quantifiedVar - (rPat, r) <- quantifiedVar - return $ Comprehension body - $ gocBefore - ++ [ Generator (GenInExpr pat [essence| [(&l,&r) - | (&lPat, &rPat) <- &f - , &l != &r] |]) - ] - ++ gocAfter - ) - theRule _ = na "rule_Comprehension" - - - -rule_Image :: Rule -rule_Image = "permutation-image{AsFunction}" `namedRule` theRule where - theRule [essence| image(&p, &i) |] = do - TypePermutation inner <- typeOf p - case match permutationLiteral p of - Nothing -> do - typeI <- typeOf i - if let ?typeCheckerMode = StronglyTyped in typesUnify [inner, typeI] - then do - [f] <- downX1 p - return ( "Vertical rule for permutation application to a single value" - , do - return [essence| [&i, catchUndef(image(&f,&i),0)][toInt(&i in defined(&f))+1] |] - ) - else if let ?typeCheckerMode = StronglyTyped in typeI `containsType` inner - then na "rule_Image" - else return ( "Vertical rule for permutation application to a type the permutation doesn't care about" - , do - return [essence| &i |] - ) - _ -> na "rule_Image" - theRule _ = na "rule_Image" - diff --git a/src/Conjure/Rules/Vertical/Permutation/PermutationAsFunction.hs b/src/Conjure/Rules/Vertical/Permutation/PermutationAsFunction.hs new file mode 100644 index 0000000000..3930fd65c6 --- /dev/null +++ b/src/Conjure/Rules/Vertical/Permutation/PermutationAsFunction.hs @@ -0,0 +1,92 @@ +{-# LANGUAGE QuasiQuotes #-} + +module Conjure.Rules.Vertical.Permutation.PermutationAsFunction where + +import Conjure.Rules.Import + +rule_Cardinality :: Rule +rule_Cardinality = "permutation-cardinality" `namedRule` theRule + where + theRule po = do + p <- match opTwoBars po + TypePermutation {} <- typeOf p + Permutation_AsFunction <- representationOf p + DomainPermutation _ _ innerDom <- domainOf p + [fun, _] <- downX1 p + return + ( "Vertical rule for permutation cardinality, AsFunction representation.", + do + (iPat, i) <- quantifiedVarOverDomain (forgetRepr innerDom) + return [essence| sum([ toInt(&i != image(&fun, &i)) | &iPat : &innerDom ]) |] + ) + +rule_Defined :: Rule +rule_Defined = "permutation-defined" `namedRule` theRule + where + theRule po = do + p <- match opDefined po + TypePermutation {} <- typeOf p + Permutation_AsFunction <- representationOf p + [fun, _] <- downX1 p + return + ( "Vertical rule for permutation defined, AsFunction representation.", + return [essence| defined(&fun) |] + ) + +rule_Comprehension :: Rule +rule_Comprehension = "permutation-comprehension-tuples{AsFunction}" `namedRule` theRule + where + theRule (Comprehension body gensOrConds) = do + (gocBefore, (pat, perm), gocAfter) <- matchFirst gensOrConds $ \case + Generator (GenInExpr pat expr) -> return (pat, matchDefs [opToSet] expr) + _ -> na "rule_Comprehension" + TypePermutation {} <- typeOf perm + Permutation_AsFunction <- representationOf perm + [f, _] <- downX1 perm + return + ( "Vertical rule for permutation-comprehension", + do + (lPat, l) <- quantifiedVar + (rPat, r) <- quantifiedVar + return $ + Comprehension body $ + gocBefore + ++ [ Generator + ( GenInExpr + pat + [essence| [(&l,&r) + | (&lPat, &rPat) <- &f + , &l != &r] |] + ) + ] + ++ gocAfter + ) + theRule _ = na "rule_Comprehension" + +rule_Image :: Rule +rule_Image = "permutation-image{AsFunction}" `namedRule` theRule + where + theRule [essence| image(&p, &i) |] = do + TypePermutation inner <- typeOf p + case match permutationLiteral p of + Nothing -> do + typeI <- typeOf i + if let ?typeCheckerMode = StronglyTyped in typesUnify [inner, typeI] + then do + [f, _] <- downX1 p + return + ( "Vertical rule for permutation application to a single value", + do + return [essence| [&i, catchUndef(image(&f,&i),0)][toInt(&i in defined(&f))+1] |] + ) + else + if let ?typeCheckerMode = StronglyTyped in typeI `containsType` inner + then na "rule_Image" + else + return + ( "Vertical rule for permutation application to a type the permutation doesn't care about", + do + return [essence| &i |] + ) + _ -> na "rule_Image" + theRule _ = na "rule_Image" From a3cbea7d1a2742f70fabb49b31adff988b10628c Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?=C3=96zg=C3=BCr=20Akg=C3=BCn?= Date: Wed, 23 Oct 2024 22:56:32 +0100 Subject: [PATCH 182/229] move the permutation rules about and fix one (forw, back) bug/regression (2) --- src/Conjure/UI/Model.hs | 12 ++++++------ 1 file changed, 6 insertions(+), 6 deletions(-) diff --git a/src/Conjure/UI/Model.hs b/src/Conjure/UI/Model.hs index 24e8de6672..06967e65fb 100644 --- a/src/Conjure/UI/Model.hs +++ b/src/Conjure/UI/Model.hs @@ -102,8 +102,8 @@ import qualified Conjure.Rules.Vertical.Partition.PartitionAsSet as Vertical.Par import qualified Conjure.Rules.Vertical.Partition.Occurrence as Vertical.Partition.Occurrence import qualified Conjure.Rules.Transform as Transform -import qualified Conjure.Rules.Vertical.Permutation as Vertical.Permutation import qualified Conjure.Rules.Horizontal.Permutation as Horizontal.Permutation +import qualified Conjure.Rules.Vertical.Permutation.PermutationAsFunction as Vertical.Permutation.PermutationAsFunction import qualified Conjure.Rules.BubbleUp as BubbleUp import qualified Conjure.Rules.DontCare as DontCare @@ -1408,10 +1408,10 @@ paramRules = verticalRules :: [Rule] verticalRules = - [ Vertical.Permutation.rule_Image - , Vertical.Permutation.rule_Cardinality - , Vertical.Permutation.rule_Defined - , Vertical.Permutation.rule_Comprehension + [ Vertical.Permutation.PermutationAsFunction.rule_Image + , Vertical.Permutation.PermutationAsFunction.rule_Cardinality + , Vertical.Permutation.PermutationAsFunction.rule_Defined + , Vertical.Permutation.PermutationAsFunction.rule_Comprehension , Vertical.Tuple.rule_Tuple_Eq @@ -2085,7 +2085,7 @@ rule_Neq = "identical-domain-neq" `namedRule` theRule where rule_QuickPermutationOrder :: Rule rule_QuickPermutationOrder = "generic-QuickPermutationOrder" `namedRule` theRule where - theRule p@[essence| quickPermutationOrder(&x, &ps) |] = do + theRule [essence| quickPermutationOrder(&x, &ps) |] = do case listOut ps of Just [perm] -> return From 760f4352c87475a7c63e54450df36280e81c6543 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?=C3=96zg=C3=BCr=20Akg=C3=BCn?= Date: Thu, 24 Oct 2024 09:50:49 +0100 Subject: [PATCH 183/229] improve bash --- tests/exhaustive/acceptOutput.sh | 4 +--- 1 file changed, 1 insertion(+), 3 deletions(-) diff --git a/tests/exhaustive/acceptOutput.sh b/tests/exhaustive/acceptOutput.sh index 682820c767..983b32fa6a 100755 --- a/tests/exhaustive/acceptOutput.sh +++ b/tests/exhaustive/acceptOutput.sh @@ -12,9 +12,7 @@ for TESTCASE in $*; do echo "Accepting the output of ${TESTCASE}" rm -rf "${TESTCASE}"/expected mkdir -p "${TESTCASE}"/expected - for file in "${TESTCASE}"/outputs/*.eprime "${TESTCASE}"/outputs/*.solution "${TESTCASE}"/outputs/*.eprime-param ; do - cp $file "${TESTCASE}"/expected/ - done + cp "${TESTCASE}"/outputs/*.eprime "${TESTCASE}"/outputs/*.solution "${TESTCASE}"/outputs/*.eprime-param "${TESTCASE}"/expected/ parallel --no-notice "[ -f {} ] && (cat {} | grep -v '\\$' > {}.temp ; mv {}.temp {})" \ ::: "${TESTCASE}"/expected/*.eprime fi From 16441d84caa420442d0f95d909bbe35915d97583 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?=C3=96zg=C3=BCr=20Akg=C3=BCn?= Date: Thu, 24 Oct 2024 09:52:09 +0100 Subject: [PATCH 184/229] update some of test files --- .../stdout.expected | 2 +- .../stdout.expected | 2 +- .../stdout.expected | 2 +- .../stdout.expected | 2 +- .../stdout.expected | 2 +- .../stdout.expected | 2 +- .../stdout.expected | 2 +- .../stdout.expected | 2 +- .../stdout.expected | 2 +- .../stdout.expected | 2 +- .../stdout.expected | 2 +- .../stdout.expected | 2 +- .../stdout.expected | 2 +- .../stdout.expected | 2 +- .../stdout.expected | 2 +- .../stdout.expected | 2 +- .../stdout.expected | 2 +- .../stdout.expected | 2 +- .../stdout.expected | 2 +- .../stdout.expected | 2 +- .../stdout.expected | 2 +- .../stdout.expected | 2 +- .../stdout.expected | 2 +- .../stdout.expected | 2 +- .../stdout.expected | 2 +- .../stdout.expected | 2 +- .../stdout.expected | 2 +- .../stdout.expected | 2 +- .../stdout.expected | 2 +- .../stdout.expected | 2 +- .../stdout.expected | 2 +- .../stdout.expected | 2 +- .../stdout.expected | 2 +- .../0003_find_permutation/stdout.expected | 2 +- .../stdout.expected | 2 +- .../stdout.expected | 2 +- .../int/0003_find_permutation/stdout.expected | 2 +- .../0003_find_permutation/stdout.expected | 2 +- .../stdout.expected | 2 +- .../stdout.expected | 2 +- .../stdout.expected | 2 +- .../stdout.expected | 2 +- .../stdout.expected | 2 +- .../stdout.expected | 2 +- .../stdout.expected | 2 +- .../stdout.expected | 2 +- .../stdout.expected | 2 +- .../stdout.expected | 2 +- .../stdout.expected | 4 +- .../stdout.expected | 2 +- .../stdout.expected | 2 +- .../stdout.expected | 4 +- .../stdout.expected | 4 +- .../stdout.expected | 4 +- .../stdout.expected | 2 +- .../stdout.expected | 4 +- .../stdout.expected | 2 +- .../stdout.expected | 2 +- .../stdout.expected | 4 +- .../stdout.expected | 4 +- .../stdout.expected | 4 +- .../stdout.expected | 2 +- .../stdout.expected | 2 +- .../stdout.expected | 2 +- .../stdout.expected | 2 +- .../0003_given_equal_letting/stdout.expected | 2 +- .../0004_letting_equal_given/stdout.expected | 2 +- .../enum/0005_find_eq_find/stdout.expected | 2 +- .../0006_in_comprehension/stdout.expected | 2 +- .../stdout.expected | 2 +- .../stdout.expected | 2 +- .../0003_given_equal_letting/stdout.expected | 2 +- .../0004_letting_equal_given/stdout.expected | 2 +- .../int/0005_find_eq_find/stdout.expected | 2 +- .../int/0006_in_comprehension/stdout.expected | 2 +- .../stdout.expected | 2 +- .../unnamed/0005_find_eq_find/stdout.expected | 2 +- .../0006_in_comprehension/stdout.expected | 2 +- .../stdout.expected | 4 +- .../stdout.expected | 4 +- .../0003_given_equal_letting/stdout.expected | 4 +- .../0004_letting_equal_given/stdout.expected | 4 +- .../enum/0005_find_eq_find/stdout.expected | 2 +- .../stdout.expected | 2 +- .../stdout.expected | 2 +- .../0003_given_equal_letting/stdout.expected | 2 +- .../0004_letting_equal_given/stdout.expected | 4 +- .../int/0005_find_eq_find/stdout.expected | 2 +- .../0005_find_inverse_find/stdout.expected | 2 +- .../stdout.expected | 6 +- .../0002_given_and_letting/stdout.expected | 2 +- .../0003_letting_and_find/stdout.expected | 4 +- .../enum/0004_find_and_find/stdout.expected | 2 +- .../stdout.expected | 6 +- .../0002_given_and_letting/stdout.expected | 2 +- .../0002_letting_and_given/stdout.expected | 2 +- .../int/0003_letting_and_find/stdout.expected | 4 +- .../int/0004_find_and_find/stdout.expected | 2 +- .../int/0005_find_composition/stdout.expected | 2 +- .../int/0006_find_composition/stdout.expected | 2 +- .../0004_find_and_find/stdout.expected | 2 +- .../stdout.expected | 2 +- .../stdout.expected | 2 +- .../stdout.expected | 2 +- .../stdout.expected | 2 +- .../stdout.expected | 2 +- .../stdout.expected | 2 +- .../stdout.expected | 2 +- .../stdout.expected | 2 +- .../stdout.expected | 2 +- .../stdout.expected | 2 +- .../stdout.expected | 2 +- .../0001_letting_permutation/stdout.expected | 2 +- .../0002_letting_permutation/stdout.expected | 2 +- .../0003_given_permutation/stdout.expected | 2 +- .../0004_given_permutation/stdout.expected | 2 +- .../0005_find_permutation/stdout.expected | 2 +- .../0001_letting_permutation/stdout.expected | 2 +- .../0002_letting_permutation/stdout.expected | 2 +- .../0003_given_permutation/stdout.expected | 2 +- .../0004_given_permutation/stdout.expected | 2 +- .../int/0005_find_permutation/stdout.expected | 2 +- .../0005_find_permutation/stdout.expected | 2 +- .../stdout.expected | 2 +- .../stdout.expected | 2 +- .../stdout.expected | 2 +- .../stdout.expected | 2 +- .../stdout.expected | 2 +- .../stdout.expected | 2 +- .../stdout.expected | 2 +- .../stdout.expected | 2 +- .../stdout.expected | 2 +- .../stdout.expected | 2 +- .../stdout.expected | 2 +- .../stdout.expected | 2 +- .../stdout.expected | 2 +- .../stdout.expected | 2 +- .../stdout.expected | 2 +- .../stdout.expected | 2 +- .../stdout.expected | 2 +- .../stdout.expected | 2 +- .../stdout.expected | 2 +- .../stdout.expected | 2 +- .../0010_given_permutation/stdout.expected | 2 +- .../0020_letting_permutation/stdout.expected | 2 +- .../0030_find_permutation/stdout.expected | 2 +- .../0010_given_permutation/stdout.expected | 2 +- .../0020_letting_permutation/stdout.expected | 2 +- .../int/0030_find_permutation/stdout.expected | 2 +- .../0010_given_permutation/stdout.expected | 2 +- .../0020_letting_permutation/stdout.expected | 2 +- .../0030_find_permutation/stdout.expected | 2 +- .../0010_given_permutation/stdout.expected | 2 +- .../0020_letting_permutation/stdout.expected | 2 +- .../int/0030_find_permutation/stdout.expected | 2 +- .../0030_find_permutation/stdout.expected | 2 +- .../0010_given_permutation/stdout.expected | 2 +- .../0020_letting_permutation/stdout.expected | 2 +- .../0030_find_permutation/stdout.expected | 2 +- .../0010_given_permutation/stdout.expected | 2 +- .../0020_letting_permutation/stdout.expected | 2 +- .../int/0030_find_permutation/stdout.expected | 2 +- .../0030_find_permutation/stdout.expected | 2 +- .../stdout.expected | 2 +- .../stdout.expected | 2 +- .../stdout.expected | 2 +- .../stdout.expected | 2 +- .../stdout.expected | 2 +- .../stdout.expected | 2 +- .../stdout.expected | 2 +- .../stdout.expected | 2 +- .../stdout.expected | 2 +- .../stdout.expected | 2 +- .../stdout.expected | 2 +- .../stdout.expected | 2 +- .../stdout.expected | 2 +- .../stdout.expected | 2 +- .../stdout.expected | 2 +- .../stdout.expected | 2 +- .../stdout.expected | 2 +- .../stdout.expected | 2 +- .../stdout.expected | 2 +- .../stdout.expected | 2 +- .../stdout.expected | 2 +- .../stdout.expected | 2 +- .../stdout.expected | 2 +- .../stdout.expected | 2 +- .../stdout.expected | 2 +- .../stdout.expected | 2 +- .../stdout.expected | 2 +- .../stdout.expected | 2 +- .../stdout.expected | 2 +- .../stdout.expected | 2 +- .../stdout.expected | 6 +- .../stdout.expected | 6 +- .../stdout.expected | 2 +- .../stdout.expected | 6 +- .../stdout.expected | 6 +- .../stdout.expected | 2 +- .../0010_set_of_tuples/stdout.expected | 2 +- .../0010_find_perm_find_set/stdout.expected | 2 +- .../expected/model-permutation.eprime-param | 3 +- .../expected/model.eprime | 3 +- .../expected/model-permutation.eprime-param | 3 +- .../expected/model.eprime | 3 +- .../expected/model-permutation.eprime-param | 3 +- .../expected/model.eprime | 3 +- .../expected/model-permutation.eprime-param | 3 +- .../expected/model.eprime | 3 +- .../expected/model.eprime | 25 +++++-- .../expected/model.eprime | 25 +++++-- .../expected/model.eprime | 23 +++++- .../expected/model.eprime | 25 +++++-- .../expected/model.eprime | 25 +++++-- .../expected/model.eprime | 27 +++++-- .../expected/model-permutation.eprime-param | 3 +- .../expected/model.eprime | 3 +- .../expected/model-permutation.eprime-param | 3 +- .../expected/model.eprime | 3 +- .../expected/model-permutation.eprime-param | 3 +- .../expected/model.eprime | 3 +- .../expected/model-permutation.eprime-param | 3 +- .../expected/model.eprime | 3 +- .../expected/model.eprime | 25 +++++-- .../expected/model.eprime | 25 +++++-- .../expected/model.eprime | 23 +++++- .../expected/model.eprime | 25 +++++-- .../expected/model.eprime | 25 +++++-- .../expected/model.eprime | 27 +++++-- .../expected/model.eprime | 25 +++++-- .../expected/model.eprime | 25 +++++-- .../expected/model.eprime | 23 +++++- .../expected/model.eprime | 25 +++++-- .../expected/model.eprime | 25 +++++-- .../expected/model.eprime | 27 +++++-- .../expected/model-permutation.eprime-param | 3 +- .../expected/model.eprime | 5 +- .../expected/model.eprime | 27 +++++-- .../expected/model-permutation.eprime-param | 3 +- .../expected/model.eprime | 5 +- .../expected/model.eprime | 27 +++++-- .../expected/model.eprime | 27 +++++-- .../expected/model-permutation.eprime-param | 3 +- .../expected/model.eprime | 8 +- .../expected/model.eprime | 34 ++++++--- .../expected/model.eprime | 31 ++++++-- .../expected/model-permutation.eprime-param | 3 +- .../expected/model.eprime | 8 +- .../expected/model.eprime | 34 ++++++--- .../expected/model.eprime | 34 ++++++--- .../expected/model.eprime | 40 +++++++--- .../expected/model.eprime | 34 ++++++--- .../expected/model-permutation.eprime-param | 3 +- .../expected/model-permutation2.eprime-param | 3 +- .../expected/model.eprime | 5 +- .../expected/model-permutation.eprime-param | 3 +- .../expected/model.eprime | 5 +- .../expected/model-permutation.eprime-param | 3 +- .../expected/model.eprime | 5 +- .../expected/model.eprime | 33 ++++++--- .../expected/model.eprime | 2 +- .../expected/model.eprime | 33 ++++++--- .../expected/model-permutation.eprime-param | 3 +- .../expected/model-permutation2.eprime-param | 3 +- .../expected/model.eprime | 5 +- .../expected/model-permutation.eprime-param | 3 +- .../expected/model.eprime | 5 +- .../expected/model-permutation.eprime-param | 3 +- .../expected/model.eprime | 3 +- .../expected/model.eprime | 33 ++++++--- .../expected/model.eprime | 2 +- .../expected/model.eprime | 27 +++++-- .../expected/model.eprime | 33 ++++++--- .../expected/model-permutation.eprime-param | 6 +- .../expected/model.eprime | 16 ++-- .../expected/model-permutation.eprime-param | 6 +- .../expected/model.eprime | 16 ++-- .../expected/model-permutation.eprime-param | 3 +- .../expected/model.eprime | 23 +++--- .../expected/model-permutation.eprime-param | 3 +- .../expected/model.eprime | 23 +++--- .../0005_find_eq_find/expected/model.eprime | 50 ++++++++++--- .../expected/model.eprime | 59 +++++++++++---- .../expected/model-permutation.eprime-param | 6 +- .../expected/model.eprime | 16 ++-- .../expected/model-permutation.eprime-param | 6 +- .../expected/model.eprime | 16 ++-- .../expected/model-permutation.eprime-param | 3 +- .../expected/model.eprime | 23 +++--- .../expected/model-permutation.eprime-param | 3 +- .../expected/model.eprime | 23 +++--- .../0005_find_eq_find/expected/model.eprime | 50 ++++++++++--- .../expected/model.eprime | 59 +++++++++++---- .../0005_find_eq_find/expected/model.eprime | 50 ++++++++++--- .../expected/model.eprime | 59 +++++++++++---- .../0005_find_eq_find/expected/model.eprime | 73 +++++++++++++------ 296 files changed, 1437 insertions(+), 650 deletions(-) diff --git a/tests/custom/permutations/01_representation/enum/0001_given_permutation_in_param/stdout.expected b/tests/custom/permutations/01_representation/enum/0001_given_permutation_in_param/stdout.expected index 5647c94283..e06ed83776 100644 --- a/tests/custom/permutations/01_representation/enum/0001_given_permutation_in_param/stdout.expected +++ b/tests/custom/permutations/01_representation/enum/0001_given_permutation_in_param/stdout.expected @@ -1,7 +1,7 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime permutation.param +Savile Row: conjure-output/model000001.eprime permutation.param Running minion for domain filtering. Running solver: minion Copying solution to: permutation-permutation.solution diff --git a/tests/custom/permutations/01_representation/enum/0002_given_permutation_in_param/stdout.expected b/tests/custom/permutations/01_representation/enum/0002_given_permutation_in_param/stdout.expected index 5647c94283..e06ed83776 100644 --- a/tests/custom/permutations/01_representation/enum/0002_given_permutation_in_param/stdout.expected +++ b/tests/custom/permutations/01_representation/enum/0002_given_permutation_in_param/stdout.expected @@ -1,7 +1,7 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime permutation.param +Savile Row: conjure-output/model000001.eprime permutation.param Running minion for domain filtering. Running solver: minion Copying solution to: permutation-permutation.solution diff --git a/tests/custom/permutations/01_representation/enum/0003_given_permutation_in_param_2_cycle/stdout.expected b/tests/custom/permutations/01_representation/enum/0003_given_permutation_in_param_2_cycle/stdout.expected index 5647c94283..e06ed83776 100644 --- a/tests/custom/permutations/01_representation/enum/0003_given_permutation_in_param_2_cycle/stdout.expected +++ b/tests/custom/permutations/01_representation/enum/0003_given_permutation_in_param_2_cycle/stdout.expected @@ -1,7 +1,7 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime permutation.param +Savile Row: conjure-output/model000001.eprime permutation.param Running minion for domain filtering. Running solver: minion Copying solution to: permutation-permutation.solution diff --git a/tests/custom/permutations/01_representation/enum/0004_given_permutation_in_param_2_cycle/stdout.expected b/tests/custom/permutations/01_representation/enum/0004_given_permutation_in_param_2_cycle/stdout.expected index 5647c94283..e06ed83776 100644 --- a/tests/custom/permutations/01_representation/enum/0004_given_permutation_in_param_2_cycle/stdout.expected +++ b/tests/custom/permutations/01_representation/enum/0004_given_permutation_in_param_2_cycle/stdout.expected @@ -1,7 +1,7 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime permutation.param +Savile Row: conjure-output/model000001.eprime permutation.param Running minion for domain filtering. Running solver: minion Copying solution to: permutation-permutation.solution diff --git a/tests/custom/permutations/01_representation/enum/0005_find_permutation_size_4_of_int1_4/stdout.expected b/tests/custom/permutations/01_representation/enum/0005_find_permutation_size_4_of_int1_4/stdout.expected index 586f9ad67c..caaf755665 100644 --- a/tests/custom/permutations/01_representation/enum/0005_find_permutation_size_4_of_int1_4/stdout.expected +++ b/tests/custom/permutations/01_representation/enum/0005_find_permutation_size_4_of_int1_4/stdout.expected @@ -1,7 +1,7 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime +Savile Row: conjure-output/model000001.eprime Running minion for domain filtering. Running solver: minion Copying solution to: permutation-000001.solution diff --git a/tests/custom/permutations/01_representation/enum/0006_find_permutation_size_0_of_int1_4/stdout.expected b/tests/custom/permutations/01_representation/enum/0006_find_permutation_size_0_of_int1_4/stdout.expected index b4f1327bab..f5bbc850ff 100644 --- a/tests/custom/permutations/01_representation/enum/0006_find_permutation_size_0_of_int1_4/stdout.expected +++ b/tests/custom/permutations/01_representation/enum/0006_find_permutation_size_0_of_int1_4/stdout.expected @@ -1,7 +1,7 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime +Savile Row: conjure-output/model000001.eprime Running minion for domain filtering. Running solver: minion Copying solution to: permutation-000001.solution diff --git a/tests/custom/permutations/01_representation/enum/0007_letting_permutation_be_empty/stdout.expected b/tests/custom/permutations/01_representation/enum/0007_letting_permutation_be_empty/stdout.expected index ec07b6eae6..5b299b17a4 100644 --- a/tests/custom/permutations/01_representation/enum/0007_letting_permutation_be_empty/stdout.expected +++ b/tests/custom/permutations/01_representation/enum/0007_letting_permutation_be_empty/stdout.expected @@ -1,7 +1,7 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime +Savile Row: conjure-output/model000001.eprime Running minion for domain filtering. Running solver: minion Copying solution to: permutation-000001.solution diff --git a/tests/custom/permutations/01_representation/enum/0008_find_permutation_of_int1_4/stdout.expected b/tests/custom/permutations/01_representation/enum/0008_find_permutation_of_int1_4/stdout.expected index f6a152cb6f..cff8aa33cc 100644 --- a/tests/custom/permutations/01_representation/enum/0008_find_permutation_of_int1_4/stdout.expected +++ b/tests/custom/permutations/01_representation/enum/0008_find_permutation_of_int1_4/stdout.expected @@ -1,7 +1,7 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime +Savile Row: conjure-output/model000001.eprime Running minion for domain filtering. Running solver: minion Copying solution to: permutation-000001.solution diff --git a/tests/custom/permutations/01_representation/enum/0009_letting_permutation_in_model/stdout.expected b/tests/custom/permutations/01_representation/enum/0009_letting_permutation_in_model/stdout.expected index 0d4e03724a..8392c51c10 100644 --- a/tests/custom/permutations/01_representation/enum/0009_letting_permutation_in_model/stdout.expected +++ b/tests/custom/permutations/01_representation/enum/0009_letting_permutation_in_model/stdout.expected @@ -1,7 +1,7 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime +Savile Row: conjure-output/model000001.eprime Running minion for domain filtering. Running solver: minion Copying solution to: permutation.solution diff --git a/tests/custom/permutations/01_representation/enum/0010_find_permutation_maxSize_2_of_int1_3/stdout.expected b/tests/custom/permutations/01_representation/enum/0010_find_permutation_maxSize_2_of_int1_3/stdout.expected index 6ee1a00604..3aeb491720 100644 --- a/tests/custom/permutations/01_representation/enum/0010_find_permutation_maxSize_2_of_int1_3/stdout.expected +++ b/tests/custom/permutations/01_representation/enum/0010_find_permutation_maxSize_2_of_int1_3/stdout.expected @@ -1,7 +1,7 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime +Savile Row: conjure-output/model000001.eprime Running minion for domain filtering. Running solver: minion Copying solution to: permutation-000001.solution diff --git a/tests/custom/permutations/01_representation/enum/0011_find_permutation_minSize_2_of_int1_3/stdout.expected b/tests/custom/permutations/01_representation/enum/0011_find_permutation_minSize_2_of_int1_3/stdout.expected index 1c9db8e0f4..c96e83295b 100644 --- a/tests/custom/permutations/01_representation/enum/0011_find_permutation_minSize_2_of_int1_3/stdout.expected +++ b/tests/custom/permutations/01_representation/enum/0011_find_permutation_minSize_2_of_int1_3/stdout.expected @@ -1,7 +1,7 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime +Savile Row: conjure-output/model000001.eprime Running minion for domain filtering. Running solver: minion Copying solution to: permutation-000001.solution diff --git a/tests/custom/permutations/01_representation/enum/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/stdout.expected b/tests/custom/permutations/01_representation/enum/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/stdout.expected index 877824e873..758182ed08 100644 --- a/tests/custom/permutations/01_representation/enum/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/stdout.expected +++ b/tests/custom/permutations/01_representation/enum/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/stdout.expected @@ -1,7 +1,7 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime +Savile Row: conjure-output/model000001.eprime Running minion for domain filtering. Running solver: minion Copying solution to: permutation-000001.solution diff --git a/tests/custom/permutations/01_representation/int/0001_given_permutation_in_param/stdout.expected b/tests/custom/permutations/01_representation/int/0001_given_permutation_in_param/stdout.expected index 5647c94283..e06ed83776 100644 --- a/tests/custom/permutations/01_representation/int/0001_given_permutation_in_param/stdout.expected +++ b/tests/custom/permutations/01_representation/int/0001_given_permutation_in_param/stdout.expected @@ -1,7 +1,7 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime permutation.param +Savile Row: conjure-output/model000001.eprime permutation.param Running minion for domain filtering. Running solver: minion Copying solution to: permutation-permutation.solution diff --git a/tests/custom/permutations/01_representation/int/0002_given_permutation_in_param/stdout.expected b/tests/custom/permutations/01_representation/int/0002_given_permutation_in_param/stdout.expected index 5647c94283..e06ed83776 100644 --- a/tests/custom/permutations/01_representation/int/0002_given_permutation_in_param/stdout.expected +++ b/tests/custom/permutations/01_representation/int/0002_given_permutation_in_param/stdout.expected @@ -1,7 +1,7 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime permutation.param +Savile Row: conjure-output/model000001.eprime permutation.param Running minion for domain filtering. Running solver: minion Copying solution to: permutation-permutation.solution diff --git a/tests/custom/permutations/01_representation/int/0003_given_permutation_in_param_2_cycle/stdout.expected b/tests/custom/permutations/01_representation/int/0003_given_permutation_in_param_2_cycle/stdout.expected index 5647c94283..e06ed83776 100644 --- a/tests/custom/permutations/01_representation/int/0003_given_permutation_in_param_2_cycle/stdout.expected +++ b/tests/custom/permutations/01_representation/int/0003_given_permutation_in_param_2_cycle/stdout.expected @@ -1,7 +1,7 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime permutation.param +Savile Row: conjure-output/model000001.eprime permutation.param Running minion for domain filtering. Running solver: minion Copying solution to: permutation-permutation.solution diff --git a/tests/custom/permutations/01_representation/int/0004_given_permutation_in_param_2_cycle/stdout.expected b/tests/custom/permutations/01_representation/int/0004_given_permutation_in_param_2_cycle/stdout.expected index 5647c94283..e06ed83776 100644 --- a/tests/custom/permutations/01_representation/int/0004_given_permutation_in_param_2_cycle/stdout.expected +++ b/tests/custom/permutations/01_representation/int/0004_given_permutation_in_param_2_cycle/stdout.expected @@ -1,7 +1,7 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime permutation.param +Savile Row: conjure-output/model000001.eprime permutation.param Running minion for domain filtering. Running solver: minion Copying solution to: permutation-permutation.solution diff --git a/tests/custom/permutations/01_representation/int/0005_find_permutation_size_4_of_int1_4/stdout.expected b/tests/custom/permutations/01_representation/int/0005_find_permutation_size_4_of_int1_4/stdout.expected index 7b1571cfa2..30233582a6 100644 --- a/tests/custom/permutations/01_representation/int/0005_find_permutation_size_4_of_int1_4/stdout.expected +++ b/tests/custom/permutations/01_representation/int/0005_find_permutation_size_4_of_int1_4/stdout.expected @@ -1,7 +1,7 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime +Savile Row: conjure-output/model000001.eprime Running minion for domain filtering. Running solver: minion Copying solution to: permutation-000001.solution diff --git a/tests/custom/permutations/01_representation/int/0006_find_permutation_size_0_of_int1_4/stdout.expected b/tests/custom/permutations/01_representation/int/0006_find_permutation_size_0_of_int1_4/stdout.expected index b4f1327bab..f5bbc850ff 100644 --- a/tests/custom/permutations/01_representation/int/0006_find_permutation_size_0_of_int1_4/stdout.expected +++ b/tests/custom/permutations/01_representation/int/0006_find_permutation_size_0_of_int1_4/stdout.expected @@ -1,7 +1,7 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime +Savile Row: conjure-output/model000001.eprime Running minion for domain filtering. Running solver: minion Copying solution to: permutation-000001.solution diff --git a/tests/custom/permutations/01_representation/int/0007_letting_permutation_be_empty/stdout.expected b/tests/custom/permutations/01_representation/int/0007_letting_permutation_be_empty/stdout.expected index ec07b6eae6..5b299b17a4 100644 --- a/tests/custom/permutations/01_representation/int/0007_letting_permutation_be_empty/stdout.expected +++ b/tests/custom/permutations/01_representation/int/0007_letting_permutation_be_empty/stdout.expected @@ -1,7 +1,7 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime +Savile Row: conjure-output/model000001.eprime Running minion for domain filtering. Running solver: minion Copying solution to: permutation-000001.solution diff --git a/tests/custom/permutations/01_representation/int/0008_find_permutation_of_int1_4/stdout.expected b/tests/custom/permutations/01_representation/int/0008_find_permutation_of_int1_4/stdout.expected index 83209a27c0..09991c86ae 100644 --- a/tests/custom/permutations/01_representation/int/0008_find_permutation_of_int1_4/stdout.expected +++ b/tests/custom/permutations/01_representation/int/0008_find_permutation_of_int1_4/stdout.expected @@ -1,7 +1,7 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime +Savile Row: conjure-output/model000001.eprime Running minion for domain filtering. Running solver: minion Copying solution to: permutation-000001.solution diff --git a/tests/custom/permutations/01_representation/int/0009_letting_permutation_in_model/stdout.expected b/tests/custom/permutations/01_representation/int/0009_letting_permutation_in_model/stdout.expected index 0d4e03724a..8392c51c10 100644 --- a/tests/custom/permutations/01_representation/int/0009_letting_permutation_in_model/stdout.expected +++ b/tests/custom/permutations/01_representation/int/0009_letting_permutation_in_model/stdout.expected @@ -1,7 +1,7 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime +Savile Row: conjure-output/model000001.eprime Running minion for domain filtering. Running solver: minion Copying solution to: permutation.solution diff --git a/tests/custom/permutations/01_representation/int/0010_find_permutation_maxSize_2_of_int1_3/stdout.expected b/tests/custom/permutations/01_representation/int/0010_find_permutation_maxSize_2_of_int1_3/stdout.expected index 91b5decf7f..417e02039c 100644 --- a/tests/custom/permutations/01_representation/int/0010_find_permutation_maxSize_2_of_int1_3/stdout.expected +++ b/tests/custom/permutations/01_representation/int/0010_find_permutation_maxSize_2_of_int1_3/stdout.expected @@ -1,7 +1,7 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime +Savile Row: conjure-output/model000001.eprime Running minion for domain filtering. Running solver: minion Copying solution to: permutation-000001.solution diff --git a/tests/custom/permutations/01_representation/int/0011_find_permutation_minSize_2_of_int1_3/stdout.expected b/tests/custom/permutations/01_representation/int/0011_find_permutation_minSize_2_of_int1_3/stdout.expected index a9a1c78abd..10c1ac494a 100644 --- a/tests/custom/permutations/01_representation/int/0011_find_permutation_minSize_2_of_int1_3/stdout.expected +++ b/tests/custom/permutations/01_representation/int/0011_find_permutation_minSize_2_of_int1_3/stdout.expected @@ -1,7 +1,7 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime +Savile Row: conjure-output/model000001.eprime Running minion for domain filtering. Running solver: minion Copying solution to: permutation-000001.solution diff --git a/tests/custom/permutations/01_representation/int/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/stdout.expected b/tests/custom/permutations/01_representation/int/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/stdout.expected index 0eaaa20d2d..2977042806 100644 --- a/tests/custom/permutations/01_representation/int/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/stdout.expected +++ b/tests/custom/permutations/01_representation/int/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/stdout.expected @@ -1,7 +1,7 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime +Savile Row: conjure-output/model000001.eprime Running minion for domain filtering. Running solver: minion Copying solution to: permutation-000001.solution diff --git a/tests/custom/permutations/01_representation/unnamed/0005_find_permutation_size_4_of_int1_4/stdout.expected b/tests/custom/permutations/01_representation/unnamed/0005_find_permutation_size_4_of_int1_4/stdout.expected index f40c0fd744..bda2fb4d61 100644 --- a/tests/custom/permutations/01_representation/unnamed/0005_find_permutation_size_4_of_int1_4/stdout.expected +++ b/tests/custom/permutations/01_representation/unnamed/0005_find_permutation_size_4_of_int1_4/stdout.expected @@ -1,7 +1,7 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime +Savile Row: conjure-output/model000001.eprime Running minion for domain filtering. Running solver: minion Copying solution to: permutation-000001.solution diff --git a/tests/custom/permutations/01_representation/unnamed/0006_find_permutation_size_0_of_int1_4/stdout.expected b/tests/custom/permutations/01_representation/unnamed/0006_find_permutation_size_0_of_int1_4/stdout.expected index bd08d5f4ce..2a1eae62d5 100644 --- a/tests/custom/permutations/01_representation/unnamed/0006_find_permutation_size_0_of_int1_4/stdout.expected +++ b/tests/custom/permutations/01_representation/unnamed/0006_find_permutation_size_0_of_int1_4/stdout.expected @@ -1,7 +1,7 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime +Savile Row: conjure-output/model000001.eprime Running minion for domain filtering. Running solver: minion Copying solution to: permutation-000001.solution diff --git a/tests/custom/permutations/01_representation/unnamed/0007_letting_permutation_be_empty/stdout.expected b/tests/custom/permutations/01_representation/unnamed/0007_letting_permutation_be_empty/stdout.expected index ec07b6eae6..5b299b17a4 100644 --- a/tests/custom/permutations/01_representation/unnamed/0007_letting_permutation_be_empty/stdout.expected +++ b/tests/custom/permutations/01_representation/unnamed/0007_letting_permutation_be_empty/stdout.expected @@ -1,7 +1,7 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime +Savile Row: conjure-output/model000001.eprime Running minion for domain filtering. Running solver: minion Copying solution to: permutation-000001.solution diff --git a/tests/custom/permutations/01_representation/unnamed/0008_find_permutation_of_int1_4/stdout.expected b/tests/custom/permutations/01_representation/unnamed/0008_find_permutation_of_int1_4/stdout.expected index 406751431a..132fdf4f0b 100644 --- a/tests/custom/permutations/01_representation/unnamed/0008_find_permutation_of_int1_4/stdout.expected +++ b/tests/custom/permutations/01_representation/unnamed/0008_find_permutation_of_int1_4/stdout.expected @@ -1,7 +1,7 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime +Savile Row: conjure-output/model000001.eprime Running minion for domain filtering. Running solver: minion Copying solution to: permutation-000001.solution diff --git a/tests/custom/permutations/01_representation/unnamed/0010_find_permutation_maxSize_2_of_int1_3/stdout.expected b/tests/custom/permutations/01_representation/unnamed/0010_find_permutation_maxSize_2_of_int1_3/stdout.expected index 433fb7e809..fb25bae5b0 100644 --- a/tests/custom/permutations/01_representation/unnamed/0010_find_permutation_maxSize_2_of_int1_3/stdout.expected +++ b/tests/custom/permutations/01_representation/unnamed/0010_find_permutation_maxSize_2_of_int1_3/stdout.expected @@ -1,7 +1,7 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime +Savile Row: conjure-output/model000001.eprime Running minion for domain filtering. Running solver: minion Copying solution to: permutation-000001.solution diff --git a/tests/custom/permutations/01_representation/unnamed/0011_find_permutation_minSize_2_of_int1_3/stdout.expected b/tests/custom/permutations/01_representation/unnamed/0011_find_permutation_minSize_2_of_int1_3/stdout.expected index e50ce95dd4..cdc194ed2d 100644 --- a/tests/custom/permutations/01_representation/unnamed/0011_find_permutation_minSize_2_of_int1_3/stdout.expected +++ b/tests/custom/permutations/01_representation/unnamed/0011_find_permutation_minSize_2_of_int1_3/stdout.expected @@ -1,7 +1,7 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime +Savile Row: conjure-output/model000001.eprime Running minion for domain filtering. Running solver: minion Copying solution to: permutation-000001.solution diff --git a/tests/custom/permutations/01_representation/unnamed/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/stdout.expected b/tests/custom/permutations/01_representation/unnamed/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/stdout.expected index 48284da1a7..8a34f2786f 100644 --- a/tests/custom/permutations/01_representation/unnamed/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/stdout.expected +++ b/tests/custom/permutations/01_representation/unnamed/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/stdout.expected @@ -1,7 +1,7 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime +Savile Row: conjure-output/model000001.eprime Running minion for domain filtering. Running solver: minion Copying solution to: permutation-000001.solution diff --git a/tests/custom/permutations/02_cardinality/enum/0001_given_permutation_in_param/stdout.expected b/tests/custom/permutations/02_cardinality/enum/0001_given_permutation_in_param/stdout.expected index 20fbad7e28..5f48ab6194 100644 --- a/tests/custom/permutations/02_cardinality/enum/0001_given_permutation_in_param/stdout.expected +++ b/tests/custom/permutations/02_cardinality/enum/0001_given_permutation_in_param/stdout.expected @@ -1,7 +1,7 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime permutation.param +Savile Row: conjure-output/model000001.eprime permutation.param Running minion for domain filtering. Running solver: minion Copying solution to: permutation-permutation.solution diff --git a/tests/custom/permutations/02_cardinality/enum/0002_letting_permutation_in_model/stdout.expected b/tests/custom/permutations/02_cardinality/enum/0002_letting_permutation_in_model/stdout.expected index 3ab39cd95e..217a24cfca 100644 --- a/tests/custom/permutations/02_cardinality/enum/0002_letting_permutation_in_model/stdout.expected +++ b/tests/custom/permutations/02_cardinality/enum/0002_letting_permutation_in_model/stdout.expected @@ -1,7 +1,7 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime +Savile Row: conjure-output/model000001.eprime Running minion for domain filtering. Running solver: minion Copying solution to: permutation.solution diff --git a/tests/custom/permutations/02_cardinality/enum/0003_find_permutation/stdout.expected b/tests/custom/permutations/02_cardinality/enum/0003_find_permutation/stdout.expected index a4d8784d54..d97affcee4 100644 --- a/tests/custom/permutations/02_cardinality/enum/0003_find_permutation/stdout.expected +++ b/tests/custom/permutations/02_cardinality/enum/0003_find_permutation/stdout.expected @@ -1,7 +1,7 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime +Savile Row: conjure-output/model000001.eprime Running minion for domain filtering. Running solver: minion Copying solution to: permutation.solution diff --git a/tests/custom/permutations/02_cardinality/int/0001_given_permutation_in_param/stdout.expected b/tests/custom/permutations/02_cardinality/int/0001_given_permutation_in_param/stdout.expected index 20fbad7e28..5f48ab6194 100644 --- a/tests/custom/permutations/02_cardinality/int/0001_given_permutation_in_param/stdout.expected +++ b/tests/custom/permutations/02_cardinality/int/0001_given_permutation_in_param/stdout.expected @@ -1,7 +1,7 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime permutation.param +Savile Row: conjure-output/model000001.eprime permutation.param Running minion for domain filtering. Running solver: minion Copying solution to: permutation-permutation.solution diff --git a/tests/custom/permutations/02_cardinality/int/0002_letting_permutation_in_model/stdout.expected b/tests/custom/permutations/02_cardinality/int/0002_letting_permutation_in_model/stdout.expected index 3ab39cd95e..217a24cfca 100644 --- a/tests/custom/permutations/02_cardinality/int/0002_letting_permutation_in_model/stdout.expected +++ b/tests/custom/permutations/02_cardinality/int/0002_letting_permutation_in_model/stdout.expected @@ -1,7 +1,7 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime +Savile Row: conjure-output/model000001.eprime Running minion for domain filtering. Running solver: minion Copying solution to: permutation.solution diff --git a/tests/custom/permutations/02_cardinality/int/0003_find_permutation/stdout.expected b/tests/custom/permutations/02_cardinality/int/0003_find_permutation/stdout.expected index 9118fc1452..f99c8a3035 100644 --- a/tests/custom/permutations/02_cardinality/int/0003_find_permutation/stdout.expected +++ b/tests/custom/permutations/02_cardinality/int/0003_find_permutation/stdout.expected @@ -1,7 +1,7 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime +Savile Row: conjure-output/model000001.eprime Running minion for domain filtering. Running solver: minion Copying solution to: permutation.solution diff --git a/tests/custom/permutations/02_cardinality/unnamed/0003_find_permutation/stdout.expected b/tests/custom/permutations/02_cardinality/unnamed/0003_find_permutation/stdout.expected index cd9a4f6023..0ed894794e 100644 --- a/tests/custom/permutations/02_cardinality/unnamed/0003_find_permutation/stdout.expected +++ b/tests/custom/permutations/02_cardinality/unnamed/0003_find_permutation/stdout.expected @@ -1,7 +1,7 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime +Savile Row: conjure-output/model000001.eprime Running minion for domain filtering. Running solver: minion Copying solution to: permutation.solution diff --git a/tests/custom/permutations/03_generators/enum/0001_given_permutation_in_generator/stdout.expected b/tests/custom/permutations/03_generators/enum/0001_given_permutation_in_generator/stdout.expected index d53f37c87f..ffac9d34a4 100644 --- a/tests/custom/permutations/03_generators/enum/0001_given_permutation_in_generator/stdout.expected +++ b/tests/custom/permutations/03_generators/enum/0001_given_permutation_in_generator/stdout.expected @@ -1,7 +1,7 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime permutation.param +Savile Row: conjure-output/model000001.eprime permutation.param Running minion for domain filtering. Running solver: minion Copying solution to: permutation-permutation.solution diff --git a/tests/custom/permutations/03_generators/enum/0002_letting_permutation_in_generator/stdout.expected b/tests/custom/permutations/03_generators/enum/0002_letting_permutation_in_generator/stdout.expected index 6486b360cf..e442316be1 100644 --- a/tests/custom/permutations/03_generators/enum/0002_letting_permutation_in_generator/stdout.expected +++ b/tests/custom/permutations/03_generators/enum/0002_letting_permutation_in_generator/stdout.expected @@ -1,7 +1,7 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime +Savile Row: conjure-output/model000001.eprime Running minion for domain filtering. Running solver: minion Copying solution to: permutation.solution diff --git a/tests/custom/permutations/03_generators/enum/0003_find_permutation_in_generator/stdout.expected b/tests/custom/permutations/03_generators/enum/0003_find_permutation_in_generator/stdout.expected index 77f077b491..e275a546af 100644 --- a/tests/custom/permutations/03_generators/enum/0003_find_permutation_in_generator/stdout.expected +++ b/tests/custom/permutations/03_generators/enum/0003_find_permutation_in_generator/stdout.expected @@ -1,7 +1,7 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime +Savile Row: conjure-output/model000001.eprime Running minion for domain filtering. Running solver: minion Copying solution to: permutation-000001.solution diff --git a/tests/custom/permutations/03_generators/enum/0004_find_permutation_in_generator/stdout.expected b/tests/custom/permutations/03_generators/enum/0004_find_permutation_in_generator/stdout.expected index d4267c724a..6816822800 100644 --- a/tests/custom/permutations/03_generators/enum/0004_find_permutation_in_generator/stdout.expected +++ b/tests/custom/permutations/03_generators/enum/0004_find_permutation_in_generator/stdout.expected @@ -1,7 +1,7 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime +Savile Row: conjure-output/model000001.eprime Running minion for domain filtering. Running solver: minion Copying solution to: permutation-000001.solution diff --git a/tests/custom/permutations/03_generators/int/0001_given_permutation_in_generator/stdout.expected b/tests/custom/permutations/03_generators/int/0001_given_permutation_in_generator/stdout.expected index e6900d7f85..60983bf161 100644 --- a/tests/custom/permutations/03_generators/int/0001_given_permutation_in_generator/stdout.expected +++ b/tests/custom/permutations/03_generators/int/0001_given_permutation_in_generator/stdout.expected @@ -1,7 +1,7 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime permutation.param +Savile Row: conjure-output/model000001.eprime permutation.param Running minion for domain filtering. Running solver: minion Copying solution to: permutation-permutation.solution diff --git a/tests/custom/permutations/03_generators/int/0002_letting_permutation_in_generator/stdout.expected b/tests/custom/permutations/03_generators/int/0002_letting_permutation_in_generator/stdout.expected index 81e68794fb..5da8f78d23 100644 --- a/tests/custom/permutations/03_generators/int/0002_letting_permutation_in_generator/stdout.expected +++ b/tests/custom/permutations/03_generators/int/0002_letting_permutation_in_generator/stdout.expected @@ -1,7 +1,7 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime +Savile Row: conjure-output/model000001.eprime Running minion for domain filtering. Running solver: minion Copying solution to: permutation.solution diff --git a/tests/custom/permutations/03_generators/int/0003_find_permutation_in_generator/stdout.expected b/tests/custom/permutations/03_generators/int/0003_find_permutation_in_generator/stdout.expected index e4bbddf612..a84e90be54 100644 --- a/tests/custom/permutations/03_generators/int/0003_find_permutation_in_generator/stdout.expected +++ b/tests/custom/permutations/03_generators/int/0003_find_permutation_in_generator/stdout.expected @@ -1,7 +1,7 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime +Savile Row: conjure-output/model000001.eprime Running minion for domain filtering. Running solver: minion Copying solution to: permutation-000001.solution diff --git a/tests/custom/permutations/03_generators/int/0004_find_permutation_in_forall/stdout.expected b/tests/custom/permutations/03_generators/int/0004_find_permutation_in_forall/stdout.expected index e4bbddf612..a84e90be54 100644 --- a/tests/custom/permutations/03_generators/int/0004_find_permutation_in_forall/stdout.expected +++ b/tests/custom/permutations/03_generators/int/0004_find_permutation_in_forall/stdout.expected @@ -1,7 +1,7 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime +Savile Row: conjure-output/model000001.eprime Running minion for domain filtering. Running solver: minion Copying solution to: permutation-000001.solution diff --git a/tests/custom/permutations/03_generators/int/0005_find_permutation_in_forall/stdout.expected b/tests/custom/permutations/03_generators/int/0005_find_permutation_in_forall/stdout.expected index e4bbddf612..a84e90be54 100644 --- a/tests/custom/permutations/03_generators/int/0005_find_permutation_in_forall/stdout.expected +++ b/tests/custom/permutations/03_generators/int/0005_find_permutation_in_forall/stdout.expected @@ -1,7 +1,7 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime +Savile Row: conjure-output/model000001.eprime Running minion for domain filtering. Running solver: minion Copying solution to: permutation-000001.solution diff --git a/tests/custom/permutations/03_generators/unnamed/0003_find_permutation_in_generator/stdout.expected b/tests/custom/permutations/03_generators/unnamed/0003_find_permutation_in_generator/stdout.expected index 9f9651a8e0..42cb55822b 100644 --- a/tests/custom/permutations/03_generators/unnamed/0003_find_permutation_in_generator/stdout.expected +++ b/tests/custom/permutations/03_generators/unnamed/0003_find_permutation_in_generator/stdout.expected @@ -1,7 +1,7 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime +Savile Row: conjure-output/model000001.eprime Running minion for domain filtering. Running solver: minion Copying solution to: permutation-000001.solution diff --git a/tests/custom/permutations/04_image/enum/0001_given_permutation_given_enum/stdout.expected b/tests/custom/permutations/04_image/enum/0001_given_permutation_given_enum/stdout.expected index 96238bbb42..5e8f3e2eed 100644 --- a/tests/custom/permutations/04_image/enum/0001_given_permutation_given_enum/stdout.expected +++ b/tests/custom/permutations/04_image/enum/0001_given_permutation_given_enum/stdout.expected @@ -1,10 +1,10 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime permutation.param +Savile Row: conjure-output/model000001.eprime permutation.param Running minion for domain filtering. Running solver: minion -Savile Row: model000001.eprime permutation2.param +Savile Row: conjure-output/model000001.eprime permutation2.param Running minion for domain filtering. Running solver: minion Copying solution to: permutation-permutation.solution diff --git a/tests/custom/permutations/04_image/enum/0002_given_permutation_letting_enum/stdout.expected b/tests/custom/permutations/04_image/enum/0002_given_permutation_letting_enum/stdout.expected index 4176f65d0c..31ee8836d7 100644 --- a/tests/custom/permutations/04_image/enum/0002_given_permutation_letting_enum/stdout.expected +++ b/tests/custom/permutations/04_image/enum/0002_given_permutation_letting_enum/stdout.expected @@ -1,7 +1,7 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime permutation.param +Savile Row: conjure-output/model000001.eprime permutation.param Running minion for domain filtering. Running solver: minion Copying solution to: permutation-permutation.solution diff --git a/tests/custom/permutations/04_image/enum/0003_given_permutation_letting_enum/stdout.expected b/tests/custom/permutations/04_image/enum/0003_given_permutation_letting_enum/stdout.expected index 905052aa12..ae72724ccc 100644 --- a/tests/custom/permutations/04_image/enum/0003_given_permutation_letting_enum/stdout.expected +++ b/tests/custom/permutations/04_image/enum/0003_given_permutation_letting_enum/stdout.expected @@ -1,7 +1,7 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime permutation.param +Savile Row: conjure-output/model000001.eprime permutation.param Running minion for domain filtering. Running solver: minion Copying solution to: permutation-permutation.solution diff --git a/tests/custom/permutations/04_image/enum/0004_given_permutation_find_enum/stdout.expected b/tests/custom/permutations/04_image/enum/0004_given_permutation_find_enum/stdout.expected index ca4b67273f..0a5568f374 100644 --- a/tests/custom/permutations/04_image/enum/0004_given_permutation_find_enum/stdout.expected +++ b/tests/custom/permutations/04_image/enum/0004_given_permutation_find_enum/stdout.expected @@ -1,10 +1,10 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime permutation2.essence +Savile Row: conjure-output/model000001.eprime permutation2.essence Running minion for domain filtering. Running solver: minion -Savile Row: model000001.eprime permutation.param +Savile Row: conjure-output/model000001.eprime permutation.param Running minion for domain filtering. Running solver: minion Copying solution to: permutation-permutation.solution diff --git a/tests/custom/permutations/04_image/enum/0005_find_permutation_given_enums/stdout.expected b/tests/custom/permutations/04_image/enum/0005_find_permutation_given_enums/stdout.expected index 89fe444110..1de0c4533d 100644 --- a/tests/custom/permutations/04_image/enum/0005_find_permutation_given_enums/stdout.expected +++ b/tests/custom/permutations/04_image/enum/0005_find_permutation_given_enums/stdout.expected @@ -1,10 +1,10 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime permutation.param +Savile Row: conjure-output/model000001.eprime permutation.param Running minion for domain filtering. Running solver: minion -Savile Row: model000001.eprime permutation2.param +Savile Row: conjure-output/model000001.eprime permutation2.param Running minion for domain filtering. Running solver: minion Copying solution to: permutation-permutation.solution diff --git a/tests/custom/permutations/04_image/enum/0006_letting_permutation_given_enum/stdout.expected b/tests/custom/permutations/04_image/enum/0006_letting_permutation_given_enum/stdout.expected index 96238bbb42..5e8f3e2eed 100644 --- a/tests/custom/permutations/04_image/enum/0006_letting_permutation_given_enum/stdout.expected +++ b/tests/custom/permutations/04_image/enum/0006_letting_permutation_given_enum/stdout.expected @@ -1,10 +1,10 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime permutation.param +Savile Row: conjure-output/model000001.eprime permutation.param Running minion for domain filtering. Running solver: minion -Savile Row: model000001.eprime permutation2.param +Savile Row: conjure-output/model000001.eprime permutation2.param Running minion for domain filtering. Running solver: minion Copying solution to: permutation-permutation.solution diff --git a/tests/custom/permutations/04_image/enum/0007_find_permutation_find_enums/stdout.expected b/tests/custom/permutations/04_image/enum/0007_find_permutation_find_enums/stdout.expected index d5fca1e209..c341d77586 100644 --- a/tests/custom/permutations/04_image/enum/0007_find_permutation_find_enums/stdout.expected +++ b/tests/custom/permutations/04_image/enum/0007_find_permutation_find_enums/stdout.expected @@ -1,7 +1,7 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime +Savile Row: conjure-output/model000001.eprime Running minion for domain filtering. Running solver: minion Copying solution to: permutation.solution diff --git a/tests/custom/permutations/04_image/int/0001_given_permutation_given_int/stdout.expected b/tests/custom/permutations/04_image/int/0001_given_permutation_given_int/stdout.expected index 1b04c05ccd..bcd441d1aa 100644 --- a/tests/custom/permutations/04_image/int/0001_given_permutation_given_int/stdout.expected +++ b/tests/custom/permutations/04_image/int/0001_given_permutation_given_int/stdout.expected @@ -1,10 +1,10 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime permutation.param +Savile Row: conjure-output/model000001.eprime permutation.param Running minion for domain filtering. Running solver: minion -Savile Row: model000001.eprime permutation2.param +Savile Row: conjure-output/model000001.eprime permutation2.param Running minion for domain filtering. Running solver: minion Copying solution to: permutation-permutation.solution diff --git a/tests/custom/permutations/04_image/int/0002_given_permutation_letting_int/stdout.expected b/tests/custom/permutations/04_image/int/0002_given_permutation_letting_int/stdout.expected index 71a75b7bc2..593cc9ff97 100644 --- a/tests/custom/permutations/04_image/int/0002_given_permutation_letting_int/stdout.expected +++ b/tests/custom/permutations/04_image/int/0002_given_permutation_letting_int/stdout.expected @@ -1,7 +1,7 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime permutation.param +Savile Row: conjure-output/model000001.eprime permutation.param Running minion for domain filtering. Running solver: minion Copying solution to: permutation-permutation.solution diff --git a/tests/custom/permutations/04_image/int/0003_given_permutation_letting_int/stdout.expected b/tests/custom/permutations/04_image/int/0003_given_permutation_letting_int/stdout.expected index f95ce6dc3a..b02339d868 100644 --- a/tests/custom/permutations/04_image/int/0003_given_permutation_letting_int/stdout.expected +++ b/tests/custom/permutations/04_image/int/0003_given_permutation_letting_int/stdout.expected @@ -1,7 +1,7 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime permutation.param +Savile Row: conjure-output/model000001.eprime permutation.param Running minion for domain filtering. Running solver: minion Copying solution to: permutation-permutation.solution diff --git a/tests/custom/permutations/04_image/int/0004_given_permutation_find_int/stdout.expected b/tests/custom/permutations/04_image/int/0004_given_permutation_find_int/stdout.expected index ddc463d77a..ccaa2e8eb3 100644 --- a/tests/custom/permutations/04_image/int/0004_given_permutation_find_int/stdout.expected +++ b/tests/custom/permutations/04_image/int/0004_given_permutation_find_int/stdout.expected @@ -1,10 +1,10 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime permutation2.essence +Savile Row: conjure-output/model000001.eprime permutation2.essence Running minion for domain filtering. Running solver: minion -Savile Row: model000001.eprime permutation.param +Savile Row: conjure-output/model000001.eprime permutation.param Running minion for domain filtering. Running solver: minion Copying solution to: permutation-permutation.solution diff --git a/tests/custom/permutations/04_image/int/0005_find_permutation_given_ints/stdout.expected b/tests/custom/permutations/04_image/int/0005_find_permutation_given_ints/stdout.expected index 12ea6f63e6..25b05b3e45 100644 --- a/tests/custom/permutations/04_image/int/0005_find_permutation_given_ints/stdout.expected +++ b/tests/custom/permutations/04_image/int/0005_find_permutation_given_ints/stdout.expected @@ -1,10 +1,10 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime permutation.param +Savile Row: conjure-output/model000001.eprime permutation.param Running minion for domain filtering. Running solver: minion -Savile Row: model000001.eprime permutation2.param +Savile Row: conjure-output/model000001.eprime permutation2.param Running minion for domain filtering. Running solver: minion Copying solution to: permutation-permutation.solution diff --git a/tests/custom/permutations/04_image/int/0006_letting_permutation_given_int/stdout.expected b/tests/custom/permutations/04_image/int/0006_letting_permutation_given_int/stdout.expected index 1b04c05ccd..bcd441d1aa 100644 --- a/tests/custom/permutations/04_image/int/0006_letting_permutation_given_int/stdout.expected +++ b/tests/custom/permutations/04_image/int/0006_letting_permutation_given_int/stdout.expected @@ -1,10 +1,10 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime permutation.param +Savile Row: conjure-output/model000001.eprime permutation.param Running minion for domain filtering. Running solver: minion -Savile Row: model000001.eprime permutation2.param +Savile Row: conjure-output/model000001.eprime permutation2.param Running minion for domain filtering. Running solver: minion Copying solution to: permutation-permutation.solution diff --git a/tests/custom/permutations/04_image/int/0007_find_permutation_find_ints/stdout.expected b/tests/custom/permutations/04_image/int/0007_find_permutation_find_ints/stdout.expected index f794d92540..1a74140bcb 100644 --- a/tests/custom/permutations/04_image/int/0007_find_permutation_find_ints/stdout.expected +++ b/tests/custom/permutations/04_image/int/0007_find_permutation_find_ints/stdout.expected @@ -1,7 +1,7 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime +Savile Row: conjure-output/model000001.eprime Running minion for domain filtering. Running solver: minion Copying solution to: permutation.solution diff --git a/tests/custom/permutations/04_image/unnamed/0007_find_permutation_find_unnameds/stdout.expected b/tests/custom/permutations/04_image/unnamed/0007_find_permutation_find_unnameds/stdout.expected index 35ff4abb03..3c90460839 100644 --- a/tests/custom/permutations/04_image/unnamed/0007_find_permutation_find_unnameds/stdout.expected +++ b/tests/custom/permutations/04_image/unnamed/0007_find_permutation_find_unnameds/stdout.expected @@ -1,7 +1,7 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime +Savile Row: conjure-output/model000001.eprime Running minion for domain filtering. Running solver: minion Copying solution to: permutation.solution diff --git a/tests/custom/permutations/05_equality/enum/0001_given_permutations_in_param/stdout.expected b/tests/custom/permutations/05_equality/enum/0001_given_permutations_in_param/stdout.expected index 8a78c0058b..0181f4d9cb 100644 --- a/tests/custom/permutations/05_equality/enum/0001_given_permutations_in_param/stdout.expected +++ b/tests/custom/permutations/05_equality/enum/0001_given_permutations_in_param/stdout.expected @@ -1,7 +1,7 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime permutation.param +Savile Row: conjure-output/model000001.eprime permutation.param Running minion for domain filtering. Running solver: minion Copying solution to: permutation-permutation.solution diff --git a/tests/custom/permutations/05_equality/enum/0002_given_permutations_in_param/stdout.expected b/tests/custom/permutations/05_equality/enum/0002_given_permutations_in_param/stdout.expected index da9c2d6b8a..5d33b20ade 100644 --- a/tests/custom/permutations/05_equality/enum/0002_given_permutations_in_param/stdout.expected +++ b/tests/custom/permutations/05_equality/enum/0002_given_permutations_in_param/stdout.expected @@ -1,7 +1,7 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime permutation.param +Savile Row: conjure-output/model000001.eprime permutation.param Running minion for domain filtering. Running solver: minion Copying solution to: permutation-permutation.solution diff --git a/tests/custom/permutations/05_equality/enum/0003_given_equal_letting/stdout.expected b/tests/custom/permutations/05_equality/enum/0003_given_equal_letting/stdout.expected index da9c2d6b8a..5d33b20ade 100644 --- a/tests/custom/permutations/05_equality/enum/0003_given_equal_letting/stdout.expected +++ b/tests/custom/permutations/05_equality/enum/0003_given_equal_letting/stdout.expected @@ -1,7 +1,7 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime permutation.param +Savile Row: conjure-output/model000001.eprime permutation.param Running minion for domain filtering. Running solver: minion Copying solution to: permutation-permutation.solution diff --git a/tests/custom/permutations/05_equality/enum/0004_letting_equal_given/stdout.expected b/tests/custom/permutations/05_equality/enum/0004_letting_equal_given/stdout.expected index da9c2d6b8a..5d33b20ade 100644 --- a/tests/custom/permutations/05_equality/enum/0004_letting_equal_given/stdout.expected +++ b/tests/custom/permutations/05_equality/enum/0004_letting_equal_given/stdout.expected @@ -1,7 +1,7 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime permutation.param +Savile Row: conjure-output/model000001.eprime permutation.param Running minion for domain filtering. Running solver: minion Copying solution to: permutation-permutation.solution diff --git a/tests/custom/permutations/05_equality/enum/0005_find_eq_find/stdout.expected b/tests/custom/permutations/05_equality/enum/0005_find_eq_find/stdout.expected index e89e1c34ab..010a0c9f45 100644 --- a/tests/custom/permutations/05_equality/enum/0005_find_eq_find/stdout.expected +++ b/tests/custom/permutations/05_equality/enum/0005_find_eq_find/stdout.expected @@ -1,7 +1,7 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime +Savile Row: conjure-output/model000001.eprime Running minion for domain filtering. Running solver: minion Copying solution to: permutation-000001.solution diff --git a/tests/custom/permutations/05_equality/enum/0006_in_comprehension/stdout.expected b/tests/custom/permutations/05_equality/enum/0006_in_comprehension/stdout.expected index 8f60251025..2009dc03a6 100644 --- a/tests/custom/permutations/05_equality/enum/0006_in_comprehension/stdout.expected +++ b/tests/custom/permutations/05_equality/enum/0006_in_comprehension/stdout.expected @@ -1,7 +1,7 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime +Savile Row: conjure-output/model000001.eprime Running minion for domain filtering. Running solver: minion Copying solution to: permutation-000001.solution diff --git a/tests/custom/permutations/05_equality/int/0001_given_permutations_in_param/stdout.expected b/tests/custom/permutations/05_equality/int/0001_given_permutations_in_param/stdout.expected index 8a78c0058b..0181f4d9cb 100644 --- a/tests/custom/permutations/05_equality/int/0001_given_permutations_in_param/stdout.expected +++ b/tests/custom/permutations/05_equality/int/0001_given_permutations_in_param/stdout.expected @@ -1,7 +1,7 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime permutation.param +Savile Row: conjure-output/model000001.eprime permutation.param Running minion for domain filtering. Running solver: minion Copying solution to: permutation-permutation.solution diff --git a/tests/custom/permutations/05_equality/int/0002_given_permutations_in_param/stdout.expected b/tests/custom/permutations/05_equality/int/0002_given_permutations_in_param/stdout.expected index da9c2d6b8a..5d33b20ade 100644 --- a/tests/custom/permutations/05_equality/int/0002_given_permutations_in_param/stdout.expected +++ b/tests/custom/permutations/05_equality/int/0002_given_permutations_in_param/stdout.expected @@ -1,7 +1,7 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime permutation.param +Savile Row: conjure-output/model000001.eprime permutation.param Running minion for domain filtering. Running solver: minion Copying solution to: permutation-permutation.solution diff --git a/tests/custom/permutations/05_equality/int/0003_given_equal_letting/stdout.expected b/tests/custom/permutations/05_equality/int/0003_given_equal_letting/stdout.expected index da9c2d6b8a..5d33b20ade 100644 --- a/tests/custom/permutations/05_equality/int/0003_given_equal_letting/stdout.expected +++ b/tests/custom/permutations/05_equality/int/0003_given_equal_letting/stdout.expected @@ -1,7 +1,7 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime permutation.param +Savile Row: conjure-output/model000001.eprime permutation.param Running minion for domain filtering. Running solver: minion Copying solution to: permutation-permutation.solution diff --git a/tests/custom/permutations/05_equality/int/0004_letting_equal_given/stdout.expected b/tests/custom/permutations/05_equality/int/0004_letting_equal_given/stdout.expected index da9c2d6b8a..5d33b20ade 100644 --- a/tests/custom/permutations/05_equality/int/0004_letting_equal_given/stdout.expected +++ b/tests/custom/permutations/05_equality/int/0004_letting_equal_given/stdout.expected @@ -1,7 +1,7 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime permutation.param +Savile Row: conjure-output/model000001.eprime permutation.param Running minion for domain filtering. Running solver: minion Copying solution to: permutation-permutation.solution diff --git a/tests/custom/permutations/05_equality/int/0005_find_eq_find/stdout.expected b/tests/custom/permutations/05_equality/int/0005_find_eq_find/stdout.expected index 9961ea40fb..dec15cb598 100644 --- a/tests/custom/permutations/05_equality/int/0005_find_eq_find/stdout.expected +++ b/tests/custom/permutations/05_equality/int/0005_find_eq_find/stdout.expected @@ -1,7 +1,7 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime +Savile Row: conjure-output/model000001.eprime Running minion for domain filtering. Running solver: minion Copying solution to: permutation-000001.solution diff --git a/tests/custom/permutations/05_equality/int/0006_in_comprehension/stdout.expected b/tests/custom/permutations/05_equality/int/0006_in_comprehension/stdout.expected index 6d6696bcce..3dfc0400c1 100644 --- a/tests/custom/permutations/05_equality/int/0006_in_comprehension/stdout.expected +++ b/tests/custom/permutations/05_equality/int/0006_in_comprehension/stdout.expected @@ -1,7 +1,7 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime +Savile Row: conjure-output/model000001.eprime Running minion for domain filtering. Running solver: minion Copying solution to: permutation-000001.solution diff --git a/tests/custom/permutations/05_equality/int/0007_letting_equal_letting/stdout.expected b/tests/custom/permutations/05_equality/int/0007_letting_equal_letting/stdout.expected index bcb4922cff..80426c3e1f 100644 --- a/tests/custom/permutations/05_equality/int/0007_letting_equal_letting/stdout.expected +++ b/tests/custom/permutations/05_equality/int/0007_letting_equal_letting/stdout.expected @@ -1,7 +1,7 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime +Savile Row: conjure-output/model000001.eprime Running minion for domain filtering. Running solver: minion Copying solution to: permutation.solution diff --git a/tests/custom/permutations/05_equality/unnamed/0005_find_eq_find/stdout.expected b/tests/custom/permutations/05_equality/unnamed/0005_find_eq_find/stdout.expected index cd78de8134..2e05a0889e 100644 --- a/tests/custom/permutations/05_equality/unnamed/0005_find_eq_find/stdout.expected +++ b/tests/custom/permutations/05_equality/unnamed/0005_find_eq_find/stdout.expected @@ -1,7 +1,7 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime +Savile Row: conjure-output/model000001.eprime Running minion for domain filtering. Running solver: minion Copying solution to: permutation-000001.solution diff --git a/tests/custom/permutations/05_equality/unnamed/0006_in_comprehension/stdout.expected b/tests/custom/permutations/05_equality/unnamed/0006_in_comprehension/stdout.expected index e971cd91ea..05828cd5c7 100644 --- a/tests/custom/permutations/05_equality/unnamed/0006_in_comprehension/stdout.expected +++ b/tests/custom/permutations/05_equality/unnamed/0006_in_comprehension/stdout.expected @@ -1,7 +1,7 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime +Savile Row: conjure-output/model000001.eprime Running minion for domain filtering. Running solver: minion Copying solution to: permutation-000001.solution diff --git a/tests/custom/permutations/06_inverse/enum/0001_given_permutations_in_param/stdout.expected b/tests/custom/permutations/06_inverse/enum/0001_given_permutations_in_param/stdout.expected index 509db792c4..2cdb038740 100644 --- a/tests/custom/permutations/06_inverse/enum/0001_given_permutations_in_param/stdout.expected +++ b/tests/custom/permutations/06_inverse/enum/0001_given_permutations_in_param/stdout.expected @@ -1,10 +1,10 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime permutation.param +Savile Row: conjure-output/model000001.eprime permutation.param Running minion for domain filtering. Running solver: minion -Savile Row: model000001.eprime permutation2.param +Savile Row: conjure-output/model000001.eprime permutation2.param Running minion for domain filtering. Running solver: minion Copying solution to: permutation-permutation.solution diff --git a/tests/custom/permutations/06_inverse/enum/0002_given_permutations_in_param/stdout.expected b/tests/custom/permutations/06_inverse/enum/0002_given_permutations_in_param/stdout.expected index 509db792c4..2cdb038740 100644 --- a/tests/custom/permutations/06_inverse/enum/0002_given_permutations_in_param/stdout.expected +++ b/tests/custom/permutations/06_inverse/enum/0002_given_permutations_in_param/stdout.expected @@ -1,10 +1,10 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime permutation.param +Savile Row: conjure-output/model000001.eprime permutation.param Running minion for domain filtering. Running solver: minion -Savile Row: model000001.eprime permutation2.param +Savile Row: conjure-output/model000001.eprime permutation2.param Running minion for domain filtering. Running solver: minion Copying solution to: permutation-permutation.solution diff --git a/tests/custom/permutations/06_inverse/enum/0003_given_equal_letting/stdout.expected b/tests/custom/permutations/06_inverse/enum/0003_given_equal_letting/stdout.expected index ad056a321b..57dfa4ed7b 100644 --- a/tests/custom/permutations/06_inverse/enum/0003_given_equal_letting/stdout.expected +++ b/tests/custom/permutations/06_inverse/enum/0003_given_equal_letting/stdout.expected @@ -1,10 +1,10 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime permutation2.essence +Savile Row: conjure-output/model000001.eprime permutation2.essence Running minion for domain filtering. Running solver: minion -Savile Row: model000001.eprime permutation.param +Savile Row: conjure-output/model000001.eprime permutation.param Running minion for domain filtering. Running solver: minion Copying solution to: permutation-permutation.solution diff --git a/tests/custom/permutations/06_inverse/enum/0004_letting_equal_given/stdout.expected b/tests/custom/permutations/06_inverse/enum/0004_letting_equal_given/stdout.expected index 509db792c4..2cdb038740 100644 --- a/tests/custom/permutations/06_inverse/enum/0004_letting_equal_given/stdout.expected +++ b/tests/custom/permutations/06_inverse/enum/0004_letting_equal_given/stdout.expected @@ -1,10 +1,10 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime permutation.param +Savile Row: conjure-output/model000001.eprime permutation.param Running minion for domain filtering. Running solver: minion -Savile Row: model000001.eprime permutation2.param +Savile Row: conjure-output/model000001.eprime permutation2.param Running minion for domain filtering. Running solver: minion Copying solution to: permutation-permutation.solution diff --git a/tests/custom/permutations/06_inverse/enum/0005_find_eq_find/stdout.expected b/tests/custom/permutations/06_inverse/enum/0005_find_eq_find/stdout.expected index 8e8d28c8fb..668c8b2afd 100644 --- a/tests/custom/permutations/06_inverse/enum/0005_find_eq_find/stdout.expected +++ b/tests/custom/permutations/06_inverse/enum/0005_find_eq_find/stdout.expected @@ -1,7 +1,7 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime +Savile Row: conjure-output/model000001.eprime Running minion for domain filtering. Running solver: minion Copying solution to: permutation-000001.solution diff --git a/tests/custom/permutations/06_inverse/int/0001_given_permutations_in_param/stdout.expected b/tests/custom/permutations/06_inverse/int/0001_given_permutations_in_param/stdout.expected index da9c2d6b8a..5d33b20ade 100644 --- a/tests/custom/permutations/06_inverse/int/0001_given_permutations_in_param/stdout.expected +++ b/tests/custom/permutations/06_inverse/int/0001_given_permutations_in_param/stdout.expected @@ -1,7 +1,7 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime permutation.param +Savile Row: conjure-output/model000001.eprime permutation.param Running minion for domain filtering. Running solver: minion Copying solution to: permutation-permutation.solution diff --git a/tests/custom/permutations/06_inverse/int/0002_given_permutations_in_param/stdout.expected b/tests/custom/permutations/06_inverse/int/0002_given_permutations_in_param/stdout.expected index da9c2d6b8a..5d33b20ade 100644 --- a/tests/custom/permutations/06_inverse/int/0002_given_permutations_in_param/stdout.expected +++ b/tests/custom/permutations/06_inverse/int/0002_given_permutations_in_param/stdout.expected @@ -1,7 +1,7 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime permutation.param +Savile Row: conjure-output/model000001.eprime permutation.param Running minion for domain filtering. Running solver: minion Copying solution to: permutation-permutation.solution diff --git a/tests/custom/permutations/06_inverse/int/0003_given_equal_letting/stdout.expected b/tests/custom/permutations/06_inverse/int/0003_given_equal_letting/stdout.expected index da9c2d6b8a..5d33b20ade 100644 --- a/tests/custom/permutations/06_inverse/int/0003_given_equal_letting/stdout.expected +++ b/tests/custom/permutations/06_inverse/int/0003_given_equal_letting/stdout.expected @@ -1,7 +1,7 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime permutation.param +Savile Row: conjure-output/model000001.eprime permutation.param Running minion for domain filtering. Running solver: minion Copying solution to: permutation-permutation.solution diff --git a/tests/custom/permutations/06_inverse/int/0004_letting_equal_given/stdout.expected b/tests/custom/permutations/06_inverse/int/0004_letting_equal_given/stdout.expected index 509db792c4..2cdb038740 100644 --- a/tests/custom/permutations/06_inverse/int/0004_letting_equal_given/stdout.expected +++ b/tests/custom/permutations/06_inverse/int/0004_letting_equal_given/stdout.expected @@ -1,10 +1,10 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime permutation.param +Savile Row: conjure-output/model000001.eprime permutation.param Running minion for domain filtering. Running solver: minion -Savile Row: model000001.eprime permutation2.param +Savile Row: conjure-output/model000001.eprime permutation2.param Running minion for domain filtering. Running solver: minion Copying solution to: permutation-permutation.solution diff --git a/tests/custom/permutations/06_inverse/int/0005_find_eq_find/stdout.expected b/tests/custom/permutations/06_inverse/int/0005_find_eq_find/stdout.expected index c58698e36d..459cd0fbac 100644 --- a/tests/custom/permutations/06_inverse/int/0005_find_eq_find/stdout.expected +++ b/tests/custom/permutations/06_inverse/int/0005_find_eq_find/stdout.expected @@ -1,7 +1,7 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime +Savile Row: conjure-output/model000001.eprime Running minion for domain filtering. Running solver: minion Copying solution to: permutation-000001.solution diff --git a/tests/custom/permutations/06_inverse/unnamed/0005_find_inverse_find/stdout.expected b/tests/custom/permutations/06_inverse/unnamed/0005_find_inverse_find/stdout.expected index de9cceb95e..21dd53a5f7 100644 --- a/tests/custom/permutations/06_inverse/unnamed/0005_find_inverse_find/stdout.expected +++ b/tests/custom/permutations/06_inverse/unnamed/0005_find_inverse_find/stdout.expected @@ -1,7 +1,7 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime +Savile Row: conjure-output/model000001.eprime Running minion for domain filtering. Running solver: minion Copying solution to: permutation-000001.solution diff --git a/tests/custom/permutations/07_compose/enum/0001_given_permutations_in_param/stdout.expected b/tests/custom/permutations/07_compose/enum/0001_given_permutations_in_param/stdout.expected index 0cba00099a..ad5d41c795 100644 --- a/tests/custom/permutations/07_compose/enum/0001_given_permutations_in_param/stdout.expected +++ b/tests/custom/permutations/07_compose/enum/0001_given_permutations_in_param/stdout.expected @@ -1,13 +1,13 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime permutation2.essence +Savile Row: conjure-output/model000001.eprime permutation2.essence Running minion for domain filtering. Running solver: minion -Savile Row: model000001.eprime permutation3.essence +Savile Row: conjure-output/model000001.eprime permutation3.essence Running minion for domain filtering. Running solver: minion -Savile Row: model000001.eprime permutation.param +Savile Row: conjure-output/model000001.eprime permutation.param Running minion for domain filtering. Running solver: minion Copying solution to: permutation-permutation.solution diff --git a/tests/custom/permutations/07_compose/enum/0002_given_and_letting/stdout.expected b/tests/custom/permutations/07_compose/enum/0002_given_and_letting/stdout.expected index 8a78c0058b..0181f4d9cb 100644 --- a/tests/custom/permutations/07_compose/enum/0002_given_and_letting/stdout.expected +++ b/tests/custom/permutations/07_compose/enum/0002_given_and_letting/stdout.expected @@ -1,7 +1,7 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime permutation.param +Savile Row: conjure-output/model000001.eprime permutation.param Running minion for domain filtering. Running solver: minion Copying solution to: permutation-permutation.solution diff --git a/tests/custom/permutations/07_compose/enum/0003_letting_and_find/stdout.expected b/tests/custom/permutations/07_compose/enum/0003_letting_and_find/stdout.expected index b911917b76..5ca67ac18b 100644 --- a/tests/custom/permutations/07_compose/enum/0003_letting_and_find/stdout.expected +++ b/tests/custom/permutations/07_compose/enum/0003_letting_and_find/stdout.expected @@ -1,10 +1,10 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime permutation.param +Savile Row: conjure-output/model000001.eprime permutation.param Running minion for domain filtering. Running solver: minion -Savile Row: model000001.eprime permutation2.param +Savile Row: conjure-output/model000001.eprime permutation2.param Running minion for domain filtering. Running solver: minion Copying solution to: permutation-permutation.solution diff --git a/tests/custom/permutations/07_compose/enum/0004_find_and_find/stdout.expected b/tests/custom/permutations/07_compose/enum/0004_find_and_find/stdout.expected index 37a8ddc8d1..251725bdca 100644 --- a/tests/custom/permutations/07_compose/enum/0004_find_and_find/stdout.expected +++ b/tests/custom/permutations/07_compose/enum/0004_find_and_find/stdout.expected @@ -1,7 +1,7 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime permutation.param +Savile Row: conjure-output/model000001.eprime permutation.param Running minion for domain filtering. Running solver: minion Copying solution to: permutation-permutation-000001.solution diff --git a/tests/custom/permutations/07_compose/int/0001_given_permutations_in_param/stdout.expected b/tests/custom/permutations/07_compose/int/0001_given_permutations_in_param/stdout.expected index 0cba00099a..ad5d41c795 100644 --- a/tests/custom/permutations/07_compose/int/0001_given_permutations_in_param/stdout.expected +++ b/tests/custom/permutations/07_compose/int/0001_given_permutations_in_param/stdout.expected @@ -1,13 +1,13 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime permutation2.essence +Savile Row: conjure-output/model000001.eprime permutation2.essence Running minion for domain filtering. Running solver: minion -Savile Row: model000001.eprime permutation3.essence +Savile Row: conjure-output/model000001.eprime permutation3.essence Running minion for domain filtering. Running solver: minion -Savile Row: model000001.eprime permutation.param +Savile Row: conjure-output/model000001.eprime permutation.param Running minion for domain filtering. Running solver: minion Copying solution to: permutation-permutation.solution diff --git a/tests/custom/permutations/07_compose/int/0002_given_and_letting/stdout.expected b/tests/custom/permutations/07_compose/int/0002_given_and_letting/stdout.expected index 8a78c0058b..0181f4d9cb 100644 --- a/tests/custom/permutations/07_compose/int/0002_given_and_letting/stdout.expected +++ b/tests/custom/permutations/07_compose/int/0002_given_and_letting/stdout.expected @@ -1,7 +1,7 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime permutation.param +Savile Row: conjure-output/model000001.eprime permutation.param Running minion for domain filtering. Running solver: minion Copying solution to: permutation-permutation.solution diff --git a/tests/custom/permutations/07_compose/int/0002_letting_and_given/stdout.expected b/tests/custom/permutations/07_compose/int/0002_letting_and_given/stdout.expected index da9c2d6b8a..5d33b20ade 100644 --- a/tests/custom/permutations/07_compose/int/0002_letting_and_given/stdout.expected +++ b/tests/custom/permutations/07_compose/int/0002_letting_and_given/stdout.expected @@ -1,7 +1,7 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime permutation.param +Savile Row: conjure-output/model000001.eprime permutation.param Running minion for domain filtering. Running solver: minion Copying solution to: permutation-permutation.solution diff --git a/tests/custom/permutations/07_compose/int/0003_letting_and_find/stdout.expected b/tests/custom/permutations/07_compose/int/0003_letting_and_find/stdout.expected index 68b324a340..c4a21b4527 100644 --- a/tests/custom/permutations/07_compose/int/0003_letting_and_find/stdout.expected +++ b/tests/custom/permutations/07_compose/int/0003_letting_and_find/stdout.expected @@ -1,10 +1,10 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime permutation.param +Savile Row: conjure-output/model000001.eprime permutation.param Running minion for domain filtering. Running solver: minion -Savile Row: model000001.eprime permutation2.param +Savile Row: conjure-output/model000001.eprime permutation2.param Running minion for domain filtering. Running solver: minion Copying solution to: permutation-permutation.solution diff --git a/tests/custom/permutations/07_compose/int/0004_find_and_find/stdout.expected b/tests/custom/permutations/07_compose/int/0004_find_and_find/stdout.expected index 63e01673f7..90c05603e5 100644 --- a/tests/custom/permutations/07_compose/int/0004_find_and_find/stdout.expected +++ b/tests/custom/permutations/07_compose/int/0004_find_and_find/stdout.expected @@ -1,7 +1,7 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime permutation.param +Savile Row: conjure-output/model000001.eprime permutation.param Running minion for domain filtering. Running solver: minion Copying solution to: permutation-permutation-000001.solution diff --git a/tests/custom/permutations/07_compose/int/0005_find_composition/stdout.expected b/tests/custom/permutations/07_compose/int/0005_find_composition/stdout.expected index 4af103b583..e5ff156c70 100644 --- a/tests/custom/permutations/07_compose/int/0005_find_composition/stdout.expected +++ b/tests/custom/permutations/07_compose/int/0005_find_composition/stdout.expected @@ -1,7 +1,7 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime +Savile Row: conjure-output/model000001.eprime Running minion for domain filtering. Running solver: minion Copying solution to: permutation-000001.solution diff --git a/tests/custom/permutations/07_compose/int/0006_find_composition/stdout.expected b/tests/custom/permutations/07_compose/int/0006_find_composition/stdout.expected index 16606b00a4..2cf09f233b 100644 --- a/tests/custom/permutations/07_compose/int/0006_find_composition/stdout.expected +++ b/tests/custom/permutations/07_compose/int/0006_find_composition/stdout.expected @@ -1,7 +1,7 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime +Savile Row: conjure-output/model000001.eprime Running minion for domain filtering. Running solver: minion Copying solution to: permutation-000001.solution diff --git a/tests/custom/permutations/07_compose/unnamed/0004_find_and_find/stdout.expected b/tests/custom/permutations/07_compose/unnamed/0004_find_and_find/stdout.expected index 8c12f73901..c3581f84ae 100644 --- a/tests/custom/permutations/07_compose/unnamed/0004_find_and_find/stdout.expected +++ b/tests/custom/permutations/07_compose/unnamed/0004_find_and_find/stdout.expected @@ -1,7 +1,7 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime +Savile Row: conjure-output/model000001.eprime Running minion for domain filtering. Running solver: minion Copying solution to: permutation-000001.solution diff --git a/tests/custom/permutations/08_transform_set/enum/0001_given_permutation_letting_set/stdout.expected b/tests/custom/permutations/08_transform_set/enum/0001_given_permutation_letting_set/stdout.expected index 7f6a2f48ee..acb3b88bfa 100644 --- a/tests/custom/permutations/08_transform_set/enum/0001_given_permutation_letting_set/stdout.expected +++ b/tests/custom/permutations/08_transform_set/enum/0001_given_permutation_letting_set/stdout.expected @@ -1,7 +1,7 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime permutation.param +Savile Row: conjure-output/model000001.eprime permutation.param Running minion for domain filtering. Running solver: minion Copying solution to: permutation-permutation.solution diff --git a/tests/custom/permutations/08_transform_set/enum/0002_given_permutation_find_sets/stdout.expected b/tests/custom/permutations/08_transform_set/enum/0002_given_permutation_find_sets/stdout.expected index a7f4317f04..7fcc373b2c 100644 --- a/tests/custom/permutations/08_transform_set/enum/0002_given_permutation_find_sets/stdout.expected +++ b/tests/custom/permutations/08_transform_set/enum/0002_given_permutation_find_sets/stdout.expected @@ -1,7 +1,7 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime permutation.param +Savile Row: conjure-output/model000001.eprime permutation.param Running minion for domain filtering. Running solver: minion Copying solution to: permutation-permutation-000001.solution diff --git a/tests/custom/permutations/08_transform_set/enum/0003_letting_permutation_find_sets/stdout.expected b/tests/custom/permutations/08_transform_set/enum/0003_letting_permutation_find_sets/stdout.expected index 2005a71b93..5adbca41d7 100644 --- a/tests/custom/permutations/08_transform_set/enum/0003_letting_permutation_find_sets/stdout.expected +++ b/tests/custom/permutations/08_transform_set/enum/0003_letting_permutation_find_sets/stdout.expected @@ -1,7 +1,7 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime +Savile Row: conjure-output/model000001.eprime Running minion for domain filtering. Running solver: minion Copying solution to: permutation-000001.solution diff --git a/tests/custom/permutations/08_transform_set/enum/0004_find_permutation_find_sets/stdout.expected b/tests/custom/permutations/08_transform_set/enum/0004_find_permutation_find_sets/stdout.expected index 5923ac139d..de22c39c03 100644 --- a/tests/custom/permutations/08_transform_set/enum/0004_find_permutation_find_sets/stdout.expected +++ b/tests/custom/permutations/08_transform_set/enum/0004_find_permutation_find_sets/stdout.expected @@ -1,7 +1,7 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime +Savile Row: conjure-output/model000001.eprime Running minion for domain filtering. Running solver: minion Copying solution to: permutation-000001.solution diff --git a/tests/custom/permutations/08_transform_set/enum/0005_find_permutation_given_set_find_set/stdout.expected b/tests/custom/permutations/08_transform_set/enum/0005_find_permutation_given_set_find_set/stdout.expected index d7aefd2589..82396195a1 100644 --- a/tests/custom/permutations/08_transform_set/enum/0005_find_permutation_given_set_find_set/stdout.expected +++ b/tests/custom/permutations/08_transform_set/enum/0005_find_permutation_given_set_find_set/stdout.expected @@ -1,7 +1,7 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime permutation.param +Savile Row: conjure-output/model000001.eprime permutation.param Running minion for domain filtering. Running solver: minion Copying solution to: permutation-permutation-000001.solution diff --git a/tests/custom/permutations/08_transform_set/int/0001_given_permutation_letting_set/stdout.expected b/tests/custom/permutations/08_transform_set/int/0001_given_permutation_letting_set/stdout.expected index faac5ab4a1..8d42d87184 100644 --- a/tests/custom/permutations/08_transform_set/int/0001_given_permutation_letting_set/stdout.expected +++ b/tests/custom/permutations/08_transform_set/int/0001_given_permutation_letting_set/stdout.expected @@ -1,7 +1,7 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime permutation.param +Savile Row: conjure-output/model000001.eprime permutation.param Running minion for domain filtering. Running solver: minion Copying solution to: permutation-permutation.solution diff --git a/tests/custom/permutations/08_transform_set/int/0002_given_permutation_find_sets/stdout.expected b/tests/custom/permutations/08_transform_set/int/0002_given_permutation_find_sets/stdout.expected index ed0335f3bd..b786b6d17a 100644 --- a/tests/custom/permutations/08_transform_set/int/0002_given_permutation_find_sets/stdout.expected +++ b/tests/custom/permutations/08_transform_set/int/0002_given_permutation_find_sets/stdout.expected @@ -1,7 +1,7 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime permutation.param +Savile Row: conjure-output/model000001.eprime permutation.param Running minion for domain filtering. Running solver: minion Copying solution to: permutation-permutation-000001.solution diff --git a/tests/custom/permutations/08_transform_set/int/0003_letting_permutation_find_sets/stdout.expected b/tests/custom/permutations/08_transform_set/int/0003_letting_permutation_find_sets/stdout.expected index 855a415b46..05ee285ebe 100644 --- a/tests/custom/permutations/08_transform_set/int/0003_letting_permutation_find_sets/stdout.expected +++ b/tests/custom/permutations/08_transform_set/int/0003_letting_permutation_find_sets/stdout.expected @@ -1,7 +1,7 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime +Savile Row: conjure-output/model000001.eprime Running minion for domain filtering. Running solver: minion Copying solution to: permutation-000001.solution diff --git a/tests/custom/permutations/08_transform_set/int/0004_find_permutation_find_sets/stdout.expected b/tests/custom/permutations/08_transform_set/int/0004_find_permutation_find_sets/stdout.expected index 2ff7ab2c06..4c3c3b7481 100644 --- a/tests/custom/permutations/08_transform_set/int/0004_find_permutation_find_sets/stdout.expected +++ b/tests/custom/permutations/08_transform_set/int/0004_find_permutation_find_sets/stdout.expected @@ -1,7 +1,7 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime +Savile Row: conjure-output/model000001.eprime Running minion for domain filtering. Running solver: minion Copying solution to: permutation-000001.solution diff --git a/tests/custom/permutations/08_transform_set/int/0005_find_permutation_given_set_find_set/stdout.expected b/tests/custom/permutations/08_transform_set/int/0005_find_permutation_given_set_find_set/stdout.expected index a43fe606e4..0173a6ccbe 100644 --- a/tests/custom/permutations/08_transform_set/int/0005_find_permutation_given_set_find_set/stdout.expected +++ b/tests/custom/permutations/08_transform_set/int/0005_find_permutation_given_set_find_set/stdout.expected @@ -1,7 +1,7 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime permutation.param +Savile Row: conjure-output/model000001.eprime permutation.param Running minion for domain filtering. Running solver: minion Copying solution to: permutation-permutation-000001.solution diff --git a/tests/custom/permutations/08_transform_set/unnamed/0004_find_permutation_find_sets/stdout.expected b/tests/custom/permutations/08_transform_set/unnamed/0004_find_permutation_find_sets/stdout.expected index 22c85d8fee..b4dafff8f4 100644 --- a/tests/custom/permutations/08_transform_set/unnamed/0004_find_permutation_find_sets/stdout.expected +++ b/tests/custom/permutations/08_transform_set/unnamed/0004_find_permutation_find_sets/stdout.expected @@ -1,7 +1,7 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime +Savile Row: conjure-output/model000001.eprime Running minion for domain filtering. Running solver: minion Copying solution to: permutation-000001.solution diff --git a/tests/custom/permutations/09_defined/enum/0001_letting_permutation/stdout.expected b/tests/custom/permutations/09_defined/enum/0001_letting_permutation/stdout.expected index 8a78c0058b..0181f4d9cb 100644 --- a/tests/custom/permutations/09_defined/enum/0001_letting_permutation/stdout.expected +++ b/tests/custom/permutations/09_defined/enum/0001_letting_permutation/stdout.expected @@ -1,7 +1,7 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime permutation.param +Savile Row: conjure-output/model000001.eprime permutation.param Running minion for domain filtering. Running solver: minion Copying solution to: permutation-permutation.solution diff --git a/tests/custom/permutations/09_defined/enum/0002_letting_permutation/stdout.expected b/tests/custom/permutations/09_defined/enum/0002_letting_permutation/stdout.expected index da9c2d6b8a..5d33b20ade 100644 --- a/tests/custom/permutations/09_defined/enum/0002_letting_permutation/stdout.expected +++ b/tests/custom/permutations/09_defined/enum/0002_letting_permutation/stdout.expected @@ -1,7 +1,7 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime permutation.param +Savile Row: conjure-output/model000001.eprime permutation.param Running minion for domain filtering. Running solver: minion Copying solution to: permutation-permutation.solution diff --git a/tests/custom/permutations/09_defined/enum/0003_given_permutation/stdout.expected b/tests/custom/permutations/09_defined/enum/0003_given_permutation/stdout.expected index 8a78c0058b..0181f4d9cb 100644 --- a/tests/custom/permutations/09_defined/enum/0003_given_permutation/stdout.expected +++ b/tests/custom/permutations/09_defined/enum/0003_given_permutation/stdout.expected @@ -1,7 +1,7 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime permutation.param +Savile Row: conjure-output/model000001.eprime permutation.param Running minion for domain filtering. Running solver: minion Copying solution to: permutation-permutation.solution diff --git a/tests/custom/permutations/09_defined/enum/0004_given_permutation/stdout.expected b/tests/custom/permutations/09_defined/enum/0004_given_permutation/stdout.expected index 01505e3c4c..42bb888e01 100644 --- a/tests/custom/permutations/09_defined/enum/0004_given_permutation/stdout.expected +++ b/tests/custom/permutations/09_defined/enum/0004_given_permutation/stdout.expected @@ -1,7 +1,7 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime permutation.param +Savile Row: conjure-output/model000001.eprime permutation.param Running minion for domain filtering. Running solver: minion Copying solution to: permutation-permutation.solution diff --git a/tests/custom/permutations/09_defined/enum/0005_find_permutation/stdout.expected b/tests/custom/permutations/09_defined/enum/0005_find_permutation/stdout.expected index e0c1eb1477..4b87476207 100644 --- a/tests/custom/permutations/09_defined/enum/0005_find_permutation/stdout.expected +++ b/tests/custom/permutations/09_defined/enum/0005_find_permutation/stdout.expected @@ -1,7 +1,7 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime +Savile Row: conjure-output/model000001.eprime Running minion for domain filtering. Running solver: minion Copying solution to: permutation.solution diff --git a/tests/custom/permutations/09_defined/int/0001_letting_permutation/stdout.expected b/tests/custom/permutations/09_defined/int/0001_letting_permutation/stdout.expected index 8a78c0058b..0181f4d9cb 100644 --- a/tests/custom/permutations/09_defined/int/0001_letting_permutation/stdout.expected +++ b/tests/custom/permutations/09_defined/int/0001_letting_permutation/stdout.expected @@ -1,7 +1,7 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime permutation.param +Savile Row: conjure-output/model000001.eprime permutation.param Running minion for domain filtering. Running solver: minion Copying solution to: permutation-permutation.solution diff --git a/tests/custom/permutations/09_defined/int/0002_letting_permutation/stdout.expected b/tests/custom/permutations/09_defined/int/0002_letting_permutation/stdout.expected index da9c2d6b8a..5d33b20ade 100644 --- a/tests/custom/permutations/09_defined/int/0002_letting_permutation/stdout.expected +++ b/tests/custom/permutations/09_defined/int/0002_letting_permutation/stdout.expected @@ -1,7 +1,7 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime permutation.param +Savile Row: conjure-output/model000001.eprime permutation.param Running minion for domain filtering. Running solver: minion Copying solution to: permutation-permutation.solution diff --git a/tests/custom/permutations/09_defined/int/0003_given_permutation/stdout.expected b/tests/custom/permutations/09_defined/int/0003_given_permutation/stdout.expected index 8a78c0058b..0181f4d9cb 100644 --- a/tests/custom/permutations/09_defined/int/0003_given_permutation/stdout.expected +++ b/tests/custom/permutations/09_defined/int/0003_given_permutation/stdout.expected @@ -1,7 +1,7 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime permutation.param +Savile Row: conjure-output/model000001.eprime permutation.param Running minion for domain filtering. Running solver: minion Copying solution to: permutation-permutation.solution diff --git a/tests/custom/permutations/09_defined/int/0004_given_permutation/stdout.expected b/tests/custom/permutations/09_defined/int/0004_given_permutation/stdout.expected index 5b87dbb8c8..04a0d05236 100644 --- a/tests/custom/permutations/09_defined/int/0004_given_permutation/stdout.expected +++ b/tests/custom/permutations/09_defined/int/0004_given_permutation/stdout.expected @@ -1,7 +1,7 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime permutation.param +Savile Row: conjure-output/model000001.eprime permutation.param Running minion for domain filtering. Running solver: minion Copying solution to: permutation-permutation.solution diff --git a/tests/custom/permutations/09_defined/int/0005_find_permutation/stdout.expected b/tests/custom/permutations/09_defined/int/0005_find_permutation/stdout.expected index 0650091188..82c3775425 100644 --- a/tests/custom/permutations/09_defined/int/0005_find_permutation/stdout.expected +++ b/tests/custom/permutations/09_defined/int/0005_find_permutation/stdout.expected @@ -1,7 +1,7 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime +Savile Row: conjure-output/model000001.eprime Running minion for domain filtering. Running solver: minion Copying solution to: permutation.solution diff --git a/tests/custom/permutations/09_defined/unnamed/0005_find_permutation/stdout.expected b/tests/custom/permutations/09_defined/unnamed/0005_find_permutation/stdout.expected index a03d43f7e0..baa9b67164 100644 --- a/tests/custom/permutations/09_defined/unnamed/0005_find_permutation/stdout.expected +++ b/tests/custom/permutations/09_defined/unnamed/0005_find_permutation/stdout.expected @@ -1,7 +1,7 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime +Savile Row: conjure-output/model000001.eprime Running minion for domain filtering. Running solver: minion Copying solution to: permutation.solution diff --git a/tests/custom/permutations/10_transform_tuple/enum/0001_letting_permutation_given_tuple_find_tuple/stdout.expected b/tests/custom/permutations/10_transform_tuple/enum/0001_letting_permutation_given_tuple_find_tuple/stdout.expected index 119078ab0f..896ed1e011 100644 --- a/tests/custom/permutations/10_transform_tuple/enum/0001_letting_permutation_given_tuple_find_tuple/stdout.expected +++ b/tests/custom/permutations/10_transform_tuple/enum/0001_letting_permutation_given_tuple_find_tuple/stdout.expected @@ -1,7 +1,7 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime permutation.param +Savile Row: conjure-output/model000001.eprime permutation.param Running minion for domain filtering. Running solver: minion Copying solution to: permutation-permutation.solution diff --git a/tests/custom/permutations/10_transform_tuple/enum/0002_letting_permutation_given_tuple_find_tuple/stdout.expected b/tests/custom/permutations/10_transform_tuple/enum/0002_letting_permutation_given_tuple_find_tuple/stdout.expected index 0c60bd23b1..e0b9567874 100644 --- a/tests/custom/permutations/10_transform_tuple/enum/0002_letting_permutation_given_tuple_find_tuple/stdout.expected +++ b/tests/custom/permutations/10_transform_tuple/enum/0002_letting_permutation_given_tuple_find_tuple/stdout.expected @@ -1,7 +1,7 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime permutation.param +Savile Row: conjure-output/model000001.eprime permutation.param Running minion for domain filtering. Running solver: minion Copying solution to: permutation-permutation.solution diff --git a/tests/custom/permutations/10_transform_tuple/enum/0003_given_permutation_given_tuple_find_tuple/stdout.expected b/tests/custom/permutations/10_transform_tuple/enum/0003_given_permutation_given_tuple_find_tuple/stdout.expected index 119078ab0f..896ed1e011 100644 --- a/tests/custom/permutations/10_transform_tuple/enum/0003_given_permutation_given_tuple_find_tuple/stdout.expected +++ b/tests/custom/permutations/10_transform_tuple/enum/0003_given_permutation_given_tuple_find_tuple/stdout.expected @@ -1,7 +1,7 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime permutation.param +Savile Row: conjure-output/model000001.eprime permutation.param Running minion for domain filtering. Running solver: minion Copying solution to: permutation-permutation.solution diff --git a/tests/custom/permutations/10_transform_tuple/enum/0004_given_permutation_find_tuple_find_tuple/stdout.expected b/tests/custom/permutations/10_transform_tuple/enum/0004_given_permutation_find_tuple_find_tuple/stdout.expected index fada2bec18..6f01b53364 100644 --- a/tests/custom/permutations/10_transform_tuple/enum/0004_given_permutation_find_tuple_find_tuple/stdout.expected +++ b/tests/custom/permutations/10_transform_tuple/enum/0004_given_permutation_find_tuple_find_tuple/stdout.expected @@ -1,7 +1,7 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime permutation.param +Savile Row: conjure-output/model000001.eprime permutation.param Running minion for domain filtering. Running solver: minion Copying solution to: permutation-permutation-000001.solution diff --git a/tests/custom/permutations/10_transform_tuple/enum/0005_find_permutation_find_tuple_find_tuple/stdout.expected b/tests/custom/permutations/10_transform_tuple/enum/0005_find_permutation_find_tuple_find_tuple/stdout.expected index cf25cc15d1..df7642c09b 100644 --- a/tests/custom/permutations/10_transform_tuple/enum/0005_find_permutation_find_tuple_find_tuple/stdout.expected +++ b/tests/custom/permutations/10_transform_tuple/enum/0005_find_permutation_find_tuple_find_tuple/stdout.expected @@ -1,7 +1,7 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime +Savile Row: conjure-output/model000001.eprime Running minion for domain filtering. Running solver: minion Copying solution to: permutation-000001.solution diff --git a/tests/custom/permutations/10_transform_tuple/int/0001_letting_permutation_given_tuple_find_tuple/stdout.expected b/tests/custom/permutations/10_transform_tuple/int/0001_letting_permutation_given_tuple_find_tuple/stdout.expected index e4d0d07195..095101eee7 100644 --- a/tests/custom/permutations/10_transform_tuple/int/0001_letting_permutation_given_tuple_find_tuple/stdout.expected +++ b/tests/custom/permutations/10_transform_tuple/int/0001_letting_permutation_given_tuple_find_tuple/stdout.expected @@ -1,7 +1,7 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime permutation.param +Savile Row: conjure-output/model000001.eprime permutation.param Running minion for domain filtering. Running solver: minion Copying solution to: permutation-permutation.solution diff --git a/tests/custom/permutations/10_transform_tuple/int/0002_letting_permutation_given_tuple_find_tuple/stdout.expected b/tests/custom/permutations/10_transform_tuple/int/0002_letting_permutation_given_tuple_find_tuple/stdout.expected index 8acee4491e..f44285827b 100644 --- a/tests/custom/permutations/10_transform_tuple/int/0002_letting_permutation_given_tuple_find_tuple/stdout.expected +++ b/tests/custom/permutations/10_transform_tuple/int/0002_letting_permutation_given_tuple_find_tuple/stdout.expected @@ -1,7 +1,7 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime permutation.param +Savile Row: conjure-output/model000001.eprime permutation.param Running minion for domain filtering. Running solver: minion Copying solution to: permutation-permutation.solution diff --git a/tests/custom/permutations/10_transform_tuple/int/0003_given_permutation_given_tuple_find_tuple/stdout.expected b/tests/custom/permutations/10_transform_tuple/int/0003_given_permutation_given_tuple_find_tuple/stdout.expected index e4d0d07195..095101eee7 100644 --- a/tests/custom/permutations/10_transform_tuple/int/0003_given_permutation_given_tuple_find_tuple/stdout.expected +++ b/tests/custom/permutations/10_transform_tuple/int/0003_given_permutation_given_tuple_find_tuple/stdout.expected @@ -1,7 +1,7 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime permutation.param +Savile Row: conjure-output/model000001.eprime permutation.param Running minion for domain filtering. Running solver: minion Copying solution to: permutation-permutation.solution diff --git a/tests/custom/permutations/10_transform_tuple/int/0004_given_permutation_find_tuple_find_tuple/stdout.expected b/tests/custom/permutations/10_transform_tuple/int/0004_given_permutation_find_tuple_find_tuple/stdout.expected index 343b8187b5..2d1caffb4c 100644 --- a/tests/custom/permutations/10_transform_tuple/int/0004_given_permutation_find_tuple_find_tuple/stdout.expected +++ b/tests/custom/permutations/10_transform_tuple/int/0004_given_permutation_find_tuple_find_tuple/stdout.expected @@ -1,7 +1,7 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime permutation.param +Savile Row: conjure-output/model000001.eprime permutation.param Running minion for domain filtering. Running solver: minion Copying solution to: permutation-permutation-000001.solution diff --git a/tests/custom/permutations/10_transform_tuple/int/0005_find_permutation_find_tuple_find_tuple/stdout.expected b/tests/custom/permutations/10_transform_tuple/int/0005_find_permutation_find_tuple_find_tuple/stdout.expected index 98113abbf7..49046f7eec 100644 --- a/tests/custom/permutations/10_transform_tuple/int/0005_find_permutation_find_tuple_find_tuple/stdout.expected +++ b/tests/custom/permutations/10_transform_tuple/int/0005_find_permutation_find_tuple_find_tuple/stdout.expected @@ -1,7 +1,7 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime +Savile Row: conjure-output/model000001.eprime Running minion for domain filtering. Running solver: minion Copying solution to: permutation-000001.solution diff --git a/tests/custom/permutations/10_transform_tuple/unnamed/0005_find_permutation_find_tuple_find_tuple/stdout.expected b/tests/custom/permutations/10_transform_tuple/unnamed/0005_find_permutation_find_tuple_find_tuple/stdout.expected index 1548177d90..af41c366dc 100644 --- a/tests/custom/permutations/10_transform_tuple/unnamed/0005_find_permutation_find_tuple_find_tuple/stdout.expected +++ b/tests/custom/permutations/10_transform_tuple/unnamed/0005_find_permutation_find_tuple_find_tuple/stdout.expected @@ -1,7 +1,7 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime +Savile Row: conjure-output/model000001.eprime Running minion for domain filtering. Running solver: minion Copying solution to: permutation-000001.solution diff --git a/tests/custom/permutations/11_transform_relation/enum/0010_given_permutation_letting_relation/stdout.expected b/tests/custom/permutations/11_transform_relation/enum/0010_given_permutation_letting_relation/stdout.expected index b53a3621a3..c75ac9c381 100644 --- a/tests/custom/permutations/11_transform_relation/enum/0010_given_permutation_letting_relation/stdout.expected +++ b/tests/custom/permutations/11_transform_relation/enum/0010_given_permutation_letting_relation/stdout.expected @@ -1,7 +1,7 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime permutation.param +Savile Row: conjure-output/model000001.eprime permutation.param Running minion for domain filtering. Running solver: minion Copying solution to: permutation-permutation.solution diff --git a/tests/custom/permutations/11_transform_relation/enum/0020_letting_permutation_letting_relation/stdout.expected b/tests/custom/permutations/11_transform_relation/enum/0020_letting_permutation_letting_relation/stdout.expected index b53a3621a3..c75ac9c381 100644 --- a/tests/custom/permutations/11_transform_relation/enum/0020_letting_permutation_letting_relation/stdout.expected +++ b/tests/custom/permutations/11_transform_relation/enum/0020_letting_permutation_letting_relation/stdout.expected @@ -1,7 +1,7 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime permutation.param +Savile Row: conjure-output/model000001.eprime permutation.param Running minion for domain filtering. Running solver: minion Copying solution to: permutation-permutation.solution diff --git a/tests/custom/permutations/11_transform_relation/enum/0030_find_permutation_given_relation/stdout.expected b/tests/custom/permutations/11_transform_relation/enum/0030_find_permutation_given_relation/stdout.expected index fcf16cbaba..37c158bf48 100644 --- a/tests/custom/permutations/11_transform_relation/enum/0030_find_permutation_given_relation/stdout.expected +++ b/tests/custom/permutations/11_transform_relation/enum/0030_find_permutation_given_relation/stdout.expected @@ -1,7 +1,7 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime permutation.param +Savile Row: conjure-output/model000001.eprime permutation.param Running minion for domain filtering. Running solver: minion Copying solution to: permutation-permutation.solution diff --git a/tests/custom/permutations/11_transform_relation/enum/0040_find_permutation_find_relation/stdout.expected b/tests/custom/permutations/11_transform_relation/enum/0040_find_permutation_find_relation/stdout.expected index 624839f190..5dba29bd33 100644 --- a/tests/custom/permutations/11_transform_relation/enum/0040_find_permutation_find_relation/stdout.expected +++ b/tests/custom/permutations/11_transform_relation/enum/0040_find_permutation_find_relation/stdout.expected @@ -1,7 +1,7 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime +Savile Row: conjure-output/model000001.eprime Running minion for domain filtering. Running solver: minion Copying solution to: permutation.solution diff --git a/tests/custom/permutations/11_transform_relation/int/0010_given_permutation_letting_relation/stdout.expected b/tests/custom/permutations/11_transform_relation/int/0010_given_permutation_letting_relation/stdout.expected index 7f5c20f6ae..8a311cb070 100644 --- a/tests/custom/permutations/11_transform_relation/int/0010_given_permutation_letting_relation/stdout.expected +++ b/tests/custom/permutations/11_transform_relation/int/0010_given_permutation_letting_relation/stdout.expected @@ -1,7 +1,7 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime permutation.param +Savile Row: conjure-output/model000001.eprime permutation.param Running minion for domain filtering. Running solver: minion Copying solution to: permutation-permutation.solution diff --git a/tests/custom/permutations/11_transform_relation/int/0020_letting_permutation_letting_relation/stdout.expected b/tests/custom/permutations/11_transform_relation/int/0020_letting_permutation_letting_relation/stdout.expected index 7f5c20f6ae..8a311cb070 100644 --- a/tests/custom/permutations/11_transform_relation/int/0020_letting_permutation_letting_relation/stdout.expected +++ b/tests/custom/permutations/11_transform_relation/int/0020_letting_permutation_letting_relation/stdout.expected @@ -1,7 +1,7 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime permutation.param +Savile Row: conjure-output/model000001.eprime permutation.param Running minion for domain filtering. Running solver: minion Copying solution to: permutation-permutation.solution diff --git a/tests/custom/permutations/11_transform_relation/int/0030_find_permutation_given_relation/stdout.expected b/tests/custom/permutations/11_transform_relation/int/0030_find_permutation_given_relation/stdout.expected index 4c5045b4f4..8f8720d197 100644 --- a/tests/custom/permutations/11_transform_relation/int/0030_find_permutation_given_relation/stdout.expected +++ b/tests/custom/permutations/11_transform_relation/int/0030_find_permutation_given_relation/stdout.expected @@ -1,7 +1,7 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime permutation.param +Savile Row: conjure-output/model000001.eprime permutation.param Running minion for domain filtering. Running solver: minion Copying solution to: permutation-permutation.solution diff --git a/tests/custom/permutations/11_transform_relation/int/0040_find_permutation_find_relation/stdout.expected b/tests/custom/permutations/11_transform_relation/int/0040_find_permutation_find_relation/stdout.expected index 59214a4f3f..60735869d0 100644 --- a/tests/custom/permutations/11_transform_relation/int/0040_find_permutation_find_relation/stdout.expected +++ b/tests/custom/permutations/11_transform_relation/int/0040_find_permutation_find_relation/stdout.expected @@ -1,7 +1,7 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime +Savile Row: conjure-output/model000001.eprime Running minion for domain filtering. Running solver: minion Copying solution to: permutation.solution diff --git a/tests/custom/permutations/11_transform_relation/unnamed/0040_find_permutation_find_relation/stdout.expected b/tests/custom/permutations/11_transform_relation/unnamed/0040_find_permutation_find_relation/stdout.expected index f306f9cfe8..a90149b935 100644 --- a/tests/custom/permutations/11_transform_relation/unnamed/0040_find_permutation_find_relation/stdout.expected +++ b/tests/custom/permutations/11_transform_relation/unnamed/0040_find_permutation_find_relation/stdout.expected @@ -1,7 +1,7 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime +Savile Row: conjure-output/model000001.eprime Running minion for domain filtering. Running solver: minion Copying solution to: permutation.solution diff --git a/tests/custom/permutations/12_transform_list/enum/0010_given_permutation/stdout.expected b/tests/custom/permutations/12_transform_list/enum/0010_given_permutation/stdout.expected index 71fe3e137a..85e0c67280 100644 --- a/tests/custom/permutations/12_transform_list/enum/0010_given_permutation/stdout.expected +++ b/tests/custom/permutations/12_transform_list/enum/0010_given_permutation/stdout.expected @@ -1,7 +1,7 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime permutation.param +Savile Row: conjure-output/model000001.eprime permutation.param Running minion for domain filtering. Running solver: minion Copying solution to: permutation-permutation.solution diff --git a/tests/custom/permutations/12_transform_list/enum/0020_letting_permutation/stdout.expected b/tests/custom/permutations/12_transform_list/enum/0020_letting_permutation/stdout.expected index 53fe5f0484..2272f4ba58 100644 --- a/tests/custom/permutations/12_transform_list/enum/0020_letting_permutation/stdout.expected +++ b/tests/custom/permutations/12_transform_list/enum/0020_letting_permutation/stdout.expected @@ -1,7 +1,7 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime +Savile Row: conjure-output/model000001.eprime Running minion for domain filtering. Running solver: minion Copying solution to: permutation.solution diff --git a/tests/custom/permutations/12_transform_list/enum/0030_find_permutation/stdout.expected b/tests/custom/permutations/12_transform_list/enum/0030_find_permutation/stdout.expected index 78d5b42fe0..38c5127aaa 100644 --- a/tests/custom/permutations/12_transform_list/enum/0030_find_permutation/stdout.expected +++ b/tests/custom/permutations/12_transform_list/enum/0030_find_permutation/stdout.expected @@ -1,7 +1,7 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime +Savile Row: conjure-output/model000001.eprime Running minion for domain filtering. Running solver: minion Copying solution to: permutation.solution diff --git a/tests/custom/permutations/12_transform_list/int/0010_given_permutation/stdout.expected b/tests/custom/permutations/12_transform_list/int/0010_given_permutation/stdout.expected index 307441720d..c88096ef87 100644 --- a/tests/custom/permutations/12_transform_list/int/0010_given_permutation/stdout.expected +++ b/tests/custom/permutations/12_transform_list/int/0010_given_permutation/stdout.expected @@ -1,7 +1,7 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime permutation.param +Savile Row: conjure-output/model000001.eprime permutation.param Running minion for domain filtering. Running solver: minion Copying solution to: permutation-permutation.solution diff --git a/tests/custom/permutations/12_transform_list/int/0020_letting_permutation/stdout.expected b/tests/custom/permutations/12_transform_list/int/0020_letting_permutation/stdout.expected index b0ec1acad6..60d9812da3 100644 --- a/tests/custom/permutations/12_transform_list/int/0020_letting_permutation/stdout.expected +++ b/tests/custom/permutations/12_transform_list/int/0020_letting_permutation/stdout.expected @@ -1,7 +1,7 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime +Savile Row: conjure-output/model000001.eprime Running minion for domain filtering. Running solver: minion Copying solution to: permutation.solution diff --git a/tests/custom/permutations/12_transform_list/int/0030_find_permutation/stdout.expected b/tests/custom/permutations/12_transform_list/int/0030_find_permutation/stdout.expected index 81d6c93cb0..0693fcc44f 100644 --- a/tests/custom/permutations/12_transform_list/int/0030_find_permutation/stdout.expected +++ b/tests/custom/permutations/12_transform_list/int/0030_find_permutation/stdout.expected @@ -1,7 +1,7 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime +Savile Row: conjure-output/model000001.eprime Running minion for domain filtering. Running solver: minion Copying solution to: permutation.solution diff --git a/tests/custom/permutations/13_transform_function/enum/0010_given_permutation/stdout.expected b/tests/custom/permutations/13_transform_function/enum/0010_given_permutation/stdout.expected index 0b3df54caf..5fa9887038 100644 --- a/tests/custom/permutations/13_transform_function/enum/0010_given_permutation/stdout.expected +++ b/tests/custom/permutations/13_transform_function/enum/0010_given_permutation/stdout.expected @@ -1,7 +1,7 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime permutation.param +Savile Row: conjure-output/model000001.eprime permutation.param Running minion for domain filtering. Running solver: minion Copying solution to: permutation-permutation.solution diff --git a/tests/custom/permutations/13_transform_function/enum/0020_letting_permutation/stdout.expected b/tests/custom/permutations/13_transform_function/enum/0020_letting_permutation/stdout.expected index d107362fc0..253eba2f4d 100644 --- a/tests/custom/permutations/13_transform_function/enum/0020_letting_permutation/stdout.expected +++ b/tests/custom/permutations/13_transform_function/enum/0020_letting_permutation/stdout.expected @@ -1,7 +1,7 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime +Savile Row: conjure-output/model000001.eprime Running minion for domain filtering. Running solver: minion Copying solution to: permutation.solution diff --git a/tests/custom/permutations/13_transform_function/enum/0030_find_permutation/stdout.expected b/tests/custom/permutations/13_transform_function/enum/0030_find_permutation/stdout.expected index b71343efb7..e96593d3b6 100644 --- a/tests/custom/permutations/13_transform_function/enum/0030_find_permutation/stdout.expected +++ b/tests/custom/permutations/13_transform_function/enum/0030_find_permutation/stdout.expected @@ -1,7 +1,7 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime +Savile Row: conjure-output/model000001.eprime Running minion for domain filtering. Running solver: minion Copying solution to: permutation.solution diff --git a/tests/custom/permutations/13_transform_function/int/0010_given_permutation/stdout.expected b/tests/custom/permutations/13_transform_function/int/0010_given_permutation/stdout.expected index 7f23926d57..dd01ed0bfc 100644 --- a/tests/custom/permutations/13_transform_function/int/0010_given_permutation/stdout.expected +++ b/tests/custom/permutations/13_transform_function/int/0010_given_permutation/stdout.expected @@ -1,7 +1,7 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime permutation.param +Savile Row: conjure-output/model000001.eprime permutation.param Running minion for domain filtering. Running solver: minion Copying solution to: permutation-permutation.solution diff --git a/tests/custom/permutations/13_transform_function/int/0020_letting_permutation/stdout.expected b/tests/custom/permutations/13_transform_function/int/0020_letting_permutation/stdout.expected index a29a803f56..68fcbcc503 100644 --- a/tests/custom/permutations/13_transform_function/int/0020_letting_permutation/stdout.expected +++ b/tests/custom/permutations/13_transform_function/int/0020_letting_permutation/stdout.expected @@ -1,7 +1,7 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime +Savile Row: conjure-output/model000001.eprime Running minion for domain filtering. Running solver: minion Copying solution to: permutation.solution diff --git a/tests/custom/permutations/13_transform_function/int/0030_find_permutation/stdout.expected b/tests/custom/permutations/13_transform_function/int/0030_find_permutation/stdout.expected index 187ae23c55..b5f7041c8b 100644 --- a/tests/custom/permutations/13_transform_function/int/0030_find_permutation/stdout.expected +++ b/tests/custom/permutations/13_transform_function/int/0030_find_permutation/stdout.expected @@ -1,7 +1,7 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime +Savile Row: conjure-output/model000001.eprime Running minion for domain filtering. Running solver: minion Copying solution to: permutation.solution diff --git a/tests/custom/permutations/13_transform_function/unnamed/0030_find_permutation/stdout.expected b/tests/custom/permutations/13_transform_function/unnamed/0030_find_permutation/stdout.expected index 75a8251b11..1c87e5d8c4 100644 --- a/tests/custom/permutations/13_transform_function/unnamed/0030_find_permutation/stdout.expected +++ b/tests/custom/permutations/13_transform_function/unnamed/0030_find_permutation/stdout.expected @@ -1,7 +1,7 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime +Savile Row: conjure-output/model000001.eprime Running minion for domain filtering. Running solver: minion Copying solution to: permutation.solution diff --git a/tests/custom/permutations/14_transform_sequence/enum/0010_given_permutation/stdout.expected b/tests/custom/permutations/14_transform_sequence/enum/0010_given_permutation/stdout.expected index 89938f5e8d..47f58c4d30 100644 --- a/tests/custom/permutations/14_transform_sequence/enum/0010_given_permutation/stdout.expected +++ b/tests/custom/permutations/14_transform_sequence/enum/0010_given_permutation/stdout.expected @@ -1,7 +1,7 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime permutation.param +Savile Row: conjure-output/model000001.eprime permutation.param Running minion for domain filtering. Running solver: minion Copying solution to: permutation-permutation.solution diff --git a/tests/custom/permutations/14_transform_sequence/enum/0020_letting_permutation/stdout.expected b/tests/custom/permutations/14_transform_sequence/enum/0020_letting_permutation/stdout.expected index d9d8d82c01..2e7424dece 100644 --- a/tests/custom/permutations/14_transform_sequence/enum/0020_letting_permutation/stdout.expected +++ b/tests/custom/permutations/14_transform_sequence/enum/0020_letting_permutation/stdout.expected @@ -1,7 +1,7 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime +Savile Row: conjure-output/model000001.eprime Running minion for domain filtering. Running solver: minion Copying solution to: permutation.solution diff --git a/tests/custom/permutations/14_transform_sequence/enum/0030_find_permutation/stdout.expected b/tests/custom/permutations/14_transform_sequence/enum/0030_find_permutation/stdout.expected index 2ab14eb1b5..331661a2fe 100644 --- a/tests/custom/permutations/14_transform_sequence/enum/0030_find_permutation/stdout.expected +++ b/tests/custom/permutations/14_transform_sequence/enum/0030_find_permutation/stdout.expected @@ -1,7 +1,7 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime +Savile Row: conjure-output/model000001.eprime Running minion for domain filtering. Running solver: minion Copying solution to: permutation.solution diff --git a/tests/custom/permutations/14_transform_sequence/int/0010_given_permutation/stdout.expected b/tests/custom/permutations/14_transform_sequence/int/0010_given_permutation/stdout.expected index 15e22b1224..3f3613093d 100644 --- a/tests/custom/permutations/14_transform_sequence/int/0010_given_permutation/stdout.expected +++ b/tests/custom/permutations/14_transform_sequence/int/0010_given_permutation/stdout.expected @@ -1,7 +1,7 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime permutation.param +Savile Row: conjure-output/model000001.eprime permutation.param Running minion for domain filtering. Running solver: minion Copying solution to: permutation-permutation.solution diff --git a/tests/custom/permutations/14_transform_sequence/int/0020_letting_permutation/stdout.expected b/tests/custom/permutations/14_transform_sequence/int/0020_letting_permutation/stdout.expected index 27f4dd5561..372662c87a 100644 --- a/tests/custom/permutations/14_transform_sequence/int/0020_letting_permutation/stdout.expected +++ b/tests/custom/permutations/14_transform_sequence/int/0020_letting_permutation/stdout.expected @@ -1,7 +1,7 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime +Savile Row: conjure-output/model000001.eprime Running minion for domain filtering. Running solver: minion Copying solution to: permutation.solution diff --git a/tests/custom/permutations/14_transform_sequence/int/0030_find_permutation/stdout.expected b/tests/custom/permutations/14_transform_sequence/int/0030_find_permutation/stdout.expected index f18eb4d299..1ffbe6f1ca 100644 --- a/tests/custom/permutations/14_transform_sequence/int/0030_find_permutation/stdout.expected +++ b/tests/custom/permutations/14_transform_sequence/int/0030_find_permutation/stdout.expected @@ -1,7 +1,7 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime +Savile Row: conjure-output/model000001.eprime Running minion for domain filtering. Running solver: minion Copying solution to: permutation.solution diff --git a/tests/custom/permutations/14_transform_sequence/unnamed/0030_find_permutation/stdout.expected b/tests/custom/permutations/14_transform_sequence/unnamed/0030_find_permutation/stdout.expected index fc6c276596..6a68b83152 100644 --- a/tests/custom/permutations/14_transform_sequence/unnamed/0030_find_permutation/stdout.expected +++ b/tests/custom/permutations/14_transform_sequence/unnamed/0030_find_permutation/stdout.expected @@ -1,7 +1,7 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime +Savile Row: conjure-output/model000001.eprime Running minion for domain filtering. Running solver: minion Copying solution to: permutation.solution diff --git a/tests/custom/permutations/15_transform_mset/enum/0010_given_permutation_letting_mset/stdout.expected b/tests/custom/permutations/15_transform_mset/enum/0010_given_permutation_letting_mset/stdout.expected index c9028d85e7..2c6324dc6d 100644 --- a/tests/custom/permutations/15_transform_mset/enum/0010_given_permutation_letting_mset/stdout.expected +++ b/tests/custom/permutations/15_transform_mset/enum/0010_given_permutation_letting_mset/stdout.expected @@ -1,7 +1,7 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime permutation.param +Savile Row: conjure-output/model000001.eprime permutation.param Running minion for domain filtering. Running solver: minion Copying solution to: permutation-permutation.solution diff --git a/tests/custom/permutations/15_transform_mset/enum/0020_given_permutation_find_msets/stdout.expected b/tests/custom/permutations/15_transform_mset/enum/0020_given_permutation_find_msets/stdout.expected index 969181b0df..8a5f7b3051 100644 --- a/tests/custom/permutations/15_transform_mset/enum/0020_given_permutation_find_msets/stdout.expected +++ b/tests/custom/permutations/15_transform_mset/enum/0020_given_permutation_find_msets/stdout.expected @@ -1,7 +1,7 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime permutation.param +Savile Row: conjure-output/model000001.eprime permutation.param Running minion for domain filtering. Running solver: minion Copying solution to: permutation-permutation-000001.solution diff --git a/tests/custom/permutations/15_transform_mset/enum/0030_letting_permutation_find_msets/stdout.expected b/tests/custom/permutations/15_transform_mset/enum/0030_letting_permutation_find_msets/stdout.expected index 172f9e30e9..afb4e372f5 100644 --- a/tests/custom/permutations/15_transform_mset/enum/0030_letting_permutation_find_msets/stdout.expected +++ b/tests/custom/permutations/15_transform_mset/enum/0030_letting_permutation_find_msets/stdout.expected @@ -1,7 +1,7 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime +Savile Row: conjure-output/model000001.eprime Running minion for domain filtering. Running solver: minion Copying solution to: permutation-000001.solution diff --git a/tests/custom/permutations/15_transform_mset/enum/0040_find_permutation_find_msets/stdout.expected b/tests/custom/permutations/15_transform_mset/enum/0040_find_permutation_find_msets/stdout.expected index 888f7406b2..e9122f2cf4 100644 --- a/tests/custom/permutations/15_transform_mset/enum/0040_find_permutation_find_msets/stdout.expected +++ b/tests/custom/permutations/15_transform_mset/enum/0040_find_permutation_find_msets/stdout.expected @@ -1,7 +1,7 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime +Savile Row: conjure-output/model000001.eprime Running minion for domain filtering. Running solver: minion Copying solution to: permutation-000001.solution diff --git a/tests/custom/permutations/15_transform_mset/enum/0050_find_permutation_given_mset_find_mset/stdout.expected b/tests/custom/permutations/15_transform_mset/enum/0050_find_permutation_given_mset_find_mset/stdout.expected index 67d1d70414..c04483b0ab 100644 --- a/tests/custom/permutations/15_transform_mset/enum/0050_find_permutation_given_mset_find_mset/stdout.expected +++ b/tests/custom/permutations/15_transform_mset/enum/0050_find_permutation_given_mset_find_mset/stdout.expected @@ -1,7 +1,7 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime permutation.param +Savile Row: conjure-output/model000001.eprime permutation.param Running minion for domain filtering. Running solver: minion Copying solution to: permutation-permutation-000001.solution diff --git a/tests/custom/permutations/15_transform_mset/int/0010_given_permutation_letting_mset/stdout.expected b/tests/custom/permutations/15_transform_mset/int/0010_given_permutation_letting_mset/stdout.expected index c741d96b56..5a60cc2126 100644 --- a/tests/custom/permutations/15_transform_mset/int/0010_given_permutation_letting_mset/stdout.expected +++ b/tests/custom/permutations/15_transform_mset/int/0010_given_permutation_letting_mset/stdout.expected @@ -1,7 +1,7 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime permutation.param +Savile Row: conjure-output/model000001.eprime permutation.param Running minion for domain filtering. Running solver: minion Copying solution to: permutation-permutation.solution diff --git a/tests/custom/permutations/15_transform_mset/int/0020_given_permutation_find_msets/stdout.expected b/tests/custom/permutations/15_transform_mset/int/0020_given_permutation_find_msets/stdout.expected index 70f822e9cc..faef95859a 100644 --- a/tests/custom/permutations/15_transform_mset/int/0020_given_permutation_find_msets/stdout.expected +++ b/tests/custom/permutations/15_transform_mset/int/0020_given_permutation_find_msets/stdout.expected @@ -1,7 +1,7 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime permutation.param +Savile Row: conjure-output/model000001.eprime permutation.param Running minion for domain filtering. Running solver: minion Copying solution to: permutation-permutation-000001.solution diff --git a/tests/custom/permutations/15_transform_mset/int/0030_letting_permutation_find_msets/stdout.expected b/tests/custom/permutations/15_transform_mset/int/0030_letting_permutation_find_msets/stdout.expected index 24a82edaf3..27eff9abac 100644 --- a/tests/custom/permutations/15_transform_mset/int/0030_letting_permutation_find_msets/stdout.expected +++ b/tests/custom/permutations/15_transform_mset/int/0030_letting_permutation_find_msets/stdout.expected @@ -1,7 +1,7 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime +Savile Row: conjure-output/model000001.eprime Running minion for domain filtering. Running solver: minion Copying solution to: permutation-000001.solution diff --git a/tests/custom/permutations/15_transform_mset/int/0040_find_permutation_find_msets/stdout.expected b/tests/custom/permutations/15_transform_mset/int/0040_find_permutation_find_msets/stdout.expected index a00f1ae67d..57bf343508 100644 --- a/tests/custom/permutations/15_transform_mset/int/0040_find_permutation_find_msets/stdout.expected +++ b/tests/custom/permutations/15_transform_mset/int/0040_find_permutation_find_msets/stdout.expected @@ -1,7 +1,7 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime +Savile Row: conjure-output/model000001.eprime Running minion for domain filtering. Running solver: minion Copying solution to: permutation-000001.solution diff --git a/tests/custom/permutations/15_transform_mset/int/0050_find_permutation_given_mset_find_mset/stdout.expected b/tests/custom/permutations/15_transform_mset/int/0050_find_permutation_given_mset_find_mset/stdout.expected index 24ef48b19d..0157b69a25 100644 --- a/tests/custom/permutations/15_transform_mset/int/0050_find_permutation_given_mset_find_mset/stdout.expected +++ b/tests/custom/permutations/15_transform_mset/int/0050_find_permutation_given_mset_find_mset/stdout.expected @@ -1,7 +1,7 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime permutation.param +Savile Row: conjure-output/model000001.eprime permutation.param Running minion for domain filtering. Running solver: minion Copying solution to: permutation-permutation-000001.solution diff --git a/tests/custom/permutations/15_transform_mset/unnamed/0004_find_permutation_find_msets/stdout.expected b/tests/custom/permutations/15_transform_mset/unnamed/0004_find_permutation_find_msets/stdout.expected index f68af1bc0a..62c859abb1 100644 --- a/tests/custom/permutations/15_transform_mset/unnamed/0004_find_permutation_find_msets/stdout.expected +++ b/tests/custom/permutations/15_transform_mset/unnamed/0004_find_permutation_find_msets/stdout.expected @@ -1,7 +1,7 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime +Savile Row: conjure-output/model000001.eprime Running minion for domain filtering. Running solver: minion Copying solution to: permutation-000001.solution diff --git a/tests/custom/permutations/16_transform_permutation/enum/0010_given_permutation_letting_permutation/stdout.expected b/tests/custom/permutations/16_transform_permutation/enum/0010_given_permutation_letting_permutation/stdout.expected index f177ed54f9..f0466bdbbc 100644 --- a/tests/custom/permutations/16_transform_permutation/enum/0010_given_permutation_letting_permutation/stdout.expected +++ b/tests/custom/permutations/16_transform_permutation/enum/0010_given_permutation_letting_permutation/stdout.expected @@ -1,7 +1,7 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime permutation.param +Savile Row: conjure-output/model000001.eprime permutation.param Running minion for domain filtering. Running solver: minion Copying solution to: permutation-permutation.solution diff --git a/tests/custom/permutations/16_transform_permutation/enum/0020_given_permutation_find_permutations/stdout.expected b/tests/custom/permutations/16_transform_permutation/enum/0020_given_permutation_find_permutations/stdout.expected index a659cab5c2..1b2dfbe67b 100644 --- a/tests/custom/permutations/16_transform_permutation/enum/0020_given_permutation_find_permutations/stdout.expected +++ b/tests/custom/permutations/16_transform_permutation/enum/0020_given_permutation_find_permutations/stdout.expected @@ -1,7 +1,7 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime permutation.param +Savile Row: conjure-output/model000001.eprime permutation.param Running minion for domain filtering. Running solver: minion Copying solution to: permutation-permutation-000001.solution diff --git a/tests/custom/permutations/16_transform_permutation/enum/0030_letting_permutation_find_permutations/stdout.expected b/tests/custom/permutations/16_transform_permutation/enum/0030_letting_permutation_find_permutations/stdout.expected index c6ebb65424..c5a5c75ff2 100644 --- a/tests/custom/permutations/16_transform_permutation/enum/0030_letting_permutation_find_permutations/stdout.expected +++ b/tests/custom/permutations/16_transform_permutation/enum/0030_letting_permutation_find_permutations/stdout.expected @@ -1,7 +1,7 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime +Savile Row: conjure-output/model000001.eprime Running minion for domain filtering. Running solver: minion Copying solution to: permutation-000001.solution diff --git a/tests/custom/permutations/16_transform_permutation/enum/0040_find_permutation_find_permutations/stdout.expected b/tests/custom/permutations/16_transform_permutation/enum/0040_find_permutation_find_permutations/stdout.expected index 8d1e719bc3..8728dade60 100644 --- a/tests/custom/permutations/16_transform_permutation/enum/0040_find_permutation_find_permutations/stdout.expected +++ b/tests/custom/permutations/16_transform_permutation/enum/0040_find_permutation_find_permutations/stdout.expected @@ -1,7 +1,7 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime +Savile Row: conjure-output/model000001.eprime Running minion for domain filtering. Running solver: minion Copying solution to: permutation-000001.solution diff --git a/tests/custom/permutations/16_transform_permutation/enum/0050_find_permutation_given_permutation_find_permutation/stdout.expected b/tests/custom/permutations/16_transform_permutation/enum/0050_find_permutation_given_permutation_find_permutation/stdout.expected index bbd361990c..bbf37305e5 100644 --- a/tests/custom/permutations/16_transform_permutation/enum/0050_find_permutation_given_permutation_find_permutation/stdout.expected +++ b/tests/custom/permutations/16_transform_permutation/enum/0050_find_permutation_given_permutation_find_permutation/stdout.expected @@ -1,7 +1,7 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime permutation.param +Savile Row: conjure-output/model000001.eprime permutation.param Running minion for domain filtering. Running solver: minion Copying solution to: permutation-permutation-000001.solution diff --git a/tests/custom/permutations/16_transform_permutation/int/0010_given_permutation_letting_permutation/stdout.expected b/tests/custom/permutations/16_transform_permutation/int/0010_given_permutation_letting_permutation/stdout.expected index f2041ec176..3b4ccc4455 100644 --- a/tests/custom/permutations/16_transform_permutation/int/0010_given_permutation_letting_permutation/stdout.expected +++ b/tests/custom/permutations/16_transform_permutation/int/0010_given_permutation_letting_permutation/stdout.expected @@ -1,7 +1,7 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime permutation.param +Savile Row: conjure-output/model000001.eprime permutation.param Running minion for domain filtering. Running solver: minion Copying solution to: permutation-permutation.solution diff --git a/tests/custom/permutations/16_transform_permutation/int/0020_given_permutation_find_permutations/stdout.expected b/tests/custom/permutations/16_transform_permutation/int/0020_given_permutation_find_permutations/stdout.expected index 948e9688f8..f5572403c5 100644 --- a/tests/custom/permutations/16_transform_permutation/int/0020_given_permutation_find_permutations/stdout.expected +++ b/tests/custom/permutations/16_transform_permutation/int/0020_given_permutation_find_permutations/stdout.expected @@ -1,7 +1,7 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime permutation.param +Savile Row: conjure-output/model000001.eprime permutation.param Running minion for domain filtering. Running solver: minion Copying solution to: permutation-permutation-000001.solution diff --git a/tests/custom/permutations/16_transform_permutation/int/0030_letting_permutation_find_permutations/stdout.expected b/tests/custom/permutations/16_transform_permutation/int/0030_letting_permutation_find_permutations/stdout.expected index f5135a83c0..7ea6575697 100644 --- a/tests/custom/permutations/16_transform_permutation/int/0030_letting_permutation_find_permutations/stdout.expected +++ b/tests/custom/permutations/16_transform_permutation/int/0030_letting_permutation_find_permutations/stdout.expected @@ -1,7 +1,7 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime +Savile Row: conjure-output/model000001.eprime Running minion for domain filtering. Running solver: minion Copying solution to: permutation-000001.solution diff --git a/tests/custom/permutations/16_transform_permutation/int/0040_find_permutation_find_permutations/stdout.expected b/tests/custom/permutations/16_transform_permutation/int/0040_find_permutation_find_permutations/stdout.expected index d5fea9ade6..67e3a58221 100644 --- a/tests/custom/permutations/16_transform_permutation/int/0040_find_permutation_find_permutations/stdout.expected +++ b/tests/custom/permutations/16_transform_permutation/int/0040_find_permutation_find_permutations/stdout.expected @@ -1,7 +1,7 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime +Savile Row: conjure-output/model000001.eprime Running minion for domain filtering. Running solver: minion Copying solution to: permutation.solutions diff --git a/tests/custom/permutations/16_transform_permutation/int/0050_find_permutation_given_permutation_find_permutation/stdout.expected b/tests/custom/permutations/16_transform_permutation/int/0050_find_permutation_given_permutation_find_permutation/stdout.expected index cdd0426367..d34446dd49 100644 --- a/tests/custom/permutations/16_transform_permutation/int/0050_find_permutation_given_permutation_find_permutation/stdout.expected +++ b/tests/custom/permutations/16_transform_permutation/int/0050_find_permutation_given_permutation_find_permutation/stdout.expected @@ -1,7 +1,7 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime permutation.param +Savile Row: conjure-output/model000001.eprime permutation.param Running minion for domain filtering. Running solver: minion Copying solution to: permutation-permutation-000001.solution diff --git a/tests/custom/permutations/16_transform_permutation/unnamed/0004_find_permutation_find_permutations/stdout.expected b/tests/custom/permutations/16_transform_permutation/unnamed/0004_find_permutation_find_permutations/stdout.expected index 77f97629e9..0344633c43 100644 --- a/tests/custom/permutations/16_transform_permutation/unnamed/0004_find_permutation_find_permutations/stdout.expected +++ b/tests/custom/permutations/16_transform_permutation/unnamed/0004_find_permutation_find_permutations/stdout.expected @@ -1,7 +1,7 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime +Savile Row: conjure-output/model000001.eprime Running minion for domain filtering. Running solver: minion Copying solution to: permutation-000001.solution diff --git a/tests/custom/permutations/17_transform_partition/enum/0010_given_partition_of_enum_BUG/stdout.expected b/tests/custom/permutations/17_transform_partition/enum/0010_given_partition_of_enum_BUG/stdout.expected index 5647c94283..e06ed83776 100644 --- a/tests/custom/permutations/17_transform_partition/enum/0010_given_partition_of_enum_BUG/stdout.expected +++ b/tests/custom/permutations/17_transform_partition/enum/0010_given_partition_of_enum_BUG/stdout.expected @@ -1,7 +1,7 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime permutation.param +Savile Row: conjure-output/model000001.eprime permutation.param Running minion for domain filtering. Running solver: minion Copying solution to: permutation-permutation.solution diff --git a/tests/custom/permutations/17_transform_partition/enum/0020_find_partition_of_enum_BUG/stdout.expected b/tests/custom/permutations/17_transform_partition/enum/0020_find_partition_of_enum_BUG/stdout.expected index 6101b6ec19..7cbdbcf4bc 100644 --- a/tests/custom/permutations/17_transform_partition/enum/0020_find_partition_of_enum_BUG/stdout.expected +++ b/tests/custom/permutations/17_transform_partition/enum/0020_find_partition_of_enum_BUG/stdout.expected @@ -1,7 +1,7 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime +Savile Row: conjure-output/model000001.eprime Running minion for domain filtering. Running solver: minion Copying solution to: permutation.solution diff --git a/tests/custom/permutations/17_transform_partition/int/0010_given_permutation_partition_find_partition/stdout.expected b/tests/custom/permutations/17_transform_partition/int/0010_given_permutation_partition_find_partition/stdout.expected index 1ef30ea1bc..84d187efb7 100644 --- a/tests/custom/permutations/17_transform_partition/int/0010_given_permutation_partition_find_partition/stdout.expected +++ b/tests/custom/permutations/17_transform_partition/int/0010_given_permutation_partition_find_partition/stdout.expected @@ -1,7 +1,7 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime permutation.param +Savile Row: conjure-output/model000001.eprime permutation.param Running minion for domain filtering. Running solver: minion Copying solution to: permutation-permutation.solution diff --git a/tests/custom/permutations/17_transform_partition/int/0020_given_permutation_find_partitions/stdout.expected b/tests/custom/permutations/17_transform_partition/int/0020_given_permutation_find_partitions/stdout.expected index 22c01e1f33..8b93555a49 100644 --- a/tests/custom/permutations/17_transform_partition/int/0020_given_permutation_find_partitions/stdout.expected +++ b/tests/custom/permutations/17_transform_partition/int/0020_given_permutation_find_partitions/stdout.expected @@ -1,7 +1,7 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime permutation.param +Savile Row: conjure-output/model000001.eprime permutation.param Running minion for domain filtering. Running solver: minion Copying solution to: permutation-permutation-000001.solution diff --git a/tests/custom/permutations/17_transform_partition/int/0030_letting_permutation_find_partitions/stdout.expected b/tests/custom/permutations/17_transform_partition/int/0030_letting_permutation_find_partitions/stdout.expected index e83b516d73..d52f59f8f0 100644 --- a/tests/custom/permutations/17_transform_partition/int/0030_letting_permutation_find_partitions/stdout.expected +++ b/tests/custom/permutations/17_transform_partition/int/0030_letting_permutation_find_partitions/stdout.expected @@ -1,7 +1,7 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime +Savile Row: conjure-output/model000001.eprime Running minion for domain filtering. Running solver: minion Copying solution to: permutation-000001.solution diff --git a/tests/custom/permutations/17_transform_partition/int/0040_find_permutation_find_partitions/stdout.expected b/tests/custom/permutations/17_transform_partition/int/0040_find_permutation_find_partitions/stdout.expected index 2ecd83b341..f567a66263 100644 --- a/tests/custom/permutations/17_transform_partition/int/0040_find_permutation_find_partitions/stdout.expected +++ b/tests/custom/permutations/17_transform_partition/int/0040_find_permutation_find_partitions/stdout.expected @@ -1,7 +1,7 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime +Savile Row: conjure-output/model000001.eprime Running minion for domain filtering. Running solver: minion Copying solution to: permutation-000001.solution diff --git a/tests/custom/permutations/17_transform_partition/int/0050_find_permutation_given_partition_find_partition/stdout.expected b/tests/custom/permutations/17_transform_partition/int/0050_find_permutation_given_partition_find_partition/stdout.expected index 105650bc2c..2a0ca335f1 100644 --- a/tests/custom/permutations/17_transform_partition/int/0050_find_permutation_given_partition_find_partition/stdout.expected +++ b/tests/custom/permutations/17_transform_partition/int/0050_find_permutation_given_partition_find_partition/stdout.expected @@ -1,7 +1,7 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime permutation.param +Savile Row: conjure-output/model000001.eprime permutation.param Running minion for domain filtering. Running solver: minion Copying solution to: permutation-permutation-000001.solution diff --git a/tests/custom/permutations/17_transform_partition/unnamed/0010_find_partition_of_unnamed/stdout.expected b/tests/custom/permutations/17_transform_partition/unnamed/0010_find_partition_of_unnamed/stdout.expected index 75a4cba9a1..63b9d54150 100644 --- a/tests/custom/permutations/17_transform_partition/unnamed/0010_find_partition_of_unnamed/stdout.expected +++ b/tests/custom/permutations/17_transform_partition/unnamed/0010_find_partition_of_unnamed/stdout.expected @@ -1,7 +1,7 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime +Savile Row: conjure-output/model000001.eprime Running minion for domain filtering. Running solver: minion Copying solution to: permutation-000001.solution diff --git a/tests/custom/permutations/18_transform_matrix/enum/0020_given_permutation_and_matrix_find_matrix/stdout.expected b/tests/custom/permutations/18_transform_matrix/enum/0020_given_permutation_and_matrix_find_matrix/stdout.expected index cf80670c07..579caec265 100644 --- a/tests/custom/permutations/18_transform_matrix/enum/0020_given_permutation_and_matrix_find_matrix/stdout.expected +++ b/tests/custom/permutations/18_transform_matrix/enum/0020_given_permutation_and_matrix_find_matrix/stdout.expected @@ -1,8 +1,10 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime permutation.param +Savile Row: conjure-output/model000001.eprime permutation.param +Running minion for domain filtering. +Running solver: minion Copying solution to: permutation-permutation.solution language Essence 1.3 -letting sn be [e_7, e_6, e_5, e_8; int(11..14)] +letting sn be [e_5, e_6, e_7, e_8; int(11..14)] diff --git a/tests/custom/permutations/18_transform_matrix/enum/0030_letting_permutation_given_matrix_find_matrix/stdout.expected b/tests/custom/permutations/18_transform_matrix/enum/0030_letting_permutation_given_matrix_find_matrix/stdout.expected index 2073aea362..be922276e3 100644 --- a/tests/custom/permutations/18_transform_matrix/enum/0030_letting_permutation_given_matrix_find_matrix/stdout.expected +++ b/tests/custom/permutations/18_transform_matrix/enum/0030_letting_permutation_given_matrix_find_matrix/stdout.expected @@ -1,8 +1,10 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime permutation.param +Savile Row: conjure-output/model000001.eprime permutation.param +Running minion for domain filtering. +Running solver: minion Copying solution to: permutation-permutation.solution language Essence 1.3 -letting sn be [e_7, e_6, e_5, e_8; int(1..4)] +letting sn be [e_5, e_6, e_7, e_8; int(1..4)] diff --git a/tests/custom/permutations/18_transform_matrix/enum/0040_find_permutation_find_matrices/stdout.expected b/tests/custom/permutations/18_transform_matrix/enum/0040_find_permutation_find_matrices/stdout.expected index 2342f944c1..b1e085ad4e 100644 --- a/tests/custom/permutations/18_transform_matrix/enum/0040_find_permutation_find_matrices/stdout.expected +++ b/tests/custom/permutations/18_transform_matrix/enum/0040_find_permutation_find_matrices/stdout.expected @@ -1,7 +1,7 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime +Savile Row: conjure-output/model000001.eprime Running minion for domain filtering. Running solver: minion Copying solution to: permutation.solutions diff --git a/tests/custom/permutations/18_transform_matrix/int/0020_given_permutation_and_matrix_find_matrix/stdout.expected b/tests/custom/permutations/18_transform_matrix/int/0020_given_permutation_and_matrix_find_matrix/stdout.expected index 448a5ef974..83e3630454 100644 --- a/tests/custom/permutations/18_transform_matrix/int/0020_given_permutation_and_matrix_find_matrix/stdout.expected +++ b/tests/custom/permutations/18_transform_matrix/int/0020_given_permutation_and_matrix_find_matrix/stdout.expected @@ -1,8 +1,10 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime permutation.param +Savile Row: conjure-output/model000001.eprime permutation.param +Running minion for domain filtering. +Running solver: minion Copying solution to: permutation-permutation.solution language Essence 1.3 -letting sn be [7, 6, 5, 8; int(1..4)] +letting sn be [5, 6, 7, 8; int(1..4)] diff --git a/tests/custom/permutations/18_transform_matrix/int/0030_letting_permutation_given_matrix_find_matrix/stdout.expected b/tests/custom/permutations/18_transform_matrix/int/0030_letting_permutation_given_matrix_find_matrix/stdout.expected index 448a5ef974..83e3630454 100644 --- a/tests/custom/permutations/18_transform_matrix/int/0030_letting_permutation_given_matrix_find_matrix/stdout.expected +++ b/tests/custom/permutations/18_transform_matrix/int/0030_letting_permutation_given_matrix_find_matrix/stdout.expected @@ -1,8 +1,10 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime permutation.param +Savile Row: conjure-output/model000001.eprime permutation.param +Running minion for domain filtering. +Running solver: minion Copying solution to: permutation-permutation.solution language Essence 1.3 -letting sn be [7, 6, 5, 8; int(1..4)] +letting sn be [5, 6, 7, 8; int(1..4)] diff --git a/tests/custom/permutations/18_transform_matrix/unnamed/0040_find_permutation_find_matrices/stdout.expected b/tests/custom/permutations/18_transform_matrix/unnamed/0040_find_permutation_find_matrices/stdout.expected index 85aa7acb0b..096f228371 100644 --- a/tests/custom/permutations/18_transform_matrix/unnamed/0040_find_permutation_find_matrices/stdout.expected +++ b/tests/custom/permutations/18_transform_matrix/unnamed/0040_find_permutation_find_matrices/stdout.expected @@ -1,7 +1,7 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime +Savile Row: conjure-output/model000001.eprime Running minion for domain filtering. Running solver: minion Copying solution to: permutation.solution diff --git a/tests/custom/permutations/19_complications/multiple_enums/0010_set_of_tuples/stdout.expected b/tests/custom/permutations/19_complications/multiple_enums/0010_set_of_tuples/stdout.expected index 81c53ebfd0..03d7092eff 100644 --- a/tests/custom/permutations/19_complications/multiple_enums/0010_set_of_tuples/stdout.expected +++ b/tests/custom/permutations/19_complications/multiple_enums/0010_set_of_tuples/stdout.expected @@ -1,7 +1,7 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime +Savile Row: conjure-output/model000001.eprime Running minion for domain filtering. Running solver: minion Copying solution to: permutation.solution diff --git a/tests/custom/permutations/24_image_comprehension_dotlt/int/0010_find_perm_find_set/stdout.expected b/tests/custom/permutations/24_image_comprehension_dotlt/int/0010_find_perm_find_set/stdout.expected index 5272e4573d..79496d08ff 100644 --- a/tests/custom/permutations/24_image_comprehension_dotlt/int/0010_find_perm_find_set/stdout.expected +++ b/tests/custom/permutations/24_image_comprehension_dotlt/int/0010_find_perm_find_set/stdout.expected @@ -1,7 +1,7 @@ Generating models for permutation.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime +Savile Row: conjure-output/model000001.eprime Running minion for domain filtering. Running solver: minion Copying solution to: permutation-000001.solution diff --git a/tests/exhaustive/basic/perms/01_representation/enum/0001_given_permutation_in_param/expected/model-permutation.eprime-param b/tests/exhaustive/basic/perms/01_representation/enum/0001_given_permutation_in_param/expected/model-permutation.eprime-param index c2bddee0e8..6ab791d030 100644 --- a/tests/exhaustive/basic/perms/01_representation/enum/0001_given_permutation_in_param/expected/model-permutation.eprime-param +++ b/tests/exhaustive/basic/perms/01_representation/enum/0001_given_permutation_in_param/expected/model-permutation.eprime-param @@ -1,3 +1,4 @@ language ESSENCE' 1.0 -letting p_PermutationAsFunction_PermutationFunction_Function1D be [3, 2, 4, 1; int(1..4)] +letting p_PermutationAsFunction_PermutationFunction_forwards_Function1D be [3, 2, 4, 1; int(1..4)] +letting p_PermutationAsFunction_PermutationFunction_backwards_Function1D be [4, 2, 1, 3; int(1..4)] diff --git a/tests/exhaustive/basic/perms/01_representation/enum/0001_given_permutation_in_param/expected/model.eprime b/tests/exhaustive/basic/perms/01_representation/enum/0001_given_permutation_in_param/expected/model.eprime index cc4c1dfa5f..dbcb2ae00e 100644 --- a/tests/exhaustive/basic/perms/01_representation/enum/0001_given_permutation_in_param/expected/model.eprime +++ b/tests/exhaustive/basic/perms/01_representation/enum/0001_given_permutation_in_param/expected/model.eprime @@ -1,6 +1,7 @@ language ESSENCE' 1.0 -given p_PermutationAsFunction_PermutationFunction_Function1D: matrix indexed by [int(1..4)] of int(1..4) +given p_PermutationAsFunction_PermutationFunction_forwards_Function1D: matrix indexed by [int(1..4)] of int(1..4) +given p_PermutationAsFunction_PermutationFunction_backwards_Function1D: matrix indexed by [int(1..4)] of int(1..4) branching on [] such that true diff --git a/tests/exhaustive/basic/perms/01_representation/enum/0002_given_permutation_in_param/expected/model-permutation.eprime-param b/tests/exhaustive/basic/perms/01_representation/enum/0002_given_permutation_in_param/expected/model-permutation.eprime-param index 7e9e727085..a57f927f00 100644 --- a/tests/exhaustive/basic/perms/01_representation/enum/0002_given_permutation_in_param/expected/model-permutation.eprime-param +++ b/tests/exhaustive/basic/perms/01_representation/enum/0002_given_permutation_in_param/expected/model-permutation.eprime-param @@ -1,3 +1,4 @@ language ESSENCE' 1.0 -letting p_PermutationAsFunction_PermutationFunction_Function1D be [3, 1, 2; int(1..3)] +letting p_PermutationAsFunction_PermutationFunction_forwards_Function1D be [3, 1, 2; int(1..3)] +letting p_PermutationAsFunction_PermutationFunction_backwards_Function1D be [2, 3, 1; int(1..3)] diff --git a/tests/exhaustive/basic/perms/01_representation/enum/0002_given_permutation_in_param/expected/model.eprime b/tests/exhaustive/basic/perms/01_representation/enum/0002_given_permutation_in_param/expected/model.eprime index b1234f8b14..79ecb254b3 100644 --- a/tests/exhaustive/basic/perms/01_representation/enum/0002_given_permutation_in_param/expected/model.eprime +++ b/tests/exhaustive/basic/perms/01_representation/enum/0002_given_permutation_in_param/expected/model.eprime @@ -1,6 +1,7 @@ language ESSENCE' 1.0 -given p_PermutationAsFunction_PermutationFunction_Function1D: matrix indexed by [int(1..3)] of int(1..3) +given p_PermutationAsFunction_PermutationFunction_forwards_Function1D: matrix indexed by [int(1..3)] of int(1..3) +given p_PermutationAsFunction_PermutationFunction_backwards_Function1D: matrix indexed by [int(1..3)] of int(1..3) branching on [] such that true diff --git a/tests/exhaustive/basic/perms/01_representation/enum/0003_given_permutation_in_param_2_cycle/expected/model-permutation.eprime-param b/tests/exhaustive/basic/perms/01_representation/enum/0003_given_permutation_in_param_2_cycle/expected/model-permutation.eprime-param index 3cc48acd18..af34d161a0 100644 --- a/tests/exhaustive/basic/perms/01_representation/enum/0003_given_permutation_in_param_2_cycle/expected/model-permutation.eprime-param +++ b/tests/exhaustive/basic/perms/01_representation/enum/0003_given_permutation_in_param_2_cycle/expected/model-permutation.eprime-param @@ -1,3 +1,4 @@ language ESSENCE' 1.0 -letting p_PermutationAsFunction_PermutationFunction_Function1D be [3, 4, 1, 2; int(1..4)] +letting p_PermutationAsFunction_PermutationFunction_forwards_Function1D be [3, 4, 1, 2; int(1..4)] +letting p_PermutationAsFunction_PermutationFunction_backwards_Function1D be [3, 4, 1, 2; int(1..4)] diff --git a/tests/exhaustive/basic/perms/01_representation/enum/0003_given_permutation_in_param_2_cycle/expected/model.eprime b/tests/exhaustive/basic/perms/01_representation/enum/0003_given_permutation_in_param_2_cycle/expected/model.eprime index cc4c1dfa5f..dbcb2ae00e 100644 --- a/tests/exhaustive/basic/perms/01_representation/enum/0003_given_permutation_in_param_2_cycle/expected/model.eprime +++ b/tests/exhaustive/basic/perms/01_representation/enum/0003_given_permutation_in_param_2_cycle/expected/model.eprime @@ -1,6 +1,7 @@ language ESSENCE' 1.0 -given p_PermutationAsFunction_PermutationFunction_Function1D: matrix indexed by [int(1..4)] of int(1..4) +given p_PermutationAsFunction_PermutationFunction_forwards_Function1D: matrix indexed by [int(1..4)] of int(1..4) +given p_PermutationAsFunction_PermutationFunction_backwards_Function1D: matrix indexed by [int(1..4)] of int(1..4) branching on [] such that true diff --git a/tests/exhaustive/basic/perms/01_representation/enum/0004_given_permutation_in_param_2_cycle/expected/model-permutation.eprime-param b/tests/exhaustive/basic/perms/01_representation/enum/0004_given_permutation_in_param_2_cycle/expected/model-permutation.eprime-param index 3cc48acd18..af34d161a0 100644 --- a/tests/exhaustive/basic/perms/01_representation/enum/0004_given_permutation_in_param_2_cycle/expected/model-permutation.eprime-param +++ b/tests/exhaustive/basic/perms/01_representation/enum/0004_given_permutation_in_param_2_cycle/expected/model-permutation.eprime-param @@ -1,3 +1,4 @@ language ESSENCE' 1.0 -letting p_PermutationAsFunction_PermutationFunction_Function1D be [3, 4, 1, 2; int(1..4)] +letting p_PermutationAsFunction_PermutationFunction_forwards_Function1D be [3, 4, 1, 2; int(1..4)] +letting p_PermutationAsFunction_PermutationFunction_backwards_Function1D be [3, 4, 1, 2; int(1..4)] diff --git a/tests/exhaustive/basic/perms/01_representation/enum/0004_given_permutation_in_param_2_cycle/expected/model.eprime b/tests/exhaustive/basic/perms/01_representation/enum/0004_given_permutation_in_param_2_cycle/expected/model.eprime index cc4c1dfa5f..dbcb2ae00e 100644 --- a/tests/exhaustive/basic/perms/01_representation/enum/0004_given_permutation_in_param_2_cycle/expected/model.eprime +++ b/tests/exhaustive/basic/perms/01_representation/enum/0004_given_permutation_in_param_2_cycle/expected/model.eprime @@ -1,6 +1,7 @@ language ESSENCE' 1.0 -given p_PermutationAsFunction_PermutationFunction_Function1D: matrix indexed by [int(1..4)] of int(1..4) +given p_PermutationAsFunction_PermutationFunction_forwards_Function1D: matrix indexed by [int(1..4)] of int(1..4) +given p_PermutationAsFunction_PermutationFunction_backwards_Function1D: matrix indexed by [int(1..4)] of int(1..4) branching on [] such that true diff --git a/tests/exhaustive/basic/perms/01_representation/enum/0005_find_permutation_size_4_of_int1_4/expected/model.eprime b/tests/exhaustive/basic/perms/01_representation/enum/0005_find_permutation_size_4_of_int1_4/expected/model.eprime index 134950077a..a1751d1c86 100644 --- a/tests/exhaustive/basic/perms/01_representation/enum/0005_find_permutation_size_4_of_int1_4/expected/model.eprime +++ b/tests/exhaustive/basic/perms/01_representation/enum/0005_find_permutation_size_4_of_int1_4/expected/model.eprime @@ -1,9 +1,24 @@ language ESSENCE' 1.0 -find p_PermutationAsFunction_PermutationFunction_Function1D: matrix indexed by [int(1..4)] of int(1..4) -branching on [p_PermutationAsFunction_PermutationFunction_Function1D] +find p_PermutationAsFunction_PermutationFunction_forwards_Function1D: matrix indexed by [int(1..4)] of int(1..4) +find p_PermutationAsFunction_PermutationFunction_backwards_Function1D: matrix indexed by [int(1..4)] of int(1..4) +branching on + [p_PermutationAsFunction_PermutationFunction_forwards_Function1D, + p_PermutationAsFunction_PermutationFunction_backwards_Function1D] such that - allDiff(p_PermutationAsFunction_PermutationFunction_Function1D), - and([or([p_PermutationAsFunction_PermutationFunction_Function1D[q3] = q2 | q3 : int(1..4)]) | q2 : int(1..4)]), - 4 = sum([toInt(q1 != p_PermutationAsFunction_PermutationFunction_Function1D[q1]) | q1 : int(1..4)]) + allDiff(p_PermutationAsFunction_PermutationFunction_forwards_Function1D), + and([or([p_PermutationAsFunction_PermutationFunction_forwards_Function1D[q3] = q2 | q3 : int(1..4)]) + | q2 : int(1..4)]), + allDiff(p_PermutationAsFunction_PermutationFunction_backwards_Function1D), + and([or([p_PermutationAsFunction_PermutationFunction_backwards_Function1D[q6] = q5 | q6 : int(1..4)]) + | q5 : int(1..4)]), + 4 = sum([toInt(q1 != p_PermutationAsFunction_PermutationFunction_forwards_Function1D[q1]) | q1 : int(1..4)]), + and([p_PermutationAsFunction_PermutationFunction_backwards_Function1D + [p_PermutationAsFunction_PermutationFunction_forwards_Function1D[q1]] + = q1 + | q1 : int(1..4)]), + and([p_PermutationAsFunction_PermutationFunction_forwards_Function1D + [p_PermutationAsFunction_PermutationFunction_backwards_Function1D[q1]] + = q1 + | q1 : int(1..4)]) diff --git a/tests/exhaustive/basic/perms/01_representation/enum/0006_find_permutation_size_0_of_int1_4/expected/model.eprime b/tests/exhaustive/basic/perms/01_representation/enum/0006_find_permutation_size_0_of_int1_4/expected/model.eprime index a03a5e86e3..e1caf81808 100644 --- a/tests/exhaustive/basic/perms/01_representation/enum/0006_find_permutation_size_0_of_int1_4/expected/model.eprime +++ b/tests/exhaustive/basic/perms/01_representation/enum/0006_find_permutation_size_0_of_int1_4/expected/model.eprime @@ -1,9 +1,24 @@ language ESSENCE' 1.0 -find p_PermutationAsFunction_PermutationFunction_Function1D: matrix indexed by [int(1..4)] of int(1..4) -branching on [p_PermutationAsFunction_PermutationFunction_Function1D] +find p_PermutationAsFunction_PermutationFunction_forwards_Function1D: matrix indexed by [int(1..4)] of int(1..4) +find p_PermutationAsFunction_PermutationFunction_backwards_Function1D: matrix indexed by [int(1..4)] of int(1..4) +branching on + [p_PermutationAsFunction_PermutationFunction_forwards_Function1D, + p_PermutationAsFunction_PermutationFunction_backwards_Function1D] such that - allDiff(p_PermutationAsFunction_PermutationFunction_Function1D), - and([or([p_PermutationAsFunction_PermutationFunction_Function1D[q3] = q2 | q3 : int(1..4)]) | q2 : int(1..4)]), - 0 = sum([toInt(q1 != p_PermutationAsFunction_PermutationFunction_Function1D[q1]) | q1 : int(1..4)]) + allDiff(p_PermutationAsFunction_PermutationFunction_forwards_Function1D), + and([or([p_PermutationAsFunction_PermutationFunction_forwards_Function1D[q3] = q2 | q3 : int(1..4)]) + | q2 : int(1..4)]), + allDiff(p_PermutationAsFunction_PermutationFunction_backwards_Function1D), + and([or([p_PermutationAsFunction_PermutationFunction_backwards_Function1D[q6] = q5 | q6 : int(1..4)]) + | q5 : int(1..4)]), + 0 = sum([toInt(q1 != p_PermutationAsFunction_PermutationFunction_forwards_Function1D[q1]) | q1 : int(1..4)]), + and([p_PermutationAsFunction_PermutationFunction_backwards_Function1D + [p_PermutationAsFunction_PermutationFunction_forwards_Function1D[q1]] + = q1 + | q1 : int(1..4)]), + and([p_PermutationAsFunction_PermutationFunction_forwards_Function1D + [p_PermutationAsFunction_PermutationFunction_backwards_Function1D[q1]] + = q1 + | q1 : int(1..4)]) diff --git a/tests/exhaustive/basic/perms/01_representation/enum/0008_find_permutation_of_int1_4/expected/model.eprime b/tests/exhaustive/basic/perms/01_representation/enum/0008_find_permutation_of_int1_4/expected/model.eprime index ac93d552d6..055fe5255f 100644 --- a/tests/exhaustive/basic/perms/01_representation/enum/0008_find_permutation_of_int1_4/expected/model.eprime +++ b/tests/exhaustive/basic/perms/01_representation/enum/0008_find_permutation_of_int1_4/expected/model.eprime @@ -1,8 +1,23 @@ language ESSENCE' 1.0 -find p_PermutationAsFunction_PermutationFunction_Function1D: matrix indexed by [int(1..4)] of int(1..4) -branching on [p_PermutationAsFunction_PermutationFunction_Function1D] +find p_PermutationAsFunction_PermutationFunction_forwards_Function1D: matrix indexed by [int(1..4)] of int(1..4) +find p_PermutationAsFunction_PermutationFunction_backwards_Function1D: matrix indexed by [int(1..4)] of int(1..4) +branching on + [p_PermutationAsFunction_PermutationFunction_forwards_Function1D, + p_PermutationAsFunction_PermutationFunction_backwards_Function1D] such that - allDiff(p_PermutationAsFunction_PermutationFunction_Function1D), - and([or([p_PermutationAsFunction_PermutationFunction_Function1D[q3] = q2 | q3 : int(1..4)]) | q2 : int(1..4)]) + allDiff(p_PermutationAsFunction_PermutationFunction_forwards_Function1D), + and([or([p_PermutationAsFunction_PermutationFunction_forwards_Function1D[q3] = q2 | q3 : int(1..4)]) + | q2 : int(1..4)]), + allDiff(p_PermutationAsFunction_PermutationFunction_backwards_Function1D), + and([or([p_PermutationAsFunction_PermutationFunction_backwards_Function1D[q6] = q5 | q6 : int(1..4)]) + | q5 : int(1..4)]), + and([p_PermutationAsFunction_PermutationFunction_backwards_Function1D + [p_PermutationAsFunction_PermutationFunction_forwards_Function1D[q1]] + = q1 + | q1 : int(1..4)]), + and([p_PermutationAsFunction_PermutationFunction_forwards_Function1D + [p_PermutationAsFunction_PermutationFunction_backwards_Function1D[q1]] + = q1 + | q1 : int(1..4)]) diff --git a/tests/exhaustive/basic/perms/01_representation/enum/0010_find_permutation_maxSize_2_of_int1_3/expected/model.eprime b/tests/exhaustive/basic/perms/01_representation/enum/0010_find_permutation_maxSize_2_of_int1_3/expected/model.eprime index 95837c9498..a153fa5e65 100644 --- a/tests/exhaustive/basic/perms/01_representation/enum/0010_find_permutation_maxSize_2_of_int1_3/expected/model.eprime +++ b/tests/exhaustive/basic/perms/01_representation/enum/0010_find_permutation_maxSize_2_of_int1_3/expected/model.eprime @@ -1,9 +1,24 @@ language ESSENCE' 1.0 -find p_PermutationAsFunction_PermutationFunction_Function1D: matrix indexed by [int(1..3)] of int(1..3) -branching on [p_PermutationAsFunction_PermutationFunction_Function1D] +find p_PermutationAsFunction_PermutationFunction_forwards_Function1D: matrix indexed by [int(1..3)] of int(1..3) +find p_PermutationAsFunction_PermutationFunction_backwards_Function1D: matrix indexed by [int(1..3)] of int(1..3) +branching on + [p_PermutationAsFunction_PermutationFunction_forwards_Function1D, + p_PermutationAsFunction_PermutationFunction_backwards_Function1D] such that - allDiff(p_PermutationAsFunction_PermutationFunction_Function1D), - and([or([p_PermutationAsFunction_PermutationFunction_Function1D[q3] = q2 | q3 : int(1..3)]) | q2 : int(1..3)]), - sum([toInt(q1 != p_PermutationAsFunction_PermutationFunction_Function1D[q1]) | q1 : int(1..3)]) <= 2 + allDiff(p_PermutationAsFunction_PermutationFunction_forwards_Function1D), + and([or([p_PermutationAsFunction_PermutationFunction_forwards_Function1D[q3] = q2 | q3 : int(1..3)]) + | q2 : int(1..3)]), + allDiff(p_PermutationAsFunction_PermutationFunction_backwards_Function1D), + and([or([p_PermutationAsFunction_PermutationFunction_backwards_Function1D[q6] = q5 | q6 : int(1..3)]) + | q5 : int(1..3)]), + sum([toInt(q1 != p_PermutationAsFunction_PermutationFunction_forwards_Function1D[q1]) | q1 : int(1..3)]) <= 2, + and([p_PermutationAsFunction_PermutationFunction_backwards_Function1D + [p_PermutationAsFunction_PermutationFunction_forwards_Function1D[q1]] + = q1 + | q1 : int(1..3)]), + and([p_PermutationAsFunction_PermutationFunction_forwards_Function1D + [p_PermutationAsFunction_PermutationFunction_backwards_Function1D[q1]] + = q1 + | q1 : int(1..3)]) diff --git a/tests/exhaustive/basic/perms/01_representation/enum/0011_find_permutation_minSize_2_of_int1_3/expected/model.eprime b/tests/exhaustive/basic/perms/01_representation/enum/0011_find_permutation_minSize_2_of_int1_3/expected/model.eprime index 7854912481..6193c6a728 100644 --- a/tests/exhaustive/basic/perms/01_representation/enum/0011_find_permutation_minSize_2_of_int1_3/expected/model.eprime +++ b/tests/exhaustive/basic/perms/01_representation/enum/0011_find_permutation_minSize_2_of_int1_3/expected/model.eprime @@ -1,9 +1,24 @@ language ESSENCE' 1.0 -find p_PermutationAsFunction_PermutationFunction_Function1D: matrix indexed by [int(1..3)] of int(1..3) -branching on [p_PermutationAsFunction_PermutationFunction_Function1D] +find p_PermutationAsFunction_PermutationFunction_forwards_Function1D: matrix indexed by [int(1..3)] of int(1..3) +find p_PermutationAsFunction_PermutationFunction_backwards_Function1D: matrix indexed by [int(1..3)] of int(1..3) +branching on + [p_PermutationAsFunction_PermutationFunction_forwards_Function1D, + p_PermutationAsFunction_PermutationFunction_backwards_Function1D] such that - allDiff(p_PermutationAsFunction_PermutationFunction_Function1D), - and([or([p_PermutationAsFunction_PermutationFunction_Function1D[q3] = q2 | q3 : int(1..3)]) | q2 : int(1..3)]), - 2 <= sum([toInt(q1 != p_PermutationAsFunction_PermutationFunction_Function1D[q1]) | q1 : int(1..3)]) + allDiff(p_PermutationAsFunction_PermutationFunction_forwards_Function1D), + and([or([p_PermutationAsFunction_PermutationFunction_forwards_Function1D[q3] = q2 | q3 : int(1..3)]) + | q2 : int(1..3)]), + allDiff(p_PermutationAsFunction_PermutationFunction_backwards_Function1D), + and([or([p_PermutationAsFunction_PermutationFunction_backwards_Function1D[q6] = q5 | q6 : int(1..3)]) + | q5 : int(1..3)]), + 2 <= sum([toInt(q1 != p_PermutationAsFunction_PermutationFunction_forwards_Function1D[q1]) | q1 : int(1..3)]), + and([p_PermutationAsFunction_PermutationFunction_backwards_Function1D + [p_PermutationAsFunction_PermutationFunction_forwards_Function1D[q1]] + = q1 + | q1 : int(1..3)]), + and([p_PermutationAsFunction_PermutationFunction_forwards_Function1D + [p_PermutationAsFunction_PermutationFunction_backwards_Function1D[q1]] + = q1 + | q1 : int(1..3)]) diff --git a/tests/exhaustive/basic/perms/01_representation/enum/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model.eprime b/tests/exhaustive/basic/perms/01_representation/enum/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model.eprime index 4292a59345..110c3278cb 100644 --- a/tests/exhaustive/basic/perms/01_representation/enum/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model.eprime +++ b/tests/exhaustive/basic/perms/01_representation/enum/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model.eprime @@ -1,10 +1,25 @@ language ESSENCE' 1.0 -find p_PermutationAsFunction_PermutationFunction_Function1D: matrix indexed by [int(1..4)] of int(1..4) -branching on [p_PermutationAsFunction_PermutationFunction_Function1D] +find p_PermutationAsFunction_PermutationFunction_forwards_Function1D: matrix indexed by [int(1..4)] of int(1..4) +find p_PermutationAsFunction_PermutationFunction_backwards_Function1D: matrix indexed by [int(1..4)] of int(1..4) +branching on + [p_PermutationAsFunction_PermutationFunction_forwards_Function1D, + p_PermutationAsFunction_PermutationFunction_backwards_Function1D] such that - allDiff(p_PermutationAsFunction_PermutationFunction_Function1D), - and([or([p_PermutationAsFunction_PermutationFunction_Function1D[q3] = q2 | q3 : int(1..4)]) | q2 : int(1..4)]), - 2 <= sum([toInt(q1 != p_PermutationAsFunction_PermutationFunction_Function1D[q1]) | q1 : int(1..4)]), - sum([toInt(q1 != p_PermutationAsFunction_PermutationFunction_Function1D[q1]) | q1 : int(1..4)]) <= 3 + allDiff(p_PermutationAsFunction_PermutationFunction_forwards_Function1D), + and([or([p_PermutationAsFunction_PermutationFunction_forwards_Function1D[q3] = q2 | q3 : int(1..4)]) + | q2 : int(1..4)]), + allDiff(p_PermutationAsFunction_PermutationFunction_backwards_Function1D), + and([or([p_PermutationAsFunction_PermutationFunction_backwards_Function1D[q6] = q5 | q6 : int(1..4)]) + | q5 : int(1..4)]), + 2 <= sum([toInt(q1 != p_PermutationAsFunction_PermutationFunction_forwards_Function1D[q1]) | q1 : int(1..4)]), + sum([toInt(q1 != p_PermutationAsFunction_PermutationFunction_forwards_Function1D[q1]) | q1 : int(1..4)]) <= 3, + and([p_PermutationAsFunction_PermutationFunction_backwards_Function1D + [p_PermutationAsFunction_PermutationFunction_forwards_Function1D[q1]] + = q1 + | q1 : int(1..4)]), + and([p_PermutationAsFunction_PermutationFunction_forwards_Function1D + [p_PermutationAsFunction_PermutationFunction_backwards_Function1D[q1]] + = q1 + | q1 : int(1..4)]) diff --git a/tests/exhaustive/basic/perms/01_representation/int/0001_given_permutation_in_param/expected/model-permutation.eprime-param b/tests/exhaustive/basic/perms/01_representation/int/0001_given_permutation_in_param/expected/model-permutation.eprime-param index c2bddee0e8..6ab791d030 100644 --- a/tests/exhaustive/basic/perms/01_representation/int/0001_given_permutation_in_param/expected/model-permutation.eprime-param +++ b/tests/exhaustive/basic/perms/01_representation/int/0001_given_permutation_in_param/expected/model-permutation.eprime-param @@ -1,3 +1,4 @@ language ESSENCE' 1.0 -letting p_PermutationAsFunction_PermutationFunction_Function1D be [3, 2, 4, 1; int(1..4)] +letting p_PermutationAsFunction_PermutationFunction_forwards_Function1D be [3, 2, 4, 1; int(1..4)] +letting p_PermutationAsFunction_PermutationFunction_backwards_Function1D be [4, 2, 1, 3; int(1..4)] diff --git a/tests/exhaustive/basic/perms/01_representation/int/0001_given_permutation_in_param/expected/model.eprime b/tests/exhaustive/basic/perms/01_representation/int/0001_given_permutation_in_param/expected/model.eprime index cc4c1dfa5f..dbcb2ae00e 100644 --- a/tests/exhaustive/basic/perms/01_representation/int/0001_given_permutation_in_param/expected/model.eprime +++ b/tests/exhaustive/basic/perms/01_representation/int/0001_given_permutation_in_param/expected/model.eprime @@ -1,6 +1,7 @@ language ESSENCE' 1.0 -given p_PermutationAsFunction_PermutationFunction_Function1D: matrix indexed by [int(1..4)] of int(1..4) +given p_PermutationAsFunction_PermutationFunction_forwards_Function1D: matrix indexed by [int(1..4)] of int(1..4) +given p_PermutationAsFunction_PermutationFunction_backwards_Function1D: matrix indexed by [int(1..4)] of int(1..4) branching on [] such that true diff --git a/tests/exhaustive/basic/perms/01_representation/int/0002_given_permutation_in_param/expected/model-permutation.eprime-param b/tests/exhaustive/basic/perms/01_representation/int/0002_given_permutation_in_param/expected/model-permutation.eprime-param index 7e9e727085..a57f927f00 100644 --- a/tests/exhaustive/basic/perms/01_representation/int/0002_given_permutation_in_param/expected/model-permutation.eprime-param +++ b/tests/exhaustive/basic/perms/01_representation/int/0002_given_permutation_in_param/expected/model-permutation.eprime-param @@ -1,3 +1,4 @@ language ESSENCE' 1.0 -letting p_PermutationAsFunction_PermutationFunction_Function1D be [3, 1, 2; int(1..3)] +letting p_PermutationAsFunction_PermutationFunction_forwards_Function1D be [3, 1, 2; int(1..3)] +letting p_PermutationAsFunction_PermutationFunction_backwards_Function1D be [2, 3, 1; int(1..3)] diff --git a/tests/exhaustive/basic/perms/01_representation/int/0002_given_permutation_in_param/expected/model.eprime b/tests/exhaustive/basic/perms/01_representation/int/0002_given_permutation_in_param/expected/model.eprime index b1234f8b14..79ecb254b3 100644 --- a/tests/exhaustive/basic/perms/01_representation/int/0002_given_permutation_in_param/expected/model.eprime +++ b/tests/exhaustive/basic/perms/01_representation/int/0002_given_permutation_in_param/expected/model.eprime @@ -1,6 +1,7 @@ language ESSENCE' 1.0 -given p_PermutationAsFunction_PermutationFunction_Function1D: matrix indexed by [int(1..3)] of int(1..3) +given p_PermutationAsFunction_PermutationFunction_forwards_Function1D: matrix indexed by [int(1..3)] of int(1..3) +given p_PermutationAsFunction_PermutationFunction_backwards_Function1D: matrix indexed by [int(1..3)] of int(1..3) branching on [] such that true diff --git a/tests/exhaustive/basic/perms/01_representation/int/0003_given_permutation_in_param_2_cycle/expected/model-permutation.eprime-param b/tests/exhaustive/basic/perms/01_representation/int/0003_given_permutation_in_param_2_cycle/expected/model-permutation.eprime-param index 3cc48acd18..af34d161a0 100644 --- a/tests/exhaustive/basic/perms/01_representation/int/0003_given_permutation_in_param_2_cycle/expected/model-permutation.eprime-param +++ b/tests/exhaustive/basic/perms/01_representation/int/0003_given_permutation_in_param_2_cycle/expected/model-permutation.eprime-param @@ -1,3 +1,4 @@ language ESSENCE' 1.0 -letting p_PermutationAsFunction_PermutationFunction_Function1D be [3, 4, 1, 2; int(1..4)] +letting p_PermutationAsFunction_PermutationFunction_forwards_Function1D be [3, 4, 1, 2; int(1..4)] +letting p_PermutationAsFunction_PermutationFunction_backwards_Function1D be [3, 4, 1, 2; int(1..4)] diff --git a/tests/exhaustive/basic/perms/01_representation/int/0003_given_permutation_in_param_2_cycle/expected/model.eprime b/tests/exhaustive/basic/perms/01_representation/int/0003_given_permutation_in_param_2_cycle/expected/model.eprime index cc4c1dfa5f..dbcb2ae00e 100644 --- a/tests/exhaustive/basic/perms/01_representation/int/0003_given_permutation_in_param_2_cycle/expected/model.eprime +++ b/tests/exhaustive/basic/perms/01_representation/int/0003_given_permutation_in_param_2_cycle/expected/model.eprime @@ -1,6 +1,7 @@ language ESSENCE' 1.0 -given p_PermutationAsFunction_PermutationFunction_Function1D: matrix indexed by [int(1..4)] of int(1..4) +given p_PermutationAsFunction_PermutationFunction_forwards_Function1D: matrix indexed by [int(1..4)] of int(1..4) +given p_PermutationAsFunction_PermutationFunction_backwards_Function1D: matrix indexed by [int(1..4)] of int(1..4) branching on [] such that true diff --git a/tests/exhaustive/basic/perms/01_representation/int/0004_given_permutation_in_param_2_cycle/expected/model-permutation.eprime-param b/tests/exhaustive/basic/perms/01_representation/int/0004_given_permutation_in_param_2_cycle/expected/model-permutation.eprime-param index 3cc48acd18..af34d161a0 100644 --- a/tests/exhaustive/basic/perms/01_representation/int/0004_given_permutation_in_param_2_cycle/expected/model-permutation.eprime-param +++ b/tests/exhaustive/basic/perms/01_representation/int/0004_given_permutation_in_param_2_cycle/expected/model-permutation.eprime-param @@ -1,3 +1,4 @@ language ESSENCE' 1.0 -letting p_PermutationAsFunction_PermutationFunction_Function1D be [3, 4, 1, 2; int(1..4)] +letting p_PermutationAsFunction_PermutationFunction_forwards_Function1D be [3, 4, 1, 2; int(1..4)] +letting p_PermutationAsFunction_PermutationFunction_backwards_Function1D be [3, 4, 1, 2; int(1..4)] diff --git a/tests/exhaustive/basic/perms/01_representation/int/0004_given_permutation_in_param_2_cycle/expected/model.eprime b/tests/exhaustive/basic/perms/01_representation/int/0004_given_permutation_in_param_2_cycle/expected/model.eprime index cc4c1dfa5f..dbcb2ae00e 100644 --- a/tests/exhaustive/basic/perms/01_representation/int/0004_given_permutation_in_param_2_cycle/expected/model.eprime +++ b/tests/exhaustive/basic/perms/01_representation/int/0004_given_permutation_in_param_2_cycle/expected/model.eprime @@ -1,6 +1,7 @@ language ESSENCE' 1.0 -given p_PermutationAsFunction_PermutationFunction_Function1D: matrix indexed by [int(1..4)] of int(1..4) +given p_PermutationAsFunction_PermutationFunction_forwards_Function1D: matrix indexed by [int(1..4)] of int(1..4) +given p_PermutationAsFunction_PermutationFunction_backwards_Function1D: matrix indexed by [int(1..4)] of int(1..4) branching on [] such that true diff --git a/tests/exhaustive/basic/perms/01_representation/int/0005_find_permutation_size_4_of_int1_4/expected/model.eprime b/tests/exhaustive/basic/perms/01_representation/int/0005_find_permutation_size_4_of_int1_4/expected/model.eprime index 661a61e88f..83fa4312d5 100644 --- a/tests/exhaustive/basic/perms/01_representation/int/0005_find_permutation_size_4_of_int1_4/expected/model.eprime +++ b/tests/exhaustive/basic/perms/01_representation/int/0005_find_permutation_size_4_of_int1_4/expected/model.eprime @@ -1,10 +1,25 @@ language ESSENCE' 1.0 letting n be 4 -find p_PermutationAsFunction_PermutationFunction_Function1D: matrix indexed by [int(1..4)] of int(1..4) -branching on [p_PermutationAsFunction_PermutationFunction_Function1D] +find p_PermutationAsFunction_PermutationFunction_forwards_Function1D: matrix indexed by [int(1..4)] of int(1..4) +find p_PermutationAsFunction_PermutationFunction_backwards_Function1D: matrix indexed by [int(1..4)] of int(1..4) +branching on + [p_PermutationAsFunction_PermutationFunction_forwards_Function1D, + p_PermutationAsFunction_PermutationFunction_backwards_Function1D] such that - allDiff(p_PermutationAsFunction_PermutationFunction_Function1D), - and([or([p_PermutationAsFunction_PermutationFunction_Function1D[q3] = q2 | q3 : int(1..4)]) | q2 : int(1..4)]), - 4 = sum([toInt(q1 != p_PermutationAsFunction_PermutationFunction_Function1D[q1]) | q1 : int(1..4)]) + allDiff(p_PermutationAsFunction_PermutationFunction_forwards_Function1D), + and([or([p_PermutationAsFunction_PermutationFunction_forwards_Function1D[q3] = q2 | q3 : int(1..4)]) + | q2 : int(1..4)]), + allDiff(p_PermutationAsFunction_PermutationFunction_backwards_Function1D), + and([or([p_PermutationAsFunction_PermutationFunction_backwards_Function1D[q6] = q5 | q6 : int(1..4)]) + | q5 : int(1..4)]), + 4 = sum([toInt(q1 != p_PermutationAsFunction_PermutationFunction_forwards_Function1D[q1]) | q1 : int(1..4)]), + and([p_PermutationAsFunction_PermutationFunction_backwards_Function1D + [p_PermutationAsFunction_PermutationFunction_forwards_Function1D[q1]] + = q1 + | q1 : int(1..4)]), + and([p_PermutationAsFunction_PermutationFunction_forwards_Function1D + [p_PermutationAsFunction_PermutationFunction_backwards_Function1D[q1]] + = q1 + | q1 : int(1..4)]) diff --git a/tests/exhaustive/basic/perms/01_representation/int/0006_find_permutation_size_0_of_int1_4/expected/model.eprime b/tests/exhaustive/basic/perms/01_representation/int/0006_find_permutation_size_0_of_int1_4/expected/model.eprime index e95d7701bd..c29799c0ac 100644 --- a/tests/exhaustive/basic/perms/01_representation/int/0006_find_permutation_size_0_of_int1_4/expected/model.eprime +++ b/tests/exhaustive/basic/perms/01_representation/int/0006_find_permutation_size_0_of_int1_4/expected/model.eprime @@ -1,10 +1,25 @@ language ESSENCE' 1.0 letting n be 4 -find p_PermutationAsFunction_PermutationFunction_Function1D: matrix indexed by [int(1..4)] of int(1..4) -branching on [p_PermutationAsFunction_PermutationFunction_Function1D] +find p_PermutationAsFunction_PermutationFunction_forwards_Function1D: matrix indexed by [int(1..4)] of int(1..4) +find p_PermutationAsFunction_PermutationFunction_backwards_Function1D: matrix indexed by [int(1..4)] of int(1..4) +branching on + [p_PermutationAsFunction_PermutationFunction_forwards_Function1D, + p_PermutationAsFunction_PermutationFunction_backwards_Function1D] such that - allDiff(p_PermutationAsFunction_PermutationFunction_Function1D), - and([or([p_PermutationAsFunction_PermutationFunction_Function1D[q3] = q2 | q3 : int(1..4)]) | q2 : int(1..4)]), - 0 = sum([toInt(q1 != p_PermutationAsFunction_PermutationFunction_Function1D[q1]) | q1 : int(1..4)]) + allDiff(p_PermutationAsFunction_PermutationFunction_forwards_Function1D), + and([or([p_PermutationAsFunction_PermutationFunction_forwards_Function1D[q3] = q2 | q3 : int(1..4)]) + | q2 : int(1..4)]), + allDiff(p_PermutationAsFunction_PermutationFunction_backwards_Function1D), + and([or([p_PermutationAsFunction_PermutationFunction_backwards_Function1D[q6] = q5 | q6 : int(1..4)]) + | q5 : int(1..4)]), + 0 = sum([toInt(q1 != p_PermutationAsFunction_PermutationFunction_forwards_Function1D[q1]) | q1 : int(1..4)]), + and([p_PermutationAsFunction_PermutationFunction_backwards_Function1D + [p_PermutationAsFunction_PermutationFunction_forwards_Function1D[q1]] + = q1 + | q1 : int(1..4)]), + and([p_PermutationAsFunction_PermutationFunction_forwards_Function1D + [p_PermutationAsFunction_PermutationFunction_backwards_Function1D[q1]] + = q1 + | q1 : int(1..4)]) diff --git a/tests/exhaustive/basic/perms/01_representation/int/0008_find_permutation_of_int1_4/expected/model.eprime b/tests/exhaustive/basic/perms/01_representation/int/0008_find_permutation_of_int1_4/expected/model.eprime index baf4941d10..5c6422b381 100644 --- a/tests/exhaustive/basic/perms/01_representation/int/0008_find_permutation_of_int1_4/expected/model.eprime +++ b/tests/exhaustive/basic/perms/01_representation/int/0008_find_permutation_of_int1_4/expected/model.eprime @@ -1,9 +1,24 @@ language ESSENCE' 1.0 letting n be 4 -find p_PermutationAsFunction_PermutationFunction_Function1D: matrix indexed by [int(1..4)] of int(1..4) -branching on [p_PermutationAsFunction_PermutationFunction_Function1D] +find p_PermutationAsFunction_PermutationFunction_forwards_Function1D: matrix indexed by [int(1..4)] of int(1..4) +find p_PermutationAsFunction_PermutationFunction_backwards_Function1D: matrix indexed by [int(1..4)] of int(1..4) +branching on + [p_PermutationAsFunction_PermutationFunction_forwards_Function1D, + p_PermutationAsFunction_PermutationFunction_backwards_Function1D] such that - allDiff(p_PermutationAsFunction_PermutationFunction_Function1D), - and([or([p_PermutationAsFunction_PermutationFunction_Function1D[q3] = q2 | q3 : int(1..4)]) | q2 : int(1..4)]) + allDiff(p_PermutationAsFunction_PermutationFunction_forwards_Function1D), + and([or([p_PermutationAsFunction_PermutationFunction_forwards_Function1D[q3] = q2 | q3 : int(1..4)]) + | q2 : int(1..4)]), + allDiff(p_PermutationAsFunction_PermutationFunction_backwards_Function1D), + and([or([p_PermutationAsFunction_PermutationFunction_backwards_Function1D[q6] = q5 | q6 : int(1..4)]) + | q5 : int(1..4)]), + and([p_PermutationAsFunction_PermutationFunction_backwards_Function1D + [p_PermutationAsFunction_PermutationFunction_forwards_Function1D[q1]] + = q1 + | q1 : int(1..4)]), + and([p_PermutationAsFunction_PermutationFunction_forwards_Function1D + [p_PermutationAsFunction_PermutationFunction_backwards_Function1D[q1]] + = q1 + | q1 : int(1..4)]) diff --git a/tests/exhaustive/basic/perms/01_representation/int/0010_find_permutation_maxSize_2_of_int1_3/expected/model.eprime b/tests/exhaustive/basic/perms/01_representation/int/0010_find_permutation_maxSize_2_of_int1_3/expected/model.eprime index 3bd6e097fb..f0b361d43b 100644 --- a/tests/exhaustive/basic/perms/01_representation/int/0010_find_permutation_maxSize_2_of_int1_3/expected/model.eprime +++ b/tests/exhaustive/basic/perms/01_representation/int/0010_find_permutation_maxSize_2_of_int1_3/expected/model.eprime @@ -1,10 +1,25 @@ language ESSENCE' 1.0 letting n be 3 -find p_PermutationAsFunction_PermutationFunction_Function1D: matrix indexed by [int(1..3)] of int(1..3) -branching on [p_PermutationAsFunction_PermutationFunction_Function1D] +find p_PermutationAsFunction_PermutationFunction_forwards_Function1D: matrix indexed by [int(1..3)] of int(1..3) +find p_PermutationAsFunction_PermutationFunction_backwards_Function1D: matrix indexed by [int(1..3)] of int(1..3) +branching on + [p_PermutationAsFunction_PermutationFunction_forwards_Function1D, + p_PermutationAsFunction_PermutationFunction_backwards_Function1D] such that - allDiff(p_PermutationAsFunction_PermutationFunction_Function1D), - and([or([p_PermutationAsFunction_PermutationFunction_Function1D[q3] = q2 | q3 : int(1..3)]) | q2 : int(1..3)]), - sum([toInt(q1 != p_PermutationAsFunction_PermutationFunction_Function1D[q1]) | q1 : int(1..3)]) <= 2 + allDiff(p_PermutationAsFunction_PermutationFunction_forwards_Function1D), + and([or([p_PermutationAsFunction_PermutationFunction_forwards_Function1D[q3] = q2 | q3 : int(1..3)]) + | q2 : int(1..3)]), + allDiff(p_PermutationAsFunction_PermutationFunction_backwards_Function1D), + and([or([p_PermutationAsFunction_PermutationFunction_backwards_Function1D[q6] = q5 | q6 : int(1..3)]) + | q5 : int(1..3)]), + sum([toInt(q1 != p_PermutationAsFunction_PermutationFunction_forwards_Function1D[q1]) | q1 : int(1..3)]) <= 2, + and([p_PermutationAsFunction_PermutationFunction_backwards_Function1D + [p_PermutationAsFunction_PermutationFunction_forwards_Function1D[q1]] + = q1 + | q1 : int(1..3)]), + and([p_PermutationAsFunction_PermutationFunction_forwards_Function1D + [p_PermutationAsFunction_PermutationFunction_backwards_Function1D[q1]] + = q1 + | q1 : int(1..3)]) diff --git a/tests/exhaustive/basic/perms/01_representation/int/0011_find_permutation_minSize_2_of_int1_3/expected/model.eprime b/tests/exhaustive/basic/perms/01_representation/int/0011_find_permutation_minSize_2_of_int1_3/expected/model.eprime index 6029393e7f..f3e785113b 100644 --- a/tests/exhaustive/basic/perms/01_representation/int/0011_find_permutation_minSize_2_of_int1_3/expected/model.eprime +++ b/tests/exhaustive/basic/perms/01_representation/int/0011_find_permutation_minSize_2_of_int1_3/expected/model.eprime @@ -1,10 +1,25 @@ language ESSENCE' 1.0 letting n be 3 -find p_PermutationAsFunction_PermutationFunction_Function1D: matrix indexed by [int(1..3)] of int(1..3) -branching on [p_PermutationAsFunction_PermutationFunction_Function1D] +find p_PermutationAsFunction_PermutationFunction_forwards_Function1D: matrix indexed by [int(1..3)] of int(1..3) +find p_PermutationAsFunction_PermutationFunction_backwards_Function1D: matrix indexed by [int(1..3)] of int(1..3) +branching on + [p_PermutationAsFunction_PermutationFunction_forwards_Function1D, + p_PermutationAsFunction_PermutationFunction_backwards_Function1D] such that - allDiff(p_PermutationAsFunction_PermutationFunction_Function1D), - and([or([p_PermutationAsFunction_PermutationFunction_Function1D[q3] = q2 | q3 : int(1..3)]) | q2 : int(1..3)]), - 2 <= sum([toInt(q1 != p_PermutationAsFunction_PermutationFunction_Function1D[q1]) | q1 : int(1..3)]) + allDiff(p_PermutationAsFunction_PermutationFunction_forwards_Function1D), + and([or([p_PermutationAsFunction_PermutationFunction_forwards_Function1D[q3] = q2 | q3 : int(1..3)]) + | q2 : int(1..3)]), + allDiff(p_PermutationAsFunction_PermutationFunction_backwards_Function1D), + and([or([p_PermutationAsFunction_PermutationFunction_backwards_Function1D[q6] = q5 | q6 : int(1..3)]) + | q5 : int(1..3)]), + 2 <= sum([toInt(q1 != p_PermutationAsFunction_PermutationFunction_forwards_Function1D[q1]) | q1 : int(1..3)]), + and([p_PermutationAsFunction_PermutationFunction_backwards_Function1D + [p_PermutationAsFunction_PermutationFunction_forwards_Function1D[q1]] + = q1 + | q1 : int(1..3)]), + and([p_PermutationAsFunction_PermutationFunction_forwards_Function1D + [p_PermutationAsFunction_PermutationFunction_backwards_Function1D[q1]] + = q1 + | q1 : int(1..3)]) diff --git a/tests/exhaustive/basic/perms/01_representation/int/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model.eprime b/tests/exhaustive/basic/perms/01_representation/int/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model.eprime index 43f442968f..96dc518031 100644 --- a/tests/exhaustive/basic/perms/01_representation/int/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model.eprime +++ b/tests/exhaustive/basic/perms/01_representation/int/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model.eprime @@ -1,11 +1,26 @@ language ESSENCE' 1.0 letting n be 4 -find p_PermutationAsFunction_PermutationFunction_Function1D: matrix indexed by [int(1..4)] of int(1..4) -branching on [p_PermutationAsFunction_PermutationFunction_Function1D] +find p_PermutationAsFunction_PermutationFunction_forwards_Function1D: matrix indexed by [int(1..4)] of int(1..4) +find p_PermutationAsFunction_PermutationFunction_backwards_Function1D: matrix indexed by [int(1..4)] of int(1..4) +branching on + [p_PermutationAsFunction_PermutationFunction_forwards_Function1D, + p_PermutationAsFunction_PermutationFunction_backwards_Function1D] such that - allDiff(p_PermutationAsFunction_PermutationFunction_Function1D), - and([or([p_PermutationAsFunction_PermutationFunction_Function1D[q3] = q2 | q3 : int(1..4)]) | q2 : int(1..4)]), - 2 <= sum([toInt(q1 != p_PermutationAsFunction_PermutationFunction_Function1D[q1]) | q1 : int(1..4)]), - sum([toInt(q1 != p_PermutationAsFunction_PermutationFunction_Function1D[q1]) | q1 : int(1..4)]) <= 3 + allDiff(p_PermutationAsFunction_PermutationFunction_forwards_Function1D), + and([or([p_PermutationAsFunction_PermutationFunction_forwards_Function1D[q3] = q2 | q3 : int(1..4)]) + | q2 : int(1..4)]), + allDiff(p_PermutationAsFunction_PermutationFunction_backwards_Function1D), + and([or([p_PermutationAsFunction_PermutationFunction_backwards_Function1D[q6] = q5 | q6 : int(1..4)]) + | q5 : int(1..4)]), + 2 <= sum([toInt(q1 != p_PermutationAsFunction_PermutationFunction_forwards_Function1D[q1]) | q1 : int(1..4)]), + sum([toInt(q1 != p_PermutationAsFunction_PermutationFunction_forwards_Function1D[q1]) | q1 : int(1..4)]) <= 3, + and([p_PermutationAsFunction_PermutationFunction_backwards_Function1D + [p_PermutationAsFunction_PermutationFunction_forwards_Function1D[q1]] + = q1 + | q1 : int(1..4)]), + and([p_PermutationAsFunction_PermutationFunction_forwards_Function1D + [p_PermutationAsFunction_PermutationFunction_backwards_Function1D[q1]] + = q1 + | q1 : int(1..4)]) diff --git a/tests/exhaustive/basic/perms/01_representation/unnamed/0005_find_permutation_size_4_of_int1_4/expected/model.eprime b/tests/exhaustive/basic/perms/01_representation/unnamed/0005_find_permutation_size_4_of_int1_4/expected/model.eprime index 134950077a..a1751d1c86 100644 --- a/tests/exhaustive/basic/perms/01_representation/unnamed/0005_find_permutation_size_4_of_int1_4/expected/model.eprime +++ b/tests/exhaustive/basic/perms/01_representation/unnamed/0005_find_permutation_size_4_of_int1_4/expected/model.eprime @@ -1,9 +1,24 @@ language ESSENCE' 1.0 -find p_PermutationAsFunction_PermutationFunction_Function1D: matrix indexed by [int(1..4)] of int(1..4) -branching on [p_PermutationAsFunction_PermutationFunction_Function1D] +find p_PermutationAsFunction_PermutationFunction_forwards_Function1D: matrix indexed by [int(1..4)] of int(1..4) +find p_PermutationAsFunction_PermutationFunction_backwards_Function1D: matrix indexed by [int(1..4)] of int(1..4) +branching on + [p_PermutationAsFunction_PermutationFunction_forwards_Function1D, + p_PermutationAsFunction_PermutationFunction_backwards_Function1D] such that - allDiff(p_PermutationAsFunction_PermutationFunction_Function1D), - and([or([p_PermutationAsFunction_PermutationFunction_Function1D[q3] = q2 | q3 : int(1..4)]) | q2 : int(1..4)]), - 4 = sum([toInt(q1 != p_PermutationAsFunction_PermutationFunction_Function1D[q1]) | q1 : int(1..4)]) + allDiff(p_PermutationAsFunction_PermutationFunction_forwards_Function1D), + and([or([p_PermutationAsFunction_PermutationFunction_forwards_Function1D[q3] = q2 | q3 : int(1..4)]) + | q2 : int(1..4)]), + allDiff(p_PermutationAsFunction_PermutationFunction_backwards_Function1D), + and([or([p_PermutationAsFunction_PermutationFunction_backwards_Function1D[q6] = q5 | q6 : int(1..4)]) + | q5 : int(1..4)]), + 4 = sum([toInt(q1 != p_PermutationAsFunction_PermutationFunction_forwards_Function1D[q1]) | q1 : int(1..4)]), + and([p_PermutationAsFunction_PermutationFunction_backwards_Function1D + [p_PermutationAsFunction_PermutationFunction_forwards_Function1D[q1]] + = q1 + | q1 : int(1..4)]), + and([p_PermutationAsFunction_PermutationFunction_forwards_Function1D + [p_PermutationAsFunction_PermutationFunction_backwards_Function1D[q1]] + = q1 + | q1 : int(1..4)]) diff --git a/tests/exhaustive/basic/perms/01_representation/unnamed/0006_find_permutation_size_0_of_int1_4/expected/model.eprime b/tests/exhaustive/basic/perms/01_representation/unnamed/0006_find_permutation_size_0_of_int1_4/expected/model.eprime index a03a5e86e3..e1caf81808 100644 --- a/tests/exhaustive/basic/perms/01_representation/unnamed/0006_find_permutation_size_0_of_int1_4/expected/model.eprime +++ b/tests/exhaustive/basic/perms/01_representation/unnamed/0006_find_permutation_size_0_of_int1_4/expected/model.eprime @@ -1,9 +1,24 @@ language ESSENCE' 1.0 -find p_PermutationAsFunction_PermutationFunction_Function1D: matrix indexed by [int(1..4)] of int(1..4) -branching on [p_PermutationAsFunction_PermutationFunction_Function1D] +find p_PermutationAsFunction_PermutationFunction_forwards_Function1D: matrix indexed by [int(1..4)] of int(1..4) +find p_PermutationAsFunction_PermutationFunction_backwards_Function1D: matrix indexed by [int(1..4)] of int(1..4) +branching on + [p_PermutationAsFunction_PermutationFunction_forwards_Function1D, + p_PermutationAsFunction_PermutationFunction_backwards_Function1D] such that - allDiff(p_PermutationAsFunction_PermutationFunction_Function1D), - and([or([p_PermutationAsFunction_PermutationFunction_Function1D[q3] = q2 | q3 : int(1..4)]) | q2 : int(1..4)]), - 0 = sum([toInt(q1 != p_PermutationAsFunction_PermutationFunction_Function1D[q1]) | q1 : int(1..4)]) + allDiff(p_PermutationAsFunction_PermutationFunction_forwards_Function1D), + and([or([p_PermutationAsFunction_PermutationFunction_forwards_Function1D[q3] = q2 | q3 : int(1..4)]) + | q2 : int(1..4)]), + allDiff(p_PermutationAsFunction_PermutationFunction_backwards_Function1D), + and([or([p_PermutationAsFunction_PermutationFunction_backwards_Function1D[q6] = q5 | q6 : int(1..4)]) + | q5 : int(1..4)]), + 0 = sum([toInt(q1 != p_PermutationAsFunction_PermutationFunction_forwards_Function1D[q1]) | q1 : int(1..4)]), + and([p_PermutationAsFunction_PermutationFunction_backwards_Function1D + [p_PermutationAsFunction_PermutationFunction_forwards_Function1D[q1]] + = q1 + | q1 : int(1..4)]), + and([p_PermutationAsFunction_PermutationFunction_forwards_Function1D + [p_PermutationAsFunction_PermutationFunction_backwards_Function1D[q1]] + = q1 + | q1 : int(1..4)]) diff --git a/tests/exhaustive/basic/perms/01_representation/unnamed/0008_find_permutation_of_int1_4/expected/model.eprime b/tests/exhaustive/basic/perms/01_representation/unnamed/0008_find_permutation_of_int1_4/expected/model.eprime index ac93d552d6..055fe5255f 100644 --- a/tests/exhaustive/basic/perms/01_representation/unnamed/0008_find_permutation_of_int1_4/expected/model.eprime +++ b/tests/exhaustive/basic/perms/01_representation/unnamed/0008_find_permutation_of_int1_4/expected/model.eprime @@ -1,8 +1,23 @@ language ESSENCE' 1.0 -find p_PermutationAsFunction_PermutationFunction_Function1D: matrix indexed by [int(1..4)] of int(1..4) -branching on [p_PermutationAsFunction_PermutationFunction_Function1D] +find p_PermutationAsFunction_PermutationFunction_forwards_Function1D: matrix indexed by [int(1..4)] of int(1..4) +find p_PermutationAsFunction_PermutationFunction_backwards_Function1D: matrix indexed by [int(1..4)] of int(1..4) +branching on + [p_PermutationAsFunction_PermutationFunction_forwards_Function1D, + p_PermutationAsFunction_PermutationFunction_backwards_Function1D] such that - allDiff(p_PermutationAsFunction_PermutationFunction_Function1D), - and([or([p_PermutationAsFunction_PermutationFunction_Function1D[q3] = q2 | q3 : int(1..4)]) | q2 : int(1..4)]) + allDiff(p_PermutationAsFunction_PermutationFunction_forwards_Function1D), + and([or([p_PermutationAsFunction_PermutationFunction_forwards_Function1D[q3] = q2 | q3 : int(1..4)]) + | q2 : int(1..4)]), + allDiff(p_PermutationAsFunction_PermutationFunction_backwards_Function1D), + and([or([p_PermutationAsFunction_PermutationFunction_backwards_Function1D[q6] = q5 | q6 : int(1..4)]) + | q5 : int(1..4)]), + and([p_PermutationAsFunction_PermutationFunction_backwards_Function1D + [p_PermutationAsFunction_PermutationFunction_forwards_Function1D[q1]] + = q1 + | q1 : int(1..4)]), + and([p_PermutationAsFunction_PermutationFunction_forwards_Function1D + [p_PermutationAsFunction_PermutationFunction_backwards_Function1D[q1]] + = q1 + | q1 : int(1..4)]) diff --git a/tests/exhaustive/basic/perms/01_representation/unnamed/0010_find_permutation_maxSize_2_of_int1_3/expected/model.eprime b/tests/exhaustive/basic/perms/01_representation/unnamed/0010_find_permutation_maxSize_2_of_int1_3/expected/model.eprime index 95837c9498..a153fa5e65 100644 --- a/tests/exhaustive/basic/perms/01_representation/unnamed/0010_find_permutation_maxSize_2_of_int1_3/expected/model.eprime +++ b/tests/exhaustive/basic/perms/01_representation/unnamed/0010_find_permutation_maxSize_2_of_int1_3/expected/model.eprime @@ -1,9 +1,24 @@ language ESSENCE' 1.0 -find p_PermutationAsFunction_PermutationFunction_Function1D: matrix indexed by [int(1..3)] of int(1..3) -branching on [p_PermutationAsFunction_PermutationFunction_Function1D] +find p_PermutationAsFunction_PermutationFunction_forwards_Function1D: matrix indexed by [int(1..3)] of int(1..3) +find p_PermutationAsFunction_PermutationFunction_backwards_Function1D: matrix indexed by [int(1..3)] of int(1..3) +branching on + [p_PermutationAsFunction_PermutationFunction_forwards_Function1D, + p_PermutationAsFunction_PermutationFunction_backwards_Function1D] such that - allDiff(p_PermutationAsFunction_PermutationFunction_Function1D), - and([or([p_PermutationAsFunction_PermutationFunction_Function1D[q3] = q2 | q3 : int(1..3)]) | q2 : int(1..3)]), - sum([toInt(q1 != p_PermutationAsFunction_PermutationFunction_Function1D[q1]) | q1 : int(1..3)]) <= 2 + allDiff(p_PermutationAsFunction_PermutationFunction_forwards_Function1D), + and([or([p_PermutationAsFunction_PermutationFunction_forwards_Function1D[q3] = q2 | q3 : int(1..3)]) + | q2 : int(1..3)]), + allDiff(p_PermutationAsFunction_PermutationFunction_backwards_Function1D), + and([or([p_PermutationAsFunction_PermutationFunction_backwards_Function1D[q6] = q5 | q6 : int(1..3)]) + | q5 : int(1..3)]), + sum([toInt(q1 != p_PermutationAsFunction_PermutationFunction_forwards_Function1D[q1]) | q1 : int(1..3)]) <= 2, + and([p_PermutationAsFunction_PermutationFunction_backwards_Function1D + [p_PermutationAsFunction_PermutationFunction_forwards_Function1D[q1]] + = q1 + | q1 : int(1..3)]), + and([p_PermutationAsFunction_PermutationFunction_forwards_Function1D + [p_PermutationAsFunction_PermutationFunction_backwards_Function1D[q1]] + = q1 + | q1 : int(1..3)]) diff --git a/tests/exhaustive/basic/perms/01_representation/unnamed/0011_find_permutation_minSize_2_of_int1_3/expected/model.eprime b/tests/exhaustive/basic/perms/01_representation/unnamed/0011_find_permutation_minSize_2_of_int1_3/expected/model.eprime index 7854912481..6193c6a728 100644 --- a/tests/exhaustive/basic/perms/01_representation/unnamed/0011_find_permutation_minSize_2_of_int1_3/expected/model.eprime +++ b/tests/exhaustive/basic/perms/01_representation/unnamed/0011_find_permutation_minSize_2_of_int1_3/expected/model.eprime @@ -1,9 +1,24 @@ language ESSENCE' 1.0 -find p_PermutationAsFunction_PermutationFunction_Function1D: matrix indexed by [int(1..3)] of int(1..3) -branching on [p_PermutationAsFunction_PermutationFunction_Function1D] +find p_PermutationAsFunction_PermutationFunction_forwards_Function1D: matrix indexed by [int(1..3)] of int(1..3) +find p_PermutationAsFunction_PermutationFunction_backwards_Function1D: matrix indexed by [int(1..3)] of int(1..3) +branching on + [p_PermutationAsFunction_PermutationFunction_forwards_Function1D, + p_PermutationAsFunction_PermutationFunction_backwards_Function1D] such that - allDiff(p_PermutationAsFunction_PermutationFunction_Function1D), - and([or([p_PermutationAsFunction_PermutationFunction_Function1D[q3] = q2 | q3 : int(1..3)]) | q2 : int(1..3)]), - 2 <= sum([toInt(q1 != p_PermutationAsFunction_PermutationFunction_Function1D[q1]) | q1 : int(1..3)]) + allDiff(p_PermutationAsFunction_PermutationFunction_forwards_Function1D), + and([or([p_PermutationAsFunction_PermutationFunction_forwards_Function1D[q3] = q2 | q3 : int(1..3)]) + | q2 : int(1..3)]), + allDiff(p_PermutationAsFunction_PermutationFunction_backwards_Function1D), + and([or([p_PermutationAsFunction_PermutationFunction_backwards_Function1D[q6] = q5 | q6 : int(1..3)]) + | q5 : int(1..3)]), + 2 <= sum([toInt(q1 != p_PermutationAsFunction_PermutationFunction_forwards_Function1D[q1]) | q1 : int(1..3)]), + and([p_PermutationAsFunction_PermutationFunction_backwards_Function1D + [p_PermutationAsFunction_PermutationFunction_forwards_Function1D[q1]] + = q1 + | q1 : int(1..3)]), + and([p_PermutationAsFunction_PermutationFunction_forwards_Function1D + [p_PermutationAsFunction_PermutationFunction_backwards_Function1D[q1]] + = q1 + | q1 : int(1..3)]) diff --git a/tests/exhaustive/basic/perms/01_representation/unnamed/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model.eprime b/tests/exhaustive/basic/perms/01_representation/unnamed/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model.eprime index 4292a59345..110c3278cb 100644 --- a/tests/exhaustive/basic/perms/01_representation/unnamed/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model.eprime +++ b/tests/exhaustive/basic/perms/01_representation/unnamed/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/expected/model.eprime @@ -1,10 +1,25 @@ language ESSENCE' 1.0 -find p_PermutationAsFunction_PermutationFunction_Function1D: matrix indexed by [int(1..4)] of int(1..4) -branching on [p_PermutationAsFunction_PermutationFunction_Function1D] +find p_PermutationAsFunction_PermutationFunction_forwards_Function1D: matrix indexed by [int(1..4)] of int(1..4) +find p_PermutationAsFunction_PermutationFunction_backwards_Function1D: matrix indexed by [int(1..4)] of int(1..4) +branching on + [p_PermutationAsFunction_PermutationFunction_forwards_Function1D, + p_PermutationAsFunction_PermutationFunction_backwards_Function1D] such that - allDiff(p_PermutationAsFunction_PermutationFunction_Function1D), - and([or([p_PermutationAsFunction_PermutationFunction_Function1D[q3] = q2 | q3 : int(1..4)]) | q2 : int(1..4)]), - 2 <= sum([toInt(q1 != p_PermutationAsFunction_PermutationFunction_Function1D[q1]) | q1 : int(1..4)]), - sum([toInt(q1 != p_PermutationAsFunction_PermutationFunction_Function1D[q1]) | q1 : int(1..4)]) <= 3 + allDiff(p_PermutationAsFunction_PermutationFunction_forwards_Function1D), + and([or([p_PermutationAsFunction_PermutationFunction_forwards_Function1D[q3] = q2 | q3 : int(1..4)]) + | q2 : int(1..4)]), + allDiff(p_PermutationAsFunction_PermutationFunction_backwards_Function1D), + and([or([p_PermutationAsFunction_PermutationFunction_backwards_Function1D[q6] = q5 | q6 : int(1..4)]) + | q5 : int(1..4)]), + 2 <= sum([toInt(q1 != p_PermutationAsFunction_PermutationFunction_forwards_Function1D[q1]) | q1 : int(1..4)]), + sum([toInt(q1 != p_PermutationAsFunction_PermutationFunction_forwards_Function1D[q1]) | q1 : int(1..4)]) <= 3, + and([p_PermutationAsFunction_PermutationFunction_backwards_Function1D + [p_PermutationAsFunction_PermutationFunction_forwards_Function1D[q1]] + = q1 + | q1 : int(1..4)]), + and([p_PermutationAsFunction_PermutationFunction_forwards_Function1D + [p_PermutationAsFunction_PermutationFunction_backwards_Function1D[q1]] + = q1 + | q1 : int(1..4)]) diff --git a/tests/exhaustive/basic/perms/02_cardinality/enum/0001_given_permutation_in_param/expected/model-permutation.eprime-param b/tests/exhaustive/basic/perms/02_cardinality/enum/0001_given_permutation_in_param/expected/model-permutation.eprime-param index c2bddee0e8..6ab791d030 100644 --- a/tests/exhaustive/basic/perms/02_cardinality/enum/0001_given_permutation_in_param/expected/model-permutation.eprime-param +++ b/tests/exhaustive/basic/perms/02_cardinality/enum/0001_given_permutation_in_param/expected/model-permutation.eprime-param @@ -1,3 +1,4 @@ language ESSENCE' 1.0 -letting p_PermutationAsFunction_PermutationFunction_Function1D be [3, 2, 4, 1; int(1..4)] +letting p_PermutationAsFunction_PermutationFunction_forwards_Function1D be [3, 2, 4, 1; int(1..4)] +letting p_PermutationAsFunction_PermutationFunction_backwards_Function1D be [4, 2, 1, 3; int(1..4)] diff --git a/tests/exhaustive/basic/perms/02_cardinality/enum/0001_given_permutation_in_param/expected/model.eprime b/tests/exhaustive/basic/perms/02_cardinality/enum/0001_given_permutation_in_param/expected/model.eprime index e05a7bb583..7f81559bba 100644 --- a/tests/exhaustive/basic/perms/02_cardinality/enum/0001_given_permutation_in_param/expected/model.eprime +++ b/tests/exhaustive/basic/perms/02_cardinality/enum/0001_given_permutation_in_param/expected/model.eprime @@ -1,7 +1,8 @@ language ESSENCE' 1.0 -given p_PermutationAsFunction_PermutationFunction_Function1D: matrix indexed by [int(1..4)] of int(1..4) +given p_PermutationAsFunction_PermutationFunction_forwards_Function1D: matrix indexed by [int(1..4)] of int(1..4) +given p_PermutationAsFunction_PermutationFunction_backwards_Function1D: matrix indexed by [int(1..4)] of int(1..4) find i: int(0..10) branching on [i] -such that i = sum([toInt(q1 != p_PermutationAsFunction_PermutationFunction_Function1D[q1]) | q1 : int(1..4)]) +such that i = sum([toInt(q1 != p_PermutationAsFunction_PermutationFunction_forwards_Function1D[q1]) | q1 : int(1..4)]) diff --git a/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model.eprime b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model.eprime index 27f6b498e7..2f4058e0b5 100644 --- a/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model.eprime +++ b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/expected/model.eprime @@ -1,11 +1,26 @@ language ESSENCE' 1.0 -find p_PermutationAsFunction_PermutationFunction_Function1D: matrix indexed by [int(1..6)] of int(1..6) +find p_PermutationAsFunction_PermutationFunction_forwards_Function1D: matrix indexed by [int(1..6)] of int(1..6) +find p_PermutationAsFunction_PermutationFunction_backwards_Function1D: matrix indexed by [int(1..6)] of int(1..6) find i: int(0..10) -branching on [p_PermutationAsFunction_PermutationFunction_Function1D, i] +branching on + [p_PermutationAsFunction_PermutationFunction_forwards_Function1D, + p_PermutationAsFunction_PermutationFunction_backwards_Function1D, i] such that - i = sum([toInt(q5 != p_PermutationAsFunction_PermutationFunction_Function1D[q5]) | q5 : int(1..6)]), - allDiff(p_PermutationAsFunction_PermutationFunction_Function1D), - and([or([p_PermutationAsFunction_PermutationFunction_Function1D[q3] = q2 | q3 : int(1..6)]) | q2 : int(1..6)]), - 4 = sum([toInt(q1 != p_PermutationAsFunction_PermutationFunction_Function1D[q1]) | q1 : int(1..6)]) + i = sum([toInt(q8 != p_PermutationAsFunction_PermutationFunction_forwards_Function1D[q8]) | q8 : int(1..6)]), + allDiff(p_PermutationAsFunction_PermutationFunction_forwards_Function1D), + and([or([p_PermutationAsFunction_PermutationFunction_forwards_Function1D[q3] = q2 | q3 : int(1..6)]) + | q2 : int(1..6)]), + allDiff(p_PermutationAsFunction_PermutationFunction_backwards_Function1D), + and([or([p_PermutationAsFunction_PermutationFunction_backwards_Function1D[q6] = q5 | q6 : int(1..6)]) + | q5 : int(1..6)]), + 4 = sum([toInt(q1 != p_PermutationAsFunction_PermutationFunction_forwards_Function1D[q1]) | q1 : int(1..6)]), + and([p_PermutationAsFunction_PermutationFunction_backwards_Function1D + [p_PermutationAsFunction_PermutationFunction_forwards_Function1D[q1]] + = q1 + | q1 : int(1..6)]), + and([p_PermutationAsFunction_PermutationFunction_forwards_Function1D + [p_PermutationAsFunction_PermutationFunction_backwards_Function1D[q1]] + = q1 + | q1 : int(1..6)]) diff --git a/tests/exhaustive/basic/perms/02_cardinality/int/0001_given_permutation_in_param/expected/model-permutation.eprime-param b/tests/exhaustive/basic/perms/02_cardinality/int/0001_given_permutation_in_param/expected/model-permutation.eprime-param index c2bddee0e8..6ab791d030 100644 --- a/tests/exhaustive/basic/perms/02_cardinality/int/0001_given_permutation_in_param/expected/model-permutation.eprime-param +++ b/tests/exhaustive/basic/perms/02_cardinality/int/0001_given_permutation_in_param/expected/model-permutation.eprime-param @@ -1,3 +1,4 @@ language ESSENCE' 1.0 -letting p_PermutationAsFunction_PermutationFunction_Function1D be [3, 2, 4, 1; int(1..4)] +letting p_PermutationAsFunction_PermutationFunction_forwards_Function1D be [3, 2, 4, 1; int(1..4)] +letting p_PermutationAsFunction_PermutationFunction_backwards_Function1D be [4, 2, 1, 3; int(1..4)] diff --git a/tests/exhaustive/basic/perms/02_cardinality/int/0001_given_permutation_in_param/expected/model.eprime b/tests/exhaustive/basic/perms/02_cardinality/int/0001_given_permutation_in_param/expected/model.eprime index e05a7bb583..7f81559bba 100644 --- a/tests/exhaustive/basic/perms/02_cardinality/int/0001_given_permutation_in_param/expected/model.eprime +++ b/tests/exhaustive/basic/perms/02_cardinality/int/0001_given_permutation_in_param/expected/model.eprime @@ -1,7 +1,8 @@ language ESSENCE' 1.0 -given p_PermutationAsFunction_PermutationFunction_Function1D: matrix indexed by [int(1..4)] of int(1..4) +given p_PermutationAsFunction_PermutationFunction_forwards_Function1D: matrix indexed by [int(1..4)] of int(1..4) +given p_PermutationAsFunction_PermutationFunction_backwards_Function1D: matrix indexed by [int(1..4)] of int(1..4) find i: int(0..10) branching on [i] -such that i = sum([toInt(q1 != p_PermutationAsFunction_PermutationFunction_Function1D[q1]) | q1 : int(1..4)]) +such that i = sum([toInt(q1 != p_PermutationAsFunction_PermutationFunction_forwards_Function1D[q1]) | q1 : int(1..4)]) diff --git a/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model.eprime b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model.eprime index 27f6b498e7..2f4058e0b5 100644 --- a/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model.eprime +++ b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/expected/model.eprime @@ -1,11 +1,26 @@ language ESSENCE' 1.0 -find p_PermutationAsFunction_PermutationFunction_Function1D: matrix indexed by [int(1..6)] of int(1..6) +find p_PermutationAsFunction_PermutationFunction_forwards_Function1D: matrix indexed by [int(1..6)] of int(1..6) +find p_PermutationAsFunction_PermutationFunction_backwards_Function1D: matrix indexed by [int(1..6)] of int(1..6) find i: int(0..10) -branching on [p_PermutationAsFunction_PermutationFunction_Function1D, i] +branching on + [p_PermutationAsFunction_PermutationFunction_forwards_Function1D, + p_PermutationAsFunction_PermutationFunction_backwards_Function1D, i] such that - i = sum([toInt(q5 != p_PermutationAsFunction_PermutationFunction_Function1D[q5]) | q5 : int(1..6)]), - allDiff(p_PermutationAsFunction_PermutationFunction_Function1D), - and([or([p_PermutationAsFunction_PermutationFunction_Function1D[q3] = q2 | q3 : int(1..6)]) | q2 : int(1..6)]), - 4 = sum([toInt(q1 != p_PermutationAsFunction_PermutationFunction_Function1D[q1]) | q1 : int(1..6)]) + i = sum([toInt(q8 != p_PermutationAsFunction_PermutationFunction_forwards_Function1D[q8]) | q8 : int(1..6)]), + allDiff(p_PermutationAsFunction_PermutationFunction_forwards_Function1D), + and([or([p_PermutationAsFunction_PermutationFunction_forwards_Function1D[q3] = q2 | q3 : int(1..6)]) + | q2 : int(1..6)]), + allDiff(p_PermutationAsFunction_PermutationFunction_backwards_Function1D), + and([or([p_PermutationAsFunction_PermutationFunction_backwards_Function1D[q6] = q5 | q6 : int(1..6)]) + | q5 : int(1..6)]), + 4 = sum([toInt(q1 != p_PermutationAsFunction_PermutationFunction_forwards_Function1D[q1]) | q1 : int(1..6)]), + and([p_PermutationAsFunction_PermutationFunction_backwards_Function1D + [p_PermutationAsFunction_PermutationFunction_forwards_Function1D[q1]] + = q1 + | q1 : int(1..6)]), + and([p_PermutationAsFunction_PermutationFunction_forwards_Function1D + [p_PermutationAsFunction_PermutationFunction_backwards_Function1D[q1]] + = q1 + | q1 : int(1..6)]) diff --git a/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model.eprime b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model.eprime index 27f6b498e7..2f4058e0b5 100644 --- a/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model.eprime +++ b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/expected/model.eprime @@ -1,11 +1,26 @@ language ESSENCE' 1.0 -find p_PermutationAsFunction_PermutationFunction_Function1D: matrix indexed by [int(1..6)] of int(1..6) +find p_PermutationAsFunction_PermutationFunction_forwards_Function1D: matrix indexed by [int(1..6)] of int(1..6) +find p_PermutationAsFunction_PermutationFunction_backwards_Function1D: matrix indexed by [int(1..6)] of int(1..6) find i: int(0..10) -branching on [p_PermutationAsFunction_PermutationFunction_Function1D, i] +branching on + [p_PermutationAsFunction_PermutationFunction_forwards_Function1D, + p_PermutationAsFunction_PermutationFunction_backwards_Function1D, i] such that - i = sum([toInt(q5 != p_PermutationAsFunction_PermutationFunction_Function1D[q5]) | q5 : int(1..6)]), - allDiff(p_PermutationAsFunction_PermutationFunction_Function1D), - and([or([p_PermutationAsFunction_PermutationFunction_Function1D[q3] = q2 | q3 : int(1..6)]) | q2 : int(1..6)]), - 4 = sum([toInt(q1 != p_PermutationAsFunction_PermutationFunction_Function1D[q1]) | q1 : int(1..6)]) + i = sum([toInt(q8 != p_PermutationAsFunction_PermutationFunction_forwards_Function1D[q8]) | q8 : int(1..6)]), + allDiff(p_PermutationAsFunction_PermutationFunction_forwards_Function1D), + and([or([p_PermutationAsFunction_PermutationFunction_forwards_Function1D[q3] = q2 | q3 : int(1..6)]) + | q2 : int(1..6)]), + allDiff(p_PermutationAsFunction_PermutationFunction_backwards_Function1D), + and([or([p_PermutationAsFunction_PermutationFunction_backwards_Function1D[q6] = q5 | q6 : int(1..6)]) + | q5 : int(1..6)]), + 4 = sum([toInt(q1 != p_PermutationAsFunction_PermutationFunction_forwards_Function1D[q1]) | q1 : int(1..6)]), + and([p_PermutationAsFunction_PermutationFunction_backwards_Function1D + [p_PermutationAsFunction_PermutationFunction_forwards_Function1D[q1]] + = q1 + | q1 : int(1..6)]), + and([p_PermutationAsFunction_PermutationFunction_forwards_Function1D + [p_PermutationAsFunction_PermutationFunction_backwards_Function1D[q1]] + = q1 + | q1 : int(1..6)]) diff --git a/tests/exhaustive/basic/perms/03_generators/enum/0001_given_permutation_in_generator/expected/model-permutation.eprime-param b/tests/exhaustive/basic/perms/03_generators/enum/0001_given_permutation_in_generator/expected/model-permutation.eprime-param index c2bddee0e8..6ab791d030 100644 --- a/tests/exhaustive/basic/perms/03_generators/enum/0001_given_permutation_in_generator/expected/model-permutation.eprime-param +++ b/tests/exhaustive/basic/perms/03_generators/enum/0001_given_permutation_in_generator/expected/model-permutation.eprime-param @@ -1,3 +1,4 @@ language ESSENCE' 1.0 -letting p_PermutationAsFunction_PermutationFunction_Function1D be [3, 2, 4, 1; int(1..4)] +letting p_PermutationAsFunction_PermutationFunction_forwards_Function1D be [3, 2, 4, 1; int(1..4)] +letting p_PermutationAsFunction_PermutationFunction_backwards_Function1D be [4, 2, 1, 3; int(1..4)] diff --git a/tests/exhaustive/basic/perms/03_generators/enum/0001_given_permutation_in_generator/expected/model.eprime b/tests/exhaustive/basic/perms/03_generators/enum/0001_given_permutation_in_generator/expected/model.eprime index 2637d263cd..86c3940673 100644 --- a/tests/exhaustive/basic/perms/03_generators/enum/0001_given_permutation_in_generator/expected/model.eprime +++ b/tests/exhaustive/basic/perms/03_generators/enum/0001_given_permutation_in_generator/expected/model.eprime @@ -1,13 +1,15 @@ language ESSENCE' 1.0 -given p_PermutationAsFunction_PermutationFunction_Function1D: matrix indexed by [int(1..4)] of int(1..4) +given p_PermutationAsFunction_PermutationFunction_forwards_Function1D: matrix indexed by [int(1..4)] of int(1..4) +given p_PermutationAsFunction_PermutationFunction_backwards_Function1D: matrix indexed by [int(1..4)] of int(1..4) find s_Explicit_1: matrix indexed by [int(1..3)] of int(1..4) find s_Explicit_2: matrix indexed by [int(1..3)] of int(1..4) branching on [s_Explicit_1, s_Explicit_2] such that - and([or([s_Explicit_1[q8] = q10 /\ s_Explicit_2[q8] = p_PermutationAsFunction_PermutationFunction_Function1D[q10] + and([or([s_Explicit_1[q8] = q10 /\ + s_Explicit_2[q8] = p_PermutationAsFunction_PermutationFunction_forwards_Function1D[q10] | q8 : int(1..3)]) - | q10 : int(1..4), q10 != p_PermutationAsFunction_PermutationFunction_Function1D[q10]]), + | q10 : int(1..4), q10 != p_PermutationAsFunction_PermutationFunction_forwards_Function1D[q10]]), and([flatten([[s_Explicit_1[q1]; int(1)], [s_Explicit_2[q1]; int(1)]; int(1..2)]) - or([s_Explicit_1[q12] = q14 /\ s_Explicit_2[q12] = p_PermutationAsFunction_PermutationFunction_Function1D[q14] - | q12 : int(1..3)]) - | q14 : int(1..4)]), + and([q17 != p_PermutationAsFunction_PermutationFunction_forwards_Function1D[q17] -> + or([s_Explicit_1[q15] = q17 /\ + s_Explicit_2[q15] = p_PermutationAsFunction_PermutationFunction_forwards_Function1D[q17] + | q15 : int(1..3)]) + | q17 : int(1..4)]), and([flatten([[s_Explicit_1[q1]; int(1)], [s_Explicit_2[q1]; int(1)]; int(1..2)]) - q11 != p_PermutationAsFunction_PermutationFunction_Function1D[q11] - | q11 : int(1..4)]), - allDiff(p_PermutationAsFunction_PermutationFunction_Function1D), - and([or([p_PermutationAsFunction_PermutationFunction_Function1D[q3] = q2 | q3 : int(1..4)]) | q2 : int(1..4)]), - 3 = sum([toInt(q1 != p_PermutationAsFunction_PermutationFunction_Function1D[q1]) | q1 : int(1..4)]) + and([q14 != p_PermutationAsFunction_PermutationFunction_forwards_Function1D[q14] -> + q14 != p_PermutationAsFunction_PermutationFunction_forwards_Function1D[q14] + | q14 : int(1..4)]), + allDiff(p_PermutationAsFunction_PermutationFunction_forwards_Function1D), + and([or([p_PermutationAsFunction_PermutationFunction_forwards_Function1D[q3] = q2 | q3 : int(1..4)]) + | q2 : int(1..4)]), + allDiff(p_PermutationAsFunction_PermutationFunction_backwards_Function1D), + and([or([p_PermutationAsFunction_PermutationFunction_backwards_Function1D[q6] = q5 | q6 : int(1..4)]) + | q5 : int(1..4)]), + 3 = sum([toInt(q1 != p_PermutationAsFunction_PermutationFunction_forwards_Function1D[q1]) | q1 : int(1..4)]), + and([p_PermutationAsFunction_PermutationFunction_backwards_Function1D + [p_PermutationAsFunction_PermutationFunction_forwards_Function1D[q1]] + = q1 + | q1 : int(1..4)]), + and([p_PermutationAsFunction_PermutationFunction_forwards_Function1D + [p_PermutationAsFunction_PermutationFunction_backwards_Function1D[q1]] + = q1 + | q1 : int(1..4)]) diff --git a/tests/exhaustive/basic/perms/03_generators/int/0001_given_permutation_in_generator/expected/model-permutation.eprime-param b/tests/exhaustive/basic/perms/03_generators/int/0001_given_permutation_in_generator/expected/model-permutation.eprime-param index c2bddee0e8..6ab791d030 100644 --- a/tests/exhaustive/basic/perms/03_generators/int/0001_given_permutation_in_generator/expected/model-permutation.eprime-param +++ b/tests/exhaustive/basic/perms/03_generators/int/0001_given_permutation_in_generator/expected/model-permutation.eprime-param @@ -1,3 +1,4 @@ language ESSENCE' 1.0 -letting p_PermutationAsFunction_PermutationFunction_Function1D be [3, 2, 4, 1; int(1..4)] +letting p_PermutationAsFunction_PermutationFunction_forwards_Function1D be [3, 2, 4, 1; int(1..4)] +letting p_PermutationAsFunction_PermutationFunction_backwards_Function1D be [4, 2, 1, 3; int(1..4)] diff --git a/tests/exhaustive/basic/perms/03_generators/int/0001_given_permutation_in_generator/expected/model.eprime b/tests/exhaustive/basic/perms/03_generators/int/0001_given_permutation_in_generator/expected/model.eprime index 2637d263cd..86c3940673 100644 --- a/tests/exhaustive/basic/perms/03_generators/int/0001_given_permutation_in_generator/expected/model.eprime +++ b/tests/exhaustive/basic/perms/03_generators/int/0001_given_permutation_in_generator/expected/model.eprime @@ -1,13 +1,15 @@ language ESSENCE' 1.0 -given p_PermutationAsFunction_PermutationFunction_Function1D: matrix indexed by [int(1..4)] of int(1..4) +given p_PermutationAsFunction_PermutationFunction_forwards_Function1D: matrix indexed by [int(1..4)] of int(1..4) +given p_PermutationAsFunction_PermutationFunction_backwards_Function1D: matrix indexed by [int(1..4)] of int(1..4) find s_Explicit_1: matrix indexed by [int(1..3)] of int(1..4) find s_Explicit_2: matrix indexed by [int(1..3)] of int(1..4) branching on [s_Explicit_1, s_Explicit_2] such that - and([or([s_Explicit_1[q8] = q10 /\ s_Explicit_2[q8] = p_PermutationAsFunction_PermutationFunction_Function1D[q10] + and([or([s_Explicit_1[q8] = q10 /\ + s_Explicit_2[q8] = p_PermutationAsFunction_PermutationFunction_forwards_Function1D[q10] | q8 : int(1..3)]) - | q10 : int(1..4), q10 != p_PermutationAsFunction_PermutationFunction_Function1D[q10]]), + | q10 : int(1..4), q10 != p_PermutationAsFunction_PermutationFunction_forwards_Function1D[q10]]), and([flatten([[s_Explicit_1[q1]; int(1)], [s_Explicit_2[q1]; int(1)]; int(1..2)]) - or([s_Explicit_1[q12] = q14 /\ s_Explicit_2[q12] = p_PermutationAsFunction_PermutationFunction_Function1D[q14] - | q12 : int(1..3)]) - | q14 : int(1..4)]), + and([q17 != p_PermutationAsFunction_PermutationFunction_forwards_Function1D[q17] -> + or([s_Explicit_1[q15] = q17 /\ + s_Explicit_2[q15] = p_PermutationAsFunction_PermutationFunction_forwards_Function1D[q17] + | q15 : int(1..3)]) + | q17 : int(1..4)]), and([flatten([[s_Explicit_1[q1]; int(1)], [s_Explicit_2[q1]; int(1)]; int(1..2)]) - or([s_Explicit_1[q12] = q14 /\ s_Explicit_2[q12] = p_PermutationAsFunction_PermutationFunction_Function1D[q14] - | q12 : int(1..3)]) - | q14 : int(1..4)]), + and([q17 != p_PermutationAsFunction_PermutationFunction_forwards_Function1D[q17] -> + or([s_Explicit_1[q15] = q17 /\ + s_Explicit_2[q15] = p_PermutationAsFunction_PermutationFunction_forwards_Function1D[q17] + | q15 : int(1..3)]) + | q17 : int(1..4)]), and([flatten([[s_Explicit_1[q1]; int(1)], [s_Explicit_2[q1]; int(1)]; int(1..2)]) - or([s_Explicit_1[q12] = q14 /\ s_Explicit_2[q12] = p_PermutationAsFunction_PermutationFunction_Function1D[q14] - | q12 : int(1..3)]) - | q14 : int(1..4)]), + and([q17 != p_PermutationAsFunction_PermutationFunction_forwards_Function1D[q17] -> + or([s_Explicit_1[q15] = q17 /\ + s_Explicit_2[q15] = p_PermutationAsFunction_PermutationFunction_forwards_Function1D[q17] + | q15 : int(1..3)]) + | q17 : int(1..4)]), and([flatten([[s_Explicit_1[q1]; int(1)], [s_Explicit_2[q1]; int(1)]; int(1..2)]) = 2, i <= 3, j >= 3, j <= 4, j = - [i, catchUndef(p_PermutationAsFunction_PermutationFunction_Function1D[i], 0); int(1..2)] - [toInt(or([q6 = i | q6 : int(1..4)])) + 1], - allDiff(p_PermutationAsFunction_PermutationFunction_Function1D), - and([or([p_PermutationAsFunction_PermutationFunction_Function1D[q3] = q2 | q3 : int(1..4)]) | q2 : int(1..4)]) + [i, catchUndef(p_PermutationAsFunction_PermutationFunction_forwards_Function1D[i], 0); int(1..2)] + [toInt(or([q9 = i | q9 : int(1..4)])) + 1], + allDiff(p_PermutationAsFunction_PermutationFunction_forwards_Function1D), + and([or([p_PermutationAsFunction_PermutationFunction_forwards_Function1D[q3] = q2 | q3 : int(1..4)]) + | q2 : int(1..4)]), + allDiff(p_PermutationAsFunction_PermutationFunction_backwards_Function1D), + and([or([p_PermutationAsFunction_PermutationFunction_backwards_Function1D[q6] = q5 | q6 : int(1..4)]) + | q5 : int(1..4)]), + and([p_PermutationAsFunction_PermutationFunction_backwards_Function1D + [p_PermutationAsFunction_PermutationFunction_forwards_Function1D[q1]] + = q1 + | q1 : int(1..4)]), + and([p_PermutationAsFunction_PermutationFunction_forwards_Function1D + [p_PermutationAsFunction_PermutationFunction_backwards_Function1D[q1]] + = q1 + | q1 : int(1..4)]) diff --git a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model.eprime b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model.eprime index d74675d6b2..5b1394ec64 100644 --- a/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model.eprime +++ b/tests/exhaustive/basic/perms/04_image/unnamed/0007_find_permutation_find_unnameds/expected/model.eprime @@ -1,17 +1,32 @@ language ESSENCE' 1.0 find i: int(1..7) -find p_PermutationAsFunction_PermutationFunction_Function1D: matrix indexed by [int(1..7)] of int(1..7) +find p_PermutationAsFunction_PermutationFunction_forwards_Function1D: matrix indexed by [int(1..7)] of int(1..7) +find p_PermutationAsFunction_PermutationFunction_backwards_Function1D: matrix indexed by [int(1..7)] of int(1..7) find j: int(1..7) -branching on [i, p_PermutationAsFunction_PermutationFunction_Function1D, j] +branching on + [i, p_PermutationAsFunction_PermutationFunction_forwards_Function1D, + p_PermutationAsFunction_PermutationFunction_backwards_Function1D, j] such that j = - [i, catchUndef(p_PermutationAsFunction_PermutationFunction_Function1D[i], 0); int(1..2)] - [toInt(or([q6 = i | q6 : int(1..7)])) + 1], - sum([toInt(q13 != p_PermutationAsFunction_PermutationFunction_Function1D[q13]) * - catchUndef(toInt(q13 != p_PermutationAsFunction_PermutationFunction_Function1D[q13]), 0) - | q13 : int(1..7)]) + [i, catchUndef(p_PermutationAsFunction_PermutationFunction_forwards_Function1D[i], 0); int(1..2)] + [toInt(or([q9 = i | q9 : int(1..7)])) + 1], + sum([toInt(q16 != p_PermutationAsFunction_PermutationFunction_forwards_Function1D[q16]) * + catchUndef(toInt(q16 != p_PermutationAsFunction_PermutationFunction_forwards_Function1D[q16]), 0) + | q16 : int(1..7)]) = 3, - allDiff(p_PermutationAsFunction_PermutationFunction_Function1D), - and([or([p_PermutationAsFunction_PermutationFunction_Function1D[q3] = q2 | q3 : int(1..7)]) | q2 : int(1..7)]) + allDiff(p_PermutationAsFunction_PermutationFunction_forwards_Function1D), + and([or([p_PermutationAsFunction_PermutationFunction_forwards_Function1D[q3] = q2 | q3 : int(1..7)]) + | q2 : int(1..7)]), + allDiff(p_PermutationAsFunction_PermutationFunction_backwards_Function1D), + and([or([p_PermutationAsFunction_PermutationFunction_backwards_Function1D[q6] = q5 | q6 : int(1..7)]) + | q5 : int(1..7)]), + and([p_PermutationAsFunction_PermutationFunction_backwards_Function1D + [p_PermutationAsFunction_PermutationFunction_forwards_Function1D[q1]] + = q1 + | q1 : int(1..7)]), + and([p_PermutationAsFunction_PermutationFunction_forwards_Function1D + [p_PermutationAsFunction_PermutationFunction_backwards_Function1D[q1]] + = q1 + | q1 : int(1..7)]) diff --git a/tests/exhaustive/basic/perms/05_equality/enum/0001_given_permutations_in_param/expected/model-permutation.eprime-param b/tests/exhaustive/basic/perms/05_equality/enum/0001_given_permutations_in_param/expected/model-permutation.eprime-param index 5a448d7146..b39cbb8aa3 100644 --- a/tests/exhaustive/basic/perms/05_equality/enum/0001_given_permutations_in_param/expected/model-permutation.eprime-param +++ b/tests/exhaustive/basic/perms/05_equality/enum/0001_given_permutations_in_param/expected/model-permutation.eprime-param @@ -1,4 +1,6 @@ language ESSENCE' 1.0 -letting p_PermutationAsFunction_PermutationFunction_Function1D be [3, 2, 4, 1; int(1..4)] -letting q_PermutationAsFunction_PermutationFunction_Function1D be [3, 2, 4, 1; int(1..4)] +letting p_PermutationAsFunction_PermutationFunction_forwards_Function1D be [3, 2, 4, 1; int(1..4)] +letting p_PermutationAsFunction_PermutationFunction_backwards_Function1D be [4, 2, 1, 3; int(1..4)] +letting q_PermutationAsFunction_PermutationFunction_forwards_Function1D be [3, 2, 4, 1; int(1..4)] +letting q_PermutationAsFunction_PermutationFunction_backwards_Function1D be [4, 2, 1, 3; int(1..4)] diff --git a/tests/exhaustive/basic/perms/05_equality/enum/0001_given_permutations_in_param/expected/model.eprime b/tests/exhaustive/basic/perms/05_equality/enum/0001_given_permutations_in_param/expected/model.eprime index 167dc8f366..34a4be8834 100644 --- a/tests/exhaustive/basic/perms/05_equality/enum/0001_given_permutations_in_param/expected/model.eprime +++ b/tests/exhaustive/basic/perms/05_equality/enum/0001_given_permutations_in_param/expected/model.eprime @@ -1,12 +1,18 @@ language ESSENCE' 1.0 -given p_PermutationAsFunction_PermutationFunction_Function1D: matrix indexed by [int(1..4)] of int(1..4) -given q_PermutationAsFunction_PermutationFunction_Function1D: matrix indexed by [int(1..4)] of int(1..4) +given p_PermutationAsFunction_PermutationFunction_forwards_Function1D: matrix indexed by [int(1..4)] of int(1..4) +given p_PermutationAsFunction_PermutationFunction_backwards_Function1D: matrix indexed by [int(1..4)] of int(1..4) +given q_PermutationAsFunction_PermutationFunction_forwards_Function1D: matrix indexed by [int(1..4)] of int(1..4) +given q_PermutationAsFunction_PermutationFunction_backwards_Function1D: matrix indexed by [int(1..4)] of int(1..4) find b: bool branching on [b] such that b = - and([p_PermutationAsFunction_PermutationFunction_Function1D[q1] = - q_PermutationAsFunction_PermutationFunction_Function1D[q1] - | q1 : int(1..4)]) + (and([p_PermutationAsFunction_PermutationFunction_forwards_Function1D[q1] = + q_PermutationAsFunction_PermutationFunction_forwards_Function1D[q1] + | q1 : int(1..4)]) + /\ + and([p_PermutationAsFunction_PermutationFunction_backwards_Function1D[q3] = + q_PermutationAsFunction_PermutationFunction_backwards_Function1D[q3] + | q3 : int(1..4)])) diff --git a/tests/exhaustive/basic/perms/05_equality/enum/0002_given_permutations_in_param/expected/model-permutation.eprime-param b/tests/exhaustive/basic/perms/05_equality/enum/0002_given_permutations_in_param/expected/model-permutation.eprime-param index fea0f3fb24..ee717be670 100644 --- a/tests/exhaustive/basic/perms/05_equality/enum/0002_given_permutations_in_param/expected/model-permutation.eprime-param +++ b/tests/exhaustive/basic/perms/05_equality/enum/0002_given_permutations_in_param/expected/model-permutation.eprime-param @@ -1,4 +1,6 @@ language ESSENCE' 1.0 -letting p_PermutationAsFunction_PermutationFunction_Function1D be [3, 2, 4, 1; int(1..4)] -letting q_PermutationAsFunction_PermutationFunction_Function1D be [2, 4, 3, 1; int(1..4)] +letting p_PermutationAsFunction_PermutationFunction_forwards_Function1D be [3, 2, 4, 1; int(1..4)] +letting p_PermutationAsFunction_PermutationFunction_backwards_Function1D be [4, 2, 1, 3; int(1..4)] +letting q_PermutationAsFunction_PermutationFunction_forwards_Function1D be [2, 4, 3, 1; int(1..4)] +letting q_PermutationAsFunction_PermutationFunction_backwards_Function1D be [4, 1, 3, 2; int(1..4)] diff --git a/tests/exhaustive/basic/perms/05_equality/enum/0002_given_permutations_in_param/expected/model.eprime b/tests/exhaustive/basic/perms/05_equality/enum/0002_given_permutations_in_param/expected/model.eprime index 167dc8f366..34a4be8834 100644 --- a/tests/exhaustive/basic/perms/05_equality/enum/0002_given_permutations_in_param/expected/model.eprime +++ b/tests/exhaustive/basic/perms/05_equality/enum/0002_given_permutations_in_param/expected/model.eprime @@ -1,12 +1,18 @@ language ESSENCE' 1.0 -given p_PermutationAsFunction_PermutationFunction_Function1D: matrix indexed by [int(1..4)] of int(1..4) -given q_PermutationAsFunction_PermutationFunction_Function1D: matrix indexed by [int(1..4)] of int(1..4) +given p_PermutationAsFunction_PermutationFunction_forwards_Function1D: matrix indexed by [int(1..4)] of int(1..4) +given p_PermutationAsFunction_PermutationFunction_backwards_Function1D: matrix indexed by [int(1..4)] of int(1..4) +given q_PermutationAsFunction_PermutationFunction_forwards_Function1D: matrix indexed by [int(1..4)] of int(1..4) +given q_PermutationAsFunction_PermutationFunction_backwards_Function1D: matrix indexed by [int(1..4)] of int(1..4) find b: bool branching on [b] such that b = - and([p_PermutationAsFunction_PermutationFunction_Function1D[q1] = - q_PermutationAsFunction_PermutationFunction_Function1D[q1] - | q1 : int(1..4)]) + (and([p_PermutationAsFunction_PermutationFunction_forwards_Function1D[q1] = + q_PermutationAsFunction_PermutationFunction_forwards_Function1D[q1] + | q1 : int(1..4)]) + /\ + and([p_PermutationAsFunction_PermutationFunction_backwards_Function1D[q3] = + q_PermutationAsFunction_PermutationFunction_backwards_Function1D[q3] + | q3 : int(1..4)])) diff --git a/tests/exhaustive/basic/perms/05_equality/enum/0003_given_equal_letting/expected/model-permutation.eprime-param b/tests/exhaustive/basic/perms/05_equality/enum/0003_given_equal_letting/expected/model-permutation.eprime-param index c2bddee0e8..6ab791d030 100644 --- a/tests/exhaustive/basic/perms/05_equality/enum/0003_given_equal_letting/expected/model-permutation.eprime-param +++ b/tests/exhaustive/basic/perms/05_equality/enum/0003_given_equal_letting/expected/model-permutation.eprime-param @@ -1,3 +1,4 @@ language ESSENCE' 1.0 -letting p_PermutationAsFunction_PermutationFunction_Function1D be [3, 2, 4, 1; int(1..4)] +letting p_PermutationAsFunction_PermutationFunction_forwards_Function1D be [3, 2, 4, 1; int(1..4)] +letting p_PermutationAsFunction_PermutationFunction_backwards_Function1D be [4, 2, 1, 3; int(1..4)] diff --git a/tests/exhaustive/basic/perms/05_equality/enum/0003_given_equal_letting/expected/model.eprime b/tests/exhaustive/basic/perms/05_equality/enum/0003_given_equal_letting/expected/model.eprime index 4047fc6e95..37c68b314d 100644 --- a/tests/exhaustive/basic/perms/05_equality/enum/0003_given_equal_letting/expected/model.eprime +++ b/tests/exhaustive/basic/perms/05_equality/enum/0003_given_equal_letting/expected/model.eprime @@ -1,21 +1,22 @@ language ESSENCE' 1.0 -given p_PermutationAsFunction_PermutationFunction_Function1D: matrix indexed by [int(1..4)] of int(1..4) +given p_PermutationAsFunction_PermutationFunction_forwards_Function1D: matrix indexed by [int(1..4)] of int(1..4) +given p_PermutationAsFunction_PermutationFunction_backwards_Function1D: matrix indexed by [int(1..4)] of int(1..4) find b: bool branching on [b] such that b = - (and([or([1 = q8 /\ 2 = p_PermutationAsFunction_PermutationFunction_Function1D[q8], - 2 = q8 /\ 4 = p_PermutationAsFunction_PermutationFunction_Function1D[q8], - 4 = q8 /\ 1 = p_PermutationAsFunction_PermutationFunction_Function1D[q8]; + (and([or([1 = q8 /\ 2 = p_PermutationAsFunction_PermutationFunction_forwards_Function1D[q8], + 2 = q8 /\ 4 = p_PermutationAsFunction_PermutationFunction_forwards_Function1D[q8], + 4 = q8 /\ 1 = p_PermutationAsFunction_PermutationFunction_forwards_Function1D[q8]; int(1..3)]) - | q8 : int(1..4), q8 != p_PermutationAsFunction_PermutationFunction_Function1D[q8]]) + | q8 : int(1..4), q8 != p_PermutationAsFunction_PermutationFunction_forwards_Function1D[q8]]) /\ - and([or([q16 = 1 /\ p_PermutationAsFunction_PermutationFunction_Function1D[q16] = 2 - | q16 : int(1..4), q16 != p_PermutationAsFunction_PermutationFunction_Function1D[q16]]), - or([q23 = 2 /\ p_PermutationAsFunction_PermutationFunction_Function1D[q23] = 4 - | q23 : int(1..4), q23 != p_PermutationAsFunction_PermutationFunction_Function1D[q23]]), - or([q30 = 4 /\ p_PermutationAsFunction_PermutationFunction_Function1D[q30] = 1 - | q30 : int(1..4), q30 != p_PermutationAsFunction_PermutationFunction_Function1D[q30]]); + and([or([q16 = 1 /\ p_PermutationAsFunction_PermutationFunction_forwards_Function1D[q16] = 2 + | q16 : int(1..4), q16 != p_PermutationAsFunction_PermutationFunction_forwards_Function1D[q16]]), + or([q23 = 2 /\ p_PermutationAsFunction_PermutationFunction_forwards_Function1D[q23] = 4 + | q23 : int(1..4), q23 != p_PermutationAsFunction_PermutationFunction_forwards_Function1D[q23]]), + or([q30 = 4 /\ p_PermutationAsFunction_PermutationFunction_forwards_Function1D[q30] = 1 + | q30 : int(1..4), q30 != p_PermutationAsFunction_PermutationFunction_forwards_Function1D[q30]]); int(1..3)])) diff --git a/tests/exhaustive/basic/perms/05_equality/enum/0004_letting_equal_given/expected/model-permutation.eprime-param b/tests/exhaustive/basic/perms/05_equality/enum/0004_letting_equal_given/expected/model-permutation.eprime-param index c2bddee0e8..6ab791d030 100644 --- a/tests/exhaustive/basic/perms/05_equality/enum/0004_letting_equal_given/expected/model-permutation.eprime-param +++ b/tests/exhaustive/basic/perms/05_equality/enum/0004_letting_equal_given/expected/model-permutation.eprime-param @@ -1,3 +1,4 @@ language ESSENCE' 1.0 -letting p_PermutationAsFunction_PermutationFunction_Function1D be [3, 2, 4, 1; int(1..4)] +letting p_PermutationAsFunction_PermutationFunction_forwards_Function1D be [3, 2, 4, 1; int(1..4)] +letting p_PermutationAsFunction_PermutationFunction_backwards_Function1D be [4, 2, 1, 3; int(1..4)] diff --git a/tests/exhaustive/basic/perms/05_equality/enum/0004_letting_equal_given/expected/model.eprime b/tests/exhaustive/basic/perms/05_equality/enum/0004_letting_equal_given/expected/model.eprime index e8d100615a..0aff12ba21 100644 --- a/tests/exhaustive/basic/perms/05_equality/enum/0004_letting_equal_given/expected/model.eprime +++ b/tests/exhaustive/basic/perms/05_equality/enum/0004_letting_equal_given/expected/model.eprime @@ -1,21 +1,22 @@ language ESSENCE' 1.0 -given p_PermutationAsFunction_PermutationFunction_Function1D: matrix indexed by [int(1..4)] of int(1..4) +given p_PermutationAsFunction_PermutationFunction_forwards_Function1D: matrix indexed by [int(1..4)] of int(1..4) +given p_PermutationAsFunction_PermutationFunction_backwards_Function1D: matrix indexed by [int(1..4)] of int(1..4) find b: bool branching on [b] such that b = - (and([or([q8 = 1 /\ p_PermutationAsFunction_PermutationFunction_Function1D[q8] = 2 - | q8 : int(1..4), q8 != p_PermutationAsFunction_PermutationFunction_Function1D[q8]]), - or([q15 = 2 /\ p_PermutationAsFunction_PermutationFunction_Function1D[q15] = 4 - | q15 : int(1..4), q15 != p_PermutationAsFunction_PermutationFunction_Function1D[q15]]), - or([q22 = 4 /\ p_PermutationAsFunction_PermutationFunction_Function1D[q22] = 1 - | q22 : int(1..4), q22 != p_PermutationAsFunction_PermutationFunction_Function1D[q22]]); + (and([or([q8 = 1 /\ p_PermutationAsFunction_PermutationFunction_forwards_Function1D[q8] = 2 + | q8 : int(1..4), q8 != p_PermutationAsFunction_PermutationFunction_forwards_Function1D[q8]]), + or([q15 = 2 /\ p_PermutationAsFunction_PermutationFunction_forwards_Function1D[q15] = 4 + | q15 : int(1..4), q15 != p_PermutationAsFunction_PermutationFunction_forwards_Function1D[q15]]), + or([q22 = 4 /\ p_PermutationAsFunction_PermutationFunction_forwards_Function1D[q22] = 1 + | q22 : int(1..4), q22 != p_PermutationAsFunction_PermutationFunction_forwards_Function1D[q22]]); int(1..3)]) /\ - and([or([1 = q30 /\ 2 = p_PermutationAsFunction_PermutationFunction_Function1D[q30], - 2 = q30 /\ 4 = p_PermutationAsFunction_PermutationFunction_Function1D[q30], - 4 = q30 /\ 1 = p_PermutationAsFunction_PermutationFunction_Function1D[q30]; + and([or([1 = q30 /\ 2 = p_PermutationAsFunction_PermutationFunction_forwards_Function1D[q30], + 2 = q30 /\ 4 = p_PermutationAsFunction_PermutationFunction_forwards_Function1D[q30], + 4 = q30 /\ 1 = p_PermutationAsFunction_PermutationFunction_forwards_Function1D[q30]; int(1..3)]) - | q30 : int(1..4), q30 != p_PermutationAsFunction_PermutationFunction_Function1D[q30]])) + | q30 : int(1..4), q30 != p_PermutationAsFunction_PermutationFunction_forwards_Function1D[q30]])) diff --git a/tests/exhaustive/basic/perms/05_equality/enum/0005_find_eq_find/expected/model.eprime b/tests/exhaustive/basic/perms/05_equality/enum/0005_find_eq_find/expected/model.eprime index f1a2530c1a..9e81e9d001 100644 --- a/tests/exhaustive/basic/perms/05_equality/enum/0005_find_eq_find/expected/model.eprime +++ b/tests/exhaustive/basic/perms/05_equality/enum/0005_find_eq_find/expected/model.eprime @@ -1,15 +1,47 @@ language ESSENCE' 1.0 -find p_PermutationAsFunction_PermutationFunction_Function1D: matrix indexed by [int(1..4)] of int(1..4) -find q_PermutationAsFunction_PermutationFunction_Function1D: matrix indexed by [int(1..4)] of int(1..4) +find p_PermutationAsFunction_PermutationFunction_forwards_Function1D: matrix indexed by [int(1..4)] of int(1..4) +find p_PermutationAsFunction_PermutationFunction_backwards_Function1D: matrix indexed by [int(1..4)] of int(1..4) +find q_PermutationAsFunction_PermutationFunction_forwards_Function1D: matrix indexed by [int(1..4)] of int(1..4) +find q_PermutationAsFunction_PermutationFunction_backwards_Function1D: matrix indexed by [int(1..4)] of int(1..4) branching on - [p_PermutationAsFunction_PermutationFunction_Function1D, q_PermutationAsFunction_PermutationFunction_Function1D] + [p_PermutationAsFunction_PermutationFunction_forwards_Function1D, + p_PermutationAsFunction_PermutationFunction_backwards_Function1D, + q_PermutationAsFunction_PermutationFunction_forwards_Function1D, + q_PermutationAsFunction_PermutationFunction_backwards_Function1D] such that - and([q_PermutationAsFunction_PermutationFunction_Function1D[q9] = - p_PermutationAsFunction_PermutationFunction_Function1D[q9] + and([q_PermutationAsFunction_PermutationFunction_forwards_Function1D[q15] = + p_PermutationAsFunction_PermutationFunction_forwards_Function1D[q15] + | q15 : int(1..4)]), + and([q_PermutationAsFunction_PermutationFunction_backwards_Function1D[q17] = + p_PermutationAsFunction_PermutationFunction_backwards_Function1D[q17] + | q17 : int(1..4)]), + allDiff(q_PermutationAsFunction_PermutationFunction_forwards_Function1D), + and([or([q_PermutationAsFunction_PermutationFunction_forwards_Function1D[q3] = q2 | q3 : int(1..4)]) + | q2 : int(1..4)]), + allDiff(q_PermutationAsFunction_PermutationFunction_backwards_Function1D), + and([or([q_PermutationAsFunction_PermutationFunction_backwards_Function1D[q6] = q5 | q6 : int(1..4)]) + | q5 : int(1..4)]), + and([q_PermutationAsFunction_PermutationFunction_backwards_Function1D + [q_PermutationAsFunction_PermutationFunction_forwards_Function1D[q1]] + = q1 + | q1 : int(1..4)]), + and([q_PermutationAsFunction_PermutationFunction_forwards_Function1D + [q_PermutationAsFunction_PermutationFunction_backwards_Function1D[q1]] + = q1 + | q1 : int(1..4)]), + allDiff(p_PermutationAsFunction_PermutationFunction_forwards_Function1D), + and([or([p_PermutationAsFunction_PermutationFunction_forwards_Function1D[q10] = q9 | q10 : int(1..4)]) | q9 : int(1..4)]), - allDiff(q_PermutationAsFunction_PermutationFunction_Function1D), - and([or([q_PermutationAsFunction_PermutationFunction_Function1D[q3] = q2 | q3 : int(1..4)]) | q2 : int(1..4)]), - allDiff(p_PermutationAsFunction_PermutationFunction_Function1D), - and([or([p_PermutationAsFunction_PermutationFunction_Function1D[q7] = q6 | q7 : int(1..4)]) | q6 : int(1..4)]) + allDiff(p_PermutationAsFunction_PermutationFunction_backwards_Function1D), + and([or([p_PermutationAsFunction_PermutationFunction_backwards_Function1D[q13] = q12 | q13 : int(1..4)]) + | q12 : int(1..4)]), + and([p_PermutationAsFunction_PermutationFunction_backwards_Function1D + [p_PermutationAsFunction_PermutationFunction_forwards_Function1D[q8]] + = q8 + | q8 : int(1..4)]), + and([p_PermutationAsFunction_PermutationFunction_forwards_Function1D + [p_PermutationAsFunction_PermutationFunction_backwards_Function1D[q8]] + = q8 + | q8 : int(1..4)]) diff --git a/tests/exhaustive/basic/perms/05_equality/enum/0006_in_comprehension/expected/model.eprime b/tests/exhaustive/basic/perms/05_equality/enum/0006_in_comprehension/expected/model.eprime index b06a4e1b4e..b0f216f57d 100644 --- a/tests/exhaustive/basic/perms/05_equality/enum/0006_in_comprehension/expected/model.eprime +++ b/tests/exhaustive/basic/perms/05_equality/enum/0006_in_comprehension/expected/model.eprime @@ -1,21 +1,50 @@ language ESSENCE' 1.0 -find p_PermutationAsFunction_PermutationFunction_Function1D: matrix indexed by [int(1..4)] of int(1..4) -find q_PermutationAsFunction_PermutationFunction_Function1D: matrix indexed by [int(1..4)] of int(1..4) +find p_PermutationAsFunction_PermutationFunction_forwards_Function1D: matrix indexed by [int(1..4)] of int(1..4) +find p_PermutationAsFunction_PermutationFunction_backwards_Function1D: matrix indexed by [int(1..4)] of int(1..4) +find q_PermutationAsFunction_PermutationFunction_forwards_Function1D: matrix indexed by [int(1..4)] of int(1..4) +find q_PermutationAsFunction_PermutationFunction_backwards_Function1D: matrix indexed by [int(1..4)] of int(1..4) branching on - [p_PermutationAsFunction_PermutationFunction_Function1D, q_PermutationAsFunction_PermutationFunction_Function1D] + [p_PermutationAsFunction_PermutationFunction_forwards_Function1D, + p_PermutationAsFunction_PermutationFunction_backwards_Function1D, + q_PermutationAsFunction_PermutationFunction_forwards_Function1D, + q_PermutationAsFunction_PermutationFunction_backwards_Function1D] such that - and([q20 != q_PermutationAsFunction_PermutationFunction_Function1D[q20] /\ - q14 != p_PermutationAsFunction_PermutationFunction_Function1D[q14] + and([q26 != q_PermutationAsFunction_PermutationFunction_forwards_Function1D[q26] /\ + q20 != p_PermutationAsFunction_PermutationFunction_forwards_Function1D[q20] -> - !(q14 = q20 /\ - p_PermutationAsFunction_PermutationFunction_Function1D[q14] = - q_PermutationAsFunction_PermutationFunction_Function1D[q20]) - | q14 : int(1..4), q20 : int(1..4)]), - allDiff(p_PermutationAsFunction_PermutationFunction_Function1D), - and([or([p_PermutationAsFunction_PermutationFunction_Function1D[q3] = q2 | q3 : int(1..4)]) | q2 : int(1..4)]), - 4 = sum([toInt(q1 != p_PermutationAsFunction_PermutationFunction_Function1D[q1]) | q1 : int(1..4)]), - allDiff(q_PermutationAsFunction_PermutationFunction_Function1D), - and([or([q_PermutationAsFunction_PermutationFunction_Function1D[q7] = q6 | q7 : int(1..4)]) | q6 : int(1..4)]), - 4 = sum([toInt(q5 != q_PermutationAsFunction_PermutationFunction_Function1D[q5]) | q5 : int(1..4)]) + !(q20 = q26 /\ + p_PermutationAsFunction_PermutationFunction_forwards_Function1D[q20] = + q_PermutationAsFunction_PermutationFunction_forwards_Function1D[q26]) + | q20 : int(1..4), q26 : int(1..4)]), + allDiff(p_PermutationAsFunction_PermutationFunction_forwards_Function1D), + and([or([p_PermutationAsFunction_PermutationFunction_forwards_Function1D[q3] = q2 | q3 : int(1..4)]) + | q2 : int(1..4)]), + allDiff(p_PermutationAsFunction_PermutationFunction_backwards_Function1D), + and([or([p_PermutationAsFunction_PermutationFunction_backwards_Function1D[q6] = q5 | q6 : int(1..4)]) + | q5 : int(1..4)]), + 4 = sum([toInt(q1 != p_PermutationAsFunction_PermutationFunction_forwards_Function1D[q1]) | q1 : int(1..4)]), + and([p_PermutationAsFunction_PermutationFunction_backwards_Function1D + [p_PermutationAsFunction_PermutationFunction_forwards_Function1D[q1]] + = q1 + | q1 : int(1..4)]), + and([p_PermutationAsFunction_PermutationFunction_forwards_Function1D + [p_PermutationAsFunction_PermutationFunction_backwards_Function1D[q1]] + = q1 + | q1 : int(1..4)]), + allDiff(q_PermutationAsFunction_PermutationFunction_forwards_Function1D), + and([or([q_PermutationAsFunction_PermutationFunction_forwards_Function1D[q10] = q9 | q10 : int(1..4)]) + | q9 : int(1..4)]), + allDiff(q_PermutationAsFunction_PermutationFunction_backwards_Function1D), + and([or([q_PermutationAsFunction_PermutationFunction_backwards_Function1D[q13] = q12 | q13 : int(1..4)]) + | q12 : int(1..4)]), + 4 = sum([toInt(q8 != q_PermutationAsFunction_PermutationFunction_forwards_Function1D[q8]) | q8 : int(1..4)]), + and([q_PermutationAsFunction_PermutationFunction_backwards_Function1D + [q_PermutationAsFunction_PermutationFunction_forwards_Function1D[q8]] + = q8 + | q8 : int(1..4)]), + and([q_PermutationAsFunction_PermutationFunction_forwards_Function1D + [q_PermutationAsFunction_PermutationFunction_backwards_Function1D[q8]] + = q8 + | q8 : int(1..4)]) diff --git a/tests/exhaustive/basic/perms/05_equality/int/0001_given_permutations_in_param/expected/model-permutation.eprime-param b/tests/exhaustive/basic/perms/05_equality/int/0001_given_permutations_in_param/expected/model-permutation.eprime-param index 5a448d7146..b39cbb8aa3 100644 --- a/tests/exhaustive/basic/perms/05_equality/int/0001_given_permutations_in_param/expected/model-permutation.eprime-param +++ b/tests/exhaustive/basic/perms/05_equality/int/0001_given_permutations_in_param/expected/model-permutation.eprime-param @@ -1,4 +1,6 @@ language ESSENCE' 1.0 -letting p_PermutationAsFunction_PermutationFunction_Function1D be [3, 2, 4, 1; int(1..4)] -letting q_PermutationAsFunction_PermutationFunction_Function1D be [3, 2, 4, 1; int(1..4)] +letting p_PermutationAsFunction_PermutationFunction_forwards_Function1D be [3, 2, 4, 1; int(1..4)] +letting p_PermutationAsFunction_PermutationFunction_backwards_Function1D be [4, 2, 1, 3; int(1..4)] +letting q_PermutationAsFunction_PermutationFunction_forwards_Function1D be [3, 2, 4, 1; int(1..4)] +letting q_PermutationAsFunction_PermutationFunction_backwards_Function1D be [4, 2, 1, 3; int(1..4)] diff --git a/tests/exhaustive/basic/perms/05_equality/int/0001_given_permutations_in_param/expected/model.eprime b/tests/exhaustive/basic/perms/05_equality/int/0001_given_permutations_in_param/expected/model.eprime index 167dc8f366..34a4be8834 100644 --- a/tests/exhaustive/basic/perms/05_equality/int/0001_given_permutations_in_param/expected/model.eprime +++ b/tests/exhaustive/basic/perms/05_equality/int/0001_given_permutations_in_param/expected/model.eprime @@ -1,12 +1,18 @@ language ESSENCE' 1.0 -given p_PermutationAsFunction_PermutationFunction_Function1D: matrix indexed by [int(1..4)] of int(1..4) -given q_PermutationAsFunction_PermutationFunction_Function1D: matrix indexed by [int(1..4)] of int(1..4) +given p_PermutationAsFunction_PermutationFunction_forwards_Function1D: matrix indexed by [int(1..4)] of int(1..4) +given p_PermutationAsFunction_PermutationFunction_backwards_Function1D: matrix indexed by [int(1..4)] of int(1..4) +given q_PermutationAsFunction_PermutationFunction_forwards_Function1D: matrix indexed by [int(1..4)] of int(1..4) +given q_PermutationAsFunction_PermutationFunction_backwards_Function1D: matrix indexed by [int(1..4)] of int(1..4) find b: bool branching on [b] such that b = - and([p_PermutationAsFunction_PermutationFunction_Function1D[q1] = - q_PermutationAsFunction_PermutationFunction_Function1D[q1] - | q1 : int(1..4)]) + (and([p_PermutationAsFunction_PermutationFunction_forwards_Function1D[q1] = + q_PermutationAsFunction_PermutationFunction_forwards_Function1D[q1] + | q1 : int(1..4)]) + /\ + and([p_PermutationAsFunction_PermutationFunction_backwards_Function1D[q3] = + q_PermutationAsFunction_PermutationFunction_backwards_Function1D[q3] + | q3 : int(1..4)])) diff --git a/tests/exhaustive/basic/perms/05_equality/int/0002_given_permutations_in_param/expected/model-permutation.eprime-param b/tests/exhaustive/basic/perms/05_equality/int/0002_given_permutations_in_param/expected/model-permutation.eprime-param index fea0f3fb24..ee717be670 100644 --- a/tests/exhaustive/basic/perms/05_equality/int/0002_given_permutations_in_param/expected/model-permutation.eprime-param +++ b/tests/exhaustive/basic/perms/05_equality/int/0002_given_permutations_in_param/expected/model-permutation.eprime-param @@ -1,4 +1,6 @@ language ESSENCE' 1.0 -letting p_PermutationAsFunction_PermutationFunction_Function1D be [3, 2, 4, 1; int(1..4)] -letting q_PermutationAsFunction_PermutationFunction_Function1D be [2, 4, 3, 1; int(1..4)] +letting p_PermutationAsFunction_PermutationFunction_forwards_Function1D be [3, 2, 4, 1; int(1..4)] +letting p_PermutationAsFunction_PermutationFunction_backwards_Function1D be [4, 2, 1, 3; int(1..4)] +letting q_PermutationAsFunction_PermutationFunction_forwards_Function1D be [2, 4, 3, 1; int(1..4)] +letting q_PermutationAsFunction_PermutationFunction_backwards_Function1D be [4, 1, 3, 2; int(1..4)] diff --git a/tests/exhaustive/basic/perms/05_equality/int/0002_given_permutations_in_param/expected/model.eprime b/tests/exhaustive/basic/perms/05_equality/int/0002_given_permutations_in_param/expected/model.eprime index 167dc8f366..34a4be8834 100644 --- a/tests/exhaustive/basic/perms/05_equality/int/0002_given_permutations_in_param/expected/model.eprime +++ b/tests/exhaustive/basic/perms/05_equality/int/0002_given_permutations_in_param/expected/model.eprime @@ -1,12 +1,18 @@ language ESSENCE' 1.0 -given p_PermutationAsFunction_PermutationFunction_Function1D: matrix indexed by [int(1..4)] of int(1..4) -given q_PermutationAsFunction_PermutationFunction_Function1D: matrix indexed by [int(1..4)] of int(1..4) +given p_PermutationAsFunction_PermutationFunction_forwards_Function1D: matrix indexed by [int(1..4)] of int(1..4) +given p_PermutationAsFunction_PermutationFunction_backwards_Function1D: matrix indexed by [int(1..4)] of int(1..4) +given q_PermutationAsFunction_PermutationFunction_forwards_Function1D: matrix indexed by [int(1..4)] of int(1..4) +given q_PermutationAsFunction_PermutationFunction_backwards_Function1D: matrix indexed by [int(1..4)] of int(1..4) find b: bool branching on [b] such that b = - and([p_PermutationAsFunction_PermutationFunction_Function1D[q1] = - q_PermutationAsFunction_PermutationFunction_Function1D[q1] - | q1 : int(1..4)]) + (and([p_PermutationAsFunction_PermutationFunction_forwards_Function1D[q1] = + q_PermutationAsFunction_PermutationFunction_forwards_Function1D[q1] + | q1 : int(1..4)]) + /\ + and([p_PermutationAsFunction_PermutationFunction_backwards_Function1D[q3] = + q_PermutationAsFunction_PermutationFunction_backwards_Function1D[q3] + | q3 : int(1..4)])) diff --git a/tests/exhaustive/basic/perms/05_equality/int/0003_given_equal_letting/expected/model-permutation.eprime-param b/tests/exhaustive/basic/perms/05_equality/int/0003_given_equal_letting/expected/model-permutation.eprime-param index c2bddee0e8..6ab791d030 100644 --- a/tests/exhaustive/basic/perms/05_equality/int/0003_given_equal_letting/expected/model-permutation.eprime-param +++ b/tests/exhaustive/basic/perms/05_equality/int/0003_given_equal_letting/expected/model-permutation.eprime-param @@ -1,3 +1,4 @@ language ESSENCE' 1.0 -letting p_PermutationAsFunction_PermutationFunction_Function1D be [3, 2, 4, 1; int(1..4)] +letting p_PermutationAsFunction_PermutationFunction_forwards_Function1D be [3, 2, 4, 1; int(1..4)] +letting p_PermutationAsFunction_PermutationFunction_backwards_Function1D be [4, 2, 1, 3; int(1..4)] diff --git a/tests/exhaustive/basic/perms/05_equality/int/0003_given_equal_letting/expected/model.eprime b/tests/exhaustive/basic/perms/05_equality/int/0003_given_equal_letting/expected/model.eprime index 09965ef373..c31008dac9 100644 --- a/tests/exhaustive/basic/perms/05_equality/int/0003_given_equal_letting/expected/model.eprime +++ b/tests/exhaustive/basic/perms/05_equality/int/0003_given_equal_letting/expected/model.eprime @@ -1,22 +1,23 @@ language ESSENCE' 1.0 letting n be 4 -given p_PermutationAsFunction_PermutationFunction_Function1D: matrix indexed by [int(1..4)] of int(1..4) +given p_PermutationAsFunction_PermutationFunction_forwards_Function1D: matrix indexed by [int(1..4)] of int(1..4) +given p_PermutationAsFunction_PermutationFunction_backwards_Function1D: matrix indexed by [int(1..4)] of int(1..4) find b: bool branching on [b] such that b = - (and([or([1 = q8 /\ 2 = p_PermutationAsFunction_PermutationFunction_Function1D[q8], - 2 = q8 /\ 4 = p_PermutationAsFunction_PermutationFunction_Function1D[q8], - 4 = q8 /\ 1 = p_PermutationAsFunction_PermutationFunction_Function1D[q8]; + (and([or([1 = q8 /\ 2 = p_PermutationAsFunction_PermutationFunction_forwards_Function1D[q8], + 2 = q8 /\ 4 = p_PermutationAsFunction_PermutationFunction_forwards_Function1D[q8], + 4 = q8 /\ 1 = p_PermutationAsFunction_PermutationFunction_forwards_Function1D[q8]; int(1..3)]) - | q8 : int(1..4), q8 != p_PermutationAsFunction_PermutationFunction_Function1D[q8]]) + | q8 : int(1..4), q8 != p_PermutationAsFunction_PermutationFunction_forwards_Function1D[q8]]) /\ - and([or([q16 = 1 /\ p_PermutationAsFunction_PermutationFunction_Function1D[q16] = 2 - | q16 : int(1..4), q16 != p_PermutationAsFunction_PermutationFunction_Function1D[q16]]), - or([q23 = 2 /\ p_PermutationAsFunction_PermutationFunction_Function1D[q23] = 4 - | q23 : int(1..4), q23 != p_PermutationAsFunction_PermutationFunction_Function1D[q23]]), - or([q30 = 4 /\ p_PermutationAsFunction_PermutationFunction_Function1D[q30] = 1 - | q30 : int(1..4), q30 != p_PermutationAsFunction_PermutationFunction_Function1D[q30]]); + and([or([q16 = 1 /\ p_PermutationAsFunction_PermutationFunction_forwards_Function1D[q16] = 2 + | q16 : int(1..4), q16 != p_PermutationAsFunction_PermutationFunction_forwards_Function1D[q16]]), + or([q23 = 2 /\ p_PermutationAsFunction_PermutationFunction_forwards_Function1D[q23] = 4 + | q23 : int(1..4), q23 != p_PermutationAsFunction_PermutationFunction_forwards_Function1D[q23]]), + or([q30 = 4 /\ p_PermutationAsFunction_PermutationFunction_forwards_Function1D[q30] = 1 + | q30 : int(1..4), q30 != p_PermutationAsFunction_PermutationFunction_forwards_Function1D[q30]]); int(1..3)])) diff --git a/tests/exhaustive/basic/perms/05_equality/int/0004_letting_equal_given/expected/model-permutation.eprime-param b/tests/exhaustive/basic/perms/05_equality/int/0004_letting_equal_given/expected/model-permutation.eprime-param index c2bddee0e8..6ab791d030 100644 --- a/tests/exhaustive/basic/perms/05_equality/int/0004_letting_equal_given/expected/model-permutation.eprime-param +++ b/tests/exhaustive/basic/perms/05_equality/int/0004_letting_equal_given/expected/model-permutation.eprime-param @@ -1,3 +1,4 @@ language ESSENCE' 1.0 -letting p_PermutationAsFunction_PermutationFunction_Function1D be [3, 2, 4, 1; int(1..4)] +letting p_PermutationAsFunction_PermutationFunction_forwards_Function1D be [3, 2, 4, 1; int(1..4)] +letting p_PermutationAsFunction_PermutationFunction_backwards_Function1D be [4, 2, 1, 3; int(1..4)] diff --git a/tests/exhaustive/basic/perms/05_equality/int/0004_letting_equal_given/expected/model.eprime b/tests/exhaustive/basic/perms/05_equality/int/0004_letting_equal_given/expected/model.eprime index e58dfc930a..41a61d99ea 100644 --- a/tests/exhaustive/basic/perms/05_equality/int/0004_letting_equal_given/expected/model.eprime +++ b/tests/exhaustive/basic/perms/05_equality/int/0004_letting_equal_given/expected/model.eprime @@ -1,22 +1,23 @@ language ESSENCE' 1.0 letting n be 4 -given p_PermutationAsFunction_PermutationFunction_Function1D: matrix indexed by [int(1..4)] of int(1..4) +given p_PermutationAsFunction_PermutationFunction_forwards_Function1D: matrix indexed by [int(1..4)] of int(1..4) +given p_PermutationAsFunction_PermutationFunction_backwards_Function1D: matrix indexed by [int(1..4)] of int(1..4) find b: bool branching on [b] such that b = - (and([or([q8 = 1 /\ p_PermutationAsFunction_PermutationFunction_Function1D[q8] = 2 - | q8 : int(1..4), q8 != p_PermutationAsFunction_PermutationFunction_Function1D[q8]]), - or([q15 = 2 /\ p_PermutationAsFunction_PermutationFunction_Function1D[q15] = 4 - | q15 : int(1..4), q15 != p_PermutationAsFunction_PermutationFunction_Function1D[q15]]), - or([q22 = 4 /\ p_PermutationAsFunction_PermutationFunction_Function1D[q22] = 1 - | q22 : int(1..4), q22 != p_PermutationAsFunction_PermutationFunction_Function1D[q22]]); + (and([or([q8 = 1 /\ p_PermutationAsFunction_PermutationFunction_forwards_Function1D[q8] = 2 + | q8 : int(1..4), q8 != p_PermutationAsFunction_PermutationFunction_forwards_Function1D[q8]]), + or([q15 = 2 /\ p_PermutationAsFunction_PermutationFunction_forwards_Function1D[q15] = 4 + | q15 : int(1..4), q15 != p_PermutationAsFunction_PermutationFunction_forwards_Function1D[q15]]), + or([q22 = 4 /\ p_PermutationAsFunction_PermutationFunction_forwards_Function1D[q22] = 1 + | q22 : int(1..4), q22 != p_PermutationAsFunction_PermutationFunction_forwards_Function1D[q22]]); int(1..3)]) /\ - and([or([1 = q30 /\ 2 = p_PermutationAsFunction_PermutationFunction_Function1D[q30], - 2 = q30 /\ 4 = p_PermutationAsFunction_PermutationFunction_Function1D[q30], - 4 = q30 /\ 1 = p_PermutationAsFunction_PermutationFunction_Function1D[q30]; + and([or([1 = q30 /\ 2 = p_PermutationAsFunction_PermutationFunction_forwards_Function1D[q30], + 2 = q30 /\ 4 = p_PermutationAsFunction_PermutationFunction_forwards_Function1D[q30], + 4 = q30 /\ 1 = p_PermutationAsFunction_PermutationFunction_forwards_Function1D[q30]; int(1..3)]) - | q30 : int(1..4), q30 != p_PermutationAsFunction_PermutationFunction_Function1D[q30]])) + | q30 : int(1..4), q30 != p_PermutationAsFunction_PermutationFunction_forwards_Function1D[q30]])) diff --git a/tests/exhaustive/basic/perms/05_equality/int/0005_find_eq_find/expected/model.eprime b/tests/exhaustive/basic/perms/05_equality/int/0005_find_eq_find/expected/model.eprime index f1a2530c1a..9e81e9d001 100644 --- a/tests/exhaustive/basic/perms/05_equality/int/0005_find_eq_find/expected/model.eprime +++ b/tests/exhaustive/basic/perms/05_equality/int/0005_find_eq_find/expected/model.eprime @@ -1,15 +1,47 @@ language ESSENCE' 1.0 -find p_PermutationAsFunction_PermutationFunction_Function1D: matrix indexed by [int(1..4)] of int(1..4) -find q_PermutationAsFunction_PermutationFunction_Function1D: matrix indexed by [int(1..4)] of int(1..4) +find p_PermutationAsFunction_PermutationFunction_forwards_Function1D: matrix indexed by [int(1..4)] of int(1..4) +find p_PermutationAsFunction_PermutationFunction_backwards_Function1D: matrix indexed by [int(1..4)] of int(1..4) +find q_PermutationAsFunction_PermutationFunction_forwards_Function1D: matrix indexed by [int(1..4)] of int(1..4) +find q_PermutationAsFunction_PermutationFunction_backwards_Function1D: matrix indexed by [int(1..4)] of int(1..4) branching on - [p_PermutationAsFunction_PermutationFunction_Function1D, q_PermutationAsFunction_PermutationFunction_Function1D] + [p_PermutationAsFunction_PermutationFunction_forwards_Function1D, + p_PermutationAsFunction_PermutationFunction_backwards_Function1D, + q_PermutationAsFunction_PermutationFunction_forwards_Function1D, + q_PermutationAsFunction_PermutationFunction_backwards_Function1D] such that - and([q_PermutationAsFunction_PermutationFunction_Function1D[q9] = - p_PermutationAsFunction_PermutationFunction_Function1D[q9] + and([q_PermutationAsFunction_PermutationFunction_forwards_Function1D[q15] = + p_PermutationAsFunction_PermutationFunction_forwards_Function1D[q15] + | q15 : int(1..4)]), + and([q_PermutationAsFunction_PermutationFunction_backwards_Function1D[q17] = + p_PermutationAsFunction_PermutationFunction_backwards_Function1D[q17] + | q17 : int(1..4)]), + allDiff(q_PermutationAsFunction_PermutationFunction_forwards_Function1D), + and([or([q_PermutationAsFunction_PermutationFunction_forwards_Function1D[q3] = q2 | q3 : int(1..4)]) + | q2 : int(1..4)]), + allDiff(q_PermutationAsFunction_PermutationFunction_backwards_Function1D), + and([or([q_PermutationAsFunction_PermutationFunction_backwards_Function1D[q6] = q5 | q6 : int(1..4)]) + | q5 : int(1..4)]), + and([q_PermutationAsFunction_PermutationFunction_backwards_Function1D + [q_PermutationAsFunction_PermutationFunction_forwards_Function1D[q1]] + = q1 + | q1 : int(1..4)]), + and([q_PermutationAsFunction_PermutationFunction_forwards_Function1D + [q_PermutationAsFunction_PermutationFunction_backwards_Function1D[q1]] + = q1 + | q1 : int(1..4)]), + allDiff(p_PermutationAsFunction_PermutationFunction_forwards_Function1D), + and([or([p_PermutationAsFunction_PermutationFunction_forwards_Function1D[q10] = q9 | q10 : int(1..4)]) | q9 : int(1..4)]), - allDiff(q_PermutationAsFunction_PermutationFunction_Function1D), - and([or([q_PermutationAsFunction_PermutationFunction_Function1D[q3] = q2 | q3 : int(1..4)]) | q2 : int(1..4)]), - allDiff(p_PermutationAsFunction_PermutationFunction_Function1D), - and([or([p_PermutationAsFunction_PermutationFunction_Function1D[q7] = q6 | q7 : int(1..4)]) | q6 : int(1..4)]) + allDiff(p_PermutationAsFunction_PermutationFunction_backwards_Function1D), + and([or([p_PermutationAsFunction_PermutationFunction_backwards_Function1D[q13] = q12 | q13 : int(1..4)]) + | q12 : int(1..4)]), + and([p_PermutationAsFunction_PermutationFunction_backwards_Function1D + [p_PermutationAsFunction_PermutationFunction_forwards_Function1D[q8]] + = q8 + | q8 : int(1..4)]), + and([p_PermutationAsFunction_PermutationFunction_forwards_Function1D + [p_PermutationAsFunction_PermutationFunction_backwards_Function1D[q8]] + = q8 + | q8 : int(1..4)]) diff --git a/tests/exhaustive/basic/perms/05_equality/int/0006_in_comprehension/expected/model.eprime b/tests/exhaustive/basic/perms/05_equality/int/0006_in_comprehension/expected/model.eprime index b06a4e1b4e..b0f216f57d 100644 --- a/tests/exhaustive/basic/perms/05_equality/int/0006_in_comprehension/expected/model.eprime +++ b/tests/exhaustive/basic/perms/05_equality/int/0006_in_comprehension/expected/model.eprime @@ -1,21 +1,50 @@ language ESSENCE' 1.0 -find p_PermutationAsFunction_PermutationFunction_Function1D: matrix indexed by [int(1..4)] of int(1..4) -find q_PermutationAsFunction_PermutationFunction_Function1D: matrix indexed by [int(1..4)] of int(1..4) +find p_PermutationAsFunction_PermutationFunction_forwards_Function1D: matrix indexed by [int(1..4)] of int(1..4) +find p_PermutationAsFunction_PermutationFunction_backwards_Function1D: matrix indexed by [int(1..4)] of int(1..4) +find q_PermutationAsFunction_PermutationFunction_forwards_Function1D: matrix indexed by [int(1..4)] of int(1..4) +find q_PermutationAsFunction_PermutationFunction_backwards_Function1D: matrix indexed by [int(1..4)] of int(1..4) branching on - [p_PermutationAsFunction_PermutationFunction_Function1D, q_PermutationAsFunction_PermutationFunction_Function1D] + [p_PermutationAsFunction_PermutationFunction_forwards_Function1D, + p_PermutationAsFunction_PermutationFunction_backwards_Function1D, + q_PermutationAsFunction_PermutationFunction_forwards_Function1D, + q_PermutationAsFunction_PermutationFunction_backwards_Function1D] such that - and([q20 != q_PermutationAsFunction_PermutationFunction_Function1D[q20] /\ - q14 != p_PermutationAsFunction_PermutationFunction_Function1D[q14] + and([q26 != q_PermutationAsFunction_PermutationFunction_forwards_Function1D[q26] /\ + q20 != p_PermutationAsFunction_PermutationFunction_forwards_Function1D[q20] -> - !(q14 = q20 /\ - p_PermutationAsFunction_PermutationFunction_Function1D[q14] = - q_PermutationAsFunction_PermutationFunction_Function1D[q20]) - | q14 : int(1..4), q20 : int(1..4)]), - allDiff(p_PermutationAsFunction_PermutationFunction_Function1D), - and([or([p_PermutationAsFunction_PermutationFunction_Function1D[q3] = q2 | q3 : int(1..4)]) | q2 : int(1..4)]), - 4 = sum([toInt(q1 != p_PermutationAsFunction_PermutationFunction_Function1D[q1]) | q1 : int(1..4)]), - allDiff(q_PermutationAsFunction_PermutationFunction_Function1D), - and([or([q_PermutationAsFunction_PermutationFunction_Function1D[q7] = q6 | q7 : int(1..4)]) | q6 : int(1..4)]), - 4 = sum([toInt(q5 != q_PermutationAsFunction_PermutationFunction_Function1D[q5]) | q5 : int(1..4)]) + !(q20 = q26 /\ + p_PermutationAsFunction_PermutationFunction_forwards_Function1D[q20] = + q_PermutationAsFunction_PermutationFunction_forwards_Function1D[q26]) + | q20 : int(1..4), q26 : int(1..4)]), + allDiff(p_PermutationAsFunction_PermutationFunction_forwards_Function1D), + and([or([p_PermutationAsFunction_PermutationFunction_forwards_Function1D[q3] = q2 | q3 : int(1..4)]) + | q2 : int(1..4)]), + allDiff(p_PermutationAsFunction_PermutationFunction_backwards_Function1D), + and([or([p_PermutationAsFunction_PermutationFunction_backwards_Function1D[q6] = q5 | q6 : int(1..4)]) + | q5 : int(1..4)]), + 4 = sum([toInt(q1 != p_PermutationAsFunction_PermutationFunction_forwards_Function1D[q1]) | q1 : int(1..4)]), + and([p_PermutationAsFunction_PermutationFunction_backwards_Function1D + [p_PermutationAsFunction_PermutationFunction_forwards_Function1D[q1]] + = q1 + | q1 : int(1..4)]), + and([p_PermutationAsFunction_PermutationFunction_forwards_Function1D + [p_PermutationAsFunction_PermutationFunction_backwards_Function1D[q1]] + = q1 + | q1 : int(1..4)]), + allDiff(q_PermutationAsFunction_PermutationFunction_forwards_Function1D), + and([or([q_PermutationAsFunction_PermutationFunction_forwards_Function1D[q10] = q9 | q10 : int(1..4)]) + | q9 : int(1..4)]), + allDiff(q_PermutationAsFunction_PermutationFunction_backwards_Function1D), + and([or([q_PermutationAsFunction_PermutationFunction_backwards_Function1D[q13] = q12 | q13 : int(1..4)]) + | q12 : int(1..4)]), + 4 = sum([toInt(q8 != q_PermutationAsFunction_PermutationFunction_forwards_Function1D[q8]) | q8 : int(1..4)]), + and([q_PermutationAsFunction_PermutationFunction_backwards_Function1D + [q_PermutationAsFunction_PermutationFunction_forwards_Function1D[q8]] + = q8 + | q8 : int(1..4)]), + and([q_PermutationAsFunction_PermutationFunction_forwards_Function1D + [q_PermutationAsFunction_PermutationFunction_backwards_Function1D[q8]] + = q8 + | q8 : int(1..4)]) diff --git a/tests/exhaustive/basic/perms/05_equality/unnamed/0005_find_eq_find/expected/model.eprime b/tests/exhaustive/basic/perms/05_equality/unnamed/0005_find_eq_find/expected/model.eprime index f1a2530c1a..9e81e9d001 100644 --- a/tests/exhaustive/basic/perms/05_equality/unnamed/0005_find_eq_find/expected/model.eprime +++ b/tests/exhaustive/basic/perms/05_equality/unnamed/0005_find_eq_find/expected/model.eprime @@ -1,15 +1,47 @@ language ESSENCE' 1.0 -find p_PermutationAsFunction_PermutationFunction_Function1D: matrix indexed by [int(1..4)] of int(1..4) -find q_PermutationAsFunction_PermutationFunction_Function1D: matrix indexed by [int(1..4)] of int(1..4) +find p_PermutationAsFunction_PermutationFunction_forwards_Function1D: matrix indexed by [int(1..4)] of int(1..4) +find p_PermutationAsFunction_PermutationFunction_backwards_Function1D: matrix indexed by [int(1..4)] of int(1..4) +find q_PermutationAsFunction_PermutationFunction_forwards_Function1D: matrix indexed by [int(1..4)] of int(1..4) +find q_PermutationAsFunction_PermutationFunction_backwards_Function1D: matrix indexed by [int(1..4)] of int(1..4) branching on - [p_PermutationAsFunction_PermutationFunction_Function1D, q_PermutationAsFunction_PermutationFunction_Function1D] + [p_PermutationAsFunction_PermutationFunction_forwards_Function1D, + p_PermutationAsFunction_PermutationFunction_backwards_Function1D, + q_PermutationAsFunction_PermutationFunction_forwards_Function1D, + q_PermutationAsFunction_PermutationFunction_backwards_Function1D] such that - and([q_PermutationAsFunction_PermutationFunction_Function1D[q9] = - p_PermutationAsFunction_PermutationFunction_Function1D[q9] + and([q_PermutationAsFunction_PermutationFunction_forwards_Function1D[q15] = + p_PermutationAsFunction_PermutationFunction_forwards_Function1D[q15] + | q15 : int(1..4)]), + and([q_PermutationAsFunction_PermutationFunction_backwards_Function1D[q17] = + p_PermutationAsFunction_PermutationFunction_backwards_Function1D[q17] + | q17 : int(1..4)]), + allDiff(q_PermutationAsFunction_PermutationFunction_forwards_Function1D), + and([or([q_PermutationAsFunction_PermutationFunction_forwards_Function1D[q3] = q2 | q3 : int(1..4)]) + | q2 : int(1..4)]), + allDiff(q_PermutationAsFunction_PermutationFunction_backwards_Function1D), + and([or([q_PermutationAsFunction_PermutationFunction_backwards_Function1D[q6] = q5 | q6 : int(1..4)]) + | q5 : int(1..4)]), + and([q_PermutationAsFunction_PermutationFunction_backwards_Function1D + [q_PermutationAsFunction_PermutationFunction_forwards_Function1D[q1]] + = q1 + | q1 : int(1..4)]), + and([q_PermutationAsFunction_PermutationFunction_forwards_Function1D + [q_PermutationAsFunction_PermutationFunction_backwards_Function1D[q1]] + = q1 + | q1 : int(1..4)]), + allDiff(p_PermutationAsFunction_PermutationFunction_forwards_Function1D), + and([or([p_PermutationAsFunction_PermutationFunction_forwards_Function1D[q10] = q9 | q10 : int(1..4)]) | q9 : int(1..4)]), - allDiff(q_PermutationAsFunction_PermutationFunction_Function1D), - and([or([q_PermutationAsFunction_PermutationFunction_Function1D[q3] = q2 | q3 : int(1..4)]) | q2 : int(1..4)]), - allDiff(p_PermutationAsFunction_PermutationFunction_Function1D), - and([or([p_PermutationAsFunction_PermutationFunction_Function1D[q7] = q6 | q7 : int(1..4)]) | q6 : int(1..4)]) + allDiff(p_PermutationAsFunction_PermutationFunction_backwards_Function1D), + and([or([p_PermutationAsFunction_PermutationFunction_backwards_Function1D[q13] = q12 | q13 : int(1..4)]) + | q12 : int(1..4)]), + and([p_PermutationAsFunction_PermutationFunction_backwards_Function1D + [p_PermutationAsFunction_PermutationFunction_forwards_Function1D[q8]] + = q8 + | q8 : int(1..4)]), + and([p_PermutationAsFunction_PermutationFunction_forwards_Function1D + [p_PermutationAsFunction_PermutationFunction_backwards_Function1D[q8]] + = q8 + | q8 : int(1..4)]) diff --git a/tests/exhaustive/basic/perms/05_equality/unnamed/0006_in_comprehension/expected/model.eprime b/tests/exhaustive/basic/perms/05_equality/unnamed/0006_in_comprehension/expected/model.eprime index b06a4e1b4e..b0f216f57d 100644 --- a/tests/exhaustive/basic/perms/05_equality/unnamed/0006_in_comprehension/expected/model.eprime +++ b/tests/exhaustive/basic/perms/05_equality/unnamed/0006_in_comprehension/expected/model.eprime @@ -1,21 +1,50 @@ language ESSENCE' 1.0 -find p_PermutationAsFunction_PermutationFunction_Function1D: matrix indexed by [int(1..4)] of int(1..4) -find q_PermutationAsFunction_PermutationFunction_Function1D: matrix indexed by [int(1..4)] of int(1..4) +find p_PermutationAsFunction_PermutationFunction_forwards_Function1D: matrix indexed by [int(1..4)] of int(1..4) +find p_PermutationAsFunction_PermutationFunction_backwards_Function1D: matrix indexed by [int(1..4)] of int(1..4) +find q_PermutationAsFunction_PermutationFunction_forwards_Function1D: matrix indexed by [int(1..4)] of int(1..4) +find q_PermutationAsFunction_PermutationFunction_backwards_Function1D: matrix indexed by [int(1..4)] of int(1..4) branching on - [p_PermutationAsFunction_PermutationFunction_Function1D, q_PermutationAsFunction_PermutationFunction_Function1D] + [p_PermutationAsFunction_PermutationFunction_forwards_Function1D, + p_PermutationAsFunction_PermutationFunction_backwards_Function1D, + q_PermutationAsFunction_PermutationFunction_forwards_Function1D, + q_PermutationAsFunction_PermutationFunction_backwards_Function1D] such that - and([q20 != q_PermutationAsFunction_PermutationFunction_Function1D[q20] /\ - q14 != p_PermutationAsFunction_PermutationFunction_Function1D[q14] + and([q26 != q_PermutationAsFunction_PermutationFunction_forwards_Function1D[q26] /\ + q20 != p_PermutationAsFunction_PermutationFunction_forwards_Function1D[q20] -> - !(q14 = q20 /\ - p_PermutationAsFunction_PermutationFunction_Function1D[q14] = - q_PermutationAsFunction_PermutationFunction_Function1D[q20]) - | q14 : int(1..4), q20 : int(1..4)]), - allDiff(p_PermutationAsFunction_PermutationFunction_Function1D), - and([or([p_PermutationAsFunction_PermutationFunction_Function1D[q3] = q2 | q3 : int(1..4)]) | q2 : int(1..4)]), - 4 = sum([toInt(q1 != p_PermutationAsFunction_PermutationFunction_Function1D[q1]) | q1 : int(1..4)]), - allDiff(q_PermutationAsFunction_PermutationFunction_Function1D), - and([or([q_PermutationAsFunction_PermutationFunction_Function1D[q7] = q6 | q7 : int(1..4)]) | q6 : int(1..4)]), - 4 = sum([toInt(q5 != q_PermutationAsFunction_PermutationFunction_Function1D[q5]) | q5 : int(1..4)]) + !(q20 = q26 /\ + p_PermutationAsFunction_PermutationFunction_forwards_Function1D[q20] = + q_PermutationAsFunction_PermutationFunction_forwards_Function1D[q26]) + | q20 : int(1..4), q26 : int(1..4)]), + allDiff(p_PermutationAsFunction_PermutationFunction_forwards_Function1D), + and([or([p_PermutationAsFunction_PermutationFunction_forwards_Function1D[q3] = q2 | q3 : int(1..4)]) + | q2 : int(1..4)]), + allDiff(p_PermutationAsFunction_PermutationFunction_backwards_Function1D), + and([or([p_PermutationAsFunction_PermutationFunction_backwards_Function1D[q6] = q5 | q6 : int(1..4)]) + | q5 : int(1..4)]), + 4 = sum([toInt(q1 != p_PermutationAsFunction_PermutationFunction_forwards_Function1D[q1]) | q1 : int(1..4)]), + and([p_PermutationAsFunction_PermutationFunction_backwards_Function1D + [p_PermutationAsFunction_PermutationFunction_forwards_Function1D[q1]] + = q1 + | q1 : int(1..4)]), + and([p_PermutationAsFunction_PermutationFunction_forwards_Function1D + [p_PermutationAsFunction_PermutationFunction_backwards_Function1D[q1]] + = q1 + | q1 : int(1..4)]), + allDiff(q_PermutationAsFunction_PermutationFunction_forwards_Function1D), + and([or([q_PermutationAsFunction_PermutationFunction_forwards_Function1D[q10] = q9 | q10 : int(1..4)]) + | q9 : int(1..4)]), + allDiff(q_PermutationAsFunction_PermutationFunction_backwards_Function1D), + and([or([q_PermutationAsFunction_PermutationFunction_backwards_Function1D[q13] = q12 | q13 : int(1..4)]) + | q12 : int(1..4)]), + 4 = sum([toInt(q8 != q_PermutationAsFunction_PermutationFunction_forwards_Function1D[q8]) | q8 : int(1..4)]), + and([q_PermutationAsFunction_PermutationFunction_backwards_Function1D + [q_PermutationAsFunction_PermutationFunction_forwards_Function1D[q8]] + = q8 + | q8 : int(1..4)]), + and([q_PermutationAsFunction_PermutationFunction_forwards_Function1D + [q_PermutationAsFunction_PermutationFunction_backwards_Function1D[q8]] + = q8 + | q8 : int(1..4)]) diff --git a/tests/exhaustive/basic/perms/06_inverse/int/0005_find_eq_find/expected/model.eprime b/tests/exhaustive/basic/perms/06_inverse/int/0005_find_eq_find/expected/model.eprime index 190fb337e8..986229607e 100644 --- a/tests/exhaustive/basic/perms/06_inverse/int/0005_find_eq_find/expected/model.eprime +++ b/tests/exhaustive/basic/perms/06_inverse/int/0005_find_eq_find/expected/model.eprime @@ -1,30 +1,61 @@ language ESSENCE' 1.0 -find p_PermutationAsFunction_PermutationFunction_Function1D: matrix indexed by [int(1..4)] of int(1..4) -find q_PermutationAsFunction_PermutationFunction_Function1D: matrix indexed by [int(1..4)] of int(1..4) +find p_PermutationAsFunction_PermutationFunction_forwards_Function1D: matrix indexed by [int(1..4)] of int(1..4) +find p_PermutationAsFunction_PermutationFunction_backwards_Function1D: matrix indexed by [int(1..4)] of int(1..4) +find q_PermutationAsFunction_PermutationFunction_forwards_Function1D: matrix indexed by [int(1..4)] of int(1..4) +find q_PermutationAsFunction_PermutationFunction_backwards_Function1D: matrix indexed by [int(1..4)] of int(1..4) branching on - [p_PermutationAsFunction_PermutationFunction_Function1D, q_PermutationAsFunction_PermutationFunction_Function1D] + [p_PermutationAsFunction_PermutationFunction_forwards_Function1D, + p_PermutationAsFunction_PermutationFunction_backwards_Function1D, + q_PermutationAsFunction_PermutationFunction_forwards_Function1D, + q_PermutationAsFunction_PermutationFunction_backwards_Function1D] such that - and([q17 != p_PermutationAsFunction_PermutationFunction_Function1D[q17] -> - [p_PermutationAsFunction_PermutationFunction_Function1D[q17], - catchUndef(q_PermutationAsFunction_PermutationFunction_Function1D - [p_PermutationAsFunction_PermutationFunction_Function1D[q17]], + and([q23 != p_PermutationAsFunction_PermutationFunction_forwards_Function1D[q23] -> + [p_PermutationAsFunction_PermutationFunction_forwards_Function1D[q23], + catchUndef(q_PermutationAsFunction_PermutationFunction_forwards_Function1D + [p_PermutationAsFunction_PermutationFunction_forwards_Function1D[q23]], 0); int(1..2)] - [toInt(or([q15 = p_PermutationAsFunction_PermutationFunction_Function1D[q17] | q15 : int(1..4)])) + 1] - = q17 - | q17 : int(1..4)]), - and([q25 != q_PermutationAsFunction_PermutationFunction_Function1D[q25] -> - [q_PermutationAsFunction_PermutationFunction_Function1D[q25], - catchUndef(p_PermutationAsFunction_PermutationFunction_Function1D - [q_PermutationAsFunction_PermutationFunction_Function1D[q25]], + [toInt(or([q21 = p_PermutationAsFunction_PermutationFunction_forwards_Function1D[q23] | q21 : int(1..4)])) + + 1] + = q23 + | q23 : int(1..4)]), + and([q31 != q_PermutationAsFunction_PermutationFunction_forwards_Function1D[q31] -> + [q_PermutationAsFunction_PermutationFunction_forwards_Function1D[q31], + catchUndef(p_PermutationAsFunction_PermutationFunction_forwards_Function1D + [q_PermutationAsFunction_PermutationFunction_forwards_Function1D[q31]], 0); int(1..2)] - [toInt(or([q23 = q_PermutationAsFunction_PermutationFunction_Function1D[q25] | q23 : int(1..4)])) + 1] - = q25 - | q25 : int(1..4)]), - allDiff(p_PermutationAsFunction_PermutationFunction_Function1D), - and([or([p_PermutationAsFunction_PermutationFunction_Function1D[q3] = q2 | q3 : int(1..4)]) | q2 : int(1..4)]), - allDiff(q_PermutationAsFunction_PermutationFunction_Function1D), - and([or([q_PermutationAsFunction_PermutationFunction_Function1D[q7] = q6 | q7 : int(1..4)]) | q6 : int(1..4)]) + [toInt(or([q29 = q_PermutationAsFunction_PermutationFunction_forwards_Function1D[q31] | q29 : int(1..4)])) + + 1] + = q31 + | q31 : int(1..4)]), + allDiff(p_PermutationAsFunction_PermutationFunction_forwards_Function1D), + and([or([p_PermutationAsFunction_PermutationFunction_forwards_Function1D[q3] = q2 | q3 : int(1..4)]) + | q2 : int(1..4)]), + allDiff(p_PermutationAsFunction_PermutationFunction_backwards_Function1D), + and([or([p_PermutationAsFunction_PermutationFunction_backwards_Function1D[q6] = q5 | q6 : int(1..4)]) + | q5 : int(1..4)]), + and([p_PermutationAsFunction_PermutationFunction_backwards_Function1D + [p_PermutationAsFunction_PermutationFunction_forwards_Function1D[q1]] + = q1 + | q1 : int(1..4)]), + and([p_PermutationAsFunction_PermutationFunction_forwards_Function1D + [p_PermutationAsFunction_PermutationFunction_backwards_Function1D[q1]] + = q1 + | q1 : int(1..4)]), + allDiff(q_PermutationAsFunction_PermutationFunction_forwards_Function1D), + and([or([q_PermutationAsFunction_PermutationFunction_forwards_Function1D[q10] = q9 | q10 : int(1..4)]) + | q9 : int(1..4)]), + allDiff(q_PermutationAsFunction_PermutationFunction_backwards_Function1D), + and([or([q_PermutationAsFunction_PermutationFunction_backwards_Function1D[q13] = q12 | q13 : int(1..4)]) + | q12 : int(1..4)]), + and([q_PermutationAsFunction_PermutationFunction_backwards_Function1D + [q_PermutationAsFunction_PermutationFunction_forwards_Function1D[q8]] + = q8 + | q8 : int(1..4)]), + and([q_PermutationAsFunction_PermutationFunction_forwards_Function1D + [q_PermutationAsFunction_PermutationFunction_backwards_Function1D[q8]] + = q8 + | q8 : int(1..4)]) From 116749b212a7611aa96c2dddf7f99e08c11d89c2 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?=C3=96zg=C3=BCr=20Akg=C3=BCn?= Date: Thu, 31 Oct 2024 09:52:26 +0000 Subject: [PATCH 185/229] permInverse --- conjure-cp.cabal | 1 + src/Conjure/Compute/DomainOf.hs | 9 +- src/Conjure/Compute/DomainUnion.hs | 8 +- src/Conjure/Language/Attributes.hs | 115 +++---- src/Conjure/Language/Domain.hs | 14 +- src/Conjure/Language/EvaluateOp.hs | 7 + src/Conjure/Language/Expression/Op.hs | 1 + .../Language/Expression/Op/Internal/Common.hs | 1 + .../Language/Expression/Op/PermInverse.hs | 48 +++ src/Conjure/Language/Instantiate.hs | 19 +- src/Conjure/Language/Lexemes.hs | 8 + src/Conjure/Language/Validator.hs | 54 +++- .../Process/ValidateConstantForDomain.hs | 2 - src/Conjure/Rules/Transform.hs | 8 +- .../Permutation/PermutationAsFunction.hs | 30 +- src/Conjure/UI/Model.hs | 1 + tests/acceptAllOutputs.sh | 6 +- tests/custom/dotlt/basic/enum/stdout.expected | 2 +- tests/custom/dotlt/basic/int/stdout.expected | 2 +- .../dotlt/basic/unnamed/stdout.expected | 2 +- .../custom/dotlt/matrix/enum/stdout.expected | 2 +- tests/custom/dotlt/matrix/int/stdout.expected | 2 +- .../dotlt/matrix/unnamed/stdout.expected | 2 +- tests/custom/dotlt/set/enum/stdout.expected | 2 +- tests/custom/dotlt/set/int/stdout.expected | 2 +- .../custom/dotlt/set/unnamed/stdout.expected | 2 +- tests/custom/dotlt/tuple/enum/stdout.expected | 2 +- tests/custom/dotlt/tuple/int/stdout.expected | 2 +- .../dotlt/tuple/unnamed/stdout.expected | 2 +- .../problem-instanceGenerator.essence | 161 ++++++++++ .../problem-instanceGenerator.essence.irace | 48 +++ .../record01/problem-instanceRepair.essence | 181 +++++++++++ .../permutation.essence | 2 +- .../permutation.essence | 2 +- .../permutation.essence | 2 +- .../permutation.essence | 2 +- .../permutation.essence | 2 +- .../permutation.essence | 2 +- .../permutation.essence | 2 +- .../permutation.essence | 2 +- .../permutation.essence | 2 +- .../permutation.essence | 2 +- .../permutation.essence | 2 +- .../permutation.essence | 2 +- .../permutation.essence | 2 +- .../permutation.essence | 2 +- .../permutation.essence | 2 +- .../0003_find_permutation/permutation.essence | 2 +- .../0003_find_permutation/permutation.essence | 2 +- .../0003_find_permutation/permutation.essence | 2 +- .../permutation.essence | 2 +- .../permutation.essence | 2 +- .../permutation.essence | 2 +- .../permutation.essence | 2 +- .../permutation.essence | 2 +- .../permutation.essence | 2 +- .../0006_in_comprehension/permutation.essence | 4 +- .../0006_in_comprehension/permutation.essence | 4 +- .../0006_in_comprehension/permutation.essence | 4 +- .../0030_find_permutation/stdout.expected | 12 - .../permutation.essence | 2 +- .../stdout.expected | 9 - .../stdout.expected | 7 - .../permutation.essence | 2 +- .../stdout.expected | 7 - .../stdout.expected | 7 - .../permutation.essence | 2 +- .../0010_set_of_tuples/permutation.essence | 2 +- .../stdout.expected | 11 - .../stdout.expected | 13 - .../21_set_comprehension/stdout.expected | 37 --- .../int/0001_permute_untagged/stdout.expected | 11 - .../int/0002_permute_tagged/stdout.expected | 11 - .../0003_tagged_lits_in_param/stdout.expected | 11 - .../div/0001_same_tags_works/stdout.expected | 11 - .../0002_diff_tags_prohibited/stdout.expected | 1 - .../0003_const_tagged_works/stdout.expected | 10 - .../div/0004_enum_doesnt_work/stdout.expected | 1 - .../0002_diff_tags_prohibited/stdout.expected | 1 - .../0003_const_tagged_works/stdout.expected | 10 - .../0002_diff_tags_prohibited/stdout.expected | 1 - .../0003_const_tagged_works/stdout.expected | 11 - .../0002_diff_tags_prohibited/stdout.expected | 1 - .../0003_const_tagged_works/stdout.expected | 11 - .../0002_diff_tags_prohibited/stdout.expected | 1 - .../0003_const_tagged_works/stdout.expected | 11 - .../max/0001_same_tags_work/stdout.expected | 11 - .../0002_diff_tags_prohibited/stdout.expected | 1 - .../0003_const_tagged_works/stdout.expected | 10 - .../min/0001_same_tags_work/stdout.expected | 11 - .../0002_diff_tags_prohibited/stdout.expected | 1 - .../0003_const_tagged_works/stdout.expected | 10 - .../0001_same_tags_works/stdout.expected | 11 - .../0002_diff_tags_prohibited/stdout.expected | 1 - .../0003_const_tagged_works/stdout.expected | 10 - .../mod/0001_same_tags_works/stdout.expected | 11 - .../0002_diff_tags_prohibited/stdout.expected | 1 - .../0003_const_tagged_works/stdout.expected | 10 - .../neg/0001_same_tags_works/stdout.expected | 11 - .../0002_diff_tags_prohibited/stdout.expected | 1 - .../0003_const_tagged_works/stdout.expected | 10 - .../0002_diff_tags_prohibited/stdout.expected | 1 - .../0003_const_tagged_works/stdout.expected | 11 - .../prod/0001_same_tags_works/stdout.expected | 11 - .../0002_diff_tags_prohibited/stdout.expected | 1 - .../0003_const_tagged_works/stdout.expected | 10 - .../0002_diff_tags_prohibited/stdout.expected | 1 - .../0003_const_tagged_works/stdout.expected | 11 - .../sum/0001_same_tags_works/stdout.expected | 11 - .../0002_diff_tags_prohibited/stdout.expected | 1 - .../0003_const_tagged_works/stdout.expected | 10 - .../0010_find_perm_find_set/stdout.expected | 53 ---- .../permutations/permInverse/01/01.essence | 7 + .../custom/permutations/permInverse/01/run.sh | 5 + .../permInverse/01/stdout.expected | 13 + .../permutations/permInverse/02/02.essence | 7 + .../custom/permutations/permInverse/02/run.sh | 5 + .../permInverse/02/stdout.expected | 31 ++ .../permutations/permInverse/03/03.essence | 7 + .../custom/permutations/permInverse/03/run.sh | 5 + .../permInverse/03/stdout.expected | 43 +++ .../symmetry/basic/one-var/stdout.expected | 86 +++--- .../symmetry/basic/two-type/stdout.expected | 281 ++++-------------- .../symmetry/basic/two-var/stdout.expected | 87 ++---- .../symmetry/set/one-var/stdout.expected | 197 ++---------- .../symmetry/set/two-type/stdout.expected | 103 +++---- .../symmetry/set/two-var/stdout.expected | 87 ++---- tests/exhaustive/acceptOutput.sh | 4 +- .../permutation.essence | 2 +- .../permutation.essence | 2 +- .../permutation.essence | 2 +- .../permutation.essence | 2 +- .../permutation.essence | 2 +- .../permutation.essence | 2 +- .../permutation.essence | 2 +- .../permutation.essence | 2 +- .../permutation.essence | 2 +- .../permutation.essence | 2 +- .../permutation.essence | 2 +- .../permutation.essence | 2 +- .../permutation.essence | 2 +- .../permutation.essence | 2 +- .../permutation.essence | 2 +- .../0003_find_permutation/permutation.essence | 2 +- .../0003_find_permutation/permutation.essence | 2 +- .../0003_find_permutation/permutation.essence | 2 +- .../permutation.essence | 2 +- .../permutation.essence | 2 +- .../permutation.essence | 2 +- .../permutation.essence | 2 +- .../permutation.essence | 2 +- .../permutation.essence | 2 +- .../0006_in_comprehension/permutation.essence | 4 +- .../0006_in_comprehension/permutation.essence | 4 +- .../0006_in_comprehension/permutation.essence | 4 +- .../subsetSum/expected/model_2_2_2.eprime | 2 +- 156 files changed, 1065 insertions(+), 1216 deletions(-) create mode 100644 src/Conjure/Language/Expression/Op/PermInverse.hs create mode 100644 tests/custom/paramgen/record01/problem-instanceGenerator.essence create mode 100644 tests/custom/paramgen/record01/problem-instanceGenerator.essence.irace create mode 100644 tests/custom/paramgen/record01/problem-instanceRepair.essence delete mode 100644 tests/custom/permutations/18_transform_matrix/enum/0010_find_permutation_indexing_given_matrix/stdout.expected delete mode 100644 tests/custom/permutations/22_tagged_ints/int/0001_permute_untagged/stdout.expected delete mode 100644 tests/custom/permutations/22_tagged_ints/int/0002_permute_tagged/stdout.expected delete mode 100644 tests/custom/permutations/22_tagged_ints/int/0003_tagged_lits_in_param/stdout.expected delete mode 100644 tests/custom/permutations/22_tagged_ints/int/div/0001_same_tags_works/stdout.expected delete mode 100644 tests/custom/permutations/22_tagged_ints/int/div/0002_diff_tags_prohibited/stdout.expected delete mode 100644 tests/custom/permutations/22_tagged_ints/int/div/0003_const_tagged_works/stdout.expected delete mode 100644 tests/custom/permutations/22_tagged_ints/int/div/0004_enum_doesnt_work/stdout.expected delete mode 100644 tests/custom/permutations/22_tagged_ints/int/factorial/0002_diff_tags_prohibited/stdout.expected delete mode 100644 tests/custom/permutations/22_tagged_ints/int/factorial/0003_const_tagged_works/stdout.expected delete mode 100644 tests/custom/permutations/22_tagged_ints/int/geq/0002_diff_tags_prohibited/stdout.expected delete mode 100644 tests/custom/permutations/22_tagged_ints/int/geq/0003_const_tagged_works/stdout.expected delete mode 100644 tests/custom/permutations/22_tagged_ints/int/leq/0002_diff_tags_prohibited/stdout.expected delete mode 100644 tests/custom/permutations/22_tagged_ints/int/leq/0003_const_tagged_works/stdout.expected delete mode 100644 tests/custom/permutations/22_tagged_ints/int/lt/0002_diff_tags_prohibited/stdout.expected delete mode 100644 tests/custom/permutations/22_tagged_ints/int/lt/0003_const_tagged_works/stdout.expected delete mode 100644 tests/custom/permutations/22_tagged_ints/int/max/0001_same_tags_work/stdout.expected delete mode 100644 tests/custom/permutations/22_tagged_ints/int/max/0002_diff_tags_prohibited/stdout.expected delete mode 100644 tests/custom/permutations/22_tagged_ints/int/max/0003_const_tagged_works/stdout.expected delete mode 100644 tests/custom/permutations/22_tagged_ints/int/min/0001_same_tags_work/stdout.expected delete mode 100644 tests/custom/permutations/22_tagged_ints/int/min/0002_diff_tags_prohibited/stdout.expected delete mode 100644 tests/custom/permutations/22_tagged_ints/int/min/0003_const_tagged_works/stdout.expected delete mode 100644 tests/custom/permutations/22_tagged_ints/int/minus/0001_same_tags_works/stdout.expected delete mode 100644 tests/custom/permutations/22_tagged_ints/int/minus/0002_diff_tags_prohibited/stdout.expected delete mode 100644 tests/custom/permutations/22_tagged_ints/int/minus/0003_const_tagged_works/stdout.expected delete mode 100644 tests/custom/permutations/22_tagged_ints/int/mod/0001_same_tags_works/stdout.expected delete mode 100644 tests/custom/permutations/22_tagged_ints/int/mod/0002_diff_tags_prohibited/stdout.expected delete mode 100644 tests/custom/permutations/22_tagged_ints/int/mod/0003_const_tagged_works/stdout.expected delete mode 100644 tests/custom/permutations/22_tagged_ints/int/neg/0001_same_tags_works/stdout.expected delete mode 100644 tests/custom/permutations/22_tagged_ints/int/neg/0002_diff_tags_prohibited/stdout.expected delete mode 100644 tests/custom/permutations/22_tagged_ints/int/neg/0003_const_tagged_works/stdout.expected delete mode 100644 tests/custom/permutations/22_tagged_ints/int/pred/0002_diff_tags_prohibited/stdout.expected delete mode 100644 tests/custom/permutations/22_tagged_ints/int/pred/0003_const_tagged_works/stdout.expected delete mode 100644 tests/custom/permutations/22_tagged_ints/int/prod/0001_same_tags_works/stdout.expected delete mode 100644 tests/custom/permutations/22_tagged_ints/int/prod/0002_diff_tags_prohibited/stdout.expected delete mode 100644 tests/custom/permutations/22_tagged_ints/int/prod/0003_const_tagged_works/stdout.expected delete mode 100644 tests/custom/permutations/22_tagged_ints/int/succ/0002_diff_tags_prohibited/stdout.expected delete mode 100644 tests/custom/permutations/22_tagged_ints/int/succ/0003_const_tagged_works/stdout.expected delete mode 100644 tests/custom/permutations/22_tagged_ints/int/sum/0001_same_tags_works/stdout.expected delete mode 100644 tests/custom/permutations/22_tagged_ints/int/sum/0002_diff_tags_prohibited/stdout.expected delete mode 100644 tests/custom/permutations/22_tagged_ints/int/sum/0003_const_tagged_works/stdout.expected create mode 100644 tests/custom/permutations/permInverse/01/01.essence create mode 100755 tests/custom/permutations/permInverse/01/run.sh create mode 100644 tests/custom/permutations/permInverse/01/stdout.expected create mode 100644 tests/custom/permutations/permInverse/02/02.essence create mode 100755 tests/custom/permutations/permInverse/02/run.sh create mode 100644 tests/custom/permutations/permInverse/02/stdout.expected create mode 100644 tests/custom/permutations/permInverse/03/03.essence create mode 100755 tests/custom/permutations/permInverse/03/run.sh create mode 100644 tests/custom/permutations/permInverse/03/stdout.expected diff --git a/conjure-cp.cabal b/conjure-cp.cabal index 181149c977..5bb992c28d 100644 --- a/conjure-cp.cabal +++ b/conjure-cp.cabal @@ -102,6 +102,7 @@ Library , Conjure.Language.Expression.Op.Participants , Conjure.Language.Expression.Op.Parts , Conjure.Language.Expression.Op.Party + , Conjure.Language.Expression.Op.PermInverse , Conjure.Language.Expression.Op.Pow , Conjure.Language.Expression.Op.PowerSet , Conjure.Language.Expression.Op.Pred diff --git a/src/Conjure/Compute/DomainOf.hs b/src/Conjure/Compute/DomainOf.hs index 8410d64cc7..0cbbb99594 100644 --- a/src/Conjure/Compute/DomainOf.hs +++ b/src/Conjure/Compute/DomainOf.hs @@ -150,6 +150,7 @@ instance (DomainOf x, TypeOf x, Pretty x, ExpressionLike x, Domain () x :< x, Do domainOf (MkOpParticipants x) = domainOf x domainOf (MkOpParts x) = domainOf x domainOf (MkOpParty x) = domainOf x + domainOf (MkOpPermInverse x) = domainOf x domainOf (MkOpPow x) = domainOf x domainOf (MkOpPowerSet x) = domainOf x domainOf (MkOpPred x) = domainOf x @@ -229,6 +230,7 @@ instance (DomainOf x, TypeOf x, Pretty x, ExpressionLike x, Domain () x :< x, Do indexDomainsOf (MkOpParticipants x) = indexDomainsOf x indexDomainsOf (MkOpParts x) = indexDomainsOf x indexDomainsOf (MkOpParty x) = indexDomainsOf x + indexDomainsOf (MkOpPermInverse x) = indexDomainsOf x indexDomainsOf (MkOpPow x) = indexDomainsOf x indexDomainsOf (MkOpPowerSet x) = indexDomainsOf x indexDomainsOf (MkOpPred x) = indexDomainsOf x @@ -334,9 +336,8 @@ instance DomainOf (AbstractLiteral Expression) where where attr = PartitionAttr (SizeAttr_MaxSize (fromInt $ genericLength xss)) (SizeAttr_MaxSize (fromInt $ maximum [genericLength xs | xs <- xss])) False - domainOf (AbsLitPermutation [] ) = return $ DomainPermutation def attr (DomainAny "domainOf-AbsLitPermutation-[]" TypeAny) - where attr = PermutationAttr (SizeAttr_Size 0) - domainOf (AbsLitPermutation xss) = DomainPermutation def def <$> (domainUnions =<< mapM domainOf (concat xss)) + domainOf (AbsLitPermutation [] ) = return $ DomainPermutation def (PermutationAttr SizeAttr_None) (DomainAny "domainOf-AbsLitPermutation-[]" TypeAny) + domainOf (AbsLitPermutation xss) = DomainPermutation def (PermutationAttr SizeAttr_None) <$> (domainUnions =<< mapM domainOf (concat xss)) indexDomainsOf (AbsLitMatrix ind inn) = (ind :) <$> (mapM domainUnions =<< mapM indexDomainsOf inn) indexDomainsOf _ = return [] @@ -558,6 +559,8 @@ instance DomainOf x => DomainOf (OpParts x) where instance (Pretty x, TypeOf x) => DomainOf (OpParty x) where domainOf op = mkDomainAny ("OpParty:" <++> pretty op) <$> typeOf op +instance (Pretty x, TypeOf x) => DomainOf (OpPermInverse x) where + domainOf op = mkDomainAny ("OpPermInverse:" <++> pretty op) <$> typeOf op instance (Pretty x, TypeOf x) => DomainOf (OpCompose x) where domainOf op = mkDomainAny ("OpCompose:" <++> pretty op) <$> typeOf op diff --git a/src/Conjure/Compute/DomainUnion.hs b/src/Conjure/Compute/DomainUnion.hs index 253640b85a..fdb0729277 100644 --- a/src/Conjure/Compute/DomainUnion.hs +++ b/src/Conjure/Compute/DomainUnion.hs @@ -33,6 +33,7 @@ domainUnions [] = return $ DomainAny "domainUnions []" TypeAny domainUnions [a] = return a domainUnions (a:as) = do b <- domainUnions as ; domainUnion a b + instance ( Eq x , ExpressionLike x @@ -90,13 +91,16 @@ instance ) => DomainUnion (SetAttr x) where domainUnion (SetAttr a) (SetAttr b) = SetAttr <$> domainUnion a b + instance ( ExpressionLike x , Op x :< x , Pretty x + , Eq x ) => DomainUnion (PermutationAttr x) where - domainUnion (PermutationAttr a) (PermutationAttr b) = PermutationAttr <$> domainUnion a b - + domainUnion (PermutationAttr a) (PermutationAttr b) + | a == b = return (PermutationAttr a) + | otherwise = bug "DomainUnion PermutationAttr" instance diff --git a/src/Conjure/Language/Attributes.hs b/src/Conjure/Language/Attributes.hs index d18d9783f2..9c11681eef 100644 --- a/src/Conjure/Language/Attributes.hs +++ b/src/Conjure/Language/Attributes.hs @@ -4,7 +4,7 @@ import Conjure.Language.Domain (BinaryRelationAttr (..)) import Conjure.Language.Expression.Op.Internal.Common (Lexeme (..)) import Conjure.Prelude import Data.Map (Map) -import qualified Data.Map.Strict as M +import Data.Map.Strict qualified as M type Attr = (Lexeme, Bool) @@ -17,6 +17,9 @@ setValidAttrs = mapFrom [sizeyAttrs] msetValidAttrs :: Map Lexeme Bool msetValidAttrs = mapFrom [sizeyAttrs, occursAttrs] +permValidAttrs :: Map Lexeme Bool +permValidAttrs = mapFrom [permAttrs] + funAttrs :: Map Lexeme Bool funAttrs = mapFrom [sizeyAttrs, jectivityAttrs, totalityAttrs] @@ -27,64 +30,71 @@ relAttrs :: Map Lexeme Bool relAttrs = mapFrom [sizeyAttrs, binRelAttrs, totalityAttrs] partitionAttrs :: Map Lexeme Bool -partitionAttrs = mapFrom [sizeyAttrs, partSizeAttrs,partNumAttrs, regularity] +partitionAttrs = mapFrom [sizeyAttrs, partSizeAttrs, partNumAttrs, regularity] sizeyAttrs :: [Attr] sizeyAttrs = - [ (L_size, True) - , (L_maxSize, True) - , (L_minSize, True) - ] + [ (L_size, True), + (L_maxSize, True), + (L_minSize, True) + ] + +permAttrs :: [Attr] +permAttrs = + [ (L_numMoved, True), + (L_minNumMoved, True), + (L_maxNumMoved, True) + ] occursAttrs :: [Attr] occursAttrs = - [ (L_minOccur, True) - , (L_maxOccur, True) - ] + [ (L_minOccur, True), + (L_maxOccur, True) + ] partNumAttrs :: [Attr] partNumAttrs = - [ (L_numParts, True) - , (L_maxNumParts, True) - , (L_minNumParts, True) - ] + [ (L_numParts, True), + (L_maxNumParts, True), + (L_minNumParts, True) + ] partSizeAttrs :: [(Lexeme, Bool)] partSizeAttrs = - [ (L_partSize, True) - , (L_minPartSize, True) - , (L_maxPartSize, True) - ] + [ (L_partSize, True), + (L_minPartSize, True), + (L_maxPartSize, True) + ] jectivityAttrs :: [(Lexeme, Bool)] jectivityAttrs = - [ (L_injective, False) - , (L_bijective, False) - , (L_surjective, False) - ] + [ (L_injective, False), + (L_bijective, False), + (L_surjective, False) + ] binRelAttrs :: [(Lexeme, Bool)] binRelAttrs = - [ (L_reflexive, False) - , (L_irreflexive, False) - , (L_coreflexive, False) - , (L_symmetric, False) - , (L_antiSymmetric, False) - , (L_aSymmetric, False) - , (L_transitive, False) - , (L_total,False) - , (L_connex, False) - , (L_Euclidean, False) - , (L_serial, False) - , (L_equivalence, False) - , (L_partialOrder, False) - , (L_linearOrder, False) - , (L_weakOrder, False) - , (L_preOrder, False) - , (L_strictPartialOrder, False) - , (L_leftTotal, False) - , (L_rightTotal, False) - ] + [ (L_reflexive, False), + (L_irreflexive, False), + (L_coreflexive, False), + (L_symmetric, False), + (L_antiSymmetric, False), + (L_aSymmetric, False), + (L_transitive, False), + (L_total, False), + (L_connex, False), + (L_Euclidean, False), + (L_serial, False), + (L_equivalence, False), + (L_partialOrder, False), + (L_linearOrder, False), + (L_weakOrder, False), + (L_preOrder, False), + (L_strictPartialOrder, False), + (L_leftTotal, False), + (L_rightTotal, False) + ] lexemeToBinRel :: Lexeme -> Maybe BinaryRelationAttr lexemeToBinRel L_reflexive = Just BinRelAttr_Reflexive @@ -116,14 +126,15 @@ regularity = [(L_regular, False)] allAttributLexemes :: [Lexeme] allAttributLexemes = - concatMap - (map fst) - [ sizeyAttrs - , jectivityAttrs - , occursAttrs - , partNumAttrs - , partSizeAttrs - , binRelAttrs - , totalityAttrs - , regularity - ] \ No newline at end of file + concatMap + (map fst) + [ sizeyAttrs, + jectivityAttrs, + occursAttrs, + partNumAttrs, + partSizeAttrs, + binRelAttrs, + totalityAttrs, + regularity, + permAttrs + ] \ No newline at end of file diff --git a/src/Conjure/Language/Domain.hs b/src/Conjure/Language/Domain.hs index 9f3ee17cd6..b7bfec0516 100644 --- a/src/Conjure/Language/Domain.hs +++ b/src/Conjure/Language/Domain.hs @@ -331,6 +331,9 @@ data AttrName | AttrName_surjective | AttrName_bijective | AttrName_regular + | AttrName_numMoved + | AttrName_minNumMoved + | AttrName_maxNumMoved -- bin rel ones | AttrName_reflexive | AttrName_irreflexive @@ -374,6 +377,9 @@ instance Pretty AttrName where pretty AttrName_surjective = "surjective" pretty AttrName_bijective = "bijective" pretty AttrName_regular = "regular" + pretty AttrName_numMoved = "numMoved" + pretty AttrName_minNumMoved = "minNumMoved" + pretty AttrName_maxNumMoved = "maxNumMoved" pretty AttrName_reflexive = "reflexive" pretty AttrName_irreflexive = "irreflexive" pretty AttrName_coreflexive = "coreflexive" @@ -754,14 +760,16 @@ instance Pretty a => Pretty (PartitionAttr a) where -data PermutationAttr x - = PermutationAttr (SizeAttr x) +data PermutationAttr a = PermutationAttr + { + numMoved :: SizeAttr a + } deriving (Eq, Ord, Show, Data, Functor, Traversable, Foldable, Typeable, Generic) instance Serialize a => Serialize (PermutationAttr a) instance Hashable a => Hashable (PermutationAttr a) instance ToJSON a => ToJSON (PermutationAttr a) where toJSON = genericToJSON jsonOptions instance FromJSON a => FromJSON (PermutationAttr a) where parseJSON = genericParseJSON jsonOptions -instance Default (PermutationAttr a) where def = PermutationAttr def +instance Default a => Default (PermutationAttr a) where def = PermutationAttr def instance Pretty a => Pretty (PermutationAttr a) where pretty (PermutationAttr a ) = let inside = filter (/=prEmpty) [pretty a] diff --git a/src/Conjure/Language/EvaluateOp.hs b/src/Conjure/Language/EvaluateOp.hs index 142811f3ae..93a75350eb 100644 --- a/src/Conjure/Language/EvaluateOp.hs +++ b/src/Conjure/Language/EvaluateOp.hs @@ -522,6 +522,12 @@ instance EvaluateOp OpParty where <++> pretty op evaluateOp op = na $ "evaluateOp{OpParty}:" <++> pretty (show op) +instance EvaluateOp OpPermInverse where + evaluateOp (OpPermInverse (viewConstantPermutation -> Just xss)) + | Right perm <- fromCycles xss + = return $ ConstantAbstract $ AbsLitPermutation $ toCyclesCanonical $ inverse perm + evaluateOp op = na $ "evaluateOp{OpPermInverse}:" <++> pretty (show op) + instance EvaluateOp OpPow where evaluateOp p | any isUndef (childrenBi p) = return $ mkUndef (TypeInt TagInt) $ "Has undefined children:" <+> pretty p @@ -1002,6 +1008,7 @@ instance EvaluateOp Op where evaluateOp (MkOpParticipants x) = evaluateOp x evaluateOp (MkOpParts x) = evaluateOp x evaluateOp (MkOpParty x) = evaluateOp x + evaluateOp (MkOpPermInverse x) = evaluateOp x evaluateOp (MkOpPow x) = evaluateOp x evaluateOp (MkOpPowerSet x) = evaluateOp x evaluateOp (MkOpPred x) = evaluateOp x diff --git a/src/Conjure/Language/Expression/Op.hs b/src/Conjure/Language/Expression/Op.hs index c897a27aee..eccd8c6cae 100644 --- a/src/Conjure/Language/Expression/Op.hs +++ b/src/Conjure/Language/Expression/Op.hs @@ -132,6 +132,7 @@ mkOp op xs = case op of (arg xs 1 "apart") L_party -> inject $ MkOpParty $ OpParty (arg xs 0 "party") (arg xs 1 "party") + L_permInverse -> inject $ MkOpPermInverse $ OpPermInverse (arg xs 0 "permInverse") L_participants -> inject $ MkOpParticipants $ OpParticipants (arg xs 0 "participants") L_compose -> inject $ MkOpCompose $ OpCompose (arg xs 0 "compose") (arg xs 1 "compose") diff --git a/src/Conjure/Language/Expression/Op/Internal/Common.hs b/src/Conjure/Language/Expression/Op/Internal/Common.hs index 7e2e264a1a..e77a2bbe54 100644 --- a/src/Conjure/Language/Expression/Op/Internal/Common.hs +++ b/src/Conjure/Language/Expression/Op/Internal/Common.hs @@ -310,6 +310,7 @@ functionals = , L_together , L_apart , L_party + , L_permInverse , L_participants , L_parts , L_image diff --git a/src/Conjure/Language/Expression/Op/PermInverse.hs b/src/Conjure/Language/Expression/Op/PermInverse.hs new file mode 100644 index 0000000000..a37877537f --- /dev/null +++ b/src/Conjure/Language/Expression/Op/PermInverse.hs @@ -0,0 +1,48 @@ +{-# LANGUAGE DeriveDataTypeable #-} +{-# LANGUAGE DeriveGeneric #-} +{-# LANGUAGE DeriveTraversable #-} + +module Conjure.Language.Expression.Op.PermInverse where + +import Conjure.Language.Expression.Op.Internal.Common +import Conjure.Prelude +import Data.Aeson qualified as JSON -- aeson +import Data.Aeson.KeyMap qualified as KM +import Data.Vector qualified as V -- vector + +newtype OpPermInverse x = OpPermInverse x + deriving (Eq, Ord, Show, Data, Functor, Traversable, Foldable, Typeable, Generic) + +instance (Serialize x) => Serialize (OpPermInverse x) + +instance (Hashable x) => Hashable (OpPermInverse x) + +instance (ToJSON x) => ToJSON (OpPermInverse x) where toJSON = genericToJSON jsonOptions + +instance (FromJSON x) => FromJSON (OpPermInverse x) where parseJSON = genericParseJSON jsonOptions + +instance (TypeOf x, Pretty x) => TypeOf (OpPermInverse x) where + typeOf p@(OpPermInverse op) = do + ty <- typeOf op + case ty of + TypePermutation {} -> return ty + _ -> raiseTypeError p + +instance SimplifyOp OpPermInverse x where + simplifyOp _ = na "simplifyOp{OpPermInverse}" + +instance (Pretty x) => Pretty (OpPermInverse x) where + prettyPrec _ (OpPermInverse a) = "permInverse" <> prParens (pretty a) + +instance (VarSymBreakingDescription x) => VarSymBreakingDescription (OpPermInverse x) where + varSymBreakingDescription (OpPermInverse a) = + JSON.Object $ + KM.fromList + [ ("type", JSON.String "OpPermInverse"), + ( "children", + JSON.Array $ + V.fromList + [ varSymBreakingDescription a + ] + ) + ] diff --git a/src/Conjure/Language/Instantiate.hs b/src/Conjure/Language/Instantiate.hs index 252a230e39..4263150d8e 100644 --- a/src/Conjure/Language/Instantiate.hs +++ b/src/Conjure/Language/Instantiate.hs @@ -391,17 +391,14 @@ instantiatePartitionAttr (PartitionAttr a b r) = <*> pure r -instantiatePermutationAttr - :: MonadFail m => - MonadUserError m => - MonadState [(Name, Expression)] m => - EnumerateDomain m => - NameGen m => - (?typeCheckerMode :: TypeCheckerMode) => - PermutationAttr Expression -> m (PermutationAttr Constant) -instantiatePermutationAttr (PermutationAttr s) = - PermutationAttr <$> instantiateSizeAttr s - +instantiatePermutationAttr :: + MonadFailDoc m => + MonadState [(Name, Expression)] m => + EnumerateDomain m => + NameGen m => + (?typeCheckerMode :: TypeCheckerMode) => + PermutationAttr Expression -> m (PermutationAttr Constant) +instantiatePermutationAttr (PermutationAttr x) = PermutationAttr <$> instantiateSizeAttr x instantiateR :: diff --git a/src/Conjure/Language/Lexemes.hs b/src/Conjure/Language/Lexemes.hs index 93ea3d8322..736333a255 100644 --- a/src/Conjure/Language/Lexemes.hs +++ b/src/Conjure/Language/Lexemes.hs @@ -112,6 +112,9 @@ data Lexeme -- type: partition | L_partition | L_regular + | L_numMoved + | L_minNumMoved + | L_maxNumMoved | L_partSize | L_minPartSize | L_maxPartSize @@ -146,6 +149,7 @@ data Lexeme | L_together | L_apart | L_party + | L_permInverse | L_participants | L_parts | L_freq @@ -382,6 +386,9 @@ lexemes = sortBy (flip (comparing (T.length . fst))) $ map swap , ( L_rightTotal , "rightTotal") , ( L_partition, "partition" ) , ( L_regular, "regular" ) + , ( L_numMoved, "numMoved" ) + , ( L_minNumMoved, "minNumMoved" ) + , ( L_maxNumMoved, "maxNumMoved" ) , ( L_partSize, "partSize" ) , ( L_minPartSize, "minPartSize" ) , ( L_maxPartSize, "maxPartSize" ) @@ -410,6 +417,7 @@ lexemes = sortBy (flip (comparing (T.length . fst))) $ map swap , ( L_together, "together" ) , ( L_apart, "apart" ) , ( L_party, "party" ) + , ( L_permInverse, "permInverse" ) , ( L_participants, "participants" ) , ( L_parts, "parts" ) , ( L_freq, "freq" ) diff --git a/src/Conjure/Language/Validator.hs b/src/Conjure/Language/Validator.hs index d0a78abdc0..d3d8f61ebe 100644 --- a/src/Conjure/Language/Validator.hs +++ b/src/Conjure/Language/Validator.hs @@ -860,7 +860,7 @@ validateDomain dm = setCategoryLimit (CatParameter, "Domain") $ case dm of let repr = () attrs' <- case attrs of Just a -> validatePermutationAttributes a - Nothing -> return def + Nothing -> return (PermutationAttr SizeAttr_None) (t, dom') <- typeSplit <$> validateDomain dom return . Typed (TypePermutation t) $ DomainPermutation repr attrs' dom' @@ -902,6 +902,18 @@ validateSizeAttributes attrs = do [(L_minSize, Just a), (L_maxSize, Just b)] -> return (SizeAttr_MinMaxSize a b) as -> return . def <* contextError $ SemanticError $ pack $ "Incompatible attributes size:" ++ show as +validatePermAttributes :: [(Lexeme, Maybe Expression)] -> ValidatorS (SizeAttr Expression) +validatePermAttributes attrs = do + let permAttrNames = [L_numMoved, L_minNumMoved, L_maxNumMoved] + let filtered = sort $ filter (\x -> fst x `elem` permAttrNames) attrs + case filtered of + [] -> return SizeAttr_None + [(L_numMoved, Just a)] -> return $ SizeAttr_Size a + [(L_minNumMoved, Just a)] -> return (SizeAttr_MinSize a) + [(L_maxNumMoved, Just a)] -> return (SizeAttr_MaxSize a) + [(L_minNumMoved, Just a), (L_maxNumMoved, Just b)] -> return (SizeAttr_MinMaxSize a b) + as -> return . def <* contextError $ SemanticError $ pack $ "Incompatible attributes numMoved:" ++ show as + validatePartSizeAttributes :: [(Lexeme, Maybe Expression)] -> ValidatorS (SizeAttr Expression) validatePartSizeAttributes attrs = do let sizeAttrs = [L_partSize, L_minPartSize, L_maxPartSize] @@ -984,8 +996,8 @@ validateSeqAttributes atts = do validatePermutationAttributes :: ListNode AttributeNode -> ValidatorS (PermutationAttr Expression) validatePermutationAttributes atts = do - attrs <- catMaybes <$> validateList_ (validateAttributeNode setValidAttrs) atts - size <- validateSizeAttributes attrs + attrs <- catMaybes <$> validateList_ (validateAttributeNode permValidAttrs) atts + size <- validatePermAttributes attrs return $ PermutationAttr size validateRelationAttributes :: ListNode AttributeNode -> ValidatorS (RelationAttr Expression) @@ -2205,6 +2217,7 @@ functionOps l = case l of L_together -> biFuncV setPartArgs (const2 TypeBool) L_apart -> biFuncV setPartArgs (const2 TypeBool) L_party -> biFuncV partyArgs partyType + L_permInverse -> unFuncV permInverseArgs id L_participants -> unFuncV part partInner L_active -> biFuncV activeArgs (const2 TypeBool) L_pred -> unFuncV enumerable enumerableType @@ -2222,26 +2235,42 @@ functionOps l = case l of valueOnly f (r, (k, e)) = do t <- getValueType k f (r, Typed t e) + valueOnly2 :: (SArg -> SArg -> Validator a) -> Arg -> Arg -> Validator a valueOnly2 f (r1, (k1, e1)) (r2, (k2, e2)) = do t1 <- getValueType k1 t2 <- getValueType k2 f (r1, Typed t1 e1) (r2, Typed t2 e2) + typeOnly :: Maybe (Kind, Expression) -> Maybe Type typeOnly (Just (Kind ValueType {} t, _)) = Just t typeOnly _ = Nothing + + unFuncV :: + (SArg -> Validator a0) -> + (Maybe Type -> Maybe Type) -> + ([Expression] -> Expression) -> + [Arg] -> + ValidatorS (Typed Expression) unFuncV a t = unFunc (valueOnly a) (t . typeOnly) + biFuncV :: (SArg -> SArg -> Validator ()) -> (Maybe Type -> Maybe Type -> Maybe Type) -> ([Expression] -> Expression) -> [Arg] -> ValidatorS (Typed Expression) biFuncV a t = biFunc (valueOnly2 a) (\t1 t2 -> t (typeOnly t1) (typeOnly t2)) + valid = return $ pure () + const2 = const . const . pure + const3 = const . const . const . pure + getNum :: Maybe (Kind, Expression) -> Maybe Int getNum (Just (_, x)) = case intOut "" x of Nothing -> Nothing Just n -> pure $ fromInteger n getNum _ = Nothing + each3 f a b c = f a >> f b >> f c + anyType = const . return $ Just () indep :: (SArg -> Validator ()) -> (SArg -> Validator ()) -> (SArg -> SArg -> Validator ()) @@ -2249,6 +2278,7 @@ functionOps l = case l of v1 <- f1 a v2 <- f2 b if not . null $ catMaybes [v1, v2] then return $ pure () else return Nothing + binaryFlattenArgs :: SArg -> SArg -> Validator () binaryFlattenArgs (r1, d) b = do off <- case intOut "" (untype d) of @@ -2258,6 +2288,7 @@ functionOps l = case l of let ref' = foldr id TypeAny ref r <- unifyTypesFailing ref' b return $ if null off || null r then Nothing else Just () + unaryFlattenArgs :: SArg -> Validator () unaryFlattenArgs (_, typeOf_ -> (TypeMatrix _ _)) = valid unaryFlattenArgs (_, typeOf_ -> (TypeList _)) = valid @@ -2272,6 +2303,7 @@ functionOps l = case l of concatType _ = Just $ TypeList TypeAny concatArgs :: SArg -> Validator () concatArgs s@(r, _) = binaryFlattenArgs (r, Typed tInt $ Constant $ ConstantInt TagInt 1) s + tableArgs :: SArg -> SArg -> Validator () tableArgs (r1, typeOf_ -> t1) (r2, typeOf_ -> t2) = do a <- case t1 of @@ -2303,6 +2335,7 @@ functionOps l = case l of TypeFunction {} -> return $ pure () TypeRelation {} -> return $ pure () _ -> invalid $ r ComplexTypeError "Matrix ,list,function,relation,mset,set " a + toSetArgs :: SArg -> Validator () toSetArgs (r, typeOf_ -> a) = case a of TypeAny -> return $ pure () @@ -2312,12 +2345,14 @@ functionOps l = case l of TypeFunction {} -> return $ pure () TypeRelation {} -> return $ pure () _ -> invalid $ r ComplexTypeError "Matrix ,list,function,relation,mset " a + listOrMatrix :: SArg -> Validator () listOrMatrix (r, typeOf_ -> a) = case a of TypeAny -> return $ pure () TypeList _ -> return $ pure () TypeMatrix {} -> return $ pure () _ -> invalid $ r ComplexTypeError "Matrix or list" a + freqArgs :: SArg -> SArg -> Validator () freqArgs (r1, a) (r2, b) = do let tb = typeOf_ b @@ -2335,10 +2370,12 @@ functionOps l = case l of a' <- unifyTypesFailing md a b' <- unifyTypesFailing md b return $ if null a' || null b' then Nothing else Just () + func :: SArg -> Validator () func (_, Typed (TypeFunction _ _) _) = valid func (_, Typed TypeAny _) = valid func (r, Typed t _) = invalid $ r TypeError (TypeFunction TypeAny TypeAny) t + set :: SArg -> Validator Type set (_, Typed (TypeSet t) _) = return $ pure t set (_, Typed TypeAny _) = return $ pure TypeAny @@ -2347,13 +2384,18 @@ functionOps l = case l of powerSetType (Just ((TypeSet i))) = Just $ TypeSet (TypeSet i) powerSetType _ = Just $ TypeSet $ TypeSet TypeAny - only t (r, typeOf_ -> t') = do setContext r; if t' == TypeAny || t == t' then return $ Just t else invalid $ r TypeError t t' + only t (r, typeOf_ -> t') = do + setContext r + if t' == TypeAny || t == t' + then return $ Just t + else invalid $ r TypeError t t' listInt (r, typeOf_ -> t') = case t' of TypeAny -> return $ Just t' TypeList TypeInt {} -> return $ Just t' TypeMatrix _ TypeInt {} -> return $ Just t' _ -> invalid $ r ComplexTypeError "Matrix or list of int or enum" t' + partInner :: Maybe Type -> Maybe Type partInner (Just (TypePartition a)) = Just $ TypeSet a partInner _ = Just $ TypeSet TypeAny @@ -2384,6 +2426,10 @@ functionOps l = case l of quickPermutationOrderArgs :: Arg -> Arg -> Validator () quickPermutationOrderArgs _ _ = return (pure ()) + -- TODO + permInverseArgs :: SArg -> Validator () + permInverseArgs _ = return (pure ()) + -- TODO quickPermutationOrderTypes :: Maybe (Kind, Expression) -> Maybe (Kind, Expression) -> Maybe Type quickPermutationOrderTypes _ _ = Just TypeBool diff --git a/src/Conjure/Process/ValidateConstantForDomain.hs b/src/Conjure/Process/ValidateConstantForDomain.hs index e7a633fb0e..0dfdf2d79a 100644 --- a/src/Conjure/Process/ValidateConstantForDomain.hs +++ b/src/Conjure/Process/ValidateConstantForDomain.hs @@ -7,9 +7,7 @@ import Conjure.Language.Constant import Conjure.Language.Definition import Conjure.Language.Domain import Conjure.Language.Pretty -import Conjure.Language.Type ( TypeCheckerMode ) import Conjure.Language.Type -import Conjure.Language.Pretty import Conjure.Language.Instantiate ( instantiateExpression ) import Conjure.Process.AttributeAsConstraints ( mkAttributeToConstraint ) import Conjure.Process.Enumerate ( EnumerateDomain, enumerateDomain ) diff --git a/src/Conjure/Rules/Transform.hs b/src/Conjure/Rules/Transform.hs index da65829240..947c3634d6 100644 --- a/src/Conjure/Rules/Transform.hs +++ b/src/Conjure/Rules/Transform.hs @@ -49,11 +49,9 @@ rule_Transform_Functorially = "transform-functorially" `namedRule` theRule ( Comprehension body $ gocBefore ++ [Generator (GenInExpr dPat y)] - ++ ( ( ComprehensionLetting - (Single pat) - [essence| - transform(&morphism, &d) |] - ) + ++ ( ComprehensionLetting + (Single pat) + [essence| transform(&morphism, &d) |] : gocAfter ) ) diff --git a/src/Conjure/Rules/Vertical/Permutation/PermutationAsFunction.hs b/src/Conjure/Rules/Vertical/Permutation/PermutationAsFunction.hs index 3930fd65c6..767d9712a6 100644 --- a/src/Conjure/Rules/Vertical/Permutation/PermutationAsFunction.hs +++ b/src/Conjure/Rules/Vertical/Permutation/PermutationAsFunction.hs @@ -85,8 +85,34 @@ rule_Image = "permutation-image{AsFunction}" `namedRule` theRule else return ( "Vertical rule for permutation application to a type the permutation doesn't care about", - do - return [essence| &i |] + return i ) _ -> na "rule_Image" theRule _ = na "rule_Image" + +rule_Image_permInverse :: Rule +rule_Image_permInverse = "permutation-image-permInverse{AsFunction}" `namedRule` theRule + where + theRule [essence| image(permInverse(&p), &i) |] = do + TypePermutation inner <- typeOf p + case match permutationLiteral p of + Nothing -> do + typeI <- typeOf i + if let ?typeCheckerMode = StronglyTyped in typesUnify [inner, typeI] + then do + [_, f] <- downX1 p + return + ( "Vertical rule for permutation application to a single value", + do + return [essence| [&i, catchUndef(image(&f,&i),0)][toInt(&i in defined(&f))+1] |] + ) + else + if let ?typeCheckerMode = StronglyTyped in typeI `containsType` inner + then na "rule_Image_permInverse" + else + return + ( "Vertical rule for permutation application to a type the permutation doesn't care about", + return i + ) + _ -> na "rule_Image_permInverse" + theRule _ = na "rule_Image_permInverse" diff --git a/src/Conjure/UI/Model.hs b/src/Conjure/UI/Model.hs index 06967e65fb..de6b34cb64 100644 --- a/src/Conjure/UI/Model.hs +++ b/src/Conjure/UI/Model.hs @@ -1409,6 +1409,7 @@ paramRules = verticalRules :: [Rule] verticalRules = [ Vertical.Permutation.PermutationAsFunction.rule_Image + , Vertical.Permutation.PermutationAsFunction.rule_Image_permInverse , Vertical.Permutation.PermutationAsFunction.rule_Cardinality , Vertical.Permutation.PermutationAsFunction.rule_Defined , Vertical.Permutation.PermutationAsFunction.rule_Comprehension diff --git a/tests/acceptAllOutputs.sh b/tests/acceptAllOutputs.sh index b00f123c34..7144883a50 100755 --- a/tests/acceptAllOutputs.sh +++ b/tests/acceptAllOutputs.sh @@ -3,6 +3,6 @@ set -o errexit set -o nounset -parallel --no-notice tests/custom/acceptOutput.sh ::: $(find tests/custom -type d) -parallel --no-notice tests/exhaustive/acceptOutput.sh ::: $(find tests/exhaustive -type d) -parallel --no-notice tests/parse_print/acceptOutput.sh ::: $(find tests/parse_print -type d) \ No newline at end of file +tests/custom/acceptOutput.sh ::: $(find tests/custom -type d) +tests/exhaustive/acceptOutput.sh ::: $(find tests/exhaustive -type d) +tests/parse_print/acceptOutput.sh ::: $(find tests/parse_print -type d) \ No newline at end of file diff --git a/tests/custom/dotlt/basic/enum/stdout.expected b/tests/custom/dotlt/basic/enum/stdout.expected index 57b7795950..df7109f15b 100644 --- a/tests/custom/dotlt/basic/enum/stdout.expected +++ b/tests/custom/dotlt/basic/enum/stdout.expected @@ -1,7 +1,7 @@ Generating models for model.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime +Savile Row: conjure-output/model000001.eprime Running minion for domain filtering. Running solver: minion Copying solution to: model.solutions diff --git a/tests/custom/dotlt/basic/int/stdout.expected b/tests/custom/dotlt/basic/int/stdout.expected index 38f48fb5e6..70d33220d4 100644 --- a/tests/custom/dotlt/basic/int/stdout.expected +++ b/tests/custom/dotlt/basic/int/stdout.expected @@ -1,7 +1,7 @@ Generating models for model.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime +Savile Row: conjure-output/model000001.eprime Running minion for domain filtering. Running solver: minion Copying solution to: model.solutions diff --git a/tests/custom/dotlt/basic/unnamed/stdout.expected b/tests/custom/dotlt/basic/unnamed/stdout.expected index 276da5a986..ca1b076780 100644 --- a/tests/custom/dotlt/basic/unnamed/stdout.expected +++ b/tests/custom/dotlt/basic/unnamed/stdout.expected @@ -1,7 +1,7 @@ Generating models for model.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime +Savile Row: conjure-output/model000001.eprime Running minion for domain filtering. Running solver: minion Copying solution to: model.solutions diff --git a/tests/custom/dotlt/matrix/enum/stdout.expected b/tests/custom/dotlt/matrix/enum/stdout.expected index a4b0057bef..94a2ae24da 100644 --- a/tests/custom/dotlt/matrix/enum/stdout.expected +++ b/tests/custom/dotlt/matrix/enum/stdout.expected @@ -1,7 +1,7 @@ Generating models for model.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime +Savile Row: conjure-output/model000001.eprime Running minion for domain filtering. Running solver: minion Copying solution to: model.solutions diff --git a/tests/custom/dotlt/matrix/int/stdout.expected b/tests/custom/dotlt/matrix/int/stdout.expected index 8b80802066..e52b20aa26 100644 --- a/tests/custom/dotlt/matrix/int/stdout.expected +++ b/tests/custom/dotlt/matrix/int/stdout.expected @@ -1,7 +1,7 @@ Generating models for model.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime +Savile Row: conjure-output/model000001.eprime Running minion for domain filtering. Running solver: minion Copying solution to: model.solutions diff --git a/tests/custom/dotlt/matrix/unnamed/stdout.expected b/tests/custom/dotlt/matrix/unnamed/stdout.expected index 16000a3172..3e5483b4f7 100644 --- a/tests/custom/dotlt/matrix/unnamed/stdout.expected +++ b/tests/custom/dotlt/matrix/unnamed/stdout.expected @@ -1,7 +1,7 @@ Generating models for model.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime +Savile Row: conjure-output/model000001.eprime Running minion for domain filtering. Running solver: minion Copying solution to: model.solutions diff --git a/tests/custom/dotlt/set/enum/stdout.expected b/tests/custom/dotlt/set/enum/stdout.expected index ecb819b09d..5e52c66ba4 100644 --- a/tests/custom/dotlt/set/enum/stdout.expected +++ b/tests/custom/dotlt/set/enum/stdout.expected @@ -1,7 +1,7 @@ Generating models for model.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime +Savile Row: conjure-output/model000001.eprime Running minion for domain filtering. Running solver: minion Copying solution to: model.solutions diff --git a/tests/custom/dotlt/set/int/stdout.expected b/tests/custom/dotlt/set/int/stdout.expected index ec78bd6e2a..195bcd6c0e 100644 --- a/tests/custom/dotlt/set/int/stdout.expected +++ b/tests/custom/dotlt/set/int/stdout.expected @@ -1,7 +1,7 @@ Generating models for model.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime +Savile Row: conjure-output/model000001.eprime Running minion for domain filtering. Running solver: minion Copying solution to: model.solutions diff --git a/tests/custom/dotlt/set/unnamed/stdout.expected b/tests/custom/dotlt/set/unnamed/stdout.expected index b63b73e417..464ab9e36c 100644 --- a/tests/custom/dotlt/set/unnamed/stdout.expected +++ b/tests/custom/dotlt/set/unnamed/stdout.expected @@ -1,7 +1,7 @@ Generating models for model.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime +Savile Row: conjure-output/model000001.eprime Running minion for domain filtering. Running solver: minion Copying solution to: model.solutions diff --git a/tests/custom/dotlt/tuple/enum/stdout.expected b/tests/custom/dotlt/tuple/enum/stdout.expected index 57b7795950..df7109f15b 100644 --- a/tests/custom/dotlt/tuple/enum/stdout.expected +++ b/tests/custom/dotlt/tuple/enum/stdout.expected @@ -1,7 +1,7 @@ Generating models for model.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime +Savile Row: conjure-output/model000001.eprime Running minion for domain filtering. Running solver: minion Copying solution to: model.solutions diff --git a/tests/custom/dotlt/tuple/int/stdout.expected b/tests/custom/dotlt/tuple/int/stdout.expected index 38f48fb5e6..70d33220d4 100644 --- a/tests/custom/dotlt/tuple/int/stdout.expected +++ b/tests/custom/dotlt/tuple/int/stdout.expected @@ -1,7 +1,7 @@ Generating models for model.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime +Savile Row: conjure-output/model000001.eprime Running minion for domain filtering. Running solver: minion Copying solution to: model.solutions diff --git a/tests/custom/dotlt/tuple/unnamed/stdout.expected b/tests/custom/dotlt/tuple/unnamed/stdout.expected index 276da5a986..ca1b076780 100644 --- a/tests/custom/dotlt/tuple/unnamed/stdout.expected +++ b/tests/custom/dotlt/tuple/unnamed/stdout.expected @@ -1,7 +1,7 @@ Generating models for model.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime +Savile Row: conjure-output/model000001.eprime Running minion for domain filtering. Running solver: minion Copying solution to: model.solutions diff --git a/tests/custom/paramgen/record01/problem-instanceGenerator.essence b/tests/custom/paramgen/record01/problem-instanceGenerator.essence new file mode 100644 index 0000000000..02cd67f85b --- /dev/null +++ b/tests/custom/paramgen/record01/problem-instanceGenerator.essence @@ -0,0 +1,161 @@ +language Essence 1.3 + +given minid_aircraft_min: int(0..100) +given minid_aircraft_max: int(0..100) +find minid_aircraft: int(0..100) +such that + minid_aircraft >= minid_aircraft_min, + minid_aircraft <= minid_aircraft_max +given maxid_aircraft_min: int(0..100) +given maxid_aircraft_max: int(0..100) +find maxid_aircraft: int(0..100) +such that + maxid_aircraft >= maxid_aircraft_min, + maxid_aircraft <= maxid_aircraft_max +given minid_person_min: int(0..100) +given minid_person_max: int(0..100) +find minid_person: int(0..100) +such that + minid_person >= minid_person_min, + minid_person <= minid_person_max +given maxid_person_min: int(0..100) +given maxid_person_max: int(0..100) +find maxid_person: int(0..100) +such that + maxid_person >= maxid_person_min, + maxid_person <= maxid_person_max +given minid_city_min: int(0..100) +given minid_city_max: int(0..100) +find minid_city: int(0..100) +such that + minid_city >= minid_city_min, + minid_city <= minid_city_max +given maxid_city_min: int(0..100) +given maxid_city_max: int(0..100) +find maxid_city: int(0..100) +such that + maxid_city >= maxid_city_min, + maxid_city <= maxid_city_max +given init_at__percentage_min: int(0..100) +given init_at__percentage_max: int(0..100) +given init_in__percentage_min: int(0..100) +given init_in__percentage_max: int(0..100) +given init_fuel_range_min: int(-65536..65536) +given init_fuel_range_max: int(-65536..65536) +given init_distance_range_min: int(-65536..65536) +given init_distance_range_max: int(-65536..65536) +given init_capacity_range_min: int(-65536..65536) +given init_capacity_range_max: int(-65536..65536) +given init_onboard_range_min: int(-65536..65536) +given init_onboard_range_max: int(-65536..65536) +given init_total_fuel_used_range_min: int(-65536..65536) +given init_total_fuel_used_range_max: int(-65536..65536) +find init: + record {at_ : function (int(0..100), int(0..100)) --> bool, in_ : function (int(0..100), int(0..100)) --> bool, + fuel : function int(0..100) --> int(-65536..65536), + distance : function (int(0..100), int(0..100)) --> int(-65536..65536), + capacity : function int(0..100) --> int(-65536..65536), + onboard : function int(0..100) --> int(-65536..65536), + total_fuel_used : function int(0) --> int(-65536..65536)} +such that + and([q1[1] >= minid_aircraft /\ q1[1] <= maxid_person /\ (q1[2] >= minid_city /\ q1[2] <= maxid_city) <-> + q1 in defined(init[at_]) + | q1 : (int(0..100), int(0..100))]), + sum([toInt(q1[2]) | q1 <- init[at_]]) <= init_at__percentage_max * |defined(init[at_])| / 100 /\ + sum([toInt(q1[2]) | q1 <- init[at_]]) >= init_at__percentage_min * |defined(init[at_])| / 100, + and([q2[1] >= minid_person /\ q2[1] <= maxid_person /\ (q2[2] >= minid_aircraft /\ q2[2] <= maxid_aircraft) <-> + q2 in defined(init[in_]) + | q2 : (int(0..100), int(0..100))]), + sum([toInt(q2[2]) | q2 <- init[in_]]) <= init_in__percentage_max * |defined(init[in_])| / 100 /\ + sum([toInt(q2[2]) | q2 <- init[in_]]) >= init_in__percentage_min * |defined(init[in_])| / 100, + and([q3 >= minid_aircraft /\ q3 <= maxid_aircraft <-> q3 in defined(init[fuel]) | q3 : int(0..100)]), + and([q3[2] >= init_fuel_range_min | q3 <- init[fuel]]), + and([q3[2] <= init_fuel_range_max | q3 <- init[fuel]]), + and([q4[1] >= minid_city /\ q4[1] <= maxid_city /\ (q4[2] >= minid_city /\ q4[2] <= maxid_city) <-> + q4 in defined(init[distance]) + | q4 : (int(0..100), int(0..100))]), + and([q4[2] >= init_distance_range_min | q4 <- init[distance]]), + and([q4[2] <= init_distance_range_max | q4 <- init[distance]]), + and([q5 >= minid_aircraft /\ q5 <= maxid_aircraft <-> q5 in defined(init[capacity]) | q5 : int(0..100)]), + and([q5[2] >= init_capacity_range_min | q5 <- init[capacity]]), + and([q5[2] <= init_capacity_range_max | q5 <- init[capacity]]), + and([q6 >= minid_aircraft /\ q6 <= maxid_aircraft <-> q6 in defined(init[onboard]) | q6 : int(0..100)]), + and([q6[2] >= init_onboard_range_min | q6 <- init[onboard]]), + and([q6[2] <= init_onboard_range_max | q6 <- init[onboard]]), + and([q7 >= 0 /\ q7 <= 0 <-> q7 in defined(init[total_fuel_used]) | q7 : int(0)]), + and([q7[2] >= init_total_fuel_used_range_min | q7 <- init[total_fuel_used]]), + and([q7[2] <= init_total_fuel_used_range_max | q7 <- init[total_fuel_used]]) +such that + and([image(init[fuel], a) > 0 /\ image(init[fuel], a) <= image(init[capacity], a) + | a : int(0..100), a >= minid_aircraft, a <= maxid_aircraft]), + and([image(init[onboard], a) = sum([toInt(value) | ((_, p2), value) <- init[in_], p2 = a]) + | a : int(0..100), a >= minid_aircraft, a <= maxid_aircraft]), + image(init[total_fuel_used], 0) = 0, + and([and([image(init[distance], (c1, c2)) = image(init[distance], (c2, c1)) /\ image(init[distance], (c1, c2)) > 0 + | c2 : int(0..100), c2 >= minid_city, c2 <= maxid_city]) + | c1 : int(0..100), c1 >= minid_city, c1 <= maxid_city]), + and([1 = sum([toInt(value = true) | ((p1, _), value) <- init[at_], p1 = a]) + | a : int(0..100), a >= minid_aircraft, a <= maxid_aircraft]), + and([!(1 = sum([toInt(value = true) | ((p1, _), value) <- init[at_], p = p1]) /\ + 1 = sum([toInt(value = true) | ((p1, _), value) <- init[in_], p = p1])) + /\ + (1 = sum([toInt(value = true) | ((p1, _), value) <- init[at_], p = p1]) \/ + 1 = sum([toInt(value = true) | ((p1, _), value) <- init[in_], p = p1])) + | p : int(0..100), p >= minid_person, p <= maxid_person]) +given goal_at__cardMin: int(0..10201) +given goal_at__cardMax: int(0..10201) +given goal_at__defined_tuple1_min: int(0..100) +given goal_at__defined_tuple1_max: int(0..100) +given goal_at__defined_tuple2_min: int(0..100) +given goal_at__defined_tuple2_max: int(0..100) +given goal_at__percentage_min: int(0..100) +given goal_at__percentage_max: int(0..100) +given goal_in__cardMin: int(0..10201) +given goal_in__cardMax: int(0..10201) +given goal_in__defined_tuple1_min: int(0..100) +given goal_in__defined_tuple1_max: int(0..100) +given goal_in__defined_tuple2_min: int(0..100) +given goal_in__defined_tuple2_max: int(0..100) +given goal_in__percentage_min: int(0..100) +given goal_in__percentage_max: int(0..100) +given goal_onboard_cardMin: int(0..101) +given goal_onboard_cardMax: int(0..101) +given goal_onboard_defined_min: int(0..100) +given goal_onboard_defined_max: int(0..100) +given goal_onboard_range_min: int(-65536..65536) +given goal_onboard_range_max: int(-65536..65536) +find goal: + record {at_ : function (maxSize 100) (int(0..100), int(0..100)) --> bool, + in_ : function (maxSize 100) (int(0..100), int(0..100)) --> bool, + onboard : function (maxSize 100) int(0..100) --> int(-65536..65536)} +such that + |goal[at_]| >= goal_at__cardMin /\ |goal[at_]| <= goal_at__cardMax, + and([q8[1, 1] >= goal_at__defined_tuple1_min | q8 <- goal[at_]]), + and([q8[1, 1] <= goal_at__defined_tuple1_max | q8 <- goal[at_]]), + and([q8[1, 1] >= minid_aircraft | q8 <- goal[at_]]), + and([q8[1, 1] <= maxid_person | q8 <- goal[at_]]), + and([q8[1, 2] >= goal_at__defined_tuple2_min | q8 <- goal[at_]]), + and([q8[1, 2] <= goal_at__defined_tuple2_max | q8 <- goal[at_]]), + and([q8[1, 2] >= minid_city | q8 <- goal[at_]]), + and([q8[1, 2] <= maxid_city | q8 <- goal[at_]]), + sum([toInt(q8[2]) | q8 <- goal[at_]]) <= goal_at__percentage_max * |defined(goal[at_])| / 100 /\ + sum([toInt(q8[2]) | q8 <- goal[at_]]) >= goal_at__percentage_min * |defined(goal[at_])| / 100, + |goal[in_]| >= goal_in__cardMin /\ |goal[in_]| <= goal_in__cardMax, + and([q9[1, 1] >= goal_in__defined_tuple1_min | q9 <- goal[in_]]), + and([q9[1, 1] <= goal_in__defined_tuple1_max | q9 <- goal[in_]]), + and([q9[1, 1] >= minid_person | q9 <- goal[in_]]), + and([q9[1, 1] <= maxid_person | q9 <- goal[in_]]), + and([q9[1, 2] >= goal_in__defined_tuple2_min | q9 <- goal[in_]]), + and([q9[1, 2] <= goal_in__defined_tuple2_max | q9 <- goal[in_]]), + and([q9[1, 2] >= minid_aircraft | q9 <- goal[in_]]), + and([q9[1, 2] <= maxid_aircraft | q9 <- goal[in_]]), + sum([toInt(q9[2]) | q9 <- goal[in_]]) <= goal_in__percentage_max * |defined(goal[in_])| / 100 /\ + sum([toInt(q9[2]) | q9 <- goal[in_]]) >= goal_in__percentage_min * |defined(goal[in_])| / 100, + |goal[onboard]| >= goal_onboard_cardMin /\ |goal[onboard]| <= goal_onboard_cardMax, + and([q10[1] >= goal_onboard_defined_min | q10 <- goal[onboard]]), + and([q10[1] <= goal_onboard_defined_max | q10 <- goal[onboard]]), + and([q10[1] >= minid_aircraft | q10 <- goal[onboard]]), + and([q10[1] <= maxid_aircraft | q10 <- goal[onboard]]), + and([q10[2] >= goal_onboard_range_min | q10 <- goal[onboard]]), + and([q10[2] <= goal_onboard_range_max | q10 <- goal[onboard]]) +such that and([image(goal[onboard], a) >= 0 | a : int(0..100), a >= minid_aircraft, a <= maxid_aircraft]) diff --git a/tests/custom/paramgen/record01/problem-instanceGenerator.essence.irace b/tests/custom/paramgen/record01/problem-instanceGenerator.essence.irace new file mode 100644 index 0000000000..b820e74483 --- /dev/null +++ b/tests/custom/paramgen/record01/problem-instanceGenerator.essence.irace @@ -0,0 +1,48 @@ +minid_aircraft_min "-minid_aircraft_min " i (0, 100) +minid_aircraft_max "-minid_aircraft_max " i (0, 100) +maxid_aircraft_min "-maxid_aircraft_min " i (0, 100) +maxid_aircraft_max "-maxid_aircraft_max " i (0, 100) +minid_person_min "-minid_person_min " i (0, 100) +minid_person_max "-minid_person_max " i (0, 100) +maxid_person_min "-maxid_person_min " i (0, 100) +maxid_person_max "-maxid_person_max " i (0, 100) +minid_city_min "-minid_city_min " i (0, 100) +minid_city_max "-minid_city_max " i (0, 100) +maxid_city_min "-maxid_city_min " i (0, 100) +maxid_city_max "-maxid_city_max " i (0, 100) +init_at__percentage_min "-init_at__percentage_min " i (0, 100) +init_at__percentage_max "-init_at__percentage_max " i (0, 100) +init_in__percentage_min "-init_in__percentage_min " i (0, 100) +init_in__percentage_max "-init_in__percentage_max " i (0, 100) +init_fuel_range_min "-init_fuel_range_min " i (-65536, 65536) +init_fuel_range_max "-init_fuel_range_max " i (-65536, 65536) +init_distance_range_min "-init_distance_range_min " i (-65536, 65536) +init_distance_range_max "-init_distance_range_max " i (-65536, 65536) +init_capacity_range_min "-init_capacity_range_min " i (-65536, 65536) +init_capacity_range_max "-init_capacity_range_max " i (-65536, 65536) +init_onboard_range_min "-init_onboard_range_min " i (-65536, 65536) +init_onboard_range_max "-init_onboard_range_max " i (-65536, 65536) +init_total_fuel_used_range_min "-init_total_fuel_used_range_min " i (-65536, 65536) +init_total_fuel_used_range_max "-init_total_fuel_used_range_max " i (-65536, 65536) +goal_at__cardMin "-goal_at__cardMin " i (0, 10201) +goal_at__cardMax "-goal_at__cardMax " i (0, 10201) +goal_at__defined_tuple1_min "-goal_at__defined_tuple1_min " i (0, 100) +goal_at__defined_tuple1_max "-goal_at__defined_tuple1_max " i (0, 100) +goal_at__defined_tuple2_min "-goal_at__defined_tuple2_min " i (0, 100) +goal_at__defined_tuple2_max "-goal_at__defined_tuple2_max " i (0, 100) +goal_at__percentage_min "-goal_at__percentage_min " i (0, 100) +goal_at__percentage_max "-goal_at__percentage_max " i (0, 100) +goal_in__cardMin "-goal_in__cardMin " i (0, 10201) +goal_in__cardMax "-goal_in__cardMax " i (0, 10201) +goal_in__defined_tuple1_min "-goal_in__defined_tuple1_min " i (0, 100) +goal_in__defined_tuple1_max "-goal_in__defined_tuple1_max " i (0, 100) +goal_in__defined_tuple2_min "-goal_in__defined_tuple2_min " i (0, 100) +goal_in__defined_tuple2_max "-goal_in__defined_tuple2_max " i (0, 100) +goal_in__percentage_min "-goal_in__percentage_min " i (0, 100) +goal_in__percentage_max "-goal_in__percentage_max " i (0, 100) +goal_onboard_cardMin "-goal_onboard_cardMin " i (0, 101) +goal_onboard_cardMax "-goal_onboard_cardMax " i (0, 101) +goal_onboard_defined_min "-goal_onboard_defined_min " i (0, 100) +goal_onboard_defined_max "-goal_onboard_defined_max " i (0, 100) +goal_onboard_range_min "-goal_onboard_range_min " i (-65536, 65536) +goal_onboard_range_max "-goal_onboard_range_max " i (-65536, 65536) diff --git a/tests/custom/paramgen/record01/problem-instanceRepair.essence b/tests/custom/paramgen/record01/problem-instanceRepair.essence new file mode 100644 index 0000000000..f97f3628f8 --- /dev/null +++ b/tests/custom/paramgen/record01/problem-instanceRepair.essence @@ -0,0 +1,181 @@ +language Essence 1.3 + +given minid_aircraft_min: int(0..100) +given minid_aircraft_max: int(0..100) +find repaired_minid_aircraft_min: int(0..100) +find repaired_minid_aircraft_max: int(0..100) +such that repaired_minid_aircraft_min <= repaired_minid_aircraft_max +given maxid_aircraft_min: int(0..100) +given maxid_aircraft_max: int(0..100) +find repaired_maxid_aircraft_min: int(0..100) +find repaired_maxid_aircraft_max: int(0..100) +such that repaired_maxid_aircraft_min <= repaired_maxid_aircraft_max +given minid_person_min: int(0..100) +given minid_person_max: int(0..100) +find repaired_minid_person_min: int(0..100) +find repaired_minid_person_max: int(0..100) +such that repaired_minid_person_min <= repaired_minid_person_max +given maxid_person_min: int(0..100) +given maxid_person_max: int(0..100) +find repaired_maxid_person_min: int(0..100) +find repaired_maxid_person_max: int(0..100) +such that repaired_maxid_person_min <= repaired_maxid_person_max +given minid_city_min: int(0..100) +given minid_city_max: int(0..100) +find repaired_minid_city_min: int(0..100) +find repaired_minid_city_max: int(0..100) +such that repaired_minid_city_min <= repaired_minid_city_max +given maxid_city_min: int(0..100) +given maxid_city_max: int(0..100) +find repaired_maxid_city_min: int(0..100) +find repaired_maxid_city_max: int(0..100) +such that repaired_maxid_city_min <= repaired_maxid_city_max +given init_at__percentage_min: int(0..100) +given init_at__percentage_max: int(0..100) +given init_in__percentage_min: int(0..100) +given init_in__percentage_max: int(0..100) +given init_fuel_range_min: int(-65536..65536) +given init_fuel_range_max: int(-65536..65536) +given init_distance_range_min: int(-65536..65536) +given init_distance_range_max: int(-65536..65536) +given init_capacity_range_min: int(-65536..65536) +given init_capacity_range_max: int(-65536..65536) +given init_onboard_range_min: int(-65536..65536) +given init_onboard_range_max: int(-65536..65536) +given init_total_fuel_used_range_min: int(-65536..65536) +given init_total_fuel_used_range_max: int(-65536..65536) +find repaired_init_at__percentage_min: int(0..100) +find repaired_init_at__percentage_max: int(0..100) +find repaired_init_in__percentage_min: int(0..100) +find repaired_init_in__percentage_max: int(0..100) +find repaired_init_fuel_range_min: int(-65536..65536) +find repaired_init_fuel_range_max: int(-65536..65536) +find repaired_init_distance_range_min: int(-65536..65536) +find repaired_init_distance_range_max: int(-65536..65536) +find repaired_init_capacity_range_min: int(-65536..65536) +find repaired_init_capacity_range_max: int(-65536..65536) +find repaired_init_onboard_range_min: int(-65536..65536) +find repaired_init_onboard_range_max: int(-65536..65536) +find repaired_init_total_fuel_used_range_min: int(-65536..65536) +find repaired_init_total_fuel_used_range_max: int(-65536..65536) +such that + repaired_init_at__percentage_max >= repaired_init_at__percentage_min, + repaired_init_in__percentage_max >= repaired_init_in__percentage_min, + repaired_init_fuel_range_min <= repaired_init_fuel_range_max, + repaired_init_distance_range_min <= repaired_init_distance_range_max, + repaired_init_capacity_range_min <= repaired_init_capacity_range_max, + repaired_init_onboard_range_min <= repaired_init_onboard_range_max, + repaired_init_total_fuel_used_range_min <= repaired_init_total_fuel_used_range_max +given goal_at__cardMin: int(0..10201) +given goal_at__cardMax: int(0..10201) +given goal_at__defined_tuple1_min: int(0..100) +given goal_at__defined_tuple1_max: int(0..100) +given goal_at__defined_tuple2_min: int(0..100) +given goal_at__defined_tuple2_max: int(0..100) +given goal_at__percentage_min: int(0..100) +given goal_at__percentage_max: int(0..100) +given goal_in__cardMin: int(0..10201) +given goal_in__cardMax: int(0..10201) +given goal_in__defined_tuple1_min: int(0..100) +given goal_in__defined_tuple1_max: int(0..100) +given goal_in__defined_tuple2_min: int(0..100) +given goal_in__defined_tuple2_max: int(0..100) +given goal_in__percentage_min: int(0..100) +given goal_in__percentage_max: int(0..100) +given goal_onboard_cardMin: int(0..101) +given goal_onboard_cardMax: int(0..101) +given goal_onboard_defined_min: int(0..100) +given goal_onboard_defined_max: int(0..100) +given goal_onboard_range_min: int(-65536..65536) +given goal_onboard_range_max: int(-65536..65536) +find repaired_goal_at__cardMin: int(0..10201) +find repaired_goal_at__cardMax: int(0..10201) +find repaired_goal_at__defined_tuple1_min: int(0..100) +find repaired_goal_at__defined_tuple1_max: int(0..100) +find repaired_goal_at__defined_tuple2_min: int(0..100) +find repaired_goal_at__defined_tuple2_max: int(0..100) +find repaired_goal_at__percentage_min: int(0..100) +find repaired_goal_at__percentage_max: int(0..100) +find repaired_goal_in__cardMin: int(0..10201) +find repaired_goal_in__cardMax: int(0..10201) +find repaired_goal_in__defined_tuple1_min: int(0..100) +find repaired_goal_in__defined_tuple1_max: int(0..100) +find repaired_goal_in__defined_tuple2_min: int(0..100) +find repaired_goal_in__defined_tuple2_max: int(0..100) +find repaired_goal_in__percentage_min: int(0..100) +find repaired_goal_in__percentage_max: int(0..100) +find repaired_goal_onboard_cardMin: int(0..101) +find repaired_goal_onboard_cardMax: int(0..101) +find repaired_goal_onboard_defined_min: int(0..100) +find repaired_goal_onboard_defined_max: int(0..100) +find repaired_goal_onboard_range_min: int(-65536..65536) +find repaired_goal_onboard_range_max: int(-65536..65536) +such that + repaired_goal_at__cardMin <= repaired_goal_at__cardMax, + (repaired_goal_at__defined_tuple1_max - repaired_goal_at__defined_tuple1_min + 1) * + (repaired_goal_at__defined_tuple2_max - repaired_goal_at__defined_tuple2_min + 1) + >= repaired_goal_at__cardMax, + repaired_goal_at__defined_tuple1_min >= repaired_minid_aircraft_min, + repaired_goal_at__defined_tuple1_max <= repaired_maxid_person_max, + repaired_goal_at__defined_tuple2_min >= repaired_minid_city_min, + repaired_goal_at__defined_tuple2_max <= repaired_maxid_city_max, + repaired_goal_at__percentage_max >= repaired_goal_at__percentage_min, + repaired_goal_at__defined_tuple1_min <= repaired_goal_at__defined_tuple1_max, + repaired_goal_at__defined_tuple2_min <= repaired_goal_at__defined_tuple2_max, + repaired_goal_in__cardMin <= repaired_goal_in__cardMax, + (repaired_goal_in__defined_tuple1_max - repaired_goal_in__defined_tuple1_min + 1) * + (repaired_goal_in__defined_tuple2_max - repaired_goal_in__defined_tuple2_min + 1) + >= repaired_goal_in__cardMax, + repaired_goal_in__defined_tuple1_min >= repaired_minid_person_min, + repaired_goal_in__defined_tuple1_max <= repaired_maxid_person_max, + repaired_goal_in__defined_tuple2_min >= repaired_minid_aircraft_min, + repaired_goal_in__defined_tuple2_max <= repaired_maxid_aircraft_max, + repaired_goal_in__percentage_max >= repaired_goal_in__percentage_min, + repaired_goal_in__defined_tuple1_min <= repaired_goal_in__defined_tuple1_max, + repaired_goal_in__defined_tuple2_min <= repaired_goal_in__defined_tuple2_max, + repaired_goal_onboard_cardMin <= repaired_goal_onboard_cardMax, + repaired_goal_onboard_defined_max - repaired_goal_onboard_defined_min + 1 >= repaired_goal_onboard_cardMax, + repaired_goal_onboard_defined_min >= repaired_minid_aircraft_min, + repaired_goal_onboard_defined_max <= repaired_maxid_aircraft_max, + repaired_goal_onboard_defined_min <= repaired_goal_onboard_defined_max, + repaired_goal_onboard_range_min <= repaired_goal_onboard_range_max +minimising + sum([|repaired_minid_aircraft_min - minid_aircraft_min|, |repaired_minid_aircraft_max - minid_aircraft_max|, + |repaired_maxid_aircraft_min - maxid_aircraft_min|, |repaired_maxid_aircraft_max - maxid_aircraft_max|, + |repaired_minid_person_min - minid_person_min|, |repaired_minid_person_max - minid_person_max|, + |repaired_maxid_person_min - maxid_person_min|, |repaired_maxid_person_max - maxid_person_max|, + |repaired_minid_city_min - minid_city_min|, |repaired_minid_city_max - minid_city_max|, + |repaired_maxid_city_min - maxid_city_min|, |repaired_maxid_city_max - maxid_city_max|, + |repaired_init_at__percentage_min - init_at__percentage_min|, + |repaired_init_at__percentage_max - init_at__percentage_max|, + |repaired_init_in__percentage_min - init_in__percentage_min|, + |repaired_init_in__percentage_max - init_in__percentage_max|, + |repaired_init_fuel_range_min - init_fuel_range_min|, |repaired_init_fuel_range_max - init_fuel_range_max|, + |repaired_init_distance_range_min - init_distance_range_min|, + |repaired_init_distance_range_max - init_distance_range_max|, + |repaired_init_capacity_range_min - init_capacity_range_min|, + |repaired_init_capacity_range_max - init_capacity_range_max|, + |repaired_init_onboard_range_min - init_onboard_range_min|, + |repaired_init_onboard_range_max - init_onboard_range_max|, + |repaired_init_total_fuel_used_range_min - init_total_fuel_used_range_min|, + |repaired_init_total_fuel_used_range_max - init_total_fuel_used_range_max|, + |repaired_goal_at__cardMin - goal_at__cardMin|, |repaired_goal_at__cardMax - goal_at__cardMax|, + |repaired_goal_at__defined_tuple1_min - goal_at__defined_tuple1_min|, + |repaired_goal_at__defined_tuple1_max - goal_at__defined_tuple1_max|, + |repaired_goal_at__defined_tuple2_min - goal_at__defined_tuple2_min|, + |repaired_goal_at__defined_tuple2_max - goal_at__defined_tuple2_max|, + |repaired_goal_at__percentage_min - goal_at__percentage_min|, + |repaired_goal_at__percentage_max - goal_at__percentage_max|, |repaired_goal_in__cardMin - goal_in__cardMin|, + |repaired_goal_in__cardMax - goal_in__cardMax|, + |repaired_goal_in__defined_tuple1_min - goal_in__defined_tuple1_min|, + |repaired_goal_in__defined_tuple1_max - goal_in__defined_tuple1_max|, + |repaired_goal_in__defined_tuple2_min - goal_in__defined_tuple2_min|, + |repaired_goal_in__defined_tuple2_max - goal_in__defined_tuple2_max|, + |repaired_goal_in__percentage_min - goal_in__percentage_min|, + |repaired_goal_in__percentage_max - goal_in__percentage_max|, + |repaired_goal_onboard_cardMin - goal_onboard_cardMin|, |repaired_goal_onboard_cardMax - goal_onboard_cardMax|, + |repaired_goal_onboard_defined_min - goal_onboard_defined_min|, + |repaired_goal_onboard_defined_max - goal_onboard_defined_max|, + |repaired_goal_onboard_range_min - goal_onboard_range_min|, + |repaired_goal_onboard_range_max - goal_onboard_range_max|; + int(1..48)]) diff --git a/tests/custom/permutations/01_representation/enum/0005_find_permutation_size_4_of_int1_4/permutation.essence b/tests/custom/permutations/01_representation/enum/0005_find_permutation_size_4_of_int1_4/permutation.essence index 26786093fd..168c3d1fcf 100644 --- a/tests/custom/permutations/01_representation/enum/0005_find_permutation_size_4_of_int1_4/permutation.essence +++ b/tests/custom/permutations/01_representation/enum/0005_find_permutation_size_4_of_int1_4/permutation.essence @@ -1,5 +1,5 @@ letting n be new type enum {E1,E2,E3,E4} -find p : permutation (size 4) of n +find p : permutation (numMoved 4) of n such that true diff --git a/tests/custom/permutations/01_representation/enum/0006_find_permutation_size_0_of_int1_4/permutation.essence b/tests/custom/permutations/01_representation/enum/0006_find_permutation_size_0_of_int1_4/permutation.essence index 9a91f2f8d1..416f090d31 100644 --- a/tests/custom/permutations/01_representation/enum/0006_find_permutation_size_0_of_int1_4/permutation.essence +++ b/tests/custom/permutations/01_representation/enum/0006_find_permutation_size_0_of_int1_4/permutation.essence @@ -1,5 +1,5 @@ letting n be new type enum {E1,E2,E3,E4} -find p : permutation (size 0) of n +find p : permutation (numMoved 0) of n such that true diff --git a/tests/custom/permutations/01_representation/enum/0010_find_permutation_maxSize_2_of_int1_3/permutation.essence b/tests/custom/permutations/01_representation/enum/0010_find_permutation_maxSize_2_of_int1_3/permutation.essence index 5e23322970..1c30cf7fba 100644 --- a/tests/custom/permutations/01_representation/enum/0010_find_permutation_maxSize_2_of_int1_3/permutation.essence +++ b/tests/custom/permutations/01_representation/enum/0010_find_permutation_maxSize_2_of_int1_3/permutation.essence @@ -1,5 +1,5 @@ letting n be new type enum {E1,E2,E3} -find p : permutation (maxSize 2) of n +find p : permutation (maxNumMoved 2) of n such that true diff --git a/tests/custom/permutations/01_representation/enum/0011_find_permutation_minSize_2_of_int1_3/permutation.essence b/tests/custom/permutations/01_representation/enum/0011_find_permutation_minSize_2_of_int1_3/permutation.essence index 3da37a3987..ff3c1e4829 100644 --- a/tests/custom/permutations/01_representation/enum/0011_find_permutation_minSize_2_of_int1_3/permutation.essence +++ b/tests/custom/permutations/01_representation/enum/0011_find_permutation_minSize_2_of_int1_3/permutation.essence @@ -1,5 +1,5 @@ letting n be new type enum {E1,E2,E3} -find p : permutation (minSize 2) of n +find p : permutation (minNumMoved 2) of n such that true diff --git a/tests/custom/permutations/01_representation/enum/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/permutation.essence b/tests/custom/permutations/01_representation/enum/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/permutation.essence index 6fc7ffd73a..efdb41fa4d 100644 --- a/tests/custom/permutations/01_representation/enum/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/permutation.essence +++ b/tests/custom/permutations/01_representation/enum/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/permutation.essence @@ -1,5 +1,5 @@ letting n be new type enum {E1,E2,E3,E4} -find p : permutation (minSize 2, maxSize 3) of n +find p : permutation (minNumMoved 2, maxNumMoved 3) of n such that true diff --git a/tests/custom/permutations/01_representation/int/0005_find_permutation_size_4_of_int1_4/permutation.essence b/tests/custom/permutations/01_representation/int/0005_find_permutation_size_4_of_int1_4/permutation.essence index 63899fe581..89236f50f6 100644 --- a/tests/custom/permutations/01_representation/int/0005_find_permutation_size_4_of_int1_4/permutation.essence +++ b/tests/custom/permutations/01_representation/int/0005_find_permutation_size_4_of_int1_4/permutation.essence @@ -1,5 +1,5 @@ letting n be 4 -find p : permutation (size n) of int(1..n) +find p : permutation (numMoved n) of int(1..n) such that true diff --git a/tests/custom/permutations/01_representation/int/0006_find_permutation_size_0_of_int1_4/permutation.essence b/tests/custom/permutations/01_representation/int/0006_find_permutation_size_0_of_int1_4/permutation.essence index 8c60c7b839..ccafebc41b 100644 --- a/tests/custom/permutations/01_representation/int/0006_find_permutation_size_0_of_int1_4/permutation.essence +++ b/tests/custom/permutations/01_representation/int/0006_find_permutation_size_0_of_int1_4/permutation.essence @@ -1,5 +1,5 @@ letting n be 4 -find p : permutation (size 0) of int(1..n) +find p : permutation (numMoved 0) of int(1..n) such that true diff --git a/tests/custom/permutations/01_representation/int/0010_find_permutation_maxSize_2_of_int1_3/permutation.essence b/tests/custom/permutations/01_representation/int/0010_find_permutation_maxSize_2_of_int1_3/permutation.essence index c5f650a6ea..15a188fb94 100644 --- a/tests/custom/permutations/01_representation/int/0010_find_permutation_maxSize_2_of_int1_3/permutation.essence +++ b/tests/custom/permutations/01_representation/int/0010_find_permutation_maxSize_2_of_int1_3/permutation.essence @@ -1,5 +1,5 @@ letting n be 3 -find p : permutation (maxSize 2) of int(1..n) +find p : permutation (maxNumMoved 2) of int(1..n) such that true diff --git a/tests/custom/permutations/01_representation/int/0011_find_permutation_minSize_2_of_int1_3/permutation.essence b/tests/custom/permutations/01_representation/int/0011_find_permutation_minSize_2_of_int1_3/permutation.essence index 73007c1924..c9843c284c 100644 --- a/tests/custom/permutations/01_representation/int/0011_find_permutation_minSize_2_of_int1_3/permutation.essence +++ b/tests/custom/permutations/01_representation/int/0011_find_permutation_minSize_2_of_int1_3/permutation.essence @@ -1,5 +1,5 @@ letting n be 3 -find p : permutation (minSize 2) of int(1..n) +find p : permutation (minNumMoved 2) of int(1..n) such that true diff --git a/tests/custom/permutations/01_representation/int/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/permutation.essence b/tests/custom/permutations/01_representation/int/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/permutation.essence index 4460f93ee0..8d766f503c 100644 --- a/tests/custom/permutations/01_representation/int/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/permutation.essence +++ b/tests/custom/permutations/01_representation/int/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/permutation.essence @@ -1,5 +1,5 @@ letting n be 4 -find p : permutation (minSize 2, maxSize 3) of int(1..n) +find p : permutation (minNumMoved 2, maxNumMoved 3) of int(1..n) such that true diff --git a/tests/custom/permutations/01_representation/unnamed/0005_find_permutation_size_4_of_int1_4/permutation.essence b/tests/custom/permutations/01_representation/unnamed/0005_find_permutation_size_4_of_int1_4/permutation.essence index 355a19fd10..7e3103b9ae 100644 --- a/tests/custom/permutations/01_representation/unnamed/0005_find_permutation_size_4_of_int1_4/permutation.essence +++ b/tests/custom/permutations/01_representation/unnamed/0005_find_permutation_size_4_of_int1_4/permutation.essence @@ -1,5 +1,5 @@ letting n be new type of size 4 -find p : permutation (size 4) of n +find p : permutation (numMoved 4) of n such that true diff --git a/tests/custom/permutations/01_representation/unnamed/0006_find_permutation_size_0_of_int1_4/permutation.essence b/tests/custom/permutations/01_representation/unnamed/0006_find_permutation_size_0_of_int1_4/permutation.essence index 264e52e6b7..bfbce4c1b3 100644 --- a/tests/custom/permutations/01_representation/unnamed/0006_find_permutation_size_0_of_int1_4/permutation.essence +++ b/tests/custom/permutations/01_representation/unnamed/0006_find_permutation_size_0_of_int1_4/permutation.essence @@ -1,5 +1,5 @@ letting n be new type of size 4 -find p : permutation (size 0) of n +find p : permutation (numMoved 0) of n such that true diff --git a/tests/custom/permutations/01_representation/unnamed/0010_find_permutation_maxSize_2_of_int1_3/permutation.essence b/tests/custom/permutations/01_representation/unnamed/0010_find_permutation_maxSize_2_of_int1_3/permutation.essence index 7e78359040..f934e59fef 100644 --- a/tests/custom/permutations/01_representation/unnamed/0010_find_permutation_maxSize_2_of_int1_3/permutation.essence +++ b/tests/custom/permutations/01_representation/unnamed/0010_find_permutation_maxSize_2_of_int1_3/permutation.essence @@ -1,5 +1,5 @@ letting n be new type of size 3 -find p : permutation (maxSize 2) of n +find p : permutation (maxNumMoved 2) of n such that true diff --git a/tests/custom/permutations/01_representation/unnamed/0011_find_permutation_minSize_2_of_int1_3/permutation.essence b/tests/custom/permutations/01_representation/unnamed/0011_find_permutation_minSize_2_of_int1_3/permutation.essence index b2a3c523d4..050ba156ba 100644 --- a/tests/custom/permutations/01_representation/unnamed/0011_find_permutation_minSize_2_of_int1_3/permutation.essence +++ b/tests/custom/permutations/01_representation/unnamed/0011_find_permutation_minSize_2_of_int1_3/permutation.essence @@ -1,5 +1,5 @@ letting n be new type of size 3 -find p : permutation (minSize 2) of n +find p : permutation (minNumMoved 2) of n such that true diff --git a/tests/custom/permutations/01_representation/unnamed/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/permutation.essence b/tests/custom/permutations/01_representation/unnamed/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/permutation.essence index 5083fed5ca..6e6fc720e0 100644 --- a/tests/custom/permutations/01_representation/unnamed/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/permutation.essence +++ b/tests/custom/permutations/01_representation/unnamed/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/permutation.essence @@ -1,5 +1,5 @@ letting n be new type of size 4 -find p : permutation (minSize 2, maxSize 3) of n +find p : permutation (minNumMoved 2, maxNumMoved 3) of n such that true diff --git a/tests/custom/permutations/02_cardinality/enum/0003_find_permutation/permutation.essence b/tests/custom/permutations/02_cardinality/enum/0003_find_permutation/permutation.essence index 663987f4f6..37609a03df 100644 --- a/tests/custom/permutations/02_cardinality/enum/0003_find_permutation/permutation.essence +++ b/tests/custom/permutations/02_cardinality/enum/0003_find_permutation/permutation.essence @@ -1,5 +1,5 @@ letting n be new type enum {E1,E2,E3,E4,E5,E6} -find p : permutation (size 4) of n +find p : permutation (numMoved 4) of n find i : int(0..10) diff --git a/tests/custom/permutations/02_cardinality/int/0003_find_permutation/permutation.essence b/tests/custom/permutations/02_cardinality/int/0003_find_permutation/permutation.essence index 59127b82f2..d45cd82f95 100644 --- a/tests/custom/permutations/02_cardinality/int/0003_find_permutation/permutation.essence +++ b/tests/custom/permutations/02_cardinality/int/0003_find_permutation/permutation.essence @@ -1,4 +1,4 @@ -find p : permutation (size 4) of int(1..6) +find p : permutation (numMoved 4) of int(1..6) find i : int(0..10) diff --git a/tests/custom/permutations/02_cardinality/unnamed/0003_find_permutation/permutation.essence b/tests/custom/permutations/02_cardinality/unnamed/0003_find_permutation/permutation.essence index 05bc8e04fa..dc3f7f4b8d 100644 --- a/tests/custom/permutations/02_cardinality/unnamed/0003_find_permutation/permutation.essence +++ b/tests/custom/permutations/02_cardinality/unnamed/0003_find_permutation/permutation.essence @@ -1,5 +1,5 @@ letting n be new type of size 6 -find p : permutation (size 4) of n +find p : permutation (numMoved 4) of n find i : int(0..10) diff --git a/tests/custom/permutations/03_generators/enum/0003_find_permutation_in_generator/permutation.essence b/tests/custom/permutations/03_generators/enum/0003_find_permutation_in_generator/permutation.essence index 6bfee9c393..00309a7bd3 100644 --- a/tests/custom/permutations/03_generators/enum/0003_find_permutation_in_generator/permutation.essence +++ b/tests/custom/permutations/03_generators/enum/0003_find_permutation_in_generator/permutation.essence @@ -1,5 +1,5 @@ letting n be new type enum {E1,E2,E3,E4} -find p : permutation (size 3) of n +find p : permutation (numMoved 3) of n find s : set (size 3) of (n,n) such that diff --git a/tests/custom/permutations/03_generators/enum/0004_find_permutation_in_generator/permutation.essence b/tests/custom/permutations/03_generators/enum/0004_find_permutation_in_generator/permutation.essence index 80c1a9b4e3..1b7555382e 100644 --- a/tests/custom/permutations/03_generators/enum/0004_find_permutation_in_generator/permutation.essence +++ b/tests/custom/permutations/03_generators/enum/0004_find_permutation_in_generator/permutation.essence @@ -1,5 +1,5 @@ letting n be new type enum {E1,E2,E3,E4} -find p : permutation (size 3) of n +find p : permutation (numMoved 3) of n such that diff --git a/tests/custom/permutations/03_generators/int/0003_find_permutation_in_generator/permutation.essence b/tests/custom/permutations/03_generators/int/0003_find_permutation_in_generator/permutation.essence index 33a9d426d3..b3e71b3d93 100644 --- a/tests/custom/permutations/03_generators/int/0003_find_permutation_in_generator/permutation.essence +++ b/tests/custom/permutations/03_generators/int/0003_find_permutation_in_generator/permutation.essence @@ -1,4 +1,4 @@ -find p : permutation (size 3) of int(1..4) +find p : permutation (numMoved 3) of int(1..4) find s : set (size 3) of (int(1..4),int(1..4)) such that diff --git a/tests/custom/permutations/03_generators/int/0004_find_permutation_in_forall/permutation.essence b/tests/custom/permutations/03_generators/int/0004_find_permutation_in_forall/permutation.essence index d4ccc8d532..28fa6d4963 100644 --- a/tests/custom/permutations/03_generators/int/0004_find_permutation_in_forall/permutation.essence +++ b/tests/custom/permutations/03_generators/int/0004_find_permutation_in_forall/permutation.essence @@ -1,4 +1,4 @@ -find p : permutation (size 3) of int(1..4) +find p : permutation (numMoved 3) of int(1..4) find s : set (size 3) of (int(1..4),int(1..4)) such that diff --git a/tests/custom/permutations/03_generators/int/0005_find_permutation_in_forall/permutation.essence b/tests/custom/permutations/03_generators/int/0005_find_permutation_in_forall/permutation.essence index 3c63df7e7d..c20f17d2be 100644 --- a/tests/custom/permutations/03_generators/int/0005_find_permutation_in_forall/permutation.essence +++ b/tests/custom/permutations/03_generators/int/0005_find_permutation_in_forall/permutation.essence @@ -1,4 +1,4 @@ -find p : permutation (size 3) of int(1..4) +find p : permutation (numMoved 3) of int(1..4) find s : set (size 3) of (int(1..4),int(1..4)) such that diff --git a/tests/custom/permutations/03_generators/unnamed/0003_find_permutation_in_generator/permutation.essence b/tests/custom/permutations/03_generators/unnamed/0003_find_permutation_in_generator/permutation.essence index 3d0835eaf5..1b5759ebc0 100644 --- a/tests/custom/permutations/03_generators/unnamed/0003_find_permutation_in_generator/permutation.essence +++ b/tests/custom/permutations/03_generators/unnamed/0003_find_permutation_in_generator/permutation.essence @@ -1,5 +1,5 @@ letting n be new type of size 4 -find p : permutation (size 3) of n +find p : permutation (numMoved 3) of n find s : set (size 3) of (n,n) such that diff --git a/tests/custom/permutations/05_equality/enum/0006_in_comprehension/permutation.essence b/tests/custom/permutations/05_equality/enum/0006_in_comprehension/permutation.essence index 673ee7f52d..2d507c5fdb 100644 --- a/tests/custom/permutations/05_equality/enum/0006_in_comprehension/permutation.essence +++ b/tests/custom/permutations/05_equality/enum/0006_in_comprehension/permutation.essence @@ -1,6 +1,6 @@ letting n be new type enum {E1,E2,E3,E4} -find p : permutation (size 4) of n -find q : permutation (size 4) of n +find p : permutation (numMoved 4) of n +find q : permutation (numMoved 4) of n such that [pt != qt | pt <- p, qt <- q] diff --git a/tests/custom/permutations/05_equality/int/0006_in_comprehension/permutation.essence b/tests/custom/permutations/05_equality/int/0006_in_comprehension/permutation.essence index a3aac36aaa..9c6ff50d00 100644 --- a/tests/custom/permutations/05_equality/int/0006_in_comprehension/permutation.essence +++ b/tests/custom/permutations/05_equality/int/0006_in_comprehension/permutation.essence @@ -1,5 +1,5 @@ -find p : permutation (size 4) of int(1..4) -find q : permutation (size 4) of int(1..4) +find p : permutation (numMoved 4) of int(1..4) +find q : permutation (numMoved 4) of int(1..4) such that [pt != qt | pt <- p, qt <- q] diff --git a/tests/custom/permutations/05_equality/unnamed/0006_in_comprehension/permutation.essence b/tests/custom/permutations/05_equality/unnamed/0006_in_comprehension/permutation.essence index 96c13569f4..0fe8646429 100644 --- a/tests/custom/permutations/05_equality/unnamed/0006_in_comprehension/permutation.essence +++ b/tests/custom/permutations/05_equality/unnamed/0006_in_comprehension/permutation.essence @@ -1,6 +1,6 @@ letting n be new type of size 4 -find p : permutation (size 4) of n -find q : permutation (size 4) of n +find p : permutation (numMoved 4) of n +find q : permutation (numMoved 4) of n such that [pt != qt | pt <- p, qt <- q] diff --git a/tests/custom/permutations/12_transform_list/unnamed/0030_find_permutation/stdout.expected b/tests/custom/permutations/12_transform_list/unnamed/0030_find_permutation/stdout.expected index 51e1357f41..d10ebe7b59 100644 --- a/tests/custom/permutations/12_transform_list/unnamed/0030_find_permutation/stdout.expected +++ b/tests/custom/permutations/12_transform_list/unnamed/0030_find_permutation/stdout.expected @@ -1,13 +1 @@ Generating models for permutation.essence -Generated models: model000001.eprime -Saved under: conjure-output -Savile Row: model000001.eprime -Running minion for domain filtering. -Running solver: minion -Copying solution to: permutation.solution -language Essence 1.3 - -letting n be new type enum {n_1, n_2, n_3, n_4} -letting b be n_3 -letting c be n_4 -letting p be permutation((n_3, n_4)) diff --git a/tests/custom/permutations/17_transform_partition/unnamed/0010_find_partition_of_unnamed/permutation.essence b/tests/custom/permutations/17_transform_partition/unnamed/0010_find_partition_of_unnamed/permutation.essence index 325b1db590..15d095bddd 100644 --- a/tests/custom/permutations/17_transform_partition/unnamed/0010_find_partition_of_unnamed/permutation.essence +++ b/tests/custom/permutations/17_transform_partition/unnamed/0010_find_partition_of_unnamed/permutation.essence @@ -1,5 +1,5 @@ letting n be new type of size 4 find a : partition from n find b : partition from n -find p : permutation (size 3) of n +find p : permutation (numMoved 3) of n such that b = transform(p,a) /\ a != b diff --git a/tests/custom/permutations/18_transform_matrix/enum/0010_find_permutation_indexing_given_matrix/stdout.expected b/tests/custom/permutations/18_transform_matrix/enum/0010_find_permutation_indexing_given_matrix/stdout.expected deleted file mode 100644 index 12b5773ca8..0000000000 --- a/tests/custom/permutations/18_transform_matrix/enum/0010_find_permutation_indexing_given_matrix/stdout.expected +++ /dev/null @@ -1,9 +0,0 @@ -Generating models for permutation.essence -Generated models: model000001.eprime -Saved under: conjure-output -Savile Row: model000001.eprime permutation.param -Copying solution to: permutation-permutation.solution -language Essence 1.3 - -letting p be permutation((e_6, e_8, e_7)) -letting t be [e_5, e_8, e_6, e_7; int(1..4)] diff --git a/tests/custom/permutations/18_transform_matrix/enum/0015_find_permutation_indexing_given_matrix/stdout.expected b/tests/custom/permutations/18_transform_matrix/enum/0015_find_permutation_indexing_given_matrix/stdout.expected index e0e4e2f757..d10ebe7b59 100644 --- a/tests/custom/permutations/18_transform_matrix/enum/0015_find_permutation_indexing_given_matrix/stdout.expected +++ b/tests/custom/permutations/18_transform_matrix/enum/0015_find_permutation_indexing_given_matrix/stdout.expected @@ -1,8 +1 @@ Generating models for permutation.essence -Generated models: model000001.eprime -Saved under: conjure-output -Savile Row: model000001.eprime -Copying solution to: permutation.solution -language Essence 1.3 - -letting p be permutation((e_6, e_8, e_7)) diff --git a/tests/custom/permutations/18_transform_matrix/enum/0040_find_permutation_find_matrices/permutation.essence b/tests/custom/permutations/18_transform_matrix/enum/0040_find_permutation_find_matrices/permutation.essence index 4b57afdd48..d4c64297b4 100644 --- a/tests/custom/permutations/18_transform_matrix/enum/0040_find_permutation_find_matrices/permutation.essence +++ b/tests/custom/permutations/18_transform_matrix/enum/0040_find_permutation_find_matrices/permutation.essence @@ -1,6 +1,6 @@ letting n be new type enum {e_5,e_6,e_7,e_8} -find p : permutation (size 3) of n +find p : permutation (numMoved 3) of n find s : matrix indexed by [int(1..2)] of n find t : matrix indexed by [int(1..2)] of n diff --git a/tests/custom/permutations/18_transform_matrix/int/0010_find_permutation_indexing_given_matrix/stdout.expected b/tests/custom/permutations/18_transform_matrix/int/0010_find_permutation_indexing_given_matrix/stdout.expected index 0a2c68038b..d10ebe7b59 100644 --- a/tests/custom/permutations/18_transform_matrix/int/0010_find_permutation_indexing_given_matrix/stdout.expected +++ b/tests/custom/permutations/18_transform_matrix/int/0010_find_permutation_indexing_given_matrix/stdout.expected @@ -1,8 +1 @@ Generating models for permutation.essence -Generated models: model000001.eprime -Saved under: conjure-output -Savile Row: model000001.eprime permutation.param -Copying solution to: permutation-permutation.solution -language Essence 1.3 - -letting p be permutation((2, 4, 3)) diff --git a/tests/custom/permutations/18_transform_matrix/int/0015_find_permutation_indexing_given_matrix/stdout.expected b/tests/custom/permutations/18_transform_matrix/int/0015_find_permutation_indexing_given_matrix/stdout.expected index 31090bced1..d10ebe7b59 100644 --- a/tests/custom/permutations/18_transform_matrix/int/0015_find_permutation_indexing_given_matrix/stdout.expected +++ b/tests/custom/permutations/18_transform_matrix/int/0015_find_permutation_indexing_given_matrix/stdout.expected @@ -1,8 +1 @@ Generating models for permutation.essence -Generated models: model000001.eprime -Saved under: conjure-output -Savile Row: model000001.eprime -Copying solution to: permutation.solution -language Essence 1.3 - -letting p be permutation((2, 4, 3)) diff --git a/tests/custom/permutations/18_transform_matrix/unnamed/0040_find_permutation_find_matrices/permutation.essence b/tests/custom/permutations/18_transform_matrix/unnamed/0040_find_permutation_find_matrices/permutation.essence index d2239aa3da..f0fd95fa61 100644 --- a/tests/custom/permutations/18_transform_matrix/unnamed/0040_find_permutation_find_matrices/permutation.essence +++ b/tests/custom/permutations/18_transform_matrix/unnamed/0040_find_permutation_find_matrices/permutation.essence @@ -1,6 +1,6 @@ letting n be new type of size 4 -find p : permutation (size 3) of n +find p : permutation (numMoved 3) of n find s : matrix indexed by [int(1..4)] of n find t : matrix indexed by [int(1..4)] of n diff --git a/tests/custom/permutations/19_complications/multiple_enums/0010_set_of_tuples/permutation.essence b/tests/custom/permutations/19_complications/multiple_enums/0010_set_of_tuples/permutation.essence index 0d85a6ad7a..6a8f82250b 100644 --- a/tests/custom/permutations/19_complications/multiple_enums/0010_set_of_tuples/permutation.essence +++ b/tests/custom/permutations/19_complications/multiple_enums/0010_set_of_tuples/permutation.essence @@ -1,7 +1,7 @@ letting e be new type enum {e_1,e_2,e_3,e_4} letting n be new type enum {n_1,n_2,n_3,n_4} -find p : permutation (size 3) of n +find p : permutation (numMoved 3) of n letting s be {(e_1,n_3),(e_2,n_4)} find t : set of (e,n) diff --git a/tests/custom/permutations/20_counting/0010_set_of_permutations_size_3/stdout.expected b/tests/custom/permutations/20_counting/0010_set_of_permutations_size_3/stdout.expected index eedac71a60..d10ebe7b59 100644 --- a/tests/custom/permutations/20_counting/0010_set_of_permutations_size_3/stdout.expected +++ b/tests/custom/permutations/20_counting/0010_set_of_permutations_size_3/stdout.expected @@ -1,12 +1 @@ Generating models for permutation.essence -Generated models: model000001.eprime -Saved under: conjure-output -Savile Row: model000001.eprime -Running minion for domain filtering. -Running solver: minion -Copying solution to: permutation.solution -language Essence 1.3 - -letting s be - {permutation(), permutation((1, 2)), permutation((1, 2, 3)), permutation((1, 3)), permutation((1, 3, 2)), - permutation((2, 3))} diff --git a/tests/custom/permutations/20_counting/0020_set_of_permutations_size_4/stdout.expected b/tests/custom/permutations/20_counting/0020_set_of_permutations_size_4/stdout.expected index 212b20776e..d10ebe7b59 100644 --- a/tests/custom/permutations/20_counting/0020_set_of_permutations_size_4/stdout.expected +++ b/tests/custom/permutations/20_counting/0020_set_of_permutations_size_4/stdout.expected @@ -1,14 +1 @@ Generating models for permutation.essence -Generated models: model000001.eprime -Saved under: conjure-output -Savile Row: model000001.eprime -Running minion for domain filtering. -Running solver: minion -Copying solution to: permutation.solution -language Essence 1.3 - -letting s be - {permutation(), permutation((1, 2)), permutation((1, 2), (3, 4)), permutation((1, 2, 3)), - permutation((1, 2, 3, 4)), permutation((1, 2, 4)), permutation((1, 2, 4, 3)), permutation((1, 3)), - permutation((1, 3, 2)), permutation((1, 3, 4)), permutation((1, 3, 4, 2)), permutation((2, 3)), - permutation((2, 3, 4)), permutation((2, 4)), permutation((2, 4, 3)), permutation((3, 4))} diff --git a/tests/custom/permutations/21_set_comprehension/stdout.expected b/tests/custom/permutations/21_set_comprehension/stdout.expected index 3446d90c20..f8cfc8e84c 100644 --- a/tests/custom/permutations/21_set_comprehension/stdout.expected +++ b/tests/custom/permutations/21_set_comprehension/stdout.expected @@ -1,38 +1 @@ Generating models for set_comprehension.essence -Generated models: model000001.eprime -Saved under: conjure-output -Savile Row: model000001.eprime -language ESSENCE' 1.0 - -find s_ExplicitVarSizeWithMarkerR2_Marker: int(0..8) -find s_ExplicitVarSizeWithMarkerR2_Values_Occurrence: matrix indexed by [int(1..8), int(1..3)] of bool -branching on [s_ExplicitVarSizeWithMarkerR2_Marker, s_ExplicitVarSizeWithMarkerR2_Values_Occurrence] -such that - flatten([[toInt(q8 <= s_ExplicitVarSizeWithMarkerR2_Marker) * - catchUndef(-toInt(s_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q8, q10]), 0) - | q10 : int(1..3)] - | q8 : int(1..8)]) - <=lex - flatten([[toInt(q9 <= s_ExplicitVarSizeWithMarkerR2_Marker) * - catchUndef(-toInt(s_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q9, q11]), 0) - | q11 : int(1..3)] - | q9 : int(1..8)]), - and([q1 + 1 <= s_ExplicitVarSizeWithMarkerR2_Marker -> - [-toInt(s_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q1, q5]) | q5 : int(1..3)] s_ExplicitVarSizeWithMarkerR2_Marker -> - and([s_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q2, q7] = false | q7 : int(1..3)]) - | q2 : int(1..8)]), - 2 <= s_ExplicitVarSizeWithMarkerR2_Marker, - and([q3 <= s_ExplicitVarSizeWithMarkerR2_Marker -> - 2 <= sum([toInt(s_ExplicitVarSizeWithMarkerR2_Values_Occurrence[q3, q4]) | q4 : int(1..3)]) - | q3 : int(1..8)]) - -language Essence 1.3 - -letting s be {{1, 3}, {2, 3}} -$ Visualisation for s -$ 1 3 -$ 2 3 - diff --git a/tests/custom/permutations/22_tagged_ints/int/0001_permute_untagged/stdout.expected b/tests/custom/permutations/22_tagged_ints/int/0001_permute_untagged/stdout.expected deleted file mode 100644 index c40fe7c84e..0000000000 --- a/tests/custom/permutations/22_tagged_ints/int/0001_permute_untagged/stdout.expected +++ /dev/null @@ -1,11 +0,0 @@ -Generating models for permutation.essence -Generated models: model000001.eprime -Saved under: conjure-output -Savile Row: model000001.eprime -Running minion for domain filtering. -Running solver: minion -Copying solution to: permutation.solution -language Essence 1.3 - -letting t be (1, 1) -letting x be (1, 2) diff --git a/tests/custom/permutations/22_tagged_ints/int/0002_permute_tagged/stdout.expected b/tests/custom/permutations/22_tagged_ints/int/0002_permute_tagged/stdout.expected deleted file mode 100644 index 2073bb1d22..0000000000 --- a/tests/custom/permutations/22_tagged_ints/int/0002_permute_tagged/stdout.expected +++ /dev/null @@ -1,11 +0,0 @@ -Generating models for permutation.essence -Generated models: model000001.eprime -Saved under: conjure-output -Savile Row: model000001.eprime -Running minion for domain filtering. -Running solver: minion -Copying solution to: permutation.solution -language Essence 1.3 - -letting t be (1, 1) -letting x be (2, 1) diff --git a/tests/custom/permutations/22_tagged_ints/int/0003_tagged_lits_in_param/stdout.expected b/tests/custom/permutations/22_tagged_ints/int/0003_tagged_lits_in_param/stdout.expected deleted file mode 100644 index b40e0f6a2a..0000000000 --- a/tests/custom/permutations/22_tagged_ints/int/0003_tagged_lits_in_param/stdout.expected +++ /dev/null @@ -1,11 +0,0 @@ -Generating models for permutation.essence -Generated models: model000001.eprime -Saved under: conjure-output -Savile Row: model000001.eprime permutation.param -Running minion for domain filtering. -Running solver: minion -Copying solution to: permutation-permutation.solution -language Essence 1.3 - -letting t be (1, 1) -letting x be (2, 1) diff --git a/tests/custom/permutations/22_tagged_ints/int/div/0001_same_tags_works/stdout.expected b/tests/custom/permutations/22_tagged_ints/int/div/0001_same_tags_works/stdout.expected deleted file mode 100644 index 3699f5924f..0000000000 --- a/tests/custom/permutations/22_tagged_ints/int/div/0001_same_tags_works/stdout.expected +++ /dev/null @@ -1,11 +0,0 @@ -Generating models for permutation.essence -Generated models: model000001.eprime -Saved under: conjure-output -Savile Row: model000001.eprime -Running minion for domain filtering. -Running solver: minion -Copying solution to: permutation.solution -language Essence 1.3 - -letting t be 3 -letting x be 1 diff --git a/tests/custom/permutations/22_tagged_ints/int/div/0002_diff_tags_prohibited/stdout.expected b/tests/custom/permutations/22_tagged_ints/int/div/0002_diff_tags_prohibited/stdout.expected deleted file mode 100644 index d10ebe7b59..0000000000 --- a/tests/custom/permutations/22_tagged_ints/int/div/0002_diff_tags_prohibited/stdout.expected +++ /dev/null @@ -1 +0,0 @@ -Generating models for permutation.essence diff --git a/tests/custom/permutations/22_tagged_ints/int/div/0003_const_tagged_works/stdout.expected b/tests/custom/permutations/22_tagged_ints/int/div/0003_const_tagged_works/stdout.expected deleted file mode 100644 index efeeb71a08..0000000000 --- a/tests/custom/permutations/22_tagged_ints/int/div/0003_const_tagged_works/stdout.expected +++ /dev/null @@ -1,10 +0,0 @@ -Generating models for permutation.essence -Generated models: model000001.eprime -Saved under: conjure-output -Savile Row: model000001.eprime -Running minion for domain filtering. -Running solver: minion -Copying solution to: permutation.solution -language Essence 1.3 - -letting x be 2 diff --git a/tests/custom/permutations/22_tagged_ints/int/div/0004_enum_doesnt_work/stdout.expected b/tests/custom/permutations/22_tagged_ints/int/div/0004_enum_doesnt_work/stdout.expected deleted file mode 100644 index d10ebe7b59..0000000000 --- a/tests/custom/permutations/22_tagged_ints/int/div/0004_enum_doesnt_work/stdout.expected +++ /dev/null @@ -1 +0,0 @@ -Generating models for permutation.essence diff --git a/tests/custom/permutations/22_tagged_ints/int/factorial/0002_diff_tags_prohibited/stdout.expected b/tests/custom/permutations/22_tagged_ints/int/factorial/0002_diff_tags_prohibited/stdout.expected deleted file mode 100644 index d10ebe7b59..0000000000 --- a/tests/custom/permutations/22_tagged_ints/int/factorial/0002_diff_tags_prohibited/stdout.expected +++ /dev/null @@ -1 +0,0 @@ -Generating models for permutation.essence diff --git a/tests/custom/permutations/22_tagged_ints/int/factorial/0003_const_tagged_works/stdout.expected b/tests/custom/permutations/22_tagged_ints/int/factorial/0003_const_tagged_works/stdout.expected deleted file mode 100644 index 53d1ddf9b0..0000000000 --- a/tests/custom/permutations/22_tagged_ints/int/factorial/0003_const_tagged_works/stdout.expected +++ /dev/null @@ -1,10 +0,0 @@ -Generating models for permutation.essence -Generated models: model000001.eprime -Saved under: conjure-output -Savile Row: model000001.eprime -Running minion for domain filtering. -Running solver: minion -Copying solution to: permutation.solution -language Essence 1.3 - -letting x be 6 diff --git a/tests/custom/permutations/22_tagged_ints/int/geq/0002_diff_tags_prohibited/stdout.expected b/tests/custom/permutations/22_tagged_ints/int/geq/0002_diff_tags_prohibited/stdout.expected deleted file mode 100644 index d10ebe7b59..0000000000 --- a/tests/custom/permutations/22_tagged_ints/int/geq/0002_diff_tags_prohibited/stdout.expected +++ /dev/null @@ -1 +0,0 @@ -Generating models for permutation.essence diff --git a/tests/custom/permutations/22_tagged_ints/int/geq/0003_const_tagged_works/stdout.expected b/tests/custom/permutations/22_tagged_ints/int/geq/0003_const_tagged_works/stdout.expected deleted file mode 100644 index 72487280db..0000000000 --- a/tests/custom/permutations/22_tagged_ints/int/geq/0003_const_tagged_works/stdout.expected +++ /dev/null @@ -1,11 +0,0 @@ -Generating models for permutation.essence -Generated models: model000001.eprime -Saved under: conjure-output -Savile Row: model000001.eprime -Running minion for domain filtering. -Running solver: minion -Copying solution to: permutation.solution -language Essence 1.3 - -letting x be 1 -letting y be 1 diff --git a/tests/custom/permutations/22_tagged_ints/int/leq/0002_diff_tags_prohibited/stdout.expected b/tests/custom/permutations/22_tagged_ints/int/leq/0002_diff_tags_prohibited/stdout.expected deleted file mode 100644 index d10ebe7b59..0000000000 --- a/tests/custom/permutations/22_tagged_ints/int/leq/0002_diff_tags_prohibited/stdout.expected +++ /dev/null @@ -1 +0,0 @@ -Generating models for permutation.essence diff --git a/tests/custom/permutations/22_tagged_ints/int/leq/0003_const_tagged_works/stdout.expected b/tests/custom/permutations/22_tagged_ints/int/leq/0003_const_tagged_works/stdout.expected deleted file mode 100644 index 72487280db..0000000000 --- a/tests/custom/permutations/22_tagged_ints/int/leq/0003_const_tagged_works/stdout.expected +++ /dev/null @@ -1,11 +0,0 @@ -Generating models for permutation.essence -Generated models: model000001.eprime -Saved under: conjure-output -Savile Row: model000001.eprime -Running minion for domain filtering. -Running solver: minion -Copying solution to: permutation.solution -language Essence 1.3 - -letting x be 1 -letting y be 1 diff --git a/tests/custom/permutations/22_tagged_ints/int/lt/0002_diff_tags_prohibited/stdout.expected b/tests/custom/permutations/22_tagged_ints/int/lt/0002_diff_tags_prohibited/stdout.expected deleted file mode 100644 index d10ebe7b59..0000000000 --- a/tests/custom/permutations/22_tagged_ints/int/lt/0002_diff_tags_prohibited/stdout.expected +++ /dev/null @@ -1 +0,0 @@ -Generating models for permutation.essence diff --git a/tests/custom/permutations/22_tagged_ints/int/lt/0003_const_tagged_works/stdout.expected b/tests/custom/permutations/22_tagged_ints/int/lt/0003_const_tagged_works/stdout.expected deleted file mode 100644 index b6829caf1f..0000000000 --- a/tests/custom/permutations/22_tagged_ints/int/lt/0003_const_tagged_works/stdout.expected +++ /dev/null @@ -1,11 +0,0 @@ -Generating models for permutation.essence -Generated models: model000001.eprime -Saved under: conjure-output -Savile Row: model000001.eprime -Running minion for domain filtering. -Running solver: minion -Copying solution to: permutation.solution -language Essence 1.3 - -letting x be 1 -letting y be 2 diff --git a/tests/custom/permutations/22_tagged_ints/int/max/0001_same_tags_work/stdout.expected b/tests/custom/permutations/22_tagged_ints/int/max/0001_same_tags_work/stdout.expected deleted file mode 100644 index 52afb68fe6..0000000000 --- a/tests/custom/permutations/22_tagged_ints/int/max/0001_same_tags_work/stdout.expected +++ /dev/null @@ -1,11 +0,0 @@ -Generating models for permutation.essence -Generated models: model000001.eprime -Saved under: conjure-output -Savile Row: model000001.eprime -Running minion for domain filtering. -Running solver: minion -Copying solution to: permutation.solution -language Essence 1.3 - -letting t be {4} -letting x be 4 diff --git a/tests/custom/permutations/22_tagged_ints/int/max/0002_diff_tags_prohibited/stdout.expected b/tests/custom/permutations/22_tagged_ints/int/max/0002_diff_tags_prohibited/stdout.expected deleted file mode 100644 index d10ebe7b59..0000000000 --- a/tests/custom/permutations/22_tagged_ints/int/max/0002_diff_tags_prohibited/stdout.expected +++ /dev/null @@ -1 +0,0 @@ -Generating models for permutation.essence diff --git a/tests/custom/permutations/22_tagged_ints/int/max/0003_const_tagged_works/stdout.expected b/tests/custom/permutations/22_tagged_ints/int/max/0003_const_tagged_works/stdout.expected deleted file mode 100644 index a3c1446354..0000000000 --- a/tests/custom/permutations/22_tagged_ints/int/max/0003_const_tagged_works/stdout.expected +++ /dev/null @@ -1,10 +0,0 @@ -Generating models for permutation.essence -Generated models: model000001.eprime -Saved under: conjure-output -Savile Row: model000001.eprime -Running minion for domain filtering. -Running solver: minion -Copying solution to: permutation.solution -language Essence 1.3 - -letting t be {3} diff --git a/tests/custom/permutations/22_tagged_ints/int/min/0001_same_tags_work/stdout.expected b/tests/custom/permutations/22_tagged_ints/int/min/0001_same_tags_work/stdout.expected deleted file mode 100644 index 52afb68fe6..0000000000 --- a/tests/custom/permutations/22_tagged_ints/int/min/0001_same_tags_work/stdout.expected +++ /dev/null @@ -1,11 +0,0 @@ -Generating models for permutation.essence -Generated models: model000001.eprime -Saved under: conjure-output -Savile Row: model000001.eprime -Running minion for domain filtering. -Running solver: minion -Copying solution to: permutation.solution -language Essence 1.3 - -letting t be {4} -letting x be 4 diff --git a/tests/custom/permutations/22_tagged_ints/int/min/0002_diff_tags_prohibited/stdout.expected b/tests/custom/permutations/22_tagged_ints/int/min/0002_diff_tags_prohibited/stdout.expected deleted file mode 100644 index d10ebe7b59..0000000000 --- a/tests/custom/permutations/22_tagged_ints/int/min/0002_diff_tags_prohibited/stdout.expected +++ /dev/null @@ -1 +0,0 @@ -Generating models for permutation.essence diff --git a/tests/custom/permutations/22_tagged_ints/int/min/0003_const_tagged_works/stdout.expected b/tests/custom/permutations/22_tagged_ints/int/min/0003_const_tagged_works/stdout.expected deleted file mode 100644 index a3c1446354..0000000000 --- a/tests/custom/permutations/22_tagged_ints/int/min/0003_const_tagged_works/stdout.expected +++ /dev/null @@ -1,10 +0,0 @@ -Generating models for permutation.essence -Generated models: model000001.eprime -Saved under: conjure-output -Savile Row: model000001.eprime -Running minion for domain filtering. -Running solver: minion -Copying solution to: permutation.solution -language Essence 1.3 - -letting t be {3} diff --git a/tests/custom/permutations/22_tagged_ints/int/minus/0001_same_tags_works/stdout.expected b/tests/custom/permutations/22_tagged_ints/int/minus/0001_same_tags_works/stdout.expected deleted file mode 100644 index da8f18aa8e..0000000000 --- a/tests/custom/permutations/22_tagged_ints/int/minus/0001_same_tags_works/stdout.expected +++ /dev/null @@ -1,11 +0,0 @@ -Generating models for permutation.essence -Generated models: model000001.eprime -Saved under: conjure-output -Savile Row: model000001.eprime -Running minion for domain filtering. -Running solver: minion -Copying solution to: permutation.solution -language Essence 1.3 - -letting t be 5 -letting x be 1 diff --git a/tests/custom/permutations/22_tagged_ints/int/minus/0002_diff_tags_prohibited/stdout.expected b/tests/custom/permutations/22_tagged_ints/int/minus/0002_diff_tags_prohibited/stdout.expected deleted file mode 100644 index d10ebe7b59..0000000000 --- a/tests/custom/permutations/22_tagged_ints/int/minus/0002_diff_tags_prohibited/stdout.expected +++ /dev/null @@ -1 +0,0 @@ -Generating models for permutation.essence diff --git a/tests/custom/permutations/22_tagged_ints/int/minus/0003_const_tagged_works/stdout.expected b/tests/custom/permutations/22_tagged_ints/int/minus/0003_const_tagged_works/stdout.expected deleted file mode 100644 index efeeb71a08..0000000000 --- a/tests/custom/permutations/22_tagged_ints/int/minus/0003_const_tagged_works/stdout.expected +++ /dev/null @@ -1,10 +0,0 @@ -Generating models for permutation.essence -Generated models: model000001.eprime -Saved under: conjure-output -Savile Row: model000001.eprime -Running minion for domain filtering. -Running solver: minion -Copying solution to: permutation.solution -language Essence 1.3 - -letting x be 2 diff --git a/tests/custom/permutations/22_tagged_ints/int/mod/0001_same_tags_works/stdout.expected b/tests/custom/permutations/22_tagged_ints/int/mod/0001_same_tags_works/stdout.expected deleted file mode 100644 index 6f7ccdf470..0000000000 --- a/tests/custom/permutations/22_tagged_ints/int/mod/0001_same_tags_works/stdout.expected +++ /dev/null @@ -1,11 +0,0 @@ -Generating models for permutation.essence -Generated models: model000001.eprime -Saved under: conjure-output -Savile Row: model000001.eprime -Running minion for domain filtering. -Running solver: minion -Copying solution to: permutation.solution -language Essence 1.3 - -letting t be 1 -letting x be 1 diff --git a/tests/custom/permutations/22_tagged_ints/int/mod/0002_diff_tags_prohibited/stdout.expected b/tests/custom/permutations/22_tagged_ints/int/mod/0002_diff_tags_prohibited/stdout.expected deleted file mode 100644 index d10ebe7b59..0000000000 --- a/tests/custom/permutations/22_tagged_ints/int/mod/0002_diff_tags_prohibited/stdout.expected +++ /dev/null @@ -1 +0,0 @@ -Generating models for permutation.essence diff --git a/tests/custom/permutations/22_tagged_ints/int/mod/0003_const_tagged_works/stdout.expected b/tests/custom/permutations/22_tagged_ints/int/mod/0003_const_tagged_works/stdout.expected deleted file mode 100644 index efeeb71a08..0000000000 --- a/tests/custom/permutations/22_tagged_ints/int/mod/0003_const_tagged_works/stdout.expected +++ /dev/null @@ -1,10 +0,0 @@ -Generating models for permutation.essence -Generated models: model000001.eprime -Saved under: conjure-output -Savile Row: model000001.eprime -Running minion for domain filtering. -Running solver: minion -Copying solution to: permutation.solution -language Essence 1.3 - -letting x be 2 diff --git a/tests/custom/permutations/22_tagged_ints/int/neg/0001_same_tags_works/stdout.expected b/tests/custom/permutations/22_tagged_ints/int/neg/0001_same_tags_works/stdout.expected deleted file mode 100644 index 97a4627bd0..0000000000 --- a/tests/custom/permutations/22_tagged_ints/int/neg/0001_same_tags_works/stdout.expected +++ /dev/null @@ -1,11 +0,0 @@ -Generating models for permutation.essence -Generated models: model000001.eprime -Saved under: conjure-output -Savile Row: model000001.eprime -Running minion for domain filtering. -Running solver: minion -Copying solution to: permutation.solution -language Essence 1.3 - -letting t be -6 -letting x be 6 diff --git a/tests/custom/permutations/22_tagged_ints/int/neg/0002_diff_tags_prohibited/stdout.expected b/tests/custom/permutations/22_tagged_ints/int/neg/0002_diff_tags_prohibited/stdout.expected deleted file mode 100644 index d10ebe7b59..0000000000 --- a/tests/custom/permutations/22_tagged_ints/int/neg/0002_diff_tags_prohibited/stdout.expected +++ /dev/null @@ -1 +0,0 @@ -Generating models for permutation.essence diff --git a/tests/custom/permutations/22_tagged_ints/int/neg/0003_const_tagged_works/stdout.expected b/tests/custom/permutations/22_tagged_ints/int/neg/0003_const_tagged_works/stdout.expected deleted file mode 100644 index 20c939f655..0000000000 --- a/tests/custom/permutations/22_tagged_ints/int/neg/0003_const_tagged_works/stdout.expected +++ /dev/null @@ -1,10 +0,0 @@ -Generating models for permutation.essence -Generated models: model000001.eprime -Saved under: conjure-output -Savile Row: model000001.eprime -Running minion for domain filtering. -Running solver: minion -Copying solution to: permutation.solution -language Essence 1.3 - -letting x be -2 diff --git a/tests/custom/permutations/22_tagged_ints/int/pred/0002_diff_tags_prohibited/stdout.expected b/tests/custom/permutations/22_tagged_ints/int/pred/0002_diff_tags_prohibited/stdout.expected deleted file mode 100644 index d10ebe7b59..0000000000 --- a/tests/custom/permutations/22_tagged_ints/int/pred/0002_diff_tags_prohibited/stdout.expected +++ /dev/null @@ -1 +0,0 @@ -Generating models for permutation.essence diff --git a/tests/custom/permutations/22_tagged_ints/int/pred/0003_const_tagged_works/stdout.expected b/tests/custom/permutations/22_tagged_ints/int/pred/0003_const_tagged_works/stdout.expected deleted file mode 100644 index b6829caf1f..0000000000 --- a/tests/custom/permutations/22_tagged_ints/int/pred/0003_const_tagged_works/stdout.expected +++ /dev/null @@ -1,11 +0,0 @@ -Generating models for permutation.essence -Generated models: model000001.eprime -Saved under: conjure-output -Savile Row: model000001.eprime -Running minion for domain filtering. -Running solver: minion -Copying solution to: permutation.solution -language Essence 1.3 - -letting x be 1 -letting y be 2 diff --git a/tests/custom/permutations/22_tagged_ints/int/prod/0001_same_tags_works/stdout.expected b/tests/custom/permutations/22_tagged_ints/int/prod/0001_same_tags_works/stdout.expected deleted file mode 100644 index 9b47e4135d..0000000000 --- a/tests/custom/permutations/22_tagged_ints/int/prod/0001_same_tags_works/stdout.expected +++ /dev/null @@ -1,11 +0,0 @@ -Generating models for permutation.essence -Generated models: model000001.eprime -Saved under: conjure-output -Savile Row: model000001.eprime -Running minion for domain filtering. -Running solver: minion -Copying solution to: permutation.solution -language Essence 1.3 - -letting t be 1 -letting x be 3 diff --git a/tests/custom/permutations/22_tagged_ints/int/prod/0002_diff_tags_prohibited/stdout.expected b/tests/custom/permutations/22_tagged_ints/int/prod/0002_diff_tags_prohibited/stdout.expected deleted file mode 100644 index d10ebe7b59..0000000000 --- a/tests/custom/permutations/22_tagged_ints/int/prod/0002_diff_tags_prohibited/stdout.expected +++ /dev/null @@ -1 +0,0 @@ -Generating models for permutation.essence diff --git a/tests/custom/permutations/22_tagged_ints/int/prod/0003_const_tagged_works/stdout.expected b/tests/custom/permutations/22_tagged_ints/int/prod/0003_const_tagged_works/stdout.expected deleted file mode 100644 index 53d1ddf9b0..0000000000 --- a/tests/custom/permutations/22_tagged_ints/int/prod/0003_const_tagged_works/stdout.expected +++ /dev/null @@ -1,10 +0,0 @@ -Generating models for permutation.essence -Generated models: model000001.eprime -Saved under: conjure-output -Savile Row: model000001.eprime -Running minion for domain filtering. -Running solver: minion -Copying solution to: permutation.solution -language Essence 1.3 - -letting x be 6 diff --git a/tests/custom/permutations/22_tagged_ints/int/succ/0002_diff_tags_prohibited/stdout.expected b/tests/custom/permutations/22_tagged_ints/int/succ/0002_diff_tags_prohibited/stdout.expected deleted file mode 100644 index d10ebe7b59..0000000000 --- a/tests/custom/permutations/22_tagged_ints/int/succ/0002_diff_tags_prohibited/stdout.expected +++ /dev/null @@ -1 +0,0 @@ -Generating models for permutation.essence diff --git a/tests/custom/permutations/22_tagged_ints/int/succ/0003_const_tagged_works/stdout.expected b/tests/custom/permutations/22_tagged_ints/int/succ/0003_const_tagged_works/stdout.expected deleted file mode 100644 index 44089a9b87..0000000000 --- a/tests/custom/permutations/22_tagged_ints/int/succ/0003_const_tagged_works/stdout.expected +++ /dev/null @@ -1,11 +0,0 @@ -Generating models for permutation.essence -Generated models: model000001.eprime -Saved under: conjure-output -Savile Row: model000001.eprime -Running minion for domain filtering. -Running solver: minion -Copying solution to: permutation.solution -language Essence 1.3 - -letting x be 2 -letting y be 1 diff --git a/tests/custom/permutations/22_tagged_ints/int/sum/0001_same_tags_works/stdout.expected b/tests/custom/permutations/22_tagged_ints/int/sum/0001_same_tags_works/stdout.expected deleted file mode 100644 index f5d65a4dec..0000000000 --- a/tests/custom/permutations/22_tagged_ints/int/sum/0001_same_tags_works/stdout.expected +++ /dev/null @@ -1,11 +0,0 @@ -Generating models for permutation.essence -Generated models: model000001.eprime -Saved under: conjure-output -Savile Row: model000001.eprime -Running minion for domain filtering. -Running solver: minion -Copying solution to: permutation.solution -language Essence 1.3 - -letting t be 1 -letting x be 5 diff --git a/tests/custom/permutations/22_tagged_ints/int/sum/0002_diff_tags_prohibited/stdout.expected b/tests/custom/permutations/22_tagged_ints/int/sum/0002_diff_tags_prohibited/stdout.expected deleted file mode 100644 index d10ebe7b59..0000000000 --- a/tests/custom/permutations/22_tagged_ints/int/sum/0002_diff_tags_prohibited/stdout.expected +++ /dev/null @@ -1 +0,0 @@ -Generating models for permutation.essence diff --git a/tests/custom/permutations/22_tagged_ints/int/sum/0003_const_tagged_works/stdout.expected b/tests/custom/permutations/22_tagged_ints/int/sum/0003_const_tagged_works/stdout.expected deleted file mode 100644 index 53d1ddf9b0..0000000000 --- a/tests/custom/permutations/22_tagged_ints/int/sum/0003_const_tagged_works/stdout.expected +++ /dev/null @@ -1,10 +0,0 @@ -Generating models for permutation.essence -Generated models: model000001.eprime -Saved under: conjure-output -Savile Row: model000001.eprime -Running minion for domain filtering. -Running solver: minion -Copying solution to: permutation.solution -language Essence 1.3 - -letting x be 6 diff --git a/tests/custom/permutations/23_image_set_dotlt/int/0010_find_perm_find_set/stdout.expected b/tests/custom/permutations/23_image_set_dotlt/int/0010_find_perm_find_set/stdout.expected index abda9428df..d10ebe7b59 100644 --- a/tests/custom/permutations/23_image_set_dotlt/int/0010_find_perm_find_set/stdout.expected +++ b/tests/custom/permutations/23_image_set_dotlt/int/0010_find_perm_find_set/stdout.expected @@ -1,54 +1 @@ Generating models for permutation.essence -Generated models: model000001.eprime -Saved under: conjure-output -Savile Row: model000001.eprime -Copying solution to: permutation-000001.solution -Copying solution to: permutation-000002.solution -Copying solution to: permutation-000003.solution -Copying solution to: permutation-000004.solution -Copying solution to: permutation-000005.solution -Copying solution to: permutation-000006.solution -Copying solution to: permutation-000007.solution -Copying solution to: permutation-000008.solution -Copying solution to: permutation-000009.solution -Copying solution to: permutation-000010.solution -language Essence 1.3 - -letting p be permutation((3, 4)) -letting s be {3} -language Essence 1.3 - -letting p be permutation((3, 4)) -letting s be {2, 3} -language Essence 1.3 - -letting p be permutation((3, 4)) -letting s be {1, 3} -language Essence 1.3 - -letting p be permutation((3, 4)) -letting s be {1, 2, 3} -language Essence 1.3 - -letting p be permutation((2, 3)) -letting s be {2} -language Essence 1.3 - -letting p be permutation((2, 3)) -letting s be {2, 4} -language Essence 1.3 - -letting p be permutation((2, 3)) -letting s be {1, 2} -language Essence 1.3 - -letting p be permutation((2, 3)) -letting s be {1, 2, 4} -language Essence 1.3 - -letting p be permutation((2, 3, 4)) -letting s be {2} -language Essence 1.3 - -letting p be permutation((2, 3, 4)) -letting s be {2, 4} diff --git a/tests/custom/permutations/permInverse/01/01.essence b/tests/custom/permutations/permInverse/01/01.essence new file mode 100644 index 0000000000..9702e9df07 --- /dev/null +++ b/tests/custom/permutations/permInverse/01/01.essence @@ -0,0 +1,7 @@ + +letting p be permutation((1,2)) + +find x, y, z : int(1..3) + +such that y = image(p, x) +such that z = image(permInverse(p), x) diff --git a/tests/custom/permutations/permInverse/01/run.sh b/tests/custom/permutations/permInverse/01/run.sh new file mode 100755 index 0000000000..6c6476a122 --- /dev/null +++ b/tests/custom/permutations/permInverse/01/run.sh @@ -0,0 +1,5 @@ + +rm -rf conjure-output +conjure solve *.essence --output-format=json --solutions-in-one-file --number-of-solutions=all --line-width=50 --copy-solutions=no +cat conjure-output/model000001.solutions.json +rm -rf conjure-output diff --git a/tests/custom/permutations/permInverse/01/stdout.expected b/tests/custom/permutations/permInverse/01/stdout.expected new file mode 100644 index 0000000000..34ebdb860a --- /dev/null +++ b/tests/custom/permutations/permInverse/01/stdout.expected @@ -0,0 +1,13 @@ +Generating models for 01.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: conjure-output/model000001.eprime +Running minion for domain filtering. +Running solver: minion +[ +{"x": 1, "y": 2, "z": 2} +, +{"x": 2, "y": 1, "z": 1} +, +{"x": 3, "y": 3, "z": 3} +] diff --git a/tests/custom/permutations/permInverse/02/02.essence b/tests/custom/permutations/permInverse/02/02.essence new file mode 100644 index 0000000000..c1ce1b2506 --- /dev/null +++ b/tests/custom/permutations/permInverse/02/02.essence @@ -0,0 +1,7 @@ + +find p : permutation (maxNumMoved 2) of int(1..3) + +find x, y, z : int(1..3) + +such that y = image(p, x) +such that z = image(permInverse(p), x) diff --git a/tests/custom/permutations/permInverse/02/run.sh b/tests/custom/permutations/permInverse/02/run.sh new file mode 100755 index 0000000000..6c6476a122 --- /dev/null +++ b/tests/custom/permutations/permInverse/02/run.sh @@ -0,0 +1,5 @@ + +rm -rf conjure-output +conjure solve *.essence --output-format=json --solutions-in-one-file --number-of-solutions=all --line-width=50 --copy-solutions=no +cat conjure-output/model000001.solutions.json +rm -rf conjure-output diff --git a/tests/custom/permutations/permInverse/02/stdout.expected b/tests/custom/permutations/permInverse/02/stdout.expected new file mode 100644 index 0000000000..b26488802c --- /dev/null +++ b/tests/custom/permutations/permInverse/02/stdout.expected @@ -0,0 +1,31 @@ +Generating models for 02.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: conjure-output/model000001.eprime +Running minion for domain filtering. +Running solver: minion +[ +{"p": [], "x": 1, "y": 1, "z": 1} +, +{"p": [], "x": 2, "y": 2, "z": 2} +, +{"p": [], "x": 3, "y": 3, "z": 3} +, +{"p": [[2, 3]], "x": 1, "y": 1, "z": 1} +, +{"p": [[2, 3]], "x": 2, "y": 3, "z": 3} +, +{"p": [[2, 3]], "x": 3, "y": 2, "z": 2} +, +{"p": [[1, 2]], "x": 1, "y": 2, "z": 2} +, +{"p": [[1, 2]], "x": 2, "y": 1, "z": 1} +, +{"p": [[1, 2]], "x": 3, "y": 3, "z": 3} +, +{"p": [[1, 3]], "x": 1, "y": 3, "z": 3} +, +{"p": [[1, 3]], "x": 2, "y": 2, "z": 2} +, +{"p": [[1, 3]], "x": 3, "y": 1, "z": 1} +] diff --git a/tests/custom/permutations/permInverse/03/03.essence b/tests/custom/permutations/permInverse/03/03.essence new file mode 100644 index 0000000000..79101ebb5a --- /dev/null +++ b/tests/custom/permutations/permInverse/03/03.essence @@ -0,0 +1,7 @@ + +find p : permutation of int(1..3) + +find x, y, z : int(1..3) + +such that y = image(p, x) +such that z = image(permInverse(p), x) diff --git a/tests/custom/permutations/permInverse/03/run.sh b/tests/custom/permutations/permInverse/03/run.sh new file mode 100755 index 0000000000..6c6476a122 --- /dev/null +++ b/tests/custom/permutations/permInverse/03/run.sh @@ -0,0 +1,5 @@ + +rm -rf conjure-output +conjure solve *.essence --output-format=json --solutions-in-one-file --number-of-solutions=all --line-width=50 --copy-solutions=no +cat conjure-output/model000001.solutions.json +rm -rf conjure-output diff --git a/tests/custom/permutations/permInverse/03/stdout.expected b/tests/custom/permutations/permInverse/03/stdout.expected new file mode 100644 index 0000000000..534b4821e8 --- /dev/null +++ b/tests/custom/permutations/permInverse/03/stdout.expected @@ -0,0 +1,43 @@ +Generating models for 03.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: conjure-output/model000001.eprime +Running minion for domain filtering. +Running solver: minion +[ +{"p": [], "x": 1, "y": 1, "z": 1} +, +{"p": [], "x": 2, "y": 2, "z": 2} +, +{"p": [], "x": 3, "y": 3, "z": 3} +, +{"p": [[2, 3]], "x": 1, "y": 1, "z": 1} +, +{"p": [[2, 3]], "x": 2, "y": 3, "z": 3} +, +{"p": [[2, 3]], "x": 3, "y": 2, "z": 2} +, +{"p": [[1, 2]], "x": 1, "y": 2, "z": 2} +, +{"p": [[1, 2]], "x": 2, "y": 1, "z": 1} +, +{"p": [[1, 2]], "x": 3, "y": 3, "z": 3} +, +{"p": [[1, 2, 3]], "x": 1, "y": 2, "z": 3} +, +{"p": [[1, 2, 3]], "x": 2, "y": 3, "z": 1} +, +{"p": [[1, 2, 3]], "x": 3, "y": 1, "z": 2} +, +{"p": [[1, 3, 2]], "x": 1, "y": 3, "z": 2} +, +{"p": [[1, 3, 2]], "x": 2, "y": 1, "z": 3} +, +{"p": [[1, 3, 2]], "x": 3, "y": 2, "z": 1} +, +{"p": [[1, 3]], "x": 1, "y": 3, "z": 3} +, +{"p": [[1, 3]], "x": 2, "y": 2, "z": 2} +, +{"p": [[1, 3]], "x": 3, "y": 1, "z": 1} +] diff --git a/tests/custom/symmetry/basic/one-var/stdout.expected b/tests/custom/symmetry/basic/one-var/stdout.expected index ac93f25c7e..e797bd6d20 100644 --- a/tests/custom/symmetry/basic/one-var/stdout.expected +++ b/tests/custom/symmetry/basic/one-var/stdout.expected @@ -1,13 +1,13 @@ Quick-Consecutive-Independently Adding the following unnamed symmetry breaking constraints: such that - and([tuple (i) .<= - transform(permutation((q1, succ(q1))), tuple (i)) + and([quickPermutationOrder(tuple (i), + [permutation((q1, succ(q1))); int(1)]) | q1 : e, q1 < 4]) Generating models for model.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime +Savile Row: conjure-output/model000001.eprime Running minion for domain filtering. Running solver: minion Copying solution to: model.solutions @@ -16,13 +16,13 @@ Copying solution to: model.solutions.json Quick-Consecutive-Altogether Adding the following unnamed symmetry breaking constraints: such that - and([tuple (i) .<= - transform(permutation((q1, succ(q1))), tuple (i)) + and([quickPermutationOrder(tuple (i), + [permutation((q1, succ(q1))); int(1)]) | q1 : e, q1 < 4]) Generating models for model.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime +Savile Row: conjure-output/model000001.eprime Running minion for domain filtering. Running solver: minion Copying solution to: model.solutions @@ -31,12 +31,13 @@ Copying solution to: model.solutions.json Quick-AllPairs-Independently Adding the following unnamed symmetry breaking constraints: such that - and([tuple (i) .<= transform(permutation((q1, q2)), tuple (i)) + and([quickPermutationOrder(tuple (i), + [permutation((q1, q2)); int(1)]) | q1 : e, q2 : e, q1 < q2]) Generating models for model.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime +Savile Row: conjure-output/model000001.eprime Running minion for domain filtering. Running solver: minion Copying solution to: model.solutions @@ -45,12 +46,13 @@ Copying solution to: model.solutions.json Quick-AllPairs-Altogether Adding the following unnamed symmetry breaking constraints: such that - and([tuple (i) .<= transform(permutation((q1, q2)), tuple (i)) + and([quickPermutationOrder(tuple (i), + [permutation((q1, q2)); int(1)]) | q1 : e, q2 : e, q1 < q2]) Generating models for model.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime +Savile Row: conjure-output/model000001.eprime Running minion for domain filtering. Running solver: minion Copying solution to: model.solutions @@ -59,12 +61,12 @@ Copying solution to: model.solutions.json Quick-AllPermutations-Independently Adding the following unnamed symmetry breaking constraints: such that - and([tuple (i) .<= transform(q1, tuple (i)) + and([quickPermutationOrder(tuple (i), [q1; int(1)]) | q1 : permutation of e]) Generating models for model.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime +Savile Row: conjure-output/model000001.eprime Running minion for domain filtering. Running solver: minion Copying solution to: model.solutions @@ -73,12 +75,12 @@ Copying solution to: model.solutions.json Quick-AllPermutations-Altogether Adding the following unnamed symmetry breaking constraints: such that - and([tuple (i) .<= transform(q1, tuple (i)) + and([quickPermutationOrder(tuple (i), [q1; int(1)]) | q1 : permutation of e]) Generating models for model.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime +Savile Row: conjure-output/model000001.eprime Running minion for domain filtering. Running solver: minion Copying solution to: model.solutions @@ -87,16 +89,13 @@ Copying solution to: model.solutions.json Complete-Consecutive-Independently Adding the following unnamed symmetry breaking constraints: such that - and([{ tuple (i) .<= tuple (i_auxFor_e) - @ find i_auxFor_e: e - such that - tuple (i_auxFor_e) = - transform(permutation((q1, succ(q1))), tuple (i)) - } | q1 : e, q1 < 4]) + and([tuple (i) .<= + transform(permutation((q1, succ(q1))), tuple (i)) + | q1 : e, q1 < 4]) Generating models for model.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime +Savile Row: conjure-output/model000001.eprime Running minion for domain filtering. Running solver: minion Copying solution to: model.solutions @@ -105,16 +104,13 @@ Copying solution to: model.solutions.json Complete-Consecutive-Altogether Adding the following unnamed symmetry breaking constraints: such that - and([{ tuple (i) .<= tuple (i_auxFor_all) - @ find i_auxFor_all: e - such that - tuple (i_auxFor_all) = - transform(permutation((q1, succ(q1))), tuple (i)) - } | q1 : e, q1 < 4]) + and([tuple (i) .<= + transform(permutation((q1, succ(q1))), tuple (i)) + | q1 : e, q1 < 4]) Generating models for model.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime +Savile Row: conjure-output/model000001.eprime Running minion for domain filtering. Running solver: minion Copying solution to: model.solutions @@ -123,15 +119,12 @@ Copying solution to: model.solutions.json Complete-AllPairs-Independently Adding the following unnamed symmetry breaking constraints: such that - and([{ tuple (i) .<= tuple (i_auxFor_e) - @ find i_auxFor_e: e - such that - tuple (i_auxFor_e) = transform(permutation((q1, q2)), tuple (i)) - } | q1 : e, q2 : e, q1 < q2]) + and([tuple (i) .<= transform(permutation((q1, q2)), tuple (i)) + | q1 : e, q2 : e, q1 < q2]) Generating models for model.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime +Savile Row: conjure-output/model000001.eprime Running minion for domain filtering. Running solver: minion Copying solution to: model.solutions @@ -140,15 +133,12 @@ Copying solution to: model.solutions.json Complete-AllPairs-Altogether Adding the following unnamed symmetry breaking constraints: such that - and([{ tuple (i) .<= tuple (i_auxFor_all) - @ find i_auxFor_all: e - such that - tuple (i_auxFor_all) = transform(permutation((q1, q2)), tuple (i)) - } | q1 : e, q2 : e, q1 < q2]) + and([tuple (i) .<= transform(permutation((q1, q2)), tuple (i)) + | q1 : e, q2 : e, q1 < q2]) Generating models for model.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime +Savile Row: conjure-output/model000001.eprime Running minion for domain filtering. Running solver: minion Copying solution to: model.solutions @@ -157,14 +147,12 @@ Copying solution to: model.solutions.json Complete-AllPermutations-Independently Adding the following unnamed symmetry breaking constraints: such that - and([{ tuple (i) .<= tuple (i_auxFor_e) - @ find i_auxFor_e: e - such that tuple (i_auxFor_e) = transform(q1, tuple (i)) - } | q1 : permutation of e]) + and([tuple (i) .<= transform(q1, tuple (i)) + | q1 : permutation of e]) Generating models for model.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime +Savile Row: conjure-output/model000001.eprime Running minion for domain filtering. Running solver: minion Copying solution to: model.solutions @@ -173,14 +161,12 @@ Copying solution to: model.solutions.json Complete-AllPermutations-Altogether Adding the following unnamed symmetry breaking constraints: such that - and([{ tuple (i) .<= tuple (i_auxFor_all) - @ find i_auxFor_all: e - such that tuple (i_auxFor_all) = transform(q1, tuple (i)) - } | q1 : permutation of e]) + and([tuple (i) .<= transform(q1, tuple (i)) + | q1 : permutation of e]) Generating models for model.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime +Savile Row: conjure-output/model000001.eprime Running minion for domain filtering. Running solver: minion Copying solution to: model.solutions diff --git a/tests/custom/symmetry/basic/two-type/stdout.expected b/tests/custom/symmetry/basic/two-type/stdout.expected index b63bbd272b..662e9cd1f4 100644 --- a/tests/custom/symmetry/basic/two-type/stdout.expected +++ b/tests/custom/symmetry/basic/two-type/stdout.expected @@ -1,14 +1,16 @@ Quick-Consecutive-Independently Adding the following unnamed symmetry breaking constraints: such that - and([(i, j) .<= transform(permutation((q1, succ(q1))), (i, j)) + and([quickPermutationOrder((i, j), + [permutation((q1, succ(q1))); int(1)]) | q1 : e, q1 < 4]), - and([(i, j) .<= transform(permutation((q2, succ(q2))), (i, j)) + and([quickPermutationOrder((i, j), + [permutation((q2, succ(q2))); int(1)]) | q2 : f, q2 < 4]) Generating models for model.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime +Savile Row: conjure-output/model000001.eprime Running minion for domain filtering. Running solver: minion Copying solution to: model.solutions @@ -17,224 +19,61 @@ Copying solution to: model.solutions.json Quick-Consecutive-Altogether Adding the following unnamed symmetry breaking constraints: such that - and([and([(i, j) .<= - transform(permutation((q2, succ(q2))), - transform(permutation((q1, succ(q1))), (i, j))) + and([and([quickPermutationOrder((i, j), + [permutation((q2, succ(q2))), permutation((q1, succ(q1))); + int(1..2)]) | q2 : f, q2 < 4]) | q1 : e, q1 < 4]) Generating models for model.essence -Generated models: model000001.eprime -Saved under: conjure-output -Savile Row: model000001.eprime -Running minion for domain filtering. -Running solver: minion -Copying solution to: model.solutions -Copying solution to: model.solutions.json -{"e": ["e_1", "e_2", "e_3", "e_4"], "f": ["f_1", "f_2", "f_3", "f_4"], "i": "e_1", "j": "f_1"} -Quick-AllPairs-Independently -Adding the following unnamed symmetry breaking constraints: - such that - and([(i, j) .<= transform(permutation((q1, q2)), (i, j)) - | q1 : e, q2 : e, q1 < q2]), - and([(i, j) .<= transform(permutation((q3, q4)), (i, j)) - | q3 : f, q4 : f, q3 < q4]) -Generating models for model.essence -Generated models: model000001.eprime -Saved under: conjure-output -Savile Row: model000001.eprime -Running minion for domain filtering. -Running solver: minion -Copying solution to: model.solutions -Copying solution to: model.solutions.json -{"e": ["e_1", "e_2", "e_3", "e_4"], "f": ["f_1", "f_2", "f_3", "f_4"], "i": "e_1", "j": "f_1"} -Quick-AllPairs-Altogether -Adding the following unnamed symmetry breaking constraints: - such that - and([and([(i, j) .<= - transform(permutation((q3, q4)), - transform(permutation((q1, q2)), (i, j))) - | q3 : f, q4 : f, q3 < q4]) - | q1 : e, q2 : e, q1 < q2]) -Generating models for model.essence -Generated models: model000001.eprime -Saved under: conjure-output -Savile Row: model000001.eprime -Running minion for domain filtering. -Running solver: minion -Copying solution to: model.solutions -Copying solution to: model.solutions.json -{"e": ["e_1", "e_2", "e_3", "e_4"], "f": ["f_1", "f_2", "f_3", "f_4"], "i": "e_1", "j": "f_1"} -Quick-AllPermutations-Independently -Adding the following unnamed symmetry breaking constraints: - such that - and([(i, j) .<= transform(q1, (i, j)) | q1 : permutation of e]), - and([(i, j) .<= transform(q2, (i, j)) | q2 : permutation of f]) -Generating models for model.essence -Generated models: model000001.eprime -Saved under: conjure-output -Savile Row: model000001.eprime -Running minion for domain filtering. -Running solver: minion -Copying solution to: model.solutions -Copying solution to: model.solutions.json -{"e": ["e_1", "e_2", "e_3", "e_4"], "f": ["f_1", "f_2", "f_3", "f_4"], "i": "e_1", "j": "f_1"} -Quick-AllPermutations-Altogether -Adding the following unnamed symmetry breaking constraints: - such that - and([and([(i, j) .<= transform(q2, transform(q1, (i, j))) - | q2 : permutation of f]) - | q1 : permutation of e]) -Generating models for model.essence -Generated models: model000001.eprime -Saved under: conjure-output -Savile Row: model000001.eprime -Running minion for domain filtering. -Running solver: minion -Copying solution to: model.solutions -Copying solution to: model.solutions.json -{"e": ["e_1", "e_2", "e_3", "e_4"], "f": ["f_1", "f_2", "f_3", "f_4"], "i": "e_1", "j": "f_1"} -Complete-Consecutive-Independently -Adding the following unnamed symmetry breaking constraints: - such that - and([{ (i, j) .<= (i_auxFor_e, j_auxFor_e) - @ find i_auxFor_e: e - find i_auxFor_f: e - find j_auxFor_e: f - find j_auxFor_f: f - such that - (i_auxFor_e, j_auxFor_e) = - transform(permutation((q1, succ(q1))), (i, j)) - } | q1 : e, q1 < 4]), - and([{ (i, j) .<= (i_auxFor_f, j_auxFor_f) - @ find i_auxFor_e: e - find i_auxFor_f: e - find j_auxFor_e: f - find j_auxFor_f: f - such that - (i_auxFor_f, j_auxFor_f) = - transform(permutation((q2, succ(q2))), (i, j)) - } | q2 : f, q2 < 4]) -Generating models for model.essence -Generated models: model000001.eprime -Saved under: conjure-output -Savile Row: model000001.eprime -Running minion for domain filtering. -Running solver: minion -Copying solution to: model.solutions -Copying solution to: model.solutions.json -{"e": ["e_1", "e_2", "e_3", "e_4"], "f": ["f_1", "f_2", "f_3", "f_4"], "i": "e_1", "j": "f_1"} -Complete-Consecutive-Altogether -Adding the following unnamed symmetry breaking constraints: - such that - and([and([{ (i, j) .<= (i_auxFor_all, j_auxFor_all) - @ find i_auxFor_all: e - find j_auxFor_all: f - such that - (i_auxFor_all, j_auxFor_all) = - transform(permutation((q2, succ(q2))), - transform(permutation((q1, succ(q1))), (i, j))) - } | q2 : f, q2 < 4]) - | q1 : e, q1 < 4]) -Generating models for model.essence -Generated models: model000001.eprime -Saved under: conjure-output -Savile Row: model000001.eprime -Running minion for domain filtering. -Running solver: minion -Copying solution to: model.solutions -Copying solution to: model.solutions.json -{"e": ["e_1", "e_2", "e_3", "e_4"], "f": ["f_1", "f_2", "f_3", "f_4"], "i": "e_1", "j": "f_1"} -Complete-AllPairs-Independently -Adding the following unnamed symmetry breaking constraints: - such that - and([{ (i, j) .<= (i_auxFor_e, j_auxFor_e) - @ find i_auxFor_e: e - find i_auxFor_f: e - find j_auxFor_e: f - find j_auxFor_f: f - such that - (i_auxFor_e, j_auxFor_e) = transform(permutation((q1, q2)), (i, j)) - } | q1 : e, q2 : e, q1 < q2]), - and([{ (i, j) .<= (i_auxFor_f, j_auxFor_f) - @ find i_auxFor_e: e - find i_auxFor_f: e - find j_auxFor_e: f - find j_auxFor_f: f - such that - (i_auxFor_f, j_auxFor_f) = transform(permutation((q3, q4)), (i, j)) - } | q3 : f, q4 : f, q3 < q4]) -Generating models for model.essence -Generated models: model000001.eprime -Saved under: conjure-output -Savile Row: model000001.eprime -Running minion for domain filtering. -Running solver: minion -Copying solution to: model.solutions -Copying solution to: model.solutions.json -{"e": ["e_1", "e_2", "e_3", "e_4"], "f": ["f_1", "f_2", "f_3", "f_4"], "i": "e_1", "j": "f_1"} -Complete-AllPairs-Altogether -Adding the following unnamed symmetry breaking constraints: - such that - and([and([{ (i, j) .<= (i_auxFor_all, j_auxFor_all) - @ find i_auxFor_all: e - find j_auxFor_all: f - such that - (i_auxFor_all, j_auxFor_all) = - transform(permutation((q3, q4)), - transform(permutation((q1, q2)), (i, j))) - } | q3 : f, q4 : f, q3 < q4]) - | q1 : e, q2 : e, q1 < q2]) -Generating models for model.essence -Generated models: model000001.eprime -Saved under: conjure-output -Savile Row: model000001.eprime -Running minion for domain filtering. -Running solver: minion -Copying solution to: model.solutions -Copying solution to: model.solutions.json -{"e": ["e_1", "e_2", "e_3", "e_4"], "f": ["f_1", "f_2", "f_3", "f_4"], "i": "e_1", "j": "f_1"} -Complete-AllPermutations-Independently -Adding the following unnamed symmetry breaking constraints: - such that - and([{ (i, j) .<= (i_auxFor_e, j_auxFor_e) - @ find i_auxFor_e: e - find i_auxFor_f: e - find j_auxFor_e: f - find j_auxFor_f: f - such that (i_auxFor_e, j_auxFor_e) = transform(q1, (i, j)) - } | q1 : permutation of e]), - and([{ (i, j) .<= (i_auxFor_f, j_auxFor_f) - @ find i_auxFor_e: e - find i_auxFor_f: e - find j_auxFor_e: f - find j_auxFor_f: f - such that (i_auxFor_f, j_auxFor_f) = transform(q2, (i, j)) - } | q2 : permutation of f]) -Generating models for model.essence -Generated models: model000001.eprime -Saved under: conjure-output -Savile Row: model000001.eprime -Running minion for domain filtering. -Running solver: minion -Copying solution to: model.solutions -Copying solution to: model.solutions.json -{"e": ["e_1", "e_2", "e_3", "e_4"], "f": ["f_1", "f_2", "f_3", "f_4"], "i": "e_1", "j": "f_1"} -Complete-AllPermutations-Altogether -Adding the following unnamed symmetry breaking constraints: - such that - and([and([{ (i, j) .<= (i_auxFor_all, j_auxFor_all) - @ find i_auxFor_all: e - find j_auxFor_all: f - such that - (i_auxFor_all, j_auxFor_all) = transform(q2, transform(q1, (i, j))) - } | q2 : permutation of f]) - | q1 : permutation of e]) -Generating models for model.essence -Generated models: model000001.eprime -Saved under: conjure-output -Savile Row: model000001.eprime -Running minion for domain filtering. -Running solver: minion -Copying solution to: model.solutions -Copying solution to: model.solutions.json -{"e": ["e_1", "e_2", "e_3", "e_4"], "f": ["f_1", "f_2", "f_3", "f_4"], "i": "e_1", "j": "f_1"} +conjure: This should never happen, sorry! + +However, it did happen, so it must be a bug. Please report it to us! + +Conjure is actively maintained, we will get back to you as soon as possible. +You can help us by providing a minimal failing example. + +Also include the repository version for this build: d4f80ef16 (2024-10-24 10:19:25 +0100) + +Issue tracker: http://github.com/conjure-cp/conjure/issues + + + +Not refined: (i, + j) AbstractLiteral (AbsLitTuple [Reference (Name "i") (Just (DeclHasRepr Find (Name "i") (DomainInt (TagUnnamed "e") [RangeBounded (Constant (ConstantInt (TagUnnamed "e") 1)) (Constant (ConstantInt (TagUnnamed "e") 4))]))),Reference (Name "j") (Just (DeclHasRepr Find (Name "j") (DomainInt (TagUnnamed "f") [RangeBounded (Constant (ConstantInt (TagUnnamed "f") 1)) (Constant (ConstantInt (TagUnnamed "f") 4))])))]) + Context #1: quickPermutationOrder((i, j), [permutation((q2, succ(q2))), permutation((q1, succ(q1))); int(1..2)]) + Context #2: [quickPermutationOrder((i, j), [permutation((q2, succ(q2))), permutation((q1, succ(q1))); int(1..2)]) + | q2 : int(1..4), q2 < 4] + Context #3: and([quickPermutationOrder((i, j), + [permutation((q2, succ(q2))), permutation((q1, succ(q1))); int(1..2)]) + | q2 : int(1..4), q2 < 4]) + Context #4: [and([quickPermutationOrder((i, j), + [permutation((q2, succ(q2))), permutation((q1, succ(q1))); int(1..2)]) + | q2 : int(1..4), q2 < 4]) + | q1 : int(1..4), q1 < 4] + Context #5: and([and([quickPermutationOrder((i, j), + [permutation((q2, succ(q2))), permutation((q1, succ(q1))); int(1..2)]) + | q2 : int(1..4), q2 < 4]) + | q1 : int(1..4), q1 < 4]) +Not refined: permutation((q2, + succ(q2))) AbstractLiteral (AbsLitPermutation [[Reference (MachineName "q" 2 []) (Just (DeclHasRepr Quantified (MachineName "q" 2 []) (DomainInt (TagUnnamed "f") [RangeBounded (Constant (ConstantInt (TagUnnamed "f") 1)) (Constant (ConstantInt (TagUnnamed "f") 4))]))),Op (MkOpSucc (OpSucc (Reference (MachineName "q" 2 []) (Just (DeclHasRepr Quantified (MachineName "q" 2 []) (DomainInt (TagUnnamed "f") [RangeBounded (Constant (ConstantInt (TagUnnamed "f") 1)) (Constant (ConstantInt (TagUnnamed "f") 4))]))))))]]) + Context #1: [permutation((q2, succ(q2))), permutation((q1, succ(q1))); int(1..2)] + Context #2: quickPermutationOrder((i, j), [permutation((q2, succ(q2))), permutation((q1, succ(q1))); int(1..2)]) + Context #3: [quickPermutationOrder((i, j), [permutation((q2, succ(q2))), permutation((q1, succ(q1))); int(1..2)]) + | q2 : int(1..4), q2 < 4] + Context #4: and([quickPermutationOrder((i, j), + [permutation((q2, succ(q2))), permutation((q1, succ(q1))); int(1..2)]) + | q2 : int(1..4), q2 < 4]) + Context #5: [and([quickPermutationOrder((i, j), + [permutation((q2, succ(q2))), permutation((q1, succ(q1))); int(1..2)]) + | q2 : int(1..4), q2 < 4]) + | q1 : int(1..4), q1 < 4] + Context #6: and([and([quickPermutationOrder((i, j), + [permutation((q2, succ(q2))), permutation((q1, succ(q1))); int(1..2)]) + | q2 : int(1..4), q2 < 4]) + | q1 : int(1..4), q1 < 4]) +Not refined: permutation((q1, + succ(q1))) AbstractLiteral (AbsLitPermutation [[Reference (MachineName "q" 1 []) (Just (DeclHasRepr Quantified (MachineName "q" 1 []) (DomainInt (TagUnnamed "e") [RangeBounded (Constant (ConstantInt (TagUnnamed "e") 1)) (Constant (ConstantInt (TagUnnamed "e") 4))]))),Op (MkOpSucc (OpSucc (Reference (MachineName "q" 1 []) (Just (DeclHasRepr Quantified (MachineName "q" 1 []) (DomainInt (TagUnnamed "e") [RangeBounded (Constant (ConstantInt (TagUnnamed "e") 1)) (Constant (ConstantInt (TagUnnamed "e") 4))]))))))]]) + +CallStack (from HasCallStack): + error, called at src/Conjure/Bug.hs:17:15 in conjure-cp-2.5.1-IwIj6VKKx9G42E8IkwFva2:Conjure.Bug + bug, called at src/Conjure/UI/Model.hs:1041:26 in conjure-cp-2.5.1-IwIj6VKKx9G42E8IkwFva2:Conjure.UI.Model diff --git a/tests/custom/symmetry/basic/two-var/stdout.expected b/tests/custom/symmetry/basic/two-var/stdout.expected index 5c05e77f4b..8a383a9f05 100644 --- a/tests/custom/symmetry/basic/two-var/stdout.expected +++ b/tests/custom/symmetry/basic/two-var/stdout.expected @@ -1,12 +1,13 @@ Quick-Consecutive-Independently Adding the following unnamed symmetry breaking constraints: such that - and([(i, j) .<= transform(permutation((q1, succ(q1))), (i, j)) + and([quickPermutationOrder((i, j), + [permutation((q1, succ(q1))); int(1)]) | q1 : e, q1 < 4]) Generating models for model.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime +Savile Row: conjure-output/model000001.eprime Running minion for domain filtering. Running solver: minion Copying solution to: model.solutions @@ -16,12 +17,13 @@ Copying solution to: model.solutions.json Quick-Consecutive-Altogether Adding the following unnamed symmetry breaking constraints: such that - and([(i, j) .<= transform(permutation((q1, succ(q1))), (i, j)) + and([quickPermutationOrder((i, j), + [permutation((q1, succ(q1))); int(1)]) | q1 : e, q1 < 4]) Generating models for model.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime +Savile Row: conjure-output/model000001.eprime Running minion for domain filtering. Running solver: minion Copying solution to: model.solutions @@ -31,12 +33,12 @@ Copying solution to: model.solutions.json Quick-AllPairs-Independently Adding the following unnamed symmetry breaking constraints: such that - and([(i, j) .<= transform(permutation((q1, q2)), (i, j)) + and([quickPermutationOrder((i, j), [permutation((q1, q2)); int(1)]) | q1 : e, q2 : e, q1 < q2]) Generating models for model.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime +Savile Row: conjure-output/model000001.eprime Running minion for domain filtering. Running solver: minion Copying solution to: model.solutions @@ -46,12 +48,12 @@ Copying solution to: model.solutions.json Quick-AllPairs-Altogether Adding the following unnamed symmetry breaking constraints: such that - and([(i, j) .<= transform(permutation((q1, q2)), (i, j)) + and([quickPermutationOrder((i, j), [permutation((q1, q2)); int(1)]) | q1 : e, q2 : e, q1 < q2]) Generating models for model.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime +Savile Row: conjure-output/model000001.eprime Running minion for domain filtering. Running solver: minion Copying solution to: model.solutions @@ -61,11 +63,12 @@ Copying solution to: model.solutions.json Quick-AllPermutations-Independently Adding the following unnamed symmetry breaking constraints: such that - and([(i, j) .<= transform(q1, (i, j)) | q1 : permutation of e]) + and([quickPermutationOrder((i, j), [q1; int(1)]) + | q1 : permutation of e]) Generating models for model.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime +Savile Row: conjure-output/model000001.eprime Running minion for domain filtering. Running solver: minion Copying solution to: model.solutions @@ -75,11 +78,12 @@ Copying solution to: model.solutions.json Quick-AllPermutations-Altogether Adding the following unnamed symmetry breaking constraints: such that - and([(i, j) .<= transform(q1, (i, j)) | q1 : permutation of e]) + and([quickPermutationOrder((i, j), [q1; int(1)]) + | q1 : permutation of e]) Generating models for model.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime +Savile Row: conjure-output/model000001.eprime Running minion for domain filtering. Running solver: minion Copying solution to: model.solutions @@ -89,17 +93,12 @@ Copying solution to: model.solutions.json Complete-Consecutive-Independently Adding the following unnamed symmetry breaking constraints: such that - and([{ (i, j) .<= (i_auxFor_e, j_auxFor_e) - @ find i_auxFor_e: e - find j_auxFor_e: e - such that - (i_auxFor_e, j_auxFor_e) = - transform(permutation((q1, succ(q1))), (i, j)) - } | q1 : e, q1 < 4]) + and([(i, j) .<= transform(permutation((q1, succ(q1))), (i, j)) + | q1 : e, q1 < 4]) Generating models for model.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime +Savile Row: conjure-output/model000001.eprime Running minion for domain filtering. Running solver: minion Copying solution to: model.solutions @@ -109,17 +108,12 @@ Copying solution to: model.solutions.json Complete-Consecutive-Altogether Adding the following unnamed symmetry breaking constraints: such that - and([{ (i, j) .<= (i_auxFor_all, j_auxFor_all) - @ find i_auxFor_all: e - find j_auxFor_all: e - such that - (i_auxFor_all, j_auxFor_all) = - transform(permutation((q1, succ(q1))), (i, j)) - } | q1 : e, q1 < 4]) + and([(i, j) .<= transform(permutation((q1, succ(q1))), (i, j)) + | q1 : e, q1 < 4]) Generating models for model.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime +Savile Row: conjure-output/model000001.eprime Running minion for domain filtering. Running solver: minion Copying solution to: model.solutions @@ -129,16 +123,12 @@ Copying solution to: model.solutions.json Complete-AllPairs-Independently Adding the following unnamed symmetry breaking constraints: such that - and([{ (i, j) .<= (i_auxFor_e, j_auxFor_e) - @ find i_auxFor_e: e - find j_auxFor_e: e - such that - (i_auxFor_e, j_auxFor_e) = transform(permutation((q1, q2)), (i, j)) - } | q1 : e, q2 : e, q1 < q2]) + and([(i, j) .<= transform(permutation((q1, q2)), (i, j)) + | q1 : e, q2 : e, q1 < q2]) Generating models for model.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime +Savile Row: conjure-output/model000001.eprime Running minion for domain filtering. Running solver: minion Copying solution to: model.solutions @@ -148,17 +138,12 @@ Copying solution to: model.solutions.json Complete-AllPairs-Altogether Adding the following unnamed symmetry breaking constraints: such that - and([{ (i, j) .<= (i_auxFor_all, j_auxFor_all) - @ find i_auxFor_all: e - find j_auxFor_all: e - such that - (i_auxFor_all, j_auxFor_all) = - transform(permutation((q1, q2)), (i, j)) - } | q1 : e, q2 : e, q1 < q2]) + and([(i, j) .<= transform(permutation((q1, q2)), (i, j)) + | q1 : e, q2 : e, q1 < q2]) Generating models for model.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime +Savile Row: conjure-output/model000001.eprime Running minion for domain filtering. Running solver: minion Copying solution to: model.solutions @@ -168,15 +153,11 @@ Copying solution to: model.solutions.json Complete-AllPermutations-Independently Adding the following unnamed symmetry breaking constraints: such that - and([{ (i, j) .<= (i_auxFor_e, j_auxFor_e) - @ find i_auxFor_e: e - find j_auxFor_e: e - such that (i_auxFor_e, j_auxFor_e) = transform(q1, (i, j)) - } | q1 : permutation of e]) + and([(i, j) .<= transform(q1, (i, j)) | q1 : permutation of e]) Generating models for model.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime +Savile Row: conjure-output/model000001.eprime Running minion for domain filtering. Running solver: minion Copying solution to: model.solutions @@ -186,15 +167,11 @@ Copying solution to: model.solutions.json Complete-AllPermutations-Altogether Adding the following unnamed symmetry breaking constraints: such that - and([{ (i, j) .<= (i_auxFor_all, j_auxFor_all) - @ find i_auxFor_all: e - find j_auxFor_all: e - such that (i_auxFor_all, j_auxFor_all) = transform(q1, (i, j)) - } | q1 : permutation of e]) + and([(i, j) .<= transform(q1, (i, j)) | q1 : permutation of e]) Generating models for model.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime +Savile Row: conjure-output/model000001.eprime Running minion for domain filtering. Running solver: minion Copying solution to: model.solutions diff --git a/tests/custom/symmetry/set/one-var/stdout.expected b/tests/custom/symmetry/set/one-var/stdout.expected index 7b7d184068..c0800d88f6 100644 --- a/tests/custom/symmetry/set/one-var/stdout.expected +++ b/tests/custom/symmetry/set/one-var/stdout.expected @@ -1,181 +1,26 @@ Quick-Consecutive-Independently -Using cached models. -Savile Row: model000001.eprime -Running minion for domain filtering. -Running solver: minion -Copying solution to: model.solutions -Copying solution to: model.solutions.json -{"e": ["e_1", "e_2", "e_3", "e_4"], "i": "e_1"} -Quick-Consecutive-Altogether +conjure solve --number-of-solutions=all --solutions-in-one-file --output-format=jsonstream --unnamed-symmetry-breaking=Quick-Consecutive-Independently model.essence Adding the following unnamed symmetry breaking constraints: such that - and([tuple (i) .<= - transform(permutation((q1, succ(q1))), tuple (i)) + and([quickPermutationOrder(tuple (i), + [permutation((q1, succ(q1))); int(1)]) | q1 : e, q1 < 4]) Generating models for model.essence -Generated models: model000001.eprime -Saved under: conjure-output -Savile Row: model000001.eprime -Running minion for domain filtering. -Running solver: minion -Copying solution to: model.solutions -Copying solution to: model.solutions.json -{"e": ["e_1", "e_2", "e_3", "e_4"], "i": "e_1"} -Quick-AllPairs-Independently -Adding the following unnamed symmetry breaking constraints: - such that - and([tuple (i) .<= transform(permutation((q1, q2)), tuple (i)) - | q1 : e, q2 : e, q1 < q2]) -Generating models for model.essence -Generated models: model000001.eprime -Saved under: conjure-output -Savile Row: model000001.eprime -Running minion for domain filtering. -Running solver: minion -Copying solution to: model.solutions -Copying solution to: model.solutions.json -{"e": ["e_1", "e_2", "e_3", "e_4"], "i": "e_1"} -Quick-AllPairs-Altogether -Adding the following unnamed symmetry breaking constraints: - such that - and([tuple (i) .<= transform(permutation((q1, q2)), tuple (i)) - | q1 : e, q2 : e, q1 < q2]) -Generating models for model.essence -Generated models: model000001.eprime -Saved under: conjure-output -Savile Row: model000001.eprime -Running minion for domain filtering. -Running solver: minion -Copying solution to: model.solutions -Copying solution to: model.solutions.json -{"e": ["e_1", "e_2", "e_3", "e_4"], "i": "e_1"} -Quick-AllPermutations-Independently -Adding the following unnamed symmetry breaking constraints: - such that - and([tuple (i) .<= transform(q1, tuple (i)) - | q1 : permutation of e]) -Generating models for model.essence -Generated models: model000001.eprime -Saved under: conjure-output -Savile Row: model000001.eprime -Running minion for domain filtering. -Running solver: minion -Copying solution to: model.solutions -Copying solution to: model.solutions.json -{"e": ["e_1", "e_2", "e_3", "e_4"], "i": "e_1"} -Quick-AllPermutations-Altogether -Adding the following unnamed symmetry breaking constraints: - such that - and([tuple (i) .<= transform(q1, tuple (i)) - | q1 : permutation of e]) -Generating models for model.essence -Generated models: model000001.eprime -Saved under: conjure-output -Savile Row: model000001.eprime -Running minion for domain filtering. -Running solver: minion -Copying solution to: model.solutions -Copying solution to: model.solutions.json -{"e": ["e_1", "e_2", "e_3", "e_4"], "i": "e_1"} -Complete-Consecutive-Independently -Adding the following unnamed symmetry breaking constraints: - such that - and([{ tuple (i) .<= tuple (i_auxFor_e) - @ find i_auxFor_e: e - such that - tuple (i_auxFor_e) = - transform(permutation((q1, succ(q1))), tuple (i)) - } | q1 : e, q1 < 4]) -Generating models for model.essence -Generated models: model000001.eprime -Saved under: conjure-output -Savile Row: model000001.eprime -Running minion for domain filtering. -Running solver: minion -Copying solution to: model.solutions -Copying solution to: model.solutions.json -{"e": ["e_1", "e_2", "e_3", "e_4"], "i": "e_1"} -Complete-Consecutive-Altogether -Adding the following unnamed symmetry breaking constraints: - such that - and([{ tuple (i) .<= tuple (i_auxFor_all) - @ find i_auxFor_all: e - such that - tuple (i_auxFor_all) = - transform(permutation((q1, succ(q1))), tuple (i)) - } | q1 : e, q1 < 4]) -Generating models for model.essence -Generated models: model000001.eprime -Saved under: conjure-output -Savile Row: model000001.eprime -Running minion for domain filtering. -Running solver: minion -Copying solution to: model.solutions -Copying solution to: model.solutions.json -{"e": ["e_1", "e_2", "e_3", "e_4"], "i": "e_1"} -Complete-AllPairs-Independently -Adding the following unnamed symmetry breaking constraints: - such that - and([{ tuple (i) .<= tuple (i_auxFor_e) - @ find i_auxFor_e: e - such that - tuple (i_auxFor_e) = transform(permutation((q1, q2)), tuple (i)) - } | q1 : e, q2 : e, q1 < q2]) -Generating models for model.essence -Generated models: model000001.eprime -Saved under: conjure-output -Savile Row: model000001.eprime -Running minion for domain filtering. -Running solver: minion -Copying solution to: model.solutions -Copying solution to: model.solutions.json -{"e": ["e_1", "e_2", "e_3", "e_4"], "i": "e_1"} -Complete-AllPairs-Altogether -Adding the following unnamed symmetry breaking constraints: - such that - and([{ tuple (i) .<= tuple (i_auxFor_all) - @ find i_auxFor_all: e - such that - tuple (i_auxFor_all) = transform(permutation((q1, q2)), tuple (i)) - } | q1 : e, q2 : e, q1 < q2]) -Generating models for model.essence -Generated models: model000001.eprime -Saved under: conjure-output -Savile Row: model000001.eprime -Running minion for domain filtering. -Running solver: minion -Copying solution to: model.solutions -Copying solution to: model.solutions.json -{"e": ["e_1", "e_2", "e_3", "e_4"], "i": "e_1"} -Complete-AllPermutations-Independently -Adding the following unnamed symmetry breaking constraints: - such that - and([{ tuple (i) .<= tuple (i_auxFor_e) - @ find i_auxFor_e: e - such that tuple (i_auxFor_e) = transform(q1, tuple (i)) - } | q1 : permutation of e]) -Generating models for model.essence -Generated models: model000001.eprime -Saved under: conjure-output -Savile Row: model000001.eprime -Running minion for domain filtering. -Running solver: minion -Copying solution to: model.solutions -Copying solution to: model.solutions.json -{"e": ["e_1", "e_2", "e_3", "e_4"], "i": "e_1"} -Complete-AllPermutations-Altogether -Adding the following unnamed symmetry breaking constraints: - such that - and([{ tuple (i) .<= tuple (i_auxFor_all) - @ find i_auxFor_all: e - such that tuple (i_auxFor_all) = transform(q1, tuple (i)) - } | q1 : permutation of e]) -Generating models for model.essence -Generated models: model000001.eprime -Saved under: conjure-output -Savile Row: model000001.eprime -Running minion for domain filtering. -Running solver: minion -Copying solution to: model.solutions -Copying solution to: model.solutions.json -{"e": ["e_1", "e_2", "e_3", "e_4"], "i": "e_1"} +conjure: This should never happen, sorry! + +However, it did happen, so it must be a bug. Please report it to us! + +Conjure is actively maintained, we will get back to you as soon as possible. +You can help us by providing a minimal failing example. + +Also include the repository version for this build: d4f80ef16 (2024-10-24 10:19:25 +0100) + +Issue tracker: http://github.com/conjure-cp/conjure/issues + + +symmetryOrdering, no OpIndexing: + MkOpTransform (OpTransform (AbstractLiteral (AbsLitPermutation [[Reference (MachineName "q" 1 []) (Just (DeclHasRepr Quantified (MachineName "q" 1 []) (DomainInt (TagUnnamed "e") [RangeBounded (Constant (ConstantInt (TagUnnamed "e") 1)) (Constant (ConstantInt (TagUnnamed "e") 4))]))),Op (MkOpSucc (OpSucc (Reference (MachineName "q" 1 []) (Just (DeclHasRepr Quantified (MachineName "q" 1 []) (DomainInt (TagUnnamed "e") [RangeBounded (Constant (ConstantInt (TagUnnamed "e") 1)) (Constant (ConstantInt (TagUnnamed "e") 4))]))))))]])) (Reference (Name "i") (Just (DeclHasRepr Find (Name "i") (DomainSet Set_Occurrence (SetAttr SizeAttr_None) (DomainInt (TagUnnamed "e") [RangeBounded (Constant (ConstantInt (TagUnnamed "e") 1)) (Constant (ConstantInt (TagUnnamed "e") 4))])))))) + +CallStack (from HasCallStack): + error, called at src/Conjure/Bug.hs:17:15 in conjure-cp-2.5.1-IwIj6VKKx9G42E8IkwFva2:Conjure.Bug + bug, called at src/Conjure/Representations.hs:207:22 in conjure-cp-2.5.1-IwIj6VKKx9G42E8IkwFva2:Conjure.Representations diff --git a/tests/custom/symmetry/set/two-type/stdout.expected b/tests/custom/symmetry/set/two-type/stdout.expected index 979dd7b1c5..662e9cd1f4 100644 --- a/tests/custom/symmetry/set/two-type/stdout.expected +++ b/tests/custom/symmetry/set/two-type/stdout.expected @@ -1,14 +1,16 @@ Quick-Consecutive-Independently Adding the following unnamed symmetry breaking constraints: such that - and([(i, j) .<= transform(permutation((q1, succ(q1))), (i, j)) + and([quickPermutationOrder((i, j), + [permutation((q1, succ(q1))); int(1)]) | q1 : e, q1 < 4]), - and([(i, j) .<= transform(permutation((q2, succ(q2))), (i, j)) + and([quickPermutationOrder((i, j), + [permutation((q2, succ(q2))); int(1)]) | q2 : f, q2 < 4]) Generating models for model.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime +Savile Row: conjure-output/model000001.eprime Running minion for domain filtering. Running solver: minion Copying solution to: model.solutions @@ -17,9 +19,9 @@ Copying solution to: model.solutions.json Quick-Consecutive-Altogether Adding the following unnamed symmetry breaking constraints: such that - and([and([(i, j) .<= - transform(permutation((q2, succ(q2))), - transform(permutation((q1, succ(q1))), (i, j))) + and([and([quickPermutationOrder((i, j), + [permutation((q2, succ(q2))), permutation((q1, succ(q1))); + int(1..2)]) | q2 : f, q2 < 4]) | q1 : e, q1 < 4]) Generating models for model.essence @@ -30,61 +32,48 @@ However, it did happen, so it must be a bug. Please report it to us! Conjure is actively maintained, we will get back to you as soon as possible. You can help us by providing a minimal failing example. -Also include the repository version for this build: unknown +Also include the repository version for this build: d4f80ef16 (2024-10-24 10:19:25 +0100) Issue tracker: http://github.com/conjure-cp/conjure/issues -dontCare on domain: f -CallStack (from HasCallStack): - error, called at src/Conjure/Bug.hs:17:15 in conjure-cp-2.5.1-DjTx4wiFQ6I2X2qEEdPm4W:Conjure.Bug - bug, called at src/Conjure/Rules/DontCare.hs:31:20 in conjure-cp-2.5.1-DjTx4wiFQ6I2X2qEEdPm4W:Conjure.Rules.DontCare -Quick-AllPairs-Independently -Adding the following unnamed symmetry breaking constraints: - such that - and([(i, j) .<= transform(permutation((q1, q2)), (i, j)) - | q1 : e, q2 : e, q1 < q2]), - and([(i, j) .<= transform(permutation((q3, q4)), (i, j)) - | q3 : f, q4 : f, q3 < q4]) -Generating models for model.essence -Generated models: model000001.eprime -Saved under: conjure-output -Savile Row: model000001.eprime -Running minion for domain filtering. -Running solver: minion -Copying solution to: model.solutions -Copying solution to: model.solutions.json -{"e": ["e_1", "e_2", "e_3", "e_4"], "f": ["f_1", "f_2", "f_3", "f_4"], "i": "e_1", "j": "f_1"} -Quick-AllPairs-Altogether -Adding the following unnamed symmetry breaking constraints: - such that - and([and([(i, j) .<= - transform(permutation((q3, q4)), - transform(permutation((q1, q2)), (i, j))) - | q3 : f, q4 : f, q3 < q4]) - | q1 : e, q2 : e, q1 < q2]) -Generating models for model.essence -conjure: This should never happen, sorry! - -However, it did happen, so it must be a bug. Please report it to us! - -Conjure is actively maintained, we will get back to you as soon as possible. -You can help us by providing a minimal failing example. - -Also include the repository version for this build: unknown - -Issue tracker: http://github.com/conjure-cp/conjure/issues - - -dontCare on domain: f +Not refined: (i, + j) AbstractLiteral (AbsLitTuple [Reference (Name "i") (Just (DeclHasRepr Find (Name "i") (DomainInt (TagUnnamed "e") [RangeBounded (Constant (ConstantInt (TagUnnamed "e") 1)) (Constant (ConstantInt (TagUnnamed "e") 4))]))),Reference (Name "j") (Just (DeclHasRepr Find (Name "j") (DomainInt (TagUnnamed "f") [RangeBounded (Constant (ConstantInt (TagUnnamed "f") 1)) (Constant (ConstantInt (TagUnnamed "f") 4))])))]) + Context #1: quickPermutationOrder((i, j), [permutation((q2, succ(q2))), permutation((q1, succ(q1))); int(1..2)]) + Context #2: [quickPermutationOrder((i, j), [permutation((q2, succ(q2))), permutation((q1, succ(q1))); int(1..2)]) + | q2 : int(1..4), q2 < 4] + Context #3: and([quickPermutationOrder((i, j), + [permutation((q2, succ(q2))), permutation((q1, succ(q1))); int(1..2)]) + | q2 : int(1..4), q2 < 4]) + Context #4: [and([quickPermutationOrder((i, j), + [permutation((q2, succ(q2))), permutation((q1, succ(q1))); int(1..2)]) + | q2 : int(1..4), q2 < 4]) + | q1 : int(1..4), q1 < 4] + Context #5: and([and([quickPermutationOrder((i, j), + [permutation((q2, succ(q2))), permutation((q1, succ(q1))); int(1..2)]) + | q2 : int(1..4), q2 < 4]) + | q1 : int(1..4), q1 < 4]) +Not refined: permutation((q2, + succ(q2))) AbstractLiteral (AbsLitPermutation [[Reference (MachineName "q" 2 []) (Just (DeclHasRepr Quantified (MachineName "q" 2 []) (DomainInt (TagUnnamed "f") [RangeBounded (Constant (ConstantInt (TagUnnamed "f") 1)) (Constant (ConstantInt (TagUnnamed "f") 4))]))),Op (MkOpSucc (OpSucc (Reference (MachineName "q" 2 []) (Just (DeclHasRepr Quantified (MachineName "q" 2 []) (DomainInt (TagUnnamed "f") [RangeBounded (Constant (ConstantInt (TagUnnamed "f") 1)) (Constant (ConstantInt (TagUnnamed "f") 4))]))))))]]) + Context #1: [permutation((q2, succ(q2))), permutation((q1, succ(q1))); int(1..2)] + Context #2: quickPermutationOrder((i, j), [permutation((q2, succ(q2))), permutation((q1, succ(q1))); int(1..2)]) + Context #3: [quickPermutationOrder((i, j), [permutation((q2, succ(q2))), permutation((q1, succ(q1))); int(1..2)]) + | q2 : int(1..4), q2 < 4] + Context #4: and([quickPermutationOrder((i, j), + [permutation((q2, succ(q2))), permutation((q1, succ(q1))); int(1..2)]) + | q2 : int(1..4), q2 < 4]) + Context #5: [and([quickPermutationOrder((i, j), + [permutation((q2, succ(q2))), permutation((q1, succ(q1))); int(1..2)]) + | q2 : int(1..4), q2 < 4]) + | q1 : int(1..4), q1 < 4] + Context #6: and([and([quickPermutationOrder((i, j), + [permutation((q2, succ(q2))), permutation((q1, succ(q1))); int(1..2)]) + | q2 : int(1..4), q2 < 4]) + | q1 : int(1..4), q1 < 4]) +Not refined: permutation((q1, + succ(q1))) AbstractLiteral (AbsLitPermutation [[Reference (MachineName "q" 1 []) (Just (DeclHasRepr Quantified (MachineName "q" 1 []) (DomainInt (TagUnnamed "e") [RangeBounded (Constant (ConstantInt (TagUnnamed "e") 1)) (Constant (ConstantInt (TagUnnamed "e") 4))]))),Op (MkOpSucc (OpSucc (Reference (MachineName "q" 1 []) (Just (DeclHasRepr Quantified (MachineName "q" 1 []) (DomainInt (TagUnnamed "e") [RangeBounded (Constant (ConstantInt (TagUnnamed "e") 1)) (Constant (ConstantInt (TagUnnamed "e") 4))]))))))]]) CallStack (from HasCallStack): - error, called at src/Conjure/Bug.hs:17:15 in conjure-cp-2.5.1-DjTx4wiFQ6I2X2qEEdPm4W:Conjure.Bug - bug, called at src/Conjure/Rules/DontCare.hs:31:20 in conjure-cp-2.5.1-DjTx4wiFQ6I2X2qEEdPm4W:Conjure.Rules.DontCare -Quick-AllPermutations-Independently -Adding the following unnamed symmetry breaking constraints: - such that - and([(i, j) .<= transform(q1, (i, j)) | q1 : permutation of e]), - and([(i, j) .<= transform(q2, (i, j)) | q2 : permutation of f]) -Generating models for model.essence + error, called at src/Conjure/Bug.hs:17:15 in conjure-cp-2.5.1-IwIj6VKKx9G42E8IkwFva2:Conjure.Bug + bug, called at src/Conjure/UI/Model.hs:1041:26 in conjure-cp-2.5.1-IwIj6VKKx9G42E8IkwFva2:Conjure.UI.Model diff --git a/tests/custom/symmetry/set/two-var/stdout.expected b/tests/custom/symmetry/set/two-var/stdout.expected index 5c05e77f4b..8a383a9f05 100644 --- a/tests/custom/symmetry/set/two-var/stdout.expected +++ b/tests/custom/symmetry/set/two-var/stdout.expected @@ -1,12 +1,13 @@ Quick-Consecutive-Independently Adding the following unnamed symmetry breaking constraints: such that - and([(i, j) .<= transform(permutation((q1, succ(q1))), (i, j)) + and([quickPermutationOrder((i, j), + [permutation((q1, succ(q1))); int(1)]) | q1 : e, q1 < 4]) Generating models for model.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime +Savile Row: conjure-output/model000001.eprime Running minion for domain filtering. Running solver: minion Copying solution to: model.solutions @@ -16,12 +17,13 @@ Copying solution to: model.solutions.json Quick-Consecutive-Altogether Adding the following unnamed symmetry breaking constraints: such that - and([(i, j) .<= transform(permutation((q1, succ(q1))), (i, j)) + and([quickPermutationOrder((i, j), + [permutation((q1, succ(q1))); int(1)]) | q1 : e, q1 < 4]) Generating models for model.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime +Savile Row: conjure-output/model000001.eprime Running minion for domain filtering. Running solver: minion Copying solution to: model.solutions @@ -31,12 +33,12 @@ Copying solution to: model.solutions.json Quick-AllPairs-Independently Adding the following unnamed symmetry breaking constraints: such that - and([(i, j) .<= transform(permutation((q1, q2)), (i, j)) + and([quickPermutationOrder((i, j), [permutation((q1, q2)); int(1)]) | q1 : e, q2 : e, q1 < q2]) Generating models for model.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime +Savile Row: conjure-output/model000001.eprime Running minion for domain filtering. Running solver: minion Copying solution to: model.solutions @@ -46,12 +48,12 @@ Copying solution to: model.solutions.json Quick-AllPairs-Altogether Adding the following unnamed symmetry breaking constraints: such that - and([(i, j) .<= transform(permutation((q1, q2)), (i, j)) + and([quickPermutationOrder((i, j), [permutation((q1, q2)); int(1)]) | q1 : e, q2 : e, q1 < q2]) Generating models for model.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime +Savile Row: conjure-output/model000001.eprime Running minion for domain filtering. Running solver: minion Copying solution to: model.solutions @@ -61,11 +63,12 @@ Copying solution to: model.solutions.json Quick-AllPermutations-Independently Adding the following unnamed symmetry breaking constraints: such that - and([(i, j) .<= transform(q1, (i, j)) | q1 : permutation of e]) + and([quickPermutationOrder((i, j), [q1; int(1)]) + | q1 : permutation of e]) Generating models for model.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime +Savile Row: conjure-output/model000001.eprime Running minion for domain filtering. Running solver: minion Copying solution to: model.solutions @@ -75,11 +78,12 @@ Copying solution to: model.solutions.json Quick-AllPermutations-Altogether Adding the following unnamed symmetry breaking constraints: such that - and([(i, j) .<= transform(q1, (i, j)) | q1 : permutation of e]) + and([quickPermutationOrder((i, j), [q1; int(1)]) + | q1 : permutation of e]) Generating models for model.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime +Savile Row: conjure-output/model000001.eprime Running minion for domain filtering. Running solver: minion Copying solution to: model.solutions @@ -89,17 +93,12 @@ Copying solution to: model.solutions.json Complete-Consecutive-Independently Adding the following unnamed symmetry breaking constraints: such that - and([{ (i, j) .<= (i_auxFor_e, j_auxFor_e) - @ find i_auxFor_e: e - find j_auxFor_e: e - such that - (i_auxFor_e, j_auxFor_e) = - transform(permutation((q1, succ(q1))), (i, j)) - } | q1 : e, q1 < 4]) + and([(i, j) .<= transform(permutation((q1, succ(q1))), (i, j)) + | q1 : e, q1 < 4]) Generating models for model.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime +Savile Row: conjure-output/model000001.eprime Running minion for domain filtering. Running solver: minion Copying solution to: model.solutions @@ -109,17 +108,12 @@ Copying solution to: model.solutions.json Complete-Consecutive-Altogether Adding the following unnamed symmetry breaking constraints: such that - and([{ (i, j) .<= (i_auxFor_all, j_auxFor_all) - @ find i_auxFor_all: e - find j_auxFor_all: e - such that - (i_auxFor_all, j_auxFor_all) = - transform(permutation((q1, succ(q1))), (i, j)) - } | q1 : e, q1 < 4]) + and([(i, j) .<= transform(permutation((q1, succ(q1))), (i, j)) + | q1 : e, q1 < 4]) Generating models for model.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime +Savile Row: conjure-output/model000001.eprime Running minion for domain filtering. Running solver: minion Copying solution to: model.solutions @@ -129,16 +123,12 @@ Copying solution to: model.solutions.json Complete-AllPairs-Independently Adding the following unnamed symmetry breaking constraints: such that - and([{ (i, j) .<= (i_auxFor_e, j_auxFor_e) - @ find i_auxFor_e: e - find j_auxFor_e: e - such that - (i_auxFor_e, j_auxFor_e) = transform(permutation((q1, q2)), (i, j)) - } | q1 : e, q2 : e, q1 < q2]) + and([(i, j) .<= transform(permutation((q1, q2)), (i, j)) + | q1 : e, q2 : e, q1 < q2]) Generating models for model.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime +Savile Row: conjure-output/model000001.eprime Running minion for domain filtering. Running solver: minion Copying solution to: model.solutions @@ -148,17 +138,12 @@ Copying solution to: model.solutions.json Complete-AllPairs-Altogether Adding the following unnamed symmetry breaking constraints: such that - and([{ (i, j) .<= (i_auxFor_all, j_auxFor_all) - @ find i_auxFor_all: e - find j_auxFor_all: e - such that - (i_auxFor_all, j_auxFor_all) = - transform(permutation((q1, q2)), (i, j)) - } | q1 : e, q2 : e, q1 < q2]) + and([(i, j) .<= transform(permutation((q1, q2)), (i, j)) + | q1 : e, q2 : e, q1 < q2]) Generating models for model.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime +Savile Row: conjure-output/model000001.eprime Running minion for domain filtering. Running solver: minion Copying solution to: model.solutions @@ -168,15 +153,11 @@ Copying solution to: model.solutions.json Complete-AllPermutations-Independently Adding the following unnamed symmetry breaking constraints: such that - and([{ (i, j) .<= (i_auxFor_e, j_auxFor_e) - @ find i_auxFor_e: e - find j_auxFor_e: e - such that (i_auxFor_e, j_auxFor_e) = transform(q1, (i, j)) - } | q1 : permutation of e]) + and([(i, j) .<= transform(q1, (i, j)) | q1 : permutation of e]) Generating models for model.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime +Savile Row: conjure-output/model000001.eprime Running minion for domain filtering. Running solver: minion Copying solution to: model.solutions @@ -186,15 +167,11 @@ Copying solution to: model.solutions.json Complete-AllPermutations-Altogether Adding the following unnamed symmetry breaking constraints: such that - and([{ (i, j) .<= (i_auxFor_all, j_auxFor_all) - @ find i_auxFor_all: e - find j_auxFor_all: e - such that (i_auxFor_all, j_auxFor_all) = transform(q1, (i, j)) - } | q1 : permutation of e]) + and([(i, j) .<= transform(q1, (i, j)) | q1 : permutation of e]) Generating models for model.essence Generated models: model000001.eprime Saved under: conjure-output -Savile Row: model000001.eprime +Savile Row: conjure-output/model000001.eprime Running minion for domain filtering. Running solver: minion Copying solution to: model.solutions diff --git a/tests/exhaustive/acceptOutput.sh b/tests/exhaustive/acceptOutput.sh index 983b32fa6a..682820c767 100755 --- a/tests/exhaustive/acceptOutput.sh +++ b/tests/exhaustive/acceptOutput.sh @@ -12,7 +12,9 @@ for TESTCASE in $*; do echo "Accepting the output of ${TESTCASE}" rm -rf "${TESTCASE}"/expected mkdir -p "${TESTCASE}"/expected - cp "${TESTCASE}"/outputs/*.eprime "${TESTCASE}"/outputs/*.solution "${TESTCASE}"/outputs/*.eprime-param "${TESTCASE}"/expected/ + for file in "${TESTCASE}"/outputs/*.eprime "${TESTCASE}"/outputs/*.solution "${TESTCASE}"/outputs/*.eprime-param ; do + cp $file "${TESTCASE}"/expected/ + done parallel --no-notice "[ -f {} ] && (cat {} | grep -v '\\$' > {}.temp ; mv {}.temp {})" \ ::: "${TESTCASE}"/expected/*.eprime fi diff --git a/tests/exhaustive/basic/perms/01_representation/enum/0005_find_permutation_size_4_of_int1_4/permutation.essence b/tests/exhaustive/basic/perms/01_representation/enum/0005_find_permutation_size_4_of_int1_4/permutation.essence index 26786093fd..168c3d1fcf 100644 --- a/tests/exhaustive/basic/perms/01_representation/enum/0005_find_permutation_size_4_of_int1_4/permutation.essence +++ b/tests/exhaustive/basic/perms/01_representation/enum/0005_find_permutation_size_4_of_int1_4/permutation.essence @@ -1,5 +1,5 @@ letting n be new type enum {E1,E2,E3,E4} -find p : permutation (size 4) of n +find p : permutation (numMoved 4) of n such that true diff --git a/tests/exhaustive/basic/perms/01_representation/enum/0006_find_permutation_size_0_of_int1_4/permutation.essence b/tests/exhaustive/basic/perms/01_representation/enum/0006_find_permutation_size_0_of_int1_4/permutation.essence index 9a91f2f8d1..416f090d31 100644 --- a/tests/exhaustive/basic/perms/01_representation/enum/0006_find_permutation_size_0_of_int1_4/permutation.essence +++ b/tests/exhaustive/basic/perms/01_representation/enum/0006_find_permutation_size_0_of_int1_4/permutation.essence @@ -1,5 +1,5 @@ letting n be new type enum {E1,E2,E3,E4} -find p : permutation (size 0) of n +find p : permutation (numMoved 0) of n such that true diff --git a/tests/exhaustive/basic/perms/01_representation/enum/0010_find_permutation_maxSize_2_of_int1_3/permutation.essence b/tests/exhaustive/basic/perms/01_representation/enum/0010_find_permutation_maxSize_2_of_int1_3/permutation.essence index 5e23322970..1c30cf7fba 100644 --- a/tests/exhaustive/basic/perms/01_representation/enum/0010_find_permutation_maxSize_2_of_int1_3/permutation.essence +++ b/tests/exhaustive/basic/perms/01_representation/enum/0010_find_permutation_maxSize_2_of_int1_3/permutation.essence @@ -1,5 +1,5 @@ letting n be new type enum {E1,E2,E3} -find p : permutation (maxSize 2) of n +find p : permutation (maxNumMoved 2) of n such that true diff --git a/tests/exhaustive/basic/perms/01_representation/enum/0011_find_permutation_minSize_2_of_int1_3/permutation.essence b/tests/exhaustive/basic/perms/01_representation/enum/0011_find_permutation_minSize_2_of_int1_3/permutation.essence index 3da37a3987..ff3c1e4829 100644 --- a/tests/exhaustive/basic/perms/01_representation/enum/0011_find_permutation_minSize_2_of_int1_3/permutation.essence +++ b/tests/exhaustive/basic/perms/01_representation/enum/0011_find_permutation_minSize_2_of_int1_3/permutation.essence @@ -1,5 +1,5 @@ letting n be new type enum {E1,E2,E3} -find p : permutation (minSize 2) of n +find p : permutation (minNumMoved 2) of n such that true diff --git a/tests/exhaustive/basic/perms/01_representation/enum/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/permutation.essence b/tests/exhaustive/basic/perms/01_representation/enum/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/permutation.essence index 6fc7ffd73a..efdb41fa4d 100644 --- a/tests/exhaustive/basic/perms/01_representation/enum/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/permutation.essence +++ b/tests/exhaustive/basic/perms/01_representation/enum/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/permutation.essence @@ -1,5 +1,5 @@ letting n be new type enum {E1,E2,E3,E4} -find p : permutation (minSize 2, maxSize 3) of n +find p : permutation (minNumMoved 2, maxNumMoved 3) of n such that true diff --git a/tests/exhaustive/basic/perms/01_representation/int/0005_find_permutation_size_4_of_int1_4/permutation.essence b/tests/exhaustive/basic/perms/01_representation/int/0005_find_permutation_size_4_of_int1_4/permutation.essence index 63899fe581..89236f50f6 100644 --- a/tests/exhaustive/basic/perms/01_representation/int/0005_find_permutation_size_4_of_int1_4/permutation.essence +++ b/tests/exhaustive/basic/perms/01_representation/int/0005_find_permutation_size_4_of_int1_4/permutation.essence @@ -1,5 +1,5 @@ letting n be 4 -find p : permutation (size n) of int(1..n) +find p : permutation (numMoved n) of int(1..n) such that true diff --git a/tests/exhaustive/basic/perms/01_representation/int/0006_find_permutation_size_0_of_int1_4/permutation.essence b/tests/exhaustive/basic/perms/01_representation/int/0006_find_permutation_size_0_of_int1_4/permutation.essence index 8c60c7b839..ccafebc41b 100644 --- a/tests/exhaustive/basic/perms/01_representation/int/0006_find_permutation_size_0_of_int1_4/permutation.essence +++ b/tests/exhaustive/basic/perms/01_representation/int/0006_find_permutation_size_0_of_int1_4/permutation.essence @@ -1,5 +1,5 @@ letting n be 4 -find p : permutation (size 0) of int(1..n) +find p : permutation (numMoved 0) of int(1..n) such that true diff --git a/tests/exhaustive/basic/perms/01_representation/int/0010_find_permutation_maxSize_2_of_int1_3/permutation.essence b/tests/exhaustive/basic/perms/01_representation/int/0010_find_permutation_maxSize_2_of_int1_3/permutation.essence index c5f650a6ea..15a188fb94 100644 --- a/tests/exhaustive/basic/perms/01_representation/int/0010_find_permutation_maxSize_2_of_int1_3/permutation.essence +++ b/tests/exhaustive/basic/perms/01_representation/int/0010_find_permutation_maxSize_2_of_int1_3/permutation.essence @@ -1,5 +1,5 @@ letting n be 3 -find p : permutation (maxSize 2) of int(1..n) +find p : permutation (maxNumMoved 2) of int(1..n) such that true diff --git a/tests/exhaustive/basic/perms/01_representation/int/0011_find_permutation_minSize_2_of_int1_3/permutation.essence b/tests/exhaustive/basic/perms/01_representation/int/0011_find_permutation_minSize_2_of_int1_3/permutation.essence index 73007c1924..c9843c284c 100644 --- a/tests/exhaustive/basic/perms/01_representation/int/0011_find_permutation_minSize_2_of_int1_3/permutation.essence +++ b/tests/exhaustive/basic/perms/01_representation/int/0011_find_permutation_minSize_2_of_int1_3/permutation.essence @@ -1,5 +1,5 @@ letting n be 3 -find p : permutation (minSize 2) of int(1..n) +find p : permutation (minNumMoved 2) of int(1..n) such that true diff --git a/tests/exhaustive/basic/perms/01_representation/int/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/permutation.essence b/tests/exhaustive/basic/perms/01_representation/int/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/permutation.essence index 4460f93ee0..8d766f503c 100644 --- a/tests/exhaustive/basic/perms/01_representation/int/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/permutation.essence +++ b/tests/exhaustive/basic/perms/01_representation/int/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/permutation.essence @@ -1,5 +1,5 @@ letting n be 4 -find p : permutation (minSize 2, maxSize 3) of int(1..n) +find p : permutation (minNumMoved 2, maxNumMoved 3) of int(1..n) such that true diff --git a/tests/exhaustive/basic/perms/01_representation/unnamed/0005_find_permutation_size_4_of_int1_4/permutation.essence b/tests/exhaustive/basic/perms/01_representation/unnamed/0005_find_permutation_size_4_of_int1_4/permutation.essence index 355a19fd10..7e3103b9ae 100644 --- a/tests/exhaustive/basic/perms/01_representation/unnamed/0005_find_permutation_size_4_of_int1_4/permutation.essence +++ b/tests/exhaustive/basic/perms/01_representation/unnamed/0005_find_permutation_size_4_of_int1_4/permutation.essence @@ -1,5 +1,5 @@ letting n be new type of size 4 -find p : permutation (size 4) of n +find p : permutation (numMoved 4) of n such that true diff --git a/tests/exhaustive/basic/perms/01_representation/unnamed/0006_find_permutation_size_0_of_int1_4/permutation.essence b/tests/exhaustive/basic/perms/01_representation/unnamed/0006_find_permutation_size_0_of_int1_4/permutation.essence index 264e52e6b7..bfbce4c1b3 100644 --- a/tests/exhaustive/basic/perms/01_representation/unnamed/0006_find_permutation_size_0_of_int1_4/permutation.essence +++ b/tests/exhaustive/basic/perms/01_representation/unnamed/0006_find_permutation_size_0_of_int1_4/permutation.essence @@ -1,5 +1,5 @@ letting n be new type of size 4 -find p : permutation (size 0) of n +find p : permutation (numMoved 0) of n such that true diff --git a/tests/exhaustive/basic/perms/01_representation/unnamed/0010_find_permutation_maxSize_2_of_int1_3/permutation.essence b/tests/exhaustive/basic/perms/01_representation/unnamed/0010_find_permutation_maxSize_2_of_int1_3/permutation.essence index 7e78359040..f934e59fef 100644 --- a/tests/exhaustive/basic/perms/01_representation/unnamed/0010_find_permutation_maxSize_2_of_int1_3/permutation.essence +++ b/tests/exhaustive/basic/perms/01_representation/unnamed/0010_find_permutation_maxSize_2_of_int1_3/permutation.essence @@ -1,5 +1,5 @@ letting n be new type of size 3 -find p : permutation (maxSize 2) of n +find p : permutation (maxNumMoved 2) of n such that true diff --git a/tests/exhaustive/basic/perms/01_representation/unnamed/0011_find_permutation_minSize_2_of_int1_3/permutation.essence b/tests/exhaustive/basic/perms/01_representation/unnamed/0011_find_permutation_minSize_2_of_int1_3/permutation.essence index b2a3c523d4..050ba156ba 100644 --- a/tests/exhaustive/basic/perms/01_representation/unnamed/0011_find_permutation_minSize_2_of_int1_3/permutation.essence +++ b/tests/exhaustive/basic/perms/01_representation/unnamed/0011_find_permutation_minSize_2_of_int1_3/permutation.essence @@ -1,5 +1,5 @@ letting n be new type of size 3 -find p : permutation (minSize 2) of n +find p : permutation (minNumMoved 2) of n such that true diff --git a/tests/exhaustive/basic/perms/01_representation/unnamed/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/permutation.essence b/tests/exhaustive/basic/perms/01_representation/unnamed/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/permutation.essence index 5083fed5ca..6e6fc720e0 100644 --- a/tests/exhaustive/basic/perms/01_representation/unnamed/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/permutation.essence +++ b/tests/exhaustive/basic/perms/01_representation/unnamed/0012_find_permutation_maxSize_3_minSize_2_of_int1_4/permutation.essence @@ -1,5 +1,5 @@ letting n be new type of size 4 -find p : permutation (minSize 2, maxSize 3) of n +find p : permutation (minNumMoved 2, maxNumMoved 3) of n such that true diff --git a/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/permutation.essence b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/permutation.essence index 663987f4f6..37609a03df 100644 --- a/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/permutation.essence +++ b/tests/exhaustive/basic/perms/02_cardinality/enum/0003_find_permutation/permutation.essence @@ -1,5 +1,5 @@ letting n be new type enum {E1,E2,E3,E4,E5,E6} -find p : permutation (size 4) of n +find p : permutation (numMoved 4) of n find i : int(0..10) diff --git a/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/permutation.essence b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/permutation.essence index 59127b82f2..d45cd82f95 100644 --- a/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/permutation.essence +++ b/tests/exhaustive/basic/perms/02_cardinality/int/0003_find_permutation/permutation.essence @@ -1,4 +1,4 @@ -find p : permutation (size 4) of int(1..6) +find p : permutation (numMoved 4) of int(1..6) find i : int(0..10) diff --git a/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/permutation.essence b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/permutation.essence index 05bc8e04fa..dc3f7f4b8d 100644 --- a/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/permutation.essence +++ b/tests/exhaustive/basic/perms/02_cardinality/unnamed/0003_find_permutation/permutation.essence @@ -1,5 +1,5 @@ letting n be new type of size 6 -find p : permutation (size 4) of n +find p : permutation (numMoved 4) of n find i : int(0..10) diff --git a/tests/exhaustive/basic/perms/03_generators/enum/0003_find_permutation_in_generator/permutation.essence b/tests/exhaustive/basic/perms/03_generators/enum/0003_find_permutation_in_generator/permutation.essence index 6bfee9c393..00309a7bd3 100644 --- a/tests/exhaustive/basic/perms/03_generators/enum/0003_find_permutation_in_generator/permutation.essence +++ b/tests/exhaustive/basic/perms/03_generators/enum/0003_find_permutation_in_generator/permutation.essence @@ -1,5 +1,5 @@ letting n be new type enum {E1,E2,E3,E4} -find p : permutation (size 3) of n +find p : permutation (numMoved 3) of n find s : set (size 3) of (n,n) such that diff --git a/tests/exhaustive/basic/perms/03_generators/enum/0004_find_permutation_in_generator/permutation.essence b/tests/exhaustive/basic/perms/03_generators/enum/0004_find_permutation_in_generator/permutation.essence index 80c1a9b4e3..1b7555382e 100644 --- a/tests/exhaustive/basic/perms/03_generators/enum/0004_find_permutation_in_generator/permutation.essence +++ b/tests/exhaustive/basic/perms/03_generators/enum/0004_find_permutation_in_generator/permutation.essence @@ -1,5 +1,5 @@ letting n be new type enum {E1,E2,E3,E4} -find p : permutation (size 3) of n +find p : permutation (numMoved 3) of n such that diff --git a/tests/exhaustive/basic/perms/03_generators/int/0003_find_permutation_in_generator/permutation.essence b/tests/exhaustive/basic/perms/03_generators/int/0003_find_permutation_in_generator/permutation.essence index 33a9d426d3..b3e71b3d93 100644 --- a/tests/exhaustive/basic/perms/03_generators/int/0003_find_permutation_in_generator/permutation.essence +++ b/tests/exhaustive/basic/perms/03_generators/int/0003_find_permutation_in_generator/permutation.essence @@ -1,4 +1,4 @@ -find p : permutation (size 3) of int(1..4) +find p : permutation (numMoved 3) of int(1..4) find s : set (size 3) of (int(1..4),int(1..4)) such that diff --git a/tests/exhaustive/basic/perms/03_generators/int/0004_find_permutation_in_forall/permutation.essence b/tests/exhaustive/basic/perms/03_generators/int/0004_find_permutation_in_forall/permutation.essence index d4ccc8d532..28fa6d4963 100644 --- a/tests/exhaustive/basic/perms/03_generators/int/0004_find_permutation_in_forall/permutation.essence +++ b/tests/exhaustive/basic/perms/03_generators/int/0004_find_permutation_in_forall/permutation.essence @@ -1,4 +1,4 @@ -find p : permutation (size 3) of int(1..4) +find p : permutation (numMoved 3) of int(1..4) find s : set (size 3) of (int(1..4),int(1..4)) such that diff --git a/tests/exhaustive/basic/perms/03_generators/int/0005_find_permutation_in_forall/permutation.essence b/tests/exhaustive/basic/perms/03_generators/int/0005_find_permutation_in_forall/permutation.essence index 3c63df7e7d..c20f17d2be 100644 --- a/tests/exhaustive/basic/perms/03_generators/int/0005_find_permutation_in_forall/permutation.essence +++ b/tests/exhaustive/basic/perms/03_generators/int/0005_find_permutation_in_forall/permutation.essence @@ -1,4 +1,4 @@ -find p : permutation (size 3) of int(1..4) +find p : permutation (numMoved 3) of int(1..4) find s : set (size 3) of (int(1..4),int(1..4)) such that diff --git a/tests/exhaustive/basic/perms/03_generators/unnamed/0003_find_permutation_in_generator/permutation.essence b/tests/exhaustive/basic/perms/03_generators/unnamed/0003_find_permutation_in_generator/permutation.essence index 3d0835eaf5..1b5759ebc0 100644 --- a/tests/exhaustive/basic/perms/03_generators/unnamed/0003_find_permutation_in_generator/permutation.essence +++ b/tests/exhaustive/basic/perms/03_generators/unnamed/0003_find_permutation_in_generator/permutation.essence @@ -1,5 +1,5 @@ letting n be new type of size 4 -find p : permutation (size 3) of n +find p : permutation (numMoved 3) of n find s : set (size 3) of (n,n) such that diff --git a/tests/exhaustive/basic/perms/05_equality/enum/0006_in_comprehension/permutation.essence b/tests/exhaustive/basic/perms/05_equality/enum/0006_in_comprehension/permutation.essence index cc47c67c6e..088963dec0 100644 --- a/tests/exhaustive/basic/perms/05_equality/enum/0006_in_comprehension/permutation.essence +++ b/tests/exhaustive/basic/perms/05_equality/enum/0006_in_comprehension/permutation.essence @@ -1,6 +1,6 @@ letting n be new type enum {E1,E2,E3,E4} -find p : permutation (size 4) of n -find q : permutation (size 4) of n +find p : permutation (numMoved 4) of n +find q : permutation (numMoved 4) of n such that and([pt != qt | pt <- p, qt <- q]) diff --git a/tests/exhaustive/basic/perms/05_equality/int/0006_in_comprehension/permutation.essence b/tests/exhaustive/basic/perms/05_equality/int/0006_in_comprehension/permutation.essence index eab596738f..a812904110 100644 --- a/tests/exhaustive/basic/perms/05_equality/int/0006_in_comprehension/permutation.essence +++ b/tests/exhaustive/basic/perms/05_equality/int/0006_in_comprehension/permutation.essence @@ -1,5 +1,5 @@ -find p : permutation (size 4) of int(1..4) -find q : permutation (size 4) of int(1..4) +find p : permutation (numMoved 4) of int(1..4) +find q : permutation (numMoved 4) of int(1..4) such that and([pt != qt | pt <- p, qt <- q]) diff --git a/tests/exhaustive/basic/perms/05_equality/unnamed/0006_in_comprehension/permutation.essence b/tests/exhaustive/basic/perms/05_equality/unnamed/0006_in_comprehension/permutation.essence index 1788ddf5fc..0a8ee886b1 100644 --- a/tests/exhaustive/basic/perms/05_equality/unnamed/0006_in_comprehension/permutation.essence +++ b/tests/exhaustive/basic/perms/05_equality/unnamed/0006_in_comprehension/permutation.essence @@ -1,6 +1,6 @@ letting n be new type of size 4 -find p : permutation (size 4) of n -find q : permutation (size 4) of n +find p : permutation (numMoved 4) of n +find q : permutation (numMoved 4) of n such that and([pt != qt | pt <- p, qt <- q]) diff --git a/tests/exhaustive/mildly_interesting/subsetSum/expected/model_2_2_2.eprime b/tests/exhaustive/mildly_interesting/subsetSum/expected/model_2_2_2.eprime index e242a71db7..627992db38 100644 --- a/tests/exhaustive/mildly_interesting/subsetSum/expected/model_2_2_2.eprime +++ b/tests/exhaustive/mildly_interesting/subsetSum/expected/model_2_2_2.eprime @@ -20,7 +20,7 @@ such that and([x_ExplicitVarSizeWithFlags_Flags[q2 + 1] -> x_ExplicitVarSizeWithFlags_Values[q2] < x_ExplicitVarSizeWithFlags_Values[q2 + 1] | q2 : int(1..let1 - 1)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3] = false -> x_ExplicitVarSizeWithFlags_Values[q3] = min(let2) + and([x_ExplicitVarSizeWithFlags_Flags[q3] = false -> dontCare(x_ExplicitVarSizeWithFlags_Values[q3]) | q3 : int(1..let1)]), and([x_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q4] | q4 : int(1..let1 - 1)]), 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q5]) | q5 : int(1..let1)]), From 3dbcd95eb78c649eb03fb5dfdff9adf3b59c3946 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?=C3=96zg=C3=BCr=20Akg=C3=BCn?= Date: Thu, 7 Nov 2024 10:38:09 +0000 Subject: [PATCH 186/229] adding the transform(p,x)[i] rule --- src/Conjure/Rules/Transform.hs | 44 ++----------------- .../permutations/permInverse/04/04.essence | 14 ++++++ .../custom/permutations/permInverse/04/run.sh | 5 +++ .../permInverse/04/stdout.expected | 31 +++++++++++++ 4 files changed, 54 insertions(+), 40 deletions(-) create mode 100644 tests/custom/permutations/permInverse/04/04.essence create mode 100755 tests/custom/permutations/permInverse/04/run.sh create mode 100644 tests/custom/permutations/permInverse/04/stdout.expected diff --git a/src/Conjure/Rules/Transform.hs b/src/Conjure/Rules/Transform.hs index 947c3634d6..27986f2d38 100644 --- a/src/Conjure/Rules/Transform.hs +++ b/src/Conjure/Rules/Transform.hs @@ -319,48 +319,12 @@ rule_Transformed_Indexing = "transformed-indexing" `namedRule` theRule rule_Lift_Transformed_Indexing :: Rule rule_Lift_Transformed_Indexing = "lift-transformed-indexing" `namedRule` theRule where - matchIndexing :: - (?typeCheckerMode :: TypeCheckerMode) => - Expression -> - Maybe (Expression, Expression, Expression, Expression) - matchIndexing exp = do - (matexp, indexer) <- match opIndexing exp - (morphism, mat) <- match opTransform matexp - return (exp, morphism, mat, indexer) - - liftIndexing (exp, morphism, mat, indexer) = do - (Single nm, m) <- quantifiedVar + theRule [essence| transform(&p, &x)[&i] |] = do + TypePermutation {} <- typeOf p return - ( (exp, [essence| transform(&morphism, &m) |]), - ComprehensionLetting (Single nm) [essence| &mat[&indexer] |] + ( "transformed indexing", + return [essence| transform(&p, &x[transform(permInverse(&p), &i)]) |] ) - - transformBody bdy [] = bdy - transformBody bdy ((orig, repl) : rest) = - let nbdy = - transformBi - ( \e -> - if e == orig - then repl - else e - ) - bdy - in transformBody nbdy rest - - theRule (Comprehension body gensOrConds) = do - let matched = catMaybes [matchIndexing exp | exp <- universeBi body] - case matched of - [] -> na "rule_Lift_Transformed_Indexing: nothing to lift" - _ -> do - replacements <- mapM liftIndexing matched - return - ( "Horizontal rule for lift transformed indexing", - return - ( Comprehension (transformBody body (fst <$> replacements)) - $ gensOrConds - ++ (snd <$> replacements) - ) - ) theRule _ = na "rule_Lift_Transformed_Indexing" rule_Transform_Indexing :: Rule diff --git a/tests/custom/permutations/permInverse/04/04.essence b/tests/custom/permutations/permInverse/04/04.essence new file mode 100644 index 0000000000..38ba6303f0 --- /dev/null +++ b/tests/custom/permutations/permInverse/04/04.essence @@ -0,0 +1,14 @@ + +$ transform(p, x)[i] ~~> transform(p, x[transform(permInverse(p), i)]) + +find p : permutation (numMoved 3) of int(1..3) + +find x : matrix [int(1..3)] of bool +find y : matrix [int(1..3)] of bool + +such that y = transform(p, x) + + + +$ keeping some of the more interesting solutions only +such that sum([toInt(x[i]) | i : int(1..3)]) = 2 diff --git a/tests/custom/permutations/permInverse/04/run.sh b/tests/custom/permutations/permInverse/04/run.sh new file mode 100755 index 0000000000..3d015566f2 --- /dev/null +++ b/tests/custom/permutations/permInverse/04/run.sh @@ -0,0 +1,5 @@ + +rm -rf conjure-output +conjure solve *.essence --output-format=json --solutions-in-one-file --number-of-solutions=all --line-width=50 --copy-solutions=no +cat conjure-output/model000001.solutions.json +# rm -rf conjure-output diff --git a/tests/custom/permutations/permInverse/04/stdout.expected b/tests/custom/permutations/permInverse/04/stdout.expected new file mode 100644 index 0000000000..295a04654e --- /dev/null +++ b/tests/custom/permutations/permInverse/04/stdout.expected @@ -0,0 +1,31 @@ +Generating models for 04.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: conjure-output/model000001.eprime +Running minion for domain filtering. +Running solver: minion +[ +{"p": [[1, 2, 3]], + "x": {"1": false, "2": true, "3": true}, + "y": {"1": true, "2": false, "3": true}} +, +{"p": [[1, 2, 3]], + "x": {"1": true, "2": false, "3": true}, + "y": {"1": true, "2": true, "3": false}} +, +{"p": [[1, 2, 3]], + "x": {"1": true, "2": true, "3": false}, + "y": {"1": false, "2": true, "3": true}} +, +{"p": [[1, 3, 2]], + "x": {"1": false, "2": true, "3": true}, + "y": {"1": true, "2": true, "3": false}} +, +{"p": [[1, 3, 2]], + "x": {"1": true, "2": false, "3": true}, + "y": {"1": false, "2": true, "3": true}} +, +{"p": [[1, 3, 2]], + "x": {"1": true, "2": true, "3": false}, + "y": {"1": true, "2": false, "3": true}} +] From 05e87c1fca7f0838a1fea07e4e9bd0ba80a736bb Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?=C3=96zg=C3=BCr=20Akg=C3=BCn?= Date: Thu, 7 Nov 2024 10:45:27 +0000 Subject: [PATCH 187/229] example 05 --- .../custom/permutations/permInverse/04/run.sh | 2 +- .../permutations/permInverse/05/05.essence | 14 +++++++ .../custom/permutations/permInverse/05/run.sh | 5 +++ .../permInverse/05/stdout.expected | 37 +++++++++++++++++++ 4 files changed, 57 insertions(+), 1 deletion(-) create mode 100644 tests/custom/permutations/permInverse/05/05.essence create mode 100755 tests/custom/permutations/permInverse/05/run.sh create mode 100644 tests/custom/permutations/permInverse/05/stdout.expected diff --git a/tests/custom/permutations/permInverse/04/run.sh b/tests/custom/permutations/permInverse/04/run.sh index 3d015566f2..6c6476a122 100755 --- a/tests/custom/permutations/permInverse/04/run.sh +++ b/tests/custom/permutations/permInverse/04/run.sh @@ -2,4 +2,4 @@ rm -rf conjure-output conjure solve *.essence --output-format=json --solutions-in-one-file --number-of-solutions=all --line-width=50 --copy-solutions=no cat conjure-output/model000001.solutions.json -# rm -rf conjure-output +rm -rf conjure-output diff --git a/tests/custom/permutations/permInverse/05/05.essence b/tests/custom/permutations/permInverse/05/05.essence new file mode 100644 index 0000000000..f5bb432a35 --- /dev/null +++ b/tests/custom/permutations/permInverse/05/05.essence @@ -0,0 +1,14 @@ + +letting A be new type of size 3 + +find p : permutation (numMoved 3) of A + +find x : matrix [A] of bool +find y : matrix [A] of bool + +such that y = transform(p, x) + + + +$ keeping some of the more interesting solutions only +such that sum([toInt(x[i]) | i : A]) = 2 diff --git a/tests/custom/permutations/permInverse/05/run.sh b/tests/custom/permutations/permInverse/05/run.sh new file mode 100755 index 0000000000..6c6476a122 --- /dev/null +++ b/tests/custom/permutations/permInverse/05/run.sh @@ -0,0 +1,5 @@ + +rm -rf conjure-output +conjure solve *.essence --output-format=json --solutions-in-one-file --number-of-solutions=all --line-width=50 --copy-solutions=no +cat conjure-output/model000001.solutions.json +rm -rf conjure-output diff --git a/tests/custom/permutations/permInverse/05/stdout.expected b/tests/custom/permutations/permInverse/05/stdout.expected new file mode 100644 index 0000000000..a26641178e --- /dev/null +++ b/tests/custom/permutations/permInverse/05/stdout.expected @@ -0,0 +1,37 @@ +Generating models for 05.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: conjure-output/model000001.eprime +Running minion for domain filtering. +Running solver: minion +[ +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2", "A_3"]], + "x": {"1": false, "2": true, "3": true}, + "y": {"1": true, "2": false, "3": true}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2", "A_3"]], + "x": {"1": true, "2": false, "3": true}, + "y": {"1": true, "2": true, "3": false}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2", "A_3"]], + "x": {"1": true, "2": true, "3": false}, + "y": {"1": false, "2": true, "3": true}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3", "A_2"]], + "x": {"1": false, "2": true, "3": true}, + "y": {"1": true, "2": true, "3": false}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3", "A_2"]], + "x": {"1": true, "2": false, "3": true}, + "y": {"1": false, "2": true, "3": true}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3", "A_2"]], + "x": {"1": true, "2": true, "3": false}, + "y": {"1": true, "2": false, "3": true}} +] From 29750e8aee2afb43a2a78a56e6b52d4dccb78324 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?=C3=96zg=C3=BCr=20Akg=C3=BCn?= Date: Fri, 15 Nov 2024 11:16:25 +0000 Subject: [PATCH 188/229] tidy --- src/Conjure/Representations.hs | 1 - src/Conjure/Representations/MSet/ExplicitWithRepetition.hs | 4 ++-- 2 files changed, 2 insertions(+), 3 deletions(-) diff --git a/src/Conjure/Representations.hs b/src/Conjure/Representations.hs index 41de7fada9..45effc0861 100644 --- a/src/Conjure/Representations.hs +++ b/src/Conjure/Representations.hs @@ -191,7 +191,6 @@ symmetryOrdering inp' = do Op op -> case op of MkOpIndexing (OpIndexing m _) -> do - ty <- typeOf m case ty of TypeMatrix{} -> return () diff --git a/src/Conjure/Representations/MSet/ExplicitWithRepetition.hs b/src/Conjure/Representations/MSet/ExplicitWithRepetition.hs index 6a19367351..1b5689cbcf 100644 --- a/src/Conjure/Representations/MSet/ExplicitWithRepetition.hs +++ b/src/Conjure/Representations/MSet/ExplicitWithRepetition.hs @@ -73,14 +73,14 @@ msetExplicitWithRepetition = Representation chck downD structuralCons downC up s let orderingUpToFlag flag values = do (iPat, i) <- quantifiedVar - return $ return $ -- list + return $ return -- list [essence| forAll &iPat : int(1..&maxIndex-1) , &i+1 <= &flag . &values[&i] .<= &values[&i+1] |] dontCareAfterFlag flag values = do (iPat, i) <- quantifiedVar - return $ return $ -- list + return $ return -- list [essence| forAll &iPat : int(1..&maxIndex) , &i > &flag . dontCare(&values[&i]) |] From ead0a564eaa70e8c420d3d34c7e2e9383f396ef9 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?=C3=96zg=C3=BCr=20Akg=C3=BCn?= Date: Sat, 16 Nov 2024 13:36:31 +0000 Subject: [PATCH 189/229] do not panic, just mark rule as not applicable --- src/Conjure/Representations.hs | 20 ++++++++++---------- 1 file changed, 10 insertions(+), 10 deletions(-) diff --git a/src/Conjure/Representations.hs b/src/Conjure/Representations.hs index 45effc0861..5496f29bc7 100644 --- a/src/Conjure/Representations.hs +++ b/src/Conjure/Representations.hs @@ -168,7 +168,7 @@ symmetryOrdering inp' = do AbsLitMatrix _ xs -> do soVals <- mapM symmetryOrdering (Constant <$> xs) return $ fromList soVals - _ -> bug ("symmetryOrdering: AbstractLiteral:" <++> pretty (show inp) <++> pretty inp) + _ -> na ("symmetryOrdering: AbstractLiteral:" <++> pretty (show inp) <++> pretty inp) AbstractLiteral x -> do case x of @@ -178,16 +178,16 @@ symmetryOrdering inp' = do AbsLitMatrix d xs -> do soVals <- mapM symmetryOrdering xs return $ AbstractLiteral $ AbsLitMatrix d soVals - _ -> bug ("symmetryOrdering: AbstractLiteral:" <++> pretty (show inp) <++> pretty inp) + _ -> na ("symmetryOrdering: AbstractLiteral:" <++> pretty (show inp) <++> pretty inp) Reference _ (Just refTo) -> do case refTo of Alias x -> symmetryOrdering x - InComprehension{} -> bug ("symmetryOrdering.InComprehension:" <++> pretty (show inp)) - DeclNoRepr{} -> bug ("symmetryOrdering.DeclNoRepr:" <++> pretty (show inp)) + InComprehension{} -> na ("symmetryOrdering.InComprehension:" <++> pretty (show inp)) + DeclNoRepr{} -> na ("symmetryOrdering.DeclNoRepr:" <++> pretty (show inp)) DeclHasRepr _forg _name domain -> symmetryOrderingDispatch downX1 inp domain - RecordField{} -> bug ("symmetryOrdering.RecordField:" <++> pretty (show inp)) - VariantField{} -> bug ("symmetryOrdering.VariantField:" <++> pretty (show inp)) + RecordField{} -> na ("symmetryOrdering.RecordField:" <++> pretty (show inp)) + VariantField{} -> na ("symmetryOrdering.VariantField:" <++> pretty (show inp)) Op op -> case op of MkOpIndexing (OpIndexing m _) -> do @@ -195,18 +195,18 @@ symmetryOrdering inp' = do case ty of TypeMatrix{} -> return () TypeList{} -> return () - _ -> bug $ "[symmetryOrdering.onOp, not a TypeMatrix or TypeList]" <+> vcat [pretty ty, pretty op] + _ -> na $ "[symmetryOrdering.onOp, not a TypeMatrix or TypeList]" <+> vcat [pretty ty, pretty op] mDom <- domainOfR m case mDom of DomainMatrix _ domainInner -> symmetryOrderingDispatch downX1 inp domainInner - _ -> bug ("symmetryOrdering, not DomainMatrix:" <++> pretty (show op)) + _ -> na ("symmetryOrdering, not DomainMatrix:" <++> pretty (show op)) MkOpImage (OpImage p x) -> do so <- symmetryOrdering x return [essence| image(&p, &so) |] - _ -> bug ("symmetryOrdering, no OpIndexing:" <++> pretty (show op)) + _ -> na ("symmetryOrdering, no OpIndexing:" <++> pretty (show op)) Comprehension body stmts -> do xs <- symmetryOrdering body return $ make opFlatten $ Comprehension xs stmts - _ -> bug ("symmetryOrdering:" <++> pretty (show inp) <++> pretty inp) + _ -> na ("symmetryOrdering:" <++> pretty (show inp) <++> pretty inp) From 3539b91421b907da3b0dff5cd852682583e084eb Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?=C3=96zg=C3=BCr=20Akg=C3=BCn?= Date: Sat, 16 Nov 2024 13:37:09 +0000 Subject: [PATCH 190/229] specialised handling of .<= when one of the args is transformed --- src/Conjure/Rules/Vertical/Tuple.hs | 21 +++++++++++++++++++-- src/Conjure/UI/Model.hs | 1 + 2 files changed, 20 insertions(+), 2 deletions(-) diff --git a/src/Conjure/Rules/Vertical/Tuple.hs b/src/Conjure/Rules/Vertical/Tuple.hs index c18edce74a..72454c741e 100644 --- a/src/Conjure/Rules/Vertical/Tuple.hs +++ b/src/Conjure/Rules/Vertical/Tuple.hs @@ -70,7 +70,7 @@ rule_Tuple_TildeLt = "tuple-TildeLt" `namedRule` theRule where xs <- downX1 x ys <- downX1 y return - ( "Horizontal rule for tuple .<" + ( "Horizontal rule for tuple ~<" , return $ decomposeLexTildeLt p xs ys ) @@ -84,11 +84,28 @@ rule_Tuple_TildeLeq = "tuple-TildeLeq" `namedRule` theRule where xs <- downX1 x ys <- downX1 y return - ( "Horizontal rule for tuple .<=" + ( "Horizontal rule for tuple ~<=" , return $ decomposeLexTildeLeq p xs ys ) +-- .<= that contains a trainsform in it cannot be handled by the general symmetryOrdering-based rule +rule_Tuple_DotLeq :: Rule +rule_Tuple_DotLeq = "tuple-DotLeq" `namedRule` theRule where + theRule p = do + (x,y) <- match opDotLeq p + TypeTuple{} <- typeOf x -- TODO: check if x and y have the same arity + TypeTuple{} <- typeOf y + let containsTransform = [ () | Op (MkOpTransform{}) <- universe p ] + when (null containsTransform) $ na "rule_Tuple_DotLeq" + xs <- downX1 x + ys <- downX1 y + return + ( "Horizontal rule for tuple .<=" + , return $ decomposeLexDotLeq p xs ys + ) + + decomposeLexLexLt :: Expression -> [Expression] -> [Expression] -> Expression decomposeLexLexLt p = unroll where diff --git a/src/Conjure/UI/Model.hs b/src/Conjure/UI/Model.hs index de6b34cb64..f25549ee1e 100644 --- a/src/Conjure/UI/Model.hs +++ b/src/Conjure/UI/Model.hs @@ -1421,6 +1421,7 @@ verticalRules = , Vertical.Tuple.rule_Tuple_Lt , Vertical.Tuple.rule_Tuple_TildeLeq , Vertical.Tuple.rule_Tuple_TildeLt + , Vertical.Tuple.rule_Tuple_DotLeq , Vertical.Tuple.rule_Tuple_Index From 5390ba1e65927be7dbdb94cccd2c4a26d76f49d6 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?=C3=96zg=C3=BCr=20Akg=C3=BCn?= Date: Sat, 16 Nov 2024 13:37:40 +0000 Subject: [PATCH 191/229] transform .<= of transforms --- src/Conjure/Rules/Transform.hs | 17 ++++++++++++++++- 1 file changed, 16 insertions(+), 1 deletion(-) diff --git a/src/Conjure/Rules/Transform.hs b/src/Conjure/Rules/Transform.hs index 27986f2d38..7ee9812224 100644 --- a/src/Conjure/Rules/Transform.hs +++ b/src/Conjure/Rules/Transform.hs @@ -7,7 +7,8 @@ import Conjure.Rules.Vertical.Variant (onTagged) rules_Transform :: [Rule] rules_Transform = - [ rule_Transform_Sequence_Literal, + [ rule_Transform_DotLess, + rule_Transform_Sequence_Literal, rule_Transform_Functorially, rule_Transform_Comprehension, rule_Transform_Product_Types, @@ -28,6 +29,20 @@ rules_Transform = rule_Transformed_Variant_Active ] +rule_Transform_DotLess :: Rule +rule_Transform_DotLess = "transform-dotless" `namedRule` theRule + where + theRule [essence| &x .<= transform(&p, &y) |] | x == y = do + TypeMatrix {} <- typeOf x + (xInd : _) <- indexDomainsOf x + return + ( "", + do + (iPat, i) <- quantifiedVar + return [essence| &x .<= [ transform(&p, &x[transform(permInverse(&p), &i)]) | &iPat : &xInd ] |] + ) + theRule _ = na "rule_Transform_DotLess" + rule_Transform_Functorially :: Rule rule_Transform_Functorially = "transform-functorially" `namedRule` theRule where From b75663868fac0811b0125823a55f6e58f12ba86b Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?=C3=96zg=C3=BCr=20Akg=C3=BCn?= Date: Sat, 16 Nov 2024 13:37:46 +0000 Subject: [PATCH 192/229] lint --- src/Conjure/Rules/Transform.hs | 37 ++++++++++++++++------------------ 1 file changed, 17 insertions(+), 20 deletions(-) diff --git a/src/Conjure/Rules/Transform.hs b/src/Conjure/Rules/Transform.hs index 7ee9812224..b0f3df667d 100644 --- a/src/Conjure/Rules/Transform.hs +++ b/src/Conjure/Rules/Transform.hs @@ -86,7 +86,7 @@ rule_Transform_Comprehension = "transform-comprehension" `namedRule` theRule return ( "Horizontal rule for transform comprehension", do - gox <- sequence (transformOverGenOrCond morphism <$> gensOrConds) + gox <- mapM (transformOverGenOrCond morphism) gensOrConds return $ Comprehension [essence| transform(&morphism, &body) |] @@ -110,33 +110,33 @@ rule_Transform_Comprehension = "transform-comprehension" `namedRule` theRule transformOverGenerator m (GenDomainNoRepr absPat d) = do (rPat, ns) <- clonePattern absPat return - $ [Generator (GenDomainNoRepr rPat d)] - ++ ( ( \(pat, exp) -> - ComprehensionLetting (Single pat) [essence| transform(&m,&exp) |] - ) - <$> ns - ) + $ Generator (GenDomainNoRepr rPat d) + : ( ( \(pat, exp) -> + ComprehensionLetting (Single pat) [essence| transform(&m,&exp) |] + ) + <$> ns + ) clonePattern (Single name) = do (nPat, n) <- quantifiedVar return (nPat, [(name, n)]) clonePattern (AbsPatTuple pats) = do - rec <- sequence (clonePattern <$> pats) + rec <- mapM clonePattern pats return ( AbsPatTuple $ fst <$> rec, - join $ snd <$> rec + snd =<< rec ) clonePattern (AbsPatMatrix pats) = do - rec <- sequence (clonePattern <$> pats) + rec <- mapM clonePattern pats return ( AbsPatMatrix $ fst <$> rec, - join $ snd <$> rec + snd =<< rec ) clonePattern (AbsPatSet pats) = do - rec <- sequence (clonePattern <$> pats) + rec <- mapM clonePattern pats return ( AbsPatSet $ fst <$> rec, - join $ snd <$> rec + snd =<< rec ) clonePattern _ = bug "rule_Transform_Comprehension: clonePattern: unsupported Abstract Pattern" @@ -155,8 +155,7 @@ rule_Transform_Product_Types = "transform-product-types" `namedRule` theRule in [essence| transform(&morphism, &i[&indexexpr]) |] tupleExpression = AbstractLiteral - $ AbsLitTuple - $ (tupleIndexTransform <$> [1 .. (fromIntegral $ length tint)]) + $ AbsLitTuple (tupleIndexTransform <$> [1 .. (fromIntegral $ length tint)]) return ( "Horizontal rule for transform of tuple", return tupleExpression @@ -263,11 +262,9 @@ rule_Transform_Sequence = "transform-sequence" `namedRule` theRule ( Comprehension body $ gocBefore ++ [Generator (GenInExpr dPat y)] - ++ ( ( ComprehensionLetting - (Single pat) - [essence| - (&d[1], transform(&morphism, &d[2])) |] - ) + ++ ( ComprehensionLetting + (Single pat) + [essence| (&d[1], transform(&morphism, &d[2])) |] : gocAfter ) ) From 75e6aabcad1e607709d19cad877eb85dfae0907e Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?=C3=96zg=C3=BCr=20Akg=C3=BCn?= Date: Sat, 16 Nov 2024 13:38:00 +0000 Subject: [PATCH 193/229] test case --- .../permutations/permInverse/06/06.essence | 16 ++++++++++++++++ tests/custom/permutations/permInverse/06/run.sh | 5 +++++ .../permutations/permInverse/06/stderr.expected | 4 ++++ .../permutations/permInverse/06/stdout.expected | 10 ++++++++++ 4 files changed, 35 insertions(+) create mode 100644 tests/custom/permutations/permInverse/06/06.essence create mode 100755 tests/custom/permutations/permInverse/06/run.sh create mode 100644 tests/custom/permutations/permInverse/06/stderr.expected create mode 100644 tests/custom/permutations/permInverse/06/stdout.expected diff --git a/tests/custom/permutations/permInverse/06/06.essence b/tests/custom/permutations/permInverse/06/06.essence new file mode 100644 index 0000000000..0294799884 --- /dev/null +++ b/tests/custom/permutations/permInverse/06/06.essence @@ -0,0 +1,16 @@ + +letting A be new type of size 3 + +find x : matrix [A] of bool + +$ keeping some of the more interesting solutions only +such that sum([toInt(x[i]) | i : A]) = 2 + + + + +$ such that +$ and([tuple (x) .<= transform(q1, tuple (x)) +$ | q1 : permutation of A]) + + diff --git a/tests/custom/permutations/permInverse/06/run.sh b/tests/custom/permutations/permInverse/06/run.sh new file mode 100755 index 0000000000..d2c1c1f208 --- /dev/null +++ b/tests/custom/permutations/permInverse/06/run.sh @@ -0,0 +1,5 @@ + +rm -rf conjure-output +conjure solve *.essence --output-format=json --solutions-in-one-file --number-of-solutions=all --line-width=50 --copy-solutions=no --unnamed-symmetry-breaking=full +cat conjure-output/model000001.solutions.json +rm -rf conjure-output diff --git a/tests/custom/permutations/permInverse/06/stderr.expected b/tests/custom/permutations/permInverse/06/stderr.expected new file mode 100644 index 0000000000..c975823c74 --- /dev/null +++ b/tests/custom/permutations/permInverse/06/stderr.expected @@ -0,0 +1,4 @@ +Adding the following unnamed symmetry breaking constraints: + such that + and([tuple (x) .<= transform(q1, tuple (x)) + | q1 : permutation of A]) diff --git a/tests/custom/permutations/permInverse/06/stdout.expected b/tests/custom/permutations/permInverse/06/stdout.expected new file mode 100644 index 0000000000..8c1d7b49f8 --- /dev/null +++ b/tests/custom/permutations/permInverse/06/stdout.expected @@ -0,0 +1,10 @@ +Generating models for 06.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: conjure-output/model000001.eprime +Running minion for domain filtering. +Running solver: minion +[ +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": true, "2": true, "3": false}} +] From 0d90a86f23e8b3676fbb868a47b2841f72e2304e Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?=C3=96zg=C3=BCr=20Akg=C3=BCn?= Date: Sat, 16 Nov 2024 13:50:19 +0000 Subject: [PATCH 194/229] rename test files --- .../permInverse/01/{01.essence => 00.essence} | 0 .../permutations/permInverse/01/stdout.expected | 2 +- .../permInverse/02/{02.essence => 00.essence} | 0 .../permutations/permInverse/02/stdout.expected | 2 +- .../permInverse/03/{03.essence => 00.essence} | 0 .../permutations/permInverse/03/stdout.expected | 2 +- .../permInverse/04/{04.essence => 00.essence} | 0 .../permutations/permInverse/04/stdout.expected | 2 +- .../permInverse/05/{05.essence => 00.essence} | 0 .../permutations/permInverse/05/stdout.expected | 2 +- .../permutations/permInverse/06/00.essence | 2 ++ .../permutations/permInverse/06/06.essence | 16 ---------------- .../permutations/permInverse/06/stdout.expected | 11 ++++++++++- .../permutations/permInverse/07/00.essence | 2 ++ tests/custom/permutations/permInverse/07/run.sh | 5 +++++ .../permutations/permInverse/07/stderr.expected | 4 ++++ .../permutations/permInverse/07/stdout.expected | 13 +++++++++++++ 17 files changed, 41 insertions(+), 22 deletions(-) rename tests/custom/permutations/permInverse/01/{01.essence => 00.essence} (100%) rename tests/custom/permutations/permInverse/02/{02.essence => 00.essence} (100%) rename tests/custom/permutations/permInverse/03/{03.essence => 00.essence} (100%) rename tests/custom/permutations/permInverse/04/{04.essence => 00.essence} (100%) rename tests/custom/permutations/permInverse/05/{05.essence => 00.essence} (100%) create mode 100644 tests/custom/permutations/permInverse/06/00.essence delete mode 100644 tests/custom/permutations/permInverse/06/06.essence create mode 100644 tests/custom/permutations/permInverse/07/00.essence create mode 100755 tests/custom/permutations/permInverse/07/run.sh create mode 100644 tests/custom/permutations/permInverse/07/stderr.expected create mode 100644 tests/custom/permutations/permInverse/07/stdout.expected diff --git a/tests/custom/permutations/permInverse/01/01.essence b/tests/custom/permutations/permInverse/01/00.essence similarity index 100% rename from tests/custom/permutations/permInverse/01/01.essence rename to tests/custom/permutations/permInverse/01/00.essence diff --git a/tests/custom/permutations/permInverse/01/stdout.expected b/tests/custom/permutations/permInverse/01/stdout.expected index 34ebdb860a..a378f7e980 100644 --- a/tests/custom/permutations/permInverse/01/stdout.expected +++ b/tests/custom/permutations/permInverse/01/stdout.expected @@ -1,4 +1,4 @@ -Generating models for 01.essence +Generating models for 00.essence Generated models: model000001.eprime Saved under: conjure-output Savile Row: conjure-output/model000001.eprime diff --git a/tests/custom/permutations/permInverse/02/02.essence b/tests/custom/permutations/permInverse/02/00.essence similarity index 100% rename from tests/custom/permutations/permInverse/02/02.essence rename to tests/custom/permutations/permInverse/02/00.essence diff --git a/tests/custom/permutations/permInverse/02/stdout.expected b/tests/custom/permutations/permInverse/02/stdout.expected index b26488802c..a492c657fe 100644 --- a/tests/custom/permutations/permInverse/02/stdout.expected +++ b/tests/custom/permutations/permInverse/02/stdout.expected @@ -1,4 +1,4 @@ -Generating models for 02.essence +Generating models for 00.essence Generated models: model000001.eprime Saved under: conjure-output Savile Row: conjure-output/model000001.eprime diff --git a/tests/custom/permutations/permInverse/03/03.essence b/tests/custom/permutations/permInverse/03/00.essence similarity index 100% rename from tests/custom/permutations/permInverse/03/03.essence rename to tests/custom/permutations/permInverse/03/00.essence diff --git a/tests/custom/permutations/permInverse/03/stdout.expected b/tests/custom/permutations/permInverse/03/stdout.expected index 534b4821e8..fa02e72c0e 100644 --- a/tests/custom/permutations/permInverse/03/stdout.expected +++ b/tests/custom/permutations/permInverse/03/stdout.expected @@ -1,4 +1,4 @@ -Generating models for 03.essence +Generating models for 00.essence Generated models: model000001.eprime Saved under: conjure-output Savile Row: conjure-output/model000001.eprime diff --git a/tests/custom/permutations/permInverse/04/04.essence b/tests/custom/permutations/permInverse/04/00.essence similarity index 100% rename from tests/custom/permutations/permInverse/04/04.essence rename to tests/custom/permutations/permInverse/04/00.essence diff --git a/tests/custom/permutations/permInverse/04/stdout.expected b/tests/custom/permutations/permInverse/04/stdout.expected index 295a04654e..dcf32f45e4 100644 --- a/tests/custom/permutations/permInverse/04/stdout.expected +++ b/tests/custom/permutations/permInverse/04/stdout.expected @@ -1,4 +1,4 @@ -Generating models for 04.essence +Generating models for 00.essence Generated models: model000001.eprime Saved under: conjure-output Savile Row: conjure-output/model000001.eprime diff --git a/tests/custom/permutations/permInverse/05/05.essence b/tests/custom/permutations/permInverse/05/00.essence similarity index 100% rename from tests/custom/permutations/permInverse/05/05.essence rename to tests/custom/permutations/permInverse/05/00.essence diff --git a/tests/custom/permutations/permInverse/05/stdout.expected b/tests/custom/permutations/permInverse/05/stdout.expected index a26641178e..79b1262bbb 100644 --- a/tests/custom/permutations/permInverse/05/stdout.expected +++ b/tests/custom/permutations/permInverse/05/stdout.expected @@ -1,4 +1,4 @@ -Generating models for 05.essence +Generating models for 00.essence Generated models: model000001.eprime Saved under: conjure-output Savile Row: conjure-output/model000001.eprime diff --git a/tests/custom/permutations/permInverse/06/00.essence b/tests/custom/permutations/permInverse/06/00.essence new file mode 100644 index 0000000000..cddb403e1d --- /dev/null +++ b/tests/custom/permutations/permInverse/06/00.essence @@ -0,0 +1,2 @@ +letting A be new type of size 3 +find x : matrix [A] of bool diff --git a/tests/custom/permutations/permInverse/06/06.essence b/tests/custom/permutations/permInverse/06/06.essence deleted file mode 100644 index 0294799884..0000000000 --- a/tests/custom/permutations/permInverse/06/06.essence +++ /dev/null @@ -1,16 +0,0 @@ - -letting A be new type of size 3 - -find x : matrix [A] of bool - -$ keeping some of the more interesting solutions only -such that sum([toInt(x[i]) | i : A]) = 2 - - - - -$ such that -$ and([tuple (x) .<= transform(q1, tuple (x)) -$ | q1 : permutation of A]) - - diff --git a/tests/custom/permutations/permInverse/06/stdout.expected b/tests/custom/permutations/permInverse/06/stdout.expected index 8c1d7b49f8..904671d4bb 100644 --- a/tests/custom/permutations/permInverse/06/stdout.expected +++ b/tests/custom/permutations/permInverse/06/stdout.expected @@ -1,10 +1,19 @@ -Generating models for 06.essence +Generating models for 00.essence Generated models: model000001.eprime Saved under: conjure-output Savile Row: conjure-output/model000001.eprime Running minion for domain filtering. Running solver: minion [ +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": false, "2": false, "3": false}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": true, "2": false, "3": false}} +, {"A": ["A_1", "A_2", "A_3"], "x": {"1": true, "2": true, "3": false}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": true, "2": true, "3": true}} ] diff --git a/tests/custom/permutations/permInverse/07/00.essence b/tests/custom/permutations/permInverse/07/00.essence new file mode 100644 index 0000000000..074e0fcdb3 --- /dev/null +++ b/tests/custom/permutations/permInverse/07/00.essence @@ -0,0 +1,2 @@ +letting A be new type of size 3 +find x : matrix [int(1..2)] of A diff --git a/tests/custom/permutations/permInverse/07/run.sh b/tests/custom/permutations/permInverse/07/run.sh new file mode 100755 index 0000000000..d2c1c1f208 --- /dev/null +++ b/tests/custom/permutations/permInverse/07/run.sh @@ -0,0 +1,5 @@ + +rm -rf conjure-output +conjure solve *.essence --output-format=json --solutions-in-one-file --number-of-solutions=all --line-width=50 --copy-solutions=no --unnamed-symmetry-breaking=full +cat conjure-output/model000001.solutions.json +rm -rf conjure-output diff --git a/tests/custom/permutations/permInverse/07/stderr.expected b/tests/custom/permutations/permInverse/07/stderr.expected new file mode 100644 index 0000000000..c975823c74 --- /dev/null +++ b/tests/custom/permutations/permInverse/07/stderr.expected @@ -0,0 +1,4 @@ +Adding the following unnamed symmetry breaking constraints: + such that + and([tuple (x) .<= transform(q1, tuple (x)) + | q1 : permutation of A]) diff --git a/tests/custom/permutations/permInverse/07/stdout.expected b/tests/custom/permutations/permInverse/07/stdout.expected new file mode 100644 index 0000000000..0194a5852e --- /dev/null +++ b/tests/custom/permutations/permInverse/07/stdout.expected @@ -0,0 +1,13 @@ +Generating models for 00.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: conjure-output/model000001.eprime +Running minion for domain filtering. +Running solver: minion +[ +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}} +] From 024e4c5bfe39ea5ee68f4c50eaacd7da47fabbaf Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?=C3=96zg=C3=BCr=20Akg=C3=BCn?= Date: Fri, 22 Nov 2024 10:08:29 +0000 Subject: [PATCH 195/229] handle .< too --- src/Conjure/Rules/Transform.hs | 9 + .../permutations/permInverse/08/00.essence | 6 + .../custom/permutations/permInverse/08/run.sh | 5 + .../permInverse/08/stdout.expected | 4024 +++++++++++++++++ .../permutations/permInverse/09/00.essence | 3 + .../custom/permutations/permInverse/09/run.sh | 5 + .../permInverse/09/stderr.expected | 3 + .../permInverse/09/stdout.expected | 171 + 8 files changed, 4226 insertions(+) create mode 100644 tests/custom/permutations/permInverse/08/00.essence create mode 100755 tests/custom/permutations/permInverse/08/run.sh create mode 100644 tests/custom/permutations/permInverse/08/stdout.expected create mode 100644 tests/custom/permutations/permInverse/09/00.essence create mode 100755 tests/custom/permutations/permInverse/09/run.sh create mode 100644 tests/custom/permutations/permInverse/09/stderr.expected create mode 100644 tests/custom/permutations/permInverse/09/stdout.expected diff --git a/src/Conjure/Rules/Transform.hs b/src/Conjure/Rules/Transform.hs index b0f3df667d..cf396a5078 100644 --- a/src/Conjure/Rules/Transform.hs +++ b/src/Conjure/Rules/Transform.hs @@ -41,6 +41,15 @@ rule_Transform_DotLess = "transform-dotless" `namedRule` theRule (iPat, i) <- quantifiedVar return [essence| &x .<= [ transform(&p, &x[transform(permInverse(&p), &i)]) | &iPat : &xInd ] |] ) + theRule [essence| &x .< transform(&p, &y) |] | x == y = do + TypeMatrix {} <- typeOf x + (xInd : _) <- indexDomainsOf x + return + ( "", + do + (iPat, i) <- quantifiedVar + return [essence| &x .< [ transform(&p, &x[transform(permInverse(&p), &i)]) | &iPat : &xInd ] |] + ) theRule _ = na "rule_Transform_DotLess" rule_Transform_Functorially :: Rule diff --git a/tests/custom/permutations/permInverse/08/00.essence b/tests/custom/permutations/permInverse/08/00.essence new file mode 100644 index 0000000000..526257236b --- /dev/null +++ b/tests/custom/permutations/permInverse/08/00.essence @@ -0,0 +1,6 @@ +letting A be new type of size 3 +find x : matrix [int(1..2)] of A +find y : matrix [int(1..3)] of A + +find p : permutation of A +such that (x, y) .<= transform(p, (x, y)) diff --git a/tests/custom/permutations/permInverse/08/run.sh b/tests/custom/permutations/permInverse/08/run.sh new file mode 100755 index 0000000000..6c6476a122 --- /dev/null +++ b/tests/custom/permutations/permInverse/08/run.sh @@ -0,0 +1,5 @@ + +rm -rf conjure-output +conjure solve *.essence --output-format=json --solutions-in-one-file --number-of-solutions=all --line-width=50 --copy-solutions=no +cat conjure-output/model000001.solutions.json +rm -rf conjure-output diff --git a/tests/custom/permutations/permInverse/08/stdout.expected b/tests/custom/permutations/permInverse/08/stdout.expected new file mode 100644 index 0000000000..812474e1e0 --- /dev/null +++ b/tests/custom/permutations/permInverse/08/stdout.expected @@ -0,0 +1,4024 @@ +Generating models for 00.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: conjure-output/model000001.eprime +Running minion for domain filtering. +Running solver: minion +[ +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_2", "A_3"]], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2"]], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2", "A_3"]], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3", "A_2"]], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3"]], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_2", "A_3"]], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2"]], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2", "A_3"]], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3", "A_2"]], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3"]], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2"]], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2", "A_3"]], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3", "A_2"]], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3"]], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_2", "A_3"]], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2"]], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2", "A_3"]], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3", "A_2"]], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3"]], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_2", "A_3"]], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2"]], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2", "A_3"]], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3", "A_2"]], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3"]], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_2", "A_3"]], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2"]], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2", "A_3"]], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3", "A_2"]], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3"]], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2"]], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2", "A_3"]], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3", "A_2"]], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3"]], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2"]], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2", "A_3"]], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3", "A_2"]], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3"]], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2"]], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2", "A_3"]], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3", "A_2"]], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3"]], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_2", "A_3"]], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2"]], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2", "A_3"]], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3", "A_2"]], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3"]], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_2", "A_3"]], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2"]], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2", "A_3"]], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3", "A_2"]], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3"]], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_2", "A_3"]], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2"]], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2", "A_3"]], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3", "A_2"]], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3"]], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_2", "A_3"]], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2"]], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2", "A_3"]], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3", "A_2"]], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3"]], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_2", "A_3"]], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2"]], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2", "A_3"]], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3", "A_2"]], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3"]], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_2", "A_3"]], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2"]], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2", "A_3"]], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3", "A_2"]], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3"]], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_2", "A_3"]], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2"]], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2", "A_3"]], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3", "A_2"]], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3"]], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_2", "A_3"]], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2"]], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2", "A_3"]], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3", "A_2"]], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3"]], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_2", "A_3"]], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2"]], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2", "A_3"]], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3", "A_2"]], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3"]], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_3", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2"]], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_3", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2", "A_3"]], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_3", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3", "A_2"]], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_3", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3"]], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_3", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_3", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2"]], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_3", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2", "A_3"]], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_3", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3", "A_2"]], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_3", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3"]], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_3", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_3", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2"]], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_3", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2", "A_3"]], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_3", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3", "A_2"]], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_3", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3"]], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_3", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_3", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2"]], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_3", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2", "A_3"]], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_3", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3", "A_2"]], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_3", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3"]], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_3", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_3", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2"]], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_3", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2", "A_3"]], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_3", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3", "A_2"]], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_3", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3"]], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_3", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_3", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2"]], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_3", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2", "A_3"]], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_3", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3", "A_2"]], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_3", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3"]], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_3", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_3", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2"]], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_3", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2", "A_3"]], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_3", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3", "A_2"]], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_3", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3"]], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_3", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_3", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2"]], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_3", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2", "A_3"]], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_3", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3", "A_2"]], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_3", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3"]], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_3", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_3", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2"]], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_3", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2", "A_3"]], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_3", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3", "A_2"]], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_3", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3"]], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_3", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_2", "A_3"]], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2"]], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2", "A_3"]], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3", "A_2"]], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3"]], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_2", "A_3"]], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2"]], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2", "A_3"]], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3", "A_2"]], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3"]], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_2", "A_3"]], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2"]], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2", "A_3"]], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3", "A_2"]], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3"]], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_2", "A_3"]], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2"]], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2", "A_3"]], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3", "A_2"]], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3"]], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_2", "A_3"]], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2"]], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2", "A_3"]], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3", "A_2"]], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3"]], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_2", "A_3"]], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2"]], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2", "A_3"]], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3", "A_2"]], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3"]], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_2", "A_3"]], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2"]], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2", "A_3"]], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3", "A_2"]], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3"]], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_2", "A_3"]], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2"]], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2", "A_3"]], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3", "A_2"]], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3"]], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_2", "A_3"]], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2"]], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2", "A_3"]], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3", "A_2"]], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3"]], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_2", "A_3"]], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2"]], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2", "A_3"]], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3", "A_2"]], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3"]], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_2", "A_3"]], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2"]], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2", "A_3"]], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3", "A_2"]], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3"]], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_2", "A_3"]], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2"]], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2", "A_3"]], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3", "A_2"]], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3"]], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_2", "A_3"]], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2"]], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2", "A_3"]], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3", "A_2"]], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3"]], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_2", "A_3"]], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2"]], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2", "A_3"]], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3", "A_2"]], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3"]], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_2", "A_3"]], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2"]], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2", "A_3"]], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3", "A_2"]], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3"]], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_2", "A_3"]], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2"]], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2", "A_3"]], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3", "A_2"]], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3"]], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_2", "A_3"]], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2"]], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2", "A_3"]], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3", "A_2"]], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3"]], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_2", "A_3"]], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2"]], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2", "A_3"]], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3", "A_2"]], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3"]], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_2", "A_3"]], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2"]], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2", "A_3"]], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3", "A_2"]], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3"]], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_2", "A_3"]], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2"]], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2", "A_3"]], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3", "A_2"]], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3"]], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_2", "A_3"]], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2"]], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2", "A_3"]], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3", "A_2"]], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3"]], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_2", "A_3"]], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2"]], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2", "A_3"]], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3", "A_2"]], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3"]], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_2", "A_3"]], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2"]], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2", "A_3"]], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3", "A_2"]], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3"]], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_2", "A_3"]], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2"]], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2", "A_3"]], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3", "A_2"]], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3"]], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_2", "A_3"]], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2"]], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2", "A_3"]], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3", "A_2"]], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3"]], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_2", "A_3"]], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2"]], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2", "A_3"]], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3", "A_2"]], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3"]], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_2", "A_3"]], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2"]], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2", "A_3"]], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3", "A_2"]], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3"]], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_1", "2": "A_3"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2"]], + "x": {"1": "A_1", "2": "A_3"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2", "A_3"]], + "x": {"1": "A_1", "2": "A_3"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3", "A_2"]], + "x": {"1": "A_1", "2": "A_3"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3"]], + "x": {"1": "A_1", "2": "A_3"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_1", "2": "A_3"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2"]], + "x": {"1": "A_1", "2": "A_3"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2", "A_3"]], + "x": {"1": "A_1", "2": "A_3"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3", "A_2"]], + "x": {"1": "A_1", "2": "A_3"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3"]], + "x": {"1": "A_1", "2": "A_3"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_1", "2": "A_3"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2"]], + "x": {"1": "A_1", "2": "A_3"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2", "A_3"]], + "x": {"1": "A_1", "2": "A_3"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3", "A_2"]], + "x": {"1": "A_1", "2": "A_3"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3"]], + "x": {"1": "A_1", "2": "A_3"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_1", "2": "A_3"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2"]], + "x": {"1": "A_1", "2": "A_3"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2", "A_3"]], + "x": {"1": "A_1", "2": "A_3"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3", "A_2"]], + "x": {"1": "A_1", "2": "A_3"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3"]], + "x": {"1": "A_1", "2": "A_3"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_1", "2": "A_3"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2"]], + "x": {"1": "A_1", "2": "A_3"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2", "A_3"]], + "x": {"1": "A_1", "2": "A_3"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3", "A_2"]], + "x": {"1": "A_1", "2": "A_3"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3"]], + "x": {"1": "A_1", "2": "A_3"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_1", "2": "A_3"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2"]], + "x": {"1": "A_1", "2": "A_3"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2", "A_3"]], + "x": {"1": "A_1", "2": "A_3"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3", "A_2"]], + "x": {"1": "A_1", "2": "A_3"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3"]], + "x": {"1": "A_1", "2": "A_3"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_1", "2": "A_3"}, + "y": {"1": "A_1", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2"]], + "x": {"1": "A_1", "2": "A_3"}, + "y": {"1": "A_1", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2", "A_3"]], + "x": {"1": "A_1", "2": "A_3"}, + "y": {"1": "A_1", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3", "A_2"]], + "x": {"1": "A_1", "2": "A_3"}, + "y": {"1": "A_1", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3"]], + "x": {"1": "A_1", "2": "A_3"}, + "y": {"1": "A_1", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_1", "2": "A_3"}, + "y": {"1": "A_1", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2"]], + "x": {"1": "A_1", "2": "A_3"}, + "y": {"1": "A_1", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2", "A_3"]], + "x": {"1": "A_1", "2": "A_3"}, + "y": {"1": "A_1", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3", "A_2"]], + "x": {"1": "A_1", "2": "A_3"}, + "y": {"1": "A_1", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3"]], + "x": {"1": "A_1", "2": "A_3"}, + "y": {"1": "A_1", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_1", "2": "A_3"}, + "y": {"1": "A_1", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2"]], + "x": {"1": "A_1", "2": "A_3"}, + "y": {"1": "A_1", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2", "A_3"]], + "x": {"1": "A_1", "2": "A_3"}, + "y": {"1": "A_1", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3", "A_2"]], + "x": {"1": "A_1", "2": "A_3"}, + "y": {"1": "A_1", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3"]], + "x": {"1": "A_1", "2": "A_3"}, + "y": {"1": "A_1", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_1", "2": "A_3"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2"]], + "x": {"1": "A_1", "2": "A_3"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2", "A_3"]], + "x": {"1": "A_1", "2": "A_3"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3", "A_2"]], + "x": {"1": "A_1", "2": "A_3"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3"]], + "x": {"1": "A_1", "2": "A_3"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_1", "2": "A_3"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2"]], + "x": {"1": "A_1", "2": "A_3"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2", "A_3"]], + "x": {"1": "A_1", "2": "A_3"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3", "A_2"]], + "x": {"1": "A_1", "2": "A_3"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3"]], + "x": {"1": "A_1", "2": "A_3"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_1", "2": "A_3"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2"]], + "x": {"1": "A_1", "2": "A_3"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2", "A_3"]], + "x": {"1": "A_1", "2": "A_3"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3", "A_2"]], + "x": {"1": "A_1", "2": "A_3"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3"]], + "x": {"1": "A_1", "2": "A_3"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_1", "2": "A_3"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2"]], + "x": {"1": "A_1", "2": "A_3"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2", "A_3"]], + "x": {"1": "A_1", "2": "A_3"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3", "A_2"]], + "x": {"1": "A_1", "2": "A_3"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3"]], + "x": {"1": "A_1", "2": "A_3"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_1", "2": "A_3"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2"]], + "x": {"1": "A_1", "2": "A_3"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2", "A_3"]], + "x": {"1": "A_1", "2": "A_3"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3", "A_2"]], + "x": {"1": "A_1", "2": "A_3"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3"]], + "x": {"1": "A_1", "2": "A_3"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_1", "2": "A_3"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2"]], + "x": {"1": "A_1", "2": "A_3"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2", "A_3"]], + "x": {"1": "A_1", "2": "A_3"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3", "A_2"]], + "x": {"1": "A_1", "2": "A_3"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3"]], + "x": {"1": "A_1", "2": "A_3"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_1", "2": "A_3"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2"]], + "x": {"1": "A_1", "2": "A_3"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2", "A_3"]], + "x": {"1": "A_1", "2": "A_3"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3", "A_2"]], + "x": {"1": "A_1", "2": "A_3"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3"]], + "x": {"1": "A_1", "2": "A_3"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_1", "2": "A_3"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2"]], + "x": {"1": "A_1", "2": "A_3"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2", "A_3"]], + "x": {"1": "A_1", "2": "A_3"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3", "A_2"]], + "x": {"1": "A_1", "2": "A_3"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3"]], + "x": {"1": "A_1", "2": "A_3"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_1", "2": "A_3"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2"]], + "x": {"1": "A_1", "2": "A_3"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2", "A_3"]], + "x": {"1": "A_1", "2": "A_3"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3", "A_2"]], + "x": {"1": "A_1", "2": "A_3"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3"]], + "x": {"1": "A_1", "2": "A_3"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_1", "2": "A_3"}, + "y": {"1": "A_3", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2"]], + "x": {"1": "A_1", "2": "A_3"}, + "y": {"1": "A_3", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2", "A_3"]], + "x": {"1": "A_1", "2": "A_3"}, + "y": {"1": "A_3", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3", "A_2"]], + "x": {"1": "A_1", "2": "A_3"}, + "y": {"1": "A_3", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3"]], + "x": {"1": "A_1", "2": "A_3"}, + "y": {"1": "A_3", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_1", "2": "A_3"}, + "y": {"1": "A_3", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2"]], + "x": {"1": "A_1", "2": "A_3"}, + "y": {"1": "A_3", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2", "A_3"]], + "x": {"1": "A_1", "2": "A_3"}, + "y": {"1": "A_3", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3", "A_2"]], + "x": {"1": "A_1", "2": "A_3"}, + "y": {"1": "A_3", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3"]], + "x": {"1": "A_1", "2": "A_3"}, + "y": {"1": "A_3", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_1", "2": "A_3"}, + "y": {"1": "A_3", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2"]], + "x": {"1": "A_1", "2": "A_3"}, + "y": {"1": "A_3", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2", "A_3"]], + "x": {"1": "A_1", "2": "A_3"}, + "y": {"1": "A_3", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3", "A_2"]], + "x": {"1": "A_1", "2": "A_3"}, + "y": {"1": "A_3", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3"]], + "x": {"1": "A_1", "2": "A_3"}, + "y": {"1": "A_3", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_1", "2": "A_3"}, + "y": {"1": "A_3", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2"]], + "x": {"1": "A_1", "2": "A_3"}, + "y": {"1": "A_3", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2", "A_3"]], + "x": {"1": "A_1", "2": "A_3"}, + "y": {"1": "A_3", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3", "A_2"]], + "x": {"1": "A_1", "2": "A_3"}, + "y": {"1": "A_3", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3"]], + "x": {"1": "A_1", "2": "A_3"}, + "y": {"1": "A_3", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_1", "2": "A_3"}, + "y": {"1": "A_3", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2"]], + "x": {"1": "A_1", "2": "A_3"}, + "y": {"1": "A_3", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2", "A_3"]], + "x": {"1": "A_1", "2": "A_3"}, + "y": {"1": "A_3", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3", "A_2"]], + "x": {"1": "A_1", "2": "A_3"}, + "y": {"1": "A_3", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3"]], + "x": {"1": "A_1", "2": "A_3"}, + "y": {"1": "A_3", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_1", "2": "A_3"}, + "y": {"1": "A_3", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2"]], + "x": {"1": "A_1", "2": "A_3"}, + "y": {"1": "A_3", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2", "A_3"]], + "x": {"1": "A_1", "2": "A_3"}, + "y": {"1": "A_3", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3", "A_2"]], + "x": {"1": "A_1", "2": "A_3"}, + "y": {"1": "A_3", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3"]], + "x": {"1": "A_1", "2": "A_3"}, + "y": {"1": "A_3", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_1", "2": "A_3"}, + "y": {"1": "A_3", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2"]], + "x": {"1": "A_1", "2": "A_3"}, + "y": {"1": "A_3", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2", "A_3"]], + "x": {"1": "A_1", "2": "A_3"}, + "y": {"1": "A_3", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3", "A_2"]], + "x": {"1": "A_1", "2": "A_3"}, + "y": {"1": "A_3", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3"]], + "x": {"1": "A_1", "2": "A_3"}, + "y": {"1": "A_3", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_1", "2": "A_3"}, + "y": {"1": "A_3", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2"]], + "x": {"1": "A_1", "2": "A_3"}, + "y": {"1": "A_3", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2", "A_3"]], + "x": {"1": "A_1", "2": "A_3"}, + "y": {"1": "A_3", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3", "A_2"]], + "x": {"1": "A_1", "2": "A_3"}, + "y": {"1": "A_3", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3"]], + "x": {"1": "A_1", "2": "A_3"}, + "y": {"1": "A_3", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_1", "2": "A_3"}, + "y": {"1": "A_3", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2"]], + "x": {"1": "A_1", "2": "A_3"}, + "y": {"1": "A_3", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2", "A_3"]], + "x": {"1": "A_1", "2": "A_3"}, + "y": {"1": "A_3", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3", "A_2"]], + "x": {"1": "A_1", "2": "A_3"}, + "y": {"1": "A_3", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3"]], + "x": {"1": "A_1", "2": "A_3"}, + "y": {"1": "A_3", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_2", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_2", "A_3"]], + "x": {"1": "A_2", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2", "A_3"]], + "x": {"1": "A_2", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3"]], + "x": {"1": "A_2", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_2", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_2", "A_3"]], + "x": {"1": "A_2", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2", "A_3"]], + "x": {"1": "A_2", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3"]], + "x": {"1": "A_2", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_2", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_2", "A_3"]], + "x": {"1": "A_2", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2", "A_3"]], + "x": {"1": "A_2", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3"]], + "x": {"1": "A_2", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_2", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_2", "A_3"]], + "x": {"1": "A_2", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2", "A_3"]], + "x": {"1": "A_2", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3"]], + "x": {"1": "A_2", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_2", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_2", "A_3"]], + "x": {"1": "A_2", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2", "A_3"]], + "x": {"1": "A_2", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3"]], + "x": {"1": "A_2", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_2", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_2", "A_3"]], + "x": {"1": "A_2", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2", "A_3"]], + "x": {"1": "A_2", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3"]], + "x": {"1": "A_2", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_2", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_2", "A_3"]], + "x": {"1": "A_2", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2", "A_3"]], + "x": {"1": "A_2", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3"]], + "x": {"1": "A_2", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_2", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_2", "A_3"]], + "x": {"1": "A_2", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2", "A_3"]], + "x": {"1": "A_2", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3"]], + "x": {"1": "A_2", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_2", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_2", "A_3"]], + "x": {"1": "A_2", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2", "A_3"]], + "x": {"1": "A_2", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3"]], + "x": {"1": "A_2", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_2", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_2", "A_3"]], + "x": {"1": "A_2", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2", "A_3"]], + "x": {"1": "A_2", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3"]], + "x": {"1": "A_2", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_2", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_2", "A_3"]], + "x": {"1": "A_2", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2", "A_3"]], + "x": {"1": "A_2", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3"]], + "x": {"1": "A_2", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_2", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_2", "A_3"]], + "x": {"1": "A_2", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2", "A_3"]], + "x": {"1": "A_2", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3"]], + "x": {"1": "A_2", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_2", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_2", "A_3"]], + "x": {"1": "A_2", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2", "A_3"]], + "x": {"1": "A_2", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3"]], + "x": {"1": "A_2", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_2", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_2", "A_3"]], + "x": {"1": "A_2", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2", "A_3"]], + "x": {"1": "A_2", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3"]], + "x": {"1": "A_2", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_2", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_2", "A_3"]], + "x": {"1": "A_2", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2", "A_3"]], + "x": {"1": "A_2", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3"]], + "x": {"1": "A_2", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_2", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_2", "A_3"]], + "x": {"1": "A_2", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2", "A_3"]], + "x": {"1": "A_2", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3"]], + "x": {"1": "A_2", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_2", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_2", "A_3"]], + "x": {"1": "A_2", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2", "A_3"]], + "x": {"1": "A_2", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3"]], + "x": {"1": "A_2", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_2", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_2", "A_3"]], + "x": {"1": "A_2", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2", "A_3"]], + "x": {"1": "A_2", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3"]], + "x": {"1": "A_2", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_2", "2": "A_1"}, + "y": {"1": "A_3", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_2", "A_3"]], + "x": {"1": "A_2", "2": "A_1"}, + "y": {"1": "A_3", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2", "A_3"]], + "x": {"1": "A_2", "2": "A_1"}, + "y": {"1": "A_3", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3"]], + "x": {"1": "A_2", "2": "A_1"}, + "y": {"1": "A_3", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_2", "2": "A_1"}, + "y": {"1": "A_3", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_2", "A_3"]], + "x": {"1": "A_2", "2": "A_1"}, + "y": {"1": "A_3", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2", "A_3"]], + "x": {"1": "A_2", "2": "A_1"}, + "y": {"1": "A_3", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3"]], + "x": {"1": "A_2", "2": "A_1"}, + "y": {"1": "A_3", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_2", "2": "A_1"}, + "y": {"1": "A_3", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_2", "A_3"]], + "x": {"1": "A_2", "2": "A_1"}, + "y": {"1": "A_3", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2", "A_3"]], + "x": {"1": "A_2", "2": "A_1"}, + "y": {"1": "A_3", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3"]], + "x": {"1": "A_2", "2": "A_1"}, + "y": {"1": "A_3", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_2", "2": "A_1"}, + "y": {"1": "A_3", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_2", "A_3"]], + "x": {"1": "A_2", "2": "A_1"}, + "y": {"1": "A_3", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2", "A_3"]], + "x": {"1": "A_2", "2": "A_1"}, + "y": {"1": "A_3", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3"]], + "x": {"1": "A_2", "2": "A_1"}, + "y": {"1": "A_3", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_2", "2": "A_1"}, + "y": {"1": "A_3", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_2", "A_3"]], + "x": {"1": "A_2", "2": "A_1"}, + "y": {"1": "A_3", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2", "A_3"]], + "x": {"1": "A_2", "2": "A_1"}, + "y": {"1": "A_3", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3"]], + "x": {"1": "A_2", "2": "A_1"}, + "y": {"1": "A_3", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_2", "2": "A_1"}, + "y": {"1": "A_3", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_2", "A_3"]], + "x": {"1": "A_2", "2": "A_1"}, + "y": {"1": "A_3", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2", "A_3"]], + "x": {"1": "A_2", "2": "A_1"}, + "y": {"1": "A_3", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3"]], + "x": {"1": "A_2", "2": "A_1"}, + "y": {"1": "A_3", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_2", "2": "A_1"}, + "y": {"1": "A_3", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_2", "A_3"]], + "x": {"1": "A_2", "2": "A_1"}, + "y": {"1": "A_3", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2", "A_3"]], + "x": {"1": "A_2", "2": "A_1"}, + "y": {"1": "A_3", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3"]], + "x": {"1": "A_2", "2": "A_1"}, + "y": {"1": "A_3", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_2", "2": "A_1"}, + "y": {"1": "A_3", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_2", "A_3"]], + "x": {"1": "A_2", "2": "A_1"}, + "y": {"1": "A_3", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2", "A_3"]], + "x": {"1": "A_2", "2": "A_1"}, + "y": {"1": "A_3", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3"]], + "x": {"1": "A_2", "2": "A_1"}, + "y": {"1": "A_3", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_2", "2": "A_1"}, + "y": {"1": "A_3", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_2", "A_3"]], + "x": {"1": "A_2", "2": "A_1"}, + "y": {"1": "A_3", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2", "A_3"]], + "x": {"1": "A_2", "2": "A_1"}, + "y": {"1": "A_3", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3"]], + "x": {"1": "A_2", "2": "A_1"}, + "y": {"1": "A_3", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_2", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_2", "A_3"]], + "x": {"1": "A_2", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2", "A_3"]], + "x": {"1": "A_2", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3"]], + "x": {"1": "A_2", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_2", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_2", "A_3"]], + "x": {"1": "A_2", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2", "A_3"]], + "x": {"1": "A_2", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3"]], + "x": {"1": "A_2", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_2", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_2", "A_3"]], + "x": {"1": "A_2", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2", "A_3"]], + "x": {"1": "A_2", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3"]], + "x": {"1": "A_2", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_2", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_2", "A_3"]], + "x": {"1": "A_2", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2", "A_3"]], + "x": {"1": "A_2", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3"]], + "x": {"1": "A_2", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_2", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_2", "A_3"]], + "x": {"1": "A_2", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2", "A_3"]], + "x": {"1": "A_2", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3"]], + "x": {"1": "A_2", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_2", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_2", "A_3"]], + "x": {"1": "A_2", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2", "A_3"]], + "x": {"1": "A_2", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3"]], + "x": {"1": "A_2", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_2", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_2", "A_3"]], + "x": {"1": "A_2", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2", "A_3"]], + "x": {"1": "A_2", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3"]], + "x": {"1": "A_2", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_2", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_2", "A_3"]], + "x": {"1": "A_2", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2", "A_3"]], + "x": {"1": "A_2", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3"]], + "x": {"1": "A_2", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_2", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_2", "A_3"]], + "x": {"1": "A_2", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2", "A_3"]], + "x": {"1": "A_2", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3"]], + "x": {"1": "A_2", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_2", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_2", "A_3"]], + "x": {"1": "A_2", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2", "A_3"]], + "x": {"1": "A_2", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3"]], + "x": {"1": "A_2", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_2", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_2", "A_3"]], + "x": {"1": "A_2", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2", "A_3"]], + "x": {"1": "A_2", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3"]], + "x": {"1": "A_2", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_2", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_2", "A_3"]], + "x": {"1": "A_2", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2", "A_3"]], + "x": {"1": "A_2", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3"]], + "x": {"1": "A_2", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_2", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_2", "A_3"]], + "x": {"1": "A_2", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2", "A_3"]], + "x": {"1": "A_2", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3"]], + "x": {"1": "A_2", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_2", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_2", "A_3"]], + "x": {"1": "A_2", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2", "A_3"]], + "x": {"1": "A_2", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3"]], + "x": {"1": "A_2", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_2", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_2", "A_3"]], + "x": {"1": "A_2", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2", "A_3"]], + "x": {"1": "A_2", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_2", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_2", "A_3"]], + "x": {"1": "A_2", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2", "A_3"]], + "x": {"1": "A_2", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_2", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_2", "A_3"]], + "x": {"1": "A_2", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2", "A_3"]], + "x": {"1": "A_2", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_2", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_2", "A_3"]], + "x": {"1": "A_2", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2", "A_3"]], + "x": {"1": "A_2", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_2", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_2", "A_3"]], + "x": {"1": "A_2", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2", "A_3"]], + "x": {"1": "A_2", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_2", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_2", "A_3"]], + "x": {"1": "A_2", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2", "A_3"]], + "x": {"1": "A_2", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_2", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_2", "A_3"]], + "x": {"1": "A_2", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2", "A_3"]], + "x": {"1": "A_2", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_2", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_2", "A_3"]], + "x": {"1": "A_2", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2", "A_3"]], + "x": {"1": "A_2", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_2", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_2", "A_3"]], + "x": {"1": "A_2", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2", "A_3"]], + "x": {"1": "A_2", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_2", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_2", "A_3"]], + "x": {"1": "A_2", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2", "A_3"]], + "x": {"1": "A_2", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_2", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_2", "A_3"]], + "x": {"1": "A_2", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2", "A_3"]], + "x": {"1": "A_2", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_2", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_2", "A_3"]], + "x": {"1": "A_2", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2", "A_3"]], + "x": {"1": "A_2", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_2", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_2", "A_3"]], + "x": {"1": "A_2", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2", "A_3"]], + "x": {"1": "A_2", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_2", "2": "A_3"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_2", "A_3"]], + "x": {"1": "A_2", "2": "A_3"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2", "A_3"]], + "x": {"1": "A_2", "2": "A_3"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_2", "2": "A_3"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_2", "A_3"]], + "x": {"1": "A_2", "2": "A_3"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2", "A_3"]], + "x": {"1": "A_2", "2": "A_3"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_2", "2": "A_3"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_2", "A_3"]], + "x": {"1": "A_2", "2": "A_3"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2", "A_3"]], + "x": {"1": "A_2", "2": "A_3"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_2", "2": "A_3"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_2", "A_3"]], + "x": {"1": "A_2", "2": "A_3"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2", "A_3"]], + "x": {"1": "A_2", "2": "A_3"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_2", "2": "A_3"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_2", "A_3"]], + "x": {"1": "A_2", "2": "A_3"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2", "A_3"]], + "x": {"1": "A_2", "2": "A_3"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_2", "2": "A_3"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_2", "A_3"]], + "x": {"1": "A_2", "2": "A_3"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2", "A_3"]], + "x": {"1": "A_2", "2": "A_3"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_2", "2": "A_3"}, + "y": {"1": "A_1", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_2", "A_3"]], + "x": {"1": "A_2", "2": "A_3"}, + "y": {"1": "A_1", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2", "A_3"]], + "x": {"1": "A_2", "2": "A_3"}, + "y": {"1": "A_1", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_2", "2": "A_3"}, + "y": {"1": "A_1", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_2", "A_3"]], + "x": {"1": "A_2", "2": "A_3"}, + "y": {"1": "A_1", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2", "A_3"]], + "x": {"1": "A_2", "2": "A_3"}, + "y": {"1": "A_1", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_2", "2": "A_3"}, + "y": {"1": "A_1", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_2", "A_3"]], + "x": {"1": "A_2", "2": "A_3"}, + "y": {"1": "A_1", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2", "A_3"]], + "x": {"1": "A_2", "2": "A_3"}, + "y": {"1": "A_1", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_2", "2": "A_3"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_2", "A_3"]], + "x": {"1": "A_2", "2": "A_3"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2", "A_3"]], + "x": {"1": "A_2", "2": "A_3"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_2", "2": "A_3"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_2", "A_3"]], + "x": {"1": "A_2", "2": "A_3"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2", "A_3"]], + "x": {"1": "A_2", "2": "A_3"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_2", "2": "A_3"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_2", "A_3"]], + "x": {"1": "A_2", "2": "A_3"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2", "A_3"]], + "x": {"1": "A_2", "2": "A_3"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_2", "2": "A_3"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_2", "A_3"]], + "x": {"1": "A_2", "2": "A_3"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2", "A_3"]], + "x": {"1": "A_2", "2": "A_3"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_2", "2": "A_3"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_2", "A_3"]], + "x": {"1": "A_2", "2": "A_3"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2", "A_3"]], + "x": {"1": "A_2", "2": "A_3"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_2", "2": "A_3"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_2", "A_3"]], + "x": {"1": "A_2", "2": "A_3"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2", "A_3"]], + "x": {"1": "A_2", "2": "A_3"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_2", "2": "A_3"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_2", "A_3"]], + "x": {"1": "A_2", "2": "A_3"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2", "A_3"]], + "x": {"1": "A_2", "2": "A_3"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_2", "2": "A_3"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_2", "A_3"]], + "x": {"1": "A_2", "2": "A_3"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2", "A_3"]], + "x": {"1": "A_2", "2": "A_3"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_2", "2": "A_3"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_2", "A_3"]], + "x": {"1": "A_2", "2": "A_3"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2", "A_3"]], + "x": {"1": "A_2", "2": "A_3"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_2", "2": "A_3"}, + "y": {"1": "A_3", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_2", "A_3"]], + "x": {"1": "A_2", "2": "A_3"}, + "y": {"1": "A_3", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2", "A_3"]], + "x": {"1": "A_2", "2": "A_3"}, + "y": {"1": "A_3", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_2", "2": "A_3"}, + "y": {"1": "A_3", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_2", "A_3"]], + "x": {"1": "A_2", "2": "A_3"}, + "y": {"1": "A_3", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2", "A_3"]], + "x": {"1": "A_2", "2": "A_3"}, + "y": {"1": "A_3", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_2", "2": "A_3"}, + "y": {"1": "A_3", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_2", "A_3"]], + "x": {"1": "A_2", "2": "A_3"}, + "y": {"1": "A_3", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2", "A_3"]], + "x": {"1": "A_2", "2": "A_3"}, + "y": {"1": "A_3", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_2", "2": "A_3"}, + "y": {"1": "A_3", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_2", "A_3"]], + "x": {"1": "A_2", "2": "A_3"}, + "y": {"1": "A_3", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2", "A_3"]], + "x": {"1": "A_2", "2": "A_3"}, + "y": {"1": "A_3", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_2", "2": "A_3"}, + "y": {"1": "A_3", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_2", "A_3"]], + "x": {"1": "A_2", "2": "A_3"}, + "y": {"1": "A_3", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2", "A_3"]], + "x": {"1": "A_2", "2": "A_3"}, + "y": {"1": "A_3", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_2", "2": "A_3"}, + "y": {"1": "A_3", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_2", "A_3"]], + "x": {"1": "A_2", "2": "A_3"}, + "y": {"1": "A_3", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2", "A_3"]], + "x": {"1": "A_2", "2": "A_3"}, + "y": {"1": "A_3", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_2", "2": "A_3"}, + "y": {"1": "A_3", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_2", "A_3"]], + "x": {"1": "A_2", "2": "A_3"}, + "y": {"1": "A_3", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2", "A_3"]], + "x": {"1": "A_2", "2": "A_3"}, + "y": {"1": "A_3", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_2", "2": "A_3"}, + "y": {"1": "A_3", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_2", "A_3"]], + "x": {"1": "A_2", "2": "A_3"}, + "y": {"1": "A_3", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2", "A_3"]], + "x": {"1": "A_2", "2": "A_3"}, + "y": {"1": "A_3", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_2", "2": "A_3"}, + "y": {"1": "A_3", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_2", "A_3"]], + "x": {"1": "A_2", "2": "A_3"}, + "y": {"1": "A_3", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2", "A_3"]], + "x": {"1": "A_2", "2": "A_3"}, + "y": {"1": "A_3", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_3", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2"]], + "x": {"1": "A_3", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_3", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2"]], + "x": {"1": "A_3", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_3", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2"]], + "x": {"1": "A_3", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_3", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2"]], + "x": {"1": "A_3", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_3", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2"]], + "x": {"1": "A_3", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_3", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2"]], + "x": {"1": "A_3", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_3", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2"]], + "x": {"1": "A_3", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_3", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2"]], + "x": {"1": "A_3", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_3", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2"]], + "x": {"1": "A_3", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_3", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2"]], + "x": {"1": "A_3", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_3", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2"]], + "x": {"1": "A_3", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_3", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2"]], + "x": {"1": "A_3", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_3", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2"]], + "x": {"1": "A_3", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_3", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2"]], + "x": {"1": "A_3", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_3", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2"]], + "x": {"1": "A_3", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_3", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2"]], + "x": {"1": "A_3", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_3", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2"]], + "x": {"1": "A_3", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_3", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2"]], + "x": {"1": "A_3", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_3", "2": "A_1"}, + "y": {"1": "A_3", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2"]], + "x": {"1": "A_3", "2": "A_1"}, + "y": {"1": "A_3", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_3", "2": "A_1"}, + "y": {"1": "A_3", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2"]], + "x": {"1": "A_3", "2": "A_1"}, + "y": {"1": "A_3", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_3", "2": "A_1"}, + "y": {"1": "A_3", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2"]], + "x": {"1": "A_3", "2": "A_1"}, + "y": {"1": "A_3", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_3", "2": "A_1"}, + "y": {"1": "A_3", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2"]], + "x": {"1": "A_3", "2": "A_1"}, + "y": {"1": "A_3", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_3", "2": "A_1"}, + "y": {"1": "A_3", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2"]], + "x": {"1": "A_3", "2": "A_1"}, + "y": {"1": "A_3", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_3", "2": "A_1"}, + "y": {"1": "A_3", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2"]], + "x": {"1": "A_3", "2": "A_1"}, + "y": {"1": "A_3", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_3", "2": "A_1"}, + "y": {"1": "A_3", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2"]], + "x": {"1": "A_3", "2": "A_1"}, + "y": {"1": "A_3", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_3", "2": "A_1"}, + "y": {"1": "A_3", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2"]], + "x": {"1": "A_3", "2": "A_1"}, + "y": {"1": "A_3", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_3", "2": "A_1"}, + "y": {"1": "A_3", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2"]], + "x": {"1": "A_3", "2": "A_1"}, + "y": {"1": "A_3", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_3", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_3", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_3", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_3", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_3", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_3", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_3", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_3", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_3", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_3", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_3", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_3", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_3", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_3", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_3", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_3", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_3", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_3", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_3", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_3", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_3", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_3", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_3", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_3", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_3", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_3", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_3", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_3", "2": "A_3"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2"]], + "x": {"1": "A_3", "2": "A_3"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_3", "2": "A_3"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2"]], + "x": {"1": "A_3", "2": "A_3"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_3", "2": "A_3"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2"]], + "x": {"1": "A_3", "2": "A_3"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_3", "2": "A_3"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2"]], + "x": {"1": "A_3", "2": "A_3"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_3", "2": "A_3"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2"]], + "x": {"1": "A_3", "2": "A_3"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_3", "2": "A_3"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2"]], + "x": {"1": "A_3", "2": "A_3"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_3", "2": "A_3"}, + "y": {"1": "A_1", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2"]], + "x": {"1": "A_3", "2": "A_3"}, + "y": {"1": "A_1", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_3", "2": "A_3"}, + "y": {"1": "A_1", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2"]], + "x": {"1": "A_3", "2": "A_3"}, + "y": {"1": "A_1", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_3", "2": "A_3"}, + "y": {"1": "A_1", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2"]], + "x": {"1": "A_3", "2": "A_3"}, + "y": {"1": "A_1", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_3", "2": "A_3"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_3", "2": "A_3"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_3", "2": "A_3"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_3", "2": "A_3"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_3", "2": "A_3"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_3", "2": "A_3"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_3", "2": "A_3"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_3", "2": "A_3"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_3", "2": "A_3"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_3", "2": "A_3"}, + "y": {"1": "A_3", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2"]], + "x": {"1": "A_3", "2": "A_3"}, + "y": {"1": "A_3", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_3", "2": "A_3"}, + "y": {"1": "A_3", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2"]], + "x": {"1": "A_3", "2": "A_3"}, + "y": {"1": "A_3", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_3", "2": "A_3"}, + "y": {"1": "A_3", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2"]], + "x": {"1": "A_3", "2": "A_3"}, + "y": {"1": "A_3", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_3", "2": "A_3"}, + "y": {"1": "A_3", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_3", "2": "A_3"}, + "y": {"1": "A_3", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_3", "2": "A_3"}, + "y": {"1": "A_3", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_3", "2": "A_3"}, + "y": {"1": "A_3", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2"]], + "x": {"1": "A_3", "2": "A_3"}, + "y": {"1": "A_3", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_3", "2": "A_3"}, + "y": {"1": "A_3", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], "p": [], + "x": {"1": "A_3", "2": "A_3"}, + "y": {"1": "A_3", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2"]], + "x": {"1": "A_3", "2": "A_3"}, + "y": {"1": "A_3", "2": "A_3", "3": "A_3"}} +] diff --git a/tests/custom/permutations/permInverse/09/00.essence b/tests/custom/permutations/permInverse/09/00.essence new file mode 100644 index 0000000000..a591580d3e --- /dev/null +++ b/tests/custom/permutations/permInverse/09/00.essence @@ -0,0 +1,3 @@ +letting A be new type of size 3 +find x : matrix [int(1..2)] of A +find y : matrix [int(1..3)] of A diff --git a/tests/custom/permutations/permInverse/09/run.sh b/tests/custom/permutations/permInverse/09/run.sh new file mode 100755 index 0000000000..d2c1c1f208 --- /dev/null +++ b/tests/custom/permutations/permInverse/09/run.sh @@ -0,0 +1,5 @@ + +rm -rf conjure-output +conjure solve *.essence --output-format=json --solutions-in-one-file --number-of-solutions=all --line-width=50 --copy-solutions=no --unnamed-symmetry-breaking=full +cat conjure-output/model000001.solutions.json +rm -rf conjure-output diff --git a/tests/custom/permutations/permInverse/09/stderr.expected b/tests/custom/permutations/permInverse/09/stderr.expected new file mode 100644 index 0000000000..d300ba3836 --- /dev/null +++ b/tests/custom/permutations/permInverse/09/stderr.expected @@ -0,0 +1,3 @@ +Adding the following unnamed symmetry breaking constraints: + such that + and([(x, y) .<= transform(q1, (x, y)) | q1 : permutation of A]) diff --git a/tests/custom/permutations/permInverse/09/stdout.expected b/tests/custom/permutations/permInverse/09/stdout.expected new file mode 100644 index 0000000000..f035644b7b --- /dev/null +++ b/tests/custom/permutations/permInverse/09/stdout.expected @@ -0,0 +1,171 @@ +Generating models for 00.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: conjure-output/model000001.eprime +Running minion for domain filtering. +Running solver: minion +[ +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_3", "3": "A_3"}} +] From ddefe73d9de1a5308ea623356fa924eb4a213073 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?=C3=96zg=C3=BCr=20Akg=C3=BCn?= Date: Fri, 22 Nov 2024 10:42:11 +0000 Subject: [PATCH 196/229] more test cases --- .../permutations/permInverse/10/00.essence | 4 + .../custom/permutations/permInverse/10/run.sh | 5 + .../permInverse/10/stderr.expected | 4 + .../permInverse/10/stdout.expected | 5477 +++++++++++++++++ .../permutations/permInverse/11/00.essence | 3 + .../custom/permutations/permInverse/11/run.sh | 21 + .../permInverse/11/stderr.expected | 4 + .../permInverse/11/stdout.expected | 171 + .../permutations/permInverse/12/00.essence | 3 + .../custom/permutations/permInverse/12/run.sh | 21 + .../permInverse/12/stderr.expected | 3 + .../permInverse/12/stdout.expected | 171 + 12 files changed, 5887 insertions(+) create mode 100644 tests/custom/permutations/permInverse/10/00.essence create mode 100755 tests/custom/permutations/permInverse/10/run.sh create mode 100644 tests/custom/permutations/permInverse/10/stderr.expected create mode 100644 tests/custom/permutations/permInverse/10/stdout.expected create mode 100644 tests/custom/permutations/permInverse/11/00.essence create mode 100755 tests/custom/permutations/permInverse/11/run.sh create mode 100644 tests/custom/permutations/permInverse/11/stderr.expected create mode 100644 tests/custom/permutations/permInverse/11/stdout.expected create mode 100644 tests/custom/permutations/permInverse/12/00.essence create mode 100755 tests/custom/permutations/permInverse/12/run.sh create mode 100644 tests/custom/permutations/permInverse/12/stderr.expected create mode 100644 tests/custom/permutations/permInverse/12/stdout.expected diff --git a/tests/custom/permutations/permInverse/10/00.essence b/tests/custom/permutations/permInverse/10/00.essence new file mode 100644 index 0000000000..89d9d4a301 --- /dev/null +++ b/tests/custom/permutations/permInverse/10/00.essence @@ -0,0 +1,4 @@ +letting A be new type of size 3 +find x : matrix [int(1..2)] of A +find y : matrix [int(1..3)] of A +find z : matrix [int(1..3)] of A \ No newline at end of file diff --git a/tests/custom/permutations/permInverse/10/run.sh b/tests/custom/permutations/permInverse/10/run.sh new file mode 100755 index 0000000000..d2c1c1f208 --- /dev/null +++ b/tests/custom/permutations/permInverse/10/run.sh @@ -0,0 +1,5 @@ + +rm -rf conjure-output +conjure solve *.essence --output-format=json --solutions-in-one-file --number-of-solutions=all --line-width=50 --copy-solutions=no --unnamed-symmetry-breaking=full +cat conjure-output/model000001.solutions.json +rm -rf conjure-output diff --git a/tests/custom/permutations/permInverse/10/stderr.expected b/tests/custom/permutations/permInverse/10/stderr.expected new file mode 100644 index 0000000000..747b75eb07 --- /dev/null +++ b/tests/custom/permutations/permInverse/10/stderr.expected @@ -0,0 +1,4 @@ +Adding the following unnamed symmetry breaking constraints: + such that + and([(x, y, z) .<= transform(q1, (x, y, z)) + | q1 : permutation of A]) diff --git a/tests/custom/permutations/permInverse/10/stdout.expected b/tests/custom/permutations/permInverse/10/stdout.expected new file mode 100644 index 0000000000..bcaf26f89c --- /dev/null +++ b/tests/custom/permutations/permInverse/10/stdout.expected @@ -0,0 +1,5477 @@ +Generating models for 00.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: conjure-output/model000001.eprime +Running minion for domain filtering. +Running solver: minion +[ +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_1"}, + "z": {"1": "A_1", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_1"}, + "z": {"1": "A_1", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_1"}, + "z": {"1": "A_1", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_1"}, + "z": {"1": "A_1", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_1"}, + "z": {"1": "A_1", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_1"}, + "z": {"1": "A_2", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_1"}, + "z": {"1": "A_2", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_1"}, + "z": {"1": "A_2", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_1"}, + "z": {"1": "A_2", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_1"}, + "z": {"1": "A_2", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_1"}, + "z": {"1": "A_2", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_1"}, + "z": {"1": "A_2", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_1"}, + "z": {"1": "A_2", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_1"}, + "z": {"1": "A_2", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_2"}, + "z": {"1": "A_1", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_2"}, + "z": {"1": "A_1", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_2"}, + "z": {"1": "A_1", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_2"}, + "z": {"1": "A_1", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_2"}, + "z": {"1": "A_1", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_2"}, + "z": {"1": "A_1", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_2"}, + "z": {"1": "A_1", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_2"}, + "z": {"1": "A_1", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_2"}, + "z": {"1": "A_1", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_2"}, + "z": {"1": "A_2", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_2"}, + "z": {"1": "A_2", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_2"}, + "z": {"1": "A_2", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_2"}, + "z": {"1": "A_2", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_2"}, + "z": {"1": "A_2", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_2"}, + "z": {"1": "A_2", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_2"}, + "z": {"1": "A_2", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_2"}, + "z": {"1": "A_2", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_2"}, + "z": {"1": "A_2", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_2"}, + "z": {"1": "A_3", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_2"}, + "z": {"1": "A_3", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_2"}, + "z": {"1": "A_3", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_2"}, + "z": {"1": "A_3", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_2"}, + "z": {"1": "A_3", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_2"}, + "z": {"1": "A_3", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_2"}, + "z": {"1": "A_3", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_2"}, + "z": {"1": "A_3", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_2"}, + "z": {"1": "A_3", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_1"}, + "z": {"1": "A_1", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_1"}, + "z": {"1": "A_1", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_1"}, + "z": {"1": "A_1", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_1"}, + "z": {"1": "A_1", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_1"}, + "z": {"1": "A_1", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_1"}, + "z": {"1": "A_1", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_1"}, + "z": {"1": "A_1", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_1"}, + "z": {"1": "A_1", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_1"}, + "z": {"1": "A_1", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_1"}, + "z": {"1": "A_2", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_1"}, + "z": {"1": "A_2", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_1"}, + "z": {"1": "A_2", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_1"}, + "z": {"1": "A_2", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_1"}, + "z": {"1": "A_2", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_1"}, + "z": {"1": "A_2", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_1"}, + "z": {"1": "A_2", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_1"}, + "z": {"1": "A_2", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_1"}, + "z": {"1": "A_2", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_1"}, + "z": {"1": "A_3", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_1"}, + "z": {"1": "A_3", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_1"}, + "z": {"1": "A_3", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_1"}, + "z": {"1": "A_3", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_1"}, + "z": {"1": "A_3", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_1"}, + "z": {"1": "A_3", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_1"}, + "z": {"1": "A_3", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_1"}, + "z": {"1": "A_3", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_1"}, + "z": {"1": "A_3", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_2"}, + "z": {"1": "A_1", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_2"}, + "z": {"1": "A_1", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_2"}, + "z": {"1": "A_1", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_2"}, + "z": {"1": "A_1", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_2"}, + "z": {"1": "A_1", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_2"}, + "z": {"1": "A_1", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_2"}, + "z": {"1": "A_1", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_2"}, + "z": {"1": "A_1", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_2"}, + "z": {"1": "A_1", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_2"}, + "z": {"1": "A_2", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_2"}, + "z": {"1": "A_2", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_2"}, + "z": {"1": "A_2", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_2"}, + "z": {"1": "A_2", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_2"}, + "z": {"1": "A_2", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_2"}, + "z": {"1": "A_2", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_2"}, + "z": {"1": "A_2", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_2"}, + "z": {"1": "A_2", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_2"}, + "z": {"1": "A_2", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_2"}, + "z": {"1": "A_3", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_2"}, + "z": {"1": "A_3", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_2"}, + "z": {"1": "A_3", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_2"}, + "z": {"1": "A_3", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_2"}, + "z": {"1": "A_3", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_2"}, + "z": {"1": "A_3", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_2"}, + "z": {"1": "A_3", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_2"}, + "z": {"1": "A_3", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_2"}, + "z": {"1": "A_3", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_3"}, + "z": {"1": "A_1", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_3"}, + "z": {"1": "A_1", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_3"}, + "z": {"1": "A_1", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_3"}, + "z": {"1": "A_1", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_3"}, + "z": {"1": "A_1", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_3"}, + "z": {"1": "A_1", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_3"}, + "z": {"1": "A_1", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_3"}, + "z": {"1": "A_1", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_3"}, + "z": {"1": "A_1", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_3"}, + "z": {"1": "A_2", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_3"}, + "z": {"1": "A_2", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_3"}, + "z": {"1": "A_2", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_3"}, + "z": {"1": "A_2", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_3"}, + "z": {"1": "A_2", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_3"}, + "z": {"1": "A_2", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_3"}, + "z": {"1": "A_2", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_3"}, + "z": {"1": "A_2", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_3"}, + "z": {"1": "A_2", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_3"}, + "z": {"1": "A_3", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_3"}, + "z": {"1": "A_3", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_3"}, + "z": {"1": "A_3", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_3"}, + "z": {"1": "A_3", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_3"}, + "z": {"1": "A_3", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_3"}, + "z": {"1": "A_3", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_3"}, + "z": {"1": "A_3", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_3"}, + "z": {"1": "A_3", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_3"}, + "z": {"1": "A_3", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_1"}, + "z": {"1": "A_1", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_1"}, + "z": {"1": "A_1", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_1"}, + "z": {"1": "A_1", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_1"}, + "z": {"1": "A_1", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_1"}, + "z": {"1": "A_1", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_1"}, + "z": {"1": "A_1", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_1"}, + "z": {"1": "A_1", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_1"}, + "z": {"1": "A_1", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_1"}, + "z": {"1": "A_1", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_1"}, + "z": {"1": "A_2", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_1"}, + "z": {"1": "A_2", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_1"}, + "z": {"1": "A_2", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_1"}, + "z": {"1": "A_2", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_1"}, + "z": {"1": "A_2", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_1"}, + "z": {"1": "A_2", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_1"}, + "z": {"1": "A_2", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_1"}, + "z": {"1": "A_2", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_1"}, + "z": {"1": "A_2", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_1"}, + "z": {"1": "A_3", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_1"}, + "z": {"1": "A_3", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_1"}, + "z": {"1": "A_3", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_1"}, + "z": {"1": "A_3", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_1"}, + "z": {"1": "A_3", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_1"}, + "z": {"1": "A_3", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_1"}, + "z": {"1": "A_3", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_1"}, + "z": {"1": "A_3", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_1"}, + "z": {"1": "A_3", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_2"}, + "z": {"1": "A_1", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_2"}, + "z": {"1": "A_1", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_2"}, + "z": {"1": "A_1", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_2"}, + "z": {"1": "A_1", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_2"}, + "z": {"1": "A_1", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_2"}, + "z": {"1": "A_1", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_2"}, + "z": {"1": "A_1", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_2"}, + "z": {"1": "A_1", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_2"}, + "z": {"1": "A_1", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_2"}, + "z": {"1": "A_2", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_2"}, + "z": {"1": "A_2", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_2"}, + "z": {"1": "A_2", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_2"}, + "z": {"1": "A_2", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_2"}, + "z": {"1": "A_2", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_2"}, + "z": {"1": "A_2", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_2"}, + "z": {"1": "A_2", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_2"}, + "z": {"1": "A_2", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_2"}, + "z": {"1": "A_2", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_2"}, + "z": {"1": "A_3", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_2"}, + "z": {"1": "A_3", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_2"}, + "z": {"1": "A_3", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_2"}, + "z": {"1": "A_3", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_2"}, + "z": {"1": "A_3", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_2"}, + "z": {"1": "A_3", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_2"}, + "z": {"1": "A_3", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_2"}, + "z": {"1": "A_3", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_2"}, + "z": {"1": "A_3", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_3"}, + "z": {"1": "A_1", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_3"}, + "z": {"1": "A_1", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_3"}, + "z": {"1": "A_1", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_3"}, + "z": {"1": "A_1", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_3"}, + "z": {"1": "A_1", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_3"}, + "z": {"1": "A_1", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_3"}, + "z": {"1": "A_1", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_3"}, + "z": {"1": "A_1", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_3"}, + "z": {"1": "A_1", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_3"}, + "z": {"1": "A_2", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_3"}, + "z": {"1": "A_2", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_3"}, + "z": {"1": "A_2", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_3"}, + "z": {"1": "A_2", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_3"}, + "z": {"1": "A_2", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_3"}, + "z": {"1": "A_2", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_3"}, + "z": {"1": "A_2", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_3"}, + "z": {"1": "A_2", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_3"}, + "z": {"1": "A_2", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_3"}, + "z": {"1": "A_3", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_3"}, + "z": {"1": "A_3", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_3"}, + "z": {"1": "A_3", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_3"}, + "z": {"1": "A_3", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_3"}, + "z": {"1": "A_3", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_3"}, + "z": {"1": "A_3", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_3"}, + "z": {"1": "A_3", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_3"}, + "z": {"1": "A_3", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_3"}, + "z": {"1": "A_3", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_1"}, + "z": {"1": "A_1", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_1"}, + "z": {"1": "A_1", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_1"}, + "z": {"1": "A_1", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_1"}, + "z": {"1": "A_1", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_1"}, + "z": {"1": "A_1", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_1"}, + "z": {"1": "A_1", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_1"}, + "z": {"1": "A_1", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_1"}, + "z": {"1": "A_1", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_1"}, + "z": {"1": "A_1", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_1"}, + "z": {"1": "A_2", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_1"}, + "z": {"1": "A_2", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_1"}, + "z": {"1": "A_2", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_1"}, + "z": {"1": "A_2", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_1"}, + "z": {"1": "A_2", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_1"}, + "z": {"1": "A_2", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_1"}, + "z": {"1": "A_2", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_1"}, + "z": {"1": "A_2", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_1"}, + "z": {"1": "A_2", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_1"}, + "z": {"1": "A_3", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_1"}, + "z": {"1": "A_3", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_1"}, + "z": {"1": "A_3", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_1"}, + "z": {"1": "A_3", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_1"}, + "z": {"1": "A_3", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_1"}, + "z": {"1": "A_3", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_1"}, + "z": {"1": "A_3", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_1"}, + "z": {"1": "A_3", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_1"}, + "z": {"1": "A_3", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_2"}, + "z": {"1": "A_1", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_2"}, + "z": {"1": "A_1", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_2"}, + "z": {"1": "A_1", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_2"}, + "z": {"1": "A_1", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_2"}, + "z": {"1": "A_1", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_2"}, + "z": {"1": "A_1", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_2"}, + "z": {"1": "A_1", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_2"}, + "z": {"1": "A_1", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_2"}, + "z": {"1": "A_1", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_2"}, + "z": {"1": "A_2", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_2"}, + "z": {"1": "A_2", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_2"}, + "z": {"1": "A_2", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_2"}, + "z": {"1": "A_2", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_2"}, + "z": {"1": "A_2", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_2"}, + "z": {"1": "A_2", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_2"}, + "z": {"1": "A_2", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_2"}, + "z": {"1": "A_2", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_2"}, + "z": {"1": "A_2", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_2"}, + "z": {"1": "A_3", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_2"}, + "z": {"1": "A_3", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_2"}, + "z": {"1": "A_3", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_2"}, + "z": {"1": "A_3", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_2"}, + "z": {"1": "A_3", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_2"}, + "z": {"1": "A_3", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_2"}, + "z": {"1": "A_3", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_2"}, + "z": {"1": "A_3", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_2"}, + "z": {"1": "A_3", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_3"}, + "z": {"1": "A_1", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_3"}, + "z": {"1": "A_1", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_3"}, + "z": {"1": "A_1", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_3"}, + "z": {"1": "A_1", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_3"}, + "z": {"1": "A_1", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_3"}, + "z": {"1": "A_1", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_3"}, + "z": {"1": "A_1", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_3"}, + "z": {"1": "A_1", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_3"}, + "z": {"1": "A_1", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_3"}, + "z": {"1": "A_2", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_3"}, + "z": {"1": "A_2", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_3"}, + "z": {"1": "A_2", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_3"}, + "z": {"1": "A_2", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_3"}, + "z": {"1": "A_2", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_3"}, + "z": {"1": "A_2", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_3"}, + "z": {"1": "A_2", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_3"}, + "z": {"1": "A_2", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_3"}, + "z": {"1": "A_2", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_3"}, + "z": {"1": "A_3", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_3"}, + "z": {"1": "A_3", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_3"}, + "z": {"1": "A_3", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_3"}, + "z": {"1": "A_3", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_3"}, + "z": {"1": "A_3", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_3"}, + "z": {"1": "A_3", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_3"}, + "z": {"1": "A_3", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_3"}, + "z": {"1": "A_3", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_3"}, + "z": {"1": "A_3", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_1"}, + "z": {"1": "A_1", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_1"}, + "z": {"1": "A_1", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_1"}, + "z": {"1": "A_1", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_1"}, + "z": {"1": "A_1", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_1"}, + "z": {"1": "A_1", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_1"}, + "z": {"1": "A_1", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_1"}, + "z": {"1": "A_1", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_1"}, + "z": {"1": "A_1", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_1"}, + "z": {"1": "A_1", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_1"}, + "z": {"1": "A_2", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_1"}, + "z": {"1": "A_2", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_1"}, + "z": {"1": "A_2", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_1"}, + "z": {"1": "A_2", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_1"}, + "z": {"1": "A_2", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_1"}, + "z": {"1": "A_2", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_1"}, + "z": {"1": "A_2", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_1"}, + "z": {"1": "A_2", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_1"}, + "z": {"1": "A_2", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_1"}, + "z": {"1": "A_3", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_1"}, + "z": {"1": "A_3", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_1"}, + "z": {"1": "A_3", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_1"}, + "z": {"1": "A_3", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_1"}, + "z": {"1": "A_3", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_1"}, + "z": {"1": "A_3", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_1"}, + "z": {"1": "A_3", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_1"}, + "z": {"1": "A_3", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_1"}, + "z": {"1": "A_3", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_2"}, + "z": {"1": "A_1", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_2"}, + "z": {"1": "A_1", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_2"}, + "z": {"1": "A_1", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_2"}, + "z": {"1": "A_1", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_2"}, + "z": {"1": "A_1", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_2"}, + "z": {"1": "A_1", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_2"}, + "z": {"1": "A_1", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_2"}, + "z": {"1": "A_1", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_2"}, + "z": {"1": "A_1", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_2"}, + "z": {"1": "A_2", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_2"}, + "z": {"1": "A_2", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_2"}, + "z": {"1": "A_2", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_2"}, + "z": {"1": "A_2", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_2"}, + "z": {"1": "A_2", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_2"}, + "z": {"1": "A_2", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_2"}, + "z": {"1": "A_2", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_2"}, + "z": {"1": "A_2", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_2"}, + "z": {"1": "A_2", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_2"}, + "z": {"1": "A_3", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_2"}, + "z": {"1": "A_3", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_2"}, + "z": {"1": "A_3", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_2"}, + "z": {"1": "A_3", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_2"}, + "z": {"1": "A_3", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_2"}, + "z": {"1": "A_3", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_2"}, + "z": {"1": "A_3", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_2"}, + "z": {"1": "A_3", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_2"}, + "z": {"1": "A_3", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_3"}, + "z": {"1": "A_1", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_3"}, + "z": {"1": "A_1", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_3"}, + "z": {"1": "A_1", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_3"}, + "z": {"1": "A_1", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_3"}, + "z": {"1": "A_1", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_3"}, + "z": {"1": "A_1", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_3"}, + "z": {"1": "A_1", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_3"}, + "z": {"1": "A_1", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_3"}, + "z": {"1": "A_1", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_3"}, + "z": {"1": "A_2", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_3"}, + "z": {"1": "A_2", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_3"}, + "z": {"1": "A_2", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_3"}, + "z": {"1": "A_2", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_3"}, + "z": {"1": "A_2", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_3"}, + "z": {"1": "A_2", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_3"}, + "z": {"1": "A_2", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_3"}, + "z": {"1": "A_2", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_3"}, + "z": {"1": "A_2", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_3"}, + "z": {"1": "A_3", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_3"}, + "z": {"1": "A_3", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_3"}, + "z": {"1": "A_3", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_3"}, + "z": {"1": "A_3", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_3"}, + "z": {"1": "A_3", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_3"}, + "z": {"1": "A_3", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_3"}, + "z": {"1": "A_3", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_3"}, + "z": {"1": "A_3", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_3"}, + "z": {"1": "A_3", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_1"}, + "z": {"1": "A_1", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_1"}, + "z": {"1": "A_1", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_1"}, + "z": {"1": "A_1", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_1"}, + "z": {"1": "A_1", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_1"}, + "z": {"1": "A_1", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_1"}, + "z": {"1": "A_1", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_1"}, + "z": {"1": "A_1", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_1"}, + "z": {"1": "A_1", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_1"}, + "z": {"1": "A_1", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_1"}, + "z": {"1": "A_2", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_1"}, + "z": {"1": "A_2", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_1"}, + "z": {"1": "A_2", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_1"}, + "z": {"1": "A_2", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_1"}, + "z": {"1": "A_2", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_1"}, + "z": {"1": "A_2", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_1"}, + "z": {"1": "A_2", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_1"}, + "z": {"1": "A_2", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_1"}, + "z": {"1": "A_2", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_1"}, + "z": {"1": "A_3", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_1"}, + "z": {"1": "A_3", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_1"}, + "z": {"1": "A_3", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_1"}, + "z": {"1": "A_3", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_1"}, + "z": {"1": "A_3", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_1"}, + "z": {"1": "A_3", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_1"}, + "z": {"1": "A_3", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_1"}, + "z": {"1": "A_3", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_1"}, + "z": {"1": "A_3", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_2"}, + "z": {"1": "A_1", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_2"}, + "z": {"1": "A_1", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_2"}, + "z": {"1": "A_1", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_2"}, + "z": {"1": "A_1", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_2"}, + "z": {"1": "A_1", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_2"}, + "z": {"1": "A_1", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_2"}, + "z": {"1": "A_1", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_2"}, + "z": {"1": "A_1", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_2"}, + "z": {"1": "A_1", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_2"}, + "z": {"1": "A_2", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_2"}, + "z": {"1": "A_2", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_2"}, + "z": {"1": "A_2", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_2"}, + "z": {"1": "A_2", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_2"}, + "z": {"1": "A_2", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_2"}, + "z": {"1": "A_2", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_2"}, + "z": {"1": "A_2", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_2"}, + "z": {"1": "A_2", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_2"}, + "z": {"1": "A_2", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_2"}, + "z": {"1": "A_3", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_2"}, + "z": {"1": "A_3", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_2"}, + "z": {"1": "A_3", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_2"}, + "z": {"1": "A_3", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_2"}, + "z": {"1": "A_3", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_2"}, + "z": {"1": "A_3", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_2"}, + "z": {"1": "A_3", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_2"}, + "z": {"1": "A_3", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_2"}, + "z": {"1": "A_3", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_3"}, + "z": {"1": "A_1", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_3"}, + "z": {"1": "A_1", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_3"}, + "z": {"1": "A_1", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_3"}, + "z": {"1": "A_1", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_3"}, + "z": {"1": "A_1", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_3"}, + "z": {"1": "A_1", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_3"}, + "z": {"1": "A_1", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_3"}, + "z": {"1": "A_1", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_3"}, + "z": {"1": "A_1", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_3"}, + "z": {"1": "A_2", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_3"}, + "z": {"1": "A_2", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_3"}, + "z": {"1": "A_2", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_3"}, + "z": {"1": "A_2", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_3"}, + "z": {"1": "A_2", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_3"}, + "z": {"1": "A_2", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_3"}, + "z": {"1": "A_2", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_3"}, + "z": {"1": "A_2", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_3"}, + "z": {"1": "A_2", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_3"}, + "z": {"1": "A_3", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_3"}, + "z": {"1": "A_3", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_3"}, + "z": {"1": "A_3", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_3"}, + "z": {"1": "A_3", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_3"}, + "z": {"1": "A_3", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_3"}, + "z": {"1": "A_3", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_3"}, + "z": {"1": "A_3", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_3"}, + "z": {"1": "A_3", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_3"}, + "z": {"1": "A_3", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_1"}, + "z": {"1": "A_1", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_1"}, + "z": {"1": "A_1", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_1"}, + "z": {"1": "A_1", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_1"}, + "z": {"1": "A_1", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_1"}, + "z": {"1": "A_1", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_1"}, + "z": {"1": "A_1", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_1"}, + "z": {"1": "A_1", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_1"}, + "z": {"1": "A_1", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_1"}, + "z": {"1": "A_1", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_1"}, + "z": {"1": "A_2", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_1"}, + "z": {"1": "A_2", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_1"}, + "z": {"1": "A_2", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_1"}, + "z": {"1": "A_2", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_1"}, + "z": {"1": "A_2", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_1"}, + "z": {"1": "A_2", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_1"}, + "z": {"1": "A_2", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_1"}, + "z": {"1": "A_2", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_1"}, + "z": {"1": "A_2", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_1"}, + "z": {"1": "A_3", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_1"}, + "z": {"1": "A_3", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_1"}, + "z": {"1": "A_3", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_1"}, + "z": {"1": "A_3", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_1"}, + "z": {"1": "A_3", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_1"}, + "z": {"1": "A_3", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_1"}, + "z": {"1": "A_3", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_1"}, + "z": {"1": "A_3", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_1"}, + "z": {"1": "A_3", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_2"}, + "z": {"1": "A_1", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_2"}, + "z": {"1": "A_1", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_2"}, + "z": {"1": "A_1", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_2"}, + "z": {"1": "A_1", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_2"}, + "z": {"1": "A_1", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_2"}, + "z": {"1": "A_1", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_2"}, + "z": {"1": "A_1", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_2"}, + "z": {"1": "A_1", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_2"}, + "z": {"1": "A_1", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_2"}, + "z": {"1": "A_2", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_2"}, + "z": {"1": "A_2", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_2"}, + "z": {"1": "A_2", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_2"}, + "z": {"1": "A_2", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_2"}, + "z": {"1": "A_2", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_2"}, + "z": {"1": "A_2", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_2"}, + "z": {"1": "A_2", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_2"}, + "z": {"1": "A_2", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_2"}, + "z": {"1": "A_2", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_2"}, + "z": {"1": "A_3", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_2"}, + "z": {"1": "A_3", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_2"}, + "z": {"1": "A_3", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_2"}, + "z": {"1": "A_3", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_2"}, + "z": {"1": "A_3", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_2"}, + "z": {"1": "A_3", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_2"}, + "z": {"1": "A_3", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_2"}, + "z": {"1": "A_3", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_2"}, + "z": {"1": "A_3", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_3"}, + "z": {"1": "A_1", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_3"}, + "z": {"1": "A_1", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_3"}, + "z": {"1": "A_1", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_3"}, + "z": {"1": "A_1", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_3"}, + "z": {"1": "A_1", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_3"}, + "z": {"1": "A_1", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_3"}, + "z": {"1": "A_1", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_3"}, + "z": {"1": "A_1", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_3"}, + "z": {"1": "A_1", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_3"}, + "z": {"1": "A_2", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_3"}, + "z": {"1": "A_2", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_3"}, + "z": {"1": "A_2", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_3"}, + "z": {"1": "A_2", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_3"}, + "z": {"1": "A_2", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_3"}, + "z": {"1": "A_2", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_3"}, + "z": {"1": "A_2", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_3"}, + "z": {"1": "A_2", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_3"}, + "z": {"1": "A_2", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_3"}, + "z": {"1": "A_3", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_3"}, + "z": {"1": "A_3", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_3"}, + "z": {"1": "A_3", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_3"}, + "z": {"1": "A_3", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_3"}, + "z": {"1": "A_3", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_3"}, + "z": {"1": "A_3", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_3"}, + "z": {"1": "A_3", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_3"}, + "z": {"1": "A_3", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_3"}, + "z": {"1": "A_3", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_3", "3": "A_1"}, + "z": {"1": "A_1", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_3", "3": "A_1"}, + "z": {"1": "A_1", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_3", "3": "A_1"}, + "z": {"1": "A_1", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_3", "3": "A_1"}, + "z": {"1": "A_1", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_3", "3": "A_1"}, + "z": {"1": "A_1", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_3", "3": "A_1"}, + "z": {"1": "A_1", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_3", "3": "A_1"}, + "z": {"1": "A_1", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_3", "3": "A_1"}, + "z": {"1": "A_1", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_3", "3": "A_1"}, + "z": {"1": "A_1", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_3", "3": "A_1"}, + "z": {"1": "A_2", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_3", "3": "A_1"}, + "z": {"1": "A_2", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_3", "3": "A_1"}, + "z": {"1": "A_2", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_3", "3": "A_1"}, + "z": {"1": "A_2", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_3", "3": "A_1"}, + "z": {"1": "A_2", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_3", "3": "A_1"}, + "z": {"1": "A_2", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_3", "3": "A_1"}, + "z": {"1": "A_2", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_3", "3": "A_1"}, + "z": {"1": "A_2", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_3", "3": "A_1"}, + "z": {"1": "A_2", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_3", "3": "A_1"}, + "z": {"1": "A_3", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_3", "3": "A_1"}, + "z": {"1": "A_3", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_3", "3": "A_1"}, + "z": {"1": "A_3", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_3", "3": "A_1"}, + "z": {"1": "A_3", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_3", "3": "A_1"}, + "z": {"1": "A_3", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_3", "3": "A_1"}, + "z": {"1": "A_3", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_3", "3": "A_1"}, + "z": {"1": "A_3", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_3", "3": "A_1"}, + "z": {"1": "A_3", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_3", "3": "A_1"}, + "z": {"1": "A_3", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_3", "3": "A_2"}, + "z": {"1": "A_1", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_3", "3": "A_2"}, + "z": {"1": "A_1", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_3", "3": "A_2"}, + "z": {"1": "A_1", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_3", "3": "A_2"}, + "z": {"1": "A_1", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_3", "3": "A_2"}, + "z": {"1": "A_1", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_3", "3": "A_2"}, + "z": {"1": "A_1", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_3", "3": "A_2"}, + "z": {"1": "A_1", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_3", "3": "A_2"}, + "z": {"1": "A_1", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_3", "3": "A_2"}, + "z": {"1": "A_1", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_3", "3": "A_2"}, + "z": {"1": "A_2", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_3", "3": "A_2"}, + "z": {"1": "A_2", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_3", "3": "A_2"}, + "z": {"1": "A_2", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_3", "3": "A_2"}, + "z": {"1": "A_2", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_3", "3": "A_2"}, + "z": {"1": "A_2", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_3", "3": "A_2"}, + "z": {"1": "A_2", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_3", "3": "A_2"}, + "z": {"1": "A_2", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_3", "3": "A_2"}, + "z": {"1": "A_2", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_3", "3": "A_2"}, + "z": {"1": "A_2", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_3", "3": "A_2"}, + "z": {"1": "A_3", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_3", "3": "A_2"}, + "z": {"1": "A_3", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_3", "3": "A_2"}, + "z": {"1": "A_3", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_3", "3": "A_2"}, + "z": {"1": "A_3", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_3", "3": "A_2"}, + "z": {"1": "A_3", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_3", "3": "A_2"}, + "z": {"1": "A_3", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_3", "3": "A_2"}, + "z": {"1": "A_3", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_3", "3": "A_2"}, + "z": {"1": "A_3", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_3", "3": "A_2"}, + "z": {"1": "A_3", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_3", "3": "A_3"}, + "z": {"1": "A_1", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_3", "3": "A_3"}, + "z": {"1": "A_1", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_3", "3": "A_3"}, + "z": {"1": "A_1", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_3", "3": "A_3"}, + "z": {"1": "A_1", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_3", "3": "A_3"}, + "z": {"1": "A_1", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_3", "3": "A_3"}, + "z": {"1": "A_1", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_3", "3": "A_3"}, + "z": {"1": "A_1", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_3", "3": "A_3"}, + "z": {"1": "A_1", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_3", "3": "A_3"}, + "z": {"1": "A_1", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_3", "3": "A_3"}, + "z": {"1": "A_2", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_3", "3": "A_3"}, + "z": {"1": "A_2", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_3", "3": "A_3"}, + "z": {"1": "A_2", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_3", "3": "A_3"}, + "z": {"1": "A_2", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_3", "3": "A_3"}, + "z": {"1": "A_2", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_3", "3": "A_3"}, + "z": {"1": "A_2", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_3", "3": "A_3"}, + "z": {"1": "A_2", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_3", "3": "A_3"}, + "z": {"1": "A_2", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_3", "3": "A_3"}, + "z": {"1": "A_2", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_3", "3": "A_3"}, + "z": {"1": "A_3", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_3", "3": "A_3"}, + "z": {"1": "A_3", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_3", "3": "A_3"}, + "z": {"1": "A_3", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_3", "3": "A_3"}, + "z": {"1": "A_3", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_3", "3": "A_3"}, + "z": {"1": "A_3", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_3", "3": "A_3"}, + "z": {"1": "A_3", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_3", "3": "A_3"}, + "z": {"1": "A_3", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_3", "3": "A_3"}, + "z": {"1": "A_3", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_3", "3": "A_3"}, + "z": {"1": "A_3", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_1"}, + "z": {"1": "A_1", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_1"}, + "z": {"1": "A_1", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_1"}, + "z": {"1": "A_1", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_1"}, + "z": {"1": "A_1", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_1"}, + "z": {"1": "A_1", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_1"}, + "z": {"1": "A_1", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_1"}, + "z": {"1": "A_1", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_1"}, + "z": {"1": "A_1", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_1"}, + "z": {"1": "A_1", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_1"}, + "z": {"1": "A_2", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_1"}, + "z": {"1": "A_2", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_1"}, + "z": {"1": "A_2", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_1"}, + "z": {"1": "A_2", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_1"}, + "z": {"1": "A_2", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_1"}, + "z": {"1": "A_2", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_1"}, + "z": {"1": "A_2", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_1"}, + "z": {"1": "A_2", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_1"}, + "z": {"1": "A_2", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_1"}, + "z": {"1": "A_3", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_1"}, + "z": {"1": "A_3", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_1"}, + "z": {"1": "A_3", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_1"}, + "z": {"1": "A_3", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_1"}, + "z": {"1": "A_3", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_1"}, + "z": {"1": "A_3", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_1"}, + "z": {"1": "A_3", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_1"}, + "z": {"1": "A_3", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_1"}, + "z": {"1": "A_3", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_2"}, + "z": {"1": "A_1", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_2"}, + "z": {"1": "A_1", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_2"}, + "z": {"1": "A_1", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_2"}, + "z": {"1": "A_1", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_2"}, + "z": {"1": "A_1", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_2"}, + "z": {"1": "A_1", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_2"}, + "z": {"1": "A_1", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_2"}, + "z": {"1": "A_1", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_2"}, + "z": {"1": "A_1", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_2"}, + "z": {"1": "A_2", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_2"}, + "z": {"1": "A_2", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_2"}, + "z": {"1": "A_2", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_2"}, + "z": {"1": "A_2", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_2"}, + "z": {"1": "A_2", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_2"}, + "z": {"1": "A_2", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_2"}, + "z": {"1": "A_2", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_2"}, + "z": {"1": "A_2", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_2"}, + "z": {"1": "A_2", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_2"}, + "z": {"1": "A_3", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_2"}, + "z": {"1": "A_3", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_2"}, + "z": {"1": "A_3", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_2"}, + "z": {"1": "A_3", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_2"}, + "z": {"1": "A_3", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_2"}, + "z": {"1": "A_3", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_2"}, + "z": {"1": "A_3", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_2"}, + "z": {"1": "A_3", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_2"}, + "z": {"1": "A_3", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_3"}, + "z": {"1": "A_1", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_3"}, + "z": {"1": "A_1", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_3"}, + "z": {"1": "A_1", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_3"}, + "z": {"1": "A_1", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_3"}, + "z": {"1": "A_1", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_3"}, + "z": {"1": "A_1", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_3"}, + "z": {"1": "A_1", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_3"}, + "z": {"1": "A_1", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_3"}, + "z": {"1": "A_1", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_3"}, + "z": {"1": "A_2", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_3"}, + "z": {"1": "A_2", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_3"}, + "z": {"1": "A_2", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_3"}, + "z": {"1": "A_2", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_3"}, + "z": {"1": "A_2", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_3"}, + "z": {"1": "A_2", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_3"}, + "z": {"1": "A_2", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_3"}, + "z": {"1": "A_2", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_3"}, + "z": {"1": "A_2", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_3"}, + "z": {"1": "A_3", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_3"}, + "z": {"1": "A_3", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_3"}, + "z": {"1": "A_3", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_3"}, + "z": {"1": "A_3", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_3"}, + "z": {"1": "A_3", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_3"}, + "z": {"1": "A_3", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_3"}, + "z": {"1": "A_3", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_3"}, + "z": {"1": "A_3", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_3"}, + "z": {"1": "A_3", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_1"}, + "z": {"1": "A_1", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_1"}, + "z": {"1": "A_1", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_1"}, + "z": {"1": "A_1", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_1"}, + "z": {"1": "A_1", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_1"}, + "z": {"1": "A_1", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_1"}, + "z": {"1": "A_1", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_1"}, + "z": {"1": "A_1", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_1"}, + "z": {"1": "A_1", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_1"}, + "z": {"1": "A_1", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_1"}, + "z": {"1": "A_2", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_1"}, + "z": {"1": "A_2", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_1"}, + "z": {"1": "A_2", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_1"}, + "z": {"1": "A_2", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_1"}, + "z": {"1": "A_2", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_1"}, + "z": {"1": "A_2", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_1"}, + "z": {"1": "A_2", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_1"}, + "z": {"1": "A_2", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_1"}, + "z": {"1": "A_2", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_1"}, + "z": {"1": "A_3", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_1"}, + "z": {"1": "A_3", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_1"}, + "z": {"1": "A_3", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_1"}, + "z": {"1": "A_3", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_1"}, + "z": {"1": "A_3", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_1"}, + "z": {"1": "A_3", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_1"}, + "z": {"1": "A_3", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_1"}, + "z": {"1": "A_3", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_1"}, + "z": {"1": "A_3", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_2"}, + "z": {"1": "A_1", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_2"}, + "z": {"1": "A_1", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_2"}, + "z": {"1": "A_1", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_2"}, + "z": {"1": "A_1", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_2"}, + "z": {"1": "A_1", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_2"}, + "z": {"1": "A_1", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_2"}, + "z": {"1": "A_1", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_2"}, + "z": {"1": "A_1", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_2"}, + "z": {"1": "A_1", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_2"}, + "z": {"1": "A_2", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_2"}, + "z": {"1": "A_2", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_2"}, + "z": {"1": "A_2", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_2"}, + "z": {"1": "A_2", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_2"}, + "z": {"1": "A_2", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_2"}, + "z": {"1": "A_2", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_2"}, + "z": {"1": "A_2", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_2"}, + "z": {"1": "A_2", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_2"}, + "z": {"1": "A_2", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_2"}, + "z": {"1": "A_3", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_2"}, + "z": {"1": "A_3", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_2"}, + "z": {"1": "A_3", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_2"}, + "z": {"1": "A_3", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_2"}, + "z": {"1": "A_3", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_2"}, + "z": {"1": "A_3", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_2"}, + "z": {"1": "A_3", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_2"}, + "z": {"1": "A_3", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_2"}, + "z": {"1": "A_3", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_3"}, + "z": {"1": "A_1", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_3"}, + "z": {"1": "A_1", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_3"}, + "z": {"1": "A_1", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_3"}, + "z": {"1": "A_1", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_3"}, + "z": {"1": "A_1", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_3"}, + "z": {"1": "A_1", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_3"}, + "z": {"1": "A_1", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_3"}, + "z": {"1": "A_1", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_3"}, + "z": {"1": "A_1", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_3"}, + "z": {"1": "A_2", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_3"}, + "z": {"1": "A_2", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_3"}, + "z": {"1": "A_2", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_3"}, + "z": {"1": "A_2", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_3"}, + "z": {"1": "A_2", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_3"}, + "z": {"1": "A_2", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_3"}, + "z": {"1": "A_2", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_3"}, + "z": {"1": "A_2", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_3"}, + "z": {"1": "A_2", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_3"}, + "z": {"1": "A_3", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_3"}, + "z": {"1": "A_3", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_3"}, + "z": {"1": "A_3", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_3"}, + "z": {"1": "A_3", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_3"}, + "z": {"1": "A_3", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_3"}, + "z": {"1": "A_3", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_3"}, + "z": {"1": "A_3", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_3"}, + "z": {"1": "A_3", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_3"}, + "z": {"1": "A_3", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_1"}, + "z": {"1": "A_1", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_1"}, + "z": {"1": "A_1", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_1"}, + "z": {"1": "A_1", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_1"}, + "z": {"1": "A_1", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_1"}, + "z": {"1": "A_1", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_1"}, + "z": {"1": "A_1", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_1"}, + "z": {"1": "A_1", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_1"}, + "z": {"1": "A_1", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_1"}, + "z": {"1": "A_1", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_1"}, + "z": {"1": "A_2", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_1"}, + "z": {"1": "A_2", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_1"}, + "z": {"1": "A_2", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_1"}, + "z": {"1": "A_2", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_1"}, + "z": {"1": "A_2", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_1"}, + "z": {"1": "A_2", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_1"}, + "z": {"1": "A_2", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_1"}, + "z": {"1": "A_2", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_1"}, + "z": {"1": "A_2", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_1"}, + "z": {"1": "A_3", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_1"}, + "z": {"1": "A_3", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_1"}, + "z": {"1": "A_3", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_1"}, + "z": {"1": "A_3", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_1"}, + "z": {"1": "A_3", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_1"}, + "z": {"1": "A_3", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_1"}, + "z": {"1": "A_3", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_1"}, + "z": {"1": "A_3", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_1"}, + "z": {"1": "A_3", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_2"}, + "z": {"1": "A_1", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_2"}, + "z": {"1": "A_1", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_2"}, + "z": {"1": "A_1", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_2"}, + "z": {"1": "A_1", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_2"}, + "z": {"1": "A_1", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_2"}, + "z": {"1": "A_1", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_2"}, + "z": {"1": "A_1", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_2"}, + "z": {"1": "A_1", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_2"}, + "z": {"1": "A_1", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_2"}, + "z": {"1": "A_2", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_2"}, + "z": {"1": "A_2", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_2"}, + "z": {"1": "A_2", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_2"}, + "z": {"1": "A_2", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_2"}, + "z": {"1": "A_2", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_2"}, + "z": {"1": "A_2", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_2"}, + "z": {"1": "A_2", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_2"}, + "z": {"1": "A_2", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_2"}, + "z": {"1": "A_2", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_2"}, + "z": {"1": "A_3", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_2"}, + "z": {"1": "A_3", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_2"}, + "z": {"1": "A_3", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_2"}, + "z": {"1": "A_3", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_2"}, + "z": {"1": "A_3", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_2"}, + "z": {"1": "A_3", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_2"}, + "z": {"1": "A_3", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_2"}, + "z": {"1": "A_3", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_2"}, + "z": {"1": "A_3", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_3"}, + "z": {"1": "A_1", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_3"}, + "z": {"1": "A_1", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_3"}, + "z": {"1": "A_1", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_3"}, + "z": {"1": "A_1", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_3"}, + "z": {"1": "A_1", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_3"}, + "z": {"1": "A_1", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_3"}, + "z": {"1": "A_1", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_3"}, + "z": {"1": "A_1", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_3"}, + "z": {"1": "A_1", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_3"}, + "z": {"1": "A_2", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_3"}, + "z": {"1": "A_2", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_3"}, + "z": {"1": "A_2", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_3"}, + "z": {"1": "A_2", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_3"}, + "z": {"1": "A_2", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_3"}, + "z": {"1": "A_2", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_3"}, + "z": {"1": "A_2", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_3"}, + "z": {"1": "A_2", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_3"}, + "z": {"1": "A_2", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_3"}, + "z": {"1": "A_3", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_3"}, + "z": {"1": "A_3", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_3"}, + "z": {"1": "A_3", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_3"}, + "z": {"1": "A_3", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_3"}, + "z": {"1": "A_3", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_3"}, + "z": {"1": "A_3", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_3"}, + "z": {"1": "A_3", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_3"}, + "z": {"1": "A_3", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_3"}, + "z": {"1": "A_3", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_1", "3": "A_1"}, + "z": {"1": "A_1", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_1", "3": "A_1"}, + "z": {"1": "A_1", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_1", "3": "A_1"}, + "z": {"1": "A_1", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_1", "3": "A_1"}, + "z": {"1": "A_1", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_1", "3": "A_1"}, + "z": {"1": "A_1", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_1", "3": "A_1"}, + "z": {"1": "A_1", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_1", "3": "A_1"}, + "z": {"1": "A_1", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_1", "3": "A_1"}, + "z": {"1": "A_1", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_1", "3": "A_1"}, + "z": {"1": "A_1", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_1", "3": "A_1"}, + "z": {"1": "A_2", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_1", "3": "A_1"}, + "z": {"1": "A_2", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_1", "3": "A_1"}, + "z": {"1": "A_2", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_1", "3": "A_1"}, + "z": {"1": "A_2", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_1", "3": "A_1"}, + "z": {"1": "A_2", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_1", "3": "A_1"}, + "z": {"1": "A_2", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_1", "3": "A_1"}, + "z": {"1": "A_2", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_1", "3": "A_1"}, + "z": {"1": "A_2", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_1", "3": "A_1"}, + "z": {"1": "A_2", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_1", "3": "A_1"}, + "z": {"1": "A_3", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_1", "3": "A_1"}, + "z": {"1": "A_3", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_1", "3": "A_1"}, + "z": {"1": "A_3", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_1", "3": "A_1"}, + "z": {"1": "A_3", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_1", "3": "A_1"}, + "z": {"1": "A_3", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_1", "3": "A_1"}, + "z": {"1": "A_3", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_1", "3": "A_1"}, + "z": {"1": "A_3", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_1", "3": "A_1"}, + "z": {"1": "A_3", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_1", "3": "A_1"}, + "z": {"1": "A_3", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_1", "3": "A_2"}, + "z": {"1": "A_1", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_1", "3": "A_2"}, + "z": {"1": "A_1", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_1", "3": "A_2"}, + "z": {"1": "A_1", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_1", "3": "A_2"}, + "z": {"1": "A_1", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_1", "3": "A_2"}, + "z": {"1": "A_1", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_1", "3": "A_2"}, + "z": {"1": "A_1", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_1", "3": "A_2"}, + "z": {"1": "A_1", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_1", "3": "A_2"}, + "z": {"1": "A_1", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_1", "3": "A_2"}, + "z": {"1": "A_1", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_1", "3": "A_2"}, + "z": {"1": "A_2", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_1", "3": "A_2"}, + "z": {"1": "A_2", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_1", "3": "A_2"}, + "z": {"1": "A_2", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_1", "3": "A_2"}, + "z": {"1": "A_2", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_1", "3": "A_2"}, + "z": {"1": "A_2", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_1", "3": "A_2"}, + "z": {"1": "A_2", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_1", "3": "A_2"}, + "z": {"1": "A_2", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_1", "3": "A_2"}, + "z": {"1": "A_2", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_1", "3": "A_2"}, + "z": {"1": "A_2", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_1", "3": "A_2"}, + "z": {"1": "A_3", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_1", "3": "A_2"}, + "z": {"1": "A_3", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_1", "3": "A_2"}, + "z": {"1": "A_3", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_1", "3": "A_2"}, + "z": {"1": "A_3", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_1", "3": "A_2"}, + "z": {"1": "A_3", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_1", "3": "A_2"}, + "z": {"1": "A_3", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_1", "3": "A_2"}, + "z": {"1": "A_3", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_1", "3": "A_2"}, + "z": {"1": "A_3", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_1", "3": "A_2"}, + "z": {"1": "A_3", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_1", "3": "A_3"}, + "z": {"1": "A_1", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_1", "3": "A_3"}, + "z": {"1": "A_1", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_1", "3": "A_3"}, + "z": {"1": "A_1", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_1", "3": "A_3"}, + "z": {"1": "A_1", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_1", "3": "A_3"}, + "z": {"1": "A_1", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_1", "3": "A_3"}, + "z": {"1": "A_1", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_1", "3": "A_3"}, + "z": {"1": "A_1", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_1", "3": "A_3"}, + "z": {"1": "A_1", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_1", "3": "A_3"}, + "z": {"1": "A_1", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_1", "3": "A_3"}, + "z": {"1": "A_2", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_1", "3": "A_3"}, + "z": {"1": "A_2", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_1", "3": "A_3"}, + "z": {"1": "A_2", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_1", "3": "A_3"}, + "z": {"1": "A_2", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_1", "3": "A_3"}, + "z": {"1": "A_2", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_1", "3": "A_3"}, + "z": {"1": "A_2", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_1", "3": "A_3"}, + "z": {"1": "A_2", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_1", "3": "A_3"}, + "z": {"1": "A_2", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_1", "3": "A_3"}, + "z": {"1": "A_2", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_1", "3": "A_3"}, + "z": {"1": "A_3", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_1", "3": "A_3"}, + "z": {"1": "A_3", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_1", "3": "A_3"}, + "z": {"1": "A_3", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_1", "3": "A_3"}, + "z": {"1": "A_3", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_1", "3": "A_3"}, + "z": {"1": "A_3", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_1", "3": "A_3"}, + "z": {"1": "A_3", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_1", "3": "A_3"}, + "z": {"1": "A_3", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_1", "3": "A_3"}, + "z": {"1": "A_3", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_1", "3": "A_3"}, + "z": {"1": "A_3", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_2", "3": "A_1"}, + "z": {"1": "A_1", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_2", "3": "A_1"}, + "z": {"1": "A_1", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_2", "3": "A_1"}, + "z": {"1": "A_1", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_2", "3": "A_1"}, + "z": {"1": "A_1", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_2", "3": "A_1"}, + "z": {"1": "A_1", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_2", "3": "A_1"}, + "z": {"1": "A_1", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_2", "3": "A_1"}, + "z": {"1": "A_1", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_2", "3": "A_1"}, + "z": {"1": "A_1", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_2", "3": "A_1"}, + "z": {"1": "A_1", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_2", "3": "A_1"}, + "z": {"1": "A_2", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_2", "3": "A_1"}, + "z": {"1": "A_2", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_2", "3": "A_1"}, + "z": {"1": "A_2", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_2", "3": "A_1"}, + "z": {"1": "A_2", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_2", "3": "A_1"}, + "z": {"1": "A_2", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_2", "3": "A_1"}, + "z": {"1": "A_2", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_2", "3": "A_1"}, + "z": {"1": "A_2", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_2", "3": "A_1"}, + "z": {"1": "A_2", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_2", "3": "A_1"}, + "z": {"1": "A_2", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_2", "3": "A_1"}, + "z": {"1": "A_3", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_2", "3": "A_1"}, + "z": {"1": "A_3", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_2", "3": "A_1"}, + "z": {"1": "A_3", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_2", "3": "A_1"}, + "z": {"1": "A_3", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_2", "3": "A_1"}, + "z": {"1": "A_3", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_2", "3": "A_1"}, + "z": {"1": "A_3", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_2", "3": "A_1"}, + "z": {"1": "A_3", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_2", "3": "A_1"}, + "z": {"1": "A_3", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_2", "3": "A_1"}, + "z": {"1": "A_3", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_2", "3": "A_2"}, + "z": {"1": "A_1", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_2", "3": "A_2"}, + "z": {"1": "A_1", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_2", "3": "A_2"}, + "z": {"1": "A_1", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_2", "3": "A_2"}, + "z": {"1": "A_1", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_2", "3": "A_2"}, + "z": {"1": "A_1", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_2", "3": "A_2"}, + "z": {"1": "A_1", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_2", "3": "A_2"}, + "z": {"1": "A_1", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_2", "3": "A_2"}, + "z": {"1": "A_1", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_2", "3": "A_2"}, + "z": {"1": "A_1", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_2", "3": "A_2"}, + "z": {"1": "A_2", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_2", "3": "A_2"}, + "z": {"1": "A_2", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_2", "3": "A_2"}, + "z": {"1": "A_2", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_2", "3": "A_2"}, + "z": {"1": "A_2", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_2", "3": "A_2"}, + "z": {"1": "A_2", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_2", "3": "A_2"}, + "z": {"1": "A_2", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_2", "3": "A_2"}, + "z": {"1": "A_2", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_2", "3": "A_2"}, + "z": {"1": "A_2", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_2", "3": "A_2"}, + "z": {"1": "A_2", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_2", "3": "A_2"}, + "z": {"1": "A_3", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_2", "3": "A_2"}, + "z": {"1": "A_3", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_2", "3": "A_2"}, + "z": {"1": "A_3", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_2", "3": "A_2"}, + "z": {"1": "A_3", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_2", "3": "A_2"}, + "z": {"1": "A_3", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_2", "3": "A_2"}, + "z": {"1": "A_3", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_2", "3": "A_2"}, + "z": {"1": "A_3", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_2", "3": "A_2"}, + "z": {"1": "A_3", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_2", "3": "A_2"}, + "z": {"1": "A_3", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_2", "3": "A_3"}, + "z": {"1": "A_1", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_2", "3": "A_3"}, + "z": {"1": "A_1", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_2", "3": "A_3"}, + "z": {"1": "A_1", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_2", "3": "A_3"}, + "z": {"1": "A_1", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_2", "3": "A_3"}, + "z": {"1": "A_1", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_2", "3": "A_3"}, + "z": {"1": "A_1", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_2", "3": "A_3"}, + "z": {"1": "A_1", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_2", "3": "A_3"}, + "z": {"1": "A_1", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_2", "3": "A_3"}, + "z": {"1": "A_1", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_2", "3": "A_3"}, + "z": {"1": "A_2", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_2", "3": "A_3"}, + "z": {"1": "A_2", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_2", "3": "A_3"}, + "z": {"1": "A_2", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_2", "3": "A_3"}, + "z": {"1": "A_2", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_2", "3": "A_3"}, + "z": {"1": "A_2", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_2", "3": "A_3"}, + "z": {"1": "A_2", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_2", "3": "A_3"}, + "z": {"1": "A_2", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_2", "3": "A_3"}, + "z": {"1": "A_2", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_2", "3": "A_3"}, + "z": {"1": "A_2", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_2", "3": "A_3"}, + "z": {"1": "A_3", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_2", "3": "A_3"}, + "z": {"1": "A_3", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_2", "3": "A_3"}, + "z": {"1": "A_3", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_2", "3": "A_3"}, + "z": {"1": "A_3", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_2", "3": "A_3"}, + "z": {"1": "A_3", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_2", "3": "A_3"}, + "z": {"1": "A_3", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_2", "3": "A_3"}, + "z": {"1": "A_3", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_2", "3": "A_3"}, + "z": {"1": "A_3", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_2", "3": "A_3"}, + "z": {"1": "A_3", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_3", "3": "A_1"}, + "z": {"1": "A_1", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_3", "3": "A_1"}, + "z": {"1": "A_1", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_3", "3": "A_1"}, + "z": {"1": "A_1", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_3", "3": "A_1"}, + "z": {"1": "A_1", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_3", "3": "A_1"}, + "z": {"1": "A_1", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_3", "3": "A_1"}, + "z": {"1": "A_1", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_3", "3": "A_1"}, + "z": {"1": "A_1", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_3", "3": "A_1"}, + "z": {"1": "A_1", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_3", "3": "A_1"}, + "z": {"1": "A_1", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_3", "3": "A_1"}, + "z": {"1": "A_2", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_3", "3": "A_1"}, + "z": {"1": "A_2", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_3", "3": "A_1"}, + "z": {"1": "A_2", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_3", "3": "A_1"}, + "z": {"1": "A_2", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_3", "3": "A_1"}, + "z": {"1": "A_2", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_3", "3": "A_1"}, + "z": {"1": "A_2", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_3", "3": "A_1"}, + "z": {"1": "A_2", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_3", "3": "A_1"}, + "z": {"1": "A_2", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_3", "3": "A_1"}, + "z": {"1": "A_2", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_3", "3": "A_1"}, + "z": {"1": "A_3", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_3", "3": "A_1"}, + "z": {"1": "A_3", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_3", "3": "A_1"}, + "z": {"1": "A_3", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_3", "3": "A_1"}, + "z": {"1": "A_3", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_3", "3": "A_1"}, + "z": {"1": "A_3", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_3", "3": "A_1"}, + "z": {"1": "A_3", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_3", "3": "A_1"}, + "z": {"1": "A_3", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_3", "3": "A_1"}, + "z": {"1": "A_3", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_3", "3": "A_1"}, + "z": {"1": "A_3", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_3", "3": "A_2"}, + "z": {"1": "A_1", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_3", "3": "A_2"}, + "z": {"1": "A_1", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_3", "3": "A_2"}, + "z": {"1": "A_1", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_3", "3": "A_2"}, + "z": {"1": "A_1", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_3", "3": "A_2"}, + "z": {"1": "A_1", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_3", "3": "A_2"}, + "z": {"1": "A_1", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_3", "3": "A_2"}, + "z": {"1": "A_1", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_3", "3": "A_2"}, + "z": {"1": "A_1", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_3", "3": "A_2"}, + "z": {"1": "A_1", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_3", "3": "A_2"}, + "z": {"1": "A_2", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_3", "3": "A_2"}, + "z": {"1": "A_2", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_3", "3": "A_2"}, + "z": {"1": "A_2", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_3", "3": "A_2"}, + "z": {"1": "A_2", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_3", "3": "A_2"}, + "z": {"1": "A_2", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_3", "3": "A_2"}, + "z": {"1": "A_2", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_3", "3": "A_2"}, + "z": {"1": "A_2", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_3", "3": "A_2"}, + "z": {"1": "A_2", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_3", "3": "A_2"}, + "z": {"1": "A_2", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_3", "3": "A_2"}, + "z": {"1": "A_3", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_3", "3": "A_2"}, + "z": {"1": "A_3", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_3", "3": "A_2"}, + "z": {"1": "A_3", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_3", "3": "A_2"}, + "z": {"1": "A_3", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_3", "3": "A_2"}, + "z": {"1": "A_3", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_3", "3": "A_2"}, + "z": {"1": "A_3", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_3", "3": "A_2"}, + "z": {"1": "A_3", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_3", "3": "A_2"}, + "z": {"1": "A_3", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_3", "3": "A_2"}, + "z": {"1": "A_3", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_3", "3": "A_3"}, + "z": {"1": "A_1", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_3", "3": "A_3"}, + "z": {"1": "A_1", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_3", "3": "A_3"}, + "z": {"1": "A_1", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_3", "3": "A_3"}, + "z": {"1": "A_1", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_3", "3": "A_3"}, + "z": {"1": "A_1", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_3", "3": "A_3"}, + "z": {"1": "A_1", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_3", "3": "A_3"}, + "z": {"1": "A_1", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_3", "3": "A_3"}, + "z": {"1": "A_1", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_3", "3": "A_3"}, + "z": {"1": "A_1", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_3", "3": "A_3"}, + "z": {"1": "A_2", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_3", "3": "A_3"}, + "z": {"1": "A_2", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_3", "3": "A_3"}, + "z": {"1": "A_2", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_3", "3": "A_3"}, + "z": {"1": "A_2", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_3", "3": "A_3"}, + "z": {"1": "A_2", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_3", "3": "A_3"}, + "z": {"1": "A_2", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_3", "3": "A_3"}, + "z": {"1": "A_2", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_3", "3": "A_3"}, + "z": {"1": "A_2", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_3", "3": "A_3"}, + "z": {"1": "A_2", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_3", "3": "A_3"}, + "z": {"1": "A_3", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_3", "3": "A_3"}, + "z": {"1": "A_3", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_3", "3": "A_3"}, + "z": {"1": "A_3", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_3", "3": "A_3"}, + "z": {"1": "A_3", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_3", "3": "A_3"}, + "z": {"1": "A_3", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_3", "3": "A_3"}, + "z": {"1": "A_3", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_3", "3": "A_3"}, + "z": {"1": "A_3", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_3", "3": "A_3"}, + "z": {"1": "A_3", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_3", "3": "A_3"}, + "z": {"1": "A_3", "2": "A_3", "3": "A_3"}} +] diff --git a/tests/custom/permutations/permInverse/11/00.essence b/tests/custom/permutations/permInverse/11/00.essence new file mode 100644 index 0000000000..a591580d3e --- /dev/null +++ b/tests/custom/permutations/permInverse/11/00.essence @@ -0,0 +1,3 @@ +letting A be new type of size 3 +find x : matrix [int(1..2)] of A +find y : matrix [int(1..3)] of A diff --git a/tests/custom/permutations/permInverse/11/run.sh b/tests/custom/permutations/permInverse/11/run.sh new file mode 100755 index 0000000000..b9e09b1816 --- /dev/null +++ b/tests/custom/permutations/permInverse/11/run.sh @@ -0,0 +1,21 @@ + +rm -rf conjure-output + +conjure solve 00.essence --output-format=json --solutions-in-one-file --number-of-solutions=all --line-width=50 --copy-solutions=no --unnamed-symmetry-breaking=Quick-AllPermutations-Independently + +# conjure solve 00.essence --output-format=json --solutions-in-one-file --number-of-solutions=all --line-width=50 --copy-solutions=no --unnamed-symmetry-breaking=full +# conjure solve 00.essence --output-format=json --solutions-in-one-file --number-of-solutions=all --line-width=50 --copy-solutions=no --unnamed-symmetry-breaking=Quick-Consecutive-Independently +# conjure solve 00.essence --output-format=json --solutions-in-one-file --number-of-solutions=all --line-width=50 --copy-solutions=no --unnamed-symmetry-breaking=Quick-Consecutive-Altogether +# conjure solve 00.essence --output-format=json --solutions-in-one-file --number-of-solutions=all --line-width=50 --copy-solutions=no --unnamed-symmetry-breaking=Quick-AllPairs-Independently +# conjure solve 00.essence --output-format=json --solutions-in-one-file --number-of-solutions=all --line-width=50 --copy-solutions=no --unnamed-symmetry-breaking=Quick-AllPairs-Altogether +# conjure solve 00.essence --output-format=json --solutions-in-one-file --number-of-solutions=all --line-width=50 --copy-solutions=no --unnamed-symmetry-breaking=Quick-AllPermutations-Independently +# conjure solve 00.essence --output-format=json --solutions-in-one-file --number-of-solutions=all --line-width=50 --copy-solutions=no --unnamed-symmetry-breaking=Quick-AllPermutations-Altogether +# conjure solve 00.essence --output-format=json --solutions-in-one-file --number-of-solutions=all --line-width=50 --copy-solutions=no --unnamed-symmetry-breaking=Complete-Consecutive-Independently +# conjure solve 00.essence --output-format=json --solutions-in-one-file --number-of-solutions=all --line-width=50 --copy-solutions=no --unnamed-symmetry-breaking=Complete-Consecutive-Altogether +# conjure solve 00.essence --output-format=json --solutions-in-one-file --number-of-solutions=all --line-width=50 --copy-solutions=no --unnamed-symmetry-breaking=Complete-AllPairs-Independently +# conjure solve 00.essence --output-format=json --solutions-in-one-file --number-of-solutions=all --line-width=50 --copy-solutions=no --unnamed-symmetry-breaking=Complete-AllPairs-Altogether +# conjure solve 00.essence --output-format=json --solutions-in-one-file --number-of-solutions=all --line-width=50 --copy-solutions=no --unnamed-symmetry-breaking=Complete-AllPermutations-Independently +# conjure solve 00.essence --output-format=json --solutions-in-one-file --number-of-solutions=all --line-width=50 --copy-solutions=no --unnamed-symmetry-breaking=Complete-AllPermutations-Altogether + +cat conjure-output/model000001.solutions.json +rm -rf conjure-output diff --git a/tests/custom/permutations/permInverse/11/stderr.expected b/tests/custom/permutations/permInverse/11/stderr.expected new file mode 100644 index 0000000000..48b82ef19e --- /dev/null +++ b/tests/custom/permutations/permInverse/11/stderr.expected @@ -0,0 +1,4 @@ +Adding the following unnamed symmetry breaking constraints: + such that + and([quickPermutationOrder((x, y), [q1; int(1)]) + | q1 : permutation of A]) diff --git a/tests/custom/permutations/permInverse/11/stdout.expected b/tests/custom/permutations/permInverse/11/stdout.expected new file mode 100644 index 0000000000..f035644b7b --- /dev/null +++ b/tests/custom/permutations/permInverse/11/stdout.expected @@ -0,0 +1,171 @@ +Generating models for 00.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: conjure-output/model000001.eprime +Running minion for domain filtering. +Running solver: minion +[ +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_3", "3": "A_3"}} +] diff --git a/tests/custom/permutations/permInverse/12/00.essence b/tests/custom/permutations/permInverse/12/00.essence new file mode 100644 index 0000000000..a591580d3e --- /dev/null +++ b/tests/custom/permutations/permInverse/12/00.essence @@ -0,0 +1,3 @@ +letting A be new type of size 3 +find x : matrix [int(1..2)] of A +find y : matrix [int(1..3)] of A diff --git a/tests/custom/permutations/permInverse/12/run.sh b/tests/custom/permutations/permInverse/12/run.sh new file mode 100755 index 0000000000..7d49294220 --- /dev/null +++ b/tests/custom/permutations/permInverse/12/run.sh @@ -0,0 +1,21 @@ + +rm -rf conjure-output + +conjure solve 00.essence --output-format=json --solutions-in-one-file --number-of-solutions=all --line-width=50 --copy-solutions=no --unnamed-symmetry-breaking=Complete-AllPermutations-Independently + +# conjure solve 00.essence --output-format=json --solutions-in-one-file --number-of-solutions=all --line-width=50 --copy-solutions=no --unnamed-symmetry-breaking=full +# conjure solve 00.essence --output-format=json --solutions-in-one-file --number-of-solutions=all --line-width=50 --copy-solutions=no --unnamed-symmetry-breaking=Quick-Consecutive-Independently +# conjure solve 00.essence --output-format=json --solutions-in-one-file --number-of-solutions=all --line-width=50 --copy-solutions=no --unnamed-symmetry-breaking=Quick-Consecutive-Altogether +# conjure solve 00.essence --output-format=json --solutions-in-one-file --number-of-solutions=all --line-width=50 --copy-solutions=no --unnamed-symmetry-breaking=Quick-AllPairs-Independently +# conjure solve 00.essence --output-format=json --solutions-in-one-file --number-of-solutions=all --line-width=50 --copy-solutions=no --unnamed-symmetry-breaking=Quick-AllPairs-Altogether +# conjure solve 00.essence --output-format=json --solutions-in-one-file --number-of-solutions=all --line-width=50 --copy-solutions=no --unnamed-symmetry-breaking=Quick-AllPermutations-Independently +# conjure solve 00.essence --output-format=json --solutions-in-one-file --number-of-solutions=all --line-width=50 --copy-solutions=no --unnamed-symmetry-breaking=Quick-AllPermutations-Altogether +# conjure solve 00.essence --output-format=json --solutions-in-one-file --number-of-solutions=all --line-width=50 --copy-solutions=no --unnamed-symmetry-breaking=Complete-Consecutive-Independently +# conjure solve 00.essence --output-format=json --solutions-in-one-file --number-of-solutions=all --line-width=50 --copy-solutions=no --unnamed-symmetry-breaking=Complete-Consecutive-Altogether +# conjure solve 00.essence --output-format=json --solutions-in-one-file --number-of-solutions=all --line-width=50 --copy-solutions=no --unnamed-symmetry-breaking=Complete-AllPairs-Independently +# conjure solve 00.essence --output-format=json --solutions-in-one-file --number-of-solutions=all --line-width=50 --copy-solutions=no --unnamed-symmetry-breaking=Complete-AllPairs-Altogether +# conjure solve 00.essence --output-format=json --solutions-in-one-file --number-of-solutions=all --line-width=50 --copy-solutions=no --unnamed-symmetry-breaking=Complete-AllPermutations-Independently +# conjure solve 00.essence --output-format=json --solutions-in-one-file --number-of-solutions=all --line-width=50 --copy-solutions=no --unnamed-symmetry-breaking=Complete-AllPermutations-Altogether + +cat conjure-output/model000001.solutions.json +rm -rf conjure-output diff --git a/tests/custom/permutations/permInverse/12/stderr.expected b/tests/custom/permutations/permInverse/12/stderr.expected new file mode 100644 index 0000000000..d300ba3836 --- /dev/null +++ b/tests/custom/permutations/permInverse/12/stderr.expected @@ -0,0 +1,3 @@ +Adding the following unnamed symmetry breaking constraints: + such that + and([(x, y) .<= transform(q1, (x, y)) | q1 : permutation of A]) diff --git a/tests/custom/permutations/permInverse/12/stdout.expected b/tests/custom/permutations/permInverse/12/stdout.expected new file mode 100644 index 0000000000..f035644b7b --- /dev/null +++ b/tests/custom/permutations/permInverse/12/stdout.expected @@ -0,0 +1,171 @@ +Generating models for 00.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: conjure-output/model000001.eprime +Running minion for domain filtering. +Running solver: minion +[ +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_1"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_1", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_2", "2": "A_3", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_1", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_1", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_1", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_2", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_2", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_2", "3": "A_3"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_3", "3": "A_1"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_3", "3": "A_2"}} +, +{"A": ["A_1", "A_2", "A_3"], + "x": {"1": "A_1", "2": "A_2"}, + "y": {"1": "A_3", "2": "A_3", "3": "A_3"}} +] From 354fa43b1fab274dbee363f64e3da156620b9dd5 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?=C3=96zg=C3=BCr=20Akg=C3=BCn?= Date: Fri, 22 Nov 2024 10:54:44 +0000 Subject: [PATCH 197/229] a set example as well, not using transform on sets yet --- .../permInverse/13-sets/00.essence | 7 ++++ .../permutations/permInverse/13-sets/run.sh | 7 ++++ .../permInverse/13-sets/stdout.expected | 42 +++++++++++++++++++ 3 files changed, 56 insertions(+) create mode 100644 tests/custom/permutations/permInverse/13-sets/00.essence create mode 100755 tests/custom/permutations/permInverse/13-sets/run.sh create mode 100644 tests/custom/permutations/permInverse/13-sets/stdout.expected diff --git a/tests/custom/permutations/permInverse/13-sets/00.essence b/tests/custom/permutations/permInverse/13-sets/00.essence new file mode 100644 index 0000000000..64cbda06b7 --- /dev/null +++ b/tests/custom/permutations/permInverse/13-sets/00.essence @@ -0,0 +1,7 @@ +letting A be new type of size 3 +find x : set of A + +find p : permutation (numMoved 3) of A +$ such that x .<= transform(p, x) + +such that x .<= toSet([ transform(p, i) | i <- x]) diff --git a/tests/custom/permutations/permInverse/13-sets/run.sh b/tests/custom/permutations/permInverse/13-sets/run.sh new file mode 100755 index 0000000000..d048cc20b0 --- /dev/null +++ b/tests/custom/permutations/permInverse/13-sets/run.sh @@ -0,0 +1,7 @@ + +rm -rf conjure-output + +conjure solve 00.essence --output-format=json --solutions-in-one-file --number-of-solutions=all --line-width=50 --copy-solutions=no --channelling=no --responses=1,1 + +cat conjure-output/model000001.solutions.json +rm -rf conjure-output diff --git a/tests/custom/permutations/permInverse/13-sets/stdout.expected b/tests/custom/permutations/permInverse/13-sets/stdout.expected new file mode 100644 index 0000000000..fa9610a1df --- /dev/null +++ b/tests/custom/permutations/permInverse/13-sets/stdout.expected @@ -0,0 +1,42 @@ +Generating models for 00.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: conjure-output/model000001.eprime +Running minion for domain filtering. +Running solver: minion +[ +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2", "A_3"]], "x": []} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3", "A_2"]], "x": []} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2", "A_3"]], "x": ["A_2"]} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2", "A_3"]], "x": ["A_1"]} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3", "A_2"]], "x": ["A_1"]} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3", "A_2"]], + "x": ["A_1", "A_3"]} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2", "A_3"]], + "x": ["A_1", "A_2"]} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3", "A_2"]], + "x": ["A_1", "A_2"]} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_2", "A_3"]], + "x": ["A_1", "A_2", "A_3"]} +, +{"A": ["A_1", "A_2", "A_3"], + "p": [["A_1", "A_3", "A_2"]], + "x": ["A_1", "A_2", "A_3"]} +] From cb41d3bcfaef6d0c557f80637398656af4c56869 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?=C3=96zg=C3=BCr=20Akg=C3=BCn?= Date: Fri, 22 Nov 2024 11:02:16 +0000 Subject: [PATCH 198/229] making sure the representations all work and adding some comments --- .../permInverse/13-sets/00.essence | 10 ++++++++ .../permutations/permInverse/13-sets/run.sh | 23 +++++++++++++++++-- .../permInverse/13-sets/stdout.expected | 18 +++++++++++++++ 3 files changed, 49 insertions(+), 2 deletions(-) diff --git a/tests/custom/permutations/permInverse/13-sets/00.essence b/tests/custom/permutations/permInverse/13-sets/00.essence index 64cbda06b7..31150bef74 100644 --- a/tests/custom/permutations/permInverse/13-sets/00.essence +++ b/tests/custom/permutations/permInverse/13-sets/00.essence @@ -4,4 +4,14 @@ find x : set of A find p : permutation (numMoved 3) of A $ such that x .<= transform(p, x) +$ the above rule, Oz thinks can be written recursively for all types +$ produce aux for the rhs +$ forAll, forAll, forAll +$ membership constraints + +$ find x' : ... +$ such that forAll i in x . transform(p, i) in x' +$ such that forAll i in x' . transform(permInverse(p), i) in x + such that x .<= toSet([ transform(p, i) | i <- x]) + diff --git a/tests/custom/permutations/permInverse/13-sets/run.sh b/tests/custom/permutations/permInverse/13-sets/run.sh index d048cc20b0..dbdd09cc42 100755 --- a/tests/custom/permutations/permInverse/13-sets/run.sh +++ b/tests/custom/permutations/permInverse/13-sets/run.sh @@ -1,7 +1,26 @@ rm -rf conjure-output +conjure solve 00.essence --output-format=json --solutions-in-one-file --number-of-solutions=all --line-width=50 --copy-solutions=no --channelling=no --responses=1,1 +mv conjure-output/model000001.solutions.json 1.sols -conjure solve 00.essence --output-format=json --solutions-in-one-file --number-of-solutions=all --line-width=50 --copy-solutions=no --channelling=no --responses=1,1 +rm -rf conjure-output +conjure solve 00.essence --output-format=json --solutions-in-one-file --number-of-solutions=all --line-width=50 --copy-solutions=no --channelling=no --responses=2,2 +mv conjure-output/model000001.solutions.json 2.sols + +rm -rf conjure-output +conjure solve 00.essence --output-format=json --solutions-in-one-file --number-of-solutions=all --line-width=50 --copy-solutions=no --channelling=no --responses=3,3 +mv conjure-output/model000001.solutions.json 3.sols -cat conjure-output/model000001.solutions.json rm -rf conjure-output +conjure solve 00.essence --output-format=json --solutions-in-one-file --number-of-solutions=all --line-width=50 --copy-solutions=no --channelling=no --responses=4,4 +cp conjure-output/model000001.solutions.json 4.sols + +cat conjure-output/model000001.solutions.json +diff 1.sols 2.sols +diff 1.sols 3.sols +diff 1.sols 4.sols +diff 2.sols 3.sols +diff 2.sols 4.sols +diff 3.sols 4.sols + +rm -rf conjure-output *.sols diff --git a/tests/custom/permutations/permInverse/13-sets/stdout.expected b/tests/custom/permutations/permInverse/13-sets/stdout.expected index fa9610a1df..e7fa8369dc 100644 --- a/tests/custom/permutations/permInverse/13-sets/stdout.expected +++ b/tests/custom/permutations/permInverse/13-sets/stdout.expected @@ -4,6 +4,24 @@ Saved under: conjure-output Savile Row: conjure-output/model000001.eprime Running minion for domain filtering. Running solver: minion +Generating models for 00.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: conjure-output/model000001.eprime +Running minion for domain filtering. +Running solver: minion +Generating models for 00.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: conjure-output/model000001.eprime +Running minion for domain filtering. +Running solver: minion +Generating models for 00.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: conjure-output/model000001.eprime +Running minion for domain filtering. +Running solver: minion [ {"A": ["A_1", "A_2", "A_3"], "p": [["A_1", "A_2", "A_3"]], "x": []} From 121b884ca478999ed42d84fc4ac7375a29877736 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?=C3=96zg=C3=BCr=20Akg=C3=BCn?= Date: Fri, 29 Nov 2024 19:06:31 +0000 Subject: [PATCH 199/229] transform and quickPermutationOrder to always carry lists of permutations --- src/Conjure/Language/Expression/Op.hs | 4 +- .../Expression/Op/QuickPermutationOrder.hs | 35 +++----- .../Language/Expression/Op/Transform.hs | 85 ++++++++++--------- src/Conjure/Language/Lenses.hs | 4 +- src/Conjure/Rules/Transform.hs | 10 +-- 5 files changed, 68 insertions(+), 70 deletions(-) diff --git a/src/Conjure/Language/Expression/Op.hs b/src/Conjure/Language/Expression/Op.hs index eccd8c6cae..debb79a372 100644 --- a/src/Conjure/Language/Expression/Op.hs +++ b/src/Conjure/Language/Expression/Op.hs @@ -104,7 +104,7 @@ mkOp op xs = case op of (arg xs 1 "allDiffExcept") L_catchUndef -> inject $ MkOpCatchUndef $ OpCatchUndef (arg xs 0 "catchUndef") (arg xs 1 "catchUndef") - L_quickPermutationOrder -> inject $ MkOpQuickPermutationOrder $ OpQuickPermutationOrder (arg xs 0 "quickPermutationOrder") (arg xs 1 "quickPermutationOrder") + L_quickPermutationOrder -> inject $ MkOpQuickPermutationOrder $ OpQuickPermutationOrder (arg xs 0 "quickPermutationOrder") (arg xs 1 "quickPermutationOrder" |> listOut |> fromMaybe (bug "")) L_dontCare -> inject $ MkOpDontCare $ OpDontCare (arg xs 0 "dontCare") L_toSet -> inject $ MkOpToSet $ OpToSet False (arg xs 0 "toSet") L_toMSet -> inject $ MkOpToMSet $ OpToMSet (arg xs 0 "toMSet") @@ -113,7 +113,7 @@ mkOp op xs = case op of L_min -> inject $ MkOpMin $ OpMin (arg xs 0 "min") L_image -> inject $ MkOpImage $ OpImage (arg xs 0 "image") (arg xs 1 "image") - L_transform -> inject $ MkOpTransform $ OpTransform (arg xs 0 "transform") + L_transform -> inject $ MkOpTransform $ OpTransform (arg xs 0 "transform" |> listOut |> fromMaybe (bug "")) (arg xs 1 "transform") L_imageSet -> inject $ MkOpImageSet $ OpImageSet (arg xs 0 "imageSet") diff --git a/src/Conjure/Language/Expression/Op/QuickPermutationOrder.hs b/src/Conjure/Language/Expression/Op/QuickPermutationOrder.hs index f0881f6d7e..fb40919ba0 100644 --- a/src/Conjure/Language/Expression/Op/QuickPermutationOrder.hs +++ b/src/Conjure/Language/Expression/Op/QuickPermutationOrder.hs @@ -1,6 +1,4 @@ {-# LANGUAGE DeriveDataTypeable #-} -{-# LANGUAGE DeriveFoldable #-} -{-# LANGUAGE DeriveFunctor #-} {-# LANGUAGE DeriveGeneric #-} {-# LANGUAGE DeriveTraversable #-} {-# LANGUAGE InstanceSigs #-} @@ -13,51 +11,44 @@ import Data.Aeson qualified as JSON -- aeson import Data.Aeson.KeyMap qualified as KM import Data.Vector qualified as V -- vector - -- first argument: the value (x) -- second argument: the tuple of permutations to apply (ps) -- the effect is a subset of: x .<= transform(ps, x) -data OpQuickPermutationOrder x = OpQuickPermutationOrder x x +data OpQuickPermutationOrder x = OpQuickPermutationOrder x [x] deriving (Eq, Ord, Show, Data, Functor, Traversable, Foldable, Typeable, Generic) instance (Serialize x) => Serialize (OpQuickPermutationOrder x) instance (Hashable x) => Hashable (OpQuickPermutationOrder x) -instance (ToJSON x) => ToJSON (OpQuickPermutationOrder x) where toJSON :: ToJSON x => OpQuickPermutationOrder x -> JSON.Value - toJSON = genericToJSON jsonOptions +instance (ToJSON x) => ToJSON (OpQuickPermutationOrder x) where + toJSON :: (ToJSON x) => OpQuickPermutationOrder x -> JSON.Value + toJSON = genericToJSON jsonOptions instance (FromJSON x) => FromJSON (OpQuickPermutationOrder x) where parseJSON = genericParseJSON jsonOptions instance (TypeOf x, Pretty x, ExpressionLike x) => TypeOf (OpQuickPermutationOrder x) where - typeOf p@(OpQuickPermutationOrder x perm) = do + typeOf p@(OpQuickPermutationOrder x perms) = do _tyX <- typeOf x - case listOut perm of - Just perms -> do - forM_ perms $ \ pe -> do - tyP <- typeOf pe - case tyP of - TypePermutation {} -> return () - _ -> raiseTypeError p - _ -> raiseTypeError p + forM_ perms $ \pe -> do + tyP <- typeOf pe + case tyP of + TypePermutation {} -> return () + _ -> raiseTypeError p return TypeBool instance SimplifyOp OpQuickPermutationOrder x where simplifyOp _ = na "simplifyOp{OpQuickPermutationOrder}" instance (Pretty x) => Pretty (OpQuickPermutationOrder x) where - prettyPrec _ (OpQuickPermutationOrder a b) = "quickPermutationOrder" <> prettyList prParens "," [a, b] + prettyPrec _ (OpQuickPermutationOrder a bs) = "quickPermutationOrder" <> prettyList prParens "," (a : bs) instance (VarSymBreakingDescription x, ExpressionLike x) => VarSymBreakingDescription (OpQuickPermutationOrder x) where - varSymBreakingDescription (OpQuickPermutationOrder x y) = + varSymBreakingDescription (OpQuickPermutationOrder x ys) = JSON.Object $ KM.fromList [ ("type", JSON.String "OpQuickPermutationOrder"), ( "children", - JSON.Array - $ V.fromList - [ varSymBreakingDescription x, - varSymBreakingDescription y - ] + JSON.Array $ V.fromList (varSymBreakingDescription x : map varSymBreakingDescription ys) ) ] diff --git a/src/Conjure/Language/Expression/Op/Transform.hs b/src/Conjure/Language/Expression/Op/Transform.hs index 49ec5ec9dd..68862434bb 100644 --- a/src/Conjure/Language/Expression/Op/Transform.hs +++ b/src/Conjure/Language/Expression/Op/Transform.hs @@ -1,53 +1,60 @@ -{-# LANGUAGE DeriveGeneric, DeriveDataTypeable, DeriveFunctor, DeriveTraversable, DeriveFoldable #-} +{-# LANGUAGE DeriveDataTypeable #-} +{-# LANGUAGE DeriveGeneric #-} +{-# LANGUAGE DeriveTraversable #-} module Conjure.Language.Expression.Op.Transform where -import Conjure.Prelude import Conjure.Language.Expression.Op.Internal.Common +import Conjure.Prelude +import Data.Aeson qualified as JSON -- aeson +import Data.Aeson.KeyMap qualified as KM +import Data.Vector qualified as V -- vector -import qualified Data.Aeson as JSON -- aeson -import qualified Data.Aeson.KeyMap as KM +data OpTransform x = OpTransform [x] x + deriving (Eq, Ord, Show, Data, Functor, Traversable, Foldable, Typeable, Generic) -import qualified Data.Vector as V -- vector +instance (Serialize x) => Serialize (OpTransform x) +instance (Hashable x) => Hashable (OpTransform x) -data OpTransform x = OpTransform x x - deriving (Eq, Ord, Show, Data, Functor, Traversable, Foldable, Typeable, Generic) +instance (ToJSON x) => ToJSON (OpTransform x) where toJSON = genericToJSON jsonOptions -instance Serialize x => Serialize (OpTransform x) -instance Hashable x => Hashable (OpTransform x) -instance ToJSON x => ToJSON (OpTransform x) where toJSON = genericToJSON jsonOptions -instance FromJSON x => FromJSON (OpTransform x) where parseJSON = genericParseJSON jsonOptions +instance (FromJSON x) => FromJSON (OpTransform x) where parseJSON = genericParseJSON jsonOptions instance (TypeOf x, Pretty x) => TypeOf (OpTransform x) where - typeOf p@(OpTransform f x) = do - tyF <- typeOf f - (from, to) <- case tyF of - TypeFunction from to -> return (from, to) - TypeSequence to -> return (TypeInt TagInt, to) - TypePermutation ov -> return (ov, ov) - _ -> raiseTypeError $ "(transform first argument not a morphism)" - <+> pretty p - if typesUnify [from, to] - then typeOf x - else raiseTypeError $ vcat - [ pretty p - , "transform morphism not homomorphic!" - , "morphism :" <+> pretty f - , "morphism type:" <+> pretty (TypeFunction from to) - ] + typeOf p@(OpTransform fs x) = do + fromTos <- forM fs $ \f -> do + tyF <- typeOf f + (from, to) <- case tyF of + TypeFunction from to -> return (from, to) + TypeSequence to -> return (TypeInt TagInt, to) + TypePermutation ov -> return (ov, ov) + _ -> raiseTypeError $ "(transform first argument not a morphism)" <+> pretty p + return (from, to) + if typesUnify $ concat [[a, b] | (a, b) <- fromTos] + then typeOf x + else + raiseTypeError + $ vcat + [ pretty p, + "transform morphism not homomorphic!", + "morphisms :" <+> vcat (map pretty fs) + ] instance SimplifyOp OpTransform x where - simplifyOp _ = na "simplifyOp{OpTransform}" - -instance Pretty x => Pretty (OpTransform x) where - prettyPrec _ (OpTransform a b) = "transform" <> prettyList prParens "," [a,b] - -instance VarSymBreakingDescription x => VarSymBreakingDescription (OpTransform x) where - varSymBreakingDescription (OpTransform a b) = JSON.Object $ KM.fromList - [ ("type", JSON.String "OpTransform") - , ("children", JSON.Array $ V.fromList - [ varSymBreakingDescription a - , varSymBreakingDescription b - ]) + simplifyOp _ = na "simplifyOp{OpTransform}" + +instance (Pretty x) => Pretty (OpTransform x) where + prettyPrec _ (OpTransform a b) = "transform" <> prettyList prParens "," (a ++ [b]) + +instance (VarSymBreakingDescription x) => VarSymBreakingDescription (OpTransform x) where + varSymBreakingDescription (OpTransform a b) = + JSON.Object + $ KM.fromList + [ ("type", JSON.String "OpTransform"), + ( "children", + JSON.Array + $ V.fromList + (map varSymBreakingDescription a ++ [varSymBreakingDescription b]) + ) ] diff --git a/src/Conjure/Language/Lenses.hs b/src/Conjure/Language/Lenses.hs index 2a9805160f..1e383a508c 100644 --- a/src/Conjure/Language/Lenses.hs +++ b/src/Conjure/Language/Lenses.hs @@ -439,8 +439,8 @@ opTransform , MonadFailDoc m ) => Proxy (m :: T.Type -> T.Type) - -> ( x -> x -> x - , x -> m (x, x) + -> ( [x] -> x -> x + , x -> m ([x], x) ) opTransform _ = ( \ x y -> inject $ MkOpTransform $ OpTransform x y diff --git a/src/Conjure/Rules/Transform.hs b/src/Conjure/Rules/Transform.hs index cf396a5078..cf83c30fb9 100644 --- a/src/Conjure/Rules/Transform.hs +++ b/src/Conjure/Rules/Transform.hs @@ -32,23 +32,23 @@ rules_Transform = rule_Transform_DotLess :: Rule rule_Transform_DotLess = "transform-dotless" `namedRule` theRule where - theRule [essence| &x .<= transform(&p, &y) |] | x == y = do + theRule [essence| &x .<= transform([&p], &y) |] | x == y = do TypeMatrix {} <- typeOf x (xInd : _) <- indexDomainsOf x return ( "", do (iPat, i) <- quantifiedVar - return [essence| &x .<= [ transform(&p, &x[transform(permInverse(&p), &i)]) | &iPat : &xInd ] |] + return [essence| &x .<= [ transform([&p], &x[transform([permInverse(&p)], &i)]) | &iPat : &xInd ] |] ) - theRule [essence| &x .< transform(&p, &y) |] | x == y = do + theRule [essence| &x .< transform([&p], &y) |] | x == y = do TypeMatrix {} <- typeOf x (xInd : _) <- indexDomainsOf x return ( "", do (iPat, i) <- quantifiedVar - return [essence| &x .< [ transform(&p, &x[transform(permInverse(&p), &i)]) | &iPat : &xInd ] |] + return [essence| &x .< [ transform([&p], &x[transform([permInverse(&p)], &i)]) | &iPat : &xInd ] |] ) theRule _ = na "rule_Transform_DotLess" @@ -75,7 +75,7 @@ rule_Transform_Functorially = "transform-functorially" `namedRule` theRule ++ [Generator (GenInExpr dPat y)] ++ ( ComprehensionLetting (Single pat) - [essence| transform(&morphism, &d) |] + [essence| transform([&morphism], &d) |] : gocAfter ) ) From a3c60ac0c06522278e3254f2678081150b54102e Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?=C3=96zg=C3=BCr=20Akg=C3=BCn?= Date: Tue, 3 Dec 2024 16:25:10 +0000 Subject: [PATCH 200/229] full: 2d matrices work (Lam) --- src/Conjure/Rules/Transform.hs | 101 ++++++++++++++++++++------------- src/Conjure/UI/Model.hs | 48 ++++++++-------- 2 files changed, 87 insertions(+), 62 deletions(-) diff --git a/src/Conjure/Rules/Transform.hs b/src/Conjure/Rules/Transform.hs index cf83c30fb9..928fb14e80 100644 --- a/src/Conjure/Rules/Transform.hs +++ b/src/Conjure/Rules/Transform.hs @@ -34,13 +34,38 @@ rule_Transform_DotLess = "transform-dotless" `namedRule` theRule where theRule [essence| &x .<= transform([&p], &y) |] | x == y = do TypeMatrix {} <- typeOf x - (xInd : _) <- indexDomainsOf x - return - ( "", - do - (iPat, i) <- quantifiedVar - return [essence| &x .<= [ transform([&p], &x[transform([permInverse(&p)], &i)]) | &iPat : &xInd ] |] - ) + xIndices <- indexDomainsOf x + case xIndices of + [xInd] -> + return + ( "", + do + (iPat, i) <- quantifiedVar + return [essence| &x .<= [ transform([&p], &x[transform([permInverse(&p)], &i)]) | &iPat : &xInd ] |] + ) + [xInd1, xInd2] -> + return + ( "", + do + (iPat1, i1) <- quantifiedVar + (iPat2, i2) <- quantifiedVar + return + [essence| + [ &x[&i1, &i2] + | &iPat1 : &xInd1 + , &iPat2 : &xInd2 + ] + .<= + [ transform( [&p] + , &x[ transform([permInverse(&p)], &i1) + , transform([permInverse(&p)], &i2) + ]) + | &iPat1 : &xInd1 + , &iPat2 : &xInd2 + ] + |] + ) + _ -> na "rule_Transform_DotLess" theRule [essence| &x .< transform([&p], &y) |] | x == y = do TypeMatrix {} <- typeOf x (xInd : _) <- indexDomainsOf x @@ -60,7 +85,7 @@ rule_Transform_Functorially = "transform-functorially" `namedRule` theRule Generator (GenInExpr (Single pat) expr) -> return (pat, matchDefs [opToSet, opToMSet] expr) _ -> na "rule_Transform_Functorially" - (morphism, y) <- match opTransform x + ([morphism], y) <- match opTransform x ty <- typeOf y inn <- morphing =<< typeOf morphism if let ?typeCheckerMode = StronglyTyped in ty `containsTypeFunctorially` inn @@ -87,7 +112,7 @@ rule_Transform_Comprehension :: Rule rule_Transform_Comprehension = "transform-comprehension" `namedRule` theRule where theRule x = do - (morphism, cmp@(Comprehension body gensOrConds)) <- match opTransform x + ([morphism], cmp@(Comprehension body gensOrConds)) <- match opTransform x ty <- typeOf cmp inn <- morphing =<< typeOf morphism if let ?typeCheckerMode = StronglyTyped in ty `containsType` inn @@ -96,32 +121,29 @@ rule_Transform_Comprehension = "transform-comprehension" `namedRule` theRule ( "Horizontal rule for transform comprehension", do gox <- mapM (transformOverGenOrCond morphism) gensOrConds - return - $ Comprehension - [essence| transform(&morphism, &body) |] - (join gox) + return $ Comprehension [essence| transform([&morphism], &body) |] (join gox) ) else na "rule_Transform_Comprehension" transformOverGenOrCond m (Generator g) = transformOverGenerator m g transformOverGenOrCond m (Condition e) = - return [Condition [essence| transform(&m,&e) |]] + return [Condition [essence| transform([&m], &e) |]] transformOverGenOrCond m (ComprehensionLetting pat e) = - return [ComprehensionLetting pat [essence| transform(&m,&e) |]] + return [ComprehensionLetting pat [essence| transform([&m], &e) |]] transformOverGenerator m (GenDomainHasRepr a d) = do (Single nm, n) <- quantifiedVarOverDomain $ forgetRepr d return [ Generator (GenDomainHasRepr nm d), - ComprehensionLetting (Single a) [essence| transform(&m, &n) |] + ComprehensionLetting (Single a) [essence| transform([&m], &n) |] ] transformOverGenerator m (GenInExpr a e) = - return [Generator (GenInExpr a [essence| transform(&m,&e) |])] + return [Generator (GenInExpr a [essence| transform([&m], &e) |])] transformOverGenerator m (GenDomainNoRepr absPat d) = do (rPat, ns) <- clonePattern absPat return $ Generator (GenDomainNoRepr rPat d) : ( ( \(pat, exp) -> - ComprehensionLetting (Single pat) [essence| transform(&m,&exp) |] + ComprehensionLetting (Single pat) [essence| transform([&m], &exp) |] ) <$> ns ) @@ -153,7 +175,7 @@ rule_Transform_Comprehension = "transform-comprehension" `namedRule` theRule rule_Transform_Product_Types :: Rule rule_Transform_Product_Types = "transform-product-types" `namedRule` theRule where - theRule [essence| transform(&morphism, &i) |] = do + theRule [essence| transform([&morphism], &i) |] = do inn <- morphing =<< typeOf morphism ti <- typeOf i if let ?typeCheckerMode = StronglyTyped in ti `containsProductType` inn @@ -161,7 +183,7 @@ rule_Transform_Product_Types = "transform-product-types" `namedRule` theRule (TypeTuple tint) -> do let tupleIndexTransform indx = let indexexpr = Constant (ConstantInt TagInt indx) - in [essence| transform(&morphism, &i[&indexexpr]) |] + in [essence| transform([&morphism], &i[&indexexpr]) |] tupleExpression = AbstractLiteral $ AbsLitTuple (tupleIndexTransform <$> [1 .. (fromIntegral $ length tint)]) @@ -175,7 +197,7 @@ rule_Transform_Product_Types = "transform-product-types" `namedRule` theRule Reference (fst indx) $ Just $ uncurry RecordField indx - in (fst indx, [essence| transform(&morphism, &i[&indexexpr]) |]) + in (fst indx, [essence| transform([&morphism], &i[&indexexpr]) |]) recordExpression = AbstractLiteral $ AbsLitRecord @@ -196,7 +218,7 @@ rule_Transform_Matrix = "transform-matrix" `namedRule` theRule (gocBefore, (pat, exp), gocAfter) <- matchFirst gensOrConds $ \case Generator (GenInExpr (Single pat) expr) -> return (pat, expr) _ -> na "rule_Transform_Matrix" - (morphism, matexp) <- match opTransform exp + ([morphism], matexp) <- match opTransform exp DomainMatrix domIndx _ <- domainOf matexp ty <- typeOf matexp inn <- morphing =<< typeOf morphism @@ -212,9 +234,9 @@ rule_Transform_Matrix = "transform-matrix" `namedRule` theRule ( Comprehension body $ gocBefore ++ [Generator (GenDomainNoRepr dPat (forgetRepr domIndx))] - ++ [ComprehensionLetting (Single iName) [essence| transform(&morphism, &d) |]] + ++ [ComprehensionLetting (Single iName) [essence| transform([&morphism], &d) |]] ++ [ComprehensionLetting (Single mName) [essence| &matexp[&i] |]] - ++ [ComprehensionLetting (Single pat) [essence| transform(&morphism, &m) |]] + ++ [ComprehensionLetting (Single pat) [essence| transform([&morphism], &m) |]] ++ gocAfter ) ) @@ -229,7 +251,7 @@ rule_Transform_Partition = "transform-partition" `namedRule` theRule Generator (GenInExpr (Single pat) expr) -> return (pat, expr) _ -> na "rule_Transform_Partition" z <- match opParts x - (morphism, y) <- match opTransform z + ([morphism], y) <- match opTransform z ty <- typeOf y case ty of TypePartition {} -> return (); _ -> na "only applies to partitions" inn <- morphing =<< typeOf morphism @@ -243,7 +265,7 @@ rule_Transform_Partition = "transform-partition" `namedRule` theRule ( Comprehension body $ gocBefore ++ [Generator (GenInExpr dPat [essence| parts(&y) |])] - ++ (ComprehensionLetting (Single pat) [essence| transform(&morphism, &d) |] : gocAfter) + ++ (ComprehensionLetting (Single pat) [essence| transform([&morphism], &d) |] : gocAfter) ) ) else na "rule_Transform_Partition" @@ -257,7 +279,7 @@ rule_Transform_Sequence = "transform-sequence" `namedRule` theRule Generator (GenInExpr (Single pat) expr) -> return (pat, matchDefs [opToSet, opToMSet] expr) _ -> na "rule_Transform_Sequence" - (morphism, y) <- match opTransform x + ([morphism], y) <- match opTransform x ty <- typeOf y case ty of TypeSequence {} -> return (); _ -> na "only applies to sequences" inn <- morphing =<< typeOf morphism @@ -273,7 +295,7 @@ rule_Transform_Sequence = "transform-sequence" `namedRule` theRule ++ [Generator (GenInExpr dPat y)] ++ ( ComprehensionLetting (Single pat) - [essence| (&d[1], transform(&morphism, &d[2])) |] + [essence| (&d[1], transform([&morphism], &d[2])) |] : gocAfter ) ) @@ -290,7 +312,7 @@ rule_Transform_Sequence_Defined = "transform-sequence-defined" `namedRule` theRu return (pat, matchDefs [opToSet, opToMSet] expr) _ -> na "rule_Transform_Sequence_Defined" defi <- match opDefined x - (morphism, y) <- match opTransform defi + ([morphism], y) <- match opTransform defi ty <- typeOf y case ty of TypeSequence {} -> return (); _ -> na "only applies to sequences" inn <- morphing =<< typeOf morphism @@ -317,7 +339,7 @@ rule_Transformed_Indexing = "transformed-indexing" `namedRule` theRule Generator (GenInExpr (Single pat) expr) -> return (pat, expr) _ -> na "rule_Transformed_Indexing" (matexp, indexer) <- match opIndexing exp - (morphism, mat) <- match opTransform matexp + ([morphism], mat) <- match opTransform matexp ty <- typeOf mat inn <- morphing =<< typeOf morphism if let ?typeCheckerMode = StronglyTyped in ty `containsType` inn @@ -330,7 +352,7 @@ rule_Transformed_Indexing = "transformed-indexing" `namedRule` theRule ( Comprehension body $ gocBefore ++ [ComprehensionLetting (Single mName) [essence| &matexp[&indexer] |]] - ++ [ComprehensionLetting (Single pat) [essence| transform(&morphism, &m) |]] + ++ [ComprehensionLetting (Single pat) [essence| transform([&morphism], &m) |]] ++ gocAfter ) ) @@ -340,11 +362,11 @@ rule_Transformed_Indexing = "transformed-indexing" `namedRule` theRule rule_Lift_Transformed_Indexing :: Rule rule_Lift_Transformed_Indexing = "lift-transformed-indexing" `namedRule` theRule where - theRule [essence| transform(&p, &x)[&i] |] = do + theRule [essence| transform([&p], &x)[&i] |] = do TypePermutation {} <- typeOf p return ( "transformed indexing", - return [essence| transform(&p, &x[transform(permInverse(&p), &i)]) |] + return [essence| transform([&p], &x[transform([permInverse(&p)], &i)]) |] ) theRule _ = na "rule_Lift_Transformed_Indexing" @@ -355,7 +377,7 @@ rule_Transform_Indexing = "transform-indexing" `namedRule` theRule (gocBefore, (pat, expr), gocAfter) <- matchFirst gensOrConds $ \case Generator (GenInExpr pat expr) -> return (pat, expr) _ -> na "rule_Transform_Indexing" - (morphism, matexp) <- match opTransform expr + ([morphism], matexp) <- match opTransform expr (mat, indexer) <- match opIndexing matexp ty <- typeOf mat inn <- morphing =<< typeOf morphism @@ -369,9 +391,9 @@ rule_Transform_Indexing = "transform-indexing" `namedRule` theRule return ( Comprehension body $ gocBefore - ++ [ComprehensionLetting (Single iName) [essence| transform(&morphism, &indexer) |]] + ++ [ComprehensionLetting (Single iName) [essence| transform([&morphism], &indexer) |]] ++ [ComprehensionLetting (Single mName) [essence| &mat[&i] |]] - ++ [Generator (GenInExpr pat [essence| transform(&morphism, &m) |])] + ++ [Generator (GenInExpr pat [essence| transform([&morphism], &m) |])] ++ gocAfter ) ) @@ -381,7 +403,7 @@ rule_Transform_Indexing = "transform-indexing" `namedRule` theRule rule_Transform_Unifying :: Rule rule_Transform_Unifying = "transform-unifying" `namedRule` theRule where - theRule [essence| transform(&morphism, &i) |] = do + theRule [essence| transform([&morphism], &i) |] = do inner <- morphing =<< typeOf morphism typeI <- typeOf i if let ?typeCheckerMode = StronglyTyped in typesUnify [inner, typeI] @@ -439,11 +461,12 @@ matchManyTransforms :: matchManyTransforms exp = case match opTransform exp of Nothing -> (exp, id) - Just (morphism, so) -> + Just ([morphism], so) -> let (nexp, ntrans) = matchManyTransforms so in ( nexp, - \x -> let nx = ntrans x in [essence| transform(&morphism, &nx) |] + \x -> let nx = ntrans x in [essence| transform([&morphism], &nx) |] ) + _ -> bug "matchManyTransforms" rule_Transform_Variant_Eq :: Rule rule_Transform_Variant_Eq = "transform-variant-eq" `namedRule` theRule diff --git a/src/Conjure/UI/Model.hs b/src/Conjure/UI/Model.hs index f25549ee1e..faffbf4d76 100644 --- a/src/Conjure/UI/Model.hs +++ b/src/Conjure/UI/Model.hs @@ -1032,11 +1032,13 @@ checkIfAllRefined m | Just modelZipper <- mkModelZipper m = do -- we | (i, c) <- zip allNats (tail (ascendants x)) ] [essence| &_ .< &_ |] -> - return ["", ("Not refined:" <+> pretty (hole x)) - <+> stringToDoc (show (hole x))] + return ["", "Not refined:" <+> vcat [ pretty (hole x) + , stringToDoc (show (hole x)) + ]] [essence| &_ .<= &_ |] -> - return ["", ("Not refined:" <+> pretty (hole x)) - <+> stringToDoc (show (hole x))] + return ["", "Not refined:" <+> vcat [ pretty (hole x) + , stringToDoc (show (hole x)) + ]] _ -> return [] unless (null fails) (bug (vcat fails)) return m @@ -2087,23 +2089,23 @@ rule_Neq = "identical-domain-neq" `namedRule` theRule where rule_QuickPermutationOrder :: Rule rule_QuickPermutationOrder = "generic-QuickPermutationOrder" `namedRule` theRule where - theRule [essence| quickPermutationOrder(&x, &ps) |] = do - case listOut ps of - Just [perm] -> - return - ( "Generic vertical rule for quickPermutationOrder:" <+> pretty perm - , return [essence| &x .<= transform(&perm, &x) |] - ) - _ -> na "rule_QuickPermutationOrder - not implemented for multiple permutations yet" - -- traceM $ show $ "HERE x " <+> pretty x - -- traceM $ show $ "HERE ps" <+> pretty ps - -- x_ord <- symmetryOrdering x - -- x_perm <- symmetryOrdering [essence| transform(&ps, &x) |] - -- traceM $ show $ "HERE x_perm" <+> pretty x_perm - -- return - -- ( "Generic vertical rule for quickPermutationOrder:" <+> pretty p - -- , return [essence| &x_ord <=lex &x_perm |] - -- ) + -- theRule p@[essence| quickPermutationOrder(&x, &ps) |] = do + -- -- case listOut ps of + -- -- Just [perm] -> + -- -- return + -- -- ( "Generic vertical rule for quickPermutationOrder:" <+> pretty perm + -- -- , return [essence| &x .<= transform(&perm, &x) |] + -- -- ) + -- -- _ -> na "rule_QuickPermutationOrder - not implemented for multiple permutations yet" + -- traceM $ show $ "HERE x " <+> pretty x + -- traceM $ show $ "HERE ps" <+> pretty ps + -- x_ord <- symmetryOrdering x + -- -- x_perm <- symmetryOrdering [essence| transform(&ps, &x) |] + -- traceM $ show $ "HERE x_ord" <+> pretty x_ord + -- return + -- ( "Generic vertical rule for quickPermutationOrder:" <+> pretty p + -- , return [essence| &x_ord .<= transform(&ps, &x_ord) |] + -- ) theRule _ = na "rule_QuickPermutationOrder" @@ -2892,7 +2894,7 @@ addUnnamedSymmetryBreaking mode model = do buildPermutationChain [] vars = vars buildPermutationChain (p:ps) vars = let applied = buildPermutationChain ps vars - in [essence| transform(&p, &applied) |] + in [essence| transform([&p], &applied) |] -- x .<= transform(p1, transform(p2, x)) -- quickPermutationOrder(x, p) to mean s subset of `x .<= transform(p,x)` @@ -2901,7 +2903,7 @@ addUnnamedSymmetryBreaking mode model = do case quickOrComplete of USBQuick -> let p = fromList perms - in [essence| quickPermutationOrder(&varsTuple, &p) |] + in [essence| quickPermutationOrder(&varsTuple, [&p]) |] USBComplete -> let applied = buildPermutationChain perms varsTuple in [essence| &varsTuple .<= &applied |] From 80ed866faf4408b11e903162be19183e734ef2e7 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?=C3=96zg=C3=BCr=20Akg=C3=BCn?= Date: Wed, 4 Dec 2024 14:16:41 +0000 Subject: [PATCH 201/229] fix pretty printing of transform --- src/Conjure/Language/Expression/Op/Transform.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Conjure/Language/Expression/Op/Transform.hs b/src/Conjure/Language/Expression/Op/Transform.hs index 68862434bb..b6608594c6 100644 --- a/src/Conjure/Language/Expression/Op/Transform.hs +++ b/src/Conjure/Language/Expression/Op/Transform.hs @@ -45,7 +45,7 @@ instance SimplifyOp OpTransform x where simplifyOp _ = na "simplifyOp{OpTransform}" instance (Pretty x) => Pretty (OpTransform x) where - prettyPrec _ (OpTransform a b) = "transform" <> prettyList prParens "," (a ++ [b]) + prettyPrec _ (OpTransform a b) = "transform" <> prettyListDoc prParens "," [prettyList prBrackets "," a, pretty b] instance (VarSymBreakingDescription x) => VarSymBreakingDescription (OpTransform x) where varSymBreakingDescription (OpTransform a b) = From 0d68952110f4a426d0682e906eb9cd788dcf512c Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?=C3=96zg=C3=BCr=20Akg=C3=BCn?= Date: Wed, 4 Dec 2024 14:16:53 +0000 Subject: [PATCH 202/229] special case unary tuples --- src/Conjure/UI/Model.hs | 12 ++++-------- 1 file changed, 4 insertions(+), 8 deletions(-) diff --git a/src/Conjure/UI/Model.hs b/src/Conjure/UI/Model.hs index faffbf4d76..94225a363a 100644 --- a/src/Conjure/UI/Model.hs +++ b/src/Conjure/UI/Model.hs @@ -2855,7 +2855,9 @@ addUnnamedSymmetryBreaking mode model = do -- | Declaration (FindOrGiven Find nm domain) <- mStatements model -- ] - varsTuple = AbstractLiteral $ AbsLitTuple $ map fst allDecVars + varsTuple = case allDecVars of + [v] -> fst v + _ -> AbstractLiteral $ AbsLitTuple $ map fst allDecVars -- mkAuxTuple auxSuffix = AbstractLiteral $ AbsLitTuple $ map fst (allDecVarsAux auxSuffix) -- traceM $ show $ "Unnamed types in this model:" <++> prettyList id "," allUnnamedTypes @@ -2891,13 +2893,7 @@ addUnnamedSymmetryBreaking mode model = do let - buildPermutationChain [] vars = vars - buildPermutationChain (p:ps) vars = - let applied = buildPermutationChain ps vars - in [essence| transform([&p], &applied) |] - - -- x .<= transform(p1, transform(p2, x)) - -- quickPermutationOrder(x, p) to mean s subset of `x .<= transform(p,x)` + buildPermutationChain = make opTransform combinedPermApply perms = case quickOrComplete of From 878d8112477da01f4fc7db4a820b9acc19e6dcf6 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?=C3=96zg=C3=BCr=20Akg=C3=BCn?= Date: Wed, 4 Dec 2024 14:17:06 +0000 Subject: [PATCH 203/229] comment out rules we aren't using (?) --- src/Conjure/Rules/Transform.hs | 378 ++++++++++++++++----------------- 1 file changed, 189 insertions(+), 189 deletions(-) diff --git a/src/Conjure/Rules/Transform.hs b/src/Conjure/Rules/Transform.hs index 928fb14e80..de9f1ca261 100644 --- a/src/Conjure/Rules/Transform.hs +++ b/src/Conjure/Rules/Transform.hs @@ -3,12 +3,12 @@ module Conjure.Rules.Transform (rules_Transform) where import Conjure.Rules.Import -import Conjure.Rules.Vertical.Variant (onTagged) +-- import Conjure.Rules.Vertical.Variant (onTagged) rules_Transform :: [Rule] rules_Transform = [ rule_Transform_DotLess, - rule_Transform_Sequence_Literal, + -- rule_Transform_Sequence_Literal, rule_Transform_Functorially, rule_Transform_Comprehension, rule_Transform_Product_Types, @@ -19,14 +19,14 @@ rules_Transform = rule_Transformed_Indexing, rule_Lift_Transformed_Indexing, rule_Transform_Indexing, - rule_Transform_Unifying, - rule_Transform_Variant_Literal, - rule_Transform_Variant_Eq, - rule_Transform_Variant_Neq, - rule_Transform_Variant_Lt, - rule_Transform_Variant_Leq, - rule_Transformed_Variant_Index, - rule_Transformed_Variant_Active + rule_Transform_Unifying + -- rule_Transform_Variant_Literal, + -- rule_Transform_Variant_Eq, + -- rule_Transform_Variant_Neq, + -- rule_Transform_Variant_Lt, + -- rule_Transform_Variant_Leq, + -- rule_Transformed_Variant_Index, + -- rule_Transformed_Variant_Active ] rule_Transform_DotLess :: Rule @@ -422,191 +422,191 @@ rule_Transform_Unifying = "transform-unifying" `namedRule` theRule ) theRule _ = na "rule_Transform_Unifying" -rule_Transform_Sequence_Literal :: Rule -rule_Transform_Sequence_Literal = "transform-sequence-literal" `namedRule` theRule - where - theRule p = do - _ <- match opTransform p - let (x, rx) = matchManyTransforms p - TypeSequence {} <- typeOf x - (_, as) <- match sequenceLiteral x - return - ( "Horizontal rule for transform sequence literal", - return $ AbstractLiteral $ AbsLitSequence $ rx <$> as - ) +-- rule_Transform_Sequence_Literal :: Rule +-- rule_Transform_Sequence_Literal = "transform-sequence-literal" `namedRule` theRule +-- where +-- theRule p = do +-- _ <- match opTransform p +-- let (x, rx) = matchManyTransforms p +-- TypeSequence {} <- typeOf x +-- (_, as) <- match sequenceLiteral x +-- return +-- ( "Horizontal rule for transform sequence literal", +-- return $ AbstractLiteral $ AbsLitSequence $ rx <$> as +-- ) -rule_Transform_Variant_Literal :: Rule -rule_Transform_Variant_Literal = "transform-variant-literal" `namedRule` theRule - where - theRule p = do - _ <- match opTransform p - let (x, rx) = matchManyTransforms p - case x of - AbstractLiteral (AbsLitVariant d n a) -> - return - ( "Horizontal rule for transform variant literal", - return $ AbstractLiteral $ AbsLitVariant d n $ rx a - ) - _ -> na "rule_Transform_Variant_Literal" +-- rule_Transform_Variant_Literal :: Rule +-- rule_Transform_Variant_Literal = "transform-variant-literal" `namedRule` theRule +-- where +-- theRule p = do +-- _ <- match opTransform p +-- let (x, rx) = matchManyTransforms p +-- case x of +-- AbstractLiteral (AbsLitVariant d n a) -> +-- return +-- ( "Horizontal rule for transform variant literal", +-- return $ AbstractLiteral $ AbsLitVariant d n $ rx a +-- ) +-- _ -> na "rule_Transform_Variant_Literal" -atLeastOneTransform :: (MonadFailDoc m) => (Expression, Expression) -> m () -atLeastOneTransform (l, r) = do - case (match opTransform l, match opTransform r) of - (Nothing, Nothing) -> na "no transforms on either side" - _ -> return () +-- atLeastOneTransform :: (MonadFailDoc m) => (Expression, Expression) -> m () +-- atLeastOneTransform (l, r) = do +-- case (match opTransform l, match opTransform r) of +-- (Nothing, Nothing) -> na "no transforms on either side" +-- _ -> return () -matchManyTransforms :: - Expression -> - (Expression, Expression -> Expression) -matchManyTransforms exp = - case match opTransform exp of - Nothing -> (exp, id) - Just ([morphism], so) -> - let (nexp, ntrans) = matchManyTransforms so - in ( nexp, - \x -> let nx = ntrans x in [essence| transform([&morphism], &nx) |] - ) - _ -> bug "matchManyTransforms" +-- matchManyTransforms :: +-- Expression -> +-- (Expression, Expression -> Expression) +-- matchManyTransforms exp = +-- case match opTransform exp of +-- Nothing -> (exp, id) +-- Just ([morphism], so) -> +-- let (nexp, ntrans) = matchManyTransforms so +-- in ( nexp, +-- \x -> let nx = ntrans x in [essence| transform([&morphism], &nx) |] +-- ) +-- _ -> bug "matchManyTransforms" -rule_Transform_Variant_Eq :: Rule -rule_Transform_Variant_Eq = "transform-variant-eq" `namedRule` theRule - where - theRule p = do - (l, r) <- match opEq p - atLeastOneTransform (l, r) - let (x, rx) = matchManyTransforms l - let (y, ry) = matchManyTransforms r - TypeVariant {} <- typeOf x - TypeVariant {} <- typeOf y - (xWhich : xs) <- downX1 x - (yWhich : ys) <- downX1 y - return - ( "Vertical rule for right transformed variant equality", - return - $ make opAnd - $ fromList - [ [essence| &xWhich = &yWhich |], - onTagged (make opEq) xWhich (rx <$> xs) (ry <$> ys) - ] - ) +-- rule_Transform_Variant_Eq :: Rule +-- rule_Transform_Variant_Eq = "transform-variant-eq" `namedRule` theRule +-- where +-- theRule p = do +-- (l, r) <- match opEq p +-- atLeastOneTransform (l, r) +-- let (x, rx) = matchManyTransforms l +-- let (y, ry) = matchManyTransforms r +-- TypeVariant {} <- typeOf x +-- TypeVariant {} <- typeOf y +-- (xWhich : xs) <- downX1 x +-- (yWhich : ys) <- downX1 y +-- return +-- ( "Vertical rule for right transformed variant equality", +-- return +-- $ make opAnd +-- $ fromList +-- [ [essence| &xWhich = &yWhich |], +-- onTagged (make opEq) xWhich (rx <$> xs) (ry <$> ys) +-- ] +-- ) -rule_Transform_Variant_Neq :: Rule -rule_Transform_Variant_Neq = "transform-variant-neq" `namedRule` theRule - where - theRule p = do - (l, r) <- match opNeq p - atLeastOneTransform (l, r) - let (x, rx) = matchManyTransforms l - let (y, ry) = matchManyTransforms r - TypeVariant {} <- typeOf x - TypeVariant {} <- typeOf y - (xWhich : xs) <- downX1 x - (yWhich : ys) <- downX1 y - return - ( "Vertical rule for right transformed variant nequality", - return - $ make opOr - $ fromList - [ [essence| &xWhich != &yWhich |], - make opAnd - $ fromList - [ [essence| &xWhich = &yWhich |], - onTagged (make opNeq) xWhich (rx <$> xs) (ry <$> ys) - ] - ] - ) +-- rule_Transform_Variant_Neq :: Rule +-- rule_Transform_Variant_Neq = "transform-variant-neq" `namedRule` theRule +-- where +-- theRule p = do +-- (l, r) <- match opNeq p +-- atLeastOneTransform (l, r) +-- let (x, rx) = matchManyTransforms l +-- let (y, ry) = matchManyTransforms r +-- TypeVariant {} <- typeOf x +-- TypeVariant {} <- typeOf y +-- (xWhich : xs) <- downX1 x +-- (yWhich : ys) <- downX1 y +-- return +-- ( "Vertical rule for right transformed variant nequality", +-- return +-- $ make opOr +-- $ fromList +-- [ [essence| &xWhich != &yWhich |], +-- make opAnd +-- $ fromList +-- [ [essence| &xWhich = &yWhich |], +-- onTagged (make opNeq) xWhich (rx <$> xs) (ry <$> ys) +-- ] +-- ] +-- ) -rule_Transform_Variant_Lt :: Rule -rule_Transform_Variant_Lt = "transform-variant-lt" `namedRule` theRule - where - theRule p = do - (l, r) <- match opLt p - atLeastOneTransform (l, r) - let (x, rx) = matchManyTransforms l - let (y, ry) = matchManyTransforms r - TypeVariant {} <- typeOf x - TypeVariant {} <- typeOf y - (xWhich : xs) <- downX1 x - (yWhich : ys) <- downX1 y - return - ( "Vertical rule for right transformed variant less than", - return - $ make opOr - $ fromList - [ [essence| &xWhich < &yWhich |], - make opAnd - $ fromList - [ [essence| &xWhich = &yWhich |], - onTagged (make opLt) xWhich (rx <$> xs) (ry <$> ys) - ] - ] - ) +-- rule_Transform_Variant_Lt :: Rule +-- rule_Transform_Variant_Lt = "transform-variant-lt" `namedRule` theRule +-- where +-- theRule p = do +-- (l, r) <- match opLt p +-- atLeastOneTransform (l, r) +-- let (x, rx) = matchManyTransforms l +-- let (y, ry) = matchManyTransforms r +-- TypeVariant {} <- typeOf x +-- TypeVariant {} <- typeOf y +-- (xWhich : xs) <- downX1 x +-- (yWhich : ys) <- downX1 y +-- return +-- ( "Vertical rule for right transformed variant less than", +-- return +-- $ make opOr +-- $ fromList +-- [ [essence| &xWhich < &yWhich |], +-- make opAnd +-- $ fromList +-- [ [essence| &xWhich = &yWhich |], +-- onTagged (make opLt) xWhich (rx <$> xs) (ry <$> ys) +-- ] +-- ] +-- ) -rule_Transform_Variant_Leq :: Rule -rule_Transform_Variant_Leq = "transform-variant-leq" `namedRule` theRule - where - theRule p = do - (l, r) <- match opLeq p - atLeastOneTransform (l, r) - let (x, rx) = matchManyTransforms l - let (y, ry) = matchManyTransforms r - TypeVariant {} <- typeOf x - TypeVariant {} <- typeOf y - (xWhich : xs) <- downX1 x - (yWhich : ys) <- downX1 y - return - ( "Vertical rule for right transformed variant less than eq", - return - $ make opOr - $ fromList - [ [essence| &xWhich < &yWhich |], - make opAnd - $ fromList - [ [essence| &xWhich = &yWhich |], - onTagged (make opLeq) xWhich (rx <$> xs) (ry <$> ys) - ] - ] - ) +-- rule_Transform_Variant_Leq :: Rule +-- rule_Transform_Variant_Leq = "transform-variant-leq" `namedRule` theRule +-- where +-- theRule p = do +-- (l, r) <- match opLeq p +-- atLeastOneTransform (l, r) +-- let (x, rx) = matchManyTransforms l +-- let (y, ry) = matchManyTransforms r +-- TypeVariant {} <- typeOf x +-- TypeVariant {} <- typeOf y +-- (xWhich : xs) <- downX1 x +-- (yWhich : ys) <- downX1 y +-- return +-- ( "Vertical rule for right transformed variant less than eq", +-- return +-- $ make opOr +-- $ fromList +-- [ [essence| &xWhich < &yWhich |], +-- make opAnd +-- $ fromList +-- [ [essence| &xWhich = &yWhich |], +-- onTagged (make opLeq) xWhich (rx <$> xs) (ry <$> ys) +-- ] +-- ] +-- ) -rule_Transformed_Variant_Index :: Rule -rule_Transformed_Variant_Index = "transformed-variant-index" `namedRule` theRule - where - theRule p = do - (l, arg) <- match opIndexing p - atLeastOneTransform (l, l) - let (x, rx) = matchManyTransforms l - TypeVariant ds <- typeOf x - (xWhich : xs) <- downX1 x - name <- nameOut arg - argInt <- - case elemIndex name (map fst ds) of - Nothing -> failDoc "Variant indexing, not a member of the type." - Just argInt -> return argInt - return - ( "Variant indexing on:" <+> pretty p, - return - $ WithLocals - (rx (atNote "Variant indexing" xs argInt)) - ( DefinednessConstraints - [ [essence| &xWhich = &argInt2 |] - | let argInt2 = fromInt (fromIntegral (argInt + 1)) - ] - ) - ) +-- rule_Transformed_Variant_Index :: Rule +-- rule_Transformed_Variant_Index = "transformed-variant-index" `namedRule` theRule +-- where +-- theRule p = do +-- (l, arg) <- match opIndexing p +-- atLeastOneTransform (l, l) +-- let (x, rx) = matchManyTransforms l +-- TypeVariant ds <- typeOf x +-- (xWhich : xs) <- downX1 x +-- name <- nameOut arg +-- argInt <- +-- case elemIndex name (map fst ds) of +-- Nothing -> failDoc "Variant indexing, not a member of the type." +-- Just argInt -> return argInt +-- return +-- ( "Variant indexing on:" <+> pretty p, +-- return +-- $ WithLocals +-- (rx (atNote "Variant indexing" xs argInt)) +-- ( DefinednessConstraints +-- [ [essence| &xWhich = &argInt2 |] +-- | let argInt2 = fromInt (fromIntegral (argInt + 1)) +-- ] +-- ) +-- ) -rule_Transformed_Variant_Active :: Rule -rule_Transformed_Variant_Active = "transformed-variant-active" `namedRule` theRule - where - theRule p = do - (l, name) <- match opActive p - atLeastOneTransform (l, l) - let (x, _) = matchManyTransforms l - TypeVariant ds <- typeOf x - (xWhich : _) <- downX1 x - argInt <- case elemIndex name (map fst ds) of - Nothing -> failDoc "Variant indexing, not a member of the type." - Just argInt -> return $ fromInt $ fromIntegral $ argInt + 1 - return - ( "Variant active on:" <+> pretty p, - return [essence| &xWhich = &argInt |] - ) +-- rule_Transformed_Variant_Active :: Rule +-- rule_Transformed_Variant_Active = "transformed-variant-active" `namedRule` theRule +-- where +-- theRule p = do +-- (l, name) <- match opActive p +-- atLeastOneTransform (l, l) +-- let (x, _) = matchManyTransforms l +-- TypeVariant ds <- typeOf x +-- (xWhich : _) <- downX1 x +-- argInt <- case elemIndex name (map fst ds) of +-- Nothing -> failDoc "Variant indexing, not a member of the type." +-- Just argInt -> return $ fromInt $ fromIntegral $ argInt + 1 +-- return +-- ( "Variant active on:" <+> pretty p, +-- return [essence| &xWhich = &argInt |] +-- ) From 0b43478963f25305e4daf5d8af11e44d30913611 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?=C3=96zg=C3=BCr=20Akg=C3=BCn?= Date: Wed, 4 Dec 2024 15:25:02 +0000 Subject: [PATCH 204/229] generalising to multiple permutations - more to come --- src/Conjure/Rules/Transform.hs | 118 +++++++++++++++++++-------------- 1 file changed, 67 insertions(+), 51 deletions(-) diff --git a/src/Conjure/Rules/Transform.hs b/src/Conjure/Rules/Transform.hs index de9f1ca261..869a5428f1 100644 --- a/src/Conjure/Rules/Transform.hs +++ b/src/Conjure/Rules/Transform.hs @@ -3,6 +3,7 @@ module Conjure.Rules.Transform (rules_Transform) where import Conjure.Rules.Import + -- import Conjure.Rules.Vertical.Variant (onTagged) rules_Transform :: [Rule] @@ -32,40 +33,46 @@ rules_Transform = rule_Transform_DotLess :: Rule rule_Transform_DotLess = "transform-dotless" `namedRule` theRule where - theRule [essence| &x .<= transform([&p], &y) |] | x == y = do - TypeMatrix {} <- typeOf x - xIndices <- indexDomainsOf x - case xIndices of - [xInd] -> - return - ( "", - do - (iPat, i) <- quantifiedVar - return [essence| &x .<= [ transform([&p], &x[transform([permInverse(&p)], &i)]) | &iPat : &xInd ] |] - ) - [xInd1, xInd2] -> - return - ( "", - do - (iPat1, i1) <- quantifiedVar - (iPat2, i2) <- quantifiedVar - return - [essence| + theRule [essence| &x .<= &rhs |] + | Just (ps, y) <- match opTransform rhs, + x == y = do + TypeMatrix {} <- typeOf x + -- traceM $ show $ "rule_Transform_DotLess 1" <+> pretty x + xIndices <- indexDomainsOf x + -- traceM $ show $ "rule_Transform_DotLess 2" <+> vcat (map pretty xIndices) + case xIndices of + [xInd] -> + return + ( "", + do + (iPat, i) <- quantifiedVar + let transformed_i = make opTransform (map (make opPermInverse) ps) i + let transformed_x_i = make opTransform ps [essence| &x[&transformed_i] |] + return [essence| &x .<= [ &transformed_x_i | &iPat : &xInd ] |] + ) + [xInd1, xInd2] -> + return + ( "", + do + (iPat1, i1) <- quantifiedVar + (iPat2, i2) <- quantifiedVar + let transformed_i1 = make opTransform (map (make opPermInverse) ps) i1 + let transformed_i2 = make opTransform (map (make opPermInverse) ps) i2 + let transformed_x_i1_i2 = make opTransform ps [essence| &x[&transformed_i1, &transformed_i2] |] + return + [essence| [ &x[&i1, &i2] | &iPat1 : &xInd1 , &iPat2 : &xInd2 ] .<= - [ transform( [&p] - , &x[ transform([permInverse(&p)], &i1) - , transform([permInverse(&p)], &i2) - ]) + [ &transformed_x_i1_i2 | &iPat1 : &xInd1 , &iPat2 : &xInd2 ] |] - ) - _ -> na "rule_Transform_DotLess" + ) + _ -> na "rule_Transform_DotLess" theRule [essence| &x .< transform([&p], &y) |] | x == y = do TypeMatrix {} <- typeOf x (xInd : _) <- indexDomainsOf x @@ -85,27 +92,22 @@ rule_Transform_Functorially = "transform-functorially" `namedRule` theRule Generator (GenInExpr (Single pat) expr) -> return (pat, matchDefs [opToSet, opToMSet] expr) _ -> na "rule_Transform_Functorially" - ([morphism], y) <- match opTransform x - ty <- typeOf y - inn <- morphing =<< typeOf morphism - if let ?typeCheckerMode = StronglyTyped in ty `containsTypeFunctorially` inn - then - return - ( "Horizontal rule for transform of functorially", - do - (dPat, d) <- quantifiedVar - return - ( Comprehension body - $ gocBefore - ++ [Generator (GenInExpr dPat y)] - ++ ( ComprehensionLetting - (Single pat) - [essence| transform([&morphism], &d) |] - : gocAfter - ) - ) - ) - else na "rule_Transform_Functorially" + (morphisms, y) <- match opTransform x + return + ( "Horizontal rule for transform of functorially", + do + (dPat, d) <- quantifiedVar + return + ( Comprehension body + $ gocBefore + ++ [Generator (GenInExpr dPat y)] + ++ ( ComprehensionLetting + (Single pat) + (make opTransform morphisms d) + : gocAfter + ) + ) + ) theRule _ = na "rule_Transform_Functorially" rule_Transform_Comprehension :: Rule @@ -406,20 +408,34 @@ rule_Transform_Unifying = "transform-unifying" `namedRule` theRule theRule [essence| transform([&morphism], &i) |] = do inner <- morphing =<< typeOf morphism typeI <- typeOf i - if let ?typeCheckerMode = StronglyTyped in typesUnify [inner, typeI] + if typesUnify [inner, typeI] then return ( "Horizontal rule for transform unifying", return [essence| image(&morphism, &i) |] ) + else na "rule_Transform_Unifying" + theRule p | Just (morphisms :: [Expression], i) <- match opTransform p = do + typeI <- typeOf i + morphisms' <- fmap catMaybes $ forM morphisms $ \morphism -> do + inner <- morphing =<< typeOf morphism + if containsType typeI inner + then return (Just morphism) + else return Nothing + if length morphisms' == length morphisms + then na "rule_Transform_Unifying" -- didn't drop anything else - if let ?typeCheckerMode = StronglyTyped in typeI `containsType` inner - then na "rule_Transform_Unifying" - else + if null morphisms' + then return - ( "Horizontal rule for transform shortcut", + ( "Horizontal rule for transform unifying", return i ) + else + return + ( "Horizontal rule for transform unifying", + return $ make opTransform morphisms' i + ) theRule _ = na "rule_Transform_Unifying" -- rule_Transform_Sequence_Literal :: Rule From fcc382a4ec2d01bec929a1cb2f3127a32a7aefb7 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?=C3=96zg=C3=BCr=20Akg=C3=BCn?= Date: Wed, 4 Dec 2024 15:25:12 +0000 Subject: [PATCH 205/229] add a opPermInverse lens --- src/Conjure/Language/Lenses.hs | 19 +++++++++++++++++++ 1 file changed, 19 insertions(+) diff --git a/src/Conjure/Language/Lenses.hs b/src/Conjure/Language/Lenses.hs index 1e383a508c..17a4908523 100644 --- a/src/Conjure/Language/Lenses.hs +++ b/src/Conjure/Language/Lenses.hs @@ -471,6 +471,25 @@ opRelationProj _ = ) +opPermInverse + :: ( Op x :< x + , Pretty x + , MonadFailDoc m + ) + => Proxy (m :: T.Type -> T.Type) + -> ( x -> x + , x -> m x + ) +opPermInverse _ = + ( inject . MkOpPermInverse . OpPermInverse + , \ p -> do + op <- project p + case op of + MkOpPermInverse (OpPermInverse x) -> return x + _ -> na ("Lenses.opPermInverse:" <++> pretty p) + ) + + opRelationImage :: ( Op x :< x , Pretty x From e113b7b309fb850c3f102a48c88608c24e062b88 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?=C3=96zg=C3=BCr=20Akg=C3=BCn?= Date: Fri, 6 Dec 2024 14:27:31 +0000 Subject: [PATCH 206/229] relaxed type-checking between an unnamed T and int:T --- src/Conjure/Language/Type.hs | 2 ++ 1 file changed, 2 insertions(+) diff --git a/src/Conjure/Language/Type.hs b/src/Conjure/Language/Type.hs index 9276948a68..6fb9b31b53 100644 --- a/src/Conjure/Language/Type.hs +++ b/src/Conjure/Language/Type.hs @@ -129,6 +129,8 @@ typeUnify (TypeInt t1) (TypeInt t2) = case ?typeCheckerMode of RelaxedIntegerTags -> True typeUnify (TypeEnum a) (TypeEnum b) = a == b typeUnify (TypeUnnamed a) (TypeUnnamed b) = a == b +typeUnify (TypeUnnamed (Name a)) (TypeInt (TagUnnamed b)) = a == b +typeUnify (TypeInt (TagUnnamed b)) (TypeUnnamed (Name a)) = a == b typeUnify (TypeTuple [TypeAny]) TypeTuple{} = True typeUnify TypeTuple{} (TypeTuple [TypeAny]) = True typeUnify (TypeTuple as) (TypeTuple bs) = (length as == length bs) && and (zipWith typeUnify as bs) From bb774d752aaa203c918d2fca2aabdc0cef5bef32 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?=C3=96zg=C3=BCr=20Akg=C3=BCn?= Date: Fri, 6 Dec 2024 15:13:35 +0000 Subject: [PATCH 207/229] add a new rule (transform-to-image) to restore functionality that was lost during the p -> ps generalisation --- src/Conjure/Rules/Transform.hs | 16 ++++++++++++---- 1 file changed, 12 insertions(+), 4 deletions(-) diff --git a/src/Conjure/Rules/Transform.hs b/src/Conjure/Rules/Transform.hs index 869a5428f1..831e0447dd 100644 --- a/src/Conjure/Rules/Transform.hs +++ b/src/Conjure/Rules/Transform.hs @@ -20,6 +20,7 @@ rules_Transform = rule_Transformed_Indexing, rule_Lift_Transformed_Indexing, rule_Transform_Indexing, + rule_TransformToImage, rule_Transform_Unifying -- rule_Transform_Variant_Literal, -- rule_Transform_Variant_Eq, @@ -402,9 +403,10 @@ rule_Transform_Indexing = "transform-indexing" `namedRule` theRule else na "rule_Transform_Indexing" theRule _ = na "rule_Transform_Indexing" -rule_Transform_Unifying :: Rule -rule_Transform_Unifying = "transform-unifying" `namedRule` theRule +rule_TransformToImage :: Rule +rule_TransformToImage = "transform-to-image" `namedRule` theRule where + -- transform([f], i) ~~> image(f, i) if the types match theRule [essence| transform([&morphism], &i) |] = do inner <- morphing =<< typeOf morphism typeI <- typeOf i @@ -415,6 +417,12 @@ rule_Transform_Unifying = "transform-unifying" `namedRule` theRule return [essence| image(&morphism, &i) |] ) else na "rule_Transform_Unifying" + theRule _ = na "rule_Transform_Unifying" + +rule_Transform_Unifying :: Rule +rule_Transform_Unifying = "transform-unifying" `namedRule` theRule + where + -- drop transforms that do not apply theRule p | Just (morphisms :: [Expression], i) <- match opTransform p = do typeI <- typeOf i morphisms' <- fmap catMaybes $ forM morphisms $ \morphism -> do @@ -428,12 +436,12 @@ rule_Transform_Unifying = "transform-unifying" `namedRule` theRule if null morphisms' then return - ( "Horizontal rule for transform unifying", + ( "Horizontal rule for transform unifying -- none of them apply", return i ) else return - ( "Horizontal rule for transform unifying", + ( "Horizontal rule for transform unifying -- some of the apply", return $ make opTransform morphisms' i ) theRule _ = na "rule_Transform_Unifying" From b3ef4122bc100b7603e2e3efee2da0fe5211f581 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?=C3=96zg=C3=BCr=20Akg=C3=BCn?= Date: Fri, 6 Dec 2024 15:26:43 +0000 Subject: [PATCH 208/229] rule_Transform_DotLess to also work with DotLt --- src/Conjure/Rules/Transform.hs | 31 ++++++++----------------------- 1 file changed, 8 insertions(+), 23 deletions(-) diff --git a/src/Conjure/Rules/Transform.hs b/src/Conjure/Rules/Transform.hs index 831e0447dd..04d3cc7af9 100644 --- a/src/Conjure/Rules/Transform.hs +++ b/src/Conjure/Rules/Transform.hs @@ -34,9 +34,11 @@ rules_Transform = rule_Transform_DotLess :: Rule rule_Transform_DotLess = "transform-dotless" `namedRule` theRule where - theRule [essence| &x .<= &rhs |] - | Just (ps, y) <- match opTransform rhs, + theRule p + | Just (x, rhs) <- match opDotLeq p <|> match opDotLt p, + Just (ps, y) <- match opTransform rhs, x == y = do + let mk = case match opDotLeq p of Just _ -> make opDotLeq; Nothing -> make opDotLt TypeMatrix {} <- typeOf x -- traceM $ show $ "rule_Transform_DotLess 1" <+> pretty x xIndices <- indexDomainsOf x @@ -49,7 +51,7 @@ rule_Transform_DotLess = "transform-dotless" `namedRule` theRule (iPat, i) <- quantifiedVar let transformed_i = make opTransform (map (make opPermInverse) ps) i let transformed_x_i = make opTransform ps [essence| &x[&transformed_i] |] - return [essence| &x .<= [ &transformed_x_i | &iPat : &xInd ] |] + return $ mk x [essence| [ &transformed_x_i | &iPat : &xInd ] |] ) [xInd1, xInd2] -> return @@ -61,28 +63,11 @@ rule_Transform_DotLess = "transform-dotless" `namedRule` theRule let transformed_i2 = make opTransform (map (make opPermInverse) ps) i2 let transformed_x_i1_i2 = make opTransform ps [essence| &x[&transformed_i1, &transformed_i2] |] return - [essence| - [ &x[&i1, &i2] - | &iPat1 : &xInd1 - , &iPat2 : &xInd2 - ] - .<= - [ &transformed_x_i1_i2 - | &iPat1 : &xInd1 - , &iPat2 : &xInd2 - ] - |] + $ mk + [essence| [ &x[&i1, &i2] | &iPat1 : &xInd1 , &iPat2 : &xInd2 ] |] + [essence| [ &transformed_x_i1_i2 | &iPat1 : &xInd1 , &iPat2 : &xInd2 ] |] ) _ -> na "rule_Transform_DotLess" - theRule [essence| &x .< transform([&p], &y) |] | x == y = do - TypeMatrix {} <- typeOf x - (xInd : _) <- indexDomainsOf x - return - ( "", - do - (iPat, i) <- quantifiedVar - return [essence| &x .< [ transform([&p], &x[transform([permInverse(&p)], &i)]) | &iPat : &xInd ] |] - ) theRule _ = na "rule_Transform_DotLess" rule_Transform_Functorially :: Rule From 41344cba4be08980bdcd6e6ad66425e96754b815 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?=C3=96zg=C3=BCr=20Akg=C3=BCn?= Date: Fri, 6 Dec 2024 16:01:22 +0000 Subject: [PATCH 209/229] permInverse on permutation literals that work on 2 objects --- .../Permutation/PermutationAsFunction.hs | 27 +++++++++++-------- 1 file changed, 16 insertions(+), 11 deletions(-) diff --git a/src/Conjure/Rules/Vertical/Permutation/PermutationAsFunction.hs b/src/Conjure/Rules/Vertical/Permutation/PermutationAsFunction.hs index 767d9712a6..a6cad61ff0 100644 --- a/src/Conjure/Rules/Vertical/Permutation/PermutationAsFunction.hs +++ b/src/Conjure/Rules/Vertical/Permutation/PermutationAsFunction.hs @@ -48,18 +48,18 @@ rule_Comprehension = "permutation-comprehension-tuples{AsFunction}" `namedRule` do (lPat, l) <- quantifiedVar (rPat, r) <- quantifiedVar - return $ - Comprehension body $ - gocBefore - ++ [ Generator - ( GenInExpr - pat - [essence| [(&l,&r) + return + $ Comprehension body + $ gocBefore + ++ [ Generator + ( GenInExpr + pat + [essence| [(&l,&r) | (&lPat, &rPat) <- &f , &l != &r] |] - ) - ] - ++ gocAfter + ) + ] + ++ gocAfter ) theRule _ = na "rule_Comprehension" @@ -114,5 +114,10 @@ rule_Image_permInverse = "permutation-image-permInverse{AsFunction}" `namedRule` ( "Vertical rule for permutation application to a type the permutation doesn't care about", return i ) - _ -> na "rule_Image_permInverse" + Just (_, [[_, _]]) -> + return + ( "Vertical rule for permutation application, where the permutation is a literal and contains 2 objects", + return [essence| image(&p, &i) |] + ) + _ -> na "rule_Image_permInverse" -- TODO: missing case for permutation literal theRule _ = na "rule_Image_permInverse" From d3e062f652cce3c528051dff462a58fc3acd19d5 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?=C3=96zg=C3=BCr=20Akg=C3=BCn?= Date: Thu, 12 Dec 2024 23:06:46 +0000 Subject: [PATCH 210/229] new transform rules --- src/Conjure/Compute/DomainUnion.hs | 352 ++++++++++-------- .../Language/Expression/Op/RelationProj.hs | 10 +- src/Conjure/Rules/Transform.hs | 277 +++++++++++++- 3 files changed, 467 insertions(+), 172 deletions(-) diff --git a/src/Conjure/Compute/DomainUnion.hs b/src/Conjure/Compute/DomainUnion.hs index fdb0729277..983fa48368 100644 --- a/src/Conjure/Compute/DomainUnion.hs +++ b/src/Conjure/Compute/DomainUnion.hs @@ -1,205 +1,229 @@ {-# LANGUAGE TupleSections #-} -{-# LANGUAGE NoMonomorphismRestriction #-} {-# LANGUAGE UndecidableInstances #-} +{-# LANGUAGE NoMonomorphismRestriction #-} module Conjure.Compute.DomainUnion - ( domainUnion, domainUnions - ) where + ( domainUnion, + domainUnions, + ) +where -- conjure -import Conjure.Prelude + import Conjure.Bug +import Conjure.Language.AdHoc import Conjure.Language.Domain -import Conjure.Language.Type import Conjure.Language.Expression.Op -import Conjure.Language.AdHoc -import Conjure.Language.Pretty import Conjure.Language.Lenses - -import Data.List as L ( union ) - +import Conjure.Language.Name +import Conjure.Language.Pretty +import Conjure.Language.Type +import Conjure.Prelude +import Data.List as L (union) -- containers -import Data.Set as S ( union ) +import Data.Set as S (union) class DomainUnion a where - domainUnion :: (Applicative m, Monad m) => a -> a -> m a - -domainUnions - :: ( Applicative m, Monad m - , Pretty r, Default r - , Eq x, Pretty x, ExpressionLike x, Op x :< x - ) => [Domain r x] -> m (Domain r x) + domainUnion :: (Applicative m, Monad m) => a -> a -> m a + +domainUnions :: + ( Applicative m, + Monad m, + Pretty r, + Default r, + Eq x, + Pretty x, + ExpressionLike x, + Op x :< x + ) => + [Domain r x] -> + m (Domain r x) domainUnions [] = return $ DomainAny "domainUnions []" TypeAny domainUnions [a] = return a -domainUnions (a:as) = do b <- domainUnions as ; domainUnion a b - +domainUnions (a : as) = do b <- domainUnions as; domainUnion a b instance - ( Eq x - , ExpressionLike x - , Op x :< x - , Pretty x - , Pretty r - , Default r - ) => DomainUnion (Domain r x) where - domainUnion DomainAny{} d = return d - domainUnion d DomainAny{} = return d - domainUnion DomainBool DomainBool = return DomainBool - domainUnion (DomainInt t r1) (DomainInt _ r2) = - return $ DomainInt t (r1 `L.union` r2) - domainUnion (DomainTuple []) d@DomainTuple{} = return d - domainUnion d@DomainTuple{} (DomainTuple []) = return d - domainUnion (DomainTuple xs) (DomainTuple ys) - | length xs == length ys - = DomainTuple <$> zipWithM domainUnion xs ys - domainUnion d1@(DomainRecord xs) d2@(DomainRecord ys) - | length xs == length ys - = DomainRecord <$> sequence [ case mdomY of - Just domY -> do - domZ <- domainUnion domX domY - return (nm, domZ) - Nothing -> bug $ vcat ["Domain.domainUnion", pretty d1, pretty d2] - | (nm, domX) <- xs - , let mdomY = lookup nm ys - ] - domainUnion (DomainMatrix x1 x2) (DomainMatrix y1 y2) - = DomainMatrix <$> domainUnion x1 y1 <*> domainUnion x2 y2 - domainUnion (DomainSet _ xA x) (DomainSet _ yA y) - = DomainSet def <$> domainUnion xA yA <*> domainUnion x y - domainUnion (DomainMSet _ xA x) (DomainMSet _ yA y) - = DomainMSet def <$> domainUnion xA yA <*> domainUnion x y - domainUnion (DomainFunction _ xA x1 x2) (DomainFunction _ yA y1 y2) - = DomainFunction def <$> domainUnion xA yA <*> domainUnion x1 y1 <*> domainUnion x2 y2 - domainUnion (DomainSequence _ xA x) (DomainSequence _ yA y) - = DomainSequence def <$> domainUnion xA yA <*> domainUnion x y - domainUnion (DomainRelation _ _ []) d@DomainRelation{} = return d - domainUnion d@DomainRelation{} (DomainRelation _ _ []) = return d - domainUnion (DomainRelation _ xA xs) (DomainRelation _ yA ys) - | length xs == length ys - = DomainRelation def <$> domainUnion xA yA <*> zipWithM domainUnion xs ys - domainUnion (DomainPartition _ xA x) (DomainPartition _ yA y) - = DomainPartition def <$> domainUnion xA yA <*> domainUnion x y - domainUnion (DomainPermutation _ xA x) (DomainPermutation _ yA y) - = DomainPermutation def <$> domainUnion xA yA <*> domainUnion x y - domainUnion d1 d2 = bug $ vcat ["Domain.domainUnion", pretty d1, pretty d2] - + ( Eq x, + ExpressionLike x, + Op x :< x, + Pretty x, + Pretty r, + Default r + ) => + DomainUnion (Domain r x) + where + domainUnion d@(DomainReference nm1 _) (DomainReference nm2 _) | nm1 == nm2 = return d + domainUnion d@(DomainInt (TagUnnamed nm1) _) (DomainReference (Name nm2) _) | nm1 == nm2 = return d + domainUnion (DomainReference (Name nm2) _) d@(DomainInt (TagUnnamed nm1) _) | nm1 == nm2 = return d + domainUnion DomainAny {} d = return d + domainUnion d DomainAny {} = return d + domainUnion DomainBool DomainBool = return DomainBool + domainUnion (DomainInt t r1) (DomainInt _ r2) = + return $ DomainInt t (r1 `L.union` r2) + domainUnion (DomainTuple []) d@DomainTuple {} = return d + domainUnion d@DomainTuple {} (DomainTuple []) = return d + domainUnion (DomainTuple xs) (DomainTuple ys) + | length xs == length ys = + DomainTuple <$> zipWithM domainUnion xs ys + domainUnion d1@(DomainRecord xs) d2@(DomainRecord ys) + | length xs == length ys = + DomainRecord + <$> sequence + [ case mdomY of + Just domY -> do + domZ <- domainUnion domX domY + return (nm, domZ) + Nothing -> bug $ vcat ["Domain.domainUnion", pretty d1, pretty d2] + | (nm, domX) <- xs, + let mdomY = lookup nm ys + ] + domainUnion (DomainMatrix x1 x2) (DomainMatrix y1 y2) = + DomainMatrix <$> domainUnion x1 y1 <*> domainUnion x2 y2 + domainUnion (DomainSet _ xA x) (DomainSet _ yA y) = + DomainSet def <$> domainUnion xA yA <*> domainUnion x y + domainUnion (DomainMSet _ xA x) (DomainMSet _ yA y) = + DomainMSet def <$> domainUnion xA yA <*> domainUnion x y + domainUnion (DomainFunction _ xA x1 x2) (DomainFunction _ yA y1 y2) = + DomainFunction def <$> domainUnion xA yA <*> domainUnion x1 y1 <*> domainUnion x2 y2 + domainUnion (DomainSequence _ xA x) (DomainSequence _ yA y) = + DomainSequence def <$> domainUnion xA yA <*> domainUnion x y + domainUnion (DomainRelation _ _ []) d@DomainRelation {} = return d + domainUnion d@DomainRelation {} (DomainRelation _ _ []) = return d + domainUnion (DomainRelation _ xA xs) (DomainRelation _ yA ys) + | length xs == length ys = + DomainRelation def <$> domainUnion xA yA <*> zipWithM domainUnion xs ys + domainUnion (DomainPartition _ xA x) (DomainPartition _ yA y) = + DomainPartition def <$> domainUnion xA yA <*> domainUnion x y + domainUnion (DomainPermutation _ xA x) (DomainPermutation _ yA y) = + DomainPermutation def <$> domainUnion xA yA <*> domainUnion x y + domainUnion d1 d2 = bug $ vcat ["Domain.domainUnion", pretty (show d1), pretty (show d2)] instance - ( ExpressionLike x - , Op x :< x - , Pretty x - ) => DomainUnion (SetAttr x) where - domainUnion (SetAttr a) (SetAttr b) = SetAttr <$> domainUnion a b - + ( ExpressionLike x, + Op x :< x, + Pretty x + ) => + DomainUnion (SetAttr x) + where + domainUnion (SetAttr a) (SetAttr b) = SetAttr <$> domainUnion a b instance - ( ExpressionLike x - , Op x :< x - , Pretty x - , Eq x - ) => DomainUnion (PermutationAttr x) where - domainUnion (PermutationAttr a) (PermutationAttr b) - | a == b = return (PermutationAttr a) - | otherwise = bug "DomainUnion PermutationAttr" - + ( ExpressionLike x, + Op x :< x, + Pretty x, + Eq x + ) => + DomainUnion (PermutationAttr x) + where + domainUnion (PermutationAttr a) (PermutationAttr b) + | a == b = return (PermutationAttr a) + | otherwise = bug "DomainUnion PermutationAttr" instance - ( ExpressionLike x - , Op x :< x - , Pretty x - ) => DomainUnion (SizeAttr x) where - domainUnion SizeAttr_None s = return s - domainUnion s SizeAttr_None = return s - domainUnion a b = return $ SizeAttr_MinMaxSize - (make opMin (fromList [minA, minB])) - (make opMax (fromList [maxA, maxB])) - where - (minA, maxA) = getMinMax a - (minB, maxB) = getMinMax b - getMinMax p = case p of - SizeAttr_None -> bug "Monoid SizeAttr" - SizeAttr_Size x -> (x,x) - SizeAttr_MinSize x -> (x,x) - SizeAttr_MaxSize x -> (x,x) - SizeAttr_MinMaxSize x y -> (x,y) - + ( ExpressionLike x, + Op x :< x, + Pretty x + ) => + DomainUnion (SizeAttr x) + where + domainUnion SizeAttr_None s = return s + domainUnion s SizeAttr_None = return s + domainUnion a b = + return + $ SizeAttr_MinMaxSize + (make opMin (fromList [minA, minB])) + (make opMax (fromList [maxA, maxB])) + where + (minA, maxA) = getMinMax a + (minB, maxB) = getMinMax b + getMinMax p = case p of + SizeAttr_None -> bug "Monoid SizeAttr" + SizeAttr_Size x -> (x, x) + SizeAttr_MinSize x -> (x, x) + SizeAttr_MaxSize x -> (x, x) + SizeAttr_MinMaxSize x y -> (x, y) instance - ( ExpressionLike x - , Op x :< x - , Pretty x - ) => DomainUnion (MSetAttr x) where - domainUnion (MSetAttr a1 a2) (MSetAttr b1 b2) = MSetAttr <$> domainUnion a1 b1 <*> domainUnion a2 b2 - + ( ExpressionLike x, + Op x :< x, + Pretty x + ) => + DomainUnion (MSetAttr x) + where + domainUnion (MSetAttr a1 a2) (MSetAttr b1 b2) = MSetAttr <$> domainUnion a1 b1 <*> domainUnion a2 b2 instance - ( ExpressionLike x - , Op x :< x - , Pretty x - ) => DomainUnion (OccurAttr x) where - domainUnion OccurAttr_None s = return s - domainUnion s OccurAttr_None = return s - domainUnion a b = return $ OccurAttr_MinMaxOccur - (make opMin (fromList [minA, minB])) - (make opMax (fromList [maxA, maxB])) - where - (minA, maxA) = getMinMax a - (minB, maxB) = getMinMax b - getMinMax p = case p of - OccurAttr_None -> bug "Monoid OccurAttr" - OccurAttr_MinOccur x -> (x,x) - OccurAttr_MaxOccur x -> (x,x) - OccurAttr_MinMaxOccur x y -> (x,y) - + ( ExpressionLike x, + Op x :< x, + Pretty x + ) => + DomainUnion (OccurAttr x) + where + domainUnion OccurAttr_None s = return s + domainUnion s OccurAttr_None = return s + domainUnion a b = + return + $ OccurAttr_MinMaxOccur + (make opMin (fromList [minA, minB])) + (make opMax (fromList [maxA, maxB])) + where + (minA, maxA) = getMinMax a + (minB, maxB) = getMinMax b + getMinMax p = case p of + OccurAttr_None -> bug "Monoid OccurAttr" + OccurAttr_MinOccur x -> (x, x) + OccurAttr_MaxOccur x -> (x, x) + OccurAttr_MinMaxOccur x y -> (x, y) instance - ( ExpressionLike x - , Op x :< x - , Pretty x - ) => DomainUnion (FunctionAttr x) where - domainUnion (FunctionAttr a1 a2 a3) (FunctionAttr b1 b2 b3) = - FunctionAttr <$> domainUnion a1 b1 <*> domainUnion a2 b2 <*> domainUnion a3 b3 - + ( ExpressionLike x, + Op x :< x, + Pretty x + ) => + DomainUnion (FunctionAttr x) + where + domainUnion (FunctionAttr a1 a2 a3) (FunctionAttr b1 b2 b3) = + FunctionAttr <$> domainUnion a1 b1 <*> domainUnion a2 b2 <*> domainUnion a3 b3 instance DomainUnion PartialityAttr where - domainUnion PartialityAttr_Partial _ = return PartialityAttr_Partial - domainUnion _ PartialityAttr_Partial = return PartialityAttr_Partial - domainUnion PartialityAttr_Total PartialityAttr_Total = return PartialityAttr_Total - + domainUnion PartialityAttr_Partial _ = return PartialityAttr_Partial + domainUnion _ PartialityAttr_Partial = return PartialityAttr_Partial + domainUnion PartialityAttr_Total PartialityAttr_Total = return PartialityAttr_Total instance DomainUnion JectivityAttr where - domainUnion x y | x == y = return x - domainUnion _ _ = return JectivityAttr_None - + domainUnion x y | x == y = return x + domainUnion _ _ = return JectivityAttr_None instance - ( ExpressionLike x - , Op x :< x - , Pretty x - ) => DomainUnion (SequenceAttr x) where - domainUnion (SequenceAttr a1 a2) (SequenceAttr b1 b2) = - SequenceAttr <$> domainUnion a1 b1 <*> domainUnion a2 b2 - + ( ExpressionLike x, + Op x :< x, + Pretty x + ) => + DomainUnion (SequenceAttr x) + where + domainUnion (SequenceAttr a1 a2) (SequenceAttr b1 b2) = + SequenceAttr <$> domainUnion a1 b1 <*> domainUnion a2 b2 instance - ( ExpressionLike x - , Op x :< x - , Pretty x - ) => DomainUnion (RelationAttr x) where - domainUnion (RelationAttr a1 a2) (RelationAttr b1 b2) = - RelationAttr <$> domainUnion a1 b1 <*> domainUnion a2 b2 - + ( ExpressionLike x, + Op x :< x, + Pretty x + ) => + DomainUnion (RelationAttr x) + where + domainUnion (RelationAttr a1 a2) (RelationAttr b1 b2) = + RelationAttr <$> domainUnion a1 b1 <*> domainUnion a2 b2 instance DomainUnion BinaryRelationAttrs where - domainUnion (BinaryRelationAttrs a) (BinaryRelationAttrs b) = - return $ BinaryRelationAttrs (S.union a b) - + domainUnion (BinaryRelationAttrs a) (BinaryRelationAttrs b) = + return $ BinaryRelationAttrs (S.union a b) instance - ( ExpressionLike x - , Op x :< x - , Pretty x - ) => DomainUnion (PartitionAttr x) where - domainUnion (PartitionAttr a1 a2 a3) (PartitionAttr b1 b2 b3) = - PartitionAttr <$> domainUnion a1 b1 <*> domainUnion a2 b2 <*> pure (a3 || b3) - + ( ExpressionLike x, + Op x :< x, + Pretty x + ) => + DomainUnion (PartitionAttr x) + where + domainUnion (PartitionAttr a1 a2 a3) (PartitionAttr b1 b2 b3) = + PartitionAttr <$> domainUnion a1 b1 <*> domainUnion a2 b2 <*> pure (a3 || b3) diff --git a/src/Conjure/Language/Expression/Op/RelationProj.hs b/src/Conjure/Language/Expression/Op/RelationProj.hs index 9ed0ad1250..39d1ec39e0 100644 --- a/src/Conjure/Language/Expression/Op/RelationProj.hs +++ b/src/Conjure/Language/Expression/Op/RelationProj.hs @@ -32,8 +32,8 @@ instance (TypeOf x, Pretty x) => TypeOf (OpRelationProj x) where tyI <- typeOf i if typesUnify [tyI,t] then loop is ts - else raiseTypeError $ "(relation projection)" <+> pretty p - loop _ _ = raiseTypeError $ "(relation projection)" <+> pretty p + else raiseTypeError $ "(relation projection 1)" <+> pretty p + loop _ _ = raiseTypeError $ "(relation projection 2)" <+> pretty p loop xs' ts' else do let loop [] [] = return [] @@ -42,10 +42,10 @@ instance (TypeOf x, Pretty x) => TypeOf (OpRelationProj x) where tyI <- typeOf i if typesUnify [tyI,t] then loop is ts - else raiseTypeError $ "(relation projection)" <+> pretty p - loop _ _ = raiseTypeError $ "(relation projection)" <+> pretty p + else raiseTypeError $ "(relation projection 3)" <+> pretty p + loop _ _ = raiseTypeError $ "(relation projection 4)" <+> pretty p TypeRelation <$> loop xs ts' - _ -> raiseTypeError $ "(relation projection)" <+> vcat [pretty p, pretty tyR] + _ -> raiseTypeError $ "(relation projection 5)" <+> vcat [pretty p, pretty tyR] instance SimplifyOp OpRelationProj x where simplifyOp _ = na "simplifyOp{OpRelationProj}" diff --git a/src/Conjure/Rules/Transform.hs b/src/Conjure/Rules/Transform.hs index 04d3cc7af9..5d3a369a41 100644 --- a/src/Conjure/Rules/Transform.hs +++ b/src/Conjure/Rules/Transform.hs @@ -8,8 +8,13 @@ import Conjure.Rules.Import rules_Transform :: [Rule] rules_Transform = - [ rule_Transform_DotLess, + [ rule_Transform_DotLess_matrix, + rule_Transform_DotLess_function, + rule_Transform_DotLess_set, + rule_Transform_DotLess_relation, -- rule_Transform_Sequence_Literal, + rule_Transform_FunctionImage, + rule_Transform_Tuple, rule_Transform_Functorially, rule_Transform_Comprehension, rule_Transform_Product_Types, @@ -31,8 +36,8 @@ rules_Transform = -- rule_Transformed_Variant_Active ] -rule_Transform_DotLess :: Rule -rule_Transform_DotLess = "transform-dotless" `namedRule` theRule +rule_Transform_DotLess_matrix :: Rule +rule_Transform_DotLess_matrix = "transform-dotless" `namedRule` theRule where theRule p | Just (x, rhs) <- match opDotLeq p <|> match opDotLt p, @@ -70,6 +75,270 @@ rule_Transform_DotLess = "transform-dotless" `namedRule` theRule _ -> na "rule_Transform_DotLess" theRule _ = na "rule_Transform_DotLess" +rule_Transform_DotLess_function :: Rule +rule_Transform_DotLess_function = "transform-dotless-function" `namedRule` theRule + where + theRule p + | Just (x, rhs) <- match opDotLeq p <|> match opDotLt p, + Just (ps, y) <- match opTransform rhs, + x == y = do + let mk :: Expression -> Expression -> Expression = case match opDotLeq p of Just _ -> make opDotLeq; Nothing -> make opDotLt + TypeFunction {} <- typeOf x + -- traceM $ show $ "rule_Transform_DotLess 1 x" <+> pretty x + domain_x@(DomainFunction _ _ _fr _to) <- domainOf x + -- traceM $ show $ "rule_Transform_DotLess 2 fr" <+> pretty fr + -- traceM $ show $ "rule_Transform_DotLess 2 to" <+> pretty to + + return + ( "", + do + (auxName, x') <- auxiliaryVar + (iPat, i) <- quantifiedVar + + let lhs1_inner = make opTransform ps [essence| &i[1] |] + let lhs1 = make opImage x' lhs1_inner + let rhs1 = make opTransform ps [essence| &i[2] |] + + let lhs2_inner = make opTransform (map (make opPermInverse) ps) [essence| &i[1] |] + let lhs2 = make opImage x lhs2_inner + let rhs2 = make opTransform (map (make opPermInverse) ps) [essence| &i[2] |] + + return + $ WithLocals + (mk x x') + ( AuxiliaryVars + [ Declaration (FindOrGiven LocalFind auxName domain_x), + SuchThat + [ [essence| forAll &iPat in &x . &lhs1 = &rhs1 |], + [essence| forAll &iPat in &x' . &lhs2 = &rhs2 |] + ] + ] + ) + ) + -- na "" + + -- x : function T --> U + -- x' : function T --> U + -- such that forAll (t,u) in x . x'(transform(ps, t)) = transform(ps, u) + -- such that forAll (t,u) in x' . x(transform(permInverse(ps), t)) = transform(permInverse(ps), u) + + -- x: set/mset/func... + -- forAll i : innerDomainOf(x) . INSIDE-LHS = INSIDE-RHS + + -- INSIDE-LHS + -- set: i in x + -- mset: freq(i, x) + -- function: i in x -- same as (x[i[0]] = i[1]) + -- partition: i in parts(x) + + -- INSIDE-RHS + -- set: transform(ps, i) in x' + -- mset: freq(transform(ps, i), x') + -- function: transform(ps, i) in x' + -- relation: same as func + -- partition: transform(ps, i) in parts(x') + + -- x, x' : set of T + -- set: forAll i : . i in x <-> transform(ps, i) in x' + -- mset: forAll i : T . i in x <-> transform(ps, i) in x' + + -- such that forAll t in x . transform(ps, t) in x' + -- such that forAll t in x' . transform(permInverse(ps), t) in x + + -- x, x' : mset of T + -- such that forAll t in x . freq(transform(ps, t), x') = freq(t, x) + -- such that forAll t in x' . freq(transform(permInverse(ps), t), x) = freq(t, x') + + -- x, x' : relation (A,B,C) + -- such that forAll entry in x . transform(ps, entry) in x' + -- such that forAll entry in x' . transform(permInverse(ps), entry) in x + + -- x, x' : partition of set of T + -- such that forAll i1, i2 : set of T . together({i1, i2}, x) <-> together({transform(ps, x), transform(ps, y)}, x') + + theRule _ = na "rule_Transform_DotLess" + +rule_Transform_DotLess_set :: Rule +rule_Transform_DotLess_set = "transform-dotless-set" `namedRule` theRule + where + theRule p + | Just (x, rhs) <- match opDotLeq p <|> match opDotLt p, + Just (ps, y) <- match opTransform rhs, + x == y = do + let mk :: Expression -> Expression -> Expression = case match opDotLeq p of Just _ -> make opDotLeq; Nothing -> make opDotLt + TypeSet {} <- typeOf x + domain_x@DomainSet {} <- domainOf x + + return + ( "", + do + (auxName, x') <- auxiliaryVar + (iPat, i) <- quantifiedVar + + let transform_i = make opTransform ps i + let transform_i' = make opTransform (map (make opPermInverse) ps) i + + return + $ WithLocals + (mk x x') + ( AuxiliaryVars + [ Declaration (FindOrGiven LocalFind auxName domain_x), + SuchThat + [ [essence| forAll &iPat in &x . &transform_i in &x' |], + [essence| forAll &iPat in &x' . &transform_i' in &x |] + ] + ] + ) + ) + theRule _ = na "rule_Transform_DotLess" + +rule_Transform_DotLess_relation :: Rule +rule_Transform_DotLess_relation = "transform-dotless-relation" `namedRule` theRule + where + theRule p + | Just (x, rhs) <- match opDotLeq p <|> match opDotLt p, + Just (ps, y) <- match opTransform rhs, + x == y = do + let mk :: Expression -> Expression -> Expression = case match opDotLeq p of Just _ -> make opDotLeq; Nothing -> make opDotLt + TypeRelation {} <- typeOf x + domain_x@DomainRelation {} <- domainOf x + + return + ( "", + do + (auxName, x') <- auxiliaryVar + (iPat, i) <- quantifiedVar + + let transform_i = make opTransform ps i + let transform_i' = make opTransform (map (make opPermInverse) ps) i + + return + $ WithLocals + (mk x x') + ( AuxiliaryVars + [ Declaration (FindOrGiven LocalFind auxName domain_x), + SuchThat + [ [essence| forAll &iPat in &x . &transform_i in &x' |], + [essence| forAll &iPat in &x' . &transform_i' in &x |] + ] + ] + ) + ) + theRule _ = na "rule_Transform_DotLess" + +rule_Transform_DotLess_rest :: Rule +rule_Transform_DotLess_rest = "transform-dotless" `namedRule` theRule + where + theRule p + | Just (x, rhs) <- match opDotLeq p <|> match opDotLt p, + Just (ps, y) <- match opTransform rhs, + x == y = do + let mk = case match opDotLeq p of Just _ -> make opDotLeq; Nothing -> make opDotLt + TypeFunction {} <- typeOf x + -- traceM $ show $ "rule_Transform_DotLess 1" <+> pretty x + xIndices <- indexDomainsOf x + -- traceM $ show $ "rule_Transform_DotLess 2" <+> vcat (map pretty xIndices) + case xIndices of + [xInd] -> + -- x .<= transform(ps, x) + + -- x .<= [ transform(ps, x[transform(permInverse(ps), i)]) | i : indexOf(x) ] + + -- x : function T --> U + -- x' : function T --> U + -- such that forAll (t,u) in x . x'(transform(ps, t)) = transform(ps, u) + -- such that forAll (t,u) in x' . x(transform(permInverse(ps), t)) = transform(permInverse(ps), u) + + -- x: set/mset/func... + -- forAll i : innerDomainOf(x) . INSIDE-LHS = INSIDE-RHS + + -- INSIDE-LHS + -- set: i in x + -- mset: freq(i, x) + -- function: i in x -- same as (x[i[0]] = i[1]) + -- partition: i in parts(x) + + -- INSIDE-RHS + -- set: transform(ps, i) in x' + -- mset: freq(transform(ps, i), x') + -- function: transform(ps, i) in x' + -- relation: same as func + -- partition: transform(ps, i) in parts(x') + + -- x, x' : set of T + -- set: forAll i : . i in x <-> transform(ps, i) in x' + -- mset: forAll i : T . i in x <-> transform(ps, i) in x' + + -- such that forAll t in x . transform(ps, t) in x' + -- such that forAll t in x' . transform(permInverse(ps), t) in x + + -- x, x' : mset of T + -- such that forAll t in x . freq(transform(ps, t), x') = freq(t, x) + -- such that forAll t in x' . freq(transform(permInverse(ps), t), x) = freq(t, x') + + -- x, x' : relation (A,B,C) + -- such that forAll entry in x . transform(ps, entry) in x' + -- such that forAll entry in x' . transform(permInverse(ps), entry) in x + + -- x, x' : partition of set of T + -- such that forAll i1, i2 : set of T . together({i1, i2}, x) <-> together({transform(ps, x), transform(ps, y)}, x') + + return + ( "", + do + (iPat, i) <- quantifiedVar + let transformed_i = make opTransform (map (make opPermInverse) ps) i + let transformed_x_i = make opTransform ps [essence| &x[&transformed_i] |] + return $ mk x [essence| [ &transformed_x_i | &iPat : &xInd ] |] + ) + [xInd1, xInd2] -> + return + ( "", + do + (iPat1, i1) <- quantifiedVar + (iPat2, i2) <- quantifiedVar + let transformed_i1 = make opTransform (map (make opPermInverse) ps) i1 + let transformed_i2 = make opTransform (map (make opPermInverse) ps) i2 + let transformed_x_i1_i2 = make opTransform ps [essence| &x[&transformed_i1, &transformed_i2] |] + return + $ mk + [essence| [ &x[&i1, &i2] | &iPat1 : &xInd1 , &iPat2 : &xInd2 ] |] + [essence| [ &transformed_x_i1_i2 | &iPat1 : &xInd1 , &iPat2 : &xInd2 ] |] + ) + _ -> na "rule_Transform_DotLess" + theRule _ = na "rule_Transform_DotLess" + +-- transform(p, x)[i] ~~> transform(p, x[transform(permInverse(p), i)]) +-- transform(p, f)[x] ~~> transform(p, f[transform(permInverse(p), x)]) +-- image(transform(p, f), x) ~~> transform(p, image(f, transform(permInverse(p), x))) +rule_Transform_FunctionImage :: Rule +rule_Transform_FunctionImage = "transform-function-image" `namedRule` theRule + where + theRule [essence| image(transform([&p], &f), &x) |] = do + return ("", return [essence| transform([&p], image(&f, transform([permInverse(&p)], &x))) |]) + theRule _ = na "rule_Transform_FunctionImage" + +-- transform(p, x)[i] ~~> transform(p, x[transform(permInverse(p), i)]) +-- transform(p, f)[x] ~~> transform(p, f[transform(permInverse(p), x)]) +-- image(transform(p, f), x) ~~> transform(p, image(f, transform(permInverse(p), x))) +rule_Transform_Tuple :: Rule +rule_Transform_Tuple = "transform-tuple" `namedRule` theRule + where + theRule p + | Just (ps, tup) <- match opTransform p, + Just (TypeTuple tup_types) <- typeOf tup = + return + ( "", + return + $ AbstractLiteral + $ AbsLitTuple + [ make opTransform ps [essence| &tup[&i] |] + | iInt <- take (length tup_types) allNats, + let i = fromInt iInt + ] + ) + theRule _ = na "rule_Transform_Tuple" + rule_Transform_Functorially :: Rule rule_Transform_Functorially = "transform-functorially" `namedRule` theRule where @@ -327,6 +596,7 @@ rule_Transformed_Indexing = "transformed-indexing" `namedRule` theRule Generator (GenInExpr (Single pat) expr) -> return (pat, expr) _ -> na "rule_Transformed_Indexing" (matexp, indexer) <- match opIndexing exp + TypeMatrix {} <- typeOf matexp ([morphism], mat) <- match opTransform matexp ty <- typeOf mat inn <- morphing =<< typeOf morphism @@ -367,6 +637,7 @@ rule_Transform_Indexing = "transform-indexing" `namedRule` theRule _ -> na "rule_Transform_Indexing" ([morphism], matexp) <- match opTransform expr (mat, indexer) <- match opIndexing matexp + TypeMatrix {} <- typeOf mat ty <- typeOf mat inn <- morphing =<< typeOf morphism if let ?typeCheckerMode = StronglyTyped in ty `containsType` inn From 296017e798259273eb61de149e0fe1a76c232277 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?=C3=96zg=C3=BCr=20Akg=C3=BCn?= Date: Sat, 14 Dec 2024 17:24:51 +0000 Subject: [PATCH 211/229] better messages --- src/Conjure/Language/Expression/Op/Indexing.hs | 4 ++-- src/Conjure/Rules/Transform.hs | 2 +- 2 files changed, 3 insertions(+), 3 deletions(-) diff --git a/src/Conjure/Language/Expression/Op/Indexing.hs b/src/Conjure/Language/Expression/Op/Indexing.hs index a620e00480..8567176db3 100644 --- a/src/Conjure/Language/Expression/Op/Indexing.hs +++ b/src/Conjure/Language/Expression/Op/Indexing.hs @@ -29,7 +29,7 @@ instance (TypeOf x, Pretty x, ExpressionLike x, ReferenceContainer x) => TypeOf case tyM of TypeMatrix tyIndex inn | typesUnify [tyIndex, tyI] -> return inn - | otherwise -> failDoc $ "Indexing with inappropriate type:" <++> vcat + | otherwise -> failDoc $ "Indexing with inappropriate type, matrix:" <++> vcat [ "The expression:" <+> pretty p , "Indexing:" <+> pretty m , "Expected type of index:" <+> pretty tyIndex @@ -37,7 +37,7 @@ instance (TypeOf x, Pretty x, ExpressionLike x, ReferenceContainer x) => TypeOf ] TypeList inn | typesUnify [TypeInt TagInt, tyI] -> return inn - | otherwise -> failDoc $ "Indexing with inappropriate type:" <++> vcat + | otherwise -> failDoc $ "Indexing with inappropriate type, list:" <++> vcat [ "The expression:" <+> pretty p , "Indexing:" <+> pretty m , "Expected type of index:" <+> pretty (TypeInt TagInt) diff --git a/src/Conjure/Rules/Transform.hs b/src/Conjure/Rules/Transform.hs index 5d3a369a41..85c7a604b7 100644 --- a/src/Conjure/Rules/Transform.hs +++ b/src/Conjure/Rules/Transform.hs @@ -697,7 +697,7 @@ rule_Transform_Unifying = "transform-unifying" `namedRule` theRule ) else return - ( "Horizontal rule for transform unifying -- some of the apply", + ( "Horizontal rule for transform unifying -- some of them apply", return $ make opTransform morphisms' i ) theRule _ = na "rule_Transform_Unifying" From 571ae7a2711dae969546b29154a1dc426fec2cf4 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?=C3=96zg=C3=BCr=20Akg=C3=BCn?= Date: Sat, 14 Dec 2024 18:37:05 +0000 Subject: [PATCH 212/229] liftvars, bugfix --- src/Conjure/Rules/BubbleUp.hs | 33 +++++++++++++++++++++++++++++++++ 1 file changed, 33 insertions(+) diff --git a/src/Conjure/Rules/BubbleUp.hs b/src/Conjure/Rules/BubbleUp.hs index d644712823..d3f008ccc0 100644 --- a/src/Conjure/Rules/BubbleUp.hs +++ b/src/Conjure/Rules/BubbleUp.hs @@ -209,12 +209,42 @@ rule_LiftVars = "bubble-up-LiftVars" `namedRule` theRule where | (nm, dom) <- decls , let domLifted = foldr (DomainMatrix . forgetRepr) dom indexDomains ] + let declsLiftedNames = + [ nm + | (nm, _dom) <- decls + ] + + -- traceM $ show $ "declsLifted" <+> vcat (map pretty declsLifted) let consLifted = [ make opAnd $ Comprehension c generators | c <- transformBi upd cons ] + -- traceM $ show $ "consLifted" <+> vcat (map pretty consLifted) + -- traceM $ show $ "head lifted 1" <+> pretty body + -- traceM $ show $ "head lifted 2" <+> pretty (transform upd body) + + let referencesInCons = nub [ r | r@(Reference _ (Just (DeclHasRepr {}))) <- concatMap universe cons] + let referencesInBody = nub [ r | r@(Reference _ (Just (DeclHasRepr {}))) <- universe body] + -- traceM $ show $ "referencesInBody" <+> vcat (map pretty referencesInBody) + + let pr :: Name -> String = show . pretty + + -- the name is a prefix of a name that's defined in the decls, but not identical + let unrefinedInBody = [ name | Reference name _ <- referencesInBody + , or [ pr name `isPrefixOf` pr declName && pr declName /= pr name | declName <- declsLiftedNames ] + ] + + let unrefinedInCons = [ name | Reference name _ <- referencesInCons + , or [ pr name `isPrefixOf` pr declName && pr declName /= pr name | declName <- declsLiftedNames ] + ] + + -- traceM $ show $ "unrefinedInBody" <+> vcat (map pretty unrefinedInBody) + -- traceM $ show $ "unrefinedInCons" <+> vcat (map pretty unrefinedInCons) + + when (not (null unrefinedInBody) || not (null unrefinedInCons)) $ na "rule_LiftVars" + return ( "Bubbling up auxiliary variables through a comprehension." , return $ WithLocals (Comprehension (transform upd body) (transformBi upd gensOrConds)) @@ -247,6 +277,9 @@ rule_LiftVars = "bubble-up-LiftVars" `namedRule` theRule where ) theRule p = do + case p of + Comprehension{} -> na "rule_LiftVars" + _ -> return () let f (WithLocals y (AuxiliaryVars locals@(_:_))) = do tell locals From 16c4c413f9092123eac7ba7e88b13ed2c7975025 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?=C3=96zg=C3=BCr=20Akg=C3=BCn?= Date: Sat, 14 Dec 2024 19:53:24 +0000 Subject: [PATCH 213/229] dontcare unless condition during lifting - hack that was left in for 9 years removed!! --- src/Conjure/Rules/BubbleUp.hs | 17 ++++++++++++----- 1 file changed, 12 insertions(+), 5 deletions(-) diff --git a/src/Conjure/Rules/BubbleUp.hs b/src/Conjure/Rules/BubbleUp.hs index d3f008ccc0..631231585b 100644 --- a/src/Conjure/Rules/BubbleUp.hs +++ b/src/Conjure/Rules/BubbleUp.hs @@ -187,15 +187,18 @@ rule_LiftVars = "bubble-up-LiftVars" `namedRule` theRule where let decls = [ (nm,dom) | Declaration (FindOrGiven LocalFind nm dom) <- locals ] let cons = concat [ xs | SuchThat xs <- locals ] - -- TODO: what to do with the conditions? - -- should we `dontCare unless condition`? - -- discard for now (_conditions, generators) <- fmap mconcat $ forM gensOrConds $ \ goc -> case goc of Condition{} -> return ([goc], []) ComprehensionLetting{} -> return ([], [goc]) Generator (GenDomainHasRepr _ _) -> return ([], [goc]) _ -> na "rule_LiftVars" + let gensOrConds_dontCare = [ case goc of + Condition c -> Condition (make opNot c) + _ -> goc + | goc <- gensOrConds + ] + let patRefs = [ Reference patName Nothing | Generator (GenDomainHasRepr patName _domain) <- generators ] let indexDomains = [domain | Generator (GenDomainHasRepr _patName domain) <- generators ] @@ -217,7 +220,7 @@ rule_LiftVars = "bubble-up-LiftVars" `namedRule` theRule where -- traceM $ show $ "declsLifted" <+> vcat (map pretty declsLifted) let consLifted = - [ make opAnd $ Comprehension c generators + [ make opAnd $ Comprehension c gensOrConds | c <- transformBi upd cons ] @@ -240,6 +243,8 @@ rule_LiftVars = "bubble-up-LiftVars" `namedRule` theRule where , or [ pr name `isPrefixOf` pr declName && pr declName /= pr name | declName <- declsLiftedNames ] ] + let dontCareCons = make opAnd $ fromList [ make opDontCare (Reference r Nothing) | r <- declsLiftedNames ] + -- traceM $ show $ "unrefinedInBody" <+> vcat (map pretty unrefinedInBody) -- traceM $ show $ "unrefinedInCons" <+> vcat (map pretty unrefinedInCons) @@ -247,7 +252,9 @@ rule_LiftVars = "bubble-up-LiftVars" `namedRule` theRule where return ( "Bubbling up auxiliary variables through a comprehension." - , return $ WithLocals (Comprehension (transform upd body) (transformBi upd gensOrConds)) + , return $ WithLocals (make opConcatenate $ fromList [ Comprehension (transform upd body) (transformBi upd gensOrConds) + , Comprehension dontCareCons (transformBi upd gensOrConds_dontCare) + ]) (AuxiliaryVars (declsLifted ++ [SuchThat consLifted])) ) theRule WithLocals{} = na "rule_LiftVars" From 18b2b151a4b80d09472cf07620196373c85be92b Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?=C3=96zg=C3=BCr=20Akg=C3=BCn?= Date: Sat, 14 Dec 2024 19:53:34 +0000 Subject: [PATCH 214/229] dontcare of unnameds --- src/Conjure/Rules/DontCare.hs | 23 ++++++++++++++++++++--- src/Conjure/UI/Model.hs | 1 + 2 files changed, 21 insertions(+), 3 deletions(-) diff --git a/src/Conjure/Rules/DontCare.hs b/src/Conjure/Rules/DontCare.hs index 4daf7ddebe..f7c5abc308 100644 --- a/src/Conjure/Rules/DontCare.hs +++ b/src/Conjure/Rules/DontCare.hs @@ -31,6 +31,20 @@ rule_Int = "dontCare-int" `namedRule` theRule where ) +rule_Unnamed :: Rule +rule_Unnamed = "dontCare-unnamed" `namedRule` theRule where + theRule p = do + x <- match opDontCare p + ty <- typeOf x + case ty of + TypeInt (TagUnnamed _) -> return () + _ -> na "rule_Unnamed" + return + ( "dontCare value for this unnamed integer is 1" + , return $ make opEq x 1 + ) + + rule_Tuple :: Rule rule_Tuple = "dontCare-tuple" `namedRule` theRule where theRule p = do @@ -71,12 +85,15 @@ rule_Matrix :: Rule rule_Matrix = "dontCare-matrix" `namedRule` theRule where theRule p = do x <- match opDontCare p - DomainMatrix index _ <- domainOf x + indices <- indexDomainsOf x return ( "dontCare handling for matrix" , do - (iPat, i) <- quantifiedVar - return [essence| forAll &iPat : &index . dontCare(&x[&i]) |] + triplets <- forM indices $ \ index -> do + (iPat, i) <- quantifiedVar + return (iPat, i, index) + let gens = [Generator (GenDomainNoRepr iPat index) | (iPat, _, index) <- triplets] + return $ make opAnd $ Comprehension (make opDontCare (make opMatrixIndexing x [i | (_, i, _) <- triplets])) gens ) rule_Permutation :: Rule diff --git a/src/Conjure/UI/Model.hs b/src/Conjure/UI/Model.hs index 94225a363a..a79059bfb0 100644 --- a/src/Conjure/UI/Model.hs +++ b/src/Conjure/UI/Model.hs @@ -1697,6 +1697,7 @@ otherRules = , [ DontCare.rule_Bool , DontCare.rule_Int + , DontCare.rule_Unnamed , DontCare.rule_Tuple , DontCare.rule_Record , DontCare.rule_Variant From dac18716658265f7d2d153437182b847f16032ac Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?=C3=96zg=C3=BCr=20Akg=C3=BCn?= Date: Sat, 14 Dec 2024 20:11:56 +0000 Subject: [PATCH 215/229] oops --- src/Conjure/Rules/DontCare.hs | 1 + 1 file changed, 1 insertion(+) diff --git a/src/Conjure/Rules/DontCare.hs b/src/Conjure/Rules/DontCare.hs index f7c5abc308..6f8e4ba85f 100644 --- a/src/Conjure/Rules/DontCare.hs +++ b/src/Conjure/Rules/DontCare.hs @@ -86,6 +86,7 @@ rule_Matrix = "dontCare-matrix" `namedRule` theRule where theRule p = do x <- match opDontCare p indices <- indexDomainsOf x + when (null indices) $ na "rule_Matrix" return ( "dontCare handling for matrix" , do From 3e4c586a10a6339e95b18b9a1596372dd9352e25 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?=C3=96zg=C3=BCr=20Akg=C3=BCn?= Date: Fri, 17 Jan 2025 11:12:40 +0000 Subject: [PATCH 216/229] change parse_print tests --- src/test/Conjure/ParsePrint.hs | 40 +- .../730~1439082038_16/model.expected.json | 1321 ----------------- .../730~1439082038_16/typecheck.expected | 14 - .../autogen/731~final/model.expected.json | 76 - .../autogen/731~final/typecheck.expected | 14 - .../768~1439583525_36/model.expected.json | 412 ----- .../768~1439583525_36/typecheck.expected | 5 - .../autogen/769~final/model.expected.json | 67 - .../autogen/769~final/typecheck.expected | 5 - 9 files changed, 21 insertions(+), 1933 deletions(-) delete mode 100644 tests/parse_print/autogen/730~1439082038_16/model.expected.json delete mode 100644 tests/parse_print/autogen/730~1439082038_16/typecheck.expected delete mode 100644 tests/parse_print/autogen/731~final/model.expected.json delete mode 100644 tests/parse_print/autogen/731~final/typecheck.expected delete mode 100644 tests/parse_print/autogen/768~1439583525_36/model.expected.json delete mode 100644 tests/parse_print/autogen/768~1439583525_36/typecheck.expected delete mode 100644 tests/parse_print/autogen/769~final/model.expected.json delete mode 100644 tests/parse_print/autogen/769~final/typecheck.expected diff --git a/src/test/Conjure/ParsePrint.hs b/src/test/Conjure/ParsePrint.hs index d46b69b3b7..a889261742 100644 --- a/src/test/Conjure/ParsePrint.hs +++ b/src/test/Conjure/ParsePrint.hs @@ -130,27 +130,29 @@ testSingleDir TestDirFiles{..} = testCaseSteps (map (\ch -> if ch == '/' then '. step "Checking Generated Representation" modelG <- fixWindowsPaths <$> readIfExists (tBaseDir "model.json") - modelE <- readIfExists (tBaseDir "model.expected.json") - let diffs = do - jGiven <- stringToJson modelG - jReference <- stringToJson modelE - let Patch ds = diff jGiven jReference - return ds - case diffs of - Nothing -> assertFailure $ "JSON parser error in" ++ modelE - Just [] -> return () - Just ops -> assertFailure $ renderNormal $ vcat ["Difference in json:" <++> vcat (map (stringToDoc . show) ops)] + unless (null modelG) $ do + modelE <- readIfExists (tBaseDir "model.expected.json") + let diffs = do + jGiven <- stringToJson modelG + jReference <- stringToJson modelE + let Patch ds = diff jGiven jReference + return ds + case diffs of + Nothing -> assertFailure $ "JSON parser error in" ++ modelE + Just [] -> return () + Just ops -> assertFailure $ renderNormal $ vcat ["Difference in json:" <++> vcat (map (stringToDoc . show) ops)] step "Checking Types" - typecheckE <- fixWindowsPaths <$> readIfExists (tBaseDir "typecheck") - typecheckG <- readIfExists (tBaseDir "typecheck.expected") - unless (typecheckE == typecheckG) $ - assertFailure $ - renderNormal $ - vcat - [ "unexpected typeError:" <++> pretty typecheckG - , "was expecting: " <++> pretty typecheckE - ] + typecheckG <- fixWindowsPaths <$> readIfExists (tBaseDir "typecheck") + unless (null typecheckG) $ do + typecheckE <- readIfExists (tBaseDir "typecheck.expected") + unless (typecheckE == typecheckG) $ + assertFailure $ + renderNormal $ + vcat + [ "unexpected typeError:" <++> pretty typecheckG + , "was expecting: " <++> pretty typecheckE + ] stringToJson :: String -> Maybe JSON.Value stringToJson "" = Just JSON.emptyObject diff --git a/tests/parse_print/autogen/730~1439082038_16/model.expected.json b/tests/parse_print/autogen/730~1439082038_16/model.expected.json deleted file mode 100644 index 2648972b55..0000000000 --- a/tests/parse_print/autogen/730~1439082038_16/model.expected.json +++ /dev/null @@ -1,1321 +0,0 @@ -{"mInfo": - {"finds": [], "givens": [], "enumGivens": [], "enumLettings": [], "lettings": [], "unnameds": [], - "strategyQ": {"Auto": {"Interactive": []}}, "strategyA": {"Auto": {"Interactive": []}}, "trailCompact": [], - "nameGenState": [], "nbExtraGivens": 0, "representations": [], "representationsTree": [], "originalDomains": [], - "trailGeneralised": [], "trailVerbose": [], "trailRewrites": []}, - "mLanguage": {"language": {"Name": "Essence"}, "version": [1, 3]}, - "mStatements": - [{"Declaration": - {"FindOrGiven": - ["Find", {"Name": "var1"}, - {"DomainInt": - [{"TagInt": []}, - [{"RangeSingle": {"Constant": {"ConstantInt": [{"TagInt": []}, 0]}}}, - {"RangeSingle": {"Constant": {"ConstantInt": [{"TagInt": []}, 0]}}}]]}]}}, - {"SuchThat": - [{"Op": - {"MkOpEq": - [{"AbstractLiteral": - {"AbsLitFunction": - [[{"Typed": - [{"Constant": {"ConstantAbstract": {"AbsLitSet": []}}}, - {"TypeSet": - {"TypeMatrix": - [{"TypeInt": {"TagInt": []}}, - {"TypePartition": {"TypeInt": {"TagInt": []}}}]}}]}, - {"AbstractLiteral": - {"AbsLitMatrix": - [{"DomainInt": - [{"TagInt": []}, - [{"RangeSingle": - {"Constant": {"ConstantInt": [{"TagInt": []}, 7]}}}, - {"RangeSingle": - {"Constant": {"ConstantInt": [{"TagInt": []}, 12]}}}, - {"RangeSingle": - {"Constant": {"ConstantInt": [{"TagInt": []}, 9]}}}, - {"RangeBounded": - [{"Constant": {"ConstantInt": [{"TagInt": []}, 2]}}, - {"Constant": {"ConstantInt": [{"TagInt": []}, 2]}}]}]]}, - [{"AbstractLiteral": - {"AbsLitMSet": - [{"Constant": - {"ConstantAbstract": - {"AbsLitMSet": [{"ConstantBool": true}]}}}, - {"Typed": - [{"Constant": {"ConstantAbstract": {"AbsLitMSet": []}}}, - {"TypeMSet": {"TypeBool": []}}]}]}}, - {"Typed": - [{"Constant": {"ConstantAbstract": {"AbsLitMSet": []}}}, - {"TypeMSet": {"TypeMSet": {"TypeBool": []}}}]}, - {"Typed": - [{"Constant": {"ConstantAbstract": {"AbsLitMSet": []}}}, - {"TypeMSet": {"TypeMSet": {"TypeBool": []}}}]}, - {"Constant": - {"ConstantAbstract": - {"AbsLitMSet": - [{"ConstantAbstract": - {"AbsLitMSet": - [{"ConstantBool": false}, - {"ConstantBool": false}]}}, - {"ConstantAbstract": - {"AbsLitMSet": - [{"ConstantBool": false}, - {"ConstantBool": true}, - {"ConstantBool": true}]}}]}}}]]}}], - [{"AbstractLiteral": - {"AbsLitSet": - [{"Constant": - {"ConstantAbstract": - {"AbsLitMatrix": - [{"DomainInt": - [{"TagInt": []}, - [{"RangeBounded": - [{"ConstantInt": [{"TagInt": []}, 1]}, - {"ConstantInt": [{"TagInt": []}, 1]}]}]]}, - [{"ConstantAbstract": - {"AbsLitPartition": - [[{"ConstantInt": [{"TagInt": []}, 4]}, - {"ConstantInt": [{"TagInt": []}, 4]}, - {"ConstantInt": [{"TagInt": []}, 4]}, - {"ConstantInt": [{"TagInt": []}, 4]}, - {"ConstantInt": [{"TagInt": []}, 1]}], - [{"ConstantInt": [{"TagInt": []}, 4]}, - {"ConstantInt": - [{"TagInt": []}, 5]}]]}}]]}}}, - {"AbstractLiteral": - {"AbsLitMatrix": - [{"DomainInt": - [{"TagInt": []}, - [{"RangeSingle": - {"Constant": - {"ConstantInt": [{"TagInt": []}, 3]}}}, - {"RangeBounded": - [{"Constant": - {"ConstantInt": [{"TagInt": []}, 2]}}, - {"Constant": - {"ConstantInt": [{"TagInt": []}, 2]}}]}]]}, - [{"Constant": - {"ConstantAbstract": - {"AbsLitPartition": - [[{"ConstantInt": [{"TagInt": []}, 5]}], - [{"ConstantInt": [{"TagInt": []}, 2]}], - [{"ConstantInt": [{"TagInt": []}, 2]}, - {"ConstantInt": [{"TagInt": []}, 1]}, - {"ConstantInt": [{"TagInt": []}, 3]}, - {"ConstantInt": [{"TagInt": []}, 5]}], - [{"ConstantInt": [{"TagInt": []}, 4]}]]}}}, - {"Typed": - [{"Constant": - {"ConstantAbstract": {"AbsLitPartition": []}}}, - {"TypePartition": {"TypeInt": {"TagInt": []}}}]}]]}}, - {"Constant": - {"ConstantAbstract": - {"AbsLitMatrix": - [{"DomainInt": - [{"TagInt": []}, - [{"RangeBounded": - [{"ConstantInt": [{"TagInt": []}, 1]}, - {"ConstantInt": [{"TagInt": []}, 1]}]}]]}, - [{"ConstantAbstract": - {"AbsLitPartition": - [[{"ConstantInt": [{"TagInt": []}, 3]}, - {"ConstantInt": [{"TagInt": []}, 1]}, - {"ConstantInt": [{"TagInt": []}, 5]}, - {"ConstantInt": [{"TagInt": []}, 4]}], - [{"ConstantInt": [{"TagInt": []}, 3]}, - {"ConstantInt": [{"TagInt": []}, 1]}, - {"ConstantInt": [{"TagInt": []}, 4]}, - {"ConstantInt": [{"TagInt": []}, 3]}, - {"ConstantInt": [{"TagInt": []}, 5]}], - [{"ConstantInt": [{"TagInt": []}, 5]}, - {"ConstantInt": [{"TagInt": []}, 1]}, - {"ConstantInt": [{"TagInt": []}, 1]}, - {"ConstantInt": [{"TagInt": []}, 5]}, - {"ConstantInt": [{"TagInt": []}, 0]}], - [{"ConstantInt": [{"TagInt": []}, 2]}, - {"ConstantInt": [{"TagInt": []}, 5]}, - {"ConstantInt": [{"TagInt": []}, 5]}, - {"ConstantInt": - [{"TagInt": []}, 3]}]]}}]]}}}]}}, - {"AbstractLiteral": - {"AbsLitMatrix": - [{"DomainInt": - [{"TagInt": []}, - [{"RangeBounded": - [{"Constant": {"ConstantInt": [{"TagInt": []}, 3]}}, - {"Constant": {"ConstantInt": [{"TagInt": []}, 5]}}]}, - {"RangeBounded": - [{"Constant": {"ConstantInt": [{"TagInt": []}, 13]}}, - {"Constant": {"ConstantInt": [{"TagInt": []}, 14]}}]}]]}, - [{"Typed": - [{"Constant": {"ConstantAbstract": {"AbsLitMSet": []}}}, - {"TypeMSet": {"TypeMSet": {"TypeBool": []}}}]}, - {"Typed": - [{"Constant": {"ConstantAbstract": {"AbsLitMSet": []}}}, - {"TypeMSet": {"TypeMSet": {"TypeBool": []}}}]}, - {"Constant": - {"ConstantAbstract": - {"AbsLitMSet": - [{"ConstantAbstract": - {"AbsLitMSet": - [{"ConstantBool": false}, - {"ConstantBool": true}, - {"ConstantBool": false}]}}, - {"ConstantAbstract": - {"AbsLitMSet": [{"ConstantBool": false}]}}]}}}, - {"Constant": - {"ConstantAbstract": - {"AbsLitMSet": - [{"ConstantAbstract": - {"AbsLitMSet": - [{"ConstantBool": true}, - {"ConstantBool": true}, - {"ConstantBool": false}]}}, - {"ConstantAbstract": - {"AbsLitMSet": - [{"ConstantBool": false}, - {"ConstantBool": true}]}}]}}}, - {"Typed": - [{"Constant": {"ConstantAbstract": {"AbsLitMSet": []}}}, - {"TypeMSet": {"TypeMSet": {"TypeBool": []}}}]}]]}}], - [{"Constant": - {"ConstantAbstract": - {"AbsLitSet": - [{"ConstantAbstract": - {"AbsLitMatrix": - [{"DomainInt": - [{"TagInt": []}, - [{"RangeSingle": - {"ConstantInt": [{"TagInt": []}, 0]}}, - {"RangeBounded": - [{"ConstantInt": [{"TagInt": []}, 9]}, - {"ConstantInt": [{"TagInt": []}, 10]}]}, - {"RangeBounded": - [{"ConstantInt": [{"TagInt": []}, 6]}, - {"ConstantInt": [{"TagInt": []}, 6]}]}]]}, - [{"ConstantAbstract": - {"AbsLitPartition": - [[{"ConstantInt": [{"TagInt": []}, 2]}, - {"ConstantInt": [{"TagInt": []}, 4]}, - {"ConstantInt": [{"TagInt": []}, 1]}, - {"ConstantInt": [{"TagInt": []}, 3]}, - {"ConstantInt": [{"TagInt": []}, 3]}], - [{"ConstantInt": [{"TagInt": []}, 1]}, - {"ConstantInt": [{"TagInt": []}, 4]}, - {"ConstantInt": [{"TagInt": []}, 1]}, - {"ConstantInt": [{"TagInt": []}, 2]}, - {"ConstantInt": [{"TagInt": []}, 3]}], - [{"ConstantInt": [{"TagInt": []}, 2]}, - {"ConstantInt": [{"TagInt": []}, 2]}, - {"ConstantInt": [{"TagInt": []}, 5]}, - {"ConstantInt": [{"TagInt": []}, 5]}, - {"ConstantInt": [{"TagInt": []}, 3]}]]}}, - {"ConstantAbstract": - {"AbsLitPartition": - [[{"ConstantInt": [{"TagInt": []}, 2]}, - {"ConstantInt": [{"TagInt": []}, 1]}, - {"ConstantInt": [{"TagInt": []}, 0]}], - [{"ConstantInt": [{"TagInt": []}, 0]}, - {"ConstantInt": [{"TagInt": []}, 2]}, - {"ConstantInt": [{"TagInt": []}, 5]}, - {"ConstantInt": [{"TagInt": []}, 5]}], - [{"ConstantInt": [{"TagInt": []}, 5]}, - {"ConstantInt": [{"TagInt": []}, 5]}, - {"ConstantInt": [{"TagInt": []}, 2]}, - {"ConstantInt": [{"TagInt": []}, 2]}], - [{"ConstantInt": [{"TagInt": []}, 2]}, - {"ConstantInt": [{"TagInt": []}, 1]}], - [{"ConstantInt": [{"TagInt": []}, 1]}, - {"ConstantInt": [{"TagInt": []}, 0]}, - {"ConstantInt": [{"TagInt": []}, 2]}, - {"ConstantInt": [{"TagInt": []}, 4]}]]}}, - {"ConstantAbstract": - {"AbsLitPartition": - [[{"ConstantInt": [{"TagInt": []}, 3]}, - {"ConstantInt": [{"TagInt": []}, 4]}, - {"ConstantInt": [{"TagInt": []}, 5]}, - {"ConstantInt": [{"TagInt": []}, 2]}, - {"ConstantInt": [{"TagInt": []}, 1]}], - [{"ConstantInt": [{"TagInt": []}, 2]}], - [{"ConstantInt": [{"TagInt": []}, 4]}, - {"ConstantInt": [{"TagInt": []}, 1]}], - [{"ConstantInt": [{"TagInt": []}, 3]}, - {"ConstantInt": [{"TagInt": []}, 4]}], - [{"ConstantInt": [{"TagInt": []}, 2]}]]}}, - {"ConstantAbstract": - {"AbsLitPartition": - [[{"ConstantInt": [{"TagInt": []}, 3]}, - {"ConstantInt": [{"TagInt": []}, 5]}, - {"ConstantInt": [{"TagInt": []}, 5]}], - [{"ConstantInt": [{"TagInt": []}, 0]}, - {"ConstantInt": [{"TagInt": []}, 5]}, - {"ConstantInt": [{"TagInt": []}, 5]}, - {"ConstantInt": [{"TagInt": []}, 5]}, - {"ConstantInt": [{"TagInt": []}, 4]}], - [{"ConstantInt": [{"TagInt": []}, 2]}]]}}]]}}, - {"ConstantAbstract": - {"AbsLitMatrix": - [{"DomainInt": - [{"TagInt": []}, - [{"RangeBounded": - [{"ConstantInt": [{"TagInt": []}, 6]}, - {"ConstantInt": [{"TagInt": []}, 7]}]}, - {"RangeBounded": - [{"ConstantInt": [{"TagInt": []}, 10]}, - {"ConstantInt": [{"TagInt": []}, 11]}]}]]}, - [{"ConstantAbstract": - {"AbsLitPartition": - [[{"ConstantInt": [{"TagInt": []}, 5]}, - {"ConstantInt": [{"TagInt": []}, 1]}], - [{"ConstantInt": [{"TagInt": []}, 2]}, - {"ConstantInt": [{"TagInt": []}, 1]}]]}}, - {"ConstantAbstract": - {"AbsLitPartition": - [[{"ConstantInt": [{"TagInt": []}, 2]}]]}}, - {"ConstantAbstract": - {"AbsLitPartition": - [[{"ConstantInt": [{"TagInt": []}, 0]}, - {"ConstantInt": [{"TagInt": []}, 4]}, - {"ConstantInt": [{"TagInt": []}, 1]}, - {"ConstantInt": [{"TagInt": []}, 0]}, - {"ConstantInt": [{"TagInt": []}, 2]}], - [{"ConstantInt": [{"TagInt": []}, 2]}, - {"ConstantInt": [{"TagInt": []}, 2]}, - {"ConstantInt": [{"TagInt": []}, 1]}, - {"ConstantInt": [{"TagInt": []}, 3]}, - {"ConstantInt": [{"TagInt": []}, 3]}]]}}, - {"ConstantAbstract": - {"AbsLitPartition": - [[{"ConstantInt": [{"TagInt": []}, 2]}, - {"ConstantInt": [{"TagInt": []}, 4]}, - {"ConstantInt": [{"TagInt": []}, 4]}, - {"ConstantInt": [{"TagInt": []}, 4]}, - {"ConstantInt": [{"TagInt": []}, 5]}]]}}]]}}, - {"ConstantAbstract": - {"AbsLitMatrix": - [{"DomainInt": - [{"TagInt": []}, - [{"RangeSingle": - {"ConstantInt": [{"TagInt": []}, 6]}}, - {"RangeBounded": - [{"ConstantInt": [{"TagInt": []}, 4]}, - {"ConstantInt": [{"TagInt": []}, 4]}]}]]}, - [{"ConstantAbstract": - {"AbsLitPartition": - [[{"ConstantInt": [{"TagInt": []}, 4]}, - {"ConstantInt": [{"TagInt": []}, 3]}, - {"ConstantInt": [{"TagInt": []}, 4]}, - {"ConstantInt": [{"TagInt": []}, 4]}], - [{"ConstantInt": [{"TagInt": []}, 4]}, - {"ConstantInt": [{"TagInt": []}, 4]}, - {"ConstantInt": [{"TagInt": []}, 4]}, - {"ConstantInt": [{"TagInt": []}, 5]}], - [{"ConstantInt": [{"TagInt": []}, 3]}, - {"ConstantInt": [{"TagInt": []}, 0]}], - [{"ConstantInt": [{"TagInt": []}, 3]}, - {"ConstantInt": [{"TagInt": []}, 1]}, - {"ConstantInt": [{"TagInt": []}, 2]}, - {"ConstantInt": [{"TagInt": []}, 2]}, - {"ConstantInt": [{"TagInt": []}, 0]}]]}}, - {"ConstantAbstract": - {"AbsLitPartition": - [[{"ConstantInt": [{"TagInt": []}, 2]}, - {"ConstantInt": [{"TagInt": []}, 2]}], - [{"ConstantInt": - [{"TagInt": []}, 0]}]]}}]]}}]}}}, - {"Typed": - [{"Constant": - {"ConstantAbstract": - {"AbsLitMatrix": - [{"DomainInt": - [{"TagInt": []}, - [{"RangeBounded": - [{"ConstantInt": [{"TagInt": []}, 1]}, - {"ConstantInt": [{"TagInt": []}, 0]}]}]]}, - []]}}}, - {"TypeMatrix": - [{"TypeInt": {"TagInt": []}}, - {"TypeMSet": {"TypeMSet": {"TypeBool": []}}}]}]}], - [{"AbstractLiteral": - {"AbsLitSet": - [{"AbstractLiteral": - {"AbsLitMatrix": - [{"DomainInt": - [{"TagInt": []}, - [{"RangeSingle": - {"Constant": - {"ConstantInt": [{"TagInt": []}, 5]}}}, - {"RangeSingle": - {"Constant": - {"ConstantInt": [{"TagInt": []}, 8]}}}, - {"RangeBounded": - [{"Constant": - {"ConstantInt": [{"TagInt": []}, 6]}}, - {"Constant": - {"ConstantInt": [{"TagInt": []}, 7]}}]}]]}, - [{"Constant": - {"ConstantAbstract": - {"AbsLitPartition": - [[{"ConstantInt": [{"TagInt": []}, 4]}, - {"ConstantInt": [{"TagInt": []}, 1]}, - {"ConstantInt": [{"TagInt": []}, 5]}], - [{"ConstantInt": [{"TagInt": []}, 4]}, - {"ConstantInt": [{"TagInt": []}, 2]}, - {"ConstantInt": [{"TagInt": []}, 4]}, - {"ConstantInt": [{"TagInt": []}, 2]}, - {"ConstantInt": [{"TagInt": []}, 5]}], - [{"ConstantInt": [{"TagInt": []}, 0]}], - [{"ConstantInt": [{"TagInt": []}, 2]}, - {"ConstantInt": [{"TagInt": []}, 3]}, - {"ConstantInt": [{"TagInt": []}, 2]}, - {"ConstantInt": [{"TagInt": []}, 0]}], - [{"ConstantInt": [{"TagInt": []}, 3]}, - {"ConstantInt": [{"TagInt": []}, 5]}, - {"ConstantInt": [{"TagInt": []}, 5]}]]}}}, - {"Constant": - {"ConstantAbstract": - {"AbsLitPartition": - [[{"ConstantInt": [{"TagInt": []}, 0]}, - {"ConstantInt": [{"TagInt": []}, 0]}], - [{"ConstantInt": [{"TagInt": []}, 0]}, - {"ConstantInt": [{"TagInt": []}, 1]}]]}}}, - {"Constant": - {"ConstantAbstract": - {"AbsLitPartition": - [[{"ConstantInt": [{"TagInt": []}, 0]}, - {"ConstantInt": [{"TagInt": []}, 4]}, - {"ConstantInt": [{"TagInt": []}, 1]}], - [{"ConstantInt": [{"TagInt": []}, 0]}, - {"ConstantInt": [{"TagInt": []}, 3]}, - {"ConstantInt": [{"TagInt": []}, 5]}], - [{"ConstantInt": [{"TagInt": []}, 2]}], - [{"ConstantInt": [{"TagInt": []}, 0]}], - [{"ConstantInt": [{"TagInt": []}, 4]}, - {"ConstantInt": [{"TagInt": []}, 2]}, - {"ConstantInt": [{"TagInt": []}, 1]}, - {"ConstantInt": [{"TagInt": []}, 2]}, - {"ConstantInt": [{"TagInt": []}, 2]}]]}}}, - {"Typed": - [{"Constant": - {"ConstantAbstract": {"AbsLitPartition": []}}}, - {"TypePartition": {"TypeInt": {"TagInt": []}}}]}]]}}, - {"AbstractLiteral": - {"AbsLitMatrix": - [{"DomainInt": - [{"TagInt": []}, - [{"RangeBounded": - [{"Constant": - {"ConstantInt": [{"TagInt": []}, 1]}}, - {"Constant": - {"ConstantInt": [{"TagInt": []}, 2]}}]}]]}, - [{"Typed": - [{"Constant": - {"ConstantAbstract": {"AbsLitPartition": []}}}, - {"TypePartition": {"TypeInt": {"TagInt": []}}}]}, - {"Constant": - {"ConstantAbstract": - {"AbsLitPartition": - [[{"ConstantInt": [{"TagInt": []}, 1]}, - {"ConstantInt": [{"TagInt": []}, 3]}, - {"ConstantInt": [{"TagInt": []}, 3]}, - {"ConstantInt": [{"TagInt": []}, 2]}], - [{"ConstantInt": [{"TagInt": []}, 0]}, - {"ConstantInt": [{"TagInt": []}, 0]}, - {"ConstantInt": [{"TagInt": []}, 4]}], - [{"ConstantInt": - [{"TagInt": []}, 1]}]]}}}]]}}]}}, - {"Typed": - [{"Constant": - {"ConstantAbstract": - {"AbsLitMatrix": - [{"DomainInt": - [{"TagInt": []}, - [{"RangeBounded": - [{"ConstantInt": [{"TagInt": []}, 1]}, - {"ConstantInt": [{"TagInt": []}, 0]}]}]]}, - []]}}}, - {"TypeMatrix": - [{"TypeInt": {"TagInt": []}}, - {"TypeMSet": {"TypeMSet": {"TypeBool": []}}}]}]}]]}}, - {"AbstractLiteral": - {"AbsLitFunction": - [[{"AbstractLiteral": - {"AbsLitSet": - [{"Typed": - [{"Constant": - {"ConstantAbstract": - {"AbsLitMatrix": - [{"DomainInt": - [{"TagInt": []}, - [{"RangeBounded": - [{"ConstantInt": [{"TagInt": []}, 1]}, - {"ConstantInt": - [{"TagInt": []}, 0]}]}]]}, - []]}}}, - {"TypeMatrix": - [{"TypeInt": {"TagInt": []}}, - {"TypePartition": {"TypeInt": {"TagInt": []}}}]}]}, - {"AbstractLiteral": - {"AbsLitMatrix": - [{"DomainInt": - [{"TagInt": []}, - [{"RangeSingle": - {"Constant": - {"ConstantInt": [{"TagInt": []}, 9]}}}, - {"RangeSingle": - {"Constant": - {"ConstantInt": [{"TagInt": []}, 6]}}}, - {"RangeBounded": - [{"Constant": - {"ConstantInt": [{"TagInt": []}, 1]}}, - {"Constant": - {"ConstantInt": [{"TagInt": []}, 2]}}]}]]}, - [{"Constant": - {"ConstantAbstract": - {"AbsLitPartition": - [[{"ConstantInt": [{"TagInt": []}, 0]}, - {"ConstantInt": [{"TagInt": []}, 1]}], - [{"ConstantInt": [{"TagInt": []}, 3]}, - {"ConstantInt": [{"TagInt": []}, 0]}, - {"ConstantInt": [{"TagInt": []}, 0]}, - {"ConstantInt": [{"TagInt": []}, 5]}, - {"ConstantInt": [{"TagInt": []}, 3]}], - [{"ConstantInt": [{"TagInt": []}, 0]}, - {"ConstantInt": [{"TagInt": []}, 2]}], - [{"ConstantInt": [{"TagInt": []}, 5]}, - {"ConstantInt": [{"TagInt": []}, 5]}, - {"ConstantInt": [{"TagInt": []}, 2]}, - {"ConstantInt": [{"TagInt": []}, 3]}]]}}}, - {"Constant": - {"ConstantAbstract": - {"AbsLitPartition": - [[{"ConstantInt": [{"TagInt": []}, 2]}]]}}}, - {"Constant": - {"ConstantAbstract": - {"AbsLitPartition": - [[{"ConstantInt": [{"TagInt": []}, 1]}, - {"ConstantInt": [{"TagInt": []}, 3]}, - {"ConstantInt": [{"TagInt": []}, 5]}], - [{"ConstantInt": [{"TagInt": []}, 3]}], - [{"ConstantInt": [{"TagInt": []}, 4]}, - {"ConstantInt": [{"TagInt": []}, 3]}, - {"ConstantInt": [{"TagInt": []}, 1]}, - {"ConstantInt": [{"TagInt": []}, 2]}]]}}}, - {"Typed": - [{"Constant": - {"ConstantAbstract": {"AbsLitPartition": []}}}, - {"TypePartition": {"TypeInt": {"TagInt": []}}}]}]]}}]}}, - {"AbstractLiteral": - {"AbsLitMatrix": - [{"DomainInt": - [{"TagInt": []}, - [{"RangeBounded": - [{"Constant": {"ConstantInt": [{"TagInt": []}, 3]}}, - {"Constant": {"ConstantInt": [{"TagInt": []}, 4]}}]}]]}, - [{"AbstractLiteral": - {"AbsLitMSet": - [{"Typed": - [{"Constant": {"ConstantAbstract": {"AbsLitMSet": []}}}, - {"TypeMSet": {"TypeBool": []}}]}, - {"Constant": - {"ConstantAbstract": - {"AbsLitMSet": - [{"ConstantBool": false}, - {"ConstantBool": true}, - {"ConstantBool": true}]}}}, - {"Constant": - {"ConstantAbstract": - {"AbsLitMSet": - [{"ConstantBool": true}, - {"ConstantBool": false}, - {"ConstantBool": false}]}}}]}}, - {"AbstractLiteral": - {"AbsLitMSet": - [{"Typed": - [{"Constant": {"ConstantAbstract": {"AbsLitMSet": []}}}, - {"TypeMSet": {"TypeBool": []}}]}, - {"Constant": - {"ConstantAbstract": - {"AbsLitMSet": - [{"ConstantBool": false}, - {"ConstantBool": false}]}}}]}}]]}}], - [{"Constant": - {"ConstantAbstract": - {"AbsLitSet": - [{"ConstantAbstract": - {"AbsLitMatrix": - [{"DomainInt": - [{"TagInt": []}, - [{"RangeSingle": - {"ConstantInt": [{"TagInt": []}, 0]}}, - {"RangeBounded": - [{"ConstantInt": [{"TagInt": []}, 10]}, - {"ConstantInt": [{"TagInt": []}, 13]}]}]]}, - [{"ConstantAbstract": - {"AbsLitPartition": - [[{"ConstantInt": [{"TagInt": []}, 3]}, - {"ConstantInt": [{"TagInt": []}, 1]}], - [{"ConstantInt": [{"TagInt": []}, 1]}, - {"ConstantInt": [{"TagInt": []}, 3]}, - {"ConstantInt": [{"TagInt": []}, 3]}, - {"ConstantInt": [{"TagInt": []}, 2]}]]}}, - {"ConstantAbstract": - {"AbsLitPartition": - [[{"ConstantInt": [{"TagInt": []}, 1]}, - {"ConstantInt": [{"TagInt": []}, 1]}], - [{"ConstantInt": [{"TagInt": []}, 5]}]]}}, - {"ConstantAbstract": - {"AbsLitPartition": - [[{"ConstantInt": [{"TagInt": []}, 4]}, - {"ConstantInt": [{"TagInt": []}, 2]}, - {"ConstantInt": [{"TagInt": []}, 3]}, - {"ConstantInt": [{"TagInt": []}, 0]}], - [{"ConstantInt": [{"TagInt": []}, 5]}, - {"ConstantInt": [{"TagInt": []}, 0]}, - {"ConstantInt": [{"TagInt": []}, 0]}, - {"ConstantInt": [{"TagInt": []}, 4]}], - [{"ConstantInt": [{"TagInt": []}, 4]}, - {"ConstantInt": [{"TagInt": []}, 2]}, - {"ConstantInt": [{"TagInt": []}, 2]}, - {"ConstantInt": [{"TagInt": []}, 2]}], - [{"ConstantInt": [{"TagInt": []}, 5]}, - {"ConstantInt": [{"TagInt": []}, 0]}, - {"ConstantInt": [{"TagInt": []}, 1]}, - {"ConstantInt": [{"TagInt": []}, 4]}]]}}, - {"ConstantAbstract": - {"AbsLitPartition": - [[{"ConstantInt": [{"TagInt": []}, 1]}, - {"ConstantInt": [{"TagInt": []}, 2]}], - [{"ConstantInt": [{"TagInt": []}, 5]}, - {"ConstantInt": [{"TagInt": []}, 3]}], - [{"ConstantInt": [{"TagInt": []}, 3]}, - {"ConstantInt": [{"TagInt": []}, 3]}, - {"ConstantInt": [{"TagInt": []}, 1]}, - {"ConstantInt": [{"TagInt": []}, 1]}, - {"ConstantInt": [{"TagInt": []}, 1]}]]}}, - {"ConstantAbstract": - {"AbsLitPartition": - [[{"ConstantInt": [{"TagInt": []}, 2]}, - {"ConstantInt": [{"TagInt": []}, 3]}, - {"ConstantInt": [{"TagInt": []}, 3]}, - {"ConstantInt": [{"TagInt": []}, 5]}], - [{"ConstantInt": [{"TagInt": []}, 4]}, - {"ConstantInt": [{"TagInt": []}, 2]}, - {"ConstantInt": [{"TagInt": []}, 4]}, - {"ConstantInt": [{"TagInt": []}, 3]}, - {"ConstantInt": [{"TagInt": []}, 5]}], - [{"ConstantInt": [{"TagInt": []}, 5]}, - {"ConstantInt": [{"TagInt": []}, 0]}, - {"ConstantInt": [{"TagInt": []}, 1]}], - [{"ConstantInt": - [{"TagInt": []}, 0]}]]}}]]}}]}}}, - {"AbstractLiteral": - {"AbsLitMatrix": - [{"DomainInt": - [{"TagInt": []}, - [{"RangeBounded": - [{"Constant": {"ConstantInt": [{"TagInt": []}, 2]}}, - {"Constant": {"ConstantInt": [{"TagInt": []}, 3]}}]}, - {"RangeBounded": - [{"Constant": {"ConstantInt": [{"TagInt": []}, 8]}}, - {"Constant": {"ConstantInt": [{"TagInt": []}, 9]}}]}]]}, - [{"Typed": - [{"Constant": {"ConstantAbstract": {"AbsLitMSet": []}}}, - {"TypeMSet": {"TypeMSet": {"TypeBool": []}}}]}, - {"Constant": - {"ConstantAbstract": - {"AbsLitMSet": - [{"ConstantAbstract": - {"AbsLitMSet": [{"ConstantBool": false}]}}, - {"ConstantAbstract": - {"AbsLitMSet": [{"ConstantBool": false}]}}]}}}, - {"Constant": - {"ConstantAbstract": - {"AbsLitMSet": - [{"ConstantAbstract": - {"AbsLitMSet": [{"ConstantBool": false}]}}, - {"ConstantAbstract": - {"AbsLitMSet": - [{"ConstantBool": true}, - {"ConstantBool": false}, - {"ConstantBool": true}]}}, - {"ConstantAbstract": - {"AbsLitMSet": [{"ConstantBool": false}]}}]}}}, - {"Constant": - {"ConstantAbstract": - {"AbsLitMSet": - [{"ConstantAbstract": - {"AbsLitMSet": - [{"ConstantBool": true}, - {"ConstantBool": true}, - {"ConstantBool": false}]}}, - {"ConstantAbstract": - {"AbsLitMSet": [{"ConstantBool": true}]}}, - {"ConstantAbstract": - {"AbsLitMSet": - [{"ConstantBool": true}, - {"ConstantBool": false}]}}]}}}]]}}], - [{"Constant": - {"ConstantAbstract": - {"AbsLitSet": - [{"ConstantAbstract": - {"AbsLitMatrix": - [{"DomainInt": - [{"TagInt": []}, - [{"RangeBounded": - [{"ConstantInt": [{"TagInt": []}, 1]}, - {"ConstantInt": [{"TagInt": []}, 3]}]}]]}, - [{"ConstantAbstract": - {"AbsLitPartition": - [[{"ConstantInt": [{"TagInt": []}, 2]}, - {"ConstantInt": [{"TagInt": []}, 1]}], - [{"ConstantInt": [{"TagInt": []}, 2]}, - {"ConstantInt": [{"TagInt": []}, 2]}, - {"ConstantInt": [{"TagInt": []}, 4]}], - [{"ConstantInt": [{"TagInt": []}, 5]}, - {"ConstantInt": [{"TagInt": []}, 4]}, - {"ConstantInt": [{"TagInt": []}, 4]}, - {"ConstantInt": [{"TagInt": []}, 0]}, - {"ConstantInt": [{"TagInt": []}, 4]}], - [{"ConstantInt": [{"TagInt": []}, 3]}, - {"ConstantInt": [{"TagInt": []}, 0]}, - {"ConstantInt": [{"TagInt": []}, 2]}, - {"ConstantInt": [{"TagInt": []}, 5]}], - [{"ConstantInt": [{"TagInt": []}, 5]}, - {"ConstantInt": [{"TagInt": []}, 5]}]]}}, - {"ConstantAbstract": - {"AbsLitPartition": - [[{"ConstantInt": [{"TagInt": []}, 3]}, - {"ConstantInt": [{"TagInt": []}, 5]}, - {"ConstantInt": [{"TagInt": []}, 0]}, - {"ConstantInt": [{"TagInt": []}, 0]}], - [{"ConstantInt": [{"TagInt": []}, 2]}, - {"ConstantInt": [{"TagInt": []}, 0]}, - {"ConstantInt": [{"TagInt": []}, 0]}], - [{"ConstantInt": [{"TagInt": []}, 3]}, - {"ConstantInt": [{"TagInt": []}, 1]}, - {"ConstantInt": [{"TagInt": []}, 5]}, - {"ConstantInt": [{"TagInt": []}, 0]}], - [{"ConstantInt": [{"TagInt": []}, 5]}, - {"ConstantInt": [{"TagInt": []}, 2]}, - {"ConstantInt": [{"TagInt": []}, 0]}, - {"ConstantInt": [{"TagInt": []}, 0]}], - [{"ConstantInt": [{"TagInt": []}, 1]}, - {"ConstantInt": [{"TagInt": []}, 3]}]]}}, - {"ConstantAbstract": - {"AbsLitPartition": - [[{"ConstantInt": [{"TagInt": []}, 5]}, - {"ConstantInt": [{"TagInt": []}, 4]}, - {"ConstantInt": [{"TagInt": []}, 2]}, - {"ConstantInt": [{"TagInt": []}, 2]}, - {"ConstantInt": [{"TagInt": []}, 1]}], - [{"ConstantInt": [{"TagInt": []}, 5]}, - {"ConstantInt": [{"TagInt": []}, 1]}, - {"ConstantInt": [{"TagInt": []}, 5]}, - {"ConstantInt": - [{"TagInt": []}, 4]}]]}}]]}}]}}}, - {"AbstractLiteral": - {"AbsLitMatrix": - [{"DomainInt": - [{"TagInt": []}, - [{"RangeBounded": - [{"Constant": {"ConstantInt": [{"TagInt": []}, 2]}}, - {"Constant": {"ConstantInt": [{"TagInt": []}, 3]}}]}, - {"RangeSingle": - {"Constant": {"ConstantInt": [{"TagInt": []}, 15]}}}, - {"RangeSingle": - {"Constant": {"ConstantInt": [{"TagInt": []}, 11]}}}, - {"RangeBounded": - [{"Constant": {"ConstantInt": [{"TagInt": []}, 9]}}, - {"Constant": {"ConstantInt": [{"TagInt": []}, 9]}}]}]]}, - [{"AbstractLiteral": - {"AbsLitMSet": - [{"Typed": - [{"Constant": {"ConstantAbstract": {"AbsLitMSet": []}}}, - {"TypeMSet": {"TypeBool": []}}]}, - {"Constant": - {"ConstantAbstract": - {"AbsLitMSet": [{"ConstantBool": false}]}}}]}}, - {"Constant": - {"ConstantAbstract": - {"AbsLitMSet": - [{"ConstantAbstract": - {"AbsLitMSet": [{"ConstantBool": true}]}}, - {"ConstantAbstract": - {"AbsLitMSet": [{"ConstantBool": false}]}}]}}}, - {"AbstractLiteral": - {"AbsLitMSet": - [{"Typed": - [{"Constant": {"ConstantAbstract": {"AbsLitMSet": []}}}, - {"TypeMSet": {"TypeBool": []}}]}, - {"Constant": - {"ConstantAbstract": - {"AbsLitMSet": - [{"ConstantBool": true}, - {"ConstantBool": false}, - {"ConstantBool": true}]}}}]}}, - {"Constant": - {"ConstantAbstract": - {"AbsLitMSet": - [{"ConstantAbstract": - {"AbsLitMSet": [{"ConstantBool": true}]}}]}}}, - {"Constant": - {"ConstantAbstract": - {"AbsLitMSet": - [{"ConstantAbstract": - {"AbsLitMSet": [{"ConstantBool": true}]}}, - {"ConstantAbstract": - {"AbsLitMSet": [{"ConstantBool": false}]}}, - {"ConstantAbstract": - {"AbsLitMSet": - [{"ConstantBool": true}, - {"ConstantBool": true}]}}]}}}]]}}], - [{"Constant": - {"ConstantAbstract": - {"AbsLitSet": - [{"ConstantAbstract": - {"AbsLitMatrix": - [{"DomainInt": - [{"TagInt": []}, - [{"RangeBounded": - [{"ConstantInt": [{"TagInt": []}, 2]}, - {"ConstantInt": [{"TagInt": []}, 2]}]}]]}, - [{"ConstantAbstract": - {"AbsLitPartition": - [[{"ConstantInt": [{"TagInt": []}, 0]}], - [{"ConstantInt": [{"TagInt": []}, 3]}, - {"ConstantInt": [{"TagInt": []}, 2]}, - {"ConstantInt": [{"TagInt": []}, 2]}]]}}]]}}, - {"ConstantAbstract": - {"AbsLitMatrix": - [{"DomainInt": - [{"TagInt": []}, - [{"RangeSingle": - {"ConstantInt": [{"TagInt": []}, 3]}}, - {"RangeBounded": - [{"ConstantInt": [{"TagInt": []}, 1]}, - {"ConstantInt": [{"TagInt": []}, 1]}]}]]}, - [{"ConstantAbstract": - {"AbsLitPartition": - [[{"ConstantInt": [{"TagInt": []}, 4]}, - {"ConstantInt": [{"TagInt": []}, 2]}], - [{"ConstantInt": [{"TagInt": []}, 4]}, - {"ConstantInt": [{"TagInt": []}, 4]}, - {"ConstantInt": [{"TagInt": []}, 5]}], - [{"ConstantInt": [{"TagInt": []}, 2]}], - [{"ConstantInt": [{"TagInt": []}, 5]}, - {"ConstantInt": [{"TagInt": []}, 3]}, - {"ConstantInt": [{"TagInt": []}, 1]}], - [{"ConstantInt": [{"TagInt": []}, 0]}]]}}, - {"ConstantAbstract": - {"AbsLitPartition": - [[{"ConstantInt": [{"TagInt": []}, 1]}], - [{"ConstantInt": [{"TagInt": []}, 4]}]]}}]]}}, - {"ConstantAbstract": - {"AbsLitMatrix": - [{"DomainInt": - [{"TagInt": []}, - [{"RangeBounded": - [{"ConstantInt": [{"TagInt": []}, 0]}, - {"ConstantInt": [{"TagInt": []}, 2]}]}]]}, - [{"ConstantAbstract": - {"AbsLitPartition": - [[{"ConstantInt": [{"TagInt": []}, 5]}, - {"ConstantInt": [{"TagInt": []}, 1]}, - {"ConstantInt": [{"TagInt": []}, 2]}]]}}, - {"ConstantAbstract": - {"AbsLitPartition": - [[{"ConstantInt": [{"TagInt": []}, 4]}, - {"ConstantInt": [{"TagInt": []}, 5]}, - {"ConstantInt": [{"TagInt": []}, 0]}], - [{"ConstantInt": [{"TagInt": []}, 5]}], - [{"ConstantInt": [{"TagInt": []}, 1]}, - {"ConstantInt": [{"TagInt": []}, 1]}], - [{"ConstantInt": [{"TagInt": []}, 5]}]]}}, - {"ConstantAbstract": - {"AbsLitPartition": - [[{"ConstantInt": [{"TagInt": []}, 5]}, - {"ConstantInt": [{"TagInt": []}, 4]}, - {"ConstantInt": [{"TagInt": []}, 1]}, - {"ConstantInt": [{"TagInt": []}, 1]}], - [{"ConstantInt": [{"TagInt": []}, 0]}, - {"ConstantInt": [{"TagInt": []}, 2]}, - {"ConstantInt": [{"TagInt": []}, 0]}, - {"ConstantInt": [{"TagInt": []}, 3]}], - [{"ConstantInt": [{"TagInt": []}, 2]}, - {"ConstantInt": - [{"TagInt": []}, 3]}]]}}]]}}]}}}, - {"AbstractLiteral": - {"AbsLitMatrix": - [{"DomainInt": - [{"TagInt": []}, - [{"RangeSingle": - {"Constant": {"ConstantInt": [{"TagInt": []}, 8]}}}, - {"RangeSingle": - {"Constant": {"ConstantInt": [{"TagInt": []}, 6]}}}, - {"RangeBounded": - [{"Constant": {"ConstantInt": [{"TagInt": []}, 3]}}, - {"Constant": {"ConstantInt": [{"TagInt": []}, 4]}}]}]]}, - [{"Constant": - {"ConstantAbstract": - {"AbsLitMSet": - [{"ConstantAbstract": - {"AbsLitMSet": - [{"ConstantBool": false}, - {"ConstantBool": false}]}}]}}}, - {"Constant": - {"ConstantAbstract": - {"AbsLitMSet": - [{"ConstantAbstract": - {"AbsLitMSet": - [{"ConstantBool": true}, - {"ConstantBool": false}]}}, - {"ConstantAbstract": - {"AbsLitMSet": - [{"ConstantBool": false}, - {"ConstantBool": true}, - {"ConstantBool": true}]}}]}}}, - {"AbstractLiteral": - {"AbsLitMSet": - [{"Constant": - {"ConstantAbstract": - {"AbsLitMSet": - [{"ConstantBool": true}, - {"ConstantBool": false}]}}}, - {"Typed": - [{"Constant": {"ConstantAbstract": {"AbsLitMSet": []}}}, - {"TypeMSet": {"TypeBool": []}}]}, - {"Constant": - {"ConstantAbstract": - {"AbsLitMSet": - [{"ConstantBool": false}, - {"ConstantBool": false}, - {"ConstantBool": true}]}}}]}}, - {"Constant": - {"ConstantAbstract": - {"AbsLitMSet": - [{"ConstantAbstract": - {"AbsLitMSet": - [{"ConstantBool": false}, - {"ConstantBool": false}, - {"ConstantBool": true}]}}]}}}]]}}]]}}]}}, - {"Op": - {"MkOpApart": - [{"Constant": - {"ConstantAbstract": - {"AbsLitSet": - [{"ConstantAbstract": - {"AbsLitSet": - [{"ConstantAbstract": - {"AbsLitMSet": - [{"ConstantAbstract": - {"AbsLitSet": - [{"ConstantInt": [{"TagInt": []}, 1]}]}}, - {"ConstantAbstract": - {"AbsLitSet": - [{"ConstantInt": [{"TagInt": []}, 2]}, - {"ConstantInt": [{"TagInt": []}, 3]}]}}]}}]}}, - {"ConstantAbstract": - {"AbsLitSet": - [{"ConstantAbstract": - {"AbsLitMSet": - [{"ConstantAbstract": - {"AbsLitSet": - [{"ConstantInt": [{"TagInt": []}, 3]}]}}, - {"ConstantAbstract": - {"AbsLitSet": - [{"ConstantInt": [{"TagInt": []}, 1]}, - {"ConstantInt": [{"TagInt": []}, 0]}, - {"ConstantInt": [{"TagInt": []}, 0]}]}}]}}, - {"ConstantAbstract": - {"AbsLitMSet": - [{"ConstantAbstract": - {"AbsLitSet": - [{"ConstantInt": - [{"TagInt": []}, 2]}]}}]}}]}}]}}}, - {"AbstractLiteral": - {"AbsLitPartition": - [[{"Typed": - [{"Constant": {"ConstantAbstract": {"AbsLitSet": []}}}, - {"TypeSet": {"TypeMSet": {"TypeSet": {"TypeInt": {"TagInt": []}}}}}]}, - {"AbstractLiteral": - {"AbsLitSet": - [{"Constant": - {"ConstantAbstract": - {"AbsLitMSet": - [{"ConstantAbstract": - {"AbsLitSet": - [{"ConstantInt": [{"TagInt": []}, 4]}, - {"ConstantInt": [{"TagInt": []}, 2]}, - {"ConstantInt": [{"TagInt": []}, 1]}]}}, - {"ConstantAbstract": - {"AbsLitSet": - [{"ConstantInt": [{"TagInt": []}, 4]}]}}, - {"ConstantAbstract": - {"AbsLitSet": - [{"ConstantInt": [{"TagInt": []}, 5]}, - {"ConstantInt": [{"TagInt": []}, 1]}]}}]}}}, - {"Typed": - [{"Constant": {"ConstantAbstract": {"AbsLitMSet": []}}}, - {"TypeMSet": {"TypeSet": {"TypeInt": {"TagInt": []}}}}]}, - {"Constant": - {"ConstantAbstract": - {"AbsLitMSet": - [{"ConstantAbstract": - {"AbsLitSet": - [{"ConstantInt": [{"TagInt": []}, 4]}, - {"ConstantInt": [{"TagInt": []}, 4]}, - {"ConstantInt": [{"TagInt": []}, 3]}]}}, - {"ConstantAbstract": - {"AbsLitSet": - [{"ConstantInt": [{"TagInt": []}, 4]}, - {"ConstantInt": [{"TagInt": []}, 2]}, - {"ConstantInt": [{"TagInt": []}, 4]}]}}]}}}]}}, - {"AbstractLiteral": - {"AbsLitSet": - [{"AbstractLiteral": - {"AbsLitMSet": - [{"Typed": - [{"Constant": {"ConstantAbstract": {"AbsLitSet": []}}}, - {"TypeSet": {"TypeInt": {"TagInt": []}}}]}, - {"Constant": - {"ConstantAbstract": - {"AbsLitSet": - [{"ConstantInt": [{"TagInt": []}, 2]}]}}}, - {"Typed": - [{"Constant": {"ConstantAbstract": {"AbsLitSet": []}}}, - {"TypeSet": {"TypeInt": {"TagInt": []}}}]}]}}]}}, - {"AbstractLiteral": - {"AbsLitSet": - [{"Constant": - {"ConstantAbstract": - {"AbsLitMSet": - [{"ConstantAbstract": - {"AbsLitSet": - [{"ConstantInt": [{"TagInt": []}, 2]}, - {"ConstantInt": [{"TagInt": []}, 1]}]}}, - {"ConstantAbstract": - {"AbsLitSet": - [{"ConstantInt": [{"TagInt": []}, 3]}, - {"ConstantInt": [{"TagInt": []}, 4]}]}}, - {"ConstantAbstract": - {"AbsLitSet": - [{"ConstantInt": [{"TagInt": []}, 5]}, - {"ConstantInt": [{"TagInt": []}, 2]}, - {"ConstantInt": [{"TagInt": []}, 4]}]}}]}}}, - {"AbstractLiteral": - {"AbsLitMSet": - [{"Constant": - {"ConstantAbstract": - {"AbsLitSet": - [{"ConstantInt": [{"TagInt": []}, 2]}]}}}, - {"Constant": - {"ConstantAbstract": - {"AbsLitSet": - [{"ConstantInt": [{"TagInt": []}, 5]}, - {"ConstantInt": [{"TagInt": []}, 0]}, - {"ConstantInt": [{"TagInt": []}, 4]}]}}}, - {"Typed": - [{"Constant": {"ConstantAbstract": {"AbsLitSet": []}}}, - {"TypeSet": {"TypeInt": {"TagInt": []}}}]}]}}, - {"AbstractLiteral": - {"AbsLitMSet": - [{"Typed": - [{"Constant": {"ConstantAbstract": {"AbsLitSet": []}}}, - {"TypeSet": {"TypeInt": {"TagInt": []}}}]}, - {"Constant": - {"ConstantAbstract": - {"AbsLitSet": - [{"ConstantInt": [{"TagInt": []}, 5]}, - {"ConstantInt": [{"TagInt": []}, 1]}, - {"ConstantInt": - [{"TagInt": []}, 5]}]}}}]}}]}}], - [{"AbstractLiteral": - {"AbsLitSet": - [{"AbstractLiteral": - {"AbsLitMSet": - [{"Typed": - [{"Constant": {"ConstantAbstract": {"AbsLitSet": []}}}, - {"TypeSet": {"TypeInt": {"TagInt": []}}}]}, - {"Typed": - [{"Constant": {"ConstantAbstract": {"AbsLitSet": []}}}, - {"TypeSet": {"TypeInt": {"TagInt": []}}}]}]}}, - {"Constant": - {"ConstantAbstract": - {"AbsLitMSet": - [{"ConstantAbstract": - {"AbsLitSet": - [{"ConstantInt": [{"TagInt": []}, 5]}]}}]}}}]}}, - {"AbstractLiteral": - {"AbsLitSet": - [{"AbstractLiteral": - {"AbsLitMSet": - [{"Typed": - [{"Constant": {"ConstantAbstract": {"AbsLitSet": []}}}, - {"TypeSet": {"TypeInt": {"TagInt": []}}}]}]}}, - {"AbstractLiteral": - {"AbsLitMSet": - [{"Typed": - [{"Constant": {"ConstantAbstract": {"AbsLitSet": []}}}, - {"TypeSet": {"TypeInt": {"TagInt": []}}}]}, - {"Constant": - {"ConstantAbstract": - {"AbsLitSet": - [{"ConstantInt": [{"TagInt": []}, 2]}]}}}]}}]}}, - {"Typed": - [{"Constant": {"ConstantAbstract": {"AbsLitSet": []}}}, - {"TypeSet": {"TypeMSet": {"TypeSet": {"TypeInt": {"TagInt": []}}}}}]}, - {"Constant": - {"ConstantAbstract": - {"AbsLitSet": - [{"ConstantAbstract": - {"AbsLitMSet": - [{"ConstantAbstract": - {"AbsLitSet": - [{"ConstantInt": - [{"TagInt": []}, 1]}]}}]}}]}}}], - [{"AbstractLiteral": - {"AbsLitSet": - [{"Typed": - [{"Constant": {"ConstantAbstract": {"AbsLitMSet": []}}}, - {"TypeMSet": {"TypeSet": {"TypeInt": {"TagInt": []}}}}]}, - {"AbstractLiteral": - {"AbsLitMSet": - [{"Typed": - [{"Constant": {"ConstantAbstract": {"AbsLitSet": []}}}, - {"TypeSet": {"TypeInt": {"TagInt": []}}}]}]}}]}}]]}}]}}, - {"Op": - {"MkOpImage": - [{"AbstractLiteral": - {"AbsLitFunction": - [[{"Typed": - [{"Constant": - {"ConstantAbstract": - {"AbsLitMatrix": - [{"DomainInt": - [{"TagInt": []}, - [{"RangeBounded": - [{"ConstantInt": [{"TagInt": []}, 1]}, - {"ConstantInt": [{"TagInt": []}, 0]}]}]]}, - []]}}}, - {"TypeMatrix": - [{"TypeInt": {"TagInt": []}}, - {"TypeSet": {"TypeMSet": {"TypeBool": []}}}]}]}, - {"Op": - {"MkOpTogether": - [{"AbstractLiteral": - {"AbsLitSet": - [{"Constant": - {"ConstantAbstract": - {"AbsLitMatrix": - [{"DomainInt": - [{"TagInt": []}, - [{"RangeSingle": - {"ConstantInt": - [{"TagInt": []}, 10]}}, - {"RangeSingle": - {"ConstantInt": - [{"TagInt": []}, 3]}}, - {"RangeSingle": - {"ConstantInt": - [{"TagInt": []}, 8]}}, - {"RangeBounded": - [{"ConstantInt": - [{"TagInt": []}, 0]}, - {"ConstantInt": - [{"TagInt": []}, 0]}]}]]}, - [{"ConstantInt": [{"TagInt": []}, 0]}, - {"ConstantInt": [{"TagInt": []}, 3]}, - {"ConstantInt": [{"TagInt": []}, 2]}, - {"ConstantInt": [{"TagInt": []}, 1]}]]}}}, - {"Typed": - [{"Constant": - {"ConstantAbstract": - {"AbsLitMatrix": - [{"DomainInt": - [{"TagInt": []}, - [{"RangeBounded": - [{"ConstantInt": - [{"TagInt": []}, 1]}, - {"ConstantInt": - [{"TagInt": []}, - 0]}]}]]}, - []]}}}, - {"TypeMatrix": - [{"TypeInt": {"TagInt": []}}, - {"TypeInt": {"TagInt": []}}]}]}]}}, - {"Typed": - [{"Constant": {"ConstantAbstract": {"AbsLitPartition": []}}}, - {"TypePartition": - {"TypeMatrix": - [{"TypeInt": {"TagInt": []}}, - {"TypeInt": {"TagInt": []}}]}}]}]}}], - [{"Constant": - {"ConstantAbstract": - {"AbsLitMatrix": - [{"DomainInt": - [{"TagInt": []}, - [{"RangeBounded": - [{"ConstantInt": [{"TagInt": []}, 6]}, - {"ConstantInt": [{"TagInt": []}, 7]}]}, - {"RangeBounded": - [{"ConstantInt": [{"TagInt": []}, 4]}, - {"ConstantInt": [{"TagInt": []}, 4]}]}]]}, - [{"ConstantAbstract": - {"AbsLitSet": - [{"ConstantAbstract": - {"AbsLitMSet": - [{"ConstantBool": true}, - {"ConstantBool": true}, - {"ConstantBool": true}]}}]}}, - {"ConstantAbstract": - {"AbsLitSet": - [{"ConstantAbstract": - {"AbsLitMSet": [{"ConstantBool": false}]}}]}}, - {"ConstantAbstract": - {"AbsLitSet": - [{"ConstantAbstract": - {"AbsLitMSet": [{"ConstantBool": false}]}}, - {"ConstantAbstract": - {"AbsLitMSet": - [{"ConstantBool": false}, - {"ConstantBool": true}, - {"ConstantBool": false}]}}]}}]]}}}, - {"Op": - {"MkOpIndexing": - [{"Comprehension": - [{"Op": - {"MkOpNeq": - [{"Constant": {"ConstantInt": [{"TagInt": []}, 5]}}, - {"Constant": {"ConstantInt": [{"TagInt": []}, 1]}}]}}, - [{"Generator": - {"GenDomainNoRepr": - [{"Single": {"Name": "l_1"}}, {"DomainBool": []}]}}, - {"Condition": - {"Op": - {"MkOpIff": - [{"Constant": {"ConstantBool": true}}, - {"Constant": {"ConstantBool": false}}]}}}]]}, - {"Op": - {"MkOpMin": - {"Typed": - [{"Constant": {"ConstantAbstract": {"AbsLitMSet": []}}}, - {"TypeMSet": {"TypeInt": {"TagInt": []}}}]}}}]}}], - [{"Typed": - [{"Constant": - {"ConstantAbstract": - {"AbsLitMatrix": - [{"DomainInt": - [{"TagInt": []}, - [{"RangeBounded": - [{"ConstantInt": [{"TagInt": []}, 1]}, - {"ConstantInt": [{"TagInt": []}, 0]}]}]]}, - []]}}}, - {"TypeMatrix": - [{"TypeInt": {"TagInt": []}}, - {"TypeSet": {"TypeMSet": {"TypeBool": []}}}]}]}, - {"Op": - {"MkOpAnd": - {"Op": - {"MkOpFlatten": - [null, - {"Constant": - {"ConstantAbstract": - {"AbsLitMatrix": - [{"DomainInt": - [{"TagInt": []}, - [{"RangeBounded": - [{"ConstantInt": - [{"TagInt": []}, 1]}, - {"ConstantInt": - [{"TagInt": []}, 2]}]}]]}, - [{"ConstantBool": false}, - {"ConstantBool": false}]]}}}]}}}}], - [{"Constant": - {"ConstantAbstract": - {"AbsLitMatrix": - [{"DomainInt": - [{"TagInt": []}, - [{"RangeSingle": {"ConstantInt": [{"TagInt": []}, 0]}}, - {"RangeBounded": - [{"ConstantInt": [{"TagInt": []}, 5]}, - {"ConstantInt": [{"TagInt": []}, 5]}]}]]}, - [{"ConstantAbstract": - {"AbsLitSet": - [{"ConstantAbstract": - {"AbsLitMSet": - [{"ConstantBool": false}, - {"ConstantBool": false}]}}]}}, - {"ConstantAbstract": - {"AbsLitSet": - [{"ConstantAbstract": - {"AbsLitMSet": - [{"ConstantBool": false}, - {"ConstantBool": true}, - {"ConstantBool": false}]}}]}}]]}}}, - {"Op": - {"MkOpNot": - {"Op": - {"MkOpNot": - {"Op": - {"MkOpImply": - [{"Constant": {"ConstantBool": true}}, - {"Constant": {"ConstantBool": true}}]}}}}}}]]}}, - {"Comprehension": - [{"Typed": - [{"Constant": {"ConstantAbstract": {"AbsLitSet": []}}}, - {"TypeSet": {"TypeMSet": {"TypeBool": []}}}]}, - [{"Generator": - {"GenDomainNoRepr": - [{"Single": {"Name": "l_2"}}, - {"DomainSet": - [[], {"SizeAttr_MinSize": {"Reference": [{"Name": "var1"}, null]}}, - {"DomainMSet": - [[], - [{"SizeAttr_MinMaxSize": - [{"Constant": {"ConstantInt": [{"TagInt": []}, 2]}}, - {"Constant": {"ConstantInt": [{"TagInt": []}, 3]}}]}, - {"OccurAttr_MinOccur": - {"Op": - {"MkOpPow": - [{"Reference": [{"Name": "var1"}, null]}, - {"Reference": [{"Name": "var1"}, null]}]}}}], - {"DomainBool": []}]}]}]}}, - {"Generator": - {"GenDomainNoRepr": - [{"Single": {"Name": "l_3"}}, - {"DomainSet": - [[], {"SizeAttr_None": []}, - {"DomainMSet": - [[], - [{"SizeAttr_MinMaxSize": - [{"Constant": {"ConstantInt": [{"TagInt": []}, 1]}}, - {"Constant": {"ConstantInt": [{"TagInt": []}, 2]}}]}, - {"OccurAttr_MaxOccur": - {"Op": - {"MkOpMod": - [{"Reference": [{"Name": "var1"}, null]}, - {"Reference": [{"Name": "var1"}, null]}]}}}], - {"DomainBool": []}]}]}]}}, - {"Condition": - {"Op": - {"MkOpGeq": - [{"Op": - {"MkOpMax": - {"Constant": - {"ConstantAbstract": - {"AbsLitSet": - [{"ConstantInt": [{"TagInt": []}, 3]}]}}}}}, - {"Op": - {"MkOpPow": - [{"Constant": {"ConstantInt": [{"TagInt": []}, 3]}}, - {"Op": - {"MkOpPow": - [{"Constant": {"ConstantInt": [{"TagInt": []}, 3]}}, - {"Op": - {"MkOpNegate": - {"Constant": - {"ConstantInt": - [{"TagInt": []}, - 0]}}}}]}}]}}]}}}]]}]}}]}, - {"Objective": ["Minimising", {"Reference": [{"Name": "var1"}, null]}]}]} \ No newline at end of file diff --git a/tests/parse_print/autogen/730~1439082038_16/typecheck.expected b/tests/parse_print/autogen/730~1439082038_16/typecheck.expected deleted file mode 100644 index 147d15558c..0000000000 --- a/tests/parse_print/autogen/730~1439082038_16/typecheck.expected +++ /dev/null @@ -1,14 +0,0 @@ -Error: - Category checking failed. - The domain : set (minSize var1) of mset (minSize 2, maxSize 3, minOccur var1 ** var1) of bool - Its category : decision - - The domain : mset (minSize 2, maxSize 3, minOccur var1 ** var1) of bool - Its category : decision - - The domain : set of mset (minSize 1, maxSize 2, maxOccur var1 % var1) of bool - Its category : decision - - The domain : mset (minSize 1, maxSize 2, maxOccur var1 % var1) of bool - Its category : decision - \ No newline at end of file diff --git a/tests/parse_print/autogen/731~final/model.expected.json b/tests/parse_print/autogen/731~final/model.expected.json deleted file mode 100644 index e09b459fe0..0000000000 --- a/tests/parse_print/autogen/731~final/model.expected.json +++ /dev/null @@ -1,76 +0,0 @@ -{"mInfo": - {"finds": [], "givens": [], "enumGivens": [], "enumLettings": [], "lettings": [], "unnameds": [], - "strategyQ": {"Auto": {"Interactive": []}}, "strategyA": {"Auto": {"Interactive": []}}, "trailCompact": [], - "nameGenState": [], "nbExtraGivens": 0, "representations": [], "representationsTree": [], "originalDomains": [], - "trailGeneralised": [], "trailVerbose": [], "trailRewrites": []}, - "mLanguage": {"language": {"Name": "Essence"}, "version": [1, 3]}, - "mStatements": - [{"Declaration": - {"FindOrGiven": - ["Find", {"Name": "var1"}, - {"DomainInt": - [{"TagInt": []}, - [{"RangeSingle": {"Constant": {"ConstantInt": [{"TagInt": []}, 0]}}}, - {"RangeSingle": {"Constant": {"ConstantInt": [{"TagInt": []}, 0]}}}]]}]}}, - {"SuchThat": - [{"Op": - {"MkOpImage": - [{"AbstractLiteral": - {"AbsLitFunction": - [[{"AbstractLiteral": - {"AbsLitMatrix": - [{"DomainInt": - [{"TagInt": []}, - [{"RangeBounded": - [{"Constant": {"ConstantInt": [{"TagInt": []}, 1]}}, - {"Constant": {"ConstantInt": [{"TagInt": []}, 1]}}]}]]}, - [{"AbstractLiteral": - {"AbsLitSet": - [{"Constant": - {"ConstantAbstract": - {"AbsLitMSet": - [{"ConstantBool": false}, - {"ConstantBool": false}]}}}, - {"Typed": - [{"Constant": {"ConstantAbstract": {"AbsLitMSet": []}}}, - {"TypeMSet": {"TypeBool": []}}]}]}}]]}}, - {"Constant": {"ConstantBool": false}}]]}}, - {"Comprehension": - [{"AbstractLiteral": - {"AbsLitSet": - [{"Constant": {"ConstantAbstract": {"AbsLitMSet": [{"ConstantBool": true}]}}}, - {"Typed": - [{"Constant": {"ConstantAbstract": {"AbsLitMSet": []}}}, - {"TypeMSet": {"TypeBool": []}}]}]}}, - [{"Generator": - {"GenDomainNoRepr": - [{"Single": {"Name": "l_2"}}, - {"DomainSet": - [[], {"SizeAttr_MinSize": {"Reference": [{"Name": "var1"}, null]}}, - {"DomainMSet": - [[], - [{"SizeAttr_MinMaxSize": - [{"Constant": {"ConstantInt": [{"TagInt": []}, 2]}}, - {"Constant": {"ConstantInt": [{"TagInt": []}, 3]}}]}, - {"OccurAttr_MinOccur": - {"Op": - {"MkOpPow": - [{"Reference": [{"Name": "var1"}, null]}, - {"Reference": [{"Name": "var1"}, null]}]}}}], - {"DomainBool": []}]}]}]}}, - {"Generator": - {"GenDomainNoRepr": - [{"Single": {"Name": "l_3"}}, - {"DomainSet": - [[], {"SizeAttr_None": []}, - {"DomainMSet": - [[], - [{"SizeAttr_MinMaxSize": - [{"Constant": {"ConstantInt": [{"TagInt": []}, 1]}}, - {"Constant": {"ConstantInt": [{"TagInt": []}, 2]}}]}, - {"OccurAttr_MaxOccur": - {"Op": - {"MkOpMod": - [{"Reference": [{"Name": "var1"}, null]}, - {"Reference": [{"Name": "var1"}, null]}]}}}], - {"DomainBool": []}]}]}]}}]]}]}}]}]} \ No newline at end of file diff --git a/tests/parse_print/autogen/731~final/typecheck.expected b/tests/parse_print/autogen/731~final/typecheck.expected deleted file mode 100644 index 147d15558c..0000000000 --- a/tests/parse_print/autogen/731~final/typecheck.expected +++ /dev/null @@ -1,14 +0,0 @@ -Error: - Category checking failed. - The domain : set (minSize var1) of mset (minSize 2, maxSize 3, minOccur var1 ** var1) of bool - Its category : decision - - The domain : mset (minSize 2, maxSize 3, minOccur var1 ** var1) of bool - Its category : decision - - The domain : set of mset (minSize 1, maxSize 2, maxOccur var1 % var1) of bool - Its category : decision - - The domain : mset (minSize 1, maxSize 2, maxOccur var1 % var1) of bool - Its category : decision - \ No newline at end of file diff --git a/tests/parse_print/autogen/768~1439583525_36/model.expected.json b/tests/parse_print/autogen/768~1439583525_36/model.expected.json deleted file mode 100644 index 738127a697..0000000000 --- a/tests/parse_print/autogen/768~1439583525_36/model.expected.json +++ /dev/null @@ -1,412 +0,0 @@ -{"mInfo": - {"finds": [], "givens": [], "enumGivens": [], "enumLettings": [], "lettings": [], "unnameds": [], - "strategyQ": {"Auto": {"Interactive": []}}, "strategyA": {"Auto": {"Interactive": []}}, "trailCompact": [], - "nameGenState": [], "nbExtraGivens": 0, "representations": [], "representationsTree": [], "originalDomains": [], - "trailGeneralised": [], "trailVerbose": [], "trailRewrites": []}, - "mLanguage": {"language": {"Name": "Essence"}, "version": [1, 3]}, - "mStatements": - [{"Declaration": {"FindOrGiven": ["Find", {"Name": "var1"}, {"DomainBool": []}]}}, - {"SuchThat": - [{"Reference": [{"Name": "var1"}, null]}, {"Reference": [{"Name": "var1"}, null]}, - {"Reference": [{"Name": "var1"}, null]}, - {"Op": - {"MkOpIn": - [{"Comprehension": - [{"Reference": [{"Name": "l_1"}, null]}, - [{"Generator": - {"GenDomainNoRepr": - [{"Single": {"Name": "l_1"}}, - {"DomainSet": - [[], - {"SizeAttr_MaxSize": - {"Op": - {"MkOpMinus": - [{"Op": - {"MkOpFreq": - [{"AbstractLiteral": - {"AbsLitMSet": - [{"Reference": - [{"Name": "var1"}, null]}]}}, - {"Reference": [{"Name": "var1"}, null]}]}}, - {"Op": - {"MkOpMod": - [{"Op": - {"MkOpMinus": - [{"Constant": - {"ConstantInt": - [{"TagInt": []}, 1]}}, - {"Constant": - {"ConstantInt": - [{"TagInt": []}, 3]}}]}}, - {"Op": - {"MkOpPow": - [{"Constant": - {"ConstantInt": - [{"TagInt": []}, 1]}}, - {"Constant": - {"ConstantInt": - [{"TagInt": []}, - 3]}}]}}]}}]}}}, - {"DomainInt": - [{"TagInt": []}, - [{"RangeSingle": - {"Constant": {"ConstantInt": [{"TagInt": []}, 1]}}}, - {"RangeSingle": - {"Constant": {"ConstantInt": [{"TagInt": []}, 4]}}}]]}]}]}}, - {"Condition": - {"Op": - {"MkOpImply": - [{"Op": - {"MkOpApart": - [{"Constant": - {"ConstantAbstract": - {"AbsLitSet": - [{"ConstantAbstract": - {"AbsLitFunction": - [[{"ConstantInt": - [{"TagInt": []}, 3]}, - {"ConstantBool": true}], - [{"ConstantInt": - [{"TagInt": []}, 2]}, - {"ConstantBool": true}]]}}]}}}, - {"Constant": - {"ConstantAbstract": - {"AbsLitPartition": - [[{"ConstantAbstract": - {"AbsLitFunction": - [[{"ConstantInt": - [{"TagInt": []}, 0]}, - {"ConstantBool": true}], - [{"ConstantInt": - [{"TagInt": []}, 2]}, - {"ConstantBool": true}], - [{"ConstantInt": - [{"TagInt": []}, 5]}, - {"ConstantBool": false}], - [{"ConstantInt": - [{"TagInt": []}, 1]}, - {"ConstantBool": true}]]}}, - {"ConstantAbstract": - {"AbsLitFunction": - [[{"ConstantInt": - [{"TagInt": []}, 1]}, - {"ConstantBool": true}], - [{"ConstantInt": - [{"TagInt": []}, 2]}, - {"ConstantBool": true}]]}}], - [{"ConstantAbstract": - {"AbsLitFunction": - [[{"ConstantInt": - [{"TagInt": []}, 1]}, - {"ConstantBool": true}]]}}, - {"ConstantAbstract": - {"AbsLitFunction": - [[{"ConstantInt": - [{"TagInt": []}, 5]}, - {"ConstantBool": true}], - [{"ConstantInt": - [{"TagInt": []}, 3]}, - {"ConstantBool": - true}]]}}]]}}}]}}, - {"Op": - {"MkOpLeq": - [{"Op": - {"MkOpSum": - {"Constant": - {"ConstantAbstract": - {"AbsLitMatrix": - [{"DomainInt": - [{"TagInt": []}, - [{"RangeSingle": - {"ConstantInt": - [{"TagInt": []}, - 3]}}, - {"RangeSingle": - {"ConstantInt": - [{"TagInt": []}, - 9]}}, - {"RangeSingle": - {"ConstantInt": - [{"TagInt": []}, - 2]}}, - {"RangeBounded": - [{"ConstantInt": - [{"TagInt": []}, - 5]}, - {"ConstantInt": - [{"TagInt": []}, - 5]}]}]]}, - [{"ConstantInt": - [{"TagInt": []}, 3]}, - {"ConstantInt": - [{"TagInt": []}, 2]}, - {"ConstantInt": - [{"TagInt": []}, 1]}, - {"ConstantInt": - [{"TagInt": []}, 5]}]]}}}}}, - {"Op": - {"MkOpPow": - [{"Constant": {"ConstantInt": [{"TagInt": []}, 0]}}, - {"Op": - {"MkOpPow": - [{"Constant": - {"ConstantInt": - [{"TagInt": []}, 5]}}, - {"Op": - {"MkOpFactorial": - {"Constant": - {"ConstantInt": - [{"TagInt": []}, - 3]}}}}]}}]}}]}}]}}}, - {"Condition": - {"Op": - {"MkOpOr": - {"Comprehension": - [{"Op": - {"MkOpTogether": - [{"Constant": - {"ConstantAbstract": - {"AbsLitSet": - [{"ConstantBool": false}, - {"ConstantBool": true}]}}}, - {"Constant": - {"ConstantAbstract": - {"AbsLitPartition": - [[{"ConstantBool": true}, - {"ConstantBool": false}, - {"ConstantBool": true}, - {"ConstantBool": true}]]}}}]}}, - [{"Generator": - {"GenDomainNoRepr": - [{"Single": {"Name": "l_2"}}, {"DomainBool": []}]}}, - {"Generator": - {"GenDomainNoRepr": - [{"Single": {"Name": "l_3"}}, {"DomainBool": []}]}}, - {"Condition": {"Reference": [{"Name": "l_3"}, null]}}]]}}}}]]}, - {"Op": - {"MkOpIndexing": - [{"AbstractLiteral": - {"AbsLitMatrix": - [{"DomainInt": - [{"TagInt": []}, - [{"RangeSingle": {"Constant": {"ConstantInt": [{"TagInt": []}, 2]}}}, - {"RangeBounded": - [{"Constant": {"ConstantInt": [{"TagInt": []}, 6]}}, - {"Constant": {"ConstantInt": [{"TagInt": []}, 7]}}]}]]}, - [{"Constant": - {"ConstantAbstract": - {"AbsLitSet": - [{"ConstantAbstract": - {"AbsLitMatrix": - [{"DomainInt": - [{"TagInt": []}, - [{"RangeBounded": - [{"ConstantInt": - [{"TagInt": []}, 2]}, - {"ConstantInt": - [{"TagInt": []}, 2]}]}]]}, - [{"ConstantAbstract": - {"AbsLitSet": - [{"ConstantInt": - [{"TagInt": []}, 4]}, - {"ConstantInt": - [{"TagInt": []}, 1]}, - {"ConstantInt": - [{"TagInt": []}, - 3]}]}}]]}}]}}}, - {"Constant": - {"ConstantAbstract": - {"AbsLitSet": - [{"ConstantAbstract": - {"AbsLitMatrix": - [{"DomainInt": - [{"TagInt": []}, - [{"RangeBounded": - [{"ConstantInt": - [{"TagInt": []}, 2]}, - {"ConstantInt": - [{"TagInt": []}, 2]}]}]]}, - [{"ConstantAbstract": - {"AbsLitSet": - [{"ConstantInt": - [{"TagInt": []}, - 0]}]}}]]}}]}}}, - {"AbstractLiteral": - {"AbsLitSet": - [{"AbstractLiteral": - {"AbsLitMatrix": - [{"DomainInt": - [{"TagInt": []}, - [{"RangeBounded": - [{"Constant": - {"ConstantInt": - [{"TagInt": []}, 1]}}, - {"Constant": - {"ConstantInt": - [{"TagInt": []}, 5]}}]}]]}, - [{"Constant": - {"ConstantAbstract": - {"AbsLitSet": - [{"ConstantInt": - [{"TagInt": []}, 1]}, - {"ConstantInt": - [{"TagInt": []}, 2]}, - {"ConstantInt": - [{"TagInt": []}, 0]}]}}}, - {"Constant": - {"ConstantAbstract": - {"AbsLitSet": - [{"ConstantInt": - [{"TagInt": []}, 1]}, - {"ConstantInt": - [{"TagInt": []}, 0]}]}}}, - {"Constant": - {"ConstantAbstract": - {"AbsLitSet": - [{"ConstantInt": - [{"TagInt": []}, 4]}, - {"ConstantInt": - [{"TagInt": []}, 3]}, - {"ConstantInt": - [{"TagInt": []}, 4]}]}}}, - {"Constant": - {"ConstantAbstract": - {"AbsLitSet": - [{"ConstantInt": - [{"TagInt": []}, 2]}, - {"ConstantInt": - [{"TagInt": []}, 1]}, - {"ConstantInt": - [{"TagInt": []}, 5]}]}}}, - {"Typed": - [{"Constant": - {"ConstantAbstract": - {"AbsLitSet": []}}}, - {"TypeSet": - {"TypeInt": {"TagInt": []}}}]}]]}}, - {"Constant": - {"ConstantAbstract": - {"AbsLitMatrix": - [{"DomainInt": - [{"TagInt": []}, - [{"RangeSingle": - {"ConstantInt": - [{"TagInt": []}, 7]}}, - {"RangeSingle": - {"ConstantInt": - [{"TagInt": []}, 4]}}, - {"RangeBounded": - [{"ConstantInt": - [{"TagInt": []}, 6]}, - {"ConstantInt": - [{"TagInt": []}, 7]}]}]]}, - [{"ConstantAbstract": - {"AbsLitSet": - [{"ConstantInt": - [{"TagInt": []}, 0]}, - {"ConstantInt": - [{"TagInt": []}, 1]}]}}, - {"ConstantAbstract": - {"AbsLitSet": - [{"ConstantInt": - [{"TagInt": []}, 3]}, - {"ConstantInt": - [{"TagInt": []}, 0]}]}}, - {"ConstantAbstract": - {"AbsLitSet": - [{"ConstantInt": - [{"TagInt": []}, 4]}, - {"ConstantInt": - [{"TagInt": []}, 1]}, - {"ConstantInt": - [{"TagInt": []}, 0]}]}}, - {"ConstantAbstract": - {"AbsLitSet": - [{"ConstantInt": - [{"TagInt": []}, 0]}]}}]]}}}, - {"Constant": - {"ConstantAbstract": - {"AbsLitMatrix": - [{"DomainInt": - [{"TagInt": []}, - [{"RangeBounded": - [{"ConstantInt": - [{"TagInt": []}, 0]}, - {"ConstantInt": - [{"TagInt": []}, 0]}]}]]}, - [{"ConstantAbstract": - {"AbsLitSet": - [{"ConstantInt": - [{"TagInt": []}, 1]}, - {"ConstantInt": - [{"TagInt": []}, 1]}, - {"ConstantInt": - [{"TagInt": []}, - 3]}]}}]]}}}]}}]]}}, - {"Op": - {"MkOpProduct": - {"Comprehension": - [{"Op": - {"MkOpFactorial": - {"Op": - {"MkOpNegate": - {"Reference": [{"Name": "l_4"}, null]}}}}}, - [{"Generator": - {"GenDomainNoRepr": - [{"Single": {"Name": "l_4"}}, - {"DomainInt": - [{"TagInt": []}, - [{"RangeSingle": - {"Constant": - {"ConstantInt": [{"TagInt": []}, 2]}}}, - {"RangeSingle": - {"Constant": - {"ConstantInt": - [{"TagInt": []}, 4]}}}]]}]}}, - {"Generator": - {"GenDomainNoRepr": - [{"Single": {"Name": "l_5"}}, - {"DomainInt": - [{"TagInt": []}, - [{"RangeSingle": - {"Constant": - {"ConstantInt": [{"TagInt": []}, 2]}}}, - {"RangeSingle": - {"Constant": - {"ConstantInt": - [{"TagInt": []}, 0]}}}]]}]}}, - {"Condition": - {"Op": - {"MkOpAllDiff": - {"Typed": - [{"Constant": - {"ConstantAbstract": - {"AbsLitMatrix": - [{"DomainInt": - [{"TagInt": []}, - [{"RangeBounded": - [{"ConstantInt": - [{"TagInt": - []}, - 1]}, - {"ConstantInt": - [{"TagInt": - []}, - 0]}]}]]}, - []]}}}, - {"TypeMatrix": - [{"TypeInt": {"TagInt": []}}, - {"TypeInt": {"TagInt": []}}]}]}}}}, - {"Condition": - {"Op": - {"MkOpIff": - [{"Op": - {"MkOpLt": - [{"Reference": [{"Name": "l_5"}, null]}, - {"Reference": [{"Name": "l_5"}, null]}]}}, - {"Op": - {"MkOpNot": - {"Constant": - {"ConstantBool": - false}}}}]}}}]]}}}]}}]}}, - {"Reference": [{"Name": "var1"}, null]}, {"Reference": [{"Name": "var1"}, null]}]}]} \ No newline at end of file diff --git a/tests/parse_print/autogen/768~1439583525_36/typecheck.expected b/tests/parse_print/autogen/768~1439583525_36/typecheck.expected deleted file mode 100644 index ceb0e13ff5..0000000000 --- a/tests/parse_print/autogen/768~1439583525_36/typecheck.expected +++ /dev/null @@ -1,5 +0,0 @@ -Error: - Category checking failed. - The domain : set (maxSize freq(mset(var1), var1) - (1 - 3) % 1 ** 3) of int(1, 4) - Its category : decision - \ No newline at end of file diff --git a/tests/parse_print/autogen/769~final/model.expected.json b/tests/parse_print/autogen/769~final/model.expected.json deleted file mode 100644 index 733477c240..0000000000 --- a/tests/parse_print/autogen/769~final/model.expected.json +++ /dev/null @@ -1,67 +0,0 @@ -{"mInfo": - {"finds": [], "givens": [], "enumGivens": [], "enumLettings": [], "lettings": [], "unnameds": [], - "strategyQ": {"Auto": {"Interactive": []}}, "strategyA": {"Auto": {"Interactive": []}}, "trailCompact": [], - "nameGenState": [], "nbExtraGivens": 0, "representations": [], "representationsTree": [], "originalDomains": [], - "trailGeneralised": [], "trailVerbose": [], "trailRewrites": []}, - "mLanguage": {"language": {"Name": "Essence"}, "version": [1, 3]}, - "mStatements": - [{"Declaration": {"FindOrGiven": ["Find", {"Name": "var1"}, {"DomainBool": []}]}}, - {"SuchThat": - [{"Op": - {"MkOpIn": - [{"Comprehension": - [{"Constant": {"ConstantAbstract": {"AbsLitSet": [{"ConstantInt": [{"TagInt": []}, 2]}]}}}, - [{"Generator": - {"GenDomainNoRepr": - [{"Single": {"Name": "l_1"}}, - {"DomainSet": - [[], - {"SizeAttr_MaxSize": - {"Op": - {"MkOpMinus": - [{"Op": - {"MkOpFreq": - [{"AbstractLiteral": - {"AbsLitMSet": - [{"Reference": - [{"Name": "var1"}, null]}]}}, - {"Reference": [{"Name": "var1"}, null]}]}}, - {"Op": - {"MkOpMod": - [{"Op": - {"MkOpMinus": - [{"Constant": - {"ConstantInt": - [{"TagInt": []}, 1]}}, - {"Constant": - {"ConstantInt": - [{"TagInt": []}, 3]}}]}}, - {"Op": - {"MkOpPow": - [{"Constant": - {"ConstantInt": - [{"TagInt": []}, 1]}}, - {"Constant": - {"ConstantInt": - [{"TagInt": []}, - 3]}}]}}]}}]}}}, - {"DomainInt": - [{"TagInt": []}, - [{"RangeSingle": - {"Constant": {"ConstantInt": [{"TagInt": []}, 1]}}}, - {"RangeSingle": - {"Constant": - {"ConstantInt": [{"TagInt": []}, 4]}}}]]}]}]}}]]}, - {"Constant": - {"ConstantAbstract": - {"AbsLitSet": - [{"ConstantAbstract": - {"AbsLitMatrix": - [{"DomainInt": - [{"TagInt": []}, - [{"RangeBounded": - [{"ConstantInt": [{"TagInt": []}, 1]}, - {"ConstantInt": [{"TagInt": []}, 1]}]}]]}, - [{"ConstantAbstract": - {"AbsLitSet": - [{"ConstantInt": [{"TagInt": []}, 5]}]}}]]}}]}}}]}}]}]} \ No newline at end of file diff --git a/tests/parse_print/autogen/769~final/typecheck.expected b/tests/parse_print/autogen/769~final/typecheck.expected deleted file mode 100644 index ceb0e13ff5..0000000000 --- a/tests/parse_print/autogen/769~final/typecheck.expected +++ /dev/null @@ -1,5 +0,0 @@ -Error: - Category checking failed. - The domain : set (maxSize freq(mset(var1), var1) - (1 - 3) % 1 ** 3) of int(1, 4) - Its category : decision - \ No newline at end of file From 97b882fab923d3501fb35c92fe3d27878ebe59ea Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?=C3=96zg=C3=BCr=20Akg=C3=BCn?= Date: Fri, 17 Jan 2025 11:49:05 +0000 Subject: [PATCH 217/229] min/max of expression domains --- src/Conjure/Language/Lenses.hs | 17 ++++++++++++++--- 1 file changed, 14 insertions(+), 3 deletions(-) diff --git a/src/Conjure/Language/Lenses.hs b/src/Conjure/Language/Lenses.hs index 17a4908523..a0674d5bfa 100644 --- a/src/Conjure/Language/Lenses.hs +++ b/src/Conjure/Language/Lenses.hs @@ -1633,7 +1633,11 @@ fixRelationProj= transformBi f -maxOfDomain :: (MonadFailDoc m, Pretty r) => Domain r Expression -> m Expression +maxOfDomain :: + MonadFailDoc m => + Pretty r => + Domain r Expression -> m Expression +maxOfDomain (DomainIntE x) = return $ make opMax x maxOfDomain (DomainInt _ [] ) = failDoc "rule_DomainMinMax.maxOfDomain []" maxOfDomain (DomainInt _ [r]) = maxOfRange r maxOfDomain (DomainInt _ rs ) = do @@ -1648,7 +1652,12 @@ maxOfRange (RangeBounded _ x) = return x maxOfRange (RangeUpperBounded x) = return x maxOfRange r = failDoc ("rule_DomainMinMax.maxOfRange" <+> pretty (show r)) -minOfDomain :: (MonadFailDoc m, Pretty r) => Domain r Expression -> m Expression +minOfDomain :: + (?typeCheckerMode::TypeCheckerMode) => + MonadFailDoc m => + Pretty r => + Domain r Expression -> m Expression +minOfDomain (DomainIntE x) = return $ make opMin x minOfDomain (DomainInt _ [] ) = failDoc "rule_DomainMinMax.minOfDomain []" minOfDomain (DomainInt _ [r]) = minOfRange r minOfDomain (DomainInt _ rs ) = do @@ -1657,7 +1666,9 @@ minOfDomain (DomainInt _ rs ) = do minOfDomain (DomainReference _ (Just d)) = minOfDomain d minOfDomain d = failDoc ("rule_DomainMinMax.minOfDomain" <+> pretty d) -minOfRange :: MonadFailDoc m => Range Expression -> m Expression +minOfRange :: + MonadFailDoc m => + Range Expression -> m Expression minOfRange (RangeSingle x) = return x minOfRange (RangeBounded x _) = return x minOfRange (RangeLowerBounded x) = return x From 932eb69c784ee3a9bce0f3ecb7ad6fa60eed6e03 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?=C3=96zg=C3=BCr=20Akg=C3=BCn?= Date: Sun, 19 Jan 2025 12:19:02 +0000 Subject: [PATCH 218/229] parsing tagged int domains and literals --- src/Conjure/Language/AST/ASTParser.hs | 12 ++++- src/Conjure/Language/AST/Reformer.hs | 4 +- src/Conjure/Language/AST/Syntax.hs | 10 ++-- src/Conjure/Language/Constant.hs | 2 +- src/Conjure/Language/Domain.hs | 26 +++++------ .../Language/Expression/DomainSizeOf.hs | 2 +- src/Conjure/Language/Instantiate.hs | 4 +- src/Conjure/Language/Lenses.hs | 4 +- src/Conjure/Language/Type.hs | 6 +++ src/Conjure/Language/Validator.hs | 46 ++++++++++++------- src/Conjure/Representations/Primitive.hs | 2 +- src/Conjure/Rules/BubbleUp.hs | 19 ++++++-- src/Conjure/Rules/DontCare.hs | 2 +- src/Conjure/UI/TypeCheck.hs | 4 +- 14 files changed, 92 insertions(+), 51 deletions(-) diff --git a/src/Conjure/Language/AST/ASTParser.hs b/src/Conjure/Language/AST/ASTParser.hs index 98d5eed1c3..cc9ef0bad5 100644 --- a/src/Conjure/Language/AST/ASTParser.hs +++ b/src/Conjure/Language/AST/ASTParser.hs @@ -296,7 +296,12 @@ parseShortTupleLiteral = try $ do return $ TupleLiteralNodeShort $ ShortTuple (ListNode lOpen exprs lClose) parseIntLiteral :: Parser LiteralNode -parseIntLiteral = IntLiteral . StrictToken [] <$> intLiteral +parseIntLiteral = do + lit <- intLiteral + maybe_tag <- optional $ do + _ <- want L_Colon + identifier + return $ IntLiteral (StrictToken [] lit) maybe_tag parseBoolLiteral :: Parser LiteralNode parseBoolLiteral = BoolLiteral <$> (need L_true <|> need L_false) @@ -631,8 +636,11 @@ parseSpecialCase = do parseIntDomain :: Parser DomainNode parseIntDomain = do lInt <- need L_int + maybe_tag <- optional $ do + _ <- want L_Colon + identifier ranges <- optional $ parenListStrict $ commaList parseRange - return $ RangedIntDomainNode lInt ranges + return $ RangedIntDomainNode lInt ranges maybe_tag parseTuple :: Parser DomainNode parseTuple = do diff --git a/src/Conjure/Language/AST/Reformer.hs b/src/Conjure/Language/AST/Reformer.hs index a69d462a4d..5e834e8c8b 100644 --- a/src/Conjure/Language/AST/Reformer.hs +++ b/src/Conjure/Language/AST/Reformer.hs @@ -129,7 +129,7 @@ instance HighLevelTree QuantificationPattern where instance HighLevelTree LiteralNode where makeTree x = case x of - IntLiteral lt -> makeTree lt + IntLiteral lt _ -> makeTree lt -- TODO: should the tag be represented here? BoolLiteral lt -> makeTree lt MatrixLiteral mln -> makeTree mln TupleLiteralNode lt -> makeTree lt @@ -214,7 +214,7 @@ instance HighLevelTree DomainNode where makeTree x = HLTagged (TIDomain x) $ case x of ParenDomainNode a b c -> [makeTree a, makeTree b, makeTree c] BoolDomainNode lt -> [makeTree lt] - RangedIntDomainNode lt ln -> [makeTree lt,makeTree ln] + RangedIntDomainNode lt ln _maybe_tag -> [makeTree lt,makeTree ln] -- TODO: should the tag be represented here? MetaVarDomain a -> [makeTree a] RangedEnumNode nn ln -> [makeTree nn , makeTree ln] -- EnumDomainNode nn -> makeTree nn diff --git a/src/Conjure/Language/AST/Syntax.hs b/src/Conjure/Language/AST/Syntax.hs index 7d7ee90858..867949989c 100644 --- a/src/Conjure/Language/AST/Syntax.hs +++ b/src/Conjure/Language/AST/Syntax.hs @@ -205,7 +205,7 @@ type MAttributes = Maybe (ListNode AttributeNode) data DomainNode = ParenDomainNode SToken DomainNode LToken | BoolDomainNode SToken - | RangedIntDomainNode SToken (Maybe (ListNode RangeNode)) + | RangedIntDomainNode SToken (Maybe (ListNode RangeNode)) (Maybe ETok) -- the IntTag | RangedEnumNode NameNodeS (Maybe (ListNode RangeNode)) | MetaVarDomain SToken | ShortTupleDomainNode (ListNode DomainNode) @@ -227,7 +227,8 @@ instance Pretty DomainNode where pretty x = case x of ParenDomainNode op dom cl -> pretty op <> pretty dom <> pretty cl BoolDomainNode lt -> pretty lt - RangedIntDomainNode lt m_ln -> pretty lt <> pretty m_ln + RangedIntDomainNode lt m_ln Nothing -> pretty lt <> pretty m_ln + RangedIntDomainNode lt m_ln (Just tag) -> pretty lt <> ":" <> pretty tag <> pretty m_ln RangedEnumNode nn m_ln -> pretty nn <> pretty m_ln MetaVarDomain lt -> pretty lt ShortTupleDomainNode ln -> pretty ln @@ -382,7 +383,7 @@ instance Null LongTuple where -- Literals data LiteralNode - = IntLiteral SToken + = IntLiteral SToken (Maybe ETok) -- the IntTag | BoolLiteral SToken | MatrixLiteral MatrixLiteralNode | TupleLiteralNode LongTuple @@ -400,7 +401,8 @@ data LiteralNode instance Pretty LiteralNode where pretty l = case l of - IntLiteral lt -> pretty lt + IntLiteral lt Nothing -> pretty lt + IntLiteral lt (Just tag) -> pretty lt <> ":" <> pretty tag BoolLiteral lt -> pretty lt MatrixLiteral mln -> pretty mln TupleLiteralNode lt -> pretty lt diff --git a/src/Conjure/Language/Constant.hs b/src/Conjure/Language/Constant.hs index 7daa0484a7..9bb39c6910 100644 --- a/src/Conjure/Language/Constant.hs +++ b/src/Conjure/Language/Constant.hs @@ -265,7 +265,7 @@ instance TypeOf Constant where instance DomainSizeOf Constant Integer where domainSizeOf DomainBool{} = return 2 - domainSizeOf (DomainIntE x) = bug ("not implemented, domainSizeOf DomainIntE" <+> pretty (show x)) + domainSizeOf (DomainIntE _ x) = bug ("not implemented, domainSizeOf DomainIntE" <+> pretty (show x)) domainSizeOf (DomainInt _ rs) = domainSizeOfRanges rs domainSizeOf DomainEnum{} = failDoc "domainSizeOf: Unknown for given enum." domainSizeOf (DomainTuple ds) = product <$> mapM domainSizeOf ds diff --git a/src/Conjure/Language/Domain.hs b/src/Conjure/Language/Domain.hs index b7bfec0516..5ad0249749 100644 --- a/src/Conjure/Language/Domain.hs +++ b/src/Conjure/Language/Domain.hs @@ -54,7 +54,7 @@ import Data.Data ( toConstr, constrIndex ) data Domain r x = DomainAny Text Type | DomainBool - | DomainIntE x + | DomainIntE IntTag x | DomainInt IntTag [Range x] | DomainEnum Name @@ -127,17 +127,17 @@ typeOfDomain :: Domain r x -> m Type typeOfDomain (DomainAny _ ty) = return ty typeOfDomain DomainBool = return TypeBool -typeOfDomain d@(DomainIntE x) = do +typeOfDomain d@(DomainIntE t x) = do ty <- typeOf x case ty of - TypeInt TagInt -> return () -- pre recoverDomainInt - TypeList (TypeInt TagInt) -> return () - TypeMatrix _ (TypeInt TagInt) -> return () - TypeSet (TypeInt TagInt) -> return () + TypeInt _ -> return () -- pre recoverDomainInt + TypeList (TypeInt _) -> return () + TypeMatrix _ (TypeInt _) -> return () + TypeSet (TypeInt _) -> return () _ -> failDoc $ vcat [ "Expected an integer, but got:" <++> pretty ty - , "In domain:" <+> pretty d - ] - return (TypeInt TagInt) + , "In domain:" <+> pretty d + ] + return (TypeInt t) typeOfDomain d@(DomainInt t rs) = do forM_ rs $ \ r -> forM_ r $ \ x -> do ty <- typeOf x @@ -183,7 +183,7 @@ changeRepr rep = go where go (DomainAny t ty) = DomainAny t ty go DomainBool = DomainBool - go (DomainIntE x) = DomainIntE x + go (DomainIntE t x) = DomainIntE t x go (DomainInt t rs) = DomainInt t rs go (DomainEnum defn rs mp) = DomainEnum defn rs mp go (DomainUnnamed defn s) = DomainUnnamed defn s @@ -898,15 +898,15 @@ instance (Pretty r, Pretty a) => Pretty (Domain r a) where pretty DomainBool = "bool" - pretty (DomainIntE x) = "int" <> prParens (pretty x) + pretty (DomainIntE t x) = "int" <> pretty t <> pretty t <> prParens (pretty x) -- print them like integers even when they are tagged -- pretty (DomainInt (TagEnum nm) _) = pretty nm -- pretty (DomainInt (TagUnnamed nm) _) = pretty nm - pretty (DomainInt _ []) = "int" + pretty (DomainInt t []) = "int" <> pretty t - pretty (DomainInt _ ranges) = "int" <> prettyList prParens "," ranges + pretty (DomainInt t ranges) = "int" <> pretty t <> prettyList prParens "," ranges pretty (DomainEnum name (Just ranges) _) = pretty name <> prettyList prParens "," ranges diff --git a/src/Conjure/Language/Expression/DomainSizeOf.hs b/src/Conjure/Language/Expression/DomainSizeOf.hs index cea198d084..321bb5e385 100644 --- a/src/Conjure/Language/Expression/DomainSizeOf.hs +++ b/src/Conjure/Language/Expression/DomainSizeOf.hs @@ -27,7 +27,7 @@ instance DomainSizeOf Expression Expression where domainSizeOf (DomainInt _ [] ) = failDoc "domainSizeOf infinite integer domain" domainSizeOf (DomainInt _ [r]) = domainSizeOfRange r domainSizeOf (DomainInt _ rs ) = make opSum . fromList <$> mapM domainSizeOfRange rs - domainSizeOf (DomainIntE x) = do + domainSizeOf (DomainIntE _ x) = do let go (Reference _ (Just (Alias y))) = go y go (Comprehension _body gocs) = return $ make opSum $ Comprehension 1 gocs diff --git a/src/Conjure/Language/Instantiate.hs b/src/Conjure/Language/Instantiate.hs index 4263150d8e..605225483d 100644 --- a/src/Conjure/Language/Instantiate.hs +++ b/src/Conjure/Language/Instantiate.hs @@ -237,14 +237,14 @@ instantiateD :: Domain r Expression -> m (Domain r Constant) instantiateD (DomainAny t ty) = return (DomainAny t ty) instantiateD DomainBool = return DomainBool -instantiateD (DomainIntE x) = do +instantiateD (DomainIntE maybe_tag x) = do x' <- instantiateE x let vals = case (x', viewConstantMatrix x', viewConstantSet x') of (ConstantInt{}, _, _) -> [x'] (_, Just (_, xs), _) -> xs (_, _, Just xs) -> xs _ -> [] - return (DomainInt TagInt (map RangeSingle vals)) + return (DomainInt maybe_tag (map RangeSingle vals)) instantiateD (DomainInt t ranges) = DomainInt t <$> mapM instantiateR ranges instantiateD (DomainEnum nm Nothing _) = do st <- gets id diff --git a/src/Conjure/Language/Lenses.hs b/src/Conjure/Language/Lenses.hs index a0674d5bfa..53afe5bd4d 100644 --- a/src/Conjure/Language/Lenses.hs +++ b/src/Conjure/Language/Lenses.hs @@ -1637,7 +1637,7 @@ maxOfDomain :: MonadFailDoc m => Pretty r => Domain r Expression -> m Expression -maxOfDomain (DomainIntE x) = return $ make opMax x +maxOfDomain (DomainIntE _ x) = return $ make opMax x maxOfDomain (DomainInt _ [] ) = failDoc "rule_DomainMinMax.maxOfDomain []" maxOfDomain (DomainInt _ [r]) = maxOfRange r maxOfDomain (DomainInt _ rs ) = do @@ -1657,7 +1657,7 @@ minOfDomain :: MonadFailDoc m => Pretty r => Domain r Expression -> m Expression -minOfDomain (DomainIntE x) = return $ make opMin x +minOfDomain (DomainIntE _ x) = return $ make opMin x minOfDomain (DomainInt _ [] ) = failDoc "rule_DomainMinMax.minOfDomain []" minOfDomain (DomainInt _ [r]) = minOfRange r minOfDomain (DomainInt _ rs ) = do diff --git a/src/Conjure/Language/Type.hs b/src/Conjure/Language/Type.hs index 6fb9b31b53..575e17dcfe 100644 --- a/src/Conjure/Language/Type.hs +++ b/src/Conjure/Language/Type.hs @@ -101,6 +101,12 @@ instance FromJSON IntTag where parseJSON = genericParseJSON jsonOptions reTag :: Data a => IntTag -> a -> a reTag t = transformBi (const t) +instance Pretty IntTag where + pretty TagInt = "" + pretty (TaggedInt t) = ":" <> pretty t + pretty (TagEnum t) = ":" <> pretty t + pretty (TagUnnamed t) = ":" <> pretty t + -- This parameter will decide the mode of the type checker. -- There are two modes: StronglyTyped and RelaxedIntegerTags. diff --git a/src/Conjure/Language/Validator.hs b/src/Conjure/Language/Validator.hs index d3d8f61ebe..327d4c5503 100644 --- a/src/Conjure/Language/Validator.hs +++ b/src/Conjure/Language/Validator.hs @@ -683,9 +683,9 @@ validateDomain dm = setCategoryLimit (CatParameter, "Domain") $ case dm of ParenDomainNode _ dom rt -> do checkSymbols [rt]; validateDomain dom MetaVarDomain lt -> do mv <- validateMetaVar lt; return . Typed TypeAny $ DomainMetaVar mv BoolDomainNode lt -> lt `isA` TtType >> (return . Typed TypeBool) DomainBool - RangedIntDomainNode l1 rs -> do + RangedIntDomainNode l1 rs maybe_tag -> do l1 `isA` TtType - validateRangedInt rs + validateRangedInt maybe_tag rs RangedEnumNode nn ranges -> validateEnumRange nn ranges ShortTupleDomainNode lst -> validateTupleDomain lst TupleDomainNode l1 doms -> do @@ -743,25 +743,25 @@ validateDomain dm = setCategoryLimit (CatParameter, "Domain") $ case dm of validatePartitionDomain attrs dom MissingDomainNode lt -> do raiseError $ lt TokenError lt; return $ fallback "Missing Domain" where - validateRangedInt :: Maybe (ListNode RangeNode) -> ValidatorS TypedDomain - validateRangedInt (Just (ListNode _ (Seq [SeqElem a _]) _)) = do + validateRangedInt :: Maybe ETok -> Maybe (ListNode RangeNode) -> ValidatorS TypedDomain + validateRangedInt maybe_tag (Just (ListNode _ (Seq [SeqElem a _]) _)) = do d <- case a of SingleRangeNode en -> do (t, e) <- typeSplit <$> validateExpression en case t of - TypeInt TagInt -> return $ DomainInt TagInt [RangeSingle e] - TypeMatrix _ _ -> return $ DomainIntE e - TypeList _ -> return $ DomainIntE e - TypeSet _ -> return $ DomainIntE e - _ -> DomainIntE e <$ raiseTypeError (symbolRegion en ComplexTypeError "Set/List of int or Int" t) + TypeInt _ -> return $ DomainInt (mkIntTag maybe_tag) [RangeSingle e] + TypeMatrix _ _ -> return $ DomainIntE (mkIntTag maybe_tag) e + TypeList _ -> return $ DomainIntE (mkIntTag maybe_tag) e + TypeSet _ -> return $ DomainIntE (mkIntTag maybe_tag) e + _ -> DomainIntE (mkIntTag maybe_tag) e <$ raiseTypeError (symbolRegion en ComplexTypeError "Set/List of int or Int" t) _ -> do r <- validateRange tInt a - return $ DomainInt TagInt [r] + return $ DomainInt (mkIntTag maybe_tag) [r] return $ Typed tInt d - validateRangedInt (Just ranges) = do + validateRangedInt maybe_tag (Just ranges) = do ranges' <- catMaybes <$> validateList_ (f2n (validateRange tInt)) ranges - return . Typed tInt $ DomainInt TagInt ranges' - validateRangedInt Nothing = return . Typed tInt $ DomainInt TagInt [] + return . Typed tInt $ DomainInt (mkIntTag maybe_tag) ranges' + validateRangedInt maybe_tag Nothing = return . Typed tInt $ DomainInt (mkIntTag maybe_tag) [] validateEnumRange :: NameNodeS -> Maybe (ListNode RangeNode) -> ValidatorS TypedDomain validateEnumRange name@(NameNodeS n) ranges = do flagSToken n TtEnum @@ -883,6 +883,13 @@ validateDomain dm = setCategoryLimit (CatParameter, "Domain") $ case dm of (t, dom') <- typeSplit <$> validateDomain dom return . Typed (TypePartition t) $ DomainPartition repr attrs' dom' +mkIntTag :: Maybe ETok -> IntTag +mkIntTag Nothing = TagInt +mkIntTag (Just t) = + case lexeme t of + LIdentifier i -> TaggedInt i + _ -> bug $ "mkIntTag" <+> pretty (show t) + validateIndexedByNode :: Maybe IndexedByNode -> ValidatorS () validateIndexedByNode Nothing = return () validateIndexedByNode (Just (IndexedByNode a b)) = [a, b] `are` TtSubKeyword @@ -1476,7 +1483,7 @@ getIndexedType _ _ = return TypeAny validateLiteral :: LiteralNode -> ValidatorS (Typed Expression) validateLiteral litNode = case litNode of - IntLiteral lt -> validateIntLiteral lt >>= \x -> return $ Typed tInt $ Constant x + IntLiteral lt maybe_tag -> validateIntLiteral lt maybe_tag >>= \x -> return $ Typed tInt $ Constant x BoolLiteral lt -> validateBoolLiteral lt >>= \x -> return $ Typed TypeBool $ Constant x MatrixLiteral mln -> validateMatrixLiteral mln TupleLiteralNode (LongTuple lt xs) -> do @@ -1723,12 +1730,17 @@ makeTupleLiteral members = do let eType = TypeTuple (fst memberTypes) return . Typed eType . mkAbstractLiteral . AbsLitTuple $ snd memberTypes -validateIntLiteral :: SToken -> ValidatorS Constant -validateIntLiteral t = do +validateIntLiteral :: SToken -> Maybe ETok -> ValidatorS Constant +validateIntLiteral t maybe_tag = do flagSToken t TtNumber l <- validateSToken t + let tag = case maybe_tag of + Just ta -> case lexeme ta of + LIdentifier ta_i -> TaggedInt ta_i + _ -> TagInt + Nothing -> TagInt case l of - (LIntLiteral x) -> return $ ConstantInt TagInt x + (LIntLiteral x) -> return $ ConstantInt tag x _ -> error "Bad int literal" validateBoolLiteral :: SToken -> ValidatorS Constant diff --git a/src/Conjure/Representations/Primitive.hs b/src/Conjure/Representations/Primitive.hs index fdc2989ca8..a5b306cb92 100644 --- a/src/Conjure/Representations/Primitive.hs +++ b/src/Conjure/Representations/Primitive.hs @@ -15,7 +15,7 @@ primitive = Representation { rCheck = \ _ domain -> return $ case domain of DomainBool -> [DomainBool] - DomainIntE x -> [DomainIntE x] + DomainIntE t x -> [DomainIntE t x] DomainInt t rs -> [DomainInt t rs] _ -> [] , rDownD = const $ return Nothing diff --git a/src/Conjure/Rules/BubbleUp.hs b/src/Conjure/Rules/BubbleUp.hs index 631231585b..483706d361 100644 --- a/src/Conjure/Rules/BubbleUp.hs +++ b/src/Conjure/Rules/BubbleUp.hs @@ -257,6 +257,22 @@ rule_LiftVars = "bubble-up-LiftVars" `namedRule` theRule where ]) (AuxiliaryVars (declsLifted ++ [SuchThat consLifted])) ) + + -- this is to deal with when an AuxiliaryVars expression is in the generator + theRule (Comprehension body gensOrConds) = do + + (gocBefore, (pat, expr, locals), gocAfter) <- matchFirst gensOrConds $ \case + Generator (GenInExpr pat (WithLocals expr (AuxiliaryVars locals))) -> + return (pat, expr, locals) + _ -> na "rule_LiftVars" + + return + ( "Bubbling up auxiliary variables through a comprehension's generator." + , return $ WithLocals + (Comprehension body (gocBefore ++ [Generator (GenInExpr pat expr)] ++ gocAfter)) + (AuxiliaryVars locals) + ) + theRule WithLocals{} = na "rule_LiftVars" theRule Reference{} = na "rule_LiftVars" @@ -284,9 +300,6 @@ rule_LiftVars = "bubble-up-LiftVars" `namedRule` theRule where ) theRule p = do - case p of - Comprehension{} -> na "rule_LiftVars" - _ -> return () let f (WithLocals y (AuxiliaryVars locals@(_:_))) = do tell locals diff --git a/src/Conjure/Rules/DontCare.hs b/src/Conjure/Rules/DontCare.hs index 6f8e4ba85f..3a16b9ccb1 100644 --- a/src/Conjure/Rules/DontCare.hs +++ b/src/Conjure/Rules/DontCare.hs @@ -156,7 +156,7 @@ handleDontCares p = RangeLowerBounded v -> v RangeUpperBounded v -> v RangeBounded v _ -> v - DomainIntE v -> [essence| min(&v) |] + DomainIntE _ v -> [essence| min(&v) |] _ -> raiseBug return $ make opEq x val TypeTuple{} -> do diff --git a/src/Conjure/UI/TypeCheck.hs b/src/Conjure/UI/TypeCheck.hs index 2910c598eb..65a9783456 100644 --- a/src/Conjure/UI/TypeCheck.hs +++ b/src/Conjure/UI/TypeCheck.hs @@ -185,10 +185,10 @@ typeCheckModel model1 = do -- DomainInt [RangeSingle x] from DomainIntE x, if x has type int let domainIntERecover :: forall m . MonadFailDoc m => Domain () Expression -> m (Domain () Expression) - domainIntERecover d@(DomainIntE x) = do + domainIntERecover d@(DomainIntE maybe_tag x) = do ty <- runExceptT $ typeOf x return $ case ty of - Right (TypeInt t) -> DomainInt t [RangeSingle x] + Right (TypeInt _) -> DomainInt maybe_tag [RangeSingle x] _ -> d domainIntERecover d = return d statements4 <- transformBiM domainIntERecover statements3 From 183c2e30a62fec114ba58cc7fee7f27d8d76ac87 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?=C3=96zg=C3=BCr=20Akg=C3=BCn?= Date: Sun, 19 Jan 2025 12:27:08 +0000 Subject: [PATCH 219/229] transform takes a list of permutations as the parameter now --- .../permutation.essence | 2 +- .../permutation.essence | 2 +- .../permutation.essence | 2 +- .../permutation.essence | 2 +- .../permutation.essence | 2 +- .../permutation.essence | 2 +- .../permutation.essence | 2 +- .../permutation.essence | 2 +- .../permutation.essence | 2 +- .../permutation.essence | 2 +- .../permutation.essence | 2 +- .../permutation.essence | 2 +- .../permutation.essence | 2 +- .../permutation.essence | 2 +- .../permutation.essence | 2 +- .../permutation.essence | 2 +- .../permutation.essence | 2 +- .../permutation.essence | 2 +- .../permutation.essence | 2 +- .../permutation.essence | 2 +- .../permutation.essence | 2 +- .../permutation.essence | 2 +- .../permutation.essence | 2 +- .../permutation.essence | 2 +- .../permutation.essence | 2 +- .../permutation.essence | 2 +- .../permutation.essence | 2 +- .../permutation.essence | 2 +- .../permutation.essence | 2 +- .../permutation.essence | 2 +- .../permutation.essence | 2 +- .../permutation.essence | 2 +- .../permutation.essence | 2 +- .../0030_find_permutation/permutation.essence | 2 +- .../permutation.essence | 2 +- .../permutation.essence | 2 +- .../0030_find_permutation/permutation.essence | 2 +- .../0030_find_permutation/permutation.essence | 2 +- .../permutation.essence | 2 +- .../permutation.essence | 2 +- .../0030_find_permutation/permutation.essence | 2 +- .../permutation.essence | 2 +- .../permutation.essence | 2 +- .../0030_find_permutation/permutation.essence | 2 +- .../0030_find_permutation/permutation.essence | 2 +- .../permutation.essence | 2 +- .../permutation.essence | 2 +- .../0030_find_permutation/permutation.essence | 2 +- .../permutation.essence | 2 +- .../permutation.essence | 2 +- .../0030_find_permutation/permutation.essence | 2 +- .../0030_find_permutation/permutation.essence | 2 +- .../permutation.essence | 2 +- .../permutation.essence | 2 +- .../permutation.essence | 2 +- .../permutation.essence | 2 +- .../permutation.essence | 2 +- .../permutation.essence | 2 +- .../permutation.essence | 2 +- .../permutation.essence | 2 +- .../permutation.essence | 2 +- .../permutation.essence | 2 +- .../permutation.essence | 2 +- .../permutation.essence | 2 +- .../permutation.essence | 2 +- .../permutation.essence | 2 +- .../permutation.essence | 2 +- .../permutation.essence | 2 +- .../permutation.essence | 2 +- .../permutation.essence | 2 +- .../permutation.essence | 2 +- .../permutation.essence | 2 +- .../permutation.essence | 2 +- .../permutation.essence | 2 +- .../permutation.essence | 2 +- .../permutation.essence | 2 +- .../permutation.essence | 2 +- .../permutation.essence | 2 +- .../permutation.essence | 2 +- .../permutation.essence | 2 +- .../permutation.essence | 2 +- .../permutation.essence | 2 +- .../permutation.essence | 2 +- .../permutation.essence | 2 +- .../permutation.essence | 2 +- .../permutation.essence | 2 +- .../permutation.essence | 2 +- .../permutation.essence | 2 +- .../permutation.essence | 2 +- .../permutation.essence | 2 +- .../0010_set_of_tuples/permutation.essence | 2 +- .../0010_size_3/permutation.essence | 2 +- .../0020_size_3/permutation.essence | 2 +- .../0001_permute_untagged/permutation.essence | 2 +- .../0002_permute_tagged/permutation.essence | 2 +- .../permutation.essence | 2 +- .../permutation.essence | 2 +- .../permutation.essence | 2 +- .../permutations/permInverse/04/00.essence | 4 ++-- .../permutations/permInverse/05/00.essence | 2 +- .../permutations/permInverse/08/00.essence | 2 +- .../permInverse/13-sets/00.essence | 8 ++++---- .../permutations/permInverse/14/00.essence | 20 +++++++++++++++++++ .../function/matrix/const_01/function.essence | 2 +- .../function/matrix/var_01/function.essence | 2 +- .../partition/const_01/function.essence | 2 +- .../partition/var_01/function.essence | 2 +- .../function/record/const_01/function.essence | 2 +- .../function/record/var_01/function.essence | 2 +- .../function/record/var_02/function.essence | 2 +- .../sequence/const_01/function.essence | 2 +- .../function/sequence/var_01/function.essence | 2 +- .../function/set/const_01/function.essence | 2 +- .../function/set/var_01/function.essence | 2 +- .../function/set/var_02/function.essence | 2 +- .../function/tuple/const_01/function.essence | 2 +- .../function/tuple/var_01/function.essence | 2 +- .../variant/const_01/function.essence | 2 +- .../function/variant/var_01/function.essence | 2 +- .../function/variant/var_02/function.essence | 2 +- .../function/variant/var_03/function.essence | 2 +- .../function/variant/var_04/function.essence | 4 ++-- 122 files changed, 146 insertions(+), 126 deletions(-) create mode 100644 tests/custom/permutations/permInverse/14/00.essence diff --git a/tests/custom/permutations/08_transform_set/enum/0001_given_permutation_letting_set/permutation.essence b/tests/custom/permutations/08_transform_set/enum/0001_given_permutation_letting_set/permutation.essence index e78d30a7ff..3df89ad1ed 100644 --- a/tests/custom/permutations/08_transform_set/enum/0001_given_permutation_letting_set/permutation.essence +++ b/tests/custom/permutations/08_transform_set/enum/0001_given_permutation_letting_set/permutation.essence @@ -6,5 +6,5 @@ given s : set of n find sn : set of n -such that sn = transform(p,s) +such that sn = transform([p],s) diff --git a/tests/custom/permutations/08_transform_set/enum/0002_given_permutation_find_sets/permutation.essence b/tests/custom/permutations/08_transform_set/enum/0002_given_permutation_find_sets/permutation.essence index 13f4aa6091..e899316d46 100644 --- a/tests/custom/permutations/08_transform_set/enum/0002_given_permutation_find_sets/permutation.essence +++ b/tests/custom/permutations/08_transform_set/enum/0002_given_permutation_find_sets/permutation.essence @@ -7,5 +7,5 @@ find s : set of n find sn : set of n -such that sn = transform(p,s) +such that sn = transform([p],s) diff --git a/tests/custom/permutations/08_transform_set/enum/0003_letting_permutation_find_sets/permutation.essence b/tests/custom/permutations/08_transform_set/enum/0003_letting_permutation_find_sets/permutation.essence index 7e6f33026e..12c7eac664 100644 --- a/tests/custom/permutations/08_transform_set/enum/0003_letting_permutation_find_sets/permutation.essence +++ b/tests/custom/permutations/08_transform_set/enum/0003_letting_permutation_find_sets/permutation.essence @@ -7,5 +7,5 @@ find s : set of n find sn : set of n -such that sn = transform(p,s) +such that sn = transform([p],s) diff --git a/tests/custom/permutations/08_transform_set/enum/0004_find_permutation_find_sets/permutation.essence b/tests/custom/permutations/08_transform_set/enum/0004_find_permutation_find_sets/permutation.essence index 0a841a421b..3010186b41 100644 --- a/tests/custom/permutations/08_transform_set/enum/0004_find_permutation_find_sets/permutation.essence +++ b/tests/custom/permutations/08_transform_set/enum/0004_find_permutation_find_sets/permutation.essence @@ -7,5 +7,5 @@ find s : set of n find sn : set of n -such that sn = transform(p,s) /\ (3 = sum([ toInt(l != r) | (l, r) <- p])) +such that sn = transform([p],s) /\ (3 = sum([ toInt(l != r) | (l, r) <- p])) diff --git a/tests/custom/permutations/08_transform_set/enum/0005_find_permutation_given_set_find_set/permutation.essence b/tests/custom/permutations/08_transform_set/enum/0005_find_permutation_given_set_find_set/permutation.essence index 45367de855..2ad5959fd1 100644 --- a/tests/custom/permutations/08_transform_set/enum/0005_find_permutation_given_set_find_set/permutation.essence +++ b/tests/custom/permutations/08_transform_set/enum/0005_find_permutation_given_set_find_set/permutation.essence @@ -7,5 +7,5 @@ given s : set of n find sn : set of n -such that sn = transform(p,s) /\ (3 = sum([ toInt(l != r) | (l, r) <- p])) +such that sn = transform([p],s) /\ (3 = sum([ toInt(l != r) | (l, r) <- p])) diff --git a/tests/custom/permutations/08_transform_set/int/0001_given_permutation_letting_set/permutation.essence b/tests/custom/permutations/08_transform_set/int/0001_given_permutation_letting_set/permutation.essence index c2c60a059c..d391938dd7 100644 --- a/tests/custom/permutations/08_transform_set/int/0001_given_permutation_letting_set/permutation.essence +++ b/tests/custom/permutations/08_transform_set/int/0001_given_permutation_letting_set/permutation.essence @@ -6,5 +6,5 @@ given s : set of int(1..n) find sn : set of int(1..n) -such that sn = transform(p,s) +such that sn = transform([p],s) diff --git a/tests/custom/permutations/08_transform_set/int/0002_given_permutation_find_sets/permutation.essence b/tests/custom/permutations/08_transform_set/int/0002_given_permutation_find_sets/permutation.essence index 6d0865db30..cd53a0fe53 100644 --- a/tests/custom/permutations/08_transform_set/int/0002_given_permutation_find_sets/permutation.essence +++ b/tests/custom/permutations/08_transform_set/int/0002_given_permutation_find_sets/permutation.essence @@ -7,5 +7,5 @@ find s : set of int(1..n) find sn : set of int(1..n) -such that sn = transform(p,s) +such that sn = transform([p],s) diff --git a/tests/custom/permutations/08_transform_set/int/0003_letting_permutation_find_sets/permutation.essence b/tests/custom/permutations/08_transform_set/int/0003_letting_permutation_find_sets/permutation.essence index b3f6f0ef69..bd3167f717 100644 --- a/tests/custom/permutations/08_transform_set/int/0003_letting_permutation_find_sets/permutation.essence +++ b/tests/custom/permutations/08_transform_set/int/0003_letting_permutation_find_sets/permutation.essence @@ -7,5 +7,5 @@ find s : set of int(1..n) find sn : set of int(1..n) -such that sn = transform(p,s) +such that sn = transform([p],s) diff --git a/tests/custom/permutations/08_transform_set/int/0004_find_permutation_find_sets/permutation.essence b/tests/custom/permutations/08_transform_set/int/0004_find_permutation_find_sets/permutation.essence index 67d8a4436e..f8f85119d4 100644 --- a/tests/custom/permutations/08_transform_set/int/0004_find_permutation_find_sets/permutation.essence +++ b/tests/custom/permutations/08_transform_set/int/0004_find_permutation_find_sets/permutation.essence @@ -7,5 +7,5 @@ find s : set of int(1..n) find sn : set of int(1..n) -such that sn = transform(p,s) /\ (3 = sum([ toInt(l != r) | (l, r) <- p])) +such that sn = transform([p],s) /\ (3 = sum([ toInt(l != r) | (l, r) <- p])) diff --git a/tests/custom/permutations/08_transform_set/int/0005_find_permutation_given_set_find_set/permutation.essence b/tests/custom/permutations/08_transform_set/int/0005_find_permutation_given_set_find_set/permutation.essence index 31bb9bbd17..c571d73187 100644 --- a/tests/custom/permutations/08_transform_set/int/0005_find_permutation_given_set_find_set/permutation.essence +++ b/tests/custom/permutations/08_transform_set/int/0005_find_permutation_given_set_find_set/permutation.essence @@ -7,5 +7,5 @@ given s : set of int(1..n) find sn : set of int(1..n) -such that sn = transform(p,s) /\ (3 = sum([ toInt(l != r) | (l, r) <- p])) +such that sn = transform([p],s) /\ (3 = sum([ toInt(l != r) | (l, r) <- p])) diff --git a/tests/custom/permutations/08_transform_set/unnamed/0004_find_permutation_find_sets/permutation.essence b/tests/custom/permutations/08_transform_set/unnamed/0004_find_permutation_find_sets/permutation.essence index 805aba3bb4..f69a4e371f 100644 --- a/tests/custom/permutations/08_transform_set/unnamed/0004_find_permutation_find_sets/permutation.essence +++ b/tests/custom/permutations/08_transform_set/unnamed/0004_find_permutation_find_sets/permutation.essence @@ -7,5 +7,5 @@ find s : set of n find sn : set of n -such that sn = transform(p,s) /\ (3 = sum([ toInt(l != r) | (l, r) <- p])) +such that sn = transform([p],s) /\ (3 = sum([ toInt(l != r) | (l, r) <- p])) diff --git a/tests/custom/permutations/10_transform_tuple/enum/0001_letting_permutation_given_tuple_find_tuple/permutation.essence b/tests/custom/permutations/10_transform_tuple/enum/0001_letting_permutation_given_tuple_find_tuple/permutation.essence index 809e9ce2fc..bbfc5c32c3 100644 --- a/tests/custom/permutations/10_transform_tuple/enum/0001_letting_permutation_given_tuple_find_tuple/permutation.essence +++ b/tests/custom/permutations/10_transform_tuple/enum/0001_letting_permutation_given_tuple_find_tuple/permutation.essence @@ -5,5 +5,5 @@ given t : (n,n,n) find q : (n,n,n) -such that q = transform(p,t) +such that q = transform([p],t) diff --git a/tests/custom/permutations/10_transform_tuple/enum/0002_letting_permutation_given_tuple_find_tuple/permutation.essence b/tests/custom/permutations/10_transform_tuple/enum/0002_letting_permutation_given_tuple_find_tuple/permutation.essence index 5380b03bc9..90d47e99cc 100644 --- a/tests/custom/permutations/10_transform_tuple/enum/0002_letting_permutation_given_tuple_find_tuple/permutation.essence +++ b/tests/custom/permutations/10_transform_tuple/enum/0002_letting_permutation_given_tuple_find_tuple/permutation.essence @@ -5,5 +5,5 @@ given t : (n,n,n,n) find q : (n,n,n,n) -such that q = transform(p,t) +such that q = transform([p],t) diff --git a/tests/custom/permutations/10_transform_tuple/enum/0003_given_permutation_given_tuple_find_tuple/permutation.essence b/tests/custom/permutations/10_transform_tuple/enum/0003_given_permutation_given_tuple_find_tuple/permutation.essence index 7335248377..cc9de9f26a 100644 --- a/tests/custom/permutations/10_transform_tuple/enum/0003_given_permutation_given_tuple_find_tuple/permutation.essence +++ b/tests/custom/permutations/10_transform_tuple/enum/0003_given_permutation_given_tuple_find_tuple/permutation.essence @@ -6,5 +6,5 @@ find q : (n,n,n) -such that q = transform(p, t) +such that q = transform([p], t) diff --git a/tests/custom/permutations/10_transform_tuple/enum/0004_given_permutation_find_tuple_find_tuple/permutation.essence b/tests/custom/permutations/10_transform_tuple/enum/0004_given_permutation_find_tuple_find_tuple/permutation.essence index 9b77826d33..ca9d068d86 100644 --- a/tests/custom/permutations/10_transform_tuple/enum/0004_given_permutation_find_tuple_find_tuple/permutation.essence +++ b/tests/custom/permutations/10_transform_tuple/enum/0004_given_permutation_find_tuple_find_tuple/permutation.essence @@ -6,5 +6,5 @@ find q : (n,n,n) -such that q = transform(p, t) +such that q = transform([p], t) diff --git a/tests/custom/permutations/10_transform_tuple/enum/0005_find_permutation_find_tuple_find_tuple/permutation.essence b/tests/custom/permutations/10_transform_tuple/enum/0005_find_permutation_find_tuple_find_tuple/permutation.essence index 571ca969ed..d4d07a390b 100644 --- a/tests/custom/permutations/10_transform_tuple/enum/0005_find_permutation_find_tuple_find_tuple/permutation.essence +++ b/tests/custom/permutations/10_transform_tuple/enum/0005_find_permutation_find_tuple_find_tuple/permutation.essence @@ -5,5 +5,5 @@ find t : (n,n,n) find q : (n,n,n) -such that (q = transform(p, t)) /\ (4 = sum([toInt(l != r) | (l,r) <- p])) +such that (q = transform([p], t)) /\ (4 = sum([toInt(l != r) | (l,r) <- p])) diff --git a/tests/custom/permutations/10_transform_tuple/int/0001_letting_permutation_given_tuple_find_tuple/permutation.essence b/tests/custom/permutations/10_transform_tuple/int/0001_letting_permutation_given_tuple_find_tuple/permutation.essence index 79c73e43c8..017c673327 100644 --- a/tests/custom/permutations/10_transform_tuple/int/0001_letting_permutation_given_tuple_find_tuple/permutation.essence +++ b/tests/custom/permutations/10_transform_tuple/int/0001_letting_permutation_given_tuple_find_tuple/permutation.essence @@ -4,5 +4,5 @@ letting p be permutation((1,3,4)) given t : (int(1..5), int(1..5), int(1..5)) find q : (int(1..5), int(1..5), int(1..5)) -such that q = transform(p,t) +such that q = transform([p],t) diff --git a/tests/custom/permutations/10_transform_tuple/int/0002_letting_permutation_given_tuple_find_tuple/permutation.essence b/tests/custom/permutations/10_transform_tuple/int/0002_letting_permutation_given_tuple_find_tuple/permutation.essence index 0258b0fed0..c624210038 100644 --- a/tests/custom/permutations/10_transform_tuple/int/0002_letting_permutation_given_tuple_find_tuple/permutation.essence +++ b/tests/custom/permutations/10_transform_tuple/int/0002_letting_permutation_given_tuple_find_tuple/permutation.essence @@ -4,5 +4,5 @@ letting p be permutation((1,3,4)) given t : (int(1..5), int(1..5), int(1..5), int(1..5)) find q : (int(1..5), int(1..5), int(1..5), int(1..5)) -such that q = transform(p,t) +such that q = transform([p],t) diff --git a/tests/custom/permutations/10_transform_tuple/int/0003_given_permutation_given_tuple_find_tuple/permutation.essence b/tests/custom/permutations/10_transform_tuple/int/0003_given_permutation_given_tuple_find_tuple/permutation.essence index 64c3e549c8..480453ee48 100644 --- a/tests/custom/permutations/10_transform_tuple/int/0003_given_permutation_given_tuple_find_tuple/permutation.essence +++ b/tests/custom/permutations/10_transform_tuple/int/0003_given_permutation_given_tuple_find_tuple/permutation.essence @@ -6,5 +6,5 @@ find q : (int(1..n), int(1..n), int(1..n)) -such that q = transform(p, t) +such that q = transform([p], t) diff --git a/tests/custom/permutations/10_transform_tuple/int/0004_given_permutation_find_tuple_find_tuple/permutation.essence b/tests/custom/permutations/10_transform_tuple/int/0004_given_permutation_find_tuple_find_tuple/permutation.essence index 233e718845..bdeb01504b 100644 --- a/tests/custom/permutations/10_transform_tuple/int/0004_given_permutation_find_tuple_find_tuple/permutation.essence +++ b/tests/custom/permutations/10_transform_tuple/int/0004_given_permutation_find_tuple_find_tuple/permutation.essence @@ -6,5 +6,5 @@ find q : (int(1..n), int(1..n), int(1..n)) -such that q = transform(p, t) +such that q = transform([p], t) diff --git a/tests/custom/permutations/10_transform_tuple/int/0005_find_permutation_find_tuple_find_tuple/permutation.essence b/tests/custom/permutations/10_transform_tuple/int/0005_find_permutation_find_tuple_find_tuple/permutation.essence index 8550cdb22e..b07231adb2 100644 --- a/tests/custom/permutations/10_transform_tuple/int/0005_find_permutation_find_tuple_find_tuple/permutation.essence +++ b/tests/custom/permutations/10_transform_tuple/int/0005_find_permutation_find_tuple_find_tuple/permutation.essence @@ -6,5 +6,5 @@ find q : (int(1..n), int(1..n), int(1..n)) -such that (q = transform(p, t)) /\ (4 = sum([toInt(l != r) | (l,r) <- p])) +such that (q = transform([p], t)) /\ (4 = sum([toInt(l != r) | (l,r) <- p])) diff --git a/tests/custom/permutations/10_transform_tuple/unnamed/0005_find_permutation_find_tuple_find_tuple/permutation.essence b/tests/custom/permutations/10_transform_tuple/unnamed/0005_find_permutation_find_tuple_find_tuple/permutation.essence index c5a863cb53..e1410add92 100644 --- a/tests/custom/permutations/10_transform_tuple/unnamed/0005_find_permutation_find_tuple_find_tuple/permutation.essence +++ b/tests/custom/permutations/10_transform_tuple/unnamed/0005_find_permutation_find_tuple_find_tuple/permutation.essence @@ -5,5 +5,5 @@ find t : (n,n,n) find q : (n,n,n) -such that (q = transform(p, t)) /\ (4 = sum([toInt(l != r) | (l,r) <- p])) +such that (q = transform([p], t)) /\ (4 = sum([toInt(l != r) | (l,r) <- p])) diff --git a/tests/custom/permutations/11_transform_relation/enum/0010_given_permutation_letting_relation/permutation.essence b/tests/custom/permutations/11_transform_relation/enum/0010_given_permutation_letting_relation/permutation.essence index 6cd61c8ad9..2ed72d5154 100644 --- a/tests/custom/permutations/11_transform_relation/enum/0010_given_permutation_letting_relation/permutation.essence +++ b/tests/custom/permutations/11_transform_relation/enum/0010_given_permutation_letting_relation/permutation.essence @@ -7,5 +7,5 @@ find sn : relation of (n * n) -such that sn = transform(p,s) +such that sn = transform([p],s) diff --git a/tests/custom/permutations/11_transform_relation/enum/0020_letting_permutation_letting_relation/permutation.essence b/tests/custom/permutations/11_transform_relation/enum/0020_letting_permutation_letting_relation/permutation.essence index 3a4dfe80e1..a988ca438f 100644 --- a/tests/custom/permutations/11_transform_relation/enum/0020_letting_permutation_letting_relation/permutation.essence +++ b/tests/custom/permutations/11_transform_relation/enum/0020_letting_permutation_letting_relation/permutation.essence @@ -7,5 +7,5 @@ find sn : relation of (n * n) -such that sn = transform(p,s) +such that sn = transform([p],s) diff --git a/tests/custom/permutations/11_transform_relation/enum/0030_find_permutation_given_relation/permutation.essence b/tests/custom/permutations/11_transform_relation/enum/0030_find_permutation_given_relation/permutation.essence index c6196d1228..efb3a6cca7 100644 --- a/tests/custom/permutations/11_transform_relation/enum/0030_find_permutation_given_relation/permutation.essence +++ b/tests/custom/permutations/11_transform_relation/enum/0030_find_permutation_given_relation/permutation.essence @@ -7,4 +7,4 @@ find sn : relation of (n * n) -such that sn = transform(p,s) /\ (3 = sum([ toInt(l!=r) | (l,r) <- p])) +such that sn = transform([p],s) /\ (3 = sum([ toInt(l!=r) | (l,r) <- p])) diff --git a/tests/custom/permutations/11_transform_relation/enum/0040_find_permutation_find_relation/permutation.essence b/tests/custom/permutations/11_transform_relation/enum/0040_find_permutation_find_relation/permutation.essence index be7a9f3968..08dbc1ea1d 100644 --- a/tests/custom/permutations/11_transform_relation/enum/0040_find_permutation_find_relation/permutation.essence +++ b/tests/custom/permutations/11_transform_relation/enum/0040_find_permutation_find_relation/permutation.essence @@ -7,4 +7,4 @@ find sn : relation of (n * n) -such that sn = transform(p,s) /\ (3 = sum([ toInt(l!=r) | (l,r) <- p]) /\ |s| = 4) +such that sn = transform([p],s) /\ (3 = sum([ toInt(l!=r) | (l,r) <- p]) /\ |s| = 4) diff --git a/tests/custom/permutations/11_transform_relation/int/0010_given_permutation_letting_relation/permutation.essence b/tests/custom/permutations/11_transform_relation/int/0010_given_permutation_letting_relation/permutation.essence index c350aea3ea..83f830a970 100644 --- a/tests/custom/permutations/11_transform_relation/int/0010_given_permutation_letting_relation/permutation.essence +++ b/tests/custom/permutations/11_transform_relation/int/0010_given_permutation_letting_relation/permutation.essence @@ -7,5 +7,5 @@ find sn : relation of (int(1..n) * int(1..n)) -such that sn = transform(p,s) +such that sn = transform([p],s) diff --git a/tests/custom/permutations/11_transform_relation/int/0020_letting_permutation_letting_relation/permutation.essence b/tests/custom/permutations/11_transform_relation/int/0020_letting_permutation_letting_relation/permutation.essence index df44f769ee..9dcc74fce6 100644 --- a/tests/custom/permutations/11_transform_relation/int/0020_letting_permutation_letting_relation/permutation.essence +++ b/tests/custom/permutations/11_transform_relation/int/0020_letting_permutation_letting_relation/permutation.essence @@ -7,5 +7,5 @@ find sn : relation of (int(1..n) * int(1..n)) -such that sn = transform(p,s) +such that sn = transform([p],s) diff --git a/tests/custom/permutations/11_transform_relation/int/0030_find_permutation_given_relation/permutation.essence b/tests/custom/permutations/11_transform_relation/int/0030_find_permutation_given_relation/permutation.essence index 1e99ec59d5..d22581cbd3 100644 --- a/tests/custom/permutations/11_transform_relation/int/0030_find_permutation_given_relation/permutation.essence +++ b/tests/custom/permutations/11_transform_relation/int/0030_find_permutation_given_relation/permutation.essence @@ -7,4 +7,4 @@ find sn : relation of (int(1..n) * int(1..n)) -such that sn = transform(p,s) /\ (3 = sum([ toInt(l!=r) | (l,r) <- p])) +such that sn = transform([p],s) /\ (3 = sum([ toInt(l!=r) | (l,r) <- p])) diff --git a/tests/custom/permutations/11_transform_relation/int/0040_find_permutation_find_relation/permutation.essence b/tests/custom/permutations/11_transform_relation/int/0040_find_permutation_find_relation/permutation.essence index abbf9c0ba4..ffcac490ef 100644 --- a/tests/custom/permutations/11_transform_relation/int/0040_find_permutation_find_relation/permutation.essence +++ b/tests/custom/permutations/11_transform_relation/int/0040_find_permutation_find_relation/permutation.essence @@ -7,4 +7,4 @@ find sn : relation of (int(1..n) * int(1..n)) -such that sn = transform(p,s) /\ (3 = sum([ toInt(l!=r) | (l,r) <- p]) /\ |s| = 4) +such that sn = transform([p],s) /\ (3 = sum([ toInt(l!=r) | (l,r) <- p]) /\ |s| = 4) diff --git a/tests/custom/permutations/11_transform_relation/unnamed/0040_find_permutation_find_relation/permutation.essence b/tests/custom/permutations/11_transform_relation/unnamed/0040_find_permutation_find_relation/permutation.essence index 71c3e75925..a590afc103 100644 --- a/tests/custom/permutations/11_transform_relation/unnamed/0040_find_permutation_find_relation/permutation.essence +++ b/tests/custom/permutations/11_transform_relation/unnamed/0040_find_permutation_find_relation/permutation.essence @@ -7,4 +7,4 @@ find sn : relation of (n * n) -such that sn = transform(p,s) /\ (3 = sum([ toInt(l!=r) | (l,r) <- p]) /\ |s| = 4) +such that sn = transform([p],s) /\ (3 = sum([ toInt(l!=r) | (l,r) <- p]) /\ |s| = 4) diff --git a/tests/custom/permutations/12_transform_list/enum/0010_given_permutation/permutation.essence b/tests/custom/permutations/12_transform_list/enum/0010_given_permutation/permutation.essence index a6bcc3b66c..82d106476e 100644 --- a/tests/custom/permutations/12_transform_list/enum/0010_given_permutation/permutation.essence +++ b/tests/custom/permutations/12_transform_list/enum/0010_given_permutation/permutation.essence @@ -4,5 +4,5 @@ given p : permutation of n find b : n -such that and([ i = b | i <- transform(p,[E4,E4,E4,E4])]) +such that and([ i = b | i <- transform([p],[E4,E4,E4,E4])]) diff --git a/tests/custom/permutations/12_transform_list/enum/0020_letting_permutation/permutation.essence b/tests/custom/permutations/12_transform_list/enum/0020_letting_permutation/permutation.essence index f71faf62a6..7548c0d129 100644 --- a/tests/custom/permutations/12_transform_list/enum/0020_letting_permutation/permutation.essence +++ b/tests/custom/permutations/12_transform_list/enum/0020_letting_permutation/permutation.essence @@ -3,5 +3,5 @@ letting n be new type enum {E1,E2,E3,E4} letting p be permutation((E1,E3,E4)) find b : n -such that and([i = b | i <- transform(p, [E4,E4,E4,E4])]) +such that and([i = b | i <- transform([p], [E4,E4,E4,E4])]) diff --git a/tests/custom/permutations/12_transform_list/enum/0030_find_permutation/permutation.essence b/tests/custom/permutations/12_transform_list/enum/0030_find_permutation/permutation.essence index a9099fa425..5d67331a9c 100644 --- a/tests/custom/permutations/12_transform_list/enum/0030_find_permutation/permutation.essence +++ b/tests/custom/permutations/12_transform_list/enum/0030_find_permutation/permutation.essence @@ -3,5 +3,5 @@ letting n be new type enum {E1,E2,E3,E4} find p : permutation of n find b : n -such that and([i = b | i <- transform(p, [E4,E4,E4,E4])]) /\ b != E4 +such that and([i = b | i <- transform([p], [E4,E4,E4,E4])]) /\ b != E4 diff --git a/tests/custom/permutations/12_transform_list/int/0010_given_permutation/permutation.essence b/tests/custom/permutations/12_transform_list/int/0010_given_permutation/permutation.essence index 874f8ff957..2b2cc2e7b7 100644 --- a/tests/custom/permutations/12_transform_list/int/0010_given_permutation/permutation.essence +++ b/tests/custom/permutations/12_transform_list/int/0010_given_permutation/permutation.essence @@ -4,5 +4,5 @@ given p : permutation of int(1..n) find b : int(1..50) -such that b = sum([ i | i <- transform(p,[4,4,4,4])]) +such that b = sum([ i | i <- transform([p],[4,4,4,4])]) diff --git a/tests/custom/permutations/12_transform_list/int/0020_letting_permutation/permutation.essence b/tests/custom/permutations/12_transform_list/int/0020_letting_permutation/permutation.essence index c0c056a3f1..e9b2f044c2 100644 --- a/tests/custom/permutations/12_transform_list/int/0020_letting_permutation/permutation.essence +++ b/tests/custom/permutations/12_transform_list/int/0020_letting_permutation/permutation.essence @@ -3,5 +3,5 @@ letting n be 4 letting p be permutation((1,3,4)) find b : int(1..50) -such that b = sum([i | i <- transform(p, [4,4,4,4])]) +such that b = sum([i | i <- transform([p], [4,4,4,4])]) diff --git a/tests/custom/permutations/12_transform_list/int/0030_find_permutation/permutation.essence b/tests/custom/permutations/12_transform_list/int/0030_find_permutation/permutation.essence index 4a2844917b..e6482c86a8 100644 --- a/tests/custom/permutations/12_transform_list/int/0030_find_permutation/permutation.essence +++ b/tests/custom/permutations/12_transform_list/int/0030_find_permutation/permutation.essence @@ -2,5 +2,5 @@ letting n be 4 find p : permutation of int(1..4) -such that 4 = sum([i | i <- transform(p, [4,4,4,4])]) +such that 4 = sum([i | i <- transform([p], [4,4,4,4])]) diff --git a/tests/custom/permutations/12_transform_list/unnamed/0030_find_permutation/permutation.essence b/tests/custom/permutations/12_transform_list/unnamed/0030_find_permutation/permutation.essence index 4d303d007d..ed90b1877c 100644 --- a/tests/custom/permutations/12_transform_list/unnamed/0030_find_permutation/permutation.essence +++ b/tests/custom/permutations/12_transform_list/unnamed/0030_find_permutation/permutation.essence @@ -4,5 +4,5 @@ find p : permutation of n find b : n find c : n -such that and([i = b | i <- transform(p, [c,c,c,c])]) /\ b != c +such that and([i = b | i <- transform([p], [c,c,c,c])]) /\ b != c diff --git a/tests/custom/permutations/13_transform_function/enum/0010_given_permutation/permutation.essence b/tests/custom/permutations/13_transform_function/enum/0010_given_permutation/permutation.essence index 55f76ef90a..e6282aeb70 100644 --- a/tests/custom/permutations/13_transform_function/enum/0010_given_permutation/permutation.essence +++ b/tests/custom/permutations/13_transform_function/enum/0010_given_permutation/permutation.essence @@ -4,5 +4,5 @@ given p : permutation of n letting f be function(E1-->E2, E2-->E3) find g : function n --> n -such that g = transform(p,f) +such that g = transform([p],f) diff --git a/tests/custom/permutations/13_transform_function/enum/0020_letting_permutation/permutation.essence b/tests/custom/permutations/13_transform_function/enum/0020_letting_permutation/permutation.essence index 014a56fd47..e3754adf6c 100644 --- a/tests/custom/permutations/13_transform_function/enum/0020_letting_permutation/permutation.essence +++ b/tests/custom/permutations/13_transform_function/enum/0020_letting_permutation/permutation.essence @@ -4,5 +4,5 @@ letting p be permutation((E2,E3)) letting f be function(E1-->E2, E2-->E4) find g : function n --> n -such that g = transform(p,f) +such that g = transform([p],f) diff --git a/tests/custom/permutations/13_transform_function/enum/0030_find_permutation/permutation.essence b/tests/custom/permutations/13_transform_function/enum/0030_find_permutation/permutation.essence index 503b4b66d2..4e455104f3 100644 --- a/tests/custom/permutations/13_transform_function/enum/0030_find_permutation/permutation.essence +++ b/tests/custom/permutations/13_transform_function/enum/0030_find_permutation/permutation.essence @@ -4,5 +4,5 @@ find p : permutation of n letting f be function(E1-->E2,E2-->E4) letting g be function(E1-->E3,E3-->E4) -such that g = transform(p,f) +such that g = transform([p],f) diff --git a/tests/custom/permutations/13_transform_function/int/0010_given_permutation/permutation.essence b/tests/custom/permutations/13_transform_function/int/0010_given_permutation/permutation.essence index 4574cdf6b9..ad79564792 100644 --- a/tests/custom/permutations/13_transform_function/int/0010_given_permutation/permutation.essence +++ b/tests/custom/permutations/13_transform_function/int/0010_given_permutation/permutation.essence @@ -4,5 +4,5 @@ given p : permutation of int(1..n) letting f be function(1-->2, 2-->3) find g : function int(1..4) --> int(1..4) -such that g = transform(p,f) +such that g = transform([p],f) diff --git a/tests/custom/permutations/13_transform_function/int/0020_letting_permutation/permutation.essence b/tests/custom/permutations/13_transform_function/int/0020_letting_permutation/permutation.essence index c67d3ada08..260d25ac1e 100644 --- a/tests/custom/permutations/13_transform_function/int/0020_letting_permutation/permutation.essence +++ b/tests/custom/permutations/13_transform_function/int/0020_letting_permutation/permutation.essence @@ -4,5 +4,5 @@ letting p be permutation((2,3)) letting f be function(1-->2, 2-->4) find g : function int(1..4) --> int(1..4) -such that g = transform(p,f) +such that g = transform([p],f) diff --git a/tests/custom/permutations/13_transform_function/int/0030_find_permutation/permutation.essence b/tests/custom/permutations/13_transform_function/int/0030_find_permutation/permutation.essence index 6508464448..c8b37643d6 100644 --- a/tests/custom/permutations/13_transform_function/int/0030_find_permutation/permutation.essence +++ b/tests/custom/permutations/13_transform_function/int/0030_find_permutation/permutation.essence @@ -4,5 +4,5 @@ find p : permutation of int(1..4) letting f be function(1-->2,2-->4) letting g be function(1-->3,3-->4) -such that g = transform(p,f) +such that g = transform([p],f) diff --git a/tests/custom/permutations/13_transform_function/unnamed/0030_find_permutation/permutation.essence b/tests/custom/permutations/13_transform_function/unnamed/0030_find_permutation/permutation.essence index a0c212ecdf..ded090351a 100644 --- a/tests/custom/permutations/13_transform_function/unnamed/0030_find_permutation/permutation.essence +++ b/tests/custom/permutations/13_transform_function/unnamed/0030_find_permutation/permutation.essence @@ -5,5 +5,5 @@ find f : function n --> n find g : function n --> n -such that g = transform(p,f) /\ |p| > 0 /\ |f| > 0 +such that g = transform([p],f) /\ |p| > 0 /\ |f| > 0 diff --git a/tests/custom/permutations/14_transform_sequence/enum/0010_given_permutation/permutation.essence b/tests/custom/permutations/14_transform_sequence/enum/0010_given_permutation/permutation.essence index 5d7dd79626..4890b1df39 100644 --- a/tests/custom/permutations/14_transform_sequence/enum/0010_given_permutation/permutation.essence +++ b/tests/custom/permutations/14_transform_sequence/enum/0010_given_permutation/permutation.essence @@ -4,5 +4,5 @@ given p : permutation of n letting f be sequence(E1,E2,E3,E4) find g : sequence (size 4) of n -such that g = transform(p,f) +such that g = transform([p],f) diff --git a/tests/custom/permutations/14_transform_sequence/enum/0020_letting_permutation/permutation.essence b/tests/custom/permutations/14_transform_sequence/enum/0020_letting_permutation/permutation.essence index 46eaa3aa2b..e8e0a503c0 100644 --- a/tests/custom/permutations/14_transform_sequence/enum/0020_letting_permutation/permutation.essence +++ b/tests/custom/permutations/14_transform_sequence/enum/0020_letting_permutation/permutation.essence @@ -4,5 +4,5 @@ letting p be permutation((E2,E3)) letting f be sequence(E1,E2,E3,E4) find g : sequence (size 4) of n -such that g = transform(p,f) +such that g = transform([p],f) diff --git a/tests/custom/permutations/14_transform_sequence/enum/0030_find_permutation/permutation.essence b/tests/custom/permutations/14_transform_sequence/enum/0030_find_permutation/permutation.essence index 5fb8a185b4..122d2bd0c3 100644 --- a/tests/custom/permutations/14_transform_sequence/enum/0030_find_permutation/permutation.essence +++ b/tests/custom/permutations/14_transform_sequence/enum/0030_find_permutation/permutation.essence @@ -4,5 +4,5 @@ find p : permutation of n letting f be sequence(E1,E2,E3,E4) letting g be sequence (E4,E3,E2,E1) -such that g = transform(p,f) +such that g = transform([p],f) diff --git a/tests/custom/permutations/14_transform_sequence/int/0010_given_permutation/permutation.essence b/tests/custom/permutations/14_transform_sequence/int/0010_given_permutation/permutation.essence index 77bdd73ab4..d1100e0ca3 100644 --- a/tests/custom/permutations/14_transform_sequence/int/0010_given_permutation/permutation.essence +++ b/tests/custom/permutations/14_transform_sequence/int/0010_given_permutation/permutation.essence @@ -4,5 +4,5 @@ given p : permutation of int(1..n) letting f be sequence(1,2,3,4) find g : sequence (size 4) of int(1..4) -such that g = transform(p,f) +such that g = transform([p],f) diff --git a/tests/custom/permutations/14_transform_sequence/int/0020_letting_permutation/permutation.essence b/tests/custom/permutations/14_transform_sequence/int/0020_letting_permutation/permutation.essence index 7d607fad85..34354f8b59 100644 --- a/tests/custom/permutations/14_transform_sequence/int/0020_letting_permutation/permutation.essence +++ b/tests/custom/permutations/14_transform_sequence/int/0020_letting_permutation/permutation.essence @@ -4,5 +4,5 @@ letting p be permutation((2,3)) letting f be sequence(1,2,3,4) find g : sequence (size 4) of int(1..4) -such that g = transform(p,f) +such that g = transform([p],f) diff --git a/tests/custom/permutations/14_transform_sequence/int/0030_find_permutation/permutation.essence b/tests/custom/permutations/14_transform_sequence/int/0030_find_permutation/permutation.essence index 150ba14c00..b2073fd09e 100644 --- a/tests/custom/permutations/14_transform_sequence/int/0030_find_permutation/permutation.essence +++ b/tests/custom/permutations/14_transform_sequence/int/0030_find_permutation/permutation.essence @@ -4,5 +4,5 @@ find p : permutation of int(1..4) letting f be sequence(1,2,3,4) letting g be sequence (4,3,2,1) -such that g = transform(p,f) +such that g = transform([p],f) diff --git a/tests/custom/permutations/14_transform_sequence/unnamed/0030_find_permutation/permutation.essence b/tests/custom/permutations/14_transform_sequence/unnamed/0030_find_permutation/permutation.essence index b2a953d10b..270a442b83 100644 --- a/tests/custom/permutations/14_transform_sequence/unnamed/0030_find_permutation/permutation.essence +++ b/tests/custom/permutations/14_transform_sequence/unnamed/0030_find_permutation/permutation.essence @@ -4,5 +4,5 @@ find p : permutation of n find f : sequence (size 4) of n find g : sequence (size 4) of n -such that g = transform(p,f) /\ f != g +such that g = transform([p],f) /\ f != g diff --git a/tests/custom/permutations/15_transform_mset/enum/0010_given_permutation_letting_mset/permutation.essence b/tests/custom/permutations/15_transform_mset/enum/0010_given_permutation_letting_mset/permutation.essence index 101f26d76e..fbb7272262 100644 --- a/tests/custom/permutations/15_transform_mset/enum/0010_given_permutation_letting_mset/permutation.essence +++ b/tests/custom/permutations/15_transform_mset/enum/0010_given_permutation_letting_mset/permutation.essence @@ -6,5 +6,5 @@ given s : mset (size 3) of n find sn : mset (size 3) of n -such that sn = transform(p,s) +such that sn = transform([p],s) diff --git a/tests/custom/permutations/15_transform_mset/enum/0020_given_permutation_find_msets/permutation.essence b/tests/custom/permutations/15_transform_mset/enum/0020_given_permutation_find_msets/permutation.essence index 84d66091b6..a5b8e2a14e 100644 --- a/tests/custom/permutations/15_transform_mset/enum/0020_given_permutation_find_msets/permutation.essence +++ b/tests/custom/permutations/15_transform_mset/enum/0020_given_permutation_find_msets/permutation.essence @@ -7,5 +7,5 @@ find s : mset (maxSize 3) of n find sn : mset (maxSize 3) of n -such that sn = transform(p,s) +such that sn = transform([p],s) diff --git a/tests/custom/permutations/15_transform_mset/enum/0030_letting_permutation_find_msets/permutation.essence b/tests/custom/permutations/15_transform_mset/enum/0030_letting_permutation_find_msets/permutation.essence index 74d18edb30..5ff6159ec5 100644 --- a/tests/custom/permutations/15_transform_mset/enum/0030_letting_permutation_find_msets/permutation.essence +++ b/tests/custom/permutations/15_transform_mset/enum/0030_letting_permutation_find_msets/permutation.essence @@ -7,5 +7,5 @@ find s : mset (maxSize 3) of n find sn : mset (maxSize 3) of n -such that sn = transform(p,s) +such that sn = transform([p],s) diff --git a/tests/custom/permutations/15_transform_mset/enum/0040_find_permutation_find_msets/permutation.essence b/tests/custom/permutations/15_transform_mset/enum/0040_find_permutation_find_msets/permutation.essence index 1007c7c4c6..c39c96fcfc 100644 --- a/tests/custom/permutations/15_transform_mset/enum/0040_find_permutation_find_msets/permutation.essence +++ b/tests/custom/permutations/15_transform_mset/enum/0040_find_permutation_find_msets/permutation.essence @@ -7,5 +7,5 @@ find s : mset (size 6) of n find sn : mset (size 6) of n -such that sn = transform(p,s) /\ (3 = sum([ toInt(l != r) | (l, r) <- p])) +such that sn = transform([p],s) /\ (3 = sum([ toInt(l != r) | (l, r) <- p])) diff --git a/tests/custom/permutations/15_transform_mset/enum/0050_find_permutation_given_mset_find_mset/permutation.essence b/tests/custom/permutations/15_transform_mset/enum/0050_find_permutation_given_mset_find_mset/permutation.essence index 9c72ef2e9e..56c89dcee5 100644 --- a/tests/custom/permutations/15_transform_mset/enum/0050_find_permutation_given_mset_find_mset/permutation.essence +++ b/tests/custom/permutations/15_transform_mset/enum/0050_find_permutation_given_mset_find_mset/permutation.essence @@ -7,5 +7,5 @@ given s : mset of n find sn : mset (maxSize 5) of n -such that sn = transform(p,s) /\ (3 = sum([ toInt(l != r) | (l, r) <- p])) +such that sn = transform([p],s) /\ (3 = sum([ toInt(l != r) | (l, r) <- p])) diff --git a/tests/custom/permutations/15_transform_mset/int/0010_given_permutation_letting_mset/permutation.essence b/tests/custom/permutations/15_transform_mset/int/0010_given_permutation_letting_mset/permutation.essence index 436e7f366a..4a7a205060 100644 --- a/tests/custom/permutations/15_transform_mset/int/0010_given_permutation_letting_mset/permutation.essence +++ b/tests/custom/permutations/15_transform_mset/int/0010_given_permutation_letting_mset/permutation.essence @@ -6,5 +6,5 @@ given s : mset (size 4) of int(1..n) find sn : mset (size 4) of int(1..n) -such that sn = transform(p,s) +such that sn = transform([p],s) diff --git a/tests/custom/permutations/15_transform_mset/int/0020_given_permutation_find_msets/permutation.essence b/tests/custom/permutations/15_transform_mset/int/0020_given_permutation_find_msets/permutation.essence index b397857ddb..f3690a9504 100644 --- a/tests/custom/permutations/15_transform_mset/int/0020_given_permutation_find_msets/permutation.essence +++ b/tests/custom/permutations/15_transform_mset/int/0020_given_permutation_find_msets/permutation.essence @@ -7,5 +7,5 @@ find s : mset (size 4) of int(1..n) find sn : mset (size 4) of int(1..n) -such that sn = transform(p,s) +such that sn = transform([p],s) diff --git a/tests/custom/permutations/15_transform_mset/int/0030_letting_permutation_find_msets/permutation.essence b/tests/custom/permutations/15_transform_mset/int/0030_letting_permutation_find_msets/permutation.essence index 83b264ba00..03bbd7bc5e 100644 --- a/tests/custom/permutations/15_transform_mset/int/0030_letting_permutation_find_msets/permutation.essence +++ b/tests/custom/permutations/15_transform_mset/int/0030_letting_permutation_find_msets/permutation.essence @@ -7,5 +7,5 @@ find s : mset (size 4) of int(1..n) find sn : mset (size 4) of int(1..n) -such that sn = transform(p,s) +such that sn = transform([p],s) diff --git a/tests/custom/permutations/15_transform_mset/int/0040_find_permutation_find_msets/permutation.essence b/tests/custom/permutations/15_transform_mset/int/0040_find_permutation_find_msets/permutation.essence index 65384aebb1..1eb516925e 100644 --- a/tests/custom/permutations/15_transform_mset/int/0040_find_permutation_find_msets/permutation.essence +++ b/tests/custom/permutations/15_transform_mset/int/0040_find_permutation_find_msets/permutation.essence @@ -7,5 +7,5 @@ find s : mset (size 4) of int(1..n) find sn : mset (size 4) of int(1..n) -such that sn = transform(p,s) /\ 3 = |p| +such that sn = transform([p],s) /\ 3 = |p| diff --git a/tests/custom/permutations/15_transform_mset/int/0050_find_permutation_given_mset_find_mset/permutation.essence b/tests/custom/permutations/15_transform_mset/int/0050_find_permutation_given_mset_find_mset/permutation.essence index ce6faf384c..bf28799f41 100644 --- a/tests/custom/permutations/15_transform_mset/int/0050_find_permutation_given_mset_find_mset/permutation.essence +++ b/tests/custom/permutations/15_transform_mset/int/0050_find_permutation_given_mset_find_mset/permutation.essence @@ -7,5 +7,5 @@ given s : mset (size 3) of int(1..n) find sn : mset (size 3) of int(1..n) -such that sn = transform(p,s) /\ (3 = sum([ toInt(l != r) | (l, r) <- p])) +such that sn = transform([p],s) /\ (3 = sum([ toInt(l != r) | (l, r) <- p])) diff --git a/tests/custom/permutations/15_transform_mset/unnamed/0004_find_permutation_find_msets/permutation.essence b/tests/custom/permutations/15_transform_mset/unnamed/0004_find_permutation_find_msets/permutation.essence index 2a9902ecaa..4b4473955b 100644 --- a/tests/custom/permutations/15_transform_mset/unnamed/0004_find_permutation_find_msets/permutation.essence +++ b/tests/custom/permutations/15_transform_mset/unnamed/0004_find_permutation_find_msets/permutation.essence @@ -7,5 +7,5 @@ find s : mset (size 4) of n find sn : mset (size 4) of n -such that sn = transform(p,s) /\ (3 = sum([ toInt(l != r) | (l, r) <- p])) +such that sn = transform([p],s) /\ (3 = sum([ toInt(l != r) | (l, r) <- p])) diff --git a/tests/custom/permutations/16_transform_permutation/enum/0010_given_permutation_letting_permutation/permutation.essence b/tests/custom/permutations/16_transform_permutation/enum/0010_given_permutation_letting_permutation/permutation.essence index 093189b861..5fd6977988 100644 --- a/tests/custom/permutations/16_transform_permutation/enum/0010_given_permutation_letting_permutation/permutation.essence +++ b/tests/custom/permutations/16_transform_permutation/enum/0010_given_permutation_letting_permutation/permutation.essence @@ -5,5 +5,5 @@ given s : permutation of n find sn : permutation of n -such that sn = transform(p,s) +such that sn = transform([p],s) diff --git a/tests/custom/permutations/16_transform_permutation/enum/0020_given_permutation_find_permutations/permutation.essence b/tests/custom/permutations/16_transform_permutation/enum/0020_given_permutation_find_permutations/permutation.essence index 991443ec79..d4c8917ba4 100644 --- a/tests/custom/permutations/16_transform_permutation/enum/0020_given_permutation_find_permutations/permutation.essence +++ b/tests/custom/permutations/16_transform_permutation/enum/0020_given_permutation_find_permutations/permutation.essence @@ -7,5 +7,5 @@ find s : permutation of n find sn : permutation of n -such that sn = transform(p,s) /\ sn != s /\ |s| > 0 +such that sn = transform([p],s) /\ sn != s /\ |s| > 0 diff --git a/tests/custom/permutations/16_transform_permutation/enum/0030_letting_permutation_find_permutations/permutation.essence b/tests/custom/permutations/16_transform_permutation/enum/0030_letting_permutation_find_permutations/permutation.essence index 72451e09ed..b712859f8c 100644 --- a/tests/custom/permutations/16_transform_permutation/enum/0030_letting_permutation_find_permutations/permutation.essence +++ b/tests/custom/permutations/16_transform_permutation/enum/0030_letting_permutation_find_permutations/permutation.essence @@ -7,5 +7,5 @@ find s : permutation of n find sn : permutation of n -such that sn = transform(p,s) +such that sn = transform([p],s) diff --git a/tests/custom/permutations/16_transform_permutation/enum/0040_find_permutation_find_permutations/permutation.essence b/tests/custom/permutations/16_transform_permutation/enum/0040_find_permutation_find_permutations/permutation.essence index 731b5f81cb..2e764a3062 100644 --- a/tests/custom/permutations/16_transform_permutation/enum/0040_find_permutation_find_permutations/permutation.essence +++ b/tests/custom/permutations/16_transform_permutation/enum/0040_find_permutation_find_permutations/permutation.essence @@ -7,5 +7,5 @@ find s : permutation of n find sn : permutation of n -such that sn = transform(p,s) /\ 3 = |p| +such that sn = transform([p],s) /\ 3 = |p| diff --git a/tests/custom/permutations/16_transform_permutation/enum/0050_find_permutation_given_permutation_find_permutation/permutation.essence b/tests/custom/permutations/16_transform_permutation/enum/0050_find_permutation_given_permutation_find_permutation/permutation.essence index c0161fd378..86fd8e6459 100644 --- a/tests/custom/permutations/16_transform_permutation/enum/0050_find_permutation_given_permutation_find_permutation/permutation.essence +++ b/tests/custom/permutations/16_transform_permutation/enum/0050_find_permutation_given_permutation_find_permutation/permutation.essence @@ -7,5 +7,5 @@ given s : permutation of n find sn : permutation of n -such that sn = transform(p,s) +such that sn = transform([p],s) diff --git a/tests/custom/permutations/16_transform_permutation/int/0010_given_permutation_letting_permutation/permutation.essence b/tests/custom/permutations/16_transform_permutation/int/0010_given_permutation_letting_permutation/permutation.essence index ef8dc79096..8a3ead378b 100644 --- a/tests/custom/permutations/16_transform_permutation/int/0010_given_permutation_letting_permutation/permutation.essence +++ b/tests/custom/permutations/16_transform_permutation/int/0010_given_permutation_letting_permutation/permutation.essence @@ -6,5 +6,5 @@ given s : permutation of int(1..n) find sn : permutation of int(1..n) -such that sn = transform(p,s) +such that sn = transform([p],s) diff --git a/tests/custom/permutations/16_transform_permutation/int/0020_given_permutation_find_permutations/permutation.essence b/tests/custom/permutations/16_transform_permutation/int/0020_given_permutation_find_permutations/permutation.essence index 6cedf3e6e3..bf29796c55 100644 --- a/tests/custom/permutations/16_transform_permutation/int/0020_given_permutation_find_permutations/permutation.essence +++ b/tests/custom/permutations/16_transform_permutation/int/0020_given_permutation_find_permutations/permutation.essence @@ -7,5 +7,5 @@ find s : permutation of int(1..n) find sn : permutation of int(1..n) -such that sn = transform(p,s) /\ sn != s /\ |s| > 0 +such that sn = transform([p],s) /\ sn != s /\ |s| > 0 diff --git a/tests/custom/permutations/16_transform_permutation/int/0030_letting_permutation_find_permutations/permutation.essence b/tests/custom/permutations/16_transform_permutation/int/0030_letting_permutation_find_permutations/permutation.essence index b509b4340c..6b188f4036 100644 --- a/tests/custom/permutations/16_transform_permutation/int/0030_letting_permutation_find_permutations/permutation.essence +++ b/tests/custom/permutations/16_transform_permutation/int/0030_letting_permutation_find_permutations/permutation.essence @@ -7,5 +7,5 @@ find s : permutation of int(1..n) find sn : permutation of int(1..n) -such that sn = transform(p,s) +such that sn = transform([p],s) diff --git a/tests/custom/permutations/16_transform_permutation/int/0040_find_permutation_find_permutations/permutation.essence b/tests/custom/permutations/16_transform_permutation/int/0040_find_permutation_find_permutations/permutation.essence index d1013736a7..0e288922d4 100644 --- a/tests/custom/permutations/16_transform_permutation/int/0040_find_permutation_find_permutations/permutation.essence +++ b/tests/custom/permutations/16_transform_permutation/int/0040_find_permutation_find_permutations/permutation.essence @@ -7,5 +7,5 @@ find s : permutation of int(1..n) find sn : permutation of int(1..n) -such that sn = transform(p,s) /\ 3 = |p| +such that sn = transform([p],s) /\ 3 = |p| diff --git a/tests/custom/permutations/16_transform_permutation/int/0050_find_permutation_given_permutation_find_permutation/permutation.essence b/tests/custom/permutations/16_transform_permutation/int/0050_find_permutation_given_permutation_find_permutation/permutation.essence index b2d77ac49e..4d1bbc78d4 100644 --- a/tests/custom/permutations/16_transform_permutation/int/0050_find_permutation_given_permutation_find_permutation/permutation.essence +++ b/tests/custom/permutations/16_transform_permutation/int/0050_find_permutation_given_permutation_find_permutation/permutation.essence @@ -7,5 +7,5 @@ given s : permutation of int(1..n) find sn : permutation of int(1..n) -such that sn = transform(p,s) +such that sn = transform([p],s) diff --git a/tests/custom/permutations/16_transform_permutation/unnamed/0004_find_permutation_find_permutations/permutation.essence b/tests/custom/permutations/16_transform_permutation/unnamed/0004_find_permutation_find_permutations/permutation.essence index c29addc20c..0c15fb12f2 100644 --- a/tests/custom/permutations/16_transform_permutation/unnamed/0004_find_permutation_find_permutations/permutation.essence +++ b/tests/custom/permutations/16_transform_permutation/unnamed/0004_find_permutation_find_permutations/permutation.essence @@ -7,5 +7,5 @@ find s : permutation of n find sn : permutation of n -such that sn = transform(p,s) /\ |p| > 0 +such that sn = transform([p],s) /\ |p| > 0 diff --git a/tests/custom/permutations/17_transform_partition/int/0010_given_permutation_partition_find_partition/permutation.essence b/tests/custom/permutations/17_transform_partition/int/0010_given_permutation_partition_find_partition/permutation.essence index 362296528c..8a165a50db 100644 --- a/tests/custom/permutations/17_transform_partition/int/0010_given_permutation_partition_find_partition/permutation.essence +++ b/tests/custom/permutations/17_transform_partition/int/0010_given_permutation_partition_find_partition/permutation.essence @@ -6,5 +6,5 @@ given s : partition from int(1..n) find sn : partition from int(1..n) -such that sn = transform(p,s) +such that sn = transform([p],s) diff --git a/tests/custom/permutations/17_transform_partition/int/0020_given_permutation_find_partitions/permutation.essence b/tests/custom/permutations/17_transform_partition/int/0020_given_permutation_find_partitions/permutation.essence index a351d7b830..da39543e8f 100644 --- a/tests/custom/permutations/17_transform_partition/int/0020_given_permutation_find_partitions/permutation.essence +++ b/tests/custom/permutations/17_transform_partition/int/0020_given_permutation_find_partitions/permutation.essence @@ -7,5 +7,5 @@ find s : partition from int(1..n) find sn : partition from int(1..n) -such that sn = transform(p,s) /\ sn != s /\ |s| > 0 +such that sn = transform([p],s) /\ sn != s /\ |s| > 0 diff --git a/tests/custom/permutations/17_transform_partition/int/0030_letting_permutation_find_partitions/permutation.essence b/tests/custom/permutations/17_transform_partition/int/0030_letting_permutation_find_partitions/permutation.essence index 044aa742d6..860474f5a2 100644 --- a/tests/custom/permutations/17_transform_partition/int/0030_letting_permutation_find_partitions/permutation.essence +++ b/tests/custom/permutations/17_transform_partition/int/0030_letting_permutation_find_partitions/permutation.essence @@ -7,5 +7,5 @@ find s : partition from int(1..n) find sn : partition from int(1..n) -such that sn = transform(p,s) +such that sn = transform([p],s) diff --git a/tests/custom/permutations/17_transform_partition/int/0040_find_permutation_find_partitions/permutation.essence b/tests/custom/permutations/17_transform_partition/int/0040_find_permutation_find_partitions/permutation.essence index 9a3e54913d..0c8f204ac1 100644 --- a/tests/custom/permutations/17_transform_partition/int/0040_find_permutation_find_partitions/permutation.essence +++ b/tests/custom/permutations/17_transform_partition/int/0040_find_permutation_find_partitions/permutation.essence @@ -7,5 +7,5 @@ find s : partition from int(1..n) find sn : partition from int(1..n) -such that sn = transform(p,s) /\ 3 = |p| +such that sn = transform([p],s) /\ 3 = |p| diff --git a/tests/custom/permutations/17_transform_partition/int/0050_find_permutation_given_partition_find_partition/permutation.essence b/tests/custom/permutations/17_transform_partition/int/0050_find_permutation_given_partition_find_partition/permutation.essence index b615b9813e..fccab75b73 100644 --- a/tests/custom/permutations/17_transform_partition/int/0050_find_permutation_given_partition_find_partition/permutation.essence +++ b/tests/custom/permutations/17_transform_partition/int/0050_find_permutation_given_partition_find_partition/permutation.essence @@ -7,5 +7,5 @@ given s : partition from int(1..n) find sn : partition from int(1..n) -such that sn = transform(p,s) +such that sn = transform([p],s) diff --git a/tests/custom/permutations/17_transform_partition/unnamed/0010_find_partition_of_unnamed/permutation.essence b/tests/custom/permutations/17_transform_partition/unnamed/0010_find_partition_of_unnamed/permutation.essence index 15d095bddd..bb5272934c 100644 --- a/tests/custom/permutations/17_transform_partition/unnamed/0010_find_partition_of_unnamed/permutation.essence +++ b/tests/custom/permutations/17_transform_partition/unnamed/0010_find_partition_of_unnamed/permutation.essence @@ -2,4 +2,4 @@ letting n be new type of size 4 find a : partition from n find b : partition from n find p : permutation (numMoved 3) of n -such that b = transform(p,a) /\ a != b +such that b = transform([p],a) /\ a != b diff --git a/tests/custom/permutations/18_transform_matrix/enum/0010_find_permutation_indexing_given_matrix/permutation.essence b/tests/custom/permutations/18_transform_matrix/enum/0010_find_permutation_indexing_given_matrix/permutation.essence index 5431ec54d7..094dbf5161 100644 --- a/tests/custom/permutations/18_transform_matrix/enum/0010_find_permutation_indexing_given_matrix/permutation.essence +++ b/tests/custom/permutations/18_transform_matrix/enum/0010_find_permutation_indexing_given_matrix/permutation.essence @@ -4,5 +4,5 @@ find p : permutation of n given s : matrix indexed by [int(1..4)] of n find t : matrix indexed by [int(1..4)] of n -such that e_8 = transform(p,s)[2] /\ t = image(p,s) +such that e_8 = transform([p],s)[2] /\ t = image(p,s) diff --git a/tests/custom/permutations/18_transform_matrix/enum/0015_find_permutation_indexing_given_matrix/permutation.essence b/tests/custom/permutations/18_transform_matrix/enum/0015_find_permutation_indexing_given_matrix/permutation.essence index 2d592b4f06..a284b3b44e 100644 --- a/tests/custom/permutations/18_transform_matrix/enum/0015_find_permutation_indexing_given_matrix/permutation.essence +++ b/tests/custom/permutations/18_transform_matrix/enum/0015_find_permutation_indexing_given_matrix/permutation.essence @@ -3,5 +3,5 @@ letting n be new type enum {e_5,e_6,e_7,e_8} find p : permutation of n letting s be [e_5,e_6,e_7,e_8] -such that e_8 = transform(p,s)[2] +such that e_8 = transform([p],s)[2] diff --git a/tests/custom/permutations/18_transform_matrix/enum/0020_given_permutation_and_matrix_find_matrix/permutation.essence b/tests/custom/permutations/18_transform_matrix/enum/0020_given_permutation_and_matrix_find_matrix/permutation.essence index 6334331928..ea6c07ffa7 100644 --- a/tests/custom/permutations/18_transform_matrix/enum/0020_given_permutation_and_matrix_find_matrix/permutation.essence +++ b/tests/custom/permutations/18_transform_matrix/enum/0020_given_permutation_and_matrix_find_matrix/permutation.essence @@ -5,5 +5,5 @@ given s : matrix indexed by [int(11..14)] of n find sn : matrix indexed by [int(11..14)] of n -such that sn = transform(p,s) +such that sn = transform([p],s) diff --git a/tests/custom/permutations/18_transform_matrix/enum/0030_letting_permutation_given_matrix_find_matrix/permutation.essence b/tests/custom/permutations/18_transform_matrix/enum/0030_letting_permutation_given_matrix_find_matrix/permutation.essence index cf493e7d21..92164acbee 100644 --- a/tests/custom/permutations/18_transform_matrix/enum/0030_letting_permutation_given_matrix_find_matrix/permutation.essence +++ b/tests/custom/permutations/18_transform_matrix/enum/0030_letting_permutation_given_matrix_find_matrix/permutation.essence @@ -5,5 +5,5 @@ given s : matrix indexed by [int(1..4)] of n find sn : matrix indexed by [int(1..4)] of n -such that sn = transform(p,s) +such that sn = transform([p],s) diff --git a/tests/custom/permutations/18_transform_matrix/enum/0040_find_permutation_find_matrices/permutation.essence b/tests/custom/permutations/18_transform_matrix/enum/0040_find_permutation_find_matrices/permutation.essence index d4c64297b4..31515dfdf9 100644 --- a/tests/custom/permutations/18_transform_matrix/enum/0040_find_permutation_find_matrices/permutation.essence +++ b/tests/custom/permutations/18_transform_matrix/enum/0040_find_permutation_find_matrices/permutation.essence @@ -5,5 +5,5 @@ find s : matrix indexed by [int(1..2)] of n find t : matrix indexed by [int(1..2)] of n -such that t = transform(p,s) /\ allDiff(s) +such that t = transform([p],s) /\ allDiff(s) diff --git a/tests/custom/permutations/18_transform_matrix/int/0010_find_permutation_indexing_given_matrix/permutation.essence b/tests/custom/permutations/18_transform_matrix/int/0010_find_permutation_indexing_given_matrix/permutation.essence index 20508b3545..d52568cd57 100644 --- a/tests/custom/permutations/18_transform_matrix/int/0010_find_permutation_indexing_given_matrix/permutation.essence +++ b/tests/custom/permutations/18_transform_matrix/int/0010_find_permutation_indexing_given_matrix/permutation.essence @@ -3,5 +3,5 @@ letting n be 4 find p : permutation of int(1..n) given s : matrix indexed by [int(1..4)] of int(5..8) -such that 8 = transform(p,s)[2] +such that 8 = transform([p],s)[2] diff --git a/tests/custom/permutations/18_transform_matrix/int/0015_find_permutation_indexing_given_matrix/permutation.essence b/tests/custom/permutations/18_transform_matrix/int/0015_find_permutation_indexing_given_matrix/permutation.essence index 95ffb595d0..3560901dc3 100644 --- a/tests/custom/permutations/18_transform_matrix/int/0015_find_permutation_indexing_given_matrix/permutation.essence +++ b/tests/custom/permutations/18_transform_matrix/int/0015_find_permutation_indexing_given_matrix/permutation.essence @@ -3,5 +3,5 @@ letting n be 4 find p : permutation of int(1..n) letting s be [5,6,7,8] -such that 8 = transform(p,s)[2] +such that 8 = transform([p],s)[2] diff --git a/tests/custom/permutations/18_transform_matrix/int/0020_given_permutation_and_matrix_find_matrix/permutation.essence b/tests/custom/permutations/18_transform_matrix/int/0020_given_permutation_and_matrix_find_matrix/permutation.essence index d716c4f430..7deac00015 100644 --- a/tests/custom/permutations/18_transform_matrix/int/0020_given_permutation_and_matrix_find_matrix/permutation.essence +++ b/tests/custom/permutations/18_transform_matrix/int/0020_given_permutation_and_matrix_find_matrix/permutation.essence @@ -5,5 +5,5 @@ given s : matrix indexed by [int(1..4)] of int(5..8) find sn : matrix indexed by [int(1..4)] of int(5..8) -such that sn = transform(p,s) +such that sn = transform([p],s) diff --git a/tests/custom/permutations/18_transform_matrix/int/0030_letting_permutation_given_matrix_find_matrix/permutation.essence b/tests/custom/permutations/18_transform_matrix/int/0030_letting_permutation_given_matrix_find_matrix/permutation.essence index 651988fbae..7aa5abbc80 100644 --- a/tests/custom/permutations/18_transform_matrix/int/0030_letting_permutation_given_matrix_find_matrix/permutation.essence +++ b/tests/custom/permutations/18_transform_matrix/int/0030_letting_permutation_given_matrix_find_matrix/permutation.essence @@ -5,5 +5,5 @@ given s : matrix indexed by [int(1..4)] of int(5..8) find sn : matrix indexed by [int(1..4)] of int(5..8) -such that sn = transform(p,s) +such that sn = transform([p],s) diff --git a/tests/custom/permutations/18_transform_matrix/unnamed/0040_find_permutation_find_matrices/permutation.essence b/tests/custom/permutations/18_transform_matrix/unnamed/0040_find_permutation_find_matrices/permutation.essence index f0fd95fa61..adefefc88d 100644 --- a/tests/custom/permutations/18_transform_matrix/unnamed/0040_find_permutation_find_matrices/permutation.essence +++ b/tests/custom/permutations/18_transform_matrix/unnamed/0040_find_permutation_find_matrices/permutation.essence @@ -5,5 +5,5 @@ find s : matrix indexed by [int(1..4)] of n find t : matrix indexed by [int(1..4)] of n -such that t = transform(p,s) /\ allDiff(s) +such that t = transform([p],s) /\ allDiff(s) diff --git a/tests/custom/permutations/19_complications/multiple_enums/0010_set_of_tuples/permutation.essence b/tests/custom/permutations/19_complications/multiple_enums/0010_set_of_tuples/permutation.essence index 6a8f82250b..dd0e28cc3e 100644 --- a/tests/custom/permutations/19_complications/multiple_enums/0010_set_of_tuples/permutation.essence +++ b/tests/custom/permutations/19_complications/multiple_enums/0010_set_of_tuples/permutation.essence @@ -6,5 +6,5 @@ letting s be {(e_1,n_3),(e_2,n_4)} find t : set of (e,n) -such that t = transform(p,s) +such that t = transform([p],s) diff --git a/tests/custom/permutations/21_superpermutations/0010_size_3/permutation.essence b/tests/custom/permutations/21_superpermutations/0010_size_3/permutation.essence index 7a27b0e9e7..4ccdc7d7ac 100644 --- a/tests/custom/permutations/21_superpermutations/0010_size_3/permutation.essence +++ b/tests/custom/permutations/21_superpermutations/0010_size_3/permutation.essence @@ -2,7 +2,7 @@ given s : set of permutation of int(1..3) given q : sequence (size 3) of int(1..3) find qs : set of sequence (size 3) of int(1..3) -such that |qs| = |s| /\ and([ transform(p,q) in qs | p <- s]) +such that |qs| = |s| /\ and([ transform([p],q) in qs | p <- s]) find superperm : sequence (maxSize 100) of int(1..3) diff --git a/tests/custom/permutations/21_superpermutations/0020_size_3/permutation.essence b/tests/custom/permutations/21_superpermutations/0020_size_3/permutation.essence index c758655ecc..fe8f3a3724 100644 --- a/tests/custom/permutations/21_superpermutations/0020_size_3/permutation.essence +++ b/tests/custom/permutations/21_superpermutations/0020_size_3/permutation.essence @@ -2,7 +2,7 @@ given s : set of permutation of int(1..3) find superperm : sequence (maxSize 100) of int(1..3) such that - and([ transform(z,sequence(1,2,3)) substring superperm | z <- s ]) + and([ transform([z],sequence(1,2,3)) substring superperm | z <- s ]) minimising |superperm| diff --git a/tests/custom/permutations/22_tagged_ints/int/0001_permute_untagged/permutation.essence b/tests/custom/permutations/22_tagged_ints/int/0001_permute_untagged/permutation.essence index 1f152d58d5..c883e5c262 100644 --- a/tests/custom/permutations/22_tagged_ints/int/0001_permute_untagged/permutation.essence +++ b/tests/custom/permutations/22_tagged_ints/int/0001_permute_untagged/permutation.essence @@ -1,5 +1,5 @@ find t : (int:A(1..6), int(1..6)) find x : (int:A(1..6), int(1..6)) -such that x = transform(permutation((1,2,3,4,5,6)),t) +such that x = transform([permutation((1,2,3,4,5,6))],t) diff --git a/tests/custom/permutations/22_tagged_ints/int/0002_permute_tagged/permutation.essence b/tests/custom/permutations/22_tagged_ints/int/0002_permute_tagged/permutation.essence index 1b9c3cadf6..fb2a3c259a 100644 --- a/tests/custom/permutations/22_tagged_ints/int/0002_permute_tagged/permutation.essence +++ b/tests/custom/permutations/22_tagged_ints/int/0002_permute_tagged/permutation.essence @@ -1,5 +1,5 @@ find t : (int:A(1..6), int(1..6)) find x : (int:A(1..6), int(1..6)) -such that x = transform(permutation((1:A,2:A,3:A,4:A,5:A,6:A)),t) +such that x = transform([permutation((1:A,2:A,3:A,4:A,5:A,6:A))],t) diff --git a/tests/custom/permutations/22_tagged_ints/int/0003_tagged_lits_in_param/permutation.essence b/tests/custom/permutations/22_tagged_ints/int/0003_tagged_lits_in_param/permutation.essence index a45cda7741..c3d54eda07 100644 --- a/tests/custom/permutations/22_tagged_ints/int/0003_tagged_lits_in_param/permutation.essence +++ b/tests/custom/permutations/22_tagged_ints/int/0003_tagged_lits_in_param/permutation.essence @@ -1,6 +1,6 @@ find t : (int:A(1..6), int(1..6)) find x : (int:A(1..6), int(1..6)) given p : permutation of int:A(1..6) -such that x = transform(p,t) +such that x = transform([p],t) diff --git a/tests/custom/permutations/23_image_set_dotlt/int/0010_find_perm_find_set/permutation.essence b/tests/custom/permutations/23_image_set_dotlt/int/0010_find_perm_find_set/permutation.essence index 5f4f842f08..4169428c22 100644 --- a/tests/custom/permutations/23_image_set_dotlt/int/0010_find_perm_find_set/permutation.essence +++ b/tests/custom/permutations/23_image_set_dotlt/int/0010_find_perm_find_set/permutation.essence @@ -3,5 +3,5 @@ find p : permutation of int(1..4) find s : set of int(1..4) -such that s .< transform(p,s) +such that s .< transform([p],s) diff --git a/tests/custom/permutations/24_image_comprehension_dotlt/int/0010_find_perm_find_set/permutation.essence b/tests/custom/permutations/24_image_comprehension_dotlt/int/0010_find_perm_find_set/permutation.essence index 012b29421b..6e6da2d7bb 100644 --- a/tests/custom/permutations/24_image_comprehension_dotlt/int/0010_find_perm_find_set/permutation.essence +++ b/tests/custom/permutations/24_image_comprehension_dotlt/int/0010_find_perm_find_set/permutation.essence @@ -3,5 +3,5 @@ find p : permutation of int(1..4) find s : set of (int(1..4),int(1..4)) such that p(4) != 4 -such that and(transform(p,[sj > si | (si,sj) <- s])) +such that and(transform([p],[sj > si | (si,sj) <- s])) diff --git a/tests/custom/permutations/permInverse/04/00.essence b/tests/custom/permutations/permInverse/04/00.essence index 38ba6303f0..5f6550a336 100644 --- a/tests/custom/permutations/permInverse/04/00.essence +++ b/tests/custom/permutations/permInverse/04/00.essence @@ -1,12 +1,12 @@ -$ transform(p, x)[i] ~~> transform(p, x[transform(permInverse(p), i)]) +$ transform([p], x)[i] ~~> transform([p], x[transform([permInverse(p)], i)]) find p : permutation (numMoved 3) of int(1..3) find x : matrix [int(1..3)] of bool find y : matrix [int(1..3)] of bool -such that y = transform(p, x) +such that y = transform([p], x) diff --git a/tests/custom/permutations/permInverse/05/00.essence b/tests/custom/permutations/permInverse/05/00.essence index f5bb432a35..4fa93f2bbd 100644 --- a/tests/custom/permutations/permInverse/05/00.essence +++ b/tests/custom/permutations/permInverse/05/00.essence @@ -6,7 +6,7 @@ find p : permutation (numMoved 3) of A find x : matrix [A] of bool find y : matrix [A] of bool -such that y = transform(p, x) +such that y = transform([p], x) diff --git a/tests/custom/permutations/permInverse/08/00.essence b/tests/custom/permutations/permInverse/08/00.essence index 526257236b..eaade1b0ad 100644 --- a/tests/custom/permutations/permInverse/08/00.essence +++ b/tests/custom/permutations/permInverse/08/00.essence @@ -3,4 +3,4 @@ find x : matrix [int(1..2)] of A find y : matrix [int(1..3)] of A find p : permutation of A -such that (x, y) .<= transform(p, (x, y)) +such that (x, y) .<= transform([p], (x, y)) diff --git a/tests/custom/permutations/permInverse/13-sets/00.essence b/tests/custom/permutations/permInverse/13-sets/00.essence index 31150bef74..716244b714 100644 --- a/tests/custom/permutations/permInverse/13-sets/00.essence +++ b/tests/custom/permutations/permInverse/13-sets/00.essence @@ -2,7 +2,7 @@ letting A be new type of size 3 find x : set of A find p : permutation (numMoved 3) of A -$ such that x .<= transform(p, x) +$ such that x .<= transform([p], x) $ the above rule, Oz thinks can be written recursively for all types $ produce aux for the rhs @@ -10,8 +10,8 @@ $ forAll, forAll, forAll $ membership constraints $ find x' : ... -$ such that forAll i in x . transform(p, i) in x' -$ such that forAll i in x' . transform(permInverse(p), i) in x +$ such that forAll i in x . transform([p], i) in x' +$ such that forAll i in x' . transform([permInverse(p)], i) in x -such that x .<= toSet([ transform(p, i) | i <- x]) +such that x .<= toSet([ transform([p], i) | i <- x]) diff --git a/tests/custom/permutations/permInverse/14/00.essence b/tests/custom/permutations/permInverse/14/00.essence new file mode 100644 index 0000000000..eaee222675 --- /dev/null +++ b/tests/custom/permutations/permInverse/14/00.essence @@ -0,0 +1,20 @@ +letting A be new type of size 3 +find x : set of A + +find p : permutation (numMoved 3) of A +$ such that x .<= transform([p], x) +such that quickPermutationOrder(x, [p]) + +$ should have 2 additional solutions with quick, or more! + +$ the above rule, Oz thinks can be written recursively for all types +$ produce aux for the rhs +$ forAll, forAll, forAll +$ membership constraints + +$ find x' : ... +$ such that forAll i in x . transform([p], i) in x' +$ such that forAll i in x' . transform([permInverse(p)], i) in x + +$ such that x .<= toSet([ transform([p], i) | i <- x]) + diff --git a/tests/custom/transform/function/matrix/const_01/function.essence b/tests/custom/transform/function/matrix/const_01/function.essence index 8bc0ba4a1d..94234ccb53 100644 --- a/tests/custom/transform/function/matrix/const_01/function.essence +++ b/tests/custom/transform/function/matrix/const_01/function.essence @@ -1,5 +1,5 @@ find m : matrix indexed by [int(1..4)] of int(1..4) find f : function (total, bijective) int(1..4) --> int(1..4) -such that m = transform(f,[3,4,2,1]) +such that m = transform([f],[3,4,2,1]) such that allDiff(m) diff --git a/tests/custom/transform/function/matrix/var_01/function.essence b/tests/custom/transform/function/matrix/var_01/function.essence index 61f9c1da59..485d3de504 100644 --- a/tests/custom/transform/function/matrix/var_01/function.essence +++ b/tests/custom/transform/function/matrix/var_01/function.essence @@ -2,6 +2,6 @@ find m : matrix indexed by [int(1..4)] of int(1..4) find n : matrix indexed by [int(1..4)] of int(1..4) find f : function (total, bijective) int(1..4) --> int(1..4) -such that m = transform(f,n) +such that m = transform([f],n) such that m != n such that allDiff(m) diff --git a/tests/custom/transform/function/partition/const_01/function.essence b/tests/custom/transform/function/partition/const_01/function.essence index 22f2b0298a..3979d0a027 100644 --- a/tests/custom/transform/function/partition/const_01/function.essence +++ b/tests/custom/transform/function/partition/const_01/function.essence @@ -1,5 +1,5 @@ letting R be domain partition (numParts 2) from int(1..4) find m : R find f : function (total, bijective) int(1..4) --> int(1..4) -such that m = transform(f,partition({1,3},{2,4})) +such that m = transform([f],partition({1,3},{2,4})) diff --git a/tests/custom/transform/function/partition/var_01/function.essence b/tests/custom/transform/function/partition/var_01/function.essence index 53f66de1c5..d2cd2a6fd0 100644 --- a/tests/custom/transform/function/partition/var_01/function.essence +++ b/tests/custom/transform/function/partition/var_01/function.essence @@ -2,6 +2,6 @@ letting R be domain partition (numParts 2) from int(1..4) find m : R find n : R find f : function (total, bijective) int(1..4) --> int(1..4) -such that m = transform(f,n) +such that m = transform([f],n) such that m != n diff --git a/tests/custom/transform/function/record/const_01/function.essence b/tests/custom/transform/function/record/const_01/function.essence index 46830c80d5..bf6585fca1 100644 --- a/tests/custom/transform/function/record/const_01/function.essence +++ b/tests/custom/transform/function/record/const_01/function.essence @@ -1,5 +1,5 @@ letting R be domain record { a : int(1..4), b : int(1..4) } find m : R find f : function (total, bijective) int(1..4) --> int(1..4) -such that m = transform(f, record { a = 3, b = 2 }) +such that m = transform([f], record { a = 3, b = 2 }) diff --git a/tests/custom/transform/function/record/var_01/function.essence b/tests/custom/transform/function/record/var_01/function.essence index 1d9ecf0518..2c10595883 100644 --- a/tests/custom/transform/function/record/var_01/function.essence +++ b/tests/custom/transform/function/record/var_01/function.essence @@ -2,5 +2,5 @@ letting R be domain record { a : int(1..4), b : int(1..4) } find m : R find n : R find f : function (total, bijective) int(1..4) --> int(1..4) -such that m = transform(f,n) +such that m = transform([f],n) $such that m = n diff --git a/tests/custom/transform/function/record/var_02/function.essence b/tests/custom/transform/function/record/var_02/function.essence index 6c91a0a0ae..4e1cb5d9d1 100644 --- a/tests/custom/transform/function/record/var_02/function.essence +++ b/tests/custom/transform/function/record/var_02/function.essence @@ -3,6 +3,6 @@ letting R be domain partition (numParts 2) from A find m : R find n : R find f : function (total, bijective) int(1..2) --> int(1..2) -such that m = transform(f,n) +such that m = transform([f],n) such that m != n diff --git a/tests/custom/transform/function/sequence/const_01/function.essence b/tests/custom/transform/function/sequence/const_01/function.essence index 108428d007..09d17255f8 100644 --- a/tests/custom/transform/function/sequence/const_01/function.essence +++ b/tests/custom/transform/function/sequence/const_01/function.essence @@ -1,6 +1,6 @@ letting R be domain sequence (size 4) of int(1..4) find m : R find f : function (total, bijective) int(1..4) --> int(1..4) -such that m = transform(f,sequence(4,3,2,1)) +such that m = transform([f],sequence(4,3,2,1)) diff --git a/tests/custom/transform/function/sequence/var_01/function.essence b/tests/custom/transform/function/sequence/var_01/function.essence index ec26ae8287..786b82add4 100644 --- a/tests/custom/transform/function/sequence/var_01/function.essence +++ b/tests/custom/transform/function/sequence/var_01/function.essence @@ -2,6 +2,6 @@ letting R be domain sequence (size 4) of int(1..4) find m : R find n : R find f : function (total, bijective) int(1..4) --> int(1..4) -such that m = transform(f,n) +such that m = transform([f],n) such that m != n diff --git a/tests/custom/transform/function/set/const_01/function.essence b/tests/custom/transform/function/set/const_01/function.essence index f7deb8261d..99f5d3615d 100644 --- a/tests/custom/transform/function/set/const_01/function.essence +++ b/tests/custom/transform/function/set/const_01/function.essence @@ -1,4 +1,4 @@ find s : set (size 3) of int(1..4) find f : function (total, bijective) int(1..4) --> int(1..4) -such that transform(f, {1,2,3}) = s +such that transform([f], {1,2,3}) = s diff --git a/tests/custom/transform/function/set/var_01/function.essence b/tests/custom/transform/function/set/var_01/function.essence index 2a9e3b683d..0f9b47817d 100644 --- a/tests/custom/transform/function/set/var_01/function.essence +++ b/tests/custom/transform/function/set/var_01/function.essence @@ -1,4 +1,4 @@ find s : set (size 3) of int(1..4) find f : function (total, bijective) int(1..4) --> int(1..4) -such that transform(f, s) = s +such that transform([f], s) = s diff --git a/tests/custom/transform/function/set/var_02/function.essence b/tests/custom/transform/function/set/var_02/function.essence index 5e0cff50b8..3b9f7742ef 100644 --- a/tests/custom/transform/function/set/var_02/function.essence +++ b/tests/custom/transform/function/set/var_02/function.essence @@ -1,4 +1,4 @@ find s : set (size 3) of int(1..4) find f : function (total, bijective) int(1..4) --> int(1..4) -such that transform(f, [ i < 4 | i <- s]) +such that transform([f], [ i < 4 | i <- s]) diff --git a/tests/custom/transform/function/tuple/const_01/function.essence b/tests/custom/transform/function/tuple/const_01/function.essence index 6dc777f6d6..443e1f2599 100644 --- a/tests/custom/transform/function/tuple/const_01/function.essence +++ b/tests/custom/transform/function/tuple/const_01/function.essence @@ -1,5 +1,5 @@ find m : (int(1..4), int(1..4)) find f : function (total, bijective) int(1..4) --> int(1..4) -such that m = transform(f,(3,4)) +such that m = transform([f],(3,4)) diff --git a/tests/custom/transform/function/tuple/var_01/function.essence b/tests/custom/transform/function/tuple/var_01/function.essence index ab0dae37c4..a0823a7046 100644 --- a/tests/custom/transform/function/tuple/var_01/function.essence +++ b/tests/custom/transform/function/tuple/var_01/function.essence @@ -2,5 +2,5 @@ find m : (int(1..4), int(1..4)) find n : (int(1..4), int(1..4)) find f : function (total, bijective) int(1..4) --> int(1..4) -such that m = transform(f,n) +such that m = transform([f],n) such that m =n diff --git a/tests/custom/transform/function/variant/const_01/function.essence b/tests/custom/transform/function/variant/const_01/function.essence index e6bff721fe..9102189d3c 100644 --- a/tests/custom/transform/function/variant/const_01/function.essence +++ b/tests/custom/transform/function/variant/const_01/function.essence @@ -2,6 +2,6 @@ letting R be domain variant { a : int(1..4), b : bool } find m : R find n : R find f : function (total, bijective) int(1..4) --> int(1..4) -such that m = transform(f,variant {a = 2}) +such that m = transform([f],variant {a = 2}) such that active(m,a) such that m != n diff --git a/tests/custom/transform/function/variant/var_01/function.essence b/tests/custom/transform/function/variant/var_01/function.essence index fe57188bfe..61b087cd13 100644 --- a/tests/custom/transform/function/variant/var_01/function.essence +++ b/tests/custom/transform/function/variant/var_01/function.essence @@ -2,6 +2,6 @@ letting R be domain variant { a : int(1..4), b : bool } find m : R find n : R find f : function (total, bijective) int(1..4) --> int(1..4) -such that m = transform(f,n) +such that m = transform([f],n) such that active(m,a) such that m != n diff --git a/tests/custom/transform/function/variant/var_02/function.essence b/tests/custom/transform/function/variant/var_02/function.essence index 8d10efa673..c0d1f4c1c5 100644 --- a/tests/custom/transform/function/variant/var_02/function.essence +++ b/tests/custom/transform/function/variant/var_02/function.essence @@ -2,6 +2,6 @@ letting R be domain variant { a : int(1..4), b : bool } find m : R find n : R find f : function (total, bijective) int(1..4) --> int(1..4) -such that transform(f,transform(f,n)) = transform(f,m) +such that transform([f],transform([f],n)) = transform([f],m) such that active(m,a) such that m != n diff --git a/tests/custom/transform/function/variant/var_03/function.essence b/tests/custom/transform/function/variant/var_03/function.essence index cf4bb0017f..47d012eeaa 100644 --- a/tests/custom/transform/function/variant/var_03/function.essence +++ b/tests/custom/transform/function/variant/var_03/function.essence @@ -2,5 +2,5 @@ letting R be domain variant { a : int(1..4), b : bool } find m : set (size 4) of R find n : set (size 4) of R find f : function (total, bijective) int(1..4) --> int(1..4) -such that transform(f,transform(f,n)) = transform(f,m) +such that transform([f],transform([f],n)) = transform([f],m) such that m != n diff --git a/tests/custom/transform/function/variant/var_04/function.essence b/tests/custom/transform/function/variant/var_04/function.essence index ea2a856a88..03e8ba64fb 100644 --- a/tests/custom/transform/function/variant/var_04/function.essence +++ b/tests/custom/transform/function/variant/var_04/function.essence @@ -2,6 +2,6 @@ letting R be domain variant { a : int(1..4), b : bool } find m : set (size 3) of R find n : set (size 3) of R find f : function (total, bijective) int(1..4) --> int(1..4) -such that transform(f,transform(f,n)) = transform(f,m) -such that [ active(i, a) | i <- transform(f, n) ] +such that transform([f],transform([f],n)) = transform([f],m) +such that [ active(i, a) | i <- transform([f], n) ] such that m != n From b16caa421c266be47ba684b307c4922ecf713fef Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?=C3=96zg=C3=BCr=20Akg=C3=BCn?= Date: Sun, 19 Jan 2025 12:28:46 +0000 Subject: [PATCH 220/229] add expected times --- tests/custom/lex_less_untouched/hamiltonian/expected-time.txt | 1 + .../basic/function_partial_record_01/expected-time.txt | 1 + .../basic/function_partial_record_param/expected-time.txt | 1 + 3 files changed, 3 insertions(+) create mode 100644 tests/custom/lex_less_untouched/hamiltonian/expected-time.txt create mode 100644 tests/exhaustive/basic/function_partial_record_01/expected-time.txt create mode 100644 tests/exhaustive/basic/function_partial_record_param/expected-time.txt diff --git a/tests/custom/lex_less_untouched/hamiltonian/expected-time.txt b/tests/custom/lex_less_untouched/hamiltonian/expected-time.txt new file mode 100644 index 0000000000..9a037142aa --- /dev/null +++ b/tests/custom/lex_less_untouched/hamiltonian/expected-time.txt @@ -0,0 +1 @@ +10 \ No newline at end of file diff --git a/tests/exhaustive/basic/function_partial_record_01/expected-time.txt b/tests/exhaustive/basic/function_partial_record_01/expected-time.txt new file mode 100644 index 0000000000..9a037142aa --- /dev/null +++ b/tests/exhaustive/basic/function_partial_record_01/expected-time.txt @@ -0,0 +1 @@ +10 \ No newline at end of file diff --git a/tests/exhaustive/basic/function_partial_record_param/expected-time.txt b/tests/exhaustive/basic/function_partial_record_param/expected-time.txt new file mode 100644 index 0000000000..301160a930 --- /dev/null +++ b/tests/exhaustive/basic/function_partial_record_param/expected-time.txt @@ -0,0 +1 @@ +8 \ No newline at end of file From 821448cd28e75479b62b11aa6aa821ad52313089 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?=C3=96zg=C3=BCr=20Akg=C3=BCn?= Date: Mon, 20 Jan 2025 10:18:06 +0000 Subject: [PATCH 221/229] reformat --- src/test/Conjure/ParserFuzz.hs | 74 +++++++++++++++------------------- 1 file changed, 32 insertions(+), 42 deletions(-) diff --git a/src/test/Conjure/ParserFuzz.hs b/src/test/Conjure/ParserFuzz.hs index 165a3e2f4e..6968526fad 100644 --- a/src/test/Conjure/ParserFuzz.hs +++ b/src/test/Conjure/ParserFuzz.hs @@ -1,54 +1,44 @@ -{-# LANGUAGE RecordWildCards #-} - module Conjure.ParserFuzz (tests) where --- conjure - -import Conjure.Prelude - --- base - --- tasty -import Test.Tasty (TestTree, testGroup) -import Test.Tasty.HUnit (assertFailure, testCaseSteps) - -import Conjure.Language.AST.ASTParser (runASTParser, parseProgram) -import Conjure.Language.Lexer (runLexer, reformList) -import qualified Data.Text as T (pack, unpack) -import qualified Data.Text.Lazy as L -import Data.ByteString.Char8(hPutStrLn, pack) +import Conjure.Language.AST.ASTParser (parseProgram, runASTParser) import Conjure.Language.AST.Reformer (flattenSeq) +import Conjure.Language.Lexer (reformList, runLexer) +import Conjure.Prelude import Data.Algorithm.Diff (getGroupedDiff) import Data.Algorithm.DiffOutput (ppDiff) +import Data.ByteString.Char8 (hPutStrLn, pack) +import Data.Text qualified as T (pack, unpack) +import Data.Text.Lazy qualified as L import GHC.IO.Handle.FD (stderr) import Shelly (run, shelly, silently) - +import Test.Tasty (TestTree, testGroup) +import Test.Tasty.HUnit (assertFailure, testCaseSteps) tests :: IO TestTree tests = do - allFiles <- shelly $ silently $ run "git" ["ls-tree", "--full-tree", "--name-only", "-r", "HEAD"] - let allFileList = lines $ T.unpack allFiles - let testCases = testFile <$> allFileList - return (testGroup "parse_fuzz" testCases) + allFiles <- shelly $ silently $ run "git" ["ls-tree", "--full-tree", "--name-only", "-r", "HEAD"] + let allFileList = lines $ T.unpack allFiles + let testCases = testFile <$> allFileList + return (testGroup "parse_fuzz" testCases) testFile :: FilePath -> TestTree -testFile fp = testCaseSteps (map (\ch -> if ch == '/' then '.' else ch) fp) $ \step -> do - fd <- readFileIfExists fp - step "Lexing" - let usableFileData = concat (take 1000 . lines $ fromMaybe [] fd) - let fText = T.pack usableFileData - case runLexer fText (Just fp) of - Left _le -> assertFailure $ "Lexer failed in:" ++ fp - Right ets -> do - step "parsing" - case runASTParser parseProgram ets of - Left _pe -> assertFailure $ "Parser failed in:" ++ fp - Right pt -> do - step "RoundTripping" - let roundTrip = L.unpack $ reformList $ flattenSeq pt - unless (roundTrip == usableFileData) $ do - let diff = getGroupedDiff (lines roundTrip) (lines usableFileData) - Data.ByteString.Char8.hPutStrLn stderr $ Data.ByteString.Char8.pack $ "===DIFF: " ++ fp - Data.ByteString.Char8.hPutStrLn stderr $ Data.ByteString.Char8.pack $ ppDiff diff - Data.ByteString.Char8.hPutStrLn stderr "===------------" - assertFailure $ "Failed to rebuild :" ++ fp \ No newline at end of file +testFile fp = testCaseSteps (map (\ch -> if ch == '/' then '.' else ch) fp) $ \step -> do + fd <- readFileIfExists fp + step "lexing" + let usableFileData = concat (take 1000 . lines $ fromMaybe [] fd) + let fText = T.pack usableFileData + case runLexer fText (Just fp) of + Left _le -> assertFailure $ "Lexer failed in:" ++ fp + Right ets -> do + step "parsing" + case runASTParser parseProgram ets of + Left _pe -> assertFailure $ "Parser failed in:" ++ fp + Right pt -> do + step "round tripping" + let roundTrip = L.unpack $ reformList $ flattenSeq pt + unless (roundTrip == usableFileData) $ do + let diff = getGroupedDiff (lines roundTrip) (lines usableFileData) + Data.ByteString.Char8.hPutStrLn stderr $ Data.ByteString.Char8.pack $ "===DIFF: " ++ fp + Data.ByteString.Char8.hPutStrLn stderr $ Data.ByteString.Char8.pack $ ppDiff diff + Data.ByteString.Char8.hPutStrLn stderr "===------------" + assertFailure $ "Failed to rebuild :" ++ fp From bfe5d06e989237efc8b11df7c154effb982b6bd4 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?=C3=96zg=C3=BCr=20Akg=C3=BCn?= Date: Mon, 20 Jan 2025 13:15:32 +0000 Subject: [PATCH 222/229] print tagged int literals with the tag --- src/Conjure/Language/Constant.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Conjure/Language/Constant.hs b/src/Conjure/Language/Constant.hs index 9bb39c6910..0a4d4e4735 100644 --- a/src/Conjure/Language/Constant.hs +++ b/src/Conjure/Language/Constant.hs @@ -338,7 +338,7 @@ instance Pretty Constant where pretty (ConstantBool False) = "false" pretty (ConstantBool True ) = "true" - pretty (ConstantInt _ x ) = pretty x + pretty (ConstantInt t x) = pretty x <> pretty t pretty (ConstantEnum _ _ x) = pretty x pretty (ConstantField n _) = pretty n pretty (ConstantAbstract x) = pretty x From 52ac9339a2ba0bce39fcd4d702c9f82c1fe5bfb3 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?=C3=96zg=C3=BCr=20Akg=C3=BCn?= Date: Mon, 20 Jan 2025 13:16:03 +0000 Subject: [PATCH 223/229] stricter type-checking for tagged int domains --- src/Conjure/Language/Domain.hs | 16 ++++++++-------- 1 file changed, 8 insertions(+), 8 deletions(-) diff --git a/src/Conjure/Language/Domain.hs b/src/Conjure/Language/Domain.hs index 5ad0249749..2c60e9eb91 100644 --- a/src/Conjure/Language/Domain.hs +++ b/src/Conjure/Language/Domain.hs @@ -130,10 +130,10 @@ typeOfDomain DomainBool = return TypeBool typeOfDomain d@(DomainIntE t x) = do ty <- typeOf x case ty of - TypeInt _ -> return () -- pre recoverDomainInt - TypeList (TypeInt _) -> return () - TypeMatrix _ (TypeInt _) -> return () - TypeSet (TypeInt _) -> return () + TypeInt TagInt -> return () -- pre recoverDomainInt + TypeList (TypeInt TagInt) -> return () + TypeMatrix _ (TypeInt TagInt) -> return () + TypeSet (TypeInt TagInt) -> return () _ -> failDoc $ vcat [ "Expected an integer, but got:" <++> pretty ty , "In domain:" <+> pretty d ] @@ -142,11 +142,11 @@ typeOfDomain d@(DomainInt t rs) = do forM_ rs $ \ r -> forM_ r $ \ x -> do ty <- typeOf x case ty of - TypeInt{} -> return () + TypeInt _ -> return () _ -> failDoc $ vcat [ "Expected an integer, but got:" <++> pretty ty - , "For:" <+> pretty x - , "In domain:" <+> pretty d - ] + , "For:" <+> pretty x + , "In domain:" <+> pretty d + ] return (TypeInt t) typeOfDomain (DomainEnum defn _ _ ) = return (TypeEnum defn) typeOfDomain (DomainUnnamed defn _ ) = return (TypeUnnamed defn) From 86dce664cabf44ca848f11ff2825837d32354f77 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?=C3=96zg=C3=BCr=20Akg=C3=BCn?= Date: Mon, 20 Jan 2025 13:16:20 +0000 Subject: [PATCH 224/229] simplify sequence equality rule --- src/Conjure/Rules/Horizontal/Sequence.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Conjure/Rules/Horizontal/Sequence.hs b/src/Conjure/Rules/Horizontal/Sequence.hs index b8fc6b1040..87bf99c6d9 100644 --- a/src/Conjure/Rules/Horizontal/Sequence.hs +++ b/src/Conjure/Rules/Horizontal/Sequence.hs @@ -128,7 +128,7 @@ rule_Eq = "sequence-eq" `namedRule` theRule where /\ (forAll &iPat in &y . &x(&i[1]) = &i[2]) /\ - defined(&x) = defined(&y) + |&x| = |&y| |] ) From 0cffff5bd6a2d115d4a27adc47ec731e9122e94b Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?=C3=96zg=C3=BCr=20Akg=C3=BCn?= Date: Mon, 20 Jan 2025 13:16:34 +0000 Subject: [PATCH 225/229] update test files --- .../custom/basic/streamline01/stdout.expected | 86 ++------- tests/custom/ide/dump-repr/stdout.expected | 2 +- tests/custom/issues/395/stdout.expected | 30 ++- tests/custom/issues/432/stderr.expected | 5 +- tests/custom/issues/440/stderr.expected | 2 +- .../problem-instanceGenerator.essence | 161 ---------------- .../problem-instanceGenerator.essence.irace | 48 ----- .../record01/problem-instanceRepair.essence | 181 ------------------ .../0030_find_permutation/stdout.expected | 12 ++ .../0010_given_permutation/stdout.expected | 2 +- .../0020_letting_permutation/stdout.expected | 2 +- .../0030_find_permutation/permutation.essence | 8 +- .../int/0030_find_permutation/stderr.expected | 1 + .../int/0030_find_permutation/stdout.expected | 5 +- .../0031_find_permutation/permutation.essence | 4 + .../int/0031_find_permutation/run.sh | 3 + .../int/0031_find_permutation/stdout.expected | 10 + .../permutation.essence | 2 +- .../stdout.expected | 11 ++ .../stdout.expected | 9 + .../stdout.expected | 2 +- .../stdout.expected | 2 +- .../stdout.expected | 9 + .../stdout.expected | 9 + .../stdout.expected | 2 +- .../stdout.expected | 2 +- .../int/0001_permute_untagged/stdout.expected | 11 ++ .../int/0002_permute_tagged/stdout.expected | 11 ++ .../0003_tagged_lits_in_param/stdout.expected | 11 ++ .../div/0001_same_tags_works/stdout.expected | 11 ++ .../0003_const_tagged_works/stdout.expected | 10 + .../0003_const_tagged_works/stdout.expected | 10 + .../0003_const_tagged_works/stdout.expected | 11 ++ .../0003_const_tagged_works/stdout.expected | 11 ++ .../0003_const_tagged_works/stdout.expected | 11 ++ .../max/0001_same_tags_work/stdout.expected | 11 ++ .../0003_const_tagged_works/stdout.expected | 10 + .../min/0001_same_tags_work/stdout.expected | 11 ++ .../0003_const_tagged_works/stdout.expected | 10 + .../0001_same_tags_works/stdout.expected | 11 ++ .../0003_const_tagged_works/stdout.expected | 10 + .../mod/0001_same_tags_works/stdout.expected | 11 ++ .../0003_const_tagged_works/stdout.expected | 10 + .../neg/0001_same_tags_works/stdout.expected | 11 ++ .../0003_const_tagged_works/stdout.expected | 10 + .../0003_const_tagged_works/stdout.expected | 11 ++ .../prod/0001_same_tags_works/stdout.expected | 11 ++ .../0003_const_tagged_works/stdout.expected | 10 + .../0003_const_tagged_works/stdout.expected | 11 ++ .../sum/0001_same_tags_works/stdout.expected | 11 ++ .../0003_const_tagged_works/stdout.expected | 10 + .../0010_find_perm_find_set/stdout.expected | 55 ++++++ .../permInverse/06/stderr.expected | 4 +- .../permInverse/07/stderr.expected | 4 +- .../permInverse/09/stderr.expected | 2 +- .../permInverse/10/stderr.expected | 2 +- .../permInverse/12/stderr.expected | 2 +- .../autogen/gen35/expected/model_1.eprime | 9 +- .../autogen/gen35/expected/model_2.eprime | 9 +- ...tion => model_3_1-solution000001.solution} | 0 ...tion => model_3_1-solution000002.solution} | 0 ...tion => model_3_1-solution000003.solution} | 0 ...tion => model_3_1-solution000004.solution} | 0 .../{model_3.eprime => model_3_1.eprime} | 0 ...tion => model_4_1-solution000001.solution} | 0 ...tion => model_4_1-solution000002.solution} | 0 ...tion => model_4_1-solution000003.solution} | 0 ...tion => model_4_1-solution000004.solution} | 0 .../{model_4.eprime => model_4_1.eprime} | 0 .../issues/182/expected/model.eprime | 5 +- .../issues/263/_old_issues_262.essence | 12 -- .../expected/model-p2-solution000001.solution | 4 - .../issues/263/expected/model-p2.eprime-param | 3 - .../issues/263/expected/model.eprime | 7 - tests/exhaustive/issues/263/p2.param | 3 - .../subsetSum/expected/model_2_2_2.eprime | 2 +- .../unnamed-redefinition/typecheck.expected | 4 +- 77 files changed, 463 insertions(+), 540 deletions(-) delete mode 100644 tests/custom/paramgen/record01/problem-instanceGenerator.essence delete mode 100644 tests/custom/paramgen/record01/problem-instanceGenerator.essence.irace delete mode 100644 tests/custom/paramgen/record01/problem-instanceRepair.essence create mode 100644 tests/custom/permutations/14_transform_sequence/int/0030_find_permutation/stderr.expected create mode 100644 tests/custom/permutations/14_transform_sequence/int/0031_find_permutation/permutation.essence create mode 100755 tests/custom/permutations/14_transform_sequence/int/0031_find_permutation/run.sh create mode 100644 tests/custom/permutations/14_transform_sequence/int/0031_find_permutation/stdout.expected create mode 100644 tests/custom/permutations/18_transform_matrix/enum/0010_find_permutation_indexing_given_matrix/stdout.expected create mode 100644 tests/custom/permutations/22_tagged_ints/int/0001_permute_untagged/stdout.expected create mode 100644 tests/custom/permutations/22_tagged_ints/int/0002_permute_tagged/stdout.expected create mode 100644 tests/custom/permutations/22_tagged_ints/int/0003_tagged_lits_in_param/stdout.expected create mode 100644 tests/custom/permutations/22_tagged_ints/int/div/0001_same_tags_works/stdout.expected create mode 100644 tests/custom/permutations/22_tagged_ints/int/div/0003_const_tagged_works/stdout.expected create mode 100644 tests/custom/permutations/22_tagged_ints/int/factorial/0003_const_tagged_works/stdout.expected create mode 100644 tests/custom/permutations/22_tagged_ints/int/geq/0003_const_tagged_works/stdout.expected create mode 100644 tests/custom/permutations/22_tagged_ints/int/leq/0003_const_tagged_works/stdout.expected create mode 100644 tests/custom/permutations/22_tagged_ints/int/lt/0003_const_tagged_works/stdout.expected create mode 100644 tests/custom/permutations/22_tagged_ints/int/max/0001_same_tags_work/stdout.expected create mode 100644 tests/custom/permutations/22_tagged_ints/int/max/0003_const_tagged_works/stdout.expected create mode 100644 tests/custom/permutations/22_tagged_ints/int/min/0001_same_tags_work/stdout.expected create mode 100644 tests/custom/permutations/22_tagged_ints/int/min/0003_const_tagged_works/stdout.expected create mode 100644 tests/custom/permutations/22_tagged_ints/int/minus/0001_same_tags_works/stdout.expected create mode 100644 tests/custom/permutations/22_tagged_ints/int/minus/0003_const_tagged_works/stdout.expected create mode 100644 tests/custom/permutations/22_tagged_ints/int/mod/0001_same_tags_works/stdout.expected create mode 100644 tests/custom/permutations/22_tagged_ints/int/mod/0003_const_tagged_works/stdout.expected create mode 100644 tests/custom/permutations/22_tagged_ints/int/neg/0001_same_tags_works/stdout.expected create mode 100644 tests/custom/permutations/22_tagged_ints/int/neg/0003_const_tagged_works/stdout.expected create mode 100644 tests/custom/permutations/22_tagged_ints/int/pred/0003_const_tagged_works/stdout.expected create mode 100644 tests/custom/permutations/22_tagged_ints/int/prod/0001_same_tags_works/stdout.expected create mode 100644 tests/custom/permutations/22_tagged_ints/int/prod/0003_const_tagged_works/stdout.expected create mode 100644 tests/custom/permutations/22_tagged_ints/int/succ/0003_const_tagged_works/stdout.expected create mode 100644 tests/custom/permutations/22_tagged_ints/int/sum/0001_same_tags_works/stdout.expected create mode 100644 tests/custom/permutations/22_tagged_ints/int/sum/0003_const_tagged_works/stdout.expected rename tests/exhaustive/basic/enum05-unnamed/expected/{model_3-solution000001.solution => model_3_1-solution000001.solution} (100%) rename tests/exhaustive/basic/enum05-unnamed/expected/{model_3-solution000002.solution => model_3_1-solution000002.solution} (100%) rename tests/exhaustive/basic/enum05-unnamed/expected/{model_3-solution000003.solution => model_3_1-solution000003.solution} (100%) rename tests/exhaustive/basic/enum05-unnamed/expected/{model_3-solution000004.solution => model_3_1-solution000004.solution} (100%) rename tests/exhaustive/basic/enum05-unnamed/expected/{model_3.eprime => model_3_1.eprime} (100%) rename tests/exhaustive/basic/enum05-unnamed/expected/{model_4-solution000001.solution => model_4_1-solution000001.solution} (100%) rename tests/exhaustive/basic/enum05-unnamed/expected/{model_4-solution000002.solution => model_4_1-solution000002.solution} (100%) rename tests/exhaustive/basic/enum05-unnamed/expected/{model_4-solution000003.solution => model_4_1-solution000003.solution} (100%) rename tests/exhaustive/basic/enum05-unnamed/expected/{model_4-solution000004.solution => model_4_1-solution000004.solution} (100%) rename tests/exhaustive/basic/enum05-unnamed/expected/{model_4.eprime => model_4_1.eprime} (100%) delete mode 100644 tests/exhaustive/issues/263/_old_issues_262.essence delete mode 100644 tests/exhaustive/issues/263/expected/model-p2-solution000001.solution delete mode 100644 tests/exhaustive/issues/263/expected/model-p2.eprime-param delete mode 100644 tests/exhaustive/issues/263/expected/model.eprime delete mode 100644 tests/exhaustive/issues/263/p2.param diff --git a/tests/custom/basic/streamline01/stdout.expected b/tests/custom/basic/streamline01/stdout.expected index fe8e2f0e79..05312d3a33 100644 --- a/tests/custom/basic/streamline01/stdout.expected +++ b/tests/custom/basic/streamline01/stdout.expected @@ -83,18 +83,6 @@ model000003-solution000005.eprime-solution model000003-solution000005.solution model000003-solution000006.eprime-solution model000003-solution000006.solution -model000003-solution000007.eprime-solution -model000003-solution000007.solution -model000003-solution000008.eprime-solution -model000003-solution000008.solution -model000003-solution000009.eprime-solution -model000003-solution000009.solution -model000003-solution000010.eprime-solution -model000003-solution000010.solution -model000003-solution000011.eprime-solution -model000003-solution000011.solution -model000003-solution000012.eprime-solution -model000003-solution000012.solution model000003.eprime model000003.eprime-info model000003.eprime-infor @@ -112,18 +100,6 @@ model000004-solution000005.eprime-solution model000004-solution000005.solution model000004-solution000006.eprime-solution model000004-solution000006.solution -model000004-solution000007.eprime-solution -model000004-solution000007.solution -model000004-solution000008.eprime-solution -model000004-solution000008.solution -model000004-solution000009.eprime-solution -model000004-solution000009.solution -model000004-solution000010.eprime-solution -model000004-solution000010.solution -model000004-solution000011.eprime-solution -model000004-solution000011.solution -model000004-solution000012.eprime-solution -model000004-solution000012.solution model000004.eprime model000004.eprime-info model000004.eprime-infor @@ -177,51 +153,27 @@ conjure-output/model000002-solution000011.solution:letting f be function(1 --> 2 conjure-output/model000002-solution000011.solution:letting s be {1} conjure-output/model000002-solution000012.solution:letting f be function(1 --> 2, 2 --> 2) conjure-output/model000002-solution000012.solution:letting s be {2} -conjure-output/model000003-solution000001.solution:letting f be function(2 --> 1) -conjure-output/model000003-solution000001.solution:letting s be {2} -conjure-output/model000003-solution000002.solution:letting f be function(2 --> 2) -conjure-output/model000003-solution000002.solution:letting s be {2} -conjure-output/model000003-solution000003.solution:letting f be function(1 --> 1) +conjure-output/model000003-solution000001.solution:letting f be function(1 --> 1) +conjure-output/model000003-solution000001.solution:letting s be {1} +conjure-output/model000003-solution000002.solution:letting f be function(1 --> 2) +conjure-output/model000003-solution000002.solution:letting s be {1} +conjure-output/model000003-solution000003.solution:letting f be function(1 --> 1, 2 --> 1) conjure-output/model000003-solution000003.solution:letting s be {1} -conjure-output/model000003-solution000004.solution:letting f be function(1 --> 2) +conjure-output/model000003-solution000004.solution:letting f be function(1 --> 1, 2 --> 2) conjure-output/model000003-solution000004.solution:letting s be {1} -conjure-output/model000003-solution000005.solution:letting f be function(1 --> 1, 2 --> 1) -conjure-output/model000003-solution000005.solution:letting s be {2} -conjure-output/model000003-solution000006.solution:letting f be function(1 --> 1, 2 --> 1) +conjure-output/model000003-solution000005.solution:letting f be function(1 --> 2, 2 --> 1) +conjure-output/model000003-solution000005.solution:letting s be {1} +conjure-output/model000003-solution000006.solution:letting f be function(1 --> 2, 2 --> 2) conjure-output/model000003-solution000006.solution:letting s be {1} -conjure-output/model000003-solution000007.solution:letting f be function(1 --> 1, 2 --> 2) -conjure-output/model000003-solution000007.solution:letting s be {2} -conjure-output/model000003-solution000008.solution:letting f be function(1 --> 1, 2 --> 2) -conjure-output/model000003-solution000008.solution:letting s be {1} -conjure-output/model000003-solution000009.solution:letting f be function(1 --> 2, 2 --> 1) -conjure-output/model000003-solution000009.solution:letting s be {2} -conjure-output/model000003-solution000010.solution:letting f be function(1 --> 2, 2 --> 1) -conjure-output/model000003-solution000010.solution:letting s be {1} -conjure-output/model000003-solution000011.solution:letting f be function(1 --> 2, 2 --> 2) -conjure-output/model000003-solution000011.solution:letting s be {2} -conjure-output/model000003-solution000012.solution:letting f be function(1 --> 2, 2 --> 2) -conjure-output/model000003-solution000012.solution:letting s be {1} -conjure-output/model000004-solution000001.solution:letting f be function(2 --> 1) -conjure-output/model000004-solution000001.solution:letting s be {2} -conjure-output/model000004-solution000002.solution:letting f be function(2 --> 2) -conjure-output/model000004-solution000002.solution:letting s be {2} -conjure-output/model000004-solution000003.solution:letting f be function(1 --> 1) +conjure-output/model000004-solution000001.solution:letting f be function(1 --> 1) +conjure-output/model000004-solution000001.solution:letting s be {1} +conjure-output/model000004-solution000002.solution:letting f be function(1 --> 1, 2 --> 1) +conjure-output/model000004-solution000002.solution:letting s be {1} +conjure-output/model000004-solution000003.solution:letting f be function(1 --> 1, 2 --> 2) conjure-output/model000004-solution000003.solution:letting s be {1} -conjure-output/model000004-solution000004.solution:letting f be function(1 --> 1, 2 --> 1) -conjure-output/model000004-solution000004.solution:letting s be {2} -conjure-output/model000004-solution000005.solution:letting f be function(1 --> 1, 2 --> 1) +conjure-output/model000004-solution000004.solution:letting f be function(1 --> 2) +conjure-output/model000004-solution000004.solution:letting s be {1} +conjure-output/model000004-solution000005.solution:letting f be function(1 --> 2, 2 --> 1) conjure-output/model000004-solution000005.solution:letting s be {1} -conjure-output/model000004-solution000006.solution:letting f be function(1 --> 1, 2 --> 2) -conjure-output/model000004-solution000006.solution:letting s be {2} -conjure-output/model000004-solution000007.solution:letting f be function(1 --> 1, 2 --> 2) -conjure-output/model000004-solution000007.solution:letting s be {1} -conjure-output/model000004-solution000008.solution:letting f be function(1 --> 2) -conjure-output/model000004-solution000008.solution:letting s be {1} -conjure-output/model000004-solution000009.solution:letting f be function(1 --> 2, 2 --> 1) -conjure-output/model000004-solution000009.solution:letting s be {2} -conjure-output/model000004-solution000010.solution:letting f be function(1 --> 2, 2 --> 1) -conjure-output/model000004-solution000010.solution:letting s be {1} -conjure-output/model000004-solution000011.solution:letting f be function(1 --> 2, 2 --> 2) -conjure-output/model000004-solution000011.solution:letting s be {2} -conjure-output/model000004-solution000012.solution:letting f be function(1 --> 2, 2 --> 2) -conjure-output/model000004-solution000012.solution:letting s be {1} +conjure-output/model000004-solution000006.solution:letting f be function(1 --> 2, 2 --> 2) +conjure-output/model000004-solution000006.solution:letting s be {1} diff --git a/tests/custom/ide/dump-repr/stdout.expected b/tests/custom/ide/dump-repr/stdout.expected index d1f69f1115..6df3a41bcb 100644 --- a/tests/custom/ide/dump-repr/stdout.expected +++ b/tests/custom/ide/dump-repr/stdout.expected @@ -109,4 +109,4 @@ {"answer": 32, "description": "set {ExplicitVarSizeWithFlags} (maxSize 1) of set {ExplicitVarSizeWithFlags} (maxSize 1) of set {ExplicitVarSizeWithFlags} (maxSize 1) of set {ExplicitVarSizeWithFlags} (maxSize 1) of int(1..n)"}]}, - {"name": "c_EnumSize", "representations": [{"answer": 1, "description": "int"}]}] + {"name": "c_EnumSize", "representations": [{"answer": 1, "description": "int:c"}]}] diff --git a/tests/custom/issues/395/stdout.expected b/tests/custom/issues/395/stdout.expected index 7b4a9e0dbc..c2ecde6bae 100644 --- a/tests/custom/issues/395/stdout.expected +++ b/tests/custom/issues/395/stdout.expected @@ -9,16 +9,24 @@ find conjure_aux1_ExplicitBounded_Values: matrix indexed by [int(m), matrix indexed by [int(1..m)] of int(0..m), int(1..m)] of int(1..m) branching on [Cs_ExplicitBounded_Length, Cs_ExplicitBounded_Values] such that - and([and([conjure_aux1_ExplicitBounded_Values[q3 - 1] < conjure_aux1_ExplicitBounded_Values[q3] /\ q3 <= m /\ - q3 - 1 <= m + and([and([conjure_aux1_ExplicitBounded_Values[m, Cz_ExplicitBounded_Values, q3 - 1] < + conjure_aux1_ExplicitBounded_Values[m, Cz_ExplicitBounded_Values, q3] + /\ q3 <= m + /\ q3 - 1 <= m | q3 : int(2..m), q3 <= m]) | Cz_ExplicitBounded_Values : matrix indexed by [int(1..m)] of int(0..m)]), and([true | Cz_ExplicitBounded_Values : matrix indexed by [int(1..m)] of int(0..m)]), - or([and([Cz_ExplicitBounded_Values[q5] = Cs_ExplicitBounded_Values[conjure_aux1_ExplicitBounded_Values[q5]] /\ - q5 <= m - /\ (conjure_aux1_ExplicitBounded_Values[q5] <= m /\ q5 <= m) + or([and([Cz_ExplicitBounded_Values[q5] = + Cs_ExplicitBounded_Values[conjure_aux1_ExplicitBounded_Values[m, Cz_ExplicitBounded_Values, q5]] + /\ q5 <= m + /\ (conjure_aux1_ExplicitBounded_Values[m, Cz_ExplicitBounded_Values, q5] <= m /\ q5 <= m) | q5 : int(1..m), q5 <= m]) | Cz_ExplicitBounded_Values : matrix indexed by [int(1..m)] of int(0..m)]) + \/ + or([and([dontCare(conjure_aux1_ExplicitBounded_Length[m, q7]) | q7 : matrix indexed by [int(1..m)] of int(0..m)]) /\ + and([dontCare(conjure_aux1_ExplicitBounded_Values[m, q10, q11]) + | q10 : matrix indexed by [int(1..m)] of int(0..m), q11 : int(1..m)]) + | Cz_ExplicitBounded_Values : matrix indexed by [int(1..m)] of int(0..m)]) language ESSENCE' 1.0 @@ -38,11 +46,17 @@ such that | q3 : int(2..m), q3 <= m]) | Cs_ExplicitBounded_Values : matrix indexed by [int(1..m)] of int(0..m)]), and([true | Cs_ExplicitBounded_Values : matrix indexed by [int(1..m)] of int(0..m)]), - or([and([Cz_ExplicitBounded_Values[q5] = Cs_ExplicitBounded_Values[conjure_aux1_ExplicitBounded_Values[q5]] /\ - q5 <= m - /\ (conjure_aux1_ExplicitBounded_Values[q5] <= m /\ q5 <= m) + or([and([Cz_ExplicitBounded_Values[q5] = + Cs_ExplicitBounded_Values[conjure_aux1_ExplicitBounded_Values[m, Cs_ExplicitBounded_Values, q5]] + /\ q5 <= m + /\ (conjure_aux1_ExplicitBounded_Values[m, Cs_ExplicitBounded_Values, q5] <= m /\ q5 <= m) | q5 : int(1..m), q5 <= m]) | Cs_ExplicitBounded_Values : matrix indexed by [int(1..m)] of int(0..m)]) + \/ + or([and([dontCare(conjure_aux1_ExplicitBounded_Length[m, q7]) | q7 : matrix indexed by [int(1..m)] of int(0..m)]) /\ + and([dontCare(conjure_aux1_ExplicitBounded_Values[m, q10, q11]) + | q10 : matrix indexed by [int(1..m)] of int(0..m), q11 : int(1..m)]) + | Cs_ExplicitBounded_Values : matrix indexed by [int(1..m)] of int(0..m)]) language ESSENCE' 1.0 diff --git a/tests/custom/issues/432/stderr.expected b/tests/custom/issues/432/stderr.expected index 91e15bdf1a..7881b76c7b 100644 --- a/tests/custom/issues/432/stderr.expected +++ b/tests/custom/issues/432/stderr.expected @@ -1,6 +1,7 @@ Error: The value is not a member of the domain. - Value : relation((1, 2)) - Domain: relation {RelationAsSet[Explicit]} (size 1, irreflexive, symmetric) of (int(1..2) * int(1..2)) + Value : relation((1:countries, 2:countries)) + Domain: relation {RelationAsSet[Explicit]} (size 1, irreflexive, symmetric) of + (int:countries(1:countries..2) * int:countries(1:countries..2)) Reason: Domain attributes are not satisfied. Specifically: symmetric diff --git a/tests/custom/issues/440/stderr.expected b/tests/custom/issues/440/stderr.expected index 48db4e5259..748a3909e0 100644 --- a/tests/custom/issues/440/stderr.expected +++ b/tests/custom/issues/440/stderr.expected @@ -3,4 +3,4 @@ Error: Bindings in context: my_function: function(E3 --> 1) my_enum_EnumSize: 2 - my_enum: `int(1..2)` + my_enum: `int:my_enum(1:my_enum..2:my_enum)` diff --git a/tests/custom/paramgen/record01/problem-instanceGenerator.essence b/tests/custom/paramgen/record01/problem-instanceGenerator.essence deleted file mode 100644 index 02cd67f85b..0000000000 --- a/tests/custom/paramgen/record01/problem-instanceGenerator.essence +++ /dev/null @@ -1,161 +0,0 @@ -language Essence 1.3 - -given minid_aircraft_min: int(0..100) -given minid_aircraft_max: int(0..100) -find minid_aircraft: int(0..100) -such that - minid_aircraft >= minid_aircraft_min, - minid_aircraft <= minid_aircraft_max -given maxid_aircraft_min: int(0..100) -given maxid_aircraft_max: int(0..100) -find maxid_aircraft: int(0..100) -such that - maxid_aircraft >= maxid_aircraft_min, - maxid_aircraft <= maxid_aircraft_max -given minid_person_min: int(0..100) -given minid_person_max: int(0..100) -find minid_person: int(0..100) -such that - minid_person >= minid_person_min, - minid_person <= minid_person_max -given maxid_person_min: int(0..100) -given maxid_person_max: int(0..100) -find maxid_person: int(0..100) -such that - maxid_person >= maxid_person_min, - maxid_person <= maxid_person_max -given minid_city_min: int(0..100) -given minid_city_max: int(0..100) -find minid_city: int(0..100) -such that - minid_city >= minid_city_min, - minid_city <= minid_city_max -given maxid_city_min: int(0..100) -given maxid_city_max: int(0..100) -find maxid_city: int(0..100) -such that - maxid_city >= maxid_city_min, - maxid_city <= maxid_city_max -given init_at__percentage_min: int(0..100) -given init_at__percentage_max: int(0..100) -given init_in__percentage_min: int(0..100) -given init_in__percentage_max: int(0..100) -given init_fuel_range_min: int(-65536..65536) -given init_fuel_range_max: int(-65536..65536) -given init_distance_range_min: int(-65536..65536) -given init_distance_range_max: int(-65536..65536) -given init_capacity_range_min: int(-65536..65536) -given init_capacity_range_max: int(-65536..65536) -given init_onboard_range_min: int(-65536..65536) -given init_onboard_range_max: int(-65536..65536) -given init_total_fuel_used_range_min: int(-65536..65536) -given init_total_fuel_used_range_max: int(-65536..65536) -find init: - record {at_ : function (int(0..100), int(0..100)) --> bool, in_ : function (int(0..100), int(0..100)) --> bool, - fuel : function int(0..100) --> int(-65536..65536), - distance : function (int(0..100), int(0..100)) --> int(-65536..65536), - capacity : function int(0..100) --> int(-65536..65536), - onboard : function int(0..100) --> int(-65536..65536), - total_fuel_used : function int(0) --> int(-65536..65536)} -such that - and([q1[1] >= minid_aircraft /\ q1[1] <= maxid_person /\ (q1[2] >= minid_city /\ q1[2] <= maxid_city) <-> - q1 in defined(init[at_]) - | q1 : (int(0..100), int(0..100))]), - sum([toInt(q1[2]) | q1 <- init[at_]]) <= init_at__percentage_max * |defined(init[at_])| / 100 /\ - sum([toInt(q1[2]) | q1 <- init[at_]]) >= init_at__percentage_min * |defined(init[at_])| / 100, - and([q2[1] >= minid_person /\ q2[1] <= maxid_person /\ (q2[2] >= minid_aircraft /\ q2[2] <= maxid_aircraft) <-> - q2 in defined(init[in_]) - | q2 : (int(0..100), int(0..100))]), - sum([toInt(q2[2]) | q2 <- init[in_]]) <= init_in__percentage_max * |defined(init[in_])| / 100 /\ - sum([toInt(q2[2]) | q2 <- init[in_]]) >= init_in__percentage_min * |defined(init[in_])| / 100, - and([q3 >= minid_aircraft /\ q3 <= maxid_aircraft <-> q3 in defined(init[fuel]) | q3 : int(0..100)]), - and([q3[2] >= init_fuel_range_min | q3 <- init[fuel]]), - and([q3[2] <= init_fuel_range_max | q3 <- init[fuel]]), - and([q4[1] >= minid_city /\ q4[1] <= maxid_city /\ (q4[2] >= minid_city /\ q4[2] <= maxid_city) <-> - q4 in defined(init[distance]) - | q4 : (int(0..100), int(0..100))]), - and([q4[2] >= init_distance_range_min | q4 <- init[distance]]), - and([q4[2] <= init_distance_range_max | q4 <- init[distance]]), - and([q5 >= minid_aircraft /\ q5 <= maxid_aircraft <-> q5 in defined(init[capacity]) | q5 : int(0..100)]), - and([q5[2] >= init_capacity_range_min | q5 <- init[capacity]]), - and([q5[2] <= init_capacity_range_max | q5 <- init[capacity]]), - and([q6 >= minid_aircraft /\ q6 <= maxid_aircraft <-> q6 in defined(init[onboard]) | q6 : int(0..100)]), - and([q6[2] >= init_onboard_range_min | q6 <- init[onboard]]), - and([q6[2] <= init_onboard_range_max | q6 <- init[onboard]]), - and([q7 >= 0 /\ q7 <= 0 <-> q7 in defined(init[total_fuel_used]) | q7 : int(0)]), - and([q7[2] >= init_total_fuel_used_range_min | q7 <- init[total_fuel_used]]), - and([q7[2] <= init_total_fuel_used_range_max | q7 <- init[total_fuel_used]]) -such that - and([image(init[fuel], a) > 0 /\ image(init[fuel], a) <= image(init[capacity], a) - | a : int(0..100), a >= minid_aircraft, a <= maxid_aircraft]), - and([image(init[onboard], a) = sum([toInt(value) | ((_, p2), value) <- init[in_], p2 = a]) - | a : int(0..100), a >= minid_aircraft, a <= maxid_aircraft]), - image(init[total_fuel_used], 0) = 0, - and([and([image(init[distance], (c1, c2)) = image(init[distance], (c2, c1)) /\ image(init[distance], (c1, c2)) > 0 - | c2 : int(0..100), c2 >= minid_city, c2 <= maxid_city]) - | c1 : int(0..100), c1 >= minid_city, c1 <= maxid_city]), - and([1 = sum([toInt(value = true) | ((p1, _), value) <- init[at_], p1 = a]) - | a : int(0..100), a >= minid_aircraft, a <= maxid_aircraft]), - and([!(1 = sum([toInt(value = true) | ((p1, _), value) <- init[at_], p = p1]) /\ - 1 = sum([toInt(value = true) | ((p1, _), value) <- init[in_], p = p1])) - /\ - (1 = sum([toInt(value = true) | ((p1, _), value) <- init[at_], p = p1]) \/ - 1 = sum([toInt(value = true) | ((p1, _), value) <- init[in_], p = p1])) - | p : int(0..100), p >= minid_person, p <= maxid_person]) -given goal_at__cardMin: int(0..10201) -given goal_at__cardMax: int(0..10201) -given goal_at__defined_tuple1_min: int(0..100) -given goal_at__defined_tuple1_max: int(0..100) -given goal_at__defined_tuple2_min: int(0..100) -given goal_at__defined_tuple2_max: int(0..100) -given goal_at__percentage_min: int(0..100) -given goal_at__percentage_max: int(0..100) -given goal_in__cardMin: int(0..10201) -given goal_in__cardMax: int(0..10201) -given goal_in__defined_tuple1_min: int(0..100) -given goal_in__defined_tuple1_max: int(0..100) -given goal_in__defined_tuple2_min: int(0..100) -given goal_in__defined_tuple2_max: int(0..100) -given goal_in__percentage_min: int(0..100) -given goal_in__percentage_max: int(0..100) -given goal_onboard_cardMin: int(0..101) -given goal_onboard_cardMax: int(0..101) -given goal_onboard_defined_min: int(0..100) -given goal_onboard_defined_max: int(0..100) -given goal_onboard_range_min: int(-65536..65536) -given goal_onboard_range_max: int(-65536..65536) -find goal: - record {at_ : function (maxSize 100) (int(0..100), int(0..100)) --> bool, - in_ : function (maxSize 100) (int(0..100), int(0..100)) --> bool, - onboard : function (maxSize 100) int(0..100) --> int(-65536..65536)} -such that - |goal[at_]| >= goal_at__cardMin /\ |goal[at_]| <= goal_at__cardMax, - and([q8[1, 1] >= goal_at__defined_tuple1_min | q8 <- goal[at_]]), - and([q8[1, 1] <= goal_at__defined_tuple1_max | q8 <- goal[at_]]), - and([q8[1, 1] >= minid_aircraft | q8 <- goal[at_]]), - and([q8[1, 1] <= maxid_person | q8 <- goal[at_]]), - and([q8[1, 2] >= goal_at__defined_tuple2_min | q8 <- goal[at_]]), - and([q8[1, 2] <= goal_at__defined_tuple2_max | q8 <- goal[at_]]), - and([q8[1, 2] >= minid_city | q8 <- goal[at_]]), - and([q8[1, 2] <= maxid_city | q8 <- goal[at_]]), - sum([toInt(q8[2]) | q8 <- goal[at_]]) <= goal_at__percentage_max * |defined(goal[at_])| / 100 /\ - sum([toInt(q8[2]) | q8 <- goal[at_]]) >= goal_at__percentage_min * |defined(goal[at_])| / 100, - |goal[in_]| >= goal_in__cardMin /\ |goal[in_]| <= goal_in__cardMax, - and([q9[1, 1] >= goal_in__defined_tuple1_min | q9 <- goal[in_]]), - and([q9[1, 1] <= goal_in__defined_tuple1_max | q9 <- goal[in_]]), - and([q9[1, 1] >= minid_person | q9 <- goal[in_]]), - and([q9[1, 1] <= maxid_person | q9 <- goal[in_]]), - and([q9[1, 2] >= goal_in__defined_tuple2_min | q9 <- goal[in_]]), - and([q9[1, 2] <= goal_in__defined_tuple2_max | q9 <- goal[in_]]), - and([q9[1, 2] >= minid_aircraft | q9 <- goal[in_]]), - and([q9[1, 2] <= maxid_aircraft | q9 <- goal[in_]]), - sum([toInt(q9[2]) | q9 <- goal[in_]]) <= goal_in__percentage_max * |defined(goal[in_])| / 100 /\ - sum([toInt(q9[2]) | q9 <- goal[in_]]) >= goal_in__percentage_min * |defined(goal[in_])| / 100, - |goal[onboard]| >= goal_onboard_cardMin /\ |goal[onboard]| <= goal_onboard_cardMax, - and([q10[1] >= goal_onboard_defined_min | q10 <- goal[onboard]]), - and([q10[1] <= goal_onboard_defined_max | q10 <- goal[onboard]]), - and([q10[1] >= minid_aircraft | q10 <- goal[onboard]]), - and([q10[1] <= maxid_aircraft | q10 <- goal[onboard]]), - and([q10[2] >= goal_onboard_range_min | q10 <- goal[onboard]]), - and([q10[2] <= goal_onboard_range_max | q10 <- goal[onboard]]) -such that and([image(goal[onboard], a) >= 0 | a : int(0..100), a >= minid_aircraft, a <= maxid_aircraft]) diff --git a/tests/custom/paramgen/record01/problem-instanceGenerator.essence.irace b/tests/custom/paramgen/record01/problem-instanceGenerator.essence.irace deleted file mode 100644 index b820e74483..0000000000 --- a/tests/custom/paramgen/record01/problem-instanceGenerator.essence.irace +++ /dev/null @@ -1,48 +0,0 @@ -minid_aircraft_min "-minid_aircraft_min " i (0, 100) -minid_aircraft_max "-minid_aircraft_max " i (0, 100) -maxid_aircraft_min "-maxid_aircraft_min " i (0, 100) -maxid_aircraft_max "-maxid_aircraft_max " i (0, 100) -minid_person_min "-minid_person_min " i (0, 100) -minid_person_max "-minid_person_max " i (0, 100) -maxid_person_min "-maxid_person_min " i (0, 100) -maxid_person_max "-maxid_person_max " i (0, 100) -minid_city_min "-minid_city_min " i (0, 100) -minid_city_max "-minid_city_max " i (0, 100) -maxid_city_min "-maxid_city_min " i (0, 100) -maxid_city_max "-maxid_city_max " i (0, 100) -init_at__percentage_min "-init_at__percentage_min " i (0, 100) -init_at__percentage_max "-init_at__percentage_max " i (0, 100) -init_in__percentage_min "-init_in__percentage_min " i (0, 100) -init_in__percentage_max "-init_in__percentage_max " i (0, 100) -init_fuel_range_min "-init_fuel_range_min " i (-65536, 65536) -init_fuel_range_max "-init_fuel_range_max " i (-65536, 65536) -init_distance_range_min "-init_distance_range_min " i (-65536, 65536) -init_distance_range_max "-init_distance_range_max " i (-65536, 65536) -init_capacity_range_min "-init_capacity_range_min " i (-65536, 65536) -init_capacity_range_max "-init_capacity_range_max " i (-65536, 65536) -init_onboard_range_min "-init_onboard_range_min " i (-65536, 65536) -init_onboard_range_max "-init_onboard_range_max " i (-65536, 65536) -init_total_fuel_used_range_min "-init_total_fuel_used_range_min " i (-65536, 65536) -init_total_fuel_used_range_max "-init_total_fuel_used_range_max " i (-65536, 65536) -goal_at__cardMin "-goal_at__cardMin " i (0, 10201) -goal_at__cardMax "-goal_at__cardMax " i (0, 10201) -goal_at__defined_tuple1_min "-goal_at__defined_tuple1_min " i (0, 100) -goal_at__defined_tuple1_max "-goal_at__defined_tuple1_max " i (0, 100) -goal_at__defined_tuple2_min "-goal_at__defined_tuple2_min " i (0, 100) -goal_at__defined_tuple2_max "-goal_at__defined_tuple2_max " i (0, 100) -goal_at__percentage_min "-goal_at__percentage_min " i (0, 100) -goal_at__percentage_max "-goal_at__percentage_max " i (0, 100) -goal_in__cardMin "-goal_in__cardMin " i (0, 10201) -goal_in__cardMax "-goal_in__cardMax " i (0, 10201) -goal_in__defined_tuple1_min "-goal_in__defined_tuple1_min " i (0, 100) -goal_in__defined_tuple1_max "-goal_in__defined_tuple1_max " i (0, 100) -goal_in__defined_tuple2_min "-goal_in__defined_tuple2_min " i (0, 100) -goal_in__defined_tuple2_max "-goal_in__defined_tuple2_max " i (0, 100) -goal_in__percentage_min "-goal_in__percentage_min " i (0, 100) -goal_in__percentage_max "-goal_in__percentage_max " i (0, 100) -goal_onboard_cardMin "-goal_onboard_cardMin " i (0, 101) -goal_onboard_cardMax "-goal_onboard_cardMax " i (0, 101) -goal_onboard_defined_min "-goal_onboard_defined_min " i (0, 100) -goal_onboard_defined_max "-goal_onboard_defined_max " i (0, 100) -goal_onboard_range_min "-goal_onboard_range_min " i (-65536, 65536) -goal_onboard_range_max "-goal_onboard_range_max " i (-65536, 65536) diff --git a/tests/custom/paramgen/record01/problem-instanceRepair.essence b/tests/custom/paramgen/record01/problem-instanceRepair.essence deleted file mode 100644 index f97f3628f8..0000000000 --- a/tests/custom/paramgen/record01/problem-instanceRepair.essence +++ /dev/null @@ -1,181 +0,0 @@ -language Essence 1.3 - -given minid_aircraft_min: int(0..100) -given minid_aircraft_max: int(0..100) -find repaired_minid_aircraft_min: int(0..100) -find repaired_minid_aircraft_max: int(0..100) -such that repaired_minid_aircraft_min <= repaired_minid_aircraft_max -given maxid_aircraft_min: int(0..100) -given maxid_aircraft_max: int(0..100) -find repaired_maxid_aircraft_min: int(0..100) -find repaired_maxid_aircraft_max: int(0..100) -such that repaired_maxid_aircraft_min <= repaired_maxid_aircraft_max -given minid_person_min: int(0..100) -given minid_person_max: int(0..100) -find repaired_minid_person_min: int(0..100) -find repaired_minid_person_max: int(0..100) -such that repaired_minid_person_min <= repaired_minid_person_max -given maxid_person_min: int(0..100) -given maxid_person_max: int(0..100) -find repaired_maxid_person_min: int(0..100) -find repaired_maxid_person_max: int(0..100) -such that repaired_maxid_person_min <= repaired_maxid_person_max -given minid_city_min: int(0..100) -given minid_city_max: int(0..100) -find repaired_minid_city_min: int(0..100) -find repaired_minid_city_max: int(0..100) -such that repaired_minid_city_min <= repaired_minid_city_max -given maxid_city_min: int(0..100) -given maxid_city_max: int(0..100) -find repaired_maxid_city_min: int(0..100) -find repaired_maxid_city_max: int(0..100) -such that repaired_maxid_city_min <= repaired_maxid_city_max -given init_at__percentage_min: int(0..100) -given init_at__percentage_max: int(0..100) -given init_in__percentage_min: int(0..100) -given init_in__percentage_max: int(0..100) -given init_fuel_range_min: int(-65536..65536) -given init_fuel_range_max: int(-65536..65536) -given init_distance_range_min: int(-65536..65536) -given init_distance_range_max: int(-65536..65536) -given init_capacity_range_min: int(-65536..65536) -given init_capacity_range_max: int(-65536..65536) -given init_onboard_range_min: int(-65536..65536) -given init_onboard_range_max: int(-65536..65536) -given init_total_fuel_used_range_min: int(-65536..65536) -given init_total_fuel_used_range_max: int(-65536..65536) -find repaired_init_at__percentage_min: int(0..100) -find repaired_init_at__percentage_max: int(0..100) -find repaired_init_in__percentage_min: int(0..100) -find repaired_init_in__percentage_max: int(0..100) -find repaired_init_fuel_range_min: int(-65536..65536) -find repaired_init_fuel_range_max: int(-65536..65536) -find repaired_init_distance_range_min: int(-65536..65536) -find repaired_init_distance_range_max: int(-65536..65536) -find repaired_init_capacity_range_min: int(-65536..65536) -find repaired_init_capacity_range_max: int(-65536..65536) -find repaired_init_onboard_range_min: int(-65536..65536) -find repaired_init_onboard_range_max: int(-65536..65536) -find repaired_init_total_fuel_used_range_min: int(-65536..65536) -find repaired_init_total_fuel_used_range_max: int(-65536..65536) -such that - repaired_init_at__percentage_max >= repaired_init_at__percentage_min, - repaired_init_in__percentage_max >= repaired_init_in__percentage_min, - repaired_init_fuel_range_min <= repaired_init_fuel_range_max, - repaired_init_distance_range_min <= repaired_init_distance_range_max, - repaired_init_capacity_range_min <= repaired_init_capacity_range_max, - repaired_init_onboard_range_min <= repaired_init_onboard_range_max, - repaired_init_total_fuel_used_range_min <= repaired_init_total_fuel_used_range_max -given goal_at__cardMin: int(0..10201) -given goal_at__cardMax: int(0..10201) -given goal_at__defined_tuple1_min: int(0..100) -given goal_at__defined_tuple1_max: int(0..100) -given goal_at__defined_tuple2_min: int(0..100) -given goal_at__defined_tuple2_max: int(0..100) -given goal_at__percentage_min: int(0..100) -given goal_at__percentage_max: int(0..100) -given goal_in__cardMin: int(0..10201) -given goal_in__cardMax: int(0..10201) -given goal_in__defined_tuple1_min: int(0..100) -given goal_in__defined_tuple1_max: int(0..100) -given goal_in__defined_tuple2_min: int(0..100) -given goal_in__defined_tuple2_max: int(0..100) -given goal_in__percentage_min: int(0..100) -given goal_in__percentage_max: int(0..100) -given goal_onboard_cardMin: int(0..101) -given goal_onboard_cardMax: int(0..101) -given goal_onboard_defined_min: int(0..100) -given goal_onboard_defined_max: int(0..100) -given goal_onboard_range_min: int(-65536..65536) -given goal_onboard_range_max: int(-65536..65536) -find repaired_goal_at__cardMin: int(0..10201) -find repaired_goal_at__cardMax: int(0..10201) -find repaired_goal_at__defined_tuple1_min: int(0..100) -find repaired_goal_at__defined_tuple1_max: int(0..100) -find repaired_goal_at__defined_tuple2_min: int(0..100) -find repaired_goal_at__defined_tuple2_max: int(0..100) -find repaired_goal_at__percentage_min: int(0..100) -find repaired_goal_at__percentage_max: int(0..100) -find repaired_goal_in__cardMin: int(0..10201) -find repaired_goal_in__cardMax: int(0..10201) -find repaired_goal_in__defined_tuple1_min: int(0..100) -find repaired_goal_in__defined_tuple1_max: int(0..100) -find repaired_goal_in__defined_tuple2_min: int(0..100) -find repaired_goal_in__defined_tuple2_max: int(0..100) -find repaired_goal_in__percentage_min: int(0..100) -find repaired_goal_in__percentage_max: int(0..100) -find repaired_goal_onboard_cardMin: int(0..101) -find repaired_goal_onboard_cardMax: int(0..101) -find repaired_goal_onboard_defined_min: int(0..100) -find repaired_goal_onboard_defined_max: int(0..100) -find repaired_goal_onboard_range_min: int(-65536..65536) -find repaired_goal_onboard_range_max: int(-65536..65536) -such that - repaired_goal_at__cardMin <= repaired_goal_at__cardMax, - (repaired_goal_at__defined_tuple1_max - repaired_goal_at__defined_tuple1_min + 1) * - (repaired_goal_at__defined_tuple2_max - repaired_goal_at__defined_tuple2_min + 1) - >= repaired_goal_at__cardMax, - repaired_goal_at__defined_tuple1_min >= repaired_minid_aircraft_min, - repaired_goal_at__defined_tuple1_max <= repaired_maxid_person_max, - repaired_goal_at__defined_tuple2_min >= repaired_minid_city_min, - repaired_goal_at__defined_tuple2_max <= repaired_maxid_city_max, - repaired_goal_at__percentage_max >= repaired_goal_at__percentage_min, - repaired_goal_at__defined_tuple1_min <= repaired_goal_at__defined_tuple1_max, - repaired_goal_at__defined_tuple2_min <= repaired_goal_at__defined_tuple2_max, - repaired_goal_in__cardMin <= repaired_goal_in__cardMax, - (repaired_goal_in__defined_tuple1_max - repaired_goal_in__defined_tuple1_min + 1) * - (repaired_goal_in__defined_tuple2_max - repaired_goal_in__defined_tuple2_min + 1) - >= repaired_goal_in__cardMax, - repaired_goal_in__defined_tuple1_min >= repaired_minid_person_min, - repaired_goal_in__defined_tuple1_max <= repaired_maxid_person_max, - repaired_goal_in__defined_tuple2_min >= repaired_minid_aircraft_min, - repaired_goal_in__defined_tuple2_max <= repaired_maxid_aircraft_max, - repaired_goal_in__percentage_max >= repaired_goal_in__percentage_min, - repaired_goal_in__defined_tuple1_min <= repaired_goal_in__defined_tuple1_max, - repaired_goal_in__defined_tuple2_min <= repaired_goal_in__defined_tuple2_max, - repaired_goal_onboard_cardMin <= repaired_goal_onboard_cardMax, - repaired_goal_onboard_defined_max - repaired_goal_onboard_defined_min + 1 >= repaired_goal_onboard_cardMax, - repaired_goal_onboard_defined_min >= repaired_minid_aircraft_min, - repaired_goal_onboard_defined_max <= repaired_maxid_aircraft_max, - repaired_goal_onboard_defined_min <= repaired_goal_onboard_defined_max, - repaired_goal_onboard_range_min <= repaired_goal_onboard_range_max -minimising - sum([|repaired_minid_aircraft_min - minid_aircraft_min|, |repaired_minid_aircraft_max - minid_aircraft_max|, - |repaired_maxid_aircraft_min - maxid_aircraft_min|, |repaired_maxid_aircraft_max - maxid_aircraft_max|, - |repaired_minid_person_min - minid_person_min|, |repaired_minid_person_max - minid_person_max|, - |repaired_maxid_person_min - maxid_person_min|, |repaired_maxid_person_max - maxid_person_max|, - |repaired_minid_city_min - minid_city_min|, |repaired_minid_city_max - minid_city_max|, - |repaired_maxid_city_min - maxid_city_min|, |repaired_maxid_city_max - maxid_city_max|, - |repaired_init_at__percentage_min - init_at__percentage_min|, - |repaired_init_at__percentage_max - init_at__percentage_max|, - |repaired_init_in__percentage_min - init_in__percentage_min|, - |repaired_init_in__percentage_max - init_in__percentage_max|, - |repaired_init_fuel_range_min - init_fuel_range_min|, |repaired_init_fuel_range_max - init_fuel_range_max|, - |repaired_init_distance_range_min - init_distance_range_min|, - |repaired_init_distance_range_max - init_distance_range_max|, - |repaired_init_capacity_range_min - init_capacity_range_min|, - |repaired_init_capacity_range_max - init_capacity_range_max|, - |repaired_init_onboard_range_min - init_onboard_range_min|, - |repaired_init_onboard_range_max - init_onboard_range_max|, - |repaired_init_total_fuel_used_range_min - init_total_fuel_used_range_min|, - |repaired_init_total_fuel_used_range_max - init_total_fuel_used_range_max|, - |repaired_goal_at__cardMin - goal_at__cardMin|, |repaired_goal_at__cardMax - goal_at__cardMax|, - |repaired_goal_at__defined_tuple1_min - goal_at__defined_tuple1_min|, - |repaired_goal_at__defined_tuple1_max - goal_at__defined_tuple1_max|, - |repaired_goal_at__defined_tuple2_min - goal_at__defined_tuple2_min|, - |repaired_goal_at__defined_tuple2_max - goal_at__defined_tuple2_max|, - |repaired_goal_at__percentage_min - goal_at__percentage_min|, - |repaired_goal_at__percentage_max - goal_at__percentage_max|, |repaired_goal_in__cardMin - goal_in__cardMin|, - |repaired_goal_in__cardMax - goal_in__cardMax|, - |repaired_goal_in__defined_tuple1_min - goal_in__defined_tuple1_min|, - |repaired_goal_in__defined_tuple1_max - goal_in__defined_tuple1_max|, - |repaired_goal_in__defined_tuple2_min - goal_in__defined_tuple2_min|, - |repaired_goal_in__defined_tuple2_max - goal_in__defined_tuple2_max|, - |repaired_goal_in__percentage_min - goal_in__percentage_min|, - |repaired_goal_in__percentage_max - goal_in__percentage_max|, - |repaired_goal_onboard_cardMin - goal_onboard_cardMin|, |repaired_goal_onboard_cardMax - goal_onboard_cardMax|, - |repaired_goal_onboard_defined_min - goal_onboard_defined_min|, - |repaired_goal_onboard_defined_max - goal_onboard_defined_max|, - |repaired_goal_onboard_range_min - goal_onboard_range_min|, - |repaired_goal_onboard_range_max - goal_onboard_range_max|; - int(1..48)]) diff --git a/tests/custom/permutations/12_transform_list/unnamed/0030_find_permutation/stdout.expected b/tests/custom/permutations/12_transform_list/unnamed/0030_find_permutation/stdout.expected index d10ebe7b59..4aafcadbf5 100644 --- a/tests/custom/permutations/12_transform_list/unnamed/0030_find_permutation/stdout.expected +++ b/tests/custom/permutations/12_transform_list/unnamed/0030_find_permutation/stdout.expected @@ -1 +1,13 @@ Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: conjure-output/model000001.eprime +Running minion for domain filtering. +Running solver: minion +Copying solution to: permutation.solution +language Essence 1.3 + +letting n be new type enum {n_1, n_2, n_3, n_4} +letting b be n_3 +letting c be n_4 +letting p be permutation((n_3, n_4)) diff --git a/tests/custom/permutations/14_transform_sequence/int/0010_given_permutation/stdout.expected b/tests/custom/permutations/14_transform_sequence/int/0010_given_permutation/stdout.expected index 3f3613093d..beb3392fd1 100644 --- a/tests/custom/permutations/14_transform_sequence/int/0010_given_permutation/stdout.expected +++ b/tests/custom/permutations/14_transform_sequence/int/0010_given_permutation/stdout.expected @@ -7,4 +7,4 @@ Running solver: minion Copying solution to: permutation-permutation.solution language Essence 1.3 -letting g be sequence(1, 4, 3, 2) +letting g be sequence(1, 2, 3, 4) diff --git a/tests/custom/permutations/14_transform_sequence/int/0020_letting_permutation/stdout.expected b/tests/custom/permutations/14_transform_sequence/int/0020_letting_permutation/stdout.expected index 372662c87a..a0ae78cc76 100644 --- a/tests/custom/permutations/14_transform_sequence/int/0020_letting_permutation/stdout.expected +++ b/tests/custom/permutations/14_transform_sequence/int/0020_letting_permutation/stdout.expected @@ -7,4 +7,4 @@ Running solver: minion Copying solution to: permutation.solution language Essence 1.3 -letting g be sequence(1, 3, 2, 4) +letting g be sequence(1, 2, 3, 4) diff --git a/tests/custom/permutations/14_transform_sequence/int/0030_find_permutation/permutation.essence b/tests/custom/permutations/14_transform_sequence/int/0030_find_permutation/permutation.essence index b2073fd09e..2237575552 100644 --- a/tests/custom/permutations/14_transform_sequence/int/0030_find_permutation/permutation.essence +++ b/tests/custom/permutations/14_transform_sequence/int/0030_find_permutation/permutation.essence @@ -1,8 +1,4 @@ -letting n be 4 - find p : permutation of int(1..4) letting f be sequence(1,2,3,4) -letting g be sequence (4,3,2,1) - -such that g = transform([p],f) - +letting g be sequence(4,3,2,1) +such that g = transform([p],f) diff --git a/tests/custom/permutations/14_transform_sequence/int/0030_find_permutation/stderr.expected b/tests/custom/permutations/14_transform_sequence/int/0030_find_permutation/stderr.expected new file mode 100644 index 0000000000..2a024b8499 --- /dev/null +++ b/tests/custom/permutations/14_transform_sequence/int/0030_find_permutation/stderr.expected @@ -0,0 +1 @@ +cat: conjure-output/*.solution: No such file or directory diff --git a/tests/custom/permutations/14_transform_sequence/int/0030_find_permutation/stdout.expected b/tests/custom/permutations/14_transform_sequence/int/0030_find_permutation/stdout.expected index 1ffbe6f1ca..2a7f0683e7 100644 --- a/tests/custom/permutations/14_transform_sequence/int/0030_find_permutation/stdout.expected +++ b/tests/custom/permutations/14_transform_sequence/int/0030_find_permutation/stdout.expected @@ -4,7 +4,4 @@ Saved under: conjure-output Savile Row: conjure-output/model000001.eprime Running minion for domain filtering. Running solver: minion -Copying solution to: permutation.solution -language Essence 1.3 - -letting p be permutation((1, 4), (2, 3)) +No solutions found. diff --git a/tests/custom/permutations/14_transform_sequence/int/0031_find_permutation/permutation.essence b/tests/custom/permutations/14_transform_sequence/int/0031_find_permutation/permutation.essence new file mode 100644 index 0000000000..f7c8c6c427 --- /dev/null +++ b/tests/custom/permutations/14_transform_sequence/int/0031_find_permutation/permutation.essence @@ -0,0 +1,4 @@ +find p : permutation of int:A(1..4) +letting f be sequence(1:A, 2:A, 3:A, 4:A) +letting g be sequence(4:A, 3:A, 2:A, 1:A) +such that g = transform([p],f) diff --git a/tests/custom/permutations/14_transform_sequence/int/0031_find_permutation/run.sh b/tests/custom/permutations/14_transform_sequence/int/0031_find_permutation/run.sh new file mode 100755 index 0000000000..b4899d6266 --- /dev/null +++ b/tests/custom/permutations/14_transform_sequence/int/0031_find_permutation/run.sh @@ -0,0 +1,3 @@ +conjure solve *.essence +cat conjure-output/*.solution +rm -rf conjure-output *.solution diff --git a/tests/custom/permutations/14_transform_sequence/int/0031_find_permutation/stdout.expected b/tests/custom/permutations/14_transform_sequence/int/0031_find_permutation/stdout.expected new file mode 100644 index 0000000000..19053a3f96 --- /dev/null +++ b/tests/custom/permutations/14_transform_sequence/int/0031_find_permutation/stdout.expected @@ -0,0 +1,10 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: conjure-output/model000001.eprime +Running minion for domain filtering. +Running solver: minion +Copying solution to: permutation.solution +language Essence 1.3 + +letting p be permutation((1:A, 4), (2:A, 3)) diff --git a/tests/custom/permutations/18_transform_matrix/enum/0010_find_permutation_indexing_given_matrix/permutation.essence b/tests/custom/permutations/18_transform_matrix/enum/0010_find_permutation_indexing_given_matrix/permutation.essence index 094dbf5161..66f61aa420 100644 --- a/tests/custom/permutations/18_transform_matrix/enum/0010_find_permutation_indexing_given_matrix/permutation.essence +++ b/tests/custom/permutations/18_transform_matrix/enum/0010_find_permutation_indexing_given_matrix/permutation.essence @@ -4,5 +4,5 @@ find p : permutation of n given s : matrix indexed by [int(1..4)] of n find t : matrix indexed by [int(1..4)] of n -such that e_8 = transform([p],s)[2] /\ t = image(p,s) +such that e_8 = transform([p],s)[2] /\ t = transform([p],s) diff --git a/tests/custom/permutations/18_transform_matrix/enum/0010_find_permutation_indexing_given_matrix/stdout.expected b/tests/custom/permutations/18_transform_matrix/enum/0010_find_permutation_indexing_given_matrix/stdout.expected new file mode 100644 index 0000000000..b22d926132 --- /dev/null +++ b/tests/custom/permutations/18_transform_matrix/enum/0010_find_permutation_indexing_given_matrix/stdout.expected @@ -0,0 +1,11 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: conjure-output/model000001.eprime permutation.param +Running minion for domain filtering. +Running solver: minion +Copying solution to: permutation-permutation.solution +language Essence 1.3 + +letting p be permutation((e_6, e_8, e_7)) +letting t be [e_5, e_8, e_6, e_7; int(1..4)] diff --git a/tests/custom/permutations/18_transform_matrix/enum/0015_find_permutation_indexing_given_matrix/stdout.expected b/tests/custom/permutations/18_transform_matrix/enum/0015_find_permutation_indexing_given_matrix/stdout.expected index d10ebe7b59..f1d96d58e0 100644 --- a/tests/custom/permutations/18_transform_matrix/enum/0015_find_permutation_indexing_given_matrix/stdout.expected +++ b/tests/custom/permutations/18_transform_matrix/enum/0015_find_permutation_indexing_given_matrix/stdout.expected @@ -1 +1,10 @@ Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: conjure-output/model000001.eprime +Running minion for domain filtering. +Running solver: minion +Copying solution to: permutation.solution +language Essence 1.3 + +letting p be permutation((e_6, e_8, e_7)) diff --git a/tests/custom/permutations/18_transform_matrix/enum/0020_given_permutation_and_matrix_find_matrix/stdout.expected b/tests/custom/permutations/18_transform_matrix/enum/0020_given_permutation_and_matrix_find_matrix/stdout.expected index 579caec265..7b3c533f0d 100644 --- a/tests/custom/permutations/18_transform_matrix/enum/0020_given_permutation_and_matrix_find_matrix/stdout.expected +++ b/tests/custom/permutations/18_transform_matrix/enum/0020_given_permutation_and_matrix_find_matrix/stdout.expected @@ -7,4 +7,4 @@ Running solver: minion Copying solution to: permutation-permutation.solution language Essence 1.3 -letting sn be [e_5, e_6, e_7, e_8; int(11..14)] +letting sn be [e_7, e_6, e_5, e_8; int(11..14)] diff --git a/tests/custom/permutations/18_transform_matrix/enum/0030_letting_permutation_given_matrix_find_matrix/stdout.expected b/tests/custom/permutations/18_transform_matrix/enum/0030_letting_permutation_given_matrix_find_matrix/stdout.expected index be922276e3..e590b51ae8 100644 --- a/tests/custom/permutations/18_transform_matrix/enum/0030_letting_permutation_given_matrix_find_matrix/stdout.expected +++ b/tests/custom/permutations/18_transform_matrix/enum/0030_letting_permutation_given_matrix_find_matrix/stdout.expected @@ -7,4 +7,4 @@ Running solver: minion Copying solution to: permutation-permutation.solution language Essence 1.3 -letting sn be [e_5, e_6, e_7, e_8; int(1..4)] +letting sn be [e_7, e_6, e_5, e_8; int(1..4)] diff --git a/tests/custom/permutations/18_transform_matrix/int/0010_find_permutation_indexing_given_matrix/stdout.expected b/tests/custom/permutations/18_transform_matrix/int/0010_find_permutation_indexing_given_matrix/stdout.expected index d10ebe7b59..df49bdaf49 100644 --- a/tests/custom/permutations/18_transform_matrix/int/0010_find_permutation_indexing_given_matrix/stdout.expected +++ b/tests/custom/permutations/18_transform_matrix/int/0010_find_permutation_indexing_given_matrix/stdout.expected @@ -1 +1,10 @@ Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: conjure-output/model000001.eprime permutation.param +Running minion for domain filtering. +Running solver: minion +Copying solution to: permutation-permutation.solution +language Essence 1.3 + +letting p be permutation((2, 3, 4)) diff --git a/tests/custom/permutations/18_transform_matrix/int/0015_find_permutation_indexing_given_matrix/stdout.expected b/tests/custom/permutations/18_transform_matrix/int/0015_find_permutation_indexing_given_matrix/stdout.expected index d10ebe7b59..d1b2b2778d 100644 --- a/tests/custom/permutations/18_transform_matrix/int/0015_find_permutation_indexing_given_matrix/stdout.expected +++ b/tests/custom/permutations/18_transform_matrix/int/0015_find_permutation_indexing_given_matrix/stdout.expected @@ -1 +1,10 @@ Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: conjure-output/model000001.eprime +Running minion for domain filtering. +Running solver: minion +Copying solution to: permutation.solution +language Essence 1.3 + +letting p be permutation((2, 3, 4)) diff --git a/tests/custom/permutations/18_transform_matrix/int/0020_given_permutation_and_matrix_find_matrix/stdout.expected b/tests/custom/permutations/18_transform_matrix/int/0020_given_permutation_and_matrix_find_matrix/stdout.expected index 83e3630454..db47cdfa5d 100644 --- a/tests/custom/permutations/18_transform_matrix/int/0020_given_permutation_and_matrix_find_matrix/stdout.expected +++ b/tests/custom/permutations/18_transform_matrix/int/0020_given_permutation_and_matrix_find_matrix/stdout.expected @@ -7,4 +7,4 @@ Running solver: minion Copying solution to: permutation-permutation.solution language Essence 1.3 -letting sn be [5, 6, 7, 8; int(1..4)] +letting sn be [7, 6, 5, 8; int(1..4)] diff --git a/tests/custom/permutations/18_transform_matrix/int/0030_letting_permutation_given_matrix_find_matrix/stdout.expected b/tests/custom/permutations/18_transform_matrix/int/0030_letting_permutation_given_matrix_find_matrix/stdout.expected index 83e3630454..db47cdfa5d 100644 --- a/tests/custom/permutations/18_transform_matrix/int/0030_letting_permutation_given_matrix_find_matrix/stdout.expected +++ b/tests/custom/permutations/18_transform_matrix/int/0030_letting_permutation_given_matrix_find_matrix/stdout.expected @@ -7,4 +7,4 @@ Running solver: minion Copying solution to: permutation-permutation.solution language Essence 1.3 -letting sn be [5, 6, 7, 8; int(1..4)] +letting sn be [7, 6, 5, 8; int(1..4)] diff --git a/tests/custom/permutations/22_tagged_ints/int/0001_permute_untagged/stdout.expected b/tests/custom/permutations/22_tagged_ints/int/0001_permute_untagged/stdout.expected new file mode 100644 index 0000000000..6166909fe8 --- /dev/null +++ b/tests/custom/permutations/22_tagged_ints/int/0001_permute_untagged/stdout.expected @@ -0,0 +1,11 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: conjure-output/model000001.eprime +Running minion for domain filtering. +Running solver: minion +Copying solution to: permutation.solution +language Essence 1.3 + +letting t be (1, 1) +letting x be (1, 2) diff --git a/tests/custom/permutations/22_tagged_ints/int/0002_permute_tagged/stdout.expected b/tests/custom/permutations/22_tagged_ints/int/0002_permute_tagged/stdout.expected new file mode 100644 index 0000000000..31d414217c --- /dev/null +++ b/tests/custom/permutations/22_tagged_ints/int/0002_permute_tagged/stdout.expected @@ -0,0 +1,11 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: conjure-output/model000001.eprime +Running minion for domain filtering. +Running solver: minion +Copying solution to: permutation.solution +language Essence 1.3 + +letting t be (1, 1) +letting x be (2, 1) diff --git a/tests/custom/permutations/22_tagged_ints/int/0003_tagged_lits_in_param/stdout.expected b/tests/custom/permutations/22_tagged_ints/int/0003_tagged_lits_in_param/stdout.expected new file mode 100644 index 0000000000..0e69863ee2 --- /dev/null +++ b/tests/custom/permutations/22_tagged_ints/int/0003_tagged_lits_in_param/stdout.expected @@ -0,0 +1,11 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: conjure-output/model000001.eprime permutation.param +Running minion for domain filtering. +Running solver: minion +Copying solution to: permutation-permutation.solution +language Essence 1.3 + +letting t be (1, 1) +letting x be (2, 1) diff --git a/tests/custom/permutations/22_tagged_ints/int/div/0001_same_tags_works/stdout.expected b/tests/custom/permutations/22_tagged_ints/int/div/0001_same_tags_works/stdout.expected new file mode 100644 index 0000000000..4948d8fb77 --- /dev/null +++ b/tests/custom/permutations/22_tagged_ints/int/div/0001_same_tags_works/stdout.expected @@ -0,0 +1,11 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: conjure-output/model000001.eprime +Running minion for domain filtering. +Running solver: minion +Copying solution to: permutation.solution +language Essence 1.3 + +letting t be 3 +letting x be 1 diff --git a/tests/custom/permutations/22_tagged_ints/int/div/0003_const_tagged_works/stdout.expected b/tests/custom/permutations/22_tagged_ints/int/div/0003_const_tagged_works/stdout.expected new file mode 100644 index 0000000000..54204f9fd2 --- /dev/null +++ b/tests/custom/permutations/22_tagged_ints/int/div/0003_const_tagged_works/stdout.expected @@ -0,0 +1,10 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: conjure-output/model000001.eprime +Running minion for domain filtering. +Running solver: minion +Copying solution to: permutation.solution +language Essence 1.3 + +letting x be 2 diff --git a/tests/custom/permutations/22_tagged_ints/int/factorial/0003_const_tagged_works/stdout.expected b/tests/custom/permutations/22_tagged_ints/int/factorial/0003_const_tagged_works/stdout.expected new file mode 100644 index 0000000000..3ff49e1811 --- /dev/null +++ b/tests/custom/permutations/22_tagged_ints/int/factorial/0003_const_tagged_works/stdout.expected @@ -0,0 +1,10 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: conjure-output/model000001.eprime +Running minion for domain filtering. +Running solver: minion +Copying solution to: permutation.solution +language Essence 1.3 + +letting x be 6 diff --git a/tests/custom/permutations/22_tagged_ints/int/geq/0003_const_tagged_works/stdout.expected b/tests/custom/permutations/22_tagged_ints/int/geq/0003_const_tagged_works/stdout.expected new file mode 100644 index 0000000000..a2c663db98 --- /dev/null +++ b/tests/custom/permutations/22_tagged_ints/int/geq/0003_const_tagged_works/stdout.expected @@ -0,0 +1,11 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: conjure-output/model000001.eprime +Running minion for domain filtering. +Running solver: minion +Copying solution to: permutation.solution +language Essence 1.3 + +letting x be 1 +letting y be 1 diff --git a/tests/custom/permutations/22_tagged_ints/int/leq/0003_const_tagged_works/stdout.expected b/tests/custom/permutations/22_tagged_ints/int/leq/0003_const_tagged_works/stdout.expected new file mode 100644 index 0000000000..a2c663db98 --- /dev/null +++ b/tests/custom/permutations/22_tagged_ints/int/leq/0003_const_tagged_works/stdout.expected @@ -0,0 +1,11 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: conjure-output/model000001.eprime +Running minion for domain filtering. +Running solver: minion +Copying solution to: permutation.solution +language Essence 1.3 + +letting x be 1 +letting y be 1 diff --git a/tests/custom/permutations/22_tagged_ints/int/lt/0003_const_tagged_works/stdout.expected b/tests/custom/permutations/22_tagged_ints/int/lt/0003_const_tagged_works/stdout.expected new file mode 100644 index 0000000000..86857c3d04 --- /dev/null +++ b/tests/custom/permutations/22_tagged_ints/int/lt/0003_const_tagged_works/stdout.expected @@ -0,0 +1,11 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: conjure-output/model000001.eprime +Running minion for domain filtering. +Running solver: minion +Copying solution to: permutation.solution +language Essence 1.3 + +letting x be 1 +letting y be 2 diff --git a/tests/custom/permutations/22_tagged_ints/int/max/0001_same_tags_work/stdout.expected b/tests/custom/permutations/22_tagged_ints/int/max/0001_same_tags_work/stdout.expected new file mode 100644 index 0000000000..862adac5da --- /dev/null +++ b/tests/custom/permutations/22_tagged_ints/int/max/0001_same_tags_work/stdout.expected @@ -0,0 +1,11 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: conjure-output/model000001.eprime +Running minion for domain filtering. +Running solver: minion +Copying solution to: permutation.solution +language Essence 1.3 + +letting t be {4} +letting x be 4 diff --git a/tests/custom/permutations/22_tagged_ints/int/max/0003_const_tagged_works/stdout.expected b/tests/custom/permutations/22_tagged_ints/int/max/0003_const_tagged_works/stdout.expected new file mode 100644 index 0000000000..9cfd56db52 --- /dev/null +++ b/tests/custom/permutations/22_tagged_ints/int/max/0003_const_tagged_works/stdout.expected @@ -0,0 +1,10 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: conjure-output/model000001.eprime +Running minion for domain filtering. +Running solver: minion +Copying solution to: permutation.solution +language Essence 1.3 + +letting t be {3} diff --git a/tests/custom/permutations/22_tagged_ints/int/min/0001_same_tags_work/stdout.expected b/tests/custom/permutations/22_tagged_ints/int/min/0001_same_tags_work/stdout.expected new file mode 100644 index 0000000000..862adac5da --- /dev/null +++ b/tests/custom/permutations/22_tagged_ints/int/min/0001_same_tags_work/stdout.expected @@ -0,0 +1,11 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: conjure-output/model000001.eprime +Running minion for domain filtering. +Running solver: minion +Copying solution to: permutation.solution +language Essence 1.3 + +letting t be {4} +letting x be 4 diff --git a/tests/custom/permutations/22_tagged_ints/int/min/0003_const_tagged_works/stdout.expected b/tests/custom/permutations/22_tagged_ints/int/min/0003_const_tagged_works/stdout.expected new file mode 100644 index 0000000000..b11ce86e51 --- /dev/null +++ b/tests/custom/permutations/22_tagged_ints/int/min/0003_const_tagged_works/stdout.expected @@ -0,0 +1,10 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: conjure-output/model000001.eprime +Running minion for domain filtering. +Running solver: minion +Copying solution to: permutation.solution +language Essence 1.3 + +letting t be {3:A} diff --git a/tests/custom/permutations/22_tagged_ints/int/minus/0001_same_tags_works/stdout.expected b/tests/custom/permutations/22_tagged_ints/int/minus/0001_same_tags_works/stdout.expected new file mode 100644 index 0000000000..03038bb87f --- /dev/null +++ b/tests/custom/permutations/22_tagged_ints/int/minus/0001_same_tags_works/stdout.expected @@ -0,0 +1,11 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: conjure-output/model000001.eprime +Running minion for domain filtering. +Running solver: minion +Copying solution to: permutation.solution +language Essence 1.3 + +letting t be 5 +letting x be 1 diff --git a/tests/custom/permutations/22_tagged_ints/int/minus/0003_const_tagged_works/stdout.expected b/tests/custom/permutations/22_tagged_ints/int/minus/0003_const_tagged_works/stdout.expected new file mode 100644 index 0000000000..54204f9fd2 --- /dev/null +++ b/tests/custom/permutations/22_tagged_ints/int/minus/0003_const_tagged_works/stdout.expected @@ -0,0 +1,10 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: conjure-output/model000001.eprime +Running minion for domain filtering. +Running solver: minion +Copying solution to: permutation.solution +language Essence 1.3 + +letting x be 2 diff --git a/tests/custom/permutations/22_tagged_ints/int/mod/0001_same_tags_works/stdout.expected b/tests/custom/permutations/22_tagged_ints/int/mod/0001_same_tags_works/stdout.expected new file mode 100644 index 0000000000..ad722b14e1 --- /dev/null +++ b/tests/custom/permutations/22_tagged_ints/int/mod/0001_same_tags_works/stdout.expected @@ -0,0 +1,11 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: conjure-output/model000001.eprime +Running minion for domain filtering. +Running solver: minion +Copying solution to: permutation.solution +language Essence 1.3 + +letting t be 1 +letting x be 1 diff --git a/tests/custom/permutations/22_tagged_ints/int/mod/0003_const_tagged_works/stdout.expected b/tests/custom/permutations/22_tagged_ints/int/mod/0003_const_tagged_works/stdout.expected new file mode 100644 index 0000000000..54204f9fd2 --- /dev/null +++ b/tests/custom/permutations/22_tagged_ints/int/mod/0003_const_tagged_works/stdout.expected @@ -0,0 +1,10 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: conjure-output/model000001.eprime +Running minion for domain filtering. +Running solver: minion +Copying solution to: permutation.solution +language Essence 1.3 + +letting x be 2 diff --git a/tests/custom/permutations/22_tagged_ints/int/neg/0001_same_tags_works/stdout.expected b/tests/custom/permutations/22_tagged_ints/int/neg/0001_same_tags_works/stdout.expected new file mode 100644 index 0000000000..50a3c98efd --- /dev/null +++ b/tests/custom/permutations/22_tagged_ints/int/neg/0001_same_tags_works/stdout.expected @@ -0,0 +1,11 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: conjure-output/model000001.eprime +Running minion for domain filtering. +Running solver: minion +Copying solution to: permutation.solution +language Essence 1.3 + +letting t be -6 +letting x be 6 diff --git a/tests/custom/permutations/22_tagged_ints/int/neg/0003_const_tagged_works/stdout.expected b/tests/custom/permutations/22_tagged_ints/int/neg/0003_const_tagged_works/stdout.expected new file mode 100644 index 0000000000..04d77a8c37 --- /dev/null +++ b/tests/custom/permutations/22_tagged_ints/int/neg/0003_const_tagged_works/stdout.expected @@ -0,0 +1,10 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: conjure-output/model000001.eprime +Running minion for domain filtering. +Running solver: minion +Copying solution to: permutation.solution +language Essence 1.3 + +letting x be -2 diff --git a/tests/custom/permutations/22_tagged_ints/int/pred/0003_const_tagged_works/stdout.expected b/tests/custom/permutations/22_tagged_ints/int/pred/0003_const_tagged_works/stdout.expected new file mode 100644 index 0000000000..86857c3d04 --- /dev/null +++ b/tests/custom/permutations/22_tagged_ints/int/pred/0003_const_tagged_works/stdout.expected @@ -0,0 +1,11 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: conjure-output/model000001.eprime +Running minion for domain filtering. +Running solver: minion +Copying solution to: permutation.solution +language Essence 1.3 + +letting x be 1 +letting y be 2 diff --git a/tests/custom/permutations/22_tagged_ints/int/prod/0001_same_tags_works/stdout.expected b/tests/custom/permutations/22_tagged_ints/int/prod/0001_same_tags_works/stdout.expected new file mode 100644 index 0000000000..595bc344ee --- /dev/null +++ b/tests/custom/permutations/22_tagged_ints/int/prod/0001_same_tags_works/stdout.expected @@ -0,0 +1,11 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: conjure-output/model000001.eprime +Running minion for domain filtering. +Running solver: minion +Copying solution to: permutation.solution +language Essence 1.3 + +letting t be 1 +letting x be 3 diff --git a/tests/custom/permutations/22_tagged_ints/int/prod/0003_const_tagged_works/stdout.expected b/tests/custom/permutations/22_tagged_ints/int/prod/0003_const_tagged_works/stdout.expected new file mode 100644 index 0000000000..3ff49e1811 --- /dev/null +++ b/tests/custom/permutations/22_tagged_ints/int/prod/0003_const_tagged_works/stdout.expected @@ -0,0 +1,10 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: conjure-output/model000001.eprime +Running minion for domain filtering. +Running solver: minion +Copying solution to: permutation.solution +language Essence 1.3 + +letting x be 6 diff --git a/tests/custom/permutations/22_tagged_ints/int/succ/0003_const_tagged_works/stdout.expected b/tests/custom/permutations/22_tagged_ints/int/succ/0003_const_tagged_works/stdout.expected new file mode 100644 index 0000000000..d60672bf1d --- /dev/null +++ b/tests/custom/permutations/22_tagged_ints/int/succ/0003_const_tagged_works/stdout.expected @@ -0,0 +1,11 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: conjure-output/model000001.eprime +Running minion for domain filtering. +Running solver: minion +Copying solution to: permutation.solution +language Essence 1.3 + +letting x be 2 +letting y be 1 diff --git a/tests/custom/permutations/22_tagged_ints/int/sum/0001_same_tags_works/stdout.expected b/tests/custom/permutations/22_tagged_ints/int/sum/0001_same_tags_works/stdout.expected new file mode 100644 index 0000000000..954721844d --- /dev/null +++ b/tests/custom/permutations/22_tagged_ints/int/sum/0001_same_tags_works/stdout.expected @@ -0,0 +1,11 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: conjure-output/model000001.eprime +Running minion for domain filtering. +Running solver: minion +Copying solution to: permutation.solution +language Essence 1.3 + +letting t be 1 +letting x be 5 diff --git a/tests/custom/permutations/22_tagged_ints/int/sum/0003_const_tagged_works/stdout.expected b/tests/custom/permutations/22_tagged_ints/int/sum/0003_const_tagged_works/stdout.expected new file mode 100644 index 0000000000..3ff49e1811 --- /dev/null +++ b/tests/custom/permutations/22_tagged_ints/int/sum/0003_const_tagged_works/stdout.expected @@ -0,0 +1,10 @@ +Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: conjure-output/model000001.eprime +Running minion for domain filtering. +Running solver: minion +Copying solution to: permutation.solution +language Essence 1.3 + +letting x be 6 diff --git a/tests/custom/permutations/23_image_set_dotlt/int/0010_find_perm_find_set/stdout.expected b/tests/custom/permutations/23_image_set_dotlt/int/0010_find_perm_find_set/stdout.expected index d10ebe7b59..e5682b4fb0 100644 --- a/tests/custom/permutations/23_image_set_dotlt/int/0010_find_perm_find_set/stdout.expected +++ b/tests/custom/permutations/23_image_set_dotlt/int/0010_find_perm_find_set/stdout.expected @@ -1 +1,56 @@ Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: conjure-output/model000001.eprime +Running minion for domain filtering. +Running solver: minion +Copying solution to: permutation-000001.solution +Copying solution to: permutation-000002.solution +Copying solution to: permutation-000003.solution +Copying solution to: permutation-000004.solution +Copying solution to: permutation-000005.solution +Copying solution to: permutation-000006.solution +Copying solution to: permutation-000007.solution +Copying solution to: permutation-000008.solution +Copying solution to: permutation-000009.solution +Copying solution to: permutation-000010.solution +language Essence 1.3 + +letting p be permutation((3, 4)) +letting s be {3} +language Essence 1.3 + +letting p be permutation((3, 4)) +letting s be {2, 3} +language Essence 1.3 + +letting p be permutation((3, 4)) +letting s be {1, 3} +language Essence 1.3 + +letting p be permutation((3, 4)) +letting s be {1, 2, 3} +language Essence 1.3 + +letting p be permutation((2, 3)) +letting s be {2} +language Essence 1.3 + +letting p be permutation((2, 3)) +letting s be {2, 4} +language Essence 1.3 + +letting p be permutation((2, 3)) +letting s be {1, 2} +language Essence 1.3 + +letting p be permutation((2, 3)) +letting s be {1, 2, 4} +language Essence 1.3 + +letting p be permutation((2, 3, 4)) +letting s be {3} +language Essence 1.3 + +letting p be permutation((2, 3, 4)) +letting s be {2} diff --git a/tests/custom/permutations/permInverse/06/stderr.expected b/tests/custom/permutations/permInverse/06/stderr.expected index c975823c74..b4c8447b6b 100644 --- a/tests/custom/permutations/permInverse/06/stderr.expected +++ b/tests/custom/permutations/permInverse/06/stderr.expected @@ -1,4 +1,2 @@ Adding the following unnamed symmetry breaking constraints: - such that - and([tuple (x) .<= transform(q1, tuple (x)) - | q1 : permutation of A]) + such that and([x .<= transform([q1], x) | q1 : permutation of A]) diff --git a/tests/custom/permutations/permInverse/07/stderr.expected b/tests/custom/permutations/permInverse/07/stderr.expected index c975823c74..b4c8447b6b 100644 --- a/tests/custom/permutations/permInverse/07/stderr.expected +++ b/tests/custom/permutations/permInverse/07/stderr.expected @@ -1,4 +1,2 @@ Adding the following unnamed symmetry breaking constraints: - such that - and([tuple (x) .<= transform(q1, tuple (x)) - | q1 : permutation of A]) + such that and([x .<= transform([q1], x) | q1 : permutation of A]) diff --git a/tests/custom/permutations/permInverse/09/stderr.expected b/tests/custom/permutations/permInverse/09/stderr.expected index d300ba3836..5554624cc0 100644 --- a/tests/custom/permutations/permInverse/09/stderr.expected +++ b/tests/custom/permutations/permInverse/09/stderr.expected @@ -1,3 +1,3 @@ Adding the following unnamed symmetry breaking constraints: such that - and([(x, y) .<= transform(q1, (x, y)) | q1 : permutation of A]) + and([(x, y) .<= transform([q1], (x, y)) | q1 : permutation of A]) diff --git a/tests/custom/permutations/permInverse/10/stderr.expected b/tests/custom/permutations/permInverse/10/stderr.expected index 747b75eb07..8d19f40fe8 100644 --- a/tests/custom/permutations/permInverse/10/stderr.expected +++ b/tests/custom/permutations/permInverse/10/stderr.expected @@ -1,4 +1,4 @@ Adding the following unnamed symmetry breaking constraints: such that - and([(x, y, z) .<= transform(q1, (x, y, z)) + and([(x, y, z) .<= transform([q1], (x, y, z)) | q1 : permutation of A]) diff --git a/tests/custom/permutations/permInverse/12/stderr.expected b/tests/custom/permutations/permInverse/12/stderr.expected index d300ba3836..5554624cc0 100644 --- a/tests/custom/permutations/permInverse/12/stderr.expected +++ b/tests/custom/permutations/permInverse/12/stderr.expected @@ -1,3 +1,3 @@ Adding the following unnamed symmetry breaking constraints: such that - and([(x, y) .<= transform(q1, (x, y)) | q1 : permutation of A]) + and([(x, y) .<= transform([q1], (x, y)) | q1 : permutation of A]) diff --git a/tests/exhaustive/autogen/gen35/expected/model_1.eprime b/tests/exhaustive/autogen/gen35/expected/model_1.eprime index 0a734c1835..c6c98bcdd4 100644 --- a/tests/exhaustive/autogen/gen35/expected/model_1.eprime +++ b/tests/exhaustive/autogen/gen35/expected/model_1.eprime @@ -29,11 +29,10 @@ such that int(1..2)]) | q1 : int(1..2)]), and([q2 > var2_FunctionAsRelationR8R17_RelationAsSetR8R17_ExplicitVarSizeWithMarkerR8R17_Marker -> - and([and([var2_FunctionAsRelationR8R17_RelationAsSetR8R17_ExplicitVarSizeWithMarkerR8R17_Values_2_RelationAsMatrix - [q2, q27, q28] - = false - | q28 : bool]) - | q27 : bool]) + and([var2_FunctionAsRelationR8R17_RelationAsSetR8R17_ExplicitVarSizeWithMarkerR8R17_Values_2_RelationAsMatrix + [q2, q27, q28] + = false + | q27 : bool, q28 : bool]) | q2 : int(1..3)]), 0 <= var2_FunctionAsRelationR8R17_RelationAsSetR8R17_ExplicitVarSizeWithMarkerR8R17_Marker, var2_FunctionAsRelationR8R17_RelationAsSetR8R17_ExplicitVarSizeWithMarkerR8R17_Marker <= 3, diff --git a/tests/exhaustive/autogen/gen35/expected/model_2.eprime b/tests/exhaustive/autogen/gen35/expected/model_2.eprime index bb62f14b2b..a9ff27e859 100644 --- a/tests/exhaustive/autogen/gen35/expected/model_2.eprime +++ b/tests/exhaustive/autogen/gen35/expected/model_2.eprime @@ -41,11 +41,10 @@ such that [q2] = 0 /\ - and([and([var2_FunctionAsRelationR9R17_RelationAsSetR9R17_ExplicitVarSizeWithMarkerR9R17_Values_2_RelationAsMatrix - [q2, q23, q24] - = false - | q24 : bool]) - | q23 : bool]) + and([var2_FunctionAsRelationR9R17_RelationAsSetR9R17_ExplicitVarSizeWithMarkerR9R17_Values_2_RelationAsMatrix + [q2, q23, q24] + = false + | q23 : bool, q24 : bool]) | q2 : int(1..3)]), 0 <= var2_FunctionAsRelationR9R17_RelationAsSetR9R17_ExplicitVarSizeWithMarkerR9R17_Marker, var2_FunctionAsRelationR9R17_RelationAsSetR9R17_ExplicitVarSizeWithMarkerR9R17_Marker <= 3, diff --git a/tests/exhaustive/basic/enum05-unnamed/expected/model_3-solution000001.solution b/tests/exhaustive/basic/enum05-unnamed/expected/model_3_1-solution000001.solution similarity index 100% rename from tests/exhaustive/basic/enum05-unnamed/expected/model_3-solution000001.solution rename to tests/exhaustive/basic/enum05-unnamed/expected/model_3_1-solution000001.solution diff --git a/tests/exhaustive/basic/enum05-unnamed/expected/model_3-solution000002.solution b/tests/exhaustive/basic/enum05-unnamed/expected/model_3_1-solution000002.solution similarity index 100% rename from tests/exhaustive/basic/enum05-unnamed/expected/model_3-solution000002.solution rename to tests/exhaustive/basic/enum05-unnamed/expected/model_3_1-solution000002.solution diff --git a/tests/exhaustive/basic/enum05-unnamed/expected/model_3-solution000003.solution b/tests/exhaustive/basic/enum05-unnamed/expected/model_3_1-solution000003.solution similarity index 100% rename from tests/exhaustive/basic/enum05-unnamed/expected/model_3-solution000003.solution rename to tests/exhaustive/basic/enum05-unnamed/expected/model_3_1-solution000003.solution diff --git a/tests/exhaustive/basic/enum05-unnamed/expected/model_3-solution000004.solution b/tests/exhaustive/basic/enum05-unnamed/expected/model_3_1-solution000004.solution similarity index 100% rename from tests/exhaustive/basic/enum05-unnamed/expected/model_3-solution000004.solution rename to tests/exhaustive/basic/enum05-unnamed/expected/model_3_1-solution000004.solution diff --git a/tests/exhaustive/basic/enum05-unnamed/expected/model_3.eprime b/tests/exhaustive/basic/enum05-unnamed/expected/model_3_1.eprime similarity index 100% rename from tests/exhaustive/basic/enum05-unnamed/expected/model_3.eprime rename to tests/exhaustive/basic/enum05-unnamed/expected/model_3_1.eprime diff --git a/tests/exhaustive/basic/enum05-unnamed/expected/model_4-solution000001.solution b/tests/exhaustive/basic/enum05-unnamed/expected/model_4_1-solution000001.solution similarity index 100% rename from tests/exhaustive/basic/enum05-unnamed/expected/model_4-solution000001.solution rename to tests/exhaustive/basic/enum05-unnamed/expected/model_4_1-solution000001.solution diff --git a/tests/exhaustive/basic/enum05-unnamed/expected/model_4-solution000002.solution b/tests/exhaustive/basic/enum05-unnamed/expected/model_4_1-solution000002.solution similarity index 100% rename from tests/exhaustive/basic/enum05-unnamed/expected/model_4-solution000002.solution rename to tests/exhaustive/basic/enum05-unnamed/expected/model_4_1-solution000002.solution diff --git a/tests/exhaustive/basic/enum05-unnamed/expected/model_4-solution000003.solution b/tests/exhaustive/basic/enum05-unnamed/expected/model_4_1-solution000003.solution similarity index 100% rename from tests/exhaustive/basic/enum05-unnamed/expected/model_4-solution000003.solution rename to tests/exhaustive/basic/enum05-unnamed/expected/model_4_1-solution000003.solution diff --git a/tests/exhaustive/basic/enum05-unnamed/expected/model_4-solution000004.solution b/tests/exhaustive/basic/enum05-unnamed/expected/model_4_1-solution000004.solution similarity index 100% rename from tests/exhaustive/basic/enum05-unnamed/expected/model_4-solution000004.solution rename to tests/exhaustive/basic/enum05-unnamed/expected/model_4_1-solution000004.solution diff --git a/tests/exhaustive/basic/enum05-unnamed/expected/model_4.eprime b/tests/exhaustive/basic/enum05-unnamed/expected/model_4_1.eprime similarity index 100% rename from tests/exhaustive/basic/enum05-unnamed/expected/model_4.eprime rename to tests/exhaustive/basic/enum05-unnamed/expected/model_4_1.eprime diff --git a/tests/exhaustive/issues/182/expected/model.eprime b/tests/exhaustive/issues/182/expected/model.eprime index 18c701db1d..905808fbb5 100644 --- a/tests/exhaustive/issues/182/expected/model.eprime +++ b/tests/exhaustive/issues/182/expected/model.eprime @@ -44,9 +44,8 @@ such that | q4 : int(1..3)]), and([q5 > p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Marker[q5] = 0 /\ - and([and([p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q5, q16, q17] = - 1 | q17 : int(1..2)]) - | q16 : int(1..4)]) + and([p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Values_ExplicitVarSizeWithMarker_Values[q5, q16, q17] = 1 + | q16 : int(1..4), q17 : int(1..2)]) | q5 : int(1..4)]), p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker <= 4, and([q6 <= p_PartitionAsSet_ExplicitVarSizeWithMarkerR5_Marker -> diff --git a/tests/exhaustive/issues/263/_old_issues_262.essence b/tests/exhaustive/issues/263/_old_issues_262.essence deleted file mode 100644 index 47f5d43ca4..0000000000 --- a/tests/exhaustive/issues/263/_old_issues_262.essence +++ /dev/null @@ -1,12 +0,0 @@ -language Essence 1.3 -$ prob028.essence: Balanced Incomplete Block Design -$ Problem details available at http://www.csplib.org/prob/prob028/ - -given v : int(1..20) - -letting O be new type of size v - -find f : function(total) O --> O - -such that - forAll v : O . f(v) = v diff --git a/tests/exhaustive/issues/263/expected/model-p2-solution000001.solution b/tests/exhaustive/issues/263/expected/model-p2-solution000001.solution deleted file mode 100644 index ac8c733f23..0000000000 --- a/tests/exhaustive/issues/263/expected/model-p2-solution000001.solution +++ /dev/null @@ -1,4 +0,0 @@ -language Essence 1.3 - -letting O be new type enum {O_1, O_2} -letting f be function(O_1 --> O_1, O_2 --> O_2) diff --git a/tests/exhaustive/issues/263/expected/model-p2.eprime-param b/tests/exhaustive/issues/263/expected/model-p2.eprime-param deleted file mode 100644 index 15cca3e147..0000000000 --- a/tests/exhaustive/issues/263/expected/model-p2.eprime-param +++ /dev/null @@ -1,3 +0,0 @@ -language ESSENCE' 1.0 - -letting v be 2 diff --git a/tests/exhaustive/issues/263/expected/model.eprime b/tests/exhaustive/issues/263/expected/model.eprime deleted file mode 100644 index c11a9a4626..0000000000 --- a/tests/exhaustive/issues/263/expected/model.eprime +++ /dev/null @@ -1,7 +0,0 @@ -language ESSENCE' 1.0 - -given v: int(1..20) -find f_Function1D: matrix indexed by [int(1..v)] of int(1..v) -branching on [f_Function1D] -such that and([f_Function1D[shadow2] = shadow2 | shadow2 : int(1..v)]) - diff --git a/tests/exhaustive/issues/263/p2.param b/tests/exhaustive/issues/263/p2.param deleted file mode 100644 index e526c82e18..0000000000 --- a/tests/exhaustive/issues/263/p2.param +++ /dev/null @@ -1,3 +0,0 @@ -language Essence 1.3 - -letting v be 2 diff --git a/tests/exhaustive/mildly_interesting/subsetSum/expected/model_2_2_2.eprime b/tests/exhaustive/mildly_interesting/subsetSum/expected/model_2_2_2.eprime index 627992db38..e242a71db7 100644 --- a/tests/exhaustive/mildly_interesting/subsetSum/expected/model_2_2_2.eprime +++ b/tests/exhaustive/mildly_interesting/subsetSum/expected/model_2_2_2.eprime @@ -20,7 +20,7 @@ such that and([x_ExplicitVarSizeWithFlags_Flags[q2 + 1] -> x_ExplicitVarSizeWithFlags_Values[q2] < x_ExplicitVarSizeWithFlags_Values[q2 + 1] | q2 : int(1..let1 - 1)]), - and([x_ExplicitVarSizeWithFlags_Flags[q3] = false -> dontCare(x_ExplicitVarSizeWithFlags_Values[q3]) + and([x_ExplicitVarSizeWithFlags_Flags[q3] = false -> x_ExplicitVarSizeWithFlags_Values[q3] = min(let2) | q3 : int(1..let1)]), and([x_ExplicitVarSizeWithFlags_Flags[q4 + 1] -> x_ExplicitVarSizeWithFlags_Flags[q4] | q4 : int(1..let1 - 1)]), 1 <= sum([toInt(x_ExplicitVarSizeWithFlags_Flags[q5]) | q5 : int(1..let1)]), diff --git a/tests/parse_print/syntax_test/declarations/unnamed-redefinition/typecheck.expected b/tests/parse_print/syntax_test/declarations/unnamed-redefinition/typecheck.expected index 2e90ed7a58..131dc0ff36 100644 --- a/tests/parse_print/syntax_test/declarations/unnamed-redefinition/typecheck.expected +++ b/tests/parse_print/syntax_test/declarations/unnamed-redefinition/typecheck.expected @@ -1,4 +1,4 @@ Error: Redefinition of name: y2 - When trying to define it as an alias for `int(1..4)` - It was already defined as an alias for `int(1..2)` \ No newline at end of file + When trying to define it as an alias for `int:y2(1..4)` + It was already defined as an alias for `int:y2(1..2)` \ No newline at end of file From bf146356dd210ece4de7a78f52f6fe4f06960832 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?=C3=96zg=C3=BCr=20Akg=C3=BCn?= Date: Mon, 20 Jan 2025 13:24:38 +0000 Subject: [PATCH 226/229] use newtype --- src/Conjure/Language/Domain.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Conjure/Language/Domain.hs b/src/Conjure/Language/Domain.hs index 2c60e9eb91..41ea8cb445 100644 --- a/src/Conjure/Language/Domain.hs +++ b/src/Conjure/Language/Domain.hs @@ -760,7 +760,7 @@ instance Pretty a => Pretty (PartitionAttr a) where -data PermutationAttr a = PermutationAttr +newtype PermutationAttr a = PermutationAttr { numMoved :: SizeAttr a } From dd7d534f098a9b44f3e3e946b9b839efaebd187e Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?=C3=96zg=C3=BCr=20Akg=C3=BCn?= Date: Mon, 20 Jan 2025 14:43:22 +0000 Subject: [PATCH 227/229] swap the order of arguments for quickPermutationOrder --- src/Conjure/Language/Expression/Op.hs | 2 +- .../Expression/Op/QuickPermutationOrder.hs | 14 +++++++------- src/Conjure/Language/Lenses.hs | 18 ++++++++++++++++++ src/Conjure/UI/Model.hs | 4 +--- 4 files changed, 27 insertions(+), 11 deletions(-) diff --git a/src/Conjure/Language/Expression/Op.hs b/src/Conjure/Language/Expression/Op.hs index debb79a372..e355e5f63a 100644 --- a/src/Conjure/Language/Expression/Op.hs +++ b/src/Conjure/Language/Expression/Op.hs @@ -104,7 +104,7 @@ mkOp op xs = case op of (arg xs 1 "allDiffExcept") L_catchUndef -> inject $ MkOpCatchUndef $ OpCatchUndef (arg xs 0 "catchUndef") (arg xs 1 "catchUndef") - L_quickPermutationOrder -> inject $ MkOpQuickPermutationOrder $ OpQuickPermutationOrder (arg xs 0 "quickPermutationOrder") (arg xs 1 "quickPermutationOrder" |> listOut |> fromMaybe (bug "")) + L_quickPermutationOrder -> inject $ MkOpQuickPermutationOrder $ OpQuickPermutationOrder (arg xs 0 "quickPermutationOrder" |> listOut |> fromMaybe (bug "")) (arg xs 1 "quickPermutationOrder") L_dontCare -> inject $ MkOpDontCare $ OpDontCare (arg xs 0 "dontCare") L_toSet -> inject $ MkOpToSet $ OpToSet False (arg xs 0 "toSet") L_toMSet -> inject $ MkOpToMSet $ OpToMSet (arg xs 0 "toMSet") diff --git a/src/Conjure/Language/Expression/Op/QuickPermutationOrder.hs b/src/Conjure/Language/Expression/Op/QuickPermutationOrder.hs index fb40919ba0..dd3503e06f 100644 --- a/src/Conjure/Language/Expression/Op/QuickPermutationOrder.hs +++ b/src/Conjure/Language/Expression/Op/QuickPermutationOrder.hs @@ -11,10 +11,10 @@ import Data.Aeson qualified as JSON -- aeson import Data.Aeson.KeyMap qualified as KM import Data.Vector qualified as V -- vector --- first argument: the value (x) --- second argument: the tuple of permutations to apply (ps) +-- first argument: the tuple of permutations to apply (ps) +-- second argument: the value (x) -- the effect is a subset of: x .<= transform(ps, x) -data OpQuickPermutationOrder x = OpQuickPermutationOrder x [x] +data OpQuickPermutationOrder x = OpQuickPermutationOrder [x] x deriving (Eq, Ord, Show, Data, Functor, Traversable, Foldable, Typeable, Generic) instance (Serialize x) => Serialize (OpQuickPermutationOrder x) @@ -28,7 +28,7 @@ instance (ToJSON x) => ToJSON (OpQuickPermutationOrder x) where instance (FromJSON x) => FromJSON (OpQuickPermutationOrder x) where parseJSON = genericParseJSON jsonOptions instance (TypeOf x, Pretty x, ExpressionLike x) => TypeOf (OpQuickPermutationOrder x) where - typeOf p@(OpQuickPermutationOrder x perms) = do + typeOf p@(OpQuickPermutationOrder perms x) = do _tyX <- typeOf x forM_ perms $ \pe -> do tyP <- typeOf pe @@ -41,14 +41,14 @@ instance SimplifyOp OpQuickPermutationOrder x where simplifyOp _ = na "simplifyOp{OpQuickPermutationOrder}" instance (Pretty x) => Pretty (OpQuickPermutationOrder x) where - prettyPrec _ (OpQuickPermutationOrder a bs) = "quickPermutationOrder" <> prettyList prParens "," (a : bs) + prettyPrec _ (OpQuickPermutationOrder as b) = "quickPermutationOrder" <> prettyList prParens "," (as ++ [b]) instance (VarSymBreakingDescription x, ExpressionLike x) => VarSymBreakingDescription (OpQuickPermutationOrder x) where - varSymBreakingDescription (OpQuickPermutationOrder x ys) = + varSymBreakingDescription (OpQuickPermutationOrder xs y) = JSON.Object $ KM.fromList [ ("type", JSON.String "OpQuickPermutationOrder"), ( "children", - JSON.Array $ V.fromList (varSymBreakingDescription x : map varSymBreakingDescription ys) + JSON.Array $ V.fromList (map varSymBreakingDescription xs ++ [varSymBreakingDescription y]) ) ] diff --git a/src/Conjure/Language/Lenses.hs b/src/Conjure/Language/Lenses.hs index 53afe5bd4d..67be676c36 100644 --- a/src/Conjure/Language/Lenses.hs +++ b/src/Conjure/Language/Lenses.hs @@ -452,6 +452,24 @@ opTransform _ = ) +opQuickPermutationOrder + :: ( Op x :< x + , Pretty x + , MonadFailDoc m + ) + => Proxy (m :: T.Type -> T.Type) + -> ( [x] -> x -> x + , x -> m ([x], x) + ) +opQuickPermutationOrder _ = + ( \ x y -> inject $ MkOpQuickPermutationOrder $ OpQuickPermutationOrder x y + , \ p -> do + op <- project p + case op of + MkOpQuickPermutationOrder (OpQuickPermutationOrder x y) -> return (x,y) + _ -> na ("Lenses.opTransform:" <++> pretty p) + ) + opRelationProj :: ( Op x :< x , Pretty x diff --git a/src/Conjure/UI/Model.hs b/src/Conjure/UI/Model.hs index a79059bfb0..e5f7c29e56 100644 --- a/src/Conjure/UI/Model.hs +++ b/src/Conjure/UI/Model.hs @@ -2898,9 +2898,7 @@ addUnnamedSymmetryBreaking mode model = do combinedPermApply perms = case quickOrComplete of - USBQuick -> - let p = fromList perms - in [essence| quickPermutationOrder(&varsTuple, [&p]) |] + USBQuick -> make opQuickPermutationOrder perms varsTuple USBComplete -> let applied = buildPermutationChain perms varsTuple in [essence| &varsTuple .<= &applied |] From f6edc19cf465aa91ed4be30f126d907f2f059478 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?=C3=96zg=C3=BCr=20Akg=C3=BCn?= Date: Mon, 20 Jan 2025 16:28:25 +0000 Subject: [PATCH 228/229] fix symmetryOrdering for permutations - reflect that they are now represented using 2 functions --- .../Language/Expression/Op/QuickPermutationOrder.hs | 2 +- src/Conjure/Representations.hs | 2 +- src/Conjure/Representations/Combined.hs | 3 +-- .../Representations/Permutation/PermutationAsFunction.hs | 8 +++++--- 4 files changed, 8 insertions(+), 7 deletions(-) diff --git a/src/Conjure/Language/Expression/Op/QuickPermutationOrder.hs b/src/Conjure/Language/Expression/Op/QuickPermutationOrder.hs index dd3503e06f..a0767d59c0 100644 --- a/src/Conjure/Language/Expression/Op/QuickPermutationOrder.hs +++ b/src/Conjure/Language/Expression/Op/QuickPermutationOrder.hs @@ -41,7 +41,7 @@ instance SimplifyOp OpQuickPermutationOrder x where simplifyOp _ = na "simplifyOp{OpQuickPermutationOrder}" instance (Pretty x) => Pretty (OpQuickPermutationOrder x) where - prettyPrec _ (OpQuickPermutationOrder as b) = "quickPermutationOrder" <> prettyList prParens "," (as ++ [b]) + prettyPrec _ (OpQuickPermutationOrder as b) = "quickPermutationOrder" <> prettyListDoc prParens "," [prettyList prBrackets "," as, pretty b] instance (VarSymBreakingDescription x, ExpressionLike x) => VarSymBreakingDescription (OpQuickPermutationOrder x) where varSymBreakingDescription (OpQuickPermutationOrder xs y) = diff --git a/src/Conjure/Representations.hs b/src/Conjure/Representations.hs index 5496f29bc7..4f18c309e2 100644 --- a/src/Conjure/Representations.hs +++ b/src/Conjure/Representations.hs @@ -153,7 +153,7 @@ symmetryOrdering inp' = do TypeInt{} -> return [essence| [&inp] |] TypeList TypeInt{} -> return inp TypeMatrix TypeInt{} TypeInt{} -> return inp - _ -> do + _ -> case inp of -- Constant x -> so_onConstant x -- AbstractLiteral _ -> return inp diff --git a/src/Conjure/Representations/Combined.hs b/src/Conjure/Representations/Combined.hs index b3d1ad8c6e..1655443ca9 100644 --- a/src/Conjure/Representations/Combined.hs +++ b/src/Conjure/Representations/Combined.hs @@ -220,8 +220,7 @@ dispatch domain = do (bug "useLevels inside dispatch") _ -> nope DomainPermutation r _ _ -> case r of - Permutation_AsFunction -> permutationAsFunction dispatch - + Permutation_AsFunction -> permutationAsFunction dispatch _ -> nope _ -> nope diff --git a/src/Conjure/Representations/Permutation/PermutationAsFunction.hs b/src/Conjure/Representations/Permutation/PermutationAsFunction.hs index 419ecb20dd..d73702a406 100644 --- a/src/Conjure/Representations/Permutation/PermutationAsFunction.hs +++ b/src/Conjure/Representations/Permutation/PermutationAsFunction.hs @@ -179,6 +179,8 @@ permutationAsFunction dispatch = Representation chck downD structuralCons downC symmetryOrdering :: TypeOf_SymmetryOrdering m symmetryOrdering innerSO downX1 inp domain = do - [x] <- downX1 inp - Just [(_, xDomain)] <- downD ("SO", domain) - innerSO downX1 x xDomain + [x, y] <- downX1 inp + Just [(_, xDomain), (_, yDomain)] <- downD ("SO", domain) + xs <- innerSO downX1 x xDomain + ys <- innerSO downX1 y yDomain + return [essence| concatenate([&xs, &ys]) |] From 0ada345af22042ccd8746078a3b35437f1d48e4a Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?=C3=96zg=C3=BCr=20Akg=C3=BCn?= Date: Mon, 20 Jan 2025 16:28:35 +0000 Subject: [PATCH 229/229] test files --- .../0010_set_of_permutations_size_3/stdout.expected | 11 +++++++++++ .../0020_set_of_permutations_size_4/stdout.expected | 13 +++++++++++++ .../int/div/0004_enum_doesnt_work/stderr.expected | 4 ++-- .../int/max/0001_same_tags_work/stdout.expected | 2 +- .../int/max/0003_const_tagged_works/stdout.expected | 2 +- .../int/min/0001_same_tags_work/stdout.expected | 2 +- 6 files changed, 29 insertions(+), 5 deletions(-) diff --git a/tests/custom/permutations/20_counting/0010_set_of_permutations_size_3/stdout.expected b/tests/custom/permutations/20_counting/0010_set_of_permutations_size_3/stdout.expected index d10ebe7b59..99e4a29007 100644 --- a/tests/custom/permutations/20_counting/0010_set_of_permutations_size_3/stdout.expected +++ b/tests/custom/permutations/20_counting/0010_set_of_permutations_size_3/stdout.expected @@ -1 +1,12 @@ Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: conjure-output/model000001.eprime +Running minion for domain filtering. +Running solver: minion +Copying solution to: permutation.solution +language Essence 1.3 + +letting s be + {permutation(), permutation((1, 2)), permutation((1, 2, 3)), permutation((1, 3)), permutation((1, 3, 2)), + permutation((2, 3))} diff --git a/tests/custom/permutations/20_counting/0020_set_of_permutations_size_4/stdout.expected b/tests/custom/permutations/20_counting/0020_set_of_permutations_size_4/stdout.expected index d10ebe7b59..ac9b53f435 100644 --- a/tests/custom/permutations/20_counting/0020_set_of_permutations_size_4/stdout.expected +++ b/tests/custom/permutations/20_counting/0020_set_of_permutations_size_4/stdout.expected @@ -1 +1,14 @@ Generating models for permutation.essence +Generated models: model000001.eprime +Saved under: conjure-output +Savile Row: conjure-output/model000001.eprime +Running minion for domain filtering. +Running solver: minion +Copying solution to: permutation.solution +language Essence 1.3 + +letting s be + {permutation(), permutation((1, 2)), permutation((1, 2), (3, 4)), permutation((1, 2, 3)), + permutation((1, 2, 3, 4)), permutation((1, 2, 4)), permutation((1, 2, 4, 3)), permutation((1, 3)), + permutation((1, 3, 2)), permutation((1, 3, 4)), permutation((1, 3, 4, 2)), permutation((2, 3)), + permutation((2, 3, 4)), permutation((2, 4)), permutation((2, 4, 3)), permutation((3, 4))} diff --git a/tests/custom/permutations/22_tagged_ints/int/div/0004_enum_doesnt_work/stderr.expected b/tests/custom/permutations/22_tagged_ints/int/div/0004_enum_doesnt_work/stderr.expected index f8961b84bf..ce66cb3a67 100644 --- a/tests/custom/permutations/22_tagged_ints/int/div/0004_enum_doesnt_work/stderr.expected +++ b/tests/custom/permutations/22_tagged_ints/int/div/0004_enum_doesnt_work/stderr.expected @@ -1,6 +1,6 @@ Error: - In a 'such that' statement: x = 6 / 3 + In a 'such that' statement: x = 6:X / 3:X Error: - When type checking: 6 / 3 + When type checking: 6:X / 3:X First argument expected to be an int, but it is: enum:X cat: conjure-output/*.solution: No such file or directory diff --git a/tests/custom/permutations/22_tagged_ints/int/max/0001_same_tags_work/stdout.expected b/tests/custom/permutations/22_tagged_ints/int/max/0001_same_tags_work/stdout.expected index 862adac5da..713814557d 100644 --- a/tests/custom/permutations/22_tagged_ints/int/max/0001_same_tags_work/stdout.expected +++ b/tests/custom/permutations/22_tagged_ints/int/max/0001_same_tags_work/stdout.expected @@ -7,5 +7,5 @@ Running solver: minion Copying solution to: permutation.solution language Essence 1.3 -letting t be {4} +letting t be {4:A} letting x be 4 diff --git a/tests/custom/permutations/22_tagged_ints/int/max/0003_const_tagged_works/stdout.expected b/tests/custom/permutations/22_tagged_ints/int/max/0003_const_tagged_works/stdout.expected index 9cfd56db52..b11ce86e51 100644 --- a/tests/custom/permutations/22_tagged_ints/int/max/0003_const_tagged_works/stdout.expected +++ b/tests/custom/permutations/22_tagged_ints/int/max/0003_const_tagged_works/stdout.expected @@ -7,4 +7,4 @@ Running solver: minion Copying solution to: permutation.solution language Essence 1.3 -letting t be {3} +letting t be {3:A} diff --git a/tests/custom/permutations/22_tagged_ints/int/min/0001_same_tags_work/stdout.expected b/tests/custom/permutations/22_tagged_ints/int/min/0001_same_tags_work/stdout.expected index 862adac5da..713814557d 100644 --- a/tests/custom/permutations/22_tagged_ints/int/min/0001_same_tags_work/stdout.expected +++ b/tests/custom/permutations/22_tagged_ints/int/min/0001_same_tags_work/stdout.expected @@ -7,5 +7,5 @@ Running solver: minion Copying solution to: permutation.solution language Essence 1.3 -letting t be {4} +letting t be {4:A} letting x be 4